smalltalk-3.2.5/0000755000175000017500000000000012130456010010476 500000000000000smalltalk-3.2.5/tests/0000755000175000017500000000000012130456006011645 500000000000000smalltalk-3.2.5/tests/intmath.st0000644000175000017500000001522612123404352013606 00000000000000"====================================================================== | | Test integer math | | ======================================================================" "====================================================================== | | Copyright (C) 1988, 1989, 1999, 2007, 2008 Free Software Foundation. | Written by Steve Byrne | | This file is part of GNU Smalltalk. | | GNU Smalltalk is free software; you can redistribute it and/or modify it | under the terms of the GNU General Public License as published by the Free | Software Foundation; either version 2, or (at your option) any later version. | | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS | FOR A PARTICULAR PURPOSE. See the GNU General Public License for more | details. | | You should have received a copy of the GNU General Public License along with | GNU Smalltalk; see the file COPYING. If not, write to the Free Software | Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. | ======================================================================" Eval [ 3 ] Eval [ -3 ] "Base tests" Eval [ 2r1010 ] Eval [ 8r377 ] Eval [ 16rFE ] "Arithmetic operation tests" Eval [ 3 + 4 ] "should return 7" Eval [ 3 - 4 ] "should return -1" Eval [ 3 < 4 ] "should return true" Eval [ 17 > 18 ] "should return false" Eval [ 17 > 17 ] "should return false" Eval [ 23 <= 23 ] "true" Eval [ 23 <= -45 ] "false" Eval [ 18 >= 21 ] "false" Eval [ 19 >= 18 ] "true" Eval [ 23 = 23 ] "true" Eval [ 23 = 24 ] "false" Eval [ 45 ~= 89 ] "true" Eval [ 45 ~= 45 ] "false" Eval [ 3 * 4 ] "should return 12" Eval [ 12 // 3 ] "should return 4" Eval [ 12 // 5 ] "should return 2" Eval [ -12 // -3 ] "should return 4" Eval [ -12 // -5 ] "should return 2" Eval [ -12 // 5 ] "should return -3" Eval [ 12 // -5 ] "should return -3" Eval [ 12 \\ 3 ] "should return 0" Eval [ 12 \\ 5 ] "should return 2" Eval [ -12 \\ -3 ] "should return 0" Eval [ -12 \\ -5 ] "should return -2" Eval [ -12 \\ 5 ] "should return 3" Eval [ 12 \\ -5 ] "should return -3" "LargeIntegers" Eval [ (1000000000 raisedToInteger: 4) printString ] Eval [ 100 factorial / 99 factorial ] "should return 100 of course" Eval [ 100 factorial printString ] Eval [ (SmallInteger largest + SmallInteger largest) > 0 ] Eval [ (SmallInteger largest - SmallInteger smallest) > 0 ] Eval [ SmallInteger smallest negated > 0 ] Eval [ (40000 * 40000) = (40000 * 40000) ] Eval [ (40000 * 40000) < (40000 * 40000) ] Eval [ (40000 * 40000) <= (40000 * 40000) ] Eval [ (40000 * 40000) > (40000 * 40000) ] Eval [ (40000 * 40000) >= (40000 * 40000) ] Eval [ (40000 * 40000) = (32000 * 32000) ] Eval [ (40000 * 40000) < (32000 * 32000) ] Eval [ (40000 * 40000) <= (32000 * 32000) ] Eval [ (40000 * 40000) > (32000 * 32000) ] Eval [ (40000 * 40000) >= (32000 * 32000) ] Eval [ (34567 * 34567) = (45678 * 45678) ] Eval [ (34567 * 34567) < (45678 * 45678) ] Eval [ (34567 * 34567) <= (45678 * 45678) ] Eval [ (34567 * 34567) > (45678 * 45678) ] Eval [ (34567 * 34567) >= (45678 * 45678) ] Eval [ (4000000000 * 4000000000) = (4000000000 * 4000000000) ] Eval [ (4000000000 * 4000000000) < (4000000000 * 4000000000) ] Eval [ (4000000000 * 4000000000) <= (4000000000 * 4000000000) ] Eval [ (4000000000 * 4000000000) > (4000000000 * 4000000000) ] Eval [ (4000000000 * 4000000000) >= (4000000000 * 4000000000) ] Eval [ (4000000000 * 4000000000) = (1600000000 * 1600000000) ] Eval [ (4000000000 * 4000000000) < (1600000000 * 1600000000) ] Eval [ (4000000000 * 4000000000) <= (1600000000 * 1600000000) ] Eval [ (4000000000 * 4000000000) > (1600000000 * 1600000000) ] Eval [ (4000000000 * 4000000000) >= (1600000000 * 1600000000) ] Eval [ (3456734567 * 3456734567) = (4567845678 * 4567845678) ] Eval [ (3456734567 * 3456734567) < (4567845678 * 4567845678) ] Eval [ (3456734567 * 3456734567) <= (4567845678 * 4567845678) ] Eval [ (3456734567 * 3456734567) > (4567845678 * 4567845678) ] Eval [ (3456734567 * 3456734567) >= (4567845678 * 4567845678) ] "parsing in bases other than 10" Eval [ 16rFFFFFFFF = 4294967295 ] Eval [ n _ 10. f _ n factorial. f1 _ f * (n+1). n timesRepeat: [f1 _ f1 - f]. (f1 - f = 0) printNl. n timesRepeat: [f1 _ f1 + f]. ((f1 // f) = (n+1)) printNl. ^f1 negated negated = f1 ] "Check normalization and conversion to/from SmallInts" Eval [ ^(SmallInteger largest + 1 - 1) == SmallInteger largest ] Eval [ ^(SmallInteger largest + 3 - 6) == (SmallInteger largest - 3) ] Eval [ ^(SmallInteger smallest - 1 + 1) == SmallInteger smallest ] Eval [ ^(SmallInteger smallest - 3 + 6) == (SmallInteger smallest + 3) ] Eval [ | bits | 'Shift -1 left then right and test for -1' printNl. bits := (1 to: 100) collect: [ :i | -1 bitShift: i ]. bits keysAndValuesDo: [:i :n | (n bitShift: i negated) = -1 ifFalse: [^i]]. 'Shift 1 left then right and test for 1' printNl. bits := (1 to: 100) collect: [ :i | 1 bitShift: i ]. bits keysAndValuesDo: [:i :n | (n bitShift: i negated) = 1 ifFalse: [^i]]. 'And a single bit with -1 and test for same value' printNl. bits keysAndValuesDo: [:i :n | (n bitAnd: -1) = n ifFalse: [^i]]. 'Verify that (n bitAnd: n negated) = n' printNl. bits keysAndValuesDo: [:i :n | (n bitAnd: n negated) = n ifFalse: [^i]]. 'Verify that (n + n complemented) = -1' printNl. bits keysAndValuesDo: [:i :n | (n + n bitInvert) = -1 ifFalse: [^i]]. 'Verify that n negated = (n complemented +1)' printNl. bits keysAndValuesDo: [:i :n | n bitInvert + 1 = n negated ifFalse: [^i]]. 'LargeInteger bit logic tests passed' printNl. ^true ] Fraction class extend [ test: n [ | sum time | sum := 0. 1 to: n do: [ :x | sum := sum + 1 / x ]. ^sum ] ] Eval [ | sum | sum := Fraction test: 20. "Try 100 or 200..." sum numerator printNl. sum denominator printNl. ^sum ] "Another fraction torture test" Stream subclass: PiSeries [ | i s tot | PiSeries class >> new [ ^super new initialize ] initialize [ i := 1. s := 4. tot := 4 ] next [ ^tot := tot + ((s := 0 - s) / (i := i + 2)) ] ] Stream extend [ accelerate [ ^Generator on: [ :gen | |s0 s1 s2| s0 := self next. s1 := self next. [ s2 := self next. gen yield: s2 - ((s2 - s1) squared / (s0 - s1 - s1 + s2)). s0 := s1. s1 := s2] repeat] ] ] Eval [ g := PiSeries new. 7 timesRepeat: [ g := g accelerate ]. pi := g peek. pi numerator size printNl. pi denominator size printNl. (pi * 100000) asInteger ] smalltalk-3.2.5/tests/pools.ok0000644000175000017500000000107312130343734013260 00000000000000 Execution begins... returned value is 42 Execution begins... returned value is 42 Execution begins... returned value is 42 Execution begins... returned value is 21 Execution begins... returned value is #Exception Execution begins... returned value is 9994 Execution begins... returned value is 'MyLibrary 1.0' Execution begins... returned value is 6667 Execution begins... returned value is Blah Execution begins... returned value is 785 Execution begins... returned value is 'MyLibrary.Foo' Execution begins... returned value is 'MyProject.MyLibWrapper.Baz' smalltalk-3.2.5/tests/AnsiInit.st0000644000175000017500000001415312123404352013656 00000000000000"====================================================================== | | Attribute protocols to existing Smalltalk classes | | This file is in the public domain. | ======================================================================" | dict | dict := Dictionary new. dict at: 'Fundamental' put: #( ('ANY' ('Object') 'inst' 'NoTst') ('Object' ('Object') 'inst' 'UT') ('nil' ('UndefinedObject') 'inst' 'UT') ('boolean' ('Boolean') 'inst' 'UT') ('Character' ('Character') 'inst' 'UT') "StdGbl" ('Character factory' ('Character') 'class' 'UT') ('failedMessage' ('Message') 'inst' 'UT') ('selector' ('Symbol') 'inst' 'UT') ('classDescription' ('ClassDescription') 'inst' 'NoTst') ('instantiator' ('Object') 'class' 'NoTst') ('Object class' ('Object') 'class' 'UT') "StdGbl" ). dict at: 'Valuable' put: #( ('valuable' ('BlockClosure') 'inst' 'NoTst') ('niladicValuable' ('BlockClosure') 'inst' 'NoTst') ('niladicBlock' ('BlockClosure') 'inst' 'UT') ('monadicValuable' ('BlockClosure') 'inst' 'NoTst') ('monadicBlock' ('BlockClosure') 'inst' 'UT') ('dyadicValuable' ('BlockClosure') 'inst' 'UT') ). dict at: 'Exception' put: #( ('exceptionDescription' ('Exception') 'inst' 'NoTst') ('exceptionSignaler' ('Exception') 'inst' 'NoTst') ('exceptionBuilder' ('Exception') 'inst' 'NoTst') ('signaledException' ('Exception') 'inst' 'NoTst') ('exceptionSelector' ('Exception') 'class' 'NoTst') ('exceptionInstantiator' ('Exception') 'class' 'NoTst') ('Exception class' ('Exception') 'class' 'UT') "StdGbl" ('Exception' ('Exception') 'inst' 'UT') ('Notification class' ('Notification') 'class' 'UT') "StdGbl" ('Notification' ('Notification') 'inst' 'UT') ('Warning class' ('Warning') 'class' 'UT') "StdGbl" ('Warning' ('Warning') 'inst' 'UT') ('Error class' ('Error') 'class' 'UT') "StdGbl" ('Error' ('Error') 'inst' 'UT') ('ZeroDivide factory' ('ZeroDivide') 'class' 'UT') "StdGbl" ('ZeroDivide' ('ZeroDivide') 'inst' 'UT') ('MessageNotUnderstoodSelector' ('MessageNotUnderstood') 'class' 'UT') ('MessageNotUnderstood' ('MessageNotUnderstood') 'inst' 'UT') "StdGbl" ('exceptionSet' ('ExceptionSet') 'inst' 'UT') ). dict at: 'Numeric' put: #( ('magnitude' ('Magnitude') 'inst' 'NoTst') ('number' ('Number') 'inst' 'NoTst') "StdGbl" ('rational' ('Fraction' 'Integer') 'inst' 'NoTst') ('Fraction' ('Fraction') 'inst' 'UT') ('integer' ('Integer') 'inst' 'UT') "StdGbl" ('scaledDecimal' ('ScaledDecimal') 'inst' 'UT') "StdGbl" ('Float' ('Float') 'inst' 'UT') ('floatCharacterization' ('Float') 'class' 'UT') "StdGbl" ('Fraction factory' ('Fraction') 'class' 'UT') "StdGbl" ). dict at: 'Collection' put: #( ('collection' ('Collection') 'inst' 'NoTst') ('abstractDictionary' ('Dictionary') 'inst' 'NoTst') ('Dictionary' ('Dictionary') 'inst' 'UT') ('IdentityDictionary' ('IdentityDictionary') 'inst' 'UT') ('extensibleCollection' ('Bag' 'OrderedCollection' 'Set' 'String') 'inst' 'NoTst') ('Bag' ('Bag') 'inst' 'UT') ('Set' ('Set') 'inst' 'UT') ('sequencedReadableCollection' ('SequenceableCollection') 'inst' 'NoTst') ('Interval' ('Interval') 'inst' 'UT') ('readableString' ('String') 'inst' 'NoTst') ('symbol' ('Symbol') 'inst' 'UT') "StdGbl" ('sequencedCollection' ('SequenceableCollection') 'inst' 'NoTst') ('String' ('String') 'inst' 'UT') ('Array' ('Array') 'inst' 'UT') ('ByteArray' ('ByteArray') 'inst' 'UT') ('sequencedContractibleCollection' ('SequenceableCollection') 'inst' 'NoTst') ('SortedCollection' ('SortedCollection') 'inst' 'UT') ('OrderedCollection' ('OrderedCollection') 'inst' 'UT') ('Interval factory' ('Interval') 'class' 'UT') "StdGbl" ('collection factory' ('Collection') 'class' 'NoTst') ('Dictionary factory' ('Dictionary') 'class' 'UT') "StdGbl" ('IdentityDictionary factory' ('IdentityDictionary') 'class' 'UT') "StdGbl" ('initializableCollection factory' ('ArrayedCollection' 'Bag' 'OrderedCollection' 'Set') 'class' 'NoTst') ('Array factory' ('Array') 'class' 'UT') "StdGbl" ('Bag factory' ('Bag') 'class' 'UT') "StdGbl" ('ByteArray factory' ('ByteArray') 'class' 'UT') "StdGbl" ('OrderedCollection factory' ('OrderedCollection') 'class' 'UT') "StdGbl" ('Set factory' ('Set') 'class' 'UT') "StdGbl" ('SortedCollection factory' ('SortedCollection') 'class' 'UT') "StdGbl" ('String factory' ('String') 'class' 'UT') "StdGbl" ). dict at: 'Date and Time' put: #( ('DateAndTime' ('DateTime') 'inst' 'UT') ('Duration' ('Duration') 'inst' 'UT') ('Duration factory' ('Duration') 'class' 'UT') "StdGbl" ('DateAndTime factory' ('DateTime') 'class' 'UT') "StdGbl" ). dict at: 'Stream' put: #( ('sequencedStream' ('PositionableStream') 'inst' 'NoTst') ('gettableStream' ('PositionableStream') 'inst' 'NoTst') ('collectionStream' ('PositionableStream') 'inst' 'NoTst') ('puttableStream' ('WriteStream') 'inst' 'NoTst') ('ReadStream' ('ReadStream') 'inst' 'UT') ('WriteStream' ('WriteStream') 'inst' 'UT') ('ReadWriteStream' ('ReadWriteStream') 'inst' 'UT') "('Transcript' ('Transcript') 'class' 'UT') ???StdGbl?? ?? ??? Transcript is instance of TranscriptStream ???" ('ReadStream factory' ('ReadStream') 'class' 'UT') "StdGbl" ('ReadWriteStream factory' ('ReadWriteStream') 'class' 'UT') "StdGbl" ('WriteStream factory' ('WriteStream') 'class' 'UT') "StdGbl" ). dict at: 'File Stream' put: #( ('FileStream' ('FileStream') 'inst' 'NoTst') ('readFileStream' ('FileStream') 'inst' 'UT') ('writeFileStream' ('FileStream') 'inst' 'UT') ('FileStream factory' ('FileStream') 'class' 'UT') "StdGbl" ). dict keysAndValuesDo: [ :protocolGroupName :groupProtocols | groupProtocols do: [ :protocolClassesIsCls || protocol class side | protocol := protocolClassesIsCls at: 1. class := protocolClassesIsCls at: 2. side := protocolClassesIsCls at: 3. "Gosh, how awful a test is this!" class := class select: [ :each || symbol | (Symbol hasInterned: each ifTrue: [ :sym | symbol := sym ]) and: [ (Smalltalk classAt: symbol ifAbsent: [ nil ]) notNil ] ]. 1 protocolManager wrkAssocProtocolNamed: protocol asSymbol toClassesNamed: class isClassSideProtocol: side = 'class' ] ]! smalltalk-3.2.5/tests/cobjects.ok0000644000175000017500000000533512123404352013721 00000000000000 Execution begins... returned value is 'asd' Execution begins... returned value is 'asd' Execution begins... returned value is nil Execution begins... returned value is CString new: 1 "<0>" Execution begins... returned value is 'asd' Execution begins... returned value is 'dsa' Execution begins... returned value is CString Execution begins... returned value is 'asd' Execution begins... returned value is 'dsa' Execution begins... returned value is CArray Execution begins... returned value is 'asd' Execution begins... returned value is 'dsa' Execution begins... returned value is 1 Execution begins... returned value is nil Execution begins... returned value is 'asd' Execution begins... returned value is 'dsa' Execution begins... returned value is CString Execution begins... returned value is 'asd' Execution begins... returned value is 'dsa' Execution begins... returned value is CString Execution begins... returned value is 'asd' Execution begins... returned value is 'dsa' Execution begins... returned value is 1 Execution begins... error: Invalid argument #int returned value is nil Execution begins... abc3def4 returned value is 9 Execution begins... cobjects.st:96: Attempt to pass an instance of String as a ... cobjects.st:96: Attempt to pass an instance of String as a ... error: primitive operation failed returned value is nil Execution begins... Marli loves Steve!!! Marli loves Steve!!! Marli loves Steve!!! returned value is 3 Execution begins... true 'abcabc' 'this is a test' result = 7.700000 returned value is true Execution begins... The string is this is a test returned value is nil Execution begins... Getting a long long 0x100110012002 returned value is '17596749520898' Execution begins... returned value is 'this is a test' Execution begins... returned value is StructB Execution begins... returned value is StructB Execution begins... 8 4369 8738 ByteArray (0 0 17 17 34 34 51 51 ) error: Invalid argument 8: offset out of range returned value is nil Execution begins... error: Invalid argument -1: offset out of range returned value is nil Execution begins... error: Invalid argument 7: offset out of range returned value is nil Execution begins... 4369 error: Invalid argument 8: offset out of range returned value is nil Execution begins... returned value is true Execution begins... CInt(0 0 0 0 0 0 0 0 @ 8) error: Invalid argument 8: offset out of range returned value is nil Execution begins... ByteArray (0 0 0 0 65 0 0 0 ) returned value is ByteArray new: 8 "<0>" Execution begins... 'abc' 'abc' 'def' returned value is CPtr new: 1 "<0>" Execution begins... 1 2 3 returned value is nil Execution begins... $1 $2 $3 $<0> returned value is nil Execution begins... true returned value is nil smalltalk-3.2.5/tests/strcat.ok0000644000175000017500000000006312123404352013416 00000000000000 Execution begins... 60000 returned value is 60000 smalltalk-3.2.5/tests/methcall.st0000644000175000017500000000362212123404352013730 00000000000000"====================================================================== | | Benchmark for message sending | | ======================================================================" "====================================================================== | | Copyright (C) 2003, 2007, 2008 Free Software Foundation. | Written by Paolo Bonzini | | This file is part of GNU Smalltalk. | | GNU Smalltalk is free software; you can redistribute it and/or modify it | under the terms of the GNU General Public License as published by the Free | Software Foundation; either version 2, or (at your option) any later version. | | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS | FOR A PARTICULAR PURPOSE. See the GNU General Public License for more | details. | | You should have received a copy of the GNU General Public License along with | GNU Smalltalk; see the file COPYING. If not, write to the Free Software | Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. | ======================================================================" ValueHolder extend [ activate [ self value: self value not ] ] ValueHolder subclass: NthValueHolder [ | counter maxCounter | maxCounter: anInteger [ maxCounter := anInteger ] value: anObject [ super value: anObject. counter := 0 ] activate [ (counter := counter + 1) >= maxCounter ifTrue: [ super activate ] ] ] Eval [ n := Smalltalk arguments isEmpty ifTrue: [ 100000 ] ifFalse: [ 1 max: Smalltalk arguments first asInteger ]. val := true. toggle := ValueHolder with: val. n timesRepeat: [ val := toggle activate value ]. val displayNl. val := true. ntoggle := NthValueHolder with: val. ntoggle maxCounter: 3. n timesRepeat: [ val := ntoggle activate value ]. val displayNl ] smalltalk-3.2.5/tests/classes.ok0000644000175000017500000000613312123404352013557 00000000000000 Execution begins... returned value is Array new: 5 "<0>" Execution begins... returned value is Array Execution begins... returned value is Metaclass Execution begins... returned value is Metaclass class Execution begins... returned value is Metaclass Execution begins... returned value is Object Execution begins... returned value is Object class Execution begins... returned value is Metaclass Execution begins... returned value is nil Execution begins... returned value is UndefinedObject Execution begins... returned value is true Execution begins... returned value is True Execution begins... returned value is Rambo Execution begins... returned value is Rambo new "<0>" Execution begins... returned value is nil Execution begins... returned value is nil Execution begins... returned value is nil Execution begins... returned value is nil Execution begins... returned value is nil Execution begins... returned value is nil Execution begins... returned value is 10 Execution begins... returned value is 7 Execution begins... returned value is 3 Execution begins... returned value is Rambo new "<0>" Execution begins... returned value is 'junior' Execution begins... returned value is 'squeeky' Execution begins... returned value is 'junior' Execution begins... returned value is 'squeeky' Execution begins... returned value is 'squeeky' Execution begins... returned value is 'junior' Execution begins... returned value is nil Execution begins... returned value is nil Execution begins... returned value is 15 Execution begins... returned value is 12 Execution begins... returned value is 3 Execution begins... returned value is 'zoneball' Execution begins... returned value is #theJumaSymbol Execution begins... returned value is Rocky new "<0>" Execution begins... returned value is 'frisky' Execution begins... returned value is 'radar' Execution begins... returned value is 'frisky' Execution begins... returned value is 'radar' Execution begins... returned value is 'radar' Execution begins... returned value is Rambo class Execution begins... returned value is nil Execution begins... returned value is 5 Execution begins... returned value is nil Execution begins... returned value is 5 Execution begins... returned value is 15 Execution begins... error: Invalid value 9whammo: invalid Smalltalk identifier returned value is nil Execution begins... error: Invalid value dog!,blammo: invalid Smalltalk identifier returned value is nil Execution begins... returned value is 2 Execution begins... returned value is 34 Execution begins... returned value is 34 Execution begins... returned value is 3 Execution begins... returned value is 34 Execution begins... returned value is 34 Execution begins... returned value is 2 Execution begins... returned value is 12 Execution begins... returned value is 12 Execution begins... returned value is 34 Execution begins... returned value is 34 Execution begins... returned value is 3 Execution begins... returned value is 12 Execution begins... returned value is 12 Execution begins... returned value is 34 Execution begins... returned value is 34 smalltalk-3.2.5/tests/AnsiRun.st0000644000175000017500000000312212123404352013511 00000000000000"====================================================================== | | Driver for the ANSI-compliancy tests | | ======================================================================" "====================================================================== | | Copyright (C) 2000 Free Software Foundation. | Written by Paolo Bonzini | | This file is part of GNU Smalltalk. | | GNU Smalltalk is free software; you can redistribute it and/or modify it | under the terms of the GNU General Public License as published by the Free | Software Foundation; either version 2, or (at your option) any later version. | | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS | FOR A PARTICULAR PURPOSE. See the GNU General Public License for more | details. | | You should have received a copy of the GNU General Public License along with | GNU Smalltalk; see the file COPYING. If not, write to the Free Software | Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. | ======================================================================" FloatANSITest isClass ifFalse: [ ObjectMemory quit: 1 ]! Smalltalk arguments do: [ :each || results | results := (Smalltalk at: each asSymbol) suite run. Transcript showCr: ('%1: %2' % { each. results }). results failureCount > 0 ifTrue: [ results failures printNl ]. results errorCount > 0 ifTrue: [ results errors printNl ]. results correctCount < results runCount ifTrue: [ ObjectMemory quit: 1 ] ]. ObjectMemory quit! smalltalk-3.2.5/tests/classes.st0000644000175000017500000001443112123404352013574 00000000000000"====================================================================== | | Test the class hierarchy | | ======================================================================" "====================================================================== | | Copyright (C) 1988, 1989, 1999, 2007, 2008 Free Software Foundation. | Written by Steve Byrne | | This file is part of GNU Smalltalk. | | GNU Smalltalk is free software; you can redistribute it and/or modify it | under the terms of the GNU General Public License as published by the Free | Software Foundation; either version 2, or (at your option) any later version. | | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS | FOR A PARTICULAR PURPOSE. See the GNU General Public License for more | details. | | You should have received a copy of the GNU General Public License along with | GNU Smalltalk; see the file COPYING. If not, write to the Free Software | Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. | ======================================================================" Eval [ Array new: 5 ] Eval [ Array ] Eval [ Metaclass ] "should be Metaclass" Eval [ Metaclass class ] Eval [ Metaclass class class ] "should be Metaclass, since the metaclass of metaclass is a metaclass" Eval [ Object ] Eval [ Object class ] "should be Object class" Eval [ Object class class ] "should be MetaClass" Eval [ nil ] Eval [ nil class ] Eval [ true ] Eval [ true class ] "Test creating classes at runtime I apologize for the apparent lack of professionalism in the choice of variable and method names here." Eval [ Object subclass: #Rambo instanceVariableNames: 'foo bar' classVariableNames: 'guinea pigs' poolDictionaries: '' category: '' ] !Rambo methodsFor: 'test'! "Assign some instance variables and return a result" ramboTest foo := 3. bar := 7. ^foo + bar ! "Assign to class variables" initPigs: guineaArg and: pigsArg guinea := guineaArg. pigs := pigsArg ! "inspect instance variables" foof ^foo ! barf ^bar ! "inspect class variables" returnGuinea ^guinea ! returnPigs ^pigs ! ! Eval [ Smalltalk at: #testVar put: (Rambo new) ] Eval [ testVar foof ] "should be nil (it hasn't been initialized)" Eval [ testVar barf ] "should be nil (it hasn't been initialized)" Eval [ testVar returnGuinea ] "should be nil (it hasn't been initialized)" Eval [ testVar returnPigs ] "should be nil (it hasn't been initialized)" Eval [ Rambo new returnPigs ] "should be nil" Eval [ Rambo new returnGuinea ] "should be nil" Eval [ testVar ramboTest ] "should be 10" Eval [ testVar barf ] "should now be set to 7" Eval [ testVar foof ] "should new be set to 3" Eval [ testVar initPigs: 'squeeky' and: 'junior' ] "nil is returned, we just set some global variables" Eval [ testVar returnPigs ] "should return 'junior'" Eval [ testVar returnGuinea ] "should return 'squeeky'" "Test that class variables really affect all instances" Eval [ Rambo new returnPigs ] "all instances now return 'junior'" Eval [ Rambo new returnGuinea ] "all instances now return 'squeeky'" "Create a subclass of a created class to test variable and method inheritance" Rambo subclass: #Rocky instanceVariableNames: 'quem juma' classVariableNames: '' poolDictionaries: '' category: ''! !Rocky methodsFor: 'test'! ramboTest foo := 12. bar := 3. ^foo + bar ! quem: arg quem := arg ! quem ^quem ! juma: arg juma := arg ! juma ^juma ! ! Eval [ Rocky new returnGuinea ] "should return 'squeeky' by inheritance" Eval [ Rocky new returnPigs ] "should return 'junior' by inheritance" Eval [ Rocky new quem ] "should return nil (not initialized)" Eval [ Rocky new juma ] "should return nil (not initialized)" "Test overriding of methods" Eval [ (testVar := Rocky new) ramboTest ] "should return 15, and set some inst vars" "Set the instance variables" testVar quem: 'zoneball'. testVar juma: #theJumaSymbol! Eval [ testVar foof ] "should return 12" Eval [ testVar barf ] "should return 3" Eval [ testVar quem ] "should return 'zoneball'" Eval [ testVar juma ] "should return #theJumaSymbol" "Test setting class variables from subclass" Eval [ (Rocky new) initPigs: 'frisky' and: 'radar' ] "should return instance of Rocky" "+++ work in tests involving Dudley (Milkdud) and Speedy too+++" "Test subclass access to class variables" Eval [ Rocky new returnGuinea ] "should return 'frisky'" Eval [ Rocky new returnPigs ] "should return 'radar'" "Test class access to class variables that were modified from subclass" Eval [ Rambo new returnGuinea ] "should return 'frisky'" Eval [ Rambo new returnPigs ] "should return 'radar'" "Make sure that the existing instance also sees the change in class vars" Eval [ testVar returnPigs ] "should return 'radar'" "test of class instance varialbes" Eval [ Rambo class instanceVariableNames: 'fred' ] !Rambo class methodsFor: 'testing'! put: x fred := x. ! get ^fred ! ! Eval [ Rambo get ] Eval [ Rambo put: 5. Rambo get ] Eval [ Rocky get ] Eval [ Rocky put: 15. Rambo get ] Eval [ Rocky get ] "Test out parsing bad instance variable names" Eval [ Rambo instanceVariableNames: 'd99ogABCRblammo 9whammo loser! dogbert++' ] Eval [ Rambo instanceVariableNames: 'dog!,blammo whammo? loser! dogbert++' ] "Test mutation" Eval [ (Object subclass: #AB) instanceVariableNames: 'a'. (AB subclass: #C) instanceVariableNames: 'c'; createGetMethod: 'c'; createSetMethod: 'c'. cObj := C new. cObj c: 34. Smalltalk at: #TestObj put: cObj. ^C instSize ] Eval [ ^TestObj c ] Eval [ ^TestObj instVarAt: 2 ] Eval [ AB instanceVariableNames: 'a b'; createGetMethod: 'b'; createSetMethod: 'b'. ^C instSize ] Eval [ ^TestObj c ] Eval [ ^TestObj instVarAt: 3 ] Eval [ TestObj b: 12. AB instanceVariableNames: 'b'. ^C instSize ] Eval [ ^TestObj b ] Eval [ ^TestObj instVarAt: 1 ] Eval [ ^TestObj c ] Eval [ ^TestObj instVarAt: 2 ] Eval [ AB instanceVariableNames: 'b a'. ^C instSize ] Eval [ ^TestObj b ] Eval [ ^TestObj instVarAt: 1 ] Eval [ ^TestObj c ] Eval [ ^TestObj instVarAt: 3 ] smalltalk-3.2.5/tests/objects.ok0000644000175000017500000000137512123404352013556 00000000000000 Execution begins... a finalized b finalized, surviving c finalized b finalized returned value is ObjectsTest Execution begins... returned value is true Execution begins... ('abc' an Object nil nil 1 ) ('abc' an Object nil nil 1 ) ('abc' nil nil nil 1 ) ('abc' nil nil nil 1 ) (true false true true true ) (true true true true true ) (true false true true true ) returned value is Array new: 5 "<0>" Execution begins... New instance of Behavior created Superclass assigned First method compiled Second method compiled Instance created 'test message' an {Object} Well it seems to work fine returned value is TextCollector new "<0>" Execution begins... returned value is 2 Execution begins... 'a' returned value is 'b' Execution begins... 5 returned value is 5 smalltalk-3.2.5/tests/AnsiDB.st0000644000175000017500000162523212123404352013247 00000000000000"====================================================================== | | ANSI Protocols database | | This file is in the public domain. | ======================================================================" (1 protocolManager newProtocolNamed: #'abstractDictionary' conformsToProtocolNames: #(#'collection') ) protocolDescription: ' Provides protocol for accessing, adding, removing, and iterating over the elements of an unordered collection whose elements are accessed using an explicitly assigned external key. Glossary Entries ' ! 1 protocolManager newMessagePattern: 'addAll: dictionary' forProtocolNamed: #'abstractDictionary' synopsis: 'Store the elements of dictionary in the receiver at the corresponding keys from dictionary. ' definedIn: 'abstractDictionary' definition: 'This message is equivalent to repeatedly sending the #at:put: message to the receiver with each of the keys and elements in dictionary in turn. If a key in dictionary is key equivalent to a key in the receiver, the associated element in dictionary replaces the element in the receiver. ' refinedIn: '' refinement: '' parameters: #( #('dictionary' 'abstractDictionary' #'unspecified') ) returnValues: #() errors: '' ! 1 protocolManager newMessagePattern: 'at: key' forProtocolNamed: #'abstractDictionary' synopsis: 'Answer the element at key in the receiver. ' definedIn: 'abstractDictionary' definition: 'This message defines element lookup based on a key. Answer the element stored at key. Lookup is successful if an element has been previously stored in the receiver at a key that is key equivalent to key. This element is answered. Specifically, the following expression must return true for all appropriate bindings of dictionary, key, and value: dictionary at: key put: value. ^(dictionary at: key) == value The result is undefined if the receiver does not contain an element keyed by key or if the key is nil. ' refinedIn: '' refinement: '' parameters: #( #('key' 'Object' #'uncaptured') ) returnValues: #( #( 'Object' #'state') ) errors: '' ! 1 protocolManager newMessagePattern: 'at: key ifAbsent: operation' forProtocolNamed: #'abstractDictionary' synopsis: 'Answer the element at key in the receiver. If key lookup for key fails, then answer the result of evaluating operation. ' definedIn: 'abstractDictionary' definition: 'Answer the element stored at the specified key if key lookup is successful. If the key lookup fails, answer the result of evaluating operation with no parameters. The result is undefined if the key is nil. ' refinedIn: '' refinement: '' parameters: #( #('key' 'Object' #'uncaptured') #('operation' 'niladicValuable' #'uncaptured') ) returnValues: #( #( 'ANY' #'unspecified') #( 'Object' #'state') ) errors: '' ! 1 protocolManager newMessagePattern: 'at: key ifAbsentPut: operation' forProtocolNamed: #'abstractDictionary' synopsis: 'Answer the element at key in the receiver. If key lookup for key fails, then store and return the result of evaluating operation. ' definedIn: 'abstractDictionary' definition: 'This message is the same as the #at: message if key lookup is successful. If the key lookup fails, the result of evaluating operation with no parameters is added at key and answered. The result is undefined if the key is nil. ' refinedIn: '' refinement: '' parameters: #( #('key' 'Object' #'unspecified') #('operation' 'niladicValuable' #'uncaptured') ) returnValues: #( #( 'Object' #'state') ) errors: '' ! 1 protocolManager newMessagePattern: 'at: newElement put: key' forProtocolNamed: #'abstractDictionary' synopsis: 'Store newElement at key in the receiver. Answer newElement. ' definedIn: 'abstractDictionary' definition: 'If lookup succeeds for key, then newElement replaces the element previously stored at key. Otherwise, the newElement is stored at the new key. In either case, subsequent successful lookups for key will answer newElement. Answer newElement. The result is undefined if the key is nil. ' refinedIn: '' refinement: '' parameters: #( #('newElement' 'Object' #'captured') #('key' 'Object' #'unspecified') ) returnValues: #( #( 'Object' #'state') ) errors: '' ! 1 protocolManager newMessagePattern: 'collect: transformer' forProtocolNamed: #'abstractDictionary' synopsis: 'Answer a new collection constructed by gathering the results of evaluating transformer with each element of the receiver. ' definedIn: 'collection' definition: 'For each element of the receiver, transformer is evaluated with the element as the parameter. The results of these evaluations are collected into a new collection. The elements are traversed in the order specified by the #do: message for the receiver. Unless specifically refined, this message is defined to answer an object conforming to the same protocol as the receiver. ' refinedIn: 'abstractDictionary' refinement: 'Answer a new instance of the receiver''s type with the same keys. For each key of the answer, a new element is obtained by evaluating transformer with the corresponding element of the receiver as the parameter. ' parameters: #( #('transformer' 'monadicValuable' #'uncaptured') ) returnValues: #( #( 'abstractDictionary' #'new') ) errors: 'If the elements of the receiver are inappropriate for use as arguments to transformer. If the result of evaluating the transformer does not conform to any element type restrictions of the collection to be returned. ' ! 1 protocolManager newMessagePattern: 'includesKey: key' forProtocolNamed: #'abstractDictionary' synopsis: 'Answer true if the receiver contains an element stored at key. Answer false otherwise. ' definedIn: 'abstractDictionary' definition: 'Answer true if the key lookup for the key succeeds. Answer false otherwise. The result is undefined if the key is nil. ' refinedIn: '' refinement: '' parameters: #( #('key' 'Object' #'uncaptured') ) returnValues: #( #( 'boolean' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'keyAtValue: value' forProtocolNamed: #'abstractDictionary' synopsis: 'Answer a key such that the element stored at this key is equal to value. Answer nil if no such key is found. ' definedIn: 'abstractDictionary' definition: 'Answer an object such that key lookup with this object will answer an element in the receiver equivalent to value. Note that if there are multiple elements in the receiver that are equivalent to value, then the one whose key is answered is arbitrary. The result is undefined if the receiver does not contain an element equivalent to value. ' refinedIn: '' refinement: '' parameters: #( #('value' 'Object' #'uncaptured') ) returnValues: #( #( 'Object' #'state') ) errors: '' ! 1 protocolManager newMessagePattern: 'keyAtValue: operation ifAbsent: value' forProtocolNamed: #'abstractDictionary' synopsis: 'Answer a key such that the element stored at this key is equivalent to value. Answer the result of evaluating operation if no such key is found. ' definedIn: 'abstractDictionary' definition: 'Answer an object such that key lookup with this object will answer an element in the receiver equivalent to value. If no element equivalent to value is found, then the result of evaluating operation with no parameters is answered. ' refinedIn: '' refinement: '' parameters: #( #('value' 'Object' #'uncaptured') #('operation' 'niladicValuable' #'uncaptured') ) returnValues: #( #( 'ANY' #'unspecified') #( 'Object' #'state') ) errors: '' ! 1 protocolManager newMessagePattern: 'keys' forProtocolNamed: #'abstractDictionary' synopsis: 'Answer a collection of keys at which there is an element stored in the receiver. ' definedIn: 'abstractDictionary' definition: 'Answer a collection of all the keys in the receiver. The size of the result is equal to the size of the receiver. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'collection' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'keysAndValuesDo: operation' forProtocolNamed: #'abstractDictionary' synopsis: 'Iteratively evaluate operation with each of the receiver''s keys and values. ' definedIn: 'abstractDictionary' definition: 'For each element in the receiver, operation is evaluated with the corresponding key as the first argument and the element as the second argument. The order in which the elements are traversed is not specified. Each key is visited exactly once. ' refinedIn: '' refinement: '' parameters: #( #('operation' 'dyadicValuable' #'uncaptured') ) returnValues: #() errors: 'If any of the keys or values are not appropriate as an argument to operation. ' ! 1 protocolManager newMessagePattern: 'keysDo: operation' forProtocolNamed: #'abstractDictionary' synopsis: 'Iteratively evaluate operation with each of the receiver''s keys at which there are elements stored. ' definedIn: 'abstractDictionary' definition: 'For each key in the receiver, operation is evaluated with the key used as the parameter. The order in which the elements are traversed is not specified. Each key is visited exactly once. ' refinedIn: '' refinement: '' parameters: #( #('operation' 'monadicValuable' #'uncaptured') ) returnValues: #() errors: 'If any of the keys are not appropriate as an argument to operation. ' ! 1 protocolManager newMessagePattern: 'reject: discriminator' forProtocolNamed: #'abstractDictionary' synopsis: 'Answer a new collection which excludes the elements in the receiver which cause discriminator to evaluate to true. ' definedIn: 'collection' definition: 'For each element of the receiver, discriminator is evaluated with the element as the parameter. Each element which causes discriminator to evaluate to false is added to the new collection. The elements are traversed in the order specified by the #do: message for the receiver. Unless specifically refined, this message is defined to answer an object conforming to the same protocol as the receiver. ' refinedIn: 'abstractDictionary' refinement: 'For each key of the receiver, discriminator is evaluated with the corresponding element as the parameter. If the element causes discriminator to evaluate to false, the key is added to the answer with the element as its corresponding value. ' parameters: #( #('discriminator' 'monadicValuable' #'uncaptured') ) returnValues: #( #( 'abstractDictionary' #'new') ) errors: 'If the elements of the receiver are inappropriate for use as arguments to discriminator. If discriminator evaluates to an object that does not conform to the protocol for any element of the receiver. ' ! 1 protocolManager newMessagePattern: 'removeAllKeys: keys' forProtocolNamed: #'abstractDictionary' synopsis: 'Remove any elements from the receiver which are stored at the keys specified in keys. ' definedIn: 'abstractDictionary' definition: 'This message has the same effect on the receiver as repeatedly sending the #removeKey: message for each element in keys. The result is undefined if duplicate keys, as defined by key equivalence, are in the keys or if any element in keys is not a valid key of the receiver. ' refinedIn: '' refinement: '' parameters: #( #('keys' 'collection' #'uncaptured') ) returnValues: #() errors: '' ! 1 protocolManager newMessagePattern: 'removeAllKeys: operation ifAbsent: keys' forProtocolNamed: #'abstractDictionary' synopsis: 'Remove any elements from the receiver which are stored at the keys specified in keys. For any element in keys which is not a valid key of the receiver, evaluate operation with that element as the argument, but do not stop the enumeration. ' definedIn: 'abstractDictionary' definition: 'This message has the same effect on the receiver as repeatedly sending the #removeKey:ifAbsent: message for each element in keys. If any element in keys is not a valid key of the receiver, evaluate operation with that element as the parameter and continue the enumeration. ' refinedIn: '' refinement: '' parameters: #( #('keys' 'collection' #'uncaptured') #('operation' 'monadicValuable' #'uncaptured') ) returnValues: #() errors: 'If any element of keys is not a valid key of the receiver and inappropriate for use as an argument to the operation. ' ! 1 protocolManager newMessagePattern: 'removeKey: key' forProtocolNamed: #'abstractDictionary' synopsis: 'Remove the element which is stored at key in the receiver. Answer the removed element. ' definedIn: 'abstractDictionary' definition: 'This message defines removal of a key from the receiver. If key lookup for key is successful, then both key and its corresponding element are removed. Answer the removed element. The result is undefined if the receiver does not contain an element keyed by key. The result is undefined if the key is nil. ' refinedIn: '' refinement: '' parameters: #( #('key' 'Object' #'uncaptured') ) returnValues: #( #( 'Object' #'state') ) errors: '' ! 1 protocolManager newMessagePattern: 'removeKey: operation ifAbsent: key' forProtocolNamed: #'abstractDictionary' synopsis: 'Remove the element which is stored at key in the receiver and answer the removed element. Answer the result of evaluating operation if no such key is found in the receiver. ' definedIn: 'abstractDictionary' definition: 'If key lookup for key is successful, then both key and its corresponding element are removed. Answer the removed element. If the key lookup fails, the result of evaluating operation with no parameters is answered. The result is undefined if the key is nil. ' refinedIn: '' refinement: '' parameters: #( #('operation' 'niladicValuable' #'uncaptured') #('key' 'Object' #'uncaptured') ) returnValues: #( #( 'ANY' #'unspecified') #( 'Object' #'state') ) errors: '' ! 1 protocolManager newMessagePattern: 'select: discriminator' forProtocolNamed: #'abstractDictionary' synopsis: 'Answer a new collection which contains the elements in the receiver which cause discriminator to evaluate to true. ' definedIn: 'collection' definition: 'For each element of the receiver, discriminator is evaluated with the element as the parameter. Each element which causes discriminator to evaluate to true is added to the new collection. The elements are traversed in the order specified by the #do: message for the receiver. Unless specifically refined, this message is defined to answer an object conforming to the same protocol as the receiver. ' refinedIn: 'abstractDictionary' refinement: 'For each key of the receiver, discriminator is evaluated with the element as the parameter. If element causes discriminator to evaluate to true, the key is added to the answer with value element. If discriminator evaluates to an object that does not conform to the protocol for any element of the receiver. ' parameters: #( #('discriminator' 'monadicValuable' #'uncaptured') ) returnValues: #( #( 'abstractDictionary' #'new') ) errors: 'If the elements of the receiver are inappropriate for use as arguments to discriminator. ' ! 1 protocolManager newMessagePattern: 'values' forProtocolNamed: #'abstractDictionary' synopsis: 'Answer a collection of the receiver''s elements. ' definedIn: 'abstractDictionary' definition: 'Answer a collection of the receiver''s elements. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'sequencedReadableCollection' #'unspecified') ) errors: '' ! (1 protocolManager newProtocolNamed: #'Array' conformsToProtocolNames: #(#'sequencedCollection') ) protocolDescription: ' Represents a keyed collection of objects which can be accessed externally using sequential integer keys. The index of the first element is one (1). ' ! (1 protocolManager newProtocolNamed: #'Array factory' conformsToProtocolNames: #(#'initializableCollection factory') ) protocolDescription: ' This protocol defines the behavior of objects that can be used to create objects that conform to . These objects are created with a specified size. If element values are not explicitly provided they default to nil. Standard Globals Array Conforms to the protocol . Its language element type is unspecified. This is a factory and discriminator for collections that conform to . ' ! 1 protocolManager newMessagePattern: 'new' forProtocolNamed: #'Array factory' synopsis: 'Create a new object. ' definedIn: 'instantiator' definition: 'Return a newly created object initialized to a standard initial state. ' refinedIn: 'Array factory' refinement: 'Create a new that contains no elements. ' parameters: #() returnValues: #( #( 'Array' #'new') ) errors: '' ! 1 protocolManager newMessagePattern: 'new: count' forProtocolNamed: #'Array factory' synopsis: 'Create a new collection. The parameter count constrains the number of elements in the result. ' definedIn: 'collection factory' definition: 'Return a new collection that has space for at least count elements. Conforming protocols may refine this message. In particular, the effect of the parameter count should be specified in refinements. It can be used to specify the exact number of elements, the minimum number, or in some cases can even be interpreted as a hint from the programmer, with no guarantee that the requested number of instance variables will actually be allocated. Unless otherwise stated the initial values of elements of the new instance of the receiver are unspecified. ' refinedIn: 'Array factory' refinement: 'The parameter count specifies the size of the receiver. The initial value of each element of the new instance of the receiver is nil. The new collections conforms to the protocol . ' parameters: #( #('count' 'integer' #'unspecified') ) returnValues: #( #( 'Array' #'new') ) errors: 'count<0 ' ! 1 protocolManager newMessagePattern: 'with: element1' forProtocolNamed: #'Array factory' synopsis: 'Create a collection initially containing the argument element. ' definedIn: 'initializableCollection factory' definition: 'Return a new collection containing one element. Conforming protocols may impose restrictions on the value of the argument and hence the element type. ' refinedIn: 'Array factory' refinement: 'The first argument is at index position 1 ' parameters: #( #('element1' 'Object' #'captured') ) returnValues: #( #( 'Array' #'new') ) errors: 'If the argument does not meet the element type constraints of the result object ' ! 1 protocolManager newMessagePattern: 'with: element1 with: element2' forProtocolNamed: #'Array factory' synopsis: 'Create a collection initially containing the argument elements. ' definedIn: 'initializableCollection factory' definition: 'Return a new collection containing two of elements. The collection contains the arguments as its elements. Conforming protocols may impose restrictions on the values of the arguments and hence the element types. ' refinedIn: 'Array factory' refinement: 'The first argument is at index position 1, the second argument is at index position 2. ' parameters: #( #('element1' 'Object' #'captured') #('element2' 'Object' #'captured') ) returnValues: #( #( 'Array' #'new') ) errors: 'If any of the arguments do not meet the element type constraints of the result object ' ! 1 protocolManager newMessagePattern: 'with: element1 with: element2 with: element3' forProtocolNamed: #'Array factory' synopsis: 'Create a collection initially containing the argument elements. ' definedIn: 'initializableCollection factory' definition: 'Return a new collection containing three elements. The collection contains the arguments as its elements. Conforming protocols may impose restrictions on the values of the arguments and hence the element types. ' refinedIn: 'Array factory' refinement: 'The first argument is at index position 1, the second argument is at index position 2, and so on... ' parameters: #( #('element1' 'Object' #'captured') #('element2' 'Object' #'captured') #('element3' 'Object' #'captured') ) returnValues: #( #( 'Array' #'new') ) errors: 'If any of the arguments do not meet the element type constraints of the result object ' ! 1 protocolManager newMessagePattern: 'with: element4 with: element1 with: element3 with: element2' forProtocolNamed: #'Array factory' synopsis: 'Create a collection initially containing the argument elements. ' definedIn: 'initializableCollection factory' definition: 'Return a new collection containing four elements. The collection contains the arguments as its elements. Conforming protocols may impose restrictions on the values of the arguments and hence the element types. ' refinedIn: 'Array factory' refinement: 'The first argument is at index position 1, the second argument is at index position 2, and so on... ' parameters: #( #('element3' 'Object' #'captured') #('element2' 'Object' #'captured') #('element4' 'Object' #'captured') #('element1' 'Object' #'captured') ) returnValues: #( #( 'Array' #'new') ) errors: 'If any of the arguments do not meet the element type constraints of the result object ' ! 1 protocolManager newMessagePattern: 'withAll: newElements' forProtocolNamed: #'Array factory' synopsis: 'Create a collection containing only the elements of newElements. ' definedIn: 'initializableCollection factory' definition: 'Return a new collection whose elements are the elements of newElements. Conforming protocols may impose restrictions on the values of newElements. ' refinedIn: 'Array factory' refinement: 'If the elements of newElements are ordered then their ordering establishing their index positions in the new collection. ' parameters: #( #('newElements' 'collection' #'unspecified') ) returnValues: #( #( 'Array' #'new') ) errors: 'If any of the elements of newElements do not meet the element type constraints of the result object ' ! (1 protocolManager newProtocolNamed: #'Bag' conformsToProtocolNames: #(#'extensibleCollection') ) protocolDescription: ' Represents an unordered, variable sized collection whose elements can be added or removed, but cannot be individually accessed by external keys. A bag is similar to a set but can contain duplicate elements. Elements are duplicates if they are equivalent. ' ! 1 protocolManager newMessagePattern: 'add: newElement' forProtocolNamed: #'Bag' synopsis: 'Add newElement to the receiver''s elements. ' definedIn: 'extensibleCollection' definition: 'This message adds a newElement to the receiver. Unless specifically refined, the position of the newElement in the element traversal order is unspecified. Conformant protocols may place restrictions on the type of objects that are valid elements. Unless otherwise specified, any object is acceptable. ' refinedIn: 'Bag' refinement: 'The result is undefined if newElement is nil. ' parameters: #( #('newElement' 'Object' #'captured') ) returnValues: #() errors: '' ! 1 protocolManager newMessagePattern: 'add: newElement withOccurrences: count' forProtocolNamed: #'Bag' synopsis: 'Add newElement count times to the receiver''s elements. ' definedIn: 'Bag' definition: 'This message adds an element to the receiver multiple times. The operation is equivalent to adding newElement to the receiver count times using the #add: message with newElement as the parameter. The result is undefined if newElement is nil. ' refinedIn: '' refinement: '' parameters: #( #('newElement' 'Object' #'captured') #('count' 'integer' #'unspecified') ) returnValues: #() errors: '' ! 1 protocolManager newMessagePattern: 'addAll: newElements' forProtocolNamed: #'Bag' synopsis: 'Add each element of newElements to the receiver''s elements. ' definedIn: 'extensibleCollection' definition: 'This message adds each element of newElements to the receiver. The operation is equivalent to adding each element of newElements to the receiver using the #add: message with the element as the parameter. The newElements are traversed in the order specified by the #do: message for newElements. ' refinedIn: 'Bag' refinement: 'The result is undefined if newElements contains nil. The traversal order is unspecified. ' parameters: #( #('newElements' 'collection' #'uncaptured') ) returnValues: #() errors: '' ! 1 protocolManager newMessagePattern: 'collect: transformer' forProtocolNamed: #'Bag' synopsis: 'Answer a new collection constructed by gathering the results of evaluating transformer with each element of the receiver. ' definedIn: 'collection' definition: 'For each element of the receiver, transformer is evaluated with the element as the parameter. The results of these evaluations are collected into a new collection. The elements are traversed in the order specified by the #do: message for the receiver. Unless specifically refined, this message is defined to answer an objects conforming to the same protocol as the receiver. ' refinedIn: 'Bag' refinement: 'The result is undefined if transformer evaluates to nil for any element of the receiver. ' parameters: #( #('transformer' 'monadicValuable' #'uncaptured') ) returnValues: #( #( 'Bag' #'new') ) errors: 'If the elements of the receiver are inappropriate for use as arguments to transformer. If the result of evaluating the transformer does not conform to any element type restrictions of the collection to be returned. ' ! (1 protocolManager newProtocolNamed: #'Bag factory' conformsToProtocolNames: #(#'initializableCollection factory') ) protocolDescription: ' This protocol defines the behavior of objects that can be used to create objects that conform to the protocol . Standard Globals Bag Conforms to the protocol . Its language element type is unspecified. This is a factory and discriminator for collections that conform to . ' ! 1 protocolManager newMessagePattern: 'new' forProtocolNamed: #'Bag factory' synopsis: 'Create a new object. ' definedIn: 'instantiator' definition: 'Return a newly created object initialized to a standard initial state. ' refinedIn: 'Bag factory' refinement: 'Return a new that is optimized to store an implementation defined number of elements. The new collection initially contains no elements. ' parameters: #() returnValues: #( #( 'Bag' #'new') ) errors: '' ! 1 protocolManager newMessagePattern: 'new: count' forProtocolNamed: #'Bag factory' synopsis: 'Create a new collection. The parameter count constrains the number of elements in the result. ' definedIn: 'collection factory' definition: 'Return a new collection that has space for at least count elements. Conforming protocols may refine this message. In particular, the effect of the parameter count should be specified in refinements. It can be used to specify the exact number of elements, the minimum number, or in some cases can even be interpreted as a hint from the programmer, with no guarantee that the requested number of instance variables will actually be allocated. Unless otherwise stated the initial values of elements of the new instance of the receiver are unspecified. ' refinedIn: 'Bag factory' refinement: 'The parameter count represents a hint to the implementation as to the likely number of elements that may be added to the new collection. The new collection initially contains no elements. The new collections conforms to the protocol . ' parameters: #( #('count' 'integer' #'unspecified') ) returnValues: #( #( 'Bag' #'new') ) errors: '' ! 1 protocolManager newMessagePattern: 'with: element1' forProtocolNamed: #'Bag factory' synopsis: 'Create a collection initially containing one element. ' definedIn: 'initializableCollection factory' definition: 'Return a new collection containing one element. The collection contains the argument as its element. Conforming protocols may impose restrictions on the values of the argument and hence the element type. ' refinedIn: 'Bag factory' refinement: 'The result is undefined if the argument is nil. ' parameters: #( #('element1' 'Object' #'captured') ) returnValues: #( #( 'Bag' #'new') ) errors: 'If the argument does not meet the element type constraints of the result object ' ! 1 protocolManager newMessagePattern: 'with: element2 with: element1' forProtocolNamed: #'Bag factory' synopsis: 'Create a collection initially containing the argument elements. ' definedIn: 'initializableCollection factory' definition: 'Return a new collection containing two elements. The collection contains the arguments as its elements. Conforming protocols may impose restrictions on the values of the arguments and hence the element types. ' refinedIn: 'Bag factory' refinement: 'The result is undefined if any of the arguments are nil. ' parameters: #( #('element2' 'Object' #'captured') #('element1' 'Object' #'captured') ) returnValues: #( #( 'Bag' #'new') ) errors: 'If any of the arguments do not meet the element type constraints of the result object ' ! 1 protocolManager newMessagePattern: 'with: element1 with: element2 with: element3' forProtocolNamed: #'Bag factory' synopsis: 'Create a collection initially containing the argument elements. ' definedIn: 'initializableCollection factory' definition: 'Return a new collection containing three elements. The collection contains the arguments as its elements. Conforming protocols may impose restrictions on the values of the arguments and hence the element types. ' refinedIn: 'Bag factory' refinement: 'The result is undefined if any of the arguments are nil. ' parameters: #( #('element1' 'Object' #'captured') #('element2' 'Object' #'captured') #('element3' 'Object' #'captured') ) returnValues: #( #( 'Bag' #'new') ) errors: 'If any of the arguments do not meet the element type constraints of the result object ' ! 1 protocolManager newMessagePattern: 'with: element2 with: element4 with: element1 with: element3' forProtocolNamed: #'Bag factory' synopsis: 'Create a collection initially containing the argument elements. ' definedIn: 'initializableCollection factory' definition: 'Return a new collection containing four elements. The collection contains the arguments as its elements. Conforming protocols may impose restrictions on the values of the arguments and hence the element types. ' refinedIn: 'Bag factory' refinement: 'The result is undefined if any of the arguments are nil. ' parameters: #( #('element1' 'Object' #'captured') #('element3' 'Object' #'captured') #('element2' 'Object' #'captured') #('element4' 'Object' #'captured') ) returnValues: #( #( 'Bag' #'new') ) errors: 'If any of the arguments do not meet the element type constraints of the result object ' ! 1 protocolManager newMessagePattern: 'withAll: newElements' forProtocolNamed: #'Bag factory' synopsis: 'Create a collection containing only the elements of newElements. ' definedIn: 'initializableCollection factory' definition: 'Return a new collection whose elements are the elements of newElements. Conforming protocols may impose restrictions on the values of newElements. ' refinedIn: 'Bag factory' refinement: 'The result is unspecified if newElements contains nil. ' parameters: #( #('newElements' 'collection' #'unspecified') ) returnValues: #( #( 'Bag' #'new') ) errors: 'If any of the elements of newElements do not meet the element type constraints of the result object ' ! (1 protocolManager newProtocolNamed: #'boolean' conformsToProtocolNames: #(#'Object') ) protocolDescription: ' This protocol describes the behavior of the objects that are the values of the reserved identifiers "true" and "false". These objects are identity objects. Several message specifications include a truth table describing the result of the binary operation implemented by that message. In each table, the value of the receiver is used to locate a row and the value of the argument is used to locate a column, the result being located at the intersection of the row and column. ' ! 1 protocolManager newMessagePattern: '& operand' forProtocolNamed: #'boolean' synopsis: 'Logical and - Boolean conjunction. ' definedIn: 'boolean' definition: 'Return the Boolean conjunction of the receiver and operand. The value returned is determined by the following truth table: & true false true true false false false false ' refinedIn: '' refinement: '' parameters: #( #('operand' 'boolean' #'uncaptured') ) returnValues: #( #( 'boolean' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'and: operand' forProtocolNamed: #'boolean' synopsis: '"Short circuit" logical and. ' definedIn: 'boolean' definition: 'If the receiver is false, return false. Otherwise, return the result of sending the message #value to operand. The result is undefined if the result of sending #value to operand is not a . Rationale Some existing implementations do not require that the operand must evaluate to a . The message #ifTrue: should be used to conditionally evaluate a block that does not return a . ' refinedIn: '' refinement: '' parameters: #( #('operand' 'niladicBlock' #'uncaptured') ) returnValues: #( #( 'boolean' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'eqv: operand' forProtocolNamed: #'boolean' synopsis: 'Boolean equivalence. ' definedIn: 'boolean' definition: 'Return the Boolean disjunction of the receiver and operand. The value returned is determined by the following truth table: eqv: true false true true false false false true ' refinedIn: '' refinement: '' parameters: #( #('operand' 'boolean' #'uncaptured') ) returnValues: #( #( 'boolean' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'ifFalse: operand' forProtocolNamed: #'boolean' synopsis: 'Evaluate the argument if receiver is false. ' definedIn: 'boolean' definition: 'If the receiver is false return the result of sending the message #value to operand. The return value is unspecified if the receiver is true. Rationale Most existing implementations define the return value to be nil if the receiver is true. This definition is less precise and potentially allows for implementation specific optimization. ' refinedIn: '' refinement: '' parameters: #( #('operand' 'niladicBlock' #'uncaptured') ) returnValues: #( #( 'ANY' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'ifFalse: trueOperand ifTrue: falseOperand' forProtocolNamed: #'boolean' synopsis: 'Selectively evaluate one of the arguments. ' definedIn: 'boolean' definition: 'If the receiver is false return the result return the result as if the message #value was sent to falseOperand, otherwise return the result as if the message #value was sent to trueOperand. ' refinedIn: '' refinement: '' parameters: #( #('falseOperand' 'niladicBlock' #'uncaptured') #('trueOperand' 'niladicBlock' #'uncaptured') ) returnValues: #( #( 'ANY' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'ifTrue: operand' forProtocolNamed: #'boolean' synopsis: 'Evaluate the argument if the receiver is true. ' definedIn: 'boolean' definition: 'If the receiver is true, return the result of sending the message #value to operand. The return value is unspecified if the receiver is false. Rationale Most existing implementations define the return value to be nil if the receiver is false. This definition is less precise and potentially allows for implementation specific optimization. ' refinedIn: '' refinement: '' parameters: #( #('operand' 'niladicBlock' #'uncaptured') ) returnValues: #( #( 'ANY' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'ifTrue: trueOperand ifFalse: falseOperand' forProtocolNamed: #'boolean' synopsis: 'Selectively evaluate one of the arguments. ' definedIn: 'boolean' definition: 'If the receiver is true return the result of sending the message #value to trueOperand, otherwise return the result of sending #value to the falseOperand. ' refinedIn: '' refinement: '' parameters: #( #('trueOperand' 'niladicBlock' #'uncaptured') #('falseOperand' 'niladicBlock' #'uncaptured') ) returnValues: #( #( 'ANY' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'not' forProtocolNamed: #'boolean' synopsis: 'Logical not - Boolean negation. ' definedIn: 'boolean' definition: 'Return the Boolean negation of the receiver. If the receiver is true the return value is false, if the receiver is false the return value is true. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'boolean' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'or: operand' forProtocolNamed: #'boolean' synopsis: '"Short circuit" logical or. ' definedIn: 'boolean' definition: 'If the receiver is true, return true. Otherwise, return the Boolean result of sending the message #value to operand. The result is undefined if the result of sending #value to operand is not a . Rationale Some existing implementations do not require that the operand must evaluate to a . The message #ifFalse: should be used to conditionally evaluate a block that does not return a Boolean. ' refinedIn: '' refinement: '' parameters: #( #('operand' 'niladicValuable' #'uncaptured') ) returnValues: #( #( 'boolean' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'printString' forProtocolNamed: #'boolean' synopsis: 'Return a string that describes the receiver. ' definedIn: 'Object' definition: 'A string consisting of a sequence of characters that describe the receiver are returned as the result. The exact sequence of characters that describe an object are implementation defined. ' refinedIn: 'boolean' refinement: 'If the receiver is true, return a string with the same characters as the string ''true'', otherwise return a string with the same characters as the string ''false''. ' parameters: #() returnValues: #( #( 'readableString' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'xor: operand' forProtocolNamed: #'boolean' synopsis: 'Boolean exclusive or. ' definedIn: 'boolean' definition: 'Return the Boolean exclusive or of the receiver and operand. The value returned is determined by the following truth table: xor: true false true false true false true false ' refinedIn: '' refinement: '' parameters: #( #('operand' 'boolean' #'uncaptured') ) returnValues: #( #( 'boolean' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: '| operand' forProtocolNamed: #'boolean' synopsis: 'Logical or - Boolean disjunction. ' definedIn: 'boolean' definition: 'Return the Boolean disjunction of the receiver and operand. The value returned is determined by the following truth table: | true false true true true false true false ' refinedIn: '' refinement: '' parameters: #( #('operand' 'boolean' #'uncaptured') ) returnValues: #( #( 'boolean' #'unspecified') ) errors: '' ! (1 protocolManager newProtocolNamed: #'ByteArray' conformsToProtocolNames: #(#'sequencedCollection') ) protocolDescription: ' Represents a keyed collection whose element type is and is limited to the range 0 to 255, inclusive. The elements can be accessed externally using sequential integer keys. The index of the first element is one (1). ' ! (1 protocolManager newProtocolNamed: #'ByteArray factory' conformsToProtocolNames: #(#'initializableCollection factory') ) protocolDescription: ' This protocol defines the behavior of objects that can be used to create objects that conform to . These objects are created with a specified size. If the element values are not explicitly provided, they default to 0. Standard Globals ByteArray Conforms to the protocol . Its language element type is unspecified. This is a factory and discriminator for collections that conform to . ' ! 1 protocolManager newMessagePattern: 'new' forProtocolNamed: #'ByteArray factory' synopsis: 'Create a new object. ' definedIn: 'instantiator' definition: 'Return a newly created object initialized to a standard initial state. ' refinedIn: 'ByteArray factory' refinement: 'Create a new that contains no elements. ' parameters: #() returnValues: #( #( 'ByteArray' #'new') ) errors: '' ! 1 protocolManager newMessagePattern: 'new: count' forProtocolNamed: #'ByteArray factory' synopsis: 'Create a new collection. The parameter count constrains the number of elements in the result. ' definedIn: 'collection factory' definition: 'Return a new collection that has space for at least count elements. Conforming protocols may refine this message. In particular, the effect of the parameter count should be specified in refinements. It can be used to specify the exact number of elements, the minimum number, or in some cases can even be interpreted as a hint from the programmer, with no guarantee that the requested number of instance variables will actually be allocated. Unless otherwise stated the initial values of elements of the new instance of the receiver are unspecified. ' refinedIn: 'ByteArray factory' refinement: 'The parameter count specifies the size of the receiver. The initial value of each element of the new instance of the receiver is 0. The new collections conforms to the protocol . ' parameters: #( #('count' 'integer' #'unspecified') ) returnValues: #( #( 'ByteArray' #'new') ) errors: 'count<0 ' ! 1 protocolManager newMessagePattern: 'with: element1' forProtocolNamed: #'ByteArray factory' synopsis: 'Create a collection initially containing the argument element. ' definedIn: 'initializableCollection factory' definition: 'Return a new collection containing one element. The collection contains the argument as its elements. Conforming protocols may impose restrictions on the value of the argument and hence the element type. ' refinedIn: 'ByteArray factory' refinement: 'The argument is at index position 1. ' parameters: #( #('element1' 'integer' #'captured') ) returnValues: #( #( 'ByteArray' #'new') ) errors: 'If the argument does not meet the element type constraints of the result object ' ! 1 protocolManager newMessagePattern: 'with: element1 with: element2' forProtocolNamed: #'ByteArray factory' synopsis: 'Create a collection initially containing the argument elements. ' definedIn: 'initializableCollection factory' definition: 'Return a new collection containing two elements. he collection contains the arguments as its elements. Conforming protocols may impose restrictions on the values of the arguments and hence the element types. ' refinedIn: 'ByteArray factory' refinement: 'The first argument is at index position 1, the second argument is at index position 2. ' parameters: #( #('element1' 'integer' #'captured') #('element2' 'integer' #'captured') ) returnValues: #( #( 'ByteArray' #'new') ) errors: 'If any of the arguments do not meet the element type constraints of the result object ' ! 1 protocolManager newMessagePattern: 'with: element1 with: element3 with: element2' forProtocolNamed: #'ByteArray factory' synopsis: 'Create a collection initially containing the argument elements. ' definedIn: 'initializableCollection factory' definition: 'Return a new collection containing three elements. The collection contains the arguments as its elements. Conforming protocols may impose restrictions on the values of the arguments and hence the element types. ' refinedIn: 'ByteArray factory' refinement: 'The first argument is at index position 1, the second argument is at index position 2, and so on... ' parameters: #( #('element1' 'integer' #'captured') #('element3' 'integer' #'captured') #('element2' 'integer' #'captured') ) returnValues: #( #( 'ByteArray' #'new') ) errors: 'If any of the arguments do not meet the element type constraints of the result object ' ! 1 protocolManager newMessagePattern: 'with: element4 with: element2 with: element1 with: element3' forProtocolNamed: #'ByteArray factory' synopsis: 'Create a collection initially containing the argument elements. ' definedIn: 'initializableCollection factory' definition: 'Return a new collection containing four elements. The collection contains the arguments as its elements. Conforming protocols may impose restrictions on the values of the arguments and hence the element types. ' refinedIn: 'ByteArray factory' refinement: 'The first argument is at index position 1, the second argument is at index position 2, and so on... ' parameters: #( #('element1' 'integer' #'captured') #('element3' 'integer' #'captured') #('element4' 'integer' #'captured') #('element2' 'integer' #'captured') ) returnValues: #( #( 'ByteArray' #'new') ) errors: 'If any of the arguments do not meet the element type constraints of the result object ' ! 1 protocolManager newMessagePattern: 'withAll: newElements' forProtocolNamed: #'ByteArray factory' synopsis: 'Create a collection containing only the elements of newElements. ' definedIn: 'initializableCollection factory' definition: 'Return a new collection whose elements are the elements of newElements. Conforming protocols may impose restrictions on the values of newElements. ' refinedIn: 'ByteArray factory' refinement: 'If the elements of newElements are ordered then their ordering establishing their index positions in the new collection. ' parameters: #( #('newElements' 'collection' #'unspecified') ) returnValues: #( #( 'ByteArray' #'new') ) errors: 'If any of the elements of newElements do not meet the element type constraints of the result object ' ! (1 protocolManager newProtocolNamed: #'Character' conformsToProtocolNames: #(#'Object') ) protocolDescription: ' This protocol describes the behavior that is common to character objects. Character objects serve as the element value for Smalltalk strings. The Smalltalk language provides a literal syntax for character objects. Character objects represent individual elements of an implementation defined execution character set whose individual elements are identified by integer values. These integers are called code points. Each character object has an associated code point. It is unspecified whether or not each code point is uniquely associated with a unique character object. The execution character set is the character set used by an implementation during execution of a Smalltalk program. It need not be the same as the character set used by that implementation to encode the definition of Smalltalk programs. ' ! 1 protocolManager newMessagePattern: '= comparand' forProtocolNamed: #'Character' synopsis: 'Object equivalence test. ' definedIn: 'Object' definition: 'This message tests whether the receiver and the comparand are equivalent objects at the time the message is processed. Return true if the receiver is equivalent to comparand. Otherwise return false. The meaning of "equivalent" cannot be precisely defined but the intent is that two objects are considered equivalent if they can be used interchangeably. Conforming protocols may choose to more precisely define the meaning of "equivalent". The value of receiver = comparand is true if and only if the value of comparand = receiver would also be true. If the value of receiver = comparand is true then the receiver and comparand must have equivalent hash values. Or more formally: receiver = comparand ? receiver hash = comparand hash The equivalence of objects need not be temporally invariant. Two independent invocations of #= with the same receiver and operand objects may not always yield the same results. Note that a collection that uses #= to discriminate objects may only reliably store objects whose hash values do not change while the objects are contained in the collection. ' refinedIn: 'Character' refinement: 'Two characters are considered equivalent if they have the same code point. In other words character1 = character2 is true if and only if character1 codePoint = character2 codePoint is also true. ' parameters: #( #('comparand' 'Character' #'uncaptured') ) returnValues: #( #( 'boolean' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'asLowercase' forProtocolNamed: #'Character' synopsis: 'Return a character which is equivalent to the lowercase representation of the receiver. ' definedIn: 'Character' definition: 'If the receiver is equal to the value of a character literal in the "receiver" row of the following table, the result object must be equal to the value of the corresponding character literal in the "result" row. receiver $A $B $C $D $E $F $G $H $I $J $K $L $M $N $O $P $Q $R $S $T $U $V $W $X $Y $Z result $a $b $c $d $e $f $g $h $i $j $k $l $m $n $o $p $q $r $s $t $u $v $w $x $y $z An implemention may define other #asLowercase mappings. If the receiver does not correspond to a character in the "receiver" row of the table and does not have an implementation defined mapping the receiver is returned as the result. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'Character' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'asString' forProtocolNamed: #'Character' synopsis: 'Return a new string whose sole element is equivalent to the receiver. ' definedIn: 'Character' definition: 'Return a new string of size one (1) whose sole element is equivalent to the receiver. The new string is created using the same constraints as defined by the #new: message defined in . It is unspecified whether the resulting string captures a reference to the receiver. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'String' #'new') ) errors: '' ! 1 protocolManager newMessagePattern: 'asUppercase' forProtocolNamed: #'Character' synopsis: 'Return a character equivalent to the uppercase representation of the receiver. ' definedIn: 'Character' definition: 'If the receiver is equal to the value of a character literal in the "receiver" row of the following table, the result object must be equal to the value of the corresponding character literal in the "result" row. receiver $a $b $c $d $e $f $g $h $i $j $k $l $m $n $o $p $q $r $s $t $u $v $w $x $y $z result $A $B $C $D $E $F $G $H $I $J $K $L $M $N $O $P $Q $R $S $T $U $V $W $X $Y $Z An implemention may define other #asUppercase mappings. If the receiver does not correspond to a character in the "receiver" row of the table and does not have an implementation defined mapping the receiver is returned as the result. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'Character' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'codePoint' forProtocolNamed: #'Character' synopsis: 'Return the encoding value of the receiver. ' definedIn: 'Character' definition: 'Return the encoding value of the receiver in the implementation defined execution character set. The following invariant must hold: (charFactory codePoint: x) codePoint = x where charFactory is an object that implements and x is an . ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'integer' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'isAlphaNumeric' forProtocolNamed: #'Character' synopsis: 'Test whether the receiver is a letter or digit. ' definedIn: 'Character' definition: 'Return true if the receiver is either a letter or digit. Otherwise return false. In other words character isAlphaNumeric is true if and only if either character isLetter is true or character isDigit is true. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'boolean' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'isDigit' forProtocolNamed: #'Character' synopsis: 'Test whether the receiver is a digit. ' definedIn: 'Character' definition: 'Return true if the receiver represents a digit. Otherwise return false. The receiver is a digit if it is equal to the value of one of the following character literals: $0 $1 $2 $3 $4 $5 $6 $7 $8 $9 ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'boolean' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'isLetter' forProtocolNamed: #'Character' synopsis: 'Test whether the receiver is a letter. ' definedIn: 'Character' definition: 'Return true if the receiver corresponds to an alphabetic character, ignoring case. Otherwise return false. The receiver is an alphabetic character if it is equal to the value of one of the following character literals: $A $B $C $D $E $F $G $H $I $J $K $L $M $N $O $P $Q $R $S $T $U $V $W $X $Y $Z $a $b $c $d $e $f $g $h $i $j $k $l $m $n $o $p $q $r $s $t $u $v $w $x $y $z Implementations may define other characters to be alphabetic characters. Any such characters will return true when set this message. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'boolean' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'isLowercase' forProtocolNamed: #'Character' synopsis: 'Test whether the receiver is a lowercase letter. ' definedIn: 'Character' definition: 'Return true if the receiver corresponds to a lowercase letter. Otherwise return false. The receiver is an lowercase letter if it is equal to the value of one of the following character literals: $a $b $c $d $e $f $g $h $i $j $k $l $m $n $o $p $q $r $s $t $u $v $w $x $y $z Implementations may define other characters to be lowercase characters. Any such characters will return true when set this message. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'boolean' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'isUppercase' forProtocolNamed: #'Character' synopsis: 'Test whether the receiver is an uppercase letter. ' definedIn: 'Character' definition: 'Return true if the receiver corresponds to a uppercase letter. Otherwise return false. The receiver is an uppercase letter if it is equal to the value of one of the following character literals: $A $B $C $D $E $F $G $H $I $J $K $L $M $N $O $P $Q $R $S $T $U $V $W $X $Y $Z Implementations may define other characters to be lowercase characters. Any such characters will return true when set this message. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'boolean' #'unspecified') ) errors: '' ! (1 protocolManager newProtocolNamed: #'Character factory' conformsToProtocolNames: #(#'Object') ) protocolDescription: ' This protocol describes the behavior for accessing character objects. Standard Globals Character Conforms to the protocol . Its language element type is unspecified. This global is a factory for for creating or accessing objects that conform to . ' ! 1 protocolManager newMessagePattern: 'codePoint: integer' forProtocolNamed: #'Character factory' synopsis: 'Return a character whose encoding value is integer. ' definedIn: 'Character factory' definition: 'Return a character whose encoding value in the implementation defined execution character set is integer. The result is undefined if the encoding value is not a valid encoding value in the implementation defined character set. ' refinedIn: '' refinement: '' parameters: #( #('integer' 'integer' #'unspecified') ) returnValues: #( #( 'Character' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'cr' forProtocolNamed: #'Character factory' synopsis: 'Return a character representing a carriage-return. ' definedIn: 'Character factory' definition: 'Return a character representing a carriage-return. The code point of the resulting character is implementation defined. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'Character' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'lf' forProtocolNamed: #'Character factory' synopsis: 'Return a character representing a line feed. ' definedIn: 'Character factory' definition: 'Return a character representing a line feed. The code point of the resulting character is implementation defined. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'Character' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'space' forProtocolNamed: #'Character factory' synopsis: 'Return a character representing a space. ' definedIn: 'Character factory' definition: 'Return a character representing a space. The code point of the resulting character is implementation defined. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'Character' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'tab' forProtocolNamed: #'Character factory' synopsis: 'Return a character representing a tab. ' definedIn: 'Character factory' definition: 'Return a character representing a tab. The code point of the resulting character is implementation defined. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'Character' #'unspecified') ) errors: '' ! (1 protocolManager newProtocolNamed: #'classDescription' conformsToProtocolNames: #(#'Object') ) protocolDescription: ' This protocol describes the behavior of class objects. It provides messages for identifying and locating class objects within the class hierarchy. ' ! 1 protocolManager newMessagePattern: 'allSubclasses' forProtocolNamed: #'classDescription' synopsis: 'Return all subclasses of a class. ' definedIn: 'classDescription' definition: 'If the receiver is a class object, return a collection containing all of the class objects whose class definitions inherit either directly or indirectly from the class definition of the receiver. If the receiver is not a class object, the result is unspecified. Each element of the result collection supports the protocol . The order of class objects within the collection is unspecified. unspecified ' refinedIn: '' refinement: '' parameters: #() returnValues: #() errors: '' ! 1 protocolManager newMessagePattern: 'allSuperclasses' forProtocolNamed: #'classDescription' synopsis: 'Return all superclasses of a class. ' definedIn: 'classDescription' definition: 'If the receiver is a class object, return a collection containing all of the class objects defined by the class definitions from which the class definition of the receiver inherits, either directly or indirectly. If the class definition of the receiver has no superclasses, return an empty collection. If the receiver is not a class object, the result is unspecified. Each element of the result collection supports the protocol . The order of class objects within the collection is unspecified. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'collection' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'name' forProtocolNamed: #'classDescription' synopsis: 'Return the name of a class. ' definedIn: 'classDescription' definition: 'Return a string containing the global name of the receiver. The global name of a class object is the global identifier that is bound to the class object. Rationale Some existing implementations may return a symbol as the result of this message. The specification of the return value should be whatever protocol is general enough to be either a string or a symbol. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'readableString' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'subclasses' forProtocolNamed: #'classDescription' synopsis: 'Return direct subclasses of a class. ' definedIn: 'classDescription' definition: 'If the receiver is a class object, return a collection containing all of the class objects whose class definitions inherit directly from the class definition of the receiver. If there are no class definitions that inherit from the class definition of the receiver, return an empty collection. If the receiver is not a class object, the result is unspecified. Each element of the result collection supports the protocol . The order of class objects within the collection is unspecified. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'collection' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'superclass' forProtocolNamed: #'classDescription' synopsis: 'Return the immediate superclass of a class. ' definedIn: 'classDescription' definition: 'If the receiver is a class object, return the class objects defined by the class definitions from which the class definition of the receiver directly inherits. If the class definition of the receiver has no superclasses, return nil. If the receiver is not a class object, the result is unspecified. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'classDescription' #'unspecified') #( 'nil' #'unspecified') ) errors: '' ! (1 protocolManager newProtocolNamed: #'collection' conformsToProtocolNames: #(#'Object') ) protocolDescription: ' Provides protocol for manipulating and operating on a collection of objects, called elements, either individually or as a whole. A collection can be fixed or variable sized, ordered or unordered, and its elements may or may not be accessible by external keys. Some implementations of collections may choose to use the hash values, as defined by either the message #hash or the message #identityHash, of either the elements of the collection or the keys by which those elements are accessed (if there are any). If the hash values of such objects are modified, the behavior of any message sent to such a collection is undefined until the message #rehash has been sent to the collection in order to restore the consistency of the collection. Rationale #rehash message was moved to Collection to avoid any pre-existing implementation assumptions about its use in the implementation of collection. Any collection concievable might use hashing and hence could need to be rehashed. ' ! 1 protocolManager newMessagePattern: 'allSatisfy: discriminator' forProtocolNamed: #'collection' synopsis: 'Return true if the discriminator evaluates to true for every element of the receiver. Otherwise return false. ' definedIn: 'collection' definition: 'Return true if the discriminator evaluates to true for every element of the receiver. Return true if the receiver is empty. Otherwise return false. It is unspecified whether the discriminator will be evaluated with every element of the receiver. ' refinedIn: '' refinement: '' parameters: #( #('discriminator' 'monadicValuable' #'uncaptured') ) returnValues: #( #( 'boolean' #'unspecified') ) errors: 'If the elements of the receiver are inappropriate for use as arguments to discriminator. If discriminator evaluates to an object that does not conform to the protocol for each element of the receiver. ' ! 1 protocolManager newMessagePattern: 'anySatisfy: discriminator' forProtocolNamed: #'collection' synopsis: 'Return true if the discriminator evaluates to true for any element of the receiver. Otherwise return false. ' definedIn: 'collection' definition: 'Return true if the discriminator evaluates to true for any element of the receiver. Otherwise return false. Return false if the receiver is empty. It is unspecified whether the discriminator will be evaluated with every element of the receiver. ' refinedIn: '' refinement: '' parameters: #( #('discriminator' 'monadicValuable' #'uncaptured') ) returnValues: #( #( 'boolean' #'unspecified') ) errors: 'If the elements of the receiver are inappropriate for use as arguments to discriminator. If discriminator evaluates to an object that does not conform to the protocol for any element of the receiver. ' ! 1 protocolManager newMessagePattern: 'asArray' forProtocolNamed: #'collection' synopsis: 'Answer an array whose elements are the elements of the receiver. ' definedIn: 'collection' definition: 'Answer an array with the same elements as the receiver. The result has the same size as the receiver, as defined by the #size message. If the receiver maintains an ordering for its elements, the order of those elements will be preserved in the result. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'Array' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'asBag' forProtocolNamed: #'collection' synopsis: 'Answer a bag with the same elements as the receiver. ' definedIn: 'collection' definition: 'Answer a bag with the same elements as the receiver. The result is unspecified if the receiver contains nil. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'Bag' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'asByteArray' forProtocolNamed: #'collection' synopsis: 'Answer a byte array whose elements are the elements of the receiver. ' definedIn: 'collection' definition: 'Answer a byte array with the same elements as the receiver. The result has the same size as the receiver, as defined by the #size message. If the receiver maintains an ordering for its elements, the order of those elements will be preserved in the result. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'ByteArray' #'unspecified') ) errors: 'If any elements in the receiver are not integers with values between 0 and 255. ' ! 1 protocolManager newMessagePattern: 'asOrderedCollection' forProtocolNamed: #'collection' synopsis: 'Answer an ordered collection whose elements are the elements of the receiver. ' definedIn: 'collection' definition: 'Answer a ordered collection with the same elements as the receiver. The result has the same size as the receiver, as defined by the #size message. If the receiver maintains an ordering for its elements, the order of those elements will be preserved in the result. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'OrderedCollection' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'asSet' forProtocolNamed: #'collection' synopsis: 'Answer a set with the same elements as the receiver. ' definedIn: 'collection' definition: 'Answer a set with the same elements as the receiver. Since sets do not store duplicate elements, the result may have fewer elements than the receiver. The result is undefined if the receiver contains nil. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'Set' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'asSortedCollection' forProtocolNamed: #'collection' synopsis: 'Answer a sorted collection with the same elements as the receiver. ' definedIn: 'collection' definition: 'Answer a sorted collection with the same elements as the receiver. The default sort block is used. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'SortedCollection' #'unspecified') ) errors: 'If any element of the receiver is not appropriate as a parameter to the default sort block. ' ! 1 protocolManager newMessagePattern: 'asSortedCollection: sortBlock' forProtocolNamed: #'collection' synopsis: 'Answer a sorted collection with the same elements as the receiver. The parameter sortBlock is used as the sort block. ' definedIn: 'collection' definition: 'Answer a sorted collection with the same elements as the receiver. The parameter sortBlock is used as the sort block and must meet the requirements of a sort block as specified by . ' refinedIn: '' refinement: '' parameters: #( #('sortBlock' 'dyadicValuable' #'captured') ) returnValues: #( #( 'SortedCollection' #'unspecified') ) errors: 'If sortBlock does not meet the requirements for a sort block as specified by . If any element of the receiver is not appropriate as a parameter to the sortBlock. ' ! 1 protocolManager newMessagePattern: 'collect: transformer' forProtocolNamed: #'collection' synopsis: 'Answer a new collection constructed by gathering the results of evaluating transformer with each element of the receiver. ' definedIn: 'collection' definition: 'For each element of the receiver, transformer is evaluated with the element as the parameter. The results of these evaluations are collected into a new collection. The elements are traversed in the same order as they would be if the message #do: had been sent to the receiver. Unless specifically refined, this message is defined to answer an object conforming to the same protocol as the receiver. ' refinedIn: '' refinement: '' parameters: #( #('transformer' 'monadicValuable' #'uncaptured') ) returnValues: #( #( 'collection' #'new') ) errors: 'If any element of the receiver is inappropriate for use as arguments to transformer. If the result of evaluating the transformer does not conform to any element type restrictions of the collection to be returned. ' ! 1 protocolManager newMessagePattern: 'detect: discriminator' forProtocolNamed: #'collection' synopsis: 'Return the first element of the receiver which causes discriminator to evaluate to true when the element is used as the argument. ' definedIn: 'collection' definition: 'Return the first element of the receiver for which the discriminator evaluates to true when given that element as an argument. The discriminator will only be evaluated until such an object is found or until all of the elements of the collection have been used as arguments. That is, there may be elements of the receiver that are never used as arguments to the discriminator. The elements are traversed in the same order as they would be if the message #do: had been sent to the receiver. The result is undefined if discriminator does not evaluate to true for any element. ' refinedIn: '' refinement: '' parameters: #( #('discriminator' 'monadicValuable' #'uncaptured') ) returnValues: #( #( 'Object' #'state') ) errors: 'If the elements of the receiver are inappropriate for use as arguments to discriminator. If discriminator evaluates to an object that does not conform to the protocol for any element of the receiver. ' ! 1 protocolManager newMessagePattern: 'detect: discriminator ifNone: exceptionHandler' forProtocolNamed: #'collection' synopsis: 'Return the first element of the receiver which causes discriminator to evaluate to true when used as the argument to the evaluation. Answer the result of evaluating exceptionHandler if no such element is found. ' definedIn: 'collection' definition: 'Return the first element of the receiver for which the discriminator evaluates to true when given that element as an argument. The discriminator will only be evaluated until such an object is found or until all of the elements of the collection have been used as arguments. That is, there may be elements of the receiver that are never used as arguments to the discriminator. The elements are traversed in the same order as they would be if the message #do: had been sent to the receiver. If no element causes discriminator to evaluate to true, answer the result of exceptionHandler value. ' refinedIn: '' refinement: '' parameters: #( #('exceptionHandler' 'niladicValuable' #'uncaptured') #('discriminator' 'monadicValuable' #'uncaptured') ) returnValues: #( #( 'Object' #'state') #( 'Object' #'unspecified') ) errors: 'If the elements of the receiver are inappropriate for use as arguments to discriminator. If discriminator evaluates to an object that does not conform to the protocol for any element of the receiver. ' ! 1 protocolManager newMessagePattern: 'do: operation' forProtocolNamed: #'collection' synopsis: 'Evaluate operation with each element of the receiver. ' definedIn: 'collection' definition: 'For each element of the receiver, operation is evaluated with the element as the parameter. Unless specifically refined, the elements are not traversed in a particular order. Each element is visited exactly once. Conformant protocols may refine this message to specify a particular ordering. ' refinedIn: '' refinement: '' parameters: #( #('operation' 'monadicValuable' #'uncaptured') ) returnValues: #() errors: 'If the elements of the receiver are inappropriate for use as arguments to operation. ' ! 1 protocolManager newMessagePattern: 'do: separator separatedBy: operation' forProtocolNamed: #'collection' synopsis: 'Evaluate operation with each element of the receiver interspersed by evaluation of separator. ' definedIn: 'collection' definition: 'For each element of the receiver, operation is evaluated with the element as the parameter. Before evaluating operation the second and subsequent times evaluate separator. Separator is not evaluated if there are less than two elements nor after the last element. ' refinedIn: '' refinement: '' parameters: #( #('separator' 'niladicValuable' #'uncaptured') #('operation' 'monadicValuable' #'uncaptured') ) returnValues: #() errors: '' ! 1 protocolManager newMessagePattern: 'includes: target' forProtocolNamed: #'collection' synopsis: 'Answer true if an element of the receiver is equivalent to target. Answer false otherwise. ' definedIn: 'collection' definition: 'This message is used to test an object for inclusion among the receiver''s elements. Answer true if at least one of the receiver''s elements is equivalent to target. Answer false otherwise. ' refinedIn: '' refinement: '' parameters: #( #('target' 'Object' #'uncaptured') ) returnValues: #( #( 'boolean' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'inject: operation into: initialValue' forProtocolNamed: #'collection' synopsis: 'Answer the final result of evaluating operation using each element of the receiver and the previous evaluation result as the parameters. ' definedIn: 'collection' definition: 'The first evaluation of operation is performed with initialValue as the first parameter, and the first element of the receiver as the second parameter. Subsequent evaluations are done with the result of the previous evaluation as the first parameter, and the next element as the second parameter. The result of the last evaluation is answered. The elements are traversed in the same order as they would be if the message #do: had been sent to the receiver. ' refinedIn: '' refinement: '' parameters: #( #('initialValue' 'Object' #'uncaptured') #('operation' 'dyadicValuable' #'uncaptured') ) returnValues: #( #( 'Object' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'isEmpty' forProtocolNamed: #'collection' synopsis: 'Return true if the receiver contains no elements. Return false otherwise. ' definedIn: 'collection' definition: 'Return true if and only if receiver size = 0 is true. Otherwise return false. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'boolean' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'notEmpty' forProtocolNamed: #'collection' synopsis: 'Return true if the receiver contains elements. Return false otherwise. ' definedIn: 'collection' definition: 'Return true if the receiver contains elements. Return false otherwise. This is equivalent to receiver isEmpty not ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'boolean' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'occurrencesOf: target' forProtocolNamed: #'collection' synopsis: 'Answer the number of elements of the receiver which are equivalent to target. ' definedIn: 'collection' definition: 'Answer the number of elements of the receiver which are equivalent to target. ' refinedIn: '' refinement: '' parameters: #( #('target' 'Object' #'uncaptured') ) returnValues: #( #( 'integer' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'rehash' forProtocolNamed: #'collection' synopsis: 'Re-establish hash invariants, if any. ' definedIn: 'collection' definition: 'Re-establish any hash invariants of the receiver. ' refinedIn: '' refinement: '' parameters: #() returnValues: #() errors: '' ! 1 protocolManager newMessagePattern: 'reject: discriminator' forProtocolNamed: #'collection' synopsis: 'Answer a new collection which includes only the elements in the receiver which cause discriminator to evaluate to false. ' definedIn: 'collection' definition: 'For each element of the receiver, discriminator is evaluated with the element as the parameter. Each element which causes discriminator to evaluate to false is included in the new collection. The elements are traversed in the same order as they would be if the message #do: had been sent to the receiver. Unless specifically refined, this message is defined to answer an object conforming to the same protocol as the receiver. If both the receiver and the result maintain an ordering of their elements, the elements of the result will be in the same relative order as the elements of the receiver. ' refinedIn: '' refinement: '' parameters: #( #('discriminator' 'monadicValuable' #'uncaptured') ) returnValues: #( #( 'collection' #'new') ) errors: 'If the elements of the receiver are inappropriate for use as arguments to discriminator. If discriminator evaluates to an object that does not conform to the protocol for any element of the receiver. ' ! 1 protocolManager newMessagePattern: 'select: discriminator' forProtocolNamed: #'collection' synopsis: 'Answer a new collection which contains only the elements in the receiver which cause discriminator to evaluate to true. ' definedIn: 'collection' definition: 'For each element of the receiver, discriminator is evaluated with the element as the parameter. Each element which causes discriminator to evaluate to true is included in the new collection. The elements are traversed in the same order as they would be if the message #do: had been sent to the receiver. Unless specifically refined, this message is defined to answer an object conforming to the same protocol as the receiver. If both the receiver and the result maintain an ordering of their elements, the elements of the result will be in the same relative order as the elements of the receiver. ' refinedIn: '' refinement: '' parameters: #( #('discriminator' 'monadicValuable' #'uncaptured') ) returnValues: #( #( 'collection' #'new') ) errors: 'If the elements of the receiver are inappropriate for use as arguments to discriminator. If discriminator evaluates to an object that does not conform to the protocol for any element of the receiver. ' ! 1 protocolManager newMessagePattern: 'size' forProtocolNamed: #'collection' synopsis: 'Answer the number of elements in the receiver. ' definedIn: 'collection' definition: 'Answer the number of elements in the receiver. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'integer' #'unspecified') ) errors: '' ! (1 protocolManager newProtocolNamed: #'collection factory' conformsToProtocolNames: #(#'instantiator') ) protocolDescription: ' Provides protocol for creating a collection of objects. A collection can be fixed or variable sized, ordered or unordered, and its elements may or may not be accessible by external keys. ' ! 1 protocolManager newMessagePattern: 'new' forProtocolNamed: #'collection factory' synopsis: 'Create a new object. ' definedIn: 'instantiator' definition: 'Return a newly created object initialized to a standard initial state. ' refinedIn: 'collection factory' refinement: 'This message has the same effect as sending the message #new: with the argument 0. ' parameters: #() returnValues: #( #( 'collection' #'new') ) errors: '' ! 1 protocolManager newMessagePattern: 'new: count' forProtocolNamed: #'collection factory' synopsis: 'Create a new collection. The parameter count constrains the number of elements in the result. ' definedIn: 'collection factory' definition: 'Return a new collection that has space for at least count elements. Conforming protocols may refine this message. In particular, the effect of the parameter count should be specified in refinements. It can be used to specify the exact number of elements, the minimum number, or in some cases can even be interpreted as a hint from the programmer, with no guarantee that the requested number of instance variables will actually be allocated. Unless otherwise stated the initial values of elements, if any, of the new collection are unspecified. ' refinedIn: '' refinement: '' parameters: #( #('count' 'integer' #'unspecified') ) returnValues: #( #( 'collection' #'new') ) errors: '' ! (1 protocolManager newProtocolNamed: #'collectionStream' conformsToProtocolNames: #(#'sequencedStream') ) protocolDescription: ' An object conforming to has a as its stream backing store. ' ! 1 protocolManager newMessagePattern: 'contents' forProtocolNamed: #'collectionStream' synopsis: 'Returns a collection containing the complete contents of the stream. ' definedIn: 'sequencedStream' definition: 'Returns a collection that contains the receiver''s past and future sequence values, in order. The size of the collection is the sum of the sizes of the past and future sequence values. ' refinedIn: 'collectionStream' refinement: 'It is unspecified whether or not the returned collection is the same object as the backing store collection. However, if the returned collection is not the same object as the stream backing store collection then the class of the returned collection is the same class as would be returned if the message #select: was sent to the backing store collection. ' parameters: #() returnValues: #( #( 'sequencedReadableCollection' #'unspecified') ) errors: '' ! (1 protocolManager newProtocolNamed: #'DateAndTime' conformsToProtocolNames: #(#'magnitude') ) protocolDescription: ' This protocol describes the behavior that is common to date time objects. Date time objects represent individual points in Coordinated Universal Time (UTC) as represented in an implementation defined local time. The exact properties of local times are unspecified. Local times may differ in their offset from UTC. A given local time may have different offsets from UTC at different points in time. All dates and times in the UTC local time are in the Gregorian calendar. Date times prior to the adoption of the Gregorian calendar are given in the retrospective astronomical Gregorian calendar. The year 1 B.C. is astronomical Gregorian year 0. The year 2 B.C. is astronomical Gregorian year -1. The year 1 A.D. is astronomical Gregorian year 1. The offset of the UTC local time is zero. ' ! 1 protocolManager newMessagePattern: '+ operand' forProtocolNamed: #'DateAndTime' synopsis: 'Answer the result of adding operand to the receiver. ' definedIn: 'DateAndTime' definition: 'Answer a that represents the UTC time that is operand after the receiver and whose local time is the same as the receiver''s. If operand is less than #zero, the result is the that is that is the absolute value of operand before the receiver. ' refinedIn: '' refinement: '' parameters: #( #('operand' 'Duration' #'uncaptured') ) returnValues: #( #( 'DateAndTime' #'new') ) errors: '' ! 1 protocolManager newMessagePattern: '- operand' forProtocolNamed: #'DateAndTime' synopsis: 'Answer the result of adding operand to the receiver. ' definedIn: 'DateAndTime' definition: 'If operand is a , answer a whose value is the period of time between the operand and the receiver. If operand is a prior to the receiver then the result is a less than #zero. If operand is a , answer a new which represents the UTC time that is operand before the receiver and whose local time is the same as the receiver''s. If operand is a duration less than #zero then the result is a that is the absolute value of operand after the receiver. ' refinedIn: '' refinement: '' parameters: #( #('operand' 'Duration DateAndTime' #'uncaptured') ) returnValues: #( #( 'Duration' #'unspecified') #( 'DateAndTime' #'unspecified') ) errors: 'none. ' ! 1 protocolManager newMessagePattern: '< operand' forProtocolNamed: #'DateAndTime' synopsis: 'Answer true if the receiver is less than operand. Answer false otherwise. ' definedIn: 'magnitude' definition: 'Answer true if the receiver is less than operand with respect to the ordering defined for them. Answer false otherwise. It is erroneous if the receiver and operand are not comparable. The semantics of the natural ordering must be defined by refinement, which may also restrict the type of operand. ' refinedIn: 'DateAndTime' refinement: 'Answer true if the UTC time represented by operand follows the UTC time represented by the receiver. Answer false otherwise. If the offsets of the receiver and operand are the same then their order is determined by their lexical order in the sequence #year, #month, #day, #hour24, #minute, #second. If their offsets differ then result is the same as if receiver asUTC < operand asUTC were evaluated. ' parameters: #( #('operand' 'DateAndTime' #'uncaptured') ) returnValues: #( #( 'boolean' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: '= comparand' forProtocolNamed: #'DateAndTime' synopsis: 'Object equivalence test. ' definedIn: 'Object' definition: 'This message tests whether the receiver and the comparand are equivalent objects at the time the message is processed. Return true if the receiver is equivalent to comparand. Otherwise return false. The meaning of "equivalent" cannot be precisely defined but the intent is that two objects are considered equivalent if they can be used interchangeably. Conforming protocols may choose to more precisely define the meaning of "equivalent". The value of receiver = comparand is true if and only if the value of comparand = receiver would also be true. If the value of receiver = comparand is true then the receiver and comparand must have equivalent hash values. Or more formally: receiver = comparand ? receiver hash = comparand hash The equivalence of objects need not be temporally invariant. Two independent invocations of #= with the same receiver and operand objects may not always yield the same results. Note that a collection that uses #= to discriminate objects may only reliably store objects whose hash values do not change while the objects are contained in the collection. ' refinedIn: 'DateAndTime' refinement: 'Answer true if the comparand conforms to and if it represents the same UTC time as the receiver. Answer false otherwise. The local times of the receiver and operand are ignored. ' parameters: #( #('comparand' 'Object' #'uncaptured') ) returnValues: #( #( 'boolean' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: '> operand' forProtocolNamed: #'DateAndTime' synopsis: 'Answer true if the receiver is greater than operand. Answer false otherwise. ' definedIn: 'magnitude' definition: 'Answer true if the receiver is greater than operand with respect to the natural ordering. Answer false otherwise. It is erroneous if the receiver and operand are not comparable. The semantics of the natural ordering must be defined by refinement, which may also restrict the type of operand. ' refinedIn: 'DateAndTime' refinement: 'Answer true if the UTC time represented by operand precedes the UTC time represented by the receiver. Answer false otherwise. If the offsets of the receiver and operand are the same then their order is determined by their lexical order in the sequence #year, #month, #day, #hour24, #minute, #second. If their offsets differ then result is the same as if receiver asUTC > operand asUTC were evaluated. ' parameters: #( #('operand' 'DateAndTime' #'uncaptured') ) returnValues: #( #( 'boolean' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'asLocal' forProtocolNamed: #'DateAndTime' synopsis: 'Answer a that represents the same UTC time as the receiver but in the local time specified by the implementation. ' definedIn: 'DateAndTime' definition: 'Answer a that represents the same UTC time as the receiver but in the local time specified by the implementation. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'DateAndTime' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'asUTC' forProtocolNamed: #'DateAndTime' synopsis: 'Answer a that represents the same absolute time as the receiver but in the local time UTC. ' definedIn: 'DateAndTime' definition: 'Answer a that represents the same absolute time as the receiver but in the local time UTC. The exact meaning of UTC local time is specified by the implementation. The UTC local time must use the Gregorian calendar. representing UTC times prior to the adoption of the Gregorian calendar must use the retrospective astronomical Gregorian calendar. It is an invariant that asUTC offset = Duration zero. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'DateAndTime' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'dayOfMonth' forProtocolNamed: #'DateAndTime' synopsis: 'Answer the number of the day in the month in the local time of the receiver which includes the receiver. ' definedIn: 'DateAndTime' definition: 'Answer an between 1 and 31 inclusive representing the number of the day in the month, in the local time of the receiver, which includes the receiver. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'integer' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'dayOfWeek' forProtocolNamed: #'DateAndTime' synopsis: 'Answer the number of the day in the week, in the local time of the receiver, which includes the receiver. ' definedIn: 'DateAndTime' definition: 'Answer an between 1 and 7 inclusive representing the number of the day in the week, in the local time of the receiver, which includes the receiver. Sunday is 1, Monday is 2, and so on. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'integer' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'dayOfWeekAbbreviation' forProtocolNamed: #'DateAndTime' synopsis: 'Answer the abbreviation of the name, in the local time of the receiver, of the day of the week which includes the receiver. ' definedIn: 'DateAndTime' definition: 'Answer an which is the abbreviation of the name, in the local time of the receiver, of the day of the week which includes the receiver. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'readableString' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'dayOfWeekName' forProtocolNamed: #'DateAndTime' synopsis: 'Answer the name, in the local time of the receiver, of the day of the week which includes the receiver. ' definedIn: 'DateAndTime' definition: 'Answer an which is the name, in the local time of the receiver, of the day of the week which includes the receiver. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'readableString' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'dayOfYear' forProtocolNamed: #'DateAndTime' synopsis: 'Answer the number of the day in the year, in the local time of the receiver, which includes the receiver. ' definedIn: 'DateAndTime' definition: 'Answer an between 1 and 366 inclusive representing the number of the day in the year, in the local time of the receiver, which includes the receiver. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'integer' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'hour' forProtocolNamed: #'DateAndTime' synopsis: 'Answer the number of the hour in the day, in the local time of the receiver, which includes the receiver. ' definedIn: 'DateAndTime' definition: 'Answer an between 0 and 23 inclusive representing the number of the hour in the day, in the local time of the receiver, which includes the receiver. It is implementation defined whether a given local time uses the 12-hour clock or the 24-hour clock, except that the UTC local time must use the 24-hour clock. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'integer' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'hour12' forProtocolNamed: #'DateAndTime' synopsis: 'Answer the hour in the day in the 12-hour clock of the local time of the receiver. ' definedIn: 'DateAndTime' definition: 'Answer an between 1 and 12 inclusive representing the hour in the day in the 12-hour clock of the local time of the receiver. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'integer' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'hour24' forProtocolNamed: #'DateAndTime' synopsis: 'Answer the hour in the day in the 24-hour clock of the local time of the receiver. ' definedIn: 'DateAndTime' definition: 'Answer an between 0 and 23 inclusive representing the hour in the day in the 24-hour clock of the local time of the receiver. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'integer' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'isLeapYear' forProtocolNamed: #'DateAndTime' synopsis: 'Test for leap year. ' definedIn: 'DateAndTime' definition: 'Answer true if the year, which includes the receiver, in the local time of the receiver is a leap year, false otherwise. Two objects that are equal can give different results for #isLeapYear. Equality depends on their UTC time whereas #isLeapYear depends on their local time. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'boolean' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'meridianAbbreviation' forProtocolNamed: #'DateAndTime' synopsis: 'Answer the abbreviation, in the local time of the receiver, of the name of the half of the day, which includes the receiver. ' definedIn: 'DateAndTime' definition: 'Answer a that is the abbreviation, in the local time of the receiver, of the name of the half of the day, which includes the receiver. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'readableString' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'minute' forProtocolNamed: #'DateAndTime' synopsis: 'Answer the minute of the hour in the local time of the receiver. ' definedIn: 'DateAndTime' definition: 'Answer an between 0 and 59 inclusive representing the minute of hour in the local time of the receiver. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'integer' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'month' forProtocolNamed: #'DateAndTime' synopsis: 'Answer the number of the month in the year, in the local time of the receiver, which includes the receiver. ' definedIn: 'DateAndTime' definition: 'Answer an between 1 and 12 inclusive representing the number of the month in the year, in the local time of the receiver, which includes the receiver. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'integer' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'monthAbbreviation' forProtocolNamed: #'DateAndTime' synopsis: 'Answer the abbreviation of the name of the month, in the local time of the receiver, which includes the receiver. ' definedIn: 'DateAndTime' definition: 'Answer a that is the abbreviation of the name of the month, in the local time of the receiver, which includes the receiver. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'readableString' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'monthName' forProtocolNamed: #'DateAndTime' synopsis: 'Answer the name of the month, in the local time of the receiver, which includes the receiver. ' definedIn: 'DateAndTime' definition: 'Answer a that is the name of the month, in the local time of the receiver, which includes the receiver. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'readableString' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'offset' forProtocolNamed: #'DateAndTime' synopsis: 'Answer the difference between the local time of the receiver and UTC at the time of the receiver. ' definedIn: 'DateAndTime' definition: 'Answer a representing the difference between the local time of the receiver and UTC at the time of the receiver. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'Duration' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'offset: offset' forProtocolNamed: #'DateAndTime' synopsis: 'Answer a equivalent to the receiver but with its local time being offset from UTC by offset. ' definedIn: 'DateAndTime' definition: 'Answer a equivalent to the receiver but with its local time being offset from UTC by offset. The impact of this on any other local time property is unspecified. Implementations may define a limit to the range of offset, but it must be at least -12:00:00 to 12:00:00 inclusive. It is an invariant that if x is a in range then ( offset: x) offset = x ' refinedIn: '' refinement: '' parameters: #( #('offset' 'Duration' #'unspecified') ) returnValues: #( #( 'DateAndTime' #'unspecified') ) errors: 'offset out of range ' ! 1 protocolManager newMessagePattern: 'printString' forProtocolNamed: #'DateAndTime' synopsis: 'Return a string that describes the receiver. ' definedIn: 'Object' definition: 'A string consisting of a sequence of characters that describe the receiver are returned as the result. The exact sequence of characters that describe an object are implementation defined. ' refinedIn: 'DateAndTime' refinement: 'The returned string will represent the UTC time of the receiver offset from UTC by the offset of the receiver. All dates are in the astronomical Gregorian calendar. The result will be formatted as -YYYY-MM-DDThh:mm:ss.s+ZZ:zz:z where - is the $- if the year is less than 0 otherwise it is the that is returned from the message #space sent to the standard global Character, YYYY is the year left zero filled to four places, - is the $-, MM is the month of the year left zero filled to two places, - is the $-, DD is the day of the month left zero filled to two places, T is the $T, hh is the hour in the 24-hour clock left zero filled to two places, : is the $:, mm is the minute left zero filled to two places, : is the $:, ss is the second left zero filled to two places, . is the $. and is present only if the fraction of a second is non-zero, s is the fraction of a second and is present only if non-zero, + is the $+ if the offset is greater than or equal to #zero and the $- if it is less, ZZ is the hours of the offset left zero filled to two places, and : is the $:, zz is the minutes of the offset left zero filled to two places, : is the $: and is present only if the seconds of the offset is non-zero, z is the seconds of the offset including any fractional part and is present only if non-zero. This format is based on ISO 8601 sections 5.3.3 and 5.4.1. Example: 8:33:14.321 PM EST January 5, 1200 B.C. ''-1199-01-05T20:33:14.321-05:00'' Example: 12 midnight UTC January 1, 2001 A.D. '' 2001-01-01T00:00:00+00:00'' ' parameters: #() returnValues: #( #( 'readableString' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'second' forProtocolNamed: #'DateAndTime' synopsis: 'Answer the second of the minute of the local time of the receiver. ' definedIn: 'DateAndTime' definition: 'Answer a greater than or equal to 0 and strictly less than 60 representing the second of the minute of the local time of the receiver. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'number' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'timeZoneAbbreviation' forProtocolNamed: #'DateAndTime' synopsis: 'Answer the abbreviation of the name, in the local time of the receiver, of the time zone of the receiver. ' definedIn: 'DateAndTime' definition: 'Answer a that is the abbreviation of the name, in the local time of the receiver, of the time zone of the receiver. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'readableString' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'timeZoneName' forProtocolNamed: #'DateAndTime' synopsis: 'Answer the name in the local time of the receiver of the time zone of the receiver. ' definedIn: 'DateAndTime' definition: 'Answer a that is the name in the local time of the receiver of the time zone of the receiver. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'readableString' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'year' forProtocolNamed: #'DateAndTime' synopsis: 'Answer the number of the year in the local time of the receiver which includes the receiver. ' definedIn: 'DateAndTime' definition: 'Answer an the number of the year which includes the receiver. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'integer' #'unspecified') ) errors: '' ! (1 protocolManager newProtocolNamed: #'DateAndTime factory' conformsToProtocolNames: #(#'Object') ) protocolDescription: ' Represents protocol for creating an abstraction for a particular day of the year. Standard Globals DateTime Conforms to the protocol . Its language element type is unspecified. ' ! 1 protocolManager newMessagePattern: 'clockPrecision' forProtocolNamed: #'DateAndTime factory' synopsis: 'Answer a such that after that period of time passes, #now is guaranteed to give a different result. ' definedIn: 'DateAndTime factory' definition: 'Answer a such that after that period of time passes, #now is guaranteed to give a different result. Ideally implementations should answer the least such duration. Return Value: unspecified ' refinedIn: '' refinement: '' parameters: #() returnValues: #() errors: '' ! 1 protocolManager newMessagePattern: 'now' forProtocolNamed: #'DateAndTime factory' synopsis: 'Answer a representing the current date and time. ' definedIn: 'DateAndTime factory' definition: 'Answer a representing the current date and time in the local time specified by the implementation. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'DateAndTime' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'year: hour day: dayOfYear hour: minute minute: second second: year' forProtocolNamed: #'DateAndTime factory' synopsis: 'Answer a which is the second second of the minute minute of the hour hour of the day dayOfYear of the year year of the astronomical Gregorian calendar in local time. ' definedIn: 'DateAndTime factory' definition: 'Answer the least which is the second second of the minute minute of the hour hour of the day dayOfYear of the year year of the astronomical Gregorian calendar in the local time specified by the implementation. The second must be a greater than or equal to 0 and strictly less than 60. The minute must be an between 0 and 59 inclusive. The hour must be an between 0 and 23 inclusive. The day must be an between 1 and 366 inclusive. An implementation may not impose any limits on the year other than those imposed on constants. It is possible that the time specified does not exist in the local time specified by the implementation. If there is a time change such that the local time is set forward and the time specified is in the interregnum, then that time does not exist in the local time. For example if at 02:00 in California on April 26, 1997 there is a time change that sets local time forward one hour, then the local time 02:30 in California does not exist. Conversely if there is a time change that sets the locale time back there are times which are ambiguous. For example if instead of setting the local time forward from 02:00 to 03:00 it is set back to 01:00 the the local time 01:30 in California is ambiguious. The result is the least that conforms to the given parameters. It is worth noting that the year 1 B.C. is year 0 in the astronomical Gregorian calendar. Similarly the year 2 B.C. is year -1 in the astronomical Gregorian calendar and so on. The year 1 A.D. is year 1 in the astronomical Gregorian calendar. ' refinedIn: '' refinement: '' parameters: #( #('year' 'integer' #'unspecified') #('dayOfYear' 'integer' #'unspecified') #('hour' 'integer' #'unspecified') #('minute' 'integer' #'unspecified') #('second' 'number' #'unspecified') ) returnValues: #( #( 'DateAndTime' #'new') ) errors: 'month is not between 1 and 12 inclusive. dayOfYear greater than the number of days in the year year of the astronomical Gregorian calendar. hour is not between 0 and 23 inclusive. minute is not between 0 and 59 inclusive. second is not greater than or equal to 0 and strictly less than 60. the time specified does not exist. ' ! 1 protocolManager newMessagePattern: 'year: minute day: hour hour: second minute: dayOfYear second: year offset: offset' forProtocolNamed: #'DateAndTime factory' synopsis: 'Answer a which is the second second of the minute minute of the hour hour of the day dayOfYear of the year year of the astronomical Gregorian calendar offset from UTC by offset. ' definedIn: 'DateAndTime factory' definition: 'Answer the least which is the second second of the minute minute of the hour hour of the day dayOfYear of the year year of the astronomical Gregorian calendar in the local time of the locale locale. The second must be a greater than or equal to 0 and strictly less than 60. The minute must be an between 0 and 59 inclusive. The hour must be an between 0 and 23 inclusive. The day must be an between 1 and 366 inclusive. An implementation may not impose any limits on the year other than those imposed on constants. It is possible that the time specified does not exist in the local time defined by the implementation. If there is a time change such that the local time is set forward and the time specified is in the interregnum, then that time does not exist in the local time. For example if at 02:00 in California on April 26, 1997 there is a time change that sets local time forward one hour, then the local time 02:30 in California does not exist. Conversely if there is a time change that sets the locale time back there are times which are ambiguous. For example if instead of setting the local time forward from 02:00 to 03:00 it is set back to 01:00 the the local time 01:30 in California is ambiguious. The result is the least that conforms to the given parameters. ' refinedIn: '' refinement: '' parameters: #( #('second' 'number' #'unspecified') #('hour' 'integer' #'unspecified') #('offset' 'Duration' #'unspecified') #('year' 'integer' #'unspecified') #('dayOfYear' 'integer' #'unspecified') #('minute' 'integer' #'unspecified') ) returnValues: #( #( 'DateAndTime' #'new') ) errors: 'month is not between 1 and 12 inclusive. dayOfYear greater than the number of days in the year year of the astronomical Gregorian calendar. hour is not between 0 and 23 inclusive. minute is not between 0 and 59 inclusive. second is not greater than or equal to 0 and strictly less than the number of seconds in the minute specified. ' ! 1 protocolManager newMessagePattern: 'year: hour month: second day: dayOfMonth hour: year minute: month second: minute' forProtocolNamed: #'DateAndTime factory' synopsis: 'Answer a which is the second second of the minute minute of the hour hour of the day dayOfMonth of the month month of the year year of the astronomical Gregorian calendar in local time. ' definedIn: 'DateAndTime factory' definition: 'Answer the least which is the second second of the minute minute of the hour hour of the day dayOfMonth of the month month of the year year of the astronomical Gregorian calendar in the local time specified by the implementation. The second must be a greater than or equal to 0 and strictly less than 60. The minute must be an between 0 and 59 inclusive. The hour must be an between 0 and 23 inclusive. The day must be an between 1 and 31 inclusive. The month must be an between 1 and 12 inclusive. An implementation may not impose any limits on the year other than those imposed on constants. It is possible that the time specified does not exist in the local time defined by the implementation. If there is a time change such that the local time is set forward and the time specified is in the interregnum, then that time does not exist in the local time. For example if at 02:00 in California on April 26, 1997 there is a time change that sets local time forward one hour, then the local time 02:30 in California does not exist. Conversely if there is a time change that sets the locale time back there are times which are ambiguous. For example if instead of setting the local time forward from 02:00 to 03:00 it is set back to 01:00 the the local time 01:30 in California is ambiguious. The result is the least that conforms to the given parameters. ' refinedIn: '' refinement: '' parameters: #( #('hour' 'integer' #'unspecified') #('second' 'number' #'unspecified') #('minute' 'integer' #'unspecified') #('month' 'integer' #'unspecified') #('dayOfMonth' 'integer' #'unspecified') #('year' 'integer' #'unspecified') ) returnValues: #( #( 'DateAndTime' #'new') ) errors: 'month is not between 1 and 12 inclusive. dayOfMonth greater than the number of days in the month month of year year of the astronomical Gregorian calendar. hour is not between 0 and 23 inclusive. minute is not between 0 and 59 inclusive. second is not greater than or equal to 0 and strictly less than 60. the time specified does not exist. ' ! 1 protocolManager newMessagePattern: 'year: hour month: minute day: month hour: second minute: offset second: dayOfMonth offset: year' forProtocolNamed: #'DateAndTime factory' synopsis: 'Answer a which is the second second of the minute minute of the hour hour of the day dayOfMonth of the month month of the year year of the astronomical Gregorian calendar offset from UTC by offset. ' definedIn: 'DateAndTime factory' definition: 'Answer the least which is the second second of the minute minute of the hour hour of the day dayOfMonth of the month month of the year year of the astronomical Gregorian calendar offset from UTC by offset. The second must be a greater than or equal to 0 and strictly less than 60. The minute must be an between 0 and 59 inclusive. The hour must be an between 0 and 23 inclusive. The day must be an between 1 and 31 inclusive. The month must be an between 1 and 12 inclusive. An implementation may not impose any limits on the year other than those imposed on constants. It is possible that the time specified does not exist in the local time defined by the implementation. If there is a time change such that the local time is set forward and the time specified is in the interregnum, then that time does not exist in the local time. For example if at 02:00 in California on April 26, 1997 there is a time change that sets local time forward one hour, then the local time 02:30 in California does not exist. Conversely if there is a time change that sets the locale time back there are times which are ambiguous. For example if instead of setting the local time forward from 02:00 to 03:00 it is set back to 01:00 the the local time 01:30 in California is ambiguious. The result is the least that conforms to the given parameters. ' refinedIn: '' refinement: '' parameters: #( #('minute' 'integer' #'unspecified') #('hour' 'integer' #'unspecified') #('month' 'integer' #'unspecified') #('second' 'number' #'unspecified') #('offset' 'Duration' #'unspecified') #('dayOfMonth' 'integer' #'unspecified') #('year' 'integer' #'unspecified') ) returnValues: #( #( 'DateAndTime' #'new') ) errors: 'month is not between 1 and 12 inclusive. dayOfMonth greater than the number of days in the month month of year year of the astronomical Gregorian calendar. hour is not between 0 and 23 inclusive. minute is not between 0 and 59 inclusive. second is not greater than or equal to 0 and strictly less than 60. ' ! (1 protocolManager newProtocolNamed: #'Dictionary' conformsToProtocolNames: #(#'abstractDictionary') ) protocolDescription: ' Represents an unordered collection whose elements can be accessed using an explicitly assigned external key. Key equivalence is defined as sending the #= message. ' ! (1 protocolManager newProtocolNamed: #'Dictionary factory' conformsToProtocolNames: #(#'collection factory') ) protocolDescription: ' This protocol defines the behavior of objects that can be used to create objects that conform to the protocol . Standard Globals Dictionary Conforms to the protocol . Its language element type is unspecified. This is a factory and discriminator for collections that conform to . ' ! 1 protocolManager newMessagePattern: 'new' forProtocolNamed: #'Dictionary factory' synopsis: 'Create a new object. ' definedIn: 'instantiator' definition: 'Return a newly created object initialized to a standard initial state. ' refinedIn: 'Dictionary factory' refinement: 'Return a new that is optimized to store an implementation defined number of elements. The new collection initially contains no elements. ' parameters: #() returnValues: #( #( 'Dictionary' #'new') ) errors: '' ! 1 protocolManager newMessagePattern: 'new: count' forProtocolNamed: #'Dictionary factory' synopsis: 'Create a new collection. The parameter count constrains the number of elements in the result. ' definedIn: 'collection factory' definition: 'Return a new collection that has space for at least count elements. Conforming protocols may refine this message. In particular, the effect of the parameter count should be specified in refinements. It can be used to specify the exact number of elements, the minimum number, or in some cases can even be interpreted as a hint from the programmer, with no guarantee that the requested number of instance variables will actually be allocated. Unless otherwise stated the initial values of elements of the new instance of the receiver are unspecified. ' refinedIn: 'Dictionary factory' refinement: 'The parameter count represents a hint for space allocation. The new collection is to optimized to contain count elements. The new collection initially contains no elements. The new collection conforms to the protocol . ' parameters: #( #('count' 'integer' #'unspecified') ) returnValues: #( #( 'Dictionary' #'new') ) errors: '' ! 1 protocolManager newMessagePattern: 'withAll: newElements' forProtocolNamed: #'Dictionary factory' synopsis: 'Create a collection containing all the elements of newElements. ' definedIn: 'Dictionary factory' definition: 'Return a new collection whose elements are the elements of newElements. The effect is the same as evaluating Dictionary new addAll: newElements; yourself. ' refinedIn: '' refinement: '' parameters: #( #('newElements' 'abstractDictionary' #'unspecified') ) returnValues: #( #( 'Dictionary' #'new') ) errors: '' ! (1 protocolManager newProtocolNamed: #'Duration' conformsToProtocolNames: #(#'magnitude') ) protocolDescription: ' Represents a length of time. ' ! 1 protocolManager newMessagePattern: '* operand' forProtocolNamed: #'Duration' synopsis: 'Answer the result of multiplying the receiver by operand. ' definedIn: 'Duration' definition: 'Answer a that is the result of multiplying the receiver by operand. ' refinedIn: '' refinement: '' parameters: #( #('operand' 'number' #'unspecified') ) returnValues: #( #( 'Duration' #'new') ) errors: '' ! 1 protocolManager newMessagePattern: '+ operand' forProtocolNamed: #'Duration' synopsis: 'Answer the result of adding operand to the receiver. ' definedIn: 'Duration' definition: 'Answer a whose value is the result of adding the receiver and operand. ' refinedIn: '' refinement: '' parameters: #( #('operand' 'Duration' #'unspecified') ) returnValues: #( #( 'Duration' #'new') ) errors: '' ! 1 protocolManager newMessagePattern: '- operand' forProtocolNamed: #'Duration' synopsis: 'Answer the result of subtracting the operand from the receiver. ' definedIn: 'Duration' definition: 'Answer a whose value is the result of subtracting operand from the receiver. ' refinedIn: '' refinement: '' parameters: #( #('operand' 'Duration' #'unspecified') ) returnValues: #( #( 'Duration' #'new') ) errors: '' ! 1 protocolManager newMessagePattern: '/ operand' forProtocolNamed: #'Duration' synopsis: 'Answer the result of dividing the receiver by operand. ' definedIn: 'Duration' definition: 'If operand is a answer a new whose value is the result of dividing the receiver by operand. If operand equals zero the ZeroDivide exception is signaled. If operand is a answer a whose value is the result of dividing the receiver by operand. If operand is #zero the ZeroDivide exception is signaled. ' refinedIn: '' refinement: '' parameters: #( #('operand' 'Duration number' #'unspecified') ) returnValues: #( #( 'number' #'unspecified') #( 'Duration' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: '< operand' forProtocolNamed: #'Duration' synopsis: 'Answer true if the receiver is less than operand. Answer false otherwise. ' definedIn: 'magnitude' definition: 'Answer true if the receiver is less than operand with respect to the ordering defined for them. Answer false otherwise. It is erroneous if the receiver and operand are not comparable. The semantics of the natural ordering must be defined by refinement, which may also restrict the type of operand. ' refinedIn: 'Duration' refinement: 'Answer true if operand represents a that is larger than the receiver. Answer false otherwise. ' parameters: #( #('operand' 'Duration' #'unspecified') ) returnValues: #( #( 'boolean' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: '= comparand' forProtocolNamed: #'Duration' synopsis: 'Object equivalence test. ' definedIn: 'Object' definition: 'This message tests whether the receiver and the comparand are equivalent objects at the time the message is processed. Return true if the receiver is equivalent to comparand. Otherwise return false. The meaning of "equivalent" cannot be precisely defined but the intent is that two objects are considered equivalent if they can be used interchangeably. Conforming protocols may choose to more precisely define the meaning of "equivalent". The value of receiver = comparand is true if and only if the value of comparand = receiver would also be true. If the value of receiver = comparand is true then the receiver and comparand must have equivalent hash values. Or more formally: receiver = comparand ? receiver hash = comparand hash The equivalence of objects need not be temporally invariant. Two independent invocations of #= with the same receiver and operand objects may not always yield the same results. Note that a collection that uses #= to discriminate objects may only reliably store objects whose hash values do not change while the objects are contained in the collection. ' refinedIn: 'Duration' refinement: 'Answer true if the comparand is a representing the same length of time as the receiver. Answer false otherwise. ' parameters: #( #('comparand' 'Object' #'uncaptured') ) returnValues: #( #( 'boolean' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: '> operand' forProtocolNamed: #'Duration' synopsis: 'Answer true if the receiver is greater than operand. Answer false otherwise. ' definedIn: 'magnitude' definition: 'Answer true if the receiver is greater than operand with respect to the natural ordering. Answer false otherwise. It is erroneous if the receiver and operand are not comparable. The semantics of the natural ordering must be defined by refinement, which may also restrict the type of operand. ' refinedIn: 'Duration' refinement: 'Answer true if operand represents a which is smaller than the receiver. Answer false otherwise. ' parameters: #( #('operand' 'Duration' #'unspecified') ) returnValues: #( #( 'boolean' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'abs' forProtocolNamed: #'Duration' synopsis: 'Answer the absolute value of the receiver. ' definedIn: 'Duration' definition: 'If the receiver is greater than or equal to #zero answer a which is equal to the receiver. Otherwise answer a which has the same magnitude as the receiver but the opposite sign. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'Duration' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'asSeconds' forProtocolNamed: #'Duration' synopsis: 'Answer the total number of seconds in the length of time represented by the receiver. ' definedIn: 'Duration' definition: 'Answer the total number of seconds in the length of time represented by the receiver including any fractional part of a second. If the receiver is less than #zero then the result will be less than 0. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'number' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'days' forProtocolNamed: #'Duration' synopsis: 'Answer the number of complete days in the receiver. ' definedIn: 'Duration' definition: 'Answer the number of complete days in the receiver. If the receiver is less than #zero then the result will be less than or equal to 0. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'integer' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'hours' forProtocolNamed: #'Duration' synopsis: 'Answer the number of complete hours in the receiver. ' definedIn: 'Duration' definition: 'Answer an between -23 and 23 inclusive that represents the number of complete hours in the receiver, after the number of complete days has been removed. If the receiver is less than #zero then the result will be less than or equal to 0. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'integer' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'minutes' forProtocolNamed: #'Duration' synopsis: 'Answer the number of complete minutes in the receiver. ' definedIn: 'Duration' definition: 'Answer an between -59 and 59 inclusive that represents the number of complete minutes in the receiver, after the number of complete days and hours have been removed. If the receiver is less than #zero then the result will be less than or equal to 0. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'integer' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'negated' forProtocolNamed: #'Duration' synopsis: 'Answer the negation of the receiver. ' definedIn: 'Duration' definition: 'Answer a which is of the same magnitude but opposite sign as the receiver. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'Duration' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'negative' forProtocolNamed: #'Duration' synopsis: 'Answer true if the receiver is less than #zero. ' definedIn: 'Duration' definition: 'Answer true if the receiver is less than #zero, false otherwise. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'boolean' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'positive' forProtocolNamed: #'Duration' synopsis: 'Answer true if the receiver is greater than or equal to #zero. ' definedIn: 'Duration' definition: 'Answer true if the receiver is greater than or equal to the #zero, false otherwise. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'boolean' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'printString' forProtocolNamed: #'Duration' synopsis: 'Return a string that describes the receiver. ' definedIn: 'Object' definition: 'A string consisting of a sequence of characters that describe the receiver are returned as the result. The exact sequence of characters that describe an object is implementation defined. ' refinedIn: 'Duration' refinement: 'Answer a description of the receiver that is formatted as [-]D:HH:MM:SS[.S] where - is a minus sign if the receiver represents a length of time going from the future into the past, D is the number of complete days with leading zeros to fill one place, HH is the number of complete hours with leading zeros to fill two places, MM is the number of complete minutes with leading zeros to fill two places, SS is. the number of complete seconds with leading zeros to fill two places, and .S is the fractional part of the number of seconds, if any. ' parameters: #() returnValues: #( #( 'readableString' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'seconds' forProtocolNamed: #'Duration' synopsis: 'Answer the number of seconds in the receiver. ' definedIn: 'Duration' definition: 'Answer a strictly greater than -60 and strictly less than 60 that represents the number of seconds in the receiver, after the complete days, hours, and minutes have been removed. If the receiver is less than #zero then the result will be less than or equal to 0. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'number' #'unspecified') ) errors: '' ! (1 protocolManager newProtocolNamed: #'Duration factory' conformsToProtocolNames: #(#'Object') ) protocolDescription: ' Represents protocol for creating a particular length of time. Standard Globals Duration Conforms to the protocol . Its language element type is unspecified. ' ! 1 protocolManager newMessagePattern: 'days: seconds hours: hours minutes: minutes seconds: days' forProtocolNamed: #'Duration factory' synopsis: 'Answer a of the number of days, hours, minutes, and seconds. ' definedIn: 'Duration factory' definition: 'Answer a of the number of days, hours, minutes, and seconds. If any of the operands are negative, the result is smaller by that number of days, hours, minutes, or seconds as appropriate. ' refinedIn: '' refinement: '' parameters: #( #('days' 'integer' #'unspecified') #('seconds' 'number' #'unspecified') #('hours' 'integer' #'unspecified') #('minutes' 'integer' #'unspecified') ) returnValues: #( #( 'Duration' #'new') ) errors: '' ! 1 protocolManager newMessagePattern: 'seconds: seconds' forProtocolNamed: #'Duration factory' synopsis: 'Answer a which is seconds in length ' definedIn: 'Duration factory' definition: 'If seconds is negative, answer a that is abs (seconds) less than #zero. ' refinedIn: '' refinement: '' parameters: #( #('seconds' 'number' #'unspecified') ) returnValues: #( #( 'Duration' #'new') ) errors: '' ! 1 protocolManager newMessagePattern: 'zero' forProtocolNamed: #'Duration factory' synopsis: 'Answer a of zero length. ' definedIn: 'Duration factory' definition: 'Answer a representing a length of no time. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'Duration' #'unspecified') ) errors: '' ! (1 protocolManager newProtocolNamed: #'dyadicValuable' conformsToProtocolNames: #(#'valuable') ) protocolDescription: ' This protocol describes the behavior for objects supporting the #value:value: selector. ' ! 1 protocolManager newMessagePattern: 'argumentCount' forProtocolNamed: #'dyadicValuable' synopsis: 'Answers the number of arguments needed to evaluate the receiver. ' definedIn: 'valuable' definition: 'The number of arguments needed to evaluate the receiver is returned. ' refinedIn: 'dyadicValuable' refinement: 'Returns 2. ' parameters: #() returnValues: #( #( 'integer' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'value: argument1 value: argument2' forProtocolNamed: #'dyadicValuable' synopsis: 'Answers the value of the receiver when applied to the arguments. ' definedIn: 'dyadicValuable' definition: 'The receiver is evaluated as defined by the receiver. Note that in the case that the receiver is a block, that the evaluation is defined by the language with argument1 bound to the block''s first argument, and argument2 bound to the block''s second argument. The result is as defined by the receiver. ' refinedIn: '' refinement: '' parameters: #( #('argument1' 'ANY' #'unspecified') #('argument2' 'ANY' #'unspecified') ) returnValues: #( #( 'ANY' #'unspecified') ) errors: '' ! (1 protocolManager newProtocolNamed: #'Error' conformsToProtocolNames: #(#'Exception') ) protocolDescription: ' This protocol describes the behavior of instances of class Error. These are used to represent error conditions that prevent the normal continuation of processing. Actual error exceptions used by an application may be subclasses of this class. As Error is explicitly specified to be subclassable, conforming implementations must implement its behavior in a non-fragile manner. ' ! 1 protocolManager newMessagePattern: 'defaultAction' forProtocolNamed: #'Error' synopsis: '' definedIn: 'exceptionDescription' definition: 'If the exception described by the receiver is signaled and the current exception environment does not contain a handler for the exception this method will be executed. The exact behavior and result of this method is implementation defined. ' refinedIn: 'Error' refinement: 'The current computation is terminated. The cause of the error should be logged or reported to the user. If the program is operating in an interactive debugging environment the computation should be suspended and the debugger activated. ' parameters: #() returnValues: #() errors: '' ! 1 protocolManager newMessagePattern: 'isResumable' forProtocolNamed: #'Error' synopsis: 'Determine whether an exception is resumable. ' definedIn: 'exceptionDescription' definition: 'This message is used to determine whether the receiver is a resumable exception. Answer true if the receiver is resumable. Answer false if the receiver is not resumable. ' refinedIn: 'Error' refinement: 'Answer false. Error exceptions by default are assumed to not be resumable. Subclasses may over-ride this definition for situations where it is appropriate for an error to be resumable. ' parameters: #() returnValues: #( #( 'boolean' #'unspecified') ) errors: '' ! (1 protocolManager newProtocolNamed: #'Error class' conformsToProtocolNames: #(#'Exception class') ) protocolDescription: ' This protocol describe the behavior of the global Error. The value of the standard global Error is a class object that conforms to this protocol. The class Error is explicitly specified to be subclassable in a standard conforming program. Conforming implementations must implement its behaviors in a non-fragile manner. The signaled exceptions generated by this type of object conform to the protocol . Standard Globals Error A class name. Conforms to the protocol . Error must inherit (possibly indirectly) from the class Exception. Instances of this class conform to the protocol . ' ! 1 protocolManager newMessagePattern: 'new' forProtocolNamed: #'Error class' synopsis: '' definedIn: 'instantiator' definition: 'Return a newly created object initialized to a standard initial state. ' refinedIn: 'Error class' refinement: 'The object returned conforms to ' parameters: #() returnValues: #( #( 'Error' #'new') ) errors: '' ! (1 protocolManager newProtocolNamed: #'Exception' conformsToProtocolNames: #(#'exceptionBuilder' #'signaledException') ) protocolDescription: ' This protocol describes the behavior of instances of class Exception. Typically, actual exceptions used by an application will be either direct or indirect subclasses of this class. Exception combines the behavior of and . Instances are used to both supplied inform before an exception is signaled and to pass the information to an exception handler. As Exception is explicitly specified to be subclassable, conforming implementations must implement its behavior in a non-fragile manner. Rationale Exception is an abstract class. It is the only true abstract class specified by the standard. It is included so as to provide a mechanism for the protable definition of new exception. Exceptions defined as subclasses of Exception will be portable to any conforming implementation.. ' ! (1 protocolManager newProtocolNamed: #'Exception class' conformsToProtocolNames: #(#'exceptionInstantiator' #'classDescription') ) protocolDescription: ' This protocol describe the behavior of class objects that are used to create, signal, and select exceptions that exist within a specialization hierarchy. The value of the standard global Exception is a class object that conforms to this protocol. The class Exception is explicitly specified to be subclassable. Conforming implementations must implement its behaviors in a non-fragile manner. Standard Globals Exception A class name. Conforms to the protocol . Instances of this class conform to the protocol . ' ! 1 protocolManager newMessagePattern: 'handles: exception' forProtocolNamed: #'Exception class' synopsis: '' definedIn: 'exceptionSelector' definition: 'This message determines whether the exception handler associated with the receiver may be used to process the argument. Answer true if an associated handler should be used to process exception. Answer false if an associated handler may not be used to process the exception. ' refinedIn: 'Exception class' refinement: 'Return true if the class of exception is the receiver or a general subclass of the receiver. This definition implies that subclasses of an exception class are considered to be subexceptions of the type of exception defined by their superclass. An exception handler that handles an exception class will also handle any exceptions that are instances of the exception class''s subclasses. ' parameters: #( #('exception' 'exceptionDescription' #'unspecified') ) returnValues: #( #( 'boolean' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'new' forProtocolNamed: #'Exception class' synopsis: '' definedIn: 'instantiator' definition: 'Return a newly created object initialized to a standard initial state. ' refinedIn: 'Exception class' refinement: 'The object returned conforms to ' parameters: #() returnValues: #( #( 'Exception' #'new') ) errors: '' ! 1 protocolManager newMessagePattern: 'signal' forProtocolNamed: #'Exception class' synopsis: '' definedIn: 'exceptionSignaler' definition: 'Associated with the receiver is an called the signaled exception. The current exception environment is searched for an exception handler whose exception selector matches the signaled exception. The search proceeds from the most recently created exception handler to the oldest exception handler. A matching handler is defined to be one which would return true if the message #handles: was sent to its exception selector with the signaled exception as the argument. If a matching handler is found, the exception action of the handler is evaluated in the exception environment that was current when the handler was created and the state of the current exception environment is preserved as the signaling environment. The exception action is evaluated as if the message #value: were sent to it with a passed as its argument. The is derived from the signaled exception in an implementation dependent manner. If the evaluation of the exception action returns normally (as if it had returned from the #value: message), the handler environment is restored and the value returned from the exception action is returned as the value of the #on:do: message that created the handler. Before returning, any active #ensure: or #ifCurtailed: termination blocks created during evaluation of the receiver of the #on:do: message are evaluated. If a matching handler is not found when the exception environment is searched, the default action for the signaled exception is performed. This is accomplished as if the message #defaultAction were sent to the object derived from the signaled exception. The #defaultAction method is executed in the context of the signaling environment. If the signaled exception is resumable the value returned from the #defaultAction method is returned as the value of the #signal message. If the signaled exception is not resumable the action taken upon completion of the #defaultAction method is implementation defined. ' refinedIn: 'Exception class' refinement: 'The exception signaled conforms to with all of its attributes set to their default values. ' parameters: #() returnValues: #( #( 'Object' #'unspecified') ) errors: '' ! (1 protocolManager newProtocolNamed: #'exceptionBuilder' conformsToProtocolNames: #(#'exceptionDescription' #'exceptionSignaler') ) protocolDescription: ' This protocol describes the messages that may be used to set the information about an occurrence of an exception. This information may be retrieved using protocol. If an object conforming to this protocol is signaled as an exception, any information set in that object using this protocol''s messages will also be available for retrival from the signaled exception that is passed to a handler block. ' ! 1 protocolManager newMessagePattern: 'messageText: signalerText' forProtocolNamed: #'exceptionBuilder' synopsis: 'Set an exception''s message text. ' definedIn: 'exceptionBuilder' definition: 'Set the signaler message text of the receiver. Subsequent sends of the message #messgeText to the receiver will return this value. Subseqent sends of of the message #messgeText to a signaled exception generated by sending the message #signal to the receiver of this message will also return this value. Return the receiver as the result of the message. ' refinedIn: '' refinement: '' parameters: #( #('signalerText' 'readableString' #'captured') ) returnValues: #( #( 'exceptionBuilder' #'unspecified') ) errors: '' ! (1 protocolManager newProtocolNamed: #'exceptionDescription' conformsToProtocolNames: #(#'Object') ) protocolDescription: ' This protocol describe the messages that may be used to obtain information about an occurrence of an exception. ' ! 1 protocolManager newMessagePattern: 'defaultAction' forProtocolNamed: #'exceptionDescription' synopsis: 'The default action taken if the exception is signaled. ' definedIn: 'exceptionDescription' definition: 'If the exception described by the receiver is signaled and the current exception environment does not contain a handler for the exception this method will be executed. The exact behavior and result of this method is implementation defined. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'Object' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'description' forProtocolNamed: #'exceptionDescription' synopsis: 'Return a textual description of the exception. ' definedIn: 'exceptionDescription' definition: 'Return text that describes in a human readable form an occurrence of an exception. If an explicit message text was provided by the signaler of the exception, that text should be incorporated into the description. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'readableString' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'isResumable' forProtocolNamed: #'exceptionDescription' synopsis: 'Determine whether an exception is resumable. ' definedIn: 'exceptionDescription' definition: 'This message is used to determine whether the receiver is a resumable exception. Answer true if the receiver is resumable. Answer false if the receiver is not resumable. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'boolean' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'messageText' forProtocolNamed: #'exceptionDescription' synopsis: 'Return an exception''s message text. ' definedIn: 'exceptionDescription' definition: 'Return the signaler message text of the receiver. If the signaler has not provided any message text, return nil. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'readableString' #'unspecified') #( 'nil' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'tag' forProtocolNamed: #'exceptionDescription' synopsis: 'Return an exception''s tag value. ' definedIn: 'exceptionDescription' definition: 'Return the tag value provided by the signaler of the receiver. If the signaler has not provided a tag value, return the same value was would be returned as if #message Text was sent to the receiver of this message. If the signaler has provided neither a tag value nor a message text, return nil. Exception tags are intended for use in situations where a particular occurrence of an exception needs to be identified and a textual description is not appropriate. For example, the message text might vary according to the locale and thus could not be used to identify the exception. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'nil' #'unspecified') #( 'Object' #'unspecified') ) errors: '' ! (1 protocolManager newProtocolNamed: #'exceptionInstantiator' conformsToProtocolNames: #(#'exceptionSignaler' #'exceptionSelector' #'instantiator') ) protocolDescription: ' This protocol describes the instantiation behavior of objects that can create exceptions. ' ! 1 protocolManager newMessagePattern: 'new' forProtocolNamed: #'exceptionInstantiator' synopsis: 'Create a new object. ' definedIn: 'instantiator' definition: 'Return a newly created object initialized to a standard initial state. ' refinedIn: 'exceptionInstantiator' refinement: 'The object returned is an that may be used to signal an exception of the same type that would be signaled if the message #signal is sent to the receiver. ' parameters: #() returnValues: #( #( 'exceptionBuilder' #'new') ) errors: '' ! 1 protocolManager newMessagePattern: 'signal' forProtocolNamed: #'exceptionInstantiator' synopsis: 'Signal the occurrence on an exceptional condition. ' definedIn: 'exceptionSignaler' definition: 'Associated with the receiver is an called the signaled exception. The current exception environment is searched for an exception handler whose exception selector matches the signaled exception. The search proceeds from the most recently created exception handler to the oldest exception handler. A matching handler is defined to be one which would return true if the message #handles: was sent to its exception selector with the signaled exception as the argument. If a matching handler is found, the exception action of the handler is evaluated in the exception environment that was current when the handler was created and the state of the current exception environment is preserved as the signaling environment. The exception action is evaluated as if the message #value: were sent to it with a passed as its argument. The is derived from the signaled exception in an implementation dependent manner. If the evaluation of the exception action returns normally (as if it had returned from the #value: message), the handler environment is restored and the value returned from the exception action is returned as the value of the #on:do: message that created the handler. Before returning, any active #ensure: or #ifCurtailed: termination blocks created during evaluation of the receiver of the #on:do: message are evaluated. If a matching handler is not found when the exception environment is searched, the default action for the signaled exception is performed. This is accomplished as if the message #defaultAction were sent to the object derived from the signaled exception. The #defaultAction method is executed in the context of the signaling environment. If the signaled exception is resumable the value returned from the #defaultAction method is returned as the value of the #signal message. If the signaled exception is not resumable the action taken upon completion of the #defaultAction method is implementation defined. ' refinedIn: 'exceptionInstantiator' refinement: 'An exception of the type associated with the receiver is signaled. The is initialized to its default state. ' parameters: #() returnValues: #( #( 'Object' #'unspecified') ) errors: '' ! (1 protocolManager newProtocolNamed: #'exceptionSelector' conformsToProtocolNames: #(#'Object') ) protocolDescription: ' This protocol describe the behavior of objects that are used to select an exception handler. In particular, objects that conform to this protocol may occur as the first argument to #on:do: message sent to blocks. ' ! 1 protocolManager newMessagePattern: ', anotherException' forProtocolNamed: #'exceptionSelector' synopsis: 'Create an exception set. ' definedIn: 'exceptionSelector' definition: 'Return an exception set that contains the receiver and the argument exception. This is commonly used to specify a set of exception selectors for an exception handler. ' refinedIn: '' refinement: '' parameters: #( #('anotherException' 'exceptionSelector' #'captured') ) returnValues: #( #( 'exceptionSet' #'new') ) errors: '' ! 1 protocolManager newMessagePattern: 'handles: exception' forProtocolNamed: #'exceptionSelector' synopsis: 'Determine whether an exception handler will accept a signaled exception. ' definedIn: 'exceptionSelector' definition: 'This message determines whether the exception handler associated with the receiver may be used to process the argument. Answer true if an associated handler should be used to process exception. Answer false if an associated handler may not be used to process the exception. ' refinedIn: '' refinement: '' parameters: #( #('exception' 'exceptionDescription' #'unspecified') ) returnValues: #( #( 'boolean' #'unspecified') ) errors: '' ! (1 protocolManager newProtocolNamed: #'exceptionSet' conformsToProtocolNames: #(#'exceptionSelector') ) protocolDescription: ' This protocol describes the behavior of objects that may be used to group a set of objects into a single . This is useful for establishing a single exception handler that may deal with several different types of exceptions. ' ! 1 protocolManager newMessagePattern: ', anotherException' forProtocolNamed: #'exceptionSet' synopsis: '' definedIn: 'exceptionSelector' definition: 'Return an exception set that contains the receiver and the argument exception. This is commonly used to specify a set of exception selectors for an exception handler. ' refinedIn: 'exceptionSet' refinement: 'In addition to anotherException the exception set that is returned contains all of theexception selectors contained in the receiver. The returned object may or may not be the same object as the receiver. ' parameters: #( #('anotherException' 'exceptionSelector' #'captured') ) returnValues: #( #( 'exceptionSet' #'unspecified') ) errors: '' ! (1 protocolManager newProtocolNamed: #'exceptionSignaler' conformsToProtocolNames: #(#'Object') ) protocolDescription: ' This protocol describes the behavior of signaling an exceptional condition, locating an exception handler, and executing an exception action. ' ! 1 protocolManager newMessagePattern: 'signal' forProtocolNamed: #'exceptionSignaler' synopsis: 'Signal the occurrence of an exceptional condition. ' definedIn: 'exceptionSignaler' definition: 'Associated with the receiver is an called the signaled exception. The current exception environment is searched for an exception handler whose exception selector matches the signaled exception. The search proceeds from the most recently created exception handler to the oldest exception handler. A matching handler is defined to be one which would return true if the message #handles: was sent to its exception selector with the signaled exception as the argument. If a matching handler is found, the exception action of the handler is evaluated in the exception environment that was current when the handler was created and the state of the current exception environment is preserved as the signaling environment. The exception action is evaluated as if the message #value: were sent to it with a passed as its argument. The is derived from the signaled exception in an implementation dependent manner. If the evaluation of the exception action returns normally (as if it had returned from the #value: message), the handler environment is restored and the value returned from the exception action is returned as the value of the #on:do: message that created the handler. Before returning, any active #ensure: or #ifCurtailed: termination blocks created during evaluation of the receiver of the #on:do: message are evaluated. If a matching handler is not found when the exception environment is searched, the default action for the signaled exception is performed. This is accomplished as if the message #defaultAction were sent to the object derived from the signaled exception. The #defaultAction method is executed in the context of the signaling environment. If the signaled exception is resumable the value returned from the #defaultAction method is returned as the value of the #signal message. If the signaled exception is not resumable the action taken upon completion of the #defaultAction method is implementation defined. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'Object' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'signal: signalerText' forProtocolNamed: #'exceptionSignaler' synopsis: 'Signal the occurrence of an exceptional condition with a specified textual description. ' definedIn: 'exceptionSignaler' definition: 'Associated with the receiver is an called the signaled exception. The message text of the signaled exception is set to the value of signalerText, and then the exception is signaled in the same manner as if the message #signal had been sent to the receiver. Note that this message does not return in some circumstances. The situations in which it does return and the returned value, if any, are the same as specified for the #signal message. ' refinedIn: '' refinement: '' parameters: #( #('signalerText' 'readableString' #'unspecified') ) returnValues: #( #( 'Object' #'unspecified') ) errors: '' ! (1 protocolManager newProtocolNamed: #'extensibleCollection' conformsToProtocolNames: #(#'collection') ) protocolDescription: ' Provides protocol for adding elements to and removing elements from a variable sized collection. ' ! 1 protocolManager newMessagePattern: 'add: newElement' forProtocolNamed: #'extensibleCollection' synopsis: 'Add newElement to the receiver''s elements. ' definedIn: 'extensibleCollection' definition: 'This message adds a newElement to the receiver. Unless specifically refined, the position of the newElement in the element traversal order is unspecified. Conformant protocols may place restrictions on the type of objects that are valid elements. Unless otherwise specified, any object is acceptable. ' refinedIn: '' refinement: '' parameters: #( #('newElement' 'Object' #'captured') ) returnValues: #() errors: '' ! 1 protocolManager newMessagePattern: 'addAll: newElements' forProtocolNamed: #'extensibleCollection' synopsis: 'Add each element of newElements to the receiver''s elements. ' definedIn: 'extensibleCollection' definition: 'This message adds each element of newElements to the receiver. The operation is equivalent to adding each element of newElements to the receiver using the #add: message with the element as the parameter. The newElements are traversed in the order specified by the #do: message for newElements. ' refinedIn: '' refinement: '' parameters: #( #('newElements' 'collection' #'unspecified') ) returnValues: #() errors: '' ! 1 protocolManager newMessagePattern: 'remove: oldElement' forProtocolNamed: #'extensibleCollection' synopsis: 'Remove the first element of the receiver which is equivalent to oldElement and return the removed element. ' definedIn: 'extensibleCollection' definition: 'Remove the first element of the receiver which is equivalent to oldElement and return the removed element. The elements are tested in the same order in which they would be enumerated by the message #do: for this receiver. The behavior is undefined if an object equivalent to oldElement is not found. ' refinedIn: '' refinement: '' parameters: #( #('oldElement' 'Object' #'uncaptured') ) returnValues: #( #( 'Object' #'state') ) errors: '' ! 1 protocolManager newMessagePattern: 'remove: oldElement ifAbsent: exceptionHandler' forProtocolNamed: #'extensibleCollection' synopsis: 'Remove the first element of the receiver which is equivalent to oldElement. If it is not found, answer the result of evaluating exceptionHandler. ' definedIn: 'extensibleCollection' definition: 'The first element of the receiver which is equivalent to oldElement is removed from the receiver''s elements. If no such element is found, answer the result of evaluating exceptionHandler with no parameters. The elements are tested in the same order in which they would be enumerated by the message #do: for this receiver. ' refinedIn: '' refinement: '' parameters: #( #('oldElement' 'Object' #'uncaptured') #('exceptionHandler' 'niladicValuable' #'uncaptured') ) returnValues: #( #( 'Object' #'state') #( 'Object' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'removeAll: oldElements' forProtocolNamed: #'extensibleCollection' synopsis: 'For each element in oldElements, remove the first element from the receiver which is equivalent to this element. ' definedIn: 'extensibleCollection' definition: 'This message is used to remove each element of a given collection from the receiver''s elements. The operation is defined to be equivalent to removing each element of oldElements from the receiver using the #remove: message with the element as the parameter. The behavior is undefined if any element of oldElements is not found. ' refinedIn: '' refinement: '' parameters: #( #('oldElements' 'collection' #'uncaptured') ) returnValues: #() errors: '' ! (1 protocolManager newProtocolNamed: #'failedMessage' conformsToProtocolNames: #(#'Object') ) protocolDescription: ' This protocol describes the behavior of objects that represent a message that was sent to an object, but was not understood by that object. ' ! 1 protocolManager newMessagePattern: 'arguments' forProtocolNamed: #'failedMessage' synopsis: 'Answer the arguments of the message that could not be sent. ' definedIn: 'failedMessage' definition: 'Return a collection containing the arguments of the message that could not be sent. The elements of the collection are ordered, from the first element to the last element, in the same order as the arguments of the message, from left to right. If the message had no arguments, the collection will be empty. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'sequencedReadableCollection' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'selector' forProtocolNamed: #'failedMessage' synopsis: 'Answer the selector of the message that could not be sent. ' definedIn: 'failedMessage' definition: 'Answer the selector of the message that could not be sent. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'selector' #'unspecified') ) errors: '' ! (1 protocolManager newProtocolNamed: #'FileStream' conformsToProtocolNames: #(#'sequencedStream') ) protocolDescription: ' Provides protocol for streams over external files. The external file serves as the stream backing store. When objects are read or written from a file stream they must be translated from or two an external data representation. File streams have an external stream type that is specified when the stream is created. The external stream type defines the data translation and the sequence value type for the stream. External stream types are specified using objects. The standard defines the following external stream types: #''binary'' The external data is treated as sequence of 8-bit bytes. The sequence value type is with values restricted to the range 0 to 255. #''text'' The external data is treated as a sequenced of 8-bit characters encoded using an implementation defined external character set. The sequence value type is restricted to those specific characters that may be represented in the external character set. Implementations may define other external stream types. Rational The file stream capability specified in the standard was motivated by the desire to support a useful, yet minimal set of functionality and to take as a guide (i.e. subset) the Posix standard. There is specification only for the creation and use of readable and writeable file streams. There is not support for read/write file streams. Nor is there any specification of file or directory manipulation, as these facilities are considered by the Committee to be too platform-dependent and too implementation-dependent to standardize at this time, and it is felt that streaming is adequate. In addition, we only support the most common subset of the Posix file stream creation modes, rather than the full set. We also considered the tradeoffs of specifying a wide range of creation messages, but decided that one fully-functional message and one most-typical creation message for each of read and write file streams would be adequate. Implementations are not prohibited from providing more options. ' ! 1 protocolManager newMessagePattern: 'contents' forProtocolNamed: #'FileStream' synopsis: 'Returns a collection containing the complete contents of the stream. ' definedIn: 'sequencedStream' definition: 'Returns a collection that contains the receiver''s past and future sequence values, in order. The size of the collection is the sum of the sizes of the past and future sequence values. ' refinedIn: 'FileStream' refinement: 'If the external stream type is #''binary'' the returned collection conforms to . If the external stream type is #''text'' the returned collection conforms to . ' parameters: #() returnValues: #( #( 'String' #'new') #( 'ByteArray' #'new') ) errors: '' ! 1 protocolManager newMessagePattern: 'externalType' forProtocolNamed: #'FileStream' synopsis: 'Returns a symbol that identifies the external stream type of the receiver. ' definedIn: 'FileStream' definition: 'Return the symbol that identifies the external stream type of the receiver. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'symbol' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'isBinary' forProtocolNamed: #'FileStream' synopsis: 'Answer wthether the receiver''s data is binary. ' definedIn: 'FileStream' definition: 'Answer true if the sequence value type conforms to . Otherwise answer false. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'boolean' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'isText' forProtocolNamed: #'FileStream' synopsis: 'Answer whether the receiver''s data is characters. ' definedIn: 'FileStream' definition: 'Answer true if the sequence value type conforms to . Otherwise answer false. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'boolean' #'unspecified') ) errors: '' ! (1 protocolManager newProtocolNamed: #'FileStream factory' conformsToProtocolNames: #(#'Object') ) protocolDescription: ' provides for the creation of objects conforming to the or protocols. Standard Globals FileStream Conforms to the protocol . Its program element type is unspecified. This is a factory for collections that conform to and . ' ! 1 protocolManager newMessagePattern: 'read: aString' forProtocolNamed: #'FileStream factory' synopsis: 'Returns a read file stream that reads text from the file with the given name. ' definedIn: 'FileStream factory' definition: 'The result is the same as if the message #read:type: was sent to the receiver with fileId as the first argument and the symbol #''text'' as the second argument. ' refinedIn: '' refinement: '' parameters: #( #('aString' 'String' #'unspecified') ) returnValues: #( #( 'readFileStream' #'new') ) errors: 'As defined by #read:type: ' ! 1 protocolManager newMessagePattern: 'read: fileType type: fileId' forProtocolNamed: #'FileStream factory' synopsis: 'Returns a read file stream that reads from the file with the given name. ' definedIn: 'FileStream factory' definition: 'Locate an external file that is identified by the value of fileID. The syntax of the fileID string is implementation defined. Return an object conforming to whose future sequence values initially consist of the elements of the external file and which initially has no past sequence values. The ordering of the sequence values is the same as the ordering within the external file. The external file serves as the stream backing store of the returned object. The value of fileType determines the external stream type and sequence value type of the result object. ' refinedIn: '' refinement: '' parameters: #( #('fileId' 'readableString' #'unspecified') #('fileType' 'symbol' #'unspecified') ) returnValues: #( #( 'readFileStream' #'new') ) errors: 'It is an error if the file does not exist, or if the user does not have read access to the file. ' ! 1 protocolManager newMessagePattern: 'write: fileId' forProtocolNamed: #'FileStream factory' synopsis: 'Returns a write file stream that writes text to the file with the given name. ' definedIn: 'FileStream factory' definition: 'The result is the same as if the message #write:mode:check:type: was sent to the receiver with fileId as the first argument, #''create'' as the second argument, false as the third argument, and the symbol #''text'' as the fourth argument. ' refinedIn: '' refinement: '' parameters: #( #('fileId' 'readableString' #'unspecified') ) returnValues: #( #( 'writeFileStream' #'new') ) errors: 'As defined by #write:mode:check:type: ' ! 1 protocolManager newMessagePattern: 'write: mode mode: fileId' forProtocolNamed: #'FileStream factory' synopsis: 'Returns a write file stream that writes text to the file with the given name. ' definedIn: 'FileStream factory' definition: 'The result is the same as if the message #write:mode:check:type: was sent to the receiver with fileId as the first argument, mode as the second argument, false as the third argument, and the symbol #''text'' as the fourth argument. ' refinedIn: '' refinement: '' parameters: #( #('mode' 'symbol' #'unspecified') #('fileId' 'readableString' #'unspecified') ) returnValues: #( #( 'writeFileStream' #'new') ) errors: 'As defined by #write:mode:check:type: ' ! 1 protocolManager newMessagePattern: 'write: fileType mode: fileID check: mode type: check' forProtocolNamed: #'FileStream factory' synopsis: 'Returns a write file stream that writes to the file with the given name. ' definedIn: 'FileStream factory' definition: 'Depending upon the values of check and mode, either create a new external file or locate an existing external file that is identified by the value of fileID. The syntax of the fileID string is implementation defined. Return an object conforming to . The external file serves as the stream backing store of the returned object. The returned object is a write-back stream. The value of fileType determines the external stream type and sequence value type of the result object. Valid values for mode are: #''create'', #''append'', and #''truncate''. The meaning of these values are: #''create'' create a new file, with initial position at the beginning #''append'' use an existing file, with initial position at its end #''truncate'' use an existing file, initially truncating it. The value of mode determines the initial state of the past sequence values and future sequence values of the result object. If mode is #''create'' or #''truncate'' the past sequence values and future sequence values are both initially empty. If mode is #''append'' the past sequence values initially consist of the elements of the external file and future sequence values is initially empty. The ordering of the sequence values is the same as the ordering within the external file. The check flag determines whether the file specified by fileID must exist or not exist. If mode = #''create'' and check = false and the file exists, then the existing file is used. If mode = #''append'' and check = false and the file does not exist, then it is created. If mode = #''truncate'' and check = false and the file does not exist, then it is created. This operation is undefined if a value other than #''create'', #''append'' or #''truncate'' is used as the mode argument. ' refinedIn: '' refinement: '' parameters: #( #('mode' 'symbol' #'unspecified') #('check' 'boolean' #'unspecified') #('fileID' 'readableString' #'unspecified') #('fileType' 'symbol' #'unspecified') ) returnValues: #( #( 'writeFileStream' #'new') ) errors: 'If mode = #create and check = true and the file exists. If mode = #append and check = true and the file does not exist. If mode = #truncate and check = true and the file does not exist. If the user does not have write permissions for the file. If the user does not have creation permissions for a file that is to be created. ' ! (1 protocolManager newProtocolNamed: #'Float' conformsToProtocolNames: #(#'number') ) protocolDescription: ' Represents a floating point representation for real numbers, whose value may be approximate. Provides protocol for performing trigonometry, exponentiation, and conversion on numerical quantities. Operations can produce results that are outside the set of representable numbers, or that are mathematically undefined. It is implementation defined whether errors are raised when results are not representable or if unrepresentable results are wrapped in implementation-defined continuation values or their equivalent. The effect of underflow and overflow is therefore implementation defined. It is erroneous if the result of an operation is mathematically undefined. ' ! 1 protocolManager newMessagePattern: '= comparand' forProtocolNamed: #'Float' synopsis: 'Object equivalence test. ' definedIn: 'Object' definition: 'This message tests whether the receiver and the comparand are equivalent objects at the time the message is processed. Return true if the receiver is equivalent to comparand. Otherwise return false. The meaning of "equivalent" cannot be precisely defined but the intent is that two objects are considered equivalent if they can be used interchangeably. Conforming protocols may choose to more precisely define the meaning of "equivalent". The value of receiver = comparand is true if and only if the value of comparand = receiver would also be true. If the value of receiver = comparand is true then the receiver and comparand must have equivalent hash values. Or more formally: receiver = comparand ? receiver hash = comparand hash The equivalence of objects need not be temporally invariant. Two independent invocations of #= with the same receiver and operand objects may not always yield the same results. Note that a collection that uses #= to discriminate objects may only reliably store objects whose hash values do not change while the objects are contained in the collection. ' refinedIn: 'Float' refinement: 'Answer true if the operand is a number which represents the same floating point number as the receiver, as specified by the ISO/IEC 10967 operation eqf. If the comparand and the receiver do not conform to the same protocol, they are converted according to the Default Conversion Table. ' parameters: #( #('comparand' 'Object' #'uncaptured') ) returnValues: #( #( 'boolean' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'arcCos' forProtocolNamed: #'Float' synopsis: ' Answer the inverse cosine of the receiver in radians. ' definedIn: 'Float' definition: 'Answer the inverse cosine of the receiver in radians, as specified by the ISO/IEC 10967 trigonometric operation arccosf. Within the limits of precision, the following invariant holds: receiver arcCos cos = receiver It is erroneous if the absolute value of the receiver is greater than 1. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'Float' #'unspecified') ) errors: '|receiver| > 1 ' ! 1 protocolManager newMessagePattern: 'arcSin' forProtocolNamed: #'Float' synopsis: 'Answer the inverse sine of the receiver in radians. ' definedIn: 'Float' definition: 'Answer the inverse sine of the receiver in radians, as specified by the ISO/IEC 10967 trigonometric operation arcsinf. Within the limits of precision, the following invariant holds: receiver arcSin sin = receiver It is erroneous if the absolute value of the receiver is greater than 1. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'Float' #'unspecified') ) errors: '|receiver| > 1 ' ! 1 protocolManager newMessagePattern: 'arcTan' forProtocolNamed: #'Float' synopsis: 'Answer the inverse tangent of the receiver in radians. ' definedIn: 'Float' definition: 'Answer the inverse tangent of the receiver in radians, as specified by the ISO/IEC 10967 trigonometric operation arctanf. Within the limits of precision, the following invariant holds: receiver arcTan tan = receiver ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'Float' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'cos' forProtocolNamed: #'Float' synopsis: 'Answer the cosine of the receiver in radians. ' definedIn: 'Float' definition: 'Answer a equal to the cosine of the receiver in radians, as specified by the ISO/IEC 10967 trigonometric operation cosf. The effect of underflow is implementation defined. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'Float' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'degreesToRadians' forProtocolNamed: #'Float' synopsis: 'Answer the receiver converted from degrees to radians. ' definedIn: 'Float' definition: 'Answer a floating-point number representing the receiver converted from degrees to radians. The result is equivalent to multiplying the receiver by (Pi / 180). ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'Float' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'exp' forProtocolNamed: #'Float' synopsis: 'Answer the natural exponential of the receiver. This is the inverse of #ln. ' definedIn: 'Float' definition: 'Answer a floating-point number representing the irrational number e (= 2.718281...) raised to the power of the receiver, as specified by the ISO/IEC 10967 operation expf. This is the inverse of the #ln message. The effect of underflow and overflow is implementation defined. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'Float' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'floorLog: operand' forProtocolNamed: #'Float' synopsis: 'Answer the largest integer less than or equal to the logarithm to the base operand of the receiver. ' definedIn: 'Float' definition: 'Answer the largest integer less than or equal to the power to which the operand must be raised to obtain the receiver (that is, the logarithm base operand of the receiver). The result is undefined if the receiver is less than or equal to zero, or if the operand is less than or equal to 1. ' refinedIn: '' refinement: '' parameters: #( #('operand' 'number' #'uncaptured') ) returnValues: #( #( 'integer' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'ln' forProtocolNamed: #'Float' synopsis: 'Answer the natural logarithm of the receiver. ' definedIn: 'Float' definition: 'Answer the natural logarithm of the receiver, as specified by the ISO/IEC 10967 operation lnf., which is a floating-point number representing the power to which the irrational number e (= 2.718281...) must be raised to obtain the receiver. This is the inverse of the #exp message. The result is undefined if the receiver is less than or equal to zero. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'Float' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'log: operand' forProtocolNamed: #'Float' synopsis: 'Answer the logarithm to the base operand of the receiver. ' definedIn: 'Float' definition: 'Answer the logarithm to the base operand of the receiver, as specified by the ISO/IEC 10967 operation logff, which is a floating-point number representing the power to which operand must be raised to obtain the receiver. The receiver must be positive, and operand must be greater than one. This is the inverse of the #raisedTo: message. The result is undefined if operand equals 1, if operand is less than or equal to zero, or if the receiver is less than or equal to zero. The effect of underflow and overflow is implementation defined. ' refinedIn: '' refinement: '' parameters: #( #('operand' 'number' #'uncaptured') ) returnValues: #( #( 'Float' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'printString' forProtocolNamed: #'Float' synopsis: 'Return a string that describes the receiver. ' definedIn: 'Object' definition: 'A string consisting of a sequence of characters that describe the receiver are returned as the result. The exact sequence of characters that describe an object are implementation defined. ' refinedIn: 'Float' refinement: 'Answer a string which is a valid Smalltalk literal representation approximately equal to the receiver. An exponent literal form is produced if the value of the exponent is greater than the precision of the receiver. ' parameters: #() returnValues: #( #( 'readableString' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'radiansToDegrees' forProtocolNamed: #'Float' synopsis: 'Answer the receiver converted from radians to degrees. ' definedIn: 'Float' definition: 'Answer a floating-point number representing the receiver converted from radians to degrees. The result is equivalent to multiplying the receiver by (180 / Pi). ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'Float' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'sin' forProtocolNamed: #'Float' synopsis: 'Answer the sine of the receiver. ' definedIn: 'Float' definition: 'Answer a floating-point number equal to the sine of the receiver in radians, as specified by the ISO/IEC 10967 trigonometric operation sinF. The effect of underflow is implementation defined. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'Float' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'tan' forProtocolNamed: #'Float' synopsis: 'Answer the tangent of the receiver. ' definedIn: 'Float' definition: 'Answer a floating-point number equal to the tangent of the receiver in radians, as specified by the ISO/IEC 10967 trigonometric root operation tanf. The effect of underflow and overflow is implementation defined. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'Float' #'unspecified') ) errors: '' ! (1 protocolManager newProtocolNamed: #'floatCharacterization' conformsToProtocolNames: #(#'Object') ) protocolDescription: ' Objects supporting this protocol characterize a floating point representation for real numbers. These characterizations are required by ISO/IEC 10967 for each precision of floating point numbers provided by an implementation. Standard Globals Float Conforms to the protocol . Its language element type is implementation defined. The value of this global is equivalent to the value of one of the globals: FloatE, FloatE, or FloatE. FloatE Conforms to the protocol . Its language element type is implementation defined. This global characterizes the floating point representation corresponding to the ''e'' floating point literal syntax. FloatD Conforms to the protocol . Its language element type is implementation defined. This global characterizes the floating point representation corresponding to the ''d'' floating point literal syntax. FloatQ Conforms to the protocol . Its language element type is implementation defined. This global characterizes the floating point representation corresponding to the ''q'' floating point literal syntax. ' ! 1 protocolManager newMessagePattern: 'denormalized' forProtocolNamed: #'floatCharacterization' synopsis: 'Indication of whether the characterized floating point object representation allows denormalized values. ' definedIn: 'floatCharacterization' definition: 'Report a boolean indicating whether the characterized floating point object representation contains denormalized values. This satisfies the ISO/IEC 10967 floating point characterization requirement denorm. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'boolean' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'e' forProtocolNamed: #'floatCharacterization' synopsis: 'The closest floating point approximation of the irrational number e. ' definedIn: 'floatCharacterization' definition: 'Return the closest floating point approximation of the irrational number e for the characterized floating point object representation. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'Float' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'emax' forProtocolNamed: #'floatCharacterization' synopsis: 'The largest exponent of the characterized floating point object representation. ' definedIn: 'floatCharacterization' definition: 'Report the largest exponent allowed by the characterized floating point object representation, providing the upper bound of the range of representable floating point numbers. This satisfies the ISO/IEC 10967 floating point characterization requirement emax. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'integer' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'emin' forProtocolNamed: #'floatCharacterization' synopsis: 'The smallest exponent of the characterized floating point object representation. ' definedIn: 'floatCharacterization' definition: 'Report the smallest exponent allowed by the characterized floating point object representation, providing the lower bound of the range of representable floating point numbers. This satisfies the ISO/IEC 10967 floating point characterization requirement emin. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'integer' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'epsilon' forProtocolNamed: #'floatCharacterization' synopsis: 'The maximum relative spacing in the characterized floating point object representation. ' definedIn: 'floatCharacterization' definition: 'Report the maximum relative spacing in the characterized floating point object representation, satisfying the ISO/IEC 10967 floating point characterization requirement epsilon. The return value is equal to self radix raisedTo: (1 - self precision) ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'Float' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'fmax' forProtocolNamed: #'floatCharacterization' synopsis: 'The largest value allowed by the characterized floating point object representation. ' definedIn: 'floatCharacterization' definition: 'Report the largest value allowed by the characterized floating point object representation. This satisfies the ISO/IEC 10967 floating point characterization requirement fmax, and is equal to (1 - (self radix raisedTo: self precision negated)) * self radix raisedTo: self emax ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'Float' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'fmin' forProtocolNamed: #'floatCharacterization' synopsis: 'The minimum value allowed by the characterized floating point object representation. ' definedIn: 'floatCharacterization' definition: 'Report the minimum value allowed by the characterized floating point object representation. This satisfies the ISO/IEC 10967 floating point characterization requirement fmin. If the described representation contains normalized values, then the result is equal to the result of sending #fminNormalized to the receiver, otherwise the result is equal to the result of sending #fminDenormalized to the receiver. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'Float' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'fminDenormalized' forProtocolNamed: #'floatCharacterization' synopsis: 'The minimum denormalized value allowed by the characterized floating point object representation. ' definedIn: 'floatCharacterization' definition: 'Report the minimum denormalized value allowed by the characterized floating point object representation. This satisfies the ISO/IEC 10967 floating point characterization requirement fminD, and is equal to self radix raisedTo: (self emin - self precision) The result is unspecified if denormalized values are not allowed by the characterized representation. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'Float' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'fminNormalized' forProtocolNamed: #'floatCharacterization' synopsis: 'The minimum normalized value allowed by the characterized floating point object representation. ' definedIn: 'floatCharacterization' definition: 'Report the minimum normalized value allowed by the characterized floating point object representation. This satisfies the ISO/IEC 10967 floating point characterization requirement fminN, and is equal to self radix raisedTo: (self emin - 1). ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'Float' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'pi' forProtocolNamed: #'floatCharacterization' synopsis: 'The closest floating point approximation to Pi. ' definedIn: 'floatCharacterization' definition: 'Return the closest floating point approximation to Pi for the characterized floating point object representation. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'Float' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'precision' forProtocolNamed: #'floatCharacterization' synopsis: 'The precision of the characterized floating point object representation. ' definedIn: 'floatCharacterization' definition: 'Report the precision, the number of radix digits, of floating point objects of the characterized floating point object representation. This satisfies the ISO/IEC 10967 floating point characterization requirement p. The result must be greater than or equal to two. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'integer' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'radix' forProtocolNamed: #'floatCharacterization' synopsis: 'The radix of the characterized floating point object representation. ' definedIn: 'floatCharacterization' definition: 'Report the base, or radix, of the characterized floating point object representation. This satisfies the ISO/IEC 10967 floating point characterization requirement r. The result must be an even number greater than or equal to two. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'integer' #'unspecified') ) errors: '' ! (1 protocolManager newProtocolNamed: #'Fraction' conformsToProtocolNames: #(#'rational') ) protocolDescription: ' An exact representation for rational numbers. It is unspecific whether the rational number are maintain in a reduced form but messages that reveal the numerator and denominator answer values as if the fraction was reduced. ' ! 1 protocolManager newMessagePattern: 'denominator' forProtocolNamed: #'Fraction' synopsis: 'Answer the denominator of the receiver. ' definedIn: 'rational' definition: 'Treating the receiver as a fraction, answer the lowest common denominator of the recevier. ' refinedIn: 'Fraction' refinement: 'Answer the integer smallest integer denominator of the receiver. ' parameters: #() returnValues: #( #( 'integer' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'numerator' forProtocolNamed: #'Fraction' synopsis: 'Answer the numerator of the receiver. ' definedIn: 'rational' definition: 'Treating the receiver as a fraction, answer the integer numerator. ' refinedIn: 'Fraction' refinement: 'Answer the integer numerator of the receiver reduced to its lowest denominator. ' parameters: #() returnValues: #( #( 'integer' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'printString' forProtocolNamed: #'Fraction' synopsis: '' definedIn: 'Object' definition: 'A string consisting of a sequence of characters that describe the receiver are returned as the result. The exact sequence of characters that describe an object are implementation defined. ' refinedIn: 'Fraction' refinement: 'Answer a string consisting of the numerator and denominator for a reduced fraction, equivalent to the receiver . The numerator and denominator are separated by the character ''/'' as follows: numerator/denominator ' parameters: #() returnValues: #( #( 'readableString' #'unspecified') ) errors: '' ! (1 protocolManager newProtocolNamed: #'Fraction factory' conformsToProtocolNames: #(#'Object') ) protocolDescription: ' Represents protocol for creating an exact representation for rational numbers. Standard Globals Fraction Conforms to the protocol . Its language element type is implementation defined. ' ! 1 protocolManager newMessagePattern: 'numerator: bottom denominator: top' forProtocolNamed: #'Fraction factory' synopsis: 'Answer a new fraction whose numerator is top, and whose denominator is bottom. ' definedIn: 'Fraction factory' definition: 'Answer a new fraction whose numerator is top, and whose denominator is bottom. It is unspecified whether the result is reduced to the smallest possible denominator. If (top = bottom) or ( |bottom = 1) the result conforms to otherwise it conforms to . If bottom = 0 a ZeroDivide exception is signaled. ' refinedIn: '' refinement: '' parameters: #( #('bottom' 'integer' #'unspecified') #('top' 'integer' #'unspecified') ) returnValues: #( #( 'Fraction' #'unspecified') #( 'integer' #'unspecified') ) errors: '' ! (1 protocolManager newProtocolNamed: #'gettableStream' conformsToProtocolNames: #(#'Object') ) protocolDescription: ' An object conforming to can read objects from its future sequence values. ' ! 1 protocolManager newMessagePattern: 'atEnd' forProtocolNamed: #'gettableStream' synopsis: 'Returns a Boolean indicating whether the receiver is at the end of its values. ' definedIn: 'gettableStream' definition: 'Return true if the receiver has no future sequence values available for reading. Return false otherwise. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'boolean' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'do: operation' forProtocolNamed: #'gettableStream' synopsis: 'Evaluates the argument with each receiver future sequence value, terminating evaluation when there are no more future sequence values. ' definedIn: 'gettableStream' definition: 'Each member of the receiver''s future sequence values is, in turn, removed from the future sequence values; appended to the past sequence values; and, passed as the argument to an evaluation of operand. The argument, operation, is evaluated as if sent the message #value:. The number of evaluations is equal to the initial size of the receiver''s future sequence values. If there initially are no future sequence values, operation is not evaluated. The future sequence values are used as arguments in their sequence order. The result is undefined if any evaluation of operand changes the receiver''s future sequence values ' refinedIn: '' refinement: '' parameters: #( #('operation' 'monadicValuable' #'uncaptured') ) returnValues: #() errors: '' ! 1 protocolManager newMessagePattern: 'next' forProtocolNamed: #'gettableStream' synopsis: 'Return the next object in the receiver. ' definedIn: 'gettableStream' definition: 'The first object is removed from the receiver''s future sequence values and appended to the end of the receiver''s past sequence values. That object is returned as the value of the message. The returned object must conform to the receiver''s sequence value type. The result is undefined if there the receiver has no future sequence values. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'Object' #'state') ) errors: '' ! 1 protocolManager newMessagePattern: 'next: amount' forProtocolNamed: #'gettableStream' synopsis: 'Returns a collection of the next amount objects in the stream. ' definedIn: 'gettableStream' definition: 'A number of objects equal to amount are removed from the receiver''s future sequence values and appended, in order, to the end of the receiver''s past sequence values. A collection whose elements consist of those objects, in the same order, is returned. If amount is equal to 0 an empty collection is returned. The result is undefined if amount is larger than the number of objects in the receiver''s future sequence values. ' refinedIn: '' refinement: '' parameters: #( #('amount' 'integer' #'uncaptured') ) returnValues: #( #( 'sequencedReadableCollection' #'new') ) errors: 'amount < 0 ' ! 1 protocolManager newMessagePattern: 'nextLine' forProtocolNamed: #'gettableStream' synopsis: 'Reads the next line from the stream. ' definedIn: 'gettableStream' definition: 'Each object in the receiver''s future sequence values up to and including the first occurrence of the objects that constitute an implementation defined end-of-line sequence is removed from the future sequence values and appended to the receiver''s past sequence values. All of the transfered objects, except the end-of-line sequence objects, are collected, in order, as the elements of a string that is the return value. The result is undefined if there are no future sequence values in the receiver or if the future-sequence values do not include the end-of-line sequence. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'readableString' #'new') ) errors: 'If any of the future sequence values to be returned do not conform to the protocol . ' ! 1 protocolManager newMessagePattern: 'nextMatchFor: anObject' forProtocolNamed: #'gettableStream' synopsis: 'Reads the next object from the stream and returns true if the object is equivalent to the argument and false if not. ' definedIn: 'gettableStream' definition: 'The first object is removed from the receiver''s future sequence value and appended to the end of the receiver''s past sequence values. The value that would result from sending #= to the object with anObject as the argument is returned. The results are undefined if there are no future sequence values in the receiver. ' refinedIn: '' refinement: '' parameters: #( #('anObject' 'Object' #'uncaptured') ) returnValues: #( #( 'boolean' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'peek' forProtocolNamed: #'gettableStream' synopsis: 'Returns the next object in the receiver''s future sequence values without advancing the receiver''s position. Returns nil if the receiver is at end of stream. ' definedIn: 'gettableStream' definition: 'Returns the first object in the receiver''s future sequence values. The object is not removed from the future sequence values. The returned object must conform to the receiver''s sequence value type. Returns nil if the receiver has no future sequence values. The return value will also be nil if the first future sequence object is nil. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'Object' #'state') ) errors: '' ! 1 protocolManager newMessagePattern: 'peekFor: anObject' forProtocolNamed: #'gettableStream' synopsis: 'Peeks at the next object in the stream and returns true if it matches the argument, and false if not. ' definedIn: 'gettableStream' definition: 'Returns the result of sending #= to the first object in the receiver''s future sequence values with anObject as the argument. Returns false if the receiver has no future sequence values. ' refinedIn: '' refinement: '' parameters: #( #('anObject' 'Object' #'uncaptured') ) returnValues: #( #( 'boolean' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'skip: amount' forProtocolNamed: #'gettableStream' synopsis: 'Skips the next amount objects in the receiver''s future sequence values. ' definedIn: 'gettableStream' definition: 'A number of objects equal to the lesser of amount and the size of the receiver''s future sequence values are removed from the receiver''s future sequence values and appended, in order, to the end of the receiver''s past sequence values. ' refinedIn: '' refinement: '' parameters: #( #('amount' 'integer' #'uncaptured') ) returnValues: #() errors: '' ! 1 protocolManager newMessagePattern: 'skipTo: anObject' forProtocolNamed: #'gettableStream' synopsis: 'Sets the stream to read the object just after the next occurrence of the argument and returns true. If the argument is not found before the end of the stream is encountered, false is returned. ' definedIn: 'gettableStream' definition: 'Each object in the receiver''s future sequence values up to and including the first occurrence of an object that is equivalent to anObject is removed from the future sequence values and appended to the receiver''s past sequence values. If an object that is equivalent to anObject is not found in the receiver''s future sequence values, all of the objects in future sequence values are removed from future sequence values and appended to past sequence values. If an object equivalent to anObject is not found false is returned. Otherwise return true. ' refinedIn: '' refinement: '' parameters: #( #('anObject' 'Object' #'uncaptured') ) returnValues: #( #( 'boolean' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'upTo: anObject' forProtocolNamed: #'gettableStream' synopsis: 'Returns a collection of all of the objects in the receiver up to, but not including, the next occurrence of the argument. Sets the stream to read the object just after the next occurrence of the argument. If the argument is not found and the end of the stream is encountered, an ordered collection of the objects read is returned. ' definedIn: 'gettableStream' definition: 'Each object in the receiver''s future sequence values up to and including the first occurrence of an object that is equivalent to anObject is removed from the future sequence values and appended to the receiver''s past sequence values. A collection, containing, in order, all of the transferred objects except the object (if any) that is equivalent to anObject is returned. If the receiver''s future sequence values is initially empty, an empty collection is returned. ' refinedIn: '' refinement: '' parameters: #( #('anObject' 'Object' #'uncaptured') ) returnValues: #( #( 'sequencedReadableCollection' #'new') ) errors: '' ! (1 protocolManager newProtocolNamed: #'IdentityDictionary' conformsToProtocolNames: #(#'abstractDictionary') ) protocolDescription: ' This protocol defines the behavior of unordered collections whose elements can be accessed using an explicitly-assigned, external key. Key equivalence is defined as sending the #== message. ' ! (1 protocolManager newProtocolNamed: #'IdentityDictionary factory' conformsToProtocolNames: #(#'Dictionary factory') ) protocolDescription: ' This protocol defines the behavior of objects that can be used to create objects that conform to the protocol . Standard Globals IdentityDictionary Conforms to the protocol . Its language element type is unspecified. This is a factory and discriminator for collections that conform to . ' ! 1 protocolManager newMessagePattern: 'new' forProtocolNamed: #'IdentityDictionary factory' synopsis: 'Create a new object. ' definedIn: 'instantiator' definition: 'Return a newly created object initialized to a standard initial state. ' refinedIn: 'IdentityDictionary factory' refinement: 'Return a new that is optimized to store an implementation defined number of elements. The new collection initially contains no elements. ' parameters: #() returnValues: #( #( 'IdentityDictionary' #'new') ) errors: '' ! 1 protocolManager newMessagePattern: 'new: count' forProtocolNamed: #'IdentityDictionary factory' synopsis: 'Create a new collection. The parameter count constrains the number of elements in the result. ' definedIn: 'collection factory' definition: 'Return a new collection that has space for at least count elements. Conforming protocols may refine this message. In particular, the effect of the parameter count should be specified in refinements. It can be used to specify the exact number of elements, the minimum number, or in some cases can even be interpreted as a hint from the programmer, with no guarantee that the requested number of instance variables will actually be allocated. Unless otherwise stated the initial values of elements of the new instance of the receiver are unspecified. ' refinedIn: 'IdentityDictionary factory' refinement: 'The parameter count represents a hint for space allocation. The new collection is to optimized to contain count elements. The new collection initially contains no elements. The new collection conforms to the protocol . ' parameters: #( #('count' 'integer' #'unspecified') ) returnValues: #( #( 'IdentityDictionary' #'new') ) errors: '' ! 1 protocolManager newMessagePattern: 'withAll: newElements' forProtocolNamed: #'IdentityDictionary factory' synopsis: 'Create a collection containing all the elements of newElements. ' definedIn: 'IdentityDictionary factory' definition: 'Return a new collection whose elements are the elements of newElements. The effect is the same as evaluating IdentityDictionary new addAll: newElements; yourself. ' refinedIn: '' refinement: '' parameters: #( #('newElements' 'abstractDictionary' #'unspecified') ) returnValues: #( #( 'IdentityDictionary' #'new') ) errors: '' ! (1 protocolManager newProtocolNamed: #'initializableCollection factory' conformsToProtocolNames: #(#'collection factory') ) protocolDescription: ' This protocol defines the behavior of objects that can be used to create non-empty collections. ' ! 1 protocolManager newMessagePattern: 'with: element1' forProtocolNamed: #'initializableCollection factory' synopsis: 'Create a collection initially containing the argument element ' definedIn: 'initializableCollection factory' definition: 'Return a new collection containing element1. The collection contains the argument as its element. Conforming protocols may impose restrictions on the values of the arguments and hence the element types. ' refinedIn: '' refinement: '' parameters: #( #('element1' 'Object' #'captured') ) returnValues: #( #( 'collection' #'new') ) errors: 'If the argument does not meet the element type constraints of the result object ' ! 1 protocolManager newMessagePattern: 'with: element1 with: element2' forProtocolNamed: #'initializableCollection factory' synopsis: 'Create a collection initially containing the argument elements ' definedIn: 'initializableCollection factory' definition: 'Return a new collection containing both elements. The collection contains the arguments as its elements. Conforming protocols may impose restrictions on the values of the arguments and hence the element types. ' refinedIn: '' refinement: '' parameters: #( #('element1' 'Object' #'captured') #('element2' 'Object' #'captured') ) returnValues: #( #( 'collection' #'new') ) errors: 'If any of the arguments do not meet the element type constraints of the result object ' ! 1 protocolManager newMessagePattern: 'with: element2 with: element1 with: element3' forProtocolNamed: #'initializableCollection factory' synopsis: 'Create a collection initially containing the argument elements ' definedIn: 'initializableCollection factory' definition: 'Return a new collection containing three of elements. The collection contains the arguments as its elements. Conforming protocols may impose restrictions on the values of the arguments and hence the element types. ' refinedIn: '' refinement: '' parameters: #( #('element2' 'Object' #'captured') #('element1' 'Object' #'captured') #('element3' 'Object' #'captured') ) returnValues: #( #( 'collection' #'new') ) errors: 'If any of the arguments do not meet the element type constraints of the result object ' ! 1 protocolManager newMessagePattern: 'with: element1 with: element3 with: element2 with: element4' forProtocolNamed: #'initializableCollection factory' synopsis: 'Create a collection initially containing the argument elements ' definedIn: 'initializableCollection factory' definition: 'Return a new collection containing four elements. The collection contains the arguments as its elements. Conforming protocols may impose restrictions on the values of the arguments and hence the element types. ' refinedIn: '' refinement: '' parameters: #( #('element2' 'Object' #'captured') #('element4' 'Object' #'captured') #('element1' 'Object' #'captured') #('element3' 'Object' #'captured') ) returnValues: #( #( 'collection' #'new') ) errors: 'If any of the arguments do not meet the element type constraints of the result object ' ! 1 protocolManager newMessagePattern: 'withAll: newElements' forProtocolNamed: #'initializableCollection factory' synopsis: 'Create a collection containing all the elements of newElements. ' definedIn: 'initializableCollection factory' definition: 'Return a new collection whose elements are the elements of newElements. Conforming protocols may impose restrictions on the values of newElements. ' refinedIn: '' refinement: '' parameters: #( #('newElements' 'collection' #'unspecified') ) returnValues: #( #( 'collection' #'new') ) errors: 'If any of the elements in newElements do not meet the element type constraints of the result object ' ! (1 protocolManager newProtocolNamed: #'instantiator' conformsToProtocolNames: #(#'Object') ) protocolDescription: ' This protocol defines the behavior of objects that can be used to create other objects without requiring any additional information. ' ! 1 protocolManager newMessagePattern: 'new' forProtocolNamed: #'instantiator' synopsis: 'Create a new object. ' definedIn: 'instantiator' definition: 'Return a newly created object initialized to a standard initial state. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'Object' #'new') ) errors: '' ! (1 protocolManager newProtocolNamed: #'integer' conformsToProtocolNames: #(#'rational') ) protocolDescription: ' Represents an abstraction for integer numbers whose value is exact. Representations must provide unbounded precision and range, hence the ISO/IEC 10967 integer type parameter bounded is bound to false. ' ! 1 protocolManager newMessagePattern: 'allMask: mask' forProtocolNamed: #'integer' synopsis: 'Answer true if all of the bits that are 1 in the binary representation of mask are 1 in the binary representation of the receiver. Answer false otherwise. ' definedIn: 'integer' definition: 'Answer true if all of the bits that are 1 in the binary representation of mask are 1 in the binary representation of the receiver. Answer false otherwise. If the receiver has fewer bits than the operand, the receiver is treated as if it were extended on the left with zeros to the length of the operand. The result is undefined if either the receiver or the operand is a negative integer. ' refinedIn: '' refinement: '' parameters: #( #('mask' 'integer' #'uncaptured') ) returnValues: #( #( 'boolean' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'anyMask: mask' forProtocolNamed: #'integer' synopsis: 'Answer true if any of the bits that are 1 in the binary representation of mask are 1 in the binary representation of the receiver. Answer false otherwise. ' definedIn: 'integer' definition: 'Answer true if any of the bits that are 1 in the binary representation of mask are 1 in the binary representation of the receiver. Answer false otherwise. If the receiver has fewer bits than the operand, the receiver is treated as if it were extended on the left with zeros to the length of the operand. Result is undefined if either the receiver or the operand is a negative integer. ' refinedIn: '' refinement: '' parameters: #( #('mask' 'integer' #'uncaptured') ) returnValues: #( #( 'boolean' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'asScaledDecimal: scale' forProtocolNamed: #'integer' synopsis: 'Answer a scaled decimal number, with a fractional precision of scale, approximating the receiver. ' definedIn: 'number' definition: 'This is a conversion message. Answer a scaled decimal number, with a fractional precision of scale, which minimizes the difference between the answered value and the receiver. The effect of underflow and overflow is implementation defined. ' refinedIn: 'integer' refinement: 'The number of significant digits of the answer is the same as the number of decimal digits in the receiver. The scale of the answer is 0. It is an error if the receiver cannot be represented within the maximum precision of the implementation. ' parameters: #( #('scale' 'integer' #'unspecified') ) returnValues: #( #( 'scaledDecimal' #'unspecified') ) errors: 'scaled decimal overflow ' ! 1 protocolManager newMessagePattern: 'bitAnd: operand' forProtocolNamed: #'integer' synopsis: 'Answer the bit-wise logical and of the receiver and the operand. ' definedIn: 'integer' definition: 'Answer the result of the bit-wise logical and of the binary representation of the receiver and the binary representation of operand. The shorter of the receiver or the operand is extended on the left with zeros to the length of the longer of the two. The result is undefined if either the receiver or the operand is a negative integer. ' refinedIn: '' refinement: '' parameters: #( #('operand' 'integer' #'uncaptured') ) returnValues: #( #( 'integer' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'bitAt: index' forProtocolNamed: #'integer' synopsis: 'Answer the value of the bit at index in the binary representation of the receiver. ' definedIn: 'integer' definition: 'Answer the value of the bit at index in the binary representation of the receiver. Answer an integer value of 0 or 1, depending upon the value of the bit at position index in the binary representation of the receiver. The least significant bit of the receiver is designated as bit 1, with indices increasing to the left. The result is undefined if either the receiver is negative. It is erroneous if index is less that or equal to zero. ' refinedIn: '' refinement: '' parameters: #( #('index' 'integer' #'uncaptured') ) returnValues: #( #( 'integer' #'unspecified') ) errors: 'index less than or equal to zero ' ! 1 protocolManager newMessagePattern: 'bitAt: index put: value' forProtocolNamed: #'integer' synopsis: 'Set the value of the bit at index in the binary representation of the receiver. ' definedIn: 'integer' definition: 'Return an integer whose binary representation is identical to the receiver with the exception that the value of the bit at position index is equal to the low order bit of value. The least significant bit of the receiver is designated as position 1, with indices increasing to the left. The result is undefined if either the receiver or value is a negative integer. It is erroneous if index is less that or equal to zero. ' refinedIn: '' refinement: '' parameters: #( #('index' 'integer' #'uncaptured') #('value' 'integer' #'uncaptured') ) returnValues: #( #( 'integer' #'unspecified') ) errors: 'index less than or equal to zero ' ! 1 protocolManager newMessagePattern: 'bitOr: operand' forProtocolNamed: #'integer' synopsis: 'Answer the logical or of the receiver and operand. ' definedIn: 'integer' definition: 'Answer the result of bit-wise logical or the binary representation of the receiver and the binary representation of operand. The shorter of the receiver or the operand is extended on the left with zeros to the length of the longer of the two. The result is undefined if either the receiver or the operand is a negative integer. ' refinedIn: '' refinement: '' parameters: #( #('operand' 'integer' #'uncaptured') ) returnValues: #( #( 'integer' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'bitShift: shift' forProtocolNamed: #'integer' synopsis: 'Answer the result of logically bit-wise shifting the binary representation of the receiver by shift bits. ' definedIn: 'integer' definition: 'If shift is positive, the receiver is shifted left and zeros (0) are shifted in on the right. If shift is negative, the receiver is shifted right and low order bits are discarded. The result is undefined if either the receiver is negative. ' refinedIn: '' refinement: '' parameters: #( #('shift' 'integer' #'uncaptured') ) returnValues: #( #( 'integer' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'bitXor: operand' forProtocolNamed: #'integer' synopsis: 'Answer bit-wise exclusive or of the receiver and the operand. ' definedIn: 'integer' definition: 'Answer the result of the bit-wise exclusive or of the binary representation of the receiver and the binary representation of operand. The shorter of the receiver or the operand is extended on the left with zeros to the length of the longer of the two. The result is undefined if either the receiver or the operand is a negative integer. ' refinedIn: '' refinement: '' parameters: #( #('operand' 'integer' #'uncaptured') ) returnValues: #( #( 'integer' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'even' forProtocolNamed: #'integer' synopsis: 'Answer true if the receiver is even. ' definedIn: 'integer' definition: 'Answer true if the receiver is divisible by 2 with no remainder. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'boolean' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'factorial' forProtocolNamed: #'integer' synopsis: 'Answer the factorial of the receiver. ' definedIn: 'integer' definition: 'Answer the product of all numbers between the receiver and 1 inclusive. The result is undefined if the receiver is negative. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'integer' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'gcd: operand' forProtocolNamed: #'integer' synopsis: 'Answer the greatest common divisor of the receiver and operand. ' definedIn: 'integer' definition: 'Answer the largest non-negative integer that divides both the receiver and operand with no remainder. Answer 0 if the receiver and operand are zero. ' refinedIn: '' refinement: '' parameters: #( #('operand' 'integer' #'uncaptured') ) returnValues: #( #( 'integer' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'highBit' forProtocolNamed: #'integer' synopsis: 'Answer the index of the most significant non-zero bit in the binary representation of the receiver. ' definedIn: 'integer' definition: 'Answer the index of the most significant non-zero bit in the binary representation of the receiver. Answer 0 if the receiver is 0. The index of the least significant bit of the receiver is 1, with indices increasing to the left. The result is undefined if the receiver is negative. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'integer' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'lcm: operand' forProtocolNamed: #'integer' synopsis: 'Answer the least common multiple of the receiver and operand. ' definedIn: 'integer' definition: 'Answer the smallest non-negative integer which is evenly divided by both the receiver and operand. Answer 0 if the receiver and operand are zero. ' refinedIn: '' refinement: '' parameters: #( #('operand' 'integer' #'uncaptured') ) returnValues: #( #( 'integer' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'noMask: mask' forProtocolNamed: #'integer' synopsis: 'Answer true if none of the bits that are 1 in the binary representation of mask are 1 in the binary representation of the receiver. Answer false otherwise. ' definedIn: 'integer' definition: 'Answer true if none of the bits that are 1 in the binary representation of mask are 1 in the binary representation of the receiver. Answer false otherwise. If the receiver has fewer bits than the operand, the receiver is treated as if it were extended on the left with zeros to the length of the operand. The result is undefined if either the receiver or the operand is a negative integer. ' refinedIn: '' refinement: '' parameters: #( #('mask' 'integer' #'uncaptured') ) returnValues: #( #( 'boolean' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'odd' forProtocolNamed: #'integer' synopsis: 'Answer true if the receiver is odd. ' definedIn: 'integer' definition: 'Answer true if the receiver is divisible by two (2) with remainder one (1). ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'boolean' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'printOn: output base: flag showRadix: base' forProtocolNamed: #'integer' synopsis: 'Write a sequence of characters that describes the receiver in radix base with optional radix specifier. ' definedIn: 'integer' definition: 'Write to output a sequence of characters that describes the receiver, starting at output''s current position. If the parameter flag is true, produce a sequence of characters that are recognizable using the radixInteger production of the Smalltalk Lexical Grammar. If the flag is false, then the sequence of characters must be recognizable using the radixDigits production as if the numeric value of the radixSpecifier was base. If the receiver is negative, a minus sign (''-'') is prepended to the sequence of characters. The result is undefined if base is less than two or greater than 36. ' refinedIn: '' refinement: '' parameters: #( #('flag' 'boolean' #'uncaptured') #('base' 'integer' #'uncaptured') #('output' 'puttableStream' #'uncaptured') ) returnValues: #() errors: '' ! 1 protocolManager newMessagePattern: 'printStringRadix: base' forProtocolNamed: #'integer' synopsis: 'Answer a string which represents the receiver in radix base. ' definedIn: 'integer' definition: 'Return a string containing a sequence of characters that represents the numeric value of the receiver in the radix specified by the argument. The sequence of characters must be recognizable using the radixDigits production of the Smalltalk Lexical Grammar as if the numeric value of the radixSpecifier was base. If the receiver is negative, a minus sign (''-'') is prepended to the sequence of characters. The result is undefined if base is less than two or greater than 36. ' refinedIn: '' refinement: '' parameters: #( #('base' 'integer' #'uncaptured') ) returnValues: #( #( 'readableString' #'unspecified') ) errors: '' ! (1 protocolManager newProtocolNamed: #'Interval' conformsToProtocolNames: #(#'sequencedReadableCollection') ) protocolDescription: ' Represents a collection whose elements are numbers which form an arithmetic progression. Elements cannot be accessed externally. ' ! 1 protocolManager newMessagePattern: ', operand' forProtocolNamed: #'Interval' synopsis: 'Answer a new collection which is the concatenation of the receiver and operand. ' definedIn: 'sequencedReadableCollection' definition: 'Answer a new collection containing all of the receiver''s elements in their original order followed by all of the elements of operand, in their original order. The size of the new collection is equal to the sum of the sizes of the receiver and operand, as defined by the #size message. Collections that enforce an ordering on their elements are permitted to refine this message to reorder the result. Unless specifically refined, this message is defined to answer an instance of the same type as the receiver. ' refinedIn: 'Interval' refinement: 'Answer a collection containing the elements of operand appended to the elements of the receiver. The enumeration order defined by the #do: message is used. The return type is generalized to . ' parameters: #( #('operand' 'sequencedReadableCollection' #'uncaptured') ) returnValues: #( #( 'sequencedReadableCollection' #'new') ) errors: '' ! 1 protocolManager newMessagePattern: 'collect: transformer' forProtocolNamed: #'Interval' synopsis: 'Answer a new collection constructed by gathering the results of evaluating transformer with each element of the receiver. ' definedIn: 'collection' definition: 'For each element of the receiver, transformer is evaluated with the element as the parameter. The results of these evaluations are collected into a new collection. The elements are traversed in the order specified by the #do: message for the receiver. Unless specifically refined, this message is defined to answer an objects conforming to the same protocol as the receiver. ' refinedIn: 'Interval' refinement: 'The return type is generalized to . ' parameters: #( #('transformer' 'monadicValuable' #'uncaptured') ) returnValues: #( #( 'sequencedReadableCollection' #'new') ) errors: 'If the elements of the receiver are inappropriate for use as arguments to transformer. ' ! 1 protocolManager newMessagePattern: 'copyFrom: start to: stop' forProtocolNamed: #'Interval' synopsis: 'Answer a new collection containing all of the elements of the receiver between the indices start and stop inclusive. If stop < start, the result has a size of zero. ' definedIn: 'sequencedReadableCollection' definition: 'Answer a new collection containing the specified range of elements of the receiver in their original order. The element at index start in the receiver is at index 1 in the new collection; the element at index start+1 is at index 2, etc. If stop is less than start, then the new collection is empty. Otherwise, the size of the new collection is the maximum of (stop - start + 1) and 0. The parameters start and stop must be positive. Unless specifically refined, this message is defined to answer an instance of the same class as the receiver''s class. ' refinedIn: 'Interval' refinement: 'The return type is generalized to . ' parameters: #( #('stop' 'integer' #'uncaptured') #('start' 'integer' #'uncaptured') ) returnValues: #( #( 'sequencedReadableCollection' #'new') ) errors: 'If start < 1 or start > self size. If stop < 1 or stop > self size. ' ! 1 protocolManager newMessagePattern: 'copyReplaceAll: targetElements with: replacementElements' forProtocolNamed: #'Interval' synopsis: 'Answer a new collection in which all subsequences of elements in the receiver matching targetElements are replaced in the new collection by the elements in replacementElements. ' definedIn: 'sequencedReadableCollection' definition: 'Answer a new collection with the elements of the receiver in their original order, except where a subsequence in the receiver matches targetElements. A subsequence in the receiver is said to match the elements of targetElements if: 1. They have the same number of elements. 2. For all indices of the subsequence, the element in the subsequence at a given index is equivalent to the element in targetElements at the same index. Where a subsequence match is found, the elements from replacementElements are placed in the new collection instead. Unless specifically refined, this message is defined to answer an instance of the same class as the receiver. Collections that enforce an ordering on their elements are permitted to refine this message to reorder the result. ' refinedIn: 'Interval' refinement: 'The return type is generalized to . ' parameters: #( #('targetElements' 'sequencedReadableCollection' #'uncaptured') #('replacementElements' 'sequencedReadableCollection' #'unspecified') ) returnValues: #( #( 'sequencedReadableCollection' #'new') ) errors: 'If any of the elements in replacementElements is inappropriate for storage in instances of the result. ' ! 1 protocolManager newMessagePattern: 'copyReplaceFrom: stop to: replacementElements with: start' forProtocolNamed: #'Interval' synopsis: 'Answer a new collection, containing the same elements as the receiver, but with the elements in the receiver between start and stop inclusive replaced by the elements in replacementElements. ' definedIn: 'sequencedReadableCollection' definition: 'This message can be used to insert, append, or replace. The size of replacementElements (as defined by #size) need not be the same as the number of elements being replaced. There are three cases: 1. If stop = start - 1 , and start is less than or equal to the size of the receiver, then the replacementElements are inserted between the elements at index stop and start. None of the receiver''s elements are replaced. 2. If stop = the size of the receiver and start = stop + 1, then the operation is an append, and the replacementElements are placed at the end of the new collection. 3. Otherwise, the operation is a replacement, and the receiver''s elements in the given range are replaced by the elements from replacementElements. In all cases, the resulting collection consists of the receiver''s elements from indices 1 to start - 1 in their original order, followed by the elements of replacementElements, followed by the remainder of the receiver''s elements from index stop + 1 in their original order. The size of the result is the receiver''s size - (stop - start + 1) + the replacementElements size. The parameters start and stop must be positive. Unless specifically refined, this message is defined to answer an instance of the same class as the receiver''s class. Collections that enforce an ordering on their elements are permitted to refine this message to reorder the result. ' refinedIn: 'Interval' refinement: 'The return type is generalized to . ' parameters: #( #('start' 'integer' #'uncaptured') #('stop' 'integer' #'uncaptured') #('replacementElements' 'sequencedReadableCollection' #'unspecified') ) returnValues: #( #( 'sequencedReadableCollection' #'new') ) errors: 'The elements in replacementElements are not suitable for storage in instances of the result. ' ! 1 protocolManager newMessagePattern: 'copyReplaceFrom: replacementElement to: stop withObject: start' forProtocolNamed: #'Interval' synopsis: 'Answer a new collection conforming to the same protocols as the receiver, in which the elements of the receiver between start and stop inclusive have been replaced with replacementElement. ' definedIn: 'sequencedReadableCollection' definition: 'This message can be used to insert, append, or replace. There are three cases: 1. If stop = start - 1 , and start is less than or equal to the size of the receiver, then replacementElement is inserted between the elements at index stop and start. None of the receiver''s elements are replaced. 2. If stop = the size of the receiver and start = stop + 1, then the operation is an append, and replacementElement is placed at the end of the new collection. 3. Otherwise, the operation is a replacement, and each of the receiver''s elements in the given range is replaced by replacementElement. The parameters start and stop must be non-negative. Unless specifically refined, this message is defined to answer an instance of the same class as the receiver''s class. Collections that by definition enforce an ordering on their elements are permitted to refine this message to reorder the result. ' refinedIn: 'Interval' refinement: 'The return type is generalized to . ' parameters: #( #('replacementElement' 'Object' #'captured') #('start' 'integer' #'uncaptured') #('stop' 'integer' #'uncaptured') ) returnValues: #( #( 'sequencedReadableCollection' #'new') ) errors: '' ! 1 protocolManager newMessagePattern: 'copyReplacing: replacementElement withObject: targetElement' forProtocolNamed: #'Interval' synopsis: 'Answer a new collection conforming to the same protocols as the receiver, in which any occurrences of targetElement are replaced by replacementElement. ' definedIn: 'sequencedReadableCollection' definition: 'A new collection is created and initialized with the same elements as the receiver in the same order, except that any objects in the receiver which are equivalent to targetElement are replaced in the new collection by replacementElement. Unless specifically refined, this message is defined to answer an instance of the same class as the receiver. Collections that enforce an ordering on their elements are permitted to refine this message to reorder the result. ' refinedIn: 'Interval' refinement: 'The return type is generalized to . ' parameters: #( #('replacementElement' 'Object' #'captured') #('targetElement' 'Object' #'uncaptured') ) returnValues: #( #( 'sequencedReadableCollection' #'new') ) errors: '' ! 1 protocolManager newMessagePattern: 'copyWith: newElement' forProtocolNamed: #'Interval' synopsis: 'Answer a new collection containing the same elements as the receiver, with newElement added. ' definedIn: 'sequencedReadableCollection' definition: 'Answer a new collection with size one greater than the size of the receiver containing the elements of the receiver and newElement placed at the end. Unless specifically refined, this message is defined to answer an instance of the same class as the receiver. Collections that enforce an ordering on their elements are permitted to refine this message to reorder the result. ' refinedIn: 'Interval' refinement: 'The return type is generalized to . ' parameters: #( #('newElement' 'Object' #'captured') ) returnValues: #( #( 'sequencedReadableCollection' #'new') ) errors: '' ! 1 protocolManager newMessagePattern: 'copyWithout: oldElement' forProtocolNamed: #'Interval' synopsis: 'Answer a new collection, containing the same elements as the receiver in their original order omitting any elements equivalent to oldElement. ' definedIn: 'sequencedReadableCollection' definition: 'Answer a new collection with all of the elements of the receiver that are not equivalent to oldElement, in their original order. Unless specifically refined, this message is defined to answer an instance of the same type as the receiver. ' refinedIn: 'Interval' refinement: 'The return type is generalized to . ' parameters: #( #('oldElement' 'Object' #'uncaptured') ) returnValues: #( #( 'sequencedReadableCollection' #'new') ) errors: '' ! 1 protocolManager newMessagePattern: 'reject: discriminator' forProtocolNamed: #'Interval' synopsis: 'Answer a new collection which excludes the elements in the receiver which cause discriminator to evaluate to true. ' definedIn: 'collection' definition: 'For each element of the receiver, discriminator is evaluated with the element as the parameter. Each element which causes discriminator to evaluate to false is added to the new collection. The elements are traversed in the order specified by the #do: message for the receiver. Unless specifically refined, this message is defined to answer an object conforming to the same protocol as the receiver. ' refinedIn: 'Interval' refinement: 'The return type is refined to . ' parameters: #( #('discriminator' 'monadicValuable' #'uncaptured') ) returnValues: #( #( 'sequencedReadableCollection' #'new') ) errors: 'If the elements of the receiver are inappropriate for use as arguments to discriminator. If discriminator evaluates to an object that does not conform to the protocol for any element of the receiver. ' ! 1 protocolManager newMessagePattern: 'reverse' forProtocolNamed: #'Interval' synopsis: 'Answer a collection with the elements of the receiver arranged in reverse order. ' definedIn: 'sequencedReadableCollection' definition: 'Answer a collection conforming to the same protocols as the receiver, but with its elements arranged in reverse order. This operation is equivalent to: 1. Create a new collection which conforms to the same protocols as the receiver; 2. Traverse the elements of the receiver in the order specified by the #reverseDo: message, adding each element of the receiver to the new collection; 3. Answer the new collection. ' refinedIn: 'Interval' refinement: 'The return type is generalized to . ' parameters: #() returnValues: #( #( 'sequencedReadableCollection' #'new') ) errors: '' ! 1 protocolManager newMessagePattern: 'select: discriminator' forProtocolNamed: #'Interval' synopsis: 'Answer a new collection which contains the elements in the receiver which cause discriminator to evaluate to true. ' definedIn: 'collection' definition: 'For each element of the receiver, discriminator is evaluated with the element as the parameter. Each element which causes discriminator to evaluate to true is added to the new collection. The elements are traversed in the order specified by the #do: message for the receiver. Unless specifically refined, this message is defined to answer an objects conforming to the same protocol as the receiver. ' refinedIn: 'Interval' refinement: 'The return type is refined to . ' parameters: #( #('discriminator' 'monadicValuable' #'uncaptured') ) returnValues: #( #( 'sequencedReadableCollection' #'new') ) errors: 'If the elements of the receiver are inappropriate for use as arguments to discriminator. If discriminator evaluates to an object that does not conform to the protocol for any element of the receiver. ' ! (1 protocolManager newProtocolNamed: #'Interval factory' conformsToProtocolNames: #(#'Object') ) protocolDescription: ' Represents protocol for creating a collection whose elements are numbers which form an arithmetic progression. Standard Globals Interval Conforms to the protocol . Its language element type is unspecified. This is a factory and discriminator for collections that conform to . ' ! 1 protocolManager newMessagePattern: 'from: stop to: start' forProtocolNamed: #'Interval factory' synopsis: 'Answer an interval which represents an arithmetic progression from start to stop in increments of 1. ' definedIn: 'Interval factory' definition: 'Answer an interval which represents an arithmetic progression from start to stop, using the increment 1 to compute each successive element. The elements are numbers which have the same type as start. Note that stop may not be the last element in the sequence; the last element is given by the formula start + ((stop - start) // 1) The interval answered will be empty (it will answer 0 to the #size message) if start > stop ' refinedIn: '' refinement: '' parameters: #( #('start' 'number' #'unspecified') #('stop' 'number' #'unspecified') ) returnValues: #( #( 'Interval' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'from: stop to: step by: start' forProtocolNamed: #'Interval factory' synopsis: 'Answer an interval which represents an arithmetic progression from start to stop in increments of step. ' definedIn: 'Interval factory' definition: 'Answer an interval which represents an arithmetic progression from start to stop, using the increment step to compute each successive element. The value of step can be positive or negative, but it must be non-zero. The elements are numbers which have the most general type of start and step. Note that stop is not necessarily an element in the sequence; the last element is given by the formula (((stop - start) // step) * step) + start The interval answered will be empty (it will answer 0 to the #size message) if: start < stop and step < 0, or start > stop and step > 0. ' refinedIn: '' refinement: '' parameters: #( #('start' 'number' #'unspecified') #('stop' 'number' #'unspecified') #('step' 'number' #'unspecified') ) returnValues: #( #( 'Interval' #'unspecified') ) errors: 'step = 0 ' ! (1 protocolManager newProtocolNamed: #'magnitude' conformsToProtocolNames: #(#'Object') ) protocolDescription: ' Provides protocol for comparing objects which are linearly ordered with respect to some comparison operation. ' ! 1 protocolManager newMessagePattern: '< operand' forProtocolNamed: #'magnitude' synopsis: 'Answer true if the receiver is less than operand. Answer false otherwise. ' definedIn: 'magnitude' definition: 'Answer true if the receiver is less than operand with respect to the ordering defined for them. Answer false otherwise. It is erroneous if the receiver and operand are not comparable. The semantics of the natural ordering must be defined by refinement, which may also restrict the type of operand. ' refinedIn: '' refinement: '' parameters: #( #('operand' 'magnitude' #'uncaptured') ) returnValues: #( #( 'boolean' #'unspecified') ) errors: 'Receiver and operand are not comparable ' ! 1 protocolManager newMessagePattern: '<= operand' forProtocolNamed: #'magnitude' synopsis: 'Answer true if the receiver is less than or equal to operand. Answer false otherwise. ' definedIn: 'magnitude' definition: 'Answer true if the receiver would answer true to either the #< or #= message with operand as the parameter. Answer false otherwise. It is erroneous if the receiver and operand are not comparable. ' refinedIn: '' refinement: '' parameters: #( #('operand' 'magnitude' #'uncaptured') ) returnValues: #( #( 'boolean' #'unspecified') ) errors: 'Receiver and operand are not comparable ' ! 1 protocolManager newMessagePattern: '> operand' forProtocolNamed: #'magnitude' synopsis: 'Answer true if the receiver is greater than operand. Answer false otherwise. ' definedIn: 'magnitude' definition: 'Answer true if the receiver is greater than operand with respect to the natural ordering. Answer false otherwise. It is erroneous if the receiver and operand are not comparable. The semantics of the natural ordering must be defined by refinement, which may also restrict the type of operand. ' refinedIn: '' refinement: '' parameters: #( #('operand' 'magnitude' #'uncaptured') ) returnValues: #( #( 'boolean' #'unspecified') ) errors: 'Receiver and operand are not comparable ' ! 1 protocolManager newMessagePattern: '>= operand' forProtocolNamed: #'magnitude' synopsis: 'Answer true if the receiver is greater than or equal to operand. Answer false otherwise. ' definedIn: 'magnitude' definition: 'Answer true if the receiver answers true to either the #> or #= message with operand as the parameter. Answer false otherwise. It is erroneous if the receiver and operand are not comparable. ' refinedIn: '' refinement: '' parameters: #( #('operand' 'magnitude' #'uncaptured') ) returnValues: #( #( 'boolean' #'unspecified') ) errors: 'Receiver and operand are not comparable ' ! 1 protocolManager newMessagePattern: 'between: max and: min' forProtocolNamed: #'magnitude' synopsis: 'Answer true if the receiver is less than or equal to max, and greater than or equal to min. Answer false otherwise. ' definedIn: 'magnitude' definition: 'Answer true if the receiver answers true to the #<= message with max as the parameter, and also answers true to the #>= message with min as the parameter. Answer false otherwise. It is erroneous if the receiver and min or max are not comparable. ' refinedIn: '' refinement: '' parameters: #( #('max' 'magnitude' #'uncaptured') #('min' 'magnitude' #'uncaptured') ) returnValues: #( #( 'boolean' #'unspecified') ) errors: 'Receiver and operands are not comparable. ' ! 1 protocolManager newMessagePattern: 'max: operand' forProtocolNamed: #'magnitude' synopsis: 'Answer the receiver if it is greater than operand. Answer operand otherwise. ' definedIn: 'magnitude' definition: 'Answer the receiver if the receiver answers true to the #> message with operand as the parameter. Answer operand otherwise. It is erroneous if the receiver and operand are not comparable. ' refinedIn: '' refinement: '' parameters: #( #('operand' 'magnitude' #'uncaptured') ) returnValues: #( #( 'magnitude' #'unspecified') ) errors: 'Receiver and operand are not comparable ' ! 1 protocolManager newMessagePattern: 'min: operand' forProtocolNamed: #'magnitude' synopsis: 'Answer the receiver if it is less than operand. Answer operand otherwise. ' definedIn: 'magnitude' definition: 'Answer the receiver if the receiver answers true to the #< message with operand as the parameter. Answer operand otherwise. It is erroneous if the receiver and operand are not comparable. ' refinedIn: '' refinement: '' parameters: #( #('operand' 'magnitude' #'uncaptured') ) returnValues: #( #( 'magnitude' #'unspecified') ) errors: 'Receiver and operand are not comparable ' ! (1 protocolManager newProtocolNamed: #'MessageNotUnderstood' conformsToProtocolNames: #(#'Error') ) protocolDescription: ' This protocol describes the behavior of exceptions that are signalled if the receiver of a message does not have a method with a matching selector. ' ! 1 protocolManager newMessagePattern: 'isResumable' forProtocolNamed: #'MessageNotUnderstood' synopsis: 'Determine whether an exception is resumable. ' definedIn: 'exceptionDescription' definition: 'This message is used to determine whether the receiver is a resumable exception. Answer true if the receiver is resumable. Answer false if the receiver is not resumable. ' refinedIn: 'MessageNotUnderstood' refinement: 'Answer true. ' parameters: #() returnValues: #( #( 'boolean' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'message' forProtocolNamed: #'MessageNotUnderstood' synopsis: 'Answer the selector and arguments of the message that failed. ' definedIn: 'MessageNotUnderstood' definition: 'Answer the selector and arguments of the message that failed. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'failedMessage' #'state') ) errors: '' ! 1 protocolManager newMessagePattern: 'receiver' forProtocolNamed: #'MessageNotUnderstood' synopsis: 'Answer the receiver the message that failed. ' definedIn: 'MessageNotUnderstood' definition: 'Answer the object that was the receiver of the message that failed. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'Object' #'state') ) errors: '' ! (1 protocolManager newProtocolNamed: #'MessageNotUnderstoodSelector' conformsToProtocolNames: #(#'exceptionSelector') ) protocolDescription: ' This protocol describe the behavior of the value of the global named MessageNotUnderstood. This object is used to as an exception selector to catch failed message sends. Message not understood exceptions are resumable so any message in this protocol that signal such an exception may ultimately return to their sender. This object is not specifed as an or an . It as assumed that message not understood exceptions are signaled by the implemention dependent implementaton of the message #doesNotUnderstand:. Standard Globals MessageNotUnderstood Unspecified language element type. Conforms to the protocol . Used as an exception selector . ' ! 1 protocolManager newMessagePattern: 'handles: exception' forProtocolNamed: #'MessageNotUnderstoodSelector' synopsis: 'Determine whether an exception handler will accept a signaled exception. ' definedIn: 'exceptionSelector' definition: 'This message determines whether the exception handler associated with the receiver may be used to process the argument. Answer true if an associated handler should be used to process exception. Answer false if an associated handler may not be used to process the exception. ' refinedIn: 'MessageNotUnderstoodSelector' refinement: 'Return true if exception is an exception that is the result of a failed message send. ' parameters: #( #('exception' 'exceptionDescription' #'unspecified') ) returnValues: #( #( 'boolean' #'unspecified') ) errors: '' ! (1 protocolManager newProtocolNamed: #'monadicBlock' conformsToProtocolNames: #(#'monadicValuable') ) protocolDescription: ' This protocol describes the behavior for blocks with one argument. Objects conforming to this protocol can be created only by the block constructor construct of the Smalltalk language. ' ! (1 protocolManager newProtocolNamed: #'monadicValuable' conformsToProtocolNames: #(#'valuable') ) protocolDescription: ' This protocol describes the behavior for objects supporting the value: selector. ' ! 1 protocolManager newMessagePattern: 'argumentCount' forProtocolNamed: #'monadicValuable' synopsis: 'Answers the number of arguments needed to evaluate the receiver. ' definedIn: 'valuable' definition: 'The number of arguments needed to evaluate the receiver is returned. ' refinedIn: 'monadicValuable' refinement: 'Returns 1. ' parameters: #() returnValues: #( #( 'integer' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'value: argument' forProtocolNamed: #'monadicValuable' synopsis: 'Answers the value of the receiver when applied to the argument. ' definedIn: 'monadicValuable' definition: 'The receiver is evaluated as defined by the receiver. Note that in the case that the receiver is a block, that the evaluation is defined by the language with argument bound to the block''s only argument. The result is as defined by the receiver. ' refinedIn: '' refinement: '' parameters: #( #('argument' 'ANY' #'unspecified') ) returnValues: #( #( 'ANY' #'unspecified') ) errors: '' ! (1 protocolManager newProtocolNamed: #'nil' conformsToProtocolNames: #(#'Object') ) protocolDescription: ' This protocol describes the behavior that is unique to the distinguished immutable, identity object that is the value of the reserved identifier "nil". ' ! 1 protocolManager newMessagePattern: 'printString' forProtocolNamed: #'nil' synopsis: 'Return a string that describes the receiver. ' definedIn: 'Object' definition: 'A string consisting of a sequence of characters that describe the receiver are returned as the result. The exact sequence of characters that describe an object are implementation defined. ' refinedIn: 'nil' refinement: 'Return a string with the same characters as the string ''nil''. ' parameters: #() returnValues: #( #( 'readableString' #'unspecified') ) errors: '' ! (1 protocolManager newProtocolNamed: #'niladicBlock' conformsToProtocolNames: #(#'niladicValuable') ) protocolDescription: ' This protocol describes the behavior for blocks with no arguments. Objects conforming to this protocol can be created only by the block constructor construct of the Smalltalk language. ' ! 1 protocolManager newMessagePattern: 'ensure: terminationBlock' forProtocolNamed: #'niladicBlock' synopsis: 'Evaluate a termination block after evaluating the receiver. ' definedIn: 'niladicBlock' definition: 'Evaluate the receiver and return its result. Immediately after successful evaluation of the receiver but before returning its result, evaluate terminationBlock. If abnormal termination of the receiver occurs, terminationBlock is evaluated. In either case, the value returned from the evaluation of terminationBlock is discarded. Activation of an exception handler from within the receiver is not in and of itself an abnormal termination. However, if the exception handler for an exception that is not resumable results in termination of the receiver or if its handler block contains a return statement that results in abnormal termination of the receiver, then terminationBlock will be evaluated after evaluation of the exception handler. If an abnormal termination results in the termination of multiple blocks which were evaluated using either #ensure: or #ifCurtailed: the respective terminationBlocks will be executed in the reverse of the order in which the corresponding receiver blocks were evaluated. ' refinedIn: '' refinement: '' parameters: #( #('terminationBlock' 'niladicBlock' #'uncaptured') ) returnValues: #( #( 'ANY' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'ifCurtailed: terminationBlock' forProtocolNamed: #'niladicBlock' synopsis: 'Evaluating the receiver with an abnormal termination action. ' definedIn: 'niladicBlock' definition: 'Evaluate the receiver and return its result. If abnormal termination of the receiver occurs, terminationBlock is evaluated. The value returned from the evaluation of terminationBlock is discarded. Activation of an exception handler from within the receiver is not in and of itself an abnormal termination. However, if the exception handler for an exception that is not resumable results in termination of the receiver or if its handler block contains a return statement that results in abnormal termination of the receiver, then terminationBlock will be evaluated after evaluation of the exception handler. If an abnormal termination result in the termination of multiple blocks which were evaluated using either #ensure: or #ifCurtailed: the respective terminationBlocks will be executed in the reverse of the order in which the corresponding receiver blocks were evaluated. ' refinedIn: '' refinement: '' parameters: #( #('terminationBlock' 'niladicBlock' #'uncaptured') ) returnValues: #( #( 'ANY' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'on: action do: selector' forProtocolNamed: #'niladicBlock' synopsis: 'Evaluate the receiver in the scope of an exception handler. ' definedIn: 'niladicBlock' definition: 'The receiver is evaluated such that if during its evaluation an exception corresponding to selector is signaled then action will be evaluated. The result of evaluating the receiver is returned. Before evaluating the receiver the current state of the exception environment is captured as the handler environment. Then a new exception handler is created with selector as its exception selector and action as its handler block. The new handler is pushed onto the exception environment. If evaluation of the receiver terminates normally then the exception environment is reset to the handler environment before returning to the sender of the #on:do: message. If signaling of an exception results in evaluation of action the evaluation will occur in the context of the handler environment. The argument to the action will be an object that conforms to the protocol . ' refinedIn: '' refinement: '' parameters: #( #('selector' 'exceptionSelector' #'uncaptured') #('action' 'monadicBlock' #'uncaptured') ) returnValues: #( #( 'ANY' #'unspecified') ) errors: '' ! (1 protocolManager newProtocolNamed: #'niladicValuable' conformsToProtocolNames: #(#'valuable') ) protocolDescription: ' This protocol describes the behavior for objects supporting the #value selector. ' ! 1 protocolManager newMessagePattern: 'argumentCount' forProtocolNamed: #'niladicValuable' synopsis: 'Answers the number of arguments needed to evaluate the receiver. ' definedIn: 'valuable' definition: 'The number of arguments needed to evaluate the receiver is returned. ' refinedIn: 'niladicValuable' refinement: 'Returns 0. ' parameters: #() returnValues: #( #( 'integer' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'value' forProtocolNamed: #'niladicValuable' synopsis: 'Answers the value of the receiver. ' definedIn: 'niladicValuable' definition: 'The receiver is evaluated as defined by the receiver. The result is as defined by the receiver. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'ANY' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'whileFalse' forProtocolNamed: #'niladicValuable' synopsis: 'Evaluates the receiver until it evaluates to true. ' definedIn: 'niladicValuable' definition: 'The receiver is evaluated as defined by the receiver. Note that in the case that the receiver is a block, the evaluation is defined by the language. If this evaluation results in false the process repeats. If and when the evaluation of the receiver results in true, the method terminates. The results are undefined if the receiver is not a block which evaluates to a Boolean value. ' refinedIn: '' refinement: '' parameters: #() returnValues: #() errors: '' ! 1 protocolManager newMessagePattern: 'whileFalse: iterationBlock' forProtocolNamed: #'niladicValuable' synopsis: 'Evaluates iterationBlock zero or more times until the receiver evaluates to true. ' definedIn: 'niladicValuable' definition: 'The receiver is evaluated as defined by the receiver. Note that in the case that the receiver is a block, that the evaluation is defined by the language. If this evaluation results in false, the argument is evaluated and the process repeats. If and when the evaluation of the receiver results in true, the method terminates. The results are undefined if the receiver is not a block which evaluates to a Boolean value. ' refinedIn: '' refinement: '' parameters: #( #('iterationBlock' 'niladicValuable' #'uncaptured') ) returnValues: #() errors: '' ! 1 protocolManager newMessagePattern: 'whileTrue' forProtocolNamed: #'niladicValuable' synopsis: 'Evaluates the receiver until it evaluates to false. ' definedIn: 'niladicValuable' definition: 'The receiver is evaluated as defined by the receiver. Note that in the case that the receiver is a block, that the evaluation is defined by the language. If this evaluation results in true the process repeats. If and when the evaluation of the receiver results in false, the method terminates. The results are undefined if the receiver is not a block which evaluates to a Boolean value. ' refinedIn: '' refinement: '' parameters: #() returnValues: #() errors: '' ! 1 protocolManager newMessagePattern: 'whileTrue: iterationBlock' forProtocolNamed: #'niladicValuable' synopsis: 'Evaluates iterationBlock zero or more times until the receiver evaluates to false. ' definedIn: 'niladicValuable' definition: 'The receiver is evaluated as defined by the receiver. Note that in the case that the receiver is a block, that the evaluation is defined by the language. If this evaluation results in true, the argument is evaluated and the process repeats. If and when the evaluation of the receiver results in false, the method terminates. The results are undefined if the receiver is not a block which evaluates to a Boolean value. ' refinedIn: '' refinement: '' parameters: #( #('iterationBlock' 'niladicValuable' #'uncaptured') ) returnValues: #() errors: '' ! (1 protocolManager newProtocolNamed: #'Notification' conformsToProtocolNames: #(#'Exception') ) protocolDescription: ' This protocol describes the behavior of instances of the class Notification. These are used to represent exceptional conditions that may occur but which are not considered errors. Actual notification exceptions used by an application may be subclasses of this class. As Notification is explicitly specified to be subclassable, conforming implementations must implement its behavior in a non-fragile manner. ' ! 1 protocolManager newMessagePattern: 'defaultAction' forProtocolNamed: #'Notification' synopsis: '' definedIn: 'exceptionDescription' definition: 'If the exception described by the receiver is signaled and the current exception environment does not contain a handler for the exception this method will be executed. The exact behavior and result of this method is implementation defined. ' refinedIn: 'Notification' refinement: 'No action is taken. The value nil is returned as the value of the message that signaled the exception. ' parameters: #() returnValues: #( #( 'nil' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'isResumable' forProtocolNamed: #'Notification' synopsis: '' definedIn: 'exceptionDescription' definition: 'This message is used to determine whether the receiver is a resumable exception. Answer true if the receiver is resumable. Answer false if the receiver is not resumable. ' refinedIn: 'Notification' refinement: 'Answer true. Notification exceptions by default are specified to be resumable. ' parameters: #() returnValues: #( #( 'boolean' #'unspecified') ) errors: '' ! (1 protocolManager newProtocolNamed: #'Notification class' conformsToProtocolNames: #(#'Exception class') ) protocolDescription: ' This protocol describe the behavior of the global Notification. The value of the standard global Notification is a class object that conforms to this protocol. The class Notification is explicitly specified to be subclassable in a standard conforming program. Conforming implementations must implement its behaviors in a non-fragile manner. The signaled exceptions generated by this type of object conform to the protocol . Standard Globals Notification A class name. Conforms to the protocol . Notification must inherit (possibly indirectly) from the class Exception. Instances of this class conform to the protocol . ' ! 1 protocolManager newMessagePattern: 'new' forProtocolNamed: #'Notification class' synopsis: '' definedIn: 'instantiator' definition: 'Return a newly created object initialized to a standard initial state. ' refinedIn: 'Notification class' refinement: 'The object returned conforms to . ' parameters: #() returnValues: #( #( 'Notification' #'new') ) errors: '' ! (1 protocolManager newProtocolNamed: #'number' conformsToProtocolNames: #(#'magnitude') ) protocolDescription: ' Provides protocol for objects that represent numeric quantities and support operations performing arithmetic, arithmetic progressions, and conversion on numerical quantities. The descriptions of messages in this protocol reference specific arithmetic and numerical operations in the ISO/IEC 10967 standard, providing definition-by-reference for these operations. Smalltalk provides for mixed-mode arithmetic with the receiver and argument having different numeric representations. Unless otherwise specified by an individual operation the receiver and argument are first converted to the same numeric representation according to the following table. Default Conversion Table: opera|nd e d q --receiver---|------------------------------------------------------- | e d q | e d q | e d q e | e e e e d q d | d d d d d q q | q q q q q q If multiple representations of are available, the representations are ordered from smallest to largest precision. This table contains multiple entries for , designated by a subscript, one for each designation of floating point literal representation. Values that are converted to are converted to the smallest precision of Float that can represent the number of digits in the original value. An converted to a will have the scale of the other operand with the fractional digits set to zero. A converted to a will be a fraction having the same numeric value but having an integer numerator and a denominator which is ten raised to the power of the ''s scale factor. The result type of most numeric opeations is based upon the operaand type. The Default Result Type for all operand types except is the type to which the operands have been converted according to the Default ConversionTable. If the converted operand type is the Default Result Type is . In all cases where the type of the return value differs from the default result type it is noted in the operation''s description. Operations can produce results that are outside the set of representable numbers, or mathematically undefined. It is implementation defined whether errors are raised when results are not representable or if unrepresentable results are wrapped in implementation-defined continuation values or their equivalent. The effect of underflow and overflow is therefore implementation defined. conforms to . All object that implement the protocol or any protocol that conforms to are comparable. ' ! 1 protocolManager newMessagePattern: '* operand' forProtocolNamed: #'number' synopsis: 'Answer the result of multiplying the receiver by operand. ' definedIn: 'number' definition: 'Answer a number whose value is the result of multiplying the receiver and operand, as specified by the ISO/IEC 10967 multiplication operation mul. To perform the operation both the receiver and operand must be objects with identical numeric representations. If they have different representations a conversion to their common numeric representation is performed, as specified by the Default Conversion Table, before applying the operation. If the common representation is , then the result value is defined by the ISO/IEC 10967 operation mulI. If the common representation is , then the result value is defined by the ISO/IEC 10967 mulF . Otherwise, the result is consistent with the mathematical definition of the ISO/IEC 10967 operation mul. The protocol and representation of the return value is defined to be the Default Result Type. If the return value conforms to then the scale of the result is at least the scale of the receiver after conversion if necessary. If the result value is outside of the range of the common numeric representation, the effect of underflow or overflow is implementation defined.. ' refinedIn: '' refinement: '' parameters: #( #('operand' 'number' #'unspecified') ) returnRule: '[ :receiver :operand | "Default Result Type" self protocolManager defaultReturnProtocolNameReceiver: receiver operand: operand ]' errors: '' ! 1 protocolManager newMessagePattern: '+ operand' forProtocolNamed: #'number' synopsis: 'Answer the result of adding operand to the receiver. ' definedIn: 'number' definition: 'Answer a number whose value is the result of adding the receiver and operand, as specified by the ISO/IEC 10967 addition operation add. To perform the operation both the receiver and operand must be objects with identical numeric representations. If they have different representations a conversion to a common numeric representation is performed, as specified by the Default Conversion Table, before applying the operation. If the resulting protocol is , then the result value is defined by the ISO/IEC 10967 operation addI. If the resulting protocol is , then the result value is defined by the ISO/IEC 10967 addF . Otherwise, the result is consistent with the mathematical definition of the ISO/IEC 10967 operation add. The protocol and representation of the return value is defined by the Default Result Type. If the return value conforms to then the scale of the result is at least the scale of the receiver after conversion if necessary. If the result value is outside of the range of the common numeric representation, the effect of underflow or overflow is implementation defined. ' refinedIn: '' refinement: '' parameters: #( #('operand' 'number' #'unspecified') ) returnRule: '[ :receiver :operand | "Default Result Type" self protocolManager defaultReturnProtocolNameReceiver: receiver operand: operand ]' errors: '' ! 1 protocolManager newMessagePattern: '- operand' forProtocolNamed: #'number' synopsis: 'Answer the result of subtracting operand from the receiver. ' definedIn: 'number' definition: 'Answer a number whose value is the result of subtracting the receiver and operand, as specified by the ISO/IEC 10967 subtraction operation sub. To perform the operation both the receiver and operand must be objects with identical numeric representations. If they have different representations a conversion to a common numeric representation is performed, as specified by the Default Conversion Table, before applying the operation. If the resulting protocol is , then the result value is defined by the ISO/IEC 10967 operation subI. If the resulting protocol is , then the result value is defined by the ISO/IEC 10967 subF . Otherwise, the result is consistent with the mathematical definition of the ISO/IEC 10967 operation sub. The protocol and representation of the return value is defined by the Default Result Type. If the return value conforms to then the scale of the result is at least the scale of the receiver after conversion if necessary. If the result value is outside of the range of the common numeric representation, the effect of underflow or overflow is implementation defined. ' refinedIn: '' refinement: '' parameters: #( #('operand' 'number' #'unspecified') ) returnRule: '[ :receiver :operand | "Default Result Type" self protocolManager defaultReturnProtocolNameReceiver: receiver operand: operand ]' errors: '' ! 1 protocolManager newMessagePattern: '/ operand' forProtocolNamed: #'number' synopsis: 'Answer the result of dividing the receiver by operand. ' definedIn: 'number' definition: 'Answer a number whose value is the result of dividing the receiver by operand, as specified by the ISO/IEC 10967 flooring division operation div To perform the operation both the receiver and operand must be objects with identical numeric representations. If they have different representations a conversion to a common numeric representation is performed, as specified by the Default Conversion Table, before applying the operation. If the resulting protocol is , then the result value is a with the receiver as the numerator and the operand as the denominator. If the resulting protocol is , then the result value is defined by the ISO/IEC 10967 divF . Otherwise, the result is consistent with the mathematical definition of the ISO/IEC 10967 operation div. If both operands conform to the result value will conform to . Otherwise the protocol and representation of the return value are defined by the Default Result Type. If the return value conforms to then the scale of the result is at least the scale of the receiver after conversion if necessary. If the result value is outside of the range of the common numeric representation, the effect of underflow or overflow is implementation defined. If either the receiver or operand are of type and the operand has a value of zero, the result is implementation defined. The implementation must either signal the ZeroDivide exception or provide a continuation value. For all other numeric representations the ZeroDivide exception is signaled. ' refinedIn: '' refinement: '' parameters: #( #('operand' 'number' #'unspecified') ) returnRule: '[ :receiver :operand | | defaultRetType | "defaultRetType is Default Conversion Table[rec, op]" defaultRetType := self protocolManager defaultReturnProtocolNameReceiver: receiver operand: operand. "conformsTo:" defaultRetType = #''integer'' ifTrue: [#''rational''] ifFalse:[defaultRetType] ]' errors: 'operand = 0 unless receiver or operand are of type ' ! 1 protocolManager newMessagePattern: '// operand' forProtocolNamed: #'number' synopsis: 'Answer the truncated quotient resulting from dividing the receiver by operand. The truncation is towards negative infinity. ' definedIn: 'number' definition: 'Answer an integer whose value is the truncated result of dividing the receiver by operand, as specified by the ISO/IEC 10967 flooring division operation divf. Truncation is towards negative infinity. The sign of the result is positive if the receiver and operand have the same sign, and negative if the signs are different. To perform the operation both the receiver and operand must be objects with identical numeric representations. If they have different representations a conversion to a common numeric representation is performed, as specified by the Default Conversion Table, before applying the operation. If the resulting protocol is , then the result value is defined by the ISO/IEC 10967 operation divf I. If the resulting protocol is , then the result value is defined by the ISO/IEC 10967 divf F . Otherwise, the result is consistent with the mathematical definition of the ISO/IEC 10967 operation divf. If the operand has a value of zero the ZeroDivide exception is signaled. ' refinedIn: '' refinement: '' parameters: #( #('operand' 'number' #'unspecified') ) returnValues: #( #( 'integer' #'unspecified') ) errors: 'operand = 0 unless receiver or operand are of type ' ! 1 protocolManager newMessagePattern: '< operand' forProtocolNamed: #'number' synopsis: 'Answer true if the receiver is less than operand. Answer false otherwise. ' definedIn: 'magnitude' definition: 'Answer true if the receiver is less than operand with respect to the ordering defined for them. Answer false otherwise. It is erroneous if the receiver and operand are not comparable. The semantics of the natural ordering must be defined by refinement, which may also restrict the type of operand. ' refinedIn: 'number' refinement: 'Answer true if the operand is numerically less than the receiver, as specified by the ISO/IEC 10967 comparison operation lss. Answer false otherwise. To perform the operation both the receiver and operand must be objects with identical numeric representations. If they have different representations a conversion to a common numeric representation is performed, as specified by the Default Conversion Table, before applying the operation. If the resulting protocol is , then the result value is defined by the ISO/IEC 10967 operation lssI. If the resulting protocol is , then the result value is defined by the ISO/IEC 10967 lssF. Otherwise, the result is consistent with the mathematical definition of the ISO/IEC 10967 operation lss. ' parameters: #( #('operand' 'number' #'uncaptured') ) returnValues: #( #( 'boolean' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: '= comparand' forProtocolNamed: #'number' synopsis: 'Object equivalence test. ' definedIn: 'Object' definition: 'This message tests whether the receiver and the comparand are equivalent objects at the time the message is processed. Return true if the receiver is equivalent to comparand. Otherwise return false. The meaning of "equivalent" cannot be precisely defined but the intent is that two objects are considered equivalent if they can be used interchangeably. Conforming protocols may choose to more precisely define the meaning of "equivalent". The value of receiver = comparand is true if and only if the value of comparand = receiver would also be true. If the value of receiver = comparand is true then the receiver and comparand must have equivalent hash values. Or more formally: receiver = comparand ? receiver hash = comparand hash The equivalence of objects need not be temporally invariant. Two independent invocations of #= with the same receiver and operand objects may not always yield the same results. Note that a collection that uses #= to discriminate objects may only reliably store objects whose hash values do not change while the objects are contained in the collection. ' refinedIn: 'number' refinement: 'Answer true if the operand is numerically equal to the receiver, as specified by the ISO/IEC 10967 equality operation eq. Answer false if they are not numerically equal or if operand is not a number. To perform the operation both the receiver and operand must be objects with identical numeric representations. If they have different representations a conversion to a common numeric representation is performed, as specified by the Default Conversion Table, before applying the operation. If the resulting protocol is , then the result value is defined by the ISO/IEC 10967 operation eqI. If the resulting protocol is , then the result value is defined by the ISO/IEC 10967 eqF. Otherwise, the result is consistent with the mathematical definition of the ISO/IEC 10967 operation eq. Numeric equality is defined by implementation defined conventions regarding round-off error and representation of numbers, hence behavior of this message may differ between platforms. ' parameters: #( #('comparand' 'Object' #'uncaptured') ) returnValues: #( #( 'boolean' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: '> operand' forProtocolNamed: #'number' synopsis: 'Answer true if the receiver is greater than operand. Answer false otherwise. ' definedIn: 'magnitude' definition: 'Answer true if the receiver is greater than operand with respect to the natural ordering. Answer false otherwise. It is erroneous if the receiver and operand are not comparable. The semantics of the natural ordering must be defined by refinement, which may also restrict the type of operand. ' refinedIn: 'number' refinement: 'Answer true if the operand is numerically less than the receiver, as specified by the ISO/IEC 10967 comparison operation gtr. Answer false otherwise. To perform the operation both the receiver and operand must be objects with identical numeric representations. If they have different representations a conversion to a common numeric representation is performed, as specified by the Default Conversion Table, before applying the operation. If the resulting protocol is , then the result value is defined by the ISO/IEC 10967 operation gtrI. If the resulting protocol is , then the result value is defined by the ISO/IEC 10967 gtrF. Otherwise, the result is consistent with the mathematical definition of the ISO/IEC 10967 operation gtr. ' parameters: #( #('operand' 'number' #'uncaptured') ) returnValues: #( #( 'boolean' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: '\\ operand' forProtocolNamed: #'number' synopsis: 'Answer the remainder after integer division of the receiver by the operand. ' definedIn: 'number' definition: 'Answer the remainder of truncating integer division as specified by the ISO/IEC 10967 remainder operation remf. The remainder has the same sign as operand. To perform the operation both the receiver and operand must be objects with identical numeric representations. If they have different representations a conversion to a common numeric representation is performed, as specified by the Default Conversion Table, before applying the operation. If the resulting protocol is , then the result value is defined by the ISO/IEC 10967 operation remI. If the resulting protocol is , then the result value is defined by the ISO/IEC 10967 remF . Otherwise, the result is consistent with the mathematical definition of the ISO/IEC 10967 operation rem. The protocol and representation of the return value is defined by the Default Result Type. If the return value conforms to then the scale of the result is at least the scale of the receiver. Within the limits of representation, the following invariant should hold: (receiver // operand) * operand + (receiver \\ operand) = receiver If the result value is outside of the range of the common numeric representation, the effect of underflow or overflow is implementation defined. If either the receiver or operand is of type and the operand has a value of zero, the result is implementation defined. The implementation may signal the ZeroDivide exception or provide a continuation value. For all other numeric representations the ZeroDivide exception is signaled. ' refinedIn: '' refinement: '' parameters: #( #('operand' 'number' #'unspecified') ) returnRule: '[ :receiver :operand | "Default Result Type" self protocolManager defaultReturnProtocolNameReceiver: receiver operand: operand ]' errors: 'operand = 0 unless receiver or operand are of type ' ! 1 protocolManager newMessagePattern: 'abs' forProtocolNamed: #'number' synopsis: 'Answer the absolute value of the receiver. ' definedIn: 'number' definition: 'Return the absolute value of the receiver, as specified by the ISO/IEC 10967 operation abs. If the receiver is greater than or equal to zero, answer an object equal to the receiver. Otherwise answer an object which is equal to the negation of the receiver. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'number' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'asFloat' forProtocolNamed: #'number' synopsis: 'Answer a floating-point number approximating the receiver. ' definedIn: 'number' definition: 'Return the nearest floating-point number to the receiver, as specified by the ISO/IEC 10967 cvt operation. If an implementation supports multiple representations for floating point numbers, the result is the representation with the smallest precision that will represent a number with the same number of digits as the receiver, truncating to the maximum precision of the representation with the largest precision. The effect of underflow or overflow is implementation defined. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'Float' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'asFloatD' forProtocolNamed: #'number' synopsis: 'Answer a d precision floating-point number approximating the receiver . ' definedIn: 'number' definition: 'Return the nearest floating-point number to the receiver, as specified by the ISO/IEC 10967 cvt operation. Use the object representation for floating point numbers that corresponds to the representation used for numeric literals with the exponent designation ''d''. The effect of underflow and overflow is implementation defined. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'Float' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'asFloatE' forProtocolNamed: #'number' synopsis: 'Answer a floating-point number approximating the receiver. ' definedIn: 'number' definition: 'Return the nearest floating-point number to the receiver, as specified by the ISO/IEC 10967 cvt operation. Use the object representation for floating point numbers that corresponds to the representation used for numeric literals with the exponent designation ''e''. The effect of underflow and overflow is implementation defined. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'Float' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'asFloatQ' forProtocolNamed: #'number' synopsis: 'Answer a floating-point number approximating the receiver. ' definedIn: 'number' definition: 'Return the nearest floating-point number to the receiver, as specified by the ISO/IEC 10967 cvt operation. Use the object representation for floating point numbers that corresponds to the representation used for numeric literals with the exponent designation ''q''. The effect of underflow and overflow is implementation defined. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'Float' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'asFraction' forProtocolNamed: #'number' synopsis: 'Answer a fraction approximating the receiver. ' definedIn: 'number' definition: 'Answer a fraction that reasonably approximates the receiver. If the receiver is an integral value the result may be . ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'rational' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'asInteger' forProtocolNamed: #'number' synopsis: 'Answer an integer approximating the receiver. ' definedIn: 'number' definition: 'Answer the result of sending #rounded to the receiver. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'integer' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'asScaledDecimal: scale' forProtocolNamed: #'number' synopsis: 'Answer a scaled decimal number, with a fractional precision of scale, approximating the receiver. ' definedIn: 'number' definition: 'This is a conversion message. Answer a scaled decimal number, with a fractional precision of scale, which minimizes the difference between the answered value and the receiver. The effect of underflow and overflow is implementation defined. ' refinedIn: '' refinement: '' parameters: #( #('scale' 'integer' #'unspecified') ) returnValues: #( #( 'scaledDecimal' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'ceiling' forProtocolNamed: #'number' synopsis: 'Answer the smallest integer greater than or equal to the receiver. ' definedIn: 'number' definition: 'Answer the smallest integer greater than or equal to the receiver. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'integer' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'floor' forProtocolNamed: #'number' synopsis: 'Answer the largest integer less than or equal to the receiver. ' definedIn: 'number' definition: 'Answer the largest integer less than or equal to the receiver. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'integer' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'fractionPart' forProtocolNamed: #'number' synopsis: 'Answer the fractional part of the receiver. ' definedIn: 'number' definition: 'Return an object conforming to the protocol of the receiver that is equal to the fractional part of the receiver. Within the limits of representation, the following invariants should hold: receiver integerPart + receiver fractionPart = receiver receiver \\1 = receiver fractionPart ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'number' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'integerPart' forProtocolNamed: #'number' synopsis: 'Answer the integer part of the receiver. ' definedIn: 'number' definition: 'Return an object that is equal to the integer part of the receiver. If the receiver is type return an object conforming to . Otherwise return an object conforming to the protocol of the receiver. ' refinedIn: '' refinement: '' parameters: #() returnRule: '[ :receiver | "conformsTo is Unary Conversion Table[receiver]" self protocolManager unaryReturnProtocolNameReceiver: receiver ]' errors: '' ! 1 protocolManager newMessagePattern: 'negated' forProtocolNamed: #'number' synopsis: 'Answer the negation of the receiver. ' definedIn: 'number' definition: 'Answer an object conforming to the receiver''s protocol that is equal to the negation of the receiver (equal in magnitude to the receiver but opposite in sign), as specified by the ISO/IEC 10967 neg operation. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'number' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'negative' forProtocolNamed: #'number' synopsis: 'Answer true if the receiver is negative. ' definedIn: 'number' definition: 'Answer true if the receiver is negative. Answer false otherwise. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'boolean' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'positive' forProtocolNamed: #'number' synopsis: 'Answer true if the receiver is positive or zero. ' definedIn: 'number' definition: 'Answer true if the receiver is positive or zero. Answer false otherwise. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'boolean' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'printString' forProtocolNamed: #'number' synopsis: 'Return a string that describes the receiver. ' definedIn: 'Object' definition: 'A string consisting of a sequence of characters that describe the receiver are returned as the result. The exact sequence of characters that describe an object are implementation defined. ' refinedIn: 'number' refinement: 'Answer a string that is a valid literal representation that approximates the numeric value of the receiver. ' parameters: #() returnValues: #( #( 'readableString' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'quo: operand' forProtocolNamed: #'number' synopsis: 'Answer the truncated integer quotient resulting from dividing the receiver by operand. Truncation is towards zero. ' definedIn: 'number' definition: 'Answer a number whose value is the result of dividing the receiver by operand, as specified by the ISO/IEC 10967 flooring division operation div To perform the operation both the receiver and operand must be objects with identical numeric representations. If they have different representations a conversion to a common numeric representation is performed, as specified by the Default Conversion Table, before applying the operation. If the resulting protocol is , then the result value is a with the receiver as the numerator and the operand as the denominator. If the resulting protocol is , then the result value is defined by the ISO/IEC 10967 divF . Otherwise, the result is consistent with the mathematical definition of the ISO/IEC 10967 operation div. The protocol and representation of the return value are defined by the Default Result Type. If the return value conforms to then the scale of the result is at least the scale of the receiver after conversion if necessary. If the result value is outside of the range of the common numeric representation, the effect of underflow or overflow is implementation defined. If either the receiver or operand are of type and the operand has a value of zero, the result is implementation defined. The implementation must either signal the ZeroDivide exception or provide a continuation value. For all other numeric representations the ZeroDivide exception is signaled. ' refinedIn: '' refinement: '' parameters: #( #('operand' 'number' #'unspecified') ) returnValues: #( #( 'integer' #'unspecified') ) errors: 'operand = 0 unless receiver or operand are of type Issues Should be the same as #//. ' ! 1 protocolManager newMessagePattern: 'raisedTo: operand' forProtocolNamed: #'number' synopsis: 'Answer the receiver raised to the power operand. ' definedIn: 'number' definition: 'If operand conforms to , answer the result of sending #raisedToInteger: with argument operand to the receiver. Otherwise answer (receiver asFloat ln * operand) exp. It is erroneous if the receiver equals zero and the operand is less than or equal to zero, or if the receiver is less than zero. The effect of underflow and overflow is implementation defined. If the numeric representation of the result has does not have unbounded precision, the effect of underflow or overflow is implementation defined. ' refinedIn: '' refinement: '' parameters: #( #('operand' 'number' #'uncaptured') ) returnValues: #( #( 'number' #'unspecified') ) errors: 'receiver = 0 and operand <= 0 receiver < 0 ' ! 1 protocolManager newMessagePattern: 'raisedToInteger: operand' forProtocolNamed: #'number' synopsis: 'Answer the receiver raised to the power operand. ' definedIn: 'number' definition: 'Answer the receiver raised to the power operand, which must be a whole number. If the operand is a whole number greater than or equal to zero, then the result is the receiver raised to the power operand. If operand is a negative whole number then the result is equivalent to the reciprocal of the absolute value of the receiver raised to the power operand. It is erroneous if the operand does not conform to the protocol . If the numeric representation of the result has does not have unbounded precision, the effect of underflow or overflow is implementation defined. ' refinedIn: '' refinement: '' parameters: #( #('operand' 'integer' #'uncaptured') ) returnValues: #( #( 'number' #'unspecified') ) errors: 'Receiver is not an integer. ' ! 1 protocolManager newMessagePattern: 'reciprocal' forProtocolNamed: #'number' synopsis: 'Answer the reciprocal of the receiver. ' definedIn: 'number' definition: 'Answer the reciprocal of the receiver, which is equal to the result of the operation (1/receiver). Signal a ZeroDivide exception if the receiver is equal to zero. ' refinedIn: '' refinement: '' parameters: #() returnRule: '[ :receiver | "conformsTo is Unary Conversion Table[receiver]" self protocolManager unaryReturnProtocolNameReceiver: receiver ]' errors: 'receiver = 0 ' ! 1 protocolManager newMessagePattern: 'rem: operand' forProtocolNamed: #'number' synopsis: 'Answer the remainder after integer division of the receiver by the operand. ' definedIn: 'number' definition: 'Answer the remainder with respect to integer division, as specified by the ISO/IEC 10967 remainder operation rem. The sign of the remainder is the same sign as the receiver. Within the limits of representation, the following invariant should hold: (receiver quo: operand)*operand + receiver rem: operand) = receiver To perform the operation both the receiver and operand must be objects with identical numeric representations. If they have different representations a conversion to a common numeric representation is performed, as specified by the Default Conversion Table, The protocol and representation of the return value is defined by the Default Result Type. If the return value conforms to then the scale of the result is at least the scale of the receiver after conversion if necessary. If either the receiver or operand are of type and the operand has a value of zero, the result is implementation defined. The implementation may signal the ZeroDivide exception or provide a continuation value. For all other numeric representations the ZeroDivide exception is signaled. If the result value is outside of the range of the common numeric representation, the effect of underflow or overflow is implementation defined. ' refinedIn: '' refinement: '' parameters: #( #('operand' 'number' #'unspecified') ) returnValues: #( #( 'number' #'unspecified') ) errors: 'operand = 0 unless receiver or operand are of type ' ! 1 protocolManager newMessagePattern: 'roundTo: factor' forProtocolNamed: #'number' synopsis: 'Answer the number nearest the receiver that is a multiple of factor. ' definedIn: 'number' definition: 'Answer the number nearest the receiver that is a multiple of factor. The result conforms to either the receiver''s or operand''s protocol, according to the Default Conversion Table. The result is undefined if factor equals zero. If the numeric representation of the result has does not have unbounded precision, the effect of underflow or overflow is implementation defined. ' refinedIn: '' refinement: '' parameters: #( #('factor' 'number' #'uncaptured') ) returnRule: '[ :receiver :operand | "Default Result Type" self protocolManager defaultReturnProtocolNameReceiver: receiver operand: operand ]' errors: '' ! 1 protocolManager newMessagePattern: 'rounded' forProtocolNamed: #'number' synopsis: 'Answer the integer nearest the receiver. ' definedIn: 'number' definition: 'Answer the integer nearest the receiver according to the following property: N rounded = the nearest integer I = N + (N sign * (1/2)) truncated towards zero. For example, 0.5 rounded = 1 and -0.5 rounded = -1. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'integer' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'sign' forProtocolNamed: #'number' synopsis: 'Answer the sign of the receiver. ' definedIn: 'number' definition: 'Answer 1 if the receiver is positive, 0 if the receiver equals 0, and -1 if it is negative, as specified by the ISO/IEC 10967 operation sign. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'integer' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'sqrt' forProtocolNamed: #'number' synopsis: 'Answer the positive square root of the receiver. ' definedIn: 'number' definition: 'Answer a number equal to the positive square root of the receiver as specified by the ISO/IEC 10967 remainder operation sqrt. If the receiver''s protocol is , then the result value is defined by the ISO/IEC 10967 operation sqrtI. If the receiver''s protocol is , then the result value is defined by the ISO/IEC 10967 sqrtF . Otherwise, the result is consistent with the mathematical definition of the ISO/IEC 10967 operation sqrt. The result is undefined if the receiver is less than zero. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'number' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'squared' forProtocolNamed: #'number' synopsis: 'Answer the receiver squared. ' definedIn: 'number' definition: 'Answer a number that is the receiver multiplied by itself. The answer must conform to the same protocol as the receiver. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'number' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'strictlyPositive' forProtocolNamed: #'number' synopsis: 'Answer true if the receiver is greater than zero. ' definedIn: 'number' definition: 'Answer true if the receiver is greater than zero. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'boolean' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'to: stop' forProtocolNamed: #'number' synopsis: 'Answer an object conforming to which represents an arithmetic progression from the receiver to stop in increments of 1. ' definedIn: 'number' definition: 'Answer an interval which represents an arithmetic progression from the receiver to stop, using the increment 1 to compute each successive element. The elements conform to the receiver''s protocol. Note that stop may not be the last element in the sequence, which is given by the formula receiver + ((stop - receiver) // 1) The interval answered will be empty if the receiver is greater than stop. ' refinedIn: '' refinement: '' parameters: #( #('stop' 'number' #'unspecified') ) returnValues: #( #( 'Interval' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'to: step by: stop' forProtocolNamed: #'number' synopsis: 'Answer an interval which represents an arithmetic progression from receiver to stop in increments of step. ' definedIn: 'number' definition: 'Answer an interval which represents an arithmetic progression from the receiver to stop, using the increment step to compute each successive element. The value of step can be positive or negative, but it must be non-zero. The elements conform to either the receiver''s or step''s protocol, according to the Default Conversion Table. Note that stop may not be the last element in the sequence, which is given by the formula (((stop - receiver) // step) * step) + receiver The interval answered will be empty if: 1. receiver < stop, and step < 0. 2. receiver > stop, and step > 0. ' refinedIn: '' refinement: '' parameters: #( #('stop' 'number' #'unspecified') #('step' 'number' #'unspecified') ) returnValues: #( #( 'Interval' #'unspecified') ) errors: 'step = 0 ' ! 1 protocolManager newMessagePattern: 'to: stop by: step do: operation' forProtocolNamed: #'number' synopsis: 'Evaluate operation for each element of an interval which represents an arithmetic progression from the receiver to stop in increments of step. ' definedIn: 'number' definition: 'Evaluate operation for each element of an interval starting at the receiver and stopping at stop where each element is step greater than the previous. The value of step can be positive or negative, but it must be non-zero. The elements must all conform to either the receiver''s or step''s protocol, according to the Default Conversion Table. Note that stop is not necessarily an element in the sequence, which is given by the formula (((stop - receiver) // step) * step) + receiver No evaluation takes place if: 1. receiver < stop, and step < 0. 2. receiver > stop, and step > 0. Implementations are not required to actually create the interval described by the receiver, stop and step. Implementations may restrict the definition of this message to specific classes. ' refinedIn: '' refinement: '' parameters: #( #('stop' 'number' #'unspecified') #('operation' 'monadicBlock' #'unspecified') #('step' 'number' #'unspecified') ) returnValues: #() errors: 'step = 0 ' ! 1 protocolManager newMessagePattern: 'to: operation do: stop' forProtocolNamed: #'number' synopsis: 'Evaluate operation for each element of an interval which represents an arithmetic progression from receiver to stop in increments of 1. ' definedIn: 'number' definition: 'Evaluate operation for each element of an interval starting at the receiver and stopping at stop where each element is 1 greater than the previous. The elements must all conform to the receiver''s protocol according to the Default Conversion Table. Note that stop may not be the last element in the sequence, which is given by the formula receiver + ((stop - receiver) // 1) No evaluation takes place if the receiver is greater than stop. Implementations are not required to actually create the interval described by the receiver and stop. ' refinedIn: '' refinement: '' parameters: #( #('stop' 'number' #'unspecified') #('operation' 'monadicBlock' #'unspecified') ) returnValues: #() errors: '' ! 1 protocolManager newMessagePattern: 'truncateTo: factor' forProtocolNamed: #'number' synopsis: 'Answer the number nearest the receiver truncated towards zero which is a multiple of factor. ' definedIn: 'number' definition: 'If the receiver is positive, answer the largest number less than or equal to the receiver which is a multiple of factor. If it is negative, answer the smallest number greater than or equal to the receiver which is a multiple of factor. The type of the return value depends on the type of the receiver and factor, as indicated by the Default Conversion Table. ' refinedIn: '' refinement: '' parameters: #( #('factor' 'number' #'uncaptured') ) returnRule: '[ :receiver :operand | "Default Result Type" self protocolManager defaultReturnProtocolNameReceiver: receiver operand: operand ]' errors: '' ! 1 protocolManager newMessagePattern: 'truncated' forProtocolNamed: #'number' synopsis: 'Answer an integer equal to the receiver truncated towards zero. ' definedIn: 'number' definition: 'As specified by the ISO/IEC 10967 truncation operation trunc. If the receiver is positive, answer the largest integer less than or equal to the receiver. If it is negative, answer the smallest integer greater than or equal to the receiver. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'integer' #'unspecified') ) errors: '' ! (1 protocolManager newProtocolNamed: #'Object' conformsToProtocolNames: #(#'ANY') ) protocolDescription: ' This protocol describe the behavior that is common to all objects. Standard Globals Integer Conforms to the protocol . Its language element type is unspecified. This global identifies integer objects. Number Conforms to the protocol . Its language element type is unspecified. This global identifies number objects. ScaledDecimal Conforms to the protocol . Its language element type is unspecified. This global identifies scaled decimal objects. Symbol Conforms to the protocol . Its language element type is unspecified. This global identifies objects that conform to the protocol . ' ! 1 protocolManager newMessagePattern: '= comparand' forProtocolNamed: #'Object' synopsis: 'Object equivalence test. ' definedIn: 'Object' definition: 'This message tests whether the receiver and the comparand are equivalent objects at the time the message is processed. Return true if the receiver is equivalent to comparand. Otherwise return false. The meaning of "equivalent" cannot be precisely defined but the intent is that two objects are considered equivalent if they can be used interchangeably. Conforming protocols may choose to more precisely define the meaning of "equivalent". The value of receiver = comparand is true if and only if the value of comparand = receiver would also be true. If the value of receiver = comparand is true then the receiver and comparand must have equivalent hash values. Or more formally: receiver = comparand ? receiver hash = comparand hash The equivalence of objects need not be temporally invariant. Two independent invocations of #= with the same receiver and operand objects may not always yield the same results. Note that a collection that uses #= to discriminate objects may only reliably store objects whose hash values do not change while the objects are contained in the collection. ' refinedIn: '' refinement: '' parameters: #( #('comparand' 'Object' #'uncaptured') ) returnValues: #( #( 'boolean' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: '== comparand' forProtocolNamed: #'Object' synopsis: 'Object identity test. ' definedIn: 'Object' definition: 'This message tests whether the receiver and the comparand are the same object. Return true if the receiver is the same object as comparand. Otherwise return false. The value of receiver == comparand is true if and only if the value of comparand == receiver would also be true. If the value of receiver == comparand is true then the receiver and comparand must have equivalent identity hash values. Or more formally: receiver == comparand ? receiver identityHash = comparand identityHash ' refinedIn: '' refinement: '' parameters: #( #('comparand' 'Object' #'uncaptured') ) returnValues: #( #( 'boolean' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'class' forProtocolNamed: #'Object' synopsis: 'Determine the class of the receiver. ' definedIn: 'Object' definition: 'If the receiver is an instance object, return the class object defined by the class definition that defines the behavior of the receiver. If the receiver is itself a class object, the result is unspecified except that it must conform to the protocol . ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'classDescription' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'copy' forProtocolNamed: #'Object' synopsis: 'Return a copy of the receiver. ' definedIn: 'Object' definition: 'Return a new object that must be as similar as possible to the receiver in its initial state and behavior. Any operation that changes the state of the new object should not as a side-effect change the state or behavior of the receiver. Similarly, any change to the receiver should not as a side-effect change the new object. If the receiver is an identity object, return the receiver. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'Object' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'doesNotUnderstand: message' forProtocolNamed: #'Object' synopsis: 'A message was sent to the receiver for which the receiver has no behavior. ' definedIn: 'Object' definition: 'A message was sent to the receiver for which the receiver has no behavior. Signal a MessageNotUnderstood exception corresponding to the failed message. If the exception resumes, the resumption value is returned as the value of this message. Conforming protocols may refine this message to perform some action other than signaling the exception. ' refinedIn: '' refinement: '' parameters: #( #('message' 'failedMessage' #'unspecified') ) returnValues: #( #( 'Object' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'error: signalerText' forProtocolNamed: #'Object' synopsis: 'Announce an error ' definedIn: 'Object' definition: 'This message is used the announce the occurrence of some type of error condition. The argument should describe the nature of the error. The default behavior is to raise an Error exception as if the message #signal: had been sent to the global Error with signalerText as the argument. Conforming protocols may refine this message to perform some action other than signaling the exception. ' refinedIn: '' refinement: '' parameters: #( #('signalerText' 'readableString' #'unspecified') ) returnValues: #() errors: '' ! 1 protocolManager newMessagePattern: 'hash' forProtocolNamed: #'Object' synopsis: 'Return an integer hash code that can be used in conjunction with an #= comparison. ' definedIn: 'Object' definition: 'An integer value that can be used as a hash code for the receiver is returned. The hash code is intended for use in conjunction with an #= comparison. The range, minimum, and maximum values of the result is implementation defined. Any two objects that are considered equivalent using the #= message must have the same hash value. More formally: receiver = comparand ? receiver hash = comparand hash The hash value of an object need not be temporally invariant. Two independent invocations of #hash with the same receiver may not always yield the same results. Note that collections that use #= to discriminate objects may only reliably store objects whose hash values do not change while the objects are contained in the collection. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'integer' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'identityHash' forProtocolNamed: #'Object' synopsis: 'Return an integer hash code that can be used in conjunction with an #== (identity) comparison. ' definedIn: 'Object' definition: 'An integer value that can be used as a hash code for the receiver is returned. The hash code is intended for use in conjunction with an #== comparison. The range, minimum, or maximum values of the result is implementation defined. The identity hash of an object must be temporally invariant. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'integer' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'isKindOf: candidateClass' forProtocolNamed: #'Object' synopsis: 'Classify an object. ' definedIn: 'Object' definition: 'Return true if the receiver is an instance of candidateClass or is an instance of a general subclass of candidateClass. Otherwise return false. The return value is unspecified if the receiver is a class object or candidateClass is not a class object. ' refinedIn: '' refinement: '' parameters: #( #('candidateClass' 'Object' #'uncaptured') ) returnValues: #( #( 'boolean' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'isMemberOf: candidateClass' forProtocolNamed: #'Object' synopsis: 'Determine whether the receiver is an instance of the argument. ' definedIn: 'Object' definition: 'Return true if the receiver is an instance of candidateClass. Otherwise return false. The return value is unspecified if the receiver is a class object or candidateClass is not a class object. ' refinedIn: '' refinement: '' parameters: #( #('candidateClass' 'Object' #'uncaptured') ) returnValues: #( #( 'boolean' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'isNil' forProtocolNamed: #'Object' synopsis: 'Determine if the receiver is the value of the reserved identifier nil. ' definedIn: 'Object' definition: 'Determine if the receiver is the same object as the value of the reserved identifier nil. Return true if it is, false if it is not. The messages #isNil and #notNil must be implemented to produce consistent results. For a given receiver if the result of #isNil is true then the result of #notNil must be false. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'boolean' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'notNil' forProtocolNamed: #'Object' synopsis: 'Determine if the receiver is not the value of the reserved identifier nil. ' definedIn: 'Object' definition: 'Determine if the receiver is the same object as the value of the reserved identifier nil. Return false if it is, true if it is not. The messages #isNil and #notNil must be implemented to produce consistent results. For a given receiver if the result of #isNil is true then the result of #notNil must be false. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'boolean' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'perform: selector' forProtocolNamed: #'Object' synopsis: 'Send a message using a computed message selector. ' definedIn: 'Object' definition: 'Send to the receiver a message whose selector is selector. Return the value of that message. If the receiver does not have a method for selector normal "message not understood" processing is performed as if the computed message hand been sent using a message send expression. If this occurs, selector may be captured. The perform messages and #respondsTo: must be implemented to produce consistent results. A message to perform a selector, selector, for a given receiver will result in a "message not understood" condition if and only if the value of receiver respondsTo: selector is false. ' refinedIn: '' refinement: '' parameters: #( #('selector' 'selector' #'unspecified') ) returnValues: #( #( 'ANY' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'perform: argument1 with: selector' forProtocolNamed: #'Object' synopsis: 'Send a message using a computed message selector. ' definedIn: 'Object' definition: 'Send to the receiver a message whose selector is selector and whose argument is argument1. Return the value of that message. If the receiver does not have a method for selector normal "message not understood" processing is performed as if the computed message hand been sent using a message send expression. If this occurs, selector and the arguments may be captured. The perform messages and #respondsTo: must be implemented to produce consistent results. A message to perform a selector, selector, for a given receiver will result in a "message not understood" condition if and only if the value of receiver respondsTo: selector is false. Behavior is undefined if the number of arguments does not match that implicitly required by the syntactic form of the selector. ' refinedIn: '' refinement: '' parameters: #( #('argument1' 'ANY' #'unspecified') #('selector' 'selector' #'unspecified') ) returnValues: #( #( 'ANY' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'perform: argument1 with: argument2 with: selector' forProtocolNamed: #'Object' synopsis: 'Send a message using a computed message selector. ' definedIn: 'Object' definition: 'Send to the receiver a message whose selector is selector and whose arguments are argument1, argument2. Return the value of that message. If the receiver does not have a method for selector normal "message not understood" processing is performed as if the computed message hand been sent using a message send expression. If this occurs, selector and the arguments may be captured. The perform messages and #respondsTo: must be implemented to produce consistent results. A message to perform a selector, selector, for a given receiver will result in a "message not understood" condition if and only if the value of receiver respondsTo: selector is false. Behavior is undefined if the number of arguments does not match that implicitly required by the syntactic form of the selector. ' refinedIn: '' refinement: '' parameters: #( #('selector' 'selector' #'unspecified') #('argument1' 'ANY' #'unspecified') #('argument2' 'ANY' #'unspecified') ) returnValues: #( #( 'ANY' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'perform: argument1 with: argument2 with: selector with: argument3' forProtocolNamed: #'Object' synopsis: 'Send a message using a computed message selector. ' definedIn: 'Object' definition: 'Send to the receiver a message whose selector is selector and whose arguments are argument1, argument2, etc. Return the value of that message. If the receiver does not have a method for selector normal "message not understood" processing is performed as if the computed message hand been sent using a message send expression. If this occurs, selector and the arguments may be captured. The perform messages and #respondsTo: must be implemented to produce consistent results. A message to perform a selector, selector, for a given receiver will result in a "message not understood" condition if and only if the value of receiver respondsTo: selector is false. Behavior is undefined if the number of arguments does not match that implicitly required by the syntactic form of the selector. ' refinedIn: '' refinement: '' parameters: #( #('argument3' 'ANY' #'unspecified') #('argument1' 'ANY' #'unspecified') #('argument2' 'ANY' #'unspecified') #('selector' 'selector' #'unspecified') ) returnValues: #( #( 'ANY' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'perform: arguments withArguments: selector' forProtocolNamed: #'Object' synopsis: 'Send a message using a computed message selector and a collection of arguments. ' definedIn: 'Object' definition: 'Send to the receiver a message whose selector is selector and whose arguments are the elements of arguments. Return the value of that message. The first element of arguments is the first argument, the second element is the second argument, and so on. If the receiver does not have a method for the selector normal "message not understood" processing is performed as if the computed message hand been sent using a message send expression. If this occurs, selector and arguments could be captured. The perform messages and #respondsTo: must be implemented to produce consistent results. A message to perform a selector, selector, for a given receiver will result in a "message not understood" condition if and only if the value of receiver respondsTo: selector is false. Behavior is undefined if the number of elements in arguments does not match that implicitly required by the syntactic form of the selector. ' refinedIn: '' refinement: '' parameters: #( #('selector' 'selector' #'unspecified') #('arguments' 'Array' #'unspecified') ) returnValues: #( #( 'ANY' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'printOn: target' forProtocolNamed: #'Object' synopsis: 'Write a textual description of the receiver to a stream. ' definedIn: 'Object' definition: 'The string of characters that would be the result of sending the message #printString to the receiver is written to target. The characters appear on the stream as if each character was, in sequence, written to the stream using the message #nextPut:. ' refinedIn: '' refinement: '' parameters: #( #('target' 'puttableStream' #'uncaptured') ) returnValues: #() errors: '' ! 1 protocolManager newMessagePattern: 'printString' forProtocolNamed: #'Object' synopsis: 'Return a string that describes the receiver. ' definedIn: 'Object' definition: 'A string consisting of a sequence of characters that describe the receiver are returned as the result. The exact sequence of characters that describe an object are implementation defined. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'readableString' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'respondsTo: selector' forProtocolNamed: #'Object' synopsis: 'Determine if the receiver can respond to a specific message selector. ' definedIn: 'Object' definition: 'Return true if the receiver has a method in its behavior that has the message selector selector. Otherwise return false. ' refinedIn: '' refinement: '' parameters: #( #('selector' 'selector' #'uncaptured') ) returnValues: #( #( 'boolean' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'yourself' forProtocolNamed: #'Object' synopsis: 'No operation. Return the receiver as the result. ' definedIn: 'Object' definition: 'Return the receiver of the message. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'Object' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: '~= comparand' forProtocolNamed: #'Object' synopsis: 'Object inequality test. ' definedIn: 'Object' definition: 'This message tests whether the receiver and the comparand are not equivalent objects at the time the message is processed. Return true if the receiver is not equivalent to comparand. Otherwise return false. The meaning of "equivalent" cannot be precisely defined but the intent is that two objects are considered equivalent if they can be used interchangeably. Conforming protocols may choose to more precisely define the meaning of "equivalent". The result must be equivalent to the Boolean negation of the result of sending the message #= to the receiver with comparand as the argument. The value of receiver ~= comparand is true if and only if the value of comparand ~= receiver would also be true. ' refinedIn: '' refinement: '' parameters: #( #('comparand' 'Object' #'uncaptured') ) returnValues: #( #( 'boolean' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: '~~ comparand' forProtocolNamed: #'Object' synopsis: 'Negated object identity test. ' definedIn: 'Object' definition: 'This message tests whether the receiver and the comparand are different objects. Return true if the receiver is not the same object as comparand. Otherwise return false. The result must be equivalent to the Boolean negation of the result of sending the message #== to the receiver with comparand as the argument. The value of receiver ~~ comparand is true if and only if the value of comparand ~~ receiver would also be true. ' refinedIn: '' refinement: '' parameters: #( #('comparand' 'Object' #'uncaptured') ) returnValues: #( #( 'boolean' #'unspecified') ) errors: '' ! (1 protocolManager newProtocolNamed: #'Object class' conformsToProtocolNames: #(#'instantiator' #'classDescription') ) protocolDescription: ' This protocol describes the behavior the class object whose global identifier is ''Object'', which is the traditional root of the class hierarchy. This class must be implemented in such a way that it is not fragile. A class is said to be fragile if it is implemented in such a way that subclasses of that class can change the behavior of any standard-specified method without overriding the implementation of those methods. This can happen when a method is implemented to use an auxiliary method that is not specified in the standard, which the subclass then (possibly unintentionally) overrides. The inherited method will then invoke the subclass'' implementation of the auxiliary method rather than the expected implementation in the superclass. One way to ensure that the implementation of a class is not fragile is to ensure that any message sent to self is either part of the specified behavior for that class or has a selector that begins with an underscore. Alternatively, an implementation may use implementation-specific means to implement these methods in a way that makes them non-fragile. Standard Globals Object Conforms to the protocol . It is a class object and the name of a class definition. ' ! 1 protocolManager newMessagePattern: 'new' forProtocolNamed: #'Object class' synopsis: 'Create a new object. ' definedIn: 'instantiator' definition: 'Return a newly created object initialized to a standard initial state. ' refinedIn: 'Object class' refinement: 'Return a newly created instance of the receiver. ' parameters: #() returnValues: #( #( 'Object' #'new') ) errors: '' ! (1 protocolManager newProtocolNamed: #'OrderedCollection' conformsToProtocolNames: #(#'sequencedCollection' #'extensibleCollection' #'sequencedContractibleCollection') ) protocolDescription: ' Represents an ordered, variable sized collection of objects. Elements may be added, removed or inserted, and can be accessed using external integer keys. ' ! 1 protocolManager newMessagePattern: 'add: newElement' forProtocolNamed: #'OrderedCollection' synopsis: 'Add newElement to the receiver''s elements. ' definedIn: 'extensibleCollection' definition: 'This message adds a newElement to the receiver. Unless specifically refined, the position of the newElement in the element traversal order is unspecified. Conformant protocols may place restrictions on the type of objects that are valid elements. Unless otherwise specified, any object is acceptable. ' refinedIn: 'OrderedCollection' refinement: 'The newElement is added to the end of the receiver''s elements so that it becomes the last element in the traversal order. This message is equivalent to #addLast: for the receiver with newElement as the parameter. ' parameters: #( #('newElement' 'Object' #'captured') ) returnValues: #() errors: '' ! 1 protocolManager newMessagePattern: 'add: newElement after: target' forProtocolNamed: #'OrderedCollection' synopsis: 'Add newElement to the receiver immediately following the first element which is equivalent to target. ' definedIn: 'OrderedCollection' definition: 'Add newElement to the receiver immediately following the first element which is equivalent to target. An element immediately follows another if its index is one greater than that of the other. The order used to determine which of the receiver''s elements is the first to equal target is the traversal order defined by #do: for the receiver. If the receiver does not include target, the operation fails. ' refinedIn: '' refinement: '' parameters: #( #('newElement' 'Object' #'captured') #('target' 'Object' #'uncaptured') ) returnValues: #( #( 'Object' #'state') ) errors: 'If there is no element in the receiver which is equivalent to target. ' ! 1 protocolManager newMessagePattern: 'add: newElement afterIndex: index' forProtocolNamed: #'OrderedCollection' synopsis: 'Add newElement to the receiver immediately following the element at position index. ' definedIn: 'OrderedCollection' definition: 'Add newElement to the receiver immediately following the element at position index. newElement is inserted at position index + 1. If index is equal to 0, newElement becomes the first element of the receiver. ' refinedIn: '' refinement: '' parameters: #( #('newElement' 'Object' #'captured') #('index' 'integer' #'uncaptured') ) returnValues: #( #( 'Object' #'state') ) errors: 'If index < 0. If index > receiver''s size. ' ! 1 protocolManager newMessagePattern: 'add: newElement before: target' forProtocolNamed: #'OrderedCollection' synopsis: 'Add newElement to the receiver immediately before the first element which is equivalent to target. ' definedIn: 'OrderedCollection' definition: 'Add newElement to the receiver immediately before the first element which is equivalent to target. An element immediately precedes another if its index is one less than that of the other. The order used to determine which of the receiver''s elements is the first to equal target in the traversal order defined by #do: for the receiver. If the receiver does not include target, the operation fails. ' refinedIn: '' refinement: '' parameters: #( #('newElement' 'Object' #'captured') #('target' 'Object' #'uncaptured') ) returnValues: #( #( 'Object' #'state') ) errors: 'If there is no element in the receiver which is equivalent to target. If the element which is equal to target is the last element in the receiver. ' ! 1 protocolManager newMessagePattern: 'add: newElement beforeIndex: index' forProtocolNamed: #'OrderedCollection' synopsis: 'Add newElement to the receiver immediately before the element at position index. ' definedIn: 'OrderedCollection' definition: 'Add newElement to the receiver immediately before the element at position index in the receiver. If index equals the receiver''s size plus 1 newElement will be inserted at the end of the receiver. The parameter index must be a positive integer less than or equal to the receiver''s size plus 1. ' refinedIn: '' refinement: '' parameters: #( #('index' 'integer' #'uncaptured') #('newElement' 'Object' #'captured') ) returnValues: #( #( 'Object' #'state') ) errors: 'If index <=0. If index > receiver''s size + 1. ' ! 1 protocolManager newMessagePattern: 'addAll: target after: newElements' forProtocolNamed: #'OrderedCollection' synopsis: 'Add each element of newElements to the receiver immediately after the first element in the receiver which is equivalent to target. Answer newElements. ' definedIn: 'OrderedCollection' definition: 'Add the elements of newElements to the receiver in the traversal order defined by #do: for newElements. The new elements are inserted in the receiver immediately after the first element in the receiver which is equivalent to target. An element immediately follows another if its index is one greater than that of the other. The order used to determine which of the receiver''s elements is the first to equal target is the traversal order defined by #do: for the receiver. If the receiver does not include target, the operation fails. ' refinedIn: '' refinement: '' parameters: #( #('newElements' 'collection' #'unspecified') #('target' 'Object' #'uncaptured') ) returnValues: #() errors: 'If there is no element in the receiver which is equivalent to target. ' ! 1 protocolManager newMessagePattern: 'addAll: index afterIndex: newElements' forProtocolNamed: #'OrderedCollection' synopsis: 'Insert the elements of newElements in the receiver immediately after the element at position index. Answer newElements. ' definedIn: 'OrderedCollection' definition: 'Add the elements of newElements to the receiver in the traversal order defined by #do: for newElements. The new elements are inserted in the receiver immediately after the element in the receiver at position index. If index is equal to 0, newElements are inserted at the beginning of the receiver. The parameter index must be a non-negative integer less than or equal to the receiver''s size. ' refinedIn: '' refinement: '' parameters: #( #('newElements' 'collection' #'unspecified') #('index' 'integer' #'uncaptured') ) returnValues: #() errors: 'If index < 0. If index > receiver''s size. ' ! 1 protocolManager newMessagePattern: 'addAll: target before: newElements' forProtocolNamed: #'OrderedCollection' synopsis: 'Add each element of newElements to the receiver immediately before the first element in the receiver which is equivalent to target. Answer newElements. ' definedIn: 'OrderedCollection' definition: 'Add the elements of newElements to the receiver in the traversal order defined by #do: for newElements. The new elements are inserted in the receiver immediately before the first element in the receiver which is equivalent to target. An element immediately follows another if its index is one greater than that of the other. The order used to determine which of the receiver''s elements is the first to equal target is the traversal order defined by #do: for the receiver. If the receiver does not include target, the operation fails. ' refinedIn: '' refinement: '' parameters: #( #('newElements' 'collection' #'unspecified') #('target' 'Object' #'uncaptured') ) returnValues: #() errors: '' ! 1 protocolManager newMessagePattern: 'addAll: index beforeIndex: newElements' forProtocolNamed: #'OrderedCollection' synopsis: 'Insert the elements of newElements in the receiver immediately before the element at position index. Answer newElements. ' definedIn: 'OrderedCollection' definition: 'Add the elements of newElements to the receiver in the traversal order defined by #do: for newElements. The new elements are inserted in the receiver immediately before the element in the receiver at position index. If index equals the receiver''s size plus 1 newElements will be inserted at the end of the receiver. The parameter index must be a positive integer less than or equal to the receiver''s size plus 1. ' refinedIn: '' refinement: '' parameters: #( #('index' 'integer' #'uncaptured') #('newElements' 'collection' #'unspecified') ) returnValues: #() errors: 'If index <=0. If index > receiver''s size + 1. ' ! 1 protocolManager newMessagePattern: 'addAllFirst: newElements' forProtocolNamed: #'OrderedCollection' synopsis: 'Add each element of newElements to the beginning of the receiver''s elements. Answer newElements. ' definedIn: 'OrderedCollection' definition: 'This message is used to iteratively add each element of a given collection to the beginning of the receiver''s elements. The operation is equivalent to adding each successive element of newElements to the receiver using the #addFirst: message with the element as the parameter, where the newElements are traversed in the order specified by the #reverseDo: message for newElements. ' refinedIn: '' refinement: '' parameters: #( #('newElements' 'sequencedCollection' #'unspecified') ) returnValues: #() errors: '' ! 1 protocolManager newMessagePattern: 'addAllLast: newElements' forProtocolNamed: #'OrderedCollection' synopsis: 'Add each element of newElements to the end of the receiver''s elements. Answer newElements. ' definedIn: 'OrderedCollection' definition: 'This message is used to iteratively add each element of a given collection to the end of the receiver''s elements. The operation is equivalent to adding each successive element of newElements to the receiver using the #addLast: message with the element as the parameter, where the newElements are traversed in the order specified by the #do: message for newElements. ' refinedIn: '' refinement: '' parameters: #( #('newElements' 'sequencedCollection' #'unspecified') ) returnValues: #( #( 'sequencedCollection' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'addFirst: newElement' forProtocolNamed: #'OrderedCollection' synopsis: 'Add newElement to the beginning of the receiver''s elements. Answer newElement. ' definedIn: 'OrderedCollection' definition: 'The newElement is added to the beginning of the receiver''s elements so that it becomes the first element in the traversal order. ' refinedIn: '' refinement: '' parameters: #( #('newElement' 'Object' #'captured') ) returnValues: #() errors: '' ! 1 protocolManager newMessagePattern: 'addLast: newElement' forProtocolNamed: #'OrderedCollection' synopsis: 'Add newElement to the end of the receiver''s elements. Answer newElement. ' definedIn: 'OrderedCollection' definition: 'The newElement is added to the end of the receiver''s elements so that it becomes the last element in the traversal order. ' refinedIn: '' refinement: '' parameters: #( #('newElement' 'Object' #'captured') ) returnValues: #() errors: '' ! (1 protocolManager newProtocolNamed: #'OrderedCollection factory' conformsToProtocolNames: #(#'initializableCollection factory') ) protocolDescription: ' This protocol defines the behavior of objects that can be used to create fixed sized ordered collections of objects which can be accessed externally using integer keys. Standard Globals OrderedCollection Conforms to the protocol . Its language element type is unspecified. This is a factory and discriminator for collections that conform to . ' ! 1 protocolManager newMessagePattern: 'new' forProtocolNamed: #'OrderedCollection factory' synopsis: 'Create a new object. ' definedIn: 'instantiator' definition: 'Return a newly created object initialized to a standard initial state. ' refinedIn: 'OrderedCollection factory' refinement: 'Create a new that is optimized to store an implementation defined number of elements. The new collection initially contains no elements. ' parameters: #() returnValues: #( #( 'OrderedCollection' #'new') ) errors: '' ! 1 protocolManager newMessagePattern: 'new: count' forProtocolNamed: #'OrderedCollection factory' synopsis: 'Create a new collection. The parameter count constrains the number of elements in the result. ' definedIn: 'collection factory' definition: 'Return a new collection that has space for at least count elements. Conforming protocols may refine this message. In particular, the effect of the parameter count should be specified in refinements. It can be used to specify the exact number of elements, the minimum number, or in some cases can even be interpreted as a hint from the programmer, with no guarantee that the requested number of instance variables will actually be allocated. Unless otherwise stated the initial values of elements of the new instance of the receiver are unspecified. ' refinedIn: 'OrderedCollection factory' refinement: 'The parameter count represents a hint for space allocation. The new collection is to optimized to contain count elements. The new collection initially contains no elements. ' parameters: #( #('count' 'integer' #'unspecified') ) returnValues: #( #( 'OrderedCollection' #'new') ) errors: 'count<0 ' ! 1 protocolManager newMessagePattern: 'with: element1' forProtocolNamed: #'OrderedCollection factory' synopsis: 'Create a collection initially containing the argument element. ' definedIn: 'initializableCollection factory' definition: 'Return a new collection containing one element.The collection contains the argument as its element. Conforming protocols may impose restrictions on the values of the argument and hence the element type. ' refinedIn: 'OrderedCollection factory' refinement: 'The argument is at index position 1. ' parameters: #( #('element1' 'Object' #'captured') ) returnValues: #( #( 'OrderedCollection' #'new') ) errors: 'If any of the arguments do not meet the element type constraints of the result object ' ! 1 protocolManager newMessagePattern: 'with: element1 with: element2' forProtocolNamed: #'OrderedCollection factory' synopsis: 'Create a collection initially containing the argument elements. ' definedIn: 'initializableCollection factory' definition: 'Return a new collection containing two elements. The collection contains the arguments as its elements. Conforming protocols may impose restrictions on the values of the arguments and hence the element types. ' refinedIn: 'OrderedCollection factory' refinement: 'The first argument is at index position 1, the second argument is at index position 2. ' parameters: #( #('element1' 'Object' #'captured') #('element2' 'Object' #'captured') ) returnValues: #( #( 'OrderedCollection' #'new') ) errors: 'If any of the arguments do not meet the element type constraints of the result object ' ! 1 protocolManager newMessagePattern: 'with: element1 with: element2 with: element3' forProtocolNamed: #'OrderedCollection factory' synopsis: 'Create a collection initially containing the argument elements. ' definedIn: 'initializableCollection factory' definition: 'Return a new collection containing three elements. The collection contains the arguments as its elements. Conforming protocols may impose restrictions on the values of the arguments and hence the element types. ' refinedIn: 'OrderedCollection factory' refinement: 'The first argument is at index position 1, the second argument is at index position 2, and so on. ' parameters: #( #('element1' 'Object' #'captured') #('element2' 'Object' #'captured') #('element3' 'Object' #'captured') ) returnValues: #( #( 'OrderedCollection' #'new') ) errors: 'If any of the arguments do not meet the element type constraints of the result object ' ! 1 protocolManager newMessagePattern: 'with: element3 with: element1 with: element4 with: element2' forProtocolNamed: #'OrderedCollection factory' synopsis: 'Create a collection initially containing the argument elements. ' definedIn: 'initializableCollection factory' definition: 'Return a new collection containing four elements. The collection contains the arguments as its elements. Conforming protocols may impose restrictions on the values of the arguments and hence the element types. ' refinedIn: 'OrderedCollection factory' refinement: 'The first argument is at index position 1, the second argument is at index position 2, and so on. ' parameters: #( #('element4' 'Object' #'captured') #('element2' 'Object' #'captured') #('element3' 'Object' #'captured') #('element1' 'Object' #'captured') ) returnValues: #( #( 'OrderedCollection' #'new') ) errors: 'If any of the arguments do not meet the element type constraints of the result object ' ! 1 protocolManager newMessagePattern: 'withAll: newElements' forProtocolNamed: #'OrderedCollection factory' synopsis: 'Create a collection containing only the elements of newElements. ' definedIn: 'initializableCollection factory' definition: 'Return a new collection whose elements are the elements of newElements. Conforming protocols may impose restrictions on the values of newElements. ' refinedIn: 'OrderedCollection factory' refinement: 'If the elements of newElements are ordered then their ordering establishing their index positions in the new collection. ' parameters: #( #('newElements' 'collection' #'unspecified') ) returnValues: #( #( 'OrderedCollection' #'new') ) errors: 'If any of the elements of newElements do not meet the element type constraints of the result object ' ! (1 protocolManager newProtocolNamed: #'puttableStream' conformsToProtocolNames: #(#'Object') ) protocolDescription: ' An object conforming to allows objects to be added to its past sequence values. ' ! 1 protocolManager newMessagePattern: 'cr' forProtocolNamed: #'puttableStream' synopsis: 'Writes an end-of-line sequence to the receiver. ' definedIn: 'puttableStream' definition: 'A sequence of character objects that constitute the implementation-defined end-of-line sequence is added to the receiver in the same manner as if the message #nextPutAll: was sent to the receiver with an argument string whose elements are the sequence of characters. ' refinedIn: '' refinement: '' parameters: #() returnValues: #() errors: 'It is erroneous if any element of the end-of-line sequence is an object that does not conform to the receiver''s sequence value type. ' ! 1 protocolManager newMessagePattern: 'flush' forProtocolNamed: #'puttableStream' synopsis: 'Update a stream''s backing store. ' definedIn: 'puttableStream' definition: 'Upon return, if the receiver is a write-back stream, the state of the stream backing store must be consistent with the current state of the receiver. If the receiver is not a write-back stream, the effect of this message is unspecified. ' refinedIn: '' refinement: '' parameters: #() returnValues: #() errors: '' ! 1 protocolManager newMessagePattern: 'nextPut: anObject' forProtocolNamed: #'puttableStream' synopsis: 'Writes the argument to the stream. ' definedIn: 'puttableStream' definition: 'Appends anObject to the receiver''s past sequence values. If the receiver''s future sequence values is not empty, removes its first object. ' refinedIn: '' refinement: '' parameters: #( #('anObject' 'Object' #'captured') ) returnValues: #() errors: 'It is erroneous if anObject is an object that does not conform to the receiver''s sequence value type. ' ! 1 protocolManager newMessagePattern: 'nextPutAll: aCollection' forProtocolNamed: #'puttableStream' synopsis: 'Enumerates the argument, adding each element to the receiver ' definedIn: 'puttableStream' definition: 'Has the effect of enumerating the aCollection with the message #do: and adding each element to the receiver with #nextPut:. That is, aCollection do: [:each | receiver nextPut: each] ' refinedIn: '' refinement: '' parameters: #( #('aCollection' 'collection' #'uncaptured') ) returnValues: #() errors: 'It is erroneous if any element of aCollection is an object that does not conform to the receiver''s sequence value type. ' ! 1 protocolManager newMessagePattern: 'space' forProtocolNamed: #'puttableStream' synopsis: 'Writes a space character to the receiver. ' definedIn: 'puttableStream' definition: 'The effect is the same as sending the message #nextPut: to the receiver with an argument that is the object that is the value returned when the message #space is sent to the standard global Character. ' refinedIn: '' refinement: '' parameters: #() returnValues: #() errors: 'It is erroneous if the space character is an object that does not conform to the receiver''s sequence value type. ' ! 1 protocolManager newMessagePattern: 'tab' forProtocolNamed: #'puttableStream' synopsis: 'Writes a tab character to the receiver. ' definedIn: 'puttableStream' definition: 'The effect is the same as sending the message #nextPut: to the receiver with an argument that is the object that is the value returned when the message #tab is sent to the standard global Character. ' refinedIn: '' refinement: '' parameters: #() returnValues: #() errors: 'It is erroneous if the tab character is an object that does not conform to the receiver''s sequence value type. ' ! (1 protocolManager newProtocolNamed: #'rational' conformsToProtocolNames: #(#'number') ) protocolDescription: ' Rational numbers may be either integers or fractions. An integer is logically a fraction whose denominator is one. This protocol is necessary because some integer and most fraction operations can produce results that may be either an integer or a fraction. ' ! 1 protocolManager newMessagePattern: 'denominator' forProtocolNamed: #'rational' synopsis: 'Answer the denominator of the receiver. ' definedIn: 'rational' definition: 'Treating the receiver as a fraction, answer the lowest common denominator of the receiver. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'integer' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'numerator' forProtocolNamed: #'rational' synopsis: 'Answer the numerator of the receiver. ' definedIn: 'rational' definition: 'Treating the receiver as a fraction reduced to its lowest common denominator, answer the integer numerator. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'integer' #'unspecified') ) errors: '' ! (1 protocolManager newProtocolNamed: #'readableString' conformsToProtocolNames: #(#'sequencedReadableCollection' #'magnitude') ) protocolDescription: ' Provides protocol for string operations such as copying, comparing, replacing, converting, indexing, and matching. All objects that conform to the protocol are comparable. ' ! 1 protocolManager newMessagePattern: ', operand' forProtocolNamed: #'readableString' synopsis: 'Answer a new collection which is the concatenation of the receiver and operand. ' definedIn: 'sequencedReadableCollection' definition: 'Answer a new collection containing all of the receiver''s elements in their original order followed by all of the elements of operand, in their original order. The size of the new collection is equal to the sum of the sizes of the receiver and operand, as defined by the #size message. Collections that enforce an ordering on their elements are permitted to refine this message to reorder the result. Unless specifically refined, this message is defined to answer an instance of the same type as the receiver. ' refinedIn: 'readableString' refinement: 'The parameter operand must be a . ' parameters: #( #('operand' 'readableString' #'uncaptured') ) returnValues: #( #( 'readableString' #'new') ) errors: '' ! 1 protocolManager newMessagePattern: '< operand' forProtocolNamed: #'readableString' synopsis: 'Answer true if the receiver is less than operand. Answer false otherwise. ' definedIn: 'magnitude' definition: 'Answer true if the receiver is less than operand with respect to the ordering defined for them. Answer false otherwise. The result is undefined if the receiver and operand are not comparable. The semantics of the natural ordering must be defined by refinement, which may also restrict the type of operand. ' refinedIn: 'readableString' refinement: 'Answer true if the receiver collates before operand, according to the implementation defined collating algorithm. Answer false otherwise. ' parameters: #( #('operand' 'readableString' #'uncaptured') ) returnValues: #( #( 'boolean' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: '<= operand' forProtocolNamed: #'readableString' synopsis: 'Answer true if the receiver is less than or equal to operand. Answer false otherwise. ' definedIn: 'magnitude' definition: 'Answer true if the receiver would answer true to either the #< or #= message with operand as the parameter. Answer false otherwise. The result is undefined if the receiver and operand are not comparable. ' refinedIn: 'readableString' refinement: 'Answer true if the receiver answers true to either the #< or #sameAs: messages with operand as the parameter. Answer false otherwise. ' parameters: #( #('operand' 'readableString' #'uncaptured') ) returnValues: #( #( 'boolean' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: '> operand' forProtocolNamed: #'readableString' synopsis: 'Answer true if the receiver is greater than operand. Answer false otherwise. ' definedIn: 'magnitude' definition: 'Answer true if the receiver is greater than operand with respect to the natural ordering. Answer false otherwise. The result is undefined if the receiver and operand are not comparable. The semantics of the natural ordering must be defined by refinement, which may also restrict the type of operand. ' refinedIn: 'readableString' refinement: 'Answer true if the receiver collates after operand, according to the implementation defined collating algorithm. Answer false otherwise. ' parameters: #( #('operand' 'readableString' #'uncaptured') ) returnValues: #( #( 'boolean' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: '>= operand' forProtocolNamed: #'readableString' synopsis: 'Answer true if the receiver is greater than or equal to operand. Answer false otherwise. ' definedIn: 'magnitude' definition: 'Answer true if the receiver answers true to either the #> or #= message with operand as the parameter. Answer false otherwise. The result is undefined if the receiver and operand are not comparable. ' refinedIn: 'readableString' refinement: 'Answer true if the receiver answers true to either the #> or #sameAs: messages with operand as the parameter. Answer false otherwise. ' parameters: #( #('operand' 'readableString' #'uncaptured') ) returnValues: #( #( 'boolean' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'asLowercase' forProtocolNamed: #'readableString' synopsis: 'Answer a new string which contains all of the elements of the receiver converted to their lower case equivalents. ' definedIn: 'readableString' definition: 'Answer a new string which contains all of the elements of the receiver converted to their lower case equivalents. Individual element of the string are converted as if they were receivers of the message #asLowercase. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'readableString' #'new') ) errors: '' ! 1 protocolManager newMessagePattern: 'asString' forProtocolNamed: #'readableString' synopsis: 'Answer a string containing the same characters as the receiver. ' definedIn: 'readableString' definition: 'Answer a string containing the same characters as the receiver, in their original order. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'readableString' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'asSymbol' forProtocolNamed: #'readableString' synopsis: 'Answer a symbol containing the same characters as the receiver. ' definedIn: 'readableString' definition: 'Answer a symbol containing the same characters as the receiver, in their original order. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'symbol' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'asUppercase' forProtocolNamed: #'readableString' synopsis: 'Answer a new string which contains all of the elements of the receiver converted to their upper case equivalents. ' definedIn: 'readableString' definition: 'Answer a new string which contains all of the elements of the receiver converted to their upper case equivalents. Individual element of the string are converted as if they were receivers of the message #asUppercase. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'readableString' #'new') ) errors: '' ! 1 protocolManager newMessagePattern: 'copyReplaceAll: targetElements with: replacementElements' forProtocolNamed: #'readableString' synopsis: 'Answer a new collection in which all subsequences of elements in the receiver matching targetElements are replaced in the new collection by the elements in replacementElements. ' definedIn: 'sequencedReadableCollection' definition: 'Answer a new collection with the elements of the receiver in their original order, except where a subsequence in the receiver matches targetElements. A subsequence in the receiver is said to match the elements of targetElements if: 1. They have the same number of elements. 2. For all indices of the subsequence, the element in the subsequence at a given index is equivalent to the element in targetElements at the same index. Where a subsequence match is found, the elements from replacementElements are placed in the new collection instead. Unless specifically refined, this message is defined to answer an instance of the same class as the receiver. Collections that enforce an ordering on their elements are permitted to refine this message to reorder the result. ' refinedIn: 'readableString' refinement: 'The elements of targetElements and replacementElements must conform to the protocol and be valid elements for the result. ' parameters: #( #('replacementElements' 'sequencedReadableCollection' #'unspecified') #('targetElements' 'sequencedReadableCollection' #'uncaptured') ) returnValues: #( #( 'readableString' #'new') ) errors: '' ! 1 protocolManager newMessagePattern: 'copyReplaceFrom: stop to: replacementElements with: start' forProtocolNamed: #'readableString' synopsis: 'Answer a new collection, containing the same elements as the receiver, but with the elements in the receiver between start and stop inclusive replaced by the elements in replacementElements. ' definedIn: 'sequencedReadableCollection' definition: 'This message can be used to insert, append, or replace. The size of replacementElements (as defined by #size) need not be the same as the number of elements being replaced. There are three cases: 1. If stop = start - 1 , and start is less than or equal to the size of the receiver, then the replacementElements are inserted between the elements at index stop and start. None of the receiver''s elements are replaced. 2. If stop = the size of the receiver and start = stop + 1, then the operation is an append, and the replacementElements are placed at the end of the new collection. 3. Otherwise, the operation is a replacement, and the receiver''s elements in the given range are replaced by the elements from replacementElements. In all cases, the resulting collection consists of the receiver''s elements from indices 1 to start - 1 in their original order, followed by the elements of replacementElements, followed by the remainder of the receiver''s elements from index stop + 1 in their original order. The size of the result is the receiver''s size - (stop - start + 1) + the replacementElements size. The parameters start and stop must be positive. Unless specifically refined, this message is defined to answer an instance of the same class as the receiver''s class. Collections that enforce an ordering on their elements are permitted to refine this message to reorder the result. ' refinedIn: 'readableString' refinement: 'The elements of replacementElements must be characters. ' parameters: #( #('start' 'integer' #'uncaptured') #('stop' 'integer' #'uncaptured') #('replacementElements' 'sequencedReadableCollection' #'unspecified') ) returnValues: #( #( 'readableString' #'new') ) errors: '' ! 1 protocolManager newMessagePattern: 'copyReplacing: replacementElement withObject: targetElement' forProtocolNamed: #'readableString' synopsis: 'Answer a new collection conforming to the same protocols as the receiver, in which any occurrences of targetElement are replaced by replacementElement. ' definedIn: 'sequencedReadableCollection' definition: 'A new collection is created and initialized with the same elements as the receiver in the same order, except that any objects in the receiver which are equivalent to targetElement are replaced in the new collection by replacementElement. Unless specifically refined, this message is defined to answer an instance of the same class as the receiver. Collections that enforce an ordering on their elements are permitted to refine this message to reorder the result. ' refinedIn: 'readableString' refinement: 'The parameters targetElement and replacementElement must be characters. ' parameters: #( #('replacementElement' 'Character' #'captured') #('targetElement' 'Character' #'uncaptured') ) returnValues: #( #( 'readableString' #'new') ) errors: '' ! 1 protocolManager newMessagePattern: 'copyWith: newElement' forProtocolNamed: #'readableString' synopsis: 'Answer a new collection containing the same elements as the receiver, with newElement added. ' definedIn: 'sequencedReadableCollection' definition: 'Answer a new collection with size one greater than the size of the receiver containing the elements of the receiver and newElement placed at the end. Unless specifically refined, this message is defined to answer an instance of the same class as the receiver. Collections that enforce an ordering on their elements are permitted to refine this message to reorder the result. ' refinedIn: 'readableString' refinement: 'The parameter newElement must be characters. ' parameters: #( #('newElement' 'Character' #'captured') ) returnValues: #( #( 'readableString' #'new') ) errors: '' ! 1 protocolManager newMessagePattern: 'sameAs: operand' forProtocolNamed: #'readableString' synopsis: 'Answer true if the receiver collates the same as operand. Answer false otherwise. ' definedIn: 'readableString' definition: 'Answer true if the receiver collates the same as operand, according to the implementation-defined collating algorithm. Answer false otherwise. This message differs from the #= message because two strings which are not equal can collate the same, and because the receiver and operand do not need to conform to the same protocols. ' refinedIn: '' refinement: '' parameters: #( #('operand' 'readableString' #'uncaptured') ) returnValues: #( #( 'boolean' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'subStrings: separators' forProtocolNamed: #'readableString' synopsis: 'Answer an array containing the substrings in the receiver separated by the elements of separators. ' definedIn: 'readableString' definition: 'Answer an array of strings. Each element represents a group of characters separated by any of the characters in the list of separators. ' refinedIn: '' refinement: '' parameters: #( #('separators' 'sequencedReadableCollection' #'uncaptured') ) returnValues: #( #( 'Array' #'unspecified') ) errors: 'If the list of separators contains anything other than characters. ' ! (1 protocolManager newProtocolNamed: #'readFileStream' conformsToProtocolNames: #(#'gettableStream' #'FileStream') ) protocolDescription: ' Provides protocol for traversing and reading elements in an external file. The sequence values are provided by the external file which also serves as the stream backing store. ' ! 1 protocolManager newMessagePattern: 'next: amount' forProtocolNamed: #'readFileStream' synopsis: 'Returns a collection of the next amount objects in the stream. ' definedIn: 'gettableStream' definition: 'A number of objects equal to amount are removed from the receiver''s future sequence values and appended, in order, to the end of the receiver''s past sequence values. A collection whose elements consist of those objects, in the same order, is returned. If amount is equal to 0 an empty collection is returned. The result is undefined if amount is larger than the number of objects in the receiver''s future sequence values. ' refinedIn: 'readFileStream' refinement: 'The result collection will conform to the same protocols as the object that would result if the message #contents was sent to the receiver. ' parameters: #( #('amount' 'integer' #'uncaptured') ) returnValues: #( #( 'sequencedReadableCollection' #'new') ) errors: 'amount < 0 ' ! 1 protocolManager newMessagePattern: 'upTo: anObject' forProtocolNamed: #'readFileStream' synopsis: 'Returns a collection of all of the objects in the receiver up to, but not including, the next occurrence of the argument. Sets the stream to read the object just after the next occurrence of the argument. If the argument is not found and the end of the stream is encountered, an ordered collection of the objects read is returned. ' definedIn: 'gettableStream' definition: 'Each object in the receiver''s future sequence values up to and including the first occurrence of an object that is equivalent to anObject is removed from the future sequence values and appended to the receiver''s past sequence values. A collection, containing, in order, all of the transferred objects except the object (if any) that is equivalent to anObject is returned. If the receiver''s future sequence values is initially empty, an empty collection is returned. ' refinedIn: 'readFileStream' refinement: 'The result collection will conform to the same protocols as the object that would result if the message #contents was sent to the receiver. ' parameters: #( #('anObject' 'Object' #'uncaptured') ) returnValues: #( #( 'sequencedReadableCollection' #'new') ) errors: '' ! (1 protocolManager newProtocolNamed: #'ReadStream' conformsToProtocolNames: #(#'collectionStream' #'gettableStream') ) protocolDescription: ' An object conforming to has a positionable sequence of values that can be read. The sequence values are provided by a sequenced collection that serves as the stream backing store. ' ! 1 protocolManager newMessagePattern: 'next: amount' forProtocolNamed: #'ReadStream' synopsis: 'Returns a collection of the next amount objects in the stream. ' definedIn: 'gettableStream' definition: 'A number of objects equal to amount are removed from the receiver''s future sequence values and appended, in order, to the end of the receiver''s past sequence values. A collection whose elements consist of those objects, in the same order, is returned. If amount is equal to 0 an empty collection is returned. The result is undefined if amount is larger than the number of objects in the receiver''s future sequence values. ' refinedIn: 'ReadStream' refinement: 'The result collection will conform to the same protocols as the object that would result if the message #select: was sent to the object that serves as the stream backing store. ' parameters: #( #('amount' 'integer' #'uncaptured') ) returnValues: #( #( 'sequencedReadableCollection' #'new') ) errors: 'amount < 0 ' ! 1 protocolManager newMessagePattern: 'upTo: anObject' forProtocolNamed: #'ReadStream' synopsis: 'Returns a collection of all of the objects in the receiver up to, but not including, the next occurrence of the argument. Sets the stream to read the object just after the next occurrence of the argument. If the argument is not found and the end of the stream is encountered, an ordered collection of the objects read is returned. ' definedIn: 'gettableStream' definition: 'Each object in the receiver''s future sequence values up to and including the first occurrence of an object that is equivalent to anObject is removed from the future sequence values and appended to the receiver''s past sequence values. A collection, containing, in order, all of the transferred objects except the object (if any) that is equivalent to anObject is returned. If the receiver''s future sequence values is initially empty, an empty collection is returned. ' refinedIn: 'ReadStream' refinement: 'The result collection will conform to the same protocols as the object that would result if the message #select: was sent to the object that serves as the stream backing store. ' parameters: #( #('anObject' 'Object' #'uncaptured') ) returnValues: #( #( 'sequencedReadableCollection' #'new') ) errors: '' ! (1 protocolManager newProtocolNamed: #'ReadStream factory' conformsToProtocolNames: #(#'Object') ) protocolDescription: ' provides for the creation of objects conforming to the protocol whose sequence values are supplied by a collection. Standard Globals ReadStream Conforms to the protocol . Its language element type is unspecified. This is a factory for streams that conform to . ' ! 1 protocolManager newMessagePattern: 'on: aCollection' forProtocolNamed: #'ReadStream factory' synopsis: 'Returns a stream that reads from the given collection. ' definedIn: 'ReadStream factory' definition: 'Returns an object conforming to whose future sequence values initially consist of the elements of aCollection and which initially has no past sequence values. The ordering of the sequence values is the same as the ordering used by #do: when sent to aCollection. The stream backing store of the returned object is aCollection. ' refinedIn: '' refinement: '' parameters: #( #('aCollection' 'sequencedReadableCollection' #'captured') ) returnValues: #( #( 'ReadStream' #'new') ) errors: '' ! (1 protocolManager newProtocolNamed: #'ReadWriteStream' conformsToProtocolNames: #(#'ReadStream' #'WriteStream') ) protocolDescription: ' An object conforming to can read from its future sequence values or write to its past sequence values. The sequence values are provided by a collection that serves as the stream backing store. It is implementation defined whether a is a write-back stream. Even if a is not a write-back stream, its associated collection may be subject to modification in an unspecified manner as long as it is associated with the stream. ' ! (1 protocolManager newProtocolNamed: #'ReadWriteStream factory' conformsToProtocolNames: #(#'Object') ) protocolDescription: ' provides for the creation of objects conforming to the protocol whose sequence values are supplied by a collection. Standard Globals ReadWriteStream Conforms to the protocol . Its language element type is unspecified. This is a factory for streams that conform to . ' ! 1 protocolManager newMessagePattern: 'with: aCollection' forProtocolNamed: #'ReadWriteStream factory' synopsis: 'Returns a stream that reads the elements of the given collection and can write new elements. ' definedIn: 'ReadWriteStream factory' definition: 'Returns an object conforming to whose past sequence values initially consist of the elements of aCollection and which initially has no future sequence values. The ordering of the sequence values is the same as the ordering used by #do: when sent to aCollection. The stream backing store of the returned object is aCollection. The sequence value type of the write stream is the element type of aCollection. Any restrictions on objects that may be elements of aCollection also apply to the stream''s sequence elements. ' refinedIn: '' refinement: '' parameters: #( #('aCollection' 'sequencedCollection' #'captured') ) returnValues: #( #( 'ReadWriteStream' #'new') ) errors: '' ! (1 protocolManager newProtocolNamed: #'scaledDecimal' conformsToProtocolNames: #(#'number') ) protocolDescription: ' Provides a numeric representation of fixed point decimal numbers. The representation must be able to accurately represent decimal fractions. The standard recommends that the implementation of this protocol support unbounded precision, with no limit to the number of digits before and after the decimal point. If a bounded implementation is provided, then any operation which exceeds the bounds has an implementation-specified result. ' ! 1 protocolManager newMessagePattern: 'scale' forProtocolNamed: #'scaledDecimal' synopsis: 'Answer a integer which represents the total number of digits used to represent the fraction part of the receiver, including trailing zeroes. ' definedIn: 'scaledDecimal' definition: 'Answer a integer which represents the total number of digits used to represent the fraction part of the receiver, including trailing zeroes. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'integer' #'unspecified') ) errors: '' ! (1 protocolManager newProtocolNamed: #'selector' conformsToProtocolNames: #(#'Object') ) protocolDescription: ' Defines the protocol supported by literal message selectors. No behavior is defined by this protocols but objects that conform to is can be used to perform dynamically generated message sends using #perform: and related messages. ' ! (1 protocolManager newProtocolNamed: #'sequencedCollection' conformsToProtocolNames: #(#'sequencedReadableCollection') ) protocolDescription: ' Provides protocol for writing to an ordered collection of objects, whose elements can be accessed using external integer keys. ' ! 1 protocolManager newMessagePattern: 'at: newElement put: index' forProtocolNamed: #'sequencedCollection' synopsis: 'Replace the element in the receiver at index with newElement. Answer newElement. ' definedIn: 'sequencedCollection' definition: 'This message sets one of the receiver''s elements based on index. The newElement is stored at index in the receiver''s elements, replacing any previously stored object. Subsequent retrievals at this index will answer newElement. ' refinedIn: '' refinement: '' parameters: #( #('index' 'integer' #'uncaptured') #('newElement' 'Object' #'captured') ) returnValues: #( #( 'Object' #'state') ) errors: 'If index < 0. If index > the receiver''s size. If newElement does not conform to any element type restrictions of the receiver. ' ! 1 protocolManager newMessagePattern: 'atAll: indices put: newElement' forProtocolNamed: #'sequencedCollection' synopsis: 'Replace the elements in the receiver specified by indices with newElement. ' definedIn: 'sequencedCollection' definition: 'The newElement is stored at each index in the receiver specified by the elements of the indices collection, replacing any previously stored objects at these indices. Subsequent retrievals at these indices will answer newElement. This message is equivalent to storing newElement in the receiver at each index specified by indices using the #at:put: message for the receiver. ' refinedIn: '' refinement: '' parameters: #( #('indices' 'collection' #'uncaptured') #('newElement' 'Object' #'captured') ) returnValues: #() errors: 'If any element of indices does not conform to . If any element in indices is <= 0 or greater than the receiver''s size. If newElement does not conform to any element type restrictions of the receiver. ' ! 1 protocolManager newMessagePattern: 'atAllPut: newElement' forProtocolNamed: #'sequencedCollection' synopsis: 'Replace all the elements in the receiver with newElement. ' definedIn: 'sequencedCollection' definition: 'The newElement is stored at each index in the receiver, replacing any previously stored objects. This message is equivalent to storing newElement in the receiver at each index from 1 to the receiver''s size using the #at:put: message for the receiver. ' refinedIn: '' refinement: '' parameters: #( #('newElement' 'Object' #'captured') ) returnValues: #() errors: 'If newElement does not conform to any element type restrictions of the receiver. ' ! 1 protocolManager newMessagePattern: 'replaceFrom: stop to: replacementElements with: start' forProtocolNamed: #'sequencedCollection' synopsis: 'Replace the elements of the receiver between positions start and stop inclusive, with the elements of replacementElements in their original order. Answer the receiver. ' definedIn: 'sequencedCollection' definition: 'The first element of replacementElements is stored in the receiver at position start, the second at position start + 1, etc. Any previously stored elements at these positions are replaced. If the size of replacementElements is not equal to stop - start + 1, the result of sending this message is unspecified. ' refinedIn: '' refinement: '' parameters: #( #('start' 'integer' #'uncaptured') #('replacementElements' 'sequencedReadableCollection' #'unspecified') #('stop' 'integer' #'uncaptured') ) returnValues: #() errors: 'If start < 1 or start > the receiver''s size. If stop < 1 or stop > the receiver''s size. If replacementElements size <> stop - start + 1. ' ! 1 protocolManager newMessagePattern: 'replaceFrom: stop to: replacementElements with: replacementStart startingAt: start' forProtocolNamed: #'sequencedCollection' synopsis: 'Replace the elements of the receiver between positions start and stop inclusive with the elements of replacementElements, in their original order, starting at position replacementStart. Answer the receiver. ' definedIn: 'sequencedCollection' definition: 'The element at position replacementStart in replacementElements is stored in the receiver at position start; the element at replacementStart + 1 is stored at position start + 1; etc. Any previously stored elements at these positions in the receiver are replaced. If the size of replacementElements is not equal to (replacementStart + stop - start), the result of sending this message is unspecified. ' refinedIn: '' refinement: '' parameters: #( #('stop' 'integer' #'uncaptured') #('start' 'integer' #'uncaptured') #('replacementStart' 'integer' #'uncaptured') #('replacementElements' 'sequencedReadableCollection' #'unspecified') ) returnValues: #() errors: 'If start < 1 or start > the receiver''s size. If stop < 1 or stop > the receiver''s size. If replacementStart < 1 or replacementStart > replacementElements size. If replacementElements size - replacementStart + 1 < stop - start + 1. ' ! 1 protocolManager newMessagePattern: 'replaceFrom: replacementElement to: stop withObject: start' forProtocolNamed: #'sequencedCollection' synopsis: 'Replace the elements of the receiver between start and stop inclusive with replacementElement. Answer the receiver. ' definedIn: 'sequencedCollection' definition: 'Replace the elements of the receiver between start and stop inclusive with replacementElement. Answer the receiver. ' refinedIn: '' refinement: '' parameters: #( #('start' 'integer' #'uncaptured') #('replacementElement' 'Object' #'captured') #('stop' 'integer' #'uncaptured') ) returnValues: #() errors: 'If start < 1 or start > the receiver''s size. If stop < 1 or stop > the receiver''s size. ' ! (1 protocolManager newProtocolNamed: #'sequencedContractibleCollection' conformsToProtocolNames: #(#'collection') ) protocolDescription: ' Provides protocol for removing elements from an ordered collection of objects, whose elements can be accessed using external integer keys. ' ! 1 protocolManager newMessagePattern: 'removeAtIndex: index' forProtocolNamed: #'sequencedContractibleCollection' synopsis: 'Remove the element of the receiver at position index, and answer the removed element. ' definedIn: 'sequencedContractibleCollection' definition: 'The element of the receiver which is at position index is removed from the receiver''s elements. Answer the removed element. index must be a positive integer less than or equal to the receiver''s size. ' refinedIn: '' refinement: '' parameters: #( #('index' 'integer' #'uncaptured') ) returnValues: #( #( 'Object' #'unspecified') ) errors: 'If index is 0 or negative. If index is greater than the receiver''s size. ' ! 1 protocolManager newMessagePattern: 'removeFirst' forProtocolNamed: #'sequencedContractibleCollection' synopsis: 'Remove and answer the first element of the receiver. ' definedIn: 'sequencedContractibleCollection' definition: 'The first element of the receiver is removed and answered. The element (if any) that was previously the second element in the traversal order now becomes the first, and the receiver has one fewer elements. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'Object' #'state') ) errors: 'The receiver is empty ' ! 1 protocolManager newMessagePattern: 'removeLast' forProtocolNamed: #'sequencedContractibleCollection' synopsis: 'Remove and answer the last element of the receiver. ' definedIn: 'sequencedContractibleCollection' definition: 'The last element of the receiver is removed and answered. The element (if any) that was previously the second from last element in the traversal order now becomes the last, and the receiver has one fewer elements. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'Object' #'state') ) errors: 'The receiver is empty ' ! (1 protocolManager newProtocolNamed: #'sequencedReadableCollection' conformsToProtocolNames: #(#'collection') ) protocolDescription: ' Provides protocol for reading an ordered collection of objects whose elements can be accessed using external integer keys. The keys are between one (1) and the number of elements in the collection, inclusive. ' ! 1 protocolManager newMessagePattern: ', operand' forProtocolNamed: #'sequencedReadableCollection' synopsis: 'Answer a new collection which is the concatenation of the receiver and operand. ' definedIn: 'sequencedReadableCollection' definition: 'Answer a new collection containing all of the receiver''s elements in their original order followed by all of the elements of operand, in their original order. The size of the new collection is equal to the sum of the sizes of the receiver and operand, as defined by the #size message. Collections that enforce an ordering on their elements are permitted to refine this message to reorder the result. ' refinedIn: '' refinement: '' parameters: #( #('operand' 'sequencedReadableCollection' #'uncaptured') ) returnValues: #( #( 'sequencedReadableCollection' #'new') ) errors: 'If the elements of operand are not suitable for storage in instances of the receiver''s class. ' ! 1 protocolManager newMessagePattern: '= comparand' forProtocolNamed: #'sequencedReadableCollection' synopsis: 'Object equivalence test. ' definedIn: 'Object' definition: 'This message tests whether the receiver and the comparand are equivalent objects at the time the message is processed. Answer true if the receiver is equivalent to comparand. Otherwise answer false. The meaning of "equivalent" cannot be precisely defined but the intent is that two objects are considered equivalent if they can be used interchangeably. Conformant protocols may choose to more precisely define the meaning of "equivalent". The value of receiver = comparand is true if and only if the value of comparand = receiver would also be true. If the value of receiver = comparand is true then the receiver and comparand must have equivalent hash values. Or more formally: receiver = comparand ? receiver hash = comparand hash The equivalence of objects need not be temporally invariant. Two independent invocations of #= with the same receiver and operand objects may not always yield the same results. However, only objects whose implementation of #= is temporally invariant can be reliably stored within collections that use #= to discriminate objects. ' refinedIn: 'sequencedReadableCollection' refinement: 'Unless specifically refined, the receiver and operand are equivalent if all of the following are true: 1. The receiver and operand are instances of the same class. 2. They answer the same value for the #size message. 3. For all indices of the receiver, the element in the receiver at a given index is equivalent to the element in operand at the same index. Element lookup is defined by the #at: message for the receiver and operand. ' parameters: #( #('comparand' 'Object' #'uncaptured') ) returnValues: #( #( 'boolean' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'after: target' forProtocolNamed: #'sequencedReadableCollection' synopsis: 'Answer the object immediately following the first element which is equivalent to target in the receiver. ' definedIn: 'sequencedReadableCollection' definition: 'Answer the object immediately following the first element which is equivalent to target in the receiver. An element immediately follows another if its index is one greater than that of the other. The order used to determine which of the receiver''s elements is the first to be equivalent to target is the traversal order defined by #do: for the receiver. It is an error if the first occurrence of target is the last element of the receiver, or if the receiver does not include target. ' refinedIn: '' refinement: '' parameters: #( #('target' 'Object' #'uncaptured') ) returnValues: #( #( 'Object' #'state') ) errors: 'If there is no element in the receiver which is equivalent to target. If the element which is equal to target is the last element in the receiver. ' ! 1 protocolManager newMessagePattern: 'at: index' forProtocolNamed: #'sequencedReadableCollection' synopsis: 'Answer the element at the position index in the receiver. ' definedIn: 'sequencedReadableCollection' definition: 'This message defines element retrieval based on an index. Answer the element at the specified index. The result is undefined if the receiver has no element at position index. ' refinedIn: '' refinement: '' parameters: #( #('index' 'integer' #'uncaptured') ) returnValues: #( #( 'Object' #'state') ) errors: 'If index is <= 0. If index is greater than the receiver''s size. ' ! 1 protocolManager newMessagePattern: 'at: exceptionBlock ifAbsent: index' forProtocolNamed: #'sequencedReadableCollection' synopsis: 'Answer the element at the position index in the receiver. If there is no position corresponding to index in the receiver, then answer the result of evaluating exceptionBlock. ' definedIn: 'sequencedReadableCollection' definition: 'This message defines element retrieval based on an index. Answer the element at the specified index. If there is no position corresponding to index in the receiver, then answer the result of evaluating exceptionBlock. ' refinedIn: '' refinement: '' parameters: #( #('index' 'integer' #'uncaptured') #('exceptionBlock' 'niladicValuable' #'uncaptured') ) returnValues: #( #( 'ANY' #'unspecified') #( 'Object' #'state') ) errors: '' ! 1 protocolManager newMessagePattern: 'before: target' forProtocolNamed: #'sequencedReadableCollection' synopsis: 'Answer the object immediately preceding the first element which is equivalent to target in the receiver. ' definedIn: 'sequencedReadableCollection' definition: 'Answer the object immediately preceding the first element which is equivalent to target in the receiver. An element immediately precedes another if its index is one less than that of the other. It is an error if target is the first element of the receiver, or if the receiver does not include target. ' refinedIn: '' refinement: '' parameters: #( #('target' 'Object' #'uncaptured') ) returnValues: #( #( 'Object' #'state') ) errors: 'If there is no element in the receiver which is equivalent to target. If the element which is equal to target is the first element in the receiver. ' ! 1 protocolManager newMessagePattern: 'copyFrom: stop to: start' forProtocolNamed: #'sequencedReadableCollection' synopsis: 'Answer a new collection containing all of the elements of the receiver between the indices start and stop inclusive. If stop < start, the result has a size of zero. ' definedIn: 'sequencedReadableCollection' definition: 'Answer a new collection containing the specified range of elements of the receiver in their original order. The element at index start in the receiver is at index 1 in the new collection; the element at index start+1 is at index 2, etc. If stop is less than start, then the new collection is empty. Otherwise, the size of the new collection is the maximum of (stop - start + 1) and 0. The parameters start and stop must be positive.. ' refinedIn: '' refinement: '' parameters: #( #('start' 'integer' #'uncaptured') #('stop' 'integer' #'uncaptured') ) returnValues: #( #( 'sequencedReadableCollection' #'new') ) errors: 'If stop >= start and (start < 1 or start > the receiver''s size). If stop >= start and (stop < 1 or stop > the receiver''s size). ' ! 1 protocolManager newMessagePattern: 'copyReplaceAll: targetElements with: replacementElements' forProtocolNamed: #'sequencedReadableCollection' synopsis: 'Answer a new collection in which all subsequences of elements in the receiver matching targetElements are replaced in the new collection by the elements in replacementElements. ' definedIn: 'sequencedReadableCollection' definition: 'Answer a new collection with the elements of the receiver in their original order, except where a subsequence in the receiver matches targetElements. A subsequence in the receiver is said to match the elements of targetElements if: 1. They have the same number of elements. 2. For all indices of the subsequence, the element in the subsequence at a given index is equivalent to the element in targetElements at the same index. Starting with the first element of the receiver and proceeding through ascending elements, each non-overlapping subsequence of the receiver matching targetElements is detected. The result is a copy of the receiver with each detected subsequence replaced by the sequence of elements of replacementElements. Collections that enforce an ordering on their elements are permitted to refine this message to reorder the result. ' refinedIn: '' refinement: '' parameters: #( #('targetElements' 'sequencedReadableCollection' #'uncaptured') #('replacementElements' 'sequencedReadableCollection' #'uncaptured') ) returnValues: #( #( 'sequencedReadableCollection' #'new') ) errors: 'If any of the elements in replacementElements does not conform to any element type restrictions of instances of the receiver''s class. ' ! 1 protocolManager newMessagePattern: 'copyReplaceFrom: stop to: replacementElements with: start' forProtocolNamed: #'sequencedReadableCollection' synopsis: 'Answer a new collection, containing the same elements as the receiver, but with the elements in the receiver between start and stop inclusive replaced by the elements in replacementElements. ' definedIn: 'sequencedReadableCollection' definition: 'This message can be used to insert, append, or replace. The size of replacementElements (as defined by #size) need not be the same as the number of elements being replaced. There are three cases: 1. If stop = start - 1 , and start is less than or equal to the size of the receiver, then the replacementElements are inserted between the elements at index stop and start. None of the receiver''s elements are replaced. 2. If stop = the size of the receiver and start = stop + 1, then the operation is an append, and the replacementElements are placed at the end of the new collection. 3. Otherwise, the operation is a replacement, and the receiver''s elements in the given range are replaced by the elements from replacementElements. In all cases, the resulting collection consists of the receiver''s elements from indices 1 to start - 1 in their original order, followed by the elements of replacementElements, followed by the remainder of the receiver''s elements from index stop + 1 in their original order. The size of the result is the receiver''s size - (stop - start + 1) + the replacementElements size. The parameters start and stop must be positive. Collections that enforce an ordering on their elements are permitted to refine this message to reorder the result. ' refinedIn: '' refinement: '' parameters: #( #('stop' 'integer' #'uncaptured') #('start' 'integer' #'uncaptured') #('replacementElements' 'sequencedReadableCollection' #'uncaptured') ) returnValues: #( #( 'sequencedReadableCollection' #'new') ) errors: 'The elements in replacementElements are not suitable for storage in instances of the receiver''s class. start > receiver''s size + 1 start < 1 stop > receiver''s size stop < start - 1 ' ! 1 protocolManager newMessagePattern: 'copyReplaceFrom: stop to: replacementElement withObject: start' forProtocolNamed: #'sequencedReadableCollection' synopsis: 'Answer a new collection conforming to the same protocols as the receiver, in which the elements of the receiver between start and stop inclusive have been replaced with replacementElement. ' definedIn: 'sequencedReadableCollection' definition: 'This message can be used to insert, append, or replace. There are three cases: 1. If stop = start - 1 , and start is less than or equal to the size of the receiver, then replacementElement is inserted between the elements at index stop and start. None of the receiver''s elements are replaced. 2. If stop = the size of the receiver and start = stop + 1, then the operation is an append, and replacementElement is placed at the end of the new collection. 3. Otherwise, the operation is a replacement, and each of the receiver''s elements in the given range is replaced by replacementElement. The parameters start and stop must be non-negative. Collections that by definition enforce an ordering on their elements are permitted to refine this message to reorder the result. ' refinedIn: '' refinement: '' parameters: #( #('start' 'integer' #'uncaptured') #('stop' 'integer' #'uncaptured') #('replacementElement' 'Object' #'uncaptured') ) returnValues: #( #( 'sequencedReadableCollection' #'new') ) errors: 'The replacementElement is not suitable for storage in instances of the receiver''s class. start > receiver''s size + 1 start < 1 stop > receiver''s size stop < start - 1 Issues What does this do? Are there (stop - start + 1) elements equal to the replacementElement, or are that many elements replaced by a single element? ' ! 1 protocolManager newMessagePattern: 'copyReplacing: replacementElement withObject: targetElement' forProtocolNamed: #'sequencedReadableCollection' synopsis: 'Answer a new collection conforming to the same protocols as the receiver, in which any occurrences of targetElement are replaced by replacementElement. ' definedIn: 'sequencedReadableCollection' definition: 'A new collection is created and initialized with the same elements as the receiver in the same order, except that any objects in the receiver which are equivalent to targetElement are replaced in the new collection by replacementElement. Collections that enforce an ordering on their elements are permitted to refine this message to reorder the result. ' refinedIn: '' refinement: '' parameters: #( #('targetElement' 'Object' #'uncaptured') #('replacementElement' 'Object' #'uncaptured') ) returnValues: #( #( 'sequencedReadableCollection' #'new') ) errors: 'If the replacementElement is inappropriate for storage in instances of the receiver''s class. ' ! 1 protocolManager newMessagePattern: 'copyWith: newElement' forProtocolNamed: #'sequencedReadableCollection' synopsis: 'Answer a new collection containing the same elements as the receiver, with newElement added. ' definedIn: 'sequencedReadableCollection' definition: 'Answer a new collection with size one greater than the size of the receiver containing the elements of the receiver and newElement placed at the end. Unless specifically refined, this message is defined to answer an instance of the same class as the receiver. Collections that enforce an ordering on their elements are permitted to refine this message to reorder the result. ' refinedIn: '' refinement: '' parameters: #( #('newElement' 'Object' #'captured') ) returnValues: #( #( 'sequencedReadableCollection' #'new') ) errors: '' ! 1 protocolManager newMessagePattern: 'copyWithout: oldElement' forProtocolNamed: #'sequencedReadableCollection' synopsis: 'Answer a new collection, containing the same elements as the receiver in their original order omitting any elements equivalent to oldElement. ' definedIn: 'sequencedReadableCollection' definition: 'Answer a new collection with all of the elements of the receiver that are not equivalent to oldElement, in their original order. ' refinedIn: '' refinement: '' parameters: #( #('oldElement' 'Object' #'uncaptured') ) returnValues: #( #( 'sequencedReadableCollection' #'new') ) errors: '' ! 1 protocolManager newMessagePattern: 'do: operation' forProtocolNamed: #'sequencedReadableCollection' synopsis: 'Evaluate operation with each element of the receiver. ' definedIn: 'collection' definition: 'For each element of the receiver, operation is evaluated with the element as the parameter. Unless specifically refined, the elements are not traversed in a particular order. Each element is visited exactly once. Conformant protocols may refine this message to specify a particular ordering. ' refinedIn: 'sequencedReadableCollection' refinement: 'The operation is evaluated with each element of the receiver in indexed order starting at 1. The first element is at index 1, the second at index 2, etc. The index of the last element is equal to the receiver''s size. ' parameters: #( #('operation' 'monadicValuable' #'uncaptured') ) returnValues: #() errors: 'If the elements of the receiver are inappropriate for use as arguments to operation. ' ! 1 protocolManager newMessagePattern: 'findFirst: discriminator' forProtocolNamed: #'sequencedReadableCollection' synopsis: 'Answer the index of the first element of the receiver which causes discriminator to evaluate to true when the element is used as the parameter. Answer zero (0) if no such element is found. ' definedIn: 'sequencedReadableCollection' definition: 'For each element of the receiver, discriminator is evaluated with the element as the parameter. Answer the index of the first element which results in an evaluation of true; no further elements are considered. If no such element exists in the receiver, answer 0. The elements are traversed in the order specified by the #do: message for the receiver. ' refinedIn: '' refinement: '' parameters: #( #('discriminator' 'monadicValuable' #'uncaptured') ) returnValues: #( #( 'integer' #'unspecified') ) errors: 'If an evaluation of discriminator results in an object that does not conform to . If the elements of the receiver are inappropriate for use as arguments to discriminator. ' ! 1 protocolManager newMessagePattern: 'findLast: discriminator' forProtocolNamed: #'sequencedReadableCollection' synopsis: 'Answer the index of the last element of the receiver which causes discriminator to evaluate to true when the element is used as the parameter. Answer zero (0) if no such element is found. ' definedIn: 'sequencedReadableCollection' definition: 'For each element of the receiver, in reverse order starting with the last, discriminator is evaluated with the element as the parameter. Answer the index of the first element which results in an evaluation of true; no further elements are considered. Answer 0 if no such element is found in the receiver. The elements are traversed in the order specified by the #reverseDo: message for the receiver. ' refinedIn: '' refinement: '' parameters: #( #('discriminator' 'monadicValuable' #'uncaptured') ) returnValues: #( #( 'integer' #'unspecified') ) errors: 'If an evaluation of discriminator results in an object that does not conform to . If the elements of the receiver are inappropriate for use as arguments to discriminator. ' ! 1 protocolManager newMessagePattern: 'first' forProtocolNamed: #'sequencedReadableCollection' synopsis: 'Answer the first element of the receiver. ' definedIn: 'sequencedReadableCollection' definition: 'Answer the element at index 1 in the receiver. The result is undefined if the receiver is empty (answers true to the #isEmpty message). ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'Object' #'state') ) errors: '' ! 1 protocolManager newMessagePattern: 'from: stop to: operation do: start' forProtocolNamed: #'sequencedReadableCollection' synopsis: 'For those elements of the receiver between positions start and stop, inclusive, evaluate operation with each element of the receiver. ' definedIn: 'sequencedReadableCollection' definition: 'For each index in the range start to stop, the operation is evaluated with the element at that index as its argument. ' refinedIn: '' refinement: '' parameters: #( #('stop' 'integer' #'uncaptured') #('start' 'integer' #'uncaptured') #('operation' 'monadicValuable' #'uncaptured') ) returnValues: #() errors: 'If the elements of the receiver are inappropriate for use as arguments to operation. start < 1 stop > receiver''s size ' ! 1 protocolManager newMessagePattern: 'from: stop to: operation keysAndValuesDo: start' forProtocolNamed: #'sequencedReadableCollection' synopsis: 'For those elements of the receiver between positions start and stop, inclusive, evaluate operation with an element of the receiver as the first argument and the element''s position (index) as the second. ' definedIn: 'sequencedReadableCollection' definition: 'For each index in the range start to stop, the operation is evaluated with the index as the first argument and the element at that index as the second argument. ' refinedIn: '' refinement: '' parameters: #( #('start' 'integer' #'uncaptured') #('stop' 'integer' #'uncaptured') #('operation' 'dyadicValuable' #'uncaptured') ) returnValues: #() errors: 'If the elements of the receiver or its indices are inappropriate for use as arguments to operation. start < 1 stop > receiver''s size ' ! 1 protocolManager newMessagePattern: 'indexOf: target' forProtocolNamed: #'sequencedReadableCollection' synopsis: 'Answer the index of the first element of the receiver which is equivalent to target. Answer zero (0) if no such element is found. ' definedIn: 'sequencedReadableCollection' definition: 'Answer the index of the first element which is equivalent to target; no further elements are considered. Answer 0 if no such element exists in the receiver. The elements are traversed in the order specified by the #do: message for the receiver. ' refinedIn: '' refinement: '' parameters: #( #('target' 'Object' #'uncaptured') ) returnValues: #( #( 'integer' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'indexOf: exceptionHandler ifAbsent: target' forProtocolNamed: #'sequencedReadableCollection' synopsis: 'Answer the index of the first element of the receiver which is equivalent to target. Answer the result of evaluating exceptionHandler with no parameters if no such element is found. ' definedIn: 'sequencedReadableCollection' definition: 'Answer the index of the first element which is equivalent to target; no further elements are considered. Answer exceptionHandler evaluated with no parameters if no such element is found. The elements are traversed in the order specified by the #do: message for the receiver. ' refinedIn: '' refinement: '' parameters: #( #('exceptionHandler' 'niladicValuable' #'uncaptured') #('target' 'Object' #'uncaptured') ) returnValues: #( #( 'Object' #'unspecified') #( 'integer' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'indexOfSubCollection: targetSequence startingAt: start' forProtocolNamed: #'sequencedReadableCollection' synopsis: 'Answer the index of the first element of the receiver which is the start of a subsequence which matches targetSequence. Start searching at index start in the receiver. Answer 0 if no such subsequence is found. ' definedIn: 'sequencedReadableCollection' definition: 'Each subsequence of the receiver starting at index start is checked for a match with targetSequence. To match, each element of a subsequence of the receiver must be equivalent to the corresponding element of targetSequence. Answer the index of the first element which begins a matching subsequence; no further subsequences are considered. Answer 0 if no such subsequence is found in the receiver, or if targetSequence is empty. The elements are traversed in the order specified by the #do: message for the receiver. ' refinedIn: '' refinement: '' parameters: #( #('targetSequence' 'sequencedReadableCollection' #'uncaptured') #('start' 'integer' #'uncaptured') ) returnValues: #( #( 'integer' #'unspecified') ) errors: 'start < 1 start > the receiver''s size ' ! 1 protocolManager newMessagePattern: 'indexOfSubCollection: exceptionHandler startingAt: targetSequence ifAbsent: start' forProtocolNamed: #'sequencedReadableCollection' synopsis: 'Answer the index of the first element of the receiver which is the start of a subsequence which matches targetSequence. Start searching at index start in the receiver. Answer the result of evaluating exceptionHandler with no parameters if no such subsequence is found. ' definedIn: 'sequencedReadableCollection' definition: 'Each subsequence of the receiver starting at index start is checked for a match with targetSequence. To match, each element of a subsequence of the receiver must be equivalent to the corresponding element of targetSequence. Answer the index of the first element which begins a matching subsequence; no further subsequences are considered. Answer the result of evaluating exceptionHandler with no parameters if no such subsequence is found or if targetSequence is empty. The elements are traversed in the order specified by the #do: message for the receiver. ' refinedIn: '' refinement: '' parameters: #( #('targetSequence' 'sequencedReadableCollection' #'uncaptured') #('exceptionHandler' 'niladicValuable' #'uncaptured') #('start' 'integer' #'uncaptured') ) returnValues: #( #( 'Object' #'unspecified') #( 'integer' #'unspecified') ) errors: 'start < 1 start > the receiver''s size ' ! 1 protocolManager newMessagePattern: 'keysAndValuesDo: operation' forProtocolNamed: #'sequencedReadableCollection' synopsis: 'Evaluate operation with the index of each element of the receiver, in order, together with the element itself. ' definedIn: 'sequencedReadableCollection' definition: 'The operation is evaluated with the index of each element of the receiver as the first argument and the element itself as the second argument. Evaluation is in indexed order starting at 1. The first element is at index 1, the second at index 2, etc. The index of the last element is equal to the receiver''s size. ' refinedIn: '' refinement: '' parameters: #( #('operation' 'dyadicValuable' #'uncaptured') ) returnValues: #() errors: 'If the elements of the receiver are inappropriate for use as arguments to operation. ' ! 1 protocolManager newMessagePattern: 'last' forProtocolNamed: #'sequencedReadableCollection' synopsis: 'Answer the last element of the receiver. ' definedIn: 'sequencedReadableCollection' definition: 'Answer the last element of the receiver, the element at the index equal to the receiver''s size. The result is unspecified if the receiver is empty (answers true to the #isEmpty message). ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'Object' #'state') ) errors: '' ! 1 protocolManager newMessagePattern: 'reverse' forProtocolNamed: #'sequencedReadableCollection' synopsis: 'Answer a collection with the elements of the receiver arranged in reverse order. ' definedIn: 'sequencedReadableCollection' definition: 'Answer a collection conforming to the same protocols as the receiver, but with its elements arranged in reverse order. This operation is equivalent to: 1. Create a new collection which conforms to the same protocols as the receiver; 2. Traverse the elements of the receiver in the order specified by the #reverseDo: message, adding each element of the receiver to the new collection; 3. Answer the new collection. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'sequencedReadableCollection' #'new') ) errors: '' ! 1 protocolManager newMessagePattern: 'reverseDo: operation' forProtocolNamed: #'sequencedReadableCollection' synopsis: 'Evaluate operation with each element of the receiver in the reverse of the receiver''s standard traversal order. ' definedIn: 'sequencedReadableCollection' definition: 'For each element of the receiver, evaluate operation with the element as the parameter. The elements are traversed in the opposite order from the #do: message. Each element is visited exactly once. ' refinedIn: '' refinement: '' parameters: #( #('operation' 'monadicValuable' #'uncaptured') ) returnValues: #() errors: 'If the elements of the receiver are inappropriate for use as arguments to operation. ' ! 1 protocolManager newMessagePattern: 'with: operation do: otherCollection' forProtocolNamed: #'sequencedReadableCollection' synopsis: 'Evaluate operation with each element of the receiver and the corresponding element of otherCollection as parameters. ' definedIn: 'sequencedReadableCollection' definition: 'For each element of the receiver and the corresponding element of otherCollection, evaluate operation with the receiver''s element as the first parameter, and the element of otherCollection as the second parameter. The receiver and otherCollection must have the same size. The elements of the receiver and otherCollection are traversed in indexed order starting at 1. The operation is first evaluated with the elements at index 1 in the two s, then index 2, etc. ' refinedIn: '' refinement: '' parameters: #( #('otherCollection' 'sequencedReadableCollection' #'uncaptured') #('operation' 'dyadicValuable' #'uncaptured') ) returnValues: #() errors: 'If the elements of the receiver or the elements of otherCollection are inappropriate for use as arguments to operation. If the receiver''s size is not equal to the size of otherCollection. ' ! (1 protocolManager newProtocolNamed: #'sequencedStream' conformsToProtocolNames: #(#'Object') ) protocolDescription: ' An object conforming to has a finite number of past and future sequence values. It maintains a position on its sequence values and allows the position to be altered. ' ! 1 protocolManager newMessagePattern: 'close' forProtocolNamed: #'sequencedStream' synopsis: 'Disassociate a stream from its backing store. ' definedIn: 'sequencedStream' definition: 'If the receiver is a write-back stream update its stream backing store as if the message #flush was sent to the receiver. Then eliminate any association between the receiver and its stream backing store. Any system resources associated with the association should be released. The effect of sending any message to the receiver subsequent to this message is undefined. ' refinedIn: '' refinement: '' parameters: #() returnValues: #() errors: '' ! 1 protocolManager newMessagePattern: 'contents' forProtocolNamed: #'sequencedStream' synopsis: 'Returns a collection containing the complete contents of the stream. ' definedIn: 'sequencedStream' definition: 'Returns a collection that contains the receiver''s past and future sequence values, in order. The size of the collection is the sum of the sizes of the past and future sequence values. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'sequencedReadableCollection' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'isEmpty' forProtocolNamed: #'sequencedStream' synopsis: 'Returns a Boolean indicating whether there are any sequence values in the receiver. ' definedIn: 'sequencedStream' definition: 'Returns true if both the set of past and future sequence values of the receiver are empty. Otherwise returns false. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'boolean' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'position' forProtocolNamed: #'sequencedStream' synopsis: 'Returns the current position of the stream. ' definedIn: 'sequencedStream' definition: 'Returns the number of sequence values in the receiver''s past sequence values. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'integer' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'position: amount' forProtocolNamed: #'sequencedStream' synopsis: 'Sets the current position in a stream of values. ' definedIn: 'sequencedStream' definition: 'If the number of sequence values in the receiver''s past sequence values is smaller than amount, move objects in sequence from the front of the receiver''s future sequence values to the back of th receiver''s past sequence values until the number of sequence values in the receiver''s past sequence values is equal to amount. If the number of sequence values in the receiver''s past sequence values is greater than amount, move objects in sequence from the back of the receiver''s past sequence values to the front of th receiver''s future sequence values until the number of sequence values in the receiver''s past sequence values is equal to amount. If the number of sequence values in the receiver''s past sequence values is equal to amount no action is taken. ' refinedIn: '' refinement: '' parameters: #( #('amount' 'integer' #'unspecified') ) returnValues: #() errors: 'If amount is negative. If the receiver has any sequence values and amount is greater than or equal to the total number of sequence values of the receiver. ' ! 1 protocolManager newMessagePattern: 'reset' forProtocolNamed: #'sequencedStream' synopsis: 'Resets the position of the receiver to be at the beginning of the stream of values. ' definedIn: 'sequencedStream' definition: 'Sets the receiver''s future sequence values to be the current past sequence values appended with the current future sequence values. Make the receiver''s past sequence values be empty. ' refinedIn: '' refinement: '' parameters: #() returnValues: #() errors: '' ! 1 protocolManager newMessagePattern: 'setToEnd' forProtocolNamed: #'sequencedStream' synopsis: 'Set the position of the stream to its end. ' definedIn: 'sequencedStream' definition: 'All of the receiver''s future sequence values are appended, in sequence, to the receiver''s past sequence values. The receiver then has no future sequence values. ' refinedIn: '' refinement: '' parameters: #() returnValues: #() errors: '' ! (1 protocolManager newProtocolNamed: #'Set' conformsToProtocolNames: #(#'extensibleCollection') ) protocolDescription: ' Represents an unordered, variable sized collection whose elements can be added or removed, but cannot be individually accessed by external keys. A set is similar to a bag but cannot contain duplicate elements. ' ! 1 protocolManager newMessagePattern: 'add: newElement' forProtocolNamed: #'Set' synopsis: 'Add newElement to the receiver''s elements. ' definedIn: 'extensibleCollection' definition: 'This message adds a newElement to the receiver. Unless specifically refined, the position of the newElement in the element traversal order is unspecified. Conformant protocols may place restrictions on the type of objects that are valid elements. Unless otherwise specified, any object is acceptable. ' refinedIn: 'Set' refinement: 'Since sets may not contain duplicates, if there is already an element in the receiver that is equivalent to newElement, this operation has no effect. The results are undefined if newElement is nil. The equivalence of newElement with respect to other objects should not be changed while newElement is in the collection, as this would violate the invariant under which the element was placed within the collection. ' parameters: #( #('newElement' 'Object' #'captured') ) returnValues: #() errors: '' ! 1 protocolManager newMessagePattern: 'addAll: newElements' forProtocolNamed: #'Set' synopsis: 'Add each element of newElements to the receiver''s elements. ' definedIn: 'extensibleCollection' definition: 'This message adds each element of newElements to the receiver. The operation is equivalent to adding each element of newElements to the receiver using the #add: message with the element as the parameter. The newElements are traversed in the order specified by the #do: message for newElements. ' refinedIn: 'Set' refinement: 'Duplicates will not be added. The results are undefined if newElements contains nil. ' parameters: #( #('newElements' 'collection' #'unspecified') ) returnValues: #() errors: '' ! 1 protocolManager newMessagePattern: 'collect: transformer' forProtocolNamed: #'Set' synopsis: 'Answer a new collection constructed by gathering the results of evaluating transformer with each element of the receiver. ' definedIn: 'collection' definition: 'For each element of the receiver, transformer is evaluated with the element as the parameter. The results of these evaluations are collected into a new collection. The elements are traversed in the order specified by the #do: message for the receiver. Unless specifically refined, this message is defined to answer an objects conforming to the same protocol as the receiver. ' refinedIn: 'Set' refinement: 'Duplicates will not be added. The results are undefined if newElements contains nil. ' parameters: #( #('transformer' 'monadicValuable' #'uncaptured') ) returnValues: #( #( 'Set' #'new') ) errors: 'If the elements of the receiver are inappropriate for use as arguments to transformer. If the result of evaluating the transformer does not conform to any element type restrictions of the collection to be returned. ' ! (1 protocolManager newProtocolNamed: #'Set factory' conformsToProtocolNames: #(#'initializableCollection factory') ) protocolDescription: ' This protocol defines the behavior of objects that can be used to create objects that conform to the protocol . Standard Globals Set Conforms to the protocol . Its language element type is unspecified. This is a factory and discriminator for collections that conform to . ' ! 1 protocolManager newMessagePattern: 'new' forProtocolNamed: #'Set factory' synopsis: 'Create a new object. ' definedIn: 'instantiator' definition: 'Return a newly created object initialized to a standard initial state. ' refinedIn: 'Set factory' refinement: 'Return a new that is optimized to store an arbitrary number of elements. The new collection initially contains no elements. ' parameters: #() returnValues: #( #( 'Set' #'new') ) errors: '' ! 1 protocolManager newMessagePattern: 'new: count' forProtocolNamed: #'Set factory' synopsis: 'Create a new collection. The parameter count constrains the number of elements in the result. ' definedIn: 'collection factory' definition: 'Return a new collection that has space for at least count elements. Conforming protocols may refine this message. In particular, the effect of the parameter count should be specified in refinements. It can be used to specify the exact number of elements, the minimum number, or in some cases can even be interpreted as a hint from the programmer, with no guarantee that the requested number of instance variables will actually be allocated. Unless otherwise stated the initial values of elements of the new instance of the receiver are unspecified. ' refinedIn: 'Set factory' refinement: 'The parameter count represents a hint for space allocation. The new collection is to optimized to contain count elements. If the value of count is zero the collection should be optimize to hold an arbitrary number of elements. The new collection initially contains no elements. The new collections conforms to the protocol . ' parameters: #( #('count' 'integer' #'unspecified') ) returnValues: #( #( 'Set' #'new') ) errors: '' ! 1 protocolManager newMessagePattern: 'with: element1' forProtocolNamed: #'Set factory' synopsis: 'Create a collection initially containing the argument element. ' definedIn: 'initializableCollection factory' definition: 'Return a new collection containing one element. The collection contains the argument as its element. Conforming protocols may impose restrictions on the value of the argument and hence the element type. ' refinedIn: 'Set factory' refinement: 'The result is undefined if the argument is nil. ' parameters: #( #('element1' 'Object' #'captured') ) returnValues: #( #( 'Set' #'new') ) errors: 'If the argument does not meet the element type constraints of the result object ' ! 1 protocolManager newMessagePattern: 'with: element1 with: element2' forProtocolNamed: #'Set factory' synopsis: 'Create a collection initially containing the argument elements ' definedIn: 'initializableCollection factory' definition: 'Return a new collection containing two elements. The collection contains the arguments as its elements. Conforming protocols may impose restrictions on the values of the arguments and hence the element types. ' refinedIn: 'Set factory' refinement: 'The result is undefined if any of the arguments are nil. ' parameters: #( #('element1' 'Object' #'captured') #('element2' 'Object' #'captured') ) returnValues: #( #( 'Set' #'new') ) errors: 'If any of the arguments do not meet the element type constraints of the result object ' ! 1 protocolManager newMessagePattern: 'with: element1 with: element3 with: element2' forProtocolNamed: #'Set factory' synopsis: 'Create a collection initially containing the argument elements. ' definedIn: 'initializableCollection factory' definition: 'Return a new collection containing three elements. The collection contains the arguments as its elements. Conforming protocols may impose restrictions on the values of the arguments and hence the element types. ' refinedIn: 'Set factory' refinement: 'The result is undefined if any of the arguments are nil. ' parameters: #( #('element1' 'Object' #'captured') #('element3' 'Object' #'captured') #('element2' 'Object' #'captured') ) returnValues: #( #( 'Set' #'new') ) errors: 'If any of the arguments do not meet the element type constraints of the result object ' ! 1 protocolManager newMessagePattern: 'with: element2 with: element4 with: element1 with: element3' forProtocolNamed: #'Set factory' synopsis: 'Create a collection initially containing the argument elements. ' definedIn: 'initializableCollection factory' definition: 'Return a new collection containing four elements. The collection contains the arguments as its elements. Conforming protocols may impose restrictions on the values of the arguments and hence the element types. ' refinedIn: 'Set factory' refinement: 'The result is undefined if any of the arguments are nil. ' parameters: #( #('element1' 'Object' #'captured') #('element3' 'Object' #'captured') #('element2' 'Object' #'captured') #('element4' 'Object' #'captured') ) returnValues: #( #( 'Set' #'new') ) errors: 'If any of the arguments do not meet the element type constraints of the result object ' ! 1 protocolManager newMessagePattern: 'withAll: newElements' forProtocolNamed: #'Set factory' synopsis: 'Create a collection containing only the elements of newElements. ' definedIn: 'initializableCollection factory' definition: 'Return a new collection whose elements are the elements of newElements. Conforming protocols may impose restrictions on the values of newElements. ' refinedIn: 'Set factory' refinement: 'The result is unspecified if newElements contains nil. ' parameters: #( #('newElements' 'collection' #'unspecified') ) returnValues: #( #( 'Set' #'new') ) errors: 'If any of the elements of newElements do not meet the element type constraints of the result object ' ! (1 protocolManager newProtocolNamed: #'signaledException' conformsToProtocolNames: #(#'exceptionDescription') ) protocolDescription: ' This protocol describes the messages that may be sent to the argument of a handler block. These message are used to explicitly control how execution will continue when it leaves the handler block. ' ! 1 protocolManager newMessagePattern: 'isNested' forProtocolNamed: #'signaledException' synopsis: 'Determine whether the current exception handler is within the scope of another handler for the same exception. ' definedIn: 'signaledException' definition: 'Answer true if the handler environment for the current exception handler contains an exception handler that will handle the receiver. Answer false if it does not. The default action for an exception is not considered to be an enclosing handler. Only the existence of a handler explicitly established using #on:do: will result in this method returning true. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'boolean' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'outer' forProtocolNamed: #'signaledException' synopsis: 'Evaluate the enclosing exception action for the receiver and return. ' definedIn: 'signaledException' definition: 'If the handler environment for the current exception handler contains an exception handler that will handle the receiver, evaluate that handler''s exception action with the receiver as the argument to its handler block. If there is no enclosing handler, send the message #defaultAction to the receiver. The #defaultAction method is evaluated using the current exception environment. If the receiver is resumable and the evaluated exception action resumes then the result returned from #outer will be the resumption value of the evaluated exception action. If the receiver is not resumable or if the exception action does not resume then this message will not return. For exceptions that are not resumable, #outer is equivalent to #pass. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'Object' #'unspecified') ) errors: 'It is erroneous to directly or indirectly send this message from within a #defaultAction method to the receiver of the #defaultAction message. ' ! 1 protocolManager newMessagePattern: 'pass' forProtocolNamed: #'signaledException' synopsis: 'Yield control to the enclosing exception action for the receiver. ' definedIn: 'signaledException' definition: 'If the handler environment for the current exception handler contains an enclosing exception handler for the receiver, activate that handler''s exception action in place of the current exception action. If there is no enclosing handler, execute the default action for the receiver as if no handler had been found when the exception was originally signaled. The default action is evaluated in the context of the signaling environment. Control does not return to the currently active exception handler. ' refinedIn: '' refinement: '' parameters: #() returnValues: #() errors: 'It is erroneous to directly or indirectly send this message from within a #defaultAction method to the receiver of the #defaultAction method. ' ! 1 protocolManager newMessagePattern: 'resignalAs: replacementException' forProtocolNamed: #'signaledException' synopsis: 'Signal an alternative exception in place of the receiver. ' definedIn: 'signaledException' definition: 'The active exception action is aborted and the exception environment and the evaluation context are restored to the same states that were in effect when the receiver was originally signaled. Restoring the evaluation context may result in the execution of #ensure: or #ifCurtailed: termination blocks. After the restoration, signal the replacementException and execute the exception action as determined by the restored exception environment. This message causes the replacementException to be treated as if it had been originally signaled instead of the receiver. If the replacementException is resumable and its exception action resumes, control will ultimately return from the message that signaled the original exception. Control does not return from this message to the currently active exception action. ' refinedIn: '' refinement: '' parameters: #( #('replacementException' 'exceptionDescription' #'unspecified') ) returnValues: #() errors: '' ! 1 protocolManager newMessagePattern: 'resume' forProtocolNamed: #'signaledException' synopsis: 'Return from the message that signaled the receiver. ' definedIn: 'signaledException' definition: 'If the current exception action was activated as the result of sending the message #outer to the receiver, return a resumption value as the value of the #outer message. If the receiver is a resumable exception a resumption value is returned as the value of the message that signaled the receiver. Before returning, the exception environment and the evaluation context are restored to the same states that were in effect when the receiver was originally signaled. Restoring the evaluation context may result in the execution of #ensure: or #ifCurtailed: termination blocks. This message does not return to its point of invocation. The resumption value is unspecified. ' refinedIn: '' refinement: '' parameters: #() returnValues: #() errors: 'It is erroneous to directly or indirectly send this message from within a #defaultAction method to the receiver of the #defaultAction method. It is erroneous to send the message if the receiver is not resumable. ' ! 1 protocolManager newMessagePattern: 'resume: resumptionValue' forProtocolNamed: #'signaledException' synopsis: 'Return the argument as the value of the message that signaled the receiver. ' definedIn: 'signaledException' definition: 'If the current exception action was activated as the result of sending the message #outer to the receiver, return resumptionValue as the value of the #outer message. If the receiver is a resumable exception, the resumptionValue is returned as the value of the message that signaled the receiver. Before returning, the exception environment and the evaluation context are restored to the same states that were in effect when the receiver was originally signaled. Restoring the evaluation context may result in the execution of #ensure: or #ifCurtailed: termination blocks. This message does not return to its point of invocation. ' refinedIn: '' refinement: '' parameters: #( #('resumptionValue' 'Object' #'uncaptured') ) returnValues: #() errors: 'It is erroneous to directly or indirectly send this message from within a #defaultAction method to the receiver of the #defaultAction method. It is erroneous to send the message if the receiver is not resumable. ' ! 1 protocolManager newMessagePattern: 'retry' forProtocolNamed: #'signaledException' synopsis: 'Abort an exception handler and re-evaluate its protected block. ' definedIn: 'signaledException' definition: 'The active exception action is aborted and the exception environment and the evaluation context are restored to the same states that were in effect when the #on:do: message that established the active handler was sent. Restoring the evaluation context may result in the execution of #ensure: or #ifCurtailed: termination blocks. After the restoration, the #on:do: method is re-evaluated with its original receiver and arguments. Control does not return from this message to the currently active exception action. ' refinedIn: '' refinement: '' parameters: #() returnValues: #() errors: 'It is erroneous to directly or indirectly send this message from within a #defaultAction method to the receiver of the #defaultAction method. ' ! 1 protocolManager newMessagePattern: 'retryUsing: alternativeBlock' forProtocolNamed: #'signaledException' synopsis: 'Abort an exception handler and evaluate a new block in place of the handler''s protected block. ' definedIn: 'signaledException' definition: 'The active exception action is aborted and the exception environment and the evaluation context are restored to the same states that were in effect when the #on:do: message that established the active handler was sent. Restoring the evaluation context may result in the execution of #ensure: or #ifCurtailed: blocks. After the restoration, the #on:do: method is re-evaluated with alternativeBlock substituted for its original receiver. The original arguments are used for the re-evaluation. Control does not return from this message to the currently active exception action. ' refinedIn: '' refinement: '' parameters: #( #('alternativeBlock' 'niladicBlock' #'captured') ) returnValues: #() errors: 'It is erroneous to directly or indirectly send this message from within a #defaultAction method to the receiver of the #defaultAction method. ' ! 1 protocolManager newMessagePattern: 'return' forProtocolNamed: #'signaledException' synopsis: 'Return nil as the value of the block protected by the active exception handler. ' definedIn: 'signaledException' definition: 'Nil is return as the value of the protected block of the active exception handler. Before returning, the exception environment and the evaluation context are restored to the same states that were in effect when the active handler was created using #on:do:. Restoring the evaluation context may result in the execution of #ensure: or #ifCurtailed: termination blocks. This message does not return to its point of invocation. ' refinedIn: '' refinement: '' parameters: #() returnValues: #() errors: 'It is erroneous to directly or indirectly send this message from within a #defaultAction method to the receiver of the #defaultAction method. ' ! 1 protocolManager newMessagePattern: 'return: returnValue' forProtocolNamed: #'signaledException' synopsis: 'Return the argument as the value of the block protected by the active exception handler. ' definedIn: 'signaledException' definition: 'The returnValue is returned as the value of the protected block of the active exception handler. Before returning, the exception environment and the evaluation context are restored to the same states that were in effect when the active handler was created using #on:do:. Restoring the evaluation context may result in the execution of #ensure: or #ifCurtailed: termination blocks. This message does not return to its point of invocation. ' refinedIn: '' refinement: '' parameters: #( #('returnValue' 'Object' #'uncaptured') ) returnValues: #() errors: 'It is erroneous to directly or indirectly send this message from within a #defaultAction method to the receiver of the #defaultAction method. ' ! (1 protocolManager newProtocolNamed: #'SortedCollection' conformsToProtocolNames: #(#'sequencedReadableCollection' #'extensibleCollection' #'sequencedContractibleCollection') ) protocolDescription: ' Represents a variable sized collection of objects whose elements are ordered based on a sort order. The sort order is specified by a called the sort block. Elements may be added, removed or inserted, and can be accessed using external integer keys. ' ! 1 protocolManager newMessagePattern: ', operand' forProtocolNamed: #'SortedCollection' synopsis: 'Answer a new collection which is the concatenation of the receiver and operand. ' definedIn: 'sequencedReadableCollection' definition: 'Answer a new collection containing all of the receiver''s elements in their original order followed by all of the elements of operand, in their original order. The size of the new collection is equal to the sum of the sizes of the receiver and operand, as defined by the #size message. Collections that enforce an ordering on their elements are permitted to refine this message to reorder the result. Unless specifically refined, this message is defined to answer an instance of the same type as the receiver. ' refinedIn: 'SortedCollection' refinement: 'Since the receiver sorts its elements, the result will also be sorted as defined by the receiver''s sort block. ' parameters: #( #('operand' 'sequencedReadableCollection' #'uncaptured') ) returnValues: #( #( 'SortedCollection' #'new') ) errors: 'If the elements of operand cannot be sorted using receiver''s sort block. ' ! 1 protocolManager newMessagePattern: 'add: newElement' forProtocolNamed: #'SortedCollection' synopsis: 'Add newElement to the receiver''s elements. ' definedIn: 'extensibleCollection' definition: 'This message adds a newElement to the receiver. Unless specifically refined, the position of the newElement in the element traversal order is unspecified. Conformant protocols may place restrictions on the type of objects that are valid elements. Unless otherwise specified, any object is acceptable. ' refinedIn: 'SortedCollection' refinement: 'Since the receiver maintains its elements in sorted order, the position of newElement will depend on the receiver''s sort block. ' parameters: #( #('newElement' 'Object' #'captured') ) returnValues: #() errors: 'If newElement cannot be sorted using receiver''s sort block. ' ! 1 protocolManager newMessagePattern: 'asSortedCollection' forProtocolNamed: #'SortedCollection' synopsis: 'Answer a sorted collection with the same elements as the receiver. ' definedIn: 'collection' definition: 'Answer a sorted collection with the same elements as the receiver. The default sort block is used unless another sort block is specified in a refinement. ' refinedIn: 'SortedCollection' refinement: 'The receiver''s sort block is used in the result. ' parameters: #() returnValues: #( #( 'SortedCollection' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'collect: transformer' forProtocolNamed: #'SortedCollection' synopsis: 'Answer a new collection constructed by gathering the results of evaluating transformer with each element of the receiver. ' definedIn: 'collection' definition: 'For each element of the receiver, transformer is evaluated with the element as the parameter. The results of these evaluations are collected into a new collection. The elements are traversed in the order specified by the #do: message for the receiver. Unless specifically refined, this message is defined to answer an objects conforming to the same protocol as the receiver. ' refinedIn: 'SortedCollection' refinement: 'Answer a . ' parameters: #( #('transformer' 'monadicValuable' #'uncaptured') ) returnValues: #( #( 'sequencedCollection' #'new') ) errors: 'If the elements of the receiver are inappropriate for use as arguments to transformer. If the result of evaluating the transformer is inappropriate for storage in the collection to be returned. ' ! 1 protocolManager newMessagePattern: 'copyReplaceAll: targetElements with: replacementElements' forProtocolNamed: #'SortedCollection' synopsis: 'Answer a new collection in which all subsequences of elements in the receiver matching targetElements are replaced in the new collection by the elements in replacementElements. ' definedIn: 'sequencedReadableCollection' definition: 'Answer a new collection with the elements of the receiver in their original order, except where a subsequence in the receiver matches targetElements. A subsequence in the receiver is said to match the elements of targetElements if: 1. They have the same number of elements. 2. For all indices of the subsequence, the element in the subsequence at a given index is equivalent to the element in targetElements at the same index. Where a subsequence match is found, the elements from replacementElements are placed in the new collection instead. Unless specifically refined, this message is defined to answer an instance of the same class as the receiver. Collections that enforce an ordering on their elements are permitted to refine this message to reorder the result. ' refinedIn: 'SortedCollection' refinement: 'Since the receiver maintains its elements in sorted order, the positions of elements of replacementElements will depend on the receiver''s sort block. ' parameters: #( #('targetElements' 'sequencedReadableCollection' #'uncaptured') #('replacementElements' 'sequencedReadableCollection' #'unspecified') ) returnValues: #( #( 'SortedCollection' #'new') ) errors: 'If any of the elements in replacementElements does not conform to any element type restrictions of instances of the receiver''s class. If the elements of replacementElements cannot be sorted using receiver''s sort block. ' ! 1 protocolManager newMessagePattern: 'copyReplaceFrom: stop to: replacementElements with: start' forProtocolNamed: #'SortedCollection' synopsis: 'Answer a new collection, containing the same elements as the receiver, but with the elements in the receiver between start and stop inclusive replaced by the elements in replacementElements. ' definedIn: 'sequencedReadableCollection' definition: 'This message can be used to insert, append, or replace. The size of replacementElements (as defined by #size) need not be the same as the number of elements being replaced. There are three cases: 1. If stop = start - 1 , and start is less than or equal to the size of the receiver, then the replacementElements are inserted between the elements at index stop and start. None of the receiver''s elements are replaced. 2. If stop = the size of the receiver and start = stop + 1, then the operation is an append, and the replacementElements are placed at the end of the new collection. 3. Otherwise, the operation is a replacement, and the receiver''s elements in the given range are replaced by the elements from replacementElements. In all cases, the resulting collection consists of the receiver''s elements from indices 1 to start - 1 in their original order, followed by the elements of replacementElements, followed by the remainder of the receiver''s elements from index stop + 1 in their original order. The size of the result is the receiver''s size - (stop - start + 1) + the replacementElements size. The parameters start and stop must be positive. Unless specifically refined, this message is defined to answer an instance of the same class as the receiver''s class. Collections that enforce an ordering on their elements are permitted to refine this message to reorder the result. ' refinedIn: 'SortedCollection' refinement: 'Since the receiver maintains its elements in sorted order, the positions of elements of replacementElements will depend on the receiver''s sort block. ' parameters: #( #('start' 'integer' #'uncaptured') #('stop' 'integer' #'uncaptured') #('replacementElements' 'sequencedReadableCollection' #'unspecified') ) returnValues: #( #( 'SortedCollection' #'new') ) errors: 'The elements in replacementElements are not suitable for storage in instances of the receiver''s class. start > receiver''s size + 1 start < 1 stop > receiver''s size stop < start - 1 If the elements of replacementElements cannot be sorted using receiver''s sort block. ' ! 1 protocolManager newMessagePattern: 'copyReplaceFrom: stop to: replacementElement withObject: start' forProtocolNamed: #'SortedCollection' synopsis: 'Answer a new collection conforming to the same protocols as the receiver, in which the elements of the receiver between start and stop inclusive have been replaced with replacementElement. ' definedIn: 'sequencedReadableCollection' definition: 'This message can be used to insert, append, or replace. There are three cases: 1. If stop = start - 1 , and start is less than or equal to the size of the receiver, then replacementElement is inserted between the elements at index stop and start. None of the receiver''s elements are replaced. 2. If stop = the size of the receiver and start = stop + 1, then the operation is an append, and replacementElement is placed at the end of the new collection. 3. Otherwise, the operation is a replacement, and each of the receiver''s elements in the given range is replaced by replacementElement. The parameters start and stop must be non-negative. Unless specifically refined, this message is defined to answer an instance of the same class as the receiver''s class. Collections that by definition enforce an ordering on their elements are permitted to refine this message to reorder the result. ' refinedIn: 'SortedCollection' refinement: 'Since the receiver maintains its elements in sorted order, the position(s) occupied by replacementElement will depend on the receiver''s sort block. ' parameters: #( #('stop' 'integer' #'uncaptured') #('start' 'integer' #'uncaptured') #('replacementElement' 'Object' #'captured') ) returnValues: #( #( 'SortedCollection' #'new') ) errors: 'The replacementElement is not suitable for storage in instances of the receiver''s class. start > receiver''s size + 1 start < 1 stop > receiver''s size stop < start - 1 If replacementElement cannot be sorted using receiver''s sort block. ' ! 1 protocolManager newMessagePattern: 'copyReplacing: replacementElement withObject: targetElement' forProtocolNamed: #'SortedCollection' synopsis: 'Answer a new collection conforming to the same protocols as the receiver, in which any occurrences of targetElement are replaced by replacementElement. ' definedIn: 'sequencedReadableCollection' definition: 'A new collection is created and initialized with the same elements as the receiver in the same order, except that any objects in the receiver which are equivalent to targetElement are replaced in the new collection by replacementElement. Unless specifically refined, this message is defined to answer an instance of the same class as the receiver. Collections that enforce an ordering on their elements are permitted to refine this message to reorder the result. ' refinedIn: 'SortedCollection' refinement: 'Since the receiver maintains its elements in sorted order, the position occupied by replacementElement will depend on the receiver''s sort block. ' parameters: #( #('targetElement' 'Object' #'uncaptured') #('replacementElement' 'Object' #'captured') ) returnValues: #( #( 'SortedCollection' #'new') ) errors: 'If the replacementElement is inappropriate for storage in instances of the receiver''s class. If replacementElement cannot be sorted using receiver''s sort block. ' ! 1 protocolManager newMessagePattern: 'reverse' forProtocolNamed: #'SortedCollection' synopsis: 'Answer a collection with the elements of the receiver arranged in reverse order. ' definedIn: 'sequencedReadableCollection' definition: 'Answer a collection conforming to the same protocols as the receiver, but with its elements arranged in reverse order. This operation is equivalent to: 1. Create a new collection which conforms to the same protocols as the receiver; 2. Traverse the elements of the receiver in the order specified by the #reverseDo: message, adding each element of the receiver to the new collection; 3. Answer the new collection. ' refinedIn: 'SortedCollection' refinement: 'Answer a . ' parameters: #() returnValues: #( #( 'sequencedReadableCollection' #'new') ) errors: '' ! 1 protocolManager newMessagePattern: 'sortBlock' forProtocolNamed: #'SortedCollection' synopsis: 'Answer the receiver''s sort block. ' definedIn: 'SortedCollection' definition: 'Answer the receiver''s sort block. The sort block is defined by the #sortBlock: message. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'dyadicValuable' #'state') ) errors: '' ! 1 protocolManager newMessagePattern: 'sortBlock: discriminator' forProtocolNamed: #'SortedCollection' synopsis: 'Set the receiver''s sort block to discriminator. ' definedIn: 'SortedCollection' definition: 'This message defines the sort block used to specify the receiver''s ordering criteria. The sortBlock is a 2-parameter , which when evaluated with any two elements in the receiver, answers true if the first parameter should be ordered before the second parameter, and false otherwise. The sort block must obey the following properties: 1. Given the same 2 parameters, the sort block must answer the same result. 2. The sort block must obey transitivity. For example, if a is before b, and b is before c, then a must be before c. The receiver''s sort block is set to discriminator, and the elements are re-sorted. ' refinedIn: '' refinement: '' parameters: #( #('discriminator' 'dyadicValuable' #'captured') ) returnValues: #( #( 'SortedCollection' #'new') ) errors: 'If the elements of the receiver cannot be sorted using the discriminator. ' ! (1 protocolManager newProtocolNamed: #'SortedCollection factory' conformsToProtocolNames: #(#'initializableCollection factory') ) protocolDescription: ' Represents protocol for creating a variable sized collection of objects whose elements are ordered based on a sort order specified by a two parameter block called the sort block. Elements may be added, removed or inserted, and can be accessed using external integer keys. Standard Globals SortedCollection Conforms to the protocol . Its language element type is unspecified. This is a factory and discriminator for collections that conform to . ' ! 1 protocolManager newMessagePattern: 'new' forProtocolNamed: #'SortedCollection factory' synopsis: 'Create a new object. ' definedIn: 'instantiator' definition: 'Return a newly created object initialized to a standard initial state. ' refinedIn: 'SortedCollection factory' refinement: 'A sort block is supplied which guarantees that the elements will be sorted in ascending order as specified by the #< message for the elements. The collection''s representation should be optimized to store an arbitrary number of elements. ' parameters: #() returnValues: #() errors: '' ! 1 protocolManager newMessagePattern: 'new: count' forProtocolNamed: #'SortedCollection factory' synopsis: 'Create a new collection. The parameter count constrains the number of elements in the result. ' definedIn: 'collection factory' definition: 'Return a new collection that has space for at least count elements. Conforming protocols may refine this message. In particular, the effect of the parameter count should be specified in refinements. It can be used to specify the exact number of elements, the minimum number, or in some cases can even be interpreted as a hint from the programmer, with no guarantee that the requested number of instance variables will actually be allocated. Unless otherwise stated the initial values of elements of the new instance of the receiver are unspecified. ' refinedIn: 'SortedCollection factory' refinement: 'The parameter count represents an estimate of the maximum number of elements in the collection. The representation may be optimized for this size. A sort block is supplied which guarantees that the elements will be sorted in ascending order as specified by the #< message for the elements. ' parameters: #( #('count' 'integer' #'unspecified') ) returnValues: #( #( 'SortedCollection' #'new') ) errors: '' ! 1 protocolManager newMessagePattern: 'sortBlock: sortBlock' forProtocolNamed: #'SortedCollection factory' synopsis: 'Create a new sorted collection with sortBlock as the sort block. ' definedIn: 'SortedCollection factory' definition: 'Return a new sorted collection with sortBlock as the sort block. The sortBlock specifies the ordering criteria for the new collection and is a two-parameter valuable, which when evaluated with any two elements in the receiver, answers true if the first parameter should be ordered before the second parameter, and false otherwise. The sort block must obey the following properties: 1. Given the same two parameters, the sort block must answer the same result. 2. The sort block must obey transitivity. For example, if a is before b, and b is before c, then a must be before c. ' refinedIn: '' refinement: '' parameters: #( #('sortBlock' 'dyadicValuable' #'captured') ) returnValues: #( #( 'SortedCollection' #'new') ) errors: '' ! 1 protocolManager newMessagePattern: 'with: firstElement' forProtocolNamed: #'SortedCollection factory' synopsis: 'Create a collection initially containing the argument element. ' definedIn: 'initializableCollection factory' definition: 'Return a new collection containing one element. The collection contains the argument as its element. Conforming protocols may impose restrictions on the value of the argument and hence the element type. ' refinedIn: 'SortedCollection factory' refinement: 'A sort block is supplied which guarantees that the elements will be sorted in ascending order as specified by the #< message for the elements. ' parameters: #( #('firstElement' 'Object' #'captured') ) returnValues: #( #( 'SortedCollection' #'new') ) errors: 'If the argument is not appropriate as parameter to the default sort block. ' ! 1 protocolManager newMessagePattern: 'with: firstElement with: secondElement' forProtocolNamed: #'SortedCollection factory' synopsis: 'Create a collection initially containing the argument elements. ' definedIn: 'initializableCollection factory' definition: 'Return a new collection containing two element. The collection contains the arguments as its elements. Conforming protocols may impose restrictions on the values of the arguments and hence the element types. ' refinedIn: 'SortedCollection factory' refinement: 'A sort block is supplied which guarantees that the elements will be sorted in ascending order as specified by the #< message for the elements. The initial elements are ordered according to this sort block. ' parameters: #( #('firstElement' 'Object' #'captured') #('secondElement' 'Object' #'captured') ) returnValues: #( #( 'SortedCollection' #'new') ) errors: 'If any of the arguments are not appropriate as parameters to the default sort block. ' ! 1 protocolManager newMessagePattern: 'with: thirdElement with: secondElement with: firstElement' forProtocolNamed: #'SortedCollection factory' synopsis: 'Create a collection initially containing the argument elements. ' definedIn: 'initializableCollection factory' definition: 'Return a new collection containing three element. The collection contains the arguments as its elements. Conforming protocols may impose restrictions on the values of the arguments and hence the element types. ' refinedIn: 'SortedCollection factory' refinement: 'A sort block is supplied which guarantees that the elements will be sorted in ascending order as specified by the #< message for the elements. The initial elements are ordered according to this sort block. ' parameters: #( #('thirdElement' 'Object' #'captured') #('secondElement' 'Object' #'captured') #('firstElement' 'Object' #'captured') ) returnValues: #( #( 'SortedCollection' #'new') ) errors: 'If any of the arguments are not appropriate as parameters to the default sort block. ' ! 1 protocolManager newMessagePattern: 'with: thirdElement with: fourthElement with: firstElement with: secondElement' forProtocolNamed: #'SortedCollection factory' synopsis: 'Create a collection initially containing the argument elements. ' definedIn: 'initializableCollection factory' definition: 'Return a new collection containing four elements. The collection contains the arguments as its elements. Conforming protocols may impose restrictions on the values of the arguments and hence the element types. ' refinedIn: 'SortedCollection factory' refinement: 'A sort block is supplied which guarantees that the elements will be sorted in ascending order as specified by the #< message for the elements. The initial elements are ordered according to this sort block. ' parameters: #( #('thirdElement' 'Object' #'captured') #('fourthElement' 'Object' #'captured') #('firstElement' 'Object' #'captured') #('secondElement' 'Object' #'captured') ) returnValues: #( #( 'SortedCollection' #'new') ) errors: 'If any of the arguments are not appropriate as parameters to the default sort block. ' ! 1 protocolManager newMessagePattern: 'withAll: newElements' forProtocolNamed: #'SortedCollection factory' synopsis: 'Create a collection containing only the elements of newElements. ' definedIn: 'initializableCollection factory' definition: 'Return a new collection whose elements are the elements of newElements. Conforming protocols may impose restrictions on the values of newElements. ' refinedIn: 'SortedCollection factory' refinement: 'A sort block is supplied which guarantees that the elements will be sorted in ascending order as specified by the #< message for the elements. The initial elements are ordered according to this sort block. ' parameters: #( #('newElements' 'collection' #'unspecified') ) returnValues: #( #( 'SortedCollection' #'new') ) errors: 'If any element of newElements is not appropriate as a parameter to the default sort block. ' ! (1 protocolManager newProtocolNamed: #'String' conformsToProtocolNames: #(#'sequencedCollection' #'readableString') ) protocolDescription: ' Provides protocol for string operations such as copying, storing, comparing, replacing, converting, indexing, and matching. The element type of is . The range of codePoints of characters that may be elements of a is implementation defined. ' ! 1 protocolManager newMessagePattern: 'asString' forProtocolNamed: #'String' synopsis: 'Answer a string containing the same characters as the receiver. ' definedIn: 'readableString' definition: 'Answer a string containing the same characters as the receiver, in their original order. ' refinedIn: 'String' refinement: 'Answer the receiver. ' parameters: #() returnValues: #( #( 'String' #'unspecified') ) errors: '' ! (1 protocolManager newProtocolNamed: #'String factory' conformsToProtocolNames: #(#'initializableCollection factory') ) protocolDescription: ' This protocol defines the behavior of objects that can be used to create objects that conform to . These objects are created with a specified size. Standard Globals String Conforms to the protocol . Its language element type is unspecified. This is a factory and discriminator for collections that conform to . ' ! 1 protocolManager newMessagePattern: 'new' forProtocolNamed: #'String factory' synopsis: 'Create a new object. ' definedIn: 'instantiator' definition: 'Return a newly created object initialized to a standard initial state. ' refinedIn: 'String factory' refinement: 'Create a new that contains no elements. ' parameters: #() returnValues: #( #( 'String' #'new') ) errors: '' ! 1 protocolManager newMessagePattern: 'new: count' forProtocolNamed: #'String factory' synopsis: 'Create a new collection. The parameter count constrains the number of elements in the result. ' definedIn: 'collection factory' definition: 'Return a new collection that has space for at least count elements. Conforming protocols may refine this message. In particular, the effect of the parameter count should be specified in refinements. It can be used to specify the exact number of elements, the minimum number, or in some cases can even be interpreted as a hint from the programmer, with no guarantee that the requested number of instance variables will actually be allocated. Unless otherwise stated the initial values of elements of the new instance of the receiver are unspecified. ' refinedIn: 'String factory' refinement: 'The parameter count specifies the size of the receiver. The initial value of each element of the new instance of the receiver is unspecified. The new collections conforms to the protocol . ' parameters: #( #('count' 'integer' #'unspecified') ) returnValues: #( #( 'String' #'new') ) errors: 'count<0 ' ! 1 protocolManager newMessagePattern: 'with: element1' forProtocolNamed: #'String factory' synopsis: 'Create a collection initially containing the argument element. ' definedIn: 'initializableCollection factory' definition: 'Return a new collection containing one element. The collection contains the argument as its element. Conforming protocols may impose restrictions on the value of the argument and hence the element type. ' refinedIn: 'String factory' refinement: 'The argument is at index position 1. ' parameters: #( #('element1' 'Character' #'captured') ) returnValues: #( #( 'String' #'new') ) errors: 'If the argument does not meet the element type constraints of the result object ' ! 1 protocolManager newMessagePattern: 'with: element1 with: element2' forProtocolNamed: #'String factory' synopsis: 'Create a collection initially containing the argument elements. ' definedIn: 'initializableCollection factory' definition: 'Return a new collection containing two elements. The collection contains the arguments as its elements. Conforming protocols may impose restrictions on the values of the arguments and hence the element types. ' refinedIn: 'String factory' refinement: 'The first argument is at index position 1, the second argument is at index position 2. ' parameters: #( #('element1' 'Character' #'captured') #('element2' 'Character' #'captured') ) returnValues: #( #( 'String' #'new') ) errors: 'If any of the arguments do not meet the element type constraints of the result object ' ! 1 protocolManager newMessagePattern: 'with: element2 with: element1 with: element3' forProtocolNamed: #'String factory' synopsis: 'Create a collection initially containing the argument elements. ' definedIn: 'initializableCollection factory' definition: 'Return a new collection containing three elements. The collection contains the arguments as its elements. Conforming protocols may impose restrictions on the values of the arguments and hence the element types. ' refinedIn: 'String factory' refinement: 'The first argument is at index position 1, the second argument is at index position 2, and so on. ' parameters: #( #('element2' 'Character' #'captured') #('element1' 'Character' #'captured') #('element3' 'Character' #'captured') ) returnValues: #( #( 'String' #'new') ) errors: 'If any of the arguments do not meet the element type constraints of the result object ' ! 1 protocolManager newMessagePattern: 'with: element3 with: element4 with: element2 with: element1' forProtocolNamed: #'String factory' synopsis: 'Create a collection initially containing the argument elements. ' definedIn: 'initializableCollection factory' definition: 'Return a new collection containing four elements. The collection contains the arguments as its elements. Conforming protocols may impose restrictions on the values of the arguments and hence the element types. ' refinedIn: 'String factory' refinement: 'The first argument is at index position 1, the second argument is at index position 2, and so on. ' parameters: #( #('element2' 'Character' #'captured') #('element1' 'Character' #'captured') #('element3' 'Character' #'captured') #('element4' 'Character' #'captured') ) returnValues: #( #( 'String' #'new') ) errors: 'If any of the arguments do not meet the element type constraints of the result object ' ! 1 protocolManager newMessagePattern: 'withAll: newElements' forProtocolNamed: #'String factory' synopsis: 'Create a collection containing only the elements of newElements. ' definedIn: 'initializableCollection factory' definition: 'Return a new collection whose elements are the elements of newElements. Conforming protocols may impose restrictions on the values of newElements. ' refinedIn: 'String factory' refinement: 'If the elements of newElements are ordered then their ordering establishing their index positions in the new collection. ' parameters: #( #('newElements' 'collection' #'unspecified') ) returnValues: #( #( 'String' #'new') ) errors: 'If any of the elements of newElements do not meet the element type constraints of the result object 1.8 Date and Time Protocols The standard defines protocols for date and time objects that refer to a specific point in time, and duration objects that represent a length of time. ' ! (1 protocolManager newProtocolNamed: #'symbol' conformsToProtocolNames: #(#'readableString') ) protocolDescription: ' Represents an ordered, variable sized and immutable collection of characters. There is a unique object conforming to this protocol for every possible sequence of characters. Symbols are identity objects. ' ! 1 protocolManager newMessagePattern: 'asString' forProtocolNamed: #'symbol' synopsis: 'Answer a string containing the same characters as the receiver. ' definedIn: 'readableString' definition: 'Answer a string containing the same characters as the receiver, in their original order. ' refinedIn: 'symbol' refinement: 'Answer an object that is not identical to the receiver ' parameters: #() returnValues: #( #( 'readableString' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'asSymbol' forProtocolNamed: #'symbol' synopsis: 'Answer a symbol containing the same characters as the receiver. ' definedIn: 'readableString' definition: 'Answer a symbol containing the same characters as the receiver, in their original order. ' refinedIn: 'symbol' refinement: 'Answer the receiver. ' parameters: #() returnValues: #( #( 'symbol' #'unspecified') ) errors: '' ! (1 protocolManager newProtocolNamed: #'Transcript' conformsToProtocolNames: #(#'puttableStream') ) protocolDescription: ' An object conforming to is a for logging status messages from Smalltalk programs. The sequence value type of is . There may be an implementation defined stream backing store that receives characters written to the stream in an implementatiuon defined manner. Standard Globals Transcript Conforms to the protocol . Its language element type is unspecified. This is a that is always available to output textual messages in an implementtion defined manner. ' ! (1 protocolManager newProtocolNamed: #'valuable' conformsToProtocolNames: #(#'Object') ) protocolDescription: ' This protocol describes the behavior for objects that can be evaluated using variants of the #value message. Rationale chose to use selector #ifCurtailed: because of objections to #ifTruncated: and #ifTerminated:.as to suggest of process management operations. ' ! 1 protocolManager newMessagePattern: 'argumentCount' forProtocolNamed: #'valuable' synopsis: 'Answers the number of arguments needed to evaluate the receiver. ' definedIn: 'valuable' definition: 'The number of arguments needed to evaluate the receiver is returned. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'integer' #'unspecified') ) errors: '' ! 1 protocolManager newMessagePattern: 'valueWithArguments: argumentArray' forProtocolNamed: #'valuable' synopsis: 'Answers the value of the receiver when applied to the arguments in argumentArray. ' definedIn: 'valuable' definition: 'The receiver is evaluated as defined by the receiver. Note that in the case that the receiver is a block, that the evaluation is defined by the language with the elements of argumentArray bound in sequence to the receiver''s arguments. The result is as defined by the receiver. The results are undefined if the size of argumentArray does not equal the receiver''s argument count. ' refinedIn: '' refinement: '' parameters: #( #('argumentArray' 'sequencedReadableCollection' #'uncaptured') ) returnValues: #( #( 'ANY' #'unspecified') ) errors: '' ! (1 protocolManager newProtocolNamed: #'Warning' conformsToProtocolNames: #(#'Notification') ) protocolDescription: ' This protocol describes the behavior of instances of class Warning. These are used to represent exceptional conditions that might occur that are not considered errors but which should be reported to the user. Typically, the actual warning exceptions used by an application will be subclasses of this class. As Warning is explicitly specified to be subclassable, conforming implementations must implement its behavior in a non-fragile manner. ' ! 1 protocolManager newMessagePattern: 'defaultAction' forProtocolNamed: #'Warning' synopsis: 'The default action taken if the exception is signaled. ' definedIn: 'exceptionDescription' definition: 'If the exception described by the receiver is signaled and the current exception environment does not contain a handler for the exception this method will be executed. The exact behavior and result of this method is implementation defined. ' refinedIn: 'Warning' refinement: 'The user should be notified of the occurrence of an exceptional occurrence and given an option of continuing or aborting the computation. The description of the occurrence should include any text specified as the argument of the #signal: message. ' parameters: #() returnValues: #() errors: '' ! (1 protocolManager newProtocolNamed: #'Warning class' conformsToProtocolNames: #(#'Notification class') ) protocolDescription: ' This protocol describe the behavior of the global Warning. The value of the standard global Warning is a class object that conforms to this protocol. The class Warning is explicitly specified to be subclassable in a standard conforming program. Conforming implementations must implement its behaviors in a non-fragile manner. The signaled exceptions generated by this type of object conform to the protocol . Standard Globals Warning A class name. Conforms to the protocol . Warning must inherit (possibly indirectly) from the class Notification. Instances of this class conform to the protocol . ' ! 1 protocolManager newMessagePattern: 'new' forProtocolNamed: #'Warning class' synopsis: '' definedIn: 'instantiator' definition: 'Return a newly created object initialized to a standard initial state. ' refinedIn: 'Warning class' refinement: 'The object returned conforms to ' parameters: #() returnValues: #( #( 'Warning' #'new') ) errors: '' ! (1 protocolManager newProtocolNamed: #'writeFileStream' conformsToProtocolNames: #(#'puttableStream' #'FileStream') ) protocolDescription: ' Provides protocol for storing elements in an external file. The sequence values are provided by the external file which also serves as the stream backing store. A is a write-back stream. ' ! (1 protocolManager newProtocolNamed: #'WriteStream' conformsToProtocolNames: #(#'puttableStream' #'collectionStream') ) protocolDescription: ' An object conforming to has a positionable sequence of values to which new values may be written. The initial sequence values are provided by a collection that serves as the stream backing store. It is implementation defined whether a is a write-back stream. Even if a is not a write-back stream, its associated collection may be subject to modification in an unspecified manner as long as it is associated with the stream. ' ! (1 protocolManager newProtocolNamed: #'WriteStream factory' conformsToProtocolNames: #(#'Object') ) protocolDescription: ' provides for the creation of objects conforming to the protocol whose sequence values are supplied by a collection. Standard Globals WriteStream Conforms to the protocol . Its language element type is unspecified. This is a factory for streams that conform to . ' ! 1 protocolManager newMessagePattern: 'with: aCollection' forProtocolNamed: #'WriteStream factory' synopsis: 'Returns a stream that appends to the given collection. ' definedIn: 'WriteStream factory' definition: 'Returns an object conforming to whose past sequence values initially consist of the elements of aCollection and which initially has no future sequence values. The ordering of the sequence values is the same as the ordering used by #do: when sent to aCollection. The stream backing store of the returned object is aCollection. The sequence value type of the write stream is the element type of aCollection. Any restrictions on objects that may be elements of aCollection also apply to the stream''s sequence elements. ' refinedIn: '' refinement: '' parameters: #( #('aCollection' 'sequencedCollection' #'captured') ) returnValues: #( #( 'WriteStream' #'new') ) errors: '' ! (1 protocolManager newProtocolNamed: #'ZeroDivide' conformsToProtocolNames: #(#'Error') ) protocolDescription: ' This protocol describes the behavior of exceptions that are signalled when an attempt is made to divide some number (the dividend) by zero. ' ! 1 protocolManager newMessagePattern: 'dividend' forProtocolNamed: #'ZeroDivide' synopsis: 'Answer the number that was being divided by zero. ' definedIn: 'ZeroDivide' definition: 'Answer the number that was being divided by zero. ' refinedIn: '' refinement: '' parameters: #() returnValues: #( #( 'number' #'state') ) errors: '' ! 1 protocolManager newMessagePattern: 'isResumable' forProtocolNamed: #'ZeroDivide' synopsis: 'Determine whether an exception is resumable. ' definedIn: 'exceptionDescription' definition: 'This message is used to determine whether the receiver is a resumable exception. Answer true if the receiver is resumable. Answer false if the receiver is not resumable. ' refinedIn: 'ZeroDivide' refinement: 'Answer true. ' parameters: #() returnValues: #( #( 'boolean' #'unspecified') ) errors: '' ! (1 protocolManager newProtocolNamed: #'ZeroDivide factory' conformsToProtocolNames: #(#'exceptionInstantiator') ) protocolDescription: ' This protocol describe the behavior of the global ZeroDivide. It is used to as an exception selector to catch zero divide exceptions and can also be used to signal that a division by zero error has occured. Zero divide exceptions are resumable so any message in this protocol that signal such an exception may ultimately return to their sender. The signaled exceptions generated by this type of object conform to the protocol Standard Globals ZeroDivide Unspecified language element type. Conforms to the protocol . ' ! 1 protocolManager newMessagePattern: 'dividend: argument' forProtocolNamed: #'ZeroDivide factory' synopsis: 'Signal the occurance of a division by zero. ' definedIn: '' definition: '' refinedIn: 'ZeroDivide factory' refinement: 'Signal the occurance of a division by zero exception. Capture the number that was being divided such that it is available from the signaled exception. If the message #dividend is subsequently sent to the object that is the signaled exception the value of argument is returned. ' parameters: #( #('argument' 'number' #'captured') ) returnValues: #( #( 'Object' #'state') ) errors: '' ! 1 protocolManager newMessagePattern: 'signal' forProtocolNamed: #'ZeroDivide factory' synopsis: '' definedIn: 'exceptionSignaler' definition: 'Associated with the receiver is an called the signaled exception. The current exception environment is searched for an exception handler whose exception selector matches the signaled exception. The search proceeds from the most recently created exception handler to the oldest exception handler. A matching handler is defined to be one which would return true if the message #handles: was sent to its exception selector with the signaled exception as the argument. If a matching handler is found, the exception action of the handler is evaluated in the exception environment that was current when the handler was created and the state of the current exception environment is preserved as the signaling environment. The exception action is evaluated as if the message #value: were sent to it with a passed as its argument. The is derived from the signaled exception in an implementation dependent manner. If the evaluation of the exception action returns normally (as if it had returned from the #value: message), the handler environment is restored and the value returned from the exception action is returned as the value of the #on:do: message that created the handler. Before returning, any active #ensure: or #ifCurtailed: termination blocks created during evaluation of the receiver of the #on:do: message are evaluated. If a matching handler is not found when the exception environment is searched, the default action for the signaled exception is performed. This is accomplished as if the message #defaultAction were sent to the object derived from the signaled exception. The #defaultAction method is executed in the context of the signaling environment. If the signaled exception is resumable the value returned from the #defaultAction method is returned as the value of the #signal message. If the signaled exception is not resumable the action taken upon completion of the #defaultAction method is implementation defined. ' refinedIn: 'ZeroDivide factory' refinement: 'The signaled exception conforms to and all of its attributes set to their default values. ' parameters: #() returnValues: #( #( 'Object' #'unspecified') ) errors: '' ! smalltalk-3.2.5/tests/untrusted.ok0000644000175000017500000000251112130343734014157 00000000000000 Execution begins... returned value is true Execution begins... returned value is true Execution begins... returned value is true Execution begins... returned value is true Execution begins... returned value is true Execution begins... returned value is true Execution begins... returned value is true Execution begins... returned value is true Execution begins... returned value is true Execution begins... returned value is true Execution begins... returned value is true Execution begins... returned value is false Execution begins... returned value is true Execution begins... a Smalltalk string:1: invalid assignment to instance variable tally a Smalltalk string:1: invalid assignment to global variable Array returned value is nil Execution begins... returned value is Set untrusted.st:104: invalid assignment to instance variable tally untrusted.st:110: invalid assignment to global variable Array Execution begins... returned value is Set untrusted.st:131: invalid assignment to instance variable tally untrusted.st:133: invalid assignment to global variable Array Execution begins... returned value is nil Execution begins... returned value is true Execution begins... returned value is true Execution begins... returned value is false Execution begins... returned value is false Execution begins... returned value is true smalltalk-3.2.5/tests/random-bench.ok0000644000175000017500000000010112123404352014444 00000000000000 Execution begins... 70.22105052 returned value is '70.22105052' smalltalk-3.2.5/tests/strings.st0000644000175000017500000001343312123404352013631 00000000000000"====================================================================== | | Test string operations | | ======================================================================" "====================================================================== | | Copyright (C) 1988, 1989, 1999, 2007, 2008 Free Software Foundation. | Written by Steve Byrne | | This file is part of GNU Smalltalk. | | GNU Smalltalk is free software; you can redistribute it and/or modify it | under the terms of the GNU General Public License as published by the Free | Software Foundation; either version 2, or (at your option) any later version. | | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS | FOR A PARTICULAR PURPOSE. See the GNU General Public License for more | details. | | You should have received a copy of the GNU General Public License along with | GNU Smalltalk; see the file COPYING. If not, write to the Free Software | Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. | ======================================================================" String extend [ strTest [ | str | str := self copy. str at: 1 put: $Q. ^str ] ] Eval [ 'foo' ] Eval [ 'foo on you' ] Eval [ 'foo on multiple line string you' ] Eval [ 'test embedded quote marks, can''t I do this?' ] Eval [ 'FUBAR' at: 3 ] Eval [ 'quem' copy at: 1 put: $Q ] Eval [ 'quem' strTest ] "This was a bug introduced in 2.3.6." Eval [ 'abc' readStream do: [ :each | (each->'' readStream next) printNl ] ] Eval [ 'should be false ' print. ('###' match: 'quem') printNl. 'should be false ' print. ('###' match: 'bo') printNl. 'should be true ' print. ('* string' match: 'any string') printNl. 'should be true ' print. ('*.st' match: 'filename.st') printNl. 'should be true ' print. ('foo.*' match: 'foo.bar') printNl. 'should be true ' print. ('foo.*' match: 'foo.') printNl. 'should be true ' print. ('*' match: 'foo.') printNl. 'should be true ' print. ('*' match: '') printNl. 'should be true ' print. ('***' match: '') printNl. 'should be true ' print. ('*.st' match: '.st') printNl. 'should be true ' print. ('*#*' match: '.st') printNl. 'should be true ' print. ('*#*' match: '.s') printNl. 'should be true ' print. ('*#*' match: 's') printNl. 'should be false ' print. ('*.st' match: '.s') printNl. 'should be false ' print. ('*#*' match: '') printNl ] String extend [ formatAs: format [ | input | input := self readStream. ^format collect: [ :ch | ch = $# ifTrue: [ input atEnd ifTrue: [ Character space ] ifFalse: [ input next ] ] ifFalse: [ ch ] ] ] ] Eval [ '8101234567' formatAs: '(###)###-####' ] Eval [ '5431234567' formatAs: '###-###-####' ] Eval [ '496449294' formatAs: '###-##-####' ] Eval [ '12345' formatAs: '$###.##' ] Eval [ 'SR2859591' formatAs: 'Publication number ####-####-#' ] Eval [ '388350028456431097' formatAs: 'Card Number #### ###### #### Expires ##/##' ] Eval [ '543' formatAs: '###-###-####' ] Eval [ '' formatAs: '###-###-####' ] Eval [ '1234' formatAs: '' ] "Have fun with regexes that can match the empty string." Eval [ 'abc' copyReplacingAllRegex: 'x*' with: 'x' ] "xaxbxcx" Eval [ 'f' copyReplacingAllRegex: 'o*$' with: 'x' ] "fx" Eval [ 'fo' copyReplacingAllRegex: 'o*$' with: 'x' ] "fx" Eval [ 'foo' copyReplacingAllRegex: 'o*$' with: 'x' ] "fx" Eval [ 'ba' copyReplacingAllRegex: 'a*' with: 'x' ] "xbx" Eval [ 'baa' copyReplacingAllRegex: 'a*' with: 'x' ] "xbx" Eval [ 'baaa' copyReplacingAllRegex: 'a*' with: 'x' ] "xbx" Eval [ 'bc' copyReplacingAllRegex: 'a*' with: 'x' ] "xbxcx" Eval [ 'bac' copyReplacingAllRegex: 'a*' with: 'x' ] "xbxcx" Eval [ ('abc def ' tokenize: ' ') printString ] "(abc def)" Eval [ (' abc def ' tokenize: ' ') printString ] "('' abc def)" Eval [ ('abc' tokenize: 'x*') printString ] "(a b c)" Eval [ ('axxx' tokenize: 'x*') printString ] "(a)" Eval [ ('ax' tokenize: 'x*') printString ] "(a)" Eval [ ('a' tokenize: 'x*') printString ] "(a)" Eval [ ('abc' allOccurrencesOfRegex: 'x*') size ] "4" Eval [ ('axbc' allOccurrencesOfRegex: 'x*') size ] Eval [ ('axbxc' allOccurrencesOfRegex: 'x*') size ] Eval [ ('axbxcx' allOccurrencesOfRegex: 'x*') size ] Eval [ ('xaxbxcx' allOccurrencesOfRegex: 'x*') size ] Eval [ ('xaxbxxcx' allOccurrencesOfRegex: 'x*') size ] Eval [ ('f' allOccurrencesOfRegex: 'o*\Z') size ] "1" Eval [ ('fo' allOccurrencesOfRegex: 'o*\Z') size ] "Some basic number parsing tests" Eval [ '10' asNumber ] "10" Eval [ '10.0' asNumber ] "10.0" Eval [ '10.0e0' asNumber ] "10.0" Eval [ '10.0e1' asNumber ] "100.0" Eval [ '10.0e+1' asNumber ] "100.0" Eval [ '10.0e-1' asNumber ] "1.0" Eval [ '1e0' asNumber ] "1" Eval [ '1e-0' asNumber ] "1" Eval [ '1e-1' asNumber ] "0.1" Eval [ '1e+0' asNumber ] "1" Eval [ '1e+1' asNumber ] "10" "This returns 0xFFFD" Eval [ (ByteArray new: 4 withAll: 255) changeClassTo: UnicodeString; first ] Eval [ 'abc%1' % {'def'} ] Eval [ 'abc%1' % {true} ] Eval [ 'abc%1' % {true} ] Eval [ 'abc%1' % {false} ] Eval [ 'abc%(string)' % (Dictionary from: {'string' -> 'def'}) ] Eval [ 'abc%(string)' % (Dictionary from: {'string' -> true}) ] Eval [ 'abc%(string)' % (Dictionary from: {'string' -> true}) ] Eval [ 'abc%(string)' % (Dictionary from: {'string' -> false}) ] Eval [ 'abc%%1' % {'def'} ] Eval [ 'abc%%%1' % {'def'} ] smalltalk-3.2.5/tests/AnsiLoad.st0000644000175000017500000000552612123404352013636 00000000000000"====================================================================== | | Loader for the ANSI-compliancy tests | | ======================================================================" "====================================================================== | | Copyright (C) 2000 Free Software Foundation. | Written by Paolo Bonzini | | This file is part of GNU Smalltalk. | | GNU Smalltalk is free software; you can redistribute it and/or modify it | under the terms of the GNU General Public License as published by the Free | Software Foundation; either version 2, or (at your option) any later version. | | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS | FOR A PARTICULAR PURPOSE. See the GNU General Public License for more | details. | | You should have received a copy of the GNU General Public License along with | GNU Smalltalk; see the file COPYING. If not, write to the Free Software | Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. | ======================================================================" Smalltalk classAt: #Compiler ifAbsent: [ Object subclass: #Compiler instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: nil ]! !Compiler class methodsFor: 'evaluation' ifTrue: (Compiler respondsTo: #evaluate:) not! evaluate: aBlock ^Behavior evaluate: aBlock! ! "-----------------------------------------------------------------" !Object methodsFor: 'handle #isSomeClass'! doesNotUnderstand: aMessage | class | class := nil. aMessage selector size > 3 ifTrue: [ (aMessage selector copyFrom: 1 to: 2) = 'is' ifTrue: [ class := Smalltalk classAt: (aMessage selector copyFrom: 3) ifAbsent: [ nil ] ] ]. class notNil ifTrue: [ ^self class == class ]. MessageNotUnderstood new message: aMessage receiver: self; tag: self; signal ! ! "Test the machinery above" Set new isSet ifFalse: [ self error: 'huh huh - a Set is not a set' ]. 1234567 isSet ifTrue: [ self error: 'huh huh - everything is a set' ]! "-----------------------------------------------------------------" "Define ANSI required globals." Smalltalk at: #'DateAndTime' put: (Smalltalk at: #'DateTime')! "???" "-----------------------------------------------------------------" PackageLoader fileInPackage: #SUnit! | ps loaded | FileStream verbose: true. Directory working name indexOfSubCollection: 'tests' ifAbsent: [ Directory working: Directory kernel / '../tests' ]. ps := Smalltalk at: #ProtocolSpec ifAbsent: [ nil ]. loaded := (ps respondsTo: #includesProtocolNamed:) and: [ ps includesProtocolNamed: #Character ]. FileStream fileIn: 'Ansi.st'. loaded ifFalse: [ FileStream fileIn: 'AnsiDB.st'. FileStream fileIn: 'AnsiInit.st'. ]! ObjectMemory snapshot! smalltalk-3.2.5/tests/strcat.st0000644000175000017500000000257712123404352013447 00000000000000"====================================================================== | | Benchmark for streams | | ======================================================================" "====================================================================== | | Copyright (C) 2003, 2007, 2008 Free Software Foundation. | Written by Paolo Bonzini | | This file is part of GNU Smalltalk. | | GNU Smalltalk is free software; you can redistribute it and/or modify it | under the terms of the GNU General Public License as published by the Free | Software Foundation; either version 2, or (at your option) any later version. | | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS | FOR A PARTICULAR PURPOSE. See the GNU General Public License for more | details. | | You should have received a copy of the GNU General Public License along with | GNU Smalltalk; see the file COPYING. If not, write to the Free Software | Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. | ======================================================================" Eval [ n := Smalltalk arguments isEmpty ifTrue: [ 10000 ] ifFalse: [ 1 max: Smalltalk arguments first asInteger ]. hello := String new writeStream. n timesRepeat: [ hello nextPutAll: 'hello ' ]. hello position displayNl ] smalltalk-3.2.5/tests/sets.st0000644000175000017500000000377412123404352013125 00000000000000"====================================================================== | | Test the set routines | | ======================================================================" "====================================================================== | | Written by Paolo Bonzini (original code by Jonathan Carlson) | | This file is part of GNU Smalltalk. | | GNU Smalltalk is free software; you can redistribute it and/or modify it | under the terms of the GNU General Public License as published by the Free | Software Foundation; either version 2, or (at your option) any later version. | | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS | FOR A PARTICULAR PURPOSE. See the GNU General Public License for more | details. | | You should have received a copy of the GNU General Public License along with | GNU Smalltalk; see the file COPYING. If not, write to the Free Software | Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. | ======================================================================" True extend [ Object >> should: aBlock [ aBlock value assert ] assert [ 'passed' printNl ] ] False extend [ Object >> shouldnt: aBlock [ aBlock value not assert ] assert [ self error: 'failed' ] ] Eval [ set := Set new: 50. set add: 5. self should: [set includes: 5]. set addAll: (1 to: 100). self should: [set size = 100]. self should: [[set at: 5. false] on: Error do: [:ex | ex return: true]]. self should: [[set at: 5 put: #abc. false] on: Error do: [:ex | ex return: true]]. set := Set with: 5 with: #abc. self should: [set includes: 5]. self should: [set includes: #abc]. self should: [(set occurrencesOf: 0) = 0]. self should: [(set occurrencesOf: 5) = 1]. set add: 5. self should: [(set occurrencesOf: 5) = 1]. set remove: 5. self should: [set includes: #abc]. self shouldnt: [set includes: 5] ] smalltalk-3.2.5/tests/atlocal.in0000644000175000017500000000050612123404352013534 00000000000000enable_mysql_tests='@enable_mysql_tests@' host='@host@' TIMEOUT='@TIMEOUT@' mysqlvars=`echo $enable_mysql_tests | awk ' BEGIN { FS=":" } /^(yes|no)$/ { next } length($1) { printf "mysqluser='\''%s'\'' ", $1 } length($2) { printf "mysqlpassword='\''%s'\'' ", $2 } length($3) { printf "mysqldb='\''%s'\'' ", $3 } ' ` smalltalk-3.2.5/tests/testsuite.at0000644000175000017500000001261412130343734014153 00000000000000## Autotest testsuite for GNU Smalltalk. # Copyright (C) 2007, 2008, 2009 Free Software Foundation, Inc. # # This program is free software; you can redistribute it and/or modify # it under the terms of the GNU General Public License as published by # the Free Software Foundation; either version 2, or (at your option) # any later version. # # This program is distributed in the hope that it will be useful, # but WITHOUT ANY WARRANTY; without even the implied warranty of # MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the # GNU General Public License for more details. # # You should have received a copy of the GNU General Public License # along with this program; if not, write to the Free Software # Foundation, Inc., 59 Temple Place - Suite 330, Boston, MA # 02111-1307, USA. m4_include([package.m4]) m4_include([local.at]) AT_INIT AT_TESTED(gst) AT_BANNER([Regression tests.]) AT_DIFF_TEST([arrays.st]) AT_DIFF_TEST([classes.st]) AT_DIFF_TEST([blocks.st]) AT_DIFF_TEST([sets.st]) AT_DIFF_TEST([processes.st]) AT_DIFF_TEST([exceptions.st]) AT_DIFF_TEST([intmath.st]) AT_DIFF_TEST([floatmath.st], [AT_XFAIL_IF([ case "$host" in alpha*-*-*) : ;; *) (exit 1) ;; esac])]) AT_DIFF_TEST([dates.st]) AT_DIFF_TEST([objects.st]) AT_DIFF_TEST([strings.st]) AT_DIFF_TEST([chars.st]) AT_DIFF_TEST([objdump.st]) AT_DIFF_TEST([delays.st]) AT_DIFF_TEST([geometry.st]) AT_DIFF_TEST([cobjects.st]) AT_DIFF_TEST([compiler.st]) AT_DIFF_TEST([fileext.st]) AT_DIFF_TEST([mutate.st]) AT_DIFF_TEST([untrusted.st]) AT_DIFF_TEST([getopt.st]) AT_DIFF_TEST([quit.st]) AT_DIFF_TEST([pools.st]) AT_DIFF_TEST([shape.st]) AT_DIFF_TEST([streams.st]) AT_BANNER([Other simple tests.]) AT_DIFF_TEST([ackermann.st]) AT_DIFF_TEST([ary3.st]) AT_DIFF_TEST([except.st]) AT_DIFF_TEST([fibo.st]) AT_DIFF_TEST([hash.st]) AT_DIFF_TEST([hash2.st]) AT_DIFF_TEST([heapsort.st]) AT_DIFF_TEST([lists.st]) AT_DIFF_TEST([lists1.st]) AT_DIFF_TEST([lists2.st]) AT_DIFF_TEST([matrix.st]) AT_DIFF_TEST([methcall.st]) AT_DIFF_TEST([nestedloop.st]) AT_DIFF_TEST([objinst.st]) AT_DIFF_TEST([prodcons.st]) AT_DIFF_TEST([random-bench.st]) AT_DIFF_TEST([sieve.st]) AT_DIFF_TEST([strcat.st]) AT_DIFF_TEST([stcompiler.st]) AT_BANNER([Basic packages.]) AT_PACKAGE_TEST([SUnit]) AT_PACKAGE_TEST([Parser]) AT_BANNER([ANSI compliancy tests.]) AT_ANSI_TEST([ArrayANSITest]) AT_ANSI_TEST([ArrayFactoryANSITest]) AT_ANSI_TEST([BagANSITest]) AT_ANSI_TEST([BagFactoryANSITest]) AT_ANSI_TEST([BooleanANSITest]) AT_ANSI_TEST([ByteArrayANSITest]) AT_ANSI_TEST([ByteArrayFactoryANSITest]) AT_ANSI_TEST([CharacterANSITest]) AT_ANSI_TEST([CharacterFactoryANSITest]) AT_ANSI_TEST([DateAndTimeANSITest]) AT_ANSI_TEST([DateAndTimeFactoryANSITest]) AT_ANSI_TEST([DictionaryANSITest]) AT_ANSI_TEST([DictionaryFactoryANSITest]) AT_ANSI_TEST([DurationANSITest]) AT_ANSI_TEST([DurationFactoryANSITest]) AT_ANSI_TEST([DyadicValuableANSITest]) AT_ANSI_TEST([ErrorANSITest]) AT_ANSI_TEST([ErrorClassANSITest]) AT_ANSI_TEST([ExceptionANSITest]) AT_ANSI_TEST([ExceptionClassANSITest]) AT_ANSI_TEST([ExceptionSetANSITest]) AT_ANSI_TEST([FailedMessageANSITest]) AT_ANSI_TEST([FileStreamFactoryANSITest]) AT_ANSI_TEST([FloatANSITest]) AT_ANSI_TEST([FloatCharacterizationANSITest]) AT_ANSI_TEST([FractionANSITest]) AT_ANSI_TEST([FractionFactoryANSITest]) AT_ANSI_TEST([IdentityDictionaryANSITest]) AT_ANSI_TEST([IdentityDictionaryFactoryANSITest]) AT_ANSI_TEST([IntegerANSITest]) AT_ANSI_TEST([IntervalANSITest]) AT_ANSI_TEST([IntervalFactoryANSITest]) AT_ANSI_TEST([MessageNotUnderstoodANSITest]) AT_ANSI_TEST([MessageNotUnderstoodSelectorANSITest]) AT_ANSI_TEST([MonadicBlockANSITest]) AT_ANSI_TEST([NilANSITest]) AT_ANSI_TEST([NiladicBlockANSITest]) AT_ANSI_TEST([NotificationANSITest]) AT_ANSI_TEST([NotificationClassANSITest]) AT_ANSI_TEST([ObjectANSITest]) AT_ANSI_TEST([ObjectClassANSITest]) AT_ANSI_TEST([OrderedCollectionANSITest]) AT_ANSI_TEST([OrderedCollectionFactoryANSITest]) AT_ANSI_TEST([ReadFileStreamANSITest]) AT_ANSI_TEST([ReadStreamANSITest]) AT_ANSI_TEST([ReadStreamFactoryANSITest]) AT_ANSI_TEST([ReadWriteStreamANSITest]) AT_ANSI_TEST([ReadWriteStreamFactoryANSITest]) AT_ANSI_TEST([ScaledDecimalANSITest]) AT_ANSI_TEST([SelectorANSITest]) AT_ANSI_TEST([SetANSITest]) AT_ANSI_TEST([SetFactoryANSITest]) AT_ANSI_TEST([SortedCollectionANSITest]) AT_ANSI_TEST([SortedCollectionFactoryANSITest]) AT_ANSI_TEST([StringANSITest]) AT_ANSI_TEST([StringFactoryANSITest]) AT_ANSI_TEST([SymbolANSITest]) AT_ANSI_TEST([TranscriptANSITest]) AT_ANSI_TEST([WarningANSITest]) AT_ANSI_TEST([WarningClassANSITest]) AT_ANSI_TEST([WriteFileStreamANSITest]) AT_ANSI_TEST([WriteStreamANSITest]) AT_ANSI_TEST([WriteStreamFactoryANSITest]) AT_ANSI_TEST([ZeroDivideANSITest]) AT_ANSI_TEST([ZeroDivideFactoryANSITest]) AT_BANNER([Other packages.]) AT_PACKAGE_TEST([Announcements]) AT_PACKAGE_TEST([Complex]) AT_PACKAGE_TEST([Continuations]) AT_PACKAGE_TEST([DBD-MySQL], [], [$mysqlvars], [test "$enable_mysql_tests" != no]) AT_OPTIONAL_PACKAGE_TEST([DBD-SQLite]) AT_PACKAGE_TEST([DebugTools]) AT_PACKAGE_TEST([DhbNumericalMethods]) AT_PACKAGE_TEST([Digest]) AT_OPTIONAL_PACKAGE_TEST([GDBM]) AT_OPTIONAL_PACKAGE_TEST([Iconv]) AT_PACKAGE_TEST([Magritte]) AT_OPTIONAL_PACKAGE_TEST([ROE]) AT_PACKAGE_TEST([SandstoneDb]) AT_OPTIONAL_PACKAGE_TEST([Seaside-Core]) AT_OPTIONAL_PACKAGE_TEST([Sockets], [AT_XFAIL_IF(:)]) AT_PACKAGE_TEST([Sport]) AT_PACKAGE_TEST([Swazoo]) AT_OPTIONAL_PACKAGE_TEST([XML-XMLParser]) AT_OPTIONAL_PACKAGE_TEST([XML-Expat]) AT_OPTIONAL_PACKAGE_TEST([ZLib]) smalltalk-3.2.5/tests/except.st0000644000175000017500000000413712123404352013431 00000000000000"====================================================================== | | Benchmark for exception handling | | ======================================================================" "====================================================================== | | Copyright (C) 2003, 2007, 2008 Free Software Foundation. | Written by Paolo Bonzini | | This file is part of GNU Smalltalk. | | GNU Smalltalk is free software; you can redistribute it and/or modify it | under the terms of the GNU General Public License as published by the Free | Software Foundation; either version 2, or (at your option) any later version. | | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS | FOR A PARTICULAR PURPOSE. See the GNU General Public License for more | details. | | You should have received a copy of the GNU General Public License along with | GNU Smalltalk; see the file COPYING. If not, write to the Free Software | Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. | ======================================================================" Notification subclass: MyException [ MyException class [ | count | count [ ^count ] increment [ count := count + 1 ] initialize [ count := 0 ] ] ] MyException subclass: LoException [ ] Eval [ LoException initialize ] MyException subclass: HiException [ ] Eval [ HiException initialize ] SmallInteger extend [ someFunction [ ^self hiFunction ] hiFunction [ ^[ self loFunction ] on: HiException do: [ :ex | ex class increment ] ] loFunction [ ^[ self blowup ] on: LoException do: [ :ex | ex class increment ] ] blowup [ ^(self odd ifTrue: [ HiException ] ifFalse: [ LoException ]) signal: self ] ] Eval [ | n | n := Smalltalk arguments isEmpty ifTrue: [ 50000 ] ifFalse: [ 1 max: Smalltalk arguments first asInteger ]. 1 to: n do: [ :each | each someFunction ]. ('Exceptions: HI=%1 / LO=%2' % { HiException count. LoException count }) displayNl ] smalltalk-3.2.5/tests/blocks.ok0000644000175000017500000000354212123404352013400 00000000000000 Execution begins... returned value is BlockClosure new "<0>" Execution begins... returned value is #quem Execution begins... returned value is 'foo' Execution begins... returned value is 'juma' Execution begins... returned value is 17 Execution begins... returned value is nil Execution begins... returned value is nil Execution begins... returned value is BlockClosure new "<0>" Execution begins... returned value is #bar Execution begins... error: return from a dead method context returned value is nil Execution begins... returned value is 'Smalltalk!' Execution begins... returned value is #two Execution begins... returned value is 14 Execution begins... returned value is 12 Execution begins... returned value is 17 Execution begins... returned value is BlockClosure new "<0>" Execution begins... returned value is 5 Execution begins... returned value is 11 Execution begins... returned value is 13 Execution begins... returned value is BlockClosure new "<0>" Execution begins... returned value is 1 Execution begins... returned value is 2 Execution begins... returned value is 55 Execution begins... error: return from a dead method context returned value is nil Execution begins... returned value is nil Execution begins... returned value is nil Execution begins... returned value is nil Execution begins... returned value is 1 Execution begins... returned value is 1 Execution begins... returned value is 1 Execution begins... error: wrong number of arguments returned value is nil Execution begins... returned value is 1 Execution begins... returned value is 1 Execution begins... returned value is 2 Execution begins... returned value is 2 Execution begins... error: wrong number of arguments returned value is nil Execution begins... returned value is 1 Execution begins... returned value is 2 Execution begins... returned value is 3 smalltalk-3.2.5/tests/floatmath.st0000644000175000017500000002375012123404352014122 00000000000000"====================================================================== | | Test floating point operations | | ======================================================================" "====================================================================== | | Copyright (C) 1988, 1989, 1999, 2006, 2007, 2008, 2009 Free Software Foundation. | Written by Steve Byrne | | This file is part of GNU Smalltalk. | | GNU Smalltalk is free software; you can redistribute it and/or modify it | under the terms of the GNU General Public License as published by the Free | Software Foundation; either version 2, or (at your option) any later version. | | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS | FOR A PARTICULAR PURPOSE. See the GNU General Public License for more | details. | | You should have received a copy of the GNU General Public License along with | GNU Smalltalk; see the file COPYING. If not, write to the Free Software | Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. | ======================================================================" Eval [ (1 to: 500000) collect: [ :each | RegressionTesting ifFalse: [ each \\ 1000 = 0 ifTrue: [ each basicPrint. Character nl basicPrint ] ]. -1.0 negated ]. ObjectMemory globalGarbageCollect ] Eval [ 3.1 ] Eval [ 3.45 ] Eval [ 3.0e4 ] Eval [ 3.45e4 ] Eval [ 3.4 + 4.3 ] Eval [ -5.5 - 3.12 ] Eval [ 5.6 < 5.5 ] Eval [ 5.5 < 5.6 ] Eval [ 5.6 > 5.5 ] Eval [ 5.5 > 5.6 ] Eval [ 3.4 <= 3.4 ] Eval [ 3.6 >= 2.5 ] Eval [ 3.12345 = 3.12345 ] Eval [ 4.5 ~= 5.67 ] Eval [ 4.5 * 0.0004 ] Eval [ 4.5 / 0.0004 ] Eval [ 3.14159 truncated ] Eval [ 3.1415926535 fractionPart ] Eval [ 4523.234 exponent ] Eval [ 45.0 timesTwoPower: 4 ] Eval [ 45.0 timesTwoPower: -4 ] Eval [ 1000 asFloat floorLog: 10 ] Eval [ 1024 asFloat reciprocal ceilingLog: 10 ] Eval [ FloatD infinity ] Eval [ FloatD infinity printString ] Eval [ FloatD negativeInfinity ] Eval [ FloatD negativeInfinity printString ] Eval [ FloatD nan ] Eval [ FloatD nan printString ] Eval [ FloatD infinity reciprocal printString ] Eval [ FloatD negativeInfinity reciprocal printString ] Eval [ 0.0 positive ] Eval [ (0.0 * -1) positive ] Eval [ FloatD nan min: FloatD nan ] Eval [ FloatD nan min: 5.0 ] Eval [ 5.0 min: FloatD nan ] Eval [ 5.0 min: 7.0 ] Eval [ 7.0 min: 5.0 ] Eval [ 7.0 min: 7.0 ] Eval [ 0.0 min: 0.0 ] Eval [ 0.0 min: 0.0 * -1 ] Eval [ 0.0 * -1 min: 0.0 ] Eval [ 0.0 * -1 min: 0.0 * -1 ] Eval [ FloatD nan max: FloatD nan ] Eval [ FloatD nan max: 5.0 ] Eval [ 5.0 max: FloatD nan ] Eval [ 5.0 max: 7.0 ] Eval [ 7.0 max: 5.0 ] Eval [ 7.0 max: 7.0 ] Eval [ 0.0 max: 0.0 ] Eval [ 0.0 max: 0.0 * -1 ] Eval [ 0.0 * -1 max: 0.0 ] Eval [ 0.0 * -1 max: 0.0 * -1 ] " ### need more tests" Eval [ (( 0.6 \\ 1) * 10) rounded == ( 6 \\ 10) ] Eval [ (( 0.6 \\ -1) * 10) rounded == ( 6 \\ -10) ] Eval [ ((-0.6 \\ 1) * 10) rounded == (-6 \\ 10) ] Eval [ ((-0.6 \\ -1) * 10) rounded == (-6 \\ -10) ] Eval [ (( 0.4 \\ 1) * 10) rounded == ( 4 \\ 10) ] Eval [ (( 0.4 \\ -1) * 10) rounded == ( 4 \\ -10) ] Eval [ ((-0.4 \\ 1) * 10) rounded == (-4 \\ 10) ] Eval [ ((-0.4 \\ -1) * 10) rounded == (-4 \\ -10) ] Eval [ (1.0e raisedTo: 1 ) class ] Eval [ (1.0d raisedTo: 1 ) class ] Eval [ (1.0q raisedTo: 1 ) class ] Eval [ (1.0e raisedTo: 1.0e) class ] Eval [ (1.0d raisedTo: 1.0e) class ] Eval [ (1.0q raisedTo: 1.0e) class ] Eval [ (1.0e raisedTo: 1.0d) class ] Eval [ (1.0d raisedTo: 1.0d) class ] Eval [ (1.0q raisedTo: 1.0d) class ] Eval [ (1.0e raisedTo: 1.0q) class ] Eval [ (1.0d raisedTo: 1.0q) class ] Eval [ (1.0q raisedTo: 1.0q) class ] " Fun with signed zeros" Eval [ #(( -0.0d -0.0d) (-0.0d 0.0d) (0.0d -0.0d) (0.0d 0.0d)) do: [ :x ||a b| a := x first. b := x last. { a. b. a negated + b. b - a. ((a negated + b) = (b - a)). a + b negated. a - b. ((a + b negated) = (a - b)) } printNl ] ] Eval [ #(( -0.0e -0.0e) (-0.0e 0.0e) (0.0e -0.0e) (0.0e 0.0e)) do: [ :x ||a b| a := x first. b := x last. { a. b. a negated + b. b - a. ((a negated + b) = (b - a)). a + b negated. a - b. ((a + b negated) = (a - b)) } printNl ] ] "This is less strict because it behaves differently on different long double formats." Eval [ #(( -0.0q -0.0q) (0.0q 0.0q)) do: [ :x ||a b| a := x first. b := x last. { a. b. a negated + b. b - a. ((a negated + b) = (b - a)). a + b negated. a - b. ((a + b negated) = (a - b)) } printNl ] ] Eval [ #((-0.0q 0.0q) (0.0q -0.0q)) do: [ :x ||a b| a := x first. b := x last. { a. b. ((b - a) negated = (a - b)). ((a negated + b) = (b - a)). ((a + b negated) = (a - b)) } printNl ] ] "Fun with printing" Float class extend [ test: bytes [ | f | "for historical results this uses little endian, reverse here." f := self fromBytes: bytes reverse. (true->f) printNl. ^f ] ] Eval [ FloatD test: #[0 128 224 55 121 195 65 67] ] Eval [ FloatE test: #[202 27 14 90] ] Eval [ FloatD test: #[0 72 224 37 219 237 69 67] ] Eval [ FloatE test: #[217 110 47 90] ] Eval [ FloatD test: #[0 0 0 0 0 0 244 63] ] Eval [ FloatD test: #[0 0 0 0 0 0 36 64] ] Eval [ FloatD test: #[57 0 44 60 121 196 49 64] ] Eval [ FloatD test: #[123 242 176 80 107 154 191 63] ] Eval [ FloatD test: #[124 242 176 80 107 154 191 63] ] Eval [ FloatD test: #[78 250 91 111 99 53 21 62] ] Eval [ FloatD test: #[79 250 91 111 99 53 21 62] ] Eval [ FloatE test: #[27 171 169 48] ] Eval [ FloatD test: #[191 220 89 240 39 160 234 63] ] Eval [ FloatD test: #[227 220 89 240 39 160 234 63] ] Eval [ FloatD test: #[157 232 59 160 26 192 225 63] ] Eval [ FloatD test: #[148 232 59 160 26 192 225 63] ] Eval [ FloatD test: #[255 255 255 255 255 255 239 63] ] Eval [ FloatD test: #[92 244 249 110 24 220 230 84] ] Eval [ FloatD test: #[236 81 184 30 133 235 34 64] ] Eval [ FloatD test: #[51 51 51 51 51 51 211 63] ] Eval [ FloatD test: #[52 51 51 51 51 51 211 63] ] "Fun reading floats" "The RHS has a 256-bit approximation that is way beyond the precision of real.c's floats." Eval [ FloatQ pi = 3.1415926535897932384626433832795028841971693993751058209749445923078164062862q ] Eval [ FloatD pi = 3.1415926535897932384626433832795028841971693993751058209749445923078164062862d ] Eval [ FloatE pi = 3.1415926535897932384626433832795028841971693993751058209749445923078164062862e ] "Use #predecessor/#succesor to test reading." Eval [ (0.2q0 successor asExactFraction - (1/5)) abs >= (0.2q0 asExactFraction - (1/5)) abs ] Eval [ (0.2q0 predecessor asExactFraction - (1/5)) abs >= (0.2q0 asExactFraction - (1/5)) abs ] Eval [ (0.2q0 successor - (1/5) asFloatQ) abs >= (0.2q0 - (1/5) asFloatQ) abs ] Eval [ (0.2q0 predecessor - (1/5) asFloatQ) abs >= (0.2q0 - (1/5) asFloatQ) abs ] Eval [ (0.137q0 successor asExactFraction - (137/1000)) abs >= (0.137q0 asExactFraction - (137/1000)) abs ] Eval [ (0.137q0 predecessor asExactFraction - (137/1000)) abs >= (0.137q0 asExactFraction - (137/1000)) abs ] Eval [ (0.137q0 successor - (137/1000) asFloatQ) abs >= (0.137q0 - (137/1000) asFloatQ) abs ] Eval [ (0.137q0 predecessor - (137/1000) asFloatQ) abs >= (0.137q0 - (137/1000) asFloatQ) abs ] Eval [ (1.3q0 successor asExactFraction - (13/10)) abs >= (1.3q0 asExactFraction - (13/10)) abs ] Eval [ (1.3q0 predecessor asExactFraction - (13/10)) abs >= (1.3q0 asExactFraction - (13/10)) abs ] Eval [ (1.3q0 successor - (13/10) asFloatQ) abs >= (1.3q0 - (13/10) asFloatQ) abs ] Eval [ (1.3q0 predecessor - (13/10) asFloatQ) abs >= (1.3q0 - (13/10) asFloatQ) abs ] "Fun with rounding" Float class extend [ assert: aBoolean [ aBoolean ifFalse: [ self halt ] ifTrue: [ aBoolean printNl ] ] test [ | p | p := 1 bitShift: self precision - 1. self assert: (self coerce: p+0+(1/4)) asExactFraction = (p+0). self assert: (self coerce: p+0+(1/2)) asExactFraction = (p+0). self assert: (self coerce: p+0+(3/4)) asExactFraction = (p+1). self assert: (self coerce: p+1+(1/4)) asExactFraction = (p+1). self assert: (self coerce: p+1+(1/2)) asExactFraction = (p+2). self assert: (self coerce: p+1+(3/4)) asExactFraction = (p+2). self assert: ((self emin - self precision - 1 to: self emax - 1) allSatisfy: [:i | p := (self coerce: 1) timesTwoPower: i. (self coerce: p asExactFraction) = p]). self assert: ((1 to: 1 + self precision - self emin) allSatisfy: [:i | p := (self coerce: 1) timesTwoPower: i negated. (self coerce: (1 bitShift: i) reciprocal negated) = p negated]). "check for negative zero" p := 1 bitShift: 1 + self precision - self emin. self assert: (self coerce: p reciprocal) positive. self assert: (self coerce: p reciprocal negated) negative. "check for infinity" p := 1 bitShift: self emax + 1. self assert: (self coerce: p) = self infinity. self assert: (self coerce: p negated) = self negativeInfinity. p := 1 bitShift: 1 + self precision - self emin. self assert: (self coerce: p / 3) = self infinity. self assert: (self coerce: p / -3) = self negativeInfinity. "check for non infinity/nan" p := 1 bitShift: self emax + 1. self assert: (self coerce: p / 3) isFinite. self assert: (self coerce: p / -3) isFinite. p := 1 bitShift: 1 + self precision - self emin. self assert: (self coerce: 3 / p) isFinite. self assert: (self coerce: -3 / p) isFinite. "check for rounding bugs" p := (1 bitShift: self precision - 1) + (self coerce: 1.0). self assert: p rounded = p asExactFraction. "Test the case with the carry == 1 in LargeInteger>>#asFloat:. The number is huge so the truncated mantissa is even. If there are other trailing bits behind the carry, as with p+1, the mantissa must be rounded up." p := (1 bitShift: self precision * 2) + (1 bitShift: self precision). self assert: p asFloatD truncated < (p + 1) asFloatD truncated ] ] Eval [ FloatD test ] Eval [ FloatE test ] smalltalk-3.2.5/tests/methcall.ok0000644000175000017500000000007012123404352013705 00000000000000 Execution begins... true false returned value is false smalltalk-3.2.5/tests/geometry.ok0000644000175000017500000000354012123404352013754 00000000000000 Execution begins... 'p1 = '123@456 'p2 = '123@456 returned value is Point new "<0>" Execution begins... '(p x) = '123 '(p y) = '456 'p = '321@456 'p = '321@654 returned value is Point new "<0>" Execution begins... 'A < B = 'true 'A < C = 'false 'A > C = 'false 'B > A = 'true 'A max: B = '175@270 'A min: B = '45@230 returned value is Point new "<0>" Execution begins... 'A + B = '220@530 'A + 175 = '220@405 'A - B = '-130@-70 'D / 50 = '16/5@24/5 'D // 50 = '3@4 'D // C = '3@4 '(A - B) abs = '130@70 '120.5@220.7 rounded = '121@221 'D truncateTo: 50 = '150@200 returned value is Point new "<0>" Execution begins... 'A dist: B = '104.0 'C dotProduct: D = '20000 'C grid: D = '150@250 'E normal * 5 = '-4@3 'C truncatedGrid: D = '150@200 '175@300 transpose = '300@175 returned value is Point new "<0>" Execution begins... '5 lines should be the same: A = 100@100 corner: 200@200' 'A = '100@100 corner: 200@200 'A = '100@100 corner: 200@200 'A = '100@100 corner: 200@200 'A = '100@100 corner: 200@200 'A = '100@100 corner: 200@200 returned value is Rectangle new "<0>" Execution begins... 'A = '100@100 corner: 250@250 'topLeft = '100@100 'top = '100 'rightCenter = '250@175 'bottom = '250 'center = '175@175 'extent = '150@150 'area = '22500 returned value is 22500 Execution begins... 50@250 120@120 corner: 200@200 100@300 corner: 300@400 (120@50 corner: 200@120 50@50 corner: 120@200 ) (100@20 corner: 300@300 20@20 corner: 100@400 300@20 corner: 400@400 ) (120@20 corner: 260@120 120@240 corner: 260@400 20@20 corner: 120@400 260@20 corner: 400@400 ) 90@290 corner: 310@410 110@320 corner: 290@380 100@120 corner: 300@400 returned value is Rectangle new "<0>" Execution begins... false true true returned value is true Execution begins... 100@100 corner: 250@250 200@300 corner: 350@450 400@600 corner: 700@900 100@200 corner: 250@350 returned value is Rectangle new "<0>" smalltalk-3.2.5/tests/cobjects.st0000644000175000017500000001341112123404352013730 00000000000000"====================================================================== | | Test CObject operations | | ======================================================================" "====================================================================== | | Copyright (C) 2002, 2005, 2007, 2008 Free Software Foundation. | Written by Paolo Bonzini | | This file is part of GNU Smalltalk. | | GNU Smalltalk is free software; you can redistribute it and/or modify it | under the terms of the GNU General Public License as published by the Free | Software Foundation; either version 2, or (at your option) any later version. | | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS | FOR A PARTICULAR PURPOSE. See the GNU General Public License for more | details. | | You should have received a copy of the GNU General Public License along with | GNU Smalltalk; see the file COPYING. If not, write to the Free Software | Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. | ======================================================================" Eval [ | ca buf | ca := (CStringType arrayType: 1) new. buf := (CCharType arrayType: 10) new. buf at: 0 put: $a. buf at: 1 put: $s. buf at: 2 put: $d. buf at: 3 put: 0 asCharacter. ca at: 0 put: buf. ^ca at: 0 ] Eval [ | ca | ca := (CStringType arrayType: 1) new. ca at: 0 put: (CString value: 'asd'). ^ca at: 0 ] Eval [ Smalltalk at: #CA put: nil ] Eval [ CA := (CStringType arrayType: 2) new. CA at: 0 put: (CString value: 'asd'). CA at: 1 put: (CString value: 'dsa') ] Eval [ CA at: 0 ] Eval [ CA at: 1 ] Eval [ (CA addressAt: 0) class ] Eval [ (CA addressAt: 0) value ] Eval [ (CA addressAt: 1) value ] Eval [ (CA + 1) class ] Eval [ (CA + 1) at: -1 ] Eval [ (CA + 1) at: 0 ] Eval [ (CA + 1) - CA ] Eval [ Smalltalk at: #CP put: nil ] Eval [ CP := CStringType ptrType new. CP value: CA. CP value at: 0 ] Eval [ CP value at: 1 ] Eval [ (CP value addressAt: 0) class ] Eval [ (CP value addressAt: 0) value ] Eval [ (CP value addressAt: 1) value ] Eval [ (CP value + 1) class ] Eval [ (CP value + 1) at: -1 ] Eval [ (CP value + 1) at: 0 ] Eval [ (CP value + 1) - CA ] Eval [ (CPtrCType elementType: #int) new value ] "test variadic arguments to callouts. note SmallInteger->long." String extend [ printf: args [ ] ] Eval [ 'abc%ld%s%g%c' printf: #(3 'def' 4.0e0 10) ] Eval [ '%s' printf: 'def' ] "error" SmallInteger extend [ testAsync [ "Asynchronous vs. synchronous actually matters only when the function calls back to Smalltalk. But otherwise, we have no coverage of how the asyncCCall pragma is compiled." ] ] Eval [ 3 testAsync ] Object extend [ testCallin: aCallback [ ] testCString: cString [ ] testCObjectPtr: cObject [ ] testLongLong: aLong [ ] ] Eval [ true testCallin: (CCallbackDescriptor for: [ :x | x printNl. 3 ] returning: #int withArgs: #(#string)) ] Eval [ nil testCString: (CString value: 'this is a test') ] Eval [ ^(nil testLongLong: 16r100110012002) printString ] Eval [ cObject := CCharType new. nil testCObjectPtr: cObject. ^cObject asString ] Eval [ CStruct subclass: #StructB. (CStruct subclass: #StructC) declaration: #((#b (#ptr #StructB))). ^StructC new b elementType cObjectType ] Eval [ (CStruct subclass: #StructD) declaration: #((#b (#ptr #{StructB}))). ^StructD new b elementType cObjectType ] "test some GCed CObjects." Eval [ cObject := (CShortType arrayType: 4) gcNew. cObject storage size printNl. cObject at: 1 put: 16r1111. cObject at: 2 put: 16r2222. cObject decr. (cObject at: 2) printNl. (cObject at: 3) printNl. cObject at: 4 put: 16r3333. cObject storage printNl. cObject at: 5 put: 16rDEAD. ] "test partly out of bound accesses" Eval [ cObject := (CShortType arrayType: 4) gcNew. cObject adjPtrBy: 7. cObject at: -4 ] Eval [ cObject := (CShortType arrayType: 4) gcNew. cObject adjPtrBy: 7. cObject at: 0 ] Eval [ cObject := (CShortType arrayType: 4) gcNew. cIntObject := (cObject + 2) castTo: CIntType. cIntObject value: 16r11111111. (cObject at: 2) printNl. cIntObject at: 1 ] Eval [ cObject := CCharType gcNew. nil testCObjectPtr: cObject. ^cObject isAbsolute "must be true" ] CStruct subclass: A [ ] Eval [ cObj := A gcNew. cObj incr. cObj a printNl. cObj a value ] Eval [ cObj := A gcNew. cObj b value: $A. cObj storage printNl ] " Play with CPtrs" Eval [ t := CStringType ptrType. c := t new: 2. c value: (CString value: 'abc'). (c+1) value: (CString value: 'def'). c value value printNl. (c at: 0) value printNl. (c at: 1) value printNl. c ] " Play with conversion for ByteArray" Eval [ c := #(1 2 3) asByteArray. d := c asCData. (d at: 0) printNl. (d at: 1) printNl. (d at: 2) printNl. d free. d free. ] " Plat with conversion for String" Eval [ c := '123' asCData. (c at: 0) printNl. (c at: 1) printNl. (c at: 2) printNl. (c at: 3) printNl. c free. c free. ] " Play with conversion for Boolean" Eval [ c := CBoolean value: true. c value printNl. c free. ] " ### need a lot more!" smalltalk-3.2.5/tests/streams.ok0000644000175000017500000000026012123404352013573 00000000000000 Execution begins... $1 $2 $3 '123' $4 $5 '456' $6 true '456' nil returned value is nil Execution begins... Array UndefinedObject String String $1 Array 2 returned value is 2 smalltalk-3.2.5/tests/arrays.ok0000644000175000017500000000375512123404352013432 00000000000000 Execution begins... returned value is Array new: 3 "<0>" Execution begins... returned value is Array Execution begins... returned value is 3 Execution begins... returned value is Array Execution begins... returned value is #foo Execution begins... returned value is Array new: 3 "<0>" Execution begins... returned value is #bar Execution begins... returned value is 'quem' Execution begins... returned value is 3.40000 Execution begins... returned value is 1 Execution begins... returned value is $C Execution begins... returned value is #barn:yard:owl: Execution begins... returned value is #baz Execution begins... returned value is Array Execution begins... returned value is 1 Execution begins... returned value is 5 Execution begins... returned value is 10 Execution begins... True Symbol False Symbol UndefinedObject Symbol returned value is nil Execution begins... error: Invalid argument -1: argument out of range returned value is nil Execution begins... returned value is ByteArray new: 1 "<0>" Execution begins... returned value is ByteArray new: 1 "<0>" Execution begins... error: Invalid argument 256: argument out of range returned value is nil Execution begins... error: Invalid argument -18446744073709551616: argument out of range returned value is nil Execution begins... error: Invalid argument -1: argument out of range returned value is nil Execution begins... returned value is WordArray new: 1 "<0>" Execution begins... returned value is WordArray new: 1 "<0>" Execution begins... returned value is WordArray new: 1 "<0>" Execution begins... error: Invalid argument 18446744073709551616: argument out of range returned value is nil Execution begins... returned value is '(() )' Execution begins... SortedCollection (8->1 12->1 4->2 7->2 5->3 6->3 9->8 ) returned value is SortedCollection new: 10 "<0>" Execution begins... (1 1 2 3 5 ) (2 3 4 4 5 ) 'aabce' 'bcdde' returned value is 'bcdde' Execution begins... returned value is 'SortedCollection (0 1 2 3 4 5 6 7 8 )' smalltalk-3.2.5/tests/compiler.st0000644000175000017500000002153712130343734013762 00000000000000"====================================================================== | | Regression tests for the compiler | | ======================================================================" "====================================================================== | | Copyright (C) 2003, 2007, 2008, 2009 Free Software Foundation. | Written by Paolo Bonzini | | This file is part of GNU Smalltalk. | | GNU Smalltalk is free software; you can redistribute it and/or modify it | under the terms of the GNU General Public License as published by the Free | Software Foundation; either version 2, or (at your option) any later version. | | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS | FOR A PARTICULAR PURPOSE. See the GNU General Public License for more | details. | | You should have received a copy of the GNU General Public License along with | GNU Smalltalk; see the file COPYING. If not, write to the Free Software | Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. | ======================================================================" Eval [ thisContext currentLineInFile + 0 ] Object subclass: #BugTest instanceVariableNames: 'value ' classVariableNames: '' poolDictionaries: '' category: 'Regression testing'! !Object methodsFor: 'bugs'! a: value ^[ undefVariable ]! ! !BugTest methodsFor: 'bugs'! bugHere "The scope for the above method isn't popped and a bogus error is returned here." value := 42! ! "Here is another one. In this case the temporaries inside the block were not counted correctly and were overwritten by push bytecodes." !String methodsFor: 'matching'! phoneNumber | s attempted | attempted := false. self keysAndValuesDo: [ :k :each | | skip ok ch | ok := false. each = $( ifTrue: [ ok := self size - k >= 13 and: [ (self at: k + 4) = $) ]. skip := 1. ]. each isDigit ifTrue: [ ok := self size - k >= 11. skip := 0. ]. ok := ok and: [ attempted not ]. attempted := skip notNil. ok ifTrue: [ skip + k to: skip + 2 + k do: [ :i | ok := ok and: [ (self at: i) isDigit ] ]. (skip * 2 + k + 4) to: (skip * 2 + k + 6) do: [ :i | ok := ok and: [ (self at: i) isDigit ] ]. (skip * 2 + k + 8) to: (skip * 2 + k + 11) do: [ :i | ok := ok and: [ (self at: i) isDigit ] ]. ch := self at: skip * 2 + k + 7. ok := ok and: [ (ch = $ ) | (ch = $-) ]. ok ifTrue: [ ^{ self copyFrom: k + skip to: k + skip + 2. self copyFrom: skip * 2 + k + 4 to: skip * 2 + k + 6. self copyFrom: skip * 2 + k + 8 to: skip * 2 + k + 11. } ] ]. ]. ^nil ! ! Eval [ '(111) 111-1111' phoneNumber ] Eval [ (Object compile: 'foo [ ^5 ]') methodCategory ] Eval [ a := Undeclared keys size. 1 to: 100 do: [ :i | Object compile: 'a%1 [ ^A%1 ]' % {i} ]. Undeclared keys size - a ] !BugTest class methodsFor: 'bugs'! pragma1 ! pragma2 ! pragma3 ! pragma4 ! ! Eval [ (BugTest class >> #pragma1) attributes size ] Eval [ (BugTest class >> #pragma1) attributes first class ] Eval [ (BugTest class >> #pragma1) attributes first selector ] Eval [ (BugTest class >> #pragma1) attributes first arguments ] Eval [ (BugTest class >> #pragma2) attributes size ] Eval [ (BugTest class >> #pragma2) attributes first class ] Eval [ (BugTest class >> #pragma2) attributes first selector ] Eval [ (BugTest class >> #pragma2) attributes first arguments ] Eval [ (BugTest class >> #pragma3) attributes size ] Eval [ (BugTest class >> #pragma3) attributes first class ] Eval [ (BugTest class >> #pragma3) attributes first selector ] Eval [ (BugTest class >> #pragma3) attributes first arguments ] Eval [ (BugTest class >> #pragma4) attributes size ] "Various errors in the recursive-descent parser" !BugTest class methodsFor: 'bugs'! c ^'No crashes'! a ^#[]! b ^{}! "The lexer crashed on this because it returned a SYMBOL_LITERAL with -123 in the ival. This gives a parse error..." c #-123! c <3 4> ^'foo'! ! "... this does not." Eval [ #(#-123) size ] Eval [ BugTest c ] "Also used to crash." Object subclass: A [ B := C. ] "Compiling a method should not capture the current temporaries dictionary." Eval [ a:=42. Object compile: 'gotcha [ "shouldn''t compile!" ^a ]' ] Eval [ nil gotcha ] "Regression test for a compiler bug. Check that jump threading is performed correctly (or not performed at all) if the threaded jump requires extension bytes and the original one had none." Number extend [ inWords [ | tens part1 part2 | ((self \\ 100) < 20 and: [(self \\ 100) > 10]) ifTrue: [ part1 := ''. ((self \\ 100) = 19) ifTrue: [ part2 := 'nineteen'. ]. ] ifFalse: [ ((self \\ 10) = 0) ifTrue: [ part1 := ''. ]. ((self \\ 10) = 1) ifTrue: [ part1 := 'one'. ]. ((self \\ 10) = 2) ifTrue: [ part1 := 'two'. ]. ((self \\ 10) = 3) ifTrue: [ part1 := 'three'. ]. ((self \\ 10) = 4) ifTrue: [ part1 := 'four'. ]. ((self \\ 10) = 5) ifTrue: [ part1 := 'five'. ]. ((self \\ 10) = 6) ifTrue: [ part1 := 'six'. ]. ((self \\ 10) = 7) ifTrue: [ part1 := 'seven'. ]. ((self \\ 10) = 8) ifTrue: [ part1 := 'eight'. ]. ((self \\ 10) = 9) ifTrue: [ part1 := 'nine'. ]. tens := tens - (tens \\ 10). ((tens \\ 100) = 10) ifTrue: [ part2 := 'ten'. ]. ((tens \\ 100) = 20) ifTrue: [ part2 := 'twenty'. ]. ((tens \\ 100) = 30) ifTrue: [ part2 := 'thirty'. ]. ((tens \\ 100) = 40) ifTrue: [ part2 := 'forty'. ]. ((tens \\ 100) = 50) ifTrue: [ part2 := 'fifty'. ]. ((tens \\ 100) = 60) ifTrue: [ part2 := 'sixty'. ]. ((tens \\ 100) = 70) ifTrue: [ part2 := 'seventy'. ]. ((tens \\ 100) = 80) ifTrue: [ part2 := 'eighty'. ]. ((tens \\ 100) = 90) ifTrue: [ part2 := 'ninety'. ]. ]. ^part2, part1 ] ] "this has a jump of exactly 256 bytes, and was buggy at some point. reduced with delta, so the code does not totally make sense. :-) " Object extend [ buggy: packagesList test: aBoolean ifMissing: aBlock [ | toBeLoaded featuresFound pending allPrereq allFeatures package name | featuresFound := Set withAll: Smalltalk.Features. [pending notEmpty] whileTrue: [ name := pending removeFirst. (featuresFound includes: name) ifFalse: [package := self at: name ifAbsent: [^aBlock value: name]. allPrereq := package prerequisites asSet. allFeatures := package features asSet. (aBoolean and: [package test notNil]) ifTrue: [ allPrereq addAll: package test prerequisites. allFeatures addAll: package test features]. (allPrereq noneSatisfy: [ :each | pending includes: each ]) ifFalse: [ pending addLast: name] ifTrue: [ pending removeAll: allPrereq ifAbsent: [:doesNotMatter | ]. pending removeAll: allFeatures ifAbsent: [:doesNotMatter | ]. allPrereq removeAll: allFeatures ifAbsent: [:doesNotMatter | ]. featuresFound addAll: allFeatures. featuresFound add: name. toBeLoaded addFirst: name. pending addAllLast: allPrereq]]]. ] ] Eval [ 19 inWords ] "test that blocks defined with ##() work properly" Object extend [ block [ ^##([ 'abc' asUppercase ]) ] ] Eval [ nil block value ] "test the limited support for unary minus in literals" Eval [ 2-2 ] Eval [ -2 + 2 ] Eval [ -16r33 + 16r33 ] "Blue Book actually says 16r-33" Eval [ 16r33 + 16r-33 ] "Blue Book actually says 16r-33" Eval [ -12345678901234567890123 + 12345678901234567890123 ] Eval [ -123.0 + 123.0 ] Eval [ -123s3 printString ] "test for errors -- we still fail on -16r-0, but that's insane..." Eval [ Object compile: 'a [ -16r-33 ]' ] Eval [ Object compile: 'a [ -16r-33.0 ]' ] Eval [ Object compile: 'a [ -16r-33s3 ]' ] Eval [ Object compile: 'a [ -16r-12345678901234567890123 ]' ] "test that streams are correctly associated to FileSegments" Eval [ (Object >> #addDependent:) descriptor sourceCode class ] Eval [ 'Object extend [ a [ ^5 ] ]' readStream fileIn. (Object >> #a) descriptor sourceCode class ] "Test scoped method within class block." Object subclass: A [ A class [ A class >> a [] "valid" A >> a [] "invalid" ] ] Eval [A class >> #a] Eval [A >> #a] "Check that lookahead tokens are not discarded after compiling a doit." Eval ['''abc'' printNl ''def'' printNl' readStream fileIn] smalltalk-3.2.5/tests/objdump.st0000644000175000017500000000513512130343734013604 00000000000000"====================================================================== | | Test ObjectDumper operations | | ======================================================================" "====================================================================== | | Copyright (C) 2002, 2007, 2008, 2009 Free Software Foundation. | Written by Paolo Bonzini and Markus Fritsche | | This file is part of GNU Smalltalk. | | GNU Smalltalk is free software; you can redistribute it and/or modify it | under the terms of the GNU General Public License as published by the Free | Software Foundation; either version 2, or (at your option) any later version. | | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS | FOR A PARTICULAR PURPOSE. See the GNU General Public License for more | details. | | You should have received a copy of the GNU General Public License along with | GNU Smalltalk; see the file COPYING. If not, write to the Free Software | Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. | ======================================================================" Eval [ stream := (String new: 1024) readWriteStream. (ObjectDumper on: stream) dump: Array. stream reset. ^(ObjectDumper on: stream) load == Array ] Eval [ stream := (String new: 1024) readWriteStream. (ObjectDumper on: stream) dump: #('asdf' 1 2 $a). stream reset. ^(ObjectDumper on: stream) load = #('asdf' 1 2 $a) ] Eval [ stream := (String new: 1024) readWriteStream. method := Object >> #yourself. (ObjectDumper on: stream) dump: method. stream reset. ^(ObjectDumper on: stream) load == method ] Eval [ stream := (String new: 1024) readWriteStream. array := Array new: 1. array at: 1 put: array. (ObjectDumper on: stream) dump: array. stream reset. secondArray := (ObjectDumper on: stream) load. ^secondArray == (secondArray at: 1) ] Eval [ stream := (String new: 1024) readWriteStream. (ObjectDumper on: stream) dump: Processor. stream reset. ^(ObjectDumper on: stream) load == Processor ] Eval [ stream := (String new: 1024) readWriteStream. (ObjectDumper on: stream) dump: 'asdf'. stream reset. ^(ObjectDumper on: stream) load = 'asdf' ] Eval [ stream := (String new: 1024) writeStream. (ObjectDumper on: stream) dump: #('asdf' 1 2 $a). ^(ObjectDumper on: stream readStream) load = #('asdf' 1 2 $a) ] Eval [ | x y | stream := String new readStream. y := [ (ObjectDumper on: stream) load ] on: SystemExceptions.EndOfStream do: [ :ex | x := true. ex resume: ex defaultAction ]. y printNl. ^x ] smalltalk-3.2.5/tests/prodcons.st0000644000175000017500000000367212123404352013773 00000000000000"====================================================================== | | Producer-consumer benchmark | | ======================================================================" "====================================================================== | | Copyright (C) 2008 Free Software Foundation. | Written by Paolo Bonzini | | This file is part of GNU Smalltalk. | | GNU Smalltalk is free software; you can redistribute it and/or modify it | under the terms of the GNU General Public License as published by the Free | Software Foundation; either version 2, or (at your option) any later version. | | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS | FOR A PARTICULAR PURPOSE. See the GNU General Public License for more | details. | | You should have received a copy of the GNU General Public License along with | GNU Smalltalk; see the file COPYING. If not, write to the Free Software | Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. | ======================================================================" Eval [ n := Smalltalk arguments isEmpty ifTrue: [ 10000 ] ifFalse: [ 1 max: Smalltalk arguments first asInteger ]. mutex := Semaphore forMutualExclusion. empty := Semaphore new. full := Semaphore new. consumed := produced := 0. join := Semaphore new. empty signal. [ | i | i := 0. [ full wait. mutex wait. i := data. mutex signal. empty signal. consumed := consumed + 1. i = n ] whileFalse. join signal. ] fork. [ 1 to: n do: [ :i | empty wait. mutex wait. data := i. mutex signal. full signal. produced := produced + 1. ]. join signal. ] fork. join wait. join wait. ('%1 %2' % { produced. consumed }) displayNl ] smalltalk-3.2.5/tests/ary3.ok0000644000175000017500000000010312123404352012767 00000000000000 Execution begins... 1000 1000000 returned value is '1000 1000000' smalltalk-3.2.5/tests/hash.ok0000644000175000017500000000006112123404352013037 00000000000000 Execution begins... 4999 returned value is 4999 smalltalk-3.2.5/tests/streams.st0000644000175000017500000000440712123404352013617 00000000000000 "====================================================================== | | Regression tests for Streams | | ======================================================================" "====================================================================== | | Copyright (C) 2012 Free Software Foundation. | Written by Holger Hans Peter Freyther. | | This file is part of GNU Smalltalk. | | GNU Smalltalk is free software; you can redistribute it and/or modify it | under the terms of the GNU General Public License as published by the Free | Software Foundation; either version 2, or (at your option) any later version. | | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS | FOR A PARTICULAR PURPOSE. See the GNU General Public License for more | details. | | You should have received a copy of the GNU General Public License along with | GNU Smalltalk; see the file COPYING. If not, write to the Free Software | Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. | ======================================================================" Eval [ | concat streamA streamB | streamA := '123' readStream. streamB := '456' readStream. concat := streamA, streamB. "Should print 123" concat next printNl. concat next printNl. concat next printNl. (concat copyFrom: 0 to: 2) printNl. "Should print 45" concat next printNl. concat next printNl. (concat copyFrom: 3 to: 5) printNl. "Should print 6" concat next printNl. concat atEnd printNl. (concat copyFrom: 3 to: 5) printNl. concat stream printNl. ] Eval [ | concat | "Should print Array" concat := Kernel.ConcatenatedStream new. concat species printNl. "Should print UndefinedObject" concat := Kernel.ConcatenatedStream with: '' readStream. concat species printNl. "Should print String" concat := Kernel.ConcatenatedStream with: ' ' readStream. concat species printNl. "Should print String and then Array" concat := Kernel.ConcatenatedStream with: '1' readStream with: #(2) readStream. concat species printNl. concat next printNl. concat species printNl. concat next printNl. ] smalltalk-3.2.5/tests/lists.ok0000644000175000017500000000006312123404352013254 00000000000000 Execution begins... 10000 returned value is 10000 smalltalk-3.2.5/tests/nestedloop.st0000644000175000017500000000273412123404352014316 00000000000000"====================================================================== | | Benchmark for looping | | ======================================================================" "====================================================================== | | Copyright (C) 2003, 2007, 2008 Free Software Foundation. | Written by Paolo Bonzini | | This file is part of GNU Smalltalk. | | GNU Smalltalk is free software; you can redistribute it and/or modify it | under the terms of the GNU General Public License as published by the Free | Software Foundation; either version 2, or (at your option) any later version. | | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS | FOR A PARTICULAR PURPOSE. See the GNU General Public License for more | details. | | You should have received a copy of the GNU General Public License along with | GNU Smalltalk; see the file COPYING. If not, write to the Free Software | Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. | ======================================================================" Eval [ n := Smalltalk arguments isEmpty ifTrue: [ 4 ] ifFalse: [ 1 max: Smalltalk arguments first asInteger ]. x := 0. n timesRepeat: [ n timesRepeat: [ n timesRepeat: [ n timesRepeat: [ n timesRepeat: [ n timesRepeat: [ x := x + 1 ] ] ] ] ] ]. x displayNl ] smalltalk-3.2.5/tests/mutate.st0000644000175000017500000001107612123404352013440 00000000000000"====================================================================== | | Regression tests for class mutation | | ======================================================================" "====================================================================== | | Copyright (C) 2003, 2007, 2008 Free Software Foundation. | Written by Paolo Bonzini. | | This file is part of GNU Smalltalk. | | GNU Smalltalk is free software; you can redistribute it and/or modify it | under the terms of the GNU General Public License as published by the Free | Software Foundation; either version 2, or (at your option) any later version. | | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS | FOR A PARTICULAR PURPOSE. See the GNU General Public License for more | details. | | You should have received a copy of the GNU General Public License along with | GNU Smalltalk; see the file COPYING. If not, write to the Free Software | Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. | ======================================================================" Object subclass: A [ | var1 | var1 [ ^var1 ] var1: a [ var1 := a ] printOn: aStream [ aStream nextPutAll: self class name; nextPut: $(. self class allInstVarNames keysAndValuesDo: [ :i :each | aStream nextPutAll: each; nextPut: $: ; print: (self instVarAt: i); space ]. aStream nextPut: $) ] ] A subclass: B [ |var2| var2 [ ^var2 ] var2: a [ var2 := a ] ] A class extend [ | instance | instance [ instance isNil ifTrue: [ instance := self new ]. ^instance ] ] Eval [ A instance var1: 1. A instance printNl. B instance var1: 0. B instance var2: 2. B instance printNl. A addInstVarName: #var2. B instance var2 printNl. B instance printNl. A removeInstVarName: #var2. B instance var2 printNl. B instance printNl. "Now make B's var2 point to A's" A addInstVarName: #var2. B removeInstVarName: #var2. B instance var2 printNl. B instance printNl ] "Now, test using #subclass: to create classes." Eval [ Association subclass: #C ] Eval [ C instSize = C allInstVarNames size ] Eval [ (C allInstVarNames -> C sharedPools) printNl ] Eval [ Object subclass: #C instanceVariableNames: 'a' classVariableNames: '' poolDictionaries: 'SystemExceptions' category: 'foo' ] Eval [ C instSize = C allInstVarNames size ] Eval [ (C allInstVarNames -> C sharedPools) printNl ] Eval [ Array subclass: #C ] Eval [ C instSize = C allInstVarNames size ] Eval [ (C allInstVarNames -> C sharedPools) printNl ] Eval [ Association subclass: #C ] Eval [ C instSize = C allInstVarNames size ] Eval [ (C allInstVarNames -> C sharedPools) printNl ] Eval [ Object subclass: #C instanceVariableNames: '' classVariableNames: 'Foo' poolDictionaries: 'SystemExceptions' category: 'foo' ] Eval [ C instSize = C allInstVarNames size ] Eval [ (C classPool keys asArray -> C allInstVarNames -> C sharedPools) printNl ] Eval [ Association subclass: #C ] Eval [ (C classPool keys asArray -> C allInstVarNames -> C sharedPools) printNl ] Eval [ Object variableSubclass: #C instanceVariableNames: '' classVariableNames: 'Foo' poolDictionaries: 'SystemExceptions' category: 'foo' ] Eval [ C instSize = C allInstVarNames size ] Eval [ (C shape -> C classPool keys asArray -> C allInstVarNames -> C sharedPools) printNl ] Eval [ Association subclass: #C ] Eval [ (C shape -> C classPool keys asArray -> C allInstVarNames -> C sharedPools) printNl ] Eval [ C class compile: 'foo [ ^MutationError ]' ] Eval [ C foo == SystemExceptions.MutationError ] "Test mutating the class when the new superclass has additional class-instance variables" CObject subclass: CFoo [ ] CStruct subclass: CFoo [ ] Eval [ CFoo environment printNl ] "Test adding variables with multiple |...| blocks or with extend." Object subclass: Foo [ | a | ] Foo subclass: Bar [ | xyz | ] Foo subclass: Bar [ | b | | c | ] Eval [ Bar allInstVarNames printNl ] Foo extend [ | d | ] Eval [ Bar allInstVarNames printNl ] Eval [ Foo allInstVarNames printNl ] "Test moving to an upper superclass, but preserving instance variables because they are specified in the instanceVariableNames: keyword." Association subclass: Blah [ ] Eval [ | blah | blah := Blah new. blah value: 'abc'. Object subclass: #Blah instanceVariableNames: 'key value' classVariableNames: '' poolDictionaries: '' category: ''. blah instVarAt: 2 ] smalltalk-3.2.5/tests/exceptions.st0000644000175000017500000001315512130343734014326 00000000000000"====================================================================== | | Test the exception handling hackery | | ======================================================================" "====================================================================== | | Written by Paolo Bonzini (original code by Jonathan Carlson) | | This file is part of GNU Smalltalk. | | GNU Smalltalk is free software; you can redistribute it and/or modify it | under the terms of the GNU General Public License as published by the Free | Software Foundation; either version 2, or (at your option) any later version. | | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS | FOR A PARTICULAR PURPOSE. See the GNU General Public License for more | details. | | You should have received a copy of the GNU General Public License along with | GNU Smalltalk; see the file COPYING. If not, write to the Free Software | Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. | ======================================================================" Exception subclass: #TestException! Eval [ [ Transcript cr; show: 'testResume...'. TestException signal. Transcript show: 'passed' ] on: TestException do: [:excp | excp resume ]. Transcript cr ] Eval [ [ Transcript cr; show: 'testReturn...'. TestException signal. Transcript show: ' - failed' ] on: TestException do: [:excp | Transcript show: 'passed if nothing follows on this line'. excp return ]. Transcript cr ] Eval [ [ Transcript cr; show: 'testPass...'. [ TestException signal. Transcript show: ' - failed' ] on: TestException do: [:ex | Transcript show: 'passing...'. ex pass ] ] on: TestException do: [:excp | Transcript show: 'passed if nothing follows on this line'. excp return]. Transcript cr ] Eval [ "Test that passing disables all exception handlers in the #on:do: snippet." Transcript cr; show: 'testPass (2)...'. [[self error: 'abc'] on: Exception do: [ :ex | Transcript show: 'failed' ] on: Error do: [ :ex | Transcript show: 'passing...'. ex pass ]] on: Error do: [ :ex | Transcript show: 'ok' ]. Transcript cr ] Eval [ [ Transcript cr; show: 'testEnsure...'. self error: ' Ignore this error'] ensure: [Transcript show: 'passed'; cr] ] Eval [ Smalltalk at: #Ok put: 0 ] Eval [ [ self error: ' Ignore this error'] ifCurtailed: [ Ok := Ok + 1 ]. Ok := Ok + 2 ] Eval [ Transcript cr; show: 'testIfCurtailed...'. Ok = 1 ifFalse: [ Ok >= 2 ifTrue: [ Transcript show: 'control returned'; cr ]. Ok even ifTrue: [ Transcript show: 'ifCurtailed not executed'; cr ]. ^self ]. Transcript show: 'passed'; cr ] Eval [ | r | Ok := 0. r := [#( 1 2 ) size] ensure: [Ok := Ok + 1]. ^(r = 2) & (Ok = 1) ] Eval [ Ok := 0. [ [#( 1 2 ) siz] ensure: [ Ok := Ok + 1 ]. ] on: MessageNotUnderstood do: [ :mnu | mnu return ]. ^Ok = 1 ] Eval [ Ok := 0. [#( 1 2 ) siz] ensure: [ Ok := Ok + 1 ] ] Eval [ ^Ok = 1 ] Eval [ Ok := 0. [ [Error signal] ensure: [ Ok := Ok + 1 ]. ] on: Error do: [ :error | error return ]. ^Ok = 1 ] Eval [ Ok := 0. [Error signal] ensure: [ Ok := Ok + 1 ] ] Eval [ ^Ok = 1 ] Eval [ | tmp | Ok := 0. [tmp := [Notification signal. Ok = 0] ensure: [ Ok := Ok + 1 ]. ] on: Notification do: [ :notification | notification resume ]. ^tmp ] Eval [ Smalltalk removeKey: #Ok ] "Do some torture testing on #ensure: and #ifCurtailed:" Eval [ [ #block printNl ] ensure: [ #outer printNl ] ] Eval [ [ #block printNl ] ensure: [ ^#outer printNl ] ] Eval [ [ [ #block printNl ] ensure: [ #inner printNl ] ] ensure: [ #outer printNl ] ] Eval [ [ [ #block printNl ] ensure: [ #inner printNl ] ] ensure: [ ^#outer printNl ] ] Eval [ [ [ #block printNl ] ensure: [ ^#inner printNl ] ] ensure: [ #outer printNl ] ] Eval [ [ [ #block printNl ] ensure: [ ^#inner printNl ] ] ensure: [ ^#outer printNl ] ] Eval [ [ #block printNl ] ifCurtailed: [ #outer printNl ] ] Eval [ [ #block printNl ] ifCurtailed: [ ^#outer printNl ] ] Eval [ [ [ #block printNl ] ifCurtailed: [ #inner printNl ] ] ifCurtailed: [ #outer printNl ] ] Eval [ [ [ #block printNl ] ifCurtailed: [ #inner printNl ] ] ifCurtailed: [ ^#outer printNl ] ] Eval [ [ [ #block printNl ] ifCurtailed: [ ^#inner printNl ] ] ifCurtailed: [ #outer printNl ] ] Eval [ [ [ #block printNl ] ifCurtailed: [ ^#inner printNl ] ] ifCurtailed: [ ^#outer printNl ] ] Eval [ [ ^#block printNl ] ifCurtailed: [ #outer printNl ] ] Eval [ [ ^#block printNl ] ifCurtailed: [ ^#outer printNl ] ] Eval [ [ [ ^#block printNl ] ifCurtailed: [ #inner printNl ] ] ifCurtailed: [ #outer printNl ] ] Eval [ [ [ ^#block printNl ] ifCurtailed: [ #inner printNl ] ] ifCurtailed: [ ^#outer printNl ] ] Eval [ [ [ ^#block printNl ] ifCurtailed: [ ^#inner printNl ] ] ifCurtailed: [ #outer printNl ] ] Eval [ [ [ ^#block printNl ] ifCurtailed: [ ^#inner printNl ] ] ifCurtailed: [ ^#outer printNl ] ] "used to go in an infinite loop" Eval [ [ self halt ] on: 1 do: [ :ex | 'blah' printNl ] ] "Test error handling within a process." Eval [ p := [^'test'] fork. [p isReady] whileTrue: [Processor yield]] "Test error handling within a process." Eval [ p := [self error: 'test'] fork. [p isReady] whileTrue: [Processor yield]] "This is invalid, but it should not give a walkback." Eval [ [1 doSomething] on: Error do: [:err | error := err]. error signalingContext ] smalltalk-3.2.5/tests/arrays.st0000644000175000017500000001046012123404352013436 00000000000000"====================================================================== | | Test the array routines | | ======================================================================" "====================================================================== | | Copyright (C) 1988, 1989, 1999, 2007, 2008 Free Software Foundation. | Written by Steve Byrne | | This file is part of GNU Smalltalk. | | GNU Smalltalk is free software; you can redistribute it and/or modify it | under the terms of the GNU General Public License as published by the Free | Software Foundation; either version 2, or (at your option) any later version. | | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS | FOR A PARTICULAR PURPOSE. See the GNU General Public License for more | details. | | You should have received a copy of the GNU General Public License along with | GNU Smalltalk; see the file COPYING. If not, write to the Free Software | Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. | ======================================================================" Object extend [ arrayConstTest1 [ | a | a := #(#foo #bar 'quem'). ^a ] arrayConstTest2 [ | a | a := #(#foo #bar 'quem'). ^a class ] arrayConstTest3 [ | a | a := #(#foo #bar 'quem'). ^a size ] arrayConstTest4 [ | a | a := #(#foo (#a #sub #array) #bar 'quem' 3.4 1 $C #barn:yard:owl: #baz). ^a class ] arrayConstSubscriptTest [ | a | a := #(#foo (#a #sub #array) #bar 'quem' 3.4 1 $C #barn:yard:owl: #baz). ^a at: self ] arrayTrueFalseNilTest [ | a | a := #(true #true false #false nil #nil). a do: [ :each | each class printNl ] ] newArray1 [ | a | a := Array new: 10. ^a class ] newArray2 [ | a | a := Array new: 10. a at: self put: self. ^a at: self ] ] Eval [ nil arrayConstTest1 ] Eval [ nil arrayConstTest2 ] Eval [ nil arrayConstTest3 ] Eval [ nil arrayConstTest4 ] Eval [ 1 arrayConstSubscriptTest ] Eval [ 2 arrayConstSubscriptTest ] Eval [ 3 arrayConstSubscriptTest ] Eval [ 4 arrayConstSubscriptTest ] Eval [ 5 arrayConstSubscriptTest ] Eval [ 6 arrayConstSubscriptTest ] Eval [ 7 arrayConstSubscriptTest ] Eval [ 8 arrayConstSubscriptTest ] Eval [ 9 arrayConstSubscriptTest ] Eval [ nil newArray1 ] Eval [ 1 newArray2 ] Eval [ 5 newArray2 ] Eval [ 10 newArray2 ] Eval [ nil arrayTrueFalseNilTest ] Eval [ ByteArray with: -1 ] Eval [ ByteArray with: 0 ] Eval [ ByteArray with: 255 ] Eval [ ByteArray with: 256 ] Eval [ WordArray with: (-1 bitShift: 64) ] Eval [ WordArray with: -1 ] Eval [ WordArray with: 0 ] Eval [ WordArray with: 255 ] Eval [ WordArray with: 256 ] Eval [ WordArray with: (1 bitShift: 64) ] "-----------------" "used to trigger a failure in the verifier" Eval [ {{}} printString ] "-----------------" "This test used to fail because #removeAtIndex: was not implemented in SortedCollection." Eval [ n4 := 4->2. n5 := 5->3. n6 := 6->3. n7 := 7->2. n8 := 8->1. n9 := 9->8. n10 := 10->8. n12 := 12->1. sc := SortedCollection new: 10. sc sortBlock: [ :a :b | a value < b value or: [ a value = b value and: [ a key <= b key ] ] ]. sc addAll: { n8. n12. n4. n7. n5. n6. n9. n10 }. sc remove: n10. sc remove: n8. sc add: n8. sc printNl ] "--------------" "Test for memmove semantics of #replaceFrom:to:with:startingAt:" Eval [ | a | (a := #(1 2 3 4 5) copy) replaceFrom: 2 to: 4 with: a startingAt: 1. a printNl. (a := #(1 2 3 4 5) copy) replaceFrom: 1 to: 3 with: a startingAt: 2. a printNl. (a := 'abcde' copy) replaceFrom: 2 to: 4 with: a startingAt: 1. a printNl. (a := 'abcde' copy) replaceFrom: 1 to: 3 with: a startingAt: 2. a printNl. ] "--------------" "This was wrong due to an off-by-one error in SortedCollection>>#percolateUp" Eval [ it := SortedCollection new. it addAll: #(1 2 3 7 9 10 11). it removeLast. it add: 6. it add: 8. it removeLast. "<<< the bug happened here, the heap was inconsistent!" it add: 5. it add: 0. it removeLast. it add: 4. it printString. ] smalltalk-3.2.5/tests/strings.ok0000644000175000017500000000662612123404352013622 00000000000000 Execution begins... returned value is 'foo' Execution begins... returned value is 'foo on you' Execution begins... returned value is 'foo on multiple line string you' Execution begins... returned value is 'test embedded quote marks, can't I do this?' Execution begins... returned value is $B Execution begins... returned value is $Q Execution begins... returned value is 'Quem' Execution begins... $a->nil $b->nil $c->nil returned value is ReadStream new "<0>" Execution begins... 'should be false 'false 'should be false 'false 'should be true 'true 'should be true 'true 'should be true 'true 'should be true 'true 'should be true 'true 'should be true 'true 'should be true 'true 'should be true 'true 'should be true 'true 'should be true 'true 'should be true 'true 'should be false 'false 'should be false 'false returned value is false Execution begins... returned value is '(810)123-4567' Execution begins... returned value is '543-123-4567' Execution begins... returned value is '496-44-9294' Execution begins... returned value is '$123.45' Execution begins... returned value is 'Publication number SR28-5959-1' Execution begins... returned value is 'Card Number 3883 500284 5643 Expires 10/97' Execution begins... returned value is '543- - ' Execution begins... returned value is ' - - ' Execution begins... returned value is '' Execution begins... returned value is 'xaxbxcx' Execution begins... returned value is 'fx' Execution begins... returned value is 'fx' Execution begins... returned value is 'fx' Execution begins... returned value is 'xbx' Execution begins... returned value is 'xbx' Execution begins... returned value is 'xbx' Execution begins... returned value is 'xbxcx' Execution begins... returned value is 'xbxcx' Execution begins... returned value is '('abc' 'def' )' Execution begins... returned value is '('' 'abc' 'def' )' Execution begins... returned value is '('a' 'b' 'c' )' Execution begins... returned value is '('a' )' Execution begins... returned value is '('a' )' Execution begins... returned value is '('a' )' Execution begins... returned value is 4 Execution begins... returned value is 4 Execution begins... returned value is 4 Execution begins... returned value is 4 Execution begins... returned value is 4 Execution begins... returned value is 4 Execution begins... returned value is 1 Execution begins... returned value is 1 Execution begins... returned value is 10 Execution begins... returned value is 10.0000 Execution begins... returned value is 10.0000 Execution begins... returned value is 100.000 Execution begins... returned value is 100.000 Execution begins... returned value is 1.00000 Execution begins... returned value is 1.00000 Execution begins... returned value is 1.00000 Execution begins... returned value is 0.100000 Execution begins... returned value is 1.00000 Execution begins... returned value is 10.0000 Execution begins... returned value is $<16rFFFD> Execution begins... returned value is 'abcdef' Execution begins... returned value is 'abctrue' Execution begins... returned value is 'abcdef' Execution begins... returned value is 'abcghi' Execution begins... returned value is 'abcdef' Execution begins... returned value is 'abctrue' Execution begins... returned value is 'abcdef' Execution begins... returned value is 'abcghi' Execution begins... returned value is 'abc%1' Execution begins... returned value is 'abc%def' smalltalk-3.2.5/tests/chars.ok0000644000175000017500000000476012123404352013226 00000000000000 Execution begins... returned value is $A Execution begins... returned value is $b Execution begins... returned value is $$ Execution begins... returned value is $! Execution begins... returned value is $ Execution begins... returned value is true Execution begins... returned value is true Execution begins... #isVowel ________________________________________________________________ _x___x___x_____x_____x___________x___x___x_____x_____x__________ ________________________________________________________________ ________________________________________________________________ #isLetter ________________________________________________________________ _xxxxxxxxxxxxxxxxxxxxxxxxxx______xxxxxxxxxxxxxxxxxxxxxxxxxx_____ ________________________________________________________________ ________________________________________________________________ #isUppercase ________________________________________________________________ _xxxxxxxxxxxxxxxxxxxxxxxxxx_____________________________________ ________________________________________________________________ ________________________________________________________________ #isLowercase ________________________________________________________________ _________________________________xxxxxxxxxxxxxxxxxxxxxxxxxx_____ ________________________________________________________________ ________________________________________________________________ #isAlphaNumeric ________________________________________________xxxxxxxxxx______ _xxxxxxxxxxxxxxxxxxxxxxxxxx______xxxxxxxxxxxxxxxxxxxxxxxxxx_____ ________________________________________________________________ ________________________________________________________________ #isDigit ________________________________________________xxxxxxxxxx______ ________________________________________________________________ ________________________________________________________________ ________________________________________________________________ #isSeparator _________xx_xx__________________x_______________________________ ________________________________________________________________ ________________________________________________________________ ________________________________________________________________ returned value is Array new: 7 "<0>" Execution begins... #asUppercase !"#$%&'()*+,-./0123456789:;<=>?@ABCDEFGHIJKLMNO PQRSTUVWXYZ[\]^_`ABCDEFGHIJKLMNOPQRSTUVWXYZ{|}~ #asLowercase !"#$%&'()*+,-./0123456789:;<=>?@abcdefghijklmno pqrstuvwxyz[\]^_`abcdefghijklmnopqrstuvwxyz{|}~ returned value is Array new: 2 "<0>" smalltalk-3.2.5/tests/intmath.ok0000644000175000017500000000744712123404352013577 00000000000000 Execution begins... returned value is 3 Execution begins... returned value is -3 Execution begins... returned value is 10 Execution begins... returned value is 255 Execution begins... returned value is 254 Execution begins... returned value is 7 Execution begins... returned value is -1 Execution begins... returned value is true Execution begins... returned value is false Execution begins... returned value is false Execution begins... returned value is true Execution begins... returned value is false Execution begins... returned value is false Execution begins... returned value is true Execution begins... returned value is true Execution begins... returned value is false Execution begins... returned value is true Execution begins... returned value is false Execution begins... returned value is 12 Execution begins... returned value is 4 Execution begins... returned value is 2 Execution begins... returned value is 4 Execution begins... returned value is 2 Execution begins... returned value is -3 Execution begins... returned value is -3 Execution begins... returned value is 0 Execution begins... returned value is 2 Execution begins... returned value is 0 Execution begins... returned value is -2 Execution begins... returned value is 3 Execution begins... returned value is -3 Execution begins... returned value is '1000000000000000000000000000000000000' Execution begins... returned value is 100 Execution begins... returned value is '93326215443944152681699238856266700490715968264381621468592963895217599993229915608941463976156518286253697920827223758251185210916864000000000000000000000000' Execution begins... returned value is true Execution begins... returned value is true Execution begins... returned value is true Execution begins... returned value is true Execution begins... returned value is false Execution begins... returned value is true Execution begins... returned value is false Execution begins... returned value is true Execution begins... returned value is false Execution begins... returned value is false Execution begins... returned value is false Execution begins... returned value is true Execution begins... returned value is true Execution begins... returned value is false Execution begins... returned value is true Execution begins... returned value is true Execution begins... returned value is false Execution begins... returned value is false Execution begins... returned value is true Execution begins... returned value is false Execution begins... returned value is true Execution begins... returned value is false Execution begins... returned value is true Execution begins... returned value is false Execution begins... returned value is false Execution begins... returned value is false Execution begins... returned value is true Execution begins... returned value is true Execution begins... returned value is false Execution begins... returned value is true Execution begins... returned value is true Execution begins... returned value is false Execution begins... returned value is false Execution begins... returned value is true Execution begins... true true returned value is true Execution begins... returned value is true Execution begins... returned value is true Execution begins... returned value is true Execution begins... returned value is true Execution begins... 'Shift -1 left then right and test for -1' 'Shift 1 left then right and test for 1' 'And a single bit with -1 and test for same value' 'Verify that (n bitAnd: n negated) = n' 'Verify that (n + n complemented) = -1' 'Verify that n negated = (n complemented +1)' 'LargeInteger bit logic tests passed' returned value is true Execution begins... 64212742967590157 1216451004088320000 returned value is Fraction new "<0>" Execution begins... 694 694 returned value is 314159 smalltalk-3.2.5/tests/testsuite0000755000175000017500000073640012130455703013561 00000000000000#! /bin/sh # Generated from testsuite.at by GNU Autoconf 2.69. # # Copyright (C) 2009-2012 Free Software Foundation, Inc. # # This test suite is free software; the Free Software Foundation gives # unlimited permission to copy, distribute and modify it. ## -------------------- ## ## M4sh Initialization. ## ## -------------------- ## # Be more Bourne compatible DUALCASE=1; export DUALCASE # for MKS sh if test -n "${ZSH_VERSION+set}" && (emulate sh) >/dev/null 2>&1; then : emulate sh NULLCMD=: # Pre-4.2 versions of Zsh do word splitting on ${1+"$@"}, which # is contrary to our usage. Disable this feature. alias -g '${1+"$@"}'='"$@"' setopt NO_GLOB_SUBST else case `(set -o) 2>/dev/null` in #( *posix*) : set -o posix ;; #( *) : ;; esac fi as_nl=' ' export as_nl # Printing a long string crashes Solaris 7 /usr/bin/printf. as_echo='\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\' as_echo=$as_echo$as_echo$as_echo$as_echo$as_echo as_echo=$as_echo$as_echo$as_echo$as_echo$as_echo$as_echo # Prefer a ksh shell builtin over an external printf program on Solaris, # but without wasting forks for bash or zsh. if test -z "$BASH_VERSION$ZSH_VERSION" \ && (test "X`print -r -- $as_echo`" = "X$as_echo") 2>/dev/null; then as_echo='print -r --' as_echo_n='print -rn --' elif (test "X`printf %s $as_echo`" = "X$as_echo") 2>/dev/null; then as_echo='printf %s\n' as_echo_n='printf %s' else if test "X`(/usr/ucb/echo -n -n $as_echo) 2>/dev/null`" = "X-n $as_echo"; then as_echo_body='eval /usr/ucb/echo -n "$1$as_nl"' as_echo_n='/usr/ucb/echo -n' else as_echo_body='eval expr "X$1" : "X\\(.*\\)"' as_echo_n_body='eval arg=$1; case $arg in #( *"$as_nl"*) expr "X$arg" : "X\\(.*\\)$as_nl"; arg=`expr "X$arg" : ".*$as_nl\\(.*\\)"`;; esac; expr "X$arg" : "X\\(.*\\)" | tr -d "$as_nl" ' export as_echo_n_body as_echo_n='sh -c $as_echo_n_body as_echo' fi export as_echo_body as_echo='sh -c $as_echo_body as_echo' fi # The user is always right. if test "${PATH_SEPARATOR+set}" != set; then PATH_SEPARATOR=: (PATH='/bin;/bin'; FPATH=$PATH; sh -c :) >/dev/null 2>&1 && { (PATH='/bin:/bin'; FPATH=$PATH; sh -c :) >/dev/null 2>&1 || PATH_SEPARATOR=';' } fi # IFS # We need space, tab and new line, in precisely that order. Quoting is # there to prevent editors from complaining about space-tab. # (If _AS_PATH_WALK were called with IFS unset, it would disable word # splitting by setting IFS to empty value.) IFS=" "" $as_nl" # Find who we are. Look in the path if we contain no directory separator. as_myself= case $0 in #(( *[\\/]* ) as_myself=$0 ;; *) as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. test -r "$as_dir/$0" && as_myself=$as_dir/$0 && break done IFS=$as_save_IFS ;; esac # We did not find ourselves, most probably we were run as `sh COMMAND' # in which case we are not to be found in the path. if test "x$as_myself" = x; then as_myself=$0 fi if test ! -f "$as_myself"; then $as_echo "$as_myself: error: cannot find myself; rerun with an absolute file name" >&2 exit 1 fi # Unset variables that we do not need and which cause bugs (e.g. in # pre-3.0 UWIN ksh). But do not cause bugs in bash 2.01; the "|| exit 1" # suppresses any "Segmentation fault" message there. '((' could # trigger a bug in pdksh 5.2.14. for as_var in BASH_ENV ENV MAIL MAILPATH do eval test x\${$as_var+set} = xset \ && ( (unset $as_var) || exit 1) >/dev/null 2>&1 && unset $as_var || : done PS1='$ ' PS2='> ' PS4='+ ' # NLS nuisances. LC_ALL=C export LC_ALL LANGUAGE=C export LANGUAGE # CDPATH. (unset CDPATH) >/dev/null 2>&1 && unset CDPATH if test "x$CONFIG_SHELL" = x; then as_bourne_compatible="if test -n \"\${ZSH_VERSION+set}\" && (emulate sh) >/dev/null 2>&1; then : emulate sh NULLCMD=: # Pre-4.2 versions of Zsh do word splitting on \${1+\"\$@\"}, which # is contrary to our usage. Disable this feature. alias -g '\${1+\"\$@\"}'='\"\$@\"' setopt NO_GLOB_SUBST else case \`(set -o) 2>/dev/null\` in #( *posix*) : set -o posix ;; #( *) : ;; esac fi " as_required="as_fn_return () { (exit \$1); } as_fn_success () { as_fn_return 0; } as_fn_failure () { as_fn_return 1; } as_fn_ret_success () { return 0; } as_fn_ret_failure () { return 1; } exitcode=0 as_fn_success || { exitcode=1; echo as_fn_success failed.; } as_fn_failure && { exitcode=1; echo as_fn_failure succeeded.; } as_fn_ret_success || { exitcode=1; echo as_fn_ret_success failed.; } as_fn_ret_failure && { exitcode=1; echo as_fn_ret_failure succeeded.; } if ( set x; as_fn_ret_success y && test x = \"\$1\" ); then : else exitcode=1; echo positional parameters were not saved. fi test x\$exitcode = x0 || exit 1 test -x / || exit 1" as_suggested=" as_lineno_1=";as_suggested=$as_suggested$LINENO;as_suggested=$as_suggested" as_lineno_1a=\$LINENO as_lineno_2=";as_suggested=$as_suggested$LINENO;as_suggested=$as_suggested" as_lineno_2a=\$LINENO eval 'test \"x\$as_lineno_1'\$as_run'\" != \"x\$as_lineno_2'\$as_run'\" && test \"x\`expr \$as_lineno_1'\$as_run' + 1\`\" = \"x\$as_lineno_2'\$as_run'\"' || exit 1 test \$(( 1 + 1 )) = 2 || exit 1" if (eval "$as_required") 2>/dev/null; then : as_have_required=yes else as_have_required=no fi if test x$as_have_required = xyes && (eval "$as_suggested") 2>/dev/null; then : else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR as_found=false for as_dir in /bin$PATH_SEPARATOR/usr/bin$PATH_SEPARATOR$PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. as_found=: case $as_dir in #( /*) for as_base in sh bash ksh sh5; do # Try only shells that exist, to save several forks. as_shell=$as_dir/$as_base if { test -f "$as_shell" || test -f "$as_shell.exe"; } && { $as_echo "$as_bourne_compatible""$as_required" | as_run=a "$as_shell"; } 2>/dev/null; then : CONFIG_SHELL=$as_shell as_have_required=yes if { $as_echo "$as_bourne_compatible""$as_suggested" | as_run=a "$as_shell"; } 2>/dev/null; then : break 2 fi fi done;; esac as_found=false done $as_found || { if { test -f "$SHELL" || test -f "$SHELL.exe"; } && { $as_echo "$as_bourne_compatible""$as_required" | as_run=a "$SHELL"; } 2>/dev/null; then : CONFIG_SHELL=$SHELL as_have_required=yes fi; } IFS=$as_save_IFS if test "x$CONFIG_SHELL" != x; then : export CONFIG_SHELL # We cannot yet assume a decent shell, so we have to provide a # neutralization value for shells without unset; and this also # works around shells that cannot unset nonexistent variables. # Preserve -v and -x to the replacement shell. BASH_ENV=/dev/null ENV=/dev/null (unset BASH_ENV) >/dev/null 2>&1 && unset BASH_ENV ENV case $- in # (((( *v*x* | *x*v* ) as_opts=-vx ;; *v* ) as_opts=-v ;; *x* ) as_opts=-x ;; * ) as_opts= ;; esac exec $CONFIG_SHELL $as_opts "$as_myself" ${1+"$@"} # Admittedly, this is quite paranoid, since all the known shells bail # out after a failed `exec'. $as_echo "$0: could not re-execute with $CONFIG_SHELL" >&2 exit 255 fi if test x$as_have_required = xno; then : $as_echo "$0: This script requires a shell more modern than all" $as_echo "$0: the shells that I found on your system." if test x${ZSH_VERSION+set} = xset ; then $as_echo "$0: In particular, zsh $ZSH_VERSION has bugs and should" $as_echo "$0: be upgraded to zsh 4.3.4 or later." else $as_echo "$0: Please tell bug-autoconf@gnu.org about your system, $0: including any error possibly output before this $0: message. Then install a modern shell, or manually run $0: the script under such a shell if you do have one." fi exit 1 fi fi fi SHELL=${CONFIG_SHELL-/bin/sh} export SHELL # Unset more variables known to interfere with behavior of common tools. CLICOLOR_FORCE= GREP_OPTIONS= unset CLICOLOR_FORCE GREP_OPTIONS ## --------------------- ## ## M4sh Shell Functions. ## ## --------------------- ## # as_fn_unset VAR # --------------- # Portably unset VAR. as_fn_unset () { { eval $1=; unset $1;} } as_unset=as_fn_unset # as_fn_set_status STATUS # ----------------------- # Set $? to STATUS, without forking. as_fn_set_status () { return $1 } # as_fn_set_status # as_fn_exit STATUS # ----------------- # Exit the shell with STATUS, even in a "trap 0" or "set -e" context. as_fn_exit () { set +e as_fn_set_status $1 exit $1 } # as_fn_exit # as_fn_mkdir_p # ------------- # Create "$as_dir" as a directory, including parents if necessary. as_fn_mkdir_p () { case $as_dir in #( -*) as_dir=./$as_dir;; esac test -d "$as_dir" || eval $as_mkdir_p || { as_dirs= while :; do case $as_dir in #( *\'*) as_qdir=`$as_echo "$as_dir" | sed "s/'/'\\\\\\\\''/g"`;; #'( *) as_qdir=$as_dir;; esac as_dirs="'$as_qdir' $as_dirs" as_dir=`$as_dirname -- "$as_dir" || $as_expr X"$as_dir" : 'X\(.*[^/]\)//*[^/][^/]*/*$' \| \ X"$as_dir" : 'X\(//\)[^/]' \| \ X"$as_dir" : 'X\(//\)$' \| \ X"$as_dir" : 'X\(/\)' \| . 2>/dev/null || $as_echo X"$as_dir" | sed '/^X\(.*[^/]\)\/\/*[^/][^/]*\/*$/{ s//\1/ q } /^X\(\/\/\)[^/].*/{ s//\1/ q } /^X\(\/\/\)$/{ s//\1/ q } /^X\(\/\).*/{ s//\1/ q } s/.*/./; q'` test -d "$as_dir" && break done test -z "$as_dirs" || eval "mkdir $as_dirs" } || test -d "$as_dir" || as_fn_error $? "cannot create directory $as_dir" } # as_fn_mkdir_p # as_fn_executable_p FILE # ----------------------- # Test if FILE is an executable regular file. as_fn_executable_p () { test -f "$1" && test -x "$1" } # as_fn_executable_p # as_fn_append VAR VALUE # ---------------------- # Append the text in VALUE to the end of the definition contained in VAR. Take # advantage of any shell optimizations that allow amortized linear growth over # repeated appends, instead of the typical quadratic growth present in naive # implementations. if (eval "as_var=1; as_var+=2; test x\$as_var = x12") 2>/dev/null; then : eval 'as_fn_append () { eval $1+=\$2 }' else as_fn_append () { eval $1=\$$1\$2 } fi # as_fn_append # as_fn_arith ARG... # ------------------ # Perform arithmetic evaluation on the ARGs, and store the result in the # global $as_val. Take advantage of shells that can avoid forks. The arguments # must be portable across $(()) and expr. if (eval "test \$(( 1 + 1 )) = 2") 2>/dev/null; then : eval 'as_fn_arith () { as_val=$(( $* )) }' else as_fn_arith () { as_val=`expr "$@" || test $? -eq 1` } fi # as_fn_arith # as_fn_error STATUS ERROR [LINENO LOG_FD] # ---------------------------------------- # Output "`basename $0`: error: ERROR" to stderr. If LINENO and LOG_FD are # provided, also output the error to LOG_FD, referencing LINENO. Then exit the # script with STATUS, using 1 if that was 0. as_fn_error () { as_status=$1; test $as_status -eq 0 && as_status=1 if test "$4"; then as_lineno=${as_lineno-"$3"} as_lineno_stack=as_lineno_stack=$as_lineno_stack $as_echo "$as_me:${as_lineno-$LINENO}: error: $2" >&$4 fi $as_echo "$as_me: error: $2" >&2 as_fn_exit $as_status } # as_fn_error if expr a : '\(a\)' >/dev/null 2>&1 && test "X`expr 00001 : '.*\(...\)'`" = X001; then as_expr=expr else as_expr=false fi if (basename -- /) >/dev/null 2>&1 && test "X`basename -- / 2>&1`" = "X/"; then as_basename=basename else as_basename=false fi as_me=`$as_basename -- "$0" || $as_expr X/"$0" : '.*/\([^/][^/]*\)/*$' \| \ X"$0" : 'X\(//\)$' \| \ X"$0" : 'X\(/\)' \| . 2>/dev/null || $as_echo X/"$0" | sed '/^.*\/\([^/][^/]*\)\/*$/{ s//\1/ q } /^X\/\(\/\/\)$/{ s//\1/ q } /^X\/\(\/\).*/{ s//\1/ q } s/.*/./; q'` if (as_dir=`dirname -- /` && test "X$as_dir" = X/) >/dev/null 2>&1; then as_dirname=dirname else as_dirname=false fi # Avoid depending upon Character Ranges. as_cr_letters='abcdefghijklmnopqrstuvwxyz' as_cr_LETTERS='ABCDEFGHIJKLMNOPQRSTUVWXYZ' as_cr_Letters=$as_cr_letters$as_cr_LETTERS as_cr_digits='0123456789' as_cr_alnum=$as_cr_Letters$as_cr_digits as_lineno_1=$LINENO as_lineno_1a=$LINENO as_lineno_2=$LINENO as_lineno_2a=$LINENO eval 'test "x$as_lineno_1'$as_run'" != "x$as_lineno_2'$as_run'" && test "x`expr $as_lineno_1'$as_run' + 1`" = "x$as_lineno_2'$as_run'"' || { # Blame Lee E. McMahon (1931-1989) for sed's syntax. :-) sed -n ' p /[$]LINENO/= ' <$as_myself | sed ' s/[$]LINENO.*/&-/ t lineno b :lineno N :loop s/[$]LINENO\([^'$as_cr_alnum'_].*\n\)\(.*\)/\2\1\2/ t loop s/-\n.*// ' >$as_me.lineno && chmod +x "$as_me.lineno" || { $as_echo "$as_me: error: cannot create $as_me.lineno; rerun with a POSIX shell" >&2; as_fn_exit 1; } # If we had to re-execute with $CONFIG_SHELL, we're ensured to have # already done that, so ensure we don't try to do so again and fall # in an infinite loop. This has already happened in practice. _as_can_reexec=no; export _as_can_reexec # Don't try to exec as it changes $[0], causing all sort of problems # (the dirname of $[0] is not the place where we might find the # original and so on. Autoconf is especially sensitive to this). . "./$as_me.lineno" # Exit status is that of the last command. exit } ECHO_C= ECHO_N= ECHO_T= case `echo -n x` in #((((( -n*) case `echo 'xy\c'` in *c*) ECHO_T=' ';; # ECHO_T is single tab character. xy) ECHO_C='\c';; *) echo `echo ksh88 bug on AIX 6.1` > /dev/null ECHO_T=' ';; esac;; *) ECHO_N='-n';; esac rm -f conf$$ conf$$.exe conf$$.file if test -d conf$$.dir; then rm -f conf$$.dir/conf$$.file else rm -f conf$$.dir mkdir conf$$.dir 2>/dev/null fi if (echo >conf$$.file) 2>/dev/null; then if ln -s conf$$.file conf$$ 2>/dev/null; then as_ln_s='ln -s' # ... but there are two gotchas: # 1) On MSYS, both `ln -s file dir' and `ln file dir' fail. # 2) DJGPP < 2.04 has no symlinks; `ln -s' creates a wrapper executable. # In both cases, we have to default to `cp -pR'. ln -s conf$$.file conf$$.dir 2>/dev/null && test ! -f conf$$.exe || as_ln_s='cp -pR' elif ln conf$$.file conf$$ 2>/dev/null; then as_ln_s=ln else as_ln_s='cp -pR' fi else as_ln_s='cp -pR' fi rm -f conf$$ conf$$.exe conf$$.dir/conf$$.file conf$$.file rmdir conf$$.dir 2>/dev/null if mkdir -p . 2>/dev/null; then as_mkdir_p='mkdir -p "$as_dir"' else test -d ./-p && rmdir ./-p as_mkdir_p=false fi as_test_x='test -x' as_executable_p=as_fn_executable_p # Sed expression to map a string onto a valid CPP name. as_tr_cpp="eval sed 'y%*$as_cr_letters%P$as_cr_LETTERS%;s%[^_$as_cr_alnum]%_%g'" # Sed expression to map a string onto a valid variable name. as_tr_sh="eval sed 'y%*+%pp%;s%[^_$as_cr_alnum]%_%g'" SHELL=${CONFIG_SHELL-/bin/sh} # How were we run? at_cli_args="$@" # Not all shells have the 'times' builtin; the subshell is needed to make # sure we discard the 'times: not found' message from the shell. at_times_p=false (times) >/dev/null 2>&1 && at_times_p=: # CLI Arguments to pass to the debugging scripts. at_debug_args= # -e sets to true at_errexit_p=false # Shall we be verbose? ':' means no, empty means yes. at_verbose=: at_quiet= # Running several jobs in parallel, 0 means as many as test groups. at_jobs=1 at_traceon=: at_trace_echo=: at_check_filter_trace=: # Shall we keep the debug scripts? Must be `:' when the suite is # run by a debug script, so that the script doesn't remove itself. at_debug_p=false # Display help message? at_help_p=false # Display the version message? at_version_p=false # List test groups? at_list_p=false # --clean at_clean=false # Test groups to run at_groups= # Whether to rerun failed tests. at_recheck= # Whether a write failure occurred at_write_fail=0 # The directory we run the suite in. Default to . if no -C option. at_dir=`pwd` # An absolute reference to this testsuite script. case $as_myself in [\\/]* | ?:[\\/]* ) at_myself=$as_myself ;; * ) at_myself=$at_dir/$as_myself ;; esac # Whether -C is in effect. at_change_dir=false # Whether to enable colored test results. at_color=no # List of the tested programs. at_tested='gst' # As many question marks as there are digits in the last test group number. # Used to normalize the test group numbers so that `ls' lists them in # numerical order. at_format='???' # Description of all the test groups. at_help_all="1;testsuite.at:27;arrays.st;base; 2;testsuite.at:28;classes.st;base; 3;testsuite.at:29;blocks.st;base; 4;testsuite.at:30;sets.st;base; 5;testsuite.at:31;processes.st;base; 6;testsuite.at:32;exceptions.st;base; 7;testsuite.at:33;intmath.st;base; 8;testsuite.at:34;floatmath.st;base; 9;testsuite.at:39;dates.st;base; 10;testsuite.at:40;objects.st;base; 11;testsuite.at:41;strings.st;base; 12;testsuite.at:42;chars.st;base; 13;testsuite.at:43;objdump.st;base; 14;testsuite.at:44;delays.st;base; 15;testsuite.at:45;geometry.st;base; 16;testsuite.at:46;cobjects.st;base; 17;testsuite.at:47;compiler.st;base; 18;testsuite.at:48;fileext.st;base; 19;testsuite.at:49;mutate.st;base; 20;testsuite.at:50;untrusted.st;base; 21;testsuite.at:51;getopt.st;base; 22;testsuite.at:52;quit.st;base; 23;testsuite.at:53;pools.st;base; 24;testsuite.at:54;shape.st;base; 25;testsuite.at:55;streams.st;base; 26;testsuite.at:58;ackermann.st;base; 27;testsuite.at:59;ary3.st;base; 28;testsuite.at:60;except.st;base; 29;testsuite.at:61;fibo.st;base; 30;testsuite.at:62;hash.st;base; 31;testsuite.at:63;hash2.st;base; 32;testsuite.at:64;heapsort.st;base; 33;testsuite.at:65;lists.st;base; 34;testsuite.at:66;lists1.st;base; 35;testsuite.at:67;lists2.st;base; 36;testsuite.at:68;matrix.st;base; 37;testsuite.at:69;methcall.st;base; 38;testsuite.at:70;nestedloop.st;base; 39;testsuite.at:71;objinst.st;base; 40;testsuite.at:72;prodcons.st;base; 41;testsuite.at:73;random-bench.st;base; 42;testsuite.at:74;sieve.st;base; 43;testsuite.at:75;strcat.st;base; 44;testsuite.at:76;stcompiler.st;base; 45;testsuite.at:79;SUnit;sunit; 46;testsuite.at:80;Parser;parser sunit; 47;testsuite.at:83;ArrayANSITest;ansi sunit; 48;testsuite.at:84;ArrayFactoryANSITest;ansi sunit; 49;testsuite.at:85;BagANSITest;ansi sunit; 50;testsuite.at:86;BagFactoryANSITest;ansi sunit; 51;testsuite.at:87;BooleanANSITest;ansi sunit; 52;testsuite.at:88;ByteArrayANSITest;ansi sunit; 53;testsuite.at:89;ByteArrayFactoryANSITest;ansi sunit; 54;testsuite.at:90;CharacterANSITest;ansi sunit; 55;testsuite.at:91;CharacterFactoryANSITest;ansi sunit; 56;testsuite.at:92;DateAndTimeANSITest;ansi sunit; 57;testsuite.at:93;DateAndTimeFactoryANSITest;ansi sunit; 58;testsuite.at:94;DictionaryANSITest;ansi sunit; 59;testsuite.at:95;DictionaryFactoryANSITest;ansi sunit; 60;testsuite.at:96;DurationANSITest;ansi sunit; 61;testsuite.at:97;DurationFactoryANSITest;ansi sunit; 62;testsuite.at:98;DyadicValuableANSITest;ansi sunit; 63;testsuite.at:99;ErrorANSITest;ansi sunit; 64;testsuite.at:100;ErrorClassANSITest;ansi sunit; 65;testsuite.at:101;ExceptionANSITest;ansi sunit; 66;testsuite.at:102;ExceptionClassANSITest;ansi sunit; 67;testsuite.at:103;ExceptionSetANSITest;ansi sunit; 68;testsuite.at:104;FailedMessageANSITest;ansi sunit; 69;testsuite.at:105;FileStreamFactoryANSITest;ansi sunit; 70;testsuite.at:106;FloatANSITest;ansi sunit; 71;testsuite.at:107;FloatCharacterizationANSITest;ansi sunit; 72;testsuite.at:108;FractionANSITest;ansi sunit; 73;testsuite.at:109;FractionFactoryANSITest;ansi sunit; 74;testsuite.at:110;IdentityDictionaryANSITest;ansi sunit; 75;testsuite.at:111;IdentityDictionaryFactoryANSITest;ansi sunit; 76;testsuite.at:112;IntegerANSITest;ansi sunit; 77;testsuite.at:113;IntervalANSITest;ansi sunit; 78;testsuite.at:114;IntervalFactoryANSITest;ansi sunit; 79;testsuite.at:115;MessageNotUnderstoodANSITest;ansi sunit; 80;testsuite.at:116;MessageNotUnderstoodSelectorANSITest;ansi sunit; 81;testsuite.at:117;MonadicBlockANSITest;ansi sunit; 82;testsuite.at:118;NilANSITest;ansi sunit; 83;testsuite.at:119;NiladicBlockANSITest;ansi sunit; 84;testsuite.at:120;NotificationANSITest;ansi sunit; 85;testsuite.at:121;NotificationClassANSITest;ansi sunit; 86;testsuite.at:122;ObjectANSITest;ansi sunit; 87;testsuite.at:123;ObjectClassANSITest;ansi sunit; 88;testsuite.at:124;OrderedCollectionANSITest;ansi sunit; 89;testsuite.at:125;OrderedCollectionFactoryANSITest;ansi sunit; 90;testsuite.at:126;ReadFileStreamANSITest;ansi sunit; 91;testsuite.at:127;ReadStreamANSITest;ansi sunit; 92;testsuite.at:128;ReadStreamFactoryANSITest;ansi sunit; 93;testsuite.at:129;ReadWriteStreamANSITest;ansi sunit; 94;testsuite.at:130;ReadWriteStreamFactoryANSITest;ansi sunit; 95;testsuite.at:131;ScaledDecimalANSITest;ansi sunit; 96;testsuite.at:132;SelectorANSITest;ansi sunit; 97;testsuite.at:133;SetANSITest;ansi sunit; 98;testsuite.at:134;SetFactoryANSITest;ansi sunit; 99;testsuite.at:135;SortedCollectionANSITest;ansi sunit; 100;testsuite.at:136;SortedCollectionFactoryANSITest;ansi sunit; 101;testsuite.at:137;StringANSITest;ansi sunit; 102;testsuite.at:138;StringFactoryANSITest;ansi sunit; 103;testsuite.at:139;SymbolANSITest;ansi sunit; 104;testsuite.at:140;TranscriptANSITest;ansi sunit; 105;testsuite.at:141;WarningANSITest;ansi sunit; 106;testsuite.at:142;WarningClassANSITest;ansi sunit; 107;testsuite.at:143;WriteFileStreamANSITest;ansi sunit; 108;testsuite.at:144;WriteStreamANSITest;ansi sunit; 109;testsuite.at:145;WriteStreamFactoryANSITest;ansi sunit; 110;testsuite.at:146;ZeroDivideANSITest;ansi sunit; 111;testsuite.at:147;ZeroDivideFactoryANSITest;ansi sunit; 112;testsuite.at:150;Announcements;announcements sunit; 113;testsuite.at:151;Complex;complex sunit; 114;testsuite.at:152;Continuations;continuations sunit; 115;testsuite.at:153;DBD-MySQL;dbd-mysql sunit; 116;testsuite.at:154;DBD-SQLite;dbd-sqlite sunit; 117;testsuite.at:155;DebugTools;debugtools sunit; 118;testsuite.at:156;DhbNumericalMethods;dhbnumericalmethods sunit; 119;testsuite.at:157;Digest;digest sunit; 120;testsuite.at:158;GDBM;gdbm sunit; 121;testsuite.at:159;Iconv;iconv sunit; 122;testsuite.at:160;Magritte;magritte sunit; 123;testsuite.at:161;ROE;roe sunit; 124;testsuite.at:162;SandstoneDb;sandstonedb sunit; 125;testsuite.at:163;Seaside-Core;seaside-core sunit; 126;testsuite.at:164;Sockets;sockets sunit; 127;testsuite.at:165;Sport;sport sunit; 128;testsuite.at:166;Swazoo;swazoo sunit; 129;testsuite.at:167;XML-XMLParser;xml-xmlparser sunit; 130;testsuite.at:168;XML-Expat;xml-expat sunit; 131;testsuite.at:169;ZLib;zlib sunit; " # List of the all the test groups. at_groups_all=`$as_echo "$at_help_all" | sed 's/;.*//'` # at_fn_validate_ranges NAME... # ----------------------------- # Validate and normalize the test group number contained in each variable # NAME. Leading zeroes are treated as decimal. at_fn_validate_ranges () { for at_grp do eval at_value=\$$at_grp if test $at_value -lt 1 || test $at_value -gt 131; then $as_echo "invalid test group: $at_value" >&2 exit 1 fi case $at_value in 0*) # We want to treat leading 0 as decimal, like expr and test, but # AS_VAR_ARITH treats it as octal if it uses $(( )). # With XSI shells, ${at_value#${at_value%%[1-9]*}} avoids the # expr fork, but it is not worth the effort to determine if the # shell supports XSI when the user can just avoid leading 0. eval $at_grp='`expr $at_value + 0`' ;; esac done } at_prev= for at_option do # If the previous option needs an argument, assign it. if test -n "$at_prev"; then at_option=$at_prev=$at_option at_prev= fi case $at_option in *=?*) at_optarg=`expr "X$at_option" : '[^=]*=\(.*\)'` ;; *) at_optarg= ;; esac # Accept the important Cygnus configure options, so we can diagnose typos. case $at_option in --help | -h ) at_help_p=: ;; --list | -l ) at_list_p=: ;; --version | -V ) at_version_p=: ;; --clean | -c ) at_clean=: ;; --color ) at_color=always ;; --color=* ) case $at_optarg in no | never | none) at_color=never ;; auto | tty | if-tty) at_color=auto ;; always | yes | force) at_color=always ;; *) at_optname=`echo " $at_option" | sed 's/^ //; s/=.*//'` as_fn_error $? "unrecognized argument to $at_optname: $at_optarg" ;; esac ;; --debug | -d ) at_debug_p=: ;; --errexit | -e ) at_debug_p=: at_errexit_p=: ;; --verbose | -v ) at_verbose=; at_quiet=: ;; --trace | -x ) at_traceon='set -x' at_trace_echo=echo at_check_filter_trace=at_fn_filter_trace ;; [0-9] | [0-9][0-9] | [0-9][0-9][0-9] | [0-9][0-9][0-9][0-9]) at_fn_validate_ranges at_option as_fn_append at_groups "$at_option$as_nl" ;; # Ranges [0-9]- | [0-9][0-9]- | [0-9][0-9][0-9]- | [0-9][0-9][0-9][0-9]-) at_range_start=`echo $at_option |tr -d X-` at_fn_validate_ranges at_range_start at_range=`$as_echo "$at_groups_all" | \ sed -ne '/^'$at_range_start'$/,$p'` as_fn_append at_groups "$at_range$as_nl" ;; -[0-9] | -[0-9][0-9] | -[0-9][0-9][0-9] | -[0-9][0-9][0-9][0-9]) at_range_end=`echo $at_option |tr -d X-` at_fn_validate_ranges at_range_end at_range=`$as_echo "$at_groups_all" | \ sed -ne '1,/^'$at_range_end'$/p'` as_fn_append at_groups "$at_range$as_nl" ;; [0-9]-[0-9] | [0-9]-[0-9][0-9] | [0-9]-[0-9][0-9][0-9] | \ [0-9]-[0-9][0-9][0-9][0-9] | [0-9][0-9]-[0-9][0-9] | \ [0-9][0-9]-[0-9][0-9][0-9] | [0-9][0-9]-[0-9][0-9][0-9][0-9] | \ [0-9][0-9][0-9]-[0-9][0-9][0-9] | \ [0-9][0-9][0-9]-[0-9][0-9][0-9][0-9] | \ [0-9][0-9][0-9][0-9]-[0-9][0-9][0-9][0-9] ) at_range_start=`expr $at_option : '\(.*\)-'` at_range_end=`expr $at_option : '.*-\(.*\)'` if test $at_range_start -gt $at_range_end; then at_tmp=$at_range_end at_range_end=$at_range_start at_range_start=$at_tmp fi at_fn_validate_ranges at_range_start at_range_end at_range=`$as_echo "$at_groups_all" | \ sed -ne '/^'$at_range_start'$/,/^'$at_range_end'$/p'` as_fn_append at_groups "$at_range$as_nl" ;; # Directory selection. --directory | -C ) at_prev=--directory ;; --directory=* ) at_change_dir=: at_dir=$at_optarg if test x- = "x$at_dir" ; then at_dir=./- fi ;; # Parallel execution. --jobs | -j ) at_jobs=0 ;; --jobs=* | -j[0-9]* ) if test -n "$at_optarg"; then at_jobs=$at_optarg else at_jobs=`expr X$at_option : 'X-j\(.*\)'` fi case $at_jobs in *[!0-9]*) at_optname=`echo " $at_option" | sed 's/^ //; s/[0-9=].*//'` as_fn_error $? "non-numeric argument to $at_optname: $at_jobs" ;; esac ;; # Keywords. --keywords | -k ) at_prev=--keywords ;; --keywords=* ) at_groups_selected=$at_help_all at_save_IFS=$IFS IFS=, set X $at_optarg shift IFS=$at_save_IFS for at_keyword do at_invert= case $at_keyword in '!'*) at_invert="-v" at_keyword=`expr "X$at_keyword" : 'X!\(.*\)'` ;; esac # It is on purpose that we match the test group titles too. at_groups_selected=`$as_echo "$at_groups_selected" | grep -i $at_invert "^[1-9][^;]*;.*[; ]$at_keyword[ ;]"` done # Smash the keywords. at_groups_selected=`$as_echo "$at_groups_selected" | sed 's/;.*//'` as_fn_append at_groups "$at_groups_selected$as_nl" ;; --recheck) at_recheck=: ;; *=*) at_envvar=`expr "x$at_option" : 'x\([^=]*\)='` # Reject names that are not valid shell variable names. case $at_envvar in '' | [0-9]* | *[!_$as_cr_alnum]* ) as_fn_error $? "invalid variable name: \`$at_envvar'" ;; esac at_value=`$as_echo "$at_optarg" | sed "s/'/'\\\\\\\\''/g"` # Export now, but save eval for later and for debug scripts. export $at_envvar as_fn_append at_debug_args " $at_envvar='$at_value'" ;; *) $as_echo "$as_me: invalid option: $at_option" >&2 $as_echo "Try \`$0 --help' for more information." >&2 exit 1 ;; esac done # Verify our last option didn't require an argument if test -n "$at_prev"; then : as_fn_error $? "\`$at_prev' requires an argument" fi # The file containing the suite. at_suite_log=$at_dir/$as_me.log # Selected test groups. if test -z "$at_groups$at_recheck"; then at_groups=$at_groups_all else if test -n "$at_recheck" && test -r "$at_suite_log"; then at_oldfails=`sed -n ' /^Failed tests:$/,/^Skipped tests:$/{ s/^[ ]*\([1-9][0-9]*\):.*/\1/p } /^Unexpected passes:$/,/^## Detailed failed tests/{ s/^[ ]*\([1-9][0-9]*\):.*/\1/p } /^## Detailed failed tests/q ' "$at_suite_log"` as_fn_append at_groups "$at_oldfails$as_nl" fi # Sort the tests, removing duplicates. at_groups=`$as_echo "$at_groups" | sort -nu | sed '/^$/d'` fi if test x"$at_color" = xalways \ || { test x"$at_color" = xauto && test -t 1; }; then at_red=`printf '\033[0;31m'` at_grn=`printf '\033[0;32m'` at_lgn=`printf '\033[1;32m'` at_blu=`printf '\033[1;34m'` at_std=`printf '\033[m'` else at_red= at_grn= at_lgn= at_blu= at_std= fi # Help message. if $at_help_p; then cat <<_ATEOF || at_write_fail=1 Usage: $0 [OPTION]... [VARIABLE=VALUE]... [TESTS] Run all the tests, or the selected TESTS, given by numeric ranges, and save a detailed log file. Upon failure, create debugging scripts. Do not change environment variables directly. Instead, set them via command line arguments. Set \`AUTOTEST_PATH' to select the executables to exercise. Each relative directory is expanded as build and source directories relative to the top level of this distribution. E.g., from within the build directory /tmp/foo-1.0, invoking this: $ $0 AUTOTEST_PATH=bin is equivalent to the following, assuming the source directory is /src/foo-1.0: PATH=/tmp/foo-1.0/bin:/src/foo-1.0/bin:\$PATH $0 _ATEOF cat <<_ATEOF || at_write_fail=1 Operation modes: -h, --help print the help message, then exit -V, --version print version number, then exit -c, --clean remove all the files this test suite might create and exit -l, --list describes all the tests, or the selected TESTS _ATEOF cat <<_ATEOF || at_write_fail=1 Execution tuning: -C, --directory=DIR change to directory DIR before starting --color[=never|auto|always] enable colored test results on terminal, or always -j, --jobs[=N] Allow N jobs at once; infinite jobs with no arg (default 1) -k, --keywords=KEYWORDS select the tests matching all the comma-separated KEYWORDS multiple \`-k' accumulate; prefixed \`!' negates a KEYWORD --recheck select all tests that failed or passed unexpectedly last time -e, --errexit abort as soon as a test fails; implies --debug -v, --verbose force more detailed output default for debugging scripts -d, --debug inhibit clean up and top-level logging default for debugging scripts -x, --trace enable tests shell tracing _ATEOF cat <<_ATEOF || at_write_fail=1 Report bugs to . General help using GNU software: . _ATEOF exit $at_write_fail fi # List of tests. if $at_list_p; then cat <<_ATEOF || at_write_fail=1 GNU Smalltalk 3.2.5 test suite test groups: NUM: FILE-NAME:LINE TEST-GROUP-NAME KEYWORDS _ATEOF # Pass an empty line as separator between selected groups and help. $as_echo "$at_groups$as_nl$as_nl$at_help_all" | awk 'NF == 1 && FS != ";" { selected[$ 1] = 1 next } /^$/ { FS = ";" } NF > 0 { if (selected[$ 1]) { printf " %3d: %-18s %s\n", $ 1, $ 2, $ 3 if ($ 4) { lmax = 79 indent = " " line = indent len = length (line) n = split ($ 4, a, " ") for (i = 1; i <= n; i++) { l = length (a[i]) + 1 if (i > 1 && len + l > lmax) { print line line = indent " " a[i] len = length (line) } else { line = line " " a[i] len += l } } if (n) print line } } }' || at_write_fail=1 exit $at_write_fail fi if $at_version_p; then $as_echo "$as_me (GNU Smalltalk 3.2.5)" && cat <<\_ATEOF || at_write_fail=1 Copyright (C) 2012 Free Software Foundation, Inc. This test suite is free software; the Free Software Foundation gives unlimited permission to copy, distribute and modify it. _ATEOF exit $at_write_fail fi # Should we print banners? Yes if more than one test is run. case $at_groups in #( *$as_nl* ) at_print_banners=: ;; #( * ) at_print_banners=false ;; esac # Text for banner N, set to a single space once printed. # Banner 1. testsuite.at:26 # Category starts at test group 1. at_banner_text_1="Regression tests." # Banner 2. testsuite.at:57 # Category starts at test group 26. at_banner_text_2="Other simple tests." # Banner 3. testsuite.at:78 # Category starts at test group 45. at_banner_text_3="Basic packages." # Banner 4. testsuite.at:82 # Category starts at test group 47. at_banner_text_4="ANSI compliancy tests." # Banner 5. testsuite.at:149 # Category starts at test group 112. at_banner_text_5="Other packages." # Take any -C into account. if $at_change_dir ; then test x != "x$at_dir" && cd "$at_dir" \ || as_fn_error $? "unable to change directory" at_dir=`pwd` fi # Load the config files for any default variable assignments. for at_file in atconfig atlocal do test -r $at_file || continue . ./$at_file || as_fn_error $? "invalid content: $at_file" done # Autoconf <=2.59b set at_top_builddir instead of at_top_build_prefix: : "${at_top_build_prefix=$at_top_builddir}" # Perform any assignments requested during argument parsing. eval "$at_debug_args" # atconfig delivers names relative to the directory the test suite is # in, but the groups themselves are run in testsuite-dir/group-dir. if test -n "$at_top_srcdir"; then builddir=../.. for at_dir_var in srcdir top_srcdir top_build_prefix do eval at_val=\$at_$at_dir_var case $at_val in [\\/$]* | ?:[\\/]* ) at_prefix= ;; *) at_prefix=../../ ;; esac eval "$at_dir_var=\$at_prefix\$at_val" done fi ## -------------------- ## ## Directory structure. ## ## -------------------- ## # This is the set of directories and files used by this script # (non-literals are capitalized): # # TESTSUITE - the testsuite # TESTSUITE.log - summarizes the complete testsuite run # TESTSUITE.dir/ - created during a run, remains after -d or failed test # + at-groups/ - during a run: status of all groups in run # | + NNN/ - during a run: meta-data about test group NNN # | | + check-line - location (source file and line) of current AT_CHECK # | | + status - exit status of current AT_CHECK # | | + stdout - stdout of current AT_CHECK # | | + stder1 - stderr, including trace # | | + stderr - stderr, with trace filtered out # | | + test-source - portion of testsuite that defines group # | | + times - timestamps for computing duration # | | + pass - created if group passed # | | + xpass - created if group xpassed # | | + fail - created if group failed # | | + xfail - created if group xfailed # | | + skip - created if group skipped # + at-stop - during a run: end the run if this file exists # + at-source-lines - during a run: cache of TESTSUITE line numbers for extraction # + 0..NNN/ - created for each group NNN, remains after -d or failed test # | + TESTSUITE.log - summarizes the group results # | + ... - files created during the group # The directory the whole suite works in. # Should be absolute to let the user `cd' at will. at_suite_dir=$at_dir/$as_me.dir # The file containing the suite ($at_dir might have changed since earlier). at_suite_log=$at_dir/$as_me.log # The directory containing helper files per test group. at_helper_dir=$at_suite_dir/at-groups # Stop file: if it exists, do not start new jobs. at_stop_file=$at_suite_dir/at-stop # The fifo used for the job dispatcher. at_job_fifo=$at_suite_dir/at-job-fifo if $at_clean; then test -d "$at_suite_dir" && find "$at_suite_dir" -type d ! -perm -700 -exec chmod u+rwx \{\} \; rm -f -r "$at_suite_dir" "$at_suite_log" exit $? fi # Don't take risks: use only absolute directories in PATH. # # For stand-alone test suites (ie. atconfig was not found), # AUTOTEST_PATH is relative to `.'. # # For embedded test suites, AUTOTEST_PATH is relative to the top level # of the package. Then expand it into build/src parts, since users # may create executables in both places. AUTOTEST_PATH=`$as_echo "$AUTOTEST_PATH" | sed "s|:|$PATH_SEPARATOR|g"` at_path= as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $AUTOTEST_PATH $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. test -n "$at_path" && as_fn_append at_path $PATH_SEPARATOR case $as_dir in [\\/]* | ?:[\\/]* ) as_fn_append at_path "$as_dir" ;; * ) if test -z "$at_top_build_prefix"; then # Stand-alone test suite. as_fn_append at_path "$as_dir" else # Embedded test suite. as_fn_append at_path "$at_top_build_prefix$as_dir$PATH_SEPARATOR" as_fn_append at_path "$at_top_srcdir/$as_dir" fi ;; esac done IFS=$as_save_IFS # Now build and simplify PATH. # # There might be directories that don't exist, but don't redirect # builtins' (eg., cd) stderr directly: Ultrix's sh hates that. at_new_path= as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $at_path do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. test -d "$as_dir" || continue case $as_dir in [\\/]* | ?:[\\/]* ) ;; * ) as_dir=`(cd "$as_dir" && pwd) 2>/dev/null` ;; esac case $PATH_SEPARATOR$at_new_path$PATH_SEPARATOR in *$PATH_SEPARATOR$as_dir$PATH_SEPARATOR*) ;; $PATH_SEPARATOR$PATH_SEPARATOR) at_new_path=$as_dir ;; *) as_fn_append at_new_path "$PATH_SEPARATOR$as_dir" ;; esac done IFS=$as_save_IFS PATH=$at_new_path export PATH # Setting up the FDs. # 5 is the log file. Not to be overwritten if `-d'. if $at_debug_p; then at_suite_log=/dev/null else : >"$at_suite_log" fi exec 5>>"$at_suite_log" # Banners and logs. $as_echo "## ------------------------------- ## ## GNU Smalltalk 3.2.5 test suite. ## ## ------------------------------- ##" { $as_echo "## ------------------------------- ## ## GNU Smalltalk 3.2.5 test suite. ## ## ------------------------------- ##" echo $as_echo "$as_me: command line was:" $as_echo " \$ $0 $at_cli_args" echo # If ChangeLog exists, list a few lines in case it might help determining # the exact version. if test -n "$at_top_srcdir" && test -f "$at_top_srcdir/ChangeLog"; then $as_echo "## ---------- ## ## ChangeLog. ## ## ---------- ##" echo sed 's/^/| /;10q' "$at_top_srcdir/ChangeLog" echo fi { cat <<_ASUNAME ## --------- ## ## Platform. ## ## --------- ## hostname = `(hostname || uname -n) 2>/dev/null | sed 1q` uname -m = `(uname -m) 2>/dev/null || echo unknown` uname -r = `(uname -r) 2>/dev/null || echo unknown` uname -s = `(uname -s) 2>/dev/null || echo unknown` uname -v = `(uname -v) 2>/dev/null || echo unknown` /usr/bin/uname -p = `(/usr/bin/uname -p) 2>/dev/null || echo unknown` /bin/uname -X = `(/bin/uname -X) 2>/dev/null || echo unknown` /bin/arch = `(/bin/arch) 2>/dev/null || echo unknown` /usr/bin/arch -k = `(/usr/bin/arch -k) 2>/dev/null || echo unknown` /usr/convex/getsysinfo = `(/usr/convex/getsysinfo) 2>/dev/null || echo unknown` /usr/bin/hostinfo = `(/usr/bin/hostinfo) 2>/dev/null || echo unknown` /bin/machine = `(/bin/machine) 2>/dev/null || echo unknown` /usr/bin/oslevel = `(/usr/bin/oslevel) 2>/dev/null || echo unknown` /bin/universe = `(/bin/universe) 2>/dev/null || echo unknown` _ASUNAME as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. $as_echo "PATH: $as_dir" done IFS=$as_save_IFS } echo # Contents of the config files. for at_file in atconfig atlocal do test -r $at_file || continue $as_echo "$as_me: $at_file:" sed 's/^/| /' $at_file echo done } >&5 ## ------------------------- ## ## Autotest shell functions. ## ## ------------------------- ## # at_fn_banner NUMBER # ------------------- # Output banner NUMBER, provided the testsuite is running multiple groups and # this particular banner has not yet been printed. at_fn_banner () { $at_print_banners || return 0 eval at_banner_text=\$at_banner_text_$1 test "x$at_banner_text" = "x " && return 0 eval "at_banner_text_$1=\" \"" if test -z "$at_banner_text"; then $at_first || echo else $as_echo "$as_nl$at_banner_text$as_nl" fi } # at_fn_banner # at_fn_check_prepare_notrace REASON LINE # --------------------------------------- # Perform AT_CHECK preparations for the command at LINE for an untraceable # command; REASON is the reason for disabling tracing. at_fn_check_prepare_notrace () { $at_trace_echo "Not enabling shell tracing (command contains $1)" $as_echo "$2" >"$at_check_line_file" at_check_trace=: at_check_filter=: : >"$at_stdout"; : >"$at_stderr" } # at_fn_check_prepare_trace LINE # ------------------------------ # Perform AT_CHECK preparations for the command at LINE for a traceable # command. at_fn_check_prepare_trace () { $as_echo "$1" >"$at_check_line_file" at_check_trace=$at_traceon at_check_filter=$at_check_filter_trace : >"$at_stdout"; : >"$at_stderr" } # at_fn_check_prepare_dynamic COMMAND LINE # ---------------------------------------- # Decide if COMMAND at LINE is traceable at runtime, and call the appropriate # preparation function. at_fn_check_prepare_dynamic () { case $1 in *$as_nl*) at_fn_check_prepare_notrace 'an embedded newline' "$2" ;; *) at_fn_check_prepare_trace "$2" ;; esac } # at_fn_filter_trace # ------------------ # Remove the lines in the file "$at_stderr" generated by "set -x" and print # them to stderr. at_fn_filter_trace () { mv "$at_stderr" "$at_stder1" grep '^ *+' "$at_stder1" >&2 grep -v '^ *+' "$at_stder1" >"$at_stderr" } # at_fn_log_failure FILE-LIST # --------------------------- # Copy the files in the list on stdout with a "> " prefix, and exit the shell # with a failure exit code. at_fn_log_failure () { for file do $as_echo "$file:"; sed 's/^/> /' "$file"; done echo 1 > "$at_status_file" exit 1 } # at_fn_check_skip EXIT-CODE LINE # ------------------------------- # Check whether EXIT-CODE is a special exit code (77 or 99), and if so exit # the test group subshell with that same exit code. Use LINE in any report # about test failure. at_fn_check_skip () { case $1 in 99) echo 99 > "$at_status_file"; at_failed=: $as_echo "$2: hard failure"; exit 99;; 77) echo 77 > "$at_status_file"; exit 77;; esac } # at_fn_check_status EXPECTED EXIT-CODE LINE # ------------------------------------------ # Check whether EXIT-CODE is the EXPECTED exit code, and if so do nothing. # Otherwise, if it is 77 or 99, exit the test group subshell with that same # exit code; if it is anything else print an error message referring to LINE, # and fail the test. at_fn_check_status () { case $2 in $1 ) ;; 77) echo 77 > "$at_status_file"; exit 77;; 99) echo 99 > "$at_status_file"; at_failed=: $as_echo "$3: hard failure"; exit 99;; *) $as_echo "$3: exit code was $2, expected $1" at_failed=:;; esac } # at_fn_diff_devnull FILE # ----------------------- # Emit a diff between /dev/null and FILE. Uses "test -s" to avoid useless diff # invocations. at_fn_diff_devnull () { test -s "$1" || return 0 $at_diff "$at_devnull" "$1" } # at_fn_test NUMBER # ----------------- # Parse out test NUMBER from the tail of this file. at_fn_test () { eval at_sed=\$at_sed$1 sed "$at_sed" "$at_myself" > "$at_test_source" } # at_fn_create_debugging_script # ----------------------------- # Create the debugging script $at_group_dir/run which will reproduce the # current test group. at_fn_create_debugging_script () { { echo "#! /bin/sh" && echo 'test "${ZSH_VERSION+set}" = set && alias -g '\''${1+"$@"}'\''='\''"$@"'\''' && $as_echo "cd '$at_dir'" && $as_echo "exec \${CONFIG_SHELL-$SHELL} \"$at_myself\" -v -d $at_debug_args $at_group \${1+\"\$@\"}" && echo 'exit 1' } >"$at_group_dir/run" && chmod +x "$at_group_dir/run" } ## -------------------------------- ## ## End of autotest shell functions. ## ## -------------------------------- ## { $as_echo "## ---------------- ## ## Tested programs. ## ## ---------------- ##" echo } >&5 # Report what programs are being tested. for at_program in : $at_tested do test "$at_program" = : && continue case $at_program in [\\/]* | ?:[\\/]* ) $at_program_=$at_program ;; * ) as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. test -f "$as_dir/$at_program" && break done IFS=$as_save_IFS at_program_=$as_dir/$at_program ;; esac if test -f "$at_program_"; then { $as_echo "$at_srcdir/testsuite.at:23: $at_program_ --version" "$at_program_" --version &5 2>&1 else as_fn_error $? "cannot find $at_program" "$LINENO" 5 fi done { $as_echo "## ------------------ ## ## Running the tests. ## ## ------------------ ##" } >&5 at_start_date=`date` at_start_time=`date +%s 2>/dev/null` $as_echo "$as_me: starting at: $at_start_date" >&5 # Create the master directory if it doesn't already exist. as_dir="$at_suite_dir"; as_fn_mkdir_p || as_fn_error $? "cannot create \`$at_suite_dir'" "$LINENO" 5 # Can we diff with `/dev/null'? DU 5.0 refuses. if diff /dev/null /dev/null >/dev/null 2>&1; then at_devnull=/dev/null else at_devnull=$at_suite_dir/devnull >"$at_devnull" fi # Use `diff -u' when possible. if at_diff=`diff -u "$at_devnull" "$at_devnull" 2>&1` && test -z "$at_diff" then at_diff='diff -u' else at_diff=diff fi # Get the last needed group. for at_group in : $at_groups; do :; done # Extract the start and end lines of each test group at the tail # of this file awk ' BEGIN { FS="" } /^#AT_START_/ { start = NR } /^#AT_STOP_/ { test = substr ($ 0, 10) print "at_sed" test "=\"1," start "d;" (NR-1) "q\"" if (test == "'"$at_group"'") exit }' "$at_myself" > "$at_suite_dir/at-source-lines" && . "$at_suite_dir/at-source-lines" || as_fn_error $? "cannot create test line number cache" "$LINENO" 5 rm -f "$at_suite_dir/at-source-lines" # Set number of jobs for `-j'; avoid more jobs than test groups. set X $at_groups; shift; at_max_jobs=$# if test $at_max_jobs -eq 0; then at_jobs=1 fi if test $at_jobs -ne 1 && { test $at_jobs -eq 0 || test $at_jobs -gt $at_max_jobs; }; then at_jobs=$at_max_jobs fi # If parallel mode, don't output banners, don't split summary lines. if test $at_jobs -ne 1; then at_print_banners=false at_quiet=: fi # Set up helper dirs. rm -rf "$at_helper_dir" && mkdir "$at_helper_dir" && cd "$at_helper_dir" && { test -z "$at_groups" || mkdir $at_groups; } || as_fn_error $? "testsuite directory setup failed" "$LINENO" 5 # Functions for running a test group. We leave the actual # test group execution outside of a shell function in order # to avoid hitting zsh 4.x exit status bugs. # at_fn_group_prepare # ------------------- # Prepare for running a test group. at_fn_group_prepare () { # The directory for additional per-group helper files. at_job_dir=$at_helper_dir/$at_group # The file containing the location of the last AT_CHECK. at_check_line_file=$at_job_dir/check-line # The file containing the exit status of the last command. at_status_file=$at_job_dir/status # The files containing the output of the tested commands. at_stdout=$at_job_dir/stdout at_stder1=$at_job_dir/stder1 at_stderr=$at_job_dir/stderr # The file containing the code for a test group. at_test_source=$at_job_dir/test-source # The file containing dates. at_times_file=$at_job_dir/times # Be sure to come back to the top test directory. cd "$at_suite_dir" # Clearly separate the test groups when verbose. $at_first || $at_verbose echo at_group_normalized=$at_group eval 'while :; do case $at_group_normalized in #( '"$at_format"'*) break;; esac at_group_normalized=0$at_group_normalized done' # Create a fresh directory for the next test group, and enter. # If one already exists, the user may have invoked ./run from # within that directory; we remove the contents, but not the # directory itself, so that we aren't pulling the rug out from # under the shell's notion of the current directory. at_group_dir=$at_suite_dir/$at_group_normalized at_group_log=$at_group_dir/$as_me.log if test -d "$at_group_dir"; then find "$at_group_dir" -type d ! -perm -700 -exec chmod u+rwx {} \; rm -fr "$at_group_dir"/* "$at_group_dir"/.[!.] "$at_group_dir"/.??* fi || { $as_echo "$as_me:${as_lineno-$LINENO}: WARNING: test directory for $at_group_normalized could not be cleaned" >&5 $as_echo "$as_me: WARNING: test directory for $at_group_normalized could not be cleaned" >&2;} # Be tolerant if the above `rm' was not able to remove the directory. as_dir="$at_group_dir"; as_fn_mkdir_p echo 0 > "$at_status_file" # In verbose mode, append to the log file *and* show on # the standard output; in quiet mode only write to the log. if test -z "$at_verbose"; then at_tee_pipe='tee -a "$at_group_log"' else at_tee_pipe='cat >> "$at_group_log"' fi } # at_fn_group_banner ORDINAL LINE DESC PAD [BANNER] # ------------------------------------------------- # Declare the test group ORDINAL, located at LINE with group description DESC, # and residing under BANNER. Use PAD to align the status column. at_fn_group_banner () { at_setup_line="$2" test -n "$5" && at_fn_banner $5 at_desc="$3" case $1 in [0-9]) at_desc_line=" $1: ";; [0-9][0-9]) at_desc_line=" $1: " ;; *) at_desc_line="$1: " ;; esac as_fn_append at_desc_line "$3$4" $at_quiet $as_echo_n "$at_desc_line" echo "# -*- compilation -*-" >> "$at_group_log" } # at_fn_group_postprocess # ----------------------- # Perform cleanup after running a test group. at_fn_group_postprocess () { # Be sure to come back to the suite directory, in particular # since below we might `rm' the group directory we are in currently. cd "$at_suite_dir" if test ! -f "$at_check_line_file"; then sed "s/^ */$as_me: WARNING: /" <<_ATEOF A failure happened in a test group before any test could be run. This means that test suite is improperly designed. Please report this failure to . _ATEOF $as_echo "$at_setup_line" >"$at_check_line_file" at_status=99 fi $at_verbose $as_echo_n "$at_group. $at_setup_line: " $as_echo_n "$at_group. $at_setup_line: " >> "$at_group_log" case $at_xfail:$at_status in yes:0) at_msg="UNEXPECTED PASS" at_res=xpass at_errexit=$at_errexit_p at_color=$at_red ;; no:0) at_msg="ok" at_res=pass at_errexit=false at_color=$at_grn ;; *:77) at_msg='skipped ('`cat "$at_check_line_file"`')' at_res=skip at_errexit=false at_color=$at_blu ;; no:* | *:99) at_msg='FAILED ('`cat "$at_check_line_file"`')' at_res=fail at_errexit=$at_errexit_p at_color=$at_red ;; yes:*) at_msg='expected failure ('`cat "$at_check_line_file"`')' at_res=xfail at_errexit=false at_color=$at_lgn ;; esac echo "$at_res" > "$at_job_dir/$at_res" # In parallel mode, output the summary line only afterwards. if test $at_jobs -ne 1 && test -n "$at_verbose"; then $as_echo "$at_desc_line $at_color$at_msg$at_std" else # Make sure there is a separator even with long titles. $as_echo " $at_color$at_msg$at_std" fi at_log_msg="$at_group. $at_desc ($at_setup_line): $at_msg" case $at_status in 0|77) # $at_times_file is only available if the group succeeded. # We're not including the group log, so the success message # is written in the global log separately. But we also # write to the group log in case they're using -d. if test -f "$at_times_file"; then at_log_msg="$at_log_msg ("`sed 1d "$at_times_file"`')' rm -f "$at_times_file" fi $as_echo "$at_log_msg" >> "$at_group_log" $as_echo "$at_log_msg" >&5 # Cleanup the group directory, unless the user wants the files # or the success was unexpected. if $at_debug_p || test $at_res = xpass; then at_fn_create_debugging_script if test $at_res = xpass && $at_errexit; then echo stop > "$at_stop_file" fi else if test -d "$at_group_dir"; then find "$at_group_dir" -type d ! -perm -700 -exec chmod u+rwx \{\} \; rm -fr "$at_group_dir" fi rm -f "$at_test_source" fi ;; *) # Upon failure, include the log into the testsuite's global # log. The failure message is written in the group log. It # is later included in the global log. $as_echo "$at_log_msg" >> "$at_group_log" # Upon failure, keep the group directory for autopsy, and create # the debugging script. With -e, do not start any further tests. at_fn_create_debugging_script if $at_errexit; then echo stop > "$at_stop_file" fi ;; esac } ## ------------ ## ## Driver loop. ## ## ------------ ## if (set -m && set +m && set +b) >/dev/null 2>&1; then set +b at_job_control_on='set -m' at_job_control_off='set +m' at_job_group=- else at_job_control_on=: at_job_control_off=: at_job_group= fi for at_signal in 1 2 15; do trap 'set +x; set +e $at_job_control_off at_signal='"$at_signal"' echo stop > "$at_stop_file" trap "" $at_signal at_pgids= for at_pgid in `jobs -p 2>/dev/null`; do at_pgids="$at_pgids $at_job_group$at_pgid" done test -z "$at_pgids" || kill -$at_signal $at_pgids 2>/dev/null wait if test "$at_jobs" -eq 1 || test -z "$at_verbose"; then echo >&2 fi at_signame=`kill -l $at_signal 2>&1 || echo $at_signal` set x $at_signame test 0 -gt 2 && at_signame=$at_signal { $as_echo "$as_me:${as_lineno-$LINENO}: WARNING: caught signal $at_signame, bailing out" >&5 $as_echo "$as_me: WARNING: caught signal $at_signame, bailing out" >&2;} as_fn_arith 128 + $at_signal && exit_status=$as_val as_fn_exit $exit_status' $at_signal done rm -f "$at_stop_file" at_first=: if test $at_jobs -ne 1 && rm -f "$at_job_fifo" && test -n "$at_job_group" && ( mkfifo "$at_job_fifo" && trap 'exit 1' PIPE STOP TSTP ) 2>/dev/null then # FIFO job dispatcher. trap 'at_pids= for at_pid in `jobs -p`; do at_pids="$at_pids $at_job_group$at_pid" done if test -n "$at_pids"; then at_sig=TSTP test "${TMOUT+set}" = set && at_sig=STOP kill -$at_sig $at_pids 2>/dev/null fi kill -STOP $$ test -z "$at_pids" || kill -CONT $at_pids 2>/dev/null' TSTP echo # Turn jobs into a list of numbers, starting from 1. at_joblist=`$as_echo "$at_groups" | sed -n 1,${at_jobs}p` set X $at_joblist shift for at_group in $at_groups; do $at_job_control_on 2>/dev/null ( # Start one test group. $at_job_control_off if $at_first; then exec 7>"$at_job_fifo" else exec 6<&- fi trap 'set +x; set +e trap "" PIPE echo stop > "$at_stop_file" echo >&7 as_fn_exit 141' PIPE at_fn_group_prepare if cd "$at_group_dir" && at_fn_test $at_group && . "$at_test_source" then :; else { $as_echo "$as_me:${as_lineno-$LINENO}: WARNING: unable to parse test group: $at_group" >&5 $as_echo "$as_me: WARNING: unable to parse test group: $at_group" >&2;} at_failed=: fi at_fn_group_postprocess echo >&7 ) & $at_job_control_off if $at_first; then at_first=false exec 6<"$at_job_fifo" 7>"$at_job_fifo" fi shift # Consume one token. if test $# -gt 0; then :; else read at_token <&6 || break set x $* fi test -f "$at_stop_file" && break done exec 7>&- # Read back the remaining ($at_jobs - 1) tokens. set X $at_joblist shift if test $# -gt 0; then shift for at_job do read at_token done <&6 fi exec 6<&- wait else # Run serially, avoid forks and other potential surprises. for at_group in $at_groups; do at_fn_group_prepare if cd "$at_group_dir" && at_fn_test $at_group && . "$at_test_source"; then :; else { $as_echo "$as_me:${as_lineno-$LINENO}: WARNING: unable to parse test group: $at_group" >&5 $as_echo "$as_me: WARNING: unable to parse test group: $at_group" >&2;} at_failed=: fi at_fn_group_postprocess test -f "$at_stop_file" && break at_first=false done fi # Wrap up the test suite with summary statistics. cd "$at_helper_dir" # Use ?..???? when the list must remain sorted, the faster * otherwise. at_pass_list=`for f in */pass; do echo $f; done | sed '/\*/d; s,/pass,,'` at_skip_list=`for f in */skip; do echo $f; done | sed '/\*/d; s,/skip,,'` at_xfail_list=`for f in */xfail; do echo $f; done | sed '/\*/d; s,/xfail,,'` at_xpass_list=`for f in ?/xpass ??/xpass ???/xpass ????/xpass; do echo $f; done | sed '/?/d; s,/xpass,,'` at_fail_list=`for f in ?/fail ??/fail ???/fail ????/fail; do echo $f; done | sed '/?/d; s,/fail,,'` set X $at_pass_list $at_xpass_list $at_xfail_list $at_fail_list $at_skip_list shift; at_group_count=$# set X $at_xpass_list; shift; at_xpass_count=$#; at_xpass_list=$* set X $at_xfail_list; shift; at_xfail_count=$# set X $at_fail_list; shift; at_fail_count=$#; at_fail_list=$* set X $at_skip_list; shift; at_skip_count=$# as_fn_arith $at_group_count - $at_skip_count && at_run_count=$as_val as_fn_arith $at_xpass_count + $at_fail_count && at_unexpected_count=$as_val as_fn_arith $at_xfail_count + $at_fail_count && at_total_fail_count=$as_val # Back to the top directory. cd "$at_dir" rm -rf "$at_helper_dir" # Compute the duration of the suite. at_stop_date=`date` at_stop_time=`date +%s 2>/dev/null` $as_echo "$as_me: ending at: $at_stop_date" >&5 case $at_start_time,$at_stop_time in [0-9]*,[0-9]*) as_fn_arith $at_stop_time - $at_start_time && at_duration_s=$as_val as_fn_arith $at_duration_s / 60 && at_duration_m=$as_val as_fn_arith $at_duration_m / 60 && at_duration_h=$as_val as_fn_arith $at_duration_s % 60 && at_duration_s=$as_val as_fn_arith $at_duration_m % 60 && at_duration_m=$as_val at_duration="${at_duration_h}h ${at_duration_m}m ${at_duration_s}s" $as_echo "$as_me: test suite duration: $at_duration" >&5 ;; esac echo $as_echo "## ------------- ## ## Test results. ## ## ------------- ##" echo { echo $as_echo "## ------------- ## ## Test results. ## ## ------------- ##" echo } >&5 if test $at_run_count = 1; then at_result="1 test" at_were=was else at_result="$at_run_count tests" at_were=were fi if $at_errexit_p && test $at_unexpected_count != 0; then if test $at_xpass_count = 1; then at_result="$at_result $at_were run, one passed" else at_result="$at_result $at_were run, one failed" fi at_result="$at_result unexpectedly and inhibited subsequent tests." at_color=$at_red else # Don't you just love exponential explosion of the number of cases? at_color=$at_red case $at_xpass_count:$at_fail_count:$at_xfail_count in # So far, so good. 0:0:0) at_result="$at_result $at_were successful." at_color=$at_grn ;; 0:0:*) at_result="$at_result behaved as expected." at_color=$at_lgn ;; # Some unexpected failures 0:*:0) at_result="$at_result $at_were run, $at_fail_count failed unexpectedly." ;; # Some failures, both expected and unexpected 0:*:1) at_result="$at_result $at_were run, $at_total_fail_count failed ($at_xfail_count expected failure)." ;; 0:*:*) at_result="$at_result $at_were run, $at_total_fail_count failed ($at_xfail_count expected failures)." ;; # No unexpected failures, but some xpasses *:0:*) at_result="$at_result $at_were run, $at_xpass_count passed unexpectedly." ;; # No expected failures, but failures and xpasses *:1:0) at_result="$at_result $at_were run, $at_unexpected_count did not behave as expected ($at_fail_count unexpected failure)." ;; *:*:0) at_result="$at_result $at_were run, $at_unexpected_count did not behave as expected ($at_fail_count unexpected failures)." ;; # All of them. *:*:1) at_result="$at_result $at_were run, $at_xpass_count passed unexpectedly, $at_total_fail_count failed ($at_xfail_count expected failure)." ;; *:*:*) at_result="$at_result $at_were run, $at_xpass_count passed unexpectedly, $at_total_fail_count failed ($at_xfail_count expected failures)." ;; esac if test $at_skip_count = 0 && test $at_run_count -gt 1; then at_result="All $at_result" fi fi # Now put skips in the mix. case $at_skip_count in 0) ;; 1) at_result="$at_result 1 test was skipped." ;; *) at_result="$at_result $at_skip_count tests were skipped." ;; esac if test $at_unexpected_count = 0; then echo "$at_color$at_result$at_std" echo "$at_result" >&5 else echo "${at_color}ERROR: $at_result$at_std" >&2 echo "ERROR: $at_result" >&5 { echo $as_echo "## ------------------------ ## ## Summary of the failures. ## ## ------------------------ ##" # Summary of failed and skipped tests. if test $at_fail_count != 0; then echo "Failed tests:" $SHELL "$at_myself" $at_fail_list --list echo fi if test $at_skip_count != 0; then echo "Skipped tests:" $SHELL "$at_myself" $at_skip_list --list echo fi if test $at_xpass_count != 0; then echo "Unexpected passes:" $SHELL "$at_myself" $at_xpass_list --list echo fi if test $at_fail_count != 0; then $as_echo "## ---------------------- ## ## Detailed failed tests. ## ## ---------------------- ##" echo for at_group in $at_fail_list do at_group_normalized=$at_group eval 'while :; do case $at_group_normalized in #( '"$at_format"'*) break;; esac at_group_normalized=0$at_group_normalized done' cat "$at_suite_dir/$at_group_normalized/$as_me.log" echo done echo fi if test -n "$at_top_srcdir"; then sed 'h;s/./-/g;s/^.../## /;s/...$/ ##/;p;x;p;x' <<_ASBOX ## ${at_top_build_prefix}config.log ## _ASBOX sed 's/^/| /' ${at_top_build_prefix}config.log echo fi } >&5 sed 'h;s/./-/g;s/^.../## /;s/...$/ ##/;p;x;p;x' <<_ASBOX ## $as_me.log was created. ## _ASBOX echo if $at_debug_p; then at_msg='per-test log files' else at_msg="\`${at_testdir+${at_testdir}/}$as_me.log'" fi $as_echo "Please send $at_msg and all information you think might help: To: Subject: [GNU Smalltalk 3.2.5] $as_me: $at_fail_list${at_fail_list:+ failed${at_xpass_list:+, }}$at_xpass_list${at_xpass_list:+ passed unexpectedly} You may investigate any problem if you feel able to do so, in which case the test suite provides a good starting point. Its output may be found below \`${at_testdir+${at_testdir}/}$as_me.dir'. " exit 1 fi exit 0 ## ------------- ## ## Actual tests. ## ## ------------- ## #AT_START_1 at_fn_group_banner 1 'testsuite.at:27' \ "arrays.st" " " 1 at_xfail=no ( $as_echo "1. $at_setup_line: testing $at_desc ..." $at_traceon cat $abs_srcdir/arrays.ok > expout case $AUTOTEST_PATH in tests) image_path="-I $abs_top_builddir/gst.im" ;; *) image_path="" ;; esac echo "{ (cd $abs_srcdir && $TIMEOUT gst $image_path -r arrays.st 2>&1); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:27: { (cd \$abs_srcdir && \$TIMEOUT gst \$image_path -r arrays.st 2>&1); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:27" ( $at_check_trace; { (cd $abs_srcdir && $TIMEOUT gst $image_path -r arrays.st 2>&1); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: $at_diff expout "$at_stdout" || at_failed=: at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:27" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_1 #AT_START_2 at_fn_group_banner 2 'testsuite.at:28' \ "classes.st" " " 1 at_xfail=no ( $as_echo "2. $at_setup_line: testing $at_desc ..." $at_traceon cat $abs_srcdir/classes.ok > expout case $AUTOTEST_PATH in tests) image_path="-I $abs_top_builddir/gst.im" ;; *) image_path="" ;; esac echo "{ (cd $abs_srcdir && $TIMEOUT gst $image_path -r classes.st 2>&1); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:28: { (cd \$abs_srcdir && \$TIMEOUT gst \$image_path -r classes.st 2>&1); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:28" ( $at_check_trace; { (cd $abs_srcdir && $TIMEOUT gst $image_path -r classes.st 2>&1); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: $at_diff expout "$at_stdout" || at_failed=: at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:28" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_2 #AT_START_3 at_fn_group_banner 3 'testsuite.at:29' \ "blocks.st" " " 1 at_xfail=no ( $as_echo "3. $at_setup_line: testing $at_desc ..." $at_traceon cat $abs_srcdir/blocks.ok > expout case $AUTOTEST_PATH in tests) image_path="-I $abs_top_builddir/gst.im" ;; *) image_path="" ;; esac echo "{ (cd $abs_srcdir && $TIMEOUT gst $image_path -r blocks.st 2>&1); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:29: { (cd \$abs_srcdir && \$TIMEOUT gst \$image_path -r blocks.st 2>&1); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:29" ( $at_check_trace; { (cd $abs_srcdir && $TIMEOUT gst $image_path -r blocks.st 2>&1); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: $at_diff expout "$at_stdout" || at_failed=: at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:29" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_3 #AT_START_4 at_fn_group_banner 4 'testsuite.at:30' \ "sets.st" " " 1 at_xfail=no ( $as_echo "4. $at_setup_line: testing $at_desc ..." $at_traceon cat $abs_srcdir/sets.ok > expout case $AUTOTEST_PATH in tests) image_path="-I $abs_top_builddir/gst.im" ;; *) image_path="" ;; esac echo "{ (cd $abs_srcdir && $TIMEOUT gst $image_path -r sets.st 2>&1); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:30: { (cd \$abs_srcdir && \$TIMEOUT gst \$image_path -r sets.st 2>&1); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:30" ( $at_check_trace; { (cd $abs_srcdir && $TIMEOUT gst $image_path -r sets.st 2>&1); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: $at_diff expout "$at_stdout" || at_failed=: at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:30" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_4 #AT_START_5 at_fn_group_banner 5 'testsuite.at:31' \ "processes.st" " " 1 at_xfail=no ( $as_echo "5. $at_setup_line: testing $at_desc ..." $at_traceon cat $abs_srcdir/processes.ok > expout case $AUTOTEST_PATH in tests) image_path="-I $abs_top_builddir/gst.im" ;; *) image_path="" ;; esac echo "{ (cd $abs_srcdir && $TIMEOUT gst $image_path -r processes.st 2>&1); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:31: { (cd \$abs_srcdir && \$TIMEOUT gst \$image_path -r processes.st 2>&1); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:31" ( $at_check_trace; { (cd $abs_srcdir && $TIMEOUT gst $image_path -r processes.st 2>&1); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: $at_diff expout "$at_stdout" || at_failed=: at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:31" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_5 #AT_START_6 at_fn_group_banner 6 'testsuite.at:32' \ "exceptions.st" " " 1 at_xfail=no ( $as_echo "6. $at_setup_line: testing $at_desc ..." $at_traceon cat $abs_srcdir/exceptions.ok > expout case $AUTOTEST_PATH in tests) image_path="-I $abs_top_builddir/gst.im" ;; *) image_path="" ;; esac echo "{ (cd $abs_srcdir && $TIMEOUT gst $image_path -r exceptions.st 2>&1); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:32: { (cd \$abs_srcdir && \$TIMEOUT gst \$image_path -r exceptions.st 2>&1); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:32" ( $at_check_trace; { (cd $abs_srcdir && $TIMEOUT gst $image_path -r exceptions.st 2>&1); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: $at_diff expout "$at_stdout" || at_failed=: at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:32" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_6 #AT_START_7 at_fn_group_banner 7 'testsuite.at:33' \ "intmath.st" " " 1 at_xfail=no ( $as_echo "7. $at_setup_line: testing $at_desc ..." $at_traceon cat $abs_srcdir/intmath.ok > expout case $AUTOTEST_PATH in tests) image_path="-I $abs_top_builddir/gst.im" ;; *) image_path="" ;; esac echo "{ (cd $abs_srcdir && $TIMEOUT gst $image_path -r intmath.st 2>&1); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:33: { (cd \$abs_srcdir && \$TIMEOUT gst \$image_path -r intmath.st 2>&1); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:33" ( $at_check_trace; { (cd $abs_srcdir && $TIMEOUT gst $image_path -r intmath.st 2>&1); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: $at_diff expout "$at_stdout" || at_failed=: at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:33" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_7 #AT_START_8 at_fn_group_banner 8 'testsuite.at:34' \ "floatmath.st" " " 1 at_xfail=no case "$host" in alpha*-*-*) : ;; *) (exit 1) ;; esac && at_xfail=yes ( $as_echo "8. $at_setup_line: testing $at_desc ..." $at_traceon cat $abs_srcdir/floatmath.ok > expout case $AUTOTEST_PATH in tests) image_path="-I $abs_top_builddir/gst.im" ;; *) image_path="" ;; esac echo "{ (cd $abs_srcdir && $TIMEOUT gst $image_path -r floatmath.st 2>&1); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:34: { (cd \$abs_srcdir && \$TIMEOUT gst \$image_path -r floatmath.st 2>&1); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:34" ( $at_check_trace; { (cd $abs_srcdir && $TIMEOUT gst $image_path -r floatmath.st 2>&1); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: $at_diff expout "$at_stdout" || at_failed=: at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:34" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_8 #AT_START_9 at_fn_group_banner 9 'testsuite.at:39' \ "dates.st" " " 1 at_xfail=no ( $as_echo "9. $at_setup_line: testing $at_desc ..." $at_traceon cat $abs_srcdir/dates.ok > expout case $AUTOTEST_PATH in tests) image_path="-I $abs_top_builddir/gst.im" ;; *) image_path="" ;; esac echo "{ (cd $abs_srcdir && $TIMEOUT gst $image_path -r dates.st 2>&1); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:39: { (cd \$abs_srcdir && \$TIMEOUT gst \$image_path -r dates.st 2>&1); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:39" ( $at_check_trace; { (cd $abs_srcdir && $TIMEOUT gst $image_path -r dates.st 2>&1); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: $at_diff expout "$at_stdout" || at_failed=: at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:39" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_9 #AT_START_10 at_fn_group_banner 10 'testsuite.at:40' \ "objects.st" " " 1 at_xfail=no ( $as_echo "10. $at_setup_line: testing $at_desc ..." $at_traceon cat $abs_srcdir/objects.ok > expout case $AUTOTEST_PATH in tests) image_path="-I $abs_top_builddir/gst.im" ;; *) image_path="" ;; esac echo "{ (cd $abs_srcdir && $TIMEOUT gst $image_path -r objects.st 2>&1); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:40: { (cd \$abs_srcdir && \$TIMEOUT gst \$image_path -r objects.st 2>&1); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:40" ( $at_check_trace; { (cd $abs_srcdir && $TIMEOUT gst $image_path -r objects.st 2>&1); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: $at_diff expout "$at_stdout" || at_failed=: at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:40" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_10 #AT_START_11 at_fn_group_banner 11 'testsuite.at:41' \ "strings.st" " " 1 at_xfail=no ( $as_echo "11. $at_setup_line: testing $at_desc ..." $at_traceon cat $abs_srcdir/strings.ok > expout case $AUTOTEST_PATH in tests) image_path="-I $abs_top_builddir/gst.im" ;; *) image_path="" ;; esac echo "{ (cd $abs_srcdir && $TIMEOUT gst $image_path -r strings.st 2>&1); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:41: { (cd \$abs_srcdir && \$TIMEOUT gst \$image_path -r strings.st 2>&1); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:41" ( $at_check_trace; { (cd $abs_srcdir && $TIMEOUT gst $image_path -r strings.st 2>&1); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: $at_diff expout "$at_stdout" || at_failed=: at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:41" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_11 #AT_START_12 at_fn_group_banner 12 'testsuite.at:42' \ "chars.st" " " 1 at_xfail=no ( $as_echo "12. $at_setup_line: testing $at_desc ..." $at_traceon cat $abs_srcdir/chars.ok > expout case $AUTOTEST_PATH in tests) image_path="-I $abs_top_builddir/gst.im" ;; *) image_path="" ;; esac echo "{ (cd $abs_srcdir && $TIMEOUT gst $image_path -r chars.st 2>&1); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:42: { (cd \$abs_srcdir && \$TIMEOUT gst \$image_path -r chars.st 2>&1); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:42" ( $at_check_trace; { (cd $abs_srcdir && $TIMEOUT gst $image_path -r chars.st 2>&1); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: $at_diff expout "$at_stdout" || at_failed=: at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:42" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_12 #AT_START_13 at_fn_group_banner 13 'testsuite.at:43' \ "objdump.st" " " 1 at_xfail=no ( $as_echo "13. $at_setup_line: testing $at_desc ..." $at_traceon cat $abs_srcdir/objdump.ok > expout case $AUTOTEST_PATH in tests) image_path="-I $abs_top_builddir/gst.im" ;; *) image_path="" ;; esac echo "{ (cd $abs_srcdir && $TIMEOUT gst $image_path -r objdump.st 2>&1); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:43: { (cd \$abs_srcdir && \$TIMEOUT gst \$image_path -r objdump.st 2>&1); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:43" ( $at_check_trace; { (cd $abs_srcdir && $TIMEOUT gst $image_path -r objdump.st 2>&1); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: $at_diff expout "$at_stdout" || at_failed=: at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:43" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_13 #AT_START_14 at_fn_group_banner 14 'testsuite.at:44' \ "delays.st" " " 1 at_xfail=no ( $as_echo "14. $at_setup_line: testing $at_desc ..." $at_traceon cat $abs_srcdir/delays.ok > expout case $AUTOTEST_PATH in tests) image_path="-I $abs_top_builddir/gst.im" ;; *) image_path="" ;; esac echo "{ (cd $abs_srcdir && $TIMEOUT gst $image_path -r delays.st 2>&1); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:44: { (cd \$abs_srcdir && \$TIMEOUT gst \$image_path -r delays.st 2>&1); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:44" ( $at_check_trace; { (cd $abs_srcdir && $TIMEOUT gst $image_path -r delays.st 2>&1); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: $at_diff expout "$at_stdout" || at_failed=: at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:44" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_14 #AT_START_15 at_fn_group_banner 15 'testsuite.at:45' \ "geometry.st" " " 1 at_xfail=no ( $as_echo "15. $at_setup_line: testing $at_desc ..." $at_traceon cat $abs_srcdir/geometry.ok > expout case $AUTOTEST_PATH in tests) image_path="-I $abs_top_builddir/gst.im" ;; *) image_path="" ;; esac echo "{ (cd $abs_srcdir && $TIMEOUT gst $image_path -r geometry.st 2>&1); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:45: { (cd \$abs_srcdir && \$TIMEOUT gst \$image_path -r geometry.st 2>&1); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:45" ( $at_check_trace; { (cd $abs_srcdir && $TIMEOUT gst $image_path -r geometry.st 2>&1); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: $at_diff expout "$at_stdout" || at_failed=: at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:45" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_15 #AT_START_16 at_fn_group_banner 16 'testsuite.at:46' \ "cobjects.st" " " 1 at_xfail=no ( $as_echo "16. $at_setup_line: testing $at_desc ..." $at_traceon cat $abs_srcdir/cobjects.ok > expout case $AUTOTEST_PATH in tests) image_path="-I $abs_top_builddir/gst.im" ;; *) image_path="" ;; esac echo "{ (cd $abs_srcdir && $TIMEOUT gst $image_path -r cobjects.st 2>&1); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:46: { (cd \$abs_srcdir && \$TIMEOUT gst \$image_path -r cobjects.st 2>&1); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:46" ( $at_check_trace; { (cd $abs_srcdir && $TIMEOUT gst $image_path -r cobjects.st 2>&1); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: $at_diff expout "$at_stdout" || at_failed=: at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:46" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_16 #AT_START_17 at_fn_group_banner 17 'testsuite.at:47' \ "compiler.st" " " 1 at_xfail=no ( $as_echo "17. $at_setup_line: testing $at_desc ..." $at_traceon cat $abs_srcdir/compiler.ok > expout case $AUTOTEST_PATH in tests) image_path="-I $abs_top_builddir/gst.im" ;; *) image_path="" ;; esac echo "{ (cd $abs_srcdir && $TIMEOUT gst $image_path -r compiler.st 2>&1); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:47: { (cd \$abs_srcdir && \$TIMEOUT gst \$image_path -r compiler.st 2>&1); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:47" ( $at_check_trace; { (cd $abs_srcdir && $TIMEOUT gst $image_path -r compiler.st 2>&1); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: $at_diff expout "$at_stdout" || at_failed=: at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:47" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_17 #AT_START_18 at_fn_group_banner 18 'testsuite.at:48' \ "fileext.st" " " 1 at_xfail=no ( $as_echo "18. $at_setup_line: testing $at_desc ..." $at_traceon cat $abs_srcdir/fileext.ok > expout case $AUTOTEST_PATH in tests) image_path="-I $abs_top_builddir/gst.im" ;; *) image_path="" ;; esac echo "{ (cd $abs_srcdir && $TIMEOUT gst $image_path -r fileext.st 2>&1); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:48: { (cd \$abs_srcdir && \$TIMEOUT gst \$image_path -r fileext.st 2>&1); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:48" ( $at_check_trace; { (cd $abs_srcdir && $TIMEOUT gst $image_path -r fileext.st 2>&1); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: $at_diff expout "$at_stdout" || at_failed=: at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:48" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_18 #AT_START_19 at_fn_group_banner 19 'testsuite.at:49' \ "mutate.st" " " 1 at_xfail=no ( $as_echo "19. $at_setup_line: testing $at_desc ..." $at_traceon cat $abs_srcdir/mutate.ok > expout case $AUTOTEST_PATH in tests) image_path="-I $abs_top_builddir/gst.im" ;; *) image_path="" ;; esac echo "{ (cd $abs_srcdir && $TIMEOUT gst $image_path -r mutate.st 2>&1); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:49: { (cd \$abs_srcdir && \$TIMEOUT gst \$image_path -r mutate.st 2>&1); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:49" ( $at_check_trace; { (cd $abs_srcdir && $TIMEOUT gst $image_path -r mutate.st 2>&1); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: $at_diff expout "$at_stdout" || at_failed=: at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:49" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_19 #AT_START_20 at_fn_group_banner 20 'testsuite.at:50' \ "untrusted.st" " " 1 at_xfail=no ( $as_echo "20. $at_setup_line: testing $at_desc ..." $at_traceon cat $abs_srcdir/untrusted.ok > expout case $AUTOTEST_PATH in tests) image_path="-I $abs_top_builddir/gst.im" ;; *) image_path="" ;; esac echo "{ (cd $abs_srcdir && $TIMEOUT gst $image_path -r untrusted.st 2>&1); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:50: { (cd \$abs_srcdir && \$TIMEOUT gst \$image_path -r untrusted.st 2>&1); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:50" ( $at_check_trace; { (cd $abs_srcdir && $TIMEOUT gst $image_path -r untrusted.st 2>&1); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: $at_diff expout "$at_stdout" || at_failed=: at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:50" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_20 #AT_START_21 at_fn_group_banner 21 'testsuite.at:51' \ "getopt.st" " " 1 at_xfail=no ( $as_echo "21. $at_setup_line: testing $at_desc ..." $at_traceon cat $abs_srcdir/getopt.ok > expout case $AUTOTEST_PATH in tests) image_path="-I $abs_top_builddir/gst.im" ;; *) image_path="" ;; esac echo "{ (cd $abs_srcdir && $TIMEOUT gst $image_path -r getopt.st 2>&1); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:51: { (cd \$abs_srcdir && \$TIMEOUT gst \$image_path -r getopt.st 2>&1); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:51" ( $at_check_trace; { (cd $abs_srcdir && $TIMEOUT gst $image_path -r getopt.st 2>&1); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: $at_diff expout "$at_stdout" || at_failed=: at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:51" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_21 #AT_START_22 at_fn_group_banner 22 'testsuite.at:52' \ "quit.st" " " 1 at_xfail=no ( $as_echo "22. $at_setup_line: testing $at_desc ..." $at_traceon cat $abs_srcdir/quit.ok > expout case $AUTOTEST_PATH in tests) image_path="-I $abs_top_builddir/gst.im" ;; *) image_path="" ;; esac echo "{ (cd $abs_srcdir && $TIMEOUT gst $image_path -r quit.st 2>&1); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:52: { (cd \$abs_srcdir && \$TIMEOUT gst \$image_path -r quit.st 2>&1); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:52" ( $at_check_trace; { (cd $abs_srcdir && $TIMEOUT gst $image_path -r quit.st 2>&1); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: $at_diff expout "$at_stdout" || at_failed=: at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:52" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_22 #AT_START_23 at_fn_group_banner 23 'testsuite.at:53' \ "pools.st" " " 1 at_xfail=no ( $as_echo "23. $at_setup_line: testing $at_desc ..." $at_traceon cat $abs_srcdir/pools.ok > expout case $AUTOTEST_PATH in tests) image_path="-I $abs_top_builddir/gst.im" ;; *) image_path="" ;; esac echo "{ (cd $abs_srcdir && $TIMEOUT gst $image_path -r pools.st 2>&1); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:53: { (cd \$abs_srcdir && \$TIMEOUT gst \$image_path -r pools.st 2>&1); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:53" ( $at_check_trace; { (cd $abs_srcdir && $TIMEOUT gst $image_path -r pools.st 2>&1); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: $at_diff expout "$at_stdout" || at_failed=: at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:53" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_23 #AT_START_24 at_fn_group_banner 24 'testsuite.at:54' \ "shape.st" " " 1 at_xfail=no ( $as_echo "24. $at_setup_line: testing $at_desc ..." $at_traceon cat $abs_srcdir/shape.ok > expout case $AUTOTEST_PATH in tests) image_path="-I $abs_top_builddir/gst.im" ;; *) image_path="" ;; esac echo "{ (cd $abs_srcdir && $TIMEOUT gst $image_path -r shape.st 2>&1); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:54: { (cd \$abs_srcdir && \$TIMEOUT gst \$image_path -r shape.st 2>&1); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:54" ( $at_check_trace; { (cd $abs_srcdir && $TIMEOUT gst $image_path -r shape.st 2>&1); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: $at_diff expout "$at_stdout" || at_failed=: at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:54" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_24 #AT_START_25 at_fn_group_banner 25 'testsuite.at:55' \ "streams.st" " " 1 at_xfail=no ( $as_echo "25. $at_setup_line: testing $at_desc ..." $at_traceon cat $abs_srcdir/streams.ok > expout case $AUTOTEST_PATH in tests) image_path="-I $abs_top_builddir/gst.im" ;; *) image_path="" ;; esac echo "{ (cd $abs_srcdir && $TIMEOUT gst $image_path -r streams.st 2>&1); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:55: { (cd \$abs_srcdir && \$TIMEOUT gst \$image_path -r streams.st 2>&1); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:55" ( $at_check_trace; { (cd $abs_srcdir && $TIMEOUT gst $image_path -r streams.st 2>&1); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: $at_diff expout "$at_stdout" || at_failed=: at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:55" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_25 #AT_START_26 at_fn_group_banner 26 'testsuite.at:58' \ "ackermann.st" " " 2 at_xfail=no ( $as_echo "26. $at_setup_line: testing $at_desc ..." $at_traceon cat $abs_srcdir/ackermann.ok > expout case $AUTOTEST_PATH in tests) image_path="-I $abs_top_builddir/gst.im" ;; *) image_path="" ;; esac echo "{ (cd $abs_srcdir && $TIMEOUT gst $image_path -r ackermann.st 2>&1); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:58: { (cd \$abs_srcdir && \$TIMEOUT gst \$image_path -r ackermann.st 2>&1); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:58" ( $at_check_trace; { (cd $abs_srcdir && $TIMEOUT gst $image_path -r ackermann.st 2>&1); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: $at_diff expout "$at_stdout" || at_failed=: at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:58" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_26 #AT_START_27 at_fn_group_banner 27 'testsuite.at:59' \ "ary3.st" " " 2 at_xfail=no ( $as_echo "27. $at_setup_line: testing $at_desc ..." $at_traceon cat $abs_srcdir/ary3.ok > expout case $AUTOTEST_PATH in tests) image_path="-I $abs_top_builddir/gst.im" ;; *) image_path="" ;; esac echo "{ (cd $abs_srcdir && $TIMEOUT gst $image_path -r ary3.st 2>&1); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:59: { (cd \$abs_srcdir && \$TIMEOUT gst \$image_path -r ary3.st 2>&1); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:59" ( $at_check_trace; { (cd $abs_srcdir && $TIMEOUT gst $image_path -r ary3.st 2>&1); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: $at_diff expout "$at_stdout" || at_failed=: at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:59" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_27 #AT_START_28 at_fn_group_banner 28 'testsuite.at:60' \ "except.st" " " 2 at_xfail=no ( $as_echo "28. $at_setup_line: testing $at_desc ..." $at_traceon cat $abs_srcdir/except.ok > expout case $AUTOTEST_PATH in tests) image_path="-I $abs_top_builddir/gst.im" ;; *) image_path="" ;; esac echo "{ (cd $abs_srcdir && $TIMEOUT gst $image_path -r except.st 2>&1); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:60: { (cd \$abs_srcdir && \$TIMEOUT gst \$image_path -r except.st 2>&1); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:60" ( $at_check_trace; { (cd $abs_srcdir && $TIMEOUT gst $image_path -r except.st 2>&1); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: $at_diff expout "$at_stdout" || at_failed=: at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:60" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_28 #AT_START_29 at_fn_group_banner 29 'testsuite.at:61' \ "fibo.st" " " 2 at_xfail=no ( $as_echo "29. $at_setup_line: testing $at_desc ..." $at_traceon cat $abs_srcdir/fibo.ok > expout case $AUTOTEST_PATH in tests) image_path="-I $abs_top_builddir/gst.im" ;; *) image_path="" ;; esac echo "{ (cd $abs_srcdir && $TIMEOUT gst $image_path -r fibo.st 2>&1); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:61: { (cd \$abs_srcdir && \$TIMEOUT gst \$image_path -r fibo.st 2>&1); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:61" ( $at_check_trace; { (cd $abs_srcdir && $TIMEOUT gst $image_path -r fibo.st 2>&1); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: $at_diff expout "$at_stdout" || at_failed=: at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:61" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_29 #AT_START_30 at_fn_group_banner 30 'testsuite.at:62' \ "hash.st" " " 2 at_xfail=no ( $as_echo "30. $at_setup_line: testing $at_desc ..." $at_traceon cat $abs_srcdir/hash.ok > expout case $AUTOTEST_PATH in tests) image_path="-I $abs_top_builddir/gst.im" ;; *) image_path="" ;; esac echo "{ (cd $abs_srcdir && $TIMEOUT gst $image_path -r hash.st 2>&1); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:62: { (cd \$abs_srcdir && \$TIMEOUT gst \$image_path -r hash.st 2>&1); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:62" ( $at_check_trace; { (cd $abs_srcdir && $TIMEOUT gst $image_path -r hash.st 2>&1); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: $at_diff expout "$at_stdout" || at_failed=: at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:62" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_30 #AT_START_31 at_fn_group_banner 31 'testsuite.at:63' \ "hash2.st" " " 2 at_xfail=no ( $as_echo "31. $at_setup_line: testing $at_desc ..." $at_traceon cat $abs_srcdir/hash2.ok > expout case $AUTOTEST_PATH in tests) image_path="-I $abs_top_builddir/gst.im" ;; *) image_path="" ;; esac echo "{ (cd $abs_srcdir && $TIMEOUT gst $image_path -r hash2.st 2>&1); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:63: { (cd \$abs_srcdir && \$TIMEOUT gst \$image_path -r hash2.st 2>&1); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:63" ( $at_check_trace; { (cd $abs_srcdir && $TIMEOUT gst $image_path -r hash2.st 2>&1); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: $at_diff expout "$at_stdout" || at_failed=: at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:63" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_31 #AT_START_32 at_fn_group_banner 32 'testsuite.at:64' \ "heapsort.st" " " 2 at_xfail=no ( $as_echo "32. $at_setup_line: testing $at_desc ..." $at_traceon cat $abs_srcdir/heapsort.ok > expout case $AUTOTEST_PATH in tests) image_path="-I $abs_top_builddir/gst.im" ;; *) image_path="" ;; esac echo "{ (cd $abs_srcdir && $TIMEOUT gst $image_path -r heapsort.st 2>&1); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:64: { (cd \$abs_srcdir && \$TIMEOUT gst \$image_path -r heapsort.st 2>&1); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:64" ( $at_check_trace; { (cd $abs_srcdir && $TIMEOUT gst $image_path -r heapsort.st 2>&1); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: $at_diff expout "$at_stdout" || at_failed=: at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:64" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_32 #AT_START_33 at_fn_group_banner 33 'testsuite.at:65' \ "lists.st" " " 2 at_xfail=no ( $as_echo "33. $at_setup_line: testing $at_desc ..." $at_traceon cat $abs_srcdir/lists.ok > expout case $AUTOTEST_PATH in tests) image_path="-I $abs_top_builddir/gst.im" ;; *) image_path="" ;; esac echo "{ (cd $abs_srcdir && $TIMEOUT gst $image_path -r lists.st 2>&1); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:65: { (cd \$abs_srcdir && \$TIMEOUT gst \$image_path -r lists.st 2>&1); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:65" ( $at_check_trace; { (cd $abs_srcdir && $TIMEOUT gst $image_path -r lists.st 2>&1); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: $at_diff expout "$at_stdout" || at_failed=: at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:65" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_33 #AT_START_34 at_fn_group_banner 34 'testsuite.at:66' \ "lists1.st" " " 2 at_xfail=no ( $as_echo "34. $at_setup_line: testing $at_desc ..." $at_traceon cat $abs_srcdir/lists1.ok > expout case $AUTOTEST_PATH in tests) image_path="-I $abs_top_builddir/gst.im" ;; *) image_path="" ;; esac echo "{ (cd $abs_srcdir && $TIMEOUT gst $image_path -r lists1.st 2>&1); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:66: { (cd \$abs_srcdir && \$TIMEOUT gst \$image_path -r lists1.st 2>&1); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:66" ( $at_check_trace; { (cd $abs_srcdir && $TIMEOUT gst $image_path -r lists1.st 2>&1); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: $at_diff expout "$at_stdout" || at_failed=: at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:66" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_34 #AT_START_35 at_fn_group_banner 35 'testsuite.at:67' \ "lists2.st" " " 2 at_xfail=no ( $as_echo "35. $at_setup_line: testing $at_desc ..." $at_traceon cat $abs_srcdir/lists2.ok > expout case $AUTOTEST_PATH in tests) image_path="-I $abs_top_builddir/gst.im" ;; *) image_path="" ;; esac echo "{ (cd $abs_srcdir && $TIMEOUT gst $image_path -r lists2.st 2>&1); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:67: { (cd \$abs_srcdir && \$TIMEOUT gst \$image_path -r lists2.st 2>&1); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:67" ( $at_check_trace; { (cd $abs_srcdir && $TIMEOUT gst $image_path -r lists2.st 2>&1); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: $at_diff expout "$at_stdout" || at_failed=: at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:67" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_35 #AT_START_36 at_fn_group_banner 36 'testsuite.at:68' \ "matrix.st" " " 2 at_xfail=no ( $as_echo "36. $at_setup_line: testing $at_desc ..." $at_traceon cat $abs_srcdir/matrix.ok > expout case $AUTOTEST_PATH in tests) image_path="-I $abs_top_builddir/gst.im" ;; *) image_path="" ;; esac echo "{ (cd $abs_srcdir && $TIMEOUT gst $image_path -r matrix.st 2>&1); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:68: { (cd \$abs_srcdir && \$TIMEOUT gst \$image_path -r matrix.st 2>&1); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:68" ( $at_check_trace; { (cd $abs_srcdir && $TIMEOUT gst $image_path -r matrix.st 2>&1); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: $at_diff expout "$at_stdout" || at_failed=: at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:68" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_36 #AT_START_37 at_fn_group_banner 37 'testsuite.at:69' \ "methcall.st" " " 2 at_xfail=no ( $as_echo "37. $at_setup_line: testing $at_desc ..." $at_traceon cat $abs_srcdir/methcall.ok > expout case $AUTOTEST_PATH in tests) image_path="-I $abs_top_builddir/gst.im" ;; *) image_path="" ;; esac echo "{ (cd $abs_srcdir && $TIMEOUT gst $image_path -r methcall.st 2>&1); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:69: { (cd \$abs_srcdir && \$TIMEOUT gst \$image_path -r methcall.st 2>&1); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:69" ( $at_check_trace; { (cd $abs_srcdir && $TIMEOUT gst $image_path -r methcall.st 2>&1); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: $at_diff expout "$at_stdout" || at_failed=: at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:69" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_37 #AT_START_38 at_fn_group_banner 38 'testsuite.at:70' \ "nestedloop.st" " " 2 at_xfail=no ( $as_echo "38. $at_setup_line: testing $at_desc ..." $at_traceon cat $abs_srcdir/nestedloop.ok > expout case $AUTOTEST_PATH in tests) image_path="-I $abs_top_builddir/gst.im" ;; *) image_path="" ;; esac echo "{ (cd $abs_srcdir && $TIMEOUT gst $image_path -r nestedloop.st 2>&1); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:70: { (cd \$abs_srcdir && \$TIMEOUT gst \$image_path -r nestedloop.st 2>&1); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:70" ( $at_check_trace; { (cd $abs_srcdir && $TIMEOUT gst $image_path -r nestedloop.st 2>&1); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: $at_diff expout "$at_stdout" || at_failed=: at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:70" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_38 #AT_START_39 at_fn_group_banner 39 'testsuite.at:71' \ "objinst.st" " " 2 at_xfail=no ( $as_echo "39. $at_setup_line: testing $at_desc ..." $at_traceon cat $abs_srcdir/objinst.ok > expout case $AUTOTEST_PATH in tests) image_path="-I $abs_top_builddir/gst.im" ;; *) image_path="" ;; esac echo "{ (cd $abs_srcdir && $TIMEOUT gst $image_path -r objinst.st 2>&1); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:71: { (cd \$abs_srcdir && \$TIMEOUT gst \$image_path -r objinst.st 2>&1); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:71" ( $at_check_trace; { (cd $abs_srcdir && $TIMEOUT gst $image_path -r objinst.st 2>&1); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: $at_diff expout "$at_stdout" || at_failed=: at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:71" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_39 #AT_START_40 at_fn_group_banner 40 'testsuite.at:72' \ "prodcons.st" " " 2 at_xfail=no ( $as_echo "40. $at_setup_line: testing $at_desc ..." $at_traceon cat $abs_srcdir/prodcons.ok > expout case $AUTOTEST_PATH in tests) image_path="-I $abs_top_builddir/gst.im" ;; *) image_path="" ;; esac echo "{ (cd $abs_srcdir && $TIMEOUT gst $image_path -r prodcons.st 2>&1); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:72: { (cd \$abs_srcdir && \$TIMEOUT gst \$image_path -r prodcons.st 2>&1); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:72" ( $at_check_trace; { (cd $abs_srcdir && $TIMEOUT gst $image_path -r prodcons.st 2>&1); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: $at_diff expout "$at_stdout" || at_failed=: at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:72" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_40 #AT_START_41 at_fn_group_banner 41 'testsuite.at:73' \ "random-bench.st" " " 2 at_xfail=no ( $as_echo "41. $at_setup_line: testing $at_desc ..." $at_traceon cat $abs_srcdir/random-bench.ok > expout case $AUTOTEST_PATH in tests) image_path="-I $abs_top_builddir/gst.im" ;; *) image_path="" ;; esac echo "{ (cd $abs_srcdir && $TIMEOUT gst $image_path -r random-bench.st 2>&1); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:73: { (cd \$abs_srcdir && \$TIMEOUT gst \$image_path -r random-bench.st 2>&1); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:73" ( $at_check_trace; { (cd $abs_srcdir && $TIMEOUT gst $image_path -r random-bench.st 2>&1); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: $at_diff expout "$at_stdout" || at_failed=: at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:73" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_41 #AT_START_42 at_fn_group_banner 42 'testsuite.at:74' \ "sieve.st" " " 2 at_xfail=no ( $as_echo "42. $at_setup_line: testing $at_desc ..." $at_traceon cat $abs_srcdir/sieve.ok > expout case $AUTOTEST_PATH in tests) image_path="-I $abs_top_builddir/gst.im" ;; *) image_path="" ;; esac echo "{ (cd $abs_srcdir && $TIMEOUT gst $image_path -r sieve.st 2>&1); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:74: { (cd \$abs_srcdir && \$TIMEOUT gst \$image_path -r sieve.st 2>&1); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:74" ( $at_check_trace; { (cd $abs_srcdir && $TIMEOUT gst $image_path -r sieve.st 2>&1); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: $at_diff expout "$at_stdout" || at_failed=: at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:74" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_42 #AT_START_43 at_fn_group_banner 43 'testsuite.at:75' \ "strcat.st" " " 2 at_xfail=no ( $as_echo "43. $at_setup_line: testing $at_desc ..." $at_traceon cat $abs_srcdir/strcat.ok > expout case $AUTOTEST_PATH in tests) image_path="-I $abs_top_builddir/gst.im" ;; *) image_path="" ;; esac echo "{ (cd $abs_srcdir && $TIMEOUT gst $image_path -r strcat.st 2>&1); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:75: { (cd \$abs_srcdir && \$TIMEOUT gst \$image_path -r strcat.st 2>&1); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:75" ( $at_check_trace; { (cd $abs_srcdir && $TIMEOUT gst $image_path -r strcat.st 2>&1); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: $at_diff expout "$at_stdout" || at_failed=: at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:75" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_43 #AT_START_44 at_fn_group_banner 44 'testsuite.at:76' \ "stcompiler.st" " " 2 at_xfail=no ( $as_echo "44. $at_setup_line: testing $at_desc ..." $at_traceon cat $abs_srcdir/stcompiler.ok > expout case $AUTOTEST_PATH in tests) image_path="-I $abs_top_builddir/gst.im" ;; *) image_path="" ;; esac echo "{ (cd $abs_srcdir && $TIMEOUT gst $image_path -r stcompiler.st 2>&1); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:76: { (cd \$abs_srcdir && \$TIMEOUT gst \$image_path -r stcompiler.st 2>&1); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:76" ( $at_check_trace; { (cd $abs_srcdir && $TIMEOUT gst $image_path -r stcompiler.st 2>&1); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: $at_diff expout "$at_stdout" || at_failed=: at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:76" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_44 #AT_START_45 at_fn_group_banner 45 'testsuite.at:79' \ "SUnit" " " 3 at_xfail=no ( $as_echo "45. $at_setup_line: testing $at_desc ..." $at_traceon case $AUTOTEST_PATH in tests) image_path="-I $abs_top_builddir/gst.im" ;; *) image_path="" ;; esac echo "{ (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_top_srcdir/scripts/Test.st --verbose -p SUnit); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:79: { (cd \$abs_top_builddir && \$TIMEOUT gst \$image_path -f \$abs_top_srcdir/scripts/Test.st --verbose -p SUnit); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:79" ( $at_check_trace; { (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_top_srcdir/scripts/Test.st --verbose -p SUnit); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: echo stdout:; cat "$at_stdout" at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:79" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_45 #AT_START_46 at_fn_group_banner 46 'testsuite.at:80' \ "Parser" " " 3 at_xfail=no ( $as_echo "46. $at_setup_line: testing $at_desc ..." $at_traceon case $AUTOTEST_PATH in tests) image_path="-I $abs_top_builddir/gst.im" ;; *) image_path="" ;; esac echo "{ (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_top_srcdir/scripts/Test.st --verbose -p Parser); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:80: { (cd \$abs_top_builddir && \$TIMEOUT gst \$image_path -f \$abs_top_srcdir/scripts/Test.st --verbose -p Parser); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:80" ( $at_check_trace; { (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_top_srcdir/scripts/Test.st --verbose -p Parser); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: echo stdout:; cat "$at_stdout" at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:80" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_46 #AT_START_47 at_fn_group_banner 47 'testsuite.at:83' \ "ArrayANSITest" " " 4 at_xfail=no ( $as_echo "47. $at_setup_line: testing $at_desc ..." $at_traceon case $AUTOTEST_PATH in tests) image_path="-I $abs_builddir/gst.im" ;; *) image_path="-I $abs_builddir/gst.im" ;; esac echo "{ (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st ArrayANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:83: { (cd \$abs_top_builddir && \$TIMEOUT gst \$image_path -f \$abs_srcdir/AnsiRun.st ArrayANSITest); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:83" ( $at_check_trace; { (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st ArrayANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: echo stdout:; cat "$at_stdout" at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:83" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_47 #AT_START_48 at_fn_group_banner 48 'testsuite.at:84' \ "ArrayFactoryANSITest" " " 4 at_xfail=no ( $as_echo "48. $at_setup_line: testing $at_desc ..." $at_traceon case $AUTOTEST_PATH in tests) image_path="-I $abs_builddir/gst.im" ;; *) image_path="-I $abs_builddir/gst.im" ;; esac echo "{ (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st ArrayFactoryANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:84: { (cd \$abs_top_builddir && \$TIMEOUT gst \$image_path -f \$abs_srcdir/AnsiRun.st ArrayFactoryANSITest); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:84" ( $at_check_trace; { (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st ArrayFactoryANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: echo stdout:; cat "$at_stdout" at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:84" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_48 #AT_START_49 at_fn_group_banner 49 'testsuite.at:85' \ "BagANSITest" " " 4 at_xfail=no ( $as_echo "49. $at_setup_line: testing $at_desc ..." $at_traceon case $AUTOTEST_PATH in tests) image_path="-I $abs_builddir/gst.im" ;; *) image_path="-I $abs_builddir/gst.im" ;; esac echo "{ (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st BagANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:85: { (cd \$abs_top_builddir && \$TIMEOUT gst \$image_path -f \$abs_srcdir/AnsiRun.st BagANSITest); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:85" ( $at_check_trace; { (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st BagANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: echo stdout:; cat "$at_stdout" at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:85" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_49 #AT_START_50 at_fn_group_banner 50 'testsuite.at:86' \ "BagFactoryANSITest" " " 4 at_xfail=no ( $as_echo "50. $at_setup_line: testing $at_desc ..." $at_traceon case $AUTOTEST_PATH in tests) image_path="-I $abs_builddir/gst.im" ;; *) image_path="-I $abs_builddir/gst.im" ;; esac echo "{ (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st BagFactoryANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:86: { (cd \$abs_top_builddir && \$TIMEOUT gst \$image_path -f \$abs_srcdir/AnsiRun.st BagFactoryANSITest); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:86" ( $at_check_trace; { (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st BagFactoryANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: echo stdout:; cat "$at_stdout" at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:86" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_50 #AT_START_51 at_fn_group_banner 51 'testsuite.at:87' \ "BooleanANSITest" " " 4 at_xfail=no ( $as_echo "51. $at_setup_line: testing $at_desc ..." $at_traceon case $AUTOTEST_PATH in tests) image_path="-I $abs_builddir/gst.im" ;; *) image_path="-I $abs_builddir/gst.im" ;; esac echo "{ (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st BooleanANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:87: { (cd \$abs_top_builddir && \$TIMEOUT gst \$image_path -f \$abs_srcdir/AnsiRun.st BooleanANSITest); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:87" ( $at_check_trace; { (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st BooleanANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: echo stdout:; cat "$at_stdout" at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:87" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_51 #AT_START_52 at_fn_group_banner 52 'testsuite.at:88' \ "ByteArrayANSITest" " " 4 at_xfail=no ( $as_echo "52. $at_setup_line: testing $at_desc ..." $at_traceon case $AUTOTEST_PATH in tests) image_path="-I $abs_builddir/gst.im" ;; *) image_path="-I $abs_builddir/gst.im" ;; esac echo "{ (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st ByteArrayANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:88: { (cd \$abs_top_builddir && \$TIMEOUT gst \$image_path -f \$abs_srcdir/AnsiRun.st ByteArrayANSITest); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:88" ( $at_check_trace; { (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st ByteArrayANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: echo stdout:; cat "$at_stdout" at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:88" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_52 #AT_START_53 at_fn_group_banner 53 'testsuite.at:89' \ "ByteArrayFactoryANSITest" " " 4 at_xfail=no ( $as_echo "53. $at_setup_line: testing $at_desc ..." $at_traceon case $AUTOTEST_PATH in tests) image_path="-I $abs_builddir/gst.im" ;; *) image_path="-I $abs_builddir/gst.im" ;; esac echo "{ (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st ByteArrayFactoryANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:89: { (cd \$abs_top_builddir && \$TIMEOUT gst \$image_path -f \$abs_srcdir/AnsiRun.st ByteArrayFactoryANSITest); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:89" ( $at_check_trace; { (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st ByteArrayFactoryANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: echo stdout:; cat "$at_stdout" at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:89" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_53 #AT_START_54 at_fn_group_banner 54 'testsuite.at:90' \ "CharacterANSITest" " " 4 at_xfail=no ( $as_echo "54. $at_setup_line: testing $at_desc ..." $at_traceon case $AUTOTEST_PATH in tests) image_path="-I $abs_builddir/gst.im" ;; *) image_path="-I $abs_builddir/gst.im" ;; esac echo "{ (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st CharacterANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:90: { (cd \$abs_top_builddir && \$TIMEOUT gst \$image_path -f \$abs_srcdir/AnsiRun.st CharacterANSITest); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:90" ( $at_check_trace; { (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st CharacterANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: echo stdout:; cat "$at_stdout" at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:90" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_54 #AT_START_55 at_fn_group_banner 55 'testsuite.at:91' \ "CharacterFactoryANSITest" " " 4 at_xfail=no ( $as_echo "55. $at_setup_line: testing $at_desc ..." $at_traceon case $AUTOTEST_PATH in tests) image_path="-I $abs_builddir/gst.im" ;; *) image_path="-I $abs_builddir/gst.im" ;; esac echo "{ (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st CharacterFactoryANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:91: { (cd \$abs_top_builddir && \$TIMEOUT gst \$image_path -f \$abs_srcdir/AnsiRun.st CharacterFactoryANSITest); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:91" ( $at_check_trace; { (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st CharacterFactoryANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: echo stdout:; cat "$at_stdout" at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:91" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_55 #AT_START_56 at_fn_group_banner 56 'testsuite.at:92' \ "DateAndTimeANSITest" " " 4 at_xfail=no ( $as_echo "56. $at_setup_line: testing $at_desc ..." $at_traceon case $AUTOTEST_PATH in tests) image_path="-I $abs_builddir/gst.im" ;; *) image_path="-I $abs_builddir/gst.im" ;; esac echo "{ (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st DateAndTimeANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:92: { (cd \$abs_top_builddir && \$TIMEOUT gst \$image_path -f \$abs_srcdir/AnsiRun.st DateAndTimeANSITest); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:92" ( $at_check_trace; { (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st DateAndTimeANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: echo stdout:; cat "$at_stdout" at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:92" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_56 #AT_START_57 at_fn_group_banner 57 'testsuite.at:93' \ "DateAndTimeFactoryANSITest" " " 4 at_xfail=no ( $as_echo "57. $at_setup_line: testing $at_desc ..." $at_traceon case $AUTOTEST_PATH in tests) image_path="-I $abs_builddir/gst.im" ;; *) image_path="-I $abs_builddir/gst.im" ;; esac echo "{ (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st DateAndTimeFactoryANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:93: { (cd \$abs_top_builddir && \$TIMEOUT gst \$image_path -f \$abs_srcdir/AnsiRun.st DateAndTimeFactoryANSITest); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:93" ( $at_check_trace; { (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st DateAndTimeFactoryANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: echo stdout:; cat "$at_stdout" at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:93" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_57 #AT_START_58 at_fn_group_banner 58 'testsuite.at:94' \ "DictionaryANSITest" " " 4 at_xfail=no ( $as_echo "58. $at_setup_line: testing $at_desc ..." $at_traceon case $AUTOTEST_PATH in tests) image_path="-I $abs_builddir/gst.im" ;; *) image_path="-I $abs_builddir/gst.im" ;; esac echo "{ (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st DictionaryANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:94: { (cd \$abs_top_builddir && \$TIMEOUT gst \$image_path -f \$abs_srcdir/AnsiRun.st DictionaryANSITest); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:94" ( $at_check_trace; { (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st DictionaryANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: echo stdout:; cat "$at_stdout" at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:94" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_58 #AT_START_59 at_fn_group_banner 59 'testsuite.at:95' \ "DictionaryFactoryANSITest" " " 4 at_xfail=no ( $as_echo "59. $at_setup_line: testing $at_desc ..." $at_traceon case $AUTOTEST_PATH in tests) image_path="-I $abs_builddir/gst.im" ;; *) image_path="-I $abs_builddir/gst.im" ;; esac echo "{ (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st DictionaryFactoryANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:95: { (cd \$abs_top_builddir && \$TIMEOUT gst \$image_path -f \$abs_srcdir/AnsiRun.st DictionaryFactoryANSITest); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:95" ( $at_check_trace; { (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st DictionaryFactoryANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: echo stdout:; cat "$at_stdout" at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:95" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_59 #AT_START_60 at_fn_group_banner 60 'testsuite.at:96' \ "DurationANSITest" " " 4 at_xfail=no ( $as_echo "60. $at_setup_line: testing $at_desc ..." $at_traceon case $AUTOTEST_PATH in tests) image_path="-I $abs_builddir/gst.im" ;; *) image_path="-I $abs_builddir/gst.im" ;; esac echo "{ (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st DurationANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:96: { (cd \$abs_top_builddir && \$TIMEOUT gst \$image_path -f \$abs_srcdir/AnsiRun.st DurationANSITest); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:96" ( $at_check_trace; { (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st DurationANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: echo stdout:; cat "$at_stdout" at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:96" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_60 #AT_START_61 at_fn_group_banner 61 'testsuite.at:97' \ "DurationFactoryANSITest" " " 4 at_xfail=no ( $as_echo "61. $at_setup_line: testing $at_desc ..." $at_traceon case $AUTOTEST_PATH in tests) image_path="-I $abs_builddir/gst.im" ;; *) image_path="-I $abs_builddir/gst.im" ;; esac echo "{ (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st DurationFactoryANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:97: { (cd \$abs_top_builddir && \$TIMEOUT gst \$image_path -f \$abs_srcdir/AnsiRun.st DurationFactoryANSITest); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:97" ( $at_check_trace; { (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st DurationFactoryANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: echo stdout:; cat "$at_stdout" at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:97" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_61 #AT_START_62 at_fn_group_banner 62 'testsuite.at:98' \ "DyadicValuableANSITest" " " 4 at_xfail=no ( $as_echo "62. $at_setup_line: testing $at_desc ..." $at_traceon case $AUTOTEST_PATH in tests) image_path="-I $abs_builddir/gst.im" ;; *) image_path="-I $abs_builddir/gst.im" ;; esac echo "{ (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st DyadicValuableANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:98: { (cd \$abs_top_builddir && \$TIMEOUT gst \$image_path -f \$abs_srcdir/AnsiRun.st DyadicValuableANSITest); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:98" ( $at_check_trace; { (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st DyadicValuableANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: echo stdout:; cat "$at_stdout" at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:98" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_62 #AT_START_63 at_fn_group_banner 63 'testsuite.at:99' \ "ErrorANSITest" " " 4 at_xfail=no ( $as_echo "63. $at_setup_line: testing $at_desc ..." $at_traceon case $AUTOTEST_PATH in tests) image_path="-I $abs_builddir/gst.im" ;; *) image_path="-I $abs_builddir/gst.im" ;; esac echo "{ (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st ErrorANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:99: { (cd \$abs_top_builddir && \$TIMEOUT gst \$image_path -f \$abs_srcdir/AnsiRun.st ErrorANSITest); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:99" ( $at_check_trace; { (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st ErrorANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: echo stdout:; cat "$at_stdout" at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:99" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_63 #AT_START_64 at_fn_group_banner 64 'testsuite.at:100' \ "ErrorClassANSITest" " " 4 at_xfail=no ( $as_echo "64. $at_setup_line: testing $at_desc ..." $at_traceon case $AUTOTEST_PATH in tests) image_path="-I $abs_builddir/gst.im" ;; *) image_path="-I $abs_builddir/gst.im" ;; esac echo "{ (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st ErrorClassANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:100: { (cd \$abs_top_builddir && \$TIMEOUT gst \$image_path -f \$abs_srcdir/AnsiRun.st ErrorClassANSITest); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:100" ( $at_check_trace; { (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st ErrorClassANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: echo stdout:; cat "$at_stdout" at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:100" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_64 #AT_START_65 at_fn_group_banner 65 'testsuite.at:101' \ "ExceptionANSITest" " " 4 at_xfail=no ( $as_echo "65. $at_setup_line: testing $at_desc ..." $at_traceon case $AUTOTEST_PATH in tests) image_path="-I $abs_builddir/gst.im" ;; *) image_path="-I $abs_builddir/gst.im" ;; esac echo "{ (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st ExceptionANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:101: { (cd \$abs_top_builddir && \$TIMEOUT gst \$image_path -f \$abs_srcdir/AnsiRun.st ExceptionANSITest); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:101" ( $at_check_trace; { (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st ExceptionANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: echo stdout:; cat "$at_stdout" at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:101" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_65 #AT_START_66 at_fn_group_banner 66 'testsuite.at:102' \ "ExceptionClassANSITest" " " 4 at_xfail=no ( $as_echo "66. $at_setup_line: testing $at_desc ..." $at_traceon case $AUTOTEST_PATH in tests) image_path="-I $abs_builddir/gst.im" ;; *) image_path="-I $abs_builddir/gst.im" ;; esac echo "{ (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st ExceptionClassANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:102: { (cd \$abs_top_builddir && \$TIMEOUT gst \$image_path -f \$abs_srcdir/AnsiRun.st ExceptionClassANSITest); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:102" ( $at_check_trace; { (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st ExceptionClassANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: echo stdout:; cat "$at_stdout" at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:102" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_66 #AT_START_67 at_fn_group_banner 67 'testsuite.at:103' \ "ExceptionSetANSITest" " " 4 at_xfail=no ( $as_echo "67. $at_setup_line: testing $at_desc ..." $at_traceon case $AUTOTEST_PATH in tests) image_path="-I $abs_builddir/gst.im" ;; *) image_path="-I $abs_builddir/gst.im" ;; esac echo "{ (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st ExceptionSetANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:103: { (cd \$abs_top_builddir && \$TIMEOUT gst \$image_path -f \$abs_srcdir/AnsiRun.st ExceptionSetANSITest); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:103" ( $at_check_trace; { (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st ExceptionSetANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: echo stdout:; cat "$at_stdout" at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:103" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_67 #AT_START_68 at_fn_group_banner 68 'testsuite.at:104' \ "FailedMessageANSITest" " " 4 at_xfail=no ( $as_echo "68. $at_setup_line: testing $at_desc ..." $at_traceon case $AUTOTEST_PATH in tests) image_path="-I $abs_builddir/gst.im" ;; *) image_path="-I $abs_builddir/gst.im" ;; esac echo "{ (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st FailedMessageANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:104: { (cd \$abs_top_builddir && \$TIMEOUT gst \$image_path -f \$abs_srcdir/AnsiRun.st FailedMessageANSITest); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:104" ( $at_check_trace; { (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st FailedMessageANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: echo stdout:; cat "$at_stdout" at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:104" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_68 #AT_START_69 at_fn_group_banner 69 'testsuite.at:105' \ "FileStreamFactoryANSITest" " " 4 at_xfail=no ( $as_echo "69. $at_setup_line: testing $at_desc ..." $at_traceon case $AUTOTEST_PATH in tests) image_path="-I $abs_builddir/gst.im" ;; *) image_path="-I $abs_builddir/gst.im" ;; esac echo "{ (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st FileStreamFactoryANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:105: { (cd \$abs_top_builddir && \$TIMEOUT gst \$image_path -f \$abs_srcdir/AnsiRun.st FileStreamFactoryANSITest); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:105" ( $at_check_trace; { (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st FileStreamFactoryANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: echo stdout:; cat "$at_stdout" at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:105" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_69 #AT_START_70 at_fn_group_banner 70 'testsuite.at:106' \ "FloatANSITest" " " 4 at_xfail=no ( $as_echo "70. $at_setup_line: testing $at_desc ..." $at_traceon case $AUTOTEST_PATH in tests) image_path="-I $abs_builddir/gst.im" ;; *) image_path="-I $abs_builddir/gst.im" ;; esac echo "{ (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st FloatANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:106: { (cd \$abs_top_builddir && \$TIMEOUT gst \$image_path -f \$abs_srcdir/AnsiRun.st FloatANSITest); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:106" ( $at_check_trace; { (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st FloatANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: echo stdout:; cat "$at_stdout" at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:106" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_70 #AT_START_71 at_fn_group_banner 71 'testsuite.at:107' \ "FloatCharacterizationANSITest" " " 4 at_xfail=no ( $as_echo "71. $at_setup_line: testing $at_desc ..." $at_traceon case $AUTOTEST_PATH in tests) image_path="-I $abs_builddir/gst.im" ;; *) image_path="-I $abs_builddir/gst.im" ;; esac echo "{ (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st FloatCharacterizationANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:107: { (cd \$abs_top_builddir && \$TIMEOUT gst \$image_path -f \$abs_srcdir/AnsiRun.st FloatCharacterizationANSITest); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:107" ( $at_check_trace; { (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st FloatCharacterizationANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: echo stdout:; cat "$at_stdout" at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:107" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_71 #AT_START_72 at_fn_group_banner 72 'testsuite.at:108' \ "FractionANSITest" " " 4 at_xfail=no ( $as_echo "72. $at_setup_line: testing $at_desc ..." $at_traceon case $AUTOTEST_PATH in tests) image_path="-I $abs_builddir/gst.im" ;; *) image_path="-I $abs_builddir/gst.im" ;; esac echo "{ (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st FractionANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:108: { (cd \$abs_top_builddir && \$TIMEOUT gst \$image_path -f \$abs_srcdir/AnsiRun.st FractionANSITest); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:108" ( $at_check_trace; { (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st FractionANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: echo stdout:; cat "$at_stdout" at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:108" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_72 #AT_START_73 at_fn_group_banner 73 'testsuite.at:109' \ "FractionFactoryANSITest" " " 4 at_xfail=no ( $as_echo "73. $at_setup_line: testing $at_desc ..." $at_traceon case $AUTOTEST_PATH in tests) image_path="-I $abs_builddir/gst.im" ;; *) image_path="-I $abs_builddir/gst.im" ;; esac echo "{ (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st FractionFactoryANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:109: { (cd \$abs_top_builddir && \$TIMEOUT gst \$image_path -f \$abs_srcdir/AnsiRun.st FractionFactoryANSITest); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:109" ( $at_check_trace; { (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st FractionFactoryANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: echo stdout:; cat "$at_stdout" at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:109" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_73 #AT_START_74 at_fn_group_banner 74 'testsuite.at:110' \ "IdentityDictionaryANSITest" " " 4 at_xfail=no ( $as_echo "74. $at_setup_line: testing $at_desc ..." $at_traceon case $AUTOTEST_PATH in tests) image_path="-I $abs_builddir/gst.im" ;; *) image_path="-I $abs_builddir/gst.im" ;; esac echo "{ (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st IdentityDictionaryANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:110: { (cd \$abs_top_builddir && \$TIMEOUT gst \$image_path -f \$abs_srcdir/AnsiRun.st IdentityDictionaryANSITest); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:110" ( $at_check_trace; { (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st IdentityDictionaryANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: echo stdout:; cat "$at_stdout" at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:110" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_74 #AT_START_75 at_fn_group_banner 75 'testsuite.at:111' \ "IdentityDictionaryFactoryANSITest" " " 4 at_xfail=no ( $as_echo "75. $at_setup_line: testing $at_desc ..." $at_traceon case $AUTOTEST_PATH in tests) image_path="-I $abs_builddir/gst.im" ;; *) image_path="-I $abs_builddir/gst.im" ;; esac echo "{ (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st IdentityDictionaryFactoryANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:111: { (cd \$abs_top_builddir && \$TIMEOUT gst \$image_path -f \$abs_srcdir/AnsiRun.st IdentityDictionaryFactoryANSITest); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:111" ( $at_check_trace; { (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st IdentityDictionaryFactoryANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: echo stdout:; cat "$at_stdout" at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:111" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_75 #AT_START_76 at_fn_group_banner 76 'testsuite.at:112' \ "IntegerANSITest" " " 4 at_xfail=no ( $as_echo "76. $at_setup_line: testing $at_desc ..." $at_traceon case $AUTOTEST_PATH in tests) image_path="-I $abs_builddir/gst.im" ;; *) image_path="-I $abs_builddir/gst.im" ;; esac echo "{ (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st IntegerANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:112: { (cd \$abs_top_builddir && \$TIMEOUT gst \$image_path -f \$abs_srcdir/AnsiRun.st IntegerANSITest); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:112" ( $at_check_trace; { (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st IntegerANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: echo stdout:; cat "$at_stdout" at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:112" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_76 #AT_START_77 at_fn_group_banner 77 'testsuite.at:113' \ "IntervalANSITest" " " 4 at_xfail=no ( $as_echo "77. $at_setup_line: testing $at_desc ..." $at_traceon case $AUTOTEST_PATH in tests) image_path="-I $abs_builddir/gst.im" ;; *) image_path="-I $abs_builddir/gst.im" ;; esac echo "{ (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st IntervalANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:113: { (cd \$abs_top_builddir && \$TIMEOUT gst \$image_path -f \$abs_srcdir/AnsiRun.st IntervalANSITest); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:113" ( $at_check_trace; { (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st IntervalANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: echo stdout:; cat "$at_stdout" at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:113" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_77 #AT_START_78 at_fn_group_banner 78 'testsuite.at:114' \ "IntervalFactoryANSITest" " " 4 at_xfail=no ( $as_echo "78. $at_setup_line: testing $at_desc ..." $at_traceon case $AUTOTEST_PATH in tests) image_path="-I $abs_builddir/gst.im" ;; *) image_path="-I $abs_builddir/gst.im" ;; esac echo "{ (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st IntervalFactoryANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:114: { (cd \$abs_top_builddir && \$TIMEOUT gst \$image_path -f \$abs_srcdir/AnsiRun.st IntervalFactoryANSITest); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:114" ( $at_check_trace; { (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st IntervalFactoryANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: echo stdout:; cat "$at_stdout" at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:114" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_78 #AT_START_79 at_fn_group_banner 79 'testsuite.at:115' \ "MessageNotUnderstoodANSITest" " " 4 at_xfail=no ( $as_echo "79. $at_setup_line: testing $at_desc ..." $at_traceon case $AUTOTEST_PATH in tests) image_path="-I $abs_builddir/gst.im" ;; *) image_path="-I $abs_builddir/gst.im" ;; esac echo "{ (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st MessageNotUnderstoodANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:115: { (cd \$abs_top_builddir && \$TIMEOUT gst \$image_path -f \$abs_srcdir/AnsiRun.st MessageNotUnderstoodANSITest); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:115" ( $at_check_trace; { (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st MessageNotUnderstoodANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: echo stdout:; cat "$at_stdout" at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:115" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_79 #AT_START_80 at_fn_group_banner 80 'testsuite.at:116' \ "MessageNotUnderstoodSelectorANSITest" " " 4 at_xfail=no ( $as_echo "80. $at_setup_line: testing $at_desc ..." $at_traceon case $AUTOTEST_PATH in tests) image_path="-I $abs_builddir/gst.im" ;; *) image_path="-I $abs_builddir/gst.im" ;; esac echo "{ (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st MessageNotUnderstoodSelectorANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:116: { (cd \$abs_top_builddir && \$TIMEOUT gst \$image_path -f \$abs_srcdir/AnsiRun.st MessageNotUnderstoodSelectorANSITest); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:116" ( $at_check_trace; { (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st MessageNotUnderstoodSelectorANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: echo stdout:; cat "$at_stdout" at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:116" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_80 #AT_START_81 at_fn_group_banner 81 'testsuite.at:117' \ "MonadicBlockANSITest" " " 4 at_xfail=no ( $as_echo "81. $at_setup_line: testing $at_desc ..." $at_traceon case $AUTOTEST_PATH in tests) image_path="-I $abs_builddir/gst.im" ;; *) image_path="-I $abs_builddir/gst.im" ;; esac echo "{ (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st MonadicBlockANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:117: { (cd \$abs_top_builddir && \$TIMEOUT gst \$image_path -f \$abs_srcdir/AnsiRun.st MonadicBlockANSITest); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:117" ( $at_check_trace; { (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st MonadicBlockANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: echo stdout:; cat "$at_stdout" at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:117" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_81 #AT_START_82 at_fn_group_banner 82 'testsuite.at:118' \ "NilANSITest" " " 4 at_xfail=no ( $as_echo "82. $at_setup_line: testing $at_desc ..." $at_traceon case $AUTOTEST_PATH in tests) image_path="-I $abs_builddir/gst.im" ;; *) image_path="-I $abs_builddir/gst.im" ;; esac echo "{ (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st NilANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:118: { (cd \$abs_top_builddir && \$TIMEOUT gst \$image_path -f \$abs_srcdir/AnsiRun.st NilANSITest); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:118" ( $at_check_trace; { (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st NilANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: echo stdout:; cat "$at_stdout" at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:118" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_82 #AT_START_83 at_fn_group_banner 83 'testsuite.at:119' \ "NiladicBlockANSITest" " " 4 at_xfail=no ( $as_echo "83. $at_setup_line: testing $at_desc ..." $at_traceon case $AUTOTEST_PATH in tests) image_path="-I $abs_builddir/gst.im" ;; *) image_path="-I $abs_builddir/gst.im" ;; esac echo "{ (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st NiladicBlockANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:119: { (cd \$abs_top_builddir && \$TIMEOUT gst \$image_path -f \$abs_srcdir/AnsiRun.st NiladicBlockANSITest); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:119" ( $at_check_trace; { (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st NiladicBlockANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: echo stdout:; cat "$at_stdout" at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:119" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_83 #AT_START_84 at_fn_group_banner 84 'testsuite.at:120' \ "NotificationANSITest" " " 4 at_xfail=no ( $as_echo "84. $at_setup_line: testing $at_desc ..." $at_traceon case $AUTOTEST_PATH in tests) image_path="-I $abs_builddir/gst.im" ;; *) image_path="-I $abs_builddir/gst.im" ;; esac echo "{ (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st NotificationANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:120: { (cd \$abs_top_builddir && \$TIMEOUT gst \$image_path -f \$abs_srcdir/AnsiRun.st NotificationANSITest); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:120" ( $at_check_trace; { (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st NotificationANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: echo stdout:; cat "$at_stdout" at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:120" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_84 #AT_START_85 at_fn_group_banner 85 'testsuite.at:121' \ "NotificationClassANSITest" " " 4 at_xfail=no ( $as_echo "85. $at_setup_line: testing $at_desc ..." $at_traceon case $AUTOTEST_PATH in tests) image_path="-I $abs_builddir/gst.im" ;; *) image_path="-I $abs_builddir/gst.im" ;; esac echo "{ (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st NotificationClassANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:121: { (cd \$abs_top_builddir && \$TIMEOUT gst \$image_path -f \$abs_srcdir/AnsiRun.st NotificationClassANSITest); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:121" ( $at_check_trace; { (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st NotificationClassANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: echo stdout:; cat "$at_stdout" at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:121" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_85 #AT_START_86 at_fn_group_banner 86 'testsuite.at:122' \ "ObjectANSITest" " " 4 at_xfail=no ( $as_echo "86. $at_setup_line: testing $at_desc ..." $at_traceon case $AUTOTEST_PATH in tests) image_path="-I $abs_builddir/gst.im" ;; *) image_path="-I $abs_builddir/gst.im" ;; esac echo "{ (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st ObjectANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:122: { (cd \$abs_top_builddir && \$TIMEOUT gst \$image_path -f \$abs_srcdir/AnsiRun.st ObjectANSITest); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:122" ( $at_check_trace; { (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st ObjectANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: echo stdout:; cat "$at_stdout" at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:122" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_86 #AT_START_87 at_fn_group_banner 87 'testsuite.at:123' \ "ObjectClassANSITest" " " 4 at_xfail=no ( $as_echo "87. $at_setup_line: testing $at_desc ..." $at_traceon case $AUTOTEST_PATH in tests) image_path="-I $abs_builddir/gst.im" ;; *) image_path="-I $abs_builddir/gst.im" ;; esac echo "{ (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st ObjectClassANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:123: { (cd \$abs_top_builddir && \$TIMEOUT gst \$image_path -f \$abs_srcdir/AnsiRun.st ObjectClassANSITest); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:123" ( $at_check_trace; { (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st ObjectClassANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: echo stdout:; cat "$at_stdout" at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:123" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_87 #AT_START_88 at_fn_group_banner 88 'testsuite.at:124' \ "OrderedCollectionANSITest" " " 4 at_xfail=no ( $as_echo "88. $at_setup_line: testing $at_desc ..." $at_traceon case $AUTOTEST_PATH in tests) image_path="-I $abs_builddir/gst.im" ;; *) image_path="-I $abs_builddir/gst.im" ;; esac echo "{ (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st OrderedCollectionANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:124: { (cd \$abs_top_builddir && \$TIMEOUT gst \$image_path -f \$abs_srcdir/AnsiRun.st OrderedCollectionANSITest); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:124" ( $at_check_trace; { (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st OrderedCollectionANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: echo stdout:; cat "$at_stdout" at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:124" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_88 #AT_START_89 at_fn_group_banner 89 'testsuite.at:125' \ "OrderedCollectionFactoryANSITest" " " 4 at_xfail=no ( $as_echo "89. $at_setup_line: testing $at_desc ..." $at_traceon case $AUTOTEST_PATH in tests) image_path="-I $abs_builddir/gst.im" ;; *) image_path="-I $abs_builddir/gst.im" ;; esac echo "{ (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st OrderedCollectionFactoryANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:125: { (cd \$abs_top_builddir && \$TIMEOUT gst \$image_path -f \$abs_srcdir/AnsiRun.st OrderedCollectionFactoryANSITest); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:125" ( $at_check_trace; { (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st OrderedCollectionFactoryANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: echo stdout:; cat "$at_stdout" at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:125" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_89 #AT_START_90 at_fn_group_banner 90 'testsuite.at:126' \ "ReadFileStreamANSITest" " " 4 at_xfail=no ( $as_echo "90. $at_setup_line: testing $at_desc ..." $at_traceon case $AUTOTEST_PATH in tests) image_path="-I $abs_builddir/gst.im" ;; *) image_path="-I $abs_builddir/gst.im" ;; esac echo "{ (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st ReadFileStreamANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:126: { (cd \$abs_top_builddir && \$TIMEOUT gst \$image_path -f \$abs_srcdir/AnsiRun.st ReadFileStreamANSITest); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:126" ( $at_check_trace; { (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st ReadFileStreamANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: echo stdout:; cat "$at_stdout" at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:126" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_90 #AT_START_91 at_fn_group_banner 91 'testsuite.at:127' \ "ReadStreamANSITest" " " 4 at_xfail=no ( $as_echo "91. $at_setup_line: testing $at_desc ..." $at_traceon case $AUTOTEST_PATH in tests) image_path="-I $abs_builddir/gst.im" ;; *) image_path="-I $abs_builddir/gst.im" ;; esac echo "{ (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st ReadStreamANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:127: { (cd \$abs_top_builddir && \$TIMEOUT gst \$image_path -f \$abs_srcdir/AnsiRun.st ReadStreamANSITest); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:127" ( $at_check_trace; { (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st ReadStreamANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: echo stdout:; cat "$at_stdout" at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:127" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_91 #AT_START_92 at_fn_group_banner 92 'testsuite.at:128' \ "ReadStreamFactoryANSITest" " " 4 at_xfail=no ( $as_echo "92. $at_setup_line: testing $at_desc ..." $at_traceon case $AUTOTEST_PATH in tests) image_path="-I $abs_builddir/gst.im" ;; *) image_path="-I $abs_builddir/gst.im" ;; esac echo "{ (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st ReadStreamFactoryANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:128: { (cd \$abs_top_builddir && \$TIMEOUT gst \$image_path -f \$abs_srcdir/AnsiRun.st ReadStreamFactoryANSITest); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:128" ( $at_check_trace; { (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st ReadStreamFactoryANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: echo stdout:; cat "$at_stdout" at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:128" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_92 #AT_START_93 at_fn_group_banner 93 'testsuite.at:129' \ "ReadWriteStreamANSITest" " " 4 at_xfail=no ( $as_echo "93. $at_setup_line: testing $at_desc ..." $at_traceon case $AUTOTEST_PATH in tests) image_path="-I $abs_builddir/gst.im" ;; *) image_path="-I $abs_builddir/gst.im" ;; esac echo "{ (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st ReadWriteStreamANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:129: { (cd \$abs_top_builddir && \$TIMEOUT gst \$image_path -f \$abs_srcdir/AnsiRun.st ReadWriteStreamANSITest); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:129" ( $at_check_trace; { (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st ReadWriteStreamANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: echo stdout:; cat "$at_stdout" at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:129" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_93 #AT_START_94 at_fn_group_banner 94 'testsuite.at:130' \ "ReadWriteStreamFactoryANSITest" " " 4 at_xfail=no ( $as_echo "94. $at_setup_line: testing $at_desc ..." $at_traceon case $AUTOTEST_PATH in tests) image_path="-I $abs_builddir/gst.im" ;; *) image_path="-I $abs_builddir/gst.im" ;; esac echo "{ (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st ReadWriteStreamFactoryANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:130: { (cd \$abs_top_builddir && \$TIMEOUT gst \$image_path -f \$abs_srcdir/AnsiRun.st ReadWriteStreamFactoryANSITest); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:130" ( $at_check_trace; { (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st ReadWriteStreamFactoryANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: echo stdout:; cat "$at_stdout" at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:130" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_94 #AT_START_95 at_fn_group_banner 95 'testsuite.at:131' \ "ScaledDecimalANSITest" " " 4 at_xfail=no ( $as_echo "95. $at_setup_line: testing $at_desc ..." $at_traceon case $AUTOTEST_PATH in tests) image_path="-I $abs_builddir/gst.im" ;; *) image_path="-I $abs_builddir/gst.im" ;; esac echo "{ (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st ScaledDecimalANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:131: { (cd \$abs_top_builddir && \$TIMEOUT gst \$image_path -f \$abs_srcdir/AnsiRun.st ScaledDecimalANSITest); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:131" ( $at_check_trace; { (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st ScaledDecimalANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: echo stdout:; cat "$at_stdout" at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:131" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_95 #AT_START_96 at_fn_group_banner 96 'testsuite.at:132' \ "SelectorANSITest" " " 4 at_xfail=no ( $as_echo "96. $at_setup_line: testing $at_desc ..." $at_traceon case $AUTOTEST_PATH in tests) image_path="-I $abs_builddir/gst.im" ;; *) image_path="-I $abs_builddir/gst.im" ;; esac echo "{ (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st SelectorANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:132: { (cd \$abs_top_builddir && \$TIMEOUT gst \$image_path -f \$abs_srcdir/AnsiRun.st SelectorANSITest); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:132" ( $at_check_trace; { (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st SelectorANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: echo stdout:; cat "$at_stdout" at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:132" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_96 #AT_START_97 at_fn_group_banner 97 'testsuite.at:133' \ "SetANSITest" " " 4 at_xfail=no ( $as_echo "97. $at_setup_line: testing $at_desc ..." $at_traceon case $AUTOTEST_PATH in tests) image_path="-I $abs_builddir/gst.im" ;; *) image_path="-I $abs_builddir/gst.im" ;; esac echo "{ (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st SetANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:133: { (cd \$abs_top_builddir && \$TIMEOUT gst \$image_path -f \$abs_srcdir/AnsiRun.st SetANSITest); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:133" ( $at_check_trace; { (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st SetANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: echo stdout:; cat "$at_stdout" at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:133" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_97 #AT_START_98 at_fn_group_banner 98 'testsuite.at:134' \ "SetFactoryANSITest" " " 4 at_xfail=no ( $as_echo "98. $at_setup_line: testing $at_desc ..." $at_traceon case $AUTOTEST_PATH in tests) image_path="-I $abs_builddir/gst.im" ;; *) image_path="-I $abs_builddir/gst.im" ;; esac echo "{ (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st SetFactoryANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:134: { (cd \$abs_top_builddir && \$TIMEOUT gst \$image_path -f \$abs_srcdir/AnsiRun.st SetFactoryANSITest); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:134" ( $at_check_trace; { (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st SetFactoryANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: echo stdout:; cat "$at_stdout" at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:134" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_98 #AT_START_99 at_fn_group_banner 99 'testsuite.at:135' \ "SortedCollectionANSITest" " " 4 at_xfail=no ( $as_echo "99. $at_setup_line: testing $at_desc ..." $at_traceon case $AUTOTEST_PATH in tests) image_path="-I $abs_builddir/gst.im" ;; *) image_path="-I $abs_builddir/gst.im" ;; esac echo "{ (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st SortedCollectionANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:135: { (cd \$abs_top_builddir && \$TIMEOUT gst \$image_path -f \$abs_srcdir/AnsiRun.st SortedCollectionANSITest); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:135" ( $at_check_trace; { (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st SortedCollectionANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: echo stdout:; cat "$at_stdout" at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:135" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_99 #AT_START_100 at_fn_group_banner 100 'testsuite.at:136' \ "SortedCollectionFactoryANSITest" " " 4 at_xfail=no ( $as_echo "100. $at_setup_line: testing $at_desc ..." $at_traceon case $AUTOTEST_PATH in tests) image_path="-I $abs_builddir/gst.im" ;; *) image_path="-I $abs_builddir/gst.im" ;; esac echo "{ (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st SortedCollectionFactoryANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:136: { (cd \$abs_top_builddir && \$TIMEOUT gst \$image_path -f \$abs_srcdir/AnsiRun.st SortedCollectionFactoryANSITest); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:136" ( $at_check_trace; { (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st SortedCollectionFactoryANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: echo stdout:; cat "$at_stdout" at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:136" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_100 #AT_START_101 at_fn_group_banner 101 'testsuite.at:137' \ "StringANSITest" " " 4 at_xfail=no ( $as_echo "101. $at_setup_line: testing $at_desc ..." $at_traceon case $AUTOTEST_PATH in tests) image_path="-I $abs_builddir/gst.im" ;; *) image_path="-I $abs_builddir/gst.im" ;; esac echo "{ (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st StringANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:137: { (cd \$abs_top_builddir && \$TIMEOUT gst \$image_path -f \$abs_srcdir/AnsiRun.st StringANSITest); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:137" ( $at_check_trace; { (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st StringANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: echo stdout:; cat "$at_stdout" at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:137" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_101 #AT_START_102 at_fn_group_banner 102 'testsuite.at:138' \ "StringFactoryANSITest" " " 4 at_xfail=no ( $as_echo "102. $at_setup_line: testing $at_desc ..." $at_traceon case $AUTOTEST_PATH in tests) image_path="-I $abs_builddir/gst.im" ;; *) image_path="-I $abs_builddir/gst.im" ;; esac echo "{ (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st StringFactoryANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:138: { (cd \$abs_top_builddir && \$TIMEOUT gst \$image_path -f \$abs_srcdir/AnsiRun.st StringFactoryANSITest); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:138" ( $at_check_trace; { (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st StringFactoryANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: echo stdout:; cat "$at_stdout" at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:138" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_102 #AT_START_103 at_fn_group_banner 103 'testsuite.at:139' \ "SymbolANSITest" " " 4 at_xfail=no ( $as_echo "103. $at_setup_line: testing $at_desc ..." $at_traceon case $AUTOTEST_PATH in tests) image_path="-I $abs_builddir/gst.im" ;; *) image_path="-I $abs_builddir/gst.im" ;; esac echo "{ (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st SymbolANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:139: { (cd \$abs_top_builddir && \$TIMEOUT gst \$image_path -f \$abs_srcdir/AnsiRun.st SymbolANSITest); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:139" ( $at_check_trace; { (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st SymbolANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: echo stdout:; cat "$at_stdout" at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:139" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_103 #AT_START_104 at_fn_group_banner 104 'testsuite.at:140' \ "TranscriptANSITest" " " 4 at_xfail=no ( $as_echo "104. $at_setup_line: testing $at_desc ..." $at_traceon case $AUTOTEST_PATH in tests) image_path="-I $abs_builddir/gst.im" ;; *) image_path="-I $abs_builddir/gst.im" ;; esac echo "{ (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st TranscriptANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:140: { (cd \$abs_top_builddir && \$TIMEOUT gst \$image_path -f \$abs_srcdir/AnsiRun.st TranscriptANSITest); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:140" ( $at_check_trace; { (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st TranscriptANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: echo stdout:; cat "$at_stdout" at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:140" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_104 #AT_START_105 at_fn_group_banner 105 'testsuite.at:141' \ "WarningANSITest" " " 4 at_xfail=no ( $as_echo "105. $at_setup_line: testing $at_desc ..." $at_traceon case $AUTOTEST_PATH in tests) image_path="-I $abs_builddir/gst.im" ;; *) image_path="-I $abs_builddir/gst.im" ;; esac echo "{ (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st WarningANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:141: { (cd \$abs_top_builddir && \$TIMEOUT gst \$image_path -f \$abs_srcdir/AnsiRun.st WarningANSITest); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:141" ( $at_check_trace; { (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st WarningANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: echo stdout:; cat "$at_stdout" at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:141" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_105 #AT_START_106 at_fn_group_banner 106 'testsuite.at:142' \ "WarningClassANSITest" " " 4 at_xfail=no ( $as_echo "106. $at_setup_line: testing $at_desc ..." $at_traceon case $AUTOTEST_PATH in tests) image_path="-I $abs_builddir/gst.im" ;; *) image_path="-I $abs_builddir/gst.im" ;; esac echo "{ (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st WarningClassANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:142: { (cd \$abs_top_builddir && \$TIMEOUT gst \$image_path -f \$abs_srcdir/AnsiRun.st WarningClassANSITest); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:142" ( $at_check_trace; { (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st WarningClassANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: echo stdout:; cat "$at_stdout" at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:142" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_106 #AT_START_107 at_fn_group_banner 107 'testsuite.at:143' \ "WriteFileStreamANSITest" " " 4 at_xfail=no ( $as_echo "107. $at_setup_line: testing $at_desc ..." $at_traceon case $AUTOTEST_PATH in tests) image_path="-I $abs_builddir/gst.im" ;; *) image_path="-I $abs_builddir/gst.im" ;; esac echo "{ (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st WriteFileStreamANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:143: { (cd \$abs_top_builddir && \$TIMEOUT gst \$image_path -f \$abs_srcdir/AnsiRun.st WriteFileStreamANSITest); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:143" ( $at_check_trace; { (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st WriteFileStreamANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: echo stdout:; cat "$at_stdout" at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:143" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_107 #AT_START_108 at_fn_group_banner 108 'testsuite.at:144' \ "WriteStreamANSITest" " " 4 at_xfail=no ( $as_echo "108. $at_setup_line: testing $at_desc ..." $at_traceon case $AUTOTEST_PATH in tests) image_path="-I $abs_builddir/gst.im" ;; *) image_path="-I $abs_builddir/gst.im" ;; esac echo "{ (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st WriteStreamANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:144: { (cd \$abs_top_builddir && \$TIMEOUT gst \$image_path -f \$abs_srcdir/AnsiRun.st WriteStreamANSITest); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:144" ( $at_check_trace; { (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st WriteStreamANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: echo stdout:; cat "$at_stdout" at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:144" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_108 #AT_START_109 at_fn_group_banner 109 'testsuite.at:145' \ "WriteStreamFactoryANSITest" " " 4 at_xfail=no ( $as_echo "109. $at_setup_line: testing $at_desc ..." $at_traceon case $AUTOTEST_PATH in tests) image_path="-I $abs_builddir/gst.im" ;; *) image_path="-I $abs_builddir/gst.im" ;; esac echo "{ (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st WriteStreamFactoryANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:145: { (cd \$abs_top_builddir && \$TIMEOUT gst \$image_path -f \$abs_srcdir/AnsiRun.st WriteStreamFactoryANSITest); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:145" ( $at_check_trace; { (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st WriteStreamFactoryANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: echo stdout:; cat "$at_stdout" at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:145" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_109 #AT_START_110 at_fn_group_banner 110 'testsuite.at:146' \ "ZeroDivideANSITest" " " 4 at_xfail=no ( $as_echo "110. $at_setup_line: testing $at_desc ..." $at_traceon case $AUTOTEST_PATH in tests) image_path="-I $abs_builddir/gst.im" ;; *) image_path="-I $abs_builddir/gst.im" ;; esac echo "{ (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st ZeroDivideANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:146: { (cd \$abs_top_builddir && \$TIMEOUT gst \$image_path -f \$abs_srcdir/AnsiRun.st ZeroDivideANSITest); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:146" ( $at_check_trace; { (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st ZeroDivideANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: echo stdout:; cat "$at_stdout" at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:146" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_110 #AT_START_111 at_fn_group_banner 111 'testsuite.at:147' \ "ZeroDivideFactoryANSITest" " " 4 at_xfail=no ( $as_echo "111. $at_setup_line: testing $at_desc ..." $at_traceon case $AUTOTEST_PATH in tests) image_path="-I $abs_builddir/gst.im" ;; *) image_path="-I $abs_builddir/gst.im" ;; esac echo "{ (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st ZeroDivideFactoryANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:147: { (cd \$abs_top_builddir && \$TIMEOUT gst \$image_path -f \$abs_srcdir/AnsiRun.st ZeroDivideFactoryANSITest); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:147" ( $at_check_trace; { (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_srcdir/AnsiRun.st ZeroDivideFactoryANSITest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: echo stdout:; cat "$at_stdout" at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:147" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_111 #AT_START_112 at_fn_group_banner 112 'testsuite.at:150' \ "Announcements" " " 5 at_xfail=no ( $as_echo "112. $at_setup_line: testing $at_desc ..." $at_traceon case $AUTOTEST_PATH in tests) image_path="-I $abs_top_builddir/gst.im" ;; *) image_path="" ;; esac echo "{ (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_top_srcdir/scripts/Test.st --verbose -p Announcements); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:150: { (cd \$abs_top_builddir && \$TIMEOUT gst \$image_path -f \$abs_top_srcdir/scripts/Test.st --verbose -p Announcements); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:150" ( $at_check_trace; { (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_top_srcdir/scripts/Test.st --verbose -p Announcements); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: echo stdout:; cat "$at_stdout" at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:150" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_112 #AT_START_113 at_fn_group_banner 113 'testsuite.at:151' \ "Complex" " " 5 at_xfail=no ( $as_echo "113. $at_setup_line: testing $at_desc ..." $at_traceon case $AUTOTEST_PATH in tests) image_path="-I $abs_top_builddir/gst.im" ;; *) image_path="" ;; esac echo "{ (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_top_srcdir/scripts/Test.st --verbose -p Complex); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:151: { (cd \$abs_top_builddir && \$TIMEOUT gst \$image_path -f \$abs_top_srcdir/scripts/Test.st --verbose -p Complex); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:151" ( $at_check_trace; { (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_top_srcdir/scripts/Test.st --verbose -p Complex); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: echo stdout:; cat "$at_stdout" at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:151" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_113 #AT_START_114 at_fn_group_banner 114 'testsuite.at:152' \ "Continuations" " " 5 at_xfail=no ( $as_echo "114. $at_setup_line: testing $at_desc ..." $at_traceon case $AUTOTEST_PATH in tests) image_path="-I $abs_top_builddir/gst.im" ;; *) image_path="" ;; esac echo "{ (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_top_srcdir/scripts/Test.st --verbose -p Continuations); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:152: { (cd \$abs_top_builddir && \$TIMEOUT gst \$image_path -f \$abs_top_srcdir/scripts/Test.st --verbose -p Continuations); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:152" ( $at_check_trace; { (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_top_srcdir/scripts/Test.st --verbose -p Continuations); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: echo stdout:; cat "$at_stdout" at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:152" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_114 #AT_START_115 at_fn_group_banner 115 'testsuite.at:153' \ "DBD-MySQL" " " 5 at_xfail=no ( $as_echo "115. $at_setup_line: testing $at_desc ..." $at_traceon { set +x $as_echo "$at_srcdir/testsuite.at:153: test \"\$enable_mysql_tests\" != no || exit 77" at_fn_check_prepare_dynamic "test \"$enable_mysql_tests\" != no || exit 77" "testsuite.at:153" ( $at_check_trace; test "$enable_mysql_tests" != no || exit 77 ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: at_fn_diff_devnull "$at_stdout" || at_failed=: at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:153" $at_failed && at_fn_log_failure $at_traceon; } case $AUTOTEST_PATH in tests) image_path="-I $abs_top_builddir/gst.im" ;; *) image_path="" ;; esac echo "{ (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_top_srcdir/scripts/Test.st --verbose $mysqlvars -p DBD-MySQL); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:153: { (cd \$abs_top_builddir && \$TIMEOUT gst \$image_path -f \$abs_top_srcdir/scripts/Test.st --verbose \$mysqlvars -p DBD-MySQL); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:153" ( $at_check_trace; { (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_top_srcdir/scripts/Test.st --verbose $mysqlvars -p DBD-MySQL); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: echo stdout:; cat "$at_stdout" at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:153" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_115 #AT_START_116 at_fn_group_banner 116 'testsuite.at:154' \ "DBD-SQLite" " " 5 at_xfail=no ( $as_echo "116. $at_setup_line: testing $at_desc ..." $at_traceon case $AUTOTEST_PATH in tests) image_path="-I $abs_top_builddir/gst.im" ;; *) image_path="" ;; esac echo "{ (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_top_srcdir/scripts/Test.st --verbose -p DBD-SQLite ret=$? case $ret in 2) exit 77 ;; 0|1) exit $ret ;; esac); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:154: { (cd \$abs_top_builddir && \$TIMEOUT gst \$image_path -f \$abs_top_srcdir/scripts/Test.st --verbose -p DBD-SQLite ret=\$? case \$ret in 2) exit 77 ;; 0|1) exit \$ret ;; esac); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'an embedded newline' "testsuite.at:154" ( $at_check_trace; { (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_top_srcdir/scripts/Test.st --verbose -p DBD-SQLite ret=$? case $ret in 2) exit 77 ;; 0|1) exit $ret ;; esac); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: echo stdout:; cat "$at_stdout" at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:154" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_116 #AT_START_117 at_fn_group_banner 117 'testsuite.at:155' \ "DebugTools" " " 5 at_xfail=no ( $as_echo "117. $at_setup_line: testing $at_desc ..." $at_traceon case $AUTOTEST_PATH in tests) image_path="-I $abs_top_builddir/gst.im" ;; *) image_path="" ;; esac echo "{ (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_top_srcdir/scripts/Test.st --verbose -p DebugTools); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:155: { (cd \$abs_top_builddir && \$TIMEOUT gst \$image_path -f \$abs_top_srcdir/scripts/Test.st --verbose -p DebugTools); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:155" ( $at_check_trace; { (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_top_srcdir/scripts/Test.st --verbose -p DebugTools); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: echo stdout:; cat "$at_stdout" at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:155" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_117 #AT_START_118 at_fn_group_banner 118 'testsuite.at:156' \ "DhbNumericalMethods" " " 5 at_xfail=no ( $as_echo "118. $at_setup_line: testing $at_desc ..." $at_traceon case $AUTOTEST_PATH in tests) image_path="-I $abs_top_builddir/gst.im" ;; *) image_path="" ;; esac echo "{ (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_top_srcdir/scripts/Test.st --verbose -p DhbNumericalMethods); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:156: { (cd \$abs_top_builddir && \$TIMEOUT gst \$image_path -f \$abs_top_srcdir/scripts/Test.st --verbose -p DhbNumericalMethods); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:156" ( $at_check_trace; { (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_top_srcdir/scripts/Test.st --verbose -p DhbNumericalMethods); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: echo stdout:; cat "$at_stdout" at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:156" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_118 #AT_START_119 at_fn_group_banner 119 'testsuite.at:157' \ "Digest" " " 5 at_xfail=no ( $as_echo "119. $at_setup_line: testing $at_desc ..." $at_traceon case $AUTOTEST_PATH in tests) image_path="-I $abs_top_builddir/gst.im" ;; *) image_path="" ;; esac echo "{ (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_top_srcdir/scripts/Test.st --verbose -p Digest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:157: { (cd \$abs_top_builddir && \$TIMEOUT gst \$image_path -f \$abs_top_srcdir/scripts/Test.st --verbose -p Digest); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:157" ( $at_check_trace; { (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_top_srcdir/scripts/Test.st --verbose -p Digest); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: echo stdout:; cat "$at_stdout" at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:157" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_119 #AT_START_120 at_fn_group_banner 120 'testsuite.at:158' \ "GDBM" " " 5 at_xfail=no ( $as_echo "120. $at_setup_line: testing $at_desc ..." $at_traceon case $AUTOTEST_PATH in tests) image_path="-I $abs_top_builddir/gst.im" ;; *) image_path="" ;; esac echo "{ (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_top_srcdir/scripts/Test.st --verbose -p GDBM ret=$? case $ret in 2) exit 77 ;; 0|1) exit $ret ;; esac); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:158: { (cd \$abs_top_builddir && \$TIMEOUT gst \$image_path -f \$abs_top_srcdir/scripts/Test.st --verbose -p GDBM ret=\$? case \$ret in 2) exit 77 ;; 0|1) exit \$ret ;; esac); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'an embedded newline' "testsuite.at:158" ( $at_check_trace; { (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_top_srcdir/scripts/Test.st --verbose -p GDBM ret=$? case $ret in 2) exit 77 ;; 0|1) exit $ret ;; esac); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: echo stdout:; cat "$at_stdout" at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:158" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_120 #AT_START_121 at_fn_group_banner 121 'testsuite.at:159' \ "Iconv" " " 5 at_xfail=no ( $as_echo "121. $at_setup_line: testing $at_desc ..." $at_traceon case $AUTOTEST_PATH in tests) image_path="-I $abs_top_builddir/gst.im" ;; *) image_path="" ;; esac echo "{ (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_top_srcdir/scripts/Test.st --verbose -p Iconv ret=$? case $ret in 2) exit 77 ;; 0|1) exit $ret ;; esac); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:159: { (cd \$abs_top_builddir && \$TIMEOUT gst \$image_path -f \$abs_top_srcdir/scripts/Test.st --verbose -p Iconv ret=\$? case \$ret in 2) exit 77 ;; 0|1) exit \$ret ;; esac); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'an embedded newline' "testsuite.at:159" ( $at_check_trace; { (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_top_srcdir/scripts/Test.st --verbose -p Iconv ret=$? case $ret in 2) exit 77 ;; 0|1) exit $ret ;; esac); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: echo stdout:; cat "$at_stdout" at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:159" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_121 #AT_START_122 at_fn_group_banner 122 'testsuite.at:160' \ "Magritte" " " 5 at_xfail=no ( $as_echo "122. $at_setup_line: testing $at_desc ..." $at_traceon case $AUTOTEST_PATH in tests) image_path="-I $abs_top_builddir/gst.im" ;; *) image_path="" ;; esac echo "{ (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_top_srcdir/scripts/Test.st --verbose -p Magritte); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:160: { (cd \$abs_top_builddir && \$TIMEOUT gst \$image_path -f \$abs_top_srcdir/scripts/Test.st --verbose -p Magritte); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:160" ( $at_check_trace; { (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_top_srcdir/scripts/Test.st --verbose -p Magritte); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: echo stdout:; cat "$at_stdout" at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:160" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_122 #AT_START_123 at_fn_group_banner 123 'testsuite.at:161' \ "ROE" " " 5 at_xfail=no ( $as_echo "123. $at_setup_line: testing $at_desc ..." $at_traceon case $AUTOTEST_PATH in tests) image_path="-I $abs_top_builddir/gst.im" ;; *) image_path="" ;; esac echo "{ (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_top_srcdir/scripts/Test.st --verbose -p ROE ret=$? case $ret in 2) exit 77 ;; 0|1) exit $ret ;; esac); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:161: { (cd \$abs_top_builddir && \$TIMEOUT gst \$image_path -f \$abs_top_srcdir/scripts/Test.st --verbose -p ROE ret=\$? case \$ret in 2) exit 77 ;; 0|1) exit \$ret ;; esac); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'an embedded newline' "testsuite.at:161" ( $at_check_trace; { (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_top_srcdir/scripts/Test.st --verbose -p ROE ret=$? case $ret in 2) exit 77 ;; 0|1) exit $ret ;; esac); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: echo stdout:; cat "$at_stdout" at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:161" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_123 #AT_START_124 at_fn_group_banner 124 'testsuite.at:162' \ "SandstoneDb" " " 5 at_xfail=no ( $as_echo "124. $at_setup_line: testing $at_desc ..." $at_traceon case $AUTOTEST_PATH in tests) image_path="-I $abs_top_builddir/gst.im" ;; *) image_path="" ;; esac echo "{ (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_top_srcdir/scripts/Test.st --verbose -p SandstoneDb); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:162: { (cd \$abs_top_builddir && \$TIMEOUT gst \$image_path -f \$abs_top_srcdir/scripts/Test.st --verbose -p SandstoneDb); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:162" ( $at_check_trace; { (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_top_srcdir/scripts/Test.st --verbose -p SandstoneDb); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: echo stdout:; cat "$at_stdout" at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:162" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_124 #AT_START_125 at_fn_group_banner 125 'testsuite.at:163' \ "Seaside-Core" " " 5 at_xfail=no ( $as_echo "125. $at_setup_line: testing $at_desc ..." $at_traceon case $AUTOTEST_PATH in tests) image_path="-I $abs_top_builddir/gst.im" ;; *) image_path="" ;; esac echo "{ (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_top_srcdir/scripts/Test.st --verbose -p Seaside-Core ret=$? case $ret in 2) exit 77 ;; 0|1) exit $ret ;; esac); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:163: { (cd \$abs_top_builddir && \$TIMEOUT gst \$image_path -f \$abs_top_srcdir/scripts/Test.st --verbose -p Seaside-Core ret=\$? case \$ret in 2) exit 77 ;; 0|1) exit \$ret ;; esac); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'an embedded newline' "testsuite.at:163" ( $at_check_trace; { (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_top_srcdir/scripts/Test.st --verbose -p Seaside-Core ret=$? case $ret in 2) exit 77 ;; 0|1) exit $ret ;; esac); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: echo stdout:; cat "$at_stdout" at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:163" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_125 #AT_START_126 at_fn_group_banner 126 'testsuite.at:164' \ "Sockets" " " 5 at_xfail=yes ( $as_echo "126. $at_setup_line: testing $at_desc ..." $at_traceon case $AUTOTEST_PATH in tests) image_path="-I $abs_top_builddir/gst.im" ;; *) image_path="" ;; esac echo "{ (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_top_srcdir/scripts/Test.st --verbose -p Sockets ret=$? case $ret in 2) exit 77 ;; 0|1) exit $ret ;; esac); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:164: { (cd \$abs_top_builddir && \$TIMEOUT gst \$image_path -f \$abs_top_srcdir/scripts/Test.st --verbose -p Sockets ret=\$? case \$ret in 2) exit 77 ;; 0|1) exit \$ret ;; esac); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'an embedded newline' "testsuite.at:164" ( $at_check_trace; { (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_top_srcdir/scripts/Test.st --verbose -p Sockets ret=$? case $ret in 2) exit 77 ;; 0|1) exit $ret ;; esac); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: echo stdout:; cat "$at_stdout" at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:164" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_126 #AT_START_127 at_fn_group_banner 127 'testsuite.at:165' \ "Sport" " " 5 at_xfail=no ( $as_echo "127. $at_setup_line: testing $at_desc ..." $at_traceon case $AUTOTEST_PATH in tests) image_path="-I $abs_top_builddir/gst.im" ;; *) image_path="" ;; esac echo "{ (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_top_srcdir/scripts/Test.st --verbose -p Sport); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:165: { (cd \$abs_top_builddir && \$TIMEOUT gst \$image_path -f \$abs_top_srcdir/scripts/Test.st --verbose -p Sport); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:165" ( $at_check_trace; { (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_top_srcdir/scripts/Test.st --verbose -p Sport); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: echo stdout:; cat "$at_stdout" at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:165" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_127 #AT_START_128 at_fn_group_banner 128 'testsuite.at:166' \ "Swazoo" " " 5 at_xfail=no ( $as_echo "128. $at_setup_line: testing $at_desc ..." $at_traceon case $AUTOTEST_PATH in tests) image_path="-I $abs_top_builddir/gst.im" ;; *) image_path="" ;; esac echo "{ (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_top_srcdir/scripts/Test.st --verbose -p Swazoo); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:166: { (cd \$abs_top_builddir && \$TIMEOUT gst \$image_path -f \$abs_top_srcdir/scripts/Test.st --verbose -p Swazoo); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'a shell pipeline' "testsuite.at:166" ( $at_check_trace; { (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_top_srcdir/scripts/Test.st --verbose -p Swazoo); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: echo stdout:; cat "$at_stdout" at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:166" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_128 #AT_START_129 at_fn_group_banner 129 'testsuite.at:167' \ "XML-XMLParser" " " 5 at_xfail=no ( $as_echo "129. $at_setup_line: testing $at_desc ..." $at_traceon case $AUTOTEST_PATH in tests) image_path="-I $abs_top_builddir/gst.im" ;; *) image_path="" ;; esac echo "{ (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_top_srcdir/scripts/Test.st --verbose -p XML-XMLParser ret=$? case $ret in 2) exit 77 ;; 0|1) exit $ret ;; esac); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:167: { (cd \$abs_top_builddir && \$TIMEOUT gst \$image_path -f \$abs_top_srcdir/scripts/Test.st --verbose -p XML-XMLParser ret=\$? case \$ret in 2) exit 77 ;; 0|1) exit \$ret ;; esac); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'an embedded newline' "testsuite.at:167" ( $at_check_trace; { (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_top_srcdir/scripts/Test.st --verbose -p XML-XMLParser ret=$? case $ret in 2) exit 77 ;; 0|1) exit $ret ;; esac); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: echo stdout:; cat "$at_stdout" at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:167" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_129 #AT_START_130 at_fn_group_banner 130 'testsuite.at:168' \ "XML-Expat" " " 5 at_xfail=no ( $as_echo "130. $at_setup_line: testing $at_desc ..." $at_traceon case $AUTOTEST_PATH in tests) image_path="-I $abs_top_builddir/gst.im" ;; *) image_path="" ;; esac echo "{ (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_top_srcdir/scripts/Test.st --verbose -p XML-Expat ret=$? case $ret in 2) exit 77 ;; 0|1) exit $ret ;; esac); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:168: { (cd \$abs_top_builddir && \$TIMEOUT gst \$image_path -f \$abs_top_srcdir/scripts/Test.st --verbose -p XML-Expat ret=\$? case \$ret in 2) exit 77 ;; 0|1) exit \$ret ;; esac); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'an embedded newline' "testsuite.at:168" ( $at_check_trace; { (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_top_srcdir/scripts/Test.st --verbose -p XML-Expat ret=$? case $ret in 2) exit 77 ;; 0|1) exit $ret ;; esac); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: echo stdout:; cat "$at_stdout" at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:168" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_130 #AT_START_131 at_fn_group_banner 131 'testsuite.at:169' \ "ZLib" " " 5 at_xfail=no ( $as_echo "131. $at_setup_line: testing $at_desc ..." $at_traceon case $AUTOTEST_PATH in tests) image_path="-I $abs_top_builddir/gst.im" ;; *) image_path="" ;; esac echo "{ (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_top_srcdir/scripts/Test.st --verbose -p ZLib ret=$? case $ret in 2) exit 77 ;; 0|1) exit $ret ;; esac); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" { set +x $as_echo "$at_srcdir/testsuite.at:169: { (cd \$abs_top_builddir && \$TIMEOUT gst \$image_path -f \$abs_top_srcdir/scripts/Test.st --verbose -p ZLib ret=\$? case \$ret in 2) exit 77 ;; 0|1) exit \$ret ;; esac); echo exit \$? > retcode; } | tr -d '\\r' | tee stdout; . ./retcode" at_fn_check_prepare_notrace 'an embedded newline' "testsuite.at:169" ( $at_check_trace; { (cd $abs_top_builddir && $TIMEOUT gst $image_path -f $abs_top_srcdir/scripts/Test.st --verbose -p ZLib ret=$? case $ret in 2) exit 77 ;; 0|1) exit $ret ;; esac); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode ) >>"$at_stdout" 2>>"$at_stderr" 5>&- at_status=$? at_failed=false $at_check_filter at_fn_diff_devnull "$at_stderr" || at_failed=: echo stdout:; cat "$at_stdout" at_fn_check_status 0 $at_status "$at_srcdir/testsuite.at:169" $at_failed && at_fn_log_failure $at_traceon; } set +x $at_times_p && times >"$at_times_file" ) 5>&1 2>&1 7>&- | eval $at_tee_pipe read at_status <"$at_status_file" #AT_STOP_131 smalltalk-3.2.5/tests/local.at0000755000175000017500000000557012123404352013216 00000000000000dnl Local Autotest macros for GNU Smalltalk. dnl dnl Copyright (C) 2007, 2009 Free Software Foundation, Inc. dnl dnl This program is free software; you can redistribute it and/or modify dnl it under the terms of the GNU General Public License as published by dnl the Free Software Foundation; either version 2, or (at your option) dnl any later version. dnl dnl This program is distributed in the hope that it will be useful, dnl but WITHOUT ANY WARRANTY; without even the implied warranty of dnl MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the dnl GNU General Public License for more details. dnl dnl You should have received a copy of the GNU General Public License dnl along with this program; if not, write to the Free Software dnl Foundation, Inc., 59 Temple Place - Suite 330, Boston, MA dnl 02111-1307, USA. dnl AT_CHECK_GST([COMMAND-LINE], [IMAGE], [DIR], [STDOUT], [STDERR]) dnl ---------------------------------------------------------------- m4_define([AT_CHECK_GST], [ case $AUTOTEST_PATH in tests) image_path="-I m4_ifval([$2], [$2], [$abs_top_builddir/gst.im])" ;; *) image_path="m4_ifval([$2], [-I $2])" ;; esac echo "{ (cd m4_ifval([$3], [$3], [$abs_top_builddir]) && $TIMEOUT gst $image_path $1); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode" AT_CHECK([{ (cd m4_ifval([$3], [$3], [$abs_top_builddir]) && $TIMEOUT gst $image_path $1); echo exit $? > retcode; } | tr -d '\r' | tee stdout; . ./retcode], 0, [$4], [$5]) ]) dnl AT_DIFF_TEST([FILE], [XFAILS]) dnl ------------------------------ m4_define([AT_DIFF_TEST], [ AT_SETUP([$1]) AT_KEYWORDS([base]) $2 cat $abs_srcdir/m4_bpatsubst([$1], [\.st$], [.ok]) > expout AT_CHECK_GST([-r $1 2>&1], [], [$abs_srcdir], [expout]) AT_CLEANUP ]) dnl AT_PACKAGE_TEST([PACKAGE], [XFAILS], [VARS], [CONDITION]) dnl --------------------------------------------------------- m4_define([AT_PACKAGE_TEST], [ AT_SETUP([$1]) AT_KEYWORDS([m4_if([$1], [SUnit], [], [$1 ])SUnit]) $2 m4_ifval([$4], [AT_CHECK([$4 || exit 77])]) AT_CHECK_GST([-f $abs_top_srcdir/scripts/Test.st --verbose $3 -p $1], [], [], [ignore]) AT_CLEANUP ]) dnl AT_OPTIONAL_PACKAGE_TEST([PACKAGE], [XFAILS], [VARS], [CONDITION]) dnl ------------------------------------------------------------------ dnl Returns exit code 77 (skip) if the package cannot be loaded. m4_define([AT_OPTIONAL_PACKAGE_TEST], [ AT_SETUP([$1]) AT_KEYWORDS([$1 SUnit]) $2 m4_ifval([$4], [AT_CHECK([$4 || exit 77])]) AT_CHECK_GST([-f $abs_top_srcdir/scripts/Test.st --verbose $3 -p $1 ret=$? case $ret in 2) exit 77 ;; 0|1) exit $ret ;; esac], [], [], [ignore]) AT_CLEANUP ]) dnl AT_ANSI_TEST([PACKAGE], [XFAILS]) dnl --------------------------------- m4_define([AT_ANSI_TEST], [ AT_SETUP([$1]) AT_KEYWORDS([ANSI SUnit]) $2 AT_CHECK_GST([-f $abs_srcdir/AnsiRun.st $1], [$abs_builddir/gst.im], [], [ignore]) AT_CLEANUP ]) smalltalk-3.2.5/tests/shape.ok0000644000175000017500000000023212123404352013214 00000000000000 Execution begins... returned value is '2147483648' Execution begins... error: Invalid argument 2147483648: argument out of range returned value is nil smalltalk-3.2.5/tests/matrix.ok0000644000175000017500000000014712123404352013425 00000000000000 Execution begins... 270165 1061760 1453695 1856025 returned value is '270165 1061760 1453695 1856025' smalltalk-3.2.5/tests/hash2.st0000644000175000017500000000324312123404352013143 00000000000000"====================================================================== | | Benchmark for hash tables (2) | | ======================================================================" "====================================================================== | | Copyright (C) 2003, 2007, 2008 Free Software Foundation. | Written by Paolo Bonzini | | This file is part of GNU Smalltalk. | | GNU Smalltalk is free software; you can redistribute it and/or modify it | under the terms of the GNU General Public License as published by the Free | Software Foundation; either version 2, or (at your option) any later version. | | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS | FOR A PARTICULAR PURPOSE. See the GNU General Public License for more | details. | | You should have received a copy of the GNU General Public License along with | GNU Smalltalk; see the file COPYING. If not, write to the Free Software | Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. | ======================================================================" Eval [ n := Smalltalk arguments isEmpty ifTrue: [ 10 ] ifFalse: [ 1 max: Smalltalk arguments first asInteger ]. hash1 := LookupTable new: 15000. 0 to: 9999 do: [ :each | hash1 at: 'foo_', each printString put: each. ]. hash2 := LookupTable new: 15000. n timesRepeat: [ hash1 keysAndValuesDo: [ :k :v | hash2 at: k put: (hash2 at: k ifAbsent: [0]) + v ]]. ('%1 %2 %3 %4' % { hash1 at: 'foo_1'. hash1 at: 'foo_9999'. hash2 at: 'foo_1'. hash2 at: 'foo_9999' }) displayNl ] smalltalk-3.2.5/tests/objdump.ok0000644000175000017500000000054412130343734013566 00000000000000 Execution begins... returned value is true Execution begins... returned value is true Execution begins... returned value is true Execution begins... returned value is true Execution begins... returned value is true Execution begins... returned value is true Execution begins... returned value is true Execution begins... nil returned value is true smalltalk-3.2.5/tests/floatmath.ok0000644000175000017500000001444312123404352014104 00000000000000 Execution begins... returned value is ObjectMemory Execution begins... returned value is 3.10000 Execution begins... returned value is 3.45000 Execution begins... returned value is 30000.0 Execution begins... returned value is 34500.0 Execution begins... returned value is 7.70000 Execution begins... returned value is -8.62000 Execution begins... returned value is false Execution begins... returned value is true Execution begins... returned value is true Execution begins... returned value is false Execution begins... returned value is true Execution begins... returned value is true Execution begins... returned value is true Execution begins... returned value is true Execution begins... returned value is 0.00180000 Execution begins... returned value is 11250.0 Execution begins... returned value is 3 Execution begins... returned value is 0.141593 Execution begins... returned value is 12 Execution begins... returned value is 720.000 Execution begins... returned value is 2.81250 Execution begins... returned value is 3 Execution begins... returned value is -3 Execution begins... returned value is inf Execution begins... returned value is 'Inf' Execution begins... returned value is -inf Execution begins... returned value is '-Inf' Execution begins... returned value is nan Execution begins... returned value is 'NaN' Execution begins... returned value is '0.0' Execution begins... returned value is '-0.0' Execution begins... returned value is true Execution begins... returned value is false Execution begins... returned value is nan Execution begins... returned value is nan Execution begins... returned value is nan Execution begins... returned value is 5.00000 Execution begins... returned value is 5.00000 Execution begins... returned value is 7.00000 Execution begins... returned value is 0.00000 Execution begins... returned value is -0.00000 Execution begins... returned value is -0.00000 Execution begins... returned value is -0.00000 Execution begins... returned value is nan Execution begins... returned value is nan Execution begins... returned value is nan Execution begins... returned value is 7.00000 Execution begins... returned value is 7.00000 Execution begins... returned value is 7.00000 Execution begins... returned value is 0.00000 Execution begins... returned value is 0.00000 Execution begins... returned value is 0.00000 Execution begins... returned value is -0.00000 Execution begins... returned value is true Execution begins... returned value is true Execution begins... returned value is true Execution begins... returned value is true Execution begins... returned value is true Execution begins... returned value is true Execution begins... returned value is true Execution begins... returned value is true Execution begins... returned value is FloatD Execution begins... returned value is FloatD Execution begins... returned value is FloatQ Execution begins... returned value is FloatD Execution begins... returned value is FloatD Execution begins... returned value is FloatQ Execution begins... returned value is FloatD Execution begins... returned value is FloatD Execution begins... returned value is FloatQ Execution begins... returned value is FloatQ Execution begins... returned value is FloatQ Execution begins... returned value is FloatQ Execution begins... (-0.0 -0.0 0.0 0.0 true 0.0 0.0 true ) (-0.0 0.0 0.0 0.0 true -0.0 -0.0 true ) (0.0 -0.0 -0.0 -0.0 true 0.0 0.0 true ) (0.0 0.0 0.0 0.0 true 0.0 0.0 true ) returned value is Array new: 4 "<0>" Execution begins... (-0.0 -0.0 0.0 0.0 true 0.0 0.0 true ) (-0.0 0.0 0.0 0.0 true -0.0 -0.0 true ) (0.0 -0.0 -0.0 -0.0 true 0.0 0.0 true ) (0.0 0.0 0.0 0.0 true 0.0 0.0 true ) returned value is Array new: 4 "<0>" Execution begins... (-0.0 -0.0 0.0 0.0 true 0.0 0.0 true ) (0.0 0.0 0.0 0.0 true 0.0 0.0 true ) returned value is Array new: 2 "<0>" Execution begins... (-0.0 0.0 true true true ) (0.0 -0.0 true true true ) returned value is Array new: 2 "<0>" Execution begins... true->10000000000000000.0 returned value is 1.00000d+16 Execution begins... true->1.0e16 returned value is 1.00000e+16 Execution begins... true->12345000000000000.0 returned value is 1.23450d+16 Execution begins... true->1.2345e16 returned value is 1.23450e+16 Execution begins... true->1.25 returned value is 1.25000 Execution begins... true->10.0 returned value is 10.0000 Execution begins... true->17.7674749 returned value is 17.7675 Execution begins... true->0.12344999999999999 returned value is 0.123450 Execution begins... true->0.12345 returned value is 0.123450 Execution begins... true->0.0000000012344999999999998 returned value is 1.23450d-09 Execution begins... true->0.0000000012345 returned value is 1.23450d-09 Execution begins... true->1.2345e-9 returned value is 1.23450e-09 Execution begins... true->0.83205029433784 returned value is 0.832050 Execution begins... true->0.8320502943378439 returned value is 0.832050 Execution begins... true->0.5547001962252299 returned value is 0.554700 Execution begins... true->0.5547001962252289 returned value is 0.554700 Execution begins... true->0.9999999999999999 returned value is 1.000000 Execution begins... true->1.0d101 returned value is 1.00000d+101 Execution begins... true->9.46 returned value is 9.46000 Execution begins... true->0.3 returned value is 0.300000 Execution begins... true->0.30000000000000004 returned value is 0.300000 Execution begins... returned value is true Execution begins... returned value is true Execution begins... returned value is true Execution begins... returned value is true Execution begins... returned value is true Execution begins... returned value is true Execution begins... returned value is true Execution begins... returned value is true Execution begins... returned value is true Execution begins... returned value is true Execution begins... returned value is true Execution begins... returned value is true Execution begins... returned value is true Execution begins... returned value is true Execution begins... returned value is true Execution begins... true true true true true true true true true true true true true true true true true true true true returned value is FloatD Execution begins... true true true true true true true true true true true true true true true true true true true true returned value is FloatE smalltalk-3.2.5/tests/dates.ok0000644000175000017500000005721512123404352013231 00000000000000 Execution begins... 1700 1707 1714 1721 leap 1728 1735 1742 1749 leap 1756 1763 1770 1777 leap 1784 1791 1798 1805 leap 1812 1819 1826 1833 leap 1840 1847 1854 1861 leap 1868 1875 1882 1889 leap 1896 1903 1910 1917 leap 1924 1931 1938 1945 leap 1952 1959 1966 1973 leap 1980 1987 1994 2001 leap 2008 2015 2022 2029 leap 2036 2043 2050 2057 leap 2064 2071 2078 2085 leap 2092 2099 2106 2113 leap 2120 2127 2134 2141 leap 2148 2155 2162 2169 leap 2176 2183 2190 2197 leap 2204 2211 2218 2225 leap 2232 2239 2246 2253 leap 2260 2267 2274 2281 leap 2288 2295 2302 2309 leap 2316 2323 2330 2337 leap 2344 2351 2358 2365 leap 2372 2379 2386 2393 leap 2400 2407 2414 2421 leap 2428 2435 2442 2449 leap 2456 2463 2470 2477 leap 2484 2491 2498 2505 leap 2512 2519 2526 2533 leap 2540 2547 2554 2561 leap 2568 2575 2582 2589 leap 2596 2603 2610 2617 leap 2624 2631 2638 2645 leap 2652 2659 2666 2673 leap 2680 2687 2694 2701 leap 2708 2715 2722 2729 leap 2736 2743 2750 2757 leap 2764 2771 2778 2785 leap 2792 2799 2806 2813 leap 2820 2827 2834 2841 leap 2848 2855 2862 2869 leap 2876 2883 2890 2897 leap 2904 2911 2918 2925 leap 2932 2939 2946 2953 leap 2960 2967 2974 2981 leap 2988 2995 3002 3009 leap 3016 3023 3030 3037 leap 3044 3051 3058 3065 leap 3072 3079 3086 3093 3100 3107 3114 3121 leap 3128 3135 3142 3149 leap 3156 3163 3170 3177 leap 3184 3191 3198 3205 leap 3212 3219 3226 3233 leap 3240 3247 3254 3261 leap 3268 3275 3282 3289 leap 3296 3303 3310 3317 leap 3324 3331 3338 3345 leap 3352 3359 3366 3373 leap 3380 3387 3394 3401 leap 3408 3415 3422 3429 leap 3436 3443 3450 3457 leap 3464 3471 3478 3485 leap 3492 3499 3506 3513 leap 3520 3527 3534 3541 leap 3548 3555 3562 3569 leap 3576 3583 3590 3597 leap 3604 3611 3618 3625 leap 3632 3639 3646 3653 leap 3660 3667 3674 3681 leap 3688 3695 3702 3709 leap 3716 3723 3730 3737 leap 3744 3751 3758 3765 leap 3772 3779 3786 3793 3800 3807 3814 3821 leap 3828 3835 3842 3849 leap 3856 3863 3870 3877 leap 3884 3891 3898 3905 leap 3912 3919 3926 3933 leap 3940 3947 3954 3961 leap 3968 3975 3982 3989 leap 3996 4003 4010 4017 leap 4024 4031 4038 4045 leap 4052 4059 4066 4073 leap 4080 4087 4094 4101 leap 4108 4115 4122 4129 leap 4136 4143 4150 4157 leap 4164 4171 4178 4185 leap 4192 4199 4206 4213 leap 4220 4227 4234 4241 leap 4248 4255 4262 4269 leap 4276 4283 4290 4297 leap 4304 4311 4318 4325 leap 4332 4339 4346 4353 leap 4360 4367 4374 4381 leap 4388 4395 4402 4409 leap 4416 4423 4430 4437 leap 4444 4451 4458 4465 leap 4472 4479 4486 4493 4500 returned value is Date Execution begins... 1-Jan-1600 1-Feb-1600 28-Feb-1600 1-Mar-1600 31-Dec-1600 29-Feb-1600 1-Jan-1699 1-Feb-1699 28-Feb-1699 1-Mar-1699 31-Dec-1699 1-Mar-1699 1-Jan-1700 1-Feb-1700 28-Feb-1700 1-Mar-1700 31-Dec-1700 1-Mar-1700 1-Jan-1799 1-Feb-1799 28-Feb-1799 1-Mar-1799 31-Dec-1799 1-Mar-1799 1-Jan-1800 1-Feb-1800 28-Feb-1800 1-Mar-1800 31-Dec-1800 1-Mar-1800 1-Jan-1899 1-Feb-1899 28-Feb-1899 1-Mar-1899 31-Dec-1899 1-Mar-1899 1-Jan-1900 1-Feb-1900 28-Feb-1900 1-Mar-1900 31-Dec-1900 1-Mar-1900 1-Jan-1901 1-Feb-1901 28-Feb-1901 1-Mar-1901 31-Dec-1901 1-Mar-1901 1-Jan-1996 1-Feb-1996 28-Feb-1996 1-Mar-1996 31-Dec-1996 29-Feb-1996 1-Jan-1997 1-Feb-1997 28-Feb-1997 1-Mar-1997 31-Dec-1997 1-Mar-1997 1-Jan-1998 1-Feb-1998 28-Feb-1998 1-Mar-1998 31-Dec-1998 1-Mar-1998 1-Jan-1999 1-Feb-1999 28-Feb-1999 1-Mar-1999 31-Dec-1999 1-Mar-1999 1-Jan-2000 1-Feb-2000 28-Feb-2000 1-Mar-2000 31-Dec-2000 29-Feb-2000 1-Jan-2001 1-Feb-2001 28-Feb-2001 1-Mar-2001 31-Dec-2001 1-Mar-2001 returned value is Date Execution begins... -8640001 22 9 1900 -101 -8640000 23 9 1900 -100 -8553601 23 9 1900 -100 -8553600 24 9 1900 -99 -8467201 24 9 1900 -99 -8467200 25 9 1900 -98 -8380801 25 9 1900 -98 -8380800 26 9 1900 -97 -8294401 26 9 1900 -97 -8294400 27 9 1900 -96 -8208001 27 9 1900 -96 -8208000 28 9 1900 -95 -8121601 28 9 1900 -95 -8121600 29 9 1900 -94 -8035201 29 9 1900 -94 -8035200 30 9 1900 -93 -7948801 30 9 1900 -93 -7948800 1 10 1900 -92 -7862401 1 10 1900 -92 -7862400 2 10 1900 -91 -7776001 2 10 1900 -91 -7776000 3 10 1900 -90 -7689601 3 10 1900 -90 -7689600 4 10 1900 -89 -7603201 4 10 1900 -89 -7603200 5 10 1900 -88 -7516801 5 10 1900 -88 -7516800 6 10 1900 -87 -7430401 6 10 1900 -87 -7430400 7 10 1900 -86 -7344001 7 10 1900 -86 -7344000 8 10 1900 -85 -7257601 8 10 1900 -85 -7257600 9 10 1900 -84 -7171201 9 10 1900 -84 -7171200 10 10 1900 -83 -7084801 10 10 1900 -83 -7084800 11 10 1900 -82 -6998401 11 10 1900 -82 -6998400 12 10 1900 -81 -6912001 12 10 1900 -81 -6912000 13 10 1900 -80 -6825601 13 10 1900 -80 -6825600 14 10 1900 -79 -6739201 14 10 1900 -79 -6739200 15 10 1900 -78 -6652801 15 10 1900 -78 -6652800 16 10 1900 -77 -6566401 16 10 1900 -77 -6566400 17 10 1900 -76 -6480001 17 10 1900 -76 -6480000 18 10 1900 -75 -6393601 18 10 1900 -75 -6393600 19 10 1900 -74 -6307201 19 10 1900 -74 -6307200 20 10 1900 -73 -6220801 20 10 1900 -73 -6220800 21 10 1900 -72 -6134401 21 10 1900 -72 -6134400 22 10 1900 -71 -6048001 22 10 1900 -71 -6048000 23 10 1900 -70 -5961601 23 10 1900 -70 -5961600 24 10 1900 -69 -5875201 24 10 1900 -69 -5875200 25 10 1900 -68 -5788801 25 10 1900 -68 -5788800 26 10 1900 -67 -5702401 26 10 1900 -67 -5702400 27 10 1900 -66 -5616001 27 10 1900 -66 -5616000 28 10 1900 -65 -5529601 28 10 1900 -65 -5529600 29 10 1900 -64 -5443201 29 10 1900 -64 -5443200 30 10 1900 -63 -5356801 30 10 1900 -63 -5356800 31 10 1900 -62 -5270401 31 10 1900 -62 -5270400 1 11 1900 -61 -5184001 1 11 1900 -61 -5184000 2 11 1900 -60 -5097601 2 11 1900 -60 -5097600 3 11 1900 -59 -5011201 3 11 1900 -59 -5011200 4 11 1900 -58 -4924801 4 11 1900 -58 -4924800 5 11 1900 -57 -4838401 5 11 1900 -57 -4838400 6 11 1900 -56 -4752001 6 11 1900 -56 -4752000 7 11 1900 -55 -4665601 7 11 1900 -55 -4665600 8 11 1900 -54 -4579201 8 11 1900 -54 -4579200 9 11 1900 -53 -4492801 9 11 1900 -53 -4492800 10 11 1900 -52 -4406401 10 11 1900 -52 -4406400 11 11 1900 -51 -4320001 11 11 1900 -51 -4320000 12 11 1900 -50 -4233601 12 11 1900 -50 -4233600 13 11 1900 -49 -4147201 13 11 1900 -49 -4147200 14 11 1900 -48 -4060801 14 11 1900 -48 -4060800 15 11 1900 -47 -3974401 15 11 1900 -47 -3974400 16 11 1900 -46 -3888001 16 11 1900 -46 -3888000 17 11 1900 -45 -3801601 17 11 1900 -45 -3801600 18 11 1900 -44 -3715201 18 11 1900 -44 -3715200 19 11 1900 -43 -3628801 19 11 1900 -43 -3628800 20 11 1900 -42 -3542401 20 11 1900 -42 -3542400 21 11 1900 -41 -3456001 21 11 1900 -41 -3456000 22 11 1900 -40 -3369601 22 11 1900 -40 -3369600 23 11 1900 -39 -3283201 23 11 1900 -39 -3283200 24 11 1900 -38 -3196801 24 11 1900 -38 -3196800 25 11 1900 -37 -3110401 25 11 1900 -37 -3110400 26 11 1900 -36 -3024001 26 11 1900 -36 -3024000 27 11 1900 -35 -2937601 27 11 1900 -35 -2937600 28 11 1900 -34 -2851201 28 11 1900 -34 -2851200 29 11 1900 -33 -2764801 29 11 1900 -33 -2764800 30 11 1900 -32 -2678401 30 11 1900 -32 -2678400 1 12 1900 -31 -2592001 1 12 1900 -31 -2592000 2 12 1900 -30 -2505601 2 12 1900 -30 -2505600 3 12 1900 -29 -2419201 3 12 1900 -29 -2419200 4 12 1900 -28 -2332801 4 12 1900 -28 -2332800 5 12 1900 -27 -2246401 5 12 1900 -27 -2246400 6 12 1900 -26 -2160001 6 12 1900 -26 -2160000 7 12 1900 -25 -2073601 7 12 1900 -25 -2073600 8 12 1900 -24 -1987201 8 12 1900 -24 -1987200 9 12 1900 -23 -1900801 9 12 1900 -23 -1900800 10 12 1900 -22 -1814401 10 12 1900 -22 -1814400 11 12 1900 -21 -1728001 11 12 1900 -21 -1728000 12 12 1900 -20 -1641601 12 12 1900 -20 -1641600 13 12 1900 -19 -1555201 13 12 1900 -19 -1555200 14 12 1900 -18 -1468801 14 12 1900 -18 -1468800 15 12 1900 -17 -1382401 15 12 1900 -17 -1382400 16 12 1900 -16 -1296001 16 12 1900 -16 -1296000 17 12 1900 -15 -1209601 17 12 1900 -15 -1209600 18 12 1900 -14 -1123201 18 12 1900 -14 -1123200 19 12 1900 -13 -1036801 19 12 1900 -13 -1036800 20 12 1900 -12 -950401 20 12 1900 -12 -950400 21 12 1900 -11 -864001 21 12 1900 -11 -864000 22 12 1900 -10 -777601 22 12 1900 -10 -777600 23 12 1900 -9 -691201 23 12 1900 -9 -691200 24 12 1900 -8 -604801 24 12 1900 -8 -604800 25 12 1900 -7 -518401 25 12 1900 -7 -518400 26 12 1900 -6 -432001 26 12 1900 -6 -432000 27 12 1900 -5 -345601 27 12 1900 -5 -345600 28 12 1900 -4 -259201 28 12 1900 -4 -259200 29 12 1900 -3 -172801 29 12 1900 -3 -172800 30 12 1900 -2 -86401 30 12 1900 -2 -86400 31 12 1900 -1 -1 31 12 1900 -1 0 1 1 1901 0 86399 1 1 1901 0 86400 2 1 1901 1 172799 2 1 1901 1 172800 3 1 1901 2 259199 3 1 1901 2 259200 4 1 1901 3 345599 4 1 1901 3 345600 5 1 1901 4 431999 5 1 1901 4 432000 6 1 1901 5 518399 6 1 1901 5 518400 7 1 1901 6 604799 7 1 1901 6 604800 8 1 1901 7 691199 8 1 1901 7 691200 9 1 1901 8 777599 9 1 1901 8 777600 10 1 1901 9 863999 10 1 1901 9 864000 11 1 1901 10 950399 11 1 1901 10 950400 12 1 1901 11 1036799 12 1 1901 11 1036800 13 1 1901 12 1123199 13 1 1901 12 1123200 14 1 1901 13 1209599 14 1 1901 13 1209600 15 1 1901 14 1295999 15 1 1901 14 1296000 16 1 1901 15 1382399 16 1 1901 15 1382400 17 1 1901 16 1468799 17 1 1901 16 1468800 18 1 1901 17 1555199 18 1 1901 17 1555200 19 1 1901 18 1641599 19 1 1901 18 1641600 20 1 1901 19 1727999 20 1 1901 19 1728000 21 1 1901 20 1814399 21 1 1901 20 1814400 22 1 1901 21 1900799 22 1 1901 21 1900800 23 1 1901 22 1987199 23 1 1901 22 1987200 24 1 1901 23 2073599 24 1 1901 23 2073600 25 1 1901 24 2159999 25 1 1901 24 2160000 26 1 1901 25 2246399 26 1 1901 25 2246400 27 1 1901 26 2332799 27 1 1901 26 2332800 28 1 1901 27 2419199 28 1 1901 27 2419200 29 1 1901 28 2505599 29 1 1901 28 2505600 30 1 1901 29 2591999 30 1 1901 29 2592000 31 1 1901 30 2678399 31 1 1901 30 2678400 1 2 1901 31 2764799 1 2 1901 31 2764800 2 2 1901 32 2851199 2 2 1901 32 2851200 3 2 1901 33 2937599 3 2 1901 33 2937600 4 2 1901 34 3023999 4 2 1901 34 3024000 5 2 1901 35 3110399 5 2 1901 35 3110400 6 2 1901 36 3196799 6 2 1901 36 3196800 7 2 1901 37 3283199 7 2 1901 37 3283200 8 2 1901 38 3369599 8 2 1901 38 3369600 9 2 1901 39 3455999 9 2 1901 39 3456000 10 2 1901 40 3542399 10 2 1901 40 3542400 11 2 1901 41 3628799 11 2 1901 41 3628800 12 2 1901 42 3715199 12 2 1901 42 3715200 13 2 1901 43 3801599 13 2 1901 43 3801600 14 2 1901 44 3887999 14 2 1901 44 3888000 15 2 1901 45 3974399 15 2 1901 45 3974400 16 2 1901 46 4060799 16 2 1901 46 4060800 17 2 1901 47 4147199 17 2 1901 47 4147200 18 2 1901 48 4233599 18 2 1901 48 4233600 19 2 1901 49 4319999 19 2 1901 49 4320000 20 2 1901 50 4406399 20 2 1901 50 4406400 21 2 1901 51 4492799 21 2 1901 51 4492800 22 2 1901 52 4579199 22 2 1901 52 4579200 23 2 1901 53 4665599 23 2 1901 53 4665600 24 2 1901 54 4751999 24 2 1901 54 4752000 25 2 1901 55 4838399 25 2 1901 55 4838400 26 2 1901 56 4924799 26 2 1901 56 4924800 27 2 1901 57 5011199 27 2 1901 57 5011200 28 2 1901 58 5097599 28 2 1901 58 5097600 1 3 1901 59 5183999 1 3 1901 59 5184000 2 3 1901 60 5270399 2 3 1901 60 5270400 3 3 1901 61 5356799 3 3 1901 61 5356800 4 3 1901 62 5443199 4 3 1901 62 5443200 5 3 1901 63 5529599 5 3 1901 63 5529600 6 3 1901 64 5615999 6 3 1901 64 5616000 7 3 1901 65 5702399 7 3 1901 65 5702400 8 3 1901 66 5788799 8 3 1901 66 5788800 9 3 1901 67 5875199 9 3 1901 67 5875200 10 3 1901 68 5961599 10 3 1901 68 5961600 11 3 1901 69 6047999 11 3 1901 69 6048000 12 3 1901 70 6134399 12 3 1901 70 6134400 13 3 1901 71 6220799 13 3 1901 71 6220800 14 3 1901 72 6307199 14 3 1901 72 6307200 15 3 1901 73 6393599 15 3 1901 73 6393600 16 3 1901 74 6479999 16 3 1901 74 6480000 17 3 1901 75 6566399 17 3 1901 75 6566400 18 3 1901 76 6652799 18 3 1901 76 6652800 19 3 1901 77 6739199 19 3 1901 77 6739200 20 3 1901 78 6825599 20 3 1901 78 6825600 21 3 1901 79 6911999 21 3 1901 79 6912000 22 3 1901 80 6998399 22 3 1901 80 6998400 23 3 1901 81 7084799 23 3 1901 81 7084800 24 3 1901 82 7171199 24 3 1901 82 7171200 25 3 1901 83 7257599 25 3 1901 83 7257600 26 3 1901 84 7343999 26 3 1901 84 7344000 27 3 1901 85 7430399 27 3 1901 85 7430400 28 3 1901 86 7516799 28 3 1901 86 7516800 29 3 1901 87 7603199 29 3 1901 87 7603200 30 3 1901 88 7689599 30 3 1901 88 7689600 31 3 1901 89 7775999 31 3 1901 89 7776000 1 4 1901 90 7862399 1 4 1901 90 7862400 2 4 1901 91 7948799 2 4 1901 91 7948800 3 4 1901 92 8035199 3 4 1901 92 8035200 4 4 1901 93 8121599 4 4 1901 93 8121600 5 4 1901 94 8207999 5 4 1901 94 8208000 6 4 1901 95 8294399 6 4 1901 95 8294400 7 4 1901 96 8380799 7 4 1901 96 8380800 8 4 1901 97 8467199 8 4 1901 97 8467200 9 4 1901 98 8553599 9 4 1901 98 8553600 10 4 1901 99 8639999 10 4 1901 99 8640000 11 4 1901 100 returned value is Date Execution begins... 1-Feb-2011->'2011-02-01'->' abcd'->'abcd' 1-Feb-2011->'2011-02-01'->'abcd'->'bcd' 1-Feb-2011->'Feb 1 2011'->' abcd'->'abcd' 1-Feb-2011->'Feb 1 2011'->'abcd'->'bcd' 1-Feb--2011->'-2011-02-01'->' abcd'->'abcd' 1-Feb--2011->'-2011-02-01'->'abcd'->'bcd' 1-Feb--2011->'Feb 1 -2011'->' abcd'->'abcd' 1-Feb--2011->'Feb 1 -2011'->'abcd'->'bcd' 9:00:02->'09:00:02'->' 1234'->'1234' 9:00:02->'09:00:02'->':1234'->'1234' 9:00:02->'09:00:02'->' abcd'->'abcd' 9:00:02->'09:00:02'->'abcd'->'bcd' 9:00:00->'09:00'->' 1234'->'1234' 9:00:00->'09:00'->'::1234'->'1234' 9:00:00->'09:00'->' abcd'->'abcd' 9:00:00->'09:00'->'abcd'->'cd' 9:00:00->'9:00'->' 1234'->'1234' 9:00:00->'9:00'->'::1234'->'1234' 9:00:00->'9:00'->' abcd'->'abcd' 9:00:00->'9:00'->'abcd'->'cd' 1:09:00:02->'01:09:00:02'->' 1234'->' 1234' 1:09:00:02->'01:09:00:02'->':1234'->'1234' 1:09:00:02->'01:09:00:02'->' abcd'->' abcd' 1:09:00:02->'01:09:00:02'->'abcd'->'bcd' 1:09:00:02->'1:09:00:02'->' 1234'->' 1234' 1:09:00:02->'1:09:00:02'->':1234'->'1234' 1:09:00:02->'1:09:00:02'->' abcd'->' abcd' 1:09:00:02->'1:09:00:02'->'abcd'->'bcd' 1:09:00:02->'1:9:00:02'->' 1234'->' 1234' 1:09:00:02->'1:9:00:02'->':1234'->'1234' 1:09:00:02->'1:9:00:02'->' abcd'->' abcd' 1:09:00:02->'1:9:00:02'->'abcd'->'bcd' 0:09:00:02->'09:00:02'->' 1234'->' 1234' 0:09:00:02->'09:00:02'->'::1234'->':1234' 0:09:00:02->'09:00:02'->' abcd'->' abcd' 0:09:00:02->'09:00:02'->'abcd'->'bcd' 0:09:00:02->'9:00:02'->' 1234'->' 1234' 0:09:00:02->'9:00:02'->'::1234'->':1234' 0:09:00:02->'9:00:02'->' abcd'->' abcd' 0:09:00:02->'9:00:02'->'abcd'->'bcd' 0:09:00:00->'09:00'->' 1234'->' 1234' 0:09:00:00->'09:00'->'::1234'->':1234' 0:09:00:00->'09:00'->' abcd'->' abcd' 0:09:00:00->'09:00'->'abcd'->'bcd' 0:09:00:00->'9:00'->' 1234'->' 1234' 0:09:00:00->'9:00'->'::1234'->':1234' 0:09:00:00->'9:00'->' abcd'->' abcd' 0:09:00:00->'9:00'->'abcd'->'bcd' -1:09:00:02->'-01:09:00:02'->' 1234'->' 1234' -1:09:00:02->'-01:09:00:02'->':1234'->'1234' -1:09:00:02->'-01:09:00:02'->' abcd'->' abcd' -1:09:00:02->'-01:09:00:02'->'abcd'->'bcd' -1:09:00:02->'-1:09:00:02'->' 1234'->' 1234' -1:09:00:02->'-1:09:00:02'->':1234'->'1234' -1:09:00:02->'-1:09:00:02'->' abcd'->' abcd' -1:09:00:02->'-1:09:00:02'->'abcd'->'bcd' -1:09:00:02->'-1:9:00:02'->' 1234'->' 1234' -1:09:00:02->'-1:9:00:02'->':1234'->'1234' -1:09:00:02->'-1:9:00:02'->' abcd'->' abcd' -1:09:00:02->'-1:9:00:02'->'abcd'->'bcd' -0:09:00:02->'-09:00:02'->' 1234'->' 1234' -0:09:00:02->'-09:00:02'->'::1234'->':1234' -0:09:00:02->'-09:00:02'->' abcd'->' abcd' -0:09:00:02->'-09:00:02'->'abcd'->'bcd' -0:09:00:02->'-9:00:02'->' 1234'->' 1234' -0:09:00:02->'-9:00:02'->'::1234'->':1234' -0:09:00:02->'-9:00:02'->' abcd'->' abcd' -0:09:00:02->'-9:00:02'->'abcd'->'bcd' -0:09:00:00->'-09:00'->' 1234'->' 1234' -0:09:00:00->'-09:00'->'::1234'->':1234' -0:09:00:00->'-09:00'->' abcd'->' abcd' -0:09:00:00->'-09:00'->'abcd'->'bcd' -0:09:00:00->'-9:00'->' 1234'->' 1234' -0:09:00:00->'-9:00'->'::1234'->':1234' -0:09:00:00->'-9:00'->' abcd'->' abcd' -0:09:00:00->'-9:00'->'abcd'->'bcd' 1:09:00:02->'+01:09:00:02'->' 1234'->' 1234' 1:09:00:02->'+01:09:00:02'->':1234'->'1234' 1:09:00:02->'+01:09:00:02'->' abcd'->' abcd' 1:09:00:02->'+01:09:00:02'->'abcd'->'bcd' 1:09:00:02->'+1:09:00:02'->' 1234'->' 1234' 1:09:00:02->'+1:09:00:02'->':1234'->'1234' 1:09:00:02->'+1:09:00:02'->' abcd'->' abcd' 1:09:00:02->'+1:09:00:02'->'abcd'->'bcd' 1:09:00:02->'+1:9:00:02'->' 1234'->' 1234' 1:09:00:02->'+1:9:00:02'->':1234'->'1234' 1:09:00:02->'+1:9:00:02'->' abcd'->' abcd' 1:09:00:02->'+1:9:00:02'->'abcd'->'bcd' 0:09:00:02->'+09:00:02'->' 1234'->' 1234' 0:09:00:02->'+09:00:02'->'::1234'->':1234' 0:09:00:02->'+09:00:02'->' abcd'->' abcd' 0:09:00:02->'+09:00:02'->'abcd'->'bcd' 0:09:00:02->'+9:00:02'->' 1234'->' 1234' 0:09:00:02->'+9:00:02'->'::1234'->':1234' 0:09:00:02->'+9:00:02'->' abcd'->' abcd' 0:09:00:02->'+9:00:02'->'abcd'->'bcd' 0:09:00:00->'+09:00'->' 1234'->' 1234' 0:09:00:00->'+09:00'->'::1234'->':1234' 0:09:00:00->'+09:00'->' abcd'->' abcd' 0:09:00:00->'+09:00'->'abcd'->'bcd' 0:09:00:00->'+9:00'->' 1234'->' 1234' 0:09:00:00->'+9:00'->'::1234'->':1234' 0:09:00:00->'+9:00'->' abcd'->' abcd' 0:09:00:00->'+9:00'->'abcd'->'bcd' 2011-02-01T09:00:00+01:30->'2011-02-01 09:00 +01:30'->' 1234'->' 1234' 2011-02-01T09:00:00+01:30->'2011-02-01 09:00 +01:30'->' abcd'->' abcd' 2011-02-01T09:00:00+01:30->'2011-02-01 09:00 +01:30'->'abcd'->'bcd' 2011-02-01T09:00:00+01:30->'2011-02-01 09:00 +01:30'->' 1234'->' 1234' 2011-02-01T09:00:00+01:30->'2011-02-01 09:00 +01:30'->' abcd'->' abcd' 2011-02-01T09:00:00+01:30->'2011-02-01 09:00 +01:30'->'abcd'->'bcd' 2011-02-01T09:00:00+01:30->'2011-02-01 09:00+01:30'->' 1234'->' 1234' 2011-02-01T09:00:00+01:30->'2011-02-01 09:00+01:30'->' abcd'->' abcd' 2011-02-01T09:00:00+01:30->'2011-02-01 09:00+01:30'->'abcd'->'bcd' 2011-02-01T09:00:00+01:30->'2011-02-01 09:00+1:30'->' abcd'->' abcd' 2011-02-01T09:00:00+01:30->'2011-02-01 09:00+1:30'->'abcd'->'bcd' 2011-02-01T09:00:00+01:00->'2011-02-01 09:00+01'->' 1234'->' 1234' 2011-02-01T09:00:00+01:00->'2011-02-01 09:00+01'->' abcd'->' abcd' 2011-02-01T09:00:00+01:00->'2011-02-01 09:00+01'->'abcd'->'bcd' 2011-02-01T09:00:10+01:30->'2011-02-01 09:00:10+01:30'->' 1234'->' 1234' 2011-02-01T09:00:10+01:30->'2011-02-01 09:00:10+01:30'->' abcd'->' abcd' 2011-02-01T09:00:10+01:30->'2011-02-01 09:00:10+01:30'->'abcd'->'bcd' 2011-02-01T09:00:10+01:30->'2011-02-01 09:00:10+1:30'->' abcd'->' abcd' 2011-02-01T09:00:10+01:30->'2011-02-01 09:00:10+1:30'->'abcd'->'bcd' 2011-02-01T09:00:10+01:00->'2011-02-01 09:00:10+01'->' 1234'->' 1234' 2011-02-01T09:00:10+01:00->'2011-02-01 09:00:10+01'->' abcd'->' abcd' 2011-02-01T09:00:10+01:00->'2011-02-01 09:00:10+01'->'abcd'->'bcd' 2011-02-01T09:00:00-01:30->'2011-02-01 09:00 -01:30'->' abcd'->' abcd' 2011-02-01T09:00:00-01:30->'2011-02-01 09:00 -01:30'->'abcd'->'bcd' 2011-02-01T09:00:00-01:30->'2011-02-01 09:00 -01:30'->' abcd'->' abcd' 2011-02-01T09:00:00-01:30->'2011-02-01 09:00 -01:30'->'abcd'->'bcd' 2011-02-01T09:00:10-01:30->'2011-02-01 09:00:10-01:30'->' abcd'->' abcd' 2011-02-01T09:00:10-01:30->'2011-02-01 09:00:10-01:30'->'abcd'->'bcd' 2011-02-01T09:00:10-01:30->'2011-02-01 09:00:10-1:30'->' abcd'->' abcd' 2011-02-01T09:00:10-01:30->'2011-02-01 09:00:10-1:30'->'abcd'->'bcd' 2011-02-01T09:00:00-01:30->'2011-02-01 09:00-01:30'->' abcd'->' abcd' 2011-02-01T09:00:00-01:30->'2011-02-01 09:00-01:30'->'abcd'->'bcd' 2011-02-01T09:00:00-01:30->'2011-02-01 09:00-1:30'->' abcd'->' abcd' 2011-02-01T09:00:00-01:30->'2011-02-01 09:00-1:30'->'abcd'->'bcd' 2011-02-01T09:00:10+00:00->'2011-02-01 09:00:10'->' abcd'->'abcd' 2011-02-01T09:00:10+00:00->'2011-02-01 09:00:10'->'abcd'->'bcd' 2011-02-01T09:00:00+00:00->'2011-02-01 09:00'->' abcd'->'abcd' 2011-02-01T09:00:00+00:00->'2011-02-01 09:00'->'abcd'->'bcd' 2011-02-01T09:00:00+01:30->'2011-02-01T09:00+01:30'->' abcd'->' abcd' 2011-02-01T09:00:00+01:30->'2011-02-01T09:00+01:30'->'abcd'->'bcd' 2011-02-01T09:00:00+01:30->'2011-02-01T09:00+1:30'->' abcd'->' abcd' 2011-02-01T09:00:00+01:30->'2011-02-01T09:00+1:30'->'abcd'->'bcd' 2011-02-01T09:00:00+01:00->'2011-02-01T09:00+01'->' abcd'->' abcd' 2011-02-01T09:00:00+01:00->'2011-02-01T09:00+01'->'abcd'->'bcd' 2011-02-01T09:00:10+01:30->'2011-02-01T09:00:10+01:30'->' abcd'->' abcd' 2011-02-01T09:00:10+01:30->'2011-02-01T09:00:10+01:30'->'abcd'->'bcd' 2011-02-01T09:00:10+01:30->'2011-02-01T09:00:10+1:30'->' abcd'->' abcd' 2011-02-01T09:00:10+01:30->'2011-02-01T09:00:10+1:30'->'abcd'->'bcd' 2011-02-01T09:00:10+01:00->'2011-02-01T09:00:10+01'->' abcd'->' abcd' 2011-02-01T09:00:10+01:00->'2011-02-01T09:00:10+01'->'abcd'->'bcd' 2011-02-01T09:00:10-01:30->'2011-02-01T09:00:10-01:30'->' abcd'->' abcd' 2011-02-01T09:00:10-01:30->'2011-02-01T09:00:10-01:30'->'abcd'->'bcd' 2011-02-01T09:00:10-01:30->'2011-02-01T09:00:10-1:30'->' abcd'->' abcd' 2011-02-01T09:00:10-01:30->'2011-02-01T09:00:10-1:30'->'abcd'->'bcd' 2011-02-01T09:00:00-01:30->'2011-02-01T09:00-01:30'->' abcd'->' abcd' 2011-02-01T09:00:00-01:30->'2011-02-01T09:00-01:30'->'abcd'->'bcd' 2011-02-01T09:00:00-01:30->'2011-02-01T09:00-1:30'->' abcd'->' abcd' 2011-02-01T09:00:00-01:30->'2011-02-01T09:00-1:30'->'abcd'->'bcd' 2011-02-01T09:00:10+00:00->'2011-02-01T09:00:10'->' abcd'->'abcd' 2011-02-01T09:00:10+00:00->'2011-02-01T09:00:10'->'abcd'->'bcd' 2011-02-01T09:00:00+00:00->'2011-02-01T09:00'->' abcd'->'abcd' 2011-02-01T09:00:00+00:00->'2011-02-01T09:00'->'abcd'->'bcd' 2011-02-01T00:00:00+00:00->'2011-02-01'->' abcd'->'abcd' 2011-02-01T00:00:00+00:00->'2011-02-01'->'abcd'->'bcd' 2011-02-01T00:00:00+00:00->'Feb 1 2011'->' abcd'->'abcd' 2011-02-01T00:00:00+00:00->'Feb 1 2011'->'abcd'->'bcd' -2011-02-01T09:00:00+01:30->'-2011-02-01T09:00+01:30'->' abcd'->' abcd' -2011-02-01T09:00:00+01:30->'-2011-02-01T09:00+01:30'->'abcd'->'bcd' -2011-02-01T00:00:00+00:00->'-2011-02-01'->' abcd'->'abcd' -2011-02-01T00:00:00+00:00->'-2011-02-01'->'abcd'->'bcd' -2011-02-01T00:00:00+00:00->'Feb 1 -2011'->' abcd'->'abcd' -2011-02-01T00:00:00+00:00->'Feb 1 -2011'->'abcd'->'bcd' 2011-02-01T09:00:00+01:30->'Feb 1 2011 09:00 +01:30'->' 1234'->' 1234' 2011-02-01T09:00:00+01:30->'Feb 1 2011 09:00 +01:30'->' abcd'->' abcd' 2011-02-01T09:00:00+01:30->'Feb 1 2011 09:00 +01:30'->'abcd'->'bcd' 2011-02-01T09:00:00+01:30->'Feb 1 2011 09:00 +01:30'->' 1234'->' 1234' 2011-02-01T09:00:00+01:30->'Feb 1 2011 09:00 +01:30'->' abcd'->' abcd' 2011-02-01T09:00:00+01:30->'Feb 1 2011 09:00 +01:30'->'abcd'->'bcd' 2011-02-01T09:00:00+01:30->'Feb 1 2011 09:00+01:30'->' 1234'->' 1234' 2011-02-01T09:00:00+01:30->'Feb 1 2011 09:00+01:30'->' abcd'->' abcd' 2011-02-01T09:00:00+01:30->'Feb 1 2011 09:00+01:30'->'abcd'->'bcd' 2011-02-01T09:00:00+01:00->'Feb 1 2011 09:00+01'->' 1234'->' 1234' 2011-02-01T09:00:00+01:00->'Feb 1 2011 09:00+01'->' abcd'->' abcd' 2011-02-01T09:00:00+01:00->'Feb 1 2011 09:00+01'->'abcd'->'bcd' 2011-02-01T09:00:10+01:30->'Feb 1 2011 09:00:10+01:30'->' 1234'->' 1234' 2011-02-01T09:00:10+01:30->'Feb 1 2011 09:00:10+01:30'->' abcd'->' abcd' 2011-02-01T09:00:10+01:30->'Feb 1 2011 09:00:10+01:30'->'abcd'->'bcd' 2011-02-01T09:00:10+01:00->'Feb 1 2011 09:00:10+01'->' 1234'->' 1234' 2011-02-01T09:00:10+01:00->'Feb 1 2011 09:00:10+01'->' abcd'->' abcd' 2011-02-01T09:00:10+01:00->'Feb 1 2011 09:00:10+01'->'abcd'->'bcd' 2011-02-01T09:00:10+01:30->'Feb 1 2011 09:00:10+1:30'->' abcd'->' abcd' 2011-02-01T09:00:10+01:30->'Feb 1 2011 09:00:10+1:30'->'abcd'->'bcd' 2011-02-01T09:00:00+01:30->'Feb 1 2011 09:00+1:30'->' abcd'->' abcd' 2011-02-01T09:00:00+01:30->'Feb 1 2011 09:00+1:30'->'abcd'->'bcd' 2011-02-01T09:00:00-01:30->'Feb 1 2011 09:00 -01:30'->' abcd'->' abcd' 2011-02-01T09:00:00-01:30->'Feb 1 2011 09:00 -01:30'->'abcd'->'bcd' 2011-02-01T09:00:00-01:30->'Feb 1 2011 09:00 -01:30'->' abcd'->' abcd' 2011-02-01T09:00:00-01:30->'Feb 1 2011 09:00 -01:30'->'abcd'->'bcd' 2011-02-01T09:00:00-01:30->'Feb 1 2011 09:00-01:30'->' abcd'->' abcd' 2011-02-01T09:00:00-01:30->'Feb 1 2011 09:00-01:30'->'abcd'->'bcd' 2011-02-01T09:00:10-01:30->'Feb 1 2011 09:00:10-01:30'->' abcd'->' abcd' 2011-02-01T09:00:10-01:30->'Feb 1 2011 09:00:10-01:30'->'abcd'->'bcd' 2011-02-01T09:00:10-01:30->'Feb 1 2011 09:00:10-1:30'->' abcd'->' abcd' 2011-02-01T09:00:10-01:30->'Feb 1 2011 09:00:10-1:30'->'abcd'->'bcd' 2011-02-01T09:00:00-01:30->'Feb 1 2011 09:00-1:30'->' abcd'->' abcd' 2011-02-01T09:00:00-01:30->'Feb 1 2011 09:00-1:30'->'abcd'->'bcd' 2011-02-01T09:00:10+00:00->'Feb 1 2011 09:00:10'->' abcd'->'abcd' 2011-02-01T09:00:10+00:00->'Feb 1 2011 09:00:10'->'abcd'->'bcd' 2011-02-01T09:00:00+00:00->'Feb 1 2011 09:00'->' abcd'->'abcd' 2011-02-01T09:00:00+00:00->'Feb 1 2011 09:00'->'abcd'->'bcd' returned value is Association new "<0>" smalltalk-3.2.5/tests/blocks.st0000644000175000017500000001163412123404352013416 00000000000000"====================================================================== | | Test out block operations | | ======================================================================" "====================================================================== | | Copyright (C) 1988, 1989, 1999, 2007, 2008 Free Software Foundation. | Written by Steve Byrne and Paolo Bonzini | | This file is part of GNU Smalltalk. | | GNU Smalltalk is free software; you can redistribute it and/or modify it | under the terms of the GNU General Public License as published by the Free | Software Foundation; either version 2, or (at your option) any later version. | | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS | FOR A PARTICULAR PURPOSE. See the GNU General Public License for more | details. | | You should have received a copy of the GNU General Public License along with | GNU Smalltalk; see the file COPYING. If not, write to the Free Software | Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. | ======================================================================" Eval [ [45] ] "should return a block" Eval [ [^#quem] value ] "should return #quem" Eval [ ['foo'] value ] "should return 'foo'" Eval [ [:i | i] value: 'juma' ] "should return 'juma'" Eval [ [:i :j| j] value: 12 value: 17 ] "should return 17" Object extend [ blockTest1 [ [#foo] ] blockTest2 [ [^#foo] ] blockTest3 [ ^[#bar] ] blockTest4 [ ^[^#bar] ] blockTest5: arg [ ^[arg] ] blockTest6: arg [ ^[:i | arg at: i] ] blockTest7: arg [ | temp | temp := (arg at: 4) + 8. ^[temp] ] blockTest8: which [ | first second | first := nil blockTest7: #('one' #two 3.0 4 $5). second := nil blockTest7: #("You are[,] number" 'six' #seven 8.0 9 $A). which ifTrue: [ ^first value ] ifFalse: [ ^second value] ] "Implements a 'closure'!!! Smalltalk is AMAZING!!!" blockTest9: initialValue [ | counter | counter := initialValue. ^[:incr | counter := counter + incr. counter] ] "Implements a REAL 'closure'!!! GNU Smalltalk is AMAZING!!!" blockTest10 [ | counter | counter := 1. "If blocks were not real closures, variable would be 1 the second time the block was called and hence it would not be modified. Instead if blocks are closures, variable is still nil the second time the block is evaluated, and is initialized to two." ^[ | variable | variable isNil ifTrue: [ variable := counter ]. counter := counter + 1. variable ] ] blockTest11: initialValue [ ^[^initialValue] ] ] Eval [ nil blockTest1 ] "should return nil" Eval [ nil blockTest2 ] "should return nil" Eval [ nil blockTest3 ] "should return a BlockClosure" Eval [ nil blockTest3 value ] "should return #bar" Eval [ nil blockTest4 value ] "should issue an error, we're returning to a non-existent context" Eval [ (nil blockTest5: 'Smalltalk!') value ] "should return 'Smalltalk!'" Eval [ (nil blockTest6: #('one' #two 3.0 4 $5)) value: 2 ] "should return #two" Eval [ (nil blockTest7: #('you' #are #number 6)) value ] "should return 14" Eval [ nil blockTest8: true ] "should return 12" Eval [ nil blockTest8: false ] "should return 17" "Create a block with the initial value of 2" Eval [ Smalltalk at: #testBlock put: (nil blockTest9: 2) ] Eval [ testBlock value: 3 ] "should return 5" Eval [ testBlock value: 6 ] "should return 11" Eval [ testBlock value: 2 ] "should return 13" Eval [ Smalltalk at: #testBlock put: (nil blockTest10) ] Eval [ testBlock value ] "should return 1" Eval [ testBlock value ] "should return 2 (1 if blocks aren't closures)" "And this is even more amazing!!!" Eval [ | array | array := (1 to: 10) collect: [ :each | [each] ]. ^array inject: 0 into: [ :sum :each | sum + each value ] "should get 55" ] Eval [ (nil blockTest11: 3) value ] "should be invalid; we're returning to non- existent parent" "Various tests on #cull:cull:cull: and friends." Eval [ [] cull: 1 ] Eval [ [] cull: 1 cull: 2 ] Eval [ [] cull: 1 cull: 2 cull: 3 ] Eval [ [:a |a] cull: 1 ] Eval [ [:a |a] cull: 1 cull: 2 ] Eval [ [:a |a] cull: 1 cull: 2 cull: 3 ] Eval [ [:a :b |a] cull: 1 ] Eval [ [:a :b |a] cull: 1 cull: 2 ] Eval [ [:a :b |a] cull: 1 cull: 2 cull: 3 ] Eval [ [:a :b |b] cull: 1 cull: 2 ] Eval [ [:a :b |b] cull: 1 cull: 2 cull: 3 ] Eval [ [:a :b :c |a] cull: 1 cull: 2 ] Eval [ [:a :b :c |a] cull: 1 cull: 2 cull: 3 ] Eval [ [:a :b :c |b] cull: 1 cull: 2 cull: 3 ] Eval [ [:a :b :c |c] cull: 1 cull: 2 cull: 3 ] smalltalk-3.2.5/tests/quit.st0000644000175000017500000000227712123404352013126 00000000000000"====================================================================== | | Test quitting | | ======================================================================" "====================================================================== | | Copyright (C) 2006, 2007, 2008 Free Software Foundation. | Written by Paolo Bonzini | | This file is part of GNU Smalltalk. | | GNU Smalltalk is free software; you can redistribute it and/or modify it | under the terms of the GNU General Public License as published by the Free | Software Foundation; either version 2, or (at your option) any later version. | | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS | FOR A PARTICULAR PURPOSE. See the GNU General Public License for more | details. | | You should have received a copy of the GNU General Public License along with | GNU Smalltalk; see the file COPYING. If not, write to the Free Software | Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. | ======================================================================" Eval [ ObjectMemory quit: 0; quit: 1 ] Eval [ 'foo' ] smalltalk-3.2.5/tests/Makefile.am0000644000175000017500000000521412130343734013626 00000000000000nodist_check_DATA = gst.im AUTOTEST = $(AUTOM4TE) --language=autotest TESTSUITE = $(srcdir)/testsuite dist_noinst_DATA = \ atlocal.in local.at testsuite.at $(TESTSUITE) package.m4 \ ackermann.ok ackermann.st arrays.ok arrays.st ary3.ok ary3.st blocks.ok \ blocks.st chars.ok chars.st classes.ok classes.st cobjects.ok cobjects.st \ compiler.ok compiler.st dates.ok dates.st delays.ok delays.st except.ok \ except.st exceptions.ok exceptions.st fibo.ok fibo.st fileext.ok fileext.st \ floatmath.ok floatmath.st getopt.ok getopt.st geometry.ok geometry.st hash.ok \ hash.st hash2.ok hash2.st heapsort.ok heapsort.st intmath.ok intmath.st \ lists.ok lists.st lists1.ok lists1.st lists2.ok lists2.st matrix.ok \ matrix.st methcall.ok methcall.st mutate.ok mutate.st nestedloop.ok \ nestedloop.st objdump.ok objdump.st objects.ok objects.st objinst.ok \ objinst.st processes.ok processes.st prodcons.ok prodcons.st quit.ok \ quit.st random-bench.ok random-bench.st untrusted.ok untrusted.st sets.ok \ sets.st sieve.ok sieve.st strcat.ok strcat.st strings.ok strings.st \ pools.ok pools.st Ansi.st AnsiDB.st AnsiInit.st AnsiLoad.st AnsiRun.st \ stcompiler.st stcompiler.ok shape.st shape.ok streams.st streams.ok CLEANFILES = gst.im DISTCLEANFILES = atconfig .PHONY: regress regress: cd $(srcdir) || exit 1; \ for test in $(TESTS); do \ result=`echo $$test | $(SED) 's/st$$/ok/'`; \ @abs_top_builddir@/gst --image=@abs_top_builddir@/gst.im -r $$test 2>&1 | tee $$result; \ done gst.im: ../kernel/stamp-classes AnsiLoad.st Ansi.st AnsiDB.st echo "PackageLoader fileInPackage: #SUnit. ObjectMemory snapshot: 'gst.im'" | ./gst --image=../gst.im - cd $(srcdir) && @abs_builddir@/gst -S --image=@abs_top_builddir@/tests/gst.im AnsiLoad.st $(srcdir)/package.m4: $(top_srcdir)/configure.ac { \ echo '# Signature of the current package.'; \ echo 'm4_define([AT_PACKAGE_NAME], [@PACKAGE_NAME@])'; \ echo 'm4_define([AT_PACKAGE_TARNAME], [@PACKAGE_TARNAME@])'; \ echo 'm4_define([AT_PACKAGE_VERSION], [@PACKAGE_VERSION@])'; \ echo 'm4_define([AT_PACKAGE_STRING], [@PACKAGE_STRING@])'; \ echo 'm4_define([AT_PACKAGE_BUGREPORT], [@PACKAGE_BUGREPORT@])'; \ } >'$(srcdir)/package.m4' check-local: gst atlocal atconfig $(TESTSUITE) $(SHELL) '$(TESTSUITE)' $(TESTSUITEFLAGS) clean-local: -$(SHELL) '$(TESTSUITE)' --clean installcheck-local: atlocal atconfig $(TESTSUITE) if test -z "$(DESTDIR)"; then \ $(SHELL) '$(TESTSUITE)' $(TESTSUITEFLAGS) AUTOTEST_PATH=$(bindir); \ fi $(TESTSUITE): $(srcdir)/testsuite.at $(srcdir)/package.m4 $(srcdir)/local.at $(AUTOTEST) -I '$(srcdir)' -o $@.tmp $@.at mv $@.tmp $@ smalltalk-3.2.5/tests/except.ok0000644000175000017500000000031712123404352013410 00000000000000 Execution begins... returned value is LoException Execution begins... returned value is HiException Execution begins... Exceptions: HI=25000 / LO=25000 returned value is 'Exceptions: HI=25000 / LO=25000' smalltalk-3.2.5/tests/compiler.ok0000644000175000017500000000504712130343734013743 00000000000000 Execution begins... returned value is 32 compiler.st:45: undefined variable undefVariable referenced Execution begins... returned value is Array new: 3 "<0>" Execution begins... returned value is 'bar' Execution begins... returned value is 100 Execution begins... returned value is 1 Execution begins... returned value is Message Execution begins... returned value is #test Execution begins... returned value is Array new: 0 "<0>" Execution begins... returned value is 1 Execution begins... returned value is Message Execution begins... returned value is #test: Execution begins... returned value is Array new: 1 "<0>" Execution begins... returned value is 1 Execution begins... returned value is Message Execution begins... returned value is #primitive: Execution begins... returned value is Array new: 1 "<0>" Execution begins... returned value is 2 compiler.st:182: parse error, expected '!' compiler.st:185: parse error, expected keyword Execution begins... returned value is 2 Execution begins... returned value is 'No crashes' compiler.st:195: undefined variable C referenced Execution begins... a Smalltalk string:1: undefined variable a referenced returned value is nil Execution begins... error: did not understand #gotcha returned value is nil Execution begins... returned value is 'nineteen' Execution begins... returned value is 'ABC' Execution begins... returned value is 0 Execution begins... returned value is 0 Execution begins... returned value is 0 Execution begins... returned value is 0 Execution begins... returned value is 0 Execution begins... returned value is 0.00000 Execution begins... returned value is '-123.000s3' Execution begins... a Smalltalk string:1: parse error, expected positive numeric literal returned value is CompiledMethod new: 8 "<0>" Execution begins... a Smalltalk string:1: parse error, expected positive numeric literal returned value is CompiledMethod new: 8 "<0>" Execution begins... a Smalltalk string:1: parse error, expected positive numeric literal returned value is CompiledMethod new: 8 "<0>" Execution begins... a Smalltalk string:1: parse error, expected positive numeric literal returned value is CompiledMethod new: 8 "<0>" Execution begins... returned value is FileSegment Execution begins... returned value is String compiler.st:321: class method expected inside class block Execution begins... returned value is CompiledMethod new: 0 "<0>" Execution begins... error: Invalid argument #a: key not found returned value is nil Execution begins... 'abc' 'def' returned value is ReadStream new "<0>" smalltalk-3.2.5/tests/hash2.ok0000644000175000017500000000011112123404352013115 00000000000000 Execution begins... 1 9999 10 99990 returned value is '1 9999 10 99990' smalltalk-3.2.5/tests/delays.st0000644000175000017500000000607212123404352013422 00000000000000"====================================================================== | | Test delays | | ======================================================================" "====================================================================== | | Copyright (C) 1999, 2007, 2008 Free Software Foundation. | Written by Paolo Bonzini | | This file is part of GNU Smalltalk. | | GNU Smalltalk is free software; you can redistribute it and/or modify it | under the terms of the GNU General Public License as published by the Free | Software Foundation; either version 2, or (at your option) any later version. | | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS | FOR A PARTICULAR PURPOSE. See the GNU General Public License for more | details. | | You should have received a copy of the GNU General Public License along with | GNU Smalltalk; see the file COPYING. If not, write to the Free Software | Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. | ======================================================================" Eval [ | i j | i := 4. [ [ (Delay forSeconds: 1) wait. i > 1 ] whileTrue: [ i := i - 1 ]. ] forkAt: Processor userInterruptPriority. [ (j := i) printNl. [ i = j ] whileTrue. i > 1 ] whileTrue ] Eval [ Smalltalk at: #MySemaphore put: Semaphore new. (Delay forSeconds: 1) timedWaitOn: MySemaphore ] Eval [ | msec s expired | s := Semaphore new. [ (Delay forSeconds: 3) wait. s signal ] fork. msec := Time millisecondsToRun: [ expired := (Delay forSeconds: 10) timedWaitOn: s ]. ^expired not and: [ msec between: 2500 and: 4500 ] ] "Test timeouts" Eval [ (Delay forSeconds: 1) value: [[(Delay forSeconds: 1000000) wait.] ensure: ['ensure' printNl]] onTimeoutDo: ['timeout' printNl]. ] Eval [ (Delay forSeconds: 1) value: [[(Delay forSeconds: 1000000) wait.] ifCurtailed: ['ifCurtailed' printNl]] onTimeoutDo: ['timeout' printNl]. ] Eval [ [ (Delay forSeconds: 1) value: [ [ (Delay forSeconds: 100000) value: [[(Delay forSeconds: 10000) wait] ensure: ['ensure-in' printNl]] onTimeoutDo: ['timeout-inner' printNl]. ] ensure: ['ensure-mid' printNl]] onTimeoutDo: ['timeout' printNl]. ] ensure: ['ensure-out' printNl]. ] Eval [ |d| d := Delay forSeconds: 1. d wait. ^(Time millisecondsToRun: [ d wait ]) >= 500 ] Eval [ | d1 d2 p1 p2 | sem := Semaphore new. d1 := Delay forSeconds: 1. p1 := [ d1 value: [ sem signal ] onTimeoutDo: [ ] ] fork. sem wait. 'value:onTimeoutDo:' displayNl. d1 := Delay forMilliseconds: 100. d1 value: [ [ true ] whileTrue ] onTimeoutDo: [ ]. [ p1 isTerminated ] whileFalse: [ Processor yield ] ] smalltalk-3.2.5/tests/stcompiler.ok0000644000175000017500000000174312123404352014305 00000000000000 Execution begins... Loading package Parser Execution begins... returned value is RBScanner Execution begins... returned value is IdentityDictionary new: 128 "<0>" Execution begins... returned value is DefaultPoolResolution Execution begins... returned value is STCompiler Loading package Compiler returned value is 3 Execution begins... 'before everything' -2 -1 0 1 2 3 4 5 6 7 8 'okay' 'okay' now I'm testing 'Cascading' (true false nil 53 $a ByteArray (1 2 3 ) (1 2 3 ) {Smalltalk.Association} #perform: #perform:with: ' Arrays... and multi-line strings' ) and now blocks with parameters... 'okay' [] in UndefinedObject>>executeStatements (a String:1) finally, many parameters, cascading and block temporaries too! returned value is TextCollector new "<0>" Execution begins... returned value is OrderedSet new: 32 "<0>" Execution begins... returned value is OrderedSet new: 32 "<0>" Execution begins... returned value is 'an' Execution begins... true true returned value is true smalltalk-3.2.5/tests/fibo.ok0000644000175000017500000000005512123404352013036 00000000000000 Execution begins... 34 returned value is 34 smalltalk-3.2.5/tests/lists1.st0000644000175000017500000000405612123404352013360 00000000000000"====================================================================== | | Benchmark for OrderedCollections (2) | | ======================================================================" "====================================================================== | | Copyright (C) 2003, 2007, 2008 Free Software Foundation. | Written by Paolo Bonzini | | This file is part of GNU Smalltalk. | | GNU Smalltalk is free software; you can redistribute it and/or modify it | under the terms of the GNU General Public License as published by the Free | Software Foundation; either version 2, or (at your option) any later version. | | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS | FOR A PARTICULAR PURPOSE. See the GNU General Public License for more | details. | | You should have received a copy of the GNU General Public License along with | GNU Smalltalk; see the file COPYING. If not, write to the Free Software | Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. | ======================================================================" SmallInteger extend [ test [ | a b sum | b := OrderedCollection new: self. a := (1 to: self) asOrderedCollection. [ a isEmpty ] whileFalse: [ b addLast: a removeLast ]. ('%1 %2' % { b at: 1. b at: 2 }) displayNl. b := b reverse. (b includes: 0) printNl. (b includes: self) printNl. a := b select: [ :each | each < (self // 2) ]. (a copyFrom: 1 to: (10 min: a size)) do: [ :each | each print ] separatedBy: [ Transcript space ]. Transcript nl. sum := a inject: 0 into: [ :old :each | each < 1000 ifTrue: [ old + each ] ifFalse: [ old ] ]. sum printNl. a := a, b. ('%1 %2' % { a size. a last }) displayNl ] ] Eval [ n := Smalltalk arguments isEmpty ifTrue: [ 100000 ] ifFalse: [ 1 max: Smalltalk arguments first asInteger ]. n test ] smalltalk-3.2.5/tests/stcompiler.st0000644000175000017500000001045112123404352014316 00000000000000"====================================================================== | | Regression tests for the STInST compiler | | ======================================================================" "====================================================================== | | Copyright (C) 1999, 200, 2001, 2002, 2011 Free Software Foundation. | Written by Paolo Bonzini and Holger Hans Peter Freyther. | | This file is part of GNU Smalltalk. | | GNU Smalltalk is free software; you can redistribute it and/or modify it | under the terms of the GNU General Public License as published by the Free | Software Foundation; either version 2, or (at your option) any later version. | | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS | FOR A PARTICULAR PURPOSE. See the GNU General Public License for more | details. | | You should have received a copy of the GNU General Public License along with | GNU Smalltalk; see the file COPYING. If not, write to the Free Software | Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. | ======================================================================" Eval [ "This is testing bug: http://smalltalk.gnu.org/project/issue/527" PackageLoader fileInPackage: 'Compiler'. Behavior evaluate: '3'. ] Eval [ "Random code to test features of the parser" PackageLoader fileInPackage: #Compiler. STInST.STEvaluationDriver new parseSmalltalk: ' | i | i := ##(| a | a := -2. ''before everything'' printNl. a). [ i < 5 ] whileTrue: [ i printNl. i := i + 1 ]. [ i = (900 // 100) ] whileFalse: [ i printNl. i := i + 1 ]. i even ifTrue: [ i printNl ]. i odd ifFalse: [ i printNl ]. (i even or: [i odd]) ifTrue: [ ''okay'' printNl] ifFalse: [ ''huh?!?'' printNl ]. (i even and: [i odd]) ifFalse: [ ''okay'' printNl] ifTrue: [ ''huh?!?'' printNl ]. Transcript nextPutAll: ''now I''''m testing ''; print: ''Cascading''; nl. #(true false nil 53 $a [1 2 3] (1 2 3) #{Smalltalk.Association} #perform: #''perform:with:'' '' Arrays... and multi-line strings'') printNl. #(''and now'' '' blocks with parameters...'') do: [ :each | Transcript nextPutAll: each ]. [ :a :b :c | | temp | temp := Smalltalk::Transcript. temp nl; print: (i = 9 ifTrue: [ ''okay'' ] ifFalse: [ ''huh?!?'' ]); nl; print: thisContext; nl; nextPutAll: a; nl; nextPutAll: b; nl; nextPutAll: c; nl ] value: ''finally, many parameters, '' value: ''cascading '' value: ''and block temporaries too! ''. !' with: STInST.STFileInParser. ] Eval [ | squeak | "Test the import of squeak code" squeak := '!String methodsFor: ''*petitparser-core-converting'' stamp: ''lr 11/7/2009 13:32''! asParser ^ PPLiteralSequenceParser on: self! !'. STInST.STClassLoader new parseSmalltalkStream: squeak readStream with: STInST.SqueakFileInParser. ] Eval [ | squeak | "Test literal parsing" squeak := '!String methodsFor: ''*unit-test'' stamp: ''lr 11/7/2009 13:32''! literalValueFoo12345 ^ 16rabcdef! !'. STInST.STClassLoader new parseSmalltalkStream: squeak readStream with: STInST.SqueakFileInParser. ] Eval [ | classes | "Attempt to parse a pragma with multiple parameters" classes := STInST.STClassLoader new parseSmalltalkStream: 'Object subclass: Bla [ ]' readStream with: STInST.GSTFileInParser. "Check if the proxy has a proper behavior" classes := STInST.STClassLoader new parseSmalltalkStream: 'Object subclass: Foo []' readStream with: STInST.GSTFileInParser. classes first article ] Eval [ | classes bla | "Check class variable parsing.." classes := STInST.STClassLoader new parseSmalltalkStream: 'Object subclass: Bla [ ClassInst := nil ]' readStream with: STInST.GSTFileInParser. "Check that both end in the bucket" bla := classes first. (bla sharedPools = #('STInST') asOrderedCollection) printNl. (bla classVarNames = #('ClassInst') asOrderedCollection) printNl. ] smalltalk-3.2.5/tests/getopt.st0000644000175000017500000000626512123404352013447 00000000000000"====================================================================== | | Smalltalk command-line parser tests | | ======================================================================" "====================================================================== | | Copyright 2006, 2007, 2008 Free Software Foundation, Inc. | Written by Paolo Bonzini. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" Getopt extend [ Getopt class [ test: args with: pattern [ args do: [ :each | self parse: each subStrings with: pattern do: [ :x :y | (x->y) printNl ] ifError: [ (each->'error') displayNl ]. Transcript nl ] ] ] testParsing: p [ self parsePattern: p. prefixes asSortedCollection printNl. (options keys asSortedCollection: [ :a :b | a asString < b asString ]) do: [ :k | (options associationAt: k) printNl ] ] ] Eval [ Getopt new testParsing: '-B' ] Eval [ Getopt new testParsing: '--long' ] Eval [ Getopt new testParsing: '--longish --longer' ] Eval [ Getopt new testParsing: '--long --longer' ] Eval [ Getopt new testParsing: '-B:' ] Eval [ Getopt new testParsing: '-B::' ] Eval [ Getopt new testParsing: '-a|-b' ] Eval [ Getopt new testParsing: '-a|--long' ] Eval [ Getopt new testParsing: '-a|--very-long|--long' ] Eval [ Getopt test: #('-a' '-b' '-ab' '-a -b') with: '-a -b' ] Eval [ Getopt test: #('-a' '-b' '-ab' '-a -b') with: '-a: -b' ] Eval [ Getopt test: #('-a' '-b' '-ab' '-a -b') with: '-a:: -b' ] Eval [ Getopt test: #('--longish' '--longer' '--longi' '--longe' '--lo' '-longer') with: '--longish --longer' ] Eval [ Getopt test: #('--lo' '--long' '--longe' '--longer') with: '--long --longer' ] Eval [ Getopt test: #('--noarg' '--mandatory' '--mandatory foo' '--mandatory=' '--mandatory=foo' '--optional' '--optional foo') with: '--noarg --mandatory: --optional::' ] Eval [ Getopt test: #('-a' '-b') with: '-a|-b' ] Eval [ Getopt test: #('--long' '-b') with: '-b|--long' ] Eval [ Getopt test: #('--long=x' '-bx') with: '-b|--long:' ] Eval [ Getopt test: #('-b' '--long' '--very-long') with: '-b|--very-long|--long' ] Eval [ Getopt test: #('--long=x' '--very-long x' '-bx') with: '-b|--very-long|--long:' ] Eval [ Getopt test: #('-b -- -b' '-- -b' '-- -b -b') with: '-b' ] smalltalk-3.2.5/tests/sieve.st0000644000175000017500000000312212123404352013245 00000000000000"====================================================================== | | How can Sieve be missing? | | ======================================================================" "====================================================================== | | Copyright (C) 2003, 2007, 2008 Free Software Foundation. | Written by Paolo Bonzini | | This file is part of GNU Smalltalk. | | GNU Smalltalk is free software; you can redistribute it and/or modify it | under the terms of the GNU General Public License as published by the Free | Software Foundation; either version 2, or (at your option) any later version. | | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS | FOR A PARTICULAR PURPOSE. See the GNU General Public License for more | details. | | You should have received a copy of the GNU General Public License along with | GNU Smalltalk; see the file COPYING. If not, write to the Free Software | Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. | ======================================================================" Eval [ n := Smalltalk arguments isEmpty ifTrue: [ 1 ] ifFalse: [ 1 max: Smalltalk arguments first asInteger ]. flags0 := Array new: 8192 withAll: true. n timesRepeat: [ count := 0. flags := flags0 copy. 2 to: 8192 do: [ :i | (flags at: i) ifTrue: [ i+i to: 8192 by: i do: [ :j | flags at: j put: false ]. count := count + 1 ]]. ]. ('Count: %1' % { count }) displayNl ] smalltalk-3.2.5/tests/heapsort.ok0000644000175000017500000000010312123404352013736 00000000000000 Execution begins... 0.9990640718 returned value is '0.9990640718' smalltalk-3.2.5/tests/package.m40000644000175000017500000000044612130343734013431 00000000000000# Signature of the current package. m4_define([AT_PACKAGE_NAME], [GNU Smalltalk]) m4_define([AT_PACKAGE_TARNAME], [smalltalk]) m4_define([AT_PACKAGE_VERSION], [3.2.5]) m4_define([AT_PACKAGE_STRING], [GNU Smalltalk 3.2.5]) m4_define([AT_PACKAGE_BUGREPORT], [help-smalltalk@gnu.org]) smalltalk-3.2.5/tests/Makefile.in0000644000175000017500000004206612130455426013647 00000000000000# Makefile.in generated by automake 1.11.6 from Makefile.am. # @configure_input@ # Copyright (C) 1994, 1995, 1996, 1997, 1998, 1999, 2000, 2001, 2002, # 2003, 2004, 2005, 2006, 2007, 2008, 2009, 2010, 2011 Free Software # Foundation, Inc. # This Makefile.in is free software; the Free Software Foundation # gives unlimited permission to copy and/or distribute it, # with or without modifications, as long as this notice is preserved. # This program is distributed in the hope that it will be useful, # but WITHOUT ANY WARRANTY, to the extent permitted by law; without # even the implied warranty of MERCHANTABILITY or FITNESS FOR A # PARTICULAR PURPOSE. @SET_MAKE@ VPATH = @srcdir@ am__make_dryrun = \ { \ am__dry=no; \ case $$MAKEFLAGS in \ *\\[\ \ ]*) \ echo 'am--echo: ; @echo "AM" OK' | $(MAKE) -f - 2>/dev/null \ | grep '^AM OK$$' >/dev/null || am__dry=yes;; \ *) \ for am__flg in $$MAKEFLAGS; do \ case $$am__flg in \ *=*|--*) ;; \ *n*) am__dry=yes; break;; \ esac; \ done;; \ esac; \ test $$am__dry = yes; \ } pkgdatadir = $(datadir)/@PACKAGE@ pkgincludedir = $(includedir)/@PACKAGE@ pkglibdir = $(libdir)/@PACKAGE@ pkglibexecdir = $(libexecdir)/@PACKAGE@ am__cd = CDPATH="$${ZSH_VERSION+.}$(PATH_SEPARATOR)" && cd install_sh_DATA = $(install_sh) -c -m 644 install_sh_PROGRAM = $(install_sh) -c install_sh_SCRIPT = $(install_sh) -c INSTALL_HEADER = $(INSTALL_DATA) transform = $(program_transform_name) NORMAL_INSTALL = : PRE_INSTALL = : POST_INSTALL = : NORMAL_UNINSTALL = : PRE_UNINSTALL = : POST_UNINSTALL = : build_triplet = @build@ host_triplet = @host@ subdir = tests DIST_COMMON = $(dist_noinst_DATA) $(srcdir)/Makefile.am \ $(srcdir)/Makefile.in $(srcdir)/atlocal.in $(srcdir)/gst.in ACLOCAL_M4 = $(top_srcdir)/aclocal.m4 am__aclocal_m4_deps = $(top_srcdir)/build-aux/bold.m4 \ $(top_srcdir)/build-aux/codeset.m4 \ $(top_srcdir)/build-aux/emacs-pkg.m4 \ $(top_srcdir)/build-aux/emacs-site-start.m4 \ $(top_srcdir)/build-aux/ext_goto.m4 \ $(top_srcdir)/build-aux/gawk.m4 $(top_srcdir)/build-aux/gcc.m4 \ $(top_srcdir)/build-aux/gl.m4 \ $(top_srcdir)/build-aux/glib-2.0.m4 \ $(top_srcdir)/build-aux/glut.m4 $(top_srcdir)/build-aux/gmp.m4 \ $(top_srcdir)/build-aux/gst-package.m4 \ $(top_srcdir)/build-aux/gtk-2.0.m4 \ $(top_srcdir)/build-aux/iconv.m4 \ $(top_srcdir)/build-aux/lib-ld.m4 \ $(top_srcdir)/build-aux/lib-link.m4 \ $(top_srcdir)/build-aux/lib-prefix.m4 \ $(top_srcdir)/build-aux/lib.m4 \ $(top_srcdir)/build-aux/libc-so-name.m4 \ $(top_srcdir)/build-aux/libtool.m4 \ $(top_srcdir)/build-aux/lightning.m4 \ $(top_srcdir)/build-aux/ln.m4 \ $(top_srcdir)/build-aux/localtime.m4 \ $(top_srcdir)/build-aux/lock.m4 \ $(top_srcdir)/build-aux/long-double.m4 \ $(top_srcdir)/build-aux/lrint.m4 \ $(top_srcdir)/build-aux/ltdl-gst.m4 \ $(top_srcdir)/build-aux/ltoptions.m4 \ $(top_srcdir)/build-aux/ltsugar.m4 \ $(top_srcdir)/build-aux/ltversion.m4 \ $(top_srcdir)/build-aux/lt~obsolete.m4 \ $(top_srcdir)/build-aux/modules.m4 \ $(top_srcdir)/build-aux/pkg.m4 $(top_srcdir)/build-aux/poll.m4 \ $(top_srcdir)/build-aux/readline.m4 \ $(top_srcdir)/build-aux/relocatable.m4 \ $(top_srcdir)/build-aux/setenv.m4 \ $(top_srcdir)/build-aux/snprintfv.m4 \ $(top_srcdir)/build-aux/sockets.m4 \ $(top_srcdir)/build-aux/sockpfaf.m4 \ $(top_srcdir)/build-aux/strtoul.m4 \ $(top_srcdir)/build-aux/sync-builtins.m4 \ $(top_srcdir)/build-aux/tcltk.m4 \ $(top_srcdir)/build-aux/version.m4 \ $(top_srcdir)/build-aux/vis-hidden.m4 \ $(top_srcdir)/build-aux/wine.m4 $(top_srcdir)/configure.ac am__configure_deps = $(am__aclocal_m4_deps) $(CONFIGURE_DEPENDENCIES) \ $(ACLOCAL_M4) mkinstalldirs = $(install_sh) -d CONFIG_HEADER = $(top_builddir)/config.h CONFIG_CLEAN_FILES = gst atlocal CONFIG_CLEAN_VPATH_FILES = SOURCES = DIST_SOURCES = am__can_run_installinfo = \ case $$AM_UPDATE_INFO_DIR in \ n|no|NO) false;; \ *) (install-info --version) >/dev/null 2>&1;; \ esac DATA = $(dist_noinst_DATA) DISTFILES = $(DIST_COMMON) $(DIST_SOURCES) $(TEXINFOS) $(EXTRA_DIST) ACLOCAL = @ACLOCAL@ ALLOCA = @ALLOCA@ ALL_PACKAGES = @ALL_PACKAGES@ AMTAR = @AMTAR@ AR = @AR@ AS = @AS@ ATK_CFLAGS = @ATK_CFLAGS@ ATK_LIBS = @ATK_LIBS@ AUTOCONF = @AUTOCONF@ AUTOHEADER = @AUTOHEADER@ AUTOM4TE = @AUTOM4TE@ AUTOMAKE = @AUTOMAKE@ AWK = @AWK@ BLOX_IMPLEMENTATION = @BLOX_IMPLEMENTATION@ BUILT_PACKAGES = @BUILT_PACKAGES@ CAIRO_CFLAGS = @CAIRO_CFLAGS@ CAIRO_LIBS = @CAIRO_LIBS@ CC = @CC@ CCDEPMODE = @CCDEPMODE@ CFLAGS = @CFLAGS@ CPP = @CPP@ CPPFLAGS = @CPPFLAGS@ CYGPATH_W = @CYGPATH_W@ DEFS = @DEFS@ DEPDIR = @DEPDIR@ DLLTOOL = @DLLTOOL@ DSYMUTIL = @DSYMUTIL@ DUMPBIN = @DUMPBIN@ ECHO_C = @ECHO_C@ ECHO_N = @ECHO_N@ ECHO_T = @ECHO_T@ EGREP = @EGREP@ EMACS = @EMACS@ EMACSLOADPATH = @EMACSLOADPATH@ EXEEXT = @EXEEXT@ FGREP = @FGREP@ GLIB_CFLAGS = @GLIB_CFLAGS@ GLIB_GENMARSHAL = @GLIB_GENMARSHAL@ GLIB_LIBS = @GLIB_LIBS@ GLIB_MKENUMS = @GLIB_MKENUMS@ GNUTLS_CFLAGS = @GNUTLS_CFLAGS@ GNUTLS_LIBS = @GNUTLS_LIBS@ GOBJECT_QUERY = @GOBJECT_QUERY@ GPERF = @GPERF@ GREP = @GREP@ GST_RUN = @GST_RUN@ GTHREAD_CFLAGS = @GTHREAD_CFLAGS@ GTHREAD_LIBS = @GTHREAD_LIBS@ GTK_CFLAGS = @GTK_CFLAGS@ GTK_LIBS = @GTK_LIBS@ ICON = @ICON@ INCFFI = @INCFFI@ INCLTDL = @INCLTDL@ INCSIGSEGV = @INCSIGSEGV@ INCSNPRINTFV = @INCSNPRINTFV@ INCTCLTK = @INCTCLTK@ INSTALL = @INSTALL@ INSTALL_DATA = @INSTALL_DATA@ INSTALL_INFO = @INSTALL_INFO@ INSTALL_PROGRAM = @INSTALL_PROGRAM@ INSTALL_SCRIPT = @INSTALL_SCRIPT@ INSTALL_STRIP_PROGRAM = @INSTALL_STRIP_PROGRAM@ LD = @LD@ LDFLAGS = @LDFLAGS@ LEX = @LEX@ LIBADD_DL = @LIBADD_DL@ LIBC_SO_DIR = @LIBC_SO_DIR@ LIBC_SO_NAME = @LIBC_SO_NAME@ LIBFFI = @LIBFFI@ LIBFFI_CFLAGS = @LIBFFI_CFLAGS@ LIBFFI_EXECUTABLE_LDFLAGS = @LIBFFI_EXECUTABLE_LDFLAGS@ LIBFFI_LIBS = @LIBFFI_LIBS@ LIBGLUT = @LIBGLUT@ LIBGMP = @LIBGMP@ LIBGST_CFLAGS = @LIBGST_CFLAGS@ LIBICONV = @LIBICONV@ LIBLTDL = @LIBLTDL@ LIBOBJS = @LIBOBJS@ LIBOPENGL = @LIBOPENGL@ LIBREADLINE = @LIBREADLINE@ LIBS = @LIBS@ LIBSIGSEGV = @LIBSIGSEGV@ LIBSNPRINTFV = @LIBSNPRINTFV@ LIBTCLTK = @LIBTCLTK@ LIBTHREAD = @LIBTHREAD@ LIBTOOL = @LIBTOOL@ LIPO = @LIPO@ LN = @LN@ LN_S = @LN_S@ LTALLOCA = @LTALLOCA@ LTLIBICONV = @LTLIBICONV@ LTLIBOBJS = @LTLIBOBJS@ MAINTAINER = @MAINTAINER@ MAKEINFO = @MAKEINFO@ MANIFEST_TOOL = @MANIFEST_TOOL@ MKDIR_P = @MKDIR_P@ MODULES = @MODULES@ NM = @NM@ NMEDIT = @NMEDIT@ OBJC = @OBJC@ OBJCDEPMODE = @OBJCDEPMODE@ OBJCFLAGS = @OBJCFLAGS@ OBJDUMP = @OBJDUMP@ OBJEXT = @OBJEXT@ OTOOL = @OTOOL@ OTOOL64 = @OTOOL64@ PACKAGE = @PACKAGE@ PACKAGE_BUGREPORT = @PACKAGE_BUGREPORT@ PACKAGE_DLOPEN_FLAGS = @PACKAGE_DLOPEN_FLAGS@ PACKAGE_NAME = @PACKAGE_NAME@ PACKAGE_STRING = @PACKAGE_STRING@ PACKAGE_TARNAME = @PACKAGE_TARNAME@ PACKAGE_URL = @PACKAGE_URL@ PACKAGE_VERSION = @PACKAGE_VERSION@ PANGO_CFLAGS = @PANGO_CFLAGS@ PANGO_LIBS = @PANGO_LIBS@ PATH_SEPARATOR = @PATH_SEPARATOR@ PKG_CONFIG = @PKG_CONFIG@ RANLIB = @RANLIB@ RELOCATABLE = @RELOCATABLE@ RELOC_CPPFLAGS = @RELOC_CPPFLAGS@ RELOC_LDFLAGS = @RELOC_LDFLAGS@ SDL_CFLAGS = @SDL_CFLAGS@ SDL_LIBS = @SDL_LIBS@ SED = @SED@ SET_MAKE = @SET_MAKE@ SHELL = @SHELL@ SOCKET_LIBS = @SOCKET_LIBS@ STRIP = @STRIP@ SYNC_CFLAGS = @SYNC_CFLAGS@ TCLSH = @TCLSH@ TIMEOUT = @TIMEOUT@ VERSION = @VERSION@ VERSION_INFO = @VERSION_INFO@ WINDRES = @WINDRES@ WINEWRAPPER = @WINEWRAPPER@ WINEWRAPPERDEP = @WINEWRAPPERDEP@ XMKMF = @XMKMF@ XZIP = @XZIP@ X_CFLAGS = @X_CFLAGS@ X_EXTRA_LIBS = @X_EXTRA_LIBS@ X_LIBS = @X_LIBS@ X_PRE_LIBS = @X_PRE_LIBS@ YACC = @YACC@ ZIP = @ZIP@ abs_builddir = @abs_builddir@ abs_srcdir = @abs_srcdir@ abs_top_builddir = @abs_top_builddir@ abs_top_srcdir = @abs_top_srcdir@ ac_ct_AR = @ac_ct_AR@ ac_ct_CC = @ac_ct_CC@ ac_ct_DUMPBIN = @ac_ct_DUMPBIN@ am__include = @am__include@ am__leading_dot = @am__leading_dot@ am__quote = @am__quote@ am__tar = @am__tar@ am__untar = @am__untar@ bindir = @bindir@ build = @build@ build_alias = @build_alias@ build_cpu = @build_cpu@ build_os = @build_os@ build_vendor = @build_vendor@ builddir = @builddir@ datadir = @datadir@ datarootdir = @datarootdir@ docdir = @docdir@ dvidir = @dvidir@ enable_mysql_tests = @enable_mysql_tests@ exec_prefix = @exec_prefix@ host = @host@ host_alias = @host_alias@ host_cpu = @host_cpu@ host_os = @host_os@ host_vendor = @host_vendor@ htmldir = @htmldir@ imagedir = @imagedir@ includedir = @includedir@ infodir = @infodir@ install_sh = @install_sh@ libdir = @libdir@ libexecdir = @libexecdir@ lispdir = @lispdir@ lispstartdir = @lispstartdir@ localedir = @localedir@ localstatedir = @localstatedir@ mandir = @mandir@ mkdir_p = @mkdir_p@ moduledir = @moduledir@ moduleexecdir = @moduleexecdir@ oldincludedir = @oldincludedir@ pdfdir = @pdfdir@ prefix = @prefix@ program_transform_name = @program_transform_name@ psdir = @psdir@ sbindir = @sbindir@ sharedstatedir = @sharedstatedir@ srcdir = @srcdir@ subdirs = @subdirs@ sysconfdir = @sysconfdir@ target_alias = @target_alias@ top_build_prefix = @top_build_prefix@ top_builddir = @top_builddir@ top_srcdir = @top_srcdir@ nodist_check_DATA = gst.im AUTOTEST = $(AUTOM4TE) --language=autotest TESTSUITE = $(srcdir)/testsuite dist_noinst_DATA = \ atlocal.in local.at testsuite.at $(TESTSUITE) package.m4 \ ackermann.ok ackermann.st arrays.ok arrays.st ary3.ok ary3.st blocks.ok \ blocks.st chars.ok chars.st classes.ok classes.st cobjects.ok cobjects.st \ compiler.ok compiler.st dates.ok dates.st delays.ok delays.st except.ok \ except.st exceptions.ok exceptions.st fibo.ok fibo.st fileext.ok fileext.st \ floatmath.ok floatmath.st getopt.ok getopt.st geometry.ok geometry.st hash.ok \ hash.st hash2.ok hash2.st heapsort.ok heapsort.st intmath.ok intmath.st \ lists.ok lists.st lists1.ok lists1.st lists2.ok lists2.st matrix.ok \ matrix.st methcall.ok methcall.st mutate.ok mutate.st nestedloop.ok \ nestedloop.st objdump.ok objdump.st objects.ok objects.st objinst.ok \ objinst.st processes.ok processes.st prodcons.ok prodcons.st quit.ok \ quit.st random-bench.ok random-bench.st untrusted.ok untrusted.st sets.ok \ sets.st sieve.ok sieve.st strcat.ok strcat.st strings.ok strings.st \ pools.ok pools.st Ansi.st AnsiDB.st AnsiInit.st AnsiLoad.st AnsiRun.st \ stcompiler.st stcompiler.ok shape.st shape.ok streams.st streams.ok CLEANFILES = gst.im DISTCLEANFILES = atconfig all: all-am .SUFFIXES: $(srcdir)/Makefile.in: $(srcdir)/Makefile.am $(am__configure_deps) @for dep in $?; do \ case '$(am__configure_deps)' in \ *$$dep*) \ ( cd $(top_builddir) && $(MAKE) $(AM_MAKEFLAGS) am--refresh ) \ && { if test -f $@; then exit 0; else break; fi; }; \ exit 1;; \ esac; \ done; \ echo ' cd $(top_srcdir) && $(AUTOMAKE) --gnu tests/Makefile'; \ $(am__cd) $(top_srcdir) && \ $(AUTOMAKE) --gnu tests/Makefile .PRECIOUS: Makefile Makefile: $(srcdir)/Makefile.in $(top_builddir)/config.status @case '$?' in \ *config.status*) \ cd $(top_builddir) && $(MAKE) $(AM_MAKEFLAGS) am--refresh;; \ *) \ echo ' cd $(top_builddir) && $(SHELL) ./config.status $(subdir)/$@ $(am__depfiles_maybe)'; \ cd $(top_builddir) && $(SHELL) ./config.status $(subdir)/$@ $(am__depfiles_maybe);; \ esac; $(top_builddir)/config.status: $(top_srcdir)/configure $(CONFIG_STATUS_DEPENDENCIES) cd $(top_builddir) && $(MAKE) $(AM_MAKEFLAGS) am--refresh $(top_srcdir)/configure: $(am__configure_deps) cd $(top_builddir) && $(MAKE) $(AM_MAKEFLAGS) am--refresh $(ACLOCAL_M4): $(am__aclocal_m4_deps) cd $(top_builddir) && $(MAKE) $(AM_MAKEFLAGS) am--refresh $(am__aclocal_m4_deps): gst: $(top_builddir)/config.status $(srcdir)/gst.in cd $(top_builddir) && $(SHELL) ./config.status $(subdir)/$@ atlocal: $(top_builddir)/config.status $(srcdir)/atlocal.in cd $(top_builddir) && $(SHELL) ./config.status $(subdir)/$@ mostlyclean-libtool: -rm -f *.lo clean-libtool: -rm -rf .libs _libs tags: TAGS TAGS: ctags: CTAGS CTAGS: distdir: $(DISTFILES) @srcdirstrip=`echo "$(srcdir)" | sed 's/[].[^$$\\*]/\\\\&/g'`; \ topsrcdirstrip=`echo "$(top_srcdir)" | sed 's/[].[^$$\\*]/\\\\&/g'`; \ list='$(DISTFILES)'; \ dist_files=`for file in $$list; do echo $$file; done | \ sed -e "s|^$$srcdirstrip/||;t" \ -e "s|^$$topsrcdirstrip/|$(top_builddir)/|;t"`; \ case $$dist_files in \ */*) $(MKDIR_P) `echo "$$dist_files" | \ sed '/\//!d;s|^|$(distdir)/|;s,/[^/]*$$,,' | \ sort -u` ;; \ esac; \ for file in $$dist_files; do \ if test -f $$file || test -d $$file; then d=.; else d=$(srcdir); fi; \ if test -d $$d/$$file; then \ dir=`echo "/$$file" | sed -e 's,/[^/]*$$,,'`; \ if test -d "$(distdir)/$$file"; then \ find "$(distdir)/$$file" -type d ! -perm -700 -exec chmod u+rwx {} \;; \ fi; \ if test -d $(srcdir)/$$file && test $$d != $(srcdir); then \ cp -fpR $(srcdir)/$$file "$(distdir)$$dir" || exit 1; \ find "$(distdir)/$$file" -type d ! -perm -700 -exec chmod u+rwx {} \;; \ fi; \ cp -fpR $$d/$$file "$(distdir)$$dir" || exit 1; \ else \ test -f "$(distdir)/$$file" \ || cp -p $$d/$$file "$(distdir)/$$file" \ || exit 1; \ fi; \ done check-am: all-am $(MAKE) $(AM_MAKEFLAGS) $(nodist_check_DATA) $(MAKE) $(AM_MAKEFLAGS) check-local check: check-am all-am: Makefile $(DATA) installdirs: install: install-am install-exec: install-exec-am install-data: install-data-am uninstall: uninstall-am install-am: all-am @$(MAKE) $(AM_MAKEFLAGS) install-exec-am install-data-am installcheck: installcheck-am install-strip: if test -z '$(STRIP)'; then \ $(MAKE) $(AM_MAKEFLAGS) INSTALL_PROGRAM="$(INSTALL_STRIP_PROGRAM)" \ install_sh_PROGRAM="$(INSTALL_STRIP_PROGRAM)" INSTALL_STRIP_FLAG=-s \ install; \ else \ $(MAKE) $(AM_MAKEFLAGS) INSTALL_PROGRAM="$(INSTALL_STRIP_PROGRAM)" \ install_sh_PROGRAM="$(INSTALL_STRIP_PROGRAM)" INSTALL_STRIP_FLAG=-s \ "INSTALL_PROGRAM_ENV=STRIPPROG='$(STRIP)'" install; \ fi mostlyclean-generic: clean-generic: -test -z "$(CLEANFILES)" || rm -f $(CLEANFILES) distclean-generic: -test -z "$(CONFIG_CLEAN_FILES)" || rm -f $(CONFIG_CLEAN_FILES) -test . = "$(srcdir)" || test -z "$(CONFIG_CLEAN_VPATH_FILES)" || rm -f $(CONFIG_CLEAN_VPATH_FILES) -test -z "$(DISTCLEANFILES)" || rm -f $(DISTCLEANFILES) maintainer-clean-generic: @echo "This command is intended for maintainers to use" @echo "it deletes files that may require special tools to rebuild." clean: clean-am clean-am: clean-generic clean-libtool clean-local mostlyclean-am distclean: distclean-am -rm -f Makefile distclean-am: clean-am distclean-generic dvi: dvi-am dvi-am: html: html-am html-am: info: info-am info-am: install-data-am: install-dvi: install-dvi-am install-dvi-am: install-exec-am: install-html: install-html-am install-html-am: install-info: install-info-am install-info-am: install-man: install-pdf: install-pdf-am install-pdf-am: install-ps: install-ps-am install-ps-am: installcheck-am: installcheck-local maintainer-clean: maintainer-clean-am -rm -f Makefile maintainer-clean-am: distclean-am maintainer-clean-generic mostlyclean: mostlyclean-am mostlyclean-am: mostlyclean-generic mostlyclean-libtool pdf: pdf-am pdf-am: ps: ps-am ps-am: uninstall-am: .MAKE: check-am install-am install-strip .PHONY: all all-am check check-am check-local clean clean-generic \ clean-libtool clean-local distclean distclean-generic \ distclean-libtool distdir dvi dvi-am html html-am info info-am \ install install-am install-data install-data-am install-dvi \ install-dvi-am install-exec install-exec-am install-html \ install-html-am install-info install-info-am install-man \ install-pdf install-pdf-am install-ps install-ps-am \ install-strip installcheck installcheck-am installcheck-local \ installdirs maintainer-clean maintainer-clean-generic \ mostlyclean mostlyclean-generic mostlyclean-libtool pdf pdf-am \ ps ps-am uninstall uninstall-am .PHONY: regress regress: cd $(srcdir) || exit 1; \ for test in $(TESTS); do \ result=`echo $$test | $(SED) 's/st$$/ok/'`; \ @abs_top_builddir@/gst --image=@abs_top_builddir@/gst.im -r $$test 2>&1 | tee $$result; \ done gst.im: ../kernel/stamp-classes AnsiLoad.st Ansi.st AnsiDB.st echo "PackageLoader fileInPackage: #SUnit. ObjectMemory snapshot: 'gst.im'" | ./gst --image=../gst.im - cd $(srcdir) && @abs_builddir@/gst -S --image=@abs_top_builddir@/tests/gst.im AnsiLoad.st $(srcdir)/package.m4: $(top_srcdir)/configure.ac { \ echo '# Signature of the current package.'; \ echo 'm4_define([AT_PACKAGE_NAME], [@PACKAGE_NAME@])'; \ echo 'm4_define([AT_PACKAGE_TARNAME], [@PACKAGE_TARNAME@])'; \ echo 'm4_define([AT_PACKAGE_VERSION], [@PACKAGE_VERSION@])'; \ echo 'm4_define([AT_PACKAGE_STRING], [@PACKAGE_STRING@])'; \ echo 'm4_define([AT_PACKAGE_BUGREPORT], [@PACKAGE_BUGREPORT@])'; \ } >'$(srcdir)/package.m4' check-local: gst atlocal atconfig $(TESTSUITE) $(SHELL) '$(TESTSUITE)' $(TESTSUITEFLAGS) clean-local: -$(SHELL) '$(TESTSUITE)' --clean installcheck-local: atlocal atconfig $(TESTSUITE) if test -z "$(DESTDIR)"; then \ $(SHELL) '$(TESTSUITE)' $(TESTSUITEFLAGS) AUTOTEST_PATH=$(bindir); \ fi $(TESTSUITE): $(srcdir)/testsuite.at $(srcdir)/package.m4 $(srcdir)/local.at $(AUTOTEST) -I '$(srcdir)' -o $@.tmp $@.at mv $@.tmp $@ # Tell versions [3.59,3.63) of GNU make to not export all variables. # Otherwise a system limit (for SysV at least) may be exceeded. .NOEXPORT: smalltalk-3.2.5/tests/shape.st0000644000175000017500000000266612123404352013246 00000000000000"====================================================================== | | Test Shape class | | ======================================================================" "====================================================================== | | Copyright (C) 2011 Free Software Foundation. | Written by Mathieu Suen | | This file is part of GNU Smalltalk. | | GNU Smalltalk is free software; you can redistribute it and/or modify it | under the terms of the GNU General Public License as published by the Free | Software Foundation; either version 2, or (at your option) any later version. | | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS | FOR A PARTICULAR PURPOSE. See the GNU General Public License for more | details. | | You should have received a copy of the GNU General Public License along with | GNU Smalltalk; see the file COPYING. If not, write to the Free Software | Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. | ======================================================================" Object subclass: UintShape [ UintShape class >> new [ ^(self new:1) at: 1 put: 16r80000000 ] ] Object subclass: IntShape [ IntShape class >> new [ ^(self new:1) at: 1 put: 16r80000000 ] ] Eval [ UintShape new printString. ] Eval [ IntShape new printString ] smalltalk-3.2.5/tests/fileext.ok0000644000175000017500000000042412123404352013557 00000000000000 Execution begins... true true true true true true true true true true true true true true true true true true true true true true true true true true true true true true true true true true true true true true true true true true true true returned value is Object new "<0>" smalltalk-3.2.5/tests/geometry.st0000644000175000017500000001177212123404352013777 00000000000000"====================================================================== | | Testing script for basic Point anr Rectangle class primitives | Tests the basic primitives to verify that they work | The test isn't exhaustive so some errors that do not show up | | ======================================================================" "====================================================================== | | Copyright (C) 1995, 1999, 2005, 2007, 2008 Free Software Foundation. | Written by Doug McCallum. | | This file is part of GNU Smalltalk. | | GNU Smalltalk is free software; you can redistribute it and/or modify it | under the terms of the GNU General Public License as published by the Free | Software Foundation; either version 2, or (at your option) any later version. | | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS | FOR A PARTICULAR PURPOSE. See the GNU General Public License for more | details. | | You should have received a copy of the GNU General Public License along with | GNU Smalltalk; see the file COPYING. If not, write to the Free Software | Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. | ======================================================================" Rectangle extend [ myAreasOutside: a [ | ans | ans := self areasOutside: a. ans := ans asSortedCollection: [ :x :y | x printString < y printString ]. ^ans asArray ] ] "Creation methods and printing" Eval [ p1 := Point x: 123 y: 456. p2 := 123@456. 'p1 = ' print. p1 printNl. 'p2 = ' print. p2 printNl. ] "accessing" Eval [ p := 123@456. '(p x) = ' print. (p x) printNl. '(p y) = ' print. (p y) printNl. p x: 321. 'p = ' print. p printNl. p y: 654. 'p = ' print. p printNl. ] "comparing" Eval [ A := 45@230. B := 175@270. C := 175@200. 'A < B = ' print. (A < B) printNl. 'A < C = ' print. (A < C) printNl. 'A > C = ' print. (A > C) printNl. 'B > A = ' print. (B > A) printNl. 'A max: B = ' print. (A max: B) printNl. 'A min: B = ' print. (A min: B) printNl. ] "arithmetic" Eval [ A := 45@230. B := 175@300. C := 50@50. D := 160@240. 'A + B = ' print. (A + B) printNl. 'A + 175 = ' print. (A + 175) printNl. 'A - B = ' print. (A - B) printNl. 'D / 50 = ' print. (D / 50) printNl. 'D // 50 = ' print. (D // 50) printNl. 'D // C = ' print. (D // C) printNl. '(A - B) abs = ' print. ((A - B) abs) printNl. '120.5@220.7 rounded = ' print. ((120.5@220.7) rounded) printNl. 'D truncateTo: 50 = ' print. (D truncateTo: 50) printNl. ] "point functions" Eval [ A := 45@230. B := 141@270. C := 160@240. D := 50@50. E := 3@4. 'A dist: B = ' print. (A dist: B) printNl. 'C dotProduct: D = ' print. (C dotProduct: D) printNl. 'C grid: D = ' print. (C grid: D) printNl. 'E normal * 5 = ' print. (E normal * 5) rounded printNl. 'C truncatedGrid: D = ' print. (C truncatedGrid: D) printNl. '175@300 transpose = ' print. ((175@300) transpose) printNl. ] "RECTANGLES--------------------------" "creation and printing" Eval [ '5 lines should be the same: A = 100@100 corner: 200@200' printNl. A := Rectangle left: 100 right: 200 top: 100 bottom: 200. 'A = ' print. A printNl. A := Rectangle origin: 100@100 corner: 200@200. 'A = ' print. A printNl. A := Rectangle origin: 100@100 extent: 100@100. 'A = ' print. A printNl. A := (100@100) corner: 200@200. 'A = ' print. A printNl. A := (100@100) extent: 100@100. 'A = ' print. A printNl ] "accessing" Eval [ A := Rectangle origin: 100@100 extent: 150@150. 'A = ' print. A printNl. 'topLeft = ' print. (A topLeft) printNl. 'top = ' print. (A top) printNl. 'rightCenter = ' print. (A rightCenter) printNl. 'bottom = ' print. (A bottom) printNl. 'center = ' print. (A center) printNl. 'extent = ' print. (A extent) printNl. 'area = ' print. (A area) printNl ] "rectangle functions" Eval [ A := 50@50 corner: 200@200. B := 120@120 corner: 260@240. C := 100@300 corner: 300@400. D := 20@20 corner: 400@400. (A amountToTranslateWithin: C) printNl. (A intersect: B) printNl. (D intersect: C) printNl. (A myAreasOutside: B) printNl. (D myAreasOutside: C) printNl. (D myAreasOutside: B) printNl. (C expandBy: 10) printNl. (C insetBy: 10@20) printNl. (B merge: C) printNl ] "testing" Eval [ A := 50@50 corner: 200@200. B := 120@120 corner: 260@240. C := 100@300 corner: 300@400. (A contains: B) printNl. (C containsPoint: 200@320) printNl. (A intersects: B) printNl ] "truncation and round off and transforming" Eval [ A := 50@50 corner: 200@200. B := 120@120 corner: 260@240. C := 100@300 corner: 300@400. (A moveBy: 50@50) printNl. (A moveTo: 200@300) printNl. (A scaleBy: 2) printNl. (A translateBy: -100) printNl ] smalltalk-3.2.5/tests/ackermann.ok0000644000175000017500000000010512123404352014052 00000000000000 Execution begins... Ack(3,4): 125 returned value is 'Ack(3,4): 125' smalltalk-3.2.5/tests/prodcons.ok0000644000175000017500000000010112123404352013736 00000000000000 Execution begins... 10000 10000 returned value is '10000 10000' smalltalk-3.2.5/tests/gst.in0000644000175000017500000000040712123404352012712 00000000000000#! /bin/sh abs_top_builddir=@abs_top_builddir@ : ${LIBTOOL=$abs_top_builddir/libtool} export LTDL_LIBRARY_PATH=$abs_top_builddir${LTDL_LIBRARY_PATH:+:$LTDL_LIBRARY_PATH} exec $LIBTOOL --mode=execute @PACKAGE_DLOPEN_FLAGS@ $abs_top_builddir/gst@EXEEXT@ ${1+"$@"} smalltalk-3.2.5/tests/processes.ok0000644000175000017500000000431712123404352014132 00000000000000 Execution begins... Process('test 1' at userSchedulingPriority, suspended) 'inside p' Process('test 1' at userSchedulingPriority, terminated) returned value is Process new "<0>" Execution begins... Process('test 2' at userSchedulingPriority, suspended) 'inside p' Process('test 2' at userSchedulingPriority, suspended) 'suspension finished' Process('test 2' at userSchedulingPriority, terminated) returned value is Process new "<0>" Execution begins... Process('test 3' at userSchedulingPriority, suspended) 'inside p' Process('test 3' at userSchedulingPriority, ready to run) 'yielded back to p' Process('test 3' at userSchedulingPriority, terminated) returned value is Process new "<0>" Execution begins... Process('test 4' at userSchedulingPriority, suspended) 'inside p' Process('test 4' at userSchedulingPriority, waiting on a semaphore) 'wait finished' Process('test 4' at userSchedulingPriority, terminated) returned value is Process new "<0>" Execution begins... Process('background' at userBackgroundPriority, active) Process('background' at userBackgroundPriority, ready to run) Process('background' at userBackgroundPriority, terminated) returned value is Process new "<0>" Execution begins... Process('interrupted' at userInterruptPriority, active) Process('interrupted' at userInterruptPriority, suspended) Process('interrupted' at userInterruptPriority, terminated) returned value is Process new "<0>" Execution begins... returned value is true Execution begins... returned value is true Execution begins... returned value is true Execution begins... returned value is true Execution begins... returned value is true Execution begins... returned value is true Execution begins... returned value is nil Execution begins... nil 1 2 nil 3 2 2 returned value is 2 Execution begins... nothing should follow... returned value is nil Execution begins... returned value is Process new "<0>" Execution begins... returned value is Process new "<0>" Execution begins... returned value is Process new "<0>" Execution begins... returned value is Process new "<0>" Execution begins... returned value is Process new "<0>" Execution begins... returned value is Process new "<0>" Execution begins... returned value is Process new "<0>" smalltalk-3.2.5/tests/heapsort.st0000644000175000017500000000430312123404352013761 00000000000000"====================================================================== | | Benchmark for array accessing and flow-control bytecodes | | ======================================================================" "====================================================================== | | Copyright (C) 2003, 2007, 2008 Free Software Foundation. | Written by Paolo Bonzini | | This file is part of GNU Smalltalk. | | GNU Smalltalk is free software; you can redistribute it and/or modify it | under the terms of the GNU General Public License as published by the Free | Software Foundation; either version 2, or (at your option) any later version. | | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS | FOR A PARTICULAR PURPOSE. See the GNU General Public License for more | details. | | You should have received a copy of the GNU General Public License along with | GNU Smalltalk; see the file COPYING. If not, write to the Free Software | Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. | ======================================================================" Number extend [ Last := 42. nextRandom [ Last := Last * 3877 + 29573 rem: 139968. ^self * Last asFloatD / 139968d ] ] Array extend [ heapSort [ | j i rra l ir | ir := self size. l := self size // 2 + 1. [ l > 1 ifTrue: [ rra := self at: (l := l - 1) ] ifFalse: [ rra := self at: ir. self at: ir put: (self at: 1). ir := ir - 1. ir = 1 ifTrue: [ self at: 1 put: rra. ^self ]. ]. i := l. j := l * 2. [ j <= ir ] whileTrue: [ (j < ir and: [ (self at: j) < (self at: j+1) ]) ifTrue: [ j := j + 1 ]. rra < (self at: j) ifTrue: [ self at: i put: (self at: j). i := j. j := j + i ] ifFalse: [ j := ir + 1 ]]. self at: i put: rra ] repeat ] ] Eval [ n := Smalltalk arguments isEmpty ifTrue: [ 1000 ] ifFalse: [ 1 max: Smalltalk arguments first asInteger ]. array := Array new: n. 1 to: n do: [ :i | array at: i put: 1d nextRandom ]. array heapSort. ((array last + 0.5d-10) printString copyFrom: 1 to: 12) displayNl ] smalltalk-3.2.5/tests/exceptions.ok0000644000175000017500000000503512130343734014307 00000000000000 Execution begins... testResume...passed returned value is TextCollector new "<0>" Execution begins... testReturn...passed if nothing follows on this line returned value is TextCollector new "<0>" Execution begins... testPass...passing...passed if nothing follows on this line returned value is TextCollector new "<0>" Execution begins... testPass (2)...passing...ok returned value is TextCollector new "<0>" Execution begins... testEnsure... error: Ignore this error passed returned value is nil Execution begins... returned value is 0 Execution begins... error: Ignore this error returned value is nil Execution begins... testIfCurtailed...passed returned value is TextCollector new "<0>" Execution begins... returned value is true Execution begins... returned value is true Execution begins... error: did not understand #siz returned value is nil Execution begins... returned value is true Execution begins... returned value is true Execution begins... error: An exceptional condition has occurred, and has prevented normal continuation of processing. returned value is nil Execution begins... returned value is true Execution begins... returned value is true Execution begins... returned value is 1 Execution begins... #block #outer returned value is #block Execution begins... #block #outer returned value is #outer Execution begins... #block #inner #outer returned value is #block Execution begins... #block #inner #outer returned value is #outer Execution begins... #block #inner #outer returned value is #inner Execution begins... #block #inner #outer returned value is #outer Execution begins... #block returned value is #block Execution begins... #block returned value is #block Execution begins... #block returned value is #block Execution begins... #block returned value is #block Execution begins... #block returned value is #block Execution begins... #block returned value is #block Execution begins... #block #outer returned value is #block Execution begins... #block #outer returned value is #outer Execution begins... #block #inner #outer returned value is #block Execution begins... #block #inner #outer returned value is #outer Execution begins... #block #inner #outer returned value is #inner Execution begins... #block #inner #outer returned value is #outer Execution begins... error: did not understand #goodness: returned value is nil Execution begins... error: return from a dead method context returned value is nil Execution begins... error: test returned value is nil Execution begins... returned value is nil smalltalk-3.2.5/tests/matrix.st0000644000175000017500000000473112123404352013445 00000000000000"====================================================================== | | Benchmark for matrices | | ======================================================================" "====================================================================== | | Copyright (C) 2003, 2007, 2008 Free Software Foundation. | Written by Paolo Bonzini | | This file is part of GNU Smalltalk. | | GNU Smalltalk is free software; you can redistribute it and/or modify it | under the terms of the GNU General Public License as published by the Free | Software Foundation; either version 2, or (at your option) any later version. | | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS | FOR A PARTICULAR PURPOSE. See the GNU General Public License for more | details. | | You should have received a copy of the GNU General Public License along with | GNU Smalltalk; see the file COPYING. If not, write to the Free Software | Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. | ======================================================================" Array extend [ Array class >> newMatrix: rows columns: cols [ | count mx row | count := 1. mx := self new: rows. 1 to: rows do: [ :i | row := mx at: i put: (Array new: cols). 1 to: cols do: [ :j | row at: j put: count. count := count + 1 ]. ]. ^mx ] atXY: coord [ ^(self at: coord x) at: coord y ] mmult: m2 [ | rows cols terms val mx row myRow | rows := self size. terms := m2 size. cols := m2 first size. mx := Array new: rows. 1 to: rows do: [ :i | row := mx at: i put: (Array new: cols). myRow := self at: i. 1 to: cols do: [ :j | val := 0. 1 to: terms do: [ :k | val := val + ((myRow at: k) * ((m2 at: k) at: j) bitAnd: 16r3FFF_FFFF) ]. row at: j put: val. ]. ]. ^mx ] ] Eval [ | m1 m2 mm size n | n := Smalltalk arguments isEmpty ifTrue: [ 1 ] ifFalse: [ 1 max: Smalltalk arguments first asInteger ]. size := 30. m1 := Array newMatrix: size columns: size. m2 := Array newMatrix: size columns: size. n timesRepeat: [ mm := m1 mmult: m2 ]. ('%1 %2 %3 %4' % { mm atXY: 1@1. mm atXY: 3@4. mm atXY: 4@3. mm atXY: 5@5 }) displayNl ] smalltalk-3.2.5/tests/sets.ok0000644000175000017500000000021612123404352013074 00000000000000 Execution begins... 'passed' 'passed' 'passed' 'passed' 'passed' 'passed' 'passed' 'passed' 'passed' 'passed' 'passed' returned value is nil smalltalk-3.2.5/tests/hash.st0000644000175000017500000000277612123404352013073 00000000000000"====================================================================== | | Benchmark for dictionaries | | ======================================================================" "====================================================================== | | Copyright (C) 2003, 2007, 2008 Free Software Foundation. | Written by Paolo Bonzini | | This file is part of GNU Smalltalk. | | GNU Smalltalk is free software; you can redistribute it and/or modify it | under the terms of the GNU General Public License as published by the Free | Software Foundation; either version 2, or (at your option) any later version. | | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS | FOR A PARTICULAR PURPOSE. See the GNU General Public License for more | details. | | You should have received a copy of the GNU General Public License along with | GNU Smalltalk; see the file COPYING. If not, write to the Free Software | Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. | ======================================================================" Eval [ n := Smalltalk arguments isEmpty ifTrue: [ 20000 ] ifFalse: [ 1 max: Smalltalk arguments first asInteger ]. hash := LookupTable new: n * 2. 1 to: n do: [ :each | hash at: (each printString: 16) put: 1. ]. c := 0. n to: 1 by: -1 do: [ :each | (hash includesKey: each printString) ifTrue: [ c := c + 1]. ]. c printNl ] smalltalk-3.2.5/tests/chars.st0000644000175000017500000000504012123404352013233 00000000000000"====================================================================== | | Test the character (of the) system | | ======================================================================" "====================================================================== | | Copyright (C) 1988, 1989, 1999, 2006, 2007, 2008 Free Software Foundation. | Written by Steve Byrne | | This file is part of GNU Smalltalk. | | GNU Smalltalk is free software; you can redistribute it and/or modify it | under the terms of the GNU General Public License as published by the Free | Software Foundation; either version 2, or (at your option) any later version. | | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS | FOR A PARTICULAR PURPOSE. See the GNU General Public License for more | details. | | You should have received a copy of the GNU General Public License along with | GNU Smalltalk; see the file COPYING. If not, write to the Free Software | Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. | ======================================================================" Eval [ $A ] Eval [ $b ] Eval [ $$ ] Eval [ $! ] Eval [ $ ] Eval [ a := 0 to: 255. b := a collect: [ :each | each asCharacter ]. c := b collect: [ :each | each asInteger ]. c = a asArray ] Eval [ allChars := (0 to: 127) asByteArray asString. ^(0 to: 127) allSatisfy: [ :index | (allChars at: index + 1) == index asCharacter ] ] Eval [ allChars := (0 to: 255) asByteArray asString. #(#isVowel #isLetter #isUppercase #isLowercase #isAlphaNumeric #isDigit #isSeparator) do: [ :symbol | symbol printNl. which := allChars collect: [ :each | (each perform: symbol) ifTrue: [ $x ] ifFalse: [ $_ ] ]. Transcript showCr: (which copyFrom: 1 to: 64). Transcript showCr: (which copyFrom: 65 to: 128). Transcript showCr: (which copyFrom: 129 to: 192). Transcript showCr: (which copyFrom: 193 to: 256). Transcript nl. ] ] Eval [ printable := (33 to: 126) asByteArray asString. #(#asUppercase #asLowercase) do: [ :symbol | symbol printNl. which := printable collect: [ :each | (each perform: symbol) ]. Transcript showCr: (which copyFrom: 1 to: 47). Transcript showCr: (which copyFrom: 48 to: 94). Transcript nl. ] ] smalltalk-3.2.5/tests/fileext.st0000644000175000017500000000514112123404352013575 00000000000000"====================================================================== | | Regression tests for File | | ======================================================================" "====================================================================== | | Copyright (C) 2003, 2007 Free Software Foundation. | Written by Paolo Bonzini, based on test vectors by Nicolas Pelletier. | This file is part of GNU Smalltalk. | | GNU Smalltalk is free software; you can redistribute it and/or modify it | under the terms of the GNU General Public License as published by the Free | Software Foundation; either version 2, or (at your option) any later version. | | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS | FOR A PARTICULAR PURPOSE. See the GNU General Public License for more | details. | | You should have received a copy of the GNU General Public License along with | GNU Smalltalk; see the file COPYING. If not, write to the Free Software | Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. | ======================================================================" Object extend [ testCaseData [ | extensions | extensions := OrderedCollection new. extensions add: '' -> ''; add: '.' -> ''; add: '/' -> ''; add: 'text' -> ''; add: 'text.' -> '.'; add: '.text' -> ''; add: 'text/' -> ''; add: '/text' -> ''; add: '/.' -> ''; add: './' -> ''; add: 'file.ext' -> '.ext'; add: 'file.ext.' -> '.'; add: '.file.ext' -> '.ext'; add: 'file.ext/' -> ''; add: '/file.ext' -> '.ext'; add: '/.file.ext' -> '.ext'; add: './file.ext' -> '.ext'; add: 'dir/file' -> ''; add: 'dir/file.' -> '.'; add: 'dir/.file' -> ''; add: 'dir/file.ext' -> '.ext'; add: 'dir/file.ext.' -> '.'. ^extensions ] testExtensionFor [ self testCaseData do: [:each | [(File extensionFor: each key) = each value] value printNl ] ] testStripExtensionFrom [ "(File stripExtensionFrom: aString), (File extensionFor: aString) = aString" self testCaseData do: [:each | [(File stripExtensionFrom: each key), (File extensionFor: each key) = each key] value printNl ] ] ] Eval [ CSymbols.PathSeparator := $/. Object new testExtensionFor; testStripExtensionFrom ] smalltalk-3.2.5/tests/ary3.st0000644000175000017500000000274412123404352013021 00000000000000"====================================================================== | | Benchmark for array accessing | | ======================================================================" "====================================================================== | | Copyright (C) 2003, 2007, 2008 Free Software Foundation. | Written by Paolo Bonzini | | This file is part of GNU Smalltalk. | | GNU Smalltalk is free software; you can redistribute it and/or modify it | under the terms of the GNU General Public License as published by the Free | Software Foundation; either version 2, or (at your option) any later version. | | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS | FOR A PARTICULAR PURPOSE. See the GNU General Public License for more | details. | | You should have received a copy of the GNU General Public License along with | GNU Smalltalk; see the file COPYING. If not, write to the Free Software | Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. | ======================================================================" Eval [ n := Smalltalk arguments isEmpty ifTrue: [ 1000 ] ifFalse: [ 1 max: Smalltalk arguments first asInteger ]. x := (1 to: n) asArray. y := Array new: n withAll: 0. 1000 timesRepeat: [ n to: 1 by: -1 do: [ :i | y at: i put: (y at: i) + (x at: i) ] ]. ('%1 %2' % { y first. y last }) displayNl ] smalltalk-3.2.5/tests/lists1.ok0000644000175000017500000000016012123404352013333 00000000000000 Execution begins... 100000 99999 false true 1 2 3 4 5 6 7 8 9 10 499500 149999 100000 returned value is 100000 smalltalk-3.2.5/tests/Ansi.st0000644000175000017500000156625312123404352013050 00000000000000Object subclass: #MsgParmSpec instanceVariableNames: 'parmName parmProtocols parmAliasingAttribute ' classVariableNames: '' poolDictionaries: '' category: ''! Object subclass: #MsgReturnSpec instanceVariableNames: 'returnValueProtocols returnValueAliasingAttribute ' classVariableNames: '' poolDictionaries: '' category: ''! TestCase subclass: #TestCaseProtocol instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: ''! TestCaseProtocol subclass: #TestCaseHelper instanceVariableNames: 'testCase ' classVariableNames: ' ' poolDictionaries: '' category: ''! TestCaseHelper class instanceVariableNames: 'testSelectors '! TestCaseHelper subclass: #CollectionStreamHelper instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: ''! TestCaseHelper subclass: #GettableStreamHelper instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: ''! TestCaseHelper subclass: #WriteStreamHelper instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: ''! TestCaseHelper subclass: #SequencedReadableCollectionHelper instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: ''! TestCaseHelper subclass: #SequencedStreamHelper instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: ''! TestCaseHelper subclass: #CollectionHelper instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: ''! TestCaseHelper subclass: #SequencedCollectionHelper instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: ''! TestCaseHelper subclass: #ReadableStringHelper instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: ''! TestCaseHelper subclass: #SequencedContractibleCollectionHelper instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: ''! TestCaseHelper subclass: #PuttableStreamHelper instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: ''! TestCaseHelper subclass: #AbstractDictionaryHelper instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: ''! TestCaseProtocol subclass: #MainTestCase instanceVariableNames: 'messages helpers ' classVariableNames: '' poolDictionaries: '' category: ''! MainTestCase subclass: #ExceptionSetANSITest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: ''! MainTestCase subclass: #IdentityDictionaryANSITest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: ''! MainTestCase subclass: #ExceptionClassANSITest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: ''! MainTestCase subclass: #SelectorANSITest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: ''! MainTestCase subclass: #ArrayFactoryANSITest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: ''! MainTestCase subclass: #ObjectClassANSITest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: ''! MainTestCase subclass: #NilANSITest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: ''! MainTestCase subclass: #FloatANSITest instanceVariableNames: 'smallInt2 largeNegInt2000000000 largePosInt2000000000 float2 fractionHalf sclDec2s3 numList ' classVariableNames: '' poolDictionaries: '' category: ''! MainTestCase subclass: #ReadWriteStreamFactoryANSITest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: ''! MainTestCase subclass: #ScaledDecimalANSITest instanceVariableNames: 'smallInt2 largeNegInt2000000000 largePosInt2000000000 float2 fractionHalf sclDec2s3 numList ' classVariableNames: '' poolDictionaries: '' category: ''! MainTestCase subclass: #NotificationANSITest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: ''! MainTestCase subclass: #CharacterANSITest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: ''! MainTestCase subclass: #ZeroDivideANSITest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: ''! MainTestCase subclass: #TranscriptANSITest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: ''! MainTestCase subclass: #MessageNotUnderstoodANSITest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: ''! MainTestCase subclass: #SequencedStreamTest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: ''! MainTestCase subclass: #BagFactoryANSITest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: ''! MainTestCase subclass: #ErrorClassANSITest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: ''! MainTestCase subclass: #WarningClassANSITest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: ''! MainTestCase subclass: #OrderedCollectionFactoryANSITest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: ''! MainTestCase subclass: #DurationANSITest instanceVariableNames: 'off0123 smallInt2 largeNegInt2000000000 largePosInt2000000000 float2 fractionHalf numList ' classVariableNames: '' poolDictionaries: '' category: ''! MainTestCase subclass: #ZeroDivideFactoryANSITest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: ''! MainTestCase subclass: #IntervalFactoryANSITest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: ''! MainTestCase subclass: #ReadStreamFactoryANSITest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: ''! MainTestCase subclass: #ByteArrayFactoryANSITest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: ''! MainTestCase subclass: #ExceptionANSITest instanceVariableNames: 'unchanged changed value ' classVariableNames: '' poolDictionaries: '' category: ''! MainTestCase subclass: #MonadicBlockANSITest instanceVariableNames: 'blk1args ' classVariableNames: '' poolDictionaries: '' category: ''! MainTestCase subclass: #DurationFactoryANSITest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: ''! MainTestCase subclass: #SortedCollectionFactoryANSITest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: ''! MainTestCase subclass: #DateAndTimeANSITest instanceVariableNames: 'd19970426t8 ' classVariableNames: '' poolDictionaries: '' category: ''! MainTestCase subclass: #ReadWriteStreamANSITest instanceVariableNames: 'readWriteStream ' classVariableNames: '' poolDictionaries: '' category: ''! MainTestCase subclass: #DateAndTimeFactoryANSITest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: ''! MainTestCase subclass: #FractionFactoryANSITest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: ''! MainTestCase subclass: #ErrorANSITest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: ''! MainTestCase subclass: #StringFactoryANSITest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: ''! MainTestCase subclass: #ReadFileStreamANSITest instanceVariableNames: 'readFileStream ' classVariableNames: '' poolDictionaries: '' category: ''! MainTestCase subclass: #FailedMessageANSITest instanceVariableNames: 'failedMsg ' classVariableNames: '' poolDictionaries: '' category: ''! TestCaseHelper subclass: #ObjectHelper instanceVariableNames: 'object ' classVariableNames: '' poolDictionaries: '' category: ''! MainTestCase subclass: #IntegerANSITest instanceVariableNames: 'smallInt2 largeNegInt2000000000 largePosInt2000000000 float2 fractionHalf sclDec2s3 numList ' classVariableNames: '' poolDictionaries: '' category: ''! MainTestCase subclass: #FileStreamFactoryANSITest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: ''! MainTestCase subclass: #WarningANSITest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: ''! MainTestCase subclass: #IdentityDictionaryFactoryANSITest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: ''! MainTestCase subclass: #FractionANSITest instanceVariableNames: 'smallInt2 largeNegInt2000000000 largePosInt2000000000 float2 fractionHalf sclDec2s3 numList ' classVariableNames: '' poolDictionaries: '' category: ''! MainTestCase subclass: #MessageNotUnderstoodSelectorANSITest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: ''! MainTestCase subclass: #NiladicBlockANSITest instanceVariableNames: 'blk0args canonicalObject ' classVariableNames: '' poolDictionaries: '' category: ''! MainTestCase subclass: #NotificationClassANSITest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: ''! MainTestCase subclass: #ObjectANSITest instanceVariableNames: 'object ' classVariableNames: '' poolDictionaries: '' category: ''! MainTestCase subclass: #SetFactoryANSITest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: ''! TestCaseHelper subclass: #ExtensibleCollectionHelper instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: ''! MainTestCase subclass: #DyadicValuableANSITest instanceVariableNames: 'blk2args ' classVariableNames: '' poolDictionaries: '' category: ''! MainTestCase subclass: #WriteStreamFactoryANSITest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: ''! SequencedStreamTest subclass: #WriteStreamANSITest instanceVariableNames: 'writeStream ' classVariableNames: '' poolDictionaries: '' category: ''! MainTestCase subclass: #WriteFileStreamANSITest instanceVariableNames: 'writeFileStream ' classVariableNames: '' poolDictionaries: '' category: ''! Object subclass: #ProtocolANYSpec instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: ''! ProtocolANYSpec subclass: #ProtocolSpec instanceVariableNames: 'name conformsTo description messageSpecifications ' classVariableNames: 'DefaultConvTable FixNum OperatorTable Protocols UnaryConvTable UndefinedConformsToNames ClassProtocols ' poolDictionaries: '' category: ''! MsgReturnSpec subclass: #MsgReturnRuleSpec instanceVariableNames: 'ruleSourceCode ruleBlock ' classVariableNames: '' poolDictionaries: '' category: ''! MainTestCase subclass: #FloatCharacterizationANSITest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: ''! MainTestCase subclass: #CharacterFactoryANSITest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: ''! SequencedStreamTest subclass: #ReadStreamANSITest instanceVariableNames: 'readStream ' classVariableNames: '' poolDictionaries: '' category: ''! Object subclass: #ProtocolMsgSpec instanceVariableNames: 'selector parameterSpecifications returnValueSpecifications specSections ' classVariableNames: '' poolDictionaries: '' category: ''! MainTestCase subclass: #DictionaryFactoryANSITest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: ''! MainTestCase subclass: #BooleanANSITest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: ''! MainTestCase subclass: #CollectionTest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: ''! CollectionTest subclass: #SequencedReadableCollectionTest instanceVariableNames: 'canonicalObjects' classVariableNames: '' poolDictionaries: '' category: ''! CollectionTest subclass: #IntervalANSITest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: ''! SequencedReadableCollectionTest subclass: #StringANSITest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: ''! CollectionTest subclass: #DictionaryANSITest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: ''! CollectionTest subclass: #SetANSITest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: ''! SequencedReadableCollectionTest subclass: #SymbolANSITest instanceVariableNames: 'smalltalkSymbol ' classVariableNames: '' poolDictionaries: '' category: ''! SequencedReadableCollectionTest subclass: #OrderedCollectionANSITest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: ''! CollectionTest subclass: #BagANSITest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: ''! SequencedReadableCollectionTest subclass: #ByteArrayANSITest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: ''! SequencedReadableCollectionTest subclass: #SortedCollectionANSITest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: ''! SequencedReadableCollectionTest subclass: #ArrayANSITest instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: ''! TestCaseHelper subclass: #ReadStreamHelper instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: ''! !ReadStreamHelper methodsFor: nil! testXupToX self canonicalObject reset. self value: [self canonicalObject upTo: $ ] should: [:r | r = 'this' & self canonicalObject next = $i] conformTo: self protocol selector: #upTo:. self value: [self canonicalObject upTo: $X] should: [:r | r = 's a string' & self canonicalObject atEnd] conformTo: self protocol selector: #upTo:. self value: [self canonicalObject upTo: $a] should: [:r | r isEmpty] conformTo: self protocol selector: #upTo:.! object: anObject! testXnextX self canonicalObject reset. self value: [self canonicalObject next: 3] should: [:r | r asArray = 'thi' asArray] conformTo: self protocol selector: #'next:'. self value: [self canonicalObject next: 0] should: [:r | r isEmpty] conformTo: self protocol selector: #'next:'. "Errors: amount < 0." self value: [self canonicalObject next: -1] shouldRaise: Error.! canonicalObject ^testCase canonicalObject! protocol ^#'ReadStream'! ! !ReadStreamHelper class methodsFor: nil! initialize "ReadStreamHelper initialize" super initialize! ! !CollectionTest methodsFor: nil! conformanceOfPutElementOnXatAllXputX: aString "Do Nothing, Has no conformance issue"! conformanceOfPutElementOnXatXputX: aString "Do Nothing, Has no conformance issue"! returnTypeHasLimitedElementTypes ^false! conformanceOfPutElementOnXatAllPutX: aString "Do Nothing, Has no conformance issue"! ! !CollectionTest class methodsFor: nil! helperClassesDo: aBlock super helperClassesDo: aBlock. aBlock value: CollectionHelper! ! !SequencedReadableCollectionTest methodsFor: nil! canonicalObjects | helper | canonicalObjects isNil ifFalse: [ ^canonicalObjects ]. helper := helpers detect: [ :each | each class == SequencedReadableCollectionHelper ]. canonicalObjects := helper canonicalObjects. ^canonicalObjects! !BooleanANSITest methodsFor: nil! testXandX " #and: " #'Fundamental'. self value: [ true and: [true] ] should: [:r | r] conformTo: #'boolean' selector: #'and:'. self value: [ true and: [nil isNil] ] should: [:r | r] conformTo: #'boolean' selector: #'and:'. self value: [ true and: [false] ] shouldnt: [:r | r] conformTo: #'boolean' selector: #'and:'. self value: [ true and: [nil notNil] ] shouldnt: [:r | r] conformTo: #'boolean' selector: #'and:'. self value: [ true and: [nil selector] ] shouldRaise: MessageNotUnderstood. self value: [ false and: [true] ] shouldnt: [:r | r] conformTo: #'boolean' selector: #'and:'. self value: [ false and: [nil isNil] ] shouldnt: [:r | r] conformTo: #'boolean' selector: #'and:'. self value: [ false and: [false] ] shouldnt: [:r | r] conformTo: #'boolean' selector: #'and:'. self value: [ false and: [nil notNil] ] shouldnt: [:r | r] conformTo: #'boolean' selector: #'and:'. "No error:" self value: [ false and: [nil selector] ] shouldnt: [:r | r] conformTo: #'boolean' selector: #'and:'.! testXnot " #not " #'Fundamental'. self value: [true not] should: [:r | r = false] conformTo: #'boolean' selector: #'not'. self value: [false not] should: [:r | r = true] conformTo: #'boolean' selector: #'not'.! testXxorX " #xor: " #'Fundamental'. self value: [true xor: true] shouldnt: [:r | r] conformTo: #'boolean' selector: #'xor:'. self value: [true xor: false] should: [:r | r] conformTo: #'boolean' selector: #'xor:'. self value: [false xor: true] should: [:r | r] conformTo: #'boolean' selector: #'xor:'. self value: [false xor: false] shouldnt: [:r | r] conformTo: #'boolean' selector: #'xor:'.! protocol ^#boolean! canonicalObject ^true! testXifFalseXifTrueX " #ifFalse:ifTrue: " #'Fundamental'. self value: [ false ifFalse: [0] ifTrue: [nil selector] ] should: [:r | r = 0] conformTo: #'boolean' selector: #'ifFalse:ifTrue:'. self value: [ true ifFalse: [nil selector] ifTrue: [1] ] should: [:r | r = 1] conformTo: #'boolean' selector: #'ifFalse:ifTrue:'.! testXandOp " #& " #'Fundamental'. self value: [true & true] should: [:r | r] conformTo: #'boolean' selector: #'&'. self value: [true & false] shouldnt: [:r | r] conformTo: #'boolean' selector: #'&'. self value: [false & true] shouldnt: [:r | r] conformTo: #'boolean' selector: #'&'. self value: [false & false] shouldnt: [:r | r] conformTo: #'boolean' selector: #'&'.! testXorX " #or: " #'Fundamental'. self value: [ true or: [true] ] should: [:r | r] conformTo: #'boolean' selector: #'or:'. self value: [ true or: [false] ] should: [:r | r] conformTo: #'boolean' selector: #'or:'. "No error:" self value: [ true or: [nil selector] ] should: [:r | r] conformTo: #'boolean' selector: #'or:'. self value: [ false or: [true] ] should: [:r | r] conformTo: #'boolean' selector: #'or:'. self value: [ false or: [nil isNil] ] should: [:r | r] conformTo: #'boolean' selector: #'or:'. self value: [ false or: [false] ] shouldnt: [:r | r] conformTo: #'boolean' selector: #'or:'. self value: [ false or: [nil notNil] ] shouldnt: [:r | r] conformTo: #'boolean' selector: #'or:'. self value: [ false or: [nil selector] ] shouldRaise: MessageNotUnderstood.! testXifTrueX " #ifTrue: " #'Fundamental'. self value: [ true ifTrue: [1] ] should: [:r | r = 1] conformTo: #'boolean' selector: #'ifTrue:'. self value: [ false ifTrue: [1] ] should: [:r | true "unspecified"] conformTo: #'boolean' selector: #'ifTrue:'.! testXifFalseX " #ifFalse: " #'Fundamental'. self value: [ false ifFalse: [0] ] should: [:r | r = 0] conformTo: #'boolean' selector: #'ifFalse:'. self value: [ true ifFalse: [0] ] should: [:r | true "unspecified"] conformTo: #'boolean' selector: #'ifFalse:'.! testXprintString " #printString " #'Fundamental'. self value: [true printString] should: [:r | r = 'true'] conformTo: #'boolean' selector: #'printString'. self value: [false printString] should: [:r | r = 'false'] conformTo: #'boolean' selector: #'printString'.! testXeqvX " #eqv: " #'Fundamental'. self value: [true eqv: true] should: [:r | r] conformTo: #'boolean' selector: #'eqv:'. self value: [true eqv: false] shouldnt: [:r | r] conformTo: #'boolean' selector: #'eqv:'. self value: [false eqv: true] shouldnt: [:r | r] conformTo: #'boolean' selector: #'eqv:'. self value: [false eqv: false] should: [:r | r] conformTo: #'boolean' selector: #'eqv:'.! testXorOp " #| " #'Fundamental'. self value: [true | true] should: [:r | r] conformTo: #'boolean' selector: #'|'. self value: [true | false] should: [:r | r] conformTo: #'boolean' selector: #'|'. self value: [false | true] should: [:r | r] conformTo: #'boolean' selector: #'|'. self value: [false | false] shouldnt: [:r | r] conformTo: #'boolean' selector: #'|'.! testXifTrueXifFalseX " #ifTrue:ifFalse: " #'Fundamental'. self value: [ true ifTrue: [ 1 ] ifFalse: [ nil selector ] ] should: [:r | r = 1] conformTo: #'boolean' selector: #'ifTrue:ifFalse:'. self value: [ false ifTrue: [ nil selector ] ifFalse: [ 0 ] ] should: [:r | r = 0] conformTo: #'boolean' selector: #'ifTrue:ifFalse:'.! ! !DictionaryFactoryANSITest methodsFor: nil! protocol ^#'Dictionary factory'! testXwithAllX " #withAll: " #'Collection'.! testXnewX " #new: " #'Collection'.! canonicalObject ^Dictionary! testXnew " #new " #'Collection'.! ! !ProtocolMsgSpec methodsFor: nil! hasReturnValue "Answer true if receiver has return value specifications, else false." ^ returnValueSpecifications notNil! isConformingReturn: returnObject "Answer true if the result, returnObject, of sending the receiver conforms to the specified return value, else false." | returnClass | #todo."??? is no return value an error or compliant ???" self hasReturnValue ifFalse: [^ true]. self isReturnValueSpecByRule ifTrue: [^ false]. returnClass := returnObject class. self specForEachReturnValueList do: [:returnSpec | (returnSpec isConformingReturnClass: returnClass) ifTrue: [^ true]]. ^ false! specForEachReturnValueList "Answer the specification for each message return value list of the receiver." returnValueSpecifications isNil ifTrue: [^ self class defaultReturnValueSpecificationCollection]. ^ returnValueSpecifications! specSections "Answer the specification sections of the receiver. Note: specSections must be a of keys and values. Keys are: #'Synopsis' #'DefinedIn' #'Definition' #'RefinedIn' #'Refinement' #'Errors'." specSections isNil ifTrue: [^ self protocolManager defaultSpecSectionsCollection]. ^ specSections! messageSelector "Answer the selector of the receiver." ^ selector! messageDefinition "Answer the definition of the receiver, or an empty string." #todo."??? should this be the proto is component of or Definition: sec proto ???" specSections isNil ifTrue: [^ String new]. ^ specSections at: #'Definition' ifAbsent: [String new]! messageSynopsis "Answer the synopsis of the receiver, or an empty string." #todo."??? should this be the proto is component of or Definition: sec proto ???" specSections isNil ifTrue: [^ String new]. ^ specSections at: #'Synopsis' ifAbsent: [String new]! hasParms "Answer true if receiver has parameter specifications, else false." ^ parameterSpecifications notNil! isConformingReturn: returnObject opRECEIVER: receiver conformTo: protocolName selector: msgSelector "Answer true if the result, returnObject, of sending the receiver conforms to the protocol in which it is used, or any protocol that conforms to that protocol, else false." #todo."??? Figure out how to do this test ???" ^ self isConformingReturn: returnObject! allReferredToProtocolNames "Answer a list of protocol names referred to by the receiver." | referredToNames protocolName | referredToNames := Set new. protocolName := self definedInProtocolName. protocolName notNil ifTrue: [referredToNames add: protocolName]. protocolName := self refinedInProtocolName. protocolName isNil ifFalse: [referredToNames add: protocolName]. self specForEachParmList do: [:msgSpecParm | referredToNames addAll: msgSpecParm parmProtocolNames]. self specForEachReturnValueList do: [:msgSpecReturn | (msgSpecReturn isKindOf: self protocolManager protocolMsgReturnValueRuleSpec) ifFalse: [referredToNames addAll: msgSpecReturn returnValueProtocolNames]]. ^ referredToNames! messagePattern "Answer the message pattern of the receiver." | aStream colonCnt parmNames | parmNames := (self specForEachParmList collect: [:msgParmSpec | msgParmSpec parmName]) asArray. (selector includes: $:) ifFalse: [parmNames size = 0 ifTrue: [^ selector asString]. parmNames size = 1 ifTrue: [^ selector asString , ' ' , (parmNames at: 1)]. self error: 'Mis-matched parms & selector.']. aStream := WriteStream on: (String new: 200). colonCnt := 0. selector do: [:char | char = $: ifTrue: [colonCnt := colonCnt + 1. aStream nextPutAll: ': '. aStream nextPutAll: (parmNames at: colonCnt). colonCnt = parmNames size ifFalse: [aStream space]] ifFalse: [aStream nextPut: char]]. ^ aStream contents! printOn: targetStream "Append to targetStream a text representation of the receiver as a developer would want to see it (inspector, etc)." #todo."??? fix ???" targetStream nextPutAll: self class name; nextPut: $(; nextPutAll: self messageSelector; nextPut: $(. self specForEachParmList do: [:parmSpec | targetStream nextPutAll: parmSpec parmName] separatedBy: [targetStream space]. targetStream nextPutAll: ') '. " self specForEachReturnValueList do: [ :returnSpec | targetStream nextPutAll: returnSpec parmName ] separatedBy: [targetStream space]. " targetStream nextPut: $)! definedInProtocolName "Answer the protocol name in which the receiver is defined, or nil." #todo."??? should this be the proto is component of or Definition: sec proto ???" specSections isNil ifTrue: [^ nil]. ^ specSections at: #'DefinedIn' ifAbsent: []! setSelector: selectorIn specSections: specSectionsIn specForEachParmList: parmSpecsIn specForEachReturnValueList: returnValueSpecsIn "Private - Note: Assumes all parms have been checked for validity." selector := selectorIn. specSections := specSectionsIn. parameterSpecifications := parmSpecsIn. returnValueSpecifications := returnValueSpecsIn! specForEachParmList "Answer the specification for each message parameter list of the receiver." parameterSpecifications isNil ifTrue: [^ self class defaultParameterSpecificationCollection]. ^ parameterSpecifications! isReturnValueSpecByRule "Answer true if the receiver return value protocol is detirmined by a rule, else false." returnValueSpecifications isNil ifTrue: [ ^false. ]. ^returnValueSpecifications any isKindOf: (self protocolManager protocolMsgReturnValueRuleSpec)! isConformingReturn: returnObject ruleReceiver: receiver operand: operand "Answer true if the result, returnObject, of sending the receiver conforms to the specified return value, else false." #todo."??? is no return value an error or compliant ???" self hasReturnValue ifFalse: [^ true]. self isReturnValueSpecByRule ifFalse: [^ false]. ^ self specForEachReturnValueList asArray first isConformingReturnClass: returnObject class ruleReceiver: receiver operand: operand! fileOutOnSIFFiler: programFiler protocol: protocolName "File out the receiver definition and its message definitions on ANSI SIF filer, programFiler." | parmString returnIsRuleSw returnOrRule tmpStream | #todo. "??? Add annotations ???" parmString := '#()'. self hasParms ifTrue: [tmpStream := WriteStream on: (String new: 200). tmpStream nextPutAll: '#( '. self specForEachParmList do: [:msgParmSpec | msgParmSpec storeSIFOn: tmpStream] separatedBy: [tmpStream space]. tmpStream nextPutAll: ' )'. parmString := tmpStream contents]. returnIsRuleSw := false. returnOrRule := '#()'. self hasReturnValue ifTrue: [self isReturnValueSpecByRule ifTrue: [returnIsRuleSw := true. returnOrRule := self specForEachReturnValueList asArray first returnValueRuleBlockSource] ifFalse: [tmpStream := WriteStream on: (String new: 200). tmpStream nextPutAll: '#( '. self specForEachReturnValueList do: [:msgReturnSpec | msgReturnSpec storeSIFOn: tmpStream] separatedBy: [tmpStream space]. tmpStream nextPutAll: ' )'. returnOrRule := tmpStream contents]]. programFiler fileOutProtocol: protocolName message: self messagePattern synopsis: self messageSynopsis definedIn: self definedInProtocolName definition: self messageDefinition refinedIn: self refinedInProtocolName refinement: self messageRefinement parameters: parmString returnIsRule: returnIsRuleSw returnValuesOrRule: returnOrRule errors: self messageErrors annotations: Dictionary new! hash "Answer the hash value for the receiver." #todo."I'm not sure this tests effectively for the same elements?????" ^ self messageSelector hash! refinedInProtocolName "Answer the protocol name in which the receiver is refined, or nil." #todo."??? should this be the proto is component of or Refinement: sec proto ???" specSections isNil ifTrue: [^ nil]. ^ specSections at: #'RefinedIn' ifAbsent: []! messageErrors "Answer the errors of the receiver, or an empty string." #todo."??? should this be the proto is component of or Definition: sec proto ???" specSections isNil ifTrue: [^ String new]. ^ specSections at: #'Errors' ifAbsent: [String new]! <= comperand "Answer whether the receiver's message selector is less than or equal to comperand's message selector. Note: This is to allow protocol message selectors to be sorted with the default sort block." (comperand isKindOf: self protocolManager protocolMsgSpec) ifFalse: [self error: 'Comperand not a ProtocolSpec.']. ^ self messageSelector <= comperand messageSelector! = comperand "Answer whether the receiver is considered equal (contains same elements) to comperand. They are equal if both are instances of the same class and have the same message selector." #todo."I'm not sure this tests effectively for the same elements?????" ^ (comperand isKindOf: self protocolManager protocolMsgSpec) and: [self messageSelector == comperand messageSelector]! messageRefinement "Answer the refinement of the receiver, or an empty string." #todo."??? should this be the proto is component of or Definition: sec proto ???" specSections isNil ifTrue: [^ String new]. ^ specSections at: #'Refinement' ifAbsent: [String new]! isConformingReturn: returnObject ruleReceiver: receiver "Answer true if the result, returnObject, of sending the receiver conforms to the specified return value, else false." #todo."??? is no return value an error or compliant ???" self hasReturnValue ifFalse: [^ true]. self isReturnValueSpecByRule ifFalse: [^ false]. ^ self specForEachReturnValueList asArray first isConformingReturnClass: returnObject class ruleReceiver: receiver! ! !ProtocolMsgSpec class methodsFor: nil! newSelector: selector specSections: specSections specsForEachParm: parmSpecs specsForEachReturnValue: retValSpecs "Answer a new protocol message specification with selector, selector, specSections, specSections, a list of specifications for each parameter, parmSpecs, and a list of specifications for each return value, retValSpecs. Note: specSections must be a of keys and values, parmSpecs must be a of s, retValSpecs, a of s." ^ self privateNewSelector: selector specSectionsOrNil: specSections specForEachParmOrListOrNil: parmSpecs specForEachReturnValueOrListOrNil: retValSpecs! privateMessagePatternParmListOrNil: parmSpecsIn selector: selectorIn "Private - Answer the message pattern of the receiver." | aStream colonCnt parmNames parmSpecsTmp | parmSpecsIn isNil ifTrue: [parmSpecsTmp := Set new] ifFalse: [parmSpecsTmp := parmSpecsIn]. parmNames := (parmSpecsTmp collect: [:msgParmSpec | msgParmSpec parmName]) asArray. (selectorIn includes: $:) ifFalse: [parmNames size = 0 ifTrue: [^ selectorIn asString]. parmNames size = 1 ifTrue: [^ selectorIn asString , ' ' , (parmNames at: 1)]. self error: 'Mis-matched parms & selectorIn.']. aStream := WriteStream on: (String new: 200). colonCnt := 0. selectorIn do: [:char | char = $: ifTrue: [colonCnt := colonCnt + 1. aStream nextPutAll: ': '. aStream nextPutAll: (parmNames at: colonCnt). colonCnt = parmNames size ifFalse: [aStream space]] ifFalse: [aStream nextPut: char]]. ^ aStream contents! privateValidReturnValueOrListOrNil: retValSpecsIn ifError: errorBlock "Private -" | retValSpecsTmp | retValSpecsIn isNil ifTrue: [^ nil]. (retValSpecsIn isKindOf: self protocolManager protocolMsgReturnValueSpec) ifTrue: [retValSpecsTmp := self defaultReturnValueSpecificationCollection. retValSpecsTmp add: retValSpecsIn. ^ retValSpecsTmp]. (retValSpecsIn isKindOf: Collection) ifFalse: [^ errorBlock value]. retValSpecsIn isEmpty ifTrue: [^ nil]. retValSpecsTmp := self defaultReturnValueSpecificationCollection. retValSpecsIn do: [:rvSpec | (rvSpec isKindOf: self protocolManager protocolMsgReturnValueSpec) ifFalse: [^ errorBlock value]. retValSpecsTmp add: rvSpec]. ^ retValSpecsTmp! privateValidParmOrListOrNil: parmSpecsIn selector: selectorIn ifError: errorBlock "Private -" | parmSpecsTmp colonCnt | (parmSpecsIn isKindOf: self protocolManager protocolMsgParmSpec) ifTrue: [self privateMessagePatternParmListOrNil: (Set with: parmSpecsIn) selector: selectorIn] ifFalse: [self privateMessagePatternParmListOrNil: parmSpecsIn selector: selectorIn]. parmSpecsIn isNil ifTrue: [^ nil]. (parmSpecsIn isKindOf: self protocolManager protocolMsgParmSpec) ifTrue: [parmSpecsTmp := self defaultParameterSpecificationCollection. parmSpecsTmp add: parmSpecsIn. ^ parmSpecsTmp]. (parmSpecsIn isKindOf: Collection) ifFalse: [^ errorBlock value]. parmSpecsIn isEmpty ifTrue: [^ nil]. colonCnt := (selectorIn select: [:char | char = $:]) size. colonCnt > 0 ifTrue: [colonCnt = parmSpecsIn size ifFalse: [self error: 'Protocol msg. spec. number of parms do not match selector.']] ifFalse: [parmSpecsIn size = 0 | (parmSpecsIn size = 1) ifFalse: [self error: 'Protocol msg. spec. number of parms do not match selector.']]. parmSpecsTmp := self defaultParameterSpecificationCollection. parmSpecsIn do: [:parmSpec | (parmSpec isKindOf: self protocolManager protocolMsgParmSpec) ifFalse: [^ errorBlock value]. parmSpecsTmp add: parmSpec]. ^ parmSpecsTmp! privateNewSelector: selectorIn specSectionsOrNil: specSectionsIn specForEachParmOrListOrNil: parmSpecsIn specForEachReturnValueOrListOrNil: retValSpecsIn "Private -" | newProtocolMsgSpec specSectionsTmp parmSpecsTmp retValSpecsTmp | (selectorIn isKindOf: Symbol) ifFalse: [self error: 'Protocol msg. spec. selector not a Symbol.']. specSectionsTmp := self privateValidSpecSectionsOrNil: specSectionsIn ifError: [^ self error: 'Protocol msg. spec. spec. sections not a Dictionary.']. parmSpecsTmp := self privateValidParmOrListOrNil: parmSpecsIn selector: selectorIn ifError: [^ self error: 'Protocol msg. spec. parm not a Collection of ProtocolMsgSpec or nil.']. retValSpecsTmp := self privateValidReturnValueOrListOrNil: retValSpecsIn ifError: [^ self error: 'Protocol ret. val. spec. not a Collection of MsgReturnSpec or nil.']. newProtocolMsgSpec := super basicNew. newProtocolMsgSpec setSelector: selectorIn specSections: specSectionsTmp specForEachParmList: parmSpecsTmp specForEachReturnValueList: retValSpecsTmp. ^ newProtocolMsgSpec! new "Raise an exception as this is an inappropriate message." ^ self shouldNotImplement! privateValidSpecSectionsOrNil: specSectionsIn ifError: errorBlock "Private -" specSectionsIn isNil ifTrue: [^ nil]. (specSectionsIn isKindOf: Dictionary) ifFalse: [^ errorBlock value]. specSectionsIn isEmpty ifTrue: [^ nil]. ^ specSectionsIn! defaultParameterSpecificationCollection "Private - Answer a , the default parameter specification collection object." ^ Set new! defaultReturnValueSpecificationCollection "Private - Answer a , the default return value specification collection object." ^ Set new! ! !ReadStreamANSITest methodsFor: nil! protocol ^#'ReadStream'! setUp super setUp. readStream := ReadStream on: 'this is a string'! canonicalObject ^readStream! ! !ReadStreamANSITest class methodsFor: nil! helperClassesDo: aBlock super helperClassesDo: aBlock. aBlock value: GettableStreamHelper. aBlock value: CollectionStreamHelper. aBlock value: ReadStreamHelper.! ! !CharacterFactoryANSITest methodsFor: nil! testXcr " #cr " #'Fundamental'. self value: [Character cr] should: [:r | true "implementation defined "] conformTo: #'Character factory' selector: #'cr'.! testXspace " #space " #'Fundamental'. self value: [Character space] should: [:r | true "implementation defined "] conformTo: #'Character factory' selector: #'space'.! protocol ^#'Character factory'! testXlf " #lf " #'Fundamental'. self value: [Character lf] should: [:r | true "implementation defined "] conformTo: #'Character factory' selector: #'lf'.! testXtab " #tab " #'Fundamental'. self value: [Character tab] should: [:r | true "implementation defined "] conformTo: #'Character factory' selector: #'tab'.! canonicalObject ^Character! testXcodePointX " #codePoint: " #'Fundamental'. self value: [Character codePoint: ($a codePoint)] should: [:r | r = $a] conformTo: #'Character factory' selector: #'codePoint:'. self value: [Character codePoint: 3000000] shouldRaise: Error.! ! !ArrayANSITest methodsFor: nil! emptyCollection ^self canonicalObject class new! canonicalElement ^self canonicalObject at: 2! canonicalObject ^#(1 2 3 4) copy! protocol ^#Array! ! !ArrayANSITest class methodsFor: nil! helperClassesDo: aBlock super helperClassesDo: aBlock. aBlock value: SequencedCollectionHelper. aBlock value: SequencedReadableCollectionHelper! ! !FloatCharacterizationANSITest methodsFor: nil! testXe " #e " #'Numeric'.! testXfminDenormalized " #fminDenormalized " #'Numeric'.! testXfmax " #fmax " #'Numeric'.! testXprecision " #precision " #'Numeric'.! testXepsilon " #epsilon " #'Numeric'.! testXpi " #pi " #'Numeric'.! protocol ^#'floatCharacterization'! canonicalObject ^Float! testXemin " #emin " #'Numeric'.! testXfminNormalized " #fminNormalized " #'Numeric'.! testXfmin " #fmin " #'Numeric'.! testXemax " #emax " #'Numeric'.! testXdenormalized " #denormalized " #'Numeric'.! testXradix " #radix " #'Numeric'.! ! !MsgReturnRuleSpec methodsFor: nil! returnProtocolName: receiver ^self ruleBlock value: receiver! returnValueRuleBlockSource: blockSource "Set the rule block source code that when evaluated with appropiate values answers the protocol message return value conforms-to protocol name." ruleBlock := nil. ruleSourceCode := blockSource. (ruleSourceCode includes: $^) ifFalse: [^self]. ruleSourceCode := ruleSourceCode select: [:c | c ~~ $^]! printOn: targetStream "Append to targetStream a text representation of the receiver as a developer would want to see it (inspector, etc)." targetStream nextPutAll: self class name; nextPut: $(; nextPutAll: self returnValueRuleBlockSource; nextPut: $)! returnValueAliasingAttribute "Signal an error as the receiver specifies no behavior." self error: 'Protocol msg. return value rule specifies no aliasing attribute.'! newRetValRuleSourceCode: ruleBlockSource "Private - ." ruleBlock := nil. ruleSourceCode := ruleBlockSource. (ruleSourceCode includes: $^) ifFalse: [^self]. ruleSourceCode := ruleSourceCode select: [:c | c ~~ $^]! isConformingReturnClass: returnClass ruleReceiver: receiver operand: operand "Answer true if the class, returnClass, of the result of sending a message conforms to the receiver, else false." | returnProtocolName | #todo. "??? bug does not allow return in block ???" returnProtocolName := self ruleBlock value: receiver value: operand. ^returnClass conformsToProtocolNamed: returnProtocolName.! returnValueProtocolNames "Signal an error as the receiver specifies no behavior." self error: 'Protocol msg. return value rule specifies no protocol.'! isConformingReturnClass: returnClass ruleReceiver: receiver "Answer true if the class, returnClass, of the result of sending a message conforms to the receiver, else false." | returnProtocolName | #todo. "??? bug does not allow return in block ???" returnProtocolName := self ruleBlock value: receiver. ^returnClass conformsToProtocolNamed: returnProtocolName.! ruleBlock ruleBlock isNil ifTrue: [ruleBlock := Compiler evaluate: ruleSourceCode]. ^ruleBlock! returnValueRuleBlockSource "Answer the rule block source code that when evaluated with appropiate values answers the protocol message return value conforms-to protocol name." ^ ruleSourceCode! ! !MsgReturnRuleSpec class methodsFor: nil! newRetValRuleSourceCode: ruleBlockSource "Answer a new return value specification representing a protocol message's return value conforms-to protocol determined by evaluating the rule, ruleBlockSource, with appropiate values." ^ self privateNewRetValRuleSourceCode: ruleBlockSource! privateNewRetValRuleSourceCode: ruleBlockSource "Private - ." (ruleBlockSource isKindOf: String) ifFalse: [self error: 'Protocol msg. return value rule block source not a String.']. ^ self basicNew newRetValRuleSourceCode: ruleBlockSource; yourself! ! !ProtocolANYSpec methodsFor: nil! conformsToMessageSelectors "Answer all of selectors which make up all protocols to which the receiver conforms." | tmpList | tmpList := self protocolManager defaultMessageSpecificationCollection. self allConformsToProtocolNames do: [:aProtocollName | tmpList addAll: (self protocolManager protocolNamed: aProtocollName) messageSelectors]. ^ tmpList! removeSelector: unused "Signal an error as the receiver specifies no behavior." self error: 'Protocol <' , self protocolName , '> specifies no behavior.'! removeSelector: unused1 ifAbsent: unused2 "Signal an error as the receiver specifies no behavior." self error: 'Protocol <' , self protocolName , '> specifies no behavior.'! wrkAllConformsToMessageSelectorsTo: aDict visited: visitedProtocols self messageSelectors do: [:aMessageSelector | (aDict includesKey: aMessageSelector) ifFalse: [aDict at: aMessageSelector put: self protocolName]]. visitedProtocols add: self protocolName. self conformsToProtocolNames do: [:aProtoName | (visitedProtocols includes: aProtoName) ifFalse: [(self protocolManager protocolNamed: aProtoName) wrkAllConformsToMessageSelectorsTo: aDict visited: visitedProtocols]]! messageSelectors "Answer an empty list of of selectors which make up the receiver's protocol." ^ self protocolManager defaultMessageSpecificationCollection! protocolName "Answer the name of the receiver." ^ self protocolManager protocolANYName! renameToProtocolName: unused "Signal an error as the receiver can not be renamed." self error: 'Protocol <' , self protocolName , '> can not be renamed.'! removeAllSelectors: unused "Signal an error as the receiver specifies no behavior." self error: 'Protocol <' , self protocolName , '> specifies no behavior.'! allConformsToProtocolNames "Answer the names of all protocols to which the receiver conforms including super protocols." | tmpList | tmpList := self conformsToProtocolNames. self conformsToProtocolNames do: [:aProtocollName | tmpList addAll: (self protocolManager protocolNamed: aProtocollName) allConformsToProtocolNames]. ^ tmpList! fileOutOnSIFFiler: programFiler "Do nothing as the receiver is created by protocol initialization." ^ self! messageOrNilAtSelector: selector "Answer nil protocol by definition can't have any messages." "2000/06/23 Harmon, R. Added to fix bug when TestCaseANSI >> #assertSend: is sent with a selector not defined in the target protocol or any of its inherited protocols." ^nil! printOn: targetStream "Append to targetStream a text representation of the receiver as a developer would want to see it (inspector, etc)." targetStream nextPut: $<; nextPutAll: self protocolName; nextPut: $>; nextPut: $(. self messageSelectors do: [:selector | targetStream nextPutAll: selector] separatedBy: [targetStream nextPutAll: ', ']. targetStream nextPut: $)! allMessageSelectors "Answer all of selectors which make up the receiver's protocol and all protocols to which the receiver conforms." | tmpList | tmpList := self messageSelectors. self allConformsToProtocolNames do: [:aProtocollName | tmpList addAll: (self protocolManager protocolNamed: aProtocollName) messageSelectors]. ^ tmpList! conformingBehaviors "Answer all classes in class then metaclass hierarchy order (i.e. superclasses first) as all conform to the receiver. Note: Return value is a of class or metaclass objects." | answer | answer := OrderedCollection new: 10. Smalltalk allClasses do: [:class | answer addLast: class. answer addLast: class class]. ^ answer! messages "Answer an empty list of of message specifications of the receiver." ^ self protocolManager defaultMessageSpecificationCollection! hash "Answer the hash value for the receiver." ^ self protocolName hash! selectorsInBehavior: classOrMetaclass "Answer an empty list of selectors ofcorresponding messages as all classes and metaclasses conform to the receiver but it specifies no behavior." ^ Set new! <= comperand "Answer whether the receiver is less than or equal to comperand. Note: This is to allow protocols to be sorted with the default sort block." (comperand isKindOf: self protocolManager protocol) | (comperand isKindOf: self protocolManager protocolANY) ifFalse: [self error: 'Comperand not a ProtocolSpec.']. ^ self protocolName asLowercase <= comperand protocolName asLowercase! conformsToProtocolNames "Answer an empty list of protocol names to which the receiver conforms." ^ self protocolManager defaultConformsToCollection! = comperand "Answer whether the receiver is considered equal (contains same elements) to comperand." ^ (comperand isKindOf: self protocolManager protocol) and: [self protocolName == comperand protocolName]! protocolDescription "Answer a description of the receiver." ^ 'A protocol to which all other protocols conform.' copy! displayOn: targetStream "Append the receiver to targetStream in a format that a user would want to see." targetStream nextPut: $<; nextPutAll: self protocolName; nextPut: $>! addUndefinedProtocolNames ^ self! includesSelector: unused "Answer false as the receiver specifies no behavior." ^ false! ! !ProtocolANYSpec class methodsFor: nil! new "Raise an exception as this is an inappropriate message." ^ self shouldNotImplement! privateNewProtocolANY "Private -" | newProtocol | newProtocol := self basicNew. ^ newProtocol! ! !WriteFileStreamANSITest methodsFor: nil! testXflush " #flush " #'File Stream'.! testXnextPutX " #nextPut: " #'File Stream'.! testXisEmpty " #isEmpty " #'File Stream'.! protocol ^#'writeFileStream'! testXtab " #tab " #'File Stream'.! setUp super setUp. " This method will create a file named 'ansiTestFile.junk' in the current directory if it does not already exist. " "writeFileStream := FileStream write: 'ansiTestFile.junk'"! testXspace " #space " #'File Stream'.! testXsetToEnd " #setToEnd " #'File Stream'.! testXpositionX " #position: " #'File Stream'.! testXisBinary " #isBinary " #'File Stream'.! tearDown "writeFileStream close"! testXcontents " #contents " #'File Stream'.! testXreset " #reset " #'File Stream'.! testXisText " #isText " #'File Stream'.! testXclose " #close " #'File Stream'.! testXexternalType " #externalType " #'File Stream'.! testXcr " #cr " #'File Stream'.! testXnextPutAllX " #nextPutAll: " #'File Stream'.! canonicalObject ^writeFileStream! testXposition " #position " #'File Stream'.! ! !WriteStreamANSITest methodsFor: nil! protocol ^#'WriteStream'! setUp super setUp. writeStream := WriteStream with: 'this is a string' copy! canonicalObject ^writeStream! ! !WriteStreamANSITest class methodsFor: nil! helperClassesDo: aBlock super helperClassesDo: aBlock. aBlock value: PuttableStreamHelper. aBlock value: CollectionStreamHelper. aBlock value: WriteStreamHelper.! ! !WriteStreamFactoryANSITest methodsFor: nil! protocol ^#'WriteStream factory'! canonicalObject ^WriteStream! testXwithX self value: [self canonicalObject with: 'this is a string'] should: [:r | r position = ('this is a string' size) & r contents = 'this is a string'] conformTo: self protocol selector: #'with:'.! ! !DyadicValuableANSITest methodsFor: nil! testXvalueWithArgumentsX " #valueWithArguments: " #'Valuable'. self value: [blk2args valueWithArguments: #(1 2)] should: [:r | r = #(1 2)] conformTo: #'valuable' selector: #'valueWithArguments:'.! testXargumentCount " #argumentCount " #'Valuable'. self value: [blk2args argumentCount] should: [:r | r = 2] conformTo: #'dyadicValuable' selector: #'argumentCount'.! protocol ^#'dyadicValuable'! setUp super setUp. blk2args := [ :arg1 :arg2 | Array with: arg1 with: arg2 ].! testXvalueXvalueX " #value:value: " #'Valuable'. self value: [blk2args value: 1 value: 2] should: [:r | r = #(1 2)] conformTo: #'dyadicValuable' selector: #'value:value:'.! canonicalObject ^blk2args! ! !ExtensibleCollectionHelper methodsFor: nil! testXaddAllX " #addAll: " | extensibleCollection addCollection compareCollection | #'Collection'. extensibleCollection := self object. self value: [extensibleCollection addAll: #(666 777)] should: [:result | (extensibleCollection includes: 777) and: [extensibleCollection includes: 666]] conformTo: #extensibleCollection selector: #addAll:. addCollection := OrderedCollection with: 555 with: 444. extensibleCollection := self object. compareCollection := self object. self should: [(addCollection do: [:each | extensibleCollection add: each]) = (compareCollection addAll: addCollection)]! testXremoveX " #remove: " | extensibleCollection sampleValue | #'Collection'. extensibleCollection := self object. extensibleCollection do: [ :each | sampleValue := each]. self value: [ extensibleCollection remove: sampleValue ] should: [:result | (extensibleCollection includes: sampleValue) not ] conformTo: #extensibleCollection selector: #remove:! testXaddX " #add: " | extensibleCollection | #'Collection'. extensibleCollection := self object. self value: [ extensibleCollection add: 777 ] should: [:result | extensibleCollection includes: 777] conformTo: #extensibleCollection selector: #add:! testXremoveAllX " #removeAll: " | extensibleCollection removeAll | #'Collection'. extensibleCollection := self object. removeAll := self object. self value: [ extensibleCollection removeAll: removeAll] should: [:result | extensibleCollection isEmpty ] conformTo: #extensibleCollection selector: #removeAll:! object: anObject! testXremoveXifAbsentX " #remove:ifAbsent: " | extensibleCollection sampleValue | #'Collection'. extensibleCollection := self object. extensibleCollection do: [ :each | sampleValue := each]. self value: [ extensibleCollection remove: sampleValue ifAbsent: [#foo]] should: [:result | result = sampleValue ] conformTo: #extensibleCollection selector: #remove:ifAbsent:. self value: [ extensibleCollection remove: sampleValue ifAbsent: [#foo]] should: [:result | result = #foo ] conformTo: #extensibleCollection selector: #remove:ifAbsent:! object ^testCase canonicalObject! ! !SetFactoryANSITest methodsFor: nil! testXwithX " #with: " #'Collection'.! testXwithXwithX " #with:with: " #'Collection'.! testXnew " #new " #'Collection'.! protocol ^#'Set factory'! testXnewX " #new: " #'Collection'.! testXwithAllX " #withAll: " #'Collection'.! canonicalObject ^Set! testXwithXwithXwithX " #with:with:with: " #'Collection'.! testXwithXwithXwithXwithX " #with:with:with:with: " #'Collection'.! ! !ObjectANSITest methodsFor: nil! protocol ^#Object! setUp super setUp. object := Object new.! canonicalObject ^object! ! !NotificationClassANSITest methodsFor: nil! testXsignalX " #signal: " #'Exception'.! testXallSubclasses " #allSubclasses " #'Exception'.! testXname " #name " #'Exception'.! testXsuperclass " #superclass " #'Exception'.! protocol ^#'Notification class'! testXconcatenateOp " #, " #'Exception'.! testXallSuperclasses " #allSuperclasses " #'Exception'.! testXnew " #new " #'Exception'. self value: [Notification new] should: [:r | true "??? r = Notification signal ???"] conformTo: #'Notification class' selector: #'new'.! testXsignal " #signal " #'Exception'.! canonicalObject ^Notification! testXhandlesX " #handles: " #'Exception'.! testXsubclasses " #subclasses " #'Exception'.! ! !NiladicBlockANSITest methodsFor: nil! setUp super setUp. blk0args := [ Array new ]. canonicalObject := [3+4]! testXonXdoX " #on:do: " #'Valuable'. self value: [ [#( 1 2 ) size] on: Error do: [ :error | error return: -1] ] should: [:r | r = 2] conformTo: #'niladicBlock' selector: #'on:do:'. self value: [[Error signal. 0] on: Error do: [:error | error return: -1]] should: [:r | r = -1] conformTo: #'niladicBlock' selector: #'on:do:'.! testXwhileTrueX " #whileTrue: " | sum | #'Valuable'. sum := 0. self value: [ [sum < 4 ] whileTrue: [sum := sum + 1] ] should: [:r | sum = 4] conformTo: #'niladicValuable' selector: #'whileTrue:'. sum := 0. self value: [ [sum < 0 ] whileTrue: [sum := sum + 1] ] should: [:r | sum = 0] conformTo: #'niladicValuable' selector: #'whileTrue:'.! testXensureX " #ensure: " | flag tmp | #'Valuable'. flag := 0. self value: [ [#( 1 2 ) size] ensure: [flag := 1] ] should: [:r | r = 2 & flag = 1] conformTo: #'niladicBlock' selector: #'ensure:'. #'todo'."I don't think this is a good test." flag := 0. [tmp := [#( 1 2 ) siz] ensure: [ flag := 1 ]. ] on: MessageNotUnderstood do: [ :mnu | mnu return ]. self value: [tmp] should: [:r | flag = 1] conformTo: #'niladicBlock' selector: #'ensure:'. self value: [ [#( 1 2 ) siz] ensure: [ flag := 1 ] ] shouldRaise: MessageNotUnderstood. #'todo'."or this ." flag := 0. [tmp := [Error signal] ensure: [ flag := 1 ]. ] on: Error do: [ :error | error return ]. self value: [ tmp ] should: [:r | flag = 1] conformTo: #'niladicBlock' selector: #'ensure:'. self value: [ [Error signal] ensure: [ flag := 1 ] ] shouldRaise: Error. #'testAnom'. "??? I think the ensure block should not be evaluated as per: Activation of an exception handler from within the receiver is not in and of itself an abnormal termination. However, if the exception handler for an exception that is not resumable results in termination of the receiver or if its handler block contains a return statement that results in abnormal termination of the receiver, then terminationBlock will be evaluated after evaluation of the exception handler. flag := 0. [tmp := [Notification signal] ensure: [ flag := 1 ]. ] on: Notification do: [ :notification | notification resume ]. self value: [ tmp ] should: [:r | flag = 0] conformTo: #'niladicBlock' selector: #'ensure:'. ???" self value: [ [Notification signal] ensure: [] ] shouldRaise: Notification.! protocol ^#'niladicBlock'! testXargumentCount " #argumentCount " #'Valuable'. self value: [blk0args argumentCount] should: [:r | r = 0] conformTo: #'niladicValuable' selector: #'argumentCount'.! testXwhileTrue " #whileTrue " | sum | #'Valuable'. sum := 0. self value: [ [(sum := sum + 1) < 4 ] whileTrue ] should: [:r | sum = 4] conformTo: #'niladicValuable' selector: #'whileTrue'.! testXvalueWithArgumentsX " #valueWithArguments: " #'Valuable'. self value: [blk0args valueWithArguments: #()] should: [:r | r = #()] conformTo: #'valuable' selector: #'valueWithArguments:'.! testXwhileFalse " #whileFalse " | sum | #'Valuable'. sum := 0. self value: [ [(sum := sum + 1) >= 3] whileFalse] should: [:r | sum = 3] conformTo: #'niladicValuable' selector: #'whileFalse'.! testXvalue " #value " #'Valuable'. self value: [blk0args value] should: [:r | r = #()] conformTo: #'niladicValuable' selector: #'value'.! canonicalObject ^canonicalObject! testXifCurtailedX " #ifCurtailed: " | flag tmp | #'Valuable'. self value: [ [flag := 0] ifCurtailed: [flag := 1] ] should: [:r | r = 0 & flag = 0] conformTo: #'niladicBlock' selector: #'ifCurtailed:'. [tmp := [Notification signal. 0] ifCurtailed: [flag := 1]. ] on: Notification do: [ :notification | notification resume ]. self value: [ tmp ] should: [:r | r = 0 & flag = 0] conformTo: #'niladicBlock' selector: #'ifCurtailed:'.! testXwhileFalseX " #whileFalse: " | element aReadStream | #'Valuable'. aReadStream := ReadStream on: (Array with: 1 with: 2 with: 3). self value: [[aReadStream atEnd] whileFalse: [ element := aReadStream next]] should: [:r | element = 3] conformTo: #'niladicValuable' selector: #'whileFalse:'. element := 0. self value: [ [element = 0] whileFalse: [element := 1] ] should: [:r | element = 0] conformTo: #'niladicValuable' selector: #'whileFalse:'.! ! !MessageNotUnderstoodSelectorANSITest methodsFor: nil! testXhandlesX " #handles: " #'Exception'. self value: [ [ MessageNotUnderstood signal ] on: MessageNotUnderstood do: [ :mnu | mnu return: (MessageNotUnderstood handles: mnu) ] ] should: [:r | r] conformTo: #'MessageNotUnderstoodSelector' selector: #'handles:'. " ??? should! " self value: [ [ MessageNotUnderstood signal ] on: MessageNotUnderstood do: [ :mnu | mnu return: (Error handles: mnu) ] ] should: [:r | r] conformTo: #'MessageNotUnderstoodSelector' selector: #'handles:'.! testXconcatenateOp " #, " #'Exception'.! canonicalObject ^MessageNotUnderstood! protocol ^#MessageNotUnderstoodSelector! ! !FractionANSITest methodsFor: nil! testXasScaledDecimalX " #asScaledDecimal: " #'Numeric'. self value: [(1/2) asScaledDecimal: 2] should: [:r | r = 0.5s2 & (r scale = 2)] conformTo: #'number' selector: #'asScaledDecimal:'. self value: [(-1/2) asScaledDecimal: 2] should: [:r | r = -0.5s2 & (r scale = 2)] conformTo: #'number' selector: #'asScaledDecimal:'.! testXtoXbyXdoX " #to:by:do: " #'Numeric'.! testXasInteger " #asInteger " #'Numeric'. self value: [(1/3) asInteger] should: [:r | r = 0] conformTo: #'number' selector: #'asInteger'. self value: [(1/2) asInteger] should: [:r | r = 1] conformTo: #'number' selector: #'asInteger'. self value: [(-1/2) asInteger] should: [:r | r = -1] conformTo: #'number' selector: #'asInteger'.! testXdenominator " #denominator " #'Numeric'.! testXmaxX " #max: " #'Numeric'. " #( 2 -2000000000 2000000000 2.0 1/2 2.0s3 )." #'todo'."It is erroneous if the receiver and operand are not comparable." self value: [(1/2) max: 3] should: [:r | r = 3] conformTo: #'magnitude' selector: #'max:'. self value: [(-9000000000/2) max: -2000000000] should: [:r | r = -2000000000] conformTo: #'magnitude' selector: #'max:'. self value: [(1/2) max: 2000000003] should: [:r | r = 2000000003] conformTo: #'magnitude' selector: #'max:'. self value: [(1/2) max: 3.0] should: [:r | r = 3.0] conformTo: #'magnitude' selector: #'max:'. self value: [(1/2) max: (5/2)] should: [:r | r = (5/2)] conformTo: #'magnitude' selector: #'max:'. self value: [(1/2) max: 3.0s3] should: [:r | r = 3.0s3] conformTo: #'magnitude' selector: #'max:'. "Num max: Num -> Num" 1 to: numList size do: [ :ndx | self value: [(numList at: ndx) max: (numList at: ndx)] should: [:r | r = (numList at: ndx)] conformTo: #'magnitude' selector: #'max:' ].! testXnotEqualityOp " #~= " #'Numeric'. " The value of receiver ~= comparand is true if and only if the value of comparand ~= receiver would also be true. " self value: [fractionHalf ~= (2/3)] should: [:r | r] conformTo: #'Object' selector: #'~='. self value: [smallInt2 ~= (6/2)] should: [:r | r] conformTo: #'Object' selector: #'~='. self value: [fractionHalf ~= fractionHalf] shouldnt: [:r | r] conformTo: #'Object' selector: #'~='. self value: [smallInt2 ~= (4/2)] shouldnt: [:r | r] conformTo: #'Object' selector: #'~='.! testXbetweenXandX " #between:and: " #'Numeric'. " #( 2 -2000000000 2000000000 2.0 1/2 2.0s3 )." #'todo'."It is erroneous if the receiver and min or max are not comparable" self value: [(1/2) between: 0 and: 3] should: [:r | r] conformTo: #'magnitude' selector: #'between:and:'. self value: [(1/ -2) between: -2000000003 and: 0] should: [:r | r] conformTo: #'magnitude' selector: #'between:and:'. self value: [(1/2) between: 0 and: 2000000003] should: [:r | r] conformTo: #'magnitude' selector: #'between:and:'. self value: [(1/2) between: 0.0 and: 3.0] should: [:r | r] conformTo: #'magnitude' selector: #'between:and:'. self value: [(1/2) between: (1/4) and: (5/2)] should: [:r | r] conformTo: #'magnitude' selector: #'between:and:'. self value: [(1/2) between: 0.0s3 and: 3.0s3] should: [:r | r] conformTo: #'magnitude' selector: #'between:and:'. self value: [(1/2) between: -2000000001 and: 2000000003] should: [:r | r] conformTo: #'magnitude' selector: #'between:and:'. self value: [(1/2) between: 0.0 and: 3.0s3] should: [:r | r] conformTo: #'magnitude' selector: #'between:and:'. "Num between: Num and: Num -> true" 1 to: numList size do: [ :ndx | self value: [(numList at: ndx) between: (numList at: ndx) and: (numList at: ndx)] should: [:r | r] conformTo: #'magnitude' selector: #'between:and:' ]. self value: [(1/2) between: 3 and: 4] shouldnt: [:r | r] conformTo: #'magnitude' selector: #'between:and:'. self value: [(1/2) between: -2000000003 and: -2000000005] shouldnt: [:r | r] conformTo: #'magnitude' selector: #'between:and:'. self value: [(1/2) between: 2000000003 and: 2000000005] shouldnt: [:r | r] conformTo: #'magnitude' selector: #'between:and:'. self value: [(1/2) between: 3.0 and: 5.0] shouldnt: [:r | r] conformTo: #'magnitude' selector: #'between:and:'. self value: [(1/2) between: (5/2) and: (7/2)] shouldnt: [:r | r] conformTo: #'magnitude' selector: #'between:and:'. self value: [(1/2) between: 3.0s3 and: 5.0s3] shouldnt: [:r | r] conformTo: #'magnitude' selector: #'between:and:'. "??? min not min but max and vice versa -> false ???" self value: [(1/2) between: 3 and: 1] shouldnt: [:r | r] conformTo: #'magnitude' selector: #'between:and:'.! testXabs " #abs (Return Values: ) " | rcvr | #'Numeric'. rcvr := 1/2. self value: [rcvr abs] should: [:r | r = (1/2)] conformTo: #'number' selector: #'abs' opRECEIVER: rcvr. rcvr := -1/2. self value: [rcvr abs] should: [:r | r = (1/2)] conformTo: #'number' selector: #'abs' opRECEIVER: rcvr.! testXraisedToIntegerX " #raisedToInteger: (Return Values: )" | rcvr | #'Numeric'. rcvr := 51/10. self value: [rcvr raisedToInteger: 0] should: [:r | r = 1] conformTo: #'number' selector: #'raisedToInteger:' opRECEIVER: rcvr. self value: [rcvr raisedToInteger: 1] should: [:r | r = rcvr] conformTo: #'number' selector: #'raisedToInteger:' opRECEIVER: rcvr. self value: [rcvr raisedToInteger: 2] should: [:r | r = (2601/100)] conformTo: #'number' selector: #'raisedToInteger:' opRECEIVER: rcvr. self value: [rcvr negated raisedToInteger: 2] should: [:r | r = (2601/100)] conformTo: #'number' selector: #'raisedToInteger:' opRECEIVER: rcvr. self value: [rcvr raisedToInteger: -2] should: [:r | r = ( 100/2601)] conformTo: #'number' selector: #'raisedToInteger:' opRECEIVER: rcvr. "It is erroneous if the operand does not conform to the protocol ." self value: [rcvr raisedToInteger: (51/10)] shouldRaise: Error.! testXasFraction " #asFraction " #'Numeric'. self value: [(1/2) asFraction] should: [:r | r = (1/2)] conformTo: #'number' selector: #'asFraction'. self value: [(-1/2) asFraction] should: [:r | r = (-1/2)] conformTo: #'number' selector: #'asFraction'.! testXisKindOfX " #isKindOf: " #'Numeric'. " The return value is unspecified if the receiver is a class object or candidateClass is not a class object. " #todo. "Fix find a test for unspecified rule above ???" self value: [fractionHalf isKindOf: Fraction] should: [:r | r] conformTo: #'Object' selector: #'isKindOf:'. "Metaclass tests:" self value: [fractionHalf class isKindOf: (Fraction class)] should: [:r | r] conformTo: #'Object' selector: #'isKindOf:'. "Inherit tests:" self value: [fractionHalf class isKindOf: (Number class)] should: [:r | r] conformTo: #'Object' selector: #'isKindOf:'. self value: [fractionHalf isKindOf: Symbol] shouldnt: [:r | r] conformTo: #'Object' selector: #'isKindOf:'.! testXtruncated " #truncated " #'Numeric'. self value: [(1/3) truncated] should: [:r | r = 0] conformTo: #'number' selector: #'truncated'. self value: [(3/2) truncated] should: [:r | r = 1] conformTo: #'number' selector: #'truncated'. self value: [(-1/2) truncated] should: [:r | r = 0] conformTo: #'number' selector: #'truncated'.! testXroundToX " #roundTo: (returnRule - :receiver :operand) " | retVals frac | #'Numeric'. " #( 2 -2000000000 2000000000 2.0 1/2 2.0s3 )." frac := (51/10). retVals := #(6 0 0 6.0 5 6.000s3). 1 to: numList size do: [ :ndx | self value: [frac roundTo: (numList at: ndx)] should: [:r | r = (retVals at: ndx)] conformTo: #'number' selector: #'roundTo:' ruleReceiver: frac operand: (numList at: ndx) ]. self should: [(0.0 roundTo: fractionHalf) = 0.0]! testXasFloat " #asFloat " #'Numeric'. self value: [(1/2) asFloat] should: [:r | r = 0.5] conformTo: #'number' selector: #'asFloat'. self value: [(-1/2) asFloat] should: [:r | r = -0.5] conformTo: #'number' selector: #'asFloat'.! testXremX " #rem: " | retVals ndx num2 frac | #'Numeric'. "Within the limits of representation, the following invariant should hold: (receiver quo: operand)*operand + (receiver rem: operand) = receiver" " #( 2 -2000000000 2000000000 2.0 1/2 2.0s3 )." numList := #( 5 5.0 5.0s3 ). frac := (53/2). retVals := Array with: (3/2) with: 1.5 with: (3/2). ndx := 0. numList do: [ :num | ndx := ndx + 1. self value: [frac rem: num] should: [:r | r = (retVals at: ndx) & ((frac quo: num) * num + (frac rem: num) = frac)] conformTo: #'number' selector: #'rem:' ]. numList := numList collect: [ :num | num negated ]. ndx := 0. numList do: [ :num | ndx := ndx + 1. self value: [frac rem: num] should: [:r | r = (retVals at: ndx) & ((frac quo: num) * num + (frac rem: num) = frac)] conformTo: #'number' selector: #'rem:' ]. frac := (-53/2). numList := #( 5 5.0 5.0s3 ). retVals := retVals collect: [ :num | num negated ]. ndx := 0. numList do: [ :num | ndx := ndx + 1. self should: [(frac rem: num) = (retVals at: ndx) & ((frac quo: num) * num + (frac rem: num) = frac)] ]. ndx := 0. numList do: [ :num | ndx := ndx + 1. self should: [(frac rem: num) = (retVals at: ndx) & ((frac quo: num) * num + (frac rem: num) = frac)] ]. frac := (53/2). num2 := (5/2). self value: [frac rem: num2] should: [:r | r = (3/2) & ((frac quo: num2) * num2 + (frac rem: num2) = frac)] conformTo: #'number' selector: #'rem:'. frac := (20000000003/2). numList := #( -2000000000 2000000000 ). numList do: [ :num | self value: [frac rem: num] should: [:r | r = (3/2) & ((frac quo: num) * num + (frac rem: num) = frac)] conformTo: #'number' selector: #'rem:' ]. "If either the receiver or operand are of type and the operand has a value of zero, the result is implementation defined. The implementation may signal the ZeroDivide exception or provide a continuation value " self value: [fractionHalf rem: 0.0] shouldRaise: ZeroDivide. self value: [fractionHalf rem: 0] shouldRaise: ZeroDivide.! testXnotIdentityOp " #~~ " #'Numeric'. " The value of receiver ~~ comparand is true if and only if the value of comparand ~~ receiver would also be true. " self should: [fractionHalf ~~ (2/3) and: [(2/3) ~~ fractionHalf]]. self value: [fractionHalf ~~ (2/3)] should: [:r | r] conformTo: #'Object' selector: #'~~'. self value: [smallInt2 ~~ (6/2)] should: [:r | r] conformTo: #'Object' selector: #'~~'. self value: [fractionHalf ~~ fractionHalf] shouldnt: [:r | r] conformTo: #'Object' selector: #'~~'. self value: [smallInt2 ~~ (4/2)] shouldnt: [:r | r] conformTo: #'Object' selector: #'~~'.! testXtoXbyX " #to:by: " #'Numeric'.! testXequalityOp " #= " #'Numeric'. " receiver = comparand => receiver hash = comparand hash " self value: [fractionHalf = fractionHalf] should: [:r | r & (fractionHalf hash = fractionHalf hash) ] conformTo: #'number' selector: #'='. self value: [ fractionHalf = (5/2) ] shouldnt: [ :r | r | (fractionHalf hash = (5/2) hash) ] conformTo: #'number' selector: #'='. " #( 2 -2000000000 2000000000 2.0 1/2 2.0s3 )." self value: [ fractionHalf = 2 ] should: [ :r | r ifTrue: [ fractionHalf hash = 2 hash ] ifFalse: [ fractionHalf hash ~= 2 hash ] ] conformTo: #'number' selector: #'='. self value: [ fractionHalf = -2000000000 ] should: [ :r | r ifTrue: [ fractionHalf hash = -2000000000 hash ] ifFalse: [ fractionHalf hash ~= -2000000000 hash ] ] conformTo: #'number' selector: #'='. self value: [ fractionHalf = 2000000000 ] should: [ :r | r ifTrue: [ fractionHalf hash = 2000000000 hash ] ifFalse: [ fractionHalf hash ~= 2000000000 hash ] ] conformTo: #'number' selector: #'='. self value: [ fractionHalf = 0.5 ] should: [ :r | r ifTrue: [ fractionHalf hash = 0.5 hash ] ifFalse: [ fractionHalf hash ~= 0.5 hash ] ] conformTo: #'number' selector: #'='. self value: [ fractionHalf = 0.5s3 ] should: [ :r | r ifTrue: [ fractionHalf hash = 0.5s3 hash ] ifFalse: [ fractionHalf hash ~= 0.5s3 hash ] ] conformTo: #'number' selector: #'='.! testXstrictlyPositive " #strictlyPositive " #'Numeric'. self value: [(1/2) strictlyPositive] should: [:r | r] conformTo: #'number' selector: #'strictlyPositive'. self value: [(-1/2) strictlyPositive] shouldnt: [:r | r] conformTo: #'number' selector: #'strictlyPositive'.! testXidentityOp " #== " #'Numeric'. " The value of receiver == comparand is true if and only if the value of comparand == receiver would also be true. If the value of receiver == comparand is true then the receiver and comparand must have equivalent identity hash values. Or more formally: receiver == comparand => receiver identityHash = comparand identityHash " self value: [fractionHalf == fractionHalf] should: [:r | r] conformTo: #'Object' selector: #'=='. self value: [smallInt2 == (4/2)] should: [:r | r] conformTo: #'Object' selector: #'=='. self value: [fractionHalf == (2/3)] shouldnt: [:r | r] conformTo: #'Object' selector: #'=='. self value: [smallInt2 == (6/2)] shouldnt: [:r | r] conformTo: #'Object' selector: #'=='.! testXnegated " #negated (Return Values: ) " | rcvr | #'Numeric'. rcvr := 3/2. self value: [rcvr negated] should: [:r | r = (-3/2)] conformTo: #'number' selector: #'negated' opRECEIVER: rcvr. rcvr := -3/2. self value: [rcvr negated] should: [:r | r = (3/2)] conformTo: #'number' selector: #'negated' opRECEIVER: rcvr.! testXisMemberOfX " #isMemberOf: " #'Numeric'. " The return value is unspecified if the receiver is a class object or candidateClass is not a class object. " #todo. "Fix find a test for unspecified rule above ???" self value: [fractionHalf isMemberOf: Fraction] should: [:r | r] conformTo: #'Object' selector: #'isMemberOf:'. "Metaclass tests:" self value: [fractionHalf class isMemberOf: (Fraction class)] should: [:r | r] conformTo: #'Object' selector: #'isMemberOf:'. "Fail inherit tests:" self value: [fractionHalf class isMemberOf: (Number class)] shouldnt: [:r | r] conformTo: #'Object' selector: #'isMemberOf:'. self value: [fractionHalf isMemberOf: Float] shouldnt: [:r | r] conformTo: #'Object' selector: #'isMemberOf:'.! testXsquared " #squared (Return Values: )" | rcvr | #'Numeric'. rcvr := 51/10. self value: [rcvr squared] should: [:r | r = (2601/100)] conformTo: #'number' selector: #'squared' opRECEIVER: rcvr. rcvr := -51/10. self value: [rcvr squared] should: [:r | r = (2601/100)] conformTo: #'number' selector: #'squared' opRECEIVER: rcvr.! testXremainderIntegerDivideOp " #\\ (returnRule - :receiver :operand) " "The remainder has the same sign as operand. Within the limits of representation, the following invariant should hold: (receiver // operand) * operand + (receiver \\ operand) = receiver " | retVals recList ndx | #'Numeric'. " #( 2 -2000000000 2000000000 2.0 1/2 2.0s3 )." recList := #( 26 -26000000006 26000000006 26.0 0 26.0s3 ) copy. recList at: 5 put: (53/2). retVals := #( 0 1 0 0.5 1 0 ) copy. retVals at: 1 put: (1/2). retVals at: 3 put: (1/2). retVals at: 6 put: (1/2). ndx := 0. recList do: [ :rec | ndx := ndx + 1. self value: [rec \\ (3/2)] should: [:r | r = (retVals at: ndx) & ((rec // (3/2)) * (3/2) + (rec \\ (3/2)) = rec)] conformTo: #'number' selector: #'\\' ruleReceiver: rec operand: (3/2). ]. "The remainder has the same sign as operand." retVals := #(-1 0 -1 -1.0 0 -1.000s3 ) copy. retVals at: 2 put: (-1/2). retVals at: 5 put: (-1/2). ndx := 0. recList do: [ :rec | ndx := ndx + 1. self value: [rec \\ (-3/2)] should: [:r | r = (retVals at: ndx) & ((rec // (-3/2)) * (-3/2) + (rec \\ (-3/2)) = rec)] conformTo: #'number' selector: #'\\' ruleReceiver: rec operand: (-3/2). ]. self should: [(53/2) \\ (3/2) = 1 & (((53/2) // (3/2)) * (3/2) + ((53/2) \\ (3/2)) = (53/2))]. self should: [(53/2) \\ (-3/2) = (-1/2) & (((53/2) // (-3/2)) * (-3/2) + ((53/2) \\ (-3/2)) = (53/2))]. self should: [0 \\ fractionHalf = 0]. "If the operand is zero, the ZeroDivide must be signaled." self value: [fractionHalf \\ 0] shouldRaise: ZeroDivide.! testXraisedToX " #raisedTo: " | numVals retVals | #'Numeric'. numVals := #(2 2.0 0 2.0s3 ) copy. numVals at: 3 put: (1/2). retVals := #(0 0.25 0.7071067811865475 0.25 ) copy. retVals at: 1 put: (1/4). 1 to: numVals size do: [ :ndx | self value: [fractionHalf raisedTo: (numVals at: ndx)] should: [:r | r closeTo: (retVals at: ndx)] conformTo: #'number' selector: #'raisedTo:'. ]. retVals := #(4 4.0 1.414213562373095 4.0 ). 1 to: numVals size do: [ :ndx | self value: [fractionHalf raisedTo: ((numVals at: ndx) negated)] should: [:r | r closeTo: (retVals at: ndx)] conformTo: #'number' selector: #'raisedTo:' ]. self value: [fractionHalf raisedTo: 0.0] should: [:r | r = 1] conformTo: #'number' selector: #'raisedTo:'. self value: [0.0 raisedTo: fractionHalf] should: [:r | r = 0.0] conformTo: #'number' selector: #'raisedTo:'. self value: [fractionHalf raisedTo: 1.0] should: [:r | r = fractionHalf] conformTo: #'number' selector: #'raisedTo:'. "It is erroneous if the receiver equals zero and the operand is less than or equal to zero," self value: [0.0 raisedTo: (fractionHalf negated)] shouldRaise: Error. " or if the receiver is less than zero." self value: [fractionHalf negated raisedTo: 2.0] shouldRaise: Error.! testXceiling " #ceiling " #'Numeric'. self value: [(1/3) ceiling] should: [:r | r = 1] conformTo: #'number' selector: #'ceiling'. self value: [(1/2) ceiling] should: [:r | r = 1] conformTo: #'number' selector: #'ceiling'. self value: [(-1/2) ceiling] should: [:r | r = 0] conformTo: #'number' selector: #'ceiling'.! testXreciprocal " #reciprocal (returnRule - :receiver) " #'Numeric'. self value: [fractionHalf reciprocal] should: [:r | r = 2] conformTo: #'number' selector: #'reciprocal' ruleReceiver: fractionHalf! testXaddOp " #+ (returnRule - :receiver :operand) " | retVals | #'Numeric'. " #( 2 -2000000000 2000000000 2.0 1/2 2.0s3 )." retVals := Array new: 6. retVals at: 1 put: (5/2). retVals at: 2 put: (-3999999999/2). retVals at: 3 put: (4000000001/2). retVals at: 4 put: 2.5. retVals at: 5 put: 1. retVals at: 6 put: (5/2). 1 to: numList size do: [ :ndx | self value: [fractionHalf + (numList at: ndx)] should: [:r | r closeTo: (retVals at: ndx)] conformTo: #'number' selector: #'+' ruleReceiver: fractionHalf operand: (numList at: ndx) ].! testXidentityHash " #identityHash " #'Numeric'. self value: [fractionHalf identityHash] should: [:r | r = fractionHalf identityHash] conformTo: #'Object' selector: #'identityHash'. self value: [smallInt2 identityHash] should: [:r | r = (4/2) identityHash] conformTo: #'Object' selector: #'identityHash'. self value: [fractionHalf identityHash] shouldnt: [:r | r = (2/3) identityHash] conformTo: #'Object' selector: #'identityHash'. self value: [smallInt2 identityHash] shouldnt: [:r | r = (6/2) identityHash] conformTo: #'Object' selector: #'identityHash'.! testXintegerDivideOp " #// " | retVals | #'Numeric'. " #( 2 -2000000000 2000000000 2.0 1/2 2.0s3 )." "The sign of the result is positive if the receiver and operand have the same sign, and negative if the signs are different." retVals := #(666666666 -1 0 666666666 2666666666 666666666 ). 1 to: numList size do: [ :ndx | self value: [(4000000000/3) // (numList at: ndx)] should: [:r | r = (retVals at: ndx)] conformTo: #'number' selector: #'//'. ]. " #( 2 -2000000000 2000000000 2.0 1/2 2.0s3 )." retVals := #( -666666667 0 -1 -666666667 -2666666667 -666666667 ). 1 to: numList size do: [ :ndx | self value: [(4000000000/3) // ((numList at: ndx) negated)] should: [:r | r = (retVals at: ndx)] conformTo: #'number' selector: #'//' ]. self should: [(256/5) // (50/5) = 5]. self should: [(126/5) // 5 = 5]. self should: [(125000000001/5) // 5000000000 = 5]. self should: [(-125000000001/5) // -5000000000 = 5]. self should: [(131/5) // 5.1 = 5]. self should: [(131/5) // 5.1s1 = 5]. self value: [0 // fractionHalf] should: [:r | r = 0] conformTo: #'number' selector: #'//'. "If the operand has a value of zero the ZeroDivide exception is signaled." self value: [fractionHalf // 0] shouldRaise: ZeroDivide.! testXpositive " #positive " #'Numeric'. self value: [(1/2) positive] should: [:r | r] conformTo: #'number' selector: #'positive'. self value: [(-1/2) positive] shouldnt: [:r | r] conformTo: #'number' selector: #'positive'.! testXgreaterThanOrEqualToOp " #>= " #'Numeric'. " #( 2 -2000000000 2000000000 2.0 1/2 2.0s3 )." #'todo'."It is erroneous if the receiver and operand are not comparable." "Small >= Big -> false" #( 2 2000000000 2.0 2.0s3 ) do: [ :tstNum | self value: [(1/3) >= tstNum] shouldnt: [:r | r] conformTo: #'magnitude' selector: #'>=' ]. self value: [(-9000000005/3) >= -2000000000] shouldnt: [:r | r] conformTo: #'magnitude' selector: #'>='. self value: [(1/4) >= (1/2)] shouldnt: [:r | r] conformTo: #'magnitude' selector: #'>='. "Num >= Num -> true" 1 to: numList size do: [ :ndx | self value: [(numList at: ndx) >= (numList at: ndx)] should: [:r | r ] conformTo: #'magnitude' selector: #'>=' ]. "Big >= Small -> true" #( 2 2.0 2.0s3 ) do: [ :tstNum | self value: [(11/2) >= tstNum] should: [:r | r] conformTo: #'magnitude' selector: #'>=' ]. self value: [(9000000005/3) >= 2000000000] should: [:r | r] conformTo: #'magnitude' selector: #'>='. self value: [(-1000000005/3) >= -2000000000] should: [:r | r] conformTo: #'magnitude' selector: #'>='. self value: [(11/2) >= (1/2)] should: [:r | r] conformTo: #'magnitude' selector: #'>='.! testXtoX " #to: " | start middleNdx stop2 | #'Numeric'. start := (1/2). numList := #( 2 2.0 0 2.0s3 ) copy. numList at: 3 put: (3/2). numList do: [ :stop | self value: [start to: stop] should: [:r | (r size = 2) ". . . the last element in the sequence . . . is . . .[:] receiver + ((stop - receiver) // 1)" & (r last = (start + ((stop - start) // 1))) "The elements conform to the receiver's protocol." & (r allSatisfy: [ :elem | elem class conformsToProtocolNamed: #'Fraction']) ] conformTo: #'number' selector: #'to:' ]. start := (3/2). stop2 := (4000000001/2). middleNdx := 1000000000. "Check conformance of first, middle and last." self value: [start to: stop2] should: [:r | (r size = 2000000000) ". . . the last element in the sequence . . . is . . .[:] receiver + ((stop - receiver) // 1)" & (r last = (start + ((stop2 - start) // 1))) "The elements conform to the receiver's protocol." & ((Array with: (r at: 1) with: (r at: middleNdx) with: (r at: 3) ) allSatisfy: [ :elem | elem class conformsToProtocolNamed: #'Fraction']) ] conformTo: #'number' selector: #'to:'. start := (-4000000001/2). stop2 := (-3/2). middleNdx := 1000000000. "Check conformance of first, middle and last." self value: [start to: stop2] should: [:r | (r size = 2000000000) ". . . the last element in the sequence . . . is . . .[:] receiver + ((stop - receiver) // 1)" & (r last = (start + ((stop2 - start) // 1))) "The elements conform to the receiver's protocol." & ((Array with: (r at: 1) with: (r at: middleNdx) with: (r at: 3) ) allSatisfy: [ :elem | elem class conformsToProtocolNamed: #'Fraction']) ] conformTo: #'number' selector: #'to:'. "The interval answered will be empty if the receiver is greater than stop." self value: [(1/2) to: (-1/2)] should: [:r | (r isEmpty)] conformTo: #'number' selector: #'to:'! canonicalObject ^1/3! testXasFloatE " #asFloatE " #'Numeric'. self value: [(1/2) asFloatE] should: [:r | r = 0.5] conformTo: #'number' selector: #'asFloatE'. self value: [(-1/2) asFloatE] should: [:r | r = -0.5] conformTo: #'number' selector: #'asFloatE'.! testXgreaterThanOp " #> " #'Numeric'. " #( 2 -2000000000 2000000000 2.0 1/2 2.0s3 )." #'todo'."It is erroneous if the receiver and operand are not comparable." "Small > Big -> false" #( 2 2000000000 2.0 2.0s3 ) do: [ :tstNum | self value: [(1/3) > tstNum] shouldnt: [:r | r] conformTo: #'number' selector: #'>' ]. self value: [(-9000000005/3) > -2000000000] shouldnt: [:r | r] conformTo: #'number' selector: #'>'. self value: [(1/4) > (1/2)] shouldnt: [:r | r] conformTo: #'number' selector: #'>'. "Num > Num -> false" 1 to: numList size do: [ :ndx | self value: [(numList at: ndx) > (numList at: ndx)] shouldnt: [:r | r ] conformTo: #'number' selector: #'>' ]. "Big > Small -> true" #( 2 2.0 2.0s3 ) do: [ :tstNum | self value: [(11/2) > tstNum] should: [:r | r] conformTo: #'number' selector: #'>' ]. self value: [(9000000005/3) > 2000000000] should: [:r | r] conformTo: #'number' selector: #'>'. self value: [(-1000000005/3) > -2000000000] should: [:r | r] conformTo: #'number' selector: #'>'. self value: [(11/2) > (1/2)] should: [:r | r] conformTo: #'number' selector: #'>'.! testXdivideOp " #/ (returnRule - :receiver :operand) " | retVals | #'Numeric'. " #( 2 -2000000000 2000000000 2.0 1/2 2.0s3 )." retVals := Array new: 6. retVals at: 1 put: (1/4). retVals at: 2 put: (-1/4000000000). retVals at: 3 put: (1/4000000000). retVals at: 4 put: 0.25. retVals at: 5 put: 1. retVals at: 6 put: (1/4). 1 to: numList size do: [ :ndx | self value: [fractionHalf / (numList at: ndx)] should: [:r | r = (retVals at: ndx)] conformTo: #'number' selector: #'/' ruleReceiver: fractionHalf operand: (numList at: ndx) ]. self value: [0 / fractionHalf] should: [:r | r = 0] conformTo: #'number' selector: #'/' ruleReceiver: fractionHalf operand: 0. "The implementation must signal the ZeroDivide exception." self value: [fractionHalf / 0] shouldRaise: ZeroDivide.! testXprintString " #printString " #'Numeric'. self value: [(1/2) printString] should: [:r | r = '1/2'] conformTo: #'Fraction' selector: #'printString'. self value: [(1/ -2) printString] should: [:r | r = '-1/2'] conformTo: #'Fraction' selector: #'printString'. self value: [(3/33) printString] should: [:r | r = '1/11'] conformTo: #'Fraction' selector: #'printString'.! testXfloor " #floor " #'Numeric'. self value: [(1/3) floor] should: [:r | r = 0] conformTo: #'number' selector: #'floor'. self value: [(1/2) floor] should: [:r | r = 0] conformTo: #'number' selector: #'floor'. self value: [(3/2) floor] should: [:r | r = 1] conformTo: #'number' selector: #'floor'. self value: [(-1/2) floor] should: [:r | r = -1] conformTo: #'number' selector: #'floor'.! testXtoXdoX " #to:do: " #'Numeric'.! setUp super setUp. smallInt2 := 2. largeNegInt2000000000 := -2000000000. largePosInt2000000000 := 2000000000. float2 := 2.0d0. fractionHalf := 1/2. sclDec2s3 := 2.0s3. numList := Array new: 6. numList at: 1 put: smallInt2. numList at: 2 put: largeNegInt2000000000. numList at: 3 put: largePosInt2000000000. numList at: 4 put: float2. numList at: 5 put: fractionHalf. numList at: 6 put: sclDec2s3.! testXsign " #sign " #'Numeric'. self value: [(1/2) sign] should: [:r | r = 1] conformTo: #'number' selector: #'sign'. self value: [(-1/2) sign] should: [:r | r = -1] conformTo: #'number' selector: #'sign'.! testXminX " #min: " #'Numeric'. " #( 2 -2000000000 2000000000 2.0 1/2 2.0s3 )." #'todo'."It is erroneous if the receiver and operand are not comparable." self value: [(1/2) min: 0] should: [:r | r = 0] conformTo: #'magnitude' selector: #'min:'. self value: [(-2000000000/2) min: -2000000000] should: [:r | r = -2000000000] conformTo: #'magnitude' selector: #'min:'. self value: [(9000000000/2) min: 2000000003] should: [:r | r = 2000000003] conformTo: #'magnitude' selector: #'min:'. self value: [(1/2) min: 0.0] should: [:r | r = 0.0] conformTo: #'magnitude' selector: #'min:'. self value: [(1/2) min: (1/4)] should: [:r | r = (1/4)] conformTo: #'magnitude' selector: #'min:'. self value: [(1/2) min: 0.1s3] should: [:r | r = 0.1s3] conformTo: #'magnitude' selector: #'min:'. "Num min: Num -> Num" 1 to: numList size do: [ :ndx | self value: [(numList at: ndx) min: (numList at: ndx)] should: [:r | r = (numList at: ndx)] conformTo: #'magnitude' selector: #'min:' ].! testXrounded " #rounded " #'Numeric'. self value: [(1/3) rounded] should: [:r | r = 0] conformTo: #'number' selector: #'rounded'. self value: [(1/2) rounded] should: [:r | r = 1] conformTo: #'number' selector: #'rounded'. self value: [(-1/2) rounded] should: [:r | r = -1] conformTo: #'number' selector: #'rounded'.! testXtruncateToX " #truncateTo: (returnRule - :receiver :operand) " | retVals frac | #'Numeric'. " #( 2 -2000000000 2000000000 2.0 1/2 2.0s3 )." frac := (51/10). retVals := #(4 0 0 4.0 5 4). 1 to: numList size do: [ :ndx | self value: [frac truncateTo: (numList at: ndx)] should: [:r | r = (retVals at: ndx)] conformTo: #'number' selector: #'truncateTo:' ruleReceiver: frac operand: (numList at: ndx) ]. self should: [(0.0 truncateTo: fractionHalf) = 0.0].! testXfractionPart " #fractionPart (Return Values: )" | rcvr | #'Numeric'. "Within the limits of representation, the following invariants should hold: receiver integerPart + receiver fractionPart = receiver receiver \\1 = receiver fractionPart (RAH - erroneous, add #'abs') " rcvr := (3/2). self value: [rcvr fractionPart] should: [:r | r = (1/2) & (rcvr integerPart + rcvr fractionPart = rcvr) & (rcvr \\ 1 = rcvr fractionPart abs)] conformTo: #'number' selector: #'fractionPart' opRECEIVER: rcvr. rcvr := (-3/2). self value: [rcvr fractionPart] should: [:r | r = (-1/2) & (rcvr integerPart + rcvr fractionPart = rcvr) & (rcvr \\ 1 = rcvr fractionPart abs)] conformTo: #'number' selector: #'fractionPart' opRECEIVER: rcvr.! testXnegative " #negative " #'Numeric'. self value: [(-1/2) negative] should: [:r | r] conformTo: #'number' selector: #'negative'. self value: [(1/2) negative] shouldnt: [:r | r] conformTo: #'number' selector: #'negative'.! testXsubtractOp " #- (returnRule - :receiver :operand) " | retVals | #'Numeric'. " #( 2 -2000000000 2000000000 2.0 1/2 2.0s3 )." retVals := Array new: 6. retVals at: 1 put: (-3/2). retVals at: 2 put: (4000000001/2). retVals at: 3 put: (-3999999999/2). retVals at: 4 put: -1.5. retVals at: 5 put: 0. retVals at: 6 put: (-3/2). 1 to: numList size do: [ :ndx | self value: [fractionHalf - (numList at: ndx)] should: [:r | r closeTo: (retVals at: ndx)] conformTo: #'number' selector: #'-' ruleReceiver: fractionHalf operand: (numList at: ndx) ].! testXcopy " #copy (Return Values: ) " #'Numeric'. " Return a new object that must be as similar as possible to the receiver in its initial state and behavior. Any operation that changes the state of the new object should not as a side-effect change the state or behavior of the receiver. Similarly, any change to the receiver should not as a side-effect change the new object. If the receiver is an identity object, return the receiver. " #todo. "??? add change-side-effect test ???" self value: [fractionHalf copy] should: [:r | (r = fractionHalf) ] conformTo: #'Object' selector: #'copy' opRECEIVER: fractionHalf.! testXhash " #hash " #'Numeric'. " Any two objects that are considered equivalent using the #= message must have the same hash value. More formally: receiver = comparand => receiver hash = comparand hash " #'testAnom'. "??? test of equivalence seems to confilict with convert then test. self shouldnt: [smallInt2 = float2]. self shouldnt: [smallInt2 hash = float2 hash]. ???" self value: [fractionHalf hash] should: [:r | r = fractionHalf hash] conformTo: #'Object' selector: #'hash'. self value: [fractionHalf hash] shouldnt: [:r | r = (2/3) hash] conformTo: #'Object' selector: #'hash'.! protocol ^#'Fraction'! testXasFloatD " #asFloatD " #'Numeric'. self value: [(1/2) asFloatD] should: [:r | r = 0.5] conformTo: #'number' selector: #'asFloatD'. self value: [(-1/2) asFloatD] should: [:r | r = -0.5] conformTo: #'number' selector: #'asFloatD'.! testXlessThanOrEqualToOp " #<= " #'Numeric'. " #( 2 -2000000000 2000000000 2.0 1/2 2.0s3 )." #'todo'."It is erroneous if the receiver and operand are not comparable." "Small <= Big -> true" #( 2 2000000000 2.0 2.0s3 ) do: [ :tstNum | self value: [(1/3) <= tstNum] should: [:r | r] conformTo: #'magnitude' selector: #'<=' ]. self value: [(-9000000005/3) <= -2000000000] should: [:r | r] conformTo: #'magnitude' selector: #'<='. self value: [(1/4) <= (1/2)] should: [:r | r] conformTo: #'magnitude' selector: #'<='. "Num <= Num -> false" 1 to: numList size do: [ :ndx | self value: [(numList at: ndx) <= (numList at: ndx)] should: [:r | r ] conformTo: #'magnitude' selector: #'<=' ]. "Big <= Small -> false" #( 2 2.0 2.0s3 ) do: [ :tstNum | self value: [(11/2) <= tstNum] shouldnt: [:r | r] conformTo: #'magnitude' selector: #'<=' ]. self value: [(9000000005/3) <= 2000000000] shouldnt: [:r | r] conformTo: #'magnitude' selector: #'<='. self value: [(-1000000005/3) <= -2000000000] shouldnt: [:r | r] conformTo: #'magnitude' selector: #'<='. self value: [(11/2) <= (1/2)] shouldnt: [:r | r] conformTo: #'magnitude' selector: #'<='.! testXintegerPart " #integerPart (returnRule - :receiver) " | rcvr | #'Numeric'. rcvr := (1/2). self value: [rcvr integerPart] should: [:result | result = 0] conformTo: #'number' selector: #'integerPart' ruleReceiver: rcvr. rcvr := (3/2). self value: [rcvr integerPart] should: [:result | result = 1] conformTo: #'number' selector: #'integerPart' ruleReceiver: rcvr. rcvr := (-3/2). self value: [rcvr integerPart] should: [:result | result = -1] conformTo: #'number' selector: #'integerPart' ruleReceiver: rcvr.! testXquoX " #quo: " | retVals | #'Numeric'. " #( 2 -2000000000 2000000000 2.0 1/2 2.0s3 )." retVals := #( 666666666 0 0 666666666 2666666666 666666666 ). 1 to: numList size do: [ :ndx | self value: [(4000000000/3) quo: (numList at: ndx)] should: [:r | r = (retVals at: ndx)] conformTo: #'number' selector: #'quo:'. ]. " #( 2 -2000000000 2000000000 2.0 1/2 2.0s3 )." retVals := #( -666666666 0 0 -666666666 -2666666666 -666666666 ). 1 to: numList size do: [ :ndx | self value: [(4000000000/3) quo: ((numList at: ndx) negated)] should: [:r | r = (retVals at: ndx)] conformTo: #'number' selector: #'quo:' ]. self should: [((256/5) quo: (50/5)) = 5]. self should: [((126/5) quo: 5) = 5]. self should: [((125000000001/5) quo: 5000000000) = 5]. self should: [((-125000000001/5) quo: -5000000000) = 5]. self should: [((131/5) quo: 5.1) = 5]. self should: [((131/5) quo: 5.1s1) = 5]. self value: [0 quo: fractionHalf] should: [:r | r = 0] conformTo: #'number' selector: #'quo:'. "If the operand has a value of zero the ZeroDivide exception is signaled." self value: [fractionHalf quo: 0] shouldRaise: ZeroDivide.! testXasFloatQ " #asFloatQ " #'Numeric'. self value: [(1/2) asFloatQ] should: [:r | r = 0.5] conformTo: #'number' selector: #'asFloatQ'. self value: [(-1/2) asFloatQ] should: [:r | r = -0.5] conformTo: #'number' selector: #'asFloatQ'.! testXmultiplyOp " #* (returnRule - :receiver :operand) " | retVals | #'Numeric'. " #( 2 -2000000000 2000000000 2.0 1/2 2.0s3 )." retVals := #(1 -1000000000 1000000000 1.0 0 1) copy. retVals at: 5 put: (1/4). 1 to: numList size do: [ :ndx | self value: [fractionHalf * (numList at: ndx)] should: [:r | r = (retVals at: ndx)] conformTo: #'number' selector: #'*' ruleReceiver: fractionHalf operand: (numList at: ndx) ].! testXnumerator " #numerator " #'Numeric'.! testXlessThanOp " #< " #'Numeric'. " #( 2 -2000000000 2000000000 2.0 1/2 2.0s3 )." #'todo'."It is erroneous if the receiver and operand are not comparable." "Small < Big -> true" #( 2 2000000000 2.0 2.0s3 ) do: [ :tstNum | self value: [(1/3) < tstNum] should: [:r | r] conformTo: #'number' selector: #'<' ]. self value: [(-9000000005/3) < -2000000000] should: [:r | r] conformTo: #'number' selector: #'<'. self value: [(1/4) < (1/2)] should: [:r | r] conformTo: #'number' selector: #'<'. "Num < Num -> false" 1 to: numList size do: [ :ndx | self value: [(numList at: ndx) < (numList at: ndx)] shouldnt: [:r | r ] conformTo: #'number' selector: #'<' ]. "Big < Small -> false" #( 2 2.0 2.0s3 ) do: [ :tstNum | self value: [(11/2) < tstNum] shouldnt: [:r | r] conformTo: #'number' selector: #'<' ]. self value: [(9000000005/3) < 2000000000] shouldnt: [:r | r] conformTo: #'number' selector: #'<'. self value: [(-1000000005/3) < -2000000000] shouldnt: [:r | r] conformTo: #'number' selector: #'<'. self value: [(11/2) < (1/2)] shouldnt: [:r | r] conformTo: #'number' selector: #'<'.! testXsqrt " #sqrt " self value: [(2601/100) sqrt] should: [:r | r closeTo: 5.1] conformTo: #'number' selector: #'sqrt'. self value: [(1/4) sqrt] should: [:r | r = 0.5] conformTo: #'number' selector: #'sqrt'! ! !IdentityDictionaryFactoryANSITest methodsFor: nil! protocol ^#'IdentityDictionary factory'! testXwithAllX " #withAll: " #'Collection'.! testXnewX " #new: " #'Collection'.! canonicalObject ^IdentityDictionary! testXnew " #new " #'Collection'.! ! !WarningANSITest methodsFor: nil! testXresignalAsX " #resignalAs: " #'Exception'.! testXretryUsingX " #retryUsing: " #'Exception'.! testXmessageText " #messageText " #'Exception'.! testXresume " #resume " #'Exception'.! testXreturn " #return " #'Exception'.! testXresumeX " #resume: " #'Exception'.! testXreturnX " #return: " #'Exception'.! protocol ^#Warning! testXsignal " #signal " #'Exception'.! testXdescription " #description " #'Exception'.! testXsignalX " #signal: " #'Exception'.! testXtag " #tag " #'Exception'.! testXmessageTextX " #messageText: (Return Values: ) " #'Exception'.! testXouter " #outer " #'Exception'.! testXpass " #pass " #'Exception'.! testXretry " #retry " #'Exception'.! testXisResumable " #isResumable " #'Exception'.! testXisNested " #isNested " #'Exception'.! canonicalObject ^Warning new! testXdefaultAction " #defaultAction " | tmp theText | #'Exception'. theText := 'the text'. self value: [[ Warning signal: 'the text' ] on: Warning do: [ :aWarning | tmp := aWarning messageText ]] should: [:r | true "UNSPECIFIED" & tmp = theText] conformTo: #'Warning' selector: #'defaultAction'.! ! !FileStreamFactoryANSITest methodsFor: nil! testXreadX " #read: " #'File Stream'.! testXwriteXmodeX " #write:mode: " #'File Stream'.! protocol ^#'FileStream factory'! testXwriteX " #write: " #'File Stream'.! testXwriteXmodeXcheckXtypeX " #write:mode:check:type: " #'File Stream'.! canonicalObject ^FileStream! testXreadXtypeX " #read:type: " #'File Stream'.! ! !IntegerANSITest methodsFor: nil! testXbitXorX " #bitXor: " #'Numeric'.! testXpositive " #positive " #'Numeric'. self value: [2 positive] should: [:r | r] conformTo: #'number' selector: #'positive'. self value: [2000000000 positive] should: [:r | r] conformTo: #'number' selector: #'positive'. self value: [0 positive] should: [:r | r] conformTo: #'number' selector: #'positive'. self value: [-2 positive] shouldnt: [:r | r] conformTo: #'number' selector: #'positive'. self value: [-2000000000 positive] shouldnt: [:r | r] conformTo: #'number' selector: #'positive'.! testXidentityHash " #identityHash " #'Numeric'. self value: [smallInt2 identityHash] should: [:r | r = smallInt2 identityHash] conformTo: #'Object' selector: #'identityHash'. self value: [largeNegInt2000000000 identityHash] should: [:r | r = largeNegInt2000000000 identityHash] conformTo: #'Object' selector: #'identityHash'. self value: [largePosInt2000000000 identityHash] should: [:r | r = largePosInt2000000000 identityHash] conformTo: #'Object' selector: #'identityHash'. self value: [smallInt2 identityHash] should: [:r | r = (4/2) identityHash] conformTo: #'Object' selector: #'identityHash'. self value: [smallInt2 identityHash] should: [:r | r = (3 - 1) identityHash] conformTo: #'Object' selector: #'identityHash'. self value: [smallInt2 identityHash] shouldnt: [:r | r = 3 identityHash] conformTo: #'Object' selector: #'identityHash'. self value: [largeNegInt2000000000 identityHash] shouldnt: [:r | r = 2000000001 identityHash] conformTo: #'Object' selector: #'identityHash'. self value: [largePosInt2000000000 identityHash] shouldnt: [:r | r = 2000000001 identityHash] conformTo: #'Object' selector: #'identityHash'. self value: [smallInt2 identityHash] shouldnt: [:r | r = (6/2) identityHash] conformTo: #'Object' selector: #'identityHash'. self value: [smallInt2 identityHash] shouldnt: [:r | r = (2 + 1) identityHash] conformTo: #'Object' selector: #'identityHash'. self shouldnt: [smallInt2 identityHash = float2 identityHash].! testXlessThanOrEqualToOp " #<= " #'Numeric'. " #( 2 -2000000000 2000000000 2.0 1/2 2.0s3 )." #'todo'."It is erroneous if the receiver and operand are not comparable." "Small <= Big -> true" #( 2 2000000000 2.0 2.0s3 ) do: [ :tstNum | self value: [1 <= tstNum] should: [:r | r] conformTo: #'magnitude' selector: #'<=' ]. self value: [-2000000005 <= -2000000000] should: [:r | r] conformTo: #'magnitude' selector: #'<='. self value: [0 <= (1/2)] should: [:r | r] conformTo: #'magnitude' selector: #'<='. "Num <= Num -> false" 1 to: numList size do: [ :ndx | self value: [(numList at: ndx) <= (numList at: ndx)] should: [:r | r ] conformTo: #'magnitude' selector: #'<=' ]. "Big <= Small -> false" #( 2 2.0 2.0s3 ) do: [ :tstNum | self value: [5 <= tstNum] shouldnt: [:r | r] conformTo: #'magnitude' selector: #'<=' ]. self value: [9000000000 <= 2000000000] shouldnt: [:r | r] conformTo: #'magnitude' selector: #'<='. self value: [-1000000005 <= -2000000000] shouldnt: [:r | r] conformTo: #'magnitude' selector: #'<='. self value: [9 <= (1/2)] shouldnt: [:r | r] conformTo: #'magnitude' selector: #'<='.! setUp super setUp. smallInt2 := 2. largeNegInt2000000000 := -2000000000. largePosInt2000000000 := 2000000000. float2 := 2.0d0. fractionHalf := 1/2. sclDec2s3 := 2.0s3. numList := Array new: 6. numList at: 1 put: smallInt2. numList at: 2 put: largeNegInt2000000000. numList at: 3 put: largePosInt2000000000. numList at: 4 put: float2. numList at: 5 put: fractionHalf. numList at: 6 put: sclDec2s3.! testXabs " #abs (Return Values: ) " | rcvr | #'Numeric'. rcvr := 2. self value: [rcvr abs] should: [:r | r = 2] conformTo: #'number' selector: #'abs' opRECEIVER: rcvr. rcvr := -2. self value: [rcvr abs] should: [:r | r = 2] conformTo: #'number' selector: #'abs' opRECEIVER: rcvr. rcvr := -2000000000. self value: [rcvr abs] should: [:r | r = 2000000000] conformTo: #'number' selector: #'abs' opRECEIVER: rcvr. rcvr := 2000000000. self value: [rcvr abs] should: [:r | r = 2000000000] conformTo: #'number' selector: #'abs' opRECEIVER: rcvr. rcvr := 0. self value: [rcvr abs] should: [:r | r = 0] conformTo: #'number' selector: #'abs' opRECEIVER: rcvr.! testXstrictlyPositive " #strictlyPositive " #'Numeric'. self value: [2 strictlyPositive] should: [:r | r] conformTo: #'number' selector: #'strictlyPositive'. self value: [2000000000 strictlyPositive] should: [:r | r] conformTo: #'number' selector: #'strictlyPositive'. self value: [0 strictlyPositive] shouldnt: [:r | r] conformTo: #'number' selector: #'strictlyPositive'. self value: [-2 strictlyPositive] shouldnt: [:r | r] conformTo: #'number' selector: #'strictlyPositive'. self value: [-2000000000 strictlyPositive] shouldnt: [:r | r] conformTo: #'number' selector: #'strictlyPositive'.! testXraisedToIntegerX " #raisedToInteger: (Return Values: )" | rcvr | #'Numeric'. rcvr := 2. self value: [rcvr raisedToInteger: 0] should: [:r | r = 1] conformTo: #'number' selector: #'raisedToInteger:' opRECEIVER: rcvr. self value: [rcvr raisedToInteger: 1] should: [:r | r = rcvr] conformTo: #'number' selector: #'raisedToInteger:' opRECEIVER: rcvr. self value: [rcvr raisedToInteger: 2] should: [:r | r = 4] conformTo: #'number' selector: #'raisedToInteger:' opRECEIVER: rcvr. self value: [rcvr negated raisedToInteger: 2] should: [:r | r = 4] conformTo: #'number' selector: #'raisedToInteger:' opRECEIVER: rcvr. self value: [rcvr raisedToInteger: -2] should: [:r | r = (1/4)] conformTo: #'number' selector: #'raisedToInteger:' opRECEIVER: rcvr. #'todo'."??? these take 5-10 min. self value: [rcvr raisedToInteger: 2000000000] should: [:r | r = ???] conformTo: #'number' selector: #'raisedToInteger:' opRECEIVER: rcvr. self value: [rcvr raisedToInteger: -2000000000] should: [:r | r = ???] conformTo: #'number' selector: #'raisedToInteger:' opRECEIVER: rcvr. " rcvr := 2000000000. self value: [rcvr raisedToInteger: 2] should: [:r | r = 4000000000000000000] conformTo: #'number' selector: #'raisedToInteger:' opRECEIVER: rcvr. rcvr := -2000000000. self value: [rcvr raisedToInteger: 2] should: [:r | r = 4000000000000000000] conformTo: #'number' selector: #'raisedToInteger:' opRECEIVER: rcvr. "It is erroneous if the operand does not conform to the protocol ." self value: [2 raisedToInteger: 2.0] shouldRaise: Error. self value: [0 raisedToInteger: -2] shouldRaise: ZeroDivide.! testXaddOp " #+ (returnRule - :receiver :operand) " | retVals | #'Numeric'. " #( 2 -2000000000 2000000000 2.0 1/2 2.0s3 )." retVals := #(4 -1999999998 2000000002 4.0s3 0 4.0) copy. retVals at: 5 put: (5/2). 1 to: numList size do: [ :ndx | self value: [smallInt2 + (numList at: ndx)] should: [:r | r closeTo: (retVals at: ndx)] conformTo: #'number' selector: #'+' ruleReceiver: smallInt2 operand: (numList at: ndx) ]. retVals := #(-1999999998 -4000000000 0 -1999999998.0s3 0 -1999999998.0) copy. retVals at: 5 put: (-3999999999/2). 1 to: numList size do: [ :ndx | self value: [largeNegInt2000000000 + (numList at: ndx)] should: [:r | r closeTo: (retVals at: ndx)] conformTo: #'number' selector: #'+' ruleReceiver: largeNegInt2000000000 operand: (numList at: ndx) ]. retVals := #(2000000002 0 4000000000 2000000002.0s3 0 2000000002.0) copy. retVals at: 5 put: (4000000001/2). 1 to: numList size do: [ :ndx | self value: [largePosInt2000000000 + (numList at: ndx)] should: [:r | r closeTo: (retVals at: ndx)] conformTo: #'number' selector: #'+' ruleReceiver: largePosInt2000000000 operand: (numList at: ndx) ].! testXgreaterThanOp " #> " #'Numeric'. " #( 2 -2000000000 2000000000 2.0 1/2 2.0s3 )." #'todo'."It is erroneous if the receiver and operand are not comparable." "Small > Big -> false" #( 2 2000000000 2.0 2.0s3 ) do: [ :tstNum | self value: [1 > tstNum] shouldnt: [:r | r] conformTo: #'number' selector: #'>' ]. self value: [-2000000005 > -2000000000] shouldnt: [:r | r] conformTo: #'number' selector: #'>'. self value: [0 > (1/2)] shouldnt: [:r | r] conformTo: #'number' selector: #'>'. "Num > Num -> false" 1 to: numList size do: [ :ndx | self value: [(numList at: ndx) > (numList at: ndx)] shouldnt: [:r | r ] conformTo: #'number' selector: #'>' ]. "Big > Small -> true" #( 2 2.0 2.0s3 ) do: [ :tstNum | self value: [5 > tstNum] should: [:r | r] conformTo: #'number' selector: #'>' ]. self value: [9000000000 > 2000000000] should: [:r | r] conformTo: #'number' selector: #'>'. self value: [-1000000005 > -2000000000] should: [:r | r] conformTo: #'number' selector: #'>'. self value: [9 > (1/2)] should: [:r | r] conformTo: #'number' selector: #'>'.! testXnotIdentityOp " #~~ " #'Numeric'. " The value of receiver ~~ comparand is true if and only if the value of comparand ~~ receiver would also be true. " self should: [smallInt2 ~~ float2 and: [float2 ~~ smallInt2]]. self value: [smallInt2 ~~ 3] should: [:r | r] conformTo: #'Object' selector: #'~~'. self value: [largeNegInt2000000000 ~~ 2000000001] should: [:r | r] conformTo: #'Object' selector: #'~~'. self value: [largePosInt2000000000 ~~ 2000000001] should: [:r | r] conformTo: #'Object' selector: #'~~'. self value: [smallInt2 ~~ (6/2)] should: [:r | r] conformTo: #'Object' selector: #'~~'. self value: [smallInt2 ~~ (2 + 1)] should: [:r | r] conformTo: #'Object' selector: #'~~'. self value: [smallInt2 ~~ smallInt2] shouldnt: [:r | r] conformTo: #'Object' selector: #'~~'. self value: [largeNegInt2000000000 ~~ largeNegInt2000000000] shouldnt: [:r | r] conformTo: #'Object' selector: #'~~'. self value: [largePosInt2000000000 ~~ largePosInt2000000000] shouldnt: [:r | r] conformTo: #'Object' selector: #'~~'. self value: [smallInt2 ~~ (4/2)] shouldnt: [:r | r] conformTo: #'Object' selector: #'~~'. self value: [smallInt2 ~~ (3 - 1)] shouldnt: [:r | r] conformTo: #'Object' selector: #'~~'.! testXtoX " #to: " | start middleNdx stop2 | #'Numeric'. start := 1. numList := #( 2 2.0 0 2.0s3 ) copy. numList at: 3 put: (5/2). numList do: [ :stop | self value: [start to: stop] should: [:r | (r size = 2) ". . . the last element in the sequence . . . is . . .[:] receiver + ((stop - receiver) // 1)" & (r last = (start + ((stop - start) // 1))) "The elements conform to the receiver's protocol." & (r allSatisfy: [ :elem | elem class conformsToProtocolNamed: #'integer']) ] conformTo: #'number' selector: #'to:' ]. stop2 := 2000000000. middleNdx := 1000000000. "Check conformance of first, middle and last." self value: [start to: stop2] should: [:r | (r size = 2000000000) ". . . the last element in the sequence . . . is . . .[:] receiver + ((stop - receiver) // 1)" & (r last = (start + ((stop2 - start) // 1))) "The elements conform to the receiver's protocol." & ((Array with: (r at: 1) with: (r at: middleNdx) with: (r at: 3) ) allSatisfy: [ :elem | elem class conformsToProtocolNamed: #'integer']) ] conformTo: #'number' selector: #'to:'. start := -2000000000. stop2 := -1. middleNdx := 1000000000. "Check conformance of first, middle and last." self value: [start to: stop2] should: [:r | (r size = 2000000000) ". . . the last element in the sequence . . . is . . .[:] receiver + ((stop - receiver) // 1)" & (r last = (start + ((stop2 - start) // 1))) "The elements conform to the receiver's protocol." & ((Array with: (r at: 1) with: (r at: middleNdx) with: (r at: 3) ) allSatisfy: [ :elem | elem class conformsToProtocolNamed: #'integer']) ] conformTo: #'number' selector: #'to:'. "The interval answered will be empty if the receiver is greater than stop." self value: [1 to: -1] should: [:r | (r isEmpty)] conformTo: #'number' selector: #'to:'! testXminX " #min: " #'Numeric'. " #( 2 -2000000000 2000000000 2.0 1/2 2.0s3 )." #'todo'."It is erroneous if the receiver and operand are not comparable." self value: [2 min: 1] should: [:r | r = 1] conformTo: #'magnitude' selector: #'min:'. self value: [-1000000000 min: -2000000000] should: [:r | r = -2000000000] conformTo: #'magnitude' selector: #'min:'. self value: [2000000003 min: 2000000001] should: [:r | r = 2000000001] conformTo: #'magnitude' selector: #'min:'. self value: [2 min: 1.0] should: [:r | r = 1.0] conformTo: #'magnitude' selector: #'min:'. self value: [2 min: (3/2)] should: [:r | r = (3/2)] conformTo: #'magnitude' selector: #'min:'. self value: [2 min: 1.0s5] should: [:r | r = 1.0s5] conformTo: #'magnitude' selector: #'min:'. "Num min: Num -> Num" 1 to: numList size do: [ :ndx | self value: [(numList at: ndx) min: (numList at: ndx)] should: [:r | r = (numList at: ndx)] conformTo: #'magnitude' selector: #'min:' ].! testXsign " #sign " #'Numeric'. self value: [2 sign] should: [:r | r = 1] conformTo: #'number' selector: #'sign'. self value: [2000000000 sign] should: [:r | r = 1] conformTo: #'number' selector: #'sign'. self value: [0 sign] should: [:r | r = 0] conformTo: #'number' selector: #'sign'. self value: [-2 sign] should: [:r | r = -1] conformTo: #'number' selector: #'sign'. self value: [-2000000000 sign] should: [:r | r = -1] conformTo: #'number' selector: #'sign'.! testXnotEqualityOp " #~= " #'Numeric'. " The value of receiver ~= comparand is true if and only if the value of comparand ~= receiver would also be true. " #'testAnom'. "??? test of equivalence seems to confilict with convert then test. ??? self should: [(smallInt2 ~= float2) & (float2 ~= smallInt2)]. " self value: [smallInt2 ~= 3] should: [:r | r] conformTo: #'Object' selector: #'~='. self value: [largeNegInt2000000000 ~= 2000000001] should: [:r | r] conformTo: #'Object' selector: #'~='. self value: [largePosInt2000000000 ~= 2000000001] should: [:r | r] conformTo: #'Object' selector: #'~='. self value: [smallInt2 ~= (6/2)] should: [:r | r] conformTo: #'Object' selector: #'~='. self value: [smallInt2 ~= (2 + 1)] should: [:r | r] conformTo: #'Object' selector: #'~='. self value: [smallInt2 ~= smallInt2] shouldnt: [:r | r] conformTo: #'Object' selector: #'~='. self value: [largeNegInt2000000000 ~= largeNegInt2000000000] shouldnt: [:r | r] conformTo: #'Object' selector: #'~='. self value: [largePosInt2000000000 ~= largePosInt2000000000] shouldnt: [:r | r] conformTo: #'Object' selector: #'~='. self value: [smallInt2 ~= (4/2)] shouldnt: [:r | r] conformTo: #'Object' selector: #'~='. self value: [smallInt2 ~= (3 - 1)] shouldnt: [:r | r] conformTo: #'Object' selector: #'~='.! testXtruncated " #truncated " self value: [2 truncated] should: [:r | r = 2] conformTo: #'number' selector: #'truncated'. self value: [-2 truncated] should: [:r | r = -2] conformTo: #'number' selector: #'truncated'. self value: [-2000000000 truncated] should: [:r | r = -2000000000] conformTo: #'number' selector: #'truncated'. self value: [2000000000 truncated] should: [:r | r = 2000000000] conformTo: #'number' selector: #'truncated'. self value: [0 truncated] should: [:r | r = 0] conformTo: #'number' selector: #'truncated'.! testXmaxX " #max: " #'Numeric'. " #( 2 -2000000000 2000000000 2.0 1/2 2.0s3 )." #'todo'."It is erroneous if the receiver and operand are not comparable." self value: [2 max: 3] should: [:r | r = 3] conformTo: #'magnitude' selector: #'max:'. self value: [-3000000000 max: -2000000000] should: [:r | r = -2000000000] conformTo: #'magnitude' selector: #'max:'. self value: [2000000000 max: 2000000003] should: [:r | r = 2000000003] conformTo: #'magnitude' selector: #'max:'. self value: [2 max: 3.0] should: [:r | r = 3.0] conformTo: #'magnitude' selector: #'max:'. self value: [2 max: (5/2)] should: [:r | r = (5/2)] conformTo: #'magnitude' selector: #'max:'. self value: [2 max: 3.0s3] should: [:r | r = 3.0s3] conformTo: #'magnitude' selector: #'max:'. "Num max: Num -> Num" 1 to: numList size do: [ :ndx | self value: [(numList at: ndx) max: (numList at: ndx)] should: [:r | r = (numList at: ndx)] conformTo: #'magnitude' selector: #'max:' ].! testXgcdX " #gcd: " #'Numeric'.! testXasFloat " #asFloat " #'Numeric'. self value: [2 asFloat] should: [:r | r = 2.0] conformTo: #'number' selector: #'asFloat'. self value: [-2 asFloat] should: [:r | r = -2.0] conformTo: #'number' selector: #'asFloat'. self value: [-2000000000 asFloat] should: [:r | r = -2000000000.0] conformTo: #'number' selector: #'asFloat'. self value: [2000000000 asFloat] should: [:r | r = 2000000000.0] conformTo: #'number' selector: #'asFloat'. self value: [0 asFloat] should: [:r | r = 0.0] conformTo: #'number' selector: #'asFloat'.! testXanyMaskX " #anyMask: " #'Numeric'.! testXbitOrX " #bitOr: " #'Numeric'.! testXsqrt " #sqrt " #'Numeric'. self value: [4 sqrt] should: [:r | r = 2.0] conformTo: #'number' selector: #'sqrt'. self value: [2000000000 sqrt] should: [:r | r closeTo: 44721.3595499958] conformTo: #'number' selector: #'sqrt'. self value: [0 sqrt] should: [:r | r = 0.0] conformTo: #'number' selector: #'sqrt'! testXasFloatD " #asFloatD " #'Numeric'. self value: [2 asFloatD] should: [:r | r = 2.0] conformTo: #'number' selector: #'asFloatD'. self value: [-2 asFloatD] should: [:r | r = -2.0] conformTo: #'number' selector: #'asFloatD'. self value: [-2000000000 asFloatD] should: [:r | r = -2000000000.0] conformTo: #'number' selector: #'asFloatD'. self value: [2000000000 asFloatD] should: [:r | r = 2000000000.0] conformTo: #'number' selector: #'asFloatD'. self value: [0 asFloatD] should: [:r | r = 0.0] conformTo: #'number' selector: #'asFloatD'.! testXeven " #even " #'Numeric'.! testXnumerator " #numerator " #'Numeric'.! testXasScaledDecimalX "2000/06/23 Harmon, R. Changed to fix illegal fixed point literals." "The number of significant digits of the answer is the same as the number of decimal digits in the receiver. The scale of the answer is 0." self value: [2 asScaledDecimal: 2] should: [:r | r = 2s & (r scale = 0)] conformTo: #'integer' selector: #'asScaledDecimal:'. self value: [-2 asScaledDecimal: 2] should: [:r | r = -2s & (r scale = 0)] conformTo: #'integer' selector: #'asScaledDecimal:'. self value: [-2000000000 asScaledDecimal: 2] should: [:r | r = -2000000000s & (r scale = 0)] conformTo: #'integer' selector: #'asScaledDecimal:'. self value: [2000000000 asScaledDecimal: 2] should: [:r | r = 2000000000s & (r scale = 0)] conformTo: #'integer' selector: #'asScaledDecimal:'. self value: [0 asScaledDecimal: 2] should: [:r | r = 0s & (r scale = 0)] conformTo: #'integer' selector: #'asScaledDecimal:'.! testXasFloatE " #asFloatE " #'Numeric'. self value: [2 asFloatE] should: [:r | r = 2.0] conformTo: #'number' selector: #'asFloatE'. self value: [-2 asFloatE] should: [:r | r = -2.0] conformTo: #'number' selector: #'asFloatE'. self value: [-2000000000 asFloatE] should: [:r | r = -2000000000.0] conformTo: #'number' selector: #'asFloatE'. self value: [2000000000 asFloatE] should: [:r | r = 2000000000.0] conformTo: #'number' selector: #'asFloatE'. self value: [0 asFloatE] should: [:r | r = 0.0] conformTo: #'number' selector: #'asFloatE'.! testXintegerPart " #integerPart (returnRule - :receiver) " | rcvr | #'Numeric'. rcvr := 2. self value: [rcvr integerPart] should: [:result | result = 2] conformTo: #'number' selector: #'integerPart' ruleReceiver: rcvr. rcvr := -2. self value: [rcvr integerPart] should: [:result | result = -2] conformTo: #'number' selector: #'integerPart' ruleReceiver: rcvr. rcvr := -2000000000. self value: [rcvr integerPart] should: [:result | result = -2000000000] conformTo: #'number' selector: #'integerPart' ruleReceiver: rcvr. rcvr := 2000000000. self value: [rcvr integerPart] should: [:result | result = 2000000000] conformTo: #'number' selector: #'integerPart' ruleReceiver: rcvr. rcvr := 0. self value: [rcvr integerPart] should: [:result | result = 0] conformTo: #'number' selector: #'integerPart' ruleReceiver: rcvr.! testXrounded " #rounded " #'Numeric'. self value: [2 rounded] should: [:r | r = 2] conformTo: #'number' selector: #'rounded'. self value: [-2 rounded] should: [:r | r = -2] conformTo: #'number' selector: #'rounded'. self value: [-2000000000 rounded] should: [:r | r = -2000000000] conformTo: #'number' selector: #'rounded'. self value: [2000000000 rounded] should: [:r | r = 2000000000] conformTo: #'number' selector: #'rounded'. self value: [0 rounded] should: [:r | r = 0] conformTo: #'number' selector: #'rounded'.! canonicalObject ^47! testXprintStringRadixX " #printStringRadix: " #'Numeric'.! testXbitShiftX " #bitShift: " #'Numeric'.! testXisKindOfX " #isKindOf: " #'Numeric'. " The return value is unspecified if the receiver is a class object or candidateClass is not a class object. " #'Fundamental'. #todo. "Fix find a test for unspecified rule above ???" self value: [smallInt2 isKindOf: Integer] should: [:r | r] conformTo: #'Object' selector: #'isKindOf:'. self value: [largeNegInt2000000000 isKindOf: Integer] should: [:r | r] conformTo: #'Object' selector: #'isKindOf:'. self value: [largePosInt2000000000 isKindOf: Integer] should: [:r | r] conformTo: #'Object' selector: #'isKindOf:'. "Metaclass tests:" self value: [smallInt2 class isKindOf: (Integer class)] should: [:r | r] conformTo: #'Object' selector: #'isKindOf:'. self value: [largeNegInt2000000000 class isKindOf: (Integer class)] should: [:r | r] conformTo: #'Object' selector: #'isKindOf:'. self value: [largePosInt2000000000 class isKindOf: (Integer class)] should: [:r | r] conformTo: #'Object' selector: #'isKindOf:'. "Inherit tests:" self value: [smallInt2 class isKindOf: (Integer class)] should: [:r | r] conformTo: #'Object' selector: #'isKindOf:'. self value: [smallInt2 class isKindOf: (Number class)] should: [:r | r] conformTo: #'Object' selector: #'isKindOf:'. self value: [smallInt2 isKindOf: Float] shouldnt: [:r | r] conformTo: #'Object' selector: #'isKindOf:'.! testXtoXbyXdoX " #to:by:do: " #'Numeric'.! testXidentityOp " #== " #'Numeric'. " The value of receiver == comparand is true if and only if the value of comparand == receiver would also be true. If the value of receiver == comparand is true then the receiver and comparand must have equivalent identity hash values. Or more formally: receiver == comparand => receiver identityHash = comparand identityHash " self shouldnt: [smallInt2 == float2]. self shouldnt: [smallInt2 identityHash == float2 identityHash]. self value: [smallInt2 == smallInt2] should: [:r | r] conformTo: #'Object' selector: #'=='. self value: [largeNegInt2000000000 == largeNegInt2000000000] should: [:r | r] conformTo: #'Object' selector: #'=='. self value: [largePosInt2000000000 == largePosInt2000000000] should: [:r | r] conformTo: #'Object' selector: #'=='. self value: [smallInt2 == (4/2)] should: [:r | r] conformTo: #'Object' selector: #'=='. self value: [smallInt2 == (3 - 1)] should: [:r | r] conformTo: #'Object' selector: #'=='. self value: [smallInt2 == 3] shouldnt: [:r | r] conformTo: #'Object' selector: #'=='. self value: [largeNegInt2000000000 == 2000000001] shouldnt: [:r | r] conformTo: #'Object' selector: #'=='. self value: [largePosInt2000000000 == 2000000001] shouldnt: [:r | r] conformTo: #'Object' selector: #'=='. self value: [smallInt2 == (6/2)] shouldnt: [:r | r] conformTo: #'Object' selector: #'=='. self value: [smallInt2 == (2 + 1)] shouldnt: [:r | r] conformTo: #'Object' selector: #'=='.! testXdivideOp " #/ (returnRule - :receiver :operand) " | retVals | #'Numeric'. " #( 2 -2000000000 2000000000 2.0 1/2 2.0s3 )." retVals := #(1 0 0 1.0 4 1.000s3) copy. retVals at: 2 put: (-1/1000000000). retVals at: 3 put: (1/1000000000). 1 to: numList size do: [ :ndx | self value: [smallInt2 / (numList at: ndx)] should: [:r | r = (retVals at: ndx)] conformTo: #'number' selector: #'/' ruleReceiver: smallInt2 operand: (numList at: ndx) ]. retVals := #(-1000000000 1 -1 -1000000000.0 -4000000000 -1000000000.000s3). 1 to: numList size do: [ :ndx | self value: [largeNegInt2000000000 / (numList at: ndx)] should: [:r | r = (retVals at: ndx) ] conformTo: #'number' selector: #'/' ruleReceiver: largeNegInt2000000000 operand: (numList at: ndx) ]. retVals := #(1000000000 -1 1 1000000000.0 4000000000 1000000000.000s3). 1 to: numList size do: [ :ndx | self value: [largePosInt2000000000 / (numList at: ndx)] should: [:r | r = (retVals at: ndx)] conformTo: #'number' selector: #'/' ruleReceiver: largePosInt2000000000 operand: (numList at: ndx) ]. self value: [0 / smallInt2] should: [:r | r = 0] conformTo: #'number' selector: #'/' ruleReceiver: smallInt2 operand: 0. self value: [0 / largeNegInt2000000000] should: [:r | r = 0] conformTo: #'number' selector: #'/' ruleReceiver: fractionHalf operand: 0. self value: [0 / largePosInt2000000000] should: [:r | r = 0] conformTo: #'number' selector: #'/' ruleReceiver: fractionHalf operand: 0. "The implementation must signal the ZeroDivide exception." self value: [smallInt2 / 0] shouldRaise: ZeroDivide. self value: [largeNegInt2000000000 / 0] shouldRaise: ZeroDivide. self value: [largePosInt2000000000 / 0] shouldRaise: ZeroDivide.! testXgreaterThanOrEqualToOp " #>= " #'Numeric'. " #( 2 -2000000000 2000000000 2.0 1/2 2.0s3 )." #'todo'."It is erroneous if the receiver and operand are not comparable." "Small >= Big -> false" #( 2 2000000000 2.0 2.0s3 ) do: [ :tstNum | self value: [1 >= tstNum] shouldnt: [:r | r] conformTo: #'magnitude' selector: #'>=' ]. self value: [-2000000005 >= -2000000000] shouldnt: [:r | r] conformTo: #'magnitude' selector: #'>='. self value: [0 >= (1/2)] shouldnt: [:r | r] conformTo: #'magnitude' selector: #'>='. "Num >= Num -> true" 1 to: numList size do: [ :ndx | self value: [(numList at: ndx) >= (numList at: ndx)] should: [:r | r ] conformTo: #'magnitude' selector: #'>=' ]. "Big >= Small -> true" #( 2 2.0 2.0s3 ) do: [ :tstNum | self value: [5 >= tstNum] should: [:r | r] conformTo: #'magnitude' selector: #'>=' ]. self value: [9000000000 >= 2000000000] should: [:r | r] conformTo: #'magnitude' selector: #'>='. self value: [-1000000005 >= -2000000000] should: [:r | r] conformTo: #'magnitude' selector: #'>='. self value: [9 >= (1/2)] should: [:r | r] conformTo: #'magnitude' selector: #'>'.! testXfloor " #floor " #'Numeric'. self value: [2 floor] should: [:r | r = 2] conformTo: #'number' selector: #'floor'. self value: [-2 floor] should: [:r | r = -2] conformTo: #'number' selector: #'floor'. self value: [-2000000000 floor] should: [:r | r = -2000000000] conformTo: #'number' selector: #'floor'. self value: [2000000000 floor] should: [:r | r = 2000000000] conformTo: #'number' selector: #'floor'. self value: [0 floor] should: [:r | r = 0] conformTo: #'number' selector: #'floor'.! testXasFloatQ " #asFloatQ " #'Numeric'. self value: [2 asFloatQ] should: [:r | r = 2.0] conformTo: #'number' selector: #'asFloatQ'. self value: [-2 asFloatQ] should: [:r | r = -2.0] conformTo: #'number' selector: #'asFloatQ'. self value: [-2000000000 asFloatQ] should: [:r | r = -2000000000.0] conformTo: #'number' selector: #'asFloatQ'. self value: [2000000000 asFloatQ] should: [:r | r = 2000000000.0] conformTo: #'number' selector: #'asFloatQ'. self value: [0 asFloatQ] should: [:r | r = 0.0] conformTo: #'number' selector: #'asFloatQ'.! testXroundToX " #roundTo: (returnRule - :receiver :operand) " | retVals | #'Numeric'. " #( 2 -2000000000 2000000000 2.0 1/2 2.0s3 )." retVals := #(2 0 0 2.0 2 2.000s3). 1 to: numList size do: [ :ndx | self value: [smallInt2 roundTo: (numList at: ndx)] should: [:r | r = (retVals at: ndx)] conformTo: #'number' selector: #'roundTo:' ruleReceiver: smallInt2 operand: (numList at: ndx) ]. self should: [(0 roundTo: smallInt2) = 0]! testXodd " #odd " #'Numeric'.! testXtoXdoX " #to:do: " #'Numeric'.! testXprintOnXbaseXshowRadixX " #printOn:base:showRadix: " #'Numeric'.! testXmultiplyOp " #* (returnRule - :receiver :operand) " | retVals negInt2 posInt2 | #'Numeric'. " #( 2 -2000000000 2000000000 2.0 1/2 2.0s3 )." retVals := #(4 -4000000000 4000000000 4.0 1 4.000s3). 1 to: numList size do: [ :ndx | self value: [smallInt2 * (numList at: ndx)] should: [:r | r = (retVals at: ndx)] conformTo: #'number' selector: #'*' ruleReceiver: smallInt2 operand: (numList at: ndx) ]. retVals := #(-4000000000 4000000000000000000 -4000000000000000000 -4000000000.0 -1000000000 -4000000000.000s3). 1 to: numList size do: [ :ndx | self value: [largeNegInt2000000000 * (numList at: ndx)] should: [:r | r = (retVals at: ndx)] conformTo: #'number' selector: #'*' ruleReceiver: largeNegInt2000000000 operand: (numList at: ndx) ]. retVals := #(4000000000 -4000000000000000000 4000000000000000000 4000000000.0 1000000000 4000000000.000s3). 1 to: numList size do: [ :ndx | self value: [largePosInt2000000000 * (numList at: ndx)] should: [:r | r = (retVals at: ndx)] conformTo: #'number' selector: #'*' ruleReceiver: largePosInt2000000000 operand: (numList at: ndx) ]. negInt2 := -2. posInt2 := 2. self value: [negInt2 * posInt2] should: [:result | result = -4] conformTo: #'number' selector: #'*' ruleReceiver: negInt2 operand: posInt2.! testXallMaskX " #allMask: " #'Numeric'.! testXbitAtX " #bitAt: " #'Numeric'.! testXsubtractOp " #- (returnRule - :receiver :operand) " | retVals | #'Numeric'. " #( 2 -2000000000 2000000000 2.0 1/2 2.0s3 )." retVals := #(0 2000000002 -1999999998 0.0s3 0 0.0) copy. retVals at: 5 put: (3/2). 1 to: numList size do: [ :ndx | self value: [smallInt2 - (numList at: ndx)] should: [:r | r closeTo: (retVals at: ndx)] conformTo: #'number' selector: #'-' ruleReceiver: smallInt2 operand: (numList at: ndx) ]. retVals := #(-2000000002 0 -4000000000 -2000000002.0s3 0 -2000000002.0) copy. retVals at: 5 put: (-4000000001/2). 1 to: numList size do: [ :ndx | self value: [largeNegInt2000000000 - (numList at: ndx)] should: [:r | r closeTo: (retVals at: ndx)] conformTo: #'number' selector: #'-' ruleReceiver: largeNegInt2000000000 operand: (numList at: ndx) ]. retVals := #(1999999998 4000000000 0 1999999998.0s3 0 1999999998.0) copy. retVals at: 5 put: (3999999999/2). 1 to: numList size do: [ :ndx | self value: [largePosInt2000000000 - (numList at: ndx)] should: [:r | r closeTo: (retVals at: ndx)] conformTo: #'number' selector: #'-' ruleReceiver: largePosInt2000000000 operand: (numList at: ndx) ].! protocol ^#'integer'! testXquoX " #quo: " | retVals | #'Numeric'. " #( 2 -2000000000 2000000000 2.0 1/2 2.0s3 )." retVals := #(1 0 0 1 4 1 ). 1 to: numList size do: [ :ndx | self value: [smallInt2 quo: (numList at: ndx)] should: [:r | r = (retVals at: ndx)] conformTo: #'number' selector: #'quo:'. ]. retVals := #(-1 0 0 -1 -4 -1 ). 1 to: numList size do: [ :ndx | self value: [smallInt2 quo: ((numList at: ndx) negated)] should: [:r | r = (retVals at: ndx)] conformTo: #'number' selector: #'quo:' ]. self should: [(26 quo: 5.1) = 5]. self should: [(26 quo: 5) = 5]. self should: [(25500000000 quo: 5000000000) = 5]. self should: [(-25500000000 quo: -5000000000) = 5]. self should: [(26 quo: (51/10)) = 5]. self should: [(26 quo: 5.1s1) = 5]. self value: [0 quo: smallInt2] should: [:r | r = 0] conformTo: #'number' selector: #'quo:'. "If the operand has a value of zero the ZeroDivide exception is signaled." self value: [smallInt2 quo: 0] shouldRaise: ZeroDivide.! testXnegative " #negative " #'Numeric'. self value: [-2 negative] should: [:r | r] conformTo: #'number' selector: #'negative'. self value: [-2000000000 negative] should: [:r | r] conformTo: #'number' selector: #'negative'. self value: [2 negative] shouldnt: [:r | r] conformTo: #'number' selector: #'negative'. self value: [2000000000 negative] shouldnt: [:r | r] conformTo: #'number' selector: #'negative'. self value: [0 negative] shouldnt: [:r | r] conformTo: #'number' selector: #'negative'.! testXremX " #rem: " | retVals ndx num2 int | #'Numeric'. "Within the limits of representation, the following invariant should hold: (receiver quo: operand)*operand + (receiver rem: operand) = receiver" " #( 2 -2000000000 2000000000 2.0 1/2 2.0s3 )." numList := #( 5 5.0 5.0s3 ). int := 26. retVals := #(1 1.0 1.000s3 ). ndx := 0. numList do: [ :num | ndx := ndx + 1. self value: [int rem: num] should: [:r | r = (retVals at: ndx) & ((int quo: num) * num + (int rem: num) = int)] conformTo: #'number' selector: #'rem:' ]. numList := numList collect: [ :num | num negated ]. ndx := 0. numList do: [ :num | ndx := ndx + 1. self value: [int rem: num] should: [:r | r = (retVals at: ndx) & ((int quo: num) * num + (int rem: num) = int)] conformTo: #'number' selector: #'rem:' ]. int := -26. numList := #( 5 5.0 5.0s3 ). retVals := retVals collect: [ :num | num negated ]. ndx := 0. numList do: [ :num | ndx := ndx + 1. self should: [(int rem: num) = (retVals at: ndx) & ((int quo: num) * num + (int rem: num) = int)] ]. numList := numList collect: [ :num | num negated ]. ndx := 0. numList do: [ :num | ndx := ndx + 1. self should: [(int rem: num) = (retVals at: ndx) & ((int quo: num) * num + (int rem: num) = int)] ]. int := 26. num2 := (5/2). self value: [int rem: num2] should: [:r | r = 1 & ((int quo: num2) * num2 + (int rem: num2) = int)] conformTo: #'number' selector: #'rem:'. int := 10000000001. numList := #(-2000000000 2000000000). retVals := #(1 1.0 1.000s3 ). ndx := 0. numList do: [ :num | self value: [int rem: num] should: [:r | r = (retVals at: 1) & ((int quo: num) * num + (int rem: num) = int)] conformTo: #'number' selector: #'rem:' ]. "If either the receiver or operand are of type and the operand has a value of zero, the result is implementation defined. The implementation may signal the ZeroDivide exception or provide a continuation value " self value: [smallInt2 rem: 0.0] shouldRaise: ZeroDivide. self value: [smallInt2 rem: 0] shouldRaise: ZeroDivide. self value: [smallInt2 rem: 0s0] shouldRaise: ZeroDivide.! testXreciprocal " #reciprocal (returnRule - :receiver) " #'Numeric'. self value: [smallInt2 reciprocal] should: [:r | r = (1.0/smallInt2)] conformTo: #'number' selector: #'reciprocal' ruleReceiver: smallInt2. self value: [smallInt2 negated reciprocal] should: [:r | r = (1/(smallInt2 negated))] conformTo: #'number' selector: #'reciprocal' ruleReceiver: (smallInt2 negated). self value: [largePosInt2000000000 reciprocal] should: [:r | r = (1/largePosInt2000000000)] conformTo: #'number' selector: #'reciprocal' ruleReceiver: largePosInt2000000000. self value: [largeNegInt2000000000 reciprocal] should: [:r | r = (1/largeNegInt2000000000)] conformTo: #'number' selector: #'reciprocal' ruleReceiver: largeNegInt2000000000. "Signal a ZeroDivide exception if the receiver is equal to zero." self value: [0 reciprocal] shouldRaise: ZeroDivide.! testXasInteger " #asInteger " #'Numeric'. self value: [2 asInteger] should: [:r | r = 2] conformTo: #'number' selector: #'asInteger'. self value: [-2 asInteger] should: [:r | r = -2] conformTo: #'number' selector: #'asInteger'. self value: [-2000000000 asInteger] should: [:r | r = -2000000000] conformTo: #'number' selector: #'asInteger'. self value: [2000000000 asInteger] should: [:r | r = 2000000000] conformTo: #'number' selector: #'asInteger'. self value: [0 asInteger] should: [:r | r = 0] conformTo: #'number' selector: #'asInteger'.! testXsquared " #squared (Return Values: )" | rcvr | #'Numeric'. self value: [smallInt2 squared] should: [:r | r = 4] conformTo: #'number' selector: #'squared' opRECEIVER: smallInt2. rcvr := -2. self value: [rcvr squared] should: [:r | r = 4] conformTo: #'number' selector: #'squared' opRECEIVER: rcvr. self value: [largeNegInt2000000000 squared] should: [:r | r = 4000000000000000000] conformTo: #'number' selector: #'squared' opRECEIVER: largeNegInt2000000000. self value: [largePosInt2000000000 squared] should: [:r | r = 4000000000000000000] conformTo: #'number' selector: #'squared' opRECEIVER: largePosInt2000000000. rcvr := 0. self value: [rcvr squared] should: [:r | r = 0] conformTo: #'number' selector: #'squared' opRECEIVER: rcvr.! testXbitAtXputX " #bitAt:put: " #'Numeric'.! testXdenominator " #denominator " #'Numeric'.! testXprintString " #printString " #'Numeric'. self value: [2 printString] should: [:r | r = '2'] conformTo: #'number' selector: #'printString'. self value: [-2 printString] should: [:r | r = '-2'] conformTo: #'number' selector: #'printString'. self value: [2000000000 printString] should: [:r | r = '2000000000'] conformTo: #'number' selector: #'printString'. self value: [-2000000000 printString] should: [:r | r = '-2000000000'] conformTo: #'number' selector: #'printString'. self value: [0 printString] should: [:r | r = '0'] conformTo: #'number' selector: #'printString'.! testXlessThanOp " #< " #'Numeric'. " #( 2 -2000000000 2000000000 2.0 1/2 2.0s3 )." #'todo'."It is erroneous if the receiver and operand are not comparable." "Small < Big -> true" #( 2 2000000000 2.0 2.0s3 ) do: [ :tstNum | self value: [1 < tstNum] should: [:r | r] conformTo: #'number' selector: #'<' ]. self value: [-2000000005 < -2000000000] should: [:r | r] conformTo: #'number' selector: #'<'. self value: [0 < (1/2)] should: [:r | r] conformTo: #'number' selector: #'<'. "Num < Num -> false" 1 to: numList size do: [ :ndx | self value: [(numList at: ndx) < (numList at: ndx)] shouldnt: [:r | r ] conformTo: #'number' selector: #'<' ]. "Big < Small -> false" #( 2 2.0 2.0s3 ) do: [ :tstNum | self value: [5 < tstNum] shouldnt: [:r | r] conformTo: #'number' selector: #'<' ]. self value: [9000000000 < 2000000000] shouldnt: [:r | r] conformTo: #'number' selector: #'<'. self value: [-1000000005 < -2000000000] shouldnt: [:r | r] conformTo: #'number' selector: #'<'. self value: [9 < (1/2)] shouldnt: [:r | r] conformTo: #'number' selector: #'<'.! testXasFraction " #asFraction " #'Numeric'. self value: [2 asFraction] should: [:r | r = 2] conformTo: #'number' selector: #'asFraction'. self value: [-2 asFraction] should: [:r | r = -2] conformTo: #'number' selector: #'asFraction'. self value: [-2000000000 asFraction] should: [:r | r = -2000000000] conformTo: #'number' selector: #'asFraction'. self value: [2000000000 asFraction] should: [:r | r = 2000000000] conformTo: #'number' selector: #'asFraction'. self value: [0 asFraction] should: [:r | r = 0] conformTo: #'number' selector: #'asFraction'.! testXhighBit " #highBit " #'Numeric'.! testXtoXbyX " #to:by: " #'Numeric'.! testXnoMaskX " #noMask: " #'Numeric'.! testXhash " #hash " #'Numeric'. " Any two objects that are considered equivalent using the #= message must have the same hash value. More formally: receiver = comparand => receiver hash = comparand hash " #'testAnom'. "??? test of equivalence seems to confilict with convert then test. ??? self shouldnt: [smallInt2 = float2]. self shouldnt: [smallInt2 hash = float2 hash]. " self value: [smallInt2 hash] should: [:r | r = smallInt2 hash] conformTo: #'Object' selector: #'hash'. self value: [largeNegInt2000000000 hash] should: [:r | r = largeNegInt2000000000 hash] conformTo: #'Object' selector: #'hash'. self value: [largePosInt2000000000 hash] should: [:r | r = largePosInt2000000000 hash] conformTo: #'Object' selector: #'hash'. self value: [smallInt2 hash] should: [:r | r = (4/2) hash] conformTo: #'Object' selector: #'hash'. self value: [smallInt2 hash] should: [:r | r = (3 - 1) hash] conformTo: #'Object' selector: #'hash'. self value: [smallInt2 hash] shouldnt: [:r | r = 3 hash] conformTo: #'Object' selector: #'hash'. self value: [largeNegInt2000000000 hash] shouldnt: [:r | r = 2000000001 hash] conformTo: #'Object' selector: #'hash'. self value: [largePosInt2000000000 hash] shouldnt: [:r | r = 2000000001 hash] conformTo: #'Object' selector: #'hash'. self value: [smallInt2 hash] shouldnt: [:r | r = (6/2) hash] conformTo: #'Object' selector: #'hash'. self value: [smallInt2 hash] shouldnt: [:r | r = (2 + 1) hash] conformTo: #'Object' selector: #'hash'.! testXbetweenXandX " #between:and: " #'Numeric'. " #( 2 -2000000000 2000000000 2.0 1/2 2.0s3 )." #'todo'."It is erroneous if the receiver and min or max are not comparable" self value: [2 between: 1 and: 3] should: [:r | r] conformTo: #'magnitude' selector: #'between:and:'. self value: [-2000000002 between: -2000000003 and: -2000000001] should: [:r | r] conformTo: #'magnitude' selector: #'between:and:'. self value: [2000000002 between: 2000000001 and: 2000000003] should: [:r | r] conformTo: #'magnitude' selector: #'between:and:'. self value: [2 between: 1.0 and: 3.0] should: [:r | r] conformTo: #'magnitude' selector: #'between:and:'. self value: [2 between: (3/2) and: (5/2)] should: [:r | r] conformTo: #'magnitude' selector: #'between:and:'. self value: [2 between: 1.0s3 and: 3.0s3] should: [:r | r] conformTo: #'magnitude' selector: #'between:and:'. self value: [2 between: (3/2) and: 2000000003] should: [:r | r] conformTo: #'magnitude' selector: #'between:and:'. self value: [2 between: -2000000001.0 and: 3.0s3] should: [:r | r] conformTo: #'magnitude' selector: #'between:and:'. "Num between: Num and: Num -> true" 1 to: numList size do: [ :ndx | self value: [(numList at: ndx) between: (numList at: ndx) and: (numList at: ndx)] should: [:r | r] conformTo: #'magnitude' selector: #'between:and:' ]. self value: [2 between: 3 and: 4] shouldnt: [:r | r] conformTo: #'magnitude' selector: #'between:and:'. self value: [-2000000000 between: -2000000003 and: -2000000005] shouldnt: [:r | r] conformTo: #'magnitude' selector: #'between:and:'. self value: [2000000000 between: 2000000003 and: 2000000005] shouldnt: [:r | r] conformTo: #'magnitude' selector: #'between:and:'. self value: [2 between: 3.0 and: 5.0] shouldnt: [:r | r] conformTo: #'magnitude' selector: #'between:and:'. self value: [2 between: (5/2) and: (7/2)] shouldnt: [:r | r] conformTo: #'magnitude' selector: #'between:and:'. self value: [2 between: 3.0s3 and: 5.0s3] shouldnt: [:r | r] conformTo: #'magnitude' selector: #'between:and:'. "??? min not min but max and vice versa -> false ???" self value: [2 between: 3 and: 1] shouldnt: [:r | r] conformTo: #'magnitude' selector: #'between:and:'.! testXlcmX " #lcm: " #'Numeric'.! testXcopy " #copy (Return Values: ) " #'Numeric'. #todo. "??? add change-side-effect test ???" " If the receiver is an identity object, return the receiver. " self value: [smallInt2 copy] should: [:r | (r = smallInt2) & (r == smallInt2)] conformTo: #'Object' selector: #'copy' opRECEIVER: smallInt2. self value: [largeNegInt2000000000 copy] should: [:r | (r = largeNegInt2000000000) ] conformTo: #'Object' selector: #'copy' opRECEIVER: largeNegInt2000000000. self value: [largePosInt2000000000 copy] should: [:r | (r = largePosInt2000000000) ] conformTo: #'Object' selector: #'copy' opRECEIVER: largePosInt2000000000.! testXraisedToX " #raisedTo: " | numVals retVals | #'Numeric'. numVals := #(2 2.0 0 2.0s3 ) copy. numVals at: 3 put: (1/2). retVals := #(4 4.0 1.414213562373095 4.0 ) copy. 1 to: numVals size do: [ :ndx | self value: [smallInt2 raisedTo: (numVals at: ndx)] should: [:r | r closeTo: (retVals at: ndx)] conformTo: #'number' selector: #'raisedTo:'. ]. retVals := #(0 0.25 0.7071067811865475 0.25 ) copy. retVals at: 1 put: (1/4). 1 to: numVals size do: [ :ndx | self value: [smallInt2 raisedTo: ((numVals at: ndx) negated)] should: [:r | r closeTo: (retVals at: ndx)] conformTo: #'number' selector: #'raisedTo:' ]. self value: [smallInt2 raisedTo: 0] should: [:r | r = 1] conformTo: #'number' selector: #'raisedTo:'. self value: [0 raisedTo: smallInt2] should: [:r | r = 0] conformTo: #'number' selector: #'raisedTo:'. self value: [smallInt2 raisedTo: 1] should: [:r | r = smallInt2] conformTo: #'number' selector: #'raisedTo:'. "It is erroneous if the receiver equals zero and the operand is less than or equal to zero," self value: [0 raisedTo: -2] shouldRaise: Error. " or if the receiver is less than zero." self value: [smallInt2 negated raisedTo: 1.1] shouldRaise: Error.! testXfactorial " #factorial " #'Numeric'.! testXnegated " #negated (Return Values: )" | rcvr | #'Numeric'. rcvr := 2. self value: [rcvr negated] should: [:r | r = -2] conformTo: #'number' selector: #'negated' opRECEIVER: rcvr. rcvr := -2. self value: [rcvr negated] should: [:r | r = 2] conformTo: #'number' selector: #'negated' opRECEIVER: rcvr. rcvr := -2000000000. self value: [rcvr negated] should: [:r | r = 2000000000] conformTo: #'number' selector: #'negated' opRECEIVER: rcvr. rcvr := 2000000000. self value: [rcvr negated] should: [:r | r = -2000000000] conformTo: #'number' selector: #'negated' opRECEIVER: rcvr. rcvr := 0. self value: [rcvr negated] should: [:r | r = 0] conformTo: #'number' selector: #'negated' opRECEIVER: rcvr.! testXequalityOp " #= " #'Numeric'. " receiver = comparand => receiver hash = comparand hash " self value: [smallInt2 = smallInt2] should: [:r | r & (smallInt2 hash = smallInt2 hash) ] conformTo: #'number' selector: #'='. self value: [ smallInt2 = 3 ] shouldnt: [ :r | r | (smallInt2 hash = 3 hash) ] conformTo: #'number' selector: #'='. self value: [largeNegInt2000000000 = largeNegInt2000000000] should: [:r | r & (largeNegInt2000000000 hash = largeNegInt2000000000 hash) ] conformTo: #'number' selector: #'='. self value: [largePosInt2000000000 = largePosInt2000000000] should: [:r | r & (largePosInt2000000000 hash = largePosInt2000000000 hash) ] conformTo: #'number' selector: #'='. " #( 2 2.0 2.0s3 )." self value: [ smallInt2 = 2 ] should: [ :r | r ifTrue: [ smallInt2 hash = 2 hash ] ifFalse: [ smallInt2 hash ~= 2 hash ] ] conformTo: #'number' selector: #'='. self value: [ smallInt2 = 2.0 ] should: [ :r | r ifTrue: [ smallInt2 hash = 2.0 hash ] ifFalse: [ smallInt2 hash ~= 2.0 hash ] ] conformTo: #'number' selector: #'='. self value: [ 2.5s3 = (5/2) ] should: [ :r | r ifTrue: [ 2.5s3 hash = (5/2) hash ] ifFalse: [ 2.5s3 hash ~= (5/2) hash ] ] conformTo: #'number' selector: #'='.! testXremainderIntegerDivideOp " #\\ (returnRule - :receiver :operand) " "The remainder has the same sign as operand. Within the limits of representation, the following invariant should hold: (receiver // operand) * operand + (receiver \\ operand) = receiver " | retVals recList ndx | #'Numeric'. " #( 2 -2000000000 2000000000 2.0 1/2 2.0s3 )." recList := #( 26 -26000000001 26000000001 26.0 0 26.0s3 ) copy. recList at: 5 put: (53/2). retVals := #(1 4 1 1.0 0 1.000s3 ) copy. retVals at: 5 put: (3/2). ndx := 0. recList do: [ :rec | ndx := ndx + 1. self value: [rec \\ 5] should: [:r | r = (retVals at: ndx) & ((rec // 5) * 5 + (rec \\ 5) = rec)] conformTo: #'number' selector: #'\\' ruleReceiver: rec operand: 5. ]. "The remainder has the same sign as operand." retVals := #(-4 -1 -4 -4.0 0 -4.000s3 ) copy. retVals at: 5 put: (-7/2). ndx := 0. recList do: [ :rec | ndx := ndx + 1. self value: [rec \\ -5] should: [:r | r = (retVals at: ndx) & ((rec // -5) * -5 + (rec \\ -5) = rec)] conformTo: #'number' selector: #'\\' ruleReceiver: rec operand: -5. ]. self should: [26 \\ 5 = 1 & ((26 // 5) * 5 + (26 \\ 5) = 26)]. self should: [26 \\ -5 = -4 & ((26 // -5) * -5 + (26 \\ -5) = 26)]. self should: [0 \\ smallInt2 = 0]. self should: [0 \\ largeNegInt2000000000 = 0]. self should: [0 \\ largePosInt2000000000 = 0]. "If the operand is zero, the implementation may signal the ZeroDivide exception or provide a continuation value." self value: [smallInt2 \\ 0] shouldRaise: ZeroDivide. self value: [largeNegInt2000000000 \\ 0] shouldRaise: ZeroDivide. self value: [largePosInt2000000000 \\ 0] shouldRaise: ZeroDivide.! testXtruncateToX " #truncateTo: (returnRule - :receiver :operand) " | retVals | #'Numeric'. " #( 2 -2000000000 2000000000 2.0 1/2 2.0s3 )." retVals := #(2 0 0 2.0 2 2.000s3). 1 to: numList size do: [ :ndx | self value: [smallInt2 truncateTo: (numList at: ndx)] should: [:r | r = (retVals at: ndx)] conformTo: #'number' selector: #'truncateTo:' ruleReceiver: smallInt2 operand: (numList at: ndx) ]. self should: [(0 truncateTo: smallInt2) = 0].! testXintegerDivideOp " #// " | retVals | #'Numeric'. " #( 2 -2000000000 2000000000 2.0 1/2 2.0s3 )." "The sign of the result is positive if the receiver and operand have the same sign, and negative if the signs are different." retVals := #(1 -1 0 1 4 1) copy. 1 to: numList size do: [ :ndx | self value: [smallInt2 // (numList at: ndx)] should: [:r | r = (retVals at: ndx)] conformTo: #'number' selector: #'//'. ]. retVals := #(-1 0 -1 -1 -4 -1) copy. 1 to: numList size do: [ :ndx | self value: [smallInt2 // ((numList at: ndx) negated)] should: [:r | r = (retVals at: ndx)] conformTo: #'number' selector: #'//' ]. self should: [26 // 5.1 = 5]. self should: [26 // 5 = 5]. self should: [25500000000 // 5000000000 = 5]. self should: [-25500000000 // -5000000000 = 5]. self should: [26 // (51/10) = 5]. self should: [26 // 5.1s1 = 5]. self value: [0 // smallInt2] should: [:r | r = 0] conformTo: #'number' selector: #'//'. "If the operand has a value of zero the ZeroDivide exception is signaled." self value: [smallInt2 // 0] shouldRaise: ZeroDivide.! testXceiling " #ceiling " #'Numeric'. self value: [2 ceiling] should: [:r | r = 2] conformTo: #'number' selector: #'ceiling'. self value: [-2 ceiling] should: [:r | r = -2] conformTo: #'number' selector: #'ceiling'. self value: [-2000000000 ceiling] should: [:r | r = -2000000000] conformTo: #'number' selector: #'ceiling'. self value: [2000000000 ceiling] should: [:r | r = 2000000000] conformTo: #'number' selector: #'ceiling'. self value: [0 ceiling] should: [:r | r = 0] conformTo: #'number' selector: #'ceiling'.! testXbitAndX " #bitAnd: " #'Numeric'.! testXfractionPart " #fractionPart (Return Values: )" | rcvr | #'Numeric'. "Within the limits of representation, the following invariants should hold: receiver integerPart + receiver fractionPart = receiver receiver \\1 = receiver fractionPart (RAH - erroneous, add #'abs') " rcvr := 2. self value: [rcvr fractionPart] should: [:r | r = 0 & (rcvr integerPart + rcvr fractionPart = rcvr) & (rcvr \\ 1 = rcvr fractionPart abs)] conformTo: #'number' selector: #'fractionPart' opRECEIVER: rcvr. rcvr := -2. self value: [rcvr fractionPart] should: [:r | r = 0 & (rcvr integerPart + rcvr fractionPart = rcvr) & (rcvr \\ 1 = rcvr fractionPart abs)] conformTo: #'number' selector: #'fractionPart' opRECEIVER: rcvr. rcvr := -2000000000. self value: [rcvr fractionPart] should: [:r | r = 0 & (rcvr integerPart + rcvr fractionPart = rcvr) & (rcvr \\ 1 = rcvr fractionPart abs)] conformTo: #'number' selector: #'fractionPart' opRECEIVER: rcvr. rcvr := 2000000000. self value: [rcvr fractionPart] should: [:r | r = 0 & (rcvr integerPart + rcvr fractionPart = rcvr) & (rcvr \\ 1 = rcvr fractionPart abs)] conformTo: #'number' selector: #'fractionPart' opRECEIVER: rcvr. rcvr := 0. self value: [rcvr fractionPart] should: [:r | r = 0 & (rcvr integerPart + rcvr fractionPart = rcvr) & (rcvr \\ 1 = rcvr fractionPart abs)] conformTo: #'number' selector: #'fractionPart' opRECEIVER: rcvr.! ! !ObjectHelper methodsFor: nil! object: anObject object := anObject! testXperformXwithX " #perform:with: " #'Fundamental'. " If the receiver does not have a method for selector normal message-not-understood processing is performed as if the computed message hand been sent using a message send expression. The perform messages and #respondsTo: must be implemented to produce consistent results. A message to perform a selector, selector, for a given receiver will result in a message-not-understood condition if and only if the value of receiver respondsTo: selector is false. Behavior is undefined if the number of arguments does not match that implicitly required by the syntactic form of the selector. " self value: [self canonicalObject perform: #'selector' with: #()] shouldRaise: MessageNotUnderstood. self value: [self canonicalObject perform: #'isNil' with: 1] shouldRaise: Error. self value: [self canonicalObject perform: #'~~' with: 1] should: [:r | r & (self canonicalObject respondsTo: #'~~')] conformTo: self protocol selector: #'perform:with:'.! testXdoesNotUnderstandX " #doesNotUnderstand: " #'Fundamental'. self value: [self canonicalObject fooXzzYZ] shouldRaise: MessageNotUnderstood.! testXnotNil " #isNil" #Fundamental. " The messages #isNil and #notNil must be implemented to produce consistent results. For a given receiver if the result of #isNil is true then the result of #notNil must be false. " self value: [self canonicalObject notNil = (self canonicalObject ~~ nil)] should: [:r | r] conformTo: #Object selector: #notNil! testXerrorX " #error: " #'Fundamental'. self value: [ [self canonicalObject error: 'dummy' ] on: Error do: [ :error | error return: true ]. ] should: [:r | r] conformTo: self protocol selector: #'error:'. self value: [self canonicalObject error: 'dummy'] shouldRaise: Error.! testXisKindOfX " #isKindOf:" #Fundamental. " The return value is unspecified if the receiver is a class object or candidateClass is not a class object. " #todo. "Fix find a test for unspecified rule above ???" self value: [self canonicalObject isKindOf: Object] should: [:r | r] conformTo: self protocol selector: #isKindOf:. "Metaclass tests:" self value: [self canonicalObject class isKindOf: Object class] should: [:r | "unspecified" true] conformTo: self protocol selector: #isKindOf:. self shouldnt: [self canonicalObject == nil ifTrue: [false] ifFalse: [self canonicalObject isKindOf: UndefinedObject]]! testXidentityHash " #identityHash " #'Fundamental'. self assertSend: #identityHash! testXperformXwithXwithX " #perform:with:with: " #'Fundamental'. " If the receiver does not have a method for selector normal message-not-understood processing is performed as if the computed message hand been sent using a message send expression. The perform messages and #respondsTo: must be implemented to produce consistent results. A message to perform a selector, selector, for a given receiver will result in a message-not-understood condition if and only if the value of receiver respondsTo: selector is false. Behavior is undefined if the number of arguments does not match that implicitly required by the syntactic form of the selector. " self value: [self canonicalObject perform: #'selector' with: #() with: #()] shouldRaise: MessageNotUnderstood. self value: [self canonicalObject perform: #'isNil' with: 1 with: 1] shouldRaise: Error. self value: [self canonicalObject perform: #perform:with: with: #'~~' with: 1] should: [:r | r & (self canonicalObject respondsTo: #perform:with:)] conformTo: self protocol selector: #'perform:with:'.! testXyourself | anObject | " #yourself (Return Values: ) " #'Fundamental'. anObject := self canonicalObject. self value: [anObject yourself] should: [:r | r == anObject] conformTo: self protocol selector: #'yourself'! canonicalObject ^object! testXprintOnX " #printOn: " | resultStream | #'Fundamental'. " The string of characters that would be the result of sending the message #printString to the receiver is written to target. " self value: [resultStream := WriteStream on: (String new: 10). self canonicalObject printOn: resultStream] should: [:r | (resultStream contents) = self canonicalObject printString] conformTo: self protocol selector: #'printOn:'.! testXisNil " #isNil" #Fundamental. " The messages #isNil and #notNil must be implemented to produce consistent results. For a given receiver if the result of #isNil is true then the result of #notNil must be false. " self value: [self canonicalObject isNil = (self canonicalObject == nil)] should: [:r | r] conformTo: #Object selector: #isNil! testXnotIdentityOp " #== " | object1 | #'Fundamental'. " The value of receiver == comparand is true if and only if the value of comparand == receiver would also be true. If the value of receiver == comparand is true then the receiver and comparand must have equivalent identity hash values. Or more formally: receiver == comparand => receiver identityHash = comparand identityHash " object1 := self canonicalObject. self value: [object1 ~~ Object new] should: [:r | r ] conformTo: self protocol selector: #'~~'.! testXrespondsToX " #respondsTo: " #'Fundamental'. self value: [self canonicalObject respondsTo: #'isNil'] should: [:r | r] conformTo: self protocol selector: #'respondsTo:'. self value: [self canonicalObject respondsTo: #'selector'] shouldnt: [:r | r] conformTo: self protocol selector: #'respondsTo:'.! testXisMemberOfX " #isMemberOf: " #'Fundamental'. " The return value is unspecified if the receiver is a class object or candidateClass is not a class object. " #todo. "Fix find a test for unspecified rule above ???" self value: [self canonicalObject isMemberOf: self canonicalObject class] should: [:r | r] conformTo: self protocol selector: #'isMemberOf:'. self shouldnt: [#'aSymbol' isMemberOf: Object].! testXhash " #hash " | | #'Fundamental'. " Any two objects that are considered equivalent using the #= message must have the same hash value. More formally: receiver = comparand => receiver hash = comparand hash " self assertSend: #hash! testXcopy " #copy (Return Values: ) " #'Fundamental'. self assertSend: #copy! testXperformXwithArgumentsX " #perform:withArguments: " #'Fundamental'. " If the receiver does not have a method for the selector normal message-not-understood processing is performed as if the computed message hand been sent using a message send expression. If this occurs, selector and arguments could be captured. The perform messages and #respondsTo: must be implemented to produce consistent results. A message to perform a selector, selector, for a given receiver will result in a message-not-understood condition if and only if the value of receiver respondsTo: selector is false. Behavior is undefined if the number of elements in arguments does not match that implicitly required by the syntactic form of the selector. " self value: [self canonicalObject perform: #'3+4' withArguments: #()] shouldRaise: MessageNotUnderstood. self value: [self canonicalObject perform: #'notNil' withArguments: #( 1 )] shouldRaise: Error. self value: [self canonicalObject perform: #'yourself' withArguments: #()] should: [:r | (self canonicalObject respondsTo: #'yourself')] conformTo: self protocol selector: #'perform:withArguments:'.! testXprintString " #printString " #'Fundamental'. self value: [self canonicalObject printString] should: [:r | true] conformTo: self protocol selector: #'printString'.! testXperformXwithXwithXwithX " #perform:with:with:with: " #'Fundamental'. self notDone! testXclass " #class " #'Fundamental'. self value: [self canonicalObject class] should: [:r | true] conformTo: self protocol selector: #'class'. self value: [self canonicalObject class class] should: [:r | true "unspecified"] conformTo: self protocol selector: #'class'.! testXequalityOp " #= " | newObject object1 | #'Fundamental'. " The value of receiver = comparand is true if and only if the value of comparand = receiver would also be true. If the value of receiver = comparand is true then the receiver and comparand must have equivalent hash values. Or more formally: receiver = comparand => receiver hash = comparand hash " object1 := self canonicalObject. self value: [object1 = object1] should: [:r | r and: [object1 hash = object1 hash] ] conformTo: #'Object' selector: #'='. newObject := Object new. self should: [(object1 ~= newObject) and: [object1 hash ~= newObject hash] ].! testXnotEqualityOp " #~= " | newObject | #'Fundamental'. " The value of receiver ~= comparand is true if and only if the value of comparand ~= receiver would also be true. " newObject := Object new. self value: [self canonicalObject ~= newObject] should: [:r | r & (newObject ~= self canonicalObject)] conformTo: self protocol selector: #'~='. self value: [self canonicalObject ~= self canonicalObject] shouldnt: [:r | r] conformTo: self protocol selector: #'~='.! testXperformX " #perform: " #'Fundamental'. " If the receiver does not have a method for selector normal message-not-understood processing is performed as if the computed message hand been sent using a message send expression. The perform messages and #respondsTo: must be implemented to produce consistent results. A message to perform a selector, selector, for a given receiver will result in a message-not-understood condition if and only if the value of receiver respondsTo: selector is false. Behavior is undefined if the number of arguments does not match that implicitly required by the syntactic form of the selector. " self value: [self canonicalObject perform: #'yourself'] should: [:r | r == r ] conformTo: self protocol selector: #'perform:'. self value: [self canonicalObject perform: #'3+4'] shouldRaise: MessageNotUnderstood.! protocol ^testCase protocol! testXidentityOp " #== " | newObject object1 | #'Fundamental'. " The value of receiver == comparand is true if and only if the value of comparand == receiver would also be true. If the value of receiver == comparand is true then the receiver and comparand must have equivalent identity hash values. Or more formally: receiver == comparand => receiver identityHash = comparand identityHash " object1 := self canonicalObject. self value: [object1 == object1] should: [:r | r and: [object1 identityHash = object1 identityHash] ] conformTo: #'Object' selector: #'=='. newObject := Object new. self should: [(object1 ~~ newObject) and: [object1 identityHash ~~ newObject identityHash] ].! ! !ObjectHelper class methodsFor: nil! initialize super initialize! ! !FailedMessageANSITest methodsFor: nil! testXselector " #selector " #'Fundamental'. #todo. "??? self op: [failedMsg := nil. self + 1. failedMsg selector] should: [:r | r = #'+'] conformTo: #'failedMessage' selector: #'selector'. self op: [failedMsg := nil. self dum. failedMsg selector] should: [:r | r = #'dum'] conformTo: #'failedMessage' selector: #'selector'. self op: [failedMsg := nil. self dum: 1 dum: 2 dum: 3. failedMsg selector] should: [:r | r = #'dum:dum:dum:'] conformTo: #'failedMessage' selector: #'selector'. ???"! setUp "Make a failed message and put it in failedMsg" super setUp. [nil foo] on: MessageNotUnderstood do: [:ex | failedMsg := ex message].! testXarguments " #arguments " #'Fundamental'. #todo. "??? self op: [failedMsg := nil. self + 1. failedMsg arguments] should: [:r | r size = 1 & (r first = 1) ] conformTo: #'failedMessage' selector: #'arguments'. self op: [failedMsg := nil. self dum. failedMsg arguments] should: [:r | r size = 0] conformTo: #'failedMessage' selector: #'arguments'. self op: [failedMsg := nil. self dum: 1 dum: 2 dum: 3. failedMsg arguments] should: [:r | r size = 3 & (r first = 1) & (r last = 3) ] conformTo: #'failedMessage' selector: #'arguments'. ???"! canonicalObject "Return a Message object, which is created when the VM traps a misunderstood message" ^failedMsg! protocol ^#'failedMessage'! ! !MainTestCase methodsFor: nil! runCase self setUp. [(self receiverFor: testSelector) perform: testSelector] on: Error do: [:ex | self tearDown. ex pass]! setUp | helper1 | helpers := Array new. self class helperClassesDo: [:each | helper1 := each new. helper1 attachTo: self. helper1 object: self canonicalObject. helpers := helpers copyWith: helper1]! receiverFor: aSelector (self respondsTo: aSelector) ifTrue: [^self]. helpers do: [:each | (each respondsTo: aSelector) ifTrue: [^each]]. self error: 'not a legal test selector'! ! !MainTestCase class methodsFor: nil! deleteIfUnnecessary: aSelector "Warning - only works for Squeak" (self hasEmptyMethodFor: aSelector) ifFalse: [^self]. (self helpersImplement: aSelector) ifTrue: [self removeSelector: aSelector] "(BagANSITest deleteIfUnnecessary: #testXaddX)"! suite | testSuite testMethods | testSuite := TestSuite new. self isAbstract ifTrue: [^testSuite]. testMethods := self testMethods. self helperClassesDo: [:eachClass | testMethods addAll: eachClass testMethods]. testMethods do: [:each | testSuite addTest: (self selector: each)]. ^testSuite! helpersImplement: aSelector "(BagANSITest helpersImplement: #testXasSet)" self helperClassesDo: [:each | (each selectors includes: aSelector) ifTrue: [^true]]. ^false! removeAllCodeThatShouldBeInHelpers "Warning - only works for Squeak" "MainTestCase removeAllCodeThatShouldBeInHelpers" self allSubclasses do: [:each | each deleteEmptyMethodsImplementedByHelpers]! hasEmptyMethodFor: aSelector "Warning - only works for Squeak" ^(self compiledMethodAt: aSelector) size = 9! isAbstract "Assume that concrete testcase classes do not have subclasses." ^self subclasses isEmpty not! helperClassesDo: aBlock aBlock value: (SUnitNameResolver classNamed: #'ObjectHelper').! deleteEmptyMethodsImplementedByHelpers "Warning - only works for Squeak" self testMethods do: [:each | self deleteIfUnnecessary: each]! ! !TestCaseProtocol methodsFor: nil! value: opBlock shouldnt: shouldNotBlock conformTo: protocolName selector: msgSelector ruleReceiver: receiver operand: operand " | negInt2 posInt2 | negInt2 := -2. posInt2 := 2. self value: [negInt2 * posInt2] shouldnt: [:result | result = 4] conformTo: #'number' selector: #'*' ruleReceiver: negInt2 operand: posInt2. " self value: opBlock should: [:result | (shouldNotBlock value: result) not] conformTo: protocolName selector: msgSelector ruleReceiver: receiver operand: operand! value: opBlock shouldnt: shouldNotBlock conformTo: protocolName selector: msgSelector " self value: [2 = -2] shouldnt: [:result | result] conformTo: #'Object' selector: #'='. " self value: opBlock should: [:result | (shouldNotBlock value: result) not] conformTo: protocolName selector: msgSelector! value: opBlock shouldnt: shouldNotBlock conformTo: protocolName selector: msgSelector ruleReceiver: receiver " | negFlt2 | negFlt2 := -2.0. self value: [negFlt2 integerPart] shouldnt: [:result | result = 2] conformTo: #'number' selector: #'integerPart' ruleReceiver: negFlt2. " self value: opBlock should: [:result | (shouldNotBlock value: result) not] conformTo: protocolName selector: msgSelector ruleReceiver: receiver! assertSend: aSelector inProtocol: aSymbol self assertSend: aSelector toObject: self canonicalObject inProtocol: aSymbol.! notDone "change this to self halt when you want to find all methods that are not done"! value: opBlock should: shouldBlock conformTo: protocolName selector: msgSelector " self value: [2 = 2] should: [:result | result] conformTo: #'Object' selector: #'='. " | msgSpec opResult | opResult := opBlock value. self assert: (shouldBlock value: opResult). [msgSpec := (self protocolManager protocolNamed: protocolName) messageAtSelector: msgSelector] on: Exception do: [:except | "Generate TestFailure as if originally signaled in except's place." self signalFailure: except description]. msgSpec isReturnValueSpecByRule ifTrue: [self signalFailure: 'Conformence failed - requires rule.']. (msgSpec isConformingReturn: opResult) ifFalse: [self signalFailure: 'Conformence failed']! value: opBlock should: shouldBlock conformTo: protocolName selector: msgSelector ruleReceiver: receiver " | negFlt2 | negFlt2 := -2.0. self value: [negFlt2 integerPart] should: [:result | result = -2] conformTo: #'number' selector: #'integerPart' ruleReceiver: negFlt2. " | msgSpec opResult | opResult := opBlock value. self assert: (shouldBlock value: opResult). msgSpec := self msgSpecFor: msgSelector inProtocol: protocolName. msgSpec isReturnValueSpecByRule ifFalse: [TestResult failure signal: 'Conformence failed - requires rule.']. (msgSpec isConformingReturn: opResult ruleReceiver: receiver) ifFalse: [self signalFailure: 'Conformence failed rule value: ' , receiver printString]! selector: aSelector inProtocol: aSymbol behavesLike: arrays arrays asANSITestArray do: [:each | self value: [each first perform: aSelector withArguments: (each copyFrom: 2 to: each size - 1)] should: [:r | r = each last] conformTo: aSymbol selector: aSelector]! assertSend: aSelector self assertSend: aSelector inProtocol: self protocol.! msgSpecFor: msgSelector inProtocol: protocolName | msgSpec newEx | [msgSpec := (self protocolManager protocolNamed: protocolName) messageAtSelector: msgSelector ] on: Exception do: [ :except | "Generate TestFailure as if originally signaled in except's place." newEx := TestResult failure new. newEx messageText: except description. except resignalAs: newEx ]. ^msgSpec! assertSend: aSelector toObject: anObject inProtocol: aSymbol | opResult msgSpec | opResult := anObject perform: aSelector. msgSpec := (self protocolManager protocolNamed: aSymbol) messageOrNilAtSelector: aSelector. msgSpec isNil ifTrue: [self signalFailure: aSelector , ' is not in protocol ', aSymbol]. self assert: (msgSpec isConformingReturn: opResult)! value: opBlock shouldnt: shouldNotBlock conformTo: protocolName selector: msgSelector opRECEIVER: receiver " | negFlt2 | negFlt2 := -2.0. self value: [negFlt2 abs] shouldnt: [:result | result = 0.0] conformTo: #'number' selector: #'abs' opRECEIVER: negFlt2. " self value: opBlock should: [:result | (shouldNotBlock value: result) not] conformTo: protocolName selector: msgSelector opRECEIVER: receiver! value: opBlock should: shouldBlock conformTo: protocolName selector: msgSelector opRECEIVER: receiver " | negFlt2 | negFlt2 := -2.0. self value: [negFlt2 abs] should: [:result | result = 2.0] conformTo: #'number' selector: #'abs' opRECEIVER: negFlt2. " | msgSpec opResult | opResult := opBlock value. self assert: (shouldBlock value: opResult). msgSpec := self msgSpecFor: msgSelector inProtocol: protocolName. (msgSpec isConformingReturn: opResult opRECEIVER: receiver conformTo: protocolName selector: msgSelector) ifFalse: [self signalFailure: 'Conformence failed return RECEIVER: ' , receiver printString]! value: opBlock should: shouldBlock conformTo: protocolName selector: msgSelector ruleReceiver: receiver operand: operand " | negInt2 posInt2 | negInt2 := -2. posInt2 := 2. self value: [negInt2 * posInt2] should: [:result | result = -4] conformTo: #'number' selector: #'*' ruleReceiver: negInt2 operand: posInt2" | msgSpec opResult | opResult := opBlock value. self assert: (shouldBlock value: opResult). msgSpec := self msgSpecFor: msgSelector inProtocol: protocolName. msgSpec isReturnValueSpecByRule ifFalse: [self signalFailure: 'Conformence failed - requires rule.']. (msgSpec isConformingReturn: opResult ruleReceiver: receiver operand: operand ) ifFalse: [self signalFailure: ('Conformence failed rule value: ', receiver printString, ' rec: ', operand printString)].! ! !TestCaseProtocol class methodsFor: nil! fileInSUnitTests "File in SUnit unit tests." | aFileName devDir SUnitDir sep | devDir := 'C:\Dev\'. "Typical DOS location" "devDir := '/usr/local/squeak/rharmon/Dev/'." "Typical Unix location" sep := FileDirectory pathNameDelimiter asString. SUnitDir := devDir, 'SUnit', sep, 'Squeak', sep, '2.7', sep. Transcript cr. aFileName := 'SUnit-Tests.st'. ChangeSorter newChangesFromStream: (FileStream readOnlyFileNamed: (SUnitDir, aFileName)) named: (aFileName sansPeriodSuffix).! testMethods ^self selectors select: [:each | 'test*' match: each].! ! !SortedCollectionANSITest methodsFor: nil! testXcopyReplaceAllXwithX " #copyReplaceAll:with: " #'Collection'.! testXsortBlockX " #sortBlock: " | co | co := self canonicalObject. self value: [co sortBlock:[:a :b | a > b]] should: [:r | co first = 4] conformTo: #SortedCollection selector: #sortBlock:! testXreverse " #reverse " #'Collection'.! testXcopyReplaceFromXtoXwithObjectX " #copyReplaceFrom:to:withObject: " #'Collection'.! testXcopyReplacingXwithObjectX " #copyReplacing:withObject: " #'Collection'.! protocol ^#SortedCollection! testXconcatenateOp | cos | cos := self canonicalObjects. self value: [(cos at: #cd), (cos at: #ab)] should: [:r | r = (cos at: #abcd)] conformTo: #SortedCollection selector: #,! canonicalObject ^SortedCollection with: 1 with: 2 with: 3 with: 4! testXaddX " #add: " | cos | cos := self canonicalObjects. self value: [(cos at: #bcd) add: ((cos at: #a) at: 1); yourself] should: [:r | r = (cos at: #abcd)] conformTo: #SortedCollection selector: #add:! testXcopyReplaceFromXtoXwithX " #copyReplaceFrom:to:with: " #'Collection'.! testXcollectX " #collect: " #'Collection'.! canonicalElement ^self canonicalObject at: 2! emptyCollection ^self canonicalObject class new! testXaddAllX " Not found in spec; but SortedCollection needs to refine it." | cos | cos := self canonicalObjects. self value: [(cos at: #cd) addAll: (cos at: #ab); yourself] should: [:r | r = (cos at: #abcd)] conformTo: #SortedCollection selector: #addAll:! testXcomma " #, " #'Collection'.! testXasSortedCollection " #asSortedCollection " #'Collection'.! testXsortBlock " #sortBlock " " self halt assertSend: #sortBlock" self value: [self canonicalObject sortBlock] should: [:result | true] conformTo: #SortedCollection selector: #sortBlock! ! !SortedCollectionANSITest class methodsFor: nil! helperClassesDo: aBlock super helperClassesDo: aBlock. aBlock value: ExtensibleCollectionHelper. aBlock value: SequencedContractibleCollectionHelper. aBlock value: SequencedReadableCollectionHelper.! ! !ReadFileStreamANSITest methodsFor: nil! testXposition " #position " #'File Stream'.! canonicalObject ^readFileStream! testXisEmpty " #isEmpty " #'File Stream'.! testXnext " #next " #'File Stream'.! testXdoX " #do: " #'File Stream'.! testXatEnd " #atEnd " #'File Stream'.! testXupToX " #upTo: " #'File Stream'.! testXnextMatchForX " #nextMatchFor: " #'File Stream'.! testXisBinary " #isBinary " #'File Stream'.! testXreset " #reset " #'File Stream'.! testXpositionX " #position: " #'File Stream'.! testXpeek " #peek " #'File Stream'.! setUp super setUp. " Requires that a file named 'ansiTestFile.junk' exists in the current directory. " " | aPossiblyNewFile | aPossiblyNewFile := FileStream write: 'ansiTestFile.junk'. aPossiblyNewFile close. " " readFileStream := FileStream read: 'ansiTestFile.junk' "! testXexternalType " #externalType " #'File Stream'.! testXskipToX " #skipTo: " #'File Stream'.! tearDown "readFileStream close."! testXcontents " #contents " #'File Stream'.! testXnextLine " #nextLine " #'File Stream'.! protocol ^#'readFileStream'! testXisText " #isText " #'File Stream'.! testXclose " #close " #'File Stream'.! testXnextX " #next: " #'File Stream'.! testXsetToEnd " #setToEnd " #'File Stream'.! testXskipX " #skip: " #'File Stream'.! testXpeekForX " #peekFor: " #'File Stream'.! ! !AbstractDictionaryHelper methodsFor: nil! testXkeysAndValuesDoX " #keysAndValuesDo: " | canonicalObject sum | #Collection. canonicalObject := self object. sum := 0. self value: [canonicalObject keysAndValuesDo: [:key :value | sum := sum + key + value]] should: [:r | sum = 120] conformTo: #abstractDictionary selector: #keysAndValuesDo:. self should: [canonicalObject keysAndValuesDo: [:key :value | key , 'a']] raise: TestResult error! testXrejectX " #reject: (Return Values: )" "standard says that reject: returns an object of the same type as the receiver, which would be either a Dictionary or an IdentityDictionary. Most Smalltalks return an OrderedCollection" | canonicalObject | #Collection. canonicalObject := self object. self value: [canonicalObject reject: [:each | each > 0]] should: [:r | r isEmpty] conformTo: #abstractDictionary selector: #reject:. self should: [canonicalObject reject: [:each | each * '2']] raise: TestResult error! testXremoveAllKeysX " #removeAllKeys: " | canonicalObject keys | #Collection. canonicalObject := self object. keys := canonicalObject keys. self value: [canonicalObject removeAllKeys: keys] should: [:r | r isEmpty] conformTo: #abstractDictionary selector: #removeAllKeys:! object ^testCase canonicalObject! testXatX " #at: " | canonicalObject | #Collection. canonicalObject := self object. self value: [canonicalObject at: 1] should: [:r | r == 11] conformTo: #abstractDictionary selector: #at:! testXselectX " #select: (Return Values: )" "standard says that select: returns an object of the same type as the receiver, which would be either a Dictionary or an IdentityDictionary. Most Smalltalks return an OrderedCollection" | canonicalObject | #Collection. canonicalObject := self object. self value: [canonicalObject select: [:each | each < 0]] should: [:r | r isEmpty] conformTo: #abstractDictionary selector: #select:. self should: [canonicalObject select: [:each | each , '2']] raise: TestResult error! object: anObject! testXatXifAbsentPutX " #at:ifAbsentPut: " | canonicalObject | #Collection. canonicalObject := self object. self value: [canonicalObject at: 3 ifAbsentPut: 99] should: [:r | r = 33] conformTo: #abstractDictionary selector: #at:ifAbsentPut:. self value: [canonicalObject at: 7 ifAbsentPut: 99] should: [:r | r = 99] conformTo: #abstractDictionary selector: #at:ifAbsentPut:. self value: [canonicalObject at: 17 ifAbsentPut: nil] should: [:r | r = nil] conformTo: #abstractDictionary selector: #at:ifAbsentPut:! testXaddAllX " #addAll: " | abstractDictionary canonicalObject | #Collection. abstractDictionary := self emptyObject. canonicalObject := self object. self value: [abstractDictionary addAll: canonicalObject] should: [:r | r keysDo: [:key | (r at: key) = (canonicalObject at: key)]] conformTo: #abstractDictionary selector: #addAll:! testXkeys " #keys " | canonicalObject | #Collection. canonicalObject := self object. self value: [canonicalObject keys] should: [:r | r size = canonicalObject size] conformTo: #abstractDictionary selector: #keys! testXremoveAllKeysifAbsentX " #removeAllKeys: " | canonicalObject keys sum | #Collection. canonicalObject := self object. sum := 0. keys := #(111 222). self value: [canonicalObject removeAllKeys: keys ifAbsent: [:key | sum := sum + key]] should: [:r | sum = 333] conformTo: #abstractDictionary selector: #removeAllKeys:ifAbsent:. sum := 0. keys := #($a $b). self should: [canonicalObject removeAllKeys: keys ifAbsent: [:key | sum := sum + key]] raise: TestResult error! testXatXputX " #at:put: " | canonicalObject | #Collection. canonicalObject := self object. self value: [canonicalObject at: 3 put: 99] should: [:r | r = 99] conformTo: #abstractDictionary selector: #at:put:. self value: [canonicalObject at: 7 put: 7] should: [:r | r = 7] conformTo: #abstractDictionary selector: #at:put:! testXremoveKeyXifAbsentX " #removeKey:ifAbsent: " | canonicalObject | #Collection. canonicalObject := self object. self value: [canonicalObject removeKey: 2 ifAbsent: [nil]] should: [:r | r = 22] conformTo: #abstractDictionary selector: #removeKey:ifAbsent:. canonicalObject := self object. self value: [canonicalObject removeKey: 666 ifAbsent: [nil]] should: [:r | r isNil] conformTo: #abstractDictionary selector: #removeKey:ifAbsent:! testXkeysDoX " #keysDo: " | sum canonicalObject | #Collection. canonicalObject := self object. sum := 0. self value: [canonicalObject keysDo: [:key | sum := sum + key]] should: [:r | sum = 10] conformTo: #abstractDictionary selector: #keysDo:. self should: [canonicalObject keysDo: [:key | key , 'a']] raise: TestResult error! testXremoveKeyX " #removeKey: " | canonicalObject | #Collection. canonicalObject := self object. self value: [canonicalObject removeKey: 2] should: [:r | r = 22] conformTo: #abstractDictionary selector: #removeKey:! testXvalues " #values" | canonicalObject checkSum | #Collection. canonicalObject := self object. self value: [canonicalObject values] should: [:r | checkSum := r inject: 0 into: [:sum :each | sum + each]. checkSum = 110] conformTo: #abstractDictionary selector: #values.! testXkeyAtValueXifAbsentX " #keyAtValue:ifAbsent: " | canonicalObject | #Collection. canonicalObject := self object. self value: [canonicalObject keyAtValue: 22 ifAbsent: [nil]] should: [:r | r = 2] conformTo: #abstractDictionary selector: #keyAtValue:ifAbsent:. self value: [canonicalObject keyAtValue: 666 ifAbsent: [nil]] should: [:r | r = nil] conformTo: #abstractDictionary selector: #keyAtValue:ifAbsent:! testXincludesKeyX " #includesKey: " | canonicalObject | #Collection. canonicalObject := self object. self value: [canonicalObject includesKey: 1] should: [:r | true] conformTo: #abstractDictionary selector: #includesKey:! testXcollectX " #collect: (Return Values: )" "standard says that collect: returns an object of the same type as the receiver, which would be either a Dictionary or an IdentityDictionary. Most Smalltalks return an OrderedCollection" | canonicalObject | #Collection. canonicalObject := self object. self value: [canonicalObject collect: [:each | each * 2]] should: [:r || ok | ok := r size = canonicalObject size. r keysDo: [:each | ok := ok and: [ (r at: each) = ((canonicalObject at: each) * 2)]]. ok ] conformTo: #abstractDictionary selector: #collect:. self should: [canonicalObject collect: [:each | each , '2']] raise: TestResult error! emptyObject ^testCase emptyCanonicalObject! testXatXifAbsentX " #at:ifAbsent: " | canonicalObject | #Collection. canonicalObject := self object. self value: [canonicalObject at: 3 ifAbsent: 99] should: [:r | r = 33] conformTo: #abstractDictionary selector: #at:ifAbsent:. self value: [canonicalObject at: 7 ifAbsent: 99] should: [:r | r = 99] conformTo: #abstractDictionary selector: #at:ifAbsent:! testXkeyAtValueX " #keyAtValue " | canonicalObject | #Collection. canonicalObject := self object. self value: [canonicalObject keyAtValue: 22] should: [:r | r = 2] conformTo: #abstractDictionary selector: #keyAtValue:. self value: [canonicalObject keyAtValue: 666] should: [:r | r = nil] conformTo: #abstractDictionary selector: #keyAtValue:! ! !StringFactoryANSITest methodsFor: nil! testXwithX " #with: " #'Collection'.! testXwithXwithX " #with:with: " #'Collection'.! testXnew " #new " #'Collection'.! protocol ^#'String factory'! testXnewX " #new: " #'Collection'.! testXwithAllX " #withAll: " #'Collection'.! canonicalObject ^String! testXwithXwithXwithX " #with:with:with: " #'Collection'.! testXwithXwithXwithXwithX " #with:with:with:with: " #'Collection'.! ! !ErrorANSITest methodsFor: nil! testXresignalAsX " #resignalAs: " #'Exception'.! testXretryUsingX " #retryUsing: " #'Exception'.! testXmessageText " #messageText " #'Exception'.! testXresume " #resume " #'Exception'.! testXreturn " #return " #'Exception'.! testXresumeX " #resume: " #'Exception'.! testXreturnX " #return: " #'Exception'.! protocol ^#Error! testXsignal " #signal " #'Exception'.! testXdescription " #description " #'Exception'.! testXsignalX " #signal: " #'Exception'.! testXtag " #tag " #'Exception'.! testXmessageTextX " #messageText: (Return Values: ) " #'Exception'.! testXouter " #outer " #'Exception'.! testXpass " #pass " #'Exception'.! testXretry " #retry " #'Exception'.! testXisResumable " #isResumable " #'Exception'. self value: [ [ Error signal ] on: Error do: [ :aError | aError return: aError isResumable ] ] shouldnt: [:r | r] conformTo: #'Error' selector: #'isResumable'.! testXisNested " #isNested " #'Exception'. self value: [ [ Error signal ] on: Error do: [ :exception | exception return: exception isNested ] ] should: [:r | r = false] conformTo: #'signaledException' selector: #'isNested'.! canonicalObject ^Error new! testXdefaultAction " #defaultAction " #'Exception'. #'todo'."??? I don't know what to test here. self value: [Error signal] should: [:r | true ??UNSPECIFIED??] conformTo: #'Error' selector: #'defaultAction'. ???" self value: [Error signal] shouldRaise: Error.! ! !FractionFactoryANSITest methodsFor: nil! protocol ^#'Fraction factory'! canonicalObject ^Fraction! testXnumeratorXdenominatorX " #numerator:denominator: " #'Numeric'.! ! !PuttableStreamHelper methodsFor: nil! object: anObject! protocol ^#'puttableStream'! testXflush #todo."Don't know how to check this: Upon return, if the receiver is a write-back stream, the state of the stream backing store must be consistent with the current state of the receiver. If the receiver is not a write-back stream, the effect of this message is unspecified. " self assertSend: #flush! testXcr #todo."Don't know how to check this: A sequence of character objects that constitute the implementation-defined end-of-line sequence is added to the receiver in the same manner as if the message #nextPutAll: was sent to the receiver with an argument string whose elements are the sequence of characters. Errors It is erroneous if any element of the end-of-line sequence is an object that does not conform to the receiver's sequence value type. " self assertSend: #cr! testXnextPutAllX #todo."Don't know how to check this: Has the effect of enumerating the aCollection with the message #do: and adding each element to the receiver with #nextPut:. That is, aCollection do: [:each | receiver nextPut: each] " self value: [self canonicalObject nextPutAll: 'abc1%ABC'] should: [:r | true "UNSPECIFIED" ] conformTo: self protocol selector: #'nextPutAll:'. "Errors: It is erroneous if any element of aCollection is an object that does not conform to the receiver's sequence value type." self value: [self canonicalObject nextPutAll: #($a 9 $X)] shouldRaise: Error.! testXspace #todo."Don't know how to check this: The effect is the same as sending the message #nextPut: to the receiver with an argument that is the object that is the value returned when the message #space is sent to the standard global Character. " self assertSend: #space! testXnextPutX #todo."Don't know how to check this: Appends anObject to the receiver's past sequence values. If the receiver's future sequence values is not empty, removes its first object. " self value: [self canonicalObject nextPut: $a] should: [:r | true "UNSPECIFIED" ] conformTo: self protocol selector: #'nextPut:'. "Errors: It is erroneous if anObject is an object that does not conform to the receiver's sequence value type." self value: [self canonicalObject nextPut: 9] shouldRaise: Error.! canonicalObject ^testCase canonicalObject! testXtab #todo."Don't know how to check this: The effect is the same as sending the message #nextPut: to the receiver with an argument that is the object that is the value returned when the message #tab is sent to the standard global Character. " self assertSend: #tab! ! !PuttableStreamHelper class methodsFor: nil! initialize "PuttableStreamHelper initialize" super initialize! ! !DateAndTimeFactoryANSITest methodsFor: nil! testXnow " #now " #'Date and Time'. self value: [DateAndTime now] should: [:r | "unspecified" true] conformTo: #'DateAndTime factory' selector: #'now'.! testXyearXdayXhourXminuteXsecondXoffsetX " #year:day:hour:minute:second:offset: " #'Date and Time'. #'todo'. "??? finish impl this. ???" "April 26, 1997 CST" self value: [DateAndTime year: 1997 day: 116 hour: 1 minute: 2 second: 3 offset: (Duration hours: -6 "CST")] should: [:r | (r year = 1997) & (r month = 4) & (r dayOfMonth = 26) & (r hour = 1) & (r minute = 2) & (r second = 3)] conformTo: #'DateAndTime factory' selector: #'year:day:hour:minute:second:offset:'.! testXyearXmonthXdayXhourXminuteXsecondX " #year:month:day:hour:minute:second: " #'Date and Time'. #'todo'. "??? finish impl this. ???" "April 26, 1997 CST" self value: [DateAndTime year: 1997 month: 4 day: 26 hour: 1 minute: 2 second: 3] should: [:r | (r year = 1997) & (r month = 4) & (r dayOfMonth = 26) & (r hour = 1) & (r minute = 2) & (r second = 3)] conformTo: #'DateAndTime factory' selector: #'year:month:day:hour:minute:second:'.! testXclockPrecision " #clockPrecision " #'Date and Time'. self value: [DateAndTime clockPrecision] should: [:r | "unspecified" true] conformTo: #'DateAndTime factory' selector: #'clockPrecision'.! canonicalObject ^DateAndTime! testXyearXdayXhourXminuteXsecondX " #year:day:hour:minute:second: " #'Date and Time'. #'todo'. "??? finish impl this. ???" "April 26, 1997 CST" self value: [DateAndTime year: 1997 day: 116 hour: 1 minute: 2 second: 3] should: [:r | (r year = 1997) & (r month = 4) & (r dayOfMonth = 26) & (r hour = 1) & (r minute = 2) & (r second = 3)] conformTo: #'DateAndTime factory' selector: #'year:day:hour:minute:second:'.! testXyearXmonthXdayXhourXminuteXsecondXoffsetX " #year:month:day:hour:minute:second:offset: " #'Date and Time'. #'todo'. "??? finish impl this. ???" "April 26, 1997 CST" self value: [DateAndTime year: 1997 month: 4 day: 26 hour: 1 minute: 2 second: 3 offset: (Duration hours: -6 "CST")] should: [:r | (r year = 1997) & (r month = 4) & (r dayOfMonth = 26) & (r hour = 1) & (r minute = 2) & (r second = 3)] conformTo: #'DateAndTime factory' selector: #'year:month:day:hour:minute:second:offset:'.! protocol ^#'DateAndTime factory'! ! !MsgReturnSpec methodsFor: nil! printOn: targetStream "Append to targetStream a text representation of the receiver as a developer would want to see it (inspector, etc)." targetStream nextPutAll: self class name; nextPut: $(. self returnValueProtocolNames do: [:protocolName | targetStream nextPut: $<; nextPutAll: protocolName; nextPut: $>] separatedBy: [targetStream nextPutAll: '|']. targetStream space; nextPutAll: self returnValueAliasingAttribute; nextPut: $)! storeSIFOn: targetStream "Append to targetStream, a , the ASCII representation of the receiver in SIF from which the receiver can be rebuilt but NOT reinstantiated via evaluate." #todo."??? Find better way to keep SIF knowledge out of model ???" targetStream nextPutAll: '#('. targetStream space; nextPut: $'. returnValueProtocols do: [:protocolName | targetStream nextPutAll: protocolName asString] separatedBy: [', ' printOn: targetStream]. targetStream nextPut: $'. targetStream nextPutAll: ' #'. returnValueAliasingAttribute asString printOn: targetStream. targetStream nextPutAll: ')'! setProtocolNames: protocolNames aliasing: aliasingAttribute "Private - ." returnValueProtocols := protocolNames. returnValueAliasingAttribute := aliasingAttribute! returnValueAliasingAttribute "Answer the protocol message return value aliasing attribute." ^ returnValueAliasingAttribute! returnValueProtocolNames "Answer the protocol names the protocol message return value conforms to." ^ returnValueProtocols! isConformingReturnClass: returnClass "Answer true if the class, returnClass, of the result of sending a message conforms to the receiver, else false." self returnValueProtocolNames do: [:protocolName | (returnClass conformsToProtocolNamed: protocolName) ifTrue: [^ true]]. ^ false! storeSIFString "Answer a , a representation of the receiver in SIF from which the receiver can be rebuilt but NOT reinstantiated via evaluate." | aStream | aStream := WriteStream on: (String new: 50). self storeSIFOn: aStream. ^ aStream contents! ! !MsgReturnSpec class methodsFor: nil! privateValidProtocolNames: protocolNamesIn ifError: errorBlock "Private -" | protocolNamesTmp | (protocolNamesIn isKindOf: Collection) ifFalse: [^ errorBlock value]. protocolNamesTmp := self protocolManager defaultProtocolNameCollection. protocolNamesIn do: [:protocolName | (protocolName isKindOf: Symbol) ifFalse: [^ errorBlock value]. protocolNamesTmp add: protocolName]. ^ protocolNamesTmp! privateNewRetValProtocolNames: protocolNames aliasing: aliasingAttribute "Private -" | protocolNamesTmp | (self aliasingAttributes includes: aliasingAttribute) ifFalse: [self error: 'Protocol msg. return value aliasing attribute not valid.']. protocolNamesTmp := self privateValidProtocolNames: protocolNames ifError: [^ self error: 'Protocol msg. return value protocol names not a of s.']. ^ super new setProtocolNames: protocolNamesTmp aliasing: aliasingAttribute! aliasingAttributes "Answer a list of protocol message return value aliasing attribute constants. Note: The list is a of s." ^ Set with: self returnValueAliasingAttributeNew with: self returnValueAliasingAttributeState with: self returnValueAliasingAttributeUnspecified! newRetValStateProtocolNames: protocolNames "Answer a new return value specification indicating a protocol message's return value has a state aliasing attribute and conforms to the protocols named, protocolNames. Note: protocolNames must be a of s." ^ self privateNewRetValProtocolNames: protocolNames aliasing: self returnValueAliasingAttributeState! returnValueAliasingAttributeState "Answer a protocol message return value state aliasing attribute constant." ^ #'state'! returnValueAliasingAttributeNew "Answer a protocol message return value new aliasing attribute constant." ^ #'new'! returnValueAliasingAttributeUnspecified "Answer a protocol message return value unspecified aliasing attribute constant." ^ #'unspecified'! new "Raise an exception as this is an inappropriate message." ^ self shouldNotImplement! newRetValNewProtocolNames: protocolNames "Answer a new return value specification indicating a protocol message's return value has a new aliasing attribute and conforms to the protocols named, protocolNames. Note: protocolNames must be a of s." ^ self privateNewRetValProtocolNames: protocolNames aliasing: self returnValueAliasingAttributeNew! newRetValProtocolNames: protocolNames aliasing: aliasingAttribute "Answer a new return value specification indicating a protocol message's return value conforms to the protocols named, protocolNames, and has an aliasing attribute, aliasingAttribute. Note: protocolNames must be a of s." ^ self privateNewRetValProtocolNames: protocolNames aliasing: aliasingAttribute! newRetValUnspecifiedProtocolNames: protocolNames "Answer a new return value specification indicating a protocol message's return value has a unspecified aliasing attribute and conforms to the protocols named, protocolNames." ^ self privateNewRetValProtocolNames: protocolNames aliasing: self returnValueAliasingAttributeUnspecified! ! !ReadWriteStreamANSITest methodsFor: nil! protocol ^#'ReadWriteStream'! setUp super setUp. readWriteStream := ReadWriteStream with: 'this is a string'! canonicalObject ^readWriteStream! ! !ReadWriteStreamANSITest class methodsFor: nil! helperClassesDo: aBlock super helperClassesDo: aBlock. aBlock value: ReadStreamHelper. aBlock value: WriteStreamHelper! ! !DateAndTimeANSITest methodsFor: nil! testXyear " #year " #'Date and Time'. self value: [d19970426t8 year] should: [:r | r = 1997] conformTo: #'DateAndTime' selector: #'year'.! testXhour12 " #hour12 " #'Date and Time'. self value: [d19970426t8 hour12] should: [:r | r = 8] conformTo: #'DateAndTime' selector: #'hour12'.! testXmonthName " #monthName " #'Date and Time'. self value: [d19970426t8 monthName] should: [:r | r asString = 'April'] conformTo: #'DateAndTime' selector: #'monthName'.! testXmonth " #month " #'Date and Time'. self value: [d19970426t8 month] should: [:r | r = 4] conformTo: #'DateAndTime' selector: #'month'.! testXminute " #minute " #'Date and Time'. self value: [d19970426t8 minute] should: [:r | r = 0] conformTo: #'DateAndTime' selector: #'minute'.! testXminX " #min: " #'Date and Time'.! setUp super setUp. d19970426t8 := DateAndTime year: 1997 month: 4 day: 26 hour: 8 minute: 0 second: 0.! testXlessThanOrEqualToOp " #<= " #'Date and Time'.! testXgreaterThanOrEqualToOp " #>= " #'Date and Time'.! testXaddOp " #+ " #'Date and Time'. self value: [d19970426t8 + (Duration days: 1 hours: 0 minutes: 0 seconds: 1)] should: [:r | r = (DateAndTime year: 1997 month: 4 day: 27 hour: 8 minute: 0 second: 1)] conformTo: #'DateAndTime' selector: #'+'. self value: [d19970426t8 + (Duration days: -1 hours: 0 minutes: 0 seconds: -1)] should: [:r | r = (DateAndTime year: 1997 month: 4 day: 25 hour: 7 minute: 59 second: 59)] conformTo: #'DateAndTime' selector: #'+'.! testXdayOfWeekName " #dayOfWeekName " #'Date and Time'. self value: [d19970426t8 dayOfWeekName] should: [:r | r asString = 'Saturday'] conformTo: #'DateAndTime' selector: #'dayOfWeekName'.! testXdayOfWeekAbbreviation " #dayOfWeekAbbreviation " #'Date and Time'. self value: [d19970426t8 dayOfWeekAbbreviation] should: [:r | r asString = 'Sat'] conformTo: #'DateAndTime' selector: #'dayOfWeekAbbreviation'.! testXdayOfMonth " #dayOfMonth " #'Date and Time'. self value: [d19970426t8 dayOfMonth] should: [:r | r = 26] conformTo: #'DateAndTime' selector: #'dayOfMonth'.! testXdayOfWeek " #dayOfWeek " #'Date and Time'. self value: [d19970426t8 dayOfWeek] should: [:r | r = 7] conformTo: #'DateAndTime' selector: #'dayOfWeek'.! testXasUTC " #asUTC " #'Date and Time'. #todo. "??? I'm not sure how to test. ???" self value: [d19970426t8 asUTC] should: [:r | "Invariant:" r offset = Duration zero] conformTo: #'DateAndTime' selector: #'asUTC'.! testXtimeZoneAbbreviation " #timeZoneAbbreviation " "Changed 2000/06/23 Harmon, R. Needs Daylight Savings Fix." | offTmp | #'Date and Time'. #'testAnom'.">>> offTmp := Duration days: 0 hours: -5 minutes: 0 seconds: 0. self value: [(d19970426t8 offset: offTmp) timeZoneAbbreviation] should: [:r | r = 'EST'] conformTo: #'DateAndTime' selector: #'timeZoneAbbreviation'. <<<" #todo.">>>Fails because d19970426t7MST is Daylight Savings not Standard. offTmp := Duration days: 0 hours: -6 minutes: 0 seconds: 0. self value: [(d19970426t8 offset: offTmp) timeZoneAbbreviation] should: [:r | r = 'CST'] conformTo: #'DateAndTime' selector: #'timeZoneAbbreviation'. <<<"! testXhour24 " #hour24 " #'Date and Time'. self value: [d19970426t8 hour24] should: [:r | r = 8] conformTo: #'DateAndTime' selector: #'hour24'.! testXlessThanOp " #< " #'Date and Time'. self value: [d19970426t8 < (DateAndTime year: 1997 month: 4 day: 27 hour: 8 minute: 0 second: 1)] should: [:r | r] conformTo: #'DateAndTime' selector: #'<'. self value: [d19970426t8 < (DateAndTime year: 2000 month: 4 day: 27 hour: 8 minute: 0 second: 0)] should: [:r | r] conformTo: #'DateAndTime' selector: #'<'. self value: [d19970426t8 < (DateAndTime year: 1996 month: 4 day: 27 hour: 7 minute: 0 second: 0)] shouldnt: [:r | r] conformTo: #'DateAndTime' selector: #'<'.! testXsecond " #second " #'Date and Time'. self value: [d19970426t8 second] should: [:r | r = 0] conformTo: #'DateAndTime' selector: #'second'.! testXoffsetX " #offset: " | d19970426t08Tmp off123 | #'Date and Time'. #todo. "??? Add int, flt, frac offset: tests. ???" off123 := Duration days: 0 hours: 1 minutes: 2 seconds: 3. d19970426t08Tmp := DateAndTime year: 1997 month: 4 day: 26 hour: 0 minute: 0 second: 0 offset: (Duration zero). self value: [(d19970426t08Tmp offset: off123)] should: [:r | r = (DateAndTime year: 1997 month: 4 day: 26 hour: 0 minute: 0 second: 0 offset: off123)] conformTo: #'DateAndTime' selector: #'offset:'. "Invariant:" self should: [(d19970426t08Tmp offset: off123) offset = off123].! testXgreaterThanOp " #> " #'Date and Time'. self value: [(DateAndTime year: 1997 month: 4 day: 27 hour: 8 minute: 0 second: 1) > d19970426t8] should: [:r | r] conformTo: #'DateAndTime' selector: #'>'. self value: [(DateAndTime year: 2000 month: 4 day: 27 hour: 8 minute: 0 second: 0) > d19970426t8] should: [:r | r] conformTo: #'DateAndTime' selector: #'>'. self value: [(DateAndTime year: 1996 month: 4 day: 27 hour: 7 minute: 0 second: 0) > d19970426t8] shouldnt: [:r | r] conformTo: #'DateAndTime' selector: #'>'.! testXbetweenXandX " #between:and: " #'Date and Time'.! testXequalityOp " #=" "Changed 2000/06/23 Harmon, R. Needs Daylight Savings Fix." | d19970426t8CST d19970426t7MST d19970426t7CST tmp1 tmp2 | #'Date and Time'. d19970426t8CST := DateAndTime year: 1997 month: 4 day: 26 hour: 8 minute: 0 second: 0. "1997-04-26T08:00:00-06:00 CST" self value: [d19970426t8 = d19970426t8CST] should: [:r | r & (d19970426t8 hash = d19970426t8CST hash)] conformTo: #DateAndTime selector: #=. d19970426t8CST := DateAndTime year: 1997 month: 4 day: 26 hour: 8 minute: 0 second: 0. "1997-04-26T08:00:00-06:00 CST" tmp1 := DateAndTime year: 1996 month: 4 day: 26 hour: 5 minute: 59 second: 50 offset: (Duration seconds: -10). tmp2 := DateAndTime year: 1996 month: 4 day: 26 hour: 6 minute: 0 second: 10 offset: (Duration seconds: 10). self value: [tmp1 = tmp2] should: [:r | r & (tmp1 hash = tmp2 hash)] conformTo: #DateAndTime selector: #=. d19970426t7MST := DateAndTime year: 1997 month: 4 day: 26 hour: 7 minute: 0 second: 0 offset: (Duration days: 0 hours: -7 minutes: 0 seconds: 0). "1997-04-26T07:00:00-07:00 MST" #todo.">>>Fails because d19970426t7MST is Daylight Savings not Standard. self value: [d19970426t8 = d19970426t7MST] should: [:r | r & (d19970426t8 hash = d19970426t7MST hash)] conformTo: #DateAndTime selector: #=. <<<" d19970426t7CST := DateAndTime year: 1996 month: 4 day: 27 hour: 7 minute: 0 second: 0. "1997-04-26T07:00:00-07:00 MST" self value: [d19970426t8 = d19970426t7CST] shouldnt: [:r | r & (d19970426t8 hash = d19970426t7CST hash)] conformTo: #DateAndTime selector: #=! testXdayOfYear " #dayOfYear " #'Date and Time'. self value: [d19970426t8 dayOfYear] should: [:r | r = 116] conformTo: #'DateAndTime' selector: #'dayOfYear'.! testXprintString " #printString " #'Date and Time'. self value: [(DateAndTime year: 1997 month: 4 day: 26 hour: 1 minute: 2 second: 3 offset: (Duration days: 0 hours: 1 minutes: 2 seconds: 3) ) printString] should: [:r | r = ' 1997-04-26T01:02:03+01:02:3'] conformTo: #'DateAndTime' selector: #'printString'. "Example: 8:33:14.321 PM EST January 5, 1200 B.C. '-1199-01-05T20:33:14.321-05:00' 8:33:14.321 PM -> 20:33:14.321 24 hour" #'testAnom'. "??? ' 0701-01-05T20:33:14-05:00' wrong--not neg. -> '-1199-01-05T20:33:14-05:00' self value: [(DateAndTime year: -1199 month: 1 day: 5 hour: 20 minute: 33 second: 14 offset: (Duration hours: -5 ??EST??)) printString] should: [:r | r = '-1199-01-05T20:33:14.321-05:00'] conformTo: #'DateAndTime' selector: #'printString'. ???" "Example: 12 midnight UTC January 1, 2001 A.D. ' 2001-01-01T00:00:00+00:00'" self value: [(DateAndTime year: 2001 month: 1 day: 1 hour: 0 minute: 0 second: 0 offset: Duration zero) printString] should: [:r | r = ' 2001-01-01T00:00:00+00:00'] conformTo: #'DateAndTime' selector: #'printString'.! testXmeridianAbbreviation " #meridianAbbreviation " #'Date and Time'. self value: [d19970426t8 meridianAbbreviation] should: [:r | r asString = 'AM'] conformTo: #'DateAndTime' selector: #'meridianAbbreviation'. self value: [(DateAndTime year: 1996 month: 2 day: 1 hour: 12 minute: 0 second: 0 ) meridianAbbreviation] should: [:r | r asString = 'PM'] conformTo: #'DateAndTime' selector: #'meridianAbbreviation'.! testXsubtractOp " #- " #'Date and Time'. "If operand is a , answer a ." self value: [d19970426t8 - (DateAndTime year: 1997 month: 4 day: 26 hour: 7 minute: 0 second: 0)] should: [:r | (r isKindOf: Duration) & r = (Duration days: 0 hours: 1 minutes: 0 seconds: 0)] conformTo: #'DateAndTime' selector: #'-'. self value: [d19970426t8 - (DateAndTime year: 1998 month: 4 day: 26 hour: 7 minute: 0 second: 0)] should: [:r | (r isKindOf: Duration) & r = (Duration days: -364 hours: -23 minutes: 0 seconds: 0)] conformTo: #'DateAndTime' selector: #'-'. "If operand is a , answer a new " self value: [d19970426t8 - (Duration days: 1 hours: 0 minutes: 0 seconds: 1)] should: [:r | (r isKindOf: DateAndTime) & r = (DateAndTime year: 1997 month: 4 day: 25 hour: 7 minute: 59 second: 59)] conformTo: #'DateAndTime' selector: #'-'. self value: [d19970426t8 - (Duration days: -1 hours: 0 minutes: 0 seconds: -1)] should: [:r | (r isKindOf: DateAndTime) & r = (DateAndTime year: 1997 month: 4 day: 27 hour: 8 minute: 0 second: 1)] conformTo: #'DateAndTime' selector: #'-'.! protocol ^#'DateAndTime'! canonicalObject ^DateAndTime year: 2000 month: 3 day: 16 hour: 16 minute: 49 second: 43! testXisLeapYear " #isLeapYear " #'Date and Time'. self value: [d19970426t8 isLeapYear] shouldnt: [:r | r] conformTo: #'DateAndTime' selector: #'isLeapYear'. self value: [(DateAndTime year: 1996 month: 2 day: 1 hour: 0 minute: 0 second: 0 ) isLeapYear] should: [:r | r] conformTo: #'DateAndTime' selector: #'isLeapYear'.! testXhour " #hour " #'Date and Time'. self value: [d19970426t8 hour] should: [:r | r = 8] conformTo: #'DateAndTime' selector: #'hour'.! testXoffset " #offset " | d19970426t8Tmp off123 | #'Date and Time'. off123 := Duration days: 0 hours: 1 minutes: 2 seconds: 3. d19970426t8Tmp := DateAndTime year: 1997 month: 4 day: 26 hour: 0 minute: 0 second: 0 offset: off123. self value: [d19970426t8Tmp offset] should: [:r | r = off123] conformTo: #'DateAndTime' selector: #'offset'.! testXasLocal " #asLocal " #'Date and Time'. #todo. "??? I'm not sure how to test. ???" self value: [d19970426t8 asLocal] should: [:r | true] conformTo: #'DateAndTime' selector: #'asLocal'.! testXmonthAbbreviation " #monthAbbreviation " #'Date and Time'. self value: [d19970426t8 monthAbbreviation] should: [:r | r asString = 'Apr'] conformTo: #'DateAndTime' selector: #'monthAbbreviation'.! testXtimeZoneName " #timeZoneName " "Changed 2000/06/23 Harmon, R. Needs Daylight Savings Fix." | offTmp | #'Date and Time'. #'testAnom'.">>> offTmp := Duration days: 0 hours: -5 minutes: 0 seconds: 0. self value: [(d19970426t8 offset: offTmp) timeZoneName] should: [:r | r = 'EST'] conformTo: #'DateAndTime' selector: #'timeZoneName'. <<<" #todo.">>>Fails because d19970426t7MST is Daylight Savings not Standard. offTmp := Duration days: 0 hours: -6 minutes: 0 seconds: 0. self value: [(d19970426t8 offset: offTmp) timeZoneName] should: [:r | r = 'Central Standard Time'] conformTo: #'DateAndTime' selector: #'timeZoneName'. <<<"! testXmaxX " #max: " #'Date and Time'.! ! !SequencedContractibleCollectionHelper methodsFor: nil! object: anObject! object ^testCase canonicalObject! testXremoveLast " #removeLast " | sequencedCollection getValue getValue2 originalLength | #'Collection'. sequencedCollection := self object. originalLength := sequencedCollection size. getValue := sequencedCollection at: originalLength. getValue2 := sequencedCollection at: originalLength - 1. self value: [sequencedCollection removeLast] should: [ :result | result = getValue and: [ ((sequencedCollection at: (originalLength - 1)) = getValue2) and: [ sequencedCollection size = (originalLength - 1) ] ] ] conformTo: #sequencedContractibleCollection selector: #removeLast.! testXremoveAtIndexX " #removeAtIndex: " | sequencedCollection getValue getValue2 | #'Collection'. sequencedCollection := self object. getValue := sequencedCollection at: 1. getValue2 := sequencedCollection at: 2. self value: [sequencedCollection removeAtIndex: 1] should: [ :result | result = getValue and: [ (sequencedCollection at: 1) = getValue2] ] conformTo: #sequencedContractibleCollection selector: #removeAtIndex:. self should: [sequencedCollection removeAtIndex: 0] raise: TestResult error. self should: [sequencedCollection removeAtIndex: sequencedCollection size + 1] raise: TestResult error.! testXremoveFirst " #removeFirst " | sequencedCollection getValue getValue2 originalLength | #'Collection'. sequencedCollection := self object. getValue := sequencedCollection at: 1. getValue2 := sequencedCollection at: 2. originalLength := sequencedCollection size. self value: [sequencedCollection removeFirst] should: [ :result | result = getValue and: [ ((sequencedCollection at: 1) = getValue2) and: [ sequencedCollection size = (originalLength - 1) ] ] ] conformTo: #sequencedContractibleCollection selector: #removeFirst.! ! !ByteArrayANSITest methodsFor: nil! canonicalElement ^self canonicalObject at: 2! conformanceOfPutElementOnXatAllXputX: aString self should: [ self canonicalObject atAll: #(1 2) put: aString] raise: TestResult error! conformanceOfPutElementOnXatAllPutX: aString self should: [ self canonicalObject atAllPut: aString] raise: TestResult error! protocol ^#'ByteArray'! conformanceOfPutElementOnXatXputX: aString self should: [ self canonicalObject at: 1 put: aString] raise: TestResult error! canonicalObject ^ByteArray with: 1 with: 2 with: 3 with: 4! emptyCollection ^self canonicalObject class new! ! !ByteArrayANSITest class methodsFor: nil! helperClassesDo: aBlock super helperClassesDo: aBlock. aBlock value: SequencedCollectionHelper. aBlock value: SequencedReadableCollectionHelper! ! !SortedCollectionFactoryANSITest methodsFor: nil! testXnew " #new " #'Collection'.! testXwithXwithX " #with:with: " #'Collection'.! testXwithX " #with: " #'Collection'.! protocol ^#'SortedCollection factory'! testXsortBlockX " #sortBlock: " #'Collection'.! testXnewX " #new: " #'Collection'.! testXwithAllX " #withAll: " #'Collection'.! canonicalObject ^SortedCollection! testXwithXwithXwithX " #with:with:with: " #'Collection'.! testXwithXwithXwithXwithX " #with:with:with:with: " #'Collection'.! ! !DurationFactoryANSITest methodsFor: nil! testXsecondsX " #seconds: " #'Date and Time'. #'todo'. "??? finish impl this. ???" "((1 * (24 * 60 * 60) + (1 * (60 * 60)) + (1 * 60) + 1)) -> 90061" self value: [(Duration seconds: 3)] should: [:r | r = (Duration days: 0 hours: 0 minutes: 0 seconds: 3)] conformTo: #'Duration factory' selector: #'seconds:'.! testXdaysXhoursXminutesXsecondsX " #days:hours:minutes:seconds: " #'Date and Time'. #'todo'. "??? finish impl this. ???" self value: [(Duration days: 0 hours: 1 minutes: 2 seconds: 3)] should: [:r | r = (Duration days: 0 hours: 1 minutes: 2 seconds: 3)] conformTo: #'Duration factory' selector: #'days:hours:minutes:seconds:'.! canonicalObject ^Duration! testXzero " #zero " #'Date and Time'. self value: [Duration zero] should: [:r | r asSeconds = 0] conformTo: #'Duration factory' selector: #'seconds:'.! protocol ^#'Duration factory'! ! !MonadicBlockANSITest methodsFor: nil! testXvalueWithArgumentsX " #valueWithArguments: " #'Valuable'. self value: [blk1args valueWithArguments: #(1)] should: [:r | r = #(1)] conformTo: #'valuable' selector: #'valueWithArguments:'.! testXvalueX " #value: " #'Valuable'. self value: [blk1args value: 1] should: [:r | r = #(1)] conformTo: #'monadicValuable' selector: #'value:'.! testXargumentCount " #argumentCount " #'Valuable'. self value: [blk1args argumentCount] should: [:r | r = 1] conformTo: #'monadicValuable' selector: #'argumentCount'.! protocol ^#'monadicBlock'! setUp super setUp. blk1args := [ :arg1 | Array with: arg1 ].! canonicalObject ^blk1args! ! !BagANSITest methodsFor: nil! protocol ^#'Bag'! canonicalElement ^2! returnTypeHasLimitedElementTypes ^true! emptyCollection ^self canonicalObject class new! limitedElementTypes ^nil! testXaddXwithOccurrencesX " #add:withOccurrences: " | it | it := Bag new. self value: [it add: 42 withOccurrences: 3] should: [:r | (it occurrencesOf: 42) = 3] conformTo: #Bag selector: #add:withOccurrences:! canonicalObject ^Bag with: 1 with: 2 with: 3 with: 4! canonicalObject ^Bag with: 1 with: 2 with: 3 with: 4! limitedElementType ^nil! ! !BagANSITest class methodsFor: nil! helperClassesDo: aBlock super helperClassesDo: aBlock. aBlock value: ExtensibleCollectionHelper.! ! !ExceptionANSITest methodsFor: nil! exceptionOuterReturn ^[[Exception signal] on: Exception do: [:except | except outer. unchanged := false]] on: Exception do: [:except | except return: true]! notificationOuterDefault "A bug in Squeak's #outer leads this next thing to an infinite loop ..." " value := 1. value := [Notification signal] on: Notification do: [:except | except outer. unchanged := false]. "! testXresume " #resume " value := 1. self resumedNotification. self should: [(value == nil) and: [unchanged]]. self setUp. changed := self resumedException. self should: [changed and: [unchanged]]! testXsignalX " #signal: " #'Exception'. "tested by the zillion other sends of signal"! setUp unchanged := true. value := nil. changed := false.! resignalExceptionAsNotification | firstTime | firstTime := true. ^[[Exception signal] on: Exception do: [:ex | firstTime ifTrue: [firstTime := false. ex resignalAs: Notification new. unchanged := false] ifFalse: [ex pass]]] on: Notification do: [:ex | ex return: true]! testXdefaultAction " #defaultAction " self should: [Notification signal == nil]! resumedExceptionWithValue ^[[Exception signal] on: Exception do: [:except | except resume: false. unchanged := false]] on: Exception do: [:ex | ex return: true]! testXretryUsingX " #retryUsing: " [Exception signal] on: Exception do: [:except | except retryUsing: [changed := true]. unchanged := false]. self should: [changed and: [unchanged]]! testXisResumable " #isResumable " #'Exception'. self mustBeBoolean: Exception new isResumable. self shouldnt: [Error new isResumable]. self should: [Notification new isResumable]. self should: [ZeroDivide new isResumable]. self should: [MessageNotUnderstood new isResumable].! mustBeBoolean: anObject self should: [anObject == true or: [anObject == false]].! testXmessageTextX " #messageText: (Return Values: ) " #'Exception'.! exceptionPass " #pass " ^[[Exception signal] on: Exception do: [:ex | ex pass. unchanged := false]] on: Exception do: [:ex | changed := true. ex return] "conformTo: #'signaledException' selector: #'pass'."! testXresignalAsX " #resignalAs: " changed := self resignalNotificationAsException. self should: [changed and: [unchanged]]. self setUp. changed := self resignalExceptionAsNotification. self should: [changed and: [unchanged]].! resumedException ^[[Exception signal] on: Exception do: [:except | except resume: false. "Exception isn't resumable - this throws an exception" unchanged := false]] on: Exception do: [:ex | ex return: true]! resumedNotification [value := Notification signal] on: Notification do: [:except | except resume. unchanged := false]! testXsignal " #signal " #'Exception'. "tested by the zillion other sends of signal"! notificationOuterResume [[changed := Notification signal] on: Notification do: [:except | except outer. unchanged := false]] on: Notification do: [:except | except resume: true]! testXdescription " #description " | exception messageText | "not sure - spec only says that default should be something 'readable'; well, at least it shouldn't be nil ..." self shouldnt: [Exception new description == nil]. exception := Exception new. messageText := 'our chief weapon is fear'. exception messageText: messageText. self shouldnt: [(exception description indexOfSubCollection: messageText) = 0].! testXretry " #retry " | firstTime | firstTime := true. [firstTime ifTrue: [Exception signal] ifFalse: [changed := true]] on: Exception do: [:except | firstTime := false. except retry. unchanged := false]. self should: [changed and: [unchanged]]! signalNestedException ^[[Exception signal] on: Exception do: [:exception | exception return: exception isNested]] on: Exception do: [:exception | exception return]! signalExceptionNestedWithError ^[[Exception signal] on: Exception do: [:exception | exception return: exception isNested]] on: Error do: [:error | error return]! testXreturnX " #return: " changed := [Exception signal] on: Exception do: [:except | except return: true. unchanged := false]. self should: [changed and: [unchanged]]! testXpass " #pass " self exceptionPass. self should: [changed and: [unchanged]]! protocol ^#Exception! canonicalObject ^Exception new! testXresumeX " #resume: " self resumedNotificationWithValue. self should: [changed and: [unchanged]]. self setUp. changed := self resumedExceptionWithValue. self should: [changed and: [unchanged]]! signalUnnestedException ^[Exception signal] on: Exception do: [:exception | exception return: exception isNested]! testXtag " #tag " | exception messageText | exception := Exception new. self should: [exception tag == nil]. messageText := 'our chief weapon is fear'. exception messageText: messageText. self should: [exception tag = messageText]. exception tag: 1. self should: [exception tag = 1].! testXisNested " #isNested " self shouldnt: [self signalUnnestedException]. self shouldnt: [self signalExceptionNestedWithError]. self should: [self signalNestedException]. " conformTo: #'signaledException' selector: #'isNested'."! exceptionReturn ^[Exception signal] on: Exception do: [:except | except return. unchanged := false]! resumedNotificationWithValue [changed := Notification signal] on: Notification do: [:except | except resume: true. unchanged := false]! testXmessageText " #messageText " | exception messageText | exception := Exception new. self should: [exception messageText == nil]. messageText := 'our chief weapon is fear'. exception messageText: messageText. self should: [exception messageText = messageText].! resignalNotificationAsException ^[[Notification signal] on: Notification do: [:ex | ex resignalAs: Exception new. unchanged := false]] on: Exception do: [:ex | ex return: true]! testXouter " #outer " #'Exception'. changed := self exceptionOuterReturn. self should: [changed and: [unchanged]]. self setUp. value := self notificationOuterDefault. self should: [value == nil and: [unchanged]]. self setUp. self notificationOuterResume. self should: [changed and: [unchanged]].! testXreturn " #return " value := 1. value := self exceptionReturn. self should: [value == nil and: [unchanged]]! ! !ExceptionANSITest class methodsFor: nil! suite ^TestSuite new! ! !ByteArrayFactoryANSITest methodsFor: nil! testXwithX " #with: " #'Collection'.! testXwithXwithX " #with:with: " #'Collection'.! testXnew " #new " #'Collection'.! protocol ^#'ByteArray factory'! testXnewX " #new: " #'Collection'.! testXwithAllX " #withAll: " #'Collection'.! canonicalObject ^ByteArray! testXwithXwithXwithX " #with:with:with: " #'Collection'.! testXwithXwithXwithXwithX " #with:with:with:with: " #'Collection'.! ! !ReadableStringHelper methodsFor: nil! testXasString " #asString " #'ReadableString'. self assertSend: #asString! testXsameAsX " #sameAs:" #'ReadableString'.! testXsubStringsX " #subStrings:" #'ReadableString'.! testXasUppercase " #asSymbol " #'ReadableString'.! testXasSymbol " #asSymbol " #'ReadableString'.! testXasLowercase " #asLowercase " #'ReadableString'. self assertSend: #asLowercase! canonicalObject ^testCase canonicalObject! ! !OrderedCollectionANSITest methodsFor: nil! testXaddFirstX " #addFirst: " | orderedCollection | #'Collection'. orderedCollection := self canonicalObject. self value: [orderedCollection addFirst: 111] should:[:result | result = 111and: [(orderedCollection at: 1) = 111]] conformTo: #OrderedCollection selector: #addFirst:! testXaddAllXafterIndexX " #addAll:afterIndex: " | orderedCollection | #'Collection'. orderedCollection := self canonicalObject. self value: [orderedCollection addAll: #(111 222) afterIndex: 5] shouldRaise: TestResult error. self value: [orderedCollection addAll: #(111 222) afterIndex: -1] shouldRaise: TestResult error. self value: [orderedCollection addAll: #(333 444) afterIndex: 1 ] should: [:result | ((orderedCollection at: 2) = 333) and: [(orderedCollection at: 3) = 444] ] conformTo: #OrderedCollection selector: #addAll:afterIndex:. self value: [orderedCollection addAll: #(555 666) afterIndex: 4] should: [:result | ((orderedCollection at: 5) = 555) and: [(orderedCollection at: 6) = 666]] conformTo: #OrderedCollection selector: #addAll:afterIndex:. self value: [orderedCollection addAll: #(777 888) afterIndex: 0] should: [:result | ((orderedCollection first) = 777) and: [( orderedCollection at: 2) = 888]] conformTo: #OrderedCollection selector: #addAll:afterIndex:! testXaddAllXbeforeX " #addAll:before: " | orderedCollection | #'Collection'. orderedCollection := self canonicalObject. self value: [orderedCollection addAll: #(111 222) before: 5] shouldRaise: TestResult error. self value: [orderedCollection addAll: #(222 333) before: 1] should: [:result | (orderedCollection first) = 222 and: [(orderedCollection at: 2) = 333] ] conformTo: #OrderedCollection selector: #addAll:before:. self value: [orderedCollection addAll: #(444 555) before: 4] should: [:result | (orderedCollection at: orderedCollection size - 2) = 444 and: [(orderedCollection at: orderedCollection size - 1) = 555] ] conformTo: #OrderedCollection selector: #addAll:before:. self value: [orderedCollection addAll: #(666 777) before: 555] should: [:result | (orderedCollection at: orderedCollection size - 3) = 666 and: [(orderedCollection at: orderedCollection size - 2) = 777] ] conformTo: #OrderedCollection selector: #addAll:before:! testXaddAllLastX " #addAllLast: " | orderedCollection | #'Collection'. orderedCollection := self canonicalObject. self value: [orderedCollection addAllLast: #(111 222)] should:[:result | result = #(111 222) and: [(orderedCollection at: orderedCollection size - 1) = 111 and: [(orderedCollection last) = 222]]] conformTo: #OrderedCollection selector: #addAllLast:! protocol ^#OrderedCollection! testXaddXbeforeX " #add:before: " | orderedCollection | #'Collection'. orderedCollection := self canonicalObject. self value: [orderedCollection add: 777 before: 5] shouldRaise: TestResult error. self value: [orderedCollection add: 777 before: 1] should: [:result | (result = 777) and: [(orderedCollection first) = 777]] conformTo: #OrderedCollection selector: #add:before:. self value: [orderedCollection add: 888 before: 4] should: [:result | (result = 888) and: [(orderedCollection at: 5) = 888]] conformTo: #OrderedCollection selector: #add:before:. self value: [orderedCollection add: 999 before: 888] should: [:result | (result = 999) and: [(orderedCollection at: 5) = 999]] conformTo: #OrderedCollection selector: #add:before:! testXaddAllFirstX " #addAllFirst: " | orderedCollection | #'Collection'. orderedCollection := self canonicalObject. self value: [orderedCollection addAllFirst: #(111 222)] should:[:result | result = #(111 222) and: [(orderedCollection at: 1) = 111 and: [(orderedCollection at: 2) = 222]]] conformTo: #OrderedCollection selector: #addAllFirst:! canonicalObject ^OrderedCollection with: 1 with: 2 with: 3 with: 4! testXaddX " #add: " | orderedCollection sampleValue | #'Collection'. orderedCollection := self canonicalObject. self value: [orderedCollection add: 777] should: [:result | orderedCollection do: [ :each | sampleValue := each]. sampleValue = 777] conformTo: #OrderedCollection selector: #add:! testXaddXafterIndexX " #add:afterIndex: " | orderedCollection | #'Collection'. orderedCollection := self canonicalObject. self value: [orderedCollection add: 555 afterIndex: 5] shouldRaise: TestResult error. self value: [orderedCollection add: 666 afterIndex: -1] shouldRaise: TestResult error. self value: [orderedCollection add: 777 afterIndex: 0] should: [:result | (result = 777) and: [(orderedCollection first) = 777]] conformTo: #OrderedCollection selector: #add:afterIndex:. self value: [orderedCollection add: 888 afterIndex: 5] should: [:result | (result = 888) and: [(orderedCollection last) = 888]] conformTo: #OrderedCollection selector: #add:afterIndex:. self value: [orderedCollection add: 999 afterIndex: 1] should: [:result | (result = 999) and: [(orderedCollection at: 2) = 999]] conformTo: #OrderedCollection selector: #add:afterIndex:! testXaddLastX " #addLast: " | orderedCollection | #'Collection'. orderedCollection := self canonicalObject. self value: [orderedCollection addLast: 111] should:[:result | result = 111and: [(orderedCollection last) = 111]] conformTo: #OrderedCollection selector: #addLast:! canonicalElement ^self canonicalObject at: 2! emptyCollection ^self canonicalObject class new! testXaddAllXafterX " #addAll:after: " | orderedCollection | #'Collection'. orderedCollection := self canonicalObject. self value: [orderedCollection addAll: #(111 222) after: 5] shouldRaise: TestResult error. self value: [orderedCollection addAll: #(333 444) after: 1] should: [:result | ((orderedCollection at: 2) = 333) and: [(orderedCollection at: 3) = 444]] conformTo: #OrderedCollection selector: #addAll:after:. self value: [orderedCollection addAll: #(555 666) after: 4] should: [:result | ((orderedCollection at: orderedCollection size - 1) = 555) and: [(orderedCollection last) = 666]] conformTo: #OrderedCollection selector: #addAll:after:. self value: [orderedCollection addAll: #(777 888) after: 555] should: [:result | ((orderedCollection at: orderedCollection size - 2) = 777) and: [( orderedCollection at: orderedCollection size - 1) = 888]] conformTo: #OrderedCollection selector: #addAll:after:! testXaddXafterX " #add:after: " | orderedCollection | #'Collection'. orderedCollection := self canonicalObject. self value: [orderedCollection add: 777 after: 5] shouldRaise: TestResult error. self value: [orderedCollection add: 777 after: 1] should: [:result | (result = 777) and: [(orderedCollection at: 2) = 777]] conformTo: #OrderedCollection selector: #add:after:. self value: [orderedCollection add: 888 after: 4] should: [:result | (result = 888) and: [(orderedCollection last) = 888]] conformTo: #OrderedCollection selector: #add:after:. self value: [orderedCollection add: 999 after: 777] should: [:result | (result = 999) and: [(orderedCollection at: 3) = 999]] conformTo: #OrderedCollection selector: #add:after:! testXaddAllXbeforeIndexX " #addAll:beforeIndex: " | orderedCollection | #'Collection'. orderedCollection := self canonicalObject. self value: [orderedCollection addAll: #(111 222) beforeIndex: 6] shouldRaise: TestResult error. self value: [orderedCollection addAll: #(111 222) beforeIndex: 0] shouldRaise: TestResult error. self value: [orderedCollection addAll: #(222 333) beforeIndex: 1] should: [:result | (orderedCollection first) = 222 and: [(orderedCollection at: 2) = 333] ] conformTo: #OrderedCollection selector: #addAll:beforeIndex:. self value: [orderedCollection addAll: #(444 555) beforeIndex: 4] should: [:result | (orderedCollection at: 4) = 444 and: [(orderedCollection at: 5) = 555] ] conformTo: #OrderedCollection selector: #addAll:beforeIndex:.! testXaddXbeforeIndexX " #add:beforeIndex: " | orderedCollection | #'Collection'. orderedCollection := self canonicalObject. self value: [orderedCollection add: 555 beforeIndex: 6] shouldRaise: TestResult error. self value: [orderedCollection add: 666 beforeIndex: 0] shouldRaise: TestResult error. self value: [orderedCollection add: 666 beforeIndex: -1] shouldRaise: TestResult error. self value: [orderedCollection add: 777 beforeIndex: 1] should: [:result | (result = 777) and: [(orderedCollection first) = 777]] conformTo: #OrderedCollection selector: #add:beforeIndex:. self value: [orderedCollection add: 888 beforeIndex: 6] should: [:result | (result = 888) and: [(orderedCollection last) = 888]] conformTo: #OrderedCollection selector: #add:beforeIndex:. self value: [orderedCollection add: 999 beforeIndex: 2] should: [:result | (result = 999) and: [(orderedCollection at: 2) = 999]] conformTo: #OrderedCollection selector: #add:beforeIndex:! ! !OrderedCollectionANSITest class methodsFor: nil! helperClassesDo: aBlock super helperClassesDo: aBlock. aBlock value: ExtensibleCollectionHelper. aBlock value: SequencedContractibleCollectionHelper. aBlock value: SequencedReadableCollectionHelper. aBlock value: SequencedCollectionHelper.! ! !ReadStreamFactoryANSITest methodsFor: nil! protocol ^#'ReadStream factory'! canonicalObject ^ReadStream! testXonX self value: [self canonicalObject on: 'this is a string'] should: [:r | r position = 0 & r contents = 'this is a string'] conformTo: self protocol selector: #'on:'.! ! !IntervalFactoryANSITest methodsFor: nil! testXfromXtoX " #from:to: " #'Collection'.! canonicalObject ^Interval! testXfromXtoXbyX " #from:to:by: " #'Collection'.! protocol ^#'Interval factory'! ! !ZeroDivideFactoryANSITest methodsFor: nil! testXsignalX " #signal: " #'Exception'.! testXhandlesX " #handles: " #'Exception'.! protocol ^#'ZeroDivide factory'! testXdividendX " #dividend: " | dividendTmp msgResult | #'Exception'. self value: [ [(msgResult := ZeroDivide dividend: 1) signal ] on: ZeroDivide do: [ :aZeroDivide | dividendTmp := aZeroDivide dividend. aZeroDivide return: msgResult ] ] should: [:r | dividendTmp = 1] conformTo: #'ZeroDivide factory' selector: #'dividend:'.! testXconcatenateOp " #, " #'Exception'.! testXsignal " #signal " | msgResult | #'Exception'. self value: [ [msgResult := (ZeroDivide dividend: 1) signal ] on: ZeroDivide do: [ :aZeroDivide | aZeroDivide return: msgResult ] ] should: [:r | true "unspecified"] conformTo: #'ZeroDivide factory' selector: #'signal'.! canonicalObject ^ZeroDivide! testXnew " #new " #'Exception'.! ! !DurationANSITest methodsFor: nil! testXgreaterThanOrEqualToOp " #>= " #'Date and Time'.! testXhours " #hours " #'Date and Time'. self value: [off0123 hours] should: [:r | r = 1] conformTo: #'Duration' selector: #'hours'. self value: [(Duration days: 9 hours: 0 minutes: 2 seconds: 0) hours] should: [:r | r = 0] conformTo: #'Duration' selector: #'hours'. self value: [(Duration days: -9 hours: -1 minutes: -2 seconds: -3) hours] should: [:r | r = -1] conformTo: #'Duration' selector: #'hours'.! testXminutes " #minutes " #'Date and Time'. self value: [off0123 minutes] should: [:r | r = 2] conformTo: #'Duration' selector: #'minutes'. self value: [(Duration days: 9 hours: 0 minutes: 0 seconds: 0) minutes] should: [:r | r = 0] conformTo: #'Duration' selector: #'minutes'. self value: [(Duration days: -9 hours: -1 minutes: -2 seconds: -3) minutes] should: [:r | r = -2] conformTo: #'Duration' selector: #'minutes'.! testXabs " #abs " | absDuration rcvr | #'Date and Time'. absDuration := Duration days: 0 hours: 1 minutes: 2 seconds: 3. self value: [off0123 abs] should: [:r | r = absDuration] conformTo: #'Duration' selector: #'abs' opRECEIVER: off0123. rcvr := Duration days: 0 hours: -1 minutes: -2 seconds: -3. self value: [rcvr abs] should: [:r | r = absDuration] conformTo: #'Duration' selector: #'abs' opRECEIVER: rcvr.! canonicalObject ^Duration seconds: 500000000! testXseconds " #seconds " #'Date and Time'. self value: [off0123 seconds] should: [:r | r = 3] conformTo: #'Duration' selector: #'seconds'. self value: [(Duration days: 9 hours: 0 minutes: 0 seconds: 0) seconds] should: [:r | r = 0] conformTo: #'Duration' selector: #'seconds'. self value: [(Duration days: -9 hours: -1 minutes: -2 seconds: -3.5) seconds] should: [:r | r = -3.5] conformTo: #'Duration' selector: #'seconds'.! testXaddOp " #+ " #'Date and Time'. self value: [off0123 + (Duration days: 1 hours: 1 minutes: 1 seconds: 1)] should: [:r | r = (Duration days: 1 hours: 2 minutes: 3 seconds: 4)] conformTo: #'Duration' selector: #'+'! testXmaxX " #max: " #'Date and Time'.! testXsubtractOp " #- " #'Date and Time'. self value: [off0123 - (Duration days: 1 hours: 1 minutes: 1 seconds: 1)] should: [:r | r = (Duration days:-0 hours:-23 minutes:-58 seconds:-58)] conformTo: #'Duration' selector: #'-'! testXprintString " #printString " #'Date and Time'. self value: [off0123 printString] should: [:r | r = '0:01:02:03'] conformTo: #'Duration' selector: #'printString'. self value: [(Duration days: 0 hours: -1 minutes: -2 seconds: -3.5) printString] should: [:r | r = '-0:01:02:03.5'] conformTo: #'Duration' selector: #'printString'. self value: [(Duration zero) printString] should: [:r | r = '0:00:00:00'] conformTo: #'Duration' selector: #'printString'.! testXasSeconds " #asSeconds " #'Date and Time'. self value: [off0123 asSeconds] should: [:r | r = 3723] conformTo: #'Duration' selector: #'asSeconds'.! setUp super setUp. off0123 := Duration days: 0 hours: 1 minutes: 2 seconds: 3. smallInt2 := 2. largeNegInt2000000000 := -2000000000. largePosInt2000000000 := 2000000000. float2 := 2.0d0. fractionHalf := 1/2. numList := Array new: 5. numList at: 1 put: smallInt2. numList at: 2 put: largeNegInt2000000000. numList at: 3 put: largePosInt2000000000. numList at: 4 put: float2. numList at: 5 put: fractionHalf.! testXmultiplyOp " #* " | retVals | #'Date and Time'. retVals := Array new: 5. "#( 2 -2000000000 2000000000 2.0 1/2 )" retVals at: 1 put: (Duration days: 0 hours: 2 minutes: 4 seconds: 6). retVals at: 2 put: (Duration days: -86180555 hours: -13 minutes: -20 seconds: 0). retVals at: 3 put: (Duration days: 86180555 hours: 13 minutes: 20 seconds: 0). retVals at: 4 put: (Duration days: 0 hours: 2 minutes: 4 seconds: 6). retVals at: 5 put: (Duration days: 0 hours: 0 minutes: 31 seconds: 1.5). 1 to: numList size do: [ :ndx | self value: [off0123 * (numList at: ndx)] should: [:r | r = (retVals at: ndx)] conformTo: #'Duration' selector: #'*' ].! testXlessThanOp " #< " #'Date and Time'. self value: [off0123 < (Duration days: 1 hours: 1 minutes: 1 seconds: 1)] should: [:r | r] conformTo: #'Duration' selector: #'<'. self value: [off0123 < (Duration days: 0 hours: 1 minutes: 2 seconds: 3)] shouldnt: [:r | r] conformTo: #'Duration' selector: #'<'. self value: [off0123 < 0] shouldRaise: Error.! testXdivideOp " #/ " | retVals | #'Date and Time'. retVals := Array new: 5. "If operand is a answer a new ." "#( 2 -2000000000 2000000000 2.0 1/2 )" retVals at: 1 put: (Duration days: 0 hours: 0 minutes: 31 seconds: 1.5). retVals at: 2 put: (Duration days: -0 hours: 0 minutes: 0 seconds: -3723/2000000000). retVals at: 3 put: (Duration days: 0 hours: 0 minutes: 0 seconds: 3723/2000000000). retVals at: 4 put: (Duration days: 0 hours: 0 minutes: 31 seconds: 1.5). retVals at: 5 put: (Duration days: 0 hours: 2 minutes: 4 seconds: 6). #'testAnom'. "??? float = test give false for -0:00:00:01.8615e-6 1 to: numList size do: [ :ndx | self value: [off0123 / (numList at: ndx)] should: [:r | (r isKindOf: Duration) and: [r = (retVals at: ndx)] ] conformTo: #'Duration' selector: #'/' ]. ???" "If operand is a answer a ." "#( 2 -2000000000 2000000000 2.0 1/2 )" retVals at: 1 put: (3723/2). retVals at: 2 put: (-3723/2000000000). retVals at: 3 put: (3723/2000000000). retVals at: 4 put: 1861.5. retVals at: 5 put: 7446.0. 1 to: numList size do: [ :ndx | self value: [off0123 / (Duration seconds: (numList at: ndx))] should: [:r | (r isKindOf: Number) and: [r = (retVals at: ndx)] ] conformTo: #'Duration' selector: #'/' ]. self value: [off0123 / 0] shouldRaise: ZeroDivide. self value: [off0123 / (Duration zero)] shouldRaise: ZeroDivide.! testXgreaterThanOp " #> " #'Date and Time'. self value: [(Duration days: 1 hours: 1 minutes: 1 seconds: 1) > off0123] should: [:r | r] conformTo: #'Duration' selector: #'>'. self value: [(Duration days: 0 hours: 1 minutes: 2 seconds: 3) > off0123] shouldnt: [:r | r] conformTo: #'Duration' selector: #'>'. self value: [off0123 > 0] shouldRaise: Error.! testXpositive " #positive " #'Date and Time'. self value: [off0123 positive] should: [:r | r] conformTo: #'Duration' selector: #'positive'. self value: [(Duration days: 0 hours: -1 minutes: -2 seconds: -3) positive] shouldnt: [:r | r] conformTo: #'Duration' selector: #'positive'. self value: [(Duration zero) positive] should: [:r | r] conformTo: #'Duration' selector: #'positive'.! testXequalityOp " #= " | tmpDuration | #'Date and Time'. tmpDuration := (Duration days: 0 hours: 1 minutes: 2 seconds: 3). self value: [off0123 = tmpDuration] should: [:r | r] conformTo: #'Duration' selector: #'='. self should: [off0123 hash = tmpDuration hash]. tmpDuration := (Duration days: 1 hours: 1 minutes: 1 seconds: 1). self value: [off0123 = tmpDuration] shouldnt: [:r | r] conformTo: #'Duration' selector: #'='. self shouldnt: [off0123 hash = tmpDuration hash].! testXdays " #days " #'Date and Time'. self value: [off0123 days] should: [:r | r = 0] conformTo: #'Duration' selector: #'days'. self value: [(Duration days: 9 hours: 0 minutes: 2 seconds: 0) days] should: [:r | r = 9] conformTo: #'Duration' selector: #'days'. self value: [(Duration days: -9 hours: -1 minutes: -2 seconds: -3) days] should: [:r | r = -9] conformTo: #'Duration' selector: #'days'.! protocol ^#'Duration'! testXnegative " #negative " #'Date and Time'. self value: [off0123 negative] shouldnt: [:r | r] conformTo: #'Duration' selector: #'negative'. self value: [(Duration days: 0 hours: -1 minutes: -2 seconds: -3) negative] should: [:r | r] conformTo: #'Duration' selector: #'negative'. self value: [(Duration zero) negative] shouldnt: [:r | r] conformTo: #'Duration' selector: #'negative'.! testXminX " #min: " #'Date and Time'.! testXlessThanOrEqualToOp " #<= " #'Date and Time'.! testXbetweenXandX " #between:and: " #'Date and Time'.! testXnegated " #negated " | negatedDuration rcvr | #'Date and Time'. negatedDuration := Duration days: 0 hours: -1 minutes: -2 seconds: -3. self value: [off0123 negated] should: [:r | r = negatedDuration] conformTo: #'Duration' selector: #'negated' opRECEIVER: off0123. self value: [negatedDuration negated] should: [:r | r = off0123] conformTo: #'Duration' selector: #'negated' opRECEIVER: negatedDuration. rcvr := Duration zero. self value: [rcvr negated] should: [:r | r = (Duration zero)] conformTo: #'Duration' selector: #'negated' opRECEIVER: rcvr.! ! !OrderedCollectionFactoryANSITest methodsFor: nil! testXwithX " #with: " #'Collection'.! testXwithXwithX " #with:with: " #'Collection'.! testXnew " #new " #'Collection'.! protocol ^#'OrderedCollection factory'! testXnewX " #new: " #'Collection'.! testXwithAllX " #withAll: " #'Collection'.! canonicalObject ^OrderedCollection! testXwithXwithXwithX " #with:with:with: " #'Collection'.! testXwithXwithXwithXwithX " #with:with:with:with: " #'Collection'.! ! !WarningClassANSITest methodsFor: nil! testXsignalX " #signal: " #'Exception'.! testXallSubclasses " #allSubclasses " #'Exception'.! testXname " #name " #'Exception'.! testXsuperclass " #superclass " #'Exception'.! protocol ^#'Warning class'! testXconcatenateOp " #, " #'Exception'.! testXallSuperclasses " #allSuperclasses " #'Exception'.! testXnew " #new " #'Exception'. self value: [Warning new] should: [:r | true "??? r = Warning signal ???"] conformTo: #'Warning class' selector: #'new'.! testXsignal " #signal " #'Exception'.! canonicalObject ^Warning! testXhandlesX " #handles: " #'Exception'.! testXsubclasses " #subclasses " #'Exception'.! ! !SymbolANSITest methodsFor: nil! testXkeysAndValuesDoX " #keysAndValuesDo: " #'Collection'.! testXlessThanOp " #< " #'Collection'.! setUp super setUp. smalltalkSymbol := #'Smalltalk'.! testXequalityOp " #= " #'Collection'. " The value of receiver = comparand is true if and only if the value of comparand = receiver would also be true. If the value of receiver = comparand is true then the receiver and comparand must have equivalent hash values. Or more formally: receiver = comparand => receiver hash = comparand hash Refinement: Unless specifically refined, the receiver and operand are equivalent if all of the following are true: 1. The receiver and operand are instances of the same class. 2. They answer the same value for the #size message. 3. For all indices of the receiver, the element in the receiver at a given index is equivalent to the element in operand at the same index. Element lookup is defined by the #at: message for the receiver and operand. " #todo. "??? add Refinement: test ???" self value: [smalltalkSymbol = smalltalkSymbol] should: [:r | r and: [smalltalkSymbol hash = smalltalkSymbol hash] ] conformTo: #'sequencedReadableCollection' selector: #'='.! emptyCollection ^#''! protocol ^#symbol! testXbetweenXandX " #between:and: " #'Collection'.! testXmaxX " #max: " #'Collection'.! testXsubStringsX " #subStrings: " #'Collection'.! testXgreaterThanOrEqualToOp " #>= " #'Collection'.! testXasSymbol " #asSymbol (Return Values: ) " #'Collection'.! testXasString " #asString " #'Collection'.! testXasLowercase " #asLowercase " #'Collection'.! returnTypeHasLimitedElementTypes ^true! testXidentityHash " #identityHash " #'Collection'. self value: [smalltalkSymbol identityHash] should: [:r | r = smalltalkSymbol identityHash] conformTo: #'Object' selector: #'identityHash'. self value: [smalltalkSymbol identityHash] shouldnt: [:r | r = #'smalltalk' identityHash] conformTo: #'Object' selector: #'identityHash'.! testXhash " #hash " #'Collection'. " Any two objects that are considered equivalent using the #= message must have the same hash value. More formally: receiver = comparand => receiver hash = comparand hash " #'Fundamental'. self shouldnt: [smalltalkSymbol = 'Smalltalk']. self shouldnt: [smalltalkSymbol hash = 'Smalltalk' hash]. self value: [smalltalkSymbol hash] should: [:r | r = smalltalkSymbol hash] conformTo: #'Object' selector: #'hash'. self value: [smalltalkSymbol hash] shouldnt: [:r | r = #'smalltalk' hash] conformTo: #'Object' selector: #'hash'.! testXidentityOp " #== " #'Collection'. " The value of receiver == comparand is true if and only if the value of comparand == receiver would also be true. If the value of receiver == comparand is true then the receiver and comparand must have equivalent identity hash values. Or more formally: receiver == comparand => receiver identityHash = comparand identityHash " self value: [smalltalkSymbol == smalltalkSymbol] should: [:r | r] conformTo: #'Object' selector: #'=='. self value: [smalltalkSymbol == #'smalltalk'] shouldnt: [:r | r] conformTo: #'Object' selector: #'=='.! testXsameAsX " #sameAs: " #'Collection'.! testXnotIdentityOp " #~~ " #'Collection'. " The value of receiver ~~ comparand is true if and only if the value of comparand ~~ receiver would also be true. " self value: [smalltalkSymbol ~~ #'smalltalk'] should: [:r | r] conformTo: #'Object' selector: #'~~'. self value: [smalltalkSymbol ~~ smalltalkSymbol] shouldnt: [:r | r] conformTo: #'Object' selector: #'~~'.! testXasUppercase " #asUppercase " #'Collection'.! testXlessThanOrEqualToOp " #<= " #'Collection'.! testXminX " #min: " #'Collection'.! canonicalElement ^self canonicalObject at: 2! testXgreaterThanOp " #> " #'Collection'.! testXlast " #last " #'Collection'.! testXisKindOfX " #isKindOf: " #'Collection'. " The return value is unspecified if the receiver is a class object or candidateClass is not a class object. " #todo. "Fix find a test for unspecified rule above ???" self value: [smalltalkSymbol isKindOf: Symbol] should: [:r | r] conformTo: #'Object' selector: #'isKindOf:'. "Metaclass tests:" self value: [smalltalkSymbol class isKindOf: (Symbol class)] should: [:r | r] conformTo: #'Object' selector: #'isKindOf:'. "Inherit tests:" self value: [smalltalkSymbol class isKindOf: (Object class)] should: [:r | r] conformTo: #'Object' selector: #'isKindOf:'. self value: [smalltalkSymbol isKindOf: Number] shouldnt: [:r | r] conformTo: #'Object' selector: #'isKindOf:'.! limitedElementTypes ^1! testXcopy " #copy (Return Values: ) " #'Collection'. #todo. "??? add change-side-effect test ???" " If the receiver is an identity object, return the receiver. " self value: [smalltalkSymbol copy] should: [:r | (r = smalltalkSymbol) & (r == smalltalkSymbol)] conformTo: #'Object' selector: #'copy' opRECEIVER: smalltalkSymbol.! canonicalObject ^#abcd! testXnotEqualityOp " #~= " #'Collection'. " The value of receiver ~= comparand is true if and only if the value of comparand ~= receiver would also be true. " self value: [smalltalkSymbol ~= #'smalltalk'] should: [:r | r] conformTo: #'Object' selector: #'~='. self value: [smalltalkSymbol ~= smalltalkSymbol] shouldnt: [:r | r] conformTo: #'Object' selector: #'~='.! testXisMemberOfX " #isMemberOf: " #'Collection'. " The return value is unspecified if the receiver is a class object or candidateClass is not a class object. " #todo. "Fix find a test for unspecified rule above ???" self value: [smalltalkSymbol isMemberOf: Symbol] should: [:r | r] conformTo: #'Object' selector: #'isMemberOf:'. "Metaclass tests:" self value: [smalltalkSymbol class isMemberOf: (Symbol class)] should: [:r | r] conformTo: #'Object' selector: #'isMemberOf:'. "Fail inherit tests:" self value: [smalltalkSymbol class isMemberOf: (Object class)] shouldnt: [:r | r] conformTo: #'Object' selector: #'isMemberOf:'. self value: [smalltalkSymbol isMemberOf: Number] shouldnt: [:r | r] conformTo: #'Object' selector: #'isMemberOf:'.! ! !SymbolANSITest class methodsFor: nil! helperClassesDo: aBlock super helperClassesDo: aBlock. aBlock value: SequencedReadableCollectionHelper! ! !ErrorClassANSITest methodsFor: nil! testXsignalX " #signal: " #'Exception'.! testXallSubclasses " #allSubclasses " #'Exception'.! testXname " #name " #'Exception'.! testXsuperclass " #superclass " #'Exception'.! protocol ^#'Error class'! testXconcatenateOp " #, " #'Exception'.! testXallSuperclasses " #allSuperclasses " #'Exception'.! testXnew " #new " #'Exception'. self value: [Error new] should: [:r | true "??? r = Error signal ???"] conformTo: #'Error class' selector: #'new'.! testXsignal " #signal " #'Exception'.! canonicalObject ^Error! testXhandlesX " #handles: " #'Exception'.! testXsubclasses " #subclasses " #'Exception'.! ! !BagFactoryANSITest methodsFor: nil! testXwithX " #with: " #'Collection'.! testXwithXwithX " #with:with: " #'Collection'.! testXnew " #new " #'Collection'.! protocol ^#'Bag factory'! testXnewX " #new: " #'Collection'.! testXwithAllX " #withAll: " #'Collection'.! canonicalObject ^Bag! testXwithXwithXwithX " #with:with:with: " #'Collection'.! testXwithXwithXwithXwithX " #with:with:with:with: " #'Collection'.! ! !SequencedCollectionHelper methodsFor: nil! testXreplaceFromXtoXwithXstartingAtX " #replaceFrom:to:with:startingAt: " | sequencedCollection putValue | #'Collection'. sequencedCollection := self object. putValue := (self object isKindOf: ByteArray) ifTrue: [#(9 8 7)] ifFalse: [#($c $b $a)]. self value: [sequencedCollection replaceFrom: 1 to: 2 with: putValue startingAt: 2] should: [:result | ((sequencedCollection at: 1) = (putValue at: 2)) & ((sequencedCollection at: 2) = (putValue at: 3))] conformTo: #sequencedCollection selector: #replaceFrom:to:with:startingAt:. self should: [sequencedCollection replaceFrom: 0 to: 1 with: putValue startingAt: 2] raise: TestResult error. self should: [sequencedCollection replaceFrom: sequencedCollection size + 1 to: 1 with: putValue startingAt: 2] raise: TestResult error. self should: [sequencedCollection replaceFrom: 1 to: sequencedCollection size + 1 with: putValue startingAt: 2] raise: TestResult error. self should: [sequencedCollection replaceFrom:1 to: 2 with: #(1 2 3 5) startingAt: 4] raise: TestResult error. self should: [sequencedCollection replaceFrom:1 to: 3 with: #(1 2) startingAt: 0] raise: TestResult error. self should: [sequencedCollection replaceFrom:1 to: 3 with: #(1 2) startingAt: 3] raise: TestResult error! object: anObject! object ^testCase canonicalObject copy! testXatAllPutX " #atAllPut: " | sequencedCollection putValue | #'Collection'. sequencedCollection := self object. putValue := (self object isKindOf: ByteArray) ifTrue: [9] ifFalse: [$a]. self value: [sequencedCollection atAllPut: putValue] should: [:result | (sequencedCollection detect: [:each | each ~= putValue ] ifNone: [nil]) isNil] conformTo: #sequencedCollection selector: #atAllPut:. testCase conformanceOfPutElementOnXatAllPutX: 'ABC'.! testXatAllXputX " #atAll:put: " | putValue indices sequencedCollection | #'Collection'. sequencedCollection := self object. indices := #(1 2 3). putValue := (self object isKindOf: ByteArray) ifTrue: [9] ifFalse: [$a]. self value: [sequencedCollection atAll: indices put: putValue] should: [:result | (indices detect: [:each | (sequencedCollection at: each) ~= putValue] ifNone: [nil]) isNil] conformTo: #sequencedCollection selector: #atAll:put:. testCase conformanceOfPutElementOnXatAllXputX: 'ABC'. self should: [sequencedCollection atAll: #($a #bee 'See') put: putValue] raise: TestResult error. self should: [sequencedCollection atAll:#(0 1) put: putValue] raise: TestResult error. self should: [sequencedCollection atAll: (Array with: 1 with: sequencedCollection size + 1) put: putValue] raise: TestResult error! testXreplaceFromXtoXwithX " #replaceFrom:to:with: " | sequencedCollection putValue | #'Collection'. sequencedCollection := self object. putValue := (self object isKindOf: ByteArray) ifTrue: [#(9 8)] ifFalse: [#($b $a)]. self value: [sequencedCollection replaceFrom: 2 to: 3 with: putValue] should: [:result | ((sequencedCollection at: 2) = (putValue at: 1)) & ((sequencedCollection at: 3) = (putValue at: 2))] conformTo: #sequencedCollection selector: #replaceFrom:to:with:. self should: [sequencedCollection replaceFrom: 0 to: 1 with: putValue] raise: TestResult error. self should: [sequencedCollection replaceFrom: sequencedCollection size + 1 to: 1 with: putValue] raise: TestResult error. self should: [sequencedCollection replaceFrom: 1 to: 0 with: putValue] raise: TestResult error. self should: [sequencedCollection replaceFrom: 1 to: sequencedCollection size + 1 with: putValue] raise: TestResult error. self should: [sequencedCollection replaceFrom:1 to: 2 with: #(1 2 3 5)] raise: TestResult error. self should: [sequencedCollection replaceFrom:1 to: 3 with: #(1)] raise: TestResult error! testXatXputX " #at:put: " | sequencedCollection putValue | #'Collection'. sequencedCollection := self object. putValue := (self object isKindOf: ByteArray) ifTrue: [9] ifFalse: [$a]. self value: [sequencedCollection at: 1 put: putValue] should: [:result | (result = putValue) & ((sequencedCollection at: 1) = putValue)] conformTo: #sequencedCollection selector: #at:put:. testCase conformanceOfPutElementOnXatXputX: 'ABC'. self should: [sequencedCollection at: -1 put: putValue] raise: TestResult error. self should: [sequencedCollection at: sequencedCollection size + 1 put: putValue] raise: TestResult error. self should: [sequencedCollection at: 0 put: putValue] raise: TestResult error.! testXreplaceFromXtoXwithObjectX " #replaceFrom:to:withObject: " | sequencedCollection putValue | #'Collection'. sequencedCollection := self object. putValue := (self object isKindOf: ByteArray) ifTrue: [9] ifFalse: [$a]. self value: [sequencedCollection replaceFrom: 2 to: 3 withObject: putValue] should: [:result | ((sequencedCollection at: 2) = putValue) & ((sequencedCollection at: 3) = putValue)] conformTo: #sequencedCollection selector: #replaceFrom:to:withObject:. self should: [sequencedCollection replaceFrom: 0 to: 1 withObject: putValue] raise: TestResult error. self should: [sequencedCollection replaceFrom: sequencedCollection size + 1 to: 1 withObject: putValue] raise: TestResult error. "self should: [sequencedCollection replaceFrom: 1 to: -1 withObject: putValue] raise: TestResult error." self should: [sequencedCollection replaceFrom: 1 to: sequencedCollection size + 1 withObject: putValue] raise: TestResult error! ! !SequencedStreamTest class methodsFor: nil! helperClassesDo: aBlock super helperClassesDo: aBlock. aBlock value: SequencedStreamHelper! ! !MessageNotUnderstoodANSITest methodsFor: nil! testXresignalAsX " #resignalAs: " #'Exception'.! testXretryUsingX " #retryUsing: " #'Exception'.! testXmessageText " #messageText " #'Exception'.! testXresume " #resume " #'Exception'.! testXreturn " #return " #'Exception'.! testXmessage " #message " #'Exception'. self value: [ [ 1 bob ] on: MessageNotUnderstood do: [ :mnu | mnu return: mnu message ] ] should: [:r | (r selector = #'bob') & (r arguments = Array new)] conformTo: #'MessageNotUnderstood' selector: #'message'. self value: [ [ 1 bob: 2 ] on: MessageNotUnderstood do: [ :mnu | mnu return: mnu message ] ] should: [:r | (r selector = #'bob:') & (r arguments = #( 2 ))] conformTo: #'MessageNotUnderstood' selector: #'message'.! testXresumeX " #resume: " #'Exception'.! testXreceiver " #receiver " #'Exception'. self value: [ [ 1 bob ] on: MessageNotUnderstood do: [ :mnu | mnu return: mnu receiver ] ] should: [:r | r = 1] conformTo: #'MessageNotUnderstood' selector: #'receiver'.! testXreturnX " #return: " #'Exception'.! protocol ^#MessageNotUnderstood! testXsignal " #signal " #'Exception'.! testXdescription " #description " #'Exception'.! testXsignalX " #signal: " #'Exception'.! testXtag " #tag " #'Exception'.! testXmessageTextX " #messageText: (Return Values: ) " #'Exception'.! testXouter " #outer " #'Exception'.! testXpass " #pass " #'Exception'.! testXretry " #retry " #'Exception'.! testXisResumable " #isResumable " #'Exception'. self value: [ [ MessageNotUnderstood signal ] on: MessageNotUnderstood do: [ :mnu | mnu return: mnu isResumable ] ] should: [:r | r] conformTo: #'MessageNotUnderstood' selector: #'isResumable'.! testXisNested " #isNested " #'Exception'.! canonicalObject ^MessageNotUnderstood new! testXdefaultAction " #defaultAction " #'Exception'.! ! !TranscriptANSITest methodsFor: nil! protocol ^#'Transcript'! canonicalObject ^Transcript! ! !TranscriptANSITest class methodsFor: nil! helperClassesDo: aBlock super helperClassesDo: aBlock. aBlock value: PuttableStreamHelper! ! !SetANSITest methodsFor: nil! testXaddAllX " #addAll: " | co oldSize | co := self canonicalObject. oldSize := co size. self value: [co addAll: co copy] should: [:r | co size = oldSize] conformTo: #Set selector: #addAll:! canonicalElement ^2! testXaddX " #add: " | co oldSize | co := self canonicalObject. oldSize := co size. self value: [co add: co any] should: [:r | co size = oldSize] conformTo: #Set selector: #add:! protocol ^#Set! canonicalObject ^Set with: 1 with: 2 with: 3 with: 4! emptyCollection ^self canonicalObject class new! ! !SetANSITest class methodsFor: nil! helperClassesDo: aBlock super helperClassesDo: aBlock. aBlock value: ExtensibleCollectionHelper.! ! !ZeroDivideANSITest methodsFor: nil! testXresignalAsX " #resignalAs: " #'Exception'.! testXretryUsingX " #retryUsing: " #'Exception'.! testXmessageText " #messageText " #'Exception'.! testXresume " #resume " #'Exception'.! testXreturn " #return " #'Exception'.! testXresumeX " #resume: " #'Exception'.! testXreturnX " #return: " #'Exception'.! protocol ^#ZeroDivide! testXsignal " #signal " #'Exception'.! testXdividend " #dividend " #'Exception'. self value: [ [(ZeroDivide dividend: 1) signal ] on: ZeroDivide do: [ :aZeroDivide | aZeroDivide return: (aZeroDivide dividend) ] ] should: [:r | r = 1] conformTo: #'ZeroDivide' selector: #'dividend'.! testXdescription " #description " #'Exception'.! testXsignalX " #signal: " #'Exception'.! testXtag " #tag " #'Exception'.! testXmessageTextX " #messageText: (Return Values: ) " #'Exception'.! testXouter " #outer " #'Exception'.! testXpass " #pass " #'Exception'.! testXretry " #retry " #'Exception'.! testXisResumable " #isResumable " #'Exception'. self value: [ [(ZeroDivide dividend: 1) signal ] on: ZeroDivide do: [ :aZeroDivide | aZeroDivide return: aZeroDivide isResumable ] ] should: [:r | r] conformTo: #'ZeroDivide' selector: #'isResumable'.! testXisNested " #isNested " #'Exception'.! canonicalObject ^ZeroDivide new! testXdefaultAction " #defaultAction " #'Exception'.! ! !CharacterANSITest methodsFor: nil! testXisAlphaNumeric " #isAlphaNumeric " #'Fundamental'. " Return true if the receiver is either a letter or digit. Otherwise return false. In other words character isAlphaNumeric is true if and only if either character isLetter is true or character isDigit is true. " self value: [$A isAlphaNumeric] should: [:r | r & ($A isLetter | $A isDigit)] conformTo: #'Character' selector: #'isAlphaNumeric'. self value: [$B isAlphaNumeric] should: [:r | r & ($B isLetter | $B isDigit)] conformTo: #'Character' selector: #'isAlphaNumeric'. self value: [$a isAlphaNumeric] should: [:r | r & ($a isLetter | $a isDigit)] conformTo: #'Character' selector: #'isAlphaNumeric'. self value: [$1 isAlphaNumeric] should: [:r | r & ($1 isLetter | $1 isDigit)] conformTo: #'Character' selector: #'isAlphaNumeric'. self value: [$: isAlphaNumeric] shouldnt: [:r | r & ($: isLetter | $: isDigit)] conformTo: #'Character' selector: #'isAlphaNumeric'.! testXasString " #asString " #'Fundamental'. self selector: #'asString' inProtocol: #'Character' behavesLike: #( #($A 'A') #($B 'B') #($a 'a') #($1 '1') #($: ':') )! testXasLowercase " #asLowercase " #'Fundamental'. " If the receiver is equal to the value of a character literal in the receiver row of the following table, the result object must be equal to the value of the corresponding character literal in the result row. receiver $A - $Z result $a - $z An implemention may define other #asLowercase mappings. If the receiver does not correspond to a character in the receiver row of the table and does not have an implementation defined mapping the receiver is returned as the result. " self selector: #'asLowercase' inProtocol: #'Character' behavesLike: #( #($A $a) #($b $b) #($1 $1) #($: $:) )! testXisLetter " #isLetter " | alphaChars | #'Fundamental'. alphaChars := #( $A $B $C $D $E $F $G $H $I $J $K $L $M $N $O $P $Q $R $S $T $U $V $W $X $Y $Z $a $b $c $d $e $f $g $h $i $j $k $l $m $n $o $p $q $r $s $t $u $v $w $x $y $z ). self value: [$A isLetter] should: [:r | r & (alphaChars includes: $A)] conformTo: #'Character' selector: #'isLetter'. self value: [$B isLetter] should: [:r | r & (alphaChars includes: $B)] conformTo: #'Character' selector: #'isLetter'. self value: [$a isLetter] should: [:r | r & (alphaChars includes: $a)] conformTo: #'Character' selector: #'isLetter'. self value: [$1 isLetter] shouldnt: [:r | r & (alphaChars includes: $1)] conformTo: #'Character' selector: #'isLetter'. self value: [$: isLetter] shouldnt: [:r | r & (alphaChars includes: $:)] conformTo: #'Character' selector: #'isLetter'.! testXasUppercase " #asUppercase " #'Fundamental'. " If the receiver is equal to the value of a character literal in the receiver row of the following table, the result object must be equal to the value of the corresponding character literal in the result row. receiver $a - $z result $A - $Z An implemention may define other #asUppercase mappings. If the receiver does not correspond to a character in the receiver row of the table and does not have an implementation defined mapping the receiver is returned as the result. " self selector: #'asUppercase' inProtocol: #'Character' behavesLike: #( #($a $A) #($B $B) #($1 $1) #($: $:) )! testXisUppercase " #isUppercase " | upperChars | #'Fundamental'. upperChars := #( $A $B $C $D $E $F $G $H $I $J $K $L $M $N $O $P $Q $R $S $T $U $V $W $X $Y $Z ). self value: [$A isUppercase] should: [:r | r & (upperChars includes: $A)] conformTo: #'Character' selector: #'isUppercase'. self value: [$B isUppercase] should: [:r | r & (upperChars includes: $B)] conformTo: #'Character' selector: #'isUppercase'. self value: [$a isUppercase] shouldnt: [:r | r & (upperChars includes: $a)] conformTo: #'Character' selector: #'isUppercase'. self value: [$1 isUppercase] shouldnt: [:r | r & (upperChars includes: $1)] conformTo: #'Character' selector: #'isUppercase'. self value: [$: isUppercase] shouldnt: [:r | r & (upperChars includes: $:)] conformTo: #'Character' selector: #'isUppercase'.! protocol ^#Character! testXcodePoint " #codePoint " #'Fundamental'. " The following invariant must hold: (charFactory codePoint: x) codePoint = x where charFactory is an object that implements and x is an . " self value: [$a codePoint] should: [:r | (Character codePoint: r) codePoint = r] conformTo: #'Character' selector: #'codePoint'.! canonicalObject ^ Character space! testXisDigit " #isDigit " #'Fundamental'. self selector: #isDigit inProtocol: #Character behavesLike: #(#($1 true) #($A false) #($B false) #($b false) #($: false)).! testXisLowercase " #isLowercase " | lowerChars | #'Fundamental'. lowerChars := #( $a $b $c $d $e $f $g $h $i $j $k $l $m $n $o $p $q $r $s $t $u $v $w $x $y $z ). self value: [$a isLowercase] should: [:r | r & (lowerChars includes: $a)] conformTo: #'Character' selector: #'isLowercase'. self value: [$A isLowercase] shouldnt: [:r | r & (lowerChars includes: $A)] conformTo: #'Character' selector: #'isLowercase'. self value: [$B isLowercase] shouldnt: [:r | r & (lowerChars includes: $B)] conformTo: #'Character' selector: #'isLowercase'. self value: [$1 isLowercase] shouldnt: [:r | r & (lowerChars includes: $1)] conformTo: #'Character' selector: #'isLowercase'. self value: [$: isLowercase] shouldnt: [:r | r & (lowerChars includes: $:)] conformTo: #'Character' selector: #'isLowercase'.! ! !NotificationANSITest methodsFor: nil! testXresignalAsX " #resignalAs: " #'Exception'.! testXretryUsingX " #retryUsing: " #'Exception'.! testXmessageText " #messageText " #'Exception'.! testXresume " #resume " #'Exception'.! testXreturn " #return " #'Exception'.! testXresumeX " #resume: " #'Exception'.! testXreturnX " #return: " #'Exception'.! protocol ^#Notification! testXsignal " #signal " #'Exception'.! testXdescription " #description " #'Exception'.! testXsignalX " #signal: " #'Exception'.! testXtag " #tag " #'Exception'.! testXmessageTextX " #messageText: (Return Values: ) " #'Exception'.! testXouter " #outer " #'Exception'.! testXpass " #pass " #'Exception'.! testXretry " #retry " #'Exception'.! testXisResumable " #isResumable " #'Exception'. self value: [ [ Notification signal ] on: Notification do: [ :aNotification | aNotification return: aNotification isResumable ] ] should: [:r | r] conformTo: #'Notification' selector: #'isResumable'.! testXisNested " #isNested " #'Exception'.! canonicalObject ^Notification new! testXdefaultAction " #defaultAction " #'Exception'. self value: [Notification signal] should: [:r | r = nil] conformTo: #'Notification' selector: #'defaultAction'.! ! !ScaledDecimalANSITest methodsFor: nil! testXmultiplyOp " #* (returnRule - :receiver :operand) " | retVals tmpRec tmpResult | #'Numeric'. " #( 2 -2000000000 2000000000 2.0 1/2 2.0s3 )." retVals := #(4.0s3 -4000000000.0s3 4000000000.0s3 4.0 1 4.0s3). 1 to: numList size do: [ :ndx | self value: [sclDec2s3 * (numList at: ndx)] should: [:r | r = (retVals at: ndx)] conformTo: #'number' selector: #'*' ruleReceiver: sclDec2s3 operand: (numList at: ndx) ]. "If the return value conforms to then the scale of the result is at least the scale of the receiver after conversion if necessary." tmpRec := 26.5s2. tmpResult := tmpRec * 5.0s1. self should: [tmpResult = 132.50s2 & (tmpResult scale >= tmpRec scale)]. tmpRec := 26.5s2. tmpResult := tmpRec * 5.0s4. self should: [tmpResult = 132.5000s4 & (tmpResult scale >= tmpRec scale)]. tmpRec := -26.5s2. tmpResult := tmpRec * 5.0s4. self should: [tmpResult = -132.5000s4 & (tmpResult scale >= tmpRec scale)].! testXremX " #rem: " | num2 sd retVals ndx | #'Numeric'. "Within the limits of representation, the following invariant should hold: (receiver quo: operand)*operand + (receiver rem: operand) = receiver" " #( 2 -2000000000 2000000000 2.0 1/2 2.0s3 )." sd := 26.5s03. numList := #( 5 5.0 5.0s3 ). retVals := #( 1.500s3 1.5 1.500s3 ). ndx := 0. numList do: [ :num | ndx := ndx + 1. self value: [sd rem: num] should: [ :r | r = (retVals at: ndx) & ((sd quo: num) * num + (sd rem: num) = sd)] conformTo: #'number' selector: #'rem:' ]. numList := numList collect: [ :num | num negated ]. ndx := 0. numList do: [ :num | ndx := ndx + 1. self value: [sd rem: num] should: [ :r | r = (retVals at: ndx) & ((sd quo: num) * num + (sd rem: num) = sd)] conformTo: #'number' selector: #'rem:' ]. sd := -26.5s3. numList := #( 5 5.0 5.0s3 ). retVals := retVals collect: [ :num | num negated ]. ndx := 0. numList do: [ :num | ndx := ndx + 1. self should: [(sd rem: num) = (retVals at: ndx) & ((sd quo: num) * num + (sd rem: num) = sd)] ]. numList := numList collect: [ :num | num negated ]. ndx := 0. numList do: [ :num | ndx := ndx + 1. self should: [(sd rem: num) = (retVals at: ndx) & ((sd quo: num) * num + (sd rem: num) = sd)] ]. sd := 26.5s3. num2 := (5/2). self value: [sd rem: num2] should: [:r | r = 1.5s3 & ((sd quo: num2) * num2 + (sd rem: num2) = sd)] conformTo: #'number' selector: #'rem:'. numList := #( -2000000000 2000000000 ). sd := 10000000001.5s3. numList do: [ :num | self value: [sd rem: num] should: [:r | r = 1.5s3 & ((sd quo: num) * num + (sd rem: num) = sd)] conformTo: #'number' selector: #'rem:' ]. "If either the receiver or operand are of type and the operand has a value of zero, the result is implementation defined. The implementation may signal the ZeroDivide exception or provide a continuation value " self value: [sclDec2s3 rem: 0.0] shouldRaise: ZeroDivide. self value: [sclDec2s3 rem: 0] shouldRaise: ZeroDivide. self value: [sclDec2s3 rem: 0.0s3] shouldRaise: ZeroDivide.! testXgreaterThanOrEqualToOp " #>= " #'Numeric'. " #( 2 -2000000000 2000000000 2.0 1/2 2.0s3 )." #'todo'."It is erroneous if the receiver and operand are not comparable." self value: [5.1s1 >= 5.1s2] should: [:r | r] conformTo: #'magnitude' selector: #'>='. self value: [-5.1s1 >= -5.9s2] should: [:r | r] conformTo: #'magnitude' selector: #'>='. "Small >= Big -> false" #( 2 2000000000 2.0 2.0s3 ) do: [ :tstNum | self value: [0.3s3 >= tstNum] shouldnt: [:r | r] conformTo: #'magnitude' selector: #'>=' ]. self value: [-2000000005.0s3 >= -2000000000] shouldnt: [:r | r] conformTo: #'magnitude' selector: #'>='. self value: [0.25s3 >= (1/2)] shouldnt: [:r | r] conformTo: #'magnitude' selector: #'>='. "Num >= Num -> true" 1 to: numList size do: [ :ndx | self value: [(numList at: ndx) >= (numList at: ndx)] should: [:r | r ] conformTo: #'magnitude' selector: #'>=' ]. "Big >= Small -> true" #( 2 2.0 2.0s3 ) do: [ :tstNum | self value: [5.0s3 >= tstNum] should: [:r | r] conformTo: #'magnitude' selector: #'>=' ]. self value: [9000000000s3 >= 2000000000] should: [:r | r] conformTo: #'magnitude' selector: #'>='. self value: [-1000000005.0s3 >= -2000000000] should: [:r | r] conformTo: #'magnitude' selector: #'>='. self value: [9.0s3 >= (1/2)] should: [:r | r] conformTo: #'magnitude' selector: #'>='.! testXasFloatQ " #asFloatQ " #'Numeric'. self value: [2.0s3 asFloatQ] should: [:r | r = 2.0] conformTo: #'number' selector: #'asFloatQ'. self value: [-2.0s3 asFloatQ] should: [:r | r = -2.0] conformTo: #'number' selector: #'asFloatQ'. self value: [0.0s3 asFloatQ] should: [:r | r = 0.0] conformTo: #'number' selector: #'asFloatQ'.! protocol ^#'scaledDecimal'! testXasFloat " #asFloat " #'Numeric'. self value: [2.0s3 asFloat] should: [:r | r = 2.0] conformTo: #'number' selector: #'asFloat'. self value: [-2.0s3 asFloat] should: [:r | r = -2.0] conformTo: #'number' selector: #'asFloat'. self value: [0.0s3 asFloat] should: [:r | r = 0.0] conformTo: #'number' selector: #'asFloat'.! testXbetweenXandX " #between:and: " #'Numeric'. " #( 2 -2000000000 2000000000 2.0 1/2 2.0s3 )." #'todo'."It is erroneous if the receiver and min or max are not comparable" self value: [2.0s3 between: 1 and: 3] should: [:r | r] conformTo: #'magnitude' selector: #'between:and:'. self value: [-2000000002.0s3 between: -2000000003 and: -2000000001] should: [:r | r] conformTo: #'magnitude' selector: #'between:and:'. self value: [2000000002.0s3 between: 2000000001 and: 2000000003] should: [:r | r] conformTo: #'magnitude' selector: #'between:and:'. self value: [2.0s3 between: 1.0 and: 3.0] should: [:r | r] conformTo: #'magnitude' selector: #'between:and:'. self value: [2.0s3 between: (3/2) and: (5/2)] should: [:r | r] conformTo: #'magnitude' selector: #'between:and:'. self value: [2.0s3 between: 1.0s3 and: 3.0s3] should: [:r | r] conformTo: #'magnitude' selector: #'between:and:'. self value: [2.0s3 between: (3/2) and: 2000000003] should: [:r | r] conformTo: #'magnitude' selector: #'between:and:'. self value: [2.0s3 between: -2000000001 and: 3.0] should: [:r | r] conformTo: #'magnitude' selector: #'between:and:'. "Num between: Num and: Num -> true" 1 to: numList size do: [ :ndx | self value: [(numList at: ndx) between: (numList at: ndx) and: (numList at: ndx)] should: [:r | r] conformTo: #'magnitude' selector: #'between:and:' ]. self value: [2.0s3 between: 3 and: 4] shouldnt: [:r | r] conformTo: #'magnitude' selector: #'between:and:'. self value: [-2000000000.0s3 between: -2000000003 and: -2000000005] shouldnt: [:r | r] conformTo: #'magnitude' selector: #'between:and:'. self value: [2000000000.0s3 between: 2000000003 and: 2000000005] shouldnt: [:r | r] conformTo: #'magnitude' selector: #'between:and:'. self value: [2.0s3 between: 3.0 and: 5.0] shouldnt: [:r | r] conformTo: #'magnitude' selector: #'between:and:'. self value: [2.0s3 between: (5/2) and: (7/2)] shouldnt: [:r | r] conformTo: #'magnitude' selector: #'between:and:'. self value: [2.0s3 between: 3.0s3 and: 5.0s3] shouldnt: [:r | r] conformTo: #'magnitude' selector: #'between:and:'. "??? min not min but max and vice versa -> false ???" self value: [2.0s3 between: 3 and: 1] shouldnt: [:r | r] conformTo: #'magnitude' selector: #'between:and:'.! testXpositive " #positive " #'Numeric'. self value: [2.0s3 positive] should: [:r | r] conformTo: #'number' selector: #'positive'. self value: [0.0s3 positive] should: [:r | r] conformTo: #'number' selector: #'positive'. self value: [-2.0s3 positive] shouldnt: [:r | r] conformTo: #'number' selector: #'positive'.! testXreciprocal " #reciprocal (returnRule - :receiver) " #'Numeric'. self value: [sclDec2s3 reciprocal] should: [:r | r = (1.0s2/sclDec2s3)] conformTo: #'number' selector: #'reciprocal' ruleReceiver: sclDec2s3. self value: [sclDec2s3 negated reciprocal] should: [:r | r = (1.0s2/(sclDec2s3 negated))] conformTo: #'number' selector: #'reciprocal' ruleReceiver: (sclDec2s3 negated). "Signal a ZeroDivide exception if the receiver is equal to zero." self value: [0.0s2 reciprocal] shouldRaise: ZeroDivide.! testXtruncateToX " #truncateTo: (returnRule - :receiver :operand) " | retVals save | #'Numeric'. " #( 2 -2000000000 2000000000 2.0 1/2 2.0s3 )." retVals := #(2.000s3 0.000s3 0.000s3 2.0 2 2.000s3). 1 to: numList size do: [ :ndx | self value: [sclDec2s3 truncateTo: (numList at: ndx)] should: [:r | (save := r) = (retVals at: ndx)] conformTo: #'number' selector: #'truncateTo:' ruleReceiver: sclDec2s3 operand: (numList at: ndx) ]. self should: [((0 truncateTo: sclDec2s3) = 0s3) & (save scale = 3)].! testXnegated " #negated (Return Values: )" | rcvr | #'Numeric'. rcvr := 2.0s3. self value: [rcvr negated] should: [:r | r = -2.0s3] conformTo: #'number' selector: #'negated' opRECEIVER: rcvr. rcvr := -2.0s3. self value: [rcvr negated] should: [:r | r = 2.0s3] conformTo: #'number' selector: #'negated' opRECEIVER: rcvr. rcvr := 0.0s3. self value: [rcvr negated] should: [:r | r = 0s3] conformTo: #'number' selector: #'negated' opRECEIVER: rcvr.! testXcopy " #copy (Return Values: ) " #'Numeric'. " Return a new object that must be as similar as possible to the receiver in its initial state and behavior. Any operation that changes the state of the new object should not as a side-effect change the state or behavior of the receiver. Similarly, any change to the receiver should not as a side-effect change the new object. If the receiver is an identity object, return the receiver. " #todo. "??? add change-side-effect test ???" self value: [sclDec2s3 copy] should: [:r | (r = sclDec2s3) ] conformTo: #'Object' selector: #'copy' opRECEIVER: sclDec2s3.! testXintegerPart " #integerPart (returnRule - :receiver) " | rcvr | #'Numeric'. rcvr := 2.5s3. self value: [rcvr integerPart] should: [:result | result = 2.0s3] conformTo: #'number' selector: #'integerPart' ruleReceiver: rcvr. rcvr := 2.0s3. self value: [rcvr integerPart] should: [:r | r = 2.0s3] conformTo: #'number' selector: #'integerPart' ruleReceiver: rcvr. rcvr := -2.0s3. self value: [rcvr integerPart] should: [:result | result = -2.0s3] conformTo: #'number' selector: #'integerPart' ruleReceiver: rcvr. rcvr := 0.0s3. self value: [rcvr integerPart] should: [:result | result = 0s3] conformTo: #'number' selector: #'integerPart' ruleReceiver: rcvr.! testXraisedToX " #raisedTo: " | numVals retVals | #'Numeric'. numVals := #(2 2.0 0 2.0s3 ) copy. numVals at: 3 put: (1/2). retVals := #(4.000s3 4.0 1.414213562373095 4.0 ) copy. 1 to: numVals size do: [ :ndx | self value: [sclDec2s3 raisedTo: (numVals at: ndx)] should: [:r | r closeTo: (retVals at: ndx)] conformTo: #'number' selector: #'raisedTo:'. ]. retVals := #(0.250s3 0.25 0.7071067811865475 0.25 ) copy. 1 to: numVals size do: [ :ndx | self value: [sclDec2s3 raisedTo: ((numVals at: ndx) negated)] should: [:r | r closeTo: (retVals at: ndx)] conformTo: #'number' selector: #'raisedTo:' ]. self value: [sclDec2s3 raisedTo: 0.0s2] should: [:r | r = 1.0s2] conformTo: #'number' selector: #'raisedTo:'. self value: [0.0s2 raisedTo: sclDec2s3] should: [:r | r = 0.0s2] conformTo: #'number' selector: #'raisedTo:'. self value: [sclDec2s3 raisedTo: 1.0s2] should: [:r | r = sclDec2s3] conformTo: #'number' selector: #'raisedTo:'. "It is erroneous if the receiver equals zero and the operand is less than or equal to zero," self value: [0.0s2 raisedTo: -2.0s2] shouldRaise: Error. " or if the receiver is less than zero." self value: [sclDec2s3 negated raisedTo: 2.0s2] shouldRaise: Error.! testXasScaledDecimalX "2000/06/23 Harmon, R. Changed to fix illegal fixed point literals." self value: [2.0s3 asScaledDecimal: 3] should: [:r | r = 2.0s3 & (r scale = 3)] conformTo: #'number' selector: #'asScaledDecimal:'. self value: [-2.0s3 asScaledDecimal: 2] should: [:r | r = -2.0s2 & (r scale = 2)] conformTo: #'number' selector: #'asScaledDecimal:'. self value: [0.0s3 asScaledDecimal: 0] should: [:r | r = 0.0s1 & (r scale = 0)] conformTo: #'number' selector: #'asScaledDecimal:'.! testXtoX " #to: " | start middleNdx stop2 | #'Numeric'. start := 1.0s3. numList := #( 2 2.0 0 2.0s3 ) copy. numList at: 3 put: (5/2). numList do: [ :stop | self value: [start to: stop] should: [:r | (r size = 2) ". . . the last element in the sequence . . . is . . .[:] receiver + ((stop - receiver) // 1)" & (r last = (start + ((stop - start) // 1))) "The elements conform to the receiver's protocol." & (r allSatisfy: [ :elem | elem class conformsToProtocolNamed: #'scaledDecimal']) ] conformTo: #'number' selector: #'to:' ]. stop2 := 2000000000s3. middleNdx := 1000000000. "Check conformance of first, middle and last." self value: [start to: stop2] should: [:r | (r size = 2000000000) ". . . the last element in the sequence . . . is . . .[:] receiver + ((stop - receiver) // 1)" & (r last = (start + ((stop2 - start) // 1))) "The elements conform to the receiver's protocol." & ((Array with: (r at: 1) with: (r at: middleNdx) with: (r at: 3) ) allSatisfy: [ :elem | elem class conformsToProtocolNamed: #'scaledDecimal']) ] conformTo: #'number' selector: #'to:'. start := -2000000000.0s3. stop2 := -1s3. middleNdx := 1000000000. "Check conformance of first, middle and last." self value: [start to: stop2] should: [:r | (r size = 2000000000) ". . . the last element in the sequence . . . is . . .[:] receiver + ((stop - receiver) // 1)" & (r last = (start + ((stop2 - start) // 1))) "The elements conform to the receiver's protocol." & ((Array with: (r at: 1) with: (r at: middleNdx) with: (r at: 3) ) allSatisfy: [ :elem | elem class conformsToProtocolNamed: #'scaledDecimal']) ] conformTo: #'number' selector: #'to:'. "The interval answered will be empty if the receiver is greater than stop." self value: [1.0s3 to: -1.0s3] should: [:r | (r isEmpty)] conformTo: #'number' selector: #'to:'! testXtoXbyXdoX " #to:by:do: " #'Numeric'.! testXceiling " #ceiling " #'Numeric'. self value: [2.0s3 ceiling] should: [:r | r = 2] conformTo: #'number' selector: #'ceiling'. self value: [2.1s3 ceiling] should: [:r | r = 3] conformTo: #'number' selector: #'ceiling'. self value: [2.5s3 ceiling] should: [:r | r = 3] conformTo: #'number' selector: #'ceiling'. self value: [-2.0s3 ceiling] should: [:r | r = -2] conformTo: #'number' selector: #'ceiling'. self value: [-2.1s3 ceiling] should: [:r | r = -2] conformTo: #'number' selector: #'ceiling'. self value: [-2.5s3 ceiling] should: [:r | r = -2] conformTo: #'number' selector: #'ceiling'. self value: [0.0s3 ceiling] should: [:r | r = 0] conformTo: #'number' selector: #'ceiling'.! testXasFraction "2000/06/23 Harmon, R. Changed to fix illegal fixed point literals." self value: [2.0s3 asFraction] should: [:r | r = 2] conformTo: #'number' selector: #'asFraction'. self value: [-2.5s3 asFraction] should: [:r | r = (-5/2)] conformTo: #'number' selector: #'asFraction'. self value: [0.0s3 asFraction] should: [:r | r = 0] conformTo: #'number' selector: #'asFraction'. "Scale less than required to represent value:" self value: [0.25s2 asFraction] should: [:r | r = (1/4)] conformTo: #'number' selector: #'asFraction'.! testXlessThanOrEqualToOp " #<= " #'Numeric'. " #( 2 -2000000000 2000000000 2.0 1/2 2.0s3 )." #'todo'."It is erroneous if the receiver and operand are not comparable." self value: [5.1s1 <= 5.1s2] should: [:r | r] conformTo: #'magnitude' selector: #'<='. "Small <= Big -> true" #( 2 2000000000 2.0 2.0s3 ) do: [ :tstNum | self value: [0.3s3 <= tstNum] should: [:r | r] conformTo: #'magnitude' selector: #'<=' ]. self value: [-2000000005.0s3 <= -2000000000] should: [:r | r] conformTo: #'magnitude' selector: #'<='. self value: [0.25s3 <= (1/2)] should: [:r | r] conformTo: #'magnitude' selector: #'<='. "Num <= Num -> false" 1 to: numList size do: [ :ndx | self value: [(numList at: ndx) <= (numList at: ndx)] should: [:r | r ] conformTo: #'magnitude' selector: #'<=' ]. "Big <= Small -> false" #( 2 2.0 2.0s3 ) do: [ :tstNum | self value: [5.0s3 <= tstNum] shouldnt: [:r | r] conformTo: #'magnitude' selector: #'<=' ]. self value: [9000000000s3 <= 2000000000] shouldnt: [:r | r] conformTo: #'magnitude' selector: #'<='. self value: [-1000000005.0s3 <= -2000000000] shouldnt: [:r | r] conformTo: #'magnitude' selector: #'<='. self value: [9.0s3 <= (1/2)] shouldnt: [:r | r] conformTo: #'magnitude' selector: #'<='.! testXsign " #sign " #'Numeric'. self value: [2.0s3 sign] should: [:r | r = 1] conformTo: #'number' selector: #'sign'. self value: [0.0s3 sign] should: [:r | r = 0] conformTo: #'number' selector: #'sign'. self value: [-2.0s3 sign] should: [:r | r = -1] conformTo: #'number' selector: #'sign'.! testXsubtractOp " #- (returnRule - :receiver :operand) " | retVals tmpRec tmpResult | #'Numeric'. " #( 2 -2000000000 2000000000 2.0 1/2 2.0s3 )." retVals := #(0.0s3 2000000002.0s3 -1999999998.0s3 0.0 1.5s3 0.0s3). 1 to: numList size do: [ :ndx | self value: [sclDec2s3 - (numList at: ndx)] should: [:r | r = (retVals at: ndx)] conformTo: #'number' selector: #'-' ruleReceiver: sclDec2s3 operand: (numList at: ndx) ]. "If the return value conforms to then the scale of the result is at least the scale of the receiver after conversion if necessary." tmpRec := 26.5s2. tmpResult := tmpRec - 5.0s1. self should: [tmpResult = 21.50s2 & (tmpResult scale >= tmpRec scale)]. tmpRec := 26.5s2. tmpResult := tmpRec - 5.0s4. self should: [tmpResult = 21.5000s4 & (tmpResult scale >= tmpRec scale)]. tmpRec := -26.5s2. tmpResult := tmpRec - 5.0s4. self should: [tmpResult = -31.5000s4 & (tmpResult scale >= tmpRec scale)].! testXintegerDivideOp " #// " | retVals | #'Numeric'. " #( 2 -2000000000 2000000000 2.0 1/2 2.0s3 )." "The sign of the result is positive if the receiver and operand have the same sign, and negative if the signs are different." retVals := #(1 -1 0 1 4 1). 1 to: numList size do: [ :ndx | self value: [sclDec2s3 // (numList at: ndx)] should: [:r | r = (retVals at: ndx)] conformTo: #'number' selector: #'//'. ]. retVals := #(-1 0 -1 -1 -4 -1). 1 to: numList size do: [ :ndx | self value: [sclDec2s3 // ((numList at: ndx) negated)] should: [:r | r = (retVals at: ndx)] conformTo: #'number' selector: #'//' ]. self should: [25.5s3 // 5.1s3 = 5]. self should: [25.5s3 // 5 = 5]. self should: [25500000000.5s3 // 5000000000 = 5]. self should: [-25500000000.5s3 // -5000000000 = 5]. self should: [25.5s3 // (51/10) = 5]. self should: [25.5s3 // 5.1 = 5]. self value: [0s // sclDec2s3] should: [:r | r = 0s] conformTo: #'number' selector: #'//'. "If the operand has a value of zero the ZeroDivide exception is signaled." self value: [sclDec2s3 // 0s] shouldRaise: ZeroDivide.! testXdivideOp " #/ (returnRule - :receiver :operand) " | retVals tmpRec tmpResult | #'Numeric'. " #( 2 -2000000000 2000000000 2.0 1/2 2.0s3 )." retVals := #(1.0s3 -0.000000001s9 0.000000001s9 1.0 4 1.0s3). 1 to: numList size do: [ :ndx | self value: [sclDec2s3 / (numList at: ndx)] should: [:r | r = (retVals at: ndx)] conformTo: #'number' selector: #'/' ruleReceiver: sclDec2s3 operand: (numList at: ndx) ]. self value: [2.0s15 / -2000000000] should: [:r | r = -0.000000001000000s15] conformTo: #'number' selector: #'/' ruleReceiver: 2.0s15 operand: -2000000000. "If the return value conforms to then the scale of the result is at least the scale of the receiver after conversion if necessary." tmpRec := 26.5s2. tmpResult := tmpRec / 5.0s1. self should: [tmpResult = 5.30s2 & (tmpResult scale >= tmpRec scale)]. tmpRec := 26.5s2. tmpResult := tmpRec / 5.0s4. self should: [tmpResult = 5.3000s4 & (tmpResult scale >= tmpRec scale)]. tmpRec := -26.5s2. tmpResult := tmpRec / 5.0s4. self should: [tmpResult = -5.3000s4 & (tmpResult scale >= tmpRec scale)]. self value: [0.0s / sclDec2s3] should: [:r | r = 0.0s] conformTo: #'number' selector: #'/' ruleReceiver: sclDec2s3 operand: 0.0s. "The implementation must signal the ZeroDivide exception." self value: [sclDec2s3 / 0.0s] shouldRaise: ZeroDivide.! testXfloor " #floor " #'Numeric'. self value: [2.0s3 floor] should: [:r | r = 2] conformTo: #'number' selector: #'floor'. self value: [2.1s3 floor] should: [:r | r = 2] conformTo: #'number' selector: #'floor'. self value: [2.5s3 floor] should: [:r | r = 2] conformTo: #'number' selector: #'floor'. self value: [-2.0s3 floor] should: [:r | r = -2] conformTo: #'number' selector: #'floor'. self value: [-2.1s3 floor] should: [:r | r = -3] conformTo: #'number' selector: #'floor'. self value: [-2.5s3 floor] should: [:r | r = -3] conformTo: #'number' selector: #'floor'. self value: [0.0s3 floor] should: [:r | r = 0] conformTo: #'number' selector: #'floor'.! testXasFloatD " #asFloatD " #'Numeric'. self value: [2.0s3 asFloatD] should: [:r | r = 2.0] conformTo: #'number' selector: #'asFloatD'. self value: [-2.0s3 asFloatD] should: [:r | r = -2.0] conformTo: #'number' selector: #'asFloatD'. self value: [0.0s3 asFloatD] should: [:r | r = 0.0] conformTo: #'number' selector: #'asFloatD'.! testXequalityOp " #= " #'Numeric'. " receiver = comparand => receiver hash = comparand hash " self value: [sclDec2s3 = sclDec2s3] should: [:r | r & (sclDec2s3 hash = sclDec2s3 hash) ] conformTo: #'number' selector: #'='. self should: [5.1s2 = 5.1s1 & (5.1s2 hash = 5.1s1 hash)]. self value: [ sclDec2s3 = 2.1s3 ] shouldnt: [ :r | r | (sclDec2s3 hash = 2.1s3 hash) ] conformTo: #'number' selector: #'='. " #( 2 -2000000000 2000000000 2.0 1/2 2.0s3 )." self value: [ sclDec2s3 = 2 ] should: [ :r | r ifTrue: [ sclDec2s3 hash = 2 hash ] ifFalse: [ sclDec2s3 hash ~= 2 hash ] ] conformTo: #'number' selector: #'='. self value: [ -2000000000.0s3 = -2000000000 ] should: [ :r | r ifTrue: [ -2000000000.0s3 hash = -2000000000 hash ] ifFalse: [ -2000000000.0s3 hash ~= -2000000000 hash ] ] conformTo: #'number' selector: #'='. self value: [ 2000000000.0s3 = 2000000000 ] should: [ :r | r ifTrue: [ 2000000000.0s3 hash = 2000000000 hash ] ifFalse: [ 2000000000.0s3 hash ~= 2000000000 hash ] ] conformTo: #'number' selector: #'='. self value: [ sclDec2s3 = 2.0 ] should: [ :r | r ifTrue: [ sclDec2s3 hash = 2.0 hash ] ifFalse: [ sclDec2s3 hash ~= 2.0 hash ] ] conformTo: #'number' selector: #'='. self value: [ 2.5s3 = (5/2) ] should: [ :r | r ifTrue: [ 2.5s3 hash = (5/2) hash ] ifFalse: [ 2.5s3 hash ~= (5/2) hash ] ] conformTo: #'number' selector: #'='.! testXasInteger " #asInteger " #'Numeric'. self value: [2.0s3 asInteger] should: [:r | r = 2] conformTo: #'number' selector: #'asInteger'. self value: [2.1s3 asInteger] should: [:r | r = 2] conformTo: #'number' selector: #'asInteger'. self value: [2.5s3 asInteger] should: [:r | r = 3] conformTo: #'number' selector: #'asInteger'. self value: [-2.0s3 asInteger] should: [:r | r = -2] conformTo: #'number' selector: #'asInteger'. self value: [-2.1s3 asInteger] should: [:r | r = -2] conformTo: #'number' selector: #'asInteger'. self value: [-2.5s3 asInteger] should: [:r | r = -3] conformTo: #'number' selector: #'asInteger'. self value: [0.0s3 asInteger] should: [:r | r = 0] conformTo: #'number' selector: #'asInteger'.! testXmaxX " #max: " #'Numeric'. " #( 2 -2000000000 2000000000 2.0 1/2 2.0s3 )." #'todo'."It is erroneous if the receiver and operand are not comparable." self value: [2.0s3 max: 3] should: [:r | r = 3] conformTo: #'magnitude' selector: #'max:'. self value: [-3000000000.0s3 max: -2000000000] should: [:r | r = -2000000000] conformTo: #'magnitude' selector: #'max:'. self value: [2000000000.0s3 max: 2000000003] should: [:r | r = 2000000003] conformTo: #'magnitude' selector: #'max:'. self value: [2.0s3 max: 3.0] should: [:r | r = 3.0] conformTo: #'magnitude' selector: #'max:'. self value: [2.0s3 max: (5/2)] should: [:r | r = (5/2)] conformTo: #'magnitude' selector: #'max:'. self value: [2.0s3 max: 3.0s3] should: [:r | r = 3.0s3] conformTo: #'magnitude' selector: #'max:'. "Num max: Num -> Num" 1 to: numList size do: [ :ndx | self value: [(numList at: ndx) max: (numList at: ndx)] should: [:r | r = (numList at: ndx)] conformTo: #'magnitude' selector: #'max:' ].! testXgreaterThanOp " #> " #'Numeric'. " #( 2 -2000000000 2000000000 2.0 1/2 2.0s3 )." #'todo'."It is erroneous if the receiver and operand are not comparable." self value: [5.1s1 > 5.1s2] shouldnt: [:r | r] conformTo: #'number' selector: #'>'. self value: [-5.1s1 > -5.2s2] should: [:r | r] conformTo: #'number' selector: #'>'. "Small > Big -> false" #( 2 2000000000 2.0 2.0s3 ) do: [ :tstNum | self value: [0.3s3 > tstNum] shouldnt: [:r | r] conformTo: #'number' selector: #'>' ]. self value: [-2000000005.0s3 > -2000000000] shouldnt: [:r | r] conformTo: #'number' selector: #'>'. self value: [0.25s3 > (1/2)] shouldnt: [:r | r] conformTo: #'number' selector: #'>'. "Num > Num -> false" 1 to: numList size do: [ :ndx | self value: [(numList at: ndx) > (numList at: ndx)] shouldnt: [:r | r ] conformTo: #'number' selector: #'>' ]. "Big > Small -> true" #( 2 2.0 2.0s3 ) do: [ :tstNum | self value: [5.0s3 > tstNum] should: [:r | r] conformTo: #'number' selector: #'>' ]. self value: [9000000000s3 > 2000000000] should: [:r | r] conformTo: #'number' selector: #'>'. self value: [-1000000005.0s3 > -2000000000] should: [:r | r] conformTo: #'number' selector: #'>'. self value: [9.0s3 > (1/2)] should: [:r | r] conformTo: #'number' selector: #'>'.! testLiterals #'Numeric'. self should: [123s = 123s0]. self should: [123s = 123s0]. self should: [123s0 = 123s0]. self should: [123.0s = 123.0s1]. self should: [123s1 = 123.0s1]. self should: [123.0s1 = 123.0s1]. self should: [123.000s = 123.000s3]. self should: [123s3 = 123.000s3]. self should: [123.0s3 = 123.000s3]. self should: [123.00s3 = 123.000s3]. self should: [123.000s3 = 123.000s3].! testXroundToX " #roundTo: (returnRule - :receiver :operand) " | retVals save | #'Numeric'. " #( 2 -2000000000 2000000000 2.0 1/2 2.0s3 )." retVals := #(2.000s3 0.000s3 0.000s3 2.0 2 2.000s3). 1 to: numList size do: [ :ndx | self value: [sclDec2s3 roundTo: (numList at: ndx)] should: [:r | (save := r) = (retVals at: ndx)] conformTo: #'number' selector: #'roundTo:' ruleReceiver: sclDec2s3 operand: (numList at: ndx) ]. self should: [((0 roundTo: sclDec2s3) = 0s3) & (save scale = 3)]! testXsqrt "2000/06/23 Harmon, R. Changed to fix illegal fixed point literals." self value: [26s0 sqrt] should: [:r | r closeTo: 5.099019513592784] conformTo: #'number' selector: #'sqrt'. self value: [26.0s1 sqrt] should: [:r | r closeTo: 5.099019513592784] conformTo: #'number' selector: #'sqrt'. self value: [26.01s2 sqrt] should: [:r | r closeTo: 5.1] conformTo: #'number' selector: #'sqrt'. self value: [26.01s3 sqrt] should: [:r | r closeTo: 5.1] conformTo: #'number' selector: #'sqrt'. self value: [0.0s3 sqrt] should: [:r | r = 0.0] conformTo: #'number' selector: #'sqrt'! testXabs " #abs (Return Values: ) " | rcvr | #'Numeric'. rcvr := 2.0s3. self value: [rcvr abs] should: [:r | r = 2.0s3] conformTo: #'number' selector: #'abs' opRECEIVER: rcvr. rcvr := 2.0s3. self value: [rcvr abs] should: [:r | r = 2.0s3] conformTo: #'number' selector: #'abs' opRECEIVER: rcvr. rcvr := 0.0s3. self value: [rcvr abs] should: [:r | r = 0s3] conformTo: #'number' selector: #'abs' opRECEIVER: rcvr.! setUp super setUp. smallInt2 := 2. largeNegInt2000000000 := -2000000000. largePosInt2000000000 := 2000000000. float2 := 2.0d0. fractionHalf := 1/2. sclDec2s3 := 2.0s3. numList := Array new: 6. numList at: 1 put: smallInt2. numList at: 2 put: largeNegInt2000000000. numList at: 3 put: largePosInt2000000000. numList at: 4 put: float2. numList at: 5 put: fractionHalf. numList at: 6 put: sclDec2s3.! testXremainderIntegerDivideOp " #\\ (returnRule - :receiver :operand) " "The remainder has the same sign as operand. Within the limits of representation, the following invariant should hold: (receiver // operand) * operand + (receiver \\ operand) = receiver " | retVals recList ndx tmpRec tmpResult | #'Numeric'. " #( 2 -2000000000 2000000000 2.0 1/2 2.0s3 )." recList := #( 26 -26000000001 26000000001 26.0 0 26.0s3 ) copy. recList at: 5 put: (53/2). retVals := #(1.0s3 4.0s3 1.0s3 1.0 0 1.0s3 ) copy. retVals at: 5 put: (3/2). ndx := 0. recList do: [ :rec | ndx := ndx + 1. self value: [rec \\ 5.0s3] should: [:r | r = (retVals at: ndx) & ((rec // 5.0s3) * 5.0s3 + (rec \\ 5.0s3) = rec)] conformTo: #'number' selector: #'\\' ruleReceiver: rec operand: 5.0s3. ]. "The remainder has the same sign as operand." retVals := #(-4.0s3 -1.0s3 -4.0s3 -4.0 0 -4.0s3 ) copy. retVals at: 5 put: (-7/2). ndx := 0. recList do: [ :rec | ndx := ndx + 1. self value: [rec \\ -5.0s3] should: [:r | r = (retVals at: ndx) & ((rec // -5.0s3) * -5.0s3 + (rec \\ -5.0s3) = rec)] conformTo: #'number' selector: #'\\' ruleReceiver: rec operand: -5.0s3. ]. self should: [26.5s3 \\ 5.0s3 = 1.5s3 & ((26.5s3 // 5.0s3) * 5.0s3 + (26.5s3 \\ 5.0s3) = 26.5s3)]. self should: [26.5s3 \\ -5.0s3 = -3.5s3 & ((26.5s3 // -5.0s3) * -5.0s3 + (26.5s3 \\ -5.0s3) = 26.5s3)]. "If the return value conforms to then the scale of the result is at least the scale of the receiver after conversion if necessary." tmpRec := 26.5s2. tmpResult := tmpRec \\ 5.0s1. self should: [tmpResult = 1.50s2 & (tmpResult scale >= tmpRec scale)]. tmpRec := 26.5s2. tmpResult := tmpRec \\ 5.0s4. self should: [tmpResult = 1.5000s4 & (tmpResult scale >= tmpRec scale)]. tmpRec := -26.5s2. tmpResult := tmpRec \\ 5.0s4. self should: [tmpResult = 3.5000s4 & (tmpResult scale >= tmpRec scale)]. self should: [0.0s3 \\ sclDec2s3 = 0.0s3]. "If the operand is zero, the implementation may signal the ZeroDivide exception or provide a continuation value." self value: [sclDec2s3 \\ 0.0s3] shouldRaise: ZeroDivide.! testXscale " #scale " #'Numeric'.! testXprintString " #printString " #'Numeric'. #'todo'."??? Uncommented fails--compiler error?. self value: [26.5s0 printString] should: [:r | r = '26s0'] conformTo: #'number' selector: #'printString'. self value: [26.5s1 printString] should: [:r | r = '26.5s1'] conformTo: #'number' selector: #'printString'. self value: [26.5s2 printString] should: [:r | r = '26.50s2'] conformTo: #'number' selector: #'printString'. " self value: [26.5s3 printString] should: [:r | r = '26.500s3'] conformTo: #'number' selector: #'printString'. self value: [-26.5s1 printString] should: [:r | r = '-26.5s1'] conformTo: #'number' selector: #'printString'. self value: [0.00s printString] should: [:r | r = '0.00s2'] conformTo: #'number' selector: #'printString'.! testXstrictlyPositive " #strictlyPositive " #'Numeric'. self value: [2.0s3 strictlyPositive] should: [:r | r] conformTo: #'number' selector: #'strictlyPositive'. self value: [0.0s3 strictlyPositive] shouldnt: [:r | r] conformTo: #'number' selector: #'strictlyPositive'. self value: [-2.0s3 strictlyPositive] shouldnt: [:r | r] conformTo: #'number' selector: #'strictlyPositive'.! canonicalObject ^sclDec2s3! testXtruncated " #truncated " #'Numeric'. self value: [2.0s3 truncated] should: [:r | r = 2] conformTo: #'number' selector: #'truncated'. self value: [2.1s3 truncated] should: [:r | r = 2] conformTo: #'number' selector: #'truncated'. self value: [2.5s3 truncated] should: [:r | r = 2] conformTo: #'number' selector: #'truncated'. self value: [-2.0s3 truncated] should: [:r | r = -2] conformTo: #'number' selector: #'truncated'. self value: [-2.1s3 truncated] should: [:r | r = -2] conformTo: #'number' selector: #'truncated'. self value: [-2.5s3 truncated] should: [:r | r = -2] conformTo: #'number' selector: #'truncated'. self value: [0.0s3 truncated] should: [:r | r = 0] conformTo: #'number' selector: #'truncated'.! testXminX " #min: " #'Numeric'. " #( 2 -2000000000 2000000000 2.0 1/2 2.0s3 )." #'todo'."It is erroneous if the receiver and operand are not comparable." self value: [2.0s3 min: 1] should: [:r | r = 1] conformTo: #'magnitude' selector: #'min:'. self value: [-1000000000.0s3 min: -2000000000] should: [:r | r = -2000000000] conformTo: #'magnitude' selector: #'min:'. self value: [2000000003.0s3 min: 2000000001] should: [:r | r = 2000000001] conformTo: #'magnitude' selector: #'min:'. self value: [2.0s3 min: 1.0] should: [:r | r = 1.0] conformTo: #'magnitude' selector: #'min:'. self value: [2.0s3 min: (3/2)] should: [:r | r = (3/2)] conformTo: #'magnitude' selector: #'min:'. self value: [2.0s3 min: 1.0s5] should: [:r | r = 1.0s5] conformTo: #'magnitude' selector: #'min:'. "Num min: Num -> Num" 1 to: numList size do: [ :ndx | self value: [(numList at: ndx) min: (numList at: ndx)] should: [:r | r = (numList at: ndx)] conformTo: #'magnitude' selector: #'min:' ].! testXsquared " #squared (Return Values: )" | rcvr | #'Numeric'. rcvr := 5.1s3. self value: [rcvr squared] should: [:r | (r = 26.010s3) & (r scale = 3)] conformTo: #'number' selector: #'squared' opRECEIVER: rcvr. #'todo'."??? Uncommented fails--compiler error?. rcvr := -5.1s3. self value: [rcvr squared] should: [:r | (r = 26.010s3) & (r scale = 3)] conformTo: #'number' selector: #'squared' opRECEIVER: rcvr. rcvr := 5.1s2. self value: [rcvr squared] should: [:r | (r = 26.01s2) & (r scale = 2)] conformTo: #'number' selector: #'squared' opRECEIVER: rcvr. rcvr := 5.1s1. self value: [rcvr squared] should: [:r | (r = 26.0s1) & (r scale = 1)] conformTo: #'number' selector: #'squared' opRECEIVER: rcvr. self halt. rcvr := 5.1s0. self value: [rcvr squared] should: [:r | (r = 26.010s3) & (r scale = 0)] conformTo: #'number' selector: #'squared' opRECEIVER: rcvr. rcvr := 0.0s3. self value: [rcvr squared] should: [:r | (r = 0.000s3) & (r scale = 3)] conformTo: #'number' selector: #'squared' opRECEIVER: rcvr. "! testXtoXbyX " #to:by: " #'Numeric'.! testXaddOp " #+ (returnRule - :receiver :operand) " | retVals tmpRec tmpResult | #'Numeric'. " #( 2 -2000000000 2000000000 2.0 1/2 2.0s3 )." retVals := #(4.0s3 -1999999998.0s3 2000000002.0s3 4.0 0 4.0s3) copy. retVals at: 5 put: (5/2). 1 to: numList size do: [ :ndx | self value: [sclDec2s3 + (numList at: ndx)] should: [:r | r = (retVals at: ndx)] conformTo: #'number' selector: #'+' ruleReceiver: sclDec2s3 operand: (numList at: ndx) ]. "If the return value conforms to then the scale of the result is at least the scale of the receiver after conversion if necessary." tmpRec := 26.5s2. tmpResult := tmpRec + 5.0s1. self should: [tmpResult = 31.50s2 & (tmpResult scale >= tmpRec scale)]. tmpRec := 26.5s2. tmpResult := tmpRec + 5.0s4. self should: [tmpResult = 31.5000s4 & (tmpResult scale >= tmpRec scale)]. tmpRec := -26.5s2. tmpResult := tmpRec + 5.0s4. self should: [tmpResult = -21.5000s4 & (tmpResult scale >= tmpRec scale)].! testXquoX " #quo: " | retVals | #'Numeric'. " #( 2 -2000000000 2000000000 2.0 1/2 2.0s3 )." retVals := #( 1 0 0 1 4 1 ). 1 to: numList size do: [ :ndx | self value: [sclDec2s3 quo: (numList at: ndx)] should: [:r | r = (retVals at: ndx)] conformTo: #'number' selector: #'quo:'. ]. retVals := #( -1 0 0 -1 -4 -1 ). 1 to: numList size do: [ :ndx | self value: [sclDec2s3 quo: ((numList at: ndx) negated)] should: [:r | r = (retVals at: ndx)] conformTo: #'number' selector: #'quo:' ]. self should: [(25.5s3 quo: 5.1s3) = 5]. self should: [(25.5s3 quo: 5) = 5]. self should: [(25500000000.5s3 quo: 5000000000) = 5]. self should: [(-25500000000.5s3 quo: -5000000000) = 5]. self should: [(25.5s3 quo: (51/10)) = 5]. self should: [(25.5s3 quo: 5.1) = 5]. self value: [0s quo: sclDec2s3] should: [:r | r = 0s] conformTo: #'number' selector: #'quo:'. "If the operand has a value of zero the ZeroDivide exception is signaled." self value: [sclDec2s3 quo: 0s] shouldRaise: ZeroDivide.! testXrounded " #rounded " #'Numeric'. self value: [2.0s3 rounded] should: [:r | r = 2] conformTo: #'number' selector: #'rounded'. self value: [2.1s3 rounded] should: [:r | r = 2] conformTo: #'number' selector: #'rounded'. self value: [2.5s3 rounded] should: [:r | r = 3] conformTo: #'number' selector: #'rounded'. self value: [-2.0s3 rounded] should: [:r | r = -2] conformTo: #'number' selector: #'rounded'. self value: [-2.1s3 rounded] should: [:r | r = -2] conformTo: #'number' selector: #'rounded'. self value: [-2.5s3 rounded] should: [:r | r = -3] conformTo: #'number' selector: #'rounded'. self value: [0.0s3 rounded] should: [:r | r = 0] conformTo: #'number' selector: #'rounded'.! testXlessThanOp " #< " #'Numeric'. " #( 2 -2000000000 2000000000 2.0 1/2 2.0s3 )." #'todo'."It is erroneous if the receiver and operand are not comparable." self value: [5.1s1 < 5.1s2] shouldnt: [:r | r] conformTo: #'number' selector: #'<'. "Small < Big -> true" #( 2 2000000000 2.0 2.0s3 ) do: [ :tstNum | self value: [0.3s3 < tstNum] should: [:r | r] conformTo: #'number' selector: #'<' ]. self value: [-2000000005.0s3 < -2000000000] should: [:r | r] conformTo: #'number' selector: #'<'. self value: [0.25s3 < (1/2)] should: [:r | r] conformTo: #'number' selector: #'<'. "Num < Num -> false" 1 to: numList size do: [ :ndx | self value: [(numList at: ndx) < (numList at: ndx)] shouldnt: [:r | r ] conformTo: #'number' selector: #'<' ]. "Big < Small -> false" #( 2 2.0 2.0s3 ) do: [ :tstNum | self value: [5.0s3 < tstNum] shouldnt: [:r | r] conformTo: #'number' selector: #'<' ]. self value: [9000000000s3 < 2000000000] shouldnt: [:r | r] conformTo: #'number' selector: #'<'. self value: [-1000000005.0s3 < -2000000000] shouldnt: [:r | r] conformTo: #'number' selector: #'<'. self value: [9.0s3 < (1/2)] shouldnt: [:r | r] conformTo: #'number' selector: #'<'.! testXtoXdoX " #to:do: " #'Numeric'.! testXfractionPart " #fractionPart (Return Values: )" | rcvr | #'Numeric'. "Within the limits of representation, the following invariants should hold: receiver integerPart + receiver fractionPart = receiver receiver \\1 = receiver fractionPart (RAH - erroneous, add #'abs') " rcvr := 26.5s3. self value: [rcvr fractionPart] should: [:r | r = 0.5s3 & (rcvr integerPart + rcvr fractionPart = rcvr) & (rcvr \\ 1 = rcvr fractionPart abs)] conformTo: #'number' selector: #'fractionPart' opRECEIVER: rcvr. rcvr := -26.5s3. self value: [rcvr fractionPart] should: [:r | r = -0.5s3 & (rcvr integerPart + rcvr fractionPart = rcvr) & (rcvr \\ 1 = rcvr fractionPart abs)] conformTo: #'number' selector: #'fractionPart' opRECEIVER: rcvr. rcvr := 0.0s3. self value: [rcvr fractionPart] should: [:r | r = 0s3 & (rcvr integerPart + rcvr fractionPart = rcvr) & (rcvr \\ 1 = rcvr fractionPart abs)] conformTo: #'number' selector: #'fractionPart' opRECEIVER: rcvr. rcvr := 0.0s3. self value: [rcvr fractionPart] should: [:r | r = 0s3 & (rcvr integerPart + rcvr fractionPart = rcvr) & (rcvr \\ 1 = rcvr fractionPart abs)] conformTo: #'number' selector: #'fractionPart' opRECEIVER: rcvr.! testXraisedToIntegerX "2000/06/23 Harmon, R. Changed to fix illegal fixed point literals." | rcvr | rcvr := 5.1s2. self value: [rcvr raisedToInteger: 0] should: [:r | r = 1.0s2] conformTo: #'number' selector: #'raisedToInteger:' opRECEIVER: rcvr. self value: [rcvr raisedToInteger: 1] should: [:r | r = rcvr] conformTo: #'number' selector: #'raisedToInteger:' opRECEIVER: rcvr. self value: [rcvr raisedToInteger: 2] should: [:r | r = 26.01s2] conformTo: #'number' selector: #'raisedToInteger:' opRECEIVER: rcvr. self value: [rcvr negated raisedToInteger: 2] should: [:r | r = 26.01s2] conformTo: #'number' selector: #'raisedToInteger:' opRECEIVER: rcvr. self value: [rcvr raisedToInteger: -2] should: [:r | r = 0.0384467512495194s16] conformTo: #'number' selector: #'raisedToInteger:' opRECEIVER: rcvr. "It is erroneous if the operand does not conform to the protocol ." self value: [rcvr raisedToInteger: 2.0s2] shouldRaise: Error. self value: [0.0s2 raisedToInteger: -2] shouldRaise: ZeroDivide.! testXasFloatE " #asFloatE " #'Numeric'. self value: [2.0s3 asFloatE] should: [:r | r = 2.0] conformTo: #'number' selector: #'asFloatE'. self value: [-2.0s3 asFloatE] should: [:r | r = -2.0] conformTo: #'number' selector: #'asFloatE'. self value: [0.0s3 asFloatE] should: [:r | r = 0.0] conformTo: #'number' selector: #'asFloatE'.! testXnegative " #negative " #'Numeric'. self value: [-2.0s3 negative] should: [:r | r] conformTo: #'number' selector: #'negative'. self value: [2.0s3 negative] shouldnt: [:r | r] conformTo: #'number' selector: #'negative'. self value: [0.0s3 negative] shouldnt: [:r | r] conformTo: #'number' selector: #'negative'.! ! !CollectionHelper methodsFor: nil! testXasOrderedCollection " #asOrderedCollection " #'Collection'. self assertSend: #asOrderedCollection! testXasByteArray " #asByteArray " #'Collection'. self assertSend: #asByteArray! testXasBag " #asBag " #'Collection'. self assertSend: #asBag! testXoccurrencesOfX " #occurrencesOf: " #'Collection'. self value: [self canonicalObject occurrencesOf: self canonicalElement] should: [:result | result = 1] conformTo: #'collection' selector: #'occurrencesOf:'. self value: [self canonicalObject occurrencesOf: 'Zornfindel'] should: [:result | result = 0] conformTo: #'collection' selector: #'occurrencesOf:'. self value: [self emptyCollection occurrencesOf: 'Zornfindel'] should: [:result | result = 0] conformTo: #'collection' selector: #'occurrencesOf:'! testXallSatisfyX " #allSatisfy: " #'Collection'. self value: [self canonicalObject allSatisfy: [:each | true]] should: [:result | result] conformTo: #'collection' selector: #'allSatisfy:'. self value: [self canonicalObject allSatisfy: [:each | false]] shouldnt: [:result | result] conformTo: #'collection' selector: #'allSatisfy:'. self value: [(self canonicalObject reject: [:each | each = self canonicalElement]) allSatisfy: [:each | each ~= self canonicalElement]] should: [:result | result] conformTo: #'collection' selector: #'allSatisfy:'. self value: [self emptyCollection allSatisfy: [:each | true]] should: [:result | result] conformTo: #'collection' selector: #'allSatisfy:'. "self value: [self canonicalObject allSatisfy: [:each | nil]] shouldRaise: TestResult error"! testXrejectX " #reject: (Return Values: )" #'Collection'. self value: [self canonicalObject reject: [:each | each = self canonicalElement]] should: [:result | (result includes: self canonicalElement) not] conformTo: #'collection' selector: #'reject:'. "Test empty class." self value: [self emptyCollection reject: [:each | true]] should: [:result | result isEmpty] conformTo: #'collection' selector: #'reject:'. "self value: [self canonicalObject reject: [:each | nil]] shouldRaise: TestResult error" self value: [self canonicalObject reject: [:each | each gobbledegook]] shouldRaise: TestResult error! object ^testCase canonicalObject! emptyCollection ^testCase emptyCollection! object: anObject! testXnotEmpty " #notEmpty " #'Collection'. self assertSend: #notEmpty! testXasSortedCollectionX " #asSortedCollection: " #'Collection'. self value: [self canonicalObject asSortedCollection: [:a :b | b < a]] should: [:result | result size = self canonicalObject size] conformTo: #'collection' selector: #'asSortedCollection:'. self value: [self emptyCollection asSortedCollection: [:a :b | b < a]] should: [:result | result size = self emptyCollection size] conformTo: #'collection' selector: #'asSortedCollection:'. "Test a garbage message for any parameter passed into the block." self value: [self canonicalObject asSortedCollection: [:a :b | a gobbledegook]] shouldRaise: TestResult error! testXselectX " #select: (Return Values: )" #'Collection'. self value: [self canonicalObject select: [:each | each ~= self canonicalElement]] should: [:result | (result includes: self canonicalElement) not] conformTo: #'collection' selector: #'select:'. "Test empty class." self value: [self emptyCollection select: [:each | true]] should: [:result | result isEmpty] conformTo: #'collection' selector: #'select:'. "self value: [self canonicalObject select: [:each | nil]] shouldRaise: TestResult error." self value: [self canonicalObject select: [:each | each gobbledegook]] shouldRaise: TestResult error! testXrehash " #rehash " #'Collection'. self assertSend: #rehash! testXcollectX " #collect: (Return Values: )" #'Collection'. self value: [self canonicalObject collect: [:each | each ]] should: [:result | result size = self canonicalObject size] conformTo: #'collection' selector: #'collect:'. "Test empty class." self value: [self emptyCollection collect: [:each | true]] should: [:result | result isEmpty] conformTo: #'collection' selector: #'collect:'. self returnTypeHasLimitedElementTypes ifTrue: [self value: [self canonicalObject collect: [:each | self limitedElementTypes]] shouldRaise: TestResult error]. self value: [self canonicalObject collect: [:each | each gobbledegook]] shouldRaise: TestResult error.! testXasSortedCollection " #asSortedCollection " #'Collection'. self assertSend: #asSortedCollection! testXdetectX " #detect: " self value: [self canonicalObject detect: [:each | each = self canonicalElement]] should: [:result | result = self canonicalElement] conformTo: #'collection' selector: #'detect:'. "Test empty class. What is the appropriate behavior for sending detect: to an empty collection? Both VA and VW raise element not found errors." self value: [self emptyCollection detect: [:each | true]] shouldRaise: TestResult error. "self value: [self canonicalObject detect: [:each | nil]] shouldRaise: TestResult error." self value: [self canonicalObject detect: [:each | false]] shouldRaise: TestResult error. self value: [self canonicalObject detect: [:each | each gobbledegook]] shouldRaise: TestResult error! testXasSet " #asSet " #'Collection'. self assertSend: #asSet! returnTypeHasLimitedElementTypes ^testCase returnTypeHasLimitedElementTypes! testXisEmpty " #isEmpty " #'Collection'. self assertSend: #isEmpty! testXanySatisfyX " #anySatisfy: " #'Collection'. self value: [self canonicalObject anySatisfy: [:each | each = self canonicalElement]] should: [:result | result] conformTo: #'collection' selector: #'anySatisfy:'. self value: [self canonicalObject anySatisfy: [:each | false]] shouldnt: [:result | result] conformTo: #'collection' selector: #'anySatisfy:'. self value: [(self canonicalObject reject: [:each | each = self canonicalElement]) anySatisfy: [:each | each = self canonicalElement]] shouldnt: [:result | result] conformTo: #'collection' selector: #'anySatisfy:'! testXdoXseparatedByX " #do:separatedBy: " #'Collection'. self value: [self canonicalObject do: [:each |] separatedBy: []] should: [:result | "The ANSI Standard states that the return is UNSPECIFIED. So, any return is valid." true] conformTo: #'collection' selector: #'do:separatedBy:'. "Send message that causes an error in the do: loop." self value: [self canonicalObject do: [:each | each gobbledegook] separatedBy: []] shouldRaise: TestResult error. "Send message that causes an error in the separatedBy: loop." self value: [self canonicalObject do: [:each |] separatedBy: [self gobbledegook]] shouldRaise: TestResult error. self value: [self emptyCollection do: [:each |] separatedBy: []] should: [:result | "The ANSI Standard states that the return is UNSPECIFIED. So, any return is valid." true] conformTo: #'collection' selector: #'do:separatedBy:'.! testXinjectXintoX " #inject:into: " #'Collection'. self value: [self canonicalObject inject: 1 into: [:value :each | (each printString at: 1) asInteger * value]] should: [:result | result > 0] conformTo: #'collection' selector: #'inject:into:'. self value: [self emptyCollection inject: 1 into: [:value :each | (each printString at: 1) asInteger * value]] should: [:result | result > 0] conformTo: #'collection' selector: #'inject:into:'! testXsize " #size " #'Collection'. self assertSend: #size! testXdetectXifNoneX " #detect:ifNone: " #'Collection'. self value: [self canonicalObject detect: [:each | each = self canonicalElement] ifNone: [nil]] should: [:result | result = self canonicalElement] conformTo: #'collection' selector: #'detect:ifNone:'. "Test empty class. What is the appropriate behavior for sending detect: to an empty collection? Both VA and VW raise element not found errors." self value: [self emptyCollection detect: [:each | true] ifNone: [#NotFound]] should: [:result | result == #NotFound] conformTo: #collection selector: #'detect:ifNone:'. "self value: [self canonicalObject detect: [:each | nil] ifNone: [nil]] shouldRaise: TestResult error." self value: [self canonicalObject detect: [:each | false] ifNone: [#NotFound]] should: [:result | result == #NotFound] conformTo: #'collection' selector: #'detect:ifNone:'. self value: [self canonicalObject detect: [:each | each gobbledegook] ifNone: []] shouldRaise: TestResult error. self value: [self canonicalObject detect: [:each | false] ifNone: [self gobbledegook]] shouldRaise: TestResult error.! canonicalElement ^testCase canonicalElement! testXasArray " #asArray " #'Collection'. self assertSend: #asArray! limitedElementTypes ^testCase limitedElementTypes! testXdoX " #do: " #'Collection'. self value: [self canonicalObject do: [:each |]] should: [:result | "The ANSI Standard states that the return is UNSPECIFIED. So, any return is valid." true] conformTo: #'collection' selector: #'do:'. self value: [self emptyCollection do: [:each |]] should: [:result | "The ANSI Standard states that the return is UNSPECIFIED. So, any return is valid." true] conformTo: #'collection' selector: #'do:'. "Send message that causes an error in the do: loop." self value: [self canonicalObject do: [:each | each gobbledegook]] shouldRaise: TestResult error.! canonicalObject ^testCase canonicalObject! testXincludesX " #includes: " #'Collection'. self value: [self canonicalObject includes: self canonicalElement] should: [:result | result] conformTo: #'collection' selector: #'includes:'. self value: [self canonicalObject includes: 'Zornfindel'] shouldnt: [:result | result] conformTo: #'collection' selector: #'includes:'. self value: [self emptyCollection includes: 'Zornfindel'] shouldnt: [:result | result] conformTo: #'collection' selector: #'includes:'! ! !CollectionHelper class methodsFor: nil! initialize "CollectionHelper initialize" super initialize! ! !SequencedStreamHelper methodsFor: nil! testXclose #todo."Don't know how to check this: If the receiver is a write-back stream update its stream backing store as if the message #flush was sent to the receiver. Then eliminate any association between the receiver and its stream backing store. Any system resources associated with the association should be released. The effect of sending any message to the receiver subsequent to this message is undefined. " self assertSend: #close! object: anObject! testXcontents #todo."Don't know how to check this:" self value: [self canonicalObject contents] should: [:r | r = 'this is a string' & r size = self canonicalObject size] conformTo: self protocol selector: #'contents'.! testXpositionX "Errors: If the receiver has any sequence values and amount is greater than or equal to the total number of sequence values of the receiver." self value: [self canonicalObject position: 99] shouldRaise: Error. self canonicalObject position: 4. "past sequence values smaller than amount:" self value: [self canonicalObject position: 6] should: [:r | true "UNSPECIFIED"] conformTo: self protocol selector: #'position:'. "past sequence values greater than amount:" self value: [self canonicalObject position: 2] should: [:r | true "UNSPECIFIED"] conformTo: self protocol selector: #'position:'. "receiver's past sequence values is equal to amount:" self value: [self canonicalObject position: 2] should: [:r | true "UNSPECIFIED"] conformTo: self protocol selector: #'position:'. "Errors: If amount is negative." self value: [self canonicalObject position: -1] shouldRaise: Error.! testXposition self canonicalObject reset. self value: [self canonicalObject position] should: [:r | r = 0] conformTo: self protocol selector: #'position'.! testXreset self value: [self canonicalObject reset] should: [:r | "r UNSPECIFIED" self canonicalObject position = 0] conformTo: self protocol selector: #'reset'. self value: [self canonicalObject reset] should: [:r | "r UNSPECIFIED" self canonicalObject position = 0] conformTo: self protocol selector: #'reset'.! testXsetToEnd self value: [self canonicalObject setToEnd] should: [:r | "r UNSPECIFIED" self canonicalObject position = self canonicalObject contents size] conformTo: self protocol selector: #'setToEnd'.! object ^testCase canonicalObject! canonicalObject ^testCase canonicalObject! testXisEmpty self value: [self canonicalObject isEmpty] shouldnt: [:r | r] conformTo: self protocol selector: #'isEmpty'.! ! !SequencedStreamHelper class methodsFor: nil! initialize "SequencedStreamHelper initialize" super initialize! ! !ReadWriteStreamFactoryANSITest methodsFor: nil! protocol ^#'ReadWriteStream factory'! canonicalObject ^ReadWriteStream! testXwithX self value: [self canonicalObject with: 'this is a string'] should: [:r | r position = 'this is a string' size & r contents = 'this is a string'] conformTo: self protocol selector: #'with:'.! ! !MsgParmSpec methodsFor: nil! printOn: targetStream "Append to targetStream a text representation of the receiver as a developer would want to see it (inspector, etc)." targetStream nextPutAll: self class name; nextPut: $(; nextPutAll: self parmName; space. self parmProtocolNames do: [:protocolName | targetStream nextPut: $<; nextPutAll: protocolName; nextPut: $>] separatedBy: [targetStream nextPutAll: '|']. targetStream space; nextPutAll: self parmAliasingAttribute; nextPut: $)! setParmName: name protocolNames: protocolNames aliasing: aliasingAttribute "Private - ." parmName := name. parmProtocols := protocolNames. parmAliasingAttribute := aliasingAttribute! storeSIFOn: targetStream "Append to targetStream, a , the ASCII representation of the receiver in SIF from which the receiver can be rebuilt but NOT reinstantiated via evaluate." #todo."??? Find better way to keep SIF knowledge out of model ???" targetStream nextPutAll: '#('. parmName asString printOn: targetStream. targetStream space; nextPut: $'. parmProtocols do: [:protocolName | targetStream nextPutAll: protocolName asString] separatedBy: [targetStream space]. targetStream nextPut: $'. targetStream nextPutAll: ' #'. parmAliasingAttribute asString printOn: targetStream. targetStream nextPutAll: ')'! parmName "Answer the protocol message parameter specification parameter name." ^ parmName! parmAliasingAttribute "Answer the protocol message parameter specification parameter aliasing attribute." ^ parmAliasingAttribute! parmProtocolNames "Answer the protocol names this protocol message parameter specification conforms to. Note: The protocol names is a of s." ^ parmProtocols! storeSIFString "Answer a , a representation of the receiver in SIF from which the receiver can be rebuilt but NOT reinstantiated via evaluate." | aStream | aStream := WriteStream on: (String new: 50). self storeSIFOn: aStream. ^ aStream contents! ! !MsgParmSpec class methodsFor: nil! newCapturedParmName: nameIn protocolNames: protocolNames "Answer a new protocol message parameter specification for parameter named, nameIn, conforming to the protocols named, protocolNames, and with a captured aliasing attribute. Note: protocolNames must be a of s." ^ self privateNewParmName: nameIn protocolNames: protocolNames aliasing: self parmAliasingAttributeCaptured! parmAliasingAttributeCaptured "Answer the captured protocol message parameter specification parameter aliasing attribute constant." ^ #'captured'! newUncapturedParmName: nameIn protocolNames: protocolNames "Answer a new protocol message parameter specification for parameter named, nameIn, conforming to the protocols named, protocolNames, and with a uncaptured aliasing attribute. Note: protocolNames must be a of s." ^ self privateNewParmName: nameIn protocolNames: protocolNames aliasing: self parmAliasingAttributeUncaptured! privateValidProtocolNames: protocolNamesIn ifError: errorBlock "Private -" | protocolNamesTmp | (protocolNamesIn isKindOf: Collection) ifFalse: [^ errorBlock value]. protocolNamesTmp := self protocolManager defaultProtocolNameCollection. protocolNamesIn do: [:protocolName | (protocolName isKindOf: Symbol) ifFalse: [^ errorBlock value]. protocolNamesTmp add: protocolName]. ^ protocolNamesTmp! parmAliasingAttributeUncaptured "Answer the uncaptured protocol message parameter specification parameter aliasing attribute constant." ^ #'uncaptured'! newParmName: nameIn protocolNames: protocolNames aliasing: attributeIn "Answer a new protocol message parameter specification for parameter named, nameIn, conforming to the protocols named, protocolNames, and with an aliasing attribute, attributeIn. Note: protocolNames must be a of s." (self aliasingAttributes includes: attributeIn) ifFalse: [self error: 'Protocol msg. parameter aliasing attribute not valid.']. ^ self privateNewParmName: nameIn protocolNames: protocolNames aliasing: attributeIn! newUnspecifiedParmName: nameIn protocolNames: protocolNames "Answer a new protocol message parameter specification for parameter named, nameIn, conforming to the protocols named, protocolNames, and with a unspecified aliasing attribute. Note: protocolNames must be a of s." ^ self privateNewParmName: nameIn protocolNames: protocolNames aliasing: self parmAliasingAttributeUnspecified! parmAliasingAttributeUnspecified "Answer the unspecified protocol message parameter specification parameter aliasing attribute constant." ^ #'unspecified'! aliasingAttributes "Answer a list of protocol message parameter aliasing attribute constants. Note: The list is a of s." ^ Set with: self parmAliasingAttributeCaptured with: self parmAliasingAttributeUncaptured with: self parmAliasingAttributeUnspecified! new "Raise an exception as this is an inappropriate message." ^ self shouldNotImplement! privateNewParmName: nameIn protocolNames: protocolNames aliasing: aliasingAttribute "Private -" | protocolNamesTmp | (nameIn isKindOf: String) ifFalse: [self error: 'parameter name not a String.']. protocolNamesTmp := self privateValidProtocolNames: protocolNames ifError: [^ self error: 'Protocol msg.parameter protocol names not a of s.']. ^ super new setParmName: nameIn protocolNames: protocolNamesTmp aliasing: aliasingAttribute! ! !DictionaryANSITest methodsFor: nil! emptyCanonicalObject ^Dictionary new! testXatX " #at: " #'Collection'.! testXincludesKeyX " #includesKey: " #'Collection'.! testXatXifAbsentX " #at:ifAbsent: " #'Collection'.! testXatXputX " #at:put: " #'Collection'.! protocol ^#'Dictionary'! canonicalElement ^self canonicalObject at: 2! emptyCollection ^self canonicalObject class new! canonicalObject ^Dictionary new at: 1 put: 11; at: 2 put: 22; at:3 put: 33; at:4 put: 44; yourself! testXaddAllX " #addAll: " #'Collection'.! testXatXifAbsentPutX " #at:ifAbsentPut: " #'Collection'.! ! !DictionaryANSITest class methodsFor: nil! helperClassesDo: aBlock "refinements must execute before the rest of the helpers" aBlock value: AbstractDictionaryHelper. super helperClassesDo: aBlock! ! !SequencedReadableCollectionHelper methodsFor: nil! testXatXifAbsentX " #at:ifAbsent: " | cos b | cos := self canonicalObjects. b := (cos at: #b) at: 1. self value: [(cos at: #abcd) at: 2 ifAbsent: [nil]] should: [:r | r = b] conformTo: #sequencedReadableCollection selector: #at:ifAbsent:. self value: [(cos at: #abcd) at: 47 ifAbsent: [nil]] should: [:r | r isNil] conformTo: #sequencedReadableCollection selector: #at:ifAbsent:! object: anObject! testXfindFirstX " #findFirst: " | cos d b it | cos := self canonicalObjects. b := (cos at: #b) at: 1. d := (cos at: #d) at: 1. it := (cos at: #ab), (cos at: #bc). self value:[it findFirst: [:e | e = b]] should: [:r | r = 2] conformTo: #sequencedReadableCollection selector: #findFirst:. self value:[(cos at:#abc) findFirst: [:e | e = d]] should: [:r | r = 0] conformTo: #sequencedReadableCollection selector: #findFirst:.! testXindexOfXifAbsentX " #indexOf:ifAbsent: " | cos c | cos := self canonicalObjects. c := (cos at:#c) at:1. self value:[(cos at: #abcd) indexOf: c ifAbsent:[nil]] should: [:r | r = 3] conformTo: #sequencedReadableCollection selector: #indexOf:ifAbsent:. self value:[(cos at: #abcd) indexOf: 42 ifAbsent:[nil]] should: [:r | r isNil] conformTo: #sequencedReadableCollection selector: #indexOf:ifAbsent:.! testXfindLastX " #findLast: " | cos d b it | cos := self canonicalObjects. b := (cos at: #b) at: 1. d := (cos at: #d) at: 1. it := (cos at: #ab), (cos at: #bc). self value:[it findLast: [:e | e = b]] should: [:r | r = 3] conformTo: #sequencedReadableCollection selector: #findLast:. self value:[(cos at:#abc) findLast: [:e | e = d]] should: [:r | r = 0] conformTo: #sequencedReadableCollection selector: #findLast:.! testXcopyReplacingXwithObjectX " #copyReplacing:withObject: (Return Values: )" | cos c a b | cos := self canonicalObjects. a := cos at:#a. b := cos at:#b. c := cos at:#c. self value:[((cos at:#ab), (cos at:#bc)) copyReplacing:(b at:1) withObject:(c at:1)] should: [:r | r = (a, c, c, c)] conformTo: #sequencedReadableCollection selector: #copyReplacing:withObject:.! canonicalObject ^testCase canonicalObject copy! testXfromXtoXkeysAndValuesDoX " #from:to:keysAndValuesDo: " | co col | co := self canonicalObject. col := Array new: 4. self value: [co from: 1 to: 4 keysAndValuesDo: [:i :e | col at: i put: e]] should: [:r | col = co asArray] conformTo: #sequencedReadableCollection selector: #from:to:keysAndValuesDo:! testXconcatenateOp " #, (Return Values: )" | cos | cos := self canonicalObjects. self value: [(cos at: #ab) , (cos at: #cd)] should: [:r | r = (cos at: #abcd)] conformTo: #sequencedReadableCollection selector: #,! testXcopyReplaceAllXwithX " #copyReplaceAll:with: (Return Values: )" | cos | cos := self canonicalObjects. self value: [(cos at:#abcd) copyReplaceAll:(cos at:#bc) with: (cos at:#bcd)] should: [:r | r = ((cos at:#abcd), (cos at:#d)) ] conformTo: #sequencedReadableCollection selector: #copyReplaceAll:with:.! testXindexOfX " #indexOf: " | cos c | cos := self canonicalObjects. c := (cos at:#c) at:1. self value:[(cos at: #abcd) indexOf: c] should: [:r | r = 3] conformTo: #sequencedReadableCollection selector: #indexOf:. self value:[(cos at: #abcd) indexOf: 42] should: [:r | r = 0] conformTo: #sequencedReadableCollection selector: #indexOf:.! testXwithXdoX " #with:do: " | col cos abc bcd | cos := self canonicalObjects. abc := cos at:#abc. bcd := cos at:#bcd. col := OrderedCollection new. self value: [abc with: bcd do: [:e1 :e2 | col add: (e1 = e2)]] should: [:r | col = #(false false false) asOrderedCollection] conformTo: #sequencedReadableCollection selector: #with:do:.! testXcopyWithX " #copyWith: (Return Values: )" | cos d | cos := self canonicalObjects. d := cos at:#d. self value:[(cos at:#abc) copyWith:(d at:1)] should: [:r | r = (cos at: #abcd)] conformTo: #sequencedReadableCollection selector: #copyWith:! testXindexOfSubCollectionXstartingAtX " #indexOfSubCollection:startingAt: " | cos | cos := self canonicalObjects. self value:[(cos at: #abcd) indexOfSubCollection:(cos at:#bc) startingAt:1] should: [:r | r = 2] conformTo: #sequencedReadableCollection selector: #indexOfSubCollection:startingAt:. self value:[(cos at: #abcd) indexOfSubCollection:(cos at:#bc) startingAt:3] should: [:r | r = 0] conformTo: #sequencedReadableCollection selector: #indexOfSubCollection:startingAt:.! testXfirst " #first " | cos a | cos := self canonicalObjects. a := (cos at: #a) at: 1. self value:[(cos at: #abcd) first] should: [:r | r = a] conformTo: #sequencedReadableCollection selector: #first.! testXafterX " #after: " | co | co := self canonicalObject. self value: [co after: (co at: 2)] should: [:r | r = (co at: 3)] conformTo: #sequencedReadableCollection selector: #after:! testXlast " #last " | cos d | cos := self canonicalObjects. d := (cos at: #d) at: 1. self value:[(cos at: #abcd) last] should: [:r | r = d] conformTo: #sequencedReadableCollection selector: #last.! testXcopyFromXtoX " #copyFrom:to: (Return Values: )" | cos | cos := self canonicalObjects. self value: [(cos at: #abcd) copyFrom: 2 to: 3] should: [:r | r = (cos at: #bc)] conformTo: #sequencedReadableCollection selector: #copyFrom:to:. self value: [(cos at: #abcd) copyFrom: 3 to: 2] should: [:r | r isEmpty] conformTo: #sequencedReadableCollection selector: #copyFrom:to:! testXequalityOp " #= " | copy cos | cos := self canonicalObjects. copy := (cos at: #abc) copy. self value:[(cos at:#abc) = copy] should: [:r | r] conformTo: #sequencedReadableCollection selector: #=. self value:[(cos at:#ab) = copy] shouldnt: [:r | r] conformTo: #sequencedReadableCollection selector: #=! testXindexOfSubCollectionXstartingAtXifAbsentX " #indexOfSubCollection:startingAt:ifAbsent: " | cos | cos := self canonicalObjects. self value:[(cos at: #abcd) indexOfSubCollection:(cos at:#bc) startingAt:1 ifAbsent:[nil] ] should: [:r | r = 2] conformTo: #sequencedReadableCollection selector: #indexOfSubCollection:startingAt:ifAbsent:. self value:[(cos at: #abcd) indexOfSubCollection:(cos at:#bc) startingAt:3 ifAbsent:[nil]] should: [:r | r isNil] conformTo: #sequencedReadableCollection selector: #indexOfSubCollection:startingAt:ifAbsent:.! testXreverseDoX " #reverseDo: " | col cos abc | cos := self canonicalObjects. abc := cos at:#abc. col := OrderedCollection new. self value: [abc reverseDo: [:e | col add: e]] should: [:r | col = abc reverse asOrderedCollection] conformTo: #sequencedReadableCollection selector: #reverseDo:.! testXcopyReplaceFromXtoXwithX " #copyReplaceFrom:to:with: (Return Values: )" | cos | cos := self canonicalObjects. self value:[(cos at:#abcd) copyReplaceFrom: 3 to: 2 with:(cos at:#bc)] should: [:r | r = ((cos at:#ab), (cos at:#bc), (cos at:#cd))] conformTo: #sequencedReadableCollection selector: #copyReplaceFrom:to:with:. self value:[(cos at:#abcd) copyReplaceFrom: 5 to: 4 with:(cos at:#bc)] should: [:r | r = ((cos at:#abcd), (cos at:#bc))] conformTo: #sequencedReadableCollection selector: #copyReplaceFrom:to:with:. self value:[(cos at:#abcd) copyReplaceFrom: 1 to: 3 with:(cos at:#bc)] should: [:r | r = (cos at:#bcd)] conformTo: #sequencedReadableCollection selector: #copyReplaceFrom:to:with:.! testXfromXtoXdoX " #from:to:do: " | co col | co := self canonicalObject. col := OrderedCollection new. self value: [co from: 1 to: co size do: [:e | col add: e]] should: [:r | co asOrderedCollection = col] conformTo: #sequencedReadableCollection selector: #from:to:do:.! testXcopyReplaceFromXtoXwithObjectX " #copyReplaceFrom:to:withObject: (Return Values: )" | cos c | cos := self canonicalObjects. c := (cos at:#c). self value:[(cos at:#abcd) copyReplaceFrom: 3 to: 2 withObject:((cos at:#b) at:1)] should: [:r | r = ((cos at:#ab), (cos at:#bcd))] conformTo: #sequencedReadableCollection selector: #copyReplaceFrom:to:withObject:. self value:[(cos at:#abc) copyReplaceFrom: 4 to: 3 withObject:((cos at:#d) at:1)] should: [:r | r = (cos at:#abcd)] conformTo: #sequencedReadableCollection selector: #copyReplaceFrom:to:withObject:. self value:[(cos at:#abc) copyReplaceFrom: 1 to: 2 withObject:(c at:1)] should: [:r | r = (c, c, c)] conformTo: #sequencedReadableCollection selector: #copyReplaceFrom:to:withObject:.! testXatX " #at: " | cos b | cos := self canonicalObjects. b := (cos at:#b) at:1. self value: [(cos at:#abcd) at: 2] should: [:r | r = b] conformTo: #sequencedReadableCollection selector: #at:! testXbeforeX " #before: " | co | co := self canonicalObject. self value: [co before: (co at: 3)] should: [:r | r = (co at: 2)] conformTo: #sequencedReadableCollection selector: #after:! canonicalObjects "answer a dictionary of subsequences of the canonical object" | can cl | can := testCase canonicalObject. cl := can species. ^(Dictionary new) at: #a put: (cl with: (can at: 1)); at: #b put: (cl with: (can at: 2)); at: #c put: (cl with: (can at: 3)); at: #d put: (cl with: (can at: 4)); at: #ab put: (cl with: (can at: 1) with: (can at: 2)); at: #bc put: (cl with: (can at: 2) with: (can at: 3)); at: #cd put: (cl with: (can at: 3) with: (can at: 4)); at: #abc put: (cl with: (can at: 1) with: (can at: 2) with: (can at: 3)); at: #bcd put: (cl with: (can at: 2) with: (can at: 3) with: (can at: 4)); at: #abcd put: (cl with: (can at: 1) with: (can at: 2) with: (can at: 3) with:(can at: 4)); yourself! testXcopyWithoutX " #copyWithout: (Return Values: )" | cos c a b | cos := self canonicalObjects. a := cos at:#a. b := cos at:#b. c := cos at:#c. self value:[(cos at:#abc) copyWithout:(b at:1)] should: [:r | r = (a, c)] conformTo: #sequencedReadableCollection selector: #copyWithout:! testXreverse " #reverse (Return Values: )" | cos abc | cos := self canonicalObjects. abc := cos at:#abc. self value: [abc reverse] should: [:r | r size = 3 and: [((r at: 1) = (abc at: 3)) and: [(r at: 3) = (abc at: 1)]]] conformTo: #sequencedReadableCollection selector: #reverse! ! !StringANSITest methodsFor: nil! testXgreaterThanOrEqualToOp " #>= " #'Collection'.! limitedElementTypes ^1! testXsameAsX " #sameAs: " #'Collection'.! canonicalElement ^self canonicalObject at: 2! testXasUppercase " #asUppercase " #'Collection'.! testXsubStringsX " #subStrings: " #'Collection'.! returnTypeHasLimitedElementTypes ^true! canonicalObject ^'abcd'! testXminX " #min: " #'Collection'.! testXlessThanOp " #< " #'Collection'.! testXlessThanOrEqualToOp " #<= " #'Collection'.! protocol ^#String! testXasSymbol " #asSymbol " #'Collection'.! testXasString " #asString " #'Collection'.! testXbetweenXandX " #between:and: " #'Collection'.! emptyCollection ^self canonicalObject class new! testXasLowercase " #asLowercase " #'Collection'.! testXmaxX " #max: " #'Collection'.! testXgreaterThanOp " #> " #'Collection'.! ! !StringANSITest class methodsFor: nil! helperClassesDo: aBlock super helperClassesDo: aBlock. aBlock value: SequencedCollectionHelper. aBlock value: SequencedReadableCollectionHelper! ! !FloatANSITest methodsFor: nil! testXlessThanOrEqualToOp " #<= " #'Numeric'. " #( 2 -2000000000 2000000000 2.0 1/2 2.0s3 )." #'todo'."It is erroneous if the receiver and operand are not comparable." "Small <= Big -> true" #( 2 2000000000 2.0 2.0s3 ) do: [ :tstNum | self value: [0.3 <= tstNum] should: [:r | r] conformTo: #'magnitude' selector: #'<=' ]. self value: [-2000000005.0 <= -2000000000] should: [:r | r] conformTo: #'magnitude' selector: #'<='. self value: [0.25 <= (1/2)] should: [:r | r] conformTo: #'magnitude' selector: #'<='. "Num <= Num -> true" 1 to: numList size do: [ :ndx | self value: [(numList at: ndx) <= (numList at: ndx)] should: [:r | r ] conformTo: #'magnitude' selector: #'<=' ]. "Big <= Small -> false" #( 2 2.0 2.0s3 ) do: [ :tstNum | self value: [5.0 <= tstNum] shouldnt: [:r | r] conformTo: #'magnitude' selector: #'<=' ]. self value: [9000000000.0 <= 2000000000] shouldnt: [:r | r] conformTo: #'magnitude' selector: #'<='. self value: [-1000000005.0 <= -2000000000] shouldnt: [:r | r] conformTo: #'magnitude' selector: #'<='. self value: [9.0 <= (1/2)] shouldnt: [:r | r] conformTo: #'magnitude' selector: #'<='.! testXisMemberOfX " #isMemberOf: " #'Numeric'. " The return value is unspecified if the receiver is a class object or candidateClass is not a class object. " #'Fundamental'. #todo. "Fix find a test for unspecified rule above ???" self value: [float2 isMemberOf: FloatD] should: [:r | r] conformTo: #'Object' selector: #'isMemberOf:'. "Metaclass tests:" self value: [float2 class isMemberOf: (FloatD class)] should: [:r | r] conformTo: #'Object' selector: #'isMemberOf:'. "Fail inherit tests:" self value: [float2 class isMemberOf: (Number class)] shouldnt: [:r | r] conformTo: #'Object' selector: #'isMemberOf:'. self value: [float2 isMemberOf: Symbol] shouldnt: [:r | r] conformTo: #'Object' selector: #'isMemberOf:'.! testXquoX " #quo: " | retVals | #'Numeric'. " #( 2 -2000000000 2000000000 2.0 1/2 2.0s3 )." retVals := #(1 0 0 1 4 1 ). 1 to: numList size do: [ :ndx | self value: [float2 quo: (numList at: ndx)] should: [:r | r = (retVals at: ndx)] conformTo: #'number' selector: #'quo:'. ]. retVals := #(-1 0 0 -1 -4 -1 ). 1 to: numList size do: [ :ndx | self value: [float2 quo: ((numList at: ndx) negated)] should: [:r | r = (retVals at: ndx)] conformTo: #'number' selector: #'quo:' ]. self should: [(25.5 quo: 5.1) = 5]. self should: [(25.5 quo: 5) = 5]. self should: [(25500000000.5 quo: 5000000000) = 5]. self should: [(-25500000000.5 quo: -5000000000) = 5]. self should: [(25.5 quo: (51/10)) = 5]. self should: [(25.5 quo: 5.1s1) = 5]. self value: [0.0 quo: float2] should: [:r | r = 0.0] conformTo: #'number' selector: #'quo:'. "If the operand has a value of zero the ZeroDivide exception is signaled." self value: [float2 quo: 0.0] shouldRaise: ZeroDivide.! testXnegated " #negated (Return Values: ) " | rcvr | #'Numeric'. rcvr := 2.0. self value: [rcvr negated] should: [:r | r = -2.0] conformTo: #'number' selector: #'negated' opRECEIVER: rcvr. rcvr := -2.0. self value: [rcvr negated] should: [:r | r = 2.0] conformTo: #'number' selector: #'negated' opRECEIVER: rcvr. rcvr := 0.0. self value: [rcvr negated] should: [:r | r = 0.0] conformTo: #'number' selector: #'negated' opRECEIVER: rcvr.! testXasFloatE " #asFloatE " #'Numeric'. self value: [2.0 asFloatE] should: [:r | r = 2.0] conformTo: #'number' selector: #'asFloatE'. self value: [-2.0 asFloatE] should: [:r | r = -2.0] conformTo: #'number' selector: #'asFloatE'. self value: [0.0 asFloatE] should: [:r | r = 0.0] conformTo: #'number' selector: #'asFloatE'.! testXraisedToIntegerX " #raisedToInteger: (Return Values: )" | rcvr | #'Numeric'. rcvr := 5.1. self value: [rcvr raisedToInteger: 0] should: [:r | r = 1.0] conformTo: #'number' selector: #'raisedToInteger:' opRECEIVER: rcvr. self value: [rcvr raisedToInteger: 1] should: [:r | r = rcvr] conformTo: #'number' selector: #'raisedToInteger:' opRECEIVER: rcvr. self value: [rcvr raisedToInteger: 2] should: [:r | r closeTo: 26.01] conformTo: #'number' selector: #'raisedToInteger:' opRECEIVER: rcvr. self value: [rcvr negated raisedToInteger: 2] should: [:r | r closeTo: 26.01] conformTo: #'number' selector: #'raisedToInteger:' opRECEIVER: rcvr. self value: [rcvr raisedToInteger: -2] should: [:r | r closeTo: 0.0384467512495194] conformTo: #'number' selector: #'raisedToInteger:' opRECEIVER: rcvr.! testXstrictlyPositive " #strictlyPositive " #'Numeric'. self value: [2.0 strictlyPositive] should: [:r | r] conformTo: #'number' selector: #'strictlyPositive'. self value: [0.0 strictlyPositive] shouldnt: [:r | r] conformTo: #'number' selector: #'strictlyPositive'. self value: [-2.0 strictlyPositive] shouldnt: [:r | r] conformTo: #'number' selector: #'strictlyPositive'.! testXfloorLogX " #floorLog: " #'Numeric'.! testXpositive " #positive " #'Numeric'. self value: [2.0 positive] should: [:r | r] conformTo: #'number' selector: #'positive'. self value: [0.0 positive] should: [:r | r] conformTo: #'number' selector: #'positive'. self value: [-2.0 positive] shouldnt: [:r | r] conformTo: #'number' selector: #'positive'.! testXradiansToDegrees " #radiansToDegrees " #'Numeric'.! testXintegerPart " #integerPart (returnRule - :receiver) " | rcvr | #'Numeric'. rcvr := 2.5. self value: [rcvr integerPart] should: [:result | result = 2.0] conformTo: #'number' selector: #'integerPart' ruleReceiver: rcvr. rcvr := 2.0. self value: [rcvr integerPart] should: [:r | r = 2.0] conformTo: #'number' selector: #'integerPart' ruleReceiver: rcvr. rcvr := -2.0. self value: [rcvr integerPart] should: [:result | result = -2.0] conformTo: #'number' selector: #'integerPart' ruleReceiver: rcvr. rcvr := 0.0. self value: [rcvr integerPart] should: [:result | result = 0.0] conformTo: #'number' selector: #'integerPart' ruleReceiver: rcvr.! testXsin " #sin " #'Numeric'.! testXcopy " #copy (Return Values: ) " #'Numeric'. " Return a new object that must be as similar as possible to the receiver in its initial state and behavior. Any operation that changes the state of the new object should not as a side-effect change the state or behavior of the receiver. Similarly, any change to the receiver should not as a side-effect change the new object. If the receiver is an identity object, return the receiver. " #todo. "??? add change-side-effect test ???" self value: [float2 copy] should: [:r | (r = float2) ] conformTo: #'Object' selector: #'copy' opRECEIVER: float2.! testXreciprocal " #reciprocal (returnRule - :receiver) " #'Numeric'. self value: [float2 reciprocal] should: [:r | r = (1.0/float2)] conformTo: #'number' selector: #'reciprocal' ruleReceiver: float2. self value: [float2 negated reciprocal] should: [:r | r = (1.0/(float2 negated))] conformTo: #'number' selector: #'reciprocal' ruleReceiver: (float2 negated). "Signal a ZeroDivide exception if the receiver is equal to zero." self value: [0.0 reciprocal] shouldRaise: ZeroDivide.! testXasScaledDecimalX " #asScaledDecimal: " #'Numeric'. self value: [2.0 asScaledDecimal: 2] should: [:r | r = 2.0s2 & (r scale = 2)] conformTo: #'number' selector: #'asScaledDecimal:'. self value: [-2.0 asScaledDecimal: 2] should: [:r | r = -2.0s2 & (r scale = 2)] conformTo: #'number' selector: #'asScaledDecimal:'. self value: [0.0 asScaledDecimal: 2] should: [:r | r = 0.0s2 & (r scale = 2)] conformTo: #'number' selector: #'asScaledDecimal:'.! testXaddOp " #+ (returnRule - :receiver :operand) " | retVals | #'Numeric'. " #( 2 -2000000000 2000000000 2.0 1/2 2.0s3 )." retVals := #(4.0 -1999999998.0 2000000002.0 4.0 2.5 4.0). 1 to: numList size do: [ :ndx | self value: [float2 + (numList at: ndx)] should: [:r | r closeTo: (retVals at: ndx)] conformTo: #'number' selector: #'+' ruleReceiver: float2 operand: (numList at: ndx) ].! testXasFraction " #asFraction " #'Numeric'. self value: [2.0 asFraction] should: [:r | r = 2] conformTo: #'number' selector: #'asFraction'. self value: [-2.5 asFraction] should: [:r | r = (-5/2)] conformTo: #'number' selector: #'asFraction'. self value: [0.0 asFraction] should: [:r | r = 0] conformTo: #'number' selector: #'asFraction'.! testXgreaterThanOp " #> " #'Numeric'. " #( 2 -2000000000 2000000000 2.0 1/2 2.0s3 )." #'todo'."It is erroneous if the receiver and operand are not comparable." "Small > Big -> false" #( 2 2000000000 2.0 2.0s3 ) do: [ :tstNum | self value: [0.3 > tstNum] shouldnt: [:r | r] conformTo: #'number' selector: #'>' ]. self value: [-2000000005.0 > -2000000000] shouldnt: [:r | r] conformTo: #'number' selector: #'>'. self value: [0.25 > (1/2)] shouldnt: [:r | r] conformTo: #'number' selector: #'>'. "Num > Num -> false" 1 to: numList size do: [ :ndx | self value: [(numList at: ndx) > (numList at: ndx)] shouldnt: [:r | r ] conformTo: #'number' selector: #'>' ]. "Big > Small -> true" #( 2 2.0 2.0s3 ) do: [ :tstNum | self value: [5.0 > tstNum] should: [:r | r] conformTo: #'number' selector: #'>' ]. self value: [9000000000.0 > 2000000000] should: [:r | r] conformTo: #'number' selector: #'>'. self value: [-1000000005.0 > -2000000000] should: [:r | r] conformTo: #'number' selector: #'>'. self value: [9.0 > (1/2)] should: [:r | r] conformTo: #'number' selector: #'>'.! testXexp " #exp " #'Numeric'.! protocol ^#'Float'! testXmultiplyOp " #* (returnRule - :receiver :operand) " | retVals | #'Numeric'. " #( 2 -2000000000 2000000000 2.0 1/2 2.0s3 )." retVals := #(4.0 -4000000000.0 4000000000.0 4.0 1.0 4.0). 1 to: numList size do: [ :ndx | self value: [float2 * (numList at: ndx)] should: [:r | r closeTo: (retVals at: ndx)] conformTo: #'number' selector: #'*' ruleReceiver: float2 operand: (numList at: ndx) ].! testXsign " #sign " #'Numeric'. self value: [2.0 sign] should: [:r | r = 1] conformTo: #'number' selector: #'sign'. self value: [0.0 sign] should: [:r | r = 0] conformTo: #'number' selector: #'sign'. self value: [-2.0 sign] should: [:r | r = -1] conformTo: #'number' selector: #'sign'.! testXidentityOp " #== " #'Numeric'. " The value of receiver == comparand is true if and only if the value of comparand == receiver would also be true. If the value of receiver == comparand is true then the receiver and comparand must have equivalent identity hash values. Or more formally: receiver == comparand => receiver identityHash = comparand identityHash " self shouldnt: [smallInt2 == float2]. self shouldnt: [smallInt2 identityHash == float2 identityHash]. self value: [float2 == float2] should: [:r | r] conformTo: #'Object' selector: #'=='. self value: [float2 == 2.1] shouldnt: [:r | r] conformTo: #'Object' selector: #'=='.! testXequalityOp " #= " #'Numeric'. " receiver = comparand => receiver hash = comparand hash " self value: [float2 = float2] should: [:r | r & (float2 hash = float2 hash) ] conformTo: #'Float' selector: #'='. self value: [ float2 = 2.1 ] shouldnt: [ :r | r | (float2 hash = 2.1 hash) ] conformTo: #'Float' selector: #'='. " #( 2 -2000000000 2000000000 2.0 1/2 2.0s3 )." self value: [ float2 = 2 ] should: [ :r | r ifTrue: [ float2 hash = 2 hash ] ifFalse: [ float2 hash ~= 2 hash ] ] conformTo: #'Float' selector: #'='. self value: [ -2000000000.0 = -2000000000 ] should: [ :r | r ifTrue: [ -2000000000.0 hash = -2000000000 hash ] ifFalse: [ -2000000000.0 hash ~= -2000000000 hash ] ] conformTo: #'Float' selector: #'='. self value: [ 2000000000.0 = 2000000000 ] should: [ :r | r ifTrue: [ 2000000000.0 hash = 2000000000 hash ] ifFalse: [ 2000000000.0 hash ~= 2000000000 hash ] ] conformTo: #'Float' selector: #'='. self value: [ 2.5 = (5/2) ] should: [ :r | r ifTrue: [ 2.5 hash = (5/2) hash ] ifFalse: [ 2.5 hash ~= (5/2) hash ] ] conformTo: #'Float' selector: #'='. self value: [ float2 = 2.0s3 ] should: [ :r | r ifTrue: [ float2 hash = 2.0s3 hash ] ifFalse: [ float2 hash ~= 2.0s3 hash ] ] conformTo: #'Float' selector: #'='.! testXraisedToX " #raisedTo: " | numVals retVals | #'Numeric'. numVals := #(2 2.0 0 2.0s3 ) copy. numVals at: 3 put: (1/2). retVals := #(4.0 4.0 1.414213562373095 4.0 ). 1 to: numVals size do: [ :ndx | self value: [float2 raisedTo: (numVals at: ndx)] should: [:r | r closeTo: (retVals at: ndx)] conformTo: #'number' selector: #'raisedTo:'. ]. retVals := #(0.25 0.25 0.7071067811865475 0.25). 1 to: numVals size do: [ :ndx | self value: [float2 raisedTo: ((numVals at: ndx) negated)] should: [:r | r closeTo: (retVals at: ndx)] conformTo: #'number' selector: #'raisedTo:' ]. self value: [float2 raisedTo: 0.0] should: [:r | r = 1.0] conformTo: #'number' selector: #'raisedTo:'. self value: [0.0 raisedTo: float2] should: [:r | r = 0.0] conformTo: #'number' selector: #'raisedTo:'. self value: [float2 raisedTo: 1.0] should: [:r | r = float2] conformTo: #'number' selector: #'raisedTo:'. "It is erroneous if the receiver equals zero and the operand is less than or equal to zero," self value: [0.0 raisedTo: -2] shouldRaise: Error. " or if the receiver is less than zero." self value: [float2 negated raisedTo: 2.0] shouldRaise: Error.! testLiterals #'Numeric'. self should: [1.1e1 = 11.0]. self should: [1.1d1 = 11.0]. self should: [1.1q1 = 11.0]. "Not ANSI conforming:" #todo. "??? fix ???" " self shouldnt: [1.0q = 1.0]. self shouldnt: [10e10 = 1.0]. "! testXceiling " #ceiling " #'Numeric'. self value: [2.0 ceiling] should: [:r | r = 2] conformTo: #'number' selector: #'ceiling'. self value: [2.1 ceiling] should: [:r | r = 3] conformTo: #'number' selector: #'ceiling'. self value: [2.5 ceiling] should: [:r | r = 3] conformTo: #'number' selector: #'ceiling'. self value: [-2.0 ceiling] should: [:r | r = -2] conformTo: #'number' selector: #'ceiling'. self value: [-2.1 ceiling] should: [:r | r = -2] conformTo: #'number' selector: #'ceiling'. self value: [-2.5 ceiling] should: [:r | r = -2] conformTo: #'number' selector: #'ceiling'. self value: [0.0 ceiling] should: [:r | r = 0] conformTo: #'number' selector: #'ceiling'.! testXarcTan " #arcTan " #'Numeric'.! testXrounded " #rounded " #'Numeric'. self value: [2.0 rounded] should: [:r | r = 2] conformTo: #'number' selector: #'rounded'. self value: [2.1 rounded] should: [:r | r = 2] conformTo: #'number' selector: #'rounded'. self value: [2.5 rounded] should: [:r | r = 3] conformTo: #'number' selector: #'rounded'. self value: [-2.0 rounded] should: [:r | r = -2] conformTo: #'number' selector: #'rounded'. self value: [-2.1 rounded] should: [:r | r = -2] conformTo: #'number' selector: #'rounded'. self value: [-2.5 rounded] should: [:r | r = -3] conformTo: #'number' selector: #'rounded'. self value: [0.0 rounded] should: [:r | r = 0] conformTo: #'number' selector: #'rounded'.! testXarcSin " #arcSin " #'Numeric'.! testXdivideOp " #/ (returnRule - :receiver :operand) " | retVals | #'Numeric'. " #( 2 -2000000000 2000000000 2.0 1/2 2.0s3 )." retVals := #(1.0 -1.0e-9 1.0e-9 1.0 4.0 1.0). 1 to: numList size do: [ :ndx | self value: [float2 / (numList at: ndx)] should: [:r | r closeTo: (retVals at: ndx)] conformTo: #'number' selector: #'/' ruleReceiver: float2 operand: (numList at: ndx) ]. self value: [0.0 / float2] should: [:r | r = 0.0] conformTo: #'number' selector: #'/' ruleReceiver: float2 operand: 0.0! testXarcCos " #arcCos " #'Numeric'.! testXasFloatD " #asFloatD " #'Numeric'. self value: [2.0 asFloatD] should: [:r | r = 2.0] conformTo: #'number' selector: #'asFloatD'. self value: [-2.0 asFloatD] should: [:r | r = -2.0] conformTo: #'number' selector: #'asFloatD'. self value: [0.0 asFloatD] should: [:r | r = 0.0] conformTo: #'number' selector: #'asFloatD'.! testXlogX " #log: " #'Numeric'.! testXln " #ln " #'Numeric'.! testXhash " #hash " #'Numeric'. " Any two objects that are considered equivalent using the #= message must have the same hash value. More formally: receiver = comparand => receiver hash = comparand hash " self value: [float2 hash] should: [:r | r = float2 hash] conformTo: #'Object' selector: #'hash'. self value: [float2 hash] shouldnt: [:r | r = 2.1 hash] conformTo: #'Object' selector: #'hash'.! testXlessThanOp " #< " #'Numeric'. " #( 2 -2000000000 2000000000 2.0 1/2 2.0s3 )." #'todo'."It is erroneous if the receiver and operand are not comparable." "Small < Big -> true" #( 2 2000000000 2.0 2.0s3 ) do: [ :tstNum | self value: [0.3 < tstNum] should: [:r | r] conformTo: #'number' selector: #'<' ]. self value: [-2000000005.0 < -2000000000] should: [:r | r] conformTo: #'number' selector: #'<'. self value: [0.25 < (1/2)] should: [:r | r] conformTo: #'number' selector: #'<'. "Num < Num -> false" 1 to: numList size do: [ :ndx | self value: [(numList at: ndx) < (numList at: ndx)] shouldnt: [:r | r ] conformTo: #'number' selector: #'<' ]. "Big < Small -> false" #( 2 2.0 2.0s3 ) do: [ :tstNum | self value: [5.0 < tstNum] shouldnt: [:r | r] conformTo: #'number' selector: #'<' ]. self value: [9000000000.0 < 2000000000] shouldnt: [:r | r] conformTo: #'number' selector: #'<'. self value: [-1000000005.0 < -2000000000] shouldnt: [:r | r] conformTo: #'number' selector: #'<'. self value: [9.0 < (1/2)] shouldnt: [:r | r] conformTo: #'number' selector: #'<'.! testXfloor " #floor " #'Numeric'. self value: [2.0 floor] should: [:r | r = 2] conformTo: #'number' selector: #'floor'. self value: [2.1 floor] should: [:r | r = 2] conformTo: #'number' selector: #'floor'. self value: [2.5 floor] should: [:r | r = 2] conformTo: #'number' selector: #'floor'. self value: [-2.0 floor] should: [:r | r = -2] conformTo: #'number' selector: #'floor'. self value: [-2.1 floor] should: [:r | r = -3] conformTo: #'number' selector: #'floor'. self value: [-2.5 floor] should: [:r | r = -3] conformTo: #'number' selector: #'floor'. self value: [0.0 floor] should: [:r | r = 0] conformTo: #'number' selector: #'floor'.! testXtruncated " #truncated " #'Numeric'. self value: [2.0 truncated] should: [:r | r = 2] conformTo: #'number' selector: #'truncated'. self value: [2.1 truncated] should: [:r | r = 2] conformTo: #'number' selector: #'truncated'. self value: [2.5 truncated] should: [:r | r = 2] conformTo: #'number' selector: #'truncated'. self value: [-2.0 truncated] should: [:r | r = -2] conformTo: #'number' selector: #'truncated'. self value: [-2.1 truncated] should: [:r | r = -2] conformTo: #'number' selector: #'truncated'. self value: [-2.5 truncated] should: [:r | r = -2] conformTo: #'number' selector: #'truncated'. self value: [0.0 truncated] should: [:r | r = 0] conformTo: #'number' selector: #'truncated'.! testXsquared " #squared (Return Values: )" | rcvr | #'Numeric'. rcvr := 5.1. self value: [rcvr squared] should: [:r | r closeTo: 26.01] conformTo: #'number' selector: #'squared' opRECEIVER: rcvr. rcvr := -5.1. self value: [rcvr squared] should: [:r | r closeTo: 26.01] conformTo: #'number' selector: #'squared' opRECEIVER: rcvr. rcvr := 0.0. self value: [rcvr squared] should: [:r | r = 0.0] conformTo: #'number' selector: #'squared' opRECEIVER: rcvr.! testXnotIdentityOp " #~~ " #'Numeric'. " The value of receiver ~~ comparand is true if and only if the value of comparand ~~ receiver would also be true. " self should: [smallInt2 ~~ float2 and: [float2 ~~ smallInt2]]. self value: [float2 ~~ 2.1] should: [:r | r] conformTo: #'Object' selector: #'~~'. self value: [float2 ~~ float2] shouldnt: [:r | r] conformTo: #'Object' selector: #'~~'.! testXdegreesToRadians " #degreesToRadians " #'Numeric'.! testXasFloatQ " #asFloatQ " #'Numeric'. self value: [2.0 asFloatQ] should: [:r | r = 2.0] conformTo: #'number' selector: #'asFloatQ'. self value: [-2.0 asFloatQ] should: [:r | r = -2.0] conformTo: #'number' selector: #'asFloatQ'. self value: [0.0 asFloatQ] should: [:r | r = 0.0] conformTo: #'number' selector: #'asFloatQ'.! testXsubtractOp " #- (returnRule - :receiver :operand) " | retVals | #'Numeric'. " #( 2 -2000000000 2000000000 2.0 1/2 2.0s3 )." retVals := #(0.0 2000000002.0 -1999999998.0 0.0 1.5 0.0). 1 to: numList size do: [ :ndx | self value: [float2 - (numList at: ndx)] should: [:r | r closeTo: (retVals at: ndx)] conformTo: #'number' selector: #'-' ruleReceiver: float2 operand: (numList at: ndx) ].! testXisKindOfX " #isKindOf: " #'Numeric'. " The return value is unspecified if the receiver is a class object or candidateClass is not a class object. " #todo. "Fix find a test for unspecified rule above ???" self value: [float2 isKindOf: Float] should: [:r | r] conformTo: #'Object' selector: #'isKindOf:'. "Metaclass tests:" self value: [float2 class isKindOf: (Float class)] should: [:r | r] conformTo: #'Object' selector: #'isKindOf:'. "Inherit tests:" self value: [float2 class isKindOf: (Number class)] should: [:r | r] conformTo: #'Object' selector: #'isKindOf:'. self value: [float2 isKindOf: Symbol] shouldnt: [:r | r] conformTo: #'Object' selector: #'isKindOf:'.! testXcos " #cos " #'Numeric'.! testXprintString " #printString " #'Numeric'. "Answer a string which is a valid Smalltalk literal representation approximately equal to the receiver. An exponent literal form is produced if the value of the exponent is greater than the precision of the receiver." self value: [(2.0e0 raisedToInteger: 1.0e0 class precision + 1) printString ] should: [:r | r includes: $e ] conformTo: #'Float' selector: #'printString'. self value: [(-2.0e0 raisedToInteger: 1.0e0 class precision + 1) printString ] should: [:r | r includes: $e ] conformTo: #'Float' selector: #'printString'. self value: [(2.0e0 raisedToInteger: -1 - 1.0e0 class precision) printString ] should: [:r | r includes: $e ] conformTo: #'Float' selector: #'printString'. self value: [(-2.0e0 raisedToInteger: -1 - 1.0e0 class precision) printString ] should: [:r | r includes: $e ] conformTo: #'Float' selector: #'printString'! testXminX " #min: " #'Numeric'. " #( 2 -2000000000 2000000000 2.0 1/2 2.0s3 )." #'todo'."It is erroneous if the receiver and operand are not comparable." self value: [2.0 min: 1] should: [:r | r = 1] conformTo: #'magnitude' selector: #'min:'. self value: [-1000000000.0 min: -2000000000] should: [:r | r = -2000000000] conformTo: #'magnitude' selector: #'min:'. self value: [2000000003.0 min: 2000000001] should: [:r | r = 2000000001] conformTo: #'magnitude' selector: #'min:'. self value: [2.0 min: 1.0] should: [:r | r = 1.0] conformTo: #'magnitude' selector: #'min:'. self value: [2.0 min: (3/2)] should: [:r | r = (3/2)] conformTo: #'magnitude' selector: #'min:'. self value: [2.0 min: 1.0s5] should: [:r | r = 1.0s5] conformTo: #'magnitude' selector: #'min:'. "Num min: Num -> Num" 1 to: numList size do: [ :ndx | self value: [(numList at: ndx) min: (numList at: ndx)] should: [:r | r = (numList at: ndx)] conformTo: #'magnitude' selector: #'min:' ].! testXroundToX " #roundTo: (returnRule - :receiver :operand) " | retVals | #'Numeric'. " #( 2 -2000000000 2000000000 2.0 1/2 2.0s3 )." retVals := #(2 0 0 2.0 2 2.000s3). 1 to: numList size do: [ :ndx | self value: [float2 roundTo: (numList at: ndx)] should: [:r | r = (retVals at: ndx)] conformTo: #'number' selector: #'roundTo:' ruleReceiver: float2 operand: (numList at: ndx) ]. self should: [(0.0 roundTo: float2) = 0.0]! testXremainderIntegerDivideOp " #\\ (returnRule - :receiver :operand) " "The remainder has the same sign as operand. Within the limits of representation, the following invariant should hold: (receiver // operand) * operand + (receiver \\ operand) = receiver " | retVals recList ndx | #'Numeric'. " #( 2 -2000000000 2000000000 2.0 1/2 2.0s3 )." recList := #( 26 -26000000001 26000000001 26.0 0 26.0s3 ) copy. recList at: 5 put: (53/2). retVals := #(1.0 4.0 1.0 1.0 1.5 1.0 ). ndx := 0. recList do: [ :rec | ndx := ndx + 1. self value: [rec \\ 5.0] should: [:r | r = (retVals at: ndx) & ((rec // 5.0) * 5.0 + (rec \\ 5.0) = rec)] conformTo: #'number' selector: #'\\' ruleReceiver: rec operand: 5.0. ]. "The remainder has the same sign as operand." retVals := #(-4.0 -1.0 -4.0 -4.0 -3.5 -4.0 ). ndx := 0. recList do: [ :rec | ndx := ndx + 1. self value: [rec \\ -5.0] should: [:r | r = (retVals at: ndx) & ((rec // -5.0) * -5.0 + (rec \\ -5.0) = rec)] conformTo: #'number' selector: #'\\' ruleReceiver: rec operand: -5.0. ]. self should: [26.5 \\ 5.0 = 1.5 & ((26.5 // 5.0) * 5.0 + (26.5 \\ 5.0) = 26.5)]. self should: [26.5 \\ -5.0 = -3.5 & ((26.5 // -5.0) * -5.0 + (26.5 \\ -5.0) = 26.5)]. self should: [0.0 \\ float2 = 0.0]. "If the operand is zero, the implementation may signal the ZeroDivide exception or provide a continuation value." self value: [float2 \\ 0.0] shouldRaise: ZeroDivide.! testXnegative " #negative " #'Numeric'. self value: [-2.0 negative] should: [:r | r] conformTo: #'number' selector: #'negative'. self value: [2.0 negative] shouldnt: [:r | r] conformTo: #'number' selector: #'negative'. self value: [0.0 negative] shouldnt: [:r | r] conformTo: #'number' selector: #'negative'.! testXtan " #tan " #'Numeric'.! canonicalObject ^Float pi "3.141592653589793"! testXabs " #abs (Return Values: ) " | rcvr | #'Numeric'. rcvr := 2.0. self value: [rcvr abs] should: [:r | r = 2.0] conformTo: #'number' selector: #'abs' opRECEIVER: rcvr. rcvr := -2.0. self value: [rcvr abs] should: [:r | r = 2.0] conformTo: #'number' selector: #'abs' opRECEIVER: rcvr. rcvr := 0.0. self value: [rcvr abs] should: [:r | r = 0.0] conformTo: #'number' selector: #'abs' opRECEIVER: rcvr.! testXintegerDivideOp " #// " | retVals | #'Numeric'. " #( 2 -2000000000 2000000000 2.0 1/2 2.0s3 )." "The sign of the result is positive if the receiver and operand have the same sign, and negative if the signs are different." retVals := #(1 -1 0 1 4 1). 1 to: numList size do: [ :ndx | self value: [float2 // (numList at: ndx)] should: [:r | r = (retVals at: ndx)] conformTo: #'number' selector: #'//'. ]. retVals := #(-1 0 -1 -1 -4 -1). 1 to: numList size do: [ :ndx | self value: [float2 // ((numList at: ndx) negated)] should: [:r | r = (retVals at: ndx)] conformTo: #'number' selector: #'//' ]. self should: [25.5 // 5.1 = 5]. self should: [25.5 // 5 = 5]. self should: [25500000000.5 // 5000000000 = 5]. self should: [-25500000000.5 // -5000000000 = 5]. self should: [25.5 // (51/10) = 5]. self should: [25.5 // 5.1s1 = 5]. self value: [0.0 // float2] should: [:r | r = 0.0] conformTo: #'number' selector: #'//'. "If the operand has a value of zero the ZeroDivide exception is signaled." self value: [float2 // 0.0] shouldRaise: ZeroDivide.! testXasInteger " #asInteger " #'Numeric'. self value: [2.0 asInteger] should: [:r | r = 2] conformTo: #'number' selector: #'asInteger'. self value: [2.1 asInteger] should: [:r | r = 2] conformTo: #'number' selector: #'asInteger'. self value: [2.5 asInteger] should: [:r | r = 3] conformTo: #'number' selector: #'asInteger'. self value: [-2.0 asInteger] should: [:r | r = -2] conformTo: #'number' selector: #'asInteger'. self value: [-2.1 asInteger] should: [:r | r = -2] conformTo: #'number' selector: #'asInteger'. self value: [-2.5 asInteger] should: [:r | r = -3] conformTo: #'number' selector: #'asInteger'. self value: [0.0 asInteger] should: [:r | r = 0] conformTo: #'number' selector: #'asInteger'.! testXgreaterThanOrEqualToOp " #>= " #'Numeric'. " #( 2 -2000000000 2000000000 2.0 1/2 2.0s3 )." #'todo'."It is erroneous if the receiver and operand are not comparable." "Small >= Big -> false" #( 2 2000000000 2.0 2.0s3 ) do: [ :tstNum | self value: [0.3 >= tstNum] shouldnt: [:r | r] conformTo: #'magnitude' selector: #'>=' ]. self value: [-2000000005.0 >= -2000000000] shouldnt: [:r | r] conformTo: #'magnitude' selector: #'>='. self value: [0.25 >= (1/2)] shouldnt: [:r | r] conformTo: #'magnitude' selector: #'>='. "Num >= Num -> true" 1 to: numList size do: [ :ndx | self value: [(numList at: ndx) >= (numList at: ndx)] should: [:r | r ] conformTo: #'magnitude' selector: #'>=' ]. "Big >= Small -> true" #( 2 2.0 2.0s3 ) do: [ :tstNum | self value: [5.0 >= tstNum] should: [:r | r] conformTo: #'magnitude' selector: #'>=' ]. self value: [9000000000.0 >= 2000000000] should: [:r | r] conformTo: #'magnitude' selector: #'>='. self value: [-1000000005.0 >= -2000000000] should: [:r | r] conformTo: #'magnitude' selector: #'>='. self value: [9.0 >= (1/2)] should: [:r | r] conformTo: #'magnitude' selector: #'>='.! testXremX " #rem: " | num2 flt | #'Numeric'. "Within the limits of representation, the following invariant should hold: (receiver quo: operand)*operand + (receiver rem: operand) = receiver" " #( 2 -2000000000 2000000000 2.0 1/2 2.0s3 )." numList := #( 5 5.0 5.0s3 ). flt := 26.5. numList do: [ :num | self value: [flt rem: num] should: [:r | r = 1.5 & ((flt quo: num) * num + (flt rem: num) = flt)] conformTo: #'number' selector: #'rem:' ]. numList := numList collect: [ :num | num negated ]. numList do: [ :num | self value: [flt rem: num] should: [:r | r = 1.5 & ((flt quo: num) * num + (flt rem: num) = flt)] conformTo: #'number' selector: #'rem:' ]. numList := #( 5 5.0 5.0s3 ). flt := -26.5. numList do: [ :num | self should: [(flt rem: num) = -1.5 & ((flt quo: num) * num + (flt rem: num) = flt)] ]. numList := numList collect: [ :num | num negated ]. numList do: [ :num | self should: [(flt rem: num) = -1.5 & ((flt quo: num) * num + (flt rem: num) = flt)] ]. flt := 26.5. num2 := (5/2). self value: [flt rem: num2] should: [:r | r = 1.5 & ((flt quo: num2) * num2 + (flt rem: num2) = flt)] conformTo: #'number' selector: #'rem:'. numList := #( -2000000000 2000000000 ). flt := 10000000001.5. numList do: [ :num | self value: [flt rem: num] should: [:r | r = 1.5 & ((flt quo: num) * num + (flt rem: num) = flt)] conformTo: #'number' selector: #'rem:' ]. "If either the receiver or operand are of type and the operand has a value of zero, the result is implementation defined. The implementation may signal the ZeroDivide exception or provide a continuation value " self value: [float2 rem: 0.0] shouldRaise: ZeroDivide. self value: [float2 rem: 0] shouldRaise: ZeroDivide. self value: [2 rem: 0.0] shouldRaise: ZeroDivide.! testXidentityHash " #identityHash " #'Numeric'. self value: [float2 identityHash] should: [:r | r = float2 identityHash] conformTo: #'Object' selector: #'identityHash'. self value: [float2 identityHash] shouldnt: [:r | r = 2.1 identityHash] conformTo: #'Object' selector: #'identityHash'. self shouldnt: [smallInt2 identityHash = float2 identityHash].! testXsqrt " #sqrt " #'Numeric'. self value: [26.01 sqrt] should: [:r | r closeTo: 5.1] conformTo: #'number' selector: #'sqrt'. self value: [4.0 sqrt] should: [:r | r = 2.0] conformTo: #'number' selector: #'sqrt'. self value: [0.0 sqrt] should: [:r | r = 0.0] conformTo: #'number' selector: #'sqrt'! testXmaxX " #max: " #'Numeric'. " #( 2 -2000000000 2000000000 2.0 1/2 2.0s3 )." #'todo'."It is erroneous if the receiver and operand are not comparable." self value: [2.0 max: 3] should: [:r | r = 3] conformTo: #'magnitude' selector: #'max:'. self value: [-3000000000.0 max: -2000000000] should: [:r | r = -2000000000] conformTo: #'magnitude' selector: #'max:'. self value: [2000000000.0 max: 2000000003] should: [:r | r = 2000000003] conformTo: #'magnitude' selector: #'max:'. self value: [2.0 max: 3.0] should: [:r | r = 3.0] conformTo: #'magnitude' selector: #'max:'. self value: [2.0 max: (5/2)] should: [:r | r = (5/2)] conformTo: #'magnitude' selector: #'max:'. self value: [2.0 max: 3.0s3] should: [:r | r = 3.0s3] conformTo: #'magnitude' selector: #'max:'. "Num max: Num -> Num" 1 to: numList size do: [ :ndx | self value: [(numList at: ndx) max: (numList at: ndx)] should: [:r | r = (numList at: ndx)] conformTo: #'magnitude' selector: #'max:' ].! testXfractionPart " #fractionPart (Return Values: )" | rcvr | #'Numeric'. "Within the limits of representation, the following invariants should hold: receiver integerPart + receiver fractionPart = receiver receiver \\1 = receiver fractionPart (RAH - erroneous, add #'abs') " rcvr := 26.5. self value: [rcvr fractionPart] should: [:r | r = 0.5 & (rcvr integerPart + rcvr fractionPart = rcvr) & (rcvr \\ 1 = rcvr fractionPart abs)] conformTo: #'number' selector: #'fractionPart' opRECEIVER: rcvr. rcvr := -26.5. self value: [rcvr fractionPart] should: [:r | r = -0.5 & (rcvr integerPart + rcvr fractionPart = rcvr) & (rcvr \\ 1 = rcvr fractionPart abs)] conformTo: #'number' selector: #'fractionPart' opRECEIVER: rcvr. rcvr := 26.0. self value: [rcvr fractionPart] should: [:r | r = 0.0 & (rcvr integerPart + rcvr fractionPart = rcvr) & (rcvr \\ 1 = rcvr fractionPart abs)] conformTo: #'number' selector: #'fractionPart' opRECEIVER: rcvr. rcvr := 0.0. self value: [rcvr fractionPart] should: [:r | r = 0.0 & (rcvr integerPart + rcvr fractionPart = rcvr) & (rcvr \\ 1 = rcvr fractionPart abs)] conformTo: #'number' selector: #'fractionPart' opRECEIVER: rcvr.! testXtoXdoX " #to:do: " #'Numeric'.! testXasFloat " #asFloat " #'Numeric'. self value: [2.0 asFloat] should: [:r | r = 2.0] conformTo: #'number' selector: #'asFloat'. self value: [-2.0 asFloat] should: [:r | r = -2.0] conformTo: #'number' selector: #'asFloat'. self value: [0.0 asFloat] should: [:r | r = 0.0] conformTo: #'number' selector: #'asFloat'.! testXtruncateToX " #truncateTo: (returnRule - :receiver :operand) " | retVals | #'Numeric'. " #( 2 -2000000000 2000000000 2.0 1/2 2.0s3 )." retVals := #(2 0 0 2.0 2 2.000s3). 1 to: numList size do: [ :ndx | self value: [float2 truncateTo: (numList at: ndx)] should: [:r | r = (retVals at: ndx)] conformTo: #'number' selector: #'truncateTo:' ruleReceiver: float2 operand: (numList at: ndx) ]. self should: [(0.0 truncateTo: float2) = 0.0].! testXbetweenXandX " #between:and: " #'Numeric'. " #( 2 -2000000000 2000000000 2.0 1/2 2.0s3 )." #'todo'."It is erroneous if the receiver and min or max are not comparable" self value: [2.0 between: 1 and: 3] should: [:r | r] conformTo: #'magnitude' selector: #'between:and:'. self value: [-2000000002.0 between: -2000000003 and: -2000000001] should: [:r | r] conformTo: #'magnitude' selector: #'between:and:'. self value: [2000000002.0 between: 2000000001 and: 2000000003] should: [:r | r] conformTo: #'magnitude' selector: #'between:and:'. self value: [2.0 between: 1.0 and: 3.0] should: [:r | r] conformTo: #'magnitude' selector: #'between:and:'. self value: [2.0 between: (3/2) and: (5/2)] should: [:r | r] conformTo: #'magnitude' selector: #'between:and:'. self value: [2.0 between: 1.0s3 and: 3.0s3] should: [:r | r] conformTo: #'magnitude' selector: #'between:and:'. self value: [2.0 between: (3/2) and: 2000000003] should: [:r | r] conformTo: #'magnitude' selector: #'between:and:'. self value: [2.0 between: -2000000001 and: 3.0s3] should: [:r | r] conformTo: #'magnitude' selector: #'between:and:'. "Num between: Num and: Num -> true" 1 to: numList size do: [ :ndx | self value: [(numList at: ndx) between: (numList at: ndx) and: (numList at: ndx)] should: [:r | r] conformTo: #'magnitude' selector: #'between:and:' ]. self value: [2.0 between: 3 and: 4] shouldnt: [:r | r] conformTo: #'magnitude' selector: #'between:and:'. self value: [-2000000000.0 between: -2000000003 and: -2000000005] shouldnt: [:r | r] conformTo: #'magnitude' selector: #'between:and:'. self value: [2000000000.0 between: 2000000003 and: 2000000005] shouldnt: [:r | r] conformTo: #'magnitude' selector: #'between:and:'. self value: [2.0 between: 3.0 and: 5.0] shouldnt: [:r | r] conformTo: #'magnitude' selector: #'between:and:'. self value: [2.0 between: (5/2) and: (7/2)] shouldnt: [:r | r] conformTo: #'magnitude' selector: #'between:and:'. self value: [2.0 between: 3.0s3 and: 5.0s3] shouldnt: [:r | r] conformTo: #'magnitude' selector: #'between:and:'. "??? min not min but max and vice versa -> false ???" self value: [2.0 between: 3 and: 1] shouldnt: [:r | r] conformTo: #'magnitude' selector: #'between:and:'.! testXtoXbyXdoX " #to:by:do: " #'Numeric'.! setUp super setUp. smallInt2 := 2. largeNegInt2000000000 := -2000000000. largePosInt2000000000 := 2000000000. float2 := 2.0d0. fractionHalf := 1/2. sclDec2s3 := 2.0s3. numList := Array new: 6. numList at: 1 put: smallInt2. numList at: 2 put: largeNegInt2000000000. numList at: 3 put: largePosInt2000000000. numList at: 4 put: float2. numList at: 5 put: fractionHalf. numList at: 6 put: sclDec2s3.! testXtoX " #to: " | start middleNdx stop2 | #'Numeric'. start := 1.0. numList := #( 2 2.0 0 2.0s3 ) copy. numList at: 3 put: (5/2). numList do: [ :stop | self value: [start to: stop] should: [:r | (r size = 2) ". . . the last element in the sequence . . . is . . .[:] receiver + ((stop - receiver) // 1)" & (r last = (start + ((stop - start) // 1))) "The elements conform to the receiver's protocol." & (r allSatisfy: [ :elem | elem class conformsToProtocolNamed: #'Float']) ] conformTo: #'number' selector: #'to:' ]. stop2 := 2000000000. middleNdx := 1000000000. "Check conformance of first, middle and last." self value: [start to: stop2] should: [:r | (r size = 2000000000) ". . . the last element in the sequence . . . is . . .[:] receiver + ((stop - receiver) // 1)" & (r last = (start + ((stop2 - start) // 1))) "The elements conform to the receiver's protocol." & ((Array with: (r at: 1) with: (r at: middleNdx) with: (r at: 3) ) allSatisfy: [ :elem | elem class conformsToProtocolNamed: #'Float']) ] conformTo: #'number' selector: #'to:'. start := -2000000000.0. stop2 := -1. middleNdx := 1000000000. "Check conformance of first, middle and last." self value: [start to: stop2] should: [:r | (r size = 2000000000) ". . . the last element in the sequence . . . is . . .[:] receiver + ((stop - receiver) // 1)" & (r last = (start + ((stop2 - start) // 1))) "The elements conform to the receiver's protocol." & ((Array with: (r at: 1) with: (r at: middleNdx) with: (r at: 3) ) allSatisfy: [ :elem | elem class conformsToProtocolNamed: #'Float']) ] conformTo: #'number' selector: #'to:'. "The interval answered will be empty if the receiver is greater than stop." self value: [1.0 to: -1.0] should: [:r | (r isEmpty)] conformTo: #'number' selector: #'to:'! testXtoXbyX " #to:by: " #'Numeric'.! ! !NilANSITest methodsFor: nil! protocol ^#'nil'! testXprintString " #printString " #'Fundamental'. self value: [nil printString] should: [:r | r = 'nil'] conformTo: #'nil' selector: #'printString'.! canonicalObject ^nil! ! !ObjectClassANSITest methodsFor: nil! protocol ^#'Object class'! testXsubclasses "2000/06/23 Harmon, R. Changed to fix missing class in second test." self value: [Number subclasses] should: [:r | (r allSatisfy: [ :element | element class conformsToProtocolNamed: #'classDescription' ]) & (r isEmpty not) ] conformTo: #'classDescription' selector: #'subclasses'. self value: [Symbol subclasses] should: [:r | r allSatisfy: [ :element | element class conformsToProtocolNamed: #'classDescription' ] ] conformTo: #'classDescription' selector: #'subclasses'.! testXallSubclasses " #allSubclasses " #'Fundamental'. " Each element of the result collection supports the protocol ." #todo. "can't tell of a class that must be present in ANSI ???" self value: [Number allSubclasses] should: [:r | (r allSatisfy: [ :element | element class conformsToProtocolNamed: #'classDescription' ]) & (r isEmpty not) ] conformTo: #'classDescription' selector: #'allSubclasses'. self value: [Symbol allSubclasses] should: [:r | r allSatisfy: [ :element | element class conformsToProtocolNamed: #'classDescription' ] ] conformTo: #'classDescription' selector: #'allSubclasses'.! testXname " #name " #'Fundamental'. self value: [Object name] should: [:r | r asString = 'Object'] conformTo: #'classDescription' selector: #'name'.! canonicalObject ^Object! testXsuperclass " #superclass " #'Fundamental'. " If the receiver is a class object, return the class objects defined by the class definitions from which the class definition of the receiver directly inherits. If the class definition of the receiver has no superclasses, return nil." #'Fundamental'. self value: [Fraction superclass] should: [:r | r isNil ifTrue: [ r conformsToProtocolNamed: #'classDescription' ] ifFalse: [ r class conformsToProtocolNamed: #'classDescription' ] ] conformTo: #'classDescription' selector: #'superclass'. self value: [Object superclass] should: [:r | r isNil ifTrue: [ r class class conformsToProtocolNamed: #'classDescription' ] ifFalse: [ r class conformsToProtocolNamed: #'classDescription' ] ] conformTo: #'classDescription' selector: #'superclass'.! testXallSuperclasses " #allSuperclasses " #'Fundamental'. " Each element of the result collection supports the protocol ." #todo. "can't tell of a class that must be present in ANSI ???" self value: [Fraction allSuperclasses] should: [:r | (r allSatisfy: [ :element | element class conformsToProtocolNamed: #'classDescription' ]) & (r isEmpty not) ] conformTo: #'classDescription' selector: #'allSuperclasses'. self value: [Object allSuperclasses] should: [:r | r allSatisfy: [ :element | element class conformsToProtocolNamed: #'classDescription' ] ] conformTo: #'classDescription' selector: #'allSuperclasses'.! testXnew " #new " #'Fundamental'. self value: [Object new] should: [:r | r class = Object] conformTo: #'Object class' selector: #'new'.! ! !ArrayFactoryANSITest methodsFor: nil! testXnew " #new " #'Collection'.! testXwithXwithX " #with:with: " #'Collection'.! testXwithX " #with: " #'Collection'.! protocol ^#'Array factory'! testXnewX " #new: " #'Collection'.! testXwithAllX " #withAll: " #'Collection'.! canonicalObject ^Array! testXwithXwithXwithX " #with:with:with: " #'Collection'.! canonicalObject ^Array! testXwithXwithXwithXwithX " #with:with:with:with: " #'Collection'.! ! !ProtocolSpec methodsFor: nil! protocolDescription "Answer a description of the receiver." description isNil ifTrue: [ ^ self protocolManager defaultEmptyDescription]. ^ description! displayOn: targetStream "Append the receiver to targetStream in a format that a user would want to see." targetStream nextPut: $<; nextPutAll: self protocolName; nextPut: $>! addUndefinedProtocolNamesInMsgSpec: aProtocolMsgSpec "Private - ." aProtocolMsgSpec allReferredToProtocolNames do: [:protoName | (self protocolManager includesProtocolNamed: protoName asSymbol) ifFalse: [self protocolManager addUndefinedProtocolName: protoName asSymbol]]! setProtocolName: protocolName "Private - ." name := protocolName! addAllMessages: protocolMsgSpecList "Add if not already present all the protocol messages in the list, protocolMsgSpecList, to the set of messages included in the receiver's protocol. Note: protocolMsgSpecList must be a of s," protocolMsgSpecList do: [:msgSpec | self addMessage: msgSpec]! <= comperand "Answer whether the receiver is less than or equal to comperand. Note: This is to allow protocols to be sorted with the default sort block." (comperand isKindOf: self protocolManager protocol) | (comperand isKindOf: self protocolManager protocolANY) ifFalse: [self error: 'Comperand not a ProtocolSpec.']. ^ self protocolName asLowercase <= comperand protocolName asLowercase! removeSelector: selector ifAbsent: notFoundBlock "Answer the message with selector, selector, after removing it from the receiver." | aProtocolMsgSpec | aProtocolMsgSpec := messageSpecifications detect: [:msgSpec | msgSpec messageSelector = selector] ifNone: [^ notFoundBlock value]. ^ messageSpecifications remove: aProtocolMsgSpec! messages "Answer a list of message specifications of the receiver. Note: Return value is a of s," messageSpecifications isNil ifTrue: [ ^ self protocolManager defaultMessageSpecificationCollection]. ^ messageSpecifications! protocolDescription: newDescription "Set the receiver's description to newDescription. Note: If newDescription is empty then description is set to nil." (newDescription isKindOf: String) ifFalse: [self error: 'Protocol description not a String.']. newDescription isEmpty ifTrue: [description := nil] ifFalse: [description := newDescription]! messageSelectors "Answer the list of selectors which make up the receiver's protocol. Note: Return value is a of s," messageSpecifications isNil ifTrue: [ ^ self protocolManager defaultMessageSpecificationCollection]. ^ messageSpecifications collect: [:msgSpec | msgSpec messageSelector]! renameToProtocolName: newName "Rename the receiver protocol to have the new name, newName and update any conforming class or metaclass." | conformingList | (self protocolManager includesProtocolNamed: newName) ifTrue: [^ self error: 'Duplicate protocol name: "' , newName , '".']. conformingList := self conformingBehaviors. conformingList do: [:classOrMetaclass | classOrMetaclass removeProtocolNamed: self protocolName]. self setProtocolName: newName. self protocolManager privateRehashProtocols. conformingList do: [:classOrMetaclass | classOrMetaclass addProtocolNamed: newName]! newProtocolName: protocolName conformsToProtocolNames: conformsToList "Private - ." name := protocolName. conformsTo := conformsToList! addUndefinedProtocolNames "Private - ." messageSpecifications isNil ifTrue: [^ self]. messageSpecifications do: [:msgSpec | self addUndefinedProtocolNamesInMsgSpec: msgSpec]! printOn: targetStream "Append to targetStream a text representation of the receiver as a developer would want to see it (inspector, etc)." targetStream nextPut: $<; nextPutAll: self protocolName; nextPut: $>; nextPut: $(. self messageSelectors do: [:selector | targetStream nextPutAll: selector] separatedBy: [targetStream nextPutAll: ', ']. targetStream nextPut: $)! includesSelector: selector "Answer whether the receiver includes the selector, selector." ^ self messageSelectors includes: selector! fileOutOnSIFFiler: programFiler "File out the receiver definition and its message definitions on ANSI SIF filer, programFiler." #todo."??? Add annotations ???" programFiler fileOutProtocolDefinitionOf: self protocolName conformsToProtocolNames: self conformsToProtocolNames description: self protocolDescription annotations: Dictionary new. self messages asSortedCollection do: [:messageSpec | messageSpec fileOutOnSIFFiler: programFiler protocol: self protocolName]! inheritedMessageOrNilAtSelector: selector | msg | conformsTo do: [:protocolName | msg := (ProtocolSpec protocolNamed: protocolName) messageOrNilAtSelector: selector. msg notNil ifTrue: [^msg]]. ^nil! addMessage: aProtocolMsgSpec "Add if not already present the protocol message, aProtocolMsgSpec, to the set of messages included in the receiver's protocol." (aProtocolMsgSpec isKindOf: self protocolManager protocolMsgSpec) ifFalse: [self error: 'Protocol message not a ProtocolMsgSpec.']. (self includesSelector: aProtocolMsgSpec messageSelector) ifFalse: [messageSpecifications isNil ifTrue: [messageSpecifications := self protocolManager defaultMessageSpecificationCollection]. messageSpecifications add: aProtocolMsgSpec. self addUndefinedProtocolNamesInMsgSpec: aProtocolMsgSpec]! hash "Answer the hash value for the receiver." ^ self protocolName hash! selectorsInBehavior: classOrMetaclass "If the class or metaclass, classOrMetaclass, conforms to the receiver answer all the selectors in which have corresponding messages, else an empty list. Note: Return value is a of s," (classOrMetaclass conformsToProtocolNamed: self protocolName) ifTrue: [^ (classOrMetaclass selectors select: [:selector | self includesSelector: selector]) asSet]. ^ Set new! removeAllSelectors: selectorList "After removing from the receiver all the messages with selectors, selectorList, answer them. Note: selectorList must be a of s." | messageSpecs | messageSpecs := Set new. selectorList do: [:selector | messageSpecs add: (self removeSelector: selector)]. ^ messageSpecs! errorSelectorNotFound: selector "Private -" self error: 'Protocol ' , self printString , ' message "' , selector , '" not found'! zremoveClass: classOrMetaclass "Remove the receiver's name from the class or the metaclass, classOrMetaclass, list of protocol names. ??not that great an idea???" classOrMetaclass removeProtocolNamed: self protocolName! = comperand "Answer whether the receiver is considered equal (contains same elements) to comperand." #todo."I'm not sure this makes any sense (= is ==) because if they have the same name they have to be the same object. If it makes sense, shouldn't this test if contains same selectors?????" ^ (comperand isKindOf: self protocolManager protocol) and: [self protocolName == comperand protocolName]! removeSelector: selector "Answer the message with selector, selector, after removing it from the receiver." ^ self removeSelector: selector ifAbsent: [self errorSelectorNotFound: selector]! messageAtSelector: selector "Answer the message spec. at selector." | msg | msg := self messageOrNilAtSelector: selector. msg notNil ifTrue: [^msg]. self error: 'Protocol message spec. at selector: "', selector, '" not found.'! messageOrNilAtSelector: selector messageSpecifications isNil ifTrue: [ ^self inheritedMessageOrNilAtSelector: selector]. ^messageSpecifications detect: [ :protocol | protocol messageSelector = selector] ifNone: [^self inheritedMessageOrNilAtSelector: selector].! conformingBehaviors "Answer all the classes which conform to the receiver in class hierarchy order (i.e. superclasses first). Note: Return value is a of class or metaclass objects." | answer | answer := OrderedCollection new: 10. Smalltalk allClasses do: [:class | (class conformsToProtocolNamed: self protocolName) ifTrue: [answer addLast: class]. (class class conformsToProtocolNamed: self protocolName) ifTrue: [answer addLast: class class]]. ^ answer! protocolName "Answer the name of the receiver." ^ name! conformsToProtocolNames "Answer the protocol names to which the receiver conforms." ^ conformsTo! ! !ProtocolSpec class methodsFor: nil! classProtocols ^ClassProtocols! installProtocolModelUnitTests | ansiDir devDir fileName sep | devDir := 'C:\Dev\'. "Typical DOS location" "devDir := '%F:\Dev\'." "Sub. doublequote for % Typical Mac location" "devDir := '/usr/local/squeak/rharmon/Dev/'." "Typical Unix location" sep := FileDirectory pathNameDelimiter asString. ansiDir := devDir , 'ANSI' , sep , 'ANSIGood' , sep , 'Squeak' , sep. fileName := 'ProtoUT.sif'. ChangeSorter newChangesOf: ["ProgramManager" nil current installProgramFileLocator: ansiDir , fileName] named: fileName sansPeriodSuffix! wrkAssocGlobalGenUnitTestsForProtocolGroup: protocolGroupName protocolGlobalsClassSideGenTests: protocolGlobalsClassSideGenTests "Private - Generate unit test stub classes for protocol group named, protocolGroupName. Parameter protocolGlobalsClassSideGenTests array has the protocol name, correspnding global classes, instance or class side protocol ind, and generate unit test ind. It will generate the methods specified by protocol and conforms-To protocols in the test class for each protocol global class (or protocol inheritance tree leaf). The test method naming convention I use is: instance side protocolmethods: testInstXselector testInstXselectorX class side protocol methods: testClsXselector testClsXselectorX conformsTo protocol methods: testConToXselector testConToXselectorX operator (+, ==, /, etc) methods: testInstXadditionOp testInstXfixOp1 The operator test methods testInstXfixOp1 have to be hand editted to change test method selector to testInstXoperatorNameOp. Example use: " | assocGlobalClasses genUnitTestSw isClassSideProtocolSw protocolName | protocolGlobalsClassSideGenTests do: [:parmArray | protocolName := parmArray at: 1. assocGlobalClasses := parmArray at: 2. isClassSideProtocolSw := (parmArray at: 3) = 'class'. genUnitTestSw := (parmArray at: 4) = 'UT'. self wrkAssocProtocolNamed: protocolName toClassesNamed: assocGlobalClasses isClassSideProtocol: isClassSideProtocolSw. genUnitTestSw ifTrue: [self wrkGenTestClassForProtocol: protocolName inProtocolGroupNamed: protocolGroupName isClassSideProtocol: isClassSideProtocolSw]]! newProtocolNamed: protocolName conformsToProtocolNames: conformsToList "Answer a new protocol with the specified name, protocolName that conforms to the protocols named in conformsToList." ^ self privateNewProtocolNamed: protocolName conformsToProtocolNames: conformsToList! xCommonTasks "The following are tasks comonly performed:" "Initialize the list of protocol objects:" 1 protocolManager initializeProtocols. "Remove protocol objects not currently assigned to any class or metaclass (Answers a list. This might take a while.):" 1 protocolManager purgeUnused. "Remove protocol object:" 1 protocolManager removeProtocolNamed: #'classDescription'. "Answer the sorted list of protocol name symbols:" 1 protocolManager allProtocolNamesSorted. "Answer the list of protocol name symbols:" 1 protocolManager allProtocolNames. "Answer the list of undefined conforms-to protocol name symbols:" 1 protocolManager undefinedConformsToProtocolNames. "Answer the list of conforming classes or metaclasses:" (1 protocolManager protocolNamed: #'integer') conformingBehaviors. "Answer the list of conforms-to protocol name symbols:" (self protocolManager protocolNamed: 'Object class' asSymbol) allConformsToProtocolNames. "-> Set (ANY Object instantiator classDescription )" "Answer the list of all of selectors which make up the protocol and all protocols to which the it conforms:" (self protocolManager protocolNamed: 'Object class' asSymbol) allMessageSelectors. "Answer the list of all of selectors which make up the protocol:" (self protocolManager protocolNamed: 'Object class' asSymbol) conformsToMessageSelectors. 1 protocolManager includesProtocolNamed: #'Object'. "-> true" "Assign or query classes or metaclasses:" (SUnitNameResolver classNamed: #'Symbol') addProtocolNamed: #'Object'. ExceptionSet removeProtocolNamed: #'exceptionSet'. ExceptionSet protocolNames. "-> Set (exceptionSet )" ExceptionSet class protocolNames. "-> Set ()" ExceptionSet conformsToProtocolNamed: #'Object'. "-> true" ExceptionSet class conformsToProtocolNamed: #'Object'. "-> true" Symbol conformsToProtocolNamed: #'Object'. "-> true" true class protocolNames. "-> Set ()" true class conformsToProtocolNamed: #'boolean'! protocolANYName "Answer the protocol name." ^ #'ANY'! defaultMessageSpecificationCollection "Private - Answer an , the default messageSpecification collection." ^ Set new! xRemoveMsgSpecSelectors: selectorList fromProtocolNamed: protoName "Answer the list of msg specs with selectors, selectorList, after removing the msg specs from protocol named, protoName. Example: 1 protocolManager xRemoveMsgSpecSelectors: #(#'name') fromProtocolNamed: #'classDescription' " | proto | proto := self protocolManager protocolNamed: protoName. ^ proto removeAllSelectors: selectorList! defaultEmptyDescription "Private - Answer an , the default empty description." ^ String new! purgeUnused "Answer a list of protocols which are not currently implemented by any class or metaclass in the system after removing them. Note: This might take a while. Example: 1 protocolManager purgeUnused " #todo."Fix??? don't forget to leave even though no class explicity conforms?? " self notYetImplemented! wrkGenTestClassForProtocol: protocolName inProtocolGroupNamed: protocolGroupName isClassSideProtocol: isClassSideProtocolSw "Private - Generate test suite stub methods for the directly specified messages and all conforms-To protocols of protocol named, protocolName, in protocol group named, protocolGroupName. Parameter isClassSideProtocolSw indicates an instance or class side protocol. The test method naming convention I use is: instance side protocol methods: testInstXselector testInstXselectorX class side protocol methods: testClsXselector testClsXselectorX conformsTo protocol methods: testConToXselector testConToXselectorX operator (+, ==, /, etc) methods: testInstXadditionOp testInstXfixOp1 The operator test methods testInstXfixOp1 have to be hand editted to change test method selector to testInstXoperatorNameOp. Example use: " | protocol testSelName commentTmp aDict visitedProtocols testClass | protocol := 1 protocolManager protocolNamed: protocolName asSymbol. FixNum := 0. testClass := self wrkTestClassForProtocol: protocolName inProtocolGroupNamed: protocolGroupName. "Build a message selector->protocol dictionary of the directly specified and all conforms-To protocols messages" aDict := Dictionary new. visitedProtocols := Set new. protocol wrkAllConformsToMessageSelectorsTo: aDict visited: visitedProtocols. "Generate test suite methods" aDict keysAndValuesDo: [:msgSel :aProtocolName | testSelName := self wrkTestMethdodNameFrom: msgSel. commentTmp := '" <' , aProtocolName , '>#' , msgSel , ' "'. testClass compile: testSelName , ' ' , commentTmp , ' #''' , protocolGroupName , '''. '. testClass classify: testSelName asSymbol under: 'testing']! xGlobalsImplementAllMsgsOfProtocolNamed: protoName "Answer the a Dictionary containing the conforming global class or metaclass name and corresponding missing selector symbol of protocol named, protoName. Example: 1 protocolManager xGlobalsImplementAllMsgsOfProtocolNamed: #'Character factory' " | protocol missingMsg conformingBehaviorObjs | protocol := 1 protocolManager protocolNamed: protoName. conformingBehaviorObjs := (1 protocolManager protocolNamed: 'Character factory' asSymbol) conformingBehaviors. missingMsg := Dictionary new. protocol messageSelectors do: [:msgSel | conformingBehaviorObjs do: [:classOrMetaclassObj | (classOrMetaclassObj includesSelector: msgSel) ifFalse: [missingMsg at: classOrMetaclassObj name put: msgSel]]]. ^ missingMsg! xRuleSourceOfMsgSelector: selector inProtocolNamed: protoName "Answer the return value rule block source of msg with selector, selector, in protocol named, protoName. Example: 1 protocolManager xRuleSourceOfMsgSelector: #'+' inProtocolNamed: #'number' " | msgSpec proto | proto := self protocolManager protocolNamed: protoName. msgSpec := proto messageAtSelector: selector. ^ msgSpec specForEachReturnValueList asArray first returnValueRuleBlockSource! allProtocolNamesSorted "Answer the names of all Protocols in the system sorted ignoring case." ^ (Protocols collect: [:protocol | protocol protocolName]) asSortedCollection sortBlock: [:x :y | x asLowercase <= y asLowercase]! allProtocols "Answer all Protocols in the system." ^ Protocols! addUndefinedProtocolName: protocolName "Private - ." (protocolName isKindOf: Symbol) ifFalse: [self error: 'Protocol name not a Symbol.']. UndefinedConformsToNames add: protocolName! fileOutSIFAllProtocolsDescOnFiler: programFiler "Private - File out an all-protocols program description in ANSI SIF format on the programFiler." | annotations | annotations := Dictionary new. annotations at: 'createdByApp' put: self portFunc dialectNameVersionString. annotations at: 'createdDateTime' put: self portFunc currentDateTimeString. programFiler fileOutProgramDescName: 'AllProto' prerequisiteProgramNames: (Set with: 'ACSProS') programAnnotations: annotations! allProtocolNames "Answer the names of all Protocols in the system." ^ (Protocols collect: [:protocol | protocol protocolName]) asSet! unaryReturnProtocolNameReceiver: receiver "Answer the return value conforms-to protocol name of a unary message performing arithmetic, arithmetic progressions, and conversion on numerical quantities sent to receiver." | receiverProto | receiverProto := self instanceProtocol: receiver. ^ UnaryConvTable at: receiverProto! xMessagesAndReturnValuesOfProtocolNamed: protoName "Answer the a string containing the messages and their corresponding return values of protocol named, protoName. Example: 1 protocolManager xMessagesAndReturnValuesOfProtocolNamed: #'instantiator' " | protocol aStream | aStream := WriteStream on: (String new: 500). aStream cr. protocol := 1 protocolManager protocolNamed: protoName. protocol messages asSortedCollection do: [:msg | msg messageSelector printOn: aStream. aStream nextPutAll: '->'. msg specForEachReturnValueList printOn: aStream. aStream cr]. aStream contents! privateRehashProtocols "Private -" Protocols rehash! defaultConformsToCollection "Private - Answer an , the default conformsTo collection." ^ Set new! initializeOperatorTable "Discard all existing protocols. Example: self protocolManager initializeOperatorTable " OperatorTable := Dictionary new. OperatorTable at: #'=' put: 'equalityOp'. OperatorTable at: #'==' put: 'identityOp'. OperatorTable at: #'~=' put: 'notEqualityOp'. OperatorTable at: #'~~' put: 'notIdentityOp'. OperatorTable at: #'&' put: 'andOp'. OperatorTable at: #'|' put: 'orOp'. OperatorTable at: #'<' put: 'lessThanOp'. OperatorTable at: #'<=' put: 'lessThanOrEqualToOp'. OperatorTable at: #'>' put: 'greaterThanOp'. OperatorTable at: #'>=' put: 'greaterThanOrEqualToOp'. OperatorTable at: #'*' put: 'multiplyOp'. OperatorTable at: #'+' put: 'addOp'. OperatorTable at: #'-' put: 'subtractOp'. OperatorTable at: #'/' put: 'divideOp'. OperatorTable at: #'//' put: 'integerDivideOp'. OperatorTable at: #'\\' put: 'remainderIntegerDivideOp'. OperatorTable at: #',' put: 'concatenateOp'! privateNewProtocolNamed: protocolName conformsToProtocolNames: conforms "Private -" | newProtocol conformsTmp | (self includesProtocolNamed: protocolName) ifTrue: [^ self error: 'Protocol named "' , protocolName , '" already exists.']. conformsTmp := self privateValidConformsToProtocolNames: conforms ifError: [^ self error: 'Protocol conforms-to list not a of existing protocol name s.']. (protocolName isKindOf: Symbol) ifFalse: [self error: 'Protocol name not a Symbol.']. newProtocol := self basicNew. newProtocol newProtocolName: protocolName conformsToProtocolNames: conformsTmp. Protocols add: newProtocol. (UndefinedConformsToNames includes: protocolName) ifTrue: [UndefinedConformsToNames remove: protocolName]. ^ newProtocol! defaultSpecSectionsCollection "Private - Answer an , the default SpecSections collection." ^ Dictionary new! renameProtocolNamed: oldName to: newName "Rename the protocol named oldName to have the new name, newName. and update any conforming class or metaclass." | targetProtocol | targetProtocol := self protocolNamed: oldName. targetProtocol renameToProtocolName: newName! specSectionsFromSynopsis: messageSynopsis definedIn: definedInProtocolName definition: messageDefinition refinedIn: refinedInProtocolName refinement: messageRefinement errors: messageErrors "Private - Create a new specification sections with parms and return it." | secDict | secDict := self protocolManager defaultSpecSectionsCollection. definedInProtocolName isEmpty ifFalse: [secDict at: #'DefinedIn' put: definedInProtocolName]. messageDefinition isEmpty ifFalse: [secDict at: #'Definition' put: messageDefinition]. messageErrors isEmpty ifFalse: [secDict at: #'Errors' put: messageErrors]. refinedInProtocolName isEmpty ifFalse: [secDict at: #'RefinedIn' put: refinedInProtocolName]. messageRefinement isEmpty ifFalse: [secDict at: #'Refinement' put: messageRefinement]. messageSynopsis isEmpty ifFalse: [secDict at: #'Synopsis' put: messageSynopsis]. ^ secDict! protocolMsgParmSpec "Answer the protocol message parameter specification class object." ^ SUnitNameResolver classNamed: #'MsgParmSpec'! instanceProtocol: number "Answer the conforms-to protocol name of number." #(#'integer' #'Float' #'Fraction' #'scaledDecimal' ) do: [:protoName | (number class conformsToProtocolNamed: protoName) ifTrue: [^ protoName]]. self error: 'Instance does not conforms to any numeric protocol.'! wrkAssocProtocolNamed: protocolName toClassesNamed: assocGlobalClassesArray isClassSideProtocol: isClassSideProtocolSw "Private - Assign a protocol to a list of ANSI class globals." | classSymbol | assocGlobalClassesArray do: [:className | classSymbol := className asSymbol. isClassSideProtocolSw ifTrue: [(SUnitNameResolver classNamed: classSymbol) class addProtocolNamed: protocolName] ifFalse: [(SUnitNameResolver classNamed: classSymbol) addProtocolNamed: protocolName]]! wrkAllRuleReturnValueList "Private - Answers a Dictionary of protocols containing messages with return value specified by a rule. The key is the protocol name and the value is a Dictionarys of message selector keys and return value spec. set with one MsgReturnRuleSpec containing the rule source code. Example use: (FileStream readOnlyFileNamed: 'C:\Dev\ANSI\ANSIGood\Squeak\AProtos.st.chg' ) fileIn. 1 protocolManager wrkAllRuleReturnValueList " | protocolsWithRuleList msgSelRuleCodeList | protocolsWithRuleList := Dictionary new. self protocolManager allProtocols do: [:protocol | protocol messages do: [:msg | msg isReturnValueSpecByRule ifTrue: [msgSelRuleCodeList := protocolsWithRuleList at: protocol protocolName ifAbsent: [protocolsWithRuleList at: protocol protocolName put: Dictionary new]. msgSelRuleCodeList at: msg messageSelector put: msg specForEachReturnValueList]]]. ^ protocolsWithRuleList! initializeDefaultConversionTable "Discard all existing protocols. Example: self protocolManager protocol initializeDefaultConversionTable " | tmp | DefaultConvTable := Dictionary new. tmp := Dictionary new. tmp at: #'integer' put: #'integer'. tmp at: #'scaledDecimal' put: #'scaledDecimal'. tmp at: #'Fraction' put: #'Fraction'. tmp at: #'Float' put: #'Float'. DefaultConvTable at: #'integer' put: tmp. tmp := Dictionary new. tmp at: #'integer' put: #'scaledDecimal'. tmp at: #'scaledDecimal' put: #'scaledDecimal'. tmp at: #'Fraction' put: #'Fraction'. tmp at: #'Float' put: #'Float'. DefaultConvTable at: #'scaledDecimal' put: tmp. tmp := Dictionary new. tmp at: #'integer' put: #'Fraction'. tmp at: #'scaledDecimal' put: #'Fraction'. tmp at: #'Fraction' put: #'Fraction'. tmp at: #'Float' put: #'Float'. DefaultConvTable at: #'Fraction' put: tmp. tmp := Dictionary new. tmp at: #'integer' put: #'Float'. tmp at: #'scaledDecimal' put: #'Float'. tmp at: #'Fraction' put: #'Float'. tmp at: #'Float' put: #'Float'. DefaultConvTable at: #'Float' put: tmp! new "ProtocolSpecs must be unique for any particular name, and must be instantiated with the #name: method." ^ self shouldNotImplement! initialize "Class initialization. Example: ProtocolSpec initialize " ClassProtocols := LookupTable new. self initializeProtocols. self initializeDefaultConversionTable. self initializeUnaryConversionTable. self initializeOperatorTable! includesProtocolNamed: protocolName "Answer whether the named protocol exists." (protocolName isKindOf: Symbol) ifFalse: [self error: 'Protocol name not a Symbol.']. Protocols detect: [:protocol | protocol protocolName = protocolName] ifNone: [^ false]. ^ true! parametersFromList: parmList "Private - Create a new protocol message specification with message, messagePattern, etc. to protocol named protocolName." | newParmSpecs names | newParmSpecs := parmList collect: [:anArray | names := (anArray at: 2) subStrings collect: [:nameString | name asSymbol]. self protocolManager protocolMsgParmSpec newParmName: (anArray at: 1) protocolNames: names aliasing: (anArray at: 3)]. ^ newParmSpecs! wrkTestClassForProtocol: protocolName inProtocolGroupNamed: protocolGroupName "Private - Answer a unit test class for protocol named, protocolName, in group named, protocolGroupName." | testClassName tmp classObj | testClassName := String new. tmp := protocolName subStrings. tmp do: [:protocolNameParts | protocolNameParts at: 1 put: (protocolNameParts at: 1) asUppercase. testClassName := testClassName , protocolNameParts]. testClassName := (testClassName , 'ANSITest') asSymbol. classObj := [(SUnitNameResolver classNamed: #'TestCaseProtocol') subclass: testClassName instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Tests-ANSI-' , protocolGroupName] on: Error do: [:except | except messageText: 'Error compiling class definition of : "' , testClassName , '" - ' , except description. except resignalAs: Warning]. ^ classObj! removeProtocolNamed: protocolName "Remove the protocol named, protocolName, from the system. Note: Protocol can not be removed." | conformingList targetProtocol | protocolName = self protocolManager protocolANYName ifTrue: [self error: 'Protocol <' , protocolName , '> can not be removed.']. targetProtocol := self protocolNamed: protocolName. #todo."fix not to use conformingBehaviors (includes subclasses) but classDescription protocolNames includes: ???" conformingList := targetProtocol conformingBehaviors. conformingList do: [:classOrMetaclass | (classOrMetaclass protocolNames includes: protocolName) ifTrue: [classOrMetaclass removeProtocolNamed: protocolName]]. Protocols remove: targetProtocol ifAbsent: [self error: 'Protocol named: "' , protocolName , '" not found.']! newMessagePattern: messagePattern forProtocolNamed: protocolName synopsis: messageSynopsis definedIn: definedInProtocolName definition: messageDefinition refinedIn: refinedInProtocolName refinement: messageRefinement parameters: parmList returnValues: returnValuesList errors: messageErrors "Create a new protocol message specification with message, messagePattern, etc. to protocol named protocolName." | newParmSpecs newReturnSpec secDict | newParmSpecs := self parametersFromList: parmList. newReturnSpec := returnValuesList collect: [:anArray | self protocolManager protocolMsgReturnValueSpec newRetValProtocolNames: (Set with: (anArray at: 1) asSymbol) aliasing: (anArray at: 2)]. secDict := self specSectionsFromSynopsis: messageSynopsis definedIn: definedInProtocolName definition: messageDefinition refinedIn: refinedInProtocolName refinement: messageRefinement errors: messageErrors. (self protocolNamed: protocolName) addMessage: (self protocolMsgSpec newSelector: (String methodSelector: messagePattern , ' ') asSymbol specSections: secDict specsForEachParm: newParmSpecs specsForEachReturnValue: newReturnSpec)! defaultReturnProtocolNameReceiver: receiver operand: operand "Answer the return value conforms-to protocol name of a message performing arithmetic, arithmetic progressions, and conversion on numerical quantities involving receiver and operand. Note: The result type of most numeric opeations is based upon the operand type. The Default Result Type for all operand types except is the type to which the operands have been converted according to the Default ConversionTable. If the converted operand type is the Default Result Type is . In all cases where the type of the return value differs from the default result type it is noted in the operation's description." | receiverProto operandProto convertedOperandType | receiverProto := self instanceProtocol: receiver. operandProto := self instanceProtocol: operand. convertedOperandType := (DefaultConvTable at: receiverProto) at: operandProto. convertedOperandType = #'Fraction' ifTrue: [^ #'rational']. ^ convertedOperandType! newMessagePattern: messagePattern forProtocolNamed: protocolName synopsis: messageSynopsis definedIn: definedInProtocolName definition: messageDefinition refinedIn: refinedInProtocolName refinement: messageRefinement parameters: parmList returnRule: returnValueRule errors: messageErrors "Create a new protocol message specification with message, messagePattern, etc. to protocol named protocolName." | newParmSpecs newReturnSpecs secDict | newParmSpecs := self parametersFromList: parmList. newReturnSpecs := Set with: (self protocolManager protocolMsgReturnValueRuleSpec newRetValRuleSourceCode: returnValueRule). secDict := self specSectionsFromSynopsis: messageSynopsis definedIn: definedInProtocolName definition: messageDefinition refinedIn: refinedInProtocolName refinement: messageRefinement errors: messageErrors. (self protocolNamed: protocolName) addMessage: (self protocolMsgSpec newSelector: (String methodSelector: messagePattern , ' ') asSymbol specSections: secDict specsForEachParm: newParmSpecs specsForEachReturnValue: newReturnSpecs)! protocolsInNameList: protocolNameList "Answer the list of protocols named in protocolNameList." ^ (protocolNameList collect: [:protocolName | self protocolNamed: protocolName]) asSet! protocolMsgSpec "Answer the protocol message specification class object." ^ SUnitNameResolver classNamed: #'ProtocolMsgSpec'! protocolANY "Answer the protocol class object." ^ SUnitNameResolver classNamed: #'ProtocolANYSpec'! initializeUnaryConversionTable "Discard all existing protocols. Example: self protocolManager protocol initializeDefaultConversionTable " UnaryConvTable := Dictionary new. UnaryConvTable at: #'integer' put: #'rational'. UnaryConvTable at: #'Fraction' put: #'rational'. UnaryConvTable at: #'rational' put: #'rational'. UnaryConvTable at: #'scaledDecimal' put: #'scaledDecimal'. UnaryConvTable at: #'Float' put: #'Float'! wrkChkTestsForProtocol: protocolName inProtocolGroupNamed: protocolGroupName isClassSideProtocol: isClassSideProtocolSw "Private - Generate test suite stub methods for the directly specified messages and all conforms-To protocols of protocol named, protocolName, in protocol group named, protocolGroupName. Parameter isClassSideProtocolSw indicates an instance or class side protocol. The test method naming convention I use is: instance side protocol methods: testInstXselector testInstXselectorX class side protocol methods: testClsXselector testClsXselectorX conformsTo protocol methods: testConToXselector testConToXselectorX operator (+, ==, /, etc) methods: testInstXadditionOp testInstXfixOp1 The operator test methods testInstXfixOp1 have to be hand editted to change test method selector to testInstXoperatorNameOp. Example use: " | protocol testSelNameSymbol protocolNameSymbolTmp sourceTmp aDict visitedProtocols testClass s1 s2 | protocol := 1 protocolManager protocolNamed: protocolName asSymbol. FixNum := 0. testClass := self wrkTestClassForProtocol: protocolName inProtocolGroupNamed: protocolGroupName. "Build a message selector->protocol dictionary of the directly specified and all conforms-To protocols messages" aDict := Dictionary new. visitedProtocols := Set new. protocol wrkAllConformsToMessageSelectorsTo: aDict visited: visitedProtocols. "Generate test suite methods" aDict keysAndValuesDo: [:msgSel :aProtocolName | testSelNameSymbol := (self wrkTestMethdodNameFrom: msgSel) asSymbol. (testClass includesSelector: testSelNameSymbol) ifTrue: [sourceTmp := (testClass sourceMethodAt: testSelNameSymbol) asString. s1 := (sourceTmp indexOf: $<) + 1. s2 := (sourceTmp indexOf: $>) - 1. protocolNameSymbolTmp := (sourceTmp copyFrom: s1 to: s2) asSymbol. self halt. protocolNameSymbolTmp = aProtocolName ifFalse: [self halt]]]! wrkGenerateMethdodsInTestClassNamed: testClassName forProtocolNamed: protocolName inProtocolGroupNamed: protocolGroupName isClassSideProtocol: isClassSideProtocolSw "Private - Generate test suite stub methods in test class named, testClassName, for protocol named, protocolName, in protocol group named, protocolGroupName, that is an instance side protocol (isClassSideProtocolSw = false) or class side protocol (isClassSideProtocolSw = true). I name instance side protocol test methods %testInstXselector% & %testInstXselectorX% for Class >>#selector & Class >>#selector:. I name class side protocol test methods %testClsXselector% & %testClsXselectorX% for Class >>#selector & Class >>#selector:. I name operator (+, ==, /, etc) test methods %testInstXfixOp1% Class >>#selector & Class >>#+. I number these fixes sequentially starting with 1. The operator (+, ==, /, etc) test methods %testInstXfixOp1% have to be hand editted to change test method selector to %testInstXadditionOp% (identityOp, divisionOp, etc). Example use: 1 protocolManager wrkGenerateMethdodsInTestClassNamed: 'CharacterFactoryProtocolTest' forProtocolNamed: #'Character factory' inProtocolGroupNamed: 'Numeric' isClassSideProtocol: true. 1 protocolManager wrkGenerateMethdodsInTestClassNamed: 'CharacterProtocolTest' forProtocolNamed: #'Character' inProtocolGroupNamed: 'Numeric' isClassSideProtocol: false. " | protocol testSelName instOrClass classOrMetaclassObj fixNum commentTmp opTable | opTable := Dictionary new. opTable at: #'=' put: 'equalityOp'. opTable at: #'==' put: 'identityOp'. opTable at: #'~=' put: 'notEqualityOp'. opTable at: #'~~' put: 'notIdentityOp'. opTable at: #'&' put: 'andOp'. opTable at: #'|' put: 'orOp'. opTable at: #'<' put: 'lessThanOp'. opTable at: #'<=' put: 'lessThanOrEqualToOp'. opTable at: #'>' put: 'greaterThanOp'. opTable at: #'>=' put: 'greaterThanOrEqualToOp'. opTable at: #'*' put: 'multiplyOp'. opTable at: #'+' put: 'addOp'. opTable at: #'-' put: 'subtractOp'. opTable at: #'/' put: 'divideOp'. opTable at: #'//' put: 'integerDivideOp'. opTable at: #'\\' put: 'remainderIntegerDivideOp'. protocol := 1 protocolManager protocolNamed: protocolName. "Generate test suite class method >>#suite :" classOrMetaclassObj := (SUnitNameResolver classNamed: testClassName asSymbol) class. classOrMetaclassObj compile: 'suite | testSuite | testSuite := TestSuite new. self selectors do: [ :selector | (selector indexOfSubCollection: ''test'') = 1 ifTrue: [ testSuite addTest: (self selector: selector) ] ]. ^testSuite '. classOrMetaclassObj classify: #'suite' under: 'instance creation'. "Generate test suite instance methods >>#testInstXetc or >>#testClsXetc :" isClassSideProtocolSw ifTrue: [instOrClass := 'Cls'] ifFalse: [instOrClass := 'Inst']. fixNum := 0. protocol messageSelectors do: [:msgSel | msgSel isInfix ifTrue: [(opTable includesKey: msgSel) ifTrue: [testSelName := 'test' , instOrClass , 'X' , (opTable at: msgSel)] ifFalse: [fixNum := fixNum + 1. testSelName := 'test' , instOrClass , 'XfixOp' , fixNum printString]] ifFalse: [testSelName := 'test' , instOrClass , 'X' , (msgSel asString collect: [:char | char = $: ifTrue: [$X] ifFalse: [char]])]. commentTmp := '" ' , msgSel , ' "'. classOrMetaclassObj := SUnitNameResolver classNamed: testClassName asSymbol. classOrMetaclassObj compile: testSelName , ' ' , commentTmp , ' #''' , protocolGroupName , '''. '. classOrMetaclassObj classify: testSelName asSymbol under: 'testing']! privateValidConformsToProtocolNames: protocolNamesIn ifError: errorBlock "Private -" | protocolNamesTmp | (protocolNamesIn isKindOf: Collection) ifFalse: [^ errorBlock value]. protocolNamesIn isEmpty ifTrue: [^ errorBlock value]. protocolNamesIn isEmpty ifTrue: [^ errorBlock value]. protocolNamesTmp := self protocolManager defaultProtocolNameCollection. protocolNamesIn do: [:protocolName | (protocolName isKindOf: Symbol) ifFalse: [^ errorBlock value]. (self protocolManager includesProtocolNamed: protocolName) ifFalse: [self protocolManager addUndefinedProtocolName: protocolName]. protocolNamesTmp add: protocolName]. ^ protocolNamesTmp! fileOutAllProtocolsSIFFiler: programFiler "File out all protocol definitions on ANSI SIF filer, programFiler." | allProtos | allProtos := self allProtocols asSortedCollection. allProtos remove: (self protocolNamed: self protocolANYName) ifAbsent: []. self fileOutSIFAllProtocolsDescOnFiler: programFiler. allProtos do: [:protocol | protocol fileOutOnSIFFiler: programFiler]! initializeProtocols "Discard all existing protocols. Example: self protocolManager protocol initializeProtocols " | nameList | (Protocols notNil and: [Protocols size > 1]) ifTrue: [nameList := String new. "Not just protocol " (Protocols asArray copyFrom: 1 to: (3 min: Protocols size)) do: [:protocol | nameList := nameList , protocol protocolName] separatedBy: [nameList := nameList , ', ']. Protocols size > 3 ifTrue: [nameList := nameList , ' ...']. (self portFunc promptYesNo: 'You are about to lose protocols (' , nameList , '). Do it?') ifFalse: ["Do NOT discard existing protocols." ^ self]]. UndefinedConformsToNames := self defaultProtocolNameCollection. Protocols := self defaultProtocolCollection. Protocols add: (SUnitNameResolver classNamed: #'ProtocolANYSpec') privateNewProtocolANY! defaultProtocolCollection "Private - Answer an , the default protocol collection." ^ Set new! installProtocolDocReader "Extracts the parts of ANSI style protocol specs from the proposed ANSI Smalltalk standard document and builds the protocol objects." | ansiDir devDir fileName sep | devDir := 'C:\Dev\'. "Typical DOS location" "devDir := '/usr/local/squeak/rharmon/Dev/'." "Typical Unix location" "devDir := '%F:\Dev\'." "Sub. doublequote for % Typical Mac location" sep := FileDirectory pathNameDelimiter asString. ansiDir := devDir , 'ANSI' , sep , 'ANSIGood' , sep , 'Squeak' , sep. fileName := 'PDocRdr.sif'. ChangeSorter newChangesOf: ["ProgramManager" nil current installProgramFileLocator: ansiDir , fileName] named: fileName sansPeriodSuffix! errorProtocolNotFound: protocolName "Private -" self error: 'Protocol <' , protocolName , '> not found'! protocolNamed: protocolName "Answer the protocol named protocolName." (protocolName isKindOf: Symbol) ifFalse: [self error: 'Protocol name not a Symbol.']. ^ Protocols detect: [:protocol | protocol protocolName = protocolName] ifNone: [self error: 'Protocol named: "' , protocolName , '" not found.']! wrkTestMethdodNameFrom: messageSelector "Private - Answer a generated test suite stub method name from messageSelector. fixNum which may be incremented if a test methdod name is generated that must be fixed up by hand." | testSelName | messageSelector isInfix ifTrue: [(OperatorTable includesKey: messageSelector) ifTrue: [testSelName := 'testX' , (OperatorTable at: messageSelector)] ifFalse: [FixNum := FixNum + 1. testSelName := 'testXfixOp' , FixNum printString]] ifFalse: [testSelName := 'testX' , (messageSelector asString collect: [:char | char = $: ifTrue: [$X] ifFalse: [char]])]. ^ testSelName! protocolMsgReturnValueRuleSpec "Answer the protocol message return value rule specification class object." ^ SUnitNameResolver classNamed: #'MsgReturnRuleSpec'! undefinedConformsToProtocolNames "Answer the undefined conforms-to protocol names in the system." ^ UndefinedConformsToNames! protocol "Answer the protocol class object." ^ SUnitNameResolver classNamed: #'ProtocolSpec'! protocolMsgReturnValueSpec "Answer the protocol message return value specification class object." ^ SUnitNameResolver classNamed: #'MsgReturnSpec'! xMsgSpecListOfSelector: selector inProtocolNamed: protoName "Answer the list of msg specs for msg with selector, selector, in protocol named, protoName. Example: 1 protocolManager xMsgSpecListOfSelector: #',' inProtocolNamed: #'exceptionSelector' " | msgSpec proto | proto := self protocolManager protocolNamed: protoName. msgSpec := proto messageAtSelector: selector. ^ msgSpec specForEachReturnValueList! fileOutSIFAllProtocolsToFileLocator: pathNameExt "File out all protocol definitions in ANSI SIF to fileLocator, pathNameExt. Note: Protocols are NOT defined in SIF, thus only a reader with macro enhancement will install protocols from the file. All other conforming readers will ignore the contents as comments." | aFileStream programFiler | aFileStream := FileStream write: pathNameExt. [programFiler := self protocolManager newWriterOn: aFileStream. "SIF" self fileOutAllProtocolsSIFFiler: programFiler] ensure: [aFileStream close]! defaultProtocolNameCollection "Private - Answer an , the default protocol name collection." ^ Set new! ! !SelectorANSITest methodsFor: nil! protocol ^#'selector'! canonicalObject ^#isNil! ! !ExceptionClassANSITest methodsFor: nil! testXsignalX " #signal: " #'Exception'. #'todo'."??? I don't know what to test here. [ Exception signal ] on: Exception do: [ :anException | anException signal: ??? ]. self op: [xxx] should: [:r | xxx] conformTo: #'exceptionDescription' selector: #'signal:'. self should: [ [xxx] ensure: [ flag := 1 ] ] raise: Exception. ???"! testXallSubclasses " #allSubclasses " #'Exception'.! testXname " #name " #'Exception'.! testXsuperclass " #superclass " #'Exception'.! protocol ^#'Exception class'! testXconcatenateOp " #, " #'Exception'. #'todo'."??? Fix" self value: [ Exception, Error ] should: [:r | true "(r class = (self protocolTestsMgr classAt: 'exceptionSet'))" and: [(r handles: (Exception new)) & (r handles: (Error new))] ] conformTo: #'exceptionSelector' selector: #','.! testXallSuperclasses " #allSuperclasses " #'Exception'.! testXnew " #new " #'Exception'. self value: [Exception new] should: [:r | true "??? r = Exception signal ???"] conformTo: #'Exception class' selector: #'new'.! testXsignal " #signal " #'Exception'. self value: [ [Exception signal] on: Exception do: [ :except | except return ] ] should: [:r | true "unspecified"] conformTo: #'Exception class' selector: #'signal'.! canonicalObject ^Exception! testXhandlesX " #handles: " #'Exception'. self value: [ [ Exception signal ] on: Exception do: [ :except | except return: (Exception handles: except) ] ] should: [:r | r] conformTo: #'Exception class' selector: #'handles:'. self value: [ [ Exception signal ] on: Exception do: [ :except | except return: (Error handles: except) ] ] shouldnt: [:r | r] conformTo: #'Exception class' selector: #'handles:'.! testXsubclasses " #subclasses " #'Exception'.! ! !IdentityDictionaryANSITest methodsFor: nil! testXasOrderedCollection " #asOrderedCollection " #'Collection'.! testXasByteArray " #asByteArray " #'Collection'.! testXasBag " #asBag " #'Collection'.! testXatX " #at: " #'Collection'.! testXoccurrencesOfX " #occurrencesOf: " #'Collection'.! testXallSatisfyX " #allSatisfy: " #'Collection'.! protocol ^#'IdentityDictionary'! testXnotEmpty " #notEmpty " #'Collection'.! testXasSortedCollectionX " #asSortedCollection: " #'Collection'.! testXrehash " #rehash " #'Collection'.! testXcollectX " #collect: (Return Values: )" #'Collection'.! testXasSortedCollection " #asSortedCollection " #'Collection'.! testXasSet " #asSet " #'Collection'.! emptyCanonicalObject ^IdentityDictionary new! testXisEmpty " #isEmpty " #'Collection'.! testXanySatisfyX " #anySatisfy: " #'Collection'.! testXatXifAbsentPutX " #at:ifAbsentPut: " #'Collection'.! testXdoXseparatedByX " #do:separatedBy: " #'Collection'.! testXinjectXintoX " #inject:into: " #'Collection'.! testXaddAllX " #addAll: " #'Collection'.! testXsize " #size " #'Collection'.! testXdetectXifNoneX " #detect:ifNone: " #'Collection'.! testXdetect " #detect: " #'Collection'.! testXincludesKeyX " #includesKey: " #'Collection'.! testXasArray " #asArray " #'Collection'.! testXatXifAbsentX " #at:ifAbsent: " #'Collection'.! testXdoX " #do: " #'Collection'.! testXatXputX " #at:put: " #'Collection'.! canonicalObject ^IdentityDictionary new at: 1 put: 11; at: 2 put: 22; at:3 put: 33; at:4 put: 44; yourself! testXincludesX " #includes: " #'Collection'.! ! !TestCaseHelper methodsFor: nil! attachTo: mainTestCase testCase := mainTestCase.! printOn: aStream aStream nextPutAll: self class printString; nextPutAll: '>>'! protocol ^testCase protocol! ! !TestCaseHelper class methodsFor: nil! suite ^TestSuite new.! initialize testSelectors := nil! testMethods testSelectors isNil ifTrue: [testSelectors := self selectors select: [:each | 'test*' match: each]]. ^testSelectors! ! !ExceptionSetANSITest methodsFor: nil! testXhandlesX " #handles: " #'Exception'.! testXconcatenateOp " #, " #'Exception'. #'todo'."??? Fix" self value: [ Warning, Error ] should: [:r | "(r class = (self protocolTestsMgr classAt: 'exceptionSet'))" true and: [(r handles: (Warning new)) & (r handles: (Error new))] ] conformTo: #'exceptionSet' selector: #','.! canonicalObject ^ExceptionSet new! protocol ^#'exceptionSet'! ! !WriteStreamHelper methodsFor: nil! protocol ^#'WriteStream'! canonicalObject ^testCase canonicalObject! object: anObject! ! !WriteStreamHelper class methodsFor: nil! initialize "WriteStreamHelper initialize" super initialize! ! !IntervalANSITest methodsFor: nil! testXkeysAndValuesDoX " #keysAndValuesDo: " #'Collection'.! canonicalElement ^2! emptyCollection ^1 to: 0! protocol ^#Interval! testXlast " #last " #'Collection'.! canonicalObject ^1 to: 4! canonicalObject ^1 to: 4! ! !IntervalANSITest class methodsFor: nil! helperClassesDo: aBlock super helperClassesDo: aBlock. aBlock value: SequencedReadableCollectionHelper! ! !GettableStreamHelper methodsFor: nil! testXnextLine self canonicalObject reset. self value: [self canonicalObject nextLine] should: [:r | true "The result is undefined if there are no future sequence values in the receiver or if the future-sequence values do not include the end-of-line sequence."] conformTo: self protocol selector: #'nextLine'.! testXupToX self canonicalObject reset. self value: [self canonicalObject upTo: $ ] should: [:r | r = 'this' & self canonicalObject next = $i] conformTo: self protocol selector: #'upTo:'. self value: [self canonicalObject upTo: $X] should: [:r | r = 's a string' & self canonicalObject atEnd] conformTo: self protocol selector: #'upTo:'. self value: [self canonicalObject upTo: $a] should: [:r | r isEmpty] conformTo: self protocol selector: #'upTo:'.! testXnext self canonicalObject reset. self value: [self canonicalObject next] should: [:r | r = $t] conformTo: self protocol selector: #'next'.! testXskipToX self canonicalObject reset. self value: [self canonicalObject skipTo: $a] should: [:r | r & self canonicalObject position = 9] conformTo: self protocol selector: #'skipTo:'. self value: [self canonicalObject skipTo: $X] should: [:r | r = false & self canonicalObject atEnd] conformTo: self protocol selector: #'skipTo:'.! protocol ^#'gettableStream'! canonicalObject ^testCase canonicalObject! testXdoX | list list2 | self canonicalObject reset. list := OrderedCollection new. self value: [self canonicalObject do: [ :elem | list add: elem]] should: [:r | list asArray = 'this is a string' asArray] conformTo: self protocol selector: #'do:'. self canonicalObject setToEnd. list2 := OrderedCollection new. self value: [self canonicalObject do: [ :elem | list2 add: elem]] should: [:r | "r UNSPECIFIED" list2 isEmpty] conformTo: self protocol selector: #'do:'.! testXpeekForX self canonicalObject reset. self value: [self canonicalObject peekFor: $t] should: [:r | r] conformTo: self protocol selector: #'peekFor:'. self value: [self canonicalObject peekFor: $X] shouldnt: [:r | r] conformTo: self protocol selector: #'peekFor:'.! testXatEnd self canonicalObject reset. self value: [self canonicalObject atEnd] shouldnt: [:r | r] conformTo: self protocol selector: #'atEnd'. self canonicalObject setToEnd. self value: [self canonicalObject atEnd] should: [:r | r] conformTo: self protocol selector: #'atEnd'.! testXpeek self canonicalObject reset. self value: [self canonicalObject peek] should: [:r | r = $t] conformTo: self protocol selector: #'peek'. self canonicalObject setToEnd. self value: [self canonicalObject peek] should: [:r | r = nil] conformTo: self protocol selector: #'peek'.! testXnextX self canonicalObject reset. self value: [self canonicalObject next: 3] should: [:r | r asArray = 'thi' asArray] conformTo: self protocol selector: #'next:'.! object: anObject! testXnextMatchForX self canonicalObject reset. self value: [self canonicalObject nextMatchFor: $t] should: [:r | r] conformTo: self protocol selector: #'nextMatchFor:'. self value: [self canonicalObject nextMatchFor: $t] shouldnt: [:r | r] conformTo: self protocol selector: #'nextMatchFor:'.! testXskipX self canonicalObject reset. self value: [self canonicalObject skip: 3] should: [:r | "r UNSPECIFIED" self canonicalObject next = $s] conformTo: self protocol selector: #'skip:'. self canonicalObject position: (self canonicalObject contents size - 1). self value: [self canonicalObject skip: 3] should: [:r | "r UNSPECIFIED" self canonicalObject next = nil] conformTo: self protocol selector: #'skip:'.! ! !GettableStreamHelper class methodsFor: nil! initialize "GettableStreamHelper initialize" super initialize! ! !CollectionStreamHelper methodsFor: nil! canonicalObject ^testCase canonicalObject! testXcontents self value: [self canonicalObject contents] should: [:r | r = 'this is a string' & r size = self canonicalObject size] conformTo: self protocol selector: #'contents'.! object: anObject! ! !CollectionStreamHelper class methodsFor: nil! initialize "CollectionStreamHelper initialize" super initialize! ! !SequenceableCollection methodsFor: nil! asANSITestArray "2000/06/23 Harmon, R. Added to RJs release from SSs stuff." ^self collect: [:each | each collect: [:each1 | each1 = #true ifTrue: [true] ifFalse: [each1 = #false ifTrue: [false] ifFalse: [each1]]]]! ! !ClassDescription methodsFor: nil! protocolNames "Answer the names of protocols to which the receiver's instances directly conform. Note: This excludes inherited protocols." | tmpList | #'ACSProS'. tmpList := self protocolManager classProtocols at: self ifAbsent: [nil]. tmpList isNil ifTrue: [^ self protocolManager defaultProtocolNameCollection]. ^ tmpList! removeProtocolNamed: protocolName "Remove the protocol named, protocolName, from the list of protocols to which the receiver conforms." #'ACSProS'. self removeProtocolNamed: protocolName ifAbsent: [self protocolManager errorProtocolNotFound: protocolName]! definedAsProtocolNames "Answer the names of protocols to which the receiver's instances directly conform. If it has no protocols, check super classes until protocols are found Note: This excludes inherited protocols. 200/03/04 Harmon, R. Added." | tmpList | #'ACSProS'. tmpList := self protocolManager classProtocols at: self ifAbsent: [nil]. tmpList isNil ifTrue: [^ self superclass definedAsProtocolNames]. ^ tmpList! protocols "Answer the protocols to which the receiver's instances directly conform. Note: This excludes inherited protocols." #'ACSProS'. ^ self protocolManager protocolsInNameList: self protocolNames! addProtocolNamed: protocolName "Add the protocol named, protocolName, to the list of protocols to which the receiver conforms." | tmpProtocolNames | #'ACSProS'. tmpProtocolNames := self protocolNames. tmpProtocolNames add: protocolName. self protocolNames: tmpProtocolNames! conformsToProtocolNamed: protocolName "Answer whether the receiver conforms to the protocol named protocolName. Note: This includes inherited protocols." #'ACSProS'. ^ (self protocolNames includes: protocolName) or: [self superclass notNil and: [self superclass conformsToProtocolNamed: protocolName]]! removeProtocolNamed: protocolName ifAbsent: notFoundBlock "Remove the protocol named, protocolName, from the list of protocols to which the receiver conforms. Evaluate notFoundBlock if not found." | tmpProtocolNames | #'ACSProS'. tmpProtocolNames := self protocolNames. tmpProtocolNames isEmpty ifTrue: [^ notFoundBlock value]. tmpProtocolNames remove: protocolName ifAbsent: [^ notFoundBlock value]. self protocolNames: tmpProtocolNames! protocolNames: protocolNameList "Private - Set the names of protocols to which the receiver's instances directly conform to protocolNameList. Note: This excludes inherited protocols. protocolNameList must be a of s." #'ACSProS'. (protocolNameList isKindOf: Set) ifFalse: [self error: 'Protocol name list not a Set.']. protocolNameList isEmpty ifTrue: [self protocolManager classProtocols removeKey: self ifAbsent: [] ] ifFalse: [self protocolManager classProtocols at: self put: protocolNameList]! ! !TestCase methodsFor: nil! value: aBlockContext shouldRaise: anException | ok | #'ACSUEnh'. ok := [ aBlockContext value. false ] on: anException do: [:ex | ex return: true ]. self assert: ok! value: aBlockContext shouldntRaise: anException | ok | #'ACSUEnh'. ok := [ aBlockContext value. true ] on: anException do: [:ex | ex return: false ]. self assert: ok! ! !String methodsFor: nil! trimBlanks "Answer a , a copy of the receiver from which leading and trailing separators have been trimmed." #'ACSProS'. ^ self trimSeparators! ! !PositionableStream methodsFor: nil! nextToken "Answer a , the next token in the receiver's element stream, delimited by elements which answer true to #isSeparator. Answer a nil if there are no more token in the receiver." "99/12/02 Harmon, R. A. Fixed error & changed to return nil if no more tokens to conform to other impls." | startPos len | #'ACSProS'. self skipSeparators. self atEnd ifTrue: [^ nil]. startPos := self position. len := 0. [self atEnd] whileFalse: [self next isSeparator ifTrue: [self position: startPos. ^ self next: len]. len := len + 1]. self position: startPos. ^ self next: len! ! !Object methodsFor: nil! protocolManager "Answer the singleton instance of the protocol manager." #'ACSProS'. ^ProtocolSpec! ! !Set methodsFor: nil! any "Return a random element. Much better than 'asArray first' " self do: [:each | ^each]. self error: 'set is empty'! ! !String class methodsFor: nil! methodSelector: methodDefinitionString "Private - Answer a , the method selector extracted from the instance or class method definition methodDefinitionString if found, or if not found. Note: This is not bullet proof. 99/12/02 Harmon, R. A. Fixed error. 99/12/03 Harmon, R. A. Fixed %Definition:% accepted as keyword error." | sourceStream selectorStream token | #'ACSProS'. sourceStream := ReadStream on: methodDefinitionString trimBlanks. sourceStream contents isEmpty ifTrue: [^ nil]. token := sourceStream nextToken. token isNil ifTrue: [^ nil]. token last = $: ifFalse: ["Binary or unary selector." ^ token]. selectorStream := WriteStream on: (String new: 20). [(token isNil or: [token isEmpty]) not and: [token last = $: & ((token includes: $") not & (token includes: $') not & (token includes: $|) not)]] whileTrue: [selectorStream nextPutAll: token. sourceStream nextToken. "Get keyword." token := sourceStream nextToken]. ^ selectorStream contents! ! PuttableStreamHelper initialize. ObjectHelper initialize. CollectionStreamHelper initialize. SequencedStreamHelper initialize. GettableStreamHelper initialize. CollectionHelper initialize. TestCaseHelper initialize. WriteStreamHelper initialize. ReadStreamHelper initialize. ProtocolSpec initialize. ! smalltalk-3.2.5/tests/fibo.st0000644000175000017500000000263112123404352013055 00000000000000"====================================================================== | | Benchmark for message sending | | ======================================================================" "====================================================================== | | Copyright (C) 2003, 2007, 2008 Free Software Foundation. | Written by Paolo Bonzini | | This file is part of GNU Smalltalk. | | GNU Smalltalk is free software; you can redistribute it and/or modify it | under the terms of the GNU General Public License as published by the Free | Software Foundation; either version 2, or (at your option) any later version. | | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS | FOR A PARTICULAR PURPOSE. See the GNU General Public License for more | details. | | You should have received a copy of the GNU General Public License along with | GNU Smalltalk; see the file COPYING. If not, write to the Free Software | Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. | ======================================================================" SmallInteger extend [ fib [ ^self < 2 ifTrue: [ 1 ] ifFalse: [ (self - 2) fib + (self - 1) fib ] ] ] Eval [ | n | n := Smalltalk arguments isEmpty ifTrue: [ 8 ] ifFalse: [ 1 max: Smalltalk arguments first asInteger ]. n fib printNl ] smalltalk-3.2.5/tests/objects.st0000644000175000017500000000726712123404352013601 00000000000000"====================================================================== | | Test special objects | | ======================================================================" "====================================================================== | | Copyright (C) 1999, 2000, 2001, 2002, 2007, 2008, 2009 Free Software Foundation. | Written by Paolo Bonzini | | This file is part of GNU Smalltalk. | | GNU Smalltalk is free software; you can redistribute it and/or modify it | under the terms of the GNU General Public License as published by the Free | Software Foundation; either version 2, or (at your option) any later version. | | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS | FOR A PARTICULAR PURPOSE. See the GNU General Public License for more | details. | | You should have received a copy of the GNU General Public License along with | GNU Smalltalk; see the file COPYING. If not, write to the Free Software | Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. | ======================================================================" Object subclass: ObjectsTest [ | name survive | Messages := nil. ObjectsTest class [ testCompaction [ Messages := SortedCollection new. ObjectMemory compact. Messages do: [ :each | each displayNl ] ] testFinalize [ | test | self new name: 'a' survive: false. self new name: 'b' survive: true. self new name: 'c' survive: false. self testCompaction. self testCompaction. self testCompaction. ] testWeak [ | a | a := Array new: 1. a makeWeak. a at: 1 put: Object new. ObjectMemory compact. ^(a at: 1) isNil ] ] name: aString survive: aBoolean [ name := aString. survive := aBoolean. self addToBeFinalized ] finalize [ survive ifTrue: [ Messages add: name, ' finalized, surviving'. survive := false. self addToBeFinalized. ^self ]. Messages add: name, ' finalized' ] ] Eval [ ObjectsTest testFinalize ] Eval [ ObjectsTest testWeak ] Eval [ | a b | a := WeakArray new: 5. a at: 1 put: 'abc'. a at: 2 put: Object new. a at: 4 put: nil. a at: 5 put: 1. b := a copy. a printNl. b printNl. ObjectMemory compact. a printNl. b printNl. ((1 to: 5) collect: [ :each | a isAlive: each ]) printNl. 1 to: 5 do: [ :index | a clearGCFlag: index ]. ((1 to: 5) collect: [ :each | a isAlive: each ]) printNl. ((1 to: 5) collect: [ :each | b isAlive: each ]) printNl ] "Test lightweight class" Eval [ Test := Behavior new. Transcript nextPutAll: 'New instance of Behavior created'; nl. Test superclass: Object. Transcript nextPutAll: 'Superclass assigned'; nl. Test compile: 'new [ ^super new ]'. Transcript nextPutAll: 'First method compiled'; nl. Test compile: 'printTestMessage [ ''test message'' printNl ]'. Transcript nextPutAll: 'Second method compiled'; nl. t := Test new. Transcript nextPutAll: 'Instance created'; nl. t printTestMessage. t printNl. Transcript nextPutAll: 'Well it seems to work fine'; nl ] "Test becomeForward" Eval [ a := Behavior new superclass: Object. a compile: 'foo [ ^1 ]'. b := Behavior new superclass: Object. b compile: 'foo [ ^2 ]'. o := a new. a become: b. o foo ] Eval [ "This uses global (Association) variables." a := 'a' copy. (a becomeForward: 'b') printNl. a ] Eval [ "This uses local (stack) variables." | a b | a := Object new. b := 5. a becomeForward: b. a printNl ] smalltalk-3.2.5/tests/random-bench.st0000644000175000017500000000300012123404352014462 00000000000000"====================================================================== | | Benchmark for floats | | ======================================================================" "====================================================================== | | Copyright (C) 2003, 2007, 2008 Free Software Foundation. | Written by Paolo Bonzini | | This file is part of GNU Smalltalk. | | GNU Smalltalk is free software; you can redistribute it and/or modify it | under the terms of the GNU General Public License as published by the Free | Software Foundation; either version 2, or (at your option) any later version. | | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS | FOR A PARTICULAR PURPOSE. See the GNU General Public License for more | details. | | You should have received a copy of the GNU General Public License along with | GNU Smalltalk; see the file COPYING. If not, write to the Free Software | Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. | ======================================================================" Number extend [ Last := 42. nextRandom [ Last := Last * 3877 + 29573 rem: 139968. ^self * Last asFloatD / 139968d ] ] Eval [ n := Smalltalk arguments isEmpty ifTrue: [ 1000 ] ifFalse: [ 1 max: Smalltalk arguments first asInteger ]. n timesRepeat: [ 100d nextRandom ]. ((100d nextRandom + 0.5d-9) printString copyFrom: 1 to: 11) displayNl ] smalltalk-3.2.5/tests/lists2.ok0000644000175000017500000000020712123404352013336 00000000000000 Execution begins... 200000 150001 50001 50000 150000 150002 50002 49999 149999 150003 50003 returned value is TextCollector new "<0>" smalltalk-3.2.5/tests/processes.st0000644000175000017500000002457012123404352014152 00000000000000"====================================================================== | | Test process operations | | ======================================================================" "====================================================================== | | Copyright (C) 1999, 2002, 2003, 2007, 2008 Free Software Foundation. | Written by Paolo Bonzini | | This file is part of GNU Smalltalk. | | GNU Smalltalk is free software; you can redistribute it and/or modify it | under the terms of the GNU General Public License as published by the Free | Software Foundation; either version 2, or (at your option) any later version. | | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS | FOR A PARTICULAR PURPOSE. See the GNU General Public License for more | details. | | You should have received a copy of the GNU General Public License along with | GNU Smalltalk; see the file COPYING. If not, write to the Free Software | Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. | ======================================================================" Process extend [ executeUntilTermination [ self isTerminated ifTrue: [ ^self ]. self isActive ifFalse: [ self resume ]. [ self isTerminated ] whileFalse: [ Processor yield ] ] ensureTermination [ self terminate; executeUntilTermination ] ] "Test resuming/terminating a process" Eval [ p := [ 'inside p' printNl ] newProcess name: 'test 1'; yourself. p printNl. p executeUntilTermination. p printNl ] "Test Process suspend/resume" Eval [ goOn := false. p := [ 'inside p' printNl. goOn := true. p suspend. 'suspension finished' printNl ] newProcess name: 'test 2'; yourself. p printNl. p resume. [ goOn ] whileFalse: [ Processor yield ]. p printNl. p executeUntilTermination. p printNl ] "Test processes yielding control to each other without suspending themselves" Eval [ goOn := false. p := [ 'inside p' printNl. goOn := true. Processor yield. 'yielded back to p' printNl ] newProcess name: 'test 3'; yourself. p printNl. p resume. [ goOn ] whileFalse: [ Processor yield ]. p printNl. p executeUntilTermination. p printNl ] "Test simple wait on a semaphore" Eval [ s := Semaphore new. p := [ 'inside p' printNl. s wait. 'wait finished' printNl ] newProcess name: 'test 4'; yourself. p printNl. p resume. [ s size = 0 ] whileTrue: [ Processor yield ]. p printNl. s signal. p printNl ] "Now test process interrupts" Eval [ s := Semaphore new. ([ [ false ] whileFalse: [ Processor yield ] ] forkAt: Processor userBackgroundPriority) name: 'background'; queueInterrupt: [ (p := Processor activeProcess) printNl. s signal ]. s wait. p printNl. p ensureTermination. p printNl ] "Now interrupt a sleeping process" Eval [ s := Semaphore new. ([ 'should go back to sleep' printNl ] newProcess) priority: Processor userInterruptPriority; name: 'interrupted'; queueInterrupt: [ (p := Processor activeProcess) printNl. s signal ]. s wait. p printNl. p ensureTermination. p printNl ] "Resume a process and check that it is removed from the semaphore" Eval [ | p1 p2 s p1ok p2ok | s := Semaphore new. p1 := [ [ s wait ] ensure: [ p1ok := true ] ] fork. p2 := [ [ s wait ] ensure: [ p2ok := true ] ] fork. [ s size = 2 ] whileFalse: [ Processor yield ]. p2 resume. s signal. p1 ensureTermination. ^p1ok & p2ok & s size = 0 ] Eval [ | p1 p2 s p1ok p2ok | s := Semaphore new. p1 := [ [ s wait ] ensure: [ p1ok := true ] ] fork. p2 := [ [ s wait ] ensure: [ p2ok := true ] ] fork. [ s size = 2 ] whileFalse: [ Processor yield ]. p1 resume. s signal. p2 ensureTermination. ^p1ok & p2ok & s size = 0 ] "Terminate a process and check that #ensure: blocks are evaluated" Eval [ dummy := Semaphore new. s := Semaphore new. p1 := [ [ dummy wait ] ensure: [ s signal ] ] fork. p2 := [ [ dummy wait ] ensure: [ s signal ] ] fork. p1 ensureTermination. p2 ensureTermination. s wait. s wait. ^s size = 0 ] Eval [ dummy := Semaphore new. s := Semaphore new. p1 := [ [ Processor activeProcess priority: Processor userBackgroundPriority. dummy wait ] ensure: [ s signal ] ] fork. p2 := [ [ Processor activeProcess priority: Processor userBackgroundPriority. dummy wait ] ensure: [ s signal ] ] fork. p1 ensureTermination. p2 ensureTermination. s wait. s wait. ^s size = 0 ] Eval [ "A semaphore that has just left the wait in Semaphore>>critical: should signal the associated semaphore before leaving." | s p | s := Semaphore new. p := [s critical:[]] forkAt: Processor activePriority - 1. "Wait until p entered the critical section" [p isWaiting] whileFalse: [Processor yield]. "Now that p entered it, signal the semaphore. p now 'owns' the semaphore but since we are running at higher priority than p it will not get to do anything." s signal. p ensureTermination. ^s signals = 1 ] Eval [ "A process that has entered the wait in Semaphore>>critical:, but never obtains the semaphore, should leave it without signaling the semaphore." | s p | s := Semaphore new. p := [s critical:[]. 'a' printNl] fork. [p isWaiting] whileFalse: [Processor yield]. p ensureTermination. ^s signals = 0 ] "Test that processes with the same priority are executed fairly. See http://permalink.gmane.org/gmane.comp.lang.smalltalk.squeak.general/122772 for a proposed patch to Squeak that would break this testcase. The two producer processes would ping-pong control to each other, and the delay won't even be started." Eval [ | queue stop s | queue := SharedQueue new. stop := false. s := Semaphore new. [ s signal. [ stop ] whileFalse: [ queue nextPut: true. Processor yield ] ] fork. s wait. [ (Delay forMilliseconds: 500) wait. stop := true ] fork. [ stop ] whileFalse: [ queue nextPut: false. Processor yield ]. ] "Test ProcessEnvironment and ProcessVariable" Eval [ "Value defaults to nil" b := Processor processEnvironment associationAt: #a. b value printNl. "#at:put: affects #value" Processor processEnvironment at: #a put: 1. b value printNl. "and #value: affects #at:" b value: 2. (Processor processEnvironment at: #a) printNl. s := Semaphore new. [ "Value defaults to nil here too." b value printNl. "Requesting value has not created the variable." Processor processEnvironment at: #a ifAbsentPut: [3]. b value printNl. s signal ] fork. s wait. "The variable exists here..." Processor processEnvironment at: #a ifAbsentPut: [4]. "... and its value is still 2." (Processor processEnvironment at: #a) printNl. b value printNl ] "Test that CallinProcesses can be terminated softly" Eval [ [ [ Processor activeProcess terminate ] ensure: [ '... ' display ] ] on: SystemExceptions.ProcessBeingTerminated do: [ :sig | 'nothing should follow' display. sig pass ]. 'failed' displayNl ] "The exception should not be resumable to avoid that execution is continued without the process actually having gotten a signal on the semaphore." Notification subclass: ProcessInterrupt [ isResumable [ ^false ] defaultAction [ Processor activeProcess terminate ] ] "Signal a process from itself." Eval [ | p1 | p1 := [ Processor activeProcess signalInterrupt: ProcessInterrupt new ] fork. p1 executeUntilTermination ] "Signal a process from the outside." Eval [ | p1 p2 | p1 := [ [ Processor activeProcess yield ] repeat ] fork. p2 := [ (Delay forMilliseconds: 500) wait. p1 signalInterrupt: (ProcessInterrupt new) ] fork. p1 executeUntilTermination. p2 executeUntilTermination ] "Signal a process from the outside, and catch the exception." Eval [ | p1 p2 sem | sem := Semaphore new. p1 := [ [ [ Processor activeProcess yield ] repeat ] on: ProcessInterrupt do: [ :ex | ex return ]. sem signal ] fork. p2 := [ (Delay forMilliseconds: 500) wait. p1 signalInterrupt: (ProcessInterrupt new) ] fork. sem wait. p1 executeUntilTermination. p2 executeUntilTermination ] "Signal a process from the outside, and pass the exception." Eval [ | p1 p2 sem | sem := Semaphore new. p1 := [ [ [ Processor activeProcess yield ] repeat ] on: ProcessInterrupt do: [ :ex | sem signal. ex pass ] ] fork. p2 := [ (Delay forMilliseconds: 500) wait. p1 signalInterrupt: (ProcessInterrupt new) ] fork. sem wait. p1 executeUntilTermination. p2 executeUntilTermination ] "Signal a sleeping process from the outside." Eval [ | p1 p2 sem | p1 := [ (Delay forSeconds: 100000) wait ] fork. [ p1 isActive ] whileTrue: [ Processor activeProcess yield ]. p2 := [ (Delay forMilliseconds: 500) wait. p1 signalInterrupt: (ProcessInterrupt new) ] fork. p1 executeUntilTermination. p2 executeUntilTermination ] "Signal a sleeping process from the outside, and pass the exception." Eval [ | p1 p2 sem | sem := Semaphore new. p1 := [ [ (Delay forSeconds: 100000) wait ] on: ProcessInterrupt do: [ :ex | ex return ]. sem signal ] fork. [ p1 isActive ] whileTrue: [ Processor activeProcess yield ]. p2 := [ (Delay forMilliseconds: 500) wait. p1 signalInterrupt: (ProcessInterrupt new) ] fork. sem wait. p1 executeUntilTermination. p2 executeUntilTermination ] "Signal a sleeping process from the outside, and pass the exception." Eval [ | p1 p2 sem | sem := Semaphore new. p1 := [ [ (Delay forSeconds: 100000) wait ] on: ProcessInterrupt do: [ :ex | sem signal. ex pass ] ] fork. [ p1 isActive ] whileTrue: [ Processor activeProcess yield ]. p2 := [ (Delay forMilliseconds: 500) wait. p1 signalInterrupt: (ProcessInterrupt new) ] fork. sem wait. p1 executeUntilTermination. p2 executeUntilTermination ] smalltalk-3.2.5/tests/lists2.st0000644000175000017500000000324512123404352013360 00000000000000"====================================================================== | | Benchmark for big OrderedCollections | | ======================================================================" "====================================================================== | | Copyright (C) 2003, 2007, 2008 Free Software Foundation. | Written by Paolo Bonzini | | This file is part of GNU Smalltalk. | | GNU Smalltalk is free software; you can redistribute it and/or modify it | under the terms of the GNU General Public License as published by the Free | Software Foundation; either version 2, or (at your option) any later version. | | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS | FOR A PARTICULAR PURPOSE. See the GNU General Public License for more | details. | | You should have received a copy of the GNU General Public License along with | GNU Smalltalk; see the file COPYING. If not, write to the Free Software | Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. | ======================================================================" Eval [ n := Smalltalk arguments isEmpty ifTrue: [ 200000 ] ifFalse: [ 1 max: Smalltalk arguments first asInteger ]. a := (1 to: n) asOrderedCollection. b := OrderedCollection new: n. [a isEmpty] whileFalse: [ b addLast: a removeFirst; addLast: a removeLast ]. [b isEmpty] whileFalse: [ a addFirst: b removeLast; addFirst: b removeFirst ]. a size printNl. (a copyFrom: 1 to: (10 min: a size)) do: [ :each | each print ] separatedBy: [ Transcript space ]. Transcript nl ] smalltalk-3.2.5/tests/quit.ok0000644000175000017500000000002512123404352013076 00000000000000 Execution begins... smalltalk-3.2.5/tests/objinst.st0000644000175000017500000000400212123404352013600 00000000000000"====================================================================== | | Benchmark for object instantiation | | ======================================================================" "====================================================================== | | Copyright (C) 2003, 2007, 2008 Free Software Foundation. | Written by Paolo Bonzini | | This file is part of GNU Smalltalk. | | GNU Smalltalk is free software; you can redistribute it and/or modify it | under the terms of the GNU General Public License as published by the Free | Software Foundation; either version 2, or (at your option) any later version. | | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS | FOR A PARTICULAR PURPOSE. See the GNU General Public License for more | details. | | You should have received a copy of the GNU General Public License along with | GNU Smalltalk; see the file COPYING. If not, write to the Free Software | Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. | ======================================================================" ValueHolder subclass: NthValueHolder [ | counter maxCounter | ValueHolder >> activate [ self value: self value not ] maxCounter: anInteger [ maxCounter := anInteger ] value: anObject [ super value: anObject. counter := 0 ] activate [ (counter := counter + 1) >= maxCounter ifTrue: [ super activate ] ] ] Eval [ n := Smalltalk arguments isEmpty ifTrue: [ 1 ] ifFalse: [ 1 max: Smalltalk arguments first asInteger ]. val := true. toggle := ValueHolder with: val. 5 timesRepeat: [ toggle activate value printNl ]. n timesRepeat: [ toggle := ValueHolder with: true ]. Transcript nl. val := true. ntoggle := NthValueHolder with: val. ntoggle maxCounter: 3. 8 timesRepeat: [ ntoggle activate value printNl ]. n timesRepeat: [ (ntoggle := NthValueHolder with: true) maxCounter: 3 ] ] smalltalk-3.2.5/tests/getopt.ok0000644000175000017500000000437112123404352013426 00000000000000 Execution begins... SortedCollection () $B->#noArg returned value is Getopt new "<0>" Execution begins... SortedCollection ('l' 'lo' 'lon' 'long' ) 'long'->#noArg returned value is Getopt new "<0>" Execution begins... SortedCollection ('longe' 'longer' 'longi' 'longis' 'longish' ) 'longer'->#noArg 'longish'->#noArg returned value is Getopt new "<0>" Execution begins... SortedCollection ('long' 'longe' 'longer' ) 'long'->#noArg 'longer'->#noArg returned value is Getopt new "<0>" Execution begins... SortedCollection () $B->#mandatoryArg returned value is Getopt new "<0>" Execution begins... SortedCollection () $B->#optionalArg returned value is Getopt new "<0>" Execution begins... SortedCollection () $a->$b $b->#noArg returned value is Getopt new "<0>" Execution begins... SortedCollection ('l' 'lo' 'lon' 'long' ) $a->'long' 'long'->#noArg returned value is Getopt new "<0>" Execution begins... SortedCollection ('l' 'lo' 'lon' 'long' 'v' 've' 'ver' 'very' 'very-' 'very-l' 'very-lo' 'very-lon' 'very-long' ) $a->'long' 'long'->#noArg 'very-long'->'long' returned value is Getopt new "<0>" Execution begins... $a->nil $b->nil $a->nil $b->nil $a->nil $b->nil returned value is Getopt Execution begins... '-a'->'error' $b->nil $a->'b' $a->'-b' returned value is Getopt Execution begins... $a->nil $b->nil $a->'b' $a->nil $b->nil returned value is Getopt Execution begins... 'longish'->nil 'longer'->nil 'longish'->nil 'longer'->nil '--lo'->'error' '-longer'->'error' returned value is Getopt Execution begins... '--lo'->'error' 'long'->nil 'longer'->nil 'longer'->nil returned value is Getopt Execution begins... 'noarg'->nil '--mandatory'->'error' 'mandatory'->'foo' 'mandatory'->'' 'mandatory'->'foo' 'optional'->nil 'optional'->nil nil->'foo' returned value is Getopt Execution begins... $b->nil $b->nil returned value is Getopt Execution begins... 'long'->nil 'long'->nil returned value is Getopt Execution begins... 'long'->'x' 'long'->'x' returned value is Getopt Execution begins... 'long'->nil 'long'->nil 'long'->nil returned value is Getopt Execution begins... 'long'->'x' 'long'->'x' 'long'->'x' returned value is Getopt Execution begins... $b->nil nil->'-b' nil->'-b' nil->'-b' nil->'-b' returned value is Getopt smalltalk-3.2.5/tests/delays.ok0000644000175000017500000000074112123404352013402 00000000000000 Execution begins... 4 3 2 returned value is nil Execution begins... returned value is true Execution begins... returned value is true Execution begins... 'ensure' 'timeout' returned value is 'timeout' Execution begins... 'ifCurtailed' 'timeout' returned value is 'timeout' Execution begins... 'ensure-in' 'ensure-mid' 'timeout' 'ensure-out' returned value is 'timeout' Execution begins... returned value is true Execution begins... value:onTimeoutDo: returned value is nil smalltalk-3.2.5/tests/sieve.ok0000644000175000017500000000010112123404352013222 00000000000000 Execution begins... Count: 1028 returned value is 'Count: 1028' smalltalk-3.2.5/tests/mutate.ok0000644000175000017500000000372712123404352013427 00000000000000 Execution begins... A(var1:1 ) B(var1:0 var2:2 ) 2 B(var1:0 var2:nil var2:2 ) 2 B(var1:0 var2:2 ) nil B(var1:0 var2:nil ) returned value is B new "<0>" Execution begins... returned value is C Execution begins... returned value is true Execution begins... (#key #value )->Set () returned value is Association new "<0>" Execution begins... returned value is C Execution begins... returned value is true Execution begins... (#a )->Set (#SystemExceptions ) returned value is Association new "<0>" Execution begins... returned value is C Execution begins... returned value is true Execution begins... (#a )->Set (#SystemExceptions ) returned value is Association new "<0>" Execution begins... returned value is C Execution begins... returned value is true Execution begins... (#key #value #a )->Set (#SystemExceptions ) returned value is Association new "<0>" Execution begins... returned value is C Execution begins... returned value is true Execution begins... (#Foo )->()->Set (#SystemExceptions ) returned value is Association new "<0>" Execution begins... returned value is C Execution begins... (#Foo )->(#key #value )->Set (#SystemExceptions ) returned value is Association new "<0>" Execution begins... returned value is C Execution begins... returned value is true Execution begins... #pointer->(#Foo )->()->Set (#SystemExceptions ) returned value is Association new "<0>" Execution begins... returned value is C Execution begins... #pointer->(#Foo )->(#key #value )->Set (#SystemExceptions ) returned value is Association new "<0>" Execution begins... returned value is CompiledMethod new: 4 "<0>" Execution begins... returned value is true Execution begins... Smalltalk returned value is SystemDictionary new: 512 "<0>" Execution begins... (#a #b #c ) returned value is Array new: 3 "<0>" Execution begins... (#a #d #b #c ) returned value is Array new: 4 "<0>" Execution begins... (#a #d ) returned value is Array new: 2 "<0>" Execution begins... returned value is 'abc' smalltalk-3.2.5/tests/pools.st0000644000175000017500000001331112130343734013273 00000000000000"====================================================================== | | Tests for the TwistedPools (3.1+) pool resolution strategy | | ======================================================================" "====================================================================== | | Copyright (C) 2008 Free Software Foundation, Inc. | Written by Stephen Compall. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" Smalltalk addSubspace: #MyLibrary; addSubspace: #MyProject; addSubspace: #MyImports. MyProject addSubspace: #MyLibWrapper. "actually for later, to demonstrate the need for the `direct superclass only' namespace-walk-stop rule" MyLibrary at: #PkgVersion put: 'MyLibrary 1.0'. MyProject at: #PkgVersion put: 'MyProject 0.3141'. Namespace current: MyLibrary [ MyLibrary at: #StandardOverrides put: (Dictionary from: {#Scape -> 42}); at: #ValueAdaptor put: 9994; yourself. Object subclass: Foo [ Exception := 42. Scape := 21. exception [^Exception] scape [^Scape] ] Foo subclass: Bar [ scape [^Scape] valueAdaptor [^ValueAdaptor] ] Bar subclass: Blah [ scape [^Scape] ] ] "end namespace MyLibrary" Namespace current: MyProject.MyLibWrapper [ Namespace current import: (Dictionary from: {#Blah -> 6667. #Scoobs -> 785}). "note this changes my superspace" MyProject at: #Exception put: #Exception. MyLibrary.Foo subclass: Baz [ scape [^Scape] exception [^Exception] valueAdaptor [^ValueAdaptor] blah [^Blah] ] ] "end namespace MyProject.MyLibWrapper" Namespace current: MyLibrary [ "you ask, Who would do this? to which I say..." MyProject.MyLibWrapper.Baz subclass: BackForMore [ pkgVersion [^PkgVersion] blah [^Blah] scoobs [^Scoobs] ] ] "end namespace MyLibrary" Namespace current: MyImports [ Object subclass: MITest [ test [^Foo] ] MITest extend [ test2 [^Baz] ] ] "here start the tests..." "prefer class pool to namespace" MyLibrary.Foo class extend [ test [ ^Exception ] ] Eval [ MyLibrary.Foo test ] "42" "prefer shared pool to super-class pool" MyLibrary.Bar class extend [ test [ ^Scape ] ] Eval [ MyLibrary.Bar test ] "42" "test inherited pools: super-shared pool" MyLibrary.Blah class extend [ test [ ^Scape ] ] Eval [ MyLibrary.Blah test ] "42" "test inherited pools: super-class pool" MyProject.MyLibWrapper.Baz class extend [ test [ ^Scape ] ] Eval [ MyProject.MyLibWrapper.Baz test ] "21" "test namespace walk" MyProject.MyLibWrapper.Baz class extend [ test [ ^Exception ] ] Eval [ MyProject.MyLibWrapper.Baz test ] "#Exception" MyProject.MyLibWrapper.Baz class extend [ test [ ^ValueAdaptor ] ] Eval [ MyProject.MyLibWrapper.Baz test ] "9994" MyLibrary.BackForMore class extend [ test [ ^PkgVersion ] ] Eval [ MyLibrary.BackForMore test ] "'MyLibrary 1.0'" "These do not work yet: ""Test resolution within class variables"" MyLibrary.Foo class extend [ TryThis := Exception printNl ] MyLibrary.Bar class extend [ TryThis := Scape printNl ] MyLibrary.Blah class extend [ TryThis := Scape printNl ] MyProject.MyLibWrapper.Baz class extend [ TryThis := Scape printNl ] MyProject.MyLibWrapper.Baz class extend [ TryThis := Exception printNl ] MyProject.MyLibWrapper.Baz class extend [ TryThis := ValueAdaptor printNl ] MyLibrary.BackForMore class extend [ TryThis := PkgVersion printNl ] ""Test resolution within compile-time constants"" MyLibrary.Foo class extend [ test [ ^##(Exception printNl) ] ] MyLibrary.Bar class extend [ test [ ^##(Scape printNl) ] ] MyLibrary.Blah class extend [ test [ ^##(Scape printNl) ] ] MyProject.MyLibWrapper.Baz class extend [ test [ ^##(Scape printNl) ] ] MyProject.MyLibWrapper.Baz class extend [ test [ ^##(Exception printNl) ] ] MyProject.MyLibWrapper.Baz class extend [ test [ ^##(ValueAdaptor printNl) ] ] MyLibrary.BackForMore class extend [ test [ ^##(PkgVersion printNl) ] ] ""Both of the above -- this does not work yet"" MyLibrary.Foo class extend [ TryThis := ##(Exception printNl) ] MyLibrary.Bar class extend [ TryThis := ##(Scape printNl) ] MyLibrary.Blah class extend [ TryThis := ##(Scape printNl) ] MyProject.MyLibWrapper.Baz class extend [ TryThis := ##(Scape printNl) ] MyProject.MyLibWrapper.Baz class extend [ TryThis := ##(Exception printNl) ] MyProject.MyLibWrapper.Baz class extend [ TryThis := ##(ValueAdaptor printNl) ] MyLibrary.BackForMore class extend [ TryThis := ##(PkgVersion printNl) ]" "test namespace-sharedpools" Eval [ MyProject.MyLibWrapper.Baz new blah ] "6667" Eval [ MyLibrary.BackForMore new blah ] "Blah" Eval [ MyLibrary.BackForMore new scoobs ] "785" "test namespace pragmas" Eval [ MyImports.MITest new test nameIn: Smalltalk ] "MyLibrary.Foo" Eval [ MyImports.MITest new test2 nameIn: Smalltalk ] "MyProject.MyLibWrapper.Baz" smalltalk-3.2.5/tests/lists.st0000644000175000017500000000334312123404352013275 00000000000000"====================================================================== | | Benchmark for OrderedCollections | | ======================================================================" "====================================================================== | | Copyright (C) 2003, 2007, 2008 Free Software Foundation. | Written by Paolo Bonzini | | This file is part of GNU Smalltalk. | | GNU Smalltalk is free software; you can redistribute it and/or modify it | under the terms of the GNU General Public License as published by the Free | Software Foundation; either version 2, or (at your option) any later version. | | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS | FOR A PARTICULAR PURPOSE. See the GNU General Public License for more | details. | | You should have received a copy of the GNU General Public License along with | GNU Smalltalk; see the file COPYING. If not, write to the Free Software | Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. | ======================================================================" SmallInteger extend [ testLists [ | li1 li2 li3 | li1 := (1 to: self) asOrderedCollection. li2 := li1 copy. li3 := OrderedCollection new. [ li2 isEmpty ] whileFalse: [ li3 addLast: li2 removeFirst ]. [ li3 isEmpty ] whileFalse: [ li2 addLast: li3 removeLast ]. li1 := li1 reverse. li1 size = self ifFalse: [ self frob ]. li1 = li2 ifFalse: [ self frob ]. ^li1 size ] ] Eval [ n := Smalltalk arguments isEmpty ifTrue: [ 1 ] ifFalse: [ 1 max: Smalltalk arguments first asInteger ]. n timesRepeat: [ result := 10000 testLists ]. result displayNl ] smalltalk-3.2.5/tests/untrusted.st0000644000175000017500000000761712130343734014210 00000000000000"====================================================================== | | Test the security framework | | ======================================================================" "====================================================================== | | Copyright (C) 2003, 2007, 2008 Free Software Foundation. | Written by Paolo Bonzini | | This file is part of GNU Smalltalk. | | GNU Smalltalk is free software; you can redistribute it and/or modify it | under the terms of the GNU General Public License as published by the Free | Software Foundation; either version 2, or (at your option) any later version. | | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS | FOR A PARTICULAR PURPOSE. See the GNU General Public License for more | details. | | You should have received a copy of the GNU General Public License along with | GNU Smalltalk; see the file COPYING. If not, write to the Free Software | Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. | ======================================================================" Object subclass: A_Super [ | a | aSuper [ ^a ] ] A_Super subclass: A [ | a | a: value [ a := value ] check [ ^thisContext isUntrusted ] check: aBlock [ ^aBlock value ] dirtyBlock [ ^[ a printString. thisContext isUntrusted ] ] cleanBlock [ ^[ thisContext isUntrusted ] ] ] "Check that contexts are properly made untrusted -------------------------" Eval [ A isUntrusted ] Eval [ A new isUntrusted ] Eval [ A new check ] Eval [ A new check: [ thisContext isUntrusted ] ] Eval [ A new check: [ A new check ] ] Eval [ A new check: [ A new check: [ thisContext isUntrusted ] ] ] Eval [ A new check: A new cleanBlock ] Eval [ A new cleanBlock value ] Eval [ A new check: A new dirtyBlock ] Eval [ A new dirtyBlock value ] "Make the current process untrusted... -----------------------------------" Eval [ Processor activeProcess makeUntrusted: true. thisContext isUntrusted ] "...and check that subsequently created process are trusted." Eval [ thisContext isUntrusted ] "Make another process untrusted. -----------------------------------------" Eval [ | s result | s := Semaphore new. [ result := thisContext isUntrusted. s signal ] newProcess makeUntrusted: true; resume. s wait. ^result ] "Check that access restrictions are enforced -----------------------------" Eval [ Processor activeProcess makeUntrusted: true. Set compile: 'lovelyMethod [ ^tally ]'. Set compile: 'dangerousMethod [ tally := 0 ]'. Set compile: 'lovelyMethod [ ^Array ]'. Set compile: 'dangerousMethod [ Array := 0 ]' ] Eval [ Processor activeProcess makeUntrusted: true. Set methodsFor: 'security checking' ] lovelyMethod ^tally! dangerousMethod tally := 0! lovelyMethod ^Array! dangerousMethod Array := 0! ! Eval [ Set methodsFor: 'security checking' ] lovelyTrustedMethod ^tally! dangerousTrustedMethod tally := 0! lovelyTrustedMethod ^Array! dangerousTrustedMethod Array := 0! ! Set subclass: UntrustedSet [ | a | lovelyMethod [ ^tally ] dangerousMethod [ tally := 0 ] lovelyMethod [ ^Array ] dangerousMethod [ Array := 0 ] lovelyMethod [ ^a ] lovelyMethod [ a := 1 ] ] "Check that subclasses are not fragile. This has security implications as this test shows..." Eval [ A new a: 5; aSuper ] "Check that methods are properly made untrusted. -------------------------" Eval [ (A >> #check:) isUntrusted ] Eval [ (Set >> #lovelyMethod) isUntrusted ] Eval [ (Set >> #lovelyTrustedMethod) isUntrusted ] Eval [ (Set >> #dangerousTrustedMethod) isUntrusted ] "Check that subclasses are properly made untrusted. ----------------------" A subclass: B [ | b | ] Eval [ B isUntrusted ] smalltalk-3.2.5/tests/ackermann.st0000644000175000017500000000355412123404352014102 00000000000000"====================================================================== | | Benchmark for message sending and integer ops | | ======================================================================" "====================================================================== | | Copyright (C) 2003, 2007, 2008 Free Software Foundation. | Written by Paolo Bonzini | | This file is part of GNU Smalltalk. | | GNU Smalltalk is free software; you can redistribute it and/or modify it | under the terms of the GNU General Public License as published by the Free | Software Foundation; either version 2, or (at your option) any later version. | | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS | FOR A PARTICULAR PURPOSE. See the GNU General Public License for more | details. | | You should have received a copy of the GNU General Public License along with | GNU Smalltalk; see the file COPYING. If not, write to the Free Software | Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. | ======================================================================" Integer extend [ ack: n [ self = 0 ifTrue: [ ^n + 1 ]. n = 0 ifTrue: [ ^self - 1 ack: 1 ]. ^self - 1 ack: (self ack: n - 1) ] ackIt: nn [ | n | ^[ | m stack | m := self. n := nn. stack := OrderedCollection new. [ m = 0 ifTrue: [ n := n + 1. m := stack removeLast ] ifFalse: [ n = 0 ifTrue: [ m := m - 1. n := 1 ] ifFalse: [ stack addLast: m - 1. n := n - 1 ] ] ] repeat ] on: Error do: [ :ex | ex return: n ] ] ] Eval [ n := Smalltalk arguments isEmpty ifTrue: [ 4 ] ifFalse: [ Smalltalk arguments first asInteger ]. ('Ack(3,%1): %2' % { n. (3 ack: n) }) displayNl. ] smalltalk-3.2.5/tests/nestedloop.ok0000644000175000017500000000006112123404352014270 00000000000000 Execution begins... 4096 returned value is 4096 smalltalk-3.2.5/tests/objinst.ok0000644000175000017500000000016112123404352013565 00000000000000 Execution begins... false true false true false true true false false false true true true returned value is 1 smalltalk-3.2.5/tests/dates.st0000644000175000017500000004550512123404352013245 00000000000000"====================================================================== | | Test the Date class | | ======================================================================" "====================================================================== | | Copyright (C) 1999, 2007, 2008 Free Software Foundation. | Written by Paolo Bonzini and Jeff Rosenwald. | | This file is part of GNU Smalltalk. | | GNU Smalltalk is free software; you can redistribute it and/or modify it | under the terms of the GNU General Public License as published by the Free | Software Foundation; either version 2, or (at your option) any later version. | | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS | FOR A PARTICULAR PURPOSE. See the GNU General Public License for more | details. | | You should have received a copy of the GNU General Public License along with | GNU Smalltalk; see the file COPYING. If not, write to the Free Software | Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. | ======================================================================" Date class extend [ inspect: aDate and: anotherDate day: dd month: mm year: yyyy [ Transcript show: 'newDay: '; print: aDate; show: '('; print: aDate days; show: ') <--> '; print: dd; show: '-'; show: (self shortNameOfMonth: mm); show: '-'; print: yyyy; show: ' <--> fromDays: '; print: anotherDate; show: '('; print: anotherDate days; show: ')'; nl. ^self error: 'bad status'. ] test3 [ | i d | -100 to: 100 do: [:j | i _ (j * 24 * 3600) - 1. "23:59:59" d _ self fromSeconds: i. i print. Transcript space. d day print. Transcript space. d month print. Transcript space. d year print. Transcript space. d days printNl. i _ (j * 24 * 3600) . "00:00:00" d _ self fromSeconds: i. i print. Transcript space. d day print. Transcript space. d month print. Transcript space. d year print. Transcript space. d days printNl. ] ] test [ | r r1 d1 k | "This step tests a reasonable interval of years in a small time. Note that 7 is prime with 4, 100, 400." 1700 to: 4500 by: 7 do: [:yyyy | (Date daysInYear: yyyy) = 366 ifTrue: [ Transcript show: 'leap ' ]. yyyy printNl. 1 to: 12 do: [:mm | k _ Date daysInMonthIndex: mm forYear: yyyy. 1 to: k do: [:dd | r _ Date newDay: dd monthIndex: mm year: yyyy. r1 _ Date fromDays: (r days). (r month = r1 month) & (r day = r1 day) & (r year = r1 year) & (r1 days = r days) & (r1 dayOfWeek = r dayOfWeek) & (r month = mm) & (r day = dd) & (r year = yyyy) & (d1 isNil or: [ (d1 - r daysFromBaseDay) ~= 1 ]) ifFalse: [ self inspect: r and: r1 day: dd month: mm year: yyyy ]. d1 := r daysFromBaseDay. ]. ] ]. ] test2 [ #(1600 1699 1700 1799 1800 1899 1900 1901 1996 1997 1998 1999 2000 2001) do: [ :y | (Date newDay: 1 month: #jan year: y) print. Transcript space. (Date newDay: 1 month: #feb year: y) print. Transcript space. (Date newDay: 28 month: #feb year: y) print. Transcript space. (Date newDay: 1 month: #mar year: y) print. Transcript space. (Date newDay: 31 month: #dec year: y) print. Transcript space. (Date newDay: 29 month: #feb year: y) printNl ] ] ] Eval [ Date test ] Eval [ Date test2 ] Eval [ Date test3 ] String extend [ suffix: suffix testReading: aClass [ | stream end result | stream := (self, suffix) readStream. result := aClass readFrom: stream. end := stream upToEnd. result = (aClass readFrom: self readStream) ifFalse: [^nil]. ^(result->self) -> (suffix->end) ] ] Eval [ ('2011-02-01' suffix: ' abcd' testReading: Date) printNl. ('2011-02-01' suffix: 'abcd' testReading: Date) printNl. ('Feb 1 2011' suffix: ' abcd' testReading: Date) printNl. ('Feb 1 2011' suffix: 'abcd' testReading: Date) printNl. ('-2011-02-01' suffix: ' abcd' testReading: Date) printNl. ('-2011-02-01' suffix: 'abcd' testReading: Date) printNl. ('Feb 1 -2011' suffix: ' abcd' testReading: Date) printNl. ('Feb 1 -2011' suffix: 'abcd' testReading: Date) printNl. ('09:00:02' suffix: ' 1234' testReading: Time) printNl. ('09:00:02' suffix: ':1234' testReading: Time) printNl. ('09:00:02' suffix: ' abcd' testReading: Time) printNl. ('09:00:02' suffix: 'abcd' testReading: Time) printNl. ('09:00' suffix: ' 1234' testReading: Time) printNl. ('09:00' suffix: '::1234' testReading: Time) printNl. ('09:00' suffix: ' abcd' testReading: Time) printNl. ('09:00' suffix: 'abcd' testReading: Time) printNl. ('9:00' suffix: ' 1234' testReading: Time) printNl. ('9:00' suffix: '::1234' testReading: Time) printNl. ('9:00' suffix: ' abcd' testReading: Time) printNl. ('9:00' suffix: 'abcd' testReading: Time) printNl. ('01:09:00:02' suffix: ' 1234' testReading: Duration) printNl. ('01:09:00:02' suffix: ':1234' testReading: Duration) printNl. ('01:09:00:02' suffix: ' abcd' testReading: Duration) printNl. ('01:09:00:02' suffix: 'abcd' testReading: Duration) printNl. ('1:09:00:02' suffix: ' 1234' testReading: Duration) printNl. ('1:09:00:02' suffix: ':1234' testReading: Duration) printNl. ('1:09:00:02' suffix: ' abcd' testReading: Duration) printNl. ('1:09:00:02' suffix: 'abcd' testReading: Duration) printNl. ('1:9:00:02' suffix: ' 1234' testReading: Duration) printNl. ('1:9:00:02' suffix: ':1234' testReading: Duration) printNl. ('1:9:00:02' suffix: ' abcd' testReading: Duration) printNl. ('1:9:00:02' suffix: 'abcd' testReading: Duration) printNl. ('09:00:02' suffix: ' 1234' testReading: Duration) printNl. ('09:00:02' suffix: '::1234' testReading: Duration) printNl. ('09:00:02' suffix: ' abcd' testReading: Duration) printNl. ('09:00:02' suffix: 'abcd' testReading: Duration) printNl. ('9:00:02' suffix: ' 1234' testReading: Duration) printNl. ('9:00:02' suffix: '::1234' testReading: Duration) printNl. ('9:00:02' suffix: ' abcd' testReading: Duration) printNl. ('9:00:02' suffix: 'abcd' testReading: Duration) printNl. ('09:00' suffix: ' 1234' testReading: Duration) printNl. ('09:00' suffix: '::1234' testReading: Duration) printNl. ('09:00' suffix: ' abcd' testReading: Duration) printNl. ('09:00' suffix: 'abcd' testReading: Duration) printNl. ('9:00' suffix: ' 1234' testReading: Duration) printNl. ('9:00' suffix: '::1234' testReading: Duration) printNl. ('9:00' suffix: ' abcd' testReading: Duration) printNl. ('9:00' suffix: 'abcd' testReading: Duration) printNl. ('-01:09:00:02' suffix: ' 1234' testReading: Duration) printNl. ('-01:09:00:02' suffix: ':1234' testReading: Duration) printNl. ('-01:09:00:02' suffix: ' abcd' testReading: Duration) printNl. ('-01:09:00:02' suffix: 'abcd' testReading: Duration) printNl. ('-1:09:00:02' suffix: ' 1234' testReading: Duration) printNl. ('-1:09:00:02' suffix: ':1234' testReading: Duration) printNl. ('-1:09:00:02' suffix: ' abcd' testReading: Duration) printNl. ('-1:09:00:02' suffix: 'abcd' testReading: Duration) printNl. ('-1:9:00:02' suffix: ' 1234' testReading: Duration) printNl. ('-1:9:00:02' suffix: ':1234' testReading: Duration) printNl. ('-1:9:00:02' suffix: ' abcd' testReading: Duration) printNl. ('-1:9:00:02' suffix: 'abcd' testReading: Duration) printNl. ('-09:00:02' suffix: ' 1234' testReading: Duration) printNl. ('-09:00:02' suffix: '::1234' testReading: Duration) printNl. ('-09:00:02' suffix: ' abcd' testReading: Duration) printNl. ('-09:00:02' suffix: 'abcd' testReading: Duration) printNl. ('-9:00:02' suffix: ' 1234' testReading: Duration) printNl. ('-9:00:02' suffix: '::1234' testReading: Duration) printNl. ('-9:00:02' suffix: ' abcd' testReading: Duration) printNl. ('-9:00:02' suffix: 'abcd' testReading: Duration) printNl. ('-09:00' suffix: ' 1234' testReading: Duration) printNl. ('-09:00' suffix: '::1234' testReading: Duration) printNl. ('-09:00' suffix: ' abcd' testReading: Duration) printNl. ('-09:00' suffix: 'abcd' testReading: Duration) printNl. ('-9:00' suffix: ' 1234' testReading: Duration) printNl. ('-9:00' suffix: '::1234' testReading: Duration) printNl. ('-9:00' suffix: ' abcd' testReading: Duration) printNl. ('-9:00' suffix: 'abcd' testReading: Duration) printNl. ('+01:09:00:02' suffix: ' 1234' testReading: Duration) printNl. ('+01:09:00:02' suffix: ':1234' testReading: Duration) printNl. ('+01:09:00:02' suffix: ' abcd' testReading: Duration) printNl. ('+01:09:00:02' suffix: 'abcd' testReading: Duration) printNl. ('+1:09:00:02' suffix: ' 1234' testReading: Duration) printNl. ('+1:09:00:02' suffix: ':1234' testReading: Duration) printNl. ('+1:09:00:02' suffix: ' abcd' testReading: Duration) printNl. ('+1:09:00:02' suffix: 'abcd' testReading: Duration) printNl. ('+1:9:00:02' suffix: ' 1234' testReading: Duration) printNl. ('+1:9:00:02' suffix: ':1234' testReading: Duration) printNl. ('+1:9:00:02' suffix: ' abcd' testReading: Duration) printNl. ('+1:9:00:02' suffix: 'abcd' testReading: Duration) printNl. ('+09:00:02' suffix: ' 1234' testReading: Duration) printNl. ('+09:00:02' suffix: '::1234' testReading: Duration) printNl. ('+09:00:02' suffix: ' abcd' testReading: Duration) printNl. ('+09:00:02' suffix: 'abcd' testReading: Duration) printNl. ('+9:00:02' suffix: ' 1234' testReading: Duration) printNl. ('+9:00:02' suffix: '::1234' testReading: Duration) printNl. ('+9:00:02' suffix: ' abcd' testReading: Duration) printNl. ('+9:00:02' suffix: 'abcd' testReading: Duration) printNl. ('+09:00' suffix: ' 1234' testReading: Duration) printNl. ('+09:00' suffix: '::1234' testReading: Duration) printNl. ('+09:00' suffix: ' abcd' testReading: Duration) printNl. ('+09:00' suffix: 'abcd' testReading: Duration) printNl. ('+9:00' suffix: ' 1234' testReading: Duration) printNl. ('+9:00' suffix: '::1234' testReading: Duration) printNl. ('+9:00' suffix: ' abcd' testReading: Duration) printNl. ('+9:00' suffix: 'abcd' testReading: Duration) printNl. ('2011-02-01 09:00 +01:30' suffix: ' 1234' testReading: DateTime) printNl. ('2011-02-01 09:00 +01:30' suffix: ' abcd' testReading: DateTime) printNl. ('2011-02-01 09:00 +01:30' suffix: 'abcd' testReading: DateTime) printNl. ('2011-02-01 09:00 +01:30' suffix: ' 1234' testReading: DateTime) printNl. ('2011-02-01 09:00 +01:30' suffix: ' abcd' testReading: DateTime) printNl. ('2011-02-01 09:00 +01:30' suffix: 'abcd' testReading: DateTime) printNl. ('2011-02-01 09:00+01:30' suffix: ' 1234' testReading: DateTime) printNl. ('2011-02-01 09:00+01:30' suffix: ' abcd' testReading: DateTime) printNl. ('2011-02-01 09:00+01:30' suffix: 'abcd' testReading: DateTime) printNl. ('2011-02-01 09:00+1:30' suffix: ' abcd' testReading: DateTime) printNl. ('2011-02-01 09:00+1:30' suffix: 'abcd' testReading: DateTime) printNl. ('2011-02-01 09:00+01' suffix: ' 1234' testReading: DateTime) printNl. ('2011-02-01 09:00+01' suffix: ' abcd' testReading: DateTime) printNl. ('2011-02-01 09:00+01' suffix: 'abcd' testReading: DateTime) printNl. ('2011-02-01 09:00:10+01:30' suffix: ' 1234' testReading: DateTime) printNl. ('2011-02-01 09:00:10+01:30' suffix: ' abcd' testReading: DateTime) printNl. ('2011-02-01 09:00:10+01:30' suffix: 'abcd' testReading: DateTime) printNl. ('2011-02-01 09:00:10+1:30' suffix: ' abcd' testReading: DateTime) printNl. ('2011-02-01 09:00:10+1:30' suffix: 'abcd' testReading: DateTime) printNl. ('2011-02-01 09:00:10+01' suffix: ' 1234' testReading: DateTime) printNl. ('2011-02-01 09:00:10+01' suffix: ' abcd' testReading: DateTime) printNl. ('2011-02-01 09:00:10+01' suffix: 'abcd' testReading: DateTime) printNl. ('2011-02-01 09:00 -01:30' suffix: ' abcd' testReading: DateTime) printNl. ('2011-02-01 09:00 -01:30' suffix: 'abcd' testReading: DateTime) printNl. ('2011-02-01 09:00 -01:30' suffix: ' abcd' testReading: DateTime) printNl. ('2011-02-01 09:00 -01:30' suffix: 'abcd' testReading: DateTime) printNl. ('2011-02-01 09:00:10-01:30' suffix: ' abcd' testReading: DateTime) printNl. ('2011-02-01 09:00:10-01:30' suffix: 'abcd' testReading: DateTime) printNl. ('2011-02-01 09:00:10-1:30' suffix: ' abcd' testReading: DateTime) printNl. ('2011-02-01 09:00:10-1:30' suffix: 'abcd' testReading: DateTime) printNl. ('2011-02-01 09:00-01:30' suffix: ' abcd' testReading: DateTime) printNl. ('2011-02-01 09:00-01:30' suffix: 'abcd' testReading: DateTime) printNl. ('2011-02-01 09:00-1:30' suffix: ' abcd' testReading: DateTime) printNl. ('2011-02-01 09:00-1:30' suffix: 'abcd' testReading: DateTime) printNl. ('2011-02-01 09:00:10' suffix: ' abcd' testReading: DateTime) printNl. ('2011-02-01 09:00:10' suffix: 'abcd' testReading: DateTime) printNl. ('2011-02-01 09:00' suffix: ' abcd' testReading: DateTime) printNl. ('2011-02-01 09:00' suffix: 'abcd' testReading: DateTime) printNl. ('2011-02-01T09:00+01:30' suffix: ' abcd' testReading: DateTime) printNl. ('2011-02-01T09:00+01:30' suffix: 'abcd' testReading: DateTime) printNl. ('2011-02-01T09:00+1:30' suffix: ' abcd' testReading: DateTime) printNl. ('2011-02-01T09:00+1:30' suffix: 'abcd' testReading: DateTime) printNl. ('2011-02-01T09:00+01' suffix: ' abcd' testReading: DateTime) printNl. ('2011-02-01T09:00+01' suffix: 'abcd' testReading: DateTime) printNl. ('2011-02-01T09:00:10+01:30' suffix: ' abcd' testReading: DateTime) printNl. ('2011-02-01T09:00:10+01:30' suffix: 'abcd' testReading: DateTime) printNl. ('2011-02-01T09:00:10+1:30' suffix: ' abcd' testReading: DateTime) printNl. ('2011-02-01T09:00:10+1:30' suffix: 'abcd' testReading: DateTime) printNl. ('2011-02-01T09:00:10+01' suffix: ' abcd' testReading: DateTime) printNl. ('2011-02-01T09:00:10+01' suffix: 'abcd' testReading: DateTime) printNl. ('2011-02-01T09:00:10-01:30' suffix: ' abcd' testReading: DateTime) printNl. ('2011-02-01T09:00:10-01:30' suffix: 'abcd' testReading: DateTime) printNl. ('2011-02-01T09:00:10-1:30' suffix: ' abcd' testReading: DateTime) printNl. ('2011-02-01T09:00:10-1:30' suffix: 'abcd' testReading: DateTime) printNl. ('2011-02-01T09:00-01:30' suffix: ' abcd' testReading: DateTime) printNl. ('2011-02-01T09:00-01:30' suffix: 'abcd' testReading: DateTime) printNl. ('2011-02-01T09:00-1:30' suffix: ' abcd' testReading: DateTime) printNl. ('2011-02-01T09:00-1:30' suffix: 'abcd' testReading: DateTime) printNl. ('2011-02-01T09:00:10' suffix: ' abcd' testReading: DateTime) printNl. ('2011-02-01T09:00:10' suffix: 'abcd' testReading: DateTime) printNl. ('2011-02-01T09:00' suffix: ' abcd' testReading: DateTime) printNl. ('2011-02-01T09:00' suffix: 'abcd' testReading: DateTime) printNl. ('2011-02-01' suffix: ' abcd' testReading: DateTime) printNl. ('2011-02-01' suffix: 'abcd' testReading: DateTime) printNl. ('Feb 1 2011' suffix: ' abcd' testReading: DateTime) printNl. ('Feb 1 2011' suffix: 'abcd' testReading: DateTime) printNl. ('-2011-02-01T09:00+01:30' suffix: ' abcd' testReading: DateTime) printNl. ('-2011-02-01T09:00+01:30' suffix: 'abcd' testReading: DateTime) printNl. ('-2011-02-01' suffix: ' abcd' testReading: DateTime) printNl. ('-2011-02-01' suffix: 'abcd' testReading: DateTime) printNl. ('Feb 1 -2011' suffix: ' abcd' testReading: DateTime) printNl. ('Feb 1 -2011' suffix: 'abcd' testReading: DateTime) printNl. ('Feb 1 2011 09:00 +01:30' suffix: ' 1234' testReading: DateTime) printNl. ('Feb 1 2011 09:00 +01:30' suffix: ' abcd' testReading: DateTime) printNl. ('Feb 1 2011 09:00 +01:30' suffix: 'abcd' testReading: DateTime) printNl. ('Feb 1 2011 09:00 +01:30' suffix: ' 1234' testReading: DateTime) printNl. ('Feb 1 2011 09:00 +01:30' suffix: ' abcd' testReading: DateTime) printNl. ('Feb 1 2011 09:00 +01:30' suffix: 'abcd' testReading: DateTime) printNl. ('Feb 1 2011 09:00+01:30' suffix: ' 1234' testReading: DateTime) printNl. ('Feb 1 2011 09:00+01:30' suffix: ' abcd' testReading: DateTime) printNl. ('Feb 1 2011 09:00+01:30' suffix: 'abcd' testReading: DateTime) printNl. ('Feb 1 2011 09:00+01' suffix: ' 1234' testReading: DateTime) printNl. ('Feb 1 2011 09:00+01' suffix: ' abcd' testReading: DateTime) printNl. ('Feb 1 2011 09:00+01' suffix: 'abcd' testReading: DateTime) printNl. ('Feb 1 2011 09:00:10+01:30' suffix: ' 1234' testReading: DateTime) printNl. ('Feb 1 2011 09:00:10+01:30' suffix: ' abcd' testReading: DateTime) printNl. ('Feb 1 2011 09:00:10+01:30' suffix: 'abcd' testReading: DateTime) printNl. ('Feb 1 2011 09:00:10+01' suffix: ' 1234' testReading: DateTime) printNl. ('Feb 1 2011 09:00:10+01' suffix: ' abcd' testReading: DateTime) printNl. ('Feb 1 2011 09:00:10+01' suffix: 'abcd' testReading: DateTime) printNl. ('Feb 1 2011 09:00:10+1:30' suffix: ' abcd' testReading: DateTime) printNl. ('Feb 1 2011 09:00:10+1:30' suffix: 'abcd' testReading: DateTime) printNl. ('Feb 1 2011 09:00+1:30' suffix: ' abcd' testReading: DateTime) printNl. ('Feb 1 2011 09:00+1:30' suffix: 'abcd' testReading: DateTime) printNl. ('Feb 1 2011 09:00 -01:30' suffix: ' abcd' testReading: DateTime) printNl. ('Feb 1 2011 09:00 -01:30' suffix: 'abcd' testReading: DateTime) printNl. ('Feb 1 2011 09:00 -01:30' suffix: ' abcd' testReading: DateTime) printNl. ('Feb 1 2011 09:00 -01:30' suffix: 'abcd' testReading: DateTime) printNl. ('Feb 1 2011 09:00-01:30' suffix: ' abcd' testReading: DateTime) printNl. ('Feb 1 2011 09:00-01:30' suffix: 'abcd' testReading: DateTime) printNl. ('Feb 1 2011 09:00:10-01:30' suffix: ' abcd' testReading: DateTime) printNl. ('Feb 1 2011 09:00:10-01:30' suffix: 'abcd' testReading: DateTime) printNl. ('Feb 1 2011 09:00:10-1:30' suffix: ' abcd' testReading: DateTime) printNl. ('Feb 1 2011 09:00:10-1:30' suffix: 'abcd' testReading: DateTime) printNl. ('Feb 1 2011 09:00-1:30' suffix: ' abcd' testReading: DateTime) printNl. ('Feb 1 2011 09:00-1:30' suffix: 'abcd' testReading: DateTime) printNl. ('Feb 1 2011 09:00:10' suffix: ' abcd' testReading: DateTime) printNl. ('Feb 1 2011 09:00:10' suffix: 'abcd' testReading: DateTime) printNl. ('Feb 1 2011 09:00' suffix: ' abcd' testReading: DateTime) printNl. ('Feb 1 2011 09:00' suffix: 'abcd' testReading: DateTime) printNl. ] smalltalk-3.2.5/sigsegv/0000755000175000017500000000000012130456003012147 500000000000000smalltalk-3.2.5/sigsegv/tests/0000755000175000017500000000000012130456003013311 500000000000000smalltalk-3.2.5/sigsegv/tests/sigsegv1.c0000644000175000017500000000513012130343734015132 00000000000000/* Test that the handler is called, with the right fault address. Copyright (C) 2002-2006 Bruno Haible This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. */ #include "sigsegv.h" #include #if HAVE_SIGSEGV_RECOVERY #include "mmaputil.h" #include unsigned long page; volatile int handler_called = 0; int handler (void *fault_address, int serious) { handler_called++; if (handler_called > 10) abort (); if (fault_address != (void *)(page + 0x678)) abort (); if (mprotect ((void *) page, 0x4000, PROT_READ_WRITE) == 0) return 1; return 0; } void crasher (unsigned long p) { *(volatile int *) (p + 0x678) = 42; } int main () { void *p; /* Preparations. */ #if !HAVE_MMAP_ANON && !HAVE_MMAP_ANONYMOUS && HAVE_MMAP_DEVZERO zero_fd = open ("/dev/zero", O_RDONLY, 0644); #endif /* Setup some mmaped memory. */ p = mmap_zeromap ((void *) 0x12340000, 0x4000); if (p == (void *)(-1)) { fprintf (stderr, "mmap_zeromap failed.\n"); exit (2); } page = (unsigned long) p; /* Make it read-only. */ if (mprotect ((void *) page, 0x4000, PROT_READ) < 0) { fprintf (stderr, "mprotect failed.\n"); exit (2); } /* Test whether it's possible to make it read-write after it was read-only. This is not possible on Cygwin. */ if (mprotect ((void *) page, 0x4000, PROT_READ_WRITE) < 0 || mprotect ((void *) page, 0x4000, PROT_READ) < 0) { fprintf (stderr, "mprotect failed.\n"); exit (2); } /* Install the SIGSEGV handler. */ sigsegv_install_handler (&handler); /* The first write access should invoke the handler and then complete. */ crasher (page); /* The second write access should not invoke the handler. */ crasher (page); /* Check that the handler was called only once. */ if (handler_called != 1) exit (1); /* Test passed! */ printf ("Test passed.\n"); return 0; } #else int main () { return 77; } #endif smalltalk-3.2.5/sigsegv/tests/Makefile.am0000644000175000017500000000241312130343734015273 00000000000000## Makefile for libsigsegv/tests. ## Copyright (C) 2002-2003 Bruno Haible ## ## This program is free software; you can redistribute it and/or modify ## it under the terms of the GNU General Public License as published by ## the Free Software Foundation; either version 2, or (at your option) ## any later version. ## ## This program is distributed in the hope that it will be useful, ## but WITHOUT ANY WARRANTY; without even the implied warranty of ## MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the ## GNU General Public License for more details. ## ## You should have received a copy of the GNU General Public License ## along with this program; if not, write to the Free Software ## Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, ## USA. ## Process this file with automake to produce Makefile.in. AUTOMAKE_OPTIONS = 1.5 gnits no-dependencies TESTS = sigsegv1 sigsegv2 stackoverflow1 stackoverflow2 EXTRA_DIST = mmaputil.h AM_CPPFLAGS = -I../src DEFS = @DEFS@ LDADD = ../src/libsigsegv_convenience.la noinst_PROGRAMS = sigsegv1 sigsegv2 stackoverflow1 stackoverflow2 # The following rule is necessary to avoid a toplevel "make -n" failure. ../src/libsigsegv_convenience.la : cd ../src && $(MAKE) libsigsegv_convenience.la smalltalk-3.2.5/sigsegv/tests/sigsegv2.c0000644000175000017500000000740712130343734015144 00000000000000/* Test the dispatcher. Copyright (C) 2002-2006 Bruno Haible This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. */ #include "sigsegv.h" #include #if HAVE_SIGSEGV_RECOVERY #include "mmaputil.h" #include static sigsegv_dispatcher dispatcher; static volatile unsigned int logcount = 0; static volatile unsigned long logdata[10]; static int area_handler (void *fault_address, void *user_arg) { unsigned long area = *(unsigned long *)user_arg; logdata[logcount++] = area; if (logcount >= sizeof (logdata) / sizeof (logdata[0])) abort (); if (!((unsigned long)fault_address >= area && (unsigned long)fault_address - area < 0x4000)) abort (); if (mprotect ((void *) area, 0x4000, PROT_READ_WRITE) == 0) return 1; return 0; } static int handler (void *fault_address, int serious) { return sigsegv_dispatch (&dispatcher, fault_address); } static void barrier () { } int main () { void *p; unsigned long area1; unsigned long area2; unsigned long area3; /* Preparations. */ #if !HAVE_MMAP_ANON && !HAVE_MMAP_ANONYMOUS && HAVE_MMAP_DEVZERO zero_fd = open ("/dev/zero", O_RDONLY, 0644); #endif sigsegv_init (&dispatcher); sigsegv_install_handler (&handler); /* Setup some mmaped memory. */ p = mmap_zeromap ((void *) 0x12340000, 0x4000); if (p == (void *)(-1)) { fprintf (stderr, "mmap_zeromap failed.\n"); exit (2); } area1 = (unsigned long) p; sigsegv_register (&dispatcher, (void *) area1, 0x4000, &area_handler, &area1); if (mprotect ((void *) area1, 0x4000, PROT_NONE) < 0) { fprintf (stderr, "mprotect failed.\n"); exit (2); } p = mmap_zeromap ((void *) 0x0BEE0000, 0x4000); if (p == (void *)(-1)) { fprintf (stderr, "mmap_zeromap failed.\n"); exit (2); } area2 = (unsigned long) p; sigsegv_register (&dispatcher, (void *) area2, 0x4000, &area_handler, &area2); if (mprotect ((void *) area2, 0x4000, PROT_READ) < 0) { fprintf (stderr, "mprotect failed.\n"); exit (2); } if (mprotect ((void *) area2, 0x4000, PROT_READ_WRITE) < 0 || mprotect ((void *) area2, 0x4000, PROT_READ) < 0) { fprintf (stderr, "mprotect failed.\n"); exit (2); } p = mmap_zeromap ((void *) 0x06990000, 0x4000); if (p == (void *)(-1)) { fprintf (stderr, "mmap_zeromap failed.\n"); exit (2); } area3 = (unsigned long) p; sigsegv_register (&dispatcher, (void *) area3, 0x4000, &area_handler, &area3); mprotect ((void *) area3, 0x4000, PROT_READ); /* This access should call the handler. */ ((volatile int *)area2)[230] = 22; /* This access should call the handler. */ ((volatile int *)area3)[412] = 33; /* This access should not give a signal. */ ((volatile int *)area2)[135] = 22; /* This access should call the handler. */ ((volatile int *)area1)[612] = 11; barrier(); /* Check that the handler was called three times. */ if (logcount != 3) exit (1); if (!(logdata[0] == area2 && logdata[1] == area3 && logdata[2] == area1)) exit (1); printf ("Test passed.\n"); return 0; } #else int main () { return 77; } #endif smalltalk-3.2.5/sigsegv/tests/mmaputil.h0000644000175000017500000000556112130343734015247 00000000000000/* Some auxiliary stuff for using mmap & friends. Copyright (C) 2002-2003 Bruno Haible This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. */ #if defined _WIN32 && !defined __CYGWIN__ # define HAVE_WIN32_VM #else # include "config.h" #endif #ifdef HAVE_WIN32_VM /* ------------------------ Windows ------------------------ */ #define WIN32_LEAN_AND_MEAN /* avoid including junk */ #include #include #define PROT_NONE PAGE_NOACCESS #define PROT_READ PAGE_READONLY #define PROT_READ_WRITE PAGE_READWRITE static void * mmap_zeromap (void *map_addr_hint, unsigned long map_len) { if (VirtualAlloc ((void *)((unsigned long) map_addr_hint & -0x10000), (((unsigned long) map_addr_hint + map_len - 1) | 0xffff) + 1 - ((unsigned long) map_addr_hint & -0x10000), MEM_RESERVE, PAGE_NOACCESS) && VirtualAlloc (map_addr_hint, map_len, MEM_COMMIT, PAGE_READWRITE)) return map_addr_hint; else return (void *)(-1); } int munmap (void *addr, unsigned long len) { if (VirtualFree (addr, len, MEM_DECOMMIT)) return 0; else return -1; } int mprotect (void *addr, unsigned long len, int prot) { DWORD oldprot; if (VirtualProtect (addr, len, prot, &oldprot)) return 0; else return -1; } #else /* ------------------------ Unix ------------------------ */ #include #include #ifndef PROT_NONE # define PROT_NONE 0 #endif #define PROT_READ_WRITE (PROT_READ|PROT_WRITE) #if HAVE_MMAP_ANON # define zero_fd -1 # define map_flags MAP_ANON | MAP_PRIVATE #elif HAVE_MMAP_ANONYMOUS # define zero_fd -1 # define map_flags MAP_ANONYMOUS | MAP_PRIVATE #elif HAVE_MMAP_DEVZERO # include # ifndef MAP_FILE # define MAP_FILE 0 # endif static int zero_fd; # define map_flags MAP_FILE | MAP_PRIVATE #endif static void * mmap_zeromap (void *map_addr_hint, unsigned long map_len) { #ifdef __hpux /* HP-UX 10 mmap() often fails when given a hint. So give the OS complete freedom about the address range. */ return (void *) mmap ((void *) 0, map_len, PROT_READ_WRITE, map_flags, zero_fd, 0); #else return (void *) mmap (map_addr_hint, map_len, PROT_READ_WRITE, map_flags, zero_fd, 0); #endif } #endif smalltalk-3.2.5/sigsegv/tests/Makefile.in0000644000175000017500000004510112130455553015310 00000000000000# Makefile.in generated by automake 1.11.6 from Makefile.am. # @configure_input@ # Copyright (C) 1994, 1995, 1996, 1997, 1998, 1999, 2000, 2001, 2002, # 2003, 2004, 2005, 2006, 2007, 2008, 2009, 2010, 2011 Free Software # Foundation, Inc. # This Makefile.in is free software; the Free Software Foundation # gives unlimited permission to copy and/or distribute it, # with or without modifications, as long as this notice is preserved. # This program is distributed in the hope that it will be useful, # but WITHOUT ANY WARRANTY, to the extent permitted by law; without # even the implied warranty of MERCHANTABILITY or FITNESS FOR A # PARTICULAR PURPOSE. @SET_MAKE@ VPATH = @srcdir@ am__make_dryrun = \ { \ am__dry=no; \ case $$MAKEFLAGS in \ *\\[\ \ ]*) \ echo 'am--echo: ; @echo "AM" OK' | $(MAKE) -f - 2>/dev/null \ | grep '^AM OK$$' >/dev/null || am__dry=yes;; \ *) \ for am__flg in $$MAKEFLAGS; do \ case $$am__flg in \ *=*|--*) ;; \ *n*) am__dry=yes; break;; \ esac; \ done;; \ esac; \ test $$am__dry = yes; \ } pkgdatadir = $(datadir)/@PACKAGE@ pkgincludedir = $(includedir)/@PACKAGE@ pkglibdir = $(libdir)/@PACKAGE@ pkglibexecdir = $(libexecdir)/@PACKAGE@ am__cd = CDPATH="$${ZSH_VERSION+.}$(PATH_SEPARATOR)" && cd install_sh_DATA = $(install_sh) -c -m 644 install_sh_PROGRAM = $(install_sh) -c install_sh_SCRIPT = $(install_sh) -c INSTALL_HEADER = $(INSTALL_DATA) transform = $(program_transform_name) NORMAL_INSTALL = : PRE_INSTALL = : POST_INSTALL = : NORMAL_UNINSTALL = : PRE_UNINSTALL = : POST_UNINSTALL = : build_triplet = @build@ host_triplet = @host@ TESTS = sigsegv1$(EXEEXT) sigsegv2$(EXEEXT) stackoverflow1$(EXEEXT) \ stackoverflow2$(EXEEXT) noinst_PROGRAMS = sigsegv1$(EXEEXT) sigsegv2$(EXEEXT) \ stackoverflow1$(EXEEXT) stackoverflow2$(EXEEXT) subdir = tests DIST_COMMON = $(srcdir)/Makefile.am $(srcdir)/Makefile.in ACLOCAL_M4 = $(top_srcdir)/aclocal.m4 am__aclocal_m4_deps = $(top_srcdir)/../build-aux/bold.m4 \ $(top_srcdir)/../build-aux/fault.m4 \ $(top_srcdir)/../build-aux/getpagesize.m4 \ $(top_srcdir)/../build-aux/libtool.m4 \ $(top_srcdir)/../build-aux/ltoptions.m4 \ $(top_srcdir)/../build-aux/ltsugar.m4 \ $(top_srcdir)/../build-aux/ltversion.m4 \ $(top_srcdir)/../build-aux/lt~obsolete.m4 \ $(top_srcdir)/../build-aux/mmap-anon.m4 \ $(top_srcdir)/../build-aux/relocatable.m4 \ $(top_srcdir)/../build-aux/sigaltstack-longjmp.m4 \ $(top_srcdir)/../build-aux/sigaltstack-siglongjmp.m4 \ $(top_srcdir)/../build-aux/sigaltstack.m4 \ $(top_srcdir)/configure.ac am__configure_deps = $(am__aclocal_m4_deps) $(CONFIGURE_DEPENDENCIES) \ $(ACLOCAL_M4) mkinstalldirs = $(install_sh) -d CONFIG_HEADER = $(top_builddir)/config.h CONFIG_CLEAN_FILES = CONFIG_CLEAN_VPATH_FILES = PROGRAMS = $(noinst_PROGRAMS) sigsegv1_SOURCES = sigsegv1.c sigsegv1_OBJECTS = sigsegv1.$(OBJEXT) sigsegv1_LDADD = $(LDADD) sigsegv1_DEPENDENCIES = ../src/libsigsegv_convenience.la sigsegv2_SOURCES = sigsegv2.c sigsegv2_OBJECTS = sigsegv2.$(OBJEXT) sigsegv2_LDADD = $(LDADD) sigsegv2_DEPENDENCIES = ../src/libsigsegv_convenience.la stackoverflow1_SOURCES = stackoverflow1.c stackoverflow1_OBJECTS = stackoverflow1.$(OBJEXT) stackoverflow1_LDADD = $(LDADD) stackoverflow1_DEPENDENCIES = ../src/libsigsegv_convenience.la stackoverflow2_SOURCES = stackoverflow2.c stackoverflow2_OBJECTS = stackoverflow2.$(OBJEXT) stackoverflow2_LDADD = $(LDADD) stackoverflow2_DEPENDENCIES = ../src/libsigsegv_convenience.la DEFAULT_INCLUDES = -I.@am__isrc@ -I$(top_builddir) depcomp = am__depfiles_maybe = COMPILE = $(CC) $(DEFS) $(DEFAULT_INCLUDES) $(INCLUDES) $(AM_CPPFLAGS) \ $(CPPFLAGS) $(AM_CFLAGS) $(CFLAGS) LTCOMPILE = $(LIBTOOL) --tag=CC $(AM_LIBTOOLFLAGS) $(LIBTOOLFLAGS) \ --mode=compile $(CC) $(DEFS) $(DEFAULT_INCLUDES) $(INCLUDES) \ $(AM_CPPFLAGS) $(CPPFLAGS) $(AM_CFLAGS) $(CFLAGS) CCLD = $(CC) LINK = $(LIBTOOL) --tag=CC $(AM_LIBTOOLFLAGS) $(LIBTOOLFLAGS) \ --mode=link $(CCLD) $(AM_CFLAGS) $(CFLAGS) $(AM_LDFLAGS) \ $(LDFLAGS) -o $@ SOURCES = sigsegv1.c sigsegv2.c stackoverflow1.c stackoverflow2.c DIST_SOURCES = sigsegv1.c sigsegv2.c stackoverflow1.c stackoverflow2.c am__can_run_installinfo = \ case $$AM_UPDATE_INFO_DIR in \ n|no|NO) false;; \ *) (install-info --version) >/dev/null 2>&1;; \ esac ETAGS = etags CTAGS = ctags am__tty_colors = \ red=; grn=; lgn=; blu=; std= DISTFILES = $(DIST_COMMON) $(DIST_SOURCES) $(TEXINFOS) $(EXTRA_DIST) ACLOCAL = @ACLOCAL@ AMTAR = @AMTAR@ AR = @AR@ AUTOCONF = @AUTOCONF@ AUTOHEADER = @AUTOHEADER@ AUTOMAKE = @AUTOMAKE@ AWK = @AWK@ CC = @CC@ CCDEPMODE = @CCDEPMODE@ CFG_HANDLER = @CFG_HANDLER@ CFG_LEAVE = @CFG_LEAVE@ CFG_STACKVMA = @CFG_STACKVMA@ CFLAGS = @CFLAGS@ CPP = @CPP@ CPPFLAGS = @CPPFLAGS@ CYGPATH_W = @CYGPATH_W@ DEFS = @DEFS@ DEPDIR = @DEPDIR@ DLLTOOL = @DLLTOOL@ DSYMUTIL = @DSYMUTIL@ DUMPBIN = @DUMPBIN@ ECHO_C = @ECHO_C@ ECHO_N = @ECHO_N@ ECHO_T = @ECHO_T@ EGREP = @EGREP@ EXEEXT = @EXEEXT@ FAULT_CONTEXT = @FAULT_CONTEXT@ FAULT_CONTEXT_INCLUDE = @FAULT_CONTEXT_INCLUDE@ FAULT_CONTEXT_INCLUDE2 = @FAULT_CONTEXT_INCLUDE2@ FGREP = @FGREP@ GREP = @GREP@ HAVE_SIGSEGV_RECOVERY = @HAVE_SIGSEGV_RECOVERY@ HAVE_STACK_OVERFLOW_RECOVERY = @HAVE_STACK_OVERFLOW_RECOVERY@ INSTALL = @INSTALL@ INSTALL_DATA = @INSTALL_DATA@ INSTALL_PROGRAM = @INSTALL_PROGRAM@ INSTALL_SCRIPT = @INSTALL_SCRIPT@ INSTALL_STRIP_PROGRAM = @INSTALL_STRIP_PROGRAM@ LD = @LD@ LDFLAGS = @LDFLAGS@ LIBOBJS = @LIBOBJS@ LIBS = @LIBS@ LIBTOOL = @LIBTOOL@ LIPO = @LIPO@ LN_S = @LN_S@ LTLIBOBJS = @LTLIBOBJS@ MAKEINFO = @MAKEINFO@ MANIFEST_TOOL = @MANIFEST_TOOL@ MKDIR_P = @MKDIR_P@ NM = @NM@ NMEDIT = @NMEDIT@ OBJDUMP = @OBJDUMP@ OBJEXT = @OBJEXT@ OTOOL = @OTOOL@ OTOOL64 = @OTOOL64@ PACKAGE = @PACKAGE@ PACKAGE_BUGREPORT = @PACKAGE_BUGREPORT@ PACKAGE_NAME = @PACKAGE_NAME@ PACKAGE_STRING = @PACKAGE_STRING@ PACKAGE_TARNAME = @PACKAGE_TARNAME@ PACKAGE_URL = @PACKAGE_URL@ PACKAGE_VERSION = @PACKAGE_VERSION@ PATH_SEPARATOR = @PATH_SEPARATOR@ PLATFORM = @PLATFORM@ RANLIB = @RANLIB@ RELOCATABLE = @RELOCATABLE@ SED = @SED@ SET_MAKE = @SET_MAKE@ SHELL = @SHELL@ STRIP = @STRIP@ VERSION = @VERSION@ abs_builddir = @abs_builddir@ abs_srcdir = @abs_srcdir@ abs_top_builddir = @abs_top_builddir@ abs_top_srcdir = @abs_top_srcdir@ ac_ct_AR = @ac_ct_AR@ ac_ct_CC = @ac_ct_CC@ ac_ct_DUMPBIN = @ac_ct_DUMPBIN@ am__include = @am__include@ am__leading_dot = @am__leading_dot@ am__quote = @am__quote@ am__tar = @am__tar@ am__untar = @am__untar@ bindir = @bindir@ build = @build@ build_alias = @build_alias@ build_cpu = @build_cpu@ build_os = @build_os@ build_vendor = @build_vendor@ builddir = @builddir@ datadir = @datadir@ datarootdir = @datarootdir@ docdir = @docdir@ dvidir = @dvidir@ exec_prefix = @exec_prefix@ host = @host@ host_alias = @host_alias@ host_cpu = @host_cpu@ host_os = @host_os@ host_vendor = @host_vendor@ htmldir = @htmldir@ includedir = @includedir@ infodir = @infodir@ install_sh = @install_sh@ libdir = @libdir@ libexecdir = @libexecdir@ localedir = @localedir@ localstatedir = @localstatedir@ mandir = @mandir@ mkdir_p = @mkdir_p@ oldincludedir = @oldincludedir@ pdfdir = @pdfdir@ prefix = @prefix@ program_transform_name = @program_transform_name@ psdir = @psdir@ sbindir = @sbindir@ sharedstatedir = @sharedstatedir@ srcdir = @srcdir@ sysconfdir = @sysconfdir@ target_alias = @target_alias@ top_build_prefix = @top_build_prefix@ top_builddir = @top_builddir@ top_srcdir = @top_srcdir@ AUTOMAKE_OPTIONS = 1.5 gnits no-dependencies EXTRA_DIST = mmaputil.h AM_CPPFLAGS = -I../src LDADD = ../src/libsigsegv_convenience.la all: all-am .SUFFIXES: .SUFFIXES: .c .lo .o .obj $(srcdir)/Makefile.in: $(srcdir)/Makefile.am $(am__configure_deps) @for dep in $?; do \ case '$(am__configure_deps)' in \ *$$dep*) \ ( cd $(top_builddir) && $(MAKE) $(AM_MAKEFLAGS) am--refresh ) \ && { if test -f $@; then exit 0; else break; fi; }; \ exit 1;; \ esac; \ done; \ echo ' cd $(top_srcdir) && $(AUTOMAKE) --gnits tests/Makefile'; \ $(am__cd) $(top_srcdir) && \ $(AUTOMAKE) --gnits tests/Makefile .PRECIOUS: Makefile Makefile: $(srcdir)/Makefile.in $(top_builddir)/config.status @case '$?' in \ *config.status*) \ cd $(top_builddir) && $(MAKE) $(AM_MAKEFLAGS) am--refresh;; \ *) \ echo ' cd $(top_builddir) && $(SHELL) ./config.status $(subdir)/$@ $(am__depfiles_maybe)'; \ cd $(top_builddir) && $(SHELL) ./config.status $(subdir)/$@ $(am__depfiles_maybe);; \ esac; $(top_builddir)/config.status: $(top_srcdir)/configure $(CONFIG_STATUS_DEPENDENCIES) cd $(top_builddir) && $(MAKE) $(AM_MAKEFLAGS) am--refresh $(top_srcdir)/configure: $(am__configure_deps) cd $(top_builddir) && $(MAKE) $(AM_MAKEFLAGS) am--refresh $(ACLOCAL_M4): $(am__aclocal_m4_deps) cd $(top_builddir) && $(MAKE) $(AM_MAKEFLAGS) am--refresh $(am__aclocal_m4_deps): clean-noinstPROGRAMS: @list='$(noinst_PROGRAMS)'; test -n "$$list" || exit 0; \ echo " rm -f" $$list; \ rm -f $$list || exit $$?; \ test -n "$(EXEEXT)" || exit 0; \ list=`for p in $$list; do echo "$$p"; done | sed 's/$(EXEEXT)$$//'`; \ echo " rm -f" $$list; \ rm -f $$list sigsegv1$(EXEEXT): $(sigsegv1_OBJECTS) $(sigsegv1_DEPENDENCIES) $(EXTRA_sigsegv1_DEPENDENCIES) @rm -f sigsegv1$(EXEEXT) $(LINK) $(sigsegv1_OBJECTS) $(sigsegv1_LDADD) $(LIBS) sigsegv2$(EXEEXT): $(sigsegv2_OBJECTS) $(sigsegv2_DEPENDENCIES) $(EXTRA_sigsegv2_DEPENDENCIES) @rm -f sigsegv2$(EXEEXT) $(LINK) $(sigsegv2_OBJECTS) $(sigsegv2_LDADD) $(LIBS) stackoverflow1$(EXEEXT): $(stackoverflow1_OBJECTS) $(stackoverflow1_DEPENDENCIES) $(EXTRA_stackoverflow1_DEPENDENCIES) @rm -f stackoverflow1$(EXEEXT) $(LINK) $(stackoverflow1_OBJECTS) $(stackoverflow1_LDADD) $(LIBS) stackoverflow2$(EXEEXT): $(stackoverflow2_OBJECTS) $(stackoverflow2_DEPENDENCIES) $(EXTRA_stackoverflow2_DEPENDENCIES) @rm -f stackoverflow2$(EXEEXT) $(LINK) $(stackoverflow2_OBJECTS) $(stackoverflow2_LDADD) $(LIBS) mostlyclean-compile: -rm -f *.$(OBJEXT) distclean-compile: -rm -f *.tab.c .c.o: $(COMPILE) -c $< .c.obj: $(COMPILE) -c `$(CYGPATH_W) '$<'` .c.lo: $(LTCOMPILE) -c -o $@ $< mostlyclean-libtool: -rm -f *.lo clean-libtool: -rm -rf .libs _libs ID: $(HEADERS) $(SOURCES) $(LISP) $(TAGS_FILES) list='$(SOURCES) $(HEADERS) $(LISP) $(TAGS_FILES)'; \ unique=`for i in $$list; do \ if test -f "$$i"; then echo $$i; else echo $(srcdir)/$$i; fi; \ done | \ $(AWK) '{ files[$$0] = 1; nonempty = 1; } \ END { if (nonempty) { for (i in files) print i; }; }'`; \ mkid -fID $$unique tags: TAGS TAGS: $(HEADERS) $(SOURCES) $(TAGS_DEPENDENCIES) \ $(TAGS_FILES) $(LISP) set x; \ here=`pwd`; \ list='$(SOURCES) $(HEADERS) $(LISP) $(TAGS_FILES)'; \ unique=`for i in $$list; do \ if test -f "$$i"; then echo $$i; else echo $(srcdir)/$$i; fi; \ done | \ $(AWK) '{ files[$$0] = 1; nonempty = 1; } \ END { if (nonempty) { for (i in files) print i; }; }'`; \ shift; \ if test -z "$(ETAGS_ARGS)$$*$$unique"; then :; else \ test -n "$$unique" || unique=$$empty_fix; \ if test $$# -gt 0; then \ $(ETAGS) $(ETAGSFLAGS) $(AM_ETAGSFLAGS) $(ETAGS_ARGS) \ "$$@" $$unique; \ else \ $(ETAGS) $(ETAGSFLAGS) $(AM_ETAGSFLAGS) $(ETAGS_ARGS) \ $$unique; \ fi; \ fi ctags: CTAGS CTAGS: $(HEADERS) $(SOURCES) $(TAGS_DEPENDENCIES) \ $(TAGS_FILES) $(LISP) list='$(SOURCES) $(HEADERS) $(LISP) $(TAGS_FILES)'; \ unique=`for i in $$list; do \ if test -f "$$i"; then echo $$i; else echo $(srcdir)/$$i; fi; \ done | \ $(AWK) '{ files[$$0] = 1; nonempty = 1; } \ END { if (nonempty) { for (i in files) print i; }; }'`; \ test -z "$(CTAGS_ARGS)$$unique" \ || $(CTAGS) $(CTAGSFLAGS) $(AM_CTAGSFLAGS) $(CTAGS_ARGS) \ $$unique GTAGS: here=`$(am__cd) $(top_builddir) && pwd` \ && $(am__cd) $(top_srcdir) \ && gtags -i $(GTAGS_ARGS) "$$here" distclean-tags: -rm -f TAGS ID GTAGS GRTAGS GSYMS GPATH tags check-TESTS: $(TESTS) @failed=0; all=0; xfail=0; xpass=0; skip=0; \ srcdir=$(srcdir); export srcdir; \ list=' $(TESTS) '; \ $(am__tty_colors); \ if test -n "$$list"; then \ for tst in $$list; do \ if test -f ./$$tst; then dir=./; \ elif test -f $$tst; then dir=; \ else dir="$(srcdir)/"; fi; \ if $(TESTS_ENVIRONMENT) $${dir}$$tst; then \ all=`expr $$all + 1`; \ case " $(XFAIL_TESTS) " in \ *[\ \ ]$$tst[\ \ ]*) \ xpass=`expr $$xpass + 1`; \ failed=`expr $$failed + 1`; \ col=$$red; res=XPASS; \ ;; \ *) \ col=$$grn; res=PASS; \ ;; \ esac; \ elif test $$? -ne 77; then \ all=`expr $$all + 1`; \ case " $(XFAIL_TESTS) " in \ *[\ \ ]$$tst[\ \ ]*) \ xfail=`expr $$xfail + 1`; \ col=$$lgn; res=XFAIL; \ ;; \ *) \ failed=`expr $$failed + 1`; \ col=$$red; res=FAIL; \ ;; \ esac; \ else \ skip=`expr $$skip + 1`; \ col=$$blu; res=SKIP; \ fi; \ echo "$${col}$$res$${std}: $$tst"; \ done; \ if test "$$all" -eq 1; then \ tests="test"; \ All=""; \ else \ tests="tests"; \ All="All "; \ fi; \ if test "$$failed" -eq 0; then \ if test "$$xfail" -eq 0; then \ banner="$$All$$all $$tests passed"; \ else \ if test "$$xfail" -eq 1; then failures=failure; else failures=failures; fi; \ banner="$$All$$all $$tests behaved as expected ($$xfail expected $$failures)"; \ fi; \ else \ if test "$$xpass" -eq 0; then \ banner="$$failed of $$all $$tests failed"; \ else \ if test "$$xpass" -eq 1; then passes=pass; else passes=passes; fi; \ banner="$$failed of $$all $$tests did not behave as expected ($$xpass unexpected $$passes)"; \ fi; \ fi; \ dashes="$$banner"; \ skipped=""; \ if test "$$skip" -ne 0; then \ if test "$$skip" -eq 1; then \ skipped="($$skip test was not run)"; \ else \ skipped="($$skip tests were not run)"; \ fi; \ test `echo "$$skipped" | wc -c` -le `echo "$$banner" | wc -c` || \ dashes="$$skipped"; \ fi; \ report=""; \ if test "$$failed" -ne 0 && test -n "$(PACKAGE_BUGREPORT)"; then \ report="Please report to $(PACKAGE_BUGREPORT)"; \ test `echo "$$report" | wc -c` -le `echo "$$banner" | wc -c` || \ dashes="$$report"; \ fi; \ dashes=`echo "$$dashes" | sed s/./=/g`; \ if test "$$failed" -eq 0; then \ col="$$grn"; \ else \ col="$$red"; \ fi; \ echo "$${col}$$dashes$${std}"; \ echo "$${col}$$banner$${std}"; \ test -z "$$skipped" || echo "$${col}$$skipped$${std}"; \ test -z "$$report" || echo "$${col}$$report$${std}"; \ echo "$${col}$$dashes$${std}"; \ test "$$failed" -eq 0; \ else :; fi distdir: $(DISTFILES) @srcdirstrip=`echo "$(srcdir)" | sed 's/[].[^$$\\*]/\\\\&/g'`; \ topsrcdirstrip=`echo "$(top_srcdir)" | sed 's/[].[^$$\\*]/\\\\&/g'`; \ list='$(DISTFILES)'; \ dist_files=`for file in $$list; do echo $$file; done | \ sed -e "s|^$$srcdirstrip/||;t" \ -e "s|^$$topsrcdirstrip/|$(top_builddir)/|;t"`; \ case $$dist_files in \ */*) $(MKDIR_P) `echo "$$dist_files" | \ sed '/\//!d;s|^|$(distdir)/|;s,/[^/]*$$,,' | \ sort -u` ;; \ esac; \ for file in $$dist_files; do \ if test -f $$file || test -d $$file; then d=.; else d=$(srcdir); fi; \ if test -d $$d/$$file; then \ dir=`echo "/$$file" | sed -e 's,/[^/]*$$,,'`; \ if test -d "$(distdir)/$$file"; then \ find "$(distdir)/$$file" -type d ! -perm -700 -exec chmod u+rwx {} \;; \ fi; \ if test -d $(srcdir)/$$file && test $$d != $(srcdir); then \ cp -fpR $(srcdir)/$$file "$(distdir)$$dir" || exit 1; \ find "$(distdir)/$$file" -type d ! -perm -700 -exec chmod u+rwx {} \;; \ fi; \ cp -fpR $$d/$$file "$(distdir)$$dir" || exit 1; \ else \ test -f "$(distdir)/$$file" \ || cp -p $$d/$$file "$(distdir)/$$file" \ || exit 1; \ fi; \ done check-am: all-am $(MAKE) $(AM_MAKEFLAGS) check-TESTS check: check-am all-am: Makefile $(PROGRAMS) installdirs: install: install-am install-exec: install-exec-am install-data: install-data-am uninstall: uninstall-am install-am: all-am @$(MAKE) $(AM_MAKEFLAGS) install-exec-am install-data-am installcheck: installcheck-am install-strip: if test -z '$(STRIP)'; then \ $(MAKE) $(AM_MAKEFLAGS) INSTALL_PROGRAM="$(INSTALL_STRIP_PROGRAM)" \ install_sh_PROGRAM="$(INSTALL_STRIP_PROGRAM)" INSTALL_STRIP_FLAG=-s \ install; \ else \ $(MAKE) $(AM_MAKEFLAGS) INSTALL_PROGRAM="$(INSTALL_STRIP_PROGRAM)" \ install_sh_PROGRAM="$(INSTALL_STRIP_PROGRAM)" INSTALL_STRIP_FLAG=-s \ "INSTALL_PROGRAM_ENV=STRIPPROG='$(STRIP)'" install; \ fi mostlyclean-generic: clean-generic: distclean-generic: -test -z "$(CONFIG_CLEAN_FILES)" || rm -f $(CONFIG_CLEAN_FILES) -test . = "$(srcdir)" || test -z "$(CONFIG_CLEAN_VPATH_FILES)" || rm -f $(CONFIG_CLEAN_VPATH_FILES) maintainer-clean-generic: @echo "This command is intended for maintainers to use" @echo "it deletes files that may require special tools to rebuild." clean: clean-am clean-am: clean-generic clean-libtool clean-noinstPROGRAMS \ mostlyclean-am distclean: distclean-am -rm -f Makefile distclean-am: clean-am distclean-compile distclean-generic \ distclean-tags dvi: dvi-am dvi-am: html: html-am html-am: info: info-am info-am: install-data-am: install-dvi: install-dvi-am install-dvi-am: install-exec-am: install-html: install-html-am install-html-am: install-info: install-info-am install-info-am: install-man: install-pdf: install-pdf-am install-pdf-am: install-ps: install-ps-am install-ps-am: installcheck-am: maintainer-clean: maintainer-clean-am -rm -f Makefile maintainer-clean-am: distclean-am maintainer-clean-generic mostlyclean: mostlyclean-am mostlyclean-am: mostlyclean-compile mostlyclean-generic \ mostlyclean-libtool pdf: pdf-am pdf-am: ps: ps-am ps-am: uninstall-am: .MAKE: check-am install-am install-strip .PHONY: CTAGS GTAGS all all-am check check-TESTS check-am clean \ clean-generic clean-libtool clean-noinstPROGRAMS ctags \ distclean distclean-compile distclean-generic \ distclean-libtool distclean-tags distdir dvi dvi-am html \ html-am info info-am install install-am install-data \ install-data-am install-dvi install-dvi-am install-exec \ install-exec-am install-html install-html-am install-info \ install-info-am install-man install-pdf install-pdf-am \ install-ps install-ps-am install-strip installcheck \ installcheck-am installdirs maintainer-clean \ maintainer-clean-generic mostlyclean mostlyclean-compile \ mostlyclean-generic mostlyclean-libtool pdf pdf-am ps ps-am \ tags uninstall uninstall-am # The following rule is necessary to avoid a toplevel "make -n" failure. ../src/libsigsegv_convenience.la : cd ../src && $(MAKE) libsigsegv_convenience.la # Tell versions [3.59,3.63) of GNU make to not export all variables. # Otherwise a system limit (for SysV at least) may be exceeded. .NOEXPORT: smalltalk-3.2.5/sigsegv/tests/stackoverflow1.c0000644000175000017500000000615212130343734016361 00000000000000/* Test the stack overflow handler. Copyright (C) 2002-2006 Bruno Haible This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. */ #include "sigsegv.h" #include #include #if HAVE_STACK_OVERFLOW_RECOVERY #if defined _WIN32 && !defined __CYGWIN__ /* Windows doesn't have sigset_t. */ typedef int sigset_t; # define sigemptyset(set) # define sigprocmask(how,set,oldset) #else /* Unix */ # include "config.h" #endif #include /* needed for NULL on SunOS4 */ #include /* for abort, exit */ #include #include #if HAVE_SETRLIMIT # include # include # include #endif #ifndef SIGSTKSZ # define SIGSTKSZ 16384 #endif jmp_buf mainloop; sigset_t mainsigset; volatile int pass = 0; void stackoverflow_handler (int emergency, stackoverflow_context_t scp) { pass++; printf ("Stack overflow %d caught.\n", pass); sigprocmask (SIG_SETMASK, &mainsigset, NULL); sigsegv_leave_handler (); longjmp (mainloop, emergency ? -1 : pass); } volatile int * recurse_1 (int n, volatile int *p) { if (n < INT_MAX) *recurse_1 (n + 1, p) += n; return p; } volatile int recurse (volatile int n) { return *recurse_1 (n, &n); } /* glibc says: Users should use SIGSTKSZ as the size of user-supplied buffers. */ char mystack[SIGSTKSZ]; int main () { sigset_t emptyset; #if HAVE_SETRLIMIT && defined RLIMIT_STACK /* Before starting the endless recursion, try to be friendly to the user's machine. On some Linux 2.2.x systems, there is no stack limit for user processes at all. We don't want to kill such systems. */ struct rlimit rl; rl.rlim_cur = rl.rlim_max = 0x100000; /* 1 MB */ setrlimit (RLIMIT_STACK, &rl); #endif /* Install the stack overflow handler. */ if (stackoverflow_install_handler (&stackoverflow_handler, mystack, sizeof (mystack)) < 0) exit (2); /* Save the current signal mask. */ sigemptyset (&emptyset); sigprocmask (SIG_BLOCK, &emptyset, &mainsigset); /* Provoke two stack overflows in a row. */ switch (setjmp (mainloop)) { case -1: printf ("emergency exit\n"); exit (1); case 0: case 1: printf ("Starting recursion pass %d.\n", pass + 1); recurse (0); printf ("no endless recursion?!\n"); exit (1); case 2: break; default: abort (); } printf ("Test passed.\n"); exit (0); } #else int main () { return 77; } #endif smalltalk-3.2.5/sigsegv/tests/stackoverflow2.c0000644000175000017500000001071612130343734016363 00000000000000/* Test that stack overflow and SIGSEGV are correctly distinguished. Copyright (C) 2002-2006 Bruno Haible This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. */ #include "sigsegv.h" #include #include #if HAVE_STACK_OVERFLOW_RECOVERY && HAVE_SIGSEGV_RECOVERY #if defined _WIN32 && !defined __CYGWIN__ /* Windows doesn't have sigset_t. */ typedef int sigset_t; # define sigemptyset(set) # define sigprocmask(how,set,oldset) #else /* Unix */ # include "config.h" #endif #include "mmaputil.h" #include /* needed for NULL on SunOS4 */ #include /* for abort, exit */ #include #include #if HAVE_SETRLIMIT # include # include # include #endif #ifndef SIGSTKSZ # define SIGSTKSZ 16384 #endif jmp_buf mainloop; sigset_t mainsigset; volatile int pass = 0; unsigned long page; void stackoverflow_handler (int emergency, stackoverflow_context_t scp) { pass++; if (pass <= 2) printf ("Stack overflow %d caught.\n", pass); else { printf ("Segmentation violation misdetected as stack overflow.\n"); exit (1); } sigprocmask (SIG_SETMASK, &mainsigset, NULL); sigsegv_leave_handler (); longjmp (mainloop, emergency ? -1 : pass); } int sigsegv_handler (void *address, int emergency) { /* This test is necessary to distinguish stack overflow and SIGSEGV. */ if (!emergency) return 0; pass++; if (pass <= 2) { printf ("Stack overflow %d missed.\n", pass); exit (1); } else printf ("Segmentation violation correctly detected.\n"); sigprocmask (SIG_SETMASK, &mainsigset, NULL); sigsegv_leave_handler (); longjmp (mainloop, pass); } volatile int * recurse_1 (int n, volatile int *p) { if (n < INT_MAX) *recurse_1 (n + 1, p) += n; return p; } volatile int recurse (volatile int n) { return *recurse_1 (n, &n); } /* glibc says: Users should use SIGSTKSZ as the size of user-supplied buffers. */ char mystack[SIGSTKSZ]; int main () { sigset_t emptyset; void *p; #if HAVE_SETRLIMIT && defined RLIMIT_STACK /* Before starting the endless recursion, try to be friendly to the user's machine. On some Linux 2.2.x systems, there is no stack limit for user processes at all. We don't want to kill such systems. */ struct rlimit rl; rl.rlim_cur = rl.rlim_max = 0x100000; /* 1 MB */ setrlimit (RLIMIT_STACK, &rl); #endif /* Install the stack overflow handler. */ if (stackoverflow_install_handler (&stackoverflow_handler, mystack, sizeof (mystack)) < 0) exit (2); /* Preparations. */ #if !HAVE_MMAP_ANON && !HAVE_MMAP_ANONYMOUS && HAVE_MMAP_DEVZERO zero_fd = open ("/dev/zero", O_RDONLY, 0644); #endif /* Setup some mmaped memory. */ p = mmap_zeromap ((void *) 0x12340000, 0x4000); if (p == (void *)(-1)) { fprintf (stderr, "mmap_zeromap failed.\n"); exit (2); } page = (unsigned long) p; /* Make it read-only. */ if (mprotect ((void *) page, 0x4000, PROT_READ) < 0) { fprintf (stderr, "mprotect failed.\n"); exit (2); } /* Install the SIGSEGV handler. */ if (sigsegv_install_handler (&sigsegv_handler) < 0) exit (2); /* Save the current signal mask. */ sigemptyset (&emptyset); sigprocmask (SIG_BLOCK, &emptyset, &mainsigset); /* Provoke two stack overflows in a row. */ switch (setjmp (mainloop)) { case -1: printf ("emergency exit\n"); exit (1); case 0: case 1: printf ("Starting recursion pass %d.\n", pass + 1); recurse (0); printf ("no endless recursion?!\n"); exit (1); case 2: *(volatile int *) (page + 0x678) = 42; break; case 3: break; default: abort (); } printf ("Test passed.\n"); exit (0); } #else int main () { return 77; } #endif smalltalk-3.2.5/sigsegv/NEWS0000644000175000017500000000267012130343734012601 00000000000000New in 2.5: * Support for MacOS X 10.5. New in 2.4: * Support for GCC 4 on more platforms. * Added support for catching stack overflow on NetBSD. * Improved support for catching stack overflow on Linux, Solaris: Works also when /proc is not mounted or lacks read permissions. New in 2.3: * Support for GCC 4 on some platforms contributed by Paolo Bonzini. * Support for MacOS X i386 contributed by Bruno Haible. * Improved support for Woe32 contributed by Doug Currie. New in 2.2: * Support for new versions of MacOS X contributed by Paolo Bonzini. * Improved support for AIX 5, contributed by Bruno Haible. New in 2.1: * Support for MacOS X contributed by Paolo Bonzini. * Support for Cygwin contributed by Paolo Bonzini. * Support for Linux/ia64 and Linux/hppa contributed by Bruno Haible. * Support for OpenBSD/i386 contributed by Bruno Haible. * Support for NetBSD/alpha contributed by Paolo Bonzini. New in 2.0: * Modernized infrastructure. * Added support for catching stack overflow on AIX 4, HP-UX, and BeOS. * Dropped support for NeXTstep. * The function sigsegv_leave_handler() no longer restores the signal mask. This must now be done by the calling handler (either through sigprocmask or through siglongjmp). New in 1.2: * Support for HP-UX contributed by Paolo Bonzini. New in 1.1: * Catching stack overflow now works on some Unix systems: - Linux 2.2.x with glibc-2.1, - Sun Solaris, - DEC OSF/1 4.0, - SGI Irix. smalltalk-3.2.5/sigsegv/ChangeLog.10000644000175000017500000003007112130343734014007 000000000000002002-07-15 Bruno Haible * sigsegv.h.in (HAVE_STACK_OVERFLOW_RECOVERY): Define also on FreeBSD. (stackoverflow_context_t): Define as 'struct sigcontext *' on FreeBSD. * handler.c (SIGSEGV_ALL_SIGNALS) [FreeBSD]: Add SIGSEGV; this is the signal that gets sent on stack overflow. (get_vma) [FreeBSD]: New. (reset_onstack_flag) [FreeBSD]: New . 2002-05-07 Paolo Bonzini * sigsegv.h.in [__hpux, hpux]: Define HAVE_SIGSEGV_RECOVERY. * handler.c (UNIX_HPUX) [__hpux, hpux]: New macro. Define the hacks to access CR21. * test1.c (mmap_zeromap): Return the address. (handler): Don't hardcode the correct fault address. (main): Set page to the result of mmap_zeromap. * test2.c (mmap_zeromap): Return the address. (main): Set area1/area2/area3 to the result of mmap_zeromap. 2002-05-06 Bruno Haible * test1.c: Include , for exit(). * test2.c: Likewise. * test3.c: Likewise. 2002-04-28 Bruno Haible * Makefile.devel (ACLOCAL): Remove variable. (ACSELECT): Remove variable. (OTHERMACROS): Remove variable. (m4/*.m4): New rules. (autoconf/aclocal.m4): Construct using aclocal instead of acselect. 2001-08-25 Bruno Haible Upgrade to autoconf-2.52. * autoconf/autoconf: Upgrade to autoconf-2.52. * autoconf/acgeneral.m4: Remove file. * autoconf/acspecific.m4: Remove file. * autoconf/autoconf.m4f: New file, from autoconf-2.52. * autoconf/aclocal.m4: Require autoconf-2.52. (CL_CANONICAL_HOST): Call AC_CANONICAL_HOST. Don't cache the result, AC_CANONICAL_HOST does it itself. Add $SHELL in front of $ac_config_guess and $ac_config_sub. (CL_SIGACTION_REINSTALL): Include , for memset declaration. * Makefile.devel (AUTOCONF_FILES): Remove acgeneral.m4, acspecific.m4. Add autoconf.m4f. (configure): Use autoconf options -A, -l instead of -m. * config.h.in: Don't define HAVE_MEMSET. (MPROTECT_CONST, SETRLIMIT_CONST): Use #undef, not #define, to work around an autoconf bug. 2001-08-05 Bruno Haible * autoconf/acgeneral.m4 (AC_MSG_RESULTPROTO): Remove macro. (AC_LANG_EXTERN): Move to aclocal.m4. * autoconf/aclocal.m4 (AC_LANG_EXTERN): Moved here from acgeneral.m4. (CL_PROTO): Use AC_MSG_RESULT directly, instead of AC_MSG_RESULTPROTO. (CL_SILENT): No need to pushdef AC_MSG_RESULTPROTO. 2001-06-08 Bruno Haible * autoconf/ltmain.sh: Upgrade to libtool-1.4. * autoconf/ltconfig: Remove file. 2001-06-08 Bruno Haible * autoconf/config.guess: Update to GNU version 2001-05-11. * autoconf/config.sub: Likewise. 2001-05-09 Bruno Haible * sigsegv.h.in: Recognize __arm__ as CPU indicator on Linux. * handler.c: Likewise. 2001-03-19 Bruno Haible * autoconf/aclocal.m4 (CL_CANONICAL_HOST): Always define ac_config_guess and ac_config_sub. Then ignore requests for AC_CONFIG_AUX_DIR_DEFAULT or AC_CANONICAL_HOST. 2001-03-19 Bruno Haible * ltconfig, ltmain.sh: Upgrade to libtool-1.3.5. 2001-02-20 Bruno Haible * Makefile.in (libdir, includedir): Use the autoconf determined value, in order to respect the configure arguments. (mandir): Remove unused variable. * Makefile.msvc (mandir): LIkewise. * Makefile.in (install, installdirs, uninstall): Support DESTDIR. 2000-12-08 Bruno Haible * Makefile.in (exec_prefix): Use configure's --exec-prefix argument. 2000-11-15 Bruno Haible * Makefile.msvc: Add support for MFLAGS and DEBUG parameters. 2000-11-12 Bruno Haible * autoconf/config.guess, autoconf/config.sub: Upgrade to newest version from GNU CVS. 2000-11-08 Bruno Haible * aclocal.m4 (CL_SIGNAL_UNBLOCK): Enable 'volatile' for gotsig, wasblocked. (CL_SIGNAL_BLOCK_OTHERS): Enable 'volatile' for gotsig, somewereblocked. (CL_SIGACTION_UNBLOCK): Enable 'volatile' for gotsig, wasblocked. 2000-09-29 Bruno Haible * autoconf/aclocal.m4 (CL_CANONICAL_HOST): Fix bug in 2000-05-23 change. 2000-05-29 Bruno Haible * autoconf/aclocal.m4 (CL_PROG_INSTALL): Fix typo. Reported by Thomas Klausner . 2000-05-25 Bruno Haible * Makefile.msvc: Use 'copy' and 'ren' instead of 'cp' and 'mv'. 2000-05-23 Bruno Haible * autoconf/aclocal.m4 (CL_CANONICAL_HOST): Determine host_cpu, host_vendor, host_os correctly if $host has more than two hyphens. 2000-04-02 Bruno Haible Allow building on filesystems lacking symlinks and hard links. * Makefile.devel (autoconf/aclocal.m4): Replace AC_PROG_LN_S with CL_PROG_LN_S. * configure.in: Add CL_PROG_LN_S. * src/Makefile.in (LN): Remove. 1999-06-18 Bruno Haible * handler.c (user_handler): Define also on WIN32. 1999-06-16 Bruno Haible * sigsegv.h.in (stackoverflow_context_t): More precise definition on Solaris, Irix, OSF/1. 1999-05-30 Bruno Haible * Makefile.in (install-lib): New target. 1999-05-29 Bruno Haible * Makefile.in (install): Make sure the directories $(prefix) and $(exec_prefix) exist. 1999-05-16 Bruno Haible Libtoolify. * autoconf/ltconfig, autoconf/ltmain.sh: New files, from libtool-1.2. * Makefile.devel (OTHERMACROS): New macro. (autoconf/aclocal.m4): Add the contents of $(OTHERMACROS). * configure.in: Call CL_CANONICAL_HOST and AM_PROG_LIBTOOL. * Makefile.in (LIBTOOL, LIBTOOL_COMPILE, LIBTOOL_LINK, LIBTOOL_INSTALL, LIBTOOL_UNINSTALL): New macros. (top_builddir): New macro. (OBJECTS): Change .o to .lo. (all): Change .a to .la. (handler.lo): Renamed from handler.o. Use $(LIBTOOL_COMPILE). (dispatcher.lo): Renamed from dispatcher.o. Use $(LIBTOOL_COMPILE). (libsigsegv.la): Renamed from libsigsegv.a. Use $(LIBTOOL_LINK). (install): Use $(LIBTOOL_INSTALL). Copy ./sigsegv.h not $(srcdir)/sigsegv.h. (uninstall): Use $(LIBTOOL_UNINSTALL). (test1, test2, test3): Change .a to .la. Use $(LIBTOOL_LINK). (clean): Also remove *.lo *.la .libs _libs. (distclean): Also remove libtool. 1999-05-16 Bruno Haible For Linux 2.0.x with glibc2.0. * aclocal.m4 (CL_SIGALTSTACK): Define HAVE_SIGALTSTACK only if the sigaction flags macro SA_ONSTACK is also defined. 1999-05-15 Bruno Haible For DEC OSF/1 3.2. * sigsegv.h.in (HAVE_STACK_OVERFLOW_RECOVERY): Undefine if test3 doesn't work. * Makefile.in (SEDPREPARE0, SEDCOMMAND3): New macros. (sigsegv.h): Also try running test3. 1999-05-09 Bruno Haible * sigsegv.h.in (HAVE_STACK_OVERFLOW_RECOVERY): Also define on Solaris, Irix, OSF/1. * handler.c: Use symbolic UNIX_* macros for various Unix brands. (SIGSEGV_FAULT_HANDLER_ARGLIST, SIGSEGV_ALL_SIGNALS): Define also when HAVE_SIGSEGV_RECOVERY is not defined. Add support for Linux/m68k, Linux/mips, Linux/alpha, Linux/arm. (SIGSEGV_FAULT_CONTEXT, SIGSEGV_FAULT_STACKPOINTER): New macros. (get_vma) [UNIX_LINUX]: No need to initialize prev twice. (reset_onstack_flag) [UNIX_LINUX]: New function. (get_vma, reset_onstack_flag) [UNIX_SUNOS, UNIX_IRIX, UNIX_OSF]: New functions. (sigsegv_leave_handler): If SIGACTION_NEED_UNBLOCK is defined, unblock the signal itself. Call reset_onstack_flag. (stackoverflow_deinstall_handler): Print something if sigaltstack fails. * aclocal.m4 (CL_SIGNAL_UNBLOCK, CL_SIGNAL_BLOCK_OTHERS, CL_SIGACTION_UNBLOCK): Perform the test if either POSIX or BSD signal mask primitives are available. Otherwise, SIGACTION_NEED_UNBLOCK would not be defined on Solaris. 1999-05-07 Bruno Haible * test3.c (main): Make more verbose. Avoid a "make check" failure with "cc" on DEC OSF/1 4.0. * test2.c (barrier): New function. (main): Call it at the right moment. * Makefile.in (SEDPREPARE1, SEDCOMMAND2): Don't use # as literal. Only GNU make understands \#, other `make's don't. 1999-05-02 Bruno Haible Support for catching stack overflow on Unix, using sigaltstack(). * aclocal.m4 (CL_SIGALTSTACK): New macro. * configure.in: Add CL_SIGALTSTACK and CL_RLIMIT. * config.h.in: Add HAVE_SIGALTSTACK, HAVE_SETRLIMIT, RLIMIT_RESOURCE_T, SETRLIMIT_CONST. * Makefile.in (SEDPREPARE1, SEDCOMMAND1, SEDCOMMAND2): New macros. (sigsegv.h): Use them. Depend on config.h. * sigsegv.h.in: Test __linux__ instead of linux. Conditionally define HAVE_STACK_OVERFLOW_RECOVERY for Linux. (sigsegv_handler_t): Add `serious' argument. (stackoverflow_context_t): New type. (stackoverflow_handler_t, stackoverflow_install_handler, stackoverflow_deinstall_handler): Declare unconditionally. (stackoverflow_handler_t): Add `scp' argument. (stackoverflow_install_handler): Change return type to `int'. * handler.c: Test __linux__ instead of linux. Move Win32 section to the end. On Unix, install SIGSEGV handler if HAVE_SIGSEGV_RECOVERY or HAVE_STACK_OVERFLOW_RECOVERY. (vma_struct): New type. (get_vma): New function. (SIGSEGV_FAULT_CONTEXT, SIGSEGV_FAULT_STACKPOINTER): New macros. (stack_top): New variable. (remember_stack_top): New function. (stk_user_handler, stk_extra_stack, stk_extra_stack_size): New variables. (no_user_handler): Remove, use NULL instead. (sigsegv_handler): Extend to support HAVE_STACK_OVERFLOW_RECOVERY. (install_for): Add SA_ONSTACK to sigaction flags if needed. (sigsegv_deinstall_handler): Deinstall handlers only if not needed for stk_user_handler. (stackoverflow_install_handler, stackoverflow_deinstall_handler): New functions. (stack_overflow_handler) [WIN32]: Add context argument. (main_exception_filter): Pass context argument. * test1.c (handler): Add `serious' argument. * test2.c (handler): Likewise. * test3.c (stackoverflow_handler): Add `scp' argument. Use sigsegv_leave_handler instead of complicated #ifdef spaghetti. (main): Call setrlimit, to make sure the recursion doesn't kill the machine. If stackoverflow_install_handler returns -1, bypass the test, because it would crash. 1999-03-15 Bruno Haible * configure.in: Add CL_CC_GCC. * Makefile.in: Use "-x none" option where appropriate. * dispatcher.c: In C++ mode, don't define a function named `delete'. 1999-02-08 Bruno Haible * sigsegv/sigsegv.h.in: Renamed from sigsegv/sigsegv.h. Added "#undef HAVE_SIGSEGV_RECOVERY", commented out. * Makefile.in (sigsegv.h): Try compiling and running test1. If it fails, like on Solaris 2.5 and 2.5.1, uncomment "#undef HAVE_SIGSEGV_RECOVERY". * Makefile.msvc: Update. 1999-01-29 Bruno Haible * sigsegv.h [linux && sparc]: Disable HAVE_SIGSEGV_RECOVERY. It does not work any more. smalltalk-3.2.5/sigsegv/configure0000755000175000017500000175777212130455553014041 00000000000000#! /bin/sh # Guess values for system-dependent variables and create Makefiles. # Generated by GNU Autoconf 2.69. # # # Copyright (C) 1992-1996, 1998-2012 Free Software Foundation, Inc. # # # This configure script is free software; the Free Software Foundation # gives unlimited permission to copy, distribute and modify it. ## -------------------- ## ## M4sh Initialization. ## ## -------------------- ## # Be more Bourne compatible DUALCASE=1; export DUALCASE # for MKS sh if test -n "${ZSH_VERSION+set}" && (emulate sh) >/dev/null 2>&1; then : emulate sh NULLCMD=: # Pre-4.2 versions of Zsh do word splitting on ${1+"$@"}, which # is contrary to our usage. Disable this feature. alias -g '${1+"$@"}'='"$@"' setopt NO_GLOB_SUBST else case `(set -o) 2>/dev/null` in #( *posix*) : set -o posix ;; #( *) : ;; esac fi as_nl=' ' export as_nl # Printing a long string crashes Solaris 7 /usr/bin/printf. as_echo='\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\' as_echo=$as_echo$as_echo$as_echo$as_echo$as_echo as_echo=$as_echo$as_echo$as_echo$as_echo$as_echo$as_echo # Prefer a ksh shell builtin over an external printf program on Solaris, # but without wasting forks for bash or zsh. if test -z "$BASH_VERSION$ZSH_VERSION" \ && (test "X`print -r -- $as_echo`" = "X$as_echo") 2>/dev/null; then as_echo='print -r --' as_echo_n='print -rn --' elif (test "X`printf %s $as_echo`" = "X$as_echo") 2>/dev/null; then as_echo='printf %s\n' as_echo_n='printf %s' else if test "X`(/usr/ucb/echo -n -n $as_echo) 2>/dev/null`" = "X-n $as_echo"; then as_echo_body='eval /usr/ucb/echo -n "$1$as_nl"' as_echo_n='/usr/ucb/echo -n' else as_echo_body='eval expr "X$1" : "X\\(.*\\)"' as_echo_n_body='eval arg=$1; case $arg in #( *"$as_nl"*) expr "X$arg" : "X\\(.*\\)$as_nl"; arg=`expr "X$arg" : ".*$as_nl\\(.*\\)"`;; esac; expr "X$arg" : "X\\(.*\\)" | tr -d "$as_nl" ' export as_echo_n_body as_echo_n='sh -c $as_echo_n_body as_echo' fi export as_echo_body as_echo='sh -c $as_echo_body as_echo' fi # The user is always right. if test "${PATH_SEPARATOR+set}" != set; then PATH_SEPARATOR=: (PATH='/bin;/bin'; FPATH=$PATH; sh -c :) >/dev/null 2>&1 && { (PATH='/bin:/bin'; FPATH=$PATH; sh -c :) >/dev/null 2>&1 || PATH_SEPARATOR=';' } fi # IFS # We need space, tab and new line, in precisely that order. Quoting is # there to prevent editors from complaining about space-tab. # (If _AS_PATH_WALK were called with IFS unset, it would disable word # splitting by setting IFS to empty value.) IFS=" "" $as_nl" # Find who we are. Look in the path if we contain no directory separator. as_myself= case $0 in #(( *[\\/]* ) as_myself=$0 ;; *) as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. test -r "$as_dir/$0" && as_myself=$as_dir/$0 && break done IFS=$as_save_IFS ;; esac # We did not find ourselves, most probably we were run as `sh COMMAND' # in which case we are not to be found in the path. if test "x$as_myself" = x; then as_myself=$0 fi if test ! -f "$as_myself"; then $as_echo "$as_myself: error: cannot find myself; rerun with an absolute file name" >&2 exit 1 fi # Unset variables that we do not need and which cause bugs (e.g. in # pre-3.0 UWIN ksh). But do not cause bugs in bash 2.01; the "|| exit 1" # suppresses any "Segmentation fault" message there. '((' could # trigger a bug in pdksh 5.2.14. for as_var in BASH_ENV ENV MAIL MAILPATH do eval test x\${$as_var+set} = xset \ && ( (unset $as_var) || exit 1) >/dev/null 2>&1 && unset $as_var || : done PS1='$ ' PS2='> ' PS4='+ ' # NLS nuisances. LC_ALL=C export LC_ALL LANGUAGE=C export LANGUAGE # CDPATH. (unset CDPATH) >/dev/null 2>&1 && unset CDPATH # Use a proper internal environment variable to ensure we don't fall # into an infinite loop, continuously re-executing ourselves. if test x"${_as_can_reexec}" != xno && test "x$CONFIG_SHELL" != x; then _as_can_reexec=no; export _as_can_reexec; # We cannot yet assume a decent shell, so we have to provide a # neutralization value for shells without unset; and this also # works around shells that cannot unset nonexistent variables. # Preserve -v and -x to the replacement shell. BASH_ENV=/dev/null ENV=/dev/null (unset BASH_ENV) >/dev/null 2>&1 && unset BASH_ENV ENV case $- in # (((( *v*x* | *x*v* ) as_opts=-vx ;; *v* ) as_opts=-v ;; *x* ) as_opts=-x ;; * ) as_opts= ;; esac exec $CONFIG_SHELL $as_opts "$as_myself" ${1+"$@"} # Admittedly, this is quite paranoid, since all the known shells bail # out after a failed `exec'. $as_echo "$0: could not re-execute with $CONFIG_SHELL" >&2 as_fn_exit 255 fi # We don't want this to propagate to other subprocesses. { _as_can_reexec=; unset _as_can_reexec;} if test "x$CONFIG_SHELL" = x; then as_bourne_compatible="if test -n \"\${ZSH_VERSION+set}\" && (emulate sh) >/dev/null 2>&1; then : emulate sh NULLCMD=: # Pre-4.2 versions of Zsh do word splitting on \${1+\"\$@\"}, which # is contrary to our usage. Disable this feature. alias -g '\${1+\"\$@\"}'='\"\$@\"' setopt NO_GLOB_SUBST else case \`(set -o) 2>/dev/null\` in #( *posix*) : set -o posix ;; #( *) : ;; esac fi " as_required="as_fn_return () { (exit \$1); } as_fn_success () { as_fn_return 0; } as_fn_failure () { as_fn_return 1; } as_fn_ret_success () { return 0; } as_fn_ret_failure () { return 1; } exitcode=0 as_fn_success || { exitcode=1; echo as_fn_success failed.; } as_fn_failure && { exitcode=1; echo as_fn_failure succeeded.; } as_fn_ret_success || { exitcode=1; echo as_fn_ret_success failed.; } as_fn_ret_failure && { exitcode=1; echo as_fn_ret_failure succeeded.; } if ( set x; as_fn_ret_success y && test x = \"\$1\" ); then : else exitcode=1; echo positional parameters were not saved. fi test x\$exitcode = x0 || exit 1 test -x / || exit 1" as_suggested=" as_lineno_1=";as_suggested=$as_suggested$LINENO;as_suggested=$as_suggested" as_lineno_1a=\$LINENO as_lineno_2=";as_suggested=$as_suggested$LINENO;as_suggested=$as_suggested" as_lineno_2a=\$LINENO eval 'test \"x\$as_lineno_1'\$as_run'\" != \"x\$as_lineno_2'\$as_run'\" && test \"x\`expr \$as_lineno_1'\$as_run' + 1\`\" = \"x\$as_lineno_2'\$as_run'\"' || exit 1 test \$(( 1 + 1 )) = 2 || exit 1 test -n \"\${ZSH_VERSION+set}\${BASH_VERSION+set}\" || ( ECHO='\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\' ECHO=\$ECHO\$ECHO\$ECHO\$ECHO\$ECHO ECHO=\$ECHO\$ECHO\$ECHO\$ECHO\$ECHO\$ECHO PATH=/empty FPATH=/empty; export PATH FPATH test \"X\`printf %s \$ECHO\`\" = \"X\$ECHO\" \\ || test \"X\`print -r -- \$ECHO\`\" = \"X\$ECHO\" ) || exit 1" if (eval "$as_required") 2>/dev/null; then : as_have_required=yes else as_have_required=no fi if test x$as_have_required = xyes && (eval "$as_suggested") 2>/dev/null; then : else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR as_found=false for as_dir in /bin$PATH_SEPARATOR/usr/bin$PATH_SEPARATOR$PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. as_found=: case $as_dir in #( /*) for as_base in sh bash ksh sh5; do # Try only shells that exist, to save several forks. as_shell=$as_dir/$as_base if { test -f "$as_shell" || test -f "$as_shell.exe"; } && { $as_echo "$as_bourne_compatible""$as_required" | as_run=a "$as_shell"; } 2>/dev/null; then : CONFIG_SHELL=$as_shell as_have_required=yes if { $as_echo "$as_bourne_compatible""$as_suggested" | as_run=a "$as_shell"; } 2>/dev/null; then : break 2 fi fi done;; esac as_found=false done $as_found || { if { test -f "$SHELL" || test -f "$SHELL.exe"; } && { $as_echo "$as_bourne_compatible""$as_required" | as_run=a "$SHELL"; } 2>/dev/null; then : CONFIG_SHELL=$SHELL as_have_required=yes fi; } IFS=$as_save_IFS if test "x$CONFIG_SHELL" != x; then : export CONFIG_SHELL # We cannot yet assume a decent shell, so we have to provide a # neutralization value for shells without unset; and this also # works around shells that cannot unset nonexistent variables. # Preserve -v and -x to the replacement shell. BASH_ENV=/dev/null ENV=/dev/null (unset BASH_ENV) >/dev/null 2>&1 && unset BASH_ENV ENV case $- in # (((( *v*x* | *x*v* ) as_opts=-vx ;; *v* ) as_opts=-v ;; *x* ) as_opts=-x ;; * ) as_opts= ;; esac exec $CONFIG_SHELL $as_opts "$as_myself" ${1+"$@"} # Admittedly, this is quite paranoid, since all the known shells bail # out after a failed `exec'. $as_echo "$0: could not re-execute with $CONFIG_SHELL" >&2 exit 255 fi if test x$as_have_required = xno; then : $as_echo "$0: This script requires a shell more modern than all" $as_echo "$0: the shells that I found on your system." if test x${ZSH_VERSION+set} = xset ; then $as_echo "$0: In particular, zsh $ZSH_VERSION has bugs and should" $as_echo "$0: be upgraded to zsh 4.3.4 or later." else $as_echo "$0: Please tell bug-autoconf@gnu.org about your system, $0: including any error possibly output before this $0: message. Then install a modern shell, or manually run $0: the script under such a shell if you do have one." fi exit 1 fi fi fi SHELL=${CONFIG_SHELL-/bin/sh} export SHELL # Unset more variables known to interfere with behavior of common tools. CLICOLOR_FORCE= GREP_OPTIONS= unset CLICOLOR_FORCE GREP_OPTIONS ## --------------------- ## ## M4sh Shell Functions. ## ## --------------------- ## # as_fn_unset VAR # --------------- # Portably unset VAR. as_fn_unset () { { eval $1=; unset $1;} } as_unset=as_fn_unset # as_fn_set_status STATUS # ----------------------- # Set $? to STATUS, without forking. as_fn_set_status () { return $1 } # as_fn_set_status # as_fn_exit STATUS # ----------------- # Exit the shell with STATUS, even in a "trap 0" or "set -e" context. as_fn_exit () { set +e as_fn_set_status $1 exit $1 } # as_fn_exit # as_fn_mkdir_p # ------------- # Create "$as_dir" as a directory, including parents if necessary. as_fn_mkdir_p () { case $as_dir in #( -*) as_dir=./$as_dir;; esac test -d "$as_dir" || eval $as_mkdir_p || { as_dirs= while :; do case $as_dir in #( *\'*) as_qdir=`$as_echo "$as_dir" | sed "s/'/'\\\\\\\\''/g"`;; #'( *) as_qdir=$as_dir;; esac as_dirs="'$as_qdir' $as_dirs" as_dir=`$as_dirname -- "$as_dir" || $as_expr X"$as_dir" : 'X\(.*[^/]\)//*[^/][^/]*/*$' \| \ X"$as_dir" : 'X\(//\)[^/]' \| \ X"$as_dir" : 'X\(//\)$' \| \ X"$as_dir" : 'X\(/\)' \| . 2>/dev/null || $as_echo X"$as_dir" | sed '/^X\(.*[^/]\)\/\/*[^/][^/]*\/*$/{ s//\1/ q } /^X\(\/\/\)[^/].*/{ s//\1/ q } /^X\(\/\/\)$/{ s//\1/ q } /^X\(\/\).*/{ s//\1/ q } s/.*/./; q'` test -d "$as_dir" && break done test -z "$as_dirs" || eval "mkdir $as_dirs" } || test -d "$as_dir" || as_fn_error $? "cannot create directory $as_dir" } # as_fn_mkdir_p # as_fn_executable_p FILE # ----------------------- # Test if FILE is an executable regular file. as_fn_executable_p () { test -f "$1" && test -x "$1" } # as_fn_executable_p # as_fn_append VAR VALUE # ---------------------- # Append the text in VALUE to the end of the definition contained in VAR. Take # advantage of any shell optimizations that allow amortized linear growth over # repeated appends, instead of the typical quadratic growth present in naive # implementations. if (eval "as_var=1; as_var+=2; test x\$as_var = x12") 2>/dev/null; then : eval 'as_fn_append () { eval $1+=\$2 }' else as_fn_append () { eval $1=\$$1\$2 } fi # as_fn_append # as_fn_arith ARG... # ------------------ # Perform arithmetic evaluation on the ARGs, and store the result in the # global $as_val. Take advantage of shells that can avoid forks. The arguments # must be portable across $(()) and expr. if (eval "test \$(( 1 + 1 )) = 2") 2>/dev/null; then : eval 'as_fn_arith () { as_val=$(( $* )) }' else as_fn_arith () { as_val=`expr "$@" || test $? -eq 1` } fi # as_fn_arith # as_fn_error STATUS ERROR [LINENO LOG_FD] # ---------------------------------------- # Output "`basename $0`: error: ERROR" to stderr. If LINENO and LOG_FD are # provided, also output the error to LOG_FD, referencing LINENO. Then exit the # script with STATUS, using 1 if that was 0. as_fn_error () { as_status=$1; test $as_status -eq 0 && as_status=1 if test "$4"; then as_lineno=${as_lineno-"$3"} as_lineno_stack=as_lineno_stack=$as_lineno_stack $as_echo "$as_me:${as_lineno-$LINENO}: error: $2" >&$4 fi $as_echo "$as_me: error: $2" >&2 as_fn_exit $as_status } # as_fn_error if expr a : '\(a\)' >/dev/null 2>&1 && test "X`expr 00001 : '.*\(...\)'`" = X001; then as_expr=expr else as_expr=false fi if (basename -- /) >/dev/null 2>&1 && test "X`basename -- / 2>&1`" = "X/"; then as_basename=basename else as_basename=false fi if (as_dir=`dirname -- /` && test "X$as_dir" = X/) >/dev/null 2>&1; then as_dirname=dirname else as_dirname=false fi as_me=`$as_basename -- "$0" || $as_expr X/"$0" : '.*/\([^/][^/]*\)/*$' \| \ X"$0" : 'X\(//\)$' \| \ X"$0" : 'X\(/\)' \| . 2>/dev/null || $as_echo X/"$0" | sed '/^.*\/\([^/][^/]*\)\/*$/{ s//\1/ q } /^X\/\(\/\/\)$/{ s//\1/ q } /^X\/\(\/\).*/{ s//\1/ q } s/.*/./; q'` # Avoid depending upon Character Ranges. as_cr_letters='abcdefghijklmnopqrstuvwxyz' as_cr_LETTERS='ABCDEFGHIJKLMNOPQRSTUVWXYZ' as_cr_Letters=$as_cr_letters$as_cr_LETTERS as_cr_digits='0123456789' as_cr_alnum=$as_cr_Letters$as_cr_digits as_lineno_1=$LINENO as_lineno_1a=$LINENO as_lineno_2=$LINENO as_lineno_2a=$LINENO eval 'test "x$as_lineno_1'$as_run'" != "x$as_lineno_2'$as_run'" && test "x`expr $as_lineno_1'$as_run' + 1`" = "x$as_lineno_2'$as_run'"' || { # Blame Lee E. McMahon (1931-1989) for sed's syntax. :-) sed -n ' p /[$]LINENO/= ' <$as_myself | sed ' s/[$]LINENO.*/&-/ t lineno b :lineno N :loop s/[$]LINENO\([^'$as_cr_alnum'_].*\n\)\(.*\)/\2\1\2/ t loop s/-\n.*// ' >$as_me.lineno && chmod +x "$as_me.lineno" || { $as_echo "$as_me: error: cannot create $as_me.lineno; rerun with a POSIX shell" >&2; as_fn_exit 1; } # If we had to re-execute with $CONFIG_SHELL, we're ensured to have # already done that, so ensure we don't try to do so again and fall # in an infinite loop. This has already happened in practice. _as_can_reexec=no; export _as_can_reexec # Don't try to exec as it changes $[0], causing all sort of problems # (the dirname of $[0] is not the place where we might find the # original and so on. Autoconf is especially sensitive to this). . "./$as_me.lineno" # Exit status is that of the last command. exit } ECHO_C= ECHO_N= ECHO_T= case `echo -n x` in #((((( -n*) case `echo 'xy\c'` in *c*) ECHO_T=' ';; # ECHO_T is single tab character. xy) ECHO_C='\c';; *) echo `echo ksh88 bug on AIX 6.1` > /dev/null ECHO_T=' ';; esac;; *) ECHO_N='-n';; esac rm -f conf$$ conf$$.exe conf$$.file if test -d conf$$.dir; then rm -f conf$$.dir/conf$$.file else rm -f conf$$.dir mkdir conf$$.dir 2>/dev/null fi if (echo >conf$$.file) 2>/dev/null; then if ln -s conf$$.file conf$$ 2>/dev/null; then as_ln_s='ln -s' # ... but there are two gotchas: # 1) On MSYS, both `ln -s file dir' and `ln file dir' fail. # 2) DJGPP < 2.04 has no symlinks; `ln -s' creates a wrapper executable. # In both cases, we have to default to `cp -pR'. ln -s conf$$.file conf$$.dir 2>/dev/null && test ! -f conf$$.exe || as_ln_s='cp -pR' elif ln conf$$.file conf$$ 2>/dev/null; then as_ln_s=ln else as_ln_s='cp -pR' fi else as_ln_s='cp -pR' fi rm -f conf$$ conf$$.exe conf$$.dir/conf$$.file conf$$.file rmdir conf$$.dir 2>/dev/null if mkdir -p . 2>/dev/null; then as_mkdir_p='mkdir -p "$as_dir"' else test -d ./-p && rmdir ./-p as_mkdir_p=false fi as_test_x='test -x' as_executable_p=as_fn_executable_p # Sed expression to map a string onto a valid CPP name. as_tr_cpp="eval sed 'y%*$as_cr_letters%P$as_cr_LETTERS%;s%[^_$as_cr_alnum]%_%g'" # Sed expression to map a string onto a valid variable name. as_tr_sh="eval sed 'y%*+%pp%;s%[^_$as_cr_alnum]%_%g'" SHELL=${CONFIG_SHELL-/bin/sh} test -n "$DJDIR" || exec 7<&0 &1 # Name of the host. # hostname on some systems (SVR3.2, old GNU/Linux) returns a bogus exit status, # so uname gets run too. ac_hostname=`(hostname || uname -n) 2>/dev/null | sed 1q` # # Initializations. # ac_default_prefix=/usr/local ac_clean_files= ac_config_libobj_dir=. LIBOBJS= cross_compiling=no subdirs= MFLAGS= MAKEFLAGS= # Identity of this package. PACKAGE_NAME= PACKAGE_TARNAME= PACKAGE_VERSION= PACKAGE_STRING= PACKAGE_BUGREPORT= PACKAGE_URL= ac_unique_file="src/sigsegv.h.in" # Factoring default headers for most tests. ac_includes_default="\ #include #ifdef HAVE_SYS_TYPES_H # include #endif #ifdef HAVE_SYS_STAT_H # include #endif #ifdef STDC_HEADERS # include # include #else # ifdef HAVE_STDLIB_H # include # endif #endif #ifdef HAVE_STRING_H # if !defined STDC_HEADERS && defined HAVE_MEMORY_H # include # endif # include #endif #ifdef HAVE_STRINGS_H # include #endif #ifdef HAVE_INTTYPES_H # include #endif #ifdef HAVE_STDINT_H # include #endif #ifdef HAVE_UNISTD_H # include #endif" ac_subst_vars='am__EXEEXT_FALSE am__EXEEXT_TRUE LTLIBOBJS LIBOBJS RELOCATABLE CFG_HANDLER CFG_LEAVE HAVE_STACK_OVERFLOW_RECOVERY CFG_STACKVMA HAVE_SIGSEGV_RECOVERY FAULT_CONTEXT_INCLUDE2 FAULT_CONTEXT_INCLUDE FAULT_CONTEXT OTOOL64 OTOOL LIPO NMEDIT DSYMUTIL MANIFEST_TOOL RANLIB ac_ct_AR AR DLLTOOL OBJDUMP LN_S NM ac_ct_DUMPBIN DUMPBIN LD FGREP EGREP GREP LIBTOOL SED PLATFORM host_os host_vendor host_cpu host build_os build_vendor build_cpu build CPP am__fastdepCC_FALSE am__fastdepCC_TRUE CCDEPMODE am__nodep AMDEPBACKSLASH AMDEP_FALSE AMDEP_TRUE am__quote am__include DEPDIR OBJEXT EXEEXT ac_ct_CC CPPFLAGS LDFLAGS CFLAGS CC am__untar am__tar AMTAR am__leading_dot SET_MAKE AWK mkdir_p MKDIR_P INSTALL_STRIP_PROGRAM STRIP install_sh MAKEINFO AUTOHEADER AUTOMAKE AUTOCONF ACLOCAL VERSION PACKAGE CYGPATH_W am__isrc INSTALL_DATA INSTALL_SCRIPT INSTALL_PROGRAM target_alias host_alias build_alias LIBS ECHO_T ECHO_N ECHO_C DEFS mandir localedir libdir psdir pdfdir dvidir htmldir infodir docdir oldincludedir includedir localstatedir sharedstatedir sysconfdir datadir datarootdir libexecdir sbindir bindir program_transform_name prefix exec_prefix PACKAGE_URL PACKAGE_BUGREPORT PACKAGE_STRING PACKAGE_VERSION PACKAGE_TARNAME PACKAGE_NAME PATH_SEPARATOR SHELL' ac_subst_files='' ac_user_opts=' enable_option_checking enable_dependency_tracking enable_shared enable_static with_pic enable_fast_install with_gnu_ld with_sysroot enable_libtool_lock enable_relocatable ' ac_precious_vars='build_alias host_alias target_alias CC CFLAGS LDFLAGS LIBS CPPFLAGS CPP' # Initialize some variables set by options. ac_init_help= ac_init_version=false ac_unrecognized_opts= ac_unrecognized_sep= # The variables have the same names as the options, with # dashes changed to underlines. cache_file=/dev/null exec_prefix=NONE no_create= no_recursion= prefix=NONE program_prefix=NONE program_suffix=NONE program_transform_name=s,x,x, silent= site= srcdir= verbose= x_includes=NONE x_libraries=NONE # Installation directory options. # These are left unexpanded so users can "make install exec_prefix=/foo" # and all the variables that are supposed to be based on exec_prefix # by default will actually change. # Use braces instead of parens because sh, perl, etc. also accept them. # (The list follows the same order as the GNU Coding Standards.) bindir='${exec_prefix}/bin' sbindir='${exec_prefix}/sbin' libexecdir='${exec_prefix}/libexec' datarootdir='${prefix}/share' datadir='${datarootdir}' sysconfdir='${prefix}/etc' sharedstatedir='${prefix}/com' localstatedir='${prefix}/var' includedir='${prefix}/include' oldincludedir='/usr/include' docdir='${datarootdir}/doc/${PACKAGE}' infodir='${datarootdir}/info' htmldir='${docdir}' dvidir='${docdir}' pdfdir='${docdir}' psdir='${docdir}' libdir='${exec_prefix}/lib' localedir='${datarootdir}/locale' mandir='${datarootdir}/man' ac_prev= ac_dashdash= for ac_option do # If the previous option needs an argument, assign it. if test -n "$ac_prev"; then eval $ac_prev=\$ac_option ac_prev= continue fi case $ac_option in *=?*) ac_optarg=`expr "X$ac_option" : '[^=]*=\(.*\)'` ;; *=) ac_optarg= ;; *) ac_optarg=yes ;; esac # Accept the important Cygnus configure options, so we can diagnose typos. case $ac_dashdash$ac_option in --) ac_dashdash=yes ;; -bindir | --bindir | --bindi | --bind | --bin | --bi) ac_prev=bindir ;; -bindir=* | --bindir=* | --bindi=* | --bind=* | --bin=* | --bi=*) bindir=$ac_optarg ;; -build | --build | --buil | --bui | --bu) ac_prev=build_alias ;; -build=* | --build=* | --buil=* | --bui=* | --bu=*) build_alias=$ac_optarg ;; -cache-file | --cache-file | --cache-fil | --cache-fi \ | --cache-f | --cache- | --cache | --cach | --cac | --ca | --c) ac_prev=cache_file ;; -cache-file=* | --cache-file=* | --cache-fil=* | --cache-fi=* \ | --cache-f=* | --cache-=* | --cache=* | --cach=* | --cac=* | --ca=* | --c=*) cache_file=$ac_optarg ;; --config-cache | -C) cache_file=config.cache ;; -datadir | --datadir | --datadi | --datad) ac_prev=datadir ;; -datadir=* | --datadir=* | --datadi=* | --datad=*) datadir=$ac_optarg ;; -datarootdir | --datarootdir | --datarootdi | --datarootd | --dataroot \ | --dataroo | --dataro | --datar) ac_prev=datarootdir ;; -datarootdir=* | --datarootdir=* | --datarootdi=* | --datarootd=* \ | --dataroot=* | --dataroo=* | --dataro=* | --datar=*) datarootdir=$ac_optarg ;; -disable-* | --disable-*) ac_useropt=`expr "x$ac_option" : 'x-*disable-\(.*\)'` # Reject names that are not valid shell variable names. expr "x$ac_useropt" : ".*[^-+._$as_cr_alnum]" >/dev/null && as_fn_error $? "invalid feature name: $ac_useropt" ac_useropt_orig=$ac_useropt ac_useropt=`$as_echo "$ac_useropt" | sed 's/[-+.]/_/g'` case $ac_user_opts in *" "enable_$ac_useropt" "*) ;; *) ac_unrecognized_opts="$ac_unrecognized_opts$ac_unrecognized_sep--disable-$ac_useropt_orig" ac_unrecognized_sep=', ';; esac eval enable_$ac_useropt=no ;; -docdir | --docdir | --docdi | --doc | --do) ac_prev=docdir ;; -docdir=* | --docdir=* | --docdi=* | --doc=* | --do=*) docdir=$ac_optarg ;; -dvidir | --dvidir | --dvidi | --dvid | --dvi | --dv) ac_prev=dvidir ;; -dvidir=* | --dvidir=* | --dvidi=* | --dvid=* | --dvi=* | --dv=*) dvidir=$ac_optarg ;; -enable-* | --enable-*) ac_useropt=`expr "x$ac_option" : 'x-*enable-\([^=]*\)'` # Reject names that are not valid shell variable names. expr "x$ac_useropt" : ".*[^-+._$as_cr_alnum]" >/dev/null && as_fn_error $? "invalid feature name: $ac_useropt" ac_useropt_orig=$ac_useropt ac_useropt=`$as_echo "$ac_useropt" | sed 's/[-+.]/_/g'` case $ac_user_opts in *" "enable_$ac_useropt" "*) ;; *) ac_unrecognized_opts="$ac_unrecognized_opts$ac_unrecognized_sep--enable-$ac_useropt_orig" ac_unrecognized_sep=', ';; esac eval enable_$ac_useropt=\$ac_optarg ;; -exec-prefix | --exec_prefix | --exec-prefix | --exec-prefi \ | --exec-pref | --exec-pre | --exec-pr | --exec-p | --exec- \ | --exec | --exe | --ex) ac_prev=exec_prefix ;; -exec-prefix=* | --exec_prefix=* | --exec-prefix=* | --exec-prefi=* \ | --exec-pref=* | --exec-pre=* | --exec-pr=* | --exec-p=* | --exec-=* \ | --exec=* | --exe=* | --ex=*) exec_prefix=$ac_optarg ;; -gas | --gas | --ga | --g) # Obsolete; use --with-gas. with_gas=yes ;; -help | --help | --hel | --he | -h) ac_init_help=long ;; -help=r* | --help=r* | --hel=r* | --he=r* | -hr*) ac_init_help=recursive ;; -help=s* | --help=s* | --hel=s* | --he=s* | -hs*) ac_init_help=short ;; -host | --host | --hos | --ho) ac_prev=host_alias ;; -host=* | --host=* | --hos=* | --ho=*) host_alias=$ac_optarg ;; -htmldir | --htmldir | --htmldi | --htmld | --html | --htm | --ht) ac_prev=htmldir ;; -htmldir=* | --htmldir=* | --htmldi=* | --htmld=* | --html=* | --htm=* \ | --ht=*) htmldir=$ac_optarg ;; -includedir | --includedir | --includedi | --included | --include \ | --includ | --inclu | --incl | --inc) ac_prev=includedir ;; -includedir=* | --includedir=* | --includedi=* | --included=* | --include=* \ | --includ=* | --inclu=* | --incl=* | --inc=*) includedir=$ac_optarg ;; -infodir | --infodir | --infodi | --infod | --info | --inf) ac_prev=infodir ;; -infodir=* | --infodir=* | --infodi=* | --infod=* | --info=* | --inf=*) infodir=$ac_optarg ;; -libdir | --libdir | --libdi | --libd) ac_prev=libdir ;; -libdir=* | --libdir=* | --libdi=* | --libd=*) libdir=$ac_optarg ;; -libexecdir | --libexecdir | --libexecdi | --libexecd | --libexec \ | --libexe | --libex | --libe) ac_prev=libexecdir ;; -libexecdir=* | --libexecdir=* | --libexecdi=* | --libexecd=* | --libexec=* \ | --libexe=* | --libex=* | --libe=*) libexecdir=$ac_optarg ;; -localedir | --localedir | --localedi | --localed | --locale) ac_prev=localedir ;; -localedir=* | --localedir=* | --localedi=* | --localed=* | --locale=*) localedir=$ac_optarg ;; -localstatedir | --localstatedir | --localstatedi | --localstated \ | --localstate | --localstat | --localsta | --localst | --locals) ac_prev=localstatedir ;; -localstatedir=* | --localstatedir=* | --localstatedi=* | --localstated=* \ | --localstate=* | --localstat=* | --localsta=* | --localst=* | --locals=*) localstatedir=$ac_optarg ;; -mandir | --mandir | --mandi | --mand | --man | --ma | --m) ac_prev=mandir ;; -mandir=* | --mandir=* | --mandi=* | --mand=* | --man=* | --ma=* | --m=*) mandir=$ac_optarg ;; -nfp | --nfp | --nf) # Obsolete; use --without-fp. with_fp=no ;; -no-create | --no-create | --no-creat | --no-crea | --no-cre \ | --no-cr | --no-c | -n) no_create=yes ;; -no-recursion | --no-recursion | --no-recursio | --no-recursi \ | --no-recurs | --no-recur | --no-recu | --no-rec | --no-re | --no-r) no_recursion=yes ;; -oldincludedir | --oldincludedir | --oldincludedi | --oldincluded \ | --oldinclude | --oldinclud | --oldinclu | --oldincl | --oldinc \ | --oldin | --oldi | --old | --ol | --o) ac_prev=oldincludedir ;; -oldincludedir=* | --oldincludedir=* | --oldincludedi=* | --oldincluded=* \ | --oldinclude=* | --oldinclud=* | --oldinclu=* | --oldincl=* | --oldinc=* \ | --oldin=* | --oldi=* | --old=* | --ol=* | --o=*) oldincludedir=$ac_optarg ;; -prefix | --prefix | --prefi | --pref | --pre | --pr | --p) ac_prev=prefix ;; -prefix=* | --prefix=* | --prefi=* | --pref=* | --pre=* | --pr=* | --p=*) prefix=$ac_optarg ;; -program-prefix | --program-prefix | --program-prefi | --program-pref \ | --program-pre | --program-pr | --program-p) ac_prev=program_prefix ;; -program-prefix=* | --program-prefix=* | --program-prefi=* \ | --program-pref=* | --program-pre=* | --program-pr=* | --program-p=*) program_prefix=$ac_optarg ;; -program-suffix | --program-suffix | --program-suffi | --program-suff \ | --program-suf | --program-su | --program-s) ac_prev=program_suffix ;; -program-suffix=* | --program-suffix=* | --program-suffi=* \ | --program-suff=* | --program-suf=* | --program-su=* | --program-s=*) program_suffix=$ac_optarg ;; -program-transform-name | --program-transform-name \ | --program-transform-nam | --program-transform-na \ | --program-transform-n | --program-transform- \ | --program-transform | --program-transfor \ | --program-transfo | --program-transf \ | --program-trans | --program-tran \ | --progr-tra | --program-tr | --program-t) ac_prev=program_transform_name ;; -program-transform-name=* | --program-transform-name=* \ | --program-transform-nam=* | --program-transform-na=* \ | --program-transform-n=* | --program-transform-=* \ | --program-transform=* | --program-transfor=* \ | --program-transfo=* | --program-transf=* \ | --program-trans=* | --program-tran=* \ | --progr-tra=* | --program-tr=* | --program-t=*) program_transform_name=$ac_optarg ;; -pdfdir | --pdfdir | --pdfdi | --pdfd | --pdf | --pd) ac_prev=pdfdir ;; -pdfdir=* | --pdfdir=* | --pdfdi=* | --pdfd=* | --pdf=* | --pd=*) pdfdir=$ac_optarg ;; -psdir | --psdir | --psdi | --psd | --ps) ac_prev=psdir ;; -psdir=* | --psdir=* | --psdi=* | --psd=* | --ps=*) psdir=$ac_optarg ;; -q | -quiet | --quiet | --quie | --qui | --qu | --q \ | -silent | --silent | --silen | --sile | --sil) silent=yes ;; -sbindir | --sbindir | --sbindi | --sbind | --sbin | --sbi | --sb) ac_prev=sbindir ;; -sbindir=* | --sbindir=* | --sbindi=* | --sbind=* | --sbin=* \ | --sbi=* | --sb=*) sbindir=$ac_optarg ;; -sharedstatedir | --sharedstatedir | --sharedstatedi \ | --sharedstated | --sharedstate | --sharedstat | --sharedsta \ | --sharedst | --shareds | --shared | --share | --shar \ | --sha | --sh) ac_prev=sharedstatedir ;; -sharedstatedir=* | --sharedstatedir=* | --sharedstatedi=* \ | --sharedstated=* | --sharedstate=* | --sharedstat=* | --sharedsta=* \ | --sharedst=* | --shareds=* | --shared=* | --share=* | --shar=* \ | --sha=* | --sh=*) sharedstatedir=$ac_optarg ;; -site | --site | --sit) ac_prev=site ;; -site=* | --site=* | --sit=*) site=$ac_optarg ;; -srcdir | --srcdir | --srcdi | --srcd | --src | --sr) ac_prev=srcdir ;; -srcdir=* | --srcdir=* | --srcdi=* | --srcd=* | --src=* | --sr=*) srcdir=$ac_optarg ;; -sysconfdir | --sysconfdir | --sysconfdi | --sysconfd | --sysconf \ | --syscon | --sysco | --sysc | --sys | --sy) ac_prev=sysconfdir ;; -sysconfdir=* | --sysconfdir=* | --sysconfdi=* | --sysconfd=* | --sysconf=* \ | --syscon=* | --sysco=* | --sysc=* | --sys=* | --sy=*) sysconfdir=$ac_optarg ;; -target | --target | --targe | --targ | --tar | --ta | --t) ac_prev=target_alias ;; -target=* | --target=* | --targe=* | --targ=* | --tar=* | --ta=* | --t=*) target_alias=$ac_optarg ;; -v | -verbose | --verbose | --verbos | --verbo | --verb) verbose=yes ;; -version | --version | --versio | --versi | --vers | -V) ac_init_version=: ;; -with-* | --with-*) ac_useropt=`expr "x$ac_option" : 'x-*with-\([^=]*\)'` # Reject names that are not valid shell variable names. expr "x$ac_useropt" : ".*[^-+._$as_cr_alnum]" >/dev/null && as_fn_error $? "invalid package name: $ac_useropt" ac_useropt_orig=$ac_useropt ac_useropt=`$as_echo "$ac_useropt" | sed 's/[-+.]/_/g'` case $ac_user_opts in *" "with_$ac_useropt" "*) ;; *) ac_unrecognized_opts="$ac_unrecognized_opts$ac_unrecognized_sep--with-$ac_useropt_orig" ac_unrecognized_sep=', ';; esac eval with_$ac_useropt=\$ac_optarg ;; -without-* | --without-*) ac_useropt=`expr "x$ac_option" : 'x-*without-\(.*\)'` # Reject names that are not valid shell variable names. expr "x$ac_useropt" : ".*[^-+._$as_cr_alnum]" >/dev/null && as_fn_error $? "invalid package name: $ac_useropt" ac_useropt_orig=$ac_useropt ac_useropt=`$as_echo "$ac_useropt" | sed 's/[-+.]/_/g'` case $ac_user_opts in *" "with_$ac_useropt" "*) ;; *) ac_unrecognized_opts="$ac_unrecognized_opts$ac_unrecognized_sep--without-$ac_useropt_orig" ac_unrecognized_sep=', ';; esac eval with_$ac_useropt=no ;; --x) # Obsolete; use --with-x. with_x=yes ;; -x-includes | --x-includes | --x-include | --x-includ | --x-inclu \ | --x-incl | --x-inc | --x-in | --x-i) ac_prev=x_includes ;; -x-includes=* | --x-includes=* | --x-include=* | --x-includ=* | --x-inclu=* \ | --x-incl=* | --x-inc=* | --x-in=* | --x-i=*) x_includes=$ac_optarg ;; -x-libraries | --x-libraries | --x-librarie | --x-librari \ | --x-librar | --x-libra | --x-libr | --x-lib | --x-li | --x-l) ac_prev=x_libraries ;; -x-libraries=* | --x-libraries=* | --x-librarie=* | --x-librari=* \ | --x-librar=* | --x-libra=* | --x-libr=* | --x-lib=* | --x-li=* | --x-l=*) x_libraries=$ac_optarg ;; -*) as_fn_error $? "unrecognized option: \`$ac_option' Try \`$0 --help' for more information" ;; *=*) ac_envvar=`expr "x$ac_option" : 'x\([^=]*\)='` # Reject names that are not valid shell variable names. case $ac_envvar in #( '' | [0-9]* | *[!_$as_cr_alnum]* ) as_fn_error $? "invalid variable name: \`$ac_envvar'" ;; esac eval $ac_envvar=\$ac_optarg export $ac_envvar ;; *) # FIXME: should be removed in autoconf 3.0. $as_echo "$as_me: WARNING: you should use --build, --host, --target" >&2 expr "x$ac_option" : ".*[^-._$as_cr_alnum]" >/dev/null && $as_echo "$as_me: WARNING: invalid host type: $ac_option" >&2 : "${build_alias=$ac_option} ${host_alias=$ac_option} ${target_alias=$ac_option}" ;; esac done if test -n "$ac_prev"; then ac_option=--`echo $ac_prev | sed 's/_/-/g'` as_fn_error $? "missing argument to $ac_option" fi if test -n "$ac_unrecognized_opts"; then case $enable_option_checking in no) ;; fatal) as_fn_error $? "unrecognized options: $ac_unrecognized_opts" ;; *) $as_echo "$as_me: WARNING: unrecognized options: $ac_unrecognized_opts" >&2 ;; esac fi # Check all directory arguments for consistency. for ac_var in exec_prefix prefix bindir sbindir libexecdir datarootdir \ datadir sysconfdir sharedstatedir localstatedir includedir \ oldincludedir docdir infodir htmldir dvidir pdfdir psdir \ libdir localedir mandir do eval ac_val=\$$ac_var # Remove trailing slashes. case $ac_val in */ ) ac_val=`expr "X$ac_val" : 'X\(.*[^/]\)' \| "X$ac_val" : 'X\(.*\)'` eval $ac_var=\$ac_val;; esac # Be sure to have absolute directory names. case $ac_val in [\\/$]* | ?:[\\/]* ) continue;; NONE | '' ) case $ac_var in *prefix ) continue;; esac;; esac as_fn_error $? "expected an absolute directory name for --$ac_var: $ac_val" done # There might be people who depend on the old broken behavior: `$host' # used to hold the argument of --host etc. # FIXME: To remove some day. build=$build_alias host=$host_alias target=$target_alias # FIXME: To remove some day. if test "x$host_alias" != x; then if test "x$build_alias" = x; then cross_compiling=maybe elif test "x$build_alias" != "x$host_alias"; then cross_compiling=yes fi fi ac_tool_prefix= test -n "$host_alias" && ac_tool_prefix=$host_alias- test "$silent" = yes && exec 6>/dev/null ac_pwd=`pwd` && test -n "$ac_pwd" && ac_ls_di=`ls -di .` && ac_pwd_ls_di=`cd "$ac_pwd" && ls -di .` || as_fn_error $? "working directory cannot be determined" test "X$ac_ls_di" = "X$ac_pwd_ls_di" || as_fn_error $? "pwd does not report name of working directory" # Find the source files, if location was not specified. if test -z "$srcdir"; then ac_srcdir_defaulted=yes # Try the directory containing this script, then the parent directory. ac_confdir=`$as_dirname -- "$as_myself" || $as_expr X"$as_myself" : 'X\(.*[^/]\)//*[^/][^/]*/*$' \| \ X"$as_myself" : 'X\(//\)[^/]' \| \ X"$as_myself" : 'X\(//\)$' \| \ X"$as_myself" : 'X\(/\)' \| . 2>/dev/null || $as_echo X"$as_myself" | sed '/^X\(.*[^/]\)\/\/*[^/][^/]*\/*$/{ s//\1/ q } /^X\(\/\/\)[^/].*/{ s//\1/ q } /^X\(\/\/\)$/{ s//\1/ q } /^X\(\/\).*/{ s//\1/ q } s/.*/./; q'` srcdir=$ac_confdir if test ! -r "$srcdir/$ac_unique_file"; then srcdir=.. fi else ac_srcdir_defaulted=no fi if test ! -r "$srcdir/$ac_unique_file"; then test "$ac_srcdir_defaulted" = yes && srcdir="$ac_confdir or .." as_fn_error $? "cannot find sources ($ac_unique_file) in $srcdir" fi ac_msg="sources are in $srcdir, but \`cd $srcdir' does not work" ac_abs_confdir=`( cd "$srcdir" && test -r "./$ac_unique_file" || as_fn_error $? "$ac_msg" pwd)` # When building in place, set srcdir=. if test "$ac_abs_confdir" = "$ac_pwd"; then srcdir=. fi # Remove unnecessary trailing slashes from srcdir. # Double slashes in file names in object file debugging info # mess up M-x gdb in Emacs. case $srcdir in */) srcdir=`expr "X$srcdir" : 'X\(.*[^/]\)' \| "X$srcdir" : 'X\(.*\)'`;; esac for ac_var in $ac_precious_vars; do eval ac_env_${ac_var}_set=\${${ac_var}+set} eval ac_env_${ac_var}_value=\$${ac_var} eval ac_cv_env_${ac_var}_set=\${${ac_var}+set} eval ac_cv_env_${ac_var}_value=\$${ac_var} done # # Report the --help message. # if test "$ac_init_help" = "long"; then # Omit some internal or obsolete options to make the list less imposing. # This message is too long to be a string in the A/UX 3.1 sh. cat <<_ACEOF \`configure' configures this package to adapt to many kinds of systems. Usage: $0 [OPTION]... [VAR=VALUE]... To assign environment variables (e.g., CC, CFLAGS...), specify them as VAR=VALUE. See below for descriptions of some of the useful variables. Defaults for the options are specified in brackets. Configuration: -h, --help display this help and exit --help=short display options specific to this package --help=recursive display the short help of all the included packages -V, --version display version information and exit -q, --quiet, --silent do not print \`checking ...' messages --cache-file=FILE cache test results in FILE [disabled] -C, --config-cache alias for \`--cache-file=config.cache' -n, --no-create do not create output files --srcdir=DIR find the sources in DIR [configure dir or \`..'] Installation directories: --prefix=PREFIX install architecture-independent files in PREFIX [$ac_default_prefix] --exec-prefix=EPREFIX install architecture-dependent files in EPREFIX [PREFIX] By default, \`make install' will install all the files in \`$ac_default_prefix/bin', \`$ac_default_prefix/lib' etc. You can specify an installation prefix other than \`$ac_default_prefix' using \`--prefix', for instance \`--prefix=\$HOME'. For better control, use the options below. Fine tuning of the installation directories: --bindir=DIR user executables [EPREFIX/bin] --sbindir=DIR system admin executables [EPREFIX/sbin] --libexecdir=DIR program executables [EPREFIX/libexec] --sysconfdir=DIR read-only single-machine data [PREFIX/etc] --sharedstatedir=DIR modifiable architecture-independent data [PREFIX/com] --localstatedir=DIR modifiable single-machine data [PREFIX/var] --libdir=DIR object code libraries [EPREFIX/lib] --includedir=DIR C header files [PREFIX/include] --oldincludedir=DIR C header files for non-gcc [/usr/include] --datarootdir=DIR read-only arch.-independent data root [PREFIX/share] --datadir=DIR read-only architecture-independent data [DATAROOTDIR] --infodir=DIR info documentation [DATAROOTDIR/info] --localedir=DIR locale-dependent data [DATAROOTDIR/locale] --mandir=DIR man documentation [DATAROOTDIR/man] --docdir=DIR documentation root [DATAROOTDIR/doc/PACKAGE] --htmldir=DIR html documentation [DOCDIR] --dvidir=DIR dvi documentation [DOCDIR] --pdfdir=DIR pdf documentation [DOCDIR] --psdir=DIR ps documentation [DOCDIR] _ACEOF cat <<\_ACEOF Program names: --program-prefix=PREFIX prepend PREFIX to installed program names --program-suffix=SUFFIX append SUFFIX to installed program names --program-transform-name=PROGRAM run sed PROGRAM on installed program names System types: --build=BUILD configure for building on BUILD [guessed] --host=HOST cross-compile to build programs to run on HOST [BUILD] _ACEOF fi if test -n "$ac_init_help"; then cat <<\_ACEOF Optional Features: --disable-option-checking ignore unrecognized --enable/--with options --disable-FEATURE do not include FEATURE (same as --enable-FEATURE=no) --enable-FEATURE[=ARG] include FEATURE [ARG=yes] --disable-dependency-tracking speeds up one-time build --enable-dependency-tracking do not reject slow dependency extractors --enable-shared[=PKGS] build shared libraries [default=yes] --enable-static[=PKGS] build static libraries [default=yes] --enable-fast-install[=PKGS] optimize for fast installation [default=yes] --disable-libtool-lock avoid locking (might break parallel builds) --enable-relocatable install a package that can be moved in the filesystem Optional Packages: --with-PACKAGE[=ARG] use PACKAGE [ARG=yes] --without-PACKAGE do not use PACKAGE (same as --with-PACKAGE=no) --with-pic[=PKGS] try to use only PIC/non-PIC objects [default=use both] --with-gnu-ld assume the C compiler uses GNU ld [default=no] --with-sysroot=DIR Search for dependent libraries within DIR (or the compiler's sysroot if not specified). Some influential environment variables: CC C compiler command CFLAGS C compiler flags LDFLAGS linker flags, e.g. -L if you have libraries in a nonstandard directory LIBS libraries to pass to the linker, e.g. -l CPPFLAGS (Objective) C/C++ preprocessor flags, e.g. -I if you have headers in a nonstandard directory CPP C preprocessor Use these variables to override the choices made by `configure' or to help it to find libraries and programs with nonstandard names/locations. Report bugs to the package provider. _ACEOF ac_status=$? fi if test "$ac_init_help" = "recursive"; then # If there are subdirs, report their specific --help. for ac_dir in : $ac_subdirs_all; do test "x$ac_dir" = x: && continue test -d "$ac_dir" || { cd "$srcdir" && ac_pwd=`pwd` && srcdir=. && test -d "$ac_dir"; } || continue ac_builddir=. case "$ac_dir" in .) ac_dir_suffix= ac_top_builddir_sub=. ac_top_build_prefix= ;; *) ac_dir_suffix=/`$as_echo "$ac_dir" | sed 's|^\.[\\/]||'` # A ".." for each directory in $ac_dir_suffix. ac_top_builddir_sub=`$as_echo "$ac_dir_suffix" | sed 's|/[^\\/]*|/..|g;s|/||'` case $ac_top_builddir_sub in "") ac_top_builddir_sub=. ac_top_build_prefix= ;; *) ac_top_build_prefix=$ac_top_builddir_sub/ ;; esac ;; esac ac_abs_top_builddir=$ac_pwd ac_abs_builddir=$ac_pwd$ac_dir_suffix # for backward compatibility: ac_top_builddir=$ac_top_build_prefix case $srcdir in .) # We are building in place. ac_srcdir=. ac_top_srcdir=$ac_top_builddir_sub ac_abs_top_srcdir=$ac_pwd ;; [\\/]* | ?:[\\/]* ) # Absolute name. ac_srcdir=$srcdir$ac_dir_suffix; ac_top_srcdir=$srcdir ac_abs_top_srcdir=$srcdir ;; *) # Relative name. ac_srcdir=$ac_top_build_prefix$srcdir$ac_dir_suffix ac_top_srcdir=$ac_top_build_prefix$srcdir ac_abs_top_srcdir=$ac_pwd/$srcdir ;; esac ac_abs_srcdir=$ac_abs_top_srcdir$ac_dir_suffix cd "$ac_dir" || { ac_status=$?; continue; } # Check for guested configure. if test -f "$ac_srcdir/configure.gnu"; then echo && $SHELL "$ac_srcdir/configure.gnu" --help=recursive elif test -f "$ac_srcdir/configure"; then echo && $SHELL "$ac_srcdir/configure" --help=recursive else $as_echo "$as_me: WARNING: no configuration information is in $ac_dir" >&2 fi || ac_status=$? cd "$ac_pwd" || { ac_status=$?; break; } done fi test -n "$ac_init_help" && exit $ac_status if $ac_init_version; then cat <<\_ACEOF configure generated by GNU Autoconf 2.69 Copyright (C) 2012 Free Software Foundation, Inc. This configure script is free software; the Free Software Foundation gives unlimited permission to copy, distribute and modify it. _ACEOF exit fi ## ------------------------ ## ## Autoconf initialization. ## ## ------------------------ ## # ac_fn_c_try_compile LINENO # -------------------------- # Try to compile conftest.$ac_ext, and return whether this succeeded. ac_fn_c_try_compile () { as_lineno=${as_lineno-"$1"} as_lineno_stack=as_lineno_stack=$as_lineno_stack rm -f conftest.$ac_objext if { { ac_try="$ac_compile" case "(($ac_try" in *\"* | *\`* | *\\*) ac_try_echo=\$ac_try;; *) ac_try_echo=$ac_try;; esac eval ac_try_echo="\"\$as_me:${as_lineno-$LINENO}: $ac_try_echo\"" $as_echo "$ac_try_echo"; } >&5 (eval "$ac_compile") 2>conftest.err ac_status=$? if test -s conftest.err; then grep -v '^ *+' conftest.err >conftest.er1 cat conftest.er1 >&5 mv -f conftest.er1 conftest.err fi $as_echo "$as_me:${as_lineno-$LINENO}: \$? = $ac_status" >&5 test $ac_status = 0; } && { test -z "$ac_c_werror_flag" || test ! -s conftest.err } && test -s conftest.$ac_objext; then : ac_retval=0 else $as_echo "$as_me: failed program was:" >&5 sed 's/^/| /' conftest.$ac_ext >&5 ac_retval=1 fi eval $as_lineno_stack; ${as_lineno_stack:+:} unset as_lineno as_fn_set_status $ac_retval } # ac_fn_c_try_compile # ac_fn_c_try_cpp LINENO # ---------------------- # Try to preprocess conftest.$ac_ext, and return whether this succeeded. ac_fn_c_try_cpp () { as_lineno=${as_lineno-"$1"} as_lineno_stack=as_lineno_stack=$as_lineno_stack if { { ac_try="$ac_cpp conftest.$ac_ext" case "(($ac_try" in *\"* | *\`* | *\\*) ac_try_echo=\$ac_try;; *) ac_try_echo=$ac_try;; esac eval ac_try_echo="\"\$as_me:${as_lineno-$LINENO}: $ac_try_echo\"" $as_echo "$ac_try_echo"; } >&5 (eval "$ac_cpp conftest.$ac_ext") 2>conftest.err ac_status=$? if test -s conftest.err; then grep -v '^ *+' conftest.err >conftest.er1 cat conftest.er1 >&5 mv -f conftest.er1 conftest.err fi $as_echo "$as_me:${as_lineno-$LINENO}: \$? = $ac_status" >&5 test $ac_status = 0; } > conftest.i && { test -z "$ac_c_preproc_warn_flag$ac_c_werror_flag" || test ! -s conftest.err }; then : ac_retval=0 else $as_echo "$as_me: failed program was:" >&5 sed 's/^/| /' conftest.$ac_ext >&5 ac_retval=1 fi eval $as_lineno_stack; ${as_lineno_stack:+:} unset as_lineno as_fn_set_status $ac_retval } # ac_fn_c_try_cpp # ac_fn_c_try_link LINENO # ----------------------- # Try to link conftest.$ac_ext, and return whether this succeeded. ac_fn_c_try_link () { as_lineno=${as_lineno-"$1"} as_lineno_stack=as_lineno_stack=$as_lineno_stack rm -f conftest.$ac_objext conftest$ac_exeext if { { ac_try="$ac_link" case "(($ac_try" in *\"* | *\`* | *\\*) ac_try_echo=\$ac_try;; *) ac_try_echo=$ac_try;; esac eval ac_try_echo="\"\$as_me:${as_lineno-$LINENO}: $ac_try_echo\"" $as_echo "$ac_try_echo"; } >&5 (eval "$ac_link") 2>conftest.err ac_status=$? if test -s conftest.err; then grep -v '^ *+' conftest.err >conftest.er1 cat conftest.er1 >&5 mv -f conftest.er1 conftest.err fi $as_echo "$as_me:${as_lineno-$LINENO}: \$? = $ac_status" >&5 test $ac_status = 0; } && { test -z "$ac_c_werror_flag" || test ! -s conftest.err } && test -s conftest$ac_exeext && { test "$cross_compiling" = yes || test -x conftest$ac_exeext }; then : ac_retval=0 else $as_echo "$as_me: failed program was:" >&5 sed 's/^/| /' conftest.$ac_ext >&5 ac_retval=1 fi # Delete the IPA/IPO (Inter Procedural Analysis/Optimization) information # created by the PGI compiler (conftest_ipa8_conftest.oo), as it would # interfere with the next link command; also delete a directory that is # left behind by Apple's compiler. We do this before executing the actions. rm -rf conftest.dSYM conftest_ipa8_conftest.oo eval $as_lineno_stack; ${as_lineno_stack:+:} unset as_lineno as_fn_set_status $ac_retval } # ac_fn_c_try_link # ac_fn_c_check_header_compile LINENO HEADER VAR INCLUDES # ------------------------------------------------------- # Tests whether HEADER exists and can be compiled using the include files in # INCLUDES, setting the cache variable VAR accordingly. ac_fn_c_check_header_compile () { as_lineno=${as_lineno-"$1"} as_lineno_stack=as_lineno_stack=$as_lineno_stack { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $2" >&5 $as_echo_n "checking for $2... " >&6; } if eval \${$3+:} false; then : $as_echo_n "(cached) " >&6 else cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ $4 #include <$2> _ACEOF if ac_fn_c_try_compile "$LINENO"; then : eval "$3=yes" else eval "$3=no" fi rm -f core conftest.err conftest.$ac_objext conftest.$ac_ext fi eval ac_res=\$$3 { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_res" >&5 $as_echo "$ac_res" >&6; } eval $as_lineno_stack; ${as_lineno_stack:+:} unset as_lineno } # ac_fn_c_check_header_compile # ac_fn_c_try_run LINENO # ---------------------- # Try to link conftest.$ac_ext, and return whether this succeeded. Assumes # that executables *can* be run. ac_fn_c_try_run () { as_lineno=${as_lineno-"$1"} as_lineno_stack=as_lineno_stack=$as_lineno_stack if { { ac_try="$ac_link" case "(($ac_try" in *\"* | *\`* | *\\*) ac_try_echo=\$ac_try;; *) ac_try_echo=$ac_try;; esac eval ac_try_echo="\"\$as_me:${as_lineno-$LINENO}: $ac_try_echo\"" $as_echo "$ac_try_echo"; } >&5 (eval "$ac_link") 2>&5 ac_status=$? $as_echo "$as_me:${as_lineno-$LINENO}: \$? = $ac_status" >&5 test $ac_status = 0; } && { ac_try='./conftest$ac_exeext' { { case "(($ac_try" in *\"* | *\`* | *\\*) ac_try_echo=\$ac_try;; *) ac_try_echo=$ac_try;; esac eval ac_try_echo="\"\$as_me:${as_lineno-$LINENO}: $ac_try_echo\"" $as_echo "$ac_try_echo"; } >&5 (eval "$ac_try") 2>&5 ac_status=$? $as_echo "$as_me:${as_lineno-$LINENO}: \$? = $ac_status" >&5 test $ac_status = 0; }; }; then : ac_retval=0 else $as_echo "$as_me: program exited with status $ac_status" >&5 $as_echo "$as_me: failed program was:" >&5 sed 's/^/| /' conftest.$ac_ext >&5 ac_retval=$ac_status fi rm -rf conftest.dSYM conftest_ipa8_conftest.oo eval $as_lineno_stack; ${as_lineno_stack:+:} unset as_lineno as_fn_set_status $ac_retval } # ac_fn_c_try_run # ac_fn_c_check_func LINENO FUNC VAR # ---------------------------------- # Tests whether FUNC exists, setting the cache variable VAR accordingly ac_fn_c_check_func () { as_lineno=${as_lineno-"$1"} as_lineno_stack=as_lineno_stack=$as_lineno_stack { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $2" >&5 $as_echo_n "checking for $2... " >&6; } if eval \${$3+:} false; then : $as_echo_n "(cached) " >&6 else cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ /* Define $2 to an innocuous variant, in case declares $2. For example, HP-UX 11i declares gettimeofday. */ #define $2 innocuous_$2 /* System header to define __stub macros and hopefully few prototypes, which can conflict with char $2 (); below. Prefer to if __STDC__ is defined, since exists even on freestanding compilers. */ #ifdef __STDC__ # include #else # include #endif #undef $2 /* Override any GCC internal prototype to avoid an error. Use char because int might match the return type of a GCC builtin and then its argument prototype would still apply. */ #ifdef __cplusplus extern "C" #endif char $2 (); /* The GNU C library defines this for functions which it implements to always fail with ENOSYS. Some functions are actually named something starting with __ and the normal name is an alias. */ #if defined __stub_$2 || defined __stub___$2 choke me #endif int main () { return $2 (); ; return 0; } _ACEOF if ac_fn_c_try_link "$LINENO"; then : eval "$3=yes" else eval "$3=no" fi rm -f core conftest.err conftest.$ac_objext \ conftest$ac_exeext conftest.$ac_ext fi eval ac_res=\$$3 { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_res" >&5 $as_echo "$ac_res" >&6; } eval $as_lineno_stack; ${as_lineno_stack:+:} unset as_lineno } # ac_fn_c_check_func # ac_fn_c_check_header_mongrel LINENO HEADER VAR INCLUDES # ------------------------------------------------------- # Tests whether HEADER exists, giving a warning if it cannot be compiled using # the include files in INCLUDES and setting the cache variable VAR # accordingly. ac_fn_c_check_header_mongrel () { as_lineno=${as_lineno-"$1"} as_lineno_stack=as_lineno_stack=$as_lineno_stack if eval \${$3+:} false; then : { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $2" >&5 $as_echo_n "checking for $2... " >&6; } if eval \${$3+:} false; then : $as_echo_n "(cached) " >&6 fi eval ac_res=\$$3 { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_res" >&5 $as_echo "$ac_res" >&6; } else # Is the header compilable? { $as_echo "$as_me:${as_lineno-$LINENO}: checking $2 usability" >&5 $as_echo_n "checking $2 usability... " >&6; } cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ $4 #include <$2> _ACEOF if ac_fn_c_try_compile "$LINENO"; then : ac_header_compiler=yes else ac_header_compiler=no fi rm -f core conftest.err conftest.$ac_objext conftest.$ac_ext { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_header_compiler" >&5 $as_echo "$ac_header_compiler" >&6; } # Is the header present? { $as_echo "$as_me:${as_lineno-$LINENO}: checking $2 presence" >&5 $as_echo_n "checking $2 presence... " >&6; } cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ #include <$2> _ACEOF if ac_fn_c_try_cpp "$LINENO"; then : ac_header_preproc=yes else ac_header_preproc=no fi rm -f conftest.err conftest.i conftest.$ac_ext { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_header_preproc" >&5 $as_echo "$ac_header_preproc" >&6; } # So? What about this header? case $ac_header_compiler:$ac_header_preproc:$ac_c_preproc_warn_flag in #(( yes:no: ) { $as_echo "$as_me:${as_lineno-$LINENO}: WARNING: $2: accepted by the compiler, rejected by the preprocessor!" >&5 $as_echo "$as_me: WARNING: $2: accepted by the compiler, rejected by the preprocessor!" >&2;} { $as_echo "$as_me:${as_lineno-$LINENO}: WARNING: $2: proceeding with the compiler's result" >&5 $as_echo "$as_me: WARNING: $2: proceeding with the compiler's result" >&2;} ;; no:yes:* ) { $as_echo "$as_me:${as_lineno-$LINENO}: WARNING: $2: present but cannot be compiled" >&5 $as_echo "$as_me: WARNING: $2: present but cannot be compiled" >&2;} { $as_echo "$as_me:${as_lineno-$LINENO}: WARNING: $2: check for missing prerequisite headers?" >&5 $as_echo "$as_me: WARNING: $2: check for missing prerequisite headers?" >&2;} { $as_echo "$as_me:${as_lineno-$LINENO}: WARNING: $2: see the Autoconf documentation" >&5 $as_echo "$as_me: WARNING: $2: see the Autoconf documentation" >&2;} { $as_echo "$as_me:${as_lineno-$LINENO}: WARNING: $2: section \"Present But Cannot Be Compiled\"" >&5 $as_echo "$as_me: WARNING: $2: section \"Present But Cannot Be Compiled\"" >&2;} { $as_echo "$as_me:${as_lineno-$LINENO}: WARNING: $2: proceeding with the compiler's result" >&5 $as_echo "$as_me: WARNING: $2: proceeding with the compiler's result" >&2;} ;; esac { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $2" >&5 $as_echo_n "checking for $2... " >&6; } if eval \${$3+:} false; then : $as_echo_n "(cached) " >&6 else eval "$3=\$ac_header_compiler" fi eval ac_res=\$$3 { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_res" >&5 $as_echo "$ac_res" >&6; } fi eval $as_lineno_stack; ${as_lineno_stack:+:} unset as_lineno } # ac_fn_c_check_header_mongrel # ac_fn_c_check_type LINENO TYPE VAR INCLUDES # ------------------------------------------- # Tests whether TYPE exists after having included INCLUDES, setting cache # variable VAR accordingly. ac_fn_c_check_type () { as_lineno=${as_lineno-"$1"} as_lineno_stack=as_lineno_stack=$as_lineno_stack { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $2" >&5 $as_echo_n "checking for $2... " >&6; } if eval \${$3+:} false; then : $as_echo_n "(cached) " >&6 else eval "$3=no" cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ $4 int main () { if (sizeof ($2)) return 0; ; return 0; } _ACEOF if ac_fn_c_try_compile "$LINENO"; then : cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ $4 int main () { if (sizeof (($2))) return 0; ; return 0; } _ACEOF if ac_fn_c_try_compile "$LINENO"; then : else eval "$3=yes" fi rm -f core conftest.err conftest.$ac_objext conftest.$ac_ext fi rm -f core conftest.err conftest.$ac_objext conftest.$ac_ext fi eval ac_res=\$$3 { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_res" >&5 $as_echo "$ac_res" >&6; } eval $as_lineno_stack; ${as_lineno_stack:+:} unset as_lineno } # ac_fn_c_check_type cat >config.log <<_ACEOF This file contains any messages produced by compilers while running configure, to aid debugging if configure makes a mistake. It was created by $as_me, which was generated by GNU Autoconf 2.69. Invocation command line was $ $0 $@ _ACEOF exec 5>>config.log { cat <<_ASUNAME ## --------- ## ## Platform. ## ## --------- ## hostname = `(hostname || uname -n) 2>/dev/null | sed 1q` uname -m = `(uname -m) 2>/dev/null || echo unknown` uname -r = `(uname -r) 2>/dev/null || echo unknown` uname -s = `(uname -s) 2>/dev/null || echo unknown` uname -v = `(uname -v) 2>/dev/null || echo unknown` /usr/bin/uname -p = `(/usr/bin/uname -p) 2>/dev/null || echo unknown` /bin/uname -X = `(/bin/uname -X) 2>/dev/null || echo unknown` /bin/arch = `(/bin/arch) 2>/dev/null || echo unknown` /usr/bin/arch -k = `(/usr/bin/arch -k) 2>/dev/null || echo unknown` /usr/convex/getsysinfo = `(/usr/convex/getsysinfo) 2>/dev/null || echo unknown` /usr/bin/hostinfo = `(/usr/bin/hostinfo) 2>/dev/null || echo unknown` /bin/machine = `(/bin/machine) 2>/dev/null || echo unknown` /usr/bin/oslevel = `(/usr/bin/oslevel) 2>/dev/null || echo unknown` /bin/universe = `(/bin/universe) 2>/dev/null || echo unknown` _ASUNAME as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. $as_echo "PATH: $as_dir" done IFS=$as_save_IFS } >&5 cat >&5 <<_ACEOF ## ----------- ## ## Core tests. ## ## ----------- ## _ACEOF # Keep a trace of the command line. # Strip out --no-create and --no-recursion so they do not pile up. # Strip out --silent because we don't want to record it for future runs. # Also quote any args containing shell meta-characters. # Make two passes to allow for proper duplicate-argument suppression. ac_configure_args= ac_configure_args0= ac_configure_args1= ac_must_keep_next=false for ac_pass in 1 2 do for ac_arg do case $ac_arg in -no-create | --no-c* | -n | -no-recursion | --no-r*) continue ;; -q | -quiet | --quiet | --quie | --qui | --qu | --q \ | -silent | --silent | --silen | --sile | --sil) continue ;; *\'*) ac_arg=`$as_echo "$ac_arg" | sed "s/'/'\\\\\\\\''/g"` ;; esac case $ac_pass in 1) as_fn_append ac_configure_args0 " '$ac_arg'" ;; 2) as_fn_append ac_configure_args1 " '$ac_arg'" if test $ac_must_keep_next = true; then ac_must_keep_next=false # Got value, back to normal. else case $ac_arg in *=* | --config-cache | -C | -disable-* | --disable-* \ | -enable-* | --enable-* | -gas | --g* | -nfp | --nf* \ | -q | -quiet | --q* | -silent | --sil* | -v | -verb* \ | -with-* | --with-* | -without-* | --without-* | --x) case "$ac_configure_args0 " in "$ac_configure_args1"*" '$ac_arg' "* ) continue ;; esac ;; -* ) ac_must_keep_next=true ;; esac fi as_fn_append ac_configure_args " '$ac_arg'" ;; esac done done { ac_configure_args0=; unset ac_configure_args0;} { ac_configure_args1=; unset ac_configure_args1;} # When interrupted or exit'd, cleanup temporary files, and complete # config.log. We remove comments because anyway the quotes in there # would cause problems or look ugly. # WARNING: Use '\'' to represent an apostrophe within the trap. # WARNING: Do not start the trap code with a newline, due to a FreeBSD 4.0 bug. trap 'exit_status=$? # Save into config.log some information that might help in debugging. { echo $as_echo "## ---------------- ## ## Cache variables. ## ## ---------------- ##" echo # The following way of writing the cache mishandles newlines in values, ( for ac_var in `(set) 2>&1 | sed -n '\''s/^\([a-zA-Z_][a-zA-Z0-9_]*\)=.*/\1/p'\''`; do eval ac_val=\$$ac_var case $ac_val in #( *${as_nl}*) case $ac_var in #( *_cv_*) { $as_echo "$as_me:${as_lineno-$LINENO}: WARNING: cache variable $ac_var contains a newline" >&5 $as_echo "$as_me: WARNING: cache variable $ac_var contains a newline" >&2;} ;; esac case $ac_var in #( _ | IFS | as_nl) ;; #( BASH_ARGV | BASH_SOURCE) eval $ac_var= ;; #( *) { eval $ac_var=; unset $ac_var;} ;; esac ;; esac done (set) 2>&1 | case $as_nl`(ac_space='\'' '\''; set) 2>&1` in #( *${as_nl}ac_space=\ *) sed -n \ "s/'\''/'\''\\\\'\'''\''/g; s/^\\([_$as_cr_alnum]*_cv_[_$as_cr_alnum]*\\)=\\(.*\\)/\\1='\''\\2'\''/p" ;; #( *) sed -n "/^[_$as_cr_alnum]*_cv_[_$as_cr_alnum]*=/p" ;; esac | sort ) echo $as_echo "## ----------------- ## ## Output variables. ## ## ----------------- ##" echo for ac_var in $ac_subst_vars do eval ac_val=\$$ac_var case $ac_val in *\'\''*) ac_val=`$as_echo "$ac_val" | sed "s/'\''/'\''\\\\\\\\'\'''\''/g"`;; esac $as_echo "$ac_var='\''$ac_val'\''" done | sort echo if test -n "$ac_subst_files"; then $as_echo "## ------------------- ## ## File substitutions. ## ## ------------------- ##" echo for ac_var in $ac_subst_files do eval ac_val=\$$ac_var case $ac_val in *\'\''*) ac_val=`$as_echo "$ac_val" | sed "s/'\''/'\''\\\\\\\\'\'''\''/g"`;; esac $as_echo "$ac_var='\''$ac_val'\''" done | sort echo fi if test -s confdefs.h; then $as_echo "## ----------- ## ## confdefs.h. ## ## ----------- ##" echo cat confdefs.h echo fi test "$ac_signal" != 0 && $as_echo "$as_me: caught signal $ac_signal" $as_echo "$as_me: exit $exit_status" } >&5 rm -f core *.core core.conftest.* && rm -f -r conftest* confdefs* conf$$* $ac_clean_files && exit $exit_status ' 0 for ac_signal in 1 2 13 15; do trap 'ac_signal='$ac_signal'; as_fn_exit 1' $ac_signal done ac_signal=0 # confdefs.h avoids OS command line length limits that DEFS can exceed. rm -f -r conftest* confdefs.h $as_echo "/* confdefs.h */" > confdefs.h # Predefined preprocessor variables. cat >>confdefs.h <<_ACEOF #define PACKAGE_NAME "$PACKAGE_NAME" _ACEOF cat >>confdefs.h <<_ACEOF #define PACKAGE_TARNAME "$PACKAGE_TARNAME" _ACEOF cat >>confdefs.h <<_ACEOF #define PACKAGE_VERSION "$PACKAGE_VERSION" _ACEOF cat >>confdefs.h <<_ACEOF #define PACKAGE_STRING "$PACKAGE_STRING" _ACEOF cat >>confdefs.h <<_ACEOF #define PACKAGE_BUGREPORT "$PACKAGE_BUGREPORT" _ACEOF cat >>confdefs.h <<_ACEOF #define PACKAGE_URL "$PACKAGE_URL" _ACEOF # Let the site file select an alternate cache file if it wants to. # Prefer an explicitly selected file to automatically selected ones. ac_site_file1=NONE ac_site_file2=NONE if test -n "$CONFIG_SITE"; then # We do not want a PATH search for config.site. case $CONFIG_SITE in #(( -*) ac_site_file1=./$CONFIG_SITE;; */*) ac_site_file1=$CONFIG_SITE;; *) ac_site_file1=./$CONFIG_SITE;; esac elif test "x$prefix" != xNONE; then ac_site_file1=$prefix/share/config.site ac_site_file2=$prefix/etc/config.site else ac_site_file1=$ac_default_prefix/share/config.site ac_site_file2=$ac_default_prefix/etc/config.site fi for ac_site_file in "$ac_site_file1" "$ac_site_file2" do test "x$ac_site_file" = xNONE && continue if test /dev/null != "$ac_site_file" && test -r "$ac_site_file"; then { $as_echo "$as_me:${as_lineno-$LINENO}: loading site script $ac_site_file" >&5 $as_echo "$as_me: loading site script $ac_site_file" >&6;} sed 's/^/| /' "$ac_site_file" >&5 . "$ac_site_file" \ || { { $as_echo "$as_me:${as_lineno-$LINENO}: error: in \`$ac_pwd':" >&5 $as_echo "$as_me: error: in \`$ac_pwd':" >&2;} as_fn_error $? "failed to load site script $ac_site_file See \`config.log' for more details" "$LINENO" 5; } fi done if test -r "$cache_file"; then # Some versions of bash will fail to source /dev/null (special files # actually), so we avoid doing that. DJGPP emulates it as a regular file. if test /dev/null != "$cache_file" && test -f "$cache_file"; then { $as_echo "$as_me:${as_lineno-$LINENO}: loading cache $cache_file" >&5 $as_echo "$as_me: loading cache $cache_file" >&6;} case $cache_file in [\\/]* | ?:[\\/]* ) . "$cache_file";; *) . "./$cache_file";; esac fi else { $as_echo "$as_me:${as_lineno-$LINENO}: creating cache $cache_file" >&5 $as_echo "$as_me: creating cache $cache_file" >&6;} >$cache_file fi # Check that the precious variables saved in the cache have kept the same # value. ac_cache_corrupted=false for ac_var in $ac_precious_vars; do eval ac_old_set=\$ac_cv_env_${ac_var}_set eval ac_new_set=\$ac_env_${ac_var}_set eval ac_old_val=\$ac_cv_env_${ac_var}_value eval ac_new_val=\$ac_env_${ac_var}_value case $ac_old_set,$ac_new_set in set,) { $as_echo "$as_me:${as_lineno-$LINENO}: error: \`$ac_var' was set to \`$ac_old_val' in the previous run" >&5 $as_echo "$as_me: error: \`$ac_var' was set to \`$ac_old_val' in the previous run" >&2;} ac_cache_corrupted=: ;; ,set) { $as_echo "$as_me:${as_lineno-$LINENO}: error: \`$ac_var' was not set in the previous run" >&5 $as_echo "$as_me: error: \`$ac_var' was not set in the previous run" >&2;} ac_cache_corrupted=: ;; ,);; *) if test "x$ac_old_val" != "x$ac_new_val"; then # differences in whitespace do not lead to failure. ac_old_val_w=`echo x $ac_old_val` ac_new_val_w=`echo x $ac_new_val` if test "$ac_old_val_w" != "$ac_new_val_w"; then { $as_echo "$as_me:${as_lineno-$LINENO}: error: \`$ac_var' has changed since the previous run:" >&5 $as_echo "$as_me: error: \`$ac_var' has changed since the previous run:" >&2;} ac_cache_corrupted=: else { $as_echo "$as_me:${as_lineno-$LINENO}: warning: ignoring whitespace changes in \`$ac_var' since the previous run:" >&5 $as_echo "$as_me: warning: ignoring whitespace changes in \`$ac_var' since the previous run:" >&2;} eval $ac_var=\$ac_old_val fi { $as_echo "$as_me:${as_lineno-$LINENO}: former value: \`$ac_old_val'" >&5 $as_echo "$as_me: former value: \`$ac_old_val'" >&2;} { $as_echo "$as_me:${as_lineno-$LINENO}: current value: \`$ac_new_val'" >&5 $as_echo "$as_me: current value: \`$ac_new_val'" >&2;} fi;; esac # Pass precious variables to config.status. if test "$ac_new_set" = set; then case $ac_new_val in *\'*) ac_arg=$ac_var=`$as_echo "$ac_new_val" | sed "s/'/'\\\\\\\\''/g"` ;; *) ac_arg=$ac_var=$ac_new_val ;; esac case " $ac_configure_args " in *" '$ac_arg' "*) ;; # Avoid dups. Use of quotes ensures accuracy. *) as_fn_append ac_configure_args " '$ac_arg'" ;; esac fi done if $ac_cache_corrupted; then { $as_echo "$as_me:${as_lineno-$LINENO}: error: in \`$ac_pwd':" >&5 $as_echo "$as_me: error: in \`$ac_pwd':" >&2;} { $as_echo "$as_me:${as_lineno-$LINENO}: error: changes in the environment can compromise the build" >&5 $as_echo "$as_me: error: changes in the environment can compromise the build" >&2;} as_fn_error $? "run \`make distclean' and/or \`rm $cache_file' and start over" "$LINENO" 5 fi ## -------------------- ## ## Main body of script. ## ## -------------------- ## ac_ext=c ac_cpp='$CPP $CPPFLAGS' ac_compile='$CC -c $CFLAGS $CPPFLAGS conftest.$ac_ext >&5' ac_link='$CC -o conftest$ac_exeext $CFLAGS $CPPFLAGS $LDFLAGS conftest.$ac_ext $LIBS >&5' ac_compiler_gnu=$ac_cv_c_compiler_gnu ac_aux_dir= for ac_dir in ../build-aux "$srcdir"/../build-aux; do if test -f "$ac_dir/install-sh"; then ac_aux_dir=$ac_dir ac_install_sh="$ac_aux_dir/install-sh -c" break elif test -f "$ac_dir/install.sh"; then ac_aux_dir=$ac_dir ac_install_sh="$ac_aux_dir/install.sh -c" break elif test -f "$ac_dir/shtool"; then ac_aux_dir=$ac_dir ac_install_sh="$ac_aux_dir/shtool install -c" break fi done if test -z "$ac_aux_dir"; then as_fn_error $? "cannot find install-sh, install.sh, or shtool in ../build-aux \"$srcdir\"/../build-aux" "$LINENO" 5 fi # These three variables are undocumented and unsupported, # and are intended to be withdrawn in a future Autoconf release. # They can cause serious problems if a builder's source tree is in a directory # whose full name contains unusual characters. ac_config_guess="$SHELL $ac_aux_dir/config.guess" # Please don't use this var. ac_config_sub="$SHELL $ac_aux_dir/config.sub" # Please don't use this var. ac_configure="$SHELL $ac_aux_dir/configure" # Please don't use this var. case $TERM in # for the most important terminal types we directly know the sequences xterm*|vt220*) term_bold=`${AWK:-awk} 'BEGIN { printf("%c%c%c%c", 27, 91, 49, 109); }' /dev/null` term_norm=`${AWK:-awk} 'BEGIN { printf("%c%c%c", 27, 91, 109); }' /dev/null` ;; vt100*) term_bold=`${AWK:-awk} 'BEGIN { printf("%c%c%c%c%c%c", 27, 91, 49, 109, 0, 0); }' /dev/null` term_norm=`${AWK:-awk} 'BEGIN { printf("%c%c%c%c%c", 27, 91, 109, 0, 0); }' /dev/null` ;; # for all others, we try to use a possibly existing `tput' or `tcout' utility *) paths=`echo "$PATH" | sed -e 's/:/ /g'` for tool in tput tcout; do for dir in $paths; do if test -r "$dir/$tool"; then for seq in bold md smso; do # 'smso' is last bold="`$dir/$tool $seq 2>/dev/null`" if test -n "$bold"; then term_bold="$bold" break fi done if test -n "$term_bold"; then for seq in sgr0 me rmso reset; do # 'reset' is last norm="`$dir/$tool $seq 2>/dev/null`" if test -n "$norm"; then term_norm="$norm" break fi done fi break fi done if test -n "$term_bold" && test -n "$term_norm"; then break fi done ;; esac echo "$term_bold" | tr -d '\n' > termbold echo "$term_norm" | tr -d '\n' > termnorm { echo; echo "${term_bold}Build Tools:${term_norm}"; } >& 6 am__api_version='1.11' # Find a good install program. We prefer a C program (faster), # so one script is as good as another. But avoid the broken or # incompatible versions: # SysV /etc/install, /usr/sbin/install # SunOS /usr/etc/install # IRIX /sbin/install # AIX /bin/install # AmigaOS /C/install, which installs bootblocks on floppy discs # AIX 4 /usr/bin/installbsd, which doesn't work without a -g flag # AFS /usr/afsws/bin/install, which mishandles nonexistent args # SVR4 /usr/ucb/install, which tries to use the nonexistent group "staff" # OS/2's system install, which has a completely different semantic # ./install, which can be erroneously created by make from ./install.sh. # Reject install programs that cannot install multiple files. { $as_echo "$as_me:${as_lineno-$LINENO}: checking for a BSD-compatible install" >&5 $as_echo_n "checking for a BSD-compatible install... " >&6; } if test -z "$INSTALL"; then if ${ac_cv_path_install+:} false; then : $as_echo_n "(cached) " >&6 else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. # Account for people who put trailing slashes in PATH elements. case $as_dir/ in #(( ./ | .// | /[cC]/* | \ /etc/* | /usr/sbin/* | /usr/etc/* | /sbin/* | /usr/afsws/bin/* | \ ?:[\\/]os2[\\/]install[\\/]* | ?:[\\/]OS2[\\/]INSTALL[\\/]* | \ /usr/ucb/* ) ;; *) # OSF1 and SCO ODT 3.0 have their own names for install. # Don't use installbsd from OSF since it installs stuff as root # by default. for ac_prog in ginstall scoinst install; do for ac_exec_ext in '' $ac_executable_extensions; do if as_fn_executable_p "$as_dir/$ac_prog$ac_exec_ext"; then if test $ac_prog = install && grep dspmsg "$as_dir/$ac_prog$ac_exec_ext" >/dev/null 2>&1; then # AIX install. It has an incompatible calling convention. : elif test $ac_prog = install && grep pwplus "$as_dir/$ac_prog$ac_exec_ext" >/dev/null 2>&1; then # program-specific install script used by HP pwplus--don't use. : else rm -rf conftest.one conftest.two conftest.dir echo one > conftest.one echo two > conftest.two mkdir conftest.dir if "$as_dir/$ac_prog$ac_exec_ext" -c conftest.one conftest.two "`pwd`/conftest.dir" && test -s conftest.one && test -s conftest.two && test -s conftest.dir/conftest.one && test -s conftest.dir/conftest.two then ac_cv_path_install="$as_dir/$ac_prog$ac_exec_ext -c" break 3 fi fi fi done done ;; esac done IFS=$as_save_IFS rm -rf conftest.one conftest.two conftest.dir fi if test "${ac_cv_path_install+set}" = set; then INSTALL=$ac_cv_path_install else # As a last resort, use the slow shell script. Don't cache a # value for INSTALL within a source directory, because that will # break other packages using the cache if that directory is # removed, or if the value is a relative name. INSTALL=$ac_install_sh fi fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $INSTALL" >&5 $as_echo "$INSTALL" >&6; } # Use test -z because SunOS4 sh mishandles braces in ${var-val}. # It thinks the first close brace ends the variable substitution. test -z "$INSTALL_PROGRAM" && INSTALL_PROGRAM='${INSTALL}' test -z "$INSTALL_SCRIPT" && INSTALL_SCRIPT='${INSTALL}' test -z "$INSTALL_DATA" && INSTALL_DATA='${INSTALL} -m 644' { $as_echo "$as_me:${as_lineno-$LINENO}: checking whether build environment is sane" >&5 $as_echo_n "checking whether build environment is sane... " >&6; } # Just in case sleep 1 echo timestamp > conftest.file # Reject unsafe characters in $srcdir or the absolute working directory # name. Accept space and tab only in the latter. am_lf=' ' case `pwd` in *[\\\"\#\$\&\'\`$am_lf]*) as_fn_error $? "unsafe absolute working directory name" "$LINENO" 5;; esac case $srcdir in *[\\\"\#\$\&\'\`$am_lf\ \ ]*) as_fn_error $? "unsafe srcdir value: \`$srcdir'" "$LINENO" 5;; esac # Do `set' in a subshell so we don't clobber the current shell's # arguments. Must try -L first in case configure is actually a # symlink; some systems play weird games with the mod time of symlinks # (eg FreeBSD returns the mod time of the symlink's containing # directory). if ( set X `ls -Lt "$srcdir/configure" conftest.file 2> /dev/null` if test "$*" = "X"; then # -L didn't work. set X `ls -t "$srcdir/configure" conftest.file` fi rm -f conftest.file if test "$*" != "X $srcdir/configure conftest.file" \ && test "$*" != "X conftest.file $srcdir/configure"; then # If neither matched, then we have a broken ls. This can happen # if, for instance, CONFIG_SHELL is bash and it inherits a # broken ls alias from the environment. This has actually # happened. Such a system could not be considered "sane". as_fn_error $? "ls -t appears to fail. Make sure there is not a broken alias in your environment" "$LINENO" 5 fi test "$2" = conftest.file ) then # Ok. : else as_fn_error $? "newly created file is older than distributed files! Check your system clock" "$LINENO" 5 fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: yes" >&5 $as_echo "yes" >&6; } test "$program_prefix" != NONE && program_transform_name="s&^&$program_prefix&;$program_transform_name" # Use a double $ so make ignores it. test "$program_suffix" != NONE && program_transform_name="s&\$&$program_suffix&;$program_transform_name" # Double any \ or $. # By default was `s,x,x', remove it if useless. ac_script='s/[\\$]/&&/g;s/;s,x,x,$//' program_transform_name=`$as_echo "$program_transform_name" | sed "$ac_script"` # expand $ac_aux_dir to an absolute path am_aux_dir=`cd $ac_aux_dir && pwd` if test x"${MISSING+set}" != xset; then case $am_aux_dir in *\ * | *\ *) MISSING="\${SHELL} \"$am_aux_dir/missing\"" ;; *) MISSING="\${SHELL} $am_aux_dir/missing" ;; esac fi # Use eval to expand $SHELL if eval "$MISSING --run true"; then am_missing_run="$MISSING --run " else am_missing_run= { $as_echo "$as_me:${as_lineno-$LINENO}: WARNING: \`missing' script is too old or missing" >&5 $as_echo "$as_me: WARNING: \`missing' script is too old or missing" >&2;} fi if test x"${install_sh}" != xset; then case $am_aux_dir in *\ * | *\ *) install_sh="\${SHELL} '$am_aux_dir/install-sh'" ;; *) install_sh="\${SHELL} $am_aux_dir/install-sh" esac fi # Installed binaries are usually stripped using `strip' when the user # run `make install-strip'. However `strip' might not be the right # tool to use in cross-compilation environments, therefore Automake # will honor the `STRIP' environment variable to overrule this program. if test "$cross_compiling" != no; then if test -n "$ac_tool_prefix"; then # Extract the first word of "${ac_tool_prefix}strip", so it can be a program name with args. set dummy ${ac_tool_prefix}strip; ac_word=$2 { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $ac_word" >&5 $as_echo_n "checking for $ac_word... " >&6; } if ${ac_cv_prog_STRIP+:} false; then : $as_echo_n "(cached) " >&6 else if test -n "$STRIP"; then ac_cv_prog_STRIP="$STRIP" # Let the user override the test. else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_exec_ext in '' $ac_executable_extensions; do if as_fn_executable_p "$as_dir/$ac_word$ac_exec_ext"; then ac_cv_prog_STRIP="${ac_tool_prefix}strip" $as_echo "$as_me:${as_lineno-$LINENO}: found $as_dir/$ac_word$ac_exec_ext" >&5 break 2 fi done done IFS=$as_save_IFS fi fi STRIP=$ac_cv_prog_STRIP if test -n "$STRIP"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $STRIP" >&5 $as_echo "$STRIP" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi fi if test -z "$ac_cv_prog_STRIP"; then ac_ct_STRIP=$STRIP # Extract the first word of "strip", so it can be a program name with args. set dummy strip; ac_word=$2 { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $ac_word" >&5 $as_echo_n "checking for $ac_word... " >&6; } if ${ac_cv_prog_ac_ct_STRIP+:} false; then : $as_echo_n "(cached) " >&6 else if test -n "$ac_ct_STRIP"; then ac_cv_prog_ac_ct_STRIP="$ac_ct_STRIP" # Let the user override the test. else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_exec_ext in '' $ac_executable_extensions; do if as_fn_executable_p "$as_dir/$ac_word$ac_exec_ext"; then ac_cv_prog_ac_ct_STRIP="strip" $as_echo "$as_me:${as_lineno-$LINENO}: found $as_dir/$ac_word$ac_exec_ext" >&5 break 2 fi done done IFS=$as_save_IFS fi fi ac_ct_STRIP=$ac_cv_prog_ac_ct_STRIP if test -n "$ac_ct_STRIP"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_ct_STRIP" >&5 $as_echo "$ac_ct_STRIP" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi if test "x$ac_ct_STRIP" = x; then STRIP=":" else case $cross_compiling:$ac_tool_warned in yes:) { $as_echo "$as_me:${as_lineno-$LINENO}: WARNING: using cross tools not prefixed with host triplet" >&5 $as_echo "$as_me: WARNING: using cross tools not prefixed with host triplet" >&2;} ac_tool_warned=yes ;; esac STRIP=$ac_ct_STRIP fi else STRIP="$ac_cv_prog_STRIP" fi fi INSTALL_STRIP_PROGRAM="\$(install_sh) -c -s" { $as_echo "$as_me:${as_lineno-$LINENO}: checking for a thread-safe mkdir -p" >&5 $as_echo_n "checking for a thread-safe mkdir -p... " >&6; } if test -z "$MKDIR_P"; then if ${ac_cv_path_mkdir+:} false; then : $as_echo_n "(cached) " >&6 else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH$PATH_SEPARATOR/opt/sfw/bin do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_prog in mkdir gmkdir; do for ac_exec_ext in '' $ac_executable_extensions; do as_fn_executable_p "$as_dir/$ac_prog$ac_exec_ext" || continue case `"$as_dir/$ac_prog$ac_exec_ext" --version 2>&1` in #( 'mkdir (GNU coreutils) '* | \ 'mkdir (coreutils) '* | \ 'mkdir (fileutils) '4.1*) ac_cv_path_mkdir=$as_dir/$ac_prog$ac_exec_ext break 3;; esac done done done IFS=$as_save_IFS fi test -d ./--version && rmdir ./--version if test "${ac_cv_path_mkdir+set}" = set; then MKDIR_P="$ac_cv_path_mkdir -p" else # As a last resort, use the slow shell script. Don't cache a # value for MKDIR_P within a source directory, because that will # break other packages using the cache if that directory is # removed, or if the value is a relative name. MKDIR_P="$ac_install_sh -d" fi fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $MKDIR_P" >&5 $as_echo "$MKDIR_P" >&6; } mkdir_p="$MKDIR_P" case $mkdir_p in [\\/$]* | ?:[\\/]*) ;; */*) mkdir_p="\$(top_builddir)/$mkdir_p" ;; esac for ac_prog in gawk mawk nawk awk do # Extract the first word of "$ac_prog", so it can be a program name with args. set dummy $ac_prog; ac_word=$2 { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $ac_word" >&5 $as_echo_n "checking for $ac_word... " >&6; } if ${ac_cv_prog_AWK+:} false; then : $as_echo_n "(cached) " >&6 else if test -n "$AWK"; then ac_cv_prog_AWK="$AWK" # Let the user override the test. else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_exec_ext in '' $ac_executable_extensions; do if as_fn_executable_p "$as_dir/$ac_word$ac_exec_ext"; then ac_cv_prog_AWK="$ac_prog" $as_echo "$as_me:${as_lineno-$LINENO}: found $as_dir/$ac_word$ac_exec_ext" >&5 break 2 fi done done IFS=$as_save_IFS fi fi AWK=$ac_cv_prog_AWK if test -n "$AWK"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $AWK" >&5 $as_echo "$AWK" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi test -n "$AWK" && break done { $as_echo "$as_me:${as_lineno-$LINENO}: checking whether ${MAKE-make} sets \$(MAKE)" >&5 $as_echo_n "checking whether ${MAKE-make} sets \$(MAKE)... " >&6; } set x ${MAKE-make} ac_make=`$as_echo "$2" | sed 's/+/p/g; s/[^a-zA-Z0-9_]/_/g'` if eval \${ac_cv_prog_make_${ac_make}_set+:} false; then : $as_echo_n "(cached) " >&6 else cat >conftest.make <<\_ACEOF SHELL = /bin/sh all: @echo '@@@%%%=$(MAKE)=@@@%%%' _ACEOF # GNU make sometimes prints "make[1]: Entering ...", which would confuse us. case `${MAKE-make} -f conftest.make 2>/dev/null` in *@@@%%%=?*=@@@%%%*) eval ac_cv_prog_make_${ac_make}_set=yes;; *) eval ac_cv_prog_make_${ac_make}_set=no;; esac rm -f conftest.make fi if eval test \$ac_cv_prog_make_${ac_make}_set = yes; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: yes" >&5 $as_echo "yes" >&6; } SET_MAKE= else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } SET_MAKE="MAKE=${MAKE-make}" fi rm -rf .tst 2>/dev/null mkdir .tst 2>/dev/null if test -d .tst; then am__leading_dot=. else am__leading_dot=_ fi rmdir .tst 2>/dev/null if test "`cd $srcdir && pwd`" != "`pwd`"; then # Use -I$(srcdir) only when $(srcdir) != ., so that make's output # is not polluted with repeated "-I." am__isrc=' -I$(srcdir)' # test to see if srcdir already configured if test -f $srcdir/config.status; then as_fn_error $? "source directory already configured; run \"make distclean\" there first" "$LINENO" 5 fi fi # test whether we have cygpath if test -z "$CYGPATH_W"; then if (cygpath --version) >/dev/null 2>/dev/null; then CYGPATH_W='cygpath -w' else CYGPATH_W=echo fi fi # Define the identity of the package. PACKAGE=libsigsegv VERSION=2.5 cat >>confdefs.h <<_ACEOF #define PACKAGE "$PACKAGE" _ACEOF cat >>confdefs.h <<_ACEOF #define VERSION "$VERSION" _ACEOF # Some tools Automake needs. ACLOCAL=${ACLOCAL-"${am_missing_run}aclocal-${am__api_version}"} AUTOCONF=${AUTOCONF-"${am_missing_run}autoconf"} AUTOMAKE=${AUTOMAKE-"${am_missing_run}automake-${am__api_version}"} AUTOHEADER=${AUTOHEADER-"${am_missing_run}autoheader"} MAKEINFO=${MAKEINFO-"${am_missing_run}makeinfo"} # We need awk for the "check" target. The system "awk" is bad on # some platforms. # Always define AMTAR for backward compatibility. Yes, it's still used # in the wild :-( We should find a proper way to deprecate it ... AMTAR='$${TAR-tar}' am__tar='$${TAR-tar} chof - "$$tardir"' am__untar='$${TAR-tar} xf -' ac_config_headers="$ac_config_headers config.h" ac_ext=c ac_cpp='$CPP $CPPFLAGS' ac_compile='$CC -c $CFLAGS $CPPFLAGS conftest.$ac_ext >&5' ac_link='$CC -o conftest$ac_exeext $CFLAGS $CPPFLAGS $LDFLAGS conftest.$ac_ext $LIBS >&5' ac_compiler_gnu=$ac_cv_c_compiler_gnu if test -n "$ac_tool_prefix"; then # Extract the first word of "${ac_tool_prefix}gcc", so it can be a program name with args. set dummy ${ac_tool_prefix}gcc; ac_word=$2 { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $ac_word" >&5 $as_echo_n "checking for $ac_word... " >&6; } if ${ac_cv_prog_CC+:} false; then : $as_echo_n "(cached) " >&6 else if test -n "$CC"; then ac_cv_prog_CC="$CC" # Let the user override the test. else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_exec_ext in '' $ac_executable_extensions; do if as_fn_executable_p "$as_dir/$ac_word$ac_exec_ext"; then ac_cv_prog_CC="${ac_tool_prefix}gcc" $as_echo "$as_me:${as_lineno-$LINENO}: found $as_dir/$ac_word$ac_exec_ext" >&5 break 2 fi done done IFS=$as_save_IFS fi fi CC=$ac_cv_prog_CC if test -n "$CC"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $CC" >&5 $as_echo "$CC" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi fi if test -z "$ac_cv_prog_CC"; then ac_ct_CC=$CC # Extract the first word of "gcc", so it can be a program name with args. set dummy gcc; ac_word=$2 { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $ac_word" >&5 $as_echo_n "checking for $ac_word... " >&6; } if ${ac_cv_prog_ac_ct_CC+:} false; then : $as_echo_n "(cached) " >&6 else if test -n "$ac_ct_CC"; then ac_cv_prog_ac_ct_CC="$ac_ct_CC" # Let the user override the test. else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_exec_ext in '' $ac_executable_extensions; do if as_fn_executable_p "$as_dir/$ac_word$ac_exec_ext"; then ac_cv_prog_ac_ct_CC="gcc" $as_echo "$as_me:${as_lineno-$LINENO}: found $as_dir/$ac_word$ac_exec_ext" >&5 break 2 fi done done IFS=$as_save_IFS fi fi ac_ct_CC=$ac_cv_prog_ac_ct_CC if test -n "$ac_ct_CC"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_ct_CC" >&5 $as_echo "$ac_ct_CC" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi if test "x$ac_ct_CC" = x; then CC="" else case $cross_compiling:$ac_tool_warned in yes:) { $as_echo "$as_me:${as_lineno-$LINENO}: WARNING: using cross tools not prefixed with host triplet" >&5 $as_echo "$as_me: WARNING: using cross tools not prefixed with host triplet" >&2;} ac_tool_warned=yes ;; esac CC=$ac_ct_CC fi else CC="$ac_cv_prog_CC" fi if test -z "$CC"; then if test -n "$ac_tool_prefix"; then # Extract the first word of "${ac_tool_prefix}cc", so it can be a program name with args. set dummy ${ac_tool_prefix}cc; ac_word=$2 { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $ac_word" >&5 $as_echo_n "checking for $ac_word... " >&6; } if ${ac_cv_prog_CC+:} false; then : $as_echo_n "(cached) " >&6 else if test -n "$CC"; then ac_cv_prog_CC="$CC" # Let the user override the test. else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_exec_ext in '' $ac_executable_extensions; do if as_fn_executable_p "$as_dir/$ac_word$ac_exec_ext"; then ac_cv_prog_CC="${ac_tool_prefix}cc" $as_echo "$as_me:${as_lineno-$LINENO}: found $as_dir/$ac_word$ac_exec_ext" >&5 break 2 fi done done IFS=$as_save_IFS fi fi CC=$ac_cv_prog_CC if test -n "$CC"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $CC" >&5 $as_echo "$CC" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi fi fi if test -z "$CC"; then # Extract the first word of "cc", so it can be a program name with args. set dummy cc; ac_word=$2 { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $ac_word" >&5 $as_echo_n "checking for $ac_word... " >&6; } if ${ac_cv_prog_CC+:} false; then : $as_echo_n "(cached) " >&6 else if test -n "$CC"; then ac_cv_prog_CC="$CC" # Let the user override the test. else ac_prog_rejected=no as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_exec_ext in '' $ac_executable_extensions; do if as_fn_executable_p "$as_dir/$ac_word$ac_exec_ext"; then if test "$as_dir/$ac_word$ac_exec_ext" = "/usr/ucb/cc"; then ac_prog_rejected=yes continue fi ac_cv_prog_CC="cc" $as_echo "$as_me:${as_lineno-$LINENO}: found $as_dir/$ac_word$ac_exec_ext" >&5 break 2 fi done done IFS=$as_save_IFS if test $ac_prog_rejected = yes; then # We found a bogon in the path, so make sure we never use it. set dummy $ac_cv_prog_CC shift if test $# != 0; then # We chose a different compiler from the bogus one. # However, it has the same basename, so the bogon will be chosen # first if we set CC to just the basename; use the full file name. shift ac_cv_prog_CC="$as_dir/$ac_word${1+' '}$@" fi fi fi fi CC=$ac_cv_prog_CC if test -n "$CC"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $CC" >&5 $as_echo "$CC" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi fi if test -z "$CC"; then if test -n "$ac_tool_prefix"; then for ac_prog in cl.exe do # Extract the first word of "$ac_tool_prefix$ac_prog", so it can be a program name with args. set dummy $ac_tool_prefix$ac_prog; ac_word=$2 { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $ac_word" >&5 $as_echo_n "checking for $ac_word... " >&6; } if ${ac_cv_prog_CC+:} false; then : $as_echo_n "(cached) " >&6 else if test -n "$CC"; then ac_cv_prog_CC="$CC" # Let the user override the test. else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_exec_ext in '' $ac_executable_extensions; do if as_fn_executable_p "$as_dir/$ac_word$ac_exec_ext"; then ac_cv_prog_CC="$ac_tool_prefix$ac_prog" $as_echo "$as_me:${as_lineno-$LINENO}: found $as_dir/$ac_word$ac_exec_ext" >&5 break 2 fi done done IFS=$as_save_IFS fi fi CC=$ac_cv_prog_CC if test -n "$CC"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $CC" >&5 $as_echo "$CC" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi test -n "$CC" && break done fi if test -z "$CC"; then ac_ct_CC=$CC for ac_prog in cl.exe do # Extract the first word of "$ac_prog", so it can be a program name with args. set dummy $ac_prog; ac_word=$2 { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $ac_word" >&5 $as_echo_n "checking for $ac_word... " >&6; } if ${ac_cv_prog_ac_ct_CC+:} false; then : $as_echo_n "(cached) " >&6 else if test -n "$ac_ct_CC"; then ac_cv_prog_ac_ct_CC="$ac_ct_CC" # Let the user override the test. else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_exec_ext in '' $ac_executable_extensions; do if as_fn_executable_p "$as_dir/$ac_word$ac_exec_ext"; then ac_cv_prog_ac_ct_CC="$ac_prog" $as_echo "$as_me:${as_lineno-$LINENO}: found $as_dir/$ac_word$ac_exec_ext" >&5 break 2 fi done done IFS=$as_save_IFS fi fi ac_ct_CC=$ac_cv_prog_ac_ct_CC if test -n "$ac_ct_CC"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_ct_CC" >&5 $as_echo "$ac_ct_CC" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi test -n "$ac_ct_CC" && break done if test "x$ac_ct_CC" = x; then CC="" else case $cross_compiling:$ac_tool_warned in yes:) { $as_echo "$as_me:${as_lineno-$LINENO}: WARNING: using cross tools not prefixed with host triplet" >&5 $as_echo "$as_me: WARNING: using cross tools not prefixed with host triplet" >&2;} ac_tool_warned=yes ;; esac CC=$ac_ct_CC fi fi fi test -z "$CC" && { { $as_echo "$as_me:${as_lineno-$LINENO}: error: in \`$ac_pwd':" >&5 $as_echo "$as_me: error: in \`$ac_pwd':" >&2;} as_fn_error $? "no acceptable C compiler found in \$PATH See \`config.log' for more details" "$LINENO" 5; } # Provide some information about the compiler. $as_echo "$as_me:${as_lineno-$LINENO}: checking for C compiler version" >&5 set X $ac_compile ac_compiler=$2 for ac_option in --version -v -V -qversion; do { { ac_try="$ac_compiler $ac_option >&5" case "(($ac_try" in *\"* | *\`* | *\\*) ac_try_echo=\$ac_try;; *) ac_try_echo=$ac_try;; esac eval ac_try_echo="\"\$as_me:${as_lineno-$LINENO}: $ac_try_echo\"" $as_echo "$ac_try_echo"; } >&5 (eval "$ac_compiler $ac_option >&5") 2>conftest.err ac_status=$? if test -s conftest.err; then sed '10a\ ... rest of stderr output deleted ... 10q' conftest.err >conftest.er1 cat conftest.er1 >&5 fi rm -f conftest.er1 conftest.err $as_echo "$as_me:${as_lineno-$LINENO}: \$? = $ac_status" >&5 test $ac_status = 0; } done cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ int main () { ; return 0; } _ACEOF ac_clean_files_save=$ac_clean_files ac_clean_files="$ac_clean_files a.out a.out.dSYM a.exe b.out" # Try to create an executable without -o first, disregard a.out. # It will help us diagnose broken compilers, and finding out an intuition # of exeext. { $as_echo "$as_me:${as_lineno-$LINENO}: checking whether the C compiler works" >&5 $as_echo_n "checking whether the C compiler works... " >&6; } ac_link_default=`$as_echo "$ac_link" | sed 's/ -o *conftest[^ ]*//'` # The possible output files: ac_files="a.out conftest.exe conftest a.exe a_out.exe b.out conftest.*" ac_rmfiles= for ac_file in $ac_files do case $ac_file in *.$ac_ext | *.xcoff | *.tds | *.d | *.pdb | *.xSYM | *.bb | *.bbg | *.map | *.inf | *.dSYM | *.o | *.obj ) ;; * ) ac_rmfiles="$ac_rmfiles $ac_file";; esac done rm -f $ac_rmfiles if { { ac_try="$ac_link_default" case "(($ac_try" in *\"* | *\`* | *\\*) ac_try_echo=\$ac_try;; *) ac_try_echo=$ac_try;; esac eval ac_try_echo="\"\$as_me:${as_lineno-$LINENO}: $ac_try_echo\"" $as_echo "$ac_try_echo"; } >&5 (eval "$ac_link_default") 2>&5 ac_status=$? $as_echo "$as_me:${as_lineno-$LINENO}: \$? = $ac_status" >&5 test $ac_status = 0; }; then : # Autoconf-2.13 could set the ac_cv_exeext variable to `no'. # So ignore a value of `no', otherwise this would lead to `EXEEXT = no' # in a Makefile. We should not override ac_cv_exeext if it was cached, # so that the user can short-circuit this test for compilers unknown to # Autoconf. for ac_file in $ac_files '' do test -f "$ac_file" || continue case $ac_file in *.$ac_ext | *.xcoff | *.tds | *.d | *.pdb | *.xSYM | *.bb | *.bbg | *.map | *.inf | *.dSYM | *.o | *.obj ) ;; [ab].out ) # We found the default executable, but exeext='' is most # certainly right. break;; *.* ) if test "${ac_cv_exeext+set}" = set && test "$ac_cv_exeext" != no; then :; else ac_cv_exeext=`expr "$ac_file" : '[^.]*\(\..*\)'` fi # We set ac_cv_exeext here because the later test for it is not # safe: cross compilers may not add the suffix if given an `-o' # argument, so we may need to know it at that point already. # Even if this section looks crufty: it has the advantage of # actually working. break;; * ) break;; esac done test "$ac_cv_exeext" = no && ac_cv_exeext= else ac_file='' fi if test -z "$ac_file"; then : { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } $as_echo "$as_me: failed program was:" >&5 sed 's/^/| /' conftest.$ac_ext >&5 { { $as_echo "$as_me:${as_lineno-$LINENO}: error: in \`$ac_pwd':" >&5 $as_echo "$as_me: error: in \`$ac_pwd':" >&2;} as_fn_error 77 "C compiler cannot create executables See \`config.log' for more details" "$LINENO" 5; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: yes" >&5 $as_echo "yes" >&6; } fi { $as_echo "$as_me:${as_lineno-$LINENO}: checking for C compiler default output file name" >&5 $as_echo_n "checking for C compiler default output file name... " >&6; } { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_file" >&5 $as_echo "$ac_file" >&6; } ac_exeext=$ac_cv_exeext rm -f -r a.out a.out.dSYM a.exe conftest$ac_cv_exeext b.out ac_clean_files=$ac_clean_files_save { $as_echo "$as_me:${as_lineno-$LINENO}: checking for suffix of executables" >&5 $as_echo_n "checking for suffix of executables... " >&6; } if { { ac_try="$ac_link" case "(($ac_try" in *\"* | *\`* | *\\*) ac_try_echo=\$ac_try;; *) ac_try_echo=$ac_try;; esac eval ac_try_echo="\"\$as_me:${as_lineno-$LINENO}: $ac_try_echo\"" $as_echo "$ac_try_echo"; } >&5 (eval "$ac_link") 2>&5 ac_status=$? $as_echo "$as_me:${as_lineno-$LINENO}: \$? = $ac_status" >&5 test $ac_status = 0; }; then : # If both `conftest.exe' and `conftest' are `present' (well, observable) # catch `conftest.exe'. For instance with Cygwin, `ls conftest' will # work properly (i.e., refer to `conftest.exe'), while it won't with # `rm'. for ac_file in conftest.exe conftest conftest.*; do test -f "$ac_file" || continue case $ac_file in *.$ac_ext | *.xcoff | *.tds | *.d | *.pdb | *.xSYM | *.bb | *.bbg | *.map | *.inf | *.dSYM | *.o | *.obj ) ;; *.* ) ac_cv_exeext=`expr "$ac_file" : '[^.]*\(\..*\)'` break;; * ) break;; esac done else { { $as_echo "$as_me:${as_lineno-$LINENO}: error: in \`$ac_pwd':" >&5 $as_echo "$as_me: error: in \`$ac_pwd':" >&2;} as_fn_error $? "cannot compute suffix of executables: cannot compile and link See \`config.log' for more details" "$LINENO" 5; } fi rm -f conftest conftest$ac_cv_exeext { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_cv_exeext" >&5 $as_echo "$ac_cv_exeext" >&6; } rm -f conftest.$ac_ext EXEEXT=$ac_cv_exeext ac_exeext=$EXEEXT cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ #include int main () { FILE *f = fopen ("conftest.out", "w"); return ferror (f) || fclose (f) != 0; ; return 0; } _ACEOF ac_clean_files="$ac_clean_files conftest.out" # Check that the compiler produces executables we can run. If not, either # the compiler is broken, or we cross compile. { $as_echo "$as_me:${as_lineno-$LINENO}: checking whether we are cross compiling" >&5 $as_echo_n "checking whether we are cross compiling... " >&6; } if test "$cross_compiling" != yes; then { { ac_try="$ac_link" case "(($ac_try" in *\"* | *\`* | *\\*) ac_try_echo=\$ac_try;; *) ac_try_echo=$ac_try;; esac eval ac_try_echo="\"\$as_me:${as_lineno-$LINENO}: $ac_try_echo\"" $as_echo "$ac_try_echo"; } >&5 (eval "$ac_link") 2>&5 ac_status=$? $as_echo "$as_me:${as_lineno-$LINENO}: \$? = $ac_status" >&5 test $ac_status = 0; } if { ac_try='./conftest$ac_cv_exeext' { { case "(($ac_try" in *\"* | *\`* | *\\*) ac_try_echo=\$ac_try;; *) ac_try_echo=$ac_try;; esac eval ac_try_echo="\"\$as_me:${as_lineno-$LINENO}: $ac_try_echo\"" $as_echo "$ac_try_echo"; } >&5 (eval "$ac_try") 2>&5 ac_status=$? $as_echo "$as_me:${as_lineno-$LINENO}: \$? = $ac_status" >&5 test $ac_status = 0; }; }; then cross_compiling=no else if test "$cross_compiling" = maybe; then cross_compiling=yes else { { $as_echo "$as_me:${as_lineno-$LINENO}: error: in \`$ac_pwd':" >&5 $as_echo "$as_me: error: in \`$ac_pwd':" >&2;} as_fn_error $? "cannot run C compiled programs. If you meant to cross compile, use \`--host'. See \`config.log' for more details" "$LINENO" 5; } fi fi fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $cross_compiling" >&5 $as_echo "$cross_compiling" >&6; } rm -f conftest.$ac_ext conftest$ac_cv_exeext conftest.out ac_clean_files=$ac_clean_files_save { $as_echo "$as_me:${as_lineno-$LINENO}: checking for suffix of object files" >&5 $as_echo_n "checking for suffix of object files... " >&6; } if ${ac_cv_objext+:} false; then : $as_echo_n "(cached) " >&6 else cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ int main () { ; return 0; } _ACEOF rm -f conftest.o conftest.obj if { { ac_try="$ac_compile" case "(($ac_try" in *\"* | *\`* | *\\*) ac_try_echo=\$ac_try;; *) ac_try_echo=$ac_try;; esac eval ac_try_echo="\"\$as_me:${as_lineno-$LINENO}: $ac_try_echo\"" $as_echo "$ac_try_echo"; } >&5 (eval "$ac_compile") 2>&5 ac_status=$? $as_echo "$as_me:${as_lineno-$LINENO}: \$? = $ac_status" >&5 test $ac_status = 0; }; then : for ac_file in conftest.o conftest.obj conftest.*; do test -f "$ac_file" || continue; case $ac_file in *.$ac_ext | *.xcoff | *.tds | *.d | *.pdb | *.xSYM | *.bb | *.bbg | *.map | *.inf | *.dSYM ) ;; *) ac_cv_objext=`expr "$ac_file" : '.*\.\(.*\)'` break;; esac done else $as_echo "$as_me: failed program was:" >&5 sed 's/^/| /' conftest.$ac_ext >&5 { { $as_echo "$as_me:${as_lineno-$LINENO}: error: in \`$ac_pwd':" >&5 $as_echo "$as_me: error: in \`$ac_pwd':" >&2;} as_fn_error $? "cannot compute suffix of object files: cannot compile See \`config.log' for more details" "$LINENO" 5; } fi rm -f conftest.$ac_cv_objext conftest.$ac_ext fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_cv_objext" >&5 $as_echo "$ac_cv_objext" >&6; } OBJEXT=$ac_cv_objext ac_objext=$OBJEXT { $as_echo "$as_me:${as_lineno-$LINENO}: checking whether we are using the GNU C compiler" >&5 $as_echo_n "checking whether we are using the GNU C compiler... " >&6; } if ${ac_cv_c_compiler_gnu+:} false; then : $as_echo_n "(cached) " >&6 else cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ int main () { #ifndef __GNUC__ choke me #endif ; return 0; } _ACEOF if ac_fn_c_try_compile "$LINENO"; then : ac_compiler_gnu=yes else ac_compiler_gnu=no fi rm -f core conftest.err conftest.$ac_objext conftest.$ac_ext ac_cv_c_compiler_gnu=$ac_compiler_gnu fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_cv_c_compiler_gnu" >&5 $as_echo "$ac_cv_c_compiler_gnu" >&6; } if test $ac_compiler_gnu = yes; then GCC=yes else GCC= fi ac_test_CFLAGS=${CFLAGS+set} ac_save_CFLAGS=$CFLAGS { $as_echo "$as_me:${as_lineno-$LINENO}: checking whether $CC accepts -g" >&5 $as_echo_n "checking whether $CC accepts -g... " >&6; } if ${ac_cv_prog_cc_g+:} false; then : $as_echo_n "(cached) " >&6 else ac_save_c_werror_flag=$ac_c_werror_flag ac_c_werror_flag=yes ac_cv_prog_cc_g=no CFLAGS="-g" cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ int main () { ; return 0; } _ACEOF if ac_fn_c_try_compile "$LINENO"; then : ac_cv_prog_cc_g=yes else CFLAGS="" cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ int main () { ; return 0; } _ACEOF if ac_fn_c_try_compile "$LINENO"; then : else ac_c_werror_flag=$ac_save_c_werror_flag CFLAGS="-g" cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ int main () { ; return 0; } _ACEOF if ac_fn_c_try_compile "$LINENO"; then : ac_cv_prog_cc_g=yes fi rm -f core conftest.err conftest.$ac_objext conftest.$ac_ext fi rm -f core conftest.err conftest.$ac_objext conftest.$ac_ext fi rm -f core conftest.err conftest.$ac_objext conftest.$ac_ext ac_c_werror_flag=$ac_save_c_werror_flag fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_cv_prog_cc_g" >&5 $as_echo "$ac_cv_prog_cc_g" >&6; } if test "$ac_test_CFLAGS" = set; then CFLAGS=$ac_save_CFLAGS elif test $ac_cv_prog_cc_g = yes; then if test "$GCC" = yes; then CFLAGS="-g -O2" else CFLAGS="-g" fi else if test "$GCC" = yes; then CFLAGS="-O2" else CFLAGS= fi fi { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $CC option to accept ISO C89" >&5 $as_echo_n "checking for $CC option to accept ISO C89... " >&6; } if ${ac_cv_prog_cc_c89+:} false; then : $as_echo_n "(cached) " >&6 else ac_cv_prog_cc_c89=no ac_save_CC=$CC cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ #include #include struct stat; /* Most of the following tests are stolen from RCS 5.7's src/conf.sh. */ struct buf { int x; }; FILE * (*rcsopen) (struct buf *, struct stat *, int); static char *e (p, i) char **p; int i; { return p[i]; } static char *f (char * (*g) (char **, int), char **p, ...) { char *s; va_list v; va_start (v,p); s = g (p, va_arg (v,int)); va_end (v); return s; } /* OSF 4.0 Compaq cc is some sort of almost-ANSI by default. It has function prototypes and stuff, but not '\xHH' hex character constants. These don't provoke an error unfortunately, instead are silently treated as 'x'. The following induces an error, until -std is added to get proper ANSI mode. Curiously '\x00'!='x' always comes out true, for an array size at least. It's necessary to write '\x00'==0 to get something that's true only with -std. */ int osf4_cc_array ['\x00' == 0 ? 1 : -1]; /* IBM C 6 for AIX is almost-ANSI by default, but it replaces macro parameters inside strings and character constants. */ #define FOO(x) 'x' int xlc6_cc_array[FOO(a) == 'x' ? 1 : -1]; int test (int i, double x); struct s1 {int (*f) (int a);}; struct s2 {int (*f) (double a);}; int pairnames (int, char **, FILE *(*)(struct buf *, struct stat *, int), int, int); int argc; char **argv; int main () { return f (e, argv, 0) != argv[0] || f (e, argv, 1) != argv[1]; ; return 0; } _ACEOF for ac_arg in '' -qlanglvl=extc89 -qlanglvl=ansi -std \ -Ae "-Aa -D_HPUX_SOURCE" "-Xc -D__EXTENSIONS__" do CC="$ac_save_CC $ac_arg" if ac_fn_c_try_compile "$LINENO"; then : ac_cv_prog_cc_c89=$ac_arg fi rm -f core conftest.err conftest.$ac_objext test "x$ac_cv_prog_cc_c89" != "xno" && break done rm -f conftest.$ac_ext CC=$ac_save_CC fi # AC_CACHE_VAL case "x$ac_cv_prog_cc_c89" in x) { $as_echo "$as_me:${as_lineno-$LINENO}: result: none needed" >&5 $as_echo "none needed" >&6; } ;; xno) { $as_echo "$as_me:${as_lineno-$LINENO}: result: unsupported" >&5 $as_echo "unsupported" >&6; } ;; *) CC="$CC $ac_cv_prog_cc_c89" { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_cv_prog_cc_c89" >&5 $as_echo "$ac_cv_prog_cc_c89" >&6; } ;; esac if test "x$ac_cv_prog_cc_c89" != xno; then : fi ac_ext=c ac_cpp='$CPP $CPPFLAGS' ac_compile='$CC -c $CFLAGS $CPPFLAGS conftest.$ac_ext >&5' ac_link='$CC -o conftest$ac_exeext $CFLAGS $CPPFLAGS $LDFLAGS conftest.$ac_ext $LIBS >&5' ac_compiler_gnu=$ac_cv_c_compiler_gnu DEPDIR="${am__leading_dot}deps" ac_config_commands="$ac_config_commands depfiles" am_make=${MAKE-make} cat > confinc << 'END' am__doit: @echo this is the am__doit target .PHONY: am__doit END # If we don't find an include directive, just comment out the code. { $as_echo "$as_me:${as_lineno-$LINENO}: checking for style of include used by $am_make" >&5 $as_echo_n "checking for style of include used by $am_make... " >&6; } am__include="#" am__quote= _am_result=none # First try GNU make style include. echo "include confinc" > confmf # Ignore all kinds of additional output from `make'. case `$am_make -s -f confmf 2> /dev/null` in #( *the\ am__doit\ target*) am__include=include am__quote= _am_result=GNU ;; esac # Now try BSD make style include. if test "$am__include" = "#"; then echo '.include "confinc"' > confmf case `$am_make -s -f confmf 2> /dev/null` in #( *the\ am__doit\ target*) am__include=.include am__quote="\"" _am_result=BSD ;; esac fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $_am_result" >&5 $as_echo "$_am_result" >&6; } rm -f confinc confmf # Check whether --enable-dependency-tracking was given. if test "${enable_dependency_tracking+set}" = set; then : enableval=$enable_dependency_tracking; fi if test "x$enable_dependency_tracking" != xno; then am_depcomp="$ac_aux_dir/depcomp" AMDEPBACKSLASH='\' am__nodep='_no' fi if test "x$enable_dependency_tracking" != xno; then AMDEP_TRUE= AMDEP_FALSE='#' else AMDEP_TRUE='#' AMDEP_FALSE= fi depcc="$CC" am_compiler_list= { $as_echo "$as_me:${as_lineno-$LINENO}: checking dependency style of $depcc" >&5 $as_echo_n "checking dependency style of $depcc... " >&6; } if ${am_cv_CC_dependencies_compiler_type+:} false; then : $as_echo_n "(cached) " >&6 else if test -z "$AMDEP_TRUE" && test -f "$am_depcomp"; then # We make a subdir and do the tests there. Otherwise we can end up # making bogus files that we don't know about and never remove. For # instance it was reported that on HP-UX the gcc test will end up # making a dummy file named `D' -- because `-MD' means `put the output # in D'. rm -rf conftest.dir mkdir conftest.dir # Copy depcomp to subdir because otherwise we won't find it if we're # using a relative directory. cp "$am_depcomp" conftest.dir cd conftest.dir # We will build objects and dependencies in a subdirectory because # it helps to detect inapplicable dependency modes. For instance # both Tru64's cc and ICC support -MD to output dependencies as a # side effect of compilation, but ICC will put the dependencies in # the current directory while Tru64 will put them in the object # directory. mkdir sub am_cv_CC_dependencies_compiler_type=none if test "$am_compiler_list" = ""; then am_compiler_list=`sed -n 's/^#*\([a-zA-Z0-9]*\))$/\1/p' < ./depcomp` fi am__universal=false case " $depcc " in #( *\ -arch\ *\ -arch\ *) am__universal=true ;; esac for depmode in $am_compiler_list; do # Setup a source with many dependencies, because some compilers # like to wrap large dependency lists on column 80 (with \), and # we should not choose a depcomp mode which is confused by this. # # We need to recreate these files for each test, as the compiler may # overwrite some of them when testing with obscure command lines. # This happens at least with the AIX C compiler. : > sub/conftest.c for i in 1 2 3 4 5 6; do echo '#include "conftst'$i'.h"' >> sub/conftest.c # Using `: > sub/conftst$i.h' creates only sub/conftst1.h with # Solaris 8's {/usr,}/bin/sh. touch sub/conftst$i.h done echo "${am__include} ${am__quote}sub/conftest.Po${am__quote}" > confmf # We check with `-c' and `-o' for the sake of the "dashmstdout" # mode. It turns out that the SunPro C++ compiler does not properly # handle `-M -o', and we need to detect this. Also, some Intel # versions had trouble with output in subdirs am__obj=sub/conftest.${OBJEXT-o} am__minus_obj="-o $am__obj" case $depmode in gcc) # This depmode causes a compiler race in universal mode. test "$am__universal" = false || continue ;; nosideeffect) # after this tag, mechanisms are not by side-effect, so they'll # only be used when explicitly requested if test "x$enable_dependency_tracking" = xyes; then continue else break fi ;; msvc7 | msvc7msys | msvisualcpp | msvcmsys) # This compiler won't grok `-c -o', but also, the minuso test has # not run yet. These depmodes are late enough in the game, and # so weak that their functioning should not be impacted. am__obj=conftest.${OBJEXT-o} am__minus_obj= ;; none) break ;; esac if depmode=$depmode \ source=sub/conftest.c object=$am__obj \ depfile=sub/conftest.Po tmpdepfile=sub/conftest.TPo \ $SHELL ./depcomp $depcc -c $am__minus_obj sub/conftest.c \ >/dev/null 2>conftest.err && grep sub/conftst1.h sub/conftest.Po > /dev/null 2>&1 && grep sub/conftst6.h sub/conftest.Po > /dev/null 2>&1 && grep $am__obj sub/conftest.Po > /dev/null 2>&1 && ${MAKE-make} -s -f confmf > /dev/null 2>&1; then # icc doesn't choke on unknown options, it will just issue warnings # or remarks (even with -Werror). So we grep stderr for any message # that says an option was ignored or not supported. # When given -MP, icc 7.0 and 7.1 complain thusly: # icc: Command line warning: ignoring option '-M'; no argument required # The diagnosis changed in icc 8.0: # icc: Command line remark: option '-MP' not supported if (grep 'ignoring option' conftest.err || grep 'not supported' conftest.err) >/dev/null 2>&1; then :; else am_cv_CC_dependencies_compiler_type=$depmode break fi fi done cd .. rm -rf conftest.dir else am_cv_CC_dependencies_compiler_type=none fi fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $am_cv_CC_dependencies_compiler_type" >&5 $as_echo "$am_cv_CC_dependencies_compiler_type" >&6; } CCDEPMODE=depmode=$am_cv_CC_dependencies_compiler_type if test "x$enable_dependency_tracking" != xno \ && test "$am_cv_CC_dependencies_compiler_type" = gcc3; then am__fastdepCC_TRUE= am__fastdepCC_FALSE='#' else am__fastdepCC_TRUE='#' am__fastdepCC_FALSE= fi ac_ext=c ac_cpp='$CPP $CPPFLAGS' ac_compile='$CC -c $CFLAGS $CPPFLAGS conftest.$ac_ext >&5' ac_link='$CC -o conftest$ac_exeext $CFLAGS $CPPFLAGS $LDFLAGS conftest.$ac_ext $LIBS >&5' ac_compiler_gnu=$ac_cv_c_compiler_gnu { $as_echo "$as_me:${as_lineno-$LINENO}: checking how to run the C preprocessor" >&5 $as_echo_n "checking how to run the C preprocessor... " >&6; } # On Suns, sometimes $CPP names a directory. if test -n "$CPP" && test -d "$CPP"; then CPP= fi if test -z "$CPP"; then if ${ac_cv_prog_CPP+:} false; then : $as_echo_n "(cached) " >&6 else # Double quotes because CPP needs to be expanded for CPP in "$CC -E" "$CC -E -traditional-cpp" "/lib/cpp" do ac_preproc_ok=false for ac_c_preproc_warn_flag in '' yes do # Use a header file that comes with gcc, so configuring glibc # with a fresh cross-compiler works. # Prefer to if __STDC__ is defined, since # exists even on freestanding compilers. # On the NeXT, cc -E runs the code through the compiler's parser, # not just through cpp. "Syntax error" is here to catch this case. cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ #ifdef __STDC__ # include #else # include #endif Syntax error _ACEOF if ac_fn_c_try_cpp "$LINENO"; then : else # Broken: fails on valid input. continue fi rm -f conftest.err conftest.i conftest.$ac_ext # OK, works on sane cases. Now check whether nonexistent headers # can be detected and how. cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ #include _ACEOF if ac_fn_c_try_cpp "$LINENO"; then : # Broken: success on invalid input. continue else # Passes both tests. ac_preproc_ok=: break fi rm -f conftest.err conftest.i conftest.$ac_ext done # Because of `break', _AC_PREPROC_IFELSE's cleaning code was skipped. rm -f conftest.i conftest.err conftest.$ac_ext if $ac_preproc_ok; then : break fi done ac_cv_prog_CPP=$CPP fi CPP=$ac_cv_prog_CPP else ac_cv_prog_CPP=$CPP fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $CPP" >&5 $as_echo "$CPP" >&6; } ac_preproc_ok=false for ac_c_preproc_warn_flag in '' yes do # Use a header file that comes with gcc, so configuring glibc # with a fresh cross-compiler works. # Prefer to if __STDC__ is defined, since # exists even on freestanding compilers. # On the NeXT, cc -E runs the code through the compiler's parser, # not just through cpp. "Syntax error" is here to catch this case. cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ #ifdef __STDC__ # include #else # include #endif Syntax error _ACEOF if ac_fn_c_try_cpp "$LINENO"; then : else # Broken: fails on valid input. continue fi rm -f conftest.err conftest.i conftest.$ac_ext # OK, works on sane cases. Now check whether nonexistent headers # can be detected and how. cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ #include _ACEOF if ac_fn_c_try_cpp "$LINENO"; then : # Broken: success on invalid input. continue else # Passes both tests. ac_preproc_ok=: break fi rm -f conftest.err conftest.i conftest.$ac_ext done # Because of `break', _AC_PREPROC_IFELSE's cleaning code was skipped. rm -f conftest.i conftest.err conftest.$ac_ext if $ac_preproc_ok; then : else { { $as_echo "$as_me:${as_lineno-$LINENO}: error: in \`$ac_pwd':" >&5 $as_echo "$as_me: error: in \`$ac_pwd':" >&2;} as_fn_error $? "C preprocessor \"$CPP\" fails sanity check See \`config.log' for more details" "$LINENO" 5; } fi ac_ext=c ac_cpp='$CPP $CPPFLAGS' ac_compile='$CC -c $CFLAGS $CPPFLAGS conftest.$ac_ext >&5' ac_link='$CC -o conftest$ac_exeext $CFLAGS $CPPFLAGS $LDFLAGS conftest.$ac_ext $LIBS >&5' ac_compiler_gnu=$ac_cv_c_compiler_gnu # Make sure we can run config.sub. $SHELL "$ac_aux_dir/config.sub" sun4 >/dev/null 2>&1 || as_fn_error $? "cannot run $SHELL $ac_aux_dir/config.sub" "$LINENO" 5 { $as_echo "$as_me:${as_lineno-$LINENO}: checking build system type" >&5 $as_echo_n "checking build system type... " >&6; } if ${ac_cv_build+:} false; then : $as_echo_n "(cached) " >&6 else ac_build_alias=$build_alias test "x$ac_build_alias" = x && ac_build_alias=`$SHELL "$ac_aux_dir/config.guess"` test "x$ac_build_alias" = x && as_fn_error $? "cannot guess build type; you must specify one" "$LINENO" 5 ac_cv_build=`$SHELL "$ac_aux_dir/config.sub" $ac_build_alias` || as_fn_error $? "$SHELL $ac_aux_dir/config.sub $ac_build_alias failed" "$LINENO" 5 fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_cv_build" >&5 $as_echo "$ac_cv_build" >&6; } case $ac_cv_build in *-*-*) ;; *) as_fn_error $? "invalid value of canonical build" "$LINENO" 5;; esac build=$ac_cv_build ac_save_IFS=$IFS; IFS='-' set x $ac_cv_build shift build_cpu=$1 build_vendor=$2 shift; shift # Remember, the first character of IFS is used to create $*, # except with old shells: build_os=$* IFS=$ac_save_IFS case $build_os in *\ *) build_os=`echo "$build_os" | sed 's/ /-/g'`;; esac { $as_echo "$as_me:${as_lineno-$LINENO}: checking host system type" >&5 $as_echo_n "checking host system type... " >&6; } if ${ac_cv_host+:} false; then : $as_echo_n "(cached) " >&6 else if test "x$host_alias" = x; then ac_cv_host=$ac_cv_build else ac_cv_host=`$SHELL "$ac_aux_dir/config.sub" $host_alias` || as_fn_error $? "$SHELL $ac_aux_dir/config.sub $host_alias failed" "$LINENO" 5 fi fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_cv_host" >&5 $as_echo "$ac_cv_host" >&6; } case $ac_cv_host in *-*-*) ;; *) as_fn_error $? "invalid value of canonical host" "$LINENO" 5;; esac host=$ac_cv_host ac_save_IFS=$IFS; IFS='-' set x $ac_cv_host shift host_cpu=$1 host_vendor=$2 shift; shift # Remember, the first character of IFS is used to create $*, # except with old shells: host_os=$* IFS=$ac_save_IFS case $host_os in *\ *) host_os=`echo "$host_os" | sed 's/ /-/g'`;; esac { $as_echo "$as_me:${as_lineno-$LINENO}: checking host platform" >&5 $as_echo_n "checking host platform... " >&6; } sv_cv_host="$host" case "$host_os" in linux | linux-*) kernelversion=`uname -r | sed -e 's/^\([0-9.]*\).*/\1/'` sv_cv_host=`echo $sv_cv_host | sed -e "s/linux/linux$kernelversion/"` ;; esac cat > conftest.c << EOF #include #ifdef __GNU_LIBRARY__ Version __GLIBC__ . __GLIBC_MINOR__ #endif EOF glibcversion=`$CPP $CPPFLAGS conftest.c 2>/dev/null | grep Version | sed -e 's/Version//' -e 's/ //g'` if test -n "$glibcversion"; then sv_cv_host="$sv_cv_host-glibc$glibcversion" fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $sv_cv_host" >&5 $as_echo "$sv_cv_host" >&6; } PLATFORM="$sv_cv_host" { $as_echo "$as_me:${as_lineno-$LINENO}: checking for a sed that does not truncate output" >&5 $as_echo_n "checking for a sed that does not truncate output... " >&6; } if ${ac_cv_path_SED+:} false; then : $as_echo_n "(cached) " >&6 else ac_script=s/aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa/bbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbb/ for ac_i in 1 2 3 4 5 6 7; do ac_script="$ac_script$as_nl$ac_script" done echo "$ac_script" 2>/dev/null | sed 99q >conftest.sed { ac_script=; unset ac_script;} if test -z "$SED"; then ac_path_SED_found=false # Loop through the user's path and test for each of PROGNAME-LIST as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_prog in sed gsed; do for ac_exec_ext in '' $ac_executable_extensions; do ac_path_SED="$as_dir/$ac_prog$ac_exec_ext" as_fn_executable_p "$ac_path_SED" || continue # Check for GNU ac_path_SED and select it if it is found. # Check for GNU $ac_path_SED case `"$ac_path_SED" --version 2>&1` in *GNU*) ac_cv_path_SED="$ac_path_SED" ac_path_SED_found=:;; *) ac_count=0 $as_echo_n 0123456789 >"conftest.in" while : do cat "conftest.in" "conftest.in" >"conftest.tmp" mv "conftest.tmp" "conftest.in" cp "conftest.in" "conftest.nl" $as_echo '' >> "conftest.nl" "$ac_path_SED" -f conftest.sed < "conftest.nl" >"conftest.out" 2>/dev/null || break diff "conftest.out" "conftest.nl" >/dev/null 2>&1 || break as_fn_arith $ac_count + 1 && ac_count=$as_val if test $ac_count -gt ${ac_path_SED_max-0}; then # Best one so far, save it but keep looking for a better one ac_cv_path_SED="$ac_path_SED" ac_path_SED_max=$ac_count fi # 10*(2^10) chars as input seems more than enough test $ac_count -gt 10 && break done rm -f conftest.in conftest.tmp conftest.nl conftest.out;; esac $ac_path_SED_found && break 3 done done done IFS=$as_save_IFS if test -z "$ac_cv_path_SED"; then as_fn_error $? "no acceptable sed could be found in \$PATH" "$LINENO" 5 fi else ac_cv_path_SED=$SED fi fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_cv_path_SED" >&5 $as_echo "$ac_cv_path_SED" >&6; } SED="$ac_cv_path_SED" rm -f conftest.sed case `pwd` in *\ * | *\ *) { $as_echo "$as_me:${as_lineno-$LINENO}: WARNING: Libtool does not cope well with whitespace in \`pwd\`" >&5 $as_echo "$as_me: WARNING: Libtool does not cope well with whitespace in \`pwd\`" >&2;} ;; esac macro_version='2.4.2' macro_revision='1.3337' ltmain="$ac_aux_dir/ltmain.sh" # Backslashify metacharacters that are still active within # double-quoted strings. sed_quote_subst='s/\(["`$\\]\)/\\\1/g' # Same as above, but do not quote variable references. double_quote_subst='s/\(["`\\]\)/\\\1/g' # Sed substitution to delay expansion of an escaped shell variable in a # double_quote_subst'ed string. delay_variable_subst='s/\\\\\\\\\\\$/\\\\\\$/g' # Sed substitution to delay expansion of an escaped single quote. delay_single_quote_subst='s/'\''/'\'\\\\\\\'\''/g' # Sed substitution to avoid accidental globbing in evaled expressions no_glob_subst='s/\*/\\\*/g' ECHO='\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\' ECHO=$ECHO$ECHO$ECHO$ECHO$ECHO ECHO=$ECHO$ECHO$ECHO$ECHO$ECHO$ECHO { $as_echo "$as_me:${as_lineno-$LINENO}: checking how to print strings" >&5 $as_echo_n "checking how to print strings... " >&6; } # Test print first, because it will be a builtin if present. if test "X`( print -r -- -n ) 2>/dev/null`" = X-n && \ test "X`print -r -- $ECHO 2>/dev/null`" = "X$ECHO"; then ECHO='print -r --' elif test "X`printf %s $ECHO 2>/dev/null`" = "X$ECHO"; then ECHO='printf %s\n' else # Use this function as a fallback that always works. func_fallback_echo () { eval 'cat <<_LTECHO_EOF $1 _LTECHO_EOF' } ECHO='func_fallback_echo' fi # func_echo_all arg... # Invoke $ECHO with all args, space-separated. func_echo_all () { $ECHO "" } case "$ECHO" in printf*) { $as_echo "$as_me:${as_lineno-$LINENO}: result: printf" >&5 $as_echo "printf" >&6; } ;; print*) { $as_echo "$as_me:${as_lineno-$LINENO}: result: print -r" >&5 $as_echo "print -r" >&6; } ;; *) { $as_echo "$as_me:${as_lineno-$LINENO}: result: cat" >&5 $as_echo "cat" >&6; } ;; esac { $as_echo "$as_me:${as_lineno-$LINENO}: checking for a sed that does not truncate output" >&5 $as_echo_n "checking for a sed that does not truncate output... " >&6; } if ${ac_cv_path_SED+:} false; then : $as_echo_n "(cached) " >&6 else ac_script=s/aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa/bbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbb/ for ac_i in 1 2 3 4 5 6 7; do ac_script="$ac_script$as_nl$ac_script" done echo "$ac_script" 2>/dev/null | sed 99q >conftest.sed { ac_script=; unset ac_script;} if test -z "$SED"; then ac_path_SED_found=false # Loop through the user's path and test for each of PROGNAME-LIST as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_prog in sed gsed; do for ac_exec_ext in '' $ac_executable_extensions; do ac_path_SED="$as_dir/$ac_prog$ac_exec_ext" as_fn_executable_p "$ac_path_SED" || continue # Check for GNU ac_path_SED and select it if it is found. # Check for GNU $ac_path_SED case `"$ac_path_SED" --version 2>&1` in *GNU*) ac_cv_path_SED="$ac_path_SED" ac_path_SED_found=:;; *) ac_count=0 $as_echo_n 0123456789 >"conftest.in" while : do cat "conftest.in" "conftest.in" >"conftest.tmp" mv "conftest.tmp" "conftest.in" cp "conftest.in" "conftest.nl" $as_echo '' >> "conftest.nl" "$ac_path_SED" -f conftest.sed < "conftest.nl" >"conftest.out" 2>/dev/null || break diff "conftest.out" "conftest.nl" >/dev/null 2>&1 || break as_fn_arith $ac_count + 1 && ac_count=$as_val if test $ac_count -gt ${ac_path_SED_max-0}; then # Best one so far, save it but keep looking for a better one ac_cv_path_SED="$ac_path_SED" ac_path_SED_max=$ac_count fi # 10*(2^10) chars as input seems more than enough test $ac_count -gt 10 && break done rm -f conftest.in conftest.tmp conftest.nl conftest.out;; esac $ac_path_SED_found && break 3 done done done IFS=$as_save_IFS if test -z "$ac_cv_path_SED"; then as_fn_error $? "no acceptable sed could be found in \$PATH" "$LINENO" 5 fi else ac_cv_path_SED=$SED fi fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_cv_path_SED" >&5 $as_echo "$ac_cv_path_SED" >&6; } SED="$ac_cv_path_SED" rm -f conftest.sed test -z "$SED" && SED=sed Xsed="$SED -e 1s/^X//" { $as_echo "$as_me:${as_lineno-$LINENO}: checking for grep that handles long lines and -e" >&5 $as_echo_n "checking for grep that handles long lines and -e... " >&6; } if ${ac_cv_path_GREP+:} false; then : $as_echo_n "(cached) " >&6 else if test -z "$GREP"; then ac_path_GREP_found=false # Loop through the user's path and test for each of PROGNAME-LIST as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH$PATH_SEPARATOR/usr/xpg4/bin do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_prog in grep ggrep; do for ac_exec_ext in '' $ac_executable_extensions; do ac_path_GREP="$as_dir/$ac_prog$ac_exec_ext" as_fn_executable_p "$ac_path_GREP" || continue # Check for GNU ac_path_GREP and select it if it is found. # Check for GNU $ac_path_GREP case `"$ac_path_GREP" --version 2>&1` in *GNU*) ac_cv_path_GREP="$ac_path_GREP" ac_path_GREP_found=:;; *) ac_count=0 $as_echo_n 0123456789 >"conftest.in" while : do cat "conftest.in" "conftest.in" >"conftest.tmp" mv "conftest.tmp" "conftest.in" cp "conftest.in" "conftest.nl" $as_echo 'GREP' >> "conftest.nl" "$ac_path_GREP" -e 'GREP$' -e '-(cannot match)-' < "conftest.nl" >"conftest.out" 2>/dev/null || break diff "conftest.out" "conftest.nl" >/dev/null 2>&1 || break as_fn_arith $ac_count + 1 && ac_count=$as_val if test $ac_count -gt ${ac_path_GREP_max-0}; then # Best one so far, save it but keep looking for a better one ac_cv_path_GREP="$ac_path_GREP" ac_path_GREP_max=$ac_count fi # 10*(2^10) chars as input seems more than enough test $ac_count -gt 10 && break done rm -f conftest.in conftest.tmp conftest.nl conftest.out;; esac $ac_path_GREP_found && break 3 done done done IFS=$as_save_IFS if test -z "$ac_cv_path_GREP"; then as_fn_error $? "no acceptable grep could be found in $PATH$PATH_SEPARATOR/usr/xpg4/bin" "$LINENO" 5 fi else ac_cv_path_GREP=$GREP fi fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_cv_path_GREP" >&5 $as_echo "$ac_cv_path_GREP" >&6; } GREP="$ac_cv_path_GREP" { $as_echo "$as_me:${as_lineno-$LINENO}: checking for egrep" >&5 $as_echo_n "checking for egrep... " >&6; } if ${ac_cv_path_EGREP+:} false; then : $as_echo_n "(cached) " >&6 else if echo a | $GREP -E '(a|b)' >/dev/null 2>&1 then ac_cv_path_EGREP="$GREP -E" else if test -z "$EGREP"; then ac_path_EGREP_found=false # Loop through the user's path and test for each of PROGNAME-LIST as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH$PATH_SEPARATOR/usr/xpg4/bin do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_prog in egrep; do for ac_exec_ext in '' $ac_executable_extensions; do ac_path_EGREP="$as_dir/$ac_prog$ac_exec_ext" as_fn_executable_p "$ac_path_EGREP" || continue # Check for GNU ac_path_EGREP and select it if it is found. # Check for GNU $ac_path_EGREP case `"$ac_path_EGREP" --version 2>&1` in *GNU*) ac_cv_path_EGREP="$ac_path_EGREP" ac_path_EGREP_found=:;; *) ac_count=0 $as_echo_n 0123456789 >"conftest.in" while : do cat "conftest.in" "conftest.in" >"conftest.tmp" mv "conftest.tmp" "conftest.in" cp "conftest.in" "conftest.nl" $as_echo 'EGREP' >> "conftest.nl" "$ac_path_EGREP" 'EGREP$' < "conftest.nl" >"conftest.out" 2>/dev/null || break diff "conftest.out" "conftest.nl" >/dev/null 2>&1 || break as_fn_arith $ac_count + 1 && ac_count=$as_val if test $ac_count -gt ${ac_path_EGREP_max-0}; then # Best one so far, save it but keep looking for a better one ac_cv_path_EGREP="$ac_path_EGREP" ac_path_EGREP_max=$ac_count fi # 10*(2^10) chars as input seems more than enough test $ac_count -gt 10 && break done rm -f conftest.in conftest.tmp conftest.nl conftest.out;; esac $ac_path_EGREP_found && break 3 done done done IFS=$as_save_IFS if test -z "$ac_cv_path_EGREP"; then as_fn_error $? "no acceptable egrep could be found in $PATH$PATH_SEPARATOR/usr/xpg4/bin" "$LINENO" 5 fi else ac_cv_path_EGREP=$EGREP fi fi fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_cv_path_EGREP" >&5 $as_echo "$ac_cv_path_EGREP" >&6; } EGREP="$ac_cv_path_EGREP" { $as_echo "$as_me:${as_lineno-$LINENO}: checking for fgrep" >&5 $as_echo_n "checking for fgrep... " >&6; } if ${ac_cv_path_FGREP+:} false; then : $as_echo_n "(cached) " >&6 else if echo 'ab*c' | $GREP -F 'ab*c' >/dev/null 2>&1 then ac_cv_path_FGREP="$GREP -F" else if test -z "$FGREP"; then ac_path_FGREP_found=false # Loop through the user's path and test for each of PROGNAME-LIST as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH$PATH_SEPARATOR/usr/xpg4/bin do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_prog in fgrep; do for ac_exec_ext in '' $ac_executable_extensions; do ac_path_FGREP="$as_dir/$ac_prog$ac_exec_ext" as_fn_executable_p "$ac_path_FGREP" || continue # Check for GNU ac_path_FGREP and select it if it is found. # Check for GNU $ac_path_FGREP case `"$ac_path_FGREP" --version 2>&1` in *GNU*) ac_cv_path_FGREP="$ac_path_FGREP" ac_path_FGREP_found=:;; *) ac_count=0 $as_echo_n 0123456789 >"conftest.in" while : do cat "conftest.in" "conftest.in" >"conftest.tmp" mv "conftest.tmp" "conftest.in" cp "conftest.in" "conftest.nl" $as_echo 'FGREP' >> "conftest.nl" "$ac_path_FGREP" FGREP < "conftest.nl" >"conftest.out" 2>/dev/null || break diff "conftest.out" "conftest.nl" >/dev/null 2>&1 || break as_fn_arith $ac_count + 1 && ac_count=$as_val if test $ac_count -gt ${ac_path_FGREP_max-0}; then # Best one so far, save it but keep looking for a better one ac_cv_path_FGREP="$ac_path_FGREP" ac_path_FGREP_max=$ac_count fi # 10*(2^10) chars as input seems more than enough test $ac_count -gt 10 && break done rm -f conftest.in conftest.tmp conftest.nl conftest.out;; esac $ac_path_FGREP_found && break 3 done done done IFS=$as_save_IFS if test -z "$ac_cv_path_FGREP"; then as_fn_error $? "no acceptable fgrep could be found in $PATH$PATH_SEPARATOR/usr/xpg4/bin" "$LINENO" 5 fi else ac_cv_path_FGREP=$FGREP fi fi fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_cv_path_FGREP" >&5 $as_echo "$ac_cv_path_FGREP" >&6; } FGREP="$ac_cv_path_FGREP" test -z "$GREP" && GREP=grep # Check whether --with-gnu-ld was given. if test "${with_gnu_ld+set}" = set; then : withval=$with_gnu_ld; test "$withval" = no || with_gnu_ld=yes else with_gnu_ld=no fi ac_prog=ld if test "$GCC" = yes; then # Check if gcc -print-prog-name=ld gives a path. { $as_echo "$as_me:${as_lineno-$LINENO}: checking for ld used by $CC" >&5 $as_echo_n "checking for ld used by $CC... " >&6; } case $host in *-*-mingw*) # gcc leaves a trailing carriage return which upsets mingw ac_prog=`($CC -print-prog-name=ld) 2>&5 | tr -d '\015'` ;; *) ac_prog=`($CC -print-prog-name=ld) 2>&5` ;; esac case $ac_prog in # Accept absolute paths. [\\/]* | ?:[\\/]*) re_direlt='/[^/][^/]*/\.\./' # Canonicalize the pathname of ld ac_prog=`$ECHO "$ac_prog"| $SED 's%\\\\%/%g'` while $ECHO "$ac_prog" | $GREP "$re_direlt" > /dev/null 2>&1; do ac_prog=`$ECHO $ac_prog| $SED "s%$re_direlt%/%"` done test -z "$LD" && LD="$ac_prog" ;; "") # If it fails, then pretend we aren't using GCC. ac_prog=ld ;; *) # If it is relative, then search for the first ld in PATH. with_gnu_ld=unknown ;; esac elif test "$with_gnu_ld" = yes; then { $as_echo "$as_me:${as_lineno-$LINENO}: checking for GNU ld" >&5 $as_echo_n "checking for GNU ld... " >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: checking for non-GNU ld" >&5 $as_echo_n "checking for non-GNU ld... " >&6; } fi if ${lt_cv_path_LD+:} false; then : $as_echo_n "(cached) " >&6 else if test -z "$LD"; then lt_save_ifs="$IFS"; IFS=$PATH_SEPARATOR for ac_dir in $PATH; do IFS="$lt_save_ifs" test -z "$ac_dir" && ac_dir=. if test -f "$ac_dir/$ac_prog" || test -f "$ac_dir/$ac_prog$ac_exeext"; then lt_cv_path_LD="$ac_dir/$ac_prog" # Check to see if the program is GNU ld. I'd rather use --version, # but apparently some variants of GNU ld only accept -v. # Break only if it was the GNU/non-GNU ld that we prefer. case `"$lt_cv_path_LD" -v 2>&1 &5 $as_echo "$LD" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi test -z "$LD" && as_fn_error $? "no acceptable ld found in \$PATH" "$LINENO" 5 { $as_echo "$as_me:${as_lineno-$LINENO}: checking if the linker ($LD) is GNU ld" >&5 $as_echo_n "checking if the linker ($LD) is GNU ld... " >&6; } if ${lt_cv_prog_gnu_ld+:} false; then : $as_echo_n "(cached) " >&6 else # I'd rather use --version here, but apparently some GNU lds only accept -v. case `$LD -v 2>&1 &5 $as_echo "$lt_cv_prog_gnu_ld" >&6; } with_gnu_ld=$lt_cv_prog_gnu_ld { $as_echo "$as_me:${as_lineno-$LINENO}: checking for BSD- or MS-compatible name lister (nm)" >&5 $as_echo_n "checking for BSD- or MS-compatible name lister (nm)... " >&6; } if ${lt_cv_path_NM+:} false; then : $as_echo_n "(cached) " >&6 else if test -n "$NM"; then # Let the user override the test. lt_cv_path_NM="$NM" else lt_nm_to_check="${ac_tool_prefix}nm" if test -n "$ac_tool_prefix" && test "$build" = "$host"; then lt_nm_to_check="$lt_nm_to_check nm" fi for lt_tmp_nm in $lt_nm_to_check; do lt_save_ifs="$IFS"; IFS=$PATH_SEPARATOR for ac_dir in $PATH /usr/ccs/bin/elf /usr/ccs/bin /usr/ucb /bin; do IFS="$lt_save_ifs" test -z "$ac_dir" && ac_dir=. tmp_nm="$ac_dir/$lt_tmp_nm" if test -f "$tmp_nm" || test -f "$tmp_nm$ac_exeext" ; then # Check to see if the nm accepts a BSD-compat flag. # Adding the `sed 1q' prevents false positives on HP-UX, which says: # nm: unknown option "B" ignored # Tru64's nm complains that /dev/null is an invalid object file case `"$tmp_nm" -B /dev/null 2>&1 | sed '1q'` in */dev/null* | *'Invalid file or object type'*) lt_cv_path_NM="$tmp_nm -B" break ;; *) case `"$tmp_nm" -p /dev/null 2>&1 | sed '1q'` in */dev/null*) lt_cv_path_NM="$tmp_nm -p" break ;; *) lt_cv_path_NM=${lt_cv_path_NM="$tmp_nm"} # keep the first match, but continue # so that we can try to find one that supports BSD flags ;; esac ;; esac fi done IFS="$lt_save_ifs" done : ${lt_cv_path_NM=no} fi fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $lt_cv_path_NM" >&5 $as_echo "$lt_cv_path_NM" >&6; } if test "$lt_cv_path_NM" != "no"; then NM="$lt_cv_path_NM" else # Didn't find any BSD compatible name lister, look for dumpbin. if test -n "$DUMPBIN"; then : # Let the user override the test. else if test -n "$ac_tool_prefix"; then for ac_prog in dumpbin "link -dump" do # Extract the first word of "$ac_tool_prefix$ac_prog", so it can be a program name with args. set dummy $ac_tool_prefix$ac_prog; ac_word=$2 { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $ac_word" >&5 $as_echo_n "checking for $ac_word... " >&6; } if ${ac_cv_prog_DUMPBIN+:} false; then : $as_echo_n "(cached) " >&6 else if test -n "$DUMPBIN"; then ac_cv_prog_DUMPBIN="$DUMPBIN" # Let the user override the test. else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_exec_ext in '' $ac_executable_extensions; do if as_fn_executable_p "$as_dir/$ac_word$ac_exec_ext"; then ac_cv_prog_DUMPBIN="$ac_tool_prefix$ac_prog" $as_echo "$as_me:${as_lineno-$LINENO}: found $as_dir/$ac_word$ac_exec_ext" >&5 break 2 fi done done IFS=$as_save_IFS fi fi DUMPBIN=$ac_cv_prog_DUMPBIN if test -n "$DUMPBIN"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $DUMPBIN" >&5 $as_echo "$DUMPBIN" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi test -n "$DUMPBIN" && break done fi if test -z "$DUMPBIN"; then ac_ct_DUMPBIN=$DUMPBIN for ac_prog in dumpbin "link -dump" do # Extract the first word of "$ac_prog", so it can be a program name with args. set dummy $ac_prog; ac_word=$2 { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $ac_word" >&5 $as_echo_n "checking for $ac_word... " >&6; } if ${ac_cv_prog_ac_ct_DUMPBIN+:} false; then : $as_echo_n "(cached) " >&6 else if test -n "$ac_ct_DUMPBIN"; then ac_cv_prog_ac_ct_DUMPBIN="$ac_ct_DUMPBIN" # Let the user override the test. else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_exec_ext in '' $ac_executable_extensions; do if as_fn_executable_p "$as_dir/$ac_word$ac_exec_ext"; then ac_cv_prog_ac_ct_DUMPBIN="$ac_prog" $as_echo "$as_me:${as_lineno-$LINENO}: found $as_dir/$ac_word$ac_exec_ext" >&5 break 2 fi done done IFS=$as_save_IFS fi fi ac_ct_DUMPBIN=$ac_cv_prog_ac_ct_DUMPBIN if test -n "$ac_ct_DUMPBIN"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_ct_DUMPBIN" >&5 $as_echo "$ac_ct_DUMPBIN" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi test -n "$ac_ct_DUMPBIN" && break done if test "x$ac_ct_DUMPBIN" = x; then DUMPBIN=":" else case $cross_compiling:$ac_tool_warned in yes:) { $as_echo "$as_me:${as_lineno-$LINENO}: WARNING: using cross tools not prefixed with host triplet" >&5 $as_echo "$as_me: WARNING: using cross tools not prefixed with host triplet" >&2;} ac_tool_warned=yes ;; esac DUMPBIN=$ac_ct_DUMPBIN fi fi case `$DUMPBIN -symbols /dev/null 2>&1 | sed '1q'` in *COFF*) DUMPBIN="$DUMPBIN -symbols" ;; *) DUMPBIN=: ;; esac fi if test "$DUMPBIN" != ":"; then NM="$DUMPBIN" fi fi test -z "$NM" && NM=nm { $as_echo "$as_me:${as_lineno-$LINENO}: checking the name lister ($NM) interface" >&5 $as_echo_n "checking the name lister ($NM) interface... " >&6; } if ${lt_cv_nm_interface+:} false; then : $as_echo_n "(cached) " >&6 else lt_cv_nm_interface="BSD nm" echo "int some_variable = 0;" > conftest.$ac_ext (eval echo "\"\$as_me:$LINENO: $ac_compile\"" >&5) (eval "$ac_compile" 2>conftest.err) cat conftest.err >&5 (eval echo "\"\$as_me:$LINENO: $NM \\\"conftest.$ac_objext\\\"\"" >&5) (eval "$NM \"conftest.$ac_objext\"" 2>conftest.err > conftest.out) cat conftest.err >&5 (eval echo "\"\$as_me:$LINENO: output\"" >&5) cat conftest.out >&5 if $GREP 'External.*some_variable' conftest.out > /dev/null; then lt_cv_nm_interface="MS dumpbin" fi rm -f conftest* fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $lt_cv_nm_interface" >&5 $as_echo "$lt_cv_nm_interface" >&6; } { $as_echo "$as_me:${as_lineno-$LINENO}: checking whether ln -s works" >&5 $as_echo_n "checking whether ln -s works... " >&6; } LN_S=$as_ln_s if test "$LN_S" = "ln -s"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: yes" >&5 $as_echo "yes" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no, using $LN_S" >&5 $as_echo "no, using $LN_S" >&6; } fi # find the maximum length of command line arguments { $as_echo "$as_me:${as_lineno-$LINENO}: checking the maximum length of command line arguments" >&5 $as_echo_n "checking the maximum length of command line arguments... " >&6; } if ${lt_cv_sys_max_cmd_len+:} false; then : $as_echo_n "(cached) " >&6 else i=0 teststring="ABCD" case $build_os in msdosdjgpp*) # On DJGPP, this test can blow up pretty badly due to problems in libc # (any single argument exceeding 2000 bytes causes a buffer overrun # during glob expansion). Even if it were fixed, the result of this # check would be larger than it should be. lt_cv_sys_max_cmd_len=12288; # 12K is about right ;; gnu*) # Under GNU Hurd, this test is not required because there is # no limit to the length of command line arguments. # Libtool will interpret -1 as no limit whatsoever lt_cv_sys_max_cmd_len=-1; ;; cygwin* | mingw* | cegcc*) # On Win9x/ME, this test blows up -- it succeeds, but takes # about 5 minutes as the teststring grows exponentially. # Worse, since 9x/ME are not pre-emptively multitasking, # you end up with a "frozen" computer, even though with patience # the test eventually succeeds (with a max line length of 256k). # Instead, let's just punt: use the minimum linelength reported by # all of the supported platforms: 8192 (on NT/2K/XP). lt_cv_sys_max_cmd_len=8192; ;; mint*) # On MiNT this can take a long time and run out of memory. lt_cv_sys_max_cmd_len=8192; ;; amigaos*) # On AmigaOS with pdksh, this test takes hours, literally. # So we just punt and use a minimum line length of 8192. lt_cv_sys_max_cmd_len=8192; ;; netbsd* | freebsd* | openbsd* | darwin* | dragonfly*) # This has been around since 386BSD, at least. Likely further. if test -x /sbin/sysctl; then lt_cv_sys_max_cmd_len=`/sbin/sysctl -n kern.argmax` elif test -x /usr/sbin/sysctl; then lt_cv_sys_max_cmd_len=`/usr/sbin/sysctl -n kern.argmax` else lt_cv_sys_max_cmd_len=65536 # usable default for all BSDs fi # And add a safety zone lt_cv_sys_max_cmd_len=`expr $lt_cv_sys_max_cmd_len \/ 4` lt_cv_sys_max_cmd_len=`expr $lt_cv_sys_max_cmd_len \* 3` ;; interix*) # We know the value 262144 and hardcode it with a safety zone (like BSD) lt_cv_sys_max_cmd_len=196608 ;; os2*) # The test takes a long time on OS/2. lt_cv_sys_max_cmd_len=8192 ;; osf*) # Dr. Hans Ekkehard Plesser reports seeing a kernel panic running configure # due to this test when exec_disable_arg_limit is 1 on Tru64. It is not # nice to cause kernel panics so lets avoid the loop below. # First set a reasonable default. lt_cv_sys_max_cmd_len=16384 # if test -x /sbin/sysconfig; then case `/sbin/sysconfig -q proc exec_disable_arg_limit` in *1*) lt_cv_sys_max_cmd_len=-1 ;; esac fi ;; sco3.2v5*) lt_cv_sys_max_cmd_len=102400 ;; sysv5* | sco5v6* | sysv4.2uw2*) kargmax=`grep ARG_MAX /etc/conf/cf.d/stune 2>/dev/null` if test -n "$kargmax"; then lt_cv_sys_max_cmd_len=`echo $kargmax | sed 's/.*[ ]//'` else lt_cv_sys_max_cmd_len=32768 fi ;; *) lt_cv_sys_max_cmd_len=`(getconf ARG_MAX) 2> /dev/null` if test -n "$lt_cv_sys_max_cmd_len" && \ test undefined != "$lt_cv_sys_max_cmd_len"; then lt_cv_sys_max_cmd_len=`expr $lt_cv_sys_max_cmd_len \/ 4` lt_cv_sys_max_cmd_len=`expr $lt_cv_sys_max_cmd_len \* 3` else # Make teststring a little bigger before we do anything with it. # a 1K string should be a reasonable start. for i in 1 2 3 4 5 6 7 8 ; do teststring=$teststring$teststring done SHELL=${SHELL-${CONFIG_SHELL-/bin/sh}} # If test is not a shell built-in, we'll probably end up computing a # maximum length that is only half of the actual maximum length, but # we can't tell. while { test "X"`env echo "$teststring$teststring" 2>/dev/null` \ = "X$teststring$teststring"; } >/dev/null 2>&1 && test $i != 17 # 1/2 MB should be enough do i=`expr $i + 1` teststring=$teststring$teststring done # Only check the string length outside the loop. lt_cv_sys_max_cmd_len=`expr "X$teststring" : ".*" 2>&1` teststring= # Add a significant safety factor because C++ compilers can tack on # massive amounts of additional arguments before passing them to the # linker. It appears as though 1/2 is a usable value. lt_cv_sys_max_cmd_len=`expr $lt_cv_sys_max_cmd_len \/ 2` fi ;; esac fi if test -n $lt_cv_sys_max_cmd_len ; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $lt_cv_sys_max_cmd_len" >&5 $as_echo "$lt_cv_sys_max_cmd_len" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: none" >&5 $as_echo "none" >&6; } fi max_cmd_len=$lt_cv_sys_max_cmd_len : ${CP="cp -f"} : ${MV="mv -f"} : ${RM="rm -f"} { $as_echo "$as_me:${as_lineno-$LINENO}: checking whether the shell understands some XSI constructs" >&5 $as_echo_n "checking whether the shell understands some XSI constructs... " >&6; } # Try some XSI features xsi_shell=no ( _lt_dummy="a/b/c" test "${_lt_dummy##*/},${_lt_dummy%/*},${_lt_dummy#??}"${_lt_dummy%"$_lt_dummy"}, \ = c,a/b,b/c, \ && eval 'test $(( 1 + 1 )) -eq 2 \ && test "${#_lt_dummy}" -eq 5' ) >/dev/null 2>&1 \ && xsi_shell=yes { $as_echo "$as_me:${as_lineno-$LINENO}: result: $xsi_shell" >&5 $as_echo "$xsi_shell" >&6; } { $as_echo "$as_me:${as_lineno-$LINENO}: checking whether the shell understands \"+=\"" >&5 $as_echo_n "checking whether the shell understands \"+=\"... " >&6; } lt_shell_append=no ( foo=bar; set foo baz; eval "$1+=\$2" && test "$foo" = barbaz ) \ >/dev/null 2>&1 \ && lt_shell_append=yes { $as_echo "$as_me:${as_lineno-$LINENO}: result: $lt_shell_append" >&5 $as_echo "$lt_shell_append" >&6; } if ( (MAIL=60; unset MAIL) || exit) >/dev/null 2>&1; then lt_unset=unset else lt_unset=false fi # test EBCDIC or ASCII case `echo X|tr X '\101'` in A) # ASCII based system # \n is not interpreted correctly by Solaris 8 /usr/ucb/tr lt_SP2NL='tr \040 \012' lt_NL2SP='tr \015\012 \040\040' ;; *) # EBCDIC based system lt_SP2NL='tr \100 \n' lt_NL2SP='tr \r\n \100\100' ;; esac { $as_echo "$as_me:${as_lineno-$LINENO}: checking how to convert $build file names to $host format" >&5 $as_echo_n "checking how to convert $build file names to $host format... " >&6; } if ${lt_cv_to_host_file_cmd+:} false; then : $as_echo_n "(cached) " >&6 else case $host in *-*-mingw* ) case $build in *-*-mingw* ) # actually msys lt_cv_to_host_file_cmd=func_convert_file_msys_to_w32 ;; *-*-cygwin* ) lt_cv_to_host_file_cmd=func_convert_file_cygwin_to_w32 ;; * ) # otherwise, assume *nix lt_cv_to_host_file_cmd=func_convert_file_nix_to_w32 ;; esac ;; *-*-cygwin* ) case $build in *-*-mingw* ) # actually msys lt_cv_to_host_file_cmd=func_convert_file_msys_to_cygwin ;; *-*-cygwin* ) lt_cv_to_host_file_cmd=func_convert_file_noop ;; * ) # otherwise, assume *nix lt_cv_to_host_file_cmd=func_convert_file_nix_to_cygwin ;; esac ;; * ) # unhandled hosts (and "normal" native builds) lt_cv_to_host_file_cmd=func_convert_file_noop ;; esac fi to_host_file_cmd=$lt_cv_to_host_file_cmd { $as_echo "$as_me:${as_lineno-$LINENO}: result: $lt_cv_to_host_file_cmd" >&5 $as_echo "$lt_cv_to_host_file_cmd" >&6; } { $as_echo "$as_me:${as_lineno-$LINENO}: checking how to convert $build file names to toolchain format" >&5 $as_echo_n "checking how to convert $build file names to toolchain format... " >&6; } if ${lt_cv_to_tool_file_cmd+:} false; then : $as_echo_n "(cached) " >&6 else #assume ordinary cross tools, or native build. lt_cv_to_tool_file_cmd=func_convert_file_noop case $host in *-*-mingw* ) case $build in *-*-mingw* ) # actually msys lt_cv_to_tool_file_cmd=func_convert_file_msys_to_w32 ;; esac ;; esac fi to_tool_file_cmd=$lt_cv_to_tool_file_cmd { $as_echo "$as_me:${as_lineno-$LINENO}: result: $lt_cv_to_tool_file_cmd" >&5 $as_echo "$lt_cv_to_tool_file_cmd" >&6; } { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $LD option to reload object files" >&5 $as_echo_n "checking for $LD option to reload object files... " >&6; } if ${lt_cv_ld_reload_flag+:} false; then : $as_echo_n "(cached) " >&6 else lt_cv_ld_reload_flag='-r' fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $lt_cv_ld_reload_flag" >&5 $as_echo "$lt_cv_ld_reload_flag" >&6; } reload_flag=$lt_cv_ld_reload_flag case $reload_flag in "" | " "*) ;; *) reload_flag=" $reload_flag" ;; esac reload_cmds='$LD$reload_flag -o $output$reload_objs' case $host_os in cygwin* | mingw* | pw32* | cegcc*) if test "$GCC" != yes; then reload_cmds=false fi ;; darwin*) if test "$GCC" = yes; then reload_cmds='$LTCC $LTCFLAGS -nostdlib ${wl}-r -o $output$reload_objs' else reload_cmds='$LD$reload_flag -o $output$reload_objs' fi ;; esac if test -n "$ac_tool_prefix"; then # Extract the first word of "${ac_tool_prefix}objdump", so it can be a program name with args. set dummy ${ac_tool_prefix}objdump; ac_word=$2 { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $ac_word" >&5 $as_echo_n "checking for $ac_word... " >&6; } if ${ac_cv_prog_OBJDUMP+:} false; then : $as_echo_n "(cached) " >&6 else if test -n "$OBJDUMP"; then ac_cv_prog_OBJDUMP="$OBJDUMP" # Let the user override the test. else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_exec_ext in '' $ac_executable_extensions; do if as_fn_executable_p "$as_dir/$ac_word$ac_exec_ext"; then ac_cv_prog_OBJDUMP="${ac_tool_prefix}objdump" $as_echo "$as_me:${as_lineno-$LINENO}: found $as_dir/$ac_word$ac_exec_ext" >&5 break 2 fi done done IFS=$as_save_IFS fi fi OBJDUMP=$ac_cv_prog_OBJDUMP if test -n "$OBJDUMP"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $OBJDUMP" >&5 $as_echo "$OBJDUMP" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi fi if test -z "$ac_cv_prog_OBJDUMP"; then ac_ct_OBJDUMP=$OBJDUMP # Extract the first word of "objdump", so it can be a program name with args. set dummy objdump; ac_word=$2 { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $ac_word" >&5 $as_echo_n "checking for $ac_word... " >&6; } if ${ac_cv_prog_ac_ct_OBJDUMP+:} false; then : $as_echo_n "(cached) " >&6 else if test -n "$ac_ct_OBJDUMP"; then ac_cv_prog_ac_ct_OBJDUMP="$ac_ct_OBJDUMP" # Let the user override the test. else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_exec_ext in '' $ac_executable_extensions; do if as_fn_executable_p "$as_dir/$ac_word$ac_exec_ext"; then ac_cv_prog_ac_ct_OBJDUMP="objdump" $as_echo "$as_me:${as_lineno-$LINENO}: found $as_dir/$ac_word$ac_exec_ext" >&5 break 2 fi done done IFS=$as_save_IFS fi fi ac_ct_OBJDUMP=$ac_cv_prog_ac_ct_OBJDUMP if test -n "$ac_ct_OBJDUMP"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_ct_OBJDUMP" >&5 $as_echo "$ac_ct_OBJDUMP" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi if test "x$ac_ct_OBJDUMP" = x; then OBJDUMP="false" else case $cross_compiling:$ac_tool_warned in yes:) { $as_echo "$as_me:${as_lineno-$LINENO}: WARNING: using cross tools not prefixed with host triplet" >&5 $as_echo "$as_me: WARNING: using cross tools not prefixed with host triplet" >&2;} ac_tool_warned=yes ;; esac OBJDUMP=$ac_ct_OBJDUMP fi else OBJDUMP="$ac_cv_prog_OBJDUMP" fi test -z "$OBJDUMP" && OBJDUMP=objdump { $as_echo "$as_me:${as_lineno-$LINENO}: checking how to recognize dependent libraries" >&5 $as_echo_n "checking how to recognize dependent libraries... " >&6; } if ${lt_cv_deplibs_check_method+:} false; then : $as_echo_n "(cached) " >&6 else lt_cv_file_magic_cmd='$MAGIC_CMD' lt_cv_file_magic_test_file= lt_cv_deplibs_check_method='unknown' # Need to set the preceding variable on all platforms that support # interlibrary dependencies. # 'none' -- dependencies not supported. # `unknown' -- same as none, but documents that we really don't know. # 'pass_all' -- all dependencies passed with no checks. # 'test_compile' -- check by making test program. # 'file_magic [[regex]]' -- check by looking for files in library path # which responds to the $file_magic_cmd with a given extended regex. # If you have `file' or equivalent on your system and you're not sure # whether `pass_all' will *always* work, you probably want this one. case $host_os in aix[4-9]*) lt_cv_deplibs_check_method=pass_all ;; beos*) lt_cv_deplibs_check_method=pass_all ;; bsdi[45]*) lt_cv_deplibs_check_method='file_magic ELF [0-9][0-9]*-bit [ML]SB (shared object|dynamic lib)' lt_cv_file_magic_cmd='/usr/bin/file -L' lt_cv_file_magic_test_file=/shlib/libc.so ;; cygwin*) # func_win32_libid is a shell function defined in ltmain.sh lt_cv_deplibs_check_method='file_magic ^x86 archive import|^x86 DLL' lt_cv_file_magic_cmd='func_win32_libid' ;; mingw* | pw32*) # Base MSYS/MinGW do not provide the 'file' command needed by # func_win32_libid shell function, so use a weaker test based on 'objdump', # unless we find 'file', for example because we are cross-compiling. # func_win32_libid assumes BSD nm, so disallow it if using MS dumpbin. if ( test "$lt_cv_nm_interface" = "BSD nm" && file / ) >/dev/null 2>&1; then lt_cv_deplibs_check_method='file_magic ^x86 archive import|^x86 DLL' lt_cv_file_magic_cmd='func_win32_libid' else # Keep this pattern in sync with the one in func_win32_libid. lt_cv_deplibs_check_method='file_magic file format (pei*-i386(.*architecture: i386)?|pe-arm-wince|pe-x86-64)' lt_cv_file_magic_cmd='$OBJDUMP -f' fi ;; cegcc*) # use the weaker test based on 'objdump'. See mingw*. lt_cv_deplibs_check_method='file_magic file format pe-arm-.*little(.*architecture: arm)?' lt_cv_file_magic_cmd='$OBJDUMP -f' ;; darwin* | rhapsody*) lt_cv_deplibs_check_method=pass_all ;; freebsd* | dragonfly*) if echo __ELF__ | $CC -E - | $GREP __ELF__ > /dev/null; then case $host_cpu in i*86 ) # Not sure whether the presence of OpenBSD here was a mistake. # Let's accept both of them until this is cleared up. lt_cv_deplibs_check_method='file_magic (FreeBSD|OpenBSD|DragonFly)/i[3-9]86 (compact )?demand paged shared library' lt_cv_file_magic_cmd=/usr/bin/file lt_cv_file_magic_test_file=`echo /usr/lib/libc.so.*` ;; esac else lt_cv_deplibs_check_method=pass_all fi ;; haiku*) lt_cv_deplibs_check_method=pass_all ;; hpux10.20* | hpux11*) lt_cv_file_magic_cmd=/usr/bin/file case $host_cpu in ia64*) lt_cv_deplibs_check_method='file_magic (s[0-9][0-9][0-9]|ELF-[0-9][0-9]) shared object file - IA64' lt_cv_file_magic_test_file=/usr/lib/hpux32/libc.so ;; hppa*64*) lt_cv_deplibs_check_method='file_magic (s[0-9][0-9][0-9]|ELF[ -][0-9][0-9])(-bit)?( [LM]SB)? shared object( file)?[, -]* PA-RISC [0-9]\.[0-9]' lt_cv_file_magic_test_file=/usr/lib/pa20_64/libc.sl ;; *) lt_cv_deplibs_check_method='file_magic (s[0-9][0-9][0-9]|PA-RISC[0-9]\.[0-9]) shared library' lt_cv_file_magic_test_file=/usr/lib/libc.sl ;; esac ;; interix[3-9]*) # PIC code is broken on Interix 3.x, that's why |\.a not |_pic\.a here lt_cv_deplibs_check_method='match_pattern /lib[^/]+(\.so|\.a)$' ;; irix5* | irix6* | nonstopux*) case $LD in *-32|*"-32 ") libmagic=32-bit;; *-n32|*"-n32 ") libmagic=N32;; *-64|*"-64 ") libmagic=64-bit;; *) libmagic=never-match;; esac lt_cv_deplibs_check_method=pass_all ;; # This must be glibc/ELF. linux* | k*bsd*-gnu | kopensolaris*-gnu | gnu*) lt_cv_deplibs_check_method=pass_all ;; netbsd* | netbsdelf*-gnu) if echo __ELF__ | $CC -E - | $GREP __ELF__ > /dev/null; then lt_cv_deplibs_check_method='match_pattern /lib[^/]+(\.so\.[0-9]+\.[0-9]+|_pic\.a)$' else lt_cv_deplibs_check_method='match_pattern /lib[^/]+(\.so|_pic\.a)$' fi ;; newos6*) lt_cv_deplibs_check_method='file_magic ELF [0-9][0-9]*-bit [ML]SB (executable|dynamic lib)' lt_cv_file_magic_cmd=/usr/bin/file lt_cv_file_magic_test_file=/usr/lib/libnls.so ;; *nto* | *qnx*) lt_cv_deplibs_check_method=pass_all ;; openbsd*) if test -z "`echo __ELF__ | $CC -E - | $GREP __ELF__`" || test "$host_os-$host_cpu" = "openbsd2.8-powerpc"; then lt_cv_deplibs_check_method='match_pattern /lib[^/]+(\.so\.[0-9]+\.[0-9]+|\.so|_pic\.a)$' else lt_cv_deplibs_check_method='match_pattern /lib[^/]+(\.so\.[0-9]+\.[0-9]+|_pic\.a)$' fi ;; osf3* | osf4* | osf5*) lt_cv_deplibs_check_method=pass_all ;; rdos*) lt_cv_deplibs_check_method=pass_all ;; solaris*) lt_cv_deplibs_check_method=pass_all ;; sysv5* | sco3.2v5* | sco5v6* | unixware* | OpenUNIX* | sysv4*uw2*) lt_cv_deplibs_check_method=pass_all ;; sysv4 | sysv4.3*) case $host_vendor in motorola) lt_cv_deplibs_check_method='file_magic ELF [0-9][0-9]*-bit [ML]SB (shared object|dynamic lib) M[0-9][0-9]* Version [0-9]' lt_cv_file_magic_test_file=`echo /usr/lib/libc.so*` ;; ncr) lt_cv_deplibs_check_method=pass_all ;; sequent) lt_cv_file_magic_cmd='/bin/file' lt_cv_deplibs_check_method='file_magic ELF [0-9][0-9]*-bit [LM]SB (shared object|dynamic lib )' ;; sni) lt_cv_file_magic_cmd='/bin/file' lt_cv_deplibs_check_method="file_magic ELF [0-9][0-9]*-bit [LM]SB dynamic lib" lt_cv_file_magic_test_file=/lib/libc.so ;; siemens) lt_cv_deplibs_check_method=pass_all ;; pc) lt_cv_deplibs_check_method=pass_all ;; esac ;; tpf*) lt_cv_deplibs_check_method=pass_all ;; esac fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $lt_cv_deplibs_check_method" >&5 $as_echo "$lt_cv_deplibs_check_method" >&6; } file_magic_glob= want_nocaseglob=no if test "$build" = "$host"; then case $host_os in mingw* | pw32*) if ( shopt | grep nocaseglob ) >/dev/null 2>&1; then want_nocaseglob=yes else file_magic_glob=`echo aAbBcCdDeEfFgGhHiIjJkKlLmMnNoOpPqQrRsStTuUvVwWxXyYzZ | $SED -e "s/\(..\)/s\/[\1]\/[\1]\/g;/g"` fi ;; esac fi file_magic_cmd=$lt_cv_file_magic_cmd deplibs_check_method=$lt_cv_deplibs_check_method test -z "$deplibs_check_method" && deplibs_check_method=unknown if test -n "$ac_tool_prefix"; then # Extract the first word of "${ac_tool_prefix}dlltool", so it can be a program name with args. set dummy ${ac_tool_prefix}dlltool; ac_word=$2 { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $ac_word" >&5 $as_echo_n "checking for $ac_word... " >&6; } if ${ac_cv_prog_DLLTOOL+:} false; then : $as_echo_n "(cached) " >&6 else if test -n "$DLLTOOL"; then ac_cv_prog_DLLTOOL="$DLLTOOL" # Let the user override the test. else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_exec_ext in '' $ac_executable_extensions; do if as_fn_executable_p "$as_dir/$ac_word$ac_exec_ext"; then ac_cv_prog_DLLTOOL="${ac_tool_prefix}dlltool" $as_echo "$as_me:${as_lineno-$LINENO}: found $as_dir/$ac_word$ac_exec_ext" >&5 break 2 fi done done IFS=$as_save_IFS fi fi DLLTOOL=$ac_cv_prog_DLLTOOL if test -n "$DLLTOOL"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $DLLTOOL" >&5 $as_echo "$DLLTOOL" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi fi if test -z "$ac_cv_prog_DLLTOOL"; then ac_ct_DLLTOOL=$DLLTOOL # Extract the first word of "dlltool", so it can be a program name with args. set dummy dlltool; ac_word=$2 { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $ac_word" >&5 $as_echo_n "checking for $ac_word... " >&6; } if ${ac_cv_prog_ac_ct_DLLTOOL+:} false; then : $as_echo_n "(cached) " >&6 else if test -n "$ac_ct_DLLTOOL"; then ac_cv_prog_ac_ct_DLLTOOL="$ac_ct_DLLTOOL" # Let the user override the test. else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_exec_ext in '' $ac_executable_extensions; do if as_fn_executable_p "$as_dir/$ac_word$ac_exec_ext"; then ac_cv_prog_ac_ct_DLLTOOL="dlltool" $as_echo "$as_me:${as_lineno-$LINENO}: found $as_dir/$ac_word$ac_exec_ext" >&5 break 2 fi done done IFS=$as_save_IFS fi fi ac_ct_DLLTOOL=$ac_cv_prog_ac_ct_DLLTOOL if test -n "$ac_ct_DLLTOOL"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_ct_DLLTOOL" >&5 $as_echo "$ac_ct_DLLTOOL" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi if test "x$ac_ct_DLLTOOL" = x; then DLLTOOL="false" else case $cross_compiling:$ac_tool_warned in yes:) { $as_echo "$as_me:${as_lineno-$LINENO}: WARNING: using cross tools not prefixed with host triplet" >&5 $as_echo "$as_me: WARNING: using cross tools not prefixed with host triplet" >&2;} ac_tool_warned=yes ;; esac DLLTOOL=$ac_ct_DLLTOOL fi else DLLTOOL="$ac_cv_prog_DLLTOOL" fi test -z "$DLLTOOL" && DLLTOOL=dlltool { $as_echo "$as_me:${as_lineno-$LINENO}: checking how to associate runtime and link libraries" >&5 $as_echo_n "checking how to associate runtime and link libraries... " >&6; } if ${lt_cv_sharedlib_from_linklib_cmd+:} false; then : $as_echo_n "(cached) " >&6 else lt_cv_sharedlib_from_linklib_cmd='unknown' case $host_os in cygwin* | mingw* | pw32* | cegcc*) # two different shell functions defined in ltmain.sh # decide which to use based on capabilities of $DLLTOOL case `$DLLTOOL --help 2>&1` in *--identify-strict*) lt_cv_sharedlib_from_linklib_cmd=func_cygming_dll_for_implib ;; *) lt_cv_sharedlib_from_linklib_cmd=func_cygming_dll_for_implib_fallback ;; esac ;; *) # fallback: assume linklib IS sharedlib lt_cv_sharedlib_from_linklib_cmd="$ECHO" ;; esac fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $lt_cv_sharedlib_from_linklib_cmd" >&5 $as_echo "$lt_cv_sharedlib_from_linklib_cmd" >&6; } sharedlib_from_linklib_cmd=$lt_cv_sharedlib_from_linklib_cmd test -z "$sharedlib_from_linklib_cmd" && sharedlib_from_linklib_cmd=$ECHO if test -n "$ac_tool_prefix"; then for ac_prog in ar do # Extract the first word of "$ac_tool_prefix$ac_prog", so it can be a program name with args. set dummy $ac_tool_prefix$ac_prog; ac_word=$2 { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $ac_word" >&5 $as_echo_n "checking for $ac_word... " >&6; } if ${ac_cv_prog_AR+:} false; then : $as_echo_n "(cached) " >&6 else if test -n "$AR"; then ac_cv_prog_AR="$AR" # Let the user override the test. else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_exec_ext in '' $ac_executable_extensions; do if as_fn_executable_p "$as_dir/$ac_word$ac_exec_ext"; then ac_cv_prog_AR="$ac_tool_prefix$ac_prog" $as_echo "$as_me:${as_lineno-$LINENO}: found $as_dir/$ac_word$ac_exec_ext" >&5 break 2 fi done done IFS=$as_save_IFS fi fi AR=$ac_cv_prog_AR if test -n "$AR"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $AR" >&5 $as_echo "$AR" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi test -n "$AR" && break done fi if test -z "$AR"; then ac_ct_AR=$AR for ac_prog in ar do # Extract the first word of "$ac_prog", so it can be a program name with args. set dummy $ac_prog; ac_word=$2 { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $ac_word" >&5 $as_echo_n "checking for $ac_word... " >&6; } if ${ac_cv_prog_ac_ct_AR+:} false; then : $as_echo_n "(cached) " >&6 else if test -n "$ac_ct_AR"; then ac_cv_prog_ac_ct_AR="$ac_ct_AR" # Let the user override the test. else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_exec_ext in '' $ac_executable_extensions; do if as_fn_executable_p "$as_dir/$ac_word$ac_exec_ext"; then ac_cv_prog_ac_ct_AR="$ac_prog" $as_echo "$as_me:${as_lineno-$LINENO}: found $as_dir/$ac_word$ac_exec_ext" >&5 break 2 fi done done IFS=$as_save_IFS fi fi ac_ct_AR=$ac_cv_prog_ac_ct_AR if test -n "$ac_ct_AR"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_ct_AR" >&5 $as_echo "$ac_ct_AR" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi test -n "$ac_ct_AR" && break done if test "x$ac_ct_AR" = x; then AR="false" else case $cross_compiling:$ac_tool_warned in yes:) { $as_echo "$as_me:${as_lineno-$LINENO}: WARNING: using cross tools not prefixed with host triplet" >&5 $as_echo "$as_me: WARNING: using cross tools not prefixed with host triplet" >&2;} ac_tool_warned=yes ;; esac AR=$ac_ct_AR fi fi : ${AR=ar} : ${AR_FLAGS=cru} { $as_echo "$as_me:${as_lineno-$LINENO}: checking for archiver @FILE support" >&5 $as_echo_n "checking for archiver @FILE support... " >&6; } if ${lt_cv_ar_at_file+:} false; then : $as_echo_n "(cached) " >&6 else lt_cv_ar_at_file=no cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ int main () { ; return 0; } _ACEOF if ac_fn_c_try_compile "$LINENO"; then : echo conftest.$ac_objext > conftest.lst lt_ar_try='$AR $AR_FLAGS libconftest.a @conftest.lst >&5' { { eval echo "\"\$as_me\":${as_lineno-$LINENO}: \"$lt_ar_try\""; } >&5 (eval $lt_ar_try) 2>&5 ac_status=$? $as_echo "$as_me:${as_lineno-$LINENO}: \$? = $ac_status" >&5 test $ac_status = 0; } if test "$ac_status" -eq 0; then # Ensure the archiver fails upon bogus file names. rm -f conftest.$ac_objext libconftest.a { { eval echo "\"\$as_me\":${as_lineno-$LINENO}: \"$lt_ar_try\""; } >&5 (eval $lt_ar_try) 2>&5 ac_status=$? $as_echo "$as_me:${as_lineno-$LINENO}: \$? = $ac_status" >&5 test $ac_status = 0; } if test "$ac_status" -ne 0; then lt_cv_ar_at_file=@ fi fi rm -f conftest.* libconftest.a fi rm -f core conftest.err conftest.$ac_objext conftest.$ac_ext fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $lt_cv_ar_at_file" >&5 $as_echo "$lt_cv_ar_at_file" >&6; } if test "x$lt_cv_ar_at_file" = xno; then archiver_list_spec= else archiver_list_spec=$lt_cv_ar_at_file fi if test -n "$ac_tool_prefix"; then # Extract the first word of "${ac_tool_prefix}strip", so it can be a program name with args. set dummy ${ac_tool_prefix}strip; ac_word=$2 { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $ac_word" >&5 $as_echo_n "checking for $ac_word... " >&6; } if ${ac_cv_prog_STRIP+:} false; then : $as_echo_n "(cached) " >&6 else if test -n "$STRIP"; then ac_cv_prog_STRIP="$STRIP" # Let the user override the test. else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_exec_ext in '' $ac_executable_extensions; do if as_fn_executable_p "$as_dir/$ac_word$ac_exec_ext"; then ac_cv_prog_STRIP="${ac_tool_prefix}strip" $as_echo "$as_me:${as_lineno-$LINENO}: found $as_dir/$ac_word$ac_exec_ext" >&5 break 2 fi done done IFS=$as_save_IFS fi fi STRIP=$ac_cv_prog_STRIP if test -n "$STRIP"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $STRIP" >&5 $as_echo "$STRIP" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi fi if test -z "$ac_cv_prog_STRIP"; then ac_ct_STRIP=$STRIP # Extract the first word of "strip", so it can be a program name with args. set dummy strip; ac_word=$2 { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $ac_word" >&5 $as_echo_n "checking for $ac_word... " >&6; } if ${ac_cv_prog_ac_ct_STRIP+:} false; then : $as_echo_n "(cached) " >&6 else if test -n "$ac_ct_STRIP"; then ac_cv_prog_ac_ct_STRIP="$ac_ct_STRIP" # Let the user override the test. else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_exec_ext in '' $ac_executable_extensions; do if as_fn_executable_p "$as_dir/$ac_word$ac_exec_ext"; then ac_cv_prog_ac_ct_STRIP="strip" $as_echo "$as_me:${as_lineno-$LINENO}: found $as_dir/$ac_word$ac_exec_ext" >&5 break 2 fi done done IFS=$as_save_IFS fi fi ac_ct_STRIP=$ac_cv_prog_ac_ct_STRIP if test -n "$ac_ct_STRIP"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_ct_STRIP" >&5 $as_echo "$ac_ct_STRIP" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi if test "x$ac_ct_STRIP" = x; then STRIP=":" else case $cross_compiling:$ac_tool_warned in yes:) { $as_echo "$as_me:${as_lineno-$LINENO}: WARNING: using cross tools not prefixed with host triplet" >&5 $as_echo "$as_me: WARNING: using cross tools not prefixed with host triplet" >&2;} ac_tool_warned=yes ;; esac STRIP=$ac_ct_STRIP fi else STRIP="$ac_cv_prog_STRIP" fi test -z "$STRIP" && STRIP=: if test -n "$ac_tool_prefix"; then # Extract the first word of "${ac_tool_prefix}ranlib", so it can be a program name with args. set dummy ${ac_tool_prefix}ranlib; ac_word=$2 { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $ac_word" >&5 $as_echo_n "checking for $ac_word... " >&6; } if ${ac_cv_prog_RANLIB+:} false; then : $as_echo_n "(cached) " >&6 else if test -n "$RANLIB"; then ac_cv_prog_RANLIB="$RANLIB" # Let the user override the test. else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_exec_ext in '' $ac_executable_extensions; do if as_fn_executable_p "$as_dir/$ac_word$ac_exec_ext"; then ac_cv_prog_RANLIB="${ac_tool_prefix}ranlib" $as_echo "$as_me:${as_lineno-$LINENO}: found $as_dir/$ac_word$ac_exec_ext" >&5 break 2 fi done done IFS=$as_save_IFS fi fi RANLIB=$ac_cv_prog_RANLIB if test -n "$RANLIB"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $RANLIB" >&5 $as_echo "$RANLIB" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi fi if test -z "$ac_cv_prog_RANLIB"; then ac_ct_RANLIB=$RANLIB # Extract the first word of "ranlib", so it can be a program name with args. set dummy ranlib; ac_word=$2 { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $ac_word" >&5 $as_echo_n "checking for $ac_word... " >&6; } if ${ac_cv_prog_ac_ct_RANLIB+:} false; then : $as_echo_n "(cached) " >&6 else if test -n "$ac_ct_RANLIB"; then ac_cv_prog_ac_ct_RANLIB="$ac_ct_RANLIB" # Let the user override the test. else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_exec_ext in '' $ac_executable_extensions; do if as_fn_executable_p "$as_dir/$ac_word$ac_exec_ext"; then ac_cv_prog_ac_ct_RANLIB="ranlib" $as_echo "$as_me:${as_lineno-$LINENO}: found $as_dir/$ac_word$ac_exec_ext" >&5 break 2 fi done done IFS=$as_save_IFS fi fi ac_ct_RANLIB=$ac_cv_prog_ac_ct_RANLIB if test -n "$ac_ct_RANLIB"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_ct_RANLIB" >&5 $as_echo "$ac_ct_RANLIB" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi if test "x$ac_ct_RANLIB" = x; then RANLIB=":" else case $cross_compiling:$ac_tool_warned in yes:) { $as_echo "$as_me:${as_lineno-$LINENO}: WARNING: using cross tools not prefixed with host triplet" >&5 $as_echo "$as_me: WARNING: using cross tools not prefixed with host triplet" >&2;} ac_tool_warned=yes ;; esac RANLIB=$ac_ct_RANLIB fi else RANLIB="$ac_cv_prog_RANLIB" fi test -z "$RANLIB" && RANLIB=: # Determine commands to create old-style static archives. old_archive_cmds='$AR $AR_FLAGS $oldlib$oldobjs' old_postinstall_cmds='chmod 644 $oldlib' old_postuninstall_cmds= if test -n "$RANLIB"; then case $host_os in openbsd*) old_postinstall_cmds="$old_postinstall_cmds~\$RANLIB -t \$tool_oldlib" ;; *) old_postinstall_cmds="$old_postinstall_cmds~\$RANLIB \$tool_oldlib" ;; esac old_archive_cmds="$old_archive_cmds~\$RANLIB \$tool_oldlib" fi case $host_os in darwin*) lock_old_archive_extraction=yes ;; *) lock_old_archive_extraction=no ;; esac # If no C compiler was specified, use CC. LTCC=${LTCC-"$CC"} # If no C compiler flags were specified, use CFLAGS. LTCFLAGS=${LTCFLAGS-"$CFLAGS"} # Allow CC to be a program name with arguments. compiler=$CC # Check for command to grab the raw symbol name followed by C symbol from nm. { $as_echo "$as_me:${as_lineno-$LINENO}: checking command to parse $NM output from $compiler object" >&5 $as_echo_n "checking command to parse $NM output from $compiler object... " >&6; } if ${lt_cv_sys_global_symbol_pipe+:} false; then : $as_echo_n "(cached) " >&6 else # These are sane defaults that work on at least a few old systems. # [They come from Ultrix. What could be older than Ultrix?!! ;)] # Character class describing NM global symbol codes. symcode='[BCDEGRST]' # Regexp to match symbols that can be accessed directly from C. sympat='\([_A-Za-z][_A-Za-z0-9]*\)' # Define system-specific variables. case $host_os in aix*) symcode='[BCDT]' ;; cygwin* | mingw* | pw32* | cegcc*) symcode='[ABCDGISTW]' ;; hpux*) if test "$host_cpu" = ia64; then symcode='[ABCDEGRST]' fi ;; irix* | nonstopux*) symcode='[BCDEGRST]' ;; osf*) symcode='[BCDEGQRST]' ;; solaris*) symcode='[BDRT]' ;; sco3.2v5*) symcode='[DT]' ;; sysv4.2uw2*) symcode='[DT]' ;; sysv5* | sco5v6* | unixware* | OpenUNIX*) symcode='[ABDT]' ;; sysv4) symcode='[DFNSTU]' ;; esac # If we're using GNU nm, then use its standard symbol codes. case `$NM -V 2>&1` in *GNU* | *'with BFD'*) symcode='[ABCDGIRSTW]' ;; esac # Transform an extracted symbol line into a proper C declaration. # Some systems (esp. on ia64) link data and code symbols differently, # so use this general approach. lt_cv_sys_global_symbol_to_cdecl="sed -n -e 's/^T .* \(.*\)$/extern int \1();/p' -e 's/^$symcode* .* \(.*\)$/extern char \1;/p'" # Transform an extracted symbol line into symbol name and symbol address lt_cv_sys_global_symbol_to_c_name_address="sed -n -e 's/^: \([^ ]*\)[ ]*$/ {\\\"\1\\\", (void *) 0},/p' -e 's/^$symcode* \([^ ]*\) \([^ ]*\)$/ {\"\2\", (void *) \&\2},/p'" lt_cv_sys_global_symbol_to_c_name_address_lib_prefix="sed -n -e 's/^: \([^ ]*\)[ ]*$/ {\\\"\1\\\", (void *) 0},/p' -e 's/^$symcode* \([^ ]*\) \(lib[^ ]*\)$/ {\"\2\", (void *) \&\2},/p' -e 's/^$symcode* \([^ ]*\) \([^ ]*\)$/ {\"lib\2\", (void *) \&\2},/p'" # Handle CRLF in mingw tool chain opt_cr= case $build_os in mingw*) opt_cr=`$ECHO 'x\{0,1\}' | tr x '\015'` # option cr in regexp ;; esac # Try without a prefix underscore, then with it. for ac_symprfx in "" "_"; do # Transform symcode, sympat, and symprfx into a raw symbol and a C symbol. symxfrm="\\1 $ac_symprfx\\2 \\2" # Write the raw and C identifiers. if test "$lt_cv_nm_interface" = "MS dumpbin"; then # Fake it for dumpbin and say T for any non-static function # and D for any global variable. # Also find C++ and __fastcall symbols from MSVC++, # which start with @ or ?. lt_cv_sys_global_symbol_pipe="$AWK '"\ " {last_section=section; section=\$ 3};"\ " /^COFF SYMBOL TABLE/{for(i in hide) delete hide[i]};"\ " /Section length .*#relocs.*(pick any)/{hide[last_section]=1};"\ " \$ 0!~/External *\|/{next};"\ " / 0+ UNDEF /{next}; / UNDEF \([^|]\)*()/{next};"\ " {if(hide[section]) next};"\ " {f=0}; \$ 0~/\(\).*\|/{f=1}; {printf f ? \"T \" : \"D \"};"\ " {split(\$ 0, a, /\||\r/); split(a[2], s)};"\ " s[1]~/^[@?]/{print s[1], s[1]; next};"\ " s[1]~prfx {split(s[1],t,\"@\"); print t[1], substr(t[1],length(prfx))}"\ " ' prfx=^$ac_symprfx" else lt_cv_sys_global_symbol_pipe="sed -n -e 's/^.*[ ]\($symcode$symcode*\)[ ][ ]*$ac_symprfx$sympat$opt_cr$/$symxfrm/p'" fi lt_cv_sys_global_symbol_pipe="$lt_cv_sys_global_symbol_pipe | sed '/ __gnu_lto/d'" # Check to see that the pipe works correctly. pipe_works=no rm -f conftest* cat > conftest.$ac_ext <<_LT_EOF #ifdef __cplusplus extern "C" { #endif char nm_test_var; void nm_test_func(void); void nm_test_func(void){} #ifdef __cplusplus } #endif int main(){nm_test_var='a';nm_test_func();return(0);} _LT_EOF if { { eval echo "\"\$as_me\":${as_lineno-$LINENO}: \"$ac_compile\""; } >&5 (eval $ac_compile) 2>&5 ac_status=$? $as_echo "$as_me:${as_lineno-$LINENO}: \$? = $ac_status" >&5 test $ac_status = 0; }; then # Now try to grab the symbols. nlist=conftest.nm if { { eval echo "\"\$as_me\":${as_lineno-$LINENO}: \"$NM conftest.$ac_objext \| "$lt_cv_sys_global_symbol_pipe" \> $nlist\""; } >&5 (eval $NM conftest.$ac_objext \| "$lt_cv_sys_global_symbol_pipe" \> $nlist) 2>&5 ac_status=$? $as_echo "$as_me:${as_lineno-$LINENO}: \$? = $ac_status" >&5 test $ac_status = 0; } && test -s "$nlist"; then # Try sorting and uniquifying the output. if sort "$nlist" | uniq > "$nlist"T; then mv -f "$nlist"T "$nlist" else rm -f "$nlist"T fi # Make sure that we snagged all the symbols we need. if $GREP ' nm_test_var$' "$nlist" >/dev/null; then if $GREP ' nm_test_func$' "$nlist" >/dev/null; then cat <<_LT_EOF > conftest.$ac_ext /* Keep this code in sync between libtool.m4, ltmain, lt_system.h, and tests. */ #if defined(_WIN32) || defined(__CYGWIN__) || defined(_WIN32_WCE) /* DATA imports from DLLs on WIN32 con't be const, because runtime relocations are performed -- see ld's documentation on pseudo-relocs. */ # define LT_DLSYM_CONST #elif defined(__osf__) /* This system does not cope well with relocations in const data. */ # define LT_DLSYM_CONST #else # define LT_DLSYM_CONST const #endif #ifdef __cplusplus extern "C" { #endif _LT_EOF # Now generate the symbol file. eval "$lt_cv_sys_global_symbol_to_cdecl"' < "$nlist" | $GREP -v main >> conftest.$ac_ext' cat <<_LT_EOF >> conftest.$ac_ext /* The mapping between symbol names and symbols. */ LT_DLSYM_CONST struct { const char *name; void *address; } lt__PROGRAM__LTX_preloaded_symbols[] = { { "@PROGRAM@", (void *) 0 }, _LT_EOF $SED "s/^$symcode$symcode* \(.*\) \(.*\)$/ {\"\2\", (void *) \&\2},/" < "$nlist" | $GREP -v main >> conftest.$ac_ext cat <<\_LT_EOF >> conftest.$ac_ext {0, (void *) 0} }; /* This works around a problem in FreeBSD linker */ #ifdef FREEBSD_WORKAROUND static const void *lt_preloaded_setup() { return lt__PROGRAM__LTX_preloaded_symbols; } #endif #ifdef __cplusplus } #endif _LT_EOF # Now try linking the two files. mv conftest.$ac_objext conftstm.$ac_objext lt_globsym_save_LIBS=$LIBS lt_globsym_save_CFLAGS=$CFLAGS LIBS="conftstm.$ac_objext" CFLAGS="$CFLAGS$lt_prog_compiler_no_builtin_flag" if { { eval echo "\"\$as_me\":${as_lineno-$LINENO}: \"$ac_link\""; } >&5 (eval $ac_link) 2>&5 ac_status=$? $as_echo "$as_me:${as_lineno-$LINENO}: \$? = $ac_status" >&5 test $ac_status = 0; } && test -s conftest${ac_exeext}; then pipe_works=yes fi LIBS=$lt_globsym_save_LIBS CFLAGS=$lt_globsym_save_CFLAGS else echo "cannot find nm_test_func in $nlist" >&5 fi else echo "cannot find nm_test_var in $nlist" >&5 fi else echo "cannot run $lt_cv_sys_global_symbol_pipe" >&5 fi else echo "$progname: failed program was:" >&5 cat conftest.$ac_ext >&5 fi rm -rf conftest* conftst* # Do not use the global_symbol_pipe unless it works. if test "$pipe_works" = yes; then break else lt_cv_sys_global_symbol_pipe= fi done fi if test -z "$lt_cv_sys_global_symbol_pipe"; then lt_cv_sys_global_symbol_to_cdecl= fi if test -z "$lt_cv_sys_global_symbol_pipe$lt_cv_sys_global_symbol_to_cdecl"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: failed" >&5 $as_echo "failed" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: ok" >&5 $as_echo "ok" >&6; } fi # Response file support. if test "$lt_cv_nm_interface" = "MS dumpbin"; then nm_file_list_spec='@' elif $NM --help 2>/dev/null | grep '[@]FILE' >/dev/null; then nm_file_list_spec='@' fi { $as_echo "$as_me:${as_lineno-$LINENO}: checking for sysroot" >&5 $as_echo_n "checking for sysroot... " >&6; } # Check whether --with-sysroot was given. if test "${with_sysroot+set}" = set; then : withval=$with_sysroot; else with_sysroot=no fi lt_sysroot= case ${with_sysroot} in #( yes) if test "$GCC" = yes; then lt_sysroot=`$CC --print-sysroot 2>/dev/null` fi ;; #( /*) lt_sysroot=`echo "$with_sysroot" | sed -e "$sed_quote_subst"` ;; #( no|'') ;; #( *) { $as_echo "$as_me:${as_lineno-$LINENO}: result: ${with_sysroot}" >&5 $as_echo "${with_sysroot}" >&6; } as_fn_error $? "The sysroot must be an absolute path." "$LINENO" 5 ;; esac { $as_echo "$as_me:${as_lineno-$LINENO}: result: ${lt_sysroot:-no}" >&5 $as_echo "${lt_sysroot:-no}" >&6; } # Check whether --enable-libtool-lock was given. if test "${enable_libtool_lock+set}" = set; then : enableval=$enable_libtool_lock; fi test "x$enable_libtool_lock" != xno && enable_libtool_lock=yes # Some flags need to be propagated to the compiler or linker for good # libtool support. case $host in ia64-*-hpux*) # Find out which ABI we are using. echo 'int i;' > conftest.$ac_ext if { { eval echo "\"\$as_me\":${as_lineno-$LINENO}: \"$ac_compile\""; } >&5 (eval $ac_compile) 2>&5 ac_status=$? $as_echo "$as_me:${as_lineno-$LINENO}: \$? = $ac_status" >&5 test $ac_status = 0; }; then case `/usr/bin/file conftest.$ac_objext` in *ELF-32*) HPUX_IA64_MODE="32" ;; *ELF-64*) HPUX_IA64_MODE="64" ;; esac fi rm -rf conftest* ;; *-*-irix6*) # Find out which ABI we are using. echo '#line '$LINENO' "configure"' > conftest.$ac_ext if { { eval echo "\"\$as_me\":${as_lineno-$LINENO}: \"$ac_compile\""; } >&5 (eval $ac_compile) 2>&5 ac_status=$? $as_echo "$as_me:${as_lineno-$LINENO}: \$? = $ac_status" >&5 test $ac_status = 0; }; then if test "$lt_cv_prog_gnu_ld" = yes; then case `/usr/bin/file conftest.$ac_objext` in *32-bit*) LD="${LD-ld} -melf32bsmip" ;; *N32*) LD="${LD-ld} -melf32bmipn32" ;; *64-bit*) LD="${LD-ld} -melf64bmip" ;; esac else case `/usr/bin/file conftest.$ac_objext` in *32-bit*) LD="${LD-ld} -32" ;; *N32*) LD="${LD-ld} -n32" ;; *64-bit*) LD="${LD-ld} -64" ;; esac fi fi rm -rf conftest* ;; x86_64-*kfreebsd*-gnu|x86_64-*linux*|ppc*-*linux*|powerpc*-*linux*| \ s390*-*linux*|s390*-*tpf*|sparc*-*linux*) # Find out which ABI we are using. echo 'int i;' > conftest.$ac_ext if { { eval echo "\"\$as_me\":${as_lineno-$LINENO}: \"$ac_compile\""; } >&5 (eval $ac_compile) 2>&5 ac_status=$? $as_echo "$as_me:${as_lineno-$LINENO}: \$? = $ac_status" >&5 test $ac_status = 0; }; then case `/usr/bin/file conftest.o` in *32-bit*) case $host in x86_64-*kfreebsd*-gnu) LD="${LD-ld} -m elf_i386_fbsd" ;; x86_64-*linux*) case `/usr/bin/file conftest.o` in *x86-64*) LD="${LD-ld} -m elf32_x86_64" ;; *) LD="${LD-ld} -m elf_i386" ;; esac ;; ppc64-*linux*|powerpc64-*linux*) LD="${LD-ld} -m elf32ppclinux" ;; s390x-*linux*) LD="${LD-ld} -m elf_s390" ;; sparc64-*linux*) LD="${LD-ld} -m elf32_sparc" ;; esac ;; *64-bit*) case $host in x86_64-*kfreebsd*-gnu) LD="${LD-ld} -m elf_x86_64_fbsd" ;; x86_64-*linux*) LD="${LD-ld} -m elf_x86_64" ;; ppc*-*linux*|powerpc*-*linux*) LD="${LD-ld} -m elf64ppc" ;; s390*-*linux*|s390*-*tpf*) LD="${LD-ld} -m elf64_s390" ;; sparc*-*linux*) LD="${LD-ld} -m elf64_sparc" ;; esac ;; esac fi rm -rf conftest* ;; *-*-sco3.2v5*) # On SCO OpenServer 5, we need -belf to get full-featured binaries. SAVE_CFLAGS="$CFLAGS" CFLAGS="$CFLAGS -belf" { $as_echo "$as_me:${as_lineno-$LINENO}: checking whether the C compiler needs -belf" >&5 $as_echo_n "checking whether the C compiler needs -belf... " >&6; } if ${lt_cv_cc_needs_belf+:} false; then : $as_echo_n "(cached) " >&6 else ac_ext=c ac_cpp='$CPP $CPPFLAGS' ac_compile='$CC -c $CFLAGS $CPPFLAGS conftest.$ac_ext >&5' ac_link='$CC -o conftest$ac_exeext $CFLAGS $CPPFLAGS $LDFLAGS conftest.$ac_ext $LIBS >&5' ac_compiler_gnu=$ac_cv_c_compiler_gnu cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ int main () { ; return 0; } _ACEOF if ac_fn_c_try_link "$LINENO"; then : lt_cv_cc_needs_belf=yes else lt_cv_cc_needs_belf=no fi rm -f core conftest.err conftest.$ac_objext \ conftest$ac_exeext conftest.$ac_ext ac_ext=c ac_cpp='$CPP $CPPFLAGS' ac_compile='$CC -c $CFLAGS $CPPFLAGS conftest.$ac_ext >&5' ac_link='$CC -o conftest$ac_exeext $CFLAGS $CPPFLAGS $LDFLAGS conftest.$ac_ext $LIBS >&5' ac_compiler_gnu=$ac_cv_c_compiler_gnu fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $lt_cv_cc_needs_belf" >&5 $as_echo "$lt_cv_cc_needs_belf" >&6; } if test x"$lt_cv_cc_needs_belf" != x"yes"; then # this is probably gcc 2.8.0, egcs 1.0 or newer; no need for -belf CFLAGS="$SAVE_CFLAGS" fi ;; *-*solaris*) # Find out which ABI we are using. echo 'int i;' > conftest.$ac_ext if { { eval echo "\"\$as_me\":${as_lineno-$LINENO}: \"$ac_compile\""; } >&5 (eval $ac_compile) 2>&5 ac_status=$? $as_echo "$as_me:${as_lineno-$LINENO}: \$? = $ac_status" >&5 test $ac_status = 0; }; then case `/usr/bin/file conftest.o` in *64-bit*) case $lt_cv_prog_gnu_ld in yes*) case $host in i?86-*-solaris*) LD="${LD-ld} -m elf_x86_64" ;; sparc*-*-solaris*) LD="${LD-ld} -m elf64_sparc" ;; esac # GNU ld 2.21 introduced _sol2 emulations. Use them if available. if ${LD-ld} -V | grep _sol2 >/dev/null 2>&1; then LD="${LD-ld}_sol2" fi ;; *) if ${LD-ld} -64 -r -o conftest2.o conftest.o >/dev/null 2>&1; then LD="${LD-ld} -64" fi ;; esac ;; esac fi rm -rf conftest* ;; esac need_locks="$enable_libtool_lock" if test -n "$ac_tool_prefix"; then # Extract the first word of "${ac_tool_prefix}mt", so it can be a program name with args. set dummy ${ac_tool_prefix}mt; ac_word=$2 { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $ac_word" >&5 $as_echo_n "checking for $ac_word... " >&6; } if ${ac_cv_prog_MANIFEST_TOOL+:} false; then : $as_echo_n "(cached) " >&6 else if test -n "$MANIFEST_TOOL"; then ac_cv_prog_MANIFEST_TOOL="$MANIFEST_TOOL" # Let the user override the test. else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_exec_ext in '' $ac_executable_extensions; do if as_fn_executable_p "$as_dir/$ac_word$ac_exec_ext"; then ac_cv_prog_MANIFEST_TOOL="${ac_tool_prefix}mt" $as_echo "$as_me:${as_lineno-$LINENO}: found $as_dir/$ac_word$ac_exec_ext" >&5 break 2 fi done done IFS=$as_save_IFS fi fi MANIFEST_TOOL=$ac_cv_prog_MANIFEST_TOOL if test -n "$MANIFEST_TOOL"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $MANIFEST_TOOL" >&5 $as_echo "$MANIFEST_TOOL" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi fi if test -z "$ac_cv_prog_MANIFEST_TOOL"; then ac_ct_MANIFEST_TOOL=$MANIFEST_TOOL # Extract the first word of "mt", so it can be a program name with args. set dummy mt; ac_word=$2 { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $ac_word" >&5 $as_echo_n "checking for $ac_word... " >&6; } if ${ac_cv_prog_ac_ct_MANIFEST_TOOL+:} false; then : $as_echo_n "(cached) " >&6 else if test -n "$ac_ct_MANIFEST_TOOL"; then ac_cv_prog_ac_ct_MANIFEST_TOOL="$ac_ct_MANIFEST_TOOL" # Let the user override the test. else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_exec_ext in '' $ac_executable_extensions; do if as_fn_executable_p "$as_dir/$ac_word$ac_exec_ext"; then ac_cv_prog_ac_ct_MANIFEST_TOOL="mt" $as_echo "$as_me:${as_lineno-$LINENO}: found $as_dir/$ac_word$ac_exec_ext" >&5 break 2 fi done done IFS=$as_save_IFS fi fi ac_ct_MANIFEST_TOOL=$ac_cv_prog_ac_ct_MANIFEST_TOOL if test -n "$ac_ct_MANIFEST_TOOL"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_ct_MANIFEST_TOOL" >&5 $as_echo "$ac_ct_MANIFEST_TOOL" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi if test "x$ac_ct_MANIFEST_TOOL" = x; then MANIFEST_TOOL=":" else case $cross_compiling:$ac_tool_warned in yes:) { $as_echo "$as_me:${as_lineno-$LINENO}: WARNING: using cross tools not prefixed with host triplet" >&5 $as_echo "$as_me: WARNING: using cross tools not prefixed with host triplet" >&2;} ac_tool_warned=yes ;; esac MANIFEST_TOOL=$ac_ct_MANIFEST_TOOL fi else MANIFEST_TOOL="$ac_cv_prog_MANIFEST_TOOL" fi test -z "$MANIFEST_TOOL" && MANIFEST_TOOL=mt { $as_echo "$as_me:${as_lineno-$LINENO}: checking if $MANIFEST_TOOL is a manifest tool" >&5 $as_echo_n "checking if $MANIFEST_TOOL is a manifest tool... " >&6; } if ${lt_cv_path_mainfest_tool+:} false; then : $as_echo_n "(cached) " >&6 else lt_cv_path_mainfest_tool=no echo "$as_me:$LINENO: $MANIFEST_TOOL '-?'" >&5 $MANIFEST_TOOL '-?' 2>conftest.err > conftest.out cat conftest.err >&5 if $GREP 'Manifest Tool' conftest.out > /dev/null; then lt_cv_path_mainfest_tool=yes fi rm -f conftest* fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $lt_cv_path_mainfest_tool" >&5 $as_echo "$lt_cv_path_mainfest_tool" >&6; } if test "x$lt_cv_path_mainfest_tool" != xyes; then MANIFEST_TOOL=: fi case $host_os in rhapsody* | darwin*) if test -n "$ac_tool_prefix"; then # Extract the first word of "${ac_tool_prefix}dsymutil", so it can be a program name with args. set dummy ${ac_tool_prefix}dsymutil; ac_word=$2 { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $ac_word" >&5 $as_echo_n "checking for $ac_word... " >&6; } if ${ac_cv_prog_DSYMUTIL+:} false; then : $as_echo_n "(cached) " >&6 else if test -n "$DSYMUTIL"; then ac_cv_prog_DSYMUTIL="$DSYMUTIL" # Let the user override the test. else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_exec_ext in '' $ac_executable_extensions; do if as_fn_executable_p "$as_dir/$ac_word$ac_exec_ext"; then ac_cv_prog_DSYMUTIL="${ac_tool_prefix}dsymutil" $as_echo "$as_me:${as_lineno-$LINENO}: found $as_dir/$ac_word$ac_exec_ext" >&5 break 2 fi done done IFS=$as_save_IFS fi fi DSYMUTIL=$ac_cv_prog_DSYMUTIL if test -n "$DSYMUTIL"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $DSYMUTIL" >&5 $as_echo "$DSYMUTIL" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi fi if test -z "$ac_cv_prog_DSYMUTIL"; then ac_ct_DSYMUTIL=$DSYMUTIL # Extract the first word of "dsymutil", so it can be a program name with args. set dummy dsymutil; ac_word=$2 { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $ac_word" >&5 $as_echo_n "checking for $ac_word... " >&6; } if ${ac_cv_prog_ac_ct_DSYMUTIL+:} false; then : $as_echo_n "(cached) " >&6 else if test -n "$ac_ct_DSYMUTIL"; then ac_cv_prog_ac_ct_DSYMUTIL="$ac_ct_DSYMUTIL" # Let the user override the test. else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_exec_ext in '' $ac_executable_extensions; do if as_fn_executable_p "$as_dir/$ac_word$ac_exec_ext"; then ac_cv_prog_ac_ct_DSYMUTIL="dsymutil" $as_echo "$as_me:${as_lineno-$LINENO}: found $as_dir/$ac_word$ac_exec_ext" >&5 break 2 fi done done IFS=$as_save_IFS fi fi ac_ct_DSYMUTIL=$ac_cv_prog_ac_ct_DSYMUTIL if test -n "$ac_ct_DSYMUTIL"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_ct_DSYMUTIL" >&5 $as_echo "$ac_ct_DSYMUTIL" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi if test "x$ac_ct_DSYMUTIL" = x; then DSYMUTIL=":" else case $cross_compiling:$ac_tool_warned in yes:) { $as_echo "$as_me:${as_lineno-$LINENO}: WARNING: using cross tools not prefixed with host triplet" >&5 $as_echo "$as_me: WARNING: using cross tools not prefixed with host triplet" >&2;} ac_tool_warned=yes ;; esac DSYMUTIL=$ac_ct_DSYMUTIL fi else DSYMUTIL="$ac_cv_prog_DSYMUTIL" fi if test -n "$ac_tool_prefix"; then # Extract the first word of "${ac_tool_prefix}nmedit", so it can be a program name with args. set dummy ${ac_tool_prefix}nmedit; ac_word=$2 { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $ac_word" >&5 $as_echo_n "checking for $ac_word... " >&6; } if ${ac_cv_prog_NMEDIT+:} false; then : $as_echo_n "(cached) " >&6 else if test -n "$NMEDIT"; then ac_cv_prog_NMEDIT="$NMEDIT" # Let the user override the test. else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_exec_ext in '' $ac_executable_extensions; do if as_fn_executable_p "$as_dir/$ac_word$ac_exec_ext"; then ac_cv_prog_NMEDIT="${ac_tool_prefix}nmedit" $as_echo "$as_me:${as_lineno-$LINENO}: found $as_dir/$ac_word$ac_exec_ext" >&5 break 2 fi done done IFS=$as_save_IFS fi fi NMEDIT=$ac_cv_prog_NMEDIT if test -n "$NMEDIT"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $NMEDIT" >&5 $as_echo "$NMEDIT" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi fi if test -z "$ac_cv_prog_NMEDIT"; then ac_ct_NMEDIT=$NMEDIT # Extract the first word of "nmedit", so it can be a program name with args. set dummy nmedit; ac_word=$2 { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $ac_word" >&5 $as_echo_n "checking for $ac_word... " >&6; } if ${ac_cv_prog_ac_ct_NMEDIT+:} false; then : $as_echo_n "(cached) " >&6 else if test -n "$ac_ct_NMEDIT"; then ac_cv_prog_ac_ct_NMEDIT="$ac_ct_NMEDIT" # Let the user override the test. else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_exec_ext in '' $ac_executable_extensions; do if as_fn_executable_p "$as_dir/$ac_word$ac_exec_ext"; then ac_cv_prog_ac_ct_NMEDIT="nmedit" $as_echo "$as_me:${as_lineno-$LINENO}: found $as_dir/$ac_word$ac_exec_ext" >&5 break 2 fi done done IFS=$as_save_IFS fi fi ac_ct_NMEDIT=$ac_cv_prog_ac_ct_NMEDIT if test -n "$ac_ct_NMEDIT"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_ct_NMEDIT" >&5 $as_echo "$ac_ct_NMEDIT" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi if test "x$ac_ct_NMEDIT" = x; then NMEDIT=":" else case $cross_compiling:$ac_tool_warned in yes:) { $as_echo "$as_me:${as_lineno-$LINENO}: WARNING: using cross tools not prefixed with host triplet" >&5 $as_echo "$as_me: WARNING: using cross tools not prefixed with host triplet" >&2;} ac_tool_warned=yes ;; esac NMEDIT=$ac_ct_NMEDIT fi else NMEDIT="$ac_cv_prog_NMEDIT" fi if test -n "$ac_tool_prefix"; then # Extract the first word of "${ac_tool_prefix}lipo", so it can be a program name with args. set dummy ${ac_tool_prefix}lipo; ac_word=$2 { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $ac_word" >&5 $as_echo_n "checking for $ac_word... " >&6; } if ${ac_cv_prog_LIPO+:} false; then : $as_echo_n "(cached) " >&6 else if test -n "$LIPO"; then ac_cv_prog_LIPO="$LIPO" # Let the user override the test. else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_exec_ext in '' $ac_executable_extensions; do if as_fn_executable_p "$as_dir/$ac_word$ac_exec_ext"; then ac_cv_prog_LIPO="${ac_tool_prefix}lipo" $as_echo "$as_me:${as_lineno-$LINENO}: found $as_dir/$ac_word$ac_exec_ext" >&5 break 2 fi done done IFS=$as_save_IFS fi fi LIPO=$ac_cv_prog_LIPO if test -n "$LIPO"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $LIPO" >&5 $as_echo "$LIPO" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi fi if test -z "$ac_cv_prog_LIPO"; then ac_ct_LIPO=$LIPO # Extract the first word of "lipo", so it can be a program name with args. set dummy lipo; ac_word=$2 { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $ac_word" >&5 $as_echo_n "checking for $ac_word... " >&6; } if ${ac_cv_prog_ac_ct_LIPO+:} false; then : $as_echo_n "(cached) " >&6 else if test -n "$ac_ct_LIPO"; then ac_cv_prog_ac_ct_LIPO="$ac_ct_LIPO" # Let the user override the test. else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_exec_ext in '' $ac_executable_extensions; do if as_fn_executable_p "$as_dir/$ac_word$ac_exec_ext"; then ac_cv_prog_ac_ct_LIPO="lipo" $as_echo "$as_me:${as_lineno-$LINENO}: found $as_dir/$ac_word$ac_exec_ext" >&5 break 2 fi done done IFS=$as_save_IFS fi fi ac_ct_LIPO=$ac_cv_prog_ac_ct_LIPO if test -n "$ac_ct_LIPO"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_ct_LIPO" >&5 $as_echo "$ac_ct_LIPO" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi if test "x$ac_ct_LIPO" = x; then LIPO=":" else case $cross_compiling:$ac_tool_warned in yes:) { $as_echo "$as_me:${as_lineno-$LINENO}: WARNING: using cross tools not prefixed with host triplet" >&5 $as_echo "$as_me: WARNING: using cross tools not prefixed with host triplet" >&2;} ac_tool_warned=yes ;; esac LIPO=$ac_ct_LIPO fi else LIPO="$ac_cv_prog_LIPO" fi if test -n "$ac_tool_prefix"; then # Extract the first word of "${ac_tool_prefix}otool", so it can be a program name with args. set dummy ${ac_tool_prefix}otool; ac_word=$2 { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $ac_word" >&5 $as_echo_n "checking for $ac_word... " >&6; } if ${ac_cv_prog_OTOOL+:} false; then : $as_echo_n "(cached) " >&6 else if test -n "$OTOOL"; then ac_cv_prog_OTOOL="$OTOOL" # Let the user override the test. else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_exec_ext in '' $ac_executable_extensions; do if as_fn_executable_p "$as_dir/$ac_word$ac_exec_ext"; then ac_cv_prog_OTOOL="${ac_tool_prefix}otool" $as_echo "$as_me:${as_lineno-$LINENO}: found $as_dir/$ac_word$ac_exec_ext" >&5 break 2 fi done done IFS=$as_save_IFS fi fi OTOOL=$ac_cv_prog_OTOOL if test -n "$OTOOL"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $OTOOL" >&5 $as_echo "$OTOOL" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi fi if test -z "$ac_cv_prog_OTOOL"; then ac_ct_OTOOL=$OTOOL # Extract the first word of "otool", so it can be a program name with args. set dummy otool; ac_word=$2 { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $ac_word" >&5 $as_echo_n "checking for $ac_word... " >&6; } if ${ac_cv_prog_ac_ct_OTOOL+:} false; then : $as_echo_n "(cached) " >&6 else if test -n "$ac_ct_OTOOL"; then ac_cv_prog_ac_ct_OTOOL="$ac_ct_OTOOL" # Let the user override the test. else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_exec_ext in '' $ac_executable_extensions; do if as_fn_executable_p "$as_dir/$ac_word$ac_exec_ext"; then ac_cv_prog_ac_ct_OTOOL="otool" $as_echo "$as_me:${as_lineno-$LINENO}: found $as_dir/$ac_word$ac_exec_ext" >&5 break 2 fi done done IFS=$as_save_IFS fi fi ac_ct_OTOOL=$ac_cv_prog_ac_ct_OTOOL if test -n "$ac_ct_OTOOL"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_ct_OTOOL" >&5 $as_echo "$ac_ct_OTOOL" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi if test "x$ac_ct_OTOOL" = x; then OTOOL=":" else case $cross_compiling:$ac_tool_warned in yes:) { $as_echo "$as_me:${as_lineno-$LINENO}: WARNING: using cross tools not prefixed with host triplet" >&5 $as_echo "$as_me: WARNING: using cross tools not prefixed with host triplet" >&2;} ac_tool_warned=yes ;; esac OTOOL=$ac_ct_OTOOL fi else OTOOL="$ac_cv_prog_OTOOL" fi if test -n "$ac_tool_prefix"; then # Extract the first word of "${ac_tool_prefix}otool64", so it can be a program name with args. set dummy ${ac_tool_prefix}otool64; ac_word=$2 { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $ac_word" >&5 $as_echo_n "checking for $ac_word... " >&6; } if ${ac_cv_prog_OTOOL64+:} false; then : $as_echo_n "(cached) " >&6 else if test -n "$OTOOL64"; then ac_cv_prog_OTOOL64="$OTOOL64" # Let the user override the test. else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_exec_ext in '' $ac_executable_extensions; do if as_fn_executable_p "$as_dir/$ac_word$ac_exec_ext"; then ac_cv_prog_OTOOL64="${ac_tool_prefix}otool64" $as_echo "$as_me:${as_lineno-$LINENO}: found $as_dir/$ac_word$ac_exec_ext" >&5 break 2 fi done done IFS=$as_save_IFS fi fi OTOOL64=$ac_cv_prog_OTOOL64 if test -n "$OTOOL64"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $OTOOL64" >&5 $as_echo "$OTOOL64" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi fi if test -z "$ac_cv_prog_OTOOL64"; then ac_ct_OTOOL64=$OTOOL64 # Extract the first word of "otool64", so it can be a program name with args. set dummy otool64; ac_word=$2 { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $ac_word" >&5 $as_echo_n "checking for $ac_word... " >&6; } if ${ac_cv_prog_ac_ct_OTOOL64+:} false; then : $as_echo_n "(cached) " >&6 else if test -n "$ac_ct_OTOOL64"; then ac_cv_prog_ac_ct_OTOOL64="$ac_ct_OTOOL64" # Let the user override the test. else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_exec_ext in '' $ac_executable_extensions; do if as_fn_executable_p "$as_dir/$ac_word$ac_exec_ext"; then ac_cv_prog_ac_ct_OTOOL64="otool64" $as_echo "$as_me:${as_lineno-$LINENO}: found $as_dir/$ac_word$ac_exec_ext" >&5 break 2 fi done done IFS=$as_save_IFS fi fi ac_ct_OTOOL64=$ac_cv_prog_ac_ct_OTOOL64 if test -n "$ac_ct_OTOOL64"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_ct_OTOOL64" >&5 $as_echo "$ac_ct_OTOOL64" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi if test "x$ac_ct_OTOOL64" = x; then OTOOL64=":" else case $cross_compiling:$ac_tool_warned in yes:) { $as_echo "$as_me:${as_lineno-$LINENO}: WARNING: using cross tools not prefixed with host triplet" >&5 $as_echo "$as_me: WARNING: using cross tools not prefixed with host triplet" >&2;} ac_tool_warned=yes ;; esac OTOOL64=$ac_ct_OTOOL64 fi else OTOOL64="$ac_cv_prog_OTOOL64" fi { $as_echo "$as_me:${as_lineno-$LINENO}: checking for -single_module linker flag" >&5 $as_echo_n "checking for -single_module linker flag... " >&6; } if ${lt_cv_apple_cc_single_mod+:} false; then : $as_echo_n "(cached) " >&6 else lt_cv_apple_cc_single_mod=no if test -z "${LT_MULTI_MODULE}"; then # By default we will add the -single_module flag. You can override # by either setting the environment variable LT_MULTI_MODULE # non-empty at configure time, or by adding -multi_module to the # link flags. rm -rf libconftest.dylib* echo "int foo(void){return 1;}" > conftest.c echo "$LTCC $LTCFLAGS $LDFLAGS -o libconftest.dylib \ -dynamiclib -Wl,-single_module conftest.c" >&5 $LTCC $LTCFLAGS $LDFLAGS -o libconftest.dylib \ -dynamiclib -Wl,-single_module conftest.c 2>conftest.err _lt_result=$? # If there is a non-empty error log, and "single_module" # appears in it, assume the flag caused a linker warning if test -s conftest.err && $GREP single_module conftest.err; then cat conftest.err >&5 # Otherwise, if the output was created with a 0 exit code from # the compiler, it worked. elif test -f libconftest.dylib && test $_lt_result -eq 0; then lt_cv_apple_cc_single_mod=yes else cat conftest.err >&5 fi rm -rf libconftest.dylib* rm -f conftest.* fi fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $lt_cv_apple_cc_single_mod" >&5 $as_echo "$lt_cv_apple_cc_single_mod" >&6; } { $as_echo "$as_me:${as_lineno-$LINENO}: checking for -exported_symbols_list linker flag" >&5 $as_echo_n "checking for -exported_symbols_list linker flag... " >&6; } if ${lt_cv_ld_exported_symbols_list+:} false; then : $as_echo_n "(cached) " >&6 else lt_cv_ld_exported_symbols_list=no save_LDFLAGS=$LDFLAGS echo "_main" > conftest.sym LDFLAGS="$LDFLAGS -Wl,-exported_symbols_list,conftest.sym" cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ int main () { ; return 0; } _ACEOF if ac_fn_c_try_link "$LINENO"; then : lt_cv_ld_exported_symbols_list=yes else lt_cv_ld_exported_symbols_list=no fi rm -f core conftest.err conftest.$ac_objext \ conftest$ac_exeext conftest.$ac_ext LDFLAGS="$save_LDFLAGS" fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $lt_cv_ld_exported_symbols_list" >&5 $as_echo "$lt_cv_ld_exported_symbols_list" >&6; } { $as_echo "$as_me:${as_lineno-$LINENO}: checking for -force_load linker flag" >&5 $as_echo_n "checking for -force_load linker flag... " >&6; } if ${lt_cv_ld_force_load+:} false; then : $as_echo_n "(cached) " >&6 else lt_cv_ld_force_load=no cat > conftest.c << _LT_EOF int forced_loaded() { return 2;} _LT_EOF echo "$LTCC $LTCFLAGS -c -o conftest.o conftest.c" >&5 $LTCC $LTCFLAGS -c -o conftest.o conftest.c 2>&5 echo "$AR cru libconftest.a conftest.o" >&5 $AR cru libconftest.a conftest.o 2>&5 echo "$RANLIB libconftest.a" >&5 $RANLIB libconftest.a 2>&5 cat > conftest.c << _LT_EOF int main() { return 0;} _LT_EOF echo "$LTCC $LTCFLAGS $LDFLAGS -o conftest conftest.c -Wl,-force_load,./libconftest.a" >&5 $LTCC $LTCFLAGS $LDFLAGS -o conftest conftest.c -Wl,-force_load,./libconftest.a 2>conftest.err _lt_result=$? if test -s conftest.err && $GREP force_load conftest.err; then cat conftest.err >&5 elif test -f conftest && test $_lt_result -eq 0 && $GREP forced_load conftest >/dev/null 2>&1 ; then lt_cv_ld_force_load=yes else cat conftest.err >&5 fi rm -f conftest.err libconftest.a conftest conftest.c rm -rf conftest.dSYM fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $lt_cv_ld_force_load" >&5 $as_echo "$lt_cv_ld_force_load" >&6; } case $host_os in rhapsody* | darwin1.[012]) _lt_dar_allow_undefined='${wl}-undefined ${wl}suppress' ;; darwin1.*) _lt_dar_allow_undefined='${wl}-flat_namespace ${wl}-undefined ${wl}suppress' ;; darwin*) # darwin 5.x on # if running on 10.5 or later, the deployment target defaults # to the OS version, if on x86, and 10.4, the deployment # target defaults to 10.4. Don't you love it? case ${MACOSX_DEPLOYMENT_TARGET-10.0},$host in 10.0,*86*-darwin8*|10.0,*-darwin[91]*) _lt_dar_allow_undefined='${wl}-undefined ${wl}dynamic_lookup' ;; 10.[012]*) _lt_dar_allow_undefined='${wl}-flat_namespace ${wl}-undefined ${wl}suppress' ;; 10.*) _lt_dar_allow_undefined='${wl}-undefined ${wl}dynamic_lookup' ;; esac ;; esac if test "$lt_cv_apple_cc_single_mod" = "yes"; then _lt_dar_single_mod='$single_module' fi if test "$lt_cv_ld_exported_symbols_list" = "yes"; then _lt_dar_export_syms=' ${wl}-exported_symbols_list,$output_objdir/${libname}-symbols.expsym' else _lt_dar_export_syms='~$NMEDIT -s $output_objdir/${libname}-symbols.expsym ${lib}' fi if test "$DSYMUTIL" != ":" && test "$lt_cv_ld_force_load" = "no"; then _lt_dsymutil='~$DSYMUTIL $lib || :' else _lt_dsymutil= fi ;; esac { $as_echo "$as_me:${as_lineno-$LINENO}: checking for ANSI C header files" >&5 $as_echo_n "checking for ANSI C header files... " >&6; } if ${ac_cv_header_stdc+:} false; then : $as_echo_n "(cached) " >&6 else cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ #include #include #include #include int main () { ; return 0; } _ACEOF if ac_fn_c_try_compile "$LINENO"; then : ac_cv_header_stdc=yes else ac_cv_header_stdc=no fi rm -f core conftest.err conftest.$ac_objext conftest.$ac_ext if test $ac_cv_header_stdc = yes; then # SunOS 4.x string.h does not declare mem*, contrary to ANSI. cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ #include _ACEOF if (eval "$ac_cpp conftest.$ac_ext") 2>&5 | $EGREP "memchr" >/dev/null 2>&1; then : else ac_cv_header_stdc=no fi rm -f conftest* fi if test $ac_cv_header_stdc = yes; then # ISC 2.0.2 stdlib.h does not declare free, contrary to ANSI. cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ #include _ACEOF if (eval "$ac_cpp conftest.$ac_ext") 2>&5 | $EGREP "free" >/dev/null 2>&1; then : else ac_cv_header_stdc=no fi rm -f conftest* fi if test $ac_cv_header_stdc = yes; then # /bin/cc in Irix-4.0.5 gets non-ANSI ctype macros unless using -ansi. if test "$cross_compiling" = yes; then : : else cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ #include #include #if ((' ' & 0x0FF) == 0x020) # define ISLOWER(c) ('a' <= (c) && (c) <= 'z') # define TOUPPER(c) (ISLOWER(c) ? 'A' + ((c) - 'a') : (c)) #else # define ISLOWER(c) \ (('a' <= (c) && (c) <= 'i') \ || ('j' <= (c) && (c) <= 'r') \ || ('s' <= (c) && (c) <= 'z')) # define TOUPPER(c) (ISLOWER(c) ? ((c) | 0x40) : (c)) #endif #define XOR(e, f) (((e) && !(f)) || (!(e) && (f))) int main () { int i; for (i = 0; i < 256; i++) if (XOR (islower (i), ISLOWER (i)) || toupper (i) != TOUPPER (i)) return 2; return 0; } _ACEOF if ac_fn_c_try_run "$LINENO"; then : else ac_cv_header_stdc=no fi rm -f core *.core core.conftest.* gmon.out bb.out conftest$ac_exeext \ conftest.$ac_objext conftest.beam conftest.$ac_ext fi fi fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_cv_header_stdc" >&5 $as_echo "$ac_cv_header_stdc" >&6; } if test $ac_cv_header_stdc = yes; then $as_echo "#define STDC_HEADERS 1" >>confdefs.h fi # On IRIX 5.3, sys/types and inttypes.h are conflicting. for ac_header in sys/types.h sys/stat.h stdlib.h string.h memory.h strings.h \ inttypes.h stdint.h unistd.h do : as_ac_Header=`$as_echo "ac_cv_header_$ac_header" | $as_tr_sh` ac_fn_c_check_header_compile "$LINENO" "$ac_header" "$as_ac_Header" "$ac_includes_default " if eval test \"x\$"$as_ac_Header"\" = x"yes"; then : cat >>confdefs.h <<_ACEOF #define `$as_echo "HAVE_$ac_header" | $as_tr_cpp` 1 _ACEOF fi done for ac_header in dlfcn.h do : ac_fn_c_check_header_compile "$LINENO" "dlfcn.h" "ac_cv_header_dlfcn_h" "$ac_includes_default " if test "x$ac_cv_header_dlfcn_h" = xyes; then : cat >>confdefs.h <<_ACEOF #define HAVE_DLFCN_H 1 _ACEOF fi done # Set options enable_dlopen=no enable_win32_dll=no # Check whether --enable-shared was given. if test "${enable_shared+set}" = set; then : enableval=$enable_shared; p=${PACKAGE-default} case $enableval in yes) enable_shared=yes ;; no) enable_shared=no ;; *) enable_shared=no # Look at the argument we got. We use all the common list separators. lt_save_ifs="$IFS"; IFS="${IFS}$PATH_SEPARATOR," for pkg in $enableval; do IFS="$lt_save_ifs" if test "X$pkg" = "X$p"; then enable_shared=yes fi done IFS="$lt_save_ifs" ;; esac else enable_shared=yes fi # Check whether --enable-static was given. if test "${enable_static+set}" = set; then : enableval=$enable_static; p=${PACKAGE-default} case $enableval in yes) enable_static=yes ;; no) enable_static=no ;; *) enable_static=no # Look at the argument we got. We use all the common list separators. lt_save_ifs="$IFS"; IFS="${IFS}$PATH_SEPARATOR," for pkg in $enableval; do IFS="$lt_save_ifs" if test "X$pkg" = "X$p"; then enable_static=yes fi done IFS="$lt_save_ifs" ;; esac else enable_static=yes fi # Check whether --with-pic was given. if test "${with_pic+set}" = set; then : withval=$with_pic; lt_p=${PACKAGE-default} case $withval in yes|no) pic_mode=$withval ;; *) pic_mode=default # Look at the argument we got. We use all the common list separators. lt_save_ifs="$IFS"; IFS="${IFS}$PATH_SEPARATOR," for lt_pkg in $withval; do IFS="$lt_save_ifs" if test "X$lt_pkg" = "X$lt_p"; then pic_mode=yes fi done IFS="$lt_save_ifs" ;; esac else pic_mode=default fi test -z "$pic_mode" && pic_mode=default # Check whether --enable-fast-install was given. if test "${enable_fast_install+set}" = set; then : enableval=$enable_fast_install; p=${PACKAGE-default} case $enableval in yes) enable_fast_install=yes ;; no) enable_fast_install=no ;; *) enable_fast_install=no # Look at the argument we got. We use all the common list separators. lt_save_ifs="$IFS"; IFS="${IFS}$PATH_SEPARATOR," for pkg in $enableval; do IFS="$lt_save_ifs" if test "X$pkg" = "X$p"; then enable_fast_install=yes fi done IFS="$lt_save_ifs" ;; esac else enable_fast_install=yes fi # This can be used to rebuild libtool when needed LIBTOOL_DEPS="$ltmain" # Always use our own libtool. LIBTOOL='$(SHELL) $(top_builddir)/libtool' test -z "$LN_S" && LN_S="ln -s" if test -n "${ZSH_VERSION+set}" ; then setopt NO_GLOB_SUBST fi { $as_echo "$as_me:${as_lineno-$LINENO}: checking for objdir" >&5 $as_echo_n "checking for objdir... " >&6; } if ${lt_cv_objdir+:} false; then : $as_echo_n "(cached) " >&6 else rm -f .libs 2>/dev/null mkdir .libs 2>/dev/null if test -d .libs; then lt_cv_objdir=.libs else # MS-DOS does not allow filenames that begin with a dot. lt_cv_objdir=_libs fi rmdir .libs 2>/dev/null fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $lt_cv_objdir" >&5 $as_echo "$lt_cv_objdir" >&6; } objdir=$lt_cv_objdir cat >>confdefs.h <<_ACEOF #define LT_OBJDIR "$lt_cv_objdir/" _ACEOF case $host_os in aix3*) # AIX sometimes has problems with the GCC collect2 program. For some # reason, if we set the COLLECT_NAMES environment variable, the problems # vanish in a puff of smoke. if test "X${COLLECT_NAMES+set}" != Xset; then COLLECT_NAMES= export COLLECT_NAMES fi ;; esac # Global variables: ofile=libtool can_build_shared=yes # All known linkers require a `.a' archive for static linking (except MSVC, # which needs '.lib'). libext=a with_gnu_ld="$lt_cv_prog_gnu_ld" old_CC="$CC" old_CFLAGS="$CFLAGS" # Set sane defaults for various variables test -z "$CC" && CC=cc test -z "$LTCC" && LTCC=$CC test -z "$LTCFLAGS" && LTCFLAGS=$CFLAGS test -z "$LD" && LD=ld test -z "$ac_objext" && ac_objext=o for cc_temp in $compiler""; do case $cc_temp in compile | *[\\/]compile | ccache | *[\\/]ccache ) ;; distcc | *[\\/]distcc | purify | *[\\/]purify ) ;; \-*) ;; *) break;; esac done cc_basename=`$ECHO "$cc_temp" | $SED "s%.*/%%; s%^$host_alias-%%"` # Only perform the check for file, if the check method requires it test -z "$MAGIC_CMD" && MAGIC_CMD=file case $deplibs_check_method in file_magic*) if test "$file_magic_cmd" = '$MAGIC_CMD'; then { $as_echo "$as_me:${as_lineno-$LINENO}: checking for ${ac_tool_prefix}file" >&5 $as_echo_n "checking for ${ac_tool_prefix}file... " >&6; } if ${lt_cv_path_MAGIC_CMD+:} false; then : $as_echo_n "(cached) " >&6 else case $MAGIC_CMD in [\\/*] | ?:[\\/]*) lt_cv_path_MAGIC_CMD="$MAGIC_CMD" # Let the user override the test with a path. ;; *) lt_save_MAGIC_CMD="$MAGIC_CMD" lt_save_ifs="$IFS"; IFS=$PATH_SEPARATOR ac_dummy="/usr/bin$PATH_SEPARATOR$PATH" for ac_dir in $ac_dummy; do IFS="$lt_save_ifs" test -z "$ac_dir" && ac_dir=. if test -f $ac_dir/${ac_tool_prefix}file; then lt_cv_path_MAGIC_CMD="$ac_dir/${ac_tool_prefix}file" if test -n "$file_magic_test_file"; then case $deplibs_check_method in "file_magic "*) file_magic_regex=`expr "$deplibs_check_method" : "file_magic \(.*\)"` MAGIC_CMD="$lt_cv_path_MAGIC_CMD" if eval $file_magic_cmd \$file_magic_test_file 2> /dev/null | $EGREP "$file_magic_regex" > /dev/null; then : else cat <<_LT_EOF 1>&2 *** Warning: the command libtool uses to detect shared libraries, *** $file_magic_cmd, produces output that libtool cannot recognize. *** The result is that libtool may fail to recognize shared libraries *** as such. This will affect the creation of libtool libraries that *** depend on shared libraries, but programs linked with such libtool *** libraries will work regardless of this problem. Nevertheless, you *** may want to report the problem to your system manager and/or to *** bug-libtool@gnu.org _LT_EOF fi ;; esac fi break fi done IFS="$lt_save_ifs" MAGIC_CMD="$lt_save_MAGIC_CMD" ;; esac fi MAGIC_CMD="$lt_cv_path_MAGIC_CMD" if test -n "$MAGIC_CMD"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $MAGIC_CMD" >&5 $as_echo "$MAGIC_CMD" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi if test -z "$lt_cv_path_MAGIC_CMD"; then if test -n "$ac_tool_prefix"; then { $as_echo "$as_me:${as_lineno-$LINENO}: checking for file" >&5 $as_echo_n "checking for file... " >&6; } if ${lt_cv_path_MAGIC_CMD+:} false; then : $as_echo_n "(cached) " >&6 else case $MAGIC_CMD in [\\/*] | ?:[\\/]*) lt_cv_path_MAGIC_CMD="$MAGIC_CMD" # Let the user override the test with a path. ;; *) lt_save_MAGIC_CMD="$MAGIC_CMD" lt_save_ifs="$IFS"; IFS=$PATH_SEPARATOR ac_dummy="/usr/bin$PATH_SEPARATOR$PATH" for ac_dir in $ac_dummy; do IFS="$lt_save_ifs" test -z "$ac_dir" && ac_dir=. if test -f $ac_dir/file; then lt_cv_path_MAGIC_CMD="$ac_dir/file" if test -n "$file_magic_test_file"; then case $deplibs_check_method in "file_magic "*) file_magic_regex=`expr "$deplibs_check_method" : "file_magic \(.*\)"` MAGIC_CMD="$lt_cv_path_MAGIC_CMD" if eval $file_magic_cmd \$file_magic_test_file 2> /dev/null | $EGREP "$file_magic_regex" > /dev/null; then : else cat <<_LT_EOF 1>&2 *** Warning: the command libtool uses to detect shared libraries, *** $file_magic_cmd, produces output that libtool cannot recognize. *** The result is that libtool may fail to recognize shared libraries *** as such. This will affect the creation of libtool libraries that *** depend on shared libraries, but programs linked with such libtool *** libraries will work regardless of this problem. Nevertheless, you *** may want to report the problem to your system manager and/or to *** bug-libtool@gnu.org _LT_EOF fi ;; esac fi break fi done IFS="$lt_save_ifs" MAGIC_CMD="$lt_save_MAGIC_CMD" ;; esac fi MAGIC_CMD="$lt_cv_path_MAGIC_CMD" if test -n "$MAGIC_CMD"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $MAGIC_CMD" >&5 $as_echo "$MAGIC_CMD" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi else MAGIC_CMD=: fi fi fi ;; esac # Use C for the default configuration in the libtool script lt_save_CC="$CC" ac_ext=c ac_cpp='$CPP $CPPFLAGS' ac_compile='$CC -c $CFLAGS $CPPFLAGS conftest.$ac_ext >&5' ac_link='$CC -o conftest$ac_exeext $CFLAGS $CPPFLAGS $LDFLAGS conftest.$ac_ext $LIBS >&5' ac_compiler_gnu=$ac_cv_c_compiler_gnu # Source file extension for C test sources. ac_ext=c # Object file extension for compiled C test sources. objext=o objext=$objext # Code to be used in simple compile tests lt_simple_compile_test_code="int some_variable = 0;" # Code to be used in simple link tests lt_simple_link_test_code='int main(){return(0);}' # If no C compiler was specified, use CC. LTCC=${LTCC-"$CC"} # If no C compiler flags were specified, use CFLAGS. LTCFLAGS=${LTCFLAGS-"$CFLAGS"} # Allow CC to be a program name with arguments. compiler=$CC # Save the default compiler, since it gets overwritten when the other # tags are being tested, and _LT_TAGVAR(compiler, []) is a NOP. compiler_DEFAULT=$CC # save warnings/boilerplate of simple test code ac_outfile=conftest.$ac_objext echo "$lt_simple_compile_test_code" >conftest.$ac_ext eval "$ac_compile" 2>&1 >/dev/null | $SED '/^$/d; /^ *+/d' >conftest.err _lt_compiler_boilerplate=`cat conftest.err` $RM conftest* ac_outfile=conftest.$ac_objext echo "$lt_simple_link_test_code" >conftest.$ac_ext eval "$ac_link" 2>&1 >/dev/null | $SED '/^$/d; /^ *+/d' >conftest.err _lt_linker_boilerplate=`cat conftest.err` $RM -r conftest* ## CAVEAT EMPTOR: ## There is no encapsulation within the following macros, do not change ## the running order or otherwise move them around unless you know exactly ## what you are doing... if test -n "$compiler"; then lt_prog_compiler_no_builtin_flag= if test "$GCC" = yes; then case $cc_basename in nvcc*) lt_prog_compiler_no_builtin_flag=' -Xcompiler -fno-builtin' ;; *) lt_prog_compiler_no_builtin_flag=' -fno-builtin' ;; esac { $as_echo "$as_me:${as_lineno-$LINENO}: checking if $compiler supports -fno-rtti -fno-exceptions" >&5 $as_echo_n "checking if $compiler supports -fno-rtti -fno-exceptions... " >&6; } if ${lt_cv_prog_compiler_rtti_exceptions+:} false; then : $as_echo_n "(cached) " >&6 else lt_cv_prog_compiler_rtti_exceptions=no ac_outfile=conftest.$ac_objext echo "$lt_simple_compile_test_code" > conftest.$ac_ext lt_compiler_flag="-fno-rtti -fno-exceptions" # Insert the option either (1) after the last *FLAGS variable, or # (2) before a word containing "conftest.", or (3) at the end. # Note that $ac_compile itself does not contain backslashes and begins # with a dollar sign (not a hyphen), so the echo should work correctly. # The option is referenced via a variable to avoid confusing sed. lt_compile=`echo "$ac_compile" | $SED \ -e 's:.*FLAGS}\{0,1\} :&$lt_compiler_flag :; t' \ -e 's: [^ ]*conftest\.: $lt_compiler_flag&:; t' \ -e 's:$: $lt_compiler_flag:'` (eval echo "\"\$as_me:$LINENO: $lt_compile\"" >&5) (eval "$lt_compile" 2>conftest.err) ac_status=$? cat conftest.err >&5 echo "$as_me:$LINENO: \$? = $ac_status" >&5 if (exit $ac_status) && test -s "$ac_outfile"; then # The compiler can only warn and ignore the option if not recognized # So say no if there are warnings other than the usual output. $ECHO "$_lt_compiler_boilerplate" | $SED '/^$/d' >conftest.exp $SED '/^$/d; /^ *+/d' conftest.err >conftest.er2 if test ! -s conftest.er2 || diff conftest.exp conftest.er2 >/dev/null; then lt_cv_prog_compiler_rtti_exceptions=yes fi fi $RM conftest* fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $lt_cv_prog_compiler_rtti_exceptions" >&5 $as_echo "$lt_cv_prog_compiler_rtti_exceptions" >&6; } if test x"$lt_cv_prog_compiler_rtti_exceptions" = xyes; then lt_prog_compiler_no_builtin_flag="$lt_prog_compiler_no_builtin_flag -fno-rtti -fno-exceptions" else : fi fi lt_prog_compiler_wl= lt_prog_compiler_pic= lt_prog_compiler_static= if test "$GCC" = yes; then lt_prog_compiler_wl='-Wl,' lt_prog_compiler_static='-static' case $host_os in aix*) # All AIX code is PIC. if test "$host_cpu" = ia64; then # AIX 5 now supports IA64 processor lt_prog_compiler_static='-Bstatic' fi ;; amigaos*) case $host_cpu in powerpc) # see comment about AmigaOS4 .so support lt_prog_compiler_pic='-fPIC' ;; m68k) # FIXME: we need at least 68020 code to build shared libraries, but # adding the `-m68020' flag to GCC prevents building anything better, # like `-m68040'. lt_prog_compiler_pic='-m68020 -resident32 -malways-restore-a4' ;; esac ;; beos* | irix5* | irix6* | nonstopux* | osf3* | osf4* | osf5*) # PIC is the default for these OSes. ;; mingw* | cygwin* | pw32* | os2* | cegcc*) # This hack is so that the source file can tell whether it is being # built for inclusion in a dll (and should export symbols for example). # Although the cygwin gcc ignores -fPIC, still need this for old-style # (--disable-auto-import) libraries lt_prog_compiler_pic='-DDLL_EXPORT' ;; darwin* | rhapsody*) # PIC is the default on this platform # Common symbols not allowed in MH_DYLIB files lt_prog_compiler_pic='-fno-common' ;; haiku*) # PIC is the default for Haiku. # The "-static" flag exists, but is broken. lt_prog_compiler_static= ;; hpux*) # PIC is the default for 64-bit PA HP-UX, but not for 32-bit # PA HP-UX. On IA64 HP-UX, PIC is the default but the pic flag # sets the default TLS model and affects inlining. case $host_cpu in hppa*64*) # +Z the default ;; *) lt_prog_compiler_pic='-fPIC' ;; esac ;; interix[3-9]*) # Interix 3.x gcc -fpic/-fPIC options generate broken code. # Instead, we relocate shared libraries at runtime. ;; msdosdjgpp*) # Just because we use GCC doesn't mean we suddenly get shared libraries # on systems that don't support them. lt_prog_compiler_can_build_shared=no enable_shared=no ;; *nto* | *qnx*) # QNX uses GNU C++, but need to define -shared option too, otherwise # it will coredump. lt_prog_compiler_pic='-fPIC -shared' ;; sysv4*MP*) if test -d /usr/nec; then lt_prog_compiler_pic=-Kconform_pic fi ;; *) lt_prog_compiler_pic='-fPIC' ;; esac case $cc_basename in nvcc*) # Cuda Compiler Driver 2.2 lt_prog_compiler_wl='-Xlinker ' if test -n "$lt_prog_compiler_pic"; then lt_prog_compiler_pic="-Xcompiler $lt_prog_compiler_pic" fi ;; esac else # PORTME Check for flag to pass linker flags through the system compiler. case $host_os in aix*) lt_prog_compiler_wl='-Wl,' if test "$host_cpu" = ia64; then # AIX 5 now supports IA64 processor lt_prog_compiler_static='-Bstatic' else lt_prog_compiler_static='-bnso -bI:/lib/syscalls.exp' fi ;; mingw* | cygwin* | pw32* | os2* | cegcc*) # This hack is so that the source file can tell whether it is being # built for inclusion in a dll (and should export symbols for example). lt_prog_compiler_pic='-DDLL_EXPORT' ;; hpux9* | hpux10* | hpux11*) lt_prog_compiler_wl='-Wl,' # PIC is the default for IA64 HP-UX and 64-bit HP-UX, but # not for PA HP-UX. case $host_cpu in hppa*64*|ia64*) # +Z the default ;; *) lt_prog_compiler_pic='+Z' ;; esac # Is there a better lt_prog_compiler_static that works with the bundled CC? lt_prog_compiler_static='${wl}-a ${wl}archive' ;; irix5* | irix6* | nonstopux*) lt_prog_compiler_wl='-Wl,' # PIC (with -KPIC) is the default. lt_prog_compiler_static='-non_shared' ;; linux* | k*bsd*-gnu | kopensolaris*-gnu | gnu*) case $cc_basename in # old Intel for x86_64 which still supported -KPIC. ecc*) lt_prog_compiler_wl='-Wl,' lt_prog_compiler_pic='-KPIC' lt_prog_compiler_static='-static' ;; # icc used to be incompatible with GCC. # ICC 10 doesn't accept -KPIC any more. icc* | ifort*) lt_prog_compiler_wl='-Wl,' lt_prog_compiler_pic='-fPIC' lt_prog_compiler_static='-static' ;; # Lahey Fortran 8.1. lf95*) lt_prog_compiler_wl='-Wl,' lt_prog_compiler_pic='--shared' lt_prog_compiler_static='--static' ;; nagfor*) # NAG Fortran compiler lt_prog_compiler_wl='-Wl,-Wl,,' lt_prog_compiler_pic='-PIC' lt_prog_compiler_static='-Bstatic' ;; pgcc* | pgf77* | pgf90* | pgf95* | pgfortran*) # Portland Group compilers (*not* the Pentium gcc compiler, # which looks to be a dead project) lt_prog_compiler_wl='-Wl,' lt_prog_compiler_pic='-fpic' lt_prog_compiler_static='-Bstatic' ;; ccc*) lt_prog_compiler_wl='-Wl,' # All Alpha code is PIC. lt_prog_compiler_static='-non_shared' ;; xl* | bgxl* | bgf* | mpixl*) # IBM XL C 8.0/Fortran 10.1, 11.1 on PPC and BlueGene lt_prog_compiler_wl='-Wl,' lt_prog_compiler_pic='-qpic' lt_prog_compiler_static='-qstaticlink' ;; *) case `$CC -V 2>&1 | sed 5q` in *Sun\ Ceres\ Fortran* | *Sun*Fortran*\ [1-7].* | *Sun*Fortran*\ 8.[0-3]*) # Sun Fortran 8.3 passes all unrecognized flags to the linker lt_prog_compiler_pic='-KPIC' lt_prog_compiler_static='-Bstatic' lt_prog_compiler_wl='' ;; *Sun\ F* | *Sun*Fortran*) lt_prog_compiler_pic='-KPIC' lt_prog_compiler_static='-Bstatic' lt_prog_compiler_wl='-Qoption ld ' ;; *Sun\ C*) # Sun C 5.9 lt_prog_compiler_pic='-KPIC' lt_prog_compiler_static='-Bstatic' lt_prog_compiler_wl='-Wl,' ;; *Intel*\ [CF]*Compiler*) lt_prog_compiler_wl='-Wl,' lt_prog_compiler_pic='-fPIC' lt_prog_compiler_static='-static' ;; *Portland\ Group*) lt_prog_compiler_wl='-Wl,' lt_prog_compiler_pic='-fpic' lt_prog_compiler_static='-Bstatic' ;; esac ;; esac ;; newsos6) lt_prog_compiler_pic='-KPIC' lt_prog_compiler_static='-Bstatic' ;; *nto* | *qnx*) # QNX uses GNU C++, but need to define -shared option too, otherwise # it will coredump. lt_prog_compiler_pic='-fPIC -shared' ;; osf3* | osf4* | osf5*) lt_prog_compiler_wl='-Wl,' # All OSF/1 code is PIC. lt_prog_compiler_static='-non_shared' ;; rdos*) lt_prog_compiler_static='-non_shared' ;; solaris*) lt_prog_compiler_pic='-KPIC' lt_prog_compiler_static='-Bstatic' case $cc_basename in f77* | f90* | f95* | sunf77* | sunf90* | sunf95*) lt_prog_compiler_wl='-Qoption ld ';; *) lt_prog_compiler_wl='-Wl,';; esac ;; sunos4*) lt_prog_compiler_wl='-Qoption ld ' lt_prog_compiler_pic='-PIC' lt_prog_compiler_static='-Bstatic' ;; sysv4 | sysv4.2uw2* | sysv4.3*) lt_prog_compiler_wl='-Wl,' lt_prog_compiler_pic='-KPIC' lt_prog_compiler_static='-Bstatic' ;; sysv4*MP*) if test -d /usr/nec ;then lt_prog_compiler_pic='-Kconform_pic' lt_prog_compiler_static='-Bstatic' fi ;; sysv5* | unixware* | sco3.2v5* | sco5v6* | OpenUNIX*) lt_prog_compiler_wl='-Wl,' lt_prog_compiler_pic='-KPIC' lt_prog_compiler_static='-Bstatic' ;; unicos*) lt_prog_compiler_wl='-Wl,' lt_prog_compiler_can_build_shared=no ;; uts4*) lt_prog_compiler_pic='-pic' lt_prog_compiler_static='-Bstatic' ;; *) lt_prog_compiler_can_build_shared=no ;; esac fi case $host_os in # For platforms which do not support PIC, -DPIC is meaningless: *djgpp*) lt_prog_compiler_pic= ;; *) lt_prog_compiler_pic="$lt_prog_compiler_pic -DPIC" ;; esac { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $compiler option to produce PIC" >&5 $as_echo_n "checking for $compiler option to produce PIC... " >&6; } if ${lt_cv_prog_compiler_pic+:} false; then : $as_echo_n "(cached) " >&6 else lt_cv_prog_compiler_pic=$lt_prog_compiler_pic fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $lt_cv_prog_compiler_pic" >&5 $as_echo "$lt_cv_prog_compiler_pic" >&6; } lt_prog_compiler_pic=$lt_cv_prog_compiler_pic # # Check to make sure the PIC flag actually works. # if test -n "$lt_prog_compiler_pic"; then { $as_echo "$as_me:${as_lineno-$LINENO}: checking if $compiler PIC flag $lt_prog_compiler_pic works" >&5 $as_echo_n "checking if $compiler PIC flag $lt_prog_compiler_pic works... " >&6; } if ${lt_cv_prog_compiler_pic_works+:} false; then : $as_echo_n "(cached) " >&6 else lt_cv_prog_compiler_pic_works=no ac_outfile=conftest.$ac_objext echo "$lt_simple_compile_test_code" > conftest.$ac_ext lt_compiler_flag="$lt_prog_compiler_pic -DPIC" # Insert the option either (1) after the last *FLAGS variable, or # (2) before a word containing "conftest.", or (3) at the end. # Note that $ac_compile itself does not contain backslashes and begins # with a dollar sign (not a hyphen), so the echo should work correctly. # The option is referenced via a variable to avoid confusing sed. lt_compile=`echo "$ac_compile" | $SED \ -e 's:.*FLAGS}\{0,1\} :&$lt_compiler_flag :; t' \ -e 's: [^ ]*conftest\.: $lt_compiler_flag&:; t' \ -e 's:$: $lt_compiler_flag:'` (eval echo "\"\$as_me:$LINENO: $lt_compile\"" >&5) (eval "$lt_compile" 2>conftest.err) ac_status=$? cat conftest.err >&5 echo "$as_me:$LINENO: \$? = $ac_status" >&5 if (exit $ac_status) && test -s "$ac_outfile"; then # The compiler can only warn and ignore the option if not recognized # So say no if there are warnings other than the usual output. $ECHO "$_lt_compiler_boilerplate" | $SED '/^$/d' >conftest.exp $SED '/^$/d; /^ *+/d' conftest.err >conftest.er2 if test ! -s conftest.er2 || diff conftest.exp conftest.er2 >/dev/null; then lt_cv_prog_compiler_pic_works=yes fi fi $RM conftest* fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $lt_cv_prog_compiler_pic_works" >&5 $as_echo "$lt_cv_prog_compiler_pic_works" >&6; } if test x"$lt_cv_prog_compiler_pic_works" = xyes; then case $lt_prog_compiler_pic in "" | " "*) ;; *) lt_prog_compiler_pic=" $lt_prog_compiler_pic" ;; esac else lt_prog_compiler_pic= lt_prog_compiler_can_build_shared=no fi fi # # Check to make sure the static flag actually works. # wl=$lt_prog_compiler_wl eval lt_tmp_static_flag=\"$lt_prog_compiler_static\" { $as_echo "$as_me:${as_lineno-$LINENO}: checking if $compiler static flag $lt_tmp_static_flag works" >&5 $as_echo_n "checking if $compiler static flag $lt_tmp_static_flag works... " >&6; } if ${lt_cv_prog_compiler_static_works+:} false; then : $as_echo_n "(cached) " >&6 else lt_cv_prog_compiler_static_works=no save_LDFLAGS="$LDFLAGS" LDFLAGS="$LDFLAGS $lt_tmp_static_flag" echo "$lt_simple_link_test_code" > conftest.$ac_ext if (eval $ac_link 2>conftest.err) && test -s conftest$ac_exeext; then # The linker can only warn and ignore the option if not recognized # So say no if there are warnings if test -s conftest.err; then # Append any errors to the config.log. cat conftest.err 1>&5 $ECHO "$_lt_linker_boilerplate" | $SED '/^$/d' > conftest.exp $SED '/^$/d; /^ *+/d' conftest.err >conftest.er2 if diff conftest.exp conftest.er2 >/dev/null; then lt_cv_prog_compiler_static_works=yes fi else lt_cv_prog_compiler_static_works=yes fi fi $RM -r conftest* LDFLAGS="$save_LDFLAGS" fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $lt_cv_prog_compiler_static_works" >&5 $as_echo "$lt_cv_prog_compiler_static_works" >&6; } if test x"$lt_cv_prog_compiler_static_works" = xyes; then : else lt_prog_compiler_static= fi { $as_echo "$as_me:${as_lineno-$LINENO}: checking if $compiler supports -c -o file.$ac_objext" >&5 $as_echo_n "checking if $compiler supports -c -o file.$ac_objext... " >&6; } if ${lt_cv_prog_compiler_c_o+:} false; then : $as_echo_n "(cached) " >&6 else lt_cv_prog_compiler_c_o=no $RM -r conftest 2>/dev/null mkdir conftest cd conftest mkdir out echo "$lt_simple_compile_test_code" > conftest.$ac_ext lt_compiler_flag="-o out/conftest2.$ac_objext" # Insert the option either (1) after the last *FLAGS variable, or # (2) before a word containing "conftest.", or (3) at the end. # Note that $ac_compile itself does not contain backslashes and begins # with a dollar sign (not a hyphen), so the echo should work correctly. lt_compile=`echo "$ac_compile" | $SED \ -e 's:.*FLAGS}\{0,1\} :&$lt_compiler_flag :; t' \ -e 's: [^ ]*conftest\.: $lt_compiler_flag&:; t' \ -e 's:$: $lt_compiler_flag:'` (eval echo "\"\$as_me:$LINENO: $lt_compile\"" >&5) (eval "$lt_compile" 2>out/conftest.err) ac_status=$? cat out/conftest.err >&5 echo "$as_me:$LINENO: \$? = $ac_status" >&5 if (exit $ac_status) && test -s out/conftest2.$ac_objext then # The compiler can only warn and ignore the option if not recognized # So say no if there are warnings $ECHO "$_lt_compiler_boilerplate" | $SED '/^$/d' > out/conftest.exp $SED '/^$/d; /^ *+/d' out/conftest.err >out/conftest.er2 if test ! -s out/conftest.er2 || diff out/conftest.exp out/conftest.er2 >/dev/null; then lt_cv_prog_compiler_c_o=yes fi fi chmod u+w . 2>&5 $RM conftest* # SGI C++ compiler will create directory out/ii_files/ for # template instantiation test -d out/ii_files && $RM out/ii_files/* && rmdir out/ii_files $RM out/* && rmdir out cd .. $RM -r conftest $RM conftest* fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $lt_cv_prog_compiler_c_o" >&5 $as_echo "$lt_cv_prog_compiler_c_o" >&6; } { $as_echo "$as_me:${as_lineno-$LINENO}: checking if $compiler supports -c -o file.$ac_objext" >&5 $as_echo_n "checking if $compiler supports -c -o file.$ac_objext... " >&6; } if ${lt_cv_prog_compiler_c_o+:} false; then : $as_echo_n "(cached) " >&6 else lt_cv_prog_compiler_c_o=no $RM -r conftest 2>/dev/null mkdir conftest cd conftest mkdir out echo "$lt_simple_compile_test_code" > conftest.$ac_ext lt_compiler_flag="-o out/conftest2.$ac_objext" # Insert the option either (1) after the last *FLAGS variable, or # (2) before a word containing "conftest.", or (3) at the end. # Note that $ac_compile itself does not contain backslashes and begins # with a dollar sign (not a hyphen), so the echo should work correctly. lt_compile=`echo "$ac_compile" | $SED \ -e 's:.*FLAGS}\{0,1\} :&$lt_compiler_flag :; t' \ -e 's: [^ ]*conftest\.: $lt_compiler_flag&:; t' \ -e 's:$: $lt_compiler_flag:'` (eval echo "\"\$as_me:$LINENO: $lt_compile\"" >&5) (eval "$lt_compile" 2>out/conftest.err) ac_status=$? cat out/conftest.err >&5 echo "$as_me:$LINENO: \$? = $ac_status" >&5 if (exit $ac_status) && test -s out/conftest2.$ac_objext then # The compiler can only warn and ignore the option if not recognized # So say no if there are warnings $ECHO "$_lt_compiler_boilerplate" | $SED '/^$/d' > out/conftest.exp $SED '/^$/d; /^ *+/d' out/conftest.err >out/conftest.er2 if test ! -s out/conftest.er2 || diff out/conftest.exp out/conftest.er2 >/dev/null; then lt_cv_prog_compiler_c_o=yes fi fi chmod u+w . 2>&5 $RM conftest* # SGI C++ compiler will create directory out/ii_files/ for # template instantiation test -d out/ii_files && $RM out/ii_files/* && rmdir out/ii_files $RM out/* && rmdir out cd .. $RM -r conftest $RM conftest* fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $lt_cv_prog_compiler_c_o" >&5 $as_echo "$lt_cv_prog_compiler_c_o" >&6; } hard_links="nottested" if test "$lt_cv_prog_compiler_c_o" = no && test "$need_locks" != no; then # do not overwrite the value of need_locks provided by the user { $as_echo "$as_me:${as_lineno-$LINENO}: checking if we can lock with hard links" >&5 $as_echo_n "checking if we can lock with hard links... " >&6; } hard_links=yes $RM conftest* ln conftest.a conftest.b 2>/dev/null && hard_links=no touch conftest.a ln conftest.a conftest.b 2>&5 || hard_links=no ln conftest.a conftest.b 2>/dev/null && hard_links=no { $as_echo "$as_me:${as_lineno-$LINENO}: result: $hard_links" >&5 $as_echo "$hard_links" >&6; } if test "$hard_links" = no; then { $as_echo "$as_me:${as_lineno-$LINENO}: WARNING: \`$CC' does not support \`-c -o', so \`make -j' may be unsafe" >&5 $as_echo "$as_me: WARNING: \`$CC' does not support \`-c -o', so \`make -j' may be unsafe" >&2;} need_locks=warn fi else need_locks=no fi { $as_echo "$as_me:${as_lineno-$LINENO}: checking whether the $compiler linker ($LD) supports shared libraries" >&5 $as_echo_n "checking whether the $compiler linker ($LD) supports shared libraries... " >&6; } runpath_var= allow_undefined_flag= always_export_symbols=no archive_cmds= archive_expsym_cmds= compiler_needs_object=no enable_shared_with_static_runtimes=no export_dynamic_flag_spec= export_symbols_cmds='$NM $libobjs $convenience | $global_symbol_pipe | $SED '\''s/.* //'\'' | sort | uniq > $export_symbols' hardcode_automatic=no hardcode_direct=no hardcode_direct_absolute=no hardcode_libdir_flag_spec= hardcode_libdir_separator= hardcode_minus_L=no hardcode_shlibpath_var=unsupported inherit_rpath=no link_all_deplibs=unknown module_cmds= module_expsym_cmds= old_archive_from_new_cmds= old_archive_from_expsyms_cmds= thread_safe_flag_spec= whole_archive_flag_spec= # include_expsyms should be a list of space-separated symbols to be *always* # included in the symbol list include_expsyms= # exclude_expsyms can be an extended regexp of symbols to exclude # it will be wrapped by ` (' and `)$', so one must not match beginning or # end of line. Example: `a|bc|.*d.*' will exclude the symbols `a' and `bc', # as well as any symbol that contains `d'. exclude_expsyms='_GLOBAL_OFFSET_TABLE_|_GLOBAL__F[ID]_.*' # Although _GLOBAL_OFFSET_TABLE_ is a valid symbol C name, most a.out # platforms (ab)use it in PIC code, but their linkers get confused if # the symbol is explicitly referenced. Since portable code cannot # rely on this symbol name, it's probably fine to never include it in # preloaded symbol tables. # Exclude shared library initialization/finalization symbols. extract_expsyms_cmds= case $host_os in cygwin* | mingw* | pw32* | cegcc*) # FIXME: the MSVC++ port hasn't been tested in a loooong time # When not using gcc, we currently assume that we are using # Microsoft Visual C++. if test "$GCC" != yes; then with_gnu_ld=no fi ;; interix*) # we just hope/assume this is gcc and not c89 (= MSVC++) with_gnu_ld=yes ;; openbsd*) with_gnu_ld=no ;; linux* | k*bsd*-gnu | gnu*) link_all_deplibs=no ;; esac ld_shlibs=yes # On some targets, GNU ld is compatible enough with the native linker # that we're better off using the native interface for both. lt_use_gnu_ld_interface=no if test "$with_gnu_ld" = yes; then case $host_os in aix*) # The AIX port of GNU ld has always aspired to compatibility # with the native linker. However, as the warning in the GNU ld # block says, versions before 2.19.5* couldn't really create working # shared libraries, regardless of the interface used. case `$LD -v 2>&1` in *\ \(GNU\ Binutils\)\ 2.19.5*) ;; *\ \(GNU\ Binutils\)\ 2.[2-9]*) ;; *\ \(GNU\ Binutils\)\ [3-9]*) ;; *) lt_use_gnu_ld_interface=yes ;; esac ;; *) lt_use_gnu_ld_interface=yes ;; esac fi if test "$lt_use_gnu_ld_interface" = yes; then # If archive_cmds runs LD, not CC, wlarc should be empty wlarc='${wl}' # Set some defaults for GNU ld with shared library support. These # are reset later if shared libraries are not supported. Putting them # here allows them to be overridden if necessary. runpath_var=LD_RUN_PATH hardcode_libdir_flag_spec='${wl}-rpath ${wl}$libdir' export_dynamic_flag_spec='${wl}--export-dynamic' # ancient GNU ld didn't support --whole-archive et. al. if $LD --help 2>&1 | $GREP 'no-whole-archive' > /dev/null; then whole_archive_flag_spec="$wlarc"'--whole-archive$convenience '"$wlarc"'--no-whole-archive' else whole_archive_flag_spec= fi supports_anon_versioning=no case `$LD -v 2>&1` in *GNU\ gold*) supports_anon_versioning=yes ;; *\ [01].* | *\ 2.[0-9].* | *\ 2.10.*) ;; # catch versions < 2.11 *\ 2.11.93.0.2\ *) supports_anon_versioning=yes ;; # RH7.3 ... *\ 2.11.92.0.12\ *) supports_anon_versioning=yes ;; # Mandrake 8.2 ... *\ 2.11.*) ;; # other 2.11 versions *) supports_anon_versioning=yes ;; esac # See if GNU ld supports shared libraries. case $host_os in aix[3-9]*) # On AIX/PPC, the GNU linker is very broken if test "$host_cpu" != ia64; then ld_shlibs=no cat <<_LT_EOF 1>&2 *** Warning: the GNU linker, at least up to release 2.19, is reported *** to be unable to reliably create shared libraries on AIX. *** Therefore, libtool is disabling shared libraries support. If you *** really care for shared libraries, you may want to install binutils *** 2.20 or above, or modify your PATH so that a non-GNU linker is found. *** You will then need to restart the configuration process. _LT_EOF fi ;; amigaos*) case $host_cpu in powerpc) # see comment about AmigaOS4 .so support archive_cmds='$CC -shared $libobjs $deplibs $compiler_flags ${wl}-soname $wl$soname -o $lib' archive_expsym_cmds='' ;; m68k) archive_cmds='$RM $output_objdir/a2ixlibrary.data~$ECHO "#define NAME $libname" > $output_objdir/a2ixlibrary.data~$ECHO "#define LIBRARY_ID 1" >> $output_objdir/a2ixlibrary.data~$ECHO "#define VERSION $major" >> $output_objdir/a2ixlibrary.data~$ECHO "#define REVISION $revision" >> $output_objdir/a2ixlibrary.data~$AR $AR_FLAGS $lib $libobjs~$RANLIB $lib~(cd $output_objdir && a2ixlibrary -32)' hardcode_libdir_flag_spec='-L$libdir' hardcode_minus_L=yes ;; esac ;; beos*) if $LD --help 2>&1 | $GREP ': supported targets:.* elf' > /dev/null; then allow_undefined_flag=unsupported # Joseph Beckenbach says some releases of gcc # support --undefined. This deserves some investigation. FIXME archive_cmds='$CC -nostart $libobjs $deplibs $compiler_flags ${wl}-soname $wl$soname -o $lib' else ld_shlibs=no fi ;; cygwin* | mingw* | pw32* | cegcc*) # _LT_TAGVAR(hardcode_libdir_flag_spec, ) is actually meaningless, # as there is no search path for DLLs. hardcode_libdir_flag_spec='-L$libdir' export_dynamic_flag_spec='${wl}--export-all-symbols' allow_undefined_flag=unsupported always_export_symbols=no enable_shared_with_static_runtimes=yes export_symbols_cmds='$NM $libobjs $convenience | $global_symbol_pipe | $SED -e '\''/^[BCDGRS][ ]/s/.*[ ]\([^ ]*\)/\1 DATA/;s/^.*[ ]__nm__\([^ ]*\)[ ][^ ]*/\1 DATA/;/^I[ ]/d;/^[AITW][ ]/s/.* //'\'' | sort | uniq > $export_symbols' exclude_expsyms='[_]+GLOBAL_OFFSET_TABLE_|[_]+GLOBAL__[FID]_.*|[_]+head_[A-Za-z0-9_]+_dll|[A-Za-z0-9_]+_dll_iname' if $LD --help 2>&1 | $GREP 'auto-import' > /dev/null; then archive_cmds='$CC -shared $libobjs $deplibs $compiler_flags -o $output_objdir/$soname ${wl}--enable-auto-image-base -Xlinker --out-implib -Xlinker $lib' # If the export-symbols file already is a .def file (1st line # is EXPORTS), use it as is; otherwise, prepend... archive_expsym_cmds='if test "x`$SED 1q $export_symbols`" = xEXPORTS; then cp $export_symbols $output_objdir/$soname.def; else echo EXPORTS > $output_objdir/$soname.def; cat $export_symbols >> $output_objdir/$soname.def; fi~ $CC -shared $output_objdir/$soname.def $libobjs $deplibs $compiler_flags -o $output_objdir/$soname ${wl}--enable-auto-image-base -Xlinker --out-implib -Xlinker $lib' else ld_shlibs=no fi ;; haiku*) archive_cmds='$CC -shared $libobjs $deplibs $compiler_flags ${wl}-soname $wl$soname -o $lib' link_all_deplibs=yes ;; interix[3-9]*) hardcode_direct=no hardcode_shlibpath_var=no hardcode_libdir_flag_spec='${wl}-rpath,$libdir' export_dynamic_flag_spec='${wl}-E' # Hack: On Interix 3.x, we cannot compile PIC because of a broken gcc. # Instead, shared libraries are loaded at an image base (0x10000000 by # default) and relocated if they conflict, which is a slow very memory # consuming and fragmenting process. To avoid this, we pick a random, # 256 KiB-aligned image base between 0x50000000 and 0x6FFC0000 at link # time. Moving up from 0x10000000 also allows more sbrk(2) space. archive_cmds='$CC -shared $pic_flag $libobjs $deplibs $compiler_flags ${wl}-h,$soname ${wl}--image-base,`expr ${RANDOM-$$} % 4096 / 2 \* 262144 + 1342177280` -o $lib' archive_expsym_cmds='sed "s,^,_," $export_symbols >$output_objdir/$soname.expsym~$CC -shared $pic_flag $libobjs $deplibs $compiler_flags ${wl}-h,$soname ${wl}--retain-symbols-file,$output_objdir/$soname.expsym ${wl}--image-base,`expr ${RANDOM-$$} % 4096 / 2 \* 262144 + 1342177280` -o $lib' ;; gnu* | linux* | tpf* | k*bsd*-gnu | kopensolaris*-gnu) tmp_diet=no if test "$host_os" = linux-dietlibc; then case $cc_basename in diet\ *) tmp_diet=yes;; # linux-dietlibc with static linking (!diet-dyn) esac fi if $LD --help 2>&1 | $EGREP ': supported targets:.* elf' > /dev/null \ && test "$tmp_diet" = no then tmp_addflag=' $pic_flag' tmp_sharedflag='-shared' case $cc_basename,$host_cpu in pgcc*) # Portland Group C compiler whole_archive_flag_spec='${wl}--whole-archive`for conv in $convenience\"\"; do test -n \"$conv\" && new_convenience=\"$new_convenience,$conv\"; done; func_echo_all \"$new_convenience\"` ${wl}--no-whole-archive' tmp_addflag=' $pic_flag' ;; pgf77* | pgf90* | pgf95* | pgfortran*) # Portland Group f77 and f90 compilers whole_archive_flag_spec='${wl}--whole-archive`for conv in $convenience\"\"; do test -n \"$conv\" && new_convenience=\"$new_convenience,$conv\"; done; func_echo_all \"$new_convenience\"` ${wl}--no-whole-archive' tmp_addflag=' $pic_flag -Mnomain' ;; ecc*,ia64* | icc*,ia64*) # Intel C compiler on ia64 tmp_addflag=' -i_dynamic' ;; efc*,ia64* | ifort*,ia64*) # Intel Fortran compiler on ia64 tmp_addflag=' -i_dynamic -nofor_main' ;; ifc* | ifort*) # Intel Fortran compiler tmp_addflag=' -nofor_main' ;; lf95*) # Lahey Fortran 8.1 whole_archive_flag_spec= tmp_sharedflag='--shared' ;; xl[cC]* | bgxl[cC]* | mpixl[cC]*) # IBM XL C 8.0 on PPC (deal with xlf below) tmp_sharedflag='-qmkshrobj' tmp_addflag= ;; nvcc*) # Cuda Compiler Driver 2.2 whole_archive_flag_spec='${wl}--whole-archive`for conv in $convenience\"\"; do test -n \"$conv\" && new_convenience=\"$new_convenience,$conv\"; done; func_echo_all \"$new_convenience\"` ${wl}--no-whole-archive' compiler_needs_object=yes ;; esac case `$CC -V 2>&1 | sed 5q` in *Sun\ C*) # Sun C 5.9 whole_archive_flag_spec='${wl}--whole-archive`new_convenience=; for conv in $convenience\"\"; do test -z \"$conv\" || new_convenience=\"$new_convenience,$conv\"; done; func_echo_all \"$new_convenience\"` ${wl}--no-whole-archive' compiler_needs_object=yes tmp_sharedflag='-G' ;; *Sun\ F*) # Sun Fortran 8.3 tmp_sharedflag='-G' ;; esac archive_cmds='$CC '"$tmp_sharedflag""$tmp_addflag"' $libobjs $deplibs $compiler_flags ${wl}-soname $wl$soname -o $lib' if test "x$supports_anon_versioning" = xyes; then archive_expsym_cmds='echo "{ global:" > $output_objdir/$libname.ver~ cat $export_symbols | sed -e "s/\(.*\)/\1;/" >> $output_objdir/$libname.ver~ echo "local: *; };" >> $output_objdir/$libname.ver~ $CC '"$tmp_sharedflag""$tmp_addflag"' $libobjs $deplibs $compiler_flags ${wl}-soname $wl$soname ${wl}-version-script ${wl}$output_objdir/$libname.ver -o $lib' fi case $cc_basename in xlf* | bgf* | bgxlf* | mpixlf*) # IBM XL Fortran 10.1 on PPC cannot create shared libs itself whole_archive_flag_spec='--whole-archive$convenience --no-whole-archive' hardcode_libdir_flag_spec='${wl}-rpath ${wl}$libdir' archive_cmds='$LD -shared $libobjs $deplibs $linker_flags -soname $soname -o $lib' if test "x$supports_anon_versioning" = xyes; then archive_expsym_cmds='echo "{ global:" > $output_objdir/$libname.ver~ cat $export_symbols | sed -e "s/\(.*\)/\1;/" >> $output_objdir/$libname.ver~ echo "local: *; };" >> $output_objdir/$libname.ver~ $LD -shared $libobjs $deplibs $linker_flags -soname $soname -version-script $output_objdir/$libname.ver -o $lib' fi ;; esac else ld_shlibs=no fi ;; netbsd* | netbsdelf*-gnu) if echo __ELF__ | $CC -E - | $GREP __ELF__ >/dev/null; then archive_cmds='$LD -Bshareable $libobjs $deplibs $linker_flags -o $lib' wlarc= else archive_cmds='$CC -shared $pic_flag $libobjs $deplibs $compiler_flags ${wl}-soname $wl$soname -o $lib' archive_expsym_cmds='$CC -shared $pic_flag $libobjs $deplibs $compiler_flags ${wl}-soname $wl$soname ${wl}-retain-symbols-file $wl$export_symbols -o $lib' fi ;; solaris*) if $LD -v 2>&1 | $GREP 'BFD 2\.8' > /dev/null; then ld_shlibs=no cat <<_LT_EOF 1>&2 *** Warning: The releases 2.8.* of the GNU linker cannot reliably *** create shared libraries on Solaris systems. Therefore, libtool *** is disabling shared libraries support. We urge you to upgrade GNU *** binutils to release 2.9.1 or newer. Another option is to modify *** your PATH or compiler configuration so that the native linker is *** used, and then restart. _LT_EOF elif $LD --help 2>&1 | $GREP ': supported targets:.* elf' > /dev/null; then archive_cmds='$CC -shared $pic_flag $libobjs $deplibs $compiler_flags ${wl}-soname $wl$soname -o $lib' archive_expsym_cmds='$CC -shared $pic_flag $libobjs $deplibs $compiler_flags ${wl}-soname $wl$soname ${wl}-retain-symbols-file $wl$export_symbols -o $lib' else ld_shlibs=no fi ;; sysv5* | sco3.2v5* | sco5v6* | unixware* | OpenUNIX*) case `$LD -v 2>&1` in *\ [01].* | *\ 2.[0-9].* | *\ 2.1[0-5].*) ld_shlibs=no cat <<_LT_EOF 1>&2 *** Warning: Releases of the GNU linker prior to 2.16.91.0.3 can not *** reliably create shared libraries on SCO systems. Therefore, libtool *** is disabling shared libraries support. We urge you to upgrade GNU *** binutils to release 2.16.91.0.3 or newer. Another option is to modify *** your PATH or compiler configuration so that the native linker is *** used, and then restart. _LT_EOF ;; *) # For security reasons, it is highly recommended that you always # use absolute paths for naming shared libraries, and exclude the # DT_RUNPATH tag from executables and libraries. But doing so # requires that you compile everything twice, which is a pain. if $LD --help 2>&1 | $GREP ': supported targets:.* elf' > /dev/null; then hardcode_libdir_flag_spec='${wl}-rpath ${wl}$libdir' archive_cmds='$CC -shared $libobjs $deplibs $compiler_flags ${wl}-soname $wl$soname -o $lib' archive_expsym_cmds='$CC -shared $libobjs $deplibs $compiler_flags ${wl}-soname $wl$soname ${wl}-retain-symbols-file $wl$export_symbols -o $lib' else ld_shlibs=no fi ;; esac ;; sunos4*) archive_cmds='$LD -assert pure-text -Bshareable -o $lib $libobjs $deplibs $linker_flags' wlarc= hardcode_direct=yes hardcode_shlibpath_var=no ;; *) if $LD --help 2>&1 | $GREP ': supported targets:.* elf' > /dev/null; then archive_cmds='$CC -shared $pic_flag $libobjs $deplibs $compiler_flags ${wl}-soname $wl$soname -o $lib' archive_expsym_cmds='$CC -shared $pic_flag $libobjs $deplibs $compiler_flags ${wl}-soname $wl$soname ${wl}-retain-symbols-file $wl$export_symbols -o $lib' else ld_shlibs=no fi ;; esac if test "$ld_shlibs" = no; then runpath_var= hardcode_libdir_flag_spec= export_dynamic_flag_spec= whole_archive_flag_spec= fi else # PORTME fill in a description of your system's linker (not GNU ld) case $host_os in aix3*) allow_undefined_flag=unsupported always_export_symbols=yes archive_expsym_cmds='$LD -o $output_objdir/$soname $libobjs $deplibs $linker_flags -bE:$export_symbols -T512 -H512 -bM:SRE~$AR $AR_FLAGS $lib $output_objdir/$soname' # Note: this linker hardcodes the directories in LIBPATH if there # are no directories specified by -L. hardcode_minus_L=yes if test "$GCC" = yes && test -z "$lt_prog_compiler_static"; then # Neither direct hardcoding nor static linking is supported with a # broken collect2. hardcode_direct=unsupported fi ;; aix[4-9]*) if test "$host_cpu" = ia64; then # On IA64, the linker does run time linking by default, so we don't # have to do anything special. aix_use_runtimelinking=no exp_sym_flag='-Bexport' no_entry_flag="" else # If we're using GNU nm, then we don't want the "-C" option. # -C means demangle to AIX nm, but means don't demangle with GNU nm # Also, AIX nm treats weak defined symbols like other global # defined symbols, whereas GNU nm marks them as "W". if $NM -V 2>&1 | $GREP 'GNU' > /dev/null; then export_symbols_cmds='$NM -Bpg $libobjs $convenience | awk '\''{ if (((\$ 2 == "T") || (\$ 2 == "D") || (\$ 2 == "B") || (\$ 2 == "W")) && (substr(\$ 3,1,1) != ".")) { print \$ 3 } }'\'' | sort -u > $export_symbols' else export_symbols_cmds='$NM -BCpg $libobjs $convenience | awk '\''{ if (((\$ 2 == "T") || (\$ 2 == "D") || (\$ 2 == "B")) && (substr(\$ 3,1,1) != ".")) { print \$ 3 } }'\'' | sort -u > $export_symbols' fi aix_use_runtimelinking=no # Test if we are trying to use run time linking or normal # AIX style linking. If -brtl is somewhere in LDFLAGS, we # need to do runtime linking. case $host_os in aix4.[23]|aix4.[23].*|aix[5-9]*) for ld_flag in $LDFLAGS; do if (test $ld_flag = "-brtl" || test $ld_flag = "-Wl,-brtl"); then aix_use_runtimelinking=yes break fi done ;; esac exp_sym_flag='-bexport' no_entry_flag='-bnoentry' fi # When large executables or shared objects are built, AIX ld can # have problems creating the table of contents. If linking a library # or program results in "error TOC overflow" add -mminimal-toc to # CXXFLAGS/CFLAGS for g++/gcc. In the cases where that is not # enough to fix the problem, add -Wl,-bbigtoc to LDFLAGS. archive_cmds='' hardcode_direct=yes hardcode_direct_absolute=yes hardcode_libdir_separator=':' link_all_deplibs=yes file_list_spec='${wl}-f,' if test "$GCC" = yes; then case $host_os in aix4.[012]|aix4.[012].*) # We only want to do this on AIX 4.2 and lower, the check # below for broken collect2 doesn't work under 4.3+ collect2name=`${CC} -print-prog-name=collect2` if test -f "$collect2name" && strings "$collect2name" | $GREP resolve_lib_name >/dev/null then # We have reworked collect2 : else # We have old collect2 hardcode_direct=unsupported # It fails to find uninstalled libraries when the uninstalled # path is not listed in the libpath. Setting hardcode_minus_L # to unsupported forces relinking hardcode_minus_L=yes hardcode_libdir_flag_spec='-L$libdir' hardcode_libdir_separator= fi ;; esac shared_flag='-shared' if test "$aix_use_runtimelinking" = yes; then shared_flag="$shared_flag "'${wl}-G' fi link_all_deplibs=no else # not using gcc if test "$host_cpu" = ia64; then # VisualAge C++, Version 5.5 for AIX 5L for IA-64, Beta 3 Release # chokes on -Wl,-G. The following line is correct: shared_flag='-G' else if test "$aix_use_runtimelinking" = yes; then shared_flag='${wl}-G' else shared_flag='${wl}-bM:SRE' fi fi fi export_dynamic_flag_spec='${wl}-bexpall' # It seems that -bexpall does not export symbols beginning with # underscore (_), so it is better to generate a list of symbols to export. always_export_symbols=yes if test "$aix_use_runtimelinking" = yes; then # Warning - without using the other runtime loading flags (-brtl), # -berok will link without error, but may produce a broken library. allow_undefined_flag='-berok' # Determine the default libpath from the value encoded in an # empty executable. if test "${lt_cv_aix_libpath+set}" = set; then aix_libpath=$lt_cv_aix_libpath else if ${lt_cv_aix_libpath_+:} false; then : $as_echo_n "(cached) " >&6 else cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ int main () { ; return 0; } _ACEOF if ac_fn_c_try_link "$LINENO"; then : lt_aix_libpath_sed=' /Import File Strings/,/^$/ { /^0/ { s/^0 *\([^ ]*\) *$/\1/ p } }' lt_cv_aix_libpath_=`dump -H conftest$ac_exeext 2>/dev/null | $SED -n -e "$lt_aix_libpath_sed"` # Check for a 64-bit object if we didn't find anything. if test -z "$lt_cv_aix_libpath_"; then lt_cv_aix_libpath_=`dump -HX64 conftest$ac_exeext 2>/dev/null | $SED -n -e "$lt_aix_libpath_sed"` fi fi rm -f core conftest.err conftest.$ac_objext \ conftest$ac_exeext conftest.$ac_ext if test -z "$lt_cv_aix_libpath_"; then lt_cv_aix_libpath_="/usr/lib:/lib" fi fi aix_libpath=$lt_cv_aix_libpath_ fi hardcode_libdir_flag_spec='${wl}-blibpath:$libdir:'"$aix_libpath" archive_expsym_cmds='$CC -o $output_objdir/$soname $libobjs $deplibs '"\${wl}$no_entry_flag"' $compiler_flags `if test "x${allow_undefined_flag}" != "x"; then func_echo_all "${wl}${allow_undefined_flag}"; else :; fi` '"\${wl}$exp_sym_flag:\$export_symbols $shared_flag" else if test "$host_cpu" = ia64; then hardcode_libdir_flag_spec='${wl}-R $libdir:/usr/lib:/lib' allow_undefined_flag="-z nodefs" archive_expsym_cmds="\$CC $shared_flag"' -o $output_objdir/$soname $libobjs $deplibs '"\${wl}$no_entry_flag"' $compiler_flags ${wl}${allow_undefined_flag} '"\${wl}$exp_sym_flag:\$export_symbols" else # Determine the default libpath from the value encoded in an # empty executable. if test "${lt_cv_aix_libpath+set}" = set; then aix_libpath=$lt_cv_aix_libpath else if ${lt_cv_aix_libpath_+:} false; then : $as_echo_n "(cached) " >&6 else cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ int main () { ; return 0; } _ACEOF if ac_fn_c_try_link "$LINENO"; then : lt_aix_libpath_sed=' /Import File Strings/,/^$/ { /^0/ { s/^0 *\([^ ]*\) *$/\1/ p } }' lt_cv_aix_libpath_=`dump -H conftest$ac_exeext 2>/dev/null | $SED -n -e "$lt_aix_libpath_sed"` # Check for a 64-bit object if we didn't find anything. if test -z "$lt_cv_aix_libpath_"; then lt_cv_aix_libpath_=`dump -HX64 conftest$ac_exeext 2>/dev/null | $SED -n -e "$lt_aix_libpath_sed"` fi fi rm -f core conftest.err conftest.$ac_objext \ conftest$ac_exeext conftest.$ac_ext if test -z "$lt_cv_aix_libpath_"; then lt_cv_aix_libpath_="/usr/lib:/lib" fi fi aix_libpath=$lt_cv_aix_libpath_ fi hardcode_libdir_flag_spec='${wl}-blibpath:$libdir:'"$aix_libpath" # Warning - without using the other run time loading flags, # -berok will link without error, but may produce a broken library. no_undefined_flag=' ${wl}-bernotok' allow_undefined_flag=' ${wl}-berok' if test "$with_gnu_ld" = yes; then # We only use this code for GNU lds that support --whole-archive. whole_archive_flag_spec='${wl}--whole-archive$convenience ${wl}--no-whole-archive' else # Exported symbols can be pulled into shared objects from archives whole_archive_flag_spec='$convenience' fi archive_cmds_need_lc=yes # This is similar to how AIX traditionally builds its shared libraries. archive_expsym_cmds="\$CC $shared_flag"' -o $output_objdir/$soname $libobjs $deplibs ${wl}-bnoentry $compiler_flags ${wl}-bE:$export_symbols${allow_undefined_flag}~$AR $AR_FLAGS $output_objdir/$libname$release.a $output_objdir/$soname' fi fi ;; amigaos*) case $host_cpu in powerpc) # see comment about AmigaOS4 .so support archive_cmds='$CC -shared $libobjs $deplibs $compiler_flags ${wl}-soname $wl$soname -o $lib' archive_expsym_cmds='' ;; m68k) archive_cmds='$RM $output_objdir/a2ixlibrary.data~$ECHO "#define NAME $libname" > $output_objdir/a2ixlibrary.data~$ECHO "#define LIBRARY_ID 1" >> $output_objdir/a2ixlibrary.data~$ECHO "#define VERSION $major" >> $output_objdir/a2ixlibrary.data~$ECHO "#define REVISION $revision" >> $output_objdir/a2ixlibrary.data~$AR $AR_FLAGS $lib $libobjs~$RANLIB $lib~(cd $output_objdir && a2ixlibrary -32)' hardcode_libdir_flag_spec='-L$libdir' hardcode_minus_L=yes ;; esac ;; bsdi[45]*) export_dynamic_flag_spec=-rdynamic ;; cygwin* | mingw* | pw32* | cegcc*) # When not using gcc, we currently assume that we are using # Microsoft Visual C++. # hardcode_libdir_flag_spec is actually meaningless, as there is # no search path for DLLs. case $cc_basename in cl*) # Native MSVC hardcode_libdir_flag_spec=' ' allow_undefined_flag=unsupported always_export_symbols=yes file_list_spec='@' # Tell ltmain to make .lib files, not .a files. libext=lib # Tell ltmain to make .dll files, not .so files. shrext_cmds=".dll" # FIXME: Setting linknames here is a bad hack. archive_cmds='$CC -o $output_objdir/$soname $libobjs $compiler_flags $deplibs -Wl,-dll~linknames=' archive_expsym_cmds='if test "x`$SED 1q $export_symbols`" = xEXPORTS; then sed -n -e 's/\\\\\\\(.*\\\\\\\)/-link\\\ -EXPORT:\\\\\\\1/' -e '1\\\!p' < $export_symbols > $output_objdir/$soname.exp; else sed -e 's/\\\\\\\(.*\\\\\\\)/-link\\\ -EXPORT:\\\\\\\1/' < $export_symbols > $output_objdir/$soname.exp; fi~ $CC -o $tool_output_objdir$soname $libobjs $compiler_flags $deplibs "@$tool_output_objdir$soname.exp" -Wl,-DLL,-IMPLIB:"$tool_output_objdir$libname.dll.lib"~ linknames=' # The linker will not automatically build a static lib if we build a DLL. # _LT_TAGVAR(old_archive_from_new_cmds, )='true' enable_shared_with_static_runtimes=yes exclude_expsyms='_NULL_IMPORT_DESCRIPTOR|_IMPORT_DESCRIPTOR_.*' export_symbols_cmds='$NM $libobjs $convenience | $global_symbol_pipe | $SED -e '\''/^[BCDGRS][ ]/s/.*[ ]\([^ ]*\)/\1,DATA/'\'' | $SED -e '\''/^[AITW][ ]/s/.*[ ]//'\'' | sort | uniq > $export_symbols' # Don't use ranlib old_postinstall_cmds='chmod 644 $oldlib' postlink_cmds='lt_outputfile="@OUTPUT@"~ lt_tool_outputfile="@TOOL_OUTPUT@"~ case $lt_outputfile in *.exe|*.EXE) ;; *) lt_outputfile="$lt_outputfile.exe" lt_tool_outputfile="$lt_tool_outputfile.exe" ;; esac~ if test "$MANIFEST_TOOL" != ":" && test -f "$lt_outputfile.manifest"; then $MANIFEST_TOOL -manifest "$lt_tool_outputfile.manifest" -outputresource:"$lt_tool_outputfile" || exit 1; $RM "$lt_outputfile.manifest"; fi' ;; *) # Assume MSVC wrapper hardcode_libdir_flag_spec=' ' allow_undefined_flag=unsupported # Tell ltmain to make .lib files, not .a files. libext=lib # Tell ltmain to make .dll files, not .so files. shrext_cmds=".dll" # FIXME: Setting linknames here is a bad hack. archive_cmds='$CC -o $lib $libobjs $compiler_flags `func_echo_all "$deplibs" | $SED '\''s/ -lc$//'\''` -link -dll~linknames=' # The linker will automatically build a .lib file if we build a DLL. old_archive_from_new_cmds='true' # FIXME: Should let the user specify the lib program. old_archive_cmds='lib -OUT:$oldlib$oldobjs$old_deplibs' enable_shared_with_static_runtimes=yes ;; esac ;; darwin* | rhapsody*) archive_cmds_need_lc=no hardcode_direct=no hardcode_automatic=yes hardcode_shlibpath_var=unsupported if test "$lt_cv_ld_force_load" = "yes"; then whole_archive_flag_spec='`for conv in $convenience\"\"; do test -n \"$conv\" && new_convenience=\"$new_convenience ${wl}-force_load,$conv\"; done; func_echo_all \"$new_convenience\"`' else whole_archive_flag_spec='' fi link_all_deplibs=yes allow_undefined_flag="$_lt_dar_allow_undefined" case $cc_basename in ifort*) _lt_dar_can_shared=yes ;; *) _lt_dar_can_shared=$GCC ;; esac if test "$_lt_dar_can_shared" = "yes"; then output_verbose_link_cmd=func_echo_all archive_cmds="\$CC -dynamiclib \$allow_undefined_flag -o \$lib \$libobjs \$deplibs \$compiler_flags -install_name \$rpath/\$soname \$verstring $_lt_dar_single_mod${_lt_dsymutil}" module_cmds="\$CC \$allow_undefined_flag -o \$lib -bundle \$libobjs \$deplibs \$compiler_flags${_lt_dsymutil}" archive_expsym_cmds="sed 's,^,_,' < \$export_symbols > \$output_objdir/\${libname}-symbols.expsym~\$CC -dynamiclib \$allow_undefined_flag -o \$lib \$libobjs \$deplibs \$compiler_flags -install_name \$rpath/\$soname \$verstring ${_lt_dar_single_mod}${_lt_dar_export_syms}${_lt_dsymutil}" module_expsym_cmds="sed -e 's,^,_,' < \$export_symbols > \$output_objdir/\${libname}-symbols.expsym~\$CC \$allow_undefined_flag -o \$lib -bundle \$libobjs \$deplibs \$compiler_flags${_lt_dar_export_syms}${_lt_dsymutil}" else ld_shlibs=no fi ;; dgux*) archive_cmds='$LD -G -h $soname -o $lib $libobjs $deplibs $linker_flags' hardcode_libdir_flag_spec='-L$libdir' hardcode_shlibpath_var=no ;; # FreeBSD 2.2.[012] allows us to include c++rt0.o to get C++ constructor # support. Future versions do this automatically, but an explicit c++rt0.o # does not break anything, and helps significantly (at the cost of a little # extra space). freebsd2.2*) archive_cmds='$LD -Bshareable -o $lib $libobjs $deplibs $linker_flags /usr/lib/c++rt0.o' hardcode_libdir_flag_spec='-R$libdir' hardcode_direct=yes hardcode_shlibpath_var=no ;; # Unfortunately, older versions of FreeBSD 2 do not have this feature. freebsd2.*) archive_cmds='$LD -Bshareable -o $lib $libobjs $deplibs $linker_flags' hardcode_direct=yes hardcode_minus_L=yes hardcode_shlibpath_var=no ;; # FreeBSD 3 and greater uses gcc -shared to do shared libraries. freebsd* | dragonfly*) archive_cmds='$CC -shared $pic_flag -o $lib $libobjs $deplibs $compiler_flags' hardcode_libdir_flag_spec='-R$libdir' hardcode_direct=yes hardcode_shlibpath_var=no ;; hpux9*) if test "$GCC" = yes; then archive_cmds='$RM $output_objdir/$soname~$CC -shared $pic_flag ${wl}+b ${wl}$install_libdir -o $output_objdir/$soname $libobjs $deplibs $compiler_flags~test $output_objdir/$soname = $lib || mv $output_objdir/$soname $lib' else archive_cmds='$RM $output_objdir/$soname~$LD -b +b $install_libdir -o $output_objdir/$soname $libobjs $deplibs $linker_flags~test $output_objdir/$soname = $lib || mv $output_objdir/$soname $lib' fi hardcode_libdir_flag_spec='${wl}+b ${wl}$libdir' hardcode_libdir_separator=: hardcode_direct=yes # hardcode_minus_L: Not really in the search PATH, # but as the default location of the library. hardcode_minus_L=yes export_dynamic_flag_spec='${wl}-E' ;; hpux10*) if test "$GCC" = yes && test "$with_gnu_ld" = no; then archive_cmds='$CC -shared $pic_flag ${wl}+h ${wl}$soname ${wl}+b ${wl}$install_libdir -o $lib $libobjs $deplibs $compiler_flags' else archive_cmds='$LD -b +h $soname +b $install_libdir -o $lib $libobjs $deplibs $linker_flags' fi if test "$with_gnu_ld" = no; then hardcode_libdir_flag_spec='${wl}+b ${wl}$libdir' hardcode_libdir_separator=: hardcode_direct=yes hardcode_direct_absolute=yes export_dynamic_flag_spec='${wl}-E' # hardcode_minus_L: Not really in the search PATH, # but as the default location of the library. hardcode_minus_L=yes fi ;; hpux11*) if test "$GCC" = yes && test "$with_gnu_ld" = no; then case $host_cpu in hppa*64*) archive_cmds='$CC -shared ${wl}+h ${wl}$soname -o $lib $libobjs $deplibs $compiler_flags' ;; ia64*) archive_cmds='$CC -shared $pic_flag ${wl}+h ${wl}$soname ${wl}+nodefaultrpath -o $lib $libobjs $deplibs $compiler_flags' ;; *) archive_cmds='$CC -shared $pic_flag ${wl}+h ${wl}$soname ${wl}+b ${wl}$install_libdir -o $lib $libobjs $deplibs $compiler_flags' ;; esac else case $host_cpu in hppa*64*) archive_cmds='$CC -b ${wl}+h ${wl}$soname -o $lib $libobjs $deplibs $compiler_flags' ;; ia64*) archive_cmds='$CC -b ${wl}+h ${wl}$soname ${wl}+nodefaultrpath -o $lib $libobjs $deplibs $compiler_flags' ;; *) # Older versions of the 11.00 compiler do not understand -b yet # (HP92453-01 A.11.01.20 doesn't, HP92453-01 B.11.X.35175-35176.GP does) { $as_echo "$as_me:${as_lineno-$LINENO}: checking if $CC understands -b" >&5 $as_echo_n "checking if $CC understands -b... " >&6; } if ${lt_cv_prog_compiler__b+:} false; then : $as_echo_n "(cached) " >&6 else lt_cv_prog_compiler__b=no save_LDFLAGS="$LDFLAGS" LDFLAGS="$LDFLAGS -b" echo "$lt_simple_link_test_code" > conftest.$ac_ext if (eval $ac_link 2>conftest.err) && test -s conftest$ac_exeext; then # The linker can only warn and ignore the option if not recognized # So say no if there are warnings if test -s conftest.err; then # Append any errors to the config.log. cat conftest.err 1>&5 $ECHO "$_lt_linker_boilerplate" | $SED '/^$/d' > conftest.exp $SED '/^$/d; /^ *+/d' conftest.err >conftest.er2 if diff conftest.exp conftest.er2 >/dev/null; then lt_cv_prog_compiler__b=yes fi else lt_cv_prog_compiler__b=yes fi fi $RM -r conftest* LDFLAGS="$save_LDFLAGS" fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $lt_cv_prog_compiler__b" >&5 $as_echo "$lt_cv_prog_compiler__b" >&6; } if test x"$lt_cv_prog_compiler__b" = xyes; then archive_cmds='$CC -b ${wl}+h ${wl}$soname ${wl}+b ${wl}$install_libdir -o $lib $libobjs $deplibs $compiler_flags' else archive_cmds='$LD -b +h $soname +b $install_libdir -o $lib $libobjs $deplibs $linker_flags' fi ;; esac fi if test "$with_gnu_ld" = no; then hardcode_libdir_flag_spec='${wl}+b ${wl}$libdir' hardcode_libdir_separator=: case $host_cpu in hppa*64*|ia64*) hardcode_direct=no hardcode_shlibpath_var=no ;; *) hardcode_direct=yes hardcode_direct_absolute=yes export_dynamic_flag_spec='${wl}-E' # hardcode_minus_L: Not really in the search PATH, # but as the default location of the library. hardcode_minus_L=yes ;; esac fi ;; irix5* | irix6* | nonstopux*) if test "$GCC" = yes; then archive_cmds='$CC -shared $pic_flag $libobjs $deplibs $compiler_flags ${wl}-soname ${wl}$soname `test -n "$verstring" && func_echo_all "${wl}-set_version ${wl}$verstring"` ${wl}-update_registry ${wl}${output_objdir}/so_locations -o $lib' # Try to use the -exported_symbol ld option, if it does not # work, assume that -exports_file does not work either and # implicitly export all symbols. # This should be the same for all languages, so no per-tag cache variable. { $as_echo "$as_me:${as_lineno-$LINENO}: checking whether the $host_os linker accepts -exported_symbol" >&5 $as_echo_n "checking whether the $host_os linker accepts -exported_symbol... " >&6; } if ${lt_cv_irix_exported_symbol+:} false; then : $as_echo_n "(cached) " >&6 else save_LDFLAGS="$LDFLAGS" LDFLAGS="$LDFLAGS -shared ${wl}-exported_symbol ${wl}foo ${wl}-update_registry ${wl}/dev/null" cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ int foo (void) { return 0; } _ACEOF if ac_fn_c_try_link "$LINENO"; then : lt_cv_irix_exported_symbol=yes else lt_cv_irix_exported_symbol=no fi rm -f core conftest.err conftest.$ac_objext \ conftest$ac_exeext conftest.$ac_ext LDFLAGS="$save_LDFLAGS" fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $lt_cv_irix_exported_symbol" >&5 $as_echo "$lt_cv_irix_exported_symbol" >&6; } if test "$lt_cv_irix_exported_symbol" = yes; then archive_expsym_cmds='$CC -shared $pic_flag $libobjs $deplibs $compiler_flags ${wl}-soname ${wl}$soname `test -n "$verstring" && func_echo_all "${wl}-set_version ${wl}$verstring"` ${wl}-update_registry ${wl}${output_objdir}/so_locations ${wl}-exports_file ${wl}$export_symbols -o $lib' fi else archive_cmds='$CC -shared $libobjs $deplibs $compiler_flags -soname $soname `test -n "$verstring" && func_echo_all "-set_version $verstring"` -update_registry ${output_objdir}/so_locations -o $lib' archive_expsym_cmds='$CC -shared $libobjs $deplibs $compiler_flags -soname $soname `test -n "$verstring" && func_echo_all "-set_version $verstring"` -update_registry ${output_objdir}/so_locations -exports_file $export_symbols -o $lib' fi archive_cmds_need_lc='no' hardcode_libdir_flag_spec='${wl}-rpath ${wl}$libdir' hardcode_libdir_separator=: inherit_rpath=yes link_all_deplibs=yes ;; netbsd* | netbsdelf*-gnu) if echo __ELF__ | $CC -E - | $GREP __ELF__ >/dev/null; then archive_cmds='$LD -Bshareable -o $lib $libobjs $deplibs $linker_flags' # a.out else archive_cmds='$LD -shared -o $lib $libobjs $deplibs $linker_flags' # ELF fi hardcode_libdir_flag_spec='-R$libdir' hardcode_direct=yes hardcode_shlibpath_var=no ;; newsos6) archive_cmds='$LD -G -h $soname -o $lib $libobjs $deplibs $linker_flags' hardcode_direct=yes hardcode_libdir_flag_spec='${wl}-rpath ${wl}$libdir' hardcode_libdir_separator=: hardcode_shlibpath_var=no ;; *nto* | *qnx*) ;; openbsd*) if test -f /usr/libexec/ld.so; then hardcode_direct=yes hardcode_shlibpath_var=no hardcode_direct_absolute=yes if test -z "`echo __ELF__ | $CC -E - | $GREP __ELF__`" || test "$host_os-$host_cpu" = "openbsd2.8-powerpc"; then archive_cmds='$CC -shared $pic_flag -o $lib $libobjs $deplibs $compiler_flags' archive_expsym_cmds='$CC -shared $pic_flag -o $lib $libobjs $deplibs $compiler_flags ${wl}-retain-symbols-file,$export_symbols' hardcode_libdir_flag_spec='${wl}-rpath,$libdir' export_dynamic_flag_spec='${wl}-E' else case $host_os in openbsd[01].* | openbsd2.[0-7] | openbsd2.[0-7].*) archive_cmds='$LD -Bshareable -o $lib $libobjs $deplibs $linker_flags' hardcode_libdir_flag_spec='-R$libdir' ;; *) archive_cmds='$CC -shared $pic_flag -o $lib $libobjs $deplibs $compiler_flags' hardcode_libdir_flag_spec='${wl}-rpath,$libdir' ;; esac fi else ld_shlibs=no fi ;; os2*) hardcode_libdir_flag_spec='-L$libdir' hardcode_minus_L=yes allow_undefined_flag=unsupported archive_cmds='$ECHO "LIBRARY $libname INITINSTANCE" > $output_objdir/$libname.def~$ECHO "DESCRIPTION \"$libname\"" >> $output_objdir/$libname.def~echo DATA >> $output_objdir/$libname.def~echo " SINGLE NONSHARED" >> $output_objdir/$libname.def~echo EXPORTS >> $output_objdir/$libname.def~emxexp $libobjs >> $output_objdir/$libname.def~$CC -Zdll -Zcrtdll -o $lib $libobjs $deplibs $compiler_flags $output_objdir/$libname.def' old_archive_from_new_cmds='emximp -o $output_objdir/$libname.a $output_objdir/$libname.def' ;; osf3*) if test "$GCC" = yes; then allow_undefined_flag=' ${wl}-expect_unresolved ${wl}\*' archive_cmds='$CC -shared${allow_undefined_flag} $libobjs $deplibs $compiler_flags ${wl}-soname ${wl}$soname `test -n "$verstring" && func_echo_all "${wl}-set_version ${wl}$verstring"` ${wl}-update_registry ${wl}${output_objdir}/so_locations -o $lib' else allow_undefined_flag=' -expect_unresolved \*' archive_cmds='$CC -shared${allow_undefined_flag} $libobjs $deplibs $compiler_flags -soname $soname `test -n "$verstring" && func_echo_all "-set_version $verstring"` -update_registry ${output_objdir}/so_locations -o $lib' fi archive_cmds_need_lc='no' hardcode_libdir_flag_spec='${wl}-rpath ${wl}$libdir' hardcode_libdir_separator=: ;; osf4* | osf5*) # as osf3* with the addition of -msym flag if test "$GCC" = yes; then allow_undefined_flag=' ${wl}-expect_unresolved ${wl}\*' archive_cmds='$CC -shared${allow_undefined_flag} $pic_flag $libobjs $deplibs $compiler_flags ${wl}-msym ${wl}-soname ${wl}$soname `test -n "$verstring" && func_echo_all "${wl}-set_version ${wl}$verstring"` ${wl}-update_registry ${wl}${output_objdir}/so_locations -o $lib' hardcode_libdir_flag_spec='${wl}-rpath ${wl}$libdir' else allow_undefined_flag=' -expect_unresolved \*' archive_cmds='$CC -shared${allow_undefined_flag} $libobjs $deplibs $compiler_flags -msym -soname $soname `test -n "$verstring" && func_echo_all "-set_version $verstring"` -update_registry ${output_objdir}/so_locations -o $lib' archive_expsym_cmds='for i in `cat $export_symbols`; do printf "%s %s\\n" -exported_symbol "\$i" >> $lib.exp; done; printf "%s\\n" "-hidden">> $lib.exp~ $CC -shared${allow_undefined_flag} ${wl}-input ${wl}$lib.exp $compiler_flags $libobjs $deplibs -soname $soname `test -n "$verstring" && $ECHO "-set_version $verstring"` -update_registry ${output_objdir}/so_locations -o $lib~$RM $lib.exp' # Both c and cxx compiler support -rpath directly hardcode_libdir_flag_spec='-rpath $libdir' fi archive_cmds_need_lc='no' hardcode_libdir_separator=: ;; solaris*) no_undefined_flag=' -z defs' if test "$GCC" = yes; then wlarc='${wl}' archive_cmds='$CC -shared $pic_flag ${wl}-z ${wl}text ${wl}-h ${wl}$soname -o $lib $libobjs $deplibs $compiler_flags' archive_expsym_cmds='echo "{ global:" > $lib.exp~cat $export_symbols | $SED -e "s/\(.*\)/\1;/" >> $lib.exp~echo "local: *; };" >> $lib.exp~ $CC -shared $pic_flag ${wl}-z ${wl}text ${wl}-M ${wl}$lib.exp ${wl}-h ${wl}$soname -o $lib $libobjs $deplibs $compiler_flags~$RM $lib.exp' else case `$CC -V 2>&1` in *"Compilers 5.0"*) wlarc='' archive_cmds='$LD -G${allow_undefined_flag} -h $soname -o $lib $libobjs $deplibs $linker_flags' archive_expsym_cmds='echo "{ global:" > $lib.exp~cat $export_symbols | $SED -e "s/\(.*\)/\1;/" >> $lib.exp~echo "local: *; };" >> $lib.exp~ $LD -G${allow_undefined_flag} -M $lib.exp -h $soname -o $lib $libobjs $deplibs $linker_flags~$RM $lib.exp' ;; *) wlarc='${wl}' archive_cmds='$CC -G${allow_undefined_flag} -h $soname -o $lib $libobjs $deplibs $compiler_flags' archive_expsym_cmds='echo "{ global:" > $lib.exp~cat $export_symbols | $SED -e "s/\(.*\)/\1;/" >> $lib.exp~echo "local: *; };" >> $lib.exp~ $CC -G${allow_undefined_flag} -M $lib.exp -h $soname -o $lib $libobjs $deplibs $compiler_flags~$RM $lib.exp' ;; esac fi hardcode_libdir_flag_spec='-R$libdir' hardcode_shlibpath_var=no case $host_os in solaris2.[0-5] | solaris2.[0-5].*) ;; *) # The compiler driver will combine and reorder linker options, # but understands `-z linker_flag'. GCC discards it without `$wl', # but is careful enough not to reorder. # Supported since Solaris 2.6 (maybe 2.5.1?) if test "$GCC" = yes; then whole_archive_flag_spec='${wl}-z ${wl}allextract$convenience ${wl}-z ${wl}defaultextract' else whole_archive_flag_spec='-z allextract$convenience -z defaultextract' fi ;; esac link_all_deplibs=yes ;; sunos4*) if test "x$host_vendor" = xsequent; then # Use $CC to link under sequent, because it throws in some extra .o # files that make .init and .fini sections work. archive_cmds='$CC -G ${wl}-h $soname -o $lib $libobjs $deplibs $compiler_flags' else archive_cmds='$LD -assert pure-text -Bstatic -o $lib $libobjs $deplibs $linker_flags' fi hardcode_libdir_flag_spec='-L$libdir' hardcode_direct=yes hardcode_minus_L=yes hardcode_shlibpath_var=no ;; sysv4) case $host_vendor in sni) archive_cmds='$LD -G -h $soname -o $lib $libobjs $deplibs $linker_flags' hardcode_direct=yes # is this really true??? ;; siemens) ## LD is ld it makes a PLAMLIB ## CC just makes a GrossModule. archive_cmds='$LD -G -o $lib $libobjs $deplibs $linker_flags' reload_cmds='$CC -r -o $output$reload_objs' hardcode_direct=no ;; motorola) archive_cmds='$LD -G -h $soname -o $lib $libobjs $deplibs $linker_flags' hardcode_direct=no #Motorola manual says yes, but my tests say they lie ;; esac runpath_var='LD_RUN_PATH' hardcode_shlibpath_var=no ;; sysv4.3*) archive_cmds='$LD -G -h $soname -o $lib $libobjs $deplibs $linker_flags' hardcode_shlibpath_var=no export_dynamic_flag_spec='-Bexport' ;; sysv4*MP*) if test -d /usr/nec; then archive_cmds='$LD -G -h $soname -o $lib $libobjs $deplibs $linker_flags' hardcode_shlibpath_var=no runpath_var=LD_RUN_PATH hardcode_runpath_var=yes ld_shlibs=yes fi ;; sysv4*uw2* | sysv5OpenUNIX* | sysv5UnixWare7.[01].[10]* | unixware7* | sco3.2v5.0.[024]*) no_undefined_flag='${wl}-z,text' archive_cmds_need_lc=no hardcode_shlibpath_var=no runpath_var='LD_RUN_PATH' if test "$GCC" = yes; then archive_cmds='$CC -shared ${wl}-h,$soname -o $lib $libobjs $deplibs $compiler_flags' archive_expsym_cmds='$CC -shared ${wl}-Bexport:$export_symbols ${wl}-h,$soname -o $lib $libobjs $deplibs $compiler_flags' else archive_cmds='$CC -G ${wl}-h,$soname -o $lib $libobjs $deplibs $compiler_flags' archive_expsym_cmds='$CC -G ${wl}-Bexport:$export_symbols ${wl}-h,$soname -o $lib $libobjs $deplibs $compiler_flags' fi ;; sysv5* | sco3.2v5* | sco5v6*) # Note: We can NOT use -z defs as we might desire, because we do not # link with -lc, and that would cause any symbols used from libc to # always be unresolved, which means just about no library would # ever link correctly. If we're not using GNU ld we use -z text # though, which does catch some bad symbols but isn't as heavy-handed # as -z defs. no_undefined_flag='${wl}-z,text' allow_undefined_flag='${wl}-z,nodefs' archive_cmds_need_lc=no hardcode_shlibpath_var=no hardcode_libdir_flag_spec='${wl}-R,$libdir' hardcode_libdir_separator=':' link_all_deplibs=yes export_dynamic_flag_spec='${wl}-Bexport' runpath_var='LD_RUN_PATH' if test "$GCC" = yes; then archive_cmds='$CC -shared ${wl}-h,$soname -o $lib $libobjs $deplibs $compiler_flags' archive_expsym_cmds='$CC -shared ${wl}-Bexport:$export_symbols ${wl}-h,$soname -o $lib $libobjs $deplibs $compiler_flags' else archive_cmds='$CC -G ${wl}-h,$soname -o $lib $libobjs $deplibs $compiler_flags' archive_expsym_cmds='$CC -G ${wl}-Bexport:$export_symbols ${wl}-h,$soname -o $lib $libobjs $deplibs $compiler_flags' fi ;; uts4*) archive_cmds='$LD -G -h $soname -o $lib $libobjs $deplibs $linker_flags' hardcode_libdir_flag_spec='-L$libdir' hardcode_shlibpath_var=no ;; *) ld_shlibs=no ;; esac if test x$host_vendor = xsni; then case $host in sysv4 | sysv4.2uw2* | sysv4.3* | sysv5*) export_dynamic_flag_spec='${wl}-Blargedynsym' ;; esac fi fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ld_shlibs" >&5 $as_echo "$ld_shlibs" >&6; } test "$ld_shlibs" = no && can_build_shared=no with_gnu_ld=$with_gnu_ld # # Do we need to explicitly link libc? # case "x$archive_cmds_need_lc" in x|xyes) # Assume -lc should be added archive_cmds_need_lc=yes if test "$enable_shared" = yes && test "$GCC" = yes; then case $archive_cmds in *'~'*) # FIXME: we may have to deal with multi-command sequences. ;; '$CC '*) # Test whether the compiler implicitly links with -lc since on some # systems, -lgcc has to come before -lc. If gcc already passes -lc # to ld, don't add -lc before -lgcc. { $as_echo "$as_me:${as_lineno-$LINENO}: checking whether -lc should be explicitly linked in" >&5 $as_echo_n "checking whether -lc should be explicitly linked in... " >&6; } if ${lt_cv_archive_cmds_need_lc+:} false; then : $as_echo_n "(cached) " >&6 else $RM conftest* echo "$lt_simple_compile_test_code" > conftest.$ac_ext if { { eval echo "\"\$as_me\":${as_lineno-$LINENO}: \"$ac_compile\""; } >&5 (eval $ac_compile) 2>&5 ac_status=$? $as_echo "$as_me:${as_lineno-$LINENO}: \$? = $ac_status" >&5 test $ac_status = 0; } 2>conftest.err; then soname=conftest lib=conftest libobjs=conftest.$ac_objext deplibs= wl=$lt_prog_compiler_wl pic_flag=$lt_prog_compiler_pic compiler_flags=-v linker_flags=-v verstring= output_objdir=. libname=conftest lt_save_allow_undefined_flag=$allow_undefined_flag allow_undefined_flag= if { { eval echo "\"\$as_me\":${as_lineno-$LINENO}: \"$archive_cmds 2\>\&1 \| $GREP \" -lc \" \>/dev/null 2\>\&1\""; } >&5 (eval $archive_cmds 2\>\&1 \| $GREP \" -lc \" \>/dev/null 2\>\&1) 2>&5 ac_status=$? $as_echo "$as_me:${as_lineno-$LINENO}: \$? = $ac_status" >&5 test $ac_status = 0; } then lt_cv_archive_cmds_need_lc=no else lt_cv_archive_cmds_need_lc=yes fi allow_undefined_flag=$lt_save_allow_undefined_flag else cat conftest.err 1>&5 fi $RM conftest* fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $lt_cv_archive_cmds_need_lc" >&5 $as_echo "$lt_cv_archive_cmds_need_lc" >&6; } archive_cmds_need_lc=$lt_cv_archive_cmds_need_lc ;; esac fi ;; esac { $as_echo "$as_me:${as_lineno-$LINENO}: checking dynamic linker characteristics" >&5 $as_echo_n "checking dynamic linker characteristics... " >&6; } if test "$GCC" = yes; then case $host_os in darwin*) lt_awk_arg="/^libraries:/,/LR/" ;; *) lt_awk_arg="/^libraries:/" ;; esac case $host_os in mingw* | cegcc*) lt_sed_strip_eq="s,=\([A-Za-z]:\),\1,g" ;; *) lt_sed_strip_eq="s,=/,/,g" ;; esac lt_search_path_spec=`$CC -print-search-dirs | awk $lt_awk_arg | $SED -e "s/^libraries://" -e $lt_sed_strip_eq` case $lt_search_path_spec in *\;*) # if the path contains ";" then we assume it to be the separator # otherwise default to the standard path separator (i.e. ":") - it is # assumed that no part of a normal pathname contains ";" but that should # okay in the real world where ";" in dirpaths is itself problematic. lt_search_path_spec=`$ECHO "$lt_search_path_spec" | $SED 's/;/ /g'` ;; *) lt_search_path_spec=`$ECHO "$lt_search_path_spec" | $SED "s/$PATH_SEPARATOR/ /g"` ;; esac # Ok, now we have the path, separated by spaces, we can step through it # and add multilib dir if necessary. lt_tmp_lt_search_path_spec= lt_multi_os_dir=`$CC $CPPFLAGS $CFLAGS $LDFLAGS -print-multi-os-directory 2>/dev/null` for lt_sys_path in $lt_search_path_spec; do if test -d "$lt_sys_path/$lt_multi_os_dir"; then lt_tmp_lt_search_path_spec="$lt_tmp_lt_search_path_spec $lt_sys_path/$lt_multi_os_dir" else test -d "$lt_sys_path" && \ lt_tmp_lt_search_path_spec="$lt_tmp_lt_search_path_spec $lt_sys_path" fi done lt_search_path_spec=`$ECHO "$lt_tmp_lt_search_path_spec" | awk ' BEGIN {RS=" "; FS="/|\n";} { lt_foo=""; lt_count=0; for (lt_i = NF; lt_i > 0; lt_i--) { if ($lt_i != "" && $lt_i != ".") { if ($lt_i == "..") { lt_count++; } else { if (lt_count == 0) { lt_foo="/" $lt_i lt_foo; } else { lt_count--; } } } } if (lt_foo != "") { lt_freq[lt_foo]++; } if (lt_freq[lt_foo] == 1) { print lt_foo; } }'` # AWK program above erroneously prepends '/' to C:/dos/paths # for these hosts. case $host_os in mingw* | cegcc*) lt_search_path_spec=`$ECHO "$lt_search_path_spec" |\ $SED 's,/\([A-Za-z]:\),\1,g'` ;; esac sys_lib_search_path_spec=`$ECHO "$lt_search_path_spec" | $lt_NL2SP` else sys_lib_search_path_spec="/lib /usr/lib /usr/local/lib" fi library_names_spec= libname_spec='lib$name' soname_spec= shrext_cmds=".so" postinstall_cmds= postuninstall_cmds= finish_cmds= finish_eval= shlibpath_var= shlibpath_overrides_runpath=unknown version_type=none dynamic_linker="$host_os ld.so" sys_lib_dlsearch_path_spec="/lib /usr/lib" need_lib_prefix=unknown hardcode_into_libs=no # when you set need_version to no, make sure it does not cause -set_version # flags to be left without arguments need_version=unknown case $host_os in aix3*) version_type=linux # correct to gnu/linux during the next big refactor library_names_spec='${libname}${release}${shared_ext}$versuffix $libname.a' shlibpath_var=LIBPATH # AIX 3 has no versioning support, so we append a major version to the name. soname_spec='${libname}${release}${shared_ext}$major' ;; aix[4-9]*) version_type=linux # correct to gnu/linux during the next big refactor need_lib_prefix=no need_version=no hardcode_into_libs=yes if test "$host_cpu" = ia64; then # AIX 5 supports IA64 library_names_spec='${libname}${release}${shared_ext}$major ${libname}${release}${shared_ext}$versuffix $libname${shared_ext}' shlibpath_var=LD_LIBRARY_PATH else # With GCC up to 2.95.x, collect2 would create an import file # for dependence libraries. The import file would start with # the line `#! .'. This would cause the generated library to # depend on `.', always an invalid library. This was fixed in # development snapshots of GCC prior to 3.0. case $host_os in aix4 | aix4.[01] | aix4.[01].*) if { echo '#if __GNUC__ > 2 || (__GNUC__ == 2 && __GNUC_MINOR__ >= 97)' echo ' yes ' echo '#endif'; } | ${CC} -E - | $GREP yes > /dev/null; then : else can_build_shared=no fi ;; esac # AIX (on Power*) has no versioning support, so currently we can not hardcode correct # soname into executable. Probably we can add versioning support to # collect2, so additional links can be useful in future. if test "$aix_use_runtimelinking" = yes; then # If using run time linking (on AIX 4.2 or later) use lib.so # instead of lib.a to let people know that these are not # typical AIX shared libraries. library_names_spec='${libname}${release}${shared_ext}$versuffix ${libname}${release}${shared_ext}$major $libname${shared_ext}' else # We preserve .a as extension for shared libraries through AIX4.2 # and later when we are not doing run time linking. library_names_spec='${libname}${release}.a $libname.a' soname_spec='${libname}${release}${shared_ext}$major' fi shlibpath_var=LIBPATH fi ;; amigaos*) case $host_cpu in powerpc) # Since July 2007 AmigaOS4 officially supports .so libraries. # When compiling the executable, add -use-dynld -Lsobjs: to the compileline. library_names_spec='${libname}${release}${shared_ext}$versuffix ${libname}${release}${shared_ext}$major $libname${shared_ext}' ;; m68k) library_names_spec='$libname.ixlibrary $libname.a' # Create ${libname}_ixlibrary.a entries in /sys/libs. finish_eval='for lib in `ls $libdir/*.ixlibrary 2>/dev/null`; do libname=`func_echo_all "$lib" | $SED '\''s%^.*/\([^/]*\)\.ixlibrary$%\1%'\''`; test $RM /sys/libs/${libname}_ixlibrary.a; $show "cd /sys/libs && $LN_S $lib ${libname}_ixlibrary.a"; cd /sys/libs && $LN_S $lib ${libname}_ixlibrary.a || exit 1; done' ;; esac ;; beos*) library_names_spec='${libname}${shared_ext}' dynamic_linker="$host_os ld.so" shlibpath_var=LIBRARY_PATH ;; bsdi[45]*) version_type=linux # correct to gnu/linux during the next big refactor need_version=no library_names_spec='${libname}${release}${shared_ext}$versuffix ${libname}${release}${shared_ext}$major $libname${shared_ext}' soname_spec='${libname}${release}${shared_ext}$major' finish_cmds='PATH="\$PATH:/sbin" ldconfig $libdir' shlibpath_var=LD_LIBRARY_PATH sys_lib_search_path_spec="/shlib /usr/lib /usr/X11/lib /usr/contrib/lib /lib /usr/local/lib" sys_lib_dlsearch_path_spec="/shlib /usr/lib /usr/local/lib" # the default ld.so.conf also contains /usr/contrib/lib and # /usr/X11R6/lib (/usr/X11 is a link to /usr/X11R6), but let us allow # libtool to hard-code these into programs ;; cygwin* | mingw* | pw32* | cegcc*) version_type=windows shrext_cmds=".dll" need_version=no need_lib_prefix=no case $GCC,$cc_basename in yes,*) # gcc library_names_spec='$libname.dll.a' # DLL is installed to $(libdir)/../bin by postinstall_cmds postinstall_cmds='base_file=`basename \${file}`~ dlpath=`$SHELL 2>&1 -c '\''. $dir/'\''\${base_file}'\''i; echo \$dlname'\''`~ dldir=$destdir/`dirname \$dlpath`~ test -d \$dldir || mkdir -p \$dldir~ $install_prog $dir/$dlname \$dldir/$dlname~ chmod a+x \$dldir/$dlname~ if test -n '\''$stripme'\'' && test -n '\''$striplib'\''; then eval '\''$striplib \$dldir/$dlname'\'' || exit \$?; fi' postuninstall_cmds='dldll=`$SHELL 2>&1 -c '\''. $file; echo \$dlname'\''`~ dlpath=$dir/\$dldll~ $RM \$dlpath' shlibpath_overrides_runpath=yes case $host_os in cygwin*) # Cygwin DLLs use 'cyg' prefix rather than 'lib' soname_spec='`echo ${libname} | sed -e 's/^lib/cyg/'``echo ${release} | $SED -e 's/[.]/-/g'`${versuffix}${shared_ext}' sys_lib_search_path_spec="$sys_lib_search_path_spec /usr/lib/w32api" ;; mingw* | cegcc*) # MinGW DLLs use traditional 'lib' prefix soname_spec='${libname}`echo ${release} | $SED -e 's/[.]/-/g'`${versuffix}${shared_ext}' ;; pw32*) # pw32 DLLs use 'pw' prefix rather than 'lib' library_names_spec='`echo ${libname} | sed -e 's/^lib/pw/'``echo ${release} | $SED -e 's/[.]/-/g'`${versuffix}${shared_ext}' ;; esac dynamic_linker='Win32 ld.exe' ;; *,cl*) # Native MSVC libname_spec='$name' soname_spec='${libname}`echo ${release} | $SED -e 's/[.]/-/g'`${versuffix}${shared_ext}' library_names_spec='${libname}.dll.lib' case $build_os in mingw*) sys_lib_search_path_spec= lt_save_ifs=$IFS IFS=';' for lt_path in $LIB do IFS=$lt_save_ifs # Let DOS variable expansion print the short 8.3 style file name. lt_path=`cd "$lt_path" 2>/dev/null && cmd //C "for %i in (".") do @echo %~si"` sys_lib_search_path_spec="$sys_lib_search_path_spec $lt_path" done IFS=$lt_save_ifs # Convert to MSYS style. sys_lib_search_path_spec=`$ECHO "$sys_lib_search_path_spec" | sed -e 's|\\\\|/|g' -e 's| \\([a-zA-Z]\\):| /\\1|g' -e 's|^ ||'` ;; cygwin*) # Convert to unix form, then to dos form, then back to unix form # but this time dos style (no spaces!) so that the unix form looks # like /cygdrive/c/PROGRA~1:/cygdr... sys_lib_search_path_spec=`cygpath --path --unix "$LIB"` sys_lib_search_path_spec=`cygpath --path --dos "$sys_lib_search_path_spec" 2>/dev/null` sys_lib_search_path_spec=`cygpath --path --unix "$sys_lib_search_path_spec" | $SED -e "s/$PATH_SEPARATOR/ /g"` ;; *) sys_lib_search_path_spec="$LIB" if $ECHO "$sys_lib_search_path_spec" | $GREP ';[c-zC-Z]:/' >/dev/null; then # It is most probably a Windows format PATH. sys_lib_search_path_spec=`$ECHO "$sys_lib_search_path_spec" | $SED -e 's/;/ /g'` else sys_lib_search_path_spec=`$ECHO "$sys_lib_search_path_spec" | $SED -e "s/$PATH_SEPARATOR/ /g"` fi # FIXME: find the short name or the path components, as spaces are # common. (e.g. "Program Files" -> "PROGRA~1") ;; esac # DLL is installed to $(libdir)/../bin by postinstall_cmds postinstall_cmds='base_file=`basename \${file}`~ dlpath=`$SHELL 2>&1 -c '\''. $dir/'\''\${base_file}'\''i; echo \$dlname'\''`~ dldir=$destdir/`dirname \$dlpath`~ test -d \$dldir || mkdir -p \$dldir~ $install_prog $dir/$dlname \$dldir/$dlname' postuninstall_cmds='dldll=`$SHELL 2>&1 -c '\''. $file; echo \$dlname'\''`~ dlpath=$dir/\$dldll~ $RM \$dlpath' shlibpath_overrides_runpath=yes dynamic_linker='Win32 link.exe' ;; *) # Assume MSVC wrapper library_names_spec='${libname}`echo ${release} | $SED -e 's/[.]/-/g'`${versuffix}${shared_ext} $libname.lib' dynamic_linker='Win32 ld.exe' ;; esac # FIXME: first we should search . and the directory the executable is in shlibpath_var=PATH ;; darwin* | rhapsody*) dynamic_linker="$host_os dyld" version_type=darwin need_lib_prefix=no need_version=no library_names_spec='${libname}${release}${major}$shared_ext ${libname}$shared_ext' soname_spec='${libname}${release}${major}$shared_ext' shlibpath_overrides_runpath=yes shlibpath_var=DYLD_LIBRARY_PATH shrext_cmds='`test .$module = .yes && echo .so || echo .dylib`' sys_lib_search_path_spec="$sys_lib_search_path_spec /usr/local/lib" sys_lib_dlsearch_path_spec='/usr/local/lib /lib /usr/lib' ;; dgux*) version_type=linux # correct to gnu/linux during the next big refactor need_lib_prefix=no need_version=no library_names_spec='${libname}${release}${shared_ext}$versuffix ${libname}${release}${shared_ext}$major $libname$shared_ext' soname_spec='${libname}${release}${shared_ext}$major' shlibpath_var=LD_LIBRARY_PATH ;; freebsd* | dragonfly*) # DragonFly does not have aout. When/if they implement a new # versioning mechanism, adjust this. if test -x /usr/bin/objformat; then objformat=`/usr/bin/objformat` else case $host_os in freebsd[23].*) objformat=aout ;; *) objformat=elf ;; esac fi version_type=freebsd-$objformat case $version_type in freebsd-elf*) library_names_spec='${libname}${release}${shared_ext}$versuffix ${libname}${release}${shared_ext} $libname${shared_ext}' need_version=no need_lib_prefix=no ;; freebsd-*) library_names_spec='${libname}${release}${shared_ext}$versuffix $libname${shared_ext}$versuffix' need_version=yes ;; esac shlibpath_var=LD_LIBRARY_PATH case $host_os in freebsd2.*) shlibpath_overrides_runpath=yes ;; freebsd3.[01]* | freebsdelf3.[01]*) shlibpath_overrides_runpath=yes hardcode_into_libs=yes ;; freebsd3.[2-9]* | freebsdelf3.[2-9]* | \ freebsd4.[0-5] | freebsdelf4.[0-5] | freebsd4.1.1 | freebsdelf4.1.1) shlibpath_overrides_runpath=no hardcode_into_libs=yes ;; *) # from 4.6 on, and DragonFly shlibpath_overrides_runpath=yes hardcode_into_libs=yes ;; esac ;; haiku*) version_type=linux # correct to gnu/linux during the next big refactor need_lib_prefix=no need_version=no dynamic_linker="$host_os runtime_loader" library_names_spec='${libname}${release}${shared_ext}$versuffix ${libname}${release}${shared_ext}${major} ${libname}${shared_ext}' soname_spec='${libname}${release}${shared_ext}$major' shlibpath_var=LIBRARY_PATH shlibpath_overrides_runpath=yes sys_lib_dlsearch_path_spec='/boot/home/config/lib /boot/common/lib /boot/system/lib' hardcode_into_libs=yes ;; hpux9* | hpux10* | hpux11*) # Give a soname corresponding to the major version so that dld.sl refuses to # link against other versions. version_type=sunos need_lib_prefix=no need_version=no case $host_cpu in ia64*) shrext_cmds='.so' hardcode_into_libs=yes dynamic_linker="$host_os dld.so" shlibpath_var=LD_LIBRARY_PATH shlibpath_overrides_runpath=yes # Unless +noenvvar is specified. library_names_spec='${libname}${release}${shared_ext}$versuffix ${libname}${release}${shared_ext}$major $libname${shared_ext}' soname_spec='${libname}${release}${shared_ext}$major' if test "X$HPUX_IA64_MODE" = X32; then sys_lib_search_path_spec="/usr/lib/hpux32 /usr/local/lib/hpux32 /usr/local/lib" else sys_lib_search_path_spec="/usr/lib/hpux64 /usr/local/lib/hpux64" fi sys_lib_dlsearch_path_spec=$sys_lib_search_path_spec ;; hppa*64*) shrext_cmds='.sl' hardcode_into_libs=yes dynamic_linker="$host_os dld.sl" shlibpath_var=LD_LIBRARY_PATH # How should we handle SHLIB_PATH shlibpath_overrides_runpath=yes # Unless +noenvvar is specified. library_names_spec='${libname}${release}${shared_ext}$versuffix ${libname}${release}${shared_ext}$major $libname${shared_ext}' soname_spec='${libname}${release}${shared_ext}$major' sys_lib_search_path_spec="/usr/lib/pa20_64 /usr/ccs/lib/pa20_64" sys_lib_dlsearch_path_spec=$sys_lib_search_path_spec ;; *) shrext_cmds='.sl' dynamic_linker="$host_os dld.sl" shlibpath_var=SHLIB_PATH shlibpath_overrides_runpath=no # +s is required to enable SHLIB_PATH library_names_spec='${libname}${release}${shared_ext}$versuffix ${libname}${release}${shared_ext}$major $libname${shared_ext}' soname_spec='${libname}${release}${shared_ext}$major' ;; esac # HP-UX runs *really* slowly unless shared libraries are mode 555, ... postinstall_cmds='chmod 555 $lib' # or fails outright, so override atomically: install_override_mode=555 ;; interix[3-9]*) version_type=linux # correct to gnu/linux during the next big refactor need_lib_prefix=no need_version=no library_names_spec='${libname}${release}${shared_ext}$versuffix ${libname}${release}${shared_ext}$major ${libname}${shared_ext}' soname_spec='${libname}${release}${shared_ext}$major' dynamic_linker='Interix 3.x ld.so.1 (PE, like ELF)' shlibpath_var=LD_LIBRARY_PATH shlibpath_overrides_runpath=no hardcode_into_libs=yes ;; irix5* | irix6* | nonstopux*) case $host_os in nonstopux*) version_type=nonstopux ;; *) if test "$lt_cv_prog_gnu_ld" = yes; then version_type=linux # correct to gnu/linux during the next big refactor else version_type=irix fi ;; esac need_lib_prefix=no need_version=no soname_spec='${libname}${release}${shared_ext}$major' library_names_spec='${libname}${release}${shared_ext}$versuffix ${libname}${release}${shared_ext}$major ${libname}${release}${shared_ext} $libname${shared_ext}' case $host_os in irix5* | nonstopux*) libsuff= shlibsuff= ;; *) case $LD in # libtool.m4 will add one of these switches to LD *-32|*"-32 "|*-melf32bsmip|*"-melf32bsmip ") libsuff= shlibsuff= libmagic=32-bit;; *-n32|*"-n32 "|*-melf32bmipn32|*"-melf32bmipn32 ") libsuff=32 shlibsuff=N32 libmagic=N32;; *-64|*"-64 "|*-melf64bmip|*"-melf64bmip ") libsuff=64 shlibsuff=64 libmagic=64-bit;; *) libsuff= shlibsuff= libmagic=never-match;; esac ;; esac shlibpath_var=LD_LIBRARY${shlibsuff}_PATH shlibpath_overrides_runpath=no sys_lib_search_path_spec="/usr/lib${libsuff} /lib${libsuff} /usr/local/lib${libsuff}" sys_lib_dlsearch_path_spec="/usr/lib${libsuff} /lib${libsuff}" hardcode_into_libs=yes ;; # No shared lib support for Linux oldld, aout, or coff. linux*oldld* | linux*aout* | linux*coff*) dynamic_linker=no ;; # This must be glibc/ELF. linux* | k*bsd*-gnu | kopensolaris*-gnu | gnu*) version_type=linux # correct to gnu/linux during the next big refactor need_lib_prefix=no need_version=no library_names_spec='${libname}${release}${shared_ext}$versuffix ${libname}${release}${shared_ext}$major $libname${shared_ext}' soname_spec='${libname}${release}${shared_ext}$major' finish_cmds='PATH="\$PATH:/sbin" ldconfig -n $libdir' shlibpath_var=LD_LIBRARY_PATH shlibpath_overrides_runpath=no # Some binutils ld are patched to set DT_RUNPATH if ${lt_cv_shlibpath_overrides_runpath+:} false; then : $as_echo_n "(cached) " >&6 else lt_cv_shlibpath_overrides_runpath=no save_LDFLAGS=$LDFLAGS save_libdir=$libdir eval "libdir=/foo; wl=\"$lt_prog_compiler_wl\"; \ LDFLAGS=\"\$LDFLAGS $hardcode_libdir_flag_spec\"" cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ int main () { ; return 0; } _ACEOF if ac_fn_c_try_link "$LINENO"; then : if ($OBJDUMP -p conftest$ac_exeext) 2>/dev/null | grep "RUNPATH.*$libdir" >/dev/null; then : lt_cv_shlibpath_overrides_runpath=yes fi fi rm -f core conftest.err conftest.$ac_objext \ conftest$ac_exeext conftest.$ac_ext LDFLAGS=$save_LDFLAGS libdir=$save_libdir fi shlibpath_overrides_runpath=$lt_cv_shlibpath_overrides_runpath # This implies no fast_install, which is unacceptable. # Some rework will be needed to allow for fast_install # before this can be enabled. hardcode_into_libs=yes # Append ld.so.conf contents to the search path if test -f /etc/ld.so.conf; then lt_ld_extra=`awk '/^include / { system(sprintf("cd /etc; cat %s 2>/dev/null", \$2)); skip = 1; } { if (!skip) print \$0; skip = 0; }' < /etc/ld.so.conf | $SED -e 's/#.*//;/^[ ]*hwcap[ ]/d;s/[:, ]/ /g;s/=[^=]*$//;s/=[^= ]* / /g;s/"//g;/^$/d' | tr '\n' ' '` sys_lib_dlsearch_path_spec="/lib /usr/lib $lt_ld_extra" fi # We used to test for /lib/ld.so.1 and disable shared libraries on # powerpc, because MkLinux only supported shared libraries with the # GNU dynamic linker. Since this was broken with cross compilers, # most powerpc-linux boxes support dynamic linking these days and # people can always --disable-shared, the test was removed, and we # assume the GNU/Linux dynamic linker is in use. dynamic_linker='GNU/Linux ld.so' ;; netbsdelf*-gnu) version_type=linux need_lib_prefix=no need_version=no library_names_spec='${libname}${release}${shared_ext}$versuffix ${libname}${release}${shared_ext}$major ${libname}${shared_ext}' soname_spec='${libname}${release}${shared_ext}$major' shlibpath_var=LD_LIBRARY_PATH shlibpath_overrides_runpath=no hardcode_into_libs=yes dynamic_linker='NetBSD ld.elf_so' ;; netbsd*) version_type=sunos need_lib_prefix=no need_version=no if echo __ELF__ | $CC -E - | $GREP __ELF__ >/dev/null; then library_names_spec='${libname}${release}${shared_ext}$versuffix ${libname}${shared_ext}$versuffix' finish_cmds='PATH="\$PATH:/sbin" ldconfig -m $libdir' dynamic_linker='NetBSD (a.out) ld.so' else library_names_spec='${libname}${release}${shared_ext}$versuffix ${libname}${release}${shared_ext}$major ${libname}${shared_ext}' soname_spec='${libname}${release}${shared_ext}$major' dynamic_linker='NetBSD ld.elf_so' fi shlibpath_var=LD_LIBRARY_PATH shlibpath_overrides_runpath=yes hardcode_into_libs=yes ;; newsos6) version_type=linux # correct to gnu/linux during the next big refactor library_names_spec='${libname}${release}${shared_ext}$versuffix ${libname}${release}${shared_ext}$major $libname${shared_ext}' shlibpath_var=LD_LIBRARY_PATH shlibpath_overrides_runpath=yes ;; *nto* | *qnx*) version_type=qnx need_lib_prefix=no need_version=no library_names_spec='${libname}${release}${shared_ext}$versuffix ${libname}${release}${shared_ext}$major $libname${shared_ext}' soname_spec='${libname}${release}${shared_ext}$major' shlibpath_var=LD_LIBRARY_PATH shlibpath_overrides_runpath=no hardcode_into_libs=yes dynamic_linker='ldqnx.so' ;; openbsd*) version_type=sunos sys_lib_dlsearch_path_spec="/usr/lib" need_lib_prefix=no # Some older versions of OpenBSD (3.3 at least) *do* need versioned libs. case $host_os in openbsd3.3 | openbsd3.3.*) need_version=yes ;; *) need_version=no ;; esac library_names_spec='${libname}${release}${shared_ext}$versuffix ${libname}${shared_ext}$versuffix' finish_cmds='PATH="\$PATH:/sbin" ldconfig -m $libdir' shlibpath_var=LD_LIBRARY_PATH if test -z "`echo __ELF__ | $CC -E - | $GREP __ELF__`" || test "$host_os-$host_cpu" = "openbsd2.8-powerpc"; then case $host_os in openbsd2.[89] | openbsd2.[89].*) shlibpath_overrides_runpath=no ;; *) shlibpath_overrides_runpath=yes ;; esac else shlibpath_overrides_runpath=yes fi ;; os2*) libname_spec='$name' shrext_cmds=".dll" need_lib_prefix=no library_names_spec='$libname${shared_ext} $libname.a' dynamic_linker='OS/2 ld.exe' shlibpath_var=LIBPATH ;; osf3* | osf4* | osf5*) version_type=osf need_lib_prefix=no need_version=no soname_spec='${libname}${release}${shared_ext}$major' library_names_spec='${libname}${release}${shared_ext}$versuffix ${libname}${release}${shared_ext}$major $libname${shared_ext}' shlibpath_var=LD_LIBRARY_PATH sys_lib_search_path_spec="/usr/shlib /usr/ccs/lib /usr/lib/cmplrs/cc /usr/lib /usr/local/lib /var/shlib" sys_lib_dlsearch_path_spec="$sys_lib_search_path_spec" ;; rdos*) dynamic_linker=no ;; solaris*) version_type=linux # correct to gnu/linux during the next big refactor need_lib_prefix=no need_version=no library_names_spec='${libname}${release}${shared_ext}$versuffix ${libname}${release}${shared_ext}$major $libname${shared_ext}' soname_spec='${libname}${release}${shared_ext}$major' shlibpath_var=LD_LIBRARY_PATH shlibpath_overrides_runpath=yes hardcode_into_libs=yes # ldd complains unless libraries are executable postinstall_cmds='chmod +x $lib' ;; sunos4*) version_type=sunos library_names_spec='${libname}${release}${shared_ext}$versuffix ${libname}${shared_ext}$versuffix' finish_cmds='PATH="\$PATH:/usr/etc" ldconfig $libdir' shlibpath_var=LD_LIBRARY_PATH shlibpath_overrides_runpath=yes if test "$with_gnu_ld" = yes; then need_lib_prefix=no fi need_version=yes ;; sysv4 | sysv4.3*) version_type=linux # correct to gnu/linux during the next big refactor library_names_spec='${libname}${release}${shared_ext}$versuffix ${libname}${release}${shared_ext}$major $libname${shared_ext}' soname_spec='${libname}${release}${shared_ext}$major' shlibpath_var=LD_LIBRARY_PATH case $host_vendor in sni) shlibpath_overrides_runpath=no need_lib_prefix=no runpath_var=LD_RUN_PATH ;; siemens) need_lib_prefix=no ;; motorola) need_lib_prefix=no need_version=no shlibpath_overrides_runpath=no sys_lib_search_path_spec='/lib /usr/lib /usr/ccs/lib' ;; esac ;; sysv4*MP*) if test -d /usr/nec ;then version_type=linux # correct to gnu/linux during the next big refactor library_names_spec='$libname${shared_ext}.$versuffix $libname${shared_ext}.$major $libname${shared_ext}' soname_spec='$libname${shared_ext}.$major' shlibpath_var=LD_LIBRARY_PATH fi ;; sysv5* | sco3.2v5* | sco5v6* | unixware* | OpenUNIX* | sysv4*uw2*) version_type=freebsd-elf need_lib_prefix=no need_version=no library_names_spec='${libname}${release}${shared_ext}$versuffix ${libname}${release}${shared_ext} $libname${shared_ext}' soname_spec='${libname}${release}${shared_ext}$major' shlibpath_var=LD_LIBRARY_PATH shlibpath_overrides_runpath=yes hardcode_into_libs=yes if test "$with_gnu_ld" = yes; then sys_lib_search_path_spec='/usr/local/lib /usr/gnu/lib /usr/ccs/lib /usr/lib /lib' else sys_lib_search_path_spec='/usr/ccs/lib /usr/lib' case $host_os in sco3.2v5*) sys_lib_search_path_spec="$sys_lib_search_path_spec /lib" ;; esac fi sys_lib_dlsearch_path_spec='/usr/lib' ;; tpf*) # TPF is a cross-target only. Preferred cross-host = GNU/Linux. version_type=linux # correct to gnu/linux during the next big refactor need_lib_prefix=no need_version=no library_names_spec='${libname}${release}${shared_ext}$versuffix ${libname}${release}${shared_ext}$major $libname${shared_ext}' shlibpath_var=LD_LIBRARY_PATH shlibpath_overrides_runpath=no hardcode_into_libs=yes ;; uts4*) version_type=linux # correct to gnu/linux during the next big refactor library_names_spec='${libname}${release}${shared_ext}$versuffix ${libname}${release}${shared_ext}$major $libname${shared_ext}' soname_spec='${libname}${release}${shared_ext}$major' shlibpath_var=LD_LIBRARY_PATH ;; *) dynamic_linker=no ;; esac { $as_echo "$as_me:${as_lineno-$LINENO}: result: $dynamic_linker" >&5 $as_echo "$dynamic_linker" >&6; } test "$dynamic_linker" = no && can_build_shared=no variables_saved_for_relink="PATH $shlibpath_var $runpath_var" if test "$GCC" = yes; then variables_saved_for_relink="$variables_saved_for_relink GCC_EXEC_PREFIX COMPILER_PATH LIBRARY_PATH" fi if test "${lt_cv_sys_lib_search_path_spec+set}" = set; then sys_lib_search_path_spec="$lt_cv_sys_lib_search_path_spec" fi if test "${lt_cv_sys_lib_dlsearch_path_spec+set}" = set; then sys_lib_dlsearch_path_spec="$lt_cv_sys_lib_dlsearch_path_spec" fi { $as_echo "$as_me:${as_lineno-$LINENO}: checking how to hardcode library paths into programs" >&5 $as_echo_n "checking how to hardcode library paths into programs... " >&6; } hardcode_action= if test -n "$hardcode_libdir_flag_spec" || test -n "$runpath_var" || test "X$hardcode_automatic" = "Xyes" ; then # We can hardcode non-existent directories. if test "$hardcode_direct" != no && # If the only mechanism to avoid hardcoding is shlibpath_var, we # have to relink, otherwise we might link with an installed library # when we should be linking with a yet-to-be-installed one ## test "$_LT_TAGVAR(hardcode_shlibpath_var, )" != no && test "$hardcode_minus_L" != no; then # Linking always hardcodes the temporary library directory. hardcode_action=relink else # We can link without hardcoding, and we can hardcode nonexisting dirs. hardcode_action=immediate fi else # We cannot hardcode anything, or else we can only hardcode existing # directories. hardcode_action=unsupported fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $hardcode_action" >&5 $as_echo "$hardcode_action" >&6; } if test "$hardcode_action" = relink || test "$inherit_rpath" = yes; then # Fast installation is not supported enable_fast_install=no elif test "$shlibpath_overrides_runpath" = yes || test "$enable_shared" = no; then # Fast installation is not necessary enable_fast_install=needless fi if test "x$enable_dlopen" != xyes; then enable_dlopen=unknown enable_dlopen_self=unknown enable_dlopen_self_static=unknown else lt_cv_dlopen=no lt_cv_dlopen_libs= case $host_os in beos*) lt_cv_dlopen="load_add_on" lt_cv_dlopen_libs= lt_cv_dlopen_self=yes ;; mingw* | pw32* | cegcc*) lt_cv_dlopen="LoadLibrary" lt_cv_dlopen_libs= ;; cygwin*) lt_cv_dlopen="dlopen" lt_cv_dlopen_libs= ;; darwin*) # if libdl is installed we need to link against it { $as_echo "$as_me:${as_lineno-$LINENO}: checking for dlopen in -ldl" >&5 $as_echo_n "checking for dlopen in -ldl... " >&6; } if ${ac_cv_lib_dl_dlopen+:} false; then : $as_echo_n "(cached) " >&6 else ac_check_lib_save_LIBS=$LIBS LIBS="-ldl $LIBS" cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ /* Override any GCC internal prototype to avoid an error. Use char because int might match the return type of a GCC builtin and then its argument prototype would still apply. */ #ifdef __cplusplus extern "C" #endif char dlopen (); int main () { return dlopen (); ; return 0; } _ACEOF if ac_fn_c_try_link "$LINENO"; then : ac_cv_lib_dl_dlopen=yes else ac_cv_lib_dl_dlopen=no fi rm -f core conftest.err conftest.$ac_objext \ conftest$ac_exeext conftest.$ac_ext LIBS=$ac_check_lib_save_LIBS fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_cv_lib_dl_dlopen" >&5 $as_echo "$ac_cv_lib_dl_dlopen" >&6; } if test "x$ac_cv_lib_dl_dlopen" = xyes; then : lt_cv_dlopen="dlopen" lt_cv_dlopen_libs="-ldl" else lt_cv_dlopen="dyld" lt_cv_dlopen_libs= lt_cv_dlopen_self=yes fi ;; *) ac_fn_c_check_func "$LINENO" "shl_load" "ac_cv_func_shl_load" if test "x$ac_cv_func_shl_load" = xyes; then : lt_cv_dlopen="shl_load" else { $as_echo "$as_me:${as_lineno-$LINENO}: checking for shl_load in -ldld" >&5 $as_echo_n "checking for shl_load in -ldld... " >&6; } if ${ac_cv_lib_dld_shl_load+:} false; then : $as_echo_n "(cached) " >&6 else ac_check_lib_save_LIBS=$LIBS LIBS="-ldld $LIBS" cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ /* Override any GCC internal prototype to avoid an error. Use char because int might match the return type of a GCC builtin and then its argument prototype would still apply. */ #ifdef __cplusplus extern "C" #endif char shl_load (); int main () { return shl_load (); ; return 0; } _ACEOF if ac_fn_c_try_link "$LINENO"; then : ac_cv_lib_dld_shl_load=yes else ac_cv_lib_dld_shl_load=no fi rm -f core conftest.err conftest.$ac_objext \ conftest$ac_exeext conftest.$ac_ext LIBS=$ac_check_lib_save_LIBS fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_cv_lib_dld_shl_load" >&5 $as_echo "$ac_cv_lib_dld_shl_load" >&6; } if test "x$ac_cv_lib_dld_shl_load" = xyes; then : lt_cv_dlopen="shl_load" lt_cv_dlopen_libs="-ldld" else ac_fn_c_check_func "$LINENO" "dlopen" "ac_cv_func_dlopen" if test "x$ac_cv_func_dlopen" = xyes; then : lt_cv_dlopen="dlopen" else { $as_echo "$as_me:${as_lineno-$LINENO}: checking for dlopen in -ldl" >&5 $as_echo_n "checking for dlopen in -ldl... " >&6; } if ${ac_cv_lib_dl_dlopen+:} false; then : $as_echo_n "(cached) " >&6 else ac_check_lib_save_LIBS=$LIBS LIBS="-ldl $LIBS" cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ /* Override any GCC internal prototype to avoid an error. Use char because int might match the return type of a GCC builtin and then its argument prototype would still apply. */ #ifdef __cplusplus extern "C" #endif char dlopen (); int main () { return dlopen (); ; return 0; } _ACEOF if ac_fn_c_try_link "$LINENO"; then : ac_cv_lib_dl_dlopen=yes else ac_cv_lib_dl_dlopen=no fi rm -f core conftest.err conftest.$ac_objext \ conftest$ac_exeext conftest.$ac_ext LIBS=$ac_check_lib_save_LIBS fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_cv_lib_dl_dlopen" >&5 $as_echo "$ac_cv_lib_dl_dlopen" >&6; } if test "x$ac_cv_lib_dl_dlopen" = xyes; then : lt_cv_dlopen="dlopen" lt_cv_dlopen_libs="-ldl" else { $as_echo "$as_me:${as_lineno-$LINENO}: checking for dlopen in -lsvld" >&5 $as_echo_n "checking for dlopen in -lsvld... " >&6; } if ${ac_cv_lib_svld_dlopen+:} false; then : $as_echo_n "(cached) " >&6 else ac_check_lib_save_LIBS=$LIBS LIBS="-lsvld $LIBS" cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ /* Override any GCC internal prototype to avoid an error. Use char because int might match the return type of a GCC builtin and then its argument prototype would still apply. */ #ifdef __cplusplus extern "C" #endif char dlopen (); int main () { return dlopen (); ; return 0; } _ACEOF if ac_fn_c_try_link "$LINENO"; then : ac_cv_lib_svld_dlopen=yes else ac_cv_lib_svld_dlopen=no fi rm -f core conftest.err conftest.$ac_objext \ conftest$ac_exeext conftest.$ac_ext LIBS=$ac_check_lib_save_LIBS fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_cv_lib_svld_dlopen" >&5 $as_echo "$ac_cv_lib_svld_dlopen" >&6; } if test "x$ac_cv_lib_svld_dlopen" = xyes; then : lt_cv_dlopen="dlopen" lt_cv_dlopen_libs="-lsvld" else { $as_echo "$as_me:${as_lineno-$LINENO}: checking for dld_link in -ldld" >&5 $as_echo_n "checking for dld_link in -ldld... " >&6; } if ${ac_cv_lib_dld_dld_link+:} false; then : $as_echo_n "(cached) " >&6 else ac_check_lib_save_LIBS=$LIBS LIBS="-ldld $LIBS" cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ /* Override any GCC internal prototype to avoid an error. Use char because int might match the return type of a GCC builtin and then its argument prototype would still apply. */ #ifdef __cplusplus extern "C" #endif char dld_link (); int main () { return dld_link (); ; return 0; } _ACEOF if ac_fn_c_try_link "$LINENO"; then : ac_cv_lib_dld_dld_link=yes else ac_cv_lib_dld_dld_link=no fi rm -f core conftest.err conftest.$ac_objext \ conftest$ac_exeext conftest.$ac_ext LIBS=$ac_check_lib_save_LIBS fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_cv_lib_dld_dld_link" >&5 $as_echo "$ac_cv_lib_dld_dld_link" >&6; } if test "x$ac_cv_lib_dld_dld_link" = xyes; then : lt_cv_dlopen="dld_link" lt_cv_dlopen_libs="-ldld" fi fi fi fi fi fi ;; esac if test "x$lt_cv_dlopen" != xno; then enable_dlopen=yes else enable_dlopen=no fi case $lt_cv_dlopen in dlopen) save_CPPFLAGS="$CPPFLAGS" test "x$ac_cv_header_dlfcn_h" = xyes && CPPFLAGS="$CPPFLAGS -DHAVE_DLFCN_H" save_LDFLAGS="$LDFLAGS" wl=$lt_prog_compiler_wl eval LDFLAGS=\"\$LDFLAGS $export_dynamic_flag_spec\" save_LIBS="$LIBS" LIBS="$lt_cv_dlopen_libs $LIBS" { $as_echo "$as_me:${as_lineno-$LINENO}: checking whether a program can dlopen itself" >&5 $as_echo_n "checking whether a program can dlopen itself... " >&6; } if ${lt_cv_dlopen_self+:} false; then : $as_echo_n "(cached) " >&6 else if test "$cross_compiling" = yes; then : lt_cv_dlopen_self=cross else lt_dlunknown=0; lt_dlno_uscore=1; lt_dlneed_uscore=2 lt_status=$lt_dlunknown cat > conftest.$ac_ext <<_LT_EOF #line $LINENO "configure" #include "confdefs.h" #if HAVE_DLFCN_H #include #endif #include #ifdef RTLD_GLOBAL # define LT_DLGLOBAL RTLD_GLOBAL #else # ifdef DL_GLOBAL # define LT_DLGLOBAL DL_GLOBAL # else # define LT_DLGLOBAL 0 # endif #endif /* We may have to define LT_DLLAZY_OR_NOW in the command line if we find out it does not work in some platform. */ #ifndef LT_DLLAZY_OR_NOW # ifdef RTLD_LAZY # define LT_DLLAZY_OR_NOW RTLD_LAZY # else # ifdef DL_LAZY # define LT_DLLAZY_OR_NOW DL_LAZY # else # ifdef RTLD_NOW # define LT_DLLAZY_OR_NOW RTLD_NOW # else # ifdef DL_NOW # define LT_DLLAZY_OR_NOW DL_NOW # else # define LT_DLLAZY_OR_NOW 0 # endif # endif # endif # endif #endif /* When -fvisbility=hidden is used, assume the code has been annotated correspondingly for the symbols needed. */ #if defined(__GNUC__) && (((__GNUC__ == 3) && (__GNUC_MINOR__ >= 3)) || (__GNUC__ > 3)) int fnord () __attribute__((visibility("default"))); #endif int fnord () { return 42; } int main () { void *self = dlopen (0, LT_DLGLOBAL|LT_DLLAZY_OR_NOW); int status = $lt_dlunknown; if (self) { if (dlsym (self,"fnord")) status = $lt_dlno_uscore; else { if (dlsym( self,"_fnord")) status = $lt_dlneed_uscore; else puts (dlerror ()); } /* dlclose (self); */ } else puts (dlerror ()); return status; } _LT_EOF if { { eval echo "\"\$as_me\":${as_lineno-$LINENO}: \"$ac_link\""; } >&5 (eval $ac_link) 2>&5 ac_status=$? $as_echo "$as_me:${as_lineno-$LINENO}: \$? = $ac_status" >&5 test $ac_status = 0; } && test -s conftest${ac_exeext} 2>/dev/null; then (./conftest; exit; ) >&5 2>/dev/null lt_status=$? case x$lt_status in x$lt_dlno_uscore) lt_cv_dlopen_self=yes ;; x$lt_dlneed_uscore) lt_cv_dlopen_self=yes ;; x$lt_dlunknown|x*) lt_cv_dlopen_self=no ;; esac else : # compilation failed lt_cv_dlopen_self=no fi fi rm -fr conftest* fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $lt_cv_dlopen_self" >&5 $as_echo "$lt_cv_dlopen_self" >&6; } if test "x$lt_cv_dlopen_self" = xyes; then wl=$lt_prog_compiler_wl eval LDFLAGS=\"\$LDFLAGS $lt_prog_compiler_static\" { $as_echo "$as_me:${as_lineno-$LINENO}: checking whether a statically linked program can dlopen itself" >&5 $as_echo_n "checking whether a statically linked program can dlopen itself... " >&6; } if ${lt_cv_dlopen_self_static+:} false; then : $as_echo_n "(cached) " >&6 else if test "$cross_compiling" = yes; then : lt_cv_dlopen_self_static=cross else lt_dlunknown=0; lt_dlno_uscore=1; lt_dlneed_uscore=2 lt_status=$lt_dlunknown cat > conftest.$ac_ext <<_LT_EOF #line $LINENO "configure" #include "confdefs.h" #if HAVE_DLFCN_H #include #endif #include #ifdef RTLD_GLOBAL # define LT_DLGLOBAL RTLD_GLOBAL #else # ifdef DL_GLOBAL # define LT_DLGLOBAL DL_GLOBAL # else # define LT_DLGLOBAL 0 # endif #endif /* We may have to define LT_DLLAZY_OR_NOW in the command line if we find out it does not work in some platform. */ #ifndef LT_DLLAZY_OR_NOW # ifdef RTLD_LAZY # define LT_DLLAZY_OR_NOW RTLD_LAZY # else # ifdef DL_LAZY # define LT_DLLAZY_OR_NOW DL_LAZY # else # ifdef RTLD_NOW # define LT_DLLAZY_OR_NOW RTLD_NOW # else # ifdef DL_NOW # define LT_DLLAZY_OR_NOW DL_NOW # else # define LT_DLLAZY_OR_NOW 0 # endif # endif # endif # endif #endif /* When -fvisbility=hidden is used, assume the code has been annotated correspondingly for the symbols needed. */ #if defined(__GNUC__) && (((__GNUC__ == 3) && (__GNUC_MINOR__ >= 3)) || (__GNUC__ > 3)) int fnord () __attribute__((visibility("default"))); #endif int fnord () { return 42; } int main () { void *self = dlopen (0, LT_DLGLOBAL|LT_DLLAZY_OR_NOW); int status = $lt_dlunknown; if (self) { if (dlsym (self,"fnord")) status = $lt_dlno_uscore; else { if (dlsym( self,"_fnord")) status = $lt_dlneed_uscore; else puts (dlerror ()); } /* dlclose (self); */ } else puts (dlerror ()); return status; } _LT_EOF if { { eval echo "\"\$as_me\":${as_lineno-$LINENO}: \"$ac_link\""; } >&5 (eval $ac_link) 2>&5 ac_status=$? $as_echo "$as_me:${as_lineno-$LINENO}: \$? = $ac_status" >&5 test $ac_status = 0; } && test -s conftest${ac_exeext} 2>/dev/null; then (./conftest; exit; ) >&5 2>/dev/null lt_status=$? case x$lt_status in x$lt_dlno_uscore) lt_cv_dlopen_self_static=yes ;; x$lt_dlneed_uscore) lt_cv_dlopen_self_static=yes ;; x$lt_dlunknown|x*) lt_cv_dlopen_self_static=no ;; esac else : # compilation failed lt_cv_dlopen_self_static=no fi fi rm -fr conftest* fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $lt_cv_dlopen_self_static" >&5 $as_echo "$lt_cv_dlopen_self_static" >&6; } fi CPPFLAGS="$save_CPPFLAGS" LDFLAGS="$save_LDFLAGS" LIBS="$save_LIBS" ;; esac case $lt_cv_dlopen_self in yes|no) enable_dlopen_self=$lt_cv_dlopen_self ;; *) enable_dlopen_self=unknown ;; esac case $lt_cv_dlopen_self_static in yes|no) enable_dlopen_self_static=$lt_cv_dlopen_self_static ;; *) enable_dlopen_self_static=unknown ;; esac fi striplib= old_striplib= { $as_echo "$as_me:${as_lineno-$LINENO}: checking whether stripping libraries is possible" >&5 $as_echo_n "checking whether stripping libraries is possible... " >&6; } if test -n "$STRIP" && $STRIP -V 2>&1 | $GREP "GNU strip" >/dev/null; then test -z "$old_striplib" && old_striplib="$STRIP --strip-debug" test -z "$striplib" && striplib="$STRIP --strip-unneeded" { $as_echo "$as_me:${as_lineno-$LINENO}: result: yes" >&5 $as_echo "yes" >&6; } else # FIXME - insert some real tests, host_os isn't really good enough case $host_os in darwin*) if test -n "$STRIP" ; then striplib="$STRIP -x" old_striplib="$STRIP -S" { $as_echo "$as_me:${as_lineno-$LINENO}: result: yes" >&5 $as_echo "yes" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi ;; *) { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } ;; esac fi # Report which library types will actually be built { $as_echo "$as_me:${as_lineno-$LINENO}: checking if libtool supports shared libraries" >&5 $as_echo_n "checking if libtool supports shared libraries... " >&6; } { $as_echo "$as_me:${as_lineno-$LINENO}: result: $can_build_shared" >&5 $as_echo "$can_build_shared" >&6; } { $as_echo "$as_me:${as_lineno-$LINENO}: checking whether to build shared libraries" >&5 $as_echo_n "checking whether to build shared libraries... " >&6; } test "$can_build_shared" = "no" && enable_shared=no # On AIX, shared libraries and static libraries use the same namespace, and # are all built from PIC. case $host_os in aix3*) test "$enable_shared" = yes && enable_static=no if test -n "$RANLIB"; then archive_cmds="$archive_cmds~\$RANLIB \$lib" postinstall_cmds='$RANLIB $lib' fi ;; aix[4-9]*) if test "$host_cpu" != ia64 && test "$aix_use_runtimelinking" = no ; then test "$enable_shared" = yes && enable_static=no fi ;; esac { $as_echo "$as_me:${as_lineno-$LINENO}: result: $enable_shared" >&5 $as_echo "$enable_shared" >&6; } { $as_echo "$as_me:${as_lineno-$LINENO}: checking whether to build static libraries" >&5 $as_echo_n "checking whether to build static libraries... " >&6; } # Make sure either enable_shared or enable_static is yes. test "$enable_shared" = yes || enable_static=yes { $as_echo "$as_me:${as_lineno-$LINENO}: result: $enable_static" >&5 $as_echo "$enable_static" >&6; } fi ac_ext=c ac_cpp='$CPP $CPPFLAGS' ac_compile='$CC -c $CFLAGS $CPPFLAGS conftest.$ac_ext >&5' ac_link='$CC -o conftest$ac_exeext $CFLAGS $CPPFLAGS $LDFLAGS conftest.$ac_ext $LIBS >&5' ac_compiler_gnu=$ac_cv_c_compiler_gnu CC="$lt_save_CC" ac_config_commands="$ac_config_commands libtool" # Only expand once: # For testing cross-compilation behaviour. #cross_compiling=yes { echo; echo "${term_bold}Optional Platform Environment:${term_norm}"; } >& 6 for ac_header in sys/signal.h do : ac_fn_c_check_header_mongrel "$LINENO" "sys/signal.h" "ac_cv_header_sys_signal_h" "$ac_includes_default" if test "x$ac_cv_header_sys_signal_h" = xyes; then : cat >>confdefs.h <<_ACEOF #define HAVE_SYS_SIGNAL_H 1 _ACEOF fi done case "$host_os" in sunos4* | freebsd* | openbsd* | netbsd* | dragonfly* | kfreebsd* | knetbsd*) CFG_SIGNALS=signals-bsd.h ;; hpux*) CFG_SIGNALS=signals-hpux.h ;; macos* | darwin*) CFG_SIGNALS=signals-macos.h ;; gnu*) CFG_SIGNALS=signals-hurd.h ;; *) CFG_SIGNALS=signals.h ;; esac cat >>confdefs.h <<_ACEOF #define CFG_SIGNALS "$CFG_SIGNALS" _ACEOF # How to determine the memory page size. for ac_header in unistd.h do : ac_fn_c_check_header_mongrel "$LINENO" "unistd.h" "ac_cv_header_unistd_h" "$ac_includes_default" if test "x$ac_cv_header_unistd_h" = xyes; then : cat >>confdefs.h <<_ACEOF #define HAVE_UNISTD_H 1 _ACEOF fi done { $as_echo "$as_me:${as_lineno-$LINENO}: checking for getpagesize" >&5 $as_echo_n "checking for getpagesize... " >&6; } if ${sv_cv_func_getpagesize+:} false; then : $as_echo_n "(cached) " >&6 else cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ #if HAVE_UNISTD_H #include #include #endif int main () { int pgsz = getpagesize(); ; return 0; } _ACEOF if ac_fn_c_try_link "$LINENO"; then : sv_cv_func_getpagesize=yes else sv_cv_func_getpagesize=no fi rm -f core conftest.err conftest.$ac_objext \ conftest$ac_exeext conftest.$ac_ext fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $sv_cv_func_getpagesize" >&5 $as_echo "$sv_cv_func_getpagesize" >&6; } if test $sv_cv_func_getpagesize = yes; then $as_echo "#define HAVE_GETPAGESIZE 1" >>confdefs.h fi { $as_echo "$as_me:${as_lineno-$LINENO}: checking for sysconf(_SC_PAGESIZE)" >&5 $as_echo_n "checking for sysconf(_SC_PAGESIZE)... " >&6; } if ${sv_cv_func_sysconf_pagesize+:} false; then : $as_echo_n "(cached) " >&6 else cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ #if HAVE_UNISTD_H #include #include #endif int main () { int pgsz = sysconf (_SC_PAGESIZE); ; return 0; } _ACEOF if ac_fn_c_try_link "$LINENO"; then : sv_cv_func_sysconf_pagesize=yes else sv_cv_func_sysconf_pagesize=no fi rm -f core conftest.err conftest.$ac_objext \ conftest$ac_exeext conftest.$ac_ext fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $sv_cv_func_sysconf_pagesize" >&5 $as_echo "$sv_cv_func_sysconf_pagesize" >&6; } if test $sv_cv_func_sysconf_pagesize = yes; then $as_echo "#define HAVE_SYSCONF_PAGESIZE 1" >>confdefs.h fi { $as_echo "$as_me:${as_lineno-$LINENO}: checking for PAGESIZE in limits.h" >&5 $as_echo_n "checking for PAGESIZE in limits.h... " >&6; } if ${sv_cv_macro_pagesize+:} false; then : $as_echo_n "(cached) " >&6 else cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ #include int main () { int pgsz = PAGESIZE; ; return 0; } _ACEOF if ac_fn_c_try_link "$LINENO"; then : sv_cv_macro_pagesize=yes else sv_cv_macro_pagesize=no fi rm -f core conftest.err conftest.$ac_objext \ conftest$ac_exeext conftest.$ac_ext fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $sv_cv_macro_pagesize" >&5 $as_echo "$sv_cv_macro_pagesize" >&6; } if test $sv_cv_macro_pagesize = yes; then $as_echo "#define HAVE_PAGESIZE 1" >>confdefs.h fi # How to allocate fresh memory using mmap. # (We need mmap, because mprotect() doesn't work on malloc()ed memory on # some systems.) { $as_echo "$as_me:${as_lineno-$LINENO}: checking for mmap with MAP_ANON" >&5 $as_echo_n "checking for mmap with MAP_ANON... " >&6; } if ${sv_cv_func_mmap_anon+:} false; then : $as_echo_n "(cached) " >&6 else if test "$cross_compiling" = yes; then : case "$host_os" in freebsd* | linux* | osf*) sv_cv_func_mmap_anon=yes ;; *) cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ #include #include int main () { mmap (0, 0x10000, PROT_READ | PROT_WRITE, MAP_ANON | MAP_PRIVATE, -1, 0); ; return 0; } _ACEOF if ac_fn_c_try_link "$LINENO"; then : sv_cv_func_mmap_anon="guessing yes" else sv_cv_func_mmap_anon=no fi rm -f core conftest.err conftest.$ac_objext \ conftest$ac_exeext conftest.$ac_ext ;; esac else cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ #include #include int main () { void *p = mmap (0, 0x10000, PROT_READ | PROT_WRITE, MAP_ANON | MAP_PRIVATE, -1, 0); return (p == (void *)(-1)); } _ACEOF if ac_fn_c_try_run "$LINENO"; then : sv_cv_func_mmap_anon=yes else sv_cv_func_mmap_anon=no fi rm -f core *.core core.conftest.* gmon.out bb.out conftest$ac_exeext \ conftest.$ac_objext conftest.beam conftest.$ac_ext fi fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $sv_cv_func_mmap_anon" >&5 $as_echo "$sv_cv_func_mmap_anon" >&6; } if test "$sv_cv_func_mmap_anon" != no; then $as_echo "#define HAVE_MMAP_ANON 1" >>confdefs.h fi { $as_echo "$as_me:${as_lineno-$LINENO}: checking for mmap with MAP_ANONYMOUS" >&5 $as_echo_n "checking for mmap with MAP_ANONYMOUS... " >&6; } if ${sv_cv_func_mmap_anonymous+:} false; then : $as_echo_n "(cached) " >&6 else if test "$cross_compiling" = yes; then : case "$host_os" in hpux* | linux* | osf*) sv_cv_func_mmap_anonymous=yes ;; *) cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ #include #include int main () { mmap (0, 0x10000, PROT_READ | PROT_WRITE, MAP_ANONYMOUS | MAP_PRIVATE, -1, 0); ; return 0; } _ACEOF if ac_fn_c_try_link "$LINENO"; then : sv_cv_func_mmap_anonymous="guessing yes" else sv_cv_func_mmap_anonymous=no fi rm -f core conftest.err conftest.$ac_objext \ conftest$ac_exeext conftest.$ac_ext ;; esac else cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ #include #include int main () { void *p = mmap (0, 0x10000, PROT_READ | PROT_WRITE, MAP_ANONYMOUS | MAP_PRIVATE, -1, 0); return (p == (void *)(-1)); } _ACEOF if ac_fn_c_try_run "$LINENO"; then : sv_cv_func_mmap_anonymous=yes else sv_cv_func_mmap_anonymous=no fi rm -f core *.core core.conftest.* gmon.out bb.out conftest$ac_exeext \ conftest.$ac_objext conftest.beam conftest.$ac_ext fi fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $sv_cv_func_mmap_anonymous" >&5 $as_echo "$sv_cv_func_mmap_anonymous" >&6; } if test "$sv_cv_func_mmap_anonymous" != no; then $as_echo "#define HAVE_MMAP_ANONYMOUS 1" >>confdefs.h fi { $as_echo "$as_me:${as_lineno-$LINENO}: checking for mmap of /dev/zero" >&5 $as_echo_n "checking for mmap of /dev/zero... " >&6; } if ${sv_cv_func_mmap_devzero+:} false; then : $as_echo_n "(cached) " >&6 else if test "$cross_compiling" = yes; then : case "$host_os" in freebsd* | irix* | linux* | osf* | solaris* | sunos4*) sv_cv_func_mmap_devzero=yes ;; *) cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ #include #include #ifndef MAP_FILE #define MAP_FILE 0 #endif int main () { mmap (0, 0x10000, PROT_READ | PROT_WRITE, MAP_FILE | MAP_PRIVATE, 7, 0); ; return 0; } _ACEOF if ac_fn_c_try_link "$LINENO"; then : sv_cv_func_mmap_devzero="guessing yes" else sv_cv_func_mmap_devzero=no fi rm -f core conftest.err conftest.$ac_objext \ conftest$ac_exeext conftest.$ac_ext ;; esac else cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ #include #include #include #ifndef MAP_FILE #define MAP_FILE 0 #endif int main () { int fd; void *p; fd = open ("/dev/zero", O_RDONLY, 0666); if (fd < 0) return 1; p = mmap (0, 0x10000, PROT_READ | PROT_WRITE, MAP_FILE | MAP_PRIVATE, fd, 0); return (p == (void *)(-1)); } _ACEOF if ac_fn_c_try_run "$LINENO"; then : sv_cv_func_mmap_devzero=yes else sv_cv_func_mmap_devzero=no fi rm -f core *.core core.conftest.* gmon.out bb.out conftest$ac_exeext \ conftest.$ac_objext conftest.beam conftest.$ac_ext fi fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $sv_cv_func_mmap_devzero" >&5 $as_echo "$sv_cv_func_mmap_devzero" >&6; } if test "$sv_cv_func_mmap_devzero" != no; then $as_echo "#define HAVE_MMAP_DEVZERO 1" >>confdefs.h fi # How to write a SIGSEGV handler with access to the fault address. # On MacOS X 10.2 or newer, we don't need these tests, because we'll end up # using handler-macos.c anyway. If we were to perform the tests, 5 Crash Report # dialog windows would pop up. case "$host_os" in macos* | darwin[6-9]* | darwin[1-9][0-9]*) ;; *) { $as_echo "$as_me:${as_lineno-$LINENO}: checking whether a fault handler according to POSIX works" >&5 $as_echo_n "checking whether a fault handler according to POSIX works... " >&6; } if ${sv_cv_fault_posix+:} false; then : $as_echo_n "(cached) " >&6 else if test "$cross_compiling" = yes; then : case "$host" in *-*-solaris2.[7-9] | i?86-*-linux2.[4-9]* | i?86-*-freebsd[4-9]* | alpha*-dec-osf[4-9]* | *-*-hpux11* | mips-sgi-irix6*) sv_cv_fault_posix=yes ;; *) cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ #include void sigsegv_handler (int sig, siginfo_t *sip, void *ucp) { void *fault_address = (void *) (sip->si_addr); } int main () { struct sigaction action; action.sa_sigaction = &sigsegv_handler; action.sa_flags = SA_SIGINFO; ; return 0; } _ACEOF if ac_fn_c_try_link "$LINENO"; then : sv_cv_fault_posix="guessing no" else sv_cv_fault_posix=no fi rm -f core conftest.err conftest.$ac_objext \ conftest$ac_exeext conftest.$ac_ext ;; esac else cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ #include #include #if HAVE_SYS_SIGNAL_H # include #endif #include #include #if HAVE_MMAP_DEVZERO # include # ifndef MAP_FILE # define MAP_FILE 0 # endif #endif #ifndef PROT_NONE # define PROT_NONE 0 #endif #if HAVE_MMAP_ANON # define zero_fd -1 # define map_flags MAP_ANON | MAP_PRIVATE #elif HAVE_MMAP_ANONYMOUS # define zero_fd -1 # define map_flags MAP_ANONYMOUS | MAP_PRIVATE #elif HAVE_MMAP_DEVZERO static int zero_fd; # define map_flags MAP_FILE | MAP_PRIVATE #endif unsigned long page; int handler_called = 0; void sigsegv_handler (int sig, siginfo_t *sip, void *ucp) { void *fault_address = (void *) (sip->si_addr); handler_called++; if (handler_called == 10) exit (4); if (fault_address != (void*)(page + 0x678)) exit (3); if (mprotect ((void *) page, 0x10000, PROT_READ | PROT_WRITE) < 0) exit (2); } void crasher (unsigned long p) { *(int *) (p + 0x678) = 42; } int main () { void *p; struct sigaction action; /* Preparations. */ #if !HAVE_MMAP_ANON && !HAVE_MMAP_ANONYMOUS && HAVE_MMAP_DEVZERO zero_fd = open ("/dev/zero", O_RDONLY, 0644); #endif /* Setup some mmaped memory. */ #ifdef __hpux /* HP-UX 10 mmap() often fails when given a hint. So give the OS complete freedom about the address range. */ p = mmap ((void *) 0, 0x10000, PROT_READ | PROT_WRITE, map_flags, zero_fd, 0); #else p = mmap ((void *) 0x12340000, 0x10000, PROT_READ | PROT_WRITE, map_flags, zero_fd, 0); #endif if (p == (void *)(-1)) exit (2); page = (unsigned long) p; /* Make it read-only. */ if (mprotect ((void *) page, 0x10000, PROT_READ) < 0) exit (2); /* Install the SIGSEGV handler. */ sigemptyset(&action.sa_mask); action.sa_sigaction = &sigsegv_handler; action.sa_flags = SA_SIGINFO; sigaction (SIGSEGV, &action, (struct sigaction *) NULL); sigaction (SIGBUS, &action, (struct sigaction *) NULL); /* The first write access should invoke the handler and then complete. */ crasher (page); /* The second write access should not invoke the handler. */ crasher (page); /* Check that the handler was called only once. */ if (handler_called != 1) exit (1); /* Test passed! */ return 0; } _ACEOF if ac_fn_c_try_run "$LINENO"; then : sv_cv_fault_posix=yes else sv_cv_fault_posix=no fi rm -f core *.core core.conftest.* gmon.out bb.out conftest$ac_exeext \ conftest.$ac_objext conftest.beam conftest.$ac_ext fi fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $sv_cv_fault_posix" >&5 $as_echo "$sv_cv_fault_posix" >&6; } { $as_echo "$as_me:${as_lineno-$LINENO}: checking whether a fault handler according to Linux/i386 works" >&5 $as_echo_n "checking whether a fault handler according to Linux/i386 works... " >&6; } if ${sv_cv_fault_linux_i386+:} false; then : $as_echo_n "(cached) " >&6 else if test "$cross_compiling" = yes; then : case "$host" in i?86-*-linux2.[2-9]*) sv_cv_fault_linux_i386=yes ;; *) cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ #include #include void sigsegv_handler (int sig, struct sigcontext sc) { void *fault_address = (void *) (sc.cr2); } int main () { struct sigaction action; ; return 0; } _ACEOF if ac_fn_c_try_link "$LINENO"; then : sv_cv_fault_linux_i386="guessing no" else sv_cv_fault_linux_i386=no fi rm -f core conftest.err conftest.$ac_objext \ conftest$ac_exeext conftest.$ac_ext ;; esac else cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ #include #include #if HAVE_SYS_SIGNAL_H # include #endif #include #include #include #if HAVE_MMAP_DEVZERO # include # ifndef MAP_FILE # define MAP_FILE 0 # endif #endif #ifndef PROT_NONE # define PROT_NONE 0 #endif #if HAVE_MMAP_ANON # define zero_fd -1 # define map_flags MAP_ANON | MAP_PRIVATE #elif HAVE_MMAP_ANONYMOUS # define zero_fd -1 # define map_flags MAP_ANONYMOUS | MAP_PRIVATE #elif HAVE_MMAP_DEVZERO static int zero_fd; # define map_flags MAP_FILE | MAP_PRIVATE #endif unsigned long page; int handler_called = 0; void sigsegv_handler (int sig, struct sigcontext sc) { void *fault_address = (void *) (sc.cr2); handler_called++; if (handler_called == 10) exit (4); if (fault_address != (void*)(page + 0x678)) exit (3); if (mprotect ((void *) page, 0x10000, PROT_READ | PROT_WRITE) < 0) exit (2); } void crasher (unsigned long p) { *(int *) (p + 0x678) = 42; } int main () { void *p; struct sigaction action; /* Preparations. */ #if !HAVE_MMAP_ANON && !HAVE_MMAP_ANONYMOUS && HAVE_MMAP_DEVZERO zero_fd = open ("/dev/zero", O_RDONLY, 0644); #endif /* Setup some mmaped memory. */ #ifdef __hpux /* HP-UX 10 mmap() often fails when given a hint. So give the OS complete freedom about the address range. */ p = mmap ((void *) 0, 0x10000, PROT_READ | PROT_WRITE, map_flags, zero_fd, 0); #else p = mmap ((void *) 0x12340000, 0x10000, PROT_READ | PROT_WRITE, map_flags, zero_fd, 0); #endif if (p == (void *)(-1)) exit (2); page = (unsigned long) p; /* Make it read-only. */ if (mprotect ((void *) page, 0x10000, PROT_READ) < 0) exit (2); /* Install the SIGSEGV handler. */ sigemptyset(&action.sa_mask); action.sa_handler = (void (*) (int)) &sigsegv_handler; action.sa_flags = 0; sigaction (SIGSEGV, &action, (struct sigaction *) NULL); sigaction (SIGBUS, &action, (struct sigaction *) NULL); /* The first write access should invoke the handler and then complete. */ crasher (page); /* The second write access should not invoke the handler. */ crasher (page); /* Check that the handler was called only once. */ if (handler_called != 1) exit (1); /* Test passed! */ return 0; } _ACEOF if ac_fn_c_try_run "$LINENO"; then : sv_cv_fault_linux_i386=yes else sv_cv_fault_linux_i386=no fi rm -f core *.core core.conftest.* gmon.out bb.out conftest$ac_exeext \ conftest.$ac_objext conftest.beam conftest.$ac_ext fi fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $sv_cv_fault_linux_i386" >&5 $as_echo "$sv_cv_fault_linux_i386" >&6; } { $as_echo "$as_me:${as_lineno-$LINENO}: checking whether a fault handler according to old Linux/i386 works" >&5 $as_echo_n "checking whether a fault handler according to old Linux/i386 works... " >&6; } if ${sv_cv_fault_linux_i386_old+:} false; then : $as_echo_n "(cached) " >&6 else if test "$cross_compiling" = yes; then : case "$host" in i?86-*-linux2.[2-9]*) sv_cv_fault_linux_i386_old=yes ;; *) cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ #include void sigsegv_handler (int sig, unsigned int more) { void *fault_address = (void *) (((unsigned long *) &more) [21]); } int main () { struct sigaction action; ; return 0; } _ACEOF if ac_fn_c_try_link "$LINENO"; then : sv_cv_fault_linux_i386_old="guessing no" else sv_cv_fault_linux_i386_old=no fi rm -f core conftest.err conftest.$ac_objext \ conftest$ac_exeext conftest.$ac_ext ;; esac else cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ #include #include #if HAVE_SYS_SIGNAL_H # include #endif #include #include #if HAVE_MMAP_DEVZERO # include # ifndef MAP_FILE # define MAP_FILE 0 # endif #endif #ifndef PROT_NONE # define PROT_NONE 0 #endif #if HAVE_MMAP_ANON # define zero_fd -1 # define map_flags MAP_ANON | MAP_PRIVATE #elif HAVE_MMAP_ANONYMOUS # define zero_fd -1 # define map_flags MAP_ANONYMOUS | MAP_PRIVATE #elif HAVE_MMAP_DEVZERO static int zero_fd; # define map_flags MAP_FILE | MAP_PRIVATE #endif unsigned long page; int handler_called = 0; void sigsegv_handler (int sig, unsigned int more) { void *fault_address = (void *) (((unsigned long *) &more) [21]); handler_called++; if (handler_called == 10) exit (4); if (fault_address != (void*)(page + 0x678)) exit (3); if (mprotect ((void *) page, 0x10000, PROT_READ | PROT_WRITE) < 0) exit (2); } void crasher (unsigned long p) { *(int *) (p + 0x678) = 42; } int main () { void *p; struct sigaction action; /* Preparations. */ #if !HAVE_MMAP_ANON && !HAVE_MMAP_ANONYMOUS && HAVE_MMAP_DEVZERO zero_fd = open ("/dev/zero", O_RDONLY, 0644); #endif /* Setup some mmaped memory. */ #ifdef __hpux /* HP-UX 10 mmap() often fails when given a hint. So give the OS complete freedom about the address range. */ p = mmap ((void *) 0, 0x10000, PROT_READ | PROT_WRITE, map_flags, zero_fd, 0); #else p = mmap ((void *) 0x12340000, 0x10000, PROT_READ | PROT_WRITE, map_flags, zero_fd, 0); #endif if (p == (void *)(-1)) exit (2); page = (unsigned long) p; /* Make it read-only. */ if (mprotect ((void *) page, 0x10000, PROT_READ) < 0) exit (2); /* Install the SIGSEGV handler. */ sigemptyset(&action.sa_mask); action.sa_handler = (void (*) (int)) &sigsegv_handler; action.sa_flags = 0; sigaction (SIGSEGV, &action, (struct sigaction *) NULL); sigaction (SIGBUS, &action, (struct sigaction *) NULL); /* The first write access should invoke the handler and then complete. */ crasher (page); /* The second write access should not invoke the handler. */ crasher (page); /* Check that the handler was called only once. */ if (handler_called != 1) exit (1); /* Test passed! */ return 0; } _ACEOF if ac_fn_c_try_run "$LINENO"; then : sv_cv_fault_linux_i386_old=yes else sv_cv_fault_linux_i386_old=no fi rm -f core *.core core.conftest.* gmon.out bb.out conftest$ac_exeext \ conftest.$ac_objext conftest.beam conftest.$ac_ext fi fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $sv_cv_fault_linux_i386_old" >&5 $as_echo "$sv_cv_fault_linux_i386_old" >&6; } { $as_echo "$as_me:${as_lineno-$LINENO}: checking whether a fault handler according to Linux/m68k works" >&5 $as_echo_n "checking whether a fault handler according to Linux/m68k works... " >&6; } if ${sv_cv_fault_linux_m68k+:} false; then : $as_echo_n "(cached) " >&6 else if test "$cross_compiling" = yes; then : case "$host" in *) cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ #include #include #include "$srcdir/src/fault-linux-m68k.c" void sigsegv_handler (int sig, int code, struct sigcontext *scp) { void *fault_address = (void *) (get_fault_addr (scp)); } int main () { struct sigaction action; ; return 0; } _ACEOF if ac_fn_c_try_link "$LINENO"; then : sv_cv_fault_linux_m68k="guessing no" else sv_cv_fault_linux_m68k=no fi rm -f core conftest.err conftest.$ac_objext \ conftest$ac_exeext conftest.$ac_ext ;; esac else cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ #include #include #if HAVE_SYS_SIGNAL_H # include #endif #include #include "$srcdir/src/fault-linux-m68k.c" #include #include #if HAVE_MMAP_DEVZERO # include # ifndef MAP_FILE # define MAP_FILE 0 # endif #endif #ifndef PROT_NONE # define PROT_NONE 0 #endif #if HAVE_MMAP_ANON # define zero_fd -1 # define map_flags MAP_ANON | MAP_PRIVATE #elif HAVE_MMAP_ANONYMOUS # define zero_fd -1 # define map_flags MAP_ANONYMOUS | MAP_PRIVATE #elif HAVE_MMAP_DEVZERO static int zero_fd; # define map_flags MAP_FILE | MAP_PRIVATE #endif unsigned long page; int handler_called = 0; void sigsegv_handler (int sig, int code, struct sigcontext *scp) { void *fault_address = (void *) (get_fault_addr (scp)); handler_called++; if (handler_called == 10) exit (4); if (fault_address != (void*)(page + 0x678)) exit (3); if (mprotect ((void *) page, 0x10000, PROT_READ | PROT_WRITE) < 0) exit (2); } void crasher (unsigned long p) { *(int *) (p + 0x678) = 42; } int main () { void *p; struct sigaction action; /* Preparations. */ #if !HAVE_MMAP_ANON && !HAVE_MMAP_ANONYMOUS && HAVE_MMAP_DEVZERO zero_fd = open ("/dev/zero", O_RDONLY, 0644); #endif /* Setup some mmaped memory. */ #ifdef __hpux /* HP-UX 10 mmap() often fails when given a hint. So give the OS complete freedom about the address range. */ p = mmap ((void *) 0, 0x10000, PROT_READ | PROT_WRITE, map_flags, zero_fd, 0); #else p = mmap ((void *) 0x12340000, 0x10000, PROT_READ | PROT_WRITE, map_flags, zero_fd, 0); #endif if (p == (void *)(-1)) exit (2); page = (unsigned long) p; /* Make it read-only. */ if (mprotect ((void *) page, 0x10000, PROT_READ) < 0) exit (2); /* Install the SIGSEGV handler. */ sigemptyset(&action.sa_mask); action.sa_handler = (void (*) (int)) &sigsegv_handler; action.sa_flags = 0; sigaction (SIGSEGV, &action, (struct sigaction *) NULL); sigaction (SIGBUS, &action, (struct sigaction *) NULL); /* The first write access should invoke the handler and then complete. */ crasher (page); /* The second write access should not invoke the handler. */ crasher (page); /* Check that the handler was called only once. */ if (handler_called != 1) exit (1); /* Test passed! */ return 0; } _ACEOF if ac_fn_c_try_run "$LINENO"; then : sv_cv_fault_linux_m68k=yes else sv_cv_fault_linux_m68k=no fi rm -f core *.core core.conftest.* gmon.out bb.out conftest$ac_exeext \ conftest.$ac_objext conftest.beam conftest.$ac_ext fi fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $sv_cv_fault_linux_m68k" >&5 $as_echo "$sv_cv_fault_linux_m68k" >&6; } { $as_echo "$as_me:${as_lineno-$LINENO}: checking whether a fault handler according to Linux/PowerPC works" >&5 $as_echo_n "checking whether a fault handler according to Linux/PowerPC works... " >&6; } if ${sv_cv_fault_linux_powerpc+:} false; then : $as_echo_n "(cached) " >&6 else if test "$cross_compiling" = yes; then : case "$host" in *) cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ #include #include void sigsegv_handler (int sig, struct sigcontext *scp) { void *fault_address = (void *) (scp->regs->dar); } int main () { struct sigaction action; ; return 0; } _ACEOF if ac_fn_c_try_link "$LINENO"; then : sv_cv_fault_linux_powerpc="guessing no" else sv_cv_fault_linux_powerpc=no fi rm -f core conftest.err conftest.$ac_objext \ conftest$ac_exeext conftest.$ac_ext ;; esac else cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ #include #include #if HAVE_SYS_SIGNAL_H # include #endif #include #include #include #if HAVE_MMAP_DEVZERO # include # ifndef MAP_FILE # define MAP_FILE 0 # endif #endif #ifndef PROT_NONE # define PROT_NONE 0 #endif #if HAVE_MMAP_ANON # define zero_fd -1 # define map_flags MAP_ANON | MAP_PRIVATE #elif HAVE_MMAP_ANONYMOUS # define zero_fd -1 # define map_flags MAP_ANONYMOUS | MAP_PRIVATE #elif HAVE_MMAP_DEVZERO static int zero_fd; # define map_flags MAP_FILE | MAP_PRIVATE #endif unsigned long page; int handler_called = 0; void sigsegv_handler (int sig, struct sigcontext *scp) { void *fault_address = (void *) (scp->regs->dar); handler_called++; if (handler_called == 10) exit (4); if (fault_address != (void*)(page + 0x678)) exit (3); if (mprotect ((void *) page, 0x10000, PROT_READ | PROT_WRITE) < 0) exit (2); } void crasher (unsigned long p) { *(int *) (p + 0x678) = 42; } int main () { void *p; struct sigaction action; /* Preparations. */ #if !HAVE_MMAP_ANON && !HAVE_MMAP_ANONYMOUS && HAVE_MMAP_DEVZERO zero_fd = open ("/dev/zero", O_RDONLY, 0644); #endif /* Setup some mmaped memory. */ #ifdef __hpux /* HP-UX 10 mmap() often fails when given a hint. So give the OS complete freedom about the address range. */ p = mmap ((void *) 0, 0x10000, PROT_READ | PROT_WRITE, map_flags, zero_fd, 0); #else p = mmap ((void *) 0x12340000, 0x10000, PROT_READ | PROT_WRITE, map_flags, zero_fd, 0); #endif if (p == (void *)(-1)) exit (2); page = (unsigned long) p; /* Make it read-only. */ if (mprotect ((void *) page, 0x10000, PROT_READ) < 0) exit (2); /* Install the SIGSEGV handler. */ sigemptyset(&action.sa_mask); action.sa_handler = (void (*) (int)) &sigsegv_handler; action.sa_flags = 0; sigaction (SIGSEGV, &action, (struct sigaction *) NULL); sigaction (SIGBUS, &action, (struct sigaction *) NULL); /* The first write access should invoke the handler and then complete. */ crasher (page); /* The second write access should not invoke the handler. */ crasher (page); /* Check that the handler was called only once. */ if (handler_called != 1) exit (1); /* Test passed! */ return 0; } _ACEOF if ac_fn_c_try_run "$LINENO"; then : sv_cv_fault_linux_powerpc=yes else sv_cv_fault_linux_powerpc=no fi rm -f core *.core core.conftest.* gmon.out bb.out conftest$ac_exeext \ conftest.$ac_objext conftest.beam conftest.$ac_ext fi fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $sv_cv_fault_linux_powerpc" >&5 $as_echo "$sv_cv_fault_linux_powerpc" >&6; } { $as_echo "$as_me:${as_lineno-$LINENO}: checking whether a fault handler according to Linux/HPPA works" >&5 $as_echo_n "checking whether a fault handler according to Linux/HPPA works... " >&6; } if ${sv_cv_fault_linux_hppa+:} false; then : $as_echo_n "(cached) " >&6 else if test "$cross_compiling" = yes; then : case "$host" in *) cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ #include void sigsegv_handler (int sig, siginfo_t *sip, void *ucp) { void *fault_address = (void *) (sip->si_ptr); } int main () { struct sigaction action; action.sa_sigaction = &sigsegv_handler; action.sa_flags = SA_SIGINFO; ; return 0; } _ACEOF if ac_fn_c_try_link "$LINENO"; then : sv_cv_fault_linux_hppa="guessing no" else sv_cv_fault_linux_hppa=no fi rm -f core conftest.err conftest.$ac_objext \ conftest$ac_exeext conftest.$ac_ext ;; esac else cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ #include #include #if HAVE_SYS_SIGNAL_H # include #endif #include #include #if HAVE_MMAP_DEVZERO # include # ifndef MAP_FILE # define MAP_FILE 0 # endif #endif #ifndef PROT_NONE # define PROT_NONE 0 #endif #if HAVE_MMAP_ANON # define zero_fd -1 # define map_flags MAP_ANON | MAP_PRIVATE #elif HAVE_MMAP_ANONYMOUS # define zero_fd -1 # define map_flags MAP_ANONYMOUS | MAP_PRIVATE #elif HAVE_MMAP_DEVZERO static int zero_fd; # define map_flags MAP_FILE | MAP_PRIVATE #endif unsigned long page; int handler_called = 0; void sigsegv_handler (int sig, siginfo_t *sip, void *ucp) { void *fault_address = (void *) (sip->si_ptr); handler_called++; if (handler_called == 10) exit (4); if (fault_address != (void*)(page + 0x678)) exit (3); if (mprotect ((void *) page, 0x10000, PROT_READ | PROT_WRITE) < 0) exit (2); } void crasher (unsigned long p) { *(int *) (p + 0x678) = 42; } int main () { void *p; struct sigaction action; /* Preparations. */ #if !HAVE_MMAP_ANON && !HAVE_MMAP_ANONYMOUS && HAVE_MMAP_DEVZERO zero_fd = open ("/dev/zero", O_RDONLY, 0644); #endif /* Setup some mmaped memory. */ #ifdef __hpux /* HP-UX 10 mmap() often fails when given a hint. So give the OS complete freedom about the address range. */ p = mmap ((void *) 0, 0x10000, PROT_READ | PROT_WRITE, map_flags, zero_fd, 0); #else p = mmap ((void *) 0x12340000, 0x10000, PROT_READ | PROT_WRITE, map_flags, zero_fd, 0); #endif if (p == (void *)(-1)) exit (2); page = (unsigned long) p; /* Make it read-only. */ if (mprotect ((void *) page, 0x10000, PROT_READ) < 0) exit (2); /* Install the SIGSEGV handler. */ sigemptyset(&action.sa_mask); action.sa_sigaction = &sigsegv_handler; action.sa_flags = SA_SIGINFO; sigaction (SIGSEGV, &action, (struct sigaction *) NULL); sigaction (SIGBUS, &action, (struct sigaction *) NULL); /* The first write access should invoke the handler and then complete. */ crasher (page); /* The second write access should not invoke the handler. */ crasher (page); /* Check that the handler was called only once. */ if (handler_called != 1) exit (1); /* Test passed! */ return 0; } _ACEOF if ac_fn_c_try_run "$LINENO"; then : sv_cv_fault_linux_hppa=yes else sv_cv_fault_linux_hppa=no fi rm -f core *.core core.conftest.* gmon.out bb.out conftest$ac_exeext \ conftest.$ac_objext conftest.beam conftest.$ac_ext fi fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $sv_cv_fault_linux_hppa" >&5 $as_echo "$sv_cv_fault_linux_hppa" >&6; } { $as_echo "$as_me:${as_lineno-$LINENO}: checking whether a fault handler according to BSD works" >&5 $as_echo_n "checking whether a fault handler according to BSD works... " >&6; } if ${sv_cv_fault_bsd+:} false; then : $as_echo_n "(cached) " >&6 else if test "$cross_compiling" = yes; then : case "$host" in i?86-*-freebsd[4-9]*) sv_cv_fault_bsd=yes ;; *) cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ #include void sigsegv_handler (int sig, int code, struct sigcontext *scp, void *addr) { void *fault_address = (void *) (addr); } int main () { struct sigaction action; ; return 0; } _ACEOF if ac_fn_c_try_link "$LINENO"; then : sv_cv_fault_bsd="guessing no" else sv_cv_fault_bsd=no fi rm -f core conftest.err conftest.$ac_objext \ conftest$ac_exeext conftest.$ac_ext ;; esac else cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ #include #include #if HAVE_SYS_SIGNAL_H # include #endif #include #include #if HAVE_MMAP_DEVZERO # include # ifndef MAP_FILE # define MAP_FILE 0 # endif #endif #ifndef PROT_NONE # define PROT_NONE 0 #endif #if HAVE_MMAP_ANON # define zero_fd -1 # define map_flags MAP_ANON | MAP_PRIVATE #elif HAVE_MMAP_ANONYMOUS # define zero_fd -1 # define map_flags MAP_ANONYMOUS | MAP_PRIVATE #elif HAVE_MMAP_DEVZERO static int zero_fd; # define map_flags MAP_FILE | MAP_PRIVATE #endif unsigned long page; int handler_called = 0; void sigsegv_handler (int sig, int code, struct sigcontext *scp, void *addr) { void *fault_address = (void *) (addr); handler_called++; if (handler_called == 10) exit (4); if (fault_address != (void*)(page + 0x678)) exit (3); if (mprotect ((void *) page, 0x10000, PROT_READ | PROT_WRITE) < 0) exit (2); } void crasher (unsigned long p) { *(int *) (p + 0x678) = 42; } int main () { void *p; struct sigaction action; /* Preparations. */ #if !HAVE_MMAP_ANON && !HAVE_MMAP_ANONYMOUS && HAVE_MMAP_DEVZERO zero_fd = open ("/dev/zero", O_RDONLY, 0644); #endif /* Setup some mmaped memory. */ #ifdef __hpux /* HP-UX 10 mmap() often fails when given a hint. So give the OS complete freedom about the address range. */ p = mmap ((void *) 0, 0x10000, PROT_READ | PROT_WRITE, map_flags, zero_fd, 0); #else p = mmap ((void *) 0x12340000, 0x10000, PROT_READ | PROT_WRITE, map_flags, zero_fd, 0); #endif if (p == (void *)(-1)) exit (2); page = (unsigned long) p; /* Make it read-only. */ if (mprotect ((void *) page, 0x10000, PROT_READ) < 0) exit (2); /* Install the SIGSEGV handler. */ sigemptyset(&action.sa_mask); action.sa_handler = (void (*) (int)) &sigsegv_handler; action.sa_flags = 0; sigaction (SIGSEGV, &action, (struct sigaction *) NULL); sigaction (SIGBUS, &action, (struct sigaction *) NULL); /* The first write access should invoke the handler and then complete. */ crasher (page); /* The second write access should not invoke the handler. */ crasher (page); /* Check that the handler was called only once. */ if (handler_called != 1) exit (1); /* Test passed! */ return 0; } _ACEOF if ac_fn_c_try_run "$LINENO"; then : sv_cv_fault_bsd=yes else sv_cv_fault_bsd=no fi rm -f core *.core core.conftest.* gmon.out bb.out conftest$ac_exeext \ conftest.$ac_objext conftest.beam conftest.$ac_ext fi fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $sv_cv_fault_bsd" >&5 $as_echo "$sv_cv_fault_bsd" >&6; } { $as_echo "$as_me:${as_lineno-$LINENO}: checking whether a fault handler according to IRIX works" >&5 $as_echo_n "checking whether a fault handler according to IRIX works... " >&6; } if ${sv_cv_fault_irix+:} false; then : $as_echo_n "(cached) " >&6 else if test "$cross_compiling" = yes; then : case "$host" in mips-sgi-irix6*) sv_cv_fault_irix=yes ;; *) cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ #include void sigsegv_handler (int sig, int code, struct sigcontext *scp) { void *fault_address = (void *) ((unsigned long) scp->sc_badvaddr); } int main () { struct sigaction action; ; return 0; } _ACEOF if ac_fn_c_try_link "$LINENO"; then : sv_cv_fault_irix="guessing no" else sv_cv_fault_irix=no fi rm -f core conftest.err conftest.$ac_objext \ conftest$ac_exeext conftest.$ac_ext ;; esac else cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ #include #include #if HAVE_SYS_SIGNAL_H # include #endif #include #include #if HAVE_MMAP_DEVZERO # include # ifndef MAP_FILE # define MAP_FILE 0 # endif #endif #ifndef PROT_NONE # define PROT_NONE 0 #endif #if HAVE_MMAP_ANON # define zero_fd -1 # define map_flags MAP_ANON | MAP_PRIVATE #elif HAVE_MMAP_ANONYMOUS # define zero_fd -1 # define map_flags MAP_ANONYMOUS | MAP_PRIVATE #elif HAVE_MMAP_DEVZERO static int zero_fd; # define map_flags MAP_FILE | MAP_PRIVATE #endif unsigned long page; int handler_called = 0; void sigsegv_handler (int sig, int code, struct sigcontext *scp) { void *fault_address = (void *) ((unsigned long) scp->sc_badvaddr); handler_called++; if (handler_called == 10) exit (4); if (fault_address != (void*)(page + 0x678)) exit (3); if (mprotect ((void *) page, 0x10000, PROT_READ | PROT_WRITE) < 0) exit (2); } void crasher (unsigned long p) { *(int *) (p + 0x678) = 42; } int main () { void *p; struct sigaction action; /* Preparations. */ #if !HAVE_MMAP_ANON && !HAVE_MMAP_ANONYMOUS && HAVE_MMAP_DEVZERO zero_fd = open ("/dev/zero", O_RDONLY, 0644); #endif /* Setup some mmaped memory. */ #ifdef __hpux /* HP-UX 10 mmap() often fails when given a hint. So give the OS complete freedom about the address range. */ p = mmap ((void *) 0, 0x10000, PROT_READ | PROT_WRITE, map_flags, zero_fd, 0); #else p = mmap ((void *) 0x12340000, 0x10000, PROT_READ | PROT_WRITE, map_flags, zero_fd, 0); #endif if (p == (void *)(-1)) exit (2); page = (unsigned long) p; /* Make it read-only. */ if (mprotect ((void *) page, 0x10000, PROT_READ) < 0) exit (2); /* Install the SIGSEGV handler. */ sigemptyset(&action.sa_mask); action.sa_handler = (void (*) (int)) &sigsegv_handler; action.sa_flags = 0; sigaction (SIGSEGV, &action, (struct sigaction *) NULL); sigaction (SIGBUS, &action, (struct sigaction *) NULL); /* The first write access should invoke the handler and then complete. */ crasher (page); /* The second write access should not invoke the handler. */ crasher (page); /* Check that the handler was called only once. */ if (handler_called != 1) exit (1); /* Test passed! */ return 0; } _ACEOF if ac_fn_c_try_run "$LINENO"; then : sv_cv_fault_irix=yes else sv_cv_fault_irix=no fi rm -f core *.core core.conftest.* gmon.out bb.out conftest$ac_exeext \ conftest.$ac_objext conftest.beam conftest.$ac_ext fi fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $sv_cv_fault_irix" >&5 $as_echo "$sv_cv_fault_irix" >&6; } { $as_echo "$as_me:${as_lineno-$LINENO}: checking whether a fault handler according to HP-UX HPPA works" >&5 $as_echo_n "checking whether a fault handler according to HP-UX HPPA works... " >&6; } if ${sv_cv_fault_hpux_hppa+:} false; then : $as_echo_n "(cached) " >&6 else if test "$cross_compiling" = yes; then : case "$host" in hppa*-*-hpux11*) sv_cv_fault_hpux_hppa=yes ;; *) cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ #include #define USE_64BIT_REGS(mc) \ (((mc).ss_flags & SS_WIDEREGS) && ((mc).ss_flags & SS_NARROWISINVALID)) #define GET_CR21(mc) \ (USE_64BIT_REGS(mc) ? (mc).ss_wide.ss_64.ss_cr21 : (mc).ss_narrow.ss_cr21) void sigsegv_handler (int sig, int code, struct sigcontext *scp) { void *fault_address = (void *) (GET_CR21 (scp->sc_sl.sl_ss)); } int main () { struct sigaction action; ; return 0; } _ACEOF if ac_fn_c_try_link "$LINENO"; then : sv_cv_fault_hpux_hppa="guessing no" else sv_cv_fault_hpux_hppa=no fi rm -f core conftest.err conftest.$ac_objext \ conftest$ac_exeext conftest.$ac_ext ;; esac else cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ #include #include #if HAVE_SYS_SIGNAL_H # include #endif #define USE_64BIT_REGS(mc) \ (((mc).ss_flags & SS_WIDEREGS) && ((mc).ss_flags & SS_NARROWISINVALID)) #define GET_CR21(mc) \ (USE_64BIT_REGS(mc) ? (mc).ss_wide.ss_64.ss_cr21 : (mc).ss_narrow.ss_cr21) #include #include #if HAVE_MMAP_DEVZERO # include # ifndef MAP_FILE # define MAP_FILE 0 # endif #endif #ifndef PROT_NONE # define PROT_NONE 0 #endif #if HAVE_MMAP_ANON # define zero_fd -1 # define map_flags MAP_ANON | MAP_PRIVATE #elif HAVE_MMAP_ANONYMOUS # define zero_fd -1 # define map_flags MAP_ANONYMOUS | MAP_PRIVATE #elif HAVE_MMAP_DEVZERO static int zero_fd; # define map_flags MAP_FILE | MAP_PRIVATE #endif unsigned long page; int handler_called = 0; void sigsegv_handler (int sig, int code, struct sigcontext *scp) { void *fault_address = (void *) (GET_CR21 (scp->sc_sl.sl_ss)); handler_called++; if (handler_called == 10) exit (4); if (fault_address != (void*)(page + 0x678)) exit (3); if (mprotect ((void *) page, 0x10000, PROT_READ | PROT_WRITE) < 0) exit (2); } void crasher (unsigned long p) { *(int *) (p + 0x678) = 42; } int main () { void *p; struct sigaction action; /* Preparations. */ #if !HAVE_MMAP_ANON && !HAVE_MMAP_ANONYMOUS && HAVE_MMAP_DEVZERO zero_fd = open ("/dev/zero", O_RDONLY, 0644); #endif /* Setup some mmaped memory. */ #ifdef __hpux /* HP-UX 10 mmap() often fails when given a hint. So give the OS complete freedom about the address range. */ p = mmap ((void *) 0, 0x10000, PROT_READ | PROT_WRITE, map_flags, zero_fd, 0); #else p = mmap ((void *) 0x12340000, 0x10000, PROT_READ | PROT_WRITE, map_flags, zero_fd, 0); #endif if (p == (void *)(-1)) exit (2); page = (unsigned long) p; /* Make it read-only. */ if (mprotect ((void *) page, 0x10000, PROT_READ) < 0) exit (2); /* Install the SIGSEGV handler. */ sigemptyset(&action.sa_mask); action.sa_handler = (void (*) (int)) &sigsegv_handler; action.sa_flags = 0; sigaction (SIGSEGV, &action, (struct sigaction *) NULL); sigaction (SIGBUS, &action, (struct sigaction *) NULL); /* The first write access should invoke the handler and then complete. */ crasher (page); /* The second write access should not invoke the handler. */ crasher (page); /* Check that the handler was called only once. */ if (handler_called != 1) exit (1); /* Test passed! */ return 0; } _ACEOF if ac_fn_c_try_run "$LINENO"; then : sv_cv_fault_hpux_hppa=yes else sv_cv_fault_hpux_hppa=no fi rm -f core *.core core.conftest.* gmon.out bb.out conftest$ac_exeext \ conftest.$ac_objext conftest.beam conftest.$ac_ext fi fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $sv_cv_fault_hpux_hppa" >&5 $as_echo "$sv_cv_fault_hpux_hppa" >&6; } { $as_echo "$as_me:${as_lineno-$LINENO}: checking whether a fault handler according to OSF/1 Alpha works" >&5 $as_echo_n "checking whether a fault handler according to OSF/1 Alpha works... " >&6; } if ${sv_cv_fault_osf_alpha+:} false; then : $as_echo_n "(cached) " >&6 else if test "$cross_compiling" = yes; then : case "$host" in alpha*-*-osf[4-9]* | alpha*-*-linux2.[4-9]*) sv_cv_fault_osf_alpha=yes ;; *) cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ #include void sigsegv_handler (int sig, int code, struct sigcontext *scp) { void *fault_address = (void *) (scp->sc_traparg_a0); } int main () { struct sigaction action; ; return 0; } _ACEOF if ac_fn_c_try_link "$LINENO"; then : sv_cv_fault_osf_alpha="guessing no" else sv_cv_fault_osf_alpha=no fi rm -f core conftest.err conftest.$ac_objext \ conftest$ac_exeext conftest.$ac_ext ;; esac else cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ #include #include #if HAVE_SYS_SIGNAL_H # include #endif #include #include #if HAVE_MMAP_DEVZERO # include # ifndef MAP_FILE # define MAP_FILE 0 # endif #endif #ifndef PROT_NONE # define PROT_NONE 0 #endif #if HAVE_MMAP_ANON # define zero_fd -1 # define map_flags MAP_ANON | MAP_PRIVATE #elif HAVE_MMAP_ANONYMOUS # define zero_fd -1 # define map_flags MAP_ANONYMOUS | MAP_PRIVATE #elif HAVE_MMAP_DEVZERO static int zero_fd; # define map_flags MAP_FILE | MAP_PRIVATE #endif unsigned long page; int handler_called = 0; void sigsegv_handler (int sig, int code, struct sigcontext *scp) { void *fault_address = (void *) (scp->sc_traparg_a0); handler_called++; if (handler_called == 10) exit (4); if (fault_address != (void*)(page + 0x678)) exit (3); if (mprotect ((void *) page, 0x10000, PROT_READ | PROT_WRITE) < 0) exit (2); } void crasher (unsigned long p) { *(int *) (p + 0x678) = 42; } int main () { void *p; struct sigaction action; /* Preparations. */ #if !HAVE_MMAP_ANON && !HAVE_MMAP_ANONYMOUS && HAVE_MMAP_DEVZERO zero_fd = open ("/dev/zero", O_RDONLY, 0644); #endif /* Setup some mmaped memory. */ #ifdef __hpux /* HP-UX 10 mmap() often fails when given a hint. So give the OS complete freedom about the address range. */ p = mmap ((void *) 0, 0x10000, PROT_READ | PROT_WRITE, map_flags, zero_fd, 0); #else p = mmap ((void *) 0x12340000, 0x10000, PROT_READ | PROT_WRITE, map_flags, zero_fd, 0); #endif if (p == (void *)(-1)) exit (2); page = (unsigned long) p; /* Make it read-only. */ if (mprotect ((void *) page, 0x10000, PROT_READ) < 0) exit (2); /* Install the SIGSEGV handler. */ sigemptyset(&action.sa_mask); action.sa_handler = (void (*) (int)) &sigsegv_handler; action.sa_flags = 0; sigaction (SIGSEGV, &action, (struct sigaction *) NULL); sigaction (SIGBUS, &action, (struct sigaction *) NULL); /* The first write access should invoke the handler and then complete. */ crasher (page); /* The second write access should not invoke the handler. */ crasher (page); /* Check that the handler was called only once. */ if (handler_called != 1) exit (1); /* Test passed! */ return 0; } _ACEOF if ac_fn_c_try_run "$LINENO"; then : sv_cv_fault_osf_alpha=yes else sv_cv_fault_osf_alpha=no fi rm -f core *.core core.conftest.* gmon.out bb.out conftest$ac_exeext \ conftest.$ac_objext conftest.beam conftest.$ac_ext fi fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $sv_cv_fault_osf_alpha" >&5 $as_echo "$sv_cv_fault_osf_alpha" >&6; } { $as_echo "$as_me:${as_lineno-$LINENO}: checking whether a fault handler according to NetBSD Alpha works" >&5 $as_echo_n "checking whether a fault handler according to NetBSD Alpha works... " >&6; } if ${sv_cv_fault_netbsd_alpha+:} false; then : $as_echo_n "(cached) " >&6 else if test "$cross_compiling" = yes; then : case "$host" in alpha*-*-osf[4-9]* | alpha-*-*bsd*) sv_cv_fault_netbsd_alpha=yes ;; *) cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ #include #include "$srcdir/src/fault-netbsd-alpha.c" void sigsegv_handler (int sig, int code, struct sigcontext *scp) { void *fault_address = (void *) (get_fault_addr (scp)); } int main () { struct sigaction action; ; return 0; } _ACEOF if ac_fn_c_try_link "$LINENO"; then : sv_cv_fault_netbsd_alpha="guessing no" else sv_cv_fault_netbsd_alpha=no fi rm -f core conftest.err conftest.$ac_objext \ conftest$ac_exeext conftest.$ac_ext ;; esac else cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ #include #include #if HAVE_SYS_SIGNAL_H # include #endif #include "$srcdir/src/fault-netbsd-alpha.c" #include #include #if HAVE_MMAP_DEVZERO # include # ifndef MAP_FILE # define MAP_FILE 0 # endif #endif #ifndef PROT_NONE # define PROT_NONE 0 #endif #if HAVE_MMAP_ANON # define zero_fd -1 # define map_flags MAP_ANON | MAP_PRIVATE #elif HAVE_MMAP_ANONYMOUS # define zero_fd -1 # define map_flags MAP_ANONYMOUS | MAP_PRIVATE #elif HAVE_MMAP_DEVZERO static int zero_fd; # define map_flags MAP_FILE | MAP_PRIVATE #endif unsigned long page; int handler_called = 0; void sigsegv_handler (int sig, int code, struct sigcontext *scp) { void *fault_address = (void *) (get_fault_addr (scp)); handler_called++; if (handler_called == 10) exit (4); if (fault_address != (void*)(page + 0x678)) exit (3); if (mprotect ((void *) page, 0x10000, PROT_READ | PROT_WRITE) < 0) exit (2); } void crasher (unsigned long p) { *(int *) (p + 0x678) = 42; } int main () { void *p; struct sigaction action; /* Preparations. */ #if !HAVE_MMAP_ANON && !HAVE_MMAP_ANONYMOUS && HAVE_MMAP_DEVZERO zero_fd = open ("/dev/zero", O_RDONLY, 0644); #endif /* Setup some mmaped memory. */ #ifdef __hpux /* HP-UX 10 mmap() often fails when given a hint. So give the OS complete freedom about the address range. */ p = mmap ((void *) 0, 0x10000, PROT_READ | PROT_WRITE, map_flags, zero_fd, 0); #else p = mmap ((void *) 0x12340000, 0x10000, PROT_READ | PROT_WRITE, map_flags, zero_fd, 0); #endif if (p == (void *)(-1)) exit (2); page = (unsigned long) p; /* Make it read-only. */ if (mprotect ((void *) page, 0x10000, PROT_READ) < 0) exit (2); /* Install the SIGSEGV handler. */ sigemptyset(&action.sa_mask); action.sa_handler = (void (*) (int)) &sigsegv_handler; action.sa_flags = 0; sigaction (SIGSEGV, &action, (struct sigaction *) NULL); sigaction (SIGBUS, &action, (struct sigaction *) NULL); /* The first write access should invoke the handler and then complete. */ crasher (page); /* The second write access should not invoke the handler. */ crasher (page); /* Check that the handler was called only once. */ if (handler_called != 1) exit (1); /* Test passed! */ return 0; } _ACEOF if ac_fn_c_try_run "$LINENO"; then : sv_cv_fault_netbsd_alpha=yes else sv_cv_fault_netbsd_alpha=no fi rm -f core *.core core.conftest.* gmon.out bb.out conftest$ac_exeext \ conftest.$ac_objext conftest.beam conftest.$ac_ext fi fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $sv_cv_fault_netbsd_alpha" >&5 $as_echo "$sv_cv_fault_netbsd_alpha" >&6; } { $as_echo "$as_me:${as_lineno-$LINENO}: checking whether a fault handler according to AIX works" >&5 $as_echo_n "checking whether a fault handler according to AIX works... " >&6; } if ${sv_cv_fault_aix+:} false; then : $as_echo_n "(cached) " >&6 else if test "$cross_compiling" = yes; then : case "$host" in *-*-aix[34]*) sv_cv_fault_aix=yes ;; *) cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ #include void sigsegv_handler (int sig, int code, struct sigcontext *scp) { void *fault_address = (void *) (scp->sc_jmpbuf.jmp_context.o_vaddr); } int main () { struct sigaction action; ; return 0; } _ACEOF if ac_fn_c_try_link "$LINENO"; then : sv_cv_fault_aix="guessing no" else sv_cv_fault_aix=no fi rm -f core conftest.err conftest.$ac_objext \ conftest$ac_exeext conftest.$ac_ext ;; esac else cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ #include #include #if HAVE_SYS_SIGNAL_H # include #endif #include #include #if HAVE_MMAP_DEVZERO # include # ifndef MAP_FILE # define MAP_FILE 0 # endif #endif #ifndef PROT_NONE # define PROT_NONE 0 #endif #if HAVE_MMAP_ANON # define zero_fd -1 # define map_flags MAP_ANON | MAP_PRIVATE #elif HAVE_MMAP_ANONYMOUS # define zero_fd -1 # define map_flags MAP_ANONYMOUS | MAP_PRIVATE #elif HAVE_MMAP_DEVZERO static int zero_fd; # define map_flags MAP_FILE | MAP_PRIVATE #endif unsigned long page; int handler_called = 0; void sigsegv_handler (int sig, int code, struct sigcontext *scp) { void *fault_address = (void *) (scp->sc_jmpbuf.jmp_context.o_vaddr); handler_called++; if (handler_called == 10) exit (4); if (fault_address != (void*)(page + 0x678)) exit (3); if (mprotect ((void *) page, 0x10000, PROT_READ | PROT_WRITE) < 0) exit (2); } void crasher (unsigned long p) { *(int *) (p + 0x678) = 42; } int main () { void *p; struct sigaction action; /* Preparations. */ #if !HAVE_MMAP_ANON && !HAVE_MMAP_ANONYMOUS && HAVE_MMAP_DEVZERO zero_fd = open ("/dev/zero", O_RDONLY, 0644); #endif /* Setup some mmaped memory. */ #ifdef __hpux /* HP-UX 10 mmap() often fails when given a hint. So give the OS complete freedom about the address range. */ p = mmap ((void *) 0, 0x10000, PROT_READ | PROT_WRITE, map_flags, zero_fd, 0); #else p = mmap ((void *) 0x12340000, 0x10000, PROT_READ | PROT_WRITE, map_flags, zero_fd, 0); #endif if (p == (void *)(-1)) exit (2); page = (unsigned long) p; /* Make it read-only. */ if (mprotect ((void *) page, 0x10000, PROT_READ) < 0) exit (2); /* Install the SIGSEGV handler. */ sigemptyset(&action.sa_mask); action.sa_handler = (void (*) (int)) &sigsegv_handler; action.sa_flags = 0; sigaction (SIGSEGV, &action, (struct sigaction *) NULL); sigaction (SIGBUS, &action, (struct sigaction *) NULL); /* The first write access should invoke the handler and then complete. */ crasher (page); /* The second write access should not invoke the handler. */ crasher (page); /* Check that the handler was called only once. */ if (handler_called != 1) exit (1); /* Test passed! */ return 0; } _ACEOF if ac_fn_c_try_run "$LINENO"; then : sv_cv_fault_aix=yes else sv_cv_fault_aix=no fi rm -f core *.core core.conftest.* gmon.out bb.out conftest$ac_exeext \ conftest.$ac_objext conftest.beam conftest.$ac_ext fi fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $sv_cv_fault_aix" >&5 $as_echo "$sv_cv_fault_aix" >&6; } { $as_echo "$as_me:${as_lineno-$LINENO}: checking whether a fault handler according to MacOSX/Darwin7 PowerPC works" >&5 $as_echo_n "checking whether a fault handler according to MacOSX/Darwin7 PowerPC works... " >&6; } if ${sv_cv_fault_macosdarwin7_ppc+:} false; then : $as_echo_n "(cached) " >&6 else if test "$cross_compiling" = yes; then : case "$host" in powerpc-*-darwin7*) sv_cv_fault_macosdarwin7_ppc=yes ;; *) cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ #include #include "$srcdir/src/fault-macosdarwin7-powerpc.c" void sigsegv_handler (int sig, siginfo_t *sip, ucontext_t *ucp) { void *fault_address = (void *) (get_fault_addr (sip, ucp)); } int main () { struct sigaction action; action.sa_sigaction = &sigsegv_handler; action.sa_flags = SA_SIGINFO; ; return 0; } _ACEOF if ac_fn_c_try_link "$LINENO"; then : sv_cv_fault_macosdarwin7_ppc="guessing no" else sv_cv_fault_macosdarwin7_ppc=no fi rm -f core conftest.err conftest.$ac_objext \ conftest$ac_exeext conftest.$ac_ext ;; esac else cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ #include #include #if HAVE_SYS_SIGNAL_H # include #endif #include "$srcdir/src/fault-macosdarwin7-powerpc.c" #include #include #if HAVE_MMAP_DEVZERO # include # ifndef MAP_FILE # define MAP_FILE 0 # endif #endif #ifndef PROT_NONE # define PROT_NONE 0 #endif #if HAVE_MMAP_ANON # define zero_fd -1 # define map_flags MAP_ANON | MAP_PRIVATE #elif HAVE_MMAP_ANONYMOUS # define zero_fd -1 # define map_flags MAP_ANONYMOUS | MAP_PRIVATE #elif HAVE_MMAP_DEVZERO static int zero_fd; # define map_flags MAP_FILE | MAP_PRIVATE #endif unsigned long page; int handler_called = 0; void sigsegv_handler (int sig, siginfo_t *sip, ucontext_t *ucp) { void *fault_address = (void *) (get_fault_addr (sip, ucp)); handler_called++; if (handler_called == 10) exit (4); if (fault_address != (void*)(page + 0x678)) exit (3); if (mprotect ((void *) page, 0x10000, PROT_READ | PROT_WRITE) < 0) exit (2); } void crasher (unsigned long p) { *(int *) (p + 0x678) = 42; } int main () { void *p; struct sigaction action; /* Preparations. */ #if !HAVE_MMAP_ANON && !HAVE_MMAP_ANONYMOUS && HAVE_MMAP_DEVZERO zero_fd = open ("/dev/zero", O_RDONLY, 0644); #endif /* Setup some mmaped memory. */ #ifdef __hpux /* HP-UX 10 mmap() often fails when given a hint. So give the OS complete freedom about the address range. */ p = mmap ((void *) 0, 0x10000, PROT_READ | PROT_WRITE, map_flags, zero_fd, 0); #else p = mmap ((void *) 0x12340000, 0x10000, PROT_READ | PROT_WRITE, map_flags, zero_fd, 0); #endif if (p == (void *)(-1)) exit (2); page = (unsigned long) p; /* Make it read-only. */ if (mprotect ((void *) page, 0x10000, PROT_READ) < 0) exit (2); /* Install the SIGSEGV handler. */ sigemptyset(&action.sa_mask); action.sa_sigaction = &sigsegv_handler; action.sa_flags = SA_SIGINFO; sigaction (SIGSEGV, &action, (struct sigaction *) NULL); sigaction (SIGBUS, &action, (struct sigaction *) NULL); /* The first write access should invoke the handler and then complete. */ crasher (page); /* The second write access should not invoke the handler. */ crasher (page); /* Check that the handler was called only once. */ if (handler_called != 1) exit (1); /* Test passed! */ return 0; } _ACEOF if ac_fn_c_try_run "$LINENO"; then : sv_cv_fault_macosdarwin7_ppc=yes else sv_cv_fault_macosdarwin7_ppc=no fi rm -f core *.core core.conftest.* gmon.out bb.out conftest$ac_exeext \ conftest.$ac_objext conftest.beam conftest.$ac_ext fi fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $sv_cv_fault_macosdarwin7_ppc" >&5 $as_echo "$sv_cv_fault_macosdarwin7_ppc" >&6; } if test "$sv_cv_fault_macosdarwin7_ppc" != yes; then { $as_echo "$as_me:${as_lineno-$LINENO}: checking whether a fault handler according to MacOSX/Darwin5 PowerPC works" >&5 $as_echo_n "checking whether a fault handler according to MacOSX/Darwin5 PowerPC works... " >&6; } if ${sv_cv_fault_macosdarwin5_ppc+:} false; then : $as_echo_n "(cached) " >&6 else if test "$cross_compiling" = yes; then : case "$host" in powerpc-*-darwin5*) sv_cv_fault_macosdarwin5_ppc=yes ;; *) cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ #include #include "$srcdir/src/fault-macosdarwin5-powerpc.c" void sigsegv_handler (int sig, int code, struct sigcontext *scp) { void *fault_address = (void *) (get_fault_addr (scp)); } int main () { struct sigaction action; ; return 0; } _ACEOF if ac_fn_c_try_link "$LINENO"; then : sv_cv_fault_macosdarwin5_ppc="guessing no" else sv_cv_fault_macosdarwin5_ppc=no fi rm -f core conftest.err conftest.$ac_objext \ conftest$ac_exeext conftest.$ac_ext ;; esac else cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ #include #include #if HAVE_SYS_SIGNAL_H # include #endif #include "$srcdir/src/fault-macosdarwin5-powerpc.c" #include #include #if HAVE_MMAP_DEVZERO # include # ifndef MAP_FILE # define MAP_FILE 0 # endif #endif #ifndef PROT_NONE # define PROT_NONE 0 #endif #if HAVE_MMAP_ANON # define zero_fd -1 # define map_flags MAP_ANON | MAP_PRIVATE #elif HAVE_MMAP_ANONYMOUS # define zero_fd -1 # define map_flags MAP_ANONYMOUS | MAP_PRIVATE #elif HAVE_MMAP_DEVZERO static int zero_fd; # define map_flags MAP_FILE | MAP_PRIVATE #endif unsigned long page; int handler_called = 0; void sigsegv_handler (int sig, int code, struct sigcontext *scp) { void *fault_address = (void *) (get_fault_addr (scp)); handler_called++; if (handler_called == 10) exit (4); if (fault_address != (void*)(page + 0x678)) exit (3); if (mprotect ((void *) page, 0x10000, PROT_READ | PROT_WRITE) < 0) exit (2); } void crasher (unsigned long p) { *(int *) (p + 0x678) = 42; } int main () { void *p; struct sigaction action; /* Preparations. */ #if !HAVE_MMAP_ANON && !HAVE_MMAP_ANONYMOUS && HAVE_MMAP_DEVZERO zero_fd = open ("/dev/zero", O_RDONLY, 0644); #endif /* Setup some mmaped memory. */ #ifdef __hpux /* HP-UX 10 mmap() often fails when given a hint. So give the OS complete freedom about the address range. */ p = mmap ((void *) 0, 0x10000, PROT_READ | PROT_WRITE, map_flags, zero_fd, 0); #else p = mmap ((void *) 0x12340000, 0x10000, PROT_READ | PROT_WRITE, map_flags, zero_fd, 0); #endif if (p == (void *)(-1)) exit (2); page = (unsigned long) p; /* Make it read-only. */ if (mprotect ((void *) page, 0x10000, PROT_READ) < 0) exit (2); /* Install the SIGSEGV handler. */ sigemptyset(&action.sa_mask); action.sa_handler = (void (*) (int)) &sigsegv_handler; action.sa_flags = 0; sigaction (SIGSEGV, &action, (struct sigaction *) NULL); sigaction (SIGBUS, &action, (struct sigaction *) NULL); /* The first write access should invoke the handler and then complete. */ crasher (page); /* The second write access should not invoke the handler. */ crasher (page); /* Check that the handler was called only once. */ if (handler_called != 1) exit (1); /* Test passed! */ return 0; } _ACEOF if ac_fn_c_try_run "$LINENO"; then : sv_cv_fault_macosdarwin5_ppc=yes else sv_cv_fault_macosdarwin5_ppc=no fi rm -f core *.core core.conftest.* gmon.out bb.out conftest$ac_exeext \ conftest.$ac_objext conftest.beam conftest.$ac_ext fi fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $sv_cv_fault_macosdarwin5_ppc" >&5 $as_echo "$sv_cv_fault_macosdarwin5_ppc" >&6; } fi { $as_echo "$as_me:${as_lineno-$LINENO}: checking whether a fault handler according to Hurd works" >&5 $as_echo_n "checking whether a fault handler according to Hurd works... " >&6; } if ${sv_cv_fault_hurd+:} false; then : $as_echo_n "(cached) " >&6 else if test "$cross_compiling" = yes; then : case "$host" in *) cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ #include void sigsegv_handler (int sig, int code, struct sigcontext *scp) { void *fault_address = (void *) (code); } int main () { struct sigaction action; ; return 0; } _ACEOF if ac_fn_c_try_link "$LINENO"; then : sv_cv_fault_hurd="guessing no" else sv_cv_fault_hurd=no fi rm -f core conftest.err conftest.$ac_objext \ conftest$ac_exeext conftest.$ac_ext ;; esac else cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ #include #include #if HAVE_SYS_SIGNAL_H # include #endif #include #include #if HAVE_MMAP_DEVZERO # include # ifndef MAP_FILE # define MAP_FILE 0 # endif #endif #ifndef PROT_NONE # define PROT_NONE 0 #endif #if HAVE_MMAP_ANON # define zero_fd -1 # define map_flags MAP_ANON | MAP_PRIVATE #elif HAVE_MMAP_ANONYMOUS # define zero_fd -1 # define map_flags MAP_ANONYMOUS | MAP_PRIVATE #elif HAVE_MMAP_DEVZERO static int zero_fd; # define map_flags MAP_FILE | MAP_PRIVATE #endif unsigned long page; int handler_called = 0; void sigsegv_handler (int sig, int code, struct sigcontext *scp) { void *fault_address = (void *) (code); handler_called++; if (handler_called == 10) exit (4); if (fault_address != (void*)(page + 0x678)) exit (3); if (mprotect ((void *) page, 0x10000, PROT_READ | PROT_WRITE) < 0) exit (2); } void crasher (unsigned long p) { *(int *) (p + 0x678) = 42; } int main () { void *p; struct sigaction action; /* Preparations. */ #if !HAVE_MMAP_ANON && !HAVE_MMAP_ANONYMOUS && HAVE_MMAP_DEVZERO zero_fd = open ("/dev/zero", O_RDONLY, 0644); #endif /* Setup some mmaped memory. */ #ifdef __hpux /* HP-UX 10 mmap() often fails when given a hint. So give the OS complete freedom about the address range. */ p = mmap ((void *) 0, 0x10000, PROT_READ | PROT_WRITE, map_flags, zero_fd, 0); #else p = mmap ((void *) 0x12340000, 0x10000, PROT_READ | PROT_WRITE, map_flags, zero_fd, 0); #endif if (p == (void *)(-1)) exit (2); page = (unsigned long) p; /* Make it read-only. */ if (mprotect ((void *) page, 0x10000, PROT_READ) < 0) exit (2); /* Install the SIGSEGV handler. */ sigemptyset(&action.sa_mask); action.sa_handler = (void (*) (int)) &sigsegv_handler; action.sa_flags = 0; sigaction (SIGSEGV, &action, (struct sigaction *) NULL); sigaction (SIGBUS, &action, (struct sigaction *) NULL); /* The first write access should invoke the handler and then complete. */ crasher (page); /* The second write access should not invoke the handler. */ crasher (page); /* Check that the handler was called only once. */ if (handler_called != 1) exit (1); /* Test passed! */ return 0; } _ACEOF if ac_fn_c_try_run "$LINENO"; then : sv_cv_fault_hurd=yes else sv_cv_fault_hurd=no fi rm -f core *.core core.conftest.* gmon.out bb.out conftest$ac_exeext \ conftest.$ac_objext conftest.beam conftest.$ac_ext fi fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $sv_cv_fault_hurd" >&5 $as_echo "$sv_cv_fault_hurd" >&6; } # End of MacOS X special casing. ;; esac CFG_HANDLER= CFG_FAULT= CFG_MACHFAULT= FAULT_CONTEXT=void FAULT_CONTEXT_INCLUDE= FAULT_CONTEXT_INCLUDE2= if test -z "$CFG_FAULT" && test "$sv_cv_fault_aix" = yes; then case "$host_cpu" in powerpc* | rs6000) CFG_FAULT=fault-aix3-powerpc.h ;; *) CFG_FAULT=fault-aix3.h ;; esac FAULT_CONTEXT='struct sigcontext' fi if test -z "$CFG_FAULT" && test "$sv_cv_fault_irix" = yes; then case "$host_cpu" in mips*) CFG_FAULT=fault-irix-mips.h ;; *) CFG_FAULT=fault-irix.h ;; esac FAULT_CONTEXT='struct sigcontext' fi if test -z "$CFG_FAULT" && test "$sv_cv_fault_hpux_hppa" = yes; then case "$host_cpu" in hppa* | parisc*) CFG_FAULT=fault-hpux-hppa.h ;; *) CFG_FAULT=fault-hpux.h ;; esac FAULT_CONTEXT='struct sigcontext' fi if test -z "$CFG_FAULT" && test "$sv_cv_fault_osf_alpha" = yes; then case "$host_cpu" in alpha*) CFG_FAULT=fault-osf-alpha.h ;; *) CFG_FAULT=fault-osf.h ;; esac FAULT_CONTEXT='struct sigcontext' fi if test -z "$CFG_FAULT" && test "$sv_cv_fault_netbsd_alpha" = yes; then case "$host_cpu" in alpha*) CFG_FAULT=fault-netbsd-alpha.h ;; esac FAULT_CONTEXT='struct sigcontext' fi if test -z "$CFG_FAULT" && test "$sv_cv_fault_linux_i386" = yes; then case "$host_cpu" in i?86 | x86_64) CFG_FAULT=fault-linux-i386.h ;; esac FAULT_CONTEXT='struct sigcontext' fi if test -z "$CFG_FAULT" && test "$sv_cv_fault_linux_i386_old" = yes; then case "$host_cpu" in i?86 | x86_64) CFG_FAULT=fault-linux-i386-old.h ;; esac FAULT_CONTEXT='struct sigcontext' fi if test -z "$CFG_FAULT" && test "$sv_cv_fault_linux_powerpc" = yes; then case "$host_cpu" in powerpc* | rs6000) CFG_FAULT=fault-linux-powerpc.h ;; esac FAULT_CONTEXT='struct sigcontext' fi if test -z "$CFG_FAULT" && test "$sv_cv_fault_linux_hppa" = yes; then case "$host_cpu" in hppa* | parisc*) CFG_FAULT=fault-linux-hppa.h ;; esac fi if test -z "$CFG_FAULT" && test "$sv_cv_fault_hurd" = yes; then case "$host_os" in netbsd*) # A false positive. ;; *) CFG_FAULT=fault-hurd.h FAULT_CONTEXT='struct sigcontext' ;; esac fi if test -z "$CFG_FAULT" && test "$sv_cv_fault_bsd" = yes; then case "$host_os" in freebsd* | dragonfly* | kfreebsd*) case "$host_cpu" in i?86 | x86_64) CFG_FAULT=fault-freebsd-i386.h FAULT_CONTEXT='struct sigcontext' ;; *) CFG_FAULT=fault-bsd.h FAULT_CONTEXT='void' ;; esac ;; *) CFG_FAULT=fault-bsd.h FAULT_CONTEXT='void' ;; esac fi if test -z "$CFG_FAULT" && test "$sv_cv_fault_posix" = yes; then case "$host_os" in openbsd*) case "$host_cpu" in i?86 | x86_64) CFG_FAULT=fault-openbsd-i386.h ;; *) CFG_FAULT=fault-openbsd.h ;; esac FAULT_CONTEXT='struct sigcontext' ;; linux*) case "$host_cpu" in ia64) CFG_FAULT=fault-linux-ia64.h FAULT_CONTEXT='struct sigcontext' ;; esac ;; esac if test -z "$CFG_FAULT"; then case "$host_os" in solaris*) case "$host_cpu" in i?86 | x86_64) CFG_FAULT=fault-solaris-i386.h ;; sparc*) CFG_FAULT=fault-solaris-sparc.h ;; *) CFG_FAULT=fault-solaris.h ;; esac ;; aix*) case "$host_cpu" in powerpc* | rs6000) CFG_FAULT=fault-aix5-powerpc.h ;; *) CFG_FAULT=fault-aix5.h ;; esac ;; netbsd*) CFG_FAULT=fault-netbsd.h ;; *) CFG_FAULT=fault-posix.h ;; esac FAULT_CONTEXT='ucontext_t' FAULT_CONTEXT_INCLUDE='#include ' fi fi if test -z "$CFG_FAULT"; then case "$host_os" in macos* | darwin[6-9]* | darwin[1-9][0-9]*) case "$host_cpu" in powerpc* | rs6000) CFG_MACHFAULT=machfault-macos-powerpc.h FAULT_CONTEXT='ppc_thread_state_t' ;; i?86 | x86_64) CFG_MACHFAULT=machfault-macos-i386.h FAULT_CONTEXT='i386_thread_state_t' ;; esac if test -n "$CFG_MACHFAULT"; then CFG_HANDLER=handler-macos.c FAULT_CONTEXT_INCLUDE='#include ' FAULT_CONTEXT_INCLUDE2='#include ' CFG_FAULT=fault-macos.h # nonexistent, just a dummy fi ;; esac fi if test -z "$CFG_FAULT" && test "$sv_cv_fault_linux_m68k" = yes; then case "$host_cpu" in m68*) CFG_FAULT=fault-linux-m68k.h FAULT_CONTEXT='struct sigcontext' ;; esac fi if test -z "$CFG_FAULT" && test "$sv_cv_fault_macosdarwin7_ppc" = yes; then case "$host_cpu" in powerpc* | rs6000) CFG_FAULT=fault-macosdarwin7-powerpc.h FAULT_CONTEXT='ucontext_t' FAULT_CONTEXT_INCLUDE='#include ' FAULT_CONTEXT_INCLUDE2='#include ' ;; esac fi if test -z "$CFG_FAULT" && test "$sv_cv_fault_macosdarwin5_ppc" = yes; then case "$host_cpu" in powerpc* | rs6000) CFG_FAULT=fault-macosdarwin5-powerpc.h FAULT_CONTEXT='struct sigcontext' ;; esac fi if test -z "$CFG_FAULT"; then case "$host_os" in mingw* | cygwin*) FAULT_CONTEXT='CONTEXT' FAULT_CONTEXT_INCLUDE='#include ' CFG_FAULT=fault-win32.h # nonexistent, just a dummy ;; esac fi if test -n "$CFG_FAULT"; then sv_cv_have_sigsegv_recovery=yes else sv_cv_have_sigsegv_recovery=no case "$host_os" in linux*) case "$host_cpu" in alpha*) CFG_FAULT=fault-linux-alpha.h FAULT_CONTEXT='struct sigcontext' ;; arm* | strongarm* | xscale*) CFG_FAULT=fault-linux-arm.h FAULT_CONTEXT='struct sigcontext' ;; cris) CFG_FAULT=fault-linux-cris.h FAULT_CONTEXT='struct sigcontext' ;; mips*) CFG_FAULT=fault-linux-mips.h FAULT_CONTEXT='struct sigcontext' ;; s390*) CFG_FAULT=fault-linux-s390.h FAULT_CONTEXT='struct sigcontext' ;; sh*) CFG_FAULT=fault-linux-sh.h FAULT_CONTEXT='struct sigcontext' ;; sparc*) CFG_FAULT=fault-linux-sparc.h FAULT_CONTEXT='struct sigcontext' ;; x86_64) CFG_FAULT=fault-linux-x86_64.h FAULT_CONTEXT='struct sigcontext' ;; esac ;; beos*) case "$host_cpu" in i?86 | x86_64) CFG_FAULT=fault-beos-i386.h ;; *) CFG_FAULT=fault-beos.h ;; esac FAULT_CONTEXT='struct vregs' ;; macos* | darwin*) case "$host_cpu" in i?86 | x86_64) CFG_FAULT=fault-macos-i386.h ;; esac FAULT_CONTEXT='struct sigcontext' ;; esac fi { $as_echo "$as_me:${as_lineno-$LINENO}: checking for the fault handler specifics" >&5 $as_echo_n "checking for the fault handler specifics... " >&6; } if test -n "$CFG_FAULT"; then sv_cv_fault_include=$CFG_FAULT else if test -n "$CFG_MACHFAULT"; then sv_cv_fault_include=$CFG_MACHFAULT else sv_cv_fault_include=none fi fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $sv_cv_fault_include" >&5 $as_echo "$sv_cv_fault_include" >&6; } if test -z "$CFG_FAULT"; then CFG_FAULT=fault-none.h fi cat >>confdefs.h <<_ACEOF #define CFG_FAULT "$CFG_FAULT" _ACEOF if test -z "$CFG_MACHFAULT"; then CFG_MACHFAULT=fault-none.h fi cat >>confdefs.h <<_ACEOF #define CFG_MACHFAULT "$CFG_MACHFAULT" _ACEOF { $as_echo "$as_me:${as_lineno-$LINENO}: checking if the system supports catching SIGSEGV" >&5 $as_echo_n "checking if the system supports catching SIGSEGV... " >&6; } { $as_echo "$as_me:${as_lineno-$LINENO}: result: $sv_cv_have_sigsegv_recovery" >&5 $as_echo "$sv_cv_have_sigsegv_recovery" >&6; } if test $sv_cv_have_sigsegv_recovery != no; then HAVE_SIGSEGV_RECOVERY=1 else HAVE_SIGSEGV_RECOVERY=0 fi { $as_echo "$as_me:${as_lineno-$LINENO}: checking for stack direction" >&5 $as_echo_n "checking for stack direction... " >&6; } if ${sv_cv_stack_direction_msg+:} false; then : $as_echo_n "(cached) " >&6 else case "$host_cpu" in a29k | \ alpha* | \ arc | \ arm* | strongarm* | xscale* | \ avr | \ c1 | c2 | c32 | c34 | c38 | \ clipper | \ cris | \ d30v | \ elxsi | \ fr30 | \ h8300 | \ i?86 | x86_64 | \ i860 | \ ia64 | \ m32r | \ m68* | \ m88k | \ mcore | \ mips* | \ mmix | \ mn10200 | \ mn10300 | \ ns32k | \ pdp11 | \ pj* | \ powerpc* | rs6000 | \ romp | \ s390* | \ sh* | \ sparc* | \ v850 | \ vax | \ xtensa) sv_cv_stack_direction=-1 ;; c4x | \ dsp16xx | \ i960 | \ hppa* | parisc* | \ stormy16 | \ we32k) sv_cv_stack_direction=1 ;; *) if test $cross_compiling = no; then cat > conftest.c < int get_stack_direction () { auto char dummy; static char *dummyaddr = (char *)0; if (dummyaddr != (char *)0) return &dummy > dummyaddr ? 1 : &dummy < dummyaddr ? -1 : 0; else { dummyaddr = &dummy; { int result = get_stack_direction (); /* The next assignment avoids tail recursion elimination (IRIX 6.4 CC). */ dummyaddr = (char *)0; return result; } } } int main () { printf ("%d\n", get_stack_direction ()); return 0; } EOF { { eval echo "\"\$as_me\":${as_lineno-$LINENO}: \"$ac_link\""; } >&5 (eval $ac_link) 2>&5 ac_status=$? $as_echo "$as_me:${as_lineno-$LINENO}: \$? = $ac_status" >&5 test $ac_status = 0; } sv_cv_stack_direction=`./conftest` else sv_cv_stack_direction=0 fi ;; esac case $sv_cv_stack_direction in 1) sv_cv_stack_direction_msg="grows up";; -1) sv_cv_stack_direction_msg="grows down";; *) sv_cv_stack_direction_msg="unknown";; esac fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $sv_cv_stack_direction_msg" >&5 $as_echo "$sv_cv_stack_direction_msg" >&6; } cat >>confdefs.h <<_ACEOF #define STACK_DIRECTION $sv_cv_stack_direction _ACEOF { $as_echo "$as_me:${as_lineno-$LINENO}: checking for PIOCMAP in sys/procfs.h" >&5 $as_echo_n "checking for PIOCMAP in sys/procfs.h... " >&6; } if ${sv_cv_procfsvma+:} false; then : $as_echo_n "(cached) " >&6 else cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ #include int main () { int x = PIOCNMAP + PIOCMAP; prmap_t y; ; return 0; } _ACEOF if ac_fn_c_try_link "$LINENO"; then : sv_cv_procfsvma=yes else sv_cv_procfsvma=no fi rm -f core conftest.err conftest.$ac_objext \ conftest$ac_exeext conftest.$ac_ext fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $sv_cv_procfsvma" >&5 $as_echo "$sv_cv_procfsvma" >&6; } for ac_func in mincore do : ac_fn_c_check_func "$LINENO" "mincore" "ac_cv_func_mincore" if test "x$ac_cv_func_mincore" = xyes; then : cat >>confdefs.h <<_ACEOF #define HAVE_MINCORE 1 _ACEOF fi done CFG_STACKVMA= if test $sv_cv_procfsvma = yes; then CFG_STACKVMA=stackvma-procfs.c else case "$host_os" in linux*) CFG_STACKVMA=stackvma-linux.c ;; freebsd*|dragonfly*) CFG_STACKVMA=stackvma-freebsd.c ;; beos*) CFG_STACKVMA=stackvma-beos.c ;; macos* | darwin*) ac_fn_c_check_func "$LINENO" "vm_region" "ac_cv_func_vm_region" if test "x$ac_cv_func_vm_region" = xyes; then : CFG_STACKVMA=stackvma-mach.c fi ;; esac fi if test -z "$CFG_STACKVMA" && test $ac_cv_func_mincore = yes; then CFG_STACKVMA=stackvma-mincore.c fi if test -n "$CFG_STACKVMA"; then $as_echo "#define HAVE_STACKVMA 1" >>confdefs.h else CFG_STACKVMA=stackvma-none.c fi cat >>confdefs.h <<_ACEOF #define CFG_STACKVMA "$CFG_STACKVMA" _ACEOF for ac_func in getrlimit setrlimit do : as_ac_var=`$as_echo "ac_cv_func_$ac_func" | $as_tr_sh` ac_fn_c_check_func "$LINENO" "$ac_func" "$as_ac_var" if eval test \"x\$"$as_ac_var"\" = x"yes"; then : cat >>confdefs.h <<_ACEOF #define `$as_echo "HAVE_$ac_func" | $as_tr_cpp` 1 _ACEOF fi done for ac_func in sigaltstack do : ac_fn_c_check_func "$LINENO" "sigaltstack" "ac_cv_func_sigaltstack" if test "x$ac_cv_func_sigaltstack" = xyes; then : cat >>confdefs.h <<_ACEOF #define HAVE_SIGALTSTACK 1 _ACEOF fi done if test "$ac_cv_func_sigaltstack" = yes; then ac_fn_c_check_type "$LINENO" "stack_t" "ac_cv_type_stack_t" " #include #if HAVE_SYS_SIGNAL_H # include #endif " if test "x$ac_cv_type_stack_t" = xyes; then : else $as_echo "#define stack_t struct sigaltstack" >>confdefs.h fi fi { $as_echo "$as_me:${as_lineno-$LINENO}: checking for working sigaltstack" >&5 $as_echo_n "checking for working sigaltstack... " >&6; } if ${sv_cv_sigaltstack+:} false; then : $as_echo_n "(cached) " >&6 else if test "$ac_cv_func_sigaltstack" = yes; then case "$host_os" in macos* | darwin[6-9]* | darwin[1-9][0-9]*) # On MacOS X 10.2 or newer, just assume that if it compiles, it will # work. If we were to perform the real test, 1 Crash Report dialog # window would pop up. cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ #include int main () { int x = SA_ONSTACK; stack_t ss; sigaltstack ((stack_t*)0, &ss); ; return 0; } _ACEOF if ac_fn_c_try_link "$LINENO"; then : sv_cv_sigaltstack="guessing yes" else sv_cv_sigaltstack=no fi rm -f core conftest.err conftest.$ac_objext \ conftest$ac_exeext conftest.$ac_ext ;; *) if test "$cross_compiling" = yes; then : case "$host_os" in *) cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ #include int main () { int x = SA_ONSTACK; stack_t ss; sigaltstack ((stack_t*)0, &ss); ; return 0; } _ACEOF if ac_fn_c_try_link "$LINENO"; then : sv_cv_sigaltstack="guessing yes" else sv_cv_sigaltstack=no fi rm -f core conftest.err conftest.$ac_objext \ conftest$ac_exeext conftest.$ac_ext ;; esac else cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ #include #include #if HAVE_SYS_SIGNAL_H # include #endif #if HAVE_SETRLIMIT # include # include # include #endif void stackoverflow_handler (int sig) { /* If we get here, the stack overflow was caught. */ exit (0); } volatile int * recurse_1 (volatile int n, volatile int *p) { if (n >= 0) *recurse_1 (n + 1, p) += n; return p; } volatile int recurse (volatile int n) { int sum = 0; return *recurse_1 (n, &sum); } char mystack[16384]; int main () { stack_t altstack; struct sigaction action; #if defined HAVE_SETRLIMIT && defined RLIMIT_STACK /* Before starting the endless recursion, try to be friendly to the user's machine. On some Linux 2.2.x systems, there is no stack limit for user processes at all. We don't want to kill such systems. */ struct rlimit rl; rl.rlim_cur = rl.rlim_max = 0x100000; /* 1 MB */ setrlimit (RLIMIT_STACK, &rl); #endif /* Install the alternate stack. */ altstack.ss_sp = mystack; altstack.ss_size = sizeof (mystack); altstack.ss_flags = 0; /* no SS_DISABLE */ if (sigaltstack (&altstack, NULL) < 0) exit (1); /* Install the SIGSEGV handler. */ sigemptyset (&action.sa_mask); action.sa_handler = &stackoverflow_handler; action.sa_flags = SA_ONSTACK; sigaction (SIGSEGV, &action, (struct sigaction *) NULL); sigaction (SIGBUS, &action, (struct sigaction *) NULL); /* Provoke a stack overflow. */ recurse (0); exit (2); } _ACEOF if ac_fn_c_try_run "$LINENO"; then : sv_cv_sigaltstack=yes else sv_cv_sigaltstack=no fi rm -f core *.core core.conftest.* gmon.out bb.out conftest$ac_exeext \ conftest.$ac_objext conftest.beam conftest.$ac_ext fi ;; esac else sv_cv_sigaltstack=no fi fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $sv_cv_sigaltstack" >&5 $as_echo "$sv_cv_sigaltstack" >&6; } if test "$sv_cv_sigaltstack" != no; then $as_echo "#define HAVE_WORKING_SIGALTSTACK 1" >>confdefs.h fi { $as_echo "$as_me:${as_lineno-$LINENO}: checking if the system supports catching stack overflow" >&5 $as_echo_n "checking if the system supports catching stack overflow... " >&6; } if ${sv_cv_have_stack_overflow_recovery+:} false; then : $as_echo_n "(cached) " >&6 else if test "$CFG_MACHFAULT" != fault-none.h; then sv_cv_have_stack_overflow_recovery=yes else if test "$sv_cv_sigaltstack" != no; then sv_cv_have_stack_overflow_recovery=maybe else case "$host_os" in beos*) sv_cv_have_stack_overflow_recovery=maybe ;; mingw* | cygwin*) sv_cv_have_stack_overflow_recovery=yes ;; *) sv_cv_have_stack_overflow_recovery=no ;; esac fi fi if test $sv_cv_have_stack_overflow_recovery = maybe; then if test -n "$CFG_FAULT"; then cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ #include "$srcdir/src/$CFG_FAULT" #ifdef SIGSEGV_FAULT_HANDLER_ARGLIST #ifdef SIGSEGV_FAULT_ADDRESS xyzzy #endif #endif _ACEOF if (eval "$ac_cpp conftest.$ac_ext") 2>&5 | $EGREP "xyzzy" >/dev/null 2>&1; then : condA=true else condA=false fi rm -f conftest* else condA=false fi if test -n "$CFG_FAULT"; then cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ #include "$srcdir/src/$CFG_FAULT" #ifdef SIGSEGV_FAULT_HANDLER_ARGLIST #ifdef SIGSEGV_FAULT_STACKPOINTER xyzzy #endif #endif _ACEOF if (eval "$ac_cpp conftest.$ac_ext") 2>&5 | $EGREP "xyzzy" >/dev/null 2>&1; then : condB=true else condB=false fi rm -f conftest* else condB=false fi if test "$CFG_STACKVMA" != "stackvma-none.c"; then condC=true else condC=false fi if { $condA && $condB; } || { $condA && $condC; } || { $condB && $condC; }; then sv_cv_have_stack_overflow_recovery=yes else sv_cv_have_stack_overflow_recovery=no fi fi fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $sv_cv_have_stack_overflow_recovery" >&5 $as_echo "$sv_cv_have_stack_overflow_recovery" >&6; } if test $sv_cv_have_stack_overflow_recovery != no; then HAVE_STACK_OVERFLOW_RECOVERY=1 else HAVE_STACK_OVERFLOW_RECOVERY=0 fi # How to longjmp out of a signal handler, in such a way that the # alternate signal stack remains functional. # On MacOS X 10.2 or newer, we don't need these tests, because we'll end up # using handler-macos.c anyway. If we were to perform the tests, 2 Crash Report # dialog windows would pop up. case "$host_os" in macos* | darwin[6-9]* | darwin[1-9][0-9]*) ;; *) { $as_echo "$as_me:${as_lineno-$LINENO}: checking whether a signal handler can be left through longjmp" >&5 $as_echo_n "checking whether a signal handler can be left through longjmp... " >&6; } if ${sv_cv_leave_handler_longjmp+:} false; then : $as_echo_n "(cached) " >&6 else if test "$cross_compiling" = yes; then : case "$host" in *-*-osf[4-9]* | *-*-hpux11* | *-*-linux2.[2-9]*) sv_cv_leave_handler_longjmp=yes ;; *) sv_cv_leave_handler_longjmp="guessing no" ;; esac else cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ #include #include #include #if HAVE_SETRLIMIT # include # include # include #endif jmp_buf mainloop; sigset_t mainsigset; int pass = 0; void stackoverflow_handler (int sig) { pass++; sigprocmask (SIG_SETMASK, &mainsigset, NULL); { } longjmp (mainloop, pass); } volatile int * recurse_1 (volatile int n, volatile int *p) { if (n >= 0) *recurse_1 (n + 1, p) += n; return p; } volatile int recurse (volatile int n) { int sum = 0; return *recurse_1 (n, &sum); } char mystack[16384]; int main () { stack_t altstack; struct sigaction action; sigset_t emptyset; #if defined HAVE_SETRLIMIT && defined RLIMIT_STACK /* Before starting the endless recursion, try to be friendly to the user's machine. On some Linux 2.2.x systems, there is no stack limit for user processes at all. We don't want to kill such systems. */ struct rlimit rl; rl.rlim_cur = rl.rlim_max = 0x100000; /* 1 MB */ setrlimit (RLIMIT_STACK, &rl); #endif /* Install the alternate stack. */ altstack.ss_sp = mystack; altstack.ss_size = sizeof (mystack); altstack.ss_flags = 0; /* no SS_DISABLE */ if (sigaltstack (&altstack, NULL) < 0) exit (1); /* Install the SIGSEGV handler. */ sigemptyset (&action.sa_mask); action.sa_handler = &stackoverflow_handler; action.sa_flags = SA_ONSTACK; sigaction (SIGSEGV, &action, (struct sigaction *) NULL); sigaction (SIGBUS, &action, (struct sigaction *) NULL); /* Save the current signal mask. */ sigemptyset (&emptyset); sigprocmask (SIG_BLOCK, &emptyset, &mainsigset); /* Provoke two stack overflows in a row. */ if (setjmp (mainloop) < 2) { recurse (0); exit (2); } exit (0); } _ACEOF if ac_fn_c_try_run "$LINENO"; then : sv_cv_leave_handler_longjmp=yes else sv_cv_leave_handler_longjmp=no fi rm -f core *.core core.conftest.* gmon.out bb.out conftest$ac_exeext \ conftest.$ac_objext conftest.beam conftest.$ac_ext fi fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $sv_cv_leave_handler_longjmp" >&5 $as_echo "$sv_cv_leave_handler_longjmp" >&6; } { $as_echo "$as_me:${as_lineno-$LINENO}: checking whether a signal handler can be left through longjmp and sigaltstack" >&5 $as_echo_n "checking whether a signal handler can be left through longjmp and sigaltstack... " >&6; } if ${sv_cv_leave_handler_longjmp_sigaltstack+:} false; then : $as_echo_n "(cached) " >&6 else if test "$cross_compiling" = yes; then : case "$host" in *-*-freebsd*) sv_cv_leave_handler_longjmp_sigaltstack=yes ;; *) sv_cv_leave_handler_longjmp_sigaltstack="guessing no" ;; esac else cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ #include #include #include #ifndef SS_ONSTACK #define SS_ONSTACK SA_ONSTACK #endif #if HAVE_SETRLIMIT # include # include # include #endif jmp_buf mainloop; sigset_t mainsigset; int pass = 0; void stackoverflow_handler (int sig) { pass++; sigprocmask (SIG_SETMASK, &mainsigset, NULL); { stack_t ss; if (sigaltstack (NULL, &ss) >= 0) { ss.ss_flags &= ~SS_ONSTACK; sigaltstack (&ss, NULL); } } longjmp (mainloop, pass); } volatile int * recurse_1 (volatile int n, volatile int *p) { if (n >= 0) *recurse_1 (n + 1, p) += n; return p; } volatile int recurse (volatile int n) { int sum = 0; return *recurse_1 (n, &sum); } char mystack[16384]; int main () { stack_t altstack; struct sigaction action; sigset_t emptyset; #if defined HAVE_SETRLIMIT && defined RLIMIT_STACK /* Before starting the endless recursion, try to be friendly to the user's machine. On some Linux 2.2.x systems, there is no stack limit for user processes at all. We don't want to kill such systems. */ struct rlimit rl; rl.rlim_cur = rl.rlim_max = 0x100000; /* 1 MB */ setrlimit (RLIMIT_STACK, &rl); #endif /* Install the alternate stack. */ altstack.ss_sp = mystack; altstack.ss_size = sizeof (mystack); altstack.ss_flags = 0; /* no SS_DISABLE */ if (sigaltstack (&altstack, NULL) < 0) exit (1); /* Install the SIGSEGV handler. */ sigemptyset (&action.sa_mask); action.sa_handler = &stackoverflow_handler; action.sa_flags = SA_ONSTACK; sigaction (SIGSEGV, &action, (struct sigaction *) NULL); sigaction (SIGBUS, &action, (struct sigaction *) NULL); /* Save the current signal mask. */ sigemptyset (&emptyset); sigprocmask (SIG_BLOCK, &emptyset, &mainsigset); /* Provoke two stack overflows in a row. */ if (setjmp (mainloop) < 2) { recurse (0); exit (2); } exit (0); } _ACEOF if ac_fn_c_try_run "$LINENO"; then : sv_cv_leave_handler_longjmp_sigaltstack=yes else sv_cv_leave_handler_longjmp_sigaltstack=no fi rm -f core *.core core.conftest.* gmon.out bb.out conftest$ac_exeext \ conftest.$ac_objext conftest.beam conftest.$ac_ext fi fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $sv_cv_leave_handler_longjmp_sigaltstack" >&5 $as_echo "$sv_cv_leave_handler_longjmp_sigaltstack" >&6; } { $as_echo "$as_me:${as_lineno-$LINENO}: checking whether a signal handler can be left through longjmp and setcontext" >&5 $as_echo_n "checking whether a signal handler can be left through longjmp and setcontext... " >&6; } if ${sv_cv_leave_handler_longjmp_setcontext+:} false; then : $as_echo_n "(cached) " >&6 else if test "$cross_compiling" = yes; then : case "$host" in *-*-irix* | *-*-solaris*) sv_cv_leave_handler_longjmp_setcontext=yes ;; *) sv_cv_leave_handler_longjmp_setcontext="guessing no" ;; esac else cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ #include #include #include #include #ifndef SS_ONSTACK #define SS_ONSTACK SA_ONSTACK #endif #if HAVE_SETRLIMIT # include # include # include #endif jmp_buf mainloop; sigset_t mainsigset; int pass = 0; void stackoverflow_handler (int sig) { pass++; sigprocmask (SIG_SETMASK, &mainsigset, NULL); { static int fl; static ucontext_t uc; fl = 0; if (getcontext (&uc) >= 0) if (fl == 0) if (uc.uc_stack.ss_flags & SS_ONSTACK) { uc.uc_stack.ss_flags &= ~SS_ONSTACK; fl = 1; setcontext (&uc); } } longjmp (mainloop, pass); } volatile int * recurse_1 (volatile int n, volatile int *p) { if (n >= 0) *recurse_1 (n + 1, p) += n; return p; } volatile int recurse (volatile int n) { int sum = 0; return *recurse_1 (n, &sum); } char mystack[16384]; int main () { stack_t altstack; struct sigaction action; sigset_t emptyset; #if defined HAVE_SETRLIMIT && defined RLIMIT_STACK /* Before starting the endless recursion, try to be friendly to the user's machine. On some Linux 2.2.x systems, there is no stack limit for user processes at all. We don't want to kill such systems. */ struct rlimit rl; rl.rlim_cur = rl.rlim_max = 0x100000; /* 1 MB */ setrlimit (RLIMIT_STACK, &rl); #endif /* Install the alternate stack. */ altstack.ss_sp = mystack; altstack.ss_size = sizeof (mystack); altstack.ss_flags = 0; /* no SS_DISABLE */ if (sigaltstack (&altstack, NULL) < 0) exit (1); /* Install the SIGSEGV handler. */ sigemptyset (&action.sa_mask); action.sa_handler = &stackoverflow_handler; action.sa_flags = SA_ONSTACK; sigaction (SIGSEGV, &action, (struct sigaction *) NULL); sigaction (SIGBUS, &action, (struct sigaction *) NULL); /* Save the current signal mask. */ sigemptyset (&emptyset); sigprocmask (SIG_BLOCK, &emptyset, &mainsigset); /* Provoke two stack overflows in a row. */ if (setjmp (mainloop) < 2) { recurse (0); exit (2); } exit (0); } _ACEOF if ac_fn_c_try_run "$LINENO"; then : sv_cv_leave_handler_longjmp_setcontext=yes else sv_cv_leave_handler_longjmp_setcontext=no fi rm -f core *.core core.conftest.* gmon.out bb.out conftest$ac_exeext \ conftest.$ac_objext conftest.beam conftest.$ac_ext fi fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $sv_cv_leave_handler_longjmp_setcontext" >&5 $as_echo "$sv_cv_leave_handler_longjmp_setcontext" >&6; } # End of MacOS X special casing. ;; esac # How to siglongjmp out of a signal handler, in such a way that the # alternate signal stack remains functional. # On MacOS X 10.2 or newer, we don't need these tests, because we'll end up # using handler-macos.c anyway. If we were to perform the tests, 2 Crash Report # dialog windows would pop up. case "$host_os" in macos* | darwin[6-9]* | darwin[1-9][0-9]*) ;; *) { $as_echo "$as_me:${as_lineno-$LINENO}: checking whether a signal handler can be left through siglongjmp" >&5 $as_echo_n "checking whether a signal handler can be left through siglongjmp... " >&6; } if ${sv_cv_leave_handler_siglongjmp+:} false; then : $as_echo_n "(cached) " >&6 else if test "$cross_compiling" = yes; then : case "$host" in *-*-osf[4-9]* | *-*-hpux11* | *-*-linux2.[2-9]* | *-*-irix* | *-*-solaris*) sv_cv_leave_handler_siglongjmp=yes ;; *) sv_cv_leave_handler_siglongjmp="guessing no" ;; esac else cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ #include #include #include #if HAVE_SETRLIMIT # include # include # include #endif sigjmp_buf mainloop; int pass = 0; void stackoverflow_handler (int sig) { pass++; { } siglongjmp (mainloop, pass); } volatile int * recurse_1 (volatile int n, volatile int *p) { if (n >= 0) *recurse_1 (n + 1, p) += n; return p; } volatile int recurse (volatile int n) { int sum = 0; return *recurse_1 (n, &sum); } char mystack[16384]; int main () { stack_t altstack; struct sigaction action; #ifdef __BEOS__ /* On BeOS, this would hang, burning CPU time. Better fail than hang. */ exit (1); #endif #if defined HAVE_SETRLIMIT && defined RLIMIT_STACK /* Before starting the endless recursion, try to be friendly to the user's machine. On some Linux 2.2.x systems, there is no stack limit for user processes at all. We don't want to kill such systems. */ struct rlimit rl; rl.rlim_cur = rl.rlim_max = 0x100000; /* 1 MB */ setrlimit (RLIMIT_STACK, &rl); #endif /* Install the alternate stack. */ altstack.ss_sp = mystack; altstack.ss_size = sizeof (mystack); altstack.ss_flags = 0; /* no SS_DISABLE */ if (sigaltstack (&altstack, NULL) < 0) exit (1); /* Install the SIGSEGV handler. */ sigemptyset (&action.sa_mask); action.sa_handler = &stackoverflow_handler; action.sa_flags = SA_ONSTACK; sigaction (SIGSEGV, &action, (struct sigaction *) NULL); sigaction (SIGBUS, &action, (struct sigaction *) NULL); /* Provoke two stack overflows in a row. */ if (sigsetjmp (mainloop, 1) < 2) { recurse (0); exit (2); } exit (0); } _ACEOF if ac_fn_c_try_run "$LINENO"; then : sv_cv_leave_handler_siglongjmp=yes else sv_cv_leave_handler_siglongjmp=no fi rm -f core *.core core.conftest.* gmon.out bb.out conftest$ac_exeext \ conftest.$ac_objext conftest.beam conftest.$ac_ext fi fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $sv_cv_leave_handler_siglongjmp" >&5 $as_echo "$sv_cv_leave_handler_siglongjmp" >&6; } { $as_echo "$as_me:${as_lineno-$LINENO}: checking whether a signal handler can be left through siglongjmp and sigaltstack" >&5 $as_echo_n "checking whether a signal handler can be left through siglongjmp and sigaltstack... " >&6; } if ${sv_cv_leave_handler_siglongjmp_sigaltstack+:} false; then : $as_echo_n "(cached) " >&6 else if test "$cross_compiling" = yes; then : case "$host" in *-*-freebsd*) sv_cv_leave_handler_siglongjmp_sigaltstack=yes ;; *) sv_cv_leave_handler_siglongjmp_sigaltstack="guessing no" ;; esac else cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ #include #include #include #ifndef SS_ONSTACK #define SS_ONSTACK SA_ONSTACK #endif #if HAVE_SETRLIMIT # include # include # include #endif sigjmp_buf mainloop; int pass = 0; void stackoverflow_handler (int sig) { pass++; { stack_t ss; if (sigaltstack (NULL, &ss) >= 0) { ss.ss_flags &= ~SS_ONSTACK; sigaltstack (&ss, NULL); } } siglongjmp (mainloop, pass); } volatile int * recurse_1 (volatile int n, volatile int *p) { if (n >= 0) *recurse_1 (n + 1, p) += n; return p; } volatile int recurse (volatile int n) { int sum = 0; return *recurse_1 (n, &sum); } char mystack[16384]; int main () { stack_t altstack; struct sigaction action; #ifdef __BEOS__ /* On BeOS, this would hang, burning CPU time. Better fail than hang. */ exit (1); #endif #if defined HAVE_SETRLIMIT && defined RLIMIT_STACK /* Before starting the endless recursion, try to be friendly to the user's machine. On some Linux 2.2.x systems, there is no stack limit for user processes at all. We don't want to kill such systems. */ struct rlimit rl; rl.rlim_cur = rl.rlim_max = 0x100000; /* 1 MB */ setrlimit (RLIMIT_STACK, &rl); #endif /* Install the alternate stack. */ altstack.ss_sp = mystack; altstack.ss_size = sizeof (mystack); altstack.ss_flags = 0; /* no SS_DISABLE */ if (sigaltstack (&altstack, NULL) < 0) exit (1); /* Install the SIGSEGV handler. */ sigemptyset (&action.sa_mask); action.sa_handler = &stackoverflow_handler; action.sa_flags = SA_ONSTACK; sigaction (SIGSEGV, &action, (struct sigaction *) NULL); sigaction (SIGBUS, &action, (struct sigaction *) NULL); /* Provoke two stack overflows in a row. */ if (sigsetjmp (mainloop, 1) < 2) { recurse (0); exit (2); } exit (0); } _ACEOF if ac_fn_c_try_run "$LINENO"; then : sv_cv_leave_handler_siglongjmp_sigaltstack=yes else sv_cv_leave_handler_siglongjmp_sigaltstack=no fi rm -f core *.core core.conftest.* gmon.out bb.out conftest$ac_exeext \ conftest.$ac_objext conftest.beam conftest.$ac_ext fi fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $sv_cv_leave_handler_siglongjmp_sigaltstack" >&5 $as_echo "$sv_cv_leave_handler_siglongjmp_sigaltstack" >&6; } { $as_echo "$as_me:${as_lineno-$LINENO}: checking whether a signal handler can be left through siglongjmp and setcontext" >&5 $as_echo_n "checking whether a signal handler can be left through siglongjmp and setcontext... " >&6; } if ${sv_cv_leave_handler_siglongjmp_setcontext+:} false; then : $as_echo_n "(cached) " >&6 else if test "$cross_compiling" = yes; then : case "$host" in *) sv_cv_leave_handler_siglongjmp_setcontext="guessing no" ;; esac else cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ #include #include #include #include #ifndef SS_ONSTACK #define SS_ONSTACK SA_ONSTACK #endif #if HAVE_SETRLIMIT # include # include # include #endif sigjmp_buf mainloop; int pass = 0; void stackoverflow_handler (int sig) { pass++; { static int fl; static ucontext_t uc; fl = 0; if (getcontext(&uc) >= 0) if (fl == 0) if (uc.uc_stack.ss_flags & SS_ONSTACK) { uc.uc_stack.ss_flags &= ~SS_ONSTACK; fl = 1; setcontext(&uc); } } siglongjmp (mainloop, pass); } volatile int * recurse_1 (volatile int n, volatile int *p) { if (n >= 0) *recurse_1 (n + 1, p) += n; return p; } volatile int recurse (volatile int n) { int sum = 0; return *recurse_1 (n, &sum); } char mystack[16384]; int main () { stack_t altstack; struct sigaction action; #ifdef __BEOS__ /* On BeOS, this would hang, burning CPU time. Better fail than hang. */ exit (1); #endif #if defined HAVE_SETRLIMIT && defined RLIMIT_STACK /* Before starting the endless recursion, try to be friendly to the user's machine. On some Linux 2.2.x systems, there is no stack limit for user processes at all. We don't want to kill such systems. */ struct rlimit rl; rl.rlim_cur = rl.rlim_max = 0x100000; /* 1 MB */ setrlimit (RLIMIT_STACK, &rl); #endif /* Install the alternate stack. */ altstack.ss_sp = mystack; altstack.ss_size = sizeof (mystack); altstack.ss_flags = 0; /* no SS_DISABLE */ if (sigaltstack (&altstack, NULL) < 0) exit (1); /* Install the SIGSEGV handler. */ sigemptyset (&action.sa_mask); action.sa_handler = &stackoverflow_handler; action.sa_flags = SA_ONSTACK; sigaction (SIGSEGV, &action, (struct sigaction *) NULL); sigaction (SIGBUS, &action, (struct sigaction *) NULL); /* Provoke two stack overflows in a row. */ if (sigsetjmp (mainloop, 1) < 2) { recurse (0); exit (2); } exit (0); } _ACEOF if ac_fn_c_try_run "$LINENO"; then : sv_cv_leave_handler_siglongjmp_setcontext=yes else sv_cv_leave_handler_siglongjmp_setcontext=no fi rm -f core *.core core.conftest.* gmon.out bb.out conftest$ac_exeext \ conftest.$ac_objext conftest.beam conftest.$ac_ext fi fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $sv_cv_leave_handler_siglongjmp_setcontext" >&5 $as_echo "$sv_cv_leave_handler_siglongjmp_setcontext" >&6; } # End of MacOS X special casing. ;; esac CFG_LEAVE= if test "$sv_cv_leave_handler_longjmp" != no; then CFG_LEAVE=leave-nop.c else if test "$sv_cv_leave_handler_longjmp_sigaltstack" != no; then CFG_LEAVE=leave-sigaltstack.c else if test "$sv_cv_leave_handler_longjmp_setcontext" != no; then CFG_LEAVE=leave-setcontext.c fi fi fi case "$host_os" in # On BeOS, the 6 tests fail because sigaltstack() doesn't exist. # If one uses set_signal_stack() instead of sigaltstack(), the first # test actually works. i.e. sv_cv_leave_handler_longjmp would be 'yes'. beos*) CFG_LEAVE=leave-nop.c ;; esac if test -z "$CFG_LEAVE"; then CFG_LEAVE=leave-none.c fi cat >>confdefs.h <<_ACEOF #define CFG_LEAVE "$CFG_LEAVE" _ACEOF case "$host_os" in mingw* | cygwin*) CFG_HANDLER=handler-win32.c ;; *) if test -z "$CFG_HANDLER"; then if test $sv_cv_have_sigsegv_recovery = no \ && test $sv_cv_have_stack_overflow_recovery = no; then CFG_HANDLER=handler-none.c else CFG_HANDLER=handler-unix.c fi fi ;; esac cat >>confdefs.h <<_ACEOF #define CFG_HANDLER "$CFG_HANDLER" _ACEOF { echo; echo "${term_bold}Build Parameters:${term_norm}"; } >& 6 # Check whether --enable-relocatable was given. if test "${enable_relocatable+set}" = set; then : enableval=$enable_relocatable; if test "$enableval" != no; then RELOCATABLE=yes else RELOCATABLE=no fi else RELOCATABLE=yes fi { echo; echo "${term_bold}Output Substitution:${term_norm}"; } >& 6 ac_config_files="$ac_config_files Makefile src/Makefile src/sigsegv.h tests/Makefile" cat >confcache <<\_ACEOF # This file is a shell script that caches the results of configure # tests run on this system so they can be shared between configure # scripts and configure runs, see configure's option --config-cache. # It is not useful on other systems. If it contains results you don't # want to keep, you may remove or edit it. # # config.status only pays attention to the cache file if you give it # the --recheck option to rerun configure. # # `ac_cv_env_foo' variables (set or unset) will be overridden when # loading this file, other *unset* `ac_cv_foo' will be assigned the # following values. _ACEOF # The following way of writing the cache mishandles newlines in values, # but we know of no workaround that is simple, portable, and efficient. # So, we kill variables containing newlines. # Ultrix sh set writes to stderr and can't be redirected directly, # and sets the high bit in the cache file unless we assign to the vars. ( for ac_var in `(set) 2>&1 | sed -n 's/^\([a-zA-Z_][a-zA-Z0-9_]*\)=.*/\1/p'`; do eval ac_val=\$$ac_var case $ac_val in #( *${as_nl}*) case $ac_var in #( *_cv_*) { $as_echo "$as_me:${as_lineno-$LINENO}: WARNING: cache variable $ac_var contains a newline" >&5 $as_echo "$as_me: WARNING: cache variable $ac_var contains a newline" >&2;} ;; esac case $ac_var in #( _ | IFS | as_nl) ;; #( BASH_ARGV | BASH_SOURCE) eval $ac_var= ;; #( *) { eval $ac_var=; unset $ac_var;} ;; esac ;; esac done (set) 2>&1 | case $as_nl`(ac_space=' '; set) 2>&1` in #( *${as_nl}ac_space=\ *) # `set' does not quote correctly, so add quotes: double-quote # substitution turns \\\\ into \\, and sed turns \\ into \. sed -n \ "s/'/'\\\\''/g; s/^\\([_$as_cr_alnum]*_cv_[_$as_cr_alnum]*\\)=\\(.*\\)/\\1='\\2'/p" ;; #( *) # `set' quotes correctly as required by POSIX, so do not add quotes. sed -n "/^[_$as_cr_alnum]*_cv_[_$as_cr_alnum]*=/p" ;; esac | sort ) | sed ' /^ac_cv_env_/b end t clear :clear s/^\([^=]*\)=\(.*[{}].*\)$/test "${\1+set}" = set || &/ t end s/^\([^=]*\)=\(.*\)$/\1=${\1=\2}/ :end' >>confcache if diff "$cache_file" confcache >/dev/null 2>&1; then :; else if test -w "$cache_file"; then if test "x$cache_file" != "x/dev/null"; then { $as_echo "$as_me:${as_lineno-$LINENO}: updating cache $cache_file" >&5 $as_echo "$as_me: updating cache $cache_file" >&6;} if test ! -f "$cache_file" || test -h "$cache_file"; then cat confcache >"$cache_file" else case $cache_file in #( */* | ?:*) mv -f confcache "$cache_file"$$ && mv -f "$cache_file"$$ "$cache_file" ;; #( *) mv -f confcache "$cache_file" ;; esac fi fi else { $as_echo "$as_me:${as_lineno-$LINENO}: not updating unwritable cache $cache_file" >&5 $as_echo "$as_me: not updating unwritable cache $cache_file" >&6;} fi fi rm -f confcache test "x$prefix" = xNONE && prefix=$ac_default_prefix # Let make expand exec_prefix. test "x$exec_prefix" = xNONE && exec_prefix='${prefix}' DEFS=-DHAVE_CONFIG_H ac_libobjs= ac_ltlibobjs= U= for ac_i in : $LIBOBJS; do test "x$ac_i" = x: && continue # 1. Remove the extension, and $U if already installed. ac_script='s/\$U\././;s/\.o$//;s/\.obj$//' ac_i=`$as_echo "$ac_i" | sed "$ac_script"` # 2. Prepend LIBOBJDIR. When used with automake>=1.10 LIBOBJDIR # will be set to the directory where LIBOBJS objects are built. as_fn_append ac_libobjs " \${LIBOBJDIR}$ac_i\$U.$ac_objext" as_fn_append ac_ltlibobjs " \${LIBOBJDIR}$ac_i"'$U.lo' done LIBOBJS=$ac_libobjs LTLIBOBJS=$ac_ltlibobjs if test -n "$EXEEXT"; then am__EXEEXT_TRUE= am__EXEEXT_FALSE='#' else am__EXEEXT_TRUE='#' am__EXEEXT_FALSE= fi if test -z "${AMDEP_TRUE}" && test -z "${AMDEP_FALSE}"; then as_fn_error $? "conditional \"AMDEP\" was never defined. Usually this means the macro was only invoked conditionally." "$LINENO" 5 fi if test -z "${am__fastdepCC_TRUE}" && test -z "${am__fastdepCC_FALSE}"; then as_fn_error $? "conditional \"am__fastdepCC\" was never defined. Usually this means the macro was only invoked conditionally." "$LINENO" 5 fi : "${CONFIG_STATUS=./config.status}" ac_write_fail=0 ac_clean_files_save=$ac_clean_files ac_clean_files="$ac_clean_files $CONFIG_STATUS" { $as_echo "$as_me:${as_lineno-$LINENO}: creating $CONFIG_STATUS" >&5 $as_echo "$as_me: creating $CONFIG_STATUS" >&6;} as_write_fail=0 cat >$CONFIG_STATUS <<_ASEOF || as_write_fail=1 #! $SHELL # Generated by $as_me. # Run this file to recreate the current configuration. # Compiler output produced by configure, useful for debugging # configure, is in config.log if it exists. debug=false ac_cs_recheck=false ac_cs_silent=false SHELL=\${CONFIG_SHELL-$SHELL} export SHELL _ASEOF cat >>$CONFIG_STATUS <<\_ASEOF || as_write_fail=1 ## -------------------- ## ## M4sh Initialization. ## ## -------------------- ## # Be more Bourne compatible DUALCASE=1; export DUALCASE # for MKS sh if test -n "${ZSH_VERSION+set}" && (emulate sh) >/dev/null 2>&1; then : emulate sh NULLCMD=: # Pre-4.2 versions of Zsh do word splitting on ${1+"$@"}, which # is contrary to our usage. Disable this feature. alias -g '${1+"$@"}'='"$@"' setopt NO_GLOB_SUBST else case `(set -o) 2>/dev/null` in #( *posix*) : set -o posix ;; #( *) : ;; esac fi as_nl=' ' export as_nl # Printing a long string crashes Solaris 7 /usr/bin/printf. as_echo='\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\' as_echo=$as_echo$as_echo$as_echo$as_echo$as_echo as_echo=$as_echo$as_echo$as_echo$as_echo$as_echo$as_echo # Prefer a ksh shell builtin over an external printf program on Solaris, # but without wasting forks for bash or zsh. if test -z "$BASH_VERSION$ZSH_VERSION" \ && (test "X`print -r -- $as_echo`" = "X$as_echo") 2>/dev/null; then as_echo='print -r --' as_echo_n='print -rn --' elif (test "X`printf %s $as_echo`" = "X$as_echo") 2>/dev/null; then as_echo='printf %s\n' as_echo_n='printf %s' else if test "X`(/usr/ucb/echo -n -n $as_echo) 2>/dev/null`" = "X-n $as_echo"; then as_echo_body='eval /usr/ucb/echo -n "$1$as_nl"' as_echo_n='/usr/ucb/echo -n' else as_echo_body='eval expr "X$1" : "X\\(.*\\)"' as_echo_n_body='eval arg=$1; case $arg in #( *"$as_nl"*) expr "X$arg" : "X\\(.*\\)$as_nl"; arg=`expr "X$arg" : ".*$as_nl\\(.*\\)"`;; esac; expr "X$arg" : "X\\(.*\\)" | tr -d "$as_nl" ' export as_echo_n_body as_echo_n='sh -c $as_echo_n_body as_echo' fi export as_echo_body as_echo='sh -c $as_echo_body as_echo' fi # The user is always right. if test "${PATH_SEPARATOR+set}" != set; then PATH_SEPARATOR=: (PATH='/bin;/bin'; FPATH=$PATH; sh -c :) >/dev/null 2>&1 && { (PATH='/bin:/bin'; FPATH=$PATH; sh -c :) >/dev/null 2>&1 || PATH_SEPARATOR=';' } fi # IFS # We need space, tab and new line, in precisely that order. Quoting is # there to prevent editors from complaining about space-tab. # (If _AS_PATH_WALK were called with IFS unset, it would disable word # splitting by setting IFS to empty value.) IFS=" "" $as_nl" # Find who we are. Look in the path if we contain no directory separator. as_myself= case $0 in #(( *[\\/]* ) as_myself=$0 ;; *) as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. test -r "$as_dir/$0" && as_myself=$as_dir/$0 && break done IFS=$as_save_IFS ;; esac # We did not find ourselves, most probably we were run as `sh COMMAND' # in which case we are not to be found in the path. if test "x$as_myself" = x; then as_myself=$0 fi if test ! -f "$as_myself"; then $as_echo "$as_myself: error: cannot find myself; rerun with an absolute file name" >&2 exit 1 fi # Unset variables that we do not need and which cause bugs (e.g. in # pre-3.0 UWIN ksh). But do not cause bugs in bash 2.01; the "|| exit 1" # suppresses any "Segmentation fault" message there. '((' could # trigger a bug in pdksh 5.2.14. for as_var in BASH_ENV ENV MAIL MAILPATH do eval test x\${$as_var+set} = xset \ && ( (unset $as_var) || exit 1) >/dev/null 2>&1 && unset $as_var || : done PS1='$ ' PS2='> ' PS4='+ ' # NLS nuisances. LC_ALL=C export LC_ALL LANGUAGE=C export LANGUAGE # CDPATH. (unset CDPATH) >/dev/null 2>&1 && unset CDPATH # as_fn_error STATUS ERROR [LINENO LOG_FD] # ---------------------------------------- # Output "`basename $0`: error: ERROR" to stderr. If LINENO and LOG_FD are # provided, also output the error to LOG_FD, referencing LINENO. Then exit the # script with STATUS, using 1 if that was 0. as_fn_error () { as_status=$1; test $as_status -eq 0 && as_status=1 if test "$4"; then as_lineno=${as_lineno-"$3"} as_lineno_stack=as_lineno_stack=$as_lineno_stack $as_echo "$as_me:${as_lineno-$LINENO}: error: $2" >&$4 fi $as_echo "$as_me: error: $2" >&2 as_fn_exit $as_status } # as_fn_error # as_fn_set_status STATUS # ----------------------- # Set $? to STATUS, without forking. as_fn_set_status () { return $1 } # as_fn_set_status # as_fn_exit STATUS # ----------------- # Exit the shell with STATUS, even in a "trap 0" or "set -e" context. as_fn_exit () { set +e as_fn_set_status $1 exit $1 } # as_fn_exit # as_fn_unset VAR # --------------- # Portably unset VAR. as_fn_unset () { { eval $1=; unset $1;} } as_unset=as_fn_unset # as_fn_append VAR VALUE # ---------------------- # Append the text in VALUE to the end of the definition contained in VAR. Take # advantage of any shell optimizations that allow amortized linear growth over # repeated appends, instead of the typical quadratic growth present in naive # implementations. if (eval "as_var=1; as_var+=2; test x\$as_var = x12") 2>/dev/null; then : eval 'as_fn_append () { eval $1+=\$2 }' else as_fn_append () { eval $1=\$$1\$2 } fi # as_fn_append # as_fn_arith ARG... # ------------------ # Perform arithmetic evaluation on the ARGs, and store the result in the # global $as_val. Take advantage of shells that can avoid forks. The arguments # must be portable across $(()) and expr. if (eval "test \$(( 1 + 1 )) = 2") 2>/dev/null; then : eval 'as_fn_arith () { as_val=$(( $* )) }' else as_fn_arith () { as_val=`expr "$@" || test $? -eq 1` } fi # as_fn_arith if expr a : '\(a\)' >/dev/null 2>&1 && test "X`expr 00001 : '.*\(...\)'`" = X001; then as_expr=expr else as_expr=false fi if (basename -- /) >/dev/null 2>&1 && test "X`basename -- / 2>&1`" = "X/"; then as_basename=basename else as_basename=false fi if (as_dir=`dirname -- /` && test "X$as_dir" = X/) >/dev/null 2>&1; then as_dirname=dirname else as_dirname=false fi as_me=`$as_basename -- "$0" || $as_expr X/"$0" : '.*/\([^/][^/]*\)/*$' \| \ X"$0" : 'X\(//\)$' \| \ X"$0" : 'X\(/\)' \| . 2>/dev/null || $as_echo X/"$0" | sed '/^.*\/\([^/][^/]*\)\/*$/{ s//\1/ q } /^X\/\(\/\/\)$/{ s//\1/ q } /^X\/\(\/\).*/{ s//\1/ q } s/.*/./; q'` # Avoid depending upon Character Ranges. as_cr_letters='abcdefghijklmnopqrstuvwxyz' as_cr_LETTERS='ABCDEFGHIJKLMNOPQRSTUVWXYZ' as_cr_Letters=$as_cr_letters$as_cr_LETTERS as_cr_digits='0123456789' as_cr_alnum=$as_cr_Letters$as_cr_digits ECHO_C= ECHO_N= ECHO_T= case `echo -n x` in #((((( -n*) case `echo 'xy\c'` in *c*) ECHO_T=' ';; # ECHO_T is single tab character. xy) ECHO_C='\c';; *) echo `echo ksh88 bug on AIX 6.1` > /dev/null ECHO_T=' ';; esac;; *) ECHO_N='-n';; esac rm -f conf$$ conf$$.exe conf$$.file if test -d conf$$.dir; then rm -f conf$$.dir/conf$$.file else rm -f conf$$.dir mkdir conf$$.dir 2>/dev/null fi if (echo >conf$$.file) 2>/dev/null; then if ln -s conf$$.file conf$$ 2>/dev/null; then as_ln_s='ln -s' # ... but there are two gotchas: # 1) On MSYS, both `ln -s file dir' and `ln file dir' fail. # 2) DJGPP < 2.04 has no symlinks; `ln -s' creates a wrapper executable. # In both cases, we have to default to `cp -pR'. ln -s conf$$.file conf$$.dir 2>/dev/null && test ! -f conf$$.exe || as_ln_s='cp -pR' elif ln conf$$.file conf$$ 2>/dev/null; then as_ln_s=ln else as_ln_s='cp -pR' fi else as_ln_s='cp -pR' fi rm -f conf$$ conf$$.exe conf$$.dir/conf$$.file conf$$.file rmdir conf$$.dir 2>/dev/null # as_fn_mkdir_p # ------------- # Create "$as_dir" as a directory, including parents if necessary. as_fn_mkdir_p () { case $as_dir in #( -*) as_dir=./$as_dir;; esac test -d "$as_dir" || eval $as_mkdir_p || { as_dirs= while :; do case $as_dir in #( *\'*) as_qdir=`$as_echo "$as_dir" | sed "s/'/'\\\\\\\\''/g"`;; #'( *) as_qdir=$as_dir;; esac as_dirs="'$as_qdir' $as_dirs" as_dir=`$as_dirname -- "$as_dir" || $as_expr X"$as_dir" : 'X\(.*[^/]\)//*[^/][^/]*/*$' \| \ X"$as_dir" : 'X\(//\)[^/]' \| \ X"$as_dir" : 'X\(//\)$' \| \ X"$as_dir" : 'X\(/\)' \| . 2>/dev/null || $as_echo X"$as_dir" | sed '/^X\(.*[^/]\)\/\/*[^/][^/]*\/*$/{ s//\1/ q } /^X\(\/\/\)[^/].*/{ s//\1/ q } /^X\(\/\/\)$/{ s//\1/ q } /^X\(\/\).*/{ s//\1/ q } s/.*/./; q'` test -d "$as_dir" && break done test -z "$as_dirs" || eval "mkdir $as_dirs" } || test -d "$as_dir" || as_fn_error $? "cannot create directory $as_dir" } # as_fn_mkdir_p if mkdir -p . 2>/dev/null; then as_mkdir_p='mkdir -p "$as_dir"' else test -d ./-p && rmdir ./-p as_mkdir_p=false fi # as_fn_executable_p FILE # ----------------------- # Test if FILE is an executable regular file. as_fn_executable_p () { test -f "$1" && test -x "$1" } # as_fn_executable_p as_test_x='test -x' as_executable_p=as_fn_executable_p # Sed expression to map a string onto a valid CPP name. as_tr_cpp="eval sed 'y%*$as_cr_letters%P$as_cr_LETTERS%;s%[^_$as_cr_alnum]%_%g'" # Sed expression to map a string onto a valid variable name. as_tr_sh="eval sed 'y%*+%pp%;s%[^_$as_cr_alnum]%_%g'" exec 6>&1 ## ----------------------------------- ## ## Main body of $CONFIG_STATUS script. ## ## ----------------------------------- ## _ASEOF test $as_write_fail = 0 && chmod +x $CONFIG_STATUS || ac_write_fail=1 cat >>$CONFIG_STATUS <<\_ACEOF || ac_write_fail=1 # Save the log message, to keep $0 and so on meaningful, and to # report actual input values of CONFIG_FILES etc. instead of their # values after options handling. ac_log=" This file was extended by $as_me, which was generated by GNU Autoconf 2.69. Invocation command line was CONFIG_FILES = $CONFIG_FILES CONFIG_HEADERS = $CONFIG_HEADERS CONFIG_LINKS = $CONFIG_LINKS CONFIG_COMMANDS = $CONFIG_COMMANDS $ $0 $@ on `(hostname || uname -n) 2>/dev/null | sed 1q` " _ACEOF case $ac_config_files in *" "*) set x $ac_config_files; shift; ac_config_files=$*;; esac case $ac_config_headers in *" "*) set x $ac_config_headers; shift; ac_config_headers=$*;; esac cat >>$CONFIG_STATUS <<_ACEOF || ac_write_fail=1 # Files that config.status was made for. config_files="$ac_config_files" config_headers="$ac_config_headers" config_commands="$ac_config_commands" _ACEOF cat >>$CONFIG_STATUS <<\_ACEOF || ac_write_fail=1 ac_cs_usage="\ \`$as_me' instantiates files and other configuration actions from templates according to the current configuration. Unless the files and actions are specified as TAGs, all are instantiated by default. Usage: $0 [OPTION]... [TAG]... -h, --help print this help, then exit -V, --version print version number and configuration settings, then exit --config print configuration, then exit -q, --quiet, --silent do not print progress messages -d, --debug don't remove temporary files --recheck update $as_me by reconfiguring in the same conditions --file=FILE[:TEMPLATE] instantiate the configuration file FILE --header=FILE[:TEMPLATE] instantiate the configuration header FILE Configuration files: $config_files Configuration headers: $config_headers Configuration commands: $config_commands Report bugs to the package provider." _ACEOF cat >>$CONFIG_STATUS <<_ACEOF || ac_write_fail=1 ac_cs_config="`$as_echo "$ac_configure_args" | sed 's/^ //; s/[\\""\`\$]/\\\\&/g'`" ac_cs_version="\\ config.status configured by $0, generated by GNU Autoconf 2.69, with options \\"\$ac_cs_config\\" Copyright (C) 2012 Free Software Foundation, Inc. This config.status script is free software; the Free Software Foundation gives unlimited permission to copy, distribute and modify it." ac_pwd='$ac_pwd' srcdir='$srcdir' INSTALL='$INSTALL' MKDIR_P='$MKDIR_P' AWK='$AWK' test -n "\$AWK" || AWK=awk _ACEOF cat >>$CONFIG_STATUS <<\_ACEOF || ac_write_fail=1 # The default lists apply if the user does not specify any file. ac_need_defaults=: while test $# != 0 do case $1 in --*=?*) ac_option=`expr "X$1" : 'X\([^=]*\)='` ac_optarg=`expr "X$1" : 'X[^=]*=\(.*\)'` ac_shift=: ;; --*=) ac_option=`expr "X$1" : 'X\([^=]*\)='` ac_optarg= ac_shift=: ;; *) ac_option=$1 ac_optarg=$2 ac_shift=shift ;; esac case $ac_option in # Handling of the options. -recheck | --recheck | --rechec | --reche | --rech | --rec | --re | --r) ac_cs_recheck=: ;; --version | --versio | --versi | --vers | --ver | --ve | --v | -V ) $as_echo "$ac_cs_version"; exit ;; --config | --confi | --conf | --con | --co | --c ) $as_echo "$ac_cs_config"; exit ;; --debug | --debu | --deb | --de | --d | -d ) debug=: ;; --file | --fil | --fi | --f ) $ac_shift case $ac_optarg in *\'*) ac_optarg=`$as_echo "$ac_optarg" | sed "s/'/'\\\\\\\\''/g"` ;; '') as_fn_error $? "missing file argument" ;; esac as_fn_append CONFIG_FILES " '$ac_optarg'" ac_need_defaults=false;; --header | --heade | --head | --hea ) $ac_shift case $ac_optarg in *\'*) ac_optarg=`$as_echo "$ac_optarg" | sed "s/'/'\\\\\\\\''/g"` ;; esac as_fn_append CONFIG_HEADERS " '$ac_optarg'" ac_need_defaults=false;; --he | --h) # Conflict between --help and --header as_fn_error $? "ambiguous option: \`$1' Try \`$0 --help' for more information.";; --help | --hel | -h ) $as_echo "$ac_cs_usage"; exit ;; -q | -quiet | --quiet | --quie | --qui | --qu | --q \ | -silent | --silent | --silen | --sile | --sil | --si | --s) ac_cs_silent=: ;; # This is an error. -*) as_fn_error $? "unrecognized option: \`$1' Try \`$0 --help' for more information." ;; *) as_fn_append ac_config_targets " $1" ac_need_defaults=false ;; esac shift done ac_configure_extra_args= if $ac_cs_silent; then exec 6>/dev/null ac_configure_extra_args="$ac_configure_extra_args --silent" fi _ACEOF cat >>$CONFIG_STATUS <<_ACEOF || ac_write_fail=1 if \$ac_cs_recheck; then set X $SHELL '$0' $ac_configure_args \$ac_configure_extra_args --no-create --no-recursion shift \$as_echo "running CONFIG_SHELL=$SHELL \$*" >&6 CONFIG_SHELL='$SHELL' export CONFIG_SHELL exec "\$@" fi _ACEOF cat >>$CONFIG_STATUS <<\_ACEOF || ac_write_fail=1 exec 5>>config.log { echo sed 'h;s/./-/g;s/^.../## /;s/...$/ ##/;p;x;p;x' <<_ASBOX ## Running $as_me. ## _ASBOX $as_echo "$ac_log" } >&5 _ACEOF cat >>$CONFIG_STATUS <<_ACEOF || ac_write_fail=1 # # INIT-COMMANDS # AMDEP_TRUE="$AMDEP_TRUE" ac_aux_dir="$ac_aux_dir" # The HP-UX ksh and POSIX shell print the target directory to stdout # if CDPATH is set. (unset CDPATH) >/dev/null 2>&1 && unset CDPATH sed_quote_subst='$sed_quote_subst' double_quote_subst='$double_quote_subst' delay_variable_subst='$delay_variable_subst' macro_version='`$ECHO "$macro_version" | $SED "$delay_single_quote_subst"`' macro_revision='`$ECHO "$macro_revision" | $SED "$delay_single_quote_subst"`' enable_shared='`$ECHO "$enable_shared" | $SED "$delay_single_quote_subst"`' enable_static='`$ECHO "$enable_static" | $SED "$delay_single_quote_subst"`' pic_mode='`$ECHO "$pic_mode" | $SED "$delay_single_quote_subst"`' enable_fast_install='`$ECHO "$enable_fast_install" | $SED "$delay_single_quote_subst"`' SHELL='`$ECHO "$SHELL" | $SED "$delay_single_quote_subst"`' ECHO='`$ECHO "$ECHO" | $SED "$delay_single_quote_subst"`' PATH_SEPARATOR='`$ECHO "$PATH_SEPARATOR" | $SED "$delay_single_quote_subst"`' host_alias='`$ECHO "$host_alias" | $SED "$delay_single_quote_subst"`' host='`$ECHO "$host" | $SED "$delay_single_quote_subst"`' host_os='`$ECHO "$host_os" | $SED "$delay_single_quote_subst"`' build_alias='`$ECHO "$build_alias" | $SED "$delay_single_quote_subst"`' build='`$ECHO "$build" | $SED "$delay_single_quote_subst"`' build_os='`$ECHO "$build_os" | $SED "$delay_single_quote_subst"`' SED='`$ECHO "$SED" | $SED "$delay_single_quote_subst"`' Xsed='`$ECHO "$Xsed" | $SED "$delay_single_quote_subst"`' GREP='`$ECHO "$GREP" | $SED "$delay_single_quote_subst"`' EGREP='`$ECHO "$EGREP" | $SED "$delay_single_quote_subst"`' FGREP='`$ECHO "$FGREP" | $SED "$delay_single_quote_subst"`' LD='`$ECHO "$LD" | $SED "$delay_single_quote_subst"`' NM='`$ECHO "$NM" | $SED "$delay_single_quote_subst"`' LN_S='`$ECHO "$LN_S" | $SED "$delay_single_quote_subst"`' max_cmd_len='`$ECHO "$max_cmd_len" | $SED "$delay_single_quote_subst"`' ac_objext='`$ECHO "$ac_objext" | $SED "$delay_single_quote_subst"`' exeext='`$ECHO "$exeext" | $SED "$delay_single_quote_subst"`' lt_unset='`$ECHO "$lt_unset" | $SED "$delay_single_quote_subst"`' lt_SP2NL='`$ECHO "$lt_SP2NL" | $SED "$delay_single_quote_subst"`' lt_NL2SP='`$ECHO "$lt_NL2SP" | $SED "$delay_single_quote_subst"`' lt_cv_to_host_file_cmd='`$ECHO "$lt_cv_to_host_file_cmd" | $SED "$delay_single_quote_subst"`' lt_cv_to_tool_file_cmd='`$ECHO "$lt_cv_to_tool_file_cmd" | $SED "$delay_single_quote_subst"`' reload_flag='`$ECHO "$reload_flag" | $SED "$delay_single_quote_subst"`' reload_cmds='`$ECHO "$reload_cmds" | $SED "$delay_single_quote_subst"`' OBJDUMP='`$ECHO "$OBJDUMP" | $SED "$delay_single_quote_subst"`' deplibs_check_method='`$ECHO "$deplibs_check_method" | $SED "$delay_single_quote_subst"`' file_magic_cmd='`$ECHO "$file_magic_cmd" | $SED "$delay_single_quote_subst"`' file_magic_glob='`$ECHO "$file_magic_glob" | $SED "$delay_single_quote_subst"`' want_nocaseglob='`$ECHO "$want_nocaseglob" | $SED "$delay_single_quote_subst"`' DLLTOOL='`$ECHO "$DLLTOOL" | $SED "$delay_single_quote_subst"`' sharedlib_from_linklib_cmd='`$ECHO "$sharedlib_from_linklib_cmd" | $SED "$delay_single_quote_subst"`' AR='`$ECHO "$AR" | $SED "$delay_single_quote_subst"`' AR_FLAGS='`$ECHO "$AR_FLAGS" | $SED "$delay_single_quote_subst"`' archiver_list_spec='`$ECHO "$archiver_list_spec" | $SED "$delay_single_quote_subst"`' STRIP='`$ECHO "$STRIP" | $SED "$delay_single_quote_subst"`' RANLIB='`$ECHO "$RANLIB" | $SED "$delay_single_quote_subst"`' old_postinstall_cmds='`$ECHO "$old_postinstall_cmds" | $SED "$delay_single_quote_subst"`' old_postuninstall_cmds='`$ECHO "$old_postuninstall_cmds" | $SED "$delay_single_quote_subst"`' old_archive_cmds='`$ECHO "$old_archive_cmds" | $SED "$delay_single_quote_subst"`' lock_old_archive_extraction='`$ECHO "$lock_old_archive_extraction" | $SED "$delay_single_quote_subst"`' CC='`$ECHO "$CC" | $SED "$delay_single_quote_subst"`' CFLAGS='`$ECHO "$CFLAGS" | $SED "$delay_single_quote_subst"`' compiler='`$ECHO "$compiler" | $SED "$delay_single_quote_subst"`' GCC='`$ECHO "$GCC" | $SED "$delay_single_quote_subst"`' lt_cv_sys_global_symbol_pipe='`$ECHO "$lt_cv_sys_global_symbol_pipe" | $SED "$delay_single_quote_subst"`' lt_cv_sys_global_symbol_to_cdecl='`$ECHO "$lt_cv_sys_global_symbol_to_cdecl" | $SED "$delay_single_quote_subst"`' lt_cv_sys_global_symbol_to_c_name_address='`$ECHO "$lt_cv_sys_global_symbol_to_c_name_address" | $SED "$delay_single_quote_subst"`' lt_cv_sys_global_symbol_to_c_name_address_lib_prefix='`$ECHO "$lt_cv_sys_global_symbol_to_c_name_address_lib_prefix" | $SED "$delay_single_quote_subst"`' nm_file_list_spec='`$ECHO "$nm_file_list_spec" | $SED "$delay_single_quote_subst"`' lt_sysroot='`$ECHO "$lt_sysroot" | $SED "$delay_single_quote_subst"`' objdir='`$ECHO "$objdir" | $SED "$delay_single_quote_subst"`' MAGIC_CMD='`$ECHO "$MAGIC_CMD" | $SED "$delay_single_quote_subst"`' lt_prog_compiler_no_builtin_flag='`$ECHO "$lt_prog_compiler_no_builtin_flag" | $SED "$delay_single_quote_subst"`' lt_prog_compiler_pic='`$ECHO "$lt_prog_compiler_pic" | $SED "$delay_single_quote_subst"`' lt_prog_compiler_wl='`$ECHO "$lt_prog_compiler_wl" | $SED "$delay_single_quote_subst"`' lt_prog_compiler_static='`$ECHO "$lt_prog_compiler_static" | $SED "$delay_single_quote_subst"`' lt_cv_prog_compiler_c_o='`$ECHO "$lt_cv_prog_compiler_c_o" | $SED "$delay_single_quote_subst"`' need_locks='`$ECHO "$need_locks" | $SED "$delay_single_quote_subst"`' MANIFEST_TOOL='`$ECHO "$MANIFEST_TOOL" | $SED "$delay_single_quote_subst"`' DSYMUTIL='`$ECHO "$DSYMUTIL" | $SED "$delay_single_quote_subst"`' NMEDIT='`$ECHO "$NMEDIT" | $SED "$delay_single_quote_subst"`' LIPO='`$ECHO "$LIPO" | $SED "$delay_single_quote_subst"`' OTOOL='`$ECHO "$OTOOL" | $SED "$delay_single_quote_subst"`' OTOOL64='`$ECHO "$OTOOL64" | $SED "$delay_single_quote_subst"`' libext='`$ECHO "$libext" | $SED "$delay_single_quote_subst"`' shrext_cmds='`$ECHO "$shrext_cmds" | $SED "$delay_single_quote_subst"`' extract_expsyms_cmds='`$ECHO "$extract_expsyms_cmds" | $SED "$delay_single_quote_subst"`' archive_cmds_need_lc='`$ECHO "$archive_cmds_need_lc" | $SED "$delay_single_quote_subst"`' enable_shared_with_static_runtimes='`$ECHO "$enable_shared_with_static_runtimes" | $SED "$delay_single_quote_subst"`' export_dynamic_flag_spec='`$ECHO "$export_dynamic_flag_spec" | $SED "$delay_single_quote_subst"`' whole_archive_flag_spec='`$ECHO "$whole_archive_flag_spec" | $SED "$delay_single_quote_subst"`' compiler_needs_object='`$ECHO "$compiler_needs_object" | $SED "$delay_single_quote_subst"`' old_archive_from_new_cmds='`$ECHO "$old_archive_from_new_cmds" | $SED "$delay_single_quote_subst"`' old_archive_from_expsyms_cmds='`$ECHO "$old_archive_from_expsyms_cmds" | $SED "$delay_single_quote_subst"`' archive_cmds='`$ECHO "$archive_cmds" | $SED "$delay_single_quote_subst"`' archive_expsym_cmds='`$ECHO "$archive_expsym_cmds" | $SED "$delay_single_quote_subst"`' module_cmds='`$ECHO "$module_cmds" | $SED "$delay_single_quote_subst"`' module_expsym_cmds='`$ECHO "$module_expsym_cmds" | $SED "$delay_single_quote_subst"`' with_gnu_ld='`$ECHO "$with_gnu_ld" | $SED "$delay_single_quote_subst"`' allow_undefined_flag='`$ECHO "$allow_undefined_flag" | $SED "$delay_single_quote_subst"`' no_undefined_flag='`$ECHO "$no_undefined_flag" | $SED "$delay_single_quote_subst"`' hardcode_libdir_flag_spec='`$ECHO "$hardcode_libdir_flag_spec" | $SED "$delay_single_quote_subst"`' hardcode_libdir_separator='`$ECHO "$hardcode_libdir_separator" | $SED "$delay_single_quote_subst"`' hardcode_direct='`$ECHO "$hardcode_direct" | $SED "$delay_single_quote_subst"`' hardcode_direct_absolute='`$ECHO "$hardcode_direct_absolute" | $SED "$delay_single_quote_subst"`' hardcode_minus_L='`$ECHO "$hardcode_minus_L" | $SED "$delay_single_quote_subst"`' hardcode_shlibpath_var='`$ECHO "$hardcode_shlibpath_var" | $SED "$delay_single_quote_subst"`' hardcode_automatic='`$ECHO "$hardcode_automatic" | $SED "$delay_single_quote_subst"`' inherit_rpath='`$ECHO "$inherit_rpath" | $SED "$delay_single_quote_subst"`' link_all_deplibs='`$ECHO "$link_all_deplibs" | $SED "$delay_single_quote_subst"`' always_export_symbols='`$ECHO "$always_export_symbols" | $SED "$delay_single_quote_subst"`' export_symbols_cmds='`$ECHO "$export_symbols_cmds" | $SED "$delay_single_quote_subst"`' exclude_expsyms='`$ECHO "$exclude_expsyms" | $SED "$delay_single_quote_subst"`' include_expsyms='`$ECHO "$include_expsyms" | $SED "$delay_single_quote_subst"`' prelink_cmds='`$ECHO "$prelink_cmds" | $SED "$delay_single_quote_subst"`' postlink_cmds='`$ECHO "$postlink_cmds" | $SED "$delay_single_quote_subst"`' file_list_spec='`$ECHO "$file_list_spec" | $SED "$delay_single_quote_subst"`' variables_saved_for_relink='`$ECHO "$variables_saved_for_relink" | $SED "$delay_single_quote_subst"`' need_lib_prefix='`$ECHO "$need_lib_prefix" | $SED "$delay_single_quote_subst"`' need_version='`$ECHO "$need_version" | $SED "$delay_single_quote_subst"`' version_type='`$ECHO "$version_type" | $SED "$delay_single_quote_subst"`' runpath_var='`$ECHO "$runpath_var" | $SED "$delay_single_quote_subst"`' shlibpath_var='`$ECHO "$shlibpath_var" | $SED "$delay_single_quote_subst"`' shlibpath_overrides_runpath='`$ECHO "$shlibpath_overrides_runpath" | $SED "$delay_single_quote_subst"`' libname_spec='`$ECHO "$libname_spec" | $SED "$delay_single_quote_subst"`' library_names_spec='`$ECHO "$library_names_spec" | $SED "$delay_single_quote_subst"`' soname_spec='`$ECHO "$soname_spec" | $SED "$delay_single_quote_subst"`' install_override_mode='`$ECHO "$install_override_mode" | $SED "$delay_single_quote_subst"`' postinstall_cmds='`$ECHO "$postinstall_cmds" | $SED "$delay_single_quote_subst"`' postuninstall_cmds='`$ECHO "$postuninstall_cmds" | $SED "$delay_single_quote_subst"`' finish_cmds='`$ECHO "$finish_cmds" | $SED "$delay_single_quote_subst"`' finish_eval='`$ECHO "$finish_eval" | $SED "$delay_single_quote_subst"`' hardcode_into_libs='`$ECHO "$hardcode_into_libs" | $SED "$delay_single_quote_subst"`' sys_lib_search_path_spec='`$ECHO "$sys_lib_search_path_spec" | $SED "$delay_single_quote_subst"`' sys_lib_dlsearch_path_spec='`$ECHO "$sys_lib_dlsearch_path_spec" | $SED "$delay_single_quote_subst"`' hardcode_action='`$ECHO "$hardcode_action" | $SED "$delay_single_quote_subst"`' enable_dlopen='`$ECHO "$enable_dlopen" | $SED "$delay_single_quote_subst"`' enable_dlopen_self='`$ECHO "$enable_dlopen_self" | $SED "$delay_single_quote_subst"`' enable_dlopen_self_static='`$ECHO "$enable_dlopen_self_static" | $SED "$delay_single_quote_subst"`' old_striplib='`$ECHO "$old_striplib" | $SED "$delay_single_quote_subst"`' striplib='`$ECHO "$striplib" | $SED "$delay_single_quote_subst"`' LTCC='$LTCC' LTCFLAGS='$LTCFLAGS' compiler='$compiler_DEFAULT' # A function that is used when there is no print builtin or printf. func_fallback_echo () { eval 'cat <<_LTECHO_EOF \$1 _LTECHO_EOF' } # Quote evaled strings. for var in SHELL \ ECHO \ PATH_SEPARATOR \ SED \ GREP \ EGREP \ FGREP \ LD \ NM \ LN_S \ lt_SP2NL \ lt_NL2SP \ reload_flag \ OBJDUMP \ deplibs_check_method \ file_magic_cmd \ file_magic_glob \ want_nocaseglob \ DLLTOOL \ sharedlib_from_linklib_cmd \ AR \ AR_FLAGS \ archiver_list_spec \ STRIP \ RANLIB \ CC \ CFLAGS \ compiler \ lt_cv_sys_global_symbol_pipe \ lt_cv_sys_global_symbol_to_cdecl \ lt_cv_sys_global_symbol_to_c_name_address \ lt_cv_sys_global_symbol_to_c_name_address_lib_prefix \ nm_file_list_spec \ lt_prog_compiler_no_builtin_flag \ lt_prog_compiler_pic \ lt_prog_compiler_wl \ lt_prog_compiler_static \ lt_cv_prog_compiler_c_o \ need_locks \ MANIFEST_TOOL \ DSYMUTIL \ NMEDIT \ LIPO \ OTOOL \ OTOOL64 \ shrext_cmds \ export_dynamic_flag_spec \ whole_archive_flag_spec \ compiler_needs_object \ with_gnu_ld \ allow_undefined_flag \ no_undefined_flag \ hardcode_libdir_flag_spec \ hardcode_libdir_separator \ exclude_expsyms \ include_expsyms \ file_list_spec \ variables_saved_for_relink \ libname_spec \ library_names_spec \ soname_spec \ install_override_mode \ finish_eval \ old_striplib \ striplib; do case \`eval \\\\\$ECHO \\\\""\\\\\$\$var"\\\\"\` in *[\\\\\\\`\\"\\\$]*) eval "lt_\$var=\\\\\\"\\\`\\\$ECHO \\"\\\$\$var\\" | \\\$SED \\"\\\$sed_quote_subst\\"\\\`\\\\\\"" ;; *) eval "lt_\$var=\\\\\\"\\\$\$var\\\\\\"" ;; esac done # Double-quote double-evaled strings. for var in reload_cmds \ old_postinstall_cmds \ old_postuninstall_cmds \ old_archive_cmds \ extract_expsyms_cmds \ old_archive_from_new_cmds \ old_archive_from_expsyms_cmds \ archive_cmds \ archive_expsym_cmds \ module_cmds \ module_expsym_cmds \ export_symbols_cmds \ prelink_cmds \ postlink_cmds \ postinstall_cmds \ postuninstall_cmds \ finish_cmds \ sys_lib_search_path_spec \ sys_lib_dlsearch_path_spec; do case \`eval \\\\\$ECHO \\\\""\\\\\$\$var"\\\\"\` in *[\\\\\\\`\\"\\\$]*) eval "lt_\$var=\\\\\\"\\\`\\\$ECHO \\"\\\$\$var\\" | \\\$SED -e \\"\\\$double_quote_subst\\" -e \\"\\\$sed_quote_subst\\" -e \\"\\\$delay_variable_subst\\"\\\`\\\\\\"" ;; *) eval "lt_\$var=\\\\\\"\\\$\$var\\\\\\"" ;; esac done ac_aux_dir='$ac_aux_dir' xsi_shell='$xsi_shell' lt_shell_append='$lt_shell_append' # See if we are running on zsh, and set the options which allow our # commands through without removal of \ escapes INIT. if test -n "\${ZSH_VERSION+set}" ; then setopt NO_GLOB_SUBST fi PACKAGE='$PACKAGE' VERSION='$VERSION' TIMESTAMP='$TIMESTAMP' RM='$RM' ofile='$ofile' _ACEOF cat >>$CONFIG_STATUS <<\_ACEOF || ac_write_fail=1 # Handling of arguments. for ac_config_target in $ac_config_targets do case $ac_config_target in "config.h") CONFIG_HEADERS="$CONFIG_HEADERS config.h" ;; "depfiles") CONFIG_COMMANDS="$CONFIG_COMMANDS depfiles" ;; "libtool") CONFIG_COMMANDS="$CONFIG_COMMANDS libtool" ;; "Makefile") CONFIG_FILES="$CONFIG_FILES Makefile" ;; "src/Makefile") CONFIG_FILES="$CONFIG_FILES src/Makefile" ;; "src/sigsegv.h") CONFIG_FILES="$CONFIG_FILES src/sigsegv.h" ;; "tests/Makefile") CONFIG_FILES="$CONFIG_FILES tests/Makefile" ;; *) as_fn_error $? "invalid argument: \`$ac_config_target'" "$LINENO" 5;; esac done # If the user did not use the arguments to specify the items to instantiate, # then the envvar interface is used. Set only those that are not. # We use the long form for the default assignment because of an extremely # bizarre bug on SunOS 4.1.3. if $ac_need_defaults; then test "${CONFIG_FILES+set}" = set || CONFIG_FILES=$config_files test "${CONFIG_HEADERS+set}" = set || CONFIG_HEADERS=$config_headers test "${CONFIG_COMMANDS+set}" = set || CONFIG_COMMANDS=$config_commands fi # Have a temporary directory for convenience. Make it in the build tree # simply because there is no reason against having it here, and in addition, # creating and moving files from /tmp can sometimes cause problems. # Hook for its removal unless debugging. # Note that there is a small window in which the directory will not be cleaned: # after its creation but before its name has been assigned to `$tmp'. $debug || { tmp= ac_tmp= trap 'exit_status=$? : "${ac_tmp:=$tmp}" { test ! -d "$ac_tmp" || rm -fr "$ac_tmp"; } && exit $exit_status ' 0 trap 'as_fn_exit 1' 1 2 13 15 } # Create a (secure) tmp directory for tmp files. { tmp=`(umask 077 && mktemp -d "./confXXXXXX") 2>/dev/null` && test -d "$tmp" } || { tmp=./conf$$-$RANDOM (umask 077 && mkdir "$tmp") } || as_fn_error $? "cannot create a temporary directory in ." "$LINENO" 5 ac_tmp=$tmp # Set up the scripts for CONFIG_FILES section. # No need to generate them if there are no CONFIG_FILES. # This happens for instance with `./config.status config.h'. if test -n "$CONFIG_FILES"; then ac_cr=`echo X | tr X '\015'` # On cygwin, bash can eat \r inside `` if the user requested igncr. # But we know of no other shell where ac_cr would be empty at this # point, so we can use a bashism as a fallback. if test "x$ac_cr" = x; then eval ac_cr=\$\'\\r\' fi ac_cs_awk_cr=`$AWK 'BEGIN { print "a\rb" }' /dev/null` if test "$ac_cs_awk_cr" = "a${ac_cr}b"; then ac_cs_awk_cr='\\r' else ac_cs_awk_cr=$ac_cr fi echo 'BEGIN {' >"$ac_tmp/subs1.awk" && _ACEOF { echo "cat >conf$$subs.awk <<_ACEOF" && echo "$ac_subst_vars" | sed 's/.*/&!$&$ac_delim/' && echo "_ACEOF" } >conf$$subs.sh || as_fn_error $? "could not make $CONFIG_STATUS" "$LINENO" 5 ac_delim_num=`echo "$ac_subst_vars" | grep -c '^'` ac_delim='%!_!# ' for ac_last_try in false false false false false :; do . ./conf$$subs.sh || as_fn_error $? "could not make $CONFIG_STATUS" "$LINENO" 5 ac_delim_n=`sed -n "s/.*$ac_delim\$/X/p" conf$$subs.awk | grep -c X` if test $ac_delim_n = $ac_delim_num; then break elif $ac_last_try; then as_fn_error $? "could not make $CONFIG_STATUS" "$LINENO" 5 else ac_delim="$ac_delim!$ac_delim _$ac_delim!! " fi done rm -f conf$$subs.sh cat >>$CONFIG_STATUS <<_ACEOF || ac_write_fail=1 cat >>"\$ac_tmp/subs1.awk" <<\\_ACAWK && _ACEOF sed -n ' h s/^/S["/; s/!.*/"]=/ p g s/^[^!]*!// :repl t repl s/'"$ac_delim"'$// t delim :nl h s/\(.\{148\}\)..*/\1/ t more1 s/["\\]/\\&/g; s/^/"/; s/$/\\n"\\/ p n b repl :more1 s/["\\]/\\&/g; s/^/"/; s/$/"\\/ p g s/.\{148\}// t nl :delim h s/\(.\{148\}\)..*/\1/ t more2 s/["\\]/\\&/g; s/^/"/; s/$/"/ p b :more2 s/["\\]/\\&/g; s/^/"/; s/$/"\\/ p g s/.\{148\}// t delim ' >$CONFIG_STATUS || ac_write_fail=1 rm -f conf$$subs.awk cat >>$CONFIG_STATUS <<_ACEOF || ac_write_fail=1 _ACAWK cat >>"\$ac_tmp/subs1.awk" <<_ACAWK && for (key in S) S_is_set[key] = 1 FS = "" } { line = $ 0 nfields = split(line, field, "@") substed = 0 len = length(field[1]) for (i = 2; i < nfields; i++) { key = field[i] keylen = length(key) if (S_is_set[key]) { value = S[key] line = substr(line, 1, len) "" value "" substr(line, len + keylen + 3) len += length(value) + length(field[++i]) substed = 1 } else len += 1 + keylen } print line } _ACAWK _ACEOF cat >>$CONFIG_STATUS <<\_ACEOF || ac_write_fail=1 if sed "s/$ac_cr//" < /dev/null > /dev/null 2>&1; then sed "s/$ac_cr\$//; s/$ac_cr/$ac_cs_awk_cr/g" else cat fi < "$ac_tmp/subs1.awk" > "$ac_tmp/subs.awk" \ || as_fn_error $? "could not setup config files machinery" "$LINENO" 5 _ACEOF # VPATH may cause trouble with some makes, so we remove sole $(srcdir), # ${srcdir} and @srcdir@ entries from VPATH if srcdir is ".", strip leading and # trailing colons and then remove the whole line if VPATH becomes empty # (actually we leave an empty line to preserve line numbers). if test "x$srcdir" = x.; then ac_vpsub='/^[ ]*VPATH[ ]*=[ ]*/{ h s/// s/^/:/ s/[ ]*$/:/ s/:\$(srcdir):/:/g s/:\${srcdir}:/:/g s/:@srcdir@:/:/g s/^:*// s/:*$// x s/\(=[ ]*\).*/\1/ G s/\n// s/^[^=]*=[ ]*$// }' fi cat >>$CONFIG_STATUS <<\_ACEOF || ac_write_fail=1 fi # test -n "$CONFIG_FILES" # Set up the scripts for CONFIG_HEADERS section. # No need to generate them if there are no CONFIG_HEADERS. # This happens for instance with `./config.status Makefile'. if test -n "$CONFIG_HEADERS"; then cat >"$ac_tmp/defines.awk" <<\_ACAWK || BEGIN { _ACEOF # Transform confdefs.h into an awk script `defines.awk', embedded as # here-document in config.status, that substitutes the proper values into # config.h.in to produce config.h. # Create a delimiter string that does not exist in confdefs.h, to ease # handling of long lines. ac_delim='%!_!# ' for ac_last_try in false false :; do ac_tt=`sed -n "/$ac_delim/p" confdefs.h` if test -z "$ac_tt"; then break elif $ac_last_try; then as_fn_error $? "could not make $CONFIG_HEADERS" "$LINENO" 5 else ac_delim="$ac_delim!$ac_delim _$ac_delim!! " fi done # For the awk script, D is an array of macro values keyed by name, # likewise P contains macro parameters if any. Preserve backslash # newline sequences. ac_word_re=[_$as_cr_Letters][_$as_cr_alnum]* sed -n ' s/.\{148\}/&'"$ac_delim"'/g t rset :rset s/^[ ]*#[ ]*define[ ][ ]*/ / t def d :def s/\\$// t bsnl s/["\\]/\\&/g s/^ \('"$ac_word_re"'\)\(([^()]*)\)[ ]*\(.*\)/P["\1"]="\2"\ D["\1"]=" \3"/p s/^ \('"$ac_word_re"'\)[ ]*\(.*\)/D["\1"]=" \2"/p d :bsnl s/["\\]/\\&/g s/^ \('"$ac_word_re"'\)\(([^()]*)\)[ ]*\(.*\)/P["\1"]="\2"\ D["\1"]=" \3\\\\\\n"\\/p t cont s/^ \('"$ac_word_re"'\)[ ]*\(.*\)/D["\1"]=" \2\\\\\\n"\\/p t cont d :cont n s/.\{148\}/&'"$ac_delim"'/g t clear :clear s/\\$// t bsnlc s/["\\]/\\&/g; s/^/"/; s/$/"/p d :bsnlc s/["\\]/\\&/g; s/^/"/; s/$/\\\\\\n"\\/p b cont ' >$CONFIG_STATUS || ac_write_fail=1 cat >>$CONFIG_STATUS <<_ACEOF || ac_write_fail=1 for (key in D) D_is_set[key] = 1 FS = "" } /^[\t ]*#[\t ]*(define|undef)[\t ]+$ac_word_re([\t (]|\$)/ { line = \$ 0 split(line, arg, " ") if (arg[1] == "#") { defundef = arg[2] mac1 = arg[3] } else { defundef = substr(arg[1], 2) mac1 = arg[2] } split(mac1, mac2, "(") #) macro = mac2[1] prefix = substr(line, 1, index(line, defundef) - 1) if (D_is_set[macro]) { # Preserve the white space surrounding the "#". print prefix "define", macro P[macro] D[macro] next } else { # Replace #undef with comments. This is necessary, for example, # in the case of _POSIX_SOURCE, which is predefined and required # on some systems where configure will not decide to define it. if (defundef == "undef") { print "/*", prefix defundef, macro, "*/" next } } } { print } _ACAWK _ACEOF cat >>$CONFIG_STATUS <<\_ACEOF || ac_write_fail=1 as_fn_error $? "could not setup config headers machinery" "$LINENO" 5 fi # test -n "$CONFIG_HEADERS" eval set X " :F $CONFIG_FILES :H $CONFIG_HEADERS :C $CONFIG_COMMANDS" shift for ac_tag do case $ac_tag in :[FHLC]) ac_mode=$ac_tag; continue;; esac case $ac_mode$ac_tag in :[FHL]*:*);; :L* | :C*:*) as_fn_error $? "invalid tag \`$ac_tag'" "$LINENO" 5;; :[FH]-) ac_tag=-:-;; :[FH]*) ac_tag=$ac_tag:$ac_tag.in;; esac ac_save_IFS=$IFS IFS=: set x $ac_tag IFS=$ac_save_IFS shift ac_file=$1 shift case $ac_mode in :L) ac_source=$1;; :[FH]) ac_file_inputs= for ac_f do case $ac_f in -) ac_f="$ac_tmp/stdin";; *) # Look for the file first in the build tree, then in the source tree # (if the path is not absolute). The absolute path cannot be DOS-style, # because $ac_f cannot contain `:'. test -f "$ac_f" || case $ac_f in [\\/$]*) false;; *) test -f "$srcdir/$ac_f" && ac_f="$srcdir/$ac_f";; esac || as_fn_error 1 "cannot find input file: \`$ac_f'" "$LINENO" 5;; esac case $ac_f in *\'*) ac_f=`$as_echo "$ac_f" | sed "s/'/'\\\\\\\\''/g"`;; esac as_fn_append ac_file_inputs " '$ac_f'" done # Let's still pretend it is `configure' which instantiates (i.e., don't # use $as_me), people would be surprised to read: # /* config.h. Generated by config.status. */ configure_input='Generated from '` $as_echo "$*" | sed 's|^[^:]*/||;s|:[^:]*/|, |g' `' by configure.' if test x"$ac_file" != x-; then configure_input="$ac_file. $configure_input" { $as_echo "$as_me:${as_lineno-$LINENO}: creating $ac_file" >&5 $as_echo "$as_me: creating $ac_file" >&6;} fi # Neutralize special characters interpreted by sed in replacement strings. case $configure_input in #( *\&* | *\|* | *\\* ) ac_sed_conf_input=`$as_echo "$configure_input" | sed 's/[\\\\&|]/\\\\&/g'`;; #( *) ac_sed_conf_input=$configure_input;; esac case $ac_tag in *:-:* | *:-) cat >"$ac_tmp/stdin" \ || as_fn_error $? "could not create $ac_file" "$LINENO" 5 ;; esac ;; esac ac_dir=`$as_dirname -- "$ac_file" || $as_expr X"$ac_file" : 'X\(.*[^/]\)//*[^/][^/]*/*$' \| \ X"$ac_file" : 'X\(//\)[^/]' \| \ X"$ac_file" : 'X\(//\)$' \| \ X"$ac_file" : 'X\(/\)' \| . 2>/dev/null || $as_echo X"$ac_file" | sed '/^X\(.*[^/]\)\/\/*[^/][^/]*\/*$/{ s//\1/ q } /^X\(\/\/\)[^/].*/{ s//\1/ q } /^X\(\/\/\)$/{ s//\1/ q } /^X\(\/\).*/{ s//\1/ q } s/.*/./; q'` as_dir="$ac_dir"; as_fn_mkdir_p ac_builddir=. case "$ac_dir" in .) ac_dir_suffix= ac_top_builddir_sub=. ac_top_build_prefix= ;; *) ac_dir_suffix=/`$as_echo "$ac_dir" | sed 's|^\.[\\/]||'` # A ".." for each directory in $ac_dir_suffix. ac_top_builddir_sub=`$as_echo "$ac_dir_suffix" | sed 's|/[^\\/]*|/..|g;s|/||'` case $ac_top_builddir_sub in "") ac_top_builddir_sub=. ac_top_build_prefix= ;; *) ac_top_build_prefix=$ac_top_builddir_sub/ ;; esac ;; esac ac_abs_top_builddir=$ac_pwd ac_abs_builddir=$ac_pwd$ac_dir_suffix # for backward compatibility: ac_top_builddir=$ac_top_build_prefix case $srcdir in .) # We are building in place. ac_srcdir=. ac_top_srcdir=$ac_top_builddir_sub ac_abs_top_srcdir=$ac_pwd ;; [\\/]* | ?:[\\/]* ) # Absolute name. ac_srcdir=$srcdir$ac_dir_suffix; ac_top_srcdir=$srcdir ac_abs_top_srcdir=$srcdir ;; *) # Relative name. ac_srcdir=$ac_top_build_prefix$srcdir$ac_dir_suffix ac_top_srcdir=$ac_top_build_prefix$srcdir ac_abs_top_srcdir=$ac_pwd/$srcdir ;; esac ac_abs_srcdir=$ac_abs_top_srcdir$ac_dir_suffix case $ac_mode in :F) # # CONFIG_FILE # case $INSTALL in [\\/$]* | ?:[\\/]* ) ac_INSTALL=$INSTALL ;; *) ac_INSTALL=$ac_top_build_prefix$INSTALL ;; esac ac_MKDIR_P=$MKDIR_P case $MKDIR_P in [\\/$]* | ?:[\\/]* ) ;; */*) ac_MKDIR_P=$ac_top_build_prefix$MKDIR_P ;; esac _ACEOF cat >>$CONFIG_STATUS <<\_ACEOF || ac_write_fail=1 # If the template does not know about datarootdir, expand it. # FIXME: This hack should be removed a few years after 2.60. ac_datarootdir_hack=; ac_datarootdir_seen= ac_sed_dataroot=' /datarootdir/ { p q } /@datadir@/p /@docdir@/p /@infodir@/p /@localedir@/p /@mandir@/p' case `eval "sed -n \"\$ac_sed_dataroot\" $ac_file_inputs"` in *datarootdir*) ac_datarootdir_seen=yes;; *@datadir@*|*@docdir@*|*@infodir@*|*@localedir@*|*@mandir@*) { $as_echo "$as_me:${as_lineno-$LINENO}: WARNING: $ac_file_inputs seems to ignore the --datarootdir setting" >&5 $as_echo "$as_me: WARNING: $ac_file_inputs seems to ignore the --datarootdir setting" >&2;} _ACEOF cat >>$CONFIG_STATUS <<_ACEOF || ac_write_fail=1 ac_datarootdir_hack=' s&@datadir@&$datadir&g s&@docdir@&$docdir&g s&@infodir@&$infodir&g s&@localedir@&$localedir&g s&@mandir@&$mandir&g s&\\\${datarootdir}&$datarootdir&g' ;; esac _ACEOF # Neutralize VPATH when `$srcdir' = `.'. # Shell code in configure.ac might set extrasub. # FIXME: do we really want to maintain this feature? cat >>$CONFIG_STATUS <<_ACEOF || ac_write_fail=1 ac_sed_extra="$ac_vpsub $extrasub _ACEOF cat >>$CONFIG_STATUS <<\_ACEOF || ac_write_fail=1 :t /@[a-zA-Z_][a-zA-Z_0-9]*@/!b s|@configure_input@|$ac_sed_conf_input|;t t s&@top_builddir@&$ac_top_builddir_sub&;t t s&@top_build_prefix@&$ac_top_build_prefix&;t t s&@srcdir@&$ac_srcdir&;t t s&@abs_srcdir@&$ac_abs_srcdir&;t t s&@top_srcdir@&$ac_top_srcdir&;t t s&@abs_top_srcdir@&$ac_abs_top_srcdir&;t t s&@builddir@&$ac_builddir&;t t s&@abs_builddir@&$ac_abs_builddir&;t t s&@abs_top_builddir@&$ac_abs_top_builddir&;t t s&@INSTALL@&$ac_INSTALL&;t t s&@MKDIR_P@&$ac_MKDIR_P&;t t $ac_datarootdir_hack " eval sed \"\$ac_sed_extra\" "$ac_file_inputs" | $AWK -f "$ac_tmp/subs.awk" \ >$ac_tmp/out || as_fn_error $? "could not create $ac_file" "$LINENO" 5 test -z "$ac_datarootdir_hack$ac_datarootdir_seen" && { ac_out=`sed -n '/\${datarootdir}/p' "$ac_tmp/out"`; test -n "$ac_out"; } && { ac_out=`sed -n '/^[ ]*datarootdir[ ]*:*=/p' \ "$ac_tmp/out"`; test -z "$ac_out"; } && { $as_echo "$as_me:${as_lineno-$LINENO}: WARNING: $ac_file contains a reference to the variable \`datarootdir' which seems to be undefined. Please make sure it is defined" >&5 $as_echo "$as_me: WARNING: $ac_file contains a reference to the variable \`datarootdir' which seems to be undefined. Please make sure it is defined" >&2;} rm -f "$ac_tmp/stdin" case $ac_file in -) cat "$ac_tmp/out" && rm -f "$ac_tmp/out";; *) rm -f "$ac_file" && mv "$ac_tmp/out" "$ac_file";; esac \ || as_fn_error $? "could not create $ac_file" "$LINENO" 5 ;; :H) # # CONFIG_HEADER # if test x"$ac_file" != x-; then { $as_echo "/* $configure_input */" \ && eval '$AWK -f "$ac_tmp/defines.awk"' "$ac_file_inputs" } >"$ac_tmp/config.h" \ || as_fn_error $? "could not create $ac_file" "$LINENO" 5 if diff "$ac_file" "$ac_tmp/config.h" >/dev/null 2>&1; then { $as_echo "$as_me:${as_lineno-$LINENO}: $ac_file is unchanged" >&5 $as_echo "$as_me: $ac_file is unchanged" >&6;} else rm -f "$ac_file" mv "$ac_tmp/config.h" "$ac_file" \ || as_fn_error $? "could not create $ac_file" "$LINENO" 5 fi else $as_echo "/* $configure_input */" \ && eval '$AWK -f "$ac_tmp/defines.awk"' "$ac_file_inputs" \ || as_fn_error $? "could not create -" "$LINENO" 5 fi # Compute "$ac_file"'s index in $config_headers. _am_arg="$ac_file" _am_stamp_count=1 for _am_header in $config_headers :; do case $_am_header in $_am_arg | $_am_arg:* ) break ;; * ) _am_stamp_count=`expr $_am_stamp_count + 1` ;; esac done echo "timestamp for $_am_arg" >`$as_dirname -- "$_am_arg" || $as_expr X"$_am_arg" : 'X\(.*[^/]\)//*[^/][^/]*/*$' \| \ X"$_am_arg" : 'X\(//\)[^/]' \| \ X"$_am_arg" : 'X\(//\)$' \| \ X"$_am_arg" : 'X\(/\)' \| . 2>/dev/null || $as_echo X"$_am_arg" | sed '/^X\(.*[^/]\)\/\/*[^/][^/]*\/*$/{ s//\1/ q } /^X\(\/\/\)[^/].*/{ s//\1/ q } /^X\(\/\/\)$/{ s//\1/ q } /^X\(\/\).*/{ s//\1/ q } s/.*/./; q'`/stamp-h$_am_stamp_count ;; :C) { $as_echo "$as_me:${as_lineno-$LINENO}: executing $ac_file commands" >&5 $as_echo "$as_me: executing $ac_file commands" >&6;} ;; esac case $ac_file$ac_mode in "depfiles":C) test x"$AMDEP_TRUE" != x"" || { # Autoconf 2.62 quotes --file arguments for eval, but not when files # are listed without --file. Let's play safe and only enable the eval # if we detect the quoting. case $CONFIG_FILES in *\'*) eval set x "$CONFIG_FILES" ;; *) set x $CONFIG_FILES ;; esac shift for mf do # Strip MF so we end up with the name of the file. mf=`echo "$mf" | sed -e 's/:.*$//'` # Check whether this is an Automake generated Makefile or not. # We used to match only the files named `Makefile.in', but # some people rename them; so instead we look at the file content. # Grep'ing the first line is not enough: some people post-process # each Makefile.in and add a new line on top of each file to say so. # Grep'ing the whole file is not good either: AIX grep has a line # limit of 2048, but all sed's we know have understand at least 4000. if sed -n 's,^#.*generated by automake.*,X,p' "$mf" | grep X >/dev/null 2>&1; then dirpart=`$as_dirname -- "$mf" || $as_expr X"$mf" : 'X\(.*[^/]\)//*[^/][^/]*/*$' \| \ X"$mf" : 'X\(//\)[^/]' \| \ X"$mf" : 'X\(//\)$' \| \ X"$mf" : 'X\(/\)' \| . 2>/dev/null || $as_echo X"$mf" | sed '/^X\(.*[^/]\)\/\/*[^/][^/]*\/*$/{ s//\1/ q } /^X\(\/\/\)[^/].*/{ s//\1/ q } /^X\(\/\/\)$/{ s//\1/ q } /^X\(\/\).*/{ s//\1/ q } s/.*/./; q'` else continue fi # Extract the definition of DEPDIR, am__include, and am__quote # from the Makefile without running `make'. DEPDIR=`sed -n 's/^DEPDIR = //p' < "$mf"` test -z "$DEPDIR" && continue am__include=`sed -n 's/^am__include = //p' < "$mf"` test -z "am__include" && continue am__quote=`sed -n 's/^am__quote = //p' < "$mf"` # When using ansi2knr, U may be empty or an underscore; expand it U=`sed -n 's/^U = //p' < "$mf"` # Find all dependency output files, they are included files with # $(DEPDIR) in their names. We invoke sed twice because it is the # simplest approach to changing $(DEPDIR) to its actual value in the # expansion. for file in `sed -n " s/^$am__include $am__quote\(.*(DEPDIR).*\)$am__quote"'$/\1/p' <"$mf" | \ sed -e 's/\$(DEPDIR)/'"$DEPDIR"'/g' -e 's/\$U/'"$U"'/g'`; do # Make sure the directory exists. test -f "$dirpart/$file" && continue fdir=`$as_dirname -- "$file" || $as_expr X"$file" : 'X\(.*[^/]\)//*[^/][^/]*/*$' \| \ X"$file" : 'X\(//\)[^/]' \| \ X"$file" : 'X\(//\)$' \| \ X"$file" : 'X\(/\)' \| . 2>/dev/null || $as_echo X"$file" | sed '/^X\(.*[^/]\)\/\/*[^/][^/]*\/*$/{ s//\1/ q } /^X\(\/\/\)[^/].*/{ s//\1/ q } /^X\(\/\/\)$/{ s//\1/ q } /^X\(\/\).*/{ s//\1/ q } s/.*/./; q'` as_dir=$dirpart/$fdir; as_fn_mkdir_p # echo "creating $dirpart/$file" echo '# dummy' > "$dirpart/$file" done done } ;; "libtool":C) # See if we are running on zsh, and set the options which allow our # commands through without removal of \ escapes. if test -n "${ZSH_VERSION+set}" ; then setopt NO_GLOB_SUBST fi cfgfile="${ofile}T" trap "$RM \"$cfgfile\"; exit 1" 1 2 15 $RM "$cfgfile" cat <<_LT_EOF >> "$cfgfile" #! $SHELL # `$ECHO "$ofile" | sed 's%^.*/%%'` - Provide generalized library-building support services. # Generated automatically by $as_me ($PACKAGE$TIMESTAMP) $VERSION # Libtool was configured on host `(hostname || uname -n) 2>/dev/null | sed 1q`: # NOTE: Changes made to this file will be lost: look at ltmain.sh. # # Copyright (C) 1996, 1997, 1998, 1999, 2000, 2001, 2003, 2004, 2005, # 2006, 2007, 2008, 2009, 2010, 2011 Free Software # Foundation, Inc. # Written by Gordon Matzigkeit, 1996 # # This file is part of GNU Libtool. # # GNU Libtool is free software; you can redistribute it and/or # modify it under the terms of the GNU General Public License as # published by the Free Software Foundation; either version 2 of # the License, or (at your option) any later version. # # As a special exception to the GNU General Public License, # if you distribute this file as part of a program or library that # is built using GNU Libtool, you may include this file under the # same distribution terms that you use for the rest of that program. # # GNU Libtool is distributed in the hope that it will be useful, # but WITHOUT ANY WARRANTY; without even the implied warranty of # MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the # GNU General Public License for more details. # # You should have received a copy of the GNU General Public License # along with GNU Libtool; see the file COPYING. If not, a copy # can be downloaded from http://www.gnu.org/licenses/gpl.html, or # obtained by writing to the Free Software Foundation, Inc., # 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. # The names of the tagged configurations supported by this script. available_tags="" # ### BEGIN LIBTOOL CONFIG # Which release of libtool.m4 was used? macro_version=$macro_version macro_revision=$macro_revision # Whether or not to build shared libraries. build_libtool_libs=$enable_shared # Whether or not to build static libraries. build_old_libs=$enable_static # What type of objects to build. pic_mode=$pic_mode # Whether or not to optimize for fast installation. fast_install=$enable_fast_install # Shell to use when invoking shell scripts. SHELL=$lt_SHELL # An echo program that protects backslashes. ECHO=$lt_ECHO # The PATH separator for the build system. PATH_SEPARATOR=$lt_PATH_SEPARATOR # The host system. host_alias=$host_alias host=$host host_os=$host_os # The build system. build_alias=$build_alias build=$build build_os=$build_os # A sed program that does not truncate output. SED=$lt_SED # Sed that helps us avoid accidentally triggering echo(1) options like -n. Xsed="\$SED -e 1s/^X//" # A grep program that handles long lines. GREP=$lt_GREP # An ERE matcher. EGREP=$lt_EGREP # A literal string matcher. FGREP=$lt_FGREP # A BSD- or MS-compatible name lister. NM=$lt_NM # Whether we need soft or hard links. LN_S=$lt_LN_S # What is the maximum length of a command? max_cmd_len=$max_cmd_len # Object file suffix (normally "o"). objext=$ac_objext # Executable file suffix (normally ""). exeext=$exeext # whether the shell understands "unset". lt_unset=$lt_unset # turn spaces into newlines. SP2NL=$lt_lt_SP2NL # turn newlines into spaces. NL2SP=$lt_lt_NL2SP # convert \$build file names to \$host format. to_host_file_cmd=$lt_cv_to_host_file_cmd # convert \$build files to toolchain format. to_tool_file_cmd=$lt_cv_to_tool_file_cmd # An object symbol dumper. OBJDUMP=$lt_OBJDUMP # Method to check whether dependent libraries are shared objects. deplibs_check_method=$lt_deplibs_check_method # Command to use when deplibs_check_method = "file_magic". file_magic_cmd=$lt_file_magic_cmd # How to find potential files when deplibs_check_method = "file_magic". file_magic_glob=$lt_file_magic_glob # Find potential files using nocaseglob when deplibs_check_method = "file_magic". want_nocaseglob=$lt_want_nocaseglob # DLL creation program. DLLTOOL=$lt_DLLTOOL # Command to associate shared and link libraries. sharedlib_from_linklib_cmd=$lt_sharedlib_from_linklib_cmd # The archiver. AR=$lt_AR # Flags to create an archive. AR_FLAGS=$lt_AR_FLAGS # How to feed a file listing to the archiver. archiver_list_spec=$lt_archiver_list_spec # A symbol stripping program. STRIP=$lt_STRIP # Commands used to install an old-style archive. RANLIB=$lt_RANLIB old_postinstall_cmds=$lt_old_postinstall_cmds old_postuninstall_cmds=$lt_old_postuninstall_cmds # Whether to use a lock for old archive extraction. lock_old_archive_extraction=$lock_old_archive_extraction # A C compiler. LTCC=$lt_CC # LTCC compiler flags. LTCFLAGS=$lt_CFLAGS # Take the output of nm and produce a listing of raw symbols and C names. global_symbol_pipe=$lt_lt_cv_sys_global_symbol_pipe # Transform the output of nm in a proper C declaration. global_symbol_to_cdecl=$lt_lt_cv_sys_global_symbol_to_cdecl # Transform the output of nm in a C name address pair. global_symbol_to_c_name_address=$lt_lt_cv_sys_global_symbol_to_c_name_address # Transform the output of nm in a C name address pair when lib prefix is needed. global_symbol_to_c_name_address_lib_prefix=$lt_lt_cv_sys_global_symbol_to_c_name_address_lib_prefix # Specify filename containing input files for \$NM. nm_file_list_spec=$lt_nm_file_list_spec # The root where to search for dependent libraries,and in which our libraries should be installed. lt_sysroot=$lt_sysroot # The name of the directory that contains temporary libtool files. objdir=$objdir # Used to examine libraries when file_magic_cmd begins with "file". MAGIC_CMD=$MAGIC_CMD # Must we lock files when doing compilation? need_locks=$lt_need_locks # Manifest tool. MANIFEST_TOOL=$lt_MANIFEST_TOOL # Tool to manipulate archived DWARF debug symbol files on Mac OS X. DSYMUTIL=$lt_DSYMUTIL # Tool to change global to local symbols on Mac OS X. NMEDIT=$lt_NMEDIT # Tool to manipulate fat objects and archives on Mac OS X. LIPO=$lt_LIPO # ldd/readelf like tool for Mach-O binaries on Mac OS X. OTOOL=$lt_OTOOL # ldd/readelf like tool for 64 bit Mach-O binaries on Mac OS X 10.4. OTOOL64=$lt_OTOOL64 # Old archive suffix (normally "a"). libext=$libext # Shared library suffix (normally ".so"). shrext_cmds=$lt_shrext_cmds # The commands to extract the exported symbol list from a shared archive. extract_expsyms_cmds=$lt_extract_expsyms_cmds # Variables whose values should be saved in libtool wrapper scripts and # restored at link time. variables_saved_for_relink=$lt_variables_saved_for_relink # Do we need the "lib" prefix for modules? need_lib_prefix=$need_lib_prefix # Do we need a version for libraries? need_version=$need_version # Library versioning type. version_type=$version_type # Shared library runtime path variable. runpath_var=$runpath_var # Shared library path variable. shlibpath_var=$shlibpath_var # Is shlibpath searched before the hard-coded library search path? shlibpath_overrides_runpath=$shlibpath_overrides_runpath # Format of library name prefix. libname_spec=$lt_libname_spec # List of archive names. First name is the real one, the rest are links. # The last name is the one that the linker finds with -lNAME library_names_spec=$lt_library_names_spec # The coded name of the library, if different from the real name. soname_spec=$lt_soname_spec # Permission mode override for installation of shared libraries. install_override_mode=$lt_install_override_mode # Command to use after installation of a shared archive. postinstall_cmds=$lt_postinstall_cmds # Command to use after uninstallation of a shared archive. postuninstall_cmds=$lt_postuninstall_cmds # Commands used to finish a libtool library installation in a directory. finish_cmds=$lt_finish_cmds # As "finish_cmds", except a single script fragment to be evaled but # not shown. finish_eval=$lt_finish_eval # Whether we should hardcode library paths into libraries. hardcode_into_libs=$hardcode_into_libs # Compile-time system search path for libraries. sys_lib_search_path_spec=$lt_sys_lib_search_path_spec # Run-time system search path for libraries. sys_lib_dlsearch_path_spec=$lt_sys_lib_dlsearch_path_spec # Whether dlopen is supported. dlopen_support=$enable_dlopen # Whether dlopen of programs is supported. dlopen_self=$enable_dlopen_self # Whether dlopen of statically linked programs is supported. dlopen_self_static=$enable_dlopen_self_static # Commands to strip libraries. old_striplib=$lt_old_striplib striplib=$lt_striplib # The linker used to build libraries. LD=$lt_LD # How to create reloadable object files. reload_flag=$lt_reload_flag reload_cmds=$lt_reload_cmds # Commands used to build an old-style archive. old_archive_cmds=$lt_old_archive_cmds # A language specific compiler. CC=$lt_compiler # Is the compiler the GNU compiler? with_gcc=$GCC # Compiler flag to turn off builtin functions. no_builtin_flag=$lt_lt_prog_compiler_no_builtin_flag # Additional compiler flags for building library objects. pic_flag=$lt_lt_prog_compiler_pic # How to pass a linker flag through the compiler. wl=$lt_lt_prog_compiler_wl # Compiler flag to prevent dynamic linking. link_static_flag=$lt_lt_prog_compiler_static # Does compiler simultaneously support -c and -o options? compiler_c_o=$lt_lt_cv_prog_compiler_c_o # Whether or not to add -lc for building shared libraries. build_libtool_need_lc=$archive_cmds_need_lc # Whether or not to disallow shared libs when runtime libs are static. allow_libtool_libs_with_static_runtimes=$enable_shared_with_static_runtimes # Compiler flag to allow reflexive dlopens. export_dynamic_flag_spec=$lt_export_dynamic_flag_spec # Compiler flag to generate shared objects directly from archives. whole_archive_flag_spec=$lt_whole_archive_flag_spec # Whether the compiler copes with passing no objects directly. compiler_needs_object=$lt_compiler_needs_object # Create an old-style archive from a shared archive. old_archive_from_new_cmds=$lt_old_archive_from_new_cmds # Create a temporary old-style archive to link instead of a shared archive. old_archive_from_expsyms_cmds=$lt_old_archive_from_expsyms_cmds # Commands used to build a shared archive. archive_cmds=$lt_archive_cmds archive_expsym_cmds=$lt_archive_expsym_cmds # Commands used to build a loadable module if different from building # a shared archive. module_cmds=$lt_module_cmds module_expsym_cmds=$lt_module_expsym_cmds # Whether we are building with GNU ld or not. with_gnu_ld=$lt_with_gnu_ld # Flag that allows shared libraries with undefined symbols to be built. allow_undefined_flag=$lt_allow_undefined_flag # Flag that enforces no undefined symbols. no_undefined_flag=$lt_no_undefined_flag # Flag to hardcode \$libdir into a binary during linking. # This must work even if \$libdir does not exist hardcode_libdir_flag_spec=$lt_hardcode_libdir_flag_spec # Whether we need a single "-rpath" flag with a separated argument. hardcode_libdir_separator=$lt_hardcode_libdir_separator # Set to "yes" if using DIR/libNAME\${shared_ext} during linking hardcodes # DIR into the resulting binary. hardcode_direct=$hardcode_direct # Set to "yes" if using DIR/libNAME\${shared_ext} during linking hardcodes # DIR into the resulting binary and the resulting library dependency is # "absolute",i.e impossible to change by setting \${shlibpath_var} if the # library is relocated. hardcode_direct_absolute=$hardcode_direct_absolute # Set to "yes" if using the -LDIR flag during linking hardcodes DIR # into the resulting binary. hardcode_minus_L=$hardcode_minus_L # Set to "yes" if using SHLIBPATH_VAR=DIR during linking hardcodes DIR # into the resulting binary. hardcode_shlibpath_var=$hardcode_shlibpath_var # Set to "yes" if building a shared library automatically hardcodes DIR # into the library and all subsequent libraries and executables linked # against it. hardcode_automatic=$hardcode_automatic # Set to yes if linker adds runtime paths of dependent libraries # to runtime path list. inherit_rpath=$inherit_rpath # Whether libtool must link a program against all its dependency libraries. link_all_deplibs=$link_all_deplibs # Set to "yes" if exported symbols are required. always_export_symbols=$always_export_symbols # The commands to list exported symbols. export_symbols_cmds=$lt_export_symbols_cmds # Symbols that should not be listed in the preloaded symbols. exclude_expsyms=$lt_exclude_expsyms # Symbols that must always be exported. include_expsyms=$lt_include_expsyms # Commands necessary for linking programs (against libraries) with templates. prelink_cmds=$lt_prelink_cmds # Commands necessary for finishing linking programs. postlink_cmds=$lt_postlink_cmds # Specify filename containing input files. file_list_spec=$lt_file_list_spec # How to hardcode a shared library path into an executable. hardcode_action=$hardcode_action # ### END LIBTOOL CONFIG _LT_EOF case $host_os in aix3*) cat <<\_LT_EOF >> "$cfgfile" # AIX sometimes has problems with the GCC collect2 program. For some # reason, if we set the COLLECT_NAMES environment variable, the problems # vanish in a puff of smoke. if test "X${COLLECT_NAMES+set}" != Xset; then COLLECT_NAMES= export COLLECT_NAMES fi _LT_EOF ;; esac ltmain="$ac_aux_dir/ltmain.sh" # We use sed instead of cat because bash on DJGPP gets confused if # if finds mixed CR/LF and LF-only lines. Since sed operates in # text mode, it properly converts lines to CR/LF. This bash problem # is reportedly fixed, but why not run on old versions too? sed '$q' "$ltmain" >> "$cfgfile" \ || (rm -f "$cfgfile"; exit 1) if test x"$xsi_shell" = xyes; then sed -e '/^func_dirname ()$/,/^} # func_dirname /c\ func_dirname ()\ {\ \ case ${1} in\ \ */*) func_dirname_result="${1%/*}${2}" ;;\ \ * ) func_dirname_result="${3}" ;;\ \ esac\ } # Extended-shell func_dirname implementation' "$cfgfile" > $cfgfile.tmp \ && mv -f "$cfgfile.tmp" "$cfgfile" \ || (rm -f "$cfgfile" && cp "$cfgfile.tmp" "$cfgfile" && rm -f "$cfgfile.tmp") test 0 -eq $? || _lt_function_replace_fail=: sed -e '/^func_basename ()$/,/^} # func_basename /c\ func_basename ()\ {\ \ func_basename_result="${1##*/}"\ } # Extended-shell func_basename implementation' "$cfgfile" > $cfgfile.tmp \ && mv -f "$cfgfile.tmp" "$cfgfile" \ || (rm -f "$cfgfile" && cp "$cfgfile.tmp" "$cfgfile" && rm -f "$cfgfile.tmp") test 0 -eq $? || _lt_function_replace_fail=: sed -e '/^func_dirname_and_basename ()$/,/^} # func_dirname_and_basename /c\ func_dirname_and_basename ()\ {\ \ case ${1} in\ \ */*) func_dirname_result="${1%/*}${2}" ;;\ \ * ) func_dirname_result="${3}" ;;\ \ esac\ \ func_basename_result="${1##*/}"\ } # Extended-shell func_dirname_and_basename implementation' "$cfgfile" > $cfgfile.tmp \ && mv -f "$cfgfile.tmp" "$cfgfile" \ || (rm -f "$cfgfile" && cp "$cfgfile.tmp" "$cfgfile" && rm -f "$cfgfile.tmp") test 0 -eq $? || _lt_function_replace_fail=: sed -e '/^func_stripname ()$/,/^} # func_stripname /c\ func_stripname ()\ {\ \ # pdksh 5.2.14 does not do ${X%$Y} correctly if both X and Y are\ \ # positional parameters, so assign one to ordinary parameter first.\ \ func_stripname_result=${3}\ \ func_stripname_result=${func_stripname_result#"${1}"}\ \ func_stripname_result=${func_stripname_result%"${2}"}\ } # Extended-shell func_stripname implementation' "$cfgfile" > $cfgfile.tmp \ && mv -f "$cfgfile.tmp" "$cfgfile" \ || (rm -f "$cfgfile" && cp "$cfgfile.tmp" "$cfgfile" && rm -f "$cfgfile.tmp") test 0 -eq $? || _lt_function_replace_fail=: sed -e '/^func_split_long_opt ()$/,/^} # func_split_long_opt /c\ func_split_long_opt ()\ {\ \ func_split_long_opt_name=${1%%=*}\ \ func_split_long_opt_arg=${1#*=}\ } # Extended-shell func_split_long_opt implementation' "$cfgfile" > $cfgfile.tmp \ && mv -f "$cfgfile.tmp" "$cfgfile" \ || (rm -f "$cfgfile" && cp "$cfgfile.tmp" "$cfgfile" && rm -f "$cfgfile.tmp") test 0 -eq $? || _lt_function_replace_fail=: sed -e '/^func_split_short_opt ()$/,/^} # func_split_short_opt /c\ func_split_short_opt ()\ {\ \ func_split_short_opt_arg=${1#??}\ \ func_split_short_opt_name=${1%"$func_split_short_opt_arg"}\ } # Extended-shell func_split_short_opt implementation' "$cfgfile" > $cfgfile.tmp \ && mv -f "$cfgfile.tmp" "$cfgfile" \ || (rm -f "$cfgfile" && cp "$cfgfile.tmp" "$cfgfile" && rm -f "$cfgfile.tmp") test 0 -eq $? || _lt_function_replace_fail=: sed -e '/^func_lo2o ()$/,/^} # func_lo2o /c\ func_lo2o ()\ {\ \ case ${1} in\ \ *.lo) func_lo2o_result=${1%.lo}.${objext} ;;\ \ *) func_lo2o_result=${1} ;;\ \ esac\ } # Extended-shell func_lo2o implementation' "$cfgfile" > $cfgfile.tmp \ && mv -f "$cfgfile.tmp" "$cfgfile" \ || (rm -f "$cfgfile" && cp "$cfgfile.tmp" "$cfgfile" && rm -f "$cfgfile.tmp") test 0 -eq $? || _lt_function_replace_fail=: sed -e '/^func_xform ()$/,/^} # func_xform /c\ func_xform ()\ {\ func_xform_result=${1%.*}.lo\ } # Extended-shell func_xform implementation' "$cfgfile" > $cfgfile.tmp \ && mv -f "$cfgfile.tmp" "$cfgfile" \ || (rm -f "$cfgfile" && cp "$cfgfile.tmp" "$cfgfile" && rm -f "$cfgfile.tmp") test 0 -eq $? || _lt_function_replace_fail=: sed -e '/^func_arith ()$/,/^} # func_arith /c\ func_arith ()\ {\ func_arith_result=$(( $* ))\ } # Extended-shell func_arith implementation' "$cfgfile" > $cfgfile.tmp \ && mv -f "$cfgfile.tmp" "$cfgfile" \ || (rm -f "$cfgfile" && cp "$cfgfile.tmp" "$cfgfile" && rm -f "$cfgfile.tmp") test 0 -eq $? || _lt_function_replace_fail=: sed -e '/^func_len ()$/,/^} # func_len /c\ func_len ()\ {\ func_len_result=${#1}\ } # Extended-shell func_len implementation' "$cfgfile" > $cfgfile.tmp \ && mv -f "$cfgfile.tmp" "$cfgfile" \ || (rm -f "$cfgfile" && cp "$cfgfile.tmp" "$cfgfile" && rm -f "$cfgfile.tmp") test 0 -eq $? || _lt_function_replace_fail=: fi if test x"$lt_shell_append" = xyes; then sed -e '/^func_append ()$/,/^} # func_append /c\ func_append ()\ {\ eval "${1}+=\\${2}"\ } # Extended-shell func_append implementation' "$cfgfile" > $cfgfile.tmp \ && mv -f "$cfgfile.tmp" "$cfgfile" \ || (rm -f "$cfgfile" && cp "$cfgfile.tmp" "$cfgfile" && rm -f "$cfgfile.tmp") test 0 -eq $? || _lt_function_replace_fail=: sed -e '/^func_append_quoted ()$/,/^} # func_append_quoted /c\ func_append_quoted ()\ {\ \ func_quote_for_eval "${2}"\ \ eval "${1}+=\\\\ \\$func_quote_for_eval_result"\ } # Extended-shell func_append_quoted implementation' "$cfgfile" > $cfgfile.tmp \ && mv -f "$cfgfile.tmp" "$cfgfile" \ || (rm -f "$cfgfile" && cp "$cfgfile.tmp" "$cfgfile" && rm -f "$cfgfile.tmp") test 0 -eq $? || _lt_function_replace_fail=: # Save a `func_append' function call where possible by direct use of '+=' sed -e 's%func_append \([a-zA-Z_]\{1,\}\) "%\1+="%g' $cfgfile > $cfgfile.tmp \ && mv -f "$cfgfile.tmp" "$cfgfile" \ || (rm -f "$cfgfile" && cp "$cfgfile.tmp" "$cfgfile" && rm -f "$cfgfile.tmp") test 0 -eq $? || _lt_function_replace_fail=: else # Save a `func_append' function call even when '+=' is not available sed -e 's%func_append \([a-zA-Z_]\{1,\}\) "%\1="$\1%g' $cfgfile > $cfgfile.tmp \ && mv -f "$cfgfile.tmp" "$cfgfile" \ || (rm -f "$cfgfile" && cp "$cfgfile.tmp" "$cfgfile" && rm -f "$cfgfile.tmp") test 0 -eq $? || _lt_function_replace_fail=: fi if test x"$_lt_function_replace_fail" = x":"; then { $as_echo "$as_me:${as_lineno-$LINENO}: WARNING: Unable to substitute extended shell functions in $ofile" >&5 $as_echo "$as_me: WARNING: Unable to substitute extended shell functions in $ofile" >&2;} fi mv -f "$cfgfile" "$ofile" || (rm -f "$ofile" && cp "$cfgfile" "$ofile" && rm -f "$cfgfile") chmod +x "$ofile" ;; esac done # for ac_tag as_fn_exit 0 _ACEOF ac_clean_files=$ac_clean_files_save test $ac_write_fail = 0 || as_fn_error $? "write failure creating $CONFIG_STATUS" "$LINENO" 5 # configure is writing to config.log, and then calls config.status. # config.status does its own redirection, appending to config.log. # Unfortunately, on DOS this fails, as config.log is still kept open # by configure, so config.status won't be able to write to it; its # output is simply discarded. So we exec the FD to /dev/null, # effectively closing config.log, so it can be properly (re)opened and # appended to by config.status. When coming back to configure, we # need to make the FD available again. if test "$no_create" != yes; then ac_cs_success=: ac_config_status_args= test "$silent" = yes && ac_config_status_args="$ac_config_status_args --quiet" exec 5>/dev/null $SHELL $CONFIG_STATUS $ac_config_status_args || ac_cs_success=false exec 5>>config.log # Use ||, not &&, to avoid exiting from the if with $? = 1, which # would make configure fail if this is the last instruction. $ac_cs_success || as_fn_exit 1 fi if test -n "$ac_unrecognized_opts" && test "$enable_option_checking" != no; then { $as_echo "$as_me:${as_lineno-$LINENO}: WARNING: unrecognized options: $ac_unrecognized_opts" >&5 $as_echo "$as_me: WARNING: unrecognized options: $ac_unrecognized_opts" >&2;} fi { echo; echo "Now please type '${term_bold}make${term_norm}' to compile. Good luck."; echo; } >& 6 smalltalk-3.2.5/sigsegv/README.woe320000644000175000017500000000422212130343734013713 00000000000000Installation on Woe32 (WinNT/2000/XP, Win95/98/ME): =============================================================================== Installation instructions on Woe32 with Cygwin, compiling for mingw32: - Requires the cygwin tools, with the mingw32 compiler and runtime packages. - Build instructions: Make sure that cygwin's 'bin' directory is the first entry in PATH. Run bash. CC="gcc -mno-cygwin" ./configure --host=i386-pc-mingw32 make make check make install =============================================================================== Installation instructions on Woe32 with MS Visual C/C++ 4.0, 5.0, 6.0, or 7.0: - Requires MS Visual C/C++ 4.0 or 5.0 or 6.0 or 7.0. Note that binaries created with MSVC 7.0 should not be distributed: They depend on a closed-source library 'msvcr70.dll' which is not normally part of a Woe32 installation. You cannot distribute 'msvcr70.dll' with the binaries - this would be a violation of the GPL and of the Microsoft EULA. You can distribute the binaries without including 'msvcr70.dll', but this will cause problems for users that don't have this library on their system. Therefore it is not recommended. This problem does not occur with MSVC 6.0 and earlier. - Cannot build in a separate directory. - Build instructions: Make sure that the MSVC4.0 or MSVC5.0 or MSVC6.0 utilities ("cl" etc.) are found in PATH. For shared library (DLL): **NOT YET SUPPORTED** nmake -f Makefile.msvc DLL=1 MFLAGS=-MD check For static library: nmake -f Makefile.msvc check If you want to build both the shared and static library, you have to unpack the libsigsegv sources twice in different directories. Don't mix the two formats; you cannot use the sigsegv.h generated for the static library together with the shared library or vice versa. - Installation: Copy sigsegv.h to your header file repository. Copy sigsegv.lib to your library repository. If you built for shared library, also copy sigsegv.dll into one of the directories listed in your PATH, or into the directory containing the executable which shall make use of libsigsegv. smalltalk-3.2.5/sigsegv/config.h.in0000644000175000017500000000711312130455564014127 00000000000000/* config.h.in. Generated from configure.ac by autoheader. */ /* The name of the include file describing the fault handler. */ #undef CFG_FAULT /* The name of the file implementing the handler functionality. */ #undef CFG_HANDLER /* The name of the file implementing sigsegv_reset_onstack_flag. */ #undef CFG_LEAVE /* The name of the include file describing the Mach fault handler. */ #undef CFG_MACHFAULT /* The name of the include file describing the fault signals. */ #undef CFG_SIGNALS /* The name of the file determining the stack virtual memory area. */ #undef CFG_STACKVMA /* Define to 1 if you have the header file. */ #undef HAVE_DLFCN_H /* Define if getpagesize() is available as a function or a macro. */ #undef HAVE_GETPAGESIZE /* Define to 1 if you have the `getrlimit' function. */ #undef HAVE_GETRLIMIT /* Define to 1 if you have the header file. */ #undef HAVE_INTTYPES_H /* Define to 1 if you have the header file. */ #undef HAVE_MEMORY_H /* Define to 1 if you have the `mincore' function. */ #undef HAVE_MINCORE /* Define if defines MAP_ANON and mmaping with MAP_ANON works. */ #undef HAVE_MMAP_ANON /* Define if defines MAP_ANONYMOUS and mmaping with MAP_ANONYMOUS works. */ #undef HAVE_MMAP_ANONYMOUS /* Define if mmaping of the special device /dev/zero works. */ #undef HAVE_MMAP_DEVZERO /* Define if PAGESIZE is available as a macro. */ #undef HAVE_PAGESIZE /* Define to 1 if you have the `setrlimit' function. */ #undef HAVE_SETRLIMIT /* Define to 1 if you have the `sigaltstack' function. */ #undef HAVE_SIGALTSTACK /* Define if CFG_STACKVMA is set to a nontrivial source file. */ #undef HAVE_STACKVMA /* Define to 1 if you have the header file. */ #undef HAVE_STDINT_H /* Define to 1 if you have the header file. */ #undef HAVE_STDLIB_H /* Define to 1 if you have the header file. */ #undef HAVE_STRINGS_H /* Define to 1 if you have the header file. */ #undef HAVE_STRING_H /* Define if sysconf(_SC_PAGESIZE) is available as a function or a macro. */ #undef HAVE_SYSCONF_PAGESIZE /* Define to 1 if you have the header file. */ #undef HAVE_SYS_SIGNAL_H /* Define to 1 if you have the header file. */ #undef HAVE_SYS_STAT_H /* Define to 1 if you have the header file. */ #undef HAVE_SYS_TYPES_H /* Define to 1 if you have the header file. */ #undef HAVE_UNISTD_H /* Define if you have the sigaltstack() function and it works. */ #undef HAVE_WORKING_SIGALTSTACK /* Define to the sub-directory in which libtool stores uninstalled libraries. */ #undef LT_OBJDIR /* Name of package */ #undef PACKAGE /* Define to the address where bug reports for this package should be sent. */ #undef PACKAGE_BUGREPORT /* Define to the full name of this package. */ #undef PACKAGE_NAME /* Define to the full name and version of this package. */ #undef PACKAGE_STRING /* Define to the one symbol short name of this package. */ #undef PACKAGE_TARNAME /* Define to the home page for this package. */ #undef PACKAGE_URL /* Define to the version of this package. */ #undef PACKAGE_VERSION /* Define as the direction of stack growth for your system. STACK_DIRECTION > 0 => grows toward higher addresses STACK_DIRECTION < 0 => grows toward lower addresses STACK_DIRECTION = 0 => spaghetti stack. */ #undef STACK_DIRECTION /* Define to 1 if you have the ANSI C header files. */ #undef STDC_HEADERS /* Version number of package */ #undef VERSION /* Define to 'struct sigaltstack' if that's the type of the argument to sigaltstack */ #undef stack_t smalltalk-3.2.5/sigsegv/PORTING0000644000175000017500000003340012130343734013142 00000000000000Successfully tested platforms ============================= __PLATFORM__________________________________SIGSEGV__STACK_OVERFLOW__VERSION___ | | | alpha-dec-osf4.0d | yes | yes | 2.1 alpha-dec-osf4.0f | yes | yes | 2.1 alphaev56-dec-osf4.0f | yes | yes | 2.4 alpha-dec-osf4.0g | yes | yes | 2.1 alpha-dec-osf5.1 | yes | yes | 2.1 alphaev67-dec-osf5.1 | yes | yes | 2.2 alpha-unknown-freebsd4.8 | yes | yes | 2.1 alpha-portbld-freebsd5.5 | yes | yes | 2.3 alphaev67-unknown-linux2.4.17-gnu-glibc2.1 | yes | yes | 1.95 alphaev6-unknown-linux2.2.19-gnu-glibc2.2 | yes | yes | 2.1 alphaev67-unknown-linux2.2.20-gnu-glibc2.2 | yes | yes | 2.1 alphaev67-unknown-linux2.4.4-gnu-glibc2.2 | yes | yes | 2.1 alphaev6-unknown-linux2.4.9-gnu-glibc2.2 | yes | yes | 2.1 alphaev67-unknown-linux2.4.9-gnu-glibc2.2 | yes | yes | 2.1 alphaev6-unknown-linux2.4.18-gnu-glibc2.2 | yes | yes | 2.1 alphaev67-unknown-linux2.4.18-gnu-glibc2.2 | yes | yes | 2.1 alpha-unknown-linux2.4.19-gnu-glibc2.3 | yes | yes | 2.4 alphaev68-unknown-linux2.6.11-gnu-glibc2.3 | yes | yes | 2.2 alpha-unknown-openbsd3.7 | yes | yes | 2.2 alpha-unknown-netbsd1.6 | yes | yes | 2.1 armv4l-unknown-linux2.4.0-gnu-glibc2.2 | no | yes | 2.1 armv4l-unknown-linux2.4.3-gnu-glibc2.2 | yes | yes | 2.1 armv4l-unknown-linux2.4.9-gnu-glibc2.2 | no | yes | 2.0.1 armv5tel-unknown-linux2.4.20-gnu-glibc2.2 | yes | yes | 2.2 armv6l-unknown-linux2.6.18-gnu-glibc2.3 | yes | yes | 2.4 hppa1.1-hp-hpux11.00 | yes | yes | 2.1 hppa2.0-hp-hpux10.20 | yes | yes | 2.2 hppa2.0w-hp-hpux11.00 | yes | yes | 2.2 hppa2.0w-hp-hpux11.11 | yes | yes | 2.4 hppa-unknown-linux2.4.19-gnu-glibc2.2 | yes | yes | 2.0.1 hppa64-unknown-linux2.4.17-gnu-glibc2.2 | yes | yes | 2.1 hppa2.0-unknown-linux2.6.20.1-gnu-glibc2.3 | yes | no | 2.4 i586-pc-beos | no | yes | 2.1 i686-pc-cygwin | yes | yes | 2.02 i686-pc-cygwin | yes | yes | 2.4 i386-apple-darwin8.6.1 | yes | yes | 2.3 i686-apple-darwin8.6.1 | yes | yes | 2.3 i386-apple-darwin8.8.1 | yes | yes | 2.4 i386-apple-darwin8.8.2 | yes | yes | 2.4 i386-apple-darwin8.8.3 | yes | yes | 2.4 i386-apple-darwin8.9.1 | yes | yes | 2.4 i386-apple-darwin8.10.1 | yes | yes | 2.4 i386-apple-darwin9.0.0 | yes | yes | 2.5 i586-pc-linux2.2.14-gnu-glibc2.1 | yes | yes | 2.1 i686-pc-linux2.2.14-gnu-glibc2.1 | yes | yes | 2.0 i686-pc-linux2.2.19-gnu-glibc2.1 | yes | yes | 1.95 i486-pc-linux2.2.21-gnu-glibc2.1 | yes | yes | 2.0 i586-pc-linux2.4.18-gnu-glibc2.1 | yes | yes | 2.0 i686-pc-linux2.4.19-gnu-glibc2.1 | yes | yes | 2.2 i686-pc-linux2.2.16-gnu-glibc2.2 | yes | yes | 2.0 i686-pc-linux2.2.19-gnu-glibc2.2 | yes | yes | 2.0 i686-pc-linux2.4.7-gnu-glibc2.2 | yes | yes | 2.1 i586-pc-linux2.4.9-gnu-glibc2.2 | yes | yes | 2.0 i686-pc-linux2.4.9-gnu-glibc2.2 | yes | yes | 2.0 i386-pc-linux2.4.18-gnu-glibc2.2 | yes | yes | 2.0 i686-pc-linux2.4.18-gnu-glibc2.2 | yes | yes | 2.0 i586-pc-linux2.4.19-gnu-glibc2.2 | yes | yes | 2.0 i686-pc-linux2.4.19-gnu-glibc2.2 | yes | yes | 2.0 i686-pc-linux2.4.20-gnu-glibc2.2 | yes | yes | 2.0 i586-pc-linux2.2.19-gnu-glibc2.3 | yes | yes | 2.1 i686-pc-linux2.4.18-gnu-glibc2.3 | yes | yes | 1.97 i486-pc-linux2.4.20-gnu-glibc2.3 | yes | yes | 2.0 i586-pc-linux2.4.20-gnu-glibc2.3 | yes | yes | 2.0 i686-pc-linux2.4.20-gnu-glibc2.3 | yes | yes | 2.0 i686-pc-linux2.4.21-gnu-glibc2.3 | yes | yes | 2.0 i586-pc-linux2.4.22-gnu-glibc2.3 | yes | yes | 2.0 i386-pc-mingw32 | yes | yes | 2.4 i586-pc-mingw32 | yes | yes | 2.1 i686-pc-mingw32 | yes | yes | 1.96 i386-pc-solaris2.9 | yes | yes | 2.2 i386-pc-solaris2.10 | yes | yes | 2.4 i386-pc-solaris2.11 | yes | yes | 2.2 i686-pc-win32-msvc6 | yes | yes | 1.96 i386-unknown-freebsd4.0 | yes | yes | 2.1 i386-unknown-freebsd4.0-gnu-glibc2.3 | yes | yes | 2.1 i386-unknown-freebsd4.6 | yes | yes | 1.95 i386-unknown-freebsd4.7 | yes | yes | 2.1 i386-unknown-freebsd4.8 | yes | yes | 2.1 i386-unknown-freebsd4.9 | yes | yes | 2.2 i386-unknown-freebsd4.10 | yes | yes | 2.2 i386-unknown-freebsd5.0 | yes | yes | 2.4 i386-portbld-freebsd6.0 | yes | yes | 2.3 i686-unknown-kfreebsd6.2-gnu-glibc2.6 | yes | yes | 2.5+ i386-unknown-netbsdelf1.6 | no | no | 2.4 i386-unknown-netbsdelf2.0.2 | yes | yes | 2.4 i386-unknown-netbsdelf3.0 | yes | yes | 2.4 i386-unknown-netbsd | yes | no | 2.2 i386-unknown-openbsd3.2 | yes | yes | 2.3 i386-unknown-openbsd3.3 | yes | yes | 2.1 i386-unknown-openbsd3.4 | yes | yes | 2.2 i386-unknown-openbsd3.6 | yes | yes | 2.1 i386-unknown-openbsd3.8 | yes | yes | 2.4 i386-unknown-openbsd3.9 | yes | yes | 2.4 i386-unknown-openbsd4.0 | yes | yes | 2.4 ia64-portbld-freebsd7.0 | yes | no | 2.3 ia64-hp-hpux11.22 | yes | no | 2.1 ia64-hp-hpux11.23 | yes | no | 2.2 ia64-unknown-linux2.4.18-gnu-glibc2.2 | yes | yes | 2.4 ia64-unknown-linux2.6.9-gnu-glibc2.3 | yes | no | 2.4 ia64-unknown-linux2.6.16.27-gnu-glibc2.4 | yes | no | 2.4 mips-sgi-irix6.5 | yes | yes | 2.4 mips-unknown-linux2.4.27-gnu-glibc2.3 | yes | yes | 2.4 nsr-tandem-nsk | no | no | 2.1 rs6000-ibm-aix3.2.5 | yes | no | 2.2 rs6000-ibm-aix4.2.0.0 | yes | yes | 2.2 rs6000-ibm-aix4.2.1.0 | yes | yes | 2.1 powerpc-ibm-aix4.3.2.0 | yes | yes | 2.4 powerpc-ibm-aix4.3.3.0 | yes | yes | 1.95 powerpc-ibm-aix5.1.0.0 | yes | yes | 2.4 powerpc-ibm-aix5.2.0.0 | yes | no | 2.1 powerpc-ibm-aix5.3.0.0 | yes | yes | 2.4 powerpc-apple-darwin5.5 | yes | yes | 2.2 powerpc-apple-darwin6.0 | yes | yes | 2.4 powerpc-apple-darwin6.8 | yes | yes | 2.2 powerpc-apple-darwin7.7.0 | yes | yes | 2.2 powerpc-apple-darwin7.8.0 | yes | yes | 2.2 powerpc-apple-darwin7.9.0 | yes | yes | 2.4 powerpc-apple-darwin8.1.0 | yes | yes | 2.2 powerpc-apple-darwin8.3.0 | yes | yes | 2.2 powerpc-apple-darwin8.4.0 | yes | yes | 2.2 powerpc-apple-darwin8.7.0 | yes | yes | 2.4 powerpc-apple-darwin8.8.0 | yes | yes | 2.4 powerpc-apple-darwin8.9.0 | yes | yes | 2.4 powerpc-apple-darwin8.10.0 | yes | yes | 2.4 powerpc-unknown-linux2.2.17-gnu-glibc2.1 | no | yes | 1.95 powerpc-unknown-linux2.2.17-gnu-glibc2.2 | yes | yes | 2.0.1 powerpc-unknown-linux2.4.19-gnu-glibc2.2 | yes | yes | 2.4 powerpc-unknown-linux2.4.28-gnu-glibc2.2 | yes | yes | 2.1 powerpc-unknown-linux2.4.26-gnu-glibc2.3 | yes | yes | 2.1 powerpc-unknown-linux2.6.10-gnu-glibc2.3 | yes | yes | 2.2 powerpc-unknown-linux2.6.16-gnu-glibc2.3 | yes | yes | 2.4 powerpc-unknown-netbsd2.0 | yes | no | 2.1 powerpc-unknown-netbsd3.99.23 | yes | yes | 2.4 powerpc-unknown-openbsd4.0 | yes | yes | 2.4 powerpc-unknown-openbsd4.1 | yes | yes | 2.4 powerpc64-unknown-linux2.6.5-gnu-glibc2.3 | yes | yes | 2.4 sparc-unknown-linux2.4.32-gnu-glibc2.3 | yes | no | 2.1 sparc-unknown-openbsd3.9 | yes | no | 2.4 sparc-sun-solaris2.5.1 | yes | yes | 2.2 sparc-sun-solaris2.6 | yes | yes | 2.2 sparc-sun-solaris2.7 | yes | yes | 2.4 sparc-sun-solaris2.8 | yes | yes | 2.4 sparc-sun-solaris2.9 | yes | yes | 2.4 sparc-sun-solaris2.10 | yes | yes | 2.4 sparc-sun-solaris2.11 | yes | yes | 2.4 sparc64-unknown-linux2.2.18-gnu-glibc2.1 | no | no | 1.95 sparc64-unknown-linux2.4.28-gnu-glibc2.3 | yes | no | 2.4 sparc64-unknown-openbsd3.6 | no | no | 2.2 x86_64-unknown-kfreebsd6.2-gnu-glibc2.6 | yes | yes | 2.5+ x86_64-unknown-linux2.4.21-gnu-glibc2.2 | yes | yes | 2.1 x86_64-unknown-linux2.4.21-gnu-glibc2.3 | yes | yes | 2.1 x86_64-unknown-linux2.6.3-gnu-glibc2.3 | yes | yes | 2.1 x86_64-unknown-linux2.6.9-gnu-glibc2.3 | yes | yes | 2.4 x86_64-unknown-linux2.6.11.4-gnu-glibc2.3 | yes | yes | 2.4 x86_64-unknown-linux2.6.13-gnu-glibc2.3 | yes | yes | 2.4 x86_64-unknown-linux2.6.16-gnu-glibc2.4 | yes | yes | 2.4 x86_64-unknown-linux2.6.16.13-gnu-glibc2.4 | yes | yes | 2.4 x86_64-unknown-linux2.6.16.21-gnu-glibc2.4 | yes | yes | 2.4 x86_64-unknown-linux2.6.17-gnu-glibc2.4 | yes | yes | 2.4 x86_64-unknown-linux2.6.20-gnu-glibc2.5 | yes | yes | 2.4 x86_64-unknown-linux2.6.20.1-gnu-glibc2.5 | yes | yes | 2.4 x86_64-unknown-linux2.6.21-gnu-glibc2.6 | yes | yes | 2.4 x86_64-unknown-netbsd3.0 | yes | yes | 2.4 amd64-portbld-freebsd5.4 | yes | yes | 2.2 amd64-portbld-freebsd6.0 | yes | yes | 2.3 amd64-portbld-freebsd7.0 | yes | yes | 2.3 On FreeBSD 5.2, libsigsegv works best if the /proc filesystem is mounted. (It is not mounted by default.) Porting to new platforms ======================== On Unix systems, where faults are notified to the program through a signal handler, the core routines in handler-unix.c can be used without modifications. But they need the following bits of information. Each of them is stored in a platform dependent file; the file is chosen in configure. * List of signals that are sent when an invalid virtual memory address is accessed, or when the stack overflows. This is a file among signals-*.h. configure chooses and sets the variable CFG_SIGNALS. * What arguments are passed to a fault handler. This is a file among fault-*.h. configure chooses and sets the variable CFG_FAULT. * How to determine the stack's virtual memory area. This is a file among stackvma-*.c. configure chooses and sets the variable CFG_STACKVMA. * How to leave a signal handler that is executing on the alternate signal stack. This is a file among leave-*.c. configure chooses and sets the variable CFG_LEAVE. For each of these, the approach should be: - Find a way to implement the needed functionality. This might involve study of the system include files (in particular and ) and of the kernel sources. For CFG_FAULT, the best starting point is to run the tests/sigsegv1 program with a breakpoint set at 'sigsegv_handler'. - Add to configure.in a test whether your new code works. This will help portability to platforms similar to yours. Then regenerate the configure script (run "autoconf") and verify that the test says "yes" on your platform. - Create a platform dependent file (e.g. fault--.h) and change configure.in to choose this particular file when your test says "yes". Then regenerate the configure script (run "autoconf"). - Verify that "make" and "make check" pass. For non-Unix systems, a separate handler-.c is likely to be needed. smalltalk-3.2.5/sigsegv/INSTALL0000644000175000017500000003660012130455416013134 00000000000000Installation Instructions ************************* Copyright (C) 1994-1996, 1999-2002, 2004-2011 Free Software Foundation, Inc. Copying and distribution of this file, with or without modification, are permitted in any medium without royalty provided the copyright notice and this notice are preserved. This file is offered as-is, without warranty of any kind. Basic Installation ================== Briefly, the shell commands `./configure; make; make install' should configure, build, and install this package. The following more-detailed instructions are generic; see the `README' file for instructions specific to this package. Some packages provide this `INSTALL' file but do not implement all of the features documented below. The lack of an optional feature in a given package is not necessarily a bug. More recommendations for GNU packages can be found in *note Makefile Conventions: (standards)Makefile Conventions. The `configure' shell script attempts to guess correct values for various system-dependent variables used during compilation. It uses those values to create a `Makefile' in each directory of the package. It may also create one or more `.h' files containing system-dependent definitions. Finally, it creates a shell script `config.status' that you can run in the future to recreate the current configuration, and a file `config.log' containing compiler output (useful mainly for debugging `configure'). It can also use an optional file (typically called `config.cache' and enabled with `--cache-file=config.cache' or simply `-C') that saves the results of its tests to speed up reconfiguring. Caching is disabled by default to prevent problems with accidental use of stale cache files. If you need to do unusual things to compile the package, please try to figure out how `configure' could check whether to do them, and mail diffs or instructions to the address given in the `README' so they can be considered for the next release. If you are using the cache, and at some point `config.cache' contains results you don't want to keep, you may remove or edit it. The file `configure.ac' (or `configure.in') is used to create `configure' by a program called `autoconf'. You need `configure.ac' if you want to change it or regenerate `configure' using a newer version of `autoconf'. The simplest way to compile this package is: 1. `cd' to the directory containing the package's source code and type `./configure' to configure the package for your system. Running `configure' might take a while. While running, it prints some messages telling which features it is checking for. 2. Type `make' to compile the package. 3. Optionally, type `make check' to run any self-tests that come with the package, generally using the just-built uninstalled binaries. 4. Type `make install' to install the programs and any data files and documentation. When installing into a prefix owned by root, it is recommended that the package be configured and built as a regular user, and only the `make install' phase executed with root privileges. 5. Optionally, type `make installcheck' to repeat any self-tests, but this time using the binaries in their final installed location. This target does not install anything. Running this target as a regular user, particularly if the prior `make install' required root privileges, verifies that the installation completed correctly. 6. You can remove the program binaries and object files from the source code directory by typing `make clean'. To also remove the files that `configure' created (so you can compile the package for a different kind of computer), type `make distclean'. There is also a `make maintainer-clean' target, but that is intended mainly for the package's developers. If you use it, you may have to get all sorts of other programs in order to regenerate files that came with the distribution. 7. Often, you can also type `make uninstall' to remove the installed files again. In practice, not all packages have tested that uninstallation works correctly, even though it is required by the GNU Coding Standards. 8. Some packages, particularly those that use Automake, provide `make distcheck', which can by used by developers to test that all other targets like `make install' and `make uninstall' work correctly. This target is generally not run by end users. Compilers and Options ===================== Some systems require unusual options for compilation or linking that the `configure' script does not know about. Run `./configure --help' for details on some of the pertinent environment variables. You can give `configure' initial values for configuration parameters by setting variables in the command line or in the environment. Here is an example: ./configure CC=c99 CFLAGS=-g LIBS=-lposix *Note Defining Variables::, for more details. Compiling For Multiple Architectures ==================================== You can compile the package for more than one kind of computer at the same time, by placing the object files for each architecture in their own directory. To do this, you can use GNU `make'. `cd' to the directory where you want the object files and executables to go and run the `configure' script. `configure' automatically checks for the source code in the directory that `configure' is in and in `..'. This is known as a "VPATH" build. With a non-GNU `make', it is safer to compile the package for one architecture at a time in the source code directory. After you have installed the package for one architecture, use `make distclean' before reconfiguring for another architecture. On MacOS X 10.5 and later systems, you can create libraries and executables that work on multiple system types--known as "fat" or "universal" binaries--by specifying multiple `-arch' options to the compiler but only a single `-arch' option to the preprocessor. Like this: ./configure CC="gcc -arch i386 -arch x86_64 -arch ppc -arch ppc64" \ CXX="g++ -arch i386 -arch x86_64 -arch ppc -arch ppc64" \ CPP="gcc -E" CXXCPP="g++ -E" This is not guaranteed to produce working output in all cases, you may have to build one architecture at a time and combine the results using the `lipo' tool if you have problems. Installation Names ================== By default, `make install' installs the package's commands under `/usr/local/bin', include files under `/usr/local/include', etc. You can specify an installation prefix other than `/usr/local' by giving `configure' the option `--prefix=PREFIX', where PREFIX must be an absolute file name. You can specify separate installation prefixes for architecture-specific files and architecture-independent files. If you pass the option `--exec-prefix=PREFIX' to `configure', the package uses PREFIX as the prefix for installing programs and libraries. Documentation and other data files still use the regular prefix. In addition, if you use an unusual directory layout you can give options like `--bindir=DIR' to specify different values for particular kinds of files. Run `configure --help' for a list of the directories you can set and what kinds of files go in them. In general, the default for these options is expressed in terms of `${prefix}', so that specifying just `--prefix' will affect all of the other directory specifications that were not explicitly provided. The most portable way to affect installation locations is to pass the correct locations to `configure'; however, many packages provide one or both of the following shortcuts of passing variable assignments to the `make install' command line to change installation locations without having to reconfigure or recompile. The first method involves providing an override variable for each affected directory. For example, `make install prefix=/alternate/directory' will choose an alternate location for all directory configuration variables that were expressed in terms of `${prefix}'. Any directories that were specified during `configure', but not in terms of `${prefix}', must each be overridden at install time for the entire installation to be relocated. The approach of makefile variable overrides for each directory variable is required by the GNU Coding Standards, and ideally causes no recompilation. However, some platforms have known limitations with the semantics of shared libraries that end up requiring recompilation when using this method, particularly noticeable in packages that use GNU Libtool. The second method involves providing the `DESTDIR' variable. For example, `make install DESTDIR=/alternate/directory' will prepend `/alternate/directory' before all installation names. The approach of `DESTDIR' overrides is not required by the GNU Coding Standards, and does not work on platforms that have drive letters. On the other hand, it does better at avoiding recompilation issues, and works well even when some directory options were not specified in terms of `${prefix}' at `configure' time. Optional Features ================= If the package supports it, you can cause programs to be installed with an extra prefix or suffix on their names by giving `configure' the option `--program-prefix=PREFIX' or `--program-suffix=SUFFIX'. Some packages pay attention to `--enable-FEATURE' options to `configure', where FEATURE indicates an optional part of the package. They may also pay attention to `--with-PACKAGE' options, where PACKAGE is something like `gnu-as' or `x' (for the X Window System). The `README' should mention any `--enable-' and `--with-' options that the package recognizes. For packages that use the X Window System, `configure' can usually find the X include and library files automatically, but if it doesn't, you can use the `configure' options `--x-includes=DIR' and `--x-libraries=DIR' to specify their locations. Some packages offer the ability to configure how verbose the execution of `make' will be. For these packages, running `./configure --enable-silent-rules' sets the default to minimal output, which can be overridden with `make V=1'; while running `./configure --disable-silent-rules' sets the default to verbose, which can be overridden with `make V=0'. Particular systems ================== On HP-UX, the default C compiler is not ANSI C compatible. If GNU CC is not installed, it is recommended to use the following options in order to use an ANSI C compiler: ./configure CC="cc -Ae -D_XOPEN_SOURCE=500" and if that doesn't work, install pre-built binaries of GCC for HP-UX. HP-UX `make' updates targets which have the same time stamps as their prerequisites, which makes it generally unusable when shipped generated files such as `configure' are involved. Use GNU `make' instead. On OSF/1 a.k.a. Tru64, some versions of the default C compiler cannot parse its `' header file. The option `-nodtk' can be used as a workaround. If GNU CC is not installed, it is therefore recommended to try ./configure CC="cc" and if that doesn't work, try ./configure CC="cc -nodtk" On Solaris, don't put `/usr/ucb' early in your `PATH'. This directory contains several dysfunctional programs; working variants of these programs are available in `/usr/bin'. So, if you need `/usr/ucb' in your `PATH', put it _after_ `/usr/bin'. On Haiku, software installed for all users goes in `/boot/common', not `/usr/local'. It is recommended to use the following options: ./configure --prefix=/boot/common Specifying the System Type ========================== There may be some features `configure' cannot figure out automatically, but needs to determine by the type of machine the package will run on. Usually, assuming the package is built to be run on the _same_ architectures, `configure' can figure that out, but if it prints a message saying it cannot guess the machine type, give it the `--build=TYPE' option. TYPE can either be a short name for the system type, such as `sun4', or a canonical name which has the form: CPU-COMPANY-SYSTEM where SYSTEM can have one of these forms: OS KERNEL-OS See the file `config.sub' for the possible values of each field. If `config.sub' isn't included in this package, then this package doesn't need to know the machine type. If you are _building_ compiler tools for cross-compiling, you should use the option `--target=TYPE' to select the type of system they will produce code for. If you want to _use_ a cross compiler, that generates code for a platform different from the build platform, you should specify the "host" platform (i.e., that on which the generated programs will eventually be run) with `--host=TYPE'. Sharing Defaults ================ If you want to set default values for `configure' scripts to share, you can create a site shell script called `config.site' that gives default values for variables like `CC', `cache_file', and `prefix'. `configure' looks for `PREFIX/share/config.site' if it exists, then `PREFIX/etc/config.site' if it exists. Or, you can set the `CONFIG_SITE' environment variable to the location of the site script. A warning: not all `configure' scripts look for a site script. Defining Variables ================== Variables not defined in a site shell script can be set in the environment passed to `configure'. However, some packages may run configure again during the build, and the customized values of these variables may be lost. In order to avoid this problem, you should set them in the `configure' command line, using `VAR=value'. For example: ./configure CC=/usr/local2/bin/gcc causes the specified `gcc' to be used as the C compiler (unless it is overridden in the site shell script). Unfortunately, this technique does not work for `CONFIG_SHELL' due to an Autoconf bug. Until the bug is fixed you can use this workaround: CONFIG_SHELL=/bin/bash /bin/bash ./configure CONFIG_SHELL=/bin/bash `configure' Invocation ====================== `configure' recognizes the following options to control how it operates. `--help' `-h' Print a summary of all of the options to `configure', and exit. `--help=short' `--help=recursive' Print a summary of the options unique to this package's `configure', and exit. The `short' variant lists options used only in the top level, while the `recursive' variant lists options also present in any nested packages. `--version' `-V' Print the version of Autoconf used to generate the `configure' script, and exit. `--cache-file=FILE' Enable the cache: use and save the results of the tests in FILE, traditionally `config.cache'. FILE defaults to `/dev/null' to disable caching. `--config-cache' `-C' Alias for `--cache-file=config.cache'. `--quiet' `--silent' `-q' Do not print messages saying which checks are being made. To suppress all normal output, redirect it to `/dev/null' (any error messages will still be shown). `--srcdir=DIR' Look for the package's source code in directory DIR. Usually `configure' can determine that directory automatically. `--prefix=DIR' Use DIR as the installation prefix. *note Installation Names:: for more details, including other options available for fine-tuning the installation locations. `--no-create' `-n' Run the configure checks, but stop before creating any output files. `configure' also accepts some other, not widely useful, options. Run `configure --help' for more details. smalltalk-3.2.5/sigsegv/aclocal.m40000644000175000017500000010606712130455552013751 00000000000000# generated automatically by aclocal 1.11.6 -*- Autoconf -*- # Copyright (C) 1996, 1997, 1998, 1999, 2000, 2001, 2002, 2003, 2004, # 2005, 2006, 2007, 2008, 2009, 2010, 2011 Free Software Foundation, # Inc. # This file is free software; the Free Software Foundation # gives unlimited permission to copy and/or distribute it, # with or without modifications, as long as this notice is preserved. # This program is distributed in the hope that it will be useful, # but WITHOUT ANY WARRANTY, to the extent permitted by law; without # even the implied warranty of MERCHANTABILITY or FITNESS FOR A # PARTICULAR PURPOSE. m4_ifndef([AC_AUTOCONF_VERSION], [m4_copy([m4_PACKAGE_VERSION], [AC_AUTOCONF_VERSION])])dnl m4_if(m4_defn([AC_AUTOCONF_VERSION]), [2.69],, [m4_warning([this file was generated for autoconf 2.69. You have another version of autoconf. It may work, but is not guaranteed to. If you have problems, you may need to regenerate the build system entirely. To do so, use the procedure documented by the package, typically `autoreconf'.])]) # Copyright (C) 2002, 2003, 2005, 2006, 2007, 2008, 2011 Free Software # Foundation, Inc. # # This file is free software; the Free Software Foundation # gives unlimited permission to copy and/or distribute it, # with or without modifications, as long as this notice is preserved. # serial 1 # AM_AUTOMAKE_VERSION(VERSION) # ---------------------------- # Automake X.Y traces this macro to ensure aclocal.m4 has been # generated from the m4 files accompanying Automake X.Y. # (This private macro should not be called outside this file.) AC_DEFUN([AM_AUTOMAKE_VERSION], [am__api_version='1.11' dnl Some users find AM_AUTOMAKE_VERSION and mistake it for a way to dnl require some minimum version. Point them to the right macro. m4_if([$1], [1.11.6], [], [AC_FATAL([Do not call $0, use AM_INIT_AUTOMAKE([$1]).])])dnl ]) # _AM_AUTOCONF_VERSION(VERSION) # ----------------------------- # aclocal traces this macro to find the Autoconf version. # This is a private macro too. Using m4_define simplifies # the logic in aclocal, which can simply ignore this definition. m4_define([_AM_AUTOCONF_VERSION], []) # AM_SET_CURRENT_AUTOMAKE_VERSION # ------------------------------- # Call AM_AUTOMAKE_VERSION and AM_AUTOMAKE_VERSION so they can be traced. # This function is AC_REQUIREd by AM_INIT_AUTOMAKE. AC_DEFUN([AM_SET_CURRENT_AUTOMAKE_VERSION], [AM_AUTOMAKE_VERSION([1.11.6])dnl m4_ifndef([AC_AUTOCONF_VERSION], [m4_copy([m4_PACKAGE_VERSION], [AC_AUTOCONF_VERSION])])dnl _AM_AUTOCONF_VERSION(m4_defn([AC_AUTOCONF_VERSION]))]) # AM_AUX_DIR_EXPAND -*- Autoconf -*- # Copyright (C) 2001, 2003, 2005, 2011 Free Software Foundation, Inc. # # This file is free software; the Free Software Foundation # gives unlimited permission to copy and/or distribute it, # with or without modifications, as long as this notice is preserved. # serial 1 # For projects using AC_CONFIG_AUX_DIR([foo]), Autoconf sets # $ac_aux_dir to `$srcdir/foo'. In other projects, it is set to # `$srcdir', `$srcdir/..', or `$srcdir/../..'. # # Of course, Automake must honor this variable whenever it calls a # tool from the auxiliary directory. The problem is that $srcdir (and # therefore $ac_aux_dir as well) can be either absolute or relative, # depending on how configure is run. This is pretty annoying, since # it makes $ac_aux_dir quite unusable in subdirectories: in the top # source directory, any form will work fine, but in subdirectories a # relative path needs to be adjusted first. # # $ac_aux_dir/missing # fails when called from a subdirectory if $ac_aux_dir is relative # $top_srcdir/$ac_aux_dir/missing # fails if $ac_aux_dir is absolute, # fails when called from a subdirectory in a VPATH build with # a relative $ac_aux_dir # # The reason of the latter failure is that $top_srcdir and $ac_aux_dir # are both prefixed by $srcdir. In an in-source build this is usually # harmless because $srcdir is `.', but things will broke when you # start a VPATH build or use an absolute $srcdir. # # So we could use something similar to $top_srcdir/$ac_aux_dir/missing, # iff we strip the leading $srcdir from $ac_aux_dir. That would be: # am_aux_dir='\$(top_srcdir)/'`expr "$ac_aux_dir" : "$srcdir//*\(.*\)"` # and then we would define $MISSING as # MISSING="\${SHELL} $am_aux_dir/missing" # This will work as long as MISSING is not called from configure, because # unfortunately $(top_srcdir) has no meaning in configure. # However there are other variables, like CC, which are often used in # configure, and could therefore not use this "fixed" $ac_aux_dir. # # Another solution, used here, is to always expand $ac_aux_dir to an # absolute PATH. The drawback is that using absolute paths prevent a # configured tree to be moved without reconfiguration. AC_DEFUN([AM_AUX_DIR_EXPAND], [dnl Rely on autoconf to set up CDPATH properly. AC_PREREQ([2.50])dnl # expand $ac_aux_dir to an absolute path am_aux_dir=`cd $ac_aux_dir && pwd` ]) # AM_CONDITIONAL -*- Autoconf -*- # Copyright (C) 1997, 2000, 2001, 2003, 2004, 2005, 2006, 2008 # Free Software Foundation, Inc. # # This file is free software; the Free Software Foundation # gives unlimited permission to copy and/or distribute it, # with or without modifications, as long as this notice is preserved. # serial 9 # AM_CONDITIONAL(NAME, SHELL-CONDITION) # ------------------------------------- # Define a conditional. AC_DEFUN([AM_CONDITIONAL], [AC_PREREQ(2.52)dnl ifelse([$1], [TRUE], [AC_FATAL([$0: invalid condition: $1])], [$1], [FALSE], [AC_FATAL([$0: invalid condition: $1])])dnl AC_SUBST([$1_TRUE])dnl AC_SUBST([$1_FALSE])dnl _AM_SUBST_NOTMAKE([$1_TRUE])dnl _AM_SUBST_NOTMAKE([$1_FALSE])dnl m4_define([_AM_COND_VALUE_$1], [$2])dnl if $2; then $1_TRUE= $1_FALSE='#' else $1_TRUE='#' $1_FALSE= fi AC_CONFIG_COMMANDS_PRE( [if test -z "${$1_TRUE}" && test -z "${$1_FALSE}"; then AC_MSG_ERROR([[conditional "$1" was never defined. Usually this means the macro was only invoked conditionally.]]) fi])]) # Copyright (C) 1999, 2000, 2001, 2002, 2003, 2004, 2005, 2006, 2009, # 2010, 2011 Free Software Foundation, Inc. # # This file is free software; the Free Software Foundation # gives unlimited permission to copy and/or distribute it, # with or without modifications, as long as this notice is preserved. # serial 12 # There are a few dirty hacks below to avoid letting `AC_PROG_CC' be # written in clear, in which case automake, when reading aclocal.m4, # will think it sees a *use*, and therefore will trigger all it's # C support machinery. Also note that it means that autoscan, seeing # CC etc. in the Makefile, will ask for an AC_PROG_CC use... # _AM_DEPENDENCIES(NAME) # ---------------------- # See how the compiler implements dependency checking. # NAME is "CC", "CXX", "GCJ", or "OBJC". # We try a few techniques and use that to set a single cache variable. # # We don't AC_REQUIRE the corresponding AC_PROG_CC since the latter was # modified to invoke _AM_DEPENDENCIES(CC); we would have a circular # dependency, and given that the user is not expected to run this macro, # just rely on AC_PROG_CC. AC_DEFUN([_AM_DEPENDENCIES], [AC_REQUIRE([AM_SET_DEPDIR])dnl AC_REQUIRE([AM_OUTPUT_DEPENDENCY_COMMANDS])dnl AC_REQUIRE([AM_MAKE_INCLUDE])dnl AC_REQUIRE([AM_DEP_TRACK])dnl ifelse([$1], CC, [depcc="$CC" am_compiler_list=], [$1], CXX, [depcc="$CXX" am_compiler_list=], [$1], OBJC, [depcc="$OBJC" am_compiler_list='gcc3 gcc'], [$1], UPC, [depcc="$UPC" am_compiler_list=], [$1], GCJ, [depcc="$GCJ" am_compiler_list='gcc3 gcc'], [depcc="$$1" am_compiler_list=]) AC_CACHE_CHECK([dependency style of $depcc], [am_cv_$1_dependencies_compiler_type], [if test -z "$AMDEP_TRUE" && test -f "$am_depcomp"; then # We make a subdir and do the tests there. Otherwise we can end up # making bogus files that we don't know about and never remove. For # instance it was reported that on HP-UX the gcc test will end up # making a dummy file named `D' -- because `-MD' means `put the output # in D'. rm -rf conftest.dir mkdir conftest.dir # Copy depcomp to subdir because otherwise we won't find it if we're # using a relative directory. cp "$am_depcomp" conftest.dir cd conftest.dir # We will build objects and dependencies in a subdirectory because # it helps to detect inapplicable dependency modes. For instance # both Tru64's cc and ICC support -MD to output dependencies as a # side effect of compilation, but ICC will put the dependencies in # the current directory while Tru64 will put them in the object # directory. mkdir sub am_cv_$1_dependencies_compiler_type=none if test "$am_compiler_list" = ""; then am_compiler_list=`sed -n ['s/^#*\([a-zA-Z0-9]*\))$/\1/p'] < ./depcomp` fi am__universal=false m4_case([$1], [CC], [case " $depcc " in #( *\ -arch\ *\ -arch\ *) am__universal=true ;; esac], [CXX], [case " $depcc " in #( *\ -arch\ *\ -arch\ *) am__universal=true ;; esac]) for depmode in $am_compiler_list; do # Setup a source with many dependencies, because some compilers # like to wrap large dependency lists on column 80 (with \), and # we should not choose a depcomp mode which is confused by this. # # We need to recreate these files for each test, as the compiler may # overwrite some of them when testing with obscure command lines. # This happens at least with the AIX C compiler. : > sub/conftest.c for i in 1 2 3 4 5 6; do echo '#include "conftst'$i'.h"' >> sub/conftest.c # Using `: > sub/conftst$i.h' creates only sub/conftst1.h with # Solaris 8's {/usr,}/bin/sh. touch sub/conftst$i.h done echo "${am__include} ${am__quote}sub/conftest.Po${am__quote}" > confmf # We check with `-c' and `-o' for the sake of the "dashmstdout" # mode. It turns out that the SunPro C++ compiler does not properly # handle `-M -o', and we need to detect this. Also, some Intel # versions had trouble with output in subdirs am__obj=sub/conftest.${OBJEXT-o} am__minus_obj="-o $am__obj" case $depmode in gcc) # This depmode causes a compiler race in universal mode. test "$am__universal" = false || continue ;; nosideeffect) # after this tag, mechanisms are not by side-effect, so they'll # only be used when explicitly requested if test "x$enable_dependency_tracking" = xyes; then continue else break fi ;; msvc7 | msvc7msys | msvisualcpp | msvcmsys) # This compiler won't grok `-c -o', but also, the minuso test has # not run yet. These depmodes are late enough in the game, and # so weak that their functioning should not be impacted. am__obj=conftest.${OBJEXT-o} am__minus_obj= ;; none) break ;; esac if depmode=$depmode \ source=sub/conftest.c object=$am__obj \ depfile=sub/conftest.Po tmpdepfile=sub/conftest.TPo \ $SHELL ./depcomp $depcc -c $am__minus_obj sub/conftest.c \ >/dev/null 2>conftest.err && grep sub/conftst1.h sub/conftest.Po > /dev/null 2>&1 && grep sub/conftst6.h sub/conftest.Po > /dev/null 2>&1 && grep $am__obj sub/conftest.Po > /dev/null 2>&1 && ${MAKE-make} -s -f confmf > /dev/null 2>&1; then # icc doesn't choke on unknown options, it will just issue warnings # or remarks (even with -Werror). So we grep stderr for any message # that says an option was ignored or not supported. # When given -MP, icc 7.0 and 7.1 complain thusly: # icc: Command line warning: ignoring option '-M'; no argument required # The diagnosis changed in icc 8.0: # icc: Command line remark: option '-MP' not supported if (grep 'ignoring option' conftest.err || grep 'not supported' conftest.err) >/dev/null 2>&1; then :; else am_cv_$1_dependencies_compiler_type=$depmode break fi fi done cd .. rm -rf conftest.dir else am_cv_$1_dependencies_compiler_type=none fi ]) AC_SUBST([$1DEPMODE], [depmode=$am_cv_$1_dependencies_compiler_type]) AM_CONDITIONAL([am__fastdep$1], [ test "x$enable_dependency_tracking" != xno \ && test "$am_cv_$1_dependencies_compiler_type" = gcc3]) ]) # AM_SET_DEPDIR # ------------- # Choose a directory name for dependency files. # This macro is AC_REQUIREd in _AM_DEPENDENCIES AC_DEFUN([AM_SET_DEPDIR], [AC_REQUIRE([AM_SET_LEADING_DOT])dnl AC_SUBST([DEPDIR], ["${am__leading_dot}deps"])dnl ]) # AM_DEP_TRACK # ------------ AC_DEFUN([AM_DEP_TRACK], [AC_ARG_ENABLE(dependency-tracking, [ --disable-dependency-tracking speeds up one-time build --enable-dependency-tracking do not reject slow dependency extractors]) if test "x$enable_dependency_tracking" != xno; then am_depcomp="$ac_aux_dir/depcomp" AMDEPBACKSLASH='\' am__nodep='_no' fi AM_CONDITIONAL([AMDEP], [test "x$enable_dependency_tracking" != xno]) AC_SUBST([AMDEPBACKSLASH])dnl _AM_SUBST_NOTMAKE([AMDEPBACKSLASH])dnl AC_SUBST([am__nodep])dnl _AM_SUBST_NOTMAKE([am__nodep])dnl ]) # Generate code to set up dependency tracking. -*- Autoconf -*- # Copyright (C) 1999, 2000, 2001, 2002, 2003, 2004, 2005, 2008 # Free Software Foundation, Inc. # # This file is free software; the Free Software Foundation # gives unlimited permission to copy and/or distribute it, # with or without modifications, as long as this notice is preserved. #serial 5 # _AM_OUTPUT_DEPENDENCY_COMMANDS # ------------------------------ AC_DEFUN([_AM_OUTPUT_DEPENDENCY_COMMANDS], [{ # Autoconf 2.62 quotes --file arguments for eval, but not when files # are listed without --file. Let's play safe and only enable the eval # if we detect the quoting. case $CONFIG_FILES in *\'*) eval set x "$CONFIG_FILES" ;; *) set x $CONFIG_FILES ;; esac shift for mf do # Strip MF so we end up with the name of the file. mf=`echo "$mf" | sed -e 's/:.*$//'` # Check whether this is an Automake generated Makefile or not. # We used to match only the files named `Makefile.in', but # some people rename them; so instead we look at the file content. # Grep'ing the first line is not enough: some people post-process # each Makefile.in and add a new line on top of each file to say so. # Grep'ing the whole file is not good either: AIX grep has a line # limit of 2048, but all sed's we know have understand at least 4000. if sed -n 's,^#.*generated by automake.*,X,p' "$mf" | grep X >/dev/null 2>&1; then dirpart=`AS_DIRNAME("$mf")` else continue fi # Extract the definition of DEPDIR, am__include, and am__quote # from the Makefile without running `make'. DEPDIR=`sed -n 's/^DEPDIR = //p' < "$mf"` test -z "$DEPDIR" && continue am__include=`sed -n 's/^am__include = //p' < "$mf"` test -z "am__include" && continue am__quote=`sed -n 's/^am__quote = //p' < "$mf"` # When using ansi2knr, U may be empty or an underscore; expand it U=`sed -n 's/^U = //p' < "$mf"` # Find all dependency output files, they are included files with # $(DEPDIR) in their names. We invoke sed twice because it is the # simplest approach to changing $(DEPDIR) to its actual value in the # expansion. for file in `sed -n " s/^$am__include $am__quote\(.*(DEPDIR).*\)$am__quote"'$/\1/p' <"$mf" | \ sed -e 's/\$(DEPDIR)/'"$DEPDIR"'/g' -e 's/\$U/'"$U"'/g'`; do # Make sure the directory exists. test -f "$dirpart/$file" && continue fdir=`AS_DIRNAME(["$file"])` AS_MKDIR_P([$dirpart/$fdir]) # echo "creating $dirpart/$file" echo '# dummy' > "$dirpart/$file" done done } ])# _AM_OUTPUT_DEPENDENCY_COMMANDS # AM_OUTPUT_DEPENDENCY_COMMANDS # ----------------------------- # This macro should only be invoked once -- use via AC_REQUIRE. # # This code is only required when automatic dependency tracking # is enabled. FIXME. This creates each `.P' file that we will # need in order to bootstrap the dependency handling code. AC_DEFUN([AM_OUTPUT_DEPENDENCY_COMMANDS], [AC_CONFIG_COMMANDS([depfiles], [test x"$AMDEP_TRUE" != x"" || _AM_OUTPUT_DEPENDENCY_COMMANDS], [AMDEP_TRUE="$AMDEP_TRUE" ac_aux_dir="$ac_aux_dir"]) ]) # Copyright (C) 1996, 1997, 2000, 2001, 2003, 2005 # Free Software Foundation, Inc. # # This file is free software; the Free Software Foundation # gives unlimited permission to copy and/or distribute it, # with or without modifications, as long as this notice is preserved. # serial 8 # AM_CONFIG_HEADER is obsolete. It has been replaced by AC_CONFIG_HEADERS. AU_DEFUN([AM_CONFIG_HEADER], [AC_CONFIG_HEADERS($@)]) # Do all the work for Automake. -*- Autoconf -*- # Copyright (C) 1996, 1997, 1998, 1999, 2000, 2001, 2002, 2003, 2004, # 2005, 2006, 2008, 2009 Free Software Foundation, Inc. # # This file is free software; the Free Software Foundation # gives unlimited permission to copy and/or distribute it, # with or without modifications, as long as this notice is preserved. # serial 16 # This macro actually does too much. Some checks are only needed if # your package does certain things. But this isn't really a big deal. # AM_INIT_AUTOMAKE(PACKAGE, VERSION, [NO-DEFINE]) # AM_INIT_AUTOMAKE([OPTIONS]) # ----------------------------------------------- # The call with PACKAGE and VERSION arguments is the old style # call (pre autoconf-2.50), which is being phased out. PACKAGE # and VERSION should now be passed to AC_INIT and removed from # the call to AM_INIT_AUTOMAKE. # We support both call styles for the transition. After # the next Automake release, Autoconf can make the AC_INIT # arguments mandatory, and then we can depend on a new Autoconf # release and drop the old call support. AC_DEFUN([AM_INIT_AUTOMAKE], [AC_PREREQ([2.62])dnl dnl Autoconf wants to disallow AM_ names. We explicitly allow dnl the ones we care about. m4_pattern_allow([^AM_[A-Z]+FLAGS$])dnl AC_REQUIRE([AM_SET_CURRENT_AUTOMAKE_VERSION])dnl AC_REQUIRE([AC_PROG_INSTALL])dnl if test "`cd $srcdir && pwd`" != "`pwd`"; then # Use -I$(srcdir) only when $(srcdir) != ., so that make's output # is not polluted with repeated "-I." AC_SUBST([am__isrc], [' -I$(srcdir)'])_AM_SUBST_NOTMAKE([am__isrc])dnl # test to see if srcdir already configured if test -f $srcdir/config.status; then AC_MSG_ERROR([source directory already configured; run "make distclean" there first]) fi fi # test whether we have cygpath if test -z "$CYGPATH_W"; then if (cygpath --version) >/dev/null 2>/dev/null; then CYGPATH_W='cygpath -w' else CYGPATH_W=echo fi fi AC_SUBST([CYGPATH_W]) # Define the identity of the package. dnl Distinguish between old-style and new-style calls. m4_ifval([$2], [m4_ifval([$3], [_AM_SET_OPTION([no-define])])dnl AC_SUBST([PACKAGE], [$1])dnl AC_SUBST([VERSION], [$2])], [_AM_SET_OPTIONS([$1])dnl dnl Diagnose old-style AC_INIT with new-style AM_AUTOMAKE_INIT. m4_if(m4_ifdef([AC_PACKAGE_NAME], 1)m4_ifdef([AC_PACKAGE_VERSION], 1), 11,, [m4_fatal([AC_INIT should be called with package and version arguments])])dnl AC_SUBST([PACKAGE], ['AC_PACKAGE_TARNAME'])dnl AC_SUBST([VERSION], ['AC_PACKAGE_VERSION'])])dnl _AM_IF_OPTION([no-define],, [AC_DEFINE_UNQUOTED(PACKAGE, "$PACKAGE", [Name of package]) AC_DEFINE_UNQUOTED(VERSION, "$VERSION", [Version number of package])])dnl # Some tools Automake needs. AC_REQUIRE([AM_SANITY_CHECK])dnl AC_REQUIRE([AC_ARG_PROGRAM])dnl AM_MISSING_PROG(ACLOCAL, aclocal-${am__api_version}) AM_MISSING_PROG(AUTOCONF, autoconf) AM_MISSING_PROG(AUTOMAKE, automake-${am__api_version}) AM_MISSING_PROG(AUTOHEADER, autoheader) AM_MISSING_PROG(MAKEINFO, makeinfo) AC_REQUIRE([AM_PROG_INSTALL_SH])dnl AC_REQUIRE([AM_PROG_INSTALL_STRIP])dnl AC_REQUIRE([AM_PROG_MKDIR_P])dnl # We need awk for the "check" target. The system "awk" is bad on # some platforms. AC_REQUIRE([AC_PROG_AWK])dnl AC_REQUIRE([AC_PROG_MAKE_SET])dnl AC_REQUIRE([AM_SET_LEADING_DOT])dnl _AM_IF_OPTION([tar-ustar], [_AM_PROG_TAR([ustar])], [_AM_IF_OPTION([tar-pax], [_AM_PROG_TAR([pax])], [_AM_PROG_TAR([v7])])]) _AM_IF_OPTION([no-dependencies],, [AC_PROVIDE_IFELSE([AC_PROG_CC], [_AM_DEPENDENCIES(CC)], [define([AC_PROG_CC], defn([AC_PROG_CC])[_AM_DEPENDENCIES(CC)])])dnl AC_PROVIDE_IFELSE([AC_PROG_CXX], [_AM_DEPENDENCIES(CXX)], [define([AC_PROG_CXX], defn([AC_PROG_CXX])[_AM_DEPENDENCIES(CXX)])])dnl AC_PROVIDE_IFELSE([AC_PROG_OBJC], [_AM_DEPENDENCIES(OBJC)], [define([AC_PROG_OBJC], defn([AC_PROG_OBJC])[_AM_DEPENDENCIES(OBJC)])])dnl ]) _AM_IF_OPTION([silent-rules], [AC_REQUIRE([AM_SILENT_RULES])])dnl dnl The `parallel-tests' driver may need to know about EXEEXT, so add the dnl `am__EXEEXT' conditional if _AM_COMPILER_EXEEXT was seen. This macro dnl is hooked onto _AC_COMPILER_EXEEXT early, see below. AC_CONFIG_COMMANDS_PRE(dnl [m4_provide_if([_AM_COMPILER_EXEEXT], [AM_CONDITIONAL([am__EXEEXT], [test -n "$EXEEXT"])])])dnl ]) dnl Hook into `_AC_COMPILER_EXEEXT' early to learn its expansion. Do not dnl add the conditional right here, as _AC_COMPILER_EXEEXT may be further dnl mangled by Autoconf and run in a shell conditional statement. m4_define([_AC_COMPILER_EXEEXT], m4_defn([_AC_COMPILER_EXEEXT])[m4_provide([_AM_COMPILER_EXEEXT])]) # When config.status generates a header, we must update the stamp-h file. # This file resides in the same directory as the config header # that is generated. The stamp files are numbered to have different names. # Autoconf calls _AC_AM_CONFIG_HEADER_HOOK (when defined) in the # loop where config.status creates the headers, so we can generate # our stamp files there. AC_DEFUN([_AC_AM_CONFIG_HEADER_HOOK], [# Compute $1's index in $config_headers. _am_arg=$1 _am_stamp_count=1 for _am_header in $config_headers :; do case $_am_header in $_am_arg | $_am_arg:* ) break ;; * ) _am_stamp_count=`expr $_am_stamp_count + 1` ;; esac done echo "timestamp for $_am_arg" >`AS_DIRNAME(["$_am_arg"])`/stamp-h[]$_am_stamp_count]) # Copyright (C) 2001, 2003, 2005, 2008, 2011 Free Software Foundation, # Inc. # # This file is free software; the Free Software Foundation # gives unlimited permission to copy and/or distribute it, # with or without modifications, as long as this notice is preserved. # serial 1 # AM_PROG_INSTALL_SH # ------------------ # Define $install_sh. AC_DEFUN([AM_PROG_INSTALL_SH], [AC_REQUIRE([AM_AUX_DIR_EXPAND])dnl if test x"${install_sh}" != xset; then case $am_aux_dir in *\ * | *\ *) install_sh="\${SHELL} '$am_aux_dir/install-sh'" ;; *) install_sh="\${SHELL} $am_aux_dir/install-sh" esac fi AC_SUBST(install_sh)]) # Copyright (C) 2003, 2005 Free Software Foundation, Inc. # # This file is free software; the Free Software Foundation # gives unlimited permission to copy and/or distribute it, # with or without modifications, as long as this notice is preserved. # serial 2 # Check whether the underlying file-system supports filenames # with a leading dot. For instance MS-DOS doesn't. AC_DEFUN([AM_SET_LEADING_DOT], [rm -rf .tst 2>/dev/null mkdir .tst 2>/dev/null if test -d .tst; then am__leading_dot=. else am__leading_dot=_ fi rmdir .tst 2>/dev/null AC_SUBST([am__leading_dot])]) # Check to see how 'make' treats includes. -*- Autoconf -*- # Copyright (C) 2001, 2002, 2003, 2005, 2009 Free Software Foundation, Inc. # # This file is free software; the Free Software Foundation # gives unlimited permission to copy and/or distribute it, # with or without modifications, as long as this notice is preserved. # serial 4 # AM_MAKE_INCLUDE() # ----------------- # Check to see how make treats includes. AC_DEFUN([AM_MAKE_INCLUDE], [am_make=${MAKE-make} cat > confinc << 'END' am__doit: @echo this is the am__doit target .PHONY: am__doit END # If we don't find an include directive, just comment out the code. AC_MSG_CHECKING([for style of include used by $am_make]) am__include="#" am__quote= _am_result=none # First try GNU make style include. echo "include confinc" > confmf # Ignore all kinds of additional output from `make'. case `$am_make -s -f confmf 2> /dev/null` in #( *the\ am__doit\ target*) am__include=include am__quote= _am_result=GNU ;; esac # Now try BSD make style include. if test "$am__include" = "#"; then echo '.include "confinc"' > confmf case `$am_make -s -f confmf 2> /dev/null` in #( *the\ am__doit\ target*) am__include=.include am__quote="\"" _am_result=BSD ;; esac fi AC_SUBST([am__include]) AC_SUBST([am__quote]) AC_MSG_RESULT([$_am_result]) rm -f confinc confmf ]) # Fake the existence of programs that GNU maintainers use. -*- Autoconf -*- # Copyright (C) 1997, 1999, 2000, 2001, 2003, 2004, 2005, 2008 # Free Software Foundation, Inc. # # This file is free software; the Free Software Foundation # gives unlimited permission to copy and/or distribute it, # with or without modifications, as long as this notice is preserved. # serial 6 # AM_MISSING_PROG(NAME, PROGRAM) # ------------------------------ AC_DEFUN([AM_MISSING_PROG], [AC_REQUIRE([AM_MISSING_HAS_RUN]) $1=${$1-"${am_missing_run}$2"} AC_SUBST($1)]) # AM_MISSING_HAS_RUN # ------------------ # Define MISSING if not defined so far and test if it supports --run. # If it does, set am_missing_run to use it, otherwise, to nothing. AC_DEFUN([AM_MISSING_HAS_RUN], [AC_REQUIRE([AM_AUX_DIR_EXPAND])dnl AC_REQUIRE_AUX_FILE([missing])dnl if test x"${MISSING+set}" != xset; then case $am_aux_dir in *\ * | *\ *) MISSING="\${SHELL} \"$am_aux_dir/missing\"" ;; *) MISSING="\${SHELL} $am_aux_dir/missing" ;; esac fi # Use eval to expand $SHELL if eval "$MISSING --run true"; then am_missing_run="$MISSING --run " else am_missing_run= AC_MSG_WARN([`missing' script is too old or missing]) fi ]) # Copyright (C) 2003, 2004, 2005, 2006, 2011 Free Software Foundation, # Inc. # # This file is free software; the Free Software Foundation # gives unlimited permission to copy and/or distribute it, # with or without modifications, as long as this notice is preserved. # serial 1 # AM_PROG_MKDIR_P # --------------- # Check for `mkdir -p'. AC_DEFUN([AM_PROG_MKDIR_P], [AC_PREREQ([2.60])dnl AC_REQUIRE([AC_PROG_MKDIR_P])dnl dnl Automake 1.8 to 1.9.6 used to define mkdir_p. We now use MKDIR_P, dnl while keeping a definition of mkdir_p for backward compatibility. dnl @MKDIR_P@ is magic: AC_OUTPUT adjusts its value for each Makefile. dnl However we cannot define mkdir_p as $(MKDIR_P) for the sake of dnl Makefile.ins that do not define MKDIR_P, so we do our own dnl adjustment using top_builddir (which is defined more often than dnl MKDIR_P). AC_SUBST([mkdir_p], ["$MKDIR_P"])dnl case $mkdir_p in [[\\/$]]* | ?:[[\\/]]*) ;; */*) mkdir_p="\$(top_builddir)/$mkdir_p" ;; esac ]) # Helper functions for option handling. -*- Autoconf -*- # Copyright (C) 2001, 2002, 2003, 2005, 2008, 2010 Free Software # Foundation, Inc. # # This file is free software; the Free Software Foundation # gives unlimited permission to copy and/or distribute it, # with or without modifications, as long as this notice is preserved. # serial 5 # _AM_MANGLE_OPTION(NAME) # ----------------------- AC_DEFUN([_AM_MANGLE_OPTION], [[_AM_OPTION_]m4_bpatsubst($1, [[^a-zA-Z0-9_]], [_])]) # _AM_SET_OPTION(NAME) # -------------------- # Set option NAME. Presently that only means defining a flag for this option. AC_DEFUN([_AM_SET_OPTION], [m4_define(_AM_MANGLE_OPTION([$1]), 1)]) # _AM_SET_OPTIONS(OPTIONS) # ------------------------ # OPTIONS is a space-separated list of Automake options. AC_DEFUN([_AM_SET_OPTIONS], [m4_foreach_w([_AM_Option], [$1], [_AM_SET_OPTION(_AM_Option)])]) # _AM_IF_OPTION(OPTION, IF-SET, [IF-NOT-SET]) # ------------------------------------------- # Execute IF-SET if OPTION is set, IF-NOT-SET otherwise. AC_DEFUN([_AM_IF_OPTION], [m4_ifset(_AM_MANGLE_OPTION([$1]), [$2], [$3])]) # Check to make sure that the build environment is sane. -*- Autoconf -*- # Copyright (C) 1996, 1997, 2000, 2001, 2003, 2005, 2008 # Free Software Foundation, Inc. # # This file is free software; the Free Software Foundation # gives unlimited permission to copy and/or distribute it, # with or without modifications, as long as this notice is preserved. # serial 5 # AM_SANITY_CHECK # --------------- AC_DEFUN([AM_SANITY_CHECK], [AC_MSG_CHECKING([whether build environment is sane]) # Just in case sleep 1 echo timestamp > conftest.file # Reject unsafe characters in $srcdir or the absolute working directory # name. Accept space and tab only in the latter. am_lf=' ' case `pwd` in *[[\\\"\#\$\&\'\`$am_lf]]*) AC_MSG_ERROR([unsafe absolute working directory name]);; esac case $srcdir in *[[\\\"\#\$\&\'\`$am_lf\ \ ]]*) AC_MSG_ERROR([unsafe srcdir value: `$srcdir']);; esac # Do `set' in a subshell so we don't clobber the current shell's # arguments. Must try -L first in case configure is actually a # symlink; some systems play weird games with the mod time of symlinks # (eg FreeBSD returns the mod time of the symlink's containing # directory). if ( set X `ls -Lt "$srcdir/configure" conftest.file 2> /dev/null` if test "$[*]" = "X"; then # -L didn't work. set X `ls -t "$srcdir/configure" conftest.file` fi rm -f conftest.file if test "$[*]" != "X $srcdir/configure conftest.file" \ && test "$[*]" != "X conftest.file $srcdir/configure"; then # If neither matched, then we have a broken ls. This can happen # if, for instance, CONFIG_SHELL is bash and it inherits a # broken ls alias from the environment. This has actually # happened. Such a system could not be considered "sane". AC_MSG_ERROR([ls -t appears to fail. Make sure there is not a broken alias in your environment]) fi test "$[2]" = conftest.file ) then # Ok. : else AC_MSG_ERROR([newly created file is older than distributed files! Check your system clock]) fi AC_MSG_RESULT(yes)]) # Copyright (C) 2001, 2003, 2005, 2011 Free Software Foundation, Inc. # # This file is free software; the Free Software Foundation # gives unlimited permission to copy and/or distribute it, # with or without modifications, as long as this notice is preserved. # serial 1 # AM_PROG_INSTALL_STRIP # --------------------- # One issue with vendor `install' (even GNU) is that you can't # specify the program used to strip binaries. This is especially # annoying in cross-compiling environments, where the build's strip # is unlikely to handle the host's binaries. # Fortunately install-sh will honor a STRIPPROG variable, so we # always use install-sh in `make install-strip', and initialize # STRIPPROG with the value of the STRIP variable (set by the user). AC_DEFUN([AM_PROG_INSTALL_STRIP], [AC_REQUIRE([AM_PROG_INSTALL_SH])dnl # Installed binaries are usually stripped using `strip' when the user # run `make install-strip'. However `strip' might not be the right # tool to use in cross-compilation environments, therefore Automake # will honor the `STRIP' environment variable to overrule this program. dnl Don't test for $cross_compiling = yes, because it might be `maybe'. if test "$cross_compiling" != no; then AC_CHECK_TOOL([STRIP], [strip], :) fi INSTALL_STRIP_PROGRAM="\$(install_sh) -c -s" AC_SUBST([INSTALL_STRIP_PROGRAM])]) # Copyright (C) 2006, 2008, 2010 Free Software Foundation, Inc. # # This file is free software; the Free Software Foundation # gives unlimited permission to copy and/or distribute it, # with or without modifications, as long as this notice is preserved. # serial 3 # _AM_SUBST_NOTMAKE(VARIABLE) # --------------------------- # Prevent Automake from outputting VARIABLE = @VARIABLE@ in Makefile.in. # This macro is traced by Automake. AC_DEFUN([_AM_SUBST_NOTMAKE]) # AM_SUBST_NOTMAKE(VARIABLE) # -------------------------- # Public sister of _AM_SUBST_NOTMAKE. AC_DEFUN([AM_SUBST_NOTMAKE], [_AM_SUBST_NOTMAKE($@)]) # Check how to create a tarball. -*- Autoconf -*- # Copyright (C) 2004, 2005, 2012 Free Software Foundation, Inc. # # This file is free software; the Free Software Foundation # gives unlimited permission to copy and/or distribute it, # with or without modifications, as long as this notice is preserved. # serial 2 # _AM_PROG_TAR(FORMAT) # -------------------- # Check how to create a tarball in format FORMAT. # FORMAT should be one of `v7', `ustar', or `pax'. # # Substitute a variable $(am__tar) that is a command # writing to stdout a FORMAT-tarball containing the directory # $tardir. # tardir=directory && $(am__tar) > result.tar # # Substitute a variable $(am__untar) that extract such # a tarball read from stdin. # $(am__untar) < result.tar AC_DEFUN([_AM_PROG_TAR], [# Always define AMTAR for backward compatibility. Yes, it's still used # in the wild :-( We should find a proper way to deprecate it ... AC_SUBST([AMTAR], ['$${TAR-tar}']) m4_if([$1], [v7], [am__tar='$${TAR-tar} chof - "$$tardir"' am__untar='$${TAR-tar} xf -'], [m4_case([$1], [ustar],, [pax],, [m4_fatal([Unknown tar format])]) AC_MSG_CHECKING([how to create a $1 tar archive]) # Loop over all known methods to create a tar archive until one works. _am_tools='gnutar m4_if([$1], [ustar], [plaintar]) pax cpio none' _am_tools=${am_cv_prog_tar_$1-$_am_tools} # Do not fold the above two line into one, because Tru64 sh and # Solaris sh will not grok spaces in the rhs of `-'. for _am_tool in $_am_tools do case $_am_tool in gnutar) for _am_tar in tar gnutar gtar; do AM_RUN_LOG([$_am_tar --version]) && break done am__tar="$_am_tar --format=m4_if([$1], [pax], [posix], [$1]) -chf - "'"$$tardir"' am__tar_="$_am_tar --format=m4_if([$1], [pax], [posix], [$1]) -chf - "'"$tardir"' am__untar="$_am_tar -xf -" ;; plaintar) # Must skip GNU tar: if it does not support --format= it doesn't create # ustar tarball either. (tar --version) >/dev/null 2>&1 && continue am__tar='tar chf - "$$tardir"' am__tar_='tar chf - "$tardir"' am__untar='tar xf -' ;; pax) am__tar='pax -L -x $1 -w "$$tardir"' am__tar_='pax -L -x $1 -w "$tardir"' am__untar='pax -r' ;; cpio) am__tar='find "$$tardir" -print | cpio -o -H $1 -L' am__tar_='find "$tardir" -print | cpio -o -H $1 -L' am__untar='cpio -i -H $1 -d' ;; none) am__tar=false am__tar_=false am__untar=false ;; esac # If the value was cached, stop now. We just wanted to have am__tar # and am__untar set. test -n "${am_cv_prog_tar_$1}" && break # tar/untar a dummy directory, and stop if the command works rm -rf conftest.dir mkdir conftest.dir echo GrepMe > conftest.dir/file AM_RUN_LOG([tardir=conftest.dir && eval $am__tar_ >conftest.tar]) rm -rf conftest.dir if test -s conftest.tar; then AM_RUN_LOG([$am__untar /dev/null 2>&1 && break fi done rm -rf conftest.dir AC_CACHE_VAL([am_cv_prog_tar_$1], [am_cv_prog_tar_$1=$_am_tool]) AC_MSG_RESULT([$am_cv_prog_tar_$1])]) AC_SUBST([am__tar]) AC_SUBST([am__untar]) ]) # _AM_PROG_TAR m4_include([../build-aux/bold.m4]) m4_include([../build-aux/fault.m4]) m4_include([../build-aux/getpagesize.m4]) m4_include([../build-aux/libtool.m4]) m4_include([../build-aux/ltoptions.m4]) m4_include([../build-aux/ltsugar.m4]) m4_include([../build-aux/ltversion.m4]) m4_include([../build-aux/lt~obsolete.m4]) m4_include([../build-aux/mmap-anon.m4]) m4_include([../build-aux/relocatable.m4]) m4_include([../build-aux/sigaltstack-longjmp.m4]) m4_include([../build-aux/sigaltstack-siglongjmp.m4]) m4_include([../build-aux/sigaltstack.m4]) smalltalk-3.2.5/sigsegv/ChangeLog0000644000175000017500000005202212130343734013650 000000000000002009-09-22 Paolo Bonzini Fix crash of stackoverflow2 on x86_64-linux. * tests/stackoverflow1.c: Make mystack global. * tests/stackoverflow2.c: Likewise. 2008-10-19 Paolo Bonzini * configure.ac: Test for vm_region before using stackvma-mach.c. 2008-01-20 Paolo Bonzini * src/machfault-macos-i386.h (SIGSEGV_EXC_STATE_TYPE, SIGSEGV_EXC_STATE_FLAVOR, SIGSEGV_EXC_STATE_COUNT, SIGSEGV_FAULT_ADDRESS): Define if _LP64 defined. * src/machfault-macos-powerpc.h: Likewise. * src/machfault.h (SIGSEGV_FAULT_ADDRESS): Provide default definition. 2008-01-19 Paolo Bonzini * src/handler-macos.c (call_user_handler): New. (catch_exception_raise): Do two-phase call of the user handler as in handler-unix.c, for speed. Pass CODE instead of the thread_state to SIGSEGV_FAULT_ADDRESS. * src/machfault-macos-i386.h (SIGSEGV_EXC_STATE_TYPE, SIGSEGV_EXC_STATE_FLAVOR, SIGSEGV_EXC_STATE_COUNT): Remove. (SIGSEGV_FAULT_ADDRESS): Use code[1]. * src/machfault-macos-powerpc.h: Likewise. 2007-11-16 Bruno Haible * src/fault-freebsd-i386.h (SIGSEGV_FAULT_STACKPOINTER): Use sc_rsp also on x86_64-freebsd platform. Reported by Dmitri Hrapof and Petr Salinger . 2007-11-15 Bruno Haible * configure.ac (CFG_SIGNALS, CFG_FAULT): Port to i586-kfreebsd-gnu and x86_64-kfreebsd-gnu. * src/fault-freebsd-i386.h (SIGSEGV_FAULT_STACKPOINTER): Likewise. Based on patch by Petr Salinger . 2007-11-11 Bruno Haible * Version 2.5 released. 2007-11-11 Bruno Haible * configure.ac: Bump version number to 2.5. * src/sigsegv.h.in (LIBSIGSEGV_VERSION): Likewise. 2007-10-28 Bruno Haible * src/handler-macos.c (catch_exception_raise): Align the new stack pointer on a 16-byte boundary. * src/handler-win32.c (main_exception_filter): Correct alignment: %esp must be aligned to == -4 mod 16 upon function entry. 2007-10-28 Bruno Haible * src/sigsegv.h.in (stackoverflow_install_handler): Avoid comment inside comment. Reported by Chris Willmore . 2007-10-28 Bruno Haible * src/machfault-macos-powerpc.h (SIGSEGV_FAULT_ADDRESS, SIGSEGV_STACK_POINTER, SIGSEGV_PROGRAM_COUNTER): Add __DARWIN_UNIX03 conditional. * src/machfault-macos-i386.h (SIGSEGV_FAULT_ADDRESS, SIGSEGV_STACK_POINTER, SIGSEGV_PROGRAM_COUNTER): Likewise. * src/fault-macosdarwin7-powerpc.h (SIGSEGV_FAULT_STACKPOINTER): Likewise. * src/fault-macosdarwin7-powerpc.c (get_fault_addr): Likewise. Reported by Chris Willmore . 2007-01-12 Bruno Haible * Makefile.am (check-next): Don't ask for reports from x86_64-*-linux* platforms. 2006-07-14 Bruno Haible * m4/sigaltstack.m4 (SV_SIGALTSTACK): Use SIGSTKSZ instead of hardcoding 16384. * m4/sigaltstack-longjmp.m4 (SV_TRY_LEAVE_HANDLER_LONGJMP): Likewise. * m4/sigaltstack-siglongjmp.m4 (SV_TRY_LEAVE_HANDLER_SIGLONGJMP): Likewise. * tests/stackoverflow1.c (main): Likewise. * tests/stackoverflow2.c (main): Likewise. * src/sigsegv.h.in (stackoverflow_install_handler): Update recommendation for extra_stack_size. Needed for ia64. Reported by Peter Van Eynde . 2006-06-23 Bruno Haible * Version 2.4 released. 2006-06-23 Bruno Haible * configure.ac: Bump version number to 2.4. * src/sigsegv.h.in (LIBSIGSEGV_VERSION): Likewise. 2006-06-17 Bruno Haible * src/Makefile.am (noinst_HEADERS): Add fault-netbsd.h. 2006-06-17 Bruno Haible * sigaltstack.m4: Insert 'volatile' and pass a pointer, to defeat GCC 4 optimizations. * sigaltstack-longjmp.m4: Likewise. * sigaltstack-siglongjmp.m4: Likewise. 2006-06-17 Bruno Haible * tests/stackoverflow1.c (recurse): Remove useless cast. * tests/stackoverflow2.c (recurse): Likewise. 2006-06-17 Bruno Haible * src/stackvma-freebsd.c (sigsegv_get_vma): Test whether mincore() works as expected before using it. 2006-03-28 Ralf Wildenhues * m4/libtool.m4 (_LT_SYS_DYNAMIC_LINKER) [ linux ]: Avoid warning when "parsing" /etc/ld.so.conf and empty /etc/ld.so.conf.d. 2006-06-13 Bruno Haible Make NetBSD/i386 stack overflow detection work even without mincore. * src/fault-netbsd.h: New file. * configure.ac (CFG_FAULT): Choose it when appropriate. 2006-05-16 Bruno Haible Don't allow the compiler to reorder instructions in the tests. * tests/sigsegv1.c (crashes): Use volatile in pointer access. * tests/sigsegv2.c (main): Likewise. * tests/stackoverflow2.c (main): Likewise. 2006-05-14 Bruno Haible Exploit the mincore() system call where available. * src/stackvma-mincore.c: New file. * src/Makefile.am (EXTRA_DIST): Add it. * src/stackvma.h: Add double-inclusion guard. * src/stackvma-freebsd.c: If mincore() is available, include also stackvma-mincore.c. (sigsegv_get_vma): If mincore() is available, use it as fallback. * src/stackvma-linux.c: If mincore() is available, include also stackvma-mincore.c. (sigsegv_get_vma): If mincore() is available, use it as fallback. * src/stackvma-procfs.c: If mincore() is available, include also stackvma-mincore.c. (sigsegv_get_vma): If mincore() is available, use it as fallback. * configure.ac: Test for mincore. (CFG_STACKVMA): Set to stackvma-mincore.c if nothing else is available. 2006-05-14 Bruno Haible * src/stackvma-simple.c: New file, extracted from handler-unix.c. * src/Makefile.am (EXTRA_DIST): Add it. * src/stackvma-beos.c: Include stackvma-simple.c. (sigsegv_get_vma): Fill the vma's is_near_this field. * src/stackvma-freebsd.c: Include stackvma-simple.c. (sigsegv_get_vma): Fill the vma's is_near_this field. * src/stackvma-linux.c: Include stackvma-simple.c. (sigsegv_get_vma): Fill the vma's is_near_this field. * src/stackvma-mach.c: Include stackvma-simple.c. (sigsegv_get_vma): Fill the vma's is_near_this field. * src/stackvma-procfs.c: Include stackvma-simple.c. (sigsegv_get_vma): Fill the vma's is_near_this field. * src/stackvma.h (vma_struct): Add is_near_this field. * src/handler-unix.c (sigsegv_handler): Use the vma's is_near_this function. 2006-04-28 Bruno Haible * Version 2.3 released. 2006-04-28 Bruno Haible * configure.ac: Bump version number to 2.3. * src/sigsegv.h.in (LIBSIGSEGV_VERSION): Likewise. * build-aux/config.guess, build-aux/config.sub: Update to GNU version 2006-04-26. * build-aux/install-sh: Update from automake-1.9.6. * build-aux/missing: Likewise. * build-aux/ltmain.sh: Update from libtool-1.5.22. * m4/libtool.m4: Likewise. 2006-04-28 Bruno Haible * build-aux: Renamed from autoconf. * configure.ac (AC_CONFIG_AUX_DIR): Set to build-aux. 2006-04-22 Bruno Haible * configure.ac: Renamed from configure.in. 2006-04-21 Bruno Haible * src/machfault-macos-i386.h: Rewritten for Darwin 8.6.1. * configure.in: Change FAULT_CONTEXT for i?86-darwin. 2005-06-21 Paolo Bonzini * configure.in: For handler-macos.c, include mach/thread_status.h. * configure: Regenerate. 2005-06-21 Paolo Bonzini * tests/stackoverflow1.c (recurse): Make more resilient to compiler optimization. (recurse_1): New. * tests/stackoverflow2.c: Likewise. 2005-05-24 Bruno Haible * src/handler-win32.c (main_exception_filter): Copy CONTEXT structure to safe area on the stack. Based on patch by Doug Currie . * src/handler-win32.c (main_exception_filter): Swap arguments passed to stack_overflow_handler. Patch by Doug Currie . * src/handler-win32.c (main_exception_filter): Align %esp on a 16-byte boundary. 2005-03-02 Bruno Haible * Version 2.2 released. 2005-03-02 Bruno Haible * autoconf/config.guess: Update. * autoconf/config.sub: Update. * autoconf/missing: Update from automake-1.9.5. * m4/libtool.m4: Upgrade to libtool-1.5.14 with gettext modifications. * autoconf/ltmain.sh: Likewise. 2005-03-02 Bruno Haible * src/fault-aix5.h: New file. * src/fault-aix5-powerpc.h: New file. * src/Makefile.am (noinst_HEADERS): Add them. * configure.in: Choose them when the POSIX test succeeds on AIX. * src/fault-aix3-powerpc.h: Renamed from src/fault-aix-powerpc.h. * src/fault-aix3.h: Renamed from src/fault-aix.h. * src/Makefile.am (noinst_HEADERS): Update. * configure.in: Update. When cross-compiling, assume the AIX test succeeds only on AIX 3 and AIX 4. 2005-03-01 Bruno Haible * configure.in: Fix test of CFG_MACHFAULT. 2005-02-27 Bruno Haible * configure.in: Skip tests that are not needed on MacOS X >= 10.2. * m4/sigaltstack.m4 (SV_SIGALTSTACK): Don't perform the test on MacOS X >= 10.2. 2005-02-18 Bruno Haible * tests/sigsegv1.c (handler_called): Declare as volatile. * tests/sigsegv2.c (logcount, logdata): Likewise. * tests/stackoverflow1.c (pass): Likewise. * tests/stackoverflow2.c (pass): Likewise. 2005-01-29 Bruno Haible * src/sigsegv.h.in (LIBSIGSEGV_VERSION): New macro. (libsigsegv_version): New declaration. * src/version.c: New file. * src/Makefile.am (libsigsegv_la_SOURCES): Add version.c. * Makefile.msvc (OBJECTS): Add version.obj. (version.obj): New rule. Suggested by Sam Steingold. 2004-08-25 Bruno Haible * m4/libtool.m4: Upgrade to libtool-1.5.6. * autoconf/ltmain.sh: Upgrade to libtool-1.5.6. 2004-08-18 Bruno Haible * configure.in: Bump version number to 2.2. 2004-08-17 Bruno Haible Finish the Mach-based MacOS X support. * src/handler-macos.c: Don't include mach/vm_map.h. Include machfault.h instead of fault.h. (save_exc_state): Remove variable. (save_thread_state): New variable. (terminating_handler): New function. (altstack_handler): Pass the save_thread_state, not the save_exc_state, to the user's handler. (catch_exception_raise): Make it work also for platforms which don't have an exc_state type. Call SIGSEGV_FAULT_ADDRESS with 2 arguments. Don't clobber the exc_state; instead set the thread's program counter to terminating_handler or altstack_handler, depending on the case. Return KERN_SUCCESS at the end. * src/machfault.h: New file. * src/machfault-macos-powerpc.h (SIGSEGV_FAULT_ADDRESS): Add a second argument. * src/machfault-macos-i386.h: New file. * src/Makefile.am (EXTRA_DIST): Add handler-macos.c. (NOINST_HEADERS): Add machfault.h, machfault-macos-i386.h, machfault-macos-powerpc.h. * configure.in (CFG_HANDLER): Initialize to empty. (CFG_MACHFAULT): New substituted variable. On MacOS X PowerPC+i386, use CFG_HANDLER=handler-macos.c unconditionally. (sv_cv_fault_include, sv_cv_have_stack_overflow_recovery): Set correctly also in the handler-macos.c case. 2004-08-16 Bruno Haible Support for MacOS X 10.3 on PowerPC. * src/fault-macosdarwin5-powerpc.h: Renamed from src/fault-macos-powerpc.h. * src/fault-macosdarwin5-powerpc.c: Renamed from src/fault-macos-powerpc.c. * src/fault-macosdarwin7-powerpc.h: New file. * src/fault-macosdarwin7-powerpc.c: New file. * src/Makefile.am (noinst_HEADERS): Update. * configure.in: Test the method for MacOSX/Darwin5 PowerPC only after the method for MacOSX/Darwin7 PowerPC failed. Substitute FAULT_CONTEXT_INCLUDE2. * src/sigsegv.h.in: Insert @FAULT_CONTEXT_INCLUDE2@. * src/Makefile.am (sigsegv.h.msvc): Replace @FAULT_CONTEXT_INCLUDE2@. 2003-12-09 Paolo Bonzini * src/handler-macos.c: Completed; removed dependency on signals. * src/machfault-macos-powerpc.h: Reorganized. 2003-12-08 Paolo Bonzini Bruno Haible * src/handler-macos.c: New file. * src/machfault.h: New file. * src/machfault-macos-powerpc.h: New file. 2003-12-05 Bruno Haible * m4/fault.m4: Tweak indentation. Bump serial number. * m4/getpagesize.m4: Likewise. * m4/mmap-anon.m4: Likewise. * m4/sigaltstack.m4: Likewise. * m4/sigaltstack-longjmp.m4: Likewise. * m4/sigaltstack-siglongjmp.m4: Likewise. 2003-12-05 Paolo Bonzini * aclocal.m4: Regenerate with Automake 1.7h. * configure.in: Drop m4/Makefile from list of generated files. * configure: Regenerate. * Makefile.am (install-data-hook): New name of the install-am target, for Automake 1.8 compatibility. Other -am targets are not affected because Automake does not have anything to do to make them. (AUTOMAKE_OPTIONS): Bump minimum Automake requirement to 1.7h. (SUBDIRS): Remove m4. ($(srcdir)/config.h.msvc): New target for config.h.msvc. * Makefile.in: Regenerate with Automake 1.7h. * m4/Makefile.am: Delete, Automake 1.7h takes care of it. * m4/Makefile.in: Delete. * src/Makefile.am (installdirs): Delete, Automake 1.7h adds it. * src/Makefile.in: Regenerate with Automake 1.7h. * tests/Makefile.in: Regenerate with Automake 1.7h. * autoconf/config.guess: Update from automake-1.7h. * autoconf/config.sub: Likewise. * autoconf/install.sh: Likewise. * autoconf/missing: Likewise. * autoconf/mkinstalldirs: Delete. * m4/fault.m4: autoupdate and manually tweak. * m4/sigaltstack.m4: Likewise. * m4/sigaltstack-longjmp.m4: Likewise. * m4/sigaltstack-siglongjmp.m4: Likewise. * m4/mmap-anon.m4: Likewise. * m4/getpagesize.m4: Likewise. 2003-10-29 Bruno Haible * tests/sigsegv1.c (main): Add a check whether mprotect with PROT_READ_WRITE really works. * tests/sigsegv2.c (main): Likewise. Reported by Ullal Devappa Kini . 2003-08-21 Bruno Haible * Version 2.1 released. 2003-06-24 Paolo Bonzini * m4/fault.m4: Exit if we detect an infinite loop. * aclocal.m4: Regenerate. * configure: Regenerate. 2003-06-18 Bruno Haible * autoconf/install-sh: Update from automake-1.7.5. 2003-05-14 Paolo Bonzini * configure.in: Use signals-bsd.h for OpenBSD and NetBSD too. Support instruction decoding to get fault address for Alphas. * src/fault-netbsd-alpha.h: New file. * src/fault-netbsd-alpha.c: New file. * src/Makefile.am (noinst_HEADERS): Add them. 2003-05-14 Paolo Bonzini * src/dispatcher.c (insert): Fix lossage in 64-bit environments (cast from void* to unsigned int). 2003-05-10 Bruno Haible * tests/Makefile.am (../src/libsigsegv.la): New rule. * Makefile.msvc (handler.obj): Complete the dependencies. (stackoverflow2.exe): New rule. (check): Depend on it. (clean): Remove it. 2003-05-10 Paolo Bonzini Bruno Haible * configure.in: AC_SUBST of CFG_STACKVMA, CFG_LEAVE, CFG_HANDLER. * src/Makefile.am: Add dependencies for the object files. 2003-05-08 Paolo Bonzini * configure.in: Add $srcdir/ to #include statements. Needed when builddir != srcdir. * src/signals-macos.h (SIGSEGV_FOR_ALL_SIGNALS): Add SIGSEGV. 2003-05-03 Paolo Bonzini * configure.in: Tweak 2003-04-26 patch so that it works on mingw32 and Cygwin. 2003-05-02 Bruno Haible * src/handler-unix.c: Add special case for stack handling on IA-64. * src/fault-linux-ia64.h: Complete the port. * configure.in: Improve Linux/IA-64 support. 2003-05-01 Bruno Haible * configure.in: Don't use fault-hurd.h on NetBSD/alpha. It does not work. 2003-05-01 Bruno Haible Support for Linux/HPPA. * fault-linux-hppa.h: Don't include . (SIGSEGV_FAULT_ADDRESS): Change. (SIGSEGV_FAULT_ADDRESS_FROM_SIGINFO): Define it, otherwise the value passed for sip is 0. (SIGSEGV_FAULT_CONTEXT, SIGSEGV_FAULT_STACKPOINTER): Remove macros. * configure.in: Improve Linux/HPPA support. 2003-05-01 Bruno Haible Support for OpenBSD/i386. * src/fault-openbsd.h: New file. * src/fault-openbsd-i386.h: New file. * src/Makefile.am (noinst_HEADERS): Add them. * configure.in: If the POSIX test works and the OS is OpenBSD, use fault-openbsd.h instead of fault-posix.h. 2003-05-01 Bruno Haible * src/fault-hpux-hppa.h: Make it work on machines with 64-bit registers as well. * configure.in: Likewise. 2003-04-29 Bruno Haible * configure.in: Define HAVE_STACKVMA if CFG_STACKVMA is nontrivial. * src/handler-unix.c: Test HAVE_STACKVMA instead of CFG_STACKVMA. * m4/fault.m4 (SV_TRY_FAULT): On HP-UX, always pass 0 as first argument of mmap(). * tests/mmaputil.h (mmap_zeromap): Likewise. 2003-04-28 Bruno Haible * src/stackvma-freebsd.c (sigsegv_get_vma): Fix logic error. 2002-04-17 Paolo Bonzini Support for Cygwin. * configure.in: Treat cygwin* like mingw*. * src/handler-win32.c [CYGWIN] (exception_list, _except_list, debug_get_except_list, cygwin_exception_handler, libsigsegv_exception_handler, do_install_main_exception_filter): New definitions. (install_main_exception_filter): New function. (sigsegv_install_handler, stackoverflow_install_handler): Call it. 2003-04-26 Bruno Haible * configure.in: Don't set sv_cv_have_stack_overflow_recovery=yes if not all of the fault-*.h and stackvma-*.h premises are fulfilled. Reported by Paolo Bonzini for NetBSD/Alpha. 2003-04-03 Bruno Haible * configure.in: Add --enable-relocatable option. * m4/relocatable.m4: New file, from GNU gettext. * m4/Makefile.am (EXTRA_DIST): Add it. * m4/libtool.m4: Update from GNU gettext, based on libtool-1.4.3. * autoconf/ltmain.sh: Likewise. 2003-04-02 Bruno Haible * configure.in: Bump version number to 2.1. * tests/stackoverflow2.c: New file, based on code by Paolo Bonzini. * tests/Makefile.am (TESTS, noinst_PROGRAMS): Add stackoverflow2. 2003-04-02 Paolo Bonzini Bruno Haible Complete the port to MacOS X (Darwin). * m4/fault.m4: Include sys/signal.h. Have an exit status of 3 instead of 1 if fault_address is misdetected. * m4/sigaltstack.m4: Define stack_t to struct sigaltstack if absent. Include . * configure.in: Add check for sys/signal.h. Add support for catching stack overflow on MacOSX. Add support for MacOSX on i386. Provide a fallback for SS_ONSTACK before using it. * src/fault-macos-i386.h: New file. * src/stackvma-mach.c: New file. * src/fault-macos-powerpc.h (SIGSEGV_FAULT_STACKPOINTER): Change. * src/handler-unix.c: Include . (SS_DISABLE): Provide a fallback. * src/leave-sigaltstack.c: Include sys/signal.h. (SS_ONSTACK): Provide a fallback. * src/Makefile.am (noinst_HEADERS): Add fault-macos-i386.h. (EXTRA_DIST): Add stackvma-mach.c. * tests/sigsegv1.c: Abort after 10 handler invocations. (main): Drop SKIP message, now emitted by automake 1.7.x. * tests/sigsegv2.c: Abort after 10 handler invocations. (main): Drop SKIP message, now emitted by automake 1.7.x. * tests/stackoverflow1.c (main): Drop SKIP message, now emitted by automake 1.7.x. 2002-10-14 Bruno Haible * src/fault-none.h: New file. * src/fault.h: Include CFG_FAULT unconditionally. * src/leave-none.c: New file. * src/leave.c: Include CFG_LEAVE unconditionally. * src/stackvma.c: Include CFG_STACKVMA unconditionally. * configure.in (CFG_LEAVE, CFG_STACKVMA): Define always. * src/Makefile.am (noinst_HEADERS): Add fault-none.h. (EXTRA_DIST): Add leave-none.c. Reported by Paolo Bonzini . 2002-09-30 Bruno Haible * src/Makefile.am (noinst_HEADERS): Add fault-hurd.h, fault-linux-m68k.c, fault-macos-powerpc.h, fault-macos-powerpc.c, signals-hurd.h, signals-macos.h. 2002-09-30 Bruno Haible * Makefile.am (check-next): Don't ask for reports from i?86-*-linux* platforms. 2002-09-30 Bruno Haible Better Linux/PowerPC support. * configure.in: Change Linux/PowerPC support. * src/fault-linux-powerpc.h (SIGSEGV_FAULT_ADDRESS): New macro. 2002-09-30 Bruno Haible Better Linux/m68k support. * configure.in: Change Linux/m68k support. * src/fault-linux-m68k.c: New file. * src/fault-linux-m68k.h: Use it. 2002-09-30 Bruno Haible Tentative Hurd support. * configure.in: Add Hurd support. * src/signals-hurd.h: New file. * src/fault-hurd.h: New file. 2002-09-30 Bruno Haible MacOSX/PowerPC support. * configure.in: Add MacOSX/PowerPC support. * src/signals-macos.h: New file. * src/fault-macos-powerpc.c: New file. * src/fault-macos-powerpc.h: New file. 2002-09-16 Bruno Haible * src/fault-posix.h: Don't include . Needed for hppa-linux. Reported by Will Newton . 2002-08-28 Bruno Haible * Version 2.0 released. 2002-07-28 Bruno Haible Big reorganization and rewrite. Every file changed. smalltalk-3.2.5/sigsegv/COPYING0000644000175000017500000004335212130343734013137 00000000000000 GNU GENERAL PUBLIC LICENSE Version 2, June 1991 Copyright (C) 1989, 1991 Free Software Foundation, Inc. 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. Everyone is permitted to copy and distribute verbatim copies of this license document, but changing it is not allowed. Preamble The licenses for most software are designed to take away your freedom to share and change it. By contrast, the GNU General Public License is intended to guarantee your freedom to share and change free software--to make sure the software is free for all its users. This General Public License applies to most of the Free Software Foundation's software and to any other program whose authors commit to using it. (Some other Free Software Foundation software is covered by the GNU Library General Public License instead.) You can apply it to your programs, too. When we speak of free software, we are referring to freedom, not price. Our General Public Licenses are designed to make sure that you have the freedom to distribute copies of free software (and charge for this service if you wish), that you receive source code or can get it if you want it, that you can change the software or use pieces of it in new free programs; and that you know you can do these things. To protect your rights, we need to make restrictions that forbid anyone to deny you these rights or to ask you to surrender the rights. These restrictions translate to certain responsibilities for you if you distribute copies of the software, or if you modify it. For example, if you distribute copies of such a program, whether gratis or for a fee, you must give the recipients all the rights that you have. You must make sure that they, too, receive or can get the source code. And you must show them these terms so they know their rights. We protect your rights with two steps: (1) copyright the software, and (2) offer you this license which gives you legal permission to copy, distribute and/or modify the software. Also, for each author's protection and ours, we want to make certain that everyone understands that there is no warranty for this free software. If the software is modified by someone else and passed on, we want its recipients to know that what they have is not the original, so that any problems introduced by others will not reflect on the original authors' reputations. Finally, any free program is threatened constantly by software patents. We wish to avoid the danger that redistributors of a free program will individually obtain patent licenses, in effect making the program proprietary. To prevent this, we have made it clear that any patent must be licensed for everyone's free use or not licensed at all. The precise terms and conditions for copying, distribution and modification follow. GNU GENERAL PUBLIC LICENSE TERMS AND CONDITIONS FOR COPYING, DISTRIBUTION AND MODIFICATION 0. This License applies to any program or other work which contains a notice placed by the copyright holder saying it may be distributed under the terms of this General Public License. The "Program", below, refers to any such program or work, and a "work based on the Program" means either the Program or any derivative work under copyright law: that is to say, a work containing the Program or a portion of it, either verbatim or with modifications and/or translated into another language. (Hereinafter, translation is included without limitation in the term "modification".) Each licensee is addressed as "you". Activities other than copying, distribution and modification are not covered by this License; they are outside its scope. The act of running the Program is not restricted, and the output from the Program is covered only if its contents constitute a work based on the Program (independent of having been made by running the Program). Whether that is true depends on what the Program does. 1. You may copy and distribute verbatim copies of the Program's source code as you receive it, in any medium, provided that you conspicuously and appropriately publish on each copy an appropriate copyright notice and disclaimer of warranty; keep intact all the notices that refer to this License and to the absence of any warranty; and give any other recipients of the Program a copy of this License along with the Program. You may charge a fee for the physical act of transferring a copy, and you may at your option offer warranty protection in exchange for a fee. 2. You may modify your copy or copies of the Program or any portion of it, thus forming a work based on the Program, and copy and distribute such modifications or work under the terms of Section 1 above, provided that you also meet all of these conditions: a) You must cause the modified files to carry prominent notices stating that you changed the files and the date of any change. b) You must cause any work that you distribute or publish, that in whole or in part contains or is derived from the Program or any part thereof, to be licensed as a whole at no charge to all third parties under the terms of this License. c) If the modified program normally reads commands interactively when run, you must cause it, when started running for such interactive use in the most ordinary way, to print or display an announcement including an appropriate copyright notice and a notice that there is no warranty (or else, saying that you provide a warranty) and that users may redistribute the program under these conditions, and telling the user how to view a copy of this License. (Exception: if the Program itself is interactive but does not normally print such an announcement, your work based on the Program is not required to print an announcement.) These requirements apply to the modified work as a whole. If identifiable sections of that work are not derived from the Program, and can be reasonably considered independent and separate works in themselves, then this License, and its terms, do not apply to those sections when you distribute them as separate works. But when you distribute the same sections as part of a whole which is a work based on the Program, the distribution of the whole must be on the terms of this License, whose permissions for other licensees extend to the entire whole, and thus to each and every part regardless of who wrote it. Thus, it is not the intent of this section to claim rights or contest your rights to work written entirely by you; rather, the intent is to exercise the right to control the distribution of derivative or collective works based on the Program. In addition, mere aggregation of another work not based on the Program with the Program (or with a work based on the Program) on a volume of a storage or distribution medium does not bring the other work under the scope of this License. 3. You may copy and distribute the Program (or a work based on it, under Section 2) in object code or executable form under the terms of Sections 1 and 2 above provided that you also do one of the following: a) Accompany it with the complete corresponding machine-readable source code, which must be distributed under the terms of Sections 1 and 2 above on a medium customarily used for software interchange; or, b) Accompany it with a written offer, valid for at least three years, to give any third party, for a charge no more than your cost of physically performing source distribution, a complete machine-readable copy of the corresponding source code, to be distributed under the terms of Sections 1 and 2 above on a medium customarily used for software interchange; or, c) Accompany it with the information you received as to the offer to distribute corresponding source code. (This alternative is allowed only for noncommercial distribution and only if you received the program in object code or executable form with such an offer, in accord with Subsection b above.) The source code for a work means the preferred form of the work for making modifications to it. For an executable work, complete source code means all the source code for all modules it contains, plus any associated interface definition files, plus the scripts used to control compilation and installation of the executable. However, as a special exception, the source code distributed need not include anything that is normally distributed (in either source or binary form) with the major components (compiler, kernel, and so on) of the operating system on which the executable runs, unless that component itself accompanies the executable. If distribution of executable or object code is made by offering access to copy from a designated place, then offering equivalent access to copy the source code from the same place counts as distribution of the source code, even though third parties are not compelled to copy the source along with the object code. 4. You may not copy, modify, sublicense, or distribute the Program except as expressly provided under this License. Any attempt otherwise to copy, modify, sublicense or distribute the Program is void, and will automatically terminate your rights under this License. However, parties who have received copies, or rights, from you under this License will not have their licenses terminated so long as such parties remain in full compliance. 5. You are not required to accept this License, since you have not signed it. However, nothing else grants you permission to modify or distribute the Program or its derivative works. These actions are prohibited by law if you do not accept this License. Therefore, by modifying or distributing the Program (or any work based on the Program), you indicate your acceptance of this License to do so, and all its terms and conditions for copying, distributing or modifying the Program or works based on it. 6. Each time you redistribute the Program (or any work based on the Program), the recipient automatically receives a license from the original licensor to copy, distribute or modify the Program subject to these terms and conditions. You may not impose any further restrictions on the recipients' exercise of the rights granted herein. You are not responsible for enforcing compliance by third parties to this License. 7. If, as a consequence of a court judgment or allegation of patent infringement or for any other reason (not limited to patent issues), conditions are imposed on you (whether by court order, agreement or otherwise) that contradict the conditions of this License, they do not excuse you from the conditions of this License. If you cannot distribute so as to satisfy simultaneously your obligations under this License and any other pertinent obligations, then as a consequence you may not distribute the Program at all. For example, if a patent license would not permit royalty-free redistribution of the Program by all those who receive copies directly or indirectly through you, then the only way you could satisfy both it and this License would be to refrain entirely from distribution of the Program. If any portion of this section is held invalid or unenforceable under any particular circumstance, the balance of the section is intended to apply and the section as a whole is intended to apply in other circumstances. It is not the purpose of this section to induce you to infringe any patents or other property right claims or to contest validity of any such claims; this section has the sole purpose of protecting the integrity of the free software distribution system, which is implemented by public license practices. Many people have made generous contributions to the wide range of software distributed through that system in reliance on consistent application of that system; it is up to the author/donor to decide if he or she is willing to distribute software through any other system and a licensee cannot impose that choice. This section is intended to make thoroughly clear what is believed to be a consequence of the rest of this License. 8. If the distribution and/or use of the Program is restricted in certain countries either by patents or by copyrighted interfaces, the original copyright holder who places the Program under this License may add an explicit geographical distribution limitation excluding those countries, so that distribution is permitted only in or among countries not thus excluded. In such case, this License incorporates the limitation as if written in the body of this License. 9. The Free Software Foundation may publish revised and/or new versions of the General Public License from time to time. Such new versions will be similar in spirit to the present version, but may differ in detail to address new problems or concerns. Each version is given a distinguishing version number. If the Program specifies a version number of this License which applies to it and "any later version", you have the option of following the terms and conditions either of that version or of any later version published by the Free Software Foundation. If the Program does not specify a version number of this License, you may choose any version ever published by the Free Software Foundation. 10. If you wish to incorporate parts of the Program into other free programs whose distribution conditions are different, write to the author to ask for permission. For software which is copyrighted by the Free Software Foundation, write to the Free Software Foundation; we sometimes make exceptions for this. Our decision will be guided by the two goals of preserving the free status of all derivatives of our free software and of promoting the sharing and reuse of software generally. NO WARRANTY 11. BECAUSE THE PROGRAM IS LICENSED FREE OF CHARGE, THERE IS NO WARRANTY FOR THE PROGRAM, TO THE EXTENT PERMITTED BY APPLICABLE LAW. EXCEPT WHEN OTHERWISE STATED IN WRITING THE COPYRIGHT HOLDERS AND/OR OTHER PARTIES PROVIDE THE PROGRAM "AS IS" WITHOUT WARRANTY OF ANY KIND, EITHER EXPRESSED OR IMPLIED, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE. THE ENTIRE RISK AS TO THE QUALITY AND PERFORMANCE OF THE PROGRAM IS WITH YOU. SHOULD THE PROGRAM PROVE DEFECTIVE, YOU ASSUME THE COST OF ALL NECESSARY SERVICING, REPAIR OR CORRECTION. 12. IN NO EVENT UNLESS REQUIRED BY APPLICABLE LAW OR AGREED TO IN WRITING WILL ANY COPYRIGHT HOLDER, OR ANY OTHER PARTY WHO MAY MODIFY AND/OR REDISTRIBUTE THE PROGRAM AS PERMITTED ABOVE, BE LIABLE TO YOU FOR DAMAGES, INCLUDING ANY GENERAL, SPECIAL, INCIDENTAL OR CONSEQUENTIAL DAMAGES ARISING OUT OF THE USE OR INABILITY TO USE THE PROGRAM (INCLUDING BUT NOT LIMITED TO LOSS OF DATA OR DATA BEING RENDERED INACCURATE OR LOSSES SUSTAINED BY YOU OR THIRD PARTIES OR A FAILURE OF THE PROGRAM TO OPERATE WITH ANY OTHER PROGRAMS), EVEN IF SUCH HOLDER OR OTHER PARTY HAS BEEN ADVISED OF THE POSSIBILITY OF SUCH DAMAGES. END OF TERMS AND CONDITIONS Appendix: How to Apply These Terms to Your New Programs If you develop a new program, and you want it to be of the greatest possible use to the public, the best way to achieve this is to make it free software which everyone can redistribute and change under these terms. To do so, attach the following notices to the program. It is safest to attach them to the start of each source file to most effectively convey the exclusion of warranty; and each file should have at least the "copyright" line and a pointer to where the full notice is found. Copyright (C) This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2 of the License, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307, USA. Also add information on how to contact you by electronic and paper mail. If the program is interactive, make it output a short notice like this when it starts in an interactive mode: Gnomovision version 69, Copyright (C) year name of author Gnomovision comes with ABSOLUTELY NO WARRANTY; for details type `show w'. This is free software, and you are welcome to redistribute it under certain conditions; type `show c' for details. The hypothetical commands `show w' and `show c' should show the appropriate parts of the General Public License. Of course, the commands you use may be called something other than `show w' and `show c'; they could even be mouse-clicks or menu items--whatever suits your program. You should also get your employer (if you work as a programmer) or your school, if any, to sign a "copyright disclaimer" for the program, if necessary. Here is a sample; alter the names: Yoyodyne, Inc., hereby disclaims all copyright interest in the program `Gnomovision' (which makes passes at compilers) written by James Hacker. , 1 April 1989 Ty Coon, President of Vice This General Public License does not permit incorporating your program into proprietary programs. If your program is a subroutine library, you may consider it more useful to permit linking proprietary applications with the library. If this is what you want to do, use the GNU Library General Public License instead of this License. smalltalk-3.2.5/sigsegv/Makefile.am0000644000175000017500000000555312130343734014141 00000000000000## Makefile for libsigsegv. ## Copyright (C) 2002-2003, 2007 Bruno Haible ## ## This program is free software; you can redistribute it and/or modify ## it under the terms of the GNU General Public License as published by ## the Free Software Foundation; either version 2, or (at your option) ## any later version. ## ## This program is distributed in the hope that it will be useful, ## but WITHOUT ANY WARRANTY; without even the implied warranty of ## MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the ## GNU General Public License for more details. ## ## You should have received a copy of the GNU General Public License ## along with this program; if not, write to the Free Software ## Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, ## USA. ## Process this file with automake to produce Makefile.in. AUTOMAKE_OPTIONS = 1.7h gnu no-dependencies ACLOCAL_AMFLAGS = -I ../build-aux SUBDIRS = src tests EXTRA_DIST = ChangeLog.1 PORTING README.woe32 Makefile.msvc config.h.msvc DISTCLEANFILES = termbold termnorm # Lead the user through the installation, in the hope that he will help us # by sending his config.log. TARGETSTACK = AM_MAKEFLAGS = TARGETSTACK="$(TARGETSTACK) $@" all-am: all-next all-next: @if echo "$(TARGETSTACK)" | grep check-recursive > /dev/null; then :; else \ if echo "$(TARGETSTACK)" | grep install-recursive > /dev/null; then :; else \ echo; echo "Now please type '"`cat termbold`"make check"`cat termnorm`"' to run a quick test suite. Hope it works."; echo; \ fi; \ fi check-am: check-next check-next: @when="Now"; \ if grep '^@PLATFORM@ .* @VERSION@$$' $(srcdir)/PORTING > /dev/null; then :; else \ case '@PLATFORM@' in \ i?86-*-linux* | x86_64-*-linux*) ;; \ *) \ echo; \ echo "Please send the following summary line via email to the author"; \ echo "Bruno Haible for inclusion into the list of"; \ echo "successfully tested platforms (see PORTING file). Please also"; \ echo "send the config.log file; this will help improving portability"; \ echo "of the package."; echo; \ if test @HAVE_SIGSEGV_RECOVERY@ = 1; then have1=yes; else have1=no; fi; \ if test @HAVE_STACK_OVERFLOW_RECOVERY@ = 1; then have2=yes; else have2=no; fi; \ echo `cat termbold`"libsigsegv: @PLATFORM@ | $$have1 | $$have2 | @VERSION@"`cat termnorm`; \ when="Then"; \ ;; \ esac; \ fi; \ echo; echo "$$when please type '"`cat termbold`"make install"`cat termnorm`"' to install the package."; echo install-data-hook: install-next install-next: @echo; echo "Now use the package; you can remove it later via '"`cat termbold`"make uninstall"`cat termnorm`"'."; echo # Rules for "make dist". $(srcdir)/config.h.msvc : config.h.in sed -e 's/#undef CFG_HANDLER/#define CFG_HANDLER "handler-win32.c"/' < $(srcdir)/config.h.in > $@ smalltalk-3.2.5/sigsegv/Makefile.in0000644000175000017500000006523512130455553014160 00000000000000# Makefile.in generated by automake 1.11.6 from Makefile.am. # @configure_input@ # Copyright (C) 1994, 1995, 1996, 1997, 1998, 1999, 2000, 2001, 2002, # 2003, 2004, 2005, 2006, 2007, 2008, 2009, 2010, 2011 Free Software # Foundation, Inc. # This Makefile.in is free software; the Free Software Foundation # gives unlimited permission to copy and/or distribute it, # with or without modifications, as long as this notice is preserved. # This program is distributed in the hope that it will be useful, # but WITHOUT ANY WARRANTY, to the extent permitted by law; without # even the implied warranty of MERCHANTABILITY or FITNESS FOR A # PARTICULAR PURPOSE. @SET_MAKE@ VPATH = @srcdir@ am__make_dryrun = \ { \ am__dry=no; \ case $$MAKEFLAGS in \ *\\[\ \ ]*) \ echo 'am--echo: ; @echo "AM" OK' | $(MAKE) -f - 2>/dev/null \ | grep '^AM OK$$' >/dev/null || am__dry=yes;; \ *) \ for am__flg in $$MAKEFLAGS; do \ case $$am__flg in \ *=*|--*) ;; \ *n*) am__dry=yes; break;; \ esac; \ done;; \ esac; \ test $$am__dry = yes; \ } pkgdatadir = $(datadir)/@PACKAGE@ pkgincludedir = $(includedir)/@PACKAGE@ pkglibdir = $(libdir)/@PACKAGE@ pkglibexecdir = $(libexecdir)/@PACKAGE@ am__cd = CDPATH="$${ZSH_VERSION+.}$(PATH_SEPARATOR)" && cd install_sh_DATA = $(install_sh) -c -m 644 install_sh_PROGRAM = $(install_sh) -c install_sh_SCRIPT = $(install_sh) -c INSTALL_HEADER = $(INSTALL_DATA) transform = $(program_transform_name) NORMAL_INSTALL = : PRE_INSTALL = : POST_INSTALL = : NORMAL_UNINSTALL = : PRE_UNINSTALL = : POST_UNINSTALL = : build_triplet = @build@ host_triplet = @host@ subdir = . DIST_COMMON = README $(am__configure_deps) \ $(srcdir)/../build-aux/config.guess \ $(srcdir)/../build-aux/config.sub \ $(srcdir)/../build-aux/install-sh \ $(srcdir)/../build-aux/ltmain.sh \ $(srcdir)/../build-aux/missing $(srcdir)/Makefile.am \ $(srcdir)/Makefile.in $(srcdir)/config.h.in \ $(top_srcdir)/configure ../build-aux/compile \ ../build-aux/config.guess ../build-aux/config.rpath \ ../build-aux/config.sub ../build-aux/depcomp \ ../build-aux/elisp-comp ../build-aux/install-sh \ ../build-aux/ltmain.sh ../build-aux/mdate-sh \ ../build-aux/missing ../build-aux/texinfo.tex \ ../build-aux/ylwrap AUTHORS COPYING ChangeLog INSTALL NEWS ACLOCAL_M4 = $(top_srcdir)/aclocal.m4 am__aclocal_m4_deps = $(top_srcdir)/../build-aux/bold.m4 \ $(top_srcdir)/../build-aux/fault.m4 \ $(top_srcdir)/../build-aux/getpagesize.m4 \ $(top_srcdir)/../build-aux/libtool.m4 \ $(top_srcdir)/../build-aux/ltoptions.m4 \ $(top_srcdir)/../build-aux/ltsugar.m4 \ $(top_srcdir)/../build-aux/ltversion.m4 \ $(top_srcdir)/../build-aux/lt~obsolete.m4 \ $(top_srcdir)/../build-aux/mmap-anon.m4 \ $(top_srcdir)/../build-aux/relocatable.m4 \ $(top_srcdir)/../build-aux/sigaltstack-longjmp.m4 \ $(top_srcdir)/../build-aux/sigaltstack-siglongjmp.m4 \ $(top_srcdir)/../build-aux/sigaltstack.m4 \ $(top_srcdir)/configure.ac am__configure_deps = $(am__aclocal_m4_deps) $(CONFIGURE_DEPENDENCIES) \ $(ACLOCAL_M4) am__CONFIG_DISTCLEAN_FILES = config.status config.cache config.log \ configure.lineno config.status.lineno mkinstalldirs = $(install_sh) -d CONFIG_HEADER = config.h CONFIG_CLEAN_FILES = CONFIG_CLEAN_VPATH_FILES = depcomp = am__depfiles_maybe = SOURCES = DIST_SOURCES = RECURSIVE_TARGETS = all-recursive check-recursive dvi-recursive \ html-recursive info-recursive install-data-recursive \ install-dvi-recursive install-exec-recursive \ install-html-recursive install-info-recursive \ install-pdf-recursive install-ps-recursive install-recursive \ installcheck-recursive installdirs-recursive pdf-recursive \ ps-recursive uninstall-recursive am__can_run_installinfo = \ case $$AM_UPDATE_INFO_DIR in \ n|no|NO) false;; \ *) (install-info --version) >/dev/null 2>&1;; \ esac RECURSIVE_CLEAN_TARGETS = mostlyclean-recursive clean-recursive \ distclean-recursive maintainer-clean-recursive AM_RECURSIVE_TARGETS = $(RECURSIVE_TARGETS:-recursive=) \ $(RECURSIVE_CLEAN_TARGETS:-recursive=) tags TAGS ctags CTAGS \ distdir dist dist-all distcheck ETAGS = etags CTAGS = ctags DIST_SUBDIRS = $(SUBDIRS) DISTFILES = $(DIST_COMMON) $(DIST_SOURCES) $(TEXINFOS) $(EXTRA_DIST) distdir = $(PACKAGE)-$(VERSION) top_distdir = $(distdir) am__remove_distdir = \ if test -d "$(distdir)"; then \ find "$(distdir)" -type d ! -perm -200 -exec chmod u+w {} ';' \ && rm -rf "$(distdir)" \ || { sleep 5 && rm -rf "$(distdir)"; }; \ else :; fi am__relativize = \ dir0=`pwd`; \ sed_first='s,^\([^/]*\)/.*$$,\1,'; \ sed_rest='s,^[^/]*/*,,'; \ sed_last='s,^.*/\([^/]*\)$$,\1,'; \ sed_butlast='s,/*[^/]*$$,,'; \ while test -n "$$dir1"; do \ first=`echo "$$dir1" | sed -e "$$sed_first"`; \ if test "$$first" != "."; then \ if test "$$first" = ".."; then \ dir2=`echo "$$dir0" | sed -e "$$sed_last"`/"$$dir2"; \ dir0=`echo "$$dir0" | sed -e "$$sed_butlast"`; \ else \ first2=`echo "$$dir2" | sed -e "$$sed_first"`; \ if test "$$first2" = "$$first"; then \ dir2=`echo "$$dir2" | sed -e "$$sed_rest"`; \ else \ dir2="../$$dir2"; \ fi; \ dir0="$$dir0"/"$$first"; \ fi; \ fi; \ dir1=`echo "$$dir1" | sed -e "$$sed_rest"`; \ done; \ reldir="$$dir2" DIST_ARCHIVES = $(distdir).tar.gz GZIP_ENV = --best distuninstallcheck_listfiles = find . -type f -print am__distuninstallcheck_listfiles = $(distuninstallcheck_listfiles) \ | sed 's|^\./|$(prefix)/|' | grep -v '$(infodir)/dir$$' distcleancheck_listfiles = find . -type f -print ACLOCAL = @ACLOCAL@ AMTAR = @AMTAR@ AR = @AR@ AUTOCONF = @AUTOCONF@ AUTOHEADER = @AUTOHEADER@ AUTOMAKE = @AUTOMAKE@ AWK = @AWK@ CC = @CC@ CCDEPMODE = @CCDEPMODE@ CFG_HANDLER = @CFG_HANDLER@ CFG_LEAVE = @CFG_LEAVE@ CFG_STACKVMA = @CFG_STACKVMA@ CFLAGS = @CFLAGS@ CPP = @CPP@ CPPFLAGS = @CPPFLAGS@ CYGPATH_W = @CYGPATH_W@ DEFS = @DEFS@ DEPDIR = @DEPDIR@ DLLTOOL = @DLLTOOL@ DSYMUTIL = @DSYMUTIL@ DUMPBIN = @DUMPBIN@ ECHO_C = @ECHO_C@ ECHO_N = @ECHO_N@ ECHO_T = @ECHO_T@ EGREP = @EGREP@ EXEEXT = @EXEEXT@ FAULT_CONTEXT = @FAULT_CONTEXT@ FAULT_CONTEXT_INCLUDE = @FAULT_CONTEXT_INCLUDE@ FAULT_CONTEXT_INCLUDE2 = @FAULT_CONTEXT_INCLUDE2@ FGREP = @FGREP@ GREP = @GREP@ HAVE_SIGSEGV_RECOVERY = @HAVE_SIGSEGV_RECOVERY@ HAVE_STACK_OVERFLOW_RECOVERY = @HAVE_STACK_OVERFLOW_RECOVERY@ INSTALL = @INSTALL@ INSTALL_DATA = @INSTALL_DATA@ INSTALL_PROGRAM = @INSTALL_PROGRAM@ INSTALL_SCRIPT = @INSTALL_SCRIPT@ INSTALL_STRIP_PROGRAM = @INSTALL_STRIP_PROGRAM@ LD = @LD@ LDFLAGS = @LDFLAGS@ LIBOBJS = @LIBOBJS@ LIBS = @LIBS@ LIBTOOL = @LIBTOOL@ LIPO = @LIPO@ LN_S = @LN_S@ LTLIBOBJS = @LTLIBOBJS@ MAKEINFO = @MAKEINFO@ MANIFEST_TOOL = @MANIFEST_TOOL@ MKDIR_P = @MKDIR_P@ NM = @NM@ NMEDIT = @NMEDIT@ OBJDUMP = @OBJDUMP@ OBJEXT = @OBJEXT@ OTOOL = @OTOOL@ OTOOL64 = @OTOOL64@ PACKAGE = @PACKAGE@ PACKAGE_BUGREPORT = @PACKAGE_BUGREPORT@ PACKAGE_NAME = @PACKAGE_NAME@ PACKAGE_STRING = @PACKAGE_STRING@ PACKAGE_TARNAME = @PACKAGE_TARNAME@ PACKAGE_URL = @PACKAGE_URL@ PACKAGE_VERSION = @PACKAGE_VERSION@ PATH_SEPARATOR = @PATH_SEPARATOR@ PLATFORM = @PLATFORM@ RANLIB = @RANLIB@ RELOCATABLE = @RELOCATABLE@ SED = @SED@ SET_MAKE = @SET_MAKE@ SHELL = @SHELL@ STRIP = @STRIP@ VERSION = @VERSION@ abs_builddir = @abs_builddir@ abs_srcdir = @abs_srcdir@ abs_top_builddir = @abs_top_builddir@ abs_top_srcdir = @abs_top_srcdir@ ac_ct_AR = @ac_ct_AR@ ac_ct_CC = @ac_ct_CC@ ac_ct_DUMPBIN = @ac_ct_DUMPBIN@ am__include = @am__include@ am__leading_dot = @am__leading_dot@ am__quote = @am__quote@ am__tar = @am__tar@ am__untar = @am__untar@ bindir = @bindir@ build = @build@ build_alias = @build_alias@ build_cpu = @build_cpu@ build_os = @build_os@ build_vendor = @build_vendor@ builddir = @builddir@ datadir = @datadir@ datarootdir = @datarootdir@ docdir = @docdir@ dvidir = @dvidir@ exec_prefix = @exec_prefix@ host = @host@ host_alias = @host_alias@ host_cpu = @host_cpu@ host_os = @host_os@ host_vendor = @host_vendor@ htmldir = @htmldir@ includedir = @includedir@ infodir = @infodir@ install_sh = @install_sh@ libdir = @libdir@ libexecdir = @libexecdir@ localedir = @localedir@ localstatedir = @localstatedir@ mandir = @mandir@ mkdir_p = @mkdir_p@ oldincludedir = @oldincludedir@ pdfdir = @pdfdir@ prefix = @prefix@ program_transform_name = @program_transform_name@ psdir = @psdir@ sbindir = @sbindir@ sharedstatedir = @sharedstatedir@ srcdir = @srcdir@ sysconfdir = @sysconfdir@ target_alias = @target_alias@ top_build_prefix = @top_build_prefix@ top_builddir = @top_builddir@ top_srcdir = @top_srcdir@ AUTOMAKE_OPTIONS = 1.7h gnu no-dependencies ACLOCAL_AMFLAGS = -I ../build-aux SUBDIRS = src tests EXTRA_DIST = ChangeLog.1 PORTING README.woe32 Makefile.msvc config.h.msvc DISTCLEANFILES = termbold termnorm # Lead the user through the installation, in the hope that he will help us # by sending his config.log. TARGETSTACK = AM_MAKEFLAGS = TARGETSTACK="$(TARGETSTACK) $@" all: config.h $(MAKE) $(AM_MAKEFLAGS) all-recursive .SUFFIXES: am--refresh: Makefile @: $(srcdir)/Makefile.in: $(srcdir)/Makefile.am $(am__configure_deps) @for dep in $?; do \ case '$(am__configure_deps)' in \ *$$dep*) \ echo ' cd $(srcdir) && $(AUTOMAKE) --gnu'; \ $(am__cd) $(srcdir) && $(AUTOMAKE) --gnu \ && exit 0; \ exit 1;; \ esac; \ done; \ echo ' cd $(top_srcdir) && $(AUTOMAKE) --gnu Makefile'; \ $(am__cd) $(top_srcdir) && \ $(AUTOMAKE) --gnu Makefile .PRECIOUS: Makefile Makefile: $(srcdir)/Makefile.in $(top_builddir)/config.status @case '$?' in \ *config.status*) \ echo ' $(SHELL) ./config.status'; \ $(SHELL) ./config.status;; \ *) \ echo ' cd $(top_builddir) && $(SHELL) ./config.status $@ $(am__depfiles_maybe)'; \ cd $(top_builddir) && $(SHELL) ./config.status $@ $(am__depfiles_maybe);; \ esac; $(top_builddir)/config.status: $(top_srcdir)/configure $(CONFIG_STATUS_DEPENDENCIES) $(SHELL) ./config.status --recheck $(top_srcdir)/configure: $(am__configure_deps) $(am__cd) $(srcdir) && $(AUTOCONF) $(ACLOCAL_M4): $(am__aclocal_m4_deps) $(am__cd) $(srcdir) && $(ACLOCAL) $(ACLOCAL_AMFLAGS) $(am__aclocal_m4_deps): config.h: stamp-h1 @if test ! -f $@; then rm -f stamp-h1; else :; fi @if test ! -f $@; then $(MAKE) $(AM_MAKEFLAGS) stamp-h1; else :; fi stamp-h1: $(srcdir)/config.h.in $(top_builddir)/config.status @rm -f stamp-h1 cd $(top_builddir) && $(SHELL) ./config.status config.h $(srcdir)/config.h.in: $(am__configure_deps) ($(am__cd) $(top_srcdir) && $(AUTOHEADER)) rm -f stamp-h1 touch $@ distclean-hdr: -rm -f config.h stamp-h1 mostlyclean-libtool: -rm -f *.lo clean-libtool: -rm -rf .libs _libs distclean-libtool: -rm -f libtool config.lt # This directory's subdirectories are mostly independent; you can cd # into them and run `make' without going through this Makefile. # To change the values of `make' variables: instead of editing Makefiles, # (1) if the variable is set in `config.status', edit `config.status' # (which will cause the Makefiles to be regenerated when you run `make'); # (2) otherwise, pass the desired values on the `make' command line. $(RECURSIVE_TARGETS): @fail= failcom='exit 1'; \ for f in x $$MAKEFLAGS; do \ case $$f in \ *=* | --[!k]*);; \ *k*) failcom='fail=yes';; \ esac; \ done; \ dot_seen=no; \ target=`echo $@ | sed s/-recursive//`; \ list='$(SUBDIRS)'; for subdir in $$list; do \ echo "Making $$target in $$subdir"; \ if test "$$subdir" = "."; then \ dot_seen=yes; \ local_target="$$target-am"; \ else \ local_target="$$target"; \ fi; \ ($(am__cd) $$subdir && $(MAKE) $(AM_MAKEFLAGS) $$local_target) \ || eval $$failcom; \ done; \ if test "$$dot_seen" = "no"; then \ $(MAKE) $(AM_MAKEFLAGS) "$$target-am" || exit 1; \ fi; test -z "$$fail" $(RECURSIVE_CLEAN_TARGETS): @fail= failcom='exit 1'; \ for f in x $$MAKEFLAGS; do \ case $$f in \ *=* | --[!k]*);; \ *k*) failcom='fail=yes';; \ esac; \ done; \ dot_seen=no; \ case "$@" in \ distclean-* | maintainer-clean-*) list='$(DIST_SUBDIRS)' ;; \ *) list='$(SUBDIRS)' ;; \ esac; \ rev=''; for subdir in $$list; do \ if test "$$subdir" = "."; then :; else \ rev="$$subdir $$rev"; \ fi; \ done; \ rev="$$rev ."; \ target=`echo $@ | sed s/-recursive//`; \ for subdir in $$rev; do \ echo "Making $$target in $$subdir"; \ if test "$$subdir" = "."; then \ local_target="$$target-am"; \ else \ local_target="$$target"; \ fi; \ ($(am__cd) $$subdir && $(MAKE) $(AM_MAKEFLAGS) $$local_target) \ || eval $$failcom; \ done && test -z "$$fail" tags-recursive: list='$(SUBDIRS)'; for subdir in $$list; do \ test "$$subdir" = . || ($(am__cd) $$subdir && $(MAKE) $(AM_MAKEFLAGS) tags); \ done ctags-recursive: list='$(SUBDIRS)'; for subdir in $$list; do \ test "$$subdir" = . || ($(am__cd) $$subdir && $(MAKE) $(AM_MAKEFLAGS) ctags); \ done ID: $(HEADERS) $(SOURCES) $(LISP) $(TAGS_FILES) list='$(SOURCES) $(HEADERS) $(LISP) $(TAGS_FILES)'; \ unique=`for i in $$list; do \ if test -f "$$i"; then echo $$i; else echo $(srcdir)/$$i; fi; \ done | \ $(AWK) '{ files[$$0] = 1; nonempty = 1; } \ END { if (nonempty) { for (i in files) print i; }; }'`; \ mkid -fID $$unique tags: TAGS TAGS: tags-recursive $(HEADERS) $(SOURCES) config.h.in $(TAGS_DEPENDENCIES) \ $(TAGS_FILES) $(LISP) set x; \ here=`pwd`; \ if ($(ETAGS) --etags-include --version) >/dev/null 2>&1; then \ include_option=--etags-include; \ empty_fix=.; \ else \ include_option=--include; \ empty_fix=; \ fi; \ list='$(SUBDIRS)'; for subdir in $$list; do \ if test "$$subdir" = .; then :; else \ test ! -f $$subdir/TAGS || \ set "$$@" "$$include_option=$$here/$$subdir/TAGS"; \ fi; \ done; \ list='$(SOURCES) $(HEADERS) config.h.in $(LISP) $(TAGS_FILES)'; \ unique=`for i in $$list; do \ if test -f "$$i"; then echo $$i; else echo $(srcdir)/$$i; fi; \ done | \ $(AWK) '{ files[$$0] = 1; nonempty = 1; } \ END { if (nonempty) { for (i in files) print i; }; }'`; \ shift; \ if test -z "$(ETAGS_ARGS)$$*$$unique"; then :; else \ test -n "$$unique" || unique=$$empty_fix; \ if test $$# -gt 0; then \ $(ETAGS) $(ETAGSFLAGS) $(AM_ETAGSFLAGS) $(ETAGS_ARGS) \ "$$@" $$unique; \ else \ $(ETAGS) $(ETAGSFLAGS) $(AM_ETAGSFLAGS) $(ETAGS_ARGS) \ $$unique; \ fi; \ fi ctags: CTAGS CTAGS: ctags-recursive $(HEADERS) $(SOURCES) config.h.in $(TAGS_DEPENDENCIES) \ $(TAGS_FILES) $(LISP) list='$(SOURCES) $(HEADERS) config.h.in $(LISP) $(TAGS_FILES)'; \ unique=`for i in $$list; do \ if test -f "$$i"; then echo $$i; else echo $(srcdir)/$$i; fi; \ done | \ $(AWK) '{ files[$$0] = 1; nonempty = 1; } \ END { if (nonempty) { for (i in files) print i; }; }'`; \ test -z "$(CTAGS_ARGS)$$unique" \ || $(CTAGS) $(CTAGSFLAGS) $(AM_CTAGSFLAGS) $(CTAGS_ARGS) \ $$unique GTAGS: here=`$(am__cd) $(top_builddir) && pwd` \ && $(am__cd) $(top_srcdir) \ && gtags -i $(GTAGS_ARGS) "$$here" distclean-tags: -rm -f TAGS ID GTAGS GRTAGS GSYMS GPATH tags distdir: $(DISTFILES) $(am__remove_distdir) test -d "$(distdir)" || mkdir "$(distdir)" @srcdirstrip=`echo "$(srcdir)" | sed 's/[].[^$$\\*]/\\\\&/g'`; \ topsrcdirstrip=`echo "$(top_srcdir)" | sed 's/[].[^$$\\*]/\\\\&/g'`; \ list='$(DISTFILES)'; \ dist_files=`for file in $$list; do echo $$file; done | \ sed -e "s|^$$srcdirstrip/||;t" \ -e "s|^$$topsrcdirstrip/|$(top_builddir)/|;t"`; \ case $$dist_files in \ */*) $(MKDIR_P) `echo "$$dist_files" | \ sed '/\//!d;s|^|$(distdir)/|;s,/[^/]*$$,,' | \ sort -u` ;; \ esac; \ for file in $$dist_files; do \ if test -f $$file || test -d $$file; then d=.; else d=$(srcdir); fi; \ if test -d $$d/$$file; then \ dir=`echo "/$$file" | sed -e 's,/[^/]*$$,,'`; \ if test -d "$(distdir)/$$file"; then \ find "$(distdir)/$$file" -type d ! -perm -700 -exec chmod u+rwx {} \;; \ fi; \ if test -d $(srcdir)/$$file && test $$d != $(srcdir); then \ cp -fpR $(srcdir)/$$file "$(distdir)$$dir" || exit 1; \ find "$(distdir)/$$file" -type d ! -perm -700 -exec chmod u+rwx {} \;; \ fi; \ cp -fpR $$d/$$file "$(distdir)$$dir" || exit 1; \ else \ test -f "$(distdir)/$$file" \ || cp -p $$d/$$file "$(distdir)/$$file" \ || exit 1; \ fi; \ done @list='$(DIST_SUBDIRS)'; for subdir in $$list; do \ if test "$$subdir" = .; then :; else \ $(am__make_dryrun) \ || test -d "$(distdir)/$$subdir" \ || $(MKDIR_P) "$(distdir)/$$subdir" \ || exit 1; \ dir1=$$subdir; dir2="$(distdir)/$$subdir"; \ $(am__relativize); \ new_distdir=$$reldir; \ dir1=$$subdir; dir2="$(top_distdir)"; \ $(am__relativize); \ new_top_distdir=$$reldir; \ echo " (cd $$subdir && $(MAKE) $(AM_MAKEFLAGS) top_distdir="$$new_top_distdir" distdir="$$new_distdir" \\"; \ echo " am__remove_distdir=: am__skip_length_check=: am__skip_mode_fix=: distdir)"; \ ($(am__cd) $$subdir && \ $(MAKE) $(AM_MAKEFLAGS) \ top_distdir="$$new_top_distdir" \ distdir="$$new_distdir" \ am__remove_distdir=: \ am__skip_length_check=: \ am__skip_mode_fix=: \ distdir) \ || exit 1; \ fi; \ done -test -n "$(am__skip_mode_fix)" \ || find "$(distdir)" -type d ! -perm -755 \ -exec chmod u+rwx,go+rx {} \; -o \ ! -type d ! -perm -444 -links 1 -exec chmod a+r {} \; -o \ ! -type d ! -perm -400 -exec chmod a+r {} \; -o \ ! -type d ! -perm -444 -exec $(install_sh) -c -m a+r {} {} \; \ || chmod -R a+r "$(distdir)" dist-gzip: distdir tardir=$(distdir) && $(am__tar) | GZIP=$(GZIP_ENV) gzip -c >$(distdir).tar.gz $(am__remove_distdir) dist-bzip2: distdir tardir=$(distdir) && $(am__tar) | BZIP2=$${BZIP2--9} bzip2 -c >$(distdir).tar.bz2 $(am__remove_distdir) dist-lzip: distdir tardir=$(distdir) && $(am__tar) | lzip -c $${LZIP_OPT--9} >$(distdir).tar.lz $(am__remove_distdir) dist-lzma: distdir tardir=$(distdir) && $(am__tar) | lzma -9 -c >$(distdir).tar.lzma $(am__remove_distdir) dist-xz: distdir tardir=$(distdir) && $(am__tar) | XZ_OPT=$${XZ_OPT--e} xz -c >$(distdir).tar.xz $(am__remove_distdir) dist-tarZ: distdir tardir=$(distdir) && $(am__tar) | compress -c >$(distdir).tar.Z $(am__remove_distdir) dist-shar: distdir shar $(distdir) | GZIP=$(GZIP_ENV) gzip -c >$(distdir).shar.gz $(am__remove_distdir) dist-zip: distdir -rm -f $(distdir).zip zip -rq $(distdir).zip $(distdir) $(am__remove_distdir) dist dist-all: distdir tardir=$(distdir) && $(am__tar) | GZIP=$(GZIP_ENV) gzip -c >$(distdir).tar.gz $(am__remove_distdir) # This target untars the dist file and tries a VPATH configuration. Then # it guarantees that the distribution is self-contained by making another # tarfile. distcheck: dist case '$(DIST_ARCHIVES)' in \ *.tar.gz*) \ GZIP=$(GZIP_ENV) gzip -dc $(distdir).tar.gz | $(am__untar) ;;\ *.tar.bz2*) \ bzip2 -dc $(distdir).tar.bz2 | $(am__untar) ;;\ *.tar.lzma*) \ lzma -dc $(distdir).tar.lzma | $(am__untar) ;;\ *.tar.lz*) \ lzip -dc $(distdir).tar.lz | $(am__untar) ;;\ *.tar.xz*) \ xz -dc $(distdir).tar.xz | $(am__untar) ;;\ *.tar.Z*) \ uncompress -c $(distdir).tar.Z | $(am__untar) ;;\ *.shar.gz*) \ GZIP=$(GZIP_ENV) gzip -dc $(distdir).shar.gz | unshar ;;\ *.zip*) \ unzip $(distdir).zip ;;\ esac chmod -R a-w $(distdir); chmod u+w $(distdir) mkdir $(distdir)/_build mkdir $(distdir)/_inst chmod a-w $(distdir) test -d $(distdir)/_build || exit 0; \ dc_install_base=`$(am__cd) $(distdir)/_inst && pwd | sed -e 's,^[^:\\/]:[\\/],/,'` \ && dc_destdir="$${TMPDIR-/tmp}/am-dc-$$$$/" \ && am__cwd=`pwd` \ && $(am__cd) $(distdir)/_build \ && ../configure --srcdir=.. --prefix="$$dc_install_base" \ $(AM_DISTCHECK_CONFIGURE_FLAGS) \ $(DISTCHECK_CONFIGURE_FLAGS) \ && $(MAKE) $(AM_MAKEFLAGS) \ && $(MAKE) $(AM_MAKEFLAGS) dvi \ && $(MAKE) $(AM_MAKEFLAGS) check \ && $(MAKE) $(AM_MAKEFLAGS) install \ && $(MAKE) $(AM_MAKEFLAGS) installcheck \ && $(MAKE) $(AM_MAKEFLAGS) uninstall \ && $(MAKE) $(AM_MAKEFLAGS) distuninstallcheck_dir="$$dc_install_base" \ distuninstallcheck \ && chmod -R a-w "$$dc_install_base" \ && ({ \ (cd ../.. && umask 077 && mkdir "$$dc_destdir") \ && $(MAKE) $(AM_MAKEFLAGS) DESTDIR="$$dc_destdir" install \ && $(MAKE) $(AM_MAKEFLAGS) DESTDIR="$$dc_destdir" uninstall \ && $(MAKE) $(AM_MAKEFLAGS) DESTDIR="$$dc_destdir" \ distuninstallcheck_dir="$$dc_destdir" distuninstallcheck; \ } || { rm -rf "$$dc_destdir"; exit 1; }) \ && rm -rf "$$dc_destdir" \ && $(MAKE) $(AM_MAKEFLAGS) dist \ && rm -rf $(DIST_ARCHIVES) \ && $(MAKE) $(AM_MAKEFLAGS) distcleancheck \ && cd "$$am__cwd" \ || exit 1 $(am__remove_distdir) @(echo "$(distdir) archives ready for distribution: "; \ list='$(DIST_ARCHIVES)'; for i in $$list; do echo $$i; done) | \ sed -e 1h -e 1s/./=/g -e 1p -e 1x -e '$$p' -e '$$x' distuninstallcheck: @test -n '$(distuninstallcheck_dir)' || { \ echo 'ERROR: trying to run $@ with an empty' \ '$$(distuninstallcheck_dir)' >&2; \ exit 1; \ }; \ $(am__cd) '$(distuninstallcheck_dir)' || { \ echo 'ERROR: cannot chdir into $(distuninstallcheck_dir)' >&2; \ exit 1; \ }; \ test `$(am__distuninstallcheck_listfiles) | wc -l` -eq 0 \ || { echo "ERROR: files left after uninstall:" ; \ if test -n "$(DESTDIR)"; then \ echo " (check DESTDIR support)"; \ fi ; \ $(distuninstallcheck_listfiles) ; \ exit 1; } >&2 distcleancheck: distclean @if test '$(srcdir)' = . ; then \ echo "ERROR: distcleancheck can only run from a VPATH build" ; \ exit 1 ; \ fi @test `$(distcleancheck_listfiles) | wc -l` -eq 0 \ || { echo "ERROR: files left in build directory after distclean:" ; \ $(distcleancheck_listfiles) ; \ exit 1; } >&2 check-am: all-am check: check-recursive all-am: Makefile config.h installdirs: installdirs-recursive installdirs-am: install: install-recursive install-exec: install-exec-recursive install-data: install-data-recursive uninstall: uninstall-recursive install-am: all-am @$(MAKE) $(AM_MAKEFLAGS) install-exec-am install-data-am installcheck: installcheck-recursive install-strip: if test -z '$(STRIP)'; then \ $(MAKE) $(AM_MAKEFLAGS) INSTALL_PROGRAM="$(INSTALL_STRIP_PROGRAM)" \ install_sh_PROGRAM="$(INSTALL_STRIP_PROGRAM)" INSTALL_STRIP_FLAG=-s \ install; \ else \ $(MAKE) $(AM_MAKEFLAGS) INSTALL_PROGRAM="$(INSTALL_STRIP_PROGRAM)" \ install_sh_PROGRAM="$(INSTALL_STRIP_PROGRAM)" INSTALL_STRIP_FLAG=-s \ "INSTALL_PROGRAM_ENV=STRIPPROG='$(STRIP)'" install; \ fi mostlyclean-generic: clean-generic: distclean-generic: -test -z "$(CONFIG_CLEAN_FILES)" || rm -f $(CONFIG_CLEAN_FILES) -test . = "$(srcdir)" || test -z "$(CONFIG_CLEAN_VPATH_FILES)" || rm -f $(CONFIG_CLEAN_VPATH_FILES) -test -z "$(DISTCLEANFILES)" || rm -f $(DISTCLEANFILES) maintainer-clean-generic: @echo "This command is intended for maintainers to use" @echo "it deletes files that may require special tools to rebuild." clean: clean-recursive clean-am: clean-generic clean-libtool mostlyclean-am distclean: distclean-recursive -rm -f $(am__CONFIG_DISTCLEAN_FILES) -rm -f Makefile distclean-am: clean-am distclean-generic distclean-hdr \ distclean-libtool distclean-tags dvi: dvi-recursive dvi-am: html: html-recursive html-am: info: info-recursive info-am: install-data-am: @$(NORMAL_INSTALL) $(MAKE) $(AM_MAKEFLAGS) install-data-hook install-dvi: install-dvi-recursive install-dvi-am: install-exec-am: install-html: install-html-recursive install-html-am: install-info: install-info-recursive install-info-am: install-man: install-pdf: install-pdf-recursive install-pdf-am: install-ps: install-ps-recursive install-ps-am: installcheck-am: maintainer-clean: maintainer-clean-recursive -rm -f $(am__CONFIG_DISTCLEAN_FILES) -rm -rf $(top_srcdir)/autom4te.cache -rm -f Makefile maintainer-clean-am: distclean-am maintainer-clean-generic mostlyclean: mostlyclean-recursive mostlyclean-am: mostlyclean-generic mostlyclean-libtool pdf: pdf-recursive pdf-am: ps: ps-recursive ps-am: uninstall-am: .MAKE: $(RECURSIVE_CLEAN_TARGETS) $(RECURSIVE_TARGETS) all \ ctags-recursive install-am install-data-am install-strip \ tags-recursive .PHONY: $(RECURSIVE_CLEAN_TARGETS) $(RECURSIVE_TARGETS) CTAGS GTAGS \ all all-am am--refresh check check-am clean clean-generic \ clean-libtool ctags ctags-recursive dist dist-all dist-bzip2 \ dist-gzip dist-lzip dist-lzma dist-shar dist-tarZ dist-xz \ dist-zip distcheck distclean distclean-generic distclean-hdr \ distclean-libtool distclean-tags distcleancheck distdir \ distuninstallcheck dvi dvi-am html html-am info info-am \ install install-am install-data install-data-am \ install-data-hook install-dvi install-dvi-am install-exec \ install-exec-am install-html install-html-am install-info \ install-info-am install-man install-pdf install-pdf-am \ install-ps install-ps-am install-strip installcheck \ installcheck-am installdirs installdirs-am maintainer-clean \ maintainer-clean-generic mostlyclean mostlyclean-generic \ mostlyclean-libtool pdf pdf-am ps ps-am tags tags-recursive \ uninstall uninstall-am all-am: all-next all-next: @if echo "$(TARGETSTACK)" | grep check-recursive > /dev/null; then :; else \ if echo "$(TARGETSTACK)" | grep install-recursive > /dev/null; then :; else \ echo; echo "Now please type '"`cat termbold`"make check"`cat termnorm`"' to run a quick test suite. Hope it works."; echo; \ fi; \ fi check-am: check-next check-next: @when="Now"; \ if grep '^@PLATFORM@ .* @VERSION@$$' $(srcdir)/PORTING > /dev/null; then :; else \ case '@PLATFORM@' in \ i?86-*-linux* | x86_64-*-linux*) ;; \ *) \ echo; \ echo "Please send the following summary line via email to the author"; \ echo "Bruno Haible for inclusion into the list of"; \ echo "successfully tested platforms (see PORTING file). Please also"; \ echo "send the config.log file; this will help improving portability"; \ echo "of the package."; echo; \ if test @HAVE_SIGSEGV_RECOVERY@ = 1; then have1=yes; else have1=no; fi; \ if test @HAVE_STACK_OVERFLOW_RECOVERY@ = 1; then have2=yes; else have2=no; fi; \ echo `cat termbold`"libsigsegv: @PLATFORM@ | $$have1 | $$have2 | @VERSION@"`cat termnorm`; \ when="Then"; \ ;; \ esac; \ fi; \ echo; echo "$$when please type '"`cat termbold`"make install"`cat termnorm`"' to install the package."; echo install-data-hook: install-next install-next: @echo; echo "Now use the package; you can remove it later via '"`cat termbold`"make uninstall"`cat termnorm`"'."; echo # Rules for "make dist". $(srcdir)/config.h.msvc : config.h.in sed -e 's/#undef CFG_HANDLER/#define CFG_HANDLER "handler-win32.c"/' < $(srcdir)/config.h.in > $@ # Tell versions [3.59,3.63) of GNU make to not export all variables. # Otherwise a system limit (for SysV at least) may be exceeded. .NOEXPORT: smalltalk-3.2.5/sigsegv/config.h.msvc0000644000175000017500000000713612130456003014463 00000000000000/* config.h.in. Generated from configure.ac by autoheader. */ /* The name of the include file describing the fault handler. */ #undef CFG_FAULT /* The name of the file implementing the handler functionality. */ #define CFG_HANDLER "handler-win32.c" /* The name of the file implementing sigsegv_reset_onstack_flag. */ #undef CFG_LEAVE /* The name of the include file describing the Mach fault handler. */ #undef CFG_MACHFAULT /* The name of the include file describing the fault signals. */ #undef CFG_SIGNALS /* The name of the file determining the stack virtual memory area. */ #undef CFG_STACKVMA /* Define to 1 if you have the header file. */ #undef HAVE_DLFCN_H /* Define if getpagesize() is available as a function or a macro. */ #undef HAVE_GETPAGESIZE /* Define to 1 if you have the `getrlimit' function. */ #undef HAVE_GETRLIMIT /* Define to 1 if you have the header file. */ #undef HAVE_INTTYPES_H /* Define to 1 if you have the header file. */ #undef HAVE_MEMORY_H /* Define to 1 if you have the `mincore' function. */ #undef HAVE_MINCORE /* Define if defines MAP_ANON and mmaping with MAP_ANON works. */ #undef HAVE_MMAP_ANON /* Define if defines MAP_ANONYMOUS and mmaping with MAP_ANONYMOUS works. */ #undef HAVE_MMAP_ANONYMOUS /* Define if mmaping of the special device /dev/zero works. */ #undef HAVE_MMAP_DEVZERO /* Define if PAGESIZE is available as a macro. */ #undef HAVE_PAGESIZE /* Define to 1 if you have the `setrlimit' function. */ #undef HAVE_SETRLIMIT /* Define to 1 if you have the `sigaltstack' function. */ #undef HAVE_SIGALTSTACK /* Define if CFG_STACKVMA is set to a nontrivial source file. */ #undef HAVE_STACKVMA /* Define to 1 if you have the header file. */ #undef HAVE_STDINT_H /* Define to 1 if you have the header file. */ #undef HAVE_STDLIB_H /* Define to 1 if you have the header file. */ #undef HAVE_STRINGS_H /* Define to 1 if you have the header file. */ #undef HAVE_STRING_H /* Define if sysconf(_SC_PAGESIZE) is available as a function or a macro. */ #undef HAVE_SYSCONF_PAGESIZE /* Define to 1 if you have the header file. */ #undef HAVE_SYS_SIGNAL_H /* Define to 1 if you have the header file. */ #undef HAVE_SYS_STAT_H /* Define to 1 if you have the header file. */ #undef HAVE_SYS_TYPES_H /* Define to 1 if you have the header file. */ #undef HAVE_UNISTD_H /* Define if you have the sigaltstack() function and it works. */ #undef HAVE_WORKING_SIGALTSTACK /* Define to the sub-directory in which libtool stores uninstalled libraries. */ #undef LT_OBJDIR /* Name of package */ #undef PACKAGE /* Define to the address where bug reports for this package should be sent. */ #undef PACKAGE_BUGREPORT /* Define to the full name of this package. */ #undef PACKAGE_NAME /* Define to the full name and version of this package. */ #undef PACKAGE_STRING /* Define to the one symbol short name of this package. */ #undef PACKAGE_TARNAME /* Define to the home page for this package. */ #undef PACKAGE_URL /* Define to the version of this package. */ #undef PACKAGE_VERSION /* Define as the direction of stack growth for your system. STACK_DIRECTION > 0 => grows toward higher addresses STACK_DIRECTION < 0 => grows toward lower addresses STACK_DIRECTION = 0 => spaghetti stack. */ #undef STACK_DIRECTION /* Define to 1 if you have the ANSI C header files. */ #undef STDC_HEADERS /* Version number of package */ #undef VERSION /* Define to 'struct sigaltstack' if that's the type of the argument to sigaltstack */ #undef stack_t smalltalk-3.2.5/sigsegv/configure.ac0000644000175000017500000006173612130343734014400 00000000000000dnl Autoconf configuration for libsigsegv. dnl Process this file with autoconf to produce a configure script. dnl dnl Copyright (C) 2002-2009 Bruno Haible dnl dnl This program is free software; you can redistribute it and/or modify dnl it under the terms of the GNU General Public License as published by dnl the Free Software Foundation; either version 2, or (at your option) dnl any later version. dnl dnl This program is distributed in the hope that it will be useful, dnl but WITHOUT ANY WARRANTY; without even the implied warranty of dnl MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the dnl GNU General Public License for more details. dnl dnl You should have received a copy of the GNU General Public License dnl along with this program; if not, write to the Free Software Foundation, dnl Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. AC_PREREQ(2.52) AC_INIT AC_CONFIG_SRCDIR(src/sigsegv.h.in) AC_CONFIG_AUX_DIR([../build-aux]) AC_CONFIG_MACRO_DIR([../build-aux]) RSE_BOLD { echo; echo "${term_bold}Build Tools:${term_norm}"; } >& AS_MESSAGE_FD AM_INIT_AUTOMAKE(libsigsegv, 2.5) AM_CONFIG_HEADER(config.h) AC_PROG_CC AC_PROG_CPP AC_CANONICAL_HOST AC_MSG_CHECKING([host platform]) sv_cv_host="$host" changequote(,)dnl Autoconf 2.52 brokenness case "$host_os" in linux | linux-*) kernelversion=`uname -r | sed -e 's/^\([0-9.]*\).*/\1/'` sv_cv_host=`echo $sv_cv_host | sed -e "s/linux/linux$kernelversion/"` ;; esac changequote([,])dnl Autoconf 2.52 brokenness cat > conftest.c << EOF #include #ifdef __GNU_LIBRARY__ Version __GLIBC__ . __GLIBC_MINOR__ #endif EOF glibcversion=`$CPP $CPPFLAGS conftest.c 2>/dev/null | grep Version | sed -e 's/Version//' -e 's/ //g'` if test -n "$glibcversion"; then sv_cv_host="$sv_cv_host-glibc$glibcversion" fi AC_MSG_RESULT([$sv_cv_host]) PLATFORM="$sv_cv_host" AC_SUBST(PLATFORM) AC_PROG_INSTALL AC_PROG_SED AC_PROG_LIBTOOL # For testing cross-compilation behaviour. #cross_compiling=yes { echo; echo "${term_bold}Optional Platform Environment:${term_norm}"; } >& AS_MESSAGE_FD dnl Headers to be included with . On MacOS X (Darwin) one also dnl needs . AC_CHECK_HEADERS([sys/signal.h]) dnl List of signals that are sent when an invalid virtual memory address dnl is accessed, or when the stack overflows. case "$host_os" in sunos4* | freebsd* | openbsd* | netbsd* | dragonfly* | kfreebsd* | knetbsd*) CFG_SIGNALS=signals-bsd.h ;; hpux*) CFG_SIGNALS=signals-hpux.h ;; macos* | darwin*) CFG_SIGNALS=signals-macos.h ;; gnu*) CFG_SIGNALS=signals-hurd.h ;; *) CFG_SIGNALS=signals.h ;; esac AC_DEFINE_UNQUOTED(CFG_SIGNALS, "$CFG_SIGNALS", [The name of the include file describing the fault signals.]) # How to determine the memory page size. SV_GETPAGESIZE # How to allocate fresh memory using mmap. # (We need mmap, because mprotect() doesn't work on malloc()ed memory on # some systems.) SV_MMAP_ANON # How to write a SIGSEGV handler with access to the fault address. # On MacOS X 10.2 or newer, we don't need these tests, because we'll end up # using handler-macos.c anyway. If we were to perform the tests, 5 Crash Report # dialog windows would pop up. case "$host_os" in macos* | darwin[[6-9]]* | darwin[[1-9]][[0-9]]*) ;; *) dnl FIXME: Put in some more known values into the third argument. SV_TRY_FAULT([POSIX], sv_cv_fault_posix, [*-*-solaris2.[7-9] | i?86-*-linux2.[4-9]* | i?86-*-freebsd[4-9]* | alpha*-dec-osf[4-9]* | *-*-hpux11* | mips-sgi-irix6*], [], [int sig, siginfo_t *sip, void *ucp], [sip->si_addr], [action.sa_sigaction = &sigsegv_handler; action.sa_flags = SA_SIGINFO;]) SV_TRY_FAULT([Linux/i386], sv_cv_fault_linux_i386, [i?86-*-linux2.[2-9]*], [#include ], [int sig, struct sigcontext sc], [sc.cr2]) SV_TRY_FAULT([old Linux/i386], sv_cv_fault_linux_i386_old, [i?86-*-linux2.[2-9]*], [], [int sig, unsigned int more], [((unsigned long *) &more) [21]]) dnl FIXME: Put in some more known values into the third argument. SV_TRY_FAULT([Linux/m68k], sv_cv_fault_linux_m68k, [], [#include #include "$srcdir/src/fault-linux-m68k.c"], [int sig, int code, struct sigcontext *scp], [get_fault_addr (scp)]) dnl FIXME: Put in some more known values into the third argument. SV_TRY_FAULT([Linux/PowerPC], sv_cv_fault_linux_powerpc, [], [#include ], [int sig, struct sigcontext *scp], [scp->regs->dar]) dnl FIXME: Put in some more known values into the third argument. SV_TRY_FAULT([Linux/HPPA], sv_cv_fault_linux_hppa, [], [], [int sig, siginfo_t *sip, void *ucp], [sip->si_ptr], [action.sa_sigaction = &sigsegv_handler; action.sa_flags = SA_SIGINFO;]) dnl FIXME: Put in some more known values into the third argument. SV_TRY_FAULT([BSD], sv_cv_fault_bsd, [i?86-*-freebsd[4-9]*], [], [int sig, int code, struct sigcontext *scp, void *addr], [addr]) dnl FIXME: Put in some more known values into the third argument. SV_TRY_FAULT([IRIX], sv_cv_fault_irix, [mips-sgi-irix6*], [], [int sig, int code, struct sigcontext *scp], [(unsigned long) scp->sc_badvaddr]) dnl FIXME: Put in some more known values into the third argument. SV_TRY_FAULT([HP-UX HPPA], sv_cv_fault_hpux_hppa, [hppa*-*-hpux11*], [ #define USE_64BIT_REGS(mc) \ (((mc).ss_flags & SS_WIDEREGS) && ((mc).ss_flags & SS_NARROWISINVALID)) #define GET_CR21(mc) \ (USE_64BIT_REGS(mc) ? (mc).ss_wide.ss_64.ss_cr21 : (mc).ss_narrow.ss_cr21) ], [int sig, int code, struct sigcontext *scp], [GET_CR21 (scp->sc_sl.sl_ss)]) dnl FIXME: Put in some more known values into the third argument. SV_TRY_FAULT([OSF/1 Alpha], sv_cv_fault_osf_alpha, [alpha*-*-osf[4-9]* | alpha*-*-linux2.[4-9]*], [], [int sig, int code, struct sigcontext *scp], [scp->sc_traparg_a0]) dnl FIXME: Put in some more known values into the third argument. SV_TRY_FAULT([NetBSD Alpha], sv_cv_fault_netbsd_alpha, [alpha*-*-osf[4-9]* | alpha-*-*bsd*], [#include "$srcdir/src/fault-netbsd-alpha.c"], [int sig, int code, struct sigcontext *scp], [get_fault_addr (scp)]) dnl FIXME: Put in some more known values into the third argument. SV_TRY_FAULT([AIX], sv_cv_fault_aix, [*-*-aix[34]*], [], [int sig, int code, struct sigcontext *scp], [scp->sc_jmpbuf.jmp_context.o_vaddr]) SV_TRY_FAULT([MacOSX/Darwin7 PowerPC], sv_cv_fault_macosdarwin7_ppc, [powerpc-*-darwin7*], [#include "$srcdir/src/fault-macosdarwin7-powerpc.c"], [int sig, siginfo_t *sip, ucontext_t *ucp], [get_fault_addr (sip, ucp)], [action.sa_sigaction = &sigsegv_handler; action.sa_flags = SA_SIGINFO;]) if test "$sv_cv_fault_macosdarwin7_ppc" != yes; then SV_TRY_FAULT([MacOSX/Darwin5 PowerPC], sv_cv_fault_macosdarwin5_ppc, [powerpc-*-darwin5*], [#include "$srcdir/src/fault-macosdarwin5-powerpc.c"], [int sig, int code, struct sigcontext *scp], [get_fault_addr (scp)]) fi dnl FIXME: Put in some more known values into the third argument. SV_TRY_FAULT([Hurd], sv_cv_fault_hurd, [], [], [int sig, int code, struct sigcontext *scp], [code]) # End of MacOS X special casing. ;; esac dnl Now determine the fault handler include file. dnl We prefer the platform specific include files to the generic fault-posix.h dnl because the former often defines SIGSEGV_FAULT_STACKPOINTER. dnl Also we put the BSD test second-to-last, because the test may produce dnl false positives. CFG_HANDLER= CFG_FAULT= CFG_MACHFAULT= FAULT_CONTEXT=void FAULT_CONTEXT_INCLUDE= FAULT_CONTEXT_INCLUDE2= dnl dnl First the cases where the OS provides the fault address. dnl if test -z "$CFG_FAULT" && test "$sv_cv_fault_aix" = yes; then case "$host_cpu" in powerpc* | rs6000) CFG_FAULT=fault-aix3-powerpc.h ;; *) CFG_FAULT=fault-aix3.h ;; esac FAULT_CONTEXT='struct sigcontext' fi if test -z "$CFG_FAULT" && test "$sv_cv_fault_irix" = yes; then case "$host_cpu" in mips*) CFG_FAULT=fault-irix-mips.h ;; *) CFG_FAULT=fault-irix.h ;; esac FAULT_CONTEXT='struct sigcontext' fi if test -z "$CFG_FAULT" && test "$sv_cv_fault_hpux_hppa" = yes; then case "$host_cpu" in hppa* | parisc*) CFG_FAULT=fault-hpux-hppa.h ;; *) CFG_FAULT=fault-hpux.h ;; esac FAULT_CONTEXT='struct sigcontext' fi if test -z "$CFG_FAULT" && test "$sv_cv_fault_osf_alpha" = yes; then case "$host_cpu" in alpha*) CFG_FAULT=fault-osf-alpha.h ;; *) CFG_FAULT=fault-osf.h ;; esac FAULT_CONTEXT='struct sigcontext' fi if test -z "$CFG_FAULT" && test "$sv_cv_fault_netbsd_alpha" = yes; then case "$host_cpu" in alpha*) CFG_FAULT=fault-netbsd-alpha.h ;; esac FAULT_CONTEXT='struct sigcontext' fi if test -z "$CFG_FAULT" && test "$sv_cv_fault_linux_i386" = yes; then case "$host_cpu" in i?86 | x86_64) CFG_FAULT=fault-linux-i386.h ;; esac FAULT_CONTEXT='struct sigcontext' fi if test -z "$CFG_FAULT" && test "$sv_cv_fault_linux_i386_old" = yes; then case "$host_cpu" in i?86 | x86_64) CFG_FAULT=fault-linux-i386-old.h ;; esac FAULT_CONTEXT='struct sigcontext' fi if test -z "$CFG_FAULT" && test "$sv_cv_fault_linux_powerpc" = yes; then case "$host_cpu" in powerpc* | rs6000) CFG_FAULT=fault-linux-powerpc.h ;; esac FAULT_CONTEXT='struct sigcontext' fi if test -z "$CFG_FAULT" && test "$sv_cv_fault_linux_hppa" = yes; then case "$host_cpu" in hppa* | parisc*) CFG_FAULT=fault-linux-hppa.h ;; esac fi if test -z "$CFG_FAULT" && test "$sv_cv_fault_hurd" = yes; then case "$host_os" in netbsd*) # A false positive. ;; *) CFG_FAULT=fault-hurd.h FAULT_CONTEXT='struct sigcontext' ;; esac fi if test -z "$CFG_FAULT" && test "$sv_cv_fault_bsd" = yes; then case "$host_os" in freebsd* | dragonfly* | kfreebsd*) case "$host_cpu" in i?86 | x86_64) CFG_FAULT=fault-freebsd-i386.h FAULT_CONTEXT='struct sigcontext' ;; *) CFG_FAULT=fault-bsd.h FAULT_CONTEXT='void' ;; esac ;; *) CFG_FAULT=fault-bsd.h FAULT_CONTEXT='void' ;; esac fi if test -z "$CFG_FAULT" && test "$sv_cv_fault_posix" = yes; then case "$host_os" in openbsd*) case "$host_cpu" in i?86 | x86_64) CFG_FAULT=fault-openbsd-i386.h ;; *) CFG_FAULT=fault-openbsd.h ;; esac FAULT_CONTEXT='struct sigcontext' ;; linux*) case "$host_cpu" in ia64) CFG_FAULT=fault-linux-ia64.h FAULT_CONTEXT='struct sigcontext' ;; esac ;; esac if test -z "$CFG_FAULT"; then case "$host_os" in solaris*) case "$host_cpu" in i?86 | x86_64) CFG_FAULT=fault-solaris-i386.h ;; sparc*) CFG_FAULT=fault-solaris-sparc.h ;; *) CFG_FAULT=fault-solaris.h ;; esac ;; aix*) case "$host_cpu" in powerpc* | rs6000) CFG_FAULT=fault-aix5-powerpc.h ;; *) CFG_FAULT=fault-aix5.h ;; esac ;; netbsd*) CFG_FAULT=fault-netbsd.h ;; *) CFG_FAULT=fault-posix.h ;; esac FAULT_CONTEXT='ucontext_t' FAULT_CONTEXT_INCLUDE='#include ' fi fi if test -z "$CFG_FAULT"; then case "$host_os" in macos* | darwin[[6-9]]* | darwin[[1-9]][[0-9]]*) case "$host_cpu" in powerpc* | rs6000) CFG_MACHFAULT=machfault-macos-powerpc.h FAULT_CONTEXT='ppc_thread_state_t' ;; i?86 | x86_64) CFG_MACHFAULT=machfault-macos-i386.h FAULT_CONTEXT='i386_thread_state_t' ;; esac if test -n "$CFG_MACHFAULT"; then CFG_HANDLER=handler-macos.c FAULT_CONTEXT_INCLUDE='#include ' FAULT_CONTEXT_INCLUDE2='#include ' CFG_FAULT=fault-macos.h # nonexistent, just a dummy fi ;; esac fi dnl dnl Next, the cases where there is a hairy CPU dependent way to get the dnl fault address. dnl if test -z "$CFG_FAULT" && test "$sv_cv_fault_linux_m68k" = yes; then case "$host_cpu" in m68*) CFG_FAULT=fault-linux-m68k.h FAULT_CONTEXT='struct sigcontext' ;; esac fi if test -z "$CFG_FAULT" && test "$sv_cv_fault_macosdarwin7_ppc" = yes; then case "$host_cpu" in powerpc* | rs6000) CFG_FAULT=fault-macosdarwin7-powerpc.h FAULT_CONTEXT='ucontext_t' FAULT_CONTEXT_INCLUDE='#include ' FAULT_CONTEXT_INCLUDE2='#include ' ;; esac fi if test -z "$CFG_FAULT" && test "$sv_cv_fault_macosdarwin5_ppc" = yes; then case "$host_cpu" in powerpc* | rs6000) CFG_FAULT=fault-macosdarwin5-powerpc.h FAULT_CONTEXT='struct sigcontext' ;; esac fi if test -z "$CFG_FAULT"; then case "$host_os" in mingw* | cygwin*) FAULT_CONTEXT='CONTEXT' FAULT_CONTEXT_INCLUDE='#include ' CFG_FAULT=fault-win32.h # nonexistent, just a dummy ;; esac fi if test -n "$CFG_FAULT"; then sv_cv_have_sigsegv_recovery=yes else sv_cv_have_sigsegv_recovery=no dnl dnl No way to get the fault address. But other information is available. dnl case "$host_os" in linux*) case "$host_cpu" in alpha*) CFG_FAULT=fault-linux-alpha.h FAULT_CONTEXT='struct sigcontext' ;; arm* | strongarm* | xscale*) CFG_FAULT=fault-linux-arm.h FAULT_CONTEXT='struct sigcontext' ;; cris) CFG_FAULT=fault-linux-cris.h FAULT_CONTEXT='struct sigcontext' ;; mips*) CFG_FAULT=fault-linux-mips.h FAULT_CONTEXT='struct sigcontext' ;; s390*) CFG_FAULT=fault-linux-s390.h FAULT_CONTEXT='struct sigcontext' ;; sh*) CFG_FAULT=fault-linux-sh.h FAULT_CONTEXT='struct sigcontext' ;; sparc*) CFG_FAULT=fault-linux-sparc.h FAULT_CONTEXT='struct sigcontext' ;; x86_64) CFG_FAULT=fault-linux-x86_64.h FAULT_CONTEXT='struct sigcontext' ;; esac ;; beos*) case "$host_cpu" in i?86 | x86_64) CFG_FAULT=fault-beos-i386.h ;; *) CFG_FAULT=fault-beos.h ;; esac FAULT_CONTEXT='struct vregs' ;; macos* | darwin*) case "$host_cpu" in i?86 | x86_64) CFG_FAULT=fault-macos-i386.h ;; esac FAULT_CONTEXT='struct sigcontext' ;; esac fi AC_MSG_CHECKING([for the fault handler specifics]) if test -n "$CFG_FAULT"; then sv_cv_fault_include=$CFG_FAULT else if test -n "$CFG_MACHFAULT"; then sv_cv_fault_include=$CFG_MACHFAULT else sv_cv_fault_include=none fi fi AC_MSG_RESULT([$sv_cv_fault_include]) if test -z "$CFG_FAULT"; then CFG_FAULT=fault-none.h fi AC_DEFINE_UNQUOTED(CFG_FAULT, "$CFG_FAULT", [The name of the include file describing the fault handler.]) if test -z "$CFG_MACHFAULT"; then CFG_MACHFAULT=fault-none.h fi AC_DEFINE_UNQUOTED(CFG_MACHFAULT, "$CFG_MACHFAULT", [The name of the include file describing the Mach fault handler.]) AC_SUBST(FAULT_CONTEXT) AC_SUBST(FAULT_CONTEXT_INCLUDE) AC_SUBST(FAULT_CONTEXT_INCLUDE2) AC_MSG_CHECKING([if the system supports catching SIGSEGV]) AC_MSG_RESULT([$sv_cv_have_sigsegv_recovery]) if test $sv_cv_have_sigsegv_recovery != no; then HAVE_SIGSEGV_RECOVERY=1 else HAVE_SIGSEGV_RECOVERY=0 fi AC_SUBST(HAVE_SIGSEGV_RECOVERY) dnl The stackoverflow_context_t type depends on the CFG_FAULT include file. dnl Stack direction. AC_CACHE_CHECK([for stack direction], sv_cv_stack_direction_msg, [ case "$host_cpu" in dnl See the #define STACK_GROWS_DOWNWARD in gcc-3.1/gcc/config/*/*.h. a29k | \ alpha* | \ arc | \ arm* | strongarm* | xscale* | \ avr | \ c1 | c2 | c32 | c34 | c38 | \ clipper | \ cris | \ d30v | \ elxsi | \ fr30 | \ h8300 | \ i?86 | x86_64 | \ i860 | \ ia64 | \ m32r | \ m68* | \ m88k | \ mcore | \ mips* | \ mmix | \ mn10200 | \ mn10300 | \ ns32k | \ pdp11 | \ pj* | \ powerpc* | rs6000 | \ romp | \ s390* | \ sh* | \ sparc* | \ v850 | \ vax | \ xtensa) sv_cv_stack_direction=-1 ;; c4x | \ dsp16xx | \ i960 | \ hppa* | parisc* | \ stormy16 | \ we32k) sv_cv_stack_direction=1 ;; *) if test $cross_compiling = no; then cat > conftest.c < int get_stack_direction () { auto char dummy; static char *dummyaddr = (char *)0; if (dummyaddr != (char *)0) return &dummy > dummyaddr ? 1 : &dummy < dummyaddr ? -1 : 0; else { dummyaddr = &dummy; { int result = get_stack_direction (); /* The next assignment avoids tail recursion elimination (IRIX 6.4 CC). */ dummyaddr = (char *)0; return result; } } } int main () { printf ("%d\n", get_stack_direction ()); return 0; } EOF AC_TRY_EVAL(ac_link) sv_cv_stack_direction=`./conftest` else sv_cv_stack_direction=0 fi ;; esac case $sv_cv_stack_direction in 1) sv_cv_stack_direction_msg="grows up";; -1) sv_cv_stack_direction_msg="grows down";; *) sv_cv_stack_direction_msg="unknown";; esac ]) AC_DEFINE_UNQUOTED(STACK_DIRECTION, [$sv_cv_stack_direction], [Define as the direction of stack growth for your system. STACK_DIRECTION > 0 => grows toward higher addresses STACK_DIRECTION < 0 => grows toward lower addresses STACK_DIRECTION = 0 => spaghetti stack.]) dnl Determination of the stack's virtual memory area. AC_CACHE_CHECK([for PIOCMAP in sys/procfs.h], sv_cv_procfsvma, [ AC_TRY_LINK([#include ], [int x = PIOCNMAP + PIOCMAP; prmap_t y;], sv_cv_procfsvma=yes, sv_cv_procfsvma=no) ]) AC_CHECK_FUNCS([mincore]) CFG_STACKVMA= if test $sv_cv_procfsvma = yes; then CFG_STACKVMA=stackvma-procfs.c else case "$host_os" in linux*) CFG_STACKVMA=stackvma-linux.c ;; freebsd*|dragonfly*) CFG_STACKVMA=stackvma-freebsd.c ;; beos*) CFG_STACKVMA=stackvma-beos.c ;; macos* | darwin*) AC_CHECK_FUNC([vm_region], [CFG_STACKVMA=stackvma-mach.c]) ;; esac fi if test -z "$CFG_STACKVMA" && test $ac_cv_func_mincore = yes; then CFG_STACKVMA=stackvma-mincore.c fi if test -n "$CFG_STACKVMA"; then AC_DEFINE(HAVE_STACKVMA, 1, [Define if CFG_STACKVMA is set to a nontrivial source file.]) else CFG_STACKVMA=stackvma-none.c fi AC_DEFINE_UNQUOTED(CFG_STACKVMA, "$CFG_STACKVMA", [The name of the file determining the stack virtual memory area.]) AC_SUBST(CFG_STACKVMA) AC_CHECK_FUNCS([getrlimit setrlimit]) dnl Catching stack overflow requires an alternate signal stack. dnl The old "install a guard page" trick would be unreliable, because dnl we don't know where exactly to place the guard page. SV_SIGALTSTACK AC_CACHE_CHECK([if the system supports catching stack overflow], sv_cv_have_stack_overflow_recovery, [ dnl On Mach, it requires a machfault-*.h (see src/handler-macos.c). dnl On Unix, it requires either sigaltstack() or the BeOS set_signal_stack() dnl function, and on Unix it requires a fault-*.h or a stackvma-*.c with dnl certain properties (see src/handler-unix.c). if test "$CFG_MACHFAULT" != fault-none.h; then sv_cv_have_stack_overflow_recovery=yes else if test "$sv_cv_sigaltstack" != no; then sv_cv_have_stack_overflow_recovery=maybe else case "$host_os" in beos*) sv_cv_have_stack_overflow_recovery=maybe ;; mingw* | cygwin*) sv_cv_have_stack_overflow_recovery=yes ;; *) sv_cv_have_stack_overflow_recovery=no ;; esac fi fi if test $sv_cv_have_stack_overflow_recovery = maybe; then if test -n "$CFG_FAULT"; then AC_EGREP_CPP([xyzzy], [ #include "$srcdir/src/$CFG_FAULT" #ifdef SIGSEGV_FAULT_HANDLER_ARGLIST #ifdef SIGSEGV_FAULT_ADDRESS xyzzy #endif #endif ], [condA=true], [condA=false]) else condA=false fi if test -n "$CFG_FAULT"; then AC_EGREP_CPP([xyzzy], [ #include "$srcdir/src/$CFG_FAULT" #ifdef SIGSEGV_FAULT_HANDLER_ARGLIST #ifdef SIGSEGV_FAULT_STACKPOINTER xyzzy #endif #endif ], [condB=true], [condB=false]) else condB=false fi if test "$CFG_STACKVMA" != "stackvma-none.c"; then condC=true else condC=false fi if { $condA && $condB; } || { $condA && $condC; } || { $condB && $condC; }; then sv_cv_have_stack_overflow_recovery=yes else sv_cv_have_stack_overflow_recovery=no fi fi ]) if test $sv_cv_have_stack_overflow_recovery != no; then HAVE_STACK_OVERFLOW_RECOVERY=1 else HAVE_STACK_OVERFLOW_RECOVERY=0 fi AC_SUBST(HAVE_STACK_OVERFLOW_RECOVERY) # How to longjmp out of a signal handler, in such a way that the # alternate signal stack remains functional. # On MacOS X 10.2 or newer, we don't need these tests, because we'll end up # using handler-macos.c anyway. If we were to perform the tests, 2 Crash Report # dialog windows would pop up. case "$host_os" in macos* | darwin[[6-9]]* | darwin[[1-9]][[0-9]]*) ;; *) dnl FIXME: Put in some more known values into the third argument. SV_TRY_LEAVE_HANDLER_LONGJMP([], sv_cv_leave_handler_longjmp, [*-*-osf[4-9]* | *-*-hpux11* | *-*-linux2.[2-9]*], [], []) dnl FIXME: Put in some more known values into the third argument. SV_TRY_LEAVE_HANDLER_LONGJMP([ and sigaltstack], sv_cv_leave_handler_longjmp_sigaltstack, [*-*-freebsd*], [ #ifndef SS_ONSTACK #define SS_ONSTACK SA_ONSTACK #endif ], [stack_t ss; if (sigaltstack (NULL, &ss) >= 0) { ss.ss_flags &= ~SS_ONSTACK; sigaltstack (&ss, NULL); } ]) dnl FIXME: Put in some more known values into the third argument. SV_TRY_LEAVE_HANDLER_LONGJMP([ and setcontext], sv_cv_leave_handler_longjmp_setcontext, [*-*-irix* | *-*-solaris*], [#include #ifndef SS_ONSTACK #define SS_ONSTACK SA_ONSTACK #endif ], [static int fl; static ucontext_t uc; fl = 0; if (getcontext (&uc) >= 0) if (fl == 0) if (uc.uc_stack.ss_flags & SS_ONSTACK) { uc.uc_stack.ss_flags &= ~SS_ONSTACK; fl = 1; setcontext (&uc); } ]) # End of MacOS X special casing. ;; esac # How to siglongjmp out of a signal handler, in such a way that the # alternate signal stack remains functional. # On MacOS X 10.2 or newer, we don't need these tests, because we'll end up # using handler-macos.c anyway. If we were to perform the tests, 2 Crash Report # dialog windows would pop up. case "$host_os" in macos* | darwin[[6-9]]* | darwin[[1-9]][[0-9]]*) ;; *) dnl FIXME: Put in some more known values into the third argument. SV_TRY_LEAVE_HANDLER_SIGLONGJMP([], sv_cv_leave_handler_siglongjmp, [*-*-osf[4-9]* | *-*-hpux11* | *-*-linux2.[2-9]* | *-*-irix* | *-*-solaris*], [], []) dnl FIXME: Put in some more known values into the third argument. SV_TRY_LEAVE_HANDLER_SIGLONGJMP([ and sigaltstack], sv_cv_leave_handler_siglongjmp_sigaltstack, [*-*-freebsd*], [ #ifndef SS_ONSTACK #define SS_ONSTACK SA_ONSTACK #endif ], [stack_t ss; if (sigaltstack (NULL, &ss) >= 0) { ss.ss_flags &= ~SS_ONSTACK; sigaltstack (&ss, NULL); } ]) dnl FIXME: Put in some more known values into the third argument. SV_TRY_LEAVE_HANDLER_SIGLONGJMP([ and setcontext], sv_cv_leave_handler_siglongjmp_setcontext, [], [#include #ifndef SS_ONSTACK #define SS_ONSTACK SA_ONSTACK #endif ], [static int fl; static ucontext_t uc; fl = 0; if (getcontext(&uc) >= 0) if (fl == 0) if (uc.uc_stack.ss_flags & SS_ONSTACK) { uc.uc_stack.ss_flags &= ~SS_ONSTACK; fl = 1; setcontext(&uc); } ]) # End of MacOS X special casing. ;; esac CFG_LEAVE= if test "$sv_cv_leave_handler_longjmp" != no; then CFG_LEAVE=leave-nop.c else if test "$sv_cv_leave_handler_longjmp_sigaltstack" != no; then CFG_LEAVE=leave-sigaltstack.c else if test "$sv_cv_leave_handler_longjmp_setcontext" != no; then CFG_LEAVE=leave-setcontext.c fi fi fi case "$host_os" in # On BeOS, the 6 tests fail because sigaltstack() doesn't exist. # If one uses set_signal_stack() instead of sigaltstack(), the first # test actually works. i.e. sv_cv_leave_handler_longjmp would be 'yes'. beos*) CFG_LEAVE=leave-nop.c ;; esac if test -z "$CFG_LEAVE"; then CFG_LEAVE=leave-none.c fi AC_DEFINE_UNQUOTED(CFG_LEAVE, "$CFG_LEAVE", [The name of the file implementing sigsegv_reset_onstack_flag.]) AC_SUBST(CFG_LEAVE) case "$host_os" in mingw* | cygwin*) CFG_HANDLER=handler-win32.c ;; *) if test -z "$CFG_HANDLER"; then if test $sv_cv_have_sigsegv_recovery = no \ && test $sv_cv_have_stack_overflow_recovery = no; then CFG_HANDLER=handler-none.c else CFG_HANDLER=handler-unix.c fi fi ;; esac AC_DEFINE_UNQUOTED(CFG_HANDLER, "$CFG_HANDLER", [The name of the file implementing the handler functionality.]) AC_SUBST(CFG_HANDLER) { echo; echo "${term_bold}Build Parameters:${term_norm}"; } >& AS_MESSAGE_FD dnl Relocatability is a nop for this package. AC_RELOCATABLE_NOP { echo; echo "${term_bold}Output Substitution:${term_norm}"; } >& AS_MESSAGE_FD dnl AC_OUTPUT(Makefile) AC_OUTPUT([Makefile src/Makefile src/sigsegv.h tests/Makefile]) { echo; echo "Now please type '${term_bold}make${term_norm}' to compile. Good luck."; echo; } >& AS_MESSAGE_FD smalltalk-3.2.5/sigsegv/README0000644000175000017500000000774212130343734012767 00000000000000 GNU libsigsegv - Handling page faults in user mode This is a library for handling page faults in user mode. A page fault occurs when a program tries to access to a region of memory that is currently not available. Catching and handling a page fault is a useful technique for implementing: - pageable virtual memory, - memory-mapped access to persistent databases, - generational garbage collectors, - stack overflow handlers, - distributed shared memory, - ... This library supports three sets of functions, all defined in : - Global SIGSEGV handlers: sigsegv_install_handler, sigsegv_deinstall_handler. - Local SIGSEGV handlers (a handler per memory area): sigsegv_init, sigsegv_register, sigsegv_unregister, sigsegv_dispatch. - Stack overflow handlers: stackoverflow_install_handler, stackoverflow_deinstall_handler. Each of the three APIs can be used independently or simultaneously. For examples of the use of the APIs, see: - Global SIGSEGV handlers: see tests/sigsegv1.c. - Local SIGSEGV handlers: see tests/sigsegv2.c. - Stack overflow handlers: see tests/stackoverflow1.c. About portability. Some platforms don't support this functionality. In , the preprocessor macro HAVE_SIGSEGV_RECOVERY will be defined if global and local SIGSEGV handlers are available, and the preprocessor macro HAVE_STACK_OVERFLOW_RECOVERY will be defined if stack overflow handlers are available. Note that the declared functions are available in all cases; on platforms where HAVE_SIGSEGV_RECOVERY or HAVE_STACK_OVERFLOW_RECOVERY is not defined, they will simply always return an error code or do nothing. The list of platforms where this library is known to work is contained in the file PORTING. About pageable virtual memory. Pageable virtual memory is usually done in the operating system's kernel. This library helps in implementing the others. Installing a page fault handler is usually more efficient than doing access checks in software at every access, because it's effectively the hardware (the MMU) which checks whether a page is present or not. Note that if you use system calls (like read()) to write into write- protected pages, the system will react by returning -1 and setting errno to EFAULT, instead of signalling SIGSEGV and restarting the system call. In this case, the program has to do what the SIGSEGV handler would do, and then restart the read() operation. Some buggy systems (SunOS 4) go into an endless loop on this occasion; on these systems you have to make sure that an area is writable _before_ you call read() on it, About stack overflow handlers. In some applications, the stack overflow handler performs some cleanup or notifies the user and then immediately terminates the application. In other applications, the stack overflow handler longjmps back to a central point in the application. This library supports both uses. In the second case, the handler must ensure to restore the normal signal mask (because many signals are blocked while the handler is executed), and must also call sigsegv_leave_handler(); then only it can longjmp away. About shared libraries. This library builds as a static library by default. This seems useful because of the small size of the library (4 KB). Of course, you can build it as a shared library by specifying the configure option '--enable-shared'. Installation instructions on Unix: ./configure make make check make install Installation instructions on Woe32: See README.woe32. Copyright notice: Copyright 1998-1999, 2002-2007 Bruno Haible Copyright 2002-2007 Paolo Bonzini This is free software distributed under the GNU General Public Licence described in the file COPYING. There is ABSOLUTELY NO WARRANTY, explicit or implied, on this software. Download: ftp://ftp.gnu.org/pub/gnu/libsigsegv/libsigsegv-2.7.tar.gz http://ftp.gnu.org/gnu/libsigsegv/libsigsegv-2.7.tar.gz Homepage: http://libsigsegv.sourceforge.net/ smalltalk-3.2.5/sigsegv/src/0000755000175000017500000000000012130456003012736 500000000000000smalltalk-3.2.5/sigsegv/src/fault-macosdarwin7-powerpc.h0000644000175000017500000000235412130343734020225 00000000000000/* Fault handler information. MacOSX/Darwin7/PowerPC version. Copyright (C) 2002-2004, 2007 Bruno Haible This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. */ #include "fault-macosdarwin7-powerpc.c" #define SIGSEGV_FAULT_HANDLER_ARGLIST int sig, siginfo_t *sip, ucontext_t *ucp #define SIGSEGV_FAULT_ADDRESS (unsigned long) get_fault_addr (sip, ucp) #define SIGSEGV_FAULT_CONTEXT ucp #define SIGSEGV_FAULT_ADDRESS_FROM_SIGINFO #if __DARWIN_UNIX03 #define SIGSEGV_FAULT_STACKPOINTER ucp->uc_mcontext->ss.__r1 #else #define SIGSEGV_FAULT_STACKPOINTER ucp->uc_mcontext->ss.r1 #endif smalltalk-3.2.5/sigsegv/src/leave-none.c0000644000175000017500000000157512130343734015071 00000000000000/* Leaving a signal handler executing on the alternate stack. Copyright (C) 2002 Bruno Haible This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. */ /* No need to define sigsegv_reset_onstack_flag() on this platform. */ smalltalk-3.2.5/sigsegv/src/fault-hurd.h0000644000175000017500000000171412130343734015113 00000000000000/* Fault handler information. Hurd version. Copyright (C) 2002 Bruno Haible This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. */ #define SIGSEGV_FAULT_HANDLER_ARGLIST int sig, int code, struct sigcontext *scp #define SIGSEGV_FAULT_ADDRESS (unsigned long) code #define SIGSEGV_FAULT_CONTEXT scp smalltalk-3.2.5/sigsegv/src/signals-bsd.h0000644000175000017500000000177412130343734015254 00000000000000/* List of signals. BSD version. Copyright (C) 2002 Bruno Haible This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. */ /* List of signals that are sent when an invalid virtual memory address is accessed, or when the stack overflows. */ #define SIGSEGV_FOR_ALL_SIGNALS(var,body) \ { int var; var = SIGSEGV; { body } var = SIGBUS; { body } } smalltalk-3.2.5/sigsegv/src/fault-linux-x86_64.h0000644000175000017500000000173612130343734016250 00000000000000/* Fault handler information. Linux/x86_64 version. Copyright (C) 2002 Bruno Haible This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. */ #include #define SIGSEGV_FAULT_HANDLER_ARGLIST int sig, struct sigcontext sc #define SIGSEGV_FAULT_CONTEXT (&sc) #define SIGSEGV_FAULT_STACKPOINTER sc.rsp smalltalk-3.2.5/sigsegv/src/signals-hurd.h0000644000175000017500000000177512130343734015447 00000000000000/* List of signals. Hurd version. Copyright (C) 2002 Bruno Haible This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. */ /* List of signals that are sent when an invalid virtual memory address is accessed, or when the stack overflows. */ #define SIGSEGV_FOR_ALL_SIGNALS(var,body) \ { int var; var = SIGSEGV; { body } var = SIGBUS; { body } } smalltalk-3.2.5/sigsegv/src/fault-linux-m68k.c0000644000175000017500000000264512130343734016072 00000000000000/* Fault handler information subroutine. Linux/m68k version. * Taken from gcc-3.2/boehm-gc/os_dep.c. * * Copyright 1988, 1989 Hans-J. Boehm, Alan J. Demers * Copyright (c) 1991-1995 by Xerox Corporation. All rights reserved. * Copyright (c) 1996-1999 by Silicon Graphics. All rights reserved. * Copyright (c) 1999 by Hewlett-Packard Company. All rights reserved. * * THIS MATERIAL IS PROVIDED AS IS, WITH ABSOLUTELY NO WARRANTY EXPRESSED * OR IMPLIED. ANY USE IS AT YOUR OWN RISK. * * Permission is hereby granted to use or copy this program * for any purpose, provided the above notices are retained on all copies. * Permission to modify the code and to distribute modified code is granted, * provided the above notices are retained, and a notice that the code was * modified is included with the above copyright notice. */ static void * get_fault_addr (struct sigcontext *scp) { int format = (scp->sc_formatvec >> 12) & 0xf; unsigned long *framedata = (unsigned long *) (scp + 1); unsigned long ea; switch (format) { case 10: case 11: /* 68020/030 */ ea = framedata[2]; return (void *) ea; case 7: /* 68040 */ ea = framedata[3]; break; case 4: /* 68060 */ ea = framedata[0]; break; default: return (void *) 0; } if (framedata[1] & 0x08000000) /* Correct addr on misaligned access. */ ea = (ea + 4095) & ~4095; return (void *) ea; } smalltalk-3.2.5/sigsegv/src/fault-irix.h0000644000175000017500000000173012130343734015122 00000000000000/* Fault handler information. IRIX version. Copyright (C) 2002 Bruno Haible This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. */ #define SIGSEGV_FAULT_HANDLER_ARGLIST int sig, int code, struct sigcontext *scp #define SIGSEGV_FAULT_ADDRESS (unsigned long) scp->sc_badvaddr #define SIGSEGV_FAULT_CONTEXT scp smalltalk-3.2.5/sigsegv/src/fault-osf-alpha.h0000644000175000017500000000165212130343734016024 00000000000000/* Fault handler information. OSF/1 Alpha version. Copyright (C) 2002 Bruno Haible This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. */ #include "fault-osf.h" #define SIGSEGV_FAULT_ADDRESS scp->sc_traparg_a0 #define SIGSEGV_FAULT_STACKPOINTER scp->sc_regs[30] smalltalk-3.2.5/sigsegv/src/fault-linux-arm.h0000644000175000017500000000225512130343734016066 00000000000000/* Fault handler information. Linux/ARM version. Copyright (C) 2002 Bruno Haible This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. */ /* This file supports only kernels >= 2.2.14 or >= 2.3.35. Support for older kernels would be more complicated, see file glibc/sysdeps/unix/sysv/linux/arm/bits/armsigctx.h. */ #include #define SIGSEGV_FAULT_HANDLER_ARGLIST int sig, int r1, int r2, int r3, struct sigcontext sc #define SIGSEGV_FAULT_CONTEXT &sc #define SIGSEGV_FAULT_STACKPOINTER sc.arm_sp smalltalk-3.2.5/sigsegv/src/sigsegv.h.in0000644000175000017500000001373612130343734015123 00000000000000/* Page fault handling library. Copyright (C) 1998-1999, 2002, 2004-2007 Bruno Haible This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. */ #ifndef _SIGSEGV_H #define _SIGSEGV_H @FAULT_CONTEXT_INCLUDE@ @FAULT_CONTEXT_INCLUDE2@ /* HAVE_SIGSEGV_RECOVERY is defined if the system supports catching SIGSEGV. */ #if @HAVE_SIGSEGV_RECOVERY@ # define HAVE_SIGSEGV_RECOVERY 1 #endif /* HAVE_STACK_OVERFLOW_RECOVERY is defined if stack overflow can be caught. */ #if @HAVE_STACK_OVERFLOW_RECOVERY@ # define HAVE_STACK_OVERFLOW_RECOVERY 1 #endif #ifdef __cplusplus extern "C" { #endif #define LIBSIGSEGV_VERSION 0x0205 /* version number: (major<<8) + minor */ extern int libsigsegv_version; /* Likewise */ /* -------------------------------------------------------------------------- */ /* * The type of a global SIGSEGV handler. * The fault address is passed as argument. * The access type (read access or write access) is not passed; your handler * has to know itself how to distinguish these two cases. * The second argument is 0, meaning it could also be a stack overflow, or 1, * meaning the handler should seriously try to fix the fault. * The return value should be nonzero if the handler has done its job * and no other handler should be called, or 0 if the handler declines * responsibility for the given address. */ typedef int (*sigsegv_handler_t) (void* fault_address, int serious); /* * Installs a global SIGSEGV handler. * This should be called once only, and it ignores any previously installed * SIGSEGV handler. * Returns 0 on success, or -1 if the system doesn't support catching SIGSEGV. */ extern int sigsegv_install_handler (sigsegv_handler_t handler); /* * Deinstalls the global SIGSEGV handler. * This goes back to the state where no SIGSEGV handler is installed. */ extern void sigsegv_deinstall_handler (void); /* * Prepares leaving a SIGSEGV handler (through longjmp or similar means). */ extern void sigsegv_leave_handler (void); /* * The type of a context passed to a stack overflow handler. * This type is system dependent; on some platforms it is an 'ucontext_t *', * on some platforms it is a 'struct sigcontext *', on others merely an * opaque 'void *'. */ typedef @FAULT_CONTEXT@ *stackoverflow_context_t; /* * The type of a stack overflow handler. * Such a handler should perform a longjmp call in order to reduce the amount * of stack needed. It must not return. * The emergency argument is 0 when the stack could be repared, or 1 if the * application should better save its state and exit now. */ typedef void (*stackoverflow_handler_t) (int emergency, stackoverflow_context_t scp); /* * Installs a stack overflow handler. * The extra_stack argument is a pointer to a pre-allocated area used as a * stack for executing the handler. It is typically allocated by use of * `alloca' during `main'. Its size should be sufficiently large. * The following code determines an appropriate size: * #include * #ifndef SIGSTKSZ / * glibc defines SIGSTKSZ for this purpose * / * # define SIGSTKSZ 16384 / * on most platforms, 16 KB are sufficient * / * #endif * Returns 0 on success, or -1 if the system doesn't support catching stack * overflow. */ extern int stackoverflow_install_handler (stackoverflow_handler_t handler, void* extra_stack, unsigned long extra_stack_size); /* * Deinstalls the stack overflow handler. */ extern void stackoverflow_deinstall_handler (void); /* -------------------------------------------------------------------------- */ /* * The following structure and functions permit to define different SIGSEGV * policies on different address ranges. */ /* * The type of a local SIGSEGV handler. * The fault address is passed as argument. * The second argument is fixed arbitrary user data. * The return value should be nonzero if the handler has done its job * and no other handler should be called, or 0 if the handler declines * responsibility for the given address. */ typedef int (*sigsegv_area_handler_t) (void* fault_address, void* user_arg); /* * This structure represents a table of memory areas (address range intervals), * with an local SIGSEGV handler for each. */ typedef struct sigsegv_dispatcher { void* tree; } sigsegv_dispatcher; /* * Initializes a sigsegv_dispatcher structure. */ extern void sigsegv_init (sigsegv_dispatcher* dispatcher); /* * Adds a local SIGSEGV handler to a sigsegv_dispatcher structure. * It will cover the interval [address..address+len-1]. * Returns a "ticket" that can be used to remove the handler later. */ extern void* sigsegv_register (sigsegv_dispatcher* dispatcher, void* address, unsigned long len, sigsegv_area_handler_t handler, void* handler_arg); /* * Removes a local SIGSEGV handler. */ extern void sigsegv_unregister (sigsegv_dispatcher* dispatcher, void* ticket); /* * Call the local SIGSEGV handler responsible for the given fault address. * Return the handler's return value. 0 means that no handler has been found, * or that a handler was found but declined responsibility. */ extern int sigsegv_dispatch (sigsegv_dispatcher* dispatcher, void* fault_address); /* -------------------------------------------------------------------------- */ #ifdef __cplusplus } #endif #endif /* _SIGSEGV_H */ smalltalk-3.2.5/sigsegv/src/fault-macos-i386.h0000644000175000017500000000172012130343734015737 00000000000000/* Fault handler information. MacOSX/i386 version. Copyright (C) 2003 Paolo Bonzini This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. */ #define SIGSEGV_FAULT_HANDLER_ARGLIST int sig, int code, struct sigcontext *scp #define SIGSEGV_FAULT_CONTEXT scp #define SIGSEGV_FAULT_STACKPOINTER scp->sc_esp smalltalk-3.2.5/sigsegv/src/fault-aix5.h0000644000175000017500000000147612130343734015024 00000000000000/* Fault handler information. AIX 5 version. Copyright (C) 2005 Bruno Haible This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. */ #include "fault-posix.h" smalltalk-3.2.5/sigsegv/src/fault-netbsd-alpha.c0000644000175000017500000000323512130343734016506 00000000000000/* Fault handler information subroutine. NetBSD/Alpha version. * Taken from gcc-3.3/boehm-gc/os_dep.c. * * Copyright 1988, 1989 Hans-J. Boehm, Alan J. Demers * Copyright (c) 1991-1995 by Xerox Corporation. All rights reserved. * Copyright (c) 1996-1999 by Silicon Graphics. All rights reserved. * Copyright (c) 1999 by Hewlett-Packard Company. All rights reserved. * * THIS MATERIAL IS PROVIDED AS IS, WITH ABSOLUTELY NO WARRANTY EXPRESSED * OR IMPLIED. ANY USE IS AT YOUR OWN RISK. * * Permission is hereby granted to use or copy this program * for any purpose, provided the above notices are retained on all copies. * Permission to modify the code and to distribute modified code is granted, * provided the above notices are retained, and a notice that the code was * modified is included with the above copyright notice. */ /* Decodes the machine instruction which was responsible for the sending of the SIGBUS signal. Luckily this is much easier than, say, on the PowerPC. */ static void * get_fault_addr (struct sigcontext *scp) { unsigned int instr = *((unsigned int *)(scp->sc_pc)); unsigned long faultaddr; /* Instructions which access memory have operands of the form ARG_MEM or ARG_FMEM, consisting of - a base register specification (PRB) in bits 20..16, - a memory displacement (MDISP) in bits 15..0, - an general register specification (RA) or a floating-point register specification (FA) in bits 25..21. See binutils-2.13.90.0.16/opcodes/alpha-opc.c. */ faultaddr = scp->sc_regs[(instr >> 16) & 0x1f]; faultaddr += (unsigned long) (long) (((int)instr << 16) >> 16); return (void *) faultaddr; } smalltalk-3.2.5/sigsegv/src/handler-win32.c0000644000175000017500000002655412130343734015421 00000000000000/* Fault handler information. Woe32 version. Copyright (C) 1993-1999, 2002-2003, 2007 Bruno Haible Copyright (C) 2003 Paolo Bonzini This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. */ #include "sigsegv.h" #define WIN32_LEAN_AND_MEAN /* avoid including junk */ #include #include /* * extern LPTOP_LEVEL_EXCEPTION_FILTER SetUnhandledExceptionFilter (LPTOP_LEVEL_EXCEPTION_FILTER TopLevelExceptionFilter); * extern DWORD VirtualQuery (LPCVOID Address, PMEMORY_BASIC_INFORMATION Buffer, DWORD Length); * extern BOOL VirtualProtect (LPVOID Address, DWORD Size, DWORD NewProtect, PDWORD OldProtect); * extern DWORD GetLastError (void); */ /* User's SIGSEGV handler. */ static sigsegv_handler_t user_handler = (sigsegv_handler_t) NULL; /* Stack overflow handling is tricky: First, we must catch a STATUS_STACK_OVERFLOW exception. This is signalled when the guard page at the end of the stack has been touched. The operating system remaps the page with protection PAGE_READWRITE and only then calls our exception handler. Actually, it's even more complicated: The stack has the following layout: | |guard|----------stack-----------| and when the guard page is touched, the system maps it PAGE_READWRITE and allocates a new guard page below it: | |guard|-------------stack--------------| Only when no new guard page can be allocated (because the maximum stack size has been reached), will we see an exception. |guard|-------------------------stack--------------------------| Second, we must reinstall the guard page. Otherwise, on the next stack overflow, the application will simply crash (on WinNT: silently, on Win95: with an error message box and freezing the system). But since we don't know where %esp points to during the exception handling, we must first leave the exception handler, before we can restore the guard page. And %esp must be made to point to a reasonable value before we do this. Note: On WinNT, the guard page has protection PAGE_READWRITE|PAGE_GUARD. On Win95, which doesn't know PAGE_GUARD, it has protection PAGE_NOACCESS. */ static stackoverflow_handler_t stk_user_handler = (stackoverflow_handler_t) NULL; static unsigned long stk_extra_stack; static unsigned long stk_extra_stack_size; static void stack_overflow_handler (unsigned long faulting_page_address, stackoverflow_context_t context) { MEMORY_BASIC_INFORMATION info; DWORD oldprot; unsigned long base; unsigned long address; /* First get stack's base address. */ if (VirtualQuery ((void*) faulting_page_address, &info, sizeof (info)) != sizeof (info)) goto failed; base = (unsigned long) info.AllocationBase; /* Now search for the first existing page. */ address = base; for (;;) { if (VirtualQuery ((void*) address, &info, sizeof (info)) != sizeof (info)) goto failed; if (address != (unsigned long) info.BaseAddress) goto failed; if (info.State != MEM_FREE) { if ((unsigned long) info.AllocationBase != base) goto failed; if (info.State == MEM_COMMIT) break; } address = (unsigned long) info.BaseAddress + info.RegionSize; } /* Now add the PAGE_GUARD bit to the first existing page. */ /* On WinNT this works... */ if (VirtualProtect (info.BaseAddress, 0x1000, info.Protect | PAGE_GUARD, &oldprot)) goto ok; if (GetLastError () == ERROR_INVALID_PARAMETER) /* ... but on Win95 we need this: */ if (VirtualProtect (info.BaseAddress, 0x1000, PAGE_NOACCESS, &oldprot)) goto ok; failed: for (;;) (*stk_user_handler) (1, context); ok: for (;;) (*stk_user_handler) (0, context); } /* This is the stack overflow and page fault handler. */ static LONG WINAPI main_exception_filter (EXCEPTION_POINTERS *ExceptionInfo) { if ((stk_user_handler && ExceptionInfo->ExceptionRecord->ExceptionCode == STATUS_STACK_OVERFLOW ) || (user_handler != (sigsegv_handler_t)NULL && ExceptionInfo->ExceptionRecord->ExceptionCode == EXCEPTION_ACCESS_VIOLATION )) { #if 0 /* for debugging only */ printf ("Exception!\n"); printf ("Code = 0x%x\n", ExceptionInfo->ExceptionRecord->ExceptionCode); printf ("Flags = 0x%x\n", ExceptionInfo->ExceptionRecord->ExceptionFlags); printf ("Address = 0x%x\n", ExceptionInfo->ExceptionRecord->ExceptionAddress); printf ("Params:"); { DWORD i; for (i = 0; i < ExceptionInfo->ExceptionRecord->NumberParameters; i++) printf (" 0x%x,", ExceptionInfo->ExceptionRecord->ExceptionInformation[i]); } printf ("\n"); printf ("Registers:\n"); printf ("eip = 0x%x\n", ExceptionInfo->ContextRecord->Eip); printf ("eax = 0x%x, ", ExceptionInfo->ContextRecord->Eax); printf ("ebx = 0x%x, ", ExceptionInfo->ContextRecord->Ebx); printf ("ecx = 0x%x, ", ExceptionInfo->ContextRecord->Ecx); printf ("edx = 0x%x\n", ExceptionInfo->ContextRecord->Edx); printf ("esi = 0x%x, ", ExceptionInfo->ContextRecord->Esi); printf ("edi = 0x%x, ", ExceptionInfo->ContextRecord->Edi); printf ("ebp = 0x%x, ", ExceptionInfo->ContextRecord->Ebp); printf ("esp = 0x%x\n", ExceptionInfo->ContextRecord->Esp); #endif if (ExceptionInfo->ExceptionRecord->NumberParameters == 2) { if (stk_user_handler && ExceptionInfo->ExceptionRecord->ExceptionCode == STATUS_STACK_OVERFLOW) { char *address = (char *) ExceptionInfo->ExceptionRecord->ExceptionInformation[1]; /* Restart the program, giving it a sane value for %esp. At the same time, copy the contents of ExceptionInfo->ContextRecord (which, on Windows XP, happens to be allocated in the guard page, where it will be inaccessible as soon as we restore the PAGE_GUARD bit!) to this new stack. */ unsigned long faulting_page_address = (unsigned long)address & -0x1000; unsigned long new_safe_esp = ((stk_extra_stack + stk_extra_stack_size) & -16); CONTEXT *orig_context = ExceptionInfo->ContextRecord; CONTEXT *safe_context = (CONTEXT *) (new_safe_esp -= sizeof (CONTEXT)); /* make room */ memcpy (safe_context, orig_context, sizeof (CONTEXT)); new_safe_esp -= 8; /* make room for arguments */ new_safe_esp &= -16; /* align */ new_safe_esp -= 4; /* make room for (unused) return address slot */ ExceptionInfo->ContextRecord->Esp = new_safe_esp; /* Call stack_overflow_handler(faulting_page_address,safe_context). */ ExceptionInfo->ContextRecord->Eip = (unsigned long)&stack_overflow_handler; *(unsigned long *)(new_safe_esp + 4) = faulting_page_address; *(unsigned long *)(new_safe_esp + 8) = (unsigned long) safe_context; return EXCEPTION_CONTINUE_EXECUTION; } if (user_handler != (sigsegv_handler_t) NULL && ExceptionInfo->ExceptionRecord->ExceptionCode == EXCEPTION_ACCESS_VIOLATION) { /* ExceptionInfo->ExceptionRecord->ExceptionInformation[0] is 1 if it's a write access, 0 if it's a read access. But we don't need this info because we don't have it on Unix either. */ void *address = (void *) ExceptionInfo->ExceptionRecord->ExceptionInformation[1]; if ((*user_handler) (address, 1)) return EXCEPTION_CONTINUE_EXECUTION; } } } return EXCEPTION_CONTINUE_SEARCH; } #if defined __CYGWIN__ && defined __i386__ /* In Cygwin programs, SetUnhandledExceptionFilter has no effect because Cygwin installs a global exception handler. We have to dig deep in order to install our main_exception_filter. */ /* Data structures for the current thread's exception handler chain. On the x86 Windows uses register fs, offset 0 to point to the current exception handler; Cygwin mucks with it, so we must do the same... :-/ */ /* Magic taken from winsup/cygwin/include/exceptions.h. */ struct exception_list { struct exception_list *prev; int (*handler) (EXCEPTION_RECORD *, void *, CONTEXT *, void *); }; typedef struct exception_list exception_list; /* Magic taken from winsup/cygwin/exceptions.cc. */ __asm__ (".equ __except_list,0"); extern exception_list *_except_list __asm__ ("%fs:__except_list"); /* For debugging. _except_list is not otherwise accessible from gdb. */ static exception_list * debug_get_except_list () { return _except_list; } /* Cygwin's original exception handler. */ static int (*cygwin_exception_handler) (EXCEPTION_RECORD *, void *, CONTEXT *, void *); /* Our exception handler. */ static int libsigsegv_exception_handler (EXCEPTION_RECORD *exception, void *frame, CONTEXT *context, void *dispatch) { EXCEPTION_POINTERS ExceptionInfo; ExceptionInfo.ExceptionRecord = exception; ExceptionInfo.ContextRecord = context; if (main_exception_filter (&ExceptionInfo) == EXCEPTION_CONTINUE_SEARCH) return cygwin_exception_handler (exception, frame, context, dispatch); else return 0; } static void do_install_main_exception_filter () { /* We cannot insert any handler into the chain, because such handlers must lie on the stack (?). Instead, we have to replace(!) Cygwin's global exception handler. */ cygwin_exception_handler = _except_list->handler; _except_list->handler = libsigsegv_exception_handler; } #else static void do_install_main_exception_filter () { SetUnhandledExceptionFilter ((LPTOP_LEVEL_EXCEPTION_FILTER) &main_exception_filter); } #endif static void install_main_exception_filter () { static int main_exception_filter_installed = 0; if (!main_exception_filter_installed) { do_install_main_exception_filter (); main_exception_filter_installed = 1; } } int sigsegv_install_handler (sigsegv_handler_t handler) { user_handler = handler; install_main_exception_filter (); return 0; } void sigsegv_deinstall_handler (void) { user_handler = (sigsegv_handler_t) NULL; } void sigsegv_leave_handler (void) { } int stackoverflow_install_handler (stackoverflow_handler_t handler, void *extra_stack, unsigned long extra_stack_size) { stk_user_handler = handler; stk_extra_stack = (unsigned long) extra_stack; stk_extra_stack_size = extra_stack_size; install_main_exception_filter (); return 0; } void stackoverflow_deinstall_handler (void) { stk_user_handler = (stackoverflow_handler_t) NULL; } smalltalk-3.2.5/sigsegv/src/fault-freebsd-i386.h0000644000175000017500000000221012130343734016242 00000000000000/* Fault handler information. FreeBSD/i386 version. Copyright (C) 2002, 2007 Bruno Haible This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. */ #define SIGSEGV_FAULT_HANDLER_ARGLIST int sig, int code, struct sigcontext *scp, void *addr #define SIGSEGV_FAULT_ADDRESS addr #define SIGSEGV_FAULT_CONTEXT scp #if defined __x86_64__ /* 64 bit registers */ #define SIGSEGV_FAULT_STACKPOINTER scp->sc_rsp #else /* 32 bit registers */ #define SIGSEGV_FAULT_STACKPOINTER scp->sc_esp #endif smalltalk-3.2.5/sigsegv/src/fault-bsd.h0000644000175000017500000000163412130343734014722 00000000000000/* Fault handler information. BSD Unix version. Copyright (C) 2002 Bruno Haible This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. */ #define SIGSEGV_FAULT_HANDLER_ARGLIST int sig, int code, void *scp, void *addr #define SIGSEGV_FAULT_ADDRESS addr smalltalk-3.2.5/sigsegv/src/handler-unix.c0000644000175000017500000003650512130343734015437 00000000000000/* Fault handler information. Unix version. Copyright (C) 1993-1999, 2002-2003 Bruno Haible This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. */ #include "sigsegv.h" /* On the average Unix platform, we define HAVE_SIGSEGV_RECOVERY if there is a fault-*.h include file which defines SIGSEGV_FAULT_HANDLER_ARGLIST and SIGSEGV_FAULT_ADDRESS. HAVE_STACK_OVERFLOW_RECOVERY if HAVE_SIGALTSTACK is set and at least two of the following are true: A) There is a fault-*.h include file which defines SIGSEGV_FAULT_HANDLER_ARGLIST and SIGSEGV_FAULT_ADDRESS. B) There is a fault-*.h include file which defines SIGSEGV_FAULT_HANDLER_ARGLIST and SIGSEGV_FAULT_STACKPOINTER. C) There is a stackvma-*.c, other than stackvma-none.c, which defines sigsegv_get_vma. Why? Obviously, to catch stack overflow, we need an alternate signal stack; this requires kernel support. But we also need to distinguish (with a reasonable confidence) a stack overflow from a regular SIGSEGV. If we have A) and B), we use the Heuristic AB: If the fault address is near the stack pointer, it's a stack overflow. If we have A) and C), we use the Heuristic AC: If the fault address is near and beyond the bottom of the stack's virtual memory area, it's a stack overflow. If we have B) and C), we use the Heuristic BC: If the stack pointer is near the bottom of the stack's virtual memory area, it's a stack overflow. This heuristic comes in two flavours: On OSes which let the stack's VMA grow continuously, we determine the bottom by use of getrlimit(). On OSes which preallocate the stack's VMA with its maximum size (like BeOS), we use the stack's VMA directly. */ #include /* needed for NULL on SunOS4 */ #include #include #if HAVE_SYS_SIGNAL_H # include #endif #include /* For MacOSX. */ #ifndef SS_DISABLE #define SS_DISABLE SA_DISABLE #endif #include "fault.h" #include CFG_SIGNALS #if HAVE_STACK_OVERFLOW_RECOVERY #include /* perror */ #if HAVE_GETRLIMIT # include # include # include /* declares struct rlimit */ #endif /* Platform dependent: Determine the virtual memory area of a given address. */ #include "stackvma.h" /* Platform dependent: Leaving a signal handler executing on the alternate stack. */ #include "leave.h" #if HAVE_STACKVMA /* Address of the last byte belonging to the stack vma. */ static unsigned long stack_top = 0; /* Needs to be called once only. */ static void remember_stack_top (void *some_variable_on_stack) { struct vma_struct vma; if (sigsegv_get_vma ((unsigned long) some_variable_on_stack, &vma) >= 0) stack_top = vma.end - 1; } #endif /* HAVE_STACKVMA */ static stackoverflow_handler_t stk_user_handler = (stackoverflow_handler_t)NULL; static unsigned long stk_extra_stack; static unsigned long stk_extra_stack_size; #endif /* HAVE_STACK_OVERFLOW_RECOVERY */ #if HAVE_SIGSEGV_RECOVERY /* User's SIGSEGV handler. */ static sigsegv_handler_t user_handler = (sigsegv_handler_t)NULL; #endif /* HAVE_SIGSEGV_RECOVERY */ /* Our SIGSEGV handler, with OS dependent argument list. */ #if HAVE_SIGSEGV_RECOVERY static void sigsegv_handler (SIGSEGV_FAULT_HANDLER_ARGLIST) { void *address = (void *) (SIGSEGV_FAULT_ADDRESS); #if HAVE_STACK_OVERFLOW_RECOVERY #if !(HAVE_STACKVMA || defined SIGSEGV_FAULT_STACKPOINTER) #error "Insufficient heuristics for detecting a stack overflow. Either define CFG_STACKVMA and HAVE_STACKVMA correctly, or define SIGSEGV_FAULT_STACKPOINTER correctly, or undefine HAVE_STACK_OVERFLOW_RECOVERY!" #endif /* Call user's handler. */ if (user_handler && (*user_handler) (address, 0)) { /* Handler successful. */ } else { /* Handler declined responsibility. */ /* Did the user install a stack overflow handler? */ if (stk_user_handler) { /* See whether it was a stack overflow. If so, longjump away. */ #ifdef SIGSEGV_FAULT_STACKPOINTER unsigned long old_sp = (unsigned long) (SIGSEGV_FAULT_STACKPOINTER); #ifdef __ia64 unsigned long old_bsp = (unsigned long) (SIGSEGV_FAULT_BSP_POINTER); #endif #endif #if HAVE_STACKVMA /* Were we able to determine the stack top? */ if (stack_top) { /* Determine stack bounds. */ struct vma_struct vma; if (sigsegv_get_vma (stack_top, &vma) >= 0) { /* Heuristic AC: If the fault_address is nearer to the stack segment's [start,end] than to the previous segment, we consider it a stack overflow. In the case of IA-64, we know that the previous segment is the up-growing bsp segment, and either of the two stacks can overflow. */ unsigned long addr = (unsigned long) address; #ifdef __ia64 if (addr >= vma.prev_end && addr <= vma.end - 1) #else #if STACK_DIRECTION < 0 if (addr >= vma.start ? (addr <= vma.end - 1) : vma.is_near_this (addr, &vma)) #else if (addr <= vma.end - 1 ? (addr >= vma.start) : vma.is_near_this (addr, &vma)) #endif #endif #else /* Heuristic AB: If the fault address is near the stack pointer, it's a stack overflow. */ unsigned long addr = (unsigned long) address; if ((addr <= old_sp + 4096 && old_sp <= addr + 4096) #ifdef __ia64 || (addr <= old_bsp + 4096 && old_bsp <= addr + 4096) #endif ) { { #endif { #ifdef SIGSEGV_FAULT_STACKPOINTER int emergency = (old_sp >= stk_extra_stack && old_sp <= stk_extra_stack + stk_extra_stack_size); stackoverflow_context_t context = (SIGSEGV_FAULT_CONTEXT); #else int emergency = 0; stackoverflow_context_t context = (void *) 0; #endif /* Call user's handler. */ (*stk_user_handler) (emergency, context); } } } } #endif /* HAVE_STACK_OVERFLOW_RECOVERY */ if (user_handler && (*user_handler) (address, 1)) { /* Handler successful. */ } else { /* Handler declined responsibility for real. */ /* Remove ourselves and dump core. */ SIGSEGV_FOR_ALL_SIGNALS (sig, signal (sig, SIG_DFL);) } #if HAVE_STACK_OVERFLOW_RECOVERY } #endif /* HAVE_STACK_OVERFLOW_RECOVERY */ } #elif HAVE_STACK_OVERFLOW_RECOVERY static void #ifdef SIGSEGV_FAULT_STACKPOINTER sigsegv_handler (SIGSEGV_FAULT_HANDLER_ARGLIST) #else sigsegv_handler (int sig) #endif { #if !((HAVE_GETRLIMIT && defined RLIMIT_STACK) || defined SIGSEGV_FAULT_STACKPOINTER) #error "Insufficient heuristics for detecting a stack overflow. Either define SIGSEGV_FAULT_STACKPOINTER correctly, or undefine HAVE_STACK_OVERFLOW_RECOVERY!" #endif /* Did the user install a handler? */ if (stk_user_handler) { /* See whether it was a stack overflow. If so, longjump away. */ #ifdef SIGSEGV_FAULT_STACKPOINTER unsigned long old_sp = (unsigned long) (SIGSEGV_FAULT_STACKPOINTER); #endif /* Were we able to determine the stack top? */ if (stack_top) { /* Determine stack bounds. */ struct vma_struct vma; if (sigsegv_get_vma (stack_top, &vma) >= 0) { #if HAVE_GETRLIMIT && defined RLIMIT_STACK /* Heuristic BC: If the stack size has reached its maximal size, and old_sp is near the low end, we consider it a stack overflow. */ struct rlimit rl; if (getrlimit (RLIMIT_STACK, &rl) >= 0) { unsigned long current_stack_size = vma.end - vma.start; unsigned long max_stack_size = rl.rlim_cur; if (current_stack_size <= max_stack_size + 4096 && max_stack_size <= current_stack_size + 4096 #else { if (1 #endif #ifdef SIGSEGV_FAULT_STACKPOINTER /* Heuristic BC: If we know old_sp, and it is neither near the low end, nor in the alternate stack, then it's probably not a stack overflow. */ && ((old_sp >= stk_extra_stack && old_sp <= stk_extra_stack + stk_extra_stack_size) #if STACK_DIRECTION < 0 || (old_sp <= vma.start + 4096 && vma.start <= old_sp + 4096)) #else || (old_sp <= vma.end + 4096 && vma.end <= old_sp + 4096)) #endif #endif ) { #ifdef SIGSEGV_FAULT_STACKPOINTER int emergency = (old_sp >= stk_extra_stack && old_sp <= stk_extra_stack + stk_extra_stack_size); stackoverflow_context_t context = (SIGSEGV_FAULT_CONTEXT); #else int emergency = 0; stackoverflow_context_t context = (void *) 0; #endif /* Call user's handler. */ (*stk_user_handler)(emergency,context); } } } } } /* Remove ourselves and dump core. */ SIGSEGV_FOR_ALL_SIGNALS (sig, signal (sig, SIG_DFL);) } #endif static void install_for (int sig) { struct sigaction action; #ifdef SIGSEGV_FAULT_ADDRESS_FROM_SIGINFO action.sa_sigaction = &sigsegv_handler; #else action.sa_handler = (void (*) (int)) &sigsegv_handler; #endif /* Block most signals while SIGSEGV is being handled. */ /* Signals SIGKILL, SIGSTOP cannot be blocked. */ /* Signals SIGCONT, SIGTSTP, SIGTTIN, SIGTTOU are not blocked because dealing with these signals seems dangerous. */ /* Signals SIGILL, SIGABRT, SIGFPE, SIGSEGV, SIGTRAP, SIGIOT, SIGEMT, SIGBUS, SIGSYS, SIGSTKFLT are not blocked because these are synchronous signals, which may require immediate intervention, otherwise the process may starve. */ sigemptyset (&action.sa_mask); #ifdef SIGHUP sigaddset (&action.sa_mask,SIGHUP); #endif #ifdef SIGINT sigaddset (&action.sa_mask,SIGINT); #endif #ifdef SIGQUIT sigaddset (&action.sa_mask,SIGQUIT); #endif #ifdef SIGPIPE sigaddset (&action.sa_mask,SIGPIPE); #endif #ifdef SIGALRM sigaddset (&action.sa_mask,SIGALRM); #endif #ifdef SIGTERM sigaddset (&action.sa_mask,SIGTERM); #endif #ifdef SIGUSR1 sigaddset (&action.sa_mask,SIGUSR1); #endif #ifdef SIGUSR2 sigaddset (&action.sa_mask,SIGUSR2); #endif #ifdef SIGCHLD sigaddset (&action.sa_mask,SIGCHLD); #endif #ifdef SIGCLD sigaddset (&action.sa_mask,SIGCLD); #endif #ifdef SIGURG sigaddset (&action.sa_mask,SIGURG); #endif #ifdef SIGIO sigaddset (&action.sa_mask,SIGIO); #endif #ifdef SIGPOLL sigaddset (&action.sa_mask,SIGPOLL); #endif #ifdef SIGXCPU sigaddset (&action.sa_mask,SIGXCPU); #endif #ifdef SIGXFSZ sigaddset (&action.sa_mask,SIGXFSZ); #endif #ifdef SIGVTALRM sigaddset (&action.sa_mask,SIGVTALRM); #endif #ifdef SIGPROF sigaddset (&action.sa_mask,SIGPROF); #endif #ifdef SIGPWR sigaddset (&action.sa_mask,SIGPWR); #endif #ifdef SIGLOST sigaddset (&action.sa_mask,SIGLOST); #endif #ifdef SIGWINCH sigaddset (&action.sa_mask,SIGWINCH); #endif /* Note that sigaction() implicitly adds sig itself to action.sa_mask. */ /* Ask the OS to provide a structure siginfo_t to the handler. */ #ifdef SIGSEGV_FAULT_ADDRESS_FROM_SIGINFO action.sa_flags = SA_SIGINFO; #else action.sa_flags = 0; #endif #if HAVE_STACK_OVERFLOW_RECOVERY && HAVE_SIGALTSTACK /* not BeOS */ /* Work around Linux 2.2.5 bug: If SA_ONSTACK is specified but sigaltstack() has not been called, the kernel will busy loop, eating CPU time. So avoid setting SA_ONSTACK until the user has requested stack overflow handling. */ if (stk_user_handler) action.sa_flags |= SA_ONSTACK; #endif sigaction (sig, &action, (struct sigaction *) NULL); } int sigsegv_install_handler (sigsegv_handler_t handler) { #if HAVE_SIGSEGV_RECOVERY user_handler = handler; SIGSEGV_FOR_ALL_SIGNALS (sig, install_for (sig);) return 0; #else return -1; #endif } void sigsegv_deinstall_handler (void) { #if HAVE_SIGSEGV_RECOVERY user_handler = (sigsegv_handler_t)NULL; #if HAVE_STACK_OVERFLOW_RECOVERY if (!stk_user_handler) #endif { SIGSEGV_FOR_ALL_SIGNALS (sig, signal (sig, SIG_DFL);) } #endif } void sigsegv_leave_handler (void) { #if HAVE_STACK_OVERFLOW_RECOVERY /* * Reset the system's knowledge that we are executing on the alternate * stack. If we didn't do that, siglongjmp would be needed instead of * longjmp to leave the signal handler. */ sigsegv_reset_onstack_flag (); #endif } int stackoverflow_install_handler (stackoverflow_handler_t handler, void *extra_stack, unsigned long extra_stack_size) { #if HAVE_STACK_OVERFLOW_RECOVERY #if HAVE_STACKVMA if (!stack_top) { int dummy; remember_stack_top (&dummy); if (!stack_top) return -1; } #endif stk_user_handler = handler; stk_extra_stack = (unsigned long) extra_stack; stk_extra_stack_size = extra_stack_size; #ifdef __BEOS__ set_signal_stack (extra_stack, extra_stack_size); #else /* HAVE_SIGALTSTACK */ { stack_t ss; ss.ss_sp = extra_stack; ss.ss_size = extra_stack_size; ss.ss_flags = 0; /* no SS_DISABLE */ if (sigaltstack (&ss, (stack_t*)0) < 0) return -1; } #endif /* Install the signal handlers with SA_ONSTACK. */ SIGSEGV_FOR_ALL_SIGNALS (sig, install_for (sig);) return 0; #else return -1; #endif } void stackoverflow_deinstall_handler (void) { #if HAVE_STACK_OVERFLOW_RECOVERY stk_user_handler = (stackoverflow_handler_t) NULL; #if HAVE_SIGSEGV_RECOVERY if (user_handler) { /* Reinstall the signal handlers without SA_ONSTACK, to avoid Linux bug. */ SIGSEGV_FOR_ALL_SIGNALS (sig, install_for (sig);) } else #endif { SIGSEGV_FOR_ALL_SIGNALS (sig, signal (sig, SIG_DFL);) } #ifdef __BEOS__ /* We cannot undo the effect of set_signal_stack. */ fprintf (stderr, "libsigsegv (stackoverflow_deinstall_handler): not supported on this platform\n"); #else /* HAVE_SIGALTSTACK */ { stack_t ss; ss.ss_flags = SS_DISABLE; if (sigaltstack (&ss, (stack_t *) 0) < 0) perror ("libsigsegv (stackoverflow_deinstall_handler)"); } #endif #endif } smalltalk-3.2.5/sigsegv/src/fault-none.h0000644000175000017500000000154312130343734015110 00000000000000/* Fault handler information. Version for platforms lacking support, or with a self-contained handler.c. Copyright (C) 2002 Bruno Haible This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. */ smalltalk-3.2.5/sigsegv/src/leave.h0000644000175000017500000000154412130343734014135 00000000000000/* Leaving a signal handler executing on the alternate stack. Copyright (C) 2002 Bruno Haible This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. */ extern void sigsegv_reset_onstack_flag (void); smalltalk-3.2.5/sigsegv/src/signals-hpux.h0000644000175000017500000000177612130343734015472 00000000000000/* List of signals. HP-UX version. Copyright (C) 2002 Bruno Haible This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. */ /* List of signals that are sent when an invalid virtual memory address is accessed, or when the stack overflows. */ #define SIGSEGV_FOR_ALL_SIGNALS(var,body) \ { int var; var = SIGSEGV; { body } var = SIGBUS; { body } } smalltalk-3.2.5/sigsegv/src/fault-aix3-powerpc.h0000644000175000017500000000164012130343734016470 00000000000000/* Fault handler information. AIX3/PowerPC and AIX4/PowerPC version. Copyright (C) 2002-2005 Bruno Haible This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. */ #include "fault-aix3.h" #define SIGSEGV_FAULT_STACKPOINTER scp->sc_jmpbuf.jmp_context.gpr[1] smalltalk-3.2.5/sigsegv/src/fault-linux-sh.h0000644000175000017500000000177212130343734015724 00000000000000/* Fault handler information. Linux/SH version. Copyright (C) 2002 Bruno Haible This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. */ #include #define SIGSEGV_FAULT_HANDLER_ARGLIST int sig, int r1, int r2, int r3, struct sigcontext sc #define SIGSEGV_FAULT_CONTEXT (&sc) #define SIGSEGV_FAULT_STACKPOINTER sc.sc_regs[15] smalltalk-3.2.5/sigsegv/src/fault-linux-mips.h0000644000175000017500000000175712130343734016265 00000000000000/* Fault handler information. Linux/MIPS version Copyright (C) 2002 Bruno Haible This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. */ #include #define SIGSEGV_FAULT_HANDLER_ARGLIST int sig, int code, struct sigcontext *scp #define SIGSEGV_FAULT_CONTEXT scp #define SIGSEGV_FAULT_STACKPOINTER scp->sc_regs[29] smalltalk-3.2.5/sigsegv/src/fault-linux-ia64.h0000644000175000017500000000261512130343734016052 00000000000000/* Fault handler information. Linux/IA-64 version. Copyright (C) 2002-2003 Bruno Haible This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. */ #define SIGSEGV_FAULT_HANDLER_ARGLIST int sig, siginfo_t *sip, struct sigcontext *scp #define SIGSEGV_FAULT_ADDRESS sip->si_addr #define SIGSEGV_FAULT_CONTEXT scp /* IA-64 has two stack pointers, one that grows down, called $r12, and one that grows up, called $bsp/$bspstore. */ #define SIGSEGV_FAULT_STACKPOINTER scp->sc_gr[12] /* It would be better to access $bspstore instead of $bsp but I don't know where to find it in 'struct sigcontext'. Anyway, it doesn't matter because $bsp and $bspstore never differ by more than ca. 1 KB. */ #define SIGSEGV_FAULT_BSP_POINTER scp->sc_ar_bsp smalltalk-3.2.5/sigsegv/src/handler-none.c0000644000175000017500000000225212130343734015403 00000000000000/* Fault handler information. Copyright (C) 1993-1999, 2002 Bruno Haible This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. */ #include "sigsegv.h" int sigsegv_install_handler (sigsegv_handler_t handler) { return -1; } void sigsegv_deinstall_handler (void) { } void sigsegv_leave_handler (void) { } int stackoverflow_install_handler (stackoverflow_handler_t handler, void *extra_stack, unsigned long extra_stack_size) { return -1; } void stackoverflow_deinstall_handler (void) { } smalltalk-3.2.5/sigsegv/src/fault-macosdarwin5-powerpc.h0000644000175000017500000000233312130343734020220 00000000000000/* Fault handler information. MacOSX/Darwin5/PowerPC version. Copyright (C) 2002-2004 Bruno Haible This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. */ #include "fault-macosdarwin5-powerpc.c" #define SIGSEGV_FAULT_HANDLER_ARGLIST int sig, int code, struct sigcontext *scp #define SIGSEGV_FAULT_ADDRESS (unsigned long) get_fault_addr (scp) #define SIGSEGV_FAULT_CONTEXT scp #if 0 #define SIGSEGV_FAULT_STACKPOINTER (&((unsigned int *) scp->sc_regs)[2])[1] #endif #define SIGSEGV_FAULT_STACKPOINTER (scp->sc_regs ? ((unsigned int *) scp->sc_regs)[3] : scp->sc_sp) smalltalk-3.2.5/sigsegv/src/fault-linux-i386-old.h0000644000175000017500000000230512130343734016550 00000000000000/* Fault handler information. Linux/i386 version, supports old kernels. Copyright (C) 2002 Bruno Haible This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. */ /* Don't include here, because some older kernels don't have it or don't define `struct sigcontext' in it. */ #define SIGSEGV_FAULT_HANDLER_ARGLIST int sig, unsigned long more #define SIGSEGV_FAULT_ADDRESS ((unsigned long *) &more) [21] #define SIGSEGV_FAULT_CONTEXT ((struct sigcontext *) &more) #define SIGSEGV_FAULT_STACKPOINTER ((unsigned long *) &more) [7] smalltalk-3.2.5/sigsegv/src/fault.h0000644000175000017500000000244412130343734014154 00000000000000/* Fault handler information. Copyright (C) 2002 Bruno Haible This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. */ /* The included file defines: SIGSEGV_FAULT_HANDLER_ARGLIST is the argument list for the actual fault handler. SIGSEGV_FAULT_ADDRESS is a macro for fetching the fault address. and if available (optional): SIGSEGV_FAULT_CONTEXT is a macro giving a pointer to the entire fault context (i.e. the register set etc.). SIGSEGV_FAULT_STACKPOINTER is a macro for fetching the stackpointer at the moment the fault occurred. */ #include CFG_FAULT smalltalk-3.2.5/sigsegv/src/stackvma-none.c0000644000175000017500000000165512130343734015605 00000000000000/* Determine the virtual memory area of a given address. Copyright (C) 2002 Bruno Haible This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. */ #include "stackvma.h" int sigsegv_get_vma (unsigned long address, struct vma_struct *vma) { /* No way. */ return -1; } smalltalk-3.2.5/sigsegv/src/leave-setcontext.c0000644000175000017500000000273412130343734016330 00000000000000/* Leaving a signal handler executing on the alternate stack. Copyright (C) 2002 Bruno Haible This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. */ #include #include void sigsegv_reset_onstack_flag (void) { ucontext_t uc; if (getcontext (&uc) >= 0) /* getcontext returns twice. We are interested in the returned context only the first time, i.e. when the SS_ONSTACK bit is set. */ if (uc.uc_stack.ss_flags & SS_ONSTACK) { uc.uc_stack.ss_flags &= ~SS_ONSTACK; /* Note that setcontext() does not refill uc. Therefore if setcontext() keeps SS_ONSTACK set in the kernel, either setcontext() will return -1 or getcontext() will return a second time, with the SS_ONSTACK bit being cleared. */ setcontext (&uc); } } smalltalk-3.2.5/sigsegv/src/fault-netbsd.h0000644000175000017500000000250312130343734015425 00000000000000/* Fault handler information. NetBSD version. Copyright (C) 2006 Bruno Haible This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. */ #include "fault-posix.h" /* _UC_MACHINE_SP is a platform independent macro. Defined in , see http://cvsweb.netbsd.org/bsdweb.cgi/src/sys/arch/$arch/include/mcontext.h Supported on alpha, amd64, i386, ia64, m68k, mips, powerpc, sparc since NetBSD 2.0. On i386, _UC_MACHINE_SP is the same as ->uc_mcontext.__gregs[_REG_UESP], and apparently the same value as ->uc_mcontext.__gregs[_REG_ESP]. */ #ifdef _UC_MACHINE_SP #define SIGSEGV_FAULT_STACKPOINTER _UC_MACHINE_SP ((ucontext_t *) ucp) #endif smalltalk-3.2.5/sigsegv/src/stackvma-mach.c0000644000175000017500000000705212130343734015553 00000000000000/* Determine the virtual memory area of a given address. Mach version. Copyright (C) 2003, 2006 Paolo Bonzini This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. */ #include "stackvma.h" #include #ifdef HAVE_UNISTD_H # include #endif #include #include #include #ifndef NeXT #include #endif #include "stackvma-simple.c" int sigsegv_get_vma (unsigned long req_address, struct vma_struct *vma) { unsigned long prev_address = 0, prev_size = 0; unsigned long join_address = 0, join_size = 0; int more = 1; vm_address_t address; vm_size_t size; mach_port_t object_name; #ifdef VM_REGION_BASIC_INFO task_t task = mach_task_self (); struct vm_region_basic_info info; mach_msg_type_number_t info_count = VM_REGION_BASIC_INFO_COUNT; #else task_t task = task_self (); vm_prot_t protection, max_protection; vm_inherit_t inheritance; boolean_t shared; vm_offset_t offset; #endif for (address = VM_MIN_ADDRESS; more; address += size) { #ifdef VM_REGION_BASIC_INFO more = (vm_region (task, &address, &size, VM_REGION_BASIC_INFO, (vm_region_info_t)&info, &info_count, &object_name) == KERN_SUCCESS); #else more = (vm_region (task, &address, &size, &protection, &max_protection, &inheritance, &shared, &object_name, &offset) == KERN_SUCCESS); #endif if (!more) { address = join_address + join_size; size = 0; } if ((unsigned long) address == join_address + join_size) join_size += size; else { prev_address = join_address; prev_size = join_size; join_address = (unsigned long) address; join_size = size; } #ifdef VM_REGION_BASIC_INFO if (object_name != MACH_PORT_NULL) mach_port_deallocate (mach_task_self (), object_name); info_count = VM_REGION_BASIC_INFO_COUNT; #endif #if STACK_DIRECTION < 0 if (join_address <= req_address && join_address + join_size > req_address) { vma->start = join_address; vma->end = join_address + join_size; vma->prev_end = prev_address + prev_size; vma->is_near_this = simple_is_near_this; return 0; } #else if (prev_address <= req_address && prev_address + prev_size > req_address) { vma->start = prev_address; vma->end = prev_address + prev_size; vma->next_start = join_address; vma->is_near_this = simple_is_near_this; return 0; } #endif } #if STACK_DIRECTION > 0 if (join_address <= req_address && join_address + size > req_address) { vma->start = prev_address; vma->end = prev_address + prev_size; vma->next_start = ~0UL; vma->is_near_this = simple_is_near_this; return 0; } #endif return -1; } smalltalk-3.2.5/sigsegv/src/leave.c0000644000175000017500000000153512130343734014130 00000000000000/* Leaving a signal handler executing on the alternate stack. Copyright (C) 2002 Bruno Haible This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. */ #include "config.h" #include CFG_LEAVE smalltalk-3.2.5/sigsegv/src/fault-beos.h0000644000175000017500000000163112130343734015077 00000000000000/* Fault handler information. BeOS version. Copyright (C) 2002 Bruno Haible This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. */ #define SIGSEGV_FAULT_HANDLER_ARGLIST int sig, void *userdata, struct vregs *vrp #define SIGSEGV_FAULT_CONTEXT vrp smalltalk-3.2.5/sigsegv/src/version.c0000644000175000017500000000151512130343734014517 00000000000000/* Version number. Copyright (C) 2005 Bruno Haible This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. */ #include "sigsegv.h" int libsigsegv_version = LIBSIGSEGV_VERSION; smalltalk-3.2.5/sigsegv/src/fault-hpux-hppa.h0000644000175000017500000000331612130343734016063 00000000000000/* Fault handler information. HP-UX HPPA version. Copyright (C) 2002 Paolo Bonzini Copyright (C) 2002-2003 Bruno Haible This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. */ #define USE_64BIT_REGS(mc) \ (((mc).ss_flags & SS_WIDEREGS) && ((mc).ss_flags & SS_NARROWISINVALID)) /* Extract the cr21 register from an mcontext_t. See the comments in /usr/include/machine/save_state.h. */ #define GET_CR21(mc) \ (USE_64BIT_REGS(mc) ? (mc).ss_wide.ss_64.ss_cr21 : (mc).ss_narrow.ss_cr21) /* Extract the stack pointer from an mcontext_t. See the comments in /usr/include/machine/save_state.h. */ #define GET_SP(mc) \ (USE_64BIT_REGS(mc) ? (mc).ss_wide.ss_64.ss_sp : (mc).ss_narrow.ss_sp) /* Both of these alternatives work on HP-UX 10.20 and HP-UX 11.00. */ #if 1 #include "fault-hpux.h" #define SIGSEGV_FAULT_ADDRESS GET_CR21 (scp->sc_sl.sl_ss) #define SIGSEGV_FAULT_STACKPOINTER GET_SP (scp->sc_ctxt.sl.sl_ss) #else #include "fault-posix.h" #define SIGSEGV_FAULT_STACKPOINTER GET_SP (((ucontext_t *) ucp)->uc_mcontext) #endif smalltalk-3.2.5/sigsegv/src/fault-solaris-sparc.h0000644000175000017500000000163512130343734016735 00000000000000/* Fault handler information. Solaris/SPARC version. Copyright (C) 2002 Bruno Haible This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. */ #include "fault-solaris.h" #define SIGSEGV_FAULT_STACKPOINTER ((ucontext_t *) ucp)->uc_mcontext.gregs[REG_O6] smalltalk-3.2.5/sigsegv/src/dispatcher.c0000644000175000017500000001653012130343734015163 00000000000000/* Dispatch signal to right virtual memory area. Copyright (C) 1993-1999, 2002-2003 Bruno Haible This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. */ #include "sigsegv.h" #include /* needed for NULL on SunOS4 */ #include #ifdef _WIN32 #include #endif /* * A dispatcher contains an AVL tree of non-empty intervals, sorted according * to their starting address. */ typedef struct node_t { /* AVL tree management. */ struct node_t *left; struct node_t *right; unsigned int height; /* Representation of interval. */ unsigned long address; unsigned long len; /* User handler. */ sigsegv_area_handler_t handler; void *handler_arg; } node_t; #define empty ((node_t *) 0) #define heightof(tree) ((tree) == empty ? 0 : (tree)->height) #define MAXHEIGHT 41 static void rebalance (node_t ***nodeplaces_ptr, unsigned int count) { if (count > 0) do { node_t **nodeplace = *--nodeplaces_ptr; node_t *node = *nodeplace; node_t *nodeleft = node->left; node_t *noderight = node->right; unsigned int heightleft = heightof (nodeleft); unsigned int heightright = heightof (noderight); if (heightright + 1 < heightleft) { node_t *nodeleftleft = nodeleft->left; node_t *nodeleftright = nodeleft->right; unsigned int heightleftright = heightof (nodeleftright); if (heightof (nodeleftleft) >= heightleftright) { node->left = nodeleftright; nodeleft->right = node; nodeleft->height = 1 + (node->height = 1 + heightleftright); *nodeplace = nodeleft; } else { nodeleft->right = nodeleftright->left; node->left = nodeleftright->right; nodeleftright->left = nodeleft; nodeleftright->right = node; nodeleft->height = node->height = heightleftright; nodeleftright->height = heightleft; *nodeplace = nodeleftright; } } else if (heightleft + 1 < heightright) { node_t *noderightright = noderight->right; node_t *noderightleft = noderight->left; unsigned int heightrightleft = heightof (noderightleft); if (heightof (noderightright) >= heightrightleft) { node->right = noderightleft; noderight->left = node; noderight->height = 1 + (node->height = 1 + heightrightleft); *nodeplace = noderight; } else { noderight->left = noderightleft->right; node->right = noderightleft->left; noderightleft->right = noderight; noderightleft->left = node; noderight->height = node->height = heightrightleft; noderightleft->height = heightright; *nodeplace = noderightleft; } } else { unsigned int height = (heightleftheight) break; node->height = height; } } while (--count > 0); } static node_t * insert (node_t *new_node, node_t *tree) { unsigned long key = new_node->address; node_t **nodeplace = &tree; node_t **stack[MAXHEIGHT]; unsigned int stack_count = 0; node_t ***stack_ptr = &stack[0]; for (;;) { node_t *node = *nodeplace; if (node == empty) break; *stack_ptr++ = nodeplace; stack_count++; if (key < node->address) nodeplace = &node->left; else nodeplace = &node->right; } new_node->left = empty; new_node->right = empty; new_node->height = 1; *nodeplace = new_node; rebalance (stack_ptr, stack_count); return tree; } static node_t * delete (node_t *node_to_delete, node_t *tree) { unsigned long key = node_to_delete->address; node_t **nodeplace = &tree; node_t **stack[MAXHEIGHT]; unsigned int stack_count = 0; node_t ***stack_ptr = &stack[0]; for (;;) { node_t *node = *nodeplace; if (node == empty) return tree; *stack_ptr++ = nodeplace; stack_count++; if (key == node->address) { if (node != node_to_delete) abort (); break; } if (key < node->address) nodeplace = &node->left; else nodeplace = &node->right; } { node_t **nodeplace_to_delete = nodeplace; if (node_to_delete->left == empty) { *nodeplace_to_delete = node_to_delete->right; stack_ptr--; stack_count--; } else { node_t ***stack_ptr_to_delete = stack_ptr; node_t **nodeplace = &node_to_delete->left; node_t *node; for (;;) { node = *nodeplace; if (node->right == empty) break; *stack_ptr++ = nodeplace; stack_count++; nodeplace = &node->right; } *nodeplace = node->left; node->left = node_to_delete->left; node->right = node_to_delete->right; node->height = node_to_delete->height; *nodeplace_to_delete = node; *stack_ptr_to_delete = &node->left; } } rebalance (stack_ptr, stack_count); return tree; } void sigsegv_init (sigsegv_dispatcher *dispatcher) { dispatcher->tree = empty; } void * sigsegv_register (sigsegv_dispatcher *dispatcher, void *address, unsigned long len, sigsegv_area_handler_t handler, void *handler_arg) { if (len == 0) return NULL; else { node_t *new_node = (node_t *) malloc (sizeof (node_t)); new_node->address = (unsigned long) address; new_node->len = len; new_node->handler = handler; new_node->handler_arg = handler_arg; dispatcher->tree = insert (new_node, (node_t *) dispatcher->tree); return new_node; } } void sigsegv_unregister (sigsegv_dispatcher *dispatcher, void *ticket) { if (ticket != NULL) { node_t *node_to_delete = (node_t *) ticket; dispatcher->tree = delete (node_to_delete, (node_t *) dispatcher->tree); free (node_to_delete); } } int sigsegv_dispatch (sigsegv_dispatcher *dispatcher, void *fault_address) { unsigned long key = (unsigned long) fault_address; node_t *tree = (node_t *) dispatcher->tree; for (;;) { if (tree == empty) return 0; if (key < tree->address) tree = tree->left; else if (key - tree->address >= tree->len) tree = tree->right; else break; } return (*tree->handler) (fault_address, tree->handler_arg); } smalltalk-3.2.5/sigsegv/src/machfault-macos-powerpc.h0000644000175000017500000000336512130343734017565 00000000000000/* Fault handler information. MacOSX/PowerPC version. Copyright (C) 2003-2004, 2007, 2008 Bruno Haible This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. */ #define SIGSEGV_THREAD_STATE_TYPE ppc_thread_state_t #define SIGSEGV_THREAD_STATE_FLAVOR PPC_THREAD_STATE #define SIGSEGV_THREAD_STATE_COUNT PPC_THREAD_STATE_COUNT #if __DARWIN_UNIX03 #define SIGSEGV_STACK_POINTER(thr_state) (thr_state).__r1 #define SIGSEGV_PROGRAM_COUNTER(thr_state) (thr_state).__srr0 #else #define SIGSEGV_STACK_POINTER(thr_state) (thr_state).r1 #define SIGSEGV_PROGRAM_COUNTER(thr_state) (thr_state).srr0 #endif #ifdef _LP64 # define SIGSEGV_EXC_STATE_TYPE ppc_exception_state_t # define SIGSEGV_EXC_STATE_FLAVOR PPC_EXCEPTION_STATE # define SIGSEGV_EXC_STATE_COUNT PPC_EXCEPTION_STATE_COUNT # if __DARWIN_UNIX03 # define SIGSEGV_FAULT_ADDRESS(thr_state,exc_state) (exc_state).__dar # else # define SIGSEGV_FAULT_ADDRESS(thr_state,exc_state) (exc_state).dar # endif #endif smalltalk-3.2.5/sigsegv/src/fault-hpux.h0000644000175000017500000000163212130343734015134 00000000000000/* Fault handler information. HP-UX version. Copyright (C) 2002 Paolo Bonzini This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. */ #define SIGSEGV_FAULT_HANDLER_ARGLIST int sig, int code, struct sigcontext *scp #define SIGSEGV_FAULT_CONTEXT scp smalltalk-3.2.5/sigsegv/src/fault-linux.h0000644000175000017500000000206512130343734015310 00000000000000/* Fault handler information. Linux stub version. Copyright (C) 2002 Bruno Haible This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. */ /* For SIGSEGV_FAULT_HANDLER_ARGLIST, see the definition of SIGCONTEXT in glibc/sysdeps/unix/sysv/linux//sigcontextinfo.h. */ /* For SIGSEGV_FAULT_STACKPOINTER, see the definition of GET_STACK in glibc/sysdeps/unix/sysv/linux//sigcontextinfo.h. */ smalltalk-3.2.5/sigsegv/src/fault-beos-i386.h0000644000175000017500000000160012130343734015562 00000000000000/* Fault handler information. BeOS/i386 version. Copyright (C) 2002 Bruno Haible This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. */ #include #include "fault-beos.h" #define SIGSEGV_FAULT_STACKPOINTER vrp->esp smalltalk-3.2.5/sigsegv/src/Makefile.am0000644000175000017500000000662212130343734014726 00000000000000## Makefile for libsigsegv/src. ## Copyright (C) 2002-2006 Bruno Haible ## ## This program is free software; you can redistribute it and/or modify ## it under the terms of the GNU General Public License as published by ## the Free Software Foundation; either version 2, or (at your option) ## any later version. ## ## This program is distributed in the hope that it will be useful, ## but WITHOUT ANY WARRANTY; without even the implied warranty of ## MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the ## GNU General Public License for more details. ## ## You should have received a copy of the GNU General Public License ## along with this program; if not, write to the Free Software ## Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, ## USA. ## Process this file with automake to produce Makefile.in. AUTOMAKE_OPTIONS = 1.5 gnits no-dependencies RM = rm -f noinst_LTLIBRARIES = libsigsegv_convenience.la noinst_HEADERS = \ fault.h fault-aix3.h fault-aix3-powerpc.h fault-aix5.h fault-aix5-powerpc.h \ fault-beos.h fault-beos-i386.h \ fault-bsd.h fault-freebsd-i386.h \ fault-hpux.h fault-hpux-hppa.h fault-hurd.h fault-irix.h fault-irix-mips.h \ fault-linux.h fault-linux-alpha.h fault-linux-arm.h fault-linux-cris.h \ fault-linux-hppa.h fault-linux-i386.h fault-linux-i386-old.h \ fault-linux-ia64.h fault-linux-m68k.h fault-linux-m68k.c fault-linux-mips.h \ fault-linux-powerpc.h fault-linux-s390.h fault-linux-sh.h \ fault-linux-sparc.h fault-linux-x86_64.h \ fault-macos-i386.h \ fault-macosdarwin5-powerpc.h fault-macosdarwin5-powerpc.c \ fault-macosdarwin7-powerpc.h fault-macosdarwin7-powerpc.c \ fault-netbsd.h fault-netbsd-alpha.h fault-netbsd-alpha.c \ fault-none.h \ fault-openbsd.h fault-openbsd-i386.h \ fault-osf.h fault-osf-alpha.h \ fault-posix.h fault-solaris.h fault-solaris-i386.h fault-solaris-sparc.h \ machfault.h machfault-macos-i386.h machfault-macos-powerpc.h \ signals.h signals-bsd.h signals-hpux.h signals-hurd.h signals-macos.h \ leave.h \ stackvma.h EXTRA_DIST = \ handler-none.c handler-unix.c handler-macos.c handler-win32.c \ stackvma-none.c stackvma-simple.c stackvma-linux.c stackvma-freebsd.c \ stackvma-procfs.c stackvma-beos.c stackvma-mach.c stackvma-mincore.c \ leave-none.c leave-nop.c leave-sigaltstack.c leave-setcontext.c \ sigsegv.h.msvc AM_CPPFLAGS = -I. -I$(srcdir) DEFS = @DEFS@ libsigsegv_convenience_la_SOURCES = handler.c stackvma.c leave.c dispatcher.c version.c libsigsegv_convenience_la_LDFLAGS = -lc -no-undefined # Dependencies. handler.$(OBJEXT) : ../config.h sigsegv.h @CFG_HANDLER@ $(noinst_HEADERS) stackvma.$(OBJEXT) : ../config.h @CFG_STACKVMA@ stackvma.h leave.$(OBJEXT) : ../config.h @CFG_LEAVE@ dispatcher.$(OBJEXT) : sigsegv.h # Special rules for installing sigsegv.h. install-data-local: $(mkinstalldirs) $(DESTDIR)$(includedir) $(INSTALL_DATA) sigsegv.h $(DESTDIR)$(includedir)/sigsegv.h installdirs-local: $(mkinstalldirs) $(DESTDIR)$(includedir) uninstall-local: $(RM) $(DESTDIR)$(includedir)/sigsegv.h DISTCLEANFILES = sigsegv.h # Rules for "make dist". sigsegv.h.msvc : sigsegv.h.in sed -e 's/@''FAULT_CONTEXT_INCLUDE''@/#include /' \ -e 's/@''FAULT_CONTEXT_INCLUDE2''@//' \ -e 's/@''FAULT_CONTEXT''@/CONTEXT/' \ -e 's/@''HAVE_SIGSEGV_RECOVERY''@/1/' \ -e 's/@''HAVE_STACK_OVERFLOW_RECOVERY''@/1/' \ < $(srcdir)/sigsegv.h.in > $@ smalltalk-3.2.5/sigsegv/src/machfault-macos-i386.h0000644000175000017500000000341412130343734016572 00000000000000/* Fault handler information. MacOSX/i386 version. Copyright (C) 2003-2004, 2006, 2007, 2008 Bruno Haible This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. */ #define SIGSEGV_THREAD_STATE_TYPE i386_thread_state_t #define SIGSEGV_THREAD_STATE_FLAVOR i386_THREAD_STATE #define SIGSEGV_THREAD_STATE_COUNT i386_THREAD_STATE_COUNT #if __DARWIN_UNIX03 #define SIGSEGV_STACK_POINTER(thr_state) (thr_state).__esp #define SIGSEGV_PROGRAM_COUNTER(thr_state) (thr_state).__eip #else #define SIGSEGV_STACK_POINTER(thr_state) (thr_state).esp #define SIGSEGV_PROGRAM_COUNTER(thr_state) (thr_state).eip #endif #ifdef _LP64 # define SIGSEGV_EXC_STATE_TYPE i386_exception_state_t # define SIGSEGV_EXC_STATE_FLAVOR i386_EXCEPTION_STATE # define SIGSEGV_EXC_STATE_COUNT i386_EXCEPTION_STATE_COUNT # if __DARWIN_UNIX03 # define SIGSEGV_FAULT_ADDRESS(thr_state,exc_state) (exc_state).__faultvaddr # else # define SIGSEGV_FAULT_ADDRESS(thr_state,exc_state) (exc_state).faultvaddr # endif #endif smalltalk-3.2.5/sigsegv/src/fault-aix5-powerpc.h0000644000175000017500000000163612130343734016477 00000000000000/* Fault handler information. AIX5/PowerPC version. Copyright (C) 2005 Bruno Haible This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. */ #include "fault-aix5.h" #define SIGSEGV_FAULT_STACKPOINTER ((ucontext_t *) ucp)->uc_mcontext.jmp_context.gpr[1] smalltalk-3.2.5/sigsegv/src/fault-solaris.h0000644000175000017500000000150012130343734015616 00000000000000/* Fault handler information. Solaris version. Copyright (C) 2002 Bruno Haible This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. */ #include "fault-posix.h" smalltalk-3.2.5/sigsegv/src/fault-linux-sparc.h0000644000175000017500000000217312130343734016416 00000000000000/* Fault handler information. Linux/SPARC version. Copyright (C) 2002 Bruno Haible This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. */ #include #define SIGSEGV_FAULT_HANDLER_ARGLIST int sig, int code, struct sigcontext *scp, void *addr /* FIXME */ #define SIGSEGV_FAULT_ADDRESS addr /* in case of SunOS4 signal frames */ #define SIGSEGV_FAULT_CONTEXT scp #define SIGSEGV_FAULT_STACKPOINTER scp->sigc_sp /* FIXME: not scp->si_regs.u_regs[14] ? */ smalltalk-3.2.5/sigsegv/src/stackvma-freebsd.c0000644000175000017500000000546612130343734016264 00000000000000/* Determine the virtual memory area of a given address. FreeBSD version. Copyright (C) 2002-2003, 2006 Bruno Haible This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. */ #include "stackvma.h" #include #include "stackvma-simple.c" #if HAVE_MINCORE # define sigsegv_get_vma mincore_get_vma # define STATIC static # include "stackvma-mincore.c" # undef sigsegv_get_vma #endif int sigsegv_get_vma (unsigned long address, struct vma_struct *vma) { FILE *fp; int c; /* The stack appears as multiple adjacents segments, therefore we merge adjacent segments. */ unsigned long next_start, next_end, curr_start, curr_end; #if STACK_DIRECTION < 0 unsigned long prev_end; #endif /* Open the current process' maps file. It describes one VMA per line. */ fp = fopen ("/proc/curproc/map", "r"); if (!fp) goto failed; #if STACK_DIRECTION < 0 prev_end = 0; #endif for (curr_start = curr_end = 0; ;) { if (fscanf (fp, "0x%lx 0x%lx", &next_start, &next_end) != 2) break; while (c = getc (fp), c != EOF && c != '\n') continue; if (next_start == curr_end) { /* Merge adjacent segments. */ curr_end = next_end; } else { if (curr_start < curr_end && address >= curr_start && address <= curr_end-1) goto found; #if STACK_DIRECTION < 0 prev_end = curr_end; #endif curr_start = next_start; curr_end = next_end; } } if (address >= curr_start && address <= curr_end-1) found: { vma->start = curr_start; vma->end = curr_end; #if STACK_DIRECTION < 0 vma->prev_end = prev_end; #else if (fscanf (fp, "0x%lx 0x%lx", &vma->next_start, &next_end) != 2) vma->next_start = 0; #endif fclose (fp); vma->is_near_this = simple_is_near_this; return 0; } fclose (fp); failed: #if HAVE_MINCORE /* FreeBSD 6.[01] doesn't allow to distinguish unmapped pages from mapped but swapped-out pages. See whether it's fixed. */ if (!is_mapped (0)) /* OK, mincore() appears to work as expected. */ return mincore_get_vma (address, vma); #endif return -1; } smalltalk-3.2.5/sigsegv/src/fault-aix3.h0000644000175000017500000000174512130343734015021 00000000000000/* Fault handler information. AIX 3 and AIX 4 version. Copyright (C) 2002 Bruno Haible This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. */ #define SIGSEGV_FAULT_HANDLER_ARGLIST int sig, int code, struct sigcontext *scp #define SIGSEGV_FAULT_ADDRESS scp->sc_jmpbuf.jmp_context.o_vaddr #define SIGSEGV_FAULT_CONTEXT scp smalltalk-3.2.5/sigsegv/src/sigsegv.h.msvc0000644000175000017500000001361012130343734015454 00000000000000/* Page fault handling library. Copyright (C) 1998-1999, 2002, 2004-2007 Bruno Haible This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. */ #ifndef _SIGSEGV_H #define _SIGSEGV_H #include /* HAVE_SIGSEGV_RECOVERY is defined if the system supports catching SIGSEGV. */ #if 1 # define HAVE_SIGSEGV_RECOVERY 1 #endif /* HAVE_STACK_OVERFLOW_RECOVERY is defined if stack overflow can be caught. */ #if 1 # define HAVE_STACK_OVERFLOW_RECOVERY 1 #endif #ifdef __cplusplus extern "C" { #endif #define LIBSIGSEGV_VERSION 0x0205 /* version number: (major<<8) + minor */ extern int libsigsegv_version; /* Likewise */ /* -------------------------------------------------------------------------- */ /* * The type of a global SIGSEGV handler. * The fault address is passed as argument. * The access type (read access or write access) is not passed; your handler * has to know itself how to distinguish these two cases. * The second argument is 0, meaning it could also be a stack overflow, or 1, * meaning the handler should seriously try to fix the fault. * The return value should be nonzero if the handler has done its job * and no other handler should be called, or 0 if the handler declines * responsibility for the given address. */ typedef int (*sigsegv_handler_t) (void* fault_address, int serious); /* * Installs a global SIGSEGV handler. * This should be called once only, and it ignores any previously installed * SIGSEGV handler. * Returns 0 on success, or -1 if the system doesn't support catching SIGSEGV. */ extern int sigsegv_install_handler (sigsegv_handler_t handler); /* * Deinstalls the global SIGSEGV handler. * This goes back to the state where no SIGSEGV handler is installed. */ extern void sigsegv_deinstall_handler (void); /* * Prepares leaving a SIGSEGV handler (through longjmp or similar means). */ extern void sigsegv_leave_handler (void); /* * The type of a context passed to a stack overflow handler. * This type is system dependent; on some platforms it is an 'ucontext_t *', * on some platforms it is a 'struct sigcontext *', on others merely an * opaque 'void *'. */ typedef CONTEXT *stackoverflow_context_t; /* * The type of a stack overflow handler. * Such a handler should perform a longjmp call in order to reduce the amount * of stack needed. It must not return. * The emergency argument is 0 when the stack could be repared, or 1 if the * application should better save its state and exit now. */ typedef void (*stackoverflow_handler_t) (int emergency, stackoverflow_context_t scp); /* * Installs a stack overflow handler. * The extra_stack argument is a pointer to a pre-allocated area used as a * stack for executing the handler. It is typically allocated by use of * `alloca' during `main'. Its size should be sufficiently large. * The following code determines an appropriate size: * #include * #ifndef SIGSTKSZ / * glibc defines SIGSTKSZ for this purpose * / * # define SIGSTKSZ 16384 / * on most platforms, 16 KB are sufficient * / * #endif * Returns 0 on success, or -1 if the system doesn't support catching stack * overflow. */ extern int stackoverflow_install_handler (stackoverflow_handler_t handler, void* extra_stack, unsigned long extra_stack_size); /* * Deinstalls the stack overflow handler. */ extern void stackoverflow_deinstall_handler (void); /* -------------------------------------------------------------------------- */ /* * The following structure and functions permit to define different SIGSEGV * policies on different address ranges. */ /* * The type of a local SIGSEGV handler. * The fault address is passed as argument. * The second argument is fixed arbitrary user data. * The return value should be nonzero if the handler has done its job * and no other handler should be called, or 0 if the handler declines * responsibility for the given address. */ typedef int (*sigsegv_area_handler_t) (void* fault_address, void* user_arg); /* * This structure represents a table of memory areas (address range intervals), * with an local SIGSEGV handler for each. */ typedef struct sigsegv_dispatcher { void* tree; } sigsegv_dispatcher; /* * Initializes a sigsegv_dispatcher structure. */ extern void sigsegv_init (sigsegv_dispatcher* dispatcher); /* * Adds a local SIGSEGV handler to a sigsegv_dispatcher structure. * It will cover the interval [address..address+len-1]. * Returns a "ticket" that can be used to remove the handler later. */ extern void* sigsegv_register (sigsegv_dispatcher* dispatcher, void* address, unsigned long len, sigsegv_area_handler_t handler, void* handler_arg); /* * Removes a local SIGSEGV handler. */ extern void sigsegv_unregister (sigsegv_dispatcher* dispatcher, void* ticket); /* * Call the local SIGSEGV handler responsible for the given fault address. * Return the handler's return value. 0 means that no handler has been found, * or that a handler was found but declined responsibility. */ extern int sigsegv_dispatch (sigsegv_dispatcher* dispatcher, void* fault_address); /* -------------------------------------------------------------------------- */ #ifdef __cplusplus } #endif #endif /* _SIGSEGV_H */ smalltalk-3.2.5/sigsegv/src/fault-irix-mips.h0000644000175000017500000000156712130343734016100 00000000000000/* Fault handler information. IRIX MIPS version. Copyright (C) 2002 Bruno Haible This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. */ #include "fault-irix.h" #define SIGSEGV_FAULT_STACKPOINTER scp->sc_regs[29] smalltalk-3.2.5/sigsegv/src/stackvma-mincore.c0000644000175000017500000002061012130343734016272 00000000000000/* Determine the virtual memory area of a given address. Copyright (C) 2006 Bruno Haible This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. */ /* mincore() is a system call that allows to inquire the status of a range of pages of virtual memory. In particular, it allows to inquire whether a page is mapped at all. As of 2006, mincore() is supported by: possible bits: - Linux, since Linux 2.4 and glibc 2.2, 1 - Solaris, since Solaris 9, 1 - MacOS X, since MacOS X 10.3 (at least), 1 - FreeBSD, since FreeBSD 6.0, MINCORE_{INCORE,REFERENCED,MODIFIED} - NetBSD, since NetBSD 3.0 (at least), 1 - OpenBSD, since OpenBSD 2.6 (at least), 1 However, while the API allows to easily determine the bounds of mapped virtual memory, it does not make it easy the bounds of _unmapped_ virtual memory ranges. We try to work around this, but it may still be slow. */ #include "stackvma.h" #include #ifdef HAVE_UNISTD_H # include #endif #include #include /* Cache for getpagesize(). */ static unsigned long pagesize; /* Initialize pagesize. */ static void init_pagesize (void) { #if HAVE_GETPAGESIZE pagesize = getpagesize (); #elif HAVE_SYSCONF_PAGESIZE pagesize = sysconf (_SC_PAGESIZE); #else pagesize = PAGESIZE; #endif } /* Test whether the page starting at ADDR is among the address range. ADDR must be a multiple of pagesize. */ static int is_mapped (unsigned long addr) { char vec[1]; return mincore ((void *) addr, pagesize, vec) >= 0; } /* Assuming that the page starting at ADDR is among the address range, return the start of its virtual memory range. ADDR must be a multiple of pagesize. */ static unsigned long mapped_range_start (unsigned long addr) { /* Use a moderately sized VEC here, small enough that it fits on the stack (without requiring malloc). */ char vec[2048]; unsigned long stepsize = sizeof (vec); for (;;) { unsigned long max_remaining; if (addr == 0) return addr; max_remaining = addr / pagesize; if (stepsize > max_remaining) stepsize = max_remaining; if (mincore ((void *) (addr - stepsize * pagesize), stepsize * pagesize, vec) < 0) /* Time to search in smaller steps. */ break; /* The entire range exists. Continue searching in large steps. */ addr -= stepsize * pagesize; } for (;;) { unsigned long halfstepsize1; unsigned long halfstepsize2; if (stepsize == 1) return addr; /* Here we know that less than stepsize pages exist starting at addr. */ halfstepsize1 = (stepsize + 1) / 2; halfstepsize2 = stepsize / 2; /* halfstepsize1 + halfstepsize2 = stepsize. */ if (mincore ((void *) (addr - halfstepsize1 * pagesize), halfstepsize1 * pagesize, vec) < 0) stepsize = halfstepsize1; else { addr -= halfstepsize1 * pagesize; stepsize = halfstepsize2; } } } /* Assuming that the page starting at ADDR is among the address range, return the end of its virtual memory range + 1. ADDR must be a multiple of pagesize. */ static unsigned long mapped_range_end (unsigned long addr) { /* Use a moderately sized VEC here, small enough that it fits on the stack (without requiring malloc). */ char vec[2048]; unsigned long stepsize = sizeof (vec); addr += pagesize; for (;;) { unsigned long max_remaining; if (addr == 0) /* wrapped around? */ return addr; max_remaining = (- addr) / pagesize; if (stepsize > max_remaining) stepsize = max_remaining; if (mincore ((void *) addr, stepsize * pagesize, vec) < 0) /* Time to search in smaller steps. */ break; /* The entire range exists. Continue searching in large steps. */ addr += stepsize * pagesize; } for (;;) { unsigned long halfstepsize1; unsigned long halfstepsize2; if (stepsize == 1) return addr; /* Here we know that less than stepsize pages exist starting at addr. */ halfstepsize1 = (stepsize + 1) / 2; halfstepsize2 = stepsize / 2; /* halfstepsize1 + halfstepsize2 = stepsize. */ if (mincore ((void *) addr, halfstepsize1 * pagesize, vec) < 0) stepsize = halfstepsize1; else { addr += halfstepsize1 * pagesize; stepsize = halfstepsize2; } } } /* Determine whether an address range [ADDR1..ADDR2] is completely unmapped. ADDR1 must be <= ADDR2. */ static int is_unmapped (unsigned long addr1, unsigned long addr2) { unsigned long count; unsigned long stepsize; /* Round addr1 down. */ addr1 = (addr1 / pagesize) * pagesize; /* Round addr2 up and turn it into an exclusive bound. */ addr2 = ((addr2 / pagesize) + 1) * pagesize; /* This is slow: mincore() does not provide a way to determine the bounds of the gaps directly. So we have to use mincore() on individual pages over and over again. Only after we've verified that all pages are unmapped, we know that the range is completely unmapped. If we were to traverse the pages from bottom to top or from top to bottom, it would be slow even in the average case. To speed up the search, we exploit the fact that mapped memory ranges are larger than one page on average, therefore we have good chances of hitting a mapped area if we traverse only every second, or only fourth page, etc. This doesn't decrease the worst-case runtime, only the average runtime. */ count = (addr2 - addr1) / pagesize; /* We have to test is_mapped (addr1 + i * pagesize) for 0 <= i < count. */ for (stepsize = 1; stepsize < count; ) stepsize = 2 * stepsize; for (;;) { unsigned long addr_stepsize; unsigned long i; unsigned long addr; stepsize = stepsize / 2; if (stepsize == 0) break; addr_stepsize = stepsize * pagesize; for (i = stepsize, addr = addr1 + addr_stepsize; i < count; i += 2 * stepsize, addr += 2 * addr_stepsize) /* Here addr = addr1 + i * pagesize. */ if (is_mapped (addr)) return 0; } return 1; } #if STACK_DIRECTION < 0 /* Info about the gap between this VMA and the previous one. addr must be < vma->start. */ static int mincore_is_near_this (unsigned long addr, struct vma_struct *vma) { /* vma->start - addr <= (vma->start - vma->prev_end) / 2 is mathematically equivalent to vma->prev_end <= 2 * addr - vma->start <==> is_unmapped (2 * addr - vma->start, vma->start - 1). But be careful about overflow. */ unsigned long testaddr = addr - (vma->start - addr); if (testaddr > addr) /* overflow? */ testaddr = 0; return is_unmapped (testaddr, addr); } #endif #if STACK_DIRECTION > 0 /* Info about the gap between this VMA and the next one. addr must be > vma->end - 1. */ static int mincore_is_near_this (unsigned long addr, struct vma_struct *vma) { /* addr - vma->end < (vma->next_start - vma->end) / 2 is mathematically equivalent to vma->next_start > 2 * addr - vma->end <==> is_unmapped (vma->end, 2 * addr - vma->end). But be careful about overflow. */ unsigned long testaddr = addr + (addr - vma->end); if (testaddr < addr) /* overflow? */ testaddr = ~0UL; return is_unmapped (addr, testaddr); } #endif #ifdef STATIC STATIC #endif int sigsegv_get_vma (unsigned long address, struct vma_struct *vma) { if (pagesize == 0) init_pagesize (); address = (address / pagesize) * pagesize; vma->start = mapped_range_start (address); vma->end = mapped_range_end (address); vma->is_near_this = mincore_is_near_this; return 0; } smalltalk-3.2.5/sigsegv/src/stackvma-simple.c0000644000175000017500000000275312130343734016137 00000000000000/* Determine the virtual memory area of a given address. Copyright (C) 2006 Bruno Haible This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. */ /* This file contains the proximity test function for the simple cases, where the OS has an API for enumerating the mapped ranges of virual memory. */ #if STACK_DIRECTION < 0 /* Info about the gap between this VMA and the previous one. addr must be < vma->start. */ static int simple_is_near_this (unsigned long addr, struct vma_struct *vma) { return (vma->start - addr <= (vma->start - vma->prev_end) / 2); } #endif #if STACK_DIRECTION > 0 /* Info about the gap between this VMA and the next one. addr must be > vma->end - 1. */ static int simple_is_near_this (unsigned long addr, struct vma_struct *vma) { return (addr - vma->end < (vma->next_start - vma->end) / 2); } #endif smalltalk-3.2.5/sigsegv/src/stackvma.c0000644000175000017500000000153312130343734014643 00000000000000/* Determine the virtual memory area of a given address. Copyright (C) 2002 Bruno Haible This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. */ #include "config.h" #include CFG_STACKVMA smalltalk-3.2.5/sigsegv/src/Makefile.in0000644000175000017500000004260112130455553014737 00000000000000# Makefile.in generated by automake 1.11.6 from Makefile.am. # @configure_input@ # Copyright (C) 1994, 1995, 1996, 1997, 1998, 1999, 2000, 2001, 2002, # 2003, 2004, 2005, 2006, 2007, 2008, 2009, 2010, 2011 Free Software # Foundation, Inc. # This Makefile.in is free software; the Free Software Foundation # gives unlimited permission to copy and/or distribute it, # with or without modifications, as long as this notice is preserved. # This program is distributed in the hope that it will be useful, # but WITHOUT ANY WARRANTY, to the extent permitted by law; without # even the implied warranty of MERCHANTABILITY or FITNESS FOR A # PARTICULAR PURPOSE. @SET_MAKE@ VPATH = @srcdir@ am__make_dryrun = \ { \ am__dry=no; \ case $$MAKEFLAGS in \ *\\[\ \ ]*) \ echo 'am--echo: ; @echo "AM" OK' | $(MAKE) -f - 2>/dev/null \ | grep '^AM OK$$' >/dev/null || am__dry=yes;; \ *) \ for am__flg in $$MAKEFLAGS; do \ case $$am__flg in \ *=*|--*) ;; \ *n*) am__dry=yes; break;; \ esac; \ done;; \ esac; \ test $$am__dry = yes; \ } pkgdatadir = $(datadir)/@PACKAGE@ pkgincludedir = $(includedir)/@PACKAGE@ pkglibdir = $(libdir)/@PACKAGE@ pkglibexecdir = $(libexecdir)/@PACKAGE@ am__cd = CDPATH="$${ZSH_VERSION+.}$(PATH_SEPARATOR)" && cd install_sh_DATA = $(install_sh) -c -m 644 install_sh_PROGRAM = $(install_sh) -c install_sh_SCRIPT = $(install_sh) -c INSTALL_HEADER = $(INSTALL_DATA) transform = $(program_transform_name) NORMAL_INSTALL = : PRE_INSTALL = : POST_INSTALL = : NORMAL_UNINSTALL = : PRE_UNINSTALL = : POST_UNINSTALL = : build_triplet = @build@ host_triplet = @host@ subdir = src DIST_COMMON = $(noinst_HEADERS) $(srcdir)/Makefile.am \ $(srcdir)/Makefile.in $(srcdir)/sigsegv.h.in ACLOCAL_M4 = $(top_srcdir)/aclocal.m4 am__aclocal_m4_deps = $(top_srcdir)/../build-aux/bold.m4 \ $(top_srcdir)/../build-aux/fault.m4 \ $(top_srcdir)/../build-aux/getpagesize.m4 \ $(top_srcdir)/../build-aux/libtool.m4 \ $(top_srcdir)/../build-aux/ltoptions.m4 \ $(top_srcdir)/../build-aux/ltsugar.m4 \ $(top_srcdir)/../build-aux/ltversion.m4 \ $(top_srcdir)/../build-aux/lt~obsolete.m4 \ $(top_srcdir)/../build-aux/mmap-anon.m4 \ $(top_srcdir)/../build-aux/relocatable.m4 \ $(top_srcdir)/../build-aux/sigaltstack-longjmp.m4 \ $(top_srcdir)/../build-aux/sigaltstack-siglongjmp.m4 \ $(top_srcdir)/../build-aux/sigaltstack.m4 \ $(top_srcdir)/configure.ac am__configure_deps = $(am__aclocal_m4_deps) $(CONFIGURE_DEPENDENCIES) \ $(ACLOCAL_M4) mkinstalldirs = $(install_sh) -d CONFIG_HEADER = $(top_builddir)/config.h CONFIG_CLEAN_FILES = sigsegv.h CONFIG_CLEAN_VPATH_FILES = LTLIBRARIES = $(noinst_LTLIBRARIES) libsigsegv_convenience_la_LIBADD = am_libsigsegv_convenience_la_OBJECTS = handler.lo stackvma.lo leave.lo \ dispatcher.lo version.lo libsigsegv_convenience_la_OBJECTS = \ $(am_libsigsegv_convenience_la_OBJECTS) libsigsegv_convenience_la_LINK = $(LIBTOOL) --tag=CC \ $(AM_LIBTOOLFLAGS) $(LIBTOOLFLAGS) --mode=link $(CCLD) \ $(AM_CFLAGS) $(CFLAGS) $(libsigsegv_convenience_la_LDFLAGS) \ $(LDFLAGS) -o $@ DEFAULT_INCLUDES = -I.@am__isrc@ -I$(top_builddir) depcomp = am__depfiles_maybe = COMPILE = $(CC) $(DEFS) $(DEFAULT_INCLUDES) $(INCLUDES) $(AM_CPPFLAGS) \ $(CPPFLAGS) $(AM_CFLAGS) $(CFLAGS) LTCOMPILE = $(LIBTOOL) --tag=CC $(AM_LIBTOOLFLAGS) $(LIBTOOLFLAGS) \ --mode=compile $(CC) $(DEFS) $(DEFAULT_INCLUDES) $(INCLUDES) \ $(AM_CPPFLAGS) $(CPPFLAGS) $(AM_CFLAGS) $(CFLAGS) CCLD = $(CC) LINK = $(LIBTOOL) --tag=CC $(AM_LIBTOOLFLAGS) $(LIBTOOLFLAGS) \ --mode=link $(CCLD) $(AM_CFLAGS) $(CFLAGS) $(AM_LDFLAGS) \ $(LDFLAGS) -o $@ SOURCES = $(libsigsegv_convenience_la_SOURCES) DIST_SOURCES = $(libsigsegv_convenience_la_SOURCES) am__can_run_installinfo = \ case $$AM_UPDATE_INFO_DIR in \ n|no|NO) false;; \ *) (install-info --version) >/dev/null 2>&1;; \ esac HEADERS = $(noinst_HEADERS) ETAGS = etags CTAGS = ctags DISTFILES = $(DIST_COMMON) $(DIST_SOURCES) $(TEXINFOS) $(EXTRA_DIST) ACLOCAL = @ACLOCAL@ AMTAR = @AMTAR@ AR = @AR@ AUTOCONF = @AUTOCONF@ AUTOHEADER = @AUTOHEADER@ AUTOMAKE = @AUTOMAKE@ AWK = @AWK@ CC = @CC@ CCDEPMODE = @CCDEPMODE@ CFG_HANDLER = @CFG_HANDLER@ CFG_LEAVE = @CFG_LEAVE@ CFG_STACKVMA = @CFG_STACKVMA@ CFLAGS = @CFLAGS@ CPP = @CPP@ CPPFLAGS = @CPPFLAGS@ CYGPATH_W = @CYGPATH_W@ DEFS = @DEFS@ DEPDIR = @DEPDIR@ DLLTOOL = @DLLTOOL@ DSYMUTIL = @DSYMUTIL@ DUMPBIN = @DUMPBIN@ ECHO_C = @ECHO_C@ ECHO_N = @ECHO_N@ ECHO_T = @ECHO_T@ EGREP = @EGREP@ EXEEXT = @EXEEXT@ FAULT_CONTEXT = @FAULT_CONTEXT@ FAULT_CONTEXT_INCLUDE = @FAULT_CONTEXT_INCLUDE@ FAULT_CONTEXT_INCLUDE2 = @FAULT_CONTEXT_INCLUDE2@ FGREP = @FGREP@ GREP = @GREP@ HAVE_SIGSEGV_RECOVERY = @HAVE_SIGSEGV_RECOVERY@ HAVE_STACK_OVERFLOW_RECOVERY = @HAVE_STACK_OVERFLOW_RECOVERY@ INSTALL = @INSTALL@ INSTALL_DATA = @INSTALL_DATA@ INSTALL_PROGRAM = @INSTALL_PROGRAM@ INSTALL_SCRIPT = @INSTALL_SCRIPT@ INSTALL_STRIP_PROGRAM = @INSTALL_STRIP_PROGRAM@ LD = @LD@ LDFLAGS = @LDFLAGS@ LIBOBJS = @LIBOBJS@ LIBS = @LIBS@ LIBTOOL = @LIBTOOL@ LIPO = @LIPO@ LN_S = @LN_S@ LTLIBOBJS = @LTLIBOBJS@ MAKEINFO = @MAKEINFO@ MANIFEST_TOOL = @MANIFEST_TOOL@ MKDIR_P = @MKDIR_P@ NM = @NM@ NMEDIT = @NMEDIT@ OBJDUMP = @OBJDUMP@ OBJEXT = @OBJEXT@ OTOOL = @OTOOL@ OTOOL64 = @OTOOL64@ PACKAGE = @PACKAGE@ PACKAGE_BUGREPORT = @PACKAGE_BUGREPORT@ PACKAGE_NAME = @PACKAGE_NAME@ PACKAGE_STRING = @PACKAGE_STRING@ PACKAGE_TARNAME = @PACKAGE_TARNAME@ PACKAGE_URL = @PACKAGE_URL@ PACKAGE_VERSION = @PACKAGE_VERSION@ PATH_SEPARATOR = @PATH_SEPARATOR@ PLATFORM = @PLATFORM@ RANLIB = @RANLIB@ RELOCATABLE = @RELOCATABLE@ SED = @SED@ SET_MAKE = @SET_MAKE@ SHELL = @SHELL@ STRIP = @STRIP@ VERSION = @VERSION@ abs_builddir = @abs_builddir@ abs_srcdir = @abs_srcdir@ abs_top_builddir = @abs_top_builddir@ abs_top_srcdir = @abs_top_srcdir@ ac_ct_AR = @ac_ct_AR@ ac_ct_CC = @ac_ct_CC@ ac_ct_DUMPBIN = @ac_ct_DUMPBIN@ am__include = @am__include@ am__leading_dot = @am__leading_dot@ am__quote = @am__quote@ am__tar = @am__tar@ am__untar = @am__untar@ bindir = @bindir@ build = @build@ build_alias = @build_alias@ build_cpu = @build_cpu@ build_os = @build_os@ build_vendor = @build_vendor@ builddir = @builddir@ datadir = @datadir@ datarootdir = @datarootdir@ docdir = @docdir@ dvidir = @dvidir@ exec_prefix = @exec_prefix@ host = @host@ host_alias = @host_alias@ host_cpu = @host_cpu@ host_os = @host_os@ host_vendor = @host_vendor@ htmldir = @htmldir@ includedir = @includedir@ infodir = @infodir@ install_sh = @install_sh@ libdir = @libdir@ libexecdir = @libexecdir@ localedir = @localedir@ localstatedir = @localstatedir@ mandir = @mandir@ mkdir_p = @mkdir_p@ oldincludedir = @oldincludedir@ pdfdir = @pdfdir@ prefix = @prefix@ program_transform_name = @program_transform_name@ psdir = @psdir@ sbindir = @sbindir@ sharedstatedir = @sharedstatedir@ srcdir = @srcdir@ sysconfdir = @sysconfdir@ target_alias = @target_alias@ top_build_prefix = @top_build_prefix@ top_builddir = @top_builddir@ top_srcdir = @top_srcdir@ AUTOMAKE_OPTIONS = 1.5 gnits no-dependencies RM = rm -f noinst_LTLIBRARIES = libsigsegv_convenience.la noinst_HEADERS = \ fault.h fault-aix3.h fault-aix3-powerpc.h fault-aix5.h fault-aix5-powerpc.h \ fault-beos.h fault-beos-i386.h \ fault-bsd.h fault-freebsd-i386.h \ fault-hpux.h fault-hpux-hppa.h fault-hurd.h fault-irix.h fault-irix-mips.h \ fault-linux.h fault-linux-alpha.h fault-linux-arm.h fault-linux-cris.h \ fault-linux-hppa.h fault-linux-i386.h fault-linux-i386-old.h \ fault-linux-ia64.h fault-linux-m68k.h fault-linux-m68k.c fault-linux-mips.h \ fault-linux-powerpc.h fault-linux-s390.h fault-linux-sh.h \ fault-linux-sparc.h fault-linux-x86_64.h \ fault-macos-i386.h \ fault-macosdarwin5-powerpc.h fault-macosdarwin5-powerpc.c \ fault-macosdarwin7-powerpc.h fault-macosdarwin7-powerpc.c \ fault-netbsd.h fault-netbsd-alpha.h fault-netbsd-alpha.c \ fault-none.h \ fault-openbsd.h fault-openbsd-i386.h \ fault-osf.h fault-osf-alpha.h \ fault-posix.h fault-solaris.h fault-solaris-i386.h fault-solaris-sparc.h \ machfault.h machfault-macos-i386.h machfault-macos-powerpc.h \ signals.h signals-bsd.h signals-hpux.h signals-hurd.h signals-macos.h \ leave.h \ stackvma.h EXTRA_DIST = \ handler-none.c handler-unix.c handler-macos.c handler-win32.c \ stackvma-none.c stackvma-simple.c stackvma-linux.c stackvma-freebsd.c \ stackvma-procfs.c stackvma-beos.c stackvma-mach.c stackvma-mincore.c \ leave-none.c leave-nop.c leave-sigaltstack.c leave-setcontext.c \ sigsegv.h.msvc AM_CPPFLAGS = -I. -I$(srcdir) libsigsegv_convenience_la_SOURCES = handler.c stackvma.c leave.c dispatcher.c version.c libsigsegv_convenience_la_LDFLAGS = -lc -no-undefined DISTCLEANFILES = sigsegv.h all: all-am .SUFFIXES: .SUFFIXES: .c .lo .o .obj $(srcdir)/Makefile.in: $(srcdir)/Makefile.am $(am__configure_deps) @for dep in $?; do \ case '$(am__configure_deps)' in \ *$$dep*) \ ( cd $(top_builddir) && $(MAKE) $(AM_MAKEFLAGS) am--refresh ) \ && { if test -f $@; then exit 0; else break; fi; }; \ exit 1;; \ esac; \ done; \ echo ' cd $(top_srcdir) && $(AUTOMAKE) --gnits src/Makefile'; \ $(am__cd) $(top_srcdir) && \ $(AUTOMAKE) --gnits src/Makefile .PRECIOUS: Makefile Makefile: $(srcdir)/Makefile.in $(top_builddir)/config.status @case '$?' in \ *config.status*) \ cd $(top_builddir) && $(MAKE) $(AM_MAKEFLAGS) am--refresh;; \ *) \ echo ' cd $(top_builddir) && $(SHELL) ./config.status $(subdir)/$@ $(am__depfiles_maybe)'; \ cd $(top_builddir) && $(SHELL) ./config.status $(subdir)/$@ $(am__depfiles_maybe);; \ esac; $(top_builddir)/config.status: $(top_srcdir)/configure $(CONFIG_STATUS_DEPENDENCIES) cd $(top_builddir) && $(MAKE) $(AM_MAKEFLAGS) am--refresh $(top_srcdir)/configure: $(am__configure_deps) cd $(top_builddir) && $(MAKE) $(AM_MAKEFLAGS) am--refresh $(ACLOCAL_M4): $(am__aclocal_m4_deps) cd $(top_builddir) && $(MAKE) $(AM_MAKEFLAGS) am--refresh $(am__aclocal_m4_deps): sigsegv.h: $(top_builddir)/config.status $(srcdir)/sigsegv.h.in cd $(top_builddir) && $(SHELL) ./config.status $(subdir)/$@ clean-noinstLTLIBRARIES: -test -z "$(noinst_LTLIBRARIES)" || rm -f $(noinst_LTLIBRARIES) @list='$(noinst_LTLIBRARIES)'; for p in $$list; do \ dir="`echo $$p | sed -e 's|/[^/]*$$||'`"; \ test "$$dir" != "$$p" || dir=.; \ echo "rm -f \"$${dir}/so_locations\""; \ rm -f "$${dir}/so_locations"; \ done libsigsegv_convenience.la: $(libsigsegv_convenience_la_OBJECTS) $(libsigsegv_convenience_la_DEPENDENCIES) $(EXTRA_libsigsegv_convenience_la_DEPENDENCIES) $(libsigsegv_convenience_la_LINK) $(libsigsegv_convenience_la_OBJECTS) $(libsigsegv_convenience_la_LIBADD) $(LIBS) mostlyclean-compile: -rm -f *.$(OBJEXT) distclean-compile: -rm -f *.tab.c .c.o: $(COMPILE) -c $< .c.obj: $(COMPILE) -c `$(CYGPATH_W) '$<'` .c.lo: $(LTCOMPILE) -c -o $@ $< mostlyclean-libtool: -rm -f *.lo clean-libtool: -rm -rf .libs _libs ID: $(HEADERS) $(SOURCES) $(LISP) $(TAGS_FILES) list='$(SOURCES) $(HEADERS) $(LISP) $(TAGS_FILES)'; \ unique=`for i in $$list; do \ if test -f "$$i"; then echo $$i; else echo $(srcdir)/$$i; fi; \ done | \ $(AWK) '{ files[$$0] = 1; nonempty = 1; } \ END { if (nonempty) { for (i in files) print i; }; }'`; \ mkid -fID $$unique tags: TAGS TAGS: $(HEADERS) $(SOURCES) $(TAGS_DEPENDENCIES) \ $(TAGS_FILES) $(LISP) set x; \ here=`pwd`; \ list='$(SOURCES) $(HEADERS) $(LISP) $(TAGS_FILES)'; \ unique=`for i in $$list; do \ if test -f "$$i"; then echo $$i; else echo $(srcdir)/$$i; fi; \ done | \ $(AWK) '{ files[$$0] = 1; nonempty = 1; } \ END { if (nonempty) { for (i in files) print i; }; }'`; \ shift; \ if test -z "$(ETAGS_ARGS)$$*$$unique"; then :; else \ test -n "$$unique" || unique=$$empty_fix; \ if test $$# -gt 0; then \ $(ETAGS) $(ETAGSFLAGS) $(AM_ETAGSFLAGS) $(ETAGS_ARGS) \ "$$@" $$unique; \ else \ $(ETAGS) $(ETAGSFLAGS) $(AM_ETAGSFLAGS) $(ETAGS_ARGS) \ $$unique; \ fi; \ fi ctags: CTAGS CTAGS: $(HEADERS) $(SOURCES) $(TAGS_DEPENDENCIES) \ $(TAGS_FILES) $(LISP) list='$(SOURCES) $(HEADERS) $(LISP) $(TAGS_FILES)'; \ unique=`for i in $$list; do \ if test -f "$$i"; then echo $$i; else echo $(srcdir)/$$i; fi; \ done | \ $(AWK) '{ files[$$0] = 1; nonempty = 1; } \ END { if (nonempty) { for (i in files) print i; }; }'`; \ test -z "$(CTAGS_ARGS)$$unique" \ || $(CTAGS) $(CTAGSFLAGS) $(AM_CTAGSFLAGS) $(CTAGS_ARGS) \ $$unique GTAGS: here=`$(am__cd) $(top_builddir) && pwd` \ && $(am__cd) $(top_srcdir) \ && gtags -i $(GTAGS_ARGS) "$$here" distclean-tags: -rm -f TAGS ID GTAGS GRTAGS GSYMS GPATH tags distdir: $(DISTFILES) @srcdirstrip=`echo "$(srcdir)" | sed 's/[].[^$$\\*]/\\\\&/g'`; \ topsrcdirstrip=`echo "$(top_srcdir)" | sed 's/[].[^$$\\*]/\\\\&/g'`; \ list='$(DISTFILES)'; \ dist_files=`for file in $$list; do echo $$file; done | \ sed -e "s|^$$srcdirstrip/||;t" \ -e "s|^$$topsrcdirstrip/|$(top_builddir)/|;t"`; \ case $$dist_files in \ */*) $(MKDIR_P) `echo "$$dist_files" | \ sed '/\//!d;s|^|$(distdir)/|;s,/[^/]*$$,,' | \ sort -u` ;; \ esac; \ for file in $$dist_files; do \ if test -f $$file || test -d $$file; then d=.; else d=$(srcdir); fi; \ if test -d $$d/$$file; then \ dir=`echo "/$$file" | sed -e 's,/[^/]*$$,,'`; \ if test -d "$(distdir)/$$file"; then \ find "$(distdir)/$$file" -type d ! -perm -700 -exec chmod u+rwx {} \;; \ fi; \ if test -d $(srcdir)/$$file && test $$d != $(srcdir); then \ cp -fpR $(srcdir)/$$file "$(distdir)$$dir" || exit 1; \ find "$(distdir)/$$file" -type d ! -perm -700 -exec chmod u+rwx {} \;; \ fi; \ cp -fpR $$d/$$file "$(distdir)$$dir" || exit 1; \ else \ test -f "$(distdir)/$$file" \ || cp -p $$d/$$file "$(distdir)/$$file" \ || exit 1; \ fi; \ done check-am: all-am check: check-am all-am: Makefile $(LTLIBRARIES) $(HEADERS) installdirs: installdirs-local install: install-am install-exec: install-exec-am install-data: install-data-am uninstall: uninstall-am install-am: all-am @$(MAKE) $(AM_MAKEFLAGS) install-exec-am install-data-am installcheck: installcheck-am install-strip: if test -z '$(STRIP)'; then \ $(MAKE) $(AM_MAKEFLAGS) INSTALL_PROGRAM="$(INSTALL_STRIP_PROGRAM)" \ install_sh_PROGRAM="$(INSTALL_STRIP_PROGRAM)" INSTALL_STRIP_FLAG=-s \ install; \ else \ $(MAKE) $(AM_MAKEFLAGS) INSTALL_PROGRAM="$(INSTALL_STRIP_PROGRAM)" \ install_sh_PROGRAM="$(INSTALL_STRIP_PROGRAM)" INSTALL_STRIP_FLAG=-s \ "INSTALL_PROGRAM_ENV=STRIPPROG='$(STRIP)'" install; \ fi mostlyclean-generic: clean-generic: distclean-generic: -test -z "$(CONFIG_CLEAN_FILES)" || rm -f $(CONFIG_CLEAN_FILES) -test . = "$(srcdir)" || test -z "$(CONFIG_CLEAN_VPATH_FILES)" || rm -f $(CONFIG_CLEAN_VPATH_FILES) -test -z "$(DISTCLEANFILES)" || rm -f $(DISTCLEANFILES) maintainer-clean-generic: @echo "This command is intended for maintainers to use" @echo "it deletes files that may require special tools to rebuild." clean: clean-am clean-am: clean-generic clean-libtool clean-noinstLTLIBRARIES \ mostlyclean-am distclean: distclean-am -rm -f Makefile distclean-am: clean-am distclean-compile distclean-generic \ distclean-tags dvi: dvi-am dvi-am: html: html-am html-am: info: info-am info-am: install-data-am: install-data-local install-dvi: install-dvi-am install-dvi-am: install-exec-am: install-html: install-html-am install-html-am: install-info: install-info-am install-info-am: install-man: install-pdf: install-pdf-am install-pdf-am: install-ps: install-ps-am install-ps-am: installcheck-am: maintainer-clean: maintainer-clean-am -rm -f Makefile maintainer-clean-am: distclean-am maintainer-clean-generic mostlyclean: mostlyclean-am mostlyclean-am: mostlyclean-compile mostlyclean-generic \ mostlyclean-libtool pdf: pdf-am pdf-am: ps: ps-am ps-am: uninstall-am: uninstall-local .MAKE: install-am install-strip .PHONY: CTAGS GTAGS all all-am check check-am clean clean-generic \ clean-libtool clean-noinstLTLIBRARIES ctags distclean \ distclean-compile distclean-generic distclean-libtool \ distclean-tags distdir dvi dvi-am html html-am info info-am \ install install-am install-data install-data-am \ install-data-local install-dvi install-dvi-am install-exec \ install-exec-am install-html install-html-am install-info \ install-info-am install-man install-pdf install-pdf-am \ install-ps install-ps-am install-strip installcheck \ installcheck-am installdirs installdirs-local maintainer-clean \ maintainer-clean-generic mostlyclean mostlyclean-compile \ mostlyclean-generic mostlyclean-libtool pdf pdf-am ps ps-am \ tags uninstall uninstall-am uninstall-local # Dependencies. handler.$(OBJEXT) : ../config.h sigsegv.h @CFG_HANDLER@ $(noinst_HEADERS) stackvma.$(OBJEXT) : ../config.h @CFG_STACKVMA@ stackvma.h leave.$(OBJEXT) : ../config.h @CFG_LEAVE@ dispatcher.$(OBJEXT) : sigsegv.h # Special rules for installing sigsegv.h. install-data-local: $(mkinstalldirs) $(DESTDIR)$(includedir) $(INSTALL_DATA) sigsegv.h $(DESTDIR)$(includedir)/sigsegv.h installdirs-local: $(mkinstalldirs) $(DESTDIR)$(includedir) uninstall-local: $(RM) $(DESTDIR)$(includedir)/sigsegv.h # Rules for "make dist". sigsegv.h.msvc : sigsegv.h.in sed -e 's/@''FAULT_CONTEXT_INCLUDE''@/#include /' \ -e 's/@''FAULT_CONTEXT_INCLUDE2''@//' \ -e 's/@''FAULT_CONTEXT''@/CONTEXT/' \ -e 's/@''HAVE_SIGSEGV_RECOVERY''@/1/' \ -e 's/@''HAVE_STACK_OVERFLOW_RECOVERY''@/1/' \ < $(srcdir)/sigsegv.h.in > $@ # Tell versions [3.59,3.63) of GNU make to not export all variables. # Otherwise a system limit (for SysV at least) may be exceeded. .NOEXPORT: smalltalk-3.2.5/sigsegv/src/machfault.h0000644000175000017500000000505012130343734015001 00000000000000/* Fault handler information. Copyright (C) 2004 Bruno Haible Copyright (C) 2008 Paolo Bonzini This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. */ /* The included file defines: SIGSEGV_EXC_STATE_TYPE is a type containing state describing details of an exception, excluding the thread state. Not needed if for example the fault address is found in code[1]. SIGSEGV_EXC_STATE_FLAVOR is a macro expanding to a constant int value denoting the SIGSEGV_EXC_STATE_TYPE type. Only needed if SIGSEGV_EXC_STATE_TYPE is given. SIGSEGV_EXC_STATE_COUNT is a macro expanding to the number of words of the SIGSEGV_EXC_STATE_TYPE type. Only needed if SIGSEGV_EXC_STATE_TYPE is given. SIGSEGV_THREAD_STATE_TYPE is a type containing the state of a (stopped or interrupted) thread. SIGSEGV_THREAD_STATE_FLAVOR is a macro expanding to a constant int value denoting the SIGSEGV_THREAD_STATE_TYPE type. SIGSEGV_THREAD_STATE_COUNT is a macro expanding to the number of words of the SIGSEGV_THREAD_STATE_TYPE type. SIGSEGV_FAULT_ADDRESS(code, exc_state) is a macro for fetching the fault address. Defaults to code[1]. SIGSEGV_STACK_POINTER(thr_state) is a macro, expanding to an lvalue, for fetching the stackpointer at the moment the fault occurred, and for setting the stackpointer in effect when the thread continues. SIGSEGV_PROGRAM_COUNTER(thr_state) is a macro, expanding to an lvalue, for fetching the program counter (= instruction pointer) at the moment the fault occurred, and for setting the program counter before letting the thread continue. */ #include CFG_MACHFAULT #ifndef SIGSEGV_FAULT_ADDRESS #define SIGSEGV_FAULT_ADDRESS(code,exc_state) (code[1]) #endif smalltalk-3.2.5/sigsegv/src/fault-linux-m68k.h0000644000175000017500000000211512130343734016067 00000000000000/* Fault handler information. Linux/m68k version. Copyright (C) 2002 Bruno Haible This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. */ #include #include "fault-linux-m68k.c" #define SIGSEGV_FAULT_HANDLER_ARGLIST int sig, int code, struct sigcontext *scp #define SIGSEGV_FAULT_ADDRESS (unsigned long) get_fault_addr (scp) #define SIGSEGV_FAULT_CONTEXT scp #define SIGSEGV_FAULT_STACKPOINTER scp->sc_usp smalltalk-3.2.5/sigsegv/src/fault-posix.h0000644000175000017500000000205012130343734015305 00000000000000/* Fault handler information. POSIX:2001 (= SUSV3 = XPG 6) version. Copyright (C) 2002 Bruno Haible This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. */ #include #define SIGSEGV_FAULT_HANDLER_ARGLIST int sig, siginfo_t *sip, void *ucp #define SIGSEGV_FAULT_ADDRESS sip->si_addr #define SIGSEGV_FAULT_CONTEXT ((ucontext_t *) ucp) #define SIGSEGV_FAULT_ADDRESS_FROM_SIGINFO smalltalk-3.2.5/sigsegv/src/fault-linux-hppa.h0000644000175000017500000000217712130343734016242 00000000000000/* Fault handler information. Linux/HPPA version. Copyright (C) 2002-2003 Bruno Haible This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. */ #include #define SIGSEGV_FAULT_HANDLER_ARGLIST int sig, siginfo_t *sip, void *ucp #define SIGSEGV_FAULT_ADDRESS sip->si_ptr #define SIGSEGV_FAULT_ADDRESS_FROM_SIGINFO #if 0 #define SIGSEGV_FAULT_CONTEXT ((ucontext_t *) ucp) #define SIGSEGV_FAULT_STACKPOINTER ((ucontext_t *) ucp)->uc_mcontext.gregs.g_regs[30] #endif smalltalk-3.2.5/sigsegv/src/handler-macos.c0000644000175000017500000003655512130343734015563 00000000000000/* Fault handler information. MacOSX version. Copyright (C) 1993-1999, 2002-2003, 2007 Bruno Haible Copyright (C) 2003, 2008 Paolo Bonzini This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. */ #include "sigsegv.h" #include #include #include #include #if HAVE_SYS_SIGNAL_H # include #endif #include #include #include #include #include #include /* For MacOSX. */ #ifndef SS_DISABLE #define SS_DISABLE SA_DISABLE #endif #include "machfault.h" /* The following sources were used as a *reference* for this exception handling code: 1. Apple's mach/xnu documentation 2. Timothy J. Wood's "Mach Exception Handlers 101" post to the omnigroup's macosx-dev list. www.omnigroup.com/mailman/archive/macosx-dev/2000-June/002030.html */ /* This is not defined in any header, although documented. */ /* http://web.mit.edu/darwin/src/modules/xnu/osfmk/man/exc_server.html says: The exc_server function is the MIG generated server handling function to handle messages from the kernel relating to the occurrence of an exception in a thread. Such messages are delivered to the exception port set via thread_set_exception_ports or task_set_exception_ports. When an exception occurs in a thread, the thread sends an exception message to its exception port, blocking in the kernel waiting for the receipt of a reply. The exc_server function performs all necessary argument handling for this kernel message and calls catch_exception_raise, catch_exception_raise_state or catch_exception_raise_state_identity, which should handle the exception. If the called routine returns KERN_SUCCESS, a reply message will be sent, allowing the thread to continue from the point of the exception; otherwise, no reply message is sent and the called routine must have dealt with the exception thread directly. */ extern boolean_t exc_server (mach_msg_header_t *request_msg, mach_msg_header_t *reply_msg); /* http://web.mit.edu/darwin/src/modules/xnu/osfmk/man/catch_exception_raise.html These functions are defined in this file, and called by exc_server. FIXME: What needs to be done when this code is put into a shared library? */ kern_return_t catch_exception_raise (mach_port_t exception_port, mach_port_t thread, mach_port_t task, exception_type_t exception, exception_data_t code, mach_msg_type_number_t code_count); kern_return_t catch_exception_raise_state (mach_port_t exception_port, exception_type_t exception, exception_data_t code, mach_msg_type_number_t code_count, thread_state_flavor_t *flavor, thread_state_t in_state, mach_msg_type_number_t in_state_count, thread_state_t out_state, mach_msg_type_number_t *out_state_count); kern_return_t catch_exception_raise_state_identity (mach_port_t exception_port, mach_port_t thread, mach_port_t task, exception_type_t exception, exception_data_t code, mach_msg_type_number_t codeCnt, thread_state_flavor_t *flavor, thread_state_t in_state, mach_msg_type_number_t in_state_count, thread_state_t out_state, mach_msg_type_number_t *out_state_count); /* The exception port on which our thread listens. */ static mach_port_t our_exception_port; /* mach_initialize() status: 0: not yet called 1: called and succeeded -1: called and failed */ static int mach_initialized = 0; /* Communication area for the exception state and thread state. */ static SIGSEGV_THREAD_STATE_TYPE save_thread_state; /* Check for reentrant signals. */ static int emergency = -1; /* User's stack overflow handler. */ static stackoverflow_handler_t stk_user_handler = (stackoverflow_handler_t)NULL; static unsigned long stk_extra_stack; static unsigned long stk_extra_stack_size; /* User's fault handler. */ static sigsegv_handler_t user_handler = (sigsegv_handler_t)NULL; /* A handler that is called in the faulting thread. It terminates the thread. */ static void terminating_handler () { /* Dump core. */ raise (SIGSEGV); /* Seriously. */ abort (); } /* A handler that is called in the faulting thread, on an alternate stack. It calls the user installed stack overflow handler. */ static void altstack_handler () { /* We arrive here when the user refused to handle a fault. */ /* Check if it is plausibly a stack overflow, and the user installed a stack overflow handler. */ if (stk_user_handler) { emergency++; /* Call user's handler. */ (*stk_user_handler) (emergency, &save_thread_state); } /* Else, terminate the thread. */ terminating_handler (); } static inline int call_user_handler (void *addr, int serious) { int done; if (!user_handler) return 0; #ifdef DEBUG_EXCEPTION_HANDLING fprintf (stderr, "Calling user handler, addr = 0x%lx\n", (char *) addr); #endif done = (*user_handler) ((void *) addr, serious); #ifdef DEBUG_EXCEPTION_HANDLING fprintf (stderr, "Back from user handler\n"); #endif return done; } /* Handle an exception by invoking the user's fault handler and/or forwarding the duty to the previously installed handlers. */ kern_return_t catch_exception_raise (mach_port_t exception_port, mach_port_t thread, mach_port_t task, exception_type_t exception, exception_data_t code, mach_msg_type_number_t code_count) { #ifdef SIGSEGV_EXC_STATE_TYPE SIGSEGV_EXC_STATE_TYPE exc_state; #endif SIGSEGV_THREAD_STATE_TYPE thread_state; mach_msg_type_number_t state_count; unsigned long addr; unsigned long sp; #ifdef DEBUG_EXCEPTION_HANDLING fprintf (stderr, "Exception: 0x%x Code: 0x%x 0x%x in catch....\n", exception, code_count > 0 ? code[0] : -1, code_count > 1 ? code[1] : -1); #endif /* See http://web.mit.edu/darwin/src/modules/xnu/osfmk/man/thread_get_state.html. */ #ifdef SIGSEGV_EXC_STATE_TYPE state_count = SIGSEGV_EXC_STATE_COUNT; if (thread_get_state (thread, SIGSEGV_EXC_STATE_FLAVOR, (void *) &exc_state, &state_count) != KERN_SUCCESS) { /* The thread is supposed to be suspended while the exception handler is called. This shouldn't fail. */ #ifdef DEBUG_EXCEPTION_HANDLING fprintf (stderr, "thread_get_state failed for exception state\n"); #endif return KERN_FAILURE; } #endif /* It turns out any Darwin kernel starting at 10.2 contains a "fast" path to determine the address of a fault: it is located into code[1]. MacOS X exception delivery is really slow, so we also pass code and make getting the EXC_STATE conditional. */ addr = (unsigned long) (SIGSEGV_FAULT_ADDRESS (code, exc_state)); /* It gets worse if we want to retrieve the machine registers, so we call the user handler before detecting if the exception is really a stack fault. */ if (call_user_handler ((void *) addr, 0)) return KERN_SUCCESS; /* See http://web.mit.edu/darwin/src/modules/xnu/osfmk/man/thread_get_state.html. */ state_count = SIGSEGV_THREAD_STATE_COUNT; if (thread_get_state (thread, SIGSEGV_THREAD_STATE_FLAVOR, (void *) &thread_state, &state_count) != KERN_SUCCESS) { /* The thread is supposed to be suspended while the exception handler is called. This shouldn't fail. */ #ifdef DEBUG_EXCEPTION_HANDLING fprintf (stderr, "thread_get_state failed for thread state\n"); #endif return KERN_FAILURE; } sp = (unsigned long) (SIGSEGV_STACK_POINTER (thread_state)); /* Got the thread's state. Now extract the address that caused the fault and invoke the user's handler. */ save_thread_state = thread_state; /* If the fault address is near the stack pointer, it's a stack overflow. Otherwise, treat it like a normal SIGSEGV. */ if (addr <= sp + 4096 && sp <= addr + 4096) { unsigned long new_safe_esp; #ifdef DEBUG_EXCEPTION_HANDLING fprintf (stderr, "Treating as stack overflow, sp = 0x%lx\n", (char *) sp); #endif new_safe_esp = #if STACK_DIRECTION < 0 stk_extra_stack + stk_extra_stack_size - 256; #else stk_extra_stack + 256; #endif #ifdef __i386__ new_safe_esp &= -16; /* align */ new_safe_esp -= 4; /* make room for (unused) return address slot */ #endif SIGSEGV_STACK_POINTER (thread_state) = new_safe_esp; /* Continue handling this fault in the faulting thread. (We cannot longjmp while in the exception handling thread, so we need to mimic what signals do!) */ SIGSEGV_PROGRAM_COUNTER (thread_state) = (unsigned long) altstack_handler; } else { if (call_user_handler ((void *) addr, 1)) return KERN_SUCCESS; SIGSEGV_PROGRAM_COUNTER (thread_state) = (unsigned long) terminating_handler; } /* See http://web.mit.edu/darwin/src/modules/xnu/osfmk/man/thread_set_state.html. */ if (thread_set_state (thread, SIGSEGV_THREAD_STATE_FLAVOR, (void *) &thread_state, state_count) != KERN_SUCCESS) { #ifdef DEBUG_EXCEPTION_HANDLING fprintf (stderr, "thread_set_state failed for altstack state\n"); #endif return KERN_FAILURE; } return KERN_SUCCESS; } /* The main function of the thread listening for exceptions. */ static void * mach_exception_thread (void *arg) { for (;;) { /* These two structures contain some private kernel data. We don't need to access any of it so we don't bother defining a proper struct. The correct definitions are in the xnu source code. */ /* Buffer for a message to be received. */ struct { mach_msg_header_t head; mach_msg_body_t msgh_body; char data[1024]; } msg; /* Buffer for a reply message. */ struct { mach_msg_header_t head; char data[1024]; } reply; mach_msg_return_t retval; #ifdef DEBUG_EXCEPTION_HANDLING fprintf (stderr, "Exception thread going to sleep\n"); #endif /* Wait for a message on the exception port. */ retval = mach_msg (&msg.head, MACH_RCV_MSG | MACH_RCV_LARGE, 0, sizeof (msg), our_exception_port, MACH_MSG_TIMEOUT_NONE, MACH_PORT_NULL); #ifdef DEBUG_EXCEPTION_HANDLING fprintf (stderr, "Exception thread woke up\n"); #endif if (retval != MACH_MSG_SUCCESS) { #ifdef DEBUG_EXCEPTION_HANDLING fprintf (stderr, "mach_msg receive failed with %d %s\n", (int) retval, mach_error_string (retval)); #endif abort (); } /* Handle the message: Call exc_server, which will call catch_exception_raise and produce a reply message. */ #ifdef DEBUG_EXCEPTION_HANDLING fprintf (stderr, "Calling exc_server\n"); #endif exc_server (&msg.head, &reply.head); #ifdef DEBUG_EXCEPTION_HANDLING fprintf (stderr, "Finished exc_server\n"); #endif /* Send the reply. */ if (mach_msg (&reply.head, MACH_SEND_MSG, reply.head.msgh_size, 0, MACH_PORT_NULL, MACH_MSG_TIMEOUT_NONE, MACH_PORT_NULL) != MACH_MSG_SUCCESS) { #ifdef DEBUG_EXCEPTION_HANDLING fprintf (stderr, "mach_msg send failed\n"); #endif abort (); } #ifdef DEBUG_EXCEPTION_HANDLING fprintf (stderr, "Reply successful\n"); #endif } } /* Initialize the Mach exception handler thread. Return 0 if OK, -1 on error. */ static int mach_initialize () { mach_port_t self; exception_mask_t mask; pthread_attr_t attr; pthread_t thread; self = mach_task_self (); /* Allocate a port on which the thread shall listen for exceptions. */ if (mach_port_allocate (self, MACH_PORT_RIGHT_RECEIVE, &our_exception_port) != KERN_SUCCESS) return -1; /* See http://web.mit.edu/darwin/src/modules/xnu/osfmk/man/mach_port_insert_right.html. */ if (mach_port_insert_right (self, our_exception_port, our_exception_port, MACH_MSG_TYPE_MAKE_SEND) != KERN_SUCCESS) return -1; /* The exceptions we want to catch. Only EXC_BAD_ACCESS is interesting for us (see above in function catch_exception_raise). */ mask = EXC_MASK_BAD_ACCESS; /* Create the thread listening on the exception port. */ if (pthread_attr_init (&attr) != 0) return -1; if (pthread_attr_setdetachstate (&attr, PTHREAD_CREATE_DETACHED) != 0) return -1; if (pthread_create (&thread, &attr, mach_exception_thread, NULL) != 0) return -1; pthread_attr_destroy (&attr); /* Replace the exception port info for these exceptions with our own. Note that we replace the exception port for the entire task, not only for a particular thread. This has the effect that when our exception port gets the message, the thread specific exception port has already been asked, and we don't need to bother about it. See http://web.mit.edu/darwin/src/modules/xnu/osfmk/man/task_set_exception_ports.html. */ if (task_set_exception_ports (self, mask, our_exception_port, EXCEPTION_DEFAULT, MACHINE_THREAD_STATE) != KERN_SUCCESS) return -1; return 0; } int sigsegv_install_handler (sigsegv_handler_t handler) { if (!mach_initialized) mach_initialized = (mach_initialize () >= 0 ? 1 : -1); if (mach_initialized < 0) return -1; user_handler = handler; return 0; } void sigsegv_deinstall_handler (void) { user_handler = (sigsegv_handler_t)NULL; } void sigsegv_leave_handler (void) { emergency--; } int stackoverflow_install_handler (stackoverflow_handler_t handler, void *extra_stack, unsigned long extra_stack_size) { if (!mach_initialized) mach_initialized = (mach_initialize () >= 0 ? 1 : -1); if (mach_initialized < 0) return -1; stk_user_handler = handler; stk_extra_stack = (unsigned long) extra_stack; stk_extra_stack_size = extra_stack_size; return 0; } void stackoverflow_deinstall_handler (void) { stk_user_handler = (stackoverflow_handler_t) NULL; } smalltalk-3.2.5/sigsegv/src/leave-sigaltstack.c0000644000175000017500000000222012130343734016427 00000000000000/* Leaving a signal handler executing on the alternate stack. Copyright (C) 2002-2003 Bruno Haible This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. */ #include #include #if HAVE_SYS_SIGNAL_H # include #endif /* For MacOSX. */ #ifndef SS_ONSTACK #define SS_ONSTACK SA_ONSTACK #endif void sigsegv_reset_onstack_flag (void) { stack_t ss; if (sigaltstack (NULL, &ss) >= 0) { ss.ss_flags &= ~SS_ONSTACK; sigaltstack (&ss, NULL); } } smalltalk-3.2.5/sigsegv/src/fault-linux-powerpc.h0000644000175000017500000000203012130343734016755 00000000000000/* Fault handler information. Linux/PowerPC version. Copyright (C) 2002 Bruno Haible This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. */ #include #define SIGSEGV_FAULT_HANDLER_ARGLIST int sig, struct sigcontext *scp #define SIGSEGV_FAULT_ADDRESS scp->regs->dar #define SIGSEGV_FAULT_CONTEXT scp #define SIGSEGV_FAULT_STACKPOINTER scp->regs->gpr[1] smalltalk-3.2.5/sigsegv/src/fault-macosdarwin5-powerpc.c0000644000175000017500000000742312130343734020220 00000000000000/* Fault handler information subroutine. MacOSX/Darwin5/PowerPC version. * Taken from gcc-3.2/boehm-gc/os_dep.c. * * Copyright 1988, 1989 Hans-J. Boehm, Alan J. Demers * Copyright (c) 1991-1995 by Xerox Corporation. All rights reserved. * Copyright (c) 1996-1999 by Silicon Graphics. All rights reserved. * Copyright (c) 1999 by Hewlett-Packard Company. All rights reserved. * * THIS MATERIAL IS PROVIDED AS IS, WITH ABSOLUTELY NO WARRANTY EXPRESSED * OR IMPLIED. ANY USE IS AT YOUR OWN RISK. * * Permission is hereby granted to use or copy this program * for any purpose, provided the above notices are retained on all copies. * Permission to modify the code and to distribute modified code is granted, * provided the above notices are retained, and a notice that the code was * modified is included with the above copyright notice. */ /* Decodes the machine instruction which was responsible for the sending of the SIGBUS signal. Sadly this is the only way to find the faulting address because the signal handler doesn't get it directly from the kernel (although it is available on the Mach level, but dropped by the BSD personality before it calls our signal handler...) This code should be able to deal correctly with all PPCs starting from the 601 up to and including the G4s (including Velocity Engine). */ #define EXTRACT_OP1(iw) (((iw) & 0xFC000000) >> 26) #define EXTRACT_OP2(iw) (((iw) & 0x000007FE) >> 1) #define EXTRACT_REGA(iw) (((iw) & 0x001F0000) >> 16) #define EXTRACT_REGB(iw) (((iw) & 0x03E00000) >> 21) #define EXTRACT_REGC(iw) (((iw) & 0x0000F800) >> 11) #define EXTRACT_DISP(iw) ((short *) &(iw))[1] static void * get_fault_addr (struct sigcontext *scp) { unsigned int instr = *((unsigned int *) scp->sc_ir); unsigned int *regs = &((unsigned int *) scp->sc_regs)[2]; int disp = 0; int tmp; unsigned int baseA = 0; unsigned int baseB = 0; unsigned int addr; unsigned int alignmask = 0xFFFFFFFF; switch (EXTRACT_OP1 (instr)) { case 38: /* stb */ case 39: /* stbu */ case 54: /* stfd */ case 55: /* stfdu */ case 52: /* stfs */ case 53: /* stfsu */ case 44: /* sth */ case 45: /* sthu */ case 47: /* stmw */ case 36: /* stw */ case 37: /* stwu */ tmp = EXTRACT_REGA (instr); if (tmp > 0) baseA = regs[tmp]; disp = EXTRACT_DISP (instr); break; case 31: switch (EXTRACT_OP2 (instr)) { case 86: /* dcbf */ case 54: /* dcbst */ case 1014: /* dcbz */ case 247: /* stbux */ case 215: /* stbx */ case 759: /* stfdux */ case 727: /* stfdx */ case 983: /* stfiwx */ case 695: /* stfsux */ case 663: /* stfsx */ case 918: /* sthbrx */ case 439: /* sthux */ case 407: /* sthx */ case 661: /* stswx */ case 662: /* stwbrx */ case 150: /* stwcx. */ case 183: /* stwux */ case 151: /* stwx */ case 135: /* stvebx */ case 167: /* stvehx */ case 199: /* stvewx */ case 231: /* stvx */ case 487: /* stvxl */ tmp = EXTRACT_REGA (instr); if (tmp > 0) baseA = regs[tmp]; baseB = regs[EXTRACT_REGC (instr)]; /* Determine Altivec alignment mask. */ switch (EXTRACT_OP2 (instr)) { case 167: /* stvehx */ alignmask = 0xFFFFFFFE; break; case 199: /* stvewx */ alignmask = 0xFFFFFFFC; break; case 231: /* stvx */ case 487: /* stvxl */ alignmask = 0xFFFFFFF0; break; } break; case 725: /* stswi */ tmp = EXTRACT_REGA (instr); if (tmp > 0) baseA = regs[tmp]; break; default: /* ignore instruction */ return (void *) 0; } break; default: /* ignore instruction */ return (void *) 0; } addr = (baseA + baseB) + disp; addr &= alignmask; return (void *) addr; } smalltalk-3.2.5/sigsegv/src/handler.c0000644000175000017500000000147712130343734014456 00000000000000/* Fault handler information. Copyright (C) 2002 Bruno Haible This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. */ #include "config.h" #include CFG_HANDLER smalltalk-3.2.5/sigsegv/src/fault-osf.h0000644000175000017500000000163112130343734014736 00000000000000/* Fault handler information. OSF/1 version. Copyright (C) 2002 Bruno Haible This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. */ #define SIGSEGV_FAULT_HANDLER_ARGLIST int sig, int code, struct sigcontext *scp #define SIGSEGV_FAULT_CONTEXT scp smalltalk-3.2.5/sigsegv/src/leave-nop.c0000644000175000017500000000172212130343734014720 00000000000000/* Leaving a signal handler executing on the alternate stack. Copyright (C) 2002 Bruno Haible This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. */ void sigsegv_reset_onstack_flag (void) { /* Nothing to do. sigaltstack() simply looks at the stack pointer, therefore SS_ONSTACK is not sticky. */ } smalltalk-3.2.5/sigsegv/src/signals-macos.h0000644000175000017500000000224212130343734015575 00000000000000/* List of signals. MacOSX version. Copyright (C) 2002 Bruno Haible Copyright (C) 2003 Paolo Bonzini This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. */ /* List of signals that are sent when an invalid virtual memory address is accessed, or when the stack overflows. On MacOS X, accessing an invalid memory address gives a SIGBUS, but a stack overflow gives a SIGSEGV. */ #define SIGSEGV_FOR_ALL_SIGNALS(var,body) \ { int var; var = SIGSEGV; { body } var = SIGBUS; { body } } smalltalk-3.2.5/sigsegv/src/stackvma-linux.c0000644000175000017500000000411412130343734015776 00000000000000/* Determine the virtual memory area of a given address. Linux version. Copyright (C) 2002, 2006 Bruno Haible This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. */ #include "stackvma.h" #include #include "stackvma-simple.c" #if HAVE_MINCORE # define sigsegv_get_vma mincore_get_vma # define STATIC static # include "stackvma-mincore.c" # undef sigsegv_get_vma #endif int sigsegv_get_vma (unsigned long address, struct vma_struct *vma) { FILE *fp; int c; unsigned long start, end; #if STACK_DIRECTION < 0 unsigned long prev; #endif /* Open the current process' maps file. It describes one VMA per line. */ fp = fopen ("/proc/self/maps", "r"); if (!fp) goto failed; #if STACK_DIRECTION < 0 prev = 0; #endif for (;;) { if (fscanf (fp, "%lx-%lx", &start, &end) != 2) break; while (c = getc (fp), c != EOF && c != '\n') continue; if (address >= start && address <= end - 1) { vma->start = start; vma->end = end; #if STACK_DIRECTION < 0 vma->prev_end = prev; #else if (fscanf (fp, "%lx-%lx", &vma->next_start, &end) != 2) vma->next_start = 0; #endif fclose (fp); vma->is_near_this = simple_is_near_this; return 0; } #if STACK_DIRECTION < 0 prev = end; #endif } fclose (fp); failed: #if HAVE_MINCORE return mincore_get_vma (address, vma); #else return -1; #endif } smalltalk-3.2.5/sigsegv/src/fault-linux-i386.h0000644000175000017500000000201212130343734015767 00000000000000/* Fault handler information. Linux/i386 version. Copyright (C) 2002 Bruno Haible This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. */ #define SIGSEGV_FAULT_HANDLER_ARGLIST int sig, struct sigcontext sc #define SIGSEGV_FAULT_ADDRESS sc.cr2 #define SIGSEGV_FAULT_CONTEXT (&sc) #define SIGSEGV_FAULT_STACKPOINTER sc.esp /* same value as sc.esp_at_signal */ smalltalk-3.2.5/sigsegv/src/fault-netbsd-alpha.h0000644000175000017500000000225712130343734016516 00000000000000/* Fault handler information. NetBSD/Alpha version. Copyright (C) 2003 Paolo Bonzini This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. */ /* NetBSD's sc_sp field depends on machine/reg.h's definition of R_SP. */ #include #include "fault-netbsd-alpha.c" #define SIGSEGV_FAULT_HANDLER_ARGLIST int sig, int code, struct sigcontext *scp #define SIGSEGV_FAULT_ADDRESS ((unsigned long) get_fault_addr (scp)) #define SIGSEGV_FAULT_CONTEXT scp #define SIGSEGV_FAULT_STACKPOINTER ((unsigned int *) scp->sc_sp) smalltalk-3.2.5/sigsegv/src/stackvma-beos.c0000644000175000017500000000340212130343734015566 00000000000000/* Determine the virtual memory area of a given address. BeOS version. Copyright (C) 2002, 2006 Bruno Haible This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. */ #include "stackvma.h" #include #include "stackvma-simple.c" int sigsegv_get_vma (unsigned long address, struct vma_struct *vma) { area_info info; int32 cookie; unsigned long start, end; #if STACK_DIRECTION < 0 unsigned long prev; #endif #if STACK_DIRECTION < 0 prev = 0; #endif cookie = 0; while (get_next_area_info (0, &cookie, &info) == B_OK) { start = (unsigned long) info.address; end = start + info.size; if (address >= start && address <= end - 1) { vma->start = start; vma->end = end; #if STACK_DIRECTION < 0 vma->prev_end = prev; #else if (get_next_area_info (0, &cookie, &info) == B_OK) vma->next_start = (unsigned long) info.address; else vma->next_start = 0; #endif vma->is_near_this = simple_is_near_this; return 0; } #if STACK_DIRECTION < 0 prev = end; #endif } return -1; } smalltalk-3.2.5/sigsegv/src/fault-linux-cris.h0000644000175000017500000000176712130343734016256 00000000000000/* Fault handler information. Linux/cris version. Copyright (C) 2002 Bruno Haible This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. */ #include #define SIGSEGV_FAULT_HANDLER_ARGLIST int sig, int r11, int r12, int r13, struct sigcontext sc #define SIGSEGV_FAULT_CONTEXT (&sc) #define SIGSEGV_FAULT_STACKPOINTER sc.usp smalltalk-3.2.5/sigsegv/src/fault-openbsd-i386.h0000644000175000017500000000157012130343734016272 00000000000000/* Fault handler information. OpenBSD/i386 version. Copyright (C) 2003 Bruno Haible This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. */ #include "fault-openbsd.h" #define SIGSEGV_FAULT_STACKPOINTER scp->sc_esp smalltalk-3.2.5/sigsegv/src/stackvma.h0000644000175000017500000000366612130343734014661 00000000000000/* Determine the virtual memory area of a given address. Copyright (C) 2002, 2006 Bruno Haible This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. */ #ifndef _STACKVMA_H #define _STACKVMA_H /* Describes a virtual memory area, with some info about the gap between it and the next or previous virtual memory area. */ struct vma_struct { unsigned long start; unsigned long end; #if STACK_DIRECTION < 0 /* Info about the gap between this VMA and the previous one. addr must be < vma->start. */ int (*is_near_this) (unsigned long addr, struct vma_struct *vma); /* Private field, not provided by all sigsegv_get_vma implementations. */ unsigned long prev_end; #endif #if STACK_DIRECTION > 0 /* Info about the gap between this VMA and the next one. addr must be > vma->end - 1. */ int (*is_near_this) (unsigned long addr, struct vma_struct *vma); /* Private field, not provided by all sigsegv_get_vma implementations. */ unsigned long next_start; #endif }; /* Determines the virtual memory area to which a given address belongs, and returns 0. Returns -1 if it cannot be determined. This function is used to determine the stack extent when a fault occurs. */ extern int sigsegv_get_vma (unsigned long address, struct vma_struct *vma); #endif /* _STACKVMA_H */ smalltalk-3.2.5/sigsegv/src/fault-linux-alpha.h0000644000175000017500000000176112130343734016375 00000000000000/* Fault handler information. Linux/Alpha version. Copyright (C) 2002 Bruno Haible This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. */ #include #define SIGSEGV_FAULT_HANDLER_ARGLIST int sig, int code, struct sigcontext *scp #define SIGSEGV_FAULT_CONTEXT scp #define SIGSEGV_FAULT_STACKPOINTER scp->sc_regs[30] smalltalk-3.2.5/sigsegv/src/fault-macosdarwin7-powerpc.c0000644000175000017500000000761112130343734020221 00000000000000/* Fault handler information subroutine. MacOSX/Darwin7/PowerPC version. * Taken from gcc-3.2/boehm-gc/os_dep.c. * * Copyright 1988, 1989 Hans-J. Boehm, Alan J. Demers * Copyright (c) 1991-1995 by Xerox Corporation. All rights reserved. * Copyright (c) 1996-1999 by Silicon Graphics. All rights reserved. * Copyright (c) 1999 by Hewlett-Packard Company. All rights reserved. * * THIS MATERIAL IS PROVIDED AS IS, WITH ABSOLUTELY NO WARRANTY EXPRESSED * OR IMPLIED. ANY USE IS AT YOUR OWN RISK. * * Permission is hereby granted to use or copy this program * for any purpose, provided the above notices are retained on all copies. * Permission to modify the code and to distribute modified code is granted, * provided the above notices are retained, and a notice that the code was * modified is included with the above copyright notice. */ #include /* Decodes the machine instruction which was responsible for the sending of the SIGBUS signal. Sadly this is the only way to find the faulting address because the signal handler doesn't get it directly from the kernel (although it is available on the Mach level, but dropped by the BSD personality before it calls our signal handler...) This code should be able to deal correctly with all PPCs starting from the 601 up to and including the G4s (including Velocity Engine). */ #define EXTRACT_OP1(iw) (((iw) & 0xFC000000) >> 26) #define EXTRACT_OP2(iw) (((iw) & 0x000007FE) >> 1) #define EXTRACT_REGA(iw) (((iw) & 0x001F0000) >> 16) #define EXTRACT_REGB(iw) (((iw) & 0x03E00000) >> 21) #define EXTRACT_REGC(iw) (((iw) & 0x0000F800) >> 11) #define EXTRACT_DISP(iw) ((short *) &(iw))[1] static void * get_fault_addr (siginfo_t *sip, ucontext_t *ucp) { unsigned int instr = *(unsigned int *) sip->si_addr; unsigned int *regs = #if __DARWIN_UNIX03 &ucp->uc_mcontext->ss.__r0; /* r0..r31 */ #else &ucp->uc_mcontext->ss.r0; /* r0..r31 */ #endif int disp = 0; int tmp; unsigned int baseA = 0; unsigned int baseB = 0; unsigned int addr; unsigned int alignmask = 0xFFFFFFFF; switch (EXTRACT_OP1 (instr)) { case 38: /* stb */ case 39: /* stbu */ case 54: /* stfd */ case 55: /* stfdu */ case 52: /* stfs */ case 53: /* stfsu */ case 44: /* sth */ case 45: /* sthu */ case 47: /* stmw */ case 36: /* stw */ case 37: /* stwu */ tmp = EXTRACT_REGA (instr); if (tmp > 0) baseA = regs[tmp]; disp = EXTRACT_DISP (instr); break; case 31: switch (EXTRACT_OP2 (instr)) { case 86: /* dcbf */ case 54: /* dcbst */ case 1014: /* dcbz */ case 247: /* stbux */ case 215: /* stbx */ case 759: /* stfdux */ case 727: /* stfdx */ case 983: /* stfiwx */ case 695: /* stfsux */ case 663: /* stfsx */ case 918: /* sthbrx */ case 439: /* sthux */ case 407: /* sthx */ case 661: /* stswx */ case 662: /* stwbrx */ case 150: /* stwcx. */ case 183: /* stwux */ case 151: /* stwx */ case 135: /* stvebx */ case 167: /* stvehx */ case 199: /* stvewx */ case 231: /* stvx */ case 487: /* stvxl */ tmp = EXTRACT_REGA (instr); if (tmp > 0) baseA = regs[tmp]; baseB = regs[EXTRACT_REGC (instr)]; /* Determine Altivec alignment mask. */ switch (EXTRACT_OP2 (instr)) { case 167: /* stvehx */ alignmask = 0xFFFFFFFE; break; case 199: /* stvewx */ alignmask = 0xFFFFFFFC; break; case 231: /* stvx */ case 487: /* stvxl */ alignmask = 0xFFFFFFF0; break; } break; case 725: /* stswi */ tmp = EXTRACT_REGA (instr); if (tmp > 0) baseA = regs[tmp]; break; default: /* ignore instruction */ return (void *) 0; } break; default: /* ignore instruction */ return (void *) 0; } addr = (baseA + baseB) + disp; addr &= alignmask; return (void *) addr; } smalltalk-3.2.5/sigsegv/src/fault-solaris-i386.h0000644000175000017500000000163112130343734016312 00000000000000/* Fault handler information. Solaris/i386 version. Copyright (C) 2002 Bruno Haible This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. */ #include "fault-solaris.h" #define SIGSEGV_FAULT_STACKPOINTER ((ucontext_t *) ucp)->uc_mcontext.gregs[ESP] smalltalk-3.2.5/sigsegv/src/signals.h0000644000175000017500000000175612130343734014506 00000000000000/* List of signals. Generic Unix version. Copyright (C) 2002 Bruno Haible This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. */ /* List of signals that are sent when an invalid virtual memory address is accessed, or when the stack overflows. */ #define SIGSEGV_FOR_ALL_SIGNALS(var,body) \ { int var; var = SIGSEGV; { body } } smalltalk-3.2.5/sigsegv/src/fault-openbsd.h0000644000175000017500000000177012130343734015605 00000000000000/* Fault handler information. OpenBSD version. Copyright (C) 2003 Bruno Haible This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. */ #define SIGSEGV_FAULT_HANDLER_ARGLIST int sig, siginfo_t *sip, struct sigcontext *scp #define SIGSEGV_FAULT_ADDRESS sip->si_addr #define SIGSEGV_FAULT_CONTEXT scp #define SIGSEGV_FAULT_ADDRESS_FROM_SIGINFO smalltalk-3.2.5/sigsegv/src/stackvma-procfs.c0000644000175000017500000000506012130343734016134 00000000000000/* Determine the virtual memory area of a given address. Copyright (C) 2002, 2006 Bruno Haible This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. */ #include "stackvma.h" #include /* sprintf */ #include /* open, close */ #include /* open */ #include /* malloc, free */ #include /* PIOC*, prmap_t */ #include "stackvma-simple.c" #if HAVE_MINCORE # define sigsegv_get_vma mincore_get_vma # define STATIC static # include "stackvma-mincore.c" # undef sigsegv_get_vma #endif int sigsegv_get_vma (unsigned long address, struct vma_struct *vma) { char fname[6+10+1]; int fd; int nmaps; prmap_t* maps; prmap_t* mp; unsigned long start, end; #if STACK_DIRECTION < 0 unsigned long prev; #endif sprintf (fname,"/proc/%u", (unsigned int) getpid ()); fd = open (fname, O_RDONLY); if (fd < 0) goto failed; if (ioctl (fd, PIOCNMAP, &nmaps) < 0) goto fail2; /* Use malloc here, not alloca, because we are low on stack space. */ maps = (prmap_t *) malloc ((nmaps + 10) * sizeof (prmap_t)); if (maps == NULL) goto fail2; if (ioctl (fd, PIOCMAP, maps) < 0) goto fail1; #if STACK_DIRECTION < 0 prev = 0; #endif for (mp = maps;;) { start = (unsigned long) mp->pr_vaddr; end = start + mp->pr_size; if (start == 0 && end == 0) break; mp++; if (address >= start && address <= end - 1) { vma->start = start; vma->end = end; #if STACK_DIRECTION < 0 vma->prev_end = prev; #else vma->next_start = (unsigned long) mp->pr_vaddr; #endif free (maps); close (fd); vma->is_near_this = simple_is_near_this; return 0; } #if STACK_DIRECTION < 0 prev = end; #endif } fail1: free (maps); fail2: close (fd); failed: #if HAVE_MINCORE return mincore_get_vma (address, vma); #else return -1; #endif } smalltalk-3.2.5/sigsegv/src/fault-linux-s390.h0000644000175000017500000000175712130343734016013 00000000000000/* Fault handler information. Linux/S390 version. Copyright (C) 2002 Bruno Haible This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. */ #include #define SIGSEGV_FAULT_HANDLER_ARGLIST int sig, struct sigcontext *scp #define SIGSEGV_FAULT_CONTEXT scp #define SIGSEGV_FAULT_STACKPOINTER scp->sregs->regs.gprs[15] smalltalk-3.2.5/sigsegv/AUTHORS0000644000175000017500000000026212130343734013145 00000000000000Authors of GNU libsigsegv. Bruno Haible Versions 1.0 and 2.0 Paolo Bonzini HP-UX, MacOS X, Cygwin support smalltalk-3.2.5/sigsegv/Makefile.msvc0000644000175000017500000000647112130343734014514 00000000000000# -*- Makefile -*- for libsigsegv #### Start of system configuration section. #### # Flags that can be set on the nmake command line: # MFLAGS={-ML|-MT|-MD} for defining the compilation model # MFLAGS=-ML (the default) Single-threaded, statically linked - libc.lib # MFLAGS=-MT Multi-threaded, statically linked - libcmt.lib # MFLAGS=-MD Multi-threaded, dynamically linked - msvcrt.lib # DEBUG=1 for compiling with debugging information # Note that nmake command line flags are automatically passed to subdirectory # Makefiles. Therefore we don't need to pass them explicitly to subdirectory # Makefiles, but the subdirectory Makefiles need to have the same defaults. # Building as a DLL not supported yet. DLL=0 !if !defined(DEBUG) DEBUG=0 !endif !if !defined(MFLAGS) !if !$(DLL) MFLAGS= !else MFLAGS=-MD !endif !endif !if $(DEBUG) OPTIMFLAGS = -Od -Z7 !else OPTIMFLAGS = -D_NDEBUG -O1 !endif # Directories used by "make": srcdir = . # Directories used by "make install": prefix = /usr/local local_prefix = /usr/local exec_prefix = $(prefix) libdir = $(exec_prefix)/lib includedir = $(prefix)/include # Programs used by "make": CC = cl CFLAGS = $(MFLAGS) $(OPTIMFLAGS) CPP = cl -E INCLUDES = -I. -I$(srcdir) AR = lib AR_FLAGS = /out: MV = ren CP = copy LN = copy RM = -del # Programs used by "make install": INSTALL = @INSTALL@ INSTALL_PROGRAM = @INSTALL_PROGRAM@ INSTALL_DATA = @INSTALL_DATA@ #### End of system configuration section. #### SHELL = /bin/sh OBJECTS = handler.obj dispatcher.obj version.obj all : sigsegv.lib config.h : config.h.msvc $(CP) $(srcdir)\config.h.msvc config.h sigsegv.h : src/sigsegv.h.msvc $(CP) $(srcdir)\src\sigsegv.h.msvc sigsegv.h handler.obj : $(srcdir)/src/handler.c $(srcdir)/src/handler-win32.c sigsegv.h config.h $(CC) $(CFLAGS) $(INCLUDES) -c $(srcdir)/src/handler.c dispatcher.obj : $(srcdir)/src/dispatcher.c sigsegv.h config.h $(CC) $(CFLAGS) $(INCLUDES) -c $(srcdir)/src/dispatcher.c version.obj : $(srcdir)/src/version.c sigsegv.h $(CC) $(CFLAGS) $(INCLUDES) -c $(srcdir)/src/version.c !if !$(DLL) sigsegv.lib : $(OBJECTS) $(RM) sigsegv.lib $(AR) $(AR_FLAGS)sigsegv.lib $(OBJECTS) !else # sigsegv.dll and sigsegv.lib are created together. sigsegv.lib : $(OBJECTS) $(CC) $(MFLAGS) -LD $(OBJECTS) -Fesigsegv.dll !endif sigsegv1.exe : $(srcdir)/tests/sigsegv1.c sigsegv.h sigsegv.lib $(CC) $(CFLAGS) $(INCLUDES) $(srcdir)/tests/sigsegv1.c sigsegv.lib /Fesigsegv1 sigsegv2.exe : $(srcdir)/tests/sigsegv2.c sigsegv.h sigsegv.lib $(CC) $(CFLAGS) $(INCLUDES) $(srcdir)/tests/sigsegv2.c sigsegv.lib /Fesigsegv2 stackoverflow1.exe : $(srcdir)/tests/stackoverflow1.c sigsegv.h sigsegv.lib $(CC) $(CFLAGS) $(INCLUDES) $(srcdir)/tests/stackoverflow1.c sigsegv.lib /Festackoverflow1 stackoverflow2.exe : $(srcdir)/tests/stackoverflow2.c sigsegv.h sigsegv.lib $(CC) $(CFLAGS) $(INCLUDES) $(srcdir)/tests/stackoverflow2.c sigsegv.lib /Festackoverflow2 check : all sigsegv1.exe sigsegv2.exe stackoverflow1.exe stackoverflow2.exe sigsegv1.exe sigsegv2.exe stackoverflow1.exe stackoverflow2.exe mostlyclean : clean clean : force $(RM) sigsegv.h *.obj *.lib *.exp *.dll core $(RM) sigsegv1.exe sigsegv2.exe stackoverflow1.exe stackoverflow2.exe distclean : clean $(RM) config.status config.log config.cache Makefile config.h maintainer-clean : distclean force : smalltalk-3.2.5/scripts/0000755000175000017500000000000012130456010012165 500000000000000smalltalk-3.2.5/scripts/Profile.st0000644000175000017500000000752312123404352014070 00000000000000"====================================================================== | | GNU Smalltalk profiling tool | | ======================================================================" "====================================================================== | | Copyright 2009 Free Software Foundation, Inc. | Written by Paolo Bonzini. | | This file is part of GNU Smalltalk. | | GNU Smalltalk is free software; you can redistribute it and/or modify it | under the terms of the GNU General Public License as published by the Free | Software Foundation; either version 2, or (at your option) any later version. | | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS | FOR A PARTICULAR PURPOSE. See the GNU General Public License for more | details. | | You should have received a copy of the GNU General Public License along with | GNU Smalltalk; see the file COPYING. If not, write to the Free Software | Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. | ======================================================================" PackageLoader fileInPackage: 'ProfileTools'. DLD addLibrary: 'libc'. SystemDictionary extend [ SmalltalkArgv := OrderedCollection new. ] | helpString output profiler profilerClass last | commands := OrderedCollection new. output := nil. profilerClass := CallGraphProfiler. helpString := 'Usage: gst-profile [ flag ... ] [FILE ARGS] Options: -f --file=FILE file in FILE -e --eval=CODE evaluate CODE -o --output=FILE output file for callgrind_annotate -h --help show this message -v --verbose print extra information while processing --no-separate-blocks do not track blocks separately --version print version information and exit FILE is always parsed, even if --file or --eval are used. It is also always parsed last. Use /dev/null to pass arguments directly to --file or --eval options. '. "Parse the command-line arguments." [Smalltalk arguments: '-f|--file: -e|--eval: -o|--output: -h|--help --version --no-separate-blocks -v|-V|--verbose' do: [ :opt :arg | opt = 'help' ifTrue: [ helpString displayOn: stdout. ObjectMemory quit: 0 ]. opt = 'no-separate-blocks' ifTrue: [ profilerClass := MethodCallGraphProfiler ]. opt = 'version' ifTrue: [ ('gst-profile - %1' % {Smalltalk version}) displayNl. ObjectMemory quit: 0 ]. opt = 'output' ifTrue: [ output isNil ifFalse: [ self error: 'multiple output files' ]. output := arg ]. opt = 'file' ifTrue: [ commands add: (File name: arg) ]. opt = 'eval' ifTrue: [ commands add: arg ]. opt = 'verbose' ifTrue: [ OutputVerbosity := 1. FileStream verbose: true ]. opt isNil ifTrue: [ last isNil ifTrue: [ last := arg ] ifFalse: [ SystemDictionary.SmalltalkArgv addLast: arg ] ]. ] ifError: [ helpString displayOn: stderr. ObjectMemory quit: 1 ]. last isNil ifFalse: [ commands add: (File name: last) ]. commands isEmpty ifTrue: [ self error: 'no commands given' ] ] on: Error do: [ :ex | ('gst-profile: ', ex messageText, ' ') displayOn: stderr. stderr flush. helpString displayOn: stderr. ObjectMemory quit: 1 ]. SystemDictionary compile: 'getpid [ ]'. SystemDictionary compile: 'arguments [ ^SmalltalkArgv asArray ]'. profiler := profilerClass new. output isNil ifTrue: [ output := Directory working / ('gst-profile.%1' % { Smalltalk getpid }) ]. commands do: [ :each | "Using #readStream makes it work both for Strings and Files. TODO: use hooks instead, maybe directly in Profiler?." profiler withProfilerDo: [ each readStream fileIn ] ]. profiler printCallGraphToFile: output. smalltalk-3.2.5/scripts/Finish.st0000644000175000017500000000375312123404352013711 00000000000000"====================================================================== | | Smalltalk installation finishing touches (utility script) | | ======================================================================" "====================================================================== | | Copyright 2002, 2008 Free Software Foundation, Inc. | Written by Paolo Bonzini. | | This file is part of GNU Smalltalk. | | GNU Smalltalk is free software; you can redistribute it and/or modify it | under the terms of the GNU General Public License as published by the Free | Software Foundation; either version 2, or (at your option) any later version. | | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS | FOR A PARTICULAR PURPOSE. See the GNU General Public License for more | details. | | You should have received a copy of the GNU General Public License along with | GNU Smalltalk; see the file COPYING. If not, write to the Free Software | Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. | ======================================================================" "Invoked as Finish.st PKGDATADIR IMAGEDIR [MODULES]..." | ok | ok := false. [ PackageLoader fileInPackages: Smalltalk arguments allButFirst. ok := true ] valueWithUnwind. ok ifFalse: [ ObjectMemory quit: 1 ]! "Symbol rebuildTable." Eval [ thisContext method stripSourceCode. "Remove DESTDIR and references to the build directory, from the paths stored in the image" ImageFileName := 'gst.im'. ImageFilePath := Smalltalk arguments first. ExecutableFileName := nil. UserFileBasePath := nil. "The image is built using the uninstalled executable (the installed executable does not work if DESTDIR is in effect and the package is no relocatable!). So, FileSegment>>#relocate does not necessarily set this to nil." KernelFilePath := nil. PackageLoader flush ] smalltalk-3.2.5/scripts/Remote.st0000644000175000017500000002172612123404352013724 00000000000000"====================================================================== | | GNU Smalltalk remote control script | | ======================================================================" "====================================================================== | | Copyright 2008, 2009 Free Software Foundation, Inc. | Written by Paolo Bonzini and Mike Anderson. | | This file is part of GNU Smalltalk. | | GNU Smalltalk is free software; you can redistribute it and/or modify it | under the terms of the GNU General Public License as published by the Free | Software Foundation; either version 2, or (at your option) any later version. | | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS | FOR A PARTICULAR PURPOSE. See the GNU General Public License for more | details. | | You should have received a copy of the GNU General Public License along with | GNU Smalltalk; see the file COPYING. If not, write to the Free Software | Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. | ======================================================================" PackageLoader fileInPackage: 'TCP'. DLD addLibrary: 'libc'. (CFunctionDescriptor isFunction: 'getpid') ifTrue: [ SystemDictionary compile: ' getpid [ ]' ] ifFalse: [ SystemDictionary compile: ' getpid [ ^''--pid not available'' ]' ]. Object subclass: RemoteServer [ RemoteServer class >> new [ ^ super new initialize; yourself ] | remoteProcess queue | initialize [ ObjectMemory addDependent: self ] update: aSymbol [ aSymbol == #aboutToSnapshot ifTrue: [ ^ remoteProcess suspend ]. aSymbol == #finishedSnapshot ifTrue: [ ^ remoteProcess resume ]. aSymbol == #returnFromSnapshot ifTrue: [ ObjectMemory removeDependent: self ]. ] process: aProcess [ remoteProcess := aProcess ] socket: aSocket [ queue := aSocket ] fork [ remoteProcess := [ [ [ queue waitForConnection. queue accept ifNotNil: [:conn | self forkClient: conn]. queue isOpen. ] whileTrue: [ Processor yield ]. ] on: Error do: [ :ex | ('gst-remote server: ', ex messageText, ' ') displayOn: stderr. ex pass. ObjectMemory quit: 1 ]. ] fork. ] forkClient: conn [ [ [[ Transcript register: conn. [ conn isPeerAlive ] whileTrue: [ Behavior evaluate: (conn upTo: $<0>) to: nil ifError: [ :fname :line :msg | conn nextPutAll: ('gst-remote: error at line %1: %2 ' % { line. msg }) ]. conn nextPut: $<0>; flush ] ] on: Error do: [ :ex | ex return ]] ensure: [ Transcript unregister. conn close ] ] fork ] ] TextCollector subclass: MultiplexingTextCollector [ | default outputs | initialize [ outputs := LookupTable new. super initialize ] register: aStream [ semaphore critical: [ outputs at: Processor activeProcess put: aStream ] ] unregister [ semaphore critical: [ outputs removeKey: Processor activeProcess ifAbsent: [] ] ] primNextPutAll: aString [ | dest | dest := outputs at: Processor activeProcess ifAbsent: [ nil ]. dest isNil ifFalse: [ [ dest nextPutAllFlush: aString ] ifCurtailed: [ self unregister. Processor activeProcess terminate ] ] ifTrue: [ super primNextPutAll: aString ]. ] ] | helpString commands server port host login remoteServer | commands := OrderedCollection new. server := false. port := 12345. host := nil. login := nil. helpString := 'Usage: gst-remote [ flag ... ] [user@]host Options: --daemon start background server --server start daemon -p --port=PORT connect/listen on given port (default 12345) -f --file=FILE file in FILE -e --eval=CODE evaluate CODE -l --login=USER use remote ssh connection --kill kill daemon --snapshot[=FILE] save image --package=PACKAGE load package --start=PACKAGE[:DATA] load package and start it (defined in package.xml) --stop=PACKAGE[:DATA] load package and stop it (defined in package.xml) --pid print daemon pid -h --help show this message -v --verbose print extra information while processing --version print version information and exit If a remote login name is given, gst-remote will use the SSH environment variable (if present) to launch commands remotely. Netcat (nc) should be available in the PATH of the remote machine. '. "Parse the command-line arguments." [Smalltalk arguments: '-h|--help --version --daemon --server -p|--port: -f|--file: -e|--eval: --pid --kill --snapshot:: --start: --stop: -l|--login: --package: -I|--image: --kernel-directory: -v|-V|--verbose' do: [ :opt :arg | opt = 'help' ifTrue: [ helpString displayOn: stdout. ObjectMemory quit: 0 ]. opt = 'version' ifTrue: [ ('gst-remote - %1' % {Smalltalk version}) displayNl. ObjectMemory quit: 0 ]. opt = 'login' ifTrue: [ login isNil ifFalse: [ self error: 'multiple logins are invalid' ]. login := arg ]. opt = 'daemon' ifTrue: [ server := true ]. opt = 'server' ifTrue: [ server := true ]. opt = 'port' ifTrue: [ port := arg asInteger ]. opt = 'start' ifTrue: [ | package data | package := arg copyUpTo: $:. package = arg ifTrue: [ commands add: '(PackageLoader packageAt: %1) start' % {package storeString} ] ifFalse: [ commands add: '(PackageLoader packageAt: %1) start: %2' % {package storeString. (arg copyAfter: $:) storeString } ] ]. opt = 'stop' ifTrue: [ | package data | package := arg copyUpTo: $:. package = arg ifTrue: [ commands add: '(PackageLoader packageAt: %1) stop' % {package storeString} ] ifFalse: [ commands add: '(PackageLoader packageAt: %1) stop: %2' % {package storeString. (arg copyAfter: $:) storeString } ] ]. opt = 'file' ifTrue: [ commands add: (File name: arg) ]. opt = 'package' ifTrue: [ commands add: 'PackageLoader fileInPackage: %1' % {arg storeString} ]. opt = 'eval' ifTrue: [ commands add: arg ]. opt = 'pid' ifTrue: [ commands add: 'Smalltalk getpid displayNl' ]. opt = 'kill' ifTrue: [ commands add: 'Transcript nextPut: $<0>. ObjectMemory quit: 0' ]. opt = 'snapshot' ifTrue: [ arg isNil ifTrue: [ commands add: 'ObjectMemory snapshot' ] ifFalse: [ commands add: 'ObjectMemory snapshot: ', (Directory working / arg) name storeString ] ]. opt = 'verbose' ifTrue: [ OutputVerbosity := 1. FileStream verbose: true ]. opt isNil ifTrue: [ host isNil ifFalse: [ self error: 'multiple hosts are invalid' ]. (arg includes: $@) ifFalse: [ host := arg ] ifTrue: [ login isNil ifFalse: [ self error: 'multiple logins are invalid' ]. login := arg copyUpTo: $@. host := arg copyAfter: $@ ]. (TCP.SocketAddress byName: host) ifNil: [ self error: 'invalid host %1' %{host} ] ifNotNil: [ :addr | host := addr ] ]. ] ifError: [ helpString displayOn: stderr. ObjectMemory quit: 1 ]. ] on: Error do: [ :ex | ('gst-remote: ', ex messageText, ' ') displayOn: stderr. stderr flush. "ex pass." helpString displayOn: stderr. ObjectMemory quit: 1 ]. server ifTrue: [ PackageLoader fileInPackage: 'Compiler'. Transcript := MultiplexingTextCollector message: Transcript message. remoteServer := RemoteServer new. remoteServer socket: (TCP.ServerSocket port: port bindTo: host). remoteServer fork. Transcript nextPutAll: 'gst-remote server started.'; nl ]. [ commands isEmpty ifFalse: [ s := (login isNil or: [ host isNil ]) ifTrue: [ host isNil ifTrue: [ host := TCP.IPAddress anyLocalAddress ]. TCP.Socket remote: host port: port ] ifFalse: [ FileStream popen: '%1 %2@%3 nc localhost %4' % { (Smalltalk getenv: 'SSH') ifNil: [ 'ssh' ]. login. host. port} dir: 'r+' ]. commands do: [ :each | "Using #readStream makes it work both for Strings and Files." s nextPutAll: each readStream; nextPut: $<0>; flush. [s canRead ifFalse: [stdout flush]. s atEnd or: [s peekFor: $<0>]] whileFalse: [stdout nextPut: s next]]. s close ] ] on: Error do: [ :ex || msg | stdout flush. msg := (s notNil and: [ s isPeerAlive not ]) ifTrue: [ 'server unavailable' ] ifFalse: [ ex messageText ]. ('gst-remote: ', msg, ' ') displayOn: stderr. stderr flush. s isNil ifFalse: [ s close ]. "ex pass." server ifFalse: [ ObjectMemory quit: 1 ] ]. server ifTrue: [ Processor activeProcess suspend ] ifFalse: [ ObjectMemory quit ] smalltalk-3.2.5/scripts/Convert.st0000644000175000017500000004232312123404352014105 00000000000000"====================================================================== | | Smalltalk syntax conversion tool | | ======================================================================" "====================================================================== | | Copyright 2007, 2008, 2009 Free Software Foundation, Inc. | Written by Daniele Sciascia. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" PackageLoader fileInPackage: #Parser. STInST.OldSyntaxExporter class extend [ emitEval: aBlock to: aStream for: namespace [ namespace isNil ifFalse: [ aStream nextPutAll: 'Namespace current: '; store: namespace; nextPut: $!; nl ]. aBlock value. aStream nextPut: $!; nl; nl. ] ] STInST.SqueakSyntaxExporter class extend [ emitEval: aBlock to: aStream for: namespace [ aBlock value. aStream nextPut: $!; nl; nl. ] ] STInST.NewSyntaxExporter class extend [ emitEval: aBlock to: aStream for: namespace [ namespace isNil ifTrue: [ aStream nextPutAll: 'Eval' ] ifFalse: [ aStream nextPutAll: 'Namespace current: '; store: namespace ]. aStream nextPutAll: ' ['. aBlock value. aStream nl; nextPut: $]; nl; nl. ] ] Object subclass: EmittedEntity [ emitTo: aStream filteredBy: aBlock [ self subclassResponsibility ] ] EmittedEntity subclass: EmittedComments [ | comments | EmittedComments class >> comments: aCollection source: aString [ ^self new comments: (aCollection collect: [ :c | aString copyFrom: c first to: c last ]) ] emitTo: outStream filteredBy: aBlock [ comments do: [ :c | STInST.FileOutExporter defaultExporter fileOutComment: c to: outStream. outStream nl; nl] ] comments: anArray [ comments := anArray ] ] EmittedEntity subclass: EmittedClass [ | class methodsToEmit classMethodsToEmit isComplete | EmittedClass class >> forClass: aClass [ (aClass superclass notNil and: [ aClass superclass isDefined not ]) ifTrue: [ Warning signal: ('superclass %1 is undefined' % {aClass superclass}) ]. ^super new initializeWithClass: aClass complete: true ] EmittedClass class >> forExtension: aClass [ aClass isDefined ifFalse: [ Warning signal: ('extensions for undefined class %1' % {aClass}) ]. ^super new initializeWithClass: aClass complete: false ] initializeWithClass: aClass complete: aBoolean [ class := aClass. methodsToEmit := STInST.OrderedSet new. classMethodsToEmit := STInST.OrderedSet new. isComplete := aBoolean ] forClass [ ^class ] addMethod: aMethod [ methodsToEmit add: aMethod selector asSymbol. ] addClassMethod: aMethod [ classMethodsToEmit add: aMethod selector asSymbol. ] emitTo: aStream filteredBy: aBlock [ (aBlock value: class) ifFalse: [ Notification signal: ('Skipping %1' % {class}). ^self ]. Notification signal: ('Converting %1...' % {class}). (STInST.FileOutExporter defaultExporter on: class to: aStream) completeFileOut: isComplete; fileOutSelectors: methodsToEmit classSelectors: classMethodsToEmit. ] ] EmittedEntity subclass: EmittedEval [ | statements comments namespace | EmittedEval class >> new [ ^super new initialize ] initialize [ statements := OrderedCollection new ] namespace [ ^namespace ] namespace: aNamespace [ namespace := aNamespace ] addStatement: aStatement [ statements add: aStatement ] emitTo: aStream filteredBy: aBlock [ statements isEmpty ifTrue: [ ^self ]. STInST.FileOutExporter defaultExporter emitEval: [ | formatter | formatter := STInST.RBFormatter new. formatter indent: 1 while: [ formatter indent. aStream nextPutAll: (formatter formatAll: statements) ]] to: aStream for: namespace. ] ] STInST.STClassLoader subclass: SyntaxConverter [ | stuffToEmit classesToEmit createdNamespaces filter outStream rewriter | SyntaxConverter class >> convertSqueakStream: in to: out [ ^self convertStream: in with: STInST.SqueakFileInParser to: out ] SyntaxConverter class >> convertSIFStream: in to: out [ ^self convertStream: in with: STInST.SIFFileInParser to: out ] SyntaxConverter class >> convertStream: in to: out [ ^self convertStream: in with: STInST.STFileInParser to: out ] SyntaxConverter class >> convertStream: in with: aParserClass to: out [ ^self new convertStream: in with: aParserClass to: out ] initialize [ super initialize. filter := [ :class | [true] ]. stuffToEmit := OrderedSet new. classesToEmit := Dictionary new. createdNamespaces := OrderedSet new. ] convertStream: in with: aParserClass to: out onError: aBlock [ self outStream: out; parseSmalltalkStream: in with: aParserClass onError: aBlock; doEmitStuff. ] convertStream: in with: aParserClass to: out [ self outStream: out; parseSmalltalkStream: in with: aParserClass; doEmitStuff. ] filter: aBlock [ filter := aBlock. ] outStream: out [ outStream := out. ] rewrite: node [ ^rewriter isNil ifTrue: [ node ] ifFalse: [ rewriter executeTree: node; tree ]. ] evaluate: node [ | rewritten | rewritten := self rewrite: node. node comments isEmpty ifFalse: [ stuffToEmit add: (EmittedComments comments: node comments source: node source) ]. ^super evaluate: rewritten ] addRule: searchString parser: aParserClass [ | tree rule | tree := aParserClass parseRewriteExpression: searchString. tree isMessage ifFalse: [ self error: 'expected ->' ]. tree selector = #-> ifFalse: [ self error: 'expected ->' ]. rule := RBStringReplaceRule searchForTree: tree receiver replaceWith: tree arguments first. rewriter isNil ifTrue: [ rewriter := ParseTreeRewriter new ]. rewriter addRule: rule ] compile: node [ | rewritten method | rewritten := self rewrite: node. method := self defineMethod: rewritten. (classesToEmit includesKey: currentClass asClass) ifTrue: [ self addMethod: method toLoadedClass: currentClass ] ifFalse: [ self addMethod: method toExtensionClass: currentClass ]. ^method ] lastEval [ | lastIsEval evalNamespace | evalNamespace := currentNamespace = self defaultNamespace ifTrue: [ nil ] ifFalse: [ currentNamespace ]. lastIsEval := stuffToEmit notEmpty and: [ (stuffToEmit last isKindOf: EmittedEval) and: [ stuffToEmit last namespace = evalNamespace ]]. ^lastIsEval ifTrue: [ stuffToEmit last ] ifFalse: [ stuffToEmit add: (EmittedEval new namespace: evalNamespace) ] ] createNamespaces [ createdNamespaces do: [ :each || stmt | stmt := RBMessageNode receiver: (RBVariableNode named: (each superspace nameIn: self currentNamespace)) selector: #addSubspace: arguments: { RBLiteralNode value: each name asSymbol }. self lastEval addStatement: stmt ]. createdNamespaces := OrderedSet new ] unknown: node [ self createNamespaces. self lastEval addStatement: node. ^false ] doSubclass: receiver selector: selector arguments: argumentNodes [ | class emittedClass | createdNamespaces remove: self currentNamespace ifAbsent: [ ]. self createNamespaces. class := super defineSubclass: receiver selector: selector arguments: argumentNodes. Notification signal: ('Parsing %1' % {class}). emittedClass := EmittedClass forClass: class. classesToEmit at: class put: emittedClass. stuffToEmit add: emittedClass. ^false ] doAddNamespace: receiver selector: selector arguments: argumentNodes [ | ns | super doAddNamespace: receiver selector: selector arguments: argumentNodes. ns := (self resolveNamespace: receiver) at: argumentNodes first value. createdNamespaces add: ns. ^false ] doEmitStuff [ stuffToEmit do: [ :each | each emitTo: outStream filteredBy: filter ] separatedBy: [ outStream nl; nextPut: 12 asCharacter; nl ]. ] addMethod: aMethod toLoadedClass: aClass [ (aClass isMetaclass) ifTrue: [ (classesToEmit at: currentClass asClass) addClassMethod: aMethod ] ifFalse: [ (classesToEmit at: currentClass) addMethod: aMethod ] ] addMethod: aMethod toExtensionClass: aClass [ ((stuffToEmit size > 0) and: [ (stuffToEmit last isKindOf: EmittedClass) and: [ stuffToEmit last forClass = aClass ] ]) ifTrue: [ stuffToEmit last addMethod: aMethod ] ifFalse: [ stuffToEmit add: ((EmittedClass forExtension: currentClass) addMethod: aMethod) ] ] ] String extend [ asFilterOn: aBlock through: valueBlock [ | regex | self first = $+ ifTrue: [ regex := self allButFirst asRegex. ^[ :obj | (aBlock value: obj) or: [ (valueBlock value: obj) ~ regex ] ] ]. self first = $- ifTrue: [ regex := self allButFirst asRegex. ^[ :obj | (aBlock value: obj) and: [ ((valueBlock value: obj) ~ regex) not ] ] ]. regex := self asRegex. ^[ :obj | (aBlock value: obj) and: [ (valueBlock value: obj) ~ regex ] ] ] ] Eval [ | helpString inFile outFile quiet verbose converter filter parser args inFormats outFormats rules | args := OrderedCollection new. parser := STInST.STFileInParser. quiet := false. verbose := false. outFile := nil. filter := [ :class | true ]. converter := SyntaxConverter new. STInST.FileOutExporter defaultExporter: STInST.FormattingExporter. outFormats := Dictionary from: { 'gst2' -> STInST.OldSyntaxExporter. 'gst' -> STInST.FormattingExporter. 'squeak' -> STInST.SqueakSyntaxExporter. }. inFormats := Dictionary from: { 'gst2' -> STInST.STFileInParser. 'gst' -> STInST.GSTFileInParser. 'squeak' -> STInST.SqueakFileInParser. 'sif' -> STInST.SIFFileInParser }. rules := OrderedCollection new. helpString := 'Usage: gst-convert [OPTION]... [INFILE [OUTFILE]] gst-convert [OPTION]... -o|--output OUTFILE INFILES Options: -q, --quiet don''t show any message -v, --verbose print extra information while processing -f, --format=FORMAT convert from given input format (supported formats are %1) -F, --output-format=FORMAT convert to given output format (supported formats are %2) -C, --class=REGEX convert only classes matching REGEX -C, --class=+REGEX in addition, convert classes matching REGEX -C, --class=-REGEX do not convert classes matching REGEX -c, --category=REGEX convert only classes whose category matches REGEX -c, --category=+REGEX in addition, convert those whose category matches REGEX -c, --category=-REGEX do not convert classes whose category matches REGEX -r, --rule=''CODE->REPL'' look for CODE and replace it with REPL -o, --output OUTFILE concatenate multiple input files into a single converted output file --help display this message and exit --version print version information and exit ' % {inFormats keys asSortedCollection fold: [ :a :b | a, ', ', b ]. outFormats keys asSortedCollection fold: [ :a :b | a, ', ', b ]}. Smalltalk arguments: '-h|--help --version -q|--quiet -v|-V|--verbose -r|--rule: -C|--class: -c|--category: -f|--format: -o|--output: -F|--output-format: -I|--image-file: --kernel-directory:' do: [ :opt :arg | opt = 'help' ifTrue: [ helpString displayOn: stdout. ObjectMemory quit: 0 ]. opt = 'version' ifTrue: [ ('gst-convert - %1' % {Smalltalk version}) displayNl. ObjectMemory quit: 0 ]. opt = 'quiet' ifTrue: [ quiet := true. verbose := false ]. opt = 'verbose' ifTrue: [ quiet := false. verbose := true ]. opt = 'output' ifTrue: [ outFile isNil ifFalse: [ helpString displayOn: stderr. ObjectMemory quit: 1 ]. outFile := arg ]. opt = 'rule' ifTrue: [ rules add: arg]. opt = 'class' ifTrue: [ [ 'a' ~ arg ] on: Error do: [ :ex | helpString displayOn: stderr. ObjectMemory quit: 1 ]. filter := arg asFilterOn: filter through: [ :class | class asClass nameIn: Smalltalk ] ]. opt = 'category' ifTrue: [ [ 'a' ~ arg ] on: Error do: [ :ex | helpString displayOn: stderr. ObjectMemory quit: 1 ]. filter := arg asFilterOn: filter through: [ :class | class category ifNil: [ '' ] ] ]. opt = 'output-format' ifTrue: [ STInST.FileOutExporter defaultExporter: (outFormats at: arg ifAbsent: [ helpString displayOn: stderr. ObjectMemory quit: 1 ]) ]. opt = 'format' ifTrue: [ parser := inFormats at: arg ifAbsent: [ helpString displayOn: stderr. ObjectMemory quit: 1 ] ]. opt isNil ifTrue: [ args addLast: arg ]. ] ifError: [ helpString displayOn: stderr. ObjectMemory quit: 1 ]. "Post process the rules now we know the target." rules do: [:rule | converter addRule: rule parser: parser]. [ outFile isNil ifTrue: [ args size > 2 ifTrue: [ helpString displayOn: stderr. ObjectMemory quit: 1 ]. inFile := (args size = 0 or: [ args first = '-' ]) ifTrue: [ stdin ] ifFalse: [ FileStream open: args first mode: FileStream read ]. outFile := (args size <= 1 or: [ args last = '-' ]) ifTrue: [ stdout ] ifFalse: [ FileStream open: args last mode: FileStream write ] ] ifFalse: [ args := args collect: [ :f | f = '-' ifTrue: [ stdin ] ifFalse: [ FileStream open: f mode: FileStream read ] ]. inFile := args fold: [ :a :b | a, b ]. outFile := outFile = '-' ifTrue: [ stdout ] ifFalse: [ FileStream open: outFile mode: FileStream write ] ]. converter filter: filter. converter convertStream: inFile with: parser to: outFile. inFile close. outFile close ] on: Notification do: [ :ex | verbose ifTrue: [ stderr nextPutAll: 'gst-convert: ', ex messageText; nl; flush ]. ex resume ] on: Warning do: [ :ex | quiet ifFalse: [ stderr nextPutAll: 'gst-convert: warning: ', ex messageText; nl; flush ]. ex resume ] on: Error do: [ :ex | stderr nextPutAll: 'gst-convert: error: ', ex messageText; nl; flush. outFile = stdout ifFalse: [ outFile close. "TODO: don't do this on non-regular files. It will make /dev/null disappear if you run gst-convert as root (which you shouldn't)." [ (File name: outFile name) remove ] on: Error do: [ :ex | ] ]. "ex pass." ObjectMemory quit: 1 ]. ] smalltalk-3.2.5/scripts/GenDoc.st0000644000175000017500000001356512123404352013632 00000000000000"====================================================================== | | Smalltalk documentation publisher (utility script) | | ======================================================================" "====================================================================== | | Copyright 2003, 2004, 2005, 2007, 2008, 2009 Free Software Foundation, Inc. | Written by Paolo Bonzini. | | This file is part of GNU Smalltalk. | | GNU Smalltalk is free software; you can redistribute it and/or modify it | under the terms of the GNU General Public License as published by the Free | Software Foundation; either version 2, or (at your option) any later version. | | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS | FOR A PARTICULAR PURPOSE. See the GNU General Public License for more | details. | | You should have received a copy of the GNU General Public License along with | GNU Smalltalk; see the file COPYING. If not, write to the Free Software | Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. | ======================================================================" "Load the prerequisites" PackageLoader fileInPackage: #ClassPublisher! | package location publisher files classes classPatterns loader defaultNamespace warnings | classPatterns := OrderedCollection new. warnings := Set new. defaultNamespace := Smalltalk. helpString := 'Usage: gst-doc [ flag ... ] class ... Options: -I --image-file=FILE look for classes in the given image -p --package=PKG look for classes in the given package -f --file=FILE look for classes in the given file -n --namespace=NAMESP load files in the given namespace -o --output=FILE emit documentation in the given file (default=stdout) --kernel-dir=PATH use the specified kernel directory -F --output-format=KIND use the given publisher (HTML or default=Texinfo) -h --help show this message -v --verbose print extra information while processing --version print version information and exit '. [ loader := STInST.STClassLoader new. Namespace current: Smalltalk. "Parse the command-line arguments." Smalltalk arguments: '-h|--help --version -p|--package: -f|--file: -n|--namespace: -I|--image-file: -o|--output: --kernel-directory: -F|--output-format: -v|-V|--verbose' do: [ :opt :arg | opt = 'help' ifTrue: [ helpString displayOn: stdout. ObjectMemory quit: 0 ]. opt = 'version' ifTrue: [ ('gst-doc - %1' % {Smalltalk version}) displayNl. ObjectMemory quit: 0 ]. opt = 'output' ifTrue: [ location isNil ifFalse: [ self error: '--output specified multiple times' ]. location := arg ]. opt = 'namespace' ifTrue: [ defaultNamespace := Smalltalk. (arg subStrings: $.) do: [:each | | key | key := each asSymbol. (defaultNamespace includesKey: key) ifFalse: [defaultNamespace addSubspace: key]. defaultNamespace := defaultNamespace at: key]. loader currentNamespace: defaultNamespace ]. opt = 'package' ifTrue: [ package := PackageLoader packageAt: arg. loader currentNamespace: package createNamespace. files := package fullPathsOf: package fileIns. files do: [ :each | loader parseSmalltalkStream: each readStream with: STInST.GSTFileInParser ]. loader currentNamespace: defaultNamespace ]. opt = 'file' ifTrue: [ loader parseSmalltalkStream: arg asFile readStream with: STInST.GSTFileInParser ]. opt = 'output-format' ifTrue: [ publisher isNil ifFalse: [ self error: '--output-format specified multiple times' ]. arg asLowercase = 'html' ifTrue: [ publisher := STInST.HTMLDocPublisher ] ifFalse: [ arg asLowercase = 'texinfo' ifTrue: [ publisher:= STInST.TexinfoDocPublisher ] ifFalse: [ self error: 'unknown --output-format arg' ] ] ]. opt = 'verbose' ifTrue: [ OutputVerbosity := 1. FileStream verbose: true ]. opt isNil ifTrue: [ classPatterns add: arg ] ] ifError: [ helpString displayOn: stderr. ObjectMemory quit: 1 ]. publisher isNil ifTrue: [ publisher := STInST.TexinfoDocPublisher ]. classPatterns isEmpty ifTrue: [ classes := loader loadedClasses. classes isEmpty ifTrue: [ self error: 'specify -p, -f, or a class name' ] ] ifFalse: [ allClasses := loader loadedClasses, (Class allSubclasses collect: [ :each | each instanceClass ]). classes := IdentitySet new. classPatterns do: [ :pat || ns | (pat last: 2) = '.*' ifTrue: [ ns := pat allButLast: 2. classes addAll: (allClasses select: [ :each | (each environment nameIn: Smalltalk) = ns ]) ] ifFalse: [ classes addAll: (allClasses select: [ :each | pat match: (each nameIn: Smalltalk) ]) ] ] ]. location isNil ifTrue: [ Transcript message: stderr -> #nextPutAllFlush:. publisher publishAll: classes ] ifFalse: [ publisher publishAll: classes toLocation: location ] ] on: Warning do: [ :ex | (warnings includes: ex messageText) ifFalse: [ warnings add: ex messageText. ('gst-doc: warning: ', ex messageText, ' ') displayOn: Transcript ]. ex resume ] on: Error do: [ :ex | ('gst-doc: ', ex messageText, ' ') displayOn: stderr. "ex pass." ObjectMemory quit: 1 ]! smalltalk-3.2.5/scripts/Package.st0000644000175000017500000007670612123404352014034 00000000000000"====================================================================== | | Smalltalk package installer | | ======================================================================" "====================================================================== | | Copyright 2007, 2008, 2009 Free Software Foundation, Inc. | Written by Paolo Bonzini. | | This file is part of GNU Smalltalk. | | GNU Smalltalk is free software; you can redistribute it and/or modify it | under the terms of the GNU General Public License as published by the Free | Software Foundation; either version 2, or (at your option) any later version. | | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS | FOR A PARTICULAR PURPOSE. See the GNU General Public License for more | details. | | You should have received a copy of the GNU General Public License along with | GNU Smalltalk; see the file COPYING. If not, write to the Free Software | Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. | ======================================================================" [PackageLoader fileInPackage: 'NetClients'] on: Error do: [:ex | ex return]. DynamicVariable subclass: CurrentCommand [ ] Package extend [ srcdir [ ^self baseDirectories last ] isStarPackageBody [ ^self baseDirectories first isKindOf: VFS.ArchiveFile ] starFileName [ | dir | self isStarPackageBody ifFalse: [ self halt ]. ^self baseDirectories first asString ] runCommand: aCommand [ self isStarPackageBody ifTrue: [ aCommand runOnStar: self ] ifFalse: [ aCommand runOnPackage: self ] ] ] Kernel.PackageContainer subclass: StarPackageFile [ | name | StarPackageFile class >> on: aFile [ ^self new file: aFile; yourself ] StarPackageFile class >> on: aFile name: aString [ ^self new file: aFile; name: aString; yourself ] baseDirectoriesFor: aPackage [ ^self file zip ] name [ ^name ] name: aString [ name := aString ] refresh: loadDate [ | package | package := Kernel.StarPackage file: self file. name isNil ifFalse: [ package name: self name ]. self packages at: package name put: package loadedPackage ] ] Kernel.PackageContainer subclass: RemotePackageFile [ RemotePackageFile class >> on: aFile [ ^self new file: aFile; yourself ] testPackageValidity: package [ ] refresh: loadDate [ | file | self file withReadStreamDo: [ :fileStream | self parse: fileStream ] ] ] Kernel.PackageContainer subclass: PackageFile [ | srcdir | PackageFile class >> on: aFile [ ^self new file: aFile; yourself ] srcdir [ ^srcdir ] srcdir: aString [ srcdir := aString ] baseDirectoriesFor: aPackage [ | srcdirFile builddirPrefix | self srcdir isNil ifTrue: [ ^{ file path } ]. "See if the file is in srcdir or builddir. In any case, we want to look for files first in the builddir, and secondarily in srcdir." srcdirFile := self file pathFrom: self srcdir. builddirPrefix := Directory working pathFrom: self srcdir. ^(srcdirFile startsWith: builddirPrefix, Directory pathSeparatorString) ifFalse: [ { "file is in srcdir." (File name: srcdirFile) parent. self file parent } ] ifTrue: [ { "file is in builddir." self file parent. (self srcdir / (self file pathFrom: Directory working)) parent } ] ] refresh: loadDate [ | file | self file withReadStreamDo: [ :fileStream | self parse: fileStream ] ] ] DynamicVariable subclass: MainPackage [] Kernel.PackageContainer subclass: PackageCheckout [ | url checkoutDirectory | PackageCheckout class >> cacheRoot [ ^Directory userBase / 'cache' ] PackageCheckout class >> on: anURL [ ^self new url: anURL; yourself ] baseDirectoriesFor: aPackage [ | mainPackage | mainPackage := MainPackage value. mainPackage isNil ifTrue: [ ^{ self checkoutDirectory } ]. aPackage = mainPackage ifTrue: [ ^{ self checkoutDirectory } ]. ^{ mainPackage baseDirectories first / (aPackage name copyFrom: mainPackage name size + 2) } ] checkoutDirectory [ | dir name | checkoutDirectory isNil ifTrue: [ name := '%1__%2__%3' % { url scheme. url host. NetClients.URL encode: url path }. checkoutDirectory := self class cacheRoot / name ]. ^checkoutDirectory ] checkout [ self subclassResponsibility ] url [ ^url ] url: anURL [ url := anURL ] parseFile: aFile [ aFile withReadStreamDo: [ :fileStream | self parse: fileStream ] ] parse: aFileStream [ | addedPackages mainPackage | addedPackages := super parse: aFileStream. addedPackages size > 1 ifTrue: [ ^addedPackages ]. mainPackage := addedPackages first. MainPackage use: mainPackage during: [ mainPackage prerequisites do: [ :each || file | ((each startsWith: mainPackage name, '-') and: [ (file := mainPackage baseDirectories first / (each copyFrom: mainPackage name size + 2) / 'package.xml') exists ]) ifTrue: [ self parseFile: file ]]]. ^addedPackages ] refresh: loadDate [ self checkout. (self checkoutDirectory / 'package.xml') exists ifFalse: [ Command dryRun ifTrue: [^self]. ^self error: 'cannot find package.xml in checked out repository']. self file: self checkoutDirectory / 'package.xml'. self parseFile: self file. ] ] PackageCheckout subclass: SvnPackageCheckout [ checkout [ | realUrl command saveDir | self checkoutDirectory exists ifFalse: [ self checkoutDirectory emitMkdir. realUrl := url copy. url scheme = 'svn+http' ifTrue: [ realUrl scheme: 'http' ]. url host = '' ifTrue: [ realUrl := realUrl path ]. command := 'svn checkout %1 .' % {realUrl} ] ifTrue: [ command := 'svn update' ]. ('cd %1 && ' % { self checkoutDirectory }, command) displayNl. saveDir := Directory working. Command execute: [ Directory working: self checkoutDirectory. Smalltalk system: command ] ensure: [ Directory working: saveDir ] ] ] PackageCheckout subclass: GitPackageCheckout [ checkout [ | realUrl command saveDir | self checkoutDirectory exists ifFalse: [ self checkoutDirectory emitMkdir. realUrl := url copy. url scheme ~ 'git+(https?|rsync)' ifTrue: [ realUrl scheme: (url scheme copyFrom: 5) ]. url host = '' ifTrue: [ realUrl := realUrl path ]. command := 'git clone --depth 1 %1 .' % {realUrl} ] ifTrue: [ command := 'git pull' ]. ('cd %1 && ' % { self checkoutDirectory }, command) displayNl. saveDir := Directory working. Command execute: [ Directory working: self checkoutDirectory. Smalltalk system: command ] ensure: [ Directory working: saveDir ]. url fragment isNil ifFalse: [ command := 'git checkout origin/%1' % {url fragment}. ('cd %1 && ' % { self checkoutDirectory }, command) displayNl. Command execute: [ Directory working: self checkoutDirectory. Smalltalk system: command ] ensure: [ Directory working: saveDir ] ] ] ] Kernel.PackageDirectories subclass: PackageFiles [ | srcdir | parseStarFile: file [ ^(StarPackageFile on: file) refresh; yourself ] parseStarFile: file name: aString [ ^(StarPackageFile on: file name: aString) refresh; yourself ] parseXMLFile: file [ ^(PackageFile on: file) srcdir: self srcdir; refresh; yourself ] parse: fileName [ | file packageFile | file := File name: fileName. ^('*.star' match: fileName) ifFalse: [ self parseXMLFile: file ] ifTrue: [ self parseStarFile: file ] ] addURL: urlString [ | url localFile package found | url := NetClients.URL fromString: urlString. "Remote package.xml: download it to find the `real' URL." ('*.xml' match: url path) ifTrue: [ localFile := File name: url entity localFileName. package := RemotePackageFile on: localFile. package parse: url readStream. found := false. package packages do: [ :each | (each url notNil and: [each url notEmpty]) ifTrue: [ found := true. each url = urlString ifTrue: [ ^self error: 'infinite loop in package.xml urls' ]. self addURL: each url ]]. found ifTrue: [^self]. ^self error: 'url element not found in remote XML file' ]. "Remote .star file: download it and install." ('*.star' match: url path) ifTrue: [ ^self add: (self parseStarFile: (File name: url entity localFileName) name: (File stripPathFrom: (File stripExtensionFrom: url path))) ]. (url scheme ~ '^svn(\+|$)') ifTrue: [ ^self add: ((SvnPackageCheckout on: url) refresh; yourself) ]. (url scheme ~ '^git(\+|$)') ifTrue: [ ^self add: ((GitPackageCheckout on: url) refresh; yourself) ]. (url scheme ~ '^(https?|ftp|file)$') ifTrue: [ self error: 'invalid URL %1' % {url} ] ifFalse: [ self error: 'unknown protocol %1' % {url scheme} ] ] addFile: fileName [ self add: (self parse: fileName). ] filesDo: aBlock [ (dirs collect: [ :each | each fileName ]) asSet do: aBlock ] srcdir [ ^srcdir ] srcdir: aString [ srcdir := aString ] ] File extend [ emitZipDir: dir [ | saveDir | self emitRemove. ('cd %1 && %2 -n .st:.xml -qr %3 .' % { dir. Command zip. self }) displayNl. saveDir := Directory working. Command execute: [ Directory working: dir name. Smalltalk system: '%1 -n .st:.xml -qr %2 .' withArguments: { Command zip. self } ] ensure: [ Directory working: saveDir ] ] emitRemove [ ('rm -f %1' % { self }) displayNl. Command execute: [ self exists ifTrue: [ self remove ] ]. ] emitSymlink: dest [ | destFile | ('%1 -f %2 %3' % { Command symLink. self. dest }) displayNl. Command execute: [ destFile := File name: dest. destFile exists ifTrue: [ destFile remove ]. destFile symlinkFrom: self name ]. ] emitInstall: dest [ | destFile srcStream destStream mode | mode := self isExecutable ifTrue: [ 8r755 ] ifFalse: [ 8r644 ]. destFile := File name: dest. ('%1 -m %2 %3 %4' % { Command install. mode printString: 8. self. destFile }) displayNl. Command execute: [ destFile exists ifTrue: [ destFile remove ]. srcStream := self readStream. destStream := destFile writeStream. destStream nextPutAll: srcStream. ] ensure: [ destStream isNil ifFalse: [ destStream close ]. srcStream isNil ifFalse: [ srcStream close ]. destFile mode: mode ]. ] emitMkdir [ | doThat | self exists ifTrue: [ ^self ]. Command execute: [ self parent emitMkdir ]. ('mkdir %1' % { self }) displayNl. Command execute: [ Directory create: self name ]. ] ] Object subclass: Command [ | installDir options | Command class >> selectionOptions [ ^#() ] Command class >> current [ ^CurrentCommand value ] Command class >> execute: aBlock [ self dryRun ifFalse: [ aBlock value ] ] Command class >> execute: aBlock ensure: ensureBlock [ self dryRun ifFalse: [ aBlock ensure: ensureBlock ] ] Command class >> dryRun [ ^self current isOption: 'dry-run' ] Command class >> zip [ ^(Smalltalk getenv: 'XZIP') ifNil: [ 'zip' ] ] Command class >> install [ ^(Smalltalk getenv: 'INSTALL') ifNil: [ 'install' ] ] Command class >> symLink [ ^(Smalltalk getenv: 'LN_S') ifNil: [ 'ln -s' ] ] options [ | optionsCollection | optionsCollection := OrderedCollection new. options keysDo: [ :opt | (options at: opt) do: [ :arg | optionsCollection add: opt->arg ]]. ^optionsCollection ] options: aCollection [ options := Dictionary new. aCollection do: [ :assoc | (options at: assoc key ifAbsentPut: [ OrderedCollection new ]) addLast: assoc value. (self isValidOption: assoc key) ifFalse: [ self error: ('--%1 invalid for this mode' % {assoc key}) ] ] ] isValidOption: aString [ ^#('srcdir' 'target-directory' 'destdir' 'image-file' 'dry-run' 'kernel-directory' 'verbose') includes: aString ] isOption: aString [ ^options includesKey: aString ] optionsAt: aString [ ^options at: aString ] optionAt: aString [ ^self optionAt: aString ifAbsent: [ nil ] ] optionAt: aString ifAbsent: aBlock [ | value | value := options at: aString ifAbsent: [ ^aBlock value ]. value size > 1 ifTrue: [ self error: '--%1 given multiple times' % {aString} ]. ^value first ] validateDestDir: destdir installDir: instDir [ instDir isNil ifTrue: [ ^self ]. (instDir asFile isAbsolute not and: [ destdir notEmpty ]) ifTrue: [ self error: '--destdir used with relative target directory' ] ] prolog [ | destdir instDir | destdir := self optionAt: 'destdir' ifAbsent: [ '' ]. instDir := self optionAt: 'target-directory' ifAbsent: [ nil ]. self validateDestDir: destdir installDir: instDir. installDir := File name: destdir, (instDir ifNil: [ self defaultInstallDir asString ]) ] defaultInstallDir [ ^Directory image ] installDir [ ^installDir ] defaultFiles [ ^#() ] runOnAll: args [ self subclassResponsibility ] executeOnAll: args [ CurrentCommand use: self during: [ | packageArgs | self prolog. packageArgs := args. packageArgs isEmpty ifTrue: [ packageArgs := self defaultFiles ]. packageArgs isEmpty ifTrue: [ self error: 'no packages given' ]. self runOnAll: packageArgs] ] ] Command subclass: PkgDownload [ PkgDownload class >> selectionOptions [ ^#('download') ] PkgDownload class >> urlBase [ ^'http://smalltalk.gnu.org/project' ] isValidOption: aString [ "Let PkgInstall decide later." ^true ] prolog [] runOnAll: args [ | urls | urls := args collect: [ :each || pkg url | pkg := PackageLoader packageAt: each ifAbsent: [ nil ]. url := pkg ifNotNil: [ pkg url ]. url ifNil: [ '%1/%2/package.xml' % { self class urlBase. each } ] ]. PkgInstall new options: self options; executeOnAll: urls ] ] Command subclass: PackageCommand [ | packages | buildPackages [ | srcdir | packages := PackageFiles new. srcdir := self optionAt: 'srcdir' ifAbsent: [ '.' ]. (srcdir = '.' or: [ (File fullNameFor: srcdir) = Directory working ]) ifTrue: [ srcdir := nil ]. packages srcdir: srcdir. ^packages ] packages [ packages isNil ifTrue: [ self buildPackages ]. ^packages ] srcdir [ ^self packages srcdir ifNil: [ '.' ] ] addFile: aString [ aString ~ '^[a-z+]*://' ifTrue: [ self handleURLs ifFalse: [ self error: 'URLs are not supported by this mode' ] ifTrue: [ self packages addURL: aString ] ] ifFalse: [ self packages addFile: aString ] ] handleURLs [ ^false ] run [ self packages do: [ :pkg | pkg runCommand: self ] ] runOnStar: aStarPackage [ self runOnPackage: aStarPackage ] runOnPackage: aPackage [ ] runOnAll: args [ args do: [ :each | self addFile: each ]. self run ] ] PackageCommand subclass: PkgDist [ PkgDist class >> selectionOptions [ ^#('dist') ] validateDestDir: destdir installDir: instDir [ (destdir isEmpty and: [ instDir isNil ]) ifTrue: [ self error: 'using --dist without specifying --distdir' ]. ] defaultInstallDir [ ^'' ] run [ super run. "Distribute package files, unless they are automatically generated from autoconf." packages filesDo: [ :each | | destName autoconfName srcdir | destName := File stripPathFrom: each. srcdir := self srcdir / (File pathFor: each). autoconfName := destName, '.in'. (srcdir includes: autoconfName) ifFalse: [ self distribute: (File name: each) as: destName in: nil ] ] ] isValidOption: aString [ (#('all-files' 'copy') includes: aString) ifTrue: [^true]. ^super isValidOption: aString ] distribute: srcFile as: file in: dir [ | destName baseDir | baseDir := self installDir. dir isNil ifFalse: [ baseDir := baseDir / dir ]. destName := baseDir nameAt: file. (self isOption: 'copy') ifTrue: [ srcFile emitInstall: destName ] ifFalse: [ srcFile emitSymlink: destName ] ] runOnPackage: aPackage [ | dirs files baseDir | files := (self isOption: 'all-files') ifTrue: [ aPackage allFiles ] ifFalse: [ aPackage allDistFiles ]. dirs := files collect: [ :file | File pathFor: file ]. dirs := dirs asSet remove: '' ifAbsent: [ ]; asSortedCollection. baseDir := self installDir. aPackage relativeDirectory isNil ifFalse: [ baseDir := baseDir / aPackage relativeDirectory ]. baseDir emitMkdir. dirs do: [ :dir | (baseDir / dir) emitMkdir ]. files do: [ :file || srcFile destName | srcFile := aPackage fullPathOf: file. self distribute: srcFile as: file in: aPackage relativeDirectory ] ] runOnStar: aPackage [ self error: 'cannot distribute sources from .star file' ] ] PackageCommand subclass: PkgInstall [ | tmpDir | isValidOption: aString [ (#('load' 'test') includes: aString) ifTrue: [^true]. ^super isValidOption: aString ] handleURLs [ ^true ] run [ "Create the installation directory." self installDir emitMkdir. [ super run ] ensure: [ tmpDir isNil ifFalse: [ tmpDir all remove ] ]. PackageLoader flush; refresh. (Command dryRun not and: [ self isOption: 'load' ]) ifTrue: [ ^self loadPackages ]. (self isOption: 'test') ifTrue: [ self runTests ] ] runTests [ "Run SUnit tests, used unless --load is given too." | script result | script := ''. self packages do: [ :each || pkg | pkg := each. script := script, ' ', pkg sunitScript. pkg test notNil ifTrue: [ pkg := pkg test. script := script, ' ', pkg sunitScript ]. pkg fileIn ]. (PackageLoader packageAt: #SUnit) loaded ifFalse: [ ^self ]. script isEmpty ifTrue: [ ^self ]. result := TestSuitesScripter run: script quiet: false verbose: false. result runCount = result passedCount ifFalse: [ ObjectMemory quit: 1 ] ] loadPackages [ "Call gst-load, needed because we added our code to the image." | gstPackage execDir gstLoad pat packageList | gstPackage := File executable. gstPackage stripPath = 'gst-tool' ifTrue: [ gstLoad := gstPackage. pat := '%1 gst-load -I %2 --kernel-directory %3 %4 %5' ] ifFalse: [ gstLoad := gstPackage directory / 'gst-load'. pat := '%1 -I %2 --kernel-directory %3 %4 %5' ]. packageList := ''. self packages do: [ :each | packageList := packageList, ' ', each name ]. Smalltalk system: pat withArguments: { gstLoad. File image. Directory kernel. (self isOption: 'test') ifTrue: [ '--test' ] ifFalse: [ '' ]. packageList } ] tmpDir [ tmpDir isNil ifTrue: [ tmpDir := Directory createTemporary: Directory temporary / 'gstar-'. ('mkdir %1' % { tmpDir }) displayNl ]. ^tmpDir ] runOnPackage: aPackage [ | pkg destFile dirs files baseDir | baseDir := self tmpDir / aPackage name. pkg := aPackage copy. pkg relativeDirectory: nil. baseDir emitMkdir. Command execute: [ (baseDir / 'package.xml') withWriteStreamDo: [ :s | pkg printOn: s ]. files := pkg allFiles. dirs := files collect: [ :file | File pathFor: file ]. (dirs asSet remove: '' ifAbsent: []; asSortedCollection) do: [ :dir | (baseDir / dir) emitMkdir ]. files do: [ :file || srcFile | srcFile := (aPackage fullPathOf: file). srcFile emitSymlink: (baseDir nameAt: file) ]. (self installDir / aPackage name, '.star') emitZipDir: baseDir ] ensure: [ baseDir all remove ]. ] runOnStar: aPackage [ | destFile | destFile := self installDir nameAt: aPackage name, '.star'. (File name: aPackage starFileName) emitInstall: destFile. ] ] PackageCommand subclass: PkgUninstall [ PkgUninstall class >> selectionOptions [ ^#('uninstall') ] run [ super run. packages filesDo: [ :each | (File name: each) emitRemove ] ] runOnPackage: aPackage [ | baseDir | baseDir := self installDir. aPackage relativeDirectory isNil ifFalse: [ baseDir := baseDir / aPackage relativeDirectory ]. aPackage allFiles do: [ :file | (baseDir / file) emitRemove ] ] runOnStar: aPackage [ ] ] PackageCommand subclass: ListCommand [ validateDestDir: destdir installDir: installDir [ destdir = '' ifFalse: [ self error: '--destdir not needed with --list-files' ]. installDir isNil ifFalse: [ self error: '--target-directory not needed with --list-files' ] ] defaultInstallDir [ ^'.' ] ] ListCommand subclass: PkgList [ PkgList class >> selectionOptions [ ^#('list-files' 'no-install') ] isValidOption: aString [ (#('list-files' 'vpath' 'load') includes: aString) ifTrue: [^true]. ^super isValidOption: aString ] run [ | base vpathBase vpath source test listFiles | super run. listFiles := self optionsAt: 'list-files'. vpath := self isOption: 'vpath'. source := self isOption: 'load'. test := self isOption: 'test'. base := self installDir. vpathBase := File name: self srcdir. listFiles do: [ :each || package files | package := self packages at: each. files := source ifFalse: [ package allFiles ] ifTrue: [ package fileIns ]. (test and: [ source and: [ package test notNil ]]) ifTrue: [ files := files, package test fileIns ]. files do: [ :file | | path relativePath | path := package fullPathOf: file. relativePath := base pathTo: path. (vpath and: [ (relativePath indexOfSubCollection: '../') > 0 ]) ifTrue: [ relativePath := vpathBase pathTo: path ]. relativePath displayNl ] ] ] ] ListCommand subclass: PkgPackageList [ PkgPackageList class >> selectionOptions [ ^#('list-packages') ] runOnPackage: aPackage [ aPackage name displayNl ] ] PackageCommand subclass: PkgPrepare [ | srcFile | PkgPrepare class >> selectionOptions [ ^#('prepare') ] validateDestDir: destdir installDir: installDir [ destdir = '' ifFalse: [ self error: '--destdir not needed with --prepare' ]. installDir isNil ifFalse: [ self error: '--target-directory not needed with --prepare' ] ] defaultFiles [ (File exists: self srcdir, '/package.xml') ifTrue: [ srcFile := 'package.xml' ]. (File exists: self srcdir, '/package.xml.in') ifTrue: [ srcFile := 'package.xml.in' ]. ^{ srcFile } ] addFile: aString [ | f | srcFile isNil ifTrue: [ f := self srcdir / aString. f exists ifTrue: [ srcFile := (File name: self srcdir) pathTo: f ]. f := f, '.in'. f exists ifTrue: [ srcFile := (File name: self srcdir) pathTo: f ]. (File exists: aString) ifTrue: [ srcFile := File name: aString ]. srcFile isNil ifTrue: [ self error: '%1 not found' % {srcFile} ] ]. super addFile: aString. ] run [ | base configureAC makefileAM gstIN | base := File name: self srcdir. configureAC := base at: 'configure.ac'. makefileAM := base at: 'Makefile.am'. gstIN := base at: 'gst.in'. configureAC exists ifFalse: [ 'creating configure.ac' displayNl. Command dryRun ifFalse: [ configureAC withWriteStreamDo: [ :ws | self writeConfigure: ws ] ] ]. gstIN exists ifFalse: [ 'creating gst.in' displayNl. Command dryRun ifFalse: [ gstIN withWriteStreamDo: [ :ws | self writeGstIn: ws ] ] ]. makefileAM exists ifFalse: [ 'creating Makefile.am' displayNl. Command dryRun ifFalse: [ makefileAM withWriteStreamDo: [ :ws | self writeMakefile: ws ] ] ] ] writeGstIn: ws [ ws nextPutAll: '#! /bin/sh abs_top_builddir=@abs_top_builddir@ : ${LIBTOOL=$abs_top_builddir/libtool} exec $LIBTOOL --mode=execute @PACKAGE_DLOPEN_FLAGS@ @GST@ ${1+"$@"} ' ] writeConfigure: ws [ | numPackages pkgName tarName | numPackages := 0. self packages do: [ :each | pkgName := each name. numPackages := numPackages + 1 ]. numPackages = 1 ifFalse: [ pkgName := 'XYZ' ]. tarName := 'gst-', (pkgName asLowercase copyReplacingAllRegex: '[-_ ]+' with: '-'). ws nextPutAll: ('AC_PREREQ(2.59) AC_INIT([GNU Smalltalk package %1], [0.0], , %2) AC_CONFIG_SRCDIR([%3]) AM_INIT_AUTOMAKE AM_PATH_GST([2.95c], , [AC_MSG_ERROR([GNU Smalltalk not found])]) ' % { pkgName. tarName. srcFile }). packages filesDo: [ :each | self writeConfigureEntry: each to: ws ]. ws nextPutAll: ' AC_CONFIG_FILES([Makefile]) AC_CONFIG_FILES([gst], [chmod +x gst]) AC_OUTPUT ' ] writeConfigureEntry: each to: ws [ | pkgName buildPath srcPath pkgSrcDir relPkgSrcDir generated | buildPath := Directory working pathTo: each. srcPath := (File name: self srcdir) pathTo: each. pkgSrcDir := srcPath size < buildPath size ifTrue: [ File pathFor: srcPath ifNone: [ self srcdir ] ] ifFalse: [ File append: (File pathFor: buildPath) to: self srcdir ]. relPkgSrcDir := (File name: self srcdir) pathTo: pkgSrcDir. ('*.in' match: each) ifTrue: [ srcPath := srcPath allButLast: 3. buildPath := buildPath allButLast: 3. generated := true ] ifFalse: [ generated := (File name: srcPath, '.in') exists ]. (File name: each) withReadStreamDo: [ :rs | | pkg | [ pkg := Package parse: rs ] on: Kernel.PackageNotAvailable do: [ :ex | ex resume ]. pkgName := pkg name ]. ws nextPutAll: ('GST_PACKAGE_ENABLE([%1], [%2]' % { pkgName. relPkgSrcDir }). generated ifTrue: [ ws nextPutAll: (', , , [%1]' % { (File name: relPkgSrcDir) pathTo: srcPath }) ]. ws nextPutAll: ')'; nl. ] writeMakefile: ws [ ws nextPutAll: 'AUTOMAKE_OPTIONS = foreign AM_CPPFLAGS = $(GST_CFLAGS) ## Example: ## ## gst_module_ldflags = -rpath $(gstlibdir) -module \ ## -no-undefined -export-symbols-regex gst_initModule ## ## noinst_HEADERS = md5.h sha1.h ## gstlib_LTLIBRARIES = digest.la ## digest_la_SOURCES = digest.c md5.c sha1.c ## digest_la_LDFLAGS = $(gst_module_ldflags) ### -------------------------------------- ### ### Rules completed by GST_PACKAGE_ENABLE. ### ### -------------------------------------- ### DISTCLEANFILES = pkgrules.tmp all-local: clean-local:: install-data-hook:: dist-hook:: uninstall-local:: @PACKAGE_RULES@ ' ] ] Object subclass: PackageManager [ | mode args options | ModeClasses := nil. PackageManager class >> classForMode: aString [ ^self modeClasses at: aString ifAbsent: [ nil ] ] PackageManager class >> modeClasses [ ModeClasses isNil ifTrue: [ ModeClasses := Dictionary new. Command allSubclassesDo: [ :each | each selectionOptions do: [ :opt | ModeClasses at: opt put: each ] ] ]. ^ModeClasses ] mode [ mode isNil ifTrue: [ mode := PkgInstall ]. ^mode ] mode: aClass [ (mode notNil and: [ mode ~~ aClass ]) ifTrue: [ self error: 'multiple modes specified' ]. mode := aClass ] options [ options isNil ifTrue: [ options := OrderedCollection new ]. ^options ] addOption: opt argument: arg [ self options add: opt->arg ] addArgument: arg [ args isNil ifTrue: [ args := OrderedCollection new ]. args add: arg ] helpString [ ^'Usage: gst-package [OPTION]... ARGS... Operation modes: --install make or install STAR packages (default) --uninstall remove the packages mentioned in the FILES --dist copy files instead of creating STAR files. --prepare create configure.ac or Makefile.am --list-files PKG just output the list of files in the package --list-packages just output the list of packages in the files --download, --update download package from smalltalk.gnu.org or from its specified URL --help display this message and exit --version print version information and exit Common suboptions: -n, --dry-run print commands without running them --srcdir DIR look for non-built files in directory DIR --distdir DIR for --dist, place files in directory DIR --destdir DIR prefix the destination directory with DIR --target-directory DIR install the files in DIR (unused for --dist) -I, --image-file=FILE load into the specified image --kernel-dir=PATH use the specified kernel directory -v, --verbose print extra information while processing --install suboptions: --test run unit tests after merging --load also load the Smalltalk files in the image --list-files suboptions: --load only list files that are filed in when loading --test with --load, also include unit test files --vpath Omit path to srcdir for files that are there --dist suboptions: --all-files Process all files, not just non-built ones --copy Do not create symbolic links All operation modes except --download (or its synonym --update) accept paths to package.xml files or .star files, including remote URLs. --download and --update accept names of packages, which will be searched in the current system or on smalltalk.gnu.org) or URLs to package.xml or .star files. Except in uninstall and list files mode, gst-package requires write access to the GNU Smalltalk image directory, and merges the XML package files on the command line with that file. The default target directory is ', Directory image name, ' ' ] displayHelpAndQuit: anInteger [ self helpString displayOn: (anInteger = 1 ifTrue: [stderr] ifFalse: [stdout]). ObjectMemory quit: anInteger ] parseArguments: args [ Getopt "--kernel-directory and --image-file are processed by gst-tool. --no-load present for backwards compatibility, it is now the default. --no-install is also present for backwards compatibility." parse: args with: '-h|--help --no-load --test --load --no-install --uninstall --dist -t|--target-directory: --list-files: --list-packages --prepare --srcdir: --distdir|--destdir: -n|--dry-run --all-files --vpath --copy -I|--image-file: --kernel-directory: --update|--download --version -v|-V|--verbose' do: [ :opt :arg || modeClass | opt = 'help' ifTrue: [ self displayHelpAndQuit: 0 ]. opt = 'version' ifTrue: [ ('gst-package - %1' % {Smalltalk version}) displayNl. ObjectMemory quit: 0 ]. opt = 'verbose' ifTrue: [ OutputVerbosity := 1. FileStream verbose: true ]. modeClass := self class classForMode: opt. modeClass notNil ifTrue: [ self mode: modeClass ]. (modeClass isNil or: [ arg notNil ]) ifTrue: [ opt isNil ifFalse: [ self addOption: opt argument: arg. ] ifTrue: [ self addArgument: arg ]]] ifError: [ self displayHelpAndQuit: 1 ]. ] run [ | command | (args isNil or: [args isEmpty]) ifTrue: [ self displayHelpAndQuit: 1 ]. command := self mode new. command options: self options. command executeOnAll: args. ] ] [ PackageManager new parseArguments: Smalltalk arguments; run ] on: Error do: [ :ex | ('gst-package: ', ex messageText, ' ') displayOn: stderr. "ex pass." ObjectMemory quit: 1 ]. smalltalk-3.2.5/scripts/Load.st0000644000175000017500000001160512123404352013343 00000000000000"====================================================================== | | Smalltalk package loader (utility script) | | ======================================================================" "====================================================================== | | Copyright 1999, 2000, 2002, 2004, 2008, 2009 Free Software Foundation, Inc. | Written by Paolo Bonzini. | | This file is part of GNU Smalltalk. | | GNU Smalltalk is free software; you can redistribute it and/or modify it | under the terms of the GNU General Public License as published by the Free | Software Foundation; either version 2, or (at your option) any later version. | | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS | FOR A PARTICULAR PURPOSE. See the GNU General Public License for more | details. | | You should have received a copy of the GNU General Public License along with | GNU Smalltalk; see the file COPYING. If not, write to the Free Software | Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. | ======================================================================" Smalltalk arguments isEmpty ifTrue: [ ObjectMemory quit ]! | helpString quiet verbose wasVerbose snapshot force test sunit packages startMessage | snapshot := true. quiet := false. verbose := false. force := false. test := false. startMessage := nil. wasVerbose := FileStream verbose: false. packages := OrderedCollection new. sunit := ''. helpString := 'Usage: gst-load [ flag ... ] package ... Options: -q --quiet hide the output -v --verbose show loaded files -f --force reload package if already loaded -n --dry-run don''t save the image after loading -t --test run SUnit tests if available --start[=ARG] start the package and keep running the image -i --rebuild-image load into a newly-created image -I --image-file=FILE load into the specified image --kernel-dir=PATH use the specified kernel directory -h --help show this message --version print version information and exit '. "Parse the command-line arguments." Smalltalk arguments: '-h|--help --version -q|--quiet -v|-V|--verbose -n|--dry-run -f|--force -t|--test -I|--image-file: --kernel-directory: --start:: -i|--rebuild-image' do: [ :opt :arg | opt = 'help' ifTrue: [ helpString displayOn: stdout. ObjectMemory quit: 0 ]. opt = 'version' ifTrue: [ ('gst-load - %1' % {Smalltalk version}) displayNl. ObjectMemory quit: 0 ]. opt = 'quiet' ifTrue: [ OutputVerbosity := 0. quiet := true. verbose := false. wasVerbose := FileStream verbose: false ]. opt = 'verbose' ifTrue: [ OutputVerbosity := 1. quiet := false. verbose := true. wasVerbose := FileStream verbose: true ]. opt = 'force' ifTrue: [ force := true ]. opt = 'test' ifTrue: [ test := true ]. opt = 'start' ifTrue: [ startMessage := Message selector: (arg isNil ifTrue: [ #start ] ifFalse: [ #start: ]) arguments: (arg isNil ifTrue: [ #() ] ifFalse: [ { arg } ]) ]. opt = 'dry-run' ifTrue: [ snapshot := false ]. opt isNil ifTrue: [ packages add: arg ] ] ifError: [ helpString displayOn: stderr. ObjectMemory quit: 1 ]. force ifTrue: [ packages do: [ :each | Smalltalk removeFeature: each asSymbol ] ]. [ packages := packages collect: [ :each | PackageLoader packageAt: each ]. (startMessage notNil and: [ startMessage selector == #start: and: [ (packages count: [ :each | each startScript notNil ]) > 1]]) ifTrue: [ stderr nextPutAll: 'gst-load: Cannot pass start argument to multiple packages '. ^self ]. packages do: [ :each | each fileIn. sunit := sunit, ' ', each sunitScript ] ] ifCurtailed: [ ObjectMemory quit: 1 ]. wasVerbose := FileStream verbose: wasVerbose. test ifTrue: [ | tmpFile tmpFileName result | snapshot ifTrue: [ tmpFile := FileDescriptor openTemporaryFile: Directory temporary / 'im-'. tmpFileName := tmpFile name. ObjectMemory snapshot: tmpFileName. wasVerbose := FileStream verbose: wasVerbose ]. packages do: [ :each | each test isNil ifFalse: [ each test fileIn. sunit := sunit, ' ', each test sunitScript ] ]. result := (Smalltalk at: #TestSuitesScripter) run: sunit quiet: quiet verbose: verbose. result runCount = result passedCount ifFalse: [ ObjectMemory quit: 1 ]. snapshot ifTrue: [ (FileDescriptor open: File image mode: FileStream write) nextPutAll: tmpFile. tmpFile close. (File name: tmpFileName) remove ] ] ifFalse: [ snapshot ifTrue: [ ObjectMemory snapshot ] ]. (startMessage notNil and: [ packages anySatisfy: [ :pkg | pkg startScript notNil ]]) ifFalse: [ ObjectMemory quit ]. packages do: [ :each | each perform: startMessage ]. Processor activeProcess suspend! smalltalk-3.2.5/scripts/Test.st0000644000175000017500000000663412123404352013411 00000000000000"====================================================================== | | Smalltalk SUnit runner (utility script) | | ======================================================================" "====================================================================== | | Copyright 2003, 2007, 2009 Free Software Foundation, Inc. | Written by Paolo Bonzini. | | This file is part of GNU Smalltalk. | | GNU Smalltalk is free software; you can redistribute it and/or modify it | under the terms of the GNU General Public License as published by the Free | Software Foundation; either version 2, or (at your option) any later version. | | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS | FOR A PARTICULAR PURPOSE. See the GNU General Public License for more | details. | | You should have received a copy of the GNU General Public License along with | GNU Smalltalk; see the file COPYING. If not, write to the Free Software | Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. | ======================================================================" Smalltalk arguments isEmpty ifTrue: [ ObjectMemory quit ]! PackageLoader fileInPackage: 'SUnit'! | helpString verbose script suite result quiet | quiet := false. verbose := false. FileStream verbose: false. script := ''. helpString := 'Usage: gst-sunit [ flag ... ] class.tests ... Options: -q --quiet hide the output -v --verbose show passed tests -f --file=FILE load file before running subsequent tests -p --package=PACKAGE load package and run its tests -I --image-file=FILE run tests on the specified image file --kernel-dir=PATH use the specified kernel directory -h --help show this message and exit --version print version information and exit '. "Parse the command-line arguments." Smalltalk arguments: '-h|--help -q|--quiet -v|-V|--verbose -f|--file: -p|--package: -I|--image-file: --kernel-directory: --version' do: [ :opt :arg | opt = 'help' ifTrue: [ helpString displayOn: stdout. ObjectMemory quit: 0 ]. opt = 'version' ifTrue: [ ('gst-sunit - %1' % {Smalltalk version}) displayNl. ObjectMemory quit: 0 ]. opt = 'verbose' ifTrue: [ OutputVerbosity := 1. quiet := false. verbose := true. FileStream verbose: true ]. opt = 'quiet' ifTrue: [ OutputVerbosity := 0. quiet := true. verbose := false. FileStream verbose: false ]. opt = 'package' ifTrue: [ [ | pkg | pkg := PackageLoader packageAt: arg. script := script, ' ', pkg sunitScript. pkg test notNil ifTrue: [ pkg := pkg test. script := script, ' ', pkg sunitScript ]. pkg fileIn ] ifCurtailed: [ ObjectMemory quit: 2 ] ]. opt = 'file' ifTrue: [ [ FileStream fileIn: arg ] ifCurtailed: [ ObjectMemory quit: 2 ] ]. opt isNil ifTrue: [ script := script, ' ', arg ] ] ifError: [ helpString displayOn: stderr. ObjectMemory quit: 1 ]. script isEmpty ifTrue: [ ObjectMemory quit ]. FileStream verbose: false. (PackageLoader packageAt: #SUnit) loaded ifFalse: [ stderr nextPutAll: 'gst-sunit: you should load SUnit first.'; nl. ObjectMemory quit: 1 ]. result := TestSuitesScripter run: script quiet: quiet verbose: verbose. result runCount = result passedCount ifFalse: [ ObjectMemory quit: 1 ]! smalltalk-3.2.5/NEWS0000644000175000017500000035040312123404352011126 00000000000000List of user-visible changes in GNU Smalltalk NEWS FROM 3.2.4 to 3.2.5 o Add Delay>>#value:onTimeoutDo: as an easy way to timeout an operation. o Improve Delay and millisecondClock behavior across image save and restore. millisecondClockValue is guaranteed to be monotonic across image save, and delays are restarted when the image is restored. o DateTime>>#today will return midnight of the current timezone. o DateTime has a new method #asLocal. o DateTime>>#readFrom: can read more time formats. o Time resolution is now based on nanoseconds. o Absolute-time delays (Delay>>#untilMilliseconds:) are precise and not anymore converted to relative-time delays. o package.xml files support a tag, like . It can be used to make package.xml clearer for large packages. o MethodDictionary is now thread-safe. o String>>#% supports string keys, like %(string). They can be used when the argument of #% is a Dictionary or LookupTable. Note that the keys of the dictionary must be Strings, not Symbols. o Socket fixes including reporting of EndOfStream on broken pipes and connection resets. o Fix the FileDescriptor finalization code to close open descriptors. o The system file descriptor of FileDescriptor is set to nil on image restore. o The asynchronous event notification has been rewritten. The old version could fail when many file descriptors became available at the same time. o DBD-Postgres gained support to bind parameters on queries and various fixes to allow to resume images that use Postgres. o Images created with gst-remote can now be resumed. o Add #system:withArguments: to avoid using #system: with #% to add arguments. o Added Integer>>#printPaddedWith:to:. o Added CharacterArray>>#withShellEscapes o Added Collection>>#includesAllOf: o Stream>>#fold: works correctly. o 64-bit integer types are available using CLongLong and CULongLong. o gst-blox and gst-browser understand the -i/--rebuild-image option. o GObject errors show backtraces. o Improvements to multiarch support. o CType objects implement #= and #hash, so they can now be used as keys in a dictionary. o Floating-point numbers are printed more accurately in some rare cases. o Some optimization of OrderedCollection and SortedCollection o Selectors starting with an underscore are treated as keyword messages. o A new function gst_uint_to_oop is in libgst, and uintToOOP is also provided by the VMProxy. o Growing the heap is working again. o Various bugfixes. o GNU Smalltalk does not run anymore on i386 hardware, an i486 is needed. o Slightly faster garbage collection. ----------------------------------------------------------------------------- NEWS FROM 3.2.3 TO 3.2.4 o Autoload is extended to allow plugging in arbitrary loaders. o Array items in a CStruct didn't work, this is fixed now. o DLD could have problems when the same library was requested multiple times. o Errors in the bind() system call were not detected correctly; this has been fixed. o Fixes for platforms with 113-bit long doubles. o Fixes to Delay in the presence of delays with the exact same expiration. o Fixes to the HTTP package, including correct flushing of POST requests and doesNotUnderstand exceptions when the host did not exist. o GLUT bindings now build correctly under Windows. o Many smalltalk-mode improvements. o New methods: TextCollector>>#critical:, o nil can be passed to a C function accepting a #cObjectPtr (i.e. void **) argument. o SocketAddress>>#allByName: returns nil now, instead of an empty array, when getaddrinfo succeeds but returns no address for the requested address class. o SocketAddress>>#byName: returns addresses for the default address class when the receiver is SocketAddress (and not a subclass). o Support for older versions of GnuTLS. o Swazoo's static content serving was broken and has been fixed. o The GST_PACKAGE macro supports having multiple .la files in its last argument. gst-package's --prepare option was broken and has been fixed. o The NetClients exception ProtocolError now includes the erroneous response. Similarly, the package includes ProtocolNotification which is used, for example, for HTTP redirects. o Updated the Squeak/Pharo fileout parser. o Updated VisualGST. ----------------------------------------------------------------------------- NEWS FROM 3.2.2 TO 3.2.3 o Class attributes can have more than 1 keyword. o Documented #byteArrayOut C call argument passing mode. o Fixed crash when an invalid UnicodeString was created using #changeClassTo: o Fixed deadlock with #atEnd and two-way pipes. o Fixed bugs when adding instance variables to an existing class. o Fixed Socket>>#isPeerAlive falsely returning true. o Fixed some bugs in UTF-7 conversion. o FreeBSD port and 64-bit Darwin port. The latter requires a pre-installed libsigsegv. o "gst-convert -f squeak" reads binary selectors with more than two characters; however they should be shortened with rewrite rules to use the output. o gst-doc can generate sensible documentation for a package if some of its prerequisite are not loaded, even if some of the package's classes subclass from the prerequisite. o GTK+ bindings are generated correctly for newer versions of GLib (tested up to 2.26). o If found, pre-installed libsigsegv, libffi and libltdl are used by default. o Improvements for Emacs mode. Installation of Emacs mode detects Debian's /etc/emacs/site-start.d, and a --with-lispstartdir option is provided for distributions that are not Red Hat- or Debian-based. o Machine-specific optimizations for x86-64, and other microoptimizations resulting in small but consistent performance improvements. o More out of memory conditions are detected. o New methods: ByteArray>>#castTo:, ByteArray>>#asCData, String>>#asCData, UndefinedObject>>#inheritsFrom: o New goodie: Announcements. o Number class>>#readFrom: can parse numbers in scientific notation. o Package descriptions do not need to include a item for each item. However, it is still possible to include them for backwards compatibility, and it is possible to include a source file as both and (so that gst-package --dist will skip it). o Packages can be downloaded using HTTPS if GnuTLS libraries are present. o Performance statistics printed by -V are now correct. o Scoped methods ("A class >> a") can be used in an "A class [ ... ]" block. o Semaphore>>#wait returns nil if the wait was interrupted externally (e.g. from Process>>#resume). o String>>#asCData: and String>>#asCData NULL-terminate their output. o Support for timeouts when waiting on a Semaphore. o Swazoo supports SCGI. Its configuration however is still manual, since the Seaside and Iliad adaptors do not know about it. o Updated VisualGST. ----------------------------------------------------------------------------- NEWS FROM 3.2.1 TO 3.2.2 o Fixes to gst-remote. o Fixes to the Emacs mode. o Fixes to compilation warnings. o Generational GC is broken on SPARC and is now disabled. o When compiling a 32-bit version on a 64-bit system, detection of which packages to install was improved. ----------------------------------------------------------------------------- NEWS FROM 3.2 TO 3.2.1 o All built-in packages can be disabled with a configure option like --disable-gdbm or --disable-complex. o All tools support --verbose. o Fixed bugs in the distributed gnu-smalltalk.pc file. o Improved portability to Solaris. o Many bug fixes to UDP sockets. In particular, daragrams received from a socket can be placed directly onto another socket using #nextPut:. o Many improvements to VisualGST. o Each test in the testsuite has a 1-minute timeout. o The undocumented DynamicVariable class in GNU Smalltalk 3.2 is now documented, but it had a small change in the implementation. The #defaultValue class method is not present anymore, and is replaced by #valueIfAbsent:. Subclasses can override #value to obtain the effect of #valueIfAbsent:. The class has also been rewritten and is much faster now. ----------------------------------------------------------------------------- NEWS FROM 3.1 TO 3.2 Backwards-incompatible bug fixes and changes: o Collection>>#anyOne gives an error if the receiver is empty. o "aNumber raisedToInteger: 0" will raise an exception if and only if aNumber is not a floating-point value. This was backwards in previous versions. o Interval>>#first and Interval>>#last give an error if the interval is empty (i.e. if start > stop and the step is positive, or start < stop and the step is negative). o SequenceableCollection>>#sortBy: was renamed to #sort:. The old message is _not_ provided for backwards-compatibility. o The semantics of recursive directory descent were adjusted as follows: 1) the '.' and '..' directory entries are not passed; 2) for #do:, the file is passed directly (3.1 used to pass another recursive decorator); 3) before the descent starts, the directory itself is passed to the block. o The XML parser will ignore whitespace if placed in non-validating mode. o The suggested way to instantiate an XML parser is now using "SAXParser defaultParserClass", which will work with either of the two available parsers (the existing Smalltalk parsers, and the Expat bindings; see below). New features (base classes): o Floating-point rounding to integer is now correct also for very large numbers; fix contributed by Nicolas Cellier. o Methods have been added to Integer to print numbers with padding to a specified width. o New FilePath methods #owner:, #group:, #owner:group: allow setting a file's owner and group. o Sending mode, file time and owner setters to a recursive directory decorator (such as `Directory working all') sets the mode/time/owner on all files under the path. o Speedups for hashed collections o String>>#subStrings: accepts a single separator character or also, in accordance with ANSI, a String holding a list of separators. o The old instance-based exception handling has been removed. Standard ANSI class-based exceptions have been available since GNU Smalltalk 1.8.2. o The text-based #inspect method is now available also as Object>>#examine and Object>>#examineOn:, so that it will also work on arbitrary streams and will be available when a GUI is loaded. Contributed by Stefan Schmiedl. New features (tools): o gst-convert can emit Squeak fileouts. o New graphical interface VisualGST, loaded with gst-browser. The old browser is still available, but obsolete. o New ProfilerTools package for callgraph profiling of Smalltalk programs. A companion gst-profile tool will create profiles in callgrind-compatible format. Contributed by Derek Zhou. o Packages can be downloaded and updated directly from the network. The repository of packages is at http://smalltalk.gnu.org/project; the repository holds the location of the package.xml files, which point to the svn or git URL of the code. In order to download a package with git, version 1.6.2 is required. o SUnit supports expected failures. New features (VM): o Fixes in garbage collection heuristics provide improved performance on programs allocating many long-lived objects. Contributed by Derek Zhou. o Floating-point numbers are now read correctly. o In idle times, GNU Smalltalk will perform incremental garbage collection. When it finishes, GNU Smalltalk will consume zero CPU. o Mostly rewritten Windows port. It should mostly work except for sockets. The socket code will be rewritten (for all platforms) for 3.3 anyway. o Support for one-way become (Object>>#becomeForward:) o The millisecond clock uses CLOCK_MONOTONIC where available. New features (packages): o Many improvements to the Gtk bindings. o NetClients supports ESMTP commands. o New goodie, the SandstoneDb object persistence framework. o Swazoo upgraded to version 2.2, plus local fixes. o The Complex package uses numerically stable algorithms o The Continuations package provides delimited continuations via BlockClosure>>#shift and BlockClosure>>#reset. Both methods accept a block (1-arg for shift, 0-arg for reset). o An XML pull parser is included as package XML-PullParser. The package is based on the VisualWorks and Squeak pull parsers by Anthony Blakey and Ken Treis. o In addition to the validating XML parser, a non-validating Expat-based parser is available in package XML-Expat. The Expat parser is experimental, but it is very fast and supports both pull and push operation. Bug fixes: o Code running as a Generator now honors exception handlers outside the Generator block. o Fixed copying of Dictionary to not share the underlying associations. o Fixed ##() expressions that return a block o EPIPE is handled correctly. o Running on kernels without SOCK_CLOEXEC support will not fail even if the VM was compiled on a kernel that supported it. o The Sockets package failed to initialize when the machine was not connected to the network; this has been fixed. o The Transcript now uses a RecursionLock. This fixes crashes when an exception occurred while printing a backtrace. Miscellaneous: o GNU Smalltalk now does not rely anymore on specific (old) versions of libtool. o GNU Smalltalk tries to enable Emacs modes automatically on systems that support a site-lisp/site-start.d directory. o REPL autocompletion includes all symbols including unary messages (and variable names). o Process-local variables are now stored in an IdentityDictionary rather than a LookupTable. ----------------------------------------------------------------------------- NEWS FROM 3.0.5 TO 3.1 o BlockClosure methods #cull:, #cull:cull:, #cull:cull:cull: evaluate blocks removing parameters that are not accepted by the block. Thanks to this new functionality, the parameter to #on:do: and #ifNotNil: can be omitted. o Collections and Streams have a common superclass, Iterable. The user-visible aspect of this is that Streams now enjoy a wider range of iteration methods, such as #anySatisfy:, #detect: and #count:. o CObjects can be backed with garbage-collected (as opposed to heap-allocated) storage. Using this is not always possible, for example for CObjects stored by external libraries or passed to functions that call back to Smalltalk or otherwise may cause garbage collections. If it is, however, it is easier to use, faster and more predictable than finalization. As an added benefit, garbage-collected CObjects accesses are bounds-checked. Garbage-collected CObjects are created by sending #gcNew instead of #new. o Error backtraces include line numbers and filenames. o FileDescriptor and FileStream raise an exception if #next: cannot return the given number of bytes. o FileDescriptor is now a subclass of Stream. o Functions gst_async_signal and gst_async_signal_and_unregister are now thread-safe, *not* async-signal-safe. To trap signals from Smalltalk, you have to use ProcessorScheduler>>#signal:onInterrupt:. o Halt is now a subclass of Exception (rather than Error). o If possible, the installation is made relocatable. To this end, the following conditions should be satisfied: 1) the exec-prefix and prefix should be identical; 2) the installation should reside entirely within the prefix; 3) on Windows, the bindir and libdir should be the same or shared libraries should be disabled; 4) if neither on Windows nor under a glibc-based system, shared libraries should be disabled. If the above conditions are satisfied, and you want a relocatable install, it is suggested that you configure with a non-existent prefix such as "--prefix=/nonexistent". To move the installation, you can install into a staging area and move it from there. ./configure --prefix=/nonexistent make make install DESTDIR=`pwd` (cd nonexistent && tar cvf - .) | (cd $HOME && tar xvf -) (cd nonexistent && tar cvf - .) | (cd /usr/local && tar xvf -) In order to support relocatable installation, libgst clients should call gst_set_executable_path *before* gst_initialize. Failure to do so won't cause any problem, except that relocatable installation will be disabled and the program will look for its files only in the configured prefix. o It is possible to create C call-outs that are not attached to a function that the VM knows about, using the method CCallable class>>#for:returning:withArgs:. The returned object can then be used to create CompiledMethods using CompiledMethod class>>#cCall:numArgs:attributes:. The address however is reset to NULL on image restart and it is up to the user to reinitialize it. You can also subclass CCallable and override the #link method (the existing CFunctionDescriptor class is now implemented on top of this). o ObjectDumper now accepts normal String streams. The class ByteStream has been removed. o ObjectMemory>>#snapshot and ObjectMemory>>#snapshot: return false in the instance of GNU Smalltalk that produced the snapshot, and true in the instance of GNU Smalltalk that was restored from the snapshot. Note that this does not apply to CallinProcesses, since those are stopped in saved images. o RegexResults method #ifMatched:ifNotMatched:, and the similar methods, accept either zero or one-argument blocks. In 3.0, #ifMatched: accepted a one-argument block, while #ifNotMatched: accepted a zero-argument block. o Streams have a set of new methods that allow to eliminate useless copies when moving data from stream to stream, as well as to eliminate useless creation of collections to store the data read from a stream. Besides the standard methods #next, #nextPut: and #atEnd, two more methods can be implemented by Stream subclasses in order to achieve better performance on block transfers, namely #nextAvailable:into:startingAt:, #nextAvailable:putAllOn: and #next:putAll:startingAt:. Another set of methods is placed in Stream; they all use the above three methods and you should not need to override them. These are #next:into:startingAt:, #next:putAllOn:, #nextAvailable:, #nextAvailable:putAllOn:, #nextAvailablePutAllOn:. In addition, #nextHunk was removed. Applications can use #nextAvailable: or, better, should be rewritten to use new stream-to-stream protocol such as #nextAvailablePutAllOn:. o The VFS subsystem was rewritten. Virtual filesystems are now accessible via special methods on File (such as File>>#zip, for example "(File name: 'abc.zip') zip") and not anymore with special filenames that could conflict with real files. This caused a few incompatible changes. The most important are: 1) methods like `File image' and `Directory kernel' return a File object, not a String; 2) Directory objects are not created anymore and instead File objects also support the Directory protocol; 3) Directory>>#do: passes File objects rather than file names to the block; 4) Directory>>#contents is now called Directory>>#entryNames. o The order for searching pool dictionaries changed. The new order, codenamed "TwistedPools", builds on three ideas: 1) the environment of a class always has lower priority than the imports, so the environment is always excluded from the imports if the environment is a superspace of the imports; 2) apart from this, the imports are visited in topological order, so that if two imports have a superspace in common, the imports are always visited before the superspace; 3) each class in the inheritance order is visited separately, so the imports of a superclass have lower priority than the environment of the subclass. At the same time, support for imports were added to namespaces (via the pragma, as for classes). Unlike the superspace, imports are not made visible through #at:. o The semantics of #on:do: were changed: executing off the end of an exception handler will always return from the associated #on:do:. Older versions of GNU Smalltalk either returned or resumed depending on the resumability of the exception. o The source code for methods loaded from Streams that are not FileStreams is stored directly in the image. o New tool gst-remote allows remote control of a GNU Smalltalk VM via a TCP socket. o Processes support thread-local variables, which are accessed through a special dictionary returned by ProcessorScheduler>>#processEnvironment. o Packages can specify start/stop scripts. Start scripts can be activated with gst-load, while both start and stop scripts are supported by gst-remote. o The sockets package (and the namespace it is installed in) was renamed from TCP to Sockets. While the old namespace is still available for backwards compatibility, it is suggested to use the Sockets namespace instead. o Unbuffered sockets available from class Sockets.StreamSocket. New goodies: o IPv6 and AF_UNIX sockets (in the Sockets package). o Bindings to Cairo and LibSDL provided by Michael Bridgen, Tony Garnock-Jones and Brad Watson. o Bindings to OpenGL and GLUT contributed by Olivier Blanc. o DBI supports querying tables for schema information, and is integrated with the "ROE" (Relational Object Expression) package. ROE support is present for all back-ends (MySQL, PostgreSQL, SQLite). o Magritte object-model description framework. o Seaside application server/web framework. o Swazoo web server. ----------------------------------------------------------------------------- NEWS FROM 3.0.4 TO 3.0.5 o Added the following methods Character class>>#ff CObject>>#isNull Collection>>#includesAnyOf: Duration>>#readFrom: Number>>#readFrom:radix: Object>>#isCObject Package>>#/ SequenceableCollection>>#copyWithFirst: SequenceableCollection>>#swap:with: UndefinedObject>>#isNull WeakArray class>>#new o Bugfixes for gst-convert. o CallinProcesses can be terminated with Process>>#terminate. o DBI connection strings accept db/dbname/database, and host/hostname, as synonyms. o Fixed rare garbage collection bugs. o Fixed rounding error in Float>>#floorLog: and Float>>#ceilingLog:. o gst-doc implements a -F option to choose output format. HTML and Texinfo are supported (contributed by Thomas Girard). o GTK+ bindings updated to support changes in 2.12. o #storeOn: fixed for classes in namespaces other than Smalltalk. ------------------------------------------------------------------------------- NEWS FROM 3.0.3 TO 3.0.4 o A few operations on collections have been sped up. o Code without a space between a binary minus and a number, such as "a-2", is parsed correctly. As a side effect of this change, the sign of a number with an explicit radix (such as "16r10") can be placed before the radix too: both -16r10 and 16r-10 are accepted. o Fixed bug that caused some children not to be reaped. o Fixed bug when reading from a FIFO file and the writing side closed the FIFO before GNU Smalltalk started reading it. o Fixed CByte to actually work. o Fixed corner case of nested exception handlers. o Fixed directory navigation on ZIP archives (when using the VFSAddOns package). o Fixed HTTP GETs that caused a redirect and had a query. o Fixed leakage of file descriptors on ZIP archives (when *not* using the VFSAddOns package). o Fixed MappedCollection>>#keysDo:. o Fixed rare bug in the bytecode optimizer that caused invalid (non-verifiable) or even incorrect bytecode to be generated. o Fixed Stream>>#do: and Stream>>#linesDo:, which would terminate in advance if *another* stream was read past its end during the argument block's execution. o Fixed the tools to work on Windows even if invoked with an explicit extension for the executable. o gst-convert is now really quiet if invoked with --quiet. o Moved SequenceableCollection>>#join to Collection. o Removed bashisms from installed shell scripts. o Sockets use the close-on-exec option (see fcntl(2) for more information). o Sport fixes: fixed SpFilename>>#fail (did not work) and SpSocket>>#readInto:startingAt:for: (should only do one I/O operation, possibly returning a partially filled buffer). o UNC paths are parsed correctly by File. ----------------------------------------------------------------------------- NEWS FROM 3.0.2 TO 3.0.3 o File>>#withReadStreamDo: and File>>#withWriteStreamDo: now return the result of evaluating their argument, instead of returning the File object. o Fixed command-line option -S to actually work. o Fixed GC bugs in SQLite bindings. Also, the bindings could sometimes call sqlite3_finalize twice. o Fixed rare finalization bug. o Fixes to the JIT compiler. o Generational GC is now disabled on Alpha. o More fixes for MinGW. o New command-line option -i (--rebuild-image) for gst-load. o New methods: Number>>#asCNumber String>>allOccurrencesOfRegex:do: String>>allOccurrencesOfRegex:from:to:do: TCP.AbstractSocket>>#canRead TCP.AbstractSocket>>#canWrite TCP.AbstractSocket>>#ensureReadable TCP.AbstractSocket>>#ensureWriteable o The callback for the #returnFromSnapshot event is executed as a high-priority process. While relatively invasive, this change was needed to fix crashes when reloading images that used C bindings extensively. o A system-installed libffi can be used. The included libffi has been upgraded to version 3.0.4. o URLs can be passed to FileDescriptor class>>#open:mode:ifFail:. Thanks to everyone who reported bugs and/or provided fixes that went into this release, including Stephen Compall, Thomas Girard, Tim Kack, Cesar Rabak. ----------------------------------------------------------------------------- NEWS FROM 3.0.1 TO 3.0.2 o Fixed bugs in floating-point I/O. o Fixed bugs in comparisons between ScaledDecimals and Integers. o Fixes for MinGW. o Fixes to the Emacs modes. o Improved GNUPlot bindings (support for histograms). o Improved SqueakParser. o Number>>#readFrom: will return floating-point numbers, not fractions. o New methods: AbstractSocket>>#isPeerAlive CharacterArray>>#endsWith: Collection>>#count: Collection>>#gather: Collection>>#noneSatisfy: Date>>#- DateTime>>#date:time: DateTime>>#date:time:offset: Dictionary>>#associations Message>>#selector:argument: Number>>#to:collect: Number>>#to:by:collect: SequenceableCollection>>#copyAfter: SequenceableCollection>>#copyAfterLast: SequenceableCollection>>#copyUpToLast: SequenceableCollection>>#identityIndexOfLast:ifAbsent: SequenceableCollection>>#indexOfLast:ifAbsent: SequenceableCollection>>#sort SequenceableCollection>>#sortBy: SequenceableCollection>>#with: (also #with:#with: etc.) Stream>>#with: (also #with:#with: etc.) Time>>#addSeconds: Time>>#midnight o Regex is now a subclass of Object. o SQLite bindings return a different Row object for each #next call to a ResultSet. ----------------------------------------------------------------------------- NEWS FROM 3.0 TO 3.0.1 o `gst-package --list-files' emits file paths relative from the current directory. The --destdir and -t options are rejected. --list-files supports options --load and --test. o The documentation for a package can now be built even if the corresponding .star file is not installed. Since documentation is part of the tarball, this problem with 3.0 was actually only visible if you modified packages for which you lacked the support libraries in /usr/lib (e.g. Tcl/Tk for package BloxTK). o Added SequenceableCollection>>#atRandom and String>>#allOccurrencesOfRegex: o Eliminated possible infinite loop in CompiledCode>>#hash. o Fixed crash on LargeInteger>>#divExact: for huge numerator and small denominator. o Fixed ping-pong between two sizes (continuously growing and shrinking) in OrderedCollection. o Fixed undeclared variable PackageNotAvailable in the default image. o Fixed Symbol>>#numArgs for methods starting with an underscore. o Fixed problems with substitution of regexes that match the empty string. o Fixed problems with very short delays. o Fixed segmentation violation when gethostbyname returned NULL. o Test floatmath.st is XFAILed on alpha due to kernel bug 9751. ----------------------------------------------------------------------------- NEWS FROM 2.3.6 TO 3.0 Important changes: o A completely new syntax for defining classes is now present. This is detailed in the manual (see the tutorial section) and the entire source code of the system uses the new syntax. o A different startup sequence is used which improves the possibility to customize GNU Smalltalk, both site-wide and per-user. The details are in the manual, the main changes are these: the `~/.stinit' and `~/.stpre' files are now named `~/.st/init.st' and `~/.st/pre.st'; files requested with the `-K' command-line option are sought for in the `~/.st' directory too; kernel files may be overridden by placing them in `~/.st/kernel'; a site-wide customization file can be placed in `/usr/local/share/smalltalk/site-pre.st'. The kernel path is stored in the image and not changed when the image is loaded. In addition, `Directory systemKernel' and `Directory localKernel' are not used anymore, and just return the same as `Directory kernel'. Finally, Smalltalk programs have access to the aforementioned `~`/.st' directory as `Directory userKernel' (name subject to change). A `packages.xml' file, as well as `.star' files (see later) can be put there. o Several classes not meant to be accessed by the user have been moved to an internal Kernel namespace. This also removes them from the automatically generated documentation. o GNU Smalltalk now needs InfoZIP to be installed on the machine where it is compiled, in order to use the new single-file package facility. In the future, this dependency may be removed. o The tool for automatic documentation generator, that has been used by the GNU Smalltalk distribution for a long time, is now installed as gst-doc. Backwards-incompatible changes: o If you want to return a specific CObject class from a C call-out, it is suggested that you stop using "returning: ClassName type", as in ! and instead use ! ^^^^^^^^^^^ The source code conversion tool might silently produce an incorrect output if you use the former syntax. o The ABI for external usage has changed. libgst.a does not know anymore how to parse options, but exports functions to achieve the same effect as options. o The #writeStream and #streamContents: method were moved down from SequenceableCollection to ArrayedCollection, since they did not really work on variable-sized collections such as OrderedCollections. o The database access library has been replaced by a new DBI-like library, contributed by Mike Anderson, with bindings to PostgreSQL (also contributed by Mike), SQLite (by Daniele Sciascia) and MySQL. o In general, GNU Smalltalk is able to load files with the old syntax. In some cases, however, it will be necessary to either convert them using the gst-convert tool, or load the Parser package before them. This is the case if you get a "not yet implemented" error while loading the files. Packages improvements: o All packages in the distribution are now installed in the new ".star" format (for SmallTalk ARchive). ".star" files include at the top a package.xml file (whose format is the same as the tag of packages.xml). The name of ".star" file should be the same as the name of the package if the package.xml file has a tag. o In install mode, gst-package automatically creates a ".star" file. gst-package also accepts ".star" files on the command line; in this case, install mode will simply copy the file instead of rebuilding it from scratch. o gst-package supports preparing a standard skeleton for package tarballs, using the --prepare option. o Packages can specify a "testing-only" subpackage that is loaded when running tests (e.g. with "gst-load --test" or "gst-sunit --package"), but not when loading the package normally. This is done with a tag nested into . Other major changes: o Added #from: to Collection, which constructs an instance of the class based on a conveniently specified Array. This allows one to construct Dictionaries or LookupTables using Dictionary from: { 1->2. 3->4 } Another methods meant to be used with the { ... } syntax is #join. For example { 'hello'. a. '!' } join returns a string and is the same as using #, repeatedly, but is more efficient. o All collection classes support #readStream, though the default implementation (which uses generators) could be slow. o Continuations and generators have moved to the base image. More complex examples of continuations still reside in the Continuations package. o Directory entries are passed to #allFilesMatching:do:'s block argument if they match aPattern. As before, the function descends in all the directories, even those that do not match aPattern. o Evaluated code now puts undeclared variables in a private namespace (so that you do not have to declare temporaries) and defers the resolution of undefined variable bindings until the time of their first access. Unfortunately, this slows down evaluated code noticeably; you can get back the performance by putting code in a method or an Eval (in the latter case, you will have to declare temporaries explicitly, or the code will still use the slower deferred variable binding). o Flushing a socket tries to push data all the way down to the network. This usually removes the need for TCP_NODELAY option. If you have applications that want to use #flush to send data to the OS, but not to the network, we're all ears. o Image load uses copy-on-write memory mapped files. This means that, as long as a loaded object is not touched, the operating system will map it to the same physical memory, for different copies of the GNU Smalltalk virtual machine that loaded the same image. o Processes that are garbage collected before they terminate execution (e.g. because they are waiting on a semaphore that is also garbage collected) are appropriately terminated. o Saving the image breaks hard links. This was done to work around a Linux kernel bug, and might change in future versions. o Since they are not portable outside Unix systems, the `archive' virtual filesystems (deb, lslR, mailfs, patchfs, uar, urar, uzoo, ulha, ucpio, utar) are now available only if the VFSAddOns package is loaded. Without the package, only #uzip is available and it will only support extracting from ZIP files. o Startup time and quit time were improved widely (the time for running a simple "Hello, World" program is about one fifth of 2.3.x). o SUnit scripts can declare variables (using a "variable=value" syntax) that can be accessed from within a testsuite. o The "" pragma can be used to set the category of a method. o The graphical browser can now be started just by typing "gst-blox". o The image is now installed in /usr/local/var/lib/smalltalk (which in most distributions will map to /var/lib/smalltalk). o The MySQL driver was updated to support MySQL 4.x authentication. Tests can be run by configuring with --enable-mysql-tests=USER:PASSWORD:DB (the given user, password and database should already exists when `make check' is run; the default is "root:root:test"). o The XML package has been split in five smaller packages, XML-SAXDriver, XML-DOM, XML-SAXParser, XML-NodeBuilder and XML-XMLParser. The previous name XML can still be used. In the future it may load a different but compatible (e.g. Expat-based) parser. o When declaring a C function, the #returning: argument now supports specifying CPtr and CArray types, the same way it is done in CStruct and CUnion declarations. For example, since you can specify an "int *" as "#{CInt}", an "int **" (pointer to pointer to Integer, i.e. pointer to CInt) would be written "#(#ptr #{CInt})". Conversion from Array to CType is generally available using the CType class>>#from: method. o The zlib bindings' WriteStream decorator supports partial flushing. Class PipeStream is distributed independently as it is not used anymore by the zlib bindings. New goodies: o A new package DebugTools provides a generic Debugger class that can be used to control an inferior Smalltalk process. It is used by the textual MiniDebugger as well as the debugger that is part of the GUI. o Complex numbers support added (package Complex). o GNUPlot bindings o JSON reader/writer contributed by Robin Redeker. o MD5 packages renamed to Digest, SHA1 support added. o New DBI-like library replacing the old one, contributed by Mike Anderson. ----------------------------------------------------------------------------- NEWS FROM 2.3.5 TO 2.3.6 o Added #% as a shortcut for CharacterArray>>#bindWithArguments:. o Added #allButFirst, #allButFirst:, #allButLast, #allButLast:, #atAll:, #removeAllSuchThat: to Collection. o Added #join to SequenceableCollection. o Added symbolic link creation to File. o A race condition was fixed where a file handler was resurrected and another object inside it had already been finalized. o Pipes use OS pipes or socketpairs instead of a pseudo-tty. o Fixed bitrot in the debugger. o Fixed bug where ~= was computed incorrectly as = (e.g. 3 ~= 3.0e). o Fixed bug with growing of the Undeclared dictionary. o Fixed many minor bugs. o Fixed GC bug that could cause crashes if two GCs happened at particularly unlucky spots. o Fixes to File and Directory for Windows. o Fixes to MIME message parsing, UTF-7 encoding and XPath. o VariableBinding objects were made read-only when used as literals. ----------------------------------------------------------------------------- NEWS FROM 2.3.4 TO 2.3.5 o Added more examples of continuations. o Fixed a floating-point accuracy problem in the test suite. o Fixed a 64-bit cleanliness problem in the GDBM bindings. o Generational GC enabled on x86_64. o Support for writing a block with arguments and no statements as [ :a :b ] in addition to [ :a :b | ]. o The StreamFilter.st example, which provided lookahead, filtering, concatenation and other kinds of manipulation for Streams, has been promoted into the default image. ----------------------------------------------------------------------------- NEWS FROM 2.3.3 TO 2.3.4 o Fixed bug in LargeInteger division on systems not equipped with GMP. o Fixed bug in socket #nextHunk implementation, which lost the first or second byte in the input buffer. o Fixed paths in the image when "make DESTDIR" was used. o Fixed implementation of Dictionary>>#addAll:, and fixed Integer>>#binomial: when the argument is 0 or self. o Fixed various minor bugs and imprecisions in the documentation. o Improvements to the ancillary scripts gst-load and gst-sunit. In particular, a package can describe the classes that constitute its testsuite, and gst-sunit allows to quickly run the testsuite for a package. o Improvements to the test suite. Several of the modules included with GNU Smalltalk are tested. The testsuite is now written using Autotest. o Installed binaries do not require the Bourne shell anymore. o Some libffi files (for IA64 and PA) were missing from the distribution. o Upgraded libsigsegv, for improved Mac OS X on Intel support o zlib bindings provided in package ZLib. ----------------------------------------------------------------------------- NEWS FROM 2.3.2 TO 2.3.3 o Introduced the --with-imagedir configure option to specify the directory used for the image. o The manual was not properly generated in version 2.3.2. o Removed text relocations from the virtual machine's shared library. ----------------------------------------------------------------------------- NEWS FROM 2.3.1 TO 2.3.2 o #copyFrom:to: is uniformly 0-based for all Streams (unlike in Collections), because a Stream has 0-based #position and #position: methods. o Fixed many floating point rounding bugs in LargeIntegers and Fractions, thanks to Nicolas Cellier. ----------------------------------------------------------------------------- NEWS FROM 2.3 TO 2.3.1 o configure does not lock up when the system emacs is XEmacs and does not include both the comint package and the package's source code. o Fixed a garbage collection bug that typically occurred when installing GNU Smalltalk, or when launching the installed image. o gst-package honors the INSTALL command found by configure. o gst-config does not "forget" to prefix the library directories with -L. o Segmentation violations on large integer operations (on 64-bit hosts) were fixed. ----------------------------------------------------------------------------- NEWS FROM 2.2 TO 2.3 IMPORTANT: GNU Smalltalk now adds an explicit exception to the GNU GPL license, allowing the programs running under the virtual machine to use a GPL-incompatible license. This exception is used both by the virtual machine and by the library bindings included in GNU Smalltalk. This clears gray areas when a Smalltalk program is using functions in the external library bindings via dynamic linking and the foreign function call interface (C call-outs). o C call-outs returning #void now return self rather than nil. Performance of code heavily using C call-outs has improved. o FileStreams can now use pwrite for more efficient operation on files opened for read/write, and will do many less gratuitous lseek operations. pread will also be used by FileStream>>#copyFrom:to:. The number of system calls issued when generating the documentation, for example, is reduced by a third. o Fixed bug in methods containing both -0.0 and 0.0 (positive and negative floating-point zero). o Fixed bug in Directory class>>#create:, that could not create a directory relative to the current directory. o Fixed bug in File>>#touch, which did not work really. There are also methods to modify a file's atime and mtime. o Fixed bug in SortedCollection. After #removeAtIndex:, adds would leave the collection unordered. o Fixed many more bugs. o Introduced a method to efficiently convert a WriteStream into a ReadStream. It is called #readStream and makes WriteStream more polymorphic with String. o Introduced two more class shapes, #character and #utf32, that can be used for String and UnicodeString. o More reliable detection of at-end-of-file condition for pipes, TTYs, and so on (especially on Mac OS X), and of sockets closed by the peer. Due to incompatibilities between various OSes, you are advised to test end-of-stream conditions *before* rather than after reading a character from stdin. In 2.2, either way would work, but serious bugs were found on Mac OS X unless stdin was redirected from a file. o Moved gdk_draw_ functions to GdkDrawable. o New goodie to parse the command line. Look at the documentation for the Getopt class and for SystemDictionary>>#arguments:do:. o New example, lazy collections. When loaded, #select:, #reject: and #collect: do not create a new collection unless necessary. Idioms like (a select: [ :each | ... ]) do: [ : each | ... ] or a := a select: [ :each | ... ]. a := a reject: [ :each | ... ]. a := a select: [ :each | ... ]. ^a size can be much faster when this example is loaded. o Regular expressions are now included in the default image. The interface is now definitive and is similar to 2.2. The concrete classes for RegexResults are in a private namespace (since the user need not instantiate them anyway). Right now, regular expressions are only usable for String objects (see Unicode support below). This may change in the future. o The backtraces now omit again the internal methods in the exception handling system. o The class above which super-send bytecodes start searching is now embedded in the bytecode stream. This provides the infrastructure to implement 'here' as in Smalltalk/X or 'self.Foo b' to execute the Foo>>#b method (these possible extensions have not been implemented). o The header files compile cleanly with a C++ compiler. For the occasion, the preferred name of the old `mst_Object' has changed to `gst_object'. o Various speedups. Unicode support: o Characters above 127 are no longer used to represent extended ASCII characters. Instead, they are only used to represent a byte in the encoding of the Unicode characters from 128 on. To create them use the Blue Book method Character class>>#value:. To represent Unicode characters above 127 use the (ANSI Smalltalk) Character class>>#codePoint: method. Note that these characters *cannot* be shown on a stream with #nextPut: (use #display: instead) nor compared with #== (use #= instead). Character literals like $+ or $A are guaranteed to create normal "Character" objects, for which you can safely use #nextPut:. Right now, these are valid only for characters between 0 and 127. To create Character literals for unicode characters, use the new syntax to express characters using their Unicode code point. This may be extended in the future to support Unicode character literals. A ``safe'' way to obtain the character whose encoding is between 128 and 255 is this (which requires the Iconv module to be loaded): ##('' asUnicodeString first) (This snippet has no shortcut by design because, in general, converting a Character to a UnicodeCharacter is not a well-defined operation). o New UnicodeCharacter and UnicodeString classes. These new classes can also be passed to and received from C functions. See the manual for more information. o New syntax $<13> to express characters using their Unicode code point. As anticipated, this syntax will create instances of the new UnicodeCharacter class when the number is > 127. o Part of the I18N module was separated into the Iconv module, which provides support for printing Unicode characters and strings correctly. Other goodies: o NCurses bindings, contributed by Brad Watson. ----------------------------------------------------------------------------- NEWS FROM 2.1.12 TO 2.2 Scripting improvements: o A sharp-bang sequence at the beginning of a file is parsed as a one-line comment. o Provides an "-f" option (long option "--file") to be used in a #! line, as in "#! /usr/bin/env gst -f", which has the same effect of -Q, processing the file indicated by the option's argument, and passing the rest of the command line to GNU Smalltalk. In other words, the two invocations that follow are equivalent: gst -f script.st ARG1 ARG2 gst script.st -Qa ARG1 ARG2 o Load.st installed as gst-load, Reload.st installed as gst-reload, Test.st installed as gst-sunit. VM changes: o Can define subclasses of CompiledMethod and have a method invoked on the instances whenever the method is called. o Can pass a "void **" to C using the #cObjectPtr parameter specifier (previously undocumented and broken). o The #class method can be overridden. This is useful for example for debuggers and proxies. o Code for decoding/interpreting the bytecode set is for the most part automatically generated. Take a look at the ``genbc'' and ``genvm'' programs if you are going to write an high performance interpreter, and write to the mailing list for any information on them or on the other program ``superops'' (this one is much more specialized). o CompiledBlocks and CompiledMethods are read-only. o Dollars are allowed in the middle of identifiers and method names. This is unportable, so do not abuse it. As with underscores, it is not possible to use them at the beginning of an identifier or method name. o Fixed bug that caused the compiler to accept duplicate argument or temporary names. o GCC needed to compile GNU Smalltalk. o gst_smalltalk_args accepts a const char **. o Improved clarity and portability using intptr_t, size_t and ptrdiff_t more widely and wisely. o Indexed instance variables can be 8-bit and 16-bit, signed and unsigned integers; or they can be 32-bit and 64-bit, signed integers and unsigned integers and floating point values; or objects of course. Previously the only three possibilities were objects, 8-bit unsigned ints, and pointer-sized unsigned ints. o Instance variables are scanned backwards: if a subclass declares an instance variable with the same name of the superclass, it wins when compiling code in the subclass (fixes the so-called "fragile subclass" problem). o Keywords and parameters need not be separated by a space (as in `self x: y z:w'). o New bytecode set. This is a significant departure from the Blue Book's instruction set, and it improves performance by ~20%. Over 150 common bytecode sequences are optimized, saving on dispatching overhead and minimizing the cost of decoding arguments. o Options -l and -L (--log-changes and --log-file) are no more. The change log is not useful outside the GUI, while inside the GUI it ought to be maintained by the GUI itself. o Option -s is no more. It was made the default in 2.1.5. o Passing floating-point arguments to C works. o Prefetching instructions are used wherever supported (Alpha, SPARC, PPC, AMD K6 or newer, Intel PIII or newer, all with GCC 3.2). This speeds up the startup by up to 20%. o Instances of subclasses of CompiledBlock and CompiledMethod can be created using the same primitive that creates CompiledBlocks and CompiledMethods, but sent to the subclass. o Several important bug fixes in event handling and asynchronous file input/output. o Subclasses of MethodInfo can be used as the descriptors for CompiledMethod objects. o Two-character binary messages ending with a minus are scanned differently if followed by a number: "1+-2" is now read as "1 + -2", not "1 +- 2". This is what you would usually expect; however, including spaces explicitly is recommended. o When GCC 3.3 or later is used, a shared library is also built. The code has been to some extent optimized to make this less expensive, but the shared library still has a 5-10% performance hit. Note that the x86 shared library is undebuggable (-fomit-frame-pointer) with GCC < 4.0 because of the dearth of registers. The installed virtual machine is not linked to the shared library for optimal speed. o Wider set of operations available to modules that plug into GNU Smalltalk, including access to system classes, queries on the method dictionaries, and access to indexed instance variables. Smalltalk changes: o CLongDouble class allows one to access long doubles; long doubles are supported by CStruct, Memory and ByteArray as well. o CompiledCode>>#literalsDo: does what CompiledCode>>#allLiteralsDo: used to do. CompiledCode>>#allLiteralsDo: recurses into literal arrays. o Glorp, a layer for mapping objects to relational databases, is provided and integrated with the MySQL driver. o GNU Smalltalk includes a mechanism for defining security policies on a class-by-class basis. See below for more information. o Interval can return a #first and #last even if the Interval is empty. These are the start and stop object that it was created with. The private methods #start, #stop and #step have thus been superseded by #first, #last and #increment. o #min: and #max: always return a NaN when one of the two operands is a NaN; previously they would always return the other operand. o New syntax for C call-outs, can be transparently filed out from the image and then filed back in. See the documentation or the kernel/CFuncs.st file for more information. o PackageLoader can be told the namespace in which to load the package. Most package loading scripts are now no longer necessary or can be reduced to simple initialization duties. o #raisedToInteger: is better optimized and does the minimum number of multiplications for exponents up to 256. o SequenceableCollection has a more efficient implementation of #fold:, as well as #second, #third, and #fourth (and I'm going to stop here!). o #return and #return: now reinstate exception handlers, which will therefore be active while executing pending #ensure: or #ifCurtailed: blocks. o Stored CompiledBlocks into the method's literal frame for non-clean blocks, and turned #blockCopy: into a `make dirty block' bytecode without introducing a method of unclear utility. This is a little faster and (consistently) saves around 1% on image files. o The syntax for primitives has been generalized into a "method attribute" mechanism; pragmas are accessible through methods in CompiledMethod. o The thisContext variable is compiled as a message send like "ContextPart thisContext". o When a send to super fails, #doesNotUnderstand: is also sent to super and not to self. This change is experimental; these semantics look more coherent to me. As a result (think about it...) sends to super from a root class are now forbidden. o When a non-existing message is sent with the wrong number of arguments (using #perform:), #doesNotUnderstand: is invoked. In the past, the wrong number of arguments error would have been printed. The reason for this is to allow selector names that would be invalid for the Smalltalk language. Work in progress: o Blox-GTK interface, to use the browser under Gtk+. Currently, only the browser works; to try it, configure with --enable-gtk=blox or load the BloxGTK package. Thanks to Robert Collins. o GNU Smalltalk now supports executing (some) Java programs. See the info documentation for more information. The class library is based on GCJ 3.4, but should be reasonably upwards-compatible. There is no AWT nor JNI support, and it is not planned; networking, reflection and serialization are not there but should be added in the future. Overview of the security mechanism: o Implemented class-level permissions. Each class can have its own permission set, and if this is not trivial (all-allowed) the class is marked untrusted; then instances of that class, as well as contexts that have at least an untrusted object as the receiver in the sender chain, are considered untrusted. In the future, security checks will be made for untrusted objects in such methods as C call-outs [#memoryAccess] CObject class>>#alloc: [#memoryAccess] CObject class>>#alloc:type: [#memoryAccess] CObject>>#free [#memoryAccess] CObject>>#at: [#memoryAccess] CObject>>#at:put: [#memoryAccess] Memory>>#at: [#memoryAccess] Memory>>#at:put: [#memoryAccess] FileDescriptor>>#fileOp:... [#io] ObjectMemory>>#snapshot: [#io] ObjectMemory>>#quit: [#system] ObjectMemory>>#abort [#system] ObjectMemory>>#setSpaceGrowRate: [#system] ObjectMemory>>#setSmoothingFactor: [#system] ObjectMemory>>#setGrowThresholdPercent: [#system] ObjectMemory>>#setBigObjectThreshold: [#system] ObjectMemory>>#growTo: [#system] Object>>#makeUntrusted: [#securityManagement] Object>>#instVarAt: [#debugging] Object>>#instVarAt:put: [#debugging] Object>>#perform:... [#debugging] Object>>#changeClassTo: [#debugging] Process>>#suspend [#processManagement] Process>>#resume [#processManagement] UndefinedObject>>#subclass:... etc... [#system] Class>>#subclass:... etc... (mutation) [#system] Metaclass>>#instanceVariableNames: [#system] MethodDictionary>>#at:put: [#system] o Instance variables of an untrusted class that are declared by a trusted class are read-only. This is necessary to avoid that a misbehaving class method screws up the instance variables of Behavior that are known to the VM. o Methods are verified. o Permissions can be granted by a method to its callees if the method's definition class owns those permissions. This can be used to invoke trusted C call-outs. o Primitives cannot be declared for untrusted objects (this might be fine-grained in the future). ----------------------------------------------------------------------------- NEWS IN 2.1.12 This is a bugfix release. It fixes several problems on 64-bit systems. ----------------------------------------------------------------------------- NEWS IN 2.1.11 This is a bugfix release. ----------------------------------------------------------------- NEWS IN 2.1.10 This is a bugfix release, but with this visible change: o PackageLoader supports loading package source code from multiple directories. Directory packages.xml is in Directories looked in /usr/share/smalltalk /usr/share/smalltalk parent of local kernel directory, if any image directory parent of local kernel directory parent of local kernel directory image directory image directory image directory o Directory>>#append:to: supports passing an absolute path as the file name (first argument). In this case, the file name itself is returned. This release works under MacOS X 10.3 and 10.4 as well. It also works around bugs in MacOS X Tiger's poll function. ----------------------------------------------------------------------------- NEWS FROM 2.1.5 TO 2.1.9 These are bugfix releases. The only visible changes are: o DLD can open the C library (2.1.6). o Fix bug in compilation of ##() expression where the expression evaluates to an integer (2.1.8). o Fix bug in #next: on sockets (2.1.6). o Fix crash when accessing an ill-formed namespace from Smalltalk code (2.1.8). o Fixes to the JIT compiler (2.1.8). o libltdl is no longer configured in a separate subdirectory (2.1.6). o Updated version of Automake, Libtool, Autoconf, snprintfv. o Updates to Emacs mode (2.1.6). o Work around bugs in MacOS X Tiger's poll function (2.1.9). ----------------------------------------------------------------------------- NEWS FROM 2.1.4 TO 2.1.5 o Changes in the internals of the GTK+ bindings. The bindings are loaded with the GTK+ package which is enabled by default if GTK+ 2.0 is installed. They don't disable the Tk bindings. o Can pass integers to C routines that expect floats (where passing floats works...) o Do idle processes correctly. o More examples provided for GTK+. o Option -s is always enabled and will be removed in 2.2. o Removed some GNU make-isms o #return and #return: should reinstate handlers according to the ANSI standard, but they currently aren't; SUnit however needs this behavior. For this reason a workaround was added to SUnit, and this behavior will be adopted uniformly in 2.2. o Warnings are suppressed correctly under GCC 3.3. o --without-emacs suppresses compilation and installation of Emacs LISP files ----------------------------------------------------------------------------- NEWS FROM 2.1.3 TO 2.1.4 o Fix bugs treating old objects that have already been considered by the incremental GC (and survived it). Example: ObjectMemory globalGarbageCollect. HomedAssociation class instanceCount gave 0 instead of 1. As a result, --enable-checking now can be used. o Fix bugs when doing #become: between old objects, exactly one of which has not been considered by the incremental GC and was incorrectly swept when the collector finally reached it. o Fix bugs when garbage collection triggered finalization while a primitive was being run. Finalization is now done in a separate Process. o Fix bugs treating very large objects. o Fix infinite loop when the big object threshold was set between the size of survivor spaces and the size of the eden. o Printing Integers was unbelievably inefficient. Fixed together with some more low-hanging fruit. o SequenceableCollection>>#replaceFrom:to:with:startingAt: allows again that stop=start-1 (like replaceFrom: 1 to: 0 with: ...) ----------------------------------------------------------------------------- NEWS FROM 2.1.2 TO 2.1.3 o Add Object>>#allOwners. o CallinProcesses do not survive across image saves. This fixed a memory leak where upon every image save, the CallinProcess that invoked the save was left ready to run in the least. This also caused mysterious bugs whenever, for example, you saved the image with ObjectMemory snapshot; quit! and then tried to do Processor yield! Now the CallinProcess would wake up from the point it was snapshotted, and happily quit the VM! o --disable-generational-gc in theory should not be necessary anymore. o Fixed a couple of bugs in printing bytecodes o Fixed bug in LargeInteger>>#bitAt: o Fixed compilation under Alpha o Fixed method caching error when using the JIT compiler o Fixed rare GC bug o Fixed syntax highlighting of unary and binary methods o New iteration method Collection>>#fold:, the latest variation on the #inject:into: and #do:separatedBy: themes. You'll undoubtedly love #('abc' 'def' 'ghi') fold: [ :string :elem | string, ' ', elem ] which yields 'abc def ghi'. This method can also replace most usages of #anyOne together with #inject:into:, as in coll inject: coll anyOne into: [ :max :elem | max max: elem ] versus coll fold: [ :max :elem | max max: elem ] o Set was incorrectly said to have 2 instance variables. o SmallIntegers are reported to be read-only. o Support for generational GC under NetBSD/Alpha (and possibly more OSes running on Alpha) o Updated libtool to Debian's 1.4.3-9. o Upgraded GNU lightning to 1.1. ----------------------------------------------------------------------------- NEWS FROM 2.1.1 TO 2.1.2 o Adding instance variables via #addInstVarName: validates their name and possibly recompiles the class if the superclass defines an identically named class. Removing class variables via #removeClassVarName: recompiles the class. o BACKWARDS INCOMPATIBLE: ObjectMemory class>>#snapshot: will fail if it cannot write to the file. o BACKWARDS INCOMPATIBLE: File class>>#extensionFor: includes the leading dot. This is necessary to obtain the sensible behavior (File stripExtensionFrom: string), (File extensionFor: string) = string o Better support for detecting the headers when multiple versions of Tcl/Tk are installed on the same machine. o Fixed call-in bug (if a primitive did a call-in and *then* failed, the call-in might have dirtied the method cache and an invalid method was invoked). This could not happen in previous releases, but the new #snapshot: primitive satisfies this condition. o Configure option --disable-generational-gc to disable usage of libsigsegv (which seems to lock up under some versions of MacOS X). o Fix lexing bugs under Linux/PPC and, supposedly, S390 and ARM too. o Fix misbehavior under GCC 2.x o Upgraded libsigsegv from CVS (includes ports to Linux/HPPA and OpenBSD/i386). ----------------------------------------------------------------------------- NEWS FROM 2.1 TO 2.1.1 o Support for readline 4.2 and 4.3. o Works under Cygwin, with generational GC enabled o .stinit is not loaded in regression testing mode. ----------------------------------------------------------------------------- NEWS FROM 2.0.11 TO 2.1 VM changes: o #asObject returns nil instead of SIGSEGV-ing when a bogus OOP number is passed. o Changed default verbosity of the virtual machine. Specify -V to get execution statistics. o Corrected an incredible number of bugs in Processes. o Do-its at the 'st>' prompt return the last evaluated value. o Finalization is no longer provided by the VM, but rather implemented on top of the more general "ephemeron object" facility. As a result of using ephemerons, code referencing the WeakKeyLookupTable class should use the new WeakKeyDictionary class (which behaves the same). o gst_init_smalltalk will not exit on error, instead it will return an error code o If an invalid image file is specified along with -I, it is considered an error. o More portable than ever! o New, redesigned implementation of call-ins and call-outs, enforces the priority under which the call-ins are executed and supports context switches during a call-out as well as asynchronous call-outs. The #defineCFunc:withSelectorArgs:forClass:returning:args: method which had been deprecated three years ago was finally removed. o Primitives are written with a `little language' (actually C with a few extra directives) and preprocessed to C at build time. o Rewritten the garbage collector: it is now generational and incremental. o Small massaging to the bytecode set. Replaced little-used push -1 and push 2 bytecodes with push signed 8-bit and push unsigned 8-bit bytecodes o Smalltalk processes can ask not to be interrupted by external events. o Source code line number stored in the bytecodes. o Support for single-stepping into a Process (to be used and abused by debuggers). o Support for compile-time evaluation with the ##( ... ) syntax. o Support for compile-time Namespace resolution, with any of the . or :: scope-resolution operators (former used in kernel source code). o Unused JIT-compiled code is garbage collected. o Upgraded libtool and libltdl to 1.4.3. Smalltalk changes: o Associations that are part of a Namespace or a class pool know which namespace they are in and, when stored, resolve to the association that is already in the namespace. This is achieved through a new class VariableBinding. o Backtraces don't show methods that are internal to the exception handling system. o Calls to dynamically loaded libraries are resolved on demand rather than right after the image is loaded. Useful for GTK+ bindings which have thousands of function to be resolved. o Class autoloading supports namespaces. In addition autoloaded classes have a proper metaclass even before they are loaded, and keep the same VariableBinding they used to have before loading. o Class pool dictionaries know about the class that hosts them. o CompiledCode supports dispatching the bytecodes to an object that wishes to decode them. o Creating an instance of a variable class with #new creates an instance with no indexed variables, instead of failing. o Deprecated Integer>>#radix: in favor of #printStringRadix:. o "Falling off" an exception handler does not resume a resumable exception: instead the #on:do: block is always left like it already was for non-resumable exceptions. For example | var | [ var := self mySelector ] on: MessageNotUnderstood do: [ :ex | 1234 ] used to give 1234 as the answer to the not understood message and hence used to assign it to var. Instead now 1234 is returned by #on:do: and then discarded. Also, [ 'Huey' printNl. self mySelector. 'Dewey' printNl. self mySelector. 'Louie' printNl. self mySelector ] on: MessageNotUnderstod do: [ :ex | ]. used to resume the block and then to print all the three strings, while now it only prints "Huey" before leaving the #on:do: block. This was caused by an incorrect reading of the ANSI standard. The correct way is to write `ex resume: 1234' or `ex resume' explicitly in the exception handler. This is *BACKWARDS INCOMPATIBLE*. o Namespaces use instance variables properly to store information about superspaces and subspaces (they used to use special keys such as #Super). o New class RecursionLock that is like Semaphores but will let the Process that owns the lock send #wait without actually waiting. o New syntax %n supported by String>>#bind... picks one of the two strings depending on the truth value of %n. o The packages file is XML. It also contains enough information to simplify the Makefiles and avoid unneeded recursive invocations of make. o Protected blocks (#ensure:/#ifCurtailed:) are executed even if the enclosing process is terminated. Processes receive a notification (SystemExceptions.ProcessBeingTerminated) when they are sent #terminate. They are also removed from the semaphore they are waiting on (if any). o Support for pluggable debuggers to be started whenever an error exception fires. An example text-mode debugger is provided, as well as a nicer Blox debugger. o The EndOfStream exception is now a notification exception (i.e. not a fatal exception). The ReadStream class raises it (it did not because ANSI mandates that it returns nil and does not fail at the end of the stream; turning EndOfStream to a notification allows us to satisfy ANSI and raise the exception at the same time). o Virtual filesystems for unzipping, untarring, uncpio-ing, etc. are now implemented. Goodies: o Database manager with MySQL driver o Emacs Smalltalk mode back from the dead (thanks to David Forster) o GTK+ bindings support callbacks and GTK+ 2.x o NetClientsBase is integrated in the base image. FileStreams support opening URLs (only file URLs until you load NetClients). o Numerical methods library o The Parser and its companion classes have been dropped, and their users converted to use the Refactoring Browser's parser, formatter and parse trees. Some of the advantages, such as better syntax highlighting in the browser, are already visible. o WebServer supports virtual hosting. The change is backwards compatible, if you don't intend to use virtual hosting you don't need to change your initialization scripts, and you don't either need to change the servlets in any way. o WebServer supports STT (Smalltalk Templates) a` la PHP o XML parser supports SAX 2.0 API Blox & the browser: o Added callbacks to BMenu o Added or improved many menus (e.g. Method set browser's upper pane) o Added menu bars that mimic the pop-ups o Changed fonts o Class definitions are syntax highlighted just like methods o Class hierarchy browsers enters "add method" mode automatically whenever a protocol is clicked o Context inspector is now a debugger with context list, variable names, and single-step capabilities (*could lock up the JIT compiler!*) o Faster! o Fixed many bugs o Rewritten inspectors, with multiple visualization and Dive/Pop functionalities o `self' is the inspected object when evaluating code from an Inspector o The clipboard and the primary selection work as expected o The label that is shown in a BDialog wraps correctly. o Undeclared variables used in a worksheet variables survive across multiple evaluations ----------------------------------------------------------------------------- NEWS FROM 2.0.2 TO 2.0.11 These are bug-fix releases. The only visible changes are: o Added Integer>>#printStringRadix: which replaces Integer>>#radix: The latter is now deprecated and will be removed in 2.2 (2.0.11) o Added shortcut keys to the browser (2.0.7) o Better error detection in TCP connections (2.0.11) o Better error recovery in the parser (2.0.7, 2.0.11) o Modified CObjects to be more orthogonal (2.0.4) Bug fixes: o Backported several little improvements for the development branch (2.0.11) o ByteStream on a ByteArray is now equivalent to a FileStream (2.0.5) o Blox compiles cleanly on FreeBSD (2.0.5) o Blox shows XPM images again (2.0.9) o Child process when opening a pipe is made a session group leader, so that job control will work correctly (2.0.11) o Detect FreeBSD's Tcl/Tk port in which tclsh is not a valid binary (2.0.11) o Fixed dangling pointer in DLD (2.0.11) o Fixed failure to compile when libtool is not installed (2.0.11) o Fixed race condition in Delay (2.0.7) o Fixed race condition between arrival of SIGCHLD and SIGIO (2.0.6) o Fixed rare bogus compilation error (2.0.11) o Fixed rare out-of-bounds access to context objects due to incorrect computation of the number of stack slots needed by cascades (2.0.6) o Fixed rare garbage collection bug, when a GC was triggered between _gst_get_cur_file_name and the creation of a FileSegment that used that name (2.0.10) o Fixed severe lossage in the JIT related to #ensure: (2.0.11) o Fixed testsuite failures when GMP is not installed (2.0.11) o Improved autoconf detection of Tcl/Tk (2.0.5) o Improved detection of pipe-like behavior of files such as FIFO special files and /proc special files (2.0.6) o Improved handling of low-water conditions (2.0.6) o Included implementations of long double transcendental functions in case the C library does not provide them (2.0.4) o Instead of guessing, if possible use MAP_NORESERVE to have the OS give us a big consecutive area of memory to store the OOP table (2.0.9) o Re-enabled separate memory space for large objects, was disabled because of a bug (2.0.6) o Removed a couple of C99-isms in the source code that had crept in (2.0.3) o Restored portability problem to systems with unaligned doubles with clever compilers such as GCC 3.0 on the SPARC (2.0.8) o SequenceableCollection>>#includes: was unnecessarily slow (2.0.6) o Support for locale files stored in a user-specified directory (2.0.9) o SUnit upgraded to 3.1 (2.0.6) o Various updates to libsnprintfv (2.0.10) o XPath package and XSL processor are included under the LGPL (2.0.6) ----------------------------------------------------------------------------- NEWS FROM 2.0.1 TO 2.0.2 This release should be ANSI compliant. All the known problems with ANSI compliancy have been fixed. VM changes: o #ensure: methods are always executed, even in the presence of non-local returns. #ifCurtailed: conditions are also more general and include non-local returns (not only exceptions). o Floating point constants are always parsed as long doubles to increase their precision. o Implemented the `make installcheck' target. o LargeInteger primitives failed and went back to Smalltalk code when zero operands were involved; LargeInteger exact division in addition failed to detect division by zero. o Object copying with the default semantics is a primitive for speed o Support for separate FloatD/FloatE/FloatQ classes with varying precision. o Uses libsnprintfv to simplify printing OOPs (custom %-specifiers) Other Smalltalk changes: o All the expected failures in the ANSI test suite have been fixed (both with the bytecode interpreter and the JIT---the causes of the failures were different in the two cases). o Fixed a few bugs in the parsing of ScaledDecimal constants in both the compilers (builtin and Smalltalk-in-Smalltalk) o Fractions print without parentheses o Some numeric methods return values of different classes (for ANSI compliancy). o The package loader stores absolute paths to the packages ----------------------------------------------------------------------------- NEWS FROM 2.0 TO 2.0.1 VM changes: o Fixed embarrassing syntax error in the JIT o Image directory must not be world-writeable anymore, unless of course the image must be built ----------------------------------------------------------------------------- NEWS FROM 1.95.13a TO 2.0 VM changes: o A few internal data structures are now implemented as balanced binary trees rather than resizable arrays. This allows for faster lookup. o All the functions and variables in the C source code are now commented. o Big objects are allocated outside the main heap, hoping to improve the locality of reference between small objects o Byte and word instance variables are range checked. Previously (it was a bug, not a feature) we only checked that the values of byte instance variables were < 256 (and not even that they were >= 0). o Globals are searched in the class namespace before and in the pool dictionaries (i.e. in the imported namespaces) after. This is backwards-incompatible. o Just-in-time compiler to native code for the PowerPC, SPARC and x86 architectures o Hash table sizes are assumed to be power of two. The class library and the VM both take care of scrambling the bits with some rotations instead of using the modulo to do this. o Image loading is up to 15% faster o LargeIntegers operations are demanded to the GNU MP library if found (otherwise, the old Smalltalk implementation is used). On my 266MHz PC this means that the factorial of 100000 is computed in 6 seconds. :-) o ObjectMemory hooks are traced only if -E/-D is specified, in order to decrease the amount of noise given by the more commonly used -e/-d. o Optionally, preemptive multitasking of Processes can be enabled. o Primitives are named rather than numbered o Removed most special-purpose hooks from the higher-level parts of the system, such as the compiler and C interface, into the low-level parts (such as GC and the VM) o SIGUSR1 triggers a backtrace o Support for file sizes over 2 gigabytes o vpath builds are fully supported Other changes: o All the libraries are loaded within their own namespace. This is STInST for the Smalltalk compiler and parser, I18N for the internationalization library, TCP for the sockets library, and BLOX for the GUI library. You might need to change your pool dictionaries declarations accordingly. o ANSI-compliance tests integrated into "make check" o Backwards-incompatible fixes for ANSI compatibility in: SequenceableCollection>>#replaceFrom:to:with: SequenceableCollection>>#copyReplaceFrom:to:withObject: Dictionary>>#keyAtValue: Bag>>#add: Bag>>#add:withOccurrences: PositionableStream>>#next PositionableStream>>#position PositionableStream>>#position: o Changed the names of these methods, for ANSI compatibility: Float class>>#largest (now #fmax) Float class>>#smallest (now #fmin) Float class>>#mantissaDigits (now #precision) o Constants like CDoubleSize that are used only to pass information about the runtime environment do not pollute the Smalltalk namespace anymore. o Deprecated methods in SystemDictionary were removed (use their counterparts in ObjectMemory). o Documentation includes BLOX, TCP and internationalization. o FileDescriptors support #atEnd for pipes as well o File operations go through a virtual filesystem layer that can provide transparent decompression and archiving of files. o Floats now implement IEEE 754 correctly. NaNs and infinities are generated by transcendental functions (since arithmetic operators already generated them), negative zero is correctly handled, and custom versions of #min:, #max: and the like are provided that take NaNs into accounts. Tests for NaN and infinity are possible for any kind of Number. o A gst.m4 file, providing an AM_PATH_GST autoconf macro, is installed (courtesy of Ryan Pavlik). o Load.st and Reload.st correctly provide an exit status. o Optimized and bugfixed many numeric computations: Fractions based on algorithms in GNU MP, bitwise operations such as #highBit, factorial, etc. o Pool dictionaries can be specified with dot notation to indicate subspaces. o Regression testing mode disables backtraces when an exception is raised. Only the error message is printed. o The behavior of the filename-manipulation class methods in File has changed in sometimes backwards incompatible, but more correct, ways. For example, the path of '/vmlinuz' is '/' and not the empty string. o The disabled operations in Blox that were kept for backwards compatibility with GNU Smalltalk 1.1.5 have been removed. o The ObjectDumper's #postLoad hook is only called the first time an object is found in the stream; once the object got its definitive shape it makes no sense to lose time (or even do harm) with post-load fixups. This change is at least in theory backwards incompatible, but I doubt it has practical relevance. o The `packages' file is searched in the parent directory of the kernel directory, rather than in the image directory. o The policy for picking the exception handler when more than one is specified is best-fit rather than first-fit. For example, previously [...] on: Error do: [...] on: MessageNotUnderstood do: [...] never picked the MessageNotUnderstood handler because the Error handler was chosen earlier. o The Random class includes a facility to use a common Random object instead of forcing every client to use his own object. o The source has been converted to ANSI C and reformatted according to the GNU standards. All the external symbols are prefixed with either _gst_ or gst_ depending on their privateness. Since there were four public symbols in all, this does not cause much trouble, but it *is* backwards incompatible o To avoid namespace pollution, the C callout mechanism does not generate global variables with strange names anymore (actually, it generates them in a separate namespace). o true, false and nil inside Arrays are parsed according to the ANSI standard. o Warnings are raised if one tries to send any of the six reserved keywords, since they most likely forgot a period (the six keywords are #self, #super, #true, #false, #nil and #thisContext). New goodies: o GTK+ bindings are provided. No way to have callbacks from GTK+ to Smalltalk yet, and we need a way to have gtk_main act as a coroutine. Note that these bindings are a proof-of-concept and are expected to be used internally by a future port of Blox to GTK+. o NetClients toolkit, supporting popular Internet protocols. NNTP and IMAP are not very well tested yet, but HTTP/FTP/SMTP/POP3 are. o New NamespaceBrowser tool (the traditional four-paned browser) o Primitive support for address families other than AF_INET. In particular, the default implementation classes for sockets are now picked by subclasses of SocketAddress, rather than by a class instance variable in Socket. Also, the #byName: and #allByName: methods should now be sent to SocketAddress rather than to one of its subclasses such as IPAddress. SO_REUSEADDR is not accessible anymore by instance methods because it was totally useless; instead it is always set for server sockets. o Proxy class loader, used to generate documentation without compiling the source code. ----------------------------------------------------------------------------- NEWS FROM 1.95.5 TO 1.95.13a These are bug fix releases. Bug fixes include: o correct installing when DESTDIR is specified (1.95.13a) o fixed possible infinite loops in exception handling (1.95.12) o improved portability to HP/UX systems and systems without the readline library (1.95.12) o fixed hangups that sometimes happened when outputting to a tty (1.95.11) o adopted the glibc implementation of MD5 (1.95.11) o fixed exactly four bugs due to missing periods (symptom: strange `does not understand' messages). (1.95.10) o improved SortedCollection performance (1.95.9) o ensured that the Directory class>>#image method returns the *current* rather than the default image path (1.95.9) o fixed bugs in the namespace classes (1.95.8) o fixed lossage when many I/O events happened in a row (1.95.7) o The #(a b) syntax for symbols inside Arrays has been obsoleted, since 2.0 will parse it according to the ANSI standard. A warning is emitted if you use it. The source code has been modified accordingly. (1.95.6) ----------------------------------------------------------------------------- NEWS FROM 1.95.4 TO 1.95.5 VM changes: o Calls to the virtual machine from plugins, and objects that are passed as OOPs in call-outs, put OOPs in the incubator rather than in the registry; call-outs are wrapped in incSavePointer/incRestorePointer. o Command line parsing uses getopt and thus behaves exactly like other programs (previously there were some discrepancies) o Errors are signaled if a file specified on the command line is not found. o Events can be passed to the Smalltalk image via an ObjectMemory class. o Fixed bug in evalExpr and typeNameToOOP (gave a parse error). o Removed the `make optimize' mess. o Supported two additional ways to pass objects from Smalltalk to C: #selfSmalltalk and #variadicSmalltalk, which are similar to respectively #self and #variadic but pass raw object pointers to the C function instead of attempting automatic conversions. Other Smalltalk changes: o #bindWith:... methods now accept other objects than Strings as parameters. o Complete hierarchy of exceptions, with more meaningful error message and possibility of more fine-grained exception handling. o FileStream calls are not blocking and can preempt the current Process. o FileStream handling has been rewritten; the buffering is now done by Smalltalk code rather than implied in stdio. Unbuffered file descriptor access (which used to be provided by UnixStream, defined by the TCP package) is provided by FileStream's parent, FileDescriptor. o Many methods in SystemDictionary were moved to ObjectMemory (a new class); the old ones are now deprecated. o SortedCollection's #includes:, #indexOf:, and #occurrencesOf: can check for objects that could not be inserted in the collection (e.g. an Integer in a collection of Strings). Fixed bugs in the same methods related to sort blocks for which sort-block equality (a <= b and b <= a) does not imply equality. o Support for init blocks will be removed in a future version, as it was replaced by the much more powerful ObjectMemory class. o The SystemDictionary>>#enableGC: method does not exist any more, since it only caused harm (the correct way to obtain its effect is to use the incubator, since what we want is to unregister a batch of many objects at the same time). o The TCP library does not poll the socket for I/O, but relies on the system's preemptive I/O facilities. As a result, the polling period methods in Socket have disappeared. o Usual round of bug fixes New goodies: o MD5 checksums o Perl regular expressions o Support for localization, internationalization and multiple character sets (note: must be tested more thoroughly) ----------------------------------------------------------------------------- NEWS FROM 1.8.5 TO 1.95.4 VM changes: o Added support for allocating objects with malloc so that they don't move across GCs. o Added support for `free' methods, that is, for calling methods that do not reside in a MethodDictionary or in the receiver's MethodDictionary. This can be achieved by sending #perform: with a CompiledMethod parameter. #executeStatements is now a free method. o A little more performance could derive from keeping the MethodDictionaries no more than 75% full (actually this was done to fix a discrepancy between the C-coded identityDictionaryFindKeyOrNil, which grew a full dictionary, and the Smalltalk class, which assumed that dictionaries are never full). o An object must be explicitly marked as to be finalized *every time the image is loaded*. That is, finalizability is not preserved by an image save. This was done because in most cases finalization is used together with CObjects that would be stale when the image is loaded, causing a segmentation violation as soon as they were accessed by the finalization method. o Fixed bug when #at: and #at:put: were handled by a C call-out. o Invalid C call-outs raise an error instead of simply writing to stdout. o Sending arithmetic selectors to a Float with a SmallInteger parameter (not vice versa) does not cause the primitive to fail (much faster!). o Support for a fetch/decode/execute pipeline on architectures with a lot of registers. o Works on Solaris and possibly other systems (thanks to Dirk Sodermann! I would never have caught it!!!) ANSI & cross-dialect compatibility: o DateTime and Duration classes provided. The Date class does not support 2-digit years anymore---instead, a proleptic calendar is adopted for years before 1582 (*backwards-incompatible*). o ScaledDecimal class provided; the 2.0s3 syntax for literals is supported. o Sending #asInteger to a Number `rounds' the number instead of `truncating' (*backwards-incompatible*) o Support for the #{ClassName} syntax referring to the association for the named class. Other Smalltalk changes: o A great part of the exception handling code has been rewritten. The new algorithm scans backtraces for contexts marked as storing exception handlers instead of storing the handlers' state in a Dictionary, which is smarter, faster when no exceptions are raised, and less bug prone. o BList (Blox's list box) used indices that were half 0-based, half 1-based. This caused an infinite loop if you double-clicked a BList; for this reason they have been corrected to be 1-based everywhere even if this is *backwards-incompatible*. o IMPORTANT: the preferred method for mantaining geometry in Blox has changed, as a provision for switching to other (less flexible in this respect) toolkits like GTK+. The #...Offset: methods should *not* be used anymore as they are now flagged implementation-dependant. Instead, you should use the new #inset: method, or rely more heavily on BContainers which now use the packer (in a backwards-compatible way). Relying on widget outside of the client area is also deprecated because GTK+ alignments do not allow this. o In general, the performance and stability of Blox are now more acceptable. o More ObjectDumper proxies are provided, including easy support for singletons, controlled creation of the object at load time, and versionable schemas. o ObjectDumper sends #postStore rather than #postLoad to restore an object to its previous state after storing it. For backwards compatibility, #postStore's default action is to send #postLoad. o ObjectDumper uses exception handling to ensure that #postStore (see above) is sent to an object that was sent #preStore. o Sets support arithmetic; to avoid this to propagate into Dictionary, a new common superclass of Dictionary and Set (HashedCollection) has been created. o Usual round of bug fixes New goodies: o Enhanced and refactored socket library, including support for multiple address families, UDP servers, out-of-band data and ICMP sockets. o GDBM interface works again and has a nice Dictionary-like layer. o LargeArray classes which obtain optimal memory consumption (at the expense of O(log n) access). o Smalltalk code pretty printer o SUnit tool for writing test suites (missing: a nicer user interface). o The command-line interface supports readline's completion (for filenames, globals, and method keywords) o The VisualWorks XML parser is now included. It will gradually replace the InDelv parser (2.0 will include the InDelv parser, but its usage will be deprecated). The reasons are that the VW parser is more modern (it is validating and supports namespaces), it is more actively mantained, and there is an open-source XSL processor that uses it. o Web server (needs more testing, but is relatively stable) Packaging and other external changes: o Automake is used to mantain makefiles more easily; the library is now in a `libgst' directory rather than `lib'. o At last, there is a new module system using libtool to build modules as shared dynamic libraries. Old-style support for portable dlopening has also been superseded by libltdl. This scheme is incompatible with the old one. o HTML documentation can be built. A custom version of texi2html is included which produces very pretty output. o Moved Emacs interface and CPP implementation to an `unsupported' directory. o The configuration file is not installed anymore o The class reference has indices and cross-references o Using libtool gives the benefit of versioning libgst. The current version is 1:0:0 (there is no cfuncs.h file anymore, hence the age of 0). ------------------------------------------------------------------------------- NEWS FROM 1.8.4 TO 1.8.5 o Had forgotten to bump up version number. o The position where we allocate the heap is now found at startup rather than when configuring, to deal (for example) with the presence of more shared libraries. The test has been made more portable and checks whether pages had already been mapped. ------------------------------------------------------------------------------- NEWS FROM 1.8.3 TO 1.8.4 o Added autoconf test to find where to mmap the heap. o Documented new mailing list (help-smalltalk@gnu.org) o Removed (as announced in 1.8.3) the ByteMemory and WordMemory classes. o Supported { ... } syntax for creating Arrays without sending #with:... (Squeak also has them on LHS, but this is seldom used). ------------------------------------------------------------------------------- NEWS FROM 1.8.2 TO 1.8.3 This is a bug-fix release. o Better Tcl/Tk autoconf test provided o ByteMemory and WordMemory are now deprecated. References to it have been removed from the manual; the code will be took out soon o DLD functions are relinked correctly when an image is restored ------------------------------------------------------------------------------- NEWS FROM 1.8.1 TO 1.8.2 This release was provided mostly as a means to synchronize with other Smalltalk dialects with regard to exception handling, and to provide a version that could run the SUnit test system. In the meanwhile, several bugs were fixed. o A few SortedCollection bugs fixed. o ANSI Exceptions provided. The only backwards-incompatible change is that the old Exception and ExceptionCollection classes are now called CoreException and ExceptionSet, respectively. Should cause little problems (if any). o Fix to the VM: not understood messages don't overwrite the method cache o Fixed bug in re-linking dynamically linked functions at image startup. o More stable in low-water conditions o OSes without /dev/zero supported ------------------------------------------------------------------------------- NEWS FROM 1.8 TO 1.8.1 I just received this patch for a gst-config script and could not wait publishing it!!! This version also modifies install-pkg to be more flexible; it is now called gst-package and installs in the binary directory. ------------------------------------------------------------------------------- NEWS FROM 1.7.5 TO 1.8 When I took over mantainance, I decided that increasing the second version number would have meant a mountain of changes and improvements in GNU Smalltalk's speed and flexibility. This is not the case with the step from 1.7.5 to 1.8, which only includes some things that I had written a few months ago and, until now, had only been in the development version. The reason is that 1.7.x was, overall, an unlucky series, crippled with bugs and packaging problems. I admit my faults, I apologize, and seek forgiving from you. :-/ I had little free time, and devoted most of it to 2.0's development instead of being more careful with the stable versions. Recently, when university courses ended, I had more free time available, and was able to fix a lot of these problems (many thanks, among others, to Albert Wagner). Hoping that changing the second version number ends the 1.7.x bug saga (in Italy 17 is believed to be an unlucky number, just like 13 in the US), I am releasing this version as 1.8. The changes from the development version that I had mentioned include: o DLD supports BeOS. o Execution times for SortedCollection are O(n log n) rather than O(n^2), and are amortized so that long runs of adds are the same as a single #addAll: o Working growable object table (OOP table in Blue Book parlance), thanks to the new memory allocator (which can handle separate sbrk-like regions). ------------------------------------------------------------------------------- NEWS FROM 1.7.4 TO 1.7.5 o Abort compilation if a method turns out to be too complex for the bytecode set (e.g. if it jumps too far). Previously, erroneous code was generated. o Fixed bug in LargeIntegers which broke gst on HP-UX (and possibly other OSes which load programs high in memory) o Fixed bug in parsing #( () ), where empty inner arrays were parsed to nils o Fixed crash in parsing #[] o Support LinuxPPC which loses on va_arg(..., char) ------------------------------------------------------------------------------- NEWS FROM 1.7.3 TO 1.7.4 o Adopted GNU Free Documentation License o Fixed bogus errors on big-endian machines o Fixed a few (innocuous) typos o Fixed bug in configure o Fixed bug in redefining a class that had pool dictionaries (caused crash on first compile!) o TCP ignores SIGPIPE on writing to a socket ------------------------------------------------------------------------------- NEWS FROM 1.7.1 TO 1.7.3 (1.7.2 was retired because of a packaging problem) o Adopted Lesser General Public License o Fixed crash on sends to super from a block o Finally fixed the installer after years of struggle... o In C call-outs, ByteArrays passed as Strings are considered null-terminated, and Strings passed as ByteArrays are not. This allows more interoperability between ByteArrays and Strings; the choice of whether to truncate them to the first null is left to the library (which uses #defineCFunc:...), not to the user. o Time zone support o Various Delay-related bug fixes ------------------------------------------------------------------------------- NEWS FROM 1.7 TO 1.7.1 o Fixed bug when left shifting -1 o Fixed bug when returning from non-existent method context o Test suite was broken (`.ok' files were not up to date) ------------------------------------------------------------------------------- NEWS FROM 1.6.2 TO 1.7 Changes to the VM: o #at: and #at:put: implementations don't retrieve the instance specification twice. o Growable object table (OOP table in Blue Book parlance) allows to use huge data structures---not working yet... I have to find a way to reserve memory without allocating it. o New structures for contexts and BlockClosure makes it possible to do things faster, creating BlockClosure objects at compilation time and simplifying the VM's job when blocks are particularly well-behaved (so called `clean' blocks). Now there are four levels of block optimization: - inlining (always been there) - `clean' (no refs. to self, to instance variables, to temporaries that reside in outer contexts, no method returns) - `self-contained' (can reference self or instance variables) - `full' (can do everything) o Number of arguments is checked in #perform:... o More polite behavior: when a Process object yields control, the virtual machine automatically goes to sleep for a millisecond to give more occasions to run to the other processes running on the operating system. o Blocks store their bytecodes in a separated CompiledBlock object. o The image no longer has to store all the pointers to the global OOPs (classes, symbols, Processor,...) Instead the program is able to rebuild the pointers after the image has been loaded. This should make the image format for future versions more stable. o The method header is cached together with the method OOP. o Using various dirty tricks increased the interpreter's speed; they include caching the number of the primitive which #at:/#at:put:/#size called last time, avoiding to retrieve instance specifications twice, and specially handling cases where execution is surely LIFO. o You can read and write 32-bit LargeIntegers (64-bit on Alphas) to word objects, to the Memory object and to C objects. Other changes to the C code: o `configure' macros specific to GNU Smalltalk are split in several small .m4 files that are then automatically grouped in aclocal.m4 o DLD interface to AIX o Floating point operations with infinity/NaN work fine with FreeBSD. o Full open-coding of control structures (including #whileTrue, #whileFalse, #repeat) o Maximum number of instance variables is now 262143 (ANSI mandates 65535) Not so useful anyway until we add bytecodes that access variables whose index exceeds 63... o New -K option to load file from the shared files path (useful for Load.st, for example). o Option parsing now more similar to getopt and getopt_long's (-- does not mean `standard input', but `no more options'). o Parameter checking in callins from C to Smalltalk. o Support for ByteArrays in Smalltalk code, like #[1 2 3]. ^ ^ o Support for forward references through the Undeclared dictionary. o Support for large integers in Smalltalk code, like 16r800000000000. o Support for sharps inside array constants, like #(1 #(2 3) 4). ^ o Support for the [ :a :b || c d e | ... ] syntax. ^^ o Support for the #(1 2 3 #a #b #'cdef' 45) syntax for Symbols ^^ ^^ ^^^^^^^ o Support for the 1.0d32 and 1.0q254 ANSI syntaxes for Floats ^ ^ o The parser uses GNU's winning obstacks to avoid memory leaks (important because large integers are passed to the parser into a structure that is created on the heap, and freeing it at the appropriate points was pretty hard). Changes to the Smalltalk system (new classes, etc.): o Class TranscriptInterface changed its name to TextCollector o Easy to use weak collections are included in the basic image o File-outs without exclamation marks are readable from other Smalltalks too (that was a bug). As for exclamation marks, please wait a bit more; I can do that only between two versions whose image files are compatible (otherwise I'd break all the code that you wrote...) o Methods know about the class to which they belongs and about their selector. o Mutation of existing instances is done with a trick that allows the original instances to preserve their original instance specification during the mutation process; the result is simpler and (I hope) more stable code. o Namespaces (yeah!) o New CharacterArray class (superclass of String) is a provision for multilingual support... o New LookupTable class: it behaves like Dictionary but it is represented as an IdentityDictionary; not in the Book but is quite standard o New MethodDictionary class avoids crashes caused by partially updated or inconsistent method dictionaries. o Printing `for the programmer' and printing `for the user' are separated. The former is accomplished by the familiar #printOn: and #printString family; the latter is accomplished by the new #display... family of methods. o Restored LookupKey now that I finally figured out what it was meant to do. o Small integers are now instances of SmallInteger (used to be Integer). Changes to BLOX and the GUI: Blox has undergone major improvements in this release. Many more features of Tk have been implemented, making it a lot more powerful especially in the creation of mega-widgets. o BImage reads XPM files; some images are available as BImage class methods o BLabels do word wrapping. o Browsers support namespaces o Callbacks in BEdit controls. o Canvases handle child windows, images and scrolling o If possible, different short-cut letters are chosen for items in the same menu o Controls with two scroll bars look better; in addition the user can force scroll bars to appear and disappear on the fly (previously the widget code hard-coded their presence or absence). Finally, scroll bars are hidden automatically when they are not needed. o Images in a text widget o Many more methods for miscellaneous features (some interesting ones are Blox class>>#atMouse to get the widget under the mouse, #fontWidth:, #fontHeight: and Blox class>>#fonts to measure and enumerate fonts, Blox class>>#createColor:saturation:value: for HSV colors). o New BEventSet class to assign the same event handlers to many widgets o New (private) BPopupWindow class allows to create popup widget (drop-down lists and balloons, and lots of other possible uses!); it is easily used by sending #new to a widget class (a `should not implement' error was issued in previous versions). o Some extended widgets are included in Blox as useful examples (progress bar, drop-down lists, balloon help). o Source more commented (but not enough yet...) o Syntax highlighting New goodies: o Lisp and Prolog (!) interpreters by Aoki Atsushi & Nishihara Satoshi o HTML/XML parser and World Wide Web Consortium's Document Object Model o TCP/UDP layer ------------------------------------------------------------------------------- NEWS FROM 1.6.1 TO 1.6.2 o Can load images produced by system with similar sizeof(long) but different endianness. o Class reference now includes a beautiful class hierarchy. o DLD class always present (even where it is not functional). This prevents `undeclared variable' errors in code using DLD where it is not supported (they will have a run-time error instead). o DLD interface to libtool's libltdl.a o DLD tries to append sensed extensions to the passed filename o Fixed more bugs in the makefiles o Fixed parse error :-( on some systems in sysdep.c (I'm sorry for the problems that this caused to so many of you). o GNU make is not needed anymore o More logical and coherent policy to look for the image file. In 1.6.1 we chose a default path, and overridden it if an image was found in the current directory: the problem was that snapshots were *always* saved to the default path! Now, instead, we choose a path for the image directly. o Now uses the `missing' shell script if bison and makeinfo aren't found o Readline interface is enabled by default. ------------------------------------------------------------------------------- NEWS FROM 1.6 TO 1.6.1 o Fixed bug in the makefiles (install target) o GNU qsort is provided ------------------------------------------------------------------------------- NEWS FROM 1.1.5 TO 1.6 The versioning scheme has changed - I didn't need three version numbers, I even wonder when and if I'll change the first. Also the mantainer has changed, from the great Steve Byrne to yours truly Paolo Bonzini. Changes to the VM: o Blocks are now real closures. This had a lot of side effects. For in- stance, context realization now happens only after a GC, making GCs much less common. o #==, #notNil and #isNil are optimized out by the bytecode interpreter. o Ctrl-C interrupts and bytecode interpreting errors (`boolean instance required') now do callbacks to Smalltalk. o Faster &&-based dispatch for GCC (to disable it, define USE_OLD_DISPATCH). o Methods that simply return a constant (i.e. ^6 or ^#(1 2 3) or ^nil) are now optimized like methods that return self or an instance variable. o More inlining in the C code. o More than 64 literals (16384) supported. o Open-coded relational operators (plus #isNil and #notNil) try to look for a jump bytecode immediately following them, and directly do that jump (only for GCC new dispatch) o Overflow detection in Integer primitives. o Sends to super are now handled outside sendMessage so that sendMessage does not have to choose its behavior at run-time (it was testing a parameter that is always a constant). o Support for breakpoints. o Support for finalizable objects. o Support for readonly objects. o Support for weak objects. o The GC code now does not analyze OOP slots which are surely free. This change made it up to five times faster. o The GC code now skips unused (beyond the stack pointer) slots of a context object. o The OOP table now has a free list (+200% speed with this!!). o The size of context stacks depends on the complexity of its method's code o The symbol table is hashed better (the new hash is based on John Boyer's). o The VM has more error handling built in: this includes passing integers where real OOPs were expected, detecting wrong number of arguments passed to blocks, trapping negative sizes passed to #new:, etc. o #to:do:, #to:by:do:, #timesRepeat: and #yourself are optimized out by the bytecode compiler. Other changes to the C code: o _ inside an identifier is now valid. Note that, in Squeak, _ always identifies the assignment operator, even in code like a_b, while GST allowed something like a:=b, but a_b was a syntax error. Use of _ inside identifiers is common in other Smalltalks to avoid namespace clashes for automatically generated code. o New command line switch -a: the C code never gets everything after -a, while Smalltalk code gets only those arguments that are past -a. o New command line switch -Q: produce absolutely no message. o New command line switch -S: automatically save a snapshot before exiting. o New system to include user modules, works like this: ./modules blox make To use it, model your Makefile.body and cfuncs.h after those in the blox or tcp directories. If you want to have many versions, proceed like this: ./modules blox; make; mv gst blox/gst ./modules; make; mv gst base_gst ./modules blox tcp; make and you'll have blox/gst with only blox; base_gst with nothing; gst with blox and tcp. o Portability: now compiles under CygWin (Win32 GCC), HPUX and more. o Precise Win32 version of Delay. o Support for long GNU style options. o The compiled bytecodes are now ran through an optimizer that performs jump and peephole optimizations, and eliminates unreachable code. Changes to the Smalltalk system (new classes, etc.): o Added ability to access the Smalltalk arguments; Smalltalk can get arguments that follow -a through the SystemDictionary>>#arguments method. o Added a thread-safe Transcript object which prints to stdout if the GUI is not loaded and which is used by #print, #printNl and companions. o Added binary dump of Smalltalk objects (class ObjectDumper). o Added endian-neutral binary I/O to FileStream through the new ByteStreams. o Added fast ByteStreams, specially crafted for ByteArrays, which can be used with ObjectDumper. o Added ContextPart (superclass of MethodContext and BlockContext). o Added DirectedMessage. o Added file-handling classes (File and Directory). o Added IdentitySets. Also, most of the Set hierarchy has been refactored and rewritten for better speed and design. o Added LargeIntegers. LargeInteger literals can't be used in Smalltalk code yet, though. o Added optional automatic freeing of CObjects (through finalization) and automatic closing of FileStreams. o Added RunArrays. o Added three subclasses of CObject: CSmalltalk, CInt, CUInt (and analogous messages to the Memory class). o Added useful functionality to Date. o Added ValueAdaptors. o Added #zero and #unity in Number; they make a few operations a bit faster if you override them in subclasses (it is not necessary though). o #allInstances now returns a weak object, thus avoiding that a call to it forces GST to keep lots of unused objects in the heap. o A lot of messages have been added to most classes. o An implementation of a great idea by Andreas Klimas: a packaging system which automatically handles prerequisites and tests availability of C call-outs. o #asSortedCollection: now uses quicksort. o ByteArrays now support accessing shorts, longs, ints, etc. o CObjects are now variable word classes (try 'stdout store' in 1.1.5!!) o Code for mutating existing class has been merged from the BLOX directory. o DLD (dynamic loading of C modules) is now a `first class' package, included in the image wherever it is available. Architectures supported (besides GNU DLD, available in 1.1.5 too) include Linux (dlopen), HP/UX and Win32. o FileStreams detect when they have been closed and refuse to do any more o- perations - this shields Smalltalk programs from C's quirks and bugs. o Fixed millisecondClock and secondClock to use correct Blue Book semantics. o Float is now a variable byte class. o Float now handles NaN and infinity values correctly. o Some fixes to Point and Rectangle. o Many fixes in PositionableStream. For example, #upToAll: and #skipToAll:. now don't seek back in the stream, and hence are usable with stdin. o Methods are not `special' objects anymore o Most of the Smalltalk code is now commented. o Removed LookupKey. o SortedCollection now uses binary search in #indexOf:, #occurrencesOf: and #add:. o Support for class-instance variables (at last!). o Support for class declarations like "nil subclass: #XXX ..." (at last!). o Support for fixed instance variables in non-pointer classes o Support for the almost standard message #copyEmpty: (with the colon!). o System classes now have a category. o The kernel now uses := (even though of course _ is still supported). o The results of most character operations are now precalculated. o The Smalltalk-in-Smalltalk compiler, even though is slow, works quite well and supports #[1 2 3 4] ByteArray and LargeInteger literals. Bug reports for the compiler are MUCH appreciated!! Please include code that is as short as possible. o WriteStreams now double the size of the collection they stream on when there's no more space. Changes to BLOX and the GUI: o Added a Transcript window. Also, the Smalltalk menu is now part of every window. o Added support for standard color selection and file selection dialogs. o BLOX now has a comprehensive test suite. o Completely rewritten, 99% Smalltalk code now, working across different platforms because it relies on Tcl/Tk, with advanced Tk features such as: - X11 color names. Also, colors can now be passed with strings like '#0080FF' or '#1234789ADEF0' ('#RRRRGGGGBBBB'). - event handling (including focus in/out, mouse enter/leave, key press/release, button press/drag/release/double click/triple click) - a much better text widget, with support for text with different attributes in the same widget - a new canvas widget for vector graphics - will somebody ever contribute a nice Asteroids for GST??? o The Class Hierarchy Browser shows classes not derived from Object. o The hierarchy for the BLOX toolkit is better designed (since I'm now implementing it in Smalltalk, if I had not done it I would have had a lot of duplicated code). o The new GUI system is not 100% compatible with the old one, partly because it now uses Tk and partly because of a few design decisions that were, to say the least, questionable. Check your old code where it sets the geometry and where it passes the gui CObject to a method (in this case, just remove the first parameter). smalltalk-3.2.5/examples/0000755000175000017500000000000012130456010012314 500000000000000smalltalk-3.2.5/examples/LazyCollection.st0000644000175000017500000002612512123404352015551 00000000000000"====================================================================== | | Lazy implementation of #select:/#collect:/#reject: | | ======================================================================" "====================================================================== | | Copyright 2006 Free Software Foundation, Inc. | Written by Paolo Bonzini. | | This file is part of GNU Smalltalk. | | GNU Smalltalk is free software; you can redistribute it and/or modify it | under the terms of the GNU General Public License as published by the Free | Software Foundation; either version 2, or (at your option) any later version. | | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS | FOR A PARTICULAR PURPOSE. See the GNU General Public License for more | details. | | You should have received a copy of the GNU General Public License along with | GNU Smalltalk; see the file COPYING. If not, write to the Free Software | Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. | ======================================================================" "This example modifies the common iteration protocol for Collections, i.e. #select:/#collect:/#reject:, so that no new collection is created. The blocks are saved until the collection is absolutely necessary. Until you ask something from the collection, no operation is done and the chain of selection/collection/rejection operators is kept. Moreover, even iteration with #do:, #fold:, #allSatisfy:, and so on does not create a new collection (which can be a mixed blessing of course, because the blocks may be evaluated many times). To get a collection from the proxy, just send it asCollection." Object subclass: #CollectionFilter instanceVariableNames: 'prev' classVariableNames: '' poolDictionaries: '' category: 'Examples-Collections'! CollectionFilter subclass: #BlockCollectionFilter instanceVariableNames: 'block' classVariableNames: '' poolDictionaries: '' category: 'Examples-Collections'! BlockCollectionFilter subclass: #SelectFilter instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Examples-Collections'! BlockCollectionFilter subclass: #RejectFilter instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Examples-Collections'! BlockCollectionFilter subclass: #CollectFilter instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Examples-Collections'! nil subclass: #CollectionProxy instanceVariableNames: 'collection filter' classVariableNames: '' poolDictionaries: '' category: 'Examples-Collections'! CollectionProxy subclass: #ArrayedCollectionProxy instanceVariableNames: 'stream' classVariableNames: '' poolDictionaries: '' category: 'Examples-Collections'! CollectionProxy subclass: #DictionaryProxy instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Examples-Collections'! !CollectionFilter class methodsFor: 'instance creation'! on: anObject ^self new initialize: anObject! !CollectionFilter methodsFor: 'applying'! map: anObject ifRemovedReturn: removedMarker | newObject | newObject := prev isNil ifTrue: [ anObject ] ifFalse: [ prev map: anObject ifRemovedReturn: removedMarker ]. newObject == removedMarker ifTrue: [ ^removedMarker ]. ^self value: newObject ifRemovedReturn: removedMarker! value: anObject ifRemovedReturn: removedMarker self subclassResponsibility! sizeFrom: aCollection ^nil! ! !CollectionFilter methodsFor: 'querying classes'! copyEmpty: collection ^prev isNil ifTrue: [ collection copyEmpty ] ifFalse: [ prev copyEmpty: collection ]! copyEmpty: collection size: size ^prev isNil ifTrue: [ collection copyEmpty: size ] ifFalse: [ prev copyEmpty: collection size: size ]! !CollectionFilter methodsFor: 'initializing'! initialize: prevFilter prev := prevFilter! ! !BlockCollectionFilter class methodsFor: 'instance creation'! on: anObject value: aBlock ^(self on: anObject) block: aBlock! !BlockCollectionFilter methodsFor: 'accessing'! value: anObject ifRemovedReturn: removedMarker ^block value: anObject! !BlockCollectionFilter methodsFor: 'initialization'! block: aBlock block := aBlock! ! !SelectFilter methodsFor: 'applying'! value: anObject ifRemovedReturn: removedMarker ^(super value: anObject ifRemovedReturn: removedMarker) ifFalse: [ removedMarker ] ifTrue: [ anObject ]! ! !RejectFilter methodsFor: 'applying'! value: anObject ifRemovedReturn: removedMarker ^(super value: anObject ifRemovedReturn: removedMarker) ifTrue: [ removedMarker ] ifFalse: [ anObject ]! ! !CollectFilter methodsFor: 'applying'! sizeFrom: aCollection ^prev isNil ifTrue: [ aCollection size ] ifFalse: [ prev sizeFrom: aCollection ]! ! !CollectFilter methodsFor: 'querying classes'! copyEmpty: collection ^collection copyEmptyForCollect! copyEmpty: collection size: size ^collection copyEmptyForCollect: size! ! !CollectionProxy class methodsFor: 'instance creation'! on: collection filter: filter ^self new initializeCollection: collection filter: filter; yourself! ! !CollectionProxy methodsFor: 'basic object protocol'! == anObject ! ~~ anObject ^(self == anObject) not ! = anObject ! ~= anObject ^(self = anObject) not ! class self primitiveFailed ! hash ! yourself ^self ! become: otherObject ^SystemExceptions.ReadOnlyObject signal ! copy ^self! shallowCopy ^self! deepCopy ^self asCollection! ! !CollectionProxy methodsFor: 'proxying'! doesNotUnderstand: aMessage ^self asCollection perform: aMessage! asCollection | builtCollection marker | builtCollection := filter copyEmpty: collection. marker := Object new. collection do: [ :each || newObject | newObject := filter map: each ifRemovedReturn: marker. newObject == marker ifFalse: [ builtCollection add: newObject ] ]. ^self become: builtCollection! size ^(filter sizeFrom: collection) ifNil: [ self asCollection size ]! !CollectionProxy methodsFor: 'iterating'! allSatisfy: aBlock | marker | marker := Object new. collection do: [ :each || newObject | newObject := filter map: each ifRemovedReturn: marker. newObject == marker ifFalse: [ (aBlock value: newObject) ifFalse: [ ^false ] ] ]. ^true! anySatisfy: aBlock | marker | marker := Object new. collection do: [ :each || newObject | newObject := filter map: each ifRemovedReturn: marker. newObject == marker ifFalse: [ (aBlock value: newObject) ifTrue: [ ^true ] ] ]. ^false! conform: aBlock ^self allSatisfy: aBlock! contains: aBlock ^self anySatisfy: aBlock! detect: aBlock ifNone: exceptionBlock | marker | marker := Object new. collection do: [ :each || newObject | newObject := filter map: each ifRemovedReturn: marker. newObject == marker ifFalse: [ (aBlock value: newObject) ifTrue: [ ^newObject ] ] ]. ^exceptionBlock value! detect: aBlock ^self detect: aBlock ifNone: [ SystemExceptions.NotFound signal: 'object not found' ]! do: aBlock | marker | marker := Object new. collection do: [ :each || newObject | newObject := filter map: each ifRemovedReturn: marker. newObject == marker ifFalse: [ aBlock value: newObject ] ]! fold: aBlock | obj marker first | first := true. marker := Object new. collection do: [ :each || newObject | newObject := filter map: each ifRemovedReturn: marker. newObject == marker ifFalse: [ obj := first ifTrue: [ newObject ] ifFalse: [ aBlock value: obj value: newObject ]. first := false ] ]. first ifTrue: [ ^SystemExceptions.EmptyCollection signalOn: self ]. ^obj! inject: anObject into: aBlock | obj marker | obj := anObject. marker := Object new. collection do: [ :each || newObject | newObject := filter map: each ifRemovedReturn: marker. newObject == marker ifFalse: [ obj := aBlock value: obj value: newObject ] ]. ^obj! ! !CollectionProxy methodsFor: 'nesting'! select: aBlock ^self class on: collection filter: (SelectFilter on: filter value: aBlock)! reject: aBlock ^self class on: collection filter: (RejectFilter on: filter value: aBlock)! collect: aBlock ^self class on: collection filter: (CollectFilter on: filter value: aBlock)! ! !CollectionProxy methodsFor: 'initializing'! initializeCollection: aCollection filter: aCollectionFilter collection := aCollection. filter := aCollectionFilter! ! !ArrayedCollectionProxy methodsFor: 'proxying'! readStream | stream marker size | stream isNil ifTrue: [ marker := Object new. stream := WriteStream on: (filter copyEmpty: collection). collection do: [ :each || newObject | newObject := filter map: each ifRemovedReturn: marker. newObject == marker ifFalse: [ stream nextPut: newObject ] ] ]. ^stream readStream! asCollection | builtCollection marker n size | (stream notNil or: [ (size := filter sizeFrom: collection) isNil ]) ifTrue: [ ^self become: self readStream contents ]. marker := Object new. builtCollection := filter copyEmpty: collection size: size. n := 0. collection do: [ :each || newObject | newObject := filter map: each ifRemovedReturn: marker. newObject == marker ifFalse: [ builtCollection at: (n := n + 1) put: newObject ] ]. ^self become: builtCollection! ! !DictionaryProxy methodsFor: 'proxying'! asCollection | builtCollection marker | builtCollection := filter copyEmpty: collection. marker := Object new. collection keysAndValuesDo: [ :key :each || newObject | newObject := filter map: each ifRemovedReturn: marker. newObject == marker ifFalse: [ builtCollection at: key put: newObject ] ]. ^self become: builtCollection! ! !Collection methodsFor: 'iterating'! select: aBlock ^CollectionProxy on: self filter: (SelectFilter on: nil value: aBlock)! reject: aBlock ^CollectionProxy on: self filter: (RejectFilter on: nil value: aBlock)! collect: aBlock ^CollectionProxy on: self filter: (CollectFilter on: nil value: aBlock)! ! !ArrayedCollection methodsFor: 'iterating'! select: aBlock ^ArrayedCollectionProxy on: self filter: (SelectFilter on: nil value: aBlock)! reject: aBlock ^ArrayedCollectionProxy on: self filter: (RejectFilter on: nil value: aBlock)! collect: aBlock ^ArrayedCollectionProxy on: self filter: (CollectFilter on: nil value: aBlock)! ! !Dictionary methodsFor: 'iterating'! select: aBlock ^DictionaryProxy on: self filter: (SelectFilter on: nil value: aBlock)! reject: aBlock ^DictionaryProxy on: self filter: (RejectFilter on: nil value: aBlock)! collect: aBlock ^DictionaryProxy on: self filter: (CollectFilter on: nil value: aBlock)! ! smalltalk-3.2.5/examples/Tetris.st0000644000175000017500000003430012123404352014062 00000000000000"====================================================================== | | BLOX Tetris... why not? | | ======================================================================" "====================================================================== | | Copyright 1999 Free Software Foundation, Inc. | Written by Paolo Bonzini. | | This file is part of GNU Smalltalk. | | GNU Smalltalk is free software; you can redistribute it and/or modify it | under the terms of the GNU General Public License as published by the Free | Software Foundation; either version 2, or (at your option) any later version. | | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS | FOR A PARTICULAR PURPOSE. See the GNU General Public License for more | details. | | You should have received a copy of the GNU General Public License along with | GNU Smalltalk; see the file LICENSE. If not, write to the Free Software | Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. | ======================================================================" PackageLoader fileInPackage: 'Blox'! Namespace current: BLOX! Object subclass: #TetrisField instanceVariableNames: 'canvas rows currentPiece nextPiece' classVariableNames: '' poolDictionaries: '' category: 'Graphics-Tetris'! Object subclass: #TetrisPiece instanceVariableNames: 'positions blocks rotation color origin' classVariableNames: 'BlockSize Pieces' poolDictionaries: '' category: 'Graphics-Tetris'! Object subclass: #Tetris instanceVariableNames: 'pause delay level grid movingBlocks window statsWindow scoreLabel levelLabel linesLabel button canvas' classVariableNames: '' poolDictionaries: '' category: 'Graphics-Tetris'! !TetrisField methodsFor: 'accessing'! at: point ^(rows at: point y) at: point x ! at: point put: value ^(rows at: point y) at: point x put: value ! ! !TetrisField class methodsFor: 'instance creation'! new: canvas ^self basicNew initialize: canvas ! !TetrisField methodsFor: 'initializing'! initialize: aBCanvas canvas := aBCanvas. rows := (1 to: 28) collect: [ :each | ByteArray new: 14 ]. rows do: [ :each | self initializeLine: each. ]. (rows at: 25) atAllPut: 1. ! initializeLine: line line at: 1 put: 1; at: 2 put: 1; atAll: (3 to: 12) put: 0; at: 13 put: 1; at: 14 put: 1 ! ! !TetrisField methodsFor: 'removing filled lines'! checkLine: y ^(rows at: y) allSatisfy: [ :each | each ~~ 0 ] ! removeLines | removed lastLine firstLine | removed := 0. firstLine := self currentPiece y. lastLine := 24 min: firstLine + 3. lastLine - firstLine + 1 timesRepeat: [ (self checkLine: lastLine) ifTrue: [ removed := removed + 1. self removeLine: lastLine. ] ifFalse: [ lastLine := lastLine - 1 ] ]. ^removed ! removeLine: filledY | saved y shift line | saved := rows at: filledY. filledY to: 2 by: -1 do: [ :each | rows at: each put: (rows at: each - 1) ]. self initializeLine: saved. rows at: 1 put: saved. "Now take care of the canvas" y := filledY * TetrisPiece blockSize. shift := 0 @ TetrisPiece blockSize. line := Rectangle origin: -1 @ (y + 2) corner: (15 * TetrisPiece blockSize) @ (y + 4). canvas items do: [ :each | each origin y < line origin y ifTrue: [ each corner y > line corner y ifTrue: [ each remove ] ifFalse: [ each moveBy: shift; redraw ] ] ]. ! ! !TetrisField methodsFor: 'moving pieces'! dropPiece [ self slidePiece ] whileTrue: [ ] ! movePieceLeft self currentPiece x: self currentPiece x - 1. ^self currentPiece moveInto: self ifFail: [ self currentPiece x: self currentPiece x + 1 ]. ! movePieceRight self currentPiece x: self currentPiece x + 1. ^self currentPiece moveInto: self ifFail: [ self currentPiece x: self currentPiece x - 1 ]. ! rotatePiece self currentPiece rotate: 1. ^self currentPiece moveInto: self ifFail: [ self currentPiece rotate: 3 ]. ! slidePiece self currentPiece y: self currentPiece y + 1. ^self currentPiece moveInto: self ifFail: [ self currentPiece y: self currentPiece y - 1 ]. ! ! !TetrisField methodsFor: 'accessing piece variables'! currentPiece ^currentPiece ! currentPiece: piece currentPiece := piece. self currentPiece x: 4; y: 1. ! nextPiece ^nextPiece ! nextPiece: piece nextPiece := piece. ! ! !TetrisPiece class methodsFor: 'pieces'! blockSize ^12 ! initialize "Initialize the class variables" BlockSize := self blockSize. Pieces := (Array new: 7) at: 1 put: (TetrisPiece new color: 'DarkKhaki' initialize: self pieceL); at: 2 put: (TetrisPiece new color: 'Magenta' initialize: self pieceInvertedL); at: 3 put: (TetrisPiece new color: 'Red' initialize: self pieceSkinny); at: 4 put: (TetrisPiece new color: 'BlueViolet' initialize: self pieceBlock); at: 5 put: (TetrisPiece new color: 'Cyan' initialize: self pieceSlash); at: 6 put: (TetrisPiece new color: 'DarkOrange' initialize: self pieceBackslash); at: 7 put: (TetrisPiece new color: 'ForestGreen' initialize: self pieceT); yourself ! pieceL ^#( (0 0 0 0) (0 0 0 0) (0 0 0 0) (0 0 0 0) (0 0 0 0) (0 8 8 0) (0 0 0 0) (0 0 8 0) (8 8 8 0) (0 8 0 0) (8 0 0 0) (0 0 8 0) (0 0 8 0) (0 8 0 0) (8 8 8 0) (0 8 8 0)) ! pieceInvertedL ^#( (0 0 0 0) (0 0 0 0) (0 0 0 0) (0 0 0 0) (0 0 0 0) (8 0 0 0) (0 0 0 0) (8 8 0 0) (8 8 8 0) (8 0 0 0) (0 0 8 0) (0 8 0 0) (8 0 0 0) (8 8 0 0) (8 8 8 0) (0 8 0 0)) ! pieceSkinny ^#( (0 8 0 0) (0 0 0 0) (0 8 0 0) (0 0 0 0) (0 8 0 0) (0 0 0 0) (0 8 0 0) (0 0 0 0) (0 8 0 0) (8 8 8 8) (0 8 0 0) (8 8 8 8) (0 8 0 0) (0 0 0 0) (0 8 0 0) (0 0 0 0)) ! pieceBlock ^#( (0 0 0 0) (0 0 0 0) (0 0 0 0) (0 0 0 0) (0 8 8 0) (0 8 8 0) (0 8 8 0) (0 8 8 0) (0 8 8 0) (0 8 8 0) (0 8 8 0) (0 8 8 0) (0 0 0 0) (0 0 0 0) (0 0 0 0) (0 0 0 0)) ! pieceSlash ^#( (0 0 0 0) (0 0 0 0) (0 0 0 0) (0 0 0 0) (0 0 8 0) (0 0 0 0) (0 0 8 0) (0 0 0 0) (0 8 8 0) (8 8 0 0) (0 8 8 0) (8 8 0 0) (0 8 0 0) (0 8 8 0) (0 8 0 0) (0 8 8 0)) ! pieceBackslash ^#( (0 0 0 0) (0 0 0 0) (0 0 0 0) (0 0 0 0) (0 8 0 0) (0 0 0 0) (0 8 0 0) (0 0 0 0) (0 8 8 0) (0 8 8 0) (0 8 8 0) (0 8 8 0) (0 0 8 0) (8 8 0 0) (0 0 8 0) (8 8 0 0)) ! pieceT ^#( (0 0 0 0) (0 0 0 0) (0 0 0 0) (0 0 0 0) (0 8 0 0) (0 0 0 0) (0 0 8 0) (8 8 8 0) (0 8 8 0) (0 8 0 0) (0 8 8 0) (0 8 0 0) (0 8 0 0) (8 8 8 0) (0 0 8 0) (0 0 0 0)) ! random | piece | piece := Random between: 1 and: 7. ^(Pieces at: piece) copy ! ! !TetrisPiece methodsFor: 'initializing'! color: myColor initialize: table color := myColor. positions := Array with: (self getPiece: table index: 1) with: (self getPiece: table index: 2) with: (self getPiece: table index: 3) with: (self getPiece: table index: 4) ! getPiece: table index: index "Private - Answer an array of four points corresponding to the coordinates of the points in table which are such that table[y*4 + x + index] <> 0. table[index+12]. This is necessary so that a human being can prepare the tables..." | firstFree y position | firstFree := 1. y := 0. position := Array new: 4. index to: index + 12 by: 4 do: [ :each | firstFree := self getPiece: (table at: each) y: y blocksFrom: firstFree storeIn: position. y := y + 1 ]. ^position ! getPiece: tableLine y: y blocksFrom: firstFree storeIn: blocks "Private - Store in the blocks Array, starting at index firstFree, points with the given y and varying x, corresponding to any values <> 0 in the tableLine Array. Answer the index, >= firstFree, of the last slot filled in blocks." | i | i := firstFree. tableLine doWithIndex: [ :each :x | each = 0 ifFalse: [ blocks at: i put: x @ y. i := i + 1 ]. ]. ^i ! ! !TetrisPiece methodsFor: 'drawing'! blockSize ^BlockSize ! cementOn: field drawOn: canvas blocks do: [ :eachCoord | field at: eachCoord / self blockSize put: 1. (BRectangle new: canvas) color: self color; grayOut; origin: eachCoord extent: self blockSize asPoint; create ] ! color ^color ! drawWith: movingBlocks movingBlocks with: blocks do: [ :eachBRect :eachCoord | eachBRect origin: eachCoord extent: self blockSize asPoint; redraw. ] ! !TetrisPiece methodsFor: 'moving'! canMoveInto: field | point | point := Point new. (positions at: rotation) do: [ :position | point x: self origin x + position x; y: self origin y + position y. (field at: point) > 0 ifTrue: [ ^false ]. ]. ^true ! move blocks with: (positions at: rotation) do: [ :block :position | block x: (self origin x + position x) * self blockSize; y: (self origin y + position y) * self blockSize ]. ! moveInto: field ifFail: aBlock (self canMoveInto: field) ifFalse: [ aBlock value. ^false ]. self move. ^true ! rotate: howMany "Three lines are necessary because rotation is in the 1..4 range, while \\ likes a 0..3 range" rotation := rotation - 1. rotation := (rotation + howMany) \\ 4. rotation := rotation + 1 ! ! !TetrisPiece methodsFor: 'accessing'! origin ^origin ! x ^self origin x ! x: x self origin x: x ! y ^self origin y ! y: y self origin y: y ! ! !TetrisPiece methodsFor: 'basic'! postCopy rotation := 1. origin := Point new. blocks := Array with: Point new with: Point new with: Point new with: Point new. ! ! !Tetris class methodsFor: 'game'! new ^self basicNew layout; bindKeys: #('Left' 'Right' 'Up' 'Down' 'Return'); yourself ! play Blox dispatchEvents: self new ! ! !Tetris methodsFor: 'game'! cycle | filledLines | grid := TetrisField new: canvas. grid nextPiece: TetrisPiece random. [ grid currentPiece: grid nextPiece. grid nextPiece: TetrisPiece random. movingBlocks do: [ :each | each color: grid currentPiece color ]. "If the piece cannot move, game over!" grid slidePiece ] whileTrue: [ [ window exists ifFalse: [ ^self ]. grid currentPiece drawWith: movingBlocks. grid slidePiece ] whileTrue: [ self delay ]. grid currentPiece cementOn: grid drawOn: canvas. self resetMovingBlocks. filledLines := grid removeLines. filledLines > 0 ifTrue: [ self lines: self lines + filledLines ]. (self lines - 1) // 10 > self level ifTrue: [ self level: self level + 1 ]. self score: 2 * self level squared + (#(0 50 150 400 900) at: filledLines + 1) + self score ]. ^self ! play button label: 'Pause'. button callback: self message: #pause. self activate; score: 0; level: 1; lines: 0; resetCanvas; cycle. button callback: self message: #play. ! ! !Tetris methodsFor: 'private'! delay "I like this method a lot!" delay wait. "Especially this semaphore!!" pause wait. pause signal. ! level ^levelLabel label asInteger ! level: nextLevel | level | level := nextLevel min: 10. delay := Delay forMilliseconds: 825 - (75 * level). levelLabel label: level printString ! lines ^linesLabel label asInteger ! lines: newLines linesLabel label: newLines printString ! score ^scoreLabel label asInteger ! score: newScore scoreLabel label: newScore printString ! ! !Tetris methodsFor: 'events'! advanceLevel self level: self level + 1 ! destroyed statsWindow exists ifTrue: [ statsWindow destroy ]. window exists ifTrue: [ window destroy ]. ^true ! movePieceLeft ^grid movePieceLeft ! movePieceRight ^grid movePieceRight ! pause button label: 'Restart'. button callback: self message: #restart. "I like this semaphore a lot!" pause wait. ! restart button label: 'Pause'. button callback: self message: #pause. self activate. "I like this semaphore a lot!" pause signal. ! rotatePiece ^grid rotatePiece ! slidePiece ^grid slidePiece ! dropPiece ^grid dropPiece ! ! !Tetris methodsFor: 'user interface'! bindKeys: keys keys with: #(#movePieceLeft #movePieceRight #rotatePiece #slidePiece #dropPiece) do: [ :key :selector | canvas onKeyEvent: key send: selector to: self ]. ! layout pause := Semaphore forMutualExclusion. (window := BWindow new: 'GNU Tetris!') width: TetrisPiece blockSize * 10 height: TetrisPiece blockSize * 22. (canvas := BCanvas new: window) x: TetrisPiece blockSize * -3 y: TetrisPiece blockSize * -3 width: TetrisPiece blockSize * 14 height: TetrisPiece blockSize * 28. window map. (statsWindow := BTransientWindow new: 'Scoring' in: window) x: window x + window width + 10 y: window y width: 100 height: 150. (BLabel new: statsWindow label: 'Score') x: 0 y: 0 width: 100 height: 16. (BLabel new: statsWindow label: 'Lines') x: 0 y: 33 width: 100 height: 16. (BLabel new: statsWindow label: 'Level') x: 0 y: 66 width: 100 height: 16. (scoreLabel := BLabel new: statsWindow label: '0') x: 0 y: 17 width: 100 height: 16. (linesLabel := BLabel new: statsWindow label: '0') x: 0 y: 50 width: 100 height: 16. (levelLabel := BLabel new: statsWindow label: '0') x: 0 y: 83 width: 100 height: 16. (button := BButton new: statsWindow label: 'Start') x: 0 y: 100 width: 100 height: 23; callback: self message: #play. (BButton new: statsWindow label: 'Next level') x: 0 y: 127 width: 100 height: 23; callback: self message: #advanceLevel. statsWindow bringToTop. statsWindow callback: self message: #destroyed. window bringToTop. window callback: self message: #destroyed. ! resetCanvas canvas empty. movingBlocks := Array with: (BRectangle new: canvas) with: (BRectangle new: canvas) with: (BRectangle new: canvas) with: (BRectangle new: canvas). self resetMovingBlocks. movingBlocks do: [ :each | each create ] ! resetMovingBlocks movingBlocks do: [ :each | each origin: (-50 @ -50) extent: TetrisPiece blockSize asPoint. ]. ! window ^window ! activate window activate. canvas activate. ! ! TetrisPiece initialize! Namespace current: Smalltalk! smalltalk-3.2.5/examples/Man.st0000644000175000017500000002212412123404352013324 00000000000000"====================================================================== | | BLOX man page viewer | | ======================================================================" "====================================================================== | | Copyright 1999 Free Software Foundation, Inc. | Written by Paolo Bonzini. | | This file is part of GNU Smalltalk. | | GNU Smalltalk is free software; you can redistribute it and/or modify it | under the terms of the GNU General Public License as published by the Free | Software Foundation; either version 2, or (at your option) any later version. | | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS | FOR A PARTICULAR PURPOSE. See the GNU General Public License for more | details. | | You should have received a copy of the GNU General Public License along with | GNU Smalltalk; see the file LICENSE. If not, write to the Free Software | Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. | ======================================================================" PackageLoader fileInPackage: 'Blox'! Namespace current: BLOX! BExtended subclass: #ManViewer instanceVariableNames: 'input separator label' classVariableNames: 'OpenParenExpansions' poolDictionaries: '' category: 'Graphics-Examples'! !ManViewer class methodsFor: 'initializing'! initialize OpenParenExpansions := Dictionary new at: 'em' put: ' -- '; at: 'en' put: ' - '; at: 'lq' put: $` asString; at: 'rq' put: $' asString; yourself ! ! !ManViewer class methodsFor: 'starting'! openOn: fileName | window text | window := BWindow new. window width: 560 height: 300. text := self new: window. [ text parse: (FileStream open: fileName mode: FileStream read) ] ifCurtailed: [ window destroy ]. window label: text label. window map. Blox idle. window activate. text activate. Blox dispatchEvents: window ! ! !ManViewer methodsFor: 'accessing'! label ^label ifNil: [ 'Man page viewer' ] ! newPrimitive ^(BText new: self parent) font: self normal font; yourself ! parse: stream input := stream. separator := ''. [ stream atEnd ] whileFalse: [ self parseLine: (stream upTo: Character nl) ]. input close. input := nil. self primitive gotoLine: 1 end: false ! text: string self parse: (ReadStream on: string) ! ! !ManViewer methodsFor: 'private - gui'! label: string label := string ! insert: line fonts: fonts | attributes font | font := 2. attributes := fonts collect: [ :each | self perform: each ]. self primitive insertAtEnd: separator. separator := ''. self breakIntoArguments: line do: [ :each | font := 3 - font. self primitive insertAtEnd: (each copyWith: Character space) attribute: (attributes at: font) ] ! insertEndSpace: line fonts: fonts | attributes font | font := 2. attributes := fonts collect: [ :each | self perform: each ]. self primitive insertAtEnd: separator. separator := ''. self breakIntoArguments: line do: [ :each | font := 3 - font. self primitive insertAtEnd: each attribute: (attributes at: font) ]. self primitive space ! nl self primitive nl ! ! !ManViewer methodsFor: 'fonts'! big ^BTextAttributes font: 'Courier 9 bold italic' ! bold ^BTextAttributes font: 'Courier 9 bold' ! italic ^BTextAttributes font: 'Courier 9 italic' ! normal ^BTextAttributes font: 'Courier 9' ! separatePara ^(String new: 2) atAllPut: Character nl; yourself ! ! !ManViewer methodsFor: 'parsing'! dispatch: directive line: line "Parse a line in the format `. ' " | symbol | directive = '\"' ifTrue: [ ^self ]. symbol := ('parse', directive asUppercase, ':') asSymbol. (self class includesSelector: symbol) ifTrue: [ self perform: symbol with: line ] ! parseLine: line | directive | line isEmpty ifTrue: [ ^self ]. (line at: 1) = $. ifFalse: [ self parseQuoted: line. ] ifTrue: [ line size < 3 ifTrue: [ ^self ]. directive := (line at: 3) = Character space ifTrue: [ (line copyFrom: 2 to: 2) ] ifFalse: [ (line copyFrom: 2 to: 3) ]. self dispatch: directive line: line. ] ! breakIntoArguments: line do: aBlock | stream argument | stream := ReadStream on: line. [ stream atEnd ifTrue: [ ^self ]. stream peek isSeparator ] whileFalse: [ stream next ]. [ [ stream atEnd ifTrue: [ ^self ]. stream peek isSeparator ] whileTrue: [ stream next ]. stream atEnd ] whileFalse: [ argument := (stream peekFor: $") ifTrue: [ self upToQuote: stream ] ifFalse: [ self nextWord: stream ]. aBlock value: argument ]. ! nextWord: line | ws ch | ws := WriteStream on: (String new: 10). [ line atEnd or: [ (ch := line next) isSeparator ] ] whileFalse: [ ch = $\ ifTrue: [ self parseQuoted: line on: ws ] ifFalse: [ ws nextPut: ch ] ]. ^ws contents ! upToQuote: line | ws ch | ws := WriteStream on: (String new: 10). [ line atEnd or: [ (ch := line next) == $" ] ] whileFalse: [ ch = $\ ifTrue: [ self parseQuoted: line on: ws ] ifFalse: [ ws nextPut: ch ] ]. ^ws contents ! parseQuoted: line | stream | self primitive insertAtEnd: separator. stream := ReadStream on: line. [ stream atEnd ifTrue: [ ^self ]. stream next isSeparator ] whileTrue: [ ]. stream skip: -1. self parseQuotedStream: stream size: line size. separator := ' '. ! parseQuotedStream: stream size: size | ws ch newFont font | font := self normal. ws := WriteStream on: (String new: size). [ stream atEnd ] whileFalse: [ ch := stream next. ch = $\ ifFalse: [ ws nextPut: ch ] ifTrue: [ newFont := self parseQuoted: stream on: ws. newFont isNil ifFalse: [ self primitive insertAtEnd: ws contents attribute: font. font := self perform: newFont. ws reset. ] ] ]. self primitive insertAtEnd: (self rtrimSeparators: ws contents) attribute: font ! parseQuoted: line on: ws | ch s | line atEnd ifTrue: [ ^nil ]. ch := line next. ch == $* ifTrue: [ line atEnd ifTrue: [ ^nil ]. ch := line next ]. ch == $& ifTrue: [ ws nextPut: line next. ^nil ]. ch == $( ifTrue: [ line atEnd ifTrue: [ ^nil ]. s := String with: line next. line atEnd ifTrue: [ ^nil ]. s := s copyWith: line next. s := OpenParenExpansions at: s ifAbsent: [ ^nil ]. ws nextPutAll: s. ^nil ]. ch == $c ifTrue: [ ^nil ]. ch == $d ifTrue: [ ^nil ]. ch == $^ ifTrue: [ ^nil ]. ch == $| ifTrue: [ ^nil ]. ch == $e ifTrue: [ ws nextPut: $\. ^nil ]. ch == $f ifTrue: [ line atEnd ifTrue: [ ^nil ]. ch := line next. ch == $B ifTrue: [ ^#bold ]. ch == $I ifTrue: [ ^#italic ]. ch == $P ifTrue: [ ^#normal ]. ch == $R ifTrue: [ ^#normal ]. ]. (ch == $s) ifFalse: [ ws nextPut: ch. ^nil ]. [ line atEnd ifTrue: [ ^nil ]. line peek isDigit ] whileFalse: [ line next ]. [ line atEnd ifTrue: [ ^nil ]. line peek isDigit ] whileTrue: [ line next ]. ^nil ! rtrimSeparators: line | size last | size := line size. last := line findLast: [ :each | each isSeparator not ]. ^last = 0 ifTrue: [ line ] ifFalse: [ line copyFrom: 1 to: last ] ! ! !ManViewer methodsFor: 'man macros'! parseTH: line | first second | self breakIntoArguments: line do: [ :each | second isNil ifFalse: [ self label: 'Viewing ', first, '(', second, ') man page'. ^self ]. first isNil ifTrue: [ first := each asLowercase ] ifFalse: [ second := each ] ]. ! parseSH: line separator := self separatePara. self insert: line fonts: #(#big #big). separator := Character nl asString. ! parseSS: line self nl; insert: line fonts: #(#bold #bold); nl ! parseBI: line self insertEndSpace: line fonts: #(#bold #italic) ! parseB: line self insert: line fonts: #(#bold #bold) ! parseBR: line self insertEndSpace: line fonts: #(#bold #normal) ! parseSP: line separator := Character nl asString. ! parseNL: line separator := Character nl asString. ! parseBR: line separator := Character nl asString. ! parsePD: line "not supported" ! parsePP: line separator := self separatePara. ! parseLP: line separator := self separatePara. ! parseTP: line separator := Character nl asString. ! parseIP: line separator := Character nl asString. self insert: line, ' ' fonts: #(#bold #bold) ! parseI: line self insert: line fonts: #(#italic #italic) ! parseIB: line self insertEndSpace: line fonts: #(#italic #bold) ! parseIR: line self insertEndSpace: line fonts: #(#italic #normal) ! parseRI: line self insertEndSpace: line fonts: #(#normal #italic) ! parseRB: line self insertEndSpace: line fonts: #(#normal #bold) ! parseSB: line self insertEndSpace: line fonts: #(#normal #bold) ! parseNormal: line self insert: line fonts: #(#normal #normal) ! parseSM: line self insert: line fonts: #(#normal #normal) ! ! ManViewer initialize! Namespace current: Smalltalk! smalltalk-3.2.5/examples/DeltaBlue.st0000644000175000017500000010251012123404352014450 00000000000000"====================================================================== | | The Richards Benchmark in Smalltalk | | ======================================================================" "====================================================================== | | Copyright 1996 John Maloney and Mario Wolczko | | This file is part of GNU Smalltalk. | | GNU Smalltalk is free software; you can redistribute it and/or modify it | under the terms of the GNU General Public License as published by the Free | Software Foundation; either version 2, or (at your option) any later version. | | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS | FOR A PARTICULAR PURPOSE. See the GNU General Public License for more | details. | | You should have received a copy of the GNU General Public License along with | GNU Smalltalk; see the file COPYING. If not, write to the Free Software | Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. | ======================================================================" Object subclass: #Planner instanceVariableNames: 'currentMark ' classVariableNames: '' poolDictionaries: '' category: 'DB-DeltaBlue'! Planner class instanceVariableNames: 'currentPlanner '! Planner comment: 'This benchmark is an implementation of the DeltaBlue Constraint Solver described in `The DeltaBlue Algorithm: An Incremental Constraint Hierarchy Solver'', by Bjorn N. Freeman-Benson and John Maloney, Communications of the ACM, January 1990 (also as University of Washington TR 89-08-06). To run the benchmark, execute the expression `Planner standardBenchmark''.'! Object subclass: #Strength instanceVariableNames: 'symbolicValue arithmeticValue ' classVariableNames: 'AbsoluteStrongest AbsoluteWeakest Required StrengthConstants StrengthTable ' poolDictionaries: '' category: 'DB-DeltaBlue'! Strength comment: 'Strengths are used to measure the relative importance of constraints. The hierarchy of available strengths is determined by the class variable StrengthTable (see my class initialization method). Because Strengths are invariant, references to Strength instances are shared (i.e. all references to "Strength of: #required" point to a single, shared instance). New strengths may be inserted in the strength hierarchy without disrupting current constraints. Instance variables: symbolicValue symbolic strength name (e.g. #required) arithmeticValue index of the constraint in the hierarchy, used for comparisons '! Object subclass: #AbstractConstraint instanceVariableNames: 'strength ' classVariableNames: '' poolDictionaries: '' category: 'DB-DeltaBlue'! AbstractConstraint comment: 'I am an abstract class representing a system-maintainable relationship (or "constraint") between a set of variables. I supply a strength instance variable; concrete subclasses provide a means of storing the constrained variables and other information required to represent a constraint. Instance variables: strength the strength of this constraint '! Object subclass: #Variable instanceVariableNames: 'value constraints determinedBy walkStrength stay mark ' classVariableNames: '' poolDictionaries: '' category: 'DB-DeltaBlue'! Variable comment: 'I represent a constrained variable. In addition to my value, I maintain the structure of the constraint graph, the current dataflow graph, and various parameters of interest to the DeltaBlue incremental constraint solver. Instance variables: value my value; changed by constraints, read by client constraints normal constraints that reference me determinedBy the constraint that currently determines my value (or nil if there isn''t one) walkStrength my walkabout strength stay true if I am a planning-time constant mark used by the planner to mark constraints '! AbstractConstraint subclass: #UnaryConstraint instanceVariableNames: 'output satisfied ' classVariableNames: '' poolDictionaries: '' category: 'DB-Constraints'! UnaryConstraint comment: 'I am an abstract superclass for constraints having a single possible output variable. Instance variables: output possible output variable satisfied true if I am currently satisfied '! UnaryConstraint subclass: #EditConstraint instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'DB-Constraints'! EditConstraint comment: 'I am a unary input constraint used to mark a variable that the client wishes to change.'! UnaryConstraint subclass: #StayConstraint instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'DB-Constraints'! StayConstraint comment: 'I mark variables that should, with some level of preference, stay the same. I have one method with zero inputs and one output, which does nothing. Planners may exploit the fact that, if I am satisfied, my output will not change during plan execution. This is called "stay optimization."'! AbstractConstraint subclass: #BinaryConstraint instanceVariableNames: 'v1 v2 direction ' classVariableNames: '' poolDictionaries: '' category: 'DB-Constraints'! BinaryConstraint comment: 'I am an abstract superclass for constraints having two possible output variables. Instance variables: v1, v2 possible output variables direction one of: #forward (v2 is output) #backward ( v1 is output) nil (not satisfied)'! BinaryConstraint subclass: #ScaleConstraint instanceVariableNames: 'scale offset ' classVariableNames: '' poolDictionaries: '' category: 'DB-Constraints'! ScaleConstraint comment: 'I relate two variables by the linear scaling relationship: "v2 = (v1 * scale) + offset". Either v1 or v2 may be changed to maintain this relationship but the scale factor and offset are considered read-only. Instance variables: scale scale factor input variable offset offset input variable '! BinaryConstraint subclass: #EqualityConstraint instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'DB-Constraints'! EqualityConstraint comment: 'I constrain two variables to have the same value: "v1 = v2".'! OrderedCollection variableSubclass: #Plan instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'DB-DeltaBlue'! Plan comment: 'A Plan is an ordered list of constraints to be executed in sequence to resatisfy all currently satisfiable constraints in the face of one or more changing inputs.'! !UnaryConstraint methodsFor: 'initialize-release'! var: aVariable strength: strengthSymbol "Initialize myself with the given variable and strength." strength := Strength of: strengthSymbol. output := aVariable. satisfied := false. self addConstraint.! ! !UnaryConstraint methodsFor: 'queries'! isSatisfied "Answer true if this constraint is satisfied in the current solution." ^satisfied! ! !UnaryConstraint methodsFor: 'add/remove'! addToGraph "Add myself to the constraint graph." output addConstraint: self. satisfied := false.! removeFromGraph "Remove myself from the constraint graph." (output == nil) ifFalse: [output removeConstraint: self]. satisfied := false.! ! !UnaryConstraint methodsFor: 'planning'! chooseMethod: mark "Decide if I can be satisfied and record that decision." satisfied := (output mark ~= mark) and: [strength stronger: output walkStrength].! execute "Enforce this constraint. Assume that it is satisfied." self subclassResponsibility! inputsDo: aBlock "I have no input variables."! markUnsatisfied "Record the fact that I am unsatisfied." satisfied := false.! output "Answer my current output variable." ^output! recalculate "Calculate the walkabout strength, the stay flag, and, if it is 'stay', the value for the current output of this constraint. Assume this constraint is satisfied." output walkStrength: strength. output stay: (self isInput not). (output stay) ifTrue: [self execute]. "stay optimization"! ! !EditConstraint methodsFor: 'queries'! isInput "I indicate that a variable is to be changed by imperative code." ^true! ! !EditConstraint methodsFor: 'execution'! execute "Edit constraints do nothing."! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! EditConstraint class instanceVariableNames: ''! !EditConstraint class methodsFor: 'instance creation'! var: aVariable strength: strengthSymbol "Install an edit constraint with the given strength on the given variable." ^(self new) var: aVariable strength: strengthSymbol! ! !StayConstraint methodsFor: 'execution'! execute "Stay constraints do nothing."! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! StayConstraint class instanceVariableNames: ''! !StayConstraint class methodsFor: 'instance creation'! var: aVariable strength: strengthSymbol "Install a stay constraint with the given strength on the given variable." ^(self new) var: aVariable strength: strengthSymbol! ! !BinaryConstraint methodsFor: 'initialize-release'! var: variable1 var: variable2 strength: strengthSymbol "Initialize myself with the given variables and strength." strength := Strength of: strengthSymbol. v1 := variable1. v2 := variable2. direction := nil. self addConstraint.! ! !BinaryConstraint methodsFor: 'queries'! isSatisfied "Answer true if this constraint is satisfied in the current solution." ^direction notNil! ! !BinaryConstraint methodsFor: 'add/remove'! addToGraph "Add myself to the constraint graph." v1 addConstraint: self. v2 addConstraint: self. direction := nil.! removeFromGraph "Remove myself from the constraint graph." (v1 == nil) ifFalse: [v1 removeConstraint: self]. (v2 == nil) ifFalse: [v2 removeConstraint: self]. direction := nil.! ! !BinaryConstraint methodsFor: 'planning'! chooseMethod: mark "Decide if I can be satisfied and which way I should flow based on the relative strength of the variables I relate, and record that decision." (v1 mark == mark) ifTrue: "forward or nothing" [((v2 mark ~= mark) and: [strength stronger: v2 walkStrength]) ifTrue: [^direction := #forward] ifFalse: [^direction := nil]]. (v2 mark == mark) ifTrue: "backward or nothing" [((v1 mark ~= mark) and: [strength stronger: v1 walkStrength]) ifTrue: [^direction := #backward] ifFalse: [^direction := nil]]. "if we get here, neither variable is marked, so we have choice" (v1 walkStrength weaker: v2 walkStrength) ifTrue: [(strength stronger: v1 walkStrength) ifTrue: [^direction := #backward] ifFalse: [^direction := nil]] ifFalse: [(strength stronger: v2 walkStrength) ifTrue: [^direction := #forward] ifFalse: [^direction := nil]].! execute "Enforce this constraint. Assume that it is satisfied." self subclassResponsibility! inputsDo: aBlock "Evaluate the given block on my current input variable." (direction == #forward) ifTrue: [aBlock value: v1] ifFalse: [aBlock value: v2].! markUnsatisfied "Record the fact that I am unsatisfied." direction := nil.! output "Answer my current output variable." (direction == #forward) ifTrue: [^v2] ifFalse: [^v1]! recalculate "Calculate the walkabout strength, the stay flag, and, if it is 'stay', the value for the current output of this constraint. Assume this constraint is satisfied." | in out | (direction == #forward) ifTrue: [in := v1. out := v2] ifFalse: [in := v2. out := v1]. out walkStrength: (strength weakest: in walkStrength). out stay: (in stay). (out stay) ifTrue: [self execute]. "stay optimization"! ! !ScaleConstraint methodsFor: 'initialize-release'! src: srcVar scale: scaleVar offset: offsetVar dst: dstVar strength: strengthSymbol "Initialize myself with the given variables and strength." strength := Strength of: strengthSymbol. v1 := srcVar. v2 := dstVar. scale := scaleVar. offset := offsetVar. direction := nil. self addConstraint.! ! !ScaleConstraint methodsFor: 'add/remove'! addToGraph "Add myself to the constraint graph." v1 addConstraint: self. v2 addConstraint: self. scale addConstraint: self. offset addConstraint: self. direction := nil.! removeFromGraph "Remove myself from the constraint graph." (v1 == nil) ifFalse: [v1 removeConstraint: self]. (v2 == nil) ifFalse: [v2 removeConstraint: self]. (scale == nil) ifFalse: [scale removeConstraint: self]. (offset == nil) ifFalse: [offset removeConstraint: self]. direction := nil.! ! !ScaleConstraint methodsFor: 'planning'! execute "Enforce this constraint. Assume that it is satisfied." (direction == #forward) ifTrue: [v2 value: (v1 value * scale value) + offset value] ifFalse: [v1 value: (v2 value - offset value) // scale value].! inputsDo: aBlock "Evaluate the given block on my current input variable." (direction == #forward) ifTrue: [aBlock value: v1; value: scale; value: offset] ifFalse: [aBlock value: v2; value: scale; value: offset].! recalculate "Calculate the walkabout strength, the stay flag, and, if it is 'stay', the value for the current output of this constraint. Assume this constraint is satisfied." | in out | (direction == #forward) ifTrue: [in := v1. out := v2] ifFalse: [out := v1. in := v2]. out walkStrength: (strength weakest: in walkStrength). out stay: ((in stay) and: [(scale stay) and: [offset stay]]). (out stay) ifTrue: [self execute]. "stay optimization"! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! ScaleConstraint class instanceVariableNames: ''! !ScaleConstraint class methodsFor: 'instance creation'! var: src var: scale var: offset var: dst strength: strengthSymbol "Install a scale constraint with the given strength on the given variables." ^(self new) src: src scale: scale offset: offset dst: dst strength: strengthSymbol! ! !EqualityConstraint methodsFor: 'execution'! execute "Enforce this constraint. Assume that it is satisfied." (direction == #forward) ifTrue: [v2 value: v1 value] ifFalse: [v1 value: v2 value].! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! EqualityConstraint class instanceVariableNames: ''! !EqualityConstraint class methodsFor: 'instance creation'! var: variable1 var: variable2 strength: strengthSymbol "Install a constraint with the given strength equating the given variables." ^(self new) var: variable1 var: variable2 strength: strengthSymbol! ! !Planner methodsFor: 'initialize'! initialize "Planner initialize" currentMark := 1.! ! !Planner methodsFor: 'add/remove'! incrementalAdd: c "Attempt to satisfy the given constraint and, if successful, incrementally update the dataflow graph. Details: If satifying the constraint is successful, it may override a weaker constraint on its output. The algorithm attempts to resatisfy that constraint using some other method. This process is repeated until either a) it reaches a variable that was not previously determined by any constraint or b) it reaches a constraint that is too weak to be satisfied using any of its methods. The variables of constraints that have been processed are marked with a unique mark value so that we know where we've been. This allows the algorithm to avoid getting into an infinite loop even if the constraint graph has an inadvertent cycle." | mark overridden | mark := self newMark. overridden := c satisfy: mark. [overridden == nil] whileFalse: [overridden := overridden satisfy: mark].! incrementalRemove: c "Entry point for retracting a constraint. Remove the given constraint, which should be satisfied, and incrementally update the dataflow graph. Details: Retracting the given constraint may allow some currently unsatisfiable downstream constraint be satisfied. We thus collect a list of unsatisfied downstream constraints and attempt to satisfy each one in turn. This list is sorted by constraint strength, strongest first, as a heuristic for avoiding unnecessarily adding and then overriding weak constraints." | out unsatisfied | out := c output. c markUnsatisfied. c removeFromGraph. unsatisfied := self removePropagateFrom: out. unsatisfied do: [: u | self incrementalAdd: u].! ! !Planner methodsFor: 'planning/value propagation'! extractPlanFromConstraints: constraints "Extract a plan for resatisfaction starting from the outputs of the given constraints, usually a set of input constraints." | sources | sources := OrderedCollection new. constraints do: [: c | ((c isInput) and: [c isSatisfied]) ifTrue: [sources add: c]]. ^self makePlan: sources! extractPlanFromVariables: variables "Extract a plan from the dataflow graph having the given variables. It is assumed that the given set of variables is complete, or at least that it contains all the input variables." | sources | sources := OrderedCollection new. variables do: [: v | (v constraints) do: [: c | ((c isInput) and: [c isSatisfied]) ifTrue: [sources add: c]]]. ^self makePlan: sources! makePlan: sources "Extract a plan for resatisfaction starting from the given satisfied source constraints, usually a set of input constraints. This method assumes that stay optimization is desired; the plan will contain only constraints whose output variables are not stay. Constraints that do no computation, such as stay and edit constraints, are not included in the plan. Details: The outputs of a constraint are marked when it is added to the plan under construction. A constraint may be appended to the plan when all its input variables are known. A variable is known if either a) the variable is marked (indicating that has been computed by a constraint appearing earlier in the plan), b) the variable is 'stay' (i.e. it is a constant at plan execution time), or c) the variable is not determined by any constraint. The last provision is for past states of history variables, which are not stay but which are also not computed by any constraint." | mark plan todo c | mark := self newMark. plan := Plan new. todo := sources. [todo isEmpty] whileFalse: [c := todo removeFirst. ((c output mark ~= mark) and: "not in plan already and..." [c inputsKnown: mark]) ifTrue: "eligible for inclusion" [plan addLast: c. c output mark: mark. self addConstraintsConsuming: c output to: todo]]. ^plan! propagateFrom: v "The given variable has changed. Propagate new values downstream." | todo c | todo := OrderedCollection new. self addConstraintsConsuming: v to: todo. [todo isEmpty] whileFalse: [c := todo removeFirst. c execute. self addConstraintsConsuming: c output to: todo].! ! !Planner methodsFor: 'private'! addConstraintsConsuming: v to: aCollection | determiningC | determiningC := v determinedBy. v constraints do: [: c | ((c == determiningC) or: [c isSatisfied not]) ifFalse: [aCollection add: c]].! addPropagate: c mark: mark "Recompute the walkabout strengths and stay flags of all variables downstream of the given constraint and recompute the actual values of all variables whose stay flag is true. If a cycle is detected, remove the given constraint and answer false. Otherwise, answer true. Details: Cycles are detected when a marked variable is encountered downstream of the given constraint. The sender is assumed to have marked the inputs of the given constraint with the given mark. Thus, encountering a marked node downstream of the output constraint means that there is a path from the constraint's output to one of its inputs." | todo d | todo := OrderedCollection with: c. [todo isEmpty] whileFalse: [d := todo removeFirst. (d output mark = mark) ifTrue: [self incrementalRemove: c. ^false]. d recalculate. self addConstraintsConsuming: d output to: todo]. ^true! changeVar: aVariable newValue: newValue | editConstraint plan | editConstraint := EditConstraint var: aVariable strength: #preferred. plan := self extractPlanFromConstraints: (Array with: editConstraint). 10 timesRepeat: [ aVariable value: newValue. plan execute]. editConstraint destroyConstraint.! constraintsConsuming: v do: aBlock | determiningC | determiningC := v determinedBy. v constraints do: [: c | ((c == determiningC) or: [c isSatisfied not]) ifFalse: [aBlock value: c]].! newMark "Select a previously unused mark value. Details: We just keep incrementing. If necessary, the counter will turn into a LargePositiveInteger. In that case, it will be a bit slower to compute the next mark but the algorithms will all behave correctly. We reserve the value '0' to mean 'unmarked'. Thus, this generator starts at '1' and will never produce '0' as a mark value." ^currentMark := currentMark + 1! removePropagateFrom: out "Update the walkabout strengths and stay flags of all variables downstream of the given constraint. Answer a collection of unsatisfied constraints sorted in order of decreasing strength." | unsatisfied todo v nextC | unsatisfied := SortedCollection sortBlock: [: c1 : c2 | c1 strength stronger: c2 strength]. out determinedBy: nil. out walkStrength: Strength absoluteWeakest. out stay: true. todo := OrderedCollection with: out. [todo isEmpty] whileFalse: [v := todo removeFirst. v constraints do: [: c | (c isSatisfied) ifFalse: [unsatisfied add: c]]. self constraintsConsuming: v do: [: c | c recalculate. todo add: c output]]. ^unsatisfied! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! !Planner class methodsFor: 'instance creation'! new ^currentPlanner := super new initialize! ! !Planner class methodsFor: 'benchmarks'! chainTest: n "Do chain-of-equality-constraints performance tests." | vars editConstraint plan planner | planner := Planner new. vars := (1 to: n+1) collect: [ :i | Variable new]. "thread a chain of equality constraints through the variables" 1 to: n do: [ :i || v1 v2 | v1 := vars at: i. v2 := vars at: i + 1. EqualityConstraint var: v1 var: v2 strength: #required]. StayConstraint var: vars last strength: #strongDefault. editConstraint := EditConstraint var: (vars first) strength: #preferred. plan := planner extractPlanFromConstraints: (Array with: editConstraint). 1 to: 100 do: [ :v | vars first value: v. plan execute. vars last value ~= v ifTrue: [self error: 'Chain test failed!!']]. editConstraint destroyConstraint! projectionTest: n "This test constructs a two sets of variables related to each other by a simple linear transformation (scale and offset)." | scale offset src dst planner dests | planner := Planner new. dests := OrderedCollection new. scale := Variable value: 10. offset := Variable value: 1000. 1 to: n do: [ :i | src := Variable value: i. dst := Variable value: i. dests add: dst. StayConstraint var: src strength: #default. ScaleConstraint var: src var: scale var: offset var: dst strength: #required]. planner changeVar: src newValue: 17. dst value ~= 1170 ifTrue: [self error: 'Projection test 1 failed!!']. planner changeVar: dst newValue: 1050. src value ~= 5 ifTrue: [self error: 'Projection test 2 failed!!']. planner changeVar: scale newValue: 5. 1 to: n - 1 do: [ :i | (dests at: i) value ~= (i*5 + 1000) ifTrue: [self error: 'Projection test 3 failed!!']]. planner changeVar: offset newValue: 2000. 1 to: n - 1 do: [ :i | (dests at: i) value ~= (i*5 + 2000) ifTrue: [self error: 'Projection test 4 failed!!']].! report: string times: count run: aBlock "Report the time required to execute the given block." | time | time := Time millisecondsToRun: [count timesRepeat: aBlock]. Transcript show: string, ' ', (time // count) printString, ' milliseconds'; cr.! standardBenchmark "This the combined benchmark." "Planner standardBenchmark" self report: 'Chain and projection tests' times: 100 run: [ self chainTest: 100. self projectionTest: 100 ]! ! !Planner class methodsFor: 'accessing'! current ^currentPlanner! ! !Plan methodsFor: 'execution'! execute "Execute my constraints in order." self do: [: c | c execute].! ! !Strength methodsFor: 'comparing'! sameAs: aStrength "Answer true if I am the same strength as the given Strength." ^arithmeticValue = aStrength arithmeticValue! stronger: aStrength "Answer true if I am stronger than the given Strength." ^arithmeticValue < aStrength arithmeticValue! weaker: aStrength "Answer true if I am weaker than the given Strength." ^arithmeticValue > aStrength arithmeticValue! ! !Strength methodsFor: 'max/min'! strongest: aStrength "Answer the stronger of myself and aStrength." (aStrength stronger: self) ifTrue: [^aStrength] ifFalse: [^self].! weakest: aStrength "Answer the weaker of myself and aStrength." (aStrength weaker: self) ifTrue: [^aStrength] ifFalse: [^self].! ! !Strength methodsFor: 'printing'! printOn: aStream "Append a string which represents my strength onto aStream." aStream nextPutAll: '%', symbolicValue, '%'.! ! !Strength methodsFor: 'private'! arithmeticValue "Answer my arithmetic value. Used for comparisons. Note that STRONGER constraints have SMALLER arithmetic values." ^arithmeticValue! initializeWith: symVal "Record my symbolic value and reset my arithmetic value." symbolicValue := symVal. arithmeticValue := StrengthTable at: symbolicValue.! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! Strength class instanceVariableNames: ''! !Strength class methodsFor: 'class initialization'! initialize "Initialize the symbolic strength table. Fix the internally caches values of all existing instances." "Strength initialize" StrengthTable := Dictionary new. StrengthTable at: #absoluteStrongest put: -10000. StrengthTable at: #required put: -800. StrengthTable at: #strongPreferred put: -600. StrengthTable at: #preferred put: -400. StrengthTable at: #strongDefault put: -200. StrengthTable at: #default put: 0. StrengthTable at: #weakDefault put: 500. StrengthTable at: #absoluteWeakest put: 10000. StrengthConstants := Dictionary new. StrengthTable keys do: [: strengthSymbol | StrengthConstants at: strengthSymbol put: ((super new) initializeWith: strengthSymbol)]. AbsoluteStrongest := Strength of: #absoluteStrongest. AbsoluteWeakest := Strength of: #absoluteWeakest. Required := Strength of: #required.! ! !Strength class methodsFor: 'instance creation'! of: aSymbol "Answer an instance with the specified strength." ^StrengthConstants at: aSymbol! ! !Strength class methodsFor: 'constants'! absoluteStrongest ^AbsoluteStrongest! absoluteWeakest ^AbsoluteWeakest! required ^Required! ! !AbstractConstraint methodsFor: 'accessing'! strength "Answer my strength." ^strength! strength: strengthSymbol "Set my strength." strength := Strength of: strengthSymbol.! ! !AbstractConstraint methodsFor: 'queries'! isInput "Normal constraints are not input constraints. An input constraint is one that depends on external state, such as the mouse, the keyboard, a clock, or some arbitrary piece of imperative code." ^false! isSatisfied "Answer true if this constraint is satisfied in the current solution." self subclassResponsibility! ! !AbstractConstraint methodsFor: 'add/remove'! addConstraint "Activate this constraint and attempt to satisfy it." self addToGraph. Planner current incrementalAdd: self.! addToGraph "Add myself to the constraint graph." self subclassResponsibility! destroyConstraint "Deactivate this constraint, remove it from the constraint graph, possibly causing other constraints to be satisfied, and destroy it." (self isSatisfied) ifTrue: [Planner current incrementalRemove: self]. self removeFromGraph. self release.! removeFromGraph "Remove myself from the constraint graph." self subclassResponsibility! ! !AbstractConstraint methodsFor: 'planning'! chooseMethod: mark "Decide if I can be satisfied and record that decision. The output of the choosen method must not have the given mark and must have a walkabout strength less than that of this constraint." self subclassResponsibility! execute "Enforce this constraint. Assume that it is satisfied." self subclassResponsibility! inputsDo: aBlock "Assume that I am satisfied. Evaluate the given block on all my current input variables." self subclassResponsibility! inputsKnown: mark "Assume that I am satisfied. Answer true if all my current inputs are known. A variable is known if either a) it is 'stay' (i.e. it is a constant at plan execution time), b) it has the given mark (indicating that it has been computed by a constraint appearing earlier in the plan), or c) it is not determined by any constraint." self inputsDo: [: v | ((v mark = mark) or: [(v stay) or: [v determinedBy == nil]]) ifFalse: [^false]]. ^true! markUnsatisfied "Record the fact that I am unsatisfied." self subclassResponsibility! output "Answer my current output variable. Raise an error if I am not currently satisfied." self subclassResponsibility! recalculate "Calculate the walkabout strength, the stay flag, and, if it is 'stay', the value for the current output of this constraint. Assume this constraint is satisfied." self subclassResponsibility! satisfy: mark "Attempt to find a way to enforce this (still unsatisfied) constraint. If successful, record the solution, perhaps modifying the current dataflow graph. Answer the constraint that this constraint overrides, if there is one, or nil, if there isn't." | overridden out | self chooseMethod: mark. (self isSatisfied) ifTrue: "constraint can be satisfied" ["mark inputs to allow cycle detection in addPropagate" self inputsDo: [: in | in mark: mark]. out := self output. overridden := out determinedBy. (overridden == nil) ifFalse: [overridden markUnsatisfied]. out determinedBy: self. (Planner current addPropagate: self mark: mark) ifFalse: [self notify: ('Cycle encountered adding:\ ', self printString, '\Constraint removed.') withCRs. ^nil]. out mark: mark] ifFalse: "constraint cannot be satisfied" [overridden := nil. (strength sameAs: (Strength required)) ifTrue: [self notify: 'Failed to satisfy a required constraint']]. ^overridden! ! !AbstractConstraint methodsFor: 'printing'! longPrintOn: aStream | bindings | aStream nextPut: $(. self shortPrintOn: aStream. aStream space; nextPutAll: self strength printString. (self isSatisfied) ifTrue: [aStream cr; space; space; space. self inputsDo: [: in | aStream nextPutAll: 'v', in asOop printString, ' ']. aStream nextPutAll: '-> '. aStream nextPutAll: 'v', self output asOop printString] ifFalse: [aStream space; nextPutAll: 'UNSATISFIED']. aStream nextPut: $); cr.! printOn: aStream self shortPrintOn: aStream! shortPrintOn: aStream aStream nextPutAll: self class name, '(', self asOop printString, ')'.! ! !Variable methodsFor: 'initialize-release'! initialize value := 0. constraints := OrderedCollection new: 2. determinedBy := nil. walkStrength := Strength absoluteWeakest. stay := true. mark := 0.! ! !Variable methodsFor: 'access'! addConstraint: aConstraint "Add the given constraint to the set of all constraints that refer to me." constraints add: aConstraint.! constraints "Answer the set of constraints that refer to me." ^constraints! determinedBy "Answer the constraint that determines my value in the current dataflow." ^determinedBy! determinedBy: aConstraint "Record that the given constraint determines my value in the current data flow." determinedBy := aConstraint.! mark "Answer my mark value." ^mark! mark: markValue "Set my mark value." mark := markValue.! removeConstraint: c "Remove all traces of c from this variable." constraints remove: c ifAbsent: []. (determinedBy == c) ifTrue: [determinedBy := nil].! stay "Answer my stay flag." ^stay! stay: aBoolean "Set my stay flag." stay := aBoolean! value "Answer my value." ^value! value: anObject "Set my value." value := anObject.! walkStrength "Answer my walkabout strength in the current dataflow." ^walkStrength! walkStrength: aStrength "Set my walkabout strength in the current dataflow." walkStrength := aStrength.! ! !Variable methodsFor: 'changes'! setValue: aValue "Attempt to assign the given value to me using a strength of #preferred." self setValue: aValue strength: #preferred.! setValue: aValue strength: strengthSymbol "Attempt to assign the given value to me using the given strength." | editConstraint | editConstraint := EditConstraint var: self strength: strengthSymbol. (editConstraint isSatisfied) ifTrue: [self value: aValue. Planner propagateFrom: self]. editConstraint destroyConstraint.! ! !Variable methodsFor: 'printing'! longPrintOn: aStream self shortPrintOn: aStream. aStream nextPutAll: ' Constraints: '. (constraints isEmpty) ifTrue: [aStream cr; tab; nextPutAll: 'none'] ifFalse: [constraints do: [: c | aStream cr; tab. c shortPrintOn: aStream]]. (determinedBy isNil) ifFalse: [aStream cr; nextPutAll: ' Determined by: '. aStream cr; tab. determinedBy shortPrintOn: aStream]. aStream cr.! printOn: aStream self shortPrintOn: aStream! shortPrintOn: aStream aStream nextPutAll: 'V(', self asOop printString, ', '. aStream nextPutAll: walkStrength printString, ', '. (stay isNil) ifFalse: [aStream nextPutAll: (stay ifTrue: ['stay, '] ifFalse: ['changing, '])]. aStream nextPutAll: value printString. aStream nextPutAll: ')'. aStream cr.! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! Variable class instanceVariableNames: ''! !Variable class methodsFor: 'instance creation'! new ^super new initialize! value: aValue ^(super new) initialize; value: aValue! ! Strength initialize! smalltalk-3.2.5/examples/CairoBlit.st0000644000175000017500000000717212123404352014467 00000000000000"====================================================================== | | Blitting example using Cairo and SDL | | ======================================================================" "====================================================================== | | Copyright 2008 Free Software Foundation, Inc. | Written by Tony Garnock-Jones. | | This file is part of GNU Smalltalk. | | GNU Smalltalk is free software; you can redistribute it and/or modify it | under the terms of the GNU General Public License as published by the Free | Software Foundation; either version 2, or (at your option) any later version. | | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS | FOR A PARTICULAR PURPOSE. See the GNU General Public License for more | details. | | You should have received a copy of the GNU General Public License along with | GNU Smalltalk; see the file COPYING. If not, write to the Free Software | Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. | ======================================================================" PackageLoader fileInPackage: #CairoSDL. PackageLoader fileInPackage: #'LibSDL_GL'. SDL.SdlEventHandler subclass: BlitDemo [ winningDirectAccess [ | color | SdlDisplay current critical: [ color := SdlDisplay current mapRed: 100 green: 200 blue: 255. SdlDisplay current fillRect: (0@0 extent: SdlDisplay current extent) color: color]. SdlDisplay current flip. ] run [ SdlDisplay current: SdlGLDisplay new. SdlDisplay current eventSource handler: self; startEventLoop. Processor activeProcess terminateOnQuit. SdlDisplay current isGLDisplay ifFalse: [ self winningDirectAccess ]. self blitStuff. ] randomColorComponent [ ^ ((Random between: 0 and: 255) / 255) asFloat ] transparentFill: surface [ "Just an example that would allow showing other OpenGL stuff behind the Cairo graphics." surface withContextDo: [ :context | context operator: #source; sourceRed: 0 green: 0 blue: 0 alpha: 0; paint; operator: #over ]. ] blitStuff [ | maxw maxh x y w h startTime count surface frameRects | startTime := Time millisecondClock. surface := Cairo.CairoSdlSurface on: SdlDisplay current. count := 0. maxw := SdlDisplay current extent x. maxh := SdlDisplay current extent y. frameRects := SdlDisplay current isGLDisplay ifTrue: [1] ifFalse: [100]. SdlDisplay current isGLDisplay ifTrue: [ self transparentFill: surface ]. [ surface withContextDo: [ :context | frameRects timesRepeat: [ x := Random between: 0 and: maxw. y := Random between: 0 and: maxh. w := Random between: 0 and: maxw - x. h := Random between: 0 and: maxh - y. count := count + 1. context sourceRed: self randomColorComponent green: self randomColorComponent blue: self randomColorComponent; fill: [ context rectangle: (x@y extent: w@h)]]]. count \\ 100 == 0 ifTrue: [ Transcript << count << ' frames, ' << (count / ((Time millisecondClock - startTime) / 1000.0)) << ' fps'; nl. Processor yield ]. ] repeat. ] handleQuit [ (ObjectMemory snapshot: 'demo.im') ifFalse: [ "false -> not resuming" Transcript << 'about to quit after snapshot'; nl. ObjectMemory quit]. ] ] Eval [ s := Semaphore new. [BlitDemo new run. s signal] fork. s wait ] smalltalk-3.2.5/examples/SortCriter.st0000644000175000017500000002605512123404352014720 00000000000000"====================================================================== | | SortCriteria example | | ======================================================================" "====================================================================== | | Written by Peter William Lount. | | This file is part of GNU Smalltalk. | ======================================================================" Object subclass: #SortCriteria instanceVariableNames: 'columnSortCriteria ' classVariableNames: '' poolDictionaries: '' category: 'Sort Criteria'! Object subclass: #SortCriteriaColumn instanceVariableNames: 'columnName ascendingFlag accessProtocol ' classVariableNames: '' poolDictionaries: '' category: 'Sort Criteria'! Object subclass: #SortCriteriaTest instanceVariableNames: 'size length code ' classVariableNames: '' poolDictionaries: '' category: 'Sort Criteria'! SortCriteria comment: 'SortCriteria and SortCriteriaColumn objects copyright 1996, 1997, 1998, and 1999 by Peter William Lount All rights reserved. peter@smalltalk.org, http://www.smalltalk.org Usage License You may use these objects for any purpose what so ever as long as this notice remains intact. If these objects are used in a used in a software product for which source code is not released to the public you must visibly display the above notice.'! !SortCriteria methodsFor: 'initialization' stamp: 'pwl 7/16/1999 12:04'! initialize columnSortCriteria := OrderedCollection new.! ! !SortCriteria methodsFor: 'sorted collection protocol' stamp: 'PWVL 9/14/1998 18:03'! fixTemps "We don't need to do anything here."! ! !SortCriteria methodsFor: 'sorted collection protocol' stamp: 'PWVL 9/14/1998 17:17'! value: theFirstElement value: theSecondElement "Part of the protocol that Blocks used in sorting use... the default sort block used by SortedCollection is [:a :b | a <= b]. We implement this protocol and can therefore be placed into the SortedCollection..." | aResult aLastColCriteria | columnSortCriteria isNil ifTrue: [ "Ignore the sorting order as we don't have any columns to sort...yet" ^ true ] ifFalse: [ "We have columns to sort, so lets sort them..." columnSortCriteria do: [:aColumnCriteria | aResult := aColumnCriteria value: theFirstElement value: theSecondElement. aResult == nil ifFalse: [ "The elements are either greater or less, but not equal, return which..." ^aResult ]. "The elements in this column were equal - use the next column (if any) to decide sort order..." aLastColCriteria := aColumnCriteria. ]. "The last comparison of the elements were equal...return the appropriate value..." ^ aLastColCriteria equalBoolean ]! ! !SortCriteria methodsFor: 'sort order' stamp: 'pwl 7/16/1999 11:35'! addColumnName: theColumnName ascendingFlag: theBoolean columnSortCriteria add: ( SortCriteriaColumn new columnName: theColumnName ; ascendingFlag: theBoolean; yourself )! ! !SortCriteria methodsFor: 'sort order'! columnNames "Generate and return a list of column names in sequence..." | aList | aList := OrderedCollection new: columnSortCriteria size. columnSortCriteria do: [:aColSortCriteria | aList add: aColSortCriteria columnName asSymbol ]. ^aList! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! SortCriteria class instanceVariableNames: ''! !SortCriteria class methodsFor: 'instance creation' stamp: 'pwl 7/16/1999 12:02'! new ^super new initialize! ! !SortCriteriaColumn methodsFor: 'initialize' stamp: 'pwl 7/16/1999 12:04'! initialize self ascendingSort. self useMethodPerformProtocol.! ! !SortCriteriaColumn methodsFor: 'equality testing'! equalBoolean "Return the boolean flag used to determine sort order when the two elements are the same... This is dependent upon the ascendingFlag sort order... i.e. Ascending sort: when a <= b return true, when a > b return false. Decending sort: when a <= b return false, when a > b return true... Therefore, if you'll notice, it works to return a logical not of the ascending flag... " ^ ascendingFlag! ! !SortCriteriaColumn methodsFor: 'sort attribute'! columnName ^columnName! ! !SortCriteriaColumn methodsFor: 'sort attribute'! columnName: theColumnName columnName := theColumnName asSymbol! ! !SortCriteriaColumn methodsFor: 'sort order'! ascendingFlag ^ascendingFlag! ! !SortCriteriaColumn methodsFor: 'sort order'! ascendingFlag: theBoolean ascendingFlag := theBoolean.! ! !SortCriteriaColumn methodsFor: 'sort order' stamp: 'PWVL 9/14/1998 17:27'! ascendingSort self ascendingFlag: true.! ! !SortCriteriaColumn methodsFor: 'sort order' stamp: 'PWVL 9/14/1998 17:27'! decendingSort self ascendingFlag: false.! ! !SortCriteriaColumn methodsFor: 'attribute access protocols' stamp: 'PWVL 9/14/1998 17:27'! useDictionaryAtProtocol accessProtocol := #dictionaryAt. ! ! !SortCriteriaColumn methodsFor: 'attribute access protocols' stamp: 'PWVL 9/14/1998 17:28'! useMethodPerformProtocol accessProtocol := #methodPerform. ! ! !SortCriteriaColumn methodsFor: 'attribute access protocols' stamp: 'pwl 7/16/1999 11:46'! valueOfColumnNamed: theColumnName for: theTargetObject ifAbsent: theAbsentBlock "Retreive the value of the column name for the target object using the appropiate access method protocol. If the object does not have the column name as an attribute then execute the absent block and return it's result." accessProtocol = #dictionaryAt ifTrue: [ ^theTargetObject at: columnName ifAbsent: [ nil ]. ]. accessProtocol = #methodPerform ifTrue: [ ^theTargetObject perform: columnName ]. ^nil! ! !SortCriteriaColumn methodsFor: 'sorted collection protocol' stamp: 'pwl 7/16/1999 08:56'! value: theFirstElement value: theSecondElement | aFirstValue aSecondValue | "Compare the two elements and determine which comes first... If a column name is missing then use a blank value order..." columnName isNil ifTrue: [^ascendingFlag]. "Get the value of the first element." aFirstValue := self valueOfColumnNamed: columnName for: theFirstElement ifAbsent: [^ascendingFlag]. aFirstValue ifNil: [^ascendingFlag]. "Get the value of the second element." aSecondValue := self valueOfColumnNamed: columnName for: theSecondElement ifAbsent: [^ascendingFlag not]. aSecondValue ifNil: [^ascendingFlag not]. "Actually compare the values now taking the ascending and decending order into account..." ascendingFlag ifTrue: [ aFirstValue < aSecondValue ifTrue: [ "The first element comes before the second element..." ^true ] ifFalse: [ "Are the two elements equal?" aFirstValue = aSecondValue ifTrue: [ "The elements are equal... the next column (if any) must be checked..." ^nil ] ifFalse: [ "The second element comes before the first..." ^false ] ] ] ifFalse: [ "The sort order is decending...reverse the comparisons..." aSecondValue < aFirstValue ifTrue: [ "The second element comes before the first element..." ^true ] ifFalse: [ "Are the two elements equal?" aSecondValue = aFirstValue ifTrue: [ "The elements are equal..." ^nil ] ifFalse: [ "The first element comes before the second..." ^false ] ] ]! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! SortCriteriaColumn class instanceVariableNames: ''! !SortCriteriaColumn class methodsFor: 'instance creation' stamp: 'pwl 7/16/1999 12:02'! new ^super new initialize! ! !SortCriteriaTest comment: 'SortCriteriaTest is a test and an example of using the sort criteria objects.'! !SortCriteriaTest methodsFor: 'accessing'! code ^code! ! !SortCriteriaTest methodsFor: 'accessing'! code: theObject code := theObject! ! !SortCriteriaTest methodsFor: 'accessing'! length ^length! ! !SortCriteriaTest methodsFor: 'accessing'! length: theObject length := theObject! ! !SortCriteriaTest methodsFor: 'accessing'! size ^size! ! !SortCriteriaTest methodsFor: 'accessing'! size: theObject size := theObject! ! !SortCriteriaTest methodsFor: 'printing' stamp: 'pwl 7/16/1999 12:46'! printOn: theStream theStream nextPutAll: '(', self class name; nextPutAll: ' code: ', self code printString; nextPutAll: ' size: ', self size printString; nextPutAll: ' length: ', self length printString; nextPutAll: ')'; cr ! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! SortCriteriaTest class instanceVariableNames: ''! !SortCriteriaTest class methodsFor: 'testing' stamp: 'pwl 7/16/1999 12:50'! addToList: theSortedList theSortedList add: ( SortCriteriaTest new code: 'R301'; size: '5M'; length: 50; yourself ). theSortedList add: ( SortCriteriaTest new code: 'R202'; size: '29M'; length: 70; yourself ). theSortedList add: ( SortCriteriaTest new code: 'R002'; size: '18M'; length: 65; yourself ). theSortedList add: ( SortCriteriaTest new code: 'R202'; size: '15M'; length: 89; yourself ). theSortedList add: ( SortCriteriaTest new code: 'R101'; size: '26M'; length: 90; yourself ). theSortedList add: ( SortCriteriaTest new code: 'R202'; size: '15M'; length: 16; yourself ). theSortedList add: ( SortCriteriaTest new code: 'R202'; size: '15M'; length: 18; yourself ). theSortedList add: ( SortCriteriaTest new code: 'R202'; size: '15M'; length: 45; yourself ). theSortedList add: ( SortCriteriaTest new code: 'R202'; size: '15M'; length: 89; yourself ). theSortedList add: ( SortCriteriaTest new code: 'R202'; size: '15M'; length: 114; yourself ). ^theSortedList! ! !SortCriteriaTest class methodsFor: 'testing' stamp: 'pwl 7/16/1999 12:48'! test1 "SortCriteriaTest test1" | aSortedList aSortCriteria | aSortCriteria := SortCriteria new. aSortCriteria addColumnName: #code ascendingFlag: true. aSortCriteria addColumnName: #size ascendingFlag: false. aSortCriteria addColumnName: #length ascendingFlag: false. aSortedList := SortedCollection sortBlock: aSortCriteria. self addToList: aSortedList. ^aSortedList! ! !SortCriteriaTest class methodsFor: 'testing' stamp: 'pwl 7/16/1999 12:49'! test2 "SortCriteriaTest test2" | aSortedList aSortCriteria | aSortCriteria := SortCriteria new. aSortCriteria addColumnName: #code ascendingFlag: true. aSortCriteria addColumnName: #size ascendingFlag: true. aSortCriteria addColumnName: #length ascendingFlag: true. aSortedList := SortedCollection sortBlock: aSortCriteria. self addToList: aSortedList. ^aSortedList! ! !SortCriteriaTest class methodsFor: 'testing' stamp: 'pwl 7/16/1999 13:05'! test3 "SortCriteriaTest test3" | aSortedList aSortCriteria | aSortCriteria := SortCriteria new. aSortCriteria addColumnName: #length ascendingFlag: false. aSortCriteria addColumnName: #code ascendingFlag: true. aSortCriteria addColumnName: #size ascendingFlag: true. aSortedList := SortedCollection sortBlock: aSortCriteria. self addToList: aSortedList. ^aSortedList! ! smalltalk-3.2.5/examples/MiniDebugger.st0000644000175000017500000003005212123404352015151 00000000000000"====================================================================== | | Minimal inspector and debugger using DebugTools | | ======================================================================" "====================================================================== | | Copyright 2002, 2006, 2007 Free Software Foundation, Inc. | Written by Paolo Bonzini. | | This file is part of GNU Smalltalk. | | GNU Smalltalk is free software; you can redistribute it and/or modify it | under the terms of the GNU General Public License as published by the Free | Software Foundation; either version 2, or (at your option) any later version. | | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS | FOR A PARTICULAR PURPOSE. See the GNU General Public License for more | details. | | You should have received a copy of the GNU General Public License along with | GNU Smalltalk; see the file COPYING. If not, write to the Free Software | Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. | ======================================================================" PackageLoader fileInPackage: #DebugTools! Object subclass: #MiniTool instanceVariableNames: 'commandArg command' classVariableNames:'' poolDictionaries:'' category: 'Debugging-Support' ! MiniTool subclass: #MiniInspector instanceVariableNames: 'inspectedObject depth' classVariableNames:'' poolDictionaries:'' category: 'Debugging-Support' ! MiniTool subclass: #MiniDebugger instanceVariableNames: 'debugger activeContext depth methodSourceCodeCache' classVariableNames: '' poolDictionaries: '' category: 'System-Debugging-Support' ! MiniInspector comment: 'I implement a primitive inspector which is launched by the MiniDebugger.'! MiniDebugger comment: 'I implement a primitive (non graphical) debugger for use on systems without graphics or when the real debugger dies (i.e. an error occurs in the graphical debugger). The interface is vaguely similar to GDB.'! !MiniTool class methodsFor: 'disabling debugging'! debuggerClass ^nil ! ! !MiniTool methodsFor: 'rep loop'! interpreterLoopWith: anObject | line | 'read-eval-print loop; exit with empty line ' displayNl. [ '(rep) ' display. line := stdin nextLine. line isEmpty ] whileFalse: [ self eval: line to: anObject ] ! eval: line to: anObject | result | result := Behavior evaluate: line to: anObject ifError: [ :f :l :e | e printNl. ^self ]. result printNl ! ! !MiniTool methodsFor: 'instance creation'! showPrompt self subclassResponsibility ! eofCommand self subclassResponsibility ! doCommand self subclassResponsibility ! getCommand | cmd | self showPrompt. cmd := stdin atEnd ifTrue: [ { self eofCommand } ] ifFalse: [ stdin nextLine substrings ]. cmd isEmpty ifFalse: [ command := (cmd at: 1) at: 1. commandArg := cmd copyFrom: 2. "Else repeat the last command." ]. self doCommand ifFalse: [ (command = $h) ifFalse: [ 'invalid command' displayNl ]. self help displayNl ]. ! help self subclassResponsibility ! ! !MiniInspector class methodsFor: 'instance creation'! openOn: anObject self openOn: anObject depth: 0 ! openOn: anObject depth: n self new initializeFor: anObject depth: n; commandLoop ! ! !MiniInspector methodsFor: 'command loop'! help ^'inspector commands: (e)val start read-eval-print loop (i)nstvars print all instvars (i)nstvars NUMBER inspect n-th instvar (negative=fixed, positive=indexed) (p)rint print object (p)rint NUMBER print n-th instvar (negative=fixed, positive=indexed) (q)uit' ! doCommand (command = $p) ifTrue: [ stdout space: depth. commandArg isEmpty ifFalse: [ (self nthInstvar: commandArg first asInteger) printNl ] ifTrue: [ inspectedObject printNl ]. ^true ]. (command = $e) ifTrue: [ self interpreterLoopWith: inspectedObject. ^true ]. (command = $i) ifTrue: [ commandArg isEmpty ifFalse: [ self inspectInstvar: commandArg first asInteger ] ifTrue: [ self printInstVarsOf: inspectedObject ]. ^true ]. ^command = $q ! eofCommand ^'q' ! commandLoop self printHeader. [ self getCommand. command = $q ] whileFalse. ! showPrompt stdout space: depth. '(insp) ' display. ! ! !MiniInspector methodsFor: 'commands'! inspectInstvar: which self doInspect: (self nthInstvar: which). self printHeader. ! printInstVarsOf: anObject stdout space: depth. anObject inspect. ! ! !MiniInspector methodsFor: 'private'! initializeFor: anObject depth: n inspectedObject := anObject. depth := n. ^self ! printHeader stdout space: depth. '-- inspector: ' display. inspectedObject basicPrintNl. ! doInspect: anObject self class openOn: anObject depth: depth + 1 ! nthInstvar: which which < 0 ifTrue: [ ^inspectedObject instVarAt: which negated ]. ^inspectedObject basicSize = 0 ifTrue: [ inspectedObject instVarAt: which ] ifFalse: [ inspectedObject basicAt: which ] ! ! !MiniDebugger class methodsFor: 'class attributes'! debuggingPriority ^FloatD infinity ! ! !MiniDebugger class methodsFor: 'instance creation'! open: aString [ :debugger || continuation arg | Processor activeProcess name: 'Debugger'. arg := Continuation currentDo: [ :cc | continuation := cc. aString ]. arg printNl. [ self new debugger: debugger; commandLoop ] on: SystemExceptions.DebuggerReentered do: [ :ex | continuation value: ex messageText ] ] forkDebugger ! ! !MiniDebugger methodsFor: 'commands'! debugger: aDebugger debugger := aDebugger. ! commandLoop "Show meaningful source code to the user." [ debugger suspendedContext isInternalExceptionHandlingContext ] whileTrue: [ debugger slowFinish ]. depth := 0. activeContext := debugger suspendedContext. debugger suspendedContext backtrace. self printCurrentLine. [ self getCommand. debugger isActive ] whileTrue. Processor activeProcess suspend ! !MiniDebugger methodsFor: 'commands'! step debugger step. self resetContext! next debugger next. self resetContext! finish debugger finish: activeContext. self resetContext! continue debugger continue! resetContext activeContext := debugger suspendedContext. depth := 0! up activeContext parentContext isNil ifTrue: [ ^self ]. activeContext := activeContext parentContext. depth := depth + 1. ! down depth > 0 ifFalse: [ ^self ]. depth := depth - 1. activeContext := debugger suspendedContext. depth timesRepeat: [ activeContext := activeContext parentContext ] ! ! !MiniDebugger methodsFor: 'printing'! printCurrentMethod | source | source := self currentMethodSource. source isNil ifTrue: [ ^self ]. source keysAndValuesDo: [ :line :code | self rightJustify: line. stdout space; nextPutAll: code; nl ] ! printCurrentLine | line source | activeContext isNil ifTrue: [ ^self ]. source := self currentMethodSource. source isNil ifTrue: [ ^self ]. line := Debugger currentLineIn: activeContext. line = 0 ifTrue: [ ^self ]. self rightJustify: line. stdout space; nextPutAll: (source at: line ifAbsent: [ '' ]); nl ! ! !MiniDebugger methodsFor: 'user commands'! doStepCommand | context arg | ('udsnfc' includes: command) ifFalse: [ ^false ]. context := activeContext. arg := commandArg at: 1 ifAbsent: [ 1 ]. arg := arg asInteger. arg timesRepeat: [ (command == $u) ifTrue: [ self up ]. (command == $d) ifTrue: [ self down ]. (command == $s) ifTrue: [ self step ]. (command == $n) ifTrue: [ self next ]. (command == $f) ifTrue: [ self finish ]. (command == $c) ifTrue: [ self continue ]. ]. activeContext isNil ifFalse: [ activeContext == context ifFalse: [ activeContext printNl ]. self printCurrentLine ]. ^true ! doProcessCommand | id processes terminated | ('TSKb' includes: command) ifFalse: [ ^false ]. (commandArg isEmpty and: [ command == $b ]) ifTrue: [ activeContext backtrace. ^true ]. processes := commandArg collect: [ :each || stream proc | stream := each readStream. id := Number readFrom: stream. stream atEnd ifFalse: [ 'please supply a valid process id' displayNl. ^true ]. proc := id asObject. (proc isKindOf: Process) ifFalse: [ 'please supply a valid process id' displayNl. ^true ]. proc ]. processes isEmpty ifTrue: [ processes := {debugger process} ]. terminated := false. processes do: [ :proc | proc suspendedContext isNil ifTrue: [('%1: process was terminated' % { proc asOop }) displayNl] ifFalse: [ (command == $b) ifTrue: [ processes size > 1 ifTrue: [ ('backtrace for process %1' % { proc asOop }) displayNl]. proc context backtrace ]. (command == $S) ifTrue: [ proc suspend ]. (command == $K) ifTrue: [ proc primTerminate ]. (command == $T) ifTrue: [ proc terminate. terminated := terminated or: [proc == debugger process]]]]. terminated ifTrue: [ self continue ]. ^true ! doCommand self doStepCommand ifTrue: [ ^true ]. self doProcessCommand ifTrue: [ ^true ]. ('PriIelwgxX' includes: command) ifFalse: [ ^false ]. (command == $h) ifTrue: [ ^true ]. commandArg isEmpty ifFalse: [ 'no argument needed for this command' displayNl. ^true ]. (command == $P) ifTrue: [ self showProcesses ]. (command == $r) ifTrue: [ activeContext receiver printNl ]. (command == $i) ifTrue: [ MiniInspector openOn: activeContext receiver ]. (command == $I) ifTrue: [ MiniInspector openOn: activeContext ]. (command == $e) ifTrue: [ self interpreterLoopWith: activeContext receiver ]. (command == $l) ifTrue: [ self printCurrentMethod ]. (command == $w) ifTrue: [ activeContext printNl. self printCurrentLine ]. (command == $g) ifTrue: [ ObjectMemory globalGarbageCollect ]. (command == $X) ifTrue: [ ObjectMemory abort ]. (command == $x) ifTrue: [ ObjectMemory quit ]. ^true ! eofCommand ^'T' ! showPrompt '(debug) ' display. ! help ^'Control flow commands: s [n] step N times n [n] next (step over send) N times f [n] finish current method N times c continue Process commands: no ID means debugged process P show process list T [id]... terminate process K [id]... kill process - no unwinds or cleanup b [id]... backtrace Examining state: r print receiver on stdout i inspect (enter MiniInspector on current receiver) I inspect context (enter MiniInspector on current context) e eval (enter read-eval-print loop on current receiver) Examining the call stack: u [n] go N frames up (default 1) d [n] go N frames down (default 1) l print current method w print current frame Other commands: g collect all garbage X exit Smalltalk, and dump core x exit Smalltalk' ! ! !MiniDebugger methodsFor: 'private'! currentMethodSource activeContext isNil ifTrue: [ ^#() ]. methodSourceCodeCache isNil ifTrue: [ methodSourceCodeCache := WeakKeyIdentityDictionary new ]. ^methodSourceCodeCache at: activeContext method ifAbsentPut: [ activeContext method methodSourceString lines ] ! rightJustify: n | printString | printString := n printString. stdout space: (7 - printString size max: 0); nextPutAll: printString ! showProcesses self rightJustify: debugger process asOop. '>' display. debugger process printNl. Process allSubinstancesDo: [ :each | each == debugger process ifFalse: [ self rightJustify: each asOop. ' ' display. each printNl ] ] ! ! !UndefinedObject methodsFor: 'polymorphism'! lines ^nil ! ! !Behavior methodsFor: 'debugging'! debuggerClass ^MiniDebugger ! ! smalltalk-3.2.5/examples/PrtHier.st0000644000175000017500000000406412123404352014171 00000000000000"====================================================================== | | Print out the class hierarchy. | | ======================================================================" "====================================================================== | | Copyright 1988,92,94,95,1999,2000 Free Software Foundation, Inc. | Written by Steve Byrne. | | This file is part of GNU Smalltalk. | | GNU Smalltalk is free software; you can redistribute it and/or modify it | under the terms of the GNU General Public License as published by the Free | Software Foundation; either version 2, or (at your option) any later version. | | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS | FOR A PARTICULAR PURPOSE. See the GNU General Public License for more | details. | | You should have received a copy of the GNU General Public License along with | GNU Smalltalk; see the file LICENSE. If not, write to the Free Software | Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. | ======================================================================" !Behavior methodsFor: 'demo'! printHierarchy "I print my entire subclass hierarchy to standard out." self printSubclasses: 0 ! ! !Behavior methodsFor: 'private'! printSubclasses: level "I print my name, and then all my subclasses, each indented according to its position in the hierarchy." | mySubclasses | self indentToLevel: level. Transcript nextPutAll: self name; nl. mySubclasses := self subclasses asSortedCollection: [ :a :b | (a name isNil or: [ b name isNil ]) ifTrue: [ true ] ifFalse: [ a name <= b name ] ]. mySubclasses do: [ :subclass | subclass class ~~ Metaclass ifTrue: [ subclass printSubclasses: level + 1 ] ] ! indentToLevel: level level timesRepeat: [ Transcript next: (self hierarchyIndent) put: Character space ] ! hierarchyIndent ^4 ! ! Object printHierarchy! smalltalk-3.2.5/examples/Queens.st0000644000175000017500000001673212123404352014061 00000000000000"====================================================================== | | Smalltalk eight queens | | ======================================================================" "====================================================================== | | Copyright 1999, 2000, 2001 Free Software Foundation, Inc. | Written by Paolo Bonzini. | | This file is part of GNU Smalltalk. | | GNU Smalltalk is free software; you can redistribute it and/or modify it | under the terms of the GNU General Public License as published by the Free | Software Foundation; either version 2, or (at your option) any later version. | | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS | FOR A PARTICULAR PURPOSE. See the GNU General Public License for more | details. | | You should have received a copy of the GNU General Public License along with | GNU Smalltalk; see the file COPYING. If not, write to the Free Software | Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. | ======================================================================" "That's how a *real* Smalltalker solves the eight queens' problem: with four classes (one is for amazons)!!" Object subclass: #NullChessPiece instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Examples-Classic'! NullChessPiece subclass: #ChessPiece instanceVariableNames: 'row column neighbor rows' classVariableNames: '' poolDictionaries: '' category: 'Examples-Classic'! ! ! ChessPiece subclass: #Rook instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Examples-Classic'! ! ! "From the code's point of view, Amazon and Queen could subclass directly from ChessPiece, but it is more cool this way... ;-)" Rook subclass: #Queen instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Examples-Classic'! ! ! Queen subclass: #Amazon instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Examples-Classic'! ! ! !NullChessPiece methodsFor: 'queens'! move "Move the queen so that it is not menaced, backtracking if necessary. Answer whether a position can be found. If the null queen is asked to advance, the search tree has been walked entirely - so return false." ^false ! menaces: test "Answer whether a queen is menaced in the given position by the queens up to and including the receiver. The null queen does not menace anything." ^false ! do: aBlock "Evaluate aBlock passing all the remaining solutions" | result | [ result := self next. result notNil ] whileTrue: [ aBlock value: result ] ! result "Answer all the queens' rows, up to and including the receiver" ^OrderedCollection new ! next "Answer a solution, or nil if there aren't anymore" ^self move ifTrue: [ self result ] ifFalse: [ nil ] ! ! !ChessPiece class methodsFor: 'testing'! test: side | line n | (line := String new: side * 2 + 1) atAll: (1 to: side * 2 + 1 by: 2) put: $|; atAll: (2 to: side * 2 + 1 by: 2) put: $_. n := 0. (self board: side) do: [ :result | n := n + 1. Transcript space; next: side * 2 - 1 put: $_; nl. result do: [:x | line at: x + x put: $*. Transcript nextPutAll: line; nl. line at: x + x put: $_. ]. Transcript nl. ]. Transcript nl. ^n! ! !ChessPiece class methodsFor: 'instance creation'! board: n "Answer a ChessPiece which will return results for a chessboard of side n" ^(1 to: n) inject: NullChessPiece new into: [ :neighbor :column | self new setColumn: column rows: n neighbor: neighbor ] ! ! !ChessPiece methodsFor: 'private'! setColumn: aNumber rows: n neighbor: aChessPiece "Initialize the receiver to work on column aNumber of a chessboard of side n, having aChessPiece as a neighbor" column := aNumber. rows := n. neighbor := aChessPiece. row := 0. "Put all the queens but the last in some place where they are safe. The last will be requested by sending #next" self neighbor move. ^self ! advance "Move the receiver one row further if possible, else backtrack and move to the first row. Answer whether there was a safe position for the neighbor (in the first case, the neighbor was already in a safe position, so answer true!)" ^row = rows ifTrue: [ row := 1. self neighbor move ] ifFalse: [ row := row + 1. true ]. ! row ^row ! column ^column ! neighbor ^neighbor ! ! !ChessPiece methodsFor: 'inherited'! menaces: test "Answer whether the receiver or any of the pieces above it menace the `test' piece if it stays where its #row and #column methods say. This method will test if the receiver itself menaces the tested piece and if not will delegate the choice to the neighbor." self subclassResponsibility ! move "Here and in #advance is where the search really takes place. We advance the queen to the next cell; if the edge has been reached, #advance takes care of backtracking by sending #move to the neighbor (which in turn could backtrack). If the queen is safe there, return true; else we advance the queen once more and check again. Sooner or later every queen will be aligned on the right edge and each one will be ask its neighbor to advance. So the first queen will send #move to the NullChessPiece, the NullChessPiece will answer false, and all the invocations of #move will in turn answer false, terminating the search." [ self advance ifFalse: [ ^false ]. self neighbor menaces: self ] whileTrue: [ ]. ^true ! result ^self neighbor result addLast: row; yourself ! ! !Rook methodsFor: 'inherited'! menaces: test "Answer whether the receiver or any of the pieces above it menace the `test' piece if it stays where its #row and #column methods say." (test row - self row) abs = 0 ifTrue: [ ^true ]. ^self neighbor menaces: test ! ! !Queen methodsFor: 'inherited'! menaces: test "Answer whether the receiver or any of the pieces above it menace the `test' piece if it stays where its #row and #column methods say." | columnDifference rowDifference | columnDifference := (test column - self column) abs. rowDifference := (test row - self row) abs. rowDifference = 0 ifTrue: [ ^true ]. rowDifference = columnDifference ifTrue: [ ^true ]. ^self neighbor menaces: test ! ! !Amazon methodsFor: 'inherited'! menaces: test "Answer whether the receiver or any of the pieces above it menace the `test' piece if it stays where its #row and #column methods say." | columnDifference rowDifference | columnDifference := (test column - self column) abs. rowDifference := (test row - self row) abs. rowDifference = 0 ifTrue: [ ^true ]. rowDifference = columnDifference ifTrue: [ ^true ]. rowDifference * 2 = columnDifference ifTrue: [ ^true ]. columnDifference * 2 = rowDifference ifTrue: [ ^true ]. ^self neighbor menaces: test ! ! " EVALUATE THIS: " "RESULT " " ^Rook test: 3! " "6 " " ^Rook test: 4! " "24 " " ^Rook test: 5! " "120 " " ^Rook test: 6! " "720 " " ^Queen test: 3! " "0 " " ^Queen test: 4! " "2 " " ^Queen test: 8! " "92 " " ^Amazon test: 8! " "0 " " ^Amazon test: 10! " "4 " "does the sequence for rooks remind you of something?..." smalltalk-3.2.5/examples/shell0000755000175000017500000001406512123404352013303 00000000000000#! /bin/sh "exec" "gst" "-f" "$0" "$@" "====================================================================== | | Example of starting a Smalltalk program from the shell | ======================================================================" " The first line above is parsed specially by GNU Smalltalk. gst -f | is similar to passing -aQ after the first argument, so the net result | is that of executing | | gst /path/to/this/script -aQ param1 param2 paramN | | Also, GNU Smalltalk sees five comments instead of the shell command | `exec gst -f $0 "$@"'. | | Now here is the file juggler by Alexander Lazarevic, the first Smalltalk | script known to me. | | Usage: popoolate [inputdir] [pooldir] | | I assume everybody has this one kind of folder called temp, incoming, | files or whatever. There is all the rubble you've downloaded from the | web (and surprisingly much more). Once in a while you wade through | all the files and delete the ones you think you don't need | anymore. The rest stays in the folder and the folder grows and | grows... | This kind of folder is what popoolate expects as the inputdir | parameter. Basically popoolate just copies the files from inputdir to | pooldir, but in addition it creates subfolders in pooldir according | to the filenames. | For example I have a directory (in) where I have some snapshots of my | son, some karaoke music and some other stuff. After using popoolate | the folder in will be empty and the folder pool will have | the following structure: | in--Leon-0019.jpg pool - l - leon - leon-0019.jpg | Leon-0030.jpg leon-0020.jpg | PeSo-99.mp3 leon10.jpg | World_9.pdf p - peso - peso-99.mp3 | leon10.jpg pop - pop10a.mp3 | pop10a.mp3 pop10b.mp3 | pop10b.mp3 pop10c.mp3 | pop10c.mp3 w - world - world-1.pdf | world-1.pdf world_9.pdf " | error inputDir poolDir namePattern rightPattern | PackageLoader fileInPackages: #('Regex'). error := [:message| stderr nextPutAll: message; nl. ObjectMemory quit: 1]. Smalltalk arguments size ~= 2 ifTrue: [error value: 'usage: popoolate [inputdir] [pooldir]']. inputDir := Directory name: (Smalltalk arguments first). inputDir isDirectory ifFalse: [error value: '"', inputDir name, '" is no directory!']. inputDir isWriteable ifFalse: [error value: '"', inputDir name, '" is unwriteable!']. inputDir isReadable ifFalse: [error value: '"', inputDir name, '" is unreadable!']. inputDir isAccessible ifFalse: [error value: '"', inputDir name, '" is unaccessible!']. poolDir := Directory name: (Smalltalk arguments last). inputDir isDirectory ifFalse: [error value: '"', inputDir name, '" is no directory!']. inputDir isWriteable ifFalse: [error value: '"', inputDir name, '" is unwriteable!']. inputDir isAccessible ifFalse: [error value: '"', inputDir name, '" is unaccessible!']. "Uncomment this to test.... #('a' 'noep' 'aa' 'n' 'Bnm' 'HjKlo') do: [:name| 1 to: 300 do: [:num||file| file := FileStream open: '/tmp/in/', name, '-', num printString, '.tst' mode: FileStream write. file close]] ]." namePattern := ( '[~]', "Not allowed anywhere in the filename" '|', '^[!._]', "Not allowed at the beginning" '|', '^.*\\', "Cut DOS path" '|', '\s[^.]*$') "Cut trailing garbage after extension" asRegex. "This pattern assumes that a (lowercase) filename belongs to a series of filenames and that it has a left and right side. The left side is the stem part and is the same for all filenames in the series. The right side consists of an index part and a file extension (in that order). This pattern tries to match the index part and file extension (right side), leaving the stem part (left side)." rightPattern := ( '(', "Index part might start with" '([_-])\d+', "a _ or - and at least one digit" '|', "or" '(\d\d\d|\d\d|\d)', "with exactly three, two or one digit(s) as an index number" ')', '[a-z]?', "Between index part and extension might be" "a single letter" '\..*') "The extension is anything including the first dot upto the end, eg. .pdf but also .tex.gz" asRegex. inputDir contents do: [:origname|| file | file := inputDir at: origname. ((origname first = $. or: [file isDirectory]) or: [file isReadable not]) ifTrue: [stdout nextPutAll: 'Ignoring ', origname; nl] ifFalse: [| cleanname series slot seriesDir slotDir| cleanname := origname asLowercase. cleanname := cleanname copyReplacingAllRegex: namePattern with: ''. series := cleanname copyReplacingAllRegex: rightPattern with: ''. (series isEmpty or: [series = cleanname]) ifTrue: [slot := 'single'. series := nil.] ifFalse: [series first isAlphaNumeric ifTrue: [slot := series first asString] ifFalse: [slot := 'misc']]. slotDir := (poolDir directoryAt: slot). slotDir exists ifFalse: [Directory create: slotDir name. stdout nextPutAll: slotDir name, ' created.';nl]. series = nil ifTrue: [seriesDir := slotDir] ifFalse: [seriesDir := (slotDir directoryAt: series). seriesDir exists ifFalse: [Directory create: seriesDir name. stdout nextPutAll: seriesDir name, ' created.';nl]]. stdout nextPutAll: origname, ' -> ', (seriesDir nameAt: cleanname); nl. file renameTo: '/', (seriesDir fullNameAt: cleanname). ]]. ObjectMemory quit: 0. ! smalltalk-3.2.5/examples/Lisp.st0000644000175000017500000020001312123404352013513 00000000000000"====================================================================== | | Lisp interpreter written in Smalltalk | | ======================================================================" "====================================================================== | | Written by Aoki Atsushi and Nishihara Satoshi. | Modified by Paolo Bonzini (removed GUI and compiler for subset of Smalltalk). | | This file is part of GNU Smalltalk. | | GNU Smalltalk is free software; you can redistribute it and/or modify it | under the terms of the GNU General Public License as published by the Free | Software Foundation; either version 2, or (at your option) any later version. | | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS | FOR A PARTICULAR PURPOSE. See the GNU General Public License for more | details. | | You should have received a copy of the GNU General Public License along with | GNU Smalltalk; see the file COPYING. If not, write to the Free Software | Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. | ======================================================================" SequenceableCollection subclass: #LispList instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Examples-Lisp'! LispList subclass: #LispCons instanceVariableNames: 'head tail ' classVariableNames: 'VerticalLevel HorizontalLevel ' poolDictionaries: '' category: 'Examples-Lisp'! LispList subclass: #LispNil instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Examples-Lisp'! Object subclass: #LispScanner instanceVariableNames: 'source mark token tokenType failBlock ' classVariableNames: 'ScanningTable ' poolDictionaries: '' category: 'Examples-Lisp'! LispScanner subclass: #LispParser instanceVariableNames: 'prevMark prevToken prevTokenType ' classVariableNames: '' poolDictionaries: '' category: 'Examples-Lisp'! Object subclass: #LispTable instanceVariableNames: 'properties ' classVariableNames: '' poolDictionaries: '' category: 'Examples-Lisp'! Object subclass: #LispInterpreter instanceVariableNames: 'lispTable bindStack failBlock textValue textCollector ' classVariableNames: '' poolDictionaries: '' category: 'Examples-Lisp'! !LispList class methodsFor: 'copyright'! copyright ^'Copyright (C) 1995-1998 AOKI Atsushi, All Rights Reserved.'! system ^'Goodies'! version ^'003'! ! !LispList class methodsFor: 'instance creation'! cell ^self subclassResponsibility! head: headObject ^self subclassResponsibility! head: headObject tail: tailObject ^self subclassResponsibility! list: anArray "LispCons list: #(1 2 3 4)" | size list | size := anArray size. list := self null. size to: 1 by: -1 do: [:i | list := self head: (anArray at: i) tail: list]. ^list! new: anInteger "LispCons new: 5" | newList | newList := self null. anInteger timesRepeat: [newList := self head: self null tail: newList]. ^newList! null ^self subclassResponsibility! with: anObject "LispCons with: 1" ^self head: anObject! with: firstObject with: secondObject "LispCons with: 1 with: 2" ^self head: firstObject tail: (self with: secondObject)! with: firstObject with: secondObject with: thirdObject "LispCons with: 1 with: 2 with: 3" ^self head: firstObject tail: (self with: secondObject with: thirdObject)! with: firstObject with: secondObject with: thirdObject with: fourthObject "LispCons with: 1 with: 2 with: 3 with: 4" ^self head: firstObject tail: (self with: secondObject with: thirdObject with: fourthObject)! ! !LispList methodsFor: 'accessing'! at: indexInteger put: anObject ^self subscriptOutOfBoundsError: indexInteger! size | tally | tally := 0. self do: [:each | tally := tally + 1]. ^tally! ! !LispList methodsFor: 'private'! subscriptOutOfBoundsError: index ^self error: 'subscript out of bounds: ' , index printString! ! !LispList methodsFor: 'testing'! isCons ^self null not! null ^false! ! !LispCons class methodsFor: 'class initialization'! initialize "LispCons initialize." HorizontalLevel := VerticalLevel := nil! ! !LispCons class methodsFor: 'copyright'! copyright ^'Copyright (C) 1995-1998 AOKI Atsushi, All Rights Reserved.'! system ^'Goodies'! version ^'003'! ! !LispCons class methodsFor: 'examples'! example1 "LispCons example1." | list | list := LispCons list: #(1 2 3 4 5 6 7 8 9 10 ). Transcript nl; show: list printString. ^list! example2 "LispCons example2." | null list | null := LispCons null. list := LispCons list: #(1 2 ). list := LispCons head: list tail: null. list := LispCons head: list tail: null. Transcript nl; show: list printString. ^list! example3 "LispCons example3." | x y z | x := LispCons list: #(1 2 3 ). y := LispCons list: #(4 5 6 ). z := LispCons list: #(1 2 3 4 5 6 ). Transcript nl; show: '(setq x ''(1 2 3)) => ' , x printString. Transcript nl; show: '(setq y ''(4 5 6)) => ' , y printString. Transcript nl; show: '(setq z ''(1 2 3 4 5 6)) => ' , z printString. Transcript nl; show: '(append x y) => ' , (x append: y) printString. Transcript nl; show: '(length z) => ' , z length printString. Transcript nl; show: '(member 3 z) => ' , (z member: 3) printString. Transcript nl; show: '(nth 4 z) => ' , (z nth: 4) printString. ^z! example4 "LispCons example4." | list | list := LispCons list: #(1 2 ). list := LispCons head: list tail: (LispCons list: #(3 4 )). list := LispCons head: list tail: (LispCons list: #(5 6 )). Transcript nl; show: list saveString. ^list! example5 "LispCons example5." | list | list := LispCons loadFrom: ' (PetriNet Aoki (Place p1 p2 p3 p4 p5) (Transition t1 t2 t3 t4 t5) (InputFunction (t1 p1 p2 p3 p4 p5) (t2 . p4) (t3 . p5)) (OutputFunction (t1 p1 p2 p3 p4 p5) (t2 . p4) (t3 . p5)) (Marking {#(1 2 3 4 5)})))'. Transcript nl; show: list saveString. ^list! example6 "LispCons example6." | list | list := LispCons loadFrom: '(aaa bbb ccc)'. Transcript nl; show: list saveString. ^list! example7 "LispCons example7." | list | list := LispCons loadFrom: ' `(`(1 2 `3) . `4 ) '. Transcript nl; show: list saveString. ^list! ! !LispCons class methodsFor: 'instance creation'! cell ^super new head: self null tail: self null! head: headObject ^super new head: headObject tail: self null! head: headObject tail: tailObject ^super new head: headObject tail: tailObject! list: anArray | size list | size := anArray size. list := self null. size to: 1 by: -1 do: [:i | list := self head: (anArray at: i) tail: list]. ^list! loadFrom: aStream "by nishis, 1998/04/19 07:51" | list | list := LispParser parse: aStream. ^list! new ^self cell! null ^LispNil null! ! !LispCons class methodsFor: 'level accessing'! horizontalLevel HorizontalLevel isNil ifTrue: [HorizontalLevel := 50]. ^HorizontalLevel! horizontalLevel: anInteger HorizontalLevel := anInteger! verticalLevel VerticalLevel isNil ifTrue: [VerticalLevel := 10]. ^VerticalLevel! verticalLevel: anInteger VerticalLevel := anInteger! ! !LispCons class methodsFor: 'utilities'! classHierarchy: aClass "LispCons classHierarchy: Number." | theClass list | aClass isMeta ifTrue: [theClass := aClass soleInstance] ifFalse: [theClass := aClass]. list := self subclassHierarchy: theClass. (theClass allSuperclasses select: [:each | each isMeta not]) do: [:each | list := self head: each name tail: (self head: list tail: self null)]. ^list! subclassHierarchy: aClass "LispCons subclassHierarchy: Number." | theClass list collection sub | aClass isMeta ifTrue: [theClass := aClass soleInstance] ifFalse: [theClass := aClass]. list := self null. theClass subclasses isEmpty ifFalse: [collection := SortedCollection sortBlock: [:x :y | x name > y name]. collection addAll: (theClass subclasses select: [:each | each isMeta not]). collection do: [:each | sub := self subclassHierarchy: each. list := self head: sub tail: list]]. ^self head: theClass name tail: list! superclassHierarchy: aClass "LispCons superclassHierarchy: Number." | theClass list | aClass isMeta ifTrue: [theClass := aClass soleInstance] ifFalse: [theClass := aClass]. list := self head: theClass name tail: self null. (theClass allSuperclasses select: [:each | each isMeta not]) do: [:each | list := self head: each name tail: (self head: list tail: self null)]. ^list! ! !LispCons methodsFor: 'accessing'! at: indexInteger | count | count := 1. self mapcdr: [:cdr | indexInteger = count ifTrue: [^cdr head]. count := count + 1]. ^self subscriptOutOfBoundsError: indexInteger! at: indexInteger put: anObject | count | count := 1. self mapcdr: [:cdr | indexInteger = count ifTrue: [^cdr head: anObject]. count := count + 1]. ^self subscriptOutOfBoundsError: indexInteger! head ^head! head: anObject ^head := anObject! head: headObject tail: tailObject self head: headObject. self tail: tailObject! tail ^tail! tail: anObject ^tail := anObject! ! !LispCons methodsFor: 'adding'! add: newObject ^self nconc: (self class head: newObject tail: self class null)! ! !LispCons methodsFor: 'enumerating'! collect: aBlock | list result | list := self. result := self class null. [list isKindOf: self class] whileTrue: [result := self class head: (aBlock value: list head) tail: result. list := list tail]. ^result reverse! do: aBlock | list | list := self. [list isKindOf: self class] whileTrue: [aBlock value: list head. list := list tail]! ! !LispCons methodsFor: 'functions'! append: list (tail isKindOf: self class) ifFalse: [^self class head: head tail: list]. ^self class head: head tail: (tail append: list)! last | list | list := self class head: nil tail: self. self do: [:each | list := list tail]. ^list! length | count | count := 0. self do: [:each | count := count + 1]. ^count! mapcdr: aBlock | list | list := self. [list isKindOf: self class] whileTrue: [aBlock value: list. list := list tail]! member: anObject | list | list := self. self do: [:each | each = anObject ifTrue: [^list]. list := list tail]. ^self species null! memq: anObject | list | list := self. self do: [:each | each == anObject ifTrue: [^list]. list := list tail]. ^self species null! nconc: list self last rplacd: list! nth: nth | count list | nth <= 0 ifTrue: [^self species null]. count := 1. list := self. list do: [:each | count >= nth ifTrue: [^each]. count := count + 1]. ^self species null! reverse | list | list := self class null. self do: [:each | list := self class head: each tail: list]. ^list! rplaca: anObject self head: anObject! rplacd: anObject self tail: anObject! ! !LispCons methodsFor: 'pretty printing'! ppOn: aStream self ppOn: aStream list: self position: 0. aStream nl! ppOn: aStream list: list position: position (list isKindOf: self class) ifFalse: [^self ppOn: aStream object: list]. (list head isKindOf: self class) not ifTrue: [aStream nextPutAll: '('. self ppOn: aStream object: list head. (list tail isKindOf: LispList) ifTrue: [self ppOn: aStream tail: list tail position: position + 1] ifFalse: [aStream nextPutAll: ' . '. self ppOn: aStream object: list tail]. aStream nextPutAll: ')'] ifFalse: [aStream nextPutAll: '('. self ppOn: aStream list: list head position: position + 1. (list tail isKindOf: self class) ifTrue: [(list tail head isKindOf: self class) ifTrue: [aStream nl. self ppOn: aStream spaceAndTab: position. self ppOn: aStream tail: list tail position: position] ifFalse: [self ppOn: aStream space: 1. self ppOn: aStream tail: list tail position: position + 1]] ifFalse: [(list tail isKindOf: LispList) ifFalse: [aStream nextPutAll: ' . '. self ppOn: aStream object: list tail]]. aStream nextPutAll: ')']! ppOn: aStream object: anObject (anObject isKindOf: Symbol) ifTrue: [^aStream nextPutAll: anObject asString]. (anObject isKindOf: String) ifTrue: [aStream nextPutAll: '"'. anObject do: [:char | char = $" ifTrue: [aStream nextPut: $"]. aStream nextPut: char]. ^aStream nextPutAll: '"']. (anObject isKindOf: Number) ifTrue: [^anObject storeOn: aStream]. (anObject isMemberOf: LispNil) ifTrue: [^aStream nextPutAll: 'nil']. aStream nextPutAll: '{'. aStream nextPutAll: (anObject printString contractTo: 80). aStream nextPutAll: '}'! ppOn: aStream space: anInteger anInteger timesRepeat: [aStream nextPut: Character space]! ppOn: aStream spaceAndTab: anInteger | tabs spaces | tabs := anInteger // self tabStop. spaces := anInteger \\ self tabStop. tabs * (self tabStop // 4) timesRepeat: [aStream tab]. spaces timesRepeat: [aStream space]! ppOn: aStream tail: list position: position list null ifTrue: [^self]. (list tail isKindOf: LispList) ifTrue: [list tail null ifTrue: [self ppOn: aStream space: 1. self ppOn: aStream list: list head position: position + 1] ifFalse: [self ppOn: aStream space: 1. self ppOn: aStream list: list head position: position + 1. aStream nl. self ppOn: aStream spaceAndTab: position. self ppOn: aStream tail: list tail position: position]] ifFalse: [self ppOn: aStream space: 1. self ppOn: aStream list: list head position: position + 1. aStream nextPutAll: ' . '. self ppOn: aStream object: list tail]! ppString | stream | stream := WriteStream on: (String new: 20). self ppOn: stream. ^stream contents! ! !LispCons methodsFor: 'printing'! printOn: aStream self printOn: aStream level: 0! printOn: aStream level: level | verticalLevel | verticalLevel := self class verticalLevel. (verticalLevel ~= 0 and: [level >= verticalLevel]) ifTrue: [aStream nextPutAll: '( ... )'. ^self]. self null ifTrue: [^super printOn: aStream]. aStream nextPutAll: '('. (head isKindOf: self class) ifTrue: [head printOn: aStream level: level + 1] ifFalse: [self printOn: aStream object: head]. (tail isKindOf: LispList) ifTrue: [self printOn: aStream tail: tail level: level] ifFalse: [aStream nextPutAll: ' . '. self printOn: aStream object: tail. ^aStream nextPutAll: ')']! printOn: aStream object: anObject (anObject isKindOf: Symbol) ifTrue: [^aStream nextPutAll: anObject asString]. (anObject isKindOf: String) ifTrue: [aStream nextPutAll: '"'. anObject do: [:char | char = $" ifTrue: [aStream nextPut: $"]. aStream nextPut: char]. ^aStream nextPutAll: '"']. (anObject isKindOf: Number) ifTrue: [^anObject storeOn: aStream]. (anObject isMemberOf: LispNil) ifTrue: [^aStream nextPutAll: 'nil']. aStream nextPutAll: '{'. aStream nextPutAll: (anObject printString contractTo: 80). aStream nextPutAll: '}'! printOn: aStream tail: cdr level: level | tailPart count horizontalLevel | cdr null ifTrue: [^aStream nextPutAll: ')']. tailPart := cdr. count := 1. horizontalLevel := self class horizontalLevel. tailPart do: [:each | (horizontalLevel ~= 0 and: [count >= horizontalLevel]) ifTrue: [aStream nextPutAll: ' ... )'. ^self]. aStream nextPutAll: ' '. (each isKindOf: self class) ifTrue: [tailPart head printOn: aStream level: level + 1] ifFalse: [self printOn: aStream object: each]. tailPart := tailPart tail. count := count + 1]. (tailPart isKindOf: LispList) ifTrue: [aStream nextPutAll: ')'] ifFalse: [aStream nextPutAll: ' . '. self printOn: aStream object: tailPart. aStream nextPutAll: ')']! ! !LispCons methodsFor: 'private'! tabStop ^8! ! !LispCons methodsFor: 'saving'! saveOn: aStream self saveOn: aStream list: self position: 0. aStream nl! saveOn: aStream list: list position: position | location length | (list isKindOf: self class) ifFalse: [^self saveOn: aStream object: list]. (list head isKindOf: self class) not ifTrue: [aStream nextPutAll: '('. location := aStream position. self saveOn: aStream object: list head. (list tail isKindOf: LispList) ifTrue: [length := aStream position - location min: 40. length := 0. self saveOn: aStream tail: list tail position: position + 1 + length] ifFalse: [aStream nextPutAll: ' . '. self saveOn: aStream object: list tail]. aStream nextPutAll: ')'] ifFalse: [aStream nextPutAll: '('. self saveOn: aStream list: list head position: position + 1. (list tail isKindOf: self class) ifTrue: [(list tail head isKindOf: self class) ifTrue: [aStream nl. self saveOn: aStream spaceAndTab: position. self saveOn: aStream tail: list tail position: position] ifFalse: [self saveOn: aStream space: 1. self saveOn: aStream tail: list tail position: position + 1]] ifFalse: [(list tail isKindOf: LispList) ifFalse: [aStream nextPutAll: ' . '. self saveOn: aStream object: list tail]]. aStream nextPutAll: ')']! saveOn: aStream object: anObject | string | (anObject isKindOf: Symbol) ifTrue: [^aStream nextPutAll: anObject asString]. (anObject isKindOf: String) ifTrue: [aStream nextPutAll: '"'. anObject do: [:char | char = $" ifTrue: [aStream nextPut: $"]. aStream nextPut: char]. ^aStream nextPutAll: '"']. (anObject isKindOf: Integer) ifTrue: [^anObject storeOn: aStream]. (anObject isKindOf: Float) ifTrue: [^anObject storeOn: aStream]. "(anObject isKindOf: Double) ifTrue: [^anObject storeOn: aStream]." (anObject isMemberOf: LispNil) ifTrue: [^aStream nextPutAll: 'nil']. aStream nextPutAll: '{'. ((anObject isKindOf: Point) or: [anObject isKindOf: Rectangle]) ifTrue: [string := anObject printString] ifFalse: [string := anObject storeString]. aStream nextPutAll: string. aStream nextPutAll: '}'! saveOn: aStream space: anInteger anInteger timesRepeat: [aStream nextPut: Character space]! saveOn: aStream spaceAndTab: anInteger | tabs spaces | tabs := anInteger // self tabStop. spaces := anInteger \\ self tabStop. tabs timesRepeat: [aStream tab]. spaces timesRepeat: [aStream space]! saveOn: aStream tail: list position: position list null ifTrue: [^self]. (list tail isKindOf: LispList) ifTrue: [list tail null ifTrue: [self saveOn: aStream space: 1. self saveOn: aStream list: list head position: position + 1] ifFalse: [self saveOn: aStream space: 1. self saveOn: aStream list: list head position: position + 1. aStream nl. self saveOn: aStream spaceAndTab: position. self saveOn: aStream tail: list tail position: position]] ifFalse: [self saveOn: aStream space: 1. self saveOn: aStream list: list head position: position + 1. aStream nextPutAll: ' . '. self saveOn: aStream object: list tail]! saveString | stream | stream := WriteStream on: (String new: 20). self saveOn: stream. ^stream contents! ! !LispCons methodsFor: 'testing'! = anObject (anObject isKindOf: self class) ifFalse: [^false]. self head = anObject head ifTrue: [^self tail = anObject tail]. ^false! ! LispCons initialize! LispNil class instanceVariableNames: 'null '! !LispNil class methodsFor: 'class initialization'! initialize "LispNil initialize." self null! ! !LispNil class methodsFor: 'copyright'! copyright ^'Copyright (C) 1995-1998 AOKI Atsushi, All Rights Reserved.'! system ^'Goodies'! version ^'003'! ! !LispNil class methodsFor: 'instance creation'! cell ^LispCons cell! head: headObject ^self shouldNotImplement! head: headObject tail: tailObject ^self shouldNotImplement! new ^self null! null null isNil ifTrue: [null := super new]. ^null! ! !LispNil methodsFor: 'accessing'! head ^self! tail ^self! ! !LispNil methodsFor: 'adding'! add: newObject ^self shouldNotImplement! ! !LispNil methodsFor: 'enumerating'! do: aBlock ^self! ! !LispNil methodsFor: 'functions'! append: list ^list! length ^0! mapcdr: aBlock ^self! member: anObject ^self! nconc: list ^list! nth: nth ^self! reverse ^self! ! !LispNil methodsFor: 'pretty printing'! ppOn: aStream aStream nextPutAll: 'nil'. aStream nl! ppString ^'nil\' withCRs! ! !LispNil methodsFor: 'printing'! printOn: aStream aStream nextPutAll: 'nil'! ! !LispNil methodsFor: 'saving'! saveOn: aStream aStream nextPutAll: 'nil'! saveString ^'nil'! ! !LispNil methodsFor: 'testing'! null ^true! ! LispNil initialize! !LispScanner class methodsFor: 'copyright'! copyright ^'Copyright (C) 1995-1998 AOKI Atsushi, All Rights Reserved.'! system ^'Goodies'! version ^'003'! ! !LispScanner class methodsFor: 'initialize-release'! initialize | newTable | newTable := Array new: 256 withAll: #xBinary. newTable atAll: #(9 10 11 12 13 32) put: #xDelimiter. newTable atAll: ($0 asInteger to: $9 asInteger) put: #xDigit. newTable atAll: ($A asInteger to: $Z asInteger) put: #xSymbol. newTable atAll: ($a asInteger to: $z asInteger) put: #xSymbol. 128 to: 256 do: [:i | newTable at: i put: #xSymbol]. newTable at: $' asInteger put: #quote. newTable at: $" asInteger put: #xDoubleQuote. newTable at: ${ asInteger put: #xBrace. newTable at: $+ asInteger put: #xSign. newTable at: $- asInteger put: #xSign. newTable at: $< asInteger put: #xSymbol. newTable at: $> asInteger put: #xSymbol. newTable at: $= asInteger put: #xSymbol. newTable at: $~ asInteger put: #xSymbol. newTable at: $* asInteger put: #xSymbol. newTable at: $/ asInteger put: #xSymbol. newTable at: $_ asInteger put: #xSymbol. newTable at: $: asInteger put: #xSymbol. newTable at: $, asInteger put: #xSymbol. newTable at: $\ asInteger put: #xSymbol. newTable at: $% asInteger put: #xComment. newTable at: $( asInteger put: #leftParenthesis. newTable at: $) asInteger put: #rightParenthesis. newTable at: $[ asInteger put: #leftParenthesis. newTable at: $] asInteger put: #rightParenthesis. newTable at: $. asInteger put: #period. newTable at: $` asInteger put: #quote. newTable at: $! asInteger put: #eof. ScanningTable := newTable! ! !LispScanner class methodsFor: 'instance creation'! new ^(super new) initScanner; yourself! ! !LispScanner methodsFor: 'initialize-release'! initScanner failBlock := [:errorMessage || label string | label := errorMessage , ' near ' , (token printString contractTo: 10). string := source upToEnd. string isEmpty ifTrue: [string := '--> end of file'] ifFalse: [string := '--> ' , (string contractTo: 30)]. self error: 'scan error ', label, Character nl asString, string]. ! on: inputStream source := inputStream. mark := source position! ! !LispScanner methodsFor: 'private'! nextChar | char | source atEnd ifTrue: [ ^$! ]. char := source next. char = Character cr ifTrue: [char := Character nl. source peekFor: char]. ^char! peekChar | char | char := source peek. char = Character cr ifTrue: [char := Character nl]. char isNil ifTrue: [char := $! ]. ^char! unNextChar source skip: -1! ! !LispScanner methodsFor: 'reading'! numberFrom: aStream ^Number readFrom: aStream! objectFrom: aStream "POSSIBLE PORTABILITY PROBLEM HERE!" | buffer char | buffer := WriteStream on: (String new: 20). char := aStream next. [char := aStream next. char = $}] whileFalse: [char == nil ifTrue: [^failBlock value: 'Syntax error unmatched ${']. buffer nextPut: char]. ^Behavior evaluate: buffer contents to: nil ifError: []! stringFrom: aStream | buffer char string | buffer := WriteStream on: (String new: 20). char := aStream next. char = $" ifTrue: [ [char := aStream peek. char ~~ nil] whileTrue: [char = $" ifTrue: [aStream next. char := aStream peek. char = $" ifFalse: [^String fromString: buffer contents]]. buffer nextPut: aStream next]]. string := aStream upToEnd. string size > 100 ifTrue: [string := string copyFrom: 1 to: 100]. ^failBlock value: 'Syntax error unmatched $'''! symbolFrom: aStream | buffer char type | buffer := WriteStream on: (String new: 20). char := aStream peek. [char notNil and: [(type := self tableAt: char) == #xSymbol or: [type == #xDigit or: [type == #xSign]]]] whileTrue: [buffer nextPut: aStream next. char := aStream peek]. buffer contents = 'nil' ifTrue: [^LispNil null]. ^Symbol intern: buffer contents! ! !LispScanner methodsFor: 'scanning'! multiChar: type self perform: type! nextToken | char | mark := source position. char := self peekChar. tokenType := self tableAt: char. [tokenType == #xDelimiter] whileTrue: [self nextChar. char := self peekChar. tokenType := self tableAt: char]. (tokenType at: 1) = $x ifTrue: [self multiChar: tokenType] ifFalse: [self singleChar: tokenType]. ^token! singleChar: type self nextChar. token := type! tableAt: char | index | index := char asInteger. ^index = 0 ifFalse: [ScanningTable at: index] ifTrue: [#xBinary]! unNextToken source position: mark! ! !LispScanner methodsFor: 'x'! xBinary ^failBlock value: 'Syntax error ' , source peek printString! xBrace tokenType := #object. token := self objectFrom: source! xComment | char | [(char := self nextChar) = Character nl] whileFalse: [char == nil ifTrue: [^self nextToken]]. ^self nextToken! xDigit tokenType := #number. token := self numberFrom: source! xDoubleQuote tokenType := #string. token := self stringFrom: source! xSign | char sign | sign := self nextChar. char := self peekChar. char isDigit ifTrue: [tokenType := #number. token := self numberFrom: source. sign == $- ifTrue: [token := token negated]] ifFalse: [self unNextChar. tokenType := #symbol. token := self symbolFrom: source]! xSymbol tokenType := #symbol. token := self symbolFrom: source! ! LispScanner initialize! !LispParser class methodsFor: 'copyright'! copyright ^'Copyright (C) 1995-1998 AOKI Atsushi, All Rights Reserved.'! system ^'Goodies'! version ^'003'! ! !LispParser class methodsFor: 'examples'! example1 "LispParser example1." | list | list := LispParser parse: '(1 2 3 4 (5 6 7 8 9) 10)'. ^list! example2 "LispParser example2." | list | list := LispParser parse: ' (10 (1 2) 20 (3 4 . 100) 30 (5 6) . 200) '. ^list! example3 "LispParser example3." | list | list := LispParser parse: ' (PetriNet Aoki (Place (p1 . {100@100}) (p2 . {200@200}) (p3 . {300@300}) (p4 . {400@400}) (p5 . {500@500})) (Transition (t1 . {100@100}) (t2 . {200@200}) (t3 . {300@300}) (t4 . {400@400}) (t5 . {500@500})) (InputFunction (t1 p1 p2 p3 p4 p5) (t2 . p4) (t3 . p5)) (OutputFunction (t1 p1 p2 p3 p4 p5) (t2 . p4) (t3 . p5)) (Marking {#(1 2 3 4 5)}))'. Transcript nl; show: list saveString. list := LispParser parse: list saveString. ^list! example4 "LispParser example4." | list | list := LispParser parse: '(1 2 3 4 (5 6 7 ~ 8 9) 10)'. ^list! example5 "LispParser example5." | list | list := LispParser parse: '(1 2 3 4 (5 6 7 {100@100 8 9) 10)'. "error" ^list! example6 "LispParser example6." | list | list := LispParser parse: '(1 2 3 4 (5 6 7 ''aaaaa 8 9) 10)'. ^list! example7 "LispParser example7." | list | list := LispParser parse: ' `(`(1 2 `3) . `4) '. "`(`(1 2 `3) . `4) -> (quote ((quote (1 2 (quote 3))) quote 4))" ^list! ! !LispParser class methodsFor: 'private'! makeStream: aStream ^(aStream respondsTo: #next) "HACK" ifTrue: [aStream] ifFalse: [ReadStream on: aStream asString].! ! !LispParser class methodsFor: 'utilities'! parse: aStream ^self new parse: (self makeStream: aStream)! parse: aStream ifFail: aBlock ^self new parse: (self makeStream: aStream) ifFail: aBlock! ! !LispParser methodsFor: 'parsing'! parse: sourceStream | label string | ^self parse: sourceStream ifFail: [:errorMessage | label := errorMessage , ' near ' , (token printString contractTo: 20). string := source upToEnd. string isEmpty ifTrue: [string := '--> end of file'] ifFalse: [string := '--> ' , (string contractTo: 30)]. self error: 'parse error ', label, Character nl asString, string. ^LispNil null]! parse: sourceStream ifFail: aBlock | result | self init: sourceStream ifFail: aBlock. result := self scan. ^result! ! !LispParser methodsFor: 'private'! init: sourceStream ifFail: aBlock super on: sourceStream. failBlock := aBlock! ! !LispParser methodsFor: 'scan and parse'! scan source atEnd ifTrue: [^LispCons null]. ^self scanList! scanList | expression | self nextToken. tokenType == #eof ifTrue: [^LispCons null]. tokenType == #number ifTrue: [^token]. tokenType == #string ifTrue: [^token]. tokenType == #object ifTrue: [^token]. tokenType == #symbol ifTrue: [^token]. tokenType == #quote ifTrue: [expression := LispCons head: self scanList tail: LispCons null. ^LispCons head: #quote tail: expression]. tokenType == #leftParenthesis ifTrue: [^self scanListAux]. ^failBlock value: 'Syntax error'! scanListAux | cdr | self nextToken. tokenType == #eof ifTrue: [^LispCons null]. tokenType == #rightParenthesis ifTrue: [^LispCons null]. tokenType == #leftParenthesis ifTrue: [^LispCons head: self scanListAux tail: self scanListAux]. tokenType == #number ifTrue: [^LispCons head: token tail: self scanListAux]. tokenType == #string ifTrue: [^LispCons head: token tail: self scanListAux]. tokenType == #object ifTrue: [^LispCons head: token tail: self scanListAux]. tokenType == #symbol ifTrue: [^LispCons head: token tail: self scanListAux]. tokenType == #period ifTrue: [cdr := self scanList. self nextToken. tokenType == #rightParenthesis ifTrue: [^cdr] ifFalse: [^failBlock value: 'Syntax error']]. tokenType == #quote ifTrue: [cdr := LispCons head: self scanList tail: LispCons null. cdr := LispCons head: #quote tail: cdr. ^LispCons head: cdr tail: self scanListAux]. self unNextToken. ^failBlock value: 'Syntax error'! ! !LispParser methodsFor: 'scanning'! nextToken prevMark := mark. prevToken := token. prevTokenType := tokenType. ^super nextToken! unNextToken super unNextToken. mark := prevMark. token := prevToken. tokenType := prevTokenType! ! !LispTable class methodsFor: 'copyright'! copyright ^'Copyright (C) 1995-1998 AOKI Atsushi, All Rights Reserved.'! system ^'Goodies'! version ^'003'! ! !LispTable class methodsFor: 'instance creation'! new ^super new initialize! ! !LispTable methodsFor: 'accessing'! at: symbol ^self getprop: symbol key: #apval! at: symbol put: value self intern: symbol. ^self putprop: symbol key: #apval value: value! identifiers ^properties keys asSortedCollection! ! !LispTable methodsFor: 'adding'! add: symbol self intern: symbol! ! !LispTable methodsFor: 'initialize-release'! initialize properties := Dictionary new! ! !LispTable methodsFor: 'private'! errorSymbolNotFound self error: 'symbol not found'! intern: symbol (properties includesKey: symbol) ifFalse: [properties at: symbol put: Dictionary new]. ^symbol! ! !LispTable methodsFor: 'property access'! getprop: identifier key: key | property | property := properties at: identifier ifAbsent: [^self errorSymbolNotFound]. ^property at: key ifAbsent: [^nil]! putprop: identifier key: key value: value | property | property := properties at: identifier ifAbsent: [^self errorSymbolNotFound]. ^property at: key put: value! remprop: identifier key: key | property | property := properties at: identifier ifAbsent: [^self errorSymbolNotFound]. ^property removeKey: key ifAbsent: [^nil]! ! !LispTable methodsFor: 'removing'! remove: symbol ^properties removeKey: symbol ifAbsent: [^nil]! ! !LispInterpreter class methodsFor: 'copyright'! copyright ^'Copyright (C) 1995-1998 AOKI Atsushi, All Rights Reserved.'! system ^'Goodies'! version ^'003'! ! !LispInterpreter class methodsFor: 'examples'! example01 "LispInterpreter example01." | aList | aList := LispInterpreter evaluateFrom: ' nil '. ^aList! example02 "LispInterpreter example02." | aList | aList := LispInterpreter evaluateFrom: ' 123 '. ^aList! example03 "LispInterpreter example03." | aList | aList := LispInterpreter evaluateFrom: ' "abc" '. ^aList! example04 "LispInterpreter example04." | aList | aList := LispInterpreter evaluateFrom: ' (cons 3 4) '. ^aList! example05 "LispInterpreter example05." | aList | aList := LispInterpreter evaluateFrom: ' (quote (3 4)) '. ^aList! example06 "LispInterpreter example06." | aList | aList := LispInterpreter evaluateFrom: ' (car (quote (3 4))) '. ^aList! example07 "LispInterpreter example07." | aList | aList := LispInterpreter evaluateFrom: ' (cdr (quote (3 4))) '. ^aList! example08 "LispInterpreter example08." | aList | aList := LispInterpreter evaluateFrom: ' (cons (car `(1 2 3)) `(3 4)) '. ^aList! example09 "LispInterpreter example09." | aList | aList := LispInterpreter evaluateFrom: ' (+ 1 2 3 4 5 6 7 8 9 10) '. ^aList! example10 "LispInterpreter example10." | aList | aList := LispInterpreter evaluateFrom: ' (progn (setq x 100) (setq y 200 z 300) (+ x y z)) '. ^aList! example11 "LispInterpreter example11." | aList | aList := LispInterpreter evaluateFrom: ' (progn (defun plus (x y) (+ x y)) (plus 3 4)) '. ^aList! example12 "LispInterpreter example12." | aList | aList := LispInterpreter evaluateFrom: ' (progn (defun concat (x y) (cond ((atom x) y) (t (cons (car x) (concat (cdr x) y))))) (concat `(1 2 3) `(4 5))) '. ^aList! example13 "LispInterpreter example13." | aList | aList := LispInterpreter evaluateFrom: ' (progn (defun plus nlambda (x) (plus1 x)) (defun plus1 lambda (x) (cond ((null x) 0) (t (+ (car x) (plus1 (cdr x)))))) (plus 1 2 3 4 5 6 7 8 9 10)) '. ^aList! example14 "LispInterpreter example14." | aList | aList := LispInterpreter evaluateFrom: ' ((lambda (x y) (cons x (cons y nil))) 3 4) '. ^aList! example15 "LispInterpreter example15." | aList | aList := LispInterpreter evaluateFrom: ' ((nlambda (x) x) 1 2 3 4 5 6 7 8 9 10) '. ^aList! example16 "LispInterpreter example16." | aList | aList := LispInterpreter evaluateFrom: ' (progn (setq x 100) (setq y 200) (do (x y) (setq x 10000) (setq y 20000) (send {Transcript} `nl) (send {Transcript} `show: (send x `printString)) (send {Transcript} `nl) (send {Transcript} `show: (send y `printString))) (send {Transcript} `nl) (send {Transcript} `show: (send x `printString)) (send {Transcript} `nl) (send {Transcript} `show: (send y `printString))) '. ^aList! example17 "LispInterpreter example17." | aList | aList := LispInterpreter evaluateFrom: ' (do (count) (setq count 1) (while (<= count 100) do (send {Transcript} `nl) (send {Transcript} `show: (send count `printString)) (setq count (+ count 1)))) '. ^aList! example18 "LispInterpreter example18." | aList | aList := LispInterpreter evaluateFrom: ' (do (count) (setq count 1) (repeat (send {Transcript} `nl) (send {Transcript} `show: (send count `printString)) (setq count (+ count 1)) until (<= count 100))) '. ^aList! ! !LispInterpreter class methodsFor: 'instance creation'! new ^super new initialize! ! !LispInterpreter class methodsFor: 'printing'! printString: anObject "LispInterpreter printString: 'string'." "LispInterpreter printString: #symbol." "LispInterpreter printString: 123." "LispInterpreter printString: 123.456." "LispInterpreter printString: 123.456e7." "LispInterpreter printString: LispNil null." "LispInterpreter printString: nil." | aStream | aStream := WriteStream on: (String new: 32). (anObject isKindOf: LispCons) ifTrue: [anObject printOn: aStream level: 0] ifFalse: [LispCons new printOn: aStream object: anObject]. ^aStream contents! ! !LispInterpreter class methodsFor: 'public access'! evaluate: sExpression ^self new evaluateTopLevel: sExpression ifFail: [:errorMessage | self error: errorMessage]! evaluate: sExpression ifFail: aBlock ^self new evaluateTopLevel: sExpression ifFail: aBlock! evaluateFrom: aStream ^self new evaluateTopLevel: (LispParser parse: aStream) ifFail: [:errorMessage | self error: errorMessage]! evaluateFrom: aStream ifFail: aBlock ^self new evaluateTopLevel: (LispCons parse: aStream ifFail: aBlock) ifFail: aBlock! ! !LispInterpreter methodsFor: 'accessing'! textCollector ^textCollector! textCollector: anObject textCollector := anObject! ! !LispInterpreter methodsFor: 'error handling'! fatal: message bindStack reverseDo: [:assoc | assoc key notNil ifTrue: [assoc value notNil ifTrue: [self putprop: assoc key key: #apval value: assoc value] ifFalse: [self remprop: assoc key key: #apval]]]. ^failBlock value: '*** Error: ' , message! ! !LispInterpreter methodsFor: 'evaluating'! evaluate: sExpression | apval | (sExpression isKindOf: LispList) ifTrue: [^self listEvaluate: sExpression]. (sExpression isKindOf: Symbol) ifTrue: [sExpression = #t ifTrue: [^#t]. lispTable intern: sExpression. apval := lispTable getprop: sExpression key: #apval. apval isNil ifTrue: [^self fatal: (self printString: sExpression) , ' is unbound atom']. ^apval]. ^sExpression! evaluateTopLevel: sExpression ^self evaluateTopLevel: sExpression ifFail: [:errorMessage | Transcript show: errorMessage; nl. LispNil null]! evaluateTopLevel: sExpression ifFail: aBlock failBlock := aBlock. ^self evaluate: sExpression! listEvaluate: sExpression | funcName arguList funcBody | sExpression null ifTrue: [^sExpression]. funcName := sExpression head. arguList := sExpression tail. (funcName isKindOf: LispCons) ifTrue: [funcBody := funcName. funcBody head = #lambda ifTrue: [funcBody := LispCons head: #lambda tail: funcBody. ^self exprEval: funcBody arguList: arguList]. funcBody head = #nlambda ifTrue: [funcBody := LispCons head: #nlambda tail: funcBody. ^self fexprEval: funcBody arguList: arguList]. ^self fatal: 'unexpected function ' , (self printString: funcBody)]. (funcName isKindOf: Symbol) ifFalse: [^self fatal: 'null function ' , (self printString: funcName)]. funcBody := self getprop: funcName key: #fexpr. funcBody = LispNil null ifFalse: [^self fexprEval: funcBody arguList: arguList]. funcBody := self getprop: funcName key: #expr. funcBody = LispNil null ifFalse: [^self exprEval: funcBody arguList: arguList]. funcBody := self getprop: funcName key: #fsubr. funcBody = LispNil null ifFalse: [^self fsubrEval: funcBody arguList: arguList]. funcBody := self getprop: funcName key: #subr. funcBody = LispNil null ifFalse: [^self subrEval: funcBody arguList: arguList]. ^self fatal: 'undefined function ' , (self printString: funcName)! ! !LispInterpreter methodsFor: 'fsubr functions'! fsubrAdd: arguList | v a | v := LispNil null. arguList do: [:each | a := self evaluate: each. (a isKindOf: Number) ifFalse: [^self fatal: 'unexpected argument ' , (self printString: a) , ' for +']. v = LispNil null ifTrue: [v := a] ifFalse: [v := v + a]]. ^v! fsubrCond: arguList | result | arguList do: [:each | (self evaluate: each head) ~= LispNil null ifTrue: [result := LispNil null. (each tail isKindOf: LispCons) ifTrue: [each tail do: [:expr | result := self evaluate: expr]]. ^result]]. ^LispNil null! fsubrDefun: arguList | funcName funcType | funcName := arguList head. (funcName isKindOf: Symbol) ifFalse: [^self fatal: 'unexpected function name ' , (self printString: funcName) , ' for defun']. funcType := arguList tail head. funcType = #lambda ifTrue: [self putprop: funcName key: #expr value: arguList. ^funcName]. funcType = #nlambda ifTrue: [self putprop: funcName key: #fexpr value: arguList. ^funcName]. self putprop: funcName key: #expr value: (LispCons head: funcName tail: (LispCons head: #lambda tail: arguList tail)). ^funcName! fsubrDiv: arguList | v a | v := LispNil null. arguList do: [:each | a := self evaluate: each. (a isKindOf: Number) ifFalse: [^self fatal: 'unexpected argument ' , (self printString: a) , ' for /']. v = LispNil null ifTrue: [v := a] ifFalse: [v := v / a]]. ^v! fsubrDo: arguList | locals executions result | locals := arguList head. executions := arguList tail. self bindMark. locals do: [:lvar | self bind: lvar value: LispNil null]. result := LispNil null. executions do: [:each | result := self evaluate: each]. self unbind. ^result! fsubrIdiv: arguList | v a | v := LispNil null. arguList do: [:each | a := self evaluate: each. (a isKindOf: Number) ifFalse: [^self fatal: 'unexpected argument ' , (self printString: a) , ' for //']. v = LispNil null ifTrue: [v := a] ifFalse: [v := v // a]]. ^v! fsubrIf: arguList | predicate then list truePart falsePart bool result | predicate := arguList head. then := arguList tail head. list := arguList tail tail. truePart := LispNil null. falsePart := LispNil null. bool := true. list do: [:each | each = #else ifTrue: [bool := false] ifFalse: [bool ifTrue: [truePart := LispCons head: each tail: truePart] ifFalse: [falsePart := LispCons head: each tail: falsePart]]]. then = #then ifFalse: [^self fatal: 'unexpected format for if']. truePart := truePart reverse. falsePart := falsePart reverse. result := LispNil null. (self evaluate: predicate) = LispNil null ifTrue: [falsePart do: [:each | result := self evaluate: each]] ifFalse: [truePart do: [:each | result := self evaluate: each]]. ^result! fsubrMlt: arguList | v a | v := LispNil null. arguList do: [:each | a := self evaluate: each. (a isKindOf: Number) ifFalse: [^self fatal: 'unexpected argument ' , (self printString: a) , ' for *']. v = LispNil null ifTrue: [v := a] ifFalse: [v := v * a]]. ^v! fsubrMod: arguList | v a | v := LispNil null. arguList do: [:each | a := self evaluate: each. (a isKindOf: Number) ifFalse: [^self fatal: 'unexpected argument ' , (self printString: a) , ' for \\']. v = LispNil null ifTrue: [v := a] ifFalse: [v := v \\ a]]. ^v! fsubrProgn: arguList | result | result := LispNil null. arguList do: [:each | result := self evaluate: each]. ^result! fsubrQuote: arguList ^arguList head! fsubrRepeat: arguList | reverse predicate until executions result | reverse := arguList reverse. predicate := reverse head. until := reverse tail head. executions := reverse tail tail reverse. until = #until ifFalse: [^self fatal: 'unexpected format for repeat']. result := LispNil null. executions do: [:each | result := self evaluate: each]. [(self evaluate: predicate) = LispNil null] whileFalse: [executions do: [:each | result := self evaluate: each]]. ^result! fsubrSend: arguList | list receiver selector arguments result | list := arguList. receiver := self evaluate: list head. list := list tail. selector := self evaluate: list head. (selector isKindOf: Symbol) ifFalse: [^self fatal: 'unexpected selector ' , (self printString: selector) , ' for send']. list := list tail. arguments := OrderedCollection new. [list isKindOf: LispCons] whileTrue: [arguments add: (self evaluate: list head). list := list tail]. result := receiver perform: selector withArguments: arguments asArray. ^result! fsubrSetq: arguList | list a1 a2 | list := arguList. a2 := LispNil null. [list isKindOf: LispCons] whileTrue: [a1 := list head. (a1 isKindOf: Symbol) ifFalse: [^self fatal: 'unexpected variable ' , (self printString: a1) , ' for setq']. list := list tail. a2 := self evaluate: list head. self putprop: a1 key: #apval value: a2. list := list tail]. ^a2! fsubrSub: arguList | v a | v := LispNil null. arguList do: [:each | a := self evaluate: each. (a isKindOf: Number) ifFalse: [^self fatal: 'unexpected argument ' , (self printString: a) , ' for -']. v = LispNil null ifTrue: [v := a] ifFalse: [v := v - a]]. ^v! fsubrWhile: arguList | predicate do executions result | predicate := arguList head. do := arguList tail head. executions := arguList tail tail. do = #do ifFalse: [^self fatal: 'unexpected format for while']. result := LispNil null. [(self evaluate: predicate) = LispNil null] whileFalse: [executions do: [:each | result := self evaluate: each]]. ^result! ! !LispInterpreter methodsFor: 'func eval'! exprEval: funcBody arguList: arguList | expression funcName lvarList lvar result | expression := funcBody. funcName := expression head. expression := expression tail. expression := expression tail. lvarList := expression head. expression := expression tail. arguList length ~= lvarList length ifTrue: [^self fatal: 'too few or many arguments ' , (self printString: arguList) , ' vs ' , (self printString: lvarList) , ' for ' , funcName]. self bindMark. arguList do: [:each | lvar := lvarList head. self bind: lvar value: (self evaluate: each). lvarList := lvarList tail]. expression do: [:each | result := self evaluate: each]. self unbind. ^result! fexprEval: funcBody arguList: arguList | expression funcName lvarList lvar result | expression := funcBody. funcName := expression head. expression := expression tail. expression := expression tail. lvarList := expression head. expression := expression tail. lvarList length ~= 1 ifTrue: [^self fatal: 'too few or many arguments ' , (self printString: lvarList) , ' for ' , (self printString: funcName)]. self bindMark. lvar := lvarList head. self bind: lvar value: arguList. expression do: [:each | result := self evaluate: each]. self unbind. ^result! fsubrEval: funcBody arguList: arguList | messageSelector | messageSelector := funcBody tail head. ^self perform: messageSelector with: arguList! subrEval: funcBody arguList: arguList | funcName messageSelector arguCount arguBuffer list | funcName := funcBody head. messageSelector := funcBody tail head. arguCount := funcBody tail tail head. arguBuffer := OrderedCollection new. list := arguList. arguCount timesRepeat: [list null ifTrue: [^self fatal: 'too few arguments for ' , (self printString: funcName)]. arguBuffer add: (self evaluate: list head). list := list tail]. list null not ifTrue: [^self fatal: 'too many arguments for ' , (self printString: funcName)]. arguBuffer isEmpty ifTrue: [^self perform: messageSelector] ifFalse: [^self perform: messageSelector with: arguBuffer asArray]! ! !LispInterpreter methodsFor: 'initialize-release'! initialize lispTable := LispTable new. bindStack := OrderedCollection new. failBlock := [:errorMessage | self error: errorMessage]. textCollector := Transcript. self initializeSubrFunctions. self initializeFsubrFunctions. self initializeExprFunctions. self initializeFexprFunctions! initializeExprFunctions self evaluateTopLevel: (LispParser parse: ' % Expr Functions (progn % ++ (defun ++ lambda (x) (+ x 1)) % -- (defun -- lambda (x) (- x 1)) % assoc (defun assoc lambda (x a) (cond ((null a) nil) ((equal x (car (car a))) (car a)) (t (assoc x (cdr a))))) % copy (defun copy lambda (x) (cond ((null x) nil) (t (cons (car x) (copy (cdr x)))))) % mapc (defun mapc lambda (f x) (cond ((null x) nil) (t (progn (eval (cons f (cons `(car x) nil))) (mapc f (cdr x)))))) % mapcar (defun mapcar lambda (f x) (cond ((null x) nil) (t (cons (eval (cons f (cons `(car x) nil))) (mapcar f (cdr x)))))) ) % end ')! initializeFexprFunctions self evaluateTopLevel: (LispParser parse: ' % Expr Functions (progn % and (defun and nlambda (x) (do (list) (setq list x) (while (if (null list) then nil else (eval (car list))) do (setq list (cdr list))) (if (null list) then t else nil))) % list (defun list nlambda (x) (mapcar `eval x)) % or (defun or nlambda (x) (do (list) (setq list x) (while (if (null list) then nil else (not (eval (car list)))) do (setq list (cdr list))) (if (null list) then nil else t))) ) % end ')! initializeFsubrFunctions self setFsubrFunc: #(#* #fsubrMlt:). self setFsubrFunc: #(#+ #fsubrAdd:). self setFsubrFunc: #(#- #fsubrSub:). self setFsubrFunc: #(#/ #fsubrDiv:). self setFsubrFunc: #(#// #fsubrIdiv:). self setFsubrFunc: #(#cond #fsubrCond:). self setFsubrFunc: #(#defun #fsubrDefun:). self setFsubrFunc: #(#do #fsubrDo:). self setFsubrFunc: #(#if #fsubrIf:). self setFsubrFunc: #(#progn #fsubrProgn:). self setFsubrFunc: #(#quote #fsubrQuote:). self setFsubrFunc: #(#repeat #fsubrRepeat:). self setFsubrFunc: #(#send #fsubrSend:). self setFsubrFunc: #(#setq #fsubrSetq:). self setFsubrFunc: #(#while #fsubrWhile:). self setFsubrFunc: #(#\\ #fsubrMod:).! initializeSubrFunctions self setSubrFunc: #(#< #subrLt: 2). self setSubrFunc: #(#<= #subrLe: 2). self setSubrFunc: #(#= #subrEqual: 2). self setSubrFunc: #(#== #subrEq: 2). self setSubrFunc: #(#> #subrGt: 2). self setSubrFunc: #(#>= #subrGe: 2). self setSubrFunc: #(#append #subrAppend: 2). self setSubrFunc: #(#atom #subrAtom: 1). self setSubrFunc: #(#car #subrCar: 1). self setSubrFunc: #(#cdr #subrCdr: 1). self setSubrFunc: #(#cons #subrCons: 2). self setSubrFunc: #(#consp #subrConsp: 1). self setSubrFunc: #(#dtpr #subrConsp: 1). self setSubrFunc: #(#doublep #subrDoublep: 1). self setSubrFunc: #(#eq #subrEq: 2). self setSubrFunc: #(#equal #subrEqual: 2). self setSubrFunc: #(#eval #subrEval: 1). self setSubrFunc: #(#exprs #subrExprs 0). self setSubrFunc: #(#fexprs #subrFexprs 0). self setSubrFunc: #(#floatp #subrFloatp: 1). self setSubrFunc: #(#fsubrs #subrFsubrs 0). self setSubrFunc: #(#gc #subrGc 0). self setSubrFunc: #(#gensym #subrGensym 0). self setSubrFunc: #(#getprop #subrGetprop: 2). self setSubrFunc: #(#integerp #subrIntegerp: 1). self setSubrFunc: #(#last #subrLast: 1). self setSubrFunc: #(#length #subrLength: 1). self setSubrFunc: #(#listp #subrListp: 1). self setSubrFunc: #(#member #subrMember: 2). self setSubrFunc: #(#memq #subrMemq: 2). self setSubrFunc: #(#nconc #subrNconc: 2). self setSubrFunc: #(#neq #subrNeq: 2). self setSubrFunc: #(#nequal #subrNequal: 2). self setSubrFunc: #(#not #subrNull: 1). self setSubrFunc: #(#nth #subrNth: 2). self setSubrFunc: #(#null #subrNull: 1). self setSubrFunc: #(#numberp #subrNumberp: 1). self setSubrFunc: #(#oblist #subrOblist 0). self setSubrFunc: #(#pp #subrPp: 1). self setSubrFunc: #(#princ #subrPrinc: 1). self setSubrFunc: #(#print #subrPrint: 1). self setSubrFunc: #(#putprop #subrPutprop: 3). self setSubrFunc: #(#remprop #subrRemprop: 2). self setSubrFunc: #(#reverse #subrReverse: 1). self setSubrFunc: #(#rplaca #subrRplaca: 2). self setSubrFunc: #(#rplacd #subrRplacd: 2). self setSubrFunc: #(#stringp #subrStringp: 1). self setSubrFunc: #(#subrs #subrSubrs 0). self setSubrFunc: #(#symbolp #subrSymbolp: 1). self setSubrFunc: #(#terpri #subrTerpri 0). self setSubrFunc: #(#~= #subrNequal: 2). self setSubrFunc: #(#~~ #subrNeq: 2)! ! !LispInterpreter methodsFor: 'printing'! printString: anObject ^self class printString: anObject! ! !LispInterpreter methodsFor: 'private'! setFsubrFunc: bodyArray self putprop: (bodyArray at: 1) asSymbol key: #fsubr value: (LispCons list: bodyArray)! setSubrFunc: bodyArray self putprop: (bodyArray at: 1) asSymbol key: #subr value: (LispCons list: bodyArray)! ! !LispInterpreter methodsFor: 'property access'! getprop: identifier key: key | value | lispTable intern: identifier. value := lispTable getprop: identifier key: key. value isNil ifTrue: [^LispNil null]. ^value! putprop: identifier key: key value: value lispTable intern: identifier. ^lispTable putprop: identifier key: key value: value! remprop: identifier key: key | value | lispTable intern: identifier. value := lispTable remprop: identifier key: key. value isNil ifTrue: [^LispNil null]. ^value! ! !LispInterpreter methodsFor: 'shallow binding'! bind: symbol value: value | saveValue assoc | lispTable intern: symbol. saveValue := lispTable getprop: symbol key: #apval. assoc := Association key: symbol value: saveValue. bindStack addLast: assoc. self putprop: symbol key: #apval value: value! bindMark | assoc | assoc := Association key: nil value: nil. bindStack addLast: assoc! unbind | assoc | [assoc := bindStack removeLast. assoc key notNil] whileTrue: [assoc value notNil ifTrue: [self putprop: assoc key key: #apval value: assoc value] ifFalse: [self remprop: assoc key key: #apval]]! ! !LispInterpreter methodsFor: 'subr functions'! subrAppend: arguArray | a1 a2 | a1 := arguArray at: 1. a2 := arguArray at: 2. (a1 isKindOf: LispCons) ifFalse: [^self fatal: 'unexpected argument ' , (self printString: a1) , ' for append']. (a2 isKindOf: LispCons) ifFalse: [^self fatal: 'unexpected argument ' , (self printString: a2) , ' for append']. ^a1 append: a2! subrAtom: arguArray | a1 | a1 := arguArray at: 1. (a1 isKindOf: LispCons) ifFalse: [^#t]. ^LispNil null! subrCar: arguArray | list | list := arguArray at: 1. (list isKindOf: LispCons) ifTrue: [^list head]. (list isKindOf: LispNil) ifTrue: [^LispNil null]. ^self fatal: 'unexpected argument ' , (self printString: list) , ' for car'! subrCdr: arguArray | list | list := arguArray at: 1. (list isKindOf: LispCons) ifTrue: [^list tail]. (list isKindOf: LispNil) ifTrue: [^LispNil null]. ^self fatal: 'unexpected argument ' , (self printString: list) , ' for cdr'! subrCons: arguArray ^LispCons head: (arguArray at: 1) tail: (arguArray at: 2)! subrConsp: arguArray | a1 | a1 := arguArray at: 1. (a1 isKindOf: LispCons) ifTrue: [^#t]. ^LispNil null! subrDoublep: arguArray | a1 | ^self subrFloatp: arguArray "a1 := arguArray at: 1. (a1 isKindOf: Double) ifTrue: [^#t]. ^LispNil null"! subrEq: arguArray | bool | (arguArray at: 1) == (arguArray at: 2) ifTrue: [bool := #t] ifFalse: [bool := LispNil null]. ^bool! subrEqual: arguArray | bool | (arguArray at: 1) = (arguArray at: 2) ifTrue: [bool := #t] ifFalse: [bool := LispNil null]. ^bool! subrEval: arguArray ^self evaluate: (arguArray at: 1)! subrExprs | list | list := LispNil null. self subrOblist reverse do: [:id | (self getprop: id key: #expr) = LispNil null ifFalse: [list := LispCons head: id tail: list]]. ^list! subrFexprs | list | list := LispNil null. self subrOblist reverse do: [:id | (self getprop: id key: #fexpr) = LispNil null ifFalse: [list := LispCons head: id tail: list]]. ^list! subrFloatp: arguArray | a1 | a1 := arguArray at: 1. (a1 isKindOf: Float) ifTrue: [^#t]. ^LispNil null! subrFsubrs | list | list := LispNil null. self subrOblist reverse do: [:id | (self getprop: id key: #fsubr) = LispNil null ifFalse: [list := LispCons head: id tail: list]]. ^list! subrGc "ObjectMemory globalCompactingGC." Smalltalk compact. Transcript nl; show: 'garbage collecting'. ^#t! subrGe: arguArray | a1 a2 | a1 := arguArray at: 1. a2 := arguArray at: 2. (a1 isKindOf: LispList) ifTrue: [^self fatal: 'unexpected argument ' , (self printString: a1) , ' for >=']. (a2 isKindOf: LispList) ifTrue: [^self fatal: 'unexpected argument ' , (self printString: a2) , ' for >=']. a1 >= a2 ifTrue: [^#t]. ^LispNil null! subrGensym | clock | (Delay forMilliseconds: 1) wait. clock := Time millisecondClockValue. ^('id' , clock printString) asSymbol! subrGetprop: arguArray | a1 a2 | a1 := arguArray at: 1. a2 := arguArray at: 2. (a1 isKindOf: Symbol) ifFalse: [^self fatal: 'unexpected argument ' , (self printString: a1) , ' for getprop']. (a2 isKindOf: Symbol) ifFalse: [^self fatal: 'unexpected argument ' , (self printString: a2) , ' for getprop']. ^self getprop: a1 key: a2! subrGt: arguArray | a1 a2 | a1 := arguArray at: 1. a2 := arguArray at: 2. (a1 isKindOf: LispList) ifTrue: [^self fatal: 'unexpected argument ' , (self printString: a1) , ' for >']. (a2 isKindOf: LispList) ifTrue: [^self fatal: 'unexpected argument ' , (self printString: a2) , ' for >']. a1 > a2 ifTrue: [^#t]. ^LispNil null! subrIntegerp: arguArray | a1 | a1 := arguArray at: 1. (a1 isKindOf: Integer) ifTrue: [^#t]. ^LispNil null! subrLast: arguArray | list | list := arguArray at: 1. (list isKindOf: LispCons) ifTrue: [^list last]. ^self fatal: 'unexpected argument ' , (self printString: list) , ' for last'! subrLe: arguArray | a1 a2 | a1 := arguArray at: 1. a2 := arguArray at: 2. (a1 isKindOf: LispList) ifTrue: [^self fatal: 'unexpected argument ' , (self printString: a1) , ' for <=']. (a2 isKindOf: LispList) ifTrue: [^self fatal: 'unexpected argument ' , (self printString: a2) , ' for <=']. a1 <= a2 ifTrue: [^#t]. ^LispNil null! subrLength: arguArray | list | list := arguArray at: 1. (list isKindOf: LispCons) ifTrue: [^list length]. ^self fatal: 'unexpected argument ' , (self printString: list) , ' for length'! subrListp: arguArray | a1 | a1 := arguArray at: 1. (a1 isKindOf: LispList) ifTrue: [^#t]. ^LispNil null! subrLt: arguArray | a1 a2 | a1 := arguArray at: 1. a2 := arguArray at: 2. (a1 isKindOf: LispList) ifTrue: [^self fatal: 'unexpected argument ' , (self printString: a1) , ' for <']. (a2 isKindOf: LispList) ifTrue: [^self fatal: 'unexpected argument ' , (self printString: a2) , ' for <']. a1 < a2 ifTrue: [^#t]. ^LispNil null! subrMember: arguArray | a1 a2 | a1 := arguArray at: 1. a2 := arguArray at: 2. (a2 isKindOf: LispCons) ifFalse: [^self fatal: 'unexpected argument ' , (self printString: a2) , ' for member']. ^a2 member: a1! subrMemq: arguArray | a1 a2 | a1 := arguArray at: 1. a2 := arguArray at: 2. (a2 isKindOf: LispCons) ifFalse: [^self fatal: 'unexpected argument ' , (self printString: a2) , ' for memq']. ^a2 memq: a1! subrNconc: arguArray | a1 a2 | a1 := arguArray at: 1. a2 := arguArray at: 2. (a1 isKindOf: LispCons) ifFalse: [^self fatal: 'unexpected argument ' , (self printString: a1) , ' for nconc']. a1 nconc: a2. ^a1! subrNeq: arguArray | bool | ((arguArray at: 1) == (arguArray at: 2)) not ifTrue: [bool := #t] ifFalse: [bool := LispNil null]. ^bool! subrNequal: arguArray | bool | ((arguArray at: 1) = (arguArray at: 2)) not ifTrue: [bool := #t] ifFalse: [bool := LispNil null]. ^bool! subrNth: arguArray | a1 a2 | a1 := arguArray at: 1. a2 := arguArray at: 2. (a1 isKindOf: Number) ifFalse: [^self fatal: 'unexpected argument ' , (self printString: a1) , ' for nth']. (a2 isKindOf: LispCons) ifFalse: [^self fatal: 'unexpected argument ' , (self printString: a2) , ' for nth']. ^a2 nth: a1! subrNull: arguArray ((arguArray at: 1) isMemberOf: LispNil) ifTrue: [^#t]. ^LispNil null! subrNumberp: arguArray | a1 | a1 := arguArray at: 1. (a1 isKindOf: Number) ifTrue: [^#t]. ^LispNil null! subrOblist | list | list := LispNil null. lispTable identifiers reverseDo: [:each | list := LispCons head: each tail: list]. ^list! subrPp: arguArray | a pretty | a := arguArray at: 1. pretty := a ppString. textCollector show: pretty. ^a! subrPrinc: arguArray | a | a := arguArray at: 1. (a isKindOf: String) ifTrue: [textCollector show: a] ifFalse: [textCollector show: (self printString: a)]. ^a! subrPrint: arguArray | a | a := self subrPrinc: arguArray. textCollector nl. ^a! subrPutprop: arguArray | a1 a2 a3 | a1 := arguArray at: 1. a2 := arguArray at: 2. a3 := arguArray at: 3. (a1 isKindOf: Symbol) ifFalse: [^self fatal: 'unexpected argument ' , (self printString: a1) , ' for putprop']. (a2 isKindOf: Symbol) ifFalse: [^self fatal: 'unexpected argument ' , (self printString: a2) , ' for putprop']. ^self putprop: a1 key: a2 value: a3! subrRemprop: arguArray | a1 a2 | a1 := arguArray at: 1. a2 := arguArray at: 2. (a1 isKindOf: Symbol) ifFalse: [^self fatal: 'unexpected argument ' , (self printString: a1) , ' for remprop']. (a2 isKindOf: Symbol) ifFalse: [^self fatal: 'unexpected argument ' , (self printString: a2) , ' for remprop']. ^self remprop: a1 key: a2! subrReverse: arguArray | a1 | a1 := arguArray at: 1. (a1 isKindOf: LispCons) ifFalse: [^self fatal: 'unexpected argument ' , (self printString: a1) , ' for reverse']. ^a1 reverse! subrRplaca: arguArray | a1 a2 | a1 := arguArray at: 1. a2 := arguArray at: 2. (a1 isKindOf: LispCons) ifFalse: [^self fatal: 'unexpected argument ' , (self printString: a2) , ' for rplaca']. a1 rplaca: a2. ^a1! subrRplacd: arguArray | a1 a2 | a1 := arguArray at: 1. a2 := arguArray at: 2. (a1 isKindOf: LispCons) ifFalse: [^self fatal: 'unexpected argument ' , (self printString: a2) , ' for rplacd']. a1 rplacd: a2. ^a1! subrStringp: arguArray | a1 | a1 := arguArray at: 1. ((a1 isKindOf: String) and: [(a1 isKindOf: Symbol) not]) ifTrue: [^#t]. ^LispNil null! subrSubrs | list | list := LispNil null. self subrOblist reverse do: [:id | (self getprop: id key: #subr) = LispNil null ifFalse: [list := LispCons head: id tail: list]]. ^list! subrSymbolp: arguArray | a1 | a1 := arguArray at: 1. (a1 isKindOf: Symbol) ifTrue: [^#t]. ^LispNil null! subrTerpri textCollector nl. ^#t! ! smalltalk-3.2.5/examples/CairoDemo.st0000644000175000017500000001710212123404352014453 00000000000000"====================================================================== | | Blitting example using Cairo and SDL | | ======================================================================" "====================================================================== | | Copyright 2008 Free Software Foundation, Inc. | Written by Paolo Bonzini. | | This file is part of GNU Smalltalk. | | GNU Smalltalk is free software; you can redistribute it and/or modify it | under the terms of the GNU General Public License as published by the Free | Software Foundation; either version 2, or (at your option) any later version. | | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS | FOR A PARTICULAR PURPOSE. See the GNU General Public License for more | details. | | You should have received a copy of the GNU General Public License along with | GNU Smalltalk; see the file COPYING. If not, write to the Free Software | Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. | ======================================================================" PackageLoader fileInPackage: #CairoSDL. PackageLoader fileInPackage: #'LibSDL_GL'. SDL.SdlEventHandler subclass: CairoDemo [ | context surface | context [ ^context ] samples [ ^#(#arc #arcNegative #clip #curveRectangle #curveTo #gradient #fillStroke #fillRule #png) ] arcNegative [ | ang1 ang2 | ang1 := 45 degreesToRadians. ang2 := 180 degreesToRadians. context lineWidth: 10; stroke: [ context arcNegative: 128@128 radius: 100 from: ang1 to: ang2 ]; paint: [ context lineWidth: 6; sourceRed: 1 green: 0.2 blue: 0.2 alpha: 1.0; fill: [ context arc: 128@128 radius: 10 from: 0 to: Float pi * 2 ]; stroke: [ context arc: 128@128 radius: 100 from: ang1 to: ang1; lineTo: 128@128; arc: 128@128 radius: 100 from: ang2 to: ang2; lineTo: 128@128 ]] withAlpha: 0.64 ] arc [ | ang1 ang2 | ang1 := 45 degreesToRadians. ang2 := 180 degreesToRadians. context lineWidth: 10; stroke: [ context arc: 128@128 radius: 100 from: ang1 to: ang2 ]; sourceRed: 1 green: 0.2 blue: 0.2 alpha: 0.6; lineWidth: 6; fill: [ context arc: 128@128 radius: 10 from: 0 to: Float pi * 2 ]; stroke: [ context arc: 128@128 radius: 100 from: ang1 to: ang1; lineTo: 128@128; arc: 128@128 radius: 100 from: ang2 to: ang2; lineTo: 128@128 ] ] clip [ context clip: [ context arc: 128@128 radius: 77 from: 0 to: Float pi * 2 ]; fill: [ context rectangle: (0@0 extent: 256@256) ]; lineWidth: 10; stroke: [ context moveTo: 0@0; lineTo: 256@256; moveTo: 256@0; lineTo: 0@256 ] with: Color green ] curveRectangle [ | x0 x1 y0 y1 mx0 mx1 my0 my1 | x0 := y0 := 25.6. x1 := y1 := 256 - x0. mx0 := x0 + 52.4. mx1 := x1 - 52.4. my0 := y0 + 52.4. my1 := y1 - 52.4. context withClosedPath: [ context moveTo: x0@my0; curveTo: mx0@y0 via: x0@y0 via: mx0@y0; lineTo: mx1@y0; curveTo: x1@my0 via: x1@y0 via: x1@my0; lineTo: x1@my1; curveTo: mx1@y1 via: x1@y1 via: mx1@y1; lineTo: mx0@y1; curveTo: x0@my1 via: x0@y1 via: x0@my1 ] do: [ context fillWith: (Color r: 0.5 g: 0.5 b: 1); lineWidth: 10; strokeWith: (Color r: 0.5 g: 0 b: 0 a: 0.5) ] ] curveTo [ | p0 p1 p2 p3 | p0 := 25.6@128. p1 := 102.4@230.4. p2 := 153.6@25.6. p3 := 230.4@128. context lineWidth: 10; stroke: [ context moveTo: p0; curveTo: p3 via: p1 via: p2 ]; lineWidth: 6; stroke: [ context moveTo: p0; lineTo: p1; moveTo: p2; lineTo: p3 ] with: (Color r: 1 g: 0.2 b: 0.2 a: 0.6) ] fillStroke [ context withPath: [ context addClosedSubPath: [ context moveTo: 128@25.6; lineTo: 230.4@230.4; relLineTo: -102.4@0; curveVia: 51.2@230.4 via: 51.2@128 to: 128@128 ]; addClosedSubPath: [ context moveTo: 64.0@25.6; relLineTo: 51.2@51.2; relLineTo: -51.2@51.2; relLineTo: -51.2 @ -51.2 ]] do: [ context lineWidth: 10; fillWith: Color blue; strokeWith: Color black ] ] png [ | png scale translate surf | (File exists: 'demo.png') ifFalse: [ ^self ]. png := CairoPngSurface on: 'demo.png'. scale := 256.0 / (png extent x max: png extent y). translate := 128@128 - (png extent / 2 * scale). context translateBy: translate; scaleBy: scale; paintWith: (surf := SurfacePattern on: png). surf release. png release ] fillRule [ | path | path := [ context rectangle: (12@12 extent: 232@70). context addSubPath: [ context arc: 64@64 radius: 40 from: 0 to: 2 * Float pi ]. context addSubPath: [ context arcNegative: 192@64 radius: 40 from: 0 to: -2 * Float pi ]]. context lineWidth: 6. context withPath: path do: [ context fillRule: #evenOdd; fillWith: Color green * 0.7; strokeWith: Color black ]. context translateBy: 0@128; withPath: path do: [ context fillRule: #winding; fillWith: Color blue * 0.9; strokeWith: Color black ]. ] gradient [ | linear radial | linear := LinearGradient from: 0@0 to: 0@256. linear addStopAt: 0 color: Color white. linear addStopAt: 1 color: Color black. radial := RadialGradient from: 115.2@102.4 radius: 25.6 to: 102.4@102.4 radius: 128. radial addStopAt: 0 color: Color white. radial addStopAt: 1 color: Color black. context fill: [ context rectangle: (0@0 extent: 256@256) ] with: linear; fill: [ context arc: 128@128 radius: 77 from: 0 to: Float pi * 2] with: radial. ] cols [ ^self samples size sqrt ceiling. ] rows [ ^(self samples size / self cols) ceiling. ] displaySize [ | defSize cols rows | defSize := SdlDisplay defaultSize. cols := self cols. rows := self rows. ^defSize x * rows / cols > defSize y ifTrue: [ ^(cols@rows) * (defSize y / rows) ] ifFalse: [ ^(cols@rows) * (defSize x / cols) ] ] clippingRectangle: index [ | cols rows col row size | cols := self cols. rows := self rows. col := (index - 1) \\ cols. row := (index - 1) // cols. size := SdlDisplay current extent / (cols @ rows). ^size * (col @ row) extent: size ] run [ SdlDisplay defaultFormat resizable: true; extent: self displaySize. "SdlDisplay current: SdlGLDisplay new." SdlDisplay current eventSource handler: self; startEventLoop. Processor activeProcess terminateOnQuit. surface := CairoSdlSurface on: SdlDisplay current. self draw. (CairoPngSurface on: 'demo.png' with: surface) save. ] handleResize: size [ super handleResize: size. self draw ] draw [ surface withContextDo: [ :ctx | context := ctx. context paintWith: Color white. self samples keysAndValuesDo: [ :index :sel | self draw: sel inside: (self clippingRectangle: index) ] ]. ] draw: sel inside: rect [ | size | size := rect width min: rect height. context saveWhile: [ context resetClip; withPath: [ context rectangle: rect ] do: [ context clip ]; translateBy: rect origin + ((rect extent - size) / 2); scaleBy: size / 256. self perform: sel ] ] ] Eval [ s := Semaphore new. [CairoDemo new run. s signal] fork. s wait ] smalltalk-3.2.5/examples/Gen3.st0000644000175000017500000001414712123404352013413 00000000000000"====================================================================== | | Python-like Generators | | ======================================================================" "====================================================================== | | Copyright 2003 Free Software Foundation, Inc. | Written by Paolo Bonzini. | | This file is part of GNU Smalltalk. | | GNU Smalltalk is free software; you can redistribute it and/or modify it | under the terms of the GNU General Public License as published by the Free | Software Foundation; either version 2, or (at your option) any later version. | | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS | FOR A PARTICULAR PURPOSE. See the GNU General Public License for more | details. | | You should have received a copy of the GNU General Public License along with | GNU Smalltalk; see the file COPYING. If not, write to the Free Software | Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. | ======================================================================" Stream subclass: #Generator instanceVariableNames: 'next producer consumer process atEnd' classVariableNames: '' poolDictionaries: '' category: 'Streams-Generators' ! Generator comment: 'A Generator object provides a way to use blocks to define a Stream of many return values. The return values are computed one at a time, as needed, and hence need not even be finite. A generator block is converted to a Generator with "Generator on: [...]". The Generator itself is passed to the block, and as soon as a message like #next, #peek, #atEnd or #peekFor: is sent to the generator, execution of the block starts/resumes and goes on until the generator''s #yield: method is called: then the argument of #yield: will be the Generator''s next element. If the block goes on to the end without calling #yield:, the Generator will produce no more elements and #atEnd will return true. You could achieve the effect of generators manually by writing your own class and storing all the local variables of the generator as instance variables. For example, returning a list of integers could be done by setting a variable to 0, and having the #next method increment it and return it. However, for a moderately complicated generator, writing a corresponding class would be much messier (and might lead to code duplication or inefficiency if you want to support #peek, #peekFor: and/or #atEnd): in general, providing a #do:-like interface is easy, but not providing a Stream-like one (think binary trees). The idea of generators comes from other programming languages, in particular this interface looks much like Scheme streams and Python generators. But Python in turn mutuated the idea for example from Icon, where the idea of generators is central. In Icon, every expression and function call behaves like a generator, and if a statement manages scalars, it automatically uses up all the results that the corresponding generator provides; on the other hand, Icon does not represent generators as first-class objects like Python and Smalltalk do.'! !Generator class methodsFor: 'instance creation'! on: aBlock "Return a generator, and also suspend the execution of the sender by returning the new generator to the method that invoked the sender. More easily seen by looking at an example: Integer>>evenNumbersUpTo: n ^Generator on: [ :gen | self to: n do: [ :each | each even ifTrue: [ gen yield: each ] ] ] Although there is no return statement in the method, evaluating it returns a Generator for the even numbers between the receiver and the argument." ^self new forkOn: aBlock; yourself ! ! !Generator methodsFor: 'stream protocol'! atEnd "Answer whether more data can be generated." atEnd isNil ifTrue: [ self generateNext ]. ^atEnd ! next "Evaluate the generator until it generates the next value or decides that nothing else can be generated." | result | self atEnd ifTrue: [ ^self pastEnd ]. atEnd := nil. result := next. next := nil. ^result ! peek "Evaluate the generator until it generates the next value or decides that nothing else can be generated, and save the value so that #peek or #next will return it again." self atEnd ifTrue: [ ^nil ]. ^next ! peekFor: anObject "Evaluate the generator until it generates the next value or decides that nothing else can be generated, and if it is not equal to anObject, save the value so that #peek or #next will return it again." self atEnd ifTrue: [ self pastEnd. ^false ]. ^next = anObject ifTrue: [ next := nil. atEnd := nil. true ] ifFalse: [ false ] ! ! !Generator methodsFor: 'private - continuations'! forkOn: aBlock producer := Semaphore new. consumer := Semaphore new. process := [ producer wait. aBlock value: self. consumer signal ] fork! yield: anObject "Save the object returned by the block in the next instance variable, then restart the consumer thread and put our own to wait." next := anObject. atEnd := false. consumer signal. producer wait! generateNext "Restart the producer thread and put our own to wait." atEnd := true. process priority = Processor activePriority ifFalse: [ process priority: Processor activePriority ]. producer signal. consumer wait! ! !Integer methodsFor: 'examples of generators'! generatorForGeneratorExample ^Generator on: [ :gen | 'Entering gen' displayNl. 1 to: self do: [ :each | ('Yielding ', each printString, '... ') display. gen yield: each. 'Resuming gen' displayNl ] ]! generatorExample: gen | n | ('Running on ', gen printString) displayNl. [ 'Calling next... ' display. n := gen next. n notNil ] whileTrue: [ ('Got ', n printString) displayNl ]! ! Eval [ Smalltalk byteCodeCounter printNl. 10 generatorExample: 10 generatorForGeneratorExample. Smalltalk byteCodeCounter printNl ] smalltalk-3.2.5/examples/JSON.st0000644000175000017500000002531212123404352013364 00000000000000"====================================================================== | | JSON reader/writer example | | ======================================================================" "====================================================================== | | Copyright 2007 Free Software Foundation, Inc. | Written by Robin Redeker. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" Stream subclass: #JSONReader instanceVariableNames: 'stream outputEncoding' classVariableNames: '' poolDictionaries: '' category: nil ! JSONReader comment: 'I read data structures (currently build of OrderedCollection and Dictionary) from and to JSON (Java Script Object Notation). Writing is done with the #toJSON method (note: it will behave badly with circular data structures).' ! !JSONReader class methodsFor: 'json'! toJSON: anObject "I'm returning a JSON string which represents the object." ^anObject toJSON ! fromJSON: string "I'm responsible for decoding the JSON string to objects." ^(self on: string readStream) nextJSONObject ! fromJSON: string inputEncoding: inputEncString outputEncoding: outputEncString "I'm responsible for decoding the JSON string to objects." | str | str := string readStream. str := I18N.EncodedStream unicodeOn: str encoding: inputEncString. ^(self on: str outputEncoding: outputEncString) nextJSONObject ! fromJSON: string inputEncoding: encString "I'm responsible for decoding the JSON string to objects." | str | str := string readStream. str := I18N.EncodedStream unicodeOn: str encoding: encString. ^(self on: str) nextJSONObject ! fromJSON: string outputEncoding: encString "I'm responsible for decoding the JSON string to objects." ^(self on: string readStream outputEncoding: encString) nextJSONObject ! on: aStream | str | str := aStream. aStream isUnicode ifFalse: [ str := I18N.EncodedStream unicodeOn: str ]. ^self new stream: str; yourself ! on: aStream outputEncoding: encString ^(self on: aStream) outputEncoding: encString; yourself ! ! !JSONReader methodsFor: 'json'! outputEncoding ^outputEncoding ! outputEncoding: aString outputEncoding := aString ! stream: aStream stream := aStream isUnicode ifTrue: [ aStream ] ifFalse: [ I18N.EncodedStream unicodeOn: aStream ] ! peek "I'm peeking for the next non-whitespace character and will drop all whitespace in front of it" | c | [ c := stream peek. c = (Character space) or: [ c = (Character tab) or: [ c = (Character lf) or: [ c = (Character cr)]]] ] whileTrue: [ stream next ]. ^c ! next "I'm returning the next non-whitespace character" | c | c := self peek. c isNil ifTrue: [ ^self error: 'expected character but found end of stream' ]. stream next. ^c ! ! !JSONReader methodsFor: 'private'! nextJSONObject "I decode a json self to a value, which will be one of: nil, true, false, OrderedCollection, Dictionary, String or Number (i will return Integer or Float depending on the input)." | c | c := self peek. (c = $n) ifTrue: [ self next: 4. ^nil ]. (c = $t) ifTrue: [ self next: 4. ^true ]. (c = $f) ifTrue: [ self next: 5. ^false ]. (c = ${) ifTrue: [ ^self nextJSONDict ]. (c = $[) ifTrue: [ ^self nextJSONArray ]. (c = $") ifTrue: [ ^self nextJSONString ]. ^self nextJSONNumber ! nextJSONArray "I decode JSON arrays from self and will return a OrderedCollection for them." | c obj value | obj := OrderedCollection new. self next. [ c := self peek. (c = $]) ] whileFalse: [ (c = $,) ifTrue: [ self next. ]. value := self nextJSONObject. obj add: value. ]. self next. ^obj ! nextJSONDict "I decode JSON objects from self and will return a Dictionary containing all the key/value pairs." | c obj key value | obj := Dictionary new. self next. [ c := self peek. c = $} ] whileFalse: [ (c = $,) ifTrue: [ self next ]. key := self nextJSONString. c := self next. c = $: ifFalse: [ self error: ('unexpected character found where name-seperator '':'' expected, found: %1' bindWith: c) ]. value := self nextJSONObject. obj at: key put: value. ]. self next. ^obj ! nextJSONString "I'm extracting a JSON string from self and return them as String." | c obj str | str := WriteStream on: (UnicodeString new: 8). self next. [ c := stream next. c = $" ] whileFalse: [ c = $\ ifTrue: [ c := stream next. c isNil ifTrue: [ ^self error: 'expected character, found end of self' ]. c = $b ifTrue: [ c := 8 asCharacter ]. c = $f ifTrue: [ c := 12 asCharacter ]. c = $n ifTrue: [ c := Character nl ]. c = $r ifTrue: [ c := Character cr ]. c = $t ifTrue: [ c := Character tab ]. c = $u ifTrue: [ c := (Integer readFrom: (stream next: 4) readStream radix: 16) asCharacter ]. ]. str nextPut: c. ]. "Same as 'str contents asString: self outputEncoding', a little more efficient." "str reset. ^(I18N.EncodedStream encoding: str as: self outputEncoding) contents" ^self outputEncoding isNil ifTrue: [str contents] ifFalse: [str contents asString: self outputEncoding] ! nextJSONNumber "I'm extracting a number in JSON format from self and return Integer or Float depending on the input." | c sgn int intexp frac exp isfloat | isfloat := false. sgn := 1. int := 0. intexp := 1. c := stream peek. (c isNil) ifTrue: [ ^self error: 'expected number or -sign, but found end of self' ]. c = $- ifTrue: [ sgn := -1. stream next. ]. c := stream peek. (c isNil) ifTrue: [ ^self error: 'expected number, but found end of self' ]. (c isDigit or: [ c = $. ]) ifFalse: [ ^self error: 'invalid JSON input' ]. [ c notNil and: [ c isDigit ] ] whileTrue: [ stream next. int := sgn * (c digitValue) + (int * 10). c := stream peek ]. (c isNil) ifTrue: [ ^int ]. c = $. ifTrue: [ stream next. isfloat := true. [ c := stream peek. c notNil and: [ c isDigit ] ] whileTrue: [ sgn := sgn / 10. int := sgn * (c digitValue) + int. stream next ] ]. exp := 0. ((c = $e) or: [ c = $E ]) ifFalse: [ ^isfloat ifTrue: [ int asFloat ] ifFalse: [ int ] ]. stream next. c := stream peek. (c isNil) ifTrue: [ ^int ]. sgn := 1. c = $+ ifTrue: [ sgn := 1. self next ]. c = $- ifTrue: [ sgn := -1. self next ]. [ c := stream peek. c notNil and: [ c isDigit ] ] whileTrue: [ exp := (c digitValue) + (exp * 10). stream next ]. int := int * (10 raisedToInteger: exp * sgn). ^int asFloat ! ! !Number methodsFor: 'json'! jsonPrintOn: aStream "I return the Number in a JSON compatible format as String." self asFloat printOn: aStream ! ! !Float methodsFor: 'json'! jsonPrintOn: aStream "I return the Number in a JSON compatible format as String." aStream nextPutAll: (self printString copyReplacing: self exponentLetter withObject: $e) ! ! !Integer methodsFor: 'json'! jsonPrintOn: aStream "I return the Integer in a JSON compatible format as String." self printOn: aStream ! ! !Dictionary methodsFor: 'json'! jsonPrintOn: ws "I encode my contents (key/value pairs) to a JSON object and return it as String." | f | ws nextPut: ${. f := true. self keysAndValuesDo: [ :key :val | f ifFalse: [ ws nextPut: $, ]. key jsonPrintOn: ws. ws nextPut: $:. val jsonPrintOn: ws. f := false ]. ws nextPut: $}. ! ! !CharacterArray methodsFor: 'json'! jsonPrintOn: ws "I will encode me as JSON String and return a String containing my encoded version." ws nextPut: $". self do: [ :c || i | i := c asInteger. (((i = 16r20 or: [ i = 16r21 ]) or: [ i >= 16r23 and: [ i <= 16r5B ] ]) or: [ i >= 16r5D ]) ifTrue: [ ws nextPut: c ]; ifFalse: [ | f | f := false. ws nextPut: $\. i = 16r22 ifTrue: [ f := true. ws nextPut: c ]. i = 16r5C ifTrue: [ f := true. ws nextPut: c ]. i = 16r2F ifTrue: [ f := true. ws nextPut: c ]. i = 16r08 ifTrue: [ f := true. ws nextPut: $b ]. i = 16r0C ifTrue: [ f := true. ws nextPut: $f ]. i = 16r0A ifTrue: [ f := true. ws nextPut: $n ]. i = 16r0D ifTrue: [ f := true. ws nextPut: $r ]. i = 16r09 ifTrue: [ f := true. ws nextPut: $t ]. f ifFalse: [ ws nextPut: $u. ws nextPutAll: ('0000', i printString: 16) last: 4 ]. ] ]. ws nextPut: $". ! !String methodsFor: 'json'! jsonPrintOn: aStream "I will encode me as JSON String and return a String containing my encoded version." (self anySatisfy: [ :ch | ch value between: 128 and: 255 ]) ifTrue: [ self asUnicodeString jsonPrintOn: aStream ] ifFalse: [ super jsonPrintOn: aStream ]! ! !SequenceableCollection methodsFor: 'json'! jsonPrintOn: ws "I'm returning a JSON encoding of my contents as String." | f | ws nextPut: $[. f := true. self do: [ :val | f ifFalse: [ ws nextPut: $, ]. val jsonPrintOn: ws. f := false ]. ws nextPut: $]. ! ! !UndefinedObject methodsFor: 'json'! jsonPrintOn: aStream "I'm returning my corresponding value as JSON String." aStream nextPutAll: 'null' ! ! !Boolean methodsFor: 'json'! jsonPrintOn: aStream "I'm returning the JSON String for truth or lie." self printOn: aStream ! ! !Object methodsFor: 'json'! jsonPrintOn: aStream self subclassResponsibility ! toJSON: encoding ^(UnicodeString streamContents: [ :aStream | self jsonPrintOn: aStream ]) asString: encoding ! toJSON ^(UnicodeString streamContents: [ :aStream | self jsonPrintOn: aStream ]) asString ! ! smalltalk-3.2.5/examples/Case.st0000644000175000017500000001244312123404352013467 00000000000000"====================================================================== | | Case syntax for Smalltalk | | ======================================================================" "====================================================================== | | Written by Ulf Dambacher. | | This file is part of GNU Smalltalk. | | GNU Smalltalk is free software; you can redistribute it and/or modify it | under the terms of the GNU General Public License as published by the Free | Software Foundation; either version 2, or (at your option) any later version. | | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS | FOR A PARTICULAR PURPOSE. See the GNU General Public License for more | details. | | You should have received a copy of the GNU General Public License along with | GNU Smalltalk; see the file COPYING. If not, write to the Free Software | Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. | ======================================================================" Object subclass: #Case instanceVariableNames: 'test found result' classVariableNames: '' poolDictionaries: '' category: 'Examples-Useful tools' ! Case comment: 'A nice class for switch-like tests. Slower than cascaded ifs but clearer. #case:do: uses identity for testing (useful since you''ll likely use Case with symbols, integers, characters, and the like), #ifEqualTo:do: uses equality. e.g. Case new test: myObject; case: 5 do: [ ''got five'' printNl ]; when: [ :testVal | testVal isInteger ] do: [ ''an integer'' printNl ]; else: [ :testVal | testVal printNl ] You can use (Case test: myObject) instead of the first line above. Which of the two possibilities is clearer, it is a matter of taste.'! !Case class methodsFor: 'instance creation'! test: anObject ^self new test: anObject ! ! !Case methodsFor: 'testing'! test: anObject test := anObject. found := false. ! reset found := false ! else: aBlock ^found ifFalse: [ self do: aBlock ] ifTrue: [ result ]. ! case: anObject do: aBlock ^(found not and: [test == anObject]) ifTrue: [ self do: aBlock ] ifFalse: [ result ]. ! ifEqualTo: anObject do: aBlock ^(found not and: [test = anObject]) ifTrue: [ self do: aBlock ] ifFalse: [ result ]. ! when: aBlock do: aBlock2 ^(found not and: [aBlock value: test]) ifTrue: [ self do: aBlock ] ifFalse: [ result ]. ! ! !Case methodsFor: 'private'! do: aBlock found := true. ^result := (aBlock cull: test) ! ! Object subclass: #Switch instanceVariableNames: 'values defaultBlock' classVariableNames: '' poolDictionaries: '' category: 'Examples-Useful tools' ! Object subclass: #SwitchCase instanceVariableNames: 'secondParameter evaluationBlock actionBlock result' classVariableNames: '' poolDictionaries: '' category: 'Examples-Useful tools' ! Switch comment: 'Another class for switch-like tests. This is reusable, i.e. an instance stores its case-do pairs. e.g. (Switch new) case: "value or Block" do: [...]; ... default: [...]; on: value. "#= equality matching of cases" (Switch new) case: "value or Block" do: [...]; ... default: [...]; exactlyOn: value. "#== identity matching of cases" '! !Switch class methodsFor: 'instance creation'! new ^self basicNew values: (ReadWriteStream on: Array new: 5) ! ! !Switch methodsFor: 'initialization'! values: aStream values := aStream ! default: aBlock defaultBlock := aBlock ! case: anObjectOrBlock do: aBlock | block | block := anObjectOrBlock class == BlockClosure ifTrue: [ [ :object :block :identity | block value: object ] ifFalse: [ [ :object :comparison :identity | identity ifTrue: [ object == comparison ] ifFalse: [ object = comparison ] ] ]. values nextPut: (SwitchCase new secondParameter: anObjectOrBlock evaluationBlock: block actionBlock: aBlock) ! ! !Switch methodsFor: 'evaluation'! on: anObject | done case | done := false. values reset. [ values atEnd ] whileFalse: [ case := values next. (case evaluateIfEqualTo: anObject) ifTrue: [ ^case result ]. ]. ^defaultBlock value! ! exactlyOn: anObject | done case | done := false. values reset. [ values atEnd ] whileFalse: [ case := values next. (case evaluateIfIdenticalTo: anObject) ifTrue: [ ^case result ]. ]. ^defaultBlock value! ! identityOn: anObject | done case | done := false. values reset. [ values atEnd ] whileFalse: [ case := values next. (case evaluateIfIdenticalTo: anObject) ifTrue: [ ^case result ]. ]. ^defaultBlock value! ! !SwitchCase methodsFor: 'evaluation'! evaluateIfEqualTo: object ^(evaluationBlock value: object value: secondParameter value: false) ifTrue: [ result := actionBlock value ]; yourself ! evaluateIfIdenticalTo: object ^(evaluationBlock value: object value: secondParameter value: true) ifTrue: [ result := actionBlock value ]; yourself ! result | answer | answer := result. result := nil. ^answer ! ! !SwitchCase methodsFor: 'initialization'! secondParameter: sP evaluationBlock: eB actionBlock: aB secondParameter := sP. evaluationBlock := eB. actionBlock := aB ! ! smalltalk-3.2.5/examples/Prolog.st0000644000175000017500000024432412123404352014063 00000000000000"====================================================================== | | Prolog interpreter written in Smalltalk | | ======================================================================" "====================================================================== | | Written by Aoki Atsushi and Nishihara Satoshi. | Modified by Paolo Bonzini (removed GUI). | | This file is part of GNU Smalltalk. | | GNU Smalltalk is free software; you can redistribute it and/or modify it | under the terms of the GNU General Public License as published by the Free | Software Foundation; either version 2, or (at your option) any later version. | | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS | FOR A PARTICULAR PURPOSE. See the GNU General Public License for more | details. | | You should have received a copy of the GNU General Public License along with | GNU Smalltalk; see the file COPYING. If not, write to the Free Software | Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. | ======================================================================" Object subclass: #PrologEntity instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Examples-Prolog'! PrologEntity subclass: #PrologList instanceVariableNames: 'carPart cdrPart ' classVariableNames: 'PrologDotPairPrintHorizontalLevel PrologDotPairPrintVerticalLevel ' poolDictionaries: '' category: 'Examples-Prolog'! PrologList subclass: #PrologBody instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Examples-Prolog'! PrologList subclass: #PrologClause instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Examples-Prolog'! PrologClause subclass: #PrologResolveClause instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Examples-Prolog'! PrologList subclass: #PrologDefinition instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Examples-Prolog'! PrologEntity subclass: #PrologObject instanceVariableNames: 'source object ' classVariableNames: '' poolDictionaries: '' category: 'Examples-Prolog'! Object subclass: #PrologScanner instanceVariableNames: 'source mark token tokenType endChar ' classVariableNames: 'EndChar ScanningTable' poolDictionaries: '' category: 'Examples-Prolog'! PrologScanner subclass: #PrologParser instanceVariableNames: 'prevMark prevToken prevTokenType failBlock ' classVariableNames: '' poolDictionaries: '' category: 'Examples-Prolog'! PrologEntity subclass: #PrologString instanceVariableNames: 'string ' classVariableNames: '' poolDictionaries: '' category: 'Examples-Prolog'! PrologList subclass: #PrologStructure instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Examples-Prolog'! PrologString subclass: #PrologSymbol instanceVariableNames: '' classVariableNames: 'PrologCut PrologFail PrologSelf PrologSend PrologSymbolTable PrologTrue PrologVar ' poolDictionaries: '' category: 'Examples-Prolog'! PrologList subclass: #PrologTerms instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'Examples-Prolog'! PrologString subclass: #PrologVariable instanceVariableNames: '' classVariableNames: 'PrologVariableCounter PrologVariableTable ' poolDictionaries: '' category: 'Examples-Prolog'! Object subclass: #PrologInterpreter instanceVariableNames: 'systemPredicates userPredicates status definition question questionEnv clause clauseEnv queue queueEnv envCounter valueEnv unbindList cutBack backTrack resolveAction definitionStack tracePredicates traceCounter textValue textCollector verbose listValue predicate ' classVariableNames: 'SystemPredicates ' poolDictionaries: '' category: 'Examples-Prolog'! !Object methodsFor: 'prolog'! car self == nil ifTrue: [^nil]. self error: 'send message car to atom'! cdr self == nil ifTrue: [^nil]. self error: 'send message cdr to atom'! cons: anObject ^PrologList car: self cdr: anObject! consp ^false! isPrologEntity self == nil ifTrue: [^true]. ^self isKindOf: Number! isPrologVariable ^false! printPrologOn: aStream self == nil ifTrue: [aStream nextPutAll: '[]'. ^self]. (self isKindOf: Number) ifTrue: [self printOn: aStream. ^self]. aStream nextPut: ${. self printOn: aStream. aStream nextPut: $}! printPrologOn: aStream level: anInteger self printPrologOn: aStream! printPrologString | aStream | aStream := WriteStream on: (String new: 20). self printPrologOn: aStream. ^aStream contents! ! !PrologEntity class methodsFor: 'copyright'! copyright ^'Copyright (C) 1995-1998 AOKI Atsushi, All Rights Reserved.'! system ^'Goodies'! version ^'003'! ! !PrologEntity methodsFor: 'testing'! isPrologEntity ^true! ! !PrologList class methodsFor: 'class initialization'! initialize "PrologList initialize" PrologDotPairPrintVerticalLevel := 10. PrologDotPairPrintHorizontalLevel := 100! ! !PrologList class methodsFor: 'copyright'! copyright ^'Copyright (C) 1995-1998 AOKI Atsushi, All Rights Reserved.'! system ^'Goodies'! version ^'003'! ! !PrologList class methodsFor: 'instance creation'! car: carObject cdr: cdrObject ^super new car: carObject cdr: cdrObject! list: anArray | size list | size := anArray size. list := nil. size to: 1 by: -1 do: [:i | list := self car: (anArray at: i) cdr: list]. ^list! ! !PrologList methodsFor: 'accessing'! car ^carPart! car: carObject carPart := carObject! cdr ^cdrPart! cdr: cdrObject cdrPart := cdrObject! nth: anInteger | count list | anInteger <= 0 ifTrue: [^self]. count := 1. list := self. [list consp] whileTrue: [count >= anInteger ifTrue: [^list car]. count := count + 1. list := list cdr]. ^nil! ! !PrologList methodsFor: 'converting'! asPrologList | list new tail | new := self car cons: nil. tail := new. list := self cdr. [list consp] whileTrue: [tail cdr: (list car cons: nil). tail := tail cdr. list := list cdr]. tail cdr: list. ^new! ! !PrologList methodsFor: 'enumerating'! do: aBlock | list | list := self. [list consp] whileTrue: [ aBlock value: list car. list := list cdr]! ! !PrologList methodsFor: 'functions'! append: aPrologDotPair (cdrPart consp) ifFalse: [^carPart cons: aPrologDotPair]. ^carPart cons: (cdrPart append: aPrologDotPair)! arity ^2! assoc: anObject | list assoc | list := self. [list consp] whileTrue: [assoc := list car. anObject = assoc car ifTrue: [^assoc]. list := list cdr]. ^nil! functor ^PrologSymbol fromString: '.'! length | list count | list := self. count := 0. [list consp] whileTrue: [count := count + 1. list := list cdr]. ^count! member: anObject | list | list := self. [list consp] whileTrue: [anObject = list car ifTrue: [^list]. list := list cdr]. ^nil! nconc: aPrologDotPair | list | list := self. [list consp] whileTrue: [(list cdr consp) ifTrue: [list := list cdr] ifFalse: [list cdr: aPrologDotPair. ^self]]. ^aPrologDotPair! reverse | list revlist mark | list := self. revlist := nil. [list consp] whileTrue: [revlist == nil ifTrue: [revlist := mark := list car cons: revlist] ifFalse: [revlist := list car cons: revlist]. list := list cdr]. mark cdr: list. ^revlist! structureList "disassemble prolog structure of myself into a list." ^self functor cons: ((self car) cons: ((self cdr) cons: nil))! ! !PrologList methodsFor: 'printing'! prettyPrintPrologOn: aStream | head body list | head := self car. body := self cdr. head printPrologOn: aStream. body ~~ nil ifTrue: [aStream nextPutAll: ' :- '. list := body. aStream nl; tab. [list cdr consp] whileTrue: [list ~~ body ifTrue: [aStream nextPutAll: ', '. aStream nl; tab]. list car printPrologOn: aStream. list := list cdr]. list ~~ self ifTrue: [aStream nextPutAll: ', '. aStream nl; tab]. list car printPrologOn: aStream]. aStream nextPut: $.! prettyPrintPrologString | aStream | aStream := WriteStream on: (String new: 20). self prettyPrintPrologOn: aStream. ^aStream contents! printOn: aStream aStream nextPutAll: self class printString. aStream nextPutAll: '('. aStream nextPutAll: self printPrologString. aStream nextPutAll: ')'! printPrologOn: aStream self printPrologOn: aStream level: 1! printPrologOn: aStream cdr: tail level: anInteger | d count | d := tail. count := 1. [d consp] whileTrue: [count >= PrologDotPairPrintHorizontalLevel ifTrue: [aStream nextPutAll: ' ... ]'. ^self]. aStream nextPut: $,. d car consp ifTrue: [d car printPrologOn: aStream level: anInteger + 1] ifFalse: [d car printPrologOn: aStream]. "d car printPrologOn: aStream level: anInteger + 1." count := count + 1. d := d cdr]. d isNil ifTrue: [aStream nextPut: $]] ifFalse: [aStream nextPut: $|. d printPrologOn: aStream. aStream nextPut: $]]! printPrologOn: aStream level: anInteger anInteger > PrologDotPairPrintVerticalLevel ifTrue: [aStream nextPutAll: ' ... '. ^self]. aStream nextPutAll: '['. carPart consp ifTrue: [carPart printPrologOn: aStream level: anInteger + 1] ifFalse: [carPart printPrologOn: aStream]. self printPrologOn: aStream cdr: cdrPart level: anInteger! ! !PrologList methodsFor: 'private'! car: carObject cdr: cdrObject carPart := carObject. cdrPart := cdrObject! ! !PrologList methodsFor: 'testing'! = anObject anObject consp ifFalse: [^false]. self car = anObject car ifTrue: [^self cdr = anObject cdr]. ^false! consp ^true! ! PrologList initialize! !PrologBody class methodsFor: 'copyright'! copyright ^'Copyright (C) 1995-1998 AOKI Atsushi, All Rights Reserved.'! system ^'Goodies'! version ^'003'! ! !PrologBody class methodsFor: 'instance creation'! fromList: aPrologDotPair aPrologDotPair consp ifFalse: [^aPrologDotPair]. ^super new fromList: aPrologDotPair! fromReverseList: aPrologDotPair aPrologDotPair consp ifFalse: [^aPrologDotPair]. ^super new fromReverseList: aPrologDotPair! structure: aPrologStructure next: link ^super new structure: aPrologStructure next: link! ! !PrologBody methodsFor: 'printing'! prettyPrintPrologOn: aStream | list | list := self. aStream nl; tab. [list cdr consp] whileTrue: [list ~~ self ifTrue: [aStream nextPutAll: ', '. aStream nl; tab]. list car printPrologOn: aStream. list := list cdr]. list ~~ self ifTrue: [aStream nextPutAll: ', '. aStream nl; tab]. list car printPrologOn: aStream! printPrologOn: aStream | list | list := self. [list cdr consp] whileTrue: [list ~~ self ifTrue: [aStream nextPutAll: ', ']. list car printPrologOn: aStream. list := list cdr]. list ~~ self ifTrue: [aStream nextPutAll: ', ']. list car printPrologOn: aStream! printPrologOn: aStream level: anInteger self printPrologOn: aStream! ! !PrologBody methodsFor: 'private'! fromList: aPrologDotPair ^self fromReverseList: aPrologDotPair reverse! fromReverseList: aPrologDotPair | list body mark | list := aPrologDotPair. body := nil. [list consp] whileTrue: [body == nil ifTrue: [body := mark := self class structure: list car next: body] ifFalse: [body := self class structure: list car next: body]. list := list cdr]. mark cdr: list. ^body! structure: aPrologStructure next: link carPart := aPrologStructure. cdrPart := link! ! !PrologClause class methodsFor: 'copyright'! copyright ^'Copyright (C) 1995-1998 AOKI Atsushi, All Rights Reserved.'! system ^'Goodies'! version ^'003'! ! !PrologClause class methodsFor: 'instance creation'! head: aPrologStructure body: aPrologBody ^super new head: aPrologStructure body: aPrologBody! ! !PrologClause methodsFor: 'accessing'! body ^cdrPart! body: aPrologBody cdrPart := aPrologBody! head ^carPart! head: aPrologStructure carPart := aPrologStructure! ! !PrologClause methodsFor: 'printing'! prettyPrintPrologOn: aStream | head body | head := self head. body := self body. head printPrologOn: aStream. body ~~ nil ifTrue: [aStream nextPutAll: ' :- '. body prettyPrintPrologOn: aStream]. aStream nextPut: $.! prettyPrintPrologString | aStream | aStream := WriteStream on: (String new: 20). self prettyPrintPrologOn: aStream. ^aStream contents! printPrologOn: aStream | head body | head := self head. body := self body. aStream nextPut: $(. head printPrologOn: aStream. body == nil ifFalse: [aStream nextPutAll: ', '. body printPrologOn: aStream]. aStream nextPut: $)! printPrologOn: aStream level: anInteger self printPrologOn: aStream! ! !PrologClause methodsFor: 'private'! head: aPrologStructure body: aPrologBody self head: aPrologStructure. self body: aPrologBody! ! !PrologClause methodsFor: 'polymorphism'! isResolveClause ^false! ! !PrologResolveClause methodsFor: 'polymorphism'! printPrologOn: aStream | head body | head := self head. body := self body. aStream nextPutAll: '?- '. head printPrologOn: aStream. body ~~ nil ifTrue: [aStream nextPutAll: ', '. body printPrologOn: aStream]. aStream nextPut: $.! isResolveClause ^true! ! !PrologDefinition class methodsFor: 'copyright'! copyright ^'Copyright (C) 1995-1998 AOKI Atsushi, All Rights Reserved.'! system ^'Goodies'! version ^'003'! ! !PrologDefinition class methodsFor: 'instance creation'! clause: aPrologClause next: link ^super new clause: aPrologClause next: link! fromList: aPrologDotPair aPrologDotPair consp ifFalse: [^aPrologDotPair]. ^super new fromList: aPrologDotPair! fromReverseList: aPrologDotPair aPrologDotPair consp ifFalse: [^aPrologDotPair]. ^super new fromReverseList: aPrologDotPair! ! !PrologDefinition methodsFor: 'private'! clause: aPrologClause next: link carPart := aPrologClause. cdrPart := link! fromList: aPrologDotPair ^self fromReverseList: aPrologDotPair reverse! fromReverseList: aPrologDotPair | list definition | list := aPrologDotPair. definition := nil. [list consp] whileTrue: [definition := self class clause: list car next: definition. list := list cdr]. ^definition! ! !PrologObject class methodsFor: 'copyright'! copyright ^'Copyright (C) 1995-1998 AOKI Atsushi, All Rights Reserved.'! system ^'Goodies'! version ^'003'! ! !PrologObject class methodsFor: 'instance creation'! readFrom: aStream | buffer char | buffer := WriteStream on: (String new: 20). [char := aStream next. char = $}] whileFalse: [char == nil ifTrue: [self error: 'Syntax error near ${ unmatched $}\-- end of file --' withCRs]. buffer nextPut: char]. ^buffer contents! source: aString object: anObject ^super new source: aString object: anObject! ! !PrologObject methodsFor: 'accessing'! object ^object! object: anObject object := anObject! source ^source! source: aString source := aString! ! !PrologObject methodsFor: 'printing'! printOn: aStream aStream nextPutAll: self class printString. aStream nextPutAll: '('. aStream nextPutAll: self object printString. aStream nextPutAll: ')'! printPrologOn: aStream aStream nextPut: ${. aStream nextPutAll: self source. aStream nextPut: $}! printPrologOn: aStream level: anInteger self printPrologOn: aStream! ! !PrologObject methodsFor: 'private'! source: aString object: anObject self source: aString. self object: anObject! ! !PrologObject methodsFor: 'testing'! = anObject anObject class = self class ifFalse: [^false]. ^self object = anObject object! ! !PrologScanner class methodsFor: 'class initialization'! initialize "PrologScanner initialize" | newTable | newTable := Array new: 256 withAll: #xBinary. newTable atAll: #(9 10 12 13 32 ) put: #xDelimiter. newTable atAll: ($0 asInteger to: $9 asInteger) put: #xDigit. newTable atAll: ($A asInteger to: $Z asInteger) put: #xVariable. newTable at: $~ asInteger put: #xVariable. newTable atAll: ($a asInteger to: $z asInteger) put: #xSymbol. 128 to: 256 do: [:i | newTable at: i put: #xSymbol]. #($! $: $* $/ $\ $> $< $= $_) do: [:each | newTable at: each asInteger put: #xSymbol]. newTable at: $^ asInteger put: #eof. newTable at: $" asInteger put: #xDoubleQuote. newTable at: $$ asInteger put: #xDollar. newTable at: $' asInteger put: #xSingleQuote. newTable at: $( asInteger put: #leftParenthesis. newTable at: $) asInteger put: #rightParenthesis. newTable at: $. asInteger put: #period. newTable at: $: asInteger put: #xColon. newTable at: $? asInteger put: #xColon. newTable at: $; asInteger put: #semicolon. newTable at: $[ asInteger put: #leftBracket. newTable at: $] asInteger put: #rightBracket. newTable at: ${ asInteger put: #leftBrace. newTable at: $} asInteger put: #rightBrace. newTable at: $, asInteger put: #comma. newTable at: $| asInteger put: #verticalBar. newTable at: $+ asInteger put: #xSign. newTable at: $- asInteger put: #xSign. newTable at: $% asInteger put: #xComment. ScanningTable := newTable. EndChar := $^! ! !PrologScanner class methodsFor: 'copyright'! copyright ^'Copyright (C) 1995-1998 AOKI Atsushi, All Rights Reserved.'! system ^'Goodies'! version ^'003'! ! !PrologScanner class methodsFor: 'instance creation'! new ^super new initScanner! ! !PrologScanner methodsFor: 'accessing'! tableAt: char | index | index := char asInteger. ^index = 0 ifFalse: [ScanningTable at: index] ifTrue: [#xDelimiter]! ! !PrologScanner methodsFor: 'error handling'! error: labelString with: contentsString "(PrologScanner new) error: 'error!' with: 'show must go on'." | handler | self error: contentsString! ! !PrologScanner methodsFor: 'initialize-release'! initScanner endChar := EndChar! on: inputStream source := inputStream. mark := source position! ! !PrologScanner methodsFor: 'private'! nextChar | char | source atEnd ifTrue: [ ^endChar ]. char := source next. char = Character cr ifTrue: [char := Character nl. source peekFor: char]. ^char! peekChar | char | char := source peek. char = Character cr ifTrue: [char := Character nl]. char == nil ifTrue: [char := endChar]. ^char! unNextChar source skip: -1! ! !PrologScanner methodsFor: 'scanning'! multiChar: type self perform: type! nextToken | char | mark := source position. char := self peekChar. tokenType := self tableAt: char asInteger. [tokenType == #xDelimiter] whileTrue: [self nextChar. char := self peekChar. tokenType := self tableAt: char asInteger]. (tokenType at: 1) = $x ifTrue:[self multiChar: tokenType] ifFalse:[self singleChar: tokenType]. ^token! singleChar: type self nextChar. token := type. tokenType == #leftBrace ifFalse: [^self]. tokenType := #object. token := PrologObject readFrom: source! unNextToken source position: mark! xBinary self error: 'Syntax error ' , source peek printString , '\' withCRs , source upToEnd! xColon | char | source next. char := source peek. char = $- ifTrue: [tokenType := #neck. self singleChar: tokenType] ifFalse: [self unNextToken. tokenType := #symbol. token := PrologSymbol readFrom: source]! xComment | char | [(char := self nextChar) = Character nl] whileFalse: [char == endChar ifTrue: [tokenType := #eof. ^self]]. self nextToken! xDigit tokenType := #number. token := Number readFrom: source! xDollar self xBinary! xDoubleQuote tokenType := #string. token := PrologString readFrom: source! xSign | char sign | sign := self nextChar. char := self peekChar. char isDigit ifTrue: [tokenType := #number. token := Number readFrom: source. sign == $- ifTrue: [token := token negated]] ifFalse: [self unNextChar. tokenType := #symbol. token := PrologSymbol readFrom: source]! xSingleQuote tokenType := #symbol. token := PrologSymbol readFrom: source! xSymbol tokenType := #symbol. token := PrologSymbol readFrom: source! xVariable tokenType := #variable. token := PrologVariable readFrom: source! ! PrologScanner initialize! !PrologParser class methodsFor: 'copyright'! copyright ^'Copyright (C) 1995-1998 AOKI Atsushi, All Rights Reserved.'! system ^'Goodies'! version ^'003'! ! !PrologParser methodsFor: 'parsing'! parse: sourceStream | label string | ^self parse: sourceStream ifFail: [:errorMessage | label := errorMessage , ' near ' , token printString. string := source upToEnd. string size > 100 ifTrue: [string := string copyFrom: 1 to: 100]. self error: label with: (string = '' ifTrue: ['-- end of file --'] ifFalse: ['--> ' , string])]! parse: sourceStream ifFail: aBlock | result | self init: sourceStream ifFail: aBlock. result := self scan. ^result! ! !PrologParser methodsFor: 'private'! compileAndEvaluate: string ^Behavior evaluate: string ifError: []! init: sourceStream ifFail: aBlock super on: sourceStream. failBlock := aBlock. PrologVariable setZero! ! !PrologParser methodsFor: 'scan'! scan source atEnd ifTrue: [^#eof]. self nextToken. tokenType == #eof ifTrue: [^#eof]. tokenType == #neck ifTrue: [^self scanClause: PrologResolveClause]. "resolve clause" self unNextToken. ^self scanClause: PrologClause! scanBody | list | list := nil. [tokenType ~~ #eof] whileTrue: [list := self scanStructure cons: list. self nextToken. tokenType == #rightParenthesis ifTrue: [^PrologBody fromReverseList: list]. tokenType == #period ifTrue: [^PrologBody fromReverseList: list]. tokenType ~~ #comma ifTrue: [failBlock value: 'Syntax error']]. failBlock value: 'Unexpected eof'! scanClause: class | head | head := self scanStructure. self nextToken. tokenType == #neck ifTrue: [^class head: head body: self scanBody]. tokenType == #comma ifTrue: [^class head: head body: self scanBody]. tokenType == #period ifTrue: [^class head: head body: nil]. tokenType == #rightParenthesis ifTrue: [^class head: head body: nil]. self unNextToken. failBlock value: 'Syntax error'! scanExpression | symbol | self nextToken. (tokenType == #eof or: [tokenType == #period]) ifTrue: [^nil]. tokenType == #number ifTrue: [^token]. tokenType == #string ifTrue: [^token]. tokenType == #object ifTrue: [^PrologObject source: token object: (self compileAndEvaluate: token)]. tokenType == #leftBracket ifTrue: [^self scanList]. tokenType == #leftParenthesis ifTrue: [^self scanClause: PrologClause]. (tokenType == #symbol or: [tokenType == #variable]) ifTrue: [symbol := token. self nextToken. tokenType == #leftParenthesis ifTrue: [self unNextToken. self unNextToken. ^self scanStructure] ifFalse: [self unNextToken. ^symbol]]. self unNextToken. failBlock value: 'Syntax error'! scanList | expression | self nextToken. tokenType == #comma ifTrue: [self nextToken]. tokenType == #neck ifTrue: [self nextToken]. tokenType == #rightBracket ifTrue: [^nil]. tokenType == #leftBracket ifTrue: [^self scanList cons: self scanList]. tokenType == #verticalBar ifTrue: [expression := self scanExpression. self nextToken. tokenType == #rightBracket ifTrue: [^expression] ifFalse: [failBlock value: 'Syntax error']]. self unNextToken. expression := self scanExpression. ^expression cons: self scanList! scanStructure | functor terms | functor := self nextToken. (tokenType == #symbol or: [tokenType == #variable]) ifTrue: [terms := self scanTerms. ^PrologStructure functor: functor terms: terms]. failBlock value: 'Syntax error'! scanTerms | list | self nextToken. tokenType == #leftParenthesis ifTrue: [self nextToken. (tokenType == #verticalBar or: [tokenType == #rightParenthesis]) ifTrue: [tokenType == #rightParenthesis ifTrue: [^nil]. list := self scanExpression. self nextToken. tokenType == #rightParenthesis ifTrue: [^list] ifFalse: [failBlock value: 'Syntax error']] ifFalse: [self unNextToken]. list := nil. [tokenType ~~ #eof] whileTrue: [list := self scanExpression cons: list. self nextToken. token == #rightParenthesis ifTrue: [^PrologTerms fromReverseList: list]. tokenType == #verticalBar ifTrue: [list := list reverse. list := list nconc: self scanExpression. self nextToken. tokenType == #rightParenthesis ifTrue: [^PrologTerms fromList: list] ifFalse: [failBlock value: 'Syntax error']]. tokenType ~~ #comma ifTrue: [failBlock value: 'Syntax error']]. failBlock value: 'Unexpected eof'] ifFalse: [self unNextToken. ^nil]! ! !PrologParser methodsFor: 'scanning'! nextToken prevMark := mark. prevToken := token. prevTokenType := tokenType. ^super nextToken! unNextToken super unNextToken. mark := prevMark. token := prevToken. tokenType := prevTokenType! ! PrologString class instanceVariableNames: 'charMap '! !PrologString class methodsFor: 'accessing'! charMap: map charMap := map! charMapAt: char | index | index := char asInteger. ^index = 0 ifTrue: [false] ifFalse: [charMap at: index]! ! !PrologString class methodsFor: 'copyright'! copyright ^'Copyright (C) 1995-1998 AOKI Atsushi, All Rights Reserved.'! system ^'Goodies'! version ^'003'! ! !PrologString class methodsFor: 'instance creation'! fromString: aString ^super new string: aString! readFrom: aStream | buffer char string | buffer := WriteStream on: (String new: 20). char := aStream next. char = $" ifTrue: [ [char := aStream peek. char ~~ nil] whileTrue: [char = $" ifTrue: [aStream next. char := aStream peek. char = $" ifFalse: [^self fromString: buffer contents]]. buffer nextPut: aStream next]]. string := aStream upToEnd. string size > 100 ifTrue: [string := string copyFrom: 1 to: 100]. self error: 'Syntax error near $" unmatched $"\' withCRs , (string = '' ifTrue: ['-- end of file --'] ifFalse: ['--> ' , string])! ! !PrologString methodsFor: 'accessing'! at: index ^string at: index! at: index put: char ^string at: index put: char! size ^string size! string ^string! string: aString string := aString! ! !PrologString methodsFor: 'comparing'! < aPrologString ^self string < aPrologString string! <= aPrologString ^self string <= aPrologString string! > aPrologString ^self string > aPrologString string! >= aPrologString ^self string >= aPrologString string! hash ^self asString hash! ! !PrologString methodsFor: 'converting'! asString ^self string! ! !PrologString methodsFor: 'enumerating'! do: aBlock ^self asString do: aBlock! ! !PrologString methodsFor: 'printing'! printOn: aStream aStream nextPutAll: self class printString. aStream nextPutAll: '('. aStream nextPutAll: self asString. aStream nextPutAll: ')'! printPrologOn: aStream | i length x | aStream nextPut: $". i := 0. length := string size. [(i := i + 1) <= length] whileTrue: [aStream nextPut: (x := string at: i). x == $" ifTrue: [aStream nextPut: x]]. aStream nextPut: $"! printPrologOn: aStream level: anInteger self printPrologOn: aStream! ! !PrologString methodsFor: 'testing'! = anObject anObject class = self class ifFalse: [^false]. ^self string = anObject string! ! !PrologStructure class methodsFor: 'copyright'! copyright ^'Copyright (C) 1995-1998 AOKI Atsushi, All Rights Reserved.'! system ^'Goodies'! version ^'003'! ! !PrologStructure class methodsFor: 'instance creation'! functor: aPrologSymbol terms: aPrologTerms ^super new functor: aPrologSymbol terms: aPrologTerms! ! !PrologStructure methodsFor: 'accessing'! arity ^self terms length! functor ^carPart! functor: aPrologSymbol carPart := aPrologSymbol! nthTerm: anInteger ^cdrPart nth: anInteger! terms ^cdrPart! terms: aPrologTerms cdrPart := aPrologTerms! ! !PrologStructure methodsFor: 'functions'! structureList "disassemble prolog structure of myself into a list." ^(self functor) cons: self terms asPrologList! ! !PrologStructure methodsFor: 'printing'! printPrologOn: aStream | functor terms | functor := self functor. terms := self terms. functor printPrologOn: aStream. terms == nil ifFalse: [(terms consp) ifTrue: [terms printPrologOn: aStream] ifFalse: [aStream nextPutAll: '(|'. terms printPrologOn: aStream. aStream nextPut: $)]]! printPrologOn: aStream level: anInteger self printPrologOn: aStream! ! !PrologStructure methodsFor: 'private'! functor: aPrologSymbol terms: aPrologTerms self functor: aPrologSymbol. self terms: aPrologTerms! ! !PrologSymbol class methodsFor: 'class initialization'! initialize "PrologSymbol initialize" | newMap | newMap := Array new: 256 withAll: false. newMap atAll: ($0 asInteger to: $9 asInteger) put: true. newMap atAll: ($A asInteger to: $Z asInteger) put: true. newMap atAll: ($a asInteger to: $z asInteger) put: true. 128 to: 256 do: [:i | newMap at: i put: true]. #($+ $- $! $: $* $/ $\ $> $< $= $_) do: [:each | newMap at: each asInteger put: true]. self charMap: newMap. PrologSymbolTable := Dictionary new. PrologCut := self install: '!'. PrologTrue := self install: 'true'. PrologFail := self install: 'fail'. PrologSend := self install: 'send'. PrologVar := self install: 'var'. PrologSelf := self install: 'self'! ! !PrologSymbol class methodsFor: 'constants'! cut ^PrologCut! ! !PrologSymbol class methodsFor: 'copyright'! copyright ^'Copyright (C) 1995-1998 AOKI Atsushi, All Rights Reserved.'! system ^'Goodies'! version ^'003'! ! !PrologSymbol class methodsFor: 'instance creation'! install: aString | symbol key | symbol := PrologSymbolTable at: aString ifAbsent: [nil]. symbol == nil ifTrue: [key := self fromString: aString. symbol := self fromString: aString. PrologSymbolTable at: key put: symbol]. ^symbol! readFrom: aStream | buffer char | buffer := WriteStream on: (String new: 20). char := aStream peek. char == $' ifTrue: [aStream next. [char := aStream peek. char ~~ nil] whileTrue: [char = $' ifTrue: [aStream next. char := aStream peek. char = $' ifFalse: [^self install: buffer contents]]. buffer nextPut: aStream next]. self error: 'Syntax error near $'' unmatched $''\-- end of file --' withCRs]. (self expect: '=..' on: aStream) ifTrue: ["Non standard (or ad hoc) parsing patterns." ^self install: '=..']. [char ~~ nil and: [self charMapAt: char]] whileTrue: [buffer nextPut: aStream next. char := aStream peek]. ^self install: buffer contents! ! !PrologSymbol class methodsFor: 'private'! expect: aString on: aStream "If aStream contains aString at the current position, then return true and set the position of aStream to the next char of the string. else return false and rewind the position." | pos string | pos := aStream position. string := String new. aString size timesRepeat: [ aStream atEnd ifFalse: [string := string , (String with: aStream next)]]. aString = string ifTrue: [^true] ifFalse: [ aStream position: pos. ^false]! ! !PrologSymbol methodsFor: 'accessing'! arity ^0! functor ^self! ! !PrologSymbol methodsFor: 'printing'! printPrologOn: aStream | flag firstChar i length x | flag := false. self do: [:each | (self class charMapAt: each) ifFalse: [flag := true]]. string isEmpty ifTrue: [aStream nextPutAll: ''''. aStream nextPutAll: ''''] ifFalse: [firstChar := string at: 1. ((firstChar >= $A and: [firstChar <= $Z]) or: [flag]) ifTrue: [aStream nextPutAll: ''''. i := 0. length := string size. [(i := i + 1) <= length] whileTrue: [aStream nextPut: (x := string at: i). x == $' ifTrue: [aStream nextPut: x]]. aStream nextPutAll: ''''] ifFalse: [i := 0. length := string size. [(i := i + 1) <= length] whileTrue: [aStream nextPut: (x := string at: i). x == $' ifTrue: [aStream nextPut: x]]]]! printPrologOn: aStream level: anInteger self printPrologOn: aStream! ! !PrologSymbol methodsFor: 'testing'! isBuiltInPredicate self isPrologCut ifTrue: [^true]. self isPrologTrue ifTrue: [^true]. self isPrologFail ifTrue: [^true]. self isPrologSend ifTrue: [^true]. self isPrologVar ifTrue: [^true]. ^false! isPrologCut ^self = PrologCut! isPrologFail ^self = PrologFail! isPrologSelf ^self = PrologSelf! isPrologSend ^self = PrologSend! isPrologTrue ^self = PrologTrue! isPrologVar ^self = PrologVar! ! PrologSymbol initialize! !PrologTerms class methodsFor: 'copyright'! copyright ^'Copyright (C) 1995-1998 AOKI Atsushi, All Rights Reserved.'! system ^'Goodies'! version ^'003'! ! !PrologTerms class methodsFor: 'instance creation'! fromList: aPrologDotPair ^super new fromList: aPrologDotPair! fromReverseList: aPrologDotPair ^super new fromReverseList: aPrologDotPair! term: term next: link ^super new term: term next: link! ! !PrologTerms methodsFor: 'printing'! printPrologOn: aStream | list | aStream nextPut: $(. list := self. [list cdr consp] whileTrue: [list ~~ self ifTrue: [aStream nextPut: $,]. list car printPrologOn: aStream. list := list cdr]. list ~~ self ifTrue: [aStream nextPut: $,]. list car printPrologOn: aStream. list cdr isNil ifTrue: [aStream nextPut: $)] ifFalse: [aStream nextPut: $|. list cdr printPrologOn: aStream. aStream nextPut: $)]! printPrologOn: aStream level: anInteger self printPrologOn: aStream! ! !PrologTerms methodsFor: 'private'! fromList: aPrologDotPair ^self fromReverseList: aPrologDotPair reverse! fromReverseList: aPrologDotPair | list terms mark | list := aPrologDotPair. terms := nil. [list consp] whileTrue: [terms == nil ifTrue: [terms := mark := self class term: list car next: terms] ifFalse: [terms := self class term: list car next: terms]. list := list cdr]. mark cdr: list. ^terms! term: anObject next: link carPart := anObject. cdrPart := link! ! !PrologVariable class methodsFor: 'class initialization'! initialize "PrologVariable initialize" | newMap | newMap := Array new: 256 withAll: false. newMap atAll: ($0 asInteger to: $9 asInteger) put: true. newMap atAll: ($A asInteger to: $Z asInteger) put: true. newMap atAll: ($a asInteger to: $z asInteger) put: true. newMap at: $~ asInteger put: true. self charMap: newMap. self setZero. PrologVariableTable := Dictionary new! ! !PrologVariable class methodsFor: 'copyright'! copyright ^'Copyright (C) 1995-1998 AOKI Atsushi, All Rights Reserved.'! system ^'Goodies'! version ^'003'! ! !PrologVariable class methodsFor: 'instance creation'! install: aString | variable key | variable := PrologVariableTable at: aString ifAbsent: [nil]. variable == nil ifTrue: [key := aString. variable := self fromString: aString. PrologVariableTable at: key put: variable]. ^variable! readFrom: aStream | buffer char | buffer := WriteStream on: (String new: 20). char := aStream peek. (char ~~ nil and: [char = $~]) ifTrue: [aStream next. self countUp. ^self install: '~' , PrologVariableCounter printString]. [char ~~ nil and: [ self charMapAt: char]] whileTrue: [buffer nextPut: aStream next. char := aStream peek]. ^self install: buffer contents! ! !PrologVariable class methodsFor: 'private'! countUp PrologVariableCounter := PrologVariableCounter + 1! setZero PrologVariableCounter := 0! ! !PrologVariable methodsFor: 'printing'! printPrologOn: aStream (self asString at: 1) = $~ ifTrue: [aStream nextPut: $~] ifFalse: [aStream nextPutAll: self asString]! printPrologOn: aStream level: anInteger self printPrologOn: aStream! ! !PrologVariable methodsFor: 'testing'! isPrologVariable ^true! ! PrologVariable initialize! !PrologInterpreter class methodsFor: 'class initialization'! flushOthers "PrologInterpreter flushOthers." self flushSystemPredicates! flushSystemPredicates "PrologInterpreter flushSystemPredicates." SystemPredicates := nil! ! !PrologInterpreter class methodsFor: 'copyright'! copyright ^'Copyright (C) 1995-1998 AOKI Atsushi, All Rights Reserved.'! system ^'Goodies'! version ^'003'! ! !PrologInterpreter class methodsFor: 'examples'! example01 "PrologInterpreter example01." self example: ' ?- remove. % remove all predicates in PrologDataBase. likes(john,mary). % assert fact. likes(john,wine). % assert fact. likes(mary,wine). % assert fact. likes(mary,john). % assert fact. ?- likes(X,Y). % question goal. ?- likes(john,X), likes(mary,X). % question goal. '! example02 "PrologInterpreter example02." self example: ' ?- remove. % remove all predicates in PrologDataBase. on(hen,cat). on(cat,dog). on(dog,donkey). above(X,Y) :- on(X,Y). above(X,Y) :- on(X,Z), above(Z,Y). ?- on(X,dog). ?- above(X,dog). '! example03 "PrologInterpreter example03." self example: ' ?- remove. % remove all predicates in PrologDataBase. hanoi(N) :- % This is Hanoi Tower Prolgram. move(N,left,right,center). move(0,X,Y,Z) :- !. move(N,A,B,C) :- -(N,1,M), move(M,A,C,B), inform(A,B), move(M,C,B,A). inform(X,Y) :- write([move,disc,from,X,to,Y]), nl. ?- hanoi(3). % question goal. '! example04 "PrologInterpreter example04." | string prolog result | self example: '?- append(X,Y,[a,b,c,d]).'! example05 "PrologInterpreter example05." self example: ' ?- send(123,+,[456],X). % X := 123 + 456. '! example06 "PrologInterpreter example06." self example: ' ?- is(X,+(3,4)). ?- is(X,F(3,4)). '! example: string ^PrologInterpreter new textCollector: Transcript; refute: string action: [:answer | answer keys asSortedCollection do: [:s | Transcript show: s. Transcript show: ' = '. Transcript show: (answer at: s) printPrologString. Transcript nl]. false]! ! !PrologInterpreter class methodsFor: 'instance creation'! new ^super new initialize! ! !PrologInterpreter class methodsFor: 'public access'! refute: stringOrStream ^self new refute: stringOrStream! refute: stringOrStream action: aBlock ^self new refute: stringOrStream action: aBlock! ! !PrologInterpreter methodsFor: 'accessing'! textCollector ^textCollector! textCollector: aTextCollector textCollector := aTextCollector! ! !PrologInterpreter methodsFor: 'binding and unbinding'! bind: x env: xEnv and: y env: yEnv | list | list := (self fetchValue: y env: yEnv) cons: valueEnv. list := (x cons: list) cons: xEnv cdr. xEnv cdr: list. unbindList := xEnv cons: unbindList! binding: x env: xEnv | assocList | assocList := xEnv cdr. assocList == nil ifTrue: [^nil]. ^assocList assoc: x! fetchValue: x env: xEnv | xx xxEnv assoc | xx := x. xxEnv := xEnv. [true] whileTrue: [valueEnv := xxEnv. xx isPrologVariable ifTrue: [assoc := self binding: xx env: xxEnv. assoc == nil ifTrue: [^xx]. assoc := assoc cdr. xx := assoc car. xxEnv := assoc cdr] ifFalse: [^xx]]! noValue: x env: xEnv | assoc | x isPrologVariable ifTrue: [assoc := self binding: x env: xEnv. assoc == nil ifTrue: [^true]. assoc := assoc cdr. ^self noValue: assoc car env: assoc cdr]. ^false! nullEnv envCounter := envCounter + 1. ^envCounter cons: nil! unbindFrom: start to: end | list env assocList | list := start. [list ~~ end] whileTrue: [env := list car. assocList := env cdr. assocList car cdr cdr: nil. env cdr: assocList cdr. list := list cdr]! ! !PrologInterpreter methodsFor: 'copying'! shallowCopy super shallowCopy. textValue := nil. listValue := nil. predicate := nil! ! !PrologInterpreter methodsFor: 'initialize-release'! initialize systemPredicates := Dictionary new. userPredicates := Dictionary new. tracePredicates := Dictionary new. textCollector := Transcript. verbose := false. self makeSystemPredicates! ! !PrologInterpreter methodsFor: 'kernel predicates'! builtInCut backTrack := cutBack car. clause := clause cdr. status := #loop! builtInFail status := #back! builtInPredicate: functor functor isPrologCut ifTrue: [^self builtInCut]. functor isPrologTrue ifTrue: [^self builtInTrue]. functor isPrologFail ifTrue: [^self builtInFail]. functor isPrologSend ifTrue: [^self builtInSend]. functor isPrologVar ifTrue: [^self builtInVar]. self error: 'Unexpected built-in predicate'! builtInSend | list receiverSymbol selectorSymbol argumentList unifyTerm result | list := self expression: clause car cdr env: clauseEnv. receiverSymbol := list car. list := list cdr. selectorSymbol := list car. list := list cdr. argumentList := list car. list := list cdr. list == nil ifTrue: [unifyTerm := nil] ifFalse: [list cdr == nil ifTrue: [unifyTerm := clause car cdr nth: 4] ifFalse: [status := #back. ^self]]. result := self receiver: receiverSymbol selector: selectorSymbol arguments: argumentList. result = PrologSymbol cut ifTrue: [self builtInCut. status := #back. ^self]. unifyTerm isNil ifTrue: [result = false ifFalse: [result := true]. result ifTrue: [clause := clause cdr. status := #loop. ^self] ifFalse: [status := #back. ^self]] ifFalse: [(self unify: unifyTerm env: clauseEnv and: result env: self nullEnv) ifTrue: [clause := clause cdr. status := #loop. ^self] ifFalse: [status := #back. ^self]]. ^self! builtInTrue clause := clause cdr. status := #loop! builtInVar | var | var := clause car cdr car. (self noValue: var env: clauseEnv) ifTrue: [clause := clause cdr. status := #loop] ifFalse: [status := #back]! call: aPrologStructure | structure functor | aPrologStructure cdr == nil ifTrue: [self callVariable: aPrologStructure car. ^self]. structure := self expression: aPrologStructure env: clauseEnv. (self unify: aPrologStructure env: clauseEnv and: structure env: clauseEnv) ifFalse: [self error: 'Unexpected unify structure']. functor := structure car. functor isPrologVariable ifTrue: [status := #back. ^self]. clause := clause cdr. clause := structure cons: clause. status := #loop! callVariable: aPrologVariable | horn functor | horn := self expression: aPrologVariable env: clauseEnv. (self unify: aPrologVariable env: clauseEnv and: horn env: clauseEnv) ifFalse: [self error: 'Unexpected unify horn clause']. horn consp ifFalse: [horn := PrologStructure functor: horn terms: nil]. horn car consp ifFalse: [horn := PrologClause head: horn body: nil]. horn := PrologClause head: horn car body: (PrologBody fromList: horn cdr). functor := horn car car. functor isPrologVariable ifTrue: [status := #back. ^self]. clause := clause cdr. horn := horn reverse. [horn consp] whileTrue: [clause := horn car cons: clause. horn := horn cdr]. status := #loop! receiver: receiverSymbol selector: selectorSymbol arguments: argumentList | receiver size selector arguments list result index | ((receiverSymbol isKindOf: PrologSymbol) and: [receiverSymbol isPrologSelf]) ifTrue: [receiver := self] ifFalse: [receiver := receiverSymbol]. (receiver isKindOf: PrologObject) ifTrue: [receiver := receiver object]. size := selectorSymbol size. selector := String new: size. 1 to: size do: [:i | selector at: i put: (selectorSymbol at: i)]. selector := selector asSymbol. list := argumentList. list == nil ifTrue: [arguments := Array new. result := receiver perform: selector] ifFalse: [size := list length. arguments := Array new: size. 1 to: size do: [:i | arguments at: i put: ((list car isKindOf: PrologObject) ifTrue: [list car object] ifFalse: [list car]). list := list cdr]. result := receiver perform: selector withArguments: arguments]. ((result = true or: [result = false]) or: [result isPrologEntity]) ifTrue: [result := result yourself] ifFalse: [list := PrologList car: receiverSymbol cdr: argumentList. index := (Array with: receiver) , arguments findFirst: [:each | each = result]. index = 0 ifTrue: [result := PrologObject source: result printString object: result] ifFalse: [result := list nth: index]]. ^result! ! !PrologInterpreter methodsFor: 'outputting'! outputAnswer: dict | anArray string assoc associations | associations := OrderedCollection new. dict associationsDo: [:association | associations add: association]. anArray := associations asSortedCollection. 1 to: anArray size do: [:i | assoc := anArray at: i. i = 1 ifTrue: [string := ''] ifFalse: [string := ',\' withCRs]. string := string , assoc key. string := string , ' = '. string := string , assoc value printPrologString. string := string , ' '. textCollector show: string]! outputTime: msec | goal string | verbose ifTrue: [goal := envCounter - 1. string := '<'. string := string , msec printString , ' milliseconds, '. string := string , goal printString , ' goals'. string := string , '>\' withCRs. textCollector show: string asText]! outputVariables: aDictionary | bool | self outputAnswer: aDictionary. bool := self confirm: 'All right ?'. bool ifTrue: [textCollector nl] ifFalse: [textCollector show: ';\' withCRs]. ^bool! ! !PrologInterpreter methodsFor: 'private'! acceptWith: aText "force to regist aText as a contents." self contents: aText. textValue := aText. self changed: #clearUserEdits! associations: aCollection "by nishis, 1998/04/12 07:34" | anOrderedCollection | anOrderedCollection := OrderedCollection new: aCollection size. aCollection associationsDo: [:association | anOrderedCollection add: association]. ^ anOrderedCollection! deallocateEnv: env | assocList assoc nextEnv | assocList := env cdr. [assocList consp] whileTrue: [assoc := assocList car. nextEnv := assoc cdr cdr. assoc cdr cdr: nil. nextEnv consp ifTrue: [self deallocateEnv: nextEnv]. assocList := assocList cdr]! getCondition | condition | condition := Array new: 14. condition at: 1 put: status. condition at: 2 put: definition. condition at: 3 put: question. condition at: 4 put: questionEnv. condition at: 5 put: clause. condition at: 6 put: clauseEnv. condition at: 7 put: queue. condition at: 8 put: queueEnv. condition at: 9 put: valueEnv. condition at: 10 put: unbindList. condition at: 11 put: cutBack. condition at: 12 put: backTrack. condition at: 13 put: resolveAction. condition at: 14 put: definitionStack. ^condition! makeSystemPredicates SystemPredicates isNil ifTrue: [self systemPredicatesNo0. self systemPredicatesNo1. self systemPredicatesNo2. self systemPredicatesNo3. self systemPredicatesNo4. self systemPredicatesNo5. self systemPredicatesNo6. self systemPredicatesNo7. self systemPredicatesNo8. self systemPredicatesNo9. SystemPredicates := systemPredicates] ifFalse: [systemPredicates := SystemPredicates]! putCondition: condition status := condition at: 1. definition := condition at: 2. question := condition at: 3. questionEnv := condition at: 4. clause := condition at: 5. clauseEnv := condition at: 6. queue := condition at: 7. queueEnv := condition at: 8. valueEnv := condition at: 9. unbindList := condition at: 10. cutBack := condition at: 11. backTrack := condition at: 12. resolveAction := condition at: 13. definitionStack := condition at: 14! systemPredicatesNo0 "PrologInterpreter flushSystemPredicates." self systemReconsult: (ReadStream on: ' ! :- builtin. true :- builtin. fail :- builtin. var(X) :- builtin. send(X,Y,Z) :- bulitin. send(X,Y,Z,A) :- bulitin. ')! systemPredicatesNo1 "PrologInterpreter flushSystemPredicates." self systemReconsult: (ReadStream on: ' repeat. repeat :- repeat. nonvar(X) :- var(X), !, fail. nonvar(X). integer(X) :- send(self,integer:,[X]). float(X) :- send(self,float:,[X]). double(X) :- send(self,double:,[X]). fraction(X) :- send(self,fraction:,[X]). number(X) :- send(self,number:,[X]). symbol(X) :- send(self,symbol:,[X]). string(X) :- send(self,string:,[X]). list(X) :- send(self,list:,[X]). dotp(X) :- send(self,dotp:,[X]). atom(X) :- symbol(X). atom(X) :- nonvar(X), =(X,[]). atom(X) :- string(X). atomic(X) :- atom(X). atomic(X) :- number(X). structure(X) :- nonvar(X), not(atomic(X)). ')! systemPredicatesNo2 "PrologInterpreter flushSystemPredicates." self systemReconsult: (ReadStream on: ' ==(X,Y) :- send(X,=,[Y]). \==(X,Y) :- ==(X,Y), !, fail. \==(X,Y). =(X,X). \=(X,Y) :- =(X,Y), !, fail. \=(X,Y). >(X,Y) :- send(X,>,[Y]). >=(X,Y) :- send(X,>=,[Y]). <(X,Y) :- send(X,<,[Y]). =<(X,Y) :- send(X,<=,[Y]). ')! systemPredicatesNo3 "PrologInterpreter flushSystemPredicates." self systemReconsult: (ReadStream on: ' +(X,Y,Z) :- send(X,+,[Y],Z). -(X,Y,Z) :- send(X,-,[Y],Z). *(X,Y,Z) :- send(X,*,[Y],Z). //(X,Y,Z) :- send(X,//,[Y],Z). /(X,Y,Z) :- send(X,/,[Y],Z). \\(X,Y,Z) :- send(X,\\,[Y],Z). is(Z,+(X,Y)) :- nonvar(Z), nonvar(X), nonvar(Y), send(X,+,[Y],Z). is(Z,+(X,Y)) :- var(Z), nonvar(X), nonvar(Y), send(X,+,[Y],Z). is(Z,+(X,Y)) :- var(X), nonvar(Y), nonvar(Z), send(Z,-,[Y],X). is(Z,+(X,Y)) :- var(Y), nonvar(Z), nonvar(X), send(Z,-,[X],Y). is(Z,-(X,Y)) :- nonvar(Z), nonvar(X), nonvar(Y), send(X,-,[Y],Z). is(Z,-(X,Y)) :- var(Z), nonvar(X), nonvar(Y), send(X,-,[Y],Z). is(Z,-(X,Y)) :- var(X), nonvar(Y), nonvar(Z), send(Z,+,[Y],X). is(Z,-(X,Y)) :- var(Y), nonvar(Z), nonvar(X), send(X,-,[Z],Y). is(Z,*(X,Y)) :- nonvar(Z), nonvar(X), nonvar(Y), send(X,*,[Y],Z). is(Z,*(X,Y)) :- var(Z), nonvar(X), nonvar(Y), send(X,*,[Y],Z). is(Z,*(X,Y)) :- var(X), nonvar(Y), nonvar(Z), send(Z,/,[Y],X). is(Z,*(X,Y)) :- var(Y), nonvar(Z), nonvar(X), send(Z,/,[X],Y). is(Z,/(X,Y)) :- nonvar(Z), nonvar(X), nonvar(Y), send(X,/,[Y],Z). is(Z,/(X,Y)) :- var(Z), nonvar(X), nonvar(Y), send(X,/,[Y],Z). is(Z,/(X,Y)) :- var(X), nonvar(Y), nonvar(Z), send(Z,*,[Y],X). is(Z,/(X,Y)) :- var(Y), nonvar(Z), nonvar(X), send(X,/,[Z],Y). is(X,Y) :- =(X,Y). ')! systemPredicatesNo4 "PrologInterpreter flushSystemPredicates." self systemReconsult: (ReadStream on: ' listing :- send(self,userListing,[]). listing(X) :- send(self,userListing:,[X]). systemListing :- send(self,systemListing,[]). systemListing(X) :- send(self,systemListing:,[X]). consult(X) :- nonvar(X), send(self,consultFile:,[X]). reconsult(X) :- nonvar(X), send(self,reconsultFile:,[X]). saving :- send(self,saving,[]). saving(X) :- send(self,saving:,[X]). userPredicates(X) :- send(self,userPredicates,[],X). systemPredicates(X) :- send(self,systemPredicates,[],X). predicates([X|Y]) :- userPredicates(X), systemPredicates(Y). functor(T,F,A) :- nonvar(T), !, send(self,functorArityOf:,[T],[F|A]). functor(T,F,A) :- number(F), !, =(0,A),=(T,F). functor(T,F,A) :- atom(F), =<(0,A), ''~addvar''([F],A,L), =..(T,L). ''~addvar''(L,0,M) :- !, =(L,M). ''~addvar''(L,NVars,M) :- -(NVars, 1, N), append(L,[FreeV],LV), ''~addvar''(LV,N,M). arg(Nth,S,T) :- integer(Nth), <(0,Nth), structure(S), =..(S,[F|L]), nth(L,Nth,T). =..(X,Y) :- send(self,univ:,[[''X''|''Y'']]). name(X,Y) :- atomic(X), list(Y), !, send(self,symToList:,[X],Y). name(X,Y) :- atomic(X), !, send(self,symToStr:,[X],Y). name(X,Y) :- var(X), !, nonvar(Y), send(self, strToSym:,[Y],X). remove :- send(self,remove,[]). remove(X) :- send(self,remove:,[X]). clause(X) :- send(self,clauseSet:,[X]), repeat, send(self,clause:,[X],X). asserta(X) :- send(self,asserta:,[X]). assert(X) :- send(self,assertz:,[X]). assertz(X) :- send(self,assertz:,[X]). retract(X) :- repeat, send(self,retract:,[X],X). ')! systemPredicatesNo5 "PrologInterpreter flushSystemPredicates." self systemReconsult: (ReadStream on: ' call(G) :- G. not(G) :- G, !, fail. not(G). or(X,Y) :- call(X). or(X,Y) :- call(Y). and(X,Y) :- call(X), call(Y). ')! systemPredicatesNo6 "PrologInterpreter flushSystemPredicates." self systemReconsult: (ReadStream on: ' write(X) :- send(self,write:,[X]). nl :- send(self,nl,[]). tab(X) :- number(X), send(self,tab:,[X]). clear :- send(self,clear,[]). ')! systemPredicatesNo7 "PrologInterpreter flushSystemPredicates." self systemReconsult: (ReadStream on: ' clock(X) :- send({Time},millisecondClockValue,[],X). verbose(X) :- send(self,verbose:,[X]). gc :- send(self,gc,[]). inspect(X) :- send(X,inspect,[]). spy(X) :- send(self,spy:,[X]). nospy(X) :- send(self,nospy:,[X]). trace :- send(self,trace,[]). notrace :- send(self,notrace,[]). ')! systemPredicatesNo8 "PrologInterpreter flushSystemPredicates." self systemReconsult: (ReadStream on: ' append([],X,X). append([A|X],Y,[A|Z]) :- append(X,Y,Z). member(X,[X|Y]). member(X,[Y|Z]) :- member(X,Z). reverse([],[]). reverse([H|T],L) :- reverse(T,Z), append(Z,[H],L). length(X,Y) :- send(self,length:,[X],Y). nth([X|Y],1,Z) :- !, =(X,Z). nth([X|Y],N,Z) :- -(N,1,PN), nth(Y,PN,Z). printlist(L) :- send(self,listPrint:,[L]). lispAppend(X,Y,Z) :- send(X,append:,[Y],Z). lispReverse(X,Y) :- send(X,reverse,[],Y). lispMember(X,Y) :- send(Y,member:,[X],A), \=(A,[]). lispMember(X,Y,Z) :- send(Y,member:,[X],Z). lispAssoc(X,Y) :- send(Y,assoc:,[X],A), \=(A,[]). lispAssoc(X,Y,Z) :- send(Y,assoc:,[X],Z). lispNconc(X,Y,Z) :- send(X,nconc:,[Y],Z). ')! systemPredicatesNo9 "PrologInterpreter flushSystemPredicates." self systemReconsult: (ReadStream on: ' % % User System Predicates % ')! ! !PrologInterpreter methodsFor: 'public accessing'! refute: stringOrStream ^self refute: stringOrStream action: [:answer | ^answer]! refute: stringOrStream action: aBlock | stream | (stringOrStream isKindOf: Stream) ifTrue: [stream := ReadStream on: stringOrStream contents] ifFalse: [stream := ReadStream on: stringOrStream]. ^self consult: stream action: aBlock! ! !PrologInterpreter methodsFor: 'representation'! collectVariables | dict | dict := Dictionary new. self collectVariables: question to: dict. ^dict! collectVariables: x to: dict | key value | (x isPrologVariable and: [(x at: 1) ~= $~]) ifTrue: [key := String fromString: x printPrologString. (dict at: key ifAbsent: []) ~~ nil ifTrue: [^self] ifFalse: [value := self represent: x env: questionEnv. dict at: key put: value]]. (x consp) ifFalse: [^self]. self collectVariables: x car to: dict. self collectVariables: x cdr to: dict! expression: x env: xEnv | assoc a d | x isPrologVariable ifTrue: [assoc := self binding: x env: xEnv. assoc == nil ifTrue: [^x]. assoc := assoc cdr. ^self expression: assoc car env: assoc cdr]. (x consp) ifFalse: [^x]. a := self expression: x car env: xEnv. d := self expression: x cdr env: xEnv. ^x class car: a cdr: d! represent: x env: xEnv | assoc a d | x isPrologVariable ifTrue: [assoc := self binding: x env: xEnv. assoc == nil ifTrue: [^self variableRepresent: x env: xEnv]. assoc := assoc cdr. ^self represent: assoc car env: assoc cdr]. (x consp) ifFalse: [^x]. a := self represent: x car env: xEnv. d := self represent: x cdr env: xEnv. ^x class car: a cdr: d! variableRepresent: x env: xEnv ^PrologVariable install: x string , xEnv car printString! ! !PrologInterpreter methodsFor: 'resolution'! resolve: goal ^self resolve: goal action: nil! resolve: goal action: actionBlock question := clause := goal. actionBlock == nil ifTrue: [resolveAction := [:dict | self outputVariables: dict]] ifFalse: [resolveAction := actionBlock]. self resolveInitialize. self resolveLoop. ^self resolveTerminate! resolveInitialize status := #loop. envCounter := 0. questionEnv := clauseEnv := self nullEnv. queue := queueEnv := valueEnv := nil. unbindList := cutBack := backTrack := nil. definitionStack := nil. traceCounter := 0! resolveLoop | totalTime time answer | totalTime := 0. time := Time millisecondClockValue. [true] whileTrue: [status == #loop ifTrue: [self loop]. status == #next ifTrue: [self next]. status == #back ifTrue: [self back]. status == #succ ifTrue: [time := Time millisecondClockValue - time. self outputTime: (totalTime := totalTime + time). answer := self collectVariables. answer isEmpty ifTrue: [^true]. (resolveAction value: answer) ifTrue: [^true] ifFalse: [status := #back. time := Time millisecondClockValue]]. status == #fail ifTrue: [time := Time millisecondClockValue - time. self outputTime: (totalTime := totalTime + time). ^false]]! resolveTerminate self deallocateEnv: questionEnv. status == #succ ifTrue: [textCollector show: 'yes'. textCollector nl. ^true]. status == #fail ifTrue: [textCollector show: 'no'. textCollector nl. ^false]. self error: 'Unexpected status'! ! !PrologInterpreter methodsFor: 'resolve modules'! back | array | backTrack == nil ifTrue: [status := #fail. ^self]. array := backTrack car. backTrack := backTrack cdr. clause := array at: 1. clauseEnv := array at: 2. queue := array at: 3. queueEnv := array at: 4. cutBack := array at: 5. definition := array at: 6. array := array at: 7. self unbindFrom: unbindList to: array. unbindList := array. status := #next! loop | structure functor | clause == nil ifTrue: [queue == nil ifTrue: [status := #succ. ^self]. clause := queue car. clauseEnv := queueEnv car. queue := queue cdr. queueEnv := queueEnv cdr. cutBack := cutBack cdr. status := #loop. ^self]. structure := clause car. structure consp ifFalse: [structure := PrologStructure functor: structure terms: nil. clause car: structure]. functor := structure car. functor isPrologVariable ifTrue: [self call: clause car. ^self]. functor isBuiltInPredicate ifTrue: [self builtInPredicate: functor. ^self]. definition := userPredicates at: functor ifAbsent: [systemPredicates at: functor ifAbsent: [status := #back. ^self]]. status := #next! next | definitionEnv saveBackTrack array | definitionEnv := self nullEnv. definition cdr == nil ifTrue: [(self unify: clause car cdr env: clauseEnv and: definition car car cdr env: definitionEnv) ifFalse: [status := #back. ^self]. queue := clause cdr cons: queue. queueEnv := clauseEnv cons: queueEnv. clause := definition car cdr. clauseEnv := definitionEnv. cutBack := backTrack cons: cutBack. status := #loop. ^self]. saveBackTrack := backTrack. array := Array new: 7. array at: 1 put: clause. array at: 2 put: clauseEnv. array at: 3 put: queue. array at: 4 put: queueEnv. array at: 5 put: cutBack. array at: 6 put: definition cdr. array at: 7 put: unbindList. backTrack := array cons: saveBackTrack. (self unify: clause car cdr env: clauseEnv and: definition car car cdr env: definitionEnv) ifFalse: [status := #back. ^self]. queue := clause cdr cons: queue. queueEnv := clauseEnv cons: queueEnv. clause := definition car cdr. clauseEnv := definitionEnv. cutBack := saveBackTrack cons: cutBack. status := #loop! ! !PrologInterpreter methodsFor: 'system predicates'! asserta: aPrologClause | horn def functor | horn := aPrologClause. horn consp ifFalse: [horn := PrologStructure functor: horn terms: nil]. horn car consp ifFalse: [horn := PrologClause head: horn body: nil]. horn := PrologClause head: horn car body: (PrologBody fromList: horn cdr). functor := horn car car. def := userPredicates at: functor ifAbsent: [nil]. def == nil ifTrue: [def := PrologDefinition fromList: (horn cons: nil). userPredicates at: functor put: def] ifFalse: [def := PrologDefinition fromList: (horn cons: def). userPredicates at: functor put: def]. ^true! assertz: aPrologClause | horn def functor | horn := aPrologClause. horn consp ifFalse: [horn := PrologStructure functor: horn terms: nil]. horn car consp ifFalse: [horn := PrologClause head: horn body: nil]. horn := PrologClause head: horn car body: (PrologBody fromList: horn cdr). functor := horn car car. def := userPredicates at: functor ifAbsent: [nil]. def == nil ifTrue: [def := PrologDefinition fromList: (horn cons: nil). userPredicates at: functor put: def] ifFalse: [def nconc: (PrologDefinition fromList: (horn cons: nil))]. ^true! clause: aPrologClause | count horn def result | count := 0. horn := aPrologClause. horn consp ifFalse: [horn := PrologStructure functor: horn terms: nil. count := count + 1]. horn car consp ifFalse: [horn := PrologClause head: horn body: nil. count := count + 1]. horn := PrologClause head: horn car body: (PrologBody fromList: horn cdr). def := definitionStack car. [def consp] whileTrue: [(self unify: horn env: self nullEnv and: def car env: self nullEnv) ifTrue: [result := def car. count timesRepeat: [result := result car]. def := def cdr. definitionStack car: def. ^result] ifFalse: [def := def cdr. definitionStack car: def]]. definitionStack := definitionStack cdr. ^PrologSymbol cut! clear textCollector clear. ^true! consultFile: fileName | aFileStream | (fileName respondsTo: #asString) ifFalse: [^false]. (File name: fileName asString) exists ifTrue: [textCollector show: '\' withCRs. aFileStream := FileStream open: fileName asString mode: FileStream read. self consult: aFileStream action: nil. aFileStream close. ^true] ifFalse: [^false]! dotp: x ^x consp! double: x ^x isKindOf: Float! float: x ^x isKindOf: Float! fraction: x ^x isKindOf: Fraction! functorArityOf: aPrologStructure aPrologStructure isNil ifTrue: [^nil cons: 0]. (self number: aPrologStructure) ifTrue: [^aPrologStructure cons: 0]. (aPrologStructure respondsTo: #functor) ifFalse: [^nil]. ^aPrologStructure functor cons: aPrologStructure arity! gc ObjectMemory compact. Transcript nl; show: 'garbage collecting: '. ^true! integer: x ^x isKindOf: Integer! length: aPrologDotPair aPrologDotPair consp ifFalse: [^0]. ^aPrologDotPair length! list: x x == nil ifTrue: [^true]. ^self dotp: x! listPrint: aPrologDotPair | list | aPrologDotPair consp ifFalse: [^false]. list := aPrologDotPair. [list consp] whileTrue: [textCollector show: list car printPrologString , ' '. list := list cdr]. ^true! nl textCollector nl. ^true! nospy: aPrologSymbol | def | def := tracePredicates at: aPrologSymbol ifAbsent: [nil]. def == nil ifTrue: [^false]. userPredicates at: aPrologSymbol put: def. tracePredicates removeKey: aPrologSymbol. ^true! notrace userPredicates associationsDo: [:assoc | self nospy: assoc key]. ^true! number: x ^x isKindOf: Number! reconsultFile: fileName | aFileStream | (fileName respondsTo: #asString) ifFalse: [^false]. (File name: fileName asString) exists ifTrue: [textCollector show: '\' withCRs. aFileStream := FileStream open: fileName asString mode: FileStream read. self reconsult: aFileStream action: nil. aFileStream close. ^true] ifFalse: [^false]! remove userPredicates keys do: [:aPrologSymbol | userPredicates removeKey: aPrologSymbol ifAbsent: []. tracePredicates removeKey: aPrologSymbol ifAbsent: []]. ^true! remove: aPrologSymbol userPredicates removeKey: aPrologSymbol ifAbsent: [^false]. tracePredicates removeKey: aPrologSymbol ifAbsent: []. ^true! retract: aPrologClause | count horn def functor prev result | count := 0. horn := aPrologClause. horn consp ifFalse: [horn := PrologStructure functor: horn terms: nil. count := count + 1]. horn car consp ifFalse: [horn := PrologClause head: horn body: nil. count := count + 1]. horn := PrologClause head: horn car body: (PrologBody fromList: horn cdr). functor := horn car car. prev := def := userPredicates at: functor ifAbsent: [^PrologSymbol cut]. [def consp] whileTrue: [(self unify: horn env: self nullEnv and: def car env: self nullEnv) ifTrue: [result := def car. count timesRepeat: [result := result car]. prev == def ifTrue: [def cdr isNil ifTrue: [userPredicates removeKey: functor ifAbsent: [nil]] ifFalse: [userPredicates at: functor put: def cdr]. ^result] ifFalse: [prev cdr: def cdr. ^result]] ifFalse: [prev := def. def := def cdr]]. ^PrologSymbol cut! saving self saveOn: self saveFileName. ^true! saving: aPrologSymbol | def | def := tracePredicates at: aPrologSymbol ifAbsent: [userPredicates at: aPrologSymbol ifAbsent: []]. def == nil ifTrue: [^false]. self saveOn: self saveFileName. ^true! spy: aPrologSymbol | def reverseClone tracedef | def := userPredicates at: aPrologSymbol ifAbsent: [nil]. def == nil ifTrue: [^false]. (tracePredicates at: aPrologSymbol ifAbsent: [nil]) isNil ifFalse: [^true]. tracePredicates at: aPrologSymbol put: def. reverseClone := nil. [def consp] whileTrue: [reverseClone := def car cons: reverseClone. def := def cdr]. tracedef := nil. [reverseClone consp] whileTrue: [tracedef := (self traceFailClause: reverseClone car car) cons: tracedef. tracedef := (self traceExitClause: reverseClone car) cons: tracedef. reverseClone cdr consp ifTrue: [tracedef := (self traceRedoClause: reverseClone car car) cons: tracedef] ifFalse: [tracedef := (self traceCallClause: reverseClone car car) cons: tracedef]. reverseClone := reverseClone cdr]. userPredicates at: aPrologSymbol put: (PrologDefinition fromList: tracedef). ^true! string: x ^x class == PrologString! strToSym: listOrString | stream string token s | listOrString consp ifTrue: [s := WriteStream on: (String new: 16). listOrString do: [:char | s nextPut: (Character value: char)]. string := s contents] ifFalse: [string := listOrString string]. stream := ReadStream on: string. token := (PrologScanner new on: stream) nextToken. ((self number: token) and: [stream atEnd]) ifTrue: [^token] ifFalse: [string = '[]' ifTrue: [^nil] ifFalse: [^PrologSymbol install: string]]! symbol: x ^x class == PrologSymbol! symToList: numOrSym | pstring | pstring := self symToStr: numOrSym. ^PrologList list: pstring string asByteArray! symToStr: numOrSym numOrSym isNil ifTrue: [^PrologString fromString: '[]']. (self number: numOrSym) ifTrue: [^PrologString fromString: numOrSym printString]. ^PrologString fromString: numOrSym string! systemListing | predicateName | (self associations: systemPredicates) asSortedCollection do: [:assoc | predicateName := assoc key. ((predicateName respondsTo: #asString) and: [predicateName string isEmpty not and: [predicateName string first = $~]]) ifFalse: [self systemListing: predicateName]]. ^true! systemListing: aPrologSymbol | def | def := systemPredicates at: aPrologSymbol ifAbsent: [nil]. def == nil ifTrue: [^false]. [def consp] whileTrue: [textCollector show: def car prettyPrintPrologString , '\' withCRs. def := def cdr]. ^true! systemPredicates | collection list | collection := (self associations: systemPredicates) asSortedCollection. list := nil. collection reverseDo: [:each | ((each key respondsTo: #asString) and: [each key string isEmpty not and: [each key string first = $~]]) ifTrue: ['not adding: invisible predicate' yourself] ifFalse: [list := each key cons: list]]. ^list! tab: aNumber | spaces | (aNumber isKindOf: Number) ifFalse: [^false]. spaces := String new. aNumber asInteger timesRepeat: [spaces := spaces , ' ']. textCollector show: spaces. ^true! trace userPredicates associationsDo: [:assoc | self spy: assoc key]. ^true! univ: aPrologList | termv listv termValue termEnv listVal listEnv functor functorEnv terms newterms newStruct car t list | termv := PrologVariable install: aPrologList car string. listv := PrologVariable install: aPrologList cdr string. termValue := self fetchValue: termv env: clauseEnv. termEnv := valueEnv. listVal := self fetchValue: listv env: clauseEnv. listEnv := valueEnv. termValue isPrologVariable ifTrue: ["construct a term from fixed length list." listVal isPrologVariable ifTrue: [^false]. listVal consp ifFalse: [^false]. functor := self fetchValue: listVal car env: listEnv. functorEnv := valueEnv. terms := self fetchValue: listVal cdr env: listEnv. listEnv := valueEnv. (self number: functor) ifTrue: [terms isNil ifFalse: [^false]. self bind: termValue env: termEnv and: functor env: listEnv. ^true]. functor consp ifTrue: ["It's a structure or a list" ^false]. terms isNil ifTrue: [self bind: termValue env: termEnv and: functor env: functorEnv. ^true]. terms consp ifFalse: ["Not a list, but an illegal dot pair." ^false]. newterms := nil. [terms isNil] whileFalse: [car := terms car. terms := self fetchValue: terms cdr env: listEnv. terms isPrologVariable ifTrue: ["The length of the list has not been fixed yet." ^false]. t := PrologTerms car: car cdr: nil. newterms isNil ifTrue: [newterms := t] ifFalse: [newterms := newterms nconc: t]]. newStruct := PrologStructure functor: functor terms: newterms. ^self unify: termValue env: termEnv and: newStruct env: listEnv] ifFalse: ["disasemble a term into a list" termValue consp ifTrue: ["It's a list or a structure." list := termValue structureList] ifFalse: ["primitive data like symbol, number, nil, or string." list := termValue cons: nil]. ^self unify: list env: termEnv and: listVal env: listEnv]! userListing | predicateName | ((self associations: userPredicates) asSortedCollection) do: [:assoc | predicateName := assoc key. self userListing: predicateName]. ^true! userListing: aPrologSymbol | def | def := userPredicates at: aPrologSymbol ifAbsent: [nil]. def == nil ifTrue: [^false]. [def consp] whileTrue: [textCollector show: def car prettyPrintPrologString , '\' withCRs. def := def cdr]. ^true! userPredicates | collection list | collection := (self associations: userPredicates) asSortedCollection. list := nil. collection reverseDo: [:each | ((each key respondsTo: #string) and: [each key string isEmpty not and: [each key string first = $~]]) ifTrue: ['not adding: invisible predicate' yourself] ifFalse: [list := each key cons: list]]. ^list! verbose: aPrologSymbol aPrologSymbol isPrologTrue ifTrue: [verbose := true] ifFalse: [verbose := false]. ^true! write: anObject (anObject respondsTo: #asString) ifTrue: [textCollector show: anObject asString] ifFalse: [textCollector show: anObject printPrologString]. ^true! ! !PrologInterpreter methodsFor: 'system support'! clauseSet: aPrologClause | horn functor def | horn := aPrologClause. horn consp ifFalse: [horn := PrologStructure functor: horn terms: nil]. horn car consp ifFalse: [horn := PrologClause head: horn body: nil]. horn := PrologClause head: horn car body: (PrologBody fromList: horn cdr). functor := horn car car. def := userPredicates at: functor ifAbsent: [^false]. definitionStack := def cons: definitionStack. ^true! consult: readStream action: aBlock | condition parser node hornClause program functor stream result | condition := self getCondition. parser := PrologParser new. result := true. [node := parser parse: readStream. node == #eof] whileFalse: [hornClause := node. node isResolveClause ifTrue: [stream := WriteStream on: (String new: 20). hornClause printPrologOn: stream. textCollector show: stream contents. textCollector nl. result := self resolve: hornClause action: aBlock] ifFalse: [functor := hornClause car car. program := tracePredicates at: functor ifAbsent: [userPredicates at: functor ifAbsent: []]. program == nil ifTrue: [program := PrologDefinition fromList: (hornClause cons: nil). userPredicates at: functor put: program] ifFalse: [program nconc: (hornClause cons: nil)]]]. self putCondition: condition. ^result! reconsult: readStream action: aBlock | condition newPredicates parser node hornClause program functor stream result | condition := self getCondition. newPredicates := Dictionary new. parser := PrologParser new. result := true. [node := parser parse: readStream. node == #eof] whileFalse: [hornClause := node. node isResolveClause ifTrue: [stream := WriteStream on: (String new: 20). hornClause printPrologOn: stream. textCollector show: stream contents. textCollector nl. result := self resolve: hornClause action: aBlock] ifFalse: [functor := hornClause car car. program := newPredicates at: functor ifAbsent: []. program == nil ifTrue: [program := PrologDefinition fromList: (hornClause cons: nil). newPredicates at: functor put: program] ifFalse: [program nconc: (hornClause cons: nil)]. userPredicates at: functor put: program]]. newPredicates keys do: [:eachPredicate | userPredicates at: eachPredicate put: (newPredicates at: eachPredicate). tracePredicates removeKey: eachPredicate ifAbsent: []]. self putCondition: condition. ^result! saveFileName ^'prolog.db'! saveOn: fileName | aFileStream def | aFileStream := FileStream open: fileName asString mode: FileStream write. (self associations: userPredicates) asSortedCollection do: [:assoc | def := assoc value. [def consp] whileTrue: [aFileStream nextPutAll: def car prettyPrintPrologString , '\' withCRs. def := def cdr]]. aFileStream close! saveOn: fileName predicateName: aPrologSymbol | aFileStream def | aFileStream := FileStream open: fileName asString mode: FileStream write. def := userPredicates at: aPrologSymbol ifAbsent: []. def == nil ifFalse: [[def consp] whileTrue: [aFileStream nextPutAll: def car prettyPrintPrologString , '\' withCRs. def := def cdr]]. aFileStream close! systemConsult: readStream | condition parser node hornClause program functor | condition := self getCondition. parser := PrologParser new. [node := parser parse: readStream. node == #eof] whileFalse: [hornClause := node. node isResolveClause ifTrue: [self resolve: hornClause] ifFalse: [functor := hornClause car car. program := systemPredicates at: functor ifAbsent: []. program == nil ifTrue: [program := PrologDefinition fromList: (hornClause cons: nil). systemPredicates at: functor put: program] ifFalse: [program nconc: (hornClause cons: nil)]]]. self putCondition: condition. ^true! systemReconsult: readStream | condition newPredicates parser node hornClause program functor | condition := self getCondition. newPredicates := Dictionary new. parser := PrologParser new. [node := parser parse: readStream. node == #eof] whileFalse: [hornClause := node. node isResolveClause ifTrue: [self resolve: hornClause] ifFalse: [functor := hornClause car car. program := newPredicates at: functor ifAbsent: []. program == nil ifTrue: [program := PrologDefinition fromList: (hornClause cons: nil). newPredicates at: functor put: program] ifFalse: [program nconc: (hornClause cons: nil)]. systemPredicates at: functor put: program]]. newPredicates keys do: [:eachPredicate | systemPredicates at: eachPredicate put: (newPredicates at: eachPredicate)]. self putCondition: condition. ^true! trace: para head: head arguments: terms | headString numberString structure arguString | headString := (self expression: head env: clauseEnv) printPrologString. para = 0 ifTrue: [traceCounter := traceCounter + 1. numberString := String new: traceCounter withAll: $|. structure := PrologStructure functor: head car terms: terms. arguString := (self expression: structure env: clauseEnv) printPrologString. headString := headString , ' ~ ' , arguString. textCollector show: numberString , ' CALL : ' , headString , '\' withCRs. ^self]. para = 1 ifTrue: [traceCounter := traceCounter + 1. numberString := String new: traceCounter withAll: $|. structure := PrologStructure functor: head car terms: terms. arguString := (self expression: structure env: clauseEnv) printPrologString. headString := headString , ' ~ ' , arguString. textCollector show: numberString , ' REDO : ' , headString , '\' withCRs. ^self]. para = 2 ifTrue: [numberString := String new: traceCounter withAll: $|. textCollector show: numberString , ' FAIL : ' , headString , '\' withCRs. traceCounter := traceCounter - 1. ^self]. para = 3 ifTrue: [numberString := String new: traceCounter withAll: $|. textCollector show: numberString , ' EXIT : ' , headString , '\' withCRs. ^self]! traceCallClause: head ^self traceClause: head flag: 0! traceClause: head flag: anInteger | arguVar headStruct failStruct traceStruct | arguVar := PrologVariable install: 'Arguments'. headStruct := PrologStructure functor: head car terms: arguVar. failStruct := PrologStructure functor: (PrologSymbol install: 'fail') terms: nil. traceStruct := arguVar cons: nil. traceStruct := head cons: traceStruct. traceStruct := anInteger cons: traceStruct. traceStruct := traceStruct cons: nil. traceStruct := (PrologSymbol install: 'trace:head:arguments:') cons: traceStruct. traceStruct := (PrologSymbol install: 'self') cons: traceStruct. traceStruct := PrologTerms fromList: traceStruct. traceStruct := PrologStructure functor: (PrologSymbol install: 'send') terms: traceStruct. anInteger = 3 ifTrue: [^PrologClause head: headStruct body: (PrologBody fromList: (traceStruct cons: nil))]. ^PrologClause head: headStruct body: (PrologBody fromList: (traceStruct cons: (failStruct cons: nil)))! traceExitClause: exitClause | traceExitClause reverseClone| traceExitClause := self traceExitClauseAux: exitClause car. traceExitClause := traceExitClause cdr. reverseClone := exitClause reverse. [reverseClone consp] whileTrue: [traceExitClause := reverseClone car cons: traceExitClause. reverseClone := reverseClone cdr]. ^PrologClause head: traceExitClause car body: (PrologBody fromList: traceExitClause cdr)! traceExitClauseAux: head ^self traceClause: head flag: 3! traceFailClause: head ^self traceClause: head flag: 2! traceRedoClause: head ^self traceClause: head flag: 1! ! !PrologInterpreter methodsFor: 'unification'! unify: x env: xEnv and: y env: yEnv | xx yy assoc | xx := x. yy := y. [true] whileTrue: [xEnv == yEnv ifTrue: [x = y ifTrue: [^true]]. xx isPrologVariable ifTrue: [(assoc := self binding: xx env: xEnv) ~~ nil ifTrue: [valueEnv := xEnv. assoc := assoc cdr. xx := self fetchValue: assoc car env: assoc cdr. ^self unify: xx env: valueEnv and: yy env: yEnv] ifFalse: [yy isPrologVariable ifTrue: [(assoc := self binding: yy env: yEnv) ~~ nil ifTrue: [valueEnv := yEnv. assoc := assoc cdr. yy := self fetchValue: assoc car env: assoc cdr. ^self unify: xx env: xEnv and: yy env: valueEnv]]. self bind: xx env: xEnv and: yy env: yEnv. ^true]]. yy isPrologVariable ifTrue: [(assoc := self binding: yy env: yEnv) ~~ nil ifTrue: [valueEnv := yEnv. assoc := assoc cdr. yy := self fetchValue: assoc car env: assoc cdr. ^self unify: xx env: xEnv and: yy env: valueEnv]. self bind: yy env: yEnv and: xx env: xEnv. ^true]. xx consp ifFalse: [^xx = yy]. yy consp ifFalse: [^yy = xx]. (self unify: xx car env: xEnv and: yy car env: yEnv) ifFalse: [^false]. xx := xx cdr. yy := yy cdr]! ! smalltalk-3.2.5/examples/EditStream.st0000644000175000017500000001244212123404352014654 00000000000000"====================================================================== | | `Splitting' stream, useful for editors and the like. | | ======================================================================" "====================================================================== | | Written by Ulf Dambacher. | | This file is part of GNU Smalltalk. | | GNU Smalltalk is free software; you can redistribute it and/or modify it | under the terms of the GNU General Public License as published by the Free | Software Foundation; either version 2, or (at your option) any later version. | | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS | FOR A PARTICULAR PURPOSE. See the GNU General Public License for more | details. | | You should have received a copy of the GNU General Public License along with | GNU Smalltalk; see the file COPYING. If not, write to the Free Software | Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. | ======================================================================" Stream subclass: #EditorStream instanceVariableNames: 'head headEnd tail tailStart overwrite' classVariableNames: '' poolDictionaries: '' category: 'Examples-Useful tools' ! " headEnd points behind the last valid member of head. tailStart points to the first valid member of tail! " !EditorStream class methodsFor: 'all'! on: aString ^self new initOn: aString ! ! !EditorStream methodsFor: 'initializing'! initOn: aColl tail _ aColl. head _ aColl species new: 10. headEnd _ tailStart _ 1. overwrite _ false. ! insert overwrite _ false. ! overwrite overwrite _ true. ! ! !EditorStream methodsFor: 'positioning'! position ^headEnd ! position: anInt anInt < headEnd ifTrue: [ self copyHeadToTail: (headEnd - anInt) ] ifFalse:[ self copyTailToHead: (anInt - headEnd)] ! skip: anInt anInt < 0 ifTrue: [ self copyHeadToTail: anInt negated ] ifFalse:[ self copyTailToHead: anInt ] ! toEnd self copyTailToHead: tail size - tailStart + 1. ! toPos1 self copyHeadToTail: headEnd. ! ! !EditorStream methodsFor: 'access'! previous self skip: -1. ^ self peek ! next ^ (self next:1) at: 1. ! next: anInt | old | self atEnd ifTrue: [ self error: 'no object to next!']. old _ headEnd. self skip: anInt. ^ head copyFrom: old to: headEnd - 1 ! nextPut: anObject headEnd > head size ifTrue: [head grow]. head at: headEnd put: anObject. headEnd _ headEnd + 1. overwrite ifTrue: [ tailStart _ (tailStart min: tail size) + 1]. ! remove: anInt anInt < 0 ifTrue: [ headEnd _ headEnd + anInt max: 1 ] ifFalse: [ tailStart _ tailStart + anInt min: tail size +1 ]. ! peek self atEnd ifTrue: [self error: 'no object to peek!']. ^tail at: tailStart ! ! !EditorStream methodsFor: 'testing'! atEnd ^ tailStart > tail size ! ! !EditorStream methodsFor: 'contents access'! head ^ head copyFrom: 1 to: headEnd - 1 ! tail ^ tail copyFrom: tailStart to: tail size ! contents ^ self head , self tail ! size " ^self contents size" ^ headEnd "- 1 " + tail size - tailStart " + 1 ". ! ! !EditorStream methodsFor: 'collection like access'! at: anInt ^self at: anInt ifAbsent: [ ^self error: 'index out of range']. ! at: anInt ifAbsent: aBlock (anInt between: 1 and: self size) ifFalse: [^aBlock value]. anInt < headEnd ifTrue: [ ^head at: anInt ] ifFalse: [ ^ tail at: (anInt - headEnd + tailStart)] ! inject: aValue into: aBlock 1 to: self size do: [ :i | aValue _ aBlock value: aValue value: (self at: i)]. ^aValue ! ! !EditorStream methodsFor: 'private'! " oldcopyHeadToTail: anInt [ (tailStart > 1 and: [headEnd > 1]) and: [anInt > 0]] whileTrue: [ tailStart _ tailStart - 1. headEnd _ headEnd - 1. tail at: tailStart put: (head at: headEnd). anInt _ anInt - 1]. anInt > 0 ifTrue: [ tail _ (head copyFrom: (headEnd - anInt max: 1) to: headEnd - 1),tail. headEnd _ headEnd - anInt max: 1] ! oldcopyTailToHead: anInt [ tailStart <= tail size and: [anInt > 0]] whileTrue: [ headEnd > head size ifTrue: [head grow]. head at: headEnd put: (tail at: tailStart). tailStart _ tailStart +1. headEnd _ headEnd + 1. anInt _ anInt - 1 ]. ! " copyHeadToTail: anInt | coll i j | anInt _ anInt min: headEnd - 1. tailStart <= anInt ifTrue: [ i _ anInt + 10. " 10 more spaces... " j _ tail size - tailStart + 1. coll _ tail species new: i + j. coll replaceFrom: i + 1 to: i + j with: tail startingAt: tailStart. tail _ coll. tailStart _ i + 1]. tail replaceFrom: tailStart - anInt to: tailStart - 1 with: head startingAt: headEnd - anInt. headEnd _ headEnd - anInt. tailStart _ tailStart - anInt. ! copyTailToHead: anInt | coll i | anInt _ anInt min: tail size - tailStart + 1. headEnd + anInt > head size ifTrue: [ i _ anInt + 10. coll _ head species new: i + headEnd - 1. coll replaceFrom: 1 to: headEnd - 1 with: head startingAt: 1. head _ coll ]. head replaceFrom: headEnd to: headEnd - 1 + anInt with: tail startingAt: tailStart. tailStart _ tailStart + anInt. headEnd _ headEnd + anInt. ! ! smalltalk-3.2.5/examples/Methods.st0000644000175000017500000001713412123404352014221 00000000000000"====================================================================== | | Examples of CompiledMethod subclasses | | ======================================================================" "====================================================================== | | Copyright 2006, 2007 Free Software Foundation, Inc. | Written by Paolo Bonzini. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" "Inspired by example code from idst-5.7, by Ian Piumarta" CompiledMethod subclass: #InterpretedMethod instanceVariableNames: 'bytecodes' classVariableNames: '' poolDictionaries: '' category: 'Examples-VM'! !InterpretedMethod class methodsFor: 'testing'! test "InterpretedMethod test" | b | b := Behavior new. b superclass: Object. b interpretedMethodAt: #testInterp1 put: #(#push 3 #push 4 #add #return). b interpretedMethodAt: #testInterp2 put: #(#push 6 #push 7 #mul #return). Transcript show: '3 + 4 = '. b new testInterp1 printNl. Transcript show: '6 * 7 = '. b new testInterp2 printNl. b interpretedMethodAt: #testInterp1 put: #(#push 3 #push 4 #mul #return). b interpretedMethodAt: #testInterp2 put: #(#push 6 #push 7 #add #return). Transcript show: '3 * 4 = '. b new testInterp1 printNl. Transcript show: '6 + 7 = '. b new testInterp2 printNl! !InterpretedMethod class methodsFor: 'instance creation'! numArgs: args bytecodes: bc ^(self numArgs: args) bytecodes: bc; yourself! ! !InterpretedMethod methodsFor: 'executing'! bytecodes: anArray bytecodes := anArray! valueWithReceiver: rec withArguments: args | stack pc insn a b | pc := 0. stack := OrderedCollection new. stack addLast: rec. stack addAllLast: args. [ insn := bytecodes at: (pc := pc + 1). insn == #push ifTrue: [ stack addLast: (bytecodes at: (pc := pc + 1)) ]. insn == #add ifTrue: [ a := stack removeLast. b := stack removeLast. stack addLast: a + b ]. insn == #mul ifTrue: [ a := stack removeLast. b := stack removeLast. stack addLast: a * b ]. insn == #return ifTrue: [^stack last] ] repeat! ! !Behavior methodsFor: 'methods'! interpretedMethodAt: aSelector put: bytecodes ^self addSelector: aSelector withMethod: (InterpretedMethod numArgs: aSelector numArgs bytecodes: bytecodes) ! ! CompiledMethod subclass: #ForwardingMethod instanceVariableNames: 'destClass destSelector' classVariableNames: '' poolDictionaries: '' category: 'Examples-VM'! !ForwardingMethod class methodsFor: 'testing'! test | foo bar | foo := Behavior new. foo superclass: Object. foo compile: 'one: a [ (''foo one'' -> a) printNl ]'. foo compile: 'two: a [ (''foo two'' -> a) printNl. self one: a ]'. bar := Behavior new. bar superclass: Object. bar compile: 'one: a [ (''bar one'' -> a) printNl ]'. bar addSelector: #two: withMethod: (ForwardingMethod to: foo -> #two:). foo new two: 1. bar new two: 2! ! !ForwardingMethod class methodsFor: 'instance creation'! to: anAssociation ^(self numArgs: anAssociation value numArgs) destClass: anAssociation key; destSelector: anAssociation value; yourself! !ForwardingMethod methodsFor: 'forwarding'! destClass ^destClass! destSelector ^destSelector! destClass: anObject destClass := anObject! destSelector: aSymbol destSelector := aSymbol! valueWithReceiver: rec withArguments: args | method | method := destClass lookupSelector: destSelector. ^method isNil ifTrue: [ rec doesNotUnderstand: (Message selector: self selector arguments: args) ] ifFalse: [ rec perform: method withArguments: args ]! ! CompiledMethod subclass: #MethodWrapper instanceVariableNames: 'method methodClass selector' classVariableNames: 'WrapperList' poolDictionaries: '' category: 'Examples-VM'! !MethodWrapper class methodsFor: 'testing'! readdWrappersAfter: aWrapper | all index toAdd | all := self wrappersFor: aWrapper basicMethod. index := all identityIndexOf: aWrapper. toAdd := all copyFrom: index + 1. all empty. toAdd do: [ :each | each install ] ! recordWrapper: aWrapper (self wrappersFor: aWrapper basicMethod) addLast: aWrapper ! wrappersFor: aMethod WrapperList isNil ifTrue: [ WrapperList := IdentityDictionary new ]. ^WrapperList at: aMethod ifAbsentPut: [ OrderedCollection new ] ! ! !MethodWrapper methodsFor: 'wrapping'! beforeMethod ! afterMethod ! valueWithReceiver: rec withArguments: args self beforeMethod. ^[ rec perform: method withArguments: args ] ensure: [ self afterMethod ] ! ! !CompiledCode methodsFor: 'installing'! basicMethod ^self ! ! !MethodWrapper methodsFor: 'installing'! basicMethod ^method basicMethod ! install method := self methodClass lookupSelector: selector. method isNil ifTrue: [ self error: 'cannot find method' ]. self methodClass methodDictionary at: selector put: self. self class recordWrapper: self. ! uninstall method methodClass == self methodClass ifTrue: [ self methodDictionary at: selector put: method ] ifFalse: [ self methodDictionary removeKey: selector ifAbsent: [] ]. self class readdWrappersAfter: self. method := nil. ! isInstalled ^method notNil ! methodClass ^methodClass ! methodDictionary ^methodClass methodDictionary ! methodClass: aClass methodClass := aClass ! selector: aSymbol selector := aSymbol ! ! !MethodWrapper class methodsFor: 'instance creation'! on: aSymbol in: aClass ^(self numArgs: aSymbol numArgs) selector: aSymbol; methodClass: aClass; yourself! ! MethodWrapper subclass: #WrapperExample instanceVariableNames: 'text' classVariableNames: 'WrapperList' poolDictionaries: '' category: 'Examples-VM'! !WrapperExample class methodsFor: 'installing'! test | a b | a := WrapperExample on: #asArray in: String. b := WrapperExample on: #asArray in: String. (a isInstalled->b isInstalled) printNl. (String includesSelector: #asArray) printNl. a install: 'wrapper1'. (a isInstalled->b isInstalled) printNl. (String includesSelector: #asArray) printNl. 'abc' asArray. b install: 'wrapper2'. (a isInstalled->b isInstalled) printNl. (String includesSelector: #asArray) printNl. 'abc' asArray. a uninstall. (a isInstalled->b isInstalled) printNl. (String includesSelector: #asArray) printNl. 'abc' asArray. b uninstall. (a isInstalled->b isInstalled) printNl. (String includesSelector: #asArray) printNl. 'abc' asArray. ! ! !WrapperExample methodsFor: 'installing'! install: aString text := aString. self install ! beforeMethod ('before ', text) printNl ! afterMethod ('after ', text) printNl ! ! InterpretedMethod test! ForwardingMethod test! WrapperExample test! smalltalk-3.2.5/examples/Tokenizer.st0000644000175000017500000000566012123404352014571 00000000000000"====================================================================== | | Generic tokenizer superclass. | | ======================================================================" "====================================================================== | | Copyright 1999, 2000, 2001 Free Software Foundation, Inc. | Written by Paolo Bonzini. | | This file is part of GNU Smalltalk. | | GNU Smalltalk is free software; you can redistribute it and/or modify it | under the terms of the GNU General Public License as published by the Free | Software Foundation; either version 2, or (at your option) any later version. | | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS | FOR A PARTICULAR PURPOSE. See the GNU General Public License for more | details. | | You should have received a copy of the GNU General Public License along with | GNU Smalltalk; see the file COPYING. If not, write to the Free Software | Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. | ======================================================================" FileStream fileIn: Directory kernel, '/../examples/PushBack.st'! Stream subclass: #Tokenizer instanceVariableNames: 'stream line' classVariableNames: 'CR LF' poolDictionaries: '' category: 'Examples-Useful'! !Tokenizer class methodsFor: 'initialization'! initialize CR := Character cr. LF := Character nl ! !Tokenizer class methodsFor: 'instance creation'! on: aFileName ^self new init: (FileStream open: aFileName mode: 'r') ! onStream: aStream ^self new init: aStream ! ! !Tokenizer methodsFor: 'accessing'! isFileStream ^self stream isKindOf: FileStream ! stream ^stream stream ! ! !Tokenizer methodsFor: 'stream compatibility'! position ^stream position ! close stream close ! nextPut: notUsed self shouldNotImplement ! next | ch tok | [ stream atEnd ifTrue: [ ^self atEndToken ]. ch := self nextChar. tok := self tokenize: ch. tok isNil ] whileTrue: [ ]. ^tok ! atEnd ^stream atEnd ! close stream close ! ! !Tokenizer methodsFor: 'parsing tokens'! atEndToken ^nil ! tokenize: ch "This must answer a token. The tokens' starting char is passed in ch" self subclassResponsibility ! ! !Tokenizer methodsFor: 'utility methods'! line ^line ! peekChar ^stream peek ! peekChar: aChar | next | (next := stream next) == aChar ifTrue: [ ^true ]. stream putBack: next. ^false ! putBack: aChar stream putBack: aChar. ! ! !Tokenizer methodsFor: 'recording'! nextChar | c | c := stream next. c == CR ifTrue: [ line := line + 1. stream peekFor: LF ]. c == LF ifTrue: [ line := line + 1 ]. ^c ! ! !Tokenizer methodsFor: 'private'! init: aStream stream := PushBackStream on: aStream. line := 1. ! ! Tokenizer initialize! smalltalk-3.2.5/examples/Richards.st0000644000175000017500000004132312123404352014352 00000000000000"====================================================================== | | The Richards Benchmark in Smalltalk | | ======================================================================" "====================================================================== | | Copyright 2000 Free Software Foundation, Inc. | | This file is part of GNU Smalltalk. | | GNU Smalltalk is free software; you can redistribute it and/or modify it | under the terms of the GNU General Public License as published by the Free | Software Foundation; either version 2, or (at your option) any later version. | | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS | FOR A PARTICULAR PURPOSE. See the GNU General Public License for more | details. | | You should have received a copy of the GNU General Public License along with | GNU Smalltalk; see the file COPYING. If not, write to the Free Software | Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. | ======================================================================" Object subclass: #RBObject instanceVariableNames: '' classVariableNames: 'DeviceA DeviceB DevicePacketKind HandlerA HandlerB Idler Worker WorkPacketKind ' poolDictionaries: '' category: 'Examples-Richards'! RBObject subclass: #Packet instanceVariableNames: 'link identity kind datum data ' classVariableNames: '' poolDictionaries: '' category: 'Examples-Richards'! RBObject subclass: #RichardsBenchmark instanceVariableNames: 'taskList currentTask currentTaskIdentity taskTable tracing layout queuePacketCount holdCount ' classVariableNames: '' poolDictionaries: '' category: 'Examples-Richards'! RBObject subclass: #TaskState instanceVariableNames: 'packetPendingIV taskWaiting taskHolding ' classVariableNames: '' poolDictionaries: '' category: 'Examples-Richards'! RBObject subclass: #DeviceTaskDataRecord instanceVariableNames: 'pending ' classVariableNames: '' poolDictionaries: '' category: 'Examples-Richards'! RBObject subclass: #HandlerTaskDataRecord instanceVariableNames: 'workIn deviceIn ' classVariableNames: '' poolDictionaries: '' category: 'Examples-Richards'! RBObject subclass: #WorkerTaskDataRecord instanceVariableNames: 'destination count ' classVariableNames: '' poolDictionaries: '' category: 'Examples-Richards'! TaskState subclass: #TaskControlBlock instanceVariableNames: 'link identity priority input state function handle ' classVariableNames: '' poolDictionaries: '' category: 'Examples-Richards'! RBObject subclass: #IdleTaskDataRecord instanceVariableNames: 'control count ' classVariableNames: '' poolDictionaries: '' category: 'Examples-Richards'! !RBObject methodsFor: 'utilities'! append: packet head: queueHead | mouse link | packet link: nil. queueHead isNil ifTrue: [^packet]. mouse := queueHead. [(link := mouse link) isNil] whileFalse: [mouse := link]. mouse link: packet. ^queueHead! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! RBObject class instanceVariableNames: ''! !RBObject class methodsFor: 'initialize'! initialize "RBObject initialize" DeviceA := 5. DeviceB := 6. DevicePacketKind := 1. HandlerA := 3. HandlerB := 4. Idler := 1. Worker := 2. WorkPacketKind := 2! ! RBObject initialize! !Packet methodsFor: 'initialize'! link: aLink identity: anIdentity kind: aKind link := aLink. identity := anIdentity. kind := aKind. datum := 1. data := ByteArray new: 4! ! !Packet methodsFor: 'accessing'! data ^data! datum ^datum! datum: someData datum := someData! identity ^identity! identity: anIdentity identity := anIdentity! kind ^kind! link ^link! link: aWorkQueue link := aWorkQueue! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! Packet class instanceVariableNames: ''! !Packet class methodsFor: 'instance creation'! create: link identity: identity kind: kind ^super new link: link identity: identity kind: kind! ! !RichardsBenchmark methodsFor: 'creation'! createDevice: identity priority: priority work: work state: state | data | data := DeviceTaskDataRecord create. self createTask: identity priority: priority work: work state: state function: [:work :word | | data functionWork | data := word. functionWork := work. functionWork isNil ifTrue: [(functionWork := data pending) isNil ifTrue: [self wait] ifFalse: [data pending: nil. self queuePacket: functionWork]] ifFalse: [data pending: functionWork. tracing ifTrue: [self trace: functionWork datum]. self holdSelf]] data: data! createHandler: identity priority: priority work: work state: state | data | data := HandlerTaskDataRecord create. self createTask: identity priority: priority work: work state: state function: [:work :word | | data workPacket count devicePacket | data := word. work isNil ifFalse: [WorkPacketKind == work kind ifTrue: [data workInAdd: work] ifFalse: [data deviceInAdd: work]]. (workPacket := data workIn) isNil ifTrue: [self wait] ifFalse: [count := workPacket datum. count > 4 ifTrue: [data workIn: workPacket link. self queuePacket: workPacket] ifFalse: [(devicePacket := data deviceIn) isNil ifTrue: [self wait] ifFalse: [data deviceIn: devicePacket link. devicePacket datum: (workPacket data at: count). workPacket datum: count + 1. self queuePacket: devicePacket]]]] data: data! createIdler: identity priority: priority work: work state: state | data | data := IdleTaskDataRecord create. self createTask: identity priority: priority work: work state: state function: [:work :word | | data | data := word. data count: data count - 1. 0 = data count ifTrue: [self holdSelf] ifFalse: [0 = (data control bitAnd: 1) ifTrue: [data control: data control // 2. self release: DeviceA] ifFalse: [data control: (data control // 2 bitXor: 53256). self release: DeviceB]]] data: data! createPacket: link identity: identity kind: kind ^Packet create: link identity: identity kind: kind! createTask: identity priority: priority work: work state: state function: aBlock data: data | t | t := TaskControlBlock link: taskList create: identity priority: priority initialWorkQueue: work initialState: state function: aBlock privateData: data. taskList := t. taskTable at: identity put: t! createWorker: identity priority: priority work: work state: state | data | data := WorkerTaskDataRecord create. self createTask: identity priority: priority work: work state: state function: [:work :word | | data | data := word. work isNil ifTrue: [self wait] ifFalse: [data destination: (HandlerA = data destination ifTrue: [HandlerB] ifFalse: [HandlerA]). work identity: data destination. work datum: 1. 1 to: 4 do: [:i | data count: data count + 1. data count > 26 ifTrue: [data count: 1]. work data at: i put: $A asInteger + data count - 1]. self queuePacket: work]] data: data! ! !RichardsBenchmark methodsFor: 'private'! findTask: identity | t | t := taskTable at: identity. t isNil ifTrue: [self error: 'findTask failed']. ^t! holdSelf holdCount := holdCount + 1. currentTask taskHolding: true. ^currentTask link! initScheduler queuePacketCount := holdCount := 0. taskTable := Array new: 6. taskList := nil! initTrace: trace tracing := trace. layout := 0! queuePacket: packet | t | t := self findTask: packet identity. t isNil ifTrue: [^nil]. queuePacketCount := queuePacketCount + 1. packet link: nil. packet identity: currentTaskIdentity. ^t addInput: packet checkPriority: currentTask! release: identity | t | t := self findTask: identity. t isNil ifTrue: [^nil]. t taskHolding: false. t priority > currentTask priority ifTrue: [^t] ifFalse: [^currentTask]! trace: id layout := layout - 1. 0 >= layout ifTrue: [Transcript cr. layout := 50]. Transcript show: id printString! wait currentTask taskWaiting: true. ^currentTask! ! !RichardsBenchmark methodsFor: 'scheduling'! schedule currentTask := taskList. [currentTask isNil] whileFalse: [currentTask isTaskHoldingOrWaiting ifTrue: [currentTask := currentTask link] ifFalse: [currentTaskIdentity := currentTask identity. tracing ifTrue: [self trace: currentTaskIdentity]. currentTask := currentTask runTask]]! ! !RichardsBenchmark methodsFor: 'initialize'! start ^self start: false ! start: trace | workQ mark1 mark2 mark3 mark4 | self initTrace: trace; initScheduler. mark1 := Time millisecondClockValue. tracing ifTrue: [Transcript show: 'Bench mark starting'; cr]. self createIdler: Idler priority: 0 work: nil state: TaskState running. workQ := self createPacket: nil identity: Worker kind: WorkPacketKind. workQ := self createPacket: workQ identity: Worker kind: WorkPacketKind. self createWorker: Worker priority: 1000 work: workQ state: TaskState waitingWithPacket. workQ := self createPacket: nil identity: DeviceA kind: DevicePacketKind. workQ := self createPacket: workQ identity: DeviceA kind: DevicePacketKind. workQ := self createPacket: workQ identity: DeviceA kind: DevicePacketKind. self createHandler: HandlerA priority: 2000 work: workQ state: TaskState waitingWithPacket. workQ := self createPacket: nil identity: DeviceB kind: DevicePacketKind. workQ := self createPacket: workQ identity: DeviceB kind: DevicePacketKind. workQ := self createPacket: workQ identity: DeviceB kind: DevicePacketKind. self createHandler: HandlerB priority: 3000 work: workQ state: TaskState waitingWithPacket. self createDevice: DeviceA priority: 4000 work: nil state: TaskState waiting. self createDevice: DeviceB priority: 5000 work: nil state: TaskState waiting. tracing ifTrue: [Transcript show: 'Starting'; cr]. mark2 := Time millisecondClockValue. self schedule. mark3 := Time millisecondClockValue. tracing ifTrue: [Transcript show: 'Finished'; cr. Transcript show: 'QueuePacket count = ' ; show: queuePacketCount printString; show: ' HoldCount = '; show: holdCount printString; cr. Transcript cr; show: 'End of run'; cr]. queuePacketCount = 23246 & (holdCount = 9297) ifFalse: [self error: 'wrong result']. mark4 := Time millisecondClockValue. tracing ifTrue: [Transcript show: '***Scheduler time = '; show: (mark3 - mark2) printString; show: ' Total time = '; show: (mark4 - mark1) printString; cr]. ^mark3 - mark2! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! RichardsBenchmark class instanceVariableNames: ''! !RichardsBenchmark class methodsFor: 'instance creation'! report: string times: count run: aBlock "Report the time required to execute the given block." | time | time := 0. count timesRepeat: [ time := time + aBlock value ]. Transcript show: string, ' ', (time // count) printString, ' milliseconds'; cr.! standardBenchmark "This the combined benchmark." "Planner standardBenchmark" self report: 'Richards simulations' times: 100 run: [ self start ]! start: trace "RichardsBenchmark start: true" ^self new start: trace! start "RichardsBenchmark start" ^self new start! ! !TaskState methodsFor: 'initialize'! packetPending packetPendingIV := true. taskWaiting := false. taskHolding := false! running packetPendingIV := taskWaiting := taskHolding := false! waiting packetPendingIV := taskHolding := false. taskWaiting := true! waitingWithPacket taskHolding := false. taskWaiting := packetPendingIV := true! ! !TaskState methodsFor: 'accessing'! isPacketPending ^packetPendingIV! isTaskHolding ^taskHolding! isTaskWaiting ^taskWaiting! taskHolding: aBoolean taskHolding := aBoolean! taskWaiting: aBoolean taskWaiting := aBoolean! ! !TaskState methodsFor: 'testing'! isRunning ^packetPendingIV not and: [taskWaiting not and: [taskHolding not]]! isTaskHoldingOrWaiting ^taskHolding or: [packetPendingIV not and: [taskWaiting]]! isWaiting ^packetPendingIV not and: [taskWaiting and: [taskHolding not]]! isWaitingWithPacket ^packetPendingIV and: [taskWaiting and: [taskHolding not]]! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! TaskState class instanceVariableNames: ''! !TaskState class methodsFor: 'instance creation'! packetPending ^super new packetPending! running ^super new running! waiting ^super new waiting! waitingWithPacket ^super new waitingWithPacket! ! !DeviceTaskDataRecord methodsFor: 'initialize'! create pending := nil! ! !DeviceTaskDataRecord methodsFor: 'accessing'! pending ^pending! pending: packet pending := packet! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! DeviceTaskDataRecord class instanceVariableNames: ''! !DeviceTaskDataRecord class methodsFor: 'instance creation'! create ^super new create! ! !HandlerTaskDataRecord methodsFor: 'initialize'! create workIn := deviceIn := nil! ! !HandlerTaskDataRecord methodsFor: 'accessing'! deviceIn ^deviceIn! deviceIn: aPacket deviceIn := aPacket! deviceInAdd: packet deviceIn := self append: packet head: deviceIn! workIn ^workIn! workIn: aWorkQueue workIn := aWorkQueue! workInAdd: packet workIn := self append: packet head: workIn! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! HandlerTaskDataRecord class instanceVariableNames: ''! !HandlerTaskDataRecord class methodsFor: 'instance creation'! create ^super new create! ! !WorkerTaskDataRecord methodsFor: 'initialize'! create destination := HandlerA. count := 0! ! !WorkerTaskDataRecord methodsFor: 'accessing'! count ^count! count: aCount count := aCount! destination ^destination! destination: aHandler destination := aHandler! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! WorkerTaskDataRecord class instanceVariableNames: ''! !WorkerTaskDataRecord class methodsFor: 'instance creation'! create ^super new create! ! !TaskControlBlock methodsFor: 'initialize'! link: aLink identity: anIdentity priority: aPriority initialWorkQueue: anInitialWorkQueue initialState: anInitialState function: aBlock privateData: aPrivateData link := aLink. identity := anIdentity. priority := aPriority. input := anInitialWorkQueue. packetPendingIV := anInitialState isPacketPending. taskWaiting := anInitialState isTaskWaiting. taskHolding := anInitialState isTaskHolding. function := aBlock. handle := aPrivateData! ! !TaskControlBlock methodsFor: 'accessing'! identity ^identity! link ^link! priority ^priority! ! !TaskControlBlock methodsFor: 'scheduling'! addInput: packet checkPriority: oldTask input isNil ifTrue: [input := packet. packetPendingIV := true. priority > oldTask priority ifTrue: [^self]] ifFalse: [input := self append: packet head: input]. ^oldTask! runTask | message | self isWaitingWithPacket ifTrue: [message := input. input := message link. input isNil ifTrue: [self running] ifFalse: [self packetPending]] ifFalse: [message := nil]. ^function value: message value: handle! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! TaskControlBlock class instanceVariableNames: ''! !TaskControlBlock class methodsFor: 'instance creation'! link: link create: identity priority: priority initialWorkQueue: initialWorkQueue initialState: initialState function: aBlock privateData: privateData ^super new link: link identity: identity priority: priority initialWorkQueue: initialWorkQueue initialState: initialState function: aBlock privateData: privateData! ! !IdleTaskDataRecord methodsFor: 'initialize'! create control := 1. count := 10000! ! !IdleTaskDataRecord methodsFor: 'accessing'! control ^control! control: aNumber control := aNumber! count ^count! count: aCount count := aCount! ! "-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "! IdleTaskDataRecord class instanceVariableNames: ''! !IdleTaskDataRecord class methodsFor: 'instance creation'! create ^super new create! ! smalltalk-3.2.5/examples/Dinner.st0000644000175000017500000000566512123404352014043 00000000000000"====================================================================== | | Smalltalk dining philosophers | | ======================================================================" "====================================================================== | | Copyright 1999, 2000 Free Software Foundation, Inc. | Written by Paolo Bonzini. | | This file is part of GNU Smalltalk. | | GNU Smalltalk is free software; you can redistribute it and/or modify it | under the terms of the GNU General Public License as published by the Free | Software Foundation; either version 2, or (at your option) any later version. | | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS | FOR A PARTICULAR PURPOSE. See the GNU General Public License for more | details. | | You should have received a copy of the GNU General Public License along with | GNU Smalltalk; see the file COPYING. If not, write to the Free Software | Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. | ======================================================================" Object subclass: #Philosophers instanceVariableNames: 'forks philosophers randy eating' classVariableNames: '' poolDictionaries: '' category: 'Examples-Processes'! !Philosophers class methodsFor: 'dining'! new self shouldNotImplement ! new: quantity ^super new initialize: quantity ! ! !Philosophers methodsFor: 'dining'! dine self dine: 15 ! dine: seconds (Delay forSeconds: seconds) wait. philosophers do: [ :each | each terminate ]. self initialize: self size ! leftFork: n ^forks at: n ! rightFork: n ^n = self size ifTrue: [ forks at: 1 ] ifFalse: [ forks at: n + 1 ] ! initialize: n eating := Semaphore new. n - 1 timesRepeat: [ eating signal ]. randy := Random new. forks := (1 to: n) collect: [ :each | Semaphore forMutualExclusion ]. philosophers := (1 to: n) collect: [ :each | self philosopher: each ]. ! philosopher: n | philosopherCode leftFork rightFork status | leftFork := self leftFork: n. rightFork := self rightFork: n. status := 'Philosopher #', n printString, ' '. philosopherCode := [[ true ] whileTrue: [ Transcript nextPutAll: status, 'thinks'; nl. (Delay forMilliseconds: randy next * 2000) wait. Transcript nextPutAll: status, 'wants to eat'; nl. eating critical: [ "Avoid deadlock" Transcript nextPutAll: status, 'waits for left fork'; nl. leftFork wait. Transcript nextPutAll: status, 'waits for right fork'; nl. rightFork wait. Transcript nextPutAll: status, 'eats'; nl. (Delay forMilliseconds: randy next * 2000) wait. leftFork signal. rightFork signal. ]. ]]. ^(philosopherCode newProcess) priority: Processor userBackgroundPriority; name: status; resume; yourself ! size ^forks size ! ! (Philosophers new: 5) dine! smalltalk-3.2.5/examples/RegExp.st0000644000175000017500000002473512123404352014015 00000000000000"====================================================================== | | Regular expressions | | ======================================================================" "====================================================================== | | Copyright 1999 Free Software Foundation, Inc. | Written by Paolo Bonzini. | | This file is part of GNU Smalltalk. | | GNU Smalltalk is free software; you can redistribute it and/or modify it | under the terms of the GNU General Public License as published by the Free | Software Foundation; either version 2, or (at your option) any later version. | | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS | FOR A PARTICULAR PURPOSE. See the GNU General Public License for more | details. | | You should have received a copy of the GNU General Public License along with | GNU Smalltalk; see the file COPYING. If not, write to the Free Software | Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. | ======================================================================" Object subclass: #RegularExpression instanceVariableNames: 'selectors params noDollar string' classVariableNames: '' poolDictionaries: '' category: 'Examples-Useful'! !RegularExpression class methodsFor: 'instance creation'! new self shouldNotImplement ! fromString: aString ^super new parseString: aString ! ! !RegularExpression class methodsFor: 'parsing'! match: aString to: regExp ^(self fromString: regExp) match: aString ! ! !RegularExpression methodsFor: 'parsing'! match: aString ^self matchStream: (ReadStream on: aString) from: 1 ! matchStream: aStream ^self matchStream: aStream from: 1 ! ! !RegularExpression methodsFor: 'private'! parseString: aString "Private - Convert a regular expression to its internal representation" | regexp endPos | params := OrderedCollection new. selectors := OrderedCollection new. "Zero-length aString is a special case" aString size = 0 ifTrue: [ noDollar := true. self addDotAsterisk. ^self ]. regexp := ReadStream on: aString. noDollar := aString last ~= $$. (regexp peekFor: $^) ifFalse: [ self addDotAsterisk ] endPos := noDollar ifTrue: [ aString size ] ifFalse: [ aString size - 1 ]. [ regexp position > endPos ] whileFalse: [ self parseAtom: regexp ] ! addDotAsterisk "Add an implicit .* sequence" params addLast: nil. selectors addLast: #wild0any:index: ! parseAtom: regexp "Private - Parse an 'atom' of the regular expression. Add to selectors the selector to be called to match it, and add to params the first parameter that will be passed to this selector" | next | (next := regexp next) = $\ ifTrue: [ params addLast: regexp next. ^selectors addLast: #char:index: ]. (next = $+) & selectors notEmpty ifTrue: [ ^selectors at: selectors size put: ('wild1', selectors last) asSymbol ]. (next = $*) & selectors notEmpty ifTrue: [ ^selectors at: selectors size put: ('wild0', selectors last) asSymbol ]. next = $. ifTrue: [ params addLast: nil. ^selectors addLast: #any:index: ]. next = $[ ifTrue: [ (regexp peekFor: $^) ifTrue: [ selectors addLast: #notRange:index: ] ifFalse: [ selectors addLast: #range:index: ]. params addLast: (self parseRange: regexp). ^selectors last ]. next = ${ ifTrue: [ params addLast: (self parseOptional: regexp). ^selectors addLast: #optional:index: ]. params addLast: next. ^selectors addLast: #char:index: ! parseRange: regexp "Private - Parse a 'range atom', that is an atom that can match to seve- ral characters." | next answerStream | answerStream := WriteStream on: (String new: 8). "Number out of a hat" [ (next := regexp next) = $] ] whileFalse: [ answerStream nextPut: next. regexp atEnd ifTrue: [ self errorBadRegexp ]. (regexp peekFor: $-) ifTrue: [ regexp atEnd ifTrue: [ self errorBadRegexp ]. next asciiValue + 1 to: regexp next asciiValue do: [:i | answerStream nextPut: i asCharacter ] ] ]. ^answerStream contents! parseOptional: regexp "Private - Parse an 'optional atom', that is an atom that can match to several regular expressions." | pos next result | pos := regexp position. result := OrderedCollection new. [ (next := regexp next) = $\ ifTrue: [regexp next] ifFalse: [ next = $| ifTrue: [ result addLast: (self class fromString: '^', (regexp copyFrom: pos to: regexp position - 2)). pos := regexp position ]. next = $} ifTrue: [ result addLast: (self class fromString: '^', (regexp copyFrom: pos to: regexp position - 2)). ^result ] ]. regexp atEnd ] whileFalse: [ ]. "If we come here, we have found no } : bad regular expression" self errorBadRegexp ! errorBadRegexp "Seems like we had some problems parsing the regular expression" self error: 'Bad regular expression' ! char: aCharacter index: dummy "Private - Check if the next character matchs to aCharacter" ^string atEnd ifTrue: [ false ] ifFalse: [ aCharacter = string next ] ! any: dummy index: dummy2 "Private - If we aren't at the end of the stream, skip a character, else answer false" ^string atEnd ifTrue: [ false ] ifFalse: [ string next. true ] ! range: aString index: dummy "Private - Check if the next character is included in aString" ^string atEnd ifTrue: [ false ] ifFalse: [ aString includes: string next ] ! notRange: aString index: dummy "Private - Check if the next character is not included in aString" ^string atEnd ifTrue: [ false] ifFalse: [ (aString includes: string next) not ] ! optional: listOfRegexp index: dummy "Private - Check if the next characters match to any of the RegularExpression objects in listOfRegexp" | pos | string atEnd ifTrue: [^false]. pos := string position. listOfRegexp do: [ :re | (re matchStream: string from: 1) ifTrue: [^true]. string position: pos. ]. ^false ! wild0any: atLeast1 index: index "Private - Match a .* sequence" ^self matchWild: #any:index: with: nil following: [ self matchStream: string from: index + 1 ] ! wild1any: atLeast1 index: index "Private - Match a .+ sequence" (self any: nil index: index) ifFalse: [^false]. ^self matchWild: #any:index: with: nil following: [ self matchStream: string from: index + 1 ] ! wild0range: aString index: index "Private - Match a [...]* sequence" ^self matchWild: #range:index: with: aString following: [ self matchStream: string from: index + 1 ] ! wild1range: aString index: index "Private - Match a [...]+ sequence" (self range: aString index: index) ifFalse: [^false]. ^self matchWild: #range:index: with: aString following: [ self matchStream: string from: index + 1 ] ! wild0notRange: aString index: index "Private - Match a [...]* sequence" ^self matchWild: #notRange:index: with: aString following: [ self matchStream: string from: index + 1 ] ! wild1notRange: aString index: index "Private - Match a [...]+ sequence" (self notRange: aString index: index) ifFalse: [^false]. ^self matchWild: #notRange:index: with: aString following: [ self matchStream: string from: index + 1 ] ! wild0char: aCharacter index: index "Private - Match a x* sequence" ^self matchWild: #char:index: with: aCharacter following: [ self matchStream: string from: index + 1 ] ! wild1char: aCharacter index: index "Private - Match a x+ sequence" (self char: aCharacter index: index) ifFalse: [^false]. ^self matchWild: #char:index: with: aCharacter following: [ self matchStream: string from: index + 1 ] ! matchWild: aSymbol with: arg following: aBlock "Private - Helper function for * sequences (+ sequences are parsed by checking for a match and then treating them as * sequences: for example, x+ becomes xx*). Try to match as many characters as possible and then look if the remaining part of the string matches the rest of the regular expression (to do so, aBlock is evaluated): if yes, answer nil; if no, try again with one character less. For example, matching [ABC]*AC to the string BAC works in this way: - try with the longest run of As, Bs or Cs (BAC). The rest of the string (that is, nothing) doesn't match the regular expression AC, so... - ...try with BA. The rest of the string (that is, C) doesn't match the regular expression AC, so... - ...try with B. The rest of the string (that is, AC) does match the regular expression AC, so we answer nil" | first last | first := string position. last := self findLastWild: aSymbol with: arg. last to: first by: -1 do: [ :i | (aBlock value == false) ifFalse: [ ^nil ]. i > 1 ifTrue: [self position: i - 1]. ]. ^false ! findLastWild: aSymbol with: arg "Send aSymbol with arg and nil as its parameter until it answers false and answer the position of the last character for which aSymbol answered true" [ string atEnd ifTrue: [ ^string position ]. self perform: aSymbol with: arg with: nil ] whileTrue: [ ]. string skip: -1. ^string position ! matchStream: aStream from: firstIndex "Private - Match all the atoms from the firstIndex-th to the string on which aStream is streaming. Answer true or false" | result oldString | oldString := string. self string: aStream. firstIndex to: self numberOfAtoms do: [ :i | " result = true ---> go on; result = false ---> answer false; result = nil ---> answer true" result := self matchAtom: i. result == true ifFalse: [ string := oldString. ^result isNil ]. ]. result := self checkIfAtEnd. string := oldString. ^result ! string: aStream "Private - Tell the other methods which string is being parsed" string := aStream ! checkIfAtEnd "Private - Answer true if there is no $ or if we're at the end of the parsed string" ^noDollar or: [string atEnd] ! numberOfAtoms "Private - Answer the number of atoms in the receiver" ^selectors size ! matchAtom: index "Private - Try to match an atom to string" | result | "index print. $ print. (selectors at: index) print. $ print. (params at: index) print. $ print. string peek print. $ printNl." ^self perform: (selectors at: index) with: (params at: index) with: index ! ! smalltalk-3.2.5/examples/GenClasses.st0000644000175000017500000000461312123404352014643 00000000000000"====================================================================== | | Generate class definitions | | ======================================================================" "====================================================================== | | Copyright 1988,92,94,95,1999,2000 Free Software Foundation, Inc. | Written by Steve Byrne. | | This file is part of GNU Smalltalk. | | GNU Smalltalk is free software; you can redistribute it and/or modify it | under the terms of the GNU General Public License as published by the Free | Software Foundation; either version 2, or (at your option) any later version. | | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS | FOR A PARTICULAR PURPOSE. See the GNU General Public License for more | details. | | You should have received a copy of the GNU General Public License along with | GNU Smalltalk; see the file COPYING. If not, write to the Free Software | Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. | ======================================================================" Object subclass: #GenClass instanceVariableNames: 'parent stream' classVariableNames: '' poolDictionaries: '' category: 'Examples-Useful tools' ! !GenClass class methodsFor: 'execution'! generate: onStream parent: parentName names: nameList prefix: aSymbol ^self new init: onStream parent: parentName names: nameList mangle: [ :name | aSymbol, name ] ! generate: onStream parent: parentName names: nameList suffix: aSymbol ^self new init: onStream parent: parentName names: nameList mangle: [ :name | name, aSymbol ] ! generate: onStream parent: parentName names: nameList ^self new init: onStream parent: parentName names: nameList mangle: [ :name | name ] ! ! !GenClass methodsFor: 'private'! init: aStream parent: parentName names: nameList mangle: aBlock parent := parentName asString. stream := aStream. nameList do: [ :name | self generate: (aBlock value: name). ] ! generate: name stream nextPutAll: parent; nextPutAll: ' subclass: #'; nextPutAll: name; nl; nextPutAll: ' instanceVariableNames: '''' ' nl; nextPutAll: ' classVariableNames: '''' ' nl; nextPutAll: ' poolDictionaries: '''' '; nl; nextPutAll: ' category: ''no category'' !'; nl; nl ! ! smalltalk-3.2.5/examples/Sync.st0000644000175000017500000002353112123404352013530 00000000000000"====================================================================== | | Sample synchronization primitives | | ======================================================================" "====================================================================== | | Copyright (C) 2002 Free Software Foundation, Inc. | Written by Paolo Bonzini. | | This file is part of GNU Smalltalk. | | GNU Smalltalk is free software; you can redistribute it and/or modify it | under the terms of the GNU General Public License as published by the Free | Software Foundation; either version 2, or (at your option) any later version. | | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS | FOR A PARTICULAR PURPOSE. See the GNU General Public License for more | details. | | You should have received a copy of the GNU General Public License along with | GNU Smalltalk; see the file COPYING. If not, write to the Free Software | Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. | ======================================================================" Object subclass: #Monitor instanceVariableNames: 'semaphore process count waitSemaphores ' classVariableNames: 'Mutex' poolDictionaries: '' category: 'Examples-Processes'! Monitor comment: ' A monitor provides process synchronization that is more highlevel than the one provided by a Semaphore. It is equivalent to the facility provided by the Java language. 1) At any time, only one process can be executing code inside a critical section of a monitor. 2) A monitor is reentrant, which means that the active process in a monitor does never get blocked when it enters a (nested) critical section of the same monitor. 3) Inside a critcal section, a process can stop to wait for events. The process leaves the monitor temporarily (in order to let other processes enter) and waits until another process notifies the event. Then, the original process checks if the event is the desired one and continues if it is. 4) The monitor is fair, which means that the process that is waiting on a notified condition the longest gets activated first.'! Semaphore subclass: #ConditionVariable instanceVariableNames: 'set' classVariableNames: '' poolDictionaries: '' category: 'Examples-Processes' ! ConditionVariable comment: 'A ConditionVariable allows Processes to suspend execution until some predicate on shared data is satisfied. The basic operations on conditions are: notify the condition (when the predicate becomes true), clear it, and wait for the condition.'! Object subclass: #Barrier instanceVariableNames: 'countdown sema' classVariableNames: '' poolDictionaries: '' category: 'Examples-Processes' ! Barrier comment: 'A Barrier has a threshold t and stops the first t-1 processes that sends it #wait; when the t-th process says it has reached the barrier (by sending it #wait) all the suspended processes are restarted and further waits will be no-ops.'! RecursionLock subclass: #ReadWriteLock instanceVariableNames: 'readMutex readers readLocked' classVariableNames: '' poolDictionaries: '' category: 'Examples-Processes' ! ReadWriteLock comment: 'A read-write lock can be locked in two modes, read-only (with #readLockDuring:) and read-write (with #critical:). When the lock is only locked by other threads in read-only mode, a read-only lock will not block and a read-write locking attempt will wait for all the read-only locks to be released. Instead, when one thread holds a read-write lock, all locking attempts will suspend the current thread until this lock is released again.'! Object subclass: #Watchdog instanceVariableNames: 'actionBlock relax ok delay' classVariableNames: '' poolDictionaries: '' category: 'Examples-Processes' ! Watchdog comment: 'I am used to watch for system hangups. Until #terminate is sent to an instance of me, I periodically check if during the time you sent #notify and, if you did not, I evaluate a user-supplied action block.'! !Monitor class methodsFor: 'initialization'! initialize Mutex := Semaphore forMutualExclusion! ! !Monitor class methodsFor: 'private'! delayProcessFor: mils semaphore: s ^[ (Delay forMilliseconds: mils) wait. s signal. Processor activeProcess suspend ]! !Monitor class methodsFor: 'instance creation'! new ^super new initialize! !Monitor methodsFor: 'initialize-release'! initialize count := 0. semaphore := Semaphore forMutualExclusion! ! !Monitor methodsFor: 'private'! checkOwnerProcess self isOwnerProcess ifFalse: [self error: 'Monitor access violation']! enter | activeProcess | activeProcess := Processor activeProcess. process == activeProcess ifFalse: [ semaphore wait. process := activeProcess ]. count := count + 1! exit Mutex wait. (count := count - 1) == 0 ifTrue: [ process := nil. semaphore signal ]. Mutex signal! unlock | oldCount | oldCount := count. count := 0. process := nil. semaphore signal. ^oldCount! lock: saveCount | activeProcess | activeProcess := Processor activeProcess. process == activeProcess ifFalse: [ semaphore wait. process := activeProcess ]. count := count + saveCount! ! !Monitor methodsFor: 'control'! critical: aBlock self enter. ^aBlock ensure: [ self exit ]! signal self checkOwnerProcess. Mutex wait. waitSemaphores isNil ifTrue: [ Mutex signal. ^self ]. waitSemaphores isEmpty ifFalse: [ waitSemaphores removeFirst signal ]. Mutex signal! signalAll self checkOwnerProcess. Mutex wait. waitSemaphores isNil ifTrue: [ Mutex signal. ^self ]. waitSemaphores size timesRepeat: [ waitSemaphores removeFirst signal ]. Mutex signal! wait ^self wait: 0! wait: msec | count process sema | self checkOwnerProcess. sema := Semaphore new. "Grab the monitor, unlock it and register the semaphore we'll wait on. Note that we unlock the monitor *before* relinquishing the mutex." Mutex wait. count := self unlock. waitSemaphores isNil ifTrue: [ waitSemaphores := OrderedCollection new ]. waitSemaphores addLast: sema. Mutex signal. "If there's a timeout, start a process to exit the wait anticipatedly." msec > 0 ifTrue: [ process := (self class delayProcessFor: msec semaphore: sema) fork ]. sema wait. "Also if there's a timeout, ensure that the semaphore is removed from the list. If there's no timeout we do not even need to reacquire the monitor afterwards (see also #exit:, which waits after getting the monitor and relinquishing the mutex)." process notNil ifTrue: [ Mutex wait. waitSemaphores remove: sema ifAbsent: []. process terminate. Mutex signal ]. self lock: count! ! !ConditionVariable methodsFor: 'all'! initialize super initialize. set := false ! wait [ set ifFalse: [ super wait ] ] valueWithoutPreemption ! reset [ set := false. ] valueWithoutPreemption ! pulse [ set ifFalse: [ self notifyAll ] ] valueWithoutPreemption ! broadcast [ | wasSet | wasSet := set. set := true. wasSet ifFalse: [ self notifyAll ]. ] valueWithoutPreemption ! signal [ | wasSet | wasSet := set. set := true. wasSet ifFalse: [ self notify ]. ] valueWithoutPreemption ! ! !Barrier class methodsFor: 'all'! new: threshold ^self new initialize: threshold; yourself ! !Barrier methodsFor: 'all'! initialize: count countdown := count. sema := Semaphore new ! wait countdown < 0 ifTrue: [ ^self ]. countdown := countdown - 1. countdown = 0 ifTrue: [ sema notifyAll ] ifFalse: [ sema wait ]. ! ! !ReadWriteLock methodsFor: 'all'! initialize super initialize. readMutex := Semaphore forMutualExclusion. readers := 0. readLocked := false. ! readLocked ^readLocked ! readLockDuring: aBlock readMutex wait. readers := readers + 1. "If readers was already >= 1, we don't have to wait for the write-lock to be freed and this is substantially equivalent to readMutex signal. aBlock value. readMutex wait. readers = readers - 1. readMutex signal. Instead if readers was zero we have to get the write lock: readLocked := true. readMutex signal. aBlock value readMutex wait. readers = readers - 1. readLocked := false. readMutex signal Note that actually the release of the lock might happen in a different process than the one that acquired the lock! That's the reason why readers is an instance variable." self critical: [ readMutex signal. aBlock value ] ! wait readers > 1 ifTrue: [ ^self ]. super wait. readLocked := readers > 0 ! signal readLocked ifTrue: [ readMutex wait. readers := readers - 1. readLocked := (readers > 0). readLocked ifTrue: [ readMutex signal. ^self ]. readMutex signal. ]. super signal ! ! !Watchdog class methodsFor: 'all'! defaultMillisecondsWatchdogTime ^60000 ! new ^self basicNew initialize: self defaultMillisecondsWatchdogTime ! forSeconds: n ^self basicNew initialize: n * 1000 ! forMilliseconds: n ^self basicNew initialize: n ! do: aBlock ^self new actionBlock: aBlock; start ! ! !Watchdog methodsFor: 'all'! initialize: msec relax := true. delay := Delay forMilliseconds: msec. ok := true. actionBlock := ValueHolder null. "Anything that answers #value will do" ! terminate relax := true. ! actionBlock: aBlock actionBlock := aBlock. ! signal ok := true. ! start relax := false. ok := false. [ [ delay wait. relax ] whileFalse: [ ok ifFalse: [ actionBlock value ]. ok := false. ] ] forkAt: Processor lowIOPriority. ! ! Monitor initialize! smalltalk-3.2.5/examples/TokenStream.st0000644000175000017500000000574412123404352015056 00000000000000"====================================================================== | | Token stream Method Definitions | | ======================================================================" "====================================================================== | | Copyright 1988,92,94,95,99,2000,2001,2007 | Free Software Foundation, Inc. | Written by Steve Byrne. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" Stream subclass: #TokenStream instanceVariableNames: 'charStream' classVariableNames: '' poolDictionaries:'' category: 'Streams-Collections' ! TokenStream comment: 'I operate on a stream of characters and return distinct whitespace-delimited groups of characters; I am used to parse the parameters of class-creation methods. Basically, I parse off whitespace separated tokens as substrings and return them (next). If the entire contents of the string are requested, I return them as an Array containing the individual strings.'! !TokenStream class methodsFor: 'instance creation'! on: aString "Answer a TokenStream working on aString" ^self onStream: (ReadStream on: aString) ! onStream: aStream "Answer a TokenStream working on the collection on which aStream is in turn streaming." ^self new setStream: aStream ! ! !TokenStream methodsFor: 'basic'! next "Answer a new whitespace-separated token from the input stream" | char tokStream | self atEnd ifTrue: [ ^nil ]. "has the nice side effect of skipping leading white space." tokStream := WriteStream on: (String new: 1). [ char := charStream peek. (char notNil) and: [ (char isSeparator) not ] ] whileTrue: [ tokStream nextPut: (charStream next) ]. ^tokStream contents ! atEnd "Answer whether the input stream has no more tokens." | char | [ char := charStream peek. char isNil ] whileFalse: [ (char isSeparator) ifFalse: [ ^false ]. charStream next ]. ^true ! ! !TokenStream methodsFor: 'write methods'! nextPut: anObject self shouldNotImplement ! ! !TokenStream methodsFor: 'private'! setStream: aStream charStream := aStream. ! ! smalltalk-3.2.5/examples/MemUsage.st0000644000175000017500000000457012123404352014321 00000000000000"====================================================================== | | Compute the amount of memory and the number of instances for each | class in the GNU Smalltalk system. | | ======================================================================" "====================================================================== | | Copyright 1988,92,94,95,99,2000,2002 Free Software Foundation, Inc. | Written by Steve Byrne. | | This file is part of GNU Smalltalk. | | GNU Smalltalk is free software; you can redistribute it and/or modify it | under the terms of the GNU General Public License as published by the Free | Software Foundation; either version 2, or (at your option) any later version. | | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS | FOR A PARTICULAR PURPOSE. See the GNU General Public License for more | details. | | You should have received a copy of the GNU General Public License along with | GNU Smalltalk; see the file LICENSE. If not, write to the Free Software | Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. | ======================================================================" !ObjectMemory class methodsFor: 'demo'! memoryUsage | t numObjs classObjs totalInstanceSize instVarSize | numObjs := t := 0. ObjectMemory compact. Object withAllSubclasses do: [ :class | class printNl. totalInstanceSize := classObjs := 0. instVarSize := class instSize. (class inheritsFrom: ContextPart) ifFalse: [ class allInstancesDo: [ :inst | totalInstanceSize := totalInstanceSize + ((Memory at: (ObjectMemory addressOf: inst)) * 4). classObjs := classObjs + 1 ] ]. Transcript nextPutAll: ' Instances: '. classObjs printNl. Transcript nextPutAll: ' Size: '. totalInstanceSize printNl. Transcript nl. t := t + totalInstanceSize. numObjs := numObjs + classObjs ]. ^numObjs -> t ! histogram | sizes size | ObjectMemory compact. sizes := Bag new. Object withAllSubclasses do: [ :class | (class inheritsFrom: ContextPart) ifFalse: [ class allInstancesDo: [ :inst | size := (Memory at: (ObjectMemory addressOf: inst)). sizes add: size ] ]. ]. sizes printNl. ! ! ObjectMemory memoryUsage printNl! ObjectMemory histogram printNl! smalltalk-3.2.5/examples/Gen2.st0000644000175000017500000002122212123404352013402 00000000000000"====================================================================== | | Python-like Generators | | ======================================================================" "====================================================================== | | Copyright 2003 Free Software Foundation, Inc. | Written by Paolo Bonzini. | | This file is part of GNU Smalltalk. | | GNU Smalltalk is free software; you can redistribute it and/or modify it | under the terms of the GNU General Public License as published by the Free | Software Foundation; either version 2, or (at your option) any later version. | | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS | FOR A PARTICULAR PURPOSE. See the GNU General Public License for more | details. | | You should have received a copy of the GNU General Public License along with | GNU Smalltalk; see the file COPYING. If not, write to the Free Software | Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. | ======================================================================" Stream subclass: #Generator instanceVariableNames: 'next topContext bottomContext contexts suspendedContext atEnd' classVariableNames: '' poolDictionaries: '' category: 'Streams-Generators' ! Generator comment: 'A Generator object provides a way to define a Generator method: such a method does not return a single value, instead it returns an object (the Generator) that uses a Stream interface to access multiple return values. The return values are computed one at a time, as needed, and hence need not even be finite. A generator methods starts by creating a Generator object with "Generator new" and saving it into a temporary variable. As soon as this is executed, even though it is not apparent, the method exits returning the newly created Generator. As soon as a message like #next, #peek, #atEnd or #peekFor: is sent to the generator, execution of the method that created it resumes and goes on until the generator''s #yield: method is called: then the argument of #yield: will be the Generator''s next element. If the generator method goes on to the end without calling #yield:, the Generator will produce no more elements and #atEnd will return true. Alternatively, a generator block can be converted to a Generator with "Generator on: [...]". The Generator itself is passed to the block and, again, the block starts its execution when a message like #next, #peek, #atEnd or #peekFor: is sent to the generator. Again, the block''s execution is temporarily suspended when the generator''s #yield: method is called. Returning a value from the generator method makes no sense at least after "Generator new" is invoked. Before, you can use it to return a different kind of Stream, or nil, or whatever else; after, the value returned will not matter and the return will put an end to the Generator''s production of elements. You could achieve the effect of generators manually by writing your own class and storing all the local variables of the generator as instance variables. For example, returning a list of integers could be done by setting a variable to 0, and having the #next method increment it and return it. However, for a moderately complicated generator, writing a corresponding class would be much messier (and might lead to code duplication or inefficiency if you want to support #peek, #peekFor: and/or #atEnd): in general, providing a #do:-like interface is easy, but not providing a Stream-like one (think binary trees). The idea of generators comes from other programming languages, in particular this interface looks much like Scheme streams and Python generators. But Python in turn mutuated the idea for example from Icon, where the idea of generators is central. In Icon, every expression and function call behaves like a generator, and if a statement manages scalars, it automatically uses up all the results that the corresponding generator provides; on the other hand, Icon does not represent generators as first-class objects like Python and Smalltalk do.'! !Generator class methodsFor: 'instance creation'! new "Return a generator, and also suspend the execution of the sender by returning the new generator to the method that invoked the sender. More easily seen by looking at an example: Integer>>evenNumbersUpTo: n | gen | gen := Generator new. self to: n do: [ :each | each even ifTrue: [ gen yield: each ] ] Although there is no return statement in the method, evaluating it returns a Generator for the even numbers between the receiver and the argument." ^super new context: thisContext parentContext ! on: aBlock | gen | gen := self new. aBlock value: gen. ! ! !Generator methodsFor: 'stream protocol'! atEnd "Answer whether more data can be generated." atEnd isNil ifTrue: [ self generateNext ]. ^atEnd ! next "Evaluate the generator until it generates the next value or decides that nothing else can be generated." | result | self atEnd ifTrue: [ ^self pastEnd ]. atEnd := nil. result := next. next := nil. ^result ! peek "Evaluate the generator until it generates the next value or decides that nothing else can be generated, and save the value so that #peek or #next will return it again." self atEnd ifTrue: [ ^nil ]. ^next ! peekFor: anObject "Evaluate the generator until it generates the next value or decides that nothing else can be generated, and if it is not equal to anObject, save the value so that #peek or #next will return it again." self atEnd ifTrue: [ self pastEnd. ^false ]. ^next = anObject ifTrue: [ next := nil. atEnd := nil. true ] ifFalse: [ false ] ! ! !Generator methodsFor: 'private - continuations'! context: aContext "Initialize the state of the generator. Its execution will resume from the context, aContext. Then return the generator itself to the sender of aContext: this method is called by Generator class>>#new, and this has the side effect of returning the Generator from the sender." contexts := OrderedCollection new. topContext := bottomContext := aContext. bottomContext parentContext continue: self ! yield: anObject "Save the object returned by the continuation in the next instance variable, then save the execution state of the continuation in topContext, bottomContext and contexts. This is because resuming execution in #invokeGenerator will cause returned blocks to be marked as non-returnable, and we want to preserve the chain." next := anObject. atEnd := false. topContext := bottomContext := thisContext parentContext. [ contexts addLast: bottomContext. bottomContext parentContext == suspendedContext ] whileFalse: [ bottomContext := bottomContext parentContext. ]. suspendedContext continue: self. ! generateNext "Invoke the continuation via #invokeGenerator, then resume execution when #yield: is invoked. Then, use the information in the contexts instance variable to reconstruct the continuation's chain of contexts." | ctx | self invokeGenerator. ctx := topContext. [ contexts isEmpty ] whileFalse: [ ctx parentContext: contexts removeFirst. ctx := ctx parentContext. ]. ! invokeGenerator "This swizzles the contexts, inserting the execution state of the continuation between the #invokeGenerator context and the #generateNext context, then starts evaluating the code in the continuation." atEnd := true. suspendedContext := thisContext parentContext. bottomContext parentContext: suspendedContext. thisContext parentContext: topContext. ! ! !Integer methodsFor: 'examples of generators'! generatorForGeneratorExample | gen | gen := Generator new. 'Entering gen' displayNl. 1 to: self do: [ :each | ('Yielding ', each printString, '... ') display. gen yield: each. 'Resuming gen' displayNl ]! generatorBlockExample ^Generator on: [ :gen | 'Entering gen' displayNl. 1 to: self do: [ :each | ('Yielding ', each printString, '... ') display. gen yield: each. 'Resuming gen' displayNl ] ]! generatorExample: gen | n | ('Running on ', gen printString) displayNl. [ 'Calling next... ' display. n := gen next. n notNil ] whileTrue: [ ('Got ', n printString) displayNl ]! ! 10 generatorExample: 10 generatorForGeneratorExample! Eval [ Smalltalk byteCodeCounter printNl. 10 generatorExample: 10 generatorBlockExample. Smalltalk byteCodeCounter printNl ] smalltalk-3.2.5/examples/README0000644000175000017500000001407012123404352013122 00000000000000This directory contains some example GNU Smalltalk programs. The programs are: bench.st An extraordinarily precise low-level benchmark for Smalltalk, by His Majesty contributed by Dwight Hughes and originarily prepared for Dan Ingalls! Squeak. It executes two pieces of code and deduces the system's speed in terms of bytecodes/second on bytecode-heavy code (arithmetics - sieve in this case) and sends/second on send-heavy code (a recursive Fibonacci computation in this case) -- they usually coincide to two digits with the speeds given by the GST runtime! CairoBlit.st A simple example of the Cairo and SDL bindings. by tonyg Case.st A nice object for C-switch like behavior. Although it is slower by Ulf than compiler-optimized ifs, try it: it really works nice. Dambacher CStream.st A stream providing functionality for writing C code. by sbb Dinner.st The classic dining philosophers problem. You need working by me Delays to try this (alarm is not very good but maybe it works). Try `(Philosophers new: 5) dine'. EditStream.st A stream handling fast insertions, using a double buffer by Ulf with a gap between the buffers. Dambacher LazyCollection.st Implementation of #collect:, #select:, #reject: that do not by me create a new collection unless really necessary. Sync.st Many kinds of synchronization devices. by me GenClasses.st Provides help in creating many similarly named classes. by sbb Lisp.st A nice Lisp interpreter class; try "LispInterpreter by Aoki Atsushi exampleXX" with XX going from 01 to 18. I modified it Nishihara Satoshi to remove the Smalltalk-subset compiler that was needed on proprietary systems that don't allow a compiler to be enclosed in a run-time image -- it was 25% of the total code; this way there is more focus on the Lisp stuff. MemUsage.st This is really more of a test suite kind of program. It by sbb iterates through all the objects in the system, counting up how much storage has been used by each, and printing a total at the end. It has found more bugs in the memory management system than I (sbb) care to admit. Methods.st Examples of subclassing CompiledMethod... 'nuff said! by Ian Piumarta and me MiniDebugger.st A simplified debugger which shows how to use the single step by me primitives to implement an interface that vaguely resembles gdb. PackageBuilder.st A simple script to make package.xml file from a Smalltalk by Stefan Schmiedl description. You may find it useful! Prolog.st This is absolutely stunning! A Prolog interpreter written in by Aoki Atsushi Smalltalk, from the same author as the Lisp interpreter; try Nishihara Satoshi PrologInterpreter exampleXX with XX going from 01 to 06 PrtHier.st prints out the class hierarchy, indented according to by sbb the number of super classes a class has. Publish.st An object-oriented, multiple format class file-out system. by me/sbb Currently includes Postscript for file-outs, and HTML/Texinfo for documentation -- by the way, this example is used by the makefile for GNU Smalltalk's info files. And also an example of namespaces. PushBack.st A Stream with unlimited push-back capabilities. Together with by sbb Tokenizer.st, it is used in many places (C interface, compiler) Queens.st An elegant solution of the queens and amazons problem (amazons by me can move like either the queen or the knight). There are: 2 solutions (1 discarding rotations/reflections) on a 4x4 board 92 solutions (12) on a 8x8 board no solutions (!) to the amazons problem on a 8x8 board 4 solutions (1) to the amazons problem on a 10x10 board A few examples usages are at the end of the file. Richards.st The Richards benchmark (a simulation of an operating systems) by unknown under Smalltalk, a classic in Smalltalk benchmarking because of its use of polymorphism and OO. shell An example of how to make a Smalltalk script work both if you by Alexander file it in from GNU Smalltalk and if you launch it from the Lazarevic shell; for it to work, the gst executable must be in the path. If it is not, just do PATH=$PATH: before running it. SortCriter.st A very nice object that allows you to easily create by Peter SortedCollections sorted using complex objects (specifying William Lount which fields are more important and which must be sorted in descending order). Tokenizer.st An abstract base class for lexical analyzers. by me/sbb TokenStream.st Formerly a part of the class hierarchy. Now replaced with by sbb CharacterArray>>#subStrings. Generator.st Python/Ruby-like generators, using continuations. Gen2.st Same, using contexts (slower). Gen3.st Same, using processes (in the middle). by me The directory also contains some bindings for external libraries; currently these are GDBM, ZLib and MD5 bindings. The directory also contains two examples of using Blox: Man.st Man page viewer widget (example of using BExtended). To test by me it evaluate "ManViewer openOn: 'path' ". Tetris.st A Tetris game written using BLOX. To start it, use by me "Tetris play". Cursor keys move the piece, Up rotates it, Return drops it. More examples can be found in the blox/BloxExtend.st and blox/test.st file In addition, this directory contains two scripts that can help converting from other Smalltalk source code formats to the traditional file in (chunk) format. These are: - `pepe.sed', that converts from the Pepe format, a portable format consisting exclusively of executable code (an example is in tests/ansi/ansi.pepe; this script can be slow. - `xml.sed', that converts from an XML DTD designed for Smalltalk source. This script does not convert `statics' (that's how the DTD calls class variables) yet. Requires GNU sed. The `unsupported/misc' directory contains some other small example GNU Smalltalk programs which test more advanced aspects of Smalltalk, either various packages or the VM. Among others, `torture.st' is Andreas Klimas' nice memory torture test program - like MemUsage.st it has found more bugs in the memory management system than I care to admit... Paolo Bonzini smalltalk-3.2.5/examples/Bench.st0000644000175000017500000000615612123404352013637 00000000000000!Integer methodsFor: 'benchmarks'! tinyBenchmarks "Report the results of running the two tiny Squeak benchmarks. The following table lists results for various Smalltalks on a 300 MHz PentiumII PC. Take these results with a grain of salt and read these notes: Notes: a) An object table does hinder performance of course, but not that much. VisualWorks is still 25% faster than IBM Smalltalk, and even 40% in the `send message' benchmark where the object table should penalize it more. b) Smalltalk MT's sending performance is poor because numbers were obtained evaluating the benchmarks from the Transcript, which activates a non-optimized build -- creating an indipendent executable would bring numbers considerably higher. Not owning a copy Smalltalk MT I cannot do that and correct the figures. c) I feel that the JIT compiler's performance is encouraging, although the current architecture cannot show great improvements in the sends benchmark. Adding type inferencing will probably shorten the gap with VisualWorks, which is a derivative of the original ParcPlace translator! d) I know that some values are for obsolete versions of the tools. Send updated values if you care. ,--- (B)ytecode interpreter, (J)IT compiler, static (C)ompiler / ,-- Uses (D)irect or (I)ndirect pointers / / ././.---------------------.---------------------.-----------------. |B|I| Dolphin Smalltalk | 17.4 Mbytecodes/sec | 1112 Ksends/sec | |B|I| GST (with GCC 3.0) | 22.4 Mbytecodes/sec | 1080 Ksends/sec | |J|D| IBM Smalltalk 3.0 | 61.9 Mbytecodes/sec | 4224 Ksends/sec | |J|I| GST (with JIT) | 72.0 Mbytecodes/sec | 2625 Ksends/sec | |J|I| VisualWorks 5i | 81.8 Mbytecodes/sec | 5950 Ksends/sec | |C|?| Smalltalk MT | 128 Mbytecodes/sec | 1076 Ksends/sec | '-'-----------------------'---------------------'-----------------" | t1 t2 r n1 n2 | n1 _ 1 bitShift: self. [ObjectMemory compact. t1 _ Time millisecondsToRun: [n1 benchmark]. t1 < 5000] whileTrue:[ n1 _ n1 * 2 ]. n2 _ 24 + self. [ObjectMemory compact. t2 _ Time millisecondsToRun: [r _ n2 benchFib]. t2 < 5000] whileTrue:[ n2 _ n2 + 1 ]. ^((n1 * 500000 * 1000) // t1) printString, ' bytecodes/sec; ', ((r * 1000) // t2) printString, ' sends/sec'! benchFib "Handy send-heavy benchmark -- result is number of sends: (result // seconds to run) = approx calls per second" ^self < 2 ifTrue: [1] ifFalse: [(self - 1) benchFib + (self - 2) benchFib + 1] ! benchmark "Handy bytecode-heavy benchmark -- approx 500000 bytecodes per run: (500000 * times ran // secs to run) = approx bytecodes per second" | size flags prime k count | size _ 8190. flags _ Array new: size. self timesRepeat: [ count _ 0. flags atAllPut: true. 1 to: size do: [:i | (flags at: i) ifTrue: [prime _ i+1. k _ i + prime. [k <= size] whileTrue: [flags at: k put: false. k _ k + prime]. count _ count + 1]]]. ^count ! ! Transcript showCr: 12 tinyBenchmarks! smalltalk-3.2.5/examples/Timer.st0000644000175000017500000000523112123404352013671 00000000000000"====================================================================== | | Handy Timer object for establishing periodic activities | | ======================================================================" "====================================================================== | | Copyright 1988-92, 1994-95, 1999, 2000 Free Software Foundation, Inc. | Written by Paolo Bonzini. | | This file is part of GNU Smalltalk. | | GNU Smalltalk is free software; you can redistribute it and/or modify it | under the terms of the GNU General Public License as published by the Free | Software Foundation; either version 2, or (at your option) any later version. | | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS | FOR A PARTICULAR PURPOSE. See the GNU General Public License for more | details. | | You should have received a copy of the GNU General Public License along with | GNU Smalltalk; see the file COPYING. If not, write to the Free Software | Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. | ======================================================================" Object subclass: #Timer instanceVariableNames: 'period doBlock stopBlock atStopBlock process ' classVariableNames: '' poolDictionaries: '' category: 'Examples-Processes'! !Timer methodsFor: 'accessing'! atStopBlock ^atStopBlock ! atStopBlock: aBlock atStopBlock := aBlock ! doBlock ^doBlock ! doBlock: aValue doBlock := aValue ! processPriority ^Processor userSchedulingPriority ! stopBlock ^stopBlock ! stopBlock: aValue stopBlock := aValue ! period ^period ! period: aValue period := aValue ! ! !Timer methodsFor: 'actions'! resume process isNil ifFalse: [ process resume. ]. ! start process isNil ifFalse: [ ^self ]. process := [ [ self stopBlock value ] whileFalse: [ (Delay forMilliseconds: self period) wait. doBlock value ]. self atStopBlock isNil ifFalse: [ self atStopBlock value ]. process := nil ] forkAt: self processPriority ! stop process isNil ifFalse: [ process terminate. ]. process := nil. ! suspend process isNil ifFalse: [ process suspend. ]. ! ! !Timer class methodsFor: 'instance-creation'! every: milliseconds do: aBlock stopWhen: anotherBlock ^self new period: milliseconds; doBlock: aBlock; stopBlock: anotherBlock; start; yourself ! every: milliseconds do: aBlock stopWhen: anotherBlock afterStopDo: stopBlock ^self new period: milliseconds; doBlock: aBlock; stopBlock: anotherBlock; atStopBlock: stopBlock; start; yourself ! ! smalltalk-3.2.5/examples/xml.sed0000755000175000017500000001544512123404352013551 00000000000000#! /bin/sed -f ####################################################################### # # Convert VisualWorks XML file-outs to chunked format # ######################################################################## ####################################################################### # # Copyright 1999, 2000, 2008 Free Software Foundation, Inc. # Written by Paolo Bonzini. # # This file is part of GNU Smalltalk # # GNU Smalltalk is free software; you can redistribute it and/or modify it # under the terms of the GNU General Public License as published by # the Free Software Foundation; either version 2, or (at your option) # any later version. # # GNU Smalltalk is distributed in the hope that it will be useful, but # WITHOUT ANY WARRANTY; without even the implied warranty of # MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU # General Public License for more details. # # You should have received a copy of the GNU General Public License # along with GNU Smalltalk; see the file COPYING. If not, write to # the Free Software Foundation, 51 Franklin Street, Fifth Floor, Boston, # MA 02110-1301, USA. # ######################################################################## # Remove processing instructions and comments s///g :xmlcomment /^/! { :continue N /-->/! b continue } s/^ mem float */ {"fstl", 1, 0xdd, 2, Modrm, { Mem, 0, 0} }, /* %st0 --> mem double */ {"fstl", 1, 0xddd0, _, ShortForm, { FloatReg, 0, 0} }, /* register */ {"fist", 1, 0xdf, 2, Modrm, { Mem, 0, 0} }, /* %st0 --> mem word (16) */ {"fistl", 1, 0xdb, 2, Modrm, { Mem, 0, 0} }, /* %st0 --> mem dword (32) */ /* store (with pop) */ {"fstp", 1, 0xddd8, _, ShortForm, { FloatReg, 0, 0} }, /* register */ {"fstps", 1, 0xd9, 3, Modrm, { Mem, 0, 0} }, /* %st0 --> mem float */ {"fstpl", 1, 0xdd, 3, Modrm, { Mem, 0, 0} }, /* %st0 --> mem double */ {"fstpl", 1, 0xddd8, _, ShortForm, { FloatReg, 0, 0} }, /* register */ {"fistp", 1, 0xdf, 3, Modrm, { Mem, 0, 0} }, /* %st0 --> mem word (16) */ {"fistpl",1, 0xdb, 3, Modrm, { Mem, 0, 0} }, /* %st0 --> mem dword (32) */ {"fistpq",1, 0xdf, 7, Modrm, { Mem, 0, 0} }, /* %st0 --> mem qword (64) */ {"fistpll",1,0xdf, 7, Modrm, { Mem, 0, 0} }, /* %st0 --> mem qword (64) */ {"fstpt", 1, 0xdb, 7, Modrm, { Mem, 0, 0} }, /* %st0 --> mem efloat */ {"fbstp", 1, 0xdf, 6, Modrm, { Mem, 0, 0} }, /* %st0 --> mem bcd */ /* exchange %st with %st0 */ {"fxch", 1, 0xd9c8, _, ShortForm, { FloatReg, 0, 0} }, {"fxch", 0, 0xd9c9, _, NoModrm, { 0, 0, 0} }, /* alias for fxch %st, %st(1) */ /* comparison (without pop) */ {"fcom", 1, 0xd8d0, _, ShortForm, { FloatReg, 0, 0} }, {"fcoms", 1, 0xd8, 2, Modrm, { Mem, 0, 0} }, /* compare %st0, mem float */ {"ficoml", 1, 0xda, 2, Modrm, { Mem, 0, 0} }, /* compare %st0, mem word */ {"fcoml", 1, 0xdc, 2, Modrm, { Mem, 0, 0} }, /* compare %st0, mem double */ {"fcoml", 1, 0xd8d0, _, ShortForm, { FloatReg, 0, 0} }, {"ficoms", 1, 0xde, 2, Modrm, { Mem, 0, 0} }, /* compare %st0, mem dword */ /* comparison (with pop) */ {"fcomp", 1, 0xd8d8, _, ShortForm, { FloatReg, 0, 0} }, {"fcomps", 1, 0xd8, 3, Modrm, { Mem, 0, 0} }, /* compare %st0, mem float */ {"ficompl", 1, 0xda, 3, Modrm, { Mem, 0, 0} }, /* compare %st0, mem word */ {"fcompl", 1, 0xdc, 3, Modrm, { Mem, 0, 0} }, /* compare %st0, mem double */ {"fcompl", 1, 0xd8d8, _, ShortForm, { FloatReg, 0, 0} }, {"ficomps", 1, 0xde, 3, Modrm, { Mem, 0, 0} }, /* compare %st0, mem dword */ {"fcompp", 0, 0xded9, _, NoModrm, { 0, 0, 0} }, /* compare %st0, %st1 & pop 2 */ /* unordered comparison (with pop) */ {"fucom", 1, 0xdde0, _, ShortForm, { FloatReg, 0, 0} }, {"fucomp", 1, 0xdde8, _, ShortForm, { FloatReg, 0, 0} }, {"fucompp", 0, 0xdae9, _, NoModrm, { 0, 0, 0} }, /* ucompare %st0, %st1 & pop twice */ {"ftst", 0, 0xd9e4, _, NoModrm, { 0, 0, 0} }, /* test %st0 */ {"fxam", 0, 0xd9e5, _, NoModrm, { 0, 0, 0} }, /* examine %st0 */ /* load constants into %st0 */ {"fld1", 0, 0xd9e8, _, NoModrm, { 0, 0, 0} }, /* %st0 <-- 1.0 */ {"fldl2t", 0, 0xd9e9, _, NoModrm, { 0, 0, 0} }, /* %st0 <-- log2(10) */ {"fldl2e", 0, 0xd9ea, _, NoModrm, { 0, 0, 0} }, /* %st0 <-- log2(e) */ {"fldpi", 0, 0xd9eb, _, NoModrm, { 0, 0, 0} }, /* %st0 <-- pi */ {"fldlg2", 0, 0xd9ec, _, NoModrm, { 0, 0, 0} }, /* %st0 <-- log10(2) */ {"fldln2", 0, 0xd9ed, _, NoModrm, { 0, 0, 0} }, /* %st0 <-- ln(2) */ {"fldz", 0, 0xd9ee, _, NoModrm, { 0, 0, 0} }, /* %st0 <-- 0.0 */ /* arithmetic */ /* add */ {"fadd", 1, 0xd8c0, _, ShortForm, { FloatReg, 0, 0} }, {"fadd", 2, 0xd8c0, _, ShortForm|FloatD, { FloatReg, FloatAcc, 0} }, {"fadd", 0, 0xdcc1, _, NoModrm, { 0, 0, 0} }, /* alias for fadd %st, %st(1) */ {"faddp", 1, 0xdac0, _, ShortForm, { FloatReg, 0, 0} }, {"faddp", 2, 0xdac0, _, ShortForm|FloatD, { FloatReg, FloatAcc, 0} }, {"faddp", 0, 0xdec1, _, NoModrm, { 0, 0, 0} }, /* alias for faddp %st, %st(1) */ {"fadds", 1, 0xd8, 0, Modrm, { Mem, 0, 0} }, {"fiaddl", 1, 0xda, 0, Modrm, { Mem, 0, 0} }, {"faddl", 1, 0xdc, 0, Modrm, { Mem, 0, 0} }, {"fiadds", 1, 0xde, 0, Modrm, { Mem, 0, 0} }, /* sub */ /* Note: intel has decided that certain of these operations are reversed in assembler syntax. */ {"fsub", 1, 0xd8e0, _, ShortForm, { FloatReg, 0, 0} }, {"fsub", 2, 0xd8e0, _, ShortForm, { FloatReg, FloatAcc, 0} }, #ifdef NON_BROKEN_OPCODES {"fsub", 2, 0xdce8, _, ShortForm, { FloatAcc, FloatReg, 0} }, #else {"fsub", 2, 0xdce0, _, ShortForm, { FloatAcc, FloatReg, 0} }, #endif {"fsub", 0, 0xdce1, _, NoModrm, { 0, 0, 0} }, {"fsubp", 1, 0xdae0, _, ShortForm, { FloatReg, 0, 0} }, {"fsubp", 2, 0xdae0, _, ShortForm, { FloatReg, FloatAcc, 0} }, #ifdef NON_BROKEN_OPCODES {"fsubp", 2, 0xdee8, _, ShortForm, { FloatAcc, FloatReg, 0} }, #else {"fsubp", 2, 0xdee0, _, ShortForm, { FloatAcc, FloatReg, 0} }, #endif {"fsubp", 0, 0xdee1, _, NoModrm, { 0, 0, 0} }, {"fsubs", 1, 0xd8, 4, Modrm, { Mem, 0, 0} }, {"fisubl", 1, 0xda, 4, Modrm, { Mem, 0, 0} }, {"fsubl", 1, 0xdc, 4, Modrm, { Mem, 0, 0} }, {"fisubs", 1, 0xde, 4, Modrm, { Mem, 0, 0} }, /* sub reverse */ {"fsubr", 1, 0xd8e8, _, ShortForm, { FloatReg, 0, 0} }, {"fsubr", 2, 0xd8e8, _, ShortForm, { FloatReg, FloatAcc, 0} }, #ifdef NON_BROKEN_OPCODES {"fsubr", 2, 0xdce0, _, ShortForm, { FloatAcc, FloatReg, 0} }, #else {"fsubr", 2, 0xdce8, _, ShortForm, { FloatAcc, FloatReg, 0} }, #endif {"fsubr", 0, 0xdce9, _, NoModrm, { 0, 0, 0} }, {"fsubrp", 1, 0xdae8, _, ShortForm, { FloatReg, 0, 0} }, {"fsubrp", 2, 0xdae8, _, ShortForm, { FloatReg, FloatAcc, 0} }, #ifdef NON_BROKEN_OPCODES {"fsubrp", 2, 0xdee0, _, ShortForm, { FloatAcc, FloatReg, 0} }, #else {"fsubrp", 2, 0xdee8, _, ShortForm, { FloatAcc, FloatReg, 0} }, #endif {"fsubrp", 0, 0xdee9, _, NoModrm, { 0, 0, 0} }, {"fsubrs", 1, 0xd8, 5, Modrm, { Mem, 0, 0} }, {"fisubrl", 1, 0xda, 5, Modrm, { Mem, 0, 0} }, {"fsubrl", 1, 0xdc, 5, Modrm, { Mem, 0, 0} }, {"fisubrs", 1, 0xde, 5, Modrm, { Mem, 0, 0} }, /* mul */ {"fmul", 1, 0xd8c8, _, ShortForm, { FloatReg, 0, 0} }, {"fmul", 2, 0xd8c8, _, ShortForm|FloatD, { FloatReg, FloatAcc, 0} }, {"fmul", 0, 0xdcc9, _, NoModrm, { 0, 0, 0} }, {"fmulp", 1, 0xdac8, _, ShortForm, { FloatReg, 0, 0} }, {"fmulp", 2, 0xdac8, _, ShortForm|FloatD, { FloatReg, FloatAcc, 0} }, {"fmulp", 0, 0xdec9, _, NoModrm, { 0, 0, 0} }, {"fmuls", 1, 0xd8, 1, Modrm, { Mem, 0, 0} }, {"fimull", 1, 0xda, 1, Modrm, { Mem, 0, 0} }, {"fmull", 1, 0xdc, 1, Modrm, { Mem, 0, 0} }, {"fimuls", 1, 0xde, 1, Modrm, { Mem, 0, 0} }, /* div */ /* Note: intel has decided that certain of these operations are reversed in assembler syntax. */ {"fdiv", 1, 0xd8f0, _, ShortForm, { FloatReg, 0, 0} }, {"fdiv", 2, 0xd8f0, _, ShortForm, { FloatReg, FloatAcc, 0} }, #ifdef NON_BROKEN_OPCODES {"fdiv", 2, 0xdcf8, _, ShortForm, { FloatAcc, FloatReg, 0} }, #else {"fdiv", 2, 0xdcf0, _, ShortForm, { FloatAcc, FloatReg, 0} }, #endif {"fdiv", 0, 0xdcf1, _, NoModrm, { 0, 0, 0} }, {"fdivp", 1, 0xdaf0, _, ShortForm, { FloatReg, 0, 0} }, {"fdivp", 2, 0xdaf0, _, ShortForm, { FloatReg, FloatAcc, 0} }, #ifdef NON_BROKEN_OPCODES {"fdivp", 2, 0xdef8, _, ShortForm, { FloatAcc, FloatReg, 0} }, #else {"fdivp", 2, 0xdef0, _, ShortForm, { FloatAcc, FloatReg, 0} }, #endif {"fdivp", 0, 0xdef1, _, NoModrm, { 0, 0, 0} }, {"fdivs", 1, 0xd8, 6, Modrm, { Mem, 0, 0} }, {"fidivl", 1, 0xda, 6, Modrm, { Mem, 0, 0} }, {"fdivl", 1, 0xdc, 6, Modrm, { Mem, 0, 0} }, {"fidivs", 1, 0xde, 6, Modrm, { Mem, 0, 0} }, /* div reverse */ {"fdivr", 1, 0xd8f8, _, ShortForm, { FloatReg, 0, 0} }, {"fdivr", 2, 0xd8f8, _, ShortForm, { FloatReg, FloatAcc, 0} }, #ifdef NON_BROKEN_OPCODES {"fdivr", 2, 0xdcf0, _, ShortForm, { FloatAcc, FloatReg, 0} }, #else {"fdivr", 2, 0xdcf8, _, ShortForm, { FloatAcc, FloatReg, 0} }, #endif {"fdivr", 0, 0xdcf9, _, NoModrm, { 0, 0, 0} }, {"fdivrp", 1, 0xdaf8, _, ShortForm, { FloatReg, 0, 0} }, {"fdivrp", 2, 0xdaf8, _, ShortForm, { FloatReg, FloatAcc, 0} }, #ifdef NON_BROKEN_OPCODES {"fdivrp", 2, 0xdef0, _, ShortForm, { FloatAcc, FloatReg, 0} }, #else {"fdivrp", 2, 0xdef8, _, ShortForm, { FloatAcc, FloatReg, 0} }, #endif {"fdivrp", 0, 0xdef9, _, NoModrm, { 0, 0, 0} }, {"fdivrs", 1, 0xd8, 7, Modrm, { Mem, 0, 0} }, {"fidivrl", 1, 0xda, 7, Modrm, { Mem, 0, 0} }, {"fdivrl", 1, 0xdc, 7, Modrm, { Mem, 0, 0} }, {"fidivrs", 1, 0xde, 7, Modrm, { Mem, 0, 0} }, {"f2xm1", 0, 0xd9f0, _, NoModrm, { 0, 0, 0} }, {"fyl2x", 0, 0xd9f1, _, NoModrm, { 0, 0, 0} }, {"fptan", 0, 0xd9f2, _, NoModrm, { 0, 0, 0} }, {"fpatan", 0, 0xd9f3, _, NoModrm, { 0, 0, 0} }, {"fxtract", 0, 0xd9f4, _, NoModrm, { 0, 0, 0} }, {"fprem1", 0, 0xd9f5, _, NoModrm, { 0, 0, 0} }, {"fdecstp", 0, 0xd9f6, _, NoModrm, { 0, 0, 0} }, {"fincstp", 0, 0xd9f7, _, NoModrm, { 0, 0, 0} }, {"fprem", 0, 0xd9f8, _, NoModrm, { 0, 0, 0} }, {"fyl2xp1", 0, 0xd9f9, _, NoModrm, { 0, 0, 0} }, {"fsqrt", 0, 0xd9fa, _, NoModrm, { 0, 0, 0} }, {"fsincos", 0, 0xd9fb, _, NoModrm, { 0, 0, 0} }, {"frndint", 0, 0xd9fc, _, NoModrm, { 0, 0, 0} }, {"fscale", 0, 0xd9fd, _, NoModrm, { 0, 0, 0} }, {"fsin", 0, 0xd9fe, _, NoModrm, { 0, 0, 0} }, {"fcos", 0, 0xd9ff, _, NoModrm, { 0, 0, 0} }, {"fchs", 0, 0xd9e0, _, NoModrm, { 0, 0, 0} }, {"fabs", 0, 0xd9e1, _, NoModrm, { 0, 0, 0} }, /* processor control */ {"fninit", 0, 0xdbe3, _, NoModrm, { 0, 0, 0} }, {"finit", 0, 0x9bdbe3, _, NoModrm, { 0, 0, 0} }, {"fldcw", 1, 0xd9, 5, Modrm, { Mem, 0, 0} }, {"fnstcw", 1, 0xd9, 7, Modrm, { Mem, 0, 0} }, {"fstcw", 1, 0x9bd9, 7, Modrm, { Mem, 0, 0} }, {"fnstsw", 1, 0xdfe0, _, NoModrm, { Acc, 0, 0} }, {"fnstsw", 1, 0xdd, 7, Modrm, { Mem, 0, 0} }, {"fnstsw", 0, 0xdfe0, _, NoModrm, { 0, 0, 0} }, {"fstsw", 1, 0x9bdfe0, _, NoModrm, { Acc, 0, 0} }, {"fstsw", 1, 0x9bdd, 7, Modrm, { Mem, 0, 0} }, {"fstsw", 0, 0x9bdfe0, _, NoModrm, { 0, 0, 0} }, {"fnclex", 0, 0xdbe2, _, NoModrm, { 0, 0, 0} }, {"fclex", 0, 0x9bdbe2, _, NoModrm, { 0, 0, 0} }, /* We ignore the short format (287) versions of fstenv/fldenv & fsave/frstor instructions; i'm not sure how to add them or how they are different. My 386/387 book offers no details about this. */ {"fnstenv", 1, 0xd9, 6, Modrm, { Mem, 0, 0} }, {"fstenv", 1, 0x9bd9, 6, Modrm, { Mem, 0, 0} }, {"fldenv", 1, 0xd9, 4, Modrm, { Mem, 0, 0} }, {"fnsave", 1, 0xdd, 6, Modrm, { Mem, 0, 0} }, {"fsave", 1, 0x9bdd, 6, Modrm, { Mem, 0, 0} }, {"frstor", 1, 0xdd, 4, Modrm, { Mem, 0, 0} }, {"ffree", 1, 0xddc0, _, ShortForm, { FloatReg, 0, 0} }, {"fnop", 0, 0xd9d0, _, NoModrm, { 0, 0, 0} }, {"fwait", 0, 0x9b, _, NoModrm, { 0, 0, 0} }, /* opcode prefixes; we allow them as seperate insns too (see prefix table below) */ {"aword", 0, 0x67, _, NoModrm, { 0, 0, 0} }, {"addr16", 0, 0x67, _, NoModrm, { 0, 0, 0} }, {"word", 0, 0x66, _, NoModrm, { 0, 0, 0} }, {"data16", 0, 0x66, _, NoModrm, { 0, 0, 0} }, {"lock", 0, 0xf0, _, NoModrm, { 0, 0, 0} }, {"cs", 0, 0x2e, _, NoModrm, { 0, 0, 0} }, {"ds", 0, 0x3e, _, NoModrm, { 0, 0, 0} }, {"es", 0, 0x26, _, NoModrm, { 0, 0, 0} }, {"fs", 0, 0x64, _, NoModrm, { 0, 0, 0} }, {"gs", 0, 0x65, _, NoModrm, { 0, 0, 0} }, {"ss", 0, 0x36, _, NoModrm, { 0, 0, 0} }, {"rep", 0, 0xf3, _, NoModrm, { 0, 0, 0} }, {"repe", 0, 0xf3, _, NoModrm, { 0, 0, 0} }, {"repz", 0, 0xf3, _, NoModrm, { 0, 0, 0} }, {"repne", 0, 0xf2, _, NoModrm, { 0, 0, 0} }, {"repnz", 0, 0xf2, _, NoModrm, { 0, 0, 0} }, /* 486 extensions */ {"bswap", 1, 0x0fc8, _, ShortForm, { Reg32,0,0 } }, {"xadd", 2, 0x0fc0, _, DW|Modrm, { Reg, Reg|Mem, 0 } }, {"cmpxchg", 2, 0x0fb0, _, DW|Modrm, { Reg, Reg|Mem, 0 } }, {"invd", 0, 0x0f08, _, NoModrm, { 0, 0, 0} }, {"wbinvd", 0, 0x0f09, _, NoModrm, { 0, 0, 0} }, {"invlpg", 1, 0x0f01, 7, Modrm, { Mem, 0, 0} }, /* 586 and late 486 extensions */ {"cpuid", 0, 0x0fa2, _, NoModrm, { 0, 0, 0} }, /* Pentium extensions */ {"wrmsr", 0, 0x0f30, _, NoModrm, { 0, 0, 0} }, {"rdtsc", 0, 0x0f31, _, NoModrm, { 0, 0, 0} }, {"rdmsr", 0, 0x0f32, _, NoModrm, { 0, 0, 0} }, {"cmpxchg8b", 1, 0x0fc7, 1, Modrm, { Mem, 0, 0} }, /* Pentium Pro extensions */ {"rdpmc", 0, 0x0f33, _, NoModrm, { 0, 0, 0} }, {"cmovo", 2, 0x0f40, _, W|Modrm|ReverseRegRegmem, { WordReg|WordMem, WordReg, 0} }, {"cmovno", 2, 0x0f41, _, W|Modrm|ReverseRegRegmem, { WordReg|WordMem, WordReg, 0} }, {"cmovb", 2, 0x0f42, _, W|Modrm|ReverseRegRegmem, { WordReg|WordMem, WordReg, 0} }, {"cmovae", 2, 0x0f43, _, W|Modrm|ReverseRegRegmem, { WordReg|WordMem, WordReg, 0} }, {"cmove", 2, 0x0f44, _, W|Modrm|ReverseRegRegmem, { WordReg|WordMem, WordReg, 0} }, {"cmovne", 2, 0x0f45, _, W|Modrm|ReverseRegRegmem, { WordReg|WordMem, WordReg, 0} }, {"cmovbe", 2, 0x0f46, _, W|Modrm|ReverseRegRegmem, { WordReg|WordMem, WordReg, 0} }, {"cmova", 2, 0x0f47, _, W|Modrm|ReverseRegRegmem, { WordReg|WordMem, WordReg, 0} }, {"cmovs", 2, 0x0f48, _, W|Modrm|ReverseRegRegmem, { WordReg|WordMem, WordReg, 0} }, {"cmovns", 2, 0x0f49, _, W|Modrm|ReverseRegRegmem, { WordReg|WordMem, WordReg, 0} }, {"cmovp", 2, 0x0f4a, _, W|Modrm|ReverseRegRegmem, { WordReg|WordMem, WordReg, 0} }, {"cmovnp", 2, 0x0f4b, _, W|Modrm|ReverseRegRegmem, { WordReg|WordMem, WordReg, 0} }, {"cmovl", 2, 0x0f4c, _, W|Modrm|ReverseRegRegmem, { WordReg|WordMem, WordReg, 0} }, {"cmovge", 2, 0x0f4d, _, W|Modrm|ReverseRegRegmem, { WordReg|WordMem, WordReg, 0} }, {"cmovle", 2, 0x0f4e, _, W|Modrm|ReverseRegRegmem, { WordReg|WordMem, WordReg, 0} }, {"cmovg", 2, 0x0f4f, _, W|Modrm|ReverseRegRegmem, { WordReg|WordMem, WordReg, 0} }, {"fcmovb", 2, 0xdac0, _, ShortForm, { FloatReg, FloatAcc, 0} }, {"fcmove", 2, 0xdac8, _, ShortForm, { FloatReg, FloatAcc, 0} }, {"fcmovbe",2, 0xdad0, _, ShortForm, { FloatReg, FloatAcc, 0} }, {"fcmovu", 2, 0xdad8, _, ShortForm, { FloatReg, FloatAcc, 0} }, {"fcmovnb", 2, 0xdbc0, _, ShortForm, { FloatReg, FloatAcc, 0} }, {"fcmovne", 2, 0xdbc8, _, ShortForm, { FloatReg, FloatAcc, 0} }, {"fcmovnbe",2, 0xdbd0, _, ShortForm, { FloatReg, FloatAcc, 0} }, {"fcmovnu", 2, 0xdbd8, _, ShortForm, { FloatReg, FloatAcc, 0} }, {"fcomi", 2, 0xdbf0, _, ShortForm, { FloatReg, FloatAcc, 0} }, {"fucomi", 2, 0xdbe8, _, ShortForm, { FloatReg, FloatAcc, 0} }, {"fcomip", 2, 0xdff0, _, ShortForm, { FloatReg, FloatAcc, 0} }, {"fucomip",2, 0xdfe8, _, ShortForm, { FloatReg, FloatAcc, 0} }, {"", 0, 0, 0, 0, { 0, 0, 0} } /* sentinel */ }; #undef _ static const template *const i386_optab_end = i386_optab + sizeof (i386_optab)/sizeof(i386_optab[0]); /* 386 register table */ static const reg_entry i386_regtab[] = { /* 8 bit regs */ {"al", Reg8|Acc, 0}, {"cl", Reg8|ShiftCount, 1}, {"dl", Reg8, 2}, {"bl", Reg8, 3}, {"ah", Reg8, 4}, {"ch", Reg8, 5}, {"dh", Reg8, 6}, {"bh", Reg8, 7}, /* 16 bit regs */ {"ax", Reg16|Acc, 0}, {"cx", Reg16, 1}, {"dx", Reg16|InOutPortReg, 2}, {"bx", Reg16, 3}, {"sp", Reg16, 4}, {"bp", Reg16, 5}, {"si", Reg16, 6}, {"di", Reg16, 7}, /* 32 bit regs */ {"eax", Reg32|Acc, 0}, {"ecx", Reg32, 1}, {"edx", Reg32, 2}, {"ebx", Reg32, 3}, {"esp", Reg32, 4}, {"ebp", Reg32, 5}, {"esi", Reg32, 6}, {"edi", Reg32, 7}, /* segment registers */ {"es", SReg2, 0}, {"cs", SReg2, 1}, {"ss", SReg2, 2}, {"ds", SReg2, 3}, {"fs", SReg3, 4}, {"gs", SReg3, 5}, /* control registers */ {"cr0", Control, 0}, {"cr2", Control, 2}, {"cr3", Control, 3}, {"cr4", Control, 4}, /* debug registers */ {"db0", Debug, 0}, {"db1", Debug, 1}, {"db2", Debug, 2}, {"db3", Debug, 3}, {"db6", Debug, 6}, {"db7", Debug, 7}, {"dr0", Debug, 0}, {"dr1", Debug, 1}, {"dr2", Debug, 2}, {"dr3", Debug, 3}, {"dr6", Debug, 6}, {"dr7", Debug, 7}, /* test registers */ {"tr3", Test, 3}, {"tr4", Test, 4}, {"tr5", Test, 5}, {"tr6", Test, 6}, {"tr7", Test, 7}, /* float registers */ {"st(0)", FloatReg|FloatAcc, 0}, {"st", FloatReg|FloatAcc, 0}, {"st(1)", FloatReg, 1}, {"st(2)", FloatReg, 2}, {"st(3)", FloatReg, 3}, {"st(4)", FloatReg, 4}, {"st(5)", FloatReg, 5}, {"st(6)", FloatReg, 6}, {"st(7)", FloatReg, 7} }; #define MAX_REG_NAME_SIZE 8 /* for parsing register names from input */ static const reg_entry *const i386_regtab_end = i386_regtab + sizeof(i386_regtab)/sizeof(i386_regtab[0]); /* segment stuff */ static const seg_entry cs = { "cs", 0x2e }; static const seg_entry ds = { "ds", 0x3e }; static const seg_entry ss = { "ss", 0x36 }; static const seg_entry es = { "es", 0x26 }; static const seg_entry fs = { "fs", 0x64 }; static const seg_entry gs = { "gs", 0x65 }; static const seg_entry null = { "", 0x0 }; /* This table is used to store the default segment register implied by all possible memory addressing modes. It is indexed by the mode & modrm entries of the modrm byte as follows: index = (mode<<3) | modrm; */ static const seg_entry *const one_byte_segment_defaults[] = { /* mode 0 */ &ds, &ds, &ds, &ds, &null, &ds, &ds, &ds, /* mode 1 */ &ds, &ds, &ds, &ds, &null, &ss, &ds, &ds, /* mode 2 */ &ds, &ds, &ds, &ds, &null, &ss, &ds, &ds, /* mode 3 --- not a memory reference; never referenced */ }; static const seg_entry *const two_byte_segment_defaults[] = { /* mode 0 */ &ds, &ds, &ds, &ds, &ss, &ds, &ds, &ds, /* mode 1 */ &ds, &ds, &ds, &ds, &ss, &ds, &ds, &ds, /* mode 2 */ &ds, &ds, &ds, &ds, &ss, &ds, &ds, &ds, /* mode 3 --- not a memory reference; never referenced */ }; static const prefix_entry i386_prefixtab[] = { #define ADDR_PREFIX_OPCODE 0x67 { "addr16", 0x67 }, /* address size prefix ==> 16bit addressing * (How is this useful?) */ #define WORD_PREFIX_OPCODE 0x66 { "data16", 0x66 }, /* operand size prefix */ { "lock", 0xf0 }, /* bus lock prefix */ { "wait", 0x9b }, /* wait for coprocessor */ { "cs", 0x2e }, { "ds", 0x3e }, /* segment overrides ... */ { "es", 0x26 }, { "fs", 0x64 }, { "gs", 0x65 }, { "ss", 0x36 }, /* REPE & REPNE used to detect rep/repne with a non-string instruction */ #define REPNE 0xf2 #define REPE 0xf3 { "rep", 0xf3 }, /* repeat string instructions */ { "repe", 0xf3 }, { "repz", 0xf3 }, { "repne", 0xf2 }, { "repnz", 0xf2 } }; static const prefix_entry *const i386_prefixtab_end = i386_prefixtab + sizeof(i386_prefixtab)/sizeof(i386_prefixtab[0]); /* end of i386-opcode.h */ smalltalk-3.2.5/opcode/Makefile.in0000644000175000017500000004612012130455425013750 00000000000000# Makefile.in generated by automake 1.11.6 from Makefile.am. # @configure_input@ # Copyright (C) 1994, 1995, 1996, 1997, 1998, 1999, 2000, 2001, 2002, # 2003, 2004, 2005, 2006, 2007, 2008, 2009, 2010, 2011 Free Software # Foundation, Inc. # This Makefile.in is free software; the Free Software Foundation # gives unlimited permission to copy and/or distribute it, # with or without modifications, as long as this notice is preserved. # This program is distributed in the hope that it will be useful, # but WITHOUT ANY WARRANTY, to the extent permitted by law; without # even the implied warranty of MERCHANTABILITY or FITNESS FOR A # PARTICULAR PURPOSE. @SET_MAKE@ VPATH = @srcdir@ am__make_dryrun = \ { \ am__dry=no; \ case $$MAKEFLAGS in \ *\\[\ \ ]*) \ echo 'am--echo: ; @echo "AM" OK' | $(MAKE) -f - 2>/dev/null \ | grep '^AM OK$$' >/dev/null || am__dry=yes;; \ *) \ for am__flg in $$MAKEFLAGS; do \ case $$am__flg in \ *=*|--*) ;; \ *n*) am__dry=yes; break;; \ esac; \ done;; \ esac; \ test $$am__dry = yes; \ } pkgdatadir = $(datadir)/@PACKAGE@ pkgincludedir = $(includedir)/@PACKAGE@ pkglibdir = $(libdir)/@PACKAGE@ pkglibexecdir = $(libexecdir)/@PACKAGE@ am__cd = CDPATH="$${ZSH_VERSION+.}$(PATH_SEPARATOR)" && cd install_sh_DATA = $(install_sh) -c -m 644 install_sh_PROGRAM = $(install_sh) -c install_sh_SCRIPT = $(install_sh) -c INSTALL_HEADER = $(INSTALL_DATA) transform = $(program_transform_name) NORMAL_INSTALL = : PRE_INSTALL = : POST_INSTALL = : NORMAL_UNINSTALL = : PRE_UNINSTALL = : POST_UNINSTALL = : build_triplet = @build@ host_triplet = @host@ subdir = opcode DIST_COMMON = $(noinst_HEADERS) $(srcdir)/Makefile.am \ $(srcdir)/Makefile.in ACLOCAL_M4 = $(top_srcdir)/aclocal.m4 am__aclocal_m4_deps = $(top_srcdir)/build-aux/bold.m4 \ $(top_srcdir)/build-aux/codeset.m4 \ $(top_srcdir)/build-aux/emacs-pkg.m4 \ $(top_srcdir)/build-aux/emacs-site-start.m4 \ $(top_srcdir)/build-aux/ext_goto.m4 \ $(top_srcdir)/build-aux/gawk.m4 $(top_srcdir)/build-aux/gcc.m4 \ $(top_srcdir)/build-aux/gl.m4 \ $(top_srcdir)/build-aux/glib-2.0.m4 \ $(top_srcdir)/build-aux/glut.m4 $(top_srcdir)/build-aux/gmp.m4 \ $(top_srcdir)/build-aux/gst-package.m4 \ $(top_srcdir)/build-aux/gtk-2.0.m4 \ $(top_srcdir)/build-aux/iconv.m4 \ $(top_srcdir)/build-aux/lib-ld.m4 \ $(top_srcdir)/build-aux/lib-link.m4 \ $(top_srcdir)/build-aux/lib-prefix.m4 \ $(top_srcdir)/build-aux/lib.m4 \ $(top_srcdir)/build-aux/libc-so-name.m4 \ $(top_srcdir)/build-aux/libtool.m4 \ $(top_srcdir)/build-aux/lightning.m4 \ $(top_srcdir)/build-aux/ln.m4 \ $(top_srcdir)/build-aux/localtime.m4 \ $(top_srcdir)/build-aux/lock.m4 \ $(top_srcdir)/build-aux/long-double.m4 \ $(top_srcdir)/build-aux/lrint.m4 \ $(top_srcdir)/build-aux/ltdl-gst.m4 \ $(top_srcdir)/build-aux/ltoptions.m4 \ $(top_srcdir)/build-aux/ltsugar.m4 \ $(top_srcdir)/build-aux/ltversion.m4 \ $(top_srcdir)/build-aux/lt~obsolete.m4 \ $(top_srcdir)/build-aux/modules.m4 \ $(top_srcdir)/build-aux/pkg.m4 $(top_srcdir)/build-aux/poll.m4 \ $(top_srcdir)/build-aux/readline.m4 \ $(top_srcdir)/build-aux/relocatable.m4 \ $(top_srcdir)/build-aux/setenv.m4 \ $(top_srcdir)/build-aux/snprintfv.m4 \ $(top_srcdir)/build-aux/sockets.m4 \ $(top_srcdir)/build-aux/sockpfaf.m4 \ $(top_srcdir)/build-aux/strtoul.m4 \ $(top_srcdir)/build-aux/sync-builtins.m4 \ $(top_srcdir)/build-aux/tcltk.m4 \ $(top_srcdir)/build-aux/version.m4 \ $(top_srcdir)/build-aux/vis-hidden.m4 \ $(top_srcdir)/build-aux/wine.m4 $(top_srcdir)/configure.ac am__configure_deps = $(am__aclocal_m4_deps) $(CONFIGURE_DEPENDENCIES) \ $(ACLOCAL_M4) mkinstalldirs = $(install_sh) -d CONFIG_HEADER = $(top_builddir)/config.h CONFIG_CLEAN_FILES = CONFIG_CLEAN_VPATH_FILES = LTLIBRARIES = $(noinst_LTLIBRARIES) libdisass_la_LIBADD = am_libdisass_la_OBJECTS = dis-buf.lo i386-dis.lo ppc-dis.lo ppc-opc.lo \ sparc-dis.lo sparc-opc.lo disass.lo libdisass_la_OBJECTS = $(am_libdisass_la_OBJECTS) DEFAULT_INCLUDES = -I.@am__isrc@ -I$(top_builddir) depcomp = $(SHELL) $(top_srcdir)/build-aux/depcomp am__depfiles_maybe = depfiles am__mv = mv -f COMPILE = $(CC) $(DEFS) $(DEFAULT_INCLUDES) $(INCLUDES) $(AM_CPPFLAGS) \ $(CPPFLAGS) $(AM_CFLAGS) $(CFLAGS) LTCOMPILE = $(LIBTOOL) --tag=CC $(AM_LIBTOOLFLAGS) $(LIBTOOLFLAGS) \ --mode=compile $(CC) $(DEFS) $(DEFAULT_INCLUDES) $(INCLUDES) \ $(AM_CPPFLAGS) $(CPPFLAGS) $(AM_CFLAGS) $(CFLAGS) CCLD = $(CC) LINK = $(LIBTOOL) --tag=CC $(AM_LIBTOOLFLAGS) $(LIBTOOLFLAGS) \ --mode=link $(CCLD) $(AM_CFLAGS) $(CFLAGS) $(AM_LDFLAGS) \ $(LDFLAGS) -o $@ SOURCES = $(libdisass_la_SOURCES) DIST_SOURCES = $(libdisass_la_SOURCES) am__can_run_installinfo = \ case $$AM_UPDATE_INFO_DIR in \ n|no|NO) false;; \ *) (install-info --version) >/dev/null 2>&1;; \ esac HEADERS = $(noinst_HEADERS) ETAGS = etags CTAGS = ctags DISTFILES = $(DIST_COMMON) $(DIST_SOURCES) $(TEXINFOS) $(EXTRA_DIST) ACLOCAL = @ACLOCAL@ ALLOCA = @ALLOCA@ ALL_PACKAGES = @ALL_PACKAGES@ AMTAR = @AMTAR@ AR = @AR@ AS = @AS@ ATK_CFLAGS = @ATK_CFLAGS@ ATK_LIBS = @ATK_LIBS@ AUTOCONF = @AUTOCONF@ AUTOHEADER = @AUTOHEADER@ AUTOM4TE = @AUTOM4TE@ AUTOMAKE = @AUTOMAKE@ AWK = @AWK@ BLOX_IMPLEMENTATION = @BLOX_IMPLEMENTATION@ BUILT_PACKAGES = @BUILT_PACKAGES@ CAIRO_CFLAGS = @CAIRO_CFLAGS@ CAIRO_LIBS = @CAIRO_LIBS@ CC = @CC@ CCDEPMODE = @CCDEPMODE@ CFLAGS = @CFLAGS@ CPP = @CPP@ CPPFLAGS = @CPPFLAGS@ CYGPATH_W = @CYGPATH_W@ DEFS = @DEFS@ DEPDIR = @DEPDIR@ DLLTOOL = @DLLTOOL@ DSYMUTIL = @DSYMUTIL@ DUMPBIN = @DUMPBIN@ ECHO_C = @ECHO_C@ ECHO_N = @ECHO_N@ ECHO_T = @ECHO_T@ EGREP = @EGREP@ EMACS = @EMACS@ EMACSLOADPATH = @EMACSLOADPATH@ EXEEXT = @EXEEXT@ FGREP = @FGREP@ GLIB_CFLAGS = @GLIB_CFLAGS@ GLIB_GENMARSHAL = @GLIB_GENMARSHAL@ GLIB_LIBS = @GLIB_LIBS@ GLIB_MKENUMS = @GLIB_MKENUMS@ GNUTLS_CFLAGS = @GNUTLS_CFLAGS@ GNUTLS_LIBS = @GNUTLS_LIBS@ GOBJECT_QUERY = @GOBJECT_QUERY@ GPERF = @GPERF@ GREP = @GREP@ GST_RUN = @GST_RUN@ GTHREAD_CFLAGS = @GTHREAD_CFLAGS@ GTHREAD_LIBS = @GTHREAD_LIBS@ GTK_CFLAGS = @GTK_CFLAGS@ GTK_LIBS = @GTK_LIBS@ ICON = @ICON@ INCFFI = @INCFFI@ INCLTDL = @INCLTDL@ INCSIGSEGV = @INCSIGSEGV@ INCSNPRINTFV = @INCSNPRINTFV@ INCTCLTK = @INCTCLTK@ INSTALL = @INSTALL@ INSTALL_DATA = @INSTALL_DATA@ INSTALL_INFO = @INSTALL_INFO@ INSTALL_PROGRAM = @INSTALL_PROGRAM@ INSTALL_SCRIPT = @INSTALL_SCRIPT@ INSTALL_STRIP_PROGRAM = @INSTALL_STRIP_PROGRAM@ LD = @LD@ LDFLAGS = @LDFLAGS@ LEX = @LEX@ LIBADD_DL = @LIBADD_DL@ LIBC_SO_DIR = @LIBC_SO_DIR@ LIBC_SO_NAME = @LIBC_SO_NAME@ LIBFFI = @LIBFFI@ LIBFFI_CFLAGS = @LIBFFI_CFLAGS@ LIBFFI_EXECUTABLE_LDFLAGS = @LIBFFI_EXECUTABLE_LDFLAGS@ LIBFFI_LIBS = @LIBFFI_LIBS@ LIBGLUT = @LIBGLUT@ LIBGMP = @LIBGMP@ LIBGST_CFLAGS = @LIBGST_CFLAGS@ LIBICONV = @LIBICONV@ LIBLTDL = @LIBLTDL@ LIBOBJS = @LIBOBJS@ LIBOPENGL = @LIBOPENGL@ LIBREADLINE = @LIBREADLINE@ LIBS = @LIBS@ LIBSIGSEGV = @LIBSIGSEGV@ LIBSNPRINTFV = @LIBSNPRINTFV@ LIBTCLTK = @LIBTCLTK@ LIBTHREAD = @LIBTHREAD@ LIBTOOL = @LIBTOOL@ LIPO = @LIPO@ LN = @LN@ LN_S = @LN_S@ LTALLOCA = @LTALLOCA@ LTLIBICONV = @LTLIBICONV@ LTLIBOBJS = @LTLIBOBJS@ MAINTAINER = @MAINTAINER@ MAKEINFO = @MAKEINFO@ MANIFEST_TOOL = @MANIFEST_TOOL@ MKDIR_P = @MKDIR_P@ MODULES = @MODULES@ NM = @NM@ NMEDIT = @NMEDIT@ OBJC = @OBJC@ OBJCDEPMODE = @OBJCDEPMODE@ OBJCFLAGS = @OBJCFLAGS@ OBJDUMP = @OBJDUMP@ OBJEXT = @OBJEXT@ OTOOL = @OTOOL@ OTOOL64 = @OTOOL64@ PACKAGE = @PACKAGE@ PACKAGE_BUGREPORT = @PACKAGE_BUGREPORT@ PACKAGE_DLOPEN_FLAGS = @PACKAGE_DLOPEN_FLAGS@ PACKAGE_NAME = @PACKAGE_NAME@ PACKAGE_STRING = @PACKAGE_STRING@ PACKAGE_TARNAME = @PACKAGE_TARNAME@ PACKAGE_URL = @PACKAGE_URL@ PACKAGE_VERSION = @PACKAGE_VERSION@ PANGO_CFLAGS = @PANGO_CFLAGS@ PANGO_LIBS = @PANGO_LIBS@ PATH_SEPARATOR = @PATH_SEPARATOR@ PKG_CONFIG = @PKG_CONFIG@ RANLIB = @RANLIB@ RELOCATABLE = @RELOCATABLE@ RELOC_CPPFLAGS = @RELOC_CPPFLAGS@ RELOC_LDFLAGS = @RELOC_LDFLAGS@ SDL_CFLAGS = @SDL_CFLAGS@ SDL_LIBS = @SDL_LIBS@ SED = @SED@ SET_MAKE = @SET_MAKE@ SHELL = @SHELL@ SOCKET_LIBS = @SOCKET_LIBS@ STRIP = @STRIP@ SYNC_CFLAGS = @SYNC_CFLAGS@ TCLSH = @TCLSH@ TIMEOUT = @TIMEOUT@ VERSION = @VERSION@ VERSION_INFO = @VERSION_INFO@ WINDRES = @WINDRES@ WINEWRAPPER = @WINEWRAPPER@ WINEWRAPPERDEP = @WINEWRAPPERDEP@ XMKMF = @XMKMF@ XZIP = @XZIP@ X_CFLAGS = @X_CFLAGS@ X_EXTRA_LIBS = @X_EXTRA_LIBS@ X_LIBS = @X_LIBS@ X_PRE_LIBS = @X_PRE_LIBS@ YACC = @YACC@ ZIP = @ZIP@ abs_builddir = @abs_builddir@ abs_srcdir = @abs_srcdir@ abs_top_builddir = @abs_top_builddir@ abs_top_srcdir = @abs_top_srcdir@ ac_ct_AR = @ac_ct_AR@ ac_ct_CC = @ac_ct_CC@ ac_ct_DUMPBIN = @ac_ct_DUMPBIN@ am__include = @am__include@ am__leading_dot = @am__leading_dot@ am__quote = @am__quote@ am__tar = @am__tar@ am__untar = @am__untar@ bindir = @bindir@ build = @build@ build_alias = @build_alias@ build_cpu = @build_cpu@ build_os = @build_os@ build_vendor = @build_vendor@ builddir = @builddir@ datadir = @datadir@ datarootdir = @datarootdir@ docdir = @docdir@ dvidir = @dvidir@ enable_mysql_tests = @enable_mysql_tests@ exec_prefix = @exec_prefix@ host = @host@ host_alias = @host_alias@ host_cpu = @host_cpu@ host_os = @host_os@ host_vendor = @host_vendor@ htmldir = @htmldir@ imagedir = @imagedir@ includedir = @includedir@ infodir = @infodir@ install_sh = @install_sh@ libdir = @libdir@ libexecdir = @libexecdir@ lispdir = @lispdir@ lispstartdir = @lispstartdir@ localedir = @localedir@ localstatedir = @localstatedir@ mandir = @mandir@ mkdir_p = @mkdir_p@ moduledir = @moduledir@ moduleexecdir = @moduleexecdir@ oldincludedir = @oldincludedir@ pdfdir = @pdfdir@ prefix = @prefix@ program_transform_name = @program_transform_name@ psdir = @psdir@ sbindir = @sbindir@ sharedstatedir = @sharedstatedir@ srcdir = @srcdir@ subdirs = @subdirs@ sysconfdir = @sysconfdir@ target_alias = @target_alias@ top_build_prefix = @top_build_prefix@ top_builddir = @top_builddir@ top_srcdir = @top_srcdir@ noinst_LTLIBRARIES = libdisass.la AM_CPPFLAGS = -I$(top_srcdir) libdisass_la_SOURCES = dis-buf.c i386-dis.c ppc-dis.c ppc-opc.c sparc-dis.c \ sparc-opc.c disass.c noinst_HEADERS = ansidecl.h bfd.h dis-asm.h i386.h ppc.h sparc.h sysdep.h all: all-am .SUFFIXES: .SUFFIXES: .c .lo .o .obj $(srcdir)/Makefile.in: $(srcdir)/Makefile.am $(am__configure_deps) @for dep in $?; do \ case '$(am__configure_deps)' in \ *$$dep*) \ ( cd $(top_builddir) && $(MAKE) $(AM_MAKEFLAGS) am--refresh ) \ && { if test -f $@; then exit 0; else break; fi; }; \ exit 1;; \ esac; \ done; \ echo ' cd $(top_srcdir) && $(AUTOMAKE) --gnu opcode/Makefile'; \ $(am__cd) $(top_srcdir) && \ $(AUTOMAKE) --gnu opcode/Makefile .PRECIOUS: Makefile Makefile: $(srcdir)/Makefile.in $(top_builddir)/config.status @case '$?' in \ *config.status*) \ cd $(top_builddir) && $(MAKE) $(AM_MAKEFLAGS) am--refresh;; \ *) \ echo ' cd $(top_builddir) && $(SHELL) ./config.status $(subdir)/$@ $(am__depfiles_maybe)'; \ cd $(top_builddir) && $(SHELL) ./config.status $(subdir)/$@ $(am__depfiles_maybe);; \ esac; $(top_builddir)/config.status: $(top_srcdir)/configure $(CONFIG_STATUS_DEPENDENCIES) cd $(top_builddir) && $(MAKE) $(AM_MAKEFLAGS) am--refresh $(top_srcdir)/configure: $(am__configure_deps) cd $(top_builddir) && $(MAKE) $(AM_MAKEFLAGS) am--refresh $(ACLOCAL_M4): $(am__aclocal_m4_deps) cd $(top_builddir) && $(MAKE) $(AM_MAKEFLAGS) am--refresh $(am__aclocal_m4_deps): clean-noinstLTLIBRARIES: -test -z "$(noinst_LTLIBRARIES)" || rm -f $(noinst_LTLIBRARIES) @list='$(noinst_LTLIBRARIES)'; for p in $$list; do \ dir="`echo $$p | sed -e 's|/[^/]*$$||'`"; \ test "$$dir" != "$$p" || dir=.; \ echo "rm -f \"$${dir}/so_locations\""; \ rm -f "$${dir}/so_locations"; \ done libdisass.la: $(libdisass_la_OBJECTS) $(libdisass_la_DEPENDENCIES) $(EXTRA_libdisass_la_DEPENDENCIES) $(LINK) $(libdisass_la_OBJECTS) $(libdisass_la_LIBADD) $(LIBS) mostlyclean-compile: -rm -f *.$(OBJEXT) distclean-compile: -rm -f *.tab.c @AMDEP_TRUE@@am__include@ @am__quote@./$(DEPDIR)/dis-buf.Plo@am__quote@ @AMDEP_TRUE@@am__include@ @am__quote@./$(DEPDIR)/disass.Plo@am__quote@ @AMDEP_TRUE@@am__include@ @am__quote@./$(DEPDIR)/i386-dis.Plo@am__quote@ @AMDEP_TRUE@@am__include@ @am__quote@./$(DEPDIR)/ppc-dis.Plo@am__quote@ @AMDEP_TRUE@@am__include@ @am__quote@./$(DEPDIR)/ppc-opc.Plo@am__quote@ @AMDEP_TRUE@@am__include@ @am__quote@./$(DEPDIR)/sparc-dis.Plo@am__quote@ @AMDEP_TRUE@@am__include@ @am__quote@./$(DEPDIR)/sparc-opc.Plo@am__quote@ .c.o: @am__fastdepCC_TRUE@ $(COMPILE) -MT $@ -MD -MP -MF $(DEPDIR)/$*.Tpo -c -o $@ $< @am__fastdepCC_TRUE@ $(am__mv) $(DEPDIR)/$*.Tpo $(DEPDIR)/$*.Po @AMDEP_TRUE@@am__fastdepCC_FALSE@ source='$<' object='$@' libtool=no @AMDEPBACKSLASH@ @AMDEP_TRUE@@am__fastdepCC_FALSE@ DEPDIR=$(DEPDIR) $(CCDEPMODE) $(depcomp) @AMDEPBACKSLASH@ @am__fastdepCC_FALSE@ $(COMPILE) -c $< .c.obj: @am__fastdepCC_TRUE@ $(COMPILE) -MT $@ -MD -MP -MF $(DEPDIR)/$*.Tpo -c -o $@ `$(CYGPATH_W) '$<'` @am__fastdepCC_TRUE@ $(am__mv) $(DEPDIR)/$*.Tpo $(DEPDIR)/$*.Po @AMDEP_TRUE@@am__fastdepCC_FALSE@ source='$<' object='$@' libtool=no @AMDEPBACKSLASH@ @AMDEP_TRUE@@am__fastdepCC_FALSE@ DEPDIR=$(DEPDIR) $(CCDEPMODE) $(depcomp) @AMDEPBACKSLASH@ @am__fastdepCC_FALSE@ $(COMPILE) -c `$(CYGPATH_W) '$<'` .c.lo: @am__fastdepCC_TRUE@ $(LTCOMPILE) -MT $@ -MD -MP -MF $(DEPDIR)/$*.Tpo -c -o $@ $< @am__fastdepCC_TRUE@ $(am__mv) $(DEPDIR)/$*.Tpo $(DEPDIR)/$*.Plo @AMDEP_TRUE@@am__fastdepCC_FALSE@ source='$<' object='$@' libtool=yes @AMDEPBACKSLASH@ @AMDEP_TRUE@@am__fastdepCC_FALSE@ DEPDIR=$(DEPDIR) $(CCDEPMODE) $(depcomp) @AMDEPBACKSLASH@ @am__fastdepCC_FALSE@ $(LTCOMPILE) -c -o $@ $< mostlyclean-libtool: -rm -f *.lo clean-libtool: -rm -rf .libs _libs ID: $(HEADERS) $(SOURCES) $(LISP) $(TAGS_FILES) list='$(SOURCES) $(HEADERS) $(LISP) $(TAGS_FILES)'; \ unique=`for i in $$list; do \ if test -f "$$i"; then echo $$i; else echo $(srcdir)/$$i; fi; \ done | \ $(AWK) '{ files[$$0] = 1; nonempty = 1; } \ END { if (nonempty) { for (i in files) print i; }; }'`; \ mkid -fID $$unique tags: TAGS TAGS: $(HEADERS) $(SOURCES) $(TAGS_DEPENDENCIES) \ $(TAGS_FILES) $(LISP) set x; \ here=`pwd`; \ list='$(SOURCES) $(HEADERS) $(LISP) $(TAGS_FILES)'; \ unique=`for i in $$list; do \ if test -f "$$i"; then echo $$i; else echo $(srcdir)/$$i; fi; \ done | \ $(AWK) '{ files[$$0] = 1; nonempty = 1; } \ END { if (nonempty) { for (i in files) print i; }; }'`; \ shift; \ if test -z "$(ETAGS_ARGS)$$*$$unique"; then :; else \ test -n "$$unique" || unique=$$empty_fix; \ if test $$# -gt 0; then \ $(ETAGS) $(ETAGSFLAGS) $(AM_ETAGSFLAGS) $(ETAGS_ARGS) \ "$$@" $$unique; \ else \ $(ETAGS) $(ETAGSFLAGS) $(AM_ETAGSFLAGS) $(ETAGS_ARGS) \ $$unique; \ fi; \ fi ctags: CTAGS CTAGS: $(HEADERS) $(SOURCES) $(TAGS_DEPENDENCIES) \ $(TAGS_FILES) $(LISP) list='$(SOURCES) $(HEADERS) $(LISP) $(TAGS_FILES)'; \ unique=`for i in $$list; do \ if test -f "$$i"; then echo $$i; else echo $(srcdir)/$$i; fi; \ done | \ $(AWK) '{ files[$$0] = 1; nonempty = 1; } \ END { if (nonempty) { for (i in files) print i; }; }'`; \ test -z "$(CTAGS_ARGS)$$unique" \ || $(CTAGS) $(CTAGSFLAGS) $(AM_CTAGSFLAGS) $(CTAGS_ARGS) \ $$unique GTAGS: here=`$(am__cd) $(top_builddir) && pwd` \ && $(am__cd) $(top_srcdir) \ && gtags -i $(GTAGS_ARGS) "$$here" distclean-tags: -rm -f TAGS ID GTAGS GRTAGS GSYMS GPATH tags distdir: $(DISTFILES) @srcdirstrip=`echo "$(srcdir)" | sed 's/[].[^$$\\*]/\\\\&/g'`; \ topsrcdirstrip=`echo "$(top_srcdir)" | sed 's/[].[^$$\\*]/\\\\&/g'`; \ list='$(DISTFILES)'; \ dist_files=`for file in $$list; do echo $$file; done | \ sed -e "s|^$$srcdirstrip/||;t" \ -e "s|^$$topsrcdirstrip/|$(top_builddir)/|;t"`; \ case $$dist_files in \ */*) $(MKDIR_P) `echo "$$dist_files" | \ sed '/\//!d;s|^|$(distdir)/|;s,/[^/]*$$,,' | \ sort -u` ;; \ esac; \ for file in $$dist_files; do \ if test -f $$file || test -d $$file; then d=.; else d=$(srcdir); fi; \ if test -d $$d/$$file; then \ dir=`echo "/$$file" | sed -e 's,/[^/]*$$,,'`; \ if test -d "$(distdir)/$$file"; then \ find "$(distdir)/$$file" -type d ! -perm -700 -exec chmod u+rwx {} \;; \ fi; \ if test -d $(srcdir)/$$file && test $$d != $(srcdir); then \ cp -fpR $(srcdir)/$$file "$(distdir)$$dir" || exit 1; \ find "$(distdir)/$$file" -type d ! -perm -700 -exec chmod u+rwx {} \;; \ fi; \ cp -fpR $$d/$$file "$(distdir)$$dir" || exit 1; \ else \ test -f "$(distdir)/$$file" \ || cp -p $$d/$$file "$(distdir)/$$file" \ || exit 1; \ fi; \ done check-am: all-am check: check-am all-am: Makefile $(LTLIBRARIES) $(HEADERS) installdirs: install: install-am install-exec: install-exec-am install-data: install-data-am uninstall: uninstall-am install-am: all-am @$(MAKE) $(AM_MAKEFLAGS) install-exec-am install-data-am installcheck: installcheck-am install-strip: if test -z '$(STRIP)'; then \ $(MAKE) $(AM_MAKEFLAGS) INSTALL_PROGRAM="$(INSTALL_STRIP_PROGRAM)" \ install_sh_PROGRAM="$(INSTALL_STRIP_PROGRAM)" INSTALL_STRIP_FLAG=-s \ install; \ else \ $(MAKE) $(AM_MAKEFLAGS) INSTALL_PROGRAM="$(INSTALL_STRIP_PROGRAM)" \ install_sh_PROGRAM="$(INSTALL_STRIP_PROGRAM)" INSTALL_STRIP_FLAG=-s \ "INSTALL_PROGRAM_ENV=STRIPPROG='$(STRIP)'" install; \ fi mostlyclean-generic: clean-generic: distclean-generic: -test -z "$(CONFIG_CLEAN_FILES)" || rm -f $(CONFIG_CLEAN_FILES) -test . = "$(srcdir)" || test -z "$(CONFIG_CLEAN_VPATH_FILES)" || rm -f $(CONFIG_CLEAN_VPATH_FILES) maintainer-clean-generic: @echo "This command is intended for maintainers to use" @echo "it deletes files that may require special tools to rebuild." clean: clean-am clean-am: clean-generic clean-libtool clean-noinstLTLIBRARIES \ mostlyclean-am distclean: distclean-am -rm -rf ./$(DEPDIR) -rm -f Makefile distclean-am: clean-am distclean-compile distclean-generic \ distclean-tags dvi: dvi-am dvi-am: html: html-am html-am: info: info-am info-am: install-data-am: install-dvi: install-dvi-am install-dvi-am: install-exec-am: install-html: install-html-am install-html-am: install-info: install-info-am install-info-am: install-man: install-pdf: install-pdf-am install-pdf-am: install-ps: install-ps-am install-ps-am: installcheck-am: maintainer-clean: maintainer-clean-am -rm -rf ./$(DEPDIR) -rm -f Makefile maintainer-clean-am: distclean-am maintainer-clean-generic mostlyclean: mostlyclean-am mostlyclean-am: mostlyclean-compile mostlyclean-generic \ mostlyclean-libtool pdf: pdf-am pdf-am: ps: ps-am ps-am: uninstall-am: .MAKE: install-am install-strip .PHONY: CTAGS GTAGS all all-am check check-am clean clean-generic \ clean-libtool clean-noinstLTLIBRARIES ctags distclean \ distclean-compile distclean-generic distclean-libtool \ distclean-tags distdir dvi dvi-am html html-am info info-am \ install install-am install-data install-data-am install-dvi \ install-dvi-am install-exec install-exec-am install-html \ install-html-am install-info install-info-am install-man \ install-pdf install-pdf-am install-ps install-ps-am \ install-strip installcheck installcheck-am installdirs \ maintainer-clean maintainer-clean-generic mostlyclean \ mostlyclean-compile mostlyclean-generic mostlyclean-libtool \ pdf pdf-am ps ps-am tags uninstall uninstall-am # Tell versions [3.59,3.63) of GNU make to not export all variables. # Otherwise a system limit (for SysV at least) may be exceeded. .NOEXPORT: smalltalk-3.2.5/opcode/sysdep.h0000644000175000017500000000007312123404352013353 00000000000000#include #include #include smalltalk-3.2.5/opcode/bfd.h0000644000175000017500000001603212123404352012601 00000000000000/* Main header file for the bfd library -- portable access to object files. Copyright 1990, 91, 92, 93, 94, 95, 1996 Free Software Foundation, Inc. Contributed by Cygnus Support. This file is part of BFD, the Binary File Descriptor library. (Simplified and modified for GNU lightning) This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2 of the License, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. */ /* bfd.h -- The only header file required by users of the bfd library The bfd.h file is generated from bfd-in.h and various .c files; if you change it, your changes will probably be lost. All the prototypes and definitions following the comment "THE FOLLOWING IS EXTRACTED FROM THE SOURCE" are extracted from the source files for BFD. If you change it, someone oneday will extract it from the source again, and your changes will be lost. To save yourself from this bind, change the definitions in the source in the bfd directory. Type "make docs" and then "make headers" in that directory, and magically this file will change to reflect your changes. If you don't have the tools to perform the extraction, then you are safe from someone on your system trampling over your header files. You should still maintain the equivalence between the source and this file though; every change you make to the .c file should be reflected here. */ #ifndef __BFD_H_SEEN__ #define __BFD_H_SEEN__ #include "ansidecl.h" #ifndef INLINE #if __GNUC__ >= 2 #define INLINE __inline__ #else #define INLINE #endif #endif /* To squelch erroneous compiler warnings ("illegal pointer combination") from the SVR3 compiler, we would like to typedef boolean to int (it doesn't like functions which return boolean. Making sure they are never implicitly declared to return int doesn't seem to help). But this file is not configured based on the host. */ /* General rules: functions which are boolean return true on success and false on failure (unless they're a predicate). -- bfd.doc */ /* I'm sure this is going to break something and someone is going to force me to change it. */ /* typedef enum boolean {false, true} boolean; */ /* Yup, SVR4 has a "typedef enum boolean" in -fnf */ /* It gets worse if the host also defines a true/false enum... -sts */ /* And even worse if your compiler has built-in boolean types... -law */ #if defined (__GNUG__) && (__GNUC_MINOR__ > 5) #define TRUE_FALSE_ALREADY_DEFINED #endif #ifdef MPW /* Pre-emptive strike - get the file with the enum. */ #include #define TRUE_FALSE_ALREADY_DEFINED #endif /* MPW */ #ifndef TRUE_FALSE_ALREADY_DEFINED typedef enum bfd_boolean {false, true} boolean; #define BFD_TRUE_FALSE #else /* Use enum names that will appear nowhere else. */ typedef enum bfd_boolean {bfd_fffalse, bfd_tttrue} boolean; #endif /* A pointer to a position in a file. */ /* FIXME: This should be using off_t from . For now, try to avoid breaking stuff by not including here. This will break on systems with 64-bit file offsets (e.g. 4.4BSD). Probably the best long-term answer is to avoid using file_ptr AND off_t in this header file, and to handle this in the BFD implementation rather than in its interface. */ /* typedef off_t file_ptr; */ typedef long int file_ptr; /* Represent a target address. Also used as a generic unsigned type which is guaranteed to be big enough to hold any arithmetic types we need to deal with. */ typedef unsigned long bfd_vma; /* A generic signed type which is guaranteed to be big enough to hold any arithmetic types we need to deal with. Can be assumed to be compatible with bfd_vma in the same way that signed and unsigned ints are compatible (as parameters, in assignment, etc). */ typedef long bfd_signed_vma; typedef unsigned long symvalue; typedef unsigned long bfd_size_type; /* Print a bfd_vma x on stream s. */ #define fprintf_vma(s,x) fprintf(s, "%08lx", x) #define sprintf_vma(s,x) sprintf(s, "%08lx", x) #define printf_vma(x) fprintf_vma(stdout,x) typedef unsigned int flagword; /* 32 bits of flags */ typedef unsigned char bfd_byte; enum bfd_architecture { bfd_arch_unknown, /* File arch not known */ bfd_arch_obscure, /* Arch known, not one of these */ bfd_arch_m68k, /* Motorola 68xxx */ bfd_arch_vax, /* DEC Vax */ bfd_arch_i960, /* Intel 960 */ /* The order of the following is important. lower number indicates a machine type that only accepts a subset of the instructions available to machines with higher numbers. The exception is the "ca", which is incompatible with all other machines except "core". */ #define bfd_mach_i960_core 1 #define bfd_mach_i960_ka_sa 2 #define bfd_mach_i960_kb_sb 3 #define bfd_mach_i960_mc 4 #define bfd_mach_i960_xa 5 #define bfd_mach_i960_ca 6 #define bfd_mach_i960_jx 7 #define bfd_mach_i960_hx 8 bfd_arch_a29k, /* AMD 29000 */ bfd_arch_sparc, /* SPARC */ #define bfd_mach_sparc 1 /* The difference between v8plus and v9 is that v9 is a true 64 bit env. */ #define bfd_mach_sparc_v8plus 2 #define bfd_mach_sparc_v8plusa 3 /* with ultrasparc add'ns */ #define bfd_mach_sparc_v9 4 #define bfd_mach_sparc_v9a 5 /* with ultrasparc add'ns */ /* Nonzero if MACH has the v9 instruction set. */ #define bfd_mach_sparc_v9_p(mach) ((mach) != bfd_mach_sparc) bfd_arch_mips, /* MIPS Rxxxx */ bfd_arch_i386, /* Intel 386 */ bfd_arch_we32k, /* AT&T WE32xxx */ bfd_arch_tahoe, /* CCI/Harris Tahoe */ bfd_arch_i860, /* Intel 860 */ bfd_arch_romp, /* IBM ROMP PC/RT */ bfd_arch_alliant, /* Alliant */ bfd_arch_convex, /* Convex */ bfd_arch_m88k, /* Motorola 88xxx */ bfd_arch_pyramid, /* Pyramid Technology */ bfd_arch_h8300, /* Hitachi H8/300 */ #define bfd_mach_h8300 1 #define bfd_mach_h8300h 2 bfd_arch_powerpc, /* PowerPC */ bfd_arch_rs6000, /* IBM RS/6000 */ bfd_arch_hppa, /* HP PA RISC */ bfd_arch_z8k, /* Zilog Z8000 */ #define bfd_mach_z8001 1 #define bfd_mach_z8002 2 bfd_arch_h8500, /* Hitachi H8/500 */ bfd_arch_sh, /* Hitachi SH */ bfd_arch_alpha, /* Dec Alpha */ bfd_arch_arm, /* Advanced Risc Machines ARM */ bfd_arch_ns32k, /* National Semiconductors ns32000 */ bfd_arch_w65, /* WDC 65816 */ bfd_arch_last }; enum bfd_endian { BFD_ENDIAN_UNKNOWN }; typedef struct bfd bfd; #define bfd_getb32(x) *((int *)(x)) #define bfd_getl32(x) *((int *)(x)) #endif smalltalk-3.2.5/opcode/i386-dis.c0000644000175000017500000011603012123404352013306 00000000000000/* Print i386 instructions for GDB, the GNU debugger. Copyright (C) 1988, 89, 91, 93, 94, 95, 1996 Free Software Foundation, Inc. This file is part of GDB. This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2 of the License, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. */ /* * 80386 instruction printer by Pace Willisson (pace@prep.ai.mit.edu) * July 1988 * modified by John Hassey (hassey@dg-rtp.dg.com) */ /* * The main tables describing the instructions is essentially a copy * of the "Opcode Map" chapter (Appendix A) of the Intel 80386 * Programmers Manual. Usually, there is a capital letter, followed * by a small letter. The capital letter tell the addressing mode, * and the small letter tells about the operand size. Refer to * the Intel manual for details. */ #include "dis-asm.h" #include "sysdep.h" #define MAXLEN 20 #include struct dis_private { /* Points to first byte not fetched. */ bfd_byte *max_fetched; bfd_byte the_buffer[MAXLEN]; bfd_vma insn_start; jmp_buf bailout; }; /* Make sure that bytes from INFO->PRIVATE_DATA->BUFFER (inclusive) to ADDR (exclusive) are valid. Returns 1 for success, longjmps on error. */ #define FETCH_DATA(info, addr) \ ((addr) <= ((struct dis_private *)(info->private_data))->max_fetched \ ? 1 : fetch_data ((info), (addr))) static int fetch_data (info, addr) struct disassemble_info *info; bfd_byte *addr; { int status; struct dis_private *priv = (struct dis_private *)info->private_data; bfd_vma start = priv->insn_start + (priv->max_fetched - priv->the_buffer); status = (*info->read_memory_func) (start, priv->max_fetched, addr - priv->max_fetched, info); if (status != 0) { (*info->memory_error_func) (status, start, info); longjmp (priv->bailout, 1); } else priv->max_fetched = addr; return 1; } #define Eb OP_E, b_mode #define indirEb OP_indirE, b_mode #define Gb OP_G, b_mode #define Ev OP_E, v_mode #define indirEv OP_indirE, v_mode #define Ew OP_E, w_mode #define Ma OP_E, v_mode #define M OP_E, 0 #define Mp OP_E, 0 /* ? */ #define Gv OP_G, v_mode #define Gw OP_G, w_mode #define Rw OP_rm, w_mode #define Rd OP_rm, d_mode #define Ib OP_I, b_mode #define sIb OP_sI, b_mode /* sign extened byte */ #define Iv OP_I, v_mode #define Iw OP_I, w_mode #define Jb OP_J, b_mode #define Jv OP_J, v_mode #define ONE OP_ONE, 0 #define Cd OP_C, d_mode #define Dd OP_D, d_mode #define Td OP_T, d_mode #define eAX OP_REG, eAX_reg #define eBX OP_REG, eBX_reg #define eCX OP_REG, eCX_reg #define eDX OP_REG, eDX_reg #define eSP OP_REG, eSP_reg #define eBP OP_REG, eBP_reg #define eSI OP_REG, eSI_reg #define eDI OP_REG, eDI_reg #define AL OP_REG, al_reg #define CL OP_REG, cl_reg #define DL OP_REG, dl_reg #define BL OP_REG, bl_reg #define AH OP_REG, ah_reg #define CH OP_REG, ch_reg #define DH OP_REG, dh_reg #define BH OP_REG, bh_reg #define AX OP_REG, ax_reg #define DX OP_REG, dx_reg #define indirDX OP_REG, indir_dx_reg #define Sw OP_SEG, w_mode #define Ap OP_DIR, lptr #define Av OP_DIR, v_mode #define Ob OP_OFF, b_mode #define Ov OP_OFF, v_mode #define Xb OP_DSSI, b_mode #define Xv OP_DSSI, v_mode #define Yb OP_ESDI, b_mode #define Yv OP_ESDI, v_mode #define es OP_REG, es_reg #define ss OP_REG, ss_reg #define cs OP_REG, cs_reg #define ds OP_REG, ds_reg #define fs OP_REG, fs_reg #define gs OP_REG, gs_reg int OP_E(), OP_indirE(), OP_G(), OP_I(), OP_sI(), OP_REG(); int OP_J(), OP_SEG(); int OP_DIR(), OP_OFF(), OP_DSSI(), OP_ESDI(), OP_ONE(), OP_C(); int OP_D(), OP_T(), OP_rm(); static void dofloat (), putop (), append_prefix (), set_op (); static int get16 (), get32 (); #define b_mode 1 #define v_mode 2 #define w_mode 3 #define d_mode 4 #define es_reg 100 #define cs_reg 101 #define ss_reg 102 #define ds_reg 103 #define fs_reg 104 #define gs_reg 105 #define eAX_reg 107 #define eCX_reg 108 #define eDX_reg 109 #define eBX_reg 110 #define eSP_reg 111 #define eBP_reg 112 #define eSI_reg 113 #define eDI_reg 114 #define lptr 115 #define al_reg 116 #define cl_reg 117 #define dl_reg 118 #define bl_reg 119 #define ah_reg 120 #define ch_reg 121 #define dh_reg 122 #define bh_reg 123 #define ax_reg 124 #define cx_reg 125 #define dx_reg 126 #define bx_reg 127 #define sp_reg 128 #define bp_reg 129 #define si_reg 130 #define di_reg 131 #define indir_dx_reg 150 #define GRP1b NULL, NULL, 0 #define GRP1S NULL, NULL, 1 #define GRP1Ss NULL, NULL, 2 #define GRP2b NULL, NULL, 3 #define GRP2S NULL, NULL, 4 #define GRP2b_one NULL, NULL, 5 #define GRP2S_one NULL, NULL, 6 #define GRP2b_cl NULL, NULL, 7 #define GRP2S_cl NULL, NULL, 8 #define GRP3b NULL, NULL, 9 #define GRP3S NULL, NULL, 10 #define GRP4 NULL, NULL, 11 #define GRP5 NULL, NULL, 12 #define GRP6 NULL, NULL, 13 #define GRP7 NULL, NULL, 14 #define GRP8 NULL, NULL, 15 #define GRP9 NULL, NULL, 16 #define FLOATCODE 50 #define FLOAT NULL, NULL, FLOATCODE struct dis386 { char *name; int (*op1)(); int bytemode1; int (*op2)(); int bytemode2; int (*op3)(); int bytemode3; }; struct dis386 dis386[] = { /* 00 */ { "addb", Eb, Gb }, { "addS", Ev, Gv }, { "addb", Gb, Eb }, { "addS", Gv, Ev }, { "addb", AL, Ib }, { "addS", eAX, Iv }, { "pushl", es }, { "popl", es }, /* 08 */ { "orb", Eb, Gb }, { "orS", Ev, Gv }, { "orb", Gb, Eb }, { "orS", Gv, Ev }, { "orb", AL, Ib }, { "orS", eAX, Iv }, { "pushl", cs }, { "(bad)" }, /* 0x0f extended opcode escape */ /* 10 */ { "adcb", Eb, Gb }, { "adcS", Ev, Gv }, { "adcb", Gb, Eb }, { "adcS", Gv, Ev }, { "adcb", AL, Ib }, { "adcS", eAX, Iv }, { "pushl", ss }, { "popl", ss }, /* 18 */ { "sbbb", Eb, Gb }, { "sbbS", Ev, Gv }, { "sbbb", Gb, Eb }, { "sbbS", Gv, Ev }, { "sbbb", AL, Ib }, { "sbbS", eAX, Iv }, { "pushl", ds }, { "popl", ds }, /* 20 */ { "andb", Eb, Gb }, { "andS", Ev, Gv }, { "andb", Gb, Eb }, { "andS", Gv, Ev }, { "andb", AL, Ib }, { "andS", eAX, Iv }, { "(bad)" }, /* SEG ES prefix */ { "daa" }, /* 28 */ { "subb", Eb, Gb }, { "subS", Ev, Gv }, { "subb", Gb, Eb }, { "subS", Gv, Ev }, { "subb", AL, Ib }, { "subS", eAX, Iv }, { "(bad)" }, /* SEG CS prefix */ { "das" }, /* 30 */ { "xorb", Eb, Gb }, { "xorS", Ev, Gv }, { "xorb", Gb, Eb }, { "xorS", Gv, Ev }, { "xorb", AL, Ib }, { "xorS", eAX, Iv }, { "(bad)" }, /* SEG SS prefix */ { "aaa" }, /* 38 */ { "cmpb", Eb, Gb }, { "cmpS", Ev, Gv }, { "cmpb", Gb, Eb }, { "cmpS", Gv, Ev }, { "cmpb", AL, Ib }, { "cmpS", eAX, Iv }, { "(bad)" }, /* SEG DS prefix */ { "aas" }, /* 40 */ { "incS", eAX }, { "incS", eCX }, { "incS", eDX }, { "incS", eBX }, { "incS", eSP }, { "incS", eBP }, { "incS", eSI }, { "incS", eDI }, /* 48 */ { "decS", eAX }, { "decS", eCX }, { "decS", eDX }, { "decS", eBX }, { "decS", eSP }, { "decS", eBP }, { "decS", eSI }, { "decS", eDI }, /* 50 */ { "pushS", eAX }, { "pushS", eCX }, { "pushS", eDX }, { "pushS", eBX }, { "pushS", eSP }, { "pushS", eBP }, { "pushS", eSI }, { "pushS", eDI }, /* 58 */ { "popS", eAX }, { "popS", eCX }, { "popS", eDX }, { "popS", eBX }, { "popS", eSP }, { "popS", eBP }, { "popS", eSI }, { "popS", eDI }, /* 60 */ { "pusha" }, { "popa" }, { "boundS", Gv, Ma }, { "arpl", Ew, Gw }, { "(bad)" }, /* seg fs */ { "(bad)" }, /* seg gs */ { "(bad)" }, /* op size prefix */ { "(bad)" }, /* adr size prefix */ /* 68 */ { "pushS", Iv }, /* 386 book wrong */ { "imulS", Gv, Ev, Iv }, { "pushl", sIb }, /* push of byte really pushes 4 bytes */ { "imulS", Gv, Ev, Ib }, { "insb", Yb, indirDX }, { "insS", Yv, indirDX }, { "outsb", indirDX, Xb }, { "outsS", indirDX, Xv }, /* 70 */ { "jo", Jb }, { "jno", Jb }, { "jb", Jb }, { "jae", Jb }, { "je", Jb }, { "jne", Jb }, { "jbe", Jb }, { "ja", Jb }, /* 78 */ { "js", Jb }, { "jns", Jb }, { "jp", Jb }, { "jnp", Jb }, { "jl", Jb }, { "jnl", Jb }, { "jle", Jb }, { "jg", Jb }, /* 80 */ { GRP1b }, { GRP1S }, { "(bad)" }, { GRP1Ss }, { "testb", Eb, Gb }, { "testS", Ev, Gv }, { "xchgb", Eb, Gb }, { "xchgS", Ev, Gv }, /* 88 */ { "movb", Eb, Gb }, { "movS", Ev, Gv }, { "movb", Gb, Eb }, { "movS", Gv, Ev }, { "movw", Ew, Sw }, { "leaS", Gv, M }, { "movw", Sw, Ew }, { "popS", Ev }, /* 90 */ { "nop" }, { "xchgS", eCX, eAX }, { "xchgS", eDX, eAX }, { "xchgS", eBX, eAX }, { "xchgS", eSP, eAX }, { "xchgS", eBP, eAX }, { "xchgS", eSI, eAX }, { "xchgS", eDI, eAX }, /* 98 */ { "cwtl" }, { "cltd" }, { "lcall", Ap }, { "(bad)" }, /* fwait */ { "pushf" }, { "popf" }, { "sahf" }, { "lahf" }, /* a0 */ { "movb", AL, Ob }, { "movS", eAX, Ov }, { "movb", Ob, AL }, { "movS", Ov, eAX }, { "movsb", Yb, Xb }, { "movsS", Yv, Xv }, { "cmpsb", Yb, Xb }, { "cmpsS", Yv, Xv }, /* a8 */ { "testb", AL, Ib }, { "testS", eAX, Iv }, { "stosb", Yb, AL }, { "stosS", Yv, eAX }, { "lodsb", AL, Xb }, { "lodsS", eAX, Xv }, { "scasb", AL, Yb }, { "scasS", eAX, Yv }, /* b0 */ { "movb", AL, Ib }, { "movb", CL, Ib }, { "movb", DL, Ib }, { "movb", BL, Ib }, { "movb", AH, Ib }, { "movb", CH, Ib }, { "movb", DH, Ib }, { "movb", BH, Ib }, /* b8 */ { "movS", eAX, Iv }, { "movS", eCX, Iv }, { "movS", eDX, Iv }, { "movS", eBX, Iv }, { "movS", eSP, Iv }, { "movS", eBP, Iv }, { "movS", eSI, Iv }, { "movS", eDI, Iv }, /* c0 */ { GRP2b }, { GRP2S }, { "ret", Iw }, { "ret" }, { "lesS", Gv, Mp }, { "ldsS", Gv, Mp }, { "movb", Eb, Ib }, { "movS", Ev, Iv }, /* c8 */ { "enter", Iw, Ib }, { "leave" }, { "lret", Iw }, { "lret" }, { "int3" }, { "int", Ib }, { "into" }, { "iret" }, /* d0 */ { GRP2b_one }, { GRP2S_one }, { GRP2b_cl }, { GRP2S_cl }, { "aam", Ib }, { "aad", Ib }, { "(bad)" }, { "xlat" }, /* d8 */ { FLOAT }, { FLOAT }, { FLOAT }, { FLOAT }, { FLOAT }, { FLOAT }, { FLOAT }, { FLOAT }, /* e0 */ { "loopne", Jb }, { "loope", Jb }, { "loop", Jb }, { "jCcxz", Jb }, { "inb", AL, Ib }, { "inS", eAX, Ib }, { "outb", Ib, AL }, { "outS", Ib, eAX }, /* e8 */ { "call", Av }, { "jmp", Jv }, { "ljmp", Ap }, { "jmp", Jb }, { "inb", AL, indirDX }, { "inS", eAX, indirDX }, { "outb", indirDX, AL }, { "outS", indirDX, eAX }, /* f0 */ { "(bad)" }, /* lock prefix */ { "(bad)" }, { "(bad)" }, /* repne */ { "(bad)" }, /* repz */ { "hlt" }, { "cmc" }, { GRP3b }, { GRP3S }, /* f8 */ { "clc" }, { "stc" }, { "cli" }, { "sti" }, { "cld" }, { "std" }, { GRP4 }, { GRP5 }, }; struct dis386 dis386_twobyte[] = { /* 00 */ { GRP6 }, { GRP7 }, { "larS", Gv, Ew }, { "lslS", Gv, Ew }, { "(bad)" }, { "(bad)" }, { "clts" }, { "(bad)" }, /* 08 */ { "invd" }, { "wbinvd" }, { "(bad)" }, { "ud2a" }, { "(bad)" }, { "(bad)" }, { "(bad)" }, { "(bad)" }, /* 10 */ { "(bad)" }, { "(bad)" }, { "(bad)" }, { "(bad)" }, { "(bad)" }, { "(bad)" }, { "(bad)" }, { "(bad)" }, /* 18 */ { "(bad)" }, { "(bad)" }, { "(bad)" }, { "(bad)" }, { "(bad)" }, { "(bad)" }, { "(bad)" }, { "(bad)" }, /* 20 */ /* these are all backward in appendix A of the intel book */ { "movl", Rd, Cd }, { "movl", Rd, Dd }, { "movl", Cd, Rd }, { "movl", Dd, Rd }, { "movl", Rd, Td }, { "(bad)" }, { "movl", Td, Rd }, { "(bad)" }, /* 28 */ { "(bad)" }, { "(bad)" }, { "(bad)" }, { "(bad)" }, { "(bad)" }, { "(bad)" }, { "(bad)" }, { "(bad)" }, /* 30 */ { "wrmsr" }, { "rdtsc" }, { "rdmsr" }, { "rdpmc" }, { "(bad)" }, { "(bad)" }, { "(bad)" }, { "(bad)" }, /* 38 */ { "(bad)" }, { "(bad)" }, { "(bad)" }, { "(bad)" }, { "(bad)" }, { "(bad)" }, { "(bad)" }, { "(bad)" }, /* 40 */ { "cmovo", Gv,Ev }, { "cmovno", Gv,Ev }, { "cmovb", Gv,Ev }, { "cmovae", Gv,Ev }, { "cmove", Gv,Ev }, { "cmovne", Gv,Ev }, { "cmovbe", Gv,Ev }, { "cmova", Gv,Ev }, /* 48 */ { "cmovs", Gv,Ev }, { "cmovns", Gv,Ev }, { "cmovp", Gv,Ev }, { "cmovnp", Gv,Ev }, { "cmovl", Gv,Ev }, { "cmovge", Gv,Ev }, { "cmovle", Gv,Ev }, { "cmovg", Gv,Ev }, /* 50 */ { "(bad)" }, { "(bad)" }, { "(bad)" }, { "(bad)" }, { "(bad)" }, { "(bad)" }, { "(bad)" }, { "(bad)" }, /* 58 */ { "(bad)" }, { "(bad)" }, { "(bad)" }, { "(bad)" }, { "(bad)" }, { "(bad)" }, { "(bad)" }, { "(bad)" }, /* 60 */ { "(bad)" }, { "(bad)" }, { "(bad)" }, { "(bad)" }, { "(bad)" }, { "(bad)" }, { "(bad)" }, { "(bad)" }, /* 68 */ { "(bad)" }, { "(bad)" }, { "(bad)" }, { "(bad)" }, { "(bad)" }, { "(bad)" }, { "(bad)" }, { "(bad)" }, /* 70 */ { "(bad)" }, { "(bad)" }, { "(bad)" }, { "(bad)" }, { "(bad)" }, { "(bad)" }, { "(bad)" }, { "(bad)" }, /* 78 */ { "(bad)" }, { "(bad)" }, { "(bad)" }, { "(bad)" }, { "(bad)" }, { "(bad)" }, { "(bad)" }, { "(bad)" }, /* 80 */ { "jo", Jv }, { "jno", Jv }, { "jb", Jv }, { "jae", Jv }, { "je", Jv }, { "jne", Jv }, { "jbe", Jv }, { "ja", Jv }, /* 88 */ { "js", Jv }, { "jns", Jv }, { "jp", Jv }, { "jnp", Jv }, { "jl", Jv }, { "jge", Jv }, { "jle", Jv }, { "jg", Jv }, /* 90 */ { "seto", Eb }, { "setno", Eb }, { "setb", Eb }, { "setae", Eb }, { "sete", Eb }, { "setne", Eb }, { "setbe", Eb }, { "seta", Eb }, /* 98 */ { "sets", Eb }, { "setns", Eb }, { "setp", Eb }, { "setnp", Eb }, { "setl", Eb }, { "setge", Eb }, { "setle", Eb }, { "setg", Eb }, /* a0 */ { "pushl", fs }, { "popl", fs }, { "cpuid" }, { "btS", Ev, Gv }, { "shldS", Ev, Gv, Ib }, { "shldS", Ev, Gv, CL }, { "(bad)" }, { "(bad)" }, /* a8 */ { "pushl", gs }, { "popl", gs }, { "rsm" }, { "btsS", Ev, Gv }, { "shrdS", Ev, Gv, Ib }, { "shrdS", Ev, Gv, CL }, { "(bad)" }, { "imulS", Gv, Ev }, /* b0 */ { "cmpxchgb", Eb, Gb }, { "cmpxchgS", Ev, Gv }, { "lssS", Gv, Mp }, /* 386 lists only Mp */ { "btrS", Ev, Gv }, { "lfsS", Gv, Mp }, /* 386 lists only Mp */ { "lgsS", Gv, Mp }, /* 386 lists only Mp */ { "movzbS", Gv, Eb }, { "movzwS", Gv, Ew }, /* b8 */ { "ud2b" }, { "(bad)" }, { GRP8 }, { "btcS", Ev, Gv }, { "bsfS", Gv, Ev }, { "bsrS", Gv, Ev }, { "movsbS", Gv, Eb }, { "movswS", Gv, Ew }, /* c0 */ { "xaddb", Eb, Gb }, { "xaddS", Ev, Gv }, { "(bad)" }, { "(bad)" }, { "(bad)" }, { "(bad)" }, { "(bad)" }, { GRP9 }, /* c8 */ { "bswap", eAX }, { "bswap", eCX }, { "bswap", eDX }, { "bswap", eBX }, { "bswap", eSP }, { "bswap", eBP }, { "bswap", eSI }, { "bswap", eDI }, /* d0 */ { "(bad)" }, { "(bad)" }, { "(bad)" }, { "(bad)" }, { "(bad)" }, { "(bad)" }, { "(bad)" }, { "(bad)" }, /* d8 */ { "(bad)" }, { "(bad)" }, { "(bad)" }, { "(bad)" }, { "(bad)" }, { "(bad)" }, { "(bad)" }, { "(bad)" }, /* e0 */ { "(bad)" }, { "(bad)" }, { "(bad)" }, { "(bad)" }, { "(bad)" }, { "(bad)" }, { "(bad)" }, { "(bad)" }, /* e8 */ { "(bad)" }, { "(bad)" }, { "(bad)" }, { "(bad)" }, { "(bad)" }, { "(bad)" }, { "(bad)" }, { "(bad)" }, /* f0 */ { "(bad)" }, { "(bad)" }, { "(bad)" }, { "(bad)" }, { "(bad)" }, { "(bad)" }, { "(bad)" }, { "(bad)" }, /* f8 */ { "(bad)" }, { "(bad)" }, { "(bad)" }, { "(bad)" }, { "(bad)" }, { "(bad)" }, { "(bad)" }, { "(bad)" }, }; static const unsigned char onebyte_has_modrm[256] = { 1,1,1,1,0,0,0,0,1,1,1,1,0,0,0,0, 1,1,1,1,0,0,0,0,1,1,1,1,0,0,0,0, 1,1,1,1,0,0,0,0,1,1,1,1,0,0,0,0, 1,1,1,1,0,0,0,0,1,1,1,1,0,0,0,0, 0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0, 0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0, 0,0,1,1,0,0,0,0,0,1,0,1,0,0,0,0, 0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0, 1,1,1,1,1,1,1,1,1,1,1,1,1,1,1,1, 0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0, 0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0, 0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0, 1,1,0,0,1,1,1,1,0,0,0,0,0,0,0,0, 1,1,1,1,0,0,0,0,1,1,1,1,1,1,1,1, 0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0, 0,0,0,0,0,0,1,1,0,0,0,0,0,0,1,1 }; static const unsigned char twobyte_has_modrm[256] = { 1,1,1,1,0,0,0,0,0,0,0,0,0,0,0,0, 0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0, 1,1,1,1,1,1,1,1,0,0,0,0,0,0,0,0, 0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0, 1,1,1,1,1,1,1,1,1,1,1,1,1,1,1,1, 0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0, 0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0, 0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0, 0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0, 1,1,1,1,1,1,1,1,1,1,1,1,1,1,1,1, 0,0,0,1,1,1,1,1,0,0,0,1,1,1,1,1, 1,1,1,1,1,1,1,1,0,0,1,1,1,1,1,1, 1,1,1,1,1,1,1,1,0,0,0,0,0,0,0,0, 0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0, 0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0, 0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,0 }; static char obuf[100]; static char *obufp; static char scratchbuf[100]; static unsigned char *start_codep; static unsigned char *codep; static disassemble_info *the_info; static int mod; static int rm; static int reg; static void oappend (); static char *names32[]={ "%eax","%ecx","%edx","%ebx", "%esp","%ebp","%esi","%edi", }; static char *names16[] = { "%ax","%cx","%dx","%bx","%sp","%bp","%si","%di", }; static char *names8[] = { "%al","%cl","%dl","%bl","%ah","%ch","%dh","%bh", }; static char *names_seg[] = { "%es","%cs","%ss","%ds","%fs","%gs","%?","%?", }; static char *index16[] = { "bx+si","bx+di","bp+si","bp+di","si","di","bp","bx" }; struct dis386 grps[][8] = { /* GRP1b */ { { "addb", Eb, Ib }, { "orb", Eb, Ib }, { "adcb", Eb, Ib }, { "sbbb", Eb, Ib }, { "andb", Eb, Ib }, { "subb", Eb, Ib }, { "xorb", Eb, Ib }, { "cmpb", Eb, Ib } }, /* GRP1S */ { { "addS", Ev, Iv }, { "orS", Ev, Iv }, { "adcS", Ev, Iv }, { "sbbS", Ev, Iv }, { "andS", Ev, Iv }, { "subS", Ev, Iv }, { "xorS", Ev, Iv }, { "cmpS", Ev, Iv } }, /* GRP1Ss */ { { "addS", Ev, sIb }, { "orS", Ev, sIb }, { "adcS", Ev, sIb }, { "sbbS", Ev, sIb }, { "andS", Ev, sIb }, { "subS", Ev, sIb }, { "xorS", Ev, sIb }, { "cmpS", Ev, sIb } }, /* GRP2b */ { { "rolb", Eb, Ib }, { "rorb", Eb, Ib }, { "rclb", Eb, Ib }, { "rcrb", Eb, Ib }, { "shlb", Eb, Ib }, { "shrb", Eb, Ib }, { "(bad)" }, { "sarb", Eb, Ib }, }, /* GRP2S */ { { "rolS", Ev, Ib }, { "rorS", Ev, Ib }, { "rclS", Ev, Ib }, { "rcrS", Ev, Ib }, { "shlS", Ev, Ib }, { "shrS", Ev, Ib }, { "(bad)" }, { "sarS", Ev, Ib }, }, /* GRP2b_one */ { { "rolb", Eb }, { "rorb", Eb }, { "rclb", Eb }, { "rcrb", Eb }, { "shlb", Eb }, { "shrb", Eb }, { "(bad)" }, { "sarb", Eb }, }, /* GRP2S_one */ { { "rolS", Ev }, { "rorS", Ev }, { "rclS", Ev }, { "rcrS", Ev }, { "shlS", Ev }, { "shrS", Ev }, { "(bad)" }, { "sarS", Ev }, }, /* GRP2b_cl */ { { "rolb", Eb, CL }, { "rorb", Eb, CL }, { "rclb", Eb, CL }, { "rcrb", Eb, CL }, { "shlb", Eb, CL }, { "shrb", Eb, CL }, { "(bad)" }, { "sarb", Eb, CL }, }, /* GRP2S_cl */ { { "rolS", Ev, CL }, { "rorS", Ev, CL }, { "rclS", Ev, CL }, { "rcrS", Ev, CL }, { "shlS", Ev, CL }, { "shrS", Ev, CL }, { "(bad)" }, { "sarS", Ev, CL } }, /* GRP3b */ { { "testb", Eb, Ib }, { "(bad)", Eb }, { "notb", Eb }, { "negb", Eb }, { "mulb", AL, Eb }, { "imulb", AL, Eb }, { "divb", AL, Eb }, { "idivb", AL, Eb } }, /* GRP3S */ { { "testS", Ev, Iv }, { "(bad)" }, { "notS", Ev }, { "negS", Ev }, { "mulS", eAX, Ev }, { "imulS", eAX, Ev }, { "divS", eAX, Ev }, { "idivS", eAX, Ev }, }, /* GRP4 */ { { "incb", Eb }, { "decb", Eb }, { "(bad)" }, { "(bad)" }, { "(bad)" }, { "(bad)" }, { "(bad)" }, { "(bad)" }, }, /* GRP5 */ { { "incS", Ev }, { "decS", Ev }, { "call", indirEv }, { "lcall", indirEv }, { "jmp", indirEv }, { "ljmp", indirEv }, { "pushS", Ev }, { "(bad)" }, }, /* GRP6 */ { { "sldt", Ew }, { "str", Ew }, { "lldt", Ew }, { "ltr", Ew }, { "verr", Ew }, { "verw", Ew }, { "(bad)" }, { "(bad)" } }, /* GRP7 */ { { "sgdt", Ew }, { "sidt", Ew }, { "lgdt", Ew }, { "lidt", Ew }, { "smsw", Ew }, { "(bad)" }, { "lmsw", Ew }, { "invlpg", Ew }, }, /* GRP8 */ { { "(bad)" }, { "(bad)" }, { "(bad)" }, { "(bad)" }, { "btS", Ev, Ib }, { "btsS", Ev, Ib }, { "btrS", Ev, Ib }, { "btcS", Ev, Ib }, }, /* GRP9 */ { { "(bad)" }, { "cmpxchg8b", Ev }, { "(bad)" }, { "(bad)" }, { "(bad)" }, { "(bad)" }, { "(bad)" }, { "(bad)" }, } }; #define PREFIX_REPZ 1 #define PREFIX_REPNZ 2 #define PREFIX_LOCK 4 #define PREFIX_CS 8 #define PREFIX_SS 0x10 #define PREFIX_DS 0x20 #define PREFIX_ES 0x40 #define PREFIX_FS 0x80 #define PREFIX_GS 0x100 #define PREFIX_DATA 0x200 #define PREFIX_ADR 0x400 #define PREFIX_FWAIT 0x800 static int prefixes; static void ckprefix () { prefixes = 0; while (1) { FETCH_DATA (the_info, codep + 1); switch (*codep) { case 0xf3: prefixes |= PREFIX_REPZ; break; case 0xf2: prefixes |= PREFIX_REPNZ; break; case 0xf0: prefixes |= PREFIX_LOCK; break; case 0x2e: prefixes |= PREFIX_CS; break; case 0x36: prefixes |= PREFIX_SS; break; case 0x3e: prefixes |= PREFIX_DS; break; case 0x26: prefixes |= PREFIX_ES; break; case 0x64: prefixes |= PREFIX_FS; break; case 0x65: prefixes |= PREFIX_GS; break; case 0x66: prefixes |= PREFIX_DATA; break; case 0x67: prefixes |= PREFIX_ADR; break; case 0x9b: prefixes |= PREFIX_FWAIT; break; default: return; } codep++; } } static int dflag; static int aflag; static char op1out[100], op2out[100], op3out[100]; static int op_address[3], op_ad, op_index[3]; static int start_pc; /* * On the 386's of 1988, the maximum length of an instruction is 15 bytes. * (see topic "Redundant prefixes" in the "Differences from 8086" * section of the "Virtual 8086 Mode" chapter.) * 'pc' should be the address of this instruction, it will * be used to print the target address if this is a relative jump or call * The function returns the length of this instruction in bytes. */ int print_insn_i386 (pc, info) bfd_vma pc; disassemble_info *info; { struct dis386 *dp; int i; int enter_instruction; char *first, *second, *third; int needcomma; unsigned char need_modrm; struct dis_private priv; bfd_byte *inbuf = priv.the_buffer; info->private_data = (PTR) &priv; priv.max_fetched = priv.the_buffer; priv.insn_start = pc; if (setjmp (priv.bailout) != 0) /* Error return. */ return -1; obuf[0] = 0; op1out[0] = 0; op2out[0] = 0; op3out[0] = 0; op_index[0] = op_index[1] = op_index[2] = -1; the_info = info; start_pc = pc; start_codep = inbuf; codep = inbuf; ckprefix (); FETCH_DATA (info, codep + 1); if (*codep == 0xc8) enter_instruction = 1; else enter_instruction = 0; obufp = obuf; if (prefixes & PREFIX_REPZ) oappend ("repz "); if (prefixes & PREFIX_REPNZ) oappend ("repnz "); if (prefixes & PREFIX_LOCK) oappend ("lock "); if ((prefixes & PREFIX_FWAIT) && ((*codep < 0xd8) || (*codep > 0xdf))) { /* fwait not followed by floating point instruction */ (*info->fprintf_func) (info->stream, "fwait"); return (1); } /* these would be initialized to 0 if disassembling for 8086 or 286 */ dflag = 1; aflag = 1; if (prefixes & PREFIX_DATA) dflag ^= 1; if (prefixes & PREFIX_ADR) { aflag ^= 1; oappend ("addr16 "); } if (*codep == 0x0f) { FETCH_DATA (info, codep + 2); dp = &dis386_twobyte[*++codep]; need_modrm = twobyte_has_modrm[*codep]; } else { dp = &dis386[*codep]; need_modrm = onebyte_has_modrm[*codep]; } codep++; if (need_modrm) { FETCH_DATA (info, codep + 1); mod = (*codep >> 6) & 3; reg = (*codep >> 3) & 7; rm = *codep & 7; } if (dp->name == NULL && dp->bytemode1 == FLOATCODE) { dofloat (); } else { if (dp->name == NULL) dp = &grps[dp->bytemode1][reg]; putop (dp->name); obufp = op1out; op_ad = 2; if (dp->op1) (*dp->op1)(dp->bytemode1); obufp = op2out; op_ad = 1; if (dp->op2) (*dp->op2)(dp->bytemode2); obufp = op3out; op_ad = 0; if (dp->op3) (*dp->op3)(dp->bytemode3); } obufp = obuf + strlen (obuf); for (i = strlen (obuf); i < 6; i++) oappend (" "); oappend (" "); (*info->fprintf_func) (info->stream, "%s", obuf); /* enter instruction is printed with operands in the * same order as the intel book; everything else * is printed in reverse order */ if (enter_instruction) { first = op1out; second = op2out; third = op3out; op_ad = op_index[0]; op_index[0] = op_index[2]; op_index[2] = op_ad; } else { first = op3out; second = op2out; third = op1out; } needcomma = 0; if (*first) { if (op_index[0] != -1) (*info->print_address_func) (op_address[op_index[0]], info); else (*info->fprintf_func) (info->stream, "%s", first); needcomma = 1; } if (*second) { if (needcomma) (*info->fprintf_func) (info->stream, ","); if (op_index[1] != -1) (*info->print_address_func) (op_address[op_index[1]], info); else (*info->fprintf_func) (info->stream, "%s", second); needcomma = 1; } if (*third) { if (needcomma) (*info->fprintf_func) (info->stream, ","); if (op_index[2] != -1) (*info->print_address_func) (op_address[op_index[2]], info); else (*info->fprintf_func) (info->stream, "%s", third); } return (codep - inbuf); } char *float_mem[] = { /* d8 */ "fadds", "fmuls", "fcoms", "fcomps", "fsubs", "fsubrs", "fdivs", "fdivrs", /* d9 */ "flds", "(bad)", "fsts", "fstps", "fldenv", "fldcw", "fNstenv", "fNstcw", /* da */ "fiaddl", "fimull", "ficoml", "ficompl", "fisubl", "fisubrl", "fidivl", "fidivrl", /* db */ "fildl", "(bad)", "fistl", "fistpl", "(bad)", "fldt", "(bad)", "fstpt", /* dc */ "faddl", "fmull", "fcoml", "fcompl", "fsubl", "fsubrl", "fdivl", "fdivrl", /* dd */ "fldl", "(bad)", "fstl", "fstpl", "frstor", "(bad)", "fNsave", "fNstsw", /* de */ "fiadd", "fimul", "ficom", "ficomp", "fisub", "fisubr", "fidiv", "fidivr", /* df */ "fild", "(bad)", "fist", "fistp", "fbld", "fildll", "fbstp", "fistpll", }; #define ST OP_ST, 0 #define STi OP_STi, 0 int OP_ST(), OP_STi(); #define FGRPd9_2 NULL, NULL, 0 #define FGRPd9_4 NULL, NULL, 1 #define FGRPd9_5 NULL, NULL, 2 #define FGRPd9_6 NULL, NULL, 3 #define FGRPd9_7 NULL, NULL, 4 #define FGRPda_5 NULL, NULL, 5 #define FGRPdb_4 NULL, NULL, 6 #define FGRPde_3 NULL, NULL, 7 #define FGRPdf_4 NULL, NULL, 8 struct dis386 float_reg[][8] = { /* d8 */ { { "fadd", ST, STi }, { "fmul", ST, STi }, { "fcom", STi }, { "fcomp", STi }, { "fsub", ST, STi }, { "fsubr", ST, STi }, { "fdiv", ST, STi }, { "fdivr", ST, STi }, }, /* d9 */ { { "fld", STi }, { "fxch", STi }, { FGRPd9_2 }, { "(bad)" }, { FGRPd9_4 }, { FGRPd9_5 }, { FGRPd9_6 }, { FGRPd9_7 }, }, /* da */ { { "fcmovb", ST, STi }, { "fcmove", ST, STi }, { "fcmovbe",ST, STi }, { "fcmovu", ST, STi }, { "(bad)" }, { FGRPda_5 }, { "(bad)" }, { "(bad)" }, }, /* db */ { { "fcmovnb",ST, STi }, { "fcmovne",ST, STi }, { "fcmovnbe",ST, STi }, { "fcmovnu",ST, STi }, { FGRPdb_4 }, { "fucomi", ST, STi }, { "fcomi", ST, STi }, { "(bad)" }, }, /* dc */ { { "fadd", STi, ST }, { "fmul", STi, ST }, { "(bad)" }, { "(bad)" }, { "fsub", STi, ST }, { "fsubr", STi, ST }, { "fdiv", STi, ST }, { "fdivr", STi, ST }, }, /* dd */ { { "ffree", STi }, { "(bad)" }, { "fst", STi }, { "fstp", STi }, { "fucom", STi }, { "fucomp", STi }, { "(bad)" }, { "(bad)" }, }, /* de */ { { "faddp", STi, ST }, { "fmulp", STi, ST }, { "(bad)" }, { FGRPde_3 }, { "fsubp", STi, ST }, { "fsubrp", STi, ST }, { "fdivp", STi, ST }, { "fdivrp", STi, ST }, }, /* df */ { { "(bad)" }, { "(bad)" }, { "(bad)" }, { "(bad)" }, { FGRPdf_4 }, { "fucomip",ST, STi }, { "fcomip", ST, STi }, { "(bad)" }, }, }; char *fgrps[][8] = { /* d9_2 0 */ { "fnop","(bad)","(bad)","(bad)","(bad)","(bad)","(bad)","(bad)", }, /* d9_4 1 */ { "fchs","fabs","(bad)","(bad)","ftst","fxam","(bad)","(bad)", }, /* d9_5 2 */ { "fld1","fldl2t","fldl2e","fldpi","fldlg2","fldln2","fldz","(bad)", }, /* d9_6 3 */ { "f2xm1","fyl2x","fptan","fpatan","fxtract","fprem1","fdecstp","fincstp", }, /* d9_7 4 */ { "fprem","fyl2xp1","fsqrt","fsincos","frndint","fscale","fsin","fcos", }, /* da_5 5 */ { "(bad)","fucompp","(bad)","(bad)","(bad)","(bad)","(bad)","(bad)", }, /* db_4 6 */ { "feni(287 only)","fdisi(287 only)","fNclex","fNinit", "fNsetpm(287 only)","(bad)","(bad)","(bad)", }, /* de_3 7 */ { "(bad)","fcompp","(bad)","(bad)","(bad)","(bad)","(bad)","(bad)", }, /* df_4 8 */ { "fNstsw","(bad)","(bad)","(bad)","(bad)","(bad)","(bad)","(bad)", }, }; static void dofloat () { struct dis386 *dp; unsigned char floatop; floatop = codep[-1]; if (mod != 3) { putop (float_mem[(floatop - 0xd8) * 8 + reg]); obufp = op1out; OP_E (v_mode); return; } codep++; dp = &float_reg[floatop - 0xd8][reg]; if (dp->name == NULL) { putop (fgrps[dp->bytemode1][rm]); /* instruction fnstsw is only one with strange arg */ if (floatop == 0xdf && FETCH_DATA (the_info, codep + 1) && *codep == 0xe0) strcpy (op1out, "%eax"); } else { putop (dp->name); obufp = op1out; if (dp->op1) (*dp->op1)(dp->bytemode1); obufp = op2out; if (dp->op2) (*dp->op2)(dp->bytemode2); } } /* ARGSUSED */ int OP_ST (ignore) int ignore; { oappend ("%st"); return (0); } /* ARGSUSED */ int OP_STi (ignore) int ignore; { sprintf (scratchbuf, "%%st(%d)", rm); oappend (scratchbuf); return (0); } /* capital letters in template are macros */ static void putop (template) char *template; { char *p; for (p = template; *p; p++) { switch (*p) { default: *obufp++ = *p; break; case 'C': /* For jcxz/jecxz */ if (aflag) *obufp++ = 'e'; break; case 'N': if ((prefixes & PREFIX_FWAIT) == 0) *obufp++ = 'n'; break; case 'S': /* operand size flag */ if (dflag) *obufp++ = 'l'; else *obufp++ = 'w'; break; } } *obufp = 0; } static void oappend (s) char *s; { strcpy (obufp, s); obufp += strlen (s); *obufp = 0; } static void append_prefix () { if (prefixes & PREFIX_CS) oappend ("%cs:"); if (prefixes & PREFIX_DS) oappend ("%ds:"); if (prefixes & PREFIX_SS) oappend ("%ss:"); if (prefixes & PREFIX_ES) oappend ("%es:"); if (prefixes & PREFIX_FS) oappend ("%fs:"); if (prefixes & PREFIX_GS) oappend ("%gs:"); } int OP_indirE (bytemode) int bytemode; { oappend ("*"); return OP_E (bytemode); } int OP_E (bytemode) int bytemode; { int disp; /* skip mod/rm byte */ codep++; if (mod == 3) { switch (bytemode) { case b_mode: oappend (names8[rm]); break; case w_mode: oappend (names16[rm]); break; case v_mode: if (dflag) oappend (names32[rm]); else oappend (names16[rm]); break; default: oappend (""); break; } return 0; } disp = 0; append_prefix (); if (aflag) /* 32 bit address mode */ { int havesib; int havebase; int base; int index; int scale; havesib = 0; havebase = 1; base = rm; if (base == 4) { havesib = 1; FETCH_DATA (the_info, codep + 1); scale = (*codep >> 6) & 3; index = (*codep >> 3) & 7; base = *codep & 7; codep++; } switch (mod) { case 0: if (base == 5) { havebase = 0; disp = get32 (); } break; case 1: FETCH_DATA (the_info, codep + 1); disp = *(char *)codep++; break; case 2: disp = get32 (); break; } if (mod != 0 || base == 5) { sprintf (scratchbuf, "0x%x", disp); oappend (scratchbuf); } if (havebase || (havesib && (index != 4 || scale != 0))) { oappend ("("); if (havebase) oappend (names32[base]); if (havesib) { if (index != 4) { sprintf (scratchbuf, ",%s", names32[index]); oappend (scratchbuf); } sprintf (scratchbuf, ",%d", 1 << scale); oappend (scratchbuf); } oappend (")"); } } else { /* 16 bit address mode */ switch (mod) { case 0: if (rm == 6) disp = (short) get16 (); break; case 1: FETCH_DATA (the_info, codep + 1); disp = *(char *)codep++; break; case 2: disp = (short) get16 (); break; } if (mod != 0 || rm == 6) { sprintf (scratchbuf, "0x%x", disp); oappend (scratchbuf); } if (mod != 0 || rm != 6) { oappend ("("); oappend (index16[rm]); oappend (")"); } } return 0; } int OP_G (bytemode) int bytemode; { switch (bytemode) { case b_mode: oappend (names8[reg]); break; case w_mode: oappend (names16[reg]); break; case d_mode: oappend (names32[reg]); break; case v_mode: if (dflag) oappend (names32[reg]); else oappend (names16[reg]); break; default: oappend (""); break; } return (0); } static int get32 () { int x = 0; FETCH_DATA (the_info, codep + 4); x = *codep++ & 0xff; x |= (*codep++ & 0xff) << 8; x |= (*codep++ & 0xff) << 16; x |= (*codep++ & 0xff) << 24; return (x); } static int get16 () { int x = 0; FETCH_DATA (the_info, codep + 2); x = *codep++ & 0xff; x |= (*codep++ & 0xff) << 8; return (x); } static void set_op (op) int op; { op_index[op_ad] = op_ad; op_address[op_ad] = op; } int OP_REG (code) int code; { char *s; switch (code) { case indir_dx_reg: s = "(%dx)"; break; case ax_reg: case cx_reg: case dx_reg: case bx_reg: case sp_reg: case bp_reg: case si_reg: case di_reg: s = names16[code - ax_reg]; break; case es_reg: case ss_reg: case cs_reg: case ds_reg: case fs_reg: case gs_reg: s = names_seg[code - es_reg]; break; case al_reg: case ah_reg: case cl_reg: case ch_reg: case dl_reg: case dh_reg: case bl_reg: case bh_reg: s = names8[code - al_reg]; break; case eAX_reg: case eCX_reg: case eDX_reg: case eBX_reg: case eSP_reg: case eBP_reg: case eSI_reg: case eDI_reg: if (dflag) s = names32[code - eAX_reg]; else s = names16[code - eAX_reg]; break; default: s = ""; break; } oappend (s); return (0); } int OP_I (bytemode) int bytemode; { int op; switch (bytemode) { case b_mode: FETCH_DATA (the_info, codep + 1); op = *codep++ & 0xff; break; case v_mode: if (dflag) op = get32 (); else op = get16 (); break; case w_mode: op = get16 (); break; default: oappend (""); return (0); } sprintf (scratchbuf, "$0x%x", op); oappend (scratchbuf); return (0); } int OP_sI (bytemode) int bytemode; { int op; switch (bytemode) { case b_mode: FETCH_DATA (the_info, codep + 1); op = *(char *)codep++; break; case v_mode: if (dflag) op = get32 (); else op = (short)get16(); break; case w_mode: op = (short)get16 (); break; default: oappend (""); return (0); } sprintf (scratchbuf, "$0x%x", op); oappend (scratchbuf); return (0); } int OP_J (bytemode) int bytemode; { int disp; int mask = -1; switch (bytemode) { case b_mode: FETCH_DATA (the_info, codep + 1); disp = *(char *)codep++; break; case v_mode: if (dflag) disp = get32 (); else { disp = (short)get16 (); /* for some reason, a data16 prefix on a jump instruction means that the pc is masked to 16 bits after the displacement is added! */ mask = 0xffff; } break; default: oappend (""); return (0); } disp = (start_pc + codep - start_codep + disp) & mask; set_op (disp); sprintf (scratchbuf, "0x%x", disp); oappend (scratchbuf); return (0); } /* ARGSUSED */ int OP_SEG (dummy) int dummy; { static char *sreg[] = { "%es","%cs","%ss","%ds","%fs","%gs","%?","%?", }; oappend (sreg[reg]); return (0); } int OP_DIR (size) int size; { int seg, offset; switch (size) { case lptr: if (aflag) { offset = get32 (); seg = get16 (); } else { offset = get16 (); seg = get16 (); } sprintf (scratchbuf, "0x%x,0x%x", seg, offset); oappend (scratchbuf); break; case v_mode: if (aflag) offset = get32 (); else offset = (short)get16 (); offset = start_pc + codep - start_codep + offset; set_op (offset); sprintf (scratchbuf, "0x%x", offset); oappend (scratchbuf); break; default: oappend (""); break; } return (0); } /* ARGSUSED */ int OP_OFF (bytemode) int bytemode; { int off; if (aflag) off = get32 (); else off = get16 (); sprintf (scratchbuf, "0x%x", off); oappend (scratchbuf); return (0); } /* ARGSUSED */ int OP_ESDI (dummy) int dummy; { oappend ("%es:("); oappend (aflag ? "%edi" : "%di"); oappend (")"); return (0); } /* ARGSUSED */ int OP_DSSI (dummy) int dummy; { oappend ("%ds:("); oappend (aflag ? "%esi" : "%si"); oappend (")"); return (0); } /* ARGSUSED */ int OP_ONE (dummy) int dummy; { oappend ("1"); return (0); } /* ARGSUSED */ int OP_C (dummy) int dummy; { codep++; /* skip mod/rm */ sprintf (scratchbuf, "%%cr%d", reg); oappend (scratchbuf); return (0); } /* ARGSUSED */ int OP_D (dummy) int dummy; { codep++; /* skip mod/rm */ sprintf (scratchbuf, "%%db%d", reg); oappend (scratchbuf); return (0); } /* ARGSUSED */ int OP_T (dummy) int dummy; { codep++; /* skip mod/rm */ sprintf (scratchbuf, "%%tr%d", reg); oappend (scratchbuf); return (0); } int OP_rm (bytemode) int bytemode; { switch (bytemode) { case d_mode: oappend (names32[rm]); break; case w_mode: oappend (names16[rm]); break; } return (0); } smalltalk-3.2.5/opcode/ppc.h0000644000175000017500000002270312123404352012632 00000000000000/* ppc.h -- Header file for PowerPC opcode table Copyright 1994, 1995 Free Software Foundation, Inc. Written by Ian Lance Taylor, Cygnus Support This file is part of GDB, GAS, and the GNU binutils. GDB, GAS, and the GNU binutils are free software; you can redistribute them and/or modify them under the terms of the GNU General Public License as published by the Free Software Foundation; either version 1, or (at your option) any later version. GDB, GAS, and the GNU binutils are distributed in the hope that they will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this file; see the file COPYING. If not, write to the Free Software Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. */ #ifndef PPC_H #define PPC_H /* The opcode table is an array of struct powerpc_opcode. */ struct powerpc_opcode { /* The opcode name. */ const char *name; /* The opcode itself. Those bits which will be filled in with operands are zeroes. */ unsigned long opcode; /* The opcode mask. This is used by the disassembler. This is a mask containing ones indicating those bits which must match the opcode field, and zeroes indicating those bits which need not match (and are presumably filled in by operands). */ unsigned long mask; /* One bit flags for the opcode. These are used to indicate which specific processors support the instructions. The defined values are listed below. */ unsigned long flags; /* An array of operand codes. Each code is an index into the operand table. They appear in the order which the operands must appear in assembly code, and are terminated by a zero. */ unsigned char operands[8]; }; /* The table itself is sorted by major opcode number, and is otherwise in the order in which the disassembler should consider instructions. */ extern const struct powerpc_opcode powerpc_opcodes[]; extern const int powerpc_num_opcodes; /* Values defined for the flags field of a struct powerpc_opcode. */ /* Opcode is defined for the PowerPC architecture. */ #define PPC_OPCODE_PPC (01) /* Opcode is defined for the POWER (RS/6000) architecture. */ #define PPC_OPCODE_POWER (02) /* Opcode is defined for the POWER2 (Rios 2) architecture. */ #define PPC_OPCODE_POWER2 (04) /* Opcode is only defined on 32 bit architectures. */ #define PPC_OPCODE_32 (010) /* Opcode is only defined on 64 bit architectures. */ #define PPC_OPCODE_64 (020) /* Opcode is supported by the Motorola PowerPC 601 processor. The 601 is assumed to support all PowerPC (PPC_OPCODE_PPC) instructions, but it also supports many additional POWER instructions. */ #define PPC_OPCODE_601 (040) /* Opcode is supported in both the Power and PowerPC architectures (ie, compiler's -mcpu=common or assembler's -mcom). */ #define PPC_OPCODE_COMMON (0100) /* Opcode is supported for any Power or PowerPC platform (this is for the assembler's -many option, and it eliminates duplicates). */ #define PPC_OPCODE_ANY (0200) /* A macro to extract the major opcode from an instruction. */ #define PPC_OP(i) (((i) >> 26) & 0x3f) /* The operands table is an array of struct powerpc_operand. */ struct powerpc_operand { /* The number of bits in the operand. */ int bits; /* How far the operand is left shifted in the instruction. */ int shift; /* Insertion function. This is used by the assembler. To insert an operand value into an instruction, check this field. If it is NULL, execute i |= (op & ((1 << o->bits) - 1)) << o->shift; (i is the instruction which we are filling in, o is a pointer to this structure, and op is the opcode value; this assumes twos complement arithmetic). If this field is not NULL, then simply call it with the instruction and the operand value. It will return the new value of the instruction. If the ERRMSG argument is not NULL, then if the operand value is illegal, *ERRMSG will be set to a warning string (the operand will be inserted in any case). If the operand value is legal, *ERRMSG will be unchanged (most operands can accept any value). */ unsigned long (*insert) PARAMS ((unsigned long instruction, long op, const char **errmsg)); /* Extraction function. This is used by the disassembler. To extract this operand type from an instruction, check this field. If it is NULL, compute op = ((i) >> o->shift) & ((1 << o->bits) - 1); if ((o->flags & PPC_OPERAND_SIGNED) != 0 && (op & (1 << (o->bits - 1))) != 0) op -= 1 << o->bits; (i is the instruction, o is a pointer to this structure, and op is the result; this assumes twos complement arithmetic). If this field is not NULL, then simply call it with the instruction value. It will return the value of the operand. If the INVALID argument is not NULL, *INVALID will be set to non-zero if this operand type can not actually be extracted from this operand (i.e., the instruction does not match). If the operand is valid, *INVALID will not be changed. */ long (*extract) PARAMS ((unsigned long instruction, int *invalid)); /* One bit syntax flags. */ unsigned long flags; }; /* Elements in the table are retrieved by indexing with values from the operands field of the powerpc_opcodes table. */ extern const struct powerpc_operand powerpc_operands[]; /* Values defined for the flags field of a struct powerpc_operand. */ /* This operand takes signed values. */ #define PPC_OPERAND_SIGNED (01) /* This operand takes signed values, but also accepts a full positive range of values when running in 32 bit mode. That is, if bits is 16, it takes any value from -0x8000 to 0xffff. In 64 bit mode, this flag is ignored. */ #define PPC_OPERAND_SIGNOPT (02) /* This operand does not actually exist in the assembler input. This is used to support extended mnemonics such as mr, for which two operands fields are identical. The assembler should call the insert function with any op value. The disassembler should call the extract function, ignore the return value, and check the value placed in the valid argument. */ #define PPC_OPERAND_FAKE (04) /* The next operand should be wrapped in parentheses rather than separated from this one by a comma. This is used for the load and store instructions which want their operands to look like reg,displacement(reg) */ #define PPC_OPERAND_PARENS (010) /* This operand may use the symbolic names for the CR fields, which are lt 0 gt 1 eq 2 so 3 un 3 cr0 0 cr1 1 cr2 2 cr3 3 cr4 4 cr5 5 cr6 6 cr7 7 These may be combined arithmetically, as in cr2*4+gt. These are only supported on the PowerPC, not the POWER. */ #define PPC_OPERAND_CR (020) /* This operand names a register. The disassembler uses this to print register names with a leading 'r'. */ #define PPC_OPERAND_GPR (040) /* This operand names a floating point register. The disassembler prints these with a leading 'f'. */ #define PPC_OPERAND_FPR (0100) /* This operand is a relative branch displacement. The disassembler prints these symbolically if possible. */ #define PPC_OPERAND_RELATIVE (0200) /* This operand is an absolute branch address. The disassembler prints these symbolically if possible. */ #define PPC_OPERAND_ABSOLUTE (0400) /* This operand is optional, and is zero if omitted. This is used for the optional BF and L fields in the comparison instructions. The assembler must count the number of operands remaining on the line, and the number of operands remaining for the opcode, and decide whether this operand is present or not. The disassembler should print this operand out only if it is not zero. */ #define PPC_OPERAND_OPTIONAL (01000) /* This flag is only used with PPC_OPERAND_OPTIONAL. If this operand is omitted, then for the next operand use this operand value plus 1, ignoring the next operand field for the opcode. This wretched hack is needed because the Power rotate instructions can take either 4 or 5 operands. The disassembler should print this operand out regardless of the PPC_OPERAND_OPTIONAL field. */ #define PPC_OPERAND_NEXT (02000) /* This operand should be regarded as a negative number for the purposes of overflow checking (i.e., the normal most negative number is disallowed and one more than the normal most positive number is allowed). This flag will only be set for a signed operand. */ #define PPC_OPERAND_NEGATIVE (04000) /* The POWER and PowerPC assemblers use a few macros. We keep them with the operands table for simplicity. The macro table is an array of struct powerpc_macro. */ struct powerpc_macro { /* The macro name. */ const char *name; /* The number of operands the macro takes. */ unsigned int operands; /* One bit flags for the opcode. These are used to indicate which specific processors support the instructions. The values are the same as those for the struct powerpc_opcode flags field. */ unsigned long flags; /* A format string to turn the macro into a normal instruction. Each %N in the string is replaced with operand number N (zero based). */ const char *format; }; extern const struct powerpc_macro powerpc_macros[]; extern const int powerpc_num_macros; #endif /* PPC_H */ smalltalk-3.2.5/opcode/sparc-dis.c0000644000175000017500000005524512123404352013737 00000000000000/* Print SPARC instructions. Copyright (C) 1989, 91-93, 1995, 1996 Free Software Foundation, Inc. This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2 of the License, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. */ #include "ansidecl.h" #include "opcode/sparc.h" #include "dis-asm.h" #include /* Bitmask of v9 architectures. */ #define MASK_V9 ((1 << SPARC_OPCODE_ARCH_V9) \ | (1 << SPARC_OPCODE_ARCH_V9A)) /* 1 if INSN is for v9 only. */ #define V9_ONLY_P(insn) (! ((insn)->architecture & ~MASK_V9)) /* 1 if INSN is for v9. */ #define V9_P(insn) (((insn)->architecture & MASK_V9) != 0) /* For faster lookup, after insns are sorted they are hashed. */ /* ??? I think there is room for even more improvement. */ #define HASH_SIZE 256 /* It is important that we only look at insn code bits as that is how the opcode table is hashed. OPCODE_BITS is a table of valid bits for each of the main types (0,1,2,3). */ static int opcode_bits[4] = { 0x01c00000, 0x0, 0x01f80000, 0x01f80000 }; #define HASH_INSN(INSN) \ ((((INSN) >> 24) & 0xc0) | (((INSN) & opcode_bits[((INSN) >> 30) & 3]) >> 19)) struct opcode_hash { struct opcode_hash *next; struct sparc_opcode *opcode; }; static struct opcode_hash *opcode_hash_table[HASH_SIZE]; static void build_hash_table (); /* Sign-extend a value which is N bits long. */ #define SEX(value, bits) \ ((((int)(value)) << ((8 * sizeof (int)) - bits)) \ >> ((8 * sizeof (int)) - bits) ) static char *reg_names[] = { "g0", "g1", "g2", "g3", "g4", "g5", "g6", "g7", "o0", "o1", "o2", "o3", "o4", "o5", "sp", "o7", "l0", "l1", "l2", "l3", "l4", "l5", "l6", "l7", "i0", "i1", "i2", "i3", "i4", "i5", "fp", "i7", "f0", "f1", "f2", "f3", "f4", "f5", "f6", "f7", "f8", "f9", "f10", "f11", "f12", "f13", "f14", "f15", "f16", "f17", "f18", "f19", "f20", "f21", "f22", "f23", "f24", "f25", "f26", "f27", "f28", "f29", "f30", "f31", "f32", "f33", "f34", "f35", "f36", "f37", "f38", "f39", "f40", "f41", "f42", "f43", "f44", "f45", "f46", "f47", "f48", "f49", "f50", "f51", "f52", "f53", "f54", "f55", "f56", "f57", "f58", "f59", "f60", "f61", "f62", "f63", /* psr, wim, tbr, fpsr, cpsr are v8 only. */ "y", "psr", "wim", "tbr", "pc", "npc", "fpsr", "cpsr" }; #define freg_names (®_names[4 * 8]) /* These are ordered according to there register number in rdpr and wrpr insns. */ static char *v9_priv_reg_names[] = { "tpc", "tnpc", "tstate", "tt", "tick", "tba", "pstate", "tl", "pil", "cwp", "cansave", "canrestore", "cleanwin", "otherwin", "wstate", "fq" /* "ver" - special cased */ }; /* Macros used to extract instruction fields. Not all fields have macros defined here, only those which are actually used. */ #define X_RD(i) (((i) >> 25) & 0x1f) #define X_RS1(i) (((i) >> 14) & 0x1f) #define X_LDST_I(i) (((i) >> 13) & 1) #define X_ASI(i) (((i) >> 5) & 0xff) #define X_RS2(i) (((i) >> 0) & 0x1f) #define X_IMM13(i) (((i) >> 0) & 0x1fff) #define X_DISP22(i) (((i) >> 0) & 0x3fffff) #define X_IMM22(i) X_DISP22 (i) #define X_DISP30(i) (((i) >> 0) & 0x3fffffff) /* These are for v9. */ #define X_DISP16(i) (((((i) >> 20) & 3) << 14) | (((i) >> 0) & 0x3fff)) #define X_DISP19(i) (((i) >> 0) & 0x7ffff) #define X_MEMBAR(i) ((i) & 0x7f) /* Here is the union which was used to extract instruction fields before the shift and mask macros were written. union sparc_insn { unsigned long int code; struct { unsigned int anop:2; #define op ldst.anop unsigned int anrd:5; #define rd ldst.anrd unsigned int op3:6; unsigned int anrs1:5; #define rs1 ldst.anrs1 unsigned int i:1; unsigned int anasi:8; #define asi ldst.anasi unsigned int anrs2:5; #define rs2 ldst.anrs2 #define shcnt rs2 } ldst; struct { unsigned int anop:2, anrd:5, op3:6, anrs1:5, i:1; unsigned int IMM13:13; #define imm13 IMM13.IMM13 } IMM13; struct { unsigned int anop:2; unsigned int a:1; unsigned int cond:4; unsigned int op2:3; unsigned int DISP22:22; #define disp22 branch.DISP22 #define imm22 disp22 } branch; struct { unsigned int anop:2; unsigned int a:1; unsigned int z:1; unsigned int rcond:3; unsigned int op2:3; unsigned int DISP16HI:2; unsigned int p:1; unsigned int _rs1:5; unsigned int DISP16LO:14; } branch16; struct { unsigned int anop:2; unsigned int adisp30:30; #define disp30 call.adisp30 } call; }; */ /* Nonzero if INSN is the opcode for a delayed branch. */ static int is_delayed_branch (insn) unsigned long insn; { struct opcode_hash *op; for (op = opcode_hash_table[HASH_INSN (insn)]; op; op = op->next) { const struct sparc_opcode *opcode = op->opcode; if ((opcode->match & insn) == opcode->match && (opcode->lose & insn) == 0) return (opcode->flags & F_DELAYED); } return 0; } /* Nonzero of opcode table has been initialized. */ static int opcodes_initialized = 0; /* extern void qsort (); */ static int compare_opcodes (); /* Print one instruction from MEMADDR on INFO->STREAM. We suffix the instruction with a comment that gives the absolute address involved, as well as its symbolic form, if the instruction is preceded by a findable `sethi' and it either adds an immediate displacement to that register, or it is an `add' or `or' instruction on that register. */ int print_insn_sparc (memaddr, info) bfd_vma memaddr; disassemble_info *info; { FILE *stream = info->stream; bfd_byte buffer[4]; unsigned long insn; register unsigned int i; register struct opcode_hash *op; int sparc_v9_p = bfd_mach_sparc_v9_p (info->mach); if (!opcodes_initialized) { qsort ((char *) sparc_opcodes, sparc_num_opcodes, sizeof (sparc_opcodes[0]), compare_opcodes); build_hash_table (sparc_opcodes, opcode_hash_table, sparc_num_opcodes); opcodes_initialized = 1; } { int status = (*info->read_memory_func) (memaddr, buffer, sizeof (buffer), info); if (status != 0) { (*info->memory_error_func) (status, memaddr, info); return -1; } } insn = bfd_getb32 (buffer); info->insn_info_valid = 1; /* We do return this info */ info->insn_type = dis_nonbranch; /* Assume non branch insn */ info->branch_delay_insns = 0; /* Assume no delay */ info->target = 0; /* Assume no target known */ for (op = opcode_hash_table[HASH_INSN (insn)]; op; op = op->next) { const struct sparc_opcode *opcode = op->opcode; /* ??? These architecture tests need to be more selective. */ /* If the current architecture isn't sparc64, skip sparc64 insns. */ if (!sparc_v9_p && V9_ONLY_P (opcode)) continue; /* If the current architecture is sparc64, skip sparc32 only insns. */ if (sparc_v9_p && ! V9_P (opcode)) continue; if ((opcode->match & insn) == opcode->match && (opcode->lose & insn) == 0) { /* Nonzero means that we have found an instruction which has the effect of adding or or'ing the imm13 field to rs1. */ int imm_added_to_rs1 = 0; /* Nonzero means that we have found a plus sign in the args field of the opcode table. */ int found_plus = 0; /* Nonzero means we have an annulled branch. */ int is_annulled = 0; /* Do we have an `add' or `or' instruction where rs1 is the same as rsd, and which has the i bit set? */ if ((opcode->match == 0x80102000 || opcode->match == 0x80002000) /* (or) (add) */ && X_RS1 (insn) == X_RD (insn)) imm_added_to_rs1 = 1; if (X_RS1 (insn) != X_RD (insn) && strchr (opcode->args, 'r') != 0) /* Can't do simple format if source and dest are different. */ continue; if (X_RS2 (insn) != X_RD (insn) && strchr (opcode->args, 'O') != 0) /* Can't do simple format if source and dest are different. */ continue; (*info->fprintf_func) (stream, opcode->name); { register const char *s; if (opcode->args[0] != ',') (*info->fprintf_func) (stream, " "); for (s = opcode->args; *s != '\0'; ++s) { while (*s == ',') { (*info->fprintf_func) (stream, ","); ++s; switch (*s) { case 'a': (*info->fprintf_func) (stream, "a"); is_annulled = 1; ++s; continue; case 'N': (*info->fprintf_func) (stream, "pn"); ++s; continue; case 'T': (*info->fprintf_func) (stream, "pt"); ++s; continue; default: break; } /* switch on arg */ } /* while there are comma started args */ (*info->fprintf_func) (stream, " "); switch (*s) { case '+': found_plus = 1; /* note fall-through */ default: (*info->fprintf_func) (stream, "%c", *s); break; case '#': (*info->fprintf_func) (stream, "0"); break; #define reg(n) (*info->fprintf_func) (stream, "%%%s", reg_names[n]) case '1': case 'r': reg (X_RS1 (insn)); break; case '2': case 'O': reg (X_RS2 (insn)); break; case 'd': reg (X_RD (insn)); break; #undef reg #define freg(n) (*info->fprintf_func) (stream, "%%%s", freg_names[n]) #define fregx(n) (*info->fprintf_func) (stream, "%%%s", freg_names[((n) & ~1) | (((n) & 1) << 5)]) case 'e': freg (X_RS1 (insn)); break; case 'v': /* double/even */ case 'V': /* quad/multiple of 4 */ fregx (X_RS1 (insn)); break; case 'f': freg (X_RS2 (insn)); break; case 'B': /* double/even */ case 'R': /* quad/multiple of 4 */ fregx (X_RS2 (insn)); break; case 'g': freg (X_RD (insn)); break; case 'H': /* double/even */ case 'J': /* quad/multiple of 4 */ fregx (X_RD (insn)); break; #undef freg #undef fregx #define creg(n) (*info->fprintf_func) (stream, "%%c%u", (unsigned int) (n)) case 'b': creg (X_RS1 (insn)); break; case 'c': creg (X_RS2 (insn)); break; case 'D': creg (X_RD (insn)); break; #undef creg case 'h': (*info->fprintf_func) (stream, "%%hi(%#x)", (0xFFFFFFFF & ((int) X_IMM22 (insn) << 10))); break; case 'i': { int imm = SEX (X_IMM13 (insn), 13); /* Check to see whether we have a 1+i, and take note of that fact. Note: because of the way we sort the table, we will be matching 1+i rather than i+1, so it is OK to assume that i is after +, not before it. */ if (found_plus) imm_added_to_rs1 = 1; if (imm <= 9) (*info->fprintf_func) (stream, "%d", imm); else (*info->fprintf_func) (stream, "%#x", imm); } break; case 'I': /* 11 bit immediate. */ case 'j': /* 10 bit immediate. */ { int imm; if (*s == 'I') imm = SEX (X_IMM13 (insn), 11); else imm = SEX (X_IMM13 (insn), 10); /* Check to see whether we have a 1+i, and take note of that fact. Note: because of the way we sort the table, we will be matching 1+i rather than i+1, so it is OK to assume that i is after +, not before it. */ if (found_plus) imm_added_to_rs1 = 1; if (imm <= 9) (info->fprintf_func) (stream, "%d", imm); else (info->fprintf_func) (stream, "%#x", (unsigned) imm); } break; case 'K': { int mask = X_MEMBAR (insn); int bit = 0x40, printed_one = 0; char *name; if (mask == 0) (info->fprintf_func) (stream, "0"); else while (bit) { if (mask & bit) { if (printed_one) (info->fprintf_func) (stream, "|"); name = sparc_decode_membar (bit); (info->fprintf_func) (stream, "%s", name); printed_one = 1; } bit >>= 1; } break; } case 'k': info->target = memaddr + SEX (X_DISP16 (insn), 16) * 4; (*info->print_address_func) (info->target, info); break; case 'G': info->target = memaddr + SEX (X_DISP19 (insn), 19) * 4; (*info->print_address_func) (info->target, info); break; case '6': case '7': case '8': case '9': (*info->fprintf_func) (stream, "%%fcc%c", *s - '6' + '0'); break; case 'z': (*info->fprintf_func) (stream, "%%icc"); break; case 'Z': (*info->fprintf_func) (stream, "%%xcc"); break; case 'E': (*info->fprintf_func) (stream, "%%ccr"); break; case 's': (*info->fprintf_func) (stream, "%%fprs"); break; case 'o': (*info->fprintf_func) (stream, "%%asi"); break; case 'W': (*info->fprintf_func) (stream, "%%tick"); break; case 'P': (*info->fprintf_func) (stream, "%%pc"); break; case '?': if (X_RS1 (insn) == 31) (*info->fprintf_func) (stream, "%%ver"); else if ((unsigned) X_RS1 (insn) < 16) (*info->fprintf_func) (stream, "%%%s", v9_priv_reg_names[X_RS1 (insn)]); else (*info->fprintf_func) (stream, "%%reserved"); break; case '!': if ((unsigned) X_RD (insn) < 15) (*info->fprintf_func) (stream, "%%%s", v9_priv_reg_names[X_RD (insn)]); else (*info->fprintf_func) (stream, "%%reserved"); break; case '*': { char *name = sparc_decode_prefetch (X_RD (insn)); if (name) (*info->fprintf_func) (stream, "%s", name); else (*info->fprintf_func) (stream, "%d", X_RD (insn)); break; } case 'M': (*info->fprintf_func) (stream, "%%asr%d", X_RS1 (insn)); break; case 'm': (*info->fprintf_func) (stream, "%%asr%d", X_RD (insn)); break; case 'L': info->target = memaddr + SEX (X_DISP30 (insn), 30) * 4; (*info->print_address_func) (info->target, info); break; case 'n': (*info->fprintf_func) (stream, "%#x", SEX (X_DISP22 (insn), 22)); break; case 'l': info->target = memaddr + SEX (X_DISP22 (insn), 22) * 4; (*info->print_address_func) (info->target, info); break; case 'A': { char *name = sparc_decode_asi (X_ASI (insn)); if (name) (*info->fprintf_func) (stream, "%s", name); else (*info->fprintf_func) (stream, "(%d)", X_ASI (insn)); break; } case 'C': (*info->fprintf_func) (stream, "%%csr"); break; case 'F': (*info->fprintf_func) (stream, "%%fsr"); break; case 'p': (*info->fprintf_func) (stream, "%%psr"); break; case 'q': (*info->fprintf_func) (stream, "%%fq"); break; case 'Q': (*info->fprintf_func) (stream, "%%cq"); break; case 't': (*info->fprintf_func) (stream, "%%tbr"); break; case 'w': (*info->fprintf_func) (stream, "%%wim"); break; case 'x': (*info->fprintf_func) (stream, "%d", ((X_LDST_I (insn) << 8) + X_ASI (insn))); break; case 'y': (*info->fprintf_func) (stream, "%%y"); break; case 'u': case 'U': { int val = *s == 'U' ? X_RS1 (insn) : X_RD (insn); char *name = sparc_decode_sparclet_cpreg (val); if (name) (*info->fprintf_func) (stream, "%s", name); else (*info->fprintf_func) (stream, "%%cpreg(%d)", val); break; } } } } /* If we are adding or or'ing something to rs1, then check to see whether the previous instruction was a sethi to the same register as in the sethi. If so, attempt to print the result of the add or or (in this context add and or do the same thing) and its symbolic value. */ if (imm_added_to_rs1) { unsigned long prev_insn; int errcode; errcode = (*info->read_memory_func) (memaddr - 4, buffer, sizeof (buffer), info); prev_insn = bfd_getb32 (buffer); if (errcode == 0) { /* If it is a delayed branch, we need to look at the instruction before the delayed branch. This handles sequences such as sethi %o1, %hi(_foo), %o1 call _printf or %o1, %lo(_foo), %o1 */ if (is_delayed_branch (prev_insn)) { errcode = (*info->read_memory_func) (memaddr - 8, buffer, sizeof (buffer), info); prev_insn = bfd_getb32 (buffer); } } /* If there was a problem reading memory, then assume the previous instruction was not sethi. */ if (errcode == 0) { /* Is it sethi to the same register? */ if ((prev_insn & 0xc1c00000) == 0x01000000 && X_RD (prev_insn) == X_RS1 (insn)) { (*info->fprintf_func) (stream, "\t! "); info->target = (0xFFFFFFFF & (int) X_IMM22 (prev_insn) << 10) | SEX (X_IMM13 (insn), 13); (*info->print_address_func) (info->target, info); info->insn_type = dis_dref; info->data_size = 4; /* FIXME!!! */ } } } if (opcode->flags & (F_UNBR|F_CONDBR|F_JSR)) { /* FIXME -- check is_annulled flag */ if (opcode->flags & F_UNBR) info->insn_type = dis_branch; if (opcode->flags & F_CONDBR) info->insn_type = dis_condbranch; if (opcode->flags & F_JSR) info->insn_type = dis_jsr; if (opcode->flags & F_DELAYED) info->branch_delay_insns = 1; } return sizeof (buffer); } } info->insn_type = dis_noninsn; /* Mark as non-valid instruction */ (*info->fprintf_func) (stream, "unknown"); return sizeof (buffer); } /* Compare opcodes A and B. */ static int compare_opcodes (a, b) char *a, *b; { struct sparc_opcode *op0 = (struct sparc_opcode *) a; struct sparc_opcode *op1 = (struct sparc_opcode *) b; unsigned long int match0 = op0->match, match1 = op1->match; unsigned long int lose0 = op0->lose, lose1 = op1->lose; register unsigned int i; /* If a bit is set in both match and lose, there is something wrong with the opcode table. */ if (match0 & lose0) { fprintf (stderr, "Internal error: bad sparc-opcode.h: \"%s\", %#.8lx, %#.8lx\n", op0->name, match0, lose0); op0->lose &= ~op0->match; lose0 = op0->lose; } if (match1 & lose1) { fprintf (stderr, "Internal error: bad sparc-opcode.h: \"%s\", %#.8lx, %#.8lx\n", op1->name, match1, lose1); op1->lose &= ~op1->match; lose1 = op1->lose; } /* Because the bits that are variable in one opcode are constant in another, it is important to order the opcodes in the right order. */ for (i = 0; i < 32; ++i) { unsigned long int x = 1 << i; int x0 = (match0 & x) != 0; int x1 = (match1 & x) != 0; if (x0 != x1) return x1 - x0; } for (i = 0; i < 32; ++i) { unsigned long int x = 1 << i; int x0 = (lose0 & x) != 0; int x1 = (lose1 & x) != 0; if (x0 != x1) return x1 - x0; } /* Put non-sparc64 insns ahead of sparc64 ones. */ if (V9_ONLY_P (op0) != V9_ONLY_P (op1)) return V9_ONLY_P (op0) - V9_ONLY_P (op1); /* They are functionally equal. So as long as the opcode table is valid, we can put whichever one first we want, on aesthetic grounds. */ /* Our first aesthetic ground is that aliases defer to real insns. */ { int alias_diff = (op0->flags & F_ALIAS) - (op1->flags & F_ALIAS); if (alias_diff != 0) /* Put the one that isn't an alias first. */ return alias_diff; } /* Except for aliases, two "identical" instructions had better have the same opcode. This is a sanity check on the table. */ i = strcmp (op0->name, op1->name); if (i) if (op0->flags & F_ALIAS) /* If they're both aliases, be arbitrary. */ return i; else fprintf (stderr, "Internal error: bad sparc-opcode.h: \"%s\" == \"%s\"\n", op0->name, op1->name); /* Fewer arguments are preferred. */ { int length_diff = strlen (op0->args) - strlen (op1->args); if (length_diff != 0) /* Put the one with fewer arguments first. */ return length_diff; } /* Put 1+i before i+1. */ { char *p0 = (char *) strchr(op0->args, '+'); char *p1 = (char *) strchr(op1->args, '+'); if (p0 && p1) { /* There is a plus in both operands. Note that a plus sign cannot be the first character in args, so the following [-1]'s are valid. */ if (p0[-1] == 'i' && p1[1] == 'i') /* op0 is i+1 and op1 is 1+i, so op1 goes first. */ return 1; if (p0[1] == 'i' && p1[-1] == 'i') /* op0 is 1+i and op1 is i+1, so op0 goes first. */ return -1; } } /* Put 1,i before i,1. */ { int i0 = strncmp (op0->args, "i,1", 3) == 0; int i1 = strncmp (op1->args, "i,1", 3) == 0; if (i0 ^ i1) return i0 - i1; } /* They are, as far as we can tell, identical. Since qsort may have rearranged the table partially, there is no way to tell which one was first in the opcode table as written, so just say there are equal. */ return 0; } /* Build a hash table from the opcode table. */ static void build_hash_table (table, hash_table, num_opcodes) struct sparc_opcode *table; struct opcode_hash **hash_table; int num_opcodes; { register int i; int hash_count[HASH_SIZE]; static struct opcode_hash *hash_buf = NULL; /* Start at the end of the table and work backwards so that each chain is sorted. */ memset (hash_table, 0, HASH_SIZE * sizeof (hash_table[0])); memset (hash_count, 0, HASH_SIZE * sizeof (hash_count[0])); if (hash_buf != NULL) free (hash_buf); hash_buf = (struct opcode_hash *) xmalloc (sizeof (struct opcode_hash) * num_opcodes); for (i = num_opcodes - 1; i >= 0; --i) { register int hash = HASH_INSN (sparc_opcodes[i].match); register struct opcode_hash *h = &hash_buf[i]; h->next = hash_table[hash]; h->opcode = &sparc_opcodes[i]; hash_table[hash] = h; ++hash_count[hash]; } #if 0 /* for debugging */ { int min_count = num_opcodes, max_count = 0; int total; for (i = 0; i < HASH_SIZE; ++i) { if (hash_count[i] < min_count) min_count = hash_count[i]; if (hash_count[i] > max_count) max_count = hash_count[i]; total += hash_count[i]; } printf ("Opcode hash table stats: min %d, max %d, ave %f\n", min_count, max_count, (double) total / HASH_SIZE); } #endif } smalltalk-3.2.5/opcode/ppc-dis.c0000644000175000017500000001557412123404352013412 00000000000000/* ppc-dis.c -- Disassemble PowerPC instructions Copyright 1994 Free Software Foundation, Inc. Written by Ian Lance Taylor, Cygnus Support This file is part of GDB, GAS, and the GNU binutils. GDB, GAS, and the GNU binutils are free software; you can redistribute them and/or modify them under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2, or (at your option) any later version. GDB, GAS, and the GNU binutils are distributed in the hope that they will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this file; see the file COPYING. If not, write to the Free Software Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. */ #include #include "ansidecl.h" #include "sysdep.h" #include "dis-asm.h" #include "opcode/ppc.h" /* This file provides several disassembler functions, all of which use the disassembler interface defined in dis-asm.h. Several functions are provided because this file handles disassembly for the PowerPC in both big and little endian mode and also for the POWER (RS/6000) chip. */ static int print_insn_powerpc PARAMS ((bfd_vma, struct disassemble_info *, int bigendian, int dialect)); /* Print a big endian PowerPC instruction. For convenience, also disassemble instructions supported by the Motorola PowerPC 601. */ int print_insn_big_powerpc (memaddr, info) bfd_vma memaddr; struct disassemble_info *info; { return print_insn_powerpc (memaddr, info, 1, PPC_OPCODE_PPC | PPC_OPCODE_601); } /* Print a little endian PowerPC instruction. For convenience, also disassemble instructions supported by the Motorola PowerPC 601. */ int print_insn_little_powerpc (memaddr, info) bfd_vma memaddr; struct disassemble_info *info; { return print_insn_powerpc (memaddr, info, 0, PPC_OPCODE_PPC | PPC_OPCODE_601); } /* Print a POWER (RS/6000) instruction. */ int print_insn_rs6000 (memaddr, info) bfd_vma memaddr; struct disassemble_info *info; { return print_insn_powerpc (memaddr, info, 1, PPC_OPCODE_POWER); } /* Print a PowerPC or POWER instruction. */ static int print_insn_powerpc (memaddr, info, bigendian, dialect) bfd_vma memaddr; struct disassemble_info *info; int bigendian; int dialect; { bfd_byte buffer[4]; int status; unsigned long insn; const struct powerpc_opcode *opcode; const struct powerpc_opcode *opcode_end; unsigned long op; status = (*info->read_memory_func) (memaddr, buffer, 4, info); if (status != 0) { (*info->memory_error_func) (status, memaddr, info); return -1; } if (bigendian) insn = bfd_getb32 (buffer); else insn = bfd_getl32 (buffer); /* Get the major opcode of the instruction. */ op = PPC_OP (insn); /* Find the first match in the opcode table. We could speed this up a bit by doing a binary search on the major opcode. */ opcode_end = powerpc_opcodes + powerpc_num_opcodes; for (opcode = powerpc_opcodes; opcode < opcode_end; opcode++) { unsigned long table_op; const unsigned char *opindex; const struct powerpc_operand *operand; int invalid; int need_comma; int need_paren; table_op = PPC_OP (opcode->opcode); if (op < table_op) break; if (op > table_op) continue; if ((insn & opcode->mask) != opcode->opcode || (opcode->flags & dialect) == 0) continue; /* Make two passes over the operands. First see if any of them have extraction functions, and, if they do, make sure the instruction is valid. */ invalid = 0; for (opindex = opcode->operands; *opindex != 0; opindex++) { operand = powerpc_operands + *opindex; if (operand->extract) (*operand->extract) (insn, &invalid); } if (invalid) continue; /* The instruction is valid. */ (*info->fprintf_func) (info->stream, "%s", opcode->name); if (opcode->operands[0] != 0) (*info->fprintf_func) (info->stream, "\t"); /* Now extract and print the operands. */ need_comma = 0; need_paren = 0; for (opindex = opcode->operands; *opindex != 0; opindex++) { long value; operand = powerpc_operands + *opindex; /* Operands that are marked FAKE are simply ignored. We already made sure that the extract function considered the instruction to be valid. */ if ((operand->flags & PPC_OPERAND_FAKE) != 0) continue; /* Extract the value from the instruction. */ if (operand->extract) value = (*operand->extract) (insn, (int *) NULL); else { value = (insn >> operand->shift) & ((1 << operand->bits) - 1); if ((operand->flags & PPC_OPERAND_SIGNED) != 0 && (value & (1 << (operand->bits - 1))) != 0) value -= 1 << operand->bits; } /* If the operand is optional, and the value is zero, don't print anything. */ if ((operand->flags & PPC_OPERAND_OPTIONAL) != 0 && (operand->flags & PPC_OPERAND_NEXT) == 0 && value == 0) continue; if (need_comma) { (*info->fprintf_func) (info->stream, ","); need_comma = 0; } /* Print the operand as directed by the flags. */ if ((operand->flags & PPC_OPERAND_GPR) != 0) (*info->fprintf_func) (info->stream, "r%ld", value); else if ((operand->flags & PPC_OPERAND_FPR) != 0) (*info->fprintf_func) (info->stream, "f%ld", value); else if ((operand->flags & PPC_OPERAND_RELATIVE) != 0) (*info->print_address_func) (memaddr + value, info); else if ((operand->flags & PPC_OPERAND_ABSOLUTE) != 0) (*info->print_address_func) ((bfd_vma) value & 0xffffffff, info); else if ((operand->flags & PPC_OPERAND_CR) == 0 || (dialect & PPC_OPCODE_PPC) == 0) (*info->fprintf_func) (info->stream, "%ld", value); else { if (operand->bits == 3) (*info->fprintf_func) (info->stream, "cr%d", value); else { static const char *cbnames[4] = { "lt", "gt", "eq", "so" }; int cr; int cc; cr = value >> 2; if (cr != 0) (*info->fprintf_func) (info->stream, "4*cr%d", cr); cc = value & 3; if (cc != 0) { if (cr != 0) (*info->fprintf_func) (info->stream, "+"); (*info->fprintf_func) (info->stream, "%s", cbnames[cc]); } } } if (need_paren) { (*info->fprintf_func) (info->stream, ")"); need_paren = 0; } if ((operand->flags & PPC_OPERAND_PARENS) == 0) need_comma = 1; else { (*info->fprintf_func) (info->stream, "("); need_paren = 1; } } /* We have found and printed an instruction; return. */ return 4; } /* We could not find a match. */ (*info->fprintf_func) (info->stream, ".long 0x%lx", insn); return 4; } smalltalk-3.2.5/opcode/disass.c0000644000175000017500000000356412123404352013335 00000000000000/******************************** -*- C -*- **************************** * * lightning disassembling support * ***********************************************************************/ /*********************************************************************** * * Copyright 2000 Free Software Foundation, Inc. * Written by Paolo Bonzini. * * This file is part of GNU lightning. * * GNU lightning is free software; you can redistribute it and/or modify it * under the terms of the GNU Lesser General Public License as published * by the Free Software Foundation; either version 2.1, or (at your option) * any later version. * * GNU lightning is distributed in the hope that it will be useful, but * WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY * or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser General Public * License for more details. * * You should have received a copy of the GNU Lesser General Public License * along with GNU lightning; see the file COPYING.LESSER; if not, write to the * Free Software Foundation, 51 Franklin Street, Fifth Floor, Boston, * MA 02110-1301, USA. * ***********************************************************************/ #include #include #include "config.h" #include "dis-asm.h" void disassemble(stream, from, to) FILE *stream; char *from, *to; { disassemble_info info; bfd_vma pc = (bfd_vma) from; bfd_vma end = (bfd_vma) to; INIT_DISASSEMBLE_INFO(info, stream, fprintf); info.buffer = NULL; info.buffer_vma = 0; info.buffer_length = end; while (pc < end) { fprintf_vma(stream, pc); putc('\t', stream); #ifdef LIGHTNING_I386 pc += print_insn_i386(pc, &info); #endif #ifdef LIGHTNING_PPC pc += print_insn_big_powerpc(pc, &info); #endif #ifdef LIGHTNING_SPARC pc += print_insn_sparc(pc, &info); #endif putc('\n', stream); } } smalltalk-3.2.5/config.h.in0000644000175000017500000006572312130455425012467 00000000000000/* config.h.in. Generated from configure.ac by autoheader. */ /* Define if building universal (internal helper macro) */ #undef AC_APPLE_UNIVERSAL_BUILD /* The normal alignment of `double', in bytes. */ #undef ALIGNOF_DOUBLE /* The normal alignment of `long double', in bytes. */ #undef ALIGNOF_LONG_DOUBLE /* The normal alignment of `long long', in bytes. */ #undef ALIGNOF_LONG_LONG /* Define to the extension for executable files, as it appears in argv[0]. */ #undef ARGV_EXEEXT /* Define to one of `_getb67', `GETB67', `getb67' for Cray-2 and Cray-YMP systems. This function is required for `alloca.c' support on those systems. */ #undef CRAY_STACKSEG_END /* Define to 1 if using `alloca.c'. */ #undef C_ALLOCA /* Define to include a disassembler in the gst executable */ #undef ENABLE_DISASSEMBLER /* Define to enable usage of libltdl to load external modules at runtime */ #undef ENABLE_DLD /* Define to enable dynamic translation to machine code */ #undef ENABLE_JIT_TRANSLATION /* Define to enable preemptive multitasking of Smalltalk processes */ #undef ENABLE_PREEMPTION /* The relative path from the program to the exec_prefix. Defined only for relocatable installs. */ #undef EXEC_PREFIX /* Define to the extension for executable files. */ #undef EXEEXT /* Define to the #include directive for GLUT. */ #undef GL_GLUT_H /* Define to the #include directive for OpenGL glu functions. */ #undef GL_GLU_H /* Define to the #include directive for OpenGL. */ #undef GL_GL_H /* Define to 1 if you have the `accept4' function. */ #undef HAVE_ACCEPT4 /* Define to 1 if you have the `acosl' function. */ #undef HAVE_ACOSL /* Define to 1 if you have the `alarm' function. */ #undef HAVE_ALARM /* Define to 1 if you have `alloca', as a function or macro. */ #undef HAVE_ALLOCA /* Define to 1 if you have and it should be used (not on Ultrix). */ #undef HAVE_ALLOCA_H /* Define to 1 if you have the `argz_append' function. */ #undef HAVE_ARGZ_APPEND /* Define to 1 if you have the `argz_create_sep' function. */ #undef HAVE_ARGZ_CREATE_SEP /* Define to 1 if you have the header file. */ #undef HAVE_ARGZ_H /* Define to 1 if you have the `argz_insert' function. */ #undef HAVE_ARGZ_INSERT /* Define to 1 if you have the `argz_next' function. */ #undef HAVE_ARGZ_NEXT /* Define to 1 if you have the `argz_stringify' function. */ #undef HAVE_ARGZ_STRINGIFY /* Define to 1 if you have the header file. */ #undef HAVE_ARPA_INET_H /* Define to 1 if you have the `asinl' function. */ #undef HAVE_ASINL /* Define to 1 if you have the header file. */ #undef HAVE_ASSERT_H /* Define to 1 if you have the `atanl' function. */ #undef HAVE_ATANL /* Define to 1 if you have the `bcopy' function. */ #undef HAVE_BCOPY /* Define to 1 if you have the `ceill' function. */ #undef HAVE_CEILL /* Define to 1 if you have the `chown' function. */ #undef HAVE_CHOWN /* Define if the system provides clock_gettime. */ #undef HAVE_CLOCK_GETTIME /* Define to 1 if you have the `closedir' function. */ #undef HAVE_CLOSEDIR /* Define to 1 if you have the `cosl' function. */ #undef HAVE_COSL /* Define to 1 if you have the header file. */ #undef HAVE_CRT_EXTERNS_H /* Define to 1 if you have the header file. */ #undef HAVE_CTYPE_H /* Define to 1 if you have the declaration of `freeaddrinfo', and to 0 if you don't. */ #undef HAVE_DECL_FREEADDRINFO /* Define to 1 if you have the declaration of `gai_strerror', and to 0 if you don't. */ #undef HAVE_DECL_GAI_STRERROR /* Define to 1 if you have the declaration of `getaddrinfo', and to 0 if you don't. */ #undef HAVE_DECL_GETADDRINFO /* Define to 1 if you have the declaration of `getnameinfo', and to 0 if you don't. */ #undef HAVE_DECL_GETNAMEINFO /* Define to 1 if you have the header file, and it defines `DIR'. */ #undef HAVE_DIRENT_H /* Define if you have the GNU dld library. */ #undef HAVE_DLD /* Define to 1 if you have the header file. */ #undef HAVE_DLD_H /* Define to 1 if you have the `dlerror' function. */ #undef HAVE_DLERROR /* Define to 1 if you have the header file. */ #undef HAVE_DLFCN_H /* Define to 1 if you have the header file. */ #undef HAVE_DL_H /* Define if you have the _dyld_func_lookup function. */ #undef HAVE_DYLD /* Define to 1 if you have the `endgrent' function. */ #undef HAVE_ENDGRENT /* Define to 1 if you have the `endpwent' function. */ #undef HAVE_ENDPWENT /* Define if you have the declaration of environ. */ #undef HAVE_ENVIRON_DECL /* Define to 1 if you have the header file. */ #undef HAVE_ERRNO_H /* Define to 1 if the system has the type `error_t'. */ #undef HAVE_ERROR_T /* Define to 1 if you have the header file. */ #undef HAVE_EXECINFO_H /* Define to 1 if you have the `expl' function. */ #undef HAVE_EXPL /* Define to 1 if you have the header file. */ #undef HAVE_FCNTL_H /* Define to 1 if you have the `floorl' function. */ #undef HAVE_FLOORL /* Define to 1 if you have the `fork' function. */ #undef HAVE_FORK /* Define to 1 if you have the `frexpl' function. */ #undef HAVE_FREXPL /* Define to 1 if you have the `ftruncate' function. */ #undef HAVE_FTRUNCATE /* Define to 1 if you have the `getaddrinfo' function. */ #undef HAVE_GETADDRINFO /* Define to 1 if you have the `getdtablesize' function. */ #undef HAVE_GETDTABLESIZE /* Define to 1 if you have the `getgrnam' function. */ #undef HAVE_GETGRNAM /* Define to 1 if you have the `gethostname' function. */ #undef HAVE_GETHOSTNAME /* Define to 1 if you have the `getipnodebyaddr' function. */ #undef HAVE_GETIPNODEBYADDR /* Define to 1 if you have the `getpagesize' function. */ #undef HAVE_GETPAGESIZE /* Define to 1 if you have the `getpwnam' function. */ #undef HAVE_GETPWNAM /* Define to 1 if you have the `getrusage' function. */ #undef HAVE_GETRUSAGE /* Define to 1 if you have the `gettimeofday' function. */ #undef HAVE_GETTIMEOFDAY /* Define if your system has GLUT installed. */ #undef HAVE_GLUT /* Define to 1 if you have the header file. */ #undef HAVE_GLUT_FREEGLUT_H /* Define to 1 if you have the header file. */ #undef HAVE_GLUT_GLUT_H /* Define to 1 if you have the header file. */ #undef HAVE_GL_FREEGLUT_H /* Define to 1 if you have the header file. */ #undef HAVE_GL_GLUT_H /* Define to 1 if you have the header file. */ #undef HAVE_GL_GLU_H /* Define to 1 if you have the header file. */ #undef HAVE_GL_GL_H /* Define if your system has the GNU MP library. */ #undef HAVE_GMP /* Define to 1 if gnutls is being used */ #undef HAVE_GNUTLS /* Define if your CC has the '&&' and 'goto void *' GCC extensions. */ #undef HAVE_GOTO_VOID_P /* Define to 1 if you have the `grantpt' function. */ #undef HAVE_GRANTPT /* Define to 1 if you have the `g_poll' function. */ #undef HAVE_G_POLL /* Define if you have the iconv() function. */ #undef HAVE_ICONV /* Define to 1 if you have the `index' function. */ #undef HAVE_INDEX /* Define to 1 if you have the `inet_ntop' function. */ #undef HAVE_INET_NTOP /* Define to 1 if the system has the type `intmax_t'. */ #undef HAVE_INTMAX_T /* Define to 1 if the system has the type `intptr_t'. */ #undef HAVE_INTPTR_T /* Define to 1 if you have the header file. */ #undef HAVE_INTTYPES_H /* Define to 1 if defines AF_INET. */ #undef HAVE_IPV4 /* Define to 1 if defines AF_INET6. */ #undef HAVE_IPV6 /* Define if you have and nl_langinfo(CODESET). */ #undef HAVE_LANGINFO_CODESET /* Define to 1 if you have the `ldexpl' function. */ #undef HAVE_LDEXPL /* Define if you have the libdl library or equivalent. */ #undef HAVE_LIBDL /* Define to 1 if you have the `expat' library (-lexpat). */ #undef HAVE_LIBEXPAT /* Define to 1 if you have the `gnutls' library (-lgnutls). */ #undef HAVE_LIBGNUTLS /* Define to 1 if you have the `libffi' library (-llibffi). */ #undef HAVE_LIBLIBFFI /* Define to 1 if you have the `ltdl' library (-lltdl). */ #undef HAVE_LIBLTDL /* Define to 1 if you have the `m' library (-lm). */ #undef HAVE_LIBM /* Define to 1 if you have the `ncurses' library (-lncurses). */ #undef HAVE_LIBNCURSES /* Define to 1 if you have the `pq' library (-lpq). */ #undef HAVE_LIBPQ /* Define to 1 if you have the `SDL_image' library (-lSDL_image). */ #undef HAVE_LIBSDL_IMAGE /* Define to 1 if you have the `SDL_mixer' library (-lSDL_mixer). */ #undef HAVE_LIBSDL_MIXER /* Define to 1 if you have the `SDL_sound' library (-lSDL_sound). */ #undef HAVE_LIBSDL_SOUND /* Define to 1 if you have the `SDL_ttf' library (-lSDL_ttf). */ #undef HAVE_LIBSDL_TTF /* Define to 1 if you have the `sigsegv' library (-lsigsegv). */ #undef HAVE_LIBSIGSEGV /* Define to 1 if you have the `sqlite3' library (-lsqlite3). */ #undef HAVE_LIBSQLITE3 /* Define to 1 if you have the `z' library (-lz). */ #undef HAVE_LIBZ /* Define if GNU lightning can be used */ #undef HAVE_LIGHTNING /* Define to 1 if you have the header file. */ #undef HAVE_LIMITS_H /* Define to 1 if you have the `logl' function. */ #undef HAVE_LOGL /* Define to 1 if the system has the type `long long int'. */ #undef HAVE_LONG_LONG_INT /* Define to 1 if you have the `lrint' function. */ #undef HAVE_LRINT /* Define to 1 if you have the `lrintf' function. */ #undef HAVE_LRINTF /* Define to 1 if you have the `lrintl' function. */ #undef HAVE_LRINTL /* Define to 1 if you have the `lstat' function. */ #undef HAVE_LSTAT /* Define to 1 if you have the header file. */ #undef HAVE_MACH_O_DYLD_H /* Define to 1 if you have the `madvise' function. */ #undef HAVE_MADVISE /* Define to 1 if you have the header file. */ #undef HAVE_MALLOC_H /* Define to 1 if you have the `memcpy' function. */ #undef HAVE_MEMCPY /* Define to 1 if you have the `memmove' function. */ #undef HAVE_MEMMOVE /* Define to 1 if you have the header file. */ #undef HAVE_MEMORY_H /* Define to 1 if you have the `mkdtemp' function. */ #undef HAVE_MKDTEMP /* Define to 1 if you have the `mkstemp' function. */ #undef HAVE_MKSTEMP /* Define to 1 if you have the `mprotect' function. */ #undef HAVE_MPROTECT /* Define if the system provides nanosleep. */ #undef HAVE_NANOSLEEP /* Define to 1 if you have the header file, and it defines `DIR'. */ #undef HAVE_NDIR_H /* Define to 1 if you have the header file. */ #undef HAVE_NETDB_H /* Define to 1 if you have the header file. */ #undef HAVE_NETINET_IN_H /* Define to 1 if you have the `nl_langinfo' function. */ #undef HAVE_NL_LANGINFO /* Define to 1 if libc includes obstacks. */ #undef HAVE_OBSTACK /* Define to 1 if you have the `opendir' function. */ #undef HAVE_OPENDIR /* Define if your system has OpenGL installed. */ #undef HAVE_OPENGL /* Define to 1 if you have the header file. */ #undef HAVE_OPENGL_GLU_H /* Define to 1 if you have the header file. */ #undef HAVE_OPENGL_GL_H /* Define to 1 if you have the header file. */ #undef HAVE_POLL_H /* Define to 1 if you have the `popen' function. */ #undef HAVE_POPEN /* Define to 1 if you have the `powl' function. */ #undef HAVE_POWL /* Define to 1 if you have the `pread' function. */ #undef HAVE_PREAD /* Define if libtool can extract symbol lists from object files. */ #undef HAVE_PRELOADED_SYMBOLS /* Define if the defines PTHREAD_MUTEX_RECURSIVE. */ #undef HAVE_PTHREAD_MUTEX_RECURSIVE /* Define if the POSIX multithreading library has read/write locks. */ #undef HAVE_PTHREAD_RWLOCK /* Define to 1 if you have the `putenv' function. */ #undef HAVE_PUTENV /* Define to 1 if you have the `pwrite' function. */ #undef HAVE_PWRITE /* Define to 1 if you have the `readdir' function. */ #undef HAVE_READDIR /* Define if your system has the GNU readline library. */ #undef HAVE_READLINE /* Define to 1 if you have the `readlink' function. */ #undef HAVE_READLINK /* Define to 1 if you have the `rindex' function. */ #undef HAVE_RINDEX /* Define to 1 if you have the `select' function. */ #undef HAVE_SELECT /* Define to 1 if you have the `setenv' function. */ #undef HAVE_SETENV /* Define to 1 if you have the `setgroupent' function. */ #undef HAVE_SETGROUPENT /* Define to 1 if you have the `setpassent' function. */ #undef HAVE_SETPASSENT /* Define to 1 if you have the `setsid' function. */ #undef HAVE_SETSID /* Define if you have the shl_load function. */ #undef HAVE_SHL_LOAD /* Define to 1 if you have the `sighold' function. */ #undef HAVE_SIGHOLD /* Define to 1 if libsigsegv is being used */ #undef HAVE_SIGSEGV_H /* Define to 1 if you have the `sigsetmask' function. */ #undef HAVE_SIGSETMASK /* Define to 1 if you have the `sinl' function. */ #undef HAVE_SINL /* Define if your system has sockets. */ #undef HAVE_SOCKETS /* Define to 1 if you have the `spawnl' function. */ #undef HAVE_SPAWNL /* Define to 1 if you have the `sqrtl' function. */ #undef HAVE_SQRTL /* Define to 1 if you have the header file. */ #undef HAVE_STDDEF_H /* Define to 1 if you have the header file. */ #undef HAVE_STDINT_H /* Define to 1 if you have the header file. */ #undef HAVE_STDIO_H /* Define to 1 if you have the header file. */ #undef HAVE_STDLIB_H /* Define to 1 if you have the `strchr' function. */ #undef HAVE_STRCHR /* Define to 1 if you have the `strcmp' function. */ #undef HAVE_STRCMP /* Define to 1 if you have the `strdup' function. */ #undef HAVE_STRDUP /* Define to 1 if you have the `strerror' function. */ #undef HAVE_STRERROR /* Define to 1 if you have the header file. */ #undef HAVE_STRINGS_H /* Define to 1 if you have the header file. */ #undef HAVE_STRING_H /* Define to 1 if you have the header file. */ #undef HAVE_STROPTS_H /* Define to 1 if you have the `strpbrk' function. */ #undef HAVE_STRPBRK /* Define to 1 if you have the `strrchr' function. */ #undef HAVE_STRRCHR /* Define to 1 if you have the `strsep' function. */ #undef HAVE_STRSEP /* Define to 1 if you have the `strsignal' function. */ #undef HAVE_STRSIGNAL /* Define to 1 if you have the `strstr' function. */ #undef HAVE_STRSTR /* Define if your system's netdb.h has struct addrinfo */ #undef HAVE_STRUCT_ADDRINFO /* Define to 1 if `sa_len' is a member of `struct sockaddr'. */ #undef HAVE_STRUCT_SOCKADDR_SA_LEN /* Define to 1 if `st_mtimensec' is a member of `struct stat'. */ #undef HAVE_STRUCT_STAT_ST_MTIMENSEC /* Define to 1 if `st_mtimespec.tv_nsec' is a member of `struct stat'. */ #undef HAVE_STRUCT_STAT_ST_MTIMESPEC_TV_NSEC /* Define to 1 if `st_mtim.tv_nsec' is a member of `struct stat'. */ #undef HAVE_STRUCT_STAT_ST_MTIM_TV_NSEC /* Define to 1 if you have the `symlink' function. */ #undef HAVE_SYMLINK /* Define to 1 if the host supports __sync_* builtins */ #undef HAVE_SYNC_BUILTINS /* Define to 1 if you have the header file, and it defines `DIR'. */ #undef HAVE_SYS_DIR_H /* Define to 1 if you have the header file. */ #undef HAVE_SYS_DL_H /* Define to 1 if you have the header file. */ #undef HAVE_SYS_FILE_H /* Define to 1 if you have the header file. */ #undef HAVE_SYS_IOCTL_H /* Define to 1 if you have the header file. */ #undef HAVE_SYS_MMAN_H /* Define to 1 if you have the header file, and it defines `DIR'. */ #undef HAVE_SYS_NDIR_H /* Define to 1 if you have the header file. */ #undef HAVE_SYS_PARAM_H /* Define to 1 if you have the header file. */ #undef HAVE_SYS_RESOURCE_H /* Define to 1 if you have the header file. */ #undef HAVE_SYS_SELECT_H /* Define to 1 if you have the header file. */ #undef HAVE_SYS_STAT_H /* Define to 1 if you have the header file. */ #undef HAVE_SYS_TIMEB_H /* Define to 1 if you have the header file. */ #undef HAVE_SYS_TYPES_H /* Define to 1 if you have the header file. */ #undef HAVE_SYS_UTSNAME_H /* Define to 1 if you have the header file. */ #undef HAVE_SYS_WAIT_H /* Define to 1 if you have the `tanl' function. */ #undef HAVE_TANL /* Define if your system has Tcl/Tk, 8.0 or later, installed. */ #undef HAVE_TCLTK /* Define to 1 if you have the header file. */ #undef HAVE_TERMIOS_H /* Define if the system provides timer_create. */ #undef HAVE_TIMER_CREATE /* Define to 1 if you have the `trunc' function. */ #undef HAVE_TRUNC /* Define to 1 if you have the `truncf' function. */ #undef HAVE_TRUNCF /* Define to 1 if you have the `truncl' function. */ #undef HAVE_TRUNCL /* Define to 1 if the system has the type `uintmax_t'. */ #undef HAVE_UINTMAX_T /* Define to 1 if the system has the type `uintptr_t'. */ #undef HAVE_UINTPTR_T /* Define to 1 if you have the `uname' function. */ #undef HAVE_UNAME /* Define to 1 if you have the header file. */ #undef HAVE_UNISTD_H /* Define to 1 if the system has the type `unsigned long long int'. */ #undef HAVE_UNSIGNED_LONG_LONG_INT /* Define to 1 if you have the `usleep' function. */ #undef HAVE_USLEEP /* Define to 1 if you have the `utime' function. */ #undef HAVE_UTIME /* Define to 1 if you have the `utimes' function. */ #undef HAVE_UTIMES /* Define to 1 if you have the header file. */ #undef HAVE_UTIME_H /* Define if the C compiler support the ELF hidden visibility */ #undef HAVE_VISIBILITY_HIDDEN /* Define to 1 if you have the `waitpid' function. */ #undef HAVE_WAITPID /* Define to 1 if you have the header file. */ #undef HAVE_WS2TCPIP_H /* Define to 1 if you have the `_NSGetEnviron' function. */ #undef HAVE__NSGETENVIRON /* Define to 1 if you have the `_NSGetExecutablePath' function. */ #undef HAVE__NSGETEXECUTABLEPATH /* Define to the host triplet. */ #undef HOST_SYSTEM /* Define as const if the declaration of iconv() needs const. */ #undef ICONV_CONST /* The relative path from the program to the image path. Defined only for relocatable installs. */ #undef IMAGE_PATH /* The relative path from the program to the kernel path. Defined only for relocatable installs. */ #undef KERNEL_PATH /* The relative path from the program to the per-package libexec path. Defined only for relocatable installs. */ #undef LIBEXEC_PATH /* Define if your system's localtime(3) caches the timezone. */ #undef LOCALTIME_CACHE /* Define if the OS needs help to load dependent libraries for dlopen(). */ #undef LTDL_DLOPEN_DEPLIBS /* Define to the sub-directory in which libtool stores uninstalled libraries. */ #undef LTDL_OBJDIR /* Define to the name of the environment variable that determines the dynamic library search path. */ #undef LTDL_SHLIBPATH_VAR /* Define to the extension used for shared libraries, say, ".so". */ #undef LTDL_SHLIB_EXT /* Define to the system default library search path. */ #undef LTDL_SYSSEARCHPATH /* Define to the sub-directory in which libtool stores uninstalled libraries. */ #undef LT_OBJDIR /* E-Mail address of the person maintaining this package */ #undef MAINTAINER /* The relative path from the program to the module path. Defined only for relocatable installs. */ #undef MODULE_PATH /* Define to 1 if assertions should be disabled. */ #undef NDEBUG /* Define if dlsym() requires a leading underscore in symbol names. */ #undef NEED_USCORE /* Define to disable assertion checking at runtime */ #undef OPTIMIZE /* Name of package */ #undef PACKAGE /* Define to the address where bug reports for this package should be sent. */ #undef PACKAGE_BUGREPORT /* The git version that GNU Smalltalk was compiled from. */ #undef PACKAGE_GIT_REVISION /* Define to the full name of this package. */ #undef PACKAGE_NAME /* Define to the full name and version of this package. */ #undef PACKAGE_STRING /* Define to the one symbol short name of this package. */ #undef PACKAGE_TARNAME /* Define to the home page for this package. */ #undef PACKAGE_URL /* Define to the version of this package. */ #undef PACKAGE_VERSION /* The relative path from the program to the prefix. Defined only for relocatable installs. */ #undef PREFIX /* Define as the return type of signal handlers (`int' or `void'). */ #undef RETSIGTYPE /* The size of `int', as computed by sizeof. */ #undef SIZEOF_INT /* The size of `long', as computed by sizeof. */ #undef SIZEOF_LONG /* The size of `mp_limb_t', as computed by sizeof. */ #undef SIZEOF_MP_LIMB_T /* The size of `off_t', as computed by sizeof. */ #undef SIZEOF_OFF_T /* The size of `OOP', as computed by sizeof. */ #undef SIZEOF_OOP /* The size of `wchar_t', as computed by sizeof. */ #undef SIZEOF_WCHAR_T /* If using the C implementation of alloca, define if you know the direction of stack growth for your system; otherwise it will be automatically deduced at runtime. STACK_DIRECTION > 0 => grows toward higher addresses STACK_DIRECTION < 0 => grows toward lower addresses STACK_DIRECTION = 0 => direction of growth unknown */ #undef STACK_DIRECTION /* Define to 1 if you have the ANSI C header files. */ #undef STDC_HEADERS /* Patch level version of GNU Smalltalk */ #undef ST_EDIT_VERSION /* Major version of GNU Smalltalk */ #undef ST_MAJOR_VERSION /* Minor version of GNU Smalltalk */ #undef ST_MINOR_VERSION /* Define to 1 if you can safely include both and . */ #undef TIME_WITH_SYS_TIME /* Define if the POSIX multithreading library can be used. */ #undef USE_POSIX_THREADS /* Enable extensions on AIX 3, Interix. */ #ifndef _ALL_SOURCE # undef _ALL_SOURCE #endif /* Enable GNU extensions on systems that have them. */ #ifndef _GNU_SOURCE # undef _GNU_SOURCE #endif /* Enable threading extensions on Solaris. */ #ifndef _POSIX_PTHREAD_SEMANTICS # undef _POSIX_PTHREAD_SEMANTICS #endif /* Enable extensions on HP NonStop. */ #ifndef _TANDEM_SOURCE # undef _TANDEM_SOURCE #endif /* Enable general extensions on Solaris. */ #ifndef __EXTENSIONS__ # undef __EXTENSIONS__ #endif /* Define if the Win32 multithreading API can be used. */ #undef USE_WIN32_THREADS /* Version number of package */ #undef VERSION /* Define WORDS_BIGENDIAN to 1 if your processor stores words with the most significant byte first (like Motorola and SPARC, unlike Intel). */ #if defined AC_APPLE_UNIVERSAL_BUILD # if defined __BIG_ENDIAN__ # define WORDS_BIGENDIAN 1 # endif #else # ifndef WORDS_BIGENDIAN # undef WORDS_BIGENDIAN # endif #endif /* Define to 1 if the X Window System is missing or not being used. */ #undef X_DISPLAY_MISSING /* Define to 1 if, like Solaris, your system has a sys/avl.h header that pollutes the name space. */ #undef _AVL_H /* Enable large inode numbers on Mac OS X 10.5. */ #ifndef _DARWIN_USE_64_BIT_INODE # define _DARWIN_USE_64_BIT_INODE 1 #endif /* Number of bits in a file offset, on hosts where this is settable. */ #undef _FILE_OFFSET_BITS /* Define for large files, on AIX-style hosts. */ #undef _LARGE_FILES /* Define to 1 if on MINIX. */ #undef _MINIX /* Define to 2 if the system does not provide POSIX.1 features except with this defined. */ #undef _POSIX_1_SOURCE /* Define to 1 if you need to in order for `stat' and other things to work. */ #undef _POSIX_SOURCE /* Define for Solaris 2.5.1 so the uint32_t typedef from , , or is not used. If the typedef were allowed, the #define below would cause a syntax error. */ #undef _UINT32_T /* Define for Solaris 2.5.1 so the uint64_t typedef from , , or is not used. If the typedef were allowed, the #define below would cause a syntax error. */ #undef _UINT64_T /* Define for Solaris 2.5.1 so the uint8_t typedef from , , or is not used. If the typedef were allowed, the #define below would cause a syntax error. */ #undef _UINT8_T /* Define to empty if `const' does not conform to ANSI C. */ #undef const /* Define to an appropriate function call if the system does not provide the environ variable. */ #undef environ /* Define to a type to use for `error_t' if it is not otherwise available. */ #undef error_t /* Define to poll if your glib does not provide g_poll. */ #undef g_poll /* Define to `__inline__' or `__inline' if that's what the C compiler calls it, or to nothing if 'inline' is not supported under any name. */ #ifndef __cplusplus #undef inline #endif /* Define to the type of a signed integer type of width exactly 16 bits if such a type exists and the standard includes do not define it. */ #undef int16_t /* Define to the type of a signed integer type of width exactly 32 bits if such a type exists and the standard includes do not define it. */ #undef int32_t /* Define to the type of a signed integer type of width exactly 64 bits if such a type exists and the standard includes do not define it. */ #undef int64_t /* Define to the type of a signed integer type of width exactly 8 bits if such a type exists and the standard includes do not define it. */ #undef int8_t /* Define to the widest signed integer type if and do not define. */ #undef intmax_t /* Define to the type of a signed integer type wide enough to hold a pointer, if such a type exists, and if the system does not define it. */ #undef intptr_t /* Define to `int' if does not define. */ #undef pid_t /* Define to rpl_poll if the replacement function should be used. */ #undef poll /* Define to the equivalent of the C99 'restrict' keyword, or to nothing if this is not supported. Do not define if restrict is supported directly. */ #undef restrict /* Work around a bug in Sun C++: it does not support _Restrict or __restrict__, even though the corresponding Sun C compiler ends up with "#define restrict _Restrict" or "#define restrict __restrict__" in the previous line. Perhaps some future version of Sun C++ will work with restrict; if so, hopefully it defines __RESTRICT like Sun C does. */ #if defined __SUNPRO_CC && !defined __RESTRICT # define _Restrict # define __restrict__ #endif /* Define to completion_matches if you have an older readline */ #undef rl_completion_matches /* Define to filename_completion_function if you have an older readline */ #undef rl_filename_completion_function /* Define to username_completion_function if you have an older readline */ #undef rl_username_completion_function /* Define to `unsigned int' if does not define. */ #undef size_t /* Define to the type of an unsigned integer type of width exactly 16 bits if such a type exists and the standard includes do not define it. */ #undef uint16_t /* Define to the type of an unsigned integer type of width exactly 32 bits if such a type exists and the standard includes do not define it. */ #undef uint32_t /* Define to the type of an unsigned integer type of width exactly 64 bits if such a type exists and the standard includes do not define it. */ #undef uint64_t /* Define to the type of an unsigned integer type of width exactly 8 bits if such a type exists and the standard includes do not define it. */ #undef uint8_t /* Define to the widest unsigned integer type if and do not define. */ #undef uintmax_t /* Define to the type of an unsigned integer type wide enough to hold a pointer, if such a type exists, and if the system does not define it. */ #undef uintptr_t smalltalk-3.2.5/libgst/0000755000175000017500000000000012130456004011765 500000000000000smalltalk-3.2.5/libgst/interp.c0000644000175000017500000024562612130343734013376 00000000000000/******************************** -*- C -*- **************************** * * The Smalltalk Virtual Machine itself. * * This, together with oop.c, is the `bridge' between Smalltalk and * the underlying machine * * ***********************************************************************/ /*********************************************************************** * * Copyright 1988,89,90,91,92,94,95,99,2000,2001,2002,2006,2007,2008,2009 * Free Software Foundation, Inc. * Written by Steve Byrne. * * This file is part of GNU Smalltalk. * * GNU Smalltalk is free software; you can redistribute it and/or modify it * under the terms of the GNU General Public License as published by the Free * Software Foundation; either version 2, or (at your option) any later * version. * * Linking GNU Smalltalk statically or dynamically with other modules is * making a combined work based on GNU Smalltalk. Thus, the terms and * conditions of the GNU General Public License cover the whole * combination. * * In addition, as a special exception, the Free Software Foundation * give you permission to combine GNU Smalltalk with free software * programs or libraries that are released under the GNU LGPL and with * independent programs running under the GNU Smalltalk virtual machine. * * You may copy and distribute such a system following the terms of the * GNU GPL for GNU Smalltalk and the licenses of the other code * concerned, provided that you include the source code of that other * code when and as the GNU GPL requires distribution of source code. * * Note that people who make modified versions of GNU Smalltalk are not * obligated to grant this special exception for their modified * versions; it is their choice whether to do so. The GNU General * Public License gives permission to release a modified version without * this exception; this exception also makes it possible to release a * modified version which carries forward this exception. * * GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or * FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for * more details. * * You should have received a copy of the GNU General Public License along with * GNU Smalltalk; see the file COPYING. If not, write to the Free Software * Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * ***********************************************************************/ #include "gstpriv.h" #include "lock.h" /* The local regs concept hopes, by caching the values of IP and SP in local register variables, to increase performance. You only need to export the variables when calling out to routines that might change them and that create objects. This is because creating objects may trigger the GC, which can change the values of IP and SP (since they point into the object space). It's easy to deal with that, however, it's just a matter of importing and exporting the registers at the correct places: for example stack operations are innocuous, while message sends can result in a GC (because stack chunks are exhausted or because primitive #new is invoked), so they export the registers and import them (possibly with their value changed by the GC) after the send. I'm leaving the code to deal with them as local registers conditionally compiled in so that you can disable it easily if necessary; however this seems quite improbable except for debugging purposes. */ #define LOCAL_REGS /* By "hard wiring" the definitions of the special math operators (bytecodes 176-191), we get a performance boost of more than 50%. Yes, it means that we cannot redefine + et al for SmallInteger and Float, but I think the trade is worth it. Besides, the Blue Book does it. */ #define OPEN_CODE_MATH /* Pipelining uses separate fetch-decode-execute stages, which is a nice choice for VLIW machines. It also enables more aggressive caching of global variables. It is currently enabled for the IA-64 only, because it is a win only where we would have had lots of unused instruction scheduling slots and an awful lot of registers. */ #if REG_AVAILABILITY == 3 #define PIPELINING #endif /* Answer the quantum assigned to each Smalltalk process (in milliseconds) before it is preempted. Setting this to zero disables preemption until gst_processor_scheduler>>#timeSlice: is invoked. */ #define DEFAULT_PREEMPTION_TIMESLICE 40 /* This symbol does not control execution speed. Instead, it causes SEND_MESSAGE to print every message that is ever sent in the SmallInteger(Object)>>#printString form. Can be useful to find out the last method sent before an error, if the context stack is trashed when the debugger gets control and printing a backtrace is impossible. */ /* #define DEBUG_CODE_FLOW */ /* The method cache is a hash table used to cache the most commonly used methods. Its size is determined by this preprocessor constant. It is currently 2048, a mostly random choice; you can modify it, but be sure it is a power of two. Additionally, separately from this, the interpreter caches the last primitive numbers used for sends of #at:, #at:put: and #size, in an attempt to speed up these messages for Arrays, Strings, and ByteArrays. */ #define METHOD_CACHE_SIZE (1 << 11) typedef struct interp_jmp_buf { jmp_buf jmpBuf; struct interp_jmp_buf *next; unsigned short suspended; unsigned char interpreter; unsigned char interrupted; OOP processOOP; } interp_jmp_buf; /* If this is true, for each byte code that is executed, we print on stdout the byte index within the current gst_compiled_method and a decoded interpretation of the byte code. */ int _gst_execution_tracing = 0; /* When this is true, and an interrupt occurs (such as SIGABRT), Smalltalk will terminate itself by making a core dump (normally it produces a backtrace). */ mst_Boolean _gst_make_core_file = false; /* When true, this indicates that there is no top level loop for control to return to, so it causes the system to exit. */ mst_Boolean _gst_non_interactive = true; /* The table of functions that implement the primitives. */ prim_table_entry _gst_primitive_table[NUM_PRIMITIVES]; prim_table_entry _gst_default_primitive_table[NUM_PRIMITIVES]; /* Some performance counters from the interpreter: these count the number of special returns. */ unsigned long _gst_literal_returns = 0; unsigned long _gst_inst_var_returns = 0; unsigned long _gst_self_returns = 0; /* The number of primitives executed. */ unsigned long _gst_primitives_executed = 0; /* The number of bytecodes executed. */ unsigned long _gst_bytecode_counter = 0; /* The number of method cache misses */ unsigned long _gst_cache_misses = 0; /* The number of cache lookups - either hits or misses */ unsigned long _gst_sample_counter = 0; /* The OOP for an IdentityDictionary that stores the raw profile. */ OOP _gst_raw_profile = NULL; /* A bytecode counter value used while profiling. */ unsigned long _gst_saved_bytecode_counter = 0; #ifdef ENABLE_JIT_TRANSLATION #define method_base 0 char *native_ip = NULL; #else /* plain bytecode interpreter */ static ip_type method_base; #endif /* Global state The following variables constitute the interpreter's state: ip -- the real memory address of the next byte code to be executed. sp -- the real memory address of the stack that's stored in the currently executing block or method context. _gst_this_method -- a gst_compiled_method or gst_compiled_block that is the currently executing method. _gst_this_context_oop -- a gst_block_context or gst_method_context that indicates the context that the interpreter is currently running in. _gst_temporaries -- physical address of the base of the method temporary variables. Typically a small number of bytes (multiple of 4 since it points to OOPs) lower than sp. _gst_literals -- physical address of the base of the method literals. _gst_self -- an OOP that is the current receiver of the current message. */ /* The virtual machine's stack and instruction pointers. */ OOP *sp = NULL; ip_type ip; OOP *_gst_temporaries = NULL; OOP *_gst_literals = NULL; OOP _gst_self = NULL; OOP _gst_this_context_oop = NULL; OOP _gst_this_method = NULL; /* Signal this semaphore at the following instruction. */ static OOP single_step_semaphore = NULL; /* CompiledMethod cache which memoizes the methods and some more information for each class->selector pairs. */ static method_cache_entry method_cache[METHOD_CACHE_SIZE] CACHELINE_ALIGNED; /* The number of the last primitive called. */ static int last_primitive; /* A special cache that tries to skip method lookup when #at:, #at:put and #size are implemented by a class through a primitive, and is repeatedly sent to instances of the same class. Since this is a mini-inline cache it makes no sense when JIT translation is enabled. */ #ifndef ENABLE_JIT_TRANSLATION static OOP at_cache_class; static intptr_t at_cache_spec; static OOP at_put_cache_class; static intptr_t at_put_cache_spec; static OOP size_cache_class; static int size_cache_prim; static OOP class_cache_class; static int class_cache_prim; #endif /* Queue for async (outside the interpreter) semaphore signals */ static mst_Boolean async_queue_enabled = true; static async_queue_entry queued_async_signals_tail; static async_queue_entry *queued_async_signals = &queued_async_signals_tail; static async_queue_entry *queued_async_signals_sig = &queued_async_signals_tail; /* When not NULL, this causes the byte code interpreter to immediately send the message whose selector is here to the current stack top. */ const char *_gst_abort_execution = NULL; /* Set to non-nil if a process must preempt the current one. */ static OOP switch_to_process; /* Set to true if it is time to switch process in a round-robin time-sharing fashion. */ static mst_Boolean time_to_preempt; /* Used to bail out of a C callout and back to the interpreter. */ static interp_jmp_buf *reentrancy_jmp_buf = NULL; /* when this flag is on and execution tracing is in effect, the top of the stack is printed as well as the byte code */ static int verbose_exec_tracing = false; /* This is the bridge to the primitive operations in the GNU Smalltalk system. This function invokes the proper primitive_func with the correct id and the same NUMARGS and METHODOOP with which it was invoked. */ static inline intptr_t execute_primitive_operation (int primitive, volatile int numArgs); /* Execute a #at: primitive, with arguments REC and IDX, knowing that the receiver's class has an instance specification SPEC. */ static inline mst_Boolean cached_index_oop_primitive (OOP rec, OOP idx, intptr_t spec); /* Execute a #at:put: primitive, with arguments REC/IDX/VAL, knowing that the receiver's class has an instance specification SPEC. */ static inline mst_Boolean cached_index_oop_put_primitive (OOP rec, OOP idx, OOP val, intptr_t spec); /* Empty the queue of asynchronous calls. */ static void empty_async_queue (void); /* Try to find another process with higher or same priority as the active one. Return whether there is one. */ static mst_Boolean would_reschedule_process (void); /* Locates in the ProcessorScheduler's process lists and returns the highest priority process different from the current process. */ static OOP highest_priority_process (void); /* Remove the head of the given list (a Semaphore is a subclass of LinkedList) and answer it. */ static OOP remove_first_link (OOP semaphoreOOP); /* Add PROCESSOOP as the head of the given list (a Semaphore is a subclass of LinkedList) and answer it. */ static void add_first_link (OOP semaphoreOOP, OOP processOOP); /* Add PROCESSOOP as the tail of the given list (a Semaphore is a subclass of LinkedList) and answer it. */ static void add_last_link (OOP semaphoreOOP, OOP processOOP); /* Answer the highest priority process different from the current one. Answer nil if there is no other process than the current one. Create a new process that terminates execution if there is no runnable process (which should never be because there is always the idle process). */ static OOP next_scheduled_process (void); /* Create a Process that is running at userSchedulingPriority on the CONTEXTOOP context, and answer it. */ static OOP create_callin_process (OOP contextOOP); /* Set a timer at the end of which we'll preempt the current process. */ static void set_preemption_timer (void); /* Same as _gst_parse_stream, but creating a reentrancy_jmpbuf. Returns true if interrupted. */ static mst_Boolean parse_stream_with_protection (mst_Boolean method); /* Put the given process to sleep by rotating the list of processes for PROCESSOOP's priority (i.e. it was the head of the list and becomes the tail). */ static void sleep_process (OOP processOOP); /* Yield control from the active process. */ static void active_process_yield (void); /* Sets flags so that the interpreter switches to PROCESSOOP at the next sequence point. Unless PROCESSOOP is already active, in which case nothing happens, the process is made the head of the list of processes for PROCESSOOP's priority. Return PROCESSOOP. */ static OOP activate_process (OOP processOOP); /* Restore the virtual machine's state from the ContextPart OOP. */ static void resume_suspended_context (OOP oop); /* Save the virtual machine's state into the suspended Process and ContextPart objects, and load them from NEWPROCESS and from NEWPROCESS's suspendedContext. The Processor (the only instance of ProcessorScheduler) is also updated accordingly. */ static void change_process_context (OOP newProcess); /* Mark the semaphores attached to the process system (asynchronous events, the signal queue, and if any the process which we'll switch to at the next sequence point). */ static void mark_semaphore_oops (void); /* Copy the semaphores attached to the process system (asynchronous events, the signal queue, and if any the process which we'll switch to at the next sequence point). */ static void copy_semaphore_oops (void); /* Suspend execution of PROCESSOOP. */ static void suspend_process (OOP processOOP); /* Resume execution of PROCESSOOP. If it must preempt the currently running process, or if ALWAYSPREEMPT is true, put to sleep the active process and activate PROCESSOOP instead; if it must not, make it the head of the process list for its priority, so that it will be picked once higher priority processes all go to sleep. If PROCESSOOP is terminating, answer false. If PROCESSOOP can be restarted or at least put back in the process list for its priority, answer true. */ static mst_Boolean resume_process (OOP processOOP, mst_Boolean alwaysPreempt); /* Answer whether PROCESSOOP is ready to execute (neither terminating, nor suspended, nor waiting on a semaphore). */ static mst_Boolean is_process_ready (OOP processOOP) ATTRIBUTE_PURE; /* Answer whether any processes are queued in the PROCESSLISTOOP (which can be a LinkedList or a Semaphore). */ static inline mst_Boolean is_empty (OOP processListOOP) ATTRIBUTE_PURE; /* Answer whether the processs is terminating, that is, it does not have an execution context to resume execution from. */ static inline mst_Boolean is_process_terminating (OOP processOOP) ATTRIBUTE_PURE; /* Answer the process that is scheduled to run (that is, the executing process or, if any, the process that is scheduled to start execution at the next sequence point. */ static inline OOP get_scheduled_process (void) ATTRIBUTE_PURE; /* Answer the active process (that is, the process that executed the last bytecode. */ static inline OOP get_active_process (void) ATTRIBUTE_PURE; /* Create a new Semaphore OOP with SIGNALS signals on it and return it. */ static inline OOP semaphore_new (int signals); /* Pop NUMARGS items from the stack and put them into a newly created Array object, which is them returned. */ static inline OOP create_args_array (int numArgs); /* This is the equivalent of SEND_MESSAGE, but is for blocks. The block context that is to the the receiver of the "value" message should be the NUMARGS-th into the stack. SP is set to the top of the arguments in the block context, which have been copied out of the caller's context. The block should accept between NUMARGS - CULL_UP_TO and NUMARGS arguments. If this is not true (failure) return true; on success return false. */ static mst_Boolean send_block_value (int numArgs, int cull_up_to); /* This is a kind of simplified _gst_send_message_internal that, instead of setting up a context for a particular receiver, stores information on the lookup into METHODDATA. Unlike _gst_send_message_internal, this function is generic and valid for both the interpreter and the JIT compiler. */ static mst_Boolean lookup_method (OOP sendSelector, method_cache_entry *methodData, int sendArgs, OOP method_class); /* This tenures context objects from the stack to the context pools (see below for a description). */ static void empty_context_stack (void); /* This allocates a new context pool, eventually triggering a GC once no more pools are available. */ static void alloc_new_chunk (); /* This allocates a context object which is SIZE words big from a pool, allocating one if the current pool is full. */ static inline gst_method_context alloc_stack_context (int size); /* This frees the most recently allocated stack from the current context pool. It is called when unwinding. */ static inline void dealloc_stack_context (gst_context_part context); /* This allocates a new context of SIZE, prepares an OOP for it (taking it from the LIFO_CONTEXTS arrays that is defined below), and pops SENDARGS arguments from the current context. Only the parentContext field of the newly-allocated context is initialized, because the other fields can be desumed from the execution state: these other fields instead are filled in the parent context since the execution state will soon be overwritten. */ static inline gst_method_context activate_new_context (int size, int sendArgs); /* Push the ARGS topmost words below the stack pointer, and then TEMPS nil objects, onto the stack of CONTEXT. */ static inline void prepare_context (gst_context_part context, int args, int temps); /* Return from the current context and restore the virtual machine's status (ip, sp, _gst_this_method, _gst_self, ...). */ static void __attribute__ ((__always_inline__)) unwind_context (void); /* Check whether it is true that sending SENDSELECTOR to RECEIVER accepts NUMARGS arguments. Note that the RECEIVER is only used to do a quick check in the method cache before examining the selector itself; in other words, true is returned even if a message is not understood by the receiver, provided that NUMARGS matches the number of arguments expected by the selector (1 if binary, else the number of colons). If you don't know a receiver you can just pass _gst_nil_oop or directly call _gst_selector_num_args. */ static inline mst_Boolean check_send_correctness (OOP receiver, OOP sendSelector, int numArgs); /* Unwind the contexts up until the caller of the method that created the block context, no matter how many levels of message sending are between where we currently are and the context that we are going to return from. Note that unwind_method is only called inside `dirty' (or `full') block closures, hence the context we return from can be found by following OUTERCONTEXT links starting from the currently executing context, and until we reach a MethodContext. */ static mst_Boolean unwind_method (void); /* Unwind up to context returnContextOOP, carefully examining the method call stack. That is, we examine each context and we only deallocate those that, during their execution, did not create a block context; the others need to be marked as returned. We continue up the call chain until we finally reach methodContextOOP or an unwind method. In this case the non-unwind contexts between the unwind method and the returnContextOOP must be removed from the chain. */ static mst_Boolean unwind_to (OOP returnContextOOP); /* Arrange things so that all the non-unwinding contexts up to returnContextOOP aren't executed. For block contexts this can be done simply by removing them from the chain, but method context must stay there so that we can do non-local returns from them! For this reason, method contexts are flagged as disabled and unwind_context takes care of skipping them when doing a local return. */ static mst_Boolean disable_non_unwind_contexts (OOP returnContextOOP); /* Called to preempt the current process after a specified amount of time has been spent in the GNU Smalltalk interpreter. */ #ifdef ENABLE_PREEMPTION static RETSIGTYPE preempt_smalltalk_process (int sig); #endif /* Push an execution state for process PROCESSOOP. The process is used for two reasons: 1) it is suspended if there is a call-in while the execution state is on the top of the stack; 2) it is sent #userInterrupt if the user presses Ctrl-C. */ static void push_jmp_buf (interp_jmp_buf *jb, int for_interpreter, OOP processOOP); /* Pop an execution state. Return true if the interruption has to be propagated up. */ static mst_Boolean pop_jmp_buf (void); /* Jump out of the top execution state. This is used by C call-out primitives to jump out repeatedly until a Smalltalk process is encountered and terminated. */ static void stop_execution (void); /* Pick a process that is the highest-priority process different from the currently executing one, and schedule it for execution after the first sequence points. */ #define ACTIVE_PROCESS_YIELD() \ activate_process(next_scheduled_process()) /* Answer an OOP for a Smalltalk object of class Array, holding the different process lists for each priority. */ #define GET_PROCESS_LISTS() \ (((gst_processor_scheduler)OOP_TO_OBJ(_gst_processor_oop))->processLists) /* Tell the interpreter that special actions are needed as soon as a sequence point is reached. */ #ifdef ENABLE_JIT_TRANSLATION mst_Boolean _gst_except_flag = false; #define SET_EXCEPT_FLAG(x) \ do { _gst_except_flag = (x); __sync_synchronize (); } while (0) #else static void * const *global_monitored_bytecodes; static void * const *global_normal_bytecodes; static void * const *dispatch_vec; #define SET_EXCEPT_FLAG(x) do { \ dispatch_vec = (x) ? global_monitored_bytecodes : global_normal_bytecodes; \ __sync_synchronize (); \ } while (0) #endif /* Answer an hash value for a send of the SENDSELECTOR message, when the CompiledMethod is found in class METHODCLASS. */ #define METHOD_CACHE_HASH(sendSelector, methodClass) \ (( ((intptr_t)(sendSelector)) ^ ((intptr_t)(methodClass)) / (2 * sizeof (PTR))) \ & (METHOD_CACHE_SIZE - 1)) /* Answer whether CONTEXT is a MethodContext. This happens whenever we have some SmallInteger flags (and not the pointer to the outer context) in the last instance variable. */ #define CONTEXT_FLAGS(context) \ ( ((gst_method_context)(context)) ->flags) /* Answer the sender of CONTEXTOOP. */ #define PARENT_CONTEXT(contextOOP) \ ( ((gst_method_context) OOP_TO_OBJ (contextOOP)) ->parentContext) /* Set whether the old context was a trusted one. Untrusted contexts are those whose receiver or sender is untrusted. */ #define UPDATE_CONTEXT_TRUSTFULNESS(contextOOP, parentContextOOP) \ MAKE_OOP_UNTRUSTED (contextOOP, \ IS_OOP_UNTRUSTED (_gst_self) | \ IS_OOP_UNTRUSTED (parentContextOOP)); /* Set whether the current context is an untrusted one. Untrusted contexts are those whose receiver or sender is untrusted. */ #define IS_THIS_CONTEXT_UNTRUSTED() \ (UPDATE_CONTEXT_TRUSTFULNESS(_gst_this_context_oop, \ PARENT_CONTEXT (_gst_this_context_oop)) \ & F_UNTRUSTED) /* Context management The contexts make up a linked list. Their structure is: +-----------------------------------+ | parentContext | +-----------------------------------+ THESE ARE CONTEXT'S | misc. information | FIXED INSTANCE VARIABLES | ... | +-----------------------------------+------------------------------- | args | | ... | THESE ARE THE CONTEXT'S +-----------------------------------+ INDEXED INSTANCE VARIABLES | temps | | ... | +-----------------------------------+ | stack | | ... | +-----------------------------------+ The space labeled "misc. information" is initialized when thisContext is pushed or when the method becomes the parent context of a newly activated context. It contains, among other things, the pointer to the CompiledMethod or CompiledBlock for the context. That's comparable to leaf procedure optimization in RISC processors. Contexts are special in that they are not created immediately in the main heap. Instead they have three life phases: a) their OOPs are allocated on a stack, and their object data is allocated outside of the main heap. This state lasts until the context returns (in which case the OOP can be reused) or until a reference to the context is made (in which case we swiftly move all the OOPs to the OOP table, leaving the object data outside the heap). b) their OOPs are allocated in the main OOP table, their object data still resides outside of the main heap. Unlike the main heap, this area grows more slowly, but like the main heap, a GC is triggered when it's full. Upon GC, most context objects (which are generated by `full' or `dirty' blocks) that could not be discarded when they were returned from are reclaimed, and the others are tenured, moving them to the main heap. c) their OOPs are allocated in the main OOP table, their object data stays in the main heap. And in this state they will remain until they become garbage and are reclaimed. */ /* I made CHUNK_SIZE a nice power of two. Allocate 64KB at a time, never use more than 3 MB; anyway these are here so behavior can be fine tuned. MAX_LIFO_DEPTH is enough to have room for an entire stack chunk and avoid testing for overflows in lifo_contexts. */ #define CHUNK_SIZE 16384 #define MAX_CHUNKS_IN_MEMORY 48 #define MAX_LIFO_DEPTH (CHUNK_SIZE / CTX_SIZE(0)) /* CHUNK points to an item of CHUNKS. CUR_CHUNK_BEGIN is equal to *CHUNK (i.e. points to the base of the current chunk) and CUR_CHUNK_END is equal to CUR_CHUNK_BEGIN + CHUNK_SIZE. */ static gst_context_part cur_chunk_begin = NULL, cur_chunk_end = NULL; static gst_context_part chunks[MAX_CHUNKS_IN_MEMORY] CACHELINE_ALIGNED; static gst_context_part *chunk = chunks - 1; /* These are used for OOP's allocated in a LIFO manner. A context is kept on this stack as long as it generates only clean blocks, as long as it resides in the same chunk as the newest object created, and as long as no context switches happen since the time the process was created. FREE_LIFO_CONTEXT points to just after the top of the stack. */ static struct oop_s lifo_contexts[MAX_LIFO_DEPTH] CACHELINE_ALIGNED; static OOP free_lifo_context = lifo_contexts; /* Include `plug-in' modules for the appropriate interpreter. A plug-in must define - _gst_send_message_internal - _gst_send_method - send_block_value - _gst_interpret - GET_CONTEXT_IP - SET_THIS_METHOD - _gst_validate_method_cache_entries - any others that are needed by the particular implementation (e.g. lookup_native_ip for the JIT plugin) They are included rather than linked to for speed (they need access to lots of inlines and macros). */ #include "prims.inl" #ifdef ENABLE_JIT_TRANSLATION #include "interp-jit.inl" #else #include "interp-bc.inl" #endif void _gst_empty_context_pool (void) { if (*chunks) { chunk = chunks; cur_chunk_begin = *chunk; cur_chunk_end = (gst_context_part) ( ((char *) cur_chunk_begin) + SIZE_TO_BYTES(CHUNK_SIZE)); } else { chunk = chunks - 1; cur_chunk_begin = cur_chunk_end = NULL; } } void empty_context_stack (void) { OOP contextOOP, last, oop; gst_method_context context; /* printf("[[[[ Gosh, not lifo anymore! (free = %p, base = %p)\n", free_lifo_context, lifo_contexts); */ if COMMON (free_lifo_context != lifo_contexts) for (free_lifo_context = contextOOP = lifo_contexts, last = _gst_this_context_oop, context = (gst_method_context) OOP_TO_OBJ (contextOOP);;) { oop = alloc_oop (context, contextOOP->flags | _gst_mem.active_flag); /* Fill the object's uninitialized fields. */ context->objClass = CONTEXT_FLAGS (context) & MCF_IS_METHOD_CONTEXT ? _gst_method_context_class : _gst_block_context_class; #ifndef ENABLE_JIT_TRANSLATION /* This field is unused without the JIT compiler, but it must be initialized when a context becomes a fully formed Smalltalk object. We do that here. Note that we need the field so that the same image is usable with or without the JIT compiler. */ context->native_ip = DUMMY_NATIVE_IP; #endif /* The last context is not referenced anywhere, so we're done with it. */ if (contextOOP++ == last) { _gst_this_context_oop = oop; break; } /* Else we redirect its sender field to the main OOP table */ context = (gst_method_context) OOP_TO_OBJ (contextOOP); context->parentContext = oop; } else { if (IS_NIL (_gst_this_context_oop)) return; context = (gst_method_context) OOP_TO_OBJ (_gst_this_context_oop); } /* When a context gets out of the context stack it must be a fully formed Smalltalk object. These fields were left uninitialized in _gst_send_message_internal and send_block_value -- set them here. */ context->method = _gst_this_method; context->receiver = _gst_self; context->spOffset = FROM_INT (sp - context->contextStack); context->ipOffset = FROM_INT (ip - method_base); UPDATE_CONTEXT_TRUSTFULNESS (_gst_this_context_oop, context->parentContext); /* Even if the JIT is active, the current context might have no attached native_ip -- in fact it has one only if we are being called from activate_new_context -- so we have to `invent' one. We test for a valid native_ip first, though; this test must have no false positives, i.e. it won't ever overwrite a valid native_ip, and won't leave a bogus OOP for the native_ip. */ if (!IS_INT (context->native_ip)) context->native_ip = DUMMY_NATIVE_IP; } void alloc_new_chunk (void) { if UNCOMMON (++chunk >= &chunks[MAX_CHUNKS_IN_MEMORY]) { /* No more chunks available - GC */ _gst_scavenge (); return; } empty_context_stack (); /* Allocate memory only the first time we're using the chunk. _gst_empty_context_pool resets the status but doesn't free the memory. */ if UNCOMMON (!*chunk) *chunk = (gst_context_part) xcalloc (1, SIZE_TO_BYTES (CHUNK_SIZE)); cur_chunk_begin = *chunk; cur_chunk_end = (gst_context_part) ( ((char *) cur_chunk_begin) + SIZE_TO_BYTES(CHUNK_SIZE)); } gst_method_context alloc_stack_context (int size) { gst_method_context newContext; size = CTX_SIZE (size); for (;;) { newContext = (gst_method_context) cur_chunk_begin; cur_chunk_begin += size; if COMMON (cur_chunk_begin < cur_chunk_end) { newContext->objSize = FROM_INT (size); return (newContext); } /* Not enough room in the current chunk */ alloc_new_chunk (); } } gst_method_context activate_new_context (int size, int sendArgs) { OOP oop; gst_method_context newContext; gst_method_context thisContext; #ifndef OPTIMIZE if (IS_NIL (_gst_this_context_oop)) { printf ("Somebody forgot _gst_prepare_execution_environment!\n"); abort (); } #endif /* We cannot overflow lifo_contexts, because it is designed to contain all of the contexts in a chunk, and we empty lifo_contexts when we exhaust a chunk. So we can get the oop the easy way. */ newContext = alloc_stack_context (size); oop = free_lifo_context++; /* printf("[[[[ Context (size %d) allocated at %p (oop = %p)\n", size, newContext, oop); */ SET_OOP_OBJECT (oop, newContext); newContext->parentContext = _gst_this_context_oop; /* save old context information */ /* leave sp pointing to receiver, which is replaced on return with value */ thisContext = (gst_method_context) OOP_TO_OBJ (_gst_this_context_oop); thisContext->method = _gst_this_method; thisContext->receiver = _gst_self; thisContext->spOffset = FROM_INT ((sp - thisContext->contextStack) - sendArgs); thisContext->ipOffset = FROM_INT (ip - method_base); UPDATE_CONTEXT_TRUSTFULNESS (_gst_this_context_oop, thisContext->parentContext); _gst_this_context_oop = oop; return (newContext); } void dealloc_stack_context (gst_context_part context) { #ifndef OPTIMIZE if (free_lifo_context == lifo_contexts || (OOP_TO_OBJ (free_lifo_context - 1) != (gst_object) context)) { _gst_errorf ("Deallocating a non-LIFO context!!!"); abort (); } #endif cur_chunk_begin = context; free_lifo_context--; } void prepare_context (gst_context_part context, int args, int temps) { REGISTER (1, OOP *stackBase); _gst_temporaries = stackBase = context->contextStack; if (args) { REGISTER (2, OOP * src); src = &sp[1 - args]; stackBase[0] = src[0]; if (args > 1) { stackBase[1] = src[1]; if (args > 2) { stackBase[2] = src[2]; if (args > 3) memcpy (&stackBase[3], &src[3], (args - 3) * sizeof (OOP)); } } stackBase += args; } if (temps) { REGISTER (2, OOP src); src = _gst_nil_oop; stackBase[0] = src; if (temps > 1) { stackBase[1] = src; if (temps > 2) { int n = 2; do stackBase[n] = src; while UNCOMMON (n++ < temps); } } stackBase += temps; } sp = stackBase - 1; } mst_Boolean lookup_method (OOP sendSelector, method_cache_entry *methodData, int sendArgs, OOP method_class) { inc_ptr inc; OOP argsArrayOOP; if (_gst_find_method (method_class, sendSelector, methodData)) return (true); inc = INC_SAVE_POINTER (); argsArrayOOP = create_args_array (sendArgs); INC_ADD_OOP (argsArrayOOP); PUSH_OOP (_gst_message_new_args (sendSelector, argsArrayOOP)); INC_RESTORE_POINTER (inc); return (false); } mst_Boolean _gst_find_method (OOP receiverClass, OOP sendSelector, method_cache_entry *methodData) { OOP method_class = receiverClass; for (; !IS_NIL (method_class); method_class = SUPERCLASS (method_class)) { OOP methodOOP = _gst_find_class_method (method_class, sendSelector); if (!IS_NIL (methodOOP)) { methodData->startingClassOOP = receiverClass; methodData->selectorOOP = sendSelector; methodData->methodOOP = methodOOP; methodData->methodClassOOP = method_class; methodData->methodHeader = GET_METHOD_HEADER (methodOOP); #ifdef ENABLE_JIT_TRANSLATION /* Force the translation to be looked up the next time this entry is used for a message send. */ methodData->receiverClass = NULL; #endif _gst_cache_misses++; return (true); } } return (false); } OOP create_args_array (int numArgs) { gst_object argsArray; OOP argsArrayOOP; int i; argsArray = new_instance_with (_gst_array_class, numArgs, &argsArrayOOP); for (i = 0; i < numArgs; i++) argsArray->data[i] = STACK_AT (numArgs - i - 1); POP_N_OOPS (numArgs); return argsArrayOOP; } mst_Boolean check_send_correctness (OOP receiver, OOP sendSelector, int numArgs) { int hashIndex; method_cache_entry *methodData; OOP receiverClass; receiverClass = OOP_INT_CLASS (receiver); hashIndex = METHOD_CACHE_HASH (sendSelector, receiverClass); methodData = &method_cache[hashIndex]; if (methodData->selectorOOP != sendSelector || methodData->startingClassOOP != receiverClass) { /* If we do not find the method, don't worry and fire #doesNotUnderstand: */ if (!_gst_find_method (receiverClass, sendSelector, methodData)) return (true); methodData = &method_cache[hashIndex]; } return (methodData->methodHeader.numArgs == numArgs); } void unwind_context (void) { gst_method_context oldContext, newContext; OOP newContextOOP; newContextOOP = _gst_this_context_oop; newContext = (gst_method_context) OOP_TO_OBJ (newContextOOP); do { oldContext = newContext; /* Descend in the chain... */ newContextOOP = oldContext->parentContext; if COMMON (free_lifo_context > lifo_contexts) dealloc_stack_context ((gst_context_part) oldContext); /* This context cannot be deallocated in a LIFO way. We must keep it around so that the blocks it created can reference arguments and temporaries in it. Method contexts, however, need to be marked as non-returnable so that attempts to return from them to an undefined place will lose; doing that for block contexts too, we skip a test and are also able to garbage collect more context objects. And doing that for _all_ method contexts is more icache-friendly. */ oldContext->parentContext = _gst_nil_oop; newContext = (gst_method_context) OOP_TO_OBJ (newContextOOP); } while UNCOMMON (CONTEXT_FLAGS (newContext) == (MCF_IS_METHOD_CONTEXT | MCF_IS_DISABLED_CONTEXT)); /* Clear the bit so that we return here just once. This makes this absurd snippet work: ^[ [ 12 ] ensure: [ ^34 ] ] ensure: [ 56 ]! If it were not for this statement, the inner #ensure: would resume after the ^34 block exited, and would answer 12 (the result of the evaluation of the receiver of the inner #ensure:). HACK ALERT!! This is actually valid only for method contexts but I carefully put the modified bits in the low bits so that they are already zero for block contexts. */ CONTEXT_FLAGS (newContext) &= ~(MCF_IS_DISABLED_CONTEXT | MCF_IS_UNWIND_CONTEXT); _gst_this_context_oop = newContextOOP; _gst_temporaries = newContext->contextStack; sp = newContext->contextStack + TO_INT (newContext->spOffset); _gst_self = newContext->receiver; SET_THIS_METHOD (newContext->method, GET_CONTEXT_IP (newContext)); } mst_Boolean unwind_method (void) { OOP oldContextOOP, newContextOOP; gst_block_context newContext; /* We're executing in a block context and an explicit return is encountered. This means that we are to return from the caller of the method that created the block context, no matter how many levels of message sending are between where we currently are and our parent method context. */ newContext = (gst_block_context) OOP_TO_OBJ (_gst_this_context_oop); do { newContextOOP = newContext->outerContext; newContext = (gst_block_context) OOP_TO_OBJ (newContextOOP); } while UNCOMMON (!(CONTEXT_FLAGS (newContext) & MCF_IS_METHOD_CONTEXT)); /* test for block return in a dead method */ if UNCOMMON (IS_NIL (newContext->parentContext)) { /* We are to create a reference to thisContext, so empty the stack. */ empty_context_stack (); oldContextOOP = _gst_this_context_oop; /* Just unwind to the caller, and prepare to send a message to the context */ unwind_context (); SET_STACKTOP (oldContextOOP); return (false); } return unwind_to (newContext->parentContext); } mst_Boolean unwind_to (OOP returnContextOOP) { OOP oldContextOOP, newContextOOP; gst_method_context oldContext, newContext; empty_context_stack (); newContextOOP = _gst_this_context_oop; newContext = (gst_method_context) OOP_TO_OBJ (newContextOOP); while (newContextOOP != returnContextOOP) { oldContextOOP = newContextOOP; oldContext = newContext; /* Descend in the chain... */ newContextOOP = oldContext->parentContext; newContext = (gst_method_context) OOP_TO_OBJ (newContextOOP); /* Check if we got to an unwinding context (#ensure:). */ if UNCOMMON (CONTEXT_FLAGS (newContext) & MCF_IS_UNWIND_CONTEXT) { mst_Boolean result; _gst_this_context_oop = oldContextOOP; /* _gst_this_context_oop is the context above the one we return to. We only unwind up to the #ensure: context. */ result = disable_non_unwind_contexts (returnContextOOP); unwind_context (); return result; } /* This context cannot be deallocated in a LIFO way. We must keep it around so that the blocks it created can reference arguments and temporaries in it. Method contexts, however, need to be marked as non-returnable so that attempts to return from them to an undefined place will lose; doing that for block contexts too, we skip a test and are also able to garbage collect more context objects. */ oldContext->parentContext = _gst_nil_oop; } /* Clear the bit so that we return here just once. This makes this absurd snippet work: ^[ [ 12 ] ensure: [ ^34 ] ] ensure: [ 56 ]! If it were not for this statement, the inner #ensure: would resume after the ^34 block exited, and would answer 12 (the result of the evaluation of the receiver of the inner #ensure:). HACK ALERT!! This is actually valid only for method contexts but I carefully put the modified bits in the low bits so that they are already zero for block contexts. */ CONTEXT_FLAGS (newContext) &= ~(MCF_IS_DISABLED_CONTEXT | MCF_IS_UNWIND_CONTEXT); _gst_this_context_oop = newContextOOP; _gst_temporaries = newContext->contextStack; sp = newContext->contextStack + TO_INT (newContext->spOffset); _gst_self = newContext->receiver; SET_THIS_METHOD (newContext->method, GET_CONTEXT_IP (newContext)); return (true); } mst_Boolean disable_non_unwind_contexts (OOP returnContextOOP) { OOP newContextOOP, *chain; gst_method_context oldContext, newContext; newContextOOP = _gst_this_context_oop; newContext = (gst_method_context) OOP_TO_OBJ (newContextOOP); chain = &newContext->parentContext; for (;;) { oldContext = newContext; /* Descend in the chain... */ newContextOOP = oldContext->parentContext; newContext = (gst_method_context) OOP_TO_OBJ (newContextOOP); if (!(CONTEXT_FLAGS (oldContext) & MCF_IS_METHOD_CONTEXT)) /* This context cannot be deallocated in a LIFO way. Setting its parent context field to nil makes us able to garbage collect more context objects. */ oldContext->parentContext = _gst_nil_oop; if (IS_NIL (newContextOOP)) { *chain = newContextOOP; return (false); } if (newContextOOP == returnContextOOP) { *chain = newContextOOP; chain = &newContext->parentContext; break; } if (CONTEXT_FLAGS (newContext) & MCF_IS_METHOD_CONTEXT) { CONTEXT_FLAGS (newContext) |= MCF_IS_DISABLED_CONTEXT; *chain = newContextOOP; chain = &newContext->parentContext; } } /* Skip any disabled methods. */ while UNCOMMON (CONTEXT_FLAGS (newContext) == (MCF_IS_METHOD_CONTEXT | MCF_IS_DISABLED_CONTEXT)) { oldContext = newContext; /* Descend in the chain... */ newContextOOP = oldContext->parentContext; newContext = (gst_method_context) OOP_TO_OBJ (newContextOOP); /* This context cannot be deallocated in a LIFO way. We must keep it around so that the blocks it created can reference arguments and temporaries in it. Method contexts, however, need to be marked as non-returnable so that attempts to return from them to an undefined place will lose; doing that for block contexts too, we skip a test and are also able to garbage collect more context objects. */ oldContext->parentContext = _gst_nil_oop; } *chain = newContext->parentContext; return (true); } OOP _gst_make_block_closure (OOP blockOOP) { gst_block_closure closure; gst_compiled_block block; OOP closureOOP; closure = (gst_block_closure) new_instance (_gst_block_closure_class, &closureOOP); /* Check how clean the block is: if it only accesses self, we can afford not moving the context chain to the heap and setting the outerContext to nil. */ block = (gst_compiled_block) OOP_TO_OBJ (blockOOP); if (block->header.clean > 1) { empty_context_stack (); closure->outerContext = _gst_this_context_oop; } else closure->outerContext = _gst_nil_oop; closure->block = blockOOP; closure->receiver = _gst_self; return (closureOOP); } void change_process_context (OOP newProcess) { OOP processOOP; gst_process process; gst_processor_scheduler processor; mst_Boolean enable_async_queue; switch_to_process = _gst_nil_oop; /* save old context information */ if (!IS_NIL (_gst_this_context_oop)) empty_context_stack (); /* printf("Switching to process %#O at priority %#O\n", ((gst_process) OOP_TO_OBJ (newProcess))->name, ((gst_process) OOP_TO_OBJ (newProcess))->priority); */ processor = (gst_processor_scheduler) OOP_TO_OBJ (_gst_processor_oop); processOOP = processor->activeProcess; if (processOOP != newProcess) { process = (gst_process) OOP_TO_OBJ (processOOP); if (!IS_NIL (processOOP) && !is_process_terminating (processOOP)) process->suspendedContext = _gst_this_context_oop; processor->activeProcess = newProcess; process = (gst_process) OOP_TO_OBJ (newProcess); enable_async_queue = IS_NIL (process->interrupts) || TO_INT (process->interrupts) >= 0; resume_suspended_context (process->suspendedContext); /* Interrupt-enabling cannot be controlled globally from Smalltalk, but only on a per-Process basis. You might think that this leaves much to be desired, because you could actually reenter a Process with interrupts disabled, if it yields control to another which has interrupts enabled. In principle, this is true, but consider that when interrupts are disabled you can yield in three ways only: - by doing Process>>#suspend -- and then your process will not be scheduled - by doing ProcessorScheduler>>#yield -- and then I'll tell you that I gave you enough rope to shoot yourself on your feet, and that's what you did - by doing Semaphore>>#wait -- and then most likely your blocking section has terminated (see RecursionLock>>#critical: for an example). */ async_queue_enabled = enable_async_queue; } } void resume_suspended_context (OOP oop) { gst_method_context thisContext; _gst_this_context_oop = oop; thisContext = (gst_method_context) OOP_TO_OBJ (oop); sp = thisContext->contextStack + TO_INT (thisContext->spOffset); SET_THIS_METHOD (thisContext->method, GET_CONTEXT_IP (thisContext)); #if ENABLE_JIT_TRANSLATION ip = TO_INT (thisContext->ipOffset); #endif _gst_temporaries = thisContext->contextStack; _gst_self = thisContext->receiver; free_lifo_context = lifo_contexts; } OOP get_active_process (void) { if (!IS_NIL (switch_to_process)) return (switch_to_process); else return (get_scheduled_process ()); } OOP get_scheduled_process (void) { gst_processor_scheduler processor; processor = (gst_processor_scheduler) OOP_TO_OBJ (_gst_processor_oop); return (processor->activeProcess); } static void remove_process_from_list (OOP processOOP) { gst_semaphore sem; gst_process process, lastProcess; OOP lastProcessOOP; if (IS_NIL (processOOP)) return; process = (gst_process) OOP_TO_OBJ (processOOP); if (!IS_NIL (process->myList)) { /* Disconnect the process from its list. */ sem = (gst_semaphore) OOP_TO_OBJ (process->myList); if (sem->firstLink == processOOP) { sem->firstLink = process->nextLink; if (sem->lastLink == processOOP) /* It was the only process in the list */ sem->lastLink = _gst_nil_oop; } else { /* Find the new prev node */ lastProcessOOP = sem->firstLink; lastProcess = (gst_process) OOP_TO_OBJ (lastProcessOOP); while (lastProcess->nextLink != processOOP) { lastProcessOOP = lastProcess->nextLink; lastProcess = (gst_process) OOP_TO_OBJ (lastProcessOOP); } lastProcess->nextLink = process->nextLink; if (sem->lastLink == processOOP) sem->lastLink = lastProcessOOP; } process->myList = _gst_nil_oop; } process->nextLink = _gst_nil_oop; } void add_first_link (OOP semaphoreOOP, OOP processOOP) { gst_semaphore sem; gst_process process; process = (gst_process) OOP_TO_OBJ (processOOP); remove_process_from_list (processOOP); sem = (gst_semaphore) OOP_TO_OBJ (semaphoreOOP); process->myList = semaphoreOOP; process->nextLink = sem->firstLink; sem->firstLink = processOOP; if (IS_NIL (sem->lastLink)) sem->lastLink = processOOP; } void suspend_process (OOP processOOP) { remove_process_from_list (processOOP); if (get_scheduled_process() == processOOP) ACTIVE_PROCESS_YIELD (); } void _gst_terminate_process (OOP processOOP) { gst_process process; process = (gst_process) OOP_TO_OBJ (processOOP); process->suspendedContext = _gst_nil_oop; suspend_process (processOOP); } void add_last_link (OOP semaphoreOOP, OOP processOOP) { gst_semaphore sem; gst_process process, lastProcess; OOP lastProcessOOP; process = (gst_process) OOP_TO_OBJ (processOOP); remove_process_from_list (processOOP); sem = (gst_semaphore) OOP_TO_OBJ (semaphoreOOP); process->myList = semaphoreOOP; process->nextLink = _gst_nil_oop; if (IS_NIL (sem->lastLink)) sem->firstLink = sem->lastLink = processOOP; else { lastProcessOOP = sem->lastLink; lastProcess = (gst_process) OOP_TO_OBJ (lastProcessOOP); lastProcess->nextLink = processOOP; sem->lastLink = processOOP; } } mst_Boolean is_empty (OOP processListOOP) { gst_semaphore processList; processList = (gst_semaphore) OOP_TO_OBJ (processListOOP); return (IS_NIL (processList->firstLink)); } /* TODO: this was taken from VMpr_Processor_yield. Try to use the macro ACTIVE_PROCESS_YIELD instead? */ void active_process_yield (void) { OOP activeProcess = get_active_process (); OOP newProcess = highest_priority_process(); if (is_process_ready (activeProcess)) sleep_process (activeProcess); /* move to the end of the list */ activate_process (IS_NIL (newProcess) ? activeProcess : newProcess); } mst_Boolean _gst_sync_signal (OOP semaphoreOOP, mst_Boolean incr_if_empty) { gst_semaphore sem; gst_process process; gst_method_context suspendedContext; OOP processOOP; int spOffset; sem = (gst_semaphore) OOP_TO_OBJ (semaphoreOOP); do { /* printf ("signal %O %O\n", semaphoreOOP, sem->firstLink); */ if (is_empty (semaphoreOOP)) { if (incr_if_empty) sem->signals = INCR_INT (sem->signals); return false; } processOOP = remove_first_link (semaphoreOOP); /* If they terminated this process, well, try another */ } while (!resume_process (processOOP, false)); /* Put the semaphore at the stack top as a marker that the wait was not interrupted. This assumes that _gst_sync_wait is only called from primitives. */ process = (gst_process) OOP_TO_OBJ (processOOP); suspendedContext = (gst_method_context) OOP_TO_OBJ (process->suspendedContext); spOffset = TO_INT (suspendedContext->spOffset); suspendedContext->contextStack[spOffset] = semaphoreOOP; return true; } void _gst_do_async_signal (OOP semaphoreOOP) { _gst_sync_signal (semaphoreOOP, true); } void _gst_do_async_signal_and_unregister (OOP semaphoreOOP) { _gst_sync_signal (semaphoreOOP, true); _gst_unregister_oop (semaphoreOOP); } /* Async-signal-safe version, does no allocation. Using an atomic operation is still the simplest choice, but on top of that we check that the entry is not already in the list. Also, the datum and next field are NULLed automatically when the call is made. */ void _gst_async_call_internal (async_queue_entry *e) { /* For async-signal safety, we need to check that the entry is not already in the list. Checking that atomically with CAS is the simplest way. */ do if (__sync_val_compare_and_swap(&e->next, NULL, queued_async_signals_sig)) return; while (!__sync_bool_compare_and_swap (&queued_async_signals_sig, e->next, e)); SET_EXCEPT_FLAG (true); } void _gst_async_call (void (*func) (OOP), OOP arg) { /* Thread-safe version for the masses. This lockless stack is reversed in the interpreter loop to get FIFO behavior. */ async_queue_entry *sig = xmalloc (sizeof (async_queue_entry)); sig->func = func; sig->data = arg; do sig->next = queued_async_signals; while (!__sync_bool_compare_and_swap (&queued_async_signals, sig->next, sig)); _gst_wakeup (); SET_EXCEPT_FLAG (true); } mst_Boolean _gst_have_pending_async_calls () { return (queued_async_signals != &queued_async_signals_tail || queued_async_signals_sig != &queued_async_signals_tail); } void empty_async_queue () { async_queue_entry *sig, *sig_reversed; /* Process a batch of asynchronous requests. These are pushed in LIFO order by _gst_async_call. By reversing the list in place before walking it, we get FIFO order. */ sig = __sync_swap (&queued_async_signals, &queued_async_signals_tail); sig_reversed = &queued_async_signals_tail; while (sig != &queued_async_signals_tail) { async_queue_entry *next = sig->next; sig->next = sig_reversed; sig_reversed = sig; sig = next; } sig = sig_reversed; while (sig != &queued_async_signals_tail) { async_queue_entry *next = sig->next; sig->func (sig->data); free (sig); sig = next; } /* For async-signal-safe processing, we need to avoid entering the same item twice into the list. So we use NEXT to mark items that have been added... */ sig = __sync_swap (&queued_async_signals_sig, &queued_async_signals_tail); sig_reversed = &queued_async_signals_tail; while (sig != &queued_async_signals_tail) { async_queue_entry *next = sig->next; sig->next = sig_reversed; sig_reversed = sig; sig = next; } sig = sig_reversed; while (sig != &queued_async_signals_tail) { async_queue_entry *next = sig->next; void (*func) (OOP) = sig->func; OOP data = sig->data; barrier (); sig->data = NULL; barrier (); /* ... and we only NULL it after a signal handler can start writing to it. */ sig->next = NULL; barrier (); func (data); sig = next; } } void _gst_async_signal (OOP semaphoreOOP) { _gst_async_call (_gst_do_async_signal, semaphoreOOP); } void _gst_async_signal_and_unregister (OOP semaphoreOOP) { _gst_async_call (_gst_do_async_signal_and_unregister, semaphoreOOP); } void _gst_sync_wait (OOP semaphoreOOP) { gst_semaphore sem; sem = (gst_semaphore) OOP_TO_OBJ (semaphoreOOP); if (TO_INT (sem->signals) <= 0) { /* Have to suspend. Prepare return value for #wait and move this process to the end of the list. Tweaking the stack top means that this function should only be called from a primitive. */ SET_STACKTOP (_gst_nil_oop); add_last_link (semaphoreOOP, get_active_process ()); if (IS_NIL (ACTIVE_PROCESS_YIELD ())) { printf ("No runnable process"); activate_process (_gst_prepare_execution_environment ()); } } else sem->signals = DECR_INT (sem->signals); /* printf ("wait %O %O\n", semaphoreOOP, sem->firstLink); */ } OOP remove_first_link (OOP semaphoreOOP) { gst_semaphore sem; gst_process process; OOP processOOP; sem = (gst_semaphore) OOP_TO_OBJ (semaphoreOOP); processOOP = sem->firstLink; process = (gst_process) OOP_TO_OBJ (processOOP); sem = (gst_semaphore) OOP_TO_OBJ (semaphoreOOP); sem->firstLink = process->nextLink; if (IS_NIL (sem->firstLink)) sem->lastLink = _gst_nil_oop; /* Unlink the process from any list it was in! */ process->myList = _gst_nil_oop; process->nextLink = _gst_nil_oop; return (processOOP); } mst_Boolean resume_process (OOP processOOP, mst_Boolean alwaysPreempt) { int priority; OOP activeOOP; OOP processLists; OOP processList; gst_process process, active; mst_Boolean ints_enabled; /* 2002-19-12: tried get_active_process instead of get_scheduled_process. */ activeOOP = get_active_process (); active = (gst_process) OOP_TO_OBJ (activeOOP); process = (gst_process) OOP_TO_OBJ (processOOP); priority = TO_INT (process->priority); /* As a special exception, don't preempt a process that has disabled interrupts. ### this behavior is currently disabled. */ ints_enabled = IS_NIL (active->interrupts) || TO_INT(active->interrupts) <= 0; /* resume_process is also used when changing the priority of a ready/active process. In this case, first remove the process from its current list. */ if (processOOP == activeOOP) { assert (!alwaysPreempt); remove_process_from_list (processOOP); } else if (priority >= TO_INT (active->priority) /* && ints_enabled */ ) alwaysPreempt = true; if (IS_NIL (processOOP) || is_process_terminating (processOOP)) /* The process was terminated - nothing to resume, fail */ return (false); /* We have no active process, activate this guy instantly. */ if (IS_NIL (activeOOP)) { activate_process (processOOP); return (true); } processLists = GET_PROCESS_LISTS (); processList = ARRAY_AT (processLists, priority); if (alwaysPreempt) { /* We're resuming a process with a *equal or higher* priority, so sleep the current one and activate the new one */ sleep_process (activeOOP); activate_process (processOOP); } else { /* this process has a lower priority than the active one, so the policy is that it doesn't preempt the currently running one. Anyway, it must be the first in its priority queue - so don't put it to sleep. */ add_first_link (processList, processOOP); } return (true); } OOP activate_process (OOP processOOP) { gst_process process; int priority; OOP processLists; OOP processList; if (IS_NIL (processOOP)) return processOOP; /* 2002-19-12: tried get_active_process instead of get_scheduled_process. */ if (processOOP != get_active_process ()) { process = (gst_process) OOP_TO_OBJ (processOOP); priority = TO_INT (process->priority); processLists = GET_PROCESS_LISTS (); processList = ARRAY_AT (processLists, priority); add_first_link (processList, processOOP); } SET_EXCEPT_FLAG (true); switch_to_process = processOOP; return processOOP; } #ifdef ENABLE_PREEMPTION RETSIGTYPE preempt_smalltalk_process (int sig) { time_to_preempt = true; SET_EXCEPT_FLAG (true); } #endif mst_Boolean is_process_terminating (OOP processOOP) { gst_process process; process = (gst_process) OOP_TO_OBJ (processOOP); return (IS_NIL (process->suspendedContext)); } mst_Boolean is_process_ready (OOP processOOP) { gst_process process; int priority; OOP processLists; OOP processList; process = (gst_process) OOP_TO_OBJ (processOOP); priority = TO_INT (process->priority); processLists = GET_PROCESS_LISTS (); processList = ARRAY_AT (processLists, priority); /* check if process is in the priority queue */ return (process->myList == processList); } void sleep_process (OOP processOOP) { gst_process process; int priority; OOP processLists; OOP processList; process = (gst_process) OOP_TO_OBJ (processOOP); priority = TO_INT (process->priority); processLists = GET_PROCESS_LISTS (); processList = ARRAY_AT (processLists, priority); /* add process to end of priority queue */ add_last_link (processList, processOOP); } mst_Boolean would_reschedule_process () { OOP processLists, processListOOP; int priority, activePriority; OOP processOOP; gst_process process; gst_semaphore processList; if (!IS_NIL (switch_to_process)) return false; processOOP = get_scheduled_process (); process = (gst_process) OOP_TO_OBJ (processOOP); activePriority = TO_INT (process->priority); processLists = GET_PROCESS_LISTS (); priority = NUM_OOPS (OOP_TO_OBJ (processLists)); do { assert (priority > 0); processListOOP = ARRAY_AT (processLists, priority); } while (is_empty (processListOOP) && --priority >= activePriority); processList = (gst_semaphore) OOP_TO_OBJ (processListOOP); return (priority < activePriority || (priority == activePriority /* If the same priority, check if the list has the current process as the sole element. */ && processList->firstLink == processList->lastLink && processList->firstLink == processOOP)); } OOP highest_priority_process (void) { OOP processLists, processListOOP; int priority; OOP processOOP; gst_semaphore processList; processLists = GET_PROCESS_LISTS (); priority = NUM_OOPS (OOP_TO_OBJ (processLists)); for (; priority > 0; priority--) { processListOOP = ARRAY_AT (processLists, priority); if (!is_empty (processListOOP)) { processOOP = remove_first_link (processListOOP); if (processOOP == get_scheduled_process ()) { add_last_link (processListOOP, processOOP); _gst_check_process_state (); /* If there's only one element in the list, discard this priority. */ processList = (gst_semaphore) OOP_TO_OBJ (processListOOP); if (processList->firstLink == processList->lastLink) continue; processOOP = remove_first_link (processListOOP); } return (processOOP); } } return (_gst_nil_oop); } OOP next_scheduled_process (void) { OOP processOOP; gst_processor_scheduler processor; processOOP = highest_priority_process (); if (!IS_NIL (processOOP)) return (processOOP); if (is_process_ready (get_scheduled_process ())) return (_gst_nil_oop); processor = (gst_processor_scheduler) OOP_TO_OBJ (_gst_processor_oop); processor->activeProcess = _gst_nil_oop; return (_gst_nil_oop); } void _gst_check_process_state (void) { OOP processLists, processListOOP, processOOP; int priority, n; gst_semaphore processList; gst_process process; processLists = GET_PROCESS_LISTS (); priority = NUM_OOPS (OOP_TO_OBJ (processLists)); for (n = 0; priority > 0; --priority) { processListOOP = ARRAY_AT (processLists, priority); processList = (gst_semaphore) OOP_TO_OBJ (processListOOP); if (IS_NIL (processList->firstLink) && IS_NIL (processList->lastLink)) continue; /* Sanity check the first and last link in the process list. */ if (IS_NIL (processList->firstLink) || IS_NIL (processList->lastLink)) abort (); for (processOOP = processList->firstLink; !IS_NIL (processOOP); processOOP = process->nextLink, n++) { process = (gst_process) OOP_TO_OBJ (processOOP); if (process->myList != processListOOP) abort (); if (process->priority != FROM_INT (priority)) abort (); /* Sanity check the last link in the process list. */ if (IS_NIL (process->nextLink) && processOOP != processList->lastLink) abort (); /* Check (rather brutally) for loops in the process lists. */ if (++n > _gst_mem.ot_size) abort (); } } } /* Mainly for being invoked from a debugger */ void _gst_print_process_state (void) { OOP processLists, processListOOP, processOOP; int priority; gst_semaphore processList; gst_process process; processLists = GET_PROCESS_LISTS (); priority = NUM_OOPS (OOP_TO_OBJ (processLists)); processOOP = get_scheduled_process (); process = (gst_process) OOP_TO_OBJ (processOOP); if (processOOP == _gst_nil_oop) printf ("No active process\n"); else printf ("Active process: \n", processOOP, TO_INT (process->priority), process->nextLink, process->suspendedContext); for (; priority > 0; priority--) { processListOOP = ARRAY_AT (processLists, priority); processList = (gst_semaphore) OOP_TO_OBJ (processListOOP); if (IS_NIL (processList->firstLink)) continue; printf (" Priority %d: First %p last %p ", priority, processList->firstLink, processList->lastLink); for (processOOP = processList->firstLink; !IS_NIL (processOOP); processOOP = process->nextLink) { process = (gst_process) OOP_TO_OBJ (processOOP); printf ("\n ", processOOP, TO_INT (process->priority), process->suspendedContext); } printf ("\n"); } } OOP semaphore_new (int signals) { gst_semaphore sem; OOP semaphoreOOP; sem = (gst_semaphore) instantiate (_gst_semaphore_class, &semaphoreOOP); sem->signals = FROM_INT (signals); return (semaphoreOOP); } void _gst_init_process_system (void) { gst_processor_scheduler processor; int i; processor = (gst_processor_scheduler) OOP_TO_OBJ (_gst_processor_oop); if (IS_NIL (processor->processLists)) { gst_object processLists; processLists = instantiate_with (_gst_array_class, NUM_PRIORITIES, &processor->processLists); for (i = 0; i < NUM_PRIORITIES; i++) processLists->data[i] = semaphore_new (0); } if (IS_NIL (processor->processTimeslice)) processor->processTimeslice = FROM_INT (DEFAULT_PREEMPTION_TIMESLICE); /* No process is active -- so highest_priority_process() need not worry about discarding an active process. */ processor->activeProcess = _gst_nil_oop; switch_to_process = _gst_nil_oop; activate_process (highest_priority_process ()); set_preemption_timer (); } OOP create_callin_process (OOP contextOOP) { OOP processListsOOP; gst_processor_scheduler processor; gst_process initialProcess; OOP initialProcessOOP, initialProcessListOOP, nameOOP; inc_ptr inc = INC_SAVE_POINTER (); processor = (gst_processor_scheduler) OOP_TO_OBJ (_gst_processor_oop); processListsOOP = processor->processLists; initialProcessListOOP = ARRAY_AT (processListsOOP, 4); nameOOP = _gst_string_new ("call-in process"); INC_ADD_OOP (nameOOP); initialProcess = (gst_process) instantiate (_gst_callin_process_class, &initialProcessOOP); INC_ADD_OOP (initialProcessOOP); initialProcess->priority = FROM_INT (USER_SCHEDULING_PRIORITY); initialProcess->interruptLock = _gst_nil_oop; initialProcess->suspendedContext = contextOOP; initialProcess->name = nameOOP; INC_RESTORE_POINTER (inc); /* Put initialProcessOOP in the root set */ add_first_link (initialProcessListOOP, initialProcessOOP); _gst_invalidate_method_cache (); return (initialProcessOOP); } int _gst_get_var (enum gst_var_index index) { switch (index) { case GST_DECLARE_TRACING: return (_gst_declare_tracing); case GST_EXECUTION_TRACING: return (_gst_execution_tracing); case GST_EXECUTION_TRACING_VERBOSE: return (verbose_exec_tracing); case GST_GC_MESSAGE: return (_gst_gc_message); case GST_VERBOSITY: return (_gst_verbosity); case GST_MAKE_CORE_FILE: return (_gst_make_core_file); case GST_REGRESSION_TESTING: return (_gst_regression_testing); default: return (-1); } } int _gst_set_var (enum gst_var_index index, int value) { int old = _gst_get_var (index); if (value < 0) return -1; switch (index) { case GST_DECLARE_TRACING: _gst_declare_tracing = value; break; case GST_EXECUTION_TRACING: _gst_execution_tracing = value; break; case GST_EXECUTION_TRACING_VERBOSE: verbose_exec_tracing = value; break; case GST_GC_MESSAGE: _gst_gc_message = value; break; case GST_VERBOSITY: _gst_verbosity = value; break; case GST_MAKE_CORE_FILE: _gst_make_core_file = value; break; case GST_REGRESSION_TESTING: _gst_regression_testing = true; break; default: return (-1); } return old; } void _gst_init_interpreter (void) { unsigned int i; #ifdef ENABLE_JIT_TRANSLATION _gst_init_translator (); ip = 0; #else ip = NULL; #endif _gst_this_context_oop = _gst_nil_oop; for (i = 0; i < MAX_LIFO_DEPTH; i++) lifo_contexts[i].flags = F_POOLED | F_CONTEXT; _gst_init_async_events (); _gst_init_process_system (); } OOP _gst_prepare_execution_environment (void) { gst_method_context dummyContext; OOP dummyContextOOP, processOOP; inc_ptr inc = INC_SAVE_POINTER (); empty_context_stack (); dummyContext = alloc_stack_context (4); dummyContext->objClass = _gst_method_context_class; dummyContext->parentContext = _gst_nil_oop; dummyContext->method = _gst_get_termination_method (); dummyContext->flags = MCF_IS_METHOD_CONTEXT | MCF_IS_EXECUTION_ENVIRONMENT | MCF_IS_UNWIND_CONTEXT; dummyContext->receiver = _gst_nil_oop; dummyContext->ipOffset = FROM_INT (0); dummyContext->spOffset = FROM_INT (-1); #ifdef ENABLE_JIT_TRANSLATION dummyContext->native_ip = GET_NATIVE_IP ((char *) _gst_return_from_native_code); #else dummyContext->native_ip = DUMMY_NATIVE_IP; /* See empty_context_stack */ #endif dummyContextOOP = alloc_oop (dummyContext, _gst_mem.active_flag | F_POOLED | F_CONTEXT); INC_ADD_OOP (dummyContextOOP); processOOP = create_callin_process (dummyContextOOP); INC_RESTORE_POINTER (inc); return (processOOP); } OOP _gst_nvmsg_send (OOP receiver, OOP sendSelector, OOP *args, int sendArgs) { inc_ptr inc = INC_SAVE_POINTER (); #if 0 OOP dirMessageOOP; #endif OOP processOOP, currentProcessOOP; OOP result; gst_process process; int i; processOOP = _gst_prepare_execution_environment (); INC_ADD_OOP (processOOP); _gst_check_process_state (); /* _gst_print_process_state (); */ /* _gst_show_backtrace (stdout); */ if (reentrancy_jmp_buf && !reentrancy_jmp_buf->suspended++) suspend_process (reentrancy_jmp_buf->processOOP); currentProcessOOP = get_active_process (); change_process_context (processOOP); PUSH_OOP (receiver); for (i = 0; i < sendArgs; i++) PUSH_OOP (args[i]); if (!sendSelector) send_block_value (sendArgs, sendArgs); else if (OOP_CLASS (sendSelector) == _gst_symbol_class) SEND_MESSAGE (sendSelector, sendArgs); else _gst_send_method (sendSelector); process = (gst_process) OOP_TO_OBJ (currentProcessOOP); if (!IS_NIL (currentProcessOOP) && TO_INT (process->priority) > USER_SCHEDULING_PRIORITY) ACTIVE_PROCESS_YIELD (); result = _gst_interpret (processOOP); INC_ADD_OOP (result); /* Re-enable the previously executing process *now*, because a primitive might expect the current stack pointer to be that of the process that was executing. */ if (reentrancy_jmp_buf && !--reentrancy_jmp_buf->suspended && !is_process_terminating (reentrancy_jmp_buf->processOOP)) { resume_process (reentrancy_jmp_buf->processOOP, true); if (!IS_NIL (switch_to_process)) change_process_context (switch_to_process); } INC_RESTORE_POINTER (inc); return (result); } void set_preemption_timer (void) { #ifdef ENABLE_PREEMPTION gst_processor_scheduler processor; int timeSlice; processor = (gst_processor_scheduler) OOP_TO_OBJ (_gst_processor_oop); timeSlice = TO_INT (processor->processTimeslice); time_to_preempt = false; if (timeSlice > 0) _gst_sigvtalrm_every (timeSlice, preempt_smalltalk_process); #endif } void _gst_invalidate_method_cache (void) { int i; /* Only do this if some code was run since the last cache cleanup, as it is quite expensive. */ if (!_gst_sample_counter) return; #ifdef ENABLE_JIT_TRANSLATION _gst_reset_inline_caches (); #else at_cache_class = at_put_cache_class = size_cache_class = class_cache_class = NULL; #endif _gst_cache_misses = _gst_sample_counter = 0; for (i = 0; i < METHOD_CACHE_SIZE; i++) { method_cache[i].selectorOOP = NULL; #ifdef ENABLE_JIT_TRANSLATION method_cache[i].receiverClass = NULL; #endif } } void _gst_copy_processor_registers (void) { copy_semaphore_oops (); /* Get everything into the main OOP table first. */ if (_gst_this_context_oop) MAYBE_COPY_OOP (_gst_this_context_oop); /* everything else is pointed to by _gst_this_context_oop, either directly or indirectly, or has been copyed when scanning the registered roots. */ } void copy_semaphore_oops (void) { async_queue_entry *sig; for (sig = queued_async_signals; sig != &queued_async_signals_tail; sig = sig->next) MAYBE_COPY_OOP (sig->data); for (sig = queued_async_signals_sig; sig != &queued_async_signals_tail; sig = sig->next) MAYBE_COPY_OOP (sig->data); /* there does seem to be a window where this is not valid */ if (single_step_semaphore) MAYBE_COPY_OOP (single_step_semaphore); /* there does seem to be a window where this is not valid */ MAYBE_COPY_OOP (switch_to_process); } void _gst_mark_processor_registers (void) { mark_semaphore_oops (); if (_gst_this_context_oop) MAYBE_MARK_OOP (_gst_this_context_oop); /* everything else is pointed to by _gst_this_context_oop, either directly or indirectly, or has been marked when scanning the registered roots. */ } void mark_semaphore_oops (void) { async_queue_entry *sig; for (sig = queued_async_signals; sig != &queued_async_signals_tail; sig = sig->next) MAYBE_MARK_OOP (sig->data); for (sig = queued_async_signals_sig; sig != &queued_async_signals_tail; sig = sig->next) MAYBE_MARK_OOP (sig->data); /* there does seem to be a window where this is not valid */ if (single_step_semaphore) MAYBE_MARK_OOP (single_step_semaphore); /* there does seem to be a window where this is not valid */ MAYBE_MARK_OOP (switch_to_process); } void _gst_fixup_object_pointers (void) { gst_method_context thisContext; if (!IS_NIL (_gst_this_context_oop)) { /* Create real OOPs for the contexts here. If we do it while copying, the newly created OOPs are in to-space and are never scanned! */ empty_context_stack (); thisContext = (gst_method_context) OOP_TO_OBJ (_gst_this_context_oop); #ifdef DEBUG_FIXUP fflush (stderr); printf ("\nF sp %x %d ip %x %d _gst_this_method %x thisContext %x", sp, sp - thisContext->contextStack, ip, ip - method_base, _gst_this_method->object, thisContext); fflush (stdout); #endif thisContext->method = _gst_this_method; thisContext->receiver = _gst_self; thisContext->spOffset = FROM_INT (sp - thisContext->contextStack); thisContext->ipOffset = FROM_INT (ip - method_base); } } void _gst_restore_object_pointers (void) { gst_context_part thisContext; /* !!! The objects can move after the growing or compact phase. But, all this information is re-computable, so we pick up _gst_this_method to adjust the ip and _gst_literals accordingly, and we also pick up the context to adjust sp and the temps accordingly. */ if (!IS_NIL (_gst_this_context_oop)) { thisContext = (gst_context_part) OOP_TO_OBJ (_gst_this_context_oop); _gst_temporaries = thisContext->contextStack; #ifndef OPTIMIZE /* Mon Jul 3 01:21:06 1995 */ /* these should not be necessary */ if (_gst_this_method != thisContext->method) { printf ("$$$$$$$$$$$$$$$$$$$ GOT ONE!!!!\n"); printf ("this method %O\n", _gst_this_method); printf ("this context %O\n", thisContext->receiver); abort (); } if (_gst_self != thisContext->receiver) { printf ("$$$$$$$$$$$$$$$$$$$ GOT ONE!!!!\n"); printf ("self %O\n", _gst_self); printf ("this context %O\n", thisContext->receiver); abort (); } #endif /* OPTIMIZE Mon Jul 3 01:21:06 1995 */ SET_THIS_METHOD (_gst_this_method, GET_CONTEXT_IP (thisContext)); sp = TO_INT (thisContext->spOffset) + thisContext->contextStack; #ifdef DEBUG_FIXUP fflush (stderr); printf ("\nR sp %x %d ip %x %d _gst_this_method %x thisContext %x\n", sp, sp - thisContext->contextStack, ip, ip - method_base, _gst_this_method->object, thisContext); fflush (stdout); #endif } SET_EXCEPT_FLAG (true); /* force to import registers */ } static RETSIGTYPE interrupt_on_signal (int sig) { if (reentrancy_jmp_buf) stop_execution (); else { _gst_set_signal_handler (sig, SIG_DFL); raise (sig); } } static void backtrace_on_signal_1 (mst_Boolean is_serious_error, mst_Boolean c_backtrace) { static int reentering = -1; /* Avoid recursive signals */ reentering++; if ((reentrancy_jmp_buf && reentrancy_jmp_buf->interpreter) && !reentering && ip && !_gst_gc_running) _gst_show_backtrace (stderr); else { if (is_serious_error) _gst_errorf ("Error occurred while not in byte code interpreter!!"); #ifdef HAVE_EXECINFO_H /* Don't print a backtrace, for example, if exiting during a compilation. */ if (c_backtrace && !reentering) { PTR array[11]; size_t size = backtrace (array, 11); backtrace_symbols_fd (array + 1, size - 1, STDERR_FILENO); } #endif } reentering--; } static RETSIGTYPE backtrace_on_signal (int sig) { _gst_errorf ("%s", strsignal (sig)); _gst_set_signal_handler (sig, backtrace_on_signal); backtrace_on_signal_1 (sig != SIGTERM, sig != SIGTERM); _gst_set_signal_handler (sig, SIG_DFL); raise (sig); } #ifdef SIGUSR1 static RETSIGTYPE user_backtrace_on_signal (int sig) { _gst_set_signal_handler (sig, user_backtrace_on_signal); backtrace_on_signal_1 (false, true); } #endif void _gst_init_signals (void) { if (!_gst_make_core_file) { #ifdef ENABLE_JIT_TRANSLATION _gst_set_signal_handler (SIGILL, backtrace_on_signal); #endif _gst_set_signal_handler (SIGABRT, backtrace_on_signal); } _gst_set_signal_handler (SIGTERM, backtrace_on_signal); _gst_set_signal_handler (SIGINT, interrupt_on_signal); #ifdef SIGUSR1 _gst_set_signal_handler (SIGUSR1, user_backtrace_on_signal); #endif } void _gst_show_backtrace (FILE *fp) { OOP contextOOP; gst_method_context context; gst_compiled_block block; gst_compiled_method method; gst_method_info methodInfo; empty_context_stack (); for (contextOOP = _gst_this_context_oop; !IS_NIL (contextOOP); contextOOP = context->parentContext) { context = (gst_method_context) OOP_TO_OBJ (contextOOP); if (CONTEXT_FLAGS (context) == (MCF_IS_METHOD_CONTEXT | MCF_IS_DISABLED_CONTEXT)) continue; /* printf ("(OOP %p)", context->method); */ fprintf (fp, "(ip %d)", TO_INT (context->ipOffset)); if (CONTEXT_FLAGS (context) & MCF_IS_METHOD_CONTEXT) { OOP receiver, receiverClass; if (CONTEXT_FLAGS (context) & MCF_IS_EXECUTION_ENVIRONMENT) { if (IS_NIL(context->parentContext)) fprintf (fp, "\n"); else fprintf (fp, "\n"); continue; } if (CONTEXT_FLAGS (context) & MCF_IS_UNWIND_CONTEXT) fprintf (fp, " "); /* a method context */ method = (gst_compiled_method) OOP_TO_OBJ (context->method); methodInfo = (gst_method_info) OOP_TO_OBJ (method->descriptor); receiver = context->receiver; if (IS_INT (receiver)) receiverClass = _gst_small_integer_class; else receiverClass = OOP_CLASS (receiver); if (receiverClass == methodInfo->class) fprintf (fp, "%O", receiverClass); else fprintf (fp, "%O(%O)", receiverClass, methodInfo->class); } else { /* a block context */ block = (gst_compiled_block) OOP_TO_OBJ (context->method); method = (gst_compiled_method) OOP_TO_OBJ (block->method); methodInfo = (gst_method_info) OOP_TO_OBJ (method->descriptor); fprintf (fp, "[] in %O", methodInfo->class); } fprintf (fp, ">>%O\n", methodInfo->selector); } } void _gst_show_stack_contents (void) { gst_method_context context; OOP *walk; mst_Boolean first; if (IS_NIL (_gst_this_context_oop)) return; context = (gst_method_context) OOP_TO_OBJ (_gst_this_context_oop); for (first = true, walk = context->contextStack; walk <= sp; first = false, walk++) { if (!first) printf (", "); printf ("%O", *walk); } printf ("\n\n"); } static inline mst_Boolean cached_index_oop_primitive (OOP rec, OOP idx, intptr_t spec) { OOP result; if (!IS_INT (idx)) return (true); result = index_oop_spec (rec, OOP_TO_OBJ (rec), TO_INT (idx), spec); if UNCOMMON (!result) return (true); POP_N_OOPS (1); SET_STACKTOP (result); return (false); } static inline mst_Boolean cached_index_oop_put_primitive (OOP rec, OOP idx, OOP val, intptr_t spec) { if (!IS_INT (idx)) return (true); if UNCOMMON (!index_oop_put_spec (rec, OOP_TO_OBJ (rec), TO_INT (idx), val, spec)) return (true); POP_N_OOPS (2); SET_STACKTOP (val); return (false); } static inline intptr_t execute_primitive_operation (int primitive, volatile int numArgs) { prim_table_entry *pte = &_gst_primitive_table[primitive]; intptr_t result = pte->func (pte->id, numArgs); last_primitive = primitive; return result; } prim_table_entry * _gst_get_primitive_attributes (int primitive) { return &_gst_default_primitive_table[primitive]; } void _gst_set_primitive_attributes (int primitive, prim_table_entry *pte) { if (pte) _gst_primitive_table[primitive] = *pte; else _gst_primitive_table[primitive] = _gst_default_primitive_table[0]; } void push_jmp_buf (interp_jmp_buf *jb, int for_interpreter, OOP processOOP) { jb->next = reentrancy_jmp_buf; jb->processOOP = processOOP; jb->suspended = 0; jb->interpreter = for_interpreter; jb->interrupted = false; _gst_register_oop (processOOP); reentrancy_jmp_buf = jb; } mst_Boolean pop_jmp_buf (void) { interp_jmp_buf *jb = reentrancy_jmp_buf; reentrancy_jmp_buf = jb->next; if (jb->interpreter && !is_process_terminating (jb->processOOP)) _gst_terminate_process (jb->processOOP); _gst_unregister_oop (jb->processOOP); return jb->interrupted && reentrancy_jmp_buf; } void stop_execution (void) { reentrancy_jmp_buf->interrupted = true; if (reentrancy_jmp_buf->interpreter && !is_process_terminating (reentrancy_jmp_buf->processOOP)) { _gst_abort_execution = "userInterrupt"; SET_EXCEPT_FLAG (true); if (get_active_process () != reentrancy_jmp_buf->processOOP) resume_process (reentrancy_jmp_buf->processOOP, true); } else longjmp (reentrancy_jmp_buf->jmpBuf, 1); } mst_Boolean parse_stream_with_protection (mst_Boolean method) { interp_jmp_buf jb; push_jmp_buf (&jb, false, get_active_process ()); if (setjmp (jb.jmpBuf) == 0) _gst_parse_stream (method); return pop_jmp_buf (); } smalltalk-3.2.5/libgst/opt.c0000644000175000017500000014637612130343734012701 00000000000000/******************************* -*- C -*- **************************** * * Functions for byte code optimization & analysis * * ***********************************************************************/ /*********************************************************************** * * Copyright 2000,2001,2002,2003,2006,2008,2009 Free Software Foundation, Inc. * Written by Paolo Bonzini. * * This file is part of GNU Smalltalk. * * GNU Smalltalk is free software; you can redistribute it and/or modify it * under the terms of the GNU General Public License as published by the Free * Software Foundation; either version 2, or (at your option) any later * version. * * Linking GNU Smalltalk statically or dynamically with other modules is * making a combined work based on GNU Smalltalk. Thus, the terms and * conditions of the GNU General Public License cover the whole * combination. * * In addition, as a special exception, the Free Software Foundation * give you permission to combine GNU Smalltalk with free software * programs or libraries that are released under the GNU LGPL and with * independent programs running under the GNU Smalltalk virtual machine. * * You may copy and distribute such a system following the terms of the * GNU GPL for GNU Smalltalk and the licenses of the other code * concerned, provided that you include the source code of that other * code when and as the GNU GPL requires distribution of source code. * * Note that people who make modified versions of GNU Smalltalk are not * obligated to grant this special exception for their modified * versions; it is their choice whether to do so. The GNU General * Public License gives permission to release a modified version without * this exception; this exception also makes it possible to release a * modified version which carries forward this exception. * * GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or * FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for * more details. * * You should have received a copy of the GNU General Public License along with * GNU Smalltalk; see the file COPYING. If not, write to the Free Software * Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * ***********************************************************************/ #include "gstpriv.h" #include "match.h" /* Define this to have verbose messages from the JIT compiler's basic-block split phase. */ /* #define DEBUG_JIT_TRANSLATOR */ /* Define this to have verbose messages from the bytecode verifier. */ /* #define DEBUG_VERIFIER */ /* Define this to disable the peephole bytecode optimizer. It works well for decreasing the footprint and increasing the speed, so there's no reason to do that unless you're debugging the compiler. */ /* #define NO_OPTIMIZE */ /* Define this to disable superoperators in the peephole bytecode optimizer. Some simple optimizations will still be done, making the output suitable for searching superoperator candidates. */ /* #define NO_SUPEROPERATORS */ /* Define this to disable bytecode verification. */ /* #define NO_VERIFIER */ /* The JIT compiler prefers optimized bytecodes, because they are more regular. */ #ifdef ENABLE_JIT_TRANSLATION #undef NO_OPTIMIZE #endif /* This structure and the following one are used by the bytecode peephole optimizer. This one, in particular, defines where basic blocks start in the non- optimized bytecodes. byte is nothing more than an offset in those bytecodes; id is used to pair jump bytecodes with their destinations: in the initial scan, when we encounter a jump bytecode we fill two block_boundaries -- one has positive id and represents the destination of the jump, one has negative id (but the same absolute value) and represents the jump bytecode itself. */ typedef struct block_boundary { /* Bytecode at the end of the basic block, -1 if not a jump. */ int kind; /* Start of the basic block. */ int start, end; /* Destination IP for the jump at the end of the basic block. */ int dest; /* Destination basic block for the jump at the end of the basic block. */ struct block_boundary *dest_bb; /* Size of the optimized basic block. */ int opt_length; /* Offset of the basic block in the optimized method. */ int final_byte; } block_boundary; /* Basic block data structure, common to the JIT and the verifier. */ typedef struct basic_block_item { struct basic_block_item *next; struct basic_block_item **bb; gst_uchar *bp; int sp; /* Suspended basic blocks are those for which we know the initial instruction pointer, but not the initial stack pointer. Since data-flow analysis should walk them, these are put aside momentarily. They are generated when there is no basic block for the bytecode after a jump or a return. If they are unreachable and they follow a jump, they're supposed to have an initial SP = 0, else the initial SP is put to the same as the return bytecode's SP (this is to accomodate comp.c's behavior when emitting "a ifTrue: [ ^1 ] ifFalse: [ ^2 ]"). However, the initial SP of a suspended block can always be overridden if a jump to the block is found, in which case the flag is cleared. Suspended basic blocks are processed FIFO, not LIFO like the normal worklist. */ mst_Boolean suspended; OOP stack[1]; } basic_block_item; #define ALLOCA_BASIC_BLOCK(dest, depth, bp_, sp_) \ do \ { \ *(dest) = alloca (sizeof (basic_block_item) + \ sizeof (OOP) * ((depth) - 1)); \ (*(dest))->bb = (dest); \ (*(dest))->bp = (bp_); \ (*(dest))->sp = (sp_); \ (*(dest))->suspended = false; \ } \ while (0) #define INIT_BASIC_BLOCK(bb, temps) \ do \ { \ int i; \ for (i = 0; i < (temps); i++) \ (bb)->stack[i] = FROM_INT (VARYING); \ for (; i < (bb)->sp; i++) \ (bb)->stack[i] = FROM_INT (UNDEFINED); \ } \ while (0) /* Use the hash table and function in superop1.inl to look for a superoperator representing bytecode BC1 with argument ARG, followed by bytecode BC2. */ static inline int search_superop_fixed_arg_1 (int bc1, int arg, int bc2); /* Use the hash table and function in superop1.inl to look for a superoperator representing bytecode BC1 followed by bytecode BC2 with argument ARG. */ static inline int search_superop_fixed_arg_2 (int bc1, int bc2, int arg); /* Scan the bytecodes between FROM and TO, performing a handful of peephole optimizations and creating superoperators with optimize_superoperators. The optimized bytecodes are written starting at FROM. */ static int optimize_basic_block (gst_uchar * from, gst_uchar * to); /* Scan the peephole-optimized bytecodes between FROM and TO. Generate superoperators and rewrite in-place starting at FROM. Return the pointer just past the final byte written. */ static gst_uchar *optimize_superoperators (gst_uchar * from, gst_uchar * to); /* This compares two block_boundary structures according to their ending bytecode position. */ static int compare_blocks (const PTR a, const PTR b) ATTRIBUTE_PURE; /* And this compares an int (A) with the starting bytecode of block B. */ static int search_block (const PTR a, const PTR b) ATTRIBUTE_PURE; /* Computes the length of a jump at distance OFS. */ static int compute_jump_length (int ofs) ATTRIBUTE_CONST; /* This answers how the dirtyness of BLOCKOOP affects the block that encloses it. */ static inline int check_inner_block (OOP blockOOP); /* This fills a table that says to which bytecodes a jump lands. Starting from BP, and for a total of SIZE bytes, bytecodes are analyzed and on output DEST[i] is non-zero if and only if BP[i] is the destination of a jump. It is positive for a forward jump and negative for a backward jump. The number of jumps is returned. */ static int make_destination_table (gst_uchar * bp, int size, char *dest); /* Helper function to compute the bytecode verifier's `in' sets from the `out' sets. */ static mst_Boolean merge_stacks (OOP *dest, int dest_sp, OOP *src, int src_sp); int _gst_is_simple_return (bc_vector bytecodes) { gst_uchar *bytes; int maybe = MTH_NORMAL; OOP maybe_object = NULL; int i; if (bytecodes == NULL) return (MTH_NORMAL); bytes = bytecodes->base; for (i = 1; i <= 4; i++) { int should_have_been_return = (maybe != MTH_NORMAL); if (bytes == bytecodes->ptr) return (MTH_NORMAL); MATCH_BYTECODES (IS_SIMPLE_RETURN, bytes, ( PUSH_SELF { maybe = MTH_RETURN_SELF; } PUSH_RECEIVER_VARIABLE { maybe = (n << 8) | MTH_RETURN_INSTVAR; } PUSH_LIT_CONSTANT { maybe = (n << 8) | MTH_RETURN_LITERAL; } PUSH_INTEGER { maybe_object = FROM_INT (n); maybe = MTH_RETURN_LITERAL; } PUSH_SPECIAL { maybe = MTH_RETURN_LITERAL; switch (n) { case NIL_INDEX: maybe_object = _gst_nil_oop; break; case TRUE_INDEX: maybe_object = _gst_true_oop; break; case FALSE_INDEX: maybe_object = _gst_false_oop; break; default: abort (); } } LINE_NUMBER_BYTECODE { } RETURN_CONTEXT_STACK_TOP { if (maybe_object) _gst_add_forced_object (maybe_object); return maybe; } STORE_RECEIVER_VARIABLE, PUSH_OUTER_TEMP, STORE_OUTER_TEMP, JUMP, POP_JUMP_TRUE, POP_JUMP_FALSE, PUSH_TEMPORARY_VARIABLE, PUSH_LIT_VARIABLE, STORE_TEMPORARY_VARIABLE, STORE_LIT_VARIABLE, SEND, POP_INTO_NEW_STACKTOP, POP_STACK_TOP, DUP_STACK_TOP, SEND_IMMEDIATE, EXIT_INTERPRETER, SEND_ARITH, SEND_SPECIAL, MAKE_DIRTY_BLOCK, RETURN_METHOD_STACK_TOP { return (MTH_NORMAL); } INVALID { abort(); } )); if (should_have_been_return) return (MTH_NORMAL); } return (MTH_NORMAL); } int _gst_check_kind_of_block (bc_vector bc, OOP * literals) { int status, newStatus; gst_uchar *bp, *end; status = 0; /* clean block */ for (bp = bc->base, end = bc->ptr; bp != end; ) { MATCH_BYTECODES (CHECK_KIND_OF_BLOCK, bp, ( PUSH_SELF, PUSH_RECEIVER_VARIABLE, STORE_RECEIVER_VARIABLE { if (status == 0) status = 1; } PUSH_LIT_CONSTANT { newStatus = check_inner_block (literals[n]); if (newStatus > status) { if (newStatus == 31) return (31); status = newStatus; } } PUSH_OUTER_TEMP, STORE_OUTER_TEMP { if (status < 1 + scopes) status = 1 + scopes; if (status > 31) /* ouch! how deep!! */ return (31); } JUMP, POP_JUMP_TRUE, POP_JUMP_FALSE, PUSH_TEMPORARY_VARIABLE, PUSH_LIT_VARIABLE, PUSH_SPECIAL, PUSH_INTEGER, RETURN_CONTEXT_STACK_TOP, LINE_NUMBER_BYTECODE, STORE_TEMPORARY_VARIABLE, STORE_LIT_VARIABLE, SEND, POP_INTO_NEW_STACKTOP, POP_STACK_TOP, DUP_STACK_TOP, EXIT_INTERPRETER, SEND_ARITH, SEND_SPECIAL, SEND_IMMEDIATE, MAKE_DIRTY_BLOCK { } RETURN_METHOD_STACK_TOP { return (31); } INVALID { abort(); } )); } return (status); } int check_inner_block (OOP blockOOP) { int newStatus; gst_compiled_block block; if (!IS_CLASS (blockOOP, _gst_compiled_block_class)) return (0); /* Check the cleanness of the inner block and adequately change the status. full block: no way dude -- exit immediately clean block: same for us receiver access: same for us access to temps in the Xth context: from the perspective of the block being checked here, it is like an access to temps in the (X-1)th context access to this block's temps: our outerContext can be nil either, but for safety we won't be a clean block. */ block = (gst_compiled_block) OOP_TO_OBJ (blockOOP); newStatus = block->header.clean; switch (newStatus) { case 31: case 0: case 1: return (newStatus); default: return (newStatus - 1); } } int compare_blocks (const PTR a, const PTR b) { const block_boundary *ba = (const block_boundary *) a; const block_boundary *bb = (const block_boundary *) b; /* Sort by bytecode. */ if (ba->end != bb->end) return (ba->end - bb->end); /* Put first the element representing the jump. */ else if (ba->kind != -1 && bb->kind == -1) return -1; else if (bb->kind != -1 && ba->kind == -1) return 1; return 0; } int search_block (const PTR a, const PTR b) { const int *ia = (const int *) a; const block_boundary *bb = (const block_boundary *) b; return (*ia - bb->start); } int compute_jump_length (int ofs) { /* The offset is counted from the end of the bytecode and the result of compute_jump_length is subtracted when computing the jump offset (the the jump offset increases in absolute value when jumping back). This means the actual range for backwards jumps is a little less than 2^8k bytes, while for forwards jumps it is a little more than 2^8k bytes. */ if (ofs > -254 && ofs < 258) return 2; else if (ofs > -65532 && ofs < 65540) return 4; else if (ofs > -16777210 && ofs < 16777222) return 6; else return 8; } bc_vector _gst_optimize_bytecodes (bc_vector bytecodes) { #ifdef NO_OPTIMIZE return (bytecodes); #else bc_vector old_bytecodes; block_boundary *blocks, *block, *last; gst_uchar *bp, *end, *first; int i; mst_Boolean changed; bp = bytecodes->base; end = bytecodes->ptr; blocks = alloca (sizeof (block_boundary) * (end - bp + 1)); memset (blocks, 0, sizeof (block_boundary) * (end - bp + 1)); /* 1) Split into basic blocks. This part cheats so that the final fixup also performs jump optimization. */ for (last = blocks; bp != end; ) { gst_uchar *dest = bp; gst_uchar *dest_ip0; mst_Boolean canOptimizeJump, split; int kind = 0; split = false; do { dest_ip0 = dest; canOptimizeJump = false; MATCH_BYTECODES (THREAD_JUMPS, dest, ( MAKE_DIRTY_BLOCK, SEND_SPECIAL, SEND_ARITH, SEND_IMMEDIATE, PUSH_RECEIVER_VARIABLE, PUSH_TEMPORARY_VARIABLE, PUSH_LIT_CONSTANT, PUSH_LIT_VARIABLE, PUSH_SELF, PUSH_SPECIAL, PUSH_INTEGER, LINE_NUMBER_BYTECODE, STORE_RECEIVER_VARIABLE, STORE_TEMPORARY_VARIABLE, STORE_LIT_VARIABLE, SEND, POP_INTO_NEW_STACKTOP, POP_STACK_TOP, DUP_STACK_TOP, PUSH_OUTER_TEMP, STORE_OUTER_TEMP, EXIT_INTERPRETER { } JUMP { if (ofs == 2 && dest[0] == LINE_NUMBER_BYTECODE) { /* This could not be optimized to a nop, cause the jump and line number bytecodes lie in different basic blocks! So we rewrite it to a functionally equivalent but optimizable bytecode sequence. */ dest[-2] = dest[0]; dest[-1] = dest[1]; } else if (ofs == 4 && IS_PUSH_BYTECODE (dest[0]) && dest[2] == POP_STACK_TOP) { /* This could not be optimized to a single pop, cause the push and pop bytecodes lie in different basic blocks! Again, rewrite to an optimizable sequence. */ dest[-2] = POP_STACK_TOP; dest[-1] = 0; } else { /* Don't optimize jumps that have extension bytes. But if we jump to a return, we can safely optimize: returns are never extended, and the interpreter ignores the extension byte. TODO: check if this is still true. */ canOptimizeJump = (*IP0 != EXT_BYTE); kind = IP[-2]; dest_ip0 = dest = IP0 + ofs; canOptimizeJump |= IS_RETURN_BYTECODE (*dest); split = true; } } POP_JUMP_TRUE, POP_JUMP_FALSE { if (ofs == 0) { dest[-2] = POP_STACK_TOP; dest[-1] = 0; } /* Jumps to CONDITIONAL jumps must not be touched, either because they were unconditional or because they pop the stack top! */ else if (dest_ip0 == bp) { kind = IP[-2]; dest_ip0 = dest = IP0 + ofs; split = true; } } RETURN_METHOD_STACK_TOP, RETURN_CONTEXT_STACK_TOP { /* Return bytecodes - patch the original jump to return directly */ bp[0] = dest[-2]; bp[1] = 0; /* This in fact eliminated the jump, don't split in basic blocks */ split = false; } INVALID { abort (); } )); } while (canOptimizeJump); while (*bp == EXT_BYTE) bp += BYTECODE_SIZE; bp += BYTECODE_SIZE; if (split) { assert (bp[-2] == kind); assert (kind == JUMP || kind == JUMP_BACK || kind == POP_JUMP_TRUE || kind == POP_JUMP_FALSE); last->dest = -1; last->end = dest_ip0 - bytecodes->base; last->kind = -1; last++; last->dest = dest_ip0 - bytecodes->base; last->end = bp - bytecodes->base; last->kind = kind; last++; } } last->dest = -1; last->end = bp - bytecodes->base; last->kind = -1; last++; /* 2) Get the "real" block boundaries by sorting them according to where they happen in the original bytecode; then complete the data that was put in BLOCKS by setting the start of the basic block, removing the jump bytecode at the end... */ qsort (blocks, last - blocks, sizeof (block_boundary), compare_blocks); i = 0; for (block = blocks; block != last; block++) { block->start = i; if (block->end == i) continue; i = block->end; bp = bytecodes->base + block->end; if (bp[-2] == JUMP || bp[-2] == JUMP_BACK || bp[-2] == POP_JUMP_TRUE || bp[-2] == POP_JUMP_FALSE) { do block->end -= BYTECODE_SIZE, bp -= BYTECODE_SIZE; while (block->end != block->start && bp[-2] == EXT_BYTE); } } /* ... and computing the destination of the jump as a basic block */ for (block = blocks; block != last; block++) if (block->kind != -1) block->dest_bb = bsearch (&block->dest, blocks, last - blocks, sizeof (block_boundary), search_block); /* Optimize the single basic blocks. */ i = 0; for (block = blocks; block != last; block++) { first = bytecodes->base + block->start; bp = bytecodes->base + block->end; block->opt_length = optimize_basic_block (first, bp); #ifndef NO_SUPEROPERATORS /* Make a superoperator with the last bytecode and the jump. */ if (block->kind != -1 && block->opt_length > 0 && !(block->opt_length > 2 && first[block->opt_length - 4] == EXT_BYTE)) { int test = search_superop_fixed_arg_1 (first[block->opt_length - 2], first[block->opt_length - 1], block->kind); if (test != -1) { block->opt_length -= 2; block->kind = test; } } #endif block->final_byte = i; i += block->opt_length; } /* Compute the size of the jump bytecodes. */ do { changed = false; i = 0; for (block = blocks; block != last; block++) { int jump_length; if (block->final_byte != i) { block->final_byte = i; changed = true; } if (block->kind != -1) jump_length = compute_jump_length (block->dest_bb->final_byte - (block->final_byte + block->opt_length)); else jump_length = 0; i += block->opt_length + jump_length; } } while (changed); /* Put together the whole method. */ old_bytecodes = _gst_save_bytecode_array (); for (block = blocks; block != last; block++) { _gst_compile_bytecodes (bytecodes->base + block->start, bytecodes->base + block->start + block->opt_length); if (block->kind != -1) { int jump_length = compute_jump_length (block->dest_bb->final_byte - (block->final_byte + block->opt_length)); int ofs = block->dest_bb->final_byte - (block->final_byte + block->opt_length + jump_length); if (ofs < 0) ofs = -ofs; _gst_compile_byte (block->kind, ofs); } } _gst_free_bytecodes (bytecodes); bytecodes = _gst_get_bytecodes (); _gst_restore_bytecode_array (old_bytecodes); return (bytecodes); #endif } static inline int search_superop_fixed_arg_1(int bc1, int arg, int bc2) { /* ARG is in the range 0..255. The format of the hash table entries is { { BC1, BC2, ARG }, SUPEROP } */ struct superop_with_fixed_arg_1_type { unsigned char bytes[3]; int superop; }; #include "superop1.inl" unsigned int key = asso_values[bc1] + asso_values[bc2] + asso_values[arg]; register const struct superop_with_fixed_arg_1_type *k; if (key > MAX_HASH_VALUE) return -1; k = &keylist[key]; if (bc1 == k->bytes[0] && bc2 == k->bytes[1] && arg == k->bytes[2]) return k->superop; else return -1; } static inline int search_superop_fixed_arg_2(int bc1, int bc2, int arg) { /* ARG is in the range 0..255. The format of the hash table entries is { { BC1, BC2, ARG }, SUPEROP } */ struct superop_with_fixed_arg_2_type { unsigned char bytes[3]; int superop; }; #include "superop2.inl" unsigned int key = asso_values[bc1] + asso_values[bc2] + asso_values[arg]; register const struct superop_with_fixed_arg_2_type *k; if (key > MAX_HASH_VALUE) return -1; k = &keylist[key]; if (bc1 == k->bytes[0] && bc2 == k->bytes[1] && arg == k->bytes[2]) return k->superop; else return -1; } int optimize_basic_block (gst_uchar *from, gst_uchar *to) { /* Points to the optimized bytecodes as they are written. */ gst_uchar *opt = from; /* Points to the unoptimized bytecodes as they are read. */ gst_uchar *bp = from; if (from == to) return 0; do { /* Perform peephole optimizations. For simplicity, the optimizations on line number bytecodes don't take into account the possibility that the line number bytecode is extended (>256 lines in a method). This almost never happens, so we don't bother. */ switch (bp[0]) { case PUSH_TEMPORARY_VARIABLE: case PUSH_RECEIVER_VARIABLE: /* Leave only the store in store/pop/push sequences. Don't do this for STORE_LIT_VARIABLE, as it fails if #value: is sent and, for example, self is returned. */ if (opt >= from + 4 && (opt == from + 4 || opt[-6] != EXT_BYTE) && opt[-4] == bp[0] + (STORE_TEMPORARY_VARIABLE - PUSH_TEMPORARY_VARIABLE) && opt[-3] == bp[1] && opt[-2] == POP_STACK_TOP && bp[-2] != EXT_BYTE) { opt -= 2; bp += 2; continue; } /* Also rewrite store/pop/line/push to store/line in the middle. */ if (opt >= from + 6 && (opt == from + 6 || opt[-8] != EXT_BYTE) && opt[-6] == bp[0] + (STORE_TEMPORARY_VARIABLE - PUSH_TEMPORARY_VARIABLE) && opt[-5] == bp[1] && opt[-4] == POP_STACK_TOP && opt[-2] == LINE_NUMBER_BYTECODE && bp[-2] != EXT_BYTE) { opt[-4] = opt[-2]; opt[-3] = opt[-1]; opt -= 2; bp += 2; continue; } /* fall through to other pushes. */ case PUSH_OUTER_TEMP: case PUSH_INTEGER: case PUSH_SELF: case PUSH_SPECIAL: case PUSH_LIT_CONSTANT: /* Remove a push followed by a pop */ if (bp < to - 2 && bp[2] == POP_STACK_TOP) { bp += 4; continue; } /* Remove the pop in a pop/push/return sequence */ if (opt >= from + 2 && bp < to - 2 && bp[2] == RETURN_CONTEXT_STACK_TOP && opt[-2] == POP_STACK_TOP) opt -= 2; /* Rewrite the pop/line number/push sequence to line number/pop/push because this can be better optimized by superoperators (making a superoperator with a nop byte saves on decoding, but not on scheduling the instructions in the interpreter!). */ if (opt >= from + 4 && opt[-4] == POP_STACK_TOP && opt[-2] == LINE_NUMBER_BYTECODE) { opt[-4] = LINE_NUMBER_BYTECODE; opt[-3] = opt[-1]; opt[-2] = POP_STACK_TOP; opt[-1] = 0; } break; case JUMP: case JUMP_BACK: case POP_JUMP_TRUE: case POP_JUMP_FALSE: abort (); default: break; } /* Else, just copy the bytecode to the optimized area. */ *opt++ = *bp++; *opt++ = *bp++; } while (bp < to); #ifndef NO_SUPEROPERATORS opt = optimize_superoperators (from, opt); #endif return opt - from; } gst_uchar * optimize_superoperators (gst_uchar * from, gst_uchar * to) { /* Points to the optimized bytecodes that have been written. */ gst_uchar *opt = from; /* Points to the unoptimized bytecodes as they are read. */ gst_uchar *bp = from; int new_bc; if (from == to) return from; *opt++ = *bp++; *opt++ = *bp++; while (bp < to) { /* Copy two bytecodes to the optimized area. */ *opt++ = *bp++; *opt++ = *bp++; do { /* Try to match the case when the second argument is fixed. We try this first because EXT_BYTE(*), SEND(1) is more beneficial than EXT_BYTE(1), SEND(*). */ new_bc = search_superop_fixed_arg_2 (opt[-4], opt[-2], opt[-1]); if (new_bc != -1) { opt[-4] = new_bc; /* opt[-3] is already ok */ opt -= 2; /* Look again at the last four bytes. */ continue; } /* If the first bytecode is not extended, try matching it with a fixed argument. We skip this when the first bytecode is extended because otherwise we might have superoperators like PUSH_OUTER_TEMP(1), SEND(*) Suppose we find EXT_BYTE(1), SUPEROP(2) Now the argument to SEND is 2, but the interpreter receives an argument of 258 and has to decode the argument to extract the real argument of PUSH_OUTER_TEMP (found in the extension byte). This messes up everything and goes against the very purpose of introducing superoperators. */ if (opt - from == 4 || opt[-6] != EXT_BYTE) { new_bc = search_superop_fixed_arg_1 (opt[-4], opt[-3], opt[-2]); if (new_bc != -1) { opt[-4] = new_bc; opt[-3] = opt[-1]; opt -= 2; /* Look again at the last four bytes. */ continue; } } /* Nothing matched. Exit. */ break; } while (opt - from >= 4); } return opt; } void _gst_compute_stack_positions (gst_uchar * bp, int size, PTR * base, PTR ** pos) { basic_block_item **bb_start, *bb_first, *worklist, *susp_head, **susp_tail = &susp_head; int bc_len; bb_start = alloca ((1 + size) * sizeof (basic_block_item *)); memset (bb_start, 0, (1 + size) * sizeof (basic_block_item *)); memset (pos, 0, (1 + size) * sizeof (PTR *)); /* Allocate the first and last basic block specially */ ALLOCA_BASIC_BLOCK (bb_start, 0, bp, 0); ALLOCA_BASIC_BLOCK (bb_start + size, 0, bp + size, 0); bb_first = bb_start[0]; bb_first->next = NULL; /* First build the pointers to the basic blocks into BB_START. Then use of a worklist here is only to find a correct order for visiting the basic blocks, not because they're visited multiple times. This works transparently when we have a return in the middle of the method. Then the basic block is ending, yet it might be that the stack height for the next bytecode is already known!!! */ for (susp_head = NULL, worklist = bb_first; worklist; ) { int curr_sp = worklist->sp; bp = worklist->bp; bb_start = worklist->bb; worklist = worklist->next; #ifdef DEBUG_JIT_TRANSLATOR printf ("Tracing basic block at %d:\n", bb_start - bb_first->bb); #endif do { int curr_ip = bb_start - bb_first->bb; int balance; gst_uchar *bp_first = bp; #ifdef DEBUG_JIT_TRANSLATOR printf ("[SP=%3d]%5d:", curr_sp, curr_ip); _gst_print_bytecode_name (bp, curr_ip, NULL, "\t"); #endif balance = 0; pos[curr_ip] = base + curr_sp; MATCH_BYTECODES (COMPUTE_STACK_POS, bp, ( RETURN_METHOD_STACK_TOP, RETURN_CONTEXT_STACK_TOP { bc_len = bp - bp_first; /* We cannot fill the basic block right now because the stack height might be different. */ if (!bb_start[bc_len]) { ALLOCA_BASIC_BLOCK (bb_start + bc_len, 0, bp_first + bc_len, curr_sp + balance); bb_start[bc_len]->suspended = true; bb_start[bc_len]->next = NULL; *susp_tail = bb_start[bc_len]; susp_tail = &(bb_start[bc_len]->next); } } POP_INTO_NEW_STACKTOP, POP_STACK_TOP { balance--; } PUSH_RECEIVER_VARIABLE, PUSH_TEMPORARY_VARIABLE, PUSH_LIT_CONSTANT, PUSH_LIT_VARIABLE, PUSH_SELF, PUSH_SPECIAL, PUSH_INTEGER, DUP_STACK_TOP, PUSH_OUTER_TEMP { balance++; } LINE_NUMBER_BYTECODE, STORE_RECEIVER_VARIABLE, STORE_TEMPORARY_VARIABLE, STORE_LIT_VARIABLE, STORE_OUTER_TEMP, EXIT_INTERPRETER, MAKE_DIRTY_BLOCK { } SEND { balance -= super + num_args; } SEND_ARITH { balance -= _gst_builtin_selectors[n].numArgs; } SEND_IMMEDIATE { balance -= super + _gst_builtin_selectors[n].numArgs; } SEND_SPECIAL { balance -= _gst_builtin_selectors[n + 16].numArgs; } INVALID { abort (); } JUMP { bc_len = bp - bp_first; /* We cannot fill the basic block right now because the stack height might be different. */ if (!bb_start[bc_len]) { ALLOCA_BASIC_BLOCK (bb_start + bc_len, 0, bp_first + bc_len, 0); bb_start[bc_len]->suspended = true; bb_start[bc_len]->next = NULL; *susp_tail = bb_start[bc_len]; susp_tail = &(bb_start[bc_len]->next); } if (!bb_start[ofs]) { ALLOCA_BASIC_BLOCK (bb_start + ofs, 0, bp_first + ofs, curr_sp + balance); bb_start[ofs]->next = worklist; worklist = bb_start[ofs]; } else if (bb_start[ofs]->suspended) { bb_start[ofs]->suspended = false; bb_start[ofs]->sp = curr_sp + balance; } else if (curr_sp + balance != bb_start[ofs]->sp) abort (); } POP_JUMP_TRUE, POP_JUMP_FALSE { balance--; bc_len = bp - bp_first; if (!bb_start[bc_len]) { ALLOCA_BASIC_BLOCK (bb_start + bc_len, 0, bp_first + bc_len, curr_sp + balance); bb_start[bc_len]->next = worklist; worklist = bb_start[bc_len]; } else if (bb_start[bc_len]->suspended) { bb_start[bc_len]->suspended = false; bb_start[bc_len]->sp = curr_sp + balance; } else if (curr_sp + balance != bb_start[bc_len]->sp) abort (); if (!bb_start[ofs]) { ALLOCA_BASIC_BLOCK (bb_start + ofs, 0, bp_first + ofs, curr_sp + balance); bb_start[ofs]->next = worklist; worklist = bb_start[ofs]; } else if (bb_start[ofs]->suspended) { bb_start[ofs]->suspended = false; bb_start[ofs]->sp = curr_sp + balance; } else if (curr_sp + balance != bb_start[ofs]->sp) abort (); } )); curr_sp += balance; bb_start += bp - bp_first; } while (!*bb_start); if (!worklist && susp_head) { worklist = susp_head; susp_head = susp_head->next; worklist->next = NULL; if (!susp_head) susp_tail = &susp_head; } } } void _gst_analyze_bytecodes (OOP methodOOP, int size, char *dest) { gst_uchar *bp; bp = GET_METHOD_BYTECODES (methodOOP); make_destination_table (bp, size, dest); /* Nothing more for now */ } int make_destination_table (gst_uchar * bp, int size, char *dest) { gst_uchar *end, *bp_first; int count; memset (dest, 0, sizeof (char) * size); for (count = 0, end = bp + size; bp != end; dest += bp - bp_first) { bp_first = bp; MATCH_BYTECODES (MAKE_DEST_TABLE, bp, ( PUSH_RECEIVER_VARIABLE, PUSH_TEMPORARY_VARIABLE, PUSH_LIT_CONSTANT, PUSH_LIT_VARIABLE, PUSH_SELF, PUSH_SPECIAL, PUSH_INTEGER, RETURN_METHOD_STACK_TOP, RETURN_CONTEXT_STACK_TOP, LINE_NUMBER_BYTECODE, STORE_RECEIVER_VARIABLE, STORE_TEMPORARY_VARIABLE, STORE_LIT_VARIABLE, SEND, POP_INTO_NEW_STACKTOP, POP_STACK_TOP, DUP_STACK_TOP, PUSH_OUTER_TEMP, STORE_OUTER_TEMP, EXIT_INTERPRETER, SEND_ARITH, SEND_SPECIAL, SEND_IMMEDIATE, MAKE_DIRTY_BLOCK { } INVALID { abort(); } JUMP, POP_JUMP_TRUE, POP_JUMP_FALSE { dest[ofs] = ofs > 0 ? 1 : -1; count++; } )); } return (count); } #define SELF 0 #define VARYING 1 #define UNDEFINED 2 typedef struct partially_constructed_array { struct partially_constructed_array *next; int sp; int size; } partially_constructed_array; #define CHECK_LITERAL(n) \ /* Todo: recurse into BlockClosures! */ \ last_used_literal = literals[n]; \ if ((n) >= num_literals) \ return ("literal out of range"); #define CHECK_TEMP(n) \ last_used_literal = NULL; \ if ((n) >= sp - stack) \ return ("temporary out of range"); #define CHECK_REC_VAR(first, n) \ last_used_literal = NULL; \ if ((n) < (first) || (n) >= num_rec_vars) \ return ("receiver variable out of range"); #define CHECK_LIT_VARIABLE(store, n) \ CHECK_LITERAL (n); \ if (IS_INT (literals[(n)]) || \ !is_a_kind_of (OOP_CLASS (literals[(n)]), _gst_lookup_key_class)) \ return ("LookupKey expected"); \ else if (store \ && untrusted \ && !IS_OOP_UNTRUSTED (literals[(n)])) \ return ("Invalid global variable access"); #define LIT_VARIABLE_CLASS(n) \ /* Special case classes because of super and {...} */ \ (IS_A_CLASS (ASSOCIATION_VALUE (literals[(n)])) \ ? OOP_CLASS (ASSOCIATION_VALUE (literals[(n)])) \ : FROM_INT (VARYING)) #define LITERAL_CLASS(n) \ OOP_INT_CLASS (literals[(n)]) /* Bytecode verification is a dataflow analysis on types. We perform it on basic blocks: `in' is the stack when entering the basic block and `out' is the stack upon exit. Each member of the stack can be UNDEFINED, a type, or VARYING. When merging two `out' stacks to compute an `in' stack, we have these possible situations: - the stacks are not the same height, and bytecode verification fails - a slot is the same in both stacks, so it has this type in the output too - a slot is different in the two stacks, so it is VARYING in the output. Bytecode verification proceeds forwards, so the worklist is added all the successors of the basic block whenever merging results in a difference. */ mst_Boolean merge_stacks (OOP *dest, int dest_sp, OOP *src, int src_sp) { mst_Boolean varied = false; assert (dest_sp == src_sp); for (; src_sp--; dest++, src++) { OOP newDest = *src; if (newDest != *src) { if (*dest != FROM_INT (UNDEFINED)) /* If different, mark as overdefined. */ newDest = FROM_INT (VARYING); if (newDest != *dest) { *dest = newDest; varied = true; } } } return (varied); } void _gst_verify_sent_method (OOP methodOOP) { const char *error; error = _gst_verify_method (methodOOP, NULL, 0); if (error) { _gst_errorf ("Bytecode verification failed: %s", error); if (OOP_CLASS (methodOOP) == _gst_compiled_block_class) methodOOP = GET_BLOCK_METHOD (methodOOP); _gst_errorf ("Method verification failed for %O>>%O", GET_METHOD_CLASS (methodOOP), GET_METHOD_SELECTOR (methodOOP)); abort (); } } const char * _gst_verify_method (OOP methodOOP, int *num_outer_temps, int depth) { #ifndef NO_VERIFIER int size, bc_len, num_temps, stack_depth, num_literals, num_rec_vars, num_ro_rec_vars; mst_Boolean untrusted; const char *error; gst_uchar *bp; OOP *literals, methodClass, last_used_literal; basic_block_item **bb_start, *bb_first, *worklist, *susp_head, **susp_tail = &susp_head; partially_constructed_array *arrays = NULL, *arrays_pool = NULL; if (IS_OOP_VERIFIED (methodOOP)) return (NULL); size = NUM_INDEXABLE_FIELDS (methodOOP); bp = GET_METHOD_BYTECODES (methodOOP); literals = GET_METHOD_LITERALS (methodOOP); methodClass = GET_METHOD_CLASS (methodOOP); num_literals = NUM_METHOD_LITERALS (methodOOP); num_rec_vars = CLASS_FIXED_FIELDS (methodClass); untrusted = IS_OOP_UNTRUSTED (methodOOP); if (is_a_kind_of (OOP_CLASS (methodOOP), _gst_compiled_method_class)) { method_header header; header = GET_METHOD_HEADER (methodOOP); num_temps = header.numArgs + header.numTemps; stack_depth = header.stack_depth << DEPTH_SCALE; switch (header.headerFlag) { case MTH_NORMAL: case MTH_PRIMITIVE: case MTH_ANNOTATED: case MTH_UNUSED: break; case MTH_USER_DEFINED: case MTH_RETURN_SELF: methodOOP->flags |= F_VERIFIED; return (NULL); case MTH_RETURN_INSTVAR: CHECK_REC_VAR (0, header.primitiveIndex); methodOOP->flags |= F_VERIFIED; return (NULL); case MTH_RETURN_LITERAL: CHECK_LITERAL (0); methodOOP->flags |= F_VERIFIED; return (NULL); } } else if (OOP_CLASS (methodOOP) == _gst_compiled_block_class) { block_header header; header = GET_BLOCK_HEADER (methodOOP); /* If we're verifying a block but not from a nested call, restart from the top-level method. */ if (header.clean != 0 && depth == 0) return _gst_verify_method (GET_BLOCK_METHOD (methodOOP), NULL, 0); num_temps = header.numArgs + header.numTemps; stack_depth = header.depth << DEPTH_SCALE; } else return "invalid class"; if (untrusted) { OOP class_oop; for (class_oop = methodClass; IS_OOP_UNTRUSTED (class_oop); class_oop = SUPERCLASS (class_oop)) ; num_ro_rec_vars = CLASS_FIXED_FIELDS (class_oop); } else num_ro_rec_vars = 0; #ifdef DEBUG_VERIFIER printf ("Verifying %O (max. stack depth = %d):\n", methodOOP, stack_depth); #endif /* Prepare the NUM_OUTER_TEMPS array for the inner blocks. */ if (depth) { int *new_num_outer_temps = alloca (sizeof (int) * (depth + 1)); memcpy (new_num_outer_temps + 1, num_outer_temps, sizeof (int) * depth); new_num_outer_temps[0] = num_temps; num_outer_temps = new_num_outer_temps; } else num_outer_temps = &num_temps; depth++; bb_start = alloca ((1 + size) * sizeof (basic_block_item *)); memset (bb_start, 0, (1 + size) * sizeof (basic_block_item *)); /* Allocate the first and last basic block specially */ ALLOCA_BASIC_BLOCK(bb_start, stack_depth, bp, num_temps); ALLOCA_BASIC_BLOCK(bb_start + size, stack_depth, bp + size, num_temps); bb_first = bb_start[0]; bb_first->next = NULL; /* First build the pointers to the basic blocks into BB_START. The use of a worklist here is only to find a correct order for visiting the basic blocks, not because they're visited multiple times. This works transparently when we have a return in the middle of the method. Then the basic block is ending, yet it might be that the stack height for the next bytecode is already known!!! */ for (susp_head = NULL, worklist = bb_first; worklist; ) { int curr_sp = worklist->sp; bp = worklist->bp; bb_start = worklist->bb; worklist = worklist->next; #ifdef DEBUG_VERIFIER printf ("Tracing basic block at %d:\n", bb_start - bb_first->bb); #endif do { int curr_ip = bb_start - bb_first->bb; int balance; gst_uchar *bp_first = bp; #ifdef DEBUG_VERIFIER printf ("[SP=%3d]%5d:", curr_sp, curr_ip); _gst_print_bytecode_name (bp, curr_ip, literals, "\t"); #endif balance = 0; MATCH_BYTECODES (CREATE_BASIC_BLOCKS, bp, ( RETURN_METHOD_STACK_TOP, RETURN_CONTEXT_STACK_TOP { bc_len = bp - bp_first; /* We cannot fill the basic block right now because the stack height might be different. */ if (!bb_start[bc_len]) { ALLOCA_BASIC_BLOCK (bb_start + bc_len, stack_depth, bp_first + bc_len, curr_sp + balance); bb_start[bc_len]->suspended = true; bb_start[bc_len]->next = NULL; *susp_tail = bb_start[bc_len]; susp_tail = &(bb_start[bc_len]->next); } } POP_STACK_TOP { balance--; } PUSH_RECEIVER_VARIABLE, PUSH_TEMPORARY_VARIABLE, PUSH_LIT_CONSTANT, PUSH_LIT_VARIABLE, PUSH_SELF, PUSH_SPECIAL, PUSH_INTEGER, PUSH_OUTER_TEMP { balance++; } LINE_NUMBER_BYTECODE, STORE_RECEIVER_VARIABLE, STORE_TEMPORARY_VARIABLE, STORE_LIT_VARIABLE, STORE_OUTER_TEMP, EXIT_INTERPRETER, MAKE_DIRTY_BLOCK { } SEND { balance -= super + num_args; /* Sends touch the new stack top, so they require an extra slot. */ if (curr_sp + balance < 1) return ("stack underflow"); } SEND_ARITH { if (!_gst_builtin_selectors[n].symbol) return ("invalid immediate send"); balance -= _gst_builtin_selectors[n].numArgs; /* Sends touch the new stack top, so they require an extra slot. */ if (curr_sp + balance < 1) return ("stack underflow"); } SEND_SPECIAL { if (!_gst_builtin_selectors[n + 16].symbol) return ("invalid immediate send"); balance -= _gst_builtin_selectors[n + 16].numArgs; /* Sends touch the new stack top, so they require an extra slot. */ if (curr_sp + balance < 1) return ("stack underflow"); } SEND_IMMEDIATE { if (!_gst_builtin_selectors[n].symbol) return ("invalid immediate send"); balance -= super + _gst_builtin_selectors[n].numArgs; /* Sends touch the new stack top, so they require an extra slot. */ if (curr_sp + balance < 1) return ("stack underflow"); } POP_INTO_NEW_STACKTOP { balance--; /* Sends touch the new stack top, so they require an extra slot. */ if (curr_sp + balance < 1) return ("stack underflow"); } DUP_STACK_TOP { balance++; } INVALID { return ("invalid bytecode"); } JUMP { if (ofs & 1) return ("jump to odd offset"); if (ofs + curr_ip < 0 || ofs + curr_ip > size) return ("jump out of range"); if (ofs + curr_ip > 0 && bp_first[ofs - 2] == EXT_BYTE) return ("jump skips extension bytecode"); bc_len = bp - bp_first; /* We cannot fill the basic block right now because the stack height might be different. */ if (!bb_start[bc_len]) { ALLOCA_BASIC_BLOCK (bb_start + bc_len, stack_depth, bp_first + bc_len, 0); bb_start[bc_len]->suspended = true; bb_start[bc_len]->next = NULL; *susp_tail = bb_start[bc_len]; susp_tail = &(bb_start[bc_len]->next); } if (!bb_start[ofs]) { ALLOCA_BASIC_BLOCK (bb_start + ofs, stack_depth, bp_first + ofs, curr_sp + balance); bb_start[ofs]->next = worklist; worklist = bb_start[ofs]; INIT_BASIC_BLOCK (worklist, num_temps); } else if (bb_start[ofs]->suspended) { bb_start[ofs]->suspended = false; bb_start[ofs]->sp = curr_sp + balance; INIT_BASIC_BLOCK (bb_start[ofs], num_temps); } else if (curr_sp + balance != bb_start[ofs]->sp) return ("stack height mismatch"); } POP_JUMP_TRUE, POP_JUMP_FALSE { balance--; if (ofs & 1) return ("jump to odd offset"); if (ofs + curr_ip < 0 || ofs + curr_ip > size) return ("jump out of range"); if (ofs + curr_ip > 0 && bp_first[ofs - 2] == EXT_BYTE) return ("jump skips extension bytecode"); bc_len = bp - bp_first; if (!bb_start[bc_len]) { ALLOCA_BASIC_BLOCK (bb_start + bc_len, stack_depth, bp_first + bc_len, curr_sp + balance); bb_start[bc_len]->next = worklist; worklist = bb_start[bc_len]; INIT_BASIC_BLOCK (worklist, num_temps); } else if (bb_start[bc_len]->suspended) { bb_start[bc_len]->suspended = false; bb_start[bc_len]->sp = curr_sp + balance; INIT_BASIC_BLOCK (bb_start[bc_len], num_temps); } else if (curr_sp + balance != bb_start[bc_len]->sp) return ("stack height mismatch"); if (!bb_start[ofs]) { ALLOCA_BASIC_BLOCK (bb_start + ofs, stack_depth, bp_first + ofs, curr_sp + balance); bb_start[ofs]->next = worklist; worklist = bb_start[ofs]; INIT_BASIC_BLOCK (worklist, num_temps); } else if (bb_start[ofs]->suspended) { bb_start[ofs]->suspended = false; bb_start[ofs]->sp = curr_sp + balance; INIT_BASIC_BLOCK (bb_start[ofs], num_temps); } else if (curr_sp + balance != bb_start[ofs]->sp) return ("stack height mismatch"); } )); curr_sp += balance; if (curr_sp >= stack_depth) return ("stack overflow"); bb_start += bp - bp_first; } while (!*bb_start); if (!worklist && susp_head) { worklist = susp_head; susp_head = susp_head->next; worklist->next = NULL; if (!susp_head) susp_tail = &susp_head; } #ifdef DEBUG_VERIFIER printf ("\n"); #endif } for (worklist = bb_first; worklist; ) { OOP *stack = worklist->stack; OOP *sp; /* Look for unreachable basic blocks. */ if (worklist->sp < 0) abort (); sp = stack + worklist->sp; bp = worklist->bp; bb_start = worklist->bb; worklist = worklist->next; #ifdef DEBUG_VERIFIER printf ("Executing basic block at %d:\n", bb_start - bb_first->bb); #endif last_used_literal = NULL; do { gst_uchar *bp_first = bp; #ifdef DEBUG_VERIFIER printf ("[SP=%3d]%5d:", sp - stack, bb_start - bb_first->bb); _gst_print_bytecode_name (bp, bb_start - bb_first->bb, literals, "\t"); #endif MATCH_BYTECODES (EXEC_BASIC_BLOCK, bp, ( PUSH_RECEIVER_VARIABLE { CHECK_REC_VAR (0, n); *sp++ = FROM_INT (VARYING); } PUSH_TEMPORARY_VARIABLE { CHECK_TEMP (n); *sp++ = stack[n]; } PUSH_LIT_CONSTANT { CHECK_LITERAL (n); *sp++ = LITERAL_CLASS (n); } PUSH_LIT_VARIABLE { CHECK_LIT_VARIABLE (false, n); *sp++ = LIT_VARIABLE_CLASS (n); } PUSH_SELF { last_used_literal = NULL; *sp++ = FROM_INT (SELF); } PUSH_SPECIAL { switch (n) { case NIL_INDEX: last_used_literal = _gst_nil_oop; break; case TRUE_INDEX: last_used_literal = _gst_true_oop; break; case FALSE_INDEX: last_used_literal = _gst_false_oop; break; default: return "invalid special object index"; } *sp++ = OOP_CLASS (last_used_literal); } PUSH_INTEGER { last_used_literal = FROM_INT (n); *sp++ = _gst_small_integer_class; } RETURN_METHOD_STACK_TOP { block_header header; if (OOP_CLASS (methodOOP) != _gst_compiled_block_class) return "invalid return from method"; header = GET_BLOCK_HEADER (methodOOP); if (header.clean != (1 << BLK_CLEAN_BITS) - 1) return "invalid return from clean block"; break; } RETURN_CONTEXT_STACK_TOP { break; } LINE_NUMBER_BYTECODE { } STORE_RECEIVER_VARIABLE { CHECK_REC_VAR (num_ro_rec_vars, n); } STORE_TEMPORARY_VARIABLE { CHECK_TEMP (n); } STORE_LIT_VARIABLE { CHECK_LIT_VARIABLE (true, n); } SEND { if (super && (!last_used_literal || (!IS_A_CLASS (last_used_literal) && !IS_A_METACLASS (last_used_literal)) || !is_a_kind_of (methodClass, last_used_literal))) return ("Invalid send to super"); last_used_literal = NULL; sp -= super + num_args; if (super && sp[-1] != FROM_INT (SELF)) return ("Invalid send to super"); sp[-1] = FROM_INT (VARYING); } POP_INTO_NEW_STACKTOP { if (sp[-2] != _gst_array_class) return ("Array expected"); if (!arrays || &sp[-2] - stack != arrays->sp) return ("Invalid Array constructor"); if (n >= arrays->size) return ("Out of bounds Array access"); /* Discard arrays whose construction has ended. */ if (n == arrays->size - 1) { partially_constructed_array *next = arrays->next; arrays->next = arrays_pool; arrays_pool = arrays; arrays = next; } last_used_literal = NULL; sp--; } POP_STACK_TOP { last_used_literal = NULL; sp--; } DUP_STACK_TOP { sp++; sp[-1] = sp[-2]; } PUSH_OUTER_TEMP { if (scopes == 0 || scopes > depth || n >= num_outer_temps[scopes]) return ("temporary out of range"); last_used_literal = NULL; *sp++ = FROM_INT (VARYING); } STORE_OUTER_TEMP { if (scopes == 0 || scopes > depth || n >= num_outer_temps[scopes]) return ("temporary out of range"); } EXIT_INTERPRETER { if (size != 4 || IP0 != GET_METHOD_BYTECODES (methodOOP) || *bp != RETURN_CONTEXT_STACK_TOP) return ("bad termination method"); } JUMP { if (merge_stacks (stack, sp - stack, bb_start[ofs]->stack, bb_start[ofs]->sp)) bb_start[ofs]->next = worklist, worklist = bb_start[ofs]; } POP_JUMP_TRUE, POP_JUMP_FALSE { sp--; bc_len = bp - bp_first; if (merge_stacks (stack, sp - stack, bb_start[bc_len]->stack, bb_start[bc_len]->sp)) bb_start[bc_len]->next = worklist, worklist = bb_start[bc_len]; if (merge_stacks (stack, sp - stack, bb_start[ofs]->stack, bb_start[ofs]->sp)) bb_start[ofs]->next = worklist, worklist = bb_start[ofs]; } SEND_ARITH { sp -= _gst_builtin_selectors[n].numArgs; sp[-1] = FROM_INT (VARYING); } SEND_SPECIAL { sp -= _gst_builtin_selectors[n + 16].numArgs; sp[-1] = FROM_INT (VARYING); } SEND_IMMEDIATE { if (n == NEW_COLON_SPECIAL && IS_INT (last_used_literal) && last_used_literal != FROM_INT (0) && sp[-2] == OOP_CLASS (_gst_array_class)) { partially_constructed_array *a; sp--; /* If possible, reuse an existing struct, else allocate a new one. */ if (arrays_pool) { a = arrays_pool; arrays_pool = arrays_pool->next; } else a = alloca (sizeof (partially_constructed_array)); a->size = TO_INT (last_used_literal); a->sp = &sp[-1] - stack; a->next = arrays; arrays = a; sp[-1] = _gst_array_class; } else { if (super && (!last_used_literal || (!IS_A_CLASS (last_used_literal) && !IS_A_METACLASS (last_used_literal)) || !is_a_kind_of (methodClass, last_used_literal))) return (_gst_debug (), "Invalid send to super"); last_used_literal = NULL; sp -= super + _gst_builtin_selectors[n].numArgs; if (super && sp[-1] != FROM_INT (SELF)) return ("Invalid send to super"); sp[-1] = FROM_INT (VARYING); } } MAKE_DIRTY_BLOCK { if (sp[-1] != _gst_compiled_block_class || !last_used_literal) return ("CompiledBlock expected"); error = _gst_verify_method (last_used_literal, num_outer_temps, depth); if (error) return (error); } INVALID { abort (); } )); bb_start += bp - bp_first; } while (!*bb_start); #ifdef DEBUG_VERIFIER printf ("\n"); #endif } #endif /* !NO_VERIFIER */ methodOOP->flags |= F_VERIFIED; return (NULL); } smalltalk-3.2.5/libgst/dict.h0000644000175000017500000005244112130343734013014 00000000000000/******************************** -*- C -*- **************************** * * Dictionary Support Module Definitions. * * ***********************************************************************/ /*********************************************************************** * * Copyright 2000, 2001, 2002, 2003, 2005, 2006, 2008, 2009 * Free Software Foundation, Inc. * Written by Steve Byrne. * * This file is part of GNU Smalltalk. * * GNU Smalltalk is free software; you can redistribute it and/or modify it * under the terms of the GNU General Public License as published by the Free * Software Foundation; either version 2, or (at your option) any later * version. * * Linking GNU Smalltalk statically or dynamically with other modules is * making a combined work based on GNU Smalltalk. Thus, the terms and * conditions of the GNU General Public License cover the whole * combination. * * In addition, as a special exception, the Free Software Foundation * give you permission to combine GNU Smalltalk with free software * programs or libraries that are released under the GNU LGPL and with * independent programs running under the GNU Smalltalk virtual machine. * * You may copy and distribute such a system following the terms of the * GNU GPL for GNU Smalltalk and the licenses of the other code * concerned, provided that you include the source code of that other * code when and as the GNU GPL requires distribution of source code. * * Note that people who make modified versions of GNU Smalltalk are not * obligated to grant this special exception for their modified * versions; it is their choice whether to do so. The GNU General * Public License gives permission to release a modified version without * this exception; this exception also makes it possible to release a * modified version which carries forward this exception. * * GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or * FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for * more details. * * You should have received a copy of the GNU General Public License along with * GNU Smalltalk; see the file COPYING. If not, write to the Free Software * Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * ***********************************************************************/ #ifndef GST_DICT_H #define GST_DICT_H /*********************************************************************** * * Below are the structural definitions for several of the important * objects present in the Smalltalk system. Their C representation * corresponds exactly with their Smalltalk representation. * ***********************************************************************/ /* Note the use of structural inheritance in C structure definitions here */ typedef struct gst_file_stream { OBJ_HEADER; OOP access; OOP fd; OOP file; OOP isPipe; OOP atEnd; OOP peek; OOP collection; OOP ptr; OOP endPtr; OOP writePtr; OOP writeEnd; } *gst_file_stream; typedef struct gst_dictionary { OBJ_HEADER; OOP tally; /* really, an int */ /* Other, indexable fields that are the associations for this dictionary. */ } *gst_dictionary; typedef struct gst_binding_dictionary { OBJ_HEADER; OOP tally; /* really, an int */ OOP environment; OOP assoc[1]; /* Other, indexable fields that are the associations for this dictionary. */ } *gst_binding_dictionary; typedef struct gst_namespace { OBJ_HEADER; OOP tally; /* really, an int */ OOP superspace; OOP name; OOP subspaces; OOP sharedPools; OOP assoc[1]; /* Other, indexable fields that are the associations for this dictionary. */ } *gst_namespace; typedef struct gst_identity_dictionary { OBJ_HEADER; OOP tally; /* really, an int */ OOP keys[1]; /* variable sized array of OOPS (keys/values) */ } *gst_identity_dictionary; #define BEHAVIOR_HEADER \ OBJ_HEADER; \ OOP superclass; \ OOP methodDictionary; \ intptr_t instanceSpec; \ OOP subClasses; \ OOP instanceVariables typedef struct gst_behavior { BEHAVIOR_HEADER; } *gst_behavior; #define CLASS_DESCRIPTION_HEADER \ BEHAVIOR_HEADER #define COBJECT_ANON_TYPE FROM_INT(-1) #define COBJECT_CHAR_TYPE FROM_INT(0) #define COBJECT_UNSIGNED_CHAR_TYPE FROM_INT(1) #define COBJECT_SHORT_TYPE FROM_INT(2) #define COBJECT_UNSIGNED_SHORT_TYPE FROM_INT(3) #define COBJECT_LONG_TYPE FROM_INT(4) #define COBJECT_UNSIGNED_LONG_TYPE FROM_INT(5) #define COBJECT_FLOAT_TYPE FROM_INT(6) #define COBJECT_DOUBLE_TYPE FROM_INT(7) #define COBJECT_STRING_TYPE FROM_INT(8) #define COBJECT_SMALLTALK_TYPE FROM_INT(9) #define COBJECT_INT_TYPE FROM_INT(10) #define COBJECT_UNSIGNED_INT_TYPE FROM_INT(11) /* 3 2 1 1 0 9 8 7 6 5 4 3 2 1 0 9 8 7 6 5 4 3 2 1 0 9 8 7 6 5 4 3 2 1 0 +-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+ | # fixed fields | unused |I| kind |1| +-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+ I'm moving it to bits 13-30 (it used to stay at bits 5-30), allocating space for more flags in case they're needed. If you change ISP_NUMFIXEDFIELDS you should modify Behavior.st too. Remember to shift by ISP_NUMFIXEDFIELDS-1 there, since Smalltalk does not see GST_ISP_INTMARK!! */ enum { ISP_NUMFIXEDFIELDS = 13, /* Set if the instances of the class have indexed instance variables. */ ISP_ISINDEXABLE = 32, /* These represent the shape of the indexed instance variables of the instances of the class. */ ISP_INDEXEDVARS = 62, ISP_SHAPE = 30, /* Set to 1 to mark a SmallInteger. */ GST_ISP_INTMARK = 1 }; typedef struct gst_class_description { CLASS_DESCRIPTION_HEADER; } *gst_class_description; typedef struct gst_deferred_variable_binding { OBJ_HEADER; OOP key; OOP class; OOP defaultDictionary; OOP association; OOP path; } *gst_deferred_variable_binding; typedef struct gst_association { OBJ_HEADER; OOP key; OOP value; } *gst_association; typedef struct gst_variable_binding { OBJ_HEADER; OOP key; OOP value; OOP environment; } *gst_variable_binding; typedef struct gst_floatd { OBJ_HEADER; double value; } *gst_floatd; typedef struct gst_floate { OBJ_HEADER; float value; } *gst_floate; typedef struct gst_floatq { OBJ_HEADER; long double value; } *gst_floatq; typedef struct gst_message { OBJ_HEADER; OOP selector; OOP args; } *gst_message; typedef struct gst_directed_message { OBJ_HEADER; OOP selector; OOP args; OOP receiver; } *gst_directed_message; typedef struct gst_string { OBJ_HEADER; char chars[1]; } *gst_string; typedef struct gst_unicode_string { OBJ_HEADER; uint32_t chars[1]; } *gst_unicode_string; typedef struct gst_byte_array { OBJ_HEADER; gst_uchar bytes[1]; } *gst_byte_array; typedef struct gst_class { CLASS_DESCRIPTION_HEADER; OOP name; OOP comment; OOP category; OOP environment; OOP classVariables; /* dictionary of name->value pairs */ OOP sharedPools; OOP securityPolicy; OOP pragmaHandlers; } *gst_class; typedef struct gst_metaclass { CLASS_DESCRIPTION_HEADER; OOP instanceClass; } *gst_metaclass; typedef struct gst_char { OBJ_HEADER; OOP codePoint; } *gst_char; typedef struct gst_ordered_collection { OBJ_HEADER; OOP firstIndex; OOP lastIndex; OOP data[1]; } *gst_ordered_collection; typedef struct gst_cobject { OBJ_HEADER; OOP type; OOP storage; } *gst_cobject; typedef struct gst_ctype { OBJ_HEADER; OOP cObjectType; /* the gst_cobject subclass to use when instantiating this type */ } *gst_ctype; extern OOP _gst_abstract_namespace_class ATTRIBUTE_HIDDEN; extern OOP _gst_array_class ATTRIBUTE_HIDDEN; extern OOP _gst_arrayed_collection_class ATTRIBUTE_HIDDEN; extern OOP _gst_association_class ATTRIBUTE_HIDDEN; extern OOP _gst_behavior_class ATTRIBUTE_HIDDEN; extern OOP _gst_binding_dictionary_class ATTRIBUTE_HIDDEN; extern OOP _gst_block_closure_class ATTRIBUTE_HIDDEN; extern OOP _gst_block_context_class ATTRIBUTE_HIDDEN; extern OOP _gst_boolean_class ATTRIBUTE_HIDDEN; extern OOP _gst_byte_array_class ATTRIBUTE_HIDDEN; extern OOP _gst_c_callable_class ATTRIBUTE_HIDDEN; extern OOP _gst_c_func_descriptor_class ATTRIBUTE_HIDDEN; extern OOP _gst_c_callback_descriptor_class ATTRIBUTE_HIDDEN; extern OOP _gst_c_object_class ATTRIBUTE_HIDDEN; extern OOP _gst_c_object_type_ctype ATTRIBUTE_HIDDEN; extern OOP _gst_c_type_class ATTRIBUTE_HIDDEN; extern OOP _gst_callin_process_class ATTRIBUTE_HIDDEN; extern OOP _gst_char_class ATTRIBUTE_HIDDEN; extern OOP _gst_character_array_class ATTRIBUTE_HIDDEN; extern OOP _gst_class_class ATTRIBUTE_HIDDEN; extern OOP _gst_class_description_class ATTRIBUTE_HIDDEN; extern OOP _gst_collection_class ATTRIBUTE_HIDDEN; extern OOP _gst_compiled_block_class ATTRIBUTE_HIDDEN; extern OOP _gst_compiled_code_class ATTRIBUTE_HIDDEN; extern OOP _gst_compiled_method_class ATTRIBUTE_HIDDEN; extern OOP _gst_context_part_class ATTRIBUTE_HIDDEN; extern OOP _gst_continuation_class ATTRIBUTE_HIDDEN; extern OOP _gst_date_class ATTRIBUTE_HIDDEN; extern OOP _gst_deferred_variable_binding_class ATTRIBUTE_HIDDEN; extern OOP _gst_dictionary_class ATTRIBUTE_HIDDEN; extern OOP _gst_directed_message_class ATTRIBUTE_HIDDEN; extern OOP _gst_false_class ATTRIBUTE_HIDDEN; extern OOP _gst_file_descriptor_class ATTRIBUTE_HIDDEN; extern OOP _gst_file_segment_class ATTRIBUTE_HIDDEN; extern OOP _gst_file_stream_class ATTRIBUTE_HIDDEN; extern OOP _gst_float_class ATTRIBUTE_HIDDEN; extern OOP _gst_floatd_class ATTRIBUTE_HIDDEN; extern OOP _gst_floate_class ATTRIBUTE_HIDDEN; extern OOP _gst_floatq_class ATTRIBUTE_HIDDEN; extern OOP _gst_fraction_class ATTRIBUTE_HIDDEN; extern OOP _gst_hashed_collection_class ATTRIBUTE_HIDDEN; extern OOP _gst_homed_association_class ATTRIBUTE_HIDDEN; extern OOP _gst_identity_dictionary_class ATTRIBUTE_HIDDEN; extern OOP _gst_identity_set_class ATTRIBUTE_HIDDEN; extern OOP _gst_integer_class ATTRIBUTE_HIDDEN; extern OOP _gst_iterable_class ATTRIBUTE_HIDDEN; extern OOP _gst_interval_class ATTRIBUTE_HIDDEN; extern OOP _gst_large_integer_class ATTRIBUTE_HIDDEN; extern OOP _gst_large_negative_integer_class ATTRIBUTE_HIDDEN; extern OOP _gst_large_positive_integer_class ATTRIBUTE_HIDDEN; extern OOP _gst_large_zero_integer_class ATTRIBUTE_HIDDEN; extern OOP _gst_link_class ATTRIBUTE_HIDDEN; extern OOP _gst_linked_list_class ATTRIBUTE_HIDDEN; extern OOP _gst_lookup_key_class ATTRIBUTE_HIDDEN; extern OOP _gst_lookup_table_class ATTRIBUTE_HIDDEN; extern OOP _gst_magnitude_class ATTRIBUTE_HIDDEN; extern OOP _gst_memory_class ATTRIBUTE_HIDDEN; extern OOP _gst_message_class ATTRIBUTE_HIDDEN; extern OOP _gst_metaclass_class ATTRIBUTE_HIDDEN; extern OOP _gst_method_context_class ATTRIBUTE_HIDDEN; extern OOP _gst_method_dictionary_class ATTRIBUTE_HIDDEN; extern OOP _gst_method_info_class ATTRIBUTE_HIDDEN; extern OOP _gst_namespace_class ATTRIBUTE_HIDDEN; extern OOP _gst_number_class ATTRIBUTE_HIDDEN; extern OOP _gst_object_class ATTRIBUTE_HIDDEN; extern OOP _gst_object_memory_class ATTRIBUTE_HIDDEN; extern OOP _gst_ordered_collection_class ATTRIBUTE_HIDDEN; extern OOP _gst_permission_class ATTRIBUTE_HIDDEN; extern OOP _gst_positionable_stream_class ATTRIBUTE_HIDDEN; extern OOP _gst_process_class ATTRIBUTE_HIDDEN; extern OOP _gst_processor_scheduler_class ATTRIBUTE_HIDDEN; extern OOP _gst_read_stream_class ATTRIBUTE_HIDDEN; extern OOP _gst_read_write_stream_class ATTRIBUTE_HIDDEN; extern OOP _gst_root_namespace_class ATTRIBUTE_HIDDEN; extern OOP _gst_security_policy_class ATTRIBUTE_HIDDEN; extern OOP _gst_semaphore_class ATTRIBUTE_HIDDEN; extern OOP _gst_sequenceable_collection_class ATTRIBUTE_HIDDEN; extern OOP _gst_set_class ATTRIBUTE_HIDDEN; extern OOP _gst_small_integer_class ATTRIBUTE_HIDDEN; extern OOP _gst_smalltalk_dictionary ATTRIBUTE_HIDDEN; extern OOP _gst_sorted_collection_class ATTRIBUTE_HIDDEN; extern OOP _gst_stream_class ATTRIBUTE_HIDDEN; extern OOP _gst_string_class ATTRIBUTE_HIDDEN; extern OOP _gst_sym_link_class ATTRIBUTE_HIDDEN; extern OOP _gst_symbol_class ATTRIBUTE_HIDDEN; extern OOP _gst_system_dictionary_class ATTRIBUTE_HIDDEN; extern OOP _gst_time_class ATTRIBUTE_HIDDEN; extern OOP _gst_true_class ATTRIBUTE_HIDDEN; extern OOP _gst_undefined_object_class ATTRIBUTE_HIDDEN; extern OOP _gst_unicode_character_class ATTRIBUTE_HIDDEN; extern OOP _gst_unicode_string_class ATTRIBUTE_HIDDEN; extern OOP _gst_variable_binding_class ATTRIBUTE_HIDDEN; extern OOP _gst_weak_array_class ATTRIBUTE_HIDDEN; extern OOP _gst_weak_set_class ATTRIBUTE_HIDDEN; extern OOP _gst_weak_key_dictionary_class ATTRIBUTE_HIDDEN; extern OOP _gst_weak_value_lookup_table_class ATTRIBUTE_HIDDEN; extern OOP _gst_weak_identity_set_class ATTRIBUTE_HIDDEN; extern OOP _gst_weak_key_identity_dictionary_class ATTRIBUTE_HIDDEN; extern OOP _gst_weak_value_identity_dictionary_class ATTRIBUTE_HIDDEN; extern OOP _gst_write_stream_class ATTRIBUTE_HIDDEN; extern OOP _gst_processor_oop ATTRIBUTE_HIDDEN; /* The size of the indexed instance variables corresponding to the various instanceSpec values declared in gstpriv.h. */ extern signed char _gst_log2_sizes[32] ATTRIBUTE_HIDDEN; /* Creates a new instance of the Dictionary class with room for SIZE items. */ extern OOP _gst_dictionary_new (int size) ATTRIBUTE_HIDDEN; /* Creates a new instance of the BindingDictionary class with room for SIZE items. The object has the ENVIRONMENTOOP environment (which for dictionary of class variables is the class that hosts the dictionary). */ extern OOP _gst_binding_dictionary_new (int size, OOP environmentOOP) ATTRIBUTE_HIDDEN; /* Gets the method dictionary associated with CLASS_OOP, and returns it. If the methodDictionary associated with CLASS_OOP is nil, one is created and installed into that class. */ extern OOP _gst_valid_class_method_dictionary (OOP class_oop) ATTRIBUTE_HIDDEN; /* This returns the dictionary of class variables for CLASS_OOP */ extern OOP _gst_class_variable_dictionary (OOP class_oop) ATTRIBUTE_PURE ATTRIBUTE_HIDDEN; /* This finds the key SYMBOL into the dictionary POOLOOP and, if any, in all of its super-namespaces. Returns the association. */ extern OOP _gst_namespace_association_at (OOP poolOOP, OOP symbol) ATTRIBUTE_PURE ATTRIBUTE_HIDDEN; /* This finds the key SYMBOL into the dictionary POOLOOP and, if any, in all of its super-namespaces. Returns the value. */ extern OOP _gst_namespace_at (OOP poolOOP, OOP symbol) ATTRIBUTE_PURE ATTRIBUTE_HIDDEN; /* Adds the Association in ASSOCIATIONOOP to the Dictionary (or a subclass sharing the same representation) DICTIONARYOOP. */ extern OOP _gst_dictionary_add (OOP dictionaryOOP, OOP associationOOP) ATTRIBUTE_HIDDEN; /* Look for the value associated to KEYOOP in IDENTITYDICTIONARYOOP and answer it or, if not found, _gst_nil_oop. */ extern OOP _gst_identity_dictionary_at (OOP identityDictionaryOOP, OOP keyOOP) ATTRIBUTE_PURE ATTRIBUTE_HIDDEN; /* Creates a String object starting from the NUL-terminated string S. */ extern OOP _gst_string_new (const char *s) ATTRIBUTE_HIDDEN; /* Creates a String object starting from the NUL-terminated wide string S. */ extern OOP _gst_unicode_string_new (const wchar_t *s) ATTRIBUTE_HIDDEN; /* Look in the Smalltalk dictionary for a class whose name is in the Symbol CLASSNAMEOOP. */ extern OOP _gst_find_class (OOP classNameOOP) ATTRIBUTE_PURE ATTRIBUTE_HIDDEN; /* Look for an implementation of SELECTOR (a Symbol) into CLASS_OOP's method dictionary or in the method dictionary of a superclass. */ extern OOP _gst_find_class_method (OOP class_oop, OOP selector) ATTRIBUTE_PURE ATTRIBUTE_HIDDEN; /* Create a new Message object for the given SELECTOR (a Symbol) and Array of arguments. */ extern OOP _gst_message_new_args (OOP selectorOOP, OOP argsArray) ATTRIBUTE_HIDDEN; /* Returns the name of CLASS_OOP (a Smalltalk Class) */ extern OOP _gst_get_class_symbol (OOP class_oop) ATTRIBUTE_PURE ATTRIBUTE_HIDDEN; /* Create and return an exact copy of OOP, which can be any kind of OOP. Builtin OOPs and integers are returned unchanged, while for other objects this is a "shallow copy"; all the instance variables in the new object are the exact same ones that are in the original object. */ extern OOP _gst_object_copy (OOP oop) ATTRIBUTE_HIDDEN; /* Returns the array of the names of the instance variables of CLASS_OOP (a Smalltalk Class). */ extern OOP _gst_instance_variable_array (OOP class_oop) ATTRIBUTE_PURE ATTRIBUTE_HIDDEN; /* Returns the array of the names of the pool dictionaries of CLASS_OOP (a Smalltalk Class). */ extern OOP _gst_shared_pool_dictionary (OOP class_oop) ATTRIBUTE_PURE ATTRIBUTE_HIDDEN; /* Creates a new CObject pointing to cObjOfs bytes in BASEOOP (or at the absolute address cObjOfs if BASEOOP is NULL), extracting the class to be instantiated from the CType, TYPEOOP, or using the provided class if TYPEOOP is nil. */ extern OOP _gst_c_object_new_base (OOP baseOOP, uintptr_t cObjOfs, OOP typeOOP, OOP defaultClassOOP) ATTRIBUTE_HIDDEN; /* Creates a new String with LEN indexed instance variables. */ extern OOP _gst_new_string (size_t len) ATTRIBUTE_HIDDEN; /* Creates a new ByteArray containing LEN bytes starting at BYTES. */ extern OOP _gst_byte_array_new (const gst_uchar * bytes, size_t len) ATTRIBUTE_HIDDEN; /* Creates a new String containing LEN characters starting at S. */ extern OOP _gst_counted_string_new (const char *s, size_t len) ATTRIBUTE_HIDDEN; /* Adds the key KEYOOP, associated with VALUEOOP, to the IdentityDictionary (or a subclass sharing the same representation) IDENTITYDICTIONARYOOP. */ extern OOP _gst_identity_dictionary_at_put (OOP identityDictionaryOOP, OOP keyOOP, OOP valueOOP) ATTRIBUTE_HIDDEN; /* Called when a dictionary becomes full, this routine replaces the dictionary instance that DICTIONARYOOP is pointing to with a new, larger dictionary, and returns this new dictionary (the object pointer, not the OOP). */ extern gst_object _gst_grow_dictionary (OOP dictionaryOOP) ATTRIBUTE_HIDDEN; /* Called when an IdentityDictionary becomes full, this routine replaces the IdentityDictionary instance that IDENTITYDICTIONARYOOP is pointing to with a new, larger dictionary, and returns this new dictionary (the object pointer, not the OOP). */ extern gst_identity_dictionary _gst_grow_identity_dictionary (OOP identityDictionaryOOP) ATTRIBUTE_HIDDEN; /* Allocates and returns a new C (NULL-terminated) string that has the same contents as STRINGOOP. Even if there are embedded NULs, the allocated area has always a size of "stringOOP size + 1" bytes. */ extern char *_gst_to_cstring (OOP stringOOP) ATTRIBUTE_HIDDEN; /* Allocates and returns a new wide C string that has the same contents as STRINGOOP. Even if there are embedded NULs, the allocated area has always a size of "unicodeStringOOP size + 1" bytes. */ extern wchar_t *_gst_to_wide_cstring (OOP unicodeStringOOP) ATTRIBUTE_HIDDEN; /* Allocates and returns a new memory block that has the same contents as BYTEARRAYOOP. Even if there are embedded NULs, the allocated area has always a size of "byteArrayOOP size" bytes. */ extern gst_uchar *_gst_to_byte_array (OOP byteArrayOOP) ATTRIBUTE_HIDDEN; /* Creates the kernel classes of the Smalltalk system. Operates in two passes: pass1 creates the class objects, but they're not completely initialized. pass2 finishes the initialization process. The garbage collector can NOT run during this time. */ extern void _gst_init_dictionary (void) ATTRIBUTE_HIDDEN; /* Copies the first bytes of S into STRINGOOP (as many bytes as the OOP can hold). */ extern void _gst_set_oopstring (OOP stringOOP, const char *s) ATTRIBUTE_HIDDEN; /* Copies the first bytes of S into STRINGOOP (as many bytes as the OOP can hold). */ extern void _gst_set_oop_unicode_string (OOP stringOOP, const wchar_t *s) ATTRIBUTE_HIDDEN; /* Set the instance variables of the FileStream object, FILESTREAMOOP. If BUFFERED is true, the variables inherited by Streams are set to a 1024-bytes String. */ extern void _gst_set_file_stream_file (OOP fileStreamOOP, int fd, OOP fileNameOOP, mst_Boolean isPipe, int access, mst_Boolean buffered) ATTRIBUTE_HIDDEN; /* Copies the first bytes of BYTES into BYTEARRAYOOP (as many bytes as the OOP can hold). */ extern void _gst_set_oop_bytes (OOP byteArrayOOP, gst_uchar * bytes) ATTRIBUTE_HIDDEN; /* Frees the memory pointed to by the CObject, COBJOOP. */ extern void _gst_free_cobject (OOP cObjOOP) ATTRIBUTE_HIDDEN; /* Loads the contents of the global variables from the Smalltalk dictionary after an image has been restored. PRIM_TABLE_MATCHES if true if the table of primitives is already set up correctly. */ extern mst_Boolean _gst_init_dictionary_on_image_load (mst_Boolean prim_table_matches) ATTRIBUTE_HIDDEN; /* Transforms a primitive name into a primitive index, looking up the VMPrimitives dictionary. */ extern int _gst_resolve_primitive_name (char *name) ATTRIBUTE_HIDDEN; /* Entry point for the profiler. */ extern void _gst_record_profile (OOP oldMethod, OOP newMethod, int ipOffset) ATTRIBUTE_HIDDEN; #endif /* GST_DICT_H */ smalltalk-3.2.5/libgst/save.c0000644000175000017500000006615612130343734013032 00000000000000/******************************** -*- C -*- **************************** * * Binary image save/restore. * * ***********************************************************************/ /*********************************************************************** * * Copyright 1988,89,90,91,92,94,95,99,2000,2001,2002,2003,2005,2006,2007,2008 * Free Software Foundation, Inc. * Written by Steve Byrne. * * This file is part of GNU Smalltalk. * * GNU Smalltalk is free software; you can redistribute it and/or modify it * under the terms of the GNU General Public License as published by the Free * Software Foundation; either version 2, or (at your option) any later * version. * * Linking GNU Smalltalk statically or dynamically with other modules is * making a combined work based on GNU Smalltalk. Thus, the terms and * conditions of the GNU General Public License cover the whole * combination. * * In addition, as a special exception, the Free Software Foundation * give you permission to combine GNU Smalltalk with free software * programs or libraries that are released under the GNU LGPL and with * independent programs running under the GNU Smalltalk virtual machine. * * You may copy and distribute such a system following the terms of the * GNU GPL for GNU Smalltalk and the licenses of the other code * concerned, provided that you include the source code of that other * code when and as the GNU GPL requires distribution of source code. * * Note that people who make modified versions of GNU Smalltalk are not * obligated to grant this special exception for their modified * versions; it is their choice whether to do so. The GNU General * Public License gives permission to release a modified version without * this exception; this exception also makes it possible to release a * modified version which carries forward this exception. * * GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or * FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for * more details. * * You should have received a copy of the GNU General Public License along with * GNU Smalltalk; see the file COPYING. If not, write to the Free Software * Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * ***********************************************************************/ #include "gstpriv.h" #define READ_BUFFER_SIZE 524288 #define WRITE_BUFFER_SIZE 65536 /* These flags help defining the flags and checking whether they are different between the image we are loading and our environment. */ #define MASK_ENDIANNESS_FLAG 1 #define MASK_SLOT_SIZE_FLAG 2 #ifdef WORDS_BIGENDIAN # define LOCAL_ENDIANNESS_FLAG MASK_ENDIANNESS_FLAG #else # define LOCAL_ENDIANNESS_FLAG 0 #endif #if SIZEOF_OOP == 4 # define LOCAL_SLOT_SIZE_FLAG 0 #else /* SIZEOF_OOP == 8 */ # define LOCAL_SLOT_SIZE_FLAG MASK_SLOT_SIZE_FLAG #endif /* SIZEOF_OOP == 8 */ #define FLAG_CHANGED(flags, whichFlag) \ ((flags ^ LOCAL_##whichFlag) & MASK_##whichFlag) #define FLAGS_WRITTEN \ (LOCAL_ENDIANNESS_FLAG | LOCAL_SLOT_SIZE_FLAG) #define VERSION_REQUIRED \ ((ST_MAJOR_VERSION << 16) + (ST_MINOR_VERSION << 8) + ST_EDIT_VERSION) /* Define to print loads of debugging information. */ /* #define SNAPSHOT_TRACE */ /* The binary image file has the following format: header complete oop table global oop variable data object data */ #define EXECUTE "#! /usr/bin/env gst -aI\nexec gst -I \"$0\" -a \"$@\"\n" #define SIGNATURE "GSTIm" typedef struct save_file_header { char dummy[64]; /* Bourne shell command to execute image */ char signature[6]; /* 6+2=8 should be enough to align version! */ char unused; char flags; /* flags for endianness and sizeof(PTR) */ size_t version; /* the Smalltalk version that made this dump */ size_t oopTableSize; /* size of the oop table at dump */ size_t edenSpaceSize; /* size of new space at dump time */ size_t survSpaceSize; /* size of survivor spaces at dump time */ size_t oldSpaceSize; /* size of old space at dump time */ size_t big_object_threshold; size_t grow_threshold_percent; size_t space_grow_rate; size_t num_free_oops; intptr_t ot_base; intptr_t prim_table_md5[16 / sizeof (intptr_t)]; /* checksum for the primitive table */ } save_file_header; /* The buffer that we use for I/O. */ static char *buf; /* The position in the buffer. */ static int buf_pos; /* The size of the buffer. */ static int buf_size; /* The size of the input file (for buffered input only). */ static off_t file_size; /* The current position in the file (for buffered input only). */ static off_t file_pos; /* Whether we are using mmap to read the file. */ static mst_Boolean buf_used_mmap; /* This function tries to write SIZE bytes to FD starting at BUFFER, and longjmps out of SAVE_JMPBUF if something goes wrong. */ static void full_write (int fd, PTR buffer, size_t size); /* This function establishes a buffer of size NUMBYTES for writes. */ static void buffer_write_init (int imageFd, int numBytes); /* This function flushes and frees the buffer used for writes. */ static void buffer_write_flush (int imageFd); /* This function buffers writes to the image file whose descriptor is IMAGEFD. */ static void buffer_write (int imageFd, PTR data, int numBytes); /* This function establishes a buffer of size NUMBYTES for reads. The base of the buffer is returned if mmap was used. */ static char *buffer_read_init (int imageFd, int numBytes); /* This function frees the buffer used for reads. */ static void buffer_read_free (int imageFd); /* This function, which only works if memory-mapped I/O is used, advances the buffer pointer by NUMBYTES and returns the pointer to the previous value of the buffer pointer. */ static inline PTR buffer_advance (int imageFd, int numBytes); /* This function buffers reads from the image file whose descriptor is IMAGEFD. Memory-mapped I/O is used is possible. */ static void buffer_read (int imageFd, PTR data, int numBytes); /* This function fills the buffer used by buffer_read. It is used internally by buffer_read. */ static void buffer_fill (int imageFd); /* This function saves the object pointed to by OOP on the image-file whose descriptor is IMAGEFD. */ static void save_object (int imageFd, OOP oop); /* This function copies NUMBYTES from SRC to DEST, tweaking some fields depending on the class. */ static inline void fixup_object (OOP oop, gst_object dest, gst_object src, int numBytes); /* This function inverts the endianness of SIZE long-words, starting at BUF. */ static inline void fixup_byte_order (PTR buf, size_t size); /* This function loads an OOP table made of OLDSLOTSUSED slots from the image file stored in the file whose descriptor is IMAGEFD. The fixup gets handled by load_normal_oops. */ static void load_oop_table (int imageFd); /* This function loads OBJECTDATASIZE bytes of object data belonging to standard (i.e. non built-in OOPs) and fixes the endianness of the objects. Endianness conversion is done in two steps: first the non-byte objects (identified by not having the F_BYTE flag), including the class objects which are necessary to fix the byte objects, then all the byte-objects which also have instance variables). Object data is loaded from the IMAGEFD file descriptor. If copy-on-write is used, return the end address of the loaded data. */ static char *load_normal_oops (int imageFd); /* Do the bulk of the save to IMAGEFD. Calling the hooks and reporting errors is left to the callers. */ static void save_to_fd (int imageFd); /* This function stores the header, HEADERP, of the image file into the file whose descriptor is IMAGEFD. */ static void save_file_version (int imageFd, struct save_file_header *headerp); /* This function loads into HEADERP the header of the image file without checking its validity. This data is loaded from the IMAGEFD file descriptor. */ static mst_Boolean load_file_version (int imageFd, save_file_header * headerp); /* This function walks the OOP table and adjusts all the OOP addresses, to account for the difference between the OOP table address at save time and now. */ static inline void restore_all_pointer_slots (void); /* This and adjusts all the addresses in OOPto account for the difference between the OOP table address at save time and now. */ static inline void restore_oop_pointer_slots (OOP oop); /* This function prepares the OOP table to be written to the image file. This contains the object sizes instead of the pointers, since addresses will be recalculated upon load. */ static struct oop_s *make_oop_table_to_be_saved (struct save_file_header *hdr); /* This function walks the OOP table and saves the data onto the file whose descriptor is IMAGEFD. */ static void save_all_objects (int imageFd); /* This function is the heart of _gst_load_from_file, which opens the file and then passes the descriptor to load_snapshot into IMAGEFD. */ static mst_Boolean load_snapshot (int imageFd); /* This variable says whether the image we are loading has the wrong endianness. */ static mst_Boolean wrong_endianness; /* This variable contains the OOP slot index of the highest non-free OOP, excluding the built-in ones (i.e., it will always be < _gst_mem.ot_size). This is used for optimizing the size of the saved image, and minimizing the load time when restoring the system. */ static int num_used_oops = 0; /* Delta from the object table address used in the saved image, and the one we allocate now. */ static intptr_t ot_delta; /* Used when writing the image fails. */ static jmp_buf save_jmpbuf; /* Convert from relative offset to actual oop table address. */ #define OOP_ABSOLUTE(obj) \ ( (OOP)((intptr_t)(obj) + ot_delta) ) struct oop_s *myOOPTable = NULL; mst_Boolean _gst_save_to_file (const char *fileName) { int imageFd; int save_errno; mst_Boolean success; _gst_invoke_hook (GST_ABOUT_TO_SNAPSHOT); _gst_global_gc (0); _gst_finish_incremental_gc (); success = false; unlink (fileName); imageFd = _gst_open_file (fileName, "w"); if (imageFd >= 0) { if (setjmp(save_jmpbuf) == 0) { save_to_fd (imageFd); success = true; } save_errno = errno; close (imageFd); if (!success) unlink (fileName); if (myOOPTable) xfree (myOOPTable); myOOPTable = NULL; } else save_errno = errno; _gst_invoke_hook (GST_FINISHED_SNAPSHOT); errno = save_errno; return success; } void save_to_fd (int imageFd) { save_file_header header; memset (&header, 0, sizeof (header)); myOOPTable = make_oop_table_to_be_saved (&header); buffer_write_init (imageFd, WRITE_BUFFER_SIZE); save_file_version (imageFd, &header); #ifdef SNAPSHOT_TRACE printf ("After saving header: %lld\n", lseek (imageFd, 0, SEEK_CUR)); #endif /* SNAPSHOT_TRACE */ /* save up to the last oop slot in use */ buffer_write (imageFd, myOOPTable, sizeof (struct oop_s) * num_used_oops); #ifdef SNAPSHOT_TRACE printf ("After saving oop table: %lld\n", lseek (imageFd, 0, SEEK_CUR)); #endif /* SNAPSHOT_TRACE */ xfree (myOOPTable); myOOPTable = NULL; save_all_objects (imageFd); #ifdef SNAPSHOT_TRACE printf ("After saving all objects: %lld\n", lseek (imageFd, 0, SEEK_CUR)); #endif /* SNAPSHOT_TRACE */ buffer_write_flush (imageFd); } struct oop_s * make_oop_table_to_be_saved (struct save_file_header *header) { OOP oop; struct oop_s *myOOPTable; int i; num_used_oops = 0; for (oop = _gst_mem.ot; oop < &_gst_mem.ot[_gst_mem.ot_size]; oop++) if (IS_OOP_VALID_GC (oop)) num_used_oops = OOP_INDEX (oop) + 1; _gst_mem.num_free_oops = _gst_mem.ot_size - num_used_oops; #ifdef SNAPSHOT_TRACE printf ("there are %d free oops out of %d oops, leaving %d\n", _gst_mem.num_free_oops, _gst_mem.ot_size, _gst_mem.ot_size - _gst_mem.num_free_oops); #endif /* SNAPSHOT_TRACE */ myOOPTable = xmalloc (sizeof (struct oop_s) * num_used_oops); for (i = 0, oop = _gst_mem.ot; i < num_used_oops; oop++, i++) { if (IS_OOP_VALID_GC (oop)) { int numPointers = NUM_OOPS (oop->object); myOOPTable[i].flags = (oop->flags & ~F_RUNTIME) | F_OLD; /* Cache the number of indexed instance variables. We prefer to do more work upon saving (done once) than upon loading (done many times). */ if (numPointers < (F_COUNT >> F_COUNT_SHIFT)) myOOPTable[i].flags |= numPointers << F_COUNT_SHIFT; else myOOPTable[i].flags |= F_COUNT; myOOPTable[i].object = (gst_object) TO_INT (oop->object->objSize); } else { myOOPTable[i].flags = 0; header->num_free_oops++; } } return (myOOPTable); } void save_all_objects (int imageFd) { OOP oop; for (oop = _gst_mem.ot; oop < &_gst_mem.ot[num_used_oops]; oop++) if (IS_OOP_VALID_GC (oop)) save_object (imageFd, oop); } void save_object (int imageFd, OOP oop) { gst_object object, saveObject; int numBytes; #ifdef SNAPSHOT_TRACE printf (">Save "); _gst_display_oop (oop); #endif object = OOP_TO_OBJ (oop); if (IS_OOP_FREE (oop)) abort (); numBytes = sizeof (OOP) * TO_INT (object->objSize); if (numBytes < 262144) { saveObject = alloca (numBytes); fixup_object (oop, saveObject, object, numBytes); buffer_write (imageFd, saveObject, numBytes); } else { saveObject = malloc (numBytes); fixup_object (oop, saveObject, object, numBytes); buffer_write (imageFd, saveObject, numBytes); free (saveObject); } } void save_file_version (int imageFd, struct save_file_header *headerp) { memcpy (headerp->dummy, EXECUTE, strlen (EXECUTE)); memcpy (headerp->signature, SIGNATURE, strlen (SIGNATURE)); headerp->flags = FLAGS_WRITTEN; headerp->version = VERSION_REQUIRED; headerp->oopTableSize = num_used_oops; headerp->edenSpaceSize = _gst_mem.eden.totalSize; headerp->survSpaceSize = _gst_mem.surv[0].totalSize; headerp->oldSpaceSize = _gst_mem.old->heap_limit; headerp->big_object_threshold = _gst_mem.big_object_threshold; headerp->grow_threshold_percent = _gst_mem.grow_threshold_percent; headerp->space_grow_rate = _gst_mem.space_grow_rate; headerp->ot_base = (intptr_t) _gst_mem.ot_base; memcpy (&headerp->prim_table_md5, _gst_primitives_md5, sizeof (_gst_primitives_md5)); buffer_write (imageFd, headerp, sizeof (save_file_header)); } /*********************************************************************** * * Binary loading routines. * ***********************************************************************/ mst_Boolean _gst_load_from_file (const char *fileName) { mst_Boolean loaded = 0; int imageFd; imageFd = _gst_open_file (fileName, "r"); loaded = (imageFd >= 0) && load_snapshot (imageFd); close (imageFd); return (loaded); } mst_Boolean load_snapshot (int imageFd) { save_file_header header; int prim_table_matches; char *base, *end; base = buffer_read_init (imageFd, READ_BUFFER_SIZE); if (!load_file_version (imageFd, &header)) return false; #ifdef SNAPSHOT_TRACE printf ("After loading header: %lld\n", file_pos + buf_pos); #endif /* SNAPSHOT_TRACE */ _gst_init_mem (header.edenSpaceSize, header.survSpaceSize, header.oldSpaceSize, header.big_object_threshold, header.grow_threshold_percent, header.space_grow_rate); _gst_init_oop_table ((PTR) header.ot_base, MAX (header.oopTableSize * 2, INITIAL_OOP_TABLE_SIZE)); ot_delta = (intptr_t) (_gst_mem.ot_base) - header.ot_base; num_used_oops = header.oopTableSize; _gst_mem.num_free_oops = header.num_free_oops; load_oop_table (imageFd); #ifdef SNAPSHOT_TRACE printf ("After loading OOP table: %lld\n", file_pos + buf_pos); #endif /* SNAPSHOT_TRACE */ end = load_normal_oops (imageFd); if (end) { _gst_mem.loaded_base = (OOP *) base; _gst_mem.loaded_end = (OOP *) end; } #ifdef SNAPSHOT_TRACE printf ("After loading objects: %lld\n", file_pos + buf_pos); #endif /* SNAPSHOT_TRACE */ if (ot_delta) restore_all_pointer_slots (); prim_table_matches = !memcmp (header.prim_table_md5, _gst_primitives_md5, sizeof (_gst_primitives_md5)); if (_gst_init_dictionary_on_image_load (prim_table_matches)) { #ifdef SNAPSHOT_TRACE _gst_dump_oop_table (); #endif /* SNAPSHOT_TRACE */ return (true); } return (false); } mst_Boolean load_file_version (int imageFd, save_file_header * headerp) { buffer_read (imageFd, headerp, sizeof (save_file_header)); if (strcmp (headerp->signature, SIGNATURE)) return (false); /* different sizeof(PTR) not supported */ if (FLAG_CHANGED (headerp->flags, SLOT_SIZE_FLAG)) return (false); if UNCOMMON ((wrong_endianness = FLAG_CHANGED (headerp->flags, ENDIANNESS_FLAG))) { headerp->oopTableSize = BYTE_INVERT (headerp->oopTableSize); headerp->edenSpaceSize = BYTE_INVERT (headerp->edenSpaceSize); headerp->survSpaceSize = BYTE_INVERT (headerp->survSpaceSize); headerp->oldSpaceSize = BYTE_INVERT (headerp->oldSpaceSize); headerp->big_object_threshold = BYTE_INVERT (headerp->big_object_threshold); headerp->grow_threshold_percent = BYTE_INVERT (headerp->grow_threshold_percent); headerp->space_grow_rate = BYTE_INVERT (headerp->space_grow_rate); headerp->version = BYTE_INVERT (headerp->version); headerp->num_free_oops = BYTE_INVERT (headerp->num_free_oops); headerp->ot_base = BYTE_INVERT (headerp->ot_base); headerp->prim_table_md5[0] = BYTE_INVERT (headerp->prim_table_md5[0]); headerp->prim_table_md5[1] = BYTE_INVERT (headerp->prim_table_md5[1]); #if SIZEOF_OOP == 4 headerp->prim_table_md5[2] = BYTE_INVERT (headerp->prim_table_md5[2]); headerp->prim_table_md5[3] = BYTE_INVERT (headerp->prim_table_md5[3]); #endif } /* check for version mismatch; if so this image file is invalid */ if (headerp->version > VERSION_REQUIRED) return (false); return (true); } void load_oop_table (int imageFd) { /* Load in the valid OOP slots from previous dump. The others are already initialized to free (0). */ buffer_read (imageFd, _gst_mem.ot, sizeof (struct oop_s) * num_used_oops); if UNCOMMON (wrong_endianness) fixup_byte_order (_gst_mem.ot, sizeof (struct oop_s) * num_used_oops / sizeof (PTR)); } char * load_normal_oops (int imageFd) { OOP oop; int i; gst_object object = NULL; size_t size = 0; mst_Boolean use_copy_on_write = #ifdef NO_SIGSEGV_HANDLING 0 && #endif buf_used_mmap && ~wrong_endianness && ot_delta == 0; /* Now walk the oop table. Load the data (or get the addresses from the mmap-ed area) and fix the byte order. */ _gst_mem.last_allocated_oop = &_gst_mem.ot[num_used_oops - 1]; PREFETCH_START (_gst_mem.ot, PREF_WRITE | PREF_NTA); for (oop = _gst_mem.ot, i = num_used_oops; i--; oop++) { intptr_t flags; PREFETCH_LOOP (oop, PREF_WRITE | PREF_NTA); flags = oop->flags; if (IS_OOP_FREE (oop)) continue; /* FIXME: a small amount of garbage is saved that is produced by mourning the ephemerons right before GC. We should probably put the objects to be mourned into a global list and walk it with a separate, *global* function _gst_mourn_objects(). This way we could save the objects before their mourning (which would happen on the image load) and before there is the occasion to create new-space objects. The solution is not however as neat as possible. */ _gst_mem.numOldOOPs++; size = sizeof (PTR) * (size_t) oop->object; if (use_copy_on_write) { oop->flags |= F_LOADED; object = buffer_advance (imageFd, size); } else { if (flags & F_FIXED) { _gst_mem.numFixedOOPs++; object = (gst_object) _gst_mem_alloc (_gst_mem.fixed, size); } else object = (gst_object) _gst_mem_alloc (_gst_mem.old, size); buffer_read (imageFd, object, size); if UNCOMMON (wrong_endianness) fixup_byte_order (object, (flags & F_BYTE) ? OBJ_HEADER_SIZE_WORDS : size / sizeof (PTR)); /* Would be nice, but causes us to touch every page and lose most of the startup-time benefits of copy-on-write. So we only do it in the slow case, anyway. */ if (object->objSize != FROM_INT ((size_t) oop->object)) abort (); } oop->object = object; if (flags & F_WEAK) _gst_make_oop_weak (oop); } /* NUM_OOPS requires access to the instance spec in the class objects. So we start by fixing the endianness of NON-BYTE objects (including classes!), for which we can do without NUM_OOPS, then do another pass here and fix the byte objects using the now correct class objects. */ if UNCOMMON (wrong_endianness) for (oop = _gst_mem.ot, i = num_used_oops; i--; oop++) if (oop->flags & F_BYTE) { OOP classOOP; object = OOP_TO_OBJ (oop); classOOP = OOP_ABSOLUTE (object->objClass); fixup_byte_order (object->data, CLASS_FIXED_FIELDS (classOOP)); } if (!use_copy_on_write) { buffer_read_free (imageFd); return NULL; } else return ((char *)object) + size; } /* Routines to convert to/from relative pointers, shared by loading and saving */ void fixup_object (OOP oop, gst_object dest, gst_object src, int numBytes) { OOP class_oop; memcpy (dest, src, numBytes); /* Do the heavy work on the objects now rather than at load time, in order to make the loading faster. In general, we should do this as little as possible, because it's pretty hard: the three cases below for Process, Semaphore and CallinProcess for example are just there to terminate all CallinProcess objects. */ class_oop = src->objClass; if (oop->flags & F_CONTEXT) { /* this is another quirk; this is not the best place to do it. We have to reset the nativeIPs so that we can find restarted processes and recompile their methods. */ gst_method_context context = (gst_method_context) dest; context->native_ip = DUMMY_NATIVE_IP; } else if (class_oop == _gst_callin_process_class) { gst_process process = (gst_process) dest; process->suspendedContext = _gst_nil_oop; process->nextLink = _gst_nil_oop; process->myList = _gst_nil_oop; } else if (class_oop == _gst_process_class) { /* Find the new next link. */ gst_process destProcess = (gst_process) dest; gst_process next = (gst_process) src; while (OOP_CLASS (next->nextLink) == _gst_callin_process_class) next = (gst_process) OOP_TO_OBJ (next->nextLink); destProcess->nextLink = next->nextLink; } else if (class_oop == _gst_semaphore_class) { /* Find the new first and last link. */ gst_semaphore destSem = (gst_semaphore) dest; gst_semaphore srcSem = (gst_semaphore) src; OOP linkOOP = srcSem->firstLink; destSem->firstLink = _gst_nil_oop; destSem->lastLink = _gst_nil_oop; while (!IS_NIL (linkOOP)) { gst_process process = (gst_process) OOP_TO_OBJ (linkOOP); if (process->objClass != _gst_callin_process_class) { if (IS_NIL (destSem->firstLink)) destSem->firstLink = linkOOP; destSem->lastLink = linkOOP; } linkOOP = process->nextLink; } } /* File descriptors are invalidated on resume. */ else if (is_a_kind_of (class_oop, _gst_file_descriptor_class)) { gst_file_stream file = (gst_file_stream) dest; file->fd = _gst_nil_oop; } /* The other case is to reset CFunctionDescriptor objects, so that we'll relink the external functions when we reload the image. */ else if (is_a_kind_of (class_oop, _gst_c_callable_class)) { gst_c_callable desc = (gst_c_callable) dest; if (desc->storageOOP == _gst_nil_oop) SET_COBJECT_OFFSET_OBJ (desc, 0); } } void restore_all_pointer_slots () { OOP oop; for (oop = _gst_mem.ot; oop < &_gst_mem.ot[num_used_oops]; oop++) if (IS_OOP_VALID_GC (oop)) restore_oop_pointer_slots (oop); } void restore_oop_pointer_slots (OOP oop) { int numPointers; gst_object object; OOP *i; object = OOP_TO_OBJ (oop); object->objClass = OOP_ABSOLUTE (object->objClass); if UNCOMMON ((oop->flags & F_COUNT) == F_COUNT) numPointers = NUM_OOPS (object); else numPointers = oop->flags >> F_COUNT_SHIFT; for (i = object->data; numPointers--; i++) if (IS_OOP (*i)) *i = OOP_ABSOLUTE (*i); } void fixup_byte_order (PTR buf, size_t size) { uintptr_t *p = (uintptr_t *) buf; for (; size--; p++) *p = BYTE_INVERT (*p); } void buffer_write_init (int imageFd, int numBytes) { buf = xmalloc (numBytes); buf_size = numBytes; buf_pos = 0; } void full_write (int fd, PTR buffer, size_t size) { char *buf = (char *) buffer; ssize_t num = SSIZE_MAX; for (; num > 0 && size; buf += num, size -= num) num = _gst_write (fd, buf, size); if (num == 0) { errno = ENOSPC; num = -1; } if (num == -1) longjmp(save_jmpbuf, 1); } void buffer_write_flush (int imageFd) { full_write (imageFd, buf, buf_pos); xfree (buf); buf_pos = 0; } void buffer_write (int imageFd, PTR data, int numBytes) { if UNCOMMON (buf_pos + numBytes > buf_size) { full_write (imageFd, buf, buf_pos); buf_pos = 0; } if UNCOMMON (numBytes > buf_size) full_write (imageFd, data, numBytes); else { memcpy (buf + buf_pos, data, numBytes); buf_pos += numBytes; } } void buffer_fill (int imageFd) { buf_pos = 0; read (imageFd, buf, buf_size); } char * buffer_read_init (int imageFd, int numBytes) { struct stat st; fstat (imageFd, &st); file_size = st.st_size; file_pos = 0; #ifndef WIN32 #ifdef NO_SIGSEGV_HANDLING buf = mmap (NULL, file_size, PROT_READ|PROT_WRITE, MAP_PRIVATE, imageFd, 0); #else buf = mmap (NULL, file_size, PROT_READ, MAP_PRIVATE, imageFd, 0); #endif if (buf != (PTR) -1) { buf_size = file_size; buf_used_mmap = true; return buf; } #endif /* !WIN32 */ /* Non-mmaped input. */ buf_used_mmap = false; buf_size = numBytes; buf = xmalloc (buf_size); buffer_fill (imageFd); return NULL; } void buffer_read_free (int imageFd) { if (buf_used_mmap) _gst_osmem_free (buf, buf_size); else xfree (buf); } PTR buffer_advance (int imageFd, int numBytes) { PTR current_pos = buf + buf_pos; buf_pos += numBytes; return current_pos; } void buffer_read (int imageFd, PTR pdata, int numBytes) { char *data = (char *) pdata; if UNCOMMON (numBytes > buf_size - buf_pos) { memcpy (data, buf + buf_pos, buf_size - buf_pos); data += buf_size - buf_pos; numBytes -= buf_size - buf_pos; file_pos += buf_size; if (numBytes > buf_size) { lseek (imageFd, file_pos, SEEK_SET); read (imageFd, data, numBytes & -buf_size); file_pos += numBytes & -buf_size; data += numBytes & -buf_size; numBytes -= numBytes & -buf_size; } /* else fill in the buffer and load the rest */ buffer_fill (imageFd); } memcpy (data, buf + buf_pos, numBytes); buf_pos += numBytes; } smalltalk-3.2.5/libgst/genpr-parse.y0000644000175000017500000002262712123404352014334 00000000000000/******************************** -*- C -*- **************************** * * GNU Smalltalk genprims tool * ***********************************************************************/ /*********************************************************************** * * Copyright 2002, 2006, 2008, 2009 Free Software Foundation, Inc. * Written by Paolo Bonzini. * * This file is part of GNU Smalltalk. * * GNU Smalltalk is free software; you can redistribute it and/or modify it * under the terms of the GNU General Public License as published by the Free * Software Foundation; either version 2, or (at your option) any later * version. * * Linking GNU Smalltalk statically or dynamically with other modules is * making a combined work based on GNU Smalltalk. Thus, the terms and * conditions of the GNU General Public License cover the whole * combination. * * In addition, as a special exception, the Free Software Foundation * give you permission to combine GNU Smalltalk with free software * programs or libraries that are released under the GNU LGPL and with * independent programs running under the GNU Smalltalk virtual machine. * * You may copy and distribute such a system following the terms of the * GNU GPL for GNU Smalltalk and the licenses of the other code * concerned, provided that you include the source code of that other * code when and as the GNU GPL requires distribution of source code. * * Note that people who make modified versions of GNU Smalltalk are not * obligated to grant this special exception for their modified * versions; it is their choice whether to do so. The GNU General * Public License gives permission to release a modified version without * this exception; this exception also makes it possible to release a * modified version which carries forward this exception. * * GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or * FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for * more details. * * You should have received a copy of the GNU General Public License along with * GNU Smalltalk; see the file COPYING. If not, write to the Free Software * Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * ***********************************************************************/ %{ #include "genprims.h" #include "md5.h" /* This program finds declarations of the form: primitive NAME[ATTRS] or primitive NAME : prim_id NAME[ATTRS], prim_id NAME[ATTRS], prim_id NAME[ATTRS] and creates a function for each primitive declaration, and an entry in _gst_init_primitives for each prim_id declaration (note that the former is just a shorthand for primitive NAME : prim_id NAME[ATTRS] and so creates both the function and an entry). The brackets are literal [ and ], and the name can be an identifier or ID = NUMBER, in which case the id that is given to the primitive is set by the programmer (this is usually done for primitives inlined by the JIT compiler). In addition, the C code is examined to see instances of expressions like prim_id(NAME), which are replaced with the identifier given (either manually or automatically) to the named primitive. Everything else is copied verbatim to the output stream. */ #define YYERROR_VERBOSE 1 static void yyerror (const char *s); static void gen_proto (const char *s); static void gen_prim_decl (const char *s); static void gen_prim_id (const char *name, int id, const char *attrs); static int lookup_prim_id (const char *s); static void free_data (); static void output (); static char *strtoupper (char *s); #define YYPRINT(fp, tok, val) fprintf (fp, "%s", val); Filament *proto_fil, *stmt_fil, *def_fil, *literal_fil; typedef struct string_list { char *name; int id; struct string_list *next; } string_list; static char *current_func_name; static int prim_no; static int current_id; static int errors; static string_list *current_ids; #define NOT_FOUND INT_MIN %} %debug %defines %union { Filament *fil; char *text; int id; } /* single definite characters */ %token PRIMITIVE "primitive" %token PRIM_ID "prim_id" %token NUMBER "number" %token ID "identifier" %token '[' ']' '(' ')' '{' '}' ',' '=' ':' %token LITERAL WSPACE %type primitive_attrs prim_id_decl %type primitive_attr_list %type primitive_number %type prim_id_ref %% input: input primitive_decl '{' { filprintf (stmt_fil, "#line %d \"prims.def\"\n{", yylineno); } body '}' { free_data (); } | /* empty */ { } ; primitive_decl: PRIMITIVE ID { current_id = 0; current_func_name = strdup ($2); gen_proto ($2); gen_prim_decl ($2); } primitive_decl_2 { } ; primitive_decl_2: primitive_number primitive_attrs { gen_prim_id (current_func_name, $1, $2); free ($2); } | ':' prim_id_decls { } ; primitive_number: '=' NUMBER { $$ = strtoul ($2, NULL, 10); } | /* empty */ { $$ = current_id--; } ; primitive_attrs: '[' primitive_attr_list ']' { $$ = fildelete ($2); strtoupper ($$); } ; primitive_attr_list: ID { $$ = filnew ("PRIM_", 5); filcat ($$, $1); } | primitive_attr_list ',' ID { $$ = $1; filcat ($$, " | PRIM_"); filcat ($$, $3); } ; prim_id_decls: prim_id_decls ',' prim_id_decl { } | prim_id_decl { } ; prim_id_decl: PRIM_ID ID { $$ = strdup($2); } primitive_number primitive_attrs { gen_prim_id ($3, $4, $5); free ($3); free ($5); } ; body: body prim_id_ref { filprintf (stmt_fil, "%d", $2); } | /* empty */ ; prim_id_ref: PRIM_ID '(' ID { $$ = lookup_prim_id ($3); if ($$ == NOT_FOUND) yyerror ("Invalid primitive id"); } ')' { $$ = $4; literal_fil = stmt_fil; } ; %% void yyerror (const char *s) { errors = 1; fprintf (stderr, "prims.def:%d: %s\n", yylineno, s); } int filprintf (Filament *fil, const char *format, ...) { va_list ap; STREAM *out = stream_new (fil, SNV_UNLIMITED, NULL, snv_filputc); int result; va_start (ap, format); result = stream_vprintf (out, format, ap); va_end (ap); stream_delete (out); return result; } void gen_proto (const char *s) { filprintf (proto_fil, "static intptr_t\n" "%s (int id ATTRIBUTE_UNUSED,\n" "%*svolatile int numArgs ATTRIBUTE_UNUSED);\n\n", s, 2 + strlen(s), ""); } static void gen_prim_decl (const char *s) { filprintf (stmt_fil, "intptr_t\n" "%s (int id,\n" "%*svolatile int numArgs)\n", s, 2 + strlen(s), ""); } char * strtoupper (char *s) { char *base = s; while (*s) *s = toupper (*s), s++; return base; } void gen_prim_id (const char *name, int id, const char *attrs) { string_list *node; node = (string_list *) malloc (sizeof (string_list)); node->name = strdup (name); node->id = id; node->next = current_ids; current_ids = node; prim_no++; filprintf (def_fil, " _gst_default_primitive_table[%d].name = \"%s\";\n" " _gst_default_primitive_table[%d].attributes = %s;\n" " _gst_default_primitive_table[%d].id = %d;\n" " _gst_default_primitive_table[%d].func = %s;\n", prim_no, name, prim_no, attrs, prim_no, id, prim_no, current_func_name); } int lookup_prim_id (const char *s) { string_list *node; for (node = current_ids; node && strcmp (s, node->name); node = node->next); return node ? node->id : NOT_FOUND; } void free_data () { string_list *first, *next; if (current_func_name) free (current_func_name); for (first = current_ids; first; first = next) { next = first->next; free (first->name); free (first); } current_ids = NULL; } void output() { char *proto, *stmt, *def; unsigned char md5[16]; gen_proto ("VMpr_HOLE"); proto = fildelete (proto_fil); stmt = fildelete (stmt_fil); def = fildelete (def_fil); md5_buffer (def, strlen (def), md5); printf ("%s\n" "%s\n" "intptr_t\n" "VMpr_HOLE (int id,\n" " volatile int numArgs)\n" "{\n" " _gst_primitives_executed++;\n" " _gst_errorf (\"Unhandled primitive operation %%d\", id);\n" "\n" " UNPOP (numArgs);\n" " PRIM_FAILED;\n" "}\n" "\n" "unsigned char\n" "_gst_primitives_md5[16] = { %d, %d, %d, %d, %d, %d, %d, %d,\n" " %d, %d, %d, %d, %d, %d, %d, %d };\n" "\n" "void\n" "_gst_init_primitives()\n" "{\n" " int i;\n" "%s" "\n" " for (i = %d; i < NUM_PRIMITIVES; i++)\n" " {\n" " _gst_default_primitive_table[i].name = NULL;\n" " _gst_default_primitive_table[i].attributes = PRIM_FAIL;\n" " _gst_default_primitive_table[i].id = i;\n" " _gst_default_primitive_table[i].func = VMpr_HOLE;\n" " }\n" "}\n" "\n", proto, stmt, md5[0], md5[1], md5[2], md5[3], md5[4], md5[5], md5[6], md5[7], md5[8], md5[9], md5[10], md5[11], md5[12], md5[13], md5[14], md5[15], def, prim_no + 1); free (proto); free (stmt); free (def); } int main () { proto_fil = filnew (NULL, 0); stmt_fil = filnew (NULL, 0); def_fil = filnew (NULL, 0); literal_fil = proto_fil; errors = 0; if (yyparse () || errors) exit (1); output (); exit (0); } smalltalk-3.2.5/libgst/genbc-scan.l0000644000175000017500000002043212123404352014064 00000000000000/******************************** -*- C -*- **************************** * * GNU Smalltalk genbc tool - lexical analyzer * ***********************************************************************/ /*********************************************************************** * * Copyright 2003, 2006 Free Software Foundation, Inc. * Written by Paolo Bonzini. * * This file is part of GNU Smalltalk. * * GNU Smalltalk is free software; you can redistribute it and/or modify it * under the terms of the GNU General Public License as published by the Free * Software Foundation; either version 2, or (at your option) any later * version. * * Linking GNU Smalltalk statically or dynamically with other modules is * making a combined work based on GNU Smalltalk. Thus, the terms and * conditions of the GNU General Public License cover the whole * combination. * * In addition, as a special exception, the Free Software Foundation * give you permission to combine GNU Smalltalk with free software * programs or libraries that are released under the GNU LGPL and with * independent programs running under the GNU Smalltalk virtual machine. * * You may copy and distribute such a system following the terms of the * GNU GPL for GNU Smalltalk and the licenses of the other code * concerned, provided that you include the source code of that other * code when and as the GNU GPL requires distribution of source code. * * Note that people who make modified versions of GNU Smalltalk are not * obligated to grant this special exception for their modified * versions; it is their choice whether to do so. The GNU General * Public License gives permission to release a modified version without * this exception; this exception also makes it possible to release a * modified version which carries forward this exception. * * GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or * FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for * more details. * * You should have received a copy of the GNU General Public License along with * GNU Smalltalk; see the file COPYING. If not, write to the Free Software * Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * ***********************************************************************/ %x DECL %x DECL_C_CODE %x IMPL %x IMPL_C_CODE %x IMPL_END %x IMPL_MATCH %x CPP_CODE %x C_COMMENT %x C_STRING %x C_CHAR %option nounput %option noyywrap %option never-interactive %{ #include "genbc.h" static Filament *literal_fil; static int from = 0, depth = 0; #if !defined YY_FLEX_SUBMINOR_VERSION || YY_FLEX_SUBMINOR_VERSION < 31 int yylineno = 1; #endif static void init_scanner (FILE **pfp, YY_BUFFER_STATE *pbuf, const char *file, int start); %} %% { /* All states know how to count lines and to skip comments. */ \n+ { yylineno += yyleng; } [ \t\f]+ { } "/*" { from = YY_START; BEGIN (C_COMMENT); } } { BEGIN { return (DECL_BEGIN); } END { return (DECL_END); } ".." { return (DECL_DOTS); } "{"[\n]* { depth = 1; yylineno += yyleng - 1; yylval.ctext = "{\n "; BEGIN (DECL_C_CODE); return '{'; } } { [1-9][0-9]* | 0x[0-9A-Fa-f]+ | 0[0-7]* { yylval.num = strtol(yytext, NULL, 0); return (NUMBER); } } { /* Looking for matchers is a no-op until we find MATCH_BYTECODES. */ "MATCH_BYTECODES" { BEGIN (IMPL_MATCH); return (MATCH_BYTECODES); } .|[^M\n]* { } } { ")" { BEGIN (IMPL); return *yytext; } } { /* Parsing a matcher only requires us to find the closing parentheses and the opening brace: the rest is included in the catch-all `.' rule. */ ")" { BEGIN (IMPL_END); return *yytext; } "{" { depth = 1; literal_fil = filnew (NULL, 0); filccat (literal_fil, *yytext); BEGIN (IMPL_C_CODE); } } { /* Learn how to skip strings and preprocessor code. */ "'" { from = YY_START; BEGIN (C_CHAR); if (literal_fil) filccat (literal_fil, *yytext); else { yylval.text = yytext; return (EXPR); } } "\"" { from = YY_START; BEGIN (C_STRING); if (literal_fil) filccat (literal_fil, *yytext); else { yylval.text = yytext; return (EXPR); } } ^[ \t]*# { if (YY_START != IMPL) yyerror ("preprocessor directives inside matchers are invalid"); } } { extract(" "+) { return (DECL_EXTRACT); } dispatch(" "+) { return (DECL_DISPATCH); } break(" "*); { return (DECL_BREAK); } continue(" "*); { return (DECL_CONTINUE); } [ \t]*"="[ \t]* { yylval.ctext = yytext; return '='; } [ \t]*"("[ \t]* { yylval.ctext = yytext; return '('; } [ \t]*")"[ \t]* { yylval.ctext = yytext; return ')'; } [ \t]*","[ \t]* { yylval.ctext = yytext; return ','; } [ \t]*"{" { depth++; yylval.ctext = yytext; return EXPR; } [ \t]*"}" { if (!--depth) { BEGIN (DECL); return '}'; } yylval.ctext = yytext; return EXPR; } \n { yylineno++; yylval.ctext = " \\\n "; return (EXPR); } [^a-zA-Z_'"{}(),=\n]* { yylval.ctext = yytext; return (EXPR); } } { [a-zA-Z_][a-zA-Z0-9_]* { yylval.text = strdup (yytext); return (ID); } /* Put this rule last so that it does not override the others. */ . { return *yytext; } } { /* Learn how to balance braces and escape new-lines. */ "{" { depth++; filccat (literal_fil, '{'); } "}" { filccat (literal_fil, '}'); if (!--depth) { yylval.text = fildelete (literal_fil); literal_fil = NULL; BEGIN (IMPL_MATCH); return EXPR; } } \n { yylineno++; filcat (literal_fil, " \\\n"); } [^\n{}]* { filcat (literal_fil, yytext); } } { /* Characters and strings have different terminations... */ "'" { BEGIN (from); if (literal_fil) filccat (literal_fil, *yytext); else { yylval.text = yytext; return (EXPR); } } } { "\"" { BEGIN (from); if (literal_fil) filccat (literal_fil, *yytext); else { yylval.text = yytext; return (EXPR); } } } { /* ... but otherwise they're the same. */ \\. { yylineno += (yytext[1] == '\n'); if (literal_fil) filcat (literal_fil, yytext); else { yylval.text = yytext; return (EXPR); } } . { yylineno += (yytext[0] == '\n'); if (literal_fil) filccat (literal_fil, *yytext); else { yylval.text = yytext; return (EXPR); } } } { /* Preprocessor directives are just skipped. */ [^\n]*"\\"[ ]*$ { } [^\n]*$ { } } { /* And so are comments. */ [^*\n]*"*"*\n { yylineno++; } [^*\n]*"*"+[^/*] { } [^*\n]*"*"+"/" { BEGIN (from); } } %% void init_scanner (FILE **pfp, YY_BUFFER_STATE *pbuf, const char *file, int start) { if (!strcmp (file, "-")) { *pfp = stdin; current_file = "stdin"; } else { *pfp = fopen (file, "r"); current_file = file; } *pbuf = yy_create_buffer (*pfp, YY_BUF_SIZE); yy_switch_to_buffer (*pbuf); yylineno = 1; BEGIN (start); } void parse_declarations (const char *file) { YY_BUFFER_STATE buf; FILE *fp; init_scanner (&fp, &buf, file, DECL); decl_yyparse (); yy_delete_buffer (buf); fclose (fp); } void parse_implementation (const char *file) { YY_BUFFER_STATE buf; FILE *fp; init_scanner (&fp, &buf, file, IMPL); impl_yyparse (); yy_delete_buffer (buf); fclose (fp); } smalltalk-3.2.5/libgst/callin.c0000644000175000017500000006451212130343734013330 00000000000000/******************************** -*- C -*- **************************** * * C Callin facilities * * This module provides many routines to allow C code to invoke * Smalltalk messages on objects, most of which are based on * low-level facilities exposed by interp.c and dict.c. * * ***********************************************************************/ /*********************************************************************** * * Copyright 1988,89,90,91,92,94,95,99,2000,2001,2002,2006,2008,2009 * Free Software Foundation, Inc. * Written by Steve Byrne. * * This file is part of GNU Smalltalk. * * GNU Smalltalk is free software; you can redistribute it and/or modify it * under the terms of the GNU General Public License as published by the Free * Software Foundation; either version 2, or (at your option) any later * version. * * Linking GNU Smalltalk statically or dynamically with other modules is * making a combined work based on GNU Smalltalk. Thus, the terms and * conditions of the GNU General Public License cover the whole * combination. * * In addition, as a special exception, the Free Software Foundation * give you permission to combine GNU Smalltalk with free software * programs or libraries that are released under the GNU LGPL and with * independent programs running under the GNU Smalltalk virtual machine. * * You may copy and distribute such a system following the terms of the * GNU GPL for GNU Smalltalk and the licenses of the other code * concerned, provided that you include the source code of that other * code when and as the GNU GPL requires distribution of source code. * * Note that people who make modified versions of GNU Smalltalk are not * obligated to grant this special exception for their modified * versions; it is their choice whether to do so. The GNU General * Public License gives permission to release a modified version without * this exception; this exception also makes it possible to release a * modified version which carries forward this exception. * * GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or * FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for * more details. * * You should have received a copy of the GNU General Public License along with * GNU Smalltalk; see the file COPYING. If not, write to the Free Software * Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * ***********************************************************************/ #include "gstpriv.h" #include "gstpub.h" #ifndef NAN #define NAN (0.0 / 0.0) #endif typedef struct oop_registry { rb_node_t rb; OOP oop; int usage; } oop_registry; typedef struct oop_array_registry { rb_node_t rb; OOP **first; OOP **last; int usage; } oop_array_registry; /* The registry of OOPs which have been passed to C code. Implemented as a red-black tree. The registry is examined at GC time to ensure that OOPs that C code knows about don't go away. */ static oop_registry *oop_registry_root; static oop_array_registry *oop_array_registry_root; OOP _gst_va_msg_send (OOP receiver, OOP selector, va_list ap) { va_list save; OOP *args, anArg; int numArgs; if (!_gst_smalltalk_initialized) _gst_initialize (NULL, NULL, GST_NO_TTY); #ifdef __va_copy __va_copy (save, ap); #else save = ap; #endif for (numArgs = 0; va_arg (ap, OOP) != NULL; numArgs++) ; if (numArgs != _gst_selector_num_args (selector)) return (_gst_nil_oop); else { args = (OOP *) alloca (sizeof (OOP) * numArgs); for (numArgs = 0; (anArg = va_arg (save, OOP)) != NULL; numArgs++) args[numArgs] = anArg; return _gst_nvmsg_send (receiver, selector, args, numArgs); } } OOP _gst_msg_send (OOP receiver, OOP selector, ...) { va_list ap; va_start (ap, selector); return _gst_va_msg_send (receiver, selector, ap); } OOP _gst_vmsg_send (OOP receiver, OOP selector, OOP * args) { int numArgs; if (!_gst_smalltalk_initialized) _gst_initialize (NULL, NULL, GST_NO_TTY); for (numArgs = 0; args[numArgs]; numArgs++); if (numArgs != _gst_selector_num_args (selector)) return (_gst_nil_oop); else return _gst_nvmsg_send (receiver, selector, args, numArgs); } OOP _gst_str_msg_send (OOP receiver, const char *sel, ...) { va_list ap; OOP selector = _gst_symbol_to_oop (sel); va_start (ap, sel); return _gst_va_msg_send (receiver, selector, ap); } /* Use like printf */ void _gst_va_msg_sendf (PTR resultPtr, const char *fmt, va_list ap) { OOP selector, *args, result; int i, numArgs; const char *fp; char *s, selectorBuf[256]; inc_ptr incPtr; mst_Boolean receiver_is_block = false; if (!_gst_smalltalk_initialized) _gst_initialize (NULL, NULL, GST_NO_TTY); incPtr = INC_SAVE_POINTER (); numArgs = 0; for (s = selectorBuf, fp = &fmt[2]; *fp; fp++) { if (*fp == '%') { fp++; numArgs++; if (*fp == '%') { *s++ = '%'; numArgs--; } else if (*fp == 'B') receiver_is_block = true; } else if (*fp != ' ' && *fp != '\t') *s++ = *fp; } *s = '\0'; if (receiver_is_block) selector = NULL; else selector = _gst_intern_string (selectorBuf); if (numArgs != 1 + _gst_selector_num_args (selector)) return; args = (OOP *) alloca (sizeof (OOP) * numArgs); for (i = -1, fp = &fmt[2]; *fp; fp++) { if (*fp != '%') continue; fp++; switch (*fp) { case 'i': args[++i] = FROM_C_INT (va_arg (ap, long)); INC_ADD_OOP (args[i]); break; case 'f': args[++i] = floatd_new (va_arg (ap, double)); INC_ADD_OOP (args[i]); break; case 'F': args[++i] = floatq_new (va_arg (ap, long double)); INC_ADD_OOP (args[i]); break; case 'b': args[++i] = va_arg (ap, int) ? _gst_true_oop : _gst_false_oop; INC_ADD_OOP (args[i]); break; case 'c': args[++i] = CHAR_OOP_AT ((char) va_arg (ap, int)); INC_ADD_OOP (args[i]); break; case 'C': args[++i] = COBJECT_NEW (va_arg (ap, PTR), _gst_nil_oop, _gst_c_object_class); INC_ADD_OOP (args[i]); break; case 's': args[++i] = _gst_string_new (va_arg (ap, const char *)); INC_ADD_OOP (args[i]); break; case 'S': args[++i] = _gst_intern_string (va_arg (ap, const char *)); INC_ADD_OOP (args[i]); break; case 'B': case 'o': args[++i] = va_arg (ap, OOP); INC_ADD_OOP (args[i]); break; case 't': /* type string, followed by a void * */ { OOP ctype; ctype = _gst_type_name_to_oop (va_arg (ap, const char *)); INC_ADD_OOP (ctype); args[++i] = COBJECT_NEW (va_arg (ap, PTR), ctype, _gst_nil_oop); INC_ADD_OOP (args[i]); } break; case 'T': /* existing type instance, and a void * */ { OOP ctype; ctype = va_arg (ap, OOP); args[++i] = COBJECT_NEW (va_arg (ap, PTR), ctype, _gst_nil_oop); INC_ADD_OOP (args[i]); } break; case 'w': #if SIZEOF_WCHAR_T <= SIZEOF_INT args[++i] = char_new ((wchar_t) va_arg (ap, int)); #else args[++i] = char_new ((wchar_t) va_arg (ap, wchar_t)); #endif INC_ADD_OOP (args[i]); break; case 'W': args[++i] = _gst_unicode_string_new (va_arg (ap, const wchar_t *)); INC_ADD_OOP (args[i]); break; } } result = _gst_nvmsg_send (args[0], selector, args + 1, numArgs - 1); if (resultPtr) { switch (fmt[1]) { case 'i': *(int *) resultPtr = IS_NIL (result) ? 0 : TO_C_INT (result); break; case 'c': *(char *) resultPtr = IS_NIL (result) ? 0 : CHAR_OOP_VALUE (result); break; case 'C': *(PTR *) resultPtr = IS_NIL (result) ? NULL : cobject_value (result); break; case 's': *(char **) resultPtr = IS_NIL (result) ? NULL : (char *) _gst_to_cstring (result); break; case 'b': *(int *) resultPtr = IS_NIL (result) ? false : (result == _gst_true_oop); break; case 'f': *(double *) resultPtr = IS_NIL (result) ? 0.0 : _gst_oop_to_float (result); break; case 'F': *(long double *) resultPtr = IS_NIL (result) ? 0.0 : _gst_oop_to_long_double (result); break; case 'v': /* don't care about the result */ break; /* "v" for "void" */ case '?': *(long *) resultPtr = _gst_oop_to_c (result); break; case 'w': *(wchar_t *) resultPtr = IS_NIL (result) ? 0 : CHAR_OOP_VALUE (result); break; case 'W': *(wchar_t **) resultPtr = IS_NIL (result) ? NULL : _gst_to_wide_cstring (result); break; case 'o': default: *(OOP *) resultPtr = result; break; } } INC_RESTORE_POINTER (incPtr); } void _gst_msg_sendf (PTR resultPtr, const char *fmt, ...) { va_list ap; va_start (ap, fmt); _gst_va_msg_sendf (resultPtr, fmt, ap); } OOP _gst_type_name_to_oop (const char *name) { OOP result; char buf[300]; sprintf (buf, "^%s!", name); result = _gst_eval_expr (buf); return (result); } void _gst_eval_code (const char *str) { if (!_gst_smalltalk_initialized) _gst_initialize (NULL, NULL, GST_NO_TTY); _gst_push_cstring (str); _gst_parse_stream (false); _gst_pop_stream (true); } OOP _gst_eval_expr (const char *str) { OOP result; if (!_gst_smalltalk_initialized) _gst_initialize (NULL, NULL, GST_NO_TTY); _gst_push_cstring (str); _gst_parse_stream (false); _gst_pop_stream (true); result = _gst_last_returned_value; return (result); } OOP _gst_object_alloc (OOP class_oop, int size) { OOP oop; if (CLASS_IS_INDEXABLE (class_oop)) instantiate_with (class_oop, size, &oop); else instantiate (class_oop, &oop); INC_ADD_OOP (oop); return oop; } int _gst_basic_size (OOP oop) { return (NUM_INDEXABLE_FIELDS (oop)); } /*********************************************************************** * * Conversion *to* Smalltalk datatypes routines * ***********************************************************************/ OOP _gst_class_name_to_oop (const char *name) { OOP result, key; char *s, *p, *prev_p; if (!name || !*name) return NULL; s = strdup (name); if (!_gst_smalltalk_initialized) _gst_initialize (NULL, NULL, GST_NO_TTY); result = _gst_smalltalk_dictionary; for (p = s; (prev_p = strsep (&p, ".")) != NULL; ) { key = _gst_intern_string (prev_p); result = dictionary_at (result, key); if (IS_NIL (result)) return NULL; } free (s); return (result); } OOP _gst_uint_to_oop (unsigned long int i) { if (!_gst_smalltalk_initialized) _gst_initialize (NULL, NULL, GST_NO_TTY); return (FROM_C_ULONG (i)); } OOP _gst_int_to_oop (long int i) { if (!_gst_smalltalk_initialized) _gst_initialize (NULL, NULL, GST_NO_TTY); return (FROM_C_LONG (i)); } OOP _gst_id_to_oop (long int i) { if (!_gst_smalltalk_initialized) _gst_initialize (NULL, NULL, GST_NO_TTY); return (OOP_AT (i)); } OOP _gst_long_double_to_oop (long double f) { return (INC_ADD_OOP (floatq_new (f))); } OOP _gst_float_to_oop (double f) { return (INC_ADD_OOP (floatd_new (f))); } OOP _gst_bool_to_oop (int b) { if (!_gst_smalltalk_initialized) _gst_initialize (NULL, NULL, GST_NO_TTY); if (b) return (_gst_true_oop); else return (_gst_false_oop); } OOP _gst_char_to_oop (char c) { if (!_gst_smalltalk_initialized) _gst_initialize (NULL, NULL, GST_NO_TTY); return (CHAR_OOP_AT (c)); } OOP _gst_wchar_to_oop (wchar_t wc) { if (!_gst_smalltalk_initialized) _gst_initialize (NULL, NULL, GST_NO_TTY); return (char_new (wc)); } /* !!! Add in byteArray support sometime soon */ OOP _gst_string_to_oop (const char *str) { if (!_gst_smalltalk_initialized) _gst_initialize (NULL, NULL, GST_NO_TTY); if (str == NULL) return (_gst_nil_oop); else return (INC_ADD_OOP (_gst_string_new (str))); } OOP _gst_wstring_to_oop (const wchar_t *str) { if (!_gst_smalltalk_initialized) _gst_initialize (NULL, NULL, GST_NO_TTY); if (str == NULL) return (_gst_nil_oop); else return (INC_ADD_OOP (_gst_unicode_string_new (str))); } OOP _gst_byte_array_to_oop (const char *str, int n) { if (!_gst_smalltalk_initialized) _gst_initialize (NULL, NULL, GST_NO_TTY); if (str == NULL) return (_gst_nil_oop); else return (INC_ADD_OOP (_gst_byte_array_new (str, n))); } OOP _gst_symbol_to_oop (const char *str) { if (!_gst_smalltalk_initialized) _gst_initialize (NULL, NULL, GST_NO_TTY); if (str == NULL) return (_gst_nil_oop); else /* Symbols don't get freed, so the new OOP doesn't need to be registered */ return (_gst_intern_string (str)); } OOP _gst_c_object_to_oop (PTR co) { if (!_gst_smalltalk_initialized) _gst_initialize (NULL, NULL, GST_NO_TTY); if (co == NULL) return (_gst_nil_oop); else return (INC_ADD_OOP (COBJECT_NEW (co, _gst_nil_oop, _gst_c_object_class))); } void _gst_set_c_object (OOP oop, PTR co) { if (!_gst_smalltalk_initialized) _gst_initialize (NULL, NULL, GST_NO_TTY); set_cobject_value (oop, co); } /*********************************************************************** * * Conversion *from* Smalltalk datatypes routines * ***********************************************************************/ /* ### need a type inquiry routine */ long _gst_oop_to_c (OOP oop) { if (!_gst_smalltalk_initialized) _gst_initialize (NULL, NULL, GST_NO_TTY); if (IS_C_LONG (oop) || IS_C_ULONG (oop)) return (TO_C_LONG (oop)); else if (OOP_CLASS (oop) == _gst_true_class || OOP_CLASS (oop) == _gst_false_class) return (oop == _gst_true_oop); else if (OOP_CLASS (oop) == _gst_char_class || OOP_CLASS (oop) == _gst_unicode_character_class) return (CHAR_OOP_VALUE (oop)); else if (IS_NIL (oop)) return (0); else if (is_a_kind_of (OOP_CLASS (oop), _gst_c_object_class)) return ((long) cobject_value (oop)); else return (0); } long _gst_oop_to_int (OOP oop) { if (!_gst_smalltalk_initialized) _gst_initialize (NULL, NULL, GST_NO_TTY); return (TO_C_LONG (oop)); } long _gst_oop_to_id (OOP oop) { if (!_gst_smalltalk_initialized) _gst_initialize (NULL, NULL, GST_NO_TTY); return (OOP_INDEX (oop)); } double _gst_oop_to_float (OOP oop) { if (!_gst_smalltalk_initialized) _gst_initialize (NULL, NULL, GST_NO_TTY); if (IS_INT (oop)) return (TO_INT (oop)); else if (IS_CLASS (oop, _gst_floatd_class)) return (FLOATD_OOP_VALUE (oop)); else if (IS_CLASS (oop, _gst_floate_class)) return (FLOATE_OOP_VALUE (oop)); else if (IS_CLASS (oop, _gst_floatq_class)) return (FLOATQ_OOP_VALUE (oop)); else return 0.0 / 0.0; } long double _gst_oop_to_long_double (OOP oop) { if (!_gst_smalltalk_initialized) _gst_initialize (NULL, NULL, GST_NO_TTY); if (IS_INT (oop)) return (TO_INT (oop)); else if (IS_CLASS (oop, _gst_floatd_class)) return (FLOATD_OOP_VALUE (oop)); else if (IS_CLASS (oop, _gst_floate_class)) return (FLOATE_OOP_VALUE (oop)); else if (IS_CLASS (oop, _gst_floatq_class)) return (FLOATQ_OOP_VALUE (oop)); else return 0.0 / 0.0; } int _gst_oop_to_bool (OOP oop) { if (!_gst_smalltalk_initialized) _gst_initialize (NULL, NULL, GST_NO_TTY); return (oop == _gst_true_oop); } char _gst_oop_to_char (OOP oop) { if (!_gst_smalltalk_initialized) _gst_initialize (NULL, NULL, GST_NO_TTY); return (CHAR_OOP_VALUE (oop)); } wchar_t _gst_oop_to_wchar (OOP oop) { if (!_gst_smalltalk_initialized) _gst_initialize (NULL, NULL, GST_NO_TTY); return (CHAR_OOP_VALUE (oop)); } char * _gst_oop_to_string (OOP oop) { if (!_gst_smalltalk_initialized) _gst_initialize (NULL, NULL, GST_NO_TTY); if (IS_NIL (oop)) return (NULL); else return ((char *) _gst_to_cstring (oop)); } wchar_t * _gst_oop_to_wstring (OOP oop) { if (!_gst_smalltalk_initialized) _gst_initialize (NULL, NULL, GST_NO_TTY); if (IS_NIL (oop)) return (NULL); else return ((wchar_t *) _gst_to_wide_cstring (oop)); } char * _gst_oop_to_byte_array (OOP oop) { if (!_gst_smalltalk_initialized) _gst_initialize (NULL, NULL, GST_NO_TTY); if (IS_NIL (oop)) return (NULL); else return ((char *) _gst_to_byte_array (oop)); } PTR _gst_oop_to_c_object (OOP oop) { if (!_gst_smalltalk_initialized) _gst_initialize (NULL, NULL, GST_NO_TTY); if (IS_NIL (oop)) return (NULL); else return (cobject_value (oop)); } OOP _gst_get_object_class (OOP oop) { if (!_gst_smalltalk_initialized) _gst_initialize (NULL, NULL, GST_NO_TTY); return OOP_INT_CLASS (oop); } OOP _gst_get_superclass (OOP oop) { if (!_gst_smalltalk_initialized) _gst_initialize (NULL, NULL, GST_NO_TTY); /* Quick tests for "class-ness". */ assert (IS_OOP (oop)); assert (OOP_CLASS (oop) == _gst_behavior_class || OOP_CLASS (OOP_CLASS (oop)) == _gst_metaclass_class); return SUPERCLASS (oop); } mst_Boolean _gst_class_is_kind_of (OOP candidate, OOP superclass) { if (!_gst_smalltalk_initialized) _gst_initialize (NULL, NULL, GST_NO_TTY); /* Quick tests for "class-ness". */ assert (IS_OOP (candidate) && IS_OOP (superclass)); assert (OOP_CLASS (candidate) == _gst_behavior_class || OOP_CLASS (OOP_CLASS (candidate)) == _gst_metaclass_class); if (superclass == _gst_nil_oop || candidate == superclass) return true; assert (OOP_CLASS (superclass) == _gst_behavior_class || OOP_CLASS (OOP_CLASS (superclass)) == _gst_metaclass_class); return is_a_kind_of (candidate, superclass); } mst_Boolean _gst_object_is_kind_of (OOP candidate, OOP superclass) { OOP its_class; if (!_gst_smalltalk_initialized) _gst_initialize (NULL, NULL, GST_NO_TTY); if (IS_INT (candidate)) { its_class = _gst_small_integer_class; if (superclass == _gst_small_integer_class || superclass == _gst_object_class) return true; } else its_class = OOP_CLASS (candidate); if (superclass == _gst_nil_oop || its_class == superclass) return true; /* Quick tests for "class-ness". */ assert (IS_OOP (superclass)); assert (OOP_CLASS (superclass) == _gst_behavior_class || OOP_CLASS (OOP_CLASS (superclass)) == _gst_metaclass_class); return is_a_kind_of (its_class, superclass); } OOP _gst_perform (OOP receiver, OOP selector) { if (!_gst_smalltalk_initialized) _gst_initialize (NULL, NULL, GST_NO_TTY); return _gst_nvmsg_send (receiver, selector, NULL, 0); } OOP _gst_perform_with (OOP receiver, OOP selector, OOP arg) { if (!_gst_smalltalk_initialized) _gst_initialize (NULL, NULL, GST_NO_TTY); return _gst_nvmsg_send (receiver, selector, &arg, 1); } mst_Boolean _gst_class_implements_selector (OOP classOOP, OOP selector) { if (!_gst_smalltalk_initialized) _gst_initialize (NULL, NULL, GST_NO_TTY); assert (IS_OOP (classOOP)); assert (OOP_CLASS (classOOP) == _gst_behavior_class || OOP_CLASS (OOP_CLASS (classOOP)) == _gst_metaclass_class); return _gst_find_class_method (classOOP, selector) != _gst_nil_oop; } mst_Boolean _gst_class_can_understand (OOP classOOP, OOP selector) { method_cache_entry dummy; if (!_gst_smalltalk_initialized) _gst_initialize (NULL, NULL, GST_NO_TTY); /* Quick test for "class-ness". */ assert (IS_OOP (classOOP)); assert (OOP_CLASS (classOOP) == _gst_behavior_class || OOP_CLASS (OOP_CLASS (classOOP)) == _gst_metaclass_class); return _gst_find_method (classOOP, selector, &dummy); } mst_Boolean _gst_responds_to (OOP oop, OOP selector) { method_cache_entry dummy; if (!_gst_smalltalk_initialized) _gst_initialize (NULL, NULL, GST_NO_TTY); return _gst_find_method (OOP_INT_CLASS (oop), selector, &dummy); } size_t _gst_oop_size (OOP oop) { if (!_gst_smalltalk_initialized) _gst_initialize (NULL, NULL, GST_NO_TTY); return NUM_INDEXABLE_FIELDS (oop); } OOP _gst_oop_at (OOP oop, size_t index) { OOP result; if (!_gst_smalltalk_initialized) _gst_initialize (NULL, NULL, GST_NO_TTY); result = index_oop (oop, index + 1); assert (result); return result; } OOP _gst_oop_at_put (OOP oop, size_t index, OOP new) { OOP old; if (!_gst_smalltalk_initialized) _gst_initialize (NULL, NULL, GST_NO_TTY); old = index_oop (oop, index + 1); assert (old); index_oop_put (oop, index + 1, new); return old; } void * _gst_oop_indexed_base (OOP oop) { if (!_gst_smalltalk_initialized) _gst_initialize (NULL, NULL, GST_NO_TTY); return &OOP_TO_OBJ (oop)->data[OOP_FIXED_FIELDS (oop)]; } enum gst_indexed_kind _gst_oop_indexed_kind (OOP oop) { if (!_gst_smalltalk_initialized) _gst_initialize (NULL, NULL, GST_NO_TTY); return OOP_INSTANCE_SPEC (oop) & ISP_INDEXEDVARS; } /*********************************************************************** * * Registry bookkeeping routines * ***********************************************************************/ OOP _gst_register_oop (OOP oop) { rb_node_t **p = (rb_node_t **) &oop_registry_root; oop_registry *node; oop_registry *entry = NULL; if (!oop || IS_NIL (oop)) return (oop); while (*p) { entry = (oop_registry *) *p; if (oop < entry->oop) p = &(*p)->rb_left; else if (oop > entry->oop) p = &(*p)->rb_right; else { entry->usage++; return (oop); } } node = (oop_registry *) xmalloc(sizeof(oop_registry)); node->rb.rb_parent = (rb_node_t *) entry; node->rb.rb_left = node->rb.rb_right = NULL; node->usage = 1; node->oop = oop; *p = &(node->rb); rb_rebalance(&node->rb, (rb_node_t **) &oop_registry_root); return (oop); } void _gst_unregister_oop (OOP oop) { oop_registry *entry = oop_registry_root; /* Speed things up, this will never be in the registry (but we allow it to simplify client code). */ if (!oop || IS_NIL (oop)) return; while (entry) { if (entry->oop == oop) { if (!--entry->usage) { rb_erase (&entry->rb, (rb_node_t **) &oop_registry_root); xfree (entry); } break; } entry = (oop_registry *) (oop < entry->oop ? entry->rb.rb_left : entry->rb.rb_right); } } void _gst_register_oop_array (OOP **first, OOP **last) { rb_node_t **p = (rb_node_t **) &oop_array_registry_root; oop_array_registry *node; oop_array_registry *entry = NULL; while (*p) { entry = (oop_array_registry *) *p; if (first < entry->first) p = &(*p)->rb_left; else if (first > entry->first) p = &(*p)->rb_right; else entry->usage++; } node = (oop_array_registry *) xmalloc(sizeof(oop_array_registry)); node->rb.rb_parent = (rb_node_t *) entry; node->rb.rb_left = node->rb.rb_right = NULL; node->usage = 1; node->first = first; node->last = last; *p = &(node->rb); rb_rebalance(&node->rb, (rb_node_t **) &oop_array_registry_root); } void _gst_unregister_oop_array (OOP **first) { oop_array_registry *entry = oop_array_registry_root; while (entry) { if (entry->first == first) { if (!--entry->usage) { rb_erase (&entry->rb, (rb_node_t **) &oop_array_registry_root); xfree (entry); } break; } entry = (oop_array_registry *) (first < entry->first ? entry->rb.rb_left : entry->rb.rb_right); } } void _gst_copy_registered_oops (void) { rb_node_t *node; rb_traverse_t t; /* Walk the OOP registry... */ for (node = rb_first(&(oop_registry_root->rb), &t); node; node = rb_next(&t)) { oop_registry *k = (oop_registry *) node; MAYBE_COPY_OOP (k->oop); } /* ...and then the OOP-array registry. */ for (node = rb_first(&(oop_array_registry_root->rb), &t); node; node = rb_next(&t)) { oop_array_registry *k = (oop_array_registry *) node; /* Dereference the pointers in the tree to obtain where the array lies. */ OOP *first = *(k->first); OOP *last = *(k->last); _gst_copy_oop_range (first, last); } } void _gst_mark_registered_oops (void) { rb_node_t *node; rb_traverse_t t; /* Walk the OOP registry... */ for (node = rb_first(&(oop_registry_root->rb), &t); node; node = rb_next(&t)) { oop_registry *k = (oop_registry *) node; MAYBE_MARK_OOP (k->oop); } /* ...and then the OOP-array registry. */ for (node = rb_first(&(oop_array_registry_root->rb), &t); node; node = rb_next(&t)) { oop_array_registry *k = (oop_array_registry *) node; /* Dereference the pointers in the tree to obtain where the array lies. */ OOP *first = *(k->first); OOP *last = *(k->last); _gst_mark_oop_range (first, last); } } void _gst_init_vmproxy (void) { gst_interpreter_proxy.nilOOP = _gst_nil_oop; gst_interpreter_proxy.trueOOP = _gst_true_oop; gst_interpreter_proxy.falseOOP = _gst_false_oop; gst_interpreter_proxy.objectClass = _gst_object_class; gst_interpreter_proxy.arrayClass = _gst_array_class; gst_interpreter_proxy.stringClass = _gst_string_class; gst_interpreter_proxy.characterClass = _gst_char_class; gst_interpreter_proxy.smallIntegerClass = _gst_small_integer_class; gst_interpreter_proxy.floatDClass = _gst_floatd_class; gst_interpreter_proxy.floatEClass = _gst_floate_class; gst_interpreter_proxy.byteArrayClass = _gst_byte_array_class; gst_interpreter_proxy.objectMemoryClass = _gst_object_memory_class; gst_interpreter_proxy.classClass = _gst_class_class; gst_interpreter_proxy.behaviorClass = _gst_behavior_class; gst_interpreter_proxy.blockClosureClass = _gst_block_closure_class; gst_interpreter_proxy.contextPartClass = _gst_context_part_class; gst_interpreter_proxy.blockContextClass = _gst_block_context_class; gst_interpreter_proxy.methodContextClass = _gst_method_context_class; gst_interpreter_proxy.compiledMethodClass = _gst_compiled_method_class; gst_interpreter_proxy.compiledBlockClass = _gst_compiled_block_class; gst_interpreter_proxy.fileDescriptorClass = _gst_file_descriptor_class; gst_interpreter_proxy.fileStreamClass = _gst_file_stream_class; gst_interpreter_proxy.processClass = _gst_process_class; gst_interpreter_proxy.semaphoreClass = _gst_semaphore_class; gst_interpreter_proxy.cObjectClass = _gst_c_object_class; /* And system objects. */ gst_interpreter_proxy.processorOOP = _gst_processor_oop; } struct VMProxy * _gst_get_vmproxy (void) { struct VMProxy *result; result = xmalloc (sizeof (struct VMProxy)); memcpy (result, &gst_interpreter_proxy, sizeof (struct VMProxy)); return result; } smalltalk-3.2.5/libgst/input.h0000644000175000017500000001723312123404352013224 00000000000000/******************************** -*- C -*- **************************** * * External definitions for the input module. * * ***********************************************************************/ /*********************************************************************** * * Copyright 2001, 2002, 2003, 2006, 2008 Free Software Foundation, Inc. * Written by Paolo Bonzini. * * This file is part of GNU Smalltalk. * * GNU Smalltalk is free software; you can redistribute it and/or modify it * under the terms of the GNU General Public License as published by the Free * Software Foundation; either version 2, or (at your option) any later * version. * * Linking GNU Smalltalk statically or dynamically with other modules is * making a combined work based on GNU Smalltalk. Thus, the terms and * conditions of the GNU General Public License cover the whole * combination. * * In addition, as a special exception, the Free Software Foundation * give you permission to combine GNU Smalltalk with free software * programs or libraries that are released under the GNU LGPL and with * independent programs running under the GNU Smalltalk virtual machine. * * You may copy and distribute such a system following the terms of the * GNU GPL for GNU Smalltalk and the licenses of the other code * concerned, provided that you include the source code of that other * code when and as the GNU GPL requires distribution of source code. * * Note that people who make modified versions of GNU Smalltalk are not * obligated to grant this special exception for their modified * versions; it is their choice whether to do so. The GNU General * Public License gives permission to release a modified version without * this exception; this exception also makes it possible to release a * modified version which carries forward this exception. * * GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or * FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for * more details. * * You should have received a copy of the GNU General Public License along with * GNU Smalltalk; see the file COPYING. If not, write to the Free Software * Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * ***********************************************************************/ #ifndef GST_INPUT_H #define GST_INPUT_H typedef enum { STREAM_UNKNOWN, STREAM_FILE, STREAM_STRING, STREAM_OOP #ifdef HAVE_READLINE , STREAM_READLINE #endif /* HAVE_READLINE */ } stream_type; /* If true, readline is suppressed. */ extern mst_Boolean _gst_no_tty ATTRIBUTE_HIDDEN; /* Pass file descriptor FD, printed as file name FILENAME, to the parser. */ extern void _gst_push_unix_file (int fd, const char *fileName) ATTRIBUTE_HIDDEN; /* Return the current line and column into Y and X, respectively. Also sets the method_start_pos pointer. */ extern YYLTYPE _gst_get_location (void) ATTRIBUTE_HIDDEN; /* Pass the OOP to the parser; it must respond to #nextHunk. */ extern void _gst_push_stream_oop (OOP oop) ATTRIBUTE_HIDDEN; /* Pass the contents of the Smalltalk String STRINGOOP to the parser. While the String is being parsed, it can change because it is saved. The String should not contain nulls. */ extern void _gst_push_smalltalk_string (OOP stringOOP) ATTRIBUTE_HIDDEN; /* Pass the contents of the null-terminated String STRING to the parser. While the String is being parsed, it can change because it is saved. */ extern void _gst_push_cstring (const char *string) ATTRIBUTE_HIDDEN; /* Pass the contents of stdin (either through the readline interface or as a vanilla file descriptor) to the parser. The readline interface is used if the Emacs interface is not active and stdin is a tty. */ extern void _gst_push_stdin_string (void) ATTRIBUTE_HIDDEN; /* Restores the previous stream on the stack, optionally closing the topmost one if CLOSEIT is true. */ extern void _gst_pop_stream (mst_Boolean closeIt) ATTRIBUTE_HIDDEN; /* This function resets the file type information for the current stream. It is typically used by fileIn type methods when filing in a subsection of a real file via a temporary file what the real source of the text is. */ extern void _gst_set_stream_info (int line, OOP fileOOP, OOP fileNameOOP, int fileOffset) ATTRIBUTE_HIDDEN; /* Emits a warning, with the current file and line in front of it, on the standard error descriptor. */ extern void _gst_warningf (const char *str, ...) ATTRIBUTE_PRINTF_1 ATTRIBUTE_HIDDEN; /* Emits a warning, with the current file and the given LINE in front of it, on the standard error descriptor. */ extern void _gst_warningf_at (int line, const char *str, ...) ATTRIBUTE_PRINTF_2 ATTRIBUTE_HIDDEN; /* Emits an error, with the current file and line in front of it, on the standard error descriptor. */ extern void _gst_errorf (const char *str, ...) ATTRIBUTE_PRINTF_1 ATTRIBUTE_HIDDEN; /* Emits an error, with the current file and the given LINE in front of it, on the standard error descriptor. */ extern void _gst_errorf_at (int line, const char *str, ...) ATTRIBUTE_PRINTF_2 ATTRIBUTE_HIDDEN; /* Interface to the Bison-generated parser. */ extern void _gst_yyerror (const char *s) ATTRIBUTE_HIDDEN; /* Push character 'ic' back into the input queue. Allows for two character pushback currently. This solves the problem of lexing 3. and then finding out that what we should have lexed was 3 followed by . as a statement terminator. */ extern void _gst_unread_char (int ic) ATTRIBUTE_HIDDEN; /* Return the next character from the topmost stream in the stack. */ extern int _gst_next_char (void) ATTRIBUTE_HIDDEN; /* Return whether the topmost stream is an interactive one. */ extern mst_Boolean _gst_get_cur_stream_prompt (void) ATTRIBUTE_PURE ATTRIBUTE_HIDDEN; /* Return the type of the topmost stream in the stack. */ extern stream_type _gst_get_cur_stream_type (void) ATTRIBUTE_PURE ATTRIBUTE_HIDDEN; /* Returns an OOP containing the string of the topmost stream if it is a STREAM_STRING, STREAM_OOP or STREAM_READLINE, or if it has a filename; nil otherwise. */ extern OOP _gst_get_source_string (off_t startPos, off_t endPos) ATTRIBUTE_HIDDEN; #ifdef HAVE_READLINE /* Initialize the completion interface for Readline. */ extern void _gst_initialize_readline (void) ATTRIBUTE_HIDDEN; /* Look at the first LEN bytes starting at STR, and add the colon-separated keywords, or the whole string if it starts with an uppercase character AND it contains no colons. */ extern void _gst_add_symbol_completion (const char *str, int len) ATTRIBUTE_HIDDEN; /* Add 1 to the completion-enabling flag. The flag starts at 1 (completions are active) and completions are enabled until the flag falls below this value. */ extern void _gst_enable_completion (void) ATTRIBUTE_HIDDEN; /* Subtract 1 from the completion-enabling flag. The flag starts at 1 (completions are active) and if completions are disabled, they are not enabled while the flag is below this value. */ extern void _gst_disable_completion (void) ATTRIBUTE_HIDDEN; #endif /* HAVE_READLINE */ /* Parse the Smalltalk source code read from stdin, showing the PROMPT that is passed. */ extern void _gst_process_stdin (const char *prompt) ATTRIBUTE_HIDDEN; /* Parse the Smalltalk source code read from file FILE found within the search path DIR. */ extern mst_Boolean _gst_process_file (const char *fileName, enum gst_file_dir dir) ATTRIBUTE_HIDDEN; #endif smalltalk-3.2.5/libgst/prims.def0000644000175000017500000042054712130343734013540 00000000000000/******************************** -*- C -*- **************************** * * Byte code interpreter primitives include file * * ***********************************************************************/ /*********************************************************************** * * Copyright 1988,89,90,91,92,94,95,99,2000,2001,2002,2003,2006,2007,2008,2009 * Free Software Foundation, Inc. * Written by Steve Byrne. * * This file is part of GNU Smalltalk. * * GNU Smalltalk is free software; you can redistribute it and/or modify it * under the terms of the GNU General Public License as published by the Free * Software Foundation; either version 2, or (at your option) any later * version. * * Linking GNU Smalltalk statically or dynamically with other modules is * making a combined work based on GNU Smalltalk. Thus, the terms and * conditions of the GNU General Public License cover the whole * combination. * * In addition, as a special exception, the Free Software Foundation * give you permission to combine GNU Smalltalk with free software * programs or libraries that are released under the GNU LGPL and with * independent programs running under the GNU Smalltalk virtual machine. * * You may copy and distribute such a system following the terms of the * GNU GPL for GNU Smalltalk and the licenses of the other code * concerned, provided that you include the source code of that other * code when and as the GNU GPL requires distribution of source code. * * Note that people who make modified versions of GNU Smalltalk are not * obligated to grant this special exception for their modified * versions; it is their choice whether to do so. The GNU General * Public License gives permission to release a modified version without * this exception; this exception also makes it possible to release a * modified version which carries forward this exception. * * GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or * FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for * more details. * * You should have received a copy of the GNU General Public License along with * GNU Smalltalk; see the file COPYING. If not, write to the Free Software * Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * ***********************************************************************/ #ifdef OPTIMIZE #define RECEIVER_IS_INT(x) (true) #define RECEIVER_IS_OOP(x) (true) #define RECEIVER_IS_CLASS(x, y) (true) #define RECEIVER_IS_A_KIND_OF(x, y) (true) #define PRIM_CHECKS_RECEIVER PRIM_SUCCEED #else #define RECEIVER_IS_INT(x) IS_INT((x)) #define RECEIVER_IS_OOP(x) IS_OOP((x)) #define RECEIVER_IS_CLASS(x, y) IS_CLASS((x), (y)) #define RECEIVER_IS_A_KIND_OF(x, y) is_a_kind_of((x), (y)) #define PRIM_CHECKS_RECEIVER (PRIM_SUCCEED | PRIM_FAIL) #endif #ifdef HAVE_GMP #define PRIM_USES_GMP (PRIM_SUCCEED | PRIM_FAIL) #else #define PRIM_USES_GMP PRIM_FAIL #endif #ifdef ENABLE_JIT_TRANSLATION #define PRIM_FAILED return ((intptr_t) -1) #define PRIM_SUCCEEDED return ((intptr_t) 0) #define PRIM_SUCCEEDED_RELOAD_IP return ((intptr_t) native_ip) #else #define PRIM_FAILED return (true) #define PRIM_SUCCEEDED return (false) #define PRIM_SUCCEEDED_RELOAD_IP return (false) #endif #define INT_BIN_OP(op, noOverflow) { \ OOP oop1; \ OOP oop2; \ mst_Boolean overflow; \ oop2 = POP_OOP(); \ oop1 = POP_OOP(); \ if COMMON (RECEIVER_IS_INT(oop1) && IS_INT(oop2)) {\ intptr_t iarg1, iarg2; \ iarg1 = TO_INT(oop1); \ iarg2 = TO_INT(oop2); \ \ oop1 = op; \ if COMMON (noOverflow || !overflow) { \ PUSH_OOP(oop1); \ PRIM_SUCCEEDED; \ } \ } \ UNPOP(2); \ PRIM_FAILED; \ } #define BOOL_BIN_OP(operator) { \ OOP oop1; \ OOP oop2; \ oop2 = POP_OOP(); \ oop1 = POP_OOP(); \ if COMMON (RECEIVER_IS_INT(oop1) && IS_INT(oop2)) { \ PUSH_BOOLEAN( ((intptr_t)oop1) operator ((intptr_t)oop2) ); \ PRIM_SUCCEEDED; \ } \ UNPOP(2); \ PRIM_FAILED; \ } /* SmallInteger + arg */ primitive VMpr_SmallInteger_plus [succeed,fail] { _gst_primitives_executed++; INT_BIN_OP (add_with_check (oop1, oop2, &overflow), false); } /* SmallInteger - arg */ primitive VMpr_SmallInteger_minus [succeed,fail] { _gst_primitives_executed++; INT_BIN_OP (sub_with_check (oop1, oop2, &overflow), false); } /* SmallInteger < arg */ primitive VMpr_SmallInteger_lt [succeed,fail] { _gst_primitives_executed++; BOOL_BIN_OP (<); } /* SmallInteger > arg */ primitive VMpr_SmallInteger_gt [succeed,fail] { _gst_primitives_executed++; BOOL_BIN_OP (>); } /* SmallInteger <= arg */ primitive VMpr_SmallInteger_le [succeed,fail] { _gst_primitives_executed++; BOOL_BIN_OP (<=); } /* SmallInteger >= arg */ primitive VMpr_SmallInteger_ge [succeed,fail] { _gst_primitives_executed++; BOOL_BIN_OP (>=); } /* SmallInteger =, == arg */ primitive VMpr_SmallInteger_eq [succeed,fail] { _gst_primitives_executed++; BOOL_BIN_OP ( ==); } /* SmallInteger ~=, ~~ arg */ primitive VMpr_SmallInteger_ne [succeed,fail] { _gst_primitives_executed++; BOOL_BIN_OP (!=); } /* SmallInteger * arg */ primitive VMpr_SmallInteger_times [succeed,fail] { _gst_primitives_executed++; INT_BIN_OP (mul_with_check (oop1, oop2, &overflow), false); } /* SmallInteger / arg */ /* quotient as exact as possible */ primitive VMpr_SmallInteger_divide [succeed,fail] { OOP oop1; OOP oop2; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = POP_OOP (); if (RECEIVER_IS_INT (oop1) && IS_INT (oop2) && oop2 != FROM_INT (0)) { intptr_t iarg1, iarg2, result; iarg1 = TO_INT (oop1); iarg2 = TO_INT (oop2); result = iarg1 / iarg2; iarg2 *= result; if COMMON (iarg1 == iarg2) { PUSH_INT (result); PRIM_SUCCEEDED; } } UNPOP (2); PRIM_FAILED; } /* SmallInteger \\ arg */ /* remainder truncated towards -infinity */ primitive VMpr_SmallInteger_modulo [succeed,fail] { OOP oop1; OOP oop2; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = POP_OOP (); if COMMON (RECEIVER_IS_INT (oop1) && IS_INT (oop2) && oop2 != FROM_INT (0)) { intptr_t iarg1, iarg2, result; iarg1 = TO_INT (oop1); iarg2 = TO_INT (oop2); result = iarg1 % iarg2; PUSH_INT (result && ((result ^ iarg2) < 0) ? result + iarg2 : result); PRIM_SUCCEEDED; } UNPOP (2); PRIM_FAILED; } /* SmallInteger // arg */ /* quotient truncated towards -infinity */ primitive VMpr_SmallInteger_intDiv [succeed,fail] { OOP oop1; OOP oop2; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = POP_OOP (); if COMMON (RECEIVER_IS_INT (oop1) && IS_INT (oop2) && oop2 != FROM_INT (0)) { intptr_t iarg1, iarg2; iarg1 = TO_INT (oop1); iarg2 = TO_INT (oop2); if (iarg2 < 0) { /* make the divisor positive */ iarg1 = -iarg1; iarg2 = -iarg2; } if (iarg1 < 0) /* differing signs => use black magic */ PUSH_INT (-((iarg2 - 1 - iarg1) / iarg2)); else PUSH_INT (iarg1 / iarg2); PRIM_SUCCEEDED; } UNPOP (2); PRIM_FAILED; } /* SmallInteger quo: arg */ /* quotient truncated towards 0 */ primitive VMpr_SmallInteger_quo [succeed,fail] { OOP oop1; OOP oop2; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = POP_OOP (); if COMMON (RECEIVER_IS_INT (oop1) && IS_INT (oop2)) { intptr_t iarg1, iarg2; iarg1 = TO_INT (oop1); iarg2 = TO_INT (oop2); if COMMON (iarg2 != 0) { PUSH_INT (iarg1 / iarg2); PRIM_SUCCEEDED; } } UNPOP (2); PRIM_FAILED; } /* SmallInteger bitAnd: arg */ primitive VMpr_SmallInteger_bitAnd [succeed,fail] { _gst_primitives_executed++; INT_BIN_OP (tagged_and (oop1, oop2), true); } /* SmallInteger bitOr: arg */ primitive VMpr_SmallInteger_bitOr [succeed,fail] { _gst_primitives_executed++; INT_BIN_OP (tagged_or (oop1, oop2), true); } /* SmallInteger bitXor: arg */ primitive VMpr_SmallInteger_bitXor [succeed,fail] { _gst_primitives_executed++; INT_BIN_OP (tagged_xor (oop1, oop2), true); } /* SmallInteger bitShift: arg */ primitive VMpr_SmallInteger_bitShift [succeed,fail] { OOP oop1; OOP oop2; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = POP_OOP (); if COMMON (RECEIVER_IS_INT (oop1) && IS_INT (oop2)) { intptr_t iarg1; intptr_t iarg2; iarg1 = TO_INT (oop1); iarg2 = TO_INT (oop2); if (iarg2 < 0) { if (iarg2 >= -ST_INT_SIZE) PUSH_INT (iarg1 >> -iarg2); else PUSH_INT (iarg1 >> ST_INT_SIZE); PRIM_SUCCEEDED; } if COMMON (iarg2 < ST_INT_SIZE) { intptr_t result = iarg1 << iarg2; if ((result >> iarg2) == iarg1 && !INT_OVERFLOW(result)) { PUSH_INT (result); PRIM_SUCCEEDED; } } } UNPOP (2); PRIM_FAILED; } /* SmallInteger scramble */ primitive VMpr_SmallInteger_scramble [checks_receiver] { OOP oop1; _gst_primitives_executed++; oop1 = POP_OOP (); if COMMON (RECEIVER_IS_INT (oop1)) { PUSH_INT (scramble (TO_INT (oop1))); PRIM_SUCCEEDED; } UNPOP (1); PRIM_FAILED; } /* SmallInteger asFloatD */ primitive VMpr_SmallInteger_asFloatD [checks_receiver] { OOP oop1; _gst_primitives_executed++; oop1 = POP_OOP (); if COMMON (RECEIVER_IS_INT (oop1)) { PUSH_OOP (floatd_new ((double) TO_INT (oop1))); PRIM_SUCCEEDED; } UNPOP (1); PRIM_FAILED; } /* SmallInteger asFloatE */ primitive VMpr_SmallInteger_asFloatE [checks_receiver] { OOP oop1; _gst_primitives_executed++; oop1 = POP_OOP (); if COMMON (RECEIVER_IS_INT (oop1)) { PUSH_OOP (floate_new ((float) TO_INT (oop1))); PRIM_SUCCEEDED; } UNPOP (1); PRIM_FAILED; } /* SmallInteger asFloatQ */ primitive VMpr_SmallInteger_asFloatQ [checks_receiver] { OOP oop1; _gst_primitives_executed++; oop1 = POP_OOP (); if COMMON (RECEIVER_IS_INT (oop1)) { PUSH_OOP (floatq_new ((long double) TO_INT (oop1))); PRIM_SUCCEEDED; } UNPOP (1); PRIM_FAILED; } primitive VMpr_LargeInteger_eq [uses_gmp] { #ifdef HAVE_GMP gst_mpz a = { 0, 0, NULL }; gst_mpz b = { 0, 0, NULL }; OOP oop1, oop2; int result; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = POP_OOP (); if COMMON (IS_INT (oop1) || SUPERCLASS (OOP_CLASS (oop1)) == _gst_large_integer_class || OOP_CLASS (oop1) == _gst_large_zero_integer_class) _gst_mpz_from_oop (&a, oop1); else { UNPOP (2); PRIM_FAILED; } if COMMON (IS_INT (oop2) || SUPERCLASS (OOP_CLASS (oop2)) == _gst_large_integer_class || OOP_CLASS (oop2) == _gst_large_zero_integer_class) _gst_mpz_from_oop (&b, oop2); else { _gst_mpz_clear (&a); UNPOP (2); PRIM_FAILED; } result = _gst_mpz_cmp (&a, &b); _gst_mpz_clear (&a); _gst_mpz_clear (&b); PUSH_BOOLEAN (result == 0); PRIM_SUCCEEDED; #else PRIM_FAILED; #endif } primitive VMpr_LargeInteger_ne [uses_gmp] { #ifdef HAVE_GMP gst_mpz a = { 0, 0, NULL }; gst_mpz b = { 0, 0, NULL }; OOP oop1, oop2; int result; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = POP_OOP (); if COMMON (IS_INT (oop1) || SUPERCLASS (OOP_CLASS (oop1)) == _gst_large_integer_class || OOP_CLASS (oop1) == _gst_large_zero_integer_class) _gst_mpz_from_oop (&a, oop1); else { UNPOP (2); PRIM_FAILED; } if COMMON (IS_INT (oop2) || SUPERCLASS (OOP_CLASS (oop2)) == _gst_large_integer_class || OOP_CLASS (oop2) == _gst_large_zero_integer_class) _gst_mpz_from_oop (&b, oop2); else { _gst_mpz_clear (&a); UNPOP (2); PRIM_FAILED; } result = _gst_mpz_cmp (&a, &b); _gst_mpz_clear (&a); _gst_mpz_clear (&b); PUSH_BOOLEAN (result != 0); PRIM_SUCCEEDED; #else PRIM_FAILED; #endif } primitive VMpr_LargeInteger_lt [uses_gmp] { #ifdef HAVE_GMP gst_mpz a = { 0, 0, NULL }; gst_mpz b = { 0, 0, NULL }; OOP oop1, oop2; int result; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = POP_OOP (); if COMMON (IS_INT (oop1) || SUPERCLASS (OOP_CLASS (oop1)) == _gst_large_integer_class || OOP_CLASS (oop1) == _gst_large_zero_integer_class) _gst_mpz_from_oop (&a, oop1); else { UNPOP (2); PRIM_FAILED; } if COMMON (IS_INT (oop2) || SUPERCLASS (OOP_CLASS (oop2)) == _gst_large_integer_class || OOP_CLASS (oop2) == _gst_large_zero_integer_class) _gst_mpz_from_oop (&b, oop2); else { _gst_mpz_clear (&a); UNPOP (2); PRIM_FAILED; } result = _gst_mpz_cmp (&a, &b); _gst_mpz_clear (&a); _gst_mpz_clear (&b); PUSH_BOOLEAN (result < 0); PRIM_SUCCEEDED; #else PRIM_FAILED; #endif } primitive VMpr_LargeInteger_le [uses_gmp] { #ifdef HAVE_GMP gst_mpz a = { 0, 0, NULL }; gst_mpz b = { 0, 0, NULL }; OOP oop1, oop2; int result; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = POP_OOP (); if COMMON (IS_INT (oop1) || SUPERCLASS (OOP_CLASS (oop1)) == _gst_large_integer_class || OOP_CLASS (oop1) == _gst_large_zero_integer_class) _gst_mpz_from_oop (&a, oop1); else { UNPOP (2); PRIM_FAILED; } if COMMON (IS_INT (oop2) || SUPERCLASS (OOP_CLASS (oop2)) == _gst_large_integer_class || OOP_CLASS (oop2) == _gst_large_zero_integer_class) _gst_mpz_from_oop (&b, oop2); else { _gst_mpz_clear (&a); UNPOP (2); PRIM_FAILED; } result = _gst_mpz_cmp (&a, &b); _gst_mpz_clear (&a); _gst_mpz_clear (&b); PUSH_BOOLEAN (result <= 0); PRIM_SUCCEEDED; #else PRIM_FAILED; #endif } primitive VMpr_LargeInteger_gt [uses_gmp] { #ifdef HAVE_GMP gst_mpz a = { 0, 0, NULL }; gst_mpz b = { 0, 0, NULL }; OOP oop1, oop2; int result; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = POP_OOP (); if COMMON (IS_INT (oop1) || SUPERCLASS (OOP_CLASS (oop1)) == _gst_large_integer_class || OOP_CLASS (oop1) == _gst_large_zero_integer_class) _gst_mpz_from_oop (&a, oop1); else { UNPOP (2); PRIM_FAILED; } if COMMON (IS_INT (oop2) || SUPERCLASS (OOP_CLASS (oop2)) == _gst_large_integer_class || OOP_CLASS (oop2) == _gst_large_zero_integer_class) _gst_mpz_from_oop (&b, oop2); else { _gst_mpz_clear (&a); UNPOP (2); PRIM_FAILED; } result = _gst_mpz_cmp (&a, &b); _gst_mpz_clear (&a); _gst_mpz_clear (&b); PUSH_BOOLEAN (result > 0); PRIM_SUCCEEDED; #else PRIM_FAILED; #endif } primitive VMpr_LargeInteger_ge [uses_gmp] { #ifdef HAVE_GMP gst_mpz a = { 0, 0, NULL }; gst_mpz b = { 0, 0, NULL }; OOP oop1, oop2; int result; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = POP_OOP (); if COMMON (IS_INT (oop1) || SUPERCLASS (OOP_CLASS (oop1)) == _gst_large_integer_class || OOP_CLASS (oop1) == _gst_large_zero_integer_class) _gst_mpz_from_oop (&a, oop1); else { UNPOP (2); PRIM_FAILED; } if COMMON (IS_INT (oop2) || SUPERCLASS (OOP_CLASS (oop2)) == _gst_large_integer_class || OOP_CLASS (oop2) == _gst_large_zero_integer_class) _gst_mpz_from_oop (&b, oop2); else { _gst_mpz_clear (&a); UNPOP (2); PRIM_FAILED; } result = _gst_mpz_cmp (&a, &b); _gst_mpz_clear (&a); _gst_mpz_clear (&b); PUSH_BOOLEAN (result >= 0); PRIM_SUCCEEDED; #else PRIM_FAILED; #endif } primitive VMpr_LargeInteger_times [uses_gmp] { #ifdef HAVE_GMP gst_mpz a = { 0, 0, NULL }; gst_mpz b = { 0, 0, NULL }; gst_mpz c = { 0, 0, NULL }; OOP oop1, oop2, oop3; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = POP_OOP (); if COMMON (IS_INT (oop1) || SUPERCLASS (OOP_CLASS (oop1)) == _gst_large_integer_class || OOP_CLASS (oop1) == _gst_large_zero_integer_class) _gst_mpz_from_oop (&a, oop1); else { UNPOP (2); PRIM_FAILED; } if COMMON (IS_INT (oop2) || SUPERCLASS (OOP_CLASS (oop2)) == _gst_large_integer_class || OOP_CLASS (oop2) == _gst_large_zero_integer_class) _gst_mpz_from_oop (&b, oop2); else { _gst_mpz_clear (&a); UNPOP (2); PRIM_FAILED; } _gst_mpz_mul (&c, &a, &b); oop3 = _gst_oop_from_mpz (&c); _gst_mpz_clear (&a); _gst_mpz_clear (&b); _gst_mpz_clear (&c); PUSH_OOP (oop3); PRIM_SUCCEEDED; #else PRIM_FAILED; #endif } primitive VMpr_LargeInteger_intDiv [uses_gmp] { #ifdef HAVE_GMP gst_mpz a = { 0, 0, NULL }; gst_mpz b = { 0, 0, NULL }; gst_mpz q = { 0, 0, NULL }; gst_mpz r = { 0, 0, NULL }; OOP oop1, oop2, oop3; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = POP_OOP (); if COMMON (IS_INT (oop1) || SUPERCLASS (OOP_CLASS (oop1)) == _gst_large_integer_class || OOP_CLASS (oop1) == _gst_large_zero_integer_class) _gst_mpz_from_oop (&a, oop1); else { UNPOP (2); PRIM_FAILED; } if COMMON (IS_INT (oop2) && oop2 != FROM_INT (0)) _gst_mpz_fdiv_qr_si (&q, &a, TO_INT(oop2)); else if (IS_OOP (oop2) && SUPERCLASS (OOP_CLASS (oop2)) == _gst_large_integer_class) { _gst_mpz_from_oop (&b, oop2); _gst_mpz_fdiv_qr (&q, &r, &a, &b); _gst_mpz_clear (&r); _gst_mpz_clear (&b); } else { _gst_mpz_clear (&a); UNPOP (2); PRIM_FAILED; } oop3 = _gst_oop_from_mpz (&q); _gst_mpz_clear (&a); _gst_mpz_clear (&q); PUSH_OOP (oop3); PRIM_SUCCEEDED; #else PRIM_FAILED; #endif } primitive VMpr_LargeInteger_modulo [uses_gmp] { #ifdef HAVE_GMP gst_mpz a = { 0, 0, NULL }; gst_mpz b = { 0, 0, NULL }; gst_mpz q = { 0, 0, NULL }; gst_mpz r = { 0, 0, NULL }; OOP oop1, oop2, oop3; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = POP_OOP (); if COMMON (IS_INT (oop1) || SUPERCLASS (OOP_CLASS (oop1)) == _gst_large_integer_class || OOP_CLASS (oop1) == _gst_large_zero_integer_class) _gst_mpz_from_oop (&a, oop1); else { UNPOP (2); PRIM_FAILED; } if COMMON (IS_INT (oop2) && oop2 != FROM_INT (0)) { mp_limb_t rem = _gst_mpz_fdiv_qr_si (&q, &a, TO_INT(oop2)); oop3 = FROM_INT (rem); } else if (IS_OOP (oop2) && SUPERCLASS (OOP_CLASS (oop2)) == _gst_large_integer_class) { _gst_mpz_from_oop (&b, oop2); _gst_mpz_fdiv_qr (&q, &r, &a, &b); oop3 = _gst_oop_from_mpz (&r); _gst_mpz_clear (&r); _gst_mpz_clear (&b); } else { _gst_mpz_clear (&a); UNPOP (2); PRIM_FAILED; } _gst_mpz_clear (&a); _gst_mpz_clear (&q); PUSH_OOP (oop3); PRIM_SUCCEEDED; #else PRIM_FAILED; #endif } primitive VMpr_LargeInteger_divExact [uses_gmp] { #ifdef HAVE_GMP gst_mpz a = { 0, 0, NULL }; gst_mpz b = { 0, 0, NULL }; gst_mpz q = { 0, 0, NULL }; OOP oop1, oop2, oop3; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = POP_OOP (); if COMMON (IS_INT (oop1) || SUPERCLASS (OOP_CLASS (oop1)) == _gst_large_integer_class || OOP_CLASS (oop1) == _gst_large_zero_integer_class) _gst_mpz_from_oop (&a, oop1); else { UNPOP (2); PRIM_FAILED; } if COMMON (IS_INT (oop2) && oop2 != FROM_INT (0)) _gst_mpz_tdiv_qr_si (&q, &a, TO_INT(oop2)); else if (IS_OOP (oop2) && SUPERCLASS (OOP_CLASS (oop2)) == _gst_large_integer_class) { _gst_mpz_from_oop (&b, oop2); _gst_mpz_divexact (&q, &a, &b); _gst_mpz_clear (&b); } else { _gst_mpz_clear (&a); UNPOP (2); PRIM_FAILED; } oop3 = _gst_oop_from_mpz (&q); _gst_mpz_clear (&a); _gst_mpz_clear (&q); PUSH_OOP (oop3); PRIM_SUCCEEDED; #else PRIM_FAILED; #endif } primitive VMpr_LargeInteger_quo [uses_gmp] { #ifdef HAVE_GMP gst_mpz a = { 0, 0, NULL }; gst_mpz b = { 0, 0, NULL }; gst_mpz q = { 0, 0, NULL }; gst_mpz r = { 0, 0, NULL }; OOP oop1, oop2, oop3; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = POP_OOP (); if COMMON (IS_INT (oop1) || SUPERCLASS (OOP_CLASS (oop1)) == _gst_large_integer_class || OOP_CLASS (oop1) == _gst_large_zero_integer_class) _gst_mpz_from_oop (&a, oop1); else { UNPOP (2); PRIM_FAILED; } if COMMON (IS_INT (oop2) && oop2 != FROM_INT (0)) _gst_mpz_tdiv_qr_si (&q, &a, TO_INT(oop2)); else if (IS_OOP (oop2) && SUPERCLASS (OOP_CLASS (oop2)) == _gst_large_integer_class) { _gst_mpz_from_oop (&b, oop2); _gst_mpz_tdiv_qr (&q, &r, &a, &b); _gst_mpz_clear (&r); _gst_mpz_clear (&b); } else { _gst_mpz_clear (&a); UNPOP (2); PRIM_FAILED; } oop3 = _gst_oop_from_mpz (&q); _gst_mpz_clear (&a); _gst_mpz_clear (&q); PUSH_OOP (oop3); PRIM_SUCCEEDED; #else PRIM_FAILED; #endif } primitive VMpr_LargeInteger_rem [uses_gmp] { #ifdef HAVE_GMP gst_mpz a = { 0, 0, NULL }; gst_mpz b = { 0, 0, NULL }; gst_mpz q = { 0, 0, NULL }; gst_mpz r = { 0, 0, NULL }; OOP oop1, oop2, oop3; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = POP_OOP (); if COMMON (IS_INT (oop1) || SUPERCLASS (OOP_CLASS (oop1)) == _gst_large_integer_class || OOP_CLASS (oop1) == _gst_large_zero_integer_class) _gst_mpz_from_oop (&a, oop1); else { UNPOP (2); PRIM_FAILED; } if COMMON (IS_INT (oop2) && oop2 != FROM_INT (0)) { mp_limb_t rem = _gst_mpz_tdiv_qr_si (&q, &a, TO_INT(oop2)); oop3 = FROM_INT (rem); } else if (IS_OOP (oop2) && SUPERCLASS (OOP_CLASS (oop2)) == _gst_large_integer_class) { _gst_mpz_from_oop (&b, oop2); _gst_mpz_tdiv_qr (&q, &r, &a, &b); oop3 = _gst_oop_from_mpz (&r); _gst_mpz_clear (&r); _gst_mpz_clear (&b); } else { _gst_mpz_clear (&a); UNPOP (2); PRIM_FAILED; } _gst_mpz_clear (&a); _gst_mpz_clear (&q); PUSH_OOP (oop3); PRIM_SUCCEEDED; #else PRIM_FAILED; #endif } primitive VMpr_LargeInteger_negated [uses_gmp] { #ifdef HAVE_GMP gst_mpz a = { 0, 0, NULL }; gst_mpz b = { 0, 0, NULL }; gst_mpz c = { 0, 0, NULL }; OOP oop2, oop3; _gst_primitives_executed++; oop2 = POP_OOP (); if COMMON (IS_INT (oop2) || SUPERCLASS (OOP_CLASS (oop2)) == _gst_large_integer_class || OOP_CLASS (oop2) == _gst_large_zero_integer_class) _gst_mpz_from_oop (&b, oop2); else { UNPOP (2); PRIM_FAILED; } _gst_mpz_sub (&c, &a, &b); oop3 = _gst_oop_from_mpz (&c); _gst_mpz_clear (&b); _gst_mpz_clear (&c); PUSH_OOP (oop3); PRIM_SUCCEEDED; #else PRIM_FAILED; #endif } primitive VMpr_LargeInteger_bitAnd [uses_gmp] { #ifdef HAVE_GMP gst_mpz a = { 0, 0, NULL }; gst_mpz b = { 0, 0, NULL }; gst_mpz c = { 0, 0, NULL }; OOP oop1, oop2, oop3; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = POP_OOP (); if COMMON (IS_INT (oop1) || SUPERCLASS (OOP_CLASS (oop1)) == _gst_large_integer_class || OOP_CLASS (oop1) == _gst_large_zero_integer_class) _gst_mpz_from_oop (&a, oop1); else { UNPOP (2); PRIM_FAILED; } if COMMON (IS_INT (oop2) || SUPERCLASS (OOP_CLASS (oop2)) == _gst_large_integer_class || OOP_CLASS (oop2) == _gst_large_zero_integer_class) _gst_mpz_from_oop (&b, oop2); else { _gst_mpz_clear (&a); UNPOP (2); PRIM_FAILED; } _gst_mpz_and (&c, &a, &b); oop3 = _gst_oop_from_mpz (&c); _gst_mpz_clear (&a); _gst_mpz_clear (&b); _gst_mpz_clear (&c); PUSH_OOP (oop3); PRIM_SUCCEEDED; #else PRIM_FAILED; #endif } primitive VMpr_LargeInteger_bitOr [uses_gmp] { #ifdef HAVE_GMP gst_mpz a = { 0, 0, NULL }; gst_mpz b = { 0, 0, NULL }; gst_mpz c = { 0, 0, NULL }; OOP oop1, oop2, oop3; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = POP_OOP (); if COMMON (IS_INT (oop1) || SUPERCLASS (OOP_CLASS (oop1)) == _gst_large_integer_class || OOP_CLASS (oop1) == _gst_large_zero_integer_class) _gst_mpz_from_oop (&a, oop1); else { UNPOP (2); PRIM_FAILED; } if COMMON (IS_INT (oop2) || SUPERCLASS (OOP_CLASS (oop2)) == _gst_large_integer_class || OOP_CLASS (oop2) == _gst_large_zero_integer_class) _gst_mpz_from_oop (&b, oop2); else { _gst_mpz_clear (&a); UNPOP (2); PRIM_FAILED; } _gst_mpz_ior (&c, &a, &b); oop3 = _gst_oop_from_mpz (&c); _gst_mpz_clear (&a); _gst_mpz_clear (&b); _gst_mpz_clear (&c); PUSH_OOP (oop3); PRIM_SUCCEEDED; #else PRIM_FAILED; #endif } primitive VMpr_LargeInteger_bitXor [uses_gmp] { #ifdef HAVE_GMP gst_mpz a = { 0, 0, NULL }; gst_mpz b = { 0, 0, NULL }; gst_mpz c = { 0, 0, NULL }; OOP oop1, oop2, oop3; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = POP_OOP (); if COMMON (IS_INT (oop1) || SUPERCLASS (OOP_CLASS (oop1)) == _gst_large_integer_class || OOP_CLASS (oop1) == _gst_large_zero_integer_class) _gst_mpz_from_oop (&a, oop1); else { UNPOP (2); PRIM_FAILED; } if COMMON (IS_INT (oop2) || SUPERCLASS (OOP_CLASS (oop2)) == _gst_large_integer_class || OOP_CLASS (oop2) == _gst_large_zero_integer_class) _gst_mpz_from_oop (&b, oop2); else { _gst_mpz_clear (&a); UNPOP (2); PRIM_FAILED; } _gst_mpz_xor (&c, &a, &b); oop3 = _gst_oop_from_mpz (&c); _gst_mpz_clear (&a); _gst_mpz_clear (&b); _gst_mpz_clear (&c); PUSH_OOP (oop3); PRIM_SUCCEEDED; #else PRIM_FAILED; #endif } primitive VMpr_LargeInteger_bitInvert [uses_gmp] { #ifdef HAVE_GMP gst_mpz a = { 0, 0, NULL }; gst_mpz c = { 0, 0, NULL }; OOP oop2, oop3; _gst_primitives_executed++; oop2 = POP_OOP (); if COMMON (IS_INT (oop2) || SUPERCLASS (OOP_CLASS (oop2)) == _gst_large_integer_class || OOP_CLASS (oop2) == _gst_large_zero_integer_class) _gst_mpz_from_oop (&a, oop2); else { UNPOP (2); PRIM_FAILED; } _gst_mpz_com (&c, &a); oop3 = _gst_oop_from_mpz (&c); _gst_mpz_clear (&a); _gst_mpz_clear (&c); PUSH_OOP (oop3); PRIM_SUCCEEDED; #else PRIM_FAILED; #endif } primitive VMpr_LargeInteger_bitShift [uses_gmp] { #ifdef HAVE_GMP int n; gst_mpz a = { 0, 0, NULL }; gst_mpz c = { 0, 0, NULL }; OOP oop1, oop2, oop3; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = POP_OOP (); if COMMON (IS_INT (oop2)) n = TO_INT (oop2); else { UNPOP (2); PRIM_FAILED; } if COMMON (IS_INT (oop1) || SUPERCLASS (OOP_CLASS (oop1)) == _gst_large_integer_class || OOP_CLASS (oop1) == _gst_large_zero_integer_class) _gst_mpz_from_oop (&a, oop1); else { UNPOP (2); PRIM_FAILED; } if (n > 0) _gst_mpz_mul_2exp (&c, &a, n); else _gst_mpz_div_2exp (&c, &a, -n); oop3 = _gst_oop_from_mpz (&c); _gst_mpz_clear (&a); _gst_mpz_clear (&c); PUSH_OOP (oop3); PRIM_SUCCEEDED; #endif PRIM_FAILED; } primitive VMpr_LargeInteger_plus [uses_gmp] { #ifdef HAVE_GMP gst_mpz a = { 0, 0, NULL }; gst_mpz b = { 0, 0, NULL }; gst_mpz c = { 0, 0, NULL }; OOP oop1, oop2, oop3; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = POP_OOP (); if COMMON (IS_INT (oop1) || SUPERCLASS (OOP_CLASS (oop1)) == _gst_large_integer_class || OOP_CLASS (oop1) == _gst_large_zero_integer_class) _gst_mpz_from_oop (&a, oop1); else { UNPOP (2); PRIM_FAILED; } if COMMON (IS_INT (oop2) || SUPERCLASS (OOP_CLASS (oop2)) == _gst_large_integer_class || OOP_CLASS (oop2) == _gst_large_zero_integer_class) _gst_mpz_from_oop (&b, oop2); else { _gst_mpz_clear (&a); UNPOP (2); PRIM_FAILED; } _gst_mpz_add (&c, &a, &b); oop3 = _gst_oop_from_mpz (&c); _gst_mpz_clear (&a); _gst_mpz_clear (&b); _gst_mpz_clear (&c); PUSH_OOP (oop3); PRIM_SUCCEEDED; #else PRIM_FAILED; #endif } primitive VMpr_LargeInteger_minus [uses_gmp] { #ifdef HAVE_GMP gst_mpz a = { 0, 0, NULL }; gst_mpz b = { 0, 0, NULL }; gst_mpz c = { 0, 0, NULL }; OOP oop1, oop2, oop3; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = POP_OOP (); if COMMON (IS_INT (oop1) || SUPERCLASS (OOP_CLASS (oop1)) == _gst_large_integer_class || OOP_CLASS (oop1) == _gst_large_zero_integer_class) _gst_mpz_from_oop (&a, oop1); else { UNPOP (2); PRIM_FAILED; } if COMMON (IS_INT (oop2) || SUPERCLASS (OOP_CLASS (oop2)) == _gst_large_integer_class || OOP_CLASS (oop2) == _gst_large_zero_integer_class) _gst_mpz_from_oop (&b, oop2); else { _gst_mpz_clear (&a); UNPOP (2); PRIM_FAILED; } _gst_mpz_sub (&c, &a, &b); oop3 = _gst_oop_from_mpz (&c); _gst_mpz_clear (&a); _gst_mpz_clear (&b); _gst_mpz_clear (&c); PUSH_OOP (oop3); PRIM_SUCCEEDED; #else PRIM_FAILED; #endif } primitive VMpr_LargeInteger_gcd [uses_gmp] { #ifdef HAVE_GMP gst_mpz a = { 0, 0, NULL }; gst_mpz b = { 0, 0, NULL }; gst_mpz c = { 0, 0, NULL }; OOP oop1, oop2, oop3; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = POP_OOP (); if COMMON (IS_INT (oop1) || SUPERCLASS (OOP_CLASS (oop1)) == _gst_large_integer_class || OOP_CLASS (oop1) == _gst_large_zero_integer_class) _gst_mpz_from_oop (&a, oop1); else { UNPOP (2); PRIM_FAILED; } if COMMON (IS_INT (oop2) || SUPERCLASS (OOP_CLASS (oop2)) == _gst_large_integer_class || OOP_CLASS (oop2) == _gst_large_zero_integer_class) _gst_mpz_from_oop (&b, oop2); else { _gst_mpz_clear (&a); UNPOP (2); PRIM_FAILED; } if (oop1 == FROM_INT(0) || oop2 == FROM_INT(0) || (IS_OOP(oop1) && OOP_CLASS (oop1) == _gst_large_zero_integer_class) || (IS_OOP(oop2) && OOP_CLASS (oop2) == _gst_large_zero_integer_class)) /* Return the non-zero number between a and b */ _gst_mpz_add (&c, &a, &b); else _gst_mpz_gcd (&c, &a, &b); oop3 = _gst_oop_from_mpz (&c); _gst_mpz_clear (&a); _gst_mpz_clear (&b); _gst_mpz_clear (&c); PUSH_OOP (oop3); PRIM_SUCCEEDED; #else PRIM_FAILED; #endif } primitive VMpr_LargeInteger_asFloatD [uses_gmp] { #ifdef HAVE_GMP gst_mpz a = { 0, 0, NULL }; OOP oop1, oop2; double d; _gst_primitives_executed++; oop1 = POP_OOP (); if COMMON (IS_INT (oop1) || SUPERCLASS (OOP_CLASS (oop1)) == _gst_large_integer_class || OOP_CLASS (oop1) == _gst_large_zero_integer_class) _gst_mpz_from_oop (&a, oop1); else { UNPOP (1); PRIM_FAILED; } if (_gst_mpz_get_d (&a, &d)) { oop2 = floatd_new (d); _gst_mpz_clear (&a); PUSH_OOP (oop2); PRIM_SUCCEEDED; } UNPOP (1); #endif PRIM_FAILED; } primitive VMpr_LargeInteger_asFloatE [uses_gmp] { #ifdef HAVE_GMP gst_mpz a = { 0, 0, NULL }; OOP oop1, oop2; double d; _gst_primitives_executed++; oop1 = POP_OOP (); if COMMON (IS_INT (oop1) || SUPERCLASS (OOP_CLASS (oop1)) == _gst_large_integer_class || OOP_CLASS (oop1) == _gst_large_zero_integer_class) _gst_mpz_from_oop (&a, oop1); else { UNPOP (1); PRIM_FAILED; } if (_gst_mpz_get_d (&a, &d) && (double) (float) d == d) { oop2 = floate_new (d); _gst_mpz_clear (&a); PUSH_OOP (oop2); PRIM_SUCCEEDED; } UNPOP (1); #endif PRIM_FAILED; } primitive VMpr_LargeInteger_asFloatQ [uses_gmp] { #ifdef HAVE_GMP gst_mpz a = { 0, 0, NULL }; OOP oop1, oop2; long double d; _gst_primitives_executed++; oop1 = POP_OOP (); if COMMON (IS_INT (oop1) || SUPERCLASS (OOP_CLASS (oop1)) == _gst_large_integer_class || OOP_CLASS (oop1) == _gst_large_zero_integer_class) _gst_mpz_from_oop (&a, oop1); else { UNPOP (1); PRIM_FAILED; } if (_gst_mpz_get_ld (&a, &d) && (long double) (float) d == d) { oop2 = floatq_new (d); _gst_mpz_clear (&a); PUSH_OOP (oop2); PRIM_SUCCEEDED; } UNPOP (1); #endif PRIM_FAILED; } primitive VMpr_FloatD_arith : prim_id VMpr_FloatD_plus [succeed,fail], prim_id VMpr_FloatD_minus [succeed,fail], prim_id VMpr_FloatD_lt [succeed,fail], prim_id VMpr_FloatD_gt [succeed,fail], prim_id VMpr_FloatD_le [succeed,fail], prim_id VMpr_FloatD_ge [succeed,fail], prim_id VMpr_FloatD_eq [succeed,fail], prim_id VMpr_FloatD_ne [succeed,fail], prim_id VMpr_FloatD_times [succeed,fail], prim_id VMpr_FloatD_divide [succeed,fail] { double farg2; OOP oop1; OOP oop2; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = POP_OOP (); if (IS_CLASS (oop2, _gst_floatd_class)) farg2 = FLOATD_OOP_VALUE (oop2); else if (IS_INT (oop2)) farg2 = (double) TO_INT (oop2); else { UNPOP (2); PRIM_FAILED; } if COMMON (RECEIVER_IS_CLASS (oop1, _gst_floatd_class)) { double farg1; farg1 = FLOATD_OOP_VALUE (oop1); switch (id) { case prim_id (VMpr_FloatD_plus): PUSH_OOP (floatd_new (farg1 + farg2)); break; case prim_id (VMpr_FloatD_minus): PUSH_OOP (floatd_new (farg1 - farg2)); break; case prim_id (VMpr_FloatD_lt): PUSH_BOOLEAN (farg1 < farg2); break; case prim_id (VMpr_FloatD_gt): PUSH_BOOLEAN (farg1 > farg2); break; case prim_id (VMpr_FloatD_le): PUSH_BOOLEAN (farg1 <= farg2); break; case prim_id (VMpr_FloatD_ge): PUSH_BOOLEAN (farg1 >= farg2); break; case prim_id (VMpr_FloatD_eq): PUSH_BOOLEAN (farg1 == farg2); break; case prim_id (VMpr_FloatD_ne): PUSH_BOOLEAN (farg1 != farg2); break; case prim_id (VMpr_FloatD_times): PUSH_OOP (floatd_new (farg1 * farg2)); break; case prim_id (VMpr_FloatD_divide): PUSH_OOP (floatd_new (farg1 / farg2)); break; } PRIM_SUCCEEDED; } UNPOP (2); PRIM_FAILED; } /* FloatD truncated */ primitive VMpr_FloatD_truncated [succeed,fail] { OOP oop1; _gst_primitives_executed++; oop1 = POP_OOP (); if COMMON (RECEIVER_IS_CLASS (oop1, _gst_floatd_class)) { double oopValue = FLOATD_OOP_VALUE (oop1); if COMMON (oopValue >= MIN_ST_INT && oopValue <= MAX_ST_INT) { PUSH_INT (lrint (trunc (oopValue))); PRIM_SUCCEEDED; } } UNPOP (1); PRIM_FAILED; } /* FloatD fractionPart */ primitive VMpr_FloatD_fractionPart [checks_receiver] { OOP oop1; _gst_primitives_executed++; oop1 = POP_OOP (); if COMMON (RECEIVER_IS_CLASS (oop1, _gst_floatd_class)) { double farg1; farg1 = FLOATD_OOP_VALUE (oop1); farg1 -= (farg1 < 0.0) ? ceil (farg1) : floor (farg1); PUSH_OOP (floatd_new (farg1)); PRIM_SUCCEEDED; } UNPOP (1); PRIM_FAILED; } /* FloatD exponent */ primitive VMpr_FloatD_exponent [checks_receiver,return_small_smallinteger] { OOP oop1; _gst_primitives_executed++; oop1 = POP_OOP (); if COMMON (RECEIVER_IS_CLASS (oop1, _gst_floatd_class)) { double farg1; int intArg1; farg1 = FLOATD_OOP_VALUE (oop1); if (farg1 == 0.0) intArg1 = 1; else { frexp (FLOATD_OOP_VALUE (oop1), &intArg1); intArg1--; } PUSH_INT (intArg1); PRIM_SUCCEEDED; } UNPOP (1); PRIM_FAILED; } /* FloatD timesTwoPower: */ primitive VMpr_FloatD_timesTwoPower [succeed,fail] { OOP oop1; OOP oop2; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = POP_OOP (); if (RECEIVER_IS_CLASS (oop1, _gst_floatd_class) && IS_INT (oop2)) { double farg1; intptr_t iarg2; farg1 = FLOATD_OOP_VALUE (oop1); iarg2 = TO_INT (oop2); PUSH_OOP (floatd_new (ldexp (farg1, iarg2))); PRIM_SUCCEEDED; } UNPOP (2); PRIM_FAILED; } /* FloatD asFloatE */ primitive VMpr_FloatD_asFloatE [checks_receiver] { OOP oop1; _gst_primitives_executed++; oop1 = POP_OOP (); if COMMON (RECEIVER_IS_CLASS (oop1, _gst_floatd_class)) { PUSH_OOP (floate_new (FLOATD_OOP_VALUE (oop1))); PRIM_SUCCEEDED; } UNPOP (1); PRIM_FAILED; } /* FloatD asFloatQ */ primitive VMpr_FloatD_asFloatQ [checks_receiver] { OOP oop1; _gst_primitives_executed++; oop1 = POP_OOP (); if COMMON (RECEIVER_IS_CLASS (oop1, _gst_floatd_class)) { PUSH_OOP (floatq_new (FLOATD_OOP_VALUE (oop1))); PRIM_SUCCEEDED; } UNPOP (1); PRIM_FAILED; } primitive VMpr_FloatE_arith : prim_id VMpr_FloatE_plus [succeed,fail], prim_id VMpr_FloatE_minus [succeed,fail], prim_id VMpr_FloatE_lt [succeed,fail], prim_id VMpr_FloatE_gt [succeed,fail], prim_id VMpr_FloatE_le [succeed,fail], prim_id VMpr_FloatE_ge [succeed,fail], prim_id VMpr_FloatE_eq [succeed,fail], prim_id VMpr_FloatE_ne [succeed,fail], prim_id VMpr_FloatE_times [succeed,fail], prim_id VMpr_FloatE_divide [succeed,fail] { double farg2; OOP oop1; OOP oop2; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = POP_OOP (); if (IS_CLASS (oop2, _gst_floate_class)) farg2 = FLOATE_OOP_VALUE (oop2); else if (IS_INT (oop2)) farg2 = (double) TO_INT (oop2); else { UNPOP (2); PRIM_FAILED; } if COMMON (RECEIVER_IS_CLASS (oop1, _gst_floate_class)) { double farg1; farg1 = FLOATE_OOP_VALUE (oop1); switch (id) { case prim_id (VMpr_FloatE_plus): PUSH_OOP (floate_new (farg1 + farg2)); break; case prim_id (VMpr_FloatE_minus): PUSH_OOP (floate_new (farg1 - farg2)); break; case prim_id (VMpr_FloatE_lt): PUSH_BOOLEAN (farg1 < farg2); break; case prim_id (VMpr_FloatE_gt): PUSH_BOOLEAN (farg1 > farg2); break; case prim_id (VMpr_FloatE_le): PUSH_BOOLEAN (farg1 <= farg2); break; case prim_id (VMpr_FloatE_ge): PUSH_BOOLEAN (farg1 >= farg2); break; case prim_id (VMpr_FloatE_eq): PUSH_BOOLEAN (farg1 == farg2); break; case prim_id (VMpr_FloatE_ne): PUSH_BOOLEAN (farg1 != farg2); break; case prim_id (VMpr_FloatE_times): PUSH_OOP (floate_new (farg1 * farg2)); break; case prim_id (VMpr_FloatE_divide): PUSH_OOP (floate_new (farg1 / farg2)); break; } PRIM_SUCCEEDED; } UNPOP (2); PRIM_FAILED; } /* FloatD truncated */ primitive VMpr_FloatE_truncated [succeed,fail] { OOP oop1; _gst_primitives_executed++; oop1 = POP_OOP (); if COMMON (RECEIVER_IS_CLASS (oop1, _gst_floate_class)) { double oopValue = FLOATE_OOP_VALUE (oop1); if COMMON (oopValue >= MIN_ST_INT && oopValue <= MAX_ST_INT) { PUSH_INT (lrintf (truncf (oopValue))); PRIM_SUCCEEDED; } } UNPOP (1); PRIM_FAILED; } /* FloatD fractionPart */ primitive VMpr_FloatE_fractionPart [checks_receiver] { OOP oop1; _gst_primitives_executed++; oop1 = POP_OOP (); if COMMON (RECEIVER_IS_CLASS (oop1, _gst_floate_class)) { double farg1; farg1 = FLOATE_OOP_VALUE (oop1); farg1 -= (farg1 < 0.0) ? ceil (farg1) : floor (farg1); PUSH_OOP (floate_new (farg1)); PRIM_SUCCEEDED; } UNPOP (1); PRIM_FAILED; } /* FloatD exponent */ primitive VMpr_FloatE_exponent [checks_receiver,return_small_smallinteger] { OOP oop1; _gst_primitives_executed++; oop1 = POP_OOP (); if COMMON (RECEIVER_IS_CLASS (oop1, _gst_floate_class)) { double farg1; int intArg1; farg1 = FLOATE_OOP_VALUE (oop1); if (farg1 == 0.0) intArg1 = 1; else { frexp (FLOATE_OOP_VALUE (oop1), &intArg1); intArg1--; } PUSH_INT (intArg1); PRIM_SUCCEEDED; } UNPOP (1); PRIM_FAILED; } /* FloatD timesTwoPower: */ primitive VMpr_FloatE_timesTwoPower [succeed,fail] { OOP oop1; OOP oop2; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = POP_OOP (); if (RECEIVER_IS_CLASS (oop1, _gst_floate_class) && IS_INT (oop2)) { double farg1; intptr_t iarg2; farg1 = FLOATE_OOP_VALUE (oop1); iarg2 = TO_INT (oop2); PUSH_OOP (floate_new (ldexp (farg1, iarg2))); PRIM_SUCCEEDED; } UNPOP (2); PRIM_FAILED; } /* FloatE asFloatD */ primitive VMpr_FloatE_asFloatD [checks_receiver] { OOP oop1; _gst_primitives_executed++; oop1 = POP_OOP (); if COMMON (RECEIVER_IS_CLASS (oop1, _gst_floate_class)) { PUSH_OOP (floatd_new (FLOATE_OOP_VALUE (oop1))); PRIM_SUCCEEDED; } UNPOP (1); PRIM_FAILED; } /* FloatD asFloatQ */ primitive VMpr_FloatE_asFloatQ [checks_receiver] { OOP oop1; _gst_primitives_executed++; oop1 = POP_OOP (); if COMMON (RECEIVER_IS_CLASS (oop1, _gst_floate_class)) { PUSH_OOP (floatq_new (FLOATE_OOP_VALUE (oop1))); PRIM_SUCCEEDED; } UNPOP (1); PRIM_FAILED; } primitive VMpr_FloatQ_arith : prim_id VMpr_FloatQ_plus [succeed,fail], prim_id VMpr_FloatQ_minus [succeed,fail], prim_id VMpr_FloatQ_lt [succeed,fail], prim_id VMpr_FloatQ_gt [succeed,fail], prim_id VMpr_FloatQ_le [succeed,fail], prim_id VMpr_FloatQ_ge [succeed,fail], prim_id VMpr_FloatQ_eq [succeed,fail], prim_id VMpr_FloatQ_ne [succeed,fail], prim_id VMpr_FloatQ_times [succeed,fail], prim_id VMpr_FloatQ_divide [succeed,fail] { long double farg2; OOP oop1; OOP oop2; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = POP_OOP (); if (IS_CLASS (oop2, _gst_floatq_class)) farg2 = FLOATQ_OOP_VALUE (oop2); else if (IS_INT (oop2)) farg2 = (long double) TO_INT (oop2); else { UNPOP (2); PRIM_FAILED; } if COMMON (RECEIVER_IS_CLASS (oop1, _gst_floatq_class)) { long double farg1; farg1 = FLOATQ_OOP_VALUE (oop1); switch (id) { case prim_id (VMpr_FloatQ_plus): PUSH_OOP (floatq_new (farg1 + farg2)); break; case prim_id (VMpr_FloatQ_minus): PUSH_OOP (floatq_new (farg1 - farg2)); break; case prim_id (VMpr_FloatQ_lt): PUSH_BOOLEAN (farg1 < farg2); break; case prim_id (VMpr_FloatQ_gt): PUSH_BOOLEAN (farg1 > farg2); break; case prim_id (VMpr_FloatQ_le): PUSH_BOOLEAN (farg1 <= farg2); break; case prim_id (VMpr_FloatQ_ge): PUSH_BOOLEAN (farg1 >= farg2); break; case prim_id (VMpr_FloatQ_eq): PUSH_BOOLEAN (farg1 == farg2); break; case prim_id (VMpr_FloatQ_ne): PUSH_BOOLEAN (farg1 != farg2); break; case prim_id (VMpr_FloatQ_times): PUSH_OOP (floatq_new (farg1 * farg2)); break; case prim_id (VMpr_FloatQ_divide): PUSH_OOP (floatq_new (farg1 / farg2)); break; } PRIM_SUCCEEDED; } UNPOP (2); PRIM_FAILED; } /* FloatD truncated */ primitive VMpr_FloatQ_truncated [succeed,fail] { OOP oop1; _gst_primitives_executed++; oop1 = POP_OOP (); if COMMON (RECEIVER_IS_CLASS (oop1, _gst_floatq_class)) { long double oopValue = FLOATQ_OOP_VALUE (oop1); if COMMON (oopValue >= MIN_ST_INT && oopValue <= MAX_ST_INT) { PUSH_INT (lrintl (truncl (oopValue))); PRIM_SUCCEEDED; } } UNPOP (1); PRIM_FAILED; } /* FloatD fractionPart */ primitive VMpr_FloatQ_fractionPart [checks_receiver] { OOP oop1; _gst_primitives_executed++; oop1 = POP_OOP (); if COMMON (RECEIVER_IS_CLASS (oop1, _gst_floatq_class)) { long double farg1; farg1 = FLOATQ_OOP_VALUE (oop1); farg1 -= (farg1 < 0.0) ? ceill (farg1) : floorl (farg1); PUSH_OOP (floatq_new (farg1)); PRIM_SUCCEEDED; } UNPOP (1); PRIM_FAILED; } /* FloatD exponent */ primitive VMpr_FloatQ_exponent [checks_receiver,return_small_smallinteger] { OOP oop1; _gst_primitives_executed++; oop1 = POP_OOP (); if COMMON (RECEIVER_IS_CLASS (oop1, _gst_floatq_class)) { long double farg1; int intArg1; farg1 = FLOATQ_OOP_VALUE (oop1); if (farg1 == 0.0) intArg1 = 1; else { frexpl (FLOATQ_OOP_VALUE (oop1), &intArg1); intArg1--; } PUSH_INT (intArg1); PRIM_SUCCEEDED; } UNPOP (1); PRIM_FAILED; } /* FloatD timesTwoPower: */ primitive VMpr_FloatQ_timesTwoPower [succeed,fail] { OOP oop1; OOP oop2; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = POP_OOP (); if (RECEIVER_IS_CLASS (oop1, _gst_floatq_class) && IS_INT (oop2)) { long double farg1; intptr_t iarg2; farg1 = FLOATQ_OOP_VALUE (oop1); iarg2 = TO_INT (oop2); PUSH_OOP (floatq_new (ldexpl (farg1, iarg2))); PRIM_SUCCEEDED; } UNPOP (2); PRIM_FAILED; } /* FloatQ asFloatD */ primitive VMpr_FloatQ_asFloatD [checks_receiver] { OOP oop1; _gst_primitives_executed++; oop1 = POP_OOP (); if COMMON (RECEIVER_IS_CLASS (oop1, _gst_floatq_class)) { PUSH_OOP (floatd_new (FLOATQ_OOP_VALUE (oop1))); PRIM_SUCCEEDED; } UNPOP (1); PRIM_FAILED; } /* FloatD asFloatQ */ primitive VMpr_FloatQ_asFloatE [checks_receiver] { OOP oop1; _gst_primitives_executed++; oop1 = POP_OOP (); if COMMON (RECEIVER_IS_CLASS (oop1, _gst_floatq_class)) { PUSH_OOP (floate_new (FLOATQ_OOP_VALUE (oop1))); PRIM_SUCCEEDED; } UNPOP (1); PRIM_FAILED; } /* Object at:, Object basicAt: */ primitive VMpr_Object_basicAt = 60 [succeed,fail,inlined] { OOP oop1; OOP oop2; _gst_primitives_executed++; POP_N_OOPS (numArgs - 1); oop2 = POP_OOP (); oop1 = STACKTOP (); if COMMON (IS_INT (oop2)) { intptr_t arg2; arg2 = TO_INT (oop2); oop1 = index_oop (oop1, arg2); if COMMON (oop1) { SET_STACKTOP (oop1); PRIM_SUCCEEDED; } } UNPOP (numArgs); PRIM_FAILED; } /* Object at:put:, Object basicAt:put: */ primitive VMpr_Object_basicAtPut = 61 [succeed,fail,inlined] { OOP oop1; OOP oop2; OOP oop3; _gst_primitives_executed++; oop3 = POP_OOP (); oop2 = POP_OOP (); oop1 = STACKTOP (); if COMMON (IS_INT (oop2) && !IS_OOP_READONLY (oop1)) { intptr_t arg2; arg2 = TO_INT (oop2); if COMMON (index_oop_put (oop1, arg2, oop3)) { SET_STACKTOP (oop3); PRIM_SUCCEEDED; } } UNPOP (2); PRIM_FAILED; } /* Object basicSize; Object size; String size */ primitive VMpr_Object_basicSize = 62 [succeed,return_small_smallinteger,inlined] { OOP oop1; _gst_primitives_executed++; oop1 = POP_OOP (); PUSH_INT (NUM_INDEXABLE_FIELDS (oop1)); PRIM_SUCCEEDED; } /* CharacterArray valueAt: */ primitive VMpr_CharacterArray_valueAt = 60 [succeed,fail] { OOP oop1; OOP oop2; intptr_t spec; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = STACKTOP (); spec = CLASS_INSTANCE_SPEC (OOP_CLASS (oop1)); switch (spec & ISP_INDEXEDVARS) { case GST_ISP_CHARACTER: spec ^= GST_ISP_CHARACTER ^ GST_ISP_UCHAR; break; case GST_ISP_UTF32: spec ^= GST_ISP_UTF32 ^ GST_ISP_UINT; break; default: UNPOP (1); PRIM_FAILED; } if COMMON (IS_INT (oop2)) { intptr_t arg2; arg2 = TO_INT (oop2); oop1 = index_oop_spec (oop1, OOP_TO_OBJ (oop1), arg2, spec); if COMMON (oop1) { SET_STACKTOP (oop1); PRIM_SUCCEEDED; } } UNPOP (1); PRIM_FAILED; } /* CharacterArray valueAt:put: */ primitive VMpr_CharacterArray_valueAtPut = 61 [succeed,fail,inlined] { OOP oop1; OOP oop2; OOP oop3; intptr_t spec; _gst_primitives_executed++; oop3 = POP_OOP (); oop2 = POP_OOP (); oop1 = STACKTOP (); spec = CLASS_INSTANCE_SPEC (OOP_CLASS (oop1)); switch (spec & ISP_INDEXEDVARS) { case GST_ISP_CHARACTER: spec ^= GST_ISP_CHARACTER ^ GST_ISP_UCHAR; break; case GST_ISP_UTF32: spec ^= GST_ISP_UTF32 ^ GST_ISP_UINT; break; default: UNPOP (2); PRIM_FAILED; } if COMMON (IS_INT (oop2) && !IS_OOP_READONLY (oop1)) { intptr_t arg2; arg2 = TO_INT (oop2); if COMMON (index_oop_put_spec (oop1, OOP_TO_OBJ (oop1), arg2, oop3, spec)) { SET_STACKTOP (oop3); PRIM_SUCCEEDED; } } UNPOP (2); PRIM_FAILED; } /* CompiledCode verificationResult */ primitive VMpr_CompiledCode_verificationResult [succeed] { OOP oop1 = STACKTOP (); const char *result = _gst_verify_method (oop1, NULL, 0); OOP resultOOP = result ? _gst_string_new (result) : _gst_nil_oop; SET_STACKTOP (resultOOP); PRIM_SUCCEEDED; } /* CompiledBlock numArgs:numTemps:bytecodes:depth:literals: */ primitive VMpr_CompiledBlock_create [succeed] { OOP *_gst_literals = OOP_TO_OBJ (STACK_AT (0))->data; int depth = TO_INT (STACK_AT (1)); OOP bytecodesOOP = STACK_AT (2); int blockTemps = TO_INT (STACK_AT (3)); int blockArgs = TO_INT (STACK_AT (4)); bc_vector bytecodes = _gst_extract_bytecodes (bytecodesOOP); OOP block = _gst_block_new (blockArgs, blockTemps, bytecodes, depth, _gst_literals); POP_N_OOPS (5); OOP_CLASS(block) = STACKTOP (); _gst_primitives_executed++; SET_STACKTOP (block); PRIM_SUCCEEDED; } /* CompiledMethod literals:numArgs:numTemps:attributes:bytecodes:depth: */ primitive VMpr_CompiledMethod_create [succeed,fail] { int depth = TO_INT (STACK_AT (0)); OOP bytecodesOOP = STACK_AT (1); OOP attributesOOP = STACK_AT (2); int methodTemps = TO_INT (STACK_AT (3)); int methodArgs = TO_INT (STACK_AT (4)); OOP literals = STACK_AT (5); bc_vector bytecodes = _gst_extract_bytecodes (bytecodesOOP); int primitive = _gst_process_attributes_array (attributesOOP); OOP method; if (primitive == -1) PRIM_FAILED; method = _gst_make_new_method (primitive, methodArgs, methodTemps, depth, literals, bytecodes, _gst_nil_oop, _gst_nil_oop, _gst_nil_oop, -1, -1); POP_N_OOPS(6); OOP_CLASS(method) = STACKTOP (); _gst_primitives_executed++; SET_STACKTOP (method); PRIM_SUCCEEDED; } /* Object shallowCopy */ primitive VMpr_Object_shallowCopy [succeed] { OOP oop1; _gst_primitives_executed++; oop1 = STACKTOP (); oop1 = _gst_object_copy (oop1); SET_STACKTOP (oop1); PRIM_SUCCEEDED; } /* Behavior basicNew; Behavior new; */ primitive VMpr_Behavior_basicNew = 70 [succeed,fail,inlined] { OOP oop1; _gst_primitives_executed++; oop1 = STACKTOP (); if COMMON (RECEIVER_IS_OOP (oop1)) { if COMMON (!CLASS_IS_INDEXABLE (oop1)) { /* Note: you cannot pass &STACKTOP() because if the stack moves it ain't valid anymore by the time it is set!!! */ OOP result; instantiate (oop1, &result); SET_STACKTOP (result); PRIM_SUCCEEDED; } } PRIM_FAILED; } /* Behavior new:; Behavior basicNew: */ primitive VMpr_Behavior_basicNewColon = 71 [succeed,fail,inlined] { OOP oop1; OOP oop2; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = STACKTOP (); if COMMON (RECEIVER_IS_OOP (oop1) && IS_INT (oop2)) { if COMMON (CLASS_IS_INDEXABLE (oop1)) { intptr_t arg2; arg2 = TO_INT (oop2); if (arg2 >= 0) { OOP result; instantiate_with (oop1, arg2, &result); SET_STACKTOP (result); PRIM_SUCCEEDED; } } } UNPOP (1); PRIM_FAILED; } /* Object become: */ primitive VMpr_Object_become [succeed,fail] { OOP oop1; OOP oop2; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = STACKTOP (); if COMMON (!IS_OOP_READONLY (oop1) && !IS_OOP_READONLY (oop2)) { _gst_swap_objects (oop1, oop2); PRIM_SUCCEEDED; } UNPOP (1); PRIM_FAILED; } /* Object instVarAt: */ primitive VMpr_Object_instVarAt = 73 [succeed,fail,inlined] { OOP oop1; OOP oop2; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = STACKTOP (); if COMMON (IS_INT (oop2)) { intptr_t arg2; arg2 = TO_INT (oop2); if COMMON (CHECK_BOUNDS_OF (oop1, arg2)) { SET_STACKTOP (inst_var_at (oop1, arg2)); PRIM_SUCCEEDED; } } UNPOP (1); PRIM_FAILED; } /* Object inst_var_at:put: */ primitive VMpr_Object_instVarAtPut = 74 [succeed,fail,inlined] { OOP oop1; OOP oop2; OOP oop3; _gst_primitives_executed++; oop3 = POP_OOP (); oop2 = POP_OOP (); oop1 = STACKTOP (); if COMMON (IS_INT (oop2)) { intptr_t arg2; arg2 = TO_INT (oop2); if COMMON (CHECK_BOUNDS_OF (oop1, arg2)) { inst_var_at_put (oop1, arg2, oop3); PRIM_SUCCEEDED; } } UNPOP (2); PRIM_FAILED; } /* Object asOop; Object hash; Symbol hash */ primitive VMpr_Object_hash [succeed,fail] { OOP oop1; _gst_primitives_executed++; oop1 = POP_OOP (); if COMMON (IS_OOP (oop1)) { PUSH_INT (OOP_INDEX (oop1)); PRIM_SUCCEEDED; } UNPOP (1); PRIM_FAILED; } /* SmallInteger asObject; SmallInteger asObjectNoFail */ primitive VMpr_SmallInteger_asObject [succeed,fail] { OOP oop1; intptr_t arg1; _gst_primitives_executed++; oop1 = STACKTOP (); arg1 = TO_INT (oop1); if COMMON (OOP_INDEX_VALID (arg1)) { oop1 = OOP_AT (arg1); if (!IS_OOP_VALID (oop1)) oop1 = _gst_nil_oop; SET_STACKTOP (oop1); PRIM_SUCCEEDED; } PRIM_FAILED; } /* SmallInteger nextValidOop */ primitive VMpr_SmallInteger_nextValidOop [succeed,fail] { OOP oop1; intptr_t arg1; _gst_primitives_executed++; oop1 = STACKTOP (); arg1 = TO_INT (oop1); while (OOP_INDEX_VALID (++arg1)) { oop1 = OOP_AT (arg1); if (IS_OOP_VALID (oop1)) { SET_STACKTOP_INT (arg1); PRIM_SUCCEEDED; } } PRIM_FAILED; } /* Behavior someInstance */ primitive VMpr_Behavior_someInstance [succeed,fail] { OOP oop1; OOP oop2, lastOOP; _gst_primitives_executed++; oop1 = STACKTOP (); PREFETCH_START (_gst_mem.ot_base, PREF_READ | PREF_NTA); for (oop2 = _gst_mem.ot_base, lastOOP = &_gst_mem.ot[_gst_mem.ot_size]; oop2 < lastOOP; oop2++) { PREFETCH_LOOP (oop2, PREF_READ | PREF_NTA); if UNCOMMON (IS_OOP_VALID (oop2) && oop1 == OOP_CLASS (oop2)) { SET_STACKTOP (oop2); PRIM_SUCCEEDED; } } PRIM_FAILED; } /* Object nextInstance */ primitive VMpr_Object_nextInstance [succeed,fail] { OOP oop1; _gst_primitives_executed++; oop1 = STACKTOP (); if (OOP_CLASS (oop1) == _gst_char_class) { /* Characters are one after another - at the end there is _gst_nil_oop */ oop1++; if (_gst_char_class == OOP_CLASS (oop1)) { SET_STACKTOP (oop1); PRIM_SUCCEEDED; } } else if (IS_OOP (oop1) && oop1 >= _gst_mem.ot) { /* There is just one copy of all other builtin objects, so fail for a builtin */ OOP class_oop = OOP_CLASS (oop1); for (++oop1; oop1 <= _gst_mem.last_allocated_oop; oop1++) { PREFETCH_LOOP (oop1, PREF_READ | PREF_NTA); if (IS_OOP_VALID (oop1) && class_oop == OOP_CLASS (oop1)) { SET_STACKTOP (oop1); PRIM_SUCCEEDED; } } } PRIM_FAILED; } /* Object becomeForward: */ primitive VMpr_Object_becomeForward [succeed] { OOP oop1, ownerOOP; OOP oop2, lastOOP; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = STACKTOP (); if COMMON (IS_INT (oop1) || IS_OOP_READONLY (oop1)) { UNPOP (1); PRIM_FAILED; } /* Search also on LIFO contexts. */ empty_context_stack (); PREFETCH_START (_gst_mem.ot_base, PREF_READ | PREF_NTA); for (ownerOOP = _gst_mem.ot_base, lastOOP = &_gst_mem.ot[_gst_mem.ot_size]; ownerOOP < lastOOP; ownerOOP++) { gst_object object; OOP *scanPtr; int n; PREFETCH_LOOP (ownerOOP, PREF_READ | PREF_NTA); if COMMON (!IS_OOP_VALID (ownerOOP)) continue; object = OOP_TO_OBJ (ownerOOP); n = num_valid_oops (ownerOOP); if UNCOMMON (object->objClass == oop1) object->objClass = oop2; for (scanPtr = object->data; n--; scanPtr++) if UNCOMMON (*scanPtr == oop1) *scanPtr = oop2; } /* The above loop changed the reference to oop1 in the stacktop, so we have to set it back manually! */ SET_STACKTOP (oop1); PRIM_SUCCEEDED; } /* Object allOwners */ primitive VMpr_Object_allOwners [succeed] { OOP oop1; OOP oop2, lastOOP; OOP result; gst_object object; _gst_primitives_executed++; oop1 = STACKTOP (); _gst_reset_buffer (); PREFETCH_START (_gst_mem.ot_base, PREF_READ | PREF_NTA); for (oop2 = _gst_mem.ot_base, lastOOP = &_gst_mem.ot[_gst_mem.ot_size]; oop2 < lastOOP; oop2++) { PREFETCH_LOOP (oop2, PREF_READ | PREF_NTA); if UNCOMMON (IS_OOP_VALID (oop2) && is_owner(oop2, oop1)) _gst_add_buf_pointer (oop2); } object = new_instance_with (_gst_array_class, _gst_buffer_size() / sizeof (PTR), &result); _gst_copy_buffer (object->data); SET_STACKTOP (result); PRIM_SUCCEEDED; } primitive VMpr_ContextPart_thisContext [succeed] { _gst_primitives_executed++; empty_context_stack (); SET_STACKTOP (_gst_this_context_oop); PRIM_SUCCEEDED; } primitive VMpr_ContextPart_continue [checks_receiver,reload_ip] { OOP oop2; OOP oop1; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = STACKTOP (); if COMMON (RECEIVER_IS_A_KIND_OF (OOP_CLASS (oop1), _gst_context_part_class)) { unwind_to (oop1); SET_STACKTOP (oop2); PRIM_SUCCEEDED_RELOAD_IP; } else { UNPOP (1); PRIM_FAILED; } } /* Continuation resume:nextContinuation: */ primitive VMpr_Continuation_resume [fail,reload_ip] { OOP oop1, oop2, oop3; _gst_primitives_executed++; oop3 = POP_OOP (); oop2 = POP_OOP (); oop1 = STACKTOP (); if COMMON (RECEIVER_IS_A_KIND_OF (OOP_CLASS (oop1), _gst_continuation_class)) { gst_continuation cc = (gst_continuation) OOP_TO_OBJ (oop1); if (COMMON (!IS_NIL (cc->stack))) { resume_suspended_context (cc->stack); cc->stack = oop3; SET_STACKTOP (oop2); PRIM_SUCCEEDED_RELOAD_IP; } } UNPOP (2); PRIM_FAILED; } /* BlockClosure value BlockClosure value: BlockClosure value:value: BlockClosure value:value:value: */ primitive VMpr_BlockClosure_value [fail,reload_ip,cache_new_ip] { _gst_primitives_executed++; if UNCOMMON (send_block_value (numArgs, 0)) PRIM_FAILED; else PRIM_SUCCEEDED_RELOAD_IP; } /* BlockClosure cull: BlockClosure cull:cull: BlockClosure cull:cull:cull: */ primitive VMpr_BlockClosure_cull [fail,reload_ip] { _gst_primitives_executed++; if UNCOMMON (send_block_value (numArgs, numArgs)) PRIM_FAILED; else PRIM_SUCCEEDED_RELOAD_IP; } /* We cannot cache the IP here, otherwise calls to #valueAndResumeOnUnwind don't actually make the context an unwind context. If we make a provision for that in xlat.c, we can set the cache_new_ip attribute. */ primitive VMpr_BlockClosure_valueAndResumeOnUnwind [fail,reload_ip] { gst_method_context context; _gst_primitives_executed++; context = (gst_method_context) OOP_TO_OBJ (_gst_this_context_oop); context->flags |= MCF_IS_UNWIND_CONTEXT; if UNCOMMON (send_block_value (numArgs, 0)) PRIM_FAILED; else PRIM_SUCCEEDED_RELOAD_IP; } /* BlockClosure valueWithArguments: */ primitive VMpr_BlockClosure_valueWithArguments [fail,reload_ip] { OOP oop1; OOP oop2; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = STACKTOP (); if (IS_CLASS (oop2, _gst_array_class)) { int i; numArgs = NUM_INDEXABLE_FIELDS (oop2); for (i = 1; i <= numArgs; i++) PUSH_OOP (ARRAY_AT (oop2, i)); if UNCOMMON (send_block_value (numArgs, 0)) { POP_N_OOPS (numArgs); PUSH_OOP (oop2); PRIM_FAILED; } else PRIM_SUCCEEDED_RELOAD_IP; } UNPOP (1); PRIM_FAILED; } /* Object perform: Object perform:with: Object perform:with:with: Object perform:with:with:with: */ primitive VMpr_Object_perform [fail,reload_ip] { OOP oop1; OOP *oopVec = alloca (numArgs * sizeof (OOP)); int i; _gst_primitives_executed++; /* pop off the arguments (if any) */ numArgs--; for (i = 0; i < numArgs; i++) oopVec[i] = POP_OOP (); oop1 = POP_OOP (); /* the selector */ if COMMON (IS_CLASS (oop1, _gst_symbol_class) && check_send_correctness (STACKTOP (), oop1, numArgs)) { /* push the args back onto the stack */ while (--i >= 0) PUSH_OOP (oopVec[i]); SEND_MESSAGE (oop1, numArgs); PRIM_SUCCEEDED_RELOAD_IP; } if COMMON (is_a_kind_of (OOP_CLASS (oop1), _gst_compiled_method_class)) { gst_compiled_method method; method_header header; method = (gst_compiled_method) OOP_TO_OBJ (oop1); header = method->header; if (header.numArgs == numArgs) { /* push the args back onto the stack */ while (--i >= 0) PUSH_OOP (oopVec[i]); _gst_send_method (oop1); PRIM_SUCCEEDED_RELOAD_IP; } } UNPOP (numArgs + 1); PRIM_FAILED; } /* Object perform:withArguments: */ primitive VMpr_Object_performWithArguments [fail,reload_ip] { OOP oop1; OOP oop2; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = POP_OOP (); numArgs = NUM_INDEXABLE_FIELDS (oop2); if UNCOMMON (!IS_CLASS (oop2, _gst_array_class)) /* fall through to UNPOP and PRIM_FAILED */ ; else if COMMON (IS_CLASS (oop1, _gst_symbol_class) && check_send_correctness (STACKTOP (), oop1, numArgs)) { int i; for (i = 1; i <= numArgs; i++) PUSH_OOP (ARRAY_AT (oop2, i)); SEND_MESSAGE (oop1, numArgs); PRIM_SUCCEEDED_RELOAD_IP; } else if COMMON (is_a_kind_of (OOP_CLASS (oop1), _gst_compiled_method_class)) { gst_compiled_method method; method_header header; method = (gst_compiled_method) OOP_TO_OBJ (oop1); header = method->header; if COMMON (header.numArgs == numArgs) { int i; for (i = 1; i <= numArgs; i++) PUSH_OOP (ARRAY_AT (oop2, i)); _gst_send_method (oop1); PRIM_SUCCEEDED_RELOAD_IP; } } UNPOP (2); PRIM_FAILED; } /* Semaphore notifyAll */ primitive VMpr_Semaphore_notifyAll [succeed,check_interrupt] { OOP oop1; _gst_primitives_executed++; oop1 = STACKTOP (); while (_gst_sync_signal (oop1, false)) ; PRIM_SUCCEEDED; } /* Semaphore signal (id = 0) or Semaphore notify (id = 1) */ primitive VMpr_Semaphore_signalNotify : prim_id VMpr_Semaphore_signal [succeed,check_interrupt], prim_id VMpr_Semaphore_notify [succeed,check_interrupt] { OOP oop1; _gst_primitives_executed++; oop1 = STACKTOP (); _gst_sync_signal (oop1, id == prim_id (VMpr_Semaphore_signal)); PRIM_SUCCEEDED; } /* Semaphore wait lock */ primitive VMpr_Semaphore_lock [succeed,check_interrupt] { OOP oop1; gst_semaphore sem; _gst_primitives_executed++; oop1 = STACKTOP (); sem = (gst_semaphore) OOP_TO_OBJ (oop1); SET_STACKTOP_BOOLEAN (TO_INT (sem->signals) > 0); sem->signals = FROM_INT (0); PRIM_SUCCEEDED; } /* Semaphore wait */ primitive VMpr_Semaphore_wait [succeed,check_interrupt] { OOP oop1; _gst_primitives_executed++; oop1 = STACKTOP (); _gst_sync_wait (oop1); PRIM_SUCCEEDED; } /* Semaphore waitAfterSignalling: aSemaphore */ primitive VMpr_Semaphore_waitAfterSignalling [succeed,check_interrupt] { OOP oop1, oop2; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = STACKTOP (); _gst_sync_signal (oop2, true); _gst_sync_wait (oop1); PRIM_SUCCEEDED; } /* Process suspend */ primitive VMpr_Process_suspend [succeed,check_interrupt] { OOP oop1; _gst_primitives_executed++; oop1 = STACKTOP (); suspend_process (oop1); PRIM_SUCCEEDED; } /* Process resume */ primitive VMpr_Process_resume [succeed,fail,check_interrupt] { OOP oop1; _gst_primitives_executed++; oop1 = STACKTOP (); if (resume_process (oop1, false)) PRIM_SUCCEEDED; else PRIM_FAILED; } /* Process singleStepWaitingOn: */ primitive VMpr_Process_singleStepWaitingOn [succeed] { OOP oop1; OOP oop2; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = POP_OOP (); if (is_process_ready (oop1) || is_process_terminating (oop1)) { UNPOP (2); PRIM_FAILED; } /* Put the current process to sleep, switch execution to the new one, and set up the VM to signal the semaphore as soon as possible. */ _gst_sync_wait (oop2); resume_process (oop1, true); single_step_semaphore = oop2; PRIM_SUCCEEDED; } /* Process yield */ primitive VMpr_Process_yield [succeed,check_interrupt] { OOP oop1; _gst_primitives_executed++; oop1 = STACKTOP (); if (oop1 == get_active_process ()) { SET_STACKTOP (_gst_nil_oop); /* this is our return value */ active_process_yield (); } PRIM_SUCCEEDED; } /* Processor pause: waitForSignal */ primitive VMpr_Processor_pause [succeed,check_interrupt] { OOP oop1; _gst_primitives_executed++; oop1 = POP_OOP (); if (would_reschedule_process ()) { if (oop1 == _gst_true_oop) _gst_pause (); else _gst_usleep (20000); } active_process_yield (); PRIM_SUCCEEDED; } /* Behavior flushCache */ primitive VMpr_Behavior_flushCache [succeed] { _gst_primitives_executed++; _gst_invalidate_method_cache (); PRIM_SUCCEEDED; } /* CompiledCode discardTranslation */ primitive VMpr_CompiledCode_discardTranslation [succeed] { _gst_primitives_executed++; #ifdef ENABLE_JIT_TRANSLATION _gst_discard_native_code (STACKTOP ()); #endif PRIM_SUCCEEDED; } /* Object changeClassTo: */ primitive VMpr_Object_changeClassTo [succeed,fail] { OOP oop1, oop2; gst_object obj1, obj2; _gst_primitives_executed++; oop1 = POP_OOP (); oop2 = STACKTOP (); obj1 = OOP_TO_OBJ (oop1); obj2 = OOP_TO_OBJ (oop2); if (NUM_WORDS (obj1) > 0 && !IS_INT (obj1->data[0]) && (IS_NIL (obj1->data[0]) || is_a_kind_of (OOP_CLASS (obj1->data[0]), _gst_behavior_class))) { obj2->objClass = oop1; PRIM_SUCCEEDED; } UNPOP (1); /* trying to do Bad Things */ PRIM_FAILED; } /* Time class timezoneBias */ primitive VMpr_Time_timezoneBias [succeed] { OOP oop1; uint64_t t; _gst_primitives_executed++; if (numArgs == 1) { if (!is_c_int_64 (STACKTOP ())) PRIM_FAILED; oop1 = POP_OOP (); /* 25202 = days between 1901 and 1970 */ t = to_c_int_64 (oop1) - (int64_t)86400 * 25202; t = _gst_adjust_time_zone (t) - t; SET_STACKTOP_INT (t); } else SET_STACKTOP_INT (_gst_current_time_zone_bias ()); PRIM_SUCCEEDED; } /* Time class timezone */ primitive VMpr_Time_timezone [succeed] { OOP oop1; char *result; _gst_primitives_executed++; result = _gst_current_time_zone_name (); oop1 = _gst_string_new (result); SET_STACKTOP (oop1); xfree (result); PRIM_SUCCEEDED; } /* Time class secondClock -- note: this primitive has different semantics from those defined in the book. This primitive returns the seconds since/to Jan 1, 2000 00:00:00 instead of Jan 1,1901. */ primitive VMpr_Time_secondClock [succeed] { _gst_primitives_executed++; /* 10957 = days between 1970 and 2000 */ SET_STACKTOP_INT (_gst_get_time () - 86400 * 10957); PRIM_SUCCEEDED; } /* Time class nanosecondClock. */ primitive VMpr_Time_nanosecondClock [succeed] { OOP nsOOP; uint64_t ns; _gst_primitives_executed++; ns = _gst_get_ns_time (); nsOOP = from_c_int_64 (ns); SET_STACKTOP (nsOOP); PRIM_SUCCEEDED; } /* Time class millisecondClock. */ primitive VMpr_Time_millisecondClock [succeed] { OOP milliOOP; uint64_t milli; _gst_primitives_executed++; milli = _gst_get_milli_time (); milliOOP = from_c_int_64 (milli); SET_STACKTOP (milliOOP); PRIM_SUCCEEDED; } /* Processor signal: semaphore atMilliseconds: deltaMilliseconds Processor signal: semaphore atNanosecondClockValue: absNanoseconds */ primitive VMpr_Processor_signalAt : prim_id VMpr_Processor_signalAtMilliseconds [succeed,fail,check_interrupt], prim_id VMpr_Processor_signalAtNanosecondClockValue [succeed,fail,check_interrupt] { OOP oop1; OOP oop2; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = POP_OOP (); if (is_c_int_64 (oop2)) { int64_t arg2 = to_c_int_64 (oop2); uint64_t ns = _gst_get_ns_time (); if (id == prim_id(VMpr_Processor_signalAtMilliseconds)) arg2 = (arg2 * 1000000) + ns; if (arg2 <= ns) _gst_sync_signal (oop1, true); else _gst_async_timed_wait (oop1, arg2); PRIM_SUCCEEDED; } UNPOP (2); PRIM_FAILED; } /* Processor isTimeoutProgrammed */ primitive VMpr_Processor_isTimeoutProgrammed [succeed] { _gst_primitives_executed++; SET_STACKTOP_BOOLEAN (_gst_is_timeout_programmed ()); PRIM_SUCCEEDED; } /* String similarityTo: */ primitive VMpr_String_similarityTo [succeed,fail] { int result, l1, l2; gst_uchar *s1, *s2; OOP oop1, oop2; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = STACKTOP (); if (IS_INT(oop2) || OOP_FIXED_FIELDS (oop2) || (OOP_INSTANCE_SPEC (oop2) & ISP_INDEXEDVARS) != GST_ISP_CHARACTER) PRIM_FAILED; #ifndef OPTIMIZE if (IS_INT(oop1) || OOP_FIXED_FIELDS (oop1) || (OOP_INSTANCE_SPEC (oop1) & ISP_INDEXEDVARS) != GST_ISP_CHARACTER) PRIM_FAILED; #endif s1 = STRING_OOP_CHARS (oop1); s2 = STRING_OOP_CHARS (oop2); l1 = NUM_INDEXABLE_FIELDS (oop1); l2 = NUM_INDEXABLE_FIELDS (oop2); /* Weights are: substitution, case change, insert, delete. Invert the sign so that differences are reported as negative numbers. */ result = -strnspell (s1, s2, l1, l2, 7, 3, 4, 4); SET_STACKTOP_INT (result); PRIM_SUCCEEDED; } /* String hash */ primitive VMpr_String_hash [checks_receiver] { uintptr_t hash; gst_uchar *base; OOP oop1; _gst_primitives_executed++; oop1 = STACKTOP (); #ifndef OPTIMIZE if (!CLASS_IS_SCALAR (OOP_CLASS (oop1))) PRIM_FAILED; #endif base = STRING_OOP_CHARS (oop1); hash = _gst_hash_string (base, NUM_INDEXABLE_FIELDS (oop1)); SET_STACKTOP_INT (hash); PRIM_SUCCEEDED; } /* LargeInteger = ByteArray = String = Array = */ primitive VMpr_ArrayedCollection_equal [succeed,fail] { OOP srcOOP, dstOOP; int dstLen, srcLen; gst_uchar *dstBase, *srcBase; _gst_primitives_executed++; srcOOP = POP_OOP (); dstOOP = STACKTOP (); if COMMON (OOP_INT_CLASS (srcOOP) == OOP_INT_CLASS (dstOOP)) { intptr_t spec = OOP_INSTANCE_SPEC (srcOOP); if (spec & (~0 << ISP_NUMFIXEDFIELDS)) goto bad; /* dstEnd is inclusive: (1 to: 1) has length 1 */ dstLen = NUM_INDEXABLE_FIELDS (dstOOP); srcLen = NUM_INDEXABLE_FIELDS (srcOOP); if (dstLen != srcLen) SET_STACKTOP_BOOLEAN (false); else if UNCOMMON (dstLen == 0) SET_STACKTOP_BOOLEAN (true); else { /* do the comparison */ dstBase = (gst_uchar *) OOP_TO_OBJ (dstOOP)->data; srcBase = (gst_uchar *) OOP_TO_OBJ (srcOOP)->data; dstLen <<= _gst_log2_sizes[spec & ISP_SHAPE]; SET_STACKTOP_BOOLEAN (!memcmp (dstBase, srcBase, dstLen)); } PRIM_SUCCEEDED; } bad: UNPOP (1); PRIM_FAILED; } /* ByteArray indexOf:startingAt: ByteArray indexOf:startingAt:ifAbsent: String indexOf:startingAt: String indexOf:startingAt:ifAbsent: */ primitive VMpr_ArrayedCollection_indexOfStartingAt [succeed,fail] { OOP srcIndexOOP, srcOOP, targetOOP; int srcIndex, srcLen, target; gst_uchar *srcBase, *srcTarget; _gst_primitives_executed++; POP_N_OOPS (numArgs - 2); srcIndexOOP = POP_OOP (); targetOOP = POP_OOP (); srcOOP = STACKTOP (); if COMMON ((IS_INT (targetOOP) || OOP_CLASS (targetOOP) == _gst_char_class) && IS_INT (srcIndexOOP) && !IS_INT (srcOOP)) { intptr_t srcSpec = OOP_INSTANCE_SPEC (srcOOP); if (srcSpec & (~0 << ISP_NUMFIXEDFIELDS)) goto bad; /* Check compatibility. */ if (_gst_log2_sizes[srcSpec & ISP_SHAPE] != 0) goto bad; target = IS_INT (targetOOP) ? TO_INT (targetOOP) : CHAR_OOP_VALUE (targetOOP); srcIndex = TO_INT (srcIndexOOP); srcLen = NUM_INDEXABLE_FIELDS (srcOOP) - srcIndex + 1; if UNCOMMON (srcLen < 0) goto bad; srcBase = (gst_uchar *) OOP_TO_OBJ (srcOOP)->data; srcTarget = memchr (&srcBase[srcIndex - 1], target, srcLen); if (!srcTarget) goto bad; SET_STACKTOP_INT (srcTarget - srcBase + 1); PRIM_SUCCEEDED; } bad: UNPOP (numArgs); PRIM_FAILED; } /* LargeInteger primReplaceFrom:to:with:startingAt ByteArray replaceFrom:to:withString:startingAt: String replaceFrom:to:withByteArray:startingAt: Array replaceFrom:to:with:startingAt:*/ primitive VMpr_ArrayedCollection_replaceFromToWithStartingAt [succeed,fail] { OOP srcIndexOOP, srcOOP, dstEndIndexOOP, dstStartIndexOOP, dstOOP; int dstEndIndex, dstStartIndex, srcIndex, dstLen, srcLen, dstRangeLen; gst_uchar *dstBase, *srcBase; _gst_primitives_executed++; srcIndexOOP = POP_OOP (); srcOOP = POP_OOP (); dstEndIndexOOP = POP_OOP (); dstStartIndexOOP = POP_OOP (); dstOOP = STACKTOP (); if COMMON (IS_INT (srcIndexOOP) && IS_INT (dstStartIndexOOP) && IS_INT (dstEndIndexOOP) && !IS_INT (srcOOP)) { uintptr_t srcSpec = OOP_INSTANCE_SPEC (srcOOP); uintptr_t dstSpec = OOP_INSTANCE_SPEC (dstOOP); int srcOffset = srcSpec >> ISP_NUMFIXEDFIELDS; int dstOffset = dstSpec >> ISP_NUMFIXEDFIELDS; int size; /* Assume the receiver knows what it is doing for collections that are not simple arrays. Typically the primitive will not be exposed to the user in that case. Instead, be strict when dstOffset == 0. */ if (srcOffset && !dstOffset) goto bad; /* Check compatibility. */ size = _gst_log2_sizes[srcSpec & ISP_SHAPE]; if (size != _gst_log2_sizes[dstSpec & ISP_SHAPE]) goto bad; if (((srcSpec & ISP_INDEXEDVARS) == GST_ISP_POINTER) != ((dstSpec & ISP_INDEXEDVARS) == GST_ISP_POINTER)) goto bad; /* dstEnd is inclusive: (1 to: 1) has length 1 */ dstEndIndex = TO_INT (dstEndIndexOOP); dstStartIndex = TO_INT (dstStartIndexOOP); srcIndex = TO_INT (srcIndexOOP); dstOOP = STACKTOP (); dstLen = NUM_INDEXABLE_FIELDS (dstOOP); srcLen = NUM_INDEXABLE_FIELDS (srcOOP); dstRangeLen = dstEndIndex - dstStartIndex + 1; if UNCOMMON (dstRangeLen < 0 || dstEndIndex > dstLen || dstStartIndex <= 0 || srcIndex + dstRangeLen - 1 > srcLen || (srcIndex <= 0 && dstRangeLen > 0)) goto bad; /* don't do it unless there's something to copy */ if COMMON (dstRangeLen > 0) { /* do the copy */ dstBase = (gst_uchar *) &(OOP_TO_OBJ (dstOOP)->data[dstOffset]); srcBase = (gst_uchar *) &(OOP_TO_OBJ (srcOOP)->data[srcOffset]); dstStartIndex = (dstStartIndex - 1) << size; srcIndex = (srcIndex - 1) << size; dstRangeLen <<= size; memmove (&dstBase[dstStartIndex], &srcBase[srcIndex], dstRangeLen); } PRIM_SUCCEEDED; } bad: UNPOP (4); PRIM_FAILED; } /* Object == */ primitive VMpr_Object_identity = 110 [succeed,inlined] { OOP oop1; OOP oop2; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = POP_OOP (); PUSH_BOOLEAN (oop1 == oop2); PRIM_SUCCEEDED; } /* Object class */ primitive VMpr_Object_class = 111 [succeed] { OOP oop1; _gst_primitives_executed++; oop1 = POP_OOP (); if (IS_INT (oop1)) PUSH_OOP (_gst_small_integer_class); else PUSH_OOP (OOP_CLASS (oop1)); PRIM_SUCCEEDED; } /* ------- GNU Smalltalk specific primitives begin here -------------------- */ /* quit: status Always fail because if it succeeds we don't return */ primitive VMpr_ObjectMemory_quit [fail] { OOP oop1; intptr_t arg1; _gst_primitives_executed++; oop1 = STACKTOP (); if (IS_INT (oop1)) { suspend_process (get_scheduled_process ()); fflush (stdout); fflush (stderr); _gst_invoke_hook (GST_ABOUT_TO_QUIT); arg1 = TO_INT (oop1); exit (arg1); } PRIM_FAILED; } /* abort */ primitive VMpr_ObjectMemory_abort [fail] { _gst_primitives_executed++; abort (); } /* Dictionary at: */ primitive VMpr_Dictionary_at [succeed] { OOP oop1; OOP oop2; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = STACKTOP (); SET_STACKTOP (dictionary_at (oop1, oop2)); PRIM_SUCCEEDED; } /* This is not defined in terms of #error: in a .st file because some of the required functionality may not be present when it gets first invoked, say during the loading of the first kernel files. We'll redefine it later. */ /* Object doesNotUnderstand: * Object error: */ primitive VMpr_Object_bootstrapException : prim_id VMpr_Object_bootstrapError [succeed], prim_id VMpr_Object_bootstrapDNU [succeed] { OOP oop1; OOP oop2; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = STACKTOP (); if (id == prim_id (VMpr_Object_bootstrapDNU)) printf ("%O did not understand selector %O\n\n", oop1, MESSAGE_SELECTOR (oop2)); else printf ("%O error: %#O\n\n", oop1, oop2); _gst_show_backtrace (stdout); _gst_show_stack_contents (); abort (); } /* Character class value: */ primitive VMpr_Character_create [succeed,fail] { OOP oop1; OOP oop2; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = STACKTOP (); if (IS_INT (oop2)) { intptr_t arg2; arg2 = TO_INT (oop2); if (arg2 >= 0 && arg2 <= 255) { SET_STACKTOP (CHAR_OOP_AT (arg2)); PRIM_SUCCEEDED; } } UNPOP (1); PRIM_FAILED; } /* UnicodeCharacter class value: */ primitive VMpr_UnicodeCharacter_create [succeed,fail] { OOP oop1; OOP oop2; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = STACKTOP (); if (IS_INT (oop2)) { intptr_t arg2; arg2 = TO_INT (oop2); if (arg2 >= 0 && arg2 <= 0x10FFFF) { SET_STACKTOP (char_new (arg2)); PRIM_SUCCEEDED; } } UNPOP (1); PRIM_FAILED; } /* Character = */ primitive VMpr_Character_equal [succeed] { OOP oop1; OOP oop2; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = POP_OOP (); PUSH_BOOLEAN (IS_OOP (oop2) && is_a_kind_of (OOP_CLASS (oop2), _gst_char_class) && CHAR_OOP_VALUE (oop2) == CHAR_OOP_VALUE (oop1) && (CHAR_OOP_VALUE (oop1) <= 127 || OOP_CLASS (oop2) == OOP_CLASS (oop1))); PRIM_SUCCEEDED; } /* Symbol class intern: aString */ primitive VMpr_Symbol_intern [succeed,fail] { OOP oop2; _gst_primitives_executed++; oop2 = STACKTOP (); /* keeps this guy referenced while being interned */ if (IS_CLASS (oop2, _gst_string_class)) { OOP internedString; internedString = _gst_intern_string_oop (oop2); POP_N_OOPS (1); SET_STACKTOP (internedString); PRIM_SUCCEEDED; } UNPOP (1); PRIM_FAILED; } /* Dictionary new */ primitive VMpr_Dictionary_new [succeed] { OOP oop1, dictionaryOOP; _gst_primitives_executed++; oop1 = STACKTOP(); dictionaryOOP = _gst_dictionary_new (32); dictionaryOOP->object->objClass = oop1; SET_STACKTOP (dictionaryOOP); PRIM_SUCCEEDED; } /* Memory addressOfOOP: oop */ primitive VMpr_Memory_addressOfOOP [succeed,fail] { OOP oop1; OOP oop2; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = POP_OOP (); if (IS_OOP (oop2)) { PUSH_OOP (FROM_C_ULONG ((uintptr_t) oop2)); PRIM_SUCCEEDED; } UNPOP (2); PRIM_FAILED; } /* Memory addressOf: oop */ primitive VMpr_Memory_addressOf [succeed,fail] { OOP oop1; OOP oop2; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = POP_OOP (); if (IS_OOP (oop2)) { PUSH_OOP (FROM_C_ULONG ((uintptr_t) OOP_TO_OBJ (oop2))); PRIM_SUCCEEDED; } UNPOP (2); PRIM_FAILED; } /* SystemDictionary backtrace */ primitive VMpr_SystemDictionary_backtrace [succeed] { _gst_primitives_executed++; _gst_show_backtrace (stdout); PRIM_SUCCEEDED; } /* SystemDictionary getTraceFlag: anIndex */ primitive VMpr_SystemDictionary_getTraceFlag [succeed,fail] { OOP oop1; OOP oop2; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = POP_OOP (); if (IS_INT (oop2)) { intptr_t arg2; int value; arg2 = TO_INT (oop2); value = _gst_get_var (arg2); if (value != -1) { oop1 = (value > 1 ? FROM_INT (oop2 ) : (value ? _gst_true_oop : _gst_false_oop)); PUSH_OOP (oop1); PRIM_SUCCEEDED; } } UNPOP (2); PRIM_FAILED; } /* SystemDictionary setTraceFlag: anIndex to: aBoolean */ primitive VMpr_SystemDictionary_setTraceFlag [succeed,fail] { OOP oop1; OOP oop2; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = POP_OOP (); if (IS_INT (oop1)) { intptr_t arg1 = TO_INT (oop1); intptr_t old_value = _gst_set_var (arg1, IS_INT (oop2) ? TO_INT (oop2) : oop2 == _gst_true_oop); if (old_value != -1) { SET_EXCEPT_FLAG (true); PRIM_SUCCEEDED; } } UNPOP (2); PRIM_FAILED; } /* Memory type: aType at: anAddress */ primitive VMpr_Memory_at [succeed,fail] { OOP oop1; OOP oop2; OOP oop3; _gst_primitives_executed++; oop3 = POP_OOP (); oop2 = POP_OOP (); oop1 = POP_OOP (); if (IS_C_LONG (oop3) && IS_INT (oop2)) { intptr_t arg1, arg2; arg1 = TO_INT (oop2); arg2 = TO_C_LONG (oop3); switch (arg1) { case CDATA_CHAR: /* char */ case CDATA_UCHAR: /* unsigned char */ PUSH_OOP (CHAR_OOP_AT (*(unsigned char *) arg2)); PRIM_SUCCEEDED; case CDATA_SHORT: /* short */ PUSH_INT (*(short *) arg2); PRIM_SUCCEEDED; case CDATA_USHORT: /* unsigned short */ PUSH_INT (*(unsigned short *) arg2); PRIM_SUCCEEDED; case CDATA_LONG: /* long */ PUSH_OOP (FROM_C_LONG (*(long *) arg2)); PRIM_SUCCEEDED; case CDATA_ULONG: /* unsigned long */ PUSH_OOP (FROM_C_ULONG (*(unsigned long *) arg2)); PRIM_SUCCEEDED; case CDATA_LONGLONG: /* long long */ PUSH_OOP (from_c_int_64 (*(long long *) arg2)); PRIM_SUCCEEDED; case CDATA_ULONGLONG: /* unsigned long long */ PUSH_OOP (from_c_uint_64 (*(unsigned long long *) arg2)); PRIM_SUCCEEDED; case CDATA_FLOAT: /* float */ PUSH_OOP (floate_new (*(float *) arg2)); PRIM_SUCCEEDED; case CDATA_DOUBLE: /* double */ PUSH_OOP (floatd_new (*(double *) arg2)); PRIM_SUCCEEDED; case CDATA_STRING: /* string */ if (*(char **) arg2) PUSH_OOP (_gst_string_new (*(char **) arg2)); else PUSH_OOP (_gst_nil_oop); PRIM_SUCCEEDED; case CDATA_OOP: /* OOP */ PUSH_OOP (*(OOP *) arg2); PRIM_SUCCEEDED; case CDATA_INT: /* int */ PUSH_OOP (FROM_C_INT (*(int *) arg2)); PRIM_SUCCEEDED; case CDATA_UINT: /* unsigned int */ PUSH_OOP (FROM_C_UINT (*(unsigned int *) arg2)); PRIM_SUCCEEDED; case CDATA_LONG_DOUBLE: /* long double */ PUSH_OOP (floatq_new (*(long double *) arg2)); PRIM_SUCCEEDED; } } UNPOP (3); PRIM_FAILED; } /* Memory type: aType at: anAddress put: aValue */ primitive VMpr_Memory_atPut [succeed,fail] { OOP oop4; OOP oop3; OOP oop2; _gst_primitives_executed++; oop4 = POP_OOP (); oop3 = POP_OOP (); oop2 = POP_OOP (); /* don't pop the receiver */ if (IS_C_LONG (oop3) && IS_INT (oop2)) { intptr_t arg1, arg2; arg1 = TO_INT (oop2); arg2 = TO_C_LONG (oop3); switch (arg1) { case CDATA_CHAR: /* char */ case CDATA_UCHAR: /* unsigned char */ /* may want to use Character instead? */ if (IS_CLASS (oop3, _gst_char_class) || (IS_CLASS (oop3, _gst_unicode_character_class) && CHAR_OOP_VALUE (oop3) <= 127)) { *(char *) arg2 = CHAR_OOP_VALUE (oop4); PRIM_SUCCEEDED; } else if (IS_INT (oop4)) { *(char *) arg2 = (char) TO_INT (oop4); PRIM_SUCCEEDED; } break; case CDATA_SHORT: /* short */ case CDATA_USHORT: /* unsigned short */ if (IS_INT (oop4)) { *(short *) arg2 = (short) TO_INT (oop4); PRIM_SUCCEEDED; } break; case CDATA_LONG: /* long */ case CDATA_ULONG: /* unsigned long */ if (IS_C_LONG (oop4) || IS_C_ULONG (oop4)) { *(long *) arg2 = TO_C_LONG (oop4); PRIM_SUCCEEDED; } break; case CDATA_LONGLONG: /* long long */ case CDATA_ULONGLONG: /* unsigned long long */ if (IS_C_LONGLONG (oop4) || IS_C_ULONGLONG (oop4)) { *(long long *) arg2 = to_c_int_64 (oop4); PRIM_SUCCEEDED; } break; case CDATA_FLOAT: /* float */ if (IS_CLASS (oop4, _gst_floatd_class)) { *(float *) arg2 = (float) FLOATD_OOP_VALUE (oop4); PRIM_SUCCEEDED; } else if (IS_CLASS (oop4, _gst_floate_class)) { *(float *) arg2 = FLOATE_OOP_VALUE (oop4); PRIM_SUCCEEDED; } else if (IS_CLASS (oop4, _gst_floatq_class)) { *(float *) arg2 = (float) FLOATQ_OOP_VALUE (oop4); PRIM_SUCCEEDED; } break; case CDATA_DOUBLE: /* double */ if (IS_CLASS (oop4, _gst_floatd_class)) { *(double *) arg2 = FLOATD_OOP_VALUE (oop4); PRIM_SUCCEEDED; } else if (IS_CLASS (oop4, _gst_floate_class)) { *(double *) arg2 = (double) FLOATE_OOP_VALUE (oop4); PRIM_SUCCEEDED; } else if (IS_CLASS (oop4, _gst_floatq_class)) { *(double *) arg2 = (double) FLOATQ_OOP_VALUE (oop4); PRIM_SUCCEEDED; } break; case CDATA_STRING: /* string */ if (IS_CLASS (oop4, _gst_string_class) || IS_CLASS (oop4, _gst_symbol_class)) { /* Char* cast on the right side needed because _gst_to_cstring returns gst_uchar * */ *(char **) arg2 = (char *) _gst_to_cstring (oop4); PRIM_SUCCEEDED; } break; case CDATA_OOP: /* OOP */ *(OOP *) arg2 = oop4; PRIM_SUCCEEDED; case CDATA_INT: /* int */ case CDATA_UINT: /* unsigned int */ if (IS_C_INT (oop4) || is_c_uint_32 (oop4)) { *(int *) arg2 = TO_C_INT (oop4); PRIM_SUCCEEDED; } break; case CDATA_LONG_DOUBLE: /* long double */ if (IS_CLASS (oop4, _gst_floatd_class)) { *(long double *) arg2 = (long double) FLOATD_OOP_VALUE (oop4); PRIM_SUCCEEDED; } else if (IS_CLASS (oop4, _gst_floate_class)) { *(long double *) arg2 = (long double) FLOATE_OOP_VALUE (oop4); PRIM_SUCCEEDED; } else if (IS_CLASS (oop4, _gst_floatq_class)) { *(long double *) arg2 = FLOATQ_OOP_VALUE (oop4); PRIM_SUCCEEDED; } break; } } UNPOP (3); PRIM_FAILED; } /* methodsFor: category */ primitive VMpr_Behavior_methodsFor [succeed,fail] { OOP oop2 = POP_OOP (); OOP oop1 = STACKTOP (); _gst_primitives_executed++; if (!_gst_current_parser || _gst_current_parser->state != PARSE_DOIT) PRIM_FAILED; _gst_set_compilation_class (oop1); _gst_set_compilation_category (oop2); _gst_display_compilation_trace ("Compiling", true); _gst_current_parser->state = PARSE_METHOD_LIST; PRIM_SUCCEEDED; } /* methodsFor: category ifTrue: condition */ primitive VMpr_Behavior_methodsForIfTrue [succeed,fail] { OOP oop3 = POP_OOP (); OOP oop2 = POP_OOP (); OOP oop1 = STACKTOP (); _gst_primitives_executed++; if (!_gst_current_parser || _gst_current_parser->state != PARSE_DOIT) PRIM_FAILED; _gst_set_compilation_class (oop1); _gst_set_compilation_category (oop2); if (oop3 == _gst_true_oop) _gst_display_compilation_trace ("Conditionally compiling", true); else { _gst_skip_compilation = true; _gst_display_compilation_trace ("Conditionally skipping", true); } _gst_current_parser->state = PARSE_METHOD_LIST; PRIM_SUCCEEDED; } primitive VMpr_Processor_disableEnableInterrupts : prim_id VMpr_Processor_disableInterrupts [succeed], prim_id VMpr_Processor_enableInterrupts [succeed] { OOP processOOP; gst_process process; gst_processor_scheduler processor; int count; _gst_primitives_executed++; processor = (gst_processor_scheduler) OOP_TO_OBJ (_gst_processor_oop); processOOP = processor->activeProcess; process = (gst_process) OOP_TO_OBJ (processOOP); count = IS_NIL (process->interrupts) ? 0 : TO_INT (process->interrupts); if (id == prim_id (VMpr_Processor_disableInterrupts) && count++ == 0) async_queue_enabled = false; else if (id == prim_id (VMpr_Processor_enableInterrupts) && --count == 0) { async_queue_enabled = true; SET_EXCEPT_FLAG (true); } process->interrupts = FROM_INT (count); PRIM_SUCCEEDED; } /* ProcessorScheduler signal: aSemaphore onInterrupt: anInteger */ primitive VMpr_Processor_signalOnInterrupt [succeed,fail,check_interrupt] { OOP oop1; OOP oop2; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = POP_OOP (); if (IS_INT (oop2)) { intptr_t arg2; arg2 = TO_INT (oop2); _gst_async_interrupt_wait (oop1, arg2); PRIM_SUCCEEDED; } UNPOP (2); PRIM_FAILED; } /* ObjectMemory spaceGrowRate */ primitive VMpr_ObjectMemory_getSpaceGrowRate [succeed] { _gst_primitives_executed++; SET_STACKTOP (floatd_new ((double) _gst_mem.space_grow_rate)); PRIM_SUCCEEDED; } /* ObjectMemory spaceGrowRate: */ primitive VMpr_ObjectMemory_setSpaceGrowRate [succeed,fail] { intptr_t arg1; OOP oop1; _gst_primitives_executed++; oop1 = POP_OOP (); if (IS_CLASS (oop1, _gst_floatd_class)) arg1 = (int) FLOATD_OOP_VALUE (oop1); else if (IS_CLASS (oop1, _gst_floate_class)) arg1 = (int) FLOATE_OOP_VALUE (oop1); else if (IS_CLASS (oop1, _gst_floatq_class)) arg1 = (int) FLOATQ_OOP_VALUE (oop1); else if (IS_INT (oop1)) arg1 = TO_INT (oop1); else { UNPOP (1); PRIM_FAILED; } if (arg1 > 0 && arg1 <= 500) { _gst_init_mem (0, 0, 0, 0, 0, arg1); PRIM_SUCCEEDED; } UNPOP (1); PRIM_FAILED; } /* ObjectMemory smoothingFactor */ primitive VMpr_ObjectMemory_getSmoothingFactor [succeed] { _gst_primitives_executed++; SET_STACKTOP (floatd_new ((double) _gst_mem.factor)); PRIM_SUCCEEDED; } /* ObjectMemory smoothingFactor: */ primitive VMpr_ObjectMemory_setSmoothingFactor [succeed,fail] { OOP oop1; intptr_t arg1; _gst_primitives_executed++; oop1 = POP_OOP (); if (IS_CLASS (oop1, _gst_floatd_class)) arg1 = (int) FLOATD_OOP_VALUE (oop1); else if (IS_CLASS (oop1, _gst_floate_class)) arg1 = (int) FLOATE_OOP_VALUE (oop1); else if (IS_CLASS (oop1, _gst_floatq_class)) arg1 = (int) FLOATQ_OOP_VALUE (oop1); else if (IS_INT (oop1)) arg1 = TO_INT (oop1); else { UNPOP (1); PRIM_FAILED; } if (arg1 >= 0 && arg1 <= 1) { _gst_mem.factor = arg1; PRIM_SUCCEEDED; } UNPOP (1); PRIM_FAILED; } /* ObjectMemory growThresholdPercent */ primitive VMpr_ObjectMemory_getGrowThresholdPercent [succeed] { _gst_primitives_executed++; SET_STACKTOP (floatd_new ((double) _gst_mem.grow_threshold_percent)); PRIM_SUCCEEDED; } /* ObjectMemory growThresholdPercent: */ primitive VMpr_ObjectMemory_setGrowThresholdPercent [succeed,fail] { OOP oop1; intptr_t arg1; _gst_primitives_executed++; oop1 = POP_OOP (); if (IS_CLASS (oop1, _gst_floatd_class)) arg1 = (int) FLOATD_OOP_VALUE (oop1); else if (IS_CLASS (oop1, _gst_floate_class)) arg1 = (int) FLOATE_OOP_VALUE (oop1); else if (IS_CLASS (oop1, _gst_floatq_class)) arg1 = (int) FLOATQ_OOP_VALUE (oop1); else if (IS_INT (oop1)) arg1 = TO_INT (oop1); else { UNPOP (1); PRIM_FAILED; } if (arg1 > 0 && arg1 < 100) { _gst_init_mem (0, 0, 0, 0, arg1, 0); PRIM_SUCCEEDED; } UNPOP (1); PRIM_FAILED; } /* ObjectMemory bigObjectThreshold */ primitive VMpr_ObjectMemory_getBigObjectThreshold [succeed] { _gst_primitives_executed++; SET_STACKTOP_INT (_gst_mem.big_object_threshold); PRIM_SUCCEEDED; } /* ObjectMemory bigObjectThreshold: */ primitive VMpr_ObjectMemory_setBigObjectThreshold [succeed,fail] { OOP oop1; intptr_t arg1; _gst_primitives_executed++; oop1 = POP_OOP (); if (IS_NIL (oop1)) arg1 = INT_MAX < MAX_ST_INT ? INT_MAX : MAX_ST_INT; else if (IS_INT (oop1)) arg1 = TO_INT (oop1); else { UNPOP (1); PRIM_FAILED; } if (arg1 >= 0) { _gst_init_mem (0, 0, 0, arg1, 0, 0); PRIM_SUCCEEDED; } UNPOP (1); PRIM_FAILED; } /* ObjectMemory growTo: numBytes */ primitive VMpr_ObjectMemory_growTo [succeed,fail] { OOP oop1; intptr_t arg1; _gst_primitives_executed++; oop1 = POP_OOP (); if (IS_INT (oop1)) { arg1 = TO_INT (oop1); _gst_grow_memory_to (arg1); PRIM_SUCCEEDED; } UNPOP (1); PRIM_FAILED; } /* ObjectMemory update */ primitive VMpr_ObjectMemory_update [checks_receiver] { _gst_primitives_executed++; #ifndef OPTIMIZE if (OOP_CLASS (STACKTOP ()) != _gst_object_memory_class) PRIM_FAILED; #endif _gst_update_object_memory_oop (STACKTOP ()); PRIM_SUCCEEDED; } /* CObject class alloc: nbytes type: aType */ primitive VMpr_CObject_allocType [succeed,fail] { OOP oop1; OOP oop2; OOP oop3; _gst_primitives_executed++; oop1 = STACK_AT (0); oop2 = STACK_AT (1); oop3 = STACK_AT (2); if (IS_INT (oop2) && (IS_NIL (oop1) || is_a_kind_of (OOP_CLASS (oop1), _gst_c_type_class)) && COMMON (RECEIVER_IS_A_KIND_OF (oop3, _gst_c_object_class))) { intptr_t arg2 = TO_INT (oop2); PTR ptr = xmalloc (arg2); OOP cObjectOOP = COBJECT_NEW (ptr, oop1, oop3); POP_N_OOPS (2); SET_STACKTOP (cObjectOOP); PRIM_SUCCEEDED; } PRIM_FAILED; } /* sin */ primitive VMpr_Float_sin [succeed,fail] { OOP oop1; _gst_primitives_executed++; oop1 = STACKTOP (); if (IS_CLASS (oop1, _gst_floatd_class)) { double farg1 = FLOATD_OOP_VALUE (oop1); SET_STACKTOP (floatd_new (sin (farg1))); PRIM_SUCCEEDED; } else if (IS_CLASS (oop1, _gst_floate_class)) { double farg1 = (double) FLOATE_OOP_VALUE (oop1); SET_STACKTOP (floate_new (sin (farg1))); PRIM_SUCCEEDED; } else if (IS_CLASS (oop1, _gst_floatq_class)) { long double farg1 = FLOATQ_OOP_VALUE (oop1); SET_STACKTOP (floatq_new (sinl (farg1))); PRIM_SUCCEEDED; } PRIM_FAILED; } /* cos */ primitive VMpr_Float_cos [succeed,fail] { OOP oop1; _gst_primitives_executed++; oop1 = STACKTOP (); if (IS_CLASS (oop1, _gst_floatd_class)) { double farg1 = FLOATD_OOP_VALUE (oop1); SET_STACKTOP (floatd_new (cos (farg1))); PRIM_SUCCEEDED; } else if (IS_CLASS (oop1, _gst_floate_class)) { double farg1 = (double) FLOATE_OOP_VALUE (oop1); SET_STACKTOP (floate_new (cos (farg1))); PRIM_SUCCEEDED; } else if (IS_CLASS (oop1, _gst_floatq_class)) { long double farg1 = FLOATQ_OOP_VALUE (oop1); SET_STACKTOP (floatq_new (cosl (farg1))); PRIM_SUCCEEDED; } PRIM_FAILED; } /* tan */ primitive VMpr_Float_tan [succeed,fail] { OOP oop1; _gst_primitives_executed++; oop1 = STACKTOP (); if (IS_CLASS (oop1, _gst_floatd_class)) { double farg1 = FLOATD_OOP_VALUE (oop1); SET_STACKTOP (floatd_new (tan (farg1))); PRIM_SUCCEEDED; } else if (IS_CLASS (oop1, _gst_floate_class)) { double farg1 = (double) FLOATE_OOP_VALUE (oop1); SET_STACKTOP (floate_new (tan (farg1))); PRIM_SUCCEEDED; } else if (IS_CLASS (oop1, _gst_floatq_class)) { long double farg1 = FLOATQ_OOP_VALUE (oop1); SET_STACKTOP (floatq_new (tanl (farg1))); PRIM_SUCCEEDED; } PRIM_FAILED; } /* arcSin */ primitive VMpr_Float_arcSin [succeed,fail] { OOP oop1; _gst_primitives_executed++; oop1 = STACKTOP (); if (IS_CLASS (oop1, _gst_floatd_class)) { double farg1 = FLOATD_OOP_VALUE (oop1); SET_STACKTOP (floatd_new (asin (farg1))); PRIM_SUCCEEDED; } else if (IS_CLASS (oop1, _gst_floate_class)) { double farg1 = (double) FLOATE_OOP_VALUE (oop1); SET_STACKTOP (floate_new (asin (farg1))); PRIM_SUCCEEDED; } else if (IS_CLASS (oop1, _gst_floatq_class)) { long double farg1 = FLOATQ_OOP_VALUE (oop1); SET_STACKTOP (floatq_new (asinl (farg1))); PRIM_SUCCEEDED; } PRIM_FAILED; } /* arcCos */ primitive VMpr_Float_arcCos [succeed,fail] { OOP oop1; _gst_primitives_executed++; oop1 = STACKTOP (); if (IS_CLASS (oop1, _gst_floatd_class)) { double farg1 = FLOATD_OOP_VALUE (oop1); SET_STACKTOP (floatd_new (acos (farg1))); PRIM_SUCCEEDED; } else if (IS_CLASS (oop1, _gst_floate_class)) { double farg1 = (double) FLOATE_OOP_VALUE (oop1); SET_STACKTOP (floate_new (acos (farg1))); PRIM_SUCCEEDED; } else if (IS_CLASS (oop1, _gst_floatq_class)) { long double farg1 = FLOATQ_OOP_VALUE (oop1); SET_STACKTOP (floatq_new (acosl (farg1))); PRIM_SUCCEEDED; } PRIM_FAILED; } /* arcTan */ primitive VMpr_Float_arcTan [succeed,fail] { OOP oop1; _gst_primitives_executed++; oop1 = STACKTOP (); if (IS_CLASS (oop1, _gst_floatd_class)) { double farg1 = FLOATD_OOP_VALUE (oop1); SET_STACKTOP (floatd_new (atan (farg1))); PRIM_SUCCEEDED; } else if (IS_CLASS (oop1, _gst_floate_class)) { double farg1 = (double) FLOATE_OOP_VALUE (oop1); SET_STACKTOP (floate_new (atan (farg1))); PRIM_SUCCEEDED; } else if (IS_CLASS (oop1, _gst_floatq_class)) { long double farg1 = FLOATQ_OOP_VALUE (oop1); SET_STACKTOP (floatq_new (atanl (farg1))); PRIM_SUCCEEDED; } PRIM_FAILED; } /* exp */ primitive VMpr_Float_exp [succeed,fail] { OOP oop1; _gst_primitives_executed++; oop1 = STACKTOP (); if (IS_CLASS (oop1, _gst_floatd_class)) { double farg1 = FLOATD_OOP_VALUE (oop1); SET_STACKTOP (floatd_new (exp (farg1))); PRIM_SUCCEEDED; } else if (IS_CLASS (oop1, _gst_floate_class)) { double farg1 = (double) FLOATE_OOP_VALUE (oop1); SET_STACKTOP (floate_new (exp (farg1))); PRIM_SUCCEEDED; } else if (IS_CLASS (oop1, _gst_floatq_class)) { long double farg1 = FLOATQ_OOP_VALUE (oop1); SET_STACKTOP (floatq_new (expl (farg1))); PRIM_SUCCEEDED; } PRIM_FAILED; } /* ln */ primitive VMpr_Float_ln [succeed,fail] { OOP oop1; _gst_primitives_executed++; oop1 = STACKTOP (); if (IS_CLASS (oop1, _gst_floatd_class)) { double farg1 = FLOATD_OOP_VALUE (oop1); SET_STACKTOP (floatd_new (log (farg1))); PRIM_SUCCEEDED; } else if (IS_CLASS (oop1, _gst_floate_class)) { double farg1 = (double) FLOATE_OOP_VALUE (oop1); SET_STACKTOP (floate_new (log (farg1))); PRIM_SUCCEEDED; } else if (IS_CLASS (oop1, _gst_floatq_class)) { long double farg1 = FLOATQ_OOP_VALUE (oop1); SET_STACKTOP (floatq_new (logl (farg1))); PRIM_SUCCEEDED; } PRIM_FAILED; } /* raisedTo: aNumber -- receiver ** aNumber */ primitive VMpr_Float_pow [succeed,fail] { OOP oop1; OOP oop2; double farg1, farg2; long double lfarg1, lfarg2; mst_Boolean long_double = false; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = STACKTOP (); if (IS_CLASS (oop1, _gst_floatd_class)) lfarg1 = farg1 = FLOATD_OOP_VALUE (oop1); else if (IS_CLASS (oop1, _gst_floate_class)) lfarg1 = farg1 = FLOATE_OOP_VALUE (oop1); else if (IS_CLASS (oop1, _gst_floatq_class)) { long_double = true; lfarg1 = farg1 = FLOATQ_OOP_VALUE (oop1); } else { UNPOP (1); PRIM_FAILED; } if (IS_CLASS (oop2, _gst_floatd_class)) lfarg2 = farg2 = FLOATD_OOP_VALUE (oop2); else if (IS_CLASS (oop2, _gst_floate_class)) lfarg2 = farg2 = FLOATE_OOP_VALUE (oop2); else if (IS_CLASS (oop2, _gst_floatq_class)) { long_double = true; lfarg2 = farg2 = FLOATQ_OOP_VALUE (oop2); } else { UNPOP (1); PRIM_FAILED; } if ((lfarg1 == 0.0 && lfarg2 < 0.0) || lfarg1 < 0.0) { UNPOP (1); PRIM_FAILED; } if (long_double) { if (IS_NAN (lfarg1) || IS_NAN (lfarg2)) /* The C99 standard mandates that pow(1, NaN) = 1.0 and pow (NaN, 0.0) = 1.0, which is plain wrong. We take the liberty to make these results be NaN. */ SET_STACKTOP (floatq_new (lfarg1 + lfarg2)); else SET_STACKTOP (floatq_new (powl (lfarg1, lfarg2))); } else { if (IS_NAN (farg1) || IS_NAN (farg2)) /* The C99 standard mandates that pow(1, NaN) = 1.0 and pow (NaN, 0.0) = 1.0, which is plain wrong. We take the liberty to make these results be NaN. */ SET_STACKTOP (floatd_new (farg1 + farg2)); else SET_STACKTOP (floatd_new (pow (farg1, farg2))); } PRIM_SUCCEEDED; } /* CObject free */ primitive VMpr_CObject_free [succeed,fail] { OOP oop1; _gst_primitives_executed++; oop1 = STACKTOP (); if COMMON (is_a_kind_of (OOP_CLASS (oop1), _gst_c_callback_descriptor_class)) { _gst_free_closure (oop1); SET_STACKTOP (_gst_nil_oop); PRIM_SUCCEEDED; } else if COMMON (RECEIVER_IS_A_KIND_OF (OOP_CLASS (oop1), _gst_c_object_class)) { _gst_free_cobject (oop1); /* free allocated space */ SET_STACKTOP (_gst_nil_oop); PRIM_SUCCEEDED; } PRIM_FAILED; } /* sqrt */ primitive VMpr_Float_sqrt [succeed,fail] { OOP oop1; _gst_primitives_executed++; oop1 = STACKTOP (); if (IS_CLASS (oop1, _gst_floatd_class)) { double farg1 = FLOATD_OOP_VALUE (oop1); SET_STACKTOP (floatd_new (sqrt (farg1))); PRIM_SUCCEEDED; } else if (IS_CLASS (oop1, _gst_floate_class)) { double farg1 = FLOATE_OOP_VALUE (oop1); SET_STACKTOP (floate_new (sqrt (farg1))); PRIM_SUCCEEDED; } else if (IS_CLASS (oop1, _gst_floatq_class)) { long double farg1 = FLOATQ_OOP_VALUE (oop1); SET_STACKTOP (floatq_new (sqrtl (farg1))); PRIM_SUCCEEDED; } PRIM_FAILED; } /* ceiling, floor */ primitive VMpr_Float_ceil_floor : prim_id VMpr_Float_ceil [succeed,fail], prim_id VMpr_Float_floor [succeed,fail] { OOP oop1; double farg1; _gst_primitives_executed++; oop1 = STACKTOP (); if (IS_CLASS (oop1, _gst_floatd_class)) farg1 = FLOATD_OOP_VALUE (oop1); else if (IS_CLASS (oop1, _gst_floate_class)) farg1 = (double) FLOATE_OOP_VALUE (oop1); else if (IS_CLASS (oop1, _gst_floatq_class)) farg1 = (double) FLOATQ_OOP_VALUE (oop1); else PRIM_FAILED; if COMMON ((farg1 > MIN_ST_INT) && farg1 < MAX_ST_INT) { switch (id) { case prim_id (VMpr_Float_ceil): SET_STACKTOP_INT ((intptr_t) ceil (farg1)); PRIM_SUCCEEDED; case prim_id (VMpr_Float_floor): SET_STACKTOP_INT ((intptr_t) floor (farg1)); PRIM_SUCCEEDED; } } PRIM_FAILED; } /* Behavior basicNewInFixedSpace */ primitive VMpr_Behavior_basicNewFixed [succeed,fail] { OOP oop1; _gst_primitives_executed++; oop1 = STACKTOP (); if (IS_OOP (oop1)) { if (!CLASS_IS_INDEXABLE (oop1)) { OOP result; instantiate (oop1, &result); _gst_make_oop_fixed (result); SET_STACKTOP (result); PRIM_SUCCEEDED; } } PRIM_FAILED; } /* Behavior basicNewInFixedSpace: */ primitive VMpr_Behavior_basicNewFixedColon [succeed,fail] { OOP oop1; OOP oop2; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = STACKTOP (); if (IS_OOP (oop1) && IS_INT (oop2)) { if (CLASS_IS_INDEXABLE (oop1)) { intptr_t arg2; arg2 = TO_INT (oop2); if (arg2 >= 0) { OOP result; instantiate_with (oop1, arg2, &result); _gst_make_oop_fixed (result); SET_STACKTOP (result); PRIM_SUCCEEDED; } } } UNPOP (1); PRIM_FAILED; } primitive VMpr_Object_tenure [succeed,fail] { OOP oop1; _gst_primitives_executed++; oop1 = STACKTOP (); if (IS_OOP (oop1)) { _gst_tenure_oop (oop1); PRIM_SUCCEEDED; } PRIM_FAILED; } primitive VMpr_Object_makeFixed [succeed,fail] { OOP oop1; _gst_primitives_executed++; oop1 = STACKTOP (); if (IS_OOP (oop1)) { _gst_make_oop_fixed (oop1); PRIM_SUCCEEDED; } PRIM_FAILED; } /* CObject at: byteoffset type: aType */ primitive VMpr_CObject_at : prim_id VMpr_CObject_derefAt [succeed,fail], prim_id VMpr_CObject_at [succeed,fail] { OOP oop1; OOP oop2; OOP oop3; _gst_primitives_executed++; oop3 = POP_OOP (); oop2 = POP_OOP (); oop1 = STACKTOP (); if (IS_INT (oop2) && ((IS_INT (oop3) && id == prim_id (VMpr_CObject_at)) || is_a_kind_of (OOP_CLASS (oop3), _gst_c_type_class))) { char *addr; intptr_t arg2; arg2 = TO_INT (oop2); if (IS_INT (oop3)) { /* int type spec means a scalar type */ intptr_t arg3 = TO_INT (oop3); if (!cobject_index_check (oop1, arg2, _gst_c_type_size (arg3))) goto fail; addr = ((char *) cobject_value (oop1)) + arg2; switch (arg3) { case CDATA_CHAR: case CDATA_UCHAR: SET_STACKTOP (CHAR_OOP_AT (*(gst_uchar *) addr)); PRIM_SUCCEEDED; case CDATA_SHORT: SET_STACKTOP_INT (*(short *) addr); PRIM_SUCCEEDED; case CDATA_USHORT: SET_STACKTOP_INT (*(unsigned short *) addr); PRIM_SUCCEEDED; case CDATA_LONGLONG: SET_STACKTOP (from_c_int_64 (*(long long *) addr)); PRIM_SUCCEEDED; case CDATA_ULONGLONG: SET_STACKTOP (from_c_uint_64 (*(unsigned long long *) addr)); PRIM_SUCCEEDED; case CDATA_LONG: SET_STACKTOP (FROM_C_LONG (*(long *) addr)); PRIM_SUCCEEDED; case CDATA_ULONG: SET_STACKTOP (FROM_C_ULONG (*(unsigned long *) addr)); PRIM_SUCCEEDED; case CDATA_FLOAT: SET_STACKTOP (floate_new (*(float *) addr)); PRIM_SUCCEEDED; case CDATA_DOUBLE: SET_STACKTOP (floatd_new (*(double *) addr)); PRIM_SUCCEEDED; case CDATA_STRING: { char **strAddr; strAddr = (char **) addr; if (*strAddr) { SET_STACKTOP (_gst_string_new (*strAddr)); PRIM_SUCCEEDED; } else { SET_STACKTOP (_gst_nil_oop); PRIM_SUCCEEDED; } } case CDATA_OOP: SET_STACKTOP (*(OOP *) addr); PRIM_SUCCEEDED; case CDATA_INT: SET_STACKTOP (FROM_C_INT (*(int *) addr)); PRIM_SUCCEEDED; case CDATA_UINT: SET_STACKTOP (FROM_C_UINT (*(unsigned int *) addr)); PRIM_SUCCEEDED; case CDATA_LONG_DOUBLE: SET_STACKTOP (floatq_new (*(long double *) addr)); PRIM_SUCCEEDED; } } else { OOP baseOOP; uintptr_t ofs; inc_ptr incPtr; /* Non-integer oop3: use it as the type of the effective address. */ if (id == prim_id (VMpr_CObject_derefAt)) { if (!cobject_index_check (oop1, arg2, sizeof (uintptr_t))) goto fail; ofs = *(uintptr_t *) (((char *)cobject_value (oop1)) + arg2); baseOOP = _gst_nil_oop; if (ofs == 0) { SET_STACKTOP (_gst_nil_oop); PRIM_SUCCEEDED; } } else { /* No need to enforce bounds here (if we ever will, remember that a pointer that is one-past the end of the object is valid!). */ gst_cobject cObj = (gst_cobject) OOP_TO_OBJ (oop1); baseOOP = cObj->storage; ofs = COBJECT_OFFSET_OBJ (cObj) + arg2; } /* oop3 could get GC'ed out of existence before it gets used: it is not on the stack, and _gst_c_object_new_base could cause a GC */ incPtr = INC_SAVE_POINTER (); INC_ADD_OOP (baseOOP); INC_ADD_OOP (oop3); SET_STACKTOP (_gst_c_object_new_base (baseOOP, ofs, oop3, _gst_c_object_class)); INC_RESTORE_POINTER (incPtr); PRIM_SUCCEEDED; } } fail: UNPOP (2); PRIM_FAILED; } /* CObject at: byteOffset put: aValue type: aType */ primitive VMpr_CObject_atPut [succeed,fail] { OOP oop1; OOP oop2; OOP oop3; OOP oop4; _gst_primitives_executed++; oop4 = POP_OOP (); oop3 = POP_OOP (); oop2 = POP_OOP (); oop1 = STACKTOP (); if (IS_INT (oop2) && IS_INT (oop4)) { char *addr; intptr_t arg2 = TO_INT (oop2); intptr_t arg4 = TO_INT (oop4); if (!cobject_index_check (oop1, arg2, _gst_c_type_size (arg4))) goto fail; addr = ((char *) cobject_value (oop1)) + arg2; switch (arg4) { case CDATA_CHAR: /* char */ case CDATA_UCHAR: /* uchar */ if (IS_CLASS (oop3, _gst_char_class) || (IS_CLASS (oop3, _gst_unicode_character_class) && CHAR_OOP_VALUE (oop3) <= 127)) { *addr = CHAR_OOP_VALUE (oop3); PRIM_SUCCEEDED; } else if (IS_INT (oop3)) { *(char *) addr = (char) TO_INT (oop3); PRIM_SUCCEEDED; } break; case CDATA_SHORT: /* short */ case CDATA_USHORT: /* ushort */ if (IS_INT (oop3)) { *(short *) addr = (short) TO_INT (oop3); PRIM_SUCCEEDED; } break; case CDATA_LONG: /* long */ case CDATA_ULONG: /* ulong */ if (IS_C_LONG (oop3) || IS_C_ULONG (oop3)) { *(long *) addr = (long) TO_C_LONG (oop3); PRIM_SUCCEEDED; } break; case CDATA_LONGLONG: /* long long */ case CDATA_ULONGLONG: /* unsigned long long */ if (IS_C_LONGLONG (oop3) || IS_C_ULONGLONG (oop3)) { *(long long *) addr = (long long) to_c_int_64 (oop3); PRIM_SUCCEEDED; } break; case CDATA_FLOAT: { float *floatAddr; floatAddr = (float *) addr; if (IS_INT (oop3)) { *floatAddr = (float) TO_INT (oop3); PRIM_SUCCEEDED; } else if (IS_CLASS (oop3, _gst_floatd_class)) { *floatAddr = (float) FLOATD_OOP_VALUE (oop3); PRIM_SUCCEEDED; } else if (IS_CLASS (oop3, _gst_floate_class)) { *floatAddr = (float) FLOATE_OOP_VALUE (oop3); PRIM_SUCCEEDED; } else if (IS_CLASS (oop3, _gst_floatq_class)) { *floatAddr = (float) FLOATQ_OOP_VALUE (oop3); PRIM_SUCCEEDED; } } break; case CDATA_DOUBLE: /* double */ { double *doubleAddr; doubleAddr = (double *) addr; if (IS_INT (oop3)) { *doubleAddr = TO_INT (oop3); PRIM_SUCCEEDED; } else if (IS_CLASS (oop3, _gst_floatd_class)) { *doubleAddr = FLOATD_OOP_VALUE (oop3); PRIM_SUCCEEDED; } else if (IS_CLASS (oop3, _gst_floate_class)) { *doubleAddr = FLOATE_OOP_VALUE (oop3); PRIM_SUCCEEDED; } else if (IS_CLASS (oop3, _gst_floatq_class)) { *doubleAddr = FLOATQ_OOP_VALUE (oop3); PRIM_SUCCEEDED; } } break; case CDATA_STRING: /* string */ { /* note that this does not allow for replacemnt in place */ /* to replace in place, use replaceFrom: */ char **strAddr; strAddr = (char **) addr; if (oop3 == _gst_nil_oop) { *strAddr = (char *) 0; PRIM_SUCCEEDED; } else if (is_a_kind_of (OOP_CLASS (oop3), _gst_string_class)) { *strAddr = (char *) _gst_to_cstring (oop3); PRIM_SUCCEEDED; } break; } case CDATA_OOP: *(OOP *) addr = oop3; PRIM_SUCCEEDED; case CDATA_INT: /* int */ case CDATA_UINT: /* uint */ if (IS_C_INT (oop3)) { *(int *) addr = (int) TO_C_INT (oop3); PRIM_SUCCEEDED; } break; case CDATA_LONG_DOUBLE: /* long double */ { long double *longDoubleAddr; longDoubleAddr = (long double *) addr; if (IS_INT (oop3)) { *longDoubleAddr = TO_INT (oop3); PRIM_SUCCEEDED; } else if (IS_CLASS (oop3, _gst_floatd_class)) { *longDoubleAddr = FLOATD_OOP_VALUE (oop3); PRIM_SUCCEEDED; } else if (IS_CLASS (oop3, _gst_floate_class)) { *longDoubleAddr = FLOATE_OOP_VALUE (oop3); PRIM_SUCCEEDED; } else if (IS_CLASS (oop3, _gst_floatq_class)) { *longDoubleAddr = FLOATQ_OOP_VALUE (oop3); PRIM_SUCCEEDED; } } break; } } fail: UNPOP (3); PRIM_FAILED; } /* CObject address */ primitive VMpr_CObject_address [succeed] { OOP oop1; gst_cobject cObj; uintptr_t ptr; _gst_primitives_executed++; oop1 = STACKTOP (); cObj = (gst_cobject) OOP_TO_OBJ (oop1); ptr = (uintptr_t) COBJECT_OFFSET_OBJ (cObj); if (IS_NIL (cObj->storage)) SET_STACKTOP (FROM_C_ULONG (ptr)); else SET_STACKTOP (FROM_C_LONG (ptr)); PRIM_SUCCEEDED; } /* CObject address: */ primitive VMpr_CObject_addressColon [succeed, fail] { OOP oop1, oop2; gst_cobject cObj; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = STACKTOP (); cObj = (gst_cobject) OOP_TO_OBJ (oop1); if (IS_NIL (cObj->storage) ? IS_C_ULONG (oop2) : IS_C_LONG (oop2)) { SET_COBJECT_OFFSET_OBJ (cObj, TO_C_LONG (oop2)); PRIM_SUCCEEDED; } UNPOP (1); PRIM_FAILED; } /* CString replaceWith: aString */ primitive VMpr_CString_replaceWith [succeed,fail] { OOP oop1; OOP oop2; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = STACKTOP (); /* assumes the receiver is already pointing at an area of memory that is the correct size; does not (re)allocate receiver's string at all. */ if (IS_CLASS (oop2, _gst_string_class) || IS_CLASS (oop2, _gst_byte_array_class)) { size_t srcLen; gst_uchar *dstBase, *srcBase; srcBase = STRING_OOP_CHARS (oop2); srcLen = NUM_INDEXABLE_FIELDS (oop2); dstBase = *(gst_uchar **) cobject_value (oop1); memcpy (dstBase, srcBase, srcLen); dstBase[srcLen] = '\0'; /* since it's a CString type, we NUL term it */ PRIM_SUCCEEDED; } UNPOP (1); PRIM_FAILED; } /* ByteArray class fromCdata: aCObject size: anInteger */ primitive VMpr_ByteArray_fromCData_size [succeed,fail] { OOP oop1; OOP oop2; OOP oop3; _gst_primitives_executed++; oop3 = POP_OOP (); oop2 = POP_OOP (); oop1 = STACKTOP (); if (IS_INT (oop3)) { intptr_t arg3 = TO_INT (oop3); OOP byteArrayOOP = _gst_byte_array_new (cobject_value (oop2), arg3); SET_STACKTOP (byteArrayOOP); PRIM_SUCCEEDED; } UNPOP (2); PRIM_FAILED; } /* String class fromCdata: aCObject size: anInteger */ primitive VMpr_String_fromCData_size [succeed,fail] { OOP oop1; OOP oop2; OOP oop3; _gst_primitives_executed++; oop3 = POP_OOP (); oop2 = POP_OOP (); oop1 = STACKTOP (); if (IS_INT (oop3)) { intptr_t arg3 = TO_INT (oop3); OOP stringOOP = _gst_counted_string_new (cobject_value (oop2), arg3); SET_STACKTOP (stringOOP); PRIM_SUCCEEDED; } UNPOP (2); PRIM_FAILED; } /* String class fromCdata: aCObject */ primitive VMpr_String_fromCData [succeed] { OOP oop1; OOP oop2; OOP stringOOP; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = STACKTOP (); stringOOP = _gst_string_new (cobject_value (oop2)); SET_STACKTOP (stringOOP); PRIM_SUCCEEDED; } /* String asCdata: aCType * ByteArray asCdata: aCType */ primitive VMpr_String_ByteArray_asCData : prim_id VMpr_String_asCData [checks_receiver], prim_id VMpr_ByteArray_asCData [checks_receiver] { OOP oop1; OOP oop2; _gst_primitives_executed++; oop2 = STACK_AT (0); oop1 = STACK_AT (1); if (is_a_kind_of (OOP_CLASS (oop2), _gst_c_type_class)) { int size = NUM_INDEXABLE_FIELDS (oop1); int alloc_size = (id == prim_id (VMpr_String_asCData)) ? size + 1 : size; char *data = xmalloc (alloc_size); OOP cObjectOOP = COBJECT_NEW (data, oop2, _gst_c_object_class); memcpy (data, OOP_TO_OBJ (oop1)->data, size); if (id == prim_id (VMpr_String_asCData)) data[size] = 0; POP_N_OOPS (1); SET_STACKTOP (cObjectOOP); PRIM_SUCCEEDED; } PRIM_FAILED; } /* SystemDictionary byteCodeCounter */ primitive VMpr_SystemDictionary_byteCodeCounter [succeed] { _gst_primitives_executed++; SET_STACKTOP_INT (_gst_bytecode_counter); PRIM_SUCCEEDED; } /* SystemDictionary debug */ primitive VMpr_SystemDictionary_debug [succeed] { _gst_primitives_executed++; _gst_debug (); /* used to allow gdb to stop based on Smalltalk execution paths. */ PRIM_SUCCEEDED; } /* Object isUntrusted */ primitive VMpr_Object_isUntrusted [succeed] { OOP oop1; _gst_primitives_executed++; oop1 = STACKTOP (); SET_STACKTOP_BOOLEAN (IS_OOP_UNTRUSTED (oop1)); PRIM_SUCCEEDED; } /* Object makeUntrusted: */ primitive VMpr_Object_makeUntrusted [succeed,fail] { OOP oop1; OOP oop2; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = STACKTOP (); if (oop2 == _gst_true_oop) { MAKE_OOP_UNTRUSTED (oop1, true); PRIM_SUCCEEDED; } else if (oop2 == _gst_false_oop) { MAKE_OOP_UNTRUSTED (oop1, false); PRIM_SUCCEEDED; } UNPOP (1); PRIM_FAILED; } /* Object isReadOnly */ primitive VMpr_Object_isReadOnly [succeed] { OOP oop1; _gst_primitives_executed++; oop1 = STACKTOP (); SET_STACKTOP_BOOLEAN (IS_OOP_READONLY (oop1)); PRIM_SUCCEEDED; } /* Object makeReadOnly: */ primitive VMpr_Object_makeReadOnly [succeed,fail] { OOP oop1; OOP oop2; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = STACKTOP (); if (IS_OOP (oop1)) { if (oop2 == _gst_true_oop) { MAKE_OOP_READONLY (oop1, true); PRIM_SUCCEEDED; } else if (oop2 == _gst_false_oop) { MAKE_OOP_READONLY (oop1, false); PRIM_SUCCEEDED; } } UNPOP (1); PRIM_FAILED; } /* Behavior primCompile: aString */ primitive VMpr_Behavior_primCompile [succeed] { OOP oop1; OOP oop2; mst_Boolean interrupted; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = POP_OOP (); if (IS_CLASS (oop2, _gst_string_class)) _gst_push_smalltalk_string (oop2); else _gst_push_stream_oop (oop2); _gst_set_compilation_class (oop1); _gst_set_compilation_category (_gst_string_new ("still unclassified")); interrupted = parse_stream_with_protection (true); _gst_pop_stream (true); PUSH_OOP (_gst_latest_compiled_method); if (interrupted) stop_execution (); PRIM_SUCCEEDED; } /* Behavior primCompile: aString ifError: aBlock */ primitive VMpr_Behavior_primCompileIfError [fail,succeed,reload_ip] { OOP oop1; OOP oop2; OOP oop3; _gst_primitives_executed++; oop3 = POP_OOP (); oop2 = POP_OOP (); oop1 = POP_OOP (); if (IS_CLASS (oop3, _gst_block_closure_class)) { mst_Boolean oldReportErrors = _gst_report_errors; mst_Boolean interrupted; if (oldReportErrors) { /* only clear out these guys on first transition */ _gst_first_error_str = _gst_first_error_file = NULL; } _gst_report_errors = false; if (IS_CLASS (oop2, _gst_string_class)) _gst_push_smalltalk_string (oop2); else _gst_push_stream_oop (oop2); _gst_set_compilation_class (oop1); _gst_set_compilation_category (_gst_string_new ("still unclassified")); interrupted = parse_stream_with_protection (true); _gst_pop_stream (true); _gst_report_errors = oldReportErrors; PUSH_OOP (_gst_latest_compiled_method); if (interrupted) stop_execution (); else if (_gst_first_error_str != NULL) { SET_STACKTOP (oop3); /* block context */ if (_gst_first_error_file != NULL) { PUSH_OOP (_gst_string_new (_gst_first_error_file)); xfree (_gst_first_error_file); } else PUSH_OOP (_gst_nil_oop); PUSH_INT (_gst_first_error_line); PUSH_OOP (_gst_string_new (_gst_first_error_str)); xfree (_gst_first_error_str); _gst_first_error_str = _gst_first_error_file = NULL; _gst_report_errors = oldReportErrors; if (send_block_value (3, 3)) PRIM_FAILED; else PRIM_SUCCEEDED_RELOAD_IP; } PRIM_SUCCEEDED; } UNPOP (3); PRIM_FAILED; } /* CCallbackDescriptor link */ primitive VMpr_CCallbackDescriptor_link [succeed,fail] { OOP oop1; _gst_primitives_executed++; oop1 = STACKTOP (); _gst_make_closure (oop1); /* Always fail so as to run the Smalltalk code that finishes the setup. */ PRIM_FAILED; } /* CFunctionDescriptor addressOf: funcNameString */ primitive VMpr_CFuncDescriptor_addressOf [succeed,fail] { OOP oop1; _gst_primitives_executed++; oop1 = STACKTOP (); if (IS_CLASS (oop1, _gst_string_class)) { char *funcName = (char *) _gst_to_cstring (oop1); void *funcAddr = _gst_lookup_function (funcName); if (funcAddr) { POP_N_OOPS (1); SET_STACKTOP (COBJECT_NEW (funcAddr, _gst_nil_oop, _gst_c_object_class)); PRIM_SUCCEEDED; } } PRIM_FAILED; } /* Object snapshot: aString */ primitive VMpr_ObjectMemory_snapshot [succeed,fail] { char *fileName; OOP oop2; interp_jmp_buf jb; _gst_primitives_executed++; oop2 = POP_OOP (); if (IS_CLASS (oop2, _gst_string_class)) { mst_Boolean success; fileName = _gst_to_cstring (oop2); errno = 0; /* first overwrite the stack top with true. When we resume from the save, the stack will be in this state. See below. */ SET_STACKTOP (_gst_true_oop); push_jmp_buf (&jb, false, get_active_process ()); if (setjmp (jb.jmpBuf) == 0) success = _gst_save_to_file (fileName); else { success = false; errno = EINTR; } xfree (fileName); if (pop_jmp_buf ()) { stop_execution (); PRIM_SUCCEEDED; } else if (success) { /* We're returning in the parent, not resuming from save. Overwite the stack top again, with false this time, to let the caller know which side of the fork we're on. */ SET_STACKTOP (_gst_false_oop); PRIM_SUCCEEDED; } else _gst_set_errno (errno); } UNPOP (1); PRIM_FAILED; } /* Object basicPrint */ primitive VMpr_Object_basicPrint [succeed] { _gst_primitives_executed++; printf ("Object: %O", STACKTOP ()); fflush (stdout); PRIM_SUCCEEDED; } /* Object makeWeak */ primitive VMpr_Object_makeWeak [succeed,fail] { OOP oop1 = STACKTOP (); _gst_primitives_executed++; if (IS_INT (oop1)) PRIM_FAILED; if (!IS_OOP_WEAK (oop1)) _gst_make_oop_weak (oop1); PRIM_SUCCEEDED; } /* Stream fileInLine: lineNum fileName: aString at: charPosInt */ primitive VMpr_Stream_fileInLine [succeed,fail] { OOP oop4 = POP_OOP (); OOP oop3 = POP_OOP (); OOP oop2 = (numArgs == 4 ? POP_OOP () : oop3); OOP oop1 = POP_OOP (); OOP streamOOP = STACKTOP (); enum undeclared_strategy old; if (!RECEIVER_IS_OOP (streamOOP)) PRIM_FAILED; if (IS_INT (oop1) && (IS_NIL (oop3) || (IS_CLASS (oop3, _gst_string_class) && IS_INT (oop4)))) { mst_Boolean interrupted; intptr_t arg1 = TO_INT (oop1); intptr_t arg4 = TO_INT (oop4); _gst_push_stream_oop (streamOOP); _gst_set_stream_info (arg1, oop2, oop3, arg4); old = _gst_set_undeclared (UNDECLARED_GLOBALS); interrupted = parse_stream_with_protection (false); _gst_set_undeclared (old); _gst_pop_stream (false); if (interrupted) stop_execution (); PRIM_SUCCEEDED; } PRIM_FAILED; } /* FileDescriptor>>#fileOp..., variadic */ primitive VMpr_FileDescriptor_fileOp [succeed,fail] { char *fileName, *fileName2; gst_file_stream fileStream; int fd, rc; OOP oop1; OOP *oopVec = alloca (numArgs * sizeof (OOP)); int i; intptr_t arg1; OOP resultOOP; _gst_primitives_executed++; for (i = numArgs; --i >= 0;) oopVec[i] = POP_OOP (); resultOOP = oop1 = STACKTOP (); UNPOP (numArgs); if (!IS_INT (oopVec[0])) goto fail; arg1 = TO_INT (oopVec[0]); switch (arg1) { case PRIM_OPEN_FILE: case PRIM_OPEN_PIPE: { int is_pipe = false; char *fileMode = NULL; int access = 0; struct stat st; /* open: fileName[1] mode: mode[2] or popen: command[1] dir: direction[2] */ fileName = _gst_to_cstring (oopVec[1]); if (IS_INT (oopVec[2]) && arg1 == PRIM_OPEN_FILE) { fd = open ((char *) fileName, TO_INT (oopVec[2])); access = TO_INT (oopVec[2]) && (O_RDONLY | O_WRONLY | O_RDWR); } else if (!is_a_kind_of (OOP_CLASS (oopVec[1]), _gst_string_class)) fd = -1; else if (arg1 == PRIM_OPEN_FILE) { fileMode = _gst_to_cstring (oopVec[2]); fd = _gst_open_file ((char *) fileName, (char *) fileMode); memset (&st, 0, sizeof (st)); fstat (fd, &st); is_pipe = S_ISFIFO(st.st_mode) ? true : S_ISREG(st.st_mode) && st.st_size > 0 ? false : -1; } else { fileMode = _gst_to_cstring (oopVec[2]); fd = _gst_open_pipe (fileName, fileMode); is_pipe = true; } if (fileMode) { access = strchr (fileMode, '+') ? O_RDWR : (fileMode[0] == 'r') ? O_RDONLY : O_WRONLY; xfree (fileMode); } xfree (fileName); if (fd < 0) goto fail; _gst_set_file_stream_file (oop1, fd, oopVec[1], is_pipe, access, false); goto succeed; } case PRIM_MK_TEMP: fileName = _gst_to_cstring (oopVec[1]); asprintf (&fileName2, "%sXXXXXX", fileName); fd = mkstemp ((char *) fileName2); xfree (fileName); if (fd < 0) { xfree (fileName2); goto fail; } _gst_set_file_stream_file (oop1, fd, _gst_string_new (fileName2), false, O_RDWR, false); xfree (fileName2); goto succeed; } fileStream = (gst_file_stream) OOP_TO_OBJ (oop1); if (!IS_INT (fileStream->fd)) goto fail; fd = TO_INT (fileStream->fd); switch (arg1) { case PRIM_CLOSE_FILE: /* FileDescriptor close */ _gst_remove_fd_polling_handlers (fd); rc = close (fd); if (rc == 0) fileStream->fd = _gst_nil_oop; resultOOP = FROM_INT (rc); goto succeed; case PRIM_FSEEK_SET: /* FileDescriptor position: position */ if (IS_OFF_T (oopVec[1]) && lseek (fd, TO_OFF_T (oopVec[1]), SEEK_SET) < 0) { errno = 0; break; } else goto succeed; case PRIM_FTELL: /* FileDescriptor position */ { off_t off = lseek(fd, 0, SEEK_CUR); if (off < 0) { errno = 0; break; } resultOOP = FROM_OFF_T (off); goto succeed; } case PRIM_FEOF: { /* FileDescriptor atEnd */ off_t oldPos; oldPos = lseek (fd, 0, SEEK_CUR); if (oldPos >= 0 && lseek (fd, 0, SEEK_END) == oldPos) resultOOP = _gst_true_oop; else { resultOOP = _gst_false_oop; if (oldPos >= 0) lseek (fd, oldPos, SEEK_SET); } errno = 0; goto succeed; } case PRIM_FSIZE: { struct stat statBuf; if (fstat (fd, &statBuf) < 0) { errno = 0; break; } resultOOP = FROM_INT (statBuf.st_size); goto succeed; } case PRIM_PUT_CHARS: if (!IS_INT(oopVec[1]) && (OOP_INSTANCE_SPEC (oopVec[1]) & ISP_INDEXEDVARS) != GST_ISP_FIXED && _gst_log2_sizes[OOP_INSTANCE_SPEC (oopVec[1]) & ISP_SHAPE] == 0) { char *data = STRING_OOP_CHARS (oopVec[1]); intptr_t from = TO_INT (oopVec[2]); intptr_t to = TO_INT (oopVec[3]); ssize_t result; if (to >= from - 1 && from > 0 && to <= NUM_INDEXABLE_FIELDS (oopVec[1])) { result = _gst_write (fd, data + from - 1, to - from + 1); if (result != -1) { resultOOP = FROM_C_ULONG ((size_t) result); goto succeed; } } } break; case PRIM_GET_CHARS: /* only works for strings */ if (!IS_INT(oopVec[1]) && (OOP_INSTANCE_SPEC (oopVec[1]) & ISP_INDEXEDVARS) != GST_ISP_FIXED && _gst_log2_sizes[OOP_INSTANCE_SPEC (oopVec[1]) & ISP_SHAPE] == 0) { char *data = STRING_OOP_CHARS (oopVec[1]); intptr_t from = TO_INT (oopVec[2]); intptr_t to = TO_INT (oopVec[3]); ssize_t result; if (to >= from - 1 && from > 0 && to <= NUM_INDEXABLE_FIELDS (oopVec[1])) { /* Parameters to system calls are not guaranteed to generate a SIGSEGV and for this reason we must touch them manually. */ _gst_grey_oop_range (data + from - 1, to - from + 1); result = _gst_read (fd, data + from - 1, to - from + 1); if (result != -1) { resultOOP = FROM_C_ULONG ((size_t) result); goto succeed; } } } break; case PRIM_GET_CHARS_AT: if (!IS_INT(oopVec[1]) && (OOP_INSTANCE_SPEC (oopVec[1]) & ISP_INDEXEDVARS) != GST_ISP_FIXED && _gst_log2_sizes[OOP_INSTANCE_SPEC (oopVec[1]) & ISP_SHAPE] == 0 && IS_OFF_T (oopVec[4])) { char *data = STRING_OOP_CHARS (oopVec[1]); intptr_t from = TO_INT (oopVec[2]); intptr_t to = TO_INT (oopVec[3]); off_t ofs = TO_OFF_T (oopVec[4]); ssize_t result; if (to >= from - 1 && from > 0 && to <= NUM_INDEXABLE_FIELDS (oopVec[1])) { /* Parameters to system calls are not guaranteed to generate a SIGSEGV and for this reason we must touch them manually. */ _gst_grey_oop_range (data + from - 1, to - from + 1); #if HAVE_PREAD result = pread (fd, data + from - 1, to - from + 1, ofs); #else { off_t save = lseek (fd, ofs, SEEK_SET); if (save != -1) { result = _gst_read (fd, data + from - 1, to - from + 1); lseek (fd, save, SEEK_SET); } else result = -1; } #endif if (result != -1) { resultOOP = FROM_C_ULONG ((size_t) result); goto succeed; } } } break; case PRIM_PUT_CHARS_AT: if (!IS_INT(oopVec[1]) && (OOP_INSTANCE_SPEC (oopVec[1]) & ISP_INDEXEDVARS) != GST_ISP_FIXED && _gst_log2_sizes[OOP_INSTANCE_SPEC (oopVec[1]) & ISP_SHAPE] == 0 && IS_OFF_T (oopVec[4])) { char *data = STRING_OOP_CHARS (oopVec[1]); intptr_t from = TO_INT (oopVec[2]); intptr_t to = TO_INT (oopVec[3]); off_t ofs = TO_OFF_T (oopVec[4]); ssize_t result; if (to >= from - 1 && from > 0 && to <= NUM_INDEXABLE_FIELDS (oopVec[1])) { /* Parameters to system calls are not guaranteed to generate a SIGSEGV and for this reason we must touch them manually. */ _gst_grey_oop_range (data + from - 1, to - from + 1); #if HAVE_PWRITE result = pwrite (fd, data + from - 1, to - from + 1, ofs); #else { off_t save = lseek (fd, ofs, SEEK_SET); if (save != -1) { result = _gst_write (fd, data + from - 1, to - from + 1); lseek (fd, save, SEEK_SET); } else result = -1; } #endif if (result != -1) { resultOOP = FROM_C_ULONG ((size_t) result); goto succeed; } } } break; case PRIM_FTRUNCATE: { off_t pos; pos = lseek (fd, 0, SEEK_CUR); if (pos < 0) break; ftruncate (fd, pos); goto succeed; } case PRIM_FSEEK_CUR: /* FileDescriptor skip: */ if (IS_OFF_T (oopVec[1]) && lseek (fd, TO_OFF_T (oopVec[1]), SEEK_CUR) < 0) break; else goto succeed; case PRIM_SYNC_POLL: { int result; result = _gst_sync_file_polling (fd, TO_INT (oopVec[1])); if (result >= 0) { resultOOP = FROM_INT (result); goto succeed; } } break; case PRIM_ASYNC_POLL: { int result; result = _gst_async_file_polling (fd, TO_INT (oopVec[1]), oopVec[2]); if (result >= 0) goto succeed; } break; case PRIM_IS_PIPE: { off_t result; result = lseek (fd, 0, SEEK_END); if (result != -1) { lseek (fd, result, SEEK_SET); resultOOP = _gst_false_oop; goto succeed; } else if (errno == ESPIPE || errno == EINVAL) { resultOOP = _gst_true_oop; errno = 0; goto succeed; } goto fail; } case PRIM_SHUTDOWN_WRITE: shutdown (FD_TO_SOCKET (fd), 1); #ifdef ENOTSOCK if (errno == ENOTSOCK && isatty (fd)) { char buf[1]; write (fd, buf, 0); errno = 0; } #endif goto succeed; } fail: if (errno) _gst_set_errno (errno); PRIM_FAILED; succeed: POP_N_OOPS (numArgs); SET_STACKTOP (resultOOP); PRIM_SUCCEEDED; } /* FileDescriptor>>#socketOp..., socket version, variadic */ primitive VMpr_FileDescriptor_socketOp [succeed,fail] { gst_file_stream fileStream; int fd, rc; OOP oop1, resultOOP; OOP *oopVec = alloca (numArgs * sizeof (OOP)); int i; intptr_t arg1; _gst_primitives_executed++; #ifdef HAVE_SOCKETS for (i = numArgs; --i >= 0;) oopVec[i] = POP_OOP (); resultOOP = oop1 = STACKTOP (); UNPOP (numArgs); if (!IS_INT (oopVec[0])) goto fail; arg1 = TO_INT (oopVec[0]); fileStream = (gst_file_stream) OOP_TO_OBJ (oop1); if (IS_NIL (fileStream->fd)) goto fail; fd = TO_INT (fileStream->fd); switch (arg1) { case PRIM_CLOSE_FILE: /* FileDescriptor close */ { int result; _gst_remove_fd_polling_handlers (fd); rc = close (fd); if (rc == 0) fileStream->fd = _gst_nil_oop; resultOOP = FROM_INT (rc); goto succeed; } case PRIM_PUT_CHARS: if (!IS_INT(oopVec[1]) && (OOP_INSTANCE_SPEC (oopVec[1]) & ISP_INDEXEDVARS) != GST_ISP_FIXED && _gst_log2_sizes[OOP_INSTANCE_SPEC (oopVec[1]) & ISP_SHAPE] == 0) { char *data = STRING_OOP_CHARS (oopVec[1]); intptr_t from = TO_INT (oopVec[2]); intptr_t to = TO_INT (oopVec[3]); ssize_t result; if (to >= from - 1 && from > 0 && to <= NUM_INDEXABLE_FIELDS (oopVec[1])) { clear_socket_error (); result = _gst_send (fd, data + from - 1, to - from + 1, 0); if (result != -1) { resultOOP = FROM_C_ULONG ((size_t) result); goto succeed; } } } break; case PRIM_GET_CHARS: /* only works for strings */ if (!IS_INT(oopVec[1]) && (OOP_INSTANCE_SPEC (oopVec[1]) & ISP_INDEXEDVARS) != GST_ISP_FIXED && _gst_log2_sizes[OOP_INSTANCE_SPEC (oopVec[1]) & ISP_SHAPE] == 0) { char *data = STRING_OOP_CHARS (oopVec[1]); intptr_t from = TO_INT (oopVec[2]); intptr_t to = TO_INT (oopVec[3]); ssize_t result; if (to >= from - 1 && from > 0 && to <= NUM_INDEXABLE_FIELDS (oopVec[1])) { /* Parameters to system calls are not guaranteed to generate a SIGSEGV and for this reason we must touch them manually. */ _gst_grey_oop_range (data + from - 1, to - from + 1); clear_socket_error (); result = _gst_recv (fd, data + from - 1, to - from + 1, 0); if (result != -1) { resultOOP = FROM_C_ULONG ((size_t) result); goto succeed; } } } break; case PRIM_SYNC_POLL: { int result; result = _gst_sync_file_polling (fd, TO_INT (oopVec[1])); if (result >= 0) { resultOOP = FROM_INT (result); goto succeed; } } break; case PRIM_ASYNC_POLL: { int result; result = _gst_async_file_polling (fd, TO_INT (oopVec[1]), oopVec[2]); if (result >= 0) goto succeed; } break; case PRIM_IS_PIPE: resultOOP =_gst_true_oop; goto succeed; break; } #endif fail: if (errno) _gst_set_errno (errno); PRIM_FAILED; succeed: POP_N_OOPS (numArgs); SET_STACKTOP (resultOOP); PRIM_SUCCEEDED; } /* C callout primitives. */ primitive VMpr_CFuncDescriptor_asyncCall [succeed,fail] { OOP resultOOP; volatile gst_method_context context; OOP contextOOP, cFuncOOP, receiverOOP; interp_jmp_buf jb; _gst_primitives_executed++; if (numArgs == 1) { contextOOP = POP_OOP (); context = (gst_method_context) OOP_TO_OBJ (contextOOP); receiverOOP = context->receiver; } else { contextOOP = _gst_this_context_oop; context = (gst_method_context) OOP_TO_OBJ (contextOOP); receiverOOP = _gst_self; } cFuncOOP = STACKTOP (); push_jmp_buf (&jb, false, _gst_nil_oop); if (setjmp (jb.jmpBuf) == 0) resultOOP = _gst_invoke_croutine (cFuncOOP, receiverOOP, context->contextStack); else resultOOP = NULL; if (pop_jmp_buf ()) { stop_execution (); PRIM_SUCCEEDED; } else if (resultOOP) { SET_EXCEPT_FLAG (true); PRIM_SUCCEEDED; } if (numArgs == 1) UNPOP (1); PRIM_FAILED; } primitive VMpr_CFuncDescriptor_call [succeed,fail] { volatile gst_method_context context; gst_object resultHolderObj; OOP receiverOOP, contextOOP, cFuncOOP, resultOOP; volatile OOP resultHolderOOP; interp_jmp_buf jb; _gst_primitives_executed++; resultHolderOOP = POP_OOP (); if (numArgs == 2) { contextOOP = POP_OOP (); context = (gst_method_context) OOP_TO_OBJ (contextOOP); receiverOOP = context->receiver; } else { contextOOP = _gst_this_context_oop; context = (gst_method_context) OOP_TO_OBJ (contextOOP); receiverOOP = _gst_self; } cFuncOOP = POP_OOP (); /* Make the result reachable, and also push it before the active process can change. */ PUSH_OOP (resultHolderOOP); push_jmp_buf (&jb, false, get_active_process ()); if (setjmp (jb.jmpBuf) == 0) resultOOP = _gst_invoke_croutine (cFuncOOP, receiverOOP, context->contextStack); else resultOOP = NULL; if (pop_jmp_buf ()) { stop_execution (); PRIM_SUCCEEDED; } else if (resultOOP) { if (!IS_NIL (resultHolderOOP)) { resultHolderObj = OOP_TO_OBJ (resultHolderOOP); resultHolderObj->data[0] = resultOOP; } SET_EXCEPT_FLAG (true); PRIM_SUCCEEDED; } /* Undo changes to the stack made above */ POP_N_OOPS (1); PUSH_OOP (cFuncOOP); if (numArgs == 2) PUSH_OOP (contextOOP); PUSH_OOP (resultHolderOOP); PRIM_FAILED; } primitive VMpr_Object_makeEphemeron [succeed,fail] { _gst_primitives_executed++; if (NUM_OOPS (OOP_TO_OBJ (STACKTOP ())) == 0) PRIM_FAILED; MAKE_OOP_EPHEMERON (STACKTOP ()); PRIM_SUCCEEDED; } /* Namespace current: aNamespace */ primitive VMpr_Namespace_setCurrent [fail] { OOP oop1; _gst_primitives_executed++; oop1 = STACKTOP (); if (is_a_kind_of (OOP_CLASS (oop1), _gst_dictionary_class)) _gst_current_namespace = oop1; else if (is_a_kind_of (OOP_CLASS (oop1), _gst_class_class)) _gst_current_namespace = _gst_class_variable_dictionary (oop1); /* Always fail */ PRIM_FAILED; } primitive VMpr_ObjectMemory_gcPrimitives : prim_id VMpr_ObjectMemory_scavenge [succeed], prim_id VMpr_ObjectMemory_compact [succeed], prim_id VMpr_ObjectMemory_globalGarbageCollect [succeed], prim_id VMpr_ObjectMemory_incrementalGCStep [succeed], prim_id VMpr_ObjectMemory_finishIncrementalGC [succeed] { _gst_primitives_executed++; switch (id) { case prim_id (VMpr_ObjectMemory_scavenge): _gst_scavenge (); break; case prim_id (VMpr_ObjectMemory_compact): _gst_global_compact (); break; case prim_id (VMpr_ObjectMemory_globalGarbageCollect): _gst_global_gc (0); break; case prim_id (VMpr_ObjectMemory_incrementalGCStep): SET_STACKTOP_BOOLEAN (_gst_incremental_gc_step ()); break; case prim_id (VMpr_ObjectMemory_finishIncrementalGC): _gst_finish_incremental_gc (); break; } PRIM_SUCCEEDED; } /* SystemDictionary profilerOn */ primitive VMpr_SystemDictionary_rawProfile [succeed] { OOP oop1 = POP_OOP (); if (_gst_raw_profile) { _gst_record_profile (_gst_this_method, NULL, -1); SET_STACKTOP (_gst_raw_profile); _gst_unregister_oop (_gst_raw_profile); } else SET_STACKTOP (_gst_nil_oop); if (IS_NIL (oop1)) _gst_raw_profile = NULL; else { _gst_raw_profile = oop1; _gst_register_oop (_gst_raw_profile); _gst_saved_bytecode_counter = _gst_bytecode_counter; } PRIM_SUCCEEDED; } #undef INT_BIN_OP #undef BOOL_BIN_OP smalltalk-3.2.5/libgst/sockets.h0000644000175000017500000000520012123404352013527 00000000000000/******************************** -*- C -*- **************************** * * External definitions for C - Smalltalk interface module * * ***********************************************************************/ /*********************************************************************** * * Copyright 1988,89,90,91,92,94,95,99,2000,2001,2002,2006,2008,2009 * Free Software Foundation, Inc. * Written by Steve Byrne. * * This file is part of GNU Smalltalk. * * GNU Smalltalk is free software; you can redistribute it and/or modify it * under the terms of the GNU General Public License as published by the Free * Software Foundation; either version 2, or (at your option) any later * version. * * Linking GNU Smalltalk statically or dynamically with other modules is * making a combined work based on GNU Smalltalk. Thus, the terms and * conditions of the GNU General Public License cover the whole * combination. * * In addition, as a special exception, the Free Software Foundation * give you permission to combine GNU Smalltalk with free software * programs or libraries that are released under the GNU LGPL and with * independent programs running under the GNU Smalltalk virtual machine. * * You may copy and distribute such a system following the terms of the * GNU GPL for GNU Smalltalk and the licenses of the other code * concerned, provided that you include the source code of that other * code when and as the GNU GPL requires distribution of source code. * * Note that people who make modified versions of GNU Smalltalk are not * obligated to grant this special exception for their modified * versions; it is their choice whether to do so. The GNU General * Public License gives permission to release a modified version without * this exception; this exception also makes it possible to release a * modified version which carries forward this exception. * * GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or * FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for * more details. * * You should have received a copy of the GNU General Public License along with * GNU Smalltalk; see the file COPYING. If not, write to the Free Software * Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * ***********************************************************************/ #ifndef GST_SOCKETS_H #define GST_SOCKETS_H /* Adds to the mapping table the socket functions supported by GNU Smalltalk. */ extern void _gst_init_sockets (void) ATTRIBUTE_HIDDEN; #endif /* GST_SOCKETS_H */ smalltalk-3.2.5/libgst/input.c0000644000175000017500000006207012130343734013222 00000000000000/******************************** -*- C -*- **************************** * * Input module: stream interface and Readline completion handling * * ***********************************************************************/ /*********************************************************************** * * Copyright 2001, 2002, 2003, 2005, 2006, 2008, 2009 * Free Software Foundation, Inc. * Written by Paolo Bonzini. * * This file is part of GNU Smalltalk. * * GNU Smalltalk is free software; you can redistribute it and/or modify it * under the terms of the GNU General Public License as published by the Free * Software Foundation; either version 2, or (at your option) any later * version. * * Linking GNU Smalltalk statically or dynamically with other modules is * making a combined work based on GNU Smalltalk. Thus, the terms and * conditions of the GNU General Public License cover the whole * combination. * * In addition, as a special exception, the Free Software Foundation * give you permission to combine GNU Smalltalk with free software * programs or libraries that are released under the GNU LGPL and with * independent programs running under the GNU Smalltalk virtual machine. * * You may copy and distribute such a system following the terms of the * GNU GPL for GNU Smalltalk and the licenses of the other code * concerned, provided that you include the source code of that other * code when and as the GNU GPL requires distribution of source code. * * Note that people who make modified versions of GNU Smalltalk are not * obligated to grant this special exception for their modified * versions; it is their choice whether to do so. The GNU General * Public License gives permission to release a modified version without * this exception; this exception also makes it possible to release a * modified version which carries forward this exception. * * GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or * FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for * more details. * * You should have received a copy of the GNU General Public License along with * GNU Smalltalk; see the file COPYING. If not, write to the Free Software * Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * ***********************************************************************/ #include "gstpriv.h" #ifdef HAVE_READLINE # include # include #endif typedef struct gst_file_segment { OBJ_HEADER; OOP fileOOP; OOP startPos; OOP length; } *gst_file_segment; typedef struct string_stream { char *strBase; /* base of asciz string */ const char *str; /* pointer into asciz string */ } string_stream; typedef struct unix_file_stream { int fd; char *buf; const char *ptr; const char *end; } unix_file_stream; typedef struct oop_stream { OOP oop; char *buf; char *ptr; const char *end; } oop_stream; typedef struct input_stream { stream_type type; /* the 3 buffered characters */ char pushedBackChars[3]; /* number of chars pushed back */ int pushedBackCount; int line; int column; const char *prompt; OOP fileOOP; /* the object stored in FileSegments */ const char *fileName; off_t fileOffset; union { unix_file_stream u_st_file; string_stream u_st_str; oop_stream u_st_oop; } st; struct input_stream *prevStream; } *input_stream; #define st_file st.u_st_file #define st_str st.u_st_str #define st_oop st.u_st_oop /* The internal interface used by _gst_next_char. */ static int my_getc (input_stream stream); /* Return the File object or a file name for the topmost stream in the stack if it is of type STREAM_FILE; nil otherwise. */ static OOP get_cur_file (void); /* Print a line indicator in front of an error message. */ static void line_stamp (int line); /* Allocate and push a new stream of type TYPE on the stack; the new stream is then available through IN_STREAM. */ static input_stream push_new_stream (stream_type type); /* The topmost stream in the stack, and the head of the linked list that implements the stack. */ static input_stream in_stream = NULL; /* Poll FD until it is available for input (or until it returns POLLHUP) and then perform a read system call. */ static int poll_and_read (int fd, char *buf, int n); /* If true, readline is disabled. */ mst_Boolean _gst_no_tty = false; /* >= 1 if completions are enabled, < 1 if they are not. Available for completeness even if Readline is not used. */ static int completions_enabled = 1; #ifdef HAVE_READLINE /* Storage for the possible completions */ static char **completions; /* Number of completions available. */ static int count; /* Number of completions before the array must be resized. */ static int free_items; /* Number of sorted completions. Completions are not sorted until we are requested to use them. */ static int sorted_count; /* Internal functions */ static void merge (char **a1, int count1, char **a2, int count2, mst_Boolean reallocate); static void add_completion (const char *str, int len); static int compare_strings (const PTR a, const PTR b); /* Readline callbacks */ static int readline_getc (FILE * file); static char *readline_quote_filename (const char *s, int rtype, const char *qcp); static char *readline_dequote_filename (const char *s, char qc); static char *symbol_generator (const char *text, int state); static char **readline_match_symbols (char *text, int start, int end); #endif /* Generic "stream" interface. A stream is an abstraction for input and output. It is most like common lisp streams. Basically, these streams provide transparent reading from either a Smalltalk string, or a UNIX file. They stack, and the previous stream can be restored by doing a "_gst_pop_stream" which optionally "closes" the current stream and goes back to using the previous stream. The `readline()' interface: The behavior is like the Smalltalk String interface. The end-of-string or a NULL strBase-pointer decides to read in a new line. The prompt is still shown by the readline() call. */ void _gst_pop_stream (mst_Boolean closeIt) { input_stream stream; stream = in_stream; in_stream = in_stream->prevStream; _gst_unregister_oop (stream->fileOOP); switch (stream->type) { case STREAM_STRING: xfree (stream->st_str.strBase); break; #ifdef HAVE_READLINE case STREAM_READLINE: #endif /* HAVE_READLINE */ case STREAM_OOP: xfree (stream->st_oop.buf); _gst_unregister_oop (stream->st_oop.oop); break; case STREAM_FILE: xfree (stream->st_file.buf); if (closeIt) close (stream->st_file.fd); break; } xfree (stream); } void _gst_push_unix_file (int fd, const char *fileName) { input_stream newStream; newStream = push_new_stream (STREAM_FILE); newStream->st_file.fd = fd; newStream->st_file.buf = xmalloc (1024); newStream->st_file.ptr = newStream->st_file.buf; newStream->st_file.end = newStream->st_file.buf; newStream->fileName = fileName; newStream->fileOffset = lseek (fd, 0, SEEK_CUR); } void _gst_push_stream_oop (OOP oop) { input_stream newStream; newStream = push_new_stream (STREAM_OOP); newStream->st_oop.oop = oop; newStream->st_oop.buf = NULL; newStream->st_oop.ptr = NULL; newStream->st_oop.end = NULL; newStream->fileName = "a Smalltalk Stream"; _gst_register_oop (oop); } void _gst_push_smalltalk_string (OOP stringOOP) { input_stream newStream; newStream = push_new_stream (STREAM_STRING); newStream->st_str.strBase = (char *) _gst_to_cstring (stringOOP); newStream->st_str.str = newStream->st_str.strBase; newStream->fileName = "a Smalltalk string"; } void _gst_push_cstring (const char *string) { input_stream newStream; newStream = push_new_stream (STREAM_STRING); newStream->st_str.strBase = xstrdup (string); newStream->st_str.str = newStream->st_str.strBase; newStream->fileName = "a C string"; } void _gst_push_stdin_string (void) { #ifdef HAVE_READLINE input_stream newStream; if (_gst_no_tty) { #endif _gst_push_unix_file (0, "stdin"); return; #ifdef HAVE_READLINE } if (count == 0) _gst_add_all_symbol_completions (); newStream = push_new_stream (STREAM_READLINE); newStream->fileOffset = 0; newStream->st_oop.buf = NULL; newStream->st_oop.ptr = NULL; newStream->st_oop.end = NULL; newStream->fileName = "stdin"; /* that's where we get input from */ #endif } input_stream push_new_stream (stream_type type) { input_stream newStream; newStream = (input_stream) xmalloc (sizeof (struct input_stream)); newStream->pushedBackCount = 0; newStream->line = 1; newStream->column = 0; newStream->fileOffset = -1; newStream->type = type; newStream->fileName = NULL; newStream->prompt = NULL; newStream->fileOOP = _gst_nil_oop; newStream->prevStream = in_stream; in_stream = newStream; return (newStream); } void _gst_set_stream_info (int line, OOP fileOOP, OOP fileNameOOP, int fileOffset) { in_stream->line = line; in_stream->column = 0; _gst_register_oop (fileOOP); in_stream->fileOOP = fileOOP; in_stream->fileOffset = fileOffset; if (!IS_NIL (fileNameOOP)) in_stream->fileName = _gst_to_cstring (fileNameOOP); } void refill_stream (input_stream stream, char *buf, int new_line) { size_t old_size = stream->st_oop.ptr - stream->st_oop.buf; size_t size = old_size + strlen (buf); /* Leave space for the '\0' at the end. */ stream->st_oop.buf = xrealloc (stream->st_oop.buf, size + new_line + 1); stream->st_oop.ptr = stream->st_oop.buf + old_size; stream->st_oop.end = stream->st_oop.buf + size + new_line; memcpy (stream->st_oop.ptr, buf, size - old_size); if (new_line) { stream->st_oop.ptr[size - old_size] = '\n'; stream->st_oop.ptr[size - old_size + 1] = '\0'; } else stream->st_oop.ptr[size - old_size] = '\0'; free (buf); } int my_getc (input_stream stream) { int ic = 0; switch (stream->type) { case STREAM_STRING: ic = (unsigned char) *stream->st_str.str; if (!ic) return EOF; else stream->st_str.str++; return ic; case STREAM_OOP: /* Refill the buffer... */ if (stream->st_oop.ptr == stream->st_oop.end) { char *buf; _gst_msg_sendf(&buf, "%s %o nextAvailable: %i", stream->st_oop.oop, 1024); if (!buf || !*buf) return EOF; refill_stream (stream, buf, false); } return (unsigned char) *stream->st_oop.ptr++; case STREAM_FILE: if (in_stream->column == 0 && in_stream->prompt) { printf ("%s", in_stream->prompt); fflush(stdout); } /* Refill the buffer... */ if (stream->st_file.ptr == stream->st_file.end) { int n = poll_and_read (stream->st_file.fd, stream->st_file.buf, 1024); if (n < 0) n = 0; stream->fileOffset += stream->st_file.ptr - stream->st_file.buf; stream->st_file.end = stream->st_file.buf + n; stream->st_file.ptr = stream->st_file.buf; } return (stream->st_file.ptr == stream->st_file.end) ? EOF : (unsigned char) *stream->st_file.ptr++; #ifdef HAVE_READLINE case STREAM_READLINE: /* Refill the buffer... */ if (stream->st_oop.ptr == stream->st_oop.end) { char *buf = readline (in_stream->prompt ? (char *) in_stream->prompt : (char *) ""); if (!buf) return EOF; add_history (buf); refill_stream (stream, buf, true); } return (unsigned char) *stream->st_oop.ptr++; #endif /* HAVE_READLINE */ default: _gst_errorf ("Bad stream type passed to my_getc"); _gst_had_error = true; } return (ic); } mst_Boolean _gst_get_cur_stream_prompt (void) { return in_stream && in_stream->prompt; } stream_type _gst_get_cur_stream_type (void) { if (in_stream) return (in_stream->type); else return (STREAM_UNKNOWN); } OOP _gst_get_source_string (off_t startPos, off_t endPos) { char *p; OOP result; int size; if (!in_stream) return (_gst_nil_oop); /* FIXME: check isPipe too? */ if (startPos != -1 && !_gst_get_cur_stream_prompt ()) { OOP fileOOP; gst_file_segment fileSegment; inc_ptr incPtr; incPtr = INC_SAVE_POINTER (); fileOOP = get_cur_file (); if (!IS_NIL (fileOOP)) { INC_ADD_OOP (fileOOP); fileSegment = (gst_file_segment) new_instance (_gst_file_segment_class, &result); fileSegment->fileOOP = fileOOP; fileSegment->startPos = from_c_int_64 (startPos); fileSegment->length = from_c_int_64 (endPos - startPos); assert (to_c_int_64 (fileSegment->length) >= 0); INC_RESTORE_POINTER (incPtr); return (result); } INC_RESTORE_POINTER (incPtr); } switch (in_stream->type) { case STREAM_STRING: p = in_stream->st_str.strBase; break; #ifdef HAVE_READLINE case STREAM_READLINE: #endif /* HAVE_READLINE */ case STREAM_OOP: case STREAM_FILE: p = in_stream->st_oop.buf; break; default: return (_gst_nil_oop); } if (startPos == -1) result = _gst_string_new (p); else result = _gst_counted_string_new (p + (startPos - in_stream->fileOffset), endPos - startPos); if (in_stream->type != STREAM_STRING) { /* Copy back to the beginning of the buffer to save memory. */ size = in_stream->st_oop.end - in_stream->st_oop.ptr; if (size) memmove (in_stream->st_oop.buf, in_stream->st_oop.ptr, size); in_stream->st_oop.buf[size] = 0; in_stream->fileOffset += in_stream->st_oop.ptr - in_stream->st_oop.buf; in_stream->st_oop.ptr = in_stream->st_oop.buf; in_stream->st_oop.end = in_stream->st_oop.buf + size; } return result; } OOP get_cur_file (void) { const char *fullFileName; if (!in_stream) return _gst_nil_oop; if (!IS_NIL (in_stream->fileOOP)) return in_stream->fileOOP; if (in_stream->type != STREAM_FILE) return (_gst_nil_oop); if (strcmp (in_stream->fileName, "stdin") == 0) fullFileName = strdup (in_stream->fileName); else fullFileName = _gst_get_full_file_name (in_stream->fileName); in_stream->fileOOP = _gst_string_new (fullFileName); _gst_register_oop (in_stream->fileOOP); return (in_stream->fileOOP); } void _gst_warningf_at (int line, const char *str, ...) { va_list ap; va_start (ap, str); if (!_gst_report_errors) return; fflush (stdout); line_stamp (line); vfprintf (stderr, str, ap); fprintf (stderr, "\n"); fflush (stderr); va_end (ap); } void _gst_warningf (const char *str, ...) { va_list ap; va_start (ap, str); if (!_gst_report_errors) return; fflush (stdout); line_stamp (0); vfprintf (stderr, str, ap); fprintf (stderr, "\n"); fflush (stderr); va_end (ap); } void _gst_errorf_at (int line, const char *str, ...) { va_list ap; va_start (ap, str); if (_gst_report_errors) fflush (stdout); line_stamp (line); if (_gst_report_errors) { vfprintf (stderr, str, ap); fprintf (stderr, "\n"); fflush (stderr); } else { if (_gst_first_error_str == NULL) vasprintf (&_gst_first_error_str, str, ap); } va_end (ap); } void _gst_errorf (const char *str, ...) { va_list ap; va_start (ap, str); if (_gst_report_errors) fflush (stdout); line_stamp (0); if (_gst_report_errors) { vfprintf (stderr, str, ap); fprintf (stderr, "\n"); fflush (stderr); } else { if (_gst_first_error_str == NULL) vasprintf (&_gst_first_error_str, str, ap); } va_end (ap); } void _gst_yyerror (const char *s) { _gst_errorf ("%s", s); } YYLTYPE _gst_get_location (void) { YYLTYPE loc; loc.first_line = in_stream->line; loc.first_column = in_stream->column; if (!in_stream || in_stream->fileOffset == -1) loc.file_offset = -1; else /* Subtract 1 to mark the position of the last character we read. */ loc.file_offset = (in_stream->st_file.ptr - in_stream->st_file.buf + in_stream->fileOffset - 1); return loc; } void line_stamp (int line) { if (line <= 0 && in_stream) line = in_stream->line; if (_gst_report_errors) { if (in_stream) fprintf (stderr, "%s:%d: ", in_stream->fileName, line); else fprintf (stderr, "gst: "); } else { /* called internally with error handling */ if (in_stream) { if (in_stream->fileName) { if (_gst_first_error_str == NULL) _gst_first_error_file = strdup (in_stream->fileName); } if (_gst_first_error_str == NULL) _gst_first_error_line = line; } else { if (_gst_first_error_str == NULL) _gst_first_error_line = -1; } } } int _gst_next_char (void) { int ic; if (in_stream->pushedBackCount > 0) { ic = (unsigned char) in_stream->pushedBackChars[--in_stream->pushedBackCount]; return (ic); } else { ic = my_getc (in_stream); if (ic == '\n') { /* a new line that was not pushed back */ in_stream->line++; in_stream->column = 0; } else in_stream->column++; return (ic); } } void _gst_unread_char (int ic) { if (ic != EOF) in_stream->pushedBackChars[in_stream->pushedBackCount++] = ic; } /* These two are not used, but are provided for additional flexibility. */ void _gst_enable_completion (void) { completions_enabled++; } void _gst_disable_completion (void) { completions_enabled--; } int poll_and_read (int fd, char *buf, int n) { int result; _gst_wait_for_input (fd); if (_gst_sync_file_polling (fd, 0)) { do { errno = 0; result = _gst_read (fd, buf, n); } while ((result == -1) && (errno == EINTR)); return result; } else return -1; } void _gst_process_stdin (const char *prompt) { if (_gst_verbosity == 3 || isatty (0)) { printf ("GNU Smalltalk ready\n\n"); fflush (stdout); } _gst_non_interactive = false; _gst_push_stdin_string (); if (isatty (0)) in_stream->prompt = prompt; _gst_parse_stream (false); _gst_pop_stream (true); _gst_non_interactive = true; } mst_Boolean _gst_process_file (const char *fileName, enum gst_file_dir dir) { enum undeclared_strategy old; int fd; char *f; f = _gst_find_file (fileName, dir); if (!f) { errno = ENOENT; return false; } errno = 0; fd = _gst_open_file (f, "r"); if (fd != -1) { if (_gst_verbosity == 3) printf ("Processing %s\n", f); old = _gst_set_undeclared (UNDECLARED_GLOBALS); _gst_push_unix_file (fd, f); _gst_parse_stream (false); _gst_pop_stream (true); _gst_set_undeclared (old); errno = 0; } xfree (f); return (fd != -1); } #ifdef HAVE_READLINE /* Find apostrophes and double them */ char * readline_quote_filename (const char *s, int rtype, const char *qcp) { char *r, *base = alloca (strlen (s) * 2 + 2); const char *p; int quote; r = base; quote = *qcp; if (!quote) quote = *rl_completer_quote_characters; *r++ = quote; for (p = s; *p;) { if (*p == quote) *r++ = quote; *r++ = *p++; } *r++ = 0; return (strdup (base)); } /* Find double apostrophes and turn them to single ones */ char * readline_dequote_filename (const char *s, char qc) { char *r, *base = alloca (strlen (s) + 2); const char *p; if (!qc) return strdup (s); r = base; for (p = s; *p;) { if (*p == qc) p++; *r++ = *p++; } *r++ = 0; return (strdup (base)); } /* Enter an item in the list */ void add_completion (const char *str, int len) { char *s = xmalloc (len + 1); memcpy (s, str, len); s[len] = 0; if (!free_items) { free_items += 50; completions = (char **) xrealloc (completions, sizeof (char *) * (count + 50)); } free_items--; completions[count++] = s; } void _gst_add_symbol_completion (const char *str, int len) { const char *base = str; const char *p = str; if (completions_enabled < 1) return; while (len-- && *p) { if (*p++ == ':' && (base != p - 1)) { add_completion (base, p - base); base = p; } } /* We enter all unary and binary symbols in the table, too */ if (base == str) add_completion (base, p - base); } /* Merge the contents of a1 with the contents of a2, * storing the result in a2. If a1 and a2 overlap, * reallocate must be true. */ void merge (char **a1, int count1, char **a2, int count2, mst_Boolean reallocate) { char *source, *dest; /* Check if an array is empty */ if (!count1) return; if (!count2) { memmove (a1, a2, count1 * sizeof (char *)); return; } if (reallocate) { char **new = (char **) alloca (count1 * sizeof (char *)); memcpy (new, a1, count1 * sizeof (char *)); a1 = new; } source = a1[count1 - 1]; dest = a2[count2 - 1]; for (;;) { if (strcmp (source, dest) < 0) { /* Take it from the destination array */ a2[count2 + count1 - 1] = dest; if (--count2 == 0) { /* Any leftovers from the source array? */ memcpy (a1, a2, count1 * sizeof (char *)); return; } dest = a2[count2 - 1]; } else { /* Take it from the source array */ a2[count2 + count1 - 1] = source; if (--count1 == 0) return; source = a1[count1 - 1]; } } } /* Comparison function for qsort */ int compare_strings (const PTR a, const PTR b) { const char **s1 = (const char **) a; const char **s2 = (const char **) b; return strcmp (*s1, *s2); } /* Communication between symbol_generator and readline_match_symbols */ static int matches_left, current_index; char * symbol_generator (const char *text, int state) { if (matches_left == 0) return (NULL); /* Since we have to sort the array to perform the binary search, we remove duplicates and avoid that readline resorts the result. */ while (matches_left > 1 && strcmp (completions[current_index], completions[current_index + 1]) == 0) { current_index++; matches_left--; } matches_left--; return strdup (completions[current_index++]); } char ** readline_match_symbols (char *text, int start, int end) { int low, high, middle, len; /* Check for strings (not matched) and for symbols (matched) */ if (start != 0 && rl_line_buffer[start - 1] == '\'') { if (start == 1 || rl_line_buffer[start - 2] != '#') { return NULL; } } /* Prepare for binary searching. We use qsort when necessary, and merge the result, instead of doing expensive (quadratic) insertion sorts. */ if (sorted_count < count) { qsort (&completions[sorted_count], count - sorted_count, sizeof (char *), compare_strings); merge (&completions[sorted_count], count - sorted_count, completions, sorted_count, true); sorted_count = count; } /* Initialize current_index and matches_left with two binary searches. */ len = strlen (text); /* The first binary search gives the first matching item. */ low = -1; high = count; while (low + 1 != high) { middle = (low + high) / 2; if (strncmp (completions[middle], text, len) < 0) low = middle; else high = middle; } current_index = high; /* This binary search gives the first non-matching item instead */ low = -1; high = count; while (low + 1 != high) { middle = (low + high) / 2; if (strncmp (completions[middle], text, len) <= 0) low = middle; else high = middle; } matches_left = high - current_index; return matches_left ? rl_completion_matches (text, symbol_generator) : NULL; } int readline_getc (FILE * file) { int result; unsigned char ch; result = poll_and_read (fileno (file), &ch, 1); return (result < 1) ? EOF : (int) ch; } void _gst_initialize_readline (void) { static char everything[255]; int i; /* Allow conditional parsing of the ~/.inputrc file. */ rl_readline_name = (char *) "Smalltalk"; /* Always put filenames in quotes */ for (i = 0; i < 255; i++) everything[i] = i + 1; rl_filename_quote_characters = everything; rl_completer_quote_characters = (char *) "'\""; rl_basic_word_break_characters = (char *) "() []{};+-=*<>~'?%/@|&#^\"\\."; /* Consider binary selectors both word-breaking characters and candidates for completion */ rl_special_prefixes = (char *) "+-=*<>~?%/@|&\\"; /* Our rules for quoting are a bit different from the default */ rl_filename_quoting_function = (CPFunction *) readline_quote_filename; rl_filename_dequoting_function = (CPFunction *) readline_dequote_filename; /* Try to match a symbol before a filename */ rl_attempted_completion_function = (CPPFunction *) readline_match_symbols; /* Since we have to sort the array to perform the binary search, remove duplicates and avoid that readline resorts the result. */ rl_ignore_completion_duplicates = 0; /* Set up to use read to read from stdin */ rl_getc_function = readline_getc; } #endif /* HAVE_READLINE */ smalltalk-3.2.5/libgst/genbc.h0000644000175000017500000000621512123404352013141 00000000000000/******************************** -*- C -*- **************************** * * GNU Smalltalk genbc tool * ***********************************************************************/ /*********************************************************************** * * Copyright 2003, 2006 Free Software Foundation, Inc. * Written by Paolo Bonzini. * * This file is part of GNU Smalltalk. * * GNU Smalltalk is free software; you can redistribute it and/or modify it * under the terms of the GNU General Public License as published by the Free * Software Foundation; either version 2, or (at your option) any later * version. * * Linking GNU Smalltalk statically or dynamically with other modules is * making a combined work based on GNU Smalltalk. Thus, the terms and * conditions of the GNU General Public License cover the whole * combination. * * In addition, as a special exception, the Free Software Foundation * give you permission to combine GNU Smalltalk with free software * programs or libraries that are released under the GNU LGPL and with * independent programs running under the GNU Smalltalk virtual machine. * * You may copy and distribute such a system following the terms of the * GNU GPL for GNU Smalltalk and the licenses of the other code * concerned, provided that you include the source code of that other * code when and as the GNU GPL requires distribution of source code. * * Note that people who make modified versions of GNU Smalltalk are not * obligated to grant this special exception for their modified * versions; it is their choice whether to do so. The GNU General * Public License gives permission to release a modified version without * this exception; this exception also makes it possible to release a * modified version which carries forward this exception. * * GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or * FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for * more details. * * You should have received a copy of the GNU General Public License along with * GNU Smalltalk; see the file COPYING. If not, write to the Free Software * Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * ***********************************************************************/ #ifdef HAVE_CONFIG_H #include "config.h" #endif #include #include #include #include #include "snprintfv/filament.h" #include "snprintfv/printf.h" #include "genbc-decl.h" #include "genbc-impl.h" /* genbc.l declarations */ extern int yylex (void); extern int yylineno; extern void parse_declarations (const char *file); extern void parse_implementation (const char *file); /* genbc-decl.y declarations */ extern int decl_yyparse (); extern int decl_yydebug; extern void emit_opcodes (); /* genbc-impl.y declarations */ extern int impl_yyparse (); extern int impl_yydebug; /* genbc.c declarations */ extern const char *current_file; extern void yyprint (FILE *file, int type, YYSTYPE yylval); extern void yyerror (const char *s); extern char *my_asprintf (const char *fmt, ...); smalltalk-3.2.5/libgst/lex.c0000644000175000017500000010470012130343734012650 00000000000000/******************************** -*- C -*- **************************** * * Lexer Module. * * ***********************************************************************/ /*********************************************************************** * * Copyright 1988,89,90,91,92,94,95,99,2000,2001,2002,2003, * 2004,2005,2006,2007,2008,2009 Free Software Foundation, Inc. * Written by Steve Byrne. * * This file is part of GNU Smalltalk. * * GNU Smalltalk is free software; you can redistribute it and/or modify it * under the terms of the GNU General Public License as published by the Free * Software Foundation; either version 2, or (at your option) any later * version. * * Linking GNU Smalltalk statically or dynamically with other modules is * making a combined work based on GNU Smalltalk. Thus, the terms and * conditions of the GNU General Public License cover the whole * combination. * * In addition, as a special exception, the Free Software Foundation * give you permission to combine GNU Smalltalk with free software * programs or libraries that are released under the GNU LGPL and with * independent programs running under the GNU Smalltalk virtual machine. * * You may copy and distribute such a system following the terms of the * GNU GPL for GNU Smalltalk and the licenses of the other code * concerned, provided that you include the source code of that other * code when and as the GNU GPL requires distribution of source code. * * Note that people who make modified versions of GNU Smalltalk are not * obligated to grant this special exception for their modified * versions; it is their choice whether to do so. The GNU General * Public License gives permission to release a modified version without * this exception; this exception also makes it possible to release a * modified version which carries forward this exception. * * GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or * FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for * more details. * * You should have received a copy of the GNU General Public License along with * GNU Smalltalk; see the file COPYING. If not, write to the Free Software * Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * ***********************************************************************/ #include "gstpriv.h" #if defined(__FreeBSD__) #include #endif /* Define this if you want the lexer to print all the tokens that it scans, * before passing them to the parser. */ /* #define LEXDEBUG */ /* Define this if you're debugging the lexer and you don't want the parser * to be ran -- only lexical scanning will take place. */ /* #define NO_PARSE */ #define WHITE_SPACE 1 #define DIGIT 2 #define ID_CHAR 4 #define BIN_OP_CHAR 8 #define SYMBOL_CHAR 16 /* The obstack containing parse tree nodes. */ struct obstack *_gst_compilation_obstack = NULL; /* True if errors must be reported to the standard error, false if errors should instead stored so that they are passed to Smalltalk code. */ mst_Boolean _gst_report_errors = true; /* This is set to true by the parser or the compiler if an error (respectively, a parse error or a semantic error) is found, and avoids that _gst_execute_statements tries to execute the result of the compilation. */ mst_Boolean _gst_had_error = false; /* This is set to true by the parser if error recovery is going on. In this case ERROR_RECOVERY tokens are generated. */ mst_Boolean _gst_error_recovery = false; /* The location of the first error reported, stored here so that compilation primitives can pass them to Smalltalk code. */ char *_gst_first_error_str = NULL; char *_gst_first_error_file = NULL; int _gst_first_error_line = 0; /* Last returned token. */ static int last_token; /* Balance of parentheses. Used to turn a newline into a period. */ static int parenthesis_depth; /* Answer true if IC is a valid base-10 digit. */ static mst_Boolean is_digit (int ic); /* Answer true if C is a valid base-BASE digit. */ static mst_Boolean is_base_digit (int c, int base); /* Parse the fractional part of a Float constant. Store it in NUMPTR. Read numbers in base-BASE, the first one being C. Answer the scale (number of digits in numPtr). If LARGEINTEGER is not NULL, the digits are stored in an obstack, and LARGEINTEGER is set to true if numPtr does not have sufficient precision. */ static int scan_fraction (int c, mst_Boolean negative, unsigned base, uintptr_t *intNumPtr, struct real *numPtr, mst_Boolean *largeInteger); /* Parse a numeric constant and return it. Read numbers in base-BASE, the first one being C. If a - was parsed, NEGATIVE must be true so that the sign of the result is changed accordingly. If LARGEINTEGER is not NULL, the digits are stored in an obstack, and LARGEINTEGER is set to true if the return value does not have sufficient precision. */ static uintptr_t scan_digits (int c, mst_Boolean negative, unsigned base, struct real * n, mst_Boolean * largeInteger); /* Parse the large integer constant stored as base-BASE digits in the buffer maintained by str.c, adjusting the sign if NEGATIVE is true. Return an embryo of the LargeInteger object as a byte_object structure. */ static byte_object scan_large_integer (mst_Boolean negative, int base); /* Raise an error. */ static int invalid (int c, YYSTYPE * lvalp); /* Parse a comment. C is '"'. Return 0 to indicate the lexer that this lexeme must be ignored. */ static int comment (int c, YYSTYPE * lvalp); /* Parse a character literal. C is '$' */ static int char_literal (int c, YYSTYPE * lvalp); /* Remember the current balance of open/close parentheses, used to treat newlines as periods. */ static int scan_open_paren (int c, YYSTYPE * lvalp); /* Remember the current balance of open/close parentheses, used to treat newlines as periods. */ static int scan_close_paren (int c, YYSTYPE * lvalp); /* Remember the current balance of open/close parentheses, used to treat newlines as periods. */ static int scan_reset_paren (int c, YYSTYPE * lvalp); /* If the current balance of open/close parentheses is zero, and the last token was not a period or bang, treat the newline as a period. */ static int scan_newline (int c, YYSTYPE * lvalp); /* Parse a binary operator. C is the first symbol in the selector */ static int scan_bin_op (int c, YYSTYPE * lvalp); /* Actual work for scan_bin_op is done here. MAYBE_NUMBER is false if we cannot parse a negative number in this context. */ static int scan_bin_op_1 (int c, YYSTYPE * lvalp, mst_Boolean maybe_number); /* Parse a string literal. C is '\'' */ static int string_literal (int c, YYSTYPE * lvalp); /* Parse a number. C is the first digit. */ static int scan_number (int c, YYSTYPE * lvalp); /* Parse an identifier. C is the first letter. */ static int scan_ident (int c, YYSTYPE * lvalp); /* Try to parse an assignment operator or namespace separator. C is ':'. */ static int scan_colon (int c, YYSTYPE * lvalp); /* Try to parse a symbol constant, or return '#'. C is '#'. */ static int scan_symbol (int c, YYSTYPE * lvalp); /* Convert the digit C (if it is a valid base-BASE digit) to its value. Raise an error if it is invalid. */ static int digit_to_int (int c, int base); #ifdef LEXDEBUG static void print_token (int token, YYSTYPE *yylval); #endif typedef struct { int (*lexFunc) (int, YYSTYPE *); int retToken; int char_class; } lex_tab_elt; /* This macro is needed to properly handle 8-bit characters */ #define CHAR_TAB(x) ((x) < 128 ? char_table + (x) : char_table) static const lex_tab_elt char_table[128] = { /* 0 */ {invalid, 0, 0}, /* 1 */ {invalid, 0, 0}, /* 2 */ {invalid, 0, 0}, /* 3 */ {invalid, 0, 0}, /* 4 */ {invalid, 0, 0}, /* 5 */ {invalid, 0, 0}, /* 6 */ {invalid, 0, 0}, /* 7 */ {invalid, 0, 0}, /* 8 */ {invalid, 0, 0}, /* 9 */ {0, 0, WHITE_SPACE}, /* 10 */ {scan_newline, 0, 0}, /* 11 */ {invalid, 0, 0}, /* 12 */ {0, 0, WHITE_SPACE}, /* 13 */ {0, 0, WHITE_SPACE}, /* 14 */ {invalid, 0, 0}, /* 15 */ {invalid, 0, 0}, /* 16 */ {invalid, 0, 0}, /* 17 */ {invalid, 0, 0}, /* 18 */ {invalid, 0, 0}, /* 19 */ {invalid, 0, 0}, /* 20 */ {invalid, 0, 0}, /* 21 */ {invalid, 0, 0}, /* 22 */ {invalid, 0, 0}, /* 23 */ {invalid, 0, 0}, /* 24 */ {invalid, 0, 0}, /* 25 */ {invalid, 0, 0}, /* 26 */ {invalid, 0, 0}, /* 27 */ {invalid, 0, 0}, /* 28 */ {invalid, 0, 0}, /* 29 */ {invalid, 0, 0}, /* 30 */ {invalid, 0, 0}, /* 31 */ {invalid, 0, 0}, /* */ {0, 0, WHITE_SPACE}, /* ! */ {scan_reset_paren, 0, 0}, /* " */ {comment, 0, 0}, /* # */ {scan_symbol, 0, 0}, /* $ */ {char_literal, 0, ID_CHAR | SYMBOL_CHAR}, /* % */ {scan_bin_op, 0, BIN_OP_CHAR}, /* & */ {scan_bin_op, 0, BIN_OP_CHAR}, /* ' */ {string_literal, 0, 0}, /* ( */ {scan_open_paren, 0, 0}, /* ) */ {scan_close_paren, 0, 0}, /* * */ {scan_bin_op, 0, BIN_OP_CHAR}, /* + */ {scan_bin_op, 0, BIN_OP_CHAR}, /* , */ {scan_bin_op, 0, BIN_OP_CHAR}, /* - */ {scan_bin_op, 0, BIN_OP_CHAR}, /* . */ {0, '.', 0}, /* / */ {scan_bin_op, 0, BIN_OP_CHAR}, /* 0 */ {scan_number, 0, DIGIT | ID_CHAR | SYMBOL_CHAR}, /* 1 */ {scan_number, 0, DIGIT | ID_CHAR | SYMBOL_CHAR}, /* 2 */ {scan_number, 0, DIGIT | ID_CHAR | SYMBOL_CHAR}, /* 3 */ {scan_number, 0, DIGIT | ID_CHAR | SYMBOL_CHAR}, /* 4 */ {scan_number, 0, DIGIT | ID_CHAR | SYMBOL_CHAR}, /* 5 */ {scan_number, 0, DIGIT | ID_CHAR | SYMBOL_CHAR}, /* 6 */ {scan_number, 0, DIGIT | ID_CHAR | SYMBOL_CHAR}, /* 7 */ {scan_number, 0, DIGIT | ID_CHAR | SYMBOL_CHAR}, /* 8 */ {scan_number, 0, DIGIT | ID_CHAR | SYMBOL_CHAR}, /* 9 */ {scan_number, 0, DIGIT | ID_CHAR | SYMBOL_CHAR}, /* : */ {scan_colon, 0, SYMBOL_CHAR}, /* ; */ {0, ';', 0}, /* < */ {scan_bin_op, 0, BIN_OP_CHAR}, /* = */ {scan_bin_op, 0, BIN_OP_CHAR}, /* > */ {scan_bin_op, 0, BIN_OP_CHAR}, /* ? */ {scan_bin_op, 0, BIN_OP_CHAR}, /* @ */ {scan_bin_op, 0, BIN_OP_CHAR}, /* A */ {scan_ident, 0, ID_CHAR | SYMBOL_CHAR}, /* B */ {scan_ident, 0, ID_CHAR | SYMBOL_CHAR}, /* C */ {scan_ident, 0, ID_CHAR | SYMBOL_CHAR}, /* D */ {scan_ident, 0, ID_CHAR | SYMBOL_CHAR}, /* E */ {scan_ident, 0, ID_CHAR | SYMBOL_CHAR}, /* F */ {scan_ident, 0, ID_CHAR | SYMBOL_CHAR}, /* G */ {scan_ident, 0, ID_CHAR | SYMBOL_CHAR}, /* H */ {scan_ident, 0, ID_CHAR | SYMBOL_CHAR}, /* I */ {scan_ident, 0, ID_CHAR | SYMBOL_CHAR}, /* J */ {scan_ident, 0, ID_CHAR | SYMBOL_CHAR}, /* K */ {scan_ident, 0, ID_CHAR | SYMBOL_CHAR}, /* L */ {scan_ident, 0, ID_CHAR | SYMBOL_CHAR}, /* M */ {scan_ident, 0, ID_CHAR | SYMBOL_CHAR}, /* N */ {scan_ident, 0, ID_CHAR | SYMBOL_CHAR}, /* O */ {scan_ident, 0, ID_CHAR | SYMBOL_CHAR}, /* P */ {scan_ident, 0, ID_CHAR | SYMBOL_CHAR}, /* Q */ {scan_ident, 0, ID_CHAR | SYMBOL_CHAR}, /* R */ {scan_ident, 0, ID_CHAR | SYMBOL_CHAR}, /* S */ {scan_ident, 0, ID_CHAR | SYMBOL_CHAR}, /* T */ {scan_ident, 0, ID_CHAR | SYMBOL_CHAR}, /* U */ {scan_ident, 0, ID_CHAR | SYMBOL_CHAR}, /* V */ {scan_ident, 0, ID_CHAR | SYMBOL_CHAR}, /* W */ {scan_ident, 0, ID_CHAR | SYMBOL_CHAR}, /* X */ {scan_ident, 0, ID_CHAR | SYMBOL_CHAR}, /* Y */ {scan_ident, 0, ID_CHAR | SYMBOL_CHAR}, /* Z */ {scan_ident, 0, ID_CHAR | SYMBOL_CHAR}, /* [ */ {scan_open_paren, 0, 0}, /* \ */ {scan_bin_op, 0, BIN_OP_CHAR}, /* ] */ {scan_close_paren, 0, 0}, /* ^ */ {0, '^', 0}, /* _ */ {0, ASSIGNMENT, ID_CHAR | SYMBOL_CHAR}, /* ` */ {invalid, 0, 0}, /* a */ {scan_ident, 0, ID_CHAR | SYMBOL_CHAR}, /* b */ {scan_ident, 0, ID_CHAR | SYMBOL_CHAR}, /* c */ {scan_ident, 0, ID_CHAR | SYMBOL_CHAR}, /* d */ {scan_ident, 0, ID_CHAR | SYMBOL_CHAR}, /* e */ {scan_ident, 0, ID_CHAR | SYMBOL_CHAR}, /* f */ {scan_ident, 0, ID_CHAR | SYMBOL_CHAR}, /* g */ {scan_ident, 0, ID_CHAR | SYMBOL_CHAR}, /* h */ {scan_ident, 0, ID_CHAR | SYMBOL_CHAR}, /* i */ {scan_ident, 0, ID_CHAR | SYMBOL_CHAR}, /* j */ {scan_ident, 0, ID_CHAR | SYMBOL_CHAR}, /* k */ {scan_ident, 0, ID_CHAR | SYMBOL_CHAR}, /* l */ {scan_ident, 0, ID_CHAR | SYMBOL_CHAR}, /* m */ {scan_ident, 0, ID_CHAR | SYMBOL_CHAR}, /* n */ {scan_ident, 0, ID_CHAR | SYMBOL_CHAR}, /* o */ {scan_ident, 0, ID_CHAR | SYMBOL_CHAR}, /* p */ {scan_ident, 0, ID_CHAR | SYMBOL_CHAR}, /* q */ {scan_ident, 0, ID_CHAR | SYMBOL_CHAR}, /* r */ {scan_ident, 0, ID_CHAR | SYMBOL_CHAR}, /* s */ {scan_ident, 0, ID_CHAR | SYMBOL_CHAR}, /* t */ {scan_ident, 0, ID_CHAR | SYMBOL_CHAR}, /* u */ {scan_ident, 0, ID_CHAR | SYMBOL_CHAR}, /* v */ {scan_ident, 0, ID_CHAR | SYMBOL_CHAR}, /* w */ {scan_ident, 0, ID_CHAR | SYMBOL_CHAR}, /* x */ {scan_ident, 0, ID_CHAR | SYMBOL_CHAR}, /* y */ {scan_ident, 0, ID_CHAR | SYMBOL_CHAR}, /* z */ {scan_ident, 0, ID_CHAR | SYMBOL_CHAR}, /* { */ {scan_open_paren, 0, 0}, /* | */ {scan_bin_op, 0, BIN_OP_CHAR}, /* } */ {scan_close_paren, 0, 0}, /* ~ */ {scan_bin_op, 0, BIN_OP_CHAR}, /* ^? */ {invalid, 0, 0} }; #if defined(LEXDEBUG) static inline int yylex_internal (); int _gst_yylex (PTR lvalp, YYLTYPE *llocp) { int result; result = yylex_internal (lvalp, llocp); print_token (result, lvalp); return (result); } #define _gst_yylex yylex_internal #endif /* LEXDEBUG */ int _gst_yylex (PTR lvalp, YYLTYPE *llocp) { int ic, result; const lex_tab_elt *ct; while ((ic = _gst_next_char ()) != EOF) { ct = CHAR_TAB (ic); if ((ct->char_class & WHITE_SPACE) == 0) { *llocp = _gst_get_location (); assert (ct->lexFunc || ct->retToken); if (ct->lexFunc) result = (*ct->lexFunc) (ic, (YYSTYPE *) lvalp); else result = ct->retToken; if (result) { if (_gst_get_cur_stream_prompt ()) last_token = result; return (result); } } } *llocp = _gst_get_location (); return (EOF); } int invalid (int c, YYSTYPE * lvalp) { char cp[5]; if (c < ' ' || c == 127) { cp[0] = '^'; cp[1] = c ^ 64; /* uncontrolify */ cp[2] = '\0'; } else if (c & 128) sprintf (cp, "%#02x", c & 255); else { cp[0] = c; cp[1] = '\0'; } _gst_errorf ("Invalid character %s", cp); _gst_had_error = true; return (0); /* tell the lexer to ignore this */ } int scan_reset_paren (int c, YYSTYPE * lvalp) { if (_gst_get_cur_stream_prompt ()) parenthesis_depth = 0; return c; } int scan_open_paren (int c, YYSTYPE * lvalp) { if (_gst_get_cur_stream_prompt ()) parenthesis_depth++; return c; } int scan_close_paren (int c, YYSTYPE * lvalp) { if (_gst_get_cur_stream_prompt ()) parenthesis_depth--; return c; } int scan_newline (int c, YYSTYPE * lvalp) { if (_gst_get_cur_stream_prompt ()) { /* Newline is special-cased in the REPL. */ if (_gst_error_recovery) return ERROR_RECOVERY; if (parenthesis_depth == 0 && last_token != 0 && last_token != '.' && last_token != '!' && last_token != KEYWORD && last_token != BINOP && last_token != '|' && last_token != '<' && last_token != '>' && last_token != ';' && last_token != ASSIGNMENT && last_token != SCOPE_SEPARATOR) return ('.'); } return 0; } int comment (int c, YYSTYPE * lvalp) { int ic; do { ic = _gst_next_char (); if (ic == EOF) { _gst_errorf ("Unterminated comment, attempting recovery"); _gst_had_error = true; break; } } while (ic != c); return (0); } int char_literal (int c, YYSTYPE * lvalp) { int ic; ic = _gst_next_char (); if (ic == EOF) { _gst_errorf ("Unterminated character literal, attempting recovery"); _gst_unread_char (ic); _gst_had_error = true; return (0); } else { if (ic > 127) { _gst_errorf ("Invalid character literal, only character codes from 0 to 127 are valid"); _gst_had_error = true; } lvalp->ival = ic; return (CHAR_LITERAL); } } int scan_colon (int c, YYSTYPE * lvalp) { int ic; ic = _gst_next_char (); if (ic == '=') return (ASSIGNMENT); else if (ic == ':') return (SCOPE_SEPARATOR); else _gst_unread_char (ic); return (':'); } int scan_symbol (int c, YYSTYPE *lvalp) { int ic; ic = _gst_next_char (); if (ic == EOF) return '#'; /* Look for a shebang (#! /). */ if (ic == '!') { YYLTYPE loc = _gst_get_location (); if (loc.first_line == 1 && loc.first_column == 2) { while (((ic = _gst_next_char ()) != EOF) && ic != '\r' && ic != '\n') continue; return (SHEBANG); } } /* We can read a binary operator and return a SYMBOL_LITERAL,... */ if (CHAR_TAB (ic)->char_class & BIN_OP_CHAR) { scan_bin_op_1 (ic, lvalp, false); return SYMBOL_LITERAL; } if (ic == '\'') { string_literal (ic, lvalp); return SYMBOL_LITERAL; } /* ...else, we can absorb identifier characters and colons, but discard anything else. */ if ((CHAR_TAB (ic)->char_class & (DIGIT | SYMBOL_CHAR)) != SYMBOL_CHAR) { _gst_unread_char (ic); return '#'; } obstack_1grow (_gst_compilation_obstack, ic); while (((ic = _gst_next_char ()) != EOF) && (CHAR_TAB (ic)->char_class & SYMBOL_CHAR)) obstack_1grow (_gst_compilation_obstack, ic); _gst_unread_char (ic); obstack_1grow (_gst_compilation_obstack, '\0'); lvalp->sval = obstack_finish (_gst_compilation_obstack); return SYMBOL_LITERAL; } int scan_bin_op_1 (int c, YYSTYPE *lvalp, mst_Boolean maybe_number) { char buf[3]; int ic; buf[0] = c; ic = _gst_next_char (); if (ic != EOF && (CHAR_TAB (ic)->char_class & BIN_OP_CHAR)) { buf[1] = ic, buf[2] = 0; /* temptatively accumulate next char */ /* This may be a two-character binary operator, except if the second character is a - and is followed by a digit. */ if (ic == '-') { ic = _gst_next_char (); _gst_unread_char (ic); if (is_digit (ic)) { _gst_unread_char ('-'); buf[1] = '\0'; } } } else { _gst_unread_char (ic); buf[1] = 0; } lvalp->sval = xstrdup (buf); if ((buf[0] == '|' || buf[0] == '<' || buf[0] == '>' || buf[0] == '-') && buf[1] == '\0') return (buf[0]); else return (BINOP); } int scan_bin_op (int c, YYSTYPE *lvalp) { return scan_bin_op_1 (c, lvalp, true); } int string_literal (int c, YYSTYPE * lvalp) { int ic; for (;;) { ic = _gst_next_char (); if (ic == EOF) { _gst_errorf ("Unterminated string, attempting recovery"); _gst_had_error = true; break; } if (ic == c) { /* check for doubled delimiters */ ic = _gst_next_char (); if (ic != c) { _gst_unread_char (ic); break; } } obstack_1grow (_gst_compilation_obstack, ic); } obstack_1grow (_gst_compilation_obstack, '\0'); lvalp->sval = obstack_finish (_gst_compilation_obstack); return (STRING_LITERAL); } int scan_ident (int c, YYSTYPE * lvalp) { int ic, identType; obstack_1grow (_gst_compilation_obstack, c); identType = IDENTIFIER; while (((ic = _gst_next_char ()) != EOF) && (CHAR_TAB (ic)->char_class & ID_CHAR)) obstack_1grow (_gst_compilation_obstack, ic); /* Read a dot as '::' if followed by a letter. */ if (ic == '.') { ic = _gst_next_char (); _gst_unread_char (ic); if (ic != EOF && (CHAR_TAB (ic)->char_class & ID_CHAR)) { _gst_unread_char (':'); _gst_unread_char (':'); } else _gst_unread_char ('.'); } else if (ic == ':') { ic = _gst_next_char (); _gst_unread_char (ic); if (ic == ':' || ic == '=') /* foo:: and foo:= split before colon */ _gst_unread_char (':'); else { obstack_1grow (_gst_compilation_obstack, ':'); identType = KEYWORD; } } else _gst_unread_char (ic); obstack_1grow (_gst_compilation_obstack, '\0'); lvalp->sval = obstack_finish (_gst_compilation_obstack); return (identType); } /* TODO: We track the number in *three* formats: struct real, uintptr_t, * and just save the bytes for large integers. We should just save * the bytes and work on those. */ int scan_number (int c, YYSTYPE * lvalp) { OOP intNumOOP; int base, exponent, ic; uintptr_t intNum; struct real num, dummy; int floatExponent; mst_Boolean isNegative = false, largeInteger = false; int float_type = 0; base = 10; exponent = 0; ic = c; assert (ic != '-'); intNum = scan_digits (ic, false, 10, &num, &largeInteger); ic = _gst_next_char (); if (ic == 'r') { char *p = obstack_finish (_gst_compilation_obstack); obstack_free (_gst_compilation_obstack, p); if (intNum > 36 || largeInteger) { _gst_errorf ("Numeric base too large %d", base); _gst_had_error = true; } else base = intNum; ic = _gst_next_char (); /* Having to support things like 16r-123 is a pity :-) because we actually incorrectly accept -16r-0. */ if (ic == '-') { isNegative = true; ic = _gst_next_char (); } intNum = scan_digits (ic, isNegative, base, &num, &largeInteger); ic = _gst_next_char (); } if (ic == '.') { ic = _gst_next_char (); if (!is_base_digit (ic, base)) { /* OOPS...we gobbled the '.' by mistake...it was a statement boundary delimiter. We have an integer that we need to return, and need to push back both the . and the character that we just read. */ _gst_unread_char (ic); ic = '.'; } else { float_type = FLOATD_LITERAL; exponent = scan_fraction (ic, isNegative, base, &intNum, &num, &largeInteger); ic = _gst_next_char (); } } if (ic == 's') do { /* By default the same as the number of decimal points we used. */ floatExponent = -exponent; ic = _gst_next_char (); if (ic == EOF) ; else if (CHAR_TAB (ic)->char_class & DIGIT) { /* 123s4 format -- parse the exponent */ floatExponent = scan_digits (ic, false, 10, &dummy, NULL); } else if (CHAR_TAB (ic)->char_class & ID_CHAR) { /* 123stuvwxyz sends #stuvwxyz to 123!!! */ _gst_unread_char (ic); ic = 's'; break; } else _gst_unread_char (ic); if (largeInteger) { /* Make a LargeInteger constant and create an object out of it. */ byte_object bo = scan_large_integer (isNegative, base); gst_object result = instantiate_with (bo->class, bo->size, &intNumOOP); memcpy (result->data, bo->body, bo->size); } else intNumOOP = FROM_INT((intptr_t) (isNegative ? -intNum : intNum)); /* too much of a chore to create a Fraction, so we call-in. We lose the ability to create ScaledDecimals during the very first phases of bootstrapping, but who cares?... This is equivalent to (intNumOOP * (10 raisedToInteger: exponent) asScaledDecimal: floatExponent) */ lvalp->oval = _gst_msg_send (intNumOOP, _gst_as_scaled_decimal_radix_scale_symbol, FROM_INT (exponent), FROM_INT (base), FROM_INT ((int) floatExponent), NULL); /* incubator is set up by _gst_compile_method */ INC_ADD_OOP (lvalp->oval); MAKE_OOP_READONLY (lvalp->oval, true); return (SCALED_DECIMAL_LITERAL); } while (0); if (ic == 'e' || ic == 'd' || ic == 'q') { int exp_char = ic; switch (ic) { case 'e': float_type = FLOATE_LITERAL; break; case 'd': float_type = FLOATD_LITERAL; break; case 'q': float_type = FLOATQ_LITERAL; break; } ic = _gst_next_char (); if (ic == EOF) ; else if (ic == '-') { floatExponent = scan_digits (_gst_next_char (), true, 10, &dummy, NULL); exponent -= (int) floatExponent; } else if (CHAR_TAB (ic)->char_class & DIGIT) { floatExponent = scan_digits (ic, false, 10, &dummy, NULL); exponent += (int) floatExponent; } else if (CHAR_TAB (ic)->char_class & ID_CHAR) { /* 123def sends #def to 123!!! */ _gst_unread_char (ic); ic = exp_char; } else _gst_unread_char (ic); } else _gst_unread_char (ic); if (float_type) { char *p = obstack_finish (_gst_compilation_obstack); obstack_free (_gst_compilation_obstack, p); if (exponent) { struct real r; _gst_real_from_int (&r, base); _gst_real_powi (&r, &r, exponent < 0 ? -exponent : exponent); if (exponent < 0) _gst_real_div (&num, &num, &r); else _gst_real_mul (&num, &r); } lvalp->fval = _gst_real_get_ld (&num); if (isNegative) lvalp->fval = -lvalp->fval; return (float_type); } else if (largeInteger) { lvalp->boval = scan_large_integer (isNegative, base); return (LARGE_INTEGER_LITERAL); } else { char *p = obstack_finish (_gst_compilation_obstack); obstack_free (_gst_compilation_obstack, p); lvalp->ival = (intptr_t) (isNegative ? -intNum : intNum); return (INTEGER_LITERAL); } } uintptr_t scan_digits (int c, mst_Boolean negative, unsigned base, struct real * n, mst_Boolean * largeInteger) { uintptr_t result; mst_Boolean oneDigit = false; while (c == '_') c = _gst_next_char (); memset (n, 0, sizeof (*n)); for (result = 0.0; is_base_digit (c, base); ) { unsigned value = digit_to_int (c, base); if (largeInteger) { obstack_1grow (_gst_compilation_obstack, digit_to_int (c, base)); if (result > (negative /* We want (uintptr_t) -MIN_ST_INT, but it's the same. */ ? (uintptr_t) MIN_ST_INT - value : (uintptr_t) MAX_ST_INT - value) / base) *largeInteger = true; } _gst_real_mul_int (n, base); _gst_real_add_int (n, value); oneDigit = true; result *= base; result += value; do c = _gst_next_char (); while (c == '_'); } if (!oneDigit) { _gst_errorf ("Unexpected EOF while scanning number"); _gst_had_error = true; } _gst_unread_char (c); return (result); } int scan_fraction (int c, mst_Boolean negative, unsigned base, uintptr_t *intNumPtr, struct real *numPtr, mst_Boolean *largeInteger) { uintptr_t intNum; int scale; scale = 0; while (c == '_') c = _gst_next_char (); for (intNum = *intNumPtr; is_base_digit (c, base); ) { unsigned value = digit_to_int (c, base); if (largeInteger) { obstack_1grow (_gst_compilation_obstack, digit_to_int (c, base)); if (intNum > (negative /* We want (uintptr_t) -MIN_ST_INT, but it's the same. */ ? (uintptr_t) MIN_ST_INT - value : (uintptr_t) MAX_ST_INT - value) / base) *largeInteger = true; } _gst_real_mul_int (numPtr, base); _gst_real_add_int (numPtr, value); intNum *= base; intNum += value; scale--; do c = _gst_next_char (); while (c == '_'); } _gst_unread_char (c); *intNumPtr = intNum; return scale; } int digit_to_int (int c, int base) { if (c < '0' || (c > '9' && c < 'A') || c > 'Z') { _gst_errorf ("Invalid digit %c in number", c); _gst_had_error = true; return (0); } if (c >= 'A') c = c - 'A' + 10; else c -= '0'; if (c >= base) { _gst_errorf ("Digit '%c' too large for base %d", c, base); _gst_had_error = true; return (0); } return (c); } mst_Boolean is_base_digit (int c, int base) { if (c < '0' || (c > '9' && c < 'A') || c > 'Z') return (false); if (c >= 'A') c = c - 'A' + 10; else c -= '0'; return (c < base); } mst_Boolean is_digit (int ic) { return (ic != EOF && (CHAR_TAB (ic)->char_class & DIGIT) != 0); } byte_object scan_large_integer (mst_Boolean negative, int base) { int i; int size, digitsLeft; gst_uchar *digits, *result; byte_object bo; /* Copy the contents of the currently grown obstack on the stack. */ size = obstack_object_size (_gst_compilation_obstack); digits = (gst_uchar *) alloca (size); memcpy (digits, obstack_base (_gst_compilation_obstack), size); /* And reuse the area on the obstack for a struct byte_object. */ obstack_blank (_gst_compilation_obstack, sizeof (struct byte_object)); bo = (byte_object) obstack_finish (_gst_compilation_obstack); bo->class = negative ? _gst_large_negative_integer_class : _gst_large_positive_integer_class; result = bo->body; memset (result, 0, size); /* On each pass, multiply the previous partial result by the base, and sum each of the digits as they were retrieved by scan_digits. */ for (digitsLeft = size; digitsLeft--;) { int total, carry; total = result[0] * base + *digits++; carry = total >> 8; result[0] = (gst_uchar) total; for (i = 1; i < size; i++) { total = result[i] * base + carry; carry = total >> 8; result[i] = (gst_uchar) total; } } if (negative) { /* Do two's complement -- first invert, then increment with carry */ for (i = 0; i < size; i++) result[i] ^= 255; for (i = 0; (++result[i]) == 0; i++); /* Search where the number really ends -- discard trailing 111... bytes but remember, the most significant bit of the last digit must be 1! */ for (; size > 0 && result[size - 1] == 255; size--); if (result[size - 1] < 128) size++; } else { /* Search where the number really ends -- discard trailing 000... bytes but remember, the most significant bit of the last digit must be 0! */ for (; size > 0 && result[size - 1] == 0; size--); if (result[size - 1] > 127) size++; } /* Only now can we set the size! */ bo->size = size; return (bo); } void _gst_parse_stream (mst_Boolean method) { struct obstack thisObstack, *oldObstack; /* Allow re-entrancy by allocating a different obstack every time _gst_parse_stream is called */ oldObstack = _gst_compilation_obstack; _gst_compilation_obstack = &thisObstack; obstack_init (&thisObstack); { #ifdef NO_PARSE YYSTYPE yylval; while (_gst_yylex (&yylval)); #else /* !NO_PARSE */ _gst_had_error = false; if (method) { _gst_parse_method (); _gst_reset_compilation_category (); } else _gst_parse_chunks (); #endif /* !NO_PARSE */ } obstack_free (&thisObstack, NULL); _gst_compilation_obstack = oldObstack; } #ifdef LEXDEBUG void print_token (token, yylval) int token; YYSTYPE *yylval; { switch (token) { case 0: break; case '.': case '!': case ':': case '|': case '^': case '#': case ';': case '(': case ')': case '[': case ']': case '{': case '}': printf ("%c\n", token); break; case SCOPE_SEPARATOR: printf ("::\n"); break; case ASSIGNMENT: printf (":=\n"); break; case IDENTIFIER: printf ("IDENTIFIER: `%s'\n", yylval->sval); break; case KEYWORD: printf ("KEYWORD: `%s'\n", yylval->sval); break; case SYMBOL_LITERAL: printf ("SYMBOL_LITERAL: #'%s'\n", yylval->sval); break; case LARGE_INTEGER_LITERAL: printf ("LARGE_INTEGER_LITERAL\n"); case INTEGER_LITERAL: printf ("INTEGER_LITERAL: %ld\n", yylval->ival); break; case FLOATD_LITERAL: printf ("FLOATD_LITERAL: %g\n", (double) yylval->fval); break; case FLOATE_LITERAL: printf ("FLOATE_LITERAL: %g\n", (float) yylval->fval); break; case FLOATQ_LITERAL: printf ("FLOATQ_LITERAL: %Lg\n", yylval->fval); break; case CHAR_LITERAL: printf ("CHAR_LITERAL: %d", yylval->ival, if (yylval->ival >= 32 && yylval->ival <= 126) printf (" ($%c)", (char) yylval->ival); printf ("\n"); break; case STRING_LITERAL: printf ("STRING_LITERAL: '%s'\n", yylval->sval); break; case BINOP: printf ("BINOP: `%s'\n", yylval->sval); break; } } #endif void _gst_yyprint (FILE * file, int token, PTR lval) { YYSTYPE *yylval = (YYSTYPE *) lval; switch (token) { case IDENTIFIER: case BINOP: case KEYWORD: fprintf (file, ": `%s'", yylval->sval); break; case SYMBOL_LITERAL: fprintf (file, ": #'%s'", yylval->sval); break; case STRING_LITERAL: fprintf (file, ": '%s'", yylval->sval); break; case INTEGER_LITERAL: fprintf (file, ": %ld", yylval->ival); break; case FLOATD_LITERAL: fprintf (file, ": %g", (double) yylval->fval); break; case FLOATE_LITERAL: fprintf (file, ": %g", (float) yylval->fval); break; case FLOATQ_LITERAL: fprintf (file, ": %Lg", yylval->fval); break; case CHAR_LITERAL: fprintf (file, ": %d", yylval->ival); if (yylval->ival >= 32 && yylval->ival <= 126) fprintf (file, " ($%c)", (char) yylval->ival); fprintf (file, "\n"); break; default: break; } } mst_Boolean _gst_negate_yylval (int token, YYSTYPE *yylval) { switch (token) { case INTEGER_LITERAL: if (yylval->ival < 0) return false; yylval->ival = -yylval->ival; break; case FLOATD_LITERAL: case FLOATE_LITERAL: case FLOATQ_LITERAL: if (yylval->fval < 0) return false; yylval->fval = -yylval->fval; break; case SCALED_DECIMAL_LITERAL: { int sign; _gst_msg_sendf (&sign, "%i %o sign", yylval->oval); if (sign < 0) return false; _gst_msg_sendf (&yylval->oval, "%o %o negated", yylval->oval); INC_ADD_OOP (yylval->oval); MAKE_OOP_READONLY (yylval->oval, true); break; } case LARGE_INTEGER_LITERAL: { byte_object bo = yylval->boval; gst_uchar *digits = bo->body; int size = bo->size; int i; /* The input value must be positive. */ if (digits[size - 1] >= 128) return false; /* Do two's complement -- first invert, then increment with carry */ for (i = 0; i < size; i++) digits[i] ^= 255; for (i = 0; (++digits[i]) == 0; i++); /* Search where the number really ends -- discard trailing 111... bytes but remember, the most significant bit of the last digit must be 1! */ for (; size > 0 && digits[size - 1] == 255; size--); if (digits[size - 1] < 128) size++; assert (size <= bo->size); bo->size = size; bo->class = _gst_large_negative_integer_class; break; } default: abort (); } return true; } smalltalk-3.2.5/libgst/genbc-scan.c0000644000175000017500000037003612130455565014075 00000000000000#line 2 "genbc-scan.c" #line 4 "genbc-scan.c" #define YY_INT_ALIGNED short int /* A lexical scanner generated by flex */ #define FLEX_SCANNER #define YY_FLEX_MAJOR_VERSION 2 #define YY_FLEX_MINOR_VERSION 5 #define YY_FLEX_SUBMINOR_VERSION 35 #if YY_FLEX_SUBMINOR_VERSION > 0 #define FLEX_BETA #endif /* First, we deal with platform-specific or compiler-specific issues. */ /* begin standard C headers. */ #include #include #include #include /* end standard C headers. */ /* flex integer type definitions */ #ifndef FLEXINT_H #define FLEXINT_H /* C99 systems have . Non-C99 systems may or may not. */ #if defined (__STDC_VERSION__) && __STDC_VERSION__ >= 199901L /* C99 says to define __STDC_LIMIT_MACROS before including stdint.h, * if you want the limit (max/min) macros for int types. */ #ifndef __STDC_LIMIT_MACROS #define __STDC_LIMIT_MACROS 1 #endif #include typedef int8_t flex_int8_t; typedef uint8_t flex_uint8_t; typedef int16_t flex_int16_t; typedef uint16_t flex_uint16_t; typedef int32_t flex_int32_t; typedef uint32_t flex_uint32_t; #else typedef signed char flex_int8_t; typedef short int flex_int16_t; typedef int flex_int32_t; typedef unsigned char flex_uint8_t; typedef unsigned short int flex_uint16_t; typedef unsigned int flex_uint32_t; /* Limits of integral types. */ #ifndef INT8_MIN #define INT8_MIN (-128) #endif #ifndef INT16_MIN #define INT16_MIN (-32767-1) #endif #ifndef INT32_MIN #define INT32_MIN (-2147483647-1) #endif #ifndef INT8_MAX #define INT8_MAX (127) #endif #ifndef INT16_MAX #define INT16_MAX (32767) #endif #ifndef INT32_MAX #define INT32_MAX (2147483647) #endif #ifndef UINT8_MAX #define UINT8_MAX (255U) #endif #ifndef UINT16_MAX #define UINT16_MAX (65535U) #endif #ifndef UINT32_MAX #define UINT32_MAX (4294967295U) #endif #endif /* ! C99 */ #endif /* ! FLEXINT_H */ #ifdef __cplusplus /* The "const" storage-class-modifier is valid. */ #define YY_USE_CONST #else /* ! __cplusplus */ /* C99 requires __STDC__ to be defined as 1. */ #if defined (__STDC__) #define YY_USE_CONST #endif /* defined (__STDC__) */ #endif /* ! __cplusplus */ #ifdef YY_USE_CONST #define yyconst const #else #define yyconst #endif /* Returned upon end-of-file. */ #define YY_NULL 0 /* Promotes a possibly negative, possibly signed char to an unsigned * integer for use as an array index. If the signed char is negative, * we want to instead treat it as an 8-bit unsigned char, hence the * double cast. */ #define YY_SC_TO_UI(c) ((unsigned int) (unsigned char) c) /* Enter a start condition. This macro really ought to take a parameter, * but we do it the disgusting crufty way forced on us by the ()-less * definition of BEGIN. */ #define BEGIN (yy_start) = 1 + 2 * /* Translate the current start state into a value that can be later handed * to BEGIN to return to the state. The YYSTATE alias is for lex * compatibility. */ #define YY_START (((yy_start) - 1) / 2) #define YYSTATE YY_START /* Action number for EOF rule of a given start state. */ #define YY_STATE_EOF(state) (YY_END_OF_BUFFER + state + 1) /* Special action meaning "start processing a new file". */ #define YY_NEW_FILE yyrestart(yyin ) #define YY_END_OF_BUFFER_CHAR 0 /* Size of default input buffer. */ #ifndef YY_BUF_SIZE #ifdef __ia64__ /* On IA-64, the buffer size is 16k, not 8k. * Moreover, YY_BUF_SIZE is 2*YY_READ_BUF_SIZE in the general case. * Ditto for the __ia64__ case accordingly. */ #define YY_BUF_SIZE 32768 #else #define YY_BUF_SIZE 16384 #endif /* __ia64__ */ #endif /* The state buf must be large enough to hold one state per character in the main buffer. */ #define YY_STATE_BUF_SIZE ((YY_BUF_SIZE + 2) * sizeof(yy_state_type)) #ifndef YY_TYPEDEF_YY_BUFFER_STATE #define YY_TYPEDEF_YY_BUFFER_STATE typedef struct yy_buffer_state *YY_BUFFER_STATE; #endif extern int yyleng; extern FILE *yyin, *yyout; #define EOB_ACT_CONTINUE_SCAN 0 #define EOB_ACT_END_OF_FILE 1 #define EOB_ACT_LAST_MATCH 2 #define YY_LESS_LINENO(n) /* Return all but the first "n" matched characters back to the input stream. */ #define yyless(n) \ do \ { \ /* Undo effects of setting up yytext. */ \ int yyless_macro_arg = (n); \ YY_LESS_LINENO(yyless_macro_arg);\ *yy_cp = (yy_hold_char); \ YY_RESTORE_YY_MORE_OFFSET \ (yy_c_buf_p) = yy_cp = yy_bp + yyless_macro_arg - YY_MORE_ADJ; \ YY_DO_BEFORE_ACTION; /* set up yytext again */ \ } \ while ( 0 ) #define unput(c) yyunput( c, (yytext_ptr) ) #ifndef YY_TYPEDEF_YY_SIZE_T #define YY_TYPEDEF_YY_SIZE_T typedef size_t yy_size_t; #endif #ifndef YY_STRUCT_YY_BUFFER_STATE #define YY_STRUCT_YY_BUFFER_STATE struct yy_buffer_state { FILE *yy_input_file; char *yy_ch_buf; /* input buffer */ char *yy_buf_pos; /* current position in input buffer */ /* Size of input buffer in bytes, not including room for EOB * characters. */ yy_size_t yy_buf_size; /* Number of characters read into yy_ch_buf, not including EOB * characters. */ int yy_n_chars; /* Whether we "own" the buffer - i.e., we know we created it, * and can realloc() it to grow it, and should free() it to * delete it. */ int yy_is_our_buffer; /* Whether this is an "interactive" input source; if so, and * if we're using stdio for input, then we want to use getc() * instead of fread(), to make sure we stop fetching input after * each newline. */ int yy_is_interactive; /* Whether we're considered to be at the beginning of a line. * If so, '^' rules will be active on the next match, otherwise * not. */ int yy_at_bol; int yy_bs_lineno; /**< The line count. */ int yy_bs_column; /**< The column count. */ /* Whether to try to fill the input buffer when we reach the * end of it. */ int yy_fill_buffer; int yy_buffer_status; #define YY_BUFFER_NEW 0 #define YY_BUFFER_NORMAL 1 /* When an EOF's been seen but there's still some text to process * then we mark the buffer as YY_EOF_PENDING, to indicate that we * shouldn't try reading from the input source any more. We might * still have a bunch of tokens to match, though, because of * possible backing-up. * * When we actually see the EOF, we change the status to "new" * (via yyrestart()), so that the user can continue scanning by * just pointing yyin at a new input file. */ #define YY_BUFFER_EOF_PENDING 2 }; #endif /* !YY_STRUCT_YY_BUFFER_STATE */ /* Stack of input buffers. */ static size_t yy_buffer_stack_top = 0; /**< index of top of stack. */ static size_t yy_buffer_stack_max = 0; /**< capacity of stack. */ static YY_BUFFER_STATE * yy_buffer_stack = 0; /**< Stack as an array. */ /* We provide macros for accessing buffer states in case in the * future we want to put the buffer states in a more general * "scanner state". * * Returns the top of the stack, or NULL. */ #define YY_CURRENT_BUFFER ( (yy_buffer_stack) \ ? (yy_buffer_stack)[(yy_buffer_stack_top)] \ : NULL) /* Same as previous macro, but useful when we know that the buffer stack is not * NULL or when we need an lvalue. For internal use only. */ #define YY_CURRENT_BUFFER_LVALUE (yy_buffer_stack)[(yy_buffer_stack_top)] /* yy_hold_char holds the character lost when yytext is formed. */ static char yy_hold_char; static int yy_n_chars; /* number of characters read into yy_ch_buf */ int yyleng; /* Points to current character in buffer. */ static char *yy_c_buf_p = (char *) 0; static int yy_init = 0; /* whether we need to initialize */ static int yy_start = 0; /* start state number */ /* Flag which is used to allow yywrap()'s to do buffer switches * instead of setting up a fresh yyin. A bit of a hack ... */ static int yy_did_buffer_switch_on_eof; void yyrestart (FILE *input_file ); void yy_switch_to_buffer (YY_BUFFER_STATE new_buffer ); YY_BUFFER_STATE yy_create_buffer (FILE *file,int size ); void yy_delete_buffer (YY_BUFFER_STATE b ); void yy_flush_buffer (YY_BUFFER_STATE b ); void yypush_buffer_state (YY_BUFFER_STATE new_buffer ); void yypop_buffer_state (void ); static void yyensure_buffer_stack (void ); static void yy_load_buffer_state (void ); static void yy_init_buffer (YY_BUFFER_STATE b,FILE *file ); #define YY_FLUSH_BUFFER yy_flush_buffer(YY_CURRENT_BUFFER ) YY_BUFFER_STATE yy_scan_buffer (char *base,yy_size_t size ); YY_BUFFER_STATE yy_scan_string (yyconst char *yy_str ); YY_BUFFER_STATE yy_scan_bytes (yyconst char *bytes,int len ); void *yyalloc (yy_size_t ); void *yyrealloc (void *,yy_size_t ); void yyfree (void * ); #define yy_new_buffer yy_create_buffer #define yy_set_interactive(is_interactive) \ { \ if ( ! YY_CURRENT_BUFFER ){ \ yyensure_buffer_stack (); \ YY_CURRENT_BUFFER_LVALUE = \ yy_create_buffer(yyin,YY_BUF_SIZE ); \ } \ YY_CURRENT_BUFFER_LVALUE->yy_is_interactive = is_interactive; \ } #define yy_set_bol(at_bol) \ { \ if ( ! YY_CURRENT_BUFFER ){\ yyensure_buffer_stack (); \ YY_CURRENT_BUFFER_LVALUE = \ yy_create_buffer(yyin,YY_BUF_SIZE ); \ } \ YY_CURRENT_BUFFER_LVALUE->yy_at_bol = at_bol; \ } #define YY_AT_BOL() (YY_CURRENT_BUFFER_LVALUE->yy_at_bol) /* Begin user sect3 */ #define yywrap(n) 1 #define YY_SKIP_YYWRAP typedef unsigned char YY_CHAR; FILE *yyin = (FILE *) 0, *yyout = (FILE *) 0; typedef int yy_state_type; extern int yylineno; int yylineno = 1; extern char *yytext; #define yytext_ptr yytext static yyconst flex_int16_t yy_nxt[][56] = { { 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0 }, { 23, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24 }, { 23, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24 }, { 23, 25, 26, 27, 26, 26, 25, 25, 25, 25, 25, 25, 25, 28, 29, 30, 31, 31, 25, 25, 32, 33, 32, 32, 34, 32, 32, 32, 32, 32, 32, 32, 32, 32, 32, 32, 25, 32, 32, 32, 32, 32, 32, 32, 32, 32, 32, 32, 32, 32, 32, 32, 32, 32, 35, 25 }, { 23, 25, 26, 27, 26, 26, 25, 25, 25, 25, 25, 25, 25, 28, 29, 30, 31, 31, 25, 25, 32, 33, 32, 32, 34, 32, 32, 32, 32, 32, 32, 32, 32, 32, 32, 32, 25, 32, 32, 32, 32, 32, 32, 32, 32, 32, 32, 32, 32, 32, 32, 32, 32, 32, 35, 25 }, { 23, 36, 37, 38, 36, 37, 39, 36, 40, 41, 42, 36, 43, 36, 36, 44, 45, 45, 36, 46, 32, 32, 32, 32, 32, 32, 32, 32, 32, 32, 32, 32, 32, 32, 32, 32, 36, 32, 32, 47, 48, 49, 50, 32, 32, 32, 32, 32, 32, 32, 32, 32, 32, 32, 51, 52 }, { 23, 36, 53, 38, 36, 53, 39, 54, 40, 41, 42, 36, 43, 36, 36, 44, 45, 45, 36, 46, 32, 32, 32, 32, 32, 32, 32, 32, 32, 32, 32, 32, 32, 32, 32, 32, 36, 32, 32, 47, 48, 49, 50, 32, 32, 32, 32, 32, 32, 32, 32, 32, 32, 32, 51, 52 }, { 23, 55, 56, 27, 56, 56, 57, 55, 58, 55, 55, 55, 55, 55, 59, 55, 55, 55, 55, 55, 55, 55, 55, 55, 55, 55, 55, 55, 55, 55, 60, 55, 55, 55, 55, 55, 55, 55, 55, 55, 55, 55, 55, 55, 55, 55, 55, 55, 55, 55, 55, 55, 55, 55, 55, 55 }, { 23, 55, 61, 27, 56, 61, 57, 62, 58, 55, 55, 55, 55, 55, 59, 55, 55, 55, 55, 55, 55, 55, 55, 55, 55, 55, 55, 55, 55, 55, 60, 55, 55, 55, 55, 55, 55, 55, 55, 55, 55, 55, 55, 55, 55, 55, 55, 55, 55, 55, 55, 55, 55, 55, 55, 55 }, { 23, 63, 63, 64, 63, 63, 65, 63, 66, 63, 63, 63, 63, 63, 63, 63, 63, 63, 63, 63, 63, 63, 63, 63, 63, 63, 63, 63, 63, 63, 63, 63, 63, 63, 63, 63, 63, 63, 63, 63, 63, 63, 63, 63, 63, 63, 63, 63, 63, 63, 63, 63, 63, 63, 67, 68 }, { 23, 63, 69, 64, 63, 69, 65, 70, 66, 63, 63, 63, 63, 63, 63, 63, 63, 63, 63, 63, 63, 63, 63, 63, 63, 63, 63, 63, 63, 63, 63, 63, 63, 63, 63, 63, 63, 63, 63, 63, 63, 63, 63, 63, 63, 63, 63, 63, 63, 63, 63, 63, 63, 63, 67, 68 }, { 23, 24, 71, 27, 71, 71, 24, 24, 24, 24, 72, 24, 24, 24, 73, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24 }, { 23, 24, 71, 27, 71, 71, 24, 24, 24, 24, 72, 24, 24, 24, 73, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24, 24 }, { 23, 25, 26, 27, 26, 26, 39, 25, 40, 25, 74, 25, 25, 25, 29, 25, 25, 25, 25, 25, 32, 32, 32, 32, 32, 32, 32, 32, 32, 32, 32, 32, 32, 32, 32, 32, 25, 32, 32, 32, 32, 32, 32, 32, 32, 32, 32, 32, 32, 32, 32, 32, 32, 32, 75, 25 }, { 23, 25, 76, 27, 26, 76, 39, 77, 40, 25, 74, 25, 25, 25, 29, 25, 25, 25, 25, 25, 32, 32, 32, 32, 32, 32, 32, 32, 32, 32, 32, 32, 32, 32, 32, 32, 25, 32, 32, 32, 32, 32, 32, 32, 32, 32, 32, 32, 32, 32, 32, 32, 32, 32, 75, 25 }, { 23, 78, 79, 80, 79, 79, 78, 78, 78, 78, 78, 78, 78, 78, 81, 78, 78, 78, 78, 78, 78, 78, 78, 78, 78, 78, 78, 78, 78, 78, 78, 78, 78, 78, 78, 78, 82, 78, 78, 78, 78, 78, 78, 78, 78, 78, 78, 78, 78, 78, 78, 78, 78, 78, 78, 78 }, { 23, 78, 79, 80, 79, 79, 78, 78, 78, 78, 78, 78, 78, 78, 81, 78, 78, 78, 78, 78, 78, 78, 78, 78, 78, 78, 78, 78, 78, 78, 78, 78, 78, 78, 78, 78, 82, 78, 78, 78, 78, 78, 78, 78, 78, 78, 78, 78, 78, 78, 78, 78, 78, 78, 78, 78 }, { 23, 83, 84, 85, 84, 84, 83, 83, 83, 83, 83, 86, 83, 83, 87, 83, 83, 83, 83, 83, 83, 83, 83, 83, 83, 83, 83, 83, 83, 83, 83, 83, 83, 83, 83, 83, 83, 83, 83, 83, 83, 83, 83, 83, 83, 83, 83, 83, 83, 83, 83, 83, 83, 83, 83, 83 }, { 23, 83, 84, 85, 84, 84, 83, 83, 83, 83, 83, 86, 83, 83, 87, 83, 83, 83, 83, 83, 83, 83, 83, 83, 83, 83, 83, 83, 83, 83, 83, 83, 83, 83, 83, 83, 83, 83, 83, 83, 83, 83, 83, 83, 83, 83, 83, 83, 83, 83, 83, 83, 83, 83, 83, 83 }, { 23, 88, 88, 24, 88, 88, 89, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 90, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88 }, { 23, 88, 88, 24, 88, 88, 89, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 90, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88 }, { 23, 88, 88, 24, 88, 88, 88, 88, 91, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 90, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88 }, { 23, 88, 88, 24, 88, 88, 88, 88, 91, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 90, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88 }, { -23, -23, -23, -23, -23, -23, -23, -23, -23, -23, -23, -23, -23, -23, -23, -23, -23, -23, -23, -23, -23, -23, -23, -23, -23, -23, -23, -23, -23, -23, -23, -23, -23, -23, -23, -23, -23, -23, -23, -23, -23, -23, -23, -23, -23, -23, -23, -23, -23, -23, -23, -23, -23, -23, -23, -23 }, { 23, -24, -24, -24, -24, -24, -24, -24, -24, -24, -24, -24, -24, -24, -24, -24, -24, -24, -24, -24, -24, -24, -24, -24, -24, -24, -24, -24, -24, -24, -24, -24, -24, -24, -24, -24, -24, -24, -24, -24, -24, -24, -24, -24, -24, -24, -24, -24, -24, -24, -24, -24, -24, -24, -24, -24 }, { 23, -25, -25, -25, -25, -25, -25, -25, -25, -25, -25, -25, -25, -25, -25, -25, -25, -25, -25, -25, -25, -25, -25, -25, -25, -25, -25, -25, -25, -25, -25, -25, -25, -25, -25, -25, -25, -25, -25, -25, -25, -25, -25, -25, -25, -25, -25, -25, -25, -25, -25, -25, -25, -25, -25, -25 }, { 23, -26, 92, -26, 92, 92, -26, -26, -26, -26, -26, -26, -26, -26, -26, -26, -26, -26, -26, -26, -26, -26, -26, -26, -26, -26, -26, -26, -26, -26, -26, -26, -26, -26, -26, -26, -26, -26, -26, -26, -26, -26, -26, -26, -26, -26, -26, -26, -26, -26, -26, -26, -26, -26, -26, -26 }, { 23, -27, -27, 93, -27, -27, -27, -27, -27, -27, -27, -27, -27, -27, -27, -27, -27, -27, -27, -27, -27, -27, -27, -27, -27, -27, -27, -27, -27, -27, -27, -27, -27, -27, -27, -27, -27, -27, -27, -27, -27, -27, -27, -27, -27, -27, -27, -27, -27, -27, -27, -27, -27, -27, -27, -27 }, { 23, -28, -28, -28, -28, -28, -28, -28, -28, -28, -28, -28, -28, 94, -28, -28, -28, -28, -28, -28, -28, -28, -28, -28, -28, -28, -28, -28, -28, -28, -28, -28, -28, -28, -28, -28, -28, -28, -28, -28, -28, -28, -28, -28, -28, -28, -28, -28, -28, -28, -28, -28, -28, -28, -28, -28 }, { 23, -29, -29, -29, -29, -29, -29, -29, -29, -29, -29, 95, -29, -29, -29, -29, -29, -29, -29, -29, -29, -29, -29, -29, -29, -29, -29, -29, -29, -29, -29, -29, -29, -29, -29, -29, -29, -29, -29, -29, -29, -29, -29, -29, -29, -29, -29, -29, -29, -29, -29, -29, -29, -29, -29, -29 }, { 23, -30, -30, -30, -30, -30, -30, -30, -30, -30, -30, -30, -30, -30, -30, 96, 96, -30, -30, -30, -30, -30, -30, -30, -30, -30, -30, -30, -30, -30, -30, -30, -30, -30, -30, -30, -30, -30, -30, -30, -30, -30, -30, -30, -30, -30, -30, -30, -30, -30, -30, -30, -30, 97, -30, -30 }, { 23, -31, -31, -31, -31, -31, -31, -31, -31, -31, -31, -31, -31, -31, -31, 98, 98, 98, -31, -31, -31, -31, -31, -31, -31, -31, -31, -31, -31, -31, -31, -31, -31, -31, -31, -31, -31, -31, -31, -31, -31, -31, -31, -31, -31, -31, -31, -31, -31, -31, -31, -31, -31, -31, -31, -31 }, { 23, -32, -32, -32, -32, -32, -32, -32, -32, -32, -32, -32, -32, -32, -32, 99, 99, 99, -32, -32, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, -32, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, -32, -32 }, { 23, -33, -33, -33, -33, -33, -33, -33, -33, -33, -33, -33, -33, -33, -33, 99, 99, 99, -33, -33, 99, 99, 99, 99, 100, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, -33, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, -33, -33 }, { 23, -34, -34, -34, -34, -34, -34, -34, -34, -34, -34, -34, -34, -34, -34, 99, 99, 99, -34, -34, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 101, 99, 99, 99, 99, -34, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, -34, -34 }, { 23, -35, -35, 102, -35, -35, -35, -35, -35, -35, -35, -35, -35, -35, -35, -35, -35, -35, -35, -35, -35, -35, -35, -35, -35, -35, -35, -35, -35, -35, -35, -35, -35, -35, -35, -35, -35, -35, -35, -35, -35, -35, -35, -35, -35, -35, -35, -35, -35, -35, -35, -35, -35, -35, -35, -35 }, { 23, 103, 103, -36, 103, 103, -36, 103, -36, -36, -36, 103, -36, 103, 103, 103, 103, 103, 103, -36, -36, -36, -36, -36, -36, -36, -36, -36, -36, -36, -36, -36, -36, -36, -36, -36, 103, -36, -36, -36, -36, -36, -36, -36, -36, -36, -36, -36, -36, -36, -36, -36, -36, -36, -36, -36 }, { 23, 103, 104, -37, 103, 104, -37, 103, -37, 105, 106, 103, 107, 103, 103, 103, 103, 103, 103, 108, -37, -37, -37, -37, -37, -37, -37, -37, -37, -37, -37, -37, -37, -37, -37, -37, 103, -37, -37, -37, -37, -37, -37, -37, -37, -37, -37, -37, -37, -37, -37, -37, -37, -37, 109, 110 }, { 23, -38, -38, -38, -38, -38, -38, -38, -38, -38, -38, -38, -38, -38, -38, -38, -38, -38, -38, -38, -38, -38, -38, -38, -38, -38, -38, -38, -38, -38, -38, -38, -38, -38, -38, -38, -38, -38, -38, -38, -38, -38, -38, -38, -38, -38, -38, -38, -38, -38, -38, -38, -38, -38, -38, -38 }, { 23, -39, -39, -39, -39, -39, -39, -39, -39, -39, -39, -39, -39, -39, -39, -39, -39, -39, -39, -39, -39, -39, -39, -39, -39, -39, -39, -39, -39, -39, -39, -39, -39, -39, -39, -39, -39, -39, -39, -39, -39, -39, -39, -39, -39, -39, -39, -39, -39, -39, -39, -39, -39, -39, -39, -39 }, { 23, -40, -40, -40, -40, -40, -40, -40, -40, -40, -40, -40, -40, -40, -40, -40, -40, -40, -40, -40, -40, -40, -40, -40, -40, -40, -40, -40, -40, -40, -40, -40, -40, -40, -40, -40, -40, -40, -40, -40, -40, -40, -40, -40, -40, -40, -40, -40, -40, -40, -40, -40, -40, -40, -40, -40 }, { 23, -41, 111, -41, -41, 111, -41, -41, -41, -41, -41, -41, -41, -41, -41, -41, -41, -41, -41, -41, -41, -41, -41, -41, -41, -41, -41, -41, -41, -41, -41, -41, -41, -41, -41, -41, -41, -41, -41, -41, -41, -41, -41, -41, -41, -41, -41, -41, -41, -41, -41, -41, -41, -41, -41, -41 }, { 23, -42, 112, -42, -42, 112, -42, -42, -42, -42, -42, -42, -42, -42, -42, -42, -42, -42, -42, -42, -42, -42, -42, -42, -42, -42, -42, -42, -42, -42, -42, -42, -42, -42, -42, -42, -42, -42, -42, -42, -42, -42, -42, -42, -42, -42, -42, -42, -42, -42, -42, -42, -42, -42, -42, -42 }, { 23, -43, 113, -43, -43, 113, -43, -43, -43, -43, -43, -43, -43, -43, -43, -43, -43, -43, -43, -43, -43, -43, -43, -43, -43, -43, -43, -43, -43, -43, -43, -43, -43, -43, -43, -43, -43, -43, -43, -43, -43, -43, -43, -43, -43, -43, -43, -43, -43, -43, -43, -43, -43, -43, -43, -43 }, { 23, 103, 103, -44, 103, 103, -44, 103, -44, -44, -44, 103, -44, 103, 103, 114, 114, 103, 103, -44, -44, -44, -44, -44, -44, -44, -44, -44, -44, -44, -44, -44, -44, -44, -44, -44, 103, -44, -44, -44, -44, -44, -44, -44, -44, -44, -44, -44, -44, -44, -44, -44, -44, 97, -44, -44 }, { 23, 103, 103, -45, 103, 103, -45, 103, -45, -45, -45, 103, -45, 103, 103, 115, 115, 115, 103, -45, -45, -45, -45, -45, -45, -45, -45, -45, -45, -45, -45, -45, -45, -45, -45, -45, 103, -45, -45, -45, -45, -45, -45, -45, -45, -45, -45, -45, -45, -45, -45, -45, -45, -45, -45, -45 }, { 23, -46, 116, -46, -46, 116, -46, -46, -46, -46, -46, -46, -46, -46, -46, -46, -46, -46, -46, -46, -46, -46, -46, -46, -46, -46, -46, -46, -46, -46, -46, -46, -46, -46, -46, -46, -46, -46, -46, -46, -46, -46, -46, -46, -46, -46, -46, -46, -46, -46, -46, -46, -46, -46, -46, -46 }, { 23, -47, -47, -47, -47, -47, -47, -47, -47, -47, -47, -47, -47, -47, -47, 99, 99, 99, -47, -47, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, -47, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 117, 99, 99, 99, 99, -47, -47 }, { 23, -48, -48, -48, -48, -48, -48, -48, -48, -48, -48, -48, -48, -48, -48, 99, 99, 99, -48, -48, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, -48, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 118, 99, 99, 99, 99, 99, 99, -48, -48 }, { 23, -49, -49, -49, -49, -49, -49, -49, -49, -49, -49, -49, -49, -49, -49, 99, 99, 99, -49, -49, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, -49, 99, 99, 99, 99, 99, 99, 99, 119, 99, 99, 99, 99, 99, 99, 99, 99, 99, -49, -49 }, { 23, -50, -50, -50, -50, -50, -50, -50, -50, -50, -50, -50, -50, -50, -50, 99, 99, 99, -50, -50, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, -50, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 120, -50, -50 }, { 23, -51, -51, -51, -51, -51, -51, -51, -51, -51, -51, -51, -51, -51, -51, -51, -51, -51, -51, -51, -51, -51, -51, -51, -51, -51, -51, -51, -51, -51, -51, -51, -51, -51, -51, -51, -51, -51, -51, -51, -51, -51, -51, -51, -51, -51, -51, -51, -51, -51, -51, -51, -51, -51, -51, -51 }, { 23, -52, -52, -52, -52, -52, -52, -52, -52, -52, -52, -52, -52, -52, -52, -52, -52, -52, -52, -52, -52, -52, -52, -52, -52, -52, -52, -52, -52, -52, -52, -52, -52, -52, -52, -52, -52, -52, -52, -52, -52, -52, -52, -52, -52, -52, -52, -52, -52, -52, -52, -52, -52, -52, -52, -52 }, { 23, 103, 121, -53, 103, 121, -53, 122, -53, 105, 106, 103, 107, 103, 103, 103, 103, 103, 103, 108, -53, -53, -53, -53, -53, -53, -53, -53, -53, -53, -53, -53, -53, -53, -53, -53, 103, -53, -53, -53, -53, -53, -53, -53, -53, -53, -53, -53, -53, -53, -53, -53, -53, -53, 109, 110 }, { 23, 103, 103, -54, 103, 103, -54, 103, -54, -54, -54, 103, -54, 103, 103, 103, 103, 103, 103, -54, -54, -54, -54, -54, -54, -54, -54, -54, -54, -54, -54, -54, -54, -54, -54, -54, 103, -54, -54, -54, -54, -54, -54, -54, -54, -54, -54, -54, -54, -54, -54, -54, -54, -54, -54, -54 }, { 23, 123, 123, -55, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, -55, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123 }, { 23, 123, 124, -56, 124, 124, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, -56, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123 }, { 23, 123, 123, -57, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, -57, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123 }, { 23, 123, 123, -58, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, -58, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123 }, { 23, 123, 123, -59, 123, 123, 123, 123, 123, 123, 123, 125, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, -59, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123 }, { 23, -60, -60, -60, -60, -60, -60, -60, -60, -60, -60, -60, -60, -60, -60, -60, -60, -60, -60, -60, 126, -60, -60, -60, -60, -60, -60, -60, -60, -60, -60, -60, -60, -60, -60, -60, -60, -60, -60, -60, -60, -60, -60, -60, -60, -60, -60, -60, -60, -60, -60, -60, -60, -60, -60, -60 }, { 23, 123, 127, -61, 124, 127, 123, 128, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, -61, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123 }, { 23, 123, 123, -62, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, -62, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123 }, { 23, 129, 129, -63, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, -63, -63 }, { 23, -64, -64, -64, -64, -64, -64, -64, -64, -64, -64, -64, -64, -64, -64, -64, -64, -64, -64, -64, -64, -64, -64, -64, -64, -64, -64, -64, -64, -64, -64, -64, -64, -64, -64, -64, -64, -64, -64, -64, -64, -64, -64, -64, -64, -64, -64, -64, -64, -64, -64, -64, -64, -64, -64, -64 }, { 23, 129, 129, -65, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, -65, -65 }, { 23, 129, 129, -66, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, -66, -66 }, { 23, -67, -67, -67, -67, -67, -67, -67, -67, -67, -67, -67, -67, -67, -67, -67, -67, -67, -67, -67, -67, -67, -67, -67, -67, -67, -67, -67, -67, -67, -67, -67, -67, -67, -67, -67, -67, -67, -67, -67, -67, -67, -67, -67, -67, -67, -67, -67, -67, -67, -67, -67, -67, -67, -67, -67 }, { 23, -68, -68, -68, -68, -68, -68, -68, -68, -68, -68, -68, -68, -68, -68, -68, -68, -68, -68, -68, -68, -68, -68, -68, -68, -68, -68, -68, -68, -68, -68, -68, -68, -68, -68, -68, -68, -68, -68, -68, -68, -68, -68, -68, -68, -68, -68, -68, -68, -68, -68, -68, -68, -68, -68, -68 }, { 23, 129, 130, -69, 129, 130, 129, 131, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, -69, -69 }, { 23, 129, 129, -70, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, -70, -70 }, { 23, -71, 92, -71, 92, 92, -71, -71, -71, -71, -71, -71, -71, -71, -71, -71, -71, -71, -71, -71, -71, -71, -71, -71, -71, -71, -71, -71, -71, -71, -71, -71, -71, -71, -71, -71, -71, -71, -71, -71, -71, -71, -71, -71, -71, -71, -71, -71, -71, -71, -71, -71, -71, -71, -71, -71 }, { 23, -72, -72, -72, -72, -72, -72, -72, -72, -72, -72, -72, -72, -72, -72, -72, -72, -72, -72, -72, -72, -72, -72, -72, -72, -72, -72, -72, -72, -72, -72, -72, -72, -72, -72, -72, -72, -72, -72, -72, -72, -72, -72, -72, -72, -72, -72, -72, -72, -72, -72, -72, -72, -72, -72, -72 }, { 23, -73, -73, -73, -73, -73, -73, -73, -73, -73, -73, 95, -73, -73, -73, -73, -73, -73, -73, -73, -73, -73, -73, -73, -73, -73, -73, -73, -73, -73, -73, -73, -73, -73, -73, -73, -73, -73, -73, -73, -73, -73, -73, -73, -73, -73, -73, -73, -73, -73, -73, -73, -73, -73, -73, -73 }, { 23, -74, -74, -74, -74, -74, -74, -74, -74, -74, -74, -74, -74, -74, -74, -74, -74, -74, -74, -74, -74, -74, -74, -74, -74, -74, -74, -74, -74, -74, -74, -74, -74, -74, -74, -74, -74, -74, -74, -74, -74, -74, -74, -74, -74, -74, -74, -74, -74, -74, -74, -74, -74, -74, -74, -74 }, { 23, -75, -75, -75, -75, -75, -75, -75, -75, -75, -75, -75, -75, -75, -75, -75, -75, -75, -75, -75, -75, -75, -75, -75, -75, -75, -75, -75, -75, -75, -75, -75, -75, -75, -75, -75, -75, -75, -75, -75, -75, -75, -75, -75, -75, -75, -75, -75, -75, -75, -75, -75, -75, -75, -75, -75 }, { 23, -76, 132, -76, 92, 132, -76, 133, -76, -76, -76, -76, -76, -76, -76, -76, -76, -76, -76, -76, -76, -76, -76, -76, -76, -76, -76, -76, -76, -76, -76, -76, -76, -76, -76, -76, -76, -76, -76, -76, -76, -76, -76, -76, -76, -76, -76, -76, -76, -76, -76, -76, -76, -76, -76, -76 }, { 23, -77, -77, -77, -77, -77, -77, -77, -77, -77, -77, -77, -77, -77, -77, -77, -77, -77, -77, -77, -77, -77, -77, -77, -77, -77, -77, -77, -77, -77, -77, -77, -77, -77, -77, -77, -77, -77, -77, -77, -77, -77, -77, -77, -77, -77, -77, -77, -77, -77, -77, -77, -77, -77, -77, -77 }, { 23, 134, 134, 135, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 136, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134 }, { 23, 134, 137, 135, 137, 137, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 136, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134 }, { 23, -80, -80, 93, -80, -80, -80, -80, -80, -80, -80, -80, -80, -80, -80, -80, -80, -80, -80, -80, -80, -80, -80, -80, -80, -80, -80, -80, -80, -80, -80, -80, -80, -80, -80, -80, -80, -80, -80, -80, -80, -80, -80, -80, -80, -80, -80, -80, -80, -80, -80, -80, -80, -80, -80, -80 }, { 23, 134, 134, 135, 134, 134, 134, 134, 134, 134, 134, 138, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 136, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134 }, { 23, 134, 134, 139, 134, 140, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 136, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134 }, { 23, 141, 141, 142, 141, 141, 141, 141, 141, 141, 141, 143, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141 }, { 23, 141, 144, 142, 144, 144, 141, 141, 141, 141, 141, 143, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141 }, { 23, -85, -85, 93, -85, -85, -85, -85, -85, -85, -85, -85, -85, -85, -85, -85, -85, -85, -85, -85, -85, -85, -85, -85, -85, -85, -85, -85, -85, -85, -85, -85, -85, -85, -85, -85, -85, -85, -85, -85, -85, -85, -85, -85, -85, -85, -85, -85, -85, -85, -85, -85, -85, -85, -85, -85 }, { 23, 145, 145, 146, 145, 145, 145, 145, 145, 145, 145, 143, 145, 145, 147, 145, 145, 145, 145, 145, 145, 145, 145, 145, 145, 145, 145, 145, 145, 145, 145, 145, 145, 145, 145, 145, 145, 145, 145, 145, 145, 145, 145, 145, 145, 145, 145, 145, 145, 145, 145, 145, 145, 145, 145, 145 }, { 23, 141, 141, 142, 141, 141, 141, 141, 141, 141, 141, 148, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141 }, { 23, -88, -88, -88, -88, -88, -88, -88, -88, -88, -88, -88, -88, -88, -88, -88, -88, -88, -88, -88, -88, -88, -88, -88, -88, -88, -88, -88, -88, -88, -88, -88, -88, -88, -88, -88, -88, -88, -88, -88, -88, -88, -88, -88, -88, -88, -88, -88, -88, -88, -88, -88, -88, -88, -88, -88 }, { 23, -89, -89, -89, -89, -89, -89, -89, -89, -89, -89, -89, -89, -89, -89, -89, -89, -89, -89, -89, -89, -89, -89, -89, -89, -89, -89, -89, -89, -89, -89, -89, -89, -89, -89, -89, -89, -89, -89, -89, -89, -89, -89, -89, -89, -89, -89, -89, -89, -89, -89, -89, -89, -89, -89, -89 }, { 23, 149, 149, -90, 149, 149, 149, 149, 149, 149, 149, 149, 149, 149, 149, 149, 149, 149, 149, 149, 149, 149, 149, 149, 149, 149, 149, 149, 149, 149, 149, 149, 149, 149, 149, 149, 149, 149, 149, 149, 149, 149, 149, 149, 149, 149, 149, 149, 149, 149, 149, 149, 149, 149, 149, 149 }, { 23, -91, -91, -91, -91, -91, -91, -91, -91, -91, -91, -91, -91, -91, -91, -91, -91, -91, -91, -91, -91, -91, -91, -91, -91, -91, -91, -91, -91, -91, -91, -91, -91, -91, -91, -91, -91, -91, -91, -91, -91, -91, -91, -91, -91, -91, -91, -91, -91, -91, -91, -91, -91, -91, -91, -91 }, { 23, -92, 92, -92, 92, 92, -92, -92, -92, -92, -92, -92, -92, -92, -92, -92, -92, -92, -92, -92, -92, -92, -92, -92, -92, -92, -92, -92, -92, -92, -92, -92, -92, -92, -92, -92, -92, -92, -92, -92, -92, -92, -92, -92, -92, -92, -92, -92, -92, -92, -92, -92, -92, -92, -92, -92 }, { 23, -93, -93, 93, -93, -93, -93, -93, -93, -93, -93, -93, -93, -93, -93, -93, -93, -93, -93, -93, -93, -93, -93, -93, -93, -93, -93, -93, -93, -93, -93, -93, -93, -93, -93, -93, -93, -93, -93, -93, -93, -93, -93, -93, -93, -93, -93, -93, -93, -93, -93, -93, -93, -93, -93, -93 }, { 23, -94, -94, -94, -94, -94, -94, -94, -94, -94, -94, -94, -94, -94, -94, -94, -94, -94, -94, -94, -94, -94, -94, -94, -94, -94, -94, -94, -94, -94, -94, -94, -94, -94, -94, -94, -94, -94, -94, -94, -94, -94, -94, -94, -94, -94, -94, -94, -94, -94, -94, -94, -94, -94, -94, -94 }, { 23, -95, -95, -95, -95, -95, -95, -95, -95, -95, -95, -95, -95, -95, -95, -95, -95, -95, -95, -95, -95, -95, -95, -95, -95, -95, -95, -95, -95, -95, -95, -95, -95, -95, -95, -95, -95, -95, -95, -95, -95, -95, -95, -95, -95, -95, -95, -95, -95, -95, -95, -95, -95, -95, -95, -95 }, { 23, -96, -96, -96, -96, -96, -96, -96, -96, -96, -96, -96, -96, -96, -96, 96, 96, -96, -96, -96, -96, -96, -96, -96, -96, -96, -96, -96, -96, -96, -96, -96, -96, -96, -96, -96, -96, -96, -96, -96, -96, -96, -96, -96, -96, -96, -96, -96, -96, -96, -96, -96, -96, -96, -96, -96 }, { 23, -97, -97, -97, -97, -97, -97, -97, -97, -97, -97, -97, -97, -97, -97, 150, 150, 150, -97, -97, 150, 150, 150, 150, 150, 150, -97, -97, -97, -97, -97, -97, -97, -97, -97, -97, -97, -97, 150, 150, 150, 150, 150, -97, -97, -97, -97, -97, -97, -97, -97, -97, -97, -97, -97, -97 }, { 23, -98, -98, -98, -98, -98, -98, -98, -98, -98, -98, -98, -98, -98, -98, 98, 98, 98, -98, -98, -98, -98, -98, -98, -98, -98, -98, -98, -98, -98, -98, -98, -98, -98, -98, -98, -98, -98, -98, -98, -98, -98, -98, -98, -98, -98, -98, -98, -98, -98, -98, -98, -98, -98, -98, -98 }, { 23, -99, -99, -99, -99, -99, -99, -99, -99, -99, -99, -99, -99, -99, -99, 99, 99, 99, -99, -99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, -99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, -99, -99 }, { 23, -100, -100, -100, -100, -100, -100, -100, -100, -100, -100, -100, -100, -100, -100, 99, 99, 99, -100, -100, 99, 99, 99, 99, 99, 99, 151, 99, 99, 99, 99, 99, 99, 99, 99, 99, -100, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, -100, -100 }, { 23, -101, -101, -101, -101, -101, -101, -101, -101, -101, -101, -101, -101, -101, -101, 99, 99, 99, -101, -101, 99, 99, 99, 152, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, -101, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, -101, -101 }, { 23, -102, -102, 102, -102, -102, -102, -102, -102, -102, -102, -102, -102, -102, -102, -102, -102, -102, -102, -102, -102, -102, -102, -102, -102, -102, -102, -102, -102, -102, -102, -102, -102, -102, -102, -102, -102, -102, -102, -102, -102, -102, -102, -102, -102, -102, -102, -102, -102, -102, -102, -102, -102, -102, -102, -102 }, { 23, 103, 103, -103, 103, 103, -103, 103, -103, -103, -103, 103, -103, 103, 103, 103, 103, 103, 103, -103, -103, -103, -103, -103, -103, -103, -103, -103, -103, -103, -103, -103, -103, -103, -103, -103, 103, -103, -103, -103, -103, -103, -103, -103, -103, -103, -103, -103, -103, -103, -103, -103, -103, -103, -103, -103 }, { 23, 103, 104, -104, 103, 104, -104, 103, -104, 105, 106, 103, 107, 103, 103, 103, 103, 103, 103, 108, -104, -104, -104, -104, -104, -104, -104, -104, -104, -104, -104, -104, -104, -104, -104, -104, 103, -104, -104, -104, -104, -104, -104, -104, -104, -104, -104, -104, -104, -104, -104, -104, -104, -104, 109, 110 }, { 23, -105, 111, -105, -105, 111, -105, -105, -105, -105, -105, -105, -105, -105, -105, -105, -105, -105, -105, -105, -105, -105, -105, -105, -105, -105, -105, -105, -105, -105, -105, -105, -105, -105, -105, -105, -105, -105, -105, -105, -105, -105, -105, -105, -105, -105, -105, -105, -105, -105, -105, -105, -105, -105, -105, -105 }, { 23, -106, 112, -106, -106, 112, -106, -106, -106, -106, -106, -106, -106, -106, -106, -106, -106, -106, -106, -106, -106, -106, -106, -106, -106, -106, -106, -106, -106, -106, -106, -106, -106, -106, -106, -106, -106, -106, -106, -106, -106, -106, -106, -106, -106, -106, -106, -106, -106, -106, -106, -106, -106, -106, -106, -106 }, { 23, -107, 113, -107, -107, 113, -107, -107, -107, -107, -107, -107, -107, -107, -107, -107, -107, -107, -107, -107, -107, -107, -107, -107, -107, -107, -107, -107, -107, -107, -107, -107, -107, -107, -107, -107, -107, -107, -107, -107, -107, -107, -107, -107, -107, -107, -107, -107, -107, -107, -107, -107, -107, -107, -107, -107 }, { 23, -108, 116, -108, -108, 116, -108, -108, -108, -108, -108, -108, -108, -108, -108, -108, -108, -108, -108, -108, -108, -108, -108, -108, -108, -108, -108, -108, -108, -108, -108, -108, -108, -108, -108, -108, -108, -108, -108, -108, -108, -108, -108, -108, -108, -108, -108, -108, -108, -108, -108, -108, -108, -108, -108, -108 }, { 23, -109, -109, -109, -109, -109, -109, -109, -109, -109, -109, -109, -109, -109, -109, -109, -109, -109, -109, -109, -109, -109, -109, -109, -109, -109, -109, -109, -109, -109, -109, -109, -109, -109, -109, -109, -109, -109, -109, -109, -109, -109, -109, -109, -109, -109, -109, -109, -109, -109, -109, -109, -109, -109, -109, -109 }, { 23, -110, -110, -110, -110, -110, -110, -110, -110, -110, -110, -110, -110, -110, -110, -110, -110, -110, -110, -110, -110, -110, -110, -110, -110, -110, -110, -110, -110, -110, -110, -110, -110, -110, -110, -110, -110, -110, -110, -110, -110, -110, -110, -110, -110, -110, -110, -110, -110, -110, -110, -110, -110, -110, -110, -110 }, { 23, -111, 111, -111, -111, 111, -111, -111, -111, -111, -111, -111, -111, -111, -111, -111, -111, -111, -111, -111, -111, -111, -111, -111, -111, -111, -111, -111, -111, -111, -111, -111, -111, -111, -111, -111, -111, -111, -111, -111, -111, -111, -111, -111, -111, -111, -111, -111, -111, -111, -111, -111, -111, -111, -111, -111 }, { 23, -112, 112, -112, -112, 112, -112, -112, -112, -112, -112, -112, -112, -112, -112, -112, -112, -112, -112, -112, -112, -112, -112, -112, -112, -112, -112, -112, -112, -112, -112, -112, -112, -112, -112, -112, -112, -112, -112, -112, -112, -112, -112, -112, -112, -112, -112, -112, -112, -112, -112, -112, -112, -112, -112, -112 }, { 23, -113, 113, -113, -113, 113, -113, -113, -113, -113, -113, -113, -113, -113, -113, -113, -113, -113, -113, -113, -113, -113, -113, -113, -113, -113, -113, -113, -113, -113, -113, -113, -113, -113, -113, -113, -113, -113, -113, -113, -113, -113, -113, -113, -113, -113, -113, -113, -113, -113, -113, -113, -113, -113, -113, -113 }, { 23, 103, 103, -114, 103, 103, -114, 103, -114, -114, -114, 103, -114, 103, 103, 114, 114, 103, 103, -114, -114, -114, -114, -114, -114, -114, -114, -114, -114, -114, -114, -114, -114, -114, -114, -114, 103, -114, -114, -114, -114, -114, -114, -114, -114, -114, -114, -114, -114, -114, -114, -114, -114, -114, -114, -114 }, { 23, 103, 103, -115, 103, 103, -115, 103, -115, -115, -115, 103, -115, 103, 103, 115, 115, 115, 103, -115, -115, -115, -115, -115, -115, -115, -115, -115, -115, -115, -115, -115, -115, -115, -115, -115, 103, -115, -115, -115, -115, -115, -115, -115, -115, -115, -115, -115, -115, -115, -115, -115, -115, -115, -115, -115 }, { 23, -116, 116, -116, -116, 116, -116, -116, -116, -116, -116, -116, -116, -116, -116, -116, -116, -116, -116, -116, -116, -116, -116, -116, -116, -116, -116, -116, -116, -116, -116, -116, -116, -116, -116, -116, -116, -116, -116, -116, -116, -116, -116, -116, -116, -116, -116, -116, -116, -116, -116, -116, -116, -116, -116, -116 }, { 23, -117, -117, -117, -117, -117, -117, -117, -117, -117, -117, -117, -117, -117, -117, 99, 99, 99, -117, -117, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, -117, 99, 99, 99, 99, 99, 153, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, -117, -117 }, { 23, -118, -118, -118, -118, -118, -118, -118, -118, -118, -118, -118, -118, -118, -118, 99, 99, 99, -118, -118, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, -118, 99, 99, 99, 99, 99, 99, 99, 99, 99, 154, 99, 99, 99, 99, 99, 99, 99, -118, -118 }, { 23, -119, -119, -119, -119, -119, -119, -119, -119, -119, -119, -119, -119, -119, -119, 99, 99, 99, -119, -119, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, -119, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 155, 99, 99, 99, -119, -119 }, { 23, -120, -120, -120, -120, -120, -120, -120, -120, -120, -120, -120, -120, -120, -120, 99, 99, 99, -120, -120, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, -120, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 156, 99, 99, -120, -120 }, { 23, 103, 121, -121, 103, 121, -121, 122, -121, 105, 106, 103, 107, 103, 103, 103, 103, 103, 103, 108, -121, -121, -121, -121, -121, -121, -121, -121, -121, -121, -121, -121, -121, -121, -121, -121, 103, -121, -121, -121, -121, -121, -121, -121, -121, -121, -121, -121, -121, -121, -121, -121, -121, -121, 109, 110 }, { 23, 103, 103, -122, 103, 103, -122, 103, -122, -122, -122, 103, -122, 103, 103, 103, 103, 103, 103, -122, -122, -122, -122, -122, -122, -122, -122, -122, -122, -122, -122, -122, -122, -122, -122, -122, 103, -122, -122, -122, -122, -122, -122, -122, -122, -122, -122, -122, -122, -122, -122, -122, -122, -122, -122, -122 }, { 23, 123, 123, -123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, -123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123 }, { 23, 123, 124, -124, 124, 124, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, -124, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123 }, { 23, 123, 123, -125, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, -125, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123 }, { 23, -126, -126, -126, -126, -126, -126, -126, -126, -126, -126, -126, -126, -126, -126, -126, -126, -126, -126, -126, -126, -126, -126, -126, -126, -126, -126, -126, -126, -126, -126, -126, -126, -126, 157, -126, -126, -126, -126, -126, -126, -126, -126, -126, -126, -126, -126, -126, -126, -126, -126, -126, -126, -126, -126, -126 }, { 23, 123, 127, -127, 124, 127, 123, 128, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, -127, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123 }, { 23, 123, 123, -128, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, -128, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123, 123 }, { 23, 129, 129, -129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, -129, -129 }, { 23, 129, 130, -130, 129, 130, 129, 131, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, -130, -130 }, { 23, 129, 129, -131, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, 129, -131, -131 }, { 23, -132, 132, -132, 92, 132, -132, 133, -132, -132, -132, -132, -132, -132, -132, -132, -132, -132, -132, -132, -132, -132, -132, -132, -132, -132, -132, -132, -132, -132, -132, -132, -132, -132, -132, -132, -132, -132, -132, -132, -132, -132, -132, -132, -132, -132, -132, -132, -132, -132, -132, -132, -132, -132, -132, -132 }, { 23, -133, -133, -133, -133, -133, -133, -133, -133, -133, -133, -133, -133, -133, -133, -133, -133, -133, -133, -133, -133, -133, -133, -133, -133, -133, -133, -133, -133, -133, -133, -133, -133, -133, -133, -133, -133, -133, -133, -133, -133, -133, -133, -133, -133, -133, -133, -133, -133, -133, -133, -133, -133, -133, -133, -133 }, { 23, 134, 134, 135, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 136, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134 }, { 23, -135, -135, -135, -135, -135, -135, -135, -135, -135, -135, -135, -135, -135, -135, -135, -135, -135, -135, -135, -135, -135, -135, -135, -135, -135, -135, -135, -135, -135, -135, -135, -135, -135, -135, -135, -135, -135, -135, -135, -135, -135, -135, -135, -135, -135, -135, -135, -135, -135, -135, -135, -135, -135, -135, -135 }, { 23, 134, 134, 139, 134, 140, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 136, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134 }, { 23, 134, 137, 135, 137, 137, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 136, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134 }, { 23, 134, 134, 135, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 136, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134 }, { 23, -139, -139, -139, -139, -139, -139, -139, -139, -139, -139, -139, -139, -139, -139, -139, -139, -139, -139, -139, -139, -139, -139, -139, -139, -139, -139, -139, -139, -139, -139, -139, -139, -139, -139, -139, -139, -139, -139, -139, -139, -139, -139, -139, -139, -139, -139, -139, -139, -139, -139, -139, -139, -139, -139, -139 }, { 23, 134, 134, 139, 134, 140, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 136, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134, 134 }, { 23, 141, 141, 142, 141, 141, 141, 141, 141, 141, 141, 143, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141 }, { 23, -142, -142, -142, -142, -142, -142, -142, -142, -142, -142, -142, -142, -142, -142, -142, -142, -142, -142, -142, -142, -142, -142, -142, -142, -142, -142, -142, -142, -142, -142, -142, -142, -142, -142, -142, -142, -142, -142, -142, -142, -142, -142, -142, -142, -142, -142, -142, -142, -142, -142, -142, -142, -142, -142, -142 }, { 23, 145, 145, 146, 145, 145, 145, 145, 145, 145, 145, 143, 145, 145, 147, 145, 145, 145, 145, 145, 145, 145, 145, 145, 145, 145, 145, 145, 145, 145, 145, 145, 145, 145, 145, 145, 145, 145, 145, 145, 145, 145, 145, 145, 145, 145, 145, 145, 145, 145, 145, 145, 145, 145, 145, 145 }, { 23, 141, 144, 142, 144, 144, 141, 141, 141, 141, 141, 143, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141, 141 }, { 23, -145, -145, -145, -145, -145, -145, -145, -145, -145, -145, -145, -145, -145, -145, -145, -145, -145, -145, -145, -145, -145, -145, -145, -145, -145, -145, -145, -145, -145, -145, -145, -145, -145, -145, -145, -145, -145, -145, -145, -145, -145, -145, -145, -145, -145, -145, -145, -145, -145, -145, -145, -145, -145, -145, -145 }, { 23, -146, -146, -146, -146, -146, -146, -146, -146, -146, -146, -146, -146, -146, -146, -146, -146, -146, -146, -146, -146, -146, -146, -146, -146, -146, -146, -146, -146, -146, -146, -146, -146, -146, -146, -146, -146, -146, -146, -146, -146, -146, -146, -146, -146, -146, -146, -146, -146, -146, -146, -146, -146, -146, -146, -146 }, { 23, -147, -147, -147, -147, -147, -147, -147, -147, -147, -147, -147, -147, -147, -147, -147, -147, -147, -147, -147, -147, -147, -147, -147, -147, -147, -147, -147, -147, -147, -147, -147, -147, -147, -147, -147, -147, -147, -147, -147, -147, -147, -147, -147, -147, -147, -147, -147, -147, -147, -147, -147, -147, -147, -147, -147 }, { 23, 145, 145, 146, 145, 145, 145, 145, 145, 145, 145, 143, 145, 145, 147, 145, 145, 145, 145, 145, 145, 145, 145, 145, 145, 145, 145, 145, 145, 145, 145, 145, 145, 145, 145, 145, 145, 145, 145, 145, 145, 145, 145, 145, 145, 145, 145, 145, 145, 145, 145, 145, 145, 145, 145, 145 }, { 23, -149, -149, -149, -149, -149, -149, -149, -149, -149, -149, -149, -149, -149, -149, -149, -149, -149, -149, -149, -149, -149, -149, -149, -149, -149, -149, -149, -149, -149, -149, -149, -149, -149, -149, -149, -149, -149, -149, -149, -149, -149, -149, -149, -149, -149, -149, -149, -149, -149, -149, -149, -149, -149, -149, -149 }, { 23, -150, -150, -150, -150, -150, -150, -150, -150, -150, -150, -150, -150, -150, -150, 150, 150, 150, -150, -150, 150, 150, 150, 150, 150, 150, -150, -150, -150, -150, -150, -150, -150, -150, -150, -150, -150, -150, 150, 150, 150, 150, 150, -150, -150, -150, -150, -150, -150, -150, -150, -150, -150, -150, -150, -150 }, { 23, -151, -151, -151, -151, -151, -151, -151, -151, -151, -151, -151, -151, -151, -151, 99, 99, 99, -151, -151, 99, 99, 99, 99, 99, 99, 99, 99, 158, 99, 99, 99, 99, 99, 99, 99, -151, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, -151, -151 }, { 23, -152, -152, -152, -152, -152, -152, -152, -152, -152, -152, -152, -152, -152, -152, 99, 99, 99, -152, -152, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, -152, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, -152, -152 }, { 23, -153, -153, -153, -153, -153, -153, -153, -153, -153, -153, -153, -153, -153, -153, 99, 99, 99, -153, -153, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, -153, 99, 159, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, -153, -153 }, { 23, -154, -154, -154, -154, -154, -154, -154, -154, -154, -154, -154, -154, -154, -154, 99, 99, 99, -154, -154, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, -154, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 160, 99, 99, -154, -154 }, { 23, -155, -155, -155, -155, -155, -155, -155, -155, -155, -155, -155, -155, -155, -155, 99, 99, 99, -155, -155, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, -155, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 161, 99, 99, 99, 99, 99, -155, -155 }, { 23, -156, -156, -156, -156, -156, -156, -156, -156, -156, -156, -156, -156, -156, -156, 99, 99, 99, -156, -156, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, -156, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 162, 99, 99, 99, 99, -156, -156 }, { 23, -157, -157, -157, -157, -157, -157, -157, -157, -157, -157, -157, -157, -157, -157, -157, -157, -157, -157, -157, -157, -157, 163, -157, -157, -157, -157, -157, -157, -157, -157, -157, -157, -157, -157, -157, -157, -157, -157, -157, -157, -157, -157, -157, -157, -157, -157, -157, -157, -157, -157, -157, -157, -157, -157, -157 }, { 23, -158, -158, -158, -158, -158, -158, -158, -158, -158, -158, -158, -158, -158, -158, 99, 99, 99, -158, -158, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 164, 99, 99, 99, 99, -158, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, -158, -158 }, { 23, -159, -159, -159, -159, -159, -159, -159, -159, -159, -159, -159, -159, -159, -159, 99, 99, 99, -159, -159, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, -159, 99, 99, 99, 99, 99, 99, 99, 99, 165, 99, 99, 99, 99, 99, 99, 99, 99, -159, -159 }, { 23, -160, -160, -160, -160, -160, -160, -160, -160, -160, -160, -160, -160, -160, -160, 99, 99, 99, -160, -160, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, -160, 99, 99, 99, 99, 99, 99, 99, 166, 99, 99, 99, 99, 99, 99, 99, 99, 99, -160, -160 }, { 23, -161, -161, -161, -161, -161, -161, -161, -161, -161, -161, -161, -161, -161, -161, 99, 99, 99, -161, -161, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, -161, 99, 167, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, -161, -161 }, { 23, -162, -162, -162, -162, -162, -162, -162, -162, -162, -162, -162, -162, -162, -162, 99, 99, 99, -162, -162, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, -162, 99, 168, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, -162, -162 }, { 23, -163, -163, -163, -163, -163, -163, -163, -163, -163, -163, -163, -163, -163, -163, -163, -163, -163, -163, -163, -163, -163, -163, -163, -163, -163, -163, 169, -163, -163, -163, -163, -163, -163, -163, -163, -163, -163, -163, -163, -163, -163, -163, -163, -163, -163, -163, -163, -163, -163, -163, -163, -163, -163, -163, -163 }, { 23, -164, -164, -164, -164, -164, -164, -164, -164, -164, -164, -164, -164, -164, -164, 99, 99, 99, -164, -164, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, -164, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, -164, -164 }, { 23, -165, -165, -165, -165, 170, -165, -165, -165, -165, -165, -165, -165, -165, -165, 99, 99, 99, 171, -165, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, -165, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, -165, -165 }, { 23, -166, -166, -166, -166, -166, -166, -166, -166, -166, -166, -166, -166, -166, -166, 99, 99, 99, -166, -166, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, -166, 99, 99, 99, 99, 99, 99, 99, 99, 99, 172, 99, 99, 99, 99, 99, 99, 99, -166, -166 }, { 23, -167, -167, -167, -167, -167, -167, -167, -167, -167, -167, -167, -167, -167, -167, 99, 99, 99, -167, -167, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, -167, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 173, 99, 99, -167, -167 }, { 23, -168, -168, -168, -168, -168, -168, -168, -168, -168, -168, -168, -168, -168, -168, 99, 99, 99, -168, -168, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, -168, 99, 99, 99, 174, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, -168, -168 }, { 23, -169, -169, -169, -169, -169, -169, -169, -169, -169, -169, -169, -169, -169, -169, -169, -169, -169, -169, -169, -169, -169, -169, -169, -169, -169, -169, -169, -169, -169, -169, -169, -169, -169, -169, -169, -169, 175, -169, -169, -169, -169, -169, -169, -169, -169, -169, -169, -169, -169, -169, -169, -169, -169, -169, -169 }, { 23, -170, -170, -170, -170, 170, -170, -170, -170, -170, -170, -170, -170, -170, -170, -170, -170, -170, 171, -170, -170, -170, -170, -170, -170, -170, -170, -170, -170, -170, -170, -170, -170, -170, -170, -170, -170, -170, -170, -170, -170, -170, -170, -170, -170, -170, -170, -170, -170, -170, -170, -170, -170, -170, -170, -170 }, { 23, -171, -171, -171, -171, -171, -171, -171, -171, -171, -171, -171, -171, -171, -171, -171, -171, -171, -171, -171, -171, -171, -171, -171, -171, -171, -171, -171, -171, -171, -171, -171, -171, -171, -171, -171, -171, -171, -171, -171, -171, -171, -171, -171, -171, -171, -171, -171, -171, -171, -171, -171, -171, -171, -171, -171 }, { 23, -172, -172, -172, -172, -172, -172, -172, -172, -172, -172, -172, -172, -172, -172, 99, 99, 99, -172, -172, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, -172, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 176, 99, -172, -172 }, { 23, -173, -173, -173, -173, -173, -173, -173, -173, -173, -173, -173, -173, -173, -173, 99, 99, 99, -173, -173, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, -173, 99, 99, 99, 177, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, -173, -173 }, { 23, -174, -174, -174, -174, -174, -174, -174, -174, -174, -174, -174, -174, -174, -174, 99, 99, 99, -174, -174, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, -174, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 178, 99, 99, -174, -174 }, { 23, -175, -175, -175, -175, -175, -175, -175, -175, -175, -175, -175, -175, -175, -175, -175, -175, -175, -175, -175, -175, 179, -175, -175, -175, -175, -175, -175, -175, -175, -175, -175, -175, -175, -175, -175, -175, -175, -175, -175, -175, -175, -175, -175, -175, -175, -175, -175, -175, -175, -175, -175, -175, -175, -175, -175 }, { 23, -176, -176, -176, -176, -176, -176, -176, -176, -176, -176, -176, -176, -176, -176, 99, 99, 99, -176, -176, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, -176, 99, 99, 99, 99, 99, 180, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, -176, -176 }, { 23, -177, -177, -177, -177, -177, -177, -177, -177, -177, -177, -177, -177, -177, -177, 99, 99, 99, -177, -177, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, -177, 99, 99, 99, 99, 99, 99, 181, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, -177, -177 }, { 23, -178, -178, -178, -178, 182, -178, -178, -178, -178, -178, -178, -178, -178, -178, 99, 99, 99, -178, -178, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, -178, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, -178, -178 }, { 23, -179, -179, -179, -179, -179, -179, -179, -179, -179, -179, -179, -179, -179, -179, -179, -179, -179, -179, -179, -179, -179, -179, -179, -179, -179, -179, -179, -179, -179, -179, -179, -179, -179, -179, 183, -179, -179, -179, -179, -179, -179, -179, -179, -179, -179, -179, -179, -179, -179, -179, -179, -179, -179, -179, -179 }, { 23, -180, -180, -180, -180, 184, -180, -180, -180, -180, -180, -180, -180, -180, -180, 99, 99, 99, 185, -180, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, -180, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, -180, -180 }, { 23, -181, -181, -181, -181, 186, -181, -181, -181, -181, -181, -181, -181, -181, -181, 99, 99, 99, -181, -181, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, -181, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, 99, -181, -181 }, { 23, -182, -182, -182, -182, 182, -182, -182, -182, -182, -182, -182, -182, -182, -182, -182, -182, -182, -182, -182, -182, -182, -182, -182, -182, -182, -182, -182, -182, -182, -182, -182, -182, -182, -182, -182, -182, -182, -182, -182, -182, -182, -182, -182, -182, -182, -182, -182, -182, -182, -182, -182, -182, -182, -182, -182 }, { 23, -183, -183, -183, -183, -183, -183, -183, -183, -183, -183, -183, -183, -183, -183, -183, -183, -183, -183, -183, -183, -183, -183, -183, -183, -183, -183, -183, -183, -183, -183, -183, -183, -183, 187, -183, -183, -183, -183, -183, -183, -183, -183, -183, -183, -183, -183, -183, -183, -183, -183, -183, -183, -183, -183, -183 }, { 23, -184, -184, -184, -184, 184, -184, -184, -184, -184, -184, -184, -184, -184, -184, -184, -184, -184, 185, -184, -184, -184, -184, -184, -184, -184, -184, -184, -184, -184, -184, -184, -184, -184, -184, -184, -184, -184, -184, -184, -184, -184, -184, -184, -184, -184, -184, -184, -184, -184, -184, -184, -184, -184, -184, -184 }, { 23, -185, -185, -185, -185, -185, -185, -185, -185, -185, -185, -185, -185, -185, -185, -185, -185, -185, -185, -185, -185, -185, -185, -185, -185, -185, -185, -185, -185, -185, -185, -185, -185, -185, -185, -185, -185, -185, -185, -185, -185, -185, -185, -185, -185, -185, -185, -185, -185, -185, -185, -185, -185, -185, -185, -185 }, { 23, -186, -186, -186, -186, 186, -186, -186, -186, -186, -186, -186, -186, -186, -186, -186, -186, -186, -186, -186, -186, -186, -186, -186, -186, -186, -186, -186, -186, -186, -186, -186, -186, -186, -186, -186, -186, -186, -186, -186, -186, -186, -186, -186, -186, -186, -186, -186, -186, -186, -186, -186, -186, -186, -186, -186 }, { 23, -187, -187, -187, -187, -187, -187, -187, -187, -187, -187, -187, -187, -187, -187, -187, -187, -187, -187, -187, -187, -187, -187, -187, 188, -187, -187, -187, -187, -187, -187, -187, -187, -187, -187, -187, -187, -187, -187, -187, -187, -187, -187, -187, -187, -187, -187, -187, -187, -187, -187, -187, -187, -187, -187, -187 }, { 23, -188, -188, -188, -188, -188, -188, -188, -188, -188, -188, -188, -188, -188, -188, -188, -188, -188, -188, -188, -188, -188, 189, -188, -188, -188, -188, -188, -188, -188, -188, -188, -188, -188, -188, -188, -188, -188, -188, -188, -188, -188, -188, -188, -188, -188, -188, -188, -188, -188, -188, -188, -188, -188, -188, -188 }, { 23, -189, -189, -189, -189, -189, -189, -189, -189, -189, -189, -189, -189, -189, -189, -189, -189, -189, -189, -189, -189, -189, -189, -189, -189, -189, -189, -189, -189, -189, -189, -189, 190, -189, -189, -189, -189, -189, -189, -189, -189, -189, -189, -189, -189, -189, -189, -189, -189, -189, -189, -189, -189, -189, -189, -189 }, { 23, -190, -190, -190, -190, -190, -190, -190, -190, -190, -190, -190, -190, -190, -190, -190, -190, -190, -190, -190, -190, -190, -190, 191, -190, -190, -190, -190, -190, -190, -190, -190, -190, -190, -190, -190, -190, -190, -190, -190, -190, -190, -190, -190, -190, -190, -190, -190, -190, -190, -190, -190, -190, -190, -190, -190 }, { 23, -191, -191, -191, -191, -191, -191, -191, -191, -191, -191, -191, -191, -191, -191, -191, -191, -191, -191, -191, -191, -191, -191, -191, 192, -191, -191, -191, -191, -191, -191, -191, -191, -191, -191, -191, -191, -191, -191, -191, -191, -191, -191, -191, -191, -191, -191, -191, -191, -191, -191, -191, -191, -191, -191, -191 }, { 23, -192, -192, -192, -192, -192, -192, -192, -192, -192, -192, -192, -192, -192, -192, -192, -192, -192, -192, -192, -192, -192, -192, -192, -192, -192, -192, -192, -192, -192, -192, -192, -192, 193, -192, -192, -192, -192, -192, -192, -192, -192, -192, -192, -192, -192, -192, -192, -192, -192, -192, -192, -192, -192, -192, -192 }, { 23, -193, -193, -193, -193, -193, -193, -193, -193, -193, -193, -193, -193, -193, -193, -193, -193, -193, -193, -193, -193, -193, -193, -193, -193, -193, -193, -193, -193, -193, -193, -193, -193, -193, -193, -193, -193, -193, -193, -193, -193, -193, -193, -193, -193, -193, -193, -193, -193, -193, -193, -193, -193, -193, -193, -193 }, } ; static yy_state_type yy_get_previous_state (void ); static yy_state_type yy_try_NUL_trans (yy_state_type current_state ); static int yy_get_next_buffer (void ); static void yy_fatal_error (yyconst char msg[] ); /* Done after the current pattern has been matched and before the * corresponding action - sets up yytext. */ #define YY_DO_BEFORE_ACTION \ (yytext_ptr) = yy_bp; \ yyleng = (size_t) (yy_cp - yy_bp); \ (yy_hold_char) = *yy_cp; \ *yy_cp = '\0'; \ (yy_c_buf_p) = yy_cp; #define YY_NUM_RULES 46 #define YY_END_OF_BUFFER 47 /* This struct is not used in this scanner, but its presence is necessary. */ struct yy_trans_info { flex_int32_t yy_verify; flex_int32_t yy_nxt; }; static yyconst flex_int16_t yy_accept[194] = { 0, 0, 0, 0, 0, 30, 30, 12, 12, 36, 36, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 47, 46, 32, 2, 1, 32, 32, 10, 8, 31, 31, 31, 7, 30, 30, 29, 17, 16, 24, 25, 26, 10, 8, 23, 31, 31, 31, 31, 27, 28, 30, 18, 12, 2, 12, 12, 12, 12, 2, 12, 36, 35, 17, 16, 33, 34, 36, 18, 2, 13, 46, 14, 15, 2, 18, 46, 2, 1, 46, 46, 46, 2, 1, 46, 46, 40, 38, 40, 37, 2, 1, 6, 3, 10, 0, 8, 31, 31, 31, 7, 30, 30, 24, 25, 26, 23, 27, 28, 24, 25, 26, 10, 8, 23, 31, 31, 31, 31, 30, 18, 12, 2, 3, 0, 2, 12, 36, 36, 18, 2, 18, 0, 42, 0, 2, 3, 41, 0, 0, 43, 0, 2, 44, 43, 45, 3, 39, 9, 31, 5, 31, 31, 31, 31, 0, 31, 31, 31, 31, 31, 0, 4, 31, 31, 31, 31, 0, 0, 21, 31, 31, 31, 0, 31, 31, 31, 0, 31, 31, 19, 0, 0, 22, 20, 0, 0, 0, 0, 0, 0, 11 } ; static yyconst flex_int32_t yy_ec[256] = { 0, 1, 1, 1, 1, 1, 1, 1, 1, 2, 3, 1, 4, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 5, 1, 6, 7, 1, 1, 1, 8, 9, 10, 11, 1, 12, 1, 13, 14, 15, 16, 16, 16, 16, 16, 16, 16, 17, 17, 1, 18, 1, 19, 1, 1, 1, 20, 21, 22, 23, 24, 25, 26, 27, 28, 29, 29, 29, 30, 31, 32, 29, 29, 29, 33, 34, 29, 29, 29, 29, 35, 29, 1, 36, 1, 1, 37, 1, 38, 39, 40, 41, 42, 25, 29, 43, 44, 29, 45, 29, 29, 46, 47, 48, 29, 49, 50, 51, 52, 29, 29, 53, 29, 29, 54, 1, 55, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1 } ; static yy_state_type yy_last_accepting_state; static char *yy_last_accepting_cpos; extern int yy_flex_debug; int yy_flex_debug = 0; /* The intent behind this definition is that it'll catch * any uses of REJECT which flex missed. */ #define REJECT reject_used_but_not_detected #define yymore() yymore_used_but_not_detected #define YY_MORE_ADJ 0 #define YY_RESTORE_YY_MORE_OFFSET char *yytext; #line 1 "genbc-scan.l" /******************************** -*- C -*- **************************** * * GNU Smalltalk genbc tool - lexical analyzer * ***********************************************************************/ /*********************************************************************** * * Copyright 2003, 2006 Free Software Foundation, Inc. * Written by Paolo Bonzini. * * This file is part of GNU Smalltalk. * * GNU Smalltalk is free software; you can redistribute it and/or modify it * under the terms of the GNU General Public License as published by the Free * Software Foundation; either version 2, or (at your option) any later * version. * * Linking GNU Smalltalk statically or dynamically with other modules is * making a combined work based on GNU Smalltalk. Thus, the terms and * conditions of the GNU General Public License cover the whole * combination. * * In addition, as a special exception, the Free Software Foundation * give you permission to combine GNU Smalltalk with free software * programs or libraries that are released under the GNU LGPL and with * independent programs running under the GNU Smalltalk virtual machine. * * You may copy and distribute such a system following the terms of the * GNU GPL for GNU Smalltalk and the licenses of the other code * concerned, provided that you include the source code of that other * code when and as the GNU GPL requires distribution of source code. * * Note that people who make modified versions of GNU Smalltalk are not * obligated to grant this special exception for their modified * versions; it is their choice whether to do so. The GNU General * Public License gives permission to release a modified version without * this exception; this exception also makes it possible to release a * modified version which carries forward this exception. * * GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or * FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for * more details. * * You should have received a copy of the GNU General Public License along with * GNU Smalltalk; see the file COPYING. If not, write to the Free Software * Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * ***********************************************************************/ #line 68 "genbc-scan.l" #include "genbc.h" static Filament *literal_fil; static int from = 0, depth = 0; #if !defined YY_FLEX_SUBMINOR_VERSION || YY_FLEX_SUBMINOR_VERSION < 31 int yylineno = 1; #endif static void init_scanner (FILE **pfp, YY_BUFFER_STATE *pbuf, const char *file, int start); #line 2394 "genbc-scan.c" #define INITIAL 0 #define DECL 1 #define DECL_C_CODE 2 #define IMPL 3 #define IMPL_C_CODE 4 #define IMPL_END 5 #define IMPL_MATCH 6 #define CPP_CODE 7 #define C_COMMENT 8 #define C_STRING 9 #define C_CHAR 10 #ifndef YY_NO_UNISTD_H /* Special case for "unistd.h", since it is non-ANSI. We include it way * down here because we want the user's section 1 to have been scanned first. * The user has a chance to override it with an option. */ #include #endif #ifndef YY_EXTRA_TYPE #define YY_EXTRA_TYPE void * #endif static int yy_init_globals (void ); /* Accessor methods to globals. These are made visible to non-reentrant scanners for convenience. */ int yylex_destroy (void ); int yyget_debug (void ); void yyset_debug (int debug_flag ); YY_EXTRA_TYPE yyget_extra (void ); void yyset_extra (YY_EXTRA_TYPE user_defined ); FILE *yyget_in (void ); void yyset_in (FILE * in_str ); FILE *yyget_out (void ); void yyset_out (FILE * out_str ); int yyget_leng (void ); char *yyget_text (void ); int yyget_lineno (void ); void yyset_lineno (int line_number ); /* Macros after this point can all be overridden by user definitions in * section 1. */ #ifndef YY_SKIP_YYWRAP #ifdef __cplusplus extern "C" int yywrap (void ); #else extern int yywrap (void ); #endif #endif #ifndef yytext_ptr static void yy_flex_strncpy (char *,yyconst char *,int ); #endif #ifdef YY_NEED_STRLEN static int yy_flex_strlen (yyconst char * ); #endif #ifndef YY_NO_INPUT #ifdef __cplusplus static int yyinput (void ); #else static int input (void ); #endif #endif /* Amount of stuff to slurp up with each read. */ #ifndef YY_READ_BUF_SIZE #ifdef __ia64__ /* On IA-64, the buffer size is 16k, not 8k */ #define YY_READ_BUF_SIZE 16384 #else #define YY_READ_BUF_SIZE 8192 #endif /* __ia64__ */ #endif /* Copy whatever the last rule matched to the standard output. */ #ifndef ECHO /* This used to be an fputs(), but since the string might contain NUL's, * we now use fwrite(). */ #define ECHO do { if (fwrite( yytext, yyleng, 1, yyout )) {} } while (0) #endif /* Gets input and stuffs it into "buf". number of characters read, or YY_NULL, * is returned in "result". */ #ifndef YY_INPUT #define YY_INPUT(buf,result,max_size) \ if ( YY_CURRENT_BUFFER_LVALUE->yy_is_interactive ) \ { \ int c = '*'; \ size_t n; \ for ( n = 0; n < max_size && \ (c = getc( yyin )) != EOF && c != '\n'; ++n ) \ buf[n] = (char) c; \ if ( c == '\n' ) \ buf[n++] = (char) c; \ if ( c == EOF && ferror( yyin ) ) \ YY_FATAL_ERROR( "input in flex scanner failed" ); \ result = n; \ } \ else \ { \ errno=0; \ while ( (result = fread(buf, 1, max_size, yyin))==0 && ferror(yyin)) \ { \ if( errno != EINTR) \ { \ YY_FATAL_ERROR( "input in flex scanner failed" ); \ break; \ } \ errno=0; \ clearerr(yyin); \ } \ }\ \ #endif /* No semi-colon after return; correct usage is to write "yyterminate();" - * we don't want an extra ';' after the "return" because that will cause * some compilers to complain about unreachable statements. */ #ifndef yyterminate #define yyterminate() return YY_NULL #endif /* Number of entries by which start-condition stack grows. */ #ifndef YY_START_STACK_INCR #define YY_START_STACK_INCR 25 #endif /* Report a fatal error. */ #ifndef YY_FATAL_ERROR #define YY_FATAL_ERROR(msg) yy_fatal_error( msg ) #endif /* end tables serialization structures and prototypes */ /* Default declaration of generated scanner - a define so the user can * easily add parameters. */ #ifndef YY_DECL #define YY_DECL_IS_OURS 1 extern int yylex (void); #define YY_DECL int yylex (void) #endif /* !YY_DECL */ /* Code executed at the beginning of each rule, after yytext and yyleng * have been set up. */ #ifndef YY_USER_ACTION #define YY_USER_ACTION #endif /* Code executed at the end of each rule. */ #ifndef YY_BREAK #define YY_BREAK break; #endif #define YY_RULE_SETUP \ if ( yyleng > 0 ) \ YY_CURRENT_BUFFER_LVALUE->yy_at_bol = \ (yytext[yyleng - 1] == '\n'); \ YY_USER_ACTION /** The main scanner function which does all the work. */ YY_DECL { register yy_state_type yy_current_state; register char *yy_cp, *yy_bp; register int yy_act; #line 81 "genbc-scan.l" #line 2595 "genbc-scan.c" if ( !(yy_init) ) { (yy_init) = 1; #ifdef YY_USER_INIT YY_USER_INIT; #endif if ( ! (yy_start) ) (yy_start) = 1; /* first start state */ if ( ! yyin ) yyin = stdin; if ( ! yyout ) yyout = stdout; if ( ! YY_CURRENT_BUFFER ) { yyensure_buffer_stack (); YY_CURRENT_BUFFER_LVALUE = yy_create_buffer(yyin,YY_BUF_SIZE ); } yy_load_buffer_state( ); } while ( 1 ) /* loops until end-of-file is reached */ { yy_cp = (yy_c_buf_p); /* Support of yytext. */ *yy_cp = (yy_hold_char); /* yy_bp points to the position in yy_ch_buf of the start of * the current run. */ yy_bp = yy_cp; yy_current_state = (yy_start); yy_current_state += YY_AT_BOL(); yy_match: while ( (yy_current_state = yy_nxt[yy_current_state][ yy_ec[YY_SC_TO_UI(*yy_cp)] ]) > 0 ) { if ( yy_accept[yy_current_state] ) { (yy_last_accepting_state) = yy_current_state; (yy_last_accepting_cpos) = yy_cp; } ++yy_cp; } yy_current_state = -yy_current_state; yy_find_action: yy_act = yy_accept[yy_current_state]; YY_DO_BEFORE_ACTION; do_action: /* This label is used only to access EOF actions. */ switch ( yy_act ) { /* beginning of action switch */ case 0: /* must back up */ /* undo the effects of YY_DO_BEFORE_ACTION */ *yy_cp = (yy_hold_char); yy_cp = (yy_last_accepting_cpos) + 1; yy_current_state = (yy_last_accepting_state); goto yy_find_action; /* All states know how to count lines and to skip comments. */ case 1: /* rule 1 can match eol */ YY_RULE_SETUP #line 85 "genbc-scan.l" { yylineno += yyleng; } YY_BREAK case 2: YY_RULE_SETUP #line 89 "genbc-scan.l" { } YY_BREAK case 3: YY_RULE_SETUP #line 92 "genbc-scan.l" { from = YY_START; BEGIN (C_COMMENT); } YY_BREAK case 4: YY_RULE_SETUP #line 99 "genbc-scan.l" { return (DECL_BEGIN); } YY_BREAK case 5: YY_RULE_SETUP #line 103 "genbc-scan.l" { return (DECL_END); } YY_BREAK case 6: YY_RULE_SETUP #line 107 "genbc-scan.l" { return (DECL_DOTS); } YY_BREAK case 7: /* rule 7 can match eol */ YY_RULE_SETUP #line 111 "genbc-scan.l" { depth = 1; yylineno += yyleng - 1; yylval.ctext = "{\n "; BEGIN (DECL_C_CODE); return '{'; } YY_BREAK case 8: #line 122 "genbc-scan.l" case 9: #line 123 "genbc-scan.l" case 10: YY_RULE_SETUP #line 123 "genbc-scan.l" { yylval.num = strtol(yytext, NULL, 0); return (NUMBER); } YY_BREAK /* Looking for matchers is a no-op until we find MATCH_BYTECODES. */ case 11: YY_RULE_SETUP #line 131 "genbc-scan.l" { BEGIN (IMPL_MATCH); return (MATCH_BYTECODES); } YY_BREAK case 12: YY_RULE_SETUP #line 136 "genbc-scan.l" { } YY_BREAK case 13: YY_RULE_SETUP #line 141 "genbc-scan.l" { BEGIN (IMPL); return *yytext; } YY_BREAK /* Parsing a matcher only requires us to find the closing parentheses and the opening brace: the rest is included in the catch-all `.' rule. */ case 14: YY_RULE_SETUP #line 150 "genbc-scan.l" { BEGIN (IMPL_END); return *yytext; } YY_BREAK case 15: YY_RULE_SETUP #line 155 "genbc-scan.l" { depth = 1; literal_fil = filnew (NULL, 0); filccat (literal_fil, *yytext); BEGIN (IMPL_C_CODE); } YY_BREAK /* Learn how to skip strings and preprocessor code. */ case 16: YY_RULE_SETUP #line 165 "genbc-scan.l" { from = YY_START; BEGIN (C_CHAR); if (literal_fil) filccat (literal_fil, *yytext); else { yylval.text = yytext; return (EXPR); } } YY_BREAK case 17: YY_RULE_SETUP #line 178 "genbc-scan.l" { from = YY_START; BEGIN (C_STRING); if (literal_fil) filccat (literal_fil, *yytext); else { yylval.text = yytext; return (EXPR); } } YY_BREAK case 18: YY_RULE_SETUP #line 191 "genbc-scan.l" { if (YY_START != IMPL) yyerror ("preprocessor directives inside matchers are invalid"); } YY_BREAK case 19: YY_RULE_SETUP #line 198 "genbc-scan.l" { return (DECL_EXTRACT); } YY_BREAK case 20: YY_RULE_SETUP #line 202 "genbc-scan.l" { return (DECL_DISPATCH); } YY_BREAK case 21: YY_RULE_SETUP #line 206 "genbc-scan.l" { return (DECL_BREAK); } YY_BREAK case 22: YY_RULE_SETUP #line 210 "genbc-scan.l" { return (DECL_CONTINUE); } YY_BREAK case 23: YY_RULE_SETUP #line 214 "genbc-scan.l" { yylval.ctext = yytext; return '='; } YY_BREAK case 24: YY_RULE_SETUP #line 219 "genbc-scan.l" { yylval.ctext = yytext; return '('; } YY_BREAK case 25: YY_RULE_SETUP #line 224 "genbc-scan.l" { yylval.ctext = yytext; return ')'; } YY_BREAK case 26: YY_RULE_SETUP #line 229 "genbc-scan.l" { yylval.ctext = yytext; return ','; } YY_BREAK case 27: YY_RULE_SETUP #line 234 "genbc-scan.l" { depth++; yylval.ctext = yytext; return EXPR; } YY_BREAK case 28: YY_RULE_SETUP #line 240 "genbc-scan.l" { if (!--depth) { BEGIN (DECL); return '}'; } yylval.ctext = yytext; return EXPR; } YY_BREAK case 29: /* rule 29 can match eol */ YY_RULE_SETUP #line 251 "genbc-scan.l" { yylineno++; yylval.ctext = " \\\n "; return (EXPR); } YY_BREAK case 30: YY_RULE_SETUP #line 257 "genbc-scan.l" { yylval.ctext = yytext; return (EXPR); } YY_BREAK case 31: YY_RULE_SETUP #line 264 "genbc-scan.l" { yylval.text = strdup (yytext); return (ID); } YY_BREAK /* Put this rule last so that it does not override the others. */ case 32: YY_RULE_SETUP #line 270 "genbc-scan.l" { return *yytext; } YY_BREAK /* Learn how to balance braces and escape new-lines. */ case 33: YY_RULE_SETUP #line 277 "genbc-scan.l" { depth++; filccat (literal_fil, '{'); } YY_BREAK case 34: YY_RULE_SETUP #line 282 "genbc-scan.l" { filccat (literal_fil, '}'); if (!--depth) { yylval.text = fildelete (literal_fil); literal_fil = NULL; BEGIN (IMPL_MATCH); return EXPR; } } YY_BREAK case 35: /* rule 35 can match eol */ YY_RULE_SETUP #line 293 "genbc-scan.l" { yylineno++; filcat (literal_fil, " \\\n"); } YY_BREAK case 36: YY_RULE_SETUP #line 298 "genbc-scan.l" { filcat (literal_fil, yytext); } YY_BREAK /* Characters and strings have different terminations... */ case 37: YY_RULE_SETUP #line 305 "genbc-scan.l" { BEGIN (from); if (literal_fil) filccat (literal_fil, *yytext); else { yylval.text = yytext; return (EXPR); } } YY_BREAK case 38: YY_RULE_SETUP #line 319 "genbc-scan.l" { BEGIN (from); if (literal_fil) filccat (literal_fil, *yytext); else { yylval.text = yytext; return (EXPR); } } YY_BREAK /* ... but otherwise they're the same. */ case 39: YY_RULE_SETUP #line 334 "genbc-scan.l" { yylineno += (yytext[1] == '\n'); if (literal_fil) filcat (literal_fil, yytext); else { yylval.text = yytext; return (EXPR); } } YY_BREAK case 40: YY_RULE_SETUP #line 345 "genbc-scan.l" { yylineno += (yytext[0] == '\n'); if (literal_fil) filccat (literal_fil, *yytext); else { yylval.text = yytext; return (EXPR); } } YY_BREAK /* Preprocessor directives are just skipped. */ case 41: *yy_cp = (yy_hold_char); /* undo effects of setting up yytext */ (yy_c_buf_p) = yy_cp -= 1; YY_DO_BEFORE_ACTION; /* set up yytext again */ YY_RULE_SETUP #line 359 "genbc-scan.l" { } YY_BREAK case 42: *yy_cp = (yy_hold_char); /* undo effects of setting up yytext */ (yy_c_buf_p) = yy_cp -= 1; YY_DO_BEFORE_ACTION; /* set up yytext again */ YY_RULE_SETUP #line 362 "genbc-scan.l" { } YY_BREAK /* And so are comments. */ case 43: /* rule 43 can match eol */ YY_RULE_SETUP #line 368 "genbc-scan.l" { yylineno++; } YY_BREAK case 44: /* rule 44 can match eol */ YY_RULE_SETUP #line 372 "genbc-scan.l" { } YY_BREAK case 45: YY_RULE_SETUP #line 375 "genbc-scan.l" { BEGIN (from); } YY_BREAK case 46: YY_RULE_SETUP #line 380 "genbc-scan.l" ECHO; YY_BREAK #line 3111 "genbc-scan.c" case YY_STATE_EOF(INITIAL): case YY_STATE_EOF(DECL): case YY_STATE_EOF(DECL_C_CODE): case YY_STATE_EOF(IMPL): case YY_STATE_EOF(IMPL_C_CODE): case YY_STATE_EOF(IMPL_END): case YY_STATE_EOF(IMPL_MATCH): case YY_STATE_EOF(CPP_CODE): case YY_STATE_EOF(C_COMMENT): case YY_STATE_EOF(C_STRING): case YY_STATE_EOF(C_CHAR): yyterminate(); case YY_END_OF_BUFFER: { /* Amount of text matched not including the EOB char. */ int yy_amount_of_matched_text = (int) (yy_cp - (yytext_ptr)) - 1; /* Undo the effects of YY_DO_BEFORE_ACTION. */ *yy_cp = (yy_hold_char); YY_RESTORE_YY_MORE_OFFSET if ( YY_CURRENT_BUFFER_LVALUE->yy_buffer_status == YY_BUFFER_NEW ) { /* We're scanning a new file or input source. It's * possible that this happened because the user * just pointed yyin at a new source and called * yylex(). If so, then we have to assure * consistency between YY_CURRENT_BUFFER and our * globals. Here is the right place to do so, because * this is the first action (other than possibly a * back-up) that will match for the new input source. */ (yy_n_chars) = YY_CURRENT_BUFFER_LVALUE->yy_n_chars; YY_CURRENT_BUFFER_LVALUE->yy_input_file = yyin; YY_CURRENT_BUFFER_LVALUE->yy_buffer_status = YY_BUFFER_NORMAL; } /* Note that here we test for yy_c_buf_p "<=" to the position * of the first EOB in the buffer, since yy_c_buf_p will * already have been incremented past the NUL character * (since all states make transitions on EOB to the * end-of-buffer state). Contrast this with the test * in input(). */ if ( (yy_c_buf_p) <= &YY_CURRENT_BUFFER_LVALUE->yy_ch_buf[(yy_n_chars)] ) { /* This was really a NUL. */ yy_state_type yy_next_state; (yy_c_buf_p) = (yytext_ptr) + yy_amount_of_matched_text; yy_current_state = yy_get_previous_state( ); /* Okay, we're now positioned to make the NUL * transition. We couldn't have * yy_get_previous_state() go ahead and do it * for us because it doesn't know how to deal * with the possibility of jamming (and we don't * want to build jamming into it because then it * will run more slowly). */ yy_next_state = yy_try_NUL_trans( yy_current_state ); yy_bp = (yytext_ptr) + YY_MORE_ADJ; if ( yy_next_state ) { /* Consume the NUL. */ yy_cp = ++(yy_c_buf_p); yy_current_state = yy_next_state; goto yy_match; } else { yy_cp = (yy_c_buf_p); goto yy_find_action; } } else switch ( yy_get_next_buffer( ) ) { case EOB_ACT_END_OF_FILE: { (yy_did_buffer_switch_on_eof) = 0; if ( yywrap( ) ) { /* Note: because we've taken care in * yy_get_next_buffer() to have set up * yytext, we can now set up * yy_c_buf_p so that if some total * hoser (like flex itself) wants to * call the scanner after we return the * YY_NULL, it'll still work - another * YY_NULL will get returned. */ (yy_c_buf_p) = (yytext_ptr) + YY_MORE_ADJ; yy_act = YY_STATE_EOF(YY_START); goto do_action; } else { if ( ! (yy_did_buffer_switch_on_eof) ) YY_NEW_FILE; } break; } case EOB_ACT_CONTINUE_SCAN: (yy_c_buf_p) = (yytext_ptr) + yy_amount_of_matched_text; yy_current_state = yy_get_previous_state( ); yy_cp = (yy_c_buf_p); yy_bp = (yytext_ptr) + YY_MORE_ADJ; goto yy_match; case EOB_ACT_LAST_MATCH: (yy_c_buf_p) = &YY_CURRENT_BUFFER_LVALUE->yy_ch_buf[(yy_n_chars)]; yy_current_state = yy_get_previous_state( ); yy_cp = (yy_c_buf_p); yy_bp = (yytext_ptr) + YY_MORE_ADJ; goto yy_find_action; } break; } default: YY_FATAL_ERROR( "fatal flex scanner internal error--no action found" ); } /* end of action switch */ } /* end of scanning one token */ } /* end of yylex */ /* yy_get_next_buffer - try to read in a new buffer * * Returns a code representing an action: * EOB_ACT_LAST_MATCH - * EOB_ACT_CONTINUE_SCAN - continue scanning from current position * EOB_ACT_END_OF_FILE - end of file */ static int yy_get_next_buffer (void) { register char *dest = YY_CURRENT_BUFFER_LVALUE->yy_ch_buf; register char *source = (yytext_ptr); register int number_to_move, i; int ret_val; if ( (yy_c_buf_p) > &YY_CURRENT_BUFFER_LVALUE->yy_ch_buf[(yy_n_chars) + 1] ) YY_FATAL_ERROR( "fatal flex scanner internal error--end of buffer missed" ); if ( YY_CURRENT_BUFFER_LVALUE->yy_fill_buffer == 0 ) { /* Don't try to fill the buffer, so this is an EOF. */ if ( (yy_c_buf_p) - (yytext_ptr) - YY_MORE_ADJ == 1 ) { /* We matched a single character, the EOB, so * treat this as a final EOF. */ return EOB_ACT_END_OF_FILE; } else { /* We matched some text prior to the EOB, first * process it. */ return EOB_ACT_LAST_MATCH; } } /* Try to read more data. */ /* First move last chars to start of buffer. */ number_to_move = (int) ((yy_c_buf_p) - (yytext_ptr)) - 1; for ( i = 0; i < number_to_move; ++i ) *(dest++) = *(source++); if ( YY_CURRENT_BUFFER_LVALUE->yy_buffer_status == YY_BUFFER_EOF_PENDING ) /* don't do the read, it's not guaranteed to return an EOF, * just force an EOF */ YY_CURRENT_BUFFER_LVALUE->yy_n_chars = (yy_n_chars) = 0; else { int num_to_read = YY_CURRENT_BUFFER_LVALUE->yy_buf_size - number_to_move - 1; while ( num_to_read <= 0 ) { /* Not enough room in the buffer - grow it. */ /* just a shorter name for the current buffer */ YY_BUFFER_STATE b = YY_CURRENT_BUFFER; int yy_c_buf_p_offset = (int) ((yy_c_buf_p) - b->yy_ch_buf); if ( b->yy_is_our_buffer ) { int new_size = b->yy_buf_size * 2; if ( new_size <= 0 ) b->yy_buf_size += b->yy_buf_size / 8; else b->yy_buf_size *= 2; b->yy_ch_buf = (char *) /* Include room in for 2 EOB chars. */ yyrealloc((void *) b->yy_ch_buf,b->yy_buf_size + 2 ); } else /* Can't grow it, we don't own it. */ b->yy_ch_buf = 0; if ( ! b->yy_ch_buf ) YY_FATAL_ERROR( "fatal error - scanner input buffer overflow" ); (yy_c_buf_p) = &b->yy_ch_buf[yy_c_buf_p_offset]; num_to_read = YY_CURRENT_BUFFER_LVALUE->yy_buf_size - number_to_move - 1; } if ( num_to_read > YY_READ_BUF_SIZE ) num_to_read = YY_READ_BUF_SIZE; /* Read in more data. */ YY_INPUT( (&YY_CURRENT_BUFFER_LVALUE->yy_ch_buf[number_to_move]), (yy_n_chars), (size_t) num_to_read ); YY_CURRENT_BUFFER_LVALUE->yy_n_chars = (yy_n_chars); } if ( (yy_n_chars) == 0 ) { if ( number_to_move == YY_MORE_ADJ ) { ret_val = EOB_ACT_END_OF_FILE; yyrestart(yyin ); } else { ret_val = EOB_ACT_LAST_MATCH; YY_CURRENT_BUFFER_LVALUE->yy_buffer_status = YY_BUFFER_EOF_PENDING; } } else ret_val = EOB_ACT_CONTINUE_SCAN; if ((yy_size_t) ((yy_n_chars) + number_to_move) > YY_CURRENT_BUFFER_LVALUE->yy_buf_size) { /* Extend the array by 50%, plus the number we really need. */ yy_size_t new_size = (yy_n_chars) + number_to_move + ((yy_n_chars) >> 1); YY_CURRENT_BUFFER_LVALUE->yy_ch_buf = (char *) yyrealloc((void *) YY_CURRENT_BUFFER_LVALUE->yy_ch_buf,new_size ); if ( ! YY_CURRENT_BUFFER_LVALUE->yy_ch_buf ) YY_FATAL_ERROR( "out of dynamic memory in yy_get_next_buffer()" ); } (yy_n_chars) += number_to_move; YY_CURRENT_BUFFER_LVALUE->yy_ch_buf[(yy_n_chars)] = YY_END_OF_BUFFER_CHAR; YY_CURRENT_BUFFER_LVALUE->yy_ch_buf[(yy_n_chars) + 1] = YY_END_OF_BUFFER_CHAR; (yytext_ptr) = &YY_CURRENT_BUFFER_LVALUE->yy_ch_buf[0]; return ret_val; } /* yy_get_previous_state - get the state just before the EOB char was reached */ static yy_state_type yy_get_previous_state (void) { register yy_state_type yy_current_state; register char *yy_cp; yy_current_state = (yy_start); yy_current_state += YY_AT_BOL(); for ( yy_cp = (yytext_ptr) + YY_MORE_ADJ; yy_cp < (yy_c_buf_p); ++yy_cp ) { yy_current_state = yy_nxt[yy_current_state][(*yy_cp ? yy_ec[YY_SC_TO_UI(*yy_cp)] : 1)]; if ( yy_accept[yy_current_state] ) { (yy_last_accepting_state) = yy_current_state; (yy_last_accepting_cpos) = yy_cp; } } return yy_current_state; } /* yy_try_NUL_trans - try to make a transition on the NUL character * * synopsis * next_state = yy_try_NUL_trans( current_state ); */ static yy_state_type yy_try_NUL_trans (yy_state_type yy_current_state ) { register int yy_is_jam; register char *yy_cp = (yy_c_buf_p); yy_current_state = yy_nxt[yy_current_state][1]; yy_is_jam = (yy_current_state <= 0); if ( ! yy_is_jam ) { if ( yy_accept[yy_current_state] ) { (yy_last_accepting_state) = yy_current_state; (yy_last_accepting_cpos) = yy_cp; } } return yy_is_jam ? 0 : yy_current_state; } #ifndef YY_NO_INPUT #ifdef __cplusplus static int yyinput (void) #else static int input (void) #endif { int c; *(yy_c_buf_p) = (yy_hold_char); if ( *(yy_c_buf_p) == YY_END_OF_BUFFER_CHAR ) { /* yy_c_buf_p now points to the character we want to return. * If this occurs *before* the EOB characters, then it's a * valid NUL; if not, then we've hit the end of the buffer. */ if ( (yy_c_buf_p) < &YY_CURRENT_BUFFER_LVALUE->yy_ch_buf[(yy_n_chars)] ) /* This was really a NUL. */ *(yy_c_buf_p) = '\0'; else { /* need more input */ int offset = (yy_c_buf_p) - (yytext_ptr); ++(yy_c_buf_p); switch ( yy_get_next_buffer( ) ) { case EOB_ACT_LAST_MATCH: /* This happens because yy_g_n_b() * sees that we've accumulated a * token and flags that we need to * try matching the token before * proceeding. But for input(), * there's no matching to consider. * So convert the EOB_ACT_LAST_MATCH * to EOB_ACT_END_OF_FILE. */ /* Reset buffer status. */ yyrestart(yyin ); /*FALLTHROUGH*/ case EOB_ACT_END_OF_FILE: { if ( yywrap( ) ) return EOF; if ( ! (yy_did_buffer_switch_on_eof) ) YY_NEW_FILE; #ifdef __cplusplus return yyinput(); #else return input(); #endif } case EOB_ACT_CONTINUE_SCAN: (yy_c_buf_p) = (yytext_ptr) + offset; break; } } } c = *(unsigned char *) (yy_c_buf_p); /* cast for 8-bit char's */ *(yy_c_buf_p) = '\0'; /* preserve yytext */ (yy_hold_char) = *++(yy_c_buf_p); YY_CURRENT_BUFFER_LVALUE->yy_at_bol = (c == '\n'); return c; } #endif /* ifndef YY_NO_INPUT */ /** Immediately switch to a different input stream. * @param input_file A readable stream. * * @note This function does not reset the start condition to @c INITIAL . */ void yyrestart (FILE * input_file ) { if ( ! YY_CURRENT_BUFFER ){ yyensure_buffer_stack (); YY_CURRENT_BUFFER_LVALUE = yy_create_buffer(yyin,YY_BUF_SIZE ); } yy_init_buffer(YY_CURRENT_BUFFER,input_file ); yy_load_buffer_state( ); } /** Switch to a different input buffer. * @param new_buffer The new input buffer. * */ void yy_switch_to_buffer (YY_BUFFER_STATE new_buffer ) { /* TODO. We should be able to replace this entire function body * with * yypop_buffer_state(); * yypush_buffer_state(new_buffer); */ yyensure_buffer_stack (); if ( YY_CURRENT_BUFFER == new_buffer ) return; if ( YY_CURRENT_BUFFER ) { /* Flush out information for old buffer. */ *(yy_c_buf_p) = (yy_hold_char); YY_CURRENT_BUFFER_LVALUE->yy_buf_pos = (yy_c_buf_p); YY_CURRENT_BUFFER_LVALUE->yy_n_chars = (yy_n_chars); } YY_CURRENT_BUFFER_LVALUE = new_buffer; yy_load_buffer_state( ); /* We don't actually know whether we did this switch during * EOF (yywrap()) processing, but the only time this flag * is looked at is after yywrap() is called, so it's safe * to go ahead and always set it. */ (yy_did_buffer_switch_on_eof) = 1; } static void yy_load_buffer_state (void) { (yy_n_chars) = YY_CURRENT_BUFFER_LVALUE->yy_n_chars; (yytext_ptr) = (yy_c_buf_p) = YY_CURRENT_BUFFER_LVALUE->yy_buf_pos; yyin = YY_CURRENT_BUFFER_LVALUE->yy_input_file; (yy_hold_char) = *(yy_c_buf_p); } /** Allocate and initialize an input buffer state. * @param file A readable stream. * @param size The character buffer size in bytes. When in doubt, use @c YY_BUF_SIZE. * * @return the allocated buffer state. */ YY_BUFFER_STATE yy_create_buffer (FILE * file, int size ) { YY_BUFFER_STATE b; b = (YY_BUFFER_STATE) yyalloc(sizeof( struct yy_buffer_state ) ); if ( ! b ) YY_FATAL_ERROR( "out of dynamic memory in yy_create_buffer()" ); b->yy_buf_size = size; /* yy_ch_buf has to be 2 characters longer than the size given because * we need to put in 2 end-of-buffer characters. */ b->yy_ch_buf = (char *) yyalloc(b->yy_buf_size + 2 ); if ( ! b->yy_ch_buf ) YY_FATAL_ERROR( "out of dynamic memory in yy_create_buffer()" ); b->yy_is_our_buffer = 1; yy_init_buffer(b,file ); return b; } /** Destroy the buffer. * @param b a buffer created with yy_create_buffer() * */ void yy_delete_buffer (YY_BUFFER_STATE b ) { if ( ! b ) return; if ( b == YY_CURRENT_BUFFER ) /* Not sure if we should pop here. */ YY_CURRENT_BUFFER_LVALUE = (YY_BUFFER_STATE) 0; if ( b->yy_is_our_buffer ) yyfree((void *) b->yy_ch_buf ); yyfree((void *) b ); } /* Initializes or reinitializes a buffer. * This function is sometimes called more than once on the same buffer, * such as during a yyrestart() or at EOF. */ static void yy_init_buffer (YY_BUFFER_STATE b, FILE * file ) { int oerrno = errno; yy_flush_buffer(b ); b->yy_input_file = file; b->yy_fill_buffer = 1; /* If b is the current buffer, then yy_init_buffer was _probably_ * called from yyrestart() or through yy_get_next_buffer. * In that case, we don't want to reset the lineno or column. */ if (b != YY_CURRENT_BUFFER){ b->yy_bs_lineno = 1; b->yy_bs_column = 0; } b->yy_is_interactive = 0; errno = oerrno; } /** Discard all buffered characters. On the next scan, YY_INPUT will be called. * @param b the buffer state to be flushed, usually @c YY_CURRENT_BUFFER. * */ void yy_flush_buffer (YY_BUFFER_STATE b ) { if ( ! b ) return; b->yy_n_chars = 0; /* We always need two end-of-buffer characters. The first causes * a transition to the end-of-buffer state. The second causes * a jam in that state. */ b->yy_ch_buf[0] = YY_END_OF_BUFFER_CHAR; b->yy_ch_buf[1] = YY_END_OF_BUFFER_CHAR; b->yy_buf_pos = &b->yy_ch_buf[0]; b->yy_at_bol = 1; b->yy_buffer_status = YY_BUFFER_NEW; if ( b == YY_CURRENT_BUFFER ) yy_load_buffer_state( ); } /** Pushes the new state onto the stack. The new state becomes * the current state. This function will allocate the stack * if necessary. * @param new_buffer The new state. * */ void yypush_buffer_state (YY_BUFFER_STATE new_buffer ) { if (new_buffer == NULL) return; yyensure_buffer_stack(); /* This block is copied from yy_switch_to_buffer. */ if ( YY_CURRENT_BUFFER ) { /* Flush out information for old buffer. */ *(yy_c_buf_p) = (yy_hold_char); YY_CURRENT_BUFFER_LVALUE->yy_buf_pos = (yy_c_buf_p); YY_CURRENT_BUFFER_LVALUE->yy_n_chars = (yy_n_chars); } /* Only push if top exists. Otherwise, replace top. */ if (YY_CURRENT_BUFFER) (yy_buffer_stack_top)++; YY_CURRENT_BUFFER_LVALUE = new_buffer; /* copied from yy_switch_to_buffer. */ yy_load_buffer_state( ); (yy_did_buffer_switch_on_eof) = 1; } /** Removes and deletes the top of the stack, if present. * The next element becomes the new top. * */ void yypop_buffer_state (void) { if (!YY_CURRENT_BUFFER) return; yy_delete_buffer(YY_CURRENT_BUFFER ); YY_CURRENT_BUFFER_LVALUE = NULL; if ((yy_buffer_stack_top) > 0) --(yy_buffer_stack_top); if (YY_CURRENT_BUFFER) { yy_load_buffer_state( ); (yy_did_buffer_switch_on_eof) = 1; } } /* Allocates the stack if it does not exist. * Guarantees space for at least one push. */ static void yyensure_buffer_stack (void) { int num_to_alloc; if (!(yy_buffer_stack)) { /* First allocation is just for 2 elements, since we don't know if this * scanner will even need a stack. We use 2 instead of 1 to avoid an * immediate realloc on the next call. */ num_to_alloc = 1; (yy_buffer_stack) = (struct yy_buffer_state**)yyalloc (num_to_alloc * sizeof(struct yy_buffer_state*) ); if ( ! (yy_buffer_stack) ) YY_FATAL_ERROR( "out of dynamic memory in yyensure_buffer_stack()" ); memset((yy_buffer_stack), 0, num_to_alloc * sizeof(struct yy_buffer_state*)); (yy_buffer_stack_max) = num_to_alloc; (yy_buffer_stack_top) = 0; return; } if ((yy_buffer_stack_top) >= ((yy_buffer_stack_max)) - 1){ /* Increase the buffer to prepare for a possible push. */ int grow_size = 8 /* arbitrary grow size */; num_to_alloc = (yy_buffer_stack_max) + grow_size; (yy_buffer_stack) = (struct yy_buffer_state**)yyrealloc ((yy_buffer_stack), num_to_alloc * sizeof(struct yy_buffer_state*) ); if ( ! (yy_buffer_stack) ) YY_FATAL_ERROR( "out of dynamic memory in yyensure_buffer_stack()" ); /* zero only the new slots.*/ memset((yy_buffer_stack) + (yy_buffer_stack_max), 0, grow_size * sizeof(struct yy_buffer_state*)); (yy_buffer_stack_max) = num_to_alloc; } } /** Setup the input buffer state to scan directly from a user-specified character buffer. * @param base the character buffer * @param size the size in bytes of the character buffer * * @return the newly allocated buffer state object. */ YY_BUFFER_STATE yy_scan_buffer (char * base, yy_size_t size ) { YY_BUFFER_STATE b; if ( size < 2 || base[size-2] != YY_END_OF_BUFFER_CHAR || base[size-1] != YY_END_OF_BUFFER_CHAR ) /* They forgot to leave room for the EOB's. */ return 0; b = (YY_BUFFER_STATE) yyalloc(sizeof( struct yy_buffer_state ) ); if ( ! b ) YY_FATAL_ERROR( "out of dynamic memory in yy_scan_buffer()" ); b->yy_buf_size = size - 2; /* "- 2" to take care of EOB's */ b->yy_buf_pos = b->yy_ch_buf = base; b->yy_is_our_buffer = 0; b->yy_input_file = 0; b->yy_n_chars = b->yy_buf_size; b->yy_is_interactive = 0; b->yy_at_bol = 1; b->yy_fill_buffer = 0; b->yy_buffer_status = YY_BUFFER_NEW; yy_switch_to_buffer(b ); return b; } /** Setup the input buffer state to scan a string. The next call to yylex() will * scan from a @e copy of @a str. * @param yystr a NUL-terminated string to scan * * @return the newly allocated buffer state object. * @note If you want to scan bytes that may contain NUL values, then use * yy_scan_bytes() instead. */ YY_BUFFER_STATE yy_scan_string (yyconst char * yystr ) { return yy_scan_bytes(yystr,strlen(yystr) ); } /** Setup the input buffer state to scan the given bytes. The next call to yylex() will * scan from a @e copy of @a bytes. * @param yybytes the byte buffer to scan * @param _yybytes_len the number of bytes in the buffer pointed to by @a bytes. * * @return the newly allocated buffer state object. */ YY_BUFFER_STATE yy_scan_bytes (yyconst char * yybytes, int _yybytes_len ) { YY_BUFFER_STATE b; char *buf; yy_size_t n; int i; /* Get memory for full buffer, including space for trailing EOB's. */ n = _yybytes_len + 2; buf = (char *) yyalloc(n ); if ( ! buf ) YY_FATAL_ERROR( "out of dynamic memory in yy_scan_bytes()" ); for ( i = 0; i < _yybytes_len; ++i ) buf[i] = yybytes[i]; buf[_yybytes_len] = buf[_yybytes_len+1] = YY_END_OF_BUFFER_CHAR; b = yy_scan_buffer(buf,n ); if ( ! b ) YY_FATAL_ERROR( "bad buffer in yy_scan_bytes()" ); /* It's okay to grow etc. this buffer, and we should throw it * away when we're done. */ b->yy_is_our_buffer = 1; return b; } #ifndef YY_EXIT_FAILURE #define YY_EXIT_FAILURE 2 #endif static void yy_fatal_error (yyconst char* msg ) { (void) fprintf( stderr, "%s\n", msg ); exit( YY_EXIT_FAILURE ); } /* Redefine yyless() so it works in section 3 code. */ #undef yyless #define yyless(n) \ do \ { \ /* Undo effects of setting up yytext. */ \ int yyless_macro_arg = (n); \ YY_LESS_LINENO(yyless_macro_arg);\ yytext[yyleng] = (yy_hold_char); \ (yy_c_buf_p) = yytext + yyless_macro_arg; \ (yy_hold_char) = *(yy_c_buf_p); \ *(yy_c_buf_p) = '\0'; \ yyleng = yyless_macro_arg; \ } \ while ( 0 ) /* Accessor methods (get/set functions) to struct members. */ /** Get the current line number. * */ int yyget_lineno (void) { return yylineno; } /** Get the input stream. * */ FILE *yyget_in (void) { return yyin; } /** Get the output stream. * */ FILE *yyget_out (void) { return yyout; } /** Get the length of the current token. * */ int yyget_leng (void) { return yyleng; } /** Get the current token. * */ char *yyget_text (void) { return yytext; } /** Set the current line number. * @param line_number * */ void yyset_lineno (int line_number ) { yylineno = line_number; } /** Set the input stream. This does not discard the current * input buffer. * @param in_str A readable stream. * * @see yy_switch_to_buffer */ void yyset_in (FILE * in_str ) { yyin = in_str ; } void yyset_out (FILE * out_str ) { yyout = out_str ; } int yyget_debug (void) { return yy_flex_debug; } void yyset_debug (int bdebug ) { yy_flex_debug = bdebug ; } static int yy_init_globals (void) { /* Initialization is the same as for the non-reentrant scanner. * This function is called from yylex_destroy(), so don't allocate here. */ (yy_buffer_stack) = 0; (yy_buffer_stack_top) = 0; (yy_buffer_stack_max) = 0; (yy_c_buf_p) = (char *) 0; (yy_init) = 0; (yy_start) = 0; /* Defined in main.c */ #ifdef YY_STDINIT yyin = stdin; yyout = stdout; #else yyin = (FILE *) 0; yyout = (FILE *) 0; #endif /* For future reference: Set errno on error, since we are called by * yylex_init() */ return 0; } /* yylex_destroy is for both reentrant and non-reentrant scanners. */ int yylex_destroy (void) { /* Pop the buffer stack, destroying each element. */ while(YY_CURRENT_BUFFER){ yy_delete_buffer(YY_CURRENT_BUFFER ); YY_CURRENT_BUFFER_LVALUE = NULL; yypop_buffer_state(); } /* Destroy the stack itself. */ yyfree((yy_buffer_stack) ); (yy_buffer_stack) = NULL; /* Reset the globals. This is important in a non-reentrant scanner so the next time * yylex() is called, initialization will occur. */ yy_init_globals( ); return 0; } /* * Internal utility routines. */ #ifndef yytext_ptr static void yy_flex_strncpy (char* s1, yyconst char * s2, int n ) { register int i; for ( i = 0; i < n; ++i ) s1[i] = s2[i]; } #endif #ifdef YY_NEED_STRLEN static int yy_flex_strlen (yyconst char * s ) { register int n; for ( n = 0; s[n]; ++n ) ; return n; } #endif void *yyalloc (yy_size_t size ) { return (void *) malloc( size ); } void *yyrealloc (void * ptr, yy_size_t size ) { /* The cast to (char *) in the following accommodates both * implementations that use char* generic pointers, and those * that use void* generic pointers. It works with the latter * because both ANSI C and C++ allow castless assignment from * any pointer type to void*, and deal with argument conversions * as though doing an assignment. */ return (void *) realloc( (char *) ptr, size ); } void yyfree (void * ptr ) { free( (char *) ptr ); /* see yyrealloc() for (char *) cast */ } #define YYTABLES_NAME "yytables" #line 380 "genbc-scan.l" void init_scanner (FILE **pfp, YY_BUFFER_STATE *pbuf, const char *file, int start) { if (!strcmp (file, "-")) { *pfp = stdin; current_file = "stdin"; } else { *pfp = fopen (file, "r"); current_file = file; } *pbuf = yy_create_buffer (*pfp, YY_BUF_SIZE); yy_switch_to_buffer (*pbuf); yylineno = 1; BEGIN (start); } void parse_declarations (const char *file) { YY_BUFFER_STATE buf; FILE *fp; init_scanner (&fp, &buf, file, DECL); decl_yyparse (); yy_delete_buffer (buf); fclose (fp); } void parse_implementation (const char *file) { YY_BUFFER_STATE buf; FILE *fp; init_scanner (&fp, &buf, file, IMPL); impl_yyparse (); yy_delete_buffer (buf); fclose (fp); } smalltalk-3.2.5/libgst/real.c0000644000175000017500000002746412123404352013012 00000000000000/******************************** -*- C -*- **************************** * * Simple floating-point data type * * ***********************************************************************/ /*********************************************************************** * * Copyright 2009 Free Software Foundation, Inc. * Written by Paolo Bonzini. * * This file is part of GNU Smalltalk. * * GNU Smalltalk is free software; you can redistribute it and/or modify it * under the terms of the GNU General Public License as published by the Free * Software Foundation; either version 2, or (at your option) any later * version. * * Linking GNU Smalltalk statically or dynamically with other modules is * making a combined work based on GNU Smalltalk. Thus, the terms and * conditions of the GNU General Public License cover the whole * combination. * * In addition, as a special exception, the Free Software Foundation * give you permission to combine GNU Smalltalk with free software * programs or libraries that are released under the GNU LGPL and with * independent programs running under the GNU Smalltalk virtual machine. * * You may copy and distribute such a system following the terms of the * GNU GPL for GNU Smalltalk and the licenses of the other code * concerned, provided that you include the source code of that other * code when and as the GNU GPL requires distribution of source code. * * Note that people who make modified versions of GNU Smalltalk are not * obligated to grant this special exception for their modified * versions; it is their choice whether to do so. The GNU General * Public License gives permission to release a modified version without * this exception; this exception also makes it possible to release a * modified version which carries forward this exception. * * GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or * FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for * more details. * * You should have received a copy of the GNU General Public License along with * GNU Smalltalk; see the file COPYING. If not, write to the Free Software * Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * ***********************************************************************/ #include "gstpriv.h" #define SIG_ELEM_BITS (CHAR_BIT * sizeof (((struct real *)0)->sig[0])) #define NUM_SIG_BITS (SIGSZ * SIG_ELEM_BITS) #define SIG_MASK ((1 << SIG_ELEM_BITS) - 1) #define SIG_MSB (1 << (SIG_ELEM_BITS - 1)) /* Shift the significant of IN by DELTA bits and store the result into OUT. OUT and IN can overlap. */ static int rshift_sig (struct real *out, struct real *in, int delta); /* Normalize the significant of IN so that the most significant bit is 1, and store the result into OUT. OUT and IN can overlap. */ static void normalize (struct real *out, struct real *in); /* Denormalize IN to increase its exponent to EXP and store the result into OUT. OUT and IN can overlap. Return false if OUT would be zero, in which case its contents are undefined. */ static int adjust_exp (struct real *out, struct real *in, int exp); /* Sum the significands of R and S. Return the carry. */ static int add_significands (struct real *r, struct real *s); /* Compare the significands of R and S and return the result like strcmp. */ static int cmp_significands (struct real *r, struct real *s); /* Subtract the significands of R and S. */ static void sub_significands (struct real *r, struct real *s); /* Sum S into R. */ static void do_add (struct real *r, struct real *s); /* Multiply S into R. LSB is the least significant nonzero byte of the significand of S, and is used to cut the iteration. */ static void do_mul (struct real *r, struct real *s, int lsb); /* Divide R by S and store the result into S. OUT can overlap either R or S, but R must not be the same as S. R is destroyed */ static void do_div (struct real *out, struct real *r, struct real *s); /* These routines are not optimized at all. Maybe I should have bit the bullet and required MPFR after all... */ static int rshift_sig (struct real *out, struct real *in, int delta) { int i, nonzero = 0; int rshift = delta & (SIG_ELEM_BITS - 1); int lshift = SIG_ELEM_BITS - rshift; delta /= SIG_ELEM_BITS; if (rshift) { for (i = 0; i + delta < SIGSZ - 1; i++) { out->sig[i] = ((in->sig[i + delta + 1] << lshift) | (in->sig[i + delta] >> rshift)); nonzero |= out->sig[i]; } out->sig[i] = in->sig[i + delta] >> rshift; nonzero |= out->sig[i]; i++; } else { for (i = 0; i + delta < SIGSZ; i++) { out->sig[i] = in->sig[i + delta]; nonzero |= out->sig[i]; } } while (i < SIGSZ) out->sig[i++] = 0; return nonzero; } static void normalize (struct real *out, struct real *in) { int i, msb, delta, rshift, lshift; int out_exp; out_exp = in->exp; delta = 0; for (i = SIGSZ; --i >= 0 && in->sig[i] == 0; ) { delta++; out_exp -= SIG_ELEM_BITS; } if (i < 0) { memset (out, 0, sizeof (struct real)); return; } /* TODO: convert this to clz. */ msb = in->sig[i]; lshift = 15; if (msb & 0xFF00) lshift -= 8; else msb <<= 8; if (msb & 0xF000) lshift -= 4; else msb <<= 4; if (msb & 0xC000) lshift -= 2; else msb <<= 2; if (msb & 0x8000) lshift -= 1; rshift = 16 - lshift; out->exp = out_exp - lshift; out->sign = in->sign; if (lshift) { for (i = SIGSZ; --i - delta >= 1; ) out->sig[i] = ((in->sig[i - delta] << lshift) | (in->sig[i - delta - 1] >> rshift)); out->sig[i] = in->sig[0] << lshift; } else { for (i = SIGSZ; --i - delta >= 0; ) out->sig[i] = in->sig[i - delta]; } while (--i >= 0) out->sig[i] = 0; } /* Adjust IN to have exponent EXP by shifting its significand right. Put the result into OUT. The shift can be done in place. */ static int adjust_exp (struct real *out, struct real *in, int exp) { int in_exp; in_exp = in->exp; assert (exp > in_exp); if (exp == in_exp) return true; if (exp - in_exp >= NUM_SIG_BITS) return false; out->exp = exp; return rshift_sig (out, in, exp - in_exp); } void _gst_real_from_int (struct real *out, int s) { memset (out, 0, sizeof (struct real)); if (s < 0) { out->sign = -1; s = -s; } else out->sign = 1; /* TODO: convert this to clz. */ if (s & 0xFF00) out->exp += 8; else s <<= 8; if (s & 0xF000) out->exp += 4; else s <<= 4; if (s & 0xC000) out->exp += 2; else s <<= 2; if (s & 0x8000) out->exp += 1; else s <<= 1; out->sig[SIGSZ - 1] = s; } static int add_significands (struct real *r, struct real *s) { int i, carry = 0; for (i = 0; i < SIGSZ; i++) { int result = r->sig[i] + s->sig[i] + carry; carry = result >> SIG_ELEM_BITS; r->sig[i] = result; } return carry; } static int cmp_significands (struct real *r, struct real *s) { int i; for (i = SIGSZ; --i >= 0; ) if (r->sig[i] != s->sig[i]) return (r->sig[i] - s->sig[i]); return 0; } static void sub_significands (struct real *r, struct real *s) { int i, carry = 0; for (i = 0; i < SIGSZ; i++) { int result = r->sig[i] - s->sig[i] + carry; carry = result >> SIG_ELEM_BITS; r->sig[i] = result; } } static void do_add (struct real *r, struct real *s) { struct real tmp; if (r->exp < s->exp) { if (!adjust_exp (r, r, s->exp)) { /* Underflow, R+S = S. */ *r = *s; return; } } else if (r->exp > s->exp) { /* We cannot modify S in place, use a temporary. */ if (!adjust_exp (&tmp, s, r->exp)) return; s = &tmp; } if (add_significands (r, s)) { /* Lose one bit of precision to fit the carry. */ rshift_sig (r, r, 1); r->exp++; r->sig[SIGSZ - 1] |= SIG_MSB; } } void _gst_real_add (struct real *r, struct real *s) { if (!s->sign) return; if (!r->sign) memcpy (r, s, sizeof (struct real)); else if (s->sign == r->sign) return do_add (r, s); else abort (); } void _gst_real_add_int (struct real *r, int s) { struct real s_real; if (!s) return; _gst_real_from_int (&s_real, s); if (!r->sign) memcpy (r, &s_real, sizeof (struct real)); else if (s_real.sign == r->sign) return do_add (r, &s_real); else abort (); } static void do_mul (struct real *r, struct real *s, int lsb) { struct real rr; unsigned short mask; int n; r->exp += s->exp; r->sign *= s->sign; rr = *r; mask = SIG_MSB; n = SIGSZ - 1; assert (s->sig[n] & mask); while (n > lsb || (s->sig[n] & (mask - 1))) { if (!(mask >>= 1)) { mask = SIG_MSB; n--; } /* Dividing rr by 2 matches the weight s->sig[n] & mask. Exit early in case of underflow. */ if (!rshift_sig (&rr, &rr, 1)) break; if (s->sig[n] & mask) { if (add_significands (r, &rr)) { /* Lose one bit of precision to fit the carry. */ rshift_sig (r, r, 1); r->sig[SIGSZ - 1] |= SIG_MSB; r->exp++; if (!rshift_sig (&rr, &rr, 1)) break; rr.exp++; } } } } void _gst_real_mul (struct real *r, struct real *s) { int i; struct real tmp; if (r->sign == 0) return; if (r == s) { tmp = *s; s = &tmp; } if (s->sign == 0) memset (r, 0, sizeof (struct real)); for (i = 0; i < SIGSZ && s->sig[i] == 0; ) i++; do_mul (r, s, i); } void _gst_real_mul_int (struct real *r, int s) { struct real s_real; if (s == 0) memset (r, 0, sizeof (struct real)); if (r->sign == 0) return; _gst_real_from_int (&s_real, s); do_mul (r, &s_real, SIGSZ - 1); } void _gst_real_powi (struct real *out, struct real *r, int s) { int k; struct real tmp; if (out == r) { tmp = *r; r = &tmp; } assert (s > 0); _gst_real_from_int (out, 1); if (!s) return; for (k = 1;; k <<= 1) { if (s & k) { _gst_real_mul (out, r); s ^= k; if (!s) break; } _gst_real_mul (r, r); } } static void do_div (struct real *out, struct real *r, struct real *s) { struct real v; int msb, i; int place = SIGSZ-1; int bit = SIG_MSB; memset (&v, 0, sizeof (struct real)); v.sign = r->sign * s->sign; v.exp = r->exp - s->exp; msb = 0; goto start; do { /* Get the MSB of U and shift it left by one. */ msb = r->sig[SIGSZ-1] & SIG_MSB; for (i = SIGSZ; --i >= 1; ) r->sig[i] = (r->sig[i] << 1) | (r->sig[i - 1] >> 15); r->sig[0] <<= 1; start: if (msb || cmp_significands (r, s) >= 0) { sub_significands (r, s); v.sig[place] |= bit; } } while ((bit >>= 1) || (bit = SIG_MSB, --place >= 0)); normalize (out, &v); } void _gst_real_div (struct real *out, struct real *r, struct real *s) { assert (s->sign); if (!r->sign) { memset (out, 0, sizeof (struct real)); return; } if (r == s) { memset (out, 0, sizeof (struct real)); out->sign = 1; out->sig[SIGSZ-1] = SIG_MSB; return; } if (out == r) do_div (out, out, s); else { /* do_div would destroy R, save it. */ struct real u = *r; do_div (out, &u, s); } } void _gst_real_inv (struct real *out, struct real *s) { struct real u; assert (s->sign); memset (&u, 0, sizeof (struct real)); u.sign = 1; u.sig[SIGSZ-1] = SIG_MSB; do_div (out, &u, s); } long double _gst_real_get_ld (struct real *r) { long double result = 0.0; int i; for (i = SIGSZ; --i >= 0; ) { result *= SIG_MASK + 1; result += r->sig[i]; } result = ldexpl (result, r->exp - NUM_SIG_BITS + 1); return r->sign == -1 ? -result : result; } smalltalk-3.2.5/libgst/genbc-impl.y0000644000175000017500000000727712123404352014132 00000000000000/******************************** -*- C -*- **************************** * * GNU Smalltalk genbc tool - parser for implementations * ***********************************************************************/ /*********************************************************************** * * Copyright 2003, 2006 Free Software Foundation, Inc. * Written by Paolo Bonzini. * * This file is part of GNU Smalltalk. * * GNU Smalltalk is free software; you can redistribute it and/or modify it * under the terms of the GNU General Public License as published by the Free * Software Foundation; either version 2, or (at your option) any later * version. * * Linking GNU Smalltalk statically or dynamically with other modules is * making a combined work based on GNU Smalltalk. Thus, the terms and * conditions of the GNU General Public License cover the whole * combination. * * In addition, as a special exception, the Free Software Foundation * give you permission to combine GNU Smalltalk with free software * programs or libraries that are released under the GNU LGPL and with * independent programs running under the GNU Smalltalk virtual machine. * * You may copy and distribute such a system following the terms of the * GNU GPL for GNU Smalltalk and the licenses of the other code * concerned, provided that you include the source code of that other * code when and as the GNU GPL requires distribution of source code. * * Note that people who make modified versions of GNU Smalltalk are not * obligated to grant this special exception for their modified * versions; it is their choice whether to do so. The GNU General * Public License gives permission to release a modified version without * this exception; this exception also makes it possible to release a * modified version which carries forward this exception. * * GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or * FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for * more details. * * You should have received a copy of the GNU General Public License along with * GNU Smalltalk; see the file COPYING. If not, write to the Free Software * Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * ***********************************************************************/ /* This parser looks for matchers into the C source files, and uses the code in the C source file to create the macros that are pasted after the decision tree. */ %{ #include "genbc.h" #define yyparse impl_yyparse #define yydebug impl_yydebug #define YYERROR_VERBOSE #define YYPRINT yyprint char *current_id; %} %debug %defines %union { struct field_info *field; const char *ctext; char *text; int num; } %token MATCH_BYTECODES "MATCH_BYTECODES" %token DECL_BEGIN "BEGIN" %token DECL_END "END" %token DECL_BREAK "break" %token DECL_CONTINUE "continue" %token DECL_DISPATCH "dispatch" %token DECL_EXTRACT "extract" %token DECL_DOTS ".." %token NUMBER "number" %token ID "identifier" %token EXPR "expression" %% program: program matcher | /* empty */ ; matcher: MATCH_BYTECODES '(' ID ',' ID ',' '(' { current_id = $3; printf ("\n"); #if 0 printf ("/* %s:%d */\n", current_file, yylineno); #endif printf ("#define MATCH_BYTECODES_%s \\\n", $3); } cases ')' ')' { free ($3); printf ("\n"); }; cases: case | cases { printf (" \\\n"); } case ; case: ids EXPR { printf (" %s \\\n" " goto MATCH_BYTECODES_SWITCH_%s;", $2, current_id); free ($2); }; ids: ids ',' id | id ; id: ID { printf (" MATCH_BYTECODES_%s_%s: \\\n", current_id, $1); free ($1); }; %% smalltalk-3.2.5/libgst/sockets.c0000644000175000017500000003647412123404352013543 00000000000000/*********************************************************************** * * C interface to BSD sockets. * * ***********************************************************************/ /*********************************************************************** * * Copyright 1988,89,90,91,92,94,95,99,2000,2001,2002,2006,2007,2008,2009 * Free Software Foundation, Inc. * Written by Steve Byrne and Paolo Bonzini. * * This file is part of GNU Smalltalk. * * GNU Smalltalk is free software; you can redistribute it and/or modify it * under the terms of the GNU General Public License as published by the Free * Software Foundation; either version 2, or (at your option) any later * version. * * Linking GNU Smalltalk statically or dynamically with other modules is * making a combined work based on GNU Smalltalk. Thus, the terms and * conditions of the GNU General Public License cover the whole * combination. * * In addition, as a special exception, the Free Software Foundation * give you permission to combine GNU Smalltalk with free software * programs or libraries that are released under the GNU LGPL and with * independent programs running under the GNU Smalltalk virtual machine. * * You may copy and distribute such a system following the terms of the * GNU GPL for GNU Smalltalk and the licenses of the other code * concerned, provided that you include the source code of that other * code when and as the GNU GPL requires distribution of source code. * * Note that people who make modified versions of GNU Smalltalk are not * obligated to grant this special exception for their modified * versions; it is their choice whether to do so. The GNU General * Public License gives permission to release a modified version without * this exception; this exception also makes it possible to release a * modified version which carries forward this exception. * * GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or * FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for * more details. * * You should have received a copy of the GNU General Public License along with * GNU Smalltalk; see the file COPYING. If not, write to the Free Software * Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * ***********************************************************************/ #include "gstpriv.h" #include #include #include #ifdef HAVE_UNISTD_H #include #endif #if __STDC__ #include #include #endif /* STDC_HEADERS */ #include #include #ifdef HAVE_SYS_UTSNAME_H #include #endif #ifdef HAVE_SOCKETS #ifndef ntohl #if WORDS_BIGENDIAN #define ntohl(x) (x) #define ntohs(x) (x) #else #define ntohl(x) \ ((unsigned long int)((((unsigned long int)(x) & 0x000000ffU) << 24) | \ (((unsigned long int)(x) & 0x0000ff00U) << 8) | \ (((unsigned long int)(x) & 0x00ff0000U) >> 8) | \ (((unsigned long int)(x) & 0xff000000U) >> 24))) #define ntohs(x) \ ((unsigned short int)((((unsigned short int)(x) & 0x00ff) << 8) | \ (((unsigned short int)(x) & 0xff00) >> 8))) #endif #endif /* ntohl */ static char * myGetHostByAddr (char *addr, int len, int type) { struct hostent *hostEnt; char *result; #if HAVE_GETIPNODEBYADDR int error; hostEnt = getipnodebyaddr (addr, len, type, &error); #else hostEnt = gethostbyaddr (addr, len, type); #endif if (hostEnt) { result = malloc (128); /* out of a hat */ strncpy (result, hostEnt->h_name, 128); #if HAVE_GETIPNODEBYADDR freehostent (hostEnt); #endif } else result = NULL; return (result); } /* The offsets of these two fields are not portable. */ static char ** get_aiCanonname (struct addrinfo *ai) { return &ai->ai_canonname; } static struct sockaddr ** get_aiAddr (struct addrinfo *ai) { return &ai->ai_addr; } static char * myGetHostName (void) { char *result; result = malloc (128); #ifdef HAVE_UNAME { struct utsname utsname; int ret; ret = uname (&utsname); if (ret < 0) return NULL; strncpy (result, utsname.nodename, 128); result[127] = '\0'; } #else #ifdef HAVE_GETHOSTNAME { extern int gethostname (); gethostname (result, 128); } #else strcpy (result, "localhost"); /* terrible guess */ #endif #endif return (result); } #define constantFunction(name, constant) \ static long name(void) { return (constant); } constantFunction (afUnspec, AF_UNSPEC); constantFunction (afInet, AF_INET); constantFunction (afUnix, AF_UNIX); constantFunction (pfUnspec, PF_UNSPEC); constantFunction (pfInet, PF_INET); constantFunction (pfUnix, PF_UNIX); constantFunction (msgOOB, MSG_OOB); constantFunction (msgPeek, MSG_PEEK); constantFunction (solSocket, SOL_SOCKET); constantFunction (soLinger, SO_LINGER); constantFunction (soReuseAddr, SO_REUSEADDR); constantFunction (sockStream, SOCK_STREAM); constantFunction (sockRaw, SOCK_RAW); constantFunction (sockRDM, SOCK_RDM); constantFunction (sockDgram, SOCK_DGRAM); constantFunction (ipprotoIcmp, IPPROTO_ICMP); constantFunction (ipprotoUdp, IPPROTO_UDP); constantFunction (ipprotoTcp, IPPROTO_TCP); constantFunction (ipprotoIp, IPPROTO_IP); constantFunction (tcpNodelay, TCP_NODELAY); #ifdef HAVE_IPV6 constantFunction (afInet6, AF_INET6); constantFunction (pfInet6, PF_INET6); constantFunction (ipprotoIcmpv6, IPPROTO_ICMPV6); #else constantFunction (afInet6, -1); constantFunction (pfInet6, -1); constantFunction (ipprotoIcmpv6, -1); #endif #ifdef IP_MULTICAST_TTL constantFunction (ipMulticastTtl, IP_MULTICAST_TTL); constantFunction (ipMulticastIf, IP_MULTICAST_IF); constantFunction (ipAddMembership, IP_ADD_MEMBERSHIP); constantFunction (ipDropMembership, IP_DROP_MEMBERSHIP); #else constantFunction (ipMulticastTtl, -1); constantFunction (ipMulticastIf, -1); constantFunction (ipAddMembership, -1); constantFunction (ipDropMembership, -1); #endif #ifndef AI_ADDRCONFIG #define AI_ADDRCONFIG 0 #endif #ifndef AI_ALL #define AI_ALL 0 #endif #ifndef AI_V4MAPPED #define AI_V4MAPPED 0 #endif constantFunction (aiAddrconfig, AI_ADDRCONFIG) constantFunction (aiCanonname, AI_CANONNAME) constantFunction (aiAll, AI_ALL) constantFunction (aiV4mapped, AI_V4MAPPED) #if defined SOCK_CLOEXEC && !defined __MSVCRT__ /* 0 = unknown, 1 = yes, -1 = no. */ static mst_Boolean have_sock_cloexec; /* Return 0 if the operation failed and an error can be returned by the caller. */ static inline int check_have_sock_cloexec (int fh, int expected_errno) { if (have_sock_cloexec == 0 && (fh >= 0 || errno == expected_errno)) have_sock_cloexec = (fh >= 0 ? 1 : -1); return (have_sock_cloexec != 0); } #endif static void socket_set_cloexec (SOCKET fh) { if (fh == SOCKET_ERROR) return; #if defined __MSVCRT__ /* Do not do FD_CLOEXEC under MinGW. */ SetHandleInformation ((HANDLE) fh, HANDLE_FLAG_INHERIT, 0); #else fcntl (fh, F_SETFD, fcntl (fh, F_GETFD, 0) | FD_CLOEXEC); #endif } static int mySocket (int domain, int type, int protocol) { SOCKET fh = SOCKET_ERROR; int fd; #if defined SOCK_CLOEXEC && !defined __MSVCRT__ if (have_sock_cloexec >= 0) { fh = socket (domain, type | SOCK_CLOEXEC, protocol); if (!check_have_sock_cloexec (fh, EINVAL)) return -1; } #endif if (fh == SOCKET_ERROR) { fh = socket (domain, type, protocol); socket_set_cloexec (fh); } fd = (fh == SOCKET_ERROR ? -1 : SOCKET_TO_FD (fh)); if (fd != SOCKET_ERROR) _gst_register_socket (fd, false); return fd; } /* BSD systems have sa_len, others have not. Smalltalk will always write sockaddr structs as if they had it. So for Linux and Winsock we read the second byte (sa_family on BSD systems) and write it in the entire sa_family field. */ static inline void fix_sockaddr (struct sockaddr *sockaddr, socklen_t len) { #ifndef HAVE_STRUCT_SOCKADDR_SA_LEN /* Make sure sa_family is a short. */ char verify[sizeof (sockaddr->sa_family) == 2 ? 1 : -1]; if (len >= 2) sockaddr->sa_family = ((unsigned char *) sockaddr)[1]; #endif } /* Same as connect, but forces the socket to be in non-blocking mode */ static int myConnect (int fd, struct sockaddr *sockaddr, int len) { SOCKET sock = FD_TO_SOCKET (fd); int rc; #ifdef __MSVCRT__ unsigned long iMode = 1; ioctlsocket (sock, FIONBIO, &iMode); #elif defined F_GETFL #ifndef O_NONBLOCK #warning Non-blocking I/O could not be enabled #else int oldflags = fcntl (sock, F_GETFL, NULL); if (!(oldflags & O_NONBLOCK)) fcntl (sock, F_SETFL, oldflags | O_NONBLOCK); #endif #endif fix_sockaddr (sockaddr, len); rc = connect (sock, sockaddr, len); if (rc == 0 || is_socket_error (EINPROGRESS) || is_socket_error (EWOULDBLOCK)) return 0; else return -1; } static int myAccept (int fd, struct sockaddr *addr, socklen_t *addrlen) { SOCKET fh = SOCKET_ERROR; int new_fd; /* Parameters to system calls are not guaranteed to generate a SIGSEGV and for this reason we must touch them manually. */ _gst_grey_oop_range (addr, *addrlen); #if defined SOCK_CLOEXEC && defined HAVE_ACCEPT4 && !defined __MSVCRT__ if (have_sock_cloexec >= 0) { fh = accept4 (FD_TO_SOCKET (fd), addr, addrlen, SOCK_CLOEXEC); if (!check_have_sock_cloexec (fh, ENOSYS)) return -1; } #endif if (fh == SOCKET_ERROR) { fh = accept (FD_TO_SOCKET (fd), addr, addrlen); socket_set_cloexec (fh); } new_fd = (fh == SOCKET_ERROR ? -1 : SOCKET_TO_FD (fh)); if (new_fd != SOCKET_ERROR) _gst_register_socket (new_fd, false); return new_fd; } static int myBind (int fd, struct sockaddr *addr, socklen_t addrlen) { fix_sockaddr (addr, addrlen); return bind (FD_TO_SOCKET (fd), addr, addrlen); } static int myGetpeername (int fd, struct sockaddr *addr, socklen_t *addrlen) { /* Parameters to system calls are not guaranteed to generate a SIGSEGV and for this reason we must touch them manually. */ _gst_grey_oop_range (addr, *addrlen); return getpeername (FD_TO_SOCKET (fd), addr, addrlen); } static int myGetsockname (int fd, struct sockaddr *addr, socklen_t *addrlen) { /* Parameters to system calls are not guaranteed to generate a SIGSEGV and for this reason we must touch them manually. */ _gst_grey_oop_range (addr, *addrlen); return getsockname (FD_TO_SOCKET (fd), addr, addrlen); } static int myGetsockopt (int fd, int level, int optname, char *optval, socklen_t *optlen) { /* Parameters to system calls are not guaranteed to generate a SIGSEGV and for this reason we must touch them manually. */ _gst_grey_oop_range (optval, *optlen); return getsockopt (FD_TO_SOCKET (fd), level, optname, optval, optlen); } static int myListen (int fd, int backlog) { int r = listen (FD_TO_SOCKET (fd), backlog); if (r != SOCKET_ERROR) _gst_register_socket (fd, true); return r; } static int myRecvfrom (int fd, char *buf, int len, int flags, struct sockaddr *from, socklen_t *fromlen) { int frombufsize = *fromlen; int r; /* Parameters to system calls are not guaranteed to generate a SIGSEGV and for this reason we must touch them manually. */ _gst_grey_oop_range (buf, len); _gst_grey_oop_range (from, *fromlen); r = recvfrom (FD_TO_SOCKET (fd), buf, len, flags, from, fromlen); /* Winsock recvfrom() only returns a valid 'from' when the socket is connectionless. POSIX gives a valid 'from' for all types of sockets. */ if (r != SOCKET_ERROR && frombufsize == *fromlen) (void) myGetpeername (fd, from, fromlen); return r; } static int mySendto (int fd, const char *buf, int len, int flags, struct sockaddr *to, int tolen) { fix_sockaddr (to, tolen); return sendto (FD_TO_SOCKET (fd), buf, len, flags, to, tolen); } static int mySetsockopt (int fd, int level, int optname, const char *optval, int optlen) { return setsockopt (FD_TO_SOCKET (fd), level, optname, optval, optlen); } static int getSoError (int fd) { int error; socklen_t size = sizeof (error); if ((error = _gst_get_fd_error (fd)) != 0) ; else if (myGetsockopt (fd, SOL_SOCKET, SO_ERROR, (char *)&error, &size) == -1) { #if defined _WIN32 && !defined __CYGWIN__ error = WSAGetLastError (); #else error = errno; #endif } /* When we get one of these, we don't return an error. However, the primitive still fails and the file/socket is closed by the Smalltalk code. */ if (error == ESHUTDOWN || error == ECONNRESET || error == ECONNABORTED || error == ENETRESET || error == EPIPE) return 0; else return error; } void _gst_init_sockets () { #if defined WIN32 && !defined __CYGWIN__ WSADATA wsaData; int iRet; iRet = WSAStartup(MAKEWORD(2,2), &wsaData); if (iRet != 0) { printf("WSAStartup failed (looking for Winsock 2.2): %d\n", iRet); return; } #endif /* _WIN32 */ _gst_define_cfunc ("TCPgetaddrinfo", getaddrinfo); _gst_define_cfunc ("TCPfreeaddrinfo", freeaddrinfo); _gst_define_cfunc ("TCPgetHostByAddr", myGetHostByAddr); _gst_define_cfunc ("TCPgetLocalName", myGetHostName); _gst_define_cfunc ("TCPgetAiCanonname", get_aiCanonname); _gst_define_cfunc ("TCPgetAiAddr", get_aiAddr); _gst_define_cfunc ("TCPaccept", myAccept); _gst_define_cfunc ("TCPbind", myBind); _gst_define_cfunc ("TCPconnect", myConnect); _gst_define_cfunc ("TCPgetpeername", myGetpeername); _gst_define_cfunc ("TCPgetsockname", myGetsockname); _gst_define_cfunc ("TCPlisten", myListen); _gst_define_cfunc ("TCPrecvfrom", myRecvfrom); _gst_define_cfunc ("TCPsendto", mySendto); _gst_define_cfunc ("TCPsetsockopt", mySetsockopt); _gst_define_cfunc ("TCPgetsockopt", myGetsockopt); _gst_define_cfunc ("TCPgetSoError", getSoError); _gst_define_cfunc ("TCPsocket", mySocket); _gst_define_cfunc ("TCPpfUnspec", pfUnspec); _gst_define_cfunc ("TCPpfInet", pfInet); _gst_define_cfunc ("TCPpfInet6", pfInet6); _gst_define_cfunc ("TCPpfUnix", pfUnix); _gst_define_cfunc ("TCPafUnspec", afUnspec); _gst_define_cfunc ("TCPafInet", afInet); _gst_define_cfunc ("TCPafInet6", afInet6); _gst_define_cfunc ("TCPafUnix", afUnix); _gst_define_cfunc ("TCPipMulticastTtl", ipMulticastTtl); _gst_define_cfunc ("TCPipMulticastIf", ipMulticastIf); _gst_define_cfunc ("TCPipAddMembership", ipAddMembership); _gst_define_cfunc ("TCPipDropMembership", ipDropMembership); _gst_define_cfunc ("TCPtcpNodelay", tcpNodelay); _gst_define_cfunc ("TCPmsgPeek", msgPeek); _gst_define_cfunc ("TCPmsgOOB", msgOOB); _gst_define_cfunc ("TCPsolSocket", solSocket); _gst_define_cfunc ("TCPsoLinger", soLinger); _gst_define_cfunc ("TCPsoReuseAddr", soReuseAddr); _gst_define_cfunc ("TCPsockStream", sockStream); _gst_define_cfunc ("TCPsockRaw", sockRaw); _gst_define_cfunc ("TCPsockRDM", sockRDM); _gst_define_cfunc ("TCPsockDgram", sockDgram); _gst_define_cfunc ("TCPipprotoIp", ipprotoIp); _gst_define_cfunc ("TCPipprotoTcp", ipprotoTcp); _gst_define_cfunc ("TCPipprotoUdp", ipprotoUdp); _gst_define_cfunc ("TCPipprotoIcmp", ipprotoIcmp); _gst_define_cfunc ("TCPipprotoIcmpv6", ipprotoIcmpv6); _gst_define_cfunc ("TCPaiAddrconfig", aiAddrconfig); _gst_define_cfunc ("TCPaiCanonname", aiCanonname); _gst_define_cfunc ("TCPaiAll", aiAll); _gst_define_cfunc ("TCPaiV4mapped", aiV4mapped); } #else /* !HAVE_SOCKETS */ void _gst_init_sockets () { } #endif smalltalk-3.2.5/libgst/events.h0000644000175000017500000001262612130343734013376 00000000000000/******************************** -*- C -*- **************************** * * Header file for asynchronous events * * ***********************************************************************/ /*********************************************************************** * * Copyright 2001, 2002, 2006, 2008, 2009 Free Software Foundation, Inc. * Written by Paolo Bonzini. * * This file is part of GNU Smalltalk. * * GNU Smalltalk is free software; you can redistribute it and/or modify it * under the terms of the GNU General Public License as published by the Free * Software Foundation; either version 2, or (at your option) any later * version. * * Linking GNU Smalltalk statically or dynamically with other modules is * making a combined work based on GNU Smalltalk. Thus, the terms and * conditions of the GNU General Public License cover the whole * combination. * * In addition, as a special exception, the Free Software Foundation * give you permission to combine GNU Smalltalk with free software * programs or libraries that are released under the GNU LGPL and with * independent programs running under the GNU Smalltalk virtual machine. * * You may copy and distribute such a system following the terms of the * GNU GPL for GNU Smalltalk and the licenses of the other code * concerned, provided that you include the source code of that other * code when and as the GNU GPL requires distribution of source code. * * Note that people who make modified versions of GNU Smalltalk are not * obligated to grant this special exception for their modified * versions; it is their choice whether to do so. The GNU General * Public License gives permission to release a modified version without * this exception; this exception also makes it possible to release a * modified version which carries forward this exception. * * GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or * FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for * more details. * * You should have received a copy of the GNU General Public License along with * GNU Smalltalk; see the file COPYING. If not, write to the Free Software * Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * ***********************************************************************/ #ifndef GST_EVENTS_H #define GST_EVENTS_H /* Array of semaphores associated to the C signals. */ extern async_queue_entry _gst_sem_int_vec[NSIG] ATTRIBUTE_HIDDEN; /* Initialize the data structures used to hold information about asynchronous events requested by Smalltalk programs. */ extern void _gst_init_async_events (void) ATTRIBUTE_HIDDEN; /* Arrange so that when the SIG signal arrives from the operating system, SEMAPHOREOOP is signaled by the virtual machine. A previous wait for the same signal, if any, are discarded. */ extern void _gst_async_interrupt_wait (OOP semaphoreOOP, int sig) ATTRIBUTE_HIDDEN; /* These are defined in sysdep/.../events.c. */ /* Arrange so that when the nanosecond clock reaches NSTIME, SEMAPHOREOOP is signaled by the virtual machine. Previous waits are discarded. */ extern void _gst_async_timed_wait (OOP semaphoreOOP, int64_t nsTime) ATTRIBUTE_HIDDEN; /* Answer whether a timeout has been scheduled and a semaphore was passed to the virtual machine, to be signaled when the timer fires. */ extern mst_Boolean _gst_is_timeout_programmed (void) ATTRIBUTE_PURE ATTRIBUTE_HIDDEN; /* Check for asynchronously reported error conditions related to file descriptor FD. */ extern int _gst_get_fd_error (int fd) ATTRIBUTE_HIDDEN; /* Fire and remove all I/O handlers for file descriptor FD. */ extern void _gst_remove_fd_polling_handlers (int fd) ATTRIBUTE_HIDDEN; /* Initialize the socket for asynchronous event notifications for the kind of socket given by PASSIVE and on the file descriptor FD. */ extern void _gst_register_socket (int fd, mst_Boolean passive) ATTRIBUTE_HIDDEN; /* Check whether I/O is possible on the FD file descriptor; COND is 0 to check for pending input, 1 to check for the possibility of doing non-blocking output, 2 to check for pending exceptional situations (such as out-of-band data). Answer -1 if there is an error (including POLLHUP -- in that case errno is left to 0), 0 if I/O is impossible, 1 if possible. */ extern int _gst_sync_file_polling (int fd, int cond) ATTRIBUTE_HIDDEN; /* Check whether I/O is possible on the FD file descriptor; COND is 0 to check for pending input, 1 to check for the possibility of doing non-blocking output, 2 to check for pending exceptional situations (such as out-of-band data). Answer -1 if there is an error (including POLLHUP -- in that case errno is left to 0), 0 if I/O is impossible, 1 if possible. If 0 is answered, the virtual machine arranges things so that when the given condition is true SEMAPHOREOOP is signaled. Note: due to lack of support from many kernels, waiting for a semaphore to be signaled when *output* is possible is risky and known to works for sockets only. */ extern int _gst_async_file_polling (int fd, int cond, OOP semaphoreOOP) ATTRIBUTE_HIDDEN; /* Pause until a signal is received. */ extern void _gst_pause (void); /* Wake up from a pause. */ extern void _gst_wakeup (void); #endif /* GST_EVENTS_H */ smalltalk-3.2.5/libgst/valgrind.supp0000644000175000017500000000103512123404352014424 00000000000000{ scanning_grey_pages_is_conservative Cond fun: scan_grey_pages fun: copy_oops } { uninitialized_context_stack_slots_written_to_image Param write(buf) obj: *libc-*.so fun: buffer_write } ######### { probing_unmapped_areas Param access(pathname) obj: *libc-*.so fun: _gst_heap_create } { probing_unmapped_areas_2 Param access(pathname) obj: *libc-*.so fun: find_heap_base } { probing_unmapped_areas_3 Addr4 fun: _gst_heap_create } { probing_unmapped_areas_4 Addr4 fun: find_heap_base } smalltalk-3.2.5/libgst/genbc-decl.y0000644000175000017500000003346212123404352014073 00000000000000/******************************** -*- C -*- **************************** * * GNU Smalltalk genbc tool - parser for definitions * ***********************************************************************/ /*********************************************************************** * * Copyright 2003, 2006, 2009 Free Software Foundation, Inc. * Written by Paolo Bonzini. * * This file is part of GNU Smalltalk. * * GNU Smalltalk is free software; you can redistribute it and/or modify it * under the terms of the GNU General Public License as published by the Free * Software Foundation; either version 2, or (at your option) any later * version. * * Linking GNU Smalltalk statically or dynamically with other modules is * making a combined work based on GNU Smalltalk. Thus, the terms and * conditions of the GNU General Public License cover the whole * combination. * * In addition, as a special exception, the Free Software Foundation * give you permission to combine GNU Smalltalk with free software * programs or libraries that are released under the GNU LGPL and with * independent programs running under the GNU Smalltalk virtual machine. * * You may copy and distribute such a system following the terms of the * GNU GPL for GNU Smalltalk and the licenses of the other code * concerned, provided that you include the source code of that other * code when and as the GNU GPL requires distribution of source code. * * Note that people who make modified versions of GNU Smalltalk are not * obligated to grant this special exception for their modified * versions; it is their choice whether to do so. The GNU General * Public License gives permission to release a modified version without * this exception; this exception also makes it possible to release a * modified version which carries forward this exception. * * GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or * FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for * more details. * * You should have received a copy of the GNU General Public License along with * GNU Smalltalk; see the file COPYING. If not, write to the Free Software * Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * ***********************************************************************/ /* This parser builds the decision tree for matching the bytecodes. This file knows also how to output C code to visit that tree. */ %{ #include "genbc.h" #include "avltrees.h" #define yyparse decl_yyparse #define yydebug decl_yydebug #define YYERROR_VERBOSE #define YYPRINT yyprint typedef struct bytecode_info { avl_node_t avl; const char *name; struct field_info *fields; } bytecode_info; typedef struct field_info { struct field_info *next, **pnext; const char *name; } field_info; typedef struct var_info { avl_node_t avl; const char *name; } var_info; typedef struct opcode { struct opcode *next; int first; int last; char *code; } opcode; static void define_decl (int first, int last, char *code); static void define_bytecode (const char *id, field_info *fields); static void define_var (const char *id); static void define_field (const char *id, int bits); static char *extraction_code (int bits); static void emit_var_names (var_info *node, const char *prefix, const char *suffix, const char *next_prefix); static int filprintf (Filament *fil, const char *format, ...); static bytecode_info *get_bytecode (const char *name); int curr_bit_offset = 0, synthetic = 256; bytecode_info *bytecode_root, *curr_bytecode; field_info *curr_field; var_info *var_root; opcode *first = NULL, **p_next = &first; Filament *curr_fil; char *begin_code, *end_code; %} %debug %defines %expect 3 %union { struct field_info *field; const char *ctext; char *text; int num; } %type field_list opt_field_list %type code %type c_code %type bitfield %type bitfields %type opt_size %token MATCH_BYTECODES "MATCH_BYTECODES" %token DECL_BEGIN "BEGIN" %token DECL_END "END" %token DECL_BREAK "break" %token DECL_CONTINUE "continue" %token DECL_DISPATCH "dispatch" %token DECL_EXTRACT "extract" %token DECL_DOTS ".." %token NUMBER "number" %token ID "identifier" %token EXPR "expression" %% decls: decls decl | decl ; decl: ID opt_field_list ';' { define_bytecode ($1, $2); } | DECL_BEGIN '{' c_code '}' { begin_code = $3; } | DECL_END '{' c_code '}' { end_code = $3; } | NUMBER '{' code '}' { define_decl ($1, $1, $3); } | NUMBER DECL_DOTS NUMBER '{' code '}' { define_decl ($1, $3, $5); } ; opt_field_list: '(' field_list ')' { $$ = $2; } | /* empty */ { $$ = NULL; } ; field_list: field_list ',' ID { struct field_info *f = malloc (sizeof (struct field_info)); define_var ($3); f->name = $3; f->next = NULL; *($1->pnext) = f; $$ = $1; $$->pnext = &(f->next); } | ID { struct field_info *f = malloc (sizeof (struct field_info)); define_var ($1); f->name = $1; f->next = NULL; $$ = f; $$->pnext = &(f->next); } ; c_code: { curr_fil = filnew (NULL, 0); } c_code_body { $$ = fildelete (curr_fil); } ; c_code_expr_body: c_code_expr_body c_code_expr_item | /* empty */; c_code_expr_item: '=' { filccat (curr_fil, '='); } | '(' { filccat (curr_fil, '('); } c_code_body ')' { filccat (curr_fil, ')'); } | ID { filcat (curr_fil, $1); free ($1); } | NUMBER { filprintf (curr_fil, "%d", $1); } | EXPR { filcat (curr_fil, $1); } ; c_code_body: c_code_body c_code_item | /* empty */; c_code_item: c_code_expr_item | ',' { filccat (curr_fil, ','); } ; code: { curr_fil = filnew (NULL, 0); } code_body { filcat (curr_fil, " goto MATCH_BYTECODES_END_##name_; "); $$ = fildelete (curr_fil); } ; code_body: code_body code_item | /* empty */; code_item: c_code_item | DECL_BREAK { filcat (curr_fil, "goto MATCH_BYTECODES_END_##name_;"); } | DECL_CONTINUE { filcat (curr_fil, "goto MATCH_BYTECODES_START_##name_;"); } | DECL_DISPATCH ID { filprintf (curr_fil, "do { \\\n" "\topcode_ = %d; \\\n", synthetic); curr_bytecode = get_bytecode ($2); if (!curr_bytecode) { curr_field = NULL; yyerror ("bad bytecode name"); } else curr_field = curr_bytecode->fields; } opt_dispatch_args { if (curr_field) yyerror ("expected field in dispatch"); filprintf (curr_fil, "\tgoto MATCH_BYTECODES_##name_##_%s; \\\n", $2); filprintf (curr_fil, " case %d: \\\n" "\t; \\\n" " } while (0)", synthetic++); free ($2); } | DECL_EXTRACT bitfields { if ($2 % 8) yyerror ("must extract an integer number of bytes"); else filprintf (curr_fil, "bp_ = (IP += %d)", $2 / 8); } ; opt_dispatch_args: '(' dispatch_args ')' | /* empty */ ; dispatch_args: dispatch_args ',' dispatch_arg | dispatch_arg ; dispatch_arg: { if (curr_field) { filprintf (curr_fil, "\t%s = ", curr_field->name); curr_field = curr_field->next; } else yyerror ("extra field in dispatch"); } c_code_expr_body { filprintf (curr_fil, "; \\\n"); } ; opt_size: '(' NUMBER ')' { $$ = $2; } | /* empty */ { $$ = 8; } ; bitfields: bitfields ',' bitfield { $$ = $1 + $3; } | bitfield { $$ = $1; } ; bitfield: ID opt_size { define_field ($1, $2); $$ = $2; } ; %% int filprintf (Filament *fil, const char *format, ...) { va_list ap; STREAM *out = stream_new (fil, SNV_UNLIMITED, NULL, snv_filputc); int result; va_start (ap, format); result = stream_vprintf (out, format, ap); va_end (ap); stream_delete (out); return result; } /* Advance the pointer by BITS bits and return the code to extract those bits. */ char * extraction_code (int bits) { char *s; int n_bit = curr_bit_offset % 8; int n_byte = curr_bit_offset / 8; if (n_bit + bits <= 8) { int rshift = 8 - (n_bit + bits); int mask = (1 << bits) - 1; curr_bit_offset += bits; if (n_bit && rshift) return my_asprintf ("(IP[%d] >> %d) & %d", n_byte, rshift, mask); if (rshift) return my_asprintf ("IP[%d] >> %d", n_byte, rshift); if (n_bit) return my_asprintf ("IP[%d] & %d", n_byte, mask); else return my_asprintf ("IP[%d]", n_byte); } /* Else, multi-byte extraction. */ if (curr_bit_offset % 8) /* Complete the current byte... */ { int n = 8 - (curr_bit_offset % 8); s = extraction_code (n); bits -= n; n_bit = 0; n_byte++; } else /* ... or do a new one. */ { s = my_asprintf ("IP[%d]", n_byte++); curr_bit_offset += 8; bits -= 8; } /* Add entire bytes as long as possible. */ while (bits >= 8) { char *new_s = my_asprintf ("((%s) << 8) | IP[%d]", s, n_byte++); free (s); s = new_s; curr_bit_offset += 8; bits -= 8; } /* And finally any spare bits. */ if (bits) { char *new_s = my_asprintf ("((%s) << 8) | %s", s, extraction_code (bits)); free (s); s = new_s; } return (s); } /* Define a bytecode that is used as an operand to dispatch. We use an AVL tree to store them so that we can do fast searches, and we can detect duplicates. */ bytecode_info * get_bytecode (const char *name) { avl_node_t **p = (avl_node_t **) &bytecode_root; bytecode_info *bytecode = NULL; while (*p) { int cmp; bytecode = (bytecode_info *) *p; cmp = strcmp(name, bytecode->name); if (cmp < 0) p = &(*p)->avl_left; else if (cmp > 0) p = &(*p)->avl_right; else return bytecode; } return NULL; } /* Define a bytecode that is used as an operand to dispatch. We use an AVL tree to store them so that we can do fast searches, and we can detect duplicates. */ void define_bytecode (const char *name, field_info *fields) { avl_node_t **p = (avl_node_t **) &bytecode_root; bytecode_info *node; bytecode_info *bytecode = NULL; while (*p) { int cmp; bytecode = (bytecode_info *) *p; cmp = strcmp(name, bytecode->name); if (cmp < 0) p = &(*p)->avl_left; else if (cmp > 0) p = &(*p)->avl_right; else { yyerror ("duplicate bytecode name"); return; } } node = (bytecode_info *) calloc(1, sizeof(struct bytecode_info)); node->avl.avl_parent = (avl_node_t *) bytecode; node->avl.avl_left = node->avl.avl_right = NULL; node->name = name; node->fields = fields; *p = &(node->avl); avl_rebalance(&node->avl, (avl_node_t **) &bytecode_root); } /* Define a variable that is used to pass the operands of the bytecode. We use an AVL tree to store them so that we can output them nicely sorted, and we can eliminate duplicates. */ void define_var (const char *name) { avl_node_t **p = (avl_node_t **) &var_root; var_info *node; var_info *var = NULL; while (*p) { int cmp; var = (var_info *) *p; cmp = strcmp(name, var->name); if (cmp < 0) p = &(*p)->avl_left; else if (cmp > 0) p = &(*p)->avl_right; else return; } node = (var_info *) calloc(1, sizeof(struct var_info)); node->avl.avl_parent = (avl_node_t *) var; node->avl.avl_left = node->avl.avl_right = NULL; node->name = name; *p = &(node->avl); avl_rebalance(&node->avl, (avl_node_t **) &var_root); } /* Define an operation that is BITS bits wide and whose opcodes start at OPCODE) and does the ID operation. */ void define_decl (int first, int last, char *code) { struct opcode *curr = calloc (1, sizeof (struct opcode)); curr->first = first; curr->last = last; curr->code = code; *p_next = curr; p_next = &(curr->next); if ((unsigned) (first | last) > 255) yyerror ("Invalid opcode specification"); curr_bit_offset = 0; } /* Define a BITS bits-wide operand named NAME of the current bytecode. */ void define_field (const char *name, int bits) { char *s = extraction_code (bits); define_var (name); filprintf (curr_fil, "%s = %s; \\\n ", name, s); free (s); } /* Emit the declarations for the variable names. NODE is the root of the tree, PREFIX ("int" or ",") is emitted before the first variable, SUFFIX after every variable, NEXT_PREFIX before every variable but the first. */ void emit_var_names (var_info *node, const char *prefix, const char *suffix, const char *next_prefix) { if (node->avl.avl_left) { emit_var_names ((var_info *) node->avl.avl_left, prefix, suffix, next_prefix); prefix = next_prefix; } printf ("%s%s%s", prefix, node->name, suffix); if (node->avl.avl_right) emit_var_names ((var_info *) node->avl.avl_right, next_prefix, suffix, next_prefix); } /* Emit the decision tree for the bytecodes. */ void emit_opcodes () { int n; struct opcode *op; define_var ("opcode_"); emit_var_names (var_root, " int ", "", ", "); printf ("; \\\n"); printf (" unsigned char *IP = bp_; \\\n"); printf (" unsigned char ATTRIBUTE_UNUSED *IP0 = bp_; \\\n"); emit_var_names (var_root, " ", " ", "= "); printf ("= 0; \\\n"); if (begin_code) printf (" { \\\n" " %s \\\n" " } \\\n", begin_code); printf ("MATCH_BYTECODES_START_##name_: \\\n" " opcode_ = *IP; \\\n" "MATCH_BYTECODES_SWITCH_##name_: \\\n" " switch (opcode_) { \\\n"); for (op = first; op; op = op->next) { int first_val = op->first; int last_val = op->last; for (n = 0; first_val <= last_val; first_val++, n++) { if (!(n & 3)) printf ("%s ", n ? "\\\n" : ""); printf ("case %d: ", first_val); } printf ("\\\n" " %s\\\n", op->code); } printf (" } \\\n" " MATCH_BYTECODES_DISPATCH(MATCH_BYTECODES_##name_) \\\n" "MATCH_BYTECODES_END_##name_: \\\n" "%s", end_code ? end_code : " ;"); } smalltalk-3.2.5/libgst/sym.h0000644000175000017500000003372112130343734012701 00000000000000/******************************** -*- C -*- **************************** * * Symbol Table declarations * * ***********************************************************************/ /*********************************************************************** * * Copyright 1988,89,90,91,92,94,95,99,2000,2001,2002,2003,2005,2006,2008 * Free Software Foundation, Inc. * Written by Steve Byrne. * * This file is part of GNU Smalltalk. * * GNU Smalltalk is free software; you can redistribute it and/or modify it * under the terms of the GNU General Public License as published by the Free * Software Foundation; either version 2, or (at your option) any later * version. * * Linking GNU Smalltalk statically or dynamically with other modules is * making a combined work based on GNU Smalltalk. Thus, the terms and * conditions of the GNU General Public License cover the whole * combination. * * In addition, as a special exception, the Free Software Foundation * give you permission to combine GNU Smalltalk with free software * programs or libraries that are released under the GNU LGPL and with * independent programs running under the GNU Smalltalk virtual machine. * * You may copy and distribute such a system following the terms of the * GNU GPL for GNU Smalltalk and the licenses of the other code * concerned, provided that you include the source code of that other * code when and as the GNU GPL requires distribution of source code. * * Note that people who make modified versions of GNU Smalltalk are not * obligated to grant this special exception for their modified * versions; it is their choice whether to do so. The GNU General * Public License gives permission to release a modified version without * this exception; this exception also makes it possible to release a * modified version which carries forward this exception. * * GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or * FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for * more details. * * You should have received a copy of the GNU General Public License along with * GNU Smalltalk; see the file COPYING. If not, write to the Free Software * Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * ***********************************************************************/ #ifndef GST_SYM_H #define GST_SYM_H #define SYMBOL_TABLE_SIZE 512 typedef enum { SCOPE_TEMPORARY, SCOPE_RECEIVER, SCOPE_GLOBAL, SCOPE_SPECIAL } scope_type; typedef struct gst_symbol { OBJ_HEADER; /* I love inheritance */ char symString[1]; } *gst_symbol; typedef struct symbol_entry { scope_type scope; OOP symbol; mst_Boolean readOnly; int varIndex; /* index of receiver or temporary */ unsigned int scopeDistance; /* how many frames up the stack is this variable from where we are? */ } symbol_entry; enum undeclared_strategy { UNDECLARED_NONE, UNDECLARED_GLOBALS, UNDECLARED_TEMPORARIES, UNDECLARED_CURRENT }; /* Set whether undeclared globals can be considered forward references, or whether they should be considered like temporary variables. */ extern int _gst_set_undeclared (enum undeclared_strategy value) ATTRIBUTE_HIDDEN; /* Establish a new dictionary that will host local variables of the evaluations; return the old one. */ extern OOP _gst_push_temporaries_dictionary (void) ATTRIBUTE_HIDDEN; /* Switch back to a previously used dictionary to host local variables of the evaluations. */ extern void _gst_pop_temporaries_dictionary (OOP dictionaryOOP) ATTRIBUTE_HIDDEN; extern OOP _gst_and_symbol ATTRIBUTE_HIDDEN; extern OOP _gst_as_scaled_decimal_radix_scale_symbol ATTRIBUTE_HIDDEN; extern OOP _gst_bad_return_error_symbol ATTRIBUTE_HIDDEN; extern OOP _gst_boolean_symbol ATTRIBUTE_HIDDEN; extern OOP _gst_byte_array_out_symbol ATTRIBUTE_HIDDEN; extern OOP _gst_byte_array_symbol ATTRIBUTE_HIDDEN; extern OOP _gst_c_object_ptr_symbol ATTRIBUTE_HIDDEN; extern OOP _gst_c_object_symbol ATTRIBUTE_HIDDEN; extern OOP _gst_category_symbol ATTRIBUTE_HIDDEN; extern OOP _gst_char_symbol ATTRIBUTE_HIDDEN; extern OOP _gst_does_not_understand_symbol ATTRIBUTE_HIDDEN; extern OOP _gst_double_symbol ATTRIBUTE_HIDDEN; extern OOP _gst_false_symbol ATTRIBUTE_HIDDEN; extern OOP _gst_float_symbol ATTRIBUTE_HIDDEN; extern OOP _gst_if_false_if_true_symbol ATTRIBUTE_HIDDEN; extern OOP _gst_if_false_symbol ATTRIBUTE_HIDDEN; extern OOP _gst_if_true_if_false_symbol ATTRIBUTE_HIDDEN; extern OOP _gst_if_true_symbol ATTRIBUTE_HIDDEN; extern OOP _gst_int_symbol ATTRIBUTE_HIDDEN; extern OOP _gst_long_double_symbol ATTRIBUTE_HIDDEN; extern OOP _gst_long_symbol ATTRIBUTE_HIDDEN; extern OOP _gst_must_be_boolean_symbol ATTRIBUTE_HIDDEN; extern OOP _gst_nil_symbol ATTRIBUTE_HIDDEN; extern OOP _gst_or_symbol ATTRIBUTE_HIDDEN; extern OOP _gst_permission_symbol ATTRIBUTE_HIDDEN; extern OOP _gst_primitive_symbol ATTRIBUTE_HIDDEN; extern OOP _gst_repeat_symbol ATTRIBUTE_HIDDEN; extern OOP _gst_self_smalltalk_symbol ATTRIBUTE_HIDDEN; extern OOP _gst_self_symbol ATTRIBUTE_HIDDEN; extern OOP _gst_short_symbol ATTRIBUTE_HIDDEN; extern OOP _gst_ushort_symbol ATTRIBUTE_HIDDEN; extern OOP _gst_smalltalk_symbol ATTRIBUTE_HIDDEN; extern OOP _gst_smalltalk_namespace_symbol ATTRIBUTE_HIDDEN; extern OOP _gst_start_execution_symbol ATTRIBUTE_HIDDEN; extern OOP _gst_string_out_symbol ATTRIBUTE_HIDDEN; extern OOP _gst_string_symbol ATTRIBUTE_HIDDEN; extern OOP _gst_super_symbol ATTRIBUTE_HIDDEN; extern OOP _gst_symbol_symbol ATTRIBUTE_HIDDEN; extern OOP _gst_symbol_out_symbol ATTRIBUTE_HIDDEN; extern OOP _gst_terminate_symbol ATTRIBUTE_HIDDEN; extern OOP _gst_this_context_symbol ATTRIBUTE_HIDDEN; extern OOP _gst_times_repeat_symbol ATTRIBUTE_HIDDEN; extern OOP _gst_to_by_do_symbol ATTRIBUTE_HIDDEN; extern OOP _gst_to_do_symbol ATTRIBUTE_HIDDEN; extern OOP _gst_true_symbol ATTRIBUTE_HIDDEN; extern OOP _gst_uchar_symbol ATTRIBUTE_HIDDEN; extern OOP _gst_uint_symbol ATTRIBUTE_HIDDEN; extern OOP _gst_ulong_symbol ATTRIBUTE_HIDDEN; extern OOP _gst_undeclared_symbol ATTRIBUTE_HIDDEN; extern OOP _gst_unknown_symbol ATTRIBUTE_HIDDEN; extern OOP _gst_value_with_rec_with_args_symbol ATTRIBUTE_HIDDEN; extern OOP _gst_variadic_smalltalk_symbol ATTRIBUTE_HIDDEN; extern OOP _gst_variadic_symbol ATTRIBUTE_HIDDEN; extern OOP _gst_vm_primitives_symbol ATTRIBUTE_HIDDEN; extern OOP _gst_void_symbol ATTRIBUTE_HIDDEN; extern OOP _gst_wchar_symbol ATTRIBUTE_HIDDEN; extern OOP _gst_wstring_symbol ATTRIBUTE_HIDDEN; extern OOP _gst_wstring_out_symbol ATTRIBUTE_HIDDEN; extern OOP _gst_while_false_colon_symbol ATTRIBUTE_HIDDEN; extern OOP _gst_while_false_symbol ATTRIBUTE_HIDDEN; extern OOP _gst_while_true_colon_symbol ATTRIBUTE_HIDDEN; extern OOP _gst_while_true_symbol ATTRIBUTE_HIDDEN; extern OOP _gst_symbol_table ATTRIBUTE_HIDDEN; extern OOP _gst_current_namespace ATTRIBUTE_HIDDEN; /* This returns the name of the given scope (instance variable, temporary, ...). */ extern const char *_gst_get_scope_kind (scope_type scope) ATTRIBUTE_CONST ATTRIBUTE_HIDDEN; /* This walks the list of scopes and of symbols defined for each scope, looking for a variable represented by the tree LIST. Then it looks in the instance variables, then in the class variables, and then in the pool dictionaries (starting from those declared in the class and going up in the hierarchy). If the variable is not found anywhere but starts with an uppercase letter, it is declared in the Undeclared dictionary and the methods will be fixed automatically as soon as it is defined (if it is). True is returned, and SE is filled with the information about the variable if it is found or it is deemed part of Undeclared. Else, SE is untouched and FALSE is returned. */ extern mst_Boolean _gst_find_variable (symbol_entry * se, tree_node list) ATTRIBUTE_HIDDEN; /* This converts a C string to a symbol and stores it in the symbol table. */ extern OOP _gst_intern_string (const char *str) ATTRIBUTE_HIDDEN; /* This makes an Array with an element for each instance variable declared in VARIABLESTRING, plus those inherited from SUPERCLASSOOP. */ extern OOP _gst_make_instance_variable_array (OOP superclassOOP, const char * variableString) ATTRIBUTE_HIDDEN; /* This makes a BindingDictionary whose keys are the class variables declared in VARIABLENAMES. The environment of the dictionary is classOOP. */ extern OOP _gst_make_class_variable_dictionary (const char * variableNames, OOP classOOP) ATTRIBUTE_HIDDEN; /* This makes an Array whose elements are the pool dictionaries declared in POOLNAMES. */ extern OOP _gst_make_pool_array (const char * poolNames) ATTRIBUTE_HIDDEN; /* This resolves the variable binding constant expressed by the LIST parse tree node. Unless DECLARE_TEMPORARY is false, temporary variables may be automatically declared. */ extern tree_node _gst_find_variable_binding (tree_node list) ATTRIBUTE_HIDDEN; /* This returns the dictionary in which to define an undeclared variable binding. */ extern OOP _gst_get_undeclared_dictionary () ATTRIBUTE_PURE ATTRIBUTE_HIDDEN; /* This converts the Smalltalk String STRINGOOP into a Symbol and return the converted Symbol. */ extern OOP _gst_intern_string_oop (OOP stringOOP) ATTRIBUTE_HIDDEN; /* This computes an hash of LEN bytes, starting at STR. */ extern uintptr_t _gst_hash_string (const char *str, int len) ATTRIBUTE_PURE ATTRIBUTE_HIDDEN; /* This computes the length of a String object OOP. */ extern int _gst_string_oop_len (OOP oop) ATTRIBUTE_PURE ATTRIBUTE_HIDDEN; /* This returns the number of arguments declared in the current scope. */ extern int _gst_get_arg_count (void) ATTRIBUTE_PURE ATTRIBUTE_HIDDEN; /* This returns the number of temporaries declared in the current scope. */ extern int _gst_get_temp_count (void) ATTRIBUTE_PURE ATTRIBUTE_HIDDEN; /* This adds the arguments corresponding to the message declaration in ARGS to the list of arguments in the current scope. Note that this handles unary, binary and keyword expressions. Arguments must be declared before temporaries, so this resets the number of temporaries in the current scope to 0 and absorbs any temporaries into the arguments. The number of arguments is returned. */ extern int _gst_declare_arguments (tree_node args) ATTRIBUTE_HIDDEN; /* This adds the declarations in TEMPS to the list of arguments in the current scope. */ extern int _gst_declare_temporaries (tree_node temps) ATTRIBUTE_HIDDEN; /* This adds the arguments corresponding to the message declaration in ARGS to the list of arguments in the current scope. Note that this does not handle unary, binary and keyword expressions, but only blocks. Arguments must be declared before temporaries, so this resets the number of temporaries in the current scope to 0 and absorbs any temporaries into the arguments. The number of arguments is returned. */ extern int _gst_declare_block_arguments (tree_node args) ATTRIBUTE_HIDDEN; /* Declare the argument or temporary variable whose name is pointed to by NAME as either WRITEABLE or not. A Symbol corresponding to NAME is created and links a new entry inside the symbol list for the currently active scope. Unless ALLOWDUP is true, search for a variable with the same name in the currently active scope and return -1 if one is found; otherwise, return the index of the variable into the activation record. */ extern int _gst_declare_name (const char *name, mst_Boolean writeable, mst_Boolean allowDup) ATTRIBUTE_HIDDEN; /* Computes the number of arguments that a message named SYMBOLOOP expects. */ extern int _gst_selector_num_args (OOP symbolOOP) ATTRIBUTE_PURE ATTRIBUTE_HIDDEN; /* This removes from the current scope the knowledge of the last declared temporary variable. */ extern void _gst_undeclare_name (void) ATTRIBUTE_HIDDEN; /* This adds a new scope (corresponding to a level of block nesting) to the linked list of scopes. */ extern void _gst_push_new_scope (void) ATTRIBUTE_HIDDEN; /* Convert a lightweight class (instance of Behavior) or a Metaclass into the corresponding Class object. */ extern OOP _gst_get_class_object (OOP classOOP) ATTRIBUTE_HIDDEN; /* Find a pragma handler for the given selector into the class and its superclasses. */ extern OOP _gst_find_pragma_handler (OOP classOOP, OOP symbolOOP) ATTRIBUTE_HIDDEN; /* This removes the outermost scope (corresponding to a level of block nesting) to the linked list of scopes. */ extern void _gst_pop_old_scope (void) ATTRIBUTE_HIDDEN; /* This frees the whole linked list of scopes. */ extern void _gst_pop_all_scopes (void) ATTRIBUTE_HIDDEN; /* For debugging purposes, this prints the declaration of ENT. */ extern void _gst_print_symbol_entry (symbol_entry * ent) ATTRIBUTE_HIDDEN; /* This routine is used for symbol table debugging only. */ extern void _gst_print_symbols (void) ATTRIBUTE_HIDDEN; /* This routine initializes the variables containing the Symbols known to the VM. This one creates the symbol OOPs, which have to be consecutive in order to speed up the load. */ extern void _gst_init_symbols_pass1 (void) ATTRIBUTE_HIDDEN; /* This one creates the SymLink OOPs for the Symbols previously created. */ extern void _gst_init_symbols_pass2 (void) ATTRIBUTE_HIDDEN; /* This routine reloads the variables containing the Symbols known to the VM. It is invocated upon image load. */ extern void _gst_restore_symbols (void) ATTRIBUTE_HIDDEN; extern void _gst_check_symbol_chain (void) ATTRIBUTE_HIDDEN; #ifdef HAVE_READLINE extern void _gst_add_all_symbol_completions (void) ATTRIBUTE_HIDDEN; #endif struct builtin_selector { int offset; OOP symbol; int numArgs; int bytecode; }; extern struct builtin_selector _gst_builtin_selectors[256] ATTRIBUTE_HIDDEN; extern struct builtin_selector *_gst_lookup_builtin_selector (const char *str, unsigned int len) ATTRIBUTE_HIDDEN; #endif /* GST_SYM_H */ smalltalk-3.2.5/libgst/genvm-parse.h0000644000175000017500000000503512130455565014320 00000000000000/* A Bison parser, made by GNU Bison 2.5. */ /* Bison interface for Yacc-like parsers in C Copyright (C) 1984, 1989-1990, 2000-2011 Free Software Foundation, Inc. This program is free software: you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation, either version 3 of the License, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program. If not, see . */ /* As a special exception, you may create a larger work that contains part or all of the Bison parser skeleton and distribute that work under terms of your choice, so long as that work isn't itself a parser generator using the skeleton or a modified version thereof as a parser skeleton. Alternatively, if you modify or redistribute the parser skeleton itself, you may (at your option) remove this special exception, which will cause the skeleton and the resulting Bison output files to be licensed under the GNU General Public License without this special exception. This special exception was added by the Free Software Foundation in version 2.2 of Bison. */ /* Tokens. */ #ifndef YYTOKENTYPE # define YYTOKENTYPE /* Put the tokens into the symbol table, so that GDB and other debuggers know about them. */ enum yytokentype { ID = 258, EXPR = 259, NUMBER = 260, VM_OPERATION = 261, VM_TABLE = 262, VM_BYTECODE = 263, VM_DOTS = 264, VM_MINUSMINUS = 265 }; #endif /* Tokens. */ #define ID 258 #define EXPR 259 #define NUMBER 260 #define VM_OPERATION 261 #define VM_TABLE 262 #define VM_BYTECODE 263 #define VM_DOTS 264 #define VM_MINUSMINUS 265 #if ! defined YYSTYPE && ! defined YYSTYPE_IS_DECLARED typedef union YYSTYPE { /* Line 2068 of yacc.c */ #line 127 "genvm-parse.y" struct operation_list *oplist; struct operation_info *op; struct table_info *tab; struct id_list *id; const char *ctext; char *text; int num; /* Line 2068 of yacc.c */ #line 82 "genvm-parse.h" } YYSTYPE; # define YYSTYPE_IS_TRIVIAL 1 # define yystype YYSTYPE /* obsolescent; will be withdrawn */ # define YYSTYPE_IS_DECLARED 1 #endif extern YYSTYPE yylval; smalltalk-3.2.5/libgst/str.h0000644000175000017500000000630112123404352012667 00000000000000/******************************** -*- C -*- **************************** * * Simple string support * * ***********************************************************************/ /*********************************************************************** * * Copyright 1988,89,90,91,92,94,95,99,2000,2001,2002,2006 * Free Software Foundation, Inc. * Written by Steve Byrne. * * This file is part of GNU Smalltalk. * * GNU Smalltalk is free software; you can redistribute it and/or modify it * under the terms of the GNU General Public License as published by the Free * Software Foundation; either version 2, or (at your option) any later * version. * * Linking GNU Smalltalk statically or dynamically with other modules is * making a combined work based on GNU Smalltalk. Thus, the terms and * conditions of the GNU General Public License cover the whole * combination. * * In addition, as a special exception, the Free Software Foundation * give you permission to combine GNU Smalltalk with free software * programs or libraries that are released under the GNU LGPL and with * independent programs running under the GNU Smalltalk virtual machine. * * You may copy and distribute such a system following the terms of the * GNU GPL for GNU Smalltalk and the licenses of the other code * concerned, provided that you include the source code of that other * code when and as the GNU GPL requires distribution of source code. * * Note that people who make modified versions of GNU Smalltalk are not * obligated to grant this special exception for their modified * versions; it is their choice whether to do so. The GNU General * Public License gives permission to release a modified version without * this exception; this exception also makes it possible to release a * modified version which carries forward this exception. * * GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or * FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for * more details. * * You should have received a copy of the GNU General Public License along with * GNU Smalltalk; see the file COPYING. If not, write to the Free Software * Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * ***********************************************************************/ #ifndef GST_STR_H #define GST_STR_H /* Returns the currently accumulated buffer, and resets the pointer to start with a new string. Instead of allocating fresh memory for the data, it is moved to the location pointed by WHERE. WHERE is returned */ extern PTR _gst_copy_buffer (PTR where) ATTRIBUTE_HIDDEN; /* Answer the current size of the buffer. */ extern size_t _gst_buffer_size (void) ATTRIBUTE_HIDDEN; /* Resets the pointer to start with a new string. */ extern void _gst_reset_buffer (void) ATTRIBUTE_HIDDEN; /* Adds a pointer PTR to the buffer being built. */ extern void _gst_add_buf_pointer (PTR ptr) ATTRIBUTE_HIDDEN; /* Adds N bytes of data starting from PTR to the string being accumulated. */ extern void _gst_add_buf_data (PTR ptr, int n) ATTRIBUTE_HIDDEN; #endif /* GST_STR_H */ smalltalk-3.2.5/libgst/byte.c0000644000175000017500000002675512130343734013040 00000000000000/******************************** -*- C -*- **************************** * * Byte code array utility routines. * * ***********************************************************************/ /*********************************************************************** * * Copyright 1988,89,90,91,92,94,95,99,2000,2001,2002,2003,2006,2008,2009 * Free Software Foundation, Inc. * Written by Steve Byrne. * * This file is part of GNU Smalltalk. * * GNU Smalltalk is free software; you can redistribute it and/or modify it * under the terms of the GNU General Public License as published by the Free * Software Foundation; either version 2, or (at your option) any later * version. * * Linking GNU Smalltalk statically or dynamically with other modules is * making a combined work based on GNU Smalltalk. Thus, the terms and * conditions of the GNU General Public License cover the whole * combination. * * In addition, as a special exception, the Free Software Foundation * give you permission to combine GNU Smalltalk with free software * programs or libraries that are released under the GNU LGPL and with * independent programs running under the GNU Smalltalk virtual machine. * * You may copy and distribute such a system following the terms of the * GNU GPL for GNU Smalltalk and the licenses of the other code * concerned, provided that you include the source code of that other * code when and as the GNU GPL requires distribution of source code. * * Note that people who make modified versions of GNU Smalltalk are not * obligated to grant this special exception for their modified * versions; it is their choice whether to do so. The GNU General * Public License gives permission to release a modified version without * this exception; this exception also makes it possible to release a * modified version which carries forward this exception. * * GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or * FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for * more details. * * You should have received a copy of the GNU General Public License along with * GNU Smalltalk; see the file COPYING. If not, write to the Free Software * Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * ***********************************************************************/ #include "gstpriv.h" #include "match.h" #define BYTECODE_CHUNK_SIZE 64 /* Where the compiled bytecodes go. */ bc_vector _gst_cur_bytecodes; /* Reallocate an array of bytecodes, leaving space for DELTA more bytes. */ static void realloc_bytecodes (bc_vector bytecodes, int delta); bc_vector _gst_extract_bytecodes (OOP byteArrayOOP) { bc_vector result; int len; gst_byte_array byteArray; byteArray = (gst_byte_array) OOP_TO_OBJ (byteArrayOOP); len = oop_num_fields (byteArrayOOP); result = (bc_vector) xmalloc (sizeof (struct bytecode_array)); result->base = (gst_uchar *) xmalloc (len); result->ptr = result->base + len; result->maxLen = len; memcpy (result->base, byteArray->bytes, len); return (result); } static int next_line_number; static void compile_byte (gst_uchar byte, int arg) { int num_bytes; long n; for (num_bytes = 2, n = arg; n > 255; n >>= 8) num_bytes += 2; assert (_gst_cur_bytecodes); if ((_gst_cur_bytecodes->ptr - _gst_cur_bytecodes->base) > _gst_cur_bytecodes->maxLen - num_bytes) realloc_bytecodes (_gst_cur_bytecodes, BYTECODE_CHUNK_SIZE); while (num_bytes > 2) { num_bytes -= 2; *_gst_cur_bytecodes->ptr++ = EXT_BYTE; *_gst_cur_bytecodes->ptr++ = (arg >> (num_bytes * 4)) & 255; } *_gst_cur_bytecodes->ptr++ = byte; *_gst_cur_bytecodes->ptr++ = arg & 255; } void _gst_line_number (int n, int flags) { static int prev_line; static int line_offset; if (n > 65535) n = 65535; if (flags & LN_RESET) { assert (!(flags & LN_FORCE)); assert (n > 0); if (flags & LN_ABSOLUTE) { compile_byte (LINE_NUMBER_BYTECODE, n); prev_line = n; } line_offset = n - 1; next_line_number = -1; } else { assert (!(flags & LN_ABSOLUTE)); if (n == -1) { prev_line = -1; next_line_number = -1; } else { assert (n > line_offset); if ((flags & LN_FORCE) || n != prev_line) { prev_line = n; next_line_number = n - line_offset; } } } } void _gst_compile_byte (gst_uchar byte, int arg) { if (next_line_number != -1) { compile_byte (LINE_NUMBER_BYTECODE, next_line_number); next_line_number = -1; } compile_byte (byte, arg); } void _gst_free_bytecodes (bc_vector bytecodes) { if (bytecodes != NULL) { xfree (bytecodes->base); xfree (bytecodes); } } void _gst_compile_and_free_bytecodes (bc_vector bytecodes) { _gst_compile_bytecodes (bytecodes->base, bytecodes->ptr); /* First add the worst case, then leave the net effect. */ ADD_STACK_DEPTH (bytecodes->max_stack_depth); SUB_STACK_DEPTH (bytecodes->max_stack_depth - bytecodes->stack_depth); _gst_free_bytecodes (bytecodes); } bc_vector _gst_get_bytecodes (void) { bc_vector curBytecodes; curBytecodes = _gst_cur_bytecodes; _gst_cur_bytecodes = NULL; return (curBytecodes); } bc_vector _gst_save_bytecode_array () { bc_vector curBytecodes; curBytecodes = _gst_cur_bytecodes; _gst_alloc_bytecodes (); return (curBytecodes); } void _gst_restore_bytecode_array (bc_vector bytecodes) { _gst_cur_bytecodes = bytecodes; } int _gst_bytecode_length (bc_vector bytecodes) { if (bytecodes == NULL) return (0); return (bytecodes->ptr - bytecodes->base); } int _gst_current_bytecode_length (void) { if (_gst_cur_bytecodes == NULL) return (0); return (_gst_cur_bytecodes->ptr - _gst_cur_bytecodes->base); } void _gst_copy_bytecodes (gst_uchar * dest, bc_vector bytecodes) { memcpy (dest, bytecodes->base, _gst_bytecode_length (bytecodes)); } void _gst_truncate_bytecodes (gst_uchar * here, bc_vector bytecodes) { bytecodes->ptr = here; } void _gst_print_bytecodes (bc_vector bytecodes, OOP * literal_vec) { gst_uchar *b; int ip; if (bytecodes == NULL) return; for (b = bytecodes->base; b < bytecodes->ptr; ) { ip = b - bytecodes->base; printf ("%5d:", ip); b = _gst_print_bytecode_name (b, ip, literal_vec, ""); } printf ("\n"); } gst_uchar * _gst_print_bytecode_name (gst_uchar * bp, int ip, OOP * literal_vec, const char *pref) { const char *prefix = ""; gst_uchar b = *bp; MATCH_BYTECODES (PRINT_BYTECODE_NAME, bp, ( PUSH_RECEIVER_VARIABLE { printf ("%s\tpush Instance Variable[%d]\n", prefix, n); prefix = pref; } PUSH_TEMPORARY_VARIABLE { printf ("%s\tpush Temporary Variable[%d]\n", prefix, n); prefix = pref; } PUSH_LIT_CONSTANT { printf ("%s\tpush Literal[%d]", prefix, n); if (literal_vec) printf (" = %O", literal_vec[n]); printf ("\n"); prefix = pref; } PUSH_LIT_VARIABLE { printf ("%s\tpush Global Variable[%d]", prefix, n); if (literal_vec) printf (" = %+O", literal_vec[n]); printf ("\n"); prefix = pref; } PUSH_SELF { printf ("%s\tpush self\n", prefix); prefix = pref; } PUSH_SPECIAL { switch (n) { case TRUE_INDEX: printf ("%s\tpush true\n", prefix); break; case FALSE_INDEX: printf ("%s\tpush false\n", prefix); break; case NIL_INDEX: printf ("%s\tpush nil\n", prefix); break; } prefix = pref; } PUSH_INTEGER { printf ("%s\tpush %d\n", prefix, n); prefix = pref; } RETURN_METHOD_STACK_TOP { printf ("%s\treturn explicitly from method\n", prefix); prefix = pref; } RETURN_CONTEXT_STACK_TOP { printf ("%s\treturn stack top\n", prefix); prefix = pref; } LINE_NUMBER_BYTECODE { printf ("%s\tsource line %d\n", prefix, n); prefix = pref; } STORE_RECEIVER_VARIABLE { printf ("%s\tstore into Instance Variable[%d]\n", prefix, n); prefix = pref; } STORE_TEMPORARY_VARIABLE { printf ("%s\tstore into Temporary Variable[%d]\n", prefix, n); prefix = pref; } STORE_LIT_VARIABLE { printf ("%s\tstore into Global Variable[%d]", prefix, n); if (literal_vec) printf (" = %+O", literal_vec[n]); printf ("\n"); prefix = pref; } SEND { printf ("%s\tsend selector %d%s, %d args", prefix, n, super ? " to super" : "", num_args); if (literal_vec) printf (" = %O", literal_vec[n]); printf ("\n"); prefix = pref; } POP_INTO_NEW_STACKTOP { printf ("%s\tpop and store into Instance Variable[%d] of new stack top\n", prefix, n); prefix = pref; } POP_STACK_TOP { printf ("%s\tpop stack top\n", prefix); prefix = pref; } DUP_STACK_TOP { printf ("%s\tduplicate stack top\n", prefix); prefix = pref; } PUSH_OUTER_TEMP { printf ("%s\tpush outer var scopes = %d varIndex = %d\n", prefix, scopes, n); prefix = pref; } STORE_OUTER_TEMP { printf ("%s\tstore outer var scopes = %d varIndex = %d\n", prefix, scopes, n); prefix = pref; } EXIT_INTERPRETER { printf ("%s\tterminate interpreter\n", prefix); prefix = pref; } JUMP { printf ("%s\tjump to %d\n", prefix, ip + ofs); prefix = pref; } POP_JUMP_TRUE { printf ("%s\tpop and jump to %d if true\n", prefix, ip + ofs); prefix = pref; } POP_JUMP_FALSE { printf ("%s\tpop and jump to %d if false\n", prefix, ip + ofs); prefix = pref; } SEND_ARITH { printf ("%s\tsend arithmetic message %O\n", prefix, _gst_builtin_selectors[n].symbol); prefix = pref; } SEND_SPECIAL { printf ("%s\tsend special message %O\n", prefix, _gst_builtin_selectors[n + 16].symbol); prefix = pref; } MAKE_DIRTY_BLOCK { printf ("%s\tmake dirty block\n", prefix); prefix = pref; } SEND_IMMEDIATE { printf ("%s\tsend special message %O%s\n", prefix, _gst_builtin_selectors[n].symbol, super ? " to super" : ""); prefix = pref; } INVALID { printf ("%s\tINVALID BYTECODE %d(%d)\n", prefix, b, arg); prefix = pref; } )); return bp; } void _gst_compile_bytecodes (gst_uchar * from, gst_uchar * to) { int free; assert (_gst_cur_bytecodes); free = _gst_cur_bytecodes->maxLen - (_gst_cur_bytecodes->ptr - _gst_cur_bytecodes->base); if (free < (to - from)) { memcpy (_gst_cur_bytecodes->ptr, from, free); _gst_cur_bytecodes->ptr += free; from += free; realloc_bytecodes (_gst_cur_bytecodes, BYTECODE_CHUNK_SIZE + (to - from)); } memcpy (_gst_cur_bytecodes->ptr, from, to - from); _gst_cur_bytecodes->ptr += to - from; } void _gst_alloc_bytecodes () { bc_vector newBytecodes; newBytecodes = (bc_vector) xmalloc (sizeof (struct bytecode_array)); newBytecodes->base = (gst_uchar *) xmalloc (BYTECODE_CHUNK_SIZE); newBytecodes->ptr = newBytecodes->base; newBytecodes->maxLen = BYTECODE_CHUNK_SIZE; newBytecodes->stack_depth = 0; newBytecodes->max_stack_depth = 0; _gst_cur_bytecodes = newBytecodes; } void realloc_bytecodes (bc_vector bytecodes, int delta) { int size; size = bytecodes->ptr - bytecodes->base; bytecodes->base = (gst_uchar *) xrealloc (bytecodes->base, bytecodes->maxLen + delta); bytecodes->ptr = bytecodes->base + size; bytecodes->maxLen += delta; } smalltalk-3.2.5/libgst/mpz.h0000644000175000017500000001160212123404352012665 00000000000000/******************************** -*- C -*- **************************** * * Definitions for GNU Smalltalk's multiple precision functions * * ***********************************************************************/ /*********************************************************************** * * Copyright 1991, 2002, 2009 Free Software Foundation, Inc. * * This file is derived from an absurdly old version of the GNU MP Library. * * The GNU MP library is free software; you can redistribute it and/or * modify it under the terms of the GNU General Public License as * published by the Free Software Foundation; either version 2, or (at * your option) any later version. * * The GNU MP Library is distributed in the hope that it will be * useful, but WITHOUT ANY WARRANTY; without even the implied warranty * of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the * GNU General Public License for more details. * * You should have received a copy of the GNU General Public License * along with the GNU MP library; see the file COPYING. If not, write * to the Free Software Foundation, 51 Franklin Street, Fifth Floor, * Boston, MA 02110-1301, USA. * ***********************************************************************/ #ifndef GST_MPZ_H #define GST_MPZ_H #if HAVE_GMP #include typedef struct { size_t alloc; /* Number of *limbs* allocated and pointed to by the D field. */ ssize_t size; /* abs(SIZE) is the number of limbs the last field points to. If SIZE is negative this is a negative number. */ mp_limb_t *d; /* Pointer to the limbs. */ } gst_mpz; /**************** Integer (i.e. Z) routines. ****************/ /* Add two integers. */ void _gst_mpz_add (gst_mpz *, const gst_mpz *, const gst_mpz *) ATTRIBUTE_HIDDEN; /* Compute the two's complement AND of two integers. */ void _gst_mpz_and (gst_mpz *, const gst_mpz *, const gst_mpz *) ATTRIBUTE_HIDDEN; /* Compute the two's complement inclusive OR of two integers. */ void _gst_mpz_ior (gst_mpz *, const gst_mpz *, const gst_mpz *) ATTRIBUTE_HIDDEN; /* Compute the two's complement XOR of two integers. */ void _gst_mpz_xor (gst_mpz *, const gst_mpz *, const gst_mpz *) ATTRIBUTE_HIDDEN; /* Assign the bit-complemented value of an integer to another */ void _gst_mpz_com (gst_mpz *dst, const gst_mpz *src) ATTRIBUTE_HIDDEN; /* Subtract two integers. */ void _gst_mpz_sub (gst_mpz *, const gst_mpz *, const gst_mpz *) ATTRIBUTE_HIDDEN; /* Multiply two integers. */ void _gst_mpz_mul (gst_mpz *, const gst_mpz *, const gst_mpz *) ATTRIBUTE_HIDDEN; /* Floor DIVision, with Quotient and Remainder, i.e. division that rounds the quotient towards -infinity, and with the remainder non-negative. */ void _gst_mpz_fdiv_qr (gst_mpz *, gst_mpz *, const gst_mpz *, const gst_mpz *) ATTRIBUTE_HIDDEN; /* Floor DIVision by a Signed Integer, with Quotient and Remainder. */ mp_limb_t _gst_mpz_fdiv_qr_si (gst_mpz *quot, const gst_mpz *num, intptr_t den) ATTRIBUTE_HIDDEN; /* Truncated DIVision, with Quotient and Remainder. */ void _gst_mpz_tdiv_qr (gst_mpz *, gst_mpz *, const gst_mpz *, const gst_mpz *) ATTRIBUTE_HIDDEN; /* Truncated DIVision by a Signed Integer, with Quotient and Remainder. */ mp_limb_t _gst_mpz_tdiv_qr_si (gst_mpz *quot, const gst_mpz *num, intptr_t den) ATTRIBUTE_HIDDEN; /* Greatest Common Divisor of two numbers. */ void _gst_mpz_gcd (gst_mpz *, const gst_mpz *, const gst_mpz *) ATTRIBUTE_HIDDEN; /* Compare two integers U, V. Return positive, zero, or negative based on if U > V, U == V, or U < V. */ int _gst_mpz_cmp (const gst_mpz *, const gst_mpz *) ATTRIBUTE_HIDDEN; /* Convert to double */ mst_Boolean _gst_mpz_get_d (const gst_mpz *, double *) ATTRIBUTE_HIDDEN; /* Convert to long double */ mst_Boolean _gst_mpz_get_ld (const gst_mpz *, long double *) ATTRIBUTE_HIDDEN; /* Multiply an integer by 2**CNT */ void _gst_mpz_mul_2exp (gst_mpz *, const gst_mpz *, unsigned) ATTRIBUTE_HIDDEN; /* Divide an integer by 2**CNT */ void _gst_mpz_div_2exp (gst_mpz *, const gst_mpz *, unsigned) ATTRIBUTE_HIDDEN; /* Divide with no remainder. */ void _gst_mpz_divexact (gst_mpz *, const gst_mpz *, const gst_mpz *) ATTRIBUTE_HIDDEN; /* Allocate space for an integer if necessary, and assign an integer from another one. */ void _gst_mpz_set (gst_mpz *, const gst_mpz *) ATTRIBUTE_HIDDEN; /* Free an integer */ void _gst_mpz_clear (gst_mpz *m) ATTRIBUTE_HIDDEN; /* Create an integer from an OOP (an instance of a subclass of Integer). Space from the object itself is pointed to on little-endian machines, so you should care that no GC's happen while we're manipulating integers. */ void _gst_mpz_from_oop (gst_mpz *, OOP) ATTRIBUTE_HIDDEN; /* Create an OOP (an instance of a subclass of Integer) from a big integer. */ OOP _gst_oop_from_mpz (gst_mpz *) ATTRIBUTE_HIDDEN; #endif #endif /* GST_MPZ_H */ smalltalk-3.2.5/libgst/gst-parse.c0000644000175000017500000014660312130343734013775 00000000000000/******************************** -*- C -*- **************************** * * GNU Smalltalk language grammar definition * ***********************************************************************/ /*********************************************************************** * * Copyright 2005, 2006, 2007, 2008, 2009 Free Software Foundation, Inc. * Written by Paolo Bonzini. * * This file is part of GNU Smalltalk. * * GNU Smalltalk is free software; you can redistribute it and/or modify it * under the terms of the GNU General Public License as published by the Free * Software Foundation; either version 2, or (at your option) any later * version. * * Linking GNU Smalltalk statically or dynamically with other modules is * making a combined work based on GNU Smalltalk. Thus, the terms and * conditions of the GNU General Public License cover the whole * combination. * * In addition, as a special exception, the Free Software Foundation * give you permission to combine GNU Smalltalk with free software * programs or libraries that are released under the GNU LGPL and with * independent programs running under the GNU Smalltalk virtual machine. * * You may copy and distribute such a system following the terms of the * GNU GPL for GNU Smalltalk and the licenses of the other code * concerned, provided that you include the source code of that other * code when and as the GNU GPL requires distribution of source code. * * Note that people who make modified versions of GNU Smalltalk are not * obligated to grant this special exception for their modified * versions; it is their choice whether to do so. The GNU General * Public License gives permission to release a modified version without * this exception; this exception also makes it possible to release a * modified version which carries forward this exception. * * GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or * FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for * more details. * * You should have received a copy of the GNU General Public License along with * GNU Smalltalk; see the file COPYING. If not, write to the Free Software * Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * ***********************************************************************/ #include "gst.h" #include "gstpriv.h" #include "gst-parse.h" #include #include typedef enum expr_kinds { EXPR_ASSIGNMENT = 1, EXPR_GREATER = 2, EXPR_BINOP = 4, EXPR_KEYWORD = 8, EXPR_CASCADE = 16, EXPR_CASCADED = EXPR_GREATER | EXPR_BINOP | EXPR_KEYWORD, EXPR_ANY = 31 } expr_kinds; /* Used to communicate with the #methodsFor: primitive. */ gst_parser *_gst_current_parser; static inline mst_Boolean is_unlikely_selector (const char *); /* Lexer interface. */ static inline void lex_init (gst_parser *p); static inline void lex_lookahead (gst_parser *p, int n); static inline void lex_consume (gst_parser *p, int n); static inline void lex (gst_parser *p); static inline int token (gst_parser *p, int n); static inline YYSTYPE *val (gst_parser *p, int n); static inline YYLTYPE *loc (gst_parser *p, int n); static inline void lex_must_be (gst_parser *p, int req_token); static inline void lex_skip_mandatory (gst_parser *p, int req_token); static inline mst_Boolean lex_skip_if (gst_parser *p, int req_token, mst_Boolean fail_at_eof); /* Error recovery. */ static void expected (gst_parser *p, int token, ...) ATTRIBUTE_NORETURN; static void recover_error (gst_parser *p) ATTRIBUTE_NORETURN; static int filprintf (Filament *fil, const char *format, ...); /* Grammar productions. */ static void parse_chunks (gst_parser *p); static void parse_doit (gst_parser *p, mst_Boolean fail_at_eof); static mst_Boolean parse_scoped_definition (gst_parser *p, tree_node first_stmt); static void parse_eval_definition (gst_parser *p); static mst_Boolean parse_and_send_attribute (gst_parser *p, OOP receiverOOP); static mst_Boolean parse_namespace_definition (gst_parser *p, tree_node first_stmt); static mst_Boolean parse_class_definition (gst_parser *p, OOP classOOP, mst_Boolean extend); static OOP parse_namespace (tree_node name); static OOP parse_class (tree_node list); static void parse_scoped_method (gst_parser *p, OOP classOOP); static void parse_instance_variables (gst_parser *p, OOP classOOP, mst_Boolean extend); static void parse_method_list (gst_parser *p); static void parse_method (gst_parser *p, int at_end); static tree_node parse_message_pattern (gst_parser *p); static tree_node parse_keyword_variable_list (gst_parser *p); static tree_node parse_variable (gst_parser *p); static tree_node parse_attributes (gst_parser *p, tree_node prev_attrs); static tree_node parse_attribute (gst_parser *p); static tree_node parse_temporaries (gst_parser *p, mst_Boolean implied_pipe); static tree_node parse_statements (gst_parser *p, tree_node first_stmt, mst_Boolean accept_caret); static tree_node parse_required_expression (gst_parser *p); static tree_node parse_expression (gst_parser *p, enum expr_kinds kind); static tree_node parse_primary (gst_parser *p); static tree_node parse_variable_primary (gst_parser *p); static tree_node parse_literal (gst_parser *p, mst_Boolean array); static tree_node parse_array_literal (gst_parser *p); static tree_node parse_builtin_identifier (gst_parser *p); static tree_node parse_byte_array_literal (gst_parser *p); static tree_node parse_binding_constant (gst_parser *p); static tree_node parse_compile_time_constant (gst_parser *p); static tree_node parse_array_constructor (gst_parser *p); static tree_node parse_block (gst_parser *p); static tree_node parse_block_variables (gst_parser *p); static tree_node parse_message_expression (gst_parser *p, tree_node receiver, enum expr_kinds kind); static tree_node parse_cascaded_messages (gst_parser *p); static tree_node parse_unary_expression (gst_parser *p, tree_node receiver, enum expr_kinds kind); static tree_node parse_binary_expression (gst_parser *p, tree_node receiver, enum expr_kinds kind); static tree_node parse_keyword_expression (gst_parser *p, tree_node receiver, enum expr_kinds kind); static tree_node parse_keyword_list (gst_parser *p, enum expr_kinds kind); static int filprintf (Filament *fil, const char *format, ...) { va_list ap; STREAM *out = stream_new (fil, SNV_UNLIMITED, NULL, snv_filputc); int result; va_start (ap, format); result = stream_vprintf (out, format, ap); va_end (ap); stream_delete (out); return result; } /* Lexer interface. Intialize the parser before using it. */ static inline void lex_init (gst_parser *p) { p->la_first = 0; p->la_size = 0; lex_lookahead (p, 1); } /* Lexer interface. Get N tokens out of the stream. */ static inline void lex_lookahead (gst_parser *p, int n) { while (p->la_size < n) { int i = (p->la_first + p->la_size) % 4; p->la[i].token = _gst_yylex (&p->la[i].val, &p->la[i].loc); p->la_size++; } } /* Lexer interface. Eat the first N lookahead tokens. */ static inline void lex_consume (gst_parser *p, int n) { p->la_first = (p->la_first + n) % 4; p->la_size -= n; } /* Lexer interface. Eat the last lookahead token and lex the next one */ static inline void lex (gst_parser *p) { lex_consume (p, 1); lex_lookahead (p, 1); } /* Lexer interface. Return the N-th lookahead token. */ static inline int token (gst_parser *p, int n) { int i = (p->la_first + n) % 4; return p->la[i].token; } /* Lexer interface. Return the value of the N-th lookahead token. */ static inline YYSTYPE* val (gst_parser *p, int n) { int i = (p->la_first + n) % 4; return &p->la[i].val; } /* Lexer interface. Return the location of the N-th lookahead token. */ static inline YYLTYPE* loc (gst_parser *p, int n) { int i = (p->la_first + n) % 4; return &p->la[i].loc; } /* Lexer interface. Check that the next token is REQ_TOKEN and fail if it is not. */ static inline void lex_must_be (gst_parser *p, int req_token) { if (token (p, 0) != req_token) expected (p, req_token, -1); } /* Lexer interface. Check that the next token is REQ_TOKEN and eat it; fail if it does not match. */ static inline void lex_skip_mandatory (gst_parser *p, int req_token) { if (token (p, 0) != req_token) expected (p, req_token, -1); else lex (p); } /* Lexer interface. If the next token is REQ_TOKEN, eat it and return true; otherwise return false. */ static inline mst_Boolean lex_skip_if (gst_parser *p, int req_token, mst_Boolean fail_at_eof) { if (token (p, 0) != req_token) { if (token (p, 0) == EOF && fail_at_eof) expected (p, req_token, -1); return false; } else { lex (p); return true; } } void _gst_print_tokens (gst_parser *p) { int i; printf ("size: %i\n", p->la_size); for (i = 0; i < p->la_size; i++) { if (token (p, i) == 264) printf ("%i - %i - %s\n", i, token (p, i), val (p, i)->sval); else printf ("%i - %i\n", i, token (p, i)); } printf ("\n"); } /* Top of the descent. */ void _gst_parse_method () { gst_parser p, *prev_parser = _gst_current_parser; _gst_current_parser = &p; p.state = PARSE_METHOD; lex_init (&p); if (setjmp (p.recover) == 0) parse_method (&p, ']'); else _gst_had_error = false; _gst_current_parser = prev_parser; } void _gst_parse_chunks () { gst_parser p, *prev_parser = _gst_current_parser; _gst_current_parser = &p; lex_init (&p); if (token (&p, 0) == SHEBANG) lex (&p); p.state = PARSE_DOIT; setjmp (p.recover); _gst_had_error = false; while (token (&p, 0) != EOF) parse_chunks (&p); _gst_current_parser = prev_parser; } static void parse_chunks (gst_parser *p) { if (lex_skip_if (p, '!', false)) p->state = PARSE_DOIT; else { OOP oldTemporaries = _gst_push_temporaries_dictionary (); jmp_buf old_recover; memcpy (old_recover, p->recover, sizeof (p->recover)); setjmp (p->recover); while (token (p, 0) != EOF && token (p, 0) != '!') { /* Pick the production here, so that subsequent methods are compiled when we come back from an error above. */ if (p->state == PARSE_METHOD_LIST) parse_method_list (p); else parse_doit (p, false); } lex_skip_if (p, '!', false); _gst_pop_temporaries_dictionary (oldTemporaries); memcpy (p->recover, old_recover, sizeof (p->recover)); } } /* Print an error message and attempt error recovery. All the parameters after P (terminated by -1) are tokens that were expected (possibly a subset to make the error message shorter). */ static void expected (gst_parser *p, int token, ...) { int named_tokens = 0; va_list ap; const char *sep = ", expected"; char *msg; Filament *out_fil = filnew (NULL, 0); filprintf (out_fil, "parse error"); va_start (ap, token); while (token != -1) { if (token < 256) { filprintf (out_fil, "%s '%c'", sep, token); sep = " or"; } else named_tokens |= 1 << (token - FIRST_TOKEN); token = va_arg (ap, int); } #define TOKEN_DEF(name, val, str, subsume) \ if ((named_tokens & (1 << (val - FIRST_TOKEN))) != 0 \ && (subsume == -1 \ || (named_tokens & (1 << (subsume - FIRST_TOKEN))) == 0)) \ { \ filprintf (out_fil, "%s %s", sep, str); \ sep = " or"; \ } TOKEN_DEFS #undef TOKEN_DEF msg = fildelete (out_fil); _gst_errorf ("%s", msg); free (msg); recover_error (p); } /* Perform error recovery and longjmp out of the parser. */ static void recover_error (gst_parser *p) { if (p->state != PARSE_METHOD) { _gst_error_recovery = true; /* Find the final bang or, if in the REPL, a newline. */ while (token (p, 0) != EOF && token (p, 0) != '!' && token (p, 0) != ERROR_RECOVERY) lex (p); _gst_error_recovery = false; lex_skip_if (p, ERROR_RECOVERY, false); } longjmp (p->recover, 1); } /* doit: temporaries statements '!' [ method_list '!' ] | empty */ static void parse_doit (gst_parser *p, mst_Boolean fail_at_eof) { tree_node statement = NULL; mst_Boolean caret; if (token (p, 0) == '|') parse_temporaries (p, false); if (token (p, 0) == EOF && !fail_at_eof) return; caret = lex_skip_if (p, '^', false); statement = parse_required_expression (p); if (!caret && lex_skip_if (p, '[', false)) { if (parse_scoped_definition (p, statement)) lex_skip_mandatory (p, ']'); else { while (!lex_skip_if (p, ']', true)) lex (p); } } else if (statement) { _gst_execute_statements (NULL, statement, UNDECLARED_TEMPORARIES, false); /* Because a '.' could be inserted automagically, the next token value might be already on the obstack. Do not free in that case! */ if (p->la_size == 0) _gst_free_tree (); } _gst_had_error = false; /* Do not lex until after _gst_free_tree, or we lose a token! */ lex_skip_if (p, '.', false); } /* scoped_definition: eval_definition | class_definition | namespace_definition */ static mst_Boolean parse_scoped_definition (gst_parser *p, tree_node first_stmt) { OOP classOOP = NULL; tree_node receiver = first_stmt->v_expr.receiver; tree_node expression = first_stmt->v_expr.expression; #if 0 _gst_print_tree (first_stmt, 0); #endif if (first_stmt->nodeType == TREE_VARIABLE_NODE && strcmp (first_stmt->v_list.name, "Eval") == 0) { parse_eval_definition (p); return true; } if (first_stmt->nodeType == TREE_KEYWORD_EXPR && receiver->nodeType == TREE_VARIABLE_NODE && expression->v_list.value->nodeType == TREE_VARIABLE_NODE && expression->v_list.next == NULL) { if (strcmp (receiver->v_list.name, "Namespace") == 0 && strcmp (expression->v_list.name, "current:") == 0) return parse_namespace_definition (p, first_stmt); if (strcmp (expression->v_list.name, "subclass:") == 0 && (classOOP = parse_class (receiver)) != NULL) { const char * name = expression->v_list.value->v_list.name; _gst_msg_sendf (&classOOP, "%o %o subclass: %S", classOOP, name); if (IS_NIL (classOOP)) _gst_had_error = true; else return parse_class_definition (p, classOOP, false); } } else if (first_stmt->nodeType == TREE_UNARY_EXPR && first_stmt->v_expr.selector == _gst_intern_string ("extend")) { OOP namespace_old = _gst_current_namespace; OOP classOrMetaclassOOP = NULL; mst_Boolean ret_value; _gst_register_oop (namespace_old); if (receiver->nodeType == TREE_VARIABLE_NODE) { classOOP = parse_class (receiver); classOrMetaclassOOP = classOOP; } else if (receiver->nodeType == TREE_UNARY_EXPR && receiver->v_expr.selector == _gst_intern_string ("class")) { classOOP = parse_class (receiver->v_expr.receiver); classOrMetaclassOOP = classOOP ? OOP_CLASS (classOOP) : NULL; } if (classOrMetaclassOOP != NULL) { OOP namespace_new = ((gst_class) OOP_TO_OBJ (classOOP))->environment; /* When creating the image, current namespace is not available. */ if (namespace_new != namespace_old) _gst_msg_sendf (NULL, "%v %o current: %o", _gst_namespace_class, namespace_new); ret_value = parse_class_definition (p, classOrMetaclassOOP, true); if (namespace_new != namespace_old) _gst_msg_sendf (NULL, "%v %o current: %o", _gst_namespace_class, namespace_old); _gst_unregister_oop (namespace_old); return ret_value; } } _gst_errorf_at (first_stmt->location.first_line, "expected Eval, Namespace or class definition"); return false; } static void parse_eval_definition (gst_parser *p) { tree_node tmps = NULL, stmts = NULL; OOP oldDictionary = _gst_push_temporaries_dictionary (); jmp_buf old_recover; memcpy (old_recover, p->recover, sizeof (p->recover)); if (setjmp (p->recover) == 0) { tmps = parse_temporaries (p, false); stmts = parse_statements (p, NULL, true); lex_must_be (p, ']'); } if (stmts && !_gst_had_error) { if (_gst_regression_testing) { printf ("\nExecution begins...\n"); fflush (stdout); fflush (stderr); } _gst_execute_statements (tmps, stmts, UNDECLARED_TEMPORARIES, _gst_regression_testing); if (_gst_regression_testing) { if (!_gst_had_error) printf ("returned value is %O\n", _gst_last_returned_value); fflush (stdout); fflush (stderr); } _gst_had_error = false; } assert (p->la_size <= 1); _gst_free_tree (); _gst_pop_temporaries_dictionary (oldDictionary); memcpy (p->recover, old_recover, sizeof (p->recover)); if (_gst_had_error) longjmp (p->recover, 1); } static mst_Boolean parse_and_send_attribute (gst_parser *p, OOP receiverOOP) { OOP selectorOOP, *args; tree_node keyword, value, stmt; int i, nb = 0; #if 0 printf ("parse attribute\n"); #endif lex_skip_mandatory (p, '<'); keyword = parse_keyword_expression (p, NULL, EXPR_KEYWORD); selectorOOP = _gst_compute_keyword_selector (keyword->v_expr.expression); nb = _gst_selector_num_args (selectorOOP); args = alloca (sizeof (*args) * nb); i = 0; for (stmt = keyword->v_expr.expression; stmt; stmt = stmt->v_list.next) { value = stmt->v_list.value; value = _gst_make_statement_list (&value->location, value); args[i] = _gst_execute_statements (NULL, value, UNDECLARED_NONE, true); if (!args[i]) { _gst_had_error = true; break; } i = i + 1; } if (!_gst_had_error) _gst_nvmsg_send (receiverOOP, selectorOOP, args, i); lex_skip_mandatory (p, '>'); return !_gst_had_error; } static mst_Boolean parse_namespace_definition (gst_parser *p, tree_node first_stmt) { tree_node expr = first_stmt->v_expr.expression; OOP new_namespace = parse_namespace (expr->v_list.value); if (new_namespace) { OOP old_namespace = _gst_current_namespace; _gst_register_oop (old_namespace); _gst_msg_sendf (NULL, "%v %o current: %o", _gst_namespace_class, new_namespace); while (token (p, 0) != ']' && token (p, 0) != EOF && token (p, 0) != '!') { if (token (p, 0) == '<') parse_and_send_attribute (p, new_namespace); else parse_doit (p, true); } _gst_msg_sendf (NULL, "%v %o current: %o", _gst_namespace_class, old_namespace); _gst_unregister_oop (old_namespace); return true; } return false; } static mst_Boolean parse_class_definition (gst_parser *p, OOP classOOP, mst_Boolean extend) { mst_Boolean add_inst_vars = extend; for (;;) { int t1, t2, t3; if (_gst_had_error) break; lex_lookahead (p, 1); if (token (p, 0) == ']' || token (p, 0) == EOF) break; #if 0 print_tokens (p); #endif t1 = token (p, 0); switch (t1) { case '>': case '-': case BINOP: case KEYWORD: #if 0 printf ("parse method\n"); #endif _gst_set_compilation_class (classOOP); parse_method (p, ']'); _gst_reset_compilation_category (); continue; case '<': lex_lookahead (p, 2); t2 = token (p, 1); if (t2 == IDENTIFIER) { #if 0 printf ("parse method\n"); #endif _gst_set_compilation_class (classOOP); parse_method (p, ']'); _gst_reset_compilation_category (); continue; } else if (t2 == KEYWORD) { parse_and_send_attribute (p, classOOP); continue; } break; case IDENTIFIER: lex_lookahead (p, 2); t2 = token (p, 1); if (t2 == ASSIGNMENT) { #if 0 printf ("parse class variable\n"); #endif OOP name, class_var_dict, result; tree_node stmt; OOP the_class = classOOP; if (IS_A_METACLASS (classOOP)) the_class = METACLASS_INSTANCE (classOOP); name = _gst_intern_string (val (p, 0)->sval); lex_skip_mandatory (p, IDENTIFIER); lex_skip_mandatory (p, ASSIGNMENT); class_var_dict = _gst_class_variable_dictionary (the_class); if (IS_NIL (class_var_dict)) { gst_class class; class_var_dict = _gst_binding_dictionary_new (8, the_class); class = (gst_class) OOP_TO_OBJ (the_class); class->classVariables = class_var_dict; } stmt = parse_required_expression (p); if (!_gst_had_error) { stmt = _gst_make_statement_list (&stmt->location, stmt); result = _gst_execute_statements (NULL, stmt, UNDECLARED_NONE, true); if (result) DICTIONARY_AT_PUT (class_var_dict, name, result); else _gst_had_error = true; } if (token (p, 0) != ']') lex_skip_mandatory(p, '.'); continue; } else if (t2 == BINOP) { #if 0 printf ("parse method\n"); #endif parse_scoped_method (p, classOOP); continue; } else if (t2 == '[') { #if 0 printf ("parse method\n"); #endif _gst_set_compilation_class (classOOP); parse_method (p, ']'); _gst_reset_compilation_category (); continue; } else if (t2 == SCOPE_SEPARATOR) { #if 0 printf ("parse method qualified name\n"); #endif parse_scoped_method (p, classOOP); continue; } else if (t2 == IDENTIFIER) { lex_lookahead (p, 3); t3 = token (p, 2); if (t3 == BINOP) { #if 0 printf ("parse class method\n"); #endif parse_scoped_method (p, classOOP); continue; } else if (t3 == '[' && strcmp (val (p, 1)->sval, "class") == 0) { #if 0 printf ("parse class protocol\n"); #endif if (_gst_object_is_kind_of (classOOP, _gst_metaclass_class)) { _gst_errorf ("already on class side"); _gst_had_error = true; continue; } else if (((gst_class) OOP_TO_OBJ (classOOP))->name != _gst_intern_string (val (p, 0)->sval)) { _gst_errorf ("`%s class' invalid within %O", val (p, 0)->sval, classOOP); _gst_had_error = true; continue; } else { lex_consume (p, 3); parse_class_definition (p, OOP_CLASS (classOOP), extend); lex_skip_mandatory (p, ']'); } continue; } } break; case '|': lex_lookahead (p, 2); t2 = token (p, 1); if (t2 == '|') { #if 0 printf ("parse instance variables - ignore\n"); #endif lex_consume (p, 2); continue; } else if (t2 == IDENTIFIER) { lex_lookahead (p, 3); t3 = token (p, 2); if (t3 == IDENTIFIER || t3 == '|') { #if 0 printf ("parse instance variables\n"); #endif parse_instance_variables (p, classOOP, add_inst_vars); add_inst_vars = true; continue; } else if (t3 == '[') { #if 0 printf ("parse method\n"); #endif _gst_set_compilation_class (classOOP); parse_method (p, ']'); _gst_reset_compilation_category (); continue; } } break; default: break; } _gst_errorf ("invalid class body element"); _gst_had_error = true; } return !_gst_had_error; } static void parse_scoped_method (gst_parser *p, OOP classOOP) { OOP class, classInstanceOOP; tree_node class_node; mst_Boolean class_method = false; class_node = parse_variable_primary (p); class = parse_class (class_node); if (OOP_CLASS (classOOP) == _gst_metaclass_class) classInstanceOOP = METACLASS_INSTANCE (classOOP); else classInstanceOOP = classOOP; if (token (p, 0) == IDENTIFIER) { if ((strcmp (val (p, 0)->sval, "class") == 0)) { class_method = true; lex_skip_mandatory (p, IDENTIFIER); } else _gst_errorf("expected `class' or `>>'"); } lex_must_be (p, BINOP); if (strcmp (val (p, 0)->sval, ">>") == 0) lex_skip_mandatory (p, BINOP); else _gst_errorf ("expected `>>'"); if (!class_method && OOP_CLASS (classOOP) == _gst_metaclass_class) { _gst_skip_compilation = true; _gst_errorf ("class method expected inside class block"); } else if (!class) { _gst_skip_compilation = true; class = classOOP; } else if (!_gst_class_is_kind_of (classInstanceOOP, class)) { _gst_skip_compilation = true; _gst_errorf ("%#O is not %#O or one of its superclasses", ((gst_class) OOP_TO_OBJ (class))->name, ((gst_class) OOP_TO_OBJ (classOOP))->name); } else { if (class_method) class = OOP_CLASS (class); } _gst_set_compilation_class (class); parse_method (p, ']'); _gst_reset_compilation_category (); _gst_skip_compilation = false; } static OOP parse_class (tree_node list) { const char* name; OOP currentOOP = _gst_current_namespace; tree_node next; if (strcmp (list->v_list.name, "nil") == 0) return _gst_nil_oop; do { name = list->v_list.name; currentOOP = _gst_namespace_at (currentOOP, _gst_intern_string (name)); if (currentOOP == _gst_nil_oop) { _gst_errorf_at (list->location.first_line, "key %s not found", name); return NULL; } next = list->v_list.next; if (next == NULL) { if (!_gst_object_is_kind_of (currentOOP, _gst_class_class)) { _gst_errorf_at (list->location.first_line, "expected class named %s, found %O", name, OOP_INT_CLASS (currentOOP)); return NULL; } } else { if (!_gst_object_is_kind_of (currentOOP, _gst_dictionary_class)) { _gst_errorf_at (list->location.first_line, "expected namespace named %s, found %O", name, OOP_INT_CLASS (currentOOP)); return NULL; } } list = next; } while (list != NULL); return currentOOP; } static OOP parse_namespace (tree_node list) { OOP name, new_namespace, current_namespace; const char *namespc; current_namespace = _gst_current_namespace; while (list->v_list.next != NULL) { name = _gst_intern_string (list->v_list.name); current_namespace = _gst_namespace_at (current_namespace, name); if (current_namespace == _gst_nil_oop) { _gst_errorf_at (list->location.first_line, "key %s not found", list->v_list.name); return NULL; } if (!_gst_object_is_kind_of (current_namespace, _gst_dictionary_class)) { _gst_errorf_at (list->location.first_line, "expected namespace named %s, found %O", list->v_list.name, OOP_INT_CLASS (current_namespace)); return NULL; } list = list->v_list.next; } namespc = list->v_list.name; name = _gst_intern_string (namespc); new_namespace = dictionary_at (current_namespace, name); if (new_namespace == _gst_nil_oop) _gst_msg_sendf (¤t_namespace, "%o %o addSubspace: %o", current_namespace, name); else if (_gst_object_is_kind_of (new_namespace, _gst_dictionary_class)) current_namespace = new_namespace; else _gst_errorf_at (list->location.first_line, "expected namespace named %s, found %O", namespc, OOP_INT_CLASS (new_namespace)); return current_namespace; } /* method_list: method_list method '!' | empty */ static void parse_instance_variables (gst_parser *p, OOP classOOP, mst_Boolean extend) { char *vars; Filament *fil = filnew (NULL, 0); if (extend) { gst_behavior class = (gst_behavior) OOP_TO_OBJ (classOOP); OOP *instVars = OOP_TO_OBJ (class->instanceVariables)->data; int n = CLASS_FIXED_FIELDS (classOOP); OOP superclassOOP = SUPERCLASS (classOOP); if (!IS_NIL (superclassOOP)) { int superclassVars = CLASS_FIXED_FIELDS (superclassOOP); instVars += superclassVars; n -= superclassVars; } for (; n--; instVars++) { char *s = _gst_to_cstring (*instVars); filprintf (fil, "%s ", s); xfree (s); } } lex_skip_mandatory (p, '|'); while (!lex_skip_if (p, '|', true)) { lex_must_be (p, IDENTIFIER); filprintf (fil, "%s ", val (p, 0)->sval); lex (p); } vars = fildelete (fil); _gst_msg_sendf (NULL, "%v %o instanceVariableNames: %S", classOOP, vars); free (vars); } static void parse_method_list (gst_parser *p) { while (token (p, 0) != '!') parse_method (p, '!'); _gst_skip_compilation = false; _gst_reset_compilation_category (); p->state = PARSE_DOIT; } /* method: message_pattern temporaries attributes statements */ static void parse_method (gst_parser *p, int at_end) { tree_node pat, temps, stmts, attrs = NULL; YYLTYPE current_pos; tree_node method; pat = parse_message_pattern (p); if (at_end == ']') lex_skip_mandatory (p, '['); if (token (p, 0) == '<') attrs = parse_attributes (p, NULL); temps = parse_temporaries (p, false); if (token (p, 0) == '<') attrs = parse_attributes (p, attrs); stmts = parse_statements (p, NULL, true); /* Don't lex until _gst_free_tree, or we lose a token. */ lex_must_be (p, at_end); /* Still, include the ']' in the method source code. */ current_pos = _gst_get_location (); if (at_end == ']') current_pos.file_offset++; method = _gst_make_method (&pat->location, ¤t_pos, pat, temps, attrs, stmts, at_end != ']'); if (!_gst_had_error && !_gst_skip_compilation) { enum undeclared_strategy oldUndeclared; oldUndeclared = _gst_set_undeclared (UNDECLARED_GLOBALS); _gst_compile_method (method, false, true); _gst_set_undeclared (oldUndeclared); } assert (p->la_size <= 1); _gst_free_tree (); _gst_had_error = false; if (at_end != EOF) lex (p); } /* message_pattern: unary_pattern | binary_pattern | keyword_pattern unary_pattern: IDENTIFIER binary_pattern: binop IDENTIFIER keyword_pattern: keyword_pattern KEYWORD IDENTIFIER | KEYWORD IDENTIFIER binop : BINOP | '<' | '>' | '-' | '|' */ static tree_node parse_message_pattern (gst_parser *p) { YYLTYPE location = *loc (p, 0); tree_node pat, arg; char *sval = val(p, 0)->sval; switch (token (p, 0)) { case IDENTIFIER: lex (p); pat = _gst_make_unary_expr (&location, NULL, sval); break; case BINOP: case '<': case '>': case '-': case '|': lex (p); arg = parse_variable (p); pat = _gst_make_binary_expr (&location, NULL, sval, arg); break; case KEYWORD: pat = parse_keyword_variable_list (p); pat = _gst_make_keyword_expr (&location, NULL, pat); break; default: expected (p, IDENTIFIER, BINOP, KEYWORD, -1); } return pat; } static tree_node parse_keyword_variable_list (gst_parser *p) { YYLTYPE location = *loc (p, 0); tree_node pat = NULL, arg; do { char *sval = val(p, 0)->sval; lex (p); arg = parse_variable (p); pat = _gst_add_node (pat, _gst_make_keyword_list (&location, sval, arg)); } while (token (p, 0) == KEYWORD); return pat; } /* variable: IDENTIFIER */ static tree_node parse_variable (gst_parser *p) { tree_node var; lex_must_be (p, IDENTIFIER); var = _gst_make_variable (loc (p, 0), val(p, 0)->sval); lex (p); return var; } /* attributes: attributes '<' attribute_keywords '>' | empty attribute_keywords: attribute KEYWORD binary_expr | KEYWORD binary_expr */ static tree_node parse_attributes (gst_parser *p, tree_node prev_attrs) { while (token (p, 0) == '<') { tree_node attr = parse_attribute (p); if (attr) prev_attrs = _gst_add_node (prev_attrs, attr); } return prev_attrs; } static tree_node parse_attribute (gst_parser *p) { tree_node message, attr, constant; OOP attributeOOP, selectorOOP, argsOOP; char *sel; YYLTYPE location = *loc (p, 0); lex_skip_mandatory (p, '<'); if (token (p, 0) == IDENTIFIER) { sel = val(p, 0)->sval; lex (p); selectorOOP = _gst_intern_string (sel); new_instance_with (_gst_array_class, 0, &argsOOP); MAKE_OOP_READONLY (selectorOOP, true); MAKE_OOP_READONLY (argsOOP, true); message = _gst_make_unary_expr (&location, NULL, sel); attributeOOP = _gst_message_new_args (selectorOOP, argsOOP); } else { lex_must_be (p, KEYWORD); message = parse_keyword_list (p, EXPR_BINOP); /* First convert the TREE_KEYWORD_EXPR into a Message object, then into a TREE_CONST_EXPR, and finally embed this one into a TREE_ATTRIBUTE_LIST. */ attributeOOP = _gst_make_attribute (message); } constant = _gst_make_oop_constant (&message->location, attributeOOP); attr = _gst_make_attribute_list (&constant->location, constant); lex_skip_mandatory (p, '>'); return attr; } /* temporaries: '|' variables '|' | empty temp_no_pipe: variables '|' variables: variables variable | empty */ static tree_node parse_temporaries (gst_parser *p, mst_Boolean implied_pipe) { tree_node temps = NULL; if (!implied_pipe && !lex_skip_if (p, '|', false)) return NULL; while (!lex_skip_if (p, '|', true)) { tree_node temp; if (token (p, 0) != IDENTIFIER) expected (p, '|', IDENTIFIER, -1); temp = parse_variable (p); temp = _gst_make_variable_list (&temp->location, temp); temps = _gst_add_node (temps, temp); } return temps; } /* statements: statements_no_ret return_statement opt_dot | statements_no_ret opt_dot statements_no_ret: statements_no_ret '.' statement | empty opt_dot: '.' | empty */ static tree_node parse_statements (gst_parser *p, tree_node first_stmt, mst_Boolean accept_caret) { tree_node stmts, stmt; mst_Boolean caret; if (first_stmt) { stmts = _gst_make_statement_list (&first_stmt->location, first_stmt); if (!lex_skip_if (p, '.', false)) return stmts; } else stmts = NULL; do { caret = accept_caret && lex_skip_if (p, '^', false); if (caret) { stmt = parse_required_expression (p); stmt = _gst_make_return (&stmt->location, stmt); } else { stmt = parse_expression (p, EXPR_ANY); if (stmt == NULL) break; } stmt = _gst_make_statement_list (&stmt->location, stmt); stmts = _gst_add_node (stmts, stmt); } while (lex_skip_if (p, '.', false) && !caret); return stmts; } /* expression: primary | variable ':=' expression | message_expression cascaded_messages */ static tree_node parse_expression (gst_parser *p, enum expr_kinds kind) { tree_node node, assigns = NULL; for (;;) { if (token (p, 0) != IDENTIFIER) { node = parse_primary (p); break; } else { node = parse_variable_primary (p); if (!node || (kind & EXPR_ASSIGNMENT) == 0 || !lex_skip_if (p, ASSIGNMENT, false)) break; } assigns = _gst_add_node (assigns, _gst_make_assignment_list (&node->location, node)); } if (!node && assigns) { _gst_errorf ("expected expression"); recover_error (p); } if (node) { node = parse_message_expression (p, node, kind & ~EXPR_ASSIGNMENT); assert (node); } if (assigns) node = _gst_make_assign (&assigns->location, assigns, node); return node; } static tree_node parse_required_expression (gst_parser *p) { tree_node stmt = parse_expression (p, EXPR_ANY); if (!stmt) { _gst_errorf ("expected expression"); recover_error (p); } return stmt; } /* primary: variable_primary | '(' expression ')' | literal | block | array_constructor */ static tree_node parse_primary (gst_parser *p) { tree_node node; switch (token (p, 0)) { case IDENTIFIER: node = parse_variable_primary (p); break; case STRING_LITERAL: case SYMBOL_LITERAL: case INTEGER_LITERAL: case LARGE_INTEGER_LITERAL: case FLOATD_LITERAL: case FLOATE_LITERAL: case FLOATQ_LITERAL: case SCALED_DECIMAL_LITERAL: case CHAR_LITERAL: case '#': case '-': node = parse_literal (p, false); break; case '[': node = parse_block (p); break; case '{': node = parse_array_constructor (p); break; case '(': lex (p); node = parse_required_expression (p); lex_skip_mandatory (p, ')'); break; default: return NULL; } return node; } /* variable_primary: variable_primary SCOPE_SEPARATOR IDENTIFIER | IDENTIFIER */ static tree_node parse_variable_primary_1 (gst_parser *p, YYLTYPE *first_loc, const char *first_val) { tree_node node; assert (token (p, 0) == IDENTIFIER); node = _gst_make_variable (first_loc, first_val); for (;;) { lex (p); if (!lex_skip_if (p, SCOPE_SEPARATOR, false)) break; lex_must_be (p, IDENTIFIER); node = _gst_add_node (node, _gst_make_variable (loc (p, 0), val(p, 0)->sval)); } return node; } static tree_node parse_variable_primary (gst_parser *p) { return parse_variable_primary_1 (p, loc (p, 0), val(p, 0)->sval); } /* array_literal_elt: array_literal | byte_array_literal | literal | builtin_identifier literal: | '#' array_literal | '#' byte_array_literal | '#' binding_constant | '#' '#' compile_time_constant */ static tree_node parse_literal (gst_parser *p, mst_Boolean array) { tree_node node; int ival; int tok = token (p, 0); switch (tok) { case '-': lex (p); tok = token (p, 0); switch (tok) { case INTEGER_LITERAL: case LARGE_INTEGER_LITERAL: case FLOATD_LITERAL: case FLOATE_LITERAL: case FLOATQ_LITERAL: case SCALED_DECIMAL_LITERAL: if (_gst_negate_yylval (tok, val (p, 0))) return parse_literal (p, array); else { _gst_errorf ("parse error, expected positive numeric literal"); recover_error (p); } default: expected (p, INTEGER_LITERAL, FLOATD_LITERAL, SCALED_DECIMAL_LITERAL, -1); } break; case '(': assert (array); node = parse_array_literal (p); return node; case '[': assert (array); node = parse_byte_array_literal (p); return node; case IDENTIFIER: node = parse_builtin_identifier (p); return node; case STRING_LITERAL: node = _gst_make_string_constant (loc (p, 0), val(p, 0)->sval); break; case SYMBOL_LITERAL: node = _gst_intern_ident (loc (p, 0), val(p, 0)->sval); node = _gst_make_symbol_constant (loc (p, 0), node); break; case INTEGER_LITERAL: node = _gst_make_int_constant (loc (p, 0), val(p, 0)->ival); break; case LARGE_INTEGER_LITERAL: node = _gst_make_byte_object_constant (loc (p, 0), val(p, 0)->boval); break; case FLOATD_LITERAL: node = _gst_make_float_constant (loc (p, 0), val(p, 0)->fval, CONST_FLOATD); break; case FLOATE_LITERAL: node = _gst_make_float_constant (loc (p, 0), val(p, 0)->fval, CONST_FLOATE); break; case FLOATQ_LITERAL: node = _gst_make_float_constant (loc (p, 0), val(p, 0)->fval, CONST_FLOATQ); break; case SCALED_DECIMAL_LITERAL: node = _gst_make_oop_constant (loc (p, 0), val(p, 0)->oval); break; case CHAR_LITERAL: ival = val(p, 0)->ival; lex (p); /* Special case $< INTEGER_LITERAL > where the integer literal is positive. */ if (ival == '<' && token (p, 0) == INTEGER_LITERAL && val(p, 0)->ival >= 0) { ival = val(p, 0)->ival; lex (p); lex_skip_mandatory (p, '>'); if (ival > 0x10FFFF) { _gst_errorf ("character code point out of range"); recover_error (p); } } return _gst_make_char_constant (loc (p, 0), ival); case '#': lex (p); switch (token (p, 0)) { case '(': case '[': return parse_literal (p, true); case '#': return parse_compile_time_constant (p); case '{': return parse_binding_constant (p); default: expected (p, '(', '[', '#', '{', -1); } break; default: return NULL; } lex (p); return node; } /* array_literal: '(' array_literal_elts ')' array_literal_elts: array_literal_elts array_literal_elt | empty */ static tree_node parse_array_literal (gst_parser *p) { tree_node elts = NULL; assert (token (p, 0) == '('); lex (p); while (!lex_skip_if (p, ')', true)) { tree_node lit = parse_literal (p, true); if (lit == NULL) return NULL; elts = _gst_add_node (elts, _gst_make_array_elt (&lit->location, lit)); } return _gst_make_array_constant (elts ? &elts->location : loc (p, 0), elts); } /* builtin_identifier: "true" | "false" | "nil" */ static tree_node parse_builtin_identifier (gst_parser *p) { OOP symbolOOP; tree_node node; YYLTYPE location = *loc(p,0); assert (token (p, 0) == IDENTIFIER); symbolOOP = _gst_intern_string (val(p, 0)->sval); if (symbolOOP == _gst_true_symbol) node = _gst_make_oop_constant (&location, _gst_true_oop); else if (symbolOOP == _gst_false_symbol) node = _gst_make_oop_constant (&location, _gst_false_oop); else if (symbolOOP == _gst_nil_symbol) node = _gst_make_oop_constant (&location, _gst_nil_oop); else { _gst_errorf ("expected true, false or nil"); recover_error (p); } lex (p); return node; } /* byte_array_literal: '[' byte_array_literal_elts ']' byte_array_literal_elts: byte_array_literal_elts INTEGER_LITERAL | empty */ static tree_node parse_byte_array_literal (gst_parser *p) { tree_node elts = NULL; assert (token (p, 0) == '['); lex (p); while (!lex_skip_if (p, ']', true)) { tree_node lit; lex_must_be (p, INTEGER_LITERAL); if (val(p, 0)->ival < 0 || val(p, 0)->ival > 255) { _gst_errorf ("byte constant out of range"); recover_error (p); } lit = _gst_make_int_constant (loc (p, 0), val(p, 0)->ival); lex (p); elts = _gst_add_node (elts, _gst_make_array_elt (&lit->location, lit)); } return _gst_make_byte_array_constant (elts ? &elts->location : loc (p, 0), elts); } /* compile_time_constant: '(' temporaries statements ')' */ static tree_node parse_compile_time_constant (gst_parser *p) { tree_node temps, statements; YYLTYPE location = *loc(p,0); OOP result = NULL; assert (token (p, 0) == '#'); lex (p); lex_skip_mandatory (p, '('); temps = parse_temporaries (p, false); statements = parse_statements (p, NULL, true); lex_skip_mandatory (p, ')'); if (statements && !_gst_had_error) result = _gst_execute_statements (temps, statements, UNDECLARED_NONE, true); return _gst_make_oop_constant (&location, result ? result : _gst_nil_oop); } /* binding_constant: '{' variable_primary '}' */ static tree_node parse_binding_constant (gst_parser *p) { tree_node node; assert (token (p, 0) == '{'); lex (p); lex_must_be (p, IDENTIFIER); node = parse_variable_primary (p); lex_skip_mandatory (p, '}'); return _gst_make_binding_constant (&node->location, node); } /* array_constructor: '{' statements_no_ret '}' */ static tree_node parse_array_constructor (gst_parser *p) { tree_node stmts; YYLTYPE location = *loc(p,0); assert (token (p, 0) == '{'); lex (p); stmts = parse_statements (p, NULL, false); lex_skip_mandatory (p, '}'); return _gst_make_array_constructor (&location, stmts); } /* block: '[' block_vars '||' temps_no_pipe statements ']' | '[' block_vars '|' temporaries statements ']' | '[' block_vars ']' | '[' temporaries statements ']' */ static tree_node parse_block (gst_parser *p) { YYLTYPE location = *loc(p,0); tree_node vars, temps, stmts; mst_Boolean implied_pipe; assert (token (p, 0) == '['); lex (p); if (token (p, 0) == ':') { vars = parse_block_variables (p); if (token (p, 0) == ']') implied_pipe = false; else if (lex_skip_if (p, '|', true)) implied_pipe = false; else if (token (p, 0) == BINOP && val(p, 0)->sval[0] == '|' && val(p, 0)->sval[1] == '|') { implied_pipe = true; lex (p); } else expected (p, ':', '|', ']', -1); } else { vars = NULL; implied_pipe = false; } temps = parse_temporaries (p, implied_pipe); stmts = parse_statements (p, NULL, true); lex_skip_mandatory (p, ']'); return _gst_make_block (&location, vars, temps, stmts); } /* block_vars: ':' IDENTIFIER | block_vars ':' IDENTIFIER */ static tree_node parse_block_variables (gst_parser *p) { tree_node vars = NULL; assert (token (p, 0) == ':'); while (lex_skip_if (p, ':', false)) vars = _gst_add_node (vars, parse_variable (p)); return vars; } /* message_expression: unary_expression | binary_expression | keyword_expression unary_expression: primary unary_message | unary_expression unary_message unary_message: IDENTIFIER binary_expression: unary_expression binop unary_expression | binary_expression binop unary_expression keyword_expression: binary_expression KEYWORD binary_expression | keyword_expression KEYWORD binary_expression */ static tree_node parse_message_expression (gst_parser *p, tree_node receiver, enum expr_kinds kind) { tree_node node = receiver; int n; for (n = 0; ; n++) { switch (token (p, 0)) { case IDENTIFIER: node = parse_unary_expression (p, node, kind & ~EXPR_CASCADE); break; case '>': if ((kind & EXPR_GREATER) == 0) return node; case BINOP: case '<': case '-': case '|': if ((kind & EXPR_BINOP) == 0) return node; node = parse_binary_expression (p, node, kind & ~EXPR_CASCADE); break; case KEYWORD: if ((kind & EXPR_KEYWORD) == 0) return node; node = parse_keyword_expression (p, node, kind & ~EXPR_CASCADE); break; case ';': if (n == 0 || (kind & EXPR_CASCADE) == 0) return node; return _gst_make_cascaded_message (&node->location, node, parse_cascaded_messages (p)); default: return node; } } abort (); } /* cascaded_messages: cascaded_messages ';' message_expression | empty */ static tree_node parse_cascaded_messages (gst_parser *p) { tree_node cascade = NULL; while (lex_skip_if (p, ';', false)) { tree_node node; switch (token (p, 0)) { case IDENTIFIER: node = parse_unary_expression (p, NULL, EXPR_CASCADED); break; case '>': case BINOP: case '<': case '-': case '|': node = parse_binary_expression (p, NULL, EXPR_CASCADED); break; case KEYWORD: node = parse_keyword_expression (p, NULL, EXPR_CASCADED); break; default: /* After a semicolon, we can expect a message send. */ expected (p, IDENTIFIER, BINOP, KEYWORD, -1); } node = _gst_make_message_list (&node->location, node); cascade = _gst_add_node (cascade, node); } return cascade; } /* See above. This function only parses one unary expression. */ static tree_node parse_unary_expression (gst_parser *p, tree_node receiver, enum expr_kinds kind) { YYLTYPE location = receiver ? receiver->location : *loc(p,0); char *sel; assert (token (p, 0) == IDENTIFIER); sel = val(p, 0)->sval; if (is_unlikely_selector (sel)) _gst_warningf ("sending `%s', most likely you forgot a period", sel); lex (p); return _gst_make_unary_expr (&location, receiver, sel); } /* See above. This function only parses one binary expression. */ static tree_node parse_binary_expression (gst_parser *p, tree_node receiver, enum expr_kinds kind) { YYLTYPE location = receiver ? receiver->location : *loc(p,0); char *sel; tree_node arg; assert (token (p, 0) == BINOP || token (p, 0) == '|' || token (p, 0) == '<' || token (p, 0) == '-' || token (p, 0) == '>'); sel = val(p, 0)->sval; lex (p); arg = parse_expression (p, kind & ~EXPR_KEYWORD & ~EXPR_BINOP); if (!arg) { _gst_errorf ("expected object"); recover_error (p); } return _gst_make_binary_expr (&location, receiver, sel, arg); } /* See above. This function parses a keyword expression with all its arguments. */ static tree_node parse_keyword_expression (gst_parser *p, tree_node receiver, enum expr_kinds kind) { YYLTYPE location = receiver ? receiver->location : *loc(p,0); tree_node list = parse_keyword_list (p, kind); return list ? _gst_make_keyword_expr (&location, receiver, list) : NULL; } static tree_node parse_keyword_list (gst_parser *p, enum expr_kinds kind) { tree_node expr = NULL; assert (token (p, 0) == KEYWORD); do { YYLTYPE location = *loc(p,0); char *sval = val(p, 0)->sval; tree_node arg; lex (p); arg = parse_expression (p, kind & ~EXPR_KEYWORD); if (!arg) { _gst_errorf ("expected object"); recover_error (p); } expr = _gst_add_node (expr, _gst_make_keyword_list (&location, sval, arg)); } while (token (p, 0) == KEYWORD); return expr; } /* Based on a hash table produced by gperf version 2.7.2 Command-line: gperf -tn -F ', false' -j1 -k1,2 with the following input: false nil self super thisContext true fe ne nh sr A few negatives have been included in the input to avoid that messages like #new or #size require a strcmp (their hash value is in range if only the six keywords are included), and the length has not been included to make the result depend on selectors *starting* with two given letters. With this hash table and this implementation, only selectors starting with "fa", "ni", "se", "su", "th", "tr" (which are unavoidable) require a strcmp, which is a good compromise. All the others require three array lookups (two for the hash function, one to check for the first character) An alternative could have been simple trie-like code like this: return ((*$1 == 's' && (strcmp ($1+1, "elf") == 0 || strcmp ($1+1, "uper") == 0)) || (*$1 == 't' && (strcmp ($1+1, "rue") == 0 || strcmp ($1+1, "hisContext") == 0)) || (*$1 == 'f' && strcmp ($1+1, "alse") == 0) || (*$1 == 'n' && strcmp ($1+1, "il") == 0)) ... but using gperf is more cool :-) */ mst_Boolean is_unlikely_selector (register const char *str) { /* The first-character table is big enough that we skip the range check on the hash value */ static const char first[31] = "s s f n tt "; static const char *rest[] = { "elf", NULL, NULL, "uper", NULL, NULL, NULL, "alse", NULL, NULL, "il", NULL, NULL, "hisContext", "rue" }; static unsigned char asso_values[] = { 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 1, 15, 15, 15, 0, 6, 15, 4, 2, 15, 15, 15, 15, 8, 15, 15, 15, 5, 0, 9, 3, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15, 15 }; register int key = asso_values[(unsigned char)str[1]] + asso_values[(unsigned char)str[0]]; return first[key] == *str && !strcmp (str + 1, rest[key]); } smalltalk-3.2.5/libgst/files.c0000644000175000017500000004325712130343734013173 00000000000000/******************************** -*- C -*- **************************** * * Public library entry points * * ***********************************************************************/ /*********************************************************************** * * Copyright 1988,89,90,91,92,94,95,99,2000,2001,2002,2003,2006,2007,2008,2009 * Free Software Foundation, Inc. * Written by Steve Byrne. * * This file is part of GNU Smalltalk. * * GNU Smalltalk is free software; you can redistribute it and/or modify it * under the terms of the GNU General Public License as published by the Free * Software Foundation; either version 2, or (at your option) any later * version. * * Linking GNU Smalltalk statically or dynamically with other modules is * making a combined work based on GNU Smalltalk. Thus, the terms and * conditions of the GNU General Public License cover the whole * combination. * * In addition, as a special exception, the Free Software Foundation * give you permission to combine GNU Smalltalk with free software * programs or libraries that are released under the GNU LGPL and with * independent programs running under the GNU Smalltalk virtual machine. * * You may copy and distribute such a system following the terms of the * GNU GPL for GNU Smalltalk and the licenses of the other code * concerned, provided that you include the source code of that other * code when and as the GNU GPL requires distribution of source code. * * Note that people who make modified versions of GNU Smalltalk are not * obligated to grant this special exception for their modified * versions; it is their choice whether to do so. The GNU General * Public License gives permission to release a modified version without * this exception; this exception also makes it possible to release a * modified version which carries forward this exception. * * GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or * FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for * more details. * * You should have received a copy of the GNU General Public License along with * GNU Smalltalk; see the file COPYING. If not, write to the Free Software * Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * ***********************************************************************/ #include "gstpriv.h" #ifndef MAXPATHLEN #define MAXPATHLEN 1024 /* max length of a file and path */ #endif /* Define to debug the getopt code. */ /* #define DEBUG_GETOPT */ #ifdef MSDOS #define LOCAL_BASE_DIR_NAME "_st" #else #define LOCAL_BASE_DIR_NAME ".st" #endif #define USER_INIT_FILE_NAME "init.st" #define USER_PRE_IMAGE_FILE_NAME "pre.st" #define LOCAL_KERNEL_DIR_NAME "kernel" #define SITE_PRE_IMAGE_FILE_NAME "site-pre.st" /* When true, this flag suppresses the printing of execution-related * messages, such as the number of byte codes executed by the * last expression, etc. */ int _gst_verbosity = 2; /* These contain the default path that was picked (after looking at the environment variables) for the kernel files and the image. */ const char *_gst_kernel_file_path = NULL; const char *_gst_image_file_path = NULL; /* The ".st" directory, in the current directory or in the user's home directory. */ const char *_gst_user_file_base_path = NULL; /* Whether to look for user files. */ static mst_Boolean no_user_files = false; /* This is the name of the binary image to load. If it is not NULL after the command line is parsed, the checking of the dates of the kernel source files against the image file date is overridden. If it is NULL, it is set to default_image_name. */ const char *_gst_binary_image_name = NULL; /* This is used by the callin functions to auto-initialize Smalltalk. When it's not true, initialization needs to be performed. It's set to true by gst_init_smalltalk(). */ mst_Boolean _gst_smalltalk_initialized = false; /* This is used to avoid doing complicated things (currently, this includes call-ins before and after _gst_execute_statements) before the system is ready to do them. */ mst_Boolean _gst_kernel_initialized = false; /* This is TRUE if we are doing regression testing, and causes whatever sources of variance to be suppressed (such as printing out execution statistics). */ mst_Boolean _gst_regression_testing = false; /*********************************************************************** * * Private declarations * ***********************************************************************/ /* Answer whether it is ok to load the binary image pointed to by _gst_binary_image_name. This is good is the image file is local and newer than all of the kernel files, or if the image file is global, newer than all of the global kernel files, and no local kernel file is found. */ static mst_Boolean ok_to_load_binary (void); /* Attempts to find a viable Smalltalk file for user-level customization. FILENAME is a simple file name, sans directory; the file name to use for the particular file is returned, or NULL if it is not found. */ static char *find_user_file (const char *fileName); /* Loads the kernel Smalltalk files. It uses a vector of file names, and loads each file individually. To provide for greater flexibility, if a one of the files exists in the current directory, that is used in preference to one in the default location. The default location can be overridden at runtime by setting the SMALLTALK_KERNEL environment variable. */ static int load_standard_files (void); /* Path names for the per-user customization files, respectively init.st (loaded at every startup) and pre.st (loaded before a local image is saved. */ static const char *user_init_file = NULL; static const char *user_pre_image_file = NULL; static const char *site_pre_image_file = NULL; /* The complete list of "kernel" class and method definitions. Each of these files is loaded, in the order given below. Their last modification dates are compared against that of the image file; if any are newer, the image file is ignored, these files are loaded, and a new image file is created. As a provision for when we'll switch to a shared library, this is not an array but a list of consecutive file names. */ static const char standard_files[] = { "Builtins.st\0" "SysDict.st\0" "Object.st\0" "Message.st\0" "DirMessage.st\0" "Boolean.st\0" "False.st\0" "True.st\0" "Magnitude.st\0" "LookupKey.st\0" "DeferBinding.st\0" "Association.st\0" "HomedAssoc.st\0" "VarBinding.st\0" "Integer.st\0" "Date.st\0" "Time.st\0" "Number.st\0" "Float.st\0" "FloatD.st\0" "FloatE.st\0" "FloatQ.st\0" "Fraction.st\0" "LargeInt.st\0" "SmallInt.st\0" "Character.st\0" "UniChar.st\0" "Link.st\0" "Process.st\0" "CallinProcess.st\0" "Iterable.st\0" "Collection.st\0" "SeqCollect.st\0" "LinkedList.st\0" "Semaphore.st\0" "ArrayColl.st\0" "CompildCode.st\0" "CompildMeth.st\0" "CompiledBlk.st\0" "Array.st\0" "ByteArray.st\0" "CharArray.st\0" "String.st\0" "Symbol.st\0" "UniString.st\0" "Interval.st\0" "OrderColl.st\0" "SortCollect.st\0" "HashedColl.st\0" "Set.st\0" "IdentitySet.st\0" "Dictionary.st\0" "LookupTable.st\0" "IdentDict.st\0" "MethodDict.st\0" "BindingDict.st\0" "AbstNamespc.st\0" "RootNamespc.st\0" "Namespace.st\0" "Stream.st\0" "PosStream.st\0" "ReadStream.st\0" "WriteStream.st\0" "RWStream.st\0" "UndefObject.st\0" "ProcSched.st\0" "ContextPart.st\0" "MthContext.st\0" "BlkContext.st\0" "BlkClosure.st\0" "Behavior.st\0" "ClassDesc.st\0" "Class.st\0" "Metaclass.st\0" "Continuation.st\0" "Memory.st\0" "MethodInfo.st\0" "FileSegment.st\0" "FileDescr.st\0" "SymLink.st\0" "Security.st\0" "WeakObjects.st\0" "ObjMemory.st\0" /* More core classes */ "Bag.st\0" "MappedColl.st\0" "Delay.st\0" "SharedQueue.st\0" "Random.st\0" "RecursionLock.st\0" "Transcript.st\0" "Point.st\0" "Rectangle.st\0" "RunArray.st\0" "AnsiDates.st\0" "ScaledDec.st\0" "ValueAdapt.st\0" "OtherArrays.st\0" /* C call-out facilities */ "CObject.st\0" "CType.st\0" "CCallable.st\0" "CFuncs.st\0" "CCallback.st\0" "CStruct.st\0" /* Exception handling and ProcessEnvironment */ "ProcEnv.st\0" "ExcHandling.st\0" "SysExcept.st\0" /* Virtual filesystem layer */ "FilePath.st\0" "File.st\0" "Directory.st\0" "VFS.st\0" "VFSZip.st\0" "URL.st\0" "FileStream.st\0" /* Goodies */ "DynVariable.st\0" "DLD.st\0" "Getopt.st\0" "Generator.st\0" "StreamOps.st\0" "ObjDumper.st\0" "Regex.st\0" "PkgLoader.st\0" "Autoload.st\0" }; /* The argc and argv that are passed to libgst via gst_smalltalk_args. The default is passing no parameters. */ static int smalltalk_argc = 0; static const char **smalltalk_argv = NULL; /* The argc and argv that are made available to Smalltalk programs through the -a option. */ int _gst_smalltalk_passed_argc = 0; const char **_gst_smalltalk_passed_argv = NULL; void _gst_smalltalk_args (int argc, const char **argv) { smalltalk_argc = argc; smalltalk_argv = argv; } int _gst_initialize (const char *kernel_dir, const char *image_file, int flags) { char *currentDirectory = _gst_get_cur_dir_name (); const char *home = getenv ("HOME"); char *str; mst_Boolean loadBinary, abortOnFailure; int rebuild_image_flags = flags & (GST_REBUILD_IMAGE | GST_MAYBE_REBUILD_IMAGE); /* Even though we're nowhere near through initialization, we set this to make sure we don't invoke a callin function which would recursively invoke us. */ _gst_smalltalk_initialized = true; _gst_init_snprintfv (); if (!_gst_executable_path) _gst_executable_path = DEFAULT_EXECUTABLE; /* By default, apply this kludge fpr OSes such as Windows and MS-DOS which have no concept of home directories. */ if (home == NULL) home = xstrdup (currentDirectory); asprintf ((char **) &_gst_user_file_base_path, "%s/%s", home, LOCAL_BASE_DIR_NAME); /* Check that supplied paths are readable. If they're not, fail unless they told us in advance. */ if (kernel_dir && !_gst_file_is_readable (kernel_dir)) { if (flags & GST_IGNORE_BAD_KERNEL_PATH) kernel_dir = NULL; else { _gst_errorf ("kernel path %s not readable", kernel_dir); exit (1); } } /* For the image file, it is okay to find none if we can/should rebuild the image file. */ if (image_file && (flags & (GST_REBUILD_IMAGE | GST_MAYBE_REBUILD_IMAGE)) == 0 && !_gst_file_is_readable (image_file)) { if (flags & GST_IGNORE_BAD_IMAGE_PATH) image_file = NULL; else { _gst_errorf ("Couldn't open image file %s", image_file); exit (1); } } /* The image path can be used as the default kernel path, so we split it anyway into directory+filename. */ if (image_file) { const char *p; /* Compute the actual path of the image file */ p = image_file + strlen (image_file); for (;;) if (*--p == '/' #if defined(MSDOS) || defined(WIN32) || defined(__OS2__) || *p == '\\' #endif ) { char *dirname; int n = p > image_file ? p - image_file : 1; asprintf (&dirname, "%.*s", n, image_file); _gst_image_file_path = dirname; /* Remove path from image_file. */ image_file = p + 1; break; } else if (p == image_file) { _gst_image_file_path = "."; break; } } else { /* No image file given, we use the system default or revert to the current directory. */ str = _gst_relocate_path (IMAGE_PATH); if (_gst_file_is_readable (str)) _gst_image_file_path = str; else { free (str); _gst_image_file_path = xstrdup (currentDirectory); } flags |= GST_IGNORE_BAD_IMAGE_PATH; image_file = "gst.im"; } if (!kernel_dir) { str = _gst_relocate_path (KERNEL_PATH); if (!_gst_file_is_readable (str)) { free (str); asprintf (&str, "%s/kernel", _gst_image_file_path); } kernel_dir = str; } xfree (currentDirectory); /* Uff, we're done with the complicated part. Set variables to mirror what we've decided in the above marathon. */ _gst_image_file_path = _gst_get_full_file_name (_gst_image_file_path); _gst_kernel_file_path = _gst_get_full_file_name (kernel_dir); asprintf (&str, "%s/%s", _gst_image_file_path, image_file); _gst_binary_image_name = str; _gst_smalltalk_passed_argc = smalltalk_argc; _gst_smalltalk_passed_argv = smalltalk_argv; no_user_files = (flags & GST_IGNORE_USER_FILES) != 0; _gst_no_tty = (flags & GST_NO_TTY) != 0 || !isatty (0); site_pre_image_file = _gst_find_file (SITE_PRE_IMAGE_FILE_NAME, GST_DIR_KERNEL_SYSTEM); user_pre_image_file = find_user_file (USER_PRE_IMAGE_FILE_NAME); if (!_gst_regression_testing) user_init_file = find_user_file (USER_INIT_FILE_NAME); else user_init_file = NULL; _gst_init_sysdep (); _gst_init_signals (); _gst_init_cfuncs (); _gst_init_sockets (); _gst_init_primitives (); if (_gst_regression_testing) { _gst_declare_tracing = 0; _gst_execution_tracing = 0; _gst_verbosity = 2; setvbuf (stdout, NULL, _IOLBF, 1024); } if (rebuild_image_flags == 0) loadBinary = abortOnFailure = true; else { loadBinary = (rebuild_image_flags == GST_MAYBE_REBUILD_IMAGE && ok_to_load_binary ()); abortOnFailure = false; /* If we must create a new non-local image, but the directory is not writeable, we must resort to the current directory. In practice this is what happens when a "normal user" puts stuff in his ".st" directory or does "gst -i". */ if (!loadBinary && !_gst_file_is_writeable (_gst_image_file_path) && (flags & GST_IGNORE_BAD_IMAGE_PATH)) { _gst_image_file_path = _gst_get_cur_dir_name (); asprintf (&str, "%s/gst.im", _gst_image_file_path); _gst_binary_image_name = str; loadBinary = (rebuild_image_flags == GST_MAYBE_REBUILD_IMAGE && ok_to_load_binary ()); } } if (loadBinary && _gst_load_from_file (_gst_binary_image_name)) { _gst_init_interpreter (); _gst_init_compiler (); _gst_init_vmproxy (); } else if (abortOnFailure) { _gst_errorf ("Couldn't load image file %s", _gst_binary_image_name); return 1; } else { mst_Boolean willRegressTest = _gst_regression_testing; int result; _gst_regression_testing = false; _gst_init_oop_table (NULL, INITIAL_OOP_TABLE_SIZE); _gst_init_mem_default (); _gst_init_dictionary (); _gst_init_interpreter (); _gst_init_compiler (); _gst_init_vmproxy (); _gst_install_initial_methods (); result = load_standard_files (); _gst_regression_testing = willRegressTest; if (result) return result; if (!_gst_save_to_file (_gst_binary_image_name)) _gst_errorf ("Couldn't open file %s", _gst_binary_image_name); } _gst_kernel_initialized = true; _gst_invoke_hook (GST_RETURN_FROM_SNAPSHOT); if (user_init_file) _gst_process_file (user_init_file, GST_DIR_ABS); #ifdef HAVE_READLINE _gst_initialize_readline (); #endif /* HAVE_READLINE */ return 0; } mst_Boolean ok_to_load_binary (void) { const char *fileName; if (!_gst_file_is_readable (_gst_binary_image_name)) return (false); for (fileName = standard_files; *fileName; fileName += strlen (fileName) + 1) { char *fullFileName = _gst_find_file (fileName, GST_DIR_KERNEL); mst_Boolean ok = _gst_file_is_newer (_gst_binary_image_name, fullFileName); xfree (fullFileName); if (!ok) return (false); } if (site_pre_image_file && !_gst_file_is_newer (_gst_binary_image_name, site_pre_image_file)) return (false); if (user_pre_image_file && !_gst_file_is_newer (_gst_binary_image_name, user_pre_image_file)) return (false); return (true); } int load_standard_files (void) { const char *fileName; for (fileName = standard_files; *fileName; fileName += strlen (fileName) + 1) { if (!_gst_process_file (fileName, GST_DIR_KERNEL)) { _gst_errorf ("couldn't load system file '%s': %s", fileName, strerror (errno)); _gst_errorf ("image bootstrap failed, use option --kernel-directory"); return 1; } } _gst_msg_sendf (NULL, "%v %o relocate", _gst_file_segment_class); if (site_pre_image_file) _gst_process_file (site_pre_image_file, GST_DIR_ABS); if (user_pre_image_file) _gst_process_file (user_pre_image_file, GST_DIR_ABS); return 0; } char * _gst_find_file (const char *fileName, enum gst_file_dir dir) { char *fullFileName, *localFileName; if (dir == GST_DIR_ABS) return xstrdup (fileName); asprintf (&fullFileName, "%s/%s%s", _gst_kernel_file_path, dir == GST_DIR_KERNEL ? "" : "../", fileName); if (!no_user_files && dir != GST_DIR_KERNEL_SYSTEM) { asprintf (&localFileName, "%s/%s%s", _gst_user_file_base_path, dir == GST_DIR_BASE ? "" : LOCAL_KERNEL_DIR_NAME "/", fileName); if (_gst_file_is_newer (localFileName, fullFileName)) { xfree (fullFileName); return localFileName; } else xfree (localFileName); } if (_gst_file_is_readable (fullFileName)) return fullFileName; xfree (fullFileName); return NULL; } char * find_user_file (const char *fileName) { char *fullFileName; if (no_user_files) return NULL; asprintf (&fullFileName, "%s/%s", _gst_user_file_base_path, fileName); if (!_gst_file_is_readable (fullFileName)) { xfree (fullFileName); return NULL; } else return fullFileName; } smalltalk-3.2.5/libgst/comp.c0000644000175000017500000025045712130343734013031 00000000000000/******************************** -*- C -*- **************************** * * Byte code compiler. * * ***********************************************************************/ /*********************************************************************** * * Copyright 1988,89,90,91,92,94,95,99,2000,2001,2002,2003,2005,2006,2007,2008,2009 * Free Software Foundation, Inc. * Written by Steve Byrne. * * This file is part of GNU Smalltalk. * * GNU Smalltalk is free software; you can redistribute it and/or modify it * under the terms of the GNU General Public License as published by the Free * Software Foundation; either version 2, or (at your option) any later * version. * * Linking GNU Smalltalk statically or dynamically with other modules is * making a combined work based on GNU Smalltalk. Thus, the terms and * conditions of the GNU General Public License cover the whole * combination. * * In addition, as a special exception, the Free Software Foundation * give you permission to combine GNU Smalltalk with free software * programs or libraries that are released under the GNU LGPL and with * independent programs running under the GNU Smalltalk virtual machine. * * You may copy and distribute such a system following the terms of the * GNU GPL for GNU Smalltalk and the licenses of the other code * concerned, provided that you include the source code of that other * code when and as the GNU GPL requires distribution of source code. * * Note that people who make modified versions of GNU Smalltalk are not * obligated to grant this special exception for their modified * versions; it is their choice whether to do so. The GNU General * Public License gives permission to release a modified version without * this exception; this exception also makes it possible to release a * modified version which carries forward this exception. * * GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or * FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for * more details. * * You should have received a copy of the GNU General Public License along with * GNU Smalltalk; see the file COPYING. If not, write to the Free Software * Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * ***********************************************************************/ #include "gstpriv.h" /* To do: extract the iterative solving of the loop jumps' size. */ /* Define this if you want declaration tracing to print the bytecodes both *before* and *after* the optimizer is ran. Default behavior is to print the bytecodes only after the optimization pass; usually it is only needed to debug the optimizer -- when debugging the compiler you should turn off optimization entirely (see NO_OPTIMIZE in opt.c). */ /* #define PRINT_BEFORE_OPTIMIZATION */ /* Define this to verify the methods after they are compiled. This is useless because anyway after an image is saved methods are re-verified, but is a wonderful way of testing the compiler's output for correctness. */ /* #define VERIFY_COMPILED_METHODS */ #define LITERAL_VEC_CHUNK_SIZE 32 typedef struct method_attributes { struct method_attributes *next; int count; OOP oop; } method_attributes; /* This holds whether the compiler should make the compiled methods untrusted. */ mst_Boolean _gst_untrusted_methods = false; /* These hold the compiler's notions of the current class for compilations, and the current category that compiled methods are to be placed into. */ OOP _gst_this_class = NULL; OOP _gst_this_category = NULL; static OOP this_method_category; /* This holds the gst_compiled_method oop for the most recently compiled method. It is only really valid after a compile: has been done, but this is the only place that its used. */ OOP _gst_latest_compiled_method = NULL; /* This flag controls whether byte codes are printed after compilation. */ int _gst_declare_tracing = 0; /* If true, the compilation of a set of methods will be skipped completely; only syntax will be checked. Set by primitive, cleared by grammar. */ mst_Boolean _gst_skip_compilation = false; /* This is the value most recently returned by _gst_execute_statements. It is used to communicate the returned value past a _gst_parse_stream call, without pushing something on the called context stack in the case of nested invocations of _gst_prepare_execution_environment/_gst_finish_execution_environment. Most often, the caller does not care about the returned value, since it often is called from a radically different context. */ OOP _gst_last_returned_value = NULL; /* Returns true if EXPR represents the symbol "super"; false if not. */ static mst_Boolean is_super (tree_node expr); /* Returns true if OOP and CONSTEXPR represent the same literal value. Primarily used by the compiler to store a single copy of duplicated literals in a method. Can call itself in the case array literals. */ static mst_Boolean equal_constant (OOP oop, tree_node constExpr); /* Special case compilation of a #timesRepeat: loop. EXPR is a node for the entire keyword message send. Returns true if byte codes were emitted, false if not. If the last argument to the message is not a block expression, this routine cannot do its job, and so returns false to indicate as much. */ static mst_Boolean compile_times_repeat (tree_node expr); /* Special case compilation of a while loop whose selector is in SELECTOR. EXPR is a node for the entire unary or keyword message send. Returns true if byte codes were emitted, false if not. If the last argument to the message is not a block expression, this routine cannot do its job, and so returns false to indicate as much. */ static mst_Boolean compile_while_loop (OOP selector, tree_node expr); /* Special case compilation of a 1-argument if (#ifTrue: or #ifFalse:) whose selector is in SELECTOR; the default value for the absent case is nil. EXPR is a node for the entire keyword message send. Returns true if byte codes were emitted, false if not. If the last argument to the message is not a block expression, this routine cannot do its job, and so returns false to indicate as much. */ static mst_Boolean compile_if_statement (OOP selector, tree_node expr); /* Special case compilation of a #to:do: (if BY is NULL) or #to:by:do: loop. The starting value for the iteration is given by TO, the block is in BLOCK. Returns true if byte codes were emitted, false if not. If the last argument to the message is not a block expression, this routine cannot do its job, and so returns false to indicate as much. */ static mst_Boolean compile_to_by_do (tree_node to, tree_node by, tree_node block); /* Special case compilation of a #and: or #or: boolean operation; very similar to compile_if_statement. EXPR is a node for the entire keyword message send. Returns true if byte codes were emitted, false if not. If the last argument to the message is not a block expression, this routine cannot do its job, and so returns false to indicate as much. */ static mst_Boolean compile_and_or_statement (OOP selector, tree_node expr); /* Special case compilation of a 2-argument if whose selector is in SELECTOR. EXPR is a node for the entire keyword message send. Returns true if byte codes were emitted, false if not. If the last argument to the message is not a block expression, this routine cannot do its job, and so returns false to indicate as much. */ static mst_Boolean compile_if_true_false_statement (OOP selector, tree_node expr); /* Special case compilation of an infinite loop, given by the parse node in RECEIVER. Returns true if byte codes were emitted, false if not. If the last argument to the message is not a block expression, this routine cannot do its job, and so returns false to indicate as much. */ static mst_Boolean compile_repeat (tree_node receiver); /* Compiles all of the statements in STATEMENTLIST. If ISBLOCK is true, adds a final instruction of the block to return the top of stack, if the final statement isn't an explicit return from method (^). Returns whether the last statement was a return (whatever the value of ISBLOCK. */ static mst_Boolean compile_statements (tree_node statementList, mst_Boolean isBlock); /* Given a tree_node, this routine picks out and concatenates the keywords in SELECTOREXPR (if a TREE_KEYWORD_EXPR) or extracts the selector (if a TREE_UNARY_EXPR or TREE_BINARY_EXPR). Then it turns them into a symbol OOP and returns that symbol. */ static OOP compute_selector (tree_node selectorExpr); /* Creates a new Array object that contains the literals for the method that's being compiled and returns it. As a side effect, the currently allocated working literal vector is freed. If there were no literals for the current method, _gst_nil_oop is returned. */ static OOP get_literals_array (void); /* Process the attributes in ATTRIBUTELIST, return the primitive number. Also record a attribute in this_method_category. */ static int process_attributes_tree (tree_node attributeList); /* Process the attribute in MESSAGEOOP, return the primitive number (so far, this is the only attribute we honor), -1 for a bad primitive number, or 0 for other attributes. */ static int process_attribute (OOP messageOOP); /* Creates and returns a CompiledMethod. The method is completely filled in, including the descriptor, the method literals, and the byte codes for the method. */ static OOP method_new (method_header header, OOP literals, bc_vector bytecodes, OOP class, OOP methodDesc); /* Returns an instance of MethodInfo. This instance is used in the reconstruction of the source code for the method, and holds the category that the method belongs to. */ static OOP method_info_new (OOP class, OOP selector, method_attributes *attrs, OOP sourceCode, OOP categoryOOP); /* This creates a CompiledBlock for the given BYTECODES. The bytecodes are passed through the peephole optimizer and stored, the header is filled according to the given number of arguments ARGS and temporaries TEMPS, and to the cleanness of the block. STACK_DEPTH contains the number of stack slots needed by the block except for arguments and temporaries. */ static OOP make_block (int args, int temps, bc_vector bytecodes, int stack_depth); /* Create a BlockClosure for the given CompiledBlock, BLOCKOOP. */ static OOP make_clean_block_closure (OOP blockOOP); /* Compiles a block tree node, EXPR, in a separate context and return the resulting bytecodes. The block's argument declarations are ignored since they are handled by compile_to_by_do (and are absent for other methods like ifTrue:, and:, whileTrue:, etc.); there are no temporaries. It is compiled as a list of statements such that the last statement leaves the value that is produced on the stack, as the value of the "block". */ static bc_vector compile_sub_expression (tree_node expr); /* Like compile_sub_expression, except that after compiling EXPR this subexpression always ends with an unconditional branch past BRANCHLEN bytecodes. */ static bc_vector compile_sub_expression_and_jump (tree_node expr, int branchLen); /* Compile a send with the given RECEIVER (used to check for sends to super), SELECTOR and number of arguments NUMARGS. */ static void compile_send (tree_node receiver, OOP selector, int numArgs); /* Computes and returns the length of a parse tree list, LISTEXPR. */ static int list_length (tree_node listExpr); /* Adds OOP to the literals associated with the method being compiled and returns the index of the literal slot that was used (0-based). Does not check for duplicates. Automatically puts OOP in the incubator. */ static int add_literal (OOP oop); /* Compiles STMT, which is a statement expression, including return expressions. */ static void compile_statement (tree_node stmt); /* Compile EXPR, which is an arbitrary expression, including an assignment expression. */ static void compile_expression (tree_node expr); /* The basic expression compiler. Often called recursively, dispatches based on the type of EXPR to different routines that specialize in compilations for that expression. */ static void compile_simple_expression (tree_node expr); /* Compile code to push the value of a variable onto the stack. The special variables, self, true, false, super, and thisContext, are handled specially. For other variables, different code is emitted depending on where the variable lives, such as in a global variable or in a method temporary. */ static void compile_variable (tree_node varName); /* Compile an expression that pushes a constant expression CONSTEXPR onto the stack. Special cases out the constants that the byte code interpreter knows about, which are the integers in the range -1 to 2. Tries to emit the shortest possible byte sequence. */ static void compile_constant (tree_node constExpr); /* Compile the expressions for a block whose parse tree is BLOCKEXPR. Also, emits code to push the BlockClosure object, and creates the BlockClosure together with its CompiledBlock. */ static void compile_block (tree_node blockExpr); /* Compiles all of the statements in arrayConstructor, preceded by (Array new: ) and with each statement followed with a instead of a simple pop. */ static void compile_array_constructor (tree_node arrayConstructor); /* Compile code to evaluate a unary expression EXPR. Special cases sends to "super". Also, checks to see if it's the first part of a cascaded message send and if so emits code to duplicate the stack top after the evaluation of the receiver for use by the subsequent cascaded expressions. */ static void compile_unary_expr (tree_node expr); /* Compile code to evaluate a binary expression EXPR. Special cases sends to "super" and open codes whileTrue/whileFalse/repeat when the receiver is a block. Also, checks to see if it's the first part of a cascaded message send and if so emits code to duplicate the stack top after the evaluation of the receiver for use by the subsequent cascaded expressions. */ static void compile_binary_expr (tree_node expr); /* Compile code to evaluate a keyword expression EXPR. Special cases sends to "super" and open codes while loops, the 4 kinds of if tests, and the conditional #and: and conditional #or: messages, #to:do:, and #to:by:do: with an Integer step. Also, checks to see if it's the first part of a cascaded message send and if so emits code to duplicate the stack top after the evaluation of the receiver for use by the subsequent cascaded expressions. */ static void compile_keyword_expr (tree_node expr); /* Compiles the code for a cascaded message send. Due to the fact that cascaded sends go to the receiver of the last message before the first cascade "operator" (the ";"), the system to perform cascaded message sends is a bit kludgy. We basically turn on a flag to the compiler that indicates that the value of the receiver of the last message before the cascaded sends is to be duplicated; and then compile code for each cascaded expression, throwing away the result, and duplicating the original receiver so that it can be used by the current message send, and following ones. Note that both the initial receiver and all the subsequent cascaded sends can be derived from CASCADEDEXPR. */ static void compile_cascaded_message (tree_node cascadedExpr); /* Compiles all the assignments in VARLIST, which is a tree_node of type listNode. The generated code assumes that the value on the top of the stack is what's to be used for the assignment. Since this routine has no notion of now the value on top of the stack will be used by the calling environment, it makes sure that when the assignments are through, that the value on top of the stack after the assignment is the same as the value on top of the stack before the assignment. The optimizer should fix this in the unnecessary cases. */ static void compile_assignments (tree_node varList); /* Compiles a forward jump instruction LEN bytes away (LEN must be > 0), using the smallest possible number of bytecodes. JUMPTYPE indicates which among the unconditional, "jump if true" and "jump if false" opcodes is desired. Special cases for the short unconditional jump and the short false jump that the byte code interpreter handles. */ static void compile_jump (int len, mst_Boolean jumpType); /* Emit code to evaluate each argument to a keyword message send, taking them from the parse tree node LIST. */ static void compile_keyword_list (tree_node list); /* Called to grow the literal vector that the compiler is using. Modifies the global variables LITERAL_VEC and LITERAL_VEC_MAX to reflect the growth. */ static void realloc_literal_vec (void); /* Takes a new CompiledMethod METHODOOP and installs it in the method dictionary for the current class. If the current class does not contain a valid method dictionary, one is allocated for it. */ static void install_method (OOP methodOOP); /* This caches the OOP of the special UndefinedObject>>#__terminate method, which is executed by contexts created with _gst_prepare_execution_environment. */ static OOP termination_method; /* Used to abort really losing compiles, jumps back to the top level of the compiler */ static jmp_buf bad_method; /* The linked list of attributes that are specified by the method. */ static method_attributes *method_attrs = NULL; /* The vector of literals that the compiler uses to accumulate literal constants into */ static OOP *literal_vec = NULL; /* These indicate the first free slot in the vector of literals in the method being compiled, and the first slot past the literal vector */ static OOP *literal_vec_curr, *literal_vec_max; /* This indicates whether we are compiling a block */ static int inside_block; /* HACK ALERT!! HACK ALERT!! This variable is used for cascading. The tree structure is all wrong for the code in cascade processing to find the receiver of the initial message. What this does is when it's true, compile_unary_expr, compile_binary_expr, and compile_keyword_expr record its value, and clear the global (to prevent propagation to compilation of subnodes). After compiling their receiver, if the saved value of the flag is true, they emit a DUP_STACK_TOP, and continue compilation. Since cascaded sends are relatively rare, I figured that this was a better alternative than passing useless parameters around all the time. */ static mst_Boolean dup_message_receiver = false; /* Exit a really losing compilation */ #define EXIT_COMPILATION() \ longjmp(bad_method, 1) /* Answer whether the BLOCKNODE parse node has temporaries or arguments. */ #define HAS_PARAMS_OR_TEMPS(blockNode) \ (blockNode->v_block.temporaries || blockNode->v_block.arguments) /* Answer whether the BLOCKNODE parse node has temporaries and has not exactly one argument. */ #define HAS_NOT_ONE_PARAM_OR_TEMPS(blockNode) \ (blockNode->v_block.temporaries \ || !blockNode->v_block.arguments \ || blockNode->v_block.arguments->v_list.next) void _gst_install_initial_methods (void) { const char *methodsForString; /* Define the termination method first of all, because compiling #methodsFor: will invoke an evaluation (to get the argument of the attribute. */ _gst_set_compilation_class (_gst_undefined_object_class); _gst_set_compilation_category (_gst_string_new ("private")); _gst_alloc_bytecodes (); _gst_compile_byte (EXIT_INTERPRETER, 0); _gst_compile_byte (JUMP_BACK, 4); /* The zeros are primitive, # of args, # of temps, stack depth */ termination_method = _gst_make_new_method (0, 0, 0, 0, _gst_nil_oop, _gst_get_bytecodes (), _gst_this_class, _gst_terminate_symbol, _gst_this_category, -1, -1); ((gst_compiled_method) OOP_TO_OBJ (termination_method))->header.headerFlag = MTH_ANNOTATED; install_method (termination_method); methodsForString = "\n\ methodsFor: aCategoryString [\n\ \"Calling this method prepares the parser to receive methods \n\ to be compiled and installed in the receiver's method dictionary. \n\ The methods are put in the category identified by the parameter.\" \n\ \n\ ]"; _gst_set_compilation_class (_gst_behavior_class); _gst_set_compilation_category (_gst_string_new ("compiling methods")); _gst_push_smalltalk_string (_gst_string_new (methodsForString)); _gst_parse_stream (true); _gst_pop_stream (true); _gst_reset_compilation_category (); } OOP _gst_get_termination_method (void) { if (!termination_method) { termination_method = _gst_find_class_method (_gst_undefined_object_class, _gst_terminate_symbol); } return (termination_method); } static void invoke_hook_smalltalk (enum gst_vm_hook hook) { const char *hook_name; if (!_gst_kernel_initialized) return; switch (hook) { case GST_BEFORE_EVAL: hook_name = "beforeEvaluation"; break; case GST_AFTER_EVAL: hook_name = "afterEvaluation"; break; case GST_RETURN_FROM_SNAPSHOT: hook_name = "returnFromSnapshot"; break; case GST_ABOUT_TO_QUIT: hook_name = "aboutToQuit"; break; case GST_ABOUT_TO_SNAPSHOT: hook_name = "aboutToSnapshot"; break; case GST_FINISHED_SNAPSHOT: hook_name = "finishedSnapshot"; break; default: return; } _gst_msg_sendf (NULL, "%v %o changed: %S", _gst_object_memory_class, hook_name); } void _gst_invoke_hook (enum gst_vm_hook hook) { int save_execution; save_execution = _gst_execution_tracing; if (_gst_execution_tracing == 1) _gst_execution_tracing = 0; invoke_hook_smalltalk (hook); _gst_execution_tracing = save_execution; } void _gst_init_compiler (void) { /* Prepare the literal vector for use. The literal vector is where the compiler will store any literals that are used by the method being compiled. */ literal_vec = (OOP *) xmalloc (LITERAL_VEC_CHUNK_SIZE * sizeof (OOP)); literal_vec_curr = literal_vec; literal_vec_max = literal_vec + LITERAL_VEC_CHUNK_SIZE; _gst_register_oop_array (&literal_vec, &literal_vec_curr); _gst_reset_compilation_category (); } void _gst_set_compilation_class (OOP class_oop) { _gst_unregister_oop (_gst_this_class); _gst_this_class = class_oop; _gst_register_oop (_gst_this_class); _gst_untrusted_methods = (IS_OOP_UNTRUSTED (_gst_this_context_oop) || IS_OOP_UNTRUSTED (_gst_this_class)); } void _gst_set_compilation_category (OOP categoryOOP) { _gst_unregister_oop (_gst_this_category); _gst_this_category = categoryOOP; _gst_register_oop (_gst_this_category); _gst_untrusted_methods = (IS_OOP_UNTRUSTED (_gst_this_context_oop) || IS_OOP_UNTRUSTED (_gst_this_class)); } void _gst_reset_compilation_category () { _gst_set_compilation_class (_gst_undefined_object_class); _gst_set_compilation_category (_gst_nil_oop); _gst_untrusted_methods = false; } void _gst_display_compilation_trace (const char *string, mst_Boolean category) { if (!_gst_declare_tracing) return; if (category) printf ("%s category %O for %O\n", string, _gst_this_category, _gst_this_class); else printf ("%s for %O\n", string, _gst_this_class); } OOP _gst_execute_statements (tree_node temps, tree_node statements, enum undeclared_strategy undeclared, mst_Boolean quiet) { tree_node messagePattern; int startTime, endTime, deltaTime; unsigned long cacheHits; #ifdef HAVE_GETRUSAGE struct rusage startRusage, endRusage; #endif OOP methodOOP; OOP oldClass, oldCategory; enum undeclared_strategy oldUndeclared; inc_ptr incPtr; YYLTYPE loc; if (_gst_regression_testing || _gst_verbosity < 2 || !_gst_get_cur_stream_prompt ()) quiet = true; oldClass = _gst_this_class; oldCategory = _gst_this_category; _gst_register_oop (oldClass); _gst_register_oop (oldCategory); _gst_set_compilation_class (_gst_undefined_object_class); _gst_set_compilation_category (_gst_nil_oop); loc = _gst_get_location (); messagePattern = _gst_make_unary_expr (&statements->location, NULL, "executeStatements"); _gst_display_compilation_trace ("Compiling doit code", false); /* This is a big hack to let doits access the variables and classes in the current namespace. */ oldUndeclared = _gst_set_undeclared (undeclared); SET_CLASS_ENVIRONMENT (_gst_undefined_object_class, _gst_current_namespace); if (statements->nodeType != TREE_STATEMENT_LIST) statements = _gst_make_statement_list (&statements->location, statements); methodOOP = _gst_compile_method (_gst_make_method (&statements->location, &loc, messagePattern, temps, NULL, statements, false), true, false); SET_CLASS_ENVIRONMENT (_gst_undefined_object_class, _gst_smalltalk_dictionary); _gst_set_undeclared (oldUndeclared); _gst_set_compilation_class (oldClass); _gst_set_compilation_category (oldCategory); _gst_unregister_oop (oldClass); _gst_unregister_oop (oldCategory); if (_gst_had_error) /* don't execute on error */ return (NULL); incPtr = INC_SAVE_POINTER (); INC_ADD_OOP (methodOOP); if (!_gst_raw_profile) _gst_bytecode_counter = _gst_primitives_executed = _gst_self_returns = _gst_inst_var_returns = _gst_literal_returns = _gst_sample_counter = 0; startTime = _gst_get_milli_time (); #ifdef HAVE_GETRUSAGE getrusage (RUSAGE_SELF, &startRusage); #endif _gst_invoke_hook (GST_BEFORE_EVAL); /* send a message to NIL, which will find this synthetic method definition in Object and execute it */ _gst_last_returned_value = _gst_nvmsg_send (_gst_nil_oop, methodOOP, NULL, 0); INC_ADD_OOP (_gst_last_returned_value); endTime = _gst_get_milli_time (); #ifdef HAVE_GETRUSAGE getrusage (RUSAGE_SELF, &endRusage); #endif if (!quiet && _gst_verbosity >= 3) { deltaTime = endTime - startTime; #ifdef ENABLE_JIT_TRANSLATION printf ("Execution took %.3f seconds", deltaTime / 1000.0); #else printf ("%lu byte codes executed\nwhich took %.3f seconds", _gst_bytecode_counter, deltaTime / 1000.0); #endif #ifdef HAVE_GETRUSAGE deltaTime = ((endRusage.ru_utime.tv_sec * 1000) + (endRusage.ru_utime.tv_usec / 1000)) - ((startRusage.ru_utime.tv_sec * 1000) + (startRusage.ru_utime.tv_usec / 1000)); printf (" (%.3fs user", deltaTime / 1000.0); deltaTime = ((endRusage.ru_stime.tv_sec * 1000) + (endRusage.ru_stime.tv_usec / 1000)) - ((startRusage.ru_stime.tv_sec * 1000) + (startRusage.ru_stime.tv_usec / 1000)); printf ("+%.3fs sys)", deltaTime / 1000.0); #endif printf ("\n"); #ifndef ENABLE_JIT_TRANSLATION if (_gst_bytecode_counter) { printf ("%lu primitives, percent %.2f\n", _gst_primitives_executed, 100.0 * _gst_primitives_executed / _gst_bytecode_counter); printf ("self returns %lu, inst var returns %lu, literal returns %lu\n", _gst_self_returns, _gst_inst_var_returns, _gst_literal_returns); printf ("%lu method cache lookups since last cleanup, percent %.2f\n", _gst_sample_counter, 100.0 * _gst_sample_counter / _gst_bytecode_counter); } #endif if (_gst_sample_counter) { #ifdef ENABLE_JIT_TRANSLATION printf ("%lu primitives, %lu inline cache misses since last cache cleanup\n", _gst_primitives_executed, _gst_sample_counter); #endif cacheHits = _gst_sample_counter - _gst_cache_misses; printf ("%lu method cache hits, %lu misses", cacheHits, _gst_cache_misses); if (cacheHits || _gst_cache_misses) printf (", %.2f percent hits\n", (100.0 * cacheHits) / _gst_sample_counter); else printf ("\n"); } /* Do more frequent flushing to ensure the result are well placed */ printf ("returned value is "); fflush(stdout); } if (!quiet) { int save_execution; save_execution = _gst_execution_tracing; if (_gst_execution_tracing == 1) _gst_execution_tracing = 0; if (_gst_responds_to (_gst_last_returned_value, _gst_intern_string ("printNl")) || _gst_responds_to (_gst_last_returned_value, _gst_does_not_understand_symbol)) _gst_str_msg_send (_gst_last_returned_value, "printNl", NULL); else printf ("%O\n", _gst_last_returned_value); fflush (stdout); fflush (stderr); _gst_execution_tracing = save_execution; } _gst_invoke_hook (GST_AFTER_EVAL); INC_RESTORE_POINTER (incPtr); return (_gst_last_returned_value); } OOP _gst_compile_method (tree_node method, mst_Boolean returnLast, mst_Boolean install) { tree_node statement; OOP selector; OOP methodOOP; bc_vector bytecodes; int primitiveIndex; int stack_depth; inc_ptr incPtr; gst_compiled_method compiledMethod; dup_message_receiver = false; literal_vec_curr = literal_vec; this_method_category = _gst_this_category; _gst_unregister_oop (_gst_latest_compiled_method); _gst_latest_compiled_method = _gst_nil_oop; incPtr = INC_SAVE_POINTER (); _gst_alloc_bytecodes (); _gst_push_new_scope (); inside_block = 0; selector = compute_selector (method->v_method.selectorExpr); /* When we are reading from stdin, it's better to write line numbers where 1 is the first line *in the current doit*, because for now the prompt does not include the line number. This might change in the future. Also, do not emit line numbers if the method has no statements. */ if ((method->location.file_offset != -1 && _gst_get_cur_stream_prompt ()) || !method->v_method.statements) _gst_line_number (method->location.first_line, LN_RESET); else _gst_line_number (method->location.first_line, LN_RESET | LN_ABSOLUTE); INC_ADD_OOP (selector); if (_gst_declare_tracing) printf (" class %O, selector %O\n", _gst_this_class, selector); if (setjmp (bad_method) == 0) { if (_gst_declare_arguments (method->v_method.selectorExpr) == -1) { _gst_errorf_at (method->location.first_line, "duplicate argument name"); EXIT_COMPILATION (); } if (_gst_declare_temporaries (method->v_method.temporaries) == -1) { _gst_errorf_at (method->location.first_line, "duplicate temporary variable name"); EXIT_COMPILATION (); } primitiveIndex = process_attributes_tree (method->v_method.attributes); for (statement = method->v_method.statements; statement; ) { mst_Boolean wasReturn = statement->v_list.value->nodeType == TREE_RETURN_EXPR; compile_statement (statement->v_list.value); statement = statement->v_list.next; if (wasReturn) continue; if (!statement && returnLast) /* compile a return of the last evaluated value. Note that in theory the pop above is not necessary in this case (and in fact older versions did not put it), but having it simplifies the optimizer's task because it reduces the number of patterns it has to look for. If necessary, the optimizer itself will remove the pop. */ { _gst_compile_byte (RETURN_CONTEXT_STACK_TOP, 0); break; } /* ignore the result of the last statement if it's not used */ SUB_STACK_DEPTH (1); _gst_compile_byte (POP_STACK_TOP, 0); if (!statement) { /* compile a return of self. Note that in theory the pop above is not necessary in this case (and in fact older versions did not put it), but having it simplifies the optimizer's task because it reduces the number of patterns it has to look for. If necessary, the optimizer itself will remove the pop. */ _gst_compile_byte (PUSH_SELF, 0); _gst_compile_byte (RETURN_CONTEXT_STACK_TOP, 0); break; } } if (method->v_method.statements == NULL) { if (returnLast) { /* special case an empty statement body to return nil */ _gst_compile_byte (PUSH_SPECIAL, NIL_INDEX); _gst_compile_byte (RETURN_CONTEXT_STACK_TOP, 0); } else { /* special case an empty statement body to return _gst_self */ _gst_compile_byte (PUSH_SELF, 0); _gst_compile_byte (RETURN_CONTEXT_STACK_TOP, 0); } } stack_depth = GET_STACK_DEPTH (); bytecodes = _gst_get_bytecodes (); methodOOP = _gst_make_new_method (primitiveIndex, _gst_get_arg_count (), _gst_get_temp_count (), stack_depth, _gst_nil_oop, bytecodes, _gst_this_class, selector, _gst_this_category, method->location.file_offset, method->v_method.endPos); compiledMethod = (gst_compiled_method) OOP_TO_OBJ (methodOOP); compiledMethod->header.isOldSyntax = method->v_method.isOldSyntax; INC_ADD_OOP (methodOOP); if (install) install_method (methodOOP); _gst_latest_compiled_method = methodOOP; /* reachable by the root set */ _gst_register_oop (_gst_latest_compiled_method); } else { _gst_had_error = true; bytecodes = _gst_get_bytecodes (); literal_vec_curr = literal_vec; _gst_free_bytecodes (bytecodes); } _gst_pop_all_scopes (); INC_RESTORE_POINTER (incPtr); return (_gst_latest_compiled_method); } void compile_statement (tree_node stmt) { tree_node receiver; if (stmt->nodeType != TREE_RETURN_EXPR) { compile_expression (stmt); return; } receiver = stmt->v_expr.receiver; if (inside_block) { compile_expression (receiver); _gst_compile_byte (RETURN_METHOD_STACK_TOP, 0); SUB_STACK_DEPTH (1); return; } compile_expression (receiver); _gst_compile_byte (RETURN_CONTEXT_STACK_TOP, 0); SUB_STACK_DEPTH (1); } void compile_expression (tree_node expr) { if (expr->nodeType == TREE_ASSIGN_EXPR) { compile_simple_expression (expr->v_expr.expression); compile_assignments (expr->v_expr.receiver); } else compile_simple_expression (expr); } void compile_simple_expression (tree_node expr) { _gst_line_number (expr->location.first_line, 0); switch (expr->nodeType) { case TREE_VARIABLE_NODE: compile_variable (expr); break; case TREE_CONST_EXPR: compile_constant (expr); break; case TREE_BLOCK_NODE: compile_block (expr); break; case TREE_UNARY_EXPR: compile_unary_expr (expr); break; case TREE_BINARY_EXPR: compile_binary_expr (expr); break; case TREE_KEYWORD_EXPR: compile_keyword_expr (expr); break; case TREE_CASCADE_EXPR: compile_cascaded_message (expr); break; case TREE_ARRAY_CONSTRUCTOR: compile_array_constructor (expr); break; default: compile_expression (expr); } } void compile_variable (tree_node varName) { symbol_entry variable; INCR_STACK_DEPTH (); if (!_gst_find_variable (&variable, varName)) { if (varName->v_list.next) _gst_errorf_at (varName->location.first_line, "invalid scope resolution"); else _gst_errorf_at (varName->location.first_line, "undefined variable %s referenced", varName->v_list.name); EXIT_COMPILATION (); } if (variable.scope == SCOPE_SPECIAL) switch (variable.varIndex) { case THIS_CONTEXT_INDEX: { static OOP contextPartAssociation; if (!contextPartAssociation) { contextPartAssociation = dictionary_association_at (_gst_smalltalk_dictionary, _gst_intern_string ("ContextPart")); } _gst_compile_byte (PUSH_LIT_VARIABLE, _gst_add_forced_object (contextPartAssociation)); _gst_compile_byte (SEND_IMMEDIATE, THIS_CONTEXT_SPECIAL); } return; case RECEIVER_INDEX: _gst_compile_byte (PUSH_SELF, 0); return; default: _gst_compile_byte (PUSH_SPECIAL, variable.varIndex); return; } if (variable.scope != SCOPE_GLOBAL && varName->v_list.next) { _gst_errorf_at (varName->location.first_line, "invalid scope resolution"); EXIT_COMPILATION (); } if (variable.scopeDistance != 0) /* must be a temporary from an outer scope */ _gst_compile_byte (PUSH_OUTER_TEMP, variable.varIndex * 256 + variable.scopeDistance); else if (variable.scope == SCOPE_TEMPORARY) _gst_compile_byte (PUSH_TEMPORARY_VARIABLE, variable.varIndex); else if (variable.scope == SCOPE_RECEIVER) _gst_compile_byte (PUSH_RECEIVER_VARIABLE, variable.varIndex); else _gst_compile_byte (PUSH_LIT_VARIABLE, variable.varIndex); } void compile_constant (tree_node constExpr) { intptr_t intVal; int index = -1; OOP constantOOP; OOP *lit; /* Scan the current literal frame, looking for a constant equal to the one that is being compiled. */ for (lit = literal_vec; lit < literal_vec_curr; lit++) if (equal_constant (*lit, constExpr)) { index = lit - literal_vec; break; } /* If not found, check if it can be compiled with a PUSH_INTEGER bytecode, or add it to the literals. */ if (index == -1) { constantOOP = _gst_make_constant_oop (constExpr); if (IS_INT (constantOOP)) { intVal = TO_INT (constantOOP); if (intVal >= 0 && intVal <= 0x7FFFFFFFL) { INCR_STACK_DEPTH (); _gst_compile_byte (PUSH_INTEGER, intVal); return; } } index = add_literal (constantOOP); } INCR_STACK_DEPTH (); _gst_compile_byte (PUSH_LIT_CONSTANT, index); } void compile_block (tree_node blockExpr) { bc_vector current_bytecodes, blockByteCodes; int argCount, tempCount; int stack_depth; OOP blockClosureOOP, blockOOP; gst_compiled_block block; inc_ptr incPtr; current_bytecodes = _gst_save_bytecode_array (); _gst_push_new_scope (); argCount = _gst_declare_block_arguments (blockExpr->v_block.arguments); tempCount = _gst_declare_temporaries (blockExpr->v_block.temporaries); if (argCount == -1) { _gst_errorf_at (blockExpr->location.first_line, "duplicate argument name"); EXIT_COMPILATION (); } if (tempCount == -1) { _gst_errorf_at (blockExpr->location.first_line, "duplicate temporary variable name"); EXIT_COMPILATION (); } compile_statements (blockExpr->v_block.statements, true); stack_depth = GET_STACK_DEPTH (); blockByteCodes = _gst_get_bytecodes (); _gst_restore_bytecode_array (current_bytecodes); /* Always allocate objects starting from the deepest one! (that is, subtle bugs arise if make_block triggers a GC, because the pointer in the closure might be no longer valid!) */ incPtr = INC_SAVE_POINTER (); blockOOP = make_block (_gst_get_arg_count (), _gst_get_temp_count (), blockByteCodes, stack_depth); INC_ADD_OOP (blockOOP); _gst_pop_old_scope (); /* emit standard byte sequence to invoke a block: push literal (a BlockClosure) or push literal (a CompiledBlock) make dirty block */ INCR_STACK_DEPTH (); block = (gst_compiled_block) OOP_TO_OBJ (blockOOP); if (block->header.clean == 0) { blockClosureOOP = make_clean_block_closure (blockOOP); _gst_compile_byte (PUSH_LIT_CONSTANT, add_literal (blockClosureOOP)); } else { _gst_compile_byte (PUSH_LIT_CONSTANT, add_literal (blockOOP)); _gst_compile_byte (MAKE_DIRTY_BLOCK, 0); } INC_RESTORE_POINTER (incPtr); } mst_Boolean compile_statements (tree_node statementList, mst_Boolean isBlock) { tree_node stmt; if (statementList == NULL) { INCR_STACK_DEPTH (); _gst_compile_byte (PUSH_SPECIAL, NIL_INDEX); if (isBlock) _gst_compile_byte (RETURN_CONTEXT_STACK_TOP, 0); return (false); } if (isBlock) { _gst_line_number (statementList->location.first_line, LN_FORCE); inside_block++; } for (stmt = statementList;; stmt = stmt->v_list.next) { compile_statement (stmt->v_list.value); if (!stmt->v_list.next) break; /* throw away the value on the top of the stack...we don't need it for all but the last one. */ SUB_STACK_DEPTH (1); _gst_compile_byte (POP_STACK_TOP, 0); } /* stmt is the last statement here. if it isn't a return, then return the value on the stack as the result. For inlined blocks, the returned value is the top of the stack (which is already there), so we are already done. */ if (stmt->v_list.value->nodeType != TREE_RETURN_EXPR && isBlock) _gst_compile_byte (RETURN_CONTEXT_STACK_TOP, 0); if (isBlock) { _gst_line_number (-1, 0); inside_block--; } return (stmt->v_list.value->nodeType == TREE_RETURN_EXPR); } void compile_array_constructor (tree_node arrayConstructor) { tree_node stmt, statementList; int i, n; static OOP arrayAssociation; statementList = arrayConstructor->v_const.val.aVal; for (n = 0, stmt = statementList; stmt; n++, stmt = stmt->v_list.next); if (!arrayAssociation) { arrayAssociation = dictionary_association_at (_gst_smalltalk_dictionary, _gst_intern_string ("Array")); } ADD_STACK_DEPTH (2); _gst_compile_byte (PUSH_LIT_VARIABLE, _gst_add_forced_object (arrayAssociation)); _gst_compile_byte (PUSH_INTEGER, n); _gst_compile_byte (SEND_IMMEDIATE, NEW_COLON_SPECIAL); SUB_STACK_DEPTH (1); /* compile the values now */ for (i = 0, stmt = statementList; i < n; i++, stmt = stmt->v_list.next) { compile_statement (stmt->v_list.value); _gst_compile_byte (POP_INTO_NEW_STACKTOP, i); /* throw away the value on the top of the stack... */ SUB_STACK_DEPTH (1); } } void compile_unary_expr (tree_node expr) { OOP selector; mst_Boolean savedDupFlag; savedDupFlag = dup_message_receiver; dup_message_receiver = false; selector = expr->v_expr.selector; /* check for optimized cases of messages to blocks and handle them specially */ if (selector == _gst_while_true_symbol || selector == _gst_while_false_symbol) { if (compile_while_loop (selector, expr)) return; } else if (selector == _gst_repeat_symbol) { if (compile_repeat (expr->v_expr.receiver)) return; } if (expr->v_expr.receiver != NULL) { compile_expression (expr->v_expr.receiver); if (savedDupFlag) { _gst_compile_byte (DUP_STACK_TOP, 0); INCR_STACK_DEPTH (); } } compile_send (expr, selector, 0); } void compile_binary_expr (tree_node expr) { OOP selector; mst_Boolean savedDupFlag; savedDupFlag = dup_message_receiver; dup_message_receiver = false; selector = expr->v_expr.selector; if (expr->v_expr.receiver != NULL) { compile_expression (expr->v_expr.receiver); if (savedDupFlag) { _gst_compile_byte (DUP_STACK_TOP, 0); INCR_STACK_DEPTH (); } } if (expr->v_expr.expression) compile_expression (expr->v_expr.expression); compile_send (expr, selector, 1); } void compile_keyword_expr (tree_node expr) { OOP selector; int numArgs; mst_Boolean savedDupFlag; savedDupFlag = dup_message_receiver; dup_message_receiver = false; selector = compute_selector (expr); /* check for optimized cases of messages to booleans and handle them specially */ if (selector == _gst_while_true_colon_symbol || selector == _gst_while_false_colon_symbol) { if (compile_while_loop (selector, expr)) return; } if (expr->v_expr.receiver) { compile_expression (expr->v_expr.receiver); if (savedDupFlag) { _gst_compile_byte (DUP_STACK_TOP, 0); INCR_STACK_DEPTH (); } } if (selector == _gst_if_true_symbol || selector == _gst_if_false_symbol) { if (compile_if_statement (selector, expr->v_expr.expression)) return; } else if (selector == _gst_if_true_if_false_symbol || selector == _gst_if_false_if_true_symbol) { if (compile_if_true_false_statement (selector, expr->v_expr.expression)) return; } else if (selector == _gst_and_symbol || selector == _gst_or_symbol) { if (compile_and_or_statement (selector, expr->v_expr.expression)) return; } else if (selector == _gst_times_repeat_symbol) { if (compile_times_repeat (expr->v_expr.expression)) return; } else if (selector == _gst_to_do_symbol) { if (compile_to_by_do (expr->v_expr.expression->v_list.value, NULL, expr->v_expr.expression->v_list.next->v_list.value)) return; } else if (selector == _gst_to_by_do_symbol) { if (compile_to_by_do (expr->v_expr.expression->v_list.value, expr->v_expr.expression->v_list.next->v_list.value, expr->v_expr.expression->v_list.next->v_list.next->v_list.value)) return; } numArgs = list_length (expr->v_expr.expression); compile_keyword_list (expr->v_expr.expression); compile_send (expr, selector, numArgs); } void compile_send (tree_node expr, OOP selector, int numArgs) { const char *str = (const char *) OOP_TO_OBJ (selector)->data; int len = NUM_INDEXABLE_FIELDS (selector); struct builtin_selector *bs = _gst_lookup_builtin_selector (str, len); int super = expr->v_expr.receiver && is_super (expr->v_expr.receiver); if (super && IS_NIL (SUPERCLASS (_gst_this_class))) { _gst_errorf ("cannot send to super from within a root class\n"); EXIT_COMPILATION (); } if (super) compile_constant (_gst_make_oop_constant (&expr->location, SUPERCLASS (_gst_this_class))); if (!bs) { int selectorIndex = _gst_add_forced_object (selector); _gst_compile_byte (SEND | super, (selectorIndex << 8) | numArgs); } else if (!super && bs->bytecode < 32) _gst_compile_byte (bs->bytecode, 0); else _gst_compile_byte (SEND_IMMEDIATE | super, bs->bytecode); SUB_STACK_DEPTH (numArgs); } void compile_keyword_list (tree_node list) { for (; list; list = list->v_list.next) compile_expression (list->v_list.value); } mst_Boolean compile_while_loop (OOP selector, tree_node expr) { int finalJumpLen, finalJumpOfs, jumpAroundLen, jumpAroundOfs, oldJumpAroundLen; int whileCondLen; bc_vector receiverExprCodes, whileExprCodes = NULL; mst_Boolean colon, whileTrue; colon = (expr->v_expr.expression != NULL); whileTrue = (selector == _gst_while_true_colon_symbol) || (selector == _gst_while_true_symbol); if (expr->v_expr.receiver->nodeType != TREE_BLOCK_NODE || (colon && expr->v_expr.expression->v_list.value->nodeType != TREE_BLOCK_NODE)) return (false); if (HAS_PARAMS_OR_TEMPS (expr->v_expr.receiver) || (colon && HAS_PARAMS_OR_TEMPS (expr->v_expr.expression->v_list.value))) return (false); receiverExprCodes = compile_sub_expression (expr->v_expr.receiver); whileCondLen = _gst_bytecode_length (receiverExprCodes); _gst_compile_and_free_bytecodes (receiverExprCodes); if (colon) { whileExprCodes = compile_sub_expression (expr->v_expr.expression->v_list.value); jumpAroundOfs = _gst_bytecode_length (whileExprCodes) + 2; } else jumpAroundOfs = 0; for (oldJumpAroundLen = finalJumpLen = 0; ; oldJumpAroundLen = jumpAroundLen) { finalJumpOfs = whileCondLen + 2 + oldJumpAroundLen + jumpAroundOfs; finalJumpLen = (finalJumpOfs + finalJumpLen >= 65536 ? 6 : finalJumpOfs + finalJumpLen >= 256 ? 4 : 2); finalJumpLen = (finalJumpOfs + finalJumpLen >= 65536 ? 6 : finalJumpOfs + finalJumpLen >= 256 ? 4 : 2); jumpAroundLen = (jumpAroundOfs + finalJumpLen >= 65536 ? 6 : jumpAroundOfs + finalJumpLen >= 256 ? 4 : 2); if (jumpAroundLen == oldJumpAroundLen) break; } /* skip to the while loop if the receiver block yields the proper value */ compile_jump (jumpAroundLen, whileTrue); /* otherwise, skip to the end, past the pop stack top and 2 byte jump and exit the loop */ _gst_compile_byte (JUMP, jumpAroundOfs + finalJumpLen); if (colon) { _gst_compile_and_free_bytecodes (whileExprCodes); _gst_compile_byte (POP_STACK_TOP, 0); /* we don't care about while expr's value */ SUB_STACK_DEPTH (1); } _gst_compile_byte (JUMP_BACK, finalJumpLen + finalJumpOfs); /* while loops always return nil (ain't expression languages grand?) -- inefficient, but anyway the optimizer deletes this. */ INCR_STACK_DEPTH (); _gst_compile_byte (PUSH_SPECIAL, NIL_INDEX); return (true); } mst_Boolean compile_repeat (tree_node receiver) { int repeatedLoopLen, finalJumpLen; bc_vector receiverExprCodes; if (receiver->nodeType != TREE_BLOCK_NODE) return (false); if (HAS_PARAMS_OR_TEMPS (receiver)) return (false); receiverExprCodes = compile_sub_expression (receiver); repeatedLoopLen = _gst_bytecode_length (receiverExprCodes); repeatedLoopLen += 2; finalJumpLen = (repeatedLoopLen >= 65536 ? 6 : repeatedLoopLen >= 256 ? 4 : 2); finalJumpLen = (repeatedLoopLen + finalJumpLen >= 65536 ? 6 : repeatedLoopLen + finalJumpLen >= 256 ? 4 : 2); finalJumpLen = (repeatedLoopLen + finalJumpLen >= 65536 ? 6 : repeatedLoopLen + finalJumpLen >= 256 ? 4 : 2); _gst_compile_and_free_bytecodes (receiverExprCodes); _gst_compile_byte (POP_STACK_TOP, 0); /* we don't care about expr's value */ SUB_STACK_DEPTH (1); _gst_compile_byte (JUMP_BACK, finalJumpLen + repeatedLoopLen); /* this code is unreachable, it is only here to please the JIT compiler */ _gst_compile_byte (PUSH_SPECIAL, NIL_INDEX); INCR_STACK_DEPTH (); return (true); } mst_Boolean compile_times_repeat (tree_node expr) { int jumpAroundOfs, oldJumpAroundLen, jumpAroundLen; int finalJumpOfs, finalJumpLen; bc_vector loopExprCodes; if (expr->v_list.value->nodeType != TREE_BLOCK_NODE) return (false); if (HAS_PARAMS_OR_TEMPS (expr->v_list.value)) return (false); /* save the receiver for the return value */ _gst_compile_byte (DUP_STACK_TOP, 0); INCR_STACK_DEPTH (); loopExprCodes = compile_sub_expression (expr->v_list.value); _gst_compile_byte (DUP_STACK_TOP, 0); INCR_STACK_DEPTH (); _gst_compile_byte (PUSH_INTEGER, 1); INCR_STACK_DEPTH (); _gst_compile_byte (GREATER_EQUAL_SPECIAL, 0); SUB_STACK_DEPTH (1); /* skip the loop if there are no more occurrences */ jumpAroundOfs = 6 + _gst_bytecode_length (loopExprCodes); for (oldJumpAroundLen = finalJumpLen = 0; ; oldJumpAroundLen = jumpAroundLen) { finalJumpOfs = 6 + oldJumpAroundLen + jumpAroundOfs; finalJumpLen = (finalJumpOfs + finalJumpLen > 65536 ? 6 : finalJumpOfs + finalJumpLen > 256 ? 4 : 2); finalJumpLen = (finalJumpOfs + finalJumpLen > 65536 ? 6 : finalJumpOfs + finalJumpLen > 256 ? 4 : 2); jumpAroundLen = (jumpAroundOfs + finalJumpLen > 65536 ? 6 : jumpAroundOfs + finalJumpLen > 256 ? 4 : 2); if (jumpAroundLen == oldJumpAroundLen) break; } compile_jump (jumpAroundOfs + finalJumpLen, false); _gst_compile_byte (PUSH_INTEGER, 1); INCR_STACK_DEPTH (); _gst_compile_byte (MINUS_SPECIAL, 0); SUB_STACK_DEPTH (1); /* we don't care about block expr's value */ _gst_compile_and_free_bytecodes (loopExprCodes); _gst_compile_byte (POP_STACK_TOP, 0); SUB_STACK_DEPTH (1); _gst_compile_byte (JUMP_BACK, finalJumpLen + finalJumpOfs); /* delete the 0 that remains on the stack */ _gst_compile_byte (POP_STACK_TOP, 0); SUB_STACK_DEPTH (1); return (true); } mst_Boolean compile_to_by_do (tree_node to, tree_node by, tree_node block) { int jumpAroundOfs, oldJumpAroundLen, jumpAroundLen; int finalJumpOfs, finalJumpLen; int index; bc_vector loopExprCodes, stepCodes = NULL; /* initialize to please gcc */ if (block->nodeType != TREE_BLOCK_NODE) return (false); if (HAS_NOT_ONE_PARAM_OR_TEMPS (block)) return (false); if (by) { if (by->nodeType != TREE_CONST_EXPR || by->v_const.constType != CONST_INT) return (false); } index = _gst_declare_name (block->v_block.arguments->v_list.name, false, true); _gst_compile_byte (STORE_TEMPORARY_VARIABLE, index); compile_expression (to); _gst_compile_byte (DUP_STACK_TOP, index); INCR_STACK_DEPTH (); _gst_compile_byte (PUSH_TEMPORARY_VARIABLE, index); if (by) { bc_vector current_bytecodes; current_bytecodes = _gst_save_bytecode_array (); compile_expression (by); stepCodes = _gst_get_bytecodes (); _gst_restore_bytecode_array (current_bytecodes); jumpAroundOfs = _gst_bytecode_length (stepCodes); } else jumpAroundOfs = 2; loopExprCodes = compile_sub_expression (block); jumpAroundOfs += _gst_bytecode_length (loopExprCodes) + 10; for (oldJumpAroundLen = jumpAroundLen = finalJumpLen = 0; ; oldJumpAroundLen = jumpAroundLen) { finalJumpOfs = jumpAroundOfs + jumpAroundLen + 2; finalJumpLen = (finalJumpOfs + finalJumpLen > 65536 ? 6 : finalJumpOfs + finalJumpLen > 256 ? 4 : 2); finalJumpLen = (finalJumpOfs + finalJumpLen > 65536 ? 6 : finalJumpOfs + finalJumpLen > 256 ? 4 : 2); jumpAroundLen = (jumpAroundOfs + finalJumpLen > 65536 ? 6 : jumpAroundOfs + finalJumpLen > 256 ? 4 : 2); if (jumpAroundLen == oldJumpAroundLen) break; } /* skip the loop if there are no more occurrences */ _gst_compile_byte ((!by || by->v_const.val.iVal > 0) ? GREATER_EQUAL_SPECIAL : LESS_EQUAL_SPECIAL, 0); SUB_STACK_DEPTH (1); compile_jump (jumpAroundOfs + finalJumpLen, false); /* we don't care about loop expr's value */ _gst_compile_and_free_bytecodes (loopExprCodes); _gst_compile_byte (POP_STACK_TOP, 0); SUB_STACK_DEPTH (1); _gst_compile_byte (DUP_STACK_TOP, 0); INCR_STACK_DEPTH (); _gst_compile_byte (PUSH_TEMPORARY_VARIABLE, index); INCR_STACK_DEPTH (); if (by) _gst_compile_and_free_bytecodes (stepCodes); else { _gst_compile_byte (PUSH_INTEGER, 1); INCR_STACK_DEPTH (); } _gst_compile_byte (PLUS_SPECIAL, 0); SUB_STACK_DEPTH (1); _gst_compile_byte (STORE_TEMPORARY_VARIABLE, index); _gst_compile_byte (JUMP_BACK, finalJumpOfs + finalJumpLen); /* delete the end from the stack */ _gst_compile_byte (POP_STACK_TOP, 0); SUB_STACK_DEPTH (1); _gst_undeclare_name (); return (true); } mst_Boolean compile_if_true_false_statement (OOP selector, tree_node expr) { bc_vector trueByteCodes, falseByteCodes; if (expr->v_list.value->nodeType != TREE_BLOCK_NODE || expr->v_list.next->v_list.value->nodeType != TREE_BLOCK_NODE) return (false); if (HAS_PARAMS_OR_TEMPS (expr->v_list.value) || HAS_PARAMS_OR_TEMPS (expr->v_list.next->v_list.value)) return (false); if (selector == _gst_if_true_if_false_symbol) { falseByteCodes = compile_sub_expression (expr->v_list.next->v_list.value); trueByteCodes = compile_sub_expression_and_jump (expr->v_list.value, _gst_bytecode_length (falseByteCodes)); } else { falseByteCodes = compile_sub_expression (expr->v_list.value); trueByteCodes = compile_sub_expression_and_jump (expr->v_list.next->v_list. value, _gst_bytecode_length (falseByteCodes)); } compile_jump (_gst_bytecode_length (trueByteCodes), false); _gst_compile_and_free_bytecodes (trueByteCodes); _gst_compile_and_free_bytecodes (falseByteCodes); return (true); } mst_Boolean compile_if_statement (OOP selector, tree_node expr) { bc_vector thenByteCodes; if (expr->v_list.value->nodeType != TREE_BLOCK_NODE || HAS_PARAMS_OR_TEMPS (expr->v_list.value)) return (false); /* The second parameter (2) is the size of a `push nil' bytecode */ thenByteCodes = compile_sub_expression_and_jump (expr->v_list.value, 2); compile_jump (_gst_bytecode_length (thenByteCodes), selector == _gst_if_false_symbol); _gst_compile_and_free_bytecodes (thenByteCodes); /* Compare the code produced here with that produced in #and:/#or: This produces less efficient bytecodes if the condition is true (there are two jumps instead of one). Actually, the push will 99% of the times be followed by a pop stack top, and the optimizer changes 0: jump to 4 2: push nil 4: pop stack top to a single pop -- so the code ends up being quite efficent. Note that instead the result of #and:/#or: will be used (no pop) so we use the other possible encoding. */ _gst_compile_byte (PUSH_SPECIAL, NIL_INDEX); return (true); } mst_Boolean compile_and_or_statement (OOP selector, tree_node expr) { bc_vector blockByteCodes; int blockLen; if (expr->v_list.value->nodeType != TREE_BLOCK_NODE || HAS_PARAMS_OR_TEMPS (expr->v_list.value)) return (false); blockByteCodes = compile_sub_expression (expr->v_list.value); blockLen = _gst_bytecode_length (blockByteCodes); _gst_compile_byte (DUP_STACK_TOP, 0); compile_jump (blockLen + 2, selector == _gst_or_symbol); _gst_compile_byte (POP_STACK_TOP, 0); _gst_compile_and_free_bytecodes (blockByteCodes); return (true); } bc_vector compile_sub_expression (tree_node expr) { mst_Boolean returns; bc_vector current_bytecodes, subExprByteCodes; current_bytecodes = _gst_save_bytecode_array (); returns = compile_statements (expr->v_block.statements, false); if (returns) INCR_STACK_DEPTH (); subExprByteCodes = _gst_get_bytecodes (); _gst_restore_bytecode_array (current_bytecodes); return (subExprByteCodes); } bc_vector compile_sub_expression_and_jump (tree_node expr, int branchLen) { bc_vector current_bytecodes, subExprByteCodes; mst_Boolean returns; current_bytecodes = _gst_save_bytecode_array (); returns = compile_statements (expr->v_block.statements, false); if (returns) INCR_STACK_DEPTH (); if (!returns) _gst_compile_byte (JUMP, branchLen); subExprByteCodes = _gst_get_bytecodes (); _gst_restore_bytecode_array (current_bytecodes); return (subExprByteCodes); } void compile_jump (int len, mst_Boolean jumpType) { if (len <= 0) { _gst_errorf ("invalid length jump %d -- internal error\n", len); EXIT_COMPILATION (); } SUB_STACK_DEPTH (1); _gst_compile_byte (jumpType ? POP_JUMP_TRUE : POP_JUMP_FALSE, len); } void compile_cascaded_message (tree_node cascadedExpr) { tree_node message; dup_message_receiver = true; compile_expression (cascadedExpr->v_expr.receiver); for (message = cascadedExpr->v_expr.expression; message; message = message->v_list.next) { _gst_compile_byte (POP_STACK_TOP, 0); if (message->v_list.next) _gst_compile_byte (DUP_STACK_TOP, 0); else SUB_STACK_DEPTH (1); compile_expression (message->v_list.value); /* !!! remember that unary, binary and keywordexpr should ignore the receiver field if it is nil; that is the case for these functions and things work out fine if that's the case. */ } } void compile_assignments (tree_node varList) { symbol_entry variable; for (; varList; varList = varList->v_list.next) { tree_node varName = varList->v_list.value; _gst_line_number (varList->location.first_line, 0); if (!_gst_find_variable (&variable, varName)) { if (varName->v_list.next) _gst_errorf_at (varName->location.first_line, "invalid scope resolution"); else _gst_errorf_at (varName->location.first_line, "assignment to undeclared variable %s", varName->v_list.name); EXIT_COMPILATION (); } if (variable.readOnly) { _gst_errorf_at (varName->location.first_line, "invalid assignment to %s %s", _gst_get_scope_kind (variable.scope), varName->v_list.name); EXIT_COMPILATION (); } /* Here we have several kinds of things to store: receiver variable, temporary variable, global variable (reference by association). */ if (variable.scope != SCOPE_GLOBAL && varName->v_list.next) { _gst_errorf_at (varName->location.first_line, "invalid scope resolution"); EXIT_COMPILATION (); } if (variable.scopeDistance > 0) _gst_compile_byte (STORE_OUTER_TEMP, (variable.varIndex << 8) | variable.scopeDistance); else if (variable.scope == SCOPE_TEMPORARY) _gst_compile_byte (STORE_TEMPORARY_VARIABLE, variable.varIndex); else if (variable.scope == SCOPE_RECEIVER) _gst_compile_byte (STORE_RECEIVER_VARIABLE, variable.varIndex); else { /* This can become a message send, which might not return the value. Compile it in a way that can be easily peephole optimized. */ _gst_compile_byte (STORE_LIT_VARIABLE, variable.varIndex); _gst_compile_byte (POP_STACK_TOP, 0); _gst_compile_byte (PUSH_LIT_VARIABLE, variable.varIndex); } } } mst_Boolean is_super (tree_node expr) { return (expr->nodeType == TREE_VARIABLE_NODE && _gst_intern_string (expr->v_list.name) == _gst_super_symbol); } mst_Boolean equal_constant (OOP oop, tree_node constExpr) { tree_node arrayElt; size_t len, i; /* ??? this kind of special casing of the elements of arrays bothers me...it should all be in one neat place. */ if (constExpr->nodeType == TREE_SYMBOL_NODE) /* symbol in array constant */ return (oop == constExpr->v_expr.selector); else if (constExpr->nodeType == TREE_ARRAY_ELT_LIST) { if (IS_OOP (oop) && OOP_CLASS (oop) == _gst_array_class) { for (len = 0, arrayElt = constExpr; arrayElt; len++, arrayElt = arrayElt->v_list.next); if (len == NUM_OOPS (OOP_TO_OBJ (oop))) { for (i = 1, arrayElt = constExpr; i <= len; i++, arrayElt = arrayElt->v_list.next) { if (!equal_constant (ARRAY_AT (oop, i), arrayElt->v_list.value)) return (false); } return (true); } } return (false); } switch (constExpr->v_const.constType) { case CONST_INT: if (oop == FROM_INT (constExpr->v_const.val.iVal)) return (true); break; case CONST_CHAR: if (IS_OOP (oop) && is_a_kind_of (OOP_CLASS (oop), _gst_char_class) && CHAR_OOP_VALUE (oop) == constExpr->v_const.val.iVal) return (true); break; case CONST_FLOATD: if (IS_OOP (oop) && OOP_CLASS (oop) == _gst_floatd_class) { double d = (double) constExpr->v_const.val.fVal; if (!memcmp (&d, &OOP_TO_OBJ (oop)->data, sizeof (double))) return (true); } break; case CONST_FLOATE: if (IS_OOP (oop) && OOP_CLASS (oop) == _gst_floate_class) { float f = (float) constExpr->v_const.val.fVal; if (!memcmp (&f, &OOP_TO_OBJ (oop)->data, sizeof (float))) return (true); } break; case CONST_FLOATQ: if (IS_OOP (oop) && OOP_CLASS (oop) == _gst_floatq_class) { long double ld = (long double) constExpr->v_const.val.fVal; if (!memcmp (&ld, &OOP_TO_OBJ (oop)->data, sizeof (long double))) return (true); } break; case CONST_STRING: if (IS_OOP (oop) && OOP_CLASS (oop) == _gst_string_class) { len = strlen (constExpr->v_const.val.sVal); if (len == _gst_string_oop_len (oop)) { if (strncmp ((char *) OOP_TO_OBJ (oop)->data, constExpr->v_const.val.sVal, len) == 0) return (true); } } break; case CONST_DEFERRED_BINDING: if (IS_OOP (oop) && OOP_CLASS (oop) == _gst_deferred_variable_binding_class) { gst_deferred_variable_binding binding = (gst_deferred_variable_binding) OOP_TO_OBJ (oop); gst_object path = OOP_TO_OBJ (binding->path); int i, size = NUM_OOPS (path); OOP *pKey; tree_node varNode = constExpr->v_const.val.aVal; /* Use <= because we test the key first. */ for (i = 0, pKey = &binding->key; i <= size; pKey = &path->data[i++]) { if (!varNode || *pKey != _gst_intern_string (varNode->v_list.name)) return (false); varNode = varNode->v_list.next; } } break; case CONST_BINDING: constExpr = _gst_find_variable_binding (constExpr->v_const.val.aVal); if (!constExpr) return (false); assert (constExpr->v_const.constType != CONST_BINDING); return equal_constant (oop, constExpr); case CONST_OOP: if (oop == constExpr->v_const.val.oopVal) return (true); break; case CONST_ARRAY: if (IS_OOP (oop) && OOP_CLASS (oop) == _gst_array_class) { /* ??? could keep the length in a counter */ for (len = 0, arrayElt = constExpr->v_const.val.aVal; arrayElt; len++, arrayElt = arrayElt->v_list.next); if (len == NUM_OOPS (OOP_TO_OBJ (oop))) { for (i = 1, arrayElt = constExpr->v_const.val.aVal; i <= len; i++, arrayElt = arrayElt->v_list.next) { if (!equal_constant (ARRAY_AT (oop, i), arrayElt->v_list.value)) return (false); } return (true); } } break; default: break; } return (false); } OOP _gst_make_constant_oop (tree_node constExpr) { tree_node subexpr; int len, i; OOP resultOOP, elementOOP; inc_ptr incPtr; byte_object bo; gst_object result; if (constExpr == NULL) return (_gst_nil_oop); /* special case empty array literals */ if (constExpr->nodeType == TREE_SYMBOL_NODE) /* symbol in array constant */ return (constExpr->v_expr.selector); else if (constExpr->nodeType == TREE_ARRAY_ELT_LIST) { for (len = 0, subexpr = constExpr; subexpr; len++, subexpr = subexpr->v_list.next); incPtr = INC_SAVE_POINTER (); /* this might be an uninitialized form of array creation for speed; but not now -- with the array temporarily part of the root set it must be completely initialized (sigh). */ instantiate_with (_gst_array_class, len, &resultOOP); INC_ADD_OOP (resultOOP); for (i = 0, subexpr = constExpr; i < len; i++, subexpr = subexpr->v_list.next) { elementOOP = _gst_make_constant_oop (subexpr->v_list.value); result = OOP_TO_OBJ (resultOOP); result->data[i] = elementOOP; } MAKE_OOP_READONLY (resultOOP, true); INC_RESTORE_POINTER (incPtr); return (resultOOP); } switch (constExpr->v_const.constType) { case CONST_INT: return (FROM_INT (constExpr->v_const.val.iVal)); case CONST_CHAR: return (char_new (constExpr->v_const.val.iVal)); case CONST_FLOATD: return (floatd_new (constExpr->v_const.val.fVal)); case CONST_FLOATE: return (floate_new (constExpr->v_const.val.fVal)); case CONST_FLOATQ: return (floatq_new (constExpr->v_const.val.fVal)); case CONST_STRING: resultOOP = _gst_string_new (constExpr->v_const.val.sVal); MAKE_OOP_READONLY (resultOOP, true); return (resultOOP); case CONST_BYTE_OBJECT: bo = constExpr->v_const.val.boVal; result = instantiate_with (bo->class, bo->size, &resultOOP); memcpy (result->data, bo->body, bo->size); MAKE_OOP_READONLY (resultOOP, true); return (resultOOP); case CONST_DEFERRED_BINDING: { gst_deferred_variable_binding dvb; tree_node varNode = constExpr->v_const.val.aVal; incPtr = INC_SAVE_POINTER (); dvb = (gst_deferred_variable_binding) instantiate (_gst_deferred_variable_binding_class, &resultOOP); INC_ADD_OOP (resultOOP); dvb->key = _gst_intern_string (varNode->v_list.name); dvb->class = _gst_this_class; dvb->defaultDictionary = _gst_get_undeclared_dictionary (); dvb->association = _gst_nil_oop; varNode = varNode->v_list.next; if (varNode) { int i, size = list_length (varNode); OOP arrayOOP; gst_object array = instantiate_with (_gst_array_class, size, &arrayOOP); dvb->path = arrayOOP; for (i = 0; i < size; i++, varNode = varNode->v_list.next) array->data[i] = _gst_intern_string (varNode->v_list.name); } INC_RESTORE_POINTER (incPtr); return (resultOOP); } case CONST_BINDING: subexpr = _gst_find_variable_binding (constExpr->v_const.val.aVal); if (!subexpr) { _gst_errorf_at (constExpr->location.first_line, "invalid variable binding"); EXIT_COMPILATION (); } assert (subexpr->v_const.constType != CONST_BINDING); return _gst_make_constant_oop (subexpr); case CONST_OOP: return (constExpr->v_const.val.oopVal); case CONST_ARRAY: for (len = 0, subexpr = constExpr->v_const.val.aVal; subexpr; len++, subexpr = subexpr->v_list.next); incPtr = INC_SAVE_POINTER (); result = instantiate_with (_gst_array_class, len, &resultOOP); INC_ADD_OOP (resultOOP); for (i = 0, subexpr = constExpr->v_const.val.aVal; i < len; i++, subexpr = subexpr->v_list.next) { elementOOP = _gst_make_constant_oop (subexpr->v_list.value); result = OOP_TO_OBJ (resultOOP); result->data[i] = elementOOP; } MAKE_OOP_READONLY (resultOOP, true); INC_RESTORE_POINTER (incPtr); return (resultOOP); } return (_gst_nil_oop); } OOP make_block (int args, int temps, bc_vector bytecodes, int stack_depth) { OOP blockOOP; if (_gst_declare_tracing) { printf (" Code for enclosed block:\n"); #ifdef PRINT_BEFORE_OPTIMIZATION _gst_print_bytecodes (bytecodes, literal_vec); #endif } bytecodes = _gst_optimize_bytecodes (bytecodes); if (_gst_declare_tracing) _gst_print_bytecodes (bytecodes, literal_vec); blockOOP = _gst_block_new (args, temps, bytecodes, stack_depth, literal_vec); _gst_free_bytecodes (bytecodes); return (blockOOP); } OOP make_clean_block_closure (OOP blockOOP) { gst_block_closure closure; OOP closureOOP; closure = (gst_block_closure) new_instance (_gst_block_closure_class, &closureOOP); /* Use the class as the receiver. This is blatantly wrong, but at least sets the correct trustfulness on the contexts. If the receiver was nil, for example, untrusted clean blocks evaluated from a trusted environment would be treated as trusted (because nil is trusted). */ closure->receiver = _gst_this_class; closure->outerContext = _gst_nil_oop; closure->block = blockOOP; return (closureOOP); } OOP compute_selector (tree_node selectorExpr) { if (selectorExpr->nodeType == TREE_UNARY_EXPR || selectorExpr->nodeType == TREE_BINARY_EXPR) return (selectorExpr->v_expr.selector); else return (_gst_compute_keyword_selector (selectorExpr->v_expr.expression)); } OOP _gst_compute_keyword_selector (tree_node keywordList) { tree_node keyword; int len; char *nameBuf, *p; len = 0; for (keyword = keywordList; keyword != NULL; keyword = keyword->v_list.next) len += strlen (keyword->v_list.name); p = nameBuf = (char *) alloca (len + 1); for (keyword = keywordList; keyword != NULL; keyword = keyword->v_list.next) { len = strlen (keyword->v_list.name); strcpy (p, keyword->v_list.name); p += len; } *p = '\0'; return (_gst_intern_string (nameBuf)); } OOP _gst_make_attribute (tree_node attribute_keywords) { tree_node keyword; OOP selectorOOP, argsArrayOOP, messageOOP; gst_object argsArray; int i, numArgs; inc_ptr incPtr; incPtr = INC_SAVE_POINTER (); if (_gst_had_error) return _gst_nil_oop; selectorOOP = _gst_compute_keyword_selector (attribute_keywords); numArgs = list_length (attribute_keywords); argsArray = instantiate_with (_gst_array_class, numArgs, &argsArrayOOP); INC_ADD_OOP (argsArrayOOP); for (i = 0, keyword = attribute_keywords; keyword != NULL; i++, keyword = keyword->v_list.next) { tree_node value = keyword->v_list.value; OOP result; if (value->nodeType != TREE_CONST_EXPR) { result = _gst_execute_statements (NULL, value, UNDECLARED_NONE, true); if (!result) { _gst_had_error = true; return _gst_nil_oop; } } else result = _gst_make_constant_oop (value); argsArray = OOP_TO_OBJ (argsArrayOOP); argsArray->data[i] = result; } messageOOP = _gst_message_new_args (selectorOOP, argsArrayOOP); INC_RESTORE_POINTER (incPtr); MAKE_OOP_READONLY (argsArrayOOP, true); MAKE_OOP_READONLY (messageOOP, true); return (messageOOP); } int process_attributes_tree (tree_node attribute_list) { int primitiveIndex = 0; for (; attribute_list; attribute_list = attribute_list->v_list.next) { tree_node value = attribute_list->v_list.value; OOP messageOOP = value->v_const.val.oopVal; int result = process_attribute (messageOOP); if (result < 0) { EXIT_COMPILATION (); } if (result > 0) { if (IS_OOP_UNTRUSTED (_gst_this_class)) { _gst_errorf ("an untrusted class cannot declare primitives"); EXIT_COMPILATION (); } if (primitiveIndex > 0) { _gst_errorf ("duplicate primitive declaration"); EXIT_COMPILATION (); } primitiveIndex = result; } } return primitiveIndex; } int _gst_process_attributes_array (OOP arrayOOP) { int primitiveIndex = 0; int n = NUM_WORDS (OOP_TO_OBJ (arrayOOP)); int i; if (IS_NIL (arrayOOP)) return 0; for (i = 0; i < n; i++) { OOP messageOOP = OOP_TO_OBJ (arrayOOP)->data[i]; int result = process_attribute (messageOOP); if (result < 0) return (-1); if (result > 0) { if (primitiveIndex > 0) return (-1); primitiveIndex = result; } } return primitiveIndex; } int process_attribute (OOP messageOOP) { gst_message message = (gst_message) OOP_TO_OBJ (messageOOP); OOP selectorOOP = message->selector; OOP argumentsOOP = message->args; gst_object arguments = OOP_TO_OBJ (argumentsOOP); if (selectorOOP == _gst_primitive_symbol) { if (IS_INT (arguments->data[0])) { int primitiveIndex = TO_INT (arguments->data[0]); if (primitiveIndex <= 0 || primitiveIndex >= NUM_PRIMITIVES) { _gst_errorf ("primitive number out of range"); return (-1); } return (primitiveIndex); } else { _gst_errorf ("bad primitive number, expected SmallInteger"); return (-1); } } else if (selectorOOP == _gst_category_symbol) { this_method_category = arguments->data[0]; return (0); } else { method_attributes *new_attr = (method_attributes *) xmalloc (sizeof (method_attributes)); new_attr->count = method_attrs ? method_attrs->count + 1 : 0; new_attr->oop = messageOOP; new_attr->next = method_attrs; method_attrs = new_attr; _gst_register_oop (messageOOP); return (0); } } void realloc_literal_vec (void) { int size; ptrdiff_t delta; size = literal_vec_max - literal_vec + LITERAL_VEC_CHUNK_SIZE; delta = ((OOP *) xrealloc (literal_vec, size * sizeof (OOP))) - literal_vec; literal_vec += delta; literal_vec_curr += delta; literal_vec_max = literal_vec + size; } int list_length (tree_node listExpr) { tree_node l; long len; for (len = 0, l = listExpr; l; l = l->v_list.next, len++); if (sizeof (int) < sizeof (long) && len > INT_MAX) { _gst_errorf ("list too long, %ld", len); len = INT_MAX; } return ((int) len); } /*********************************************************************** * * Literal Vector manipulation routines. * ***********************************************************************/ int add_literal (OOP oop) { if (literal_vec_curr >= literal_vec_max) realloc_literal_vec (); *literal_vec_curr++ = oop; return (literal_vec_curr - literal_vec - 1); } int _gst_add_forced_object (OOP oop) { OOP *lit; for (lit = literal_vec; lit < literal_vec_curr; lit++) if (*lit == oop) return (lit - literal_vec); return (add_literal (oop)); } OOP get_literals_array (void) { OOP methodLiteralsOOP; gst_object methodLiterals; assert (literal_vec_curr > literal_vec); methodLiterals = new_instance_with (_gst_array_class, literal_vec_curr - literal_vec, &methodLiteralsOOP); memcpy (methodLiterals->data, literal_vec, (literal_vec_curr - literal_vec) * sizeof(OOP)); literal_vec_curr = literal_vec; MAKE_OOP_READONLY (methodLiteralsOOP, true); return (methodLiteralsOOP); } void install_method (OOP methodOOP) { OOP oldMethod, selector, methodDictionaryOOP; gst_compiled_method method; gst_method_info descriptor; int num_attrs, i; method = (gst_compiled_method) OOP_TO_OBJ (methodOOP); descriptor = (gst_method_info) OOP_TO_OBJ (method->descriptor); num_attrs = NUM_INDEXABLE_FIELDS (method->descriptor); for (i = 0; i < num_attrs; i++) { char *result; OOP attributeOOP = descriptor->attributes[i]; gst_message attribute = (gst_message) OOP_TO_OBJ (attributeOOP); OOP handlerBlockOOP = _gst_find_pragma_handler (_gst_this_class, attribute->selector); if (!IS_NIL (handlerBlockOOP)) { _gst_msg_sendf (&result, "%s %o value: %o value: %o", handlerBlockOOP, methodOOP, attributeOOP); if (result != NULL) { _gst_errorf ("%s", result); EXIT_COMPILATION (); } } method = (gst_compiled_method) OOP_TO_OBJ (methodOOP); descriptor = (gst_method_info) OOP_TO_OBJ (method->descriptor); if (num_attrs != NUM_INDEXABLE_FIELDS (method->descriptor)) { _gst_errorf ("cannot modify method descriptor in pragma handler"); EXIT_COMPILATION (); } } selector = descriptor->selector; /* methodDictionaryOOP is held onto by the class, which is already reachable by the root set so we don't need to hold onto it here. */ methodDictionaryOOP = _gst_valid_class_method_dictionary (_gst_this_class); if (_gst_untrusted_methods) { oldMethod = _gst_identity_dictionary_at (methodDictionaryOOP, selector); if (!IS_NIL (oldMethod) && !IS_OOP_UNTRUSTED (oldMethod)) { _gst_errorf ("cannot redefine a trusted method as untrusted"); EXIT_COMPILATION (); } } MAKE_OOP_READONLY (methodOOP, true); oldMethod = _gst_identity_dictionary_at_put (methodDictionaryOOP, selector, methodOOP); #ifdef ENABLE_JIT_TRANSLATION if (oldMethod != _gst_nil_oop) _gst_discard_native_code (oldMethod); #endif #ifdef VERIFY_COMPILED_METHODS _gst_verify_sent_method (methodOOP); #endif _gst_invalidate_method_cache (); } OOP _gst_make_new_method (int primitiveIndex, int numArgs, int numTemps, int maximumStackDepth, OOP literals, bc_vector bytecodes, OOP class, OOP selector, OOP defaultCategoryOOP, int64_t startPos, int64_t endPos) { method_header header; int newFlags; OOP method, methodDesc, sourceCode, category; inc_ptr incPtr; maximumStackDepth += numArgs + numTemps; memset (&header, 0, sizeof (method_header)); incPtr = INC_SAVE_POINTER (); if (primitiveIndex) { if (_gst_declare_tracing) printf (" Primitive Index %d\n", primitiveIndex); header.headerFlag = MTH_PRIMITIVE; } else if (method_attrs) header.headerFlag = MTH_ANNOTATED; /* if returning a literal, we must either use comp.c's literal pool (IS_NIL (LITERALS)), get it from a preexisting literal pool (LITERAL_VEC_CURR == LITERAL_VEC), or put it into an empty pool (NUM_WORDS (...) == 0). */ else if (numArgs == 0 && numTemps == 0 && (newFlags = _gst_is_simple_return (bytecodes)) != 0 && (newFlags != MTH_RETURN_LITERAL || IS_NIL (literals) || NUM_WORDS (OOP_TO_OBJ (literals)) == 0 || literal_vec_curr == literal_vec)) { header.headerFlag = newFlags & 0xFF; /* if returning an instance variable, its index is indicated in the primitive index */ primitiveIndex = newFlags >> 8; numTemps = 0; _gst_free_bytecodes (bytecodes); bytecodes = NULL; /* If returning a literal but we have none, it was added with _gst_add_forced_object. */ } else header.headerFlag = MTH_NORMAL; if (literal_vec_curr > literal_vec) { literals = get_literals_array (); literal_vec_curr = literal_vec; INC_ADD_OOP (literals); } if (bytecodes) { #ifdef PRINT_BEFORE_OPTIMIZATION if (_gst_declare_tracing) _gst_print_bytecodes (bytecodes, OOP_TO_OBJ (literals)->data); #endif bytecodes = _gst_optimize_bytecodes (bytecodes); } if (_gst_declare_tracing) printf (" Allocated stack slots %d\n", maximumStackDepth); if (_gst_declare_tracing) _gst_print_bytecodes (bytecodes, OOP_TO_OBJ (literals)->data); maximumStackDepth += (1 << DEPTH_SCALE) - 1; /* round */ maximumStackDepth >>= DEPTH_SCALE; maximumStackDepth++; /* just to be sure */ header.stack_depth = maximumStackDepth; header.primitiveIndex = primitiveIndex; header.numArgs = numArgs; header.numTemps = numTemps; header.intMark = 1; if (this_method_category) { category = this_method_category; this_method_category = NULL; } else category = defaultCategoryOOP; if (IS_NIL (class)) sourceCode = _gst_nil_oop; else { sourceCode = _gst_get_source_string (startPos, endPos); INC_ADD_OOP (sourceCode); } methodDesc = method_info_new (class, selector, method_attrs, sourceCode, category); INC_ADD_OOP (methodDesc); method = method_new (header, literals, bytecodes, class, methodDesc); INC_RESTORE_POINTER (incPtr); return (method); } OOP method_new (method_header header, OOP literals, bc_vector bytecodes, OOP class, OOP methodDesc) { int numByteCodes; gst_compiled_method method; OOP methodOOP; gst_object lit; int i; if (bytecodes != NULL) numByteCodes = _gst_bytecode_length (bytecodes); else numByteCodes = 0; method_attrs = NULL; method = (gst_compiled_method) instantiate_with (_gst_compiled_method_class, numByteCodes, &methodOOP); MAKE_OOP_UNTRUSTED (methodOOP, _gst_untrusted_methods || IS_OOP_UNTRUSTED (_gst_this_context_oop) || IS_OOP_UNTRUSTED (class)); method->header = header; method->descriptor = methodDesc; method->literals = literals; for (lit = OOP_TO_OBJ (literals), i = NUM_OOPS (lit); i--;) { OOP blockOOP; gst_compiled_block block; if (IS_CLASS (lit->data[i], _gst_block_closure_class)) { gst_block_closure bc; bc = (gst_block_closure) OOP_TO_OBJ (lit->data[i]); blockOOP = bc->block; } else if (IS_CLASS (lit->data[i], _gst_compiled_block_class)) blockOOP = lit->data[i]; else continue; block = (gst_compiled_block) OOP_TO_OBJ (blockOOP); if (IS_NIL (block->method)) { MAKE_OOP_UNTRUSTED (blockOOP, IS_OOP_UNTRUSTED (methodOOP)); block->method = methodOOP; block->literals = literals; } } if (bytecodes != NULL) { _gst_copy_bytecodes (method->bytecodes, bytecodes); _gst_free_bytecodes (bytecodes); } return (methodOOP); } OOP _gst_block_new (int numArgs, int numTemps, bc_vector bytecodes, int maximumStackDepth, OOP * literals) { int numByteCodes; OOP blockOOP; gst_compiled_block block; block_header header; maximumStackDepth += numArgs + numTemps; maximumStackDepth += (1 << DEPTH_SCALE) - 1; /* round */ maximumStackDepth >>= DEPTH_SCALE; maximumStackDepth++; /* just to be sure */ numByteCodes = _gst_bytecode_length (bytecodes); memset (&header, 0, sizeof (header)); header.numArgs = numArgs; header.numTemps = numTemps; header.depth = maximumStackDepth; header.intMark = 1; header.clean = _gst_check_kind_of_block (bytecodes, literals); block = (gst_compiled_block) instantiate_with (_gst_compiled_block_class, numByteCodes, &blockOOP); block->header = header; block->method = block->literals = _gst_nil_oop; _gst_copy_bytecodes (block->bytecodes, bytecodes); MAKE_OOP_READONLY (blockOOP, true); return (blockOOP); } OOP method_info_new (OOP class, OOP selector, method_attributes *attrs, OOP sourceCode, OOP categoryOOP) { method_attributes *next; gst_method_info methodInfo; OOP methodInfoOOP; methodInfo = (gst_method_info) new_instance_with (_gst_method_info_class, attrs ? attrs->count + 1 : 0, &methodInfoOOP); methodInfo->sourceCode = sourceCode; methodInfo->category = categoryOOP; methodInfo->class = class; methodInfo->selector = selector; while (attrs) { methodInfo->attributes[attrs->count] = attrs->oop; next = attrs->next; _gst_unregister_oop (attrs->oop); free (attrs); attrs = next; } return (methodInfoOOP); } smalltalk-3.2.5/libgst/sysdep/0000755000175000017500000000000012130456004013274 500000000000000smalltalk-3.2.5/libgst/sysdep/win32/0000755000175000017500000000000012130456004014236 500000000000000smalltalk-3.2.5/libgst/sysdep/win32/signals.c0000644000175000017500000000751312123404352015771 00000000000000/******************************** -*- C -*- **************************** * * System specific implementation module. * * This module contains implementations of various operating system * specific routines. This module should encapsulate most (or all) * of these calls so that the rest of the code is portable. * * ***********************************************************************/ /*********************************************************************** * * Copyright 1988,89,90,91,92,94,95,99,2000,2001,2002,2003,2006,2007,2008,2009 * Free Software Foundation, Inc. * Written by Steve Byrne. * * This file is part of GNU Smalltalk. * * GNU Smalltalk is free software; you can redistribute it and/or modify it * under the terms of the GNU General Public License as published by the Free * Software Foundation; either version 2, or (at your option) any later * version. * * Linking GNU Smalltalk statically or dynamically with other modules is * making a combined work based on GNU Smalltalk. Thus, the terms and * conditions of the GNU General Public License cover the whole * combination. * * In addition, as a special exception, the Free Software Foundation * give you permission to combine GNU Smalltalk with free software * programs or libraries that are released under the GNU LGPL and with * independent programs running under the GNU Smalltalk virtual machine. * * You may copy and distribute such a system following the terms of the * GNU GPL for GNU Smalltalk and the licenses of the other code * concerned, provided that you include the source code of that other * code when and as the GNU GPL requires distribution of source code. * * Note that people who make modified versions of GNU Smalltalk are not * obligated to grant this special exception for their modified * versions; it is their choice whether to do so. The GNU General * Public License gives permission to release a modified version without * this exception; this exception also makes it possible to release a * modified version which carries forward this exception. * * GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or * FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for * more details. * * You should have received a copy of the GNU General Public License along with * GNU Smalltalk; see the file COPYING. If not, write to the Free Software * Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * ***********************************************************************/ #include "gstpriv.h" static long pending_sigs = 0; static SigHandler saved_handlers[NSIG]; static RETSIGTYPE dummy_signal_handler (int sig) { pending_sigs |= 1L << sig; signal (sig, SIG_IGN); } int _gst_signal_count; void _gst_disable_interrupts (mst_Boolean from_signal_handler) { __sync_synchronize (); if (_gst_signal_count++ == 0) { __sync_synchronize (); saved_handlers[SIGINT] = signal (SIGINT, dummy_signal_handler); saved_handlers[SIGBREAK] = signal (SIGBREAK, dummy_signal_handler); saved_handlers[SIGTERM] = signal (SIGTERM, dummy_signal_handler); } } void _gst_enable_interrupts (mst_Boolean from_signal_handler) { int i; long local_pending_sigs; __sync_synchronize (); if (--_gst_signal_count == 0) { __sync_synchronize (); signal (SIGINT, saved_handlers[SIGINT]); signal (SIGBREAK, saved_handlers[SIGBREAK]); signal (SIGTERM, saved_handlers[SIGTERM]); local_pending_sigs = pending_sigs; pending_sigs = 0; for (i = 0; local_pending_sigs; local_pending_sigs >>= 1, i++) if (local_pending_sigs & 1) raise (i); } } SigHandler _gst_set_signal_handler (int signum, SigHandler handlerFunc) { return signal (signum, handlerFunc); } smalltalk-3.2.5/libgst/sysdep/win32/files.c0000644000175000017500000001377012123404352015435 00000000000000/******************************** -*- C -*- **************************** * * System specific implementation module. * * This module contains implementations of various operating system * specific routines. This module should encapsulate most (or all) * of these calls so that the rest of the code is portable. * * ***********************************************************************/ /*********************************************************************** * * Copyright 1988,89,90,91,92,94,95,99,2000,2001,2002,2003,2006,2007,2008,2009 * Free Software Foundation, Inc. * Written by Steve Byrne. * * This file is part of GNU Smalltalk. * * GNU Smalltalk is free software; you can redistribute it and/or modify it * under the terms of the GNU General Public License as published by the Free * Software Foundation; either version 2, or (at your option) any later * version. * * Linking GNU Smalltalk statically or dynamically with other modules is * making a combined work based on GNU Smalltalk. Thus, the terms and * conditions of the GNU General Public License cover the whole * combination. * * In addition, as a special exception, the Free Software Foundation * give you permission to combine GNU Smalltalk with free software * programs or libraries that are released under the GNU LGPL and with * independent programs running under the GNU Smalltalk virtual machine. * * You may copy and distribute such a system following the terms of the * GNU GPL for GNU Smalltalk and the licenses of the other code * concerned, provided that you include the source code of that other * code when and as the GNU GPL requires distribution of source code. * * Note that people who make modified versions of GNU Smalltalk are not * obligated to grant this special exception for their modified * versions; it is their choice whether to do so. The GNU General * Public License gives permission to release a modified version without * this exception; this exception also makes it possible to release a * modified version which carries forward this exception. * * GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or * FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for * more details. * * You should have received a copy of the GNU General Public License along with * GNU Smalltalk; see the file COPYING. If not, write to the Free Software * Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * ***********************************************************************/ #include "gstpriv.h" #ifdef WIN32 # define WIN32_LEAN_AND_MEAN /* avoid including junk */ # include #endif #ifdef HAVE_SPAWNL #include #ifndef P_WAIT #define P_WAIT 0 #define P_NOWAIT 1 #define P_OVERLAY 2 #define P_NOWAITO 3 #define P_DETACH 4 #endif /* !P_WAIT */ #endif /* HAVE_SPAWNL */ char * _gst_get_full_file_name (const char *name) { char *rpath; long int path_max; struct stat st; DWORD retval; path_max = PATH_MAX; rpath = malloc (path_max); if (rpath == NULL) return NULL; retval = GetFullPathNameA (name, path_max, rpath, NULL); if (retval > path_max) { rpath = realloc (rpath, retval); retval = GetFullPathNameA (name, retval, rpath, NULL); } if (retval != 0 && stat (rpath, &st) != -1) return rpath; { int saved_errno = errno; free (rpath); errno = saved_errno; } return NULL; } #define NAMED_PIPE_PREFIX "\\\\..\\pipe\\_gnu_smalltalk_named_pipe" int _gst_open_pipe (const char *command, const char *mode) { int master, slave; int access; int result; int save_stdin = -1; int save_stdout = -1; char slavenam[sizeof (NAMED_PIPE_PREFIX) + 25]; HANDLE hMaster, hSlave; static long int id = 0; access = strchr (mode, '+') ? O_RDWR : (mode[0] == 'r' ? O_RDONLY : O_WRONLY); /* Windows 95 only has anonymous pipes, so we prefer them for unidirectional pipes; we have no choice but named pipes for bidirectional operation. Note that CreatePipe gives two handles, so we open both sides at once and store the file descriptor into SLAVE, while CreateNamedPipe has to be opened on the slave side separately. */ switch (access) { case O_RDONLY: if (!CreatePipe (&hMaster, &hSlave, NULL, 0)) return -1; slave = _open_osfhandle (hSlave, O_WRONLY | O_BINARY); break; case O_WRONLY: if (!CreatePipe (&hSlave, &hMaster, NULL, 0)) return -1; slave = _open_osfhandle (hSlave, O_RDONLY | O_BINARY); break; case O_RDWR: sprintf (slavenam, NAMED_PIPE_PREFIX "_%d_%d__", getpid (), id++); hMaster = CreateNamedPipe (slavenam, PIPE_ACCESS_DUPLEX, 0, 1, 0, 0, 0, NULL); if (!hMaster) return -1; slave = open (slavenam, O_RDWR | O_BINARY); break; } master = _open_osfhandle (hMaster, access | O_NOINHERIT | O_BINARY); if (master == -1 || slave == -1) { if (master != -1) close (master); if (slave != -1) close (slave); return -1; } /* Duplicate the handles. Which handles are to be hooked is anti-intuitive: remember that ACCESS gives the parent's point of view, not the child's, so `read only' means the child should write to the pipe and `write only' means the child should read from the pipe. */ if (access != O_RDONLY) { save_stdin = dup (0); dup2 (slave, 0); } if (access != O_WRONLY) { save_stdout = dup (1); dup2 (slave, 1); } if (slave > 2) close (slave); result = spawnl (P_NOWAIT, getenv("COMSPEC"), "/C", command, NULL); if (save_stdin != -1) { dup2 (save_stdin, 0); close (save_stdin); } if (save_stdout != -1) { dup2 (save_stdout, 1); close (save_stdout); } if (result == -1) { int save_errno; save_errno = errno; close (master); errno = save_errno; return (-1); } else return (master); } smalltalk-3.2.5/libgst/sysdep/win32/mem.c0000644000175000017500000001105712123404352015105 00000000000000/******************************** -*- C -*- **************************** * * System specific implementation module. * * This module contains implementations of various operating system * specific routines. This module should encapsulate most (or all) * of these calls so that the rest of the code is portable. * * ***********************************************************************/ /*********************************************************************** * * Copyright 1988,89,90,91,92,94,95,99,2000,2001,2002,2003,2006,2007,2008,2009 * Free Software Foundation, Inc. * Written by Steve Byrne. * * This file is part of GNU Smalltalk. * * GNU Smalltalk is free software; you can redistribute it and/or modify it * under the terms of the GNU General Public License as published by the Free * Software Foundation; either version 2, or (at your option) any later * version. * * Linking GNU Smalltalk statically or dynamically with other modules is * making a combined work based on GNU Smalltalk. Thus, the terms and * conditions of the GNU General Public License cover the whole * combination. * * In addition, as a special exception, the Free Software Foundation * give you permission to combine GNU Smalltalk with free software * programs or libraries that are released under the GNU LGPL and with * independent programs running under the GNU Smalltalk virtual machine. * * You may copy and distribute such a system following the terms of the * GNU GPL for GNU Smalltalk and the licenses of the other code * concerned, provided that you include the source code of that other * code when and as the GNU GPL requires distribution of source code. * * Note that people who make modified versions of GNU Smalltalk are not * obligated to grant this special exception for their modified * versions; it is their choice whether to do so. The GNU General * Public License gives permission to release a modified version without * this exception; this exception also makes it possible to release a * modified version which carries forward this exception. * * GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or * FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for * more details. * * You should have received a copy of the GNU General Public License along with * GNU Smalltalk; see the file COPYING. If not, write to the Free Software * Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * ***********************************************************************/ #include "gstpriv.h" #ifdef WIN32 # define WIN32_LEAN_AND_MEAN /* avoid including junk */ # include #endif #ifndef MAP_FAILED # define MAP_FAILED ((char *) -1) #endif int _gst_mem_protect (PTR addr, size_t len, int prot) { DWORD oldprot; int my_prot; switch (prot & (PROT_READ | PROT_WRITE | PROT_EXEC)) { case PROT_NONE: my_prot = 0; break; case PROT_READ: my_prot = PAGE_READONLY; break; case PROT_WRITE: case PROT_READ | PROT_WRITE: my_prot = PAGE_READWRITE; break; case PROT_EXEC: my_prot = PAGE_EXECUTE; break; case PROT_EXEC | PROT_READ: my_prot = PAGE_EXECUTE_READ; break; case PROT_EXEC | PROT_WRITE: case PROT_EXEC | PROT_READ | PROT_WRITE: my_prot = PAGE_EXECUTE_READWRITE; break; default: return -1; } if (VirtualProtect (addr, len, my_prot, &oldprot)) return 0; else return -1; } PTR _gst_osmem_alloc (size_t size) { PTR addr; addr = VirtualAlloc(NULL, size, MEM_RESERVE, PAGE_NOACCESS); if (addr) { PTR result = VirtualAlloc (addr, size, MEM_COMMIT, PAGE_EXECUTE_READWRITE); if (result) return result; VirtualFree (addr, size, MEM_RELEASE); } errno = ENOMEM; return NULL; } void _gst_osmem_free (PTR ptr, size_t size) { VirtualFree(ptr, size, MEM_DECOMMIT); VirtualFree(ptr, size, MEM_RELEASE); } PTR _gst_osmem_reserve (PTR address, size_t size) { PTR base; base = VirtualAlloc(address, size, MEM_RESERVE, PAGE_NOACCESS); if (!base && address) base = VirtualAlloc(NULL, size, MEM_RESERVE, PAGE_NOACCESS); if (!base) errno = ENOMEM; return base; } void _gst_osmem_release (PTR base, size_t size) { VirtualFree(base, size, MEM_RELEASE); } PTR _gst_osmem_commit (PTR base, size_t size) { PTR addr; addr = VirtualAlloc (base, size, MEM_COMMIT, PAGE_EXECUTE_READWRITE); if (!addr) errno = ENOMEM; return addr; } void _gst_osmem_decommit (PTR base, size_t size) { VirtualFree(base, size, MEM_DECOMMIT); } smalltalk-3.2.5/libgst/sysdep/win32/events.c0000644000175000017500000003505312123404352015635 00000000000000/******************************** -*- C -*- **************************** * * Asynchronous events from the VM - Win32 version * * ***********************************************************************/ /*********************************************************************** * * Copyright 2009 Free Software Foundation, Inc. * Written by Paolo Bonzini. * * This file is part of GNU Smalltalk. * * GNU Smalltalk is free software; you can redistribute it and/or modify it * under the terms of the GNU General Public License as published by the Free * Software Foundation; either version 2, or (at your option) any later * version. * * Linking GNU Smalltalk statically or dynamically with other modules is * making a combined work based on GNU Smalltalk. Thus, the terms and * conditions of the GNU General Public License cover the whole * combination. * * In addition, as a special exception, the Free Software Foundation * give you permission to combine GNU Smalltalk with free software * programs or libraries that are released under the GNU LGPL and with * independent programs running under the GNU Smalltalk virtual machine. * * You may copy and distribute such a system following the terms of the * GNU GPL for GNU Smalltalk and the licenses of the other code * concerned, provided that you include the source code of that other * code when and as the GNU GPL requires distribution of source code. * * Note that people who make modified versions of GNU Smalltalk are not * obligated to grant this special exception for their modified * versions; it is their choice whether to do so. The GNU General * Public License gives permission to release a modified version without * this exception; this exception also makes it possible to release a * modified version which carries forward this exception. * * GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or * FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for * more details. * * You should have received a copy of the GNU General Public License along with * GNU Smalltalk; see the file COPYING. If not, write to the Free Software * Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * ***********************************************************************/ #include "gstpriv.h" /* Note: this code is mostly untested, especially the delicate socket handling parts. However it works decently enough for consoles and delays, and it gets rid of many hacks, so I am enabling it already. */ enum fhev_kind { EV_TTY, EV_SOCKET, EV_PASSIVE_SOCKET, EV_EVENT }; /* This structure defines a list of pairs `struct pollfd'->semaphore which map each pollfd that is passed by the OS to the semaphore to be signalled when the corresponding I/O situation becomes possible. */ struct handle_events { volatile LONG refcount; enum fhev_kind kind; HANDLE handle; OOP semaphoreOOP; int error; struct semaphore_list *list; struct handle_events *next; }; /* This structure defines a list of pairs `struct pollfd'->semaphore which map each pollfd that is passed by the OS to the semaphore to be signalled when the corresponding I/O situation becomes possible. */ typedef struct semaphore_list { int mask; OOP semaphoreOOP; struct semaphore_list *next; } semaphore_list; /* These two variables hold the list of `handle_events' structures. Replacing this with a binary tree is not really useful because the array of pollfd structures must be scanned and kept sequential every time that I/O happens, so it does not bother us very much to have to scan the list to find the semaphore that is to be signaled. */ static struct handle_events *head; static CRITICAL_SECTION handle_events_cs; /* Communication with the timer thread. */ static HANDLE hNewWaitEvent; static long sleepTime; /* Communication with sockets. */ #define hAlarmEvent handles[0] #define hSocketEvent handles[1] #define hConIn handles[2] static HANDLE handles[3]; /* */ static HANDLE hWakeUpEvent; static const LONG masks[3] = { FD_READ | FD_ACCEPT, FD_WRITE | FD_CONNECT, FD_OOB }; static inline struct handle_events * fhev_ref (struct handle_events *ev) { if (ev) InterlockedIncrement (&ev->refcount); return ev; } static inline struct handle_events * fhev_unref (struct handle_events *ev) { if (ev && InterlockedDecrement (&ev->refcount) != 0) return ev; xfree (ev); return NULL; } static struct handle_events * fhev_find (HANDLE handle) { struct handle_events *ev, **p_ev; EnterCriticalSection (&handle_events_cs); for (p_ev = &head; (ev = *p_ev); p_ev = &ev->next) if (ev->handle == handle) break; fhev_ref (ev); LeaveCriticalSection (&handle_events_cs); return ev; } static struct handle_events * fhev_delete (HANDLE handle) { struct handle_events *ev, **p_ev; EnterCriticalSection (&handle_events_cs); for (p_ev = &head; (ev = *p_ev); p_ev = &ev->next) if (ev->handle == handle) break; if (ev) { ev->semaphoreOOP = NULL; *p_ev = ev->next; } LeaveCriticalSection (&handle_events_cs); return ev; } static struct handle_events * fhev_new (HANDLE handle, enum fhev_kind kind) { struct handle_events *ev, **p_ev; EnterCriticalSection (&handle_events_cs); for (p_ev = &head; ; p_ev = &ev->next) { ev = *p_ev; if (!ev) { ev = xcalloc (1, sizeof (struct handle_events)); ev->refcount = 2; ev->kind = kind; ev->handle = handle; *p_ev = ev; break; } else if (ev->handle == handle) { fhev_ref (ev); break; } } LeaveCriticalSection (&handle_events_cs); return ev; } static int poll_console_input (HANDLE fh) { DWORD avail, nbuffer; INPUT_RECORD *irbuffer; BOOL bRet; int i; bRet = GetNumberOfConsoleInputEvents (fh, &nbuffer); if (!bRet || nbuffer == 0) return 0; irbuffer = (INPUT_RECORD *) alloca (nbuffer * sizeof (INPUT_RECORD)); bRet = PeekConsoleInput (fh, irbuffer, nbuffer, &avail); if (!bRet || avail == 0) return 0; for (i = 0; i < avail; i++) if (irbuffer[i].EventType == KEY_EVENT) return 1; return 0; } int fhev_poll (struct handle_events *ev) { static struct timeval tv0 = { 0, 0 }; SOCKET s; fd_set rfds, wfds, xfds; if (ev->error) return FD_CLOSE; switch (ev->kind) { case EV_TTY: if (poll_console_input (ev->handle)) return FD_READ | FD_WRITE; else return FD_WRITE; case EV_SOCKET: s = (SOCKET) ev->handle; FD_ZERO (&rfds); FD_ZERO (&wfds); FD_ZERO (&xfds); FD_SET (s, &rfds); FD_SET (s, &wfds); FD_SET (s, &xfds); select (0, &rfds, &wfds, &xfds, &tv0); return ((FD_ISSET (s, &rfds) ? FD_READ : 0) | (FD_ISSET (s, &wfds) ? FD_WRITE : 0) | (FD_ISSET (s, &xfds) ? FD_OOB : 0)); case EV_PASSIVE_SOCKET: s = (SOCKET) ev->handle; FD_ZERO (&rfds); FD_SET (s, &rfds); select (0, &rfds, NULL, NULL, &tv0); return FD_ISSET (s, &rfds) ? FD_ACCEPT : 0; default: return FD_READ | FD_WRITE; } } /* thread for precise alarm callbacks */ static unsigned WINAPI alarm_thread (LPVOID unused) { WaitForSingleObject (hNewWaitEvent, INFINITE); for (;;) { if (sleepTime > 0) { if (WaitForSingleObject (hNewWaitEvent, sleepTime) != WAIT_TIMEOUT) { /* The old wait was canceled by a new one */ continue; } } SetEvent (hAlarmEvent); WaitForSingleObject (hNewWaitEvent, INFINITE); } return 0; } static void signal_semaphores (struct handle_events *ev, LONG lEvents) { struct semaphore_list *node, **pprev; for (node = ev->list, pprev = &ev->list; node; node = *pprev) if (ev->error || (lEvents & node->mask) != 0) { _gst_async_signal_and_unregister (node->semaphoreOOP); *pprev = node->next; xfree (node); } else pprev = &node->next; } static unsigned WaitForMultipleObjectsDispatchMsg (int nhandles, HANDLE *handles, BOOLEAN bWaitAll, DWORD dwTimeout, DWORD qsMask) { DWORD ret; ret = MsgWaitForMultipleObjects (nhandles, handles, FALSE, INFINITE, QS_ALLINPUT); if (ret == WAIT_OBJECT_0 + nhandles) { /* new input of some other kind */ BOOL bRet; MSG msg; while ((bRet = PeekMessage (&msg, NULL, 0, 0, PM_REMOVE)) != 0) { TranslateMessage (&msg); DispatchMessage (&msg); } } return ret; } static unsigned WINAPI polling_thread (LPVOID unused) { struct handle_events *ev; for (;;) { DWORD ret; HANDLE *h; OOP semOOP; int nhandles; nhandles = hConIn ? 3 : 2; ret = WaitForMultipleObjects (nhandles, handles, FALSE, INFINITE); h = &handles[ret - WAIT_OBJECT_0]; EnterCriticalSection (&handle_events_cs); if (h == &hSocketEvent) { for (ev = head; ev; ev = ev->next) { SOCKET s = (SOCKET) ev->handle; WSANETWORKEVENTS nev; int i; if (ev->kind != EV_SOCKET && ev->kind != EV_PASSIVE_SOCKET) continue; if (ev->error) continue; WSAEnumNetworkEvents (s, NULL, &nev); if (nev.lNetworkEvents & FD_CLOSE) ev->error = WSAESHUTDOWN; else for (i = 0; i < FD_CLOSE_BIT; i++) if (nev.lNetworkEvents & (1 << i) && nev.iErrorCode[i] != 0) { ev->error = nev.iErrorCode[i]; break; } if (ev->error) signal_semaphores (ev, 0); else { int r = fhev_poll (ev); if (r) signal_semaphores (ev, r); } } } else if (h == &hAlarmEvent) { ev = fhev_find (*h); assert (ev->list == NULL); semOOP = ev ? ev->semaphoreOOP : NULL; if (semOOP) { _gst_async_signal (semOOP); ev->semaphoreOOP = NULL; } fhev_unref (ev); } else { if (poll_console_input (hConIn)) { assert (hConIn && *h == hConIn); ev = fhev_find (*h); assert (ev); signal_semaphores (ev, FD_READ | FD_WRITE); fhev_unref (ev); } } LeaveCriticalSection (&handle_events_cs); } return 0; } void _gst_init_async_events (void) { extern HANDLE WINAPI GetConsoleInputWaitHandle (void); DWORD dummy; /* Starts as non-signaled, so alarm_thread will wait */ InitializeCriticalSection (&handle_events_cs); hSocketEvent = CreateEvent (NULL, FALSE, FALSE, NULL); hNewWaitEvent = CreateEvent (NULL, FALSE, FALSE, NULL); hAlarmEvent = CreateEvent (NULL, FALSE, FALSE, NULL); hWakeUpEvent = CreateEvent (NULL, FALSE, FALSE, NULL); fhev_unref (fhev_new (hAlarmEvent, EV_EVENT)); hConIn = CreateFile ("CONIN$", GENERIC_READ, FILE_SHARE_READ, NULL, OPEN_EXISTING, 0, NULL); if (GetConsoleMode (hConIn, &dummy) == 0) hConIn = 0; else fhev_unref (fhev_new (hConIn, EV_TTY)); _beginthreadex (NULL, 1024, alarm_thread, NULL, 0, NULL); _beginthreadex (NULL, 1024, polling_thread, NULL, 0, NULL); } void _gst_async_timed_wait (OOP semaphoreOOP, int64_t nsTime) { struct handle_events *ev = fhev_find (hAlarmEvent); ev->semaphoreOOP = NULL; EnterCriticalSection (&handle_events_cs); sleepTime = (nsTime - _gst_get_ns_time()) / 1000000; SetEvent (hNewWaitEvent); ev->semaphoreOOP = semaphoreOOP; LeaveCriticalSection (&handle_events_cs); fhev_unref (ev); } mst_Boolean _gst_is_timeout_programmed (void) { struct handle_events *ev = fhev_find (hAlarmEvent); int result = (ev->semaphoreOOP != NULL); fhev_unref (ev); return result; } void _gst_register_socket (int fd, mst_Boolean passive) { HANDLE fh = _get_osfhandle (fd); struct handle_events *ev = fhev_new (fh, EV_SOCKET); if (passive) ev->kind = EV_PASSIVE_SOCKET; WSAEventSelect ((SOCKET) fh, hSocketEvent, masks[0] | masks[1] | masks[2] | FD_CLOSE); fhev_unref (ev); } int _gst_sync_file_polling (int fd, int cond) { HANDLE fh = _get_osfhandle (fd); struct handle_events *ev; LONG lEvents; if (cond < 0 || cond > 2) return -1; ev = fhev_find (fh); /* For now, make pipes blocking. */ if (!ev) return (GetFileType (fh) != 0 || GetLastError () != NO_ERROR) ? 1 : -1; EnterCriticalSection (&handle_events_cs); lEvents = fhev_poll (ev); LeaveCriticalSection (&handle_events_cs); if (lEvents & FD_CLOSE) { _gst_set_errno (ev->error); fhev_unref (ev); return -1; } else { fhev_unref (ev); return (lEvents & masks[cond]) != 0; } } void _gst_remove_fd_polling_handlers (int fd) { HANDLE fh = _get_osfhandle (fd); fhev_unref (fhev_delete (fh)); } int _gst_get_fd_error (int fd) { HANDLE fh = _get_osfhandle (fd); struct handle_events *ev = fhev_find (fh); int error; if (!ev) return 0; error = ev->error; fhev_unref (ev); return error; } void _gst_pause (void) { /* Doing an async call between the _gst_have_pending_async_calls and the wait will set the event again, so the wait will exit immediately. */ ResetEvent (hWakeUpEvent); if (!_gst_have_pending_async_calls ()) WaitForMultipleObjectsDispatchMsg (1, &hWakeUpEvent, FALSE, INFINITE, QS_ALLINPUT); } void _gst_wakeup (void) { SetEvent (hWakeUpEvent); } int _gst_async_file_polling (int fd, int cond, OOP semaphoreOOP) { HANDLE fh = _get_osfhandle (fd); struct handle_events *ev; struct semaphore_list *node; LONG lEvents; if (cond < 0 || cond > 2) return -1; ev = fhev_find (fh); /* For now, make pipes blocking. */ if (!ev) return (GetFileType (fh) != 0 || GetLastError () != NO_ERROR) ? 1 : -1; EnterCriticalSection (&handle_events_cs); lEvents = fhev_poll (ev); if (lEvents & FD_CLOSE) { _gst_set_errno (ev->error); fhev_unref (ev); LeaveCriticalSection (&handle_events_cs); return -1; } else if ((lEvents & masks[cond]) != 0) { fhev_unref (ev); LeaveCriticalSection (&handle_events_cs); return 1; } node = (struct semaphore_list *) xcalloc (1, sizeof (struct semaphore_list)); node->semaphoreOOP = semaphoreOOP; node->mask = masks[cond]; node->next = ev->list; ev->list = node; _gst_register_oop (semaphoreOOP); _gst_sync_wait (semaphoreOOP); fhev_unref (ev); LeaveCriticalSection (&handle_events_cs); return 0; } void _gst_wait_for_input (int fd) { HANDLE h = _get_osfhandle (fd); DWORD dummy; if (GetConsoleMode (h, &dummy) != 0) { while (!poll_console_input (h)) WaitForMultipleObjectsDispatchMsg (1, &h, FALSE, INFINITE, QS_ALLINPUT); } } smalltalk-3.2.5/libgst/sysdep/win32/time.c0000644000175000017500000000753512123404352015273 00000000000000/******************************** -*- C -*- **************************** * * System specific implementation module. * * This module contains implementations of various operating system * specific routines. This module should encapsulate most (or all) * of these calls so that the rest of the code is portable. * * ***********************************************************************/ /*********************************************************************** * * Copyright 1988,89,90,91,92,94,95,99,2000,2001,2002,2003,2006,2007,2008,2009 * Free Software Foundation, Inc. * Written by Steve Byrne. * * This file is part of GNU Smalltalk. * * GNU Smalltalk is free software; you can redistribute it and/or modify it * under the terms of the GNU General Public License as published by the Free * Software Foundation; either version 2, or (at your option) any later * version. * * Linking GNU Smalltalk statically or dynamically with other modules is * making a combined work based on GNU Smalltalk. Thus, the terms and * conditions of the GNU General Public License cover the whole * combination. * * In addition, as a special exception, the Free Software Foundation * give you permission to combine GNU Smalltalk with free software * programs or libraries that are released under the GNU LGPL and with * independent programs running under the GNU Smalltalk virtual machine. * * You may copy and distribute such a system following the terms of the * GNU GPL for GNU Smalltalk and the licenses of the other code * concerned, provided that you include the source code of that other * code when and as the GNU GPL requires distribution of source code. * * Note that people who make modified versions of GNU Smalltalk are not * obligated to grant this special exception for their modified * versions; it is their choice whether to do so. The GNU General * Public License gives permission to release a modified version without * this exception; this exception also makes it possible to release a * modified version which carries forward this exception. * * GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or * FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for * more details. * * You should have received a copy of the GNU General Public License along with * GNU Smalltalk; see the file COPYING. If not, write to the Free Software * Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * ***********************************************************************/ #include "gstpriv.h" #ifdef HAVE_SYS_TIMES_H # include #endif #ifdef HAVE_SYS_TIMEB_H #include #endif #ifdef WIN32 # define WIN32_LEAN_AND_MEAN /* avoid including junk */ # include #endif static inline uint64_t muldiv64(uint64_t a, uint32_t b, uint32_t c) { uint64_t tl = (a & 0xffffffff) * b; uint64_t th = (a >> 32) * b + (tl >> 32); uint64_t rem = ((th % c) << 32) + (tl & 0xffffffff); return ((uint64_t) (th / c) << 32) | (rem / c); } uint64_t _gst_get_ns_time (void) { static long frequency = 0; LARGE_INTEGER counter; if (!frequency) { QueryPerformanceFrequency (&counter); frequency = counter.LowPart; } QueryPerformanceCounter (&counter); return muldiv64(counter.QuadPart, 1000000000, frequency); } char * _gst_current_time_zone_name (void) { char *zone; long bias = _gst_current_time_zone_bias () / 60; TIME_ZONE_INFORMATION tzi; LPCWSTR name; static char buffer[32]; GetTimeZoneInformation (&tzi); zone = buffer; name = (bias == (tzi.Bias + tzi.StandardBias)) ? tzi.StandardName : tzi.DaylightName; WideCharToMultiByte (CP_ACP, 0, name, lstrlenW (name), zone, 32, NULL, NULL); return xstrdup (zone); } void _gst_usleep (int us) { Sleep (us / 1000); } smalltalk-3.2.5/libgst/sysdep/win32/timer.c0000644000175000017500000000550212123404352015445 00000000000000/******************************** -*- C -*- **************************** * * System specific implementation module. * * This module contains implementations of various operating system * specific routines. This module should encapsulate most (or all) * of these calls so that the rest of the code is portable. * * ***********************************************************************/ /*********************************************************************** * * Copyright 1988,89,90,91,92,94,95,99,2000,2001,2002,2003,2006,2007,2008,2009 * Free Software Foundation, Inc. * Written by Steve Byrne. * * This file is part of GNU Smalltalk. * * GNU Smalltalk is free software; you can redistribute it and/or modify it * under the terms of the GNU General Public License as published by the Free * Software Foundation; either version 2, or (at your option) any later * version. * * Linking GNU Smalltalk statically or dynamically with other modules is * making a combined work based on GNU Smalltalk. Thus, the terms and * conditions of the GNU General Public License cover the whole * combination. * * In addition, as a special exception, the Free Software Foundation * give you permission to combine GNU Smalltalk with free software * programs or libraries that are released under the GNU LGPL and with * independent programs running under the GNU Smalltalk virtual machine. * * You may copy and distribute such a system following the terms of the * GNU GPL for GNU Smalltalk and the licenses of the other code * concerned, provided that you include the source code of that other * code when and as the GNU GPL requires distribution of source code. * * Note that people who make modified versions of GNU Smalltalk are not * obligated to grant this special exception for their modified * versions; it is their choice whether to do so. The GNU General * Public License gives permission to release a modified version without * this exception; this exception also makes it possible to release a * modified version which carries forward this exception. * * GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or * FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for * more details. * * You should have received a copy of the GNU General Public License along with * GNU Smalltalk; see the file COPYING. If not, write to the Free Software * Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * ***********************************************************************/ #include "gstpriv.h" #ifdef WIN32 # define WIN32_LEAN_AND_MEAN /* avoid including junk */ # include #endif void _gst_sigvtalrm_every (int deltaMilli, SigHandler func) { } void _gst_init_sysdep_timer (void) { } smalltalk-3.2.5/libgst/sysdep/win32/findexec.c0000644000175000017500000000617112123404352016115 00000000000000/******************************** -*- C -*- **************************** * * System specific implementation module. * * This module contains implementations of various operating system * specific routines. This module should encapsulate most (or all) * of these calls so that the rest of the code is portable. * * ***********************************************************************/ /*********************************************************************** * * Copyright 1988,89,90,91,92,94,95,99,2000,2001,2002,2003,2006,2007,2008,2009 * Free Software Foundation, Inc. * Written by Steve Byrne. * * This file is part of GNU Smalltalk. * * GNU Smalltalk is free software; you can redistribute it and/or modify it * under the terms of the GNU General Public License as published by the Free * Software Foundation; either version 2, or (at your option) any later * version. * * Linking GNU Smalltalk statically or dynamically with other modules is * making a combined work based on GNU Smalltalk. Thus, the terms and * conditions of the GNU General Public License cover the whole * combination. * * In addition, as a special exception, the Free Software Foundation * give you permission to combine GNU Smalltalk with free software * programs or libraries that are released under the GNU LGPL and with * independent programs running under the GNU Smalltalk virtual machine. * * You may copy and distribute such a system following the terms of the * GNU GPL for GNU Smalltalk and the licenses of the other code * concerned, provided that you include the source code of that other * code when and as the GNU GPL requires distribution of source code. * * Note that people who make modified versions of GNU Smalltalk are not * obligated to grant this special exception for their modified * versions; it is their choice whether to do so. The GNU General * Public License gives permission to release a modified version without * this exception; this exception also makes it possible to release a * modified version which carries forward this exception. * * GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or * FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for * more details. * * You should have received a copy of the GNU General Public License along with * GNU Smalltalk; see the file COPYING. If not, write to the Free Software * Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * ***********************************************************************/ #include "gstpriv.h" #ifdef WIN32 # define WIN32_LEAN_AND_MEAN /* avoid including junk */ # include #endif /* The path to the executable, derived from argv[0]. */ const char *_gst_executable_path = NULL; /* Store the full pathname of the current executable. */ void _gst_set_executable_path (const char *argv0) { char location[MAX_PATH]; int length = GetModuleFileName (NULL, location, sizeof (location)); if (length <= 0) _gst_executable_path = NULL; else _gst_executable_path = xstrdup (location); } smalltalk-3.2.5/libgst/sysdep/cygwin/0000755000175000017500000000000012130456004014574 500000000000000smalltalk-3.2.5/libgst/sysdep/cygwin/signals.c0000644000175000017500000000003612123404352016320 00000000000000#include "../posix/signals.c" smalltalk-3.2.5/libgst/sysdep/cygwin/files.c0000644000175000017500000000003412123404352015760 00000000000000#include "../posix/files.c" smalltalk-3.2.5/libgst/sysdep/cygwin/mem.c0000644000175000017500000000003212123404352015432 00000000000000#include "../win32/mem.c" smalltalk-3.2.5/libgst/sysdep/cygwin/events.c0000644000175000017500000000003512123404352016163 00000000000000#include "../posix/events.c" smalltalk-3.2.5/libgst/sysdep/cygwin/time.c0000644000175000017500000000003312123404352015613 00000000000000#include "../win32/time.c" smalltalk-3.2.5/libgst/sysdep/cygwin/timer.c0000644000175000017500000001055712123404352016011 00000000000000/******************************** -*- C -*- **************************** * * System specific implementation module. * * This module contains implementations of various operating system * specific routines. This module should encapsulate most (or all) * of these calls so that the rest of the code is portable. * * ***********************************************************************/ /*********************************************************************** * * Copyright 1988,89,90,91,92,94,95,99,2000,2001,2002,2003,2006,2007,2008,2009 * Free Software Foundation, Inc. * Written by Steve Byrne. * * This file is part of GNU Smalltalk. * * GNU Smalltalk is free software; you can redistribute it and/or modify it * under the terms of the GNU General Public License as published by the Free * Software Foundation; either version 2, or (at your option) any later * version. * * Linking GNU Smalltalk statically or dynamically with other modules is * making a combined work based on GNU Smalltalk. Thus, the terms and * conditions of the GNU General Public License cover the whole * combination. * * In addition, as a special exception, the Free Software Foundation * give you permission to combine GNU Smalltalk with free software * programs or libraries that are released under the GNU LGPL and with * independent programs running under the GNU Smalltalk virtual machine. * * You may copy and distribute such a system following the terms of the * GNU GPL for GNU Smalltalk and the licenses of the other code * concerned, provided that you include the source code of that other * code when and as the GNU GPL requires distribution of source code. * * Note that people who make modified versions of GNU Smalltalk are not * obligated to grant this special exception for their modified * versions; it is their choice whether to do so. The GNU General * Public License gives permission to release a modified version without * this exception; this exception also makes it possible to release a * modified version which carries forward this exception. * * GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or * FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for * more details. * * You should have received a copy of the GNU General Public License along with * GNU Smalltalk; see the file COPYING. If not, write to the Free Software * Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * ***********************************************************************/ #include "gstpriv.h" #ifdef WIN32 # define WIN32_LEAN_AND_MEAN /* avoid including junk */ # include #endif struct { HANDLE hNewWaitEvent; long sleepTime; } alarms; /* thread for precise alarm callbacks */ void CALLBACK alarm_thread (unused) LPVOID unused; { WaitForSingleObject (alarms.hNewWaitEvent, INFINITE); for (;;) { int sleepTime; sleepTime = alarms.sleepTime; if (sleepTime > 0) { if (WaitForSingleObject (alarms.hNewWaitEvent, sleepTime) != WAIT_TIMEOUT) { /* The old wait was canceled by a new one */ continue; } } raise (SIGALRM); WaitForSingleObject (alarms.hNewWaitEvent, INFINITE); } } void _gst_init_sysdep_timer (void) { HANDLE hthread; DWORD tid; /* Starts as non-signaled, so alarm_thread will wait */ alarms.hNewWaitEvent = CreateEvent (NULL, FALSE, FALSE, NULL); /* Start alarm_thread with a 1024 bytes stack */ hthread = CreateThread (NULL, 1024, (LPTHREAD_START_ROUTINE) alarm_thread, NULL, 0, &tid); /* This does not terminate the thread - it only releases our handle */ CloseHandle (hthread); } void _gst_sigvtalrm_every (int deltaMilli, SigHandler func) { #if defined ITIMER_VIRTUAL struct itimerval value; _gst_set_signal_handler (SIGVTALRM, func); value.it_value.tv_sec = value.it_value.tv_usec = 0; value.it_interval.tv_sec = deltaMilli / 1000; value.it_interval.tv_usec = (deltaMilli % 1000) * 1000; setitimer (ITIMER_VIRTUAL, &value, (struct itimerval *) 0); #endif } void _gst_sigalrm_at (int64_t nsTime) { int64_t deltaMilli = (nsTime - _gst_get_ns_time()) / 1000000; if (deltaMilli <= 0) { raise (kind); return; } alarms.sleepTime = deltaMilli; SetEvent (alarms.hNewWaitEvent); } smalltalk-3.2.5/libgst/sysdep/cygwin/findexec.c0000644000175000017500000000746012123404352016455 00000000000000/******************************** -*- C -*- **************************** * * System specific implementation module. * * This module contains implementations of various operating system * specific routines. This module should encapsulate most (or all) * of these calls so that the rest of the code is portable. * * ***********************************************************************/ /*********************************************************************** * * Copyright 1988,89,90,91,92,94,95,99,2000,2001,2002,2003,2006,2007,2008,2009 * Free Software Foundation, Inc. * Written by Steve Byrne. * * This file is part of GNU Smalltalk. * * GNU Smalltalk is free software; you can redistribute it and/or modify it * under the terms of the GNU General Public License as published by the Free * Software Foundation; either version 2, or (at your option) any later * version. * * Linking GNU Smalltalk statically or dynamically with other modules is * making a combined work based on GNU Smalltalk. Thus, the terms and * conditions of the GNU General Public License cover the whole * combination. * * In addition, as a special exception, the Free Software Foundation * give you permission to combine GNU Smalltalk with free software * programs or libraries that are released under the GNU LGPL and with * independent programs running under the GNU Smalltalk virtual machine. * * You may copy and distribute such a system following the terms of the * GNU GPL for GNU Smalltalk and the licenses of the other code * concerned, provided that you include the source code of that other * code when and as the GNU GPL requires distribution of source code. * * Note that people who make modified versions of GNU Smalltalk are not * obligated to grant this special exception for their modified * versions; it is their choice whether to do so. The GNU General * Public License gives permission to release a modified version without * this exception; this exception also makes it possible to release a * modified version which carries forward this exception. * * GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or * FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for * more details. * * You should have received a copy of the GNU General Public License along with * GNU Smalltalk; see the file COPYING. If not, write to the Free Software * Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * ***********************************************************************/ #include "gstpriv.h" #ifdef WIN32 # define WIN32_LEAN_AND_MEAN /* avoid including junk */ # include #endif /* The path to the executable, derived from argv[0]. */ const char *_gst_executable_path = NULL; /* Store the full pathname of the current executable. */ void _gst_set_executable_path (const char *argv0) { char location[MAX_PATH]; static char location_as_posix_path[2 * MAX_PATH]; int length = GetModuleFileName (NULL, location, sizeof (location)); if (length <= 0) return NULL; /* On Cygwin, we need to convert paths coming from Win32 system calls to the Unix-like slashified notation. There's no error return defined for cygwin_conv_to_posix_path. See cygwin-api/func-cygwin-conv-to-posix-path.html. Does it overflow the buffer of expected size MAX_PATH or does it truncate the path? I don't know. Let's catch both. */ cygwin_conv_to_posix_path (location, location_as_posix_path); location_as_posix_path[MAX_PATH - 1] = '\0'; if (strlen (location_as_posix_path) >= MAX_PATH - 1) /* A sign of buffer overflow or path truncation. */ _gst_executable_path = NULL; else _gst_executable_path = _gst_get_full_file_name (location_as_posix_path); } smalltalk-3.2.5/libgst/sysdep/posix/0000755000175000017500000000000012130456004014436 500000000000000smalltalk-3.2.5/libgst/sysdep/posix/signals.c0000644000175000017500000001032012123404352016157 00000000000000/******************************** -*- C -*- **************************** * * System specific implementation module. * * This module contains implementations of various operating system * specific routines. This module should encapsulate most (or all) * of these calls so that the rest of the code is portable. * * ***********************************************************************/ /*********************************************************************** * * Copyright 1988,89,90,91,92,94,95,99,2000,2001,2002,2003,2006,2007,2008,2009 * Free Software Foundation, Inc. * Written by Steve Byrne. * * This file is part of GNU Smalltalk. * * GNU Smalltalk is free software; you can redistribute it and/or modify it * under the terms of the GNU General Public License as published by the Free * Software Foundation; either version 2, or (at your option) any later * version. * * Linking GNU Smalltalk statically or dynamically with other modules is * making a combined work based on GNU Smalltalk. Thus, the terms and * conditions of the GNU General Public License cover the whole * combination. * * In addition, as a special exception, the Free Software Foundation * give you permission to combine GNU Smalltalk with free software * programs or libraries that are released under the GNU LGPL and with * independent programs running under the GNU Smalltalk virtual machine. * * You may copy and distribute such a system following the terms of the * GNU GPL for GNU Smalltalk and the licenses of the other code * concerned, provided that you include the source code of that other * code when and as the GNU GPL requires distribution of source code. * * Note that people who make modified versions of GNU Smalltalk are not * obligated to grant this special exception for their modified * versions; it is their choice whether to do so. The GNU General * Public License gives permission to release a modified version without * this exception; this exception also makes it possible to release a * modified version which carries forward this exception. * * GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or * FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for * more details. * * You should have received a copy of the GNU General Public License along with * GNU Smalltalk; see the file COPYING. If not, write to the Free Software * Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * ***********************************************************************/ #include "gstpriv.h" #ifndef USE_POSIX_THREADS #define pthread_sigmask sigprocmask #endif #if defined FASYNC && !defined O_ASYNC #define O_ASYNC FASYNC #endif /* Yield A - B, measured in seconds. This function is copied from the GNU C Library. */ static int tm_diff (struct tm *a, struct tm *b); static sigset_t oldSet; int _gst_signal_count; void _gst_disable_interrupts (mst_Boolean from_signal_handler) { sigset_t newSet; __sync_synchronize (); if (_gst_signal_count++ == 0) { __sync_synchronize (); if (from_signal_handler) return; sigfillset (&newSet); sigdelset (&newSet, SIGSEGV); sigdelset (&newSet, SIGBUS); sigdelset (&newSet, SIGILL); sigdelset (&newSet, SIGQUIT); sigdelset (&newSet, SIGABRT); pthread_sigmask (SIG_BLOCK, &newSet, &oldSet); } } void _gst_enable_interrupts (mst_Boolean from_signal_handler) { __sync_synchronize (); if (--_gst_signal_count == 0) { __sync_synchronize (); if (from_signal_handler) return; pthread_sigmask (SIG_SETMASK, &oldSet, NULL); } } SigHandler _gst_set_signal_handler (int signum, SigHandler handlerFunc) { /* If we are running on a POSIX-compliant system, then do things the POSIX way. */ struct sigaction act, o_act; act.sa_handler = handlerFunc; act.sa_flags = 0; sigfillset (&act.sa_mask); sigdelset (&act.sa_mask, SIGSEGV); sigdelset (&act.sa_mask, SIGBUS); sigdelset (&act.sa_mask, SIGILL); sigdelset (&act.sa_mask, SIGQUIT); sigdelset (&act.sa_mask, SIGABRT); sigaction (signum, &act, &o_act); return o_act.sa_handler; } smalltalk-3.2.5/libgst/sysdep/posix/files.c0000644000175000017500000002116512123404352015632 00000000000000/******************************** -*- C -*- **************************** * * System specific implementation module. * * This module contains implementations of various operating system * specific routines. This module should encapsulate most (or all) * of these calls so that the rest of the code is portable. * * ***********************************************************************/ /*********************************************************************** * * Copyright 1988,89,90,91,92,94,95,99,2000,2001,2002,2003,2006,2007,2008,2009 * Free Software Foundation, Inc. * Written by Steve Byrne. * * This file is part of GNU Smalltalk. * * GNU Smalltalk is free software; you can redistribute it and/or modify it * under the terms of the GNU General Public License as published by the Free * Software Foundation; either version 2, or (at your option) any later * version. * * Linking GNU Smalltalk statically or dynamically with other modules is * making a combined work based on GNU Smalltalk. Thus, the terms and * conditions of the GNU General Public License cover the whole * combination. * * In addition, as a special exception, the Free Software Foundation * give you permission to combine GNU Smalltalk with free software * programs or libraries that are released under the GNU LGPL and with * independent programs running under the GNU Smalltalk virtual machine. * * You may copy and distribute such a system following the terms of the * GNU GPL for GNU Smalltalk and the licenses of the other code * concerned, provided that you include the source code of that other * code when and as the GNU GPL requires distribution of source code. * * Note that people who make modified versions of GNU Smalltalk are not * obligated to grant this special exception for their modified * versions; it is their choice whether to do so. The GNU General * Public License gives permission to release a modified version without * this exception; this exception also makes it possible to release a * modified version which carries forward this exception. * * GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or * FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for * more details. * * You should have received a copy of the GNU General Public License along with * GNU Smalltalk; see the file COPYING. If not, write to the Free Software * Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * ***********************************************************************/ #include "gstpriv.h" #ifdef HAVE_SYS_WAIT_H #include #endif #ifndef O_BINARY #define O_BINARY 0 #endif #ifdef HAVE_SPAWNL #include #ifndef P_WAIT #define P_WAIT 0 #define P_NOWAIT 1 #define P_OVERLAY 2 #define P_NOWAITO 3 #define P_DETACH 4 #endif /* !P_WAIT */ #endif /* HAVE_SPAWNL */ #if defined FASYNC && !defined O_ASYNC #define O_ASYNC FASYNC #endif #ifndef PATH_MAX #define PATH_MAX 1024 /* max length of a file and path */ #endif #ifndef MAXSYMLINKS #define MAXSYMLINKS 5 #endif char * _gst_get_full_file_name (const char *name) { char *rpath, *dest; const char *start, *end, *rpath_limit; long int path_max; #ifdef HAVE_READLINK int num_links = 0; char *extra_buf = NULL; #endif #ifdef PATH_MAX path_max = PATH_MAX; #else path_max = pathconf (name, _PC_PATH_MAX); if (path_max <= 0) path_max = 1024; #endif rpath = malloc (path_max); if (rpath == NULL) return NULL; rpath_limit = rpath + path_max; if (name[0] != '/') { if (!getcwd (rpath, path_max)) goto error; dest = strchr (rpath, '\0'); } else { rpath[0] = '/'; dest = rpath + 1; } for (start = end = name; *start; start = end) { struct stat st; /* Skip sequence of multiple path-separators. */ while (*start == '/') ++start; /* Find end of path component. */ for (end = start; *end && *end != '/'; ++end) /* Nothing. */; if (end - start == 0) break; else if (end - start == 1 && start[0] == '.') /* nothing */; else if (end - start == 2 && start[0] == '.' && start[1] == '.') { /* Back up to previous component, ignore if at root already. */ if (dest > rpath + 1) while ((--dest)[-1] != '/'); } else { size_t new_size; if (dest[-1] != '/') *dest++ = '/'; if (dest + (end - start) >= rpath_limit) { ptrdiff_t dest_offset = dest - rpath; char *new_rpath; new_size = rpath_limit - rpath; if (end - start + 1 > path_max) new_size += end - start + 1; else new_size += path_max; new_rpath = (char *) realloc (rpath, new_size); if (new_rpath == NULL) goto error; rpath = new_rpath; rpath_limit = rpath + new_size; dest = rpath + dest_offset; } memcpy (dest, start, end - start); dest += end - start; *dest = '\0'; if (lstat (rpath, &st) < 0) goto error; #if HAVE_READLINK if (S_ISLNK (st.st_mode)) { char *buf; size_t len; int n; if (++num_links > MAXSYMLINKS) { errno = ELOOP; goto error; } buf = alloca (path_max); n = readlink (rpath, buf, path_max - 1); if (n < 0) { int saved_errno = errno; errno = saved_errno; goto error; } buf[n] = '\0'; if (!extra_buf) extra_buf = alloca (path_max); len = strlen (end); if ((long int) (n + len) >= path_max) { errno = ENAMETOOLONG; goto error; } /* Careful here, end may be a pointer into extra_buf... */ memmove (&extra_buf[n], end, len + 1); name = end = memcpy (extra_buf, buf, n); if (buf[0] == '/') dest = rpath + 1; /* It's an absolute symlink */ else /* Back up to previous component, ignore if at root already: */ if (dest > rpath + 1) while ((--dest)[-1] != '/'); } #endif } } if (dest > rpath + 1 && dest[-1] == '/') --dest; *dest = '\0'; return rpath; error: { int saved_errno = errno; free (rpath); errno = saved_errno; } return NULL; } static void sigchld_handler (int signum) { #ifdef HAVE_WAITPID int pid, status, serrno; serrno = errno; do pid = waitpid (-1, &status, WNOHANG); while (pid > 0); errno = serrno; #endif /* Pass it to the SIGIO handler, it might reveal a POLLHUP event. */ raise (SIGIO); _gst_set_signal_handler (SIGCHLD, sigchld_handler); } /* Use sockets or pipes. */ int _gst_open_pipe (const char *command, const char *mode) { int fd[2]; int our_fd, child_fd; int access; int result; _gst_set_signal_handler (SIGCHLD, sigchld_handler); access = strchr (mode, '+') ? O_RDWR : (mode[0] == 'r' ? O_RDONLY : O_WRONLY); if (access == O_RDWR) { result = socketpair (AF_UNIX, SOCK_STREAM, 0, fd); our_fd = fd[1]; child_fd = fd[0]; } else { result = pipe (fd); our_fd = access == O_RDONLY ? fd[0] : fd[1]; child_fd = access == O_RDONLY ? fd[1] : fd[0]; } if (result == -1) return -1; _gst_set_signal_handler (SIGPIPE, SIG_DFL); _gst_set_signal_handler (SIGFPE, SIG_DFL); #ifdef HAVE_SPAWNL { /* Prepare file descriptors, saving the old ones so that we can keep them. */ int save_stdin = -1, save_stdout = -1, save_stderr = -1; if (access != O_WRONLY) { save_stdout = dup (1); save_stderr = dup (2); dup2 (child_fd, 1); dup2 (child_fd, 2); } if (access != O_RDONLY) { save_stdin = dup (0); dup2 (child_fd, 0); } result = spawnl (P_NOWAIT, "/bin/sh", "/bin/sh", "-c", command, NULL); if (save_stdin != -1) { dup2 (save_stdin, 0); close (save_stdin); } if (save_stdout != -1) { dup2 (save_stdout, 1); close (save_stdout); } if (save_stderr != -1) { dup2 (save_stderr, 2); close (save_stderr); } } #else /* !HAVE_SPAWNL */ /* We suppose it is a system that has fork. */ result = fork (); if (result == 0) { /* Child process */ close (our_fd); if (access != O_WRONLY) dup2 (child_fd, 1); if (access != O_RDONLY) dup2 (child_fd, 0); _exit (system (command) >= 0); /*NOTREACHED*/ } #endif /* !HAVE_SPAWNL */ close (child_fd); _gst_set_signal_handler (SIGPIPE, SIG_IGN); _gst_set_signal_handler (SIGFPE, SIG_IGN); if (result == -1) { int save_errno; save_errno = errno; close (our_fd); errno = save_errno; return (-1); } else return (our_fd); } smalltalk-3.2.5/libgst/sysdep/posix/mem.c0000644000175000017500000002410612123404352015304 00000000000000/******************************** -*- C -*- **************************** * * System specific implementation module. * * This module contains implementations of various operating system * specific routines. This module should encapsulate most (or all) * of these calls so that the rest of the code is portable. * * ***********************************************************************/ /*********************************************************************** * * Copyright 1988,89,90,91,92,94,95,99,2000,2001,2002,2003,2006,2007,2008,2009 * Free Software Foundation, Inc. * Written by Steve Byrne. * * This file is part of GNU Smalltalk. * * GNU Smalltalk is free software; you can redistribute it and/or modify it * under the terms of the GNU General Public License as published by the Free * Software Foundation; either version 2, or (at your option) any later * version. * * Linking GNU Smalltalk statically or dynamically with other modules is * making a combined work based on GNU Smalltalk. Thus, the terms and * conditions of the GNU General Public License cover the whole * combination. * * In addition, as a special exception, the Free Software Foundation * give you permission to combine GNU Smalltalk with free software * programs or libraries that are released under the GNU LGPL and with * independent programs running under the GNU Smalltalk virtual machine. * * You may copy and distribute such a system following the terms of the * GNU GPL for GNU Smalltalk and the licenses of the other code * concerned, provided that you include the source code of that other * code when and as the GNU GPL requires distribution of source code. * * Note that people who make modified versions of GNU Smalltalk are not * obligated to grant this special exception for their modified * versions; it is their choice whether to do so. The GNU General * Public License gives permission to release a modified version without * this exception; this exception also makes it possible to release a * modified version which carries forward this exception. * * GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or * FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for * more details. * * You should have received a copy of the GNU General Public License along with * GNU Smalltalk; see the file COPYING. If not, write to the Free Software * Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * ***********************************************************************/ #include "gstpriv.h" #if defined MAP_ANONYMOUS && !defined MAP_ANON # define MAP_ANON MAP_ANONYMOUS #endif #ifndef MAP_FAILED # define MAP_FAILED ((char *) -1) #endif int _gst_mem_protect (PTR addr, size_t len, int prot) { #ifdef HAVE_MPROTECT return mprotect (addr, len, prot); #else return -1; #endif } /* We have three possible implementations: Win32, mmap-ing /dev/zero or using anonymous mmaps, and anonymous mmaps with MAP_NORESERVE. There is support for providing fallback implementations, but it is not used currently. */ typedef struct heap_implementation { mst_Boolean (*check) (); PTR (*reserve) (PTR, size_t); void (*release) (PTR, size_t); PTR (*commit) (PTR, size_t); void (*decommit) (PTR, size_t); } heap_implementation; #if defined MAP_AUTORESRV && !defined MAP_NORESERVE # define MAP_NORESERVE MAP_AUTORESRV #endif #ifdef MAP_NORESERVE static PTR noreserve_reserve (PTR, size_t); static void noreserve_decommit (PTR, size_t); #endif static mst_Boolean anon_mmap_check (void); static PTR anon_mmap_reserve (PTR, size_t); static void anon_mmap_release (PTR, size_t); static PTR anon_mmap_commit (PTR, size_t); struct heap_implementation heap_impl_tab[] = { #ifdef MAP_NORESERVE { NULL, noreserve_reserve, _gst_osmem_free, anon_mmap_commit, noreserve_decommit }, #endif { anon_mmap_check, anon_mmap_reserve, anon_mmap_release, anon_mmap_commit, _gst_osmem_free }, { NULL, NULL, NULL, NULL, NULL } }; static heap_implementation *impl; PTR _gst_osmem_reserve (PTR address, size_t size) { if (!impl) { /* Find an implementation of heaps that is ok for this machine. The check is done at run-time because it is cheap. */ for (impl = heap_impl_tab; impl->reserve; impl++) if (!impl->check || impl->check ()) return impl->reserve (address, size); /* Not found, check again the next time just in case and return ENOMEM. */ impl = NULL; errno = ENOMEM; return (NULL); } else return impl->reserve (address, size); } void _gst_osmem_release (PTR base, size_t size) { impl->release (base, size); } PTR _gst_osmem_commit (PTR base, size_t size) { return impl->commit (base, size); } void _gst_osmem_decommit (PTR base, size_t size) { impl->decommit (base, size); } PTR _gst_osmem_alloc (size_t size) { PTR addr; addr = mmap (NULL, size, PROT_READ | PROT_WRITE | PROT_EXEC, MAP_ANON | MAP_PRIVATE, -1, 0); return addr == MAP_FAILED ? NULL : addr; } void _gst_osmem_free (PTR ptr, size_t size) { munmap (ptr, size); } #ifdef MAP_NORESERVE /* Implementation of the four basic primitives when MAP_NORESERVE is available. */ PTR noreserve_reserve (PTR address, size_t size) { PTR result = mmap (address, size, PROT_NONE, MAP_ANON | MAP_PRIVATE | MAP_NORESERVE, -1, 0); return result == MAP_FAILED ? NULL : result; } void noreserve_decommit (PTR base, size_t size) { mmap (base, size, PROT_NONE, MAP_ANON | MAP_PRIVATE | MAP_NORESERVE | MAP_FIXED, -1, 0); } #endif /* Implementation of the four basic primitives when MAP_NORESERVE is not available. Not foolproof, but we try to keep the balance between simplicity and usefulness. */ static char *baseaddr; PTR anon_mmap_reserve (PTR address, size_t size) { PTR base; /* We must check for overflows in baseaddr! Note that we ignore address. */ if (((uintptr_t) baseaddr) + size < (uintptr_t) baseaddr) { errno = ENOMEM; return NULL; } else { base = baseaddr; baseaddr += size; return base; } } void anon_mmap_release (PTR base, size_t size) { if ((char *) baseaddr == (char *) base + size) baseaddr = base; } PTR anon_mmap_commit (PTR base, size_t size) { PTR result = mmap (base, size, PROT_READ | PROT_WRITE | PROT_EXEC, MAP_ANON | MAP_PRIVATE | MAP_FIXED, -1, 0); return UNCOMMON (result == MAP_FAILED) ? NULL : result; } /* This is hairy and a hack. We have to find a place for our heaps... */ /* This signal handler is used if it is the only means to decide if a page is mapped into memory. We intercept SIGSEGV and decide that the heap can be allocated at a given location only if we receive a signal. We also try access(2) and EFAULT, but it is not ensured that it works because the whole EFAULT business is quite unclear; however it is worth doing because debugging is way more painful if we have SIGSEGV's as part of the normal initialization sequence. */ static RETSIGTYPE not_mapped (int sig); static jmp_buf already_mapped; RETSIGTYPE not_mapped (sig) int sig; { _gst_set_signal_handler (sig, not_mapped); longjmp (already_mapped, 1); } mst_Boolean anon_mmap_check (void) { volatile char *mmapGuess, *higher, *lower; /* reference addresses */ volatile char *first = NULL, *second; /* probed addresses */ volatile const int *step; static const int steps[] = { true, 256, 256, 0, /* try 256 Mb after the higher address */ true, 128, 256, 0, /* try 128 Mb after the higher address */ true, 64, 256, 0, /* try 64 Mb after the higher address */ false, 256, 256, 512, /* try 256 Mb after the lower address */ false, 128, 256, 384, /* try 128 Mb after the lower address */ false, 64, 256, 320, /* try 64 Mb after the lower address */ true, 32, 256, 0, /* try 32 Mb after the higher address */ true, 32, 128, 0, /* again, for a smaller heap */ false, 64, 128, 192, /* this has a smaller heap too */ -1 }; volatile int test, *testPtr = &test; volatile SigHandler oldSegvHandler; int pagesize = getpagesize(); if (baseaddr) return (true); /* Placate GNU C's warnings about clobbered variables */ testPtr = (volatile int *) &higher; testPtr = (volatile int *) &lower; testPtr = (volatile int *) &first; testPtr = (volatile int *) &step; testPtr = (volatile int *) &test; /* Install custom signal handlers to detect failed memory accesses */ oldSegvHandler = _gst_set_signal_handler (SIGSEGV, not_mapped); /* Get two reference addresses which we will base ourselves on */ mmapGuess = higher = _gst_osmem_alloc (pagesize); lower = sbrk (0); if (higher < lower) { higher = lower; lower = mmapGuess; } /* Now try each of the possibilities... */ for (step = steps; *step > -1; step += 4) { if (higher > lower + (step[3] << 20)) { first = ((step[0] ? higher : lower) + (step[1] << 20)); second = (first + (step[2] << 20)); assert ( ((intptr_t)first & (pagesize-1)) == 0); assert ( ((intptr_t)second & (pagesize-1)) == 0); /* Try reading the two locations */ if (setjmp (already_mapped) == 0) { errno = 0; access ((char *) first, F_OK); if (errno != EFAULT) { *testPtr = *first; continue; } } if (setjmp (already_mapped) == 0) { errno = 0; access ((char *) second, F_OK); if (errno != EFAULT) { *testPtr = *second; continue; } } /* Try mmap-ing them */ if (!anon_mmap_commit ((char *) first, pagesize)) continue; _gst_osmem_free ((char *) first, pagesize); if (!anon_mmap_commit ((char *) second, pagesize)) continue; /* Were not readable and could be mmap-ed. We're done. */ _gst_osmem_free ((char *) second, pagesize); break; } } /* Restore things... */ _gst_set_signal_handler (SIGSEGV, oldSegvHandler); munmap ((char *) mmapGuess, pagesize); if (first == NULL || *step == -1) return (false); else { baseaddr = (PTR) first; return (true); } } smalltalk-3.2.5/libgst/sysdep/posix/events.c0000644000175000017500000002526112123404352016035 00000000000000/******************************** -*- C -*- **************************** * * Asynchronous events from the VM - POSIX version * * ***********************************************************************/ /*********************************************************************** * * Copyright 2003, 2006, 2008, 2009 Free Software Foundation, Inc. * Written by Paolo Bonzini. * * This file is part of GNU Smalltalk. * * GNU Smalltalk is free software; you can redistribute it and/or modify it * under the terms of the GNU General Public License as published by the Free * Software Foundation; either version 2, or (at your option) any later * version. * * Linking GNU Smalltalk statically or dynamically with other modules is * making a combined work based on GNU Smalltalk. Thus, the terms and * conditions of the GNU General Public License cover the whole * combination. * * In addition, as a special exception, the Free Software Foundation * give you permission to combine GNU Smalltalk with free software * programs or libraries that are released under the GNU LGPL and with * independent programs running under the GNU Smalltalk virtual machine. * * You may copy and distribute such a system following the terms of the * GNU GPL for GNU Smalltalk and the licenses of the other code * concerned, provided that you include the source code of that other * code when and as the GNU GPL requires distribution of source code. * * Note that people who make modified versions of GNU Smalltalk are not * obligated to grant this special exception for their modified * versions; it is their choice whether to do so. The GNU General * Public License gives permission to release a modified version without * this exception; this exception also makes it possible to release a * modified version which carries forward this exception. * * GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or * FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for * more details. * * You should have received a copy of the GNU General Public License along with * GNU Smalltalk; see the file COPYING. If not, write to the Free Software * Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * ***********************************************************************/ #include "gstpriv.h" #include "lock.h" #include #ifdef HAVE_UTIME_H # include #endif #ifdef HAVE_SYS_TIMES_H # include #endif #ifdef HAVE_SYS_IOCTL_H # include #endif #ifdef HAVE_TERMIOS_H # include #endif #ifdef HAVE_STROPTS_H # include #endif #ifdef USE_POSIX_THREADS # include #endif static SigHandler sigio_handler = SIG_IGN; void set_file_interrupt (int fd, SigHandler func) { if (func != sigio_handler) { sigio_handler = func; #ifdef SIGPOLL _gst_set_signal_handler (SIGPOLL, func); #else _gst_set_signal_handler (SIGIO, func); #endif #ifdef SIGURG _gst_set_signal_handler (SIGURG, func); #endif } #if defined F_SETOWN && defined O_ASYNC { int oldflags; oldflags = fcntl (fd, F_GETFL, 0); if (((oldflags & O_ASYNC) || (fcntl (fd, F_SETFL, oldflags | O_ASYNC) != -1)) && fcntl (fd, F_SETOWN, getpid ()) != -1) return; } #endif #ifdef I_SETSIG if (ioctl (fd, I_SETSIG, S_INPUT | S_OUTPUT | S_HIPRI) > -1) return; #endif #ifdef FIOSSAIOSTAT #ifdef FIOSSAIOOWN { int stat_flags = 1; int own_flags = getpid(); if (ioctl (fd, FIOSSAIOSTAT, &stat_flags) != -1 && ioctl (fd, FIOSSAIOOWN, &own_flags) != -1) return; } #endif #endif #ifndef __MSVCRT__ #ifdef FIOASYNC { int argFIOASYNC = 1; #if defined SIOCSPGRP int argSIOCSPGRP = getpid (); if (ioctl (fd, SIOCSPGRP, &argSIOCSPGRP) > -1 || ioctl (fd, FIOASYNC, &argFIOASYNC) > -1) return; #elif defined O_ASYNC int oldflags; oldflags = fcntl (fd, F_GETFL, 0); if (((oldflags & O_ASYNC) || (fcntl (fd, F_SETFL, oldflags | O_ASYNC) != -1)) && ioctl (fd, FIOASYNC, &argFIOASYNC) > -1) return; #else if (ioctl (fd, FIOASYNC, &argFIOASYNC) > -1) return; #endif } #endif #endif /* FIOASYNC */ } /* This structure defines a list of pairs `struct pollfd'->semaphore which map each pollfd that is passed by the OS to the semaphore to be signalled when the corresponding I/O situation becomes possible. */ typedef struct polling_queue { int poll; OOP semaphoreOOP; struct polling_queue *next; } polling_queue; /* These two variables hold the list of `polling_queue' structures. Replacing this with a binary tree is not really useful because the array of pollfd structures must be scanned and kept sequential every time that I/O happens, so it does not bother us very much to have to scan the list to find the semaphore that is to be signaled. */ static polling_queue *head, **p_tail_next = &head; /* This variable holds a variable-sized array of pollfd structures. NUM_USED_POLLFDS of the total NUM_TOTAL_POLLFDS items available are being used. */ static struct pollfd *pollfds; static int num_used_pollfds, num_total_pollfds; /* These are the signal handlers that we install to process asynchronous events and pass them to the Smalltalk virtual machine. file_polling_handler scans the above array of pollfds and signals the corresponding semaphores. */ static RETSIGTYPE file_polling_handler (int sig); static RETSIGTYPE dummy_signal_handler (int sig) { } void _gst_init_async_events (void) { _gst_set_signal_handler (SIGUSR2, dummy_signal_handler); } void _gst_async_timed_wait (OOP semaphoreOOP, int64_t milliTime) { _gst_async_interrupt_wait (semaphoreOOP, SIGALRM); _gst_sigalrm_at (milliTime); } mst_Boolean _gst_is_timeout_programmed (void) { return (!IS_NIL (no_opt (_gst_sem_int_vec[SIGALRM].data))); } void _gst_register_socket (int fd, mst_Boolean passive) { } int _gst_sync_file_polling (int fd, int cond) { int result; struct pollfd pfd; pfd.fd = fd; switch (cond) { case 0: pfd.events = POLLIN; break; case 1: pfd.events = POLLOUT; break; case 2: pfd.events = POLLPRI; break; default: return -1; } do { errno = 0; pfd.revents = 0; result = poll (&pfd, 1, 0); } while ((result == -1) && (errno == EINTR)); if (result == -1) return -1; if (pfd.revents & pfd.events) return 1; else if (pfd.revents & (POLLERR | POLLHUP | POLLNVAL)) { errno = 0; return -1; } else return 0; } static void signal_polled_files (int fd, mst_Boolean try_again) { polling_queue *node, **pprev; int n, more; if (num_used_pollfds == 0) return; do { if (fd == -1) do { errno = 0; n = poll (pollfds, num_used_pollfds, 0); } while (n == -1 && errno == EINTR); num_used_pollfds = 0; more = false; for (node = head, pprev = &head; node; node = *pprev) { struct pollfd *poll = &pollfds[node->poll]; if (fd == -1 ? (poll->revents & (poll->events | POLLERR | POLLHUP | POLLNVAL)) : poll->fd == fd) { more = try_again; poll->events = 0; _gst_sync_signal (node->semaphoreOOP, false); _gst_unregister_oop (node->semaphoreOOP); /* Pass over the current node */ *pprev = node->next; if (p_tail_next == &node->next) p_tail_next = pprev; xfree (node); } else { poll->revents = 0; node->poll = num_used_pollfds; pollfds[num_used_pollfds++] = *poll; /* Prepare to get the next node */ pprev = &(node->next); } } } while (more && num_used_pollfds); } int _gst_get_fd_error (int fd) { return 0; } void _gst_remove_fd_polling_handlers (int fd) { signal_polled_files (fd, false); } static void async_signal_polled_files (OOP unusedOOP) { signal_polled_files (-1, true); } RETSIGTYPE file_polling_handler (int sig) { if (num_used_pollfds > 0) { static async_queue_entry e = { async_signal_polled_files, NULL, NULL }; e.data = _gst_nil_oop; _gst_async_call_internal (&e); } _gst_set_signal_handler (sig, file_polling_handler); _gst_wakeup (); } #ifdef USE_POSIX_THREADS pthread_t waiting_thread; #endif void _gst_pause (void) { #ifdef USE_POSIX_THREADS waiting_thread = pthread_self (); #endif _gst_disable_interrupts (false); if (!_gst_have_pending_async_calls ()) { /* We use sigsuspend to atomically replace the mask. pause does not allow that. */ sigset_t set; sigemptyset (&set); sigsuspend (&set); } #ifdef USE_POSIX_THREADS waiting_thread = 0; #endif _gst_enable_interrupts (false); } void _gst_wakeup (void) { #ifdef USE_POSIX_THREADS __sync_synchronize (); if (waiting_thread && pthread_self () != waiting_thread) pthread_kill (waiting_thread, SIGUSR2); #endif } int _gst_async_file_polling (int fd, int cond, OOP semaphoreOOP) { int result; int index; polling_queue *new; index = num_used_pollfds++; /* Enable async io on the fd before we poll as data could arrive after the fd was polled and before the async io was enabled. */ set_file_interrupt (fd, file_polling_handler); result = _gst_sync_file_polling (fd, cond); if (result != 0) { --num_used_pollfds; return (result); } new = (polling_queue *) xmalloc (sizeof (polling_queue)); new->poll = index; new->semaphoreOOP = semaphoreOOP; new->next = NULL; if (index == num_total_pollfds) { num_total_pollfds += 64; pollfds = (struct pollfd *) xrealloc (pollfds, num_total_pollfds * sizeof (struct pollfd)); } pollfds[index].fd = fd; switch (cond) { case 0: pollfds[index].events = POLLIN; break; case 1: pollfds[index].events = POLLOUT; break; case 2: pollfds[index].events = POLLPRI; break; default: return -1; } pollfds[index].revents = 0; /* Even if I/O was made possible while setting up our machinery, the list will only be walked before the next bytecode, so there is no race. We incremented num_used_pollfds very early so that the async call will be scheduled. */ *p_tail_next = new; p_tail_next = &new->next; _gst_register_oop (semaphoreOOP); _gst_sync_wait (semaphoreOOP); return (result); } void _gst_wait_for_input (int fd) { int result; struct pollfd pfd; pfd.fd = fd; pfd.events = POLLIN; pfd.revents = 0; do { errno = 0; result = poll (&pfd, 1, -1); /* Infinite wait */ } while ((result == 0 && (pfd.revents & POLLHUP) == 0) || ((result == -1) && (errno == EINTR))); } smalltalk-3.2.5/libgst/sysdep/posix/time.c0000644000175000017500000000663112123404352015467 00000000000000/******************************** -*- C -*- **************************** * * System specific implementation module. * * This module contains implementations of various operating system * specific routines. This module should encapsulate most (or all) * of these calls so that the rest of the code is portable. * * ***********************************************************************/ /*********************************************************************** * * Copyright 1988,89,90,91,92,94,95,99,2000,2001,2002,2003,2006,2007,2008,2009 * Free Software Foundation, Inc. * Written by Steve Byrne. * * This file is part of GNU Smalltalk. * * GNU Smalltalk is free software; you can redistribute it and/or modify it * under the terms of the GNU General Public License as published by the Free * Software Foundation; either version 2, or (at your option) any later * version. * * Linking GNU Smalltalk statically or dynamically with other modules is * making a combined work based on GNU Smalltalk. Thus, the terms and * conditions of the GNU General Public License cover the whole * combination. * * In addition, as a special exception, the Free Software Foundation * give you permission to combine GNU Smalltalk with free software * programs or libraries that are released under the GNU LGPL and with * independent programs running under the GNU Smalltalk virtual machine. * * You may copy and distribute such a system following the terms of the * GNU GPL for GNU Smalltalk and the licenses of the other code * concerned, provided that you include the source code of that other * code when and as the GNU GPL requires distribution of source code. * * Note that people who make modified versions of GNU Smalltalk are not * obligated to grant this special exception for their modified * versions; it is their choice whether to do so. The GNU General * Public License gives permission to release a modified version without * this exception; this exception also makes it possible to release a * modified version which carries forward this exception. * * GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or * FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for * more details. * * You should have received a copy of the GNU General Public License along with * GNU Smalltalk; see the file COPYING. If not, write to the Free Software * Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * ***********************************************************************/ #include "gstpriv.h" #ifdef HAVE_SYS_TIMES_H # include #endif #ifdef HAVE_SYS_TIMEB_H #include #endif uint64_t _gst_get_ns_time (void) { #if defined HAVE_CLOCK_GETTIME && defined _POSIX_MONOTONIC_CLOCK struct timespec tp; clock_gettime (CLOCK_MONOTONIC, &tp); return (tp.tv_sec * (uint64_t) 1000000000 + tp.tv_nsec); #else struct timeval t; gettimeofday (&t, NULL); return (t.tv_sec * (uint64_t) 1000000000 + t.tv_usec * 1000); #endif } char * _gst_current_time_zone_name (void) { const char *zone; zone = getenv ("TZ"); if (!zone) zone = "XXX"; return xstrdup (zone); } void _gst_usleep (int us) { #if defined HAVE_NANOSLEEP struct timespec ts = { us / 1000000, (us % 1000000) * 1000 }; nanosleep (&ts, NULL); #elif defined HAVE_USLEEP usleep (us); #endif } smalltalk-3.2.5/libgst/sysdep/posix/timer.c0000644000175000017500000001023412123404352015643 00000000000000/******************************** -*- C -*- **************************** * * System specific implementation module. * * This module contains implementations of various operating system * specific routines. This module should encapsulate most (or all) * of these calls so that the rest of the code is portable. * * ***********************************************************************/ /*********************************************************************** * * Copyright 1988,89,90,91,92,94,95,99,2000,2001,2002,2003,2006,2007,2008,2009 * Free Software Foundation, Inc. * Written by Steve Byrne. * * This file is part of GNU Smalltalk. * * GNU Smalltalk is free software; you can redistribute it and/or modify it * under the terms of the GNU General Public License as published by the Free * Software Foundation; either version 2, or (at your option) any later * version. * * Linking GNU Smalltalk statically or dynamically with other modules is * making a combined work based on GNU Smalltalk. Thus, the terms and * conditions of the GNU General Public License cover the whole * combination. * * In addition, as a special exception, the Free Software Foundation * give you permission to combine GNU Smalltalk with free software * programs or libraries that are released under the GNU LGPL and with * independent programs running under the GNU Smalltalk virtual machine. * * You may copy and distribute such a system following the terms of the * GNU GPL for GNU Smalltalk and the licenses of the other code * concerned, provided that you include the source code of that other * code when and as the GNU GPL requires distribution of source code. * * Note that people who make modified versions of GNU Smalltalk are not * obligated to grant this special exception for their modified * versions; it is their choice whether to do so. The GNU General * Public License gives permission to release a modified version without * this exception; this exception also makes it possible to release a * modified version which carries forward this exception. * * GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or * FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for * more details. * * You should have received a copy of the GNU General Public License along with * GNU Smalltalk; see the file COPYING. If not, write to the Free Software * Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * ***********************************************************************/ #include "gstpriv.h" #ifdef HAVE_SYS_TIMES_H # include #endif void _gst_sigvtalrm_every (int deltaMilli, SigHandler func) { #if defined ITIMER_VIRTUAL struct itimerval value; _gst_set_signal_handler (SIGVTALRM, func); value.it_value.tv_sec = value.it_value.tv_usec = 0; value.it_interval.tv_sec = deltaMilli / 1000; value.it_interval.tv_usec = (deltaMilli % 1000) * 1000; setitimer (ITIMER_VIRTUAL, &value, (struct itimerval *) 0); #endif } #ifdef HAVE_TIMER_CREATE static timer_t timer; static mst_Boolean have_timer; #endif void _gst_sigalrm_at (int64_t nsTime) { #ifdef HAVE_TIMER_CREATE if (have_timer) { struct itimerspec value; value.it_interval.tv_sec = value.it_interval.tv_nsec = 0; value.it_value.tv_sec = nsTime / 1000000000; value.it_value.tv_nsec = nsTime % 1000000000; timer_settime (timer, TIMER_ABSTIME, &value, NULL); } else #endif { int64_t deltaMilli = (nsTime - _gst_get_ns_time()) / 1000000; struct itimerval value; value.it_interval.tv_sec = value.it_interval.tv_usec = 0; value.it_value.tv_sec = deltaMilli / 1000; value.it_value.tv_usec = (deltaMilli % 1000) * 1000; setitimer (ITIMER_REAL, &value, (struct itimerval *) 0); } } void _gst_init_sysdep_timer (void) { #if defined HAVE_TIMER_CREATE && defined _POSIX_MONOTONIC_CLOCK struct sigevent sev; memset(&sev, 0, sizeof(sev)); sev.sigev_notify = SIGEV_SIGNAL; sev.sigev_signo = SIGALRM; if (timer_create (CLOCK_MONOTONIC, &sev, &timer) != -1) have_timer = true; #endif } smalltalk-3.2.5/libgst/sysdep/posix/findexec.c0000644000175000017500000001446712123404352016324 00000000000000/******************************** -*- C -*- **************************** * * System specific implementation module. * * This module contains implementations of various operating system * specific routines. This module should encapsulate most (or all) * of these calls so that the rest of the code is portable. * * ***********************************************************************/ /*********************************************************************** * * Copyright 1988,89,90,91,92,94,95,99,2000,2001,2002,2003,2006,2007,2008,2009 * Free Software Foundation, Inc. * Written by Steve Byrne. * * This file is part of GNU Smalltalk. * * GNU Smalltalk is free software; you can redistribute it and/or modify it * under the terms of the GNU General Public License as published by the Free * Software Foundation; either version 2, or (at your option) any later * version. * * Linking GNU Smalltalk statically or dynamically with other modules is * making a combined work based on GNU Smalltalk. Thus, the terms and * conditions of the GNU General Public License cover the whole * combination. * * In addition, as a special exception, the Free Software Foundation * give you permission to combine GNU Smalltalk with free software * programs or libraries that are released under the GNU LGPL and with * independent programs running under the GNU Smalltalk virtual machine. * * You may copy and distribute such a system following the terms of the * GNU GPL for GNU Smalltalk and the licenses of the other code * concerned, provided that you include the source code of that other * code when and as the GNU GPL requires distribution of source code. * * Note that people who make modified versions of GNU Smalltalk are not * obligated to grant this special exception for their modified * versions; it is their choice whether to do so. The GNU General * Public License gives permission to release a modified version without * this exception; this exception also makes it possible to release a * modified version which carries forward this exception. * * GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or * FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for * more details. * * You should have received a copy of the GNU General Public License along with * GNU Smalltalk; see the file COPYING. If not, write to the Free Software * Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * ***********************************************************************/ #include "gstpriv.h" #ifdef HAVE_SYS_PARAM_H # include #endif /* Get declaration of _NSGetExecutablePath on MacOS X 10.2 or newer. */ #if HAVE_MACH_O_DYLD_H # define ENUM_DYLD_BOOL # include #endif #ifdef __linux__ /* File descriptor of the executable, used for double checking. */ static int executable_fd = -1; #endif /* The path to the executable, derived from argv[0]. */ const char *_gst_executable_path = NULL; /* Tests whether a given pathname may belong to the executable. */ static mst_Boolean maybe_executable (const char *filename) { if (!_gst_file_is_executable (filename)) return false; #ifdef __linux__ if (executable_fd >= 0) { /* If we already have an executable_fd, check that filename points to the same inode. */ struct stat statexe, statfile; if (fstat (executable_fd, &statexe) < 0 || stat (filename, &statfile) < 0 || !(statfile.st_dev && statfile.st_dev == statexe.st_dev && statfile.st_ino == statexe.st_ino)) return false; close (executable_fd); executable_fd = -1; } #endif return true; } /* Determine the full pathname of the current executable, freshly allocated. Return NULL if unknown. Guaranteed to work on Linux and Win32, Mac OS X. Likely to work on the other Unixes (maybe except BeOS), under most conditions. */ static char * find_executable (const char *argv0) { #ifdef PATH_MAX int path_max = PATH_MAX; #else int path_max = pathconf (name, _PC_PATH_MAX); if (path_max <= 0) path_max = 1024; #endif #if HAVE_MACH_O_DYLD_H && HAVE__NSGETEXECUTABLEPATH char *location = alloca (path_max); uint32_t length = path_max; if (_NSGetExecutablePath (location, &length) == 0 && location[0] == '/') return _gst_get_full_file_name (location); #elif defined __linux__ /* The executable is accessible as /proc//exe. In newer Linux versions, also as /proc/self/exe. Linux >= 2.1 provides a symlink to the true pathname; older Linux versions give only device and ino, enclosed in brackets, which we cannot use here. */ { char buf[6 + 10 + 5]; char *location = xmalloc (path_max + 1); ssize_t n; sprintf (buf, "/proc/%d/exe", getpid ()); n = readlink (buf, location, path_max); if (n > 0 && location[0] != '[') { location[n] = '\0'; return location; } if (executable_fd < 0) executable_fd = open (buf, O_RDONLY, 0); } #endif if (*argv0 == '-') argv0++; /* Guess the executable's full path. We assume the executable has been called via execlp() or execvp() with properly set up argv[0]. exec searches paths without slashes in the directory list given by $PATH. */ if (!strchr (argv0, '/')) { const char *p_next = getenv ("PATH"); const char *p; while ((p = p_next) != NULL) { char *concat_name; p_next = strchr (p, ':'); /* An empty PATH element designates the current directory. */ if (p_next == p + 1) concat_name = xstrdup (argv0); else if (!p_next) asprintf (&concat_name, "%s/%s", p, argv0); else asprintf (&concat_name, "%.*s/%s", (int)(p_next++ - p), p, argv0); if (maybe_executable (concat_name)) { char *full_path = _gst_get_full_file_name (concat_name); free (concat_name); return full_path; } free (concat_name); } /* Not found in the PATH, assume the current directory. */ } if (maybe_executable (argv0)) return _gst_get_full_file_name (argv0); /* No way to find the executable. */ #ifdef __linux__ close (executable_fd); executable_fd = -1; #endif return NULL; } void _gst_set_executable_path (const char *argv0) { _gst_executable_path = find_executable (argv0); } smalltalk-3.2.5/libgst/sysdep/common/0000755000175000017500000000000012130456004014564 500000000000000smalltalk-3.2.5/libgst/sysdep/common/files.c0000644000175000017500000002317712123404352015765 00000000000000/******************************** -*- C -*- **************************** * * System specific implementation module. * * This module contains implementations of various operating system * specific routines. This module should encapsulate most (or all) * of these calls so that the rest of the code is portable. * * ***********************************************************************/ /*********************************************************************** * * Copyright 1988,89,90,91,92,94,95,99,2000,2001,2002,2003,2006,2007,2008,2009 * Free Software Foundation, Inc. * Written by Steve Byrne. * * This file is part of GNU Smalltalk. * * GNU Smalltalk is free software; you can redistribute it and/or modify it * under the terms of the GNU General Public License as published by the Free * Software Foundation; either version 2, or (at your option) any later * version. * * Linking GNU Smalltalk statically or dynamically with other modules is * making a combined work based on GNU Smalltalk. Thus, the terms and * conditions of the GNU General Public License cover the whole * combination. * * In addition, as a special exception, the Free Software Foundation * give you permission to combine GNU Smalltalk with free software * programs or libraries that are released under the GNU LGPL and with * independent programs running under the GNU Smalltalk virtual machine. * * You may copy and distribute such a system following the terms of the * GNU GPL for GNU Smalltalk and the licenses of the other code * concerned, provided that you include the source code of that other * code when and as the GNU GPL requires distribution of source code. * * Note that people who make modified versions of GNU Smalltalk are not * obligated to grant this special exception for their modified * versions; it is their choice whether to do so. The GNU General * Public License gives permission to release a modified version without * this exception; this exception also makes it possible to release a * modified version which carries forward this exception. * * GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or * FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for * more details. * * You should have received a copy of the GNU General Public License along with * GNU Smalltalk; see the file COPYING. If not, write to the Free Software * Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * ***********************************************************************/ #include "gstpriv.h" #ifdef HAVE_UTIME_H # include #endif #ifdef HAVE_SYS_TIMES_H # include #endif #ifdef HAVE_SYS_WAIT_H #include #endif #ifdef HAVE_SYS_PARAM_H #include #endif #ifdef HAVE_SYS_TIMEB_H #include #endif #ifndef F_OK #define F_OK 0 #define X_OK 1 #define W_OK 2 #define R_OK 4 #endif #ifndef O_BINARY #define O_BINARY 0 #endif #if !defined O_CLOEXEC && defined O_NOINHERIT #define O_CLOEXEC O_NOINHERIT #endif #ifndef PATH_MAX #define PATH_MAX 1024 /* max length of a file and path */ #endif #ifndef MAXSYMLINKS #define MAXSYMLINKS 5 #endif char * _gst_get_cur_dir_name (void) { char *cwd; char *ret; unsigned path_max; int save_errno; path_max = (unsigned) PATH_MAX; path_max += 2; /* The getcwd docs say to do this. */ cwd = xmalloc (path_max); errno = 0; do { ret = getcwd (cwd, path_max); if (ret) return (cwd); if (errno != ERANGE) break; errno = 0; path_max += 128; cwd = xrealloc (cwd, path_max); } while (!errno); save_errno = errno; xfree (cwd); errno = save_errno; return (NULL); } int _gst_set_file_access_times (const char *name, long new_atime, long new_mtime) { int result; #if defined HAVE_UTIMES struct timeval times[2]; times[0].tv_sec = new_atime + 86400 * 10957; times[1].tv_sec = new_mtime + 86400 * 10957; times[0].tv_usec = times[1].tv_usec = 0; result = utimes (name, times); #elif defined HAVE_UTIME struct utimbuf utb; utb.actime = new_atime + 86400 * 10957; utb.modtime = new_mtime + 86400 * 10957; result = utime (name, &utb); #else #warning neither utime nor utimes are available. errno = ENOSYS; result = -1; #endif if (!result) errno = 0; return (result); } mst_Boolean _gst_file_is_newer (const char *file1, const char *file2) { static char *prev_file1; static struct stat st1; struct stat st2; if (!prev_file1 || strcmp (file1, prev_file1)) { if (prev_file1) xfree (prev_file1); prev_file1 = xstrdup (file1); if (!_gst_file_is_readable (file1)) return false; if (stat (file1, &st1) < 0) return false; } if (!_gst_file_is_readable (file2)) return true; if (stat (file2, &st2) < 0) return true; if (st1.st_mtime != st2.st_mtime) return st1.st_mtime > st2.st_mtime; /* 15 years have passed and nothing seems to have changed. */ #if defined HAVE_STRUCT_STAT_ST_MTIMENSEC return st1.st_mtimensec >= st2.st_mtimensec; #elif defined HAVE_STRUCT_STAT_ST_MTIM_TV_NSEC return st1.st_mtim.tv_nsec >= st2.st_mtim.tv_nsec; #elif defined HAVE_STRUCT_STAT_ST_MTIMESPEC_TV_NSEC return st1.st_mtimespec.tv_nsec >= st2.st_mtimespec.tv_nsec; #else /* Say that the image file is newer. */ return true; #endif } mst_Boolean _gst_file_is_readable (const char *fileName) { return (access (fileName, R_OK) == 0); } mst_Boolean _gst_file_is_writeable (const char *fileName) { return (access (fileName, W_OK) == 0); } mst_Boolean _gst_file_is_executable (const char *fileName) { return (access (fileName, X_OK) == 0); } char * _gst_relocate_path (const char *path) { const char *p; char *s; /* Detect absolute paths. */ #if defined(MSDOS) || defined(WIN32) || defined(__OS2__) if ((path[0] && path[1] == ':') || path[0] == '/' || path[0] == '\\') return xstrdup (path); #else if (path[0] == '/') return xstrdup (path); #endif /* Remove filename from executable path. */ p = _gst_executable_path + strlen (_gst_executable_path); do --p; while (p >= _gst_executable_path && *p != '/' #if defined(MSDOS) || defined(WIN32) || defined(__OS2__) && *p != '\\' #endif ); p++; /* Now p points just past the last separator (if any). */ s = alloca (p - _gst_executable_path + strlen (path) + 1); sprintf (s, "%.*s%s", (int)(p - _gst_executable_path), _gst_executable_path, path); return _gst_get_full_file_name (s); } int _gst_open_file (const char *filename, const char *mode) { mst_Boolean create = false; int oflags = O_BINARY, access = 0; int fd, i; switch (*mode) { case 'a': access = O_WRONLY; oflags |= O_APPEND; create = 1; break; case 'w': access = O_WRONLY; oflags |= O_TRUNC; create = 1; break; case 'r': access = O_RDONLY; break; default: return -1; } for (i = 1; i < 3; ++i) { ++mode; if (*mode == '\0') break; else if (*mode == '+') create = 1, access = O_RDWR; else if (*mode == 'x') oflags |= O_EXCL; } #ifdef O_CLOEXEC oflags |= O_CLOEXEC; #endif if (create) fd = open (filename, oflags | access | O_CREAT, 0666); else fd = open (filename, oflags | access); if (fd < 0) return -1; #ifndef O_CLOEXEC fcntl (fd, F_SETFD, fcntl (fd, F_GETFD, 0) | 1); #endif return fd; } mst_Boolean _gst_is_pipe (int fd) { struct stat st; fstat (fd, &st); #ifdef S_IFREG return !(st.st_mode & S_IFREG); #else return !S_ISREG (st.st_mode); #endif } ssize_t _gst_recv (int fd, PTR buffer, size_t size, int flags) { #ifdef HAVE_SOCKETS ssize_t result; int save_errno = errno; for (;;) { result = recvfrom (FD_TO_SOCKET (fd), buffer, size, flags, NULL, NULL); if (is_socket_error (EFAULT)) abort (); if (is_socket_error (EINTR)) clear_socket_error (); else break; } if (errno == EINTR) errno = save_errno; return result; #else errno = ENOSYS; return -1; #endif } ssize_t _gst_send (int fd, PTR buffer, size_t size, int flags) { #ifdef HAVE_SOCKETS ssize_t result; int save_errno = errno; for (;;) { result = send (FD_TO_SOCKET (fd), buffer, size, flags); if (is_socket_error (EFAULT)) abort (); if (is_socket_error (EINTR)) clear_socket_error (); else break; } if (errno == EINTR) errno = save_errno; return result; #else errno = ENOSYS; return -1; #endif } ssize_t _gst_read (int fd, PTR buffer, size_t size) { ssize_t result; int save_errno = errno; do { result = read (fd, buffer, size); if (errno == EFAULT) abort (); } while (result == -1 && errno == EINTR); if (errno == EINTR) errno = save_errno; return result; } ssize_t _gst_write (int fd, PTR buffer, size_t size) { ssize_t result; int save_errno = errno; do { result = write (fd, buffer, size); if (errno == EFAULT) abort (); } while (result == -1 && errno == EINTR); if (errno == EINTR) errno = save_errno; return result; } void _gst_init_sysdep (void) { _gst_init_sysdep_timer (); tzset (); #ifdef SIGPIPE _gst_set_signal_handler (SIGPIPE, SIG_IGN); #endif _gst_set_signal_handler (SIGFPE, SIG_IGN); #ifdef SIGPOLL _gst_set_signal_handler (SIGPOLL, SIG_IGN); #elif defined SIGIO _gst_set_signal_handler (SIGIO, SIG_IGN); #endif #ifdef SIGURG _gst_set_signal_handler (SIGURG, SIG_IGN); #endif } void _gst_debug (void) { fflush (stdout); /* abort(); */ /* raise(SIGTRAP); */ /* getchar(); */ } smalltalk-3.2.5/libgst/sysdep/common/time.c0000644000175000017500000001077012123404352015614 00000000000000/******************************** -*- C -*- **************************** * * System specific implementation module. * * This module contains implementations of various operating system * specific routines. This module should encapsulate most (or all) * of these calls so that the rest of the code is portable. * * ***********************************************************************/ /*********************************************************************** * * Copyright 1988,89,90,91,92,94,95,99,2000,2001,2002,2003,2006,2007,2008,2009 * Free Software Foundation, Inc. * Written by Steve Byrne. * * This file is part of GNU Smalltalk. * * GNU Smalltalk is free software; you can redistribute it and/or modify it * under the terms of the GNU General Public License as published by the Free * Software Foundation; either version 2, or (at your option) any later * version. * * Linking GNU Smalltalk statically or dynamically with other modules is * making a combined work based on GNU Smalltalk. Thus, the terms and * conditions of the GNU General Public License cover the whole * combination. * * In addition, as a special exception, the Free Software Foundation * give you permission to combine GNU Smalltalk with free software * programs or libraries that are released under the GNU LGPL and with * independent programs running under the GNU Smalltalk virtual machine. * * You may copy and distribute such a system following the terms of the * GNU GPL for GNU Smalltalk and the licenses of the other code * concerned, provided that you include the source code of that other * code when and as the GNU GPL requires distribution of source code. * * Note that people who make modified versions of GNU Smalltalk are not * obligated to grant this special exception for their modified * versions; it is their choice whether to do so. The GNU General * Public License gives permission to release a modified version without * this exception; this exception also makes it possible to release a * modified version which carries forward this exception. * * GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or * FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for * more details. * * You should have received a copy of the GNU General Public License along with * GNU Smalltalk; see the file COPYING. If not, write to the Free Software * Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * ***********************************************************************/ #include "gstpriv.h" #ifdef HAVE_UTIME_H # include #endif #ifdef HAVE_SYS_TIMES_H # include #endif #ifdef HAVE_SYS_TIMEB_H #include #endif #define TM_YEAR_BASE 1900 /* Yield A - B, measured in seconds. This function is copied from the GNU C Library. */ static int tm_diff (struct tm *a, struct tm *b) { /* Compute intervening leap days correctly even if year is negative. Take care to avoid int overflow in leap day calculations, but it's OK to assume that A and B are close to each other. */ int a4 = (a->tm_year >> 2) + (TM_YEAR_BASE >> 2) - !(a->tm_year & 3); int b4 = (b->tm_year >> 2) + (TM_YEAR_BASE >> 2) - !(b->tm_year & 3); int a100 = a4 / 25 - (a4 % 25 < 0); int b100 = b4 / 25 - (b4 % 25 < 0); int a400 = a100 >> 2; int b400 = b100 >> 2; int intervening_leap_days = (a4 - b4) - (a100 - b100) + (a400 - b400); int years = a->tm_year - b->tm_year; int days = (365 * years + intervening_leap_days + (a->tm_yday - b->tm_yday)); return (60 * (60 * (24 * days + (a->tm_hour - b->tm_hour)) + (a->tm_min - b->tm_min)) + (a->tm_sec - b->tm_sec)); } time_t _gst_adjust_time_zone (time_t t) { struct tm save_tm, *decoded_time; time_t bias; #ifdef LOCALTIME_CACHE tzset (); #endif decoded_time = localtime (&t); save_tm = *decoded_time; decoded_time = gmtime (&t); bias = tm_diff (&save_tm, decoded_time); return (t + bias); } long _gst_current_time_zone_bias (void) { time_t now; long bias; struct tm save_tm, *decoded_time; time (&now); #ifdef LOCALTIME_CACHE tzset (); #endif decoded_time = localtime (&now); save_tm = *decoded_time; decoded_time = gmtime (&now); bias = tm_diff (&save_tm, decoded_time); return (bias); } time_t _gst_get_time (void) { time_t now; time (&now); return (_gst_adjust_time_zone (now)); } uint64_t _gst_get_milli_time (void) { return _gst_get_ns_time() / 1000000; } smalltalk-3.2.5/libgst/oop.h0000644000175000017500000003760012130343734012666 00000000000000/******************************** -*- C -*- **************************** * * Object Table declarations. * * ***********************************************************************/ /*********************************************************************** * * Copyright 1988,89,90,91,92,94,95,99,2000,2001,2002,2006,2007,2008,2009 * Free Software Foundation, Inc. * Written by Steve Byrne. * * This file is part of GNU Smalltalk. * * GNU Smalltalk is free software; you can redistribute it and/or modify it * under the terms of the GNU General Public License as published by the Free * Software Foundation; either version 2, or (at your option) any later * version. * * Linking GNU Smalltalk statically or dynamically with other modules is * making a combined work based on GNU Smalltalk. Thus, the terms and * conditions of the GNU General Public License cover the whole * combination. * * In addition, as a special exception, the Free Software Foundation * give you permission to combine GNU Smalltalk with free software * programs or libraries that are released under the GNU LGPL and with * independent programs running under the GNU Smalltalk virtual machine. * * You may copy and distribute such a system following the terms of the * GNU GPL for GNU Smalltalk and the licenses of the other code * concerned, provided that you include the source code of that other * code when and as the GNU GPL requires distribution of source code. * * Note that people who make modified versions of GNU Smalltalk are not * obligated to grant this special exception for their modified * versions; it is their choice whether to do so. The GNU General * Public License gives permission to release a modified version without * this exception; this exception also makes it possible to release a * modified version which carries forward this exception. * * GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or * FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for * more details. * * You should have received a copy of the GNU General Public License along with * GNU Smalltalk; see the file COPYING. If not, write to the Free Software * Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * ***********************************************************************/ #ifndef GST_OOP_H #define GST_OOP_H /* Define this flag to disable blacking of grey pages (that is, the entire oldspace is scanned to look for reachable newspace objects). This is also necessary to run valgrind on GNU Smalltalk. */ /* #define NO_SIGSEGV_HANDLING */ /* ... but always define it if libsigsegv does not support this platform. */ #if !defined HAVE_SIGSEGV_RECOVERY || !(HAVE_SIGSEGV_RECOVERY-0) #define NO_SIGSEGV_HANDLING #endif #define NUM_CHAR_OBJECTS 256 #define NUM_BUILTIN_OBJECTS 3 #define FIRST_OOP_INDEX (-NUM_CHAR_OBJECTS-NUM_BUILTIN_OBJECTS) #define CHAR_OBJECT_BASE FIRST_OOP_INDEX #define BUILTIN_OBJECT_BASE (-NUM_BUILTIN_OBJECTS) /* The number of OOPs in the system. This is exclusive of Character, True, False, and UndefinedObject (nil) oops, which are built-ins. */ #define INITIAL_OOP_TABLE_SIZE (1024 * 128 + BUILTIN_OBJECT_BASE) #define MAX_OOP_TABLE_SIZE (1 << 23) /* The number of free OOPs under which we trigger GCs. 0 is not enough because _gst_scavenge might still need some oops in empty_context_stack!!! */ #define LOW_WATER_OOP_THRESHOLD (1024 * 2) #define SMALLTALK_OOP_INDEX 0 #define PROCESSOR_OOP_INDEX 1 #define SYM_TABLE_OOP_INDEX 2 #define NIL_OOP_INDEX (BUILTIN_OBJECT_BASE + 0) #define TRUE_OOP_INDEX (BUILTIN_OBJECT_BASE + 1) #define FALSE_OOP_INDEX (BUILTIN_OBJECT_BASE + 2) /* Given a number of bytes "x", return the number of 32 bit words needed to represent that object, rounded up to the nearest 32 bit word boundary. */ #define ROUNDED_WORDS(x) \ (((x) + sizeof(long) - 1) / sizeof(long)) /* Given a number of bytes "x", round it up to the next multiple of sizeof (long). */ #define ROUNDED_BYTES(x) \ (((x) + sizeof(long) - 1) & ~(sizeof(long) - 1)) struct gst_character { OBJ_HEADER; OOP charVal; }; struct gst_undefined_object { OBJ_HEADER; }; struct gst_boolean { OBJ_HEADER; OOP booleanValue; }; typedef struct gst_object_memory { OBJ_HEADER; OOP bytesPerOOP, bytesPerOTE, edenSize, survSpaceSize, oldSpaceSize, fixedSpaceSize, edenUsedBytes, survSpaceUsedBytes, oldSpaceUsedBytes, fixedSpaceUsedBytes, rememberedTableEntries, numScavenges, numGlobalGCs, numCompactions, numGrowths, numOldOOPs, numFixedOOPs, numWeakOOPs, numOTEs, numFreeOTEs, timeBetweenScavenges, timeBetweenGlobalGCs, timeBetweenGrowths, timeToScavenge, timeToCollect, timeToCompact, reclaimedBytesPerScavenge, tenuredBytesPerScavenge, reclaimedBytesPerGlobalGC, reclaimedPercentPerScavenge, allocFailures, allocMatches, allocSplits, allocProbes; } *gst_object_memory; typedef unsigned long inc_ptr; /* Garbage collector data structures */ typedef struct page_tree { rb_node_t rb; OOP *base; } page_tree; typedef struct weak_area_tree { rb_node_t rb; OOP oop; /* Weak OOP */ } weak_area_tree; typedef struct new_space { OOP *minPtr; /* points to lowest addr in heap */ OOP *maxPtr; /* points to highest addr in heap */ OOP *allocPtr; /* new space ptr, starts low, goes up */ unsigned long totalSize; /* allocated size */ } new_space; typedef struct surv_space { OOP *tenurePtr; /* points to oldest object */ OOP *allocPtr; /* points to past newest object */ OOP *minPtr; /* points to lowest addr in heap */ OOP *maxPtr; /* points to highest addr in heap */ OOP *topPtr; /* points to highest used addr in heap */ int allocated; /* bytes allocated in the last scavenge */ int filled; /* bytes currently used */ int totalSize; /* allocated size */ } surv_space; typedef struct grey_area_node { struct grey_area_node *next; OOP *base; int n; OOP oop; } grey_area_node; typedef struct grey_area_list { grey_area_node *head, *tail; } grey_area_list; typedef struct cheney_scan_state { OOP *queue_at; /* Next scanned object in queue */ OOP *at; /* Base of currently scanned object */ OOP current; /* Currently scanned object */ } cheney_scan_state; struct mark_queue { OOP *firstOOP, *endOOP; }; struct memory_space { heap_data *old, *fixed; struct new_space eden; struct surv_space surv[2], tenuring_queue; struct mark_queue *markQueue, *lastMarkQueue; /* The current state of the copying collector's scan phase. */ struct cheney_scan_state scan; /* The object table. This contains a pointer to the object, and some flag bits indicating whether the object is read-only, reachable and/or pooled. Some of the bits indicate the difference between the allocated length (stored in the object itself), and the real length, because variable byte objects may not be an even multiple of sizeof(PTR). */ struct oop_s *ot, *ot_base; /* The number of OOPs in the free list and in the full OOP table. num_free_oops is only correct after a GC! */ int num_free_oops, ot_size; /* The root set of the scavenger. This includes pages in oldspace that were written to, and objects that had to be tenured before they were scanned. */ grey_area_list grey_pages, grey_areas; int rememberedTableEntries; /* A list of areas used by weak objects. */ weak_area_tree *weak_areas; /* These are the pointer to the first allocated OOP since the last completed incremental GC pass, to the last low OOP considered by the incremental sweeper, to the first high OOP not considered by the incremental sweeper. */ OOP last_allocated_oop, last_swept_oop, next_oop_to_sweep; /* The active survivor space */ struct surv_space *active_half; /* The beginning and end of the area mmap-ed directly from the image. */ OOP *loaded_base, *loaded_end; /* The OOP flag corresponding to the active survivor space */ int active_flag; /* The OOP flag corresponding to the inactive survivor space. */ int live_flags; /* These hold onto the object incubator's state */ OOP *inc_base, *inc_ptr, *inc_end; /* Objects that are at least this big (in bytes) are allocated outside the main heap, hoping to provide more locality of reference between small objects. */ size_t big_object_threshold; /* If there is this much space used after a oldspace collection, we need to grow the object heap by _gst_space_grow_rate % next time we do a collection, so that the storage gets copied into the new, larger area. */ int grow_threshold_percent; /* Grow the object heap by this percentage when the amount of space used exceeds _gst_grow_threshold_percent. */ int space_grow_rate; /* Some statistics are computed using exponential smoothing. The smoothing factor is stored here. */ double factor; /* Here are the stats. */ int numScavenges, numGlobalGCs, numCompactions, numGrowths; int numOldOOPs, numFixedOOPs, numWeakOOPs; double timeBetweenScavenges, timeBetweenGlobalGCs, timeBetweenGrowths; double timeToScavenge, timeToCollect, timeToCompact; double reclaimedBytesPerScavenge, tenuredBytesPerScavenge, reclaimedBytesPerGlobalGC, reclaimedPercentPerScavenge; }; /* This is true to show a message whenever a GC happens. */ extern int _gst_gc_message ATTRIBUTE_HIDDEN; /* This is true in the middle of a GC. */ extern int _gst_gc_running ATTRIBUTE_HIDDEN; /* Finds and returns an instance of the class CLASS_OOP. Returns "nil" if there are no instances present. */ extern OOP _gst_find_an_instance (OOP class_oop) ATTRIBUTE_PURE ATTRIBUTE_HIDDEN; /* Execute a two-way become operation between OOP1 and OOP2. */ extern void _gst_swap_objects (OOP oop1, OOP oop2) ATTRIBUTE_HIDDEN; /* Flip the two survivor spaces. Starting from the root set, move eden objects to survivor space, tenuring objects when the top of the space is hit. Then tell the incremental sweeper not to sweep old objects. */ extern void _gst_scavenge (void) ATTRIBUTE_HIDDEN; /* Mark the old objects. Starting from the root set, recursively mark objects as reachable, and tell the incremental sweeper to sweep unreachable objects. Decide whether the heap should be compacted or even grown, so that allocating NEXT_ALLOCATION bytes leaves it empty enough. */ extern void _gst_global_gc (int next_allocation) ATTRIBUTE_HIDDEN; /* Mark, sweep & compact the old objects. */ extern void _gst_global_compact (void) ATTRIBUTE_HIDDEN; /* Sweep a bunch of old objects, return whether there are more. */ extern mst_Boolean _gst_incremental_gc_step (void) ATTRIBUTE_HIDDEN; /* The incremental collector has done its job. Update statistics, and if it was also sweeping old objects, make it consider all objects as alive. */ extern void _gst_finished_incremental_gc (void) ATTRIBUTE_HIDDEN; /* Finish the incremental sweep phase of the GC. */ extern void _gst_finish_incremental_gc (void) ATTRIBUTE_HIDDEN; /* Move all the object in survivor space to old space. */ extern void _gst_tenure_all_survivors () ATTRIBUTE_HIDDEN; /* Initialize the memory allocator. The memory space is allocated, and the various garbage collection flags are set to their initial values. */ extern void _gst_init_mem_default () ATTRIBUTE_HIDDEN; /* Initialize the memory allocator. The memory space is allocated, and the various garbage collection flags are set to the given values. */ extern void _gst_init_mem (size_t eden, size_t survivor, size_t old, size_t big_threshold, int grow_threshold_percent, int space_grow_rate) ATTRIBUTE_HIDDEN; /* Initialize an OOP table of SIZE bytes, trying at the given address if possible. Initially, all the OOPs are on the free list so that's just how we initialize them. We do as much initialization as we can, but we're called before classses are defined, so things that have definite classes must wait until the classes are defined. */ extern void _gst_init_oop_table (PTR address, size_t size) ATTRIBUTE_HIDDEN; /* Dump the entire contents of the OOP table. Mainly for debugging purposes. */ extern void _gst_dump_oop_table () ATTRIBUTE_HIDDEN; /* The almost-depth-first copying collector. If survivor space is full, tenuring of the oldest object is invoked (in a circular fashion). This function does not copy children of weak objects, for obvious reasons. */ extern void _gst_copy_an_oop (OOP oop) ATTRIBUTE_HIDDEN; /* Mark the objects pointed to by the list of pointers to OOPs at CUROOP (included) and finishing at ATENDOOP (excluded). */ extern void _gst_mark_oop_range (OOP * curOOP, OOP * atEndOOP) ATTRIBUTE_HIDDEN; /* Copy the objects pointed to by the list of pointers to OOPs at CUROOP (included) and finishing at ATENDOOP (excluded). */ extern void _gst_copy_oop_range (OOP * curOOP, OOP * atEndOOP) ATTRIBUTE_HIDDEN; /* Grey the pointers pointed to by the list of pointers to OOPs at FROM (included) and for SIZE bytes. */ extern void _gst_grey_oop_range (PTR from, size_t size) ATTRIBUTE_HIDDEN; /* Mark OOP and the pointers pointed by that. */ extern void _gst_mark_an_oop_internal (OOP oop) ATTRIBUTE_HIDDEN; /* Fully initialize the builtin objects, possible after the respective classes have been created. */ extern void _gst_init_builtin_objects_classes (void) ATTRIBUTE_HIDDEN; /* Create the registry of incubated objects. */ extern void _gst_inc_init_registry (void) ATTRIBUTE_HIDDEN; /* Grow the registry of incubated objects when it is full. */ extern void _gst_inc_grow_registry (void) ATTRIBUTE_HIDDEN; /* Allocate and return space for an object of SIZE bytes. This basically means moving the allocation pointer for the current space up by SIZE bytes, and, if there isn't enough space left, flipping the garbage collector after memory is compacted. The space is merely allocated; it is not initialized. The pointer to the object data is returned, the OOP is stored in P_OOP. */ extern gst_object _gst_alloc_obj (size_t size, OOP *p_oop) ATTRIBUTE_HIDDEN; /* Allocate and return space for an object of SIZE words, without creating an OOP. This is a special operation that is only needed at bootstrap time, so it does not care about garbage collection. */ extern gst_object _gst_alloc_words (size_t size) ATTRIBUTE_HIDDEN; /* Grows the allocated memory to SPACESIZE bytes, if it's not there already. the memory could not be allocated. Should be called after the sweep has occurred so that things are contiguous. Ensures that the OOP table pointers are fixed up to point to the new objects. */ extern void _gst_grow_memory_to (size_t size) ATTRIBUTE_HIDDEN; /* Grow the OOP table to NEWSIZE pointers and initialize the newly created pointers. */ extern mst_Boolean _gst_realloc_oop_table (size_t newSize) ATTRIBUTE_HIDDEN; /* Move OOP to oldspace. */ extern void _gst_tenure_oop (OOP oop) ATTRIBUTE_HIDDEN; /* Move OOP to fixedspace. */ extern void _gst_make_oop_fixed (OOP oop) ATTRIBUTE_HIDDEN; /* Make OOP a weak object. */ extern void _gst_make_oop_weak (OOP oop) ATTRIBUTE_HIDDEN; /* Make OOP a non-weak object. */ extern void _gst_make_oop_non_weak (OOP oop) ATTRIBUTE_HIDDEN; /* Clear the OOP data related to OOP */ extern void _gst_sweep_oop (OOP oop) ATTRIBUTE_HIDDEN; /* Set the fields of the given ObjectMemory object */ extern void _gst_update_object_memory_oop (OOP oop) ATTRIBUTE_HIDDEN; /* This variable represents information about the memory space. _gst_mem holds the required information: basically the pointer to the base and top of the space, and the pointers into it for allocation and copying. */ extern struct memory_space _gst_mem ATTRIBUTE_HIDDEN; #endif /* GST_OOP_H */ smalltalk-3.2.5/libgst/builtins.inl0000644000175000017500000025446712123404352014265 00000000000000/* C code produced by gperf version 3.0.1 */ /* Command-line: gperf -k'1-3,6,$' -r ../../libgst/builtins.gperf */ #if !((' ' == 32) && ('!' == 33) && ('"' == 34) && ('#' == 35) \ && ('%' == 37) && ('&' == 38) && ('\'' == 39) && ('(' == 40) \ && (')' == 41) && ('*' == 42) && ('+' == 43) && (',' == 44) \ && ('-' == 45) && ('.' == 46) && ('/' == 47) && ('0' == 48) \ && ('1' == 49) && ('2' == 50) && ('3' == 51) && ('4' == 52) \ && ('5' == 53) && ('6' == 54) && ('7' == 55) && ('8' == 56) \ && ('9' == 57) && (':' == 58) && (';' == 59) && ('<' == 60) \ && ('=' == 61) && ('>' == 62) && ('?' == 63) && ('A' == 65) \ && ('B' == 66) && ('C' == 67) && ('D' == 68) && ('E' == 69) \ && ('F' == 70) && ('G' == 71) && ('H' == 72) && ('I' == 73) \ && ('J' == 74) && ('K' == 75) && ('L' == 76) && ('M' == 77) \ && ('N' == 78) && ('O' == 79) && ('P' == 80) && ('Q' == 81) \ && ('R' == 82) && ('S' == 83) && ('T' == 84) && ('U' == 85) \ && ('V' == 86) && ('W' == 87) && ('X' == 88) && ('Y' == 89) \ && ('Z' == 90) && ('[' == 91) && ('\\' == 92) && (']' == 93) \ && ('^' == 94) && ('_' == 95) && ('a' == 97) && ('b' == 98) \ && ('c' == 99) && ('d' == 100) && ('e' == 101) && ('f' == 102) \ && ('g' == 103) && ('h' == 104) && ('i' == 105) && ('j' == 106) \ && ('k' == 107) && ('l' == 108) && ('m' == 109) && ('n' == 110) \ && ('o' == 111) && ('p' == 112) && ('q' == 113) && ('r' == 114) \ && ('s' == 115) && ('t' == 116) && ('u' == 117) && ('v' == 118) \ && ('w' == 119) && ('x' == 120) && ('y' == 121) && ('z' == 122) \ && ('{' == 123) && ('|' == 124) && ('}' == 125) && ('~' == 126)) /* The character set is not based on ISO-646. */ error "gperf generated tables don't work with this execution character set. Please report a bug to ." #endif #line 15 "../../libgst/builtins.gperf" /* Process with gperf -k'1-3,6,$' -r This table was generated starting from a 5 megabyte image including Blox (TK), the GTK bindings, the Browser (and hence the parser), TCP, NetClients, I18N, NumericalMethods, GDBM, MD5, and MySQL, starting from the output of this script | b | b := Bag new. CompiledMethod allInstances do: [ :each || n | each literals do: [ :each | each isSymbol ifTrue: [ b add: each ] ]. ]. Transcript nl. b sortedByCount from: 1 to: 226 keysAndValuesDo: [ :i :each | ('%1; NULL, %2, %3' bindWith: each value with: each value numArgs with: i + 31) displayNl ]! */ enum { TOTAL_KEYWORDS = 251, MIN_WORD_LENGTH = 1, MAX_WORD_LENGTH = 31, MIN_HASH_VALUE = 1, MAX_HASH_VALUE = 973 }; /* maximum key range = 973, duplicates = 0 */ #ifdef __GNUC__ __inline #else #ifdef __cplusplus inline #endif #endif static unsigned int _gst_hash_selector (str, len) register const char *str; register unsigned int len; { static unsigned short asso_values[] = { 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 240, 974, 974, 974, 3, 96, 47, 84, 974, 0, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 187, 974, 202, 137, 17, 974, 974, 148, 974, 223, 76, 124, 1, 974, 974, 83, 974, 183, 87, 974, 197, 4, 182, 974, 61, 242, 63, 974, 203, 974, 974, 974, 974, 974, 84, 974, 974, 974, 974, 81, 215, 244, 136, 158, 255, 255, 111, 28, 68, 1, 52, 2, 128, 206, 18, 10, 67, 142, 196, 24, 174, 173, 171, 37, 140, 974, 176, 974, 239, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974, 974 }; register int hval = len; switch (hval) { default: hval += asso_values[(unsigned char)str[5]]; /*FALLTHROUGH*/ case 5: case 4: case 3: hval += asso_values[(unsigned char)str[2]]; /*FALLTHROUGH*/ case 2: hval += asso_values[(unsigned char)str[1]]; /*FALLTHROUGH*/ case 1: hval += asso_values[(unsigned char)str[0]]; break; } return hval + asso_values[(unsigned char)str[len - 1]]; } struct _gst_builtin_selectors_names_t { char _gst_builtin_selectors_names_str1[sizeof("/")]; char _gst_builtin_selectors_names_str2[sizeof("//")]; char _gst_builtin_selectors_names_str7[sizeof("*")]; char _gst_builtin_selectors_names_str35[sizeof(">")]; char _gst_builtin_selectors_names_str75[sizeof("y")]; char _gst_builtin_selectors_names_str76[sizeof("pi")]; char _gst_builtin_selectors_names_str95[sizeof(",")]; char _gst_builtin_selectors_names_str120[sizeof("->")]; char _gst_builtin_selectors_names_str169[sizeof("-")]; char _gst_builtin_selectors_names_str192[sizeof("implementation")]; char _gst_builtin_selectors_names_str193[sizeof("+")]; char _gst_builtin_selectors_names_str234[sizeof("nl")]; char _gst_builtin_selectors_names_str236[sizeof("key")]; char _gst_builtin_selectors_names_str250[sizeof("asOop")]; char _gst_builtin_selectors_names_str254[sizeof("\\\\")]; char _gst_builtin_selectors_names_str275[sizeof("=")]; char _gst_builtin_selectors_names_str286[sizeof("random")]; char _gst_builtin_selectors_names_str293[sizeof(">=")]; char _gst_builtin_selectors_names_str297[sizeof("upTo:")]; char _gst_builtin_selectors_names_str307[sizeof("primSize")]; char _gst_builtin_selectors_names_str310[sizeof("ln")]; char _gst_builtin_selectors_names_str312[sizeof("printOn:")]; char _gst_builtin_selectors_names_str339[sizeof("peek")]; char _gst_builtin_selectors_names_str342[sizeof("keys")]; char _gst_builtin_selectors_names_str343[sizeof("x")]; char _gst_builtin_selectors_names_str349[sizeof("min:")]; char _gst_builtin_selectors_names_str353[sizeof("|")]; char _gst_builtin_selectors_names_str363[sizeof("skip:")]; char _gst_builtin_selectors_names_str368[sizeof("exp")]; char _gst_builtin_selectors_names_str373[sizeof("name")]; char _gst_builtin_selectors_names_str376[sizeof("upToEnd")]; char _gst_builtin_selectors_names_str380[sizeof("cr")]; char _gst_builtin_selectors_names_str389[sizeof("asFloatD")]; char _gst_builtin_selectors_names_str400[sizeof("days")]; char _gst_builtin_selectors_names_str403[sizeof("name:")]; char _gst_builtin_selectors_names_str404[sizeof("space")]; char _gst_builtin_selectors_names_str405[sizeof("<")]; char _gst_builtin_selectors_names_str413[sizeof("==")]; char _gst_builtin_selectors_names_str419[sizeof("sqrt")]; char _gst_builtin_selectors_names_str424[sizeof("isNil")]; char _gst_builtin_selectors_names_str433[sizeof("initialize")]; char _gst_builtin_selectors_names_str445[sizeof("max:")]; char _gst_builtin_selectors_names_str447[sizeof("flush")]; char _gst_builtin_selectors_names_str449[sizeof("hash")]; char _gst_builtin_selectors_names_str453[sizeof("width")]; char _gst_builtin_selectors_names_str460[sizeof("primitiveFailed")]; char _gst_builtin_selectors_names_str463[sizeof("initialize:")]; char _gst_builtin_selectors_names_str470[sizeof("value")]; char _gst_builtin_selectors_names_str472[sizeof("size")]; char _gst_builtin_selectors_names_str475[sizeof("last")]; char _gst_builtin_selectors_names_str476[sizeof("primitive")]; char _gst_builtin_selectors_names_str477[sizeof("squared")]; char _gst_builtin_selectors_names_str478[sizeof("<=")]; char _gst_builtin_selectors_names_str481[sizeof("&")]; char _gst_builtin_selectors_names_str482[sizeof("wait")]; char _gst_builtin_selectors_names_str485[sizeof("skipSeparators")]; char _gst_builtin_selectors_names_str487[sizeof("isInteger")]; char _gst_builtin_selectors_names_str489[sizeof("updateViews")]; char _gst_builtin_selectors_names_str493[sizeof("print:")]; char _gst_builtin_selectors_names_str494[sizeof("superspace")]; char _gst_builtin_selectors_names_str496[sizeof("asArray")]; char _gst_builtin_selectors_names_str503[sizeof("primAt:")]; char _gst_builtin_selectors_names_str505[sizeof("perform:")]; char _gst_builtin_selectors_names_str507[sizeof("primAt:put:")]; char _gst_builtin_selectors_names_str508[sizeof("asFloat")]; char _gst_builtin_selectors_names_str509[sizeof("copy")]; char _gst_builtin_selectors_names_str510[sizeof("properties")]; char _gst_builtin_selectors_names_str513[sizeof("truncated")]; char _gst_builtin_selectors_names_str514[sizeof("readStream")]; char _gst_builtin_selectors_names_str515[sizeof("~=")]; char _gst_builtin_selectors_names_str518[sizeof("step")]; char _gst_builtin_selectors_names_str521[sizeof("subclassResponsibility")]; char _gst_builtin_selectors_names_str523[sizeof("writeStream")]; char _gst_builtin_selectors_names_str524[sizeof("class")]; char _gst_builtin_selectors_names_str527[sizeof("keysAndValuesDo:")]; char _gst_builtin_selectors_names_str530[sizeof("position")]; char _gst_builtin_selectors_names_str532[sizeof("asOrderedCollection")]; char _gst_builtin_selectors_names_str533[sizeof("nameIn:")]; char _gst_builtin_selectors_names_str534[sizeof("isEmpty")]; char _gst_builtin_selectors_names_str535[sizeof("signal")]; char _gst_builtin_selectors_names_str540[sizeof("asInteger")]; char _gst_builtin_selectors_names_str544[sizeof("add:")]; char _gst_builtin_selectors_names_str545[sizeof("methodDictionary")]; char _gst_builtin_selectors_names_str551[sizeof("first")]; char _gst_builtin_selectors_names_str553[sizeof("beep")]; char _gst_builtin_selectors_names_str555[sizeof("signalError")]; char _gst_builtin_selectors_names_str556[sizeof("parent:")]; char _gst_builtin_selectors_names_str557[sizeof("sign")]; char _gst_builtin_selectors_names_str558[sizeof("numArgs")]; char _gst_builtin_selectors_names_str562[sizeof("invalidArgsError:")]; char _gst_builtin_selectors_names_str563[sizeof("origin")]; char _gst_builtin_selectors_names_str564[sizeof("parent")]; char _gst_builtin_selectors_names_str566[sizeof("stop")]; char _gst_builtin_selectors_names_str568[sizeof("reset")]; char _gst_builtin_selectors_names_str569[sizeof("readFrom:")]; char _gst_builtin_selectors_names_str571[sizeof("parentContext")]; char _gst_builtin_selectors_names_str573[sizeof("statements")]; char _gst_builtin_selectors_names_str575[sizeof("zero")]; char _gst_builtin_selectors_names_str576[sizeof("temporaries")]; char _gst_builtin_selectors_names_str579[sizeof("allSatisfy:")]; char _gst_builtin_selectors_names_str580[sizeof("superclass")]; char _gst_builtin_selectors_names_str581[sizeof("instanceClass")]; char _gst_builtin_selectors_names_str582[sizeof("state")]; char _gst_builtin_selectors_names_str583[sizeof("abs")]; char _gst_builtin_selectors_names_str586[sizeof("x:y:")]; char _gst_builtin_selectors_names_str589[sizeof("with:")]; char _gst_builtin_selectors_names_str590[sizeof("position:")]; char _gst_builtin_selectors_names_str591[sizeof("removeLast")]; char _gst_builtin_selectors_names_str595[sizeof("bindWith:")]; char _gst_builtin_selectors_names_str598[sizeof("body")]; char _gst_builtin_selectors_names_str599[sizeof("addAll:")]; char _gst_builtin_selectors_names_str600[sizeof("bindWith:with:")]; char _gst_builtin_selectors_names_str603[sizeof("allSubclassesDo:")]; char _gst_builtin_selectors_names_str605[sizeof("data:")]; char _gst_builtin_selectors_names_str611[sizeof("clientPI")]; char _gst_builtin_selectors_names_str616[sizeof("variance")]; char _gst_builtin_selectors_names_str617[sizeof("postCopy")]; char _gst_builtin_selectors_names_str619[sizeof("inject:into:")]; char _gst_builtin_selectors_names_str620[sizeof("start")]; char _gst_builtin_selectors_names_str621[sizeof("printString")]; char _gst_builtin_selectors_names_str623[sizeof("selector")]; char _gst_builtin_selectors_names_str625[sizeof("species")]; char _gst_builtin_selectors_names_str628[sizeof("narrow")]; char _gst_builtin_selectors_names_str630[sizeof("origin:corner:")]; char _gst_builtin_selectors_names_str634[sizeof("method")]; char _gst_builtin_selectors_names_str635[sizeof("new")]; char _gst_builtin_selectors_names_str637[sizeof("asLowercase")]; char _gst_builtin_selectors_names_str638[sizeof("rows:")]; char _gst_builtin_selectors_names_str640[sizeof("notNil")]; char _gst_builtin_selectors_names_str646[sizeof("login")]; char _gst_builtin_selectors_names_str647[sizeof("exists")]; char _gst_builtin_selectors_names_str648[sizeof("blox")]; char _gst_builtin_selectors_names_str650[sizeof("new:")]; char _gst_builtin_selectors_names_str654[sizeof("at:")]; char _gst_builtin_selectors_names_str655[sizeof("displayString")]; char _gst_builtin_selectors_names_str660[sizeof("evaluate")]; char _gst_builtin_selectors_names_str663[sizeof("bitShift:")]; char _gst_builtin_selectors_names_str665[sizeof("close")]; char _gst_builtin_selectors_names_str666[sizeof("current")]; char _gst_builtin_selectors_names_str667[sizeof("copyEmpty:")]; char _gst_builtin_selectors_names_str668[sizeof("completedSuccessfully")]; char _gst_builtin_selectors_names_str669[sizeof("generality")]; char _gst_builtin_selectors_names_str670[sizeof("javaAsInt")]; char _gst_builtin_selectors_names_str671[sizeof("signal:")]; char _gst_builtin_selectors_names_str672[sizeof("error:")]; char _gst_builtin_selectors_names_str673[sizeof("signalOn:")]; char _gst_builtin_selectors_names_str675[sizeof("count")]; char _gst_builtin_selectors_names_str677[sizeof("at:type:")]; char _gst_builtin_selectors_names_str678[sizeof("signalOn:what:")]; char _gst_builtin_selectors_names_str679[sizeof("nextPutAll:")]; char _gst_builtin_selectors_names_str680[sizeof("signalOn:mustBe:")]; char _gst_builtin_selectors_names_str682[sizeof("container")]; char _gst_builtin_selectors_names_str683[sizeof("signalOn:withIndex:")]; char _gst_builtin_selectors_names_str685[sizeof("isKindOf:")]; char _gst_builtin_selectors_names_str687[sizeof("value:")]; char _gst_builtin_selectors_names_str688[sizeof("yourself")]; char _gst_builtin_selectors_names_str690[sizeof("addLast:")]; char _gst_builtin_selectors_names_str692[sizeof("copyWith:")]; char _gst_builtin_selectors_names_str693[sizeof("value:value:")]; char _gst_builtin_selectors_names_str694[sizeof("source")]; char _gst_builtin_selectors_names_str695[sizeof("height")]; char _gst_builtin_selectors_names_str696[sizeof("retryRelationalOp:coercing:")]; char _gst_builtin_selectors_names_str697[sizeof("asVector")]; char _gst_builtin_selectors_names_str700[sizeof("bitXor:")]; char _gst_builtin_selectors_names_str701[sizeof("callInto:")]; char _gst_builtin_selectors_names_str703[sizeof("variable")]; char _gst_builtin_selectors_names_str705[sizeof("replaceFrom:to:with:startingAt:")]; char _gst_builtin_selectors_names_str709[sizeof("status")]; char _gst_builtin_selectors_names_str710[sizeof("asNumber")]; char _gst_builtin_selectors_names_str711[sizeof("on:")]; char _gst_builtin_selectors_names_str712[sizeof("arguments")]; char _gst_builtin_selectors_names_str714[sizeof("checkError")]; char _gst_builtin_selectors_names_str716[sizeof("errorContents:")]; char _gst_builtin_selectors_names_str718[sizeof("receiver")]; char _gst_builtin_selectors_names_str719[sizeof("~~")]; char _gst_builtin_selectors_names_str724[sizeof("width:height:")]; char _gst_builtin_selectors_names_str725[sizeof("text")]; char _gst_builtin_selectors_names_str728[sizeof("with:do:")]; char _gst_builtin_selectors_names_str729[sizeof("not")]; char _gst_builtin_selectors_names_str730[sizeof("javaAsLong")]; char _gst_builtin_selectors_names_str732[sizeof("includes:")]; char _gst_builtin_selectors_names_str734[sizeof("copyFrom:to:")]; char _gst_builtin_selectors_names_str735[sizeof("includesKey:")]; char _gst_builtin_selectors_names_str737[sizeof("asClass")]; char _gst_builtin_selectors_names_str738[sizeof("visitNode:")]; char _gst_builtin_selectors_names_str740[sizeof("asSymbol")]; char _gst_builtin_selectors_names_str741[sizeof("findIndexOrNil:")]; char _gst_builtin_selectors_names_str742[sizeof("select:")]; char _gst_builtin_selectors_names_str743[sizeof("return:")]; char _gst_builtin_selectors_names_str744[sizeof("selector:")]; char _gst_builtin_selectors_names_str745[sizeof("checkResponse")]; char _gst_builtin_selectors_names_str747[sizeof("asTkString")]; char _gst_builtin_selectors_names_str748[sizeof("thisContext")]; char _gst_builtin_selectors_names_str749[sizeof("body:")]; char _gst_builtin_selectors_names_str753[sizeof("background")]; char _gst_builtin_selectors_names_str755[sizeof("assert:")]; char _gst_builtin_selectors_names_str756[sizeof("asString")]; char _gst_builtin_selectors_names_str758[sizeof("arguments:")]; char _gst_builtin_selectors_names_str763[sizeof("selectors:receiver:argument:")]; char _gst_builtin_selectors_names_str767[sizeof("with:with:")]; char _gst_builtin_selectors_names_str768[sizeof("tclEval:")]; char _gst_builtin_selectors_names_str769[sizeof("bitAnd:")]; char _gst_builtin_selectors_names_str773[sizeof("tclEval:with:")]; char _gst_builtin_selectors_names_str776[sizeof("bind:to:of:parameters:")]; char _gst_builtin_selectors_names_str778[sizeof("tclEval:with:with:")]; char _gst_builtin_selectors_names_str779[sizeof("to:")]; char _gst_builtin_selectors_names_str780[sizeof("ensure:")]; char _gst_builtin_selectors_names_str781[sizeof("basicAt:")]; char _gst_builtin_selectors_names_str783[sizeof("tclEval:with:with:with:")]; char _gst_builtin_selectors_names_str785[sizeof("basicAt:put:")]; char _gst_builtin_selectors_names_str789[sizeof("should:")]; char _gst_builtin_selectors_names_str791[sizeof("accumulate:")]; char _gst_builtin_selectors_names_str793[sizeof("changeState:")]; char _gst_builtin_selectors_names_str798[sizeof("foregroundColor:")]; char _gst_builtin_selectors_names_str800[sizeof("nextToken")]; char _gst_builtin_selectors_names_str803[sizeof("atAllPut:")]; char _gst_builtin_selectors_names_str804[sizeof("default")]; char _gst_builtin_selectors_names_str807[sizeof("asSortedCollection")]; char _gst_builtin_selectors_names_str809[sizeof("shouldNotImplement")]; char _gst_builtin_selectors_names_str810[sizeof("backgroundColor:")]; char _gst_builtin_selectors_names_str811[sizeof("at:ifAbsent:")]; char _gst_builtin_selectors_names_str814[sizeof("at:ifAbsentPut:")]; char _gst_builtin_selectors_names_str816[sizeof("basicNew")]; char _gst_builtin_selectors_names_str819[sizeof("bitOr:")]; char _gst_builtin_selectors_names_str821[sizeof("create:")]; char _gst_builtin_selectors_names_str822[sizeof("asSeconds")]; char _gst_builtin_selectors_names_str826[sizeof("sizeof")]; char _gst_builtin_selectors_names_str833[sizeof("average")]; char _gst_builtin_selectors_names_str834[sizeof("activeProcess")]; char _gst_builtin_selectors_names_str836[sizeof("coefficients:")]; char _gst_builtin_selectors_names_str839[sizeof("tclResult")]; char _gst_builtin_selectors_names_str842[sizeof("negated")]; char _gst_builtin_selectors_names_str846[sizeof("at:ifPresent:")]; char _gst_builtin_selectors_names_str847[sizeof("basicSize")]; char _gst_builtin_selectors_names_str852[sizeof("bytecodeAt:")]; char _gst_builtin_selectors_names_str854[sizeof("at:put:")]; char _gst_builtin_selectors_names_str856[sizeof("contents")]; char _gst_builtin_selectors_names_str873[sizeof("environment")]; char _gst_builtin_selectors_names_str885[sizeof("fromSeconds:")]; char _gst_builtin_selectors_names_str887[sizeof("detect:ifNone:")]; char _gst_builtin_selectors_names_str895[sizeof("executeAndWait:arguments:")]; char _gst_builtin_selectors_names_str901[sizeof("on:do:")]; char _gst_builtin_selectors_names_str920[sizeof("getResponse")]; char _gst_builtin_selectors_names_str924[sizeof("store:")]; char _gst_builtin_selectors_names_str926[sizeof("between:and:")]; char _gst_builtin_selectors_names_str941[sizeof("collect:")]; char _gst_builtin_selectors_names_str946[sizeof("beConsistent")]; char _gst_builtin_selectors_names_str960[sizeof("coerce:")]; char _gst_builtin_selectors_names_str967[sizeof("connected")]; char _gst_builtin_selectors_names_str969[sizeof("become:")]; char _gst_builtin_selectors_names_str973[sizeof("connectIfClosed")]; }; static struct _gst_builtin_selectors_names_t _gst_builtin_selectors_names_contents = { "/", "//", "*", ">", "y", "pi", ",", "->", "-", "implementation", "+", "nl", "key", "asOop", "\\\\", "=", "random", ">=", "upTo:", "primSize", "ln", "printOn:", "peek", "keys", "x", "min:", "|", "skip:", "exp", "name", "upToEnd", "cr", "asFloatD", "days", "name:", "space", "<", "==", "sqrt", "isNil", "initialize", "max:", "flush", "hash", "width", "primitiveFailed", "initialize:", "value", "size", "last", "primitive", "squared", "<=", "&", "wait", "skipSeparators", "isInteger", "updateViews", "print:", "superspace", "asArray", "primAt:", "perform:", "primAt:put:", "asFloat", "copy", "properties", "truncated", "readStream", "~=", "step", "subclassResponsibility", "writeStream", "class", "keysAndValuesDo:", "position", "asOrderedCollection", "nameIn:", "isEmpty", "signal", "asInteger", "add:", "methodDictionary", "first", "beep", "signalError", "parent:", "sign", "numArgs", "invalidArgsError:", "origin", "parent", "stop", "reset", "readFrom:", "parentContext", "statements", "zero", "temporaries", "allSatisfy:", "superclass", "instanceClass", "state", "abs", "x:y:", "with:", "position:", "removeLast", "bindWith:", "body", "addAll:", "bindWith:with:", "allSubclassesDo:", "data:", "clientPI", "variance", "postCopy", "inject:into:", "start", "printString", "selector", "species", "narrow", "origin:corner:", "method", "new", "asLowercase", "rows:", "notNil", "login", "exists", "blox", "new:", "at:", "displayString", "evaluate", "bitShift:", "close", "current", "copyEmpty:", "completedSuccessfully", "generality", "javaAsInt", "signal:", "error:", "signalOn:", "count", "at:type:", "signalOn:what:", "nextPutAll:", "signalOn:mustBe:", "container", "signalOn:withIndex:", "isKindOf:", "value:", "yourself", "addLast:", "copyWith:", "value:value:", "source", "height", "retryRelationalOp:coercing:", "asVector", "bitXor:", "callInto:", "variable", "replaceFrom:to:with:startingAt:", "status", "asNumber", "on:", "arguments", "checkError", "errorContents:", "receiver", "~~", "width:height:", "text", "with:do:", "not", "javaAsLong", "includes:", "copyFrom:to:", "includesKey:", "asClass", "visitNode:", "asSymbol", "findIndexOrNil:", "select:", "return:", "selector:", "checkResponse", "asTkString", "thisContext", "body:", "background", "assert:", "asString", "arguments:", "selectors:receiver:argument:", "with:with:", "tclEval:", "bitAnd:", "tclEval:with:", "bind:to:of:parameters:", "tclEval:with:with:", "to:", "ensure:", "basicAt:", "tclEval:with:with:with:", "basicAt:put:", "should:", "accumulate:", "changeState:", "foregroundColor:", "nextToken", "atAllPut:", "default", "asSortedCollection", "shouldNotImplement", "backgroundColor:", "at:ifAbsent:", "at:ifAbsentPut:", "basicNew", "bitOr:", "create:", "asSeconds", "sizeof", "average", "activeProcess", "coefficients:", "tclResult", "negated", "at:ifPresent:", "basicSize", "bytecodeAt:", "at:put:", "contents", "environment", "fromSeconds:", "detect:ifNone:", "executeAndWait:arguments:", "on:do:", "getResponse", "store:", "between:and:", "collect:", "beConsistent", "coerce:", "connected", "become:", "connectIfClosed" }; #define _gst_builtin_selectors_names ((const char *) &_gst_builtin_selectors_names_contents) static unsigned char lengthtable[] = { 0, 1, 2, 0, 0, 0, 0, 1, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 1, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 1, 2, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 1, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 2, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 1, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 14, 1, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 2, 0, 3, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 5, 0, 0, 0, 2, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 1, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 6, 0, 0, 0, 0, 0, 0, 2, 0, 0, 0, 5, 0, 0, 0, 0, 0, 0, 0, 0, 0, 8, 0, 0, 2, 0, 8, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 4, 0, 0, 4, 1, 0, 0, 0, 0, 0, 4, 0, 0, 0, 1, 0, 0, 0, 0, 0, 0, 0, 0, 0, 5, 0, 0, 0, 0, 3, 0, 0, 0, 0, 4, 0, 0, 7, 0, 0, 0, 2, 0, 0, 0, 0, 0, 0, 0, 0, 8, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 4, 0, 0, 5, 5, 1, 0, 0, 0, 0, 0, 0, 0, 2, 0, 0, 0, 0, 0, 4, 0, 0, 0, 0, 5, 0, 0, 0, 0, 0, 0, 0, 0, 10, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 4, 0, 5, 0, 4, 0, 0, 0, 5, 0, 0, 0, 0, 0, 0, 15, 0, 0, 11, 0, 0, 0, 0, 0, 0, 5, 0, 4, 0, 0, 4, 9, 7, 2, 0, 0, 1, 4, 0, 0, 14, 0, 9, 0, 11, 0, 0, 0, 6, 10, 0, 7, 0, 0, 0, 0, 0, 0, 7, 0, 8, 0, 11, 7, 4, 10, 0, 0, 9, 10, 2, 0, 0, 4, 0, 0, 22, 0, 11, 5, 0, 0, 16, 0, 0, 8, 0, 19, 7, 7, 6, 0, 0, 0, 0, 9, 0, 0, 0, 4, 16, 0, 0, 0, 0, 0, 5, 0, 4, 0, 11, 7, 4, 7, 0, 0, 0, 17, 6, 6, 0, 4, 0, 5, 9, 0, 13, 0, 10, 0, 4, 11, 0, 0, 11, 10, 13, 5, 3, 0, 0, 4, 0, 0, 5, 9, 10, 0, 0, 0, 9, 0, 0, 4, 7, 14, 0, 0, 16, 0, 5, 0, 0, 0, 0, 0, 8, 0, 0, 0, 0, 8, 8, 0, 12, 5, 11, 0, 8, 0, 7, 0, 0, 6, 0, 14, 0, 0, 0, 6, 3, 0, 11, 5, 0, 6, 0, 0, 0, 0, 0, 5, 6, 4, 0, 4, 0, 0, 0, 3, 13, 0, 0, 0, 0, 8, 0, 0, 9, 0, 5, 7, 10, 21, 10, 9, 7, 6, 9, 0, 5, 0, 8, 14, 11, 16, 0, 9, 19, 0, 9, 0, 6, 8, 0, 8, 0, 9, 12, 6, 6, 27, 8, 0, 0, 7, 9, 0, 8, 0, 31, 0, 0, 0, 6, 8, 3, 9, 0, 10, 0, 14, 0, 8, 2, 0, 0, 0, 0, 13, 4, 0, 0, 8, 3, 10, 0, 9, 0, 12, 12, 0, 7, 10, 0, 8, 15, 7, 7, 9, 13, 0, 10, 11, 5, 0, 0, 0, 10, 0, 7, 8, 0, 10, 0, 0, 0, 0, 28, 0, 0, 0, 10, 8, 7, 0, 0, 0, 13, 0, 0, 22, 0, 18, 3, 7, 8, 0, 23, 0, 12, 0, 0, 0, 7, 0, 11, 0, 12, 0, 0, 0, 0, 16, 0, 9, 0, 0, 9, 7, 0, 0, 18, 0, 18, 16, 12, 0, 0, 15, 0, 8, 0, 0, 6, 0, 7, 9, 0, 0, 0, 6, 0, 0, 0, 0, 0, 0, 7, 13, 0, 13, 0, 0, 9, 0, 0, 7, 0, 0, 0, 13, 9, 0, 0, 0, 0, 11, 0, 7, 0, 8, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 11, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 12, 0, 14, 0, 0, 0, 0, 0, 0, 0, 25, 0, 0, 0, 0, 0, 6, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 11, 0, 0, 0, 6, 0, 12, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 8, 0, 0, 0, 0, 12, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 7, 0, 0, 0, 0, 0, 0, 9, 0, 7, 0, 0, 0, 15 }; static struct builtin_selector _gst_builtin_selectors_hash[] = { {-1,NULL,-1,-1}, #line 48 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str1, NULL, 1, DIVIDE_SPECIAL}, #line 52 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str2, NULL, 1, INTEGER_DIVIDE_SPECIAL}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, #line 47 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str7, NULL, 1, TIMES_SPECIAL}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, #line 42 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str35, NULL, 1, GREATER_THAN_SPECIAL}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, #line 114 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str75, NULL, 0, 80}, #line 189 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str76, NULL, 0, 155}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, #line 72 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str95, NULL, 1, 38}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, #line 120 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str120, NULL, 1, 86}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, #line 40 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str169, NULL, 1, MINUS_SPECIAL}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, #line 172 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str192, NULL, 0, 138}, #line 39 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str193, NULL, 1, PLUS_SPECIAL}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, #line 76 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str234, NULL, 0, 42}, {-1,NULL,-1,-1}, #line 88 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str236, NULL, 0, 54}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, #line 212 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str250, NULL, 0, 178}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, #line 49 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str254, NULL, 1, REMAINDER_SPECIAL}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, #line 45 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str275, NULL, 1, EQUAL_SPECIAL}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, #line 238 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str286, NULL, 0, 204}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, #line 44 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str293, NULL, 1, GREATER_EQUAL_SPECIAL}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, #line 175 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str297, NULL, 1, 141}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, #line 162 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str307, NULL, 0, 128}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, #line 171 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str310, NULL, 0, 137}, {-1,NULL,-1,-1}, #line 139 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str312, NULL, 1, 105}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, #line 177 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str339, NULL, 0, 143}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, #line 236 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str342, NULL, 0, 202}, #line 112 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str343, NULL, 0, 78}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, #line 205 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str349, NULL, 1, 171}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, #line 186 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str353, NULL, 1, 152}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, #line 272 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str363, NULL, 1, 238}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, #line 183 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str368, NULL, 0, 149}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, #line 79 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str373, NULL, 0, 45}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, #line 277 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str376, NULL, 0, 243}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, #line 109 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str380, NULL, 0, 75}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, #line 159 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str389, NULL, 0, 125}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, #line 273 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str400, NULL, 0, 239}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, #line 144 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str403, NULL, 1, 110}, #line 117 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str404, NULL, 0, 83}, #line 41 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str405, NULL, 1, LESS_THAN_SPECIAL}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, #line 63 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str413, NULL, 1, SAME_OBJECT_SPECIAL}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, #line 146 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str419, NULL, 0, 112}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, #line 59 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str424, NULL, 0, IS_NIL_SPECIAL}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, #line 103 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str433, NULL, 0, 69}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, #line 137 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str445, NULL, 1, 103}, {-1,NULL,-1,-1}, #line 157 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str447, NULL, 0, 123}, {-1,NULL,-1,-1}, #line 145 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str449, NULL, 0, 111}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, #line 206 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str453, NULL, 0, 172}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, #line 106 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str460, NULL, 0, 72}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, #line 107 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str463, NULL, 1, 73}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, #line 61 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str470, NULL, 0, VALUE_SPECIAL}, {-1,NULL,-1,-1}, #line 57 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str472, NULL, 0, SIZE_SPECIAL}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, #line 102 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str475, NULL, 0, 68}, #line 261 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str476, NULL, 0, 227}, #line 132 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str477, NULL, 0, 98}, #line 43 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str478, NULL, 1, LESS_EQUAL_SPECIAL}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, #line 276 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str481, NULL, 1, 242}, #line 233 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str482, NULL, 0, 199}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, #line 266 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str485, NULL, 0, 232}, {-1,NULL,-1,-1}, #line 143 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str487, NULL, 0, 109}, {-1,NULL,-1,-1}, #line 263 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str489, NULL, 0, 229}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, #line 101 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str493, NULL, 1, 67}, #line 240 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str494, NULL, 0, 206}, {-1,NULL,-1,-1}, #line 218 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str496, NULL, 0, 184}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, #line 148 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str503, NULL, 1, 114}, {-1,NULL,-1,-1}, #line 242 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str505, NULL, 1, 208}, {-1,NULL,-1,-1}, #line 247 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str507, NULL, 2, 213}, #line 237 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str508, NULL, 0, 203}, #line 99 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str509, NULL, 0, 65}, #line 81 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str510, NULL, 0, 47}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, #line 195 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str513, NULL, 0, 161}, #line 113 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str514, NULL, 0, 79}, #line 46 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str515, NULL, 1, NOT_EQUAL_SPECIAL}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, #line 125 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str518, NULL, 0, 91}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, #line 74 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str521, NULL, 0, 40}, {-1,NULL,-1,-1}, #line 191 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str523, NULL, 0, 157}, #line 58 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str524, NULL, 0, CLASS_SPECIAL}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, #line 138 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str527, NULL, 1, 104}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, #line 150 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str530, NULL, 0, 116}, {-1,NULL,-1,-1}, #line 235 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str532, NULL, 0, 201}, #line 255 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str533, NULL, 1, 221}, #line 80 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str534, NULL, 0, 46}, #line 126 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str535, NULL, 0, 92}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, #line 116 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str540, NULL, 0, 82}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, #line 75 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str544, NULL, 1, 41}, #line 214 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str545, NULL, 0, 180}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, #line 84 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str551, NULL, 0, 50}, {-1,NULL,-1,-1}, #line 147 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str553, NULL, 0, 113}, {-1,NULL,-1,-1}, #line 257 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str555, NULL, 0, 223}, #line 222 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str556, NULL, 1, 188}, #line 229 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str557, NULL, 0, 195}, #line 121 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str558, NULL, 0, 87}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, #line 254 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str562, NULL, 1, 220}, #line 239 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str563, NULL, 0, 205}, #line 127 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str564, NULL, 0, 93}, {-1,NULL,-1,-1}, #line 241 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str566, NULL, 0, 207}, {-1,NULL,-1,-1}, #line 165 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str568, NULL, 0, 131}, #line 154 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str569, NULL, 1, 120}, {-1,NULL,-1,-1}, #line 207 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str571, NULL, 0, 173}, {-1,NULL,-1,-1}, #line 184 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str573, NULL, 0, 150}, {-1,NULL,-1,-1}, #line 209 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str575, NULL, 0, 175}, #line 211 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str576, NULL, 0, 177}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, #line 249 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str579, NULL, 1, 215}, #line 192 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str580, NULL, 0, 158}, #line 234 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str581, NULL, 0, 200}, #line 194 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str582, NULL, 0, 160}, #line 90 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str583, NULL, 0, 56}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, #line 179 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str586, NULL, 2, 145}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, #line 98 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str589, NULL, 1, 64}, #line 250 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str590, NULL, 1, 216}, #line 208 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str591, NULL, 0, 174}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, #line 269 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str595, NULL, 1, 235}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, #line 136 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str598, NULL, 0, 102}, #line 142 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str599, NULL, 1, 108}, #line 210 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str600, NULL, 2, 176}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, #line 256 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str603, NULL, 1, 222}, {-1,NULL,-1,-1}, #line 245 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str605, NULL, 1, 211}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, #line 156 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str611, NULL, 0, 122}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, #line 230 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str616, NULL, 0, 196}, #line 153 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str617, NULL, 0, 119}, {-1,NULL,-1,-1}, #line 196 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str619, NULL, 2, 162}, #line 167 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str620, NULL, 0, 133}, #line 77 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str621, NULL, 0, 43}, {-1,NULL,-1,-1}, #line 128 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str623, NULL, 0, 94}, {-1,NULL,-1,-1}, #line 123 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str625, NULL, 0, 89}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, #line 69 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str628, NULL, 0, 35}, {-1,NULL,-1,-1}, #line 267 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str630, NULL, 2, 233}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, #line 248 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str634, NULL, 0, 214}, #line 118 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str635, NULL, 0, 84}, {-1,NULL,-1,-1}, #line 217 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str637, NULL, 0, 183}, #line 181 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str638, NULL, 1, 147}, {-1,NULL,-1,-1}, #line 60 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str640, NULL, 0, NOT_NIL_SPECIAL}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, #line 244 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str646, NULL, 0, 210}, #line 219 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str647, NULL, 0, 185}, #line 124 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str648, NULL, 0, 90}, {-1,NULL,-1,-1}, #line 66 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str650, NULL, 1, NEW_COLON_SPECIAL}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, #line 55 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str654, NULL, 1, AT_SPECIAL}, #line 265 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str655, NULL, 0, 231}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, #line 163 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str660, NULL, 0, 129}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, #line 51 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str663, NULL, 1, BIT_SHIFT_SPECIAL}, {-1,NULL,-1,-1}, #line 94 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str665, NULL, 0, 60}, #line 198 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str666, NULL, 0, 164}, #line 166 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str667, NULL, 1, 132}, #line 190 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str668, NULL, 0, 156}, #line 133 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str669, NULL, 0, 99}, #line 64 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str670, NULL, 0, JAVA_AS_INT_SPECIAL}, #line 152 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str671, NULL, 1, 118}, #line 83 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str672, NULL, 1, 49}, #line 168 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str673, NULL, 1, 134}, {-1,NULL,-1,-1}, #line 216 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str675, NULL, 0, 182}, {-1,NULL,-1,-1}, #line 271 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str677, NULL, 2, 237}, #line 220 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str678, NULL, 2, 186}, #line 70 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str679, NULL, 1, 36}, #line 134 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str680, NULL, 2, 100}, {-1,NULL,-1,-1}, #line 82 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str682, NULL, 0, 48}, #line 224 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str683, NULL, 2, 190}, {-1,NULL,-1,-1}, #line 140 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str685, NULL, 1, 106}, {-1,NULL,-1,-1}, #line 62 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str687, NULL, 1, VALUE_COLON_SPECIAL}, #line 71 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str688, NULL, 0, 37}, {-1,NULL,-1,-1}, #line 131 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str690, NULL, 1, 97}, {-1,NULL,-1,-1}, #line 283 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str692, NULL, 1, 249}, #line 158 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str693, NULL, 2, 124}, #line 259 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str694, NULL, 0, 225}, #line 258 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str695, NULL, 0, 224}, #line 200 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str696, NULL, 2, 166}, #line 231 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str697, NULL, 0, 197}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, #line 50 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str700, NULL, 1, BIT_XOR_SPECIAL}, #line 68 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str701, NULL, 1, 34}, {-1,NULL,-1,-1}, #line 278 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str703, NULL, 0, 244}, {-1,NULL,-1,-1}, #line 197 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str705, NULL, 4, 163}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, #line 285 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str709, NULL, 0, 251}, #line 260 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str710, NULL, 0, 226}, #line 73 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str711, NULL, 1, 39}, #line 111 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str712, NULL, 0, 77}, {-1,NULL,-1,-1}, #line 203 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str714, NULL, 0, 169}, {-1,NULL,-1,-1}, #line 264 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str716, NULL, 1, 230}, {-1,NULL,-1,-1}, #line 176 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str718, NULL, 0, 142}, #line 227 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str719, NULL, 1, 193}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, #line 213 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str724, NULL, 2, 179}, #line 182 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str725, NULL, 0, 148}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, #line 280 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str728, NULL, 2, 246}, #line 93 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str729, NULL, 0, 59}, #line 65 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str730, NULL, 0, JAVA_AS_LONG_SPECIAL}, {-1,NULL,-1,-1}, #line 95 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str732, NULL, 1, 61}, {-1,NULL,-1,-1}, #line 100 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str734, NULL, 2, 66}, #line 188 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str735, NULL, 1, 154}, {-1,NULL,-1,-1}, #line 170 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str737, NULL, 0, 136}, #line 141 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str738, NULL, 1, 107}, {-1,NULL,-1,-1}, #line 97 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str740, NULL, 0, 63}, #line 281 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str741, NULL, 1, 247}, #line 221 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str742, NULL, 1, 187}, #line 226 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str743, NULL, 1, 192}, #line 223 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str744, NULL, 1, 189}, #line 173 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str745, NULL, 0, 139}, {-1,NULL,-1,-1}, #line 89 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str747, NULL, 0, 55}, #line 67 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str748, NULL, 0, THIS_CONTEXT_SPECIAL}, #line 185 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str749, NULL, 1, 151}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, #line 284 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str753, NULL, 0, 250}, {-1,NULL,-1,-1}, #line 105 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str755, NULL, 1, 71}, #line 108 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str756, NULL, 0, 74}, {-1,NULL,-1,-1}, #line 193 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str758, NULL, 1, 159}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, #line 286 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str763, NULL, 3, 252}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, #line 122 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str767, NULL, 2, 88}, #line 85 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str768, NULL, 1, 51}, #line 53 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str769, NULL, 1, BIT_AND_SPECIAL}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, #line 274 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str773, NULL, 2, 240}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, #line 225 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str776, NULL, 4, 191}, {-1,NULL,-1,-1}, #line 104 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str778, NULL, 3, 70}, #line 130 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str779, NULL, 1, 96}, #line 135 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str780, NULL, 1, 101}, #line 169 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str781, NULL, 1, 135}, {-1,NULL,-1,-1}, #line 115 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str783, NULL, 4, 81}, {-1,NULL,-1,-1}, #line 161 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str785, NULL, 2, 127}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, #line 110 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str789, NULL, 1, 76}, {-1,NULL,-1,-1}, #line 215 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str791, NULL, 1, 181}, {-1,NULL,-1,-1}, #line 228 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str793, NULL, 1, 194}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, #line 180 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str798, NULL, 1, 146}, {-1,NULL,-1,-1}, #line 246 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str800, NULL, 0, 212}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, #line 252 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str803, NULL, 1, 218}, #line 251 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str804, NULL, 0, 217}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, #line 253 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str807, NULL, 0, 219}, {-1,NULL,-1,-1}, #line 119 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str809, NULL, 0, 85}, #line 243 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str810, NULL, 1, 209}, #line 96 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str811, NULL, 2, 62}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, #line 151 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str814, NULL, 2, 117}, {-1,NULL,-1,-1}, #line 91 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str816, NULL, 0, 57}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, #line 54 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str819, NULL, 1, BIT_OR_SPECIAL}, {-1,NULL,-1,-1}, #line 287 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str821, NULL, 1, 253}, #line 282 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str822, NULL, 0, 248}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, #line 187 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str826, NULL, 0, 153}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, #line 174 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str833, NULL, 0, 140}, #line 268 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str834, NULL, 0, 234}, {-1,NULL,-1,-1}, #line 155 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str836, NULL, 1, 121}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, #line 87 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str839, NULL, 0, 53}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, #line 92 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str842, NULL, 0, 58}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, #line 129 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str846, NULL, 2, 95}, #line 178 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str847, NULL, 0, 144}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, #line 289 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str852, NULL, 1, 255}, {-1,NULL,-1,-1}, #line 56 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str854, NULL, 2, AT_PUT_SPECIAL}, {-1,NULL,-1,-1}, #line 78 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str856, NULL, 0, 44}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, #line 149 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str873, NULL, 0, 115}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, #line 275 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str885, NULL, 1, 241}, {-1,NULL,-1,-1}, #line 202 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str887, NULL, 2, 168}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, #line 204 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str895, NULL, 2, 170}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, #line 160 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str901, NULL, 2, 126}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, #line 232 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str920, NULL, 0, 198}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, #line 262 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str924, NULL, 1, 228}, {-1,NULL,-1,-1}, #line 199 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str926, NULL, 2, 165}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, #line 86 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str941, NULL, 1, 52}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, #line 270 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str946, NULL, 0, 236}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, #line 288 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str960, NULL, 1, 254}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, #line 164 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str967, NULL, 0, 130}, {-1,NULL,-1,-1}, #line 279 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str969, NULL, 1, 245}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, {-1,NULL,-1,-1}, #line 201 "../../libgst/builtins.gperf" {(int)(long)&((struct _gst_builtin_selectors_names_t *)0)->_gst_builtin_selectors_names_str973, NULL, 0, 167} }; #ifdef __GNUC__ __inline #endif struct builtin_selector * _gst_lookup_builtin_selector (str, len) register const char *str; register unsigned int len; { if (len <= MAX_WORD_LENGTH && len >= MIN_WORD_LENGTH) { register int key = _gst_hash_selector (str, len); if (key <= MAX_HASH_VALUE && key >= 0) if (len == lengthtable[key]) { register const char *s = _gst_builtin_selectors_hash[key].offset + _gst_builtin_selectors_names; if (*str == *s && !memcmp (str + 1, s + 1, len - 1)) return &_gst_builtin_selectors_hash[key]; } } return 0; } smalltalk-3.2.5/libgst/genpr-parse.h0000644000175000017500000000450212130455565014315 00000000000000/* A Bison parser, made by GNU Bison 2.5. */ /* Bison interface for Yacc-like parsers in C Copyright (C) 1984, 1989-1990, 2000-2011 Free Software Foundation, Inc. This program is free software: you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation, either version 3 of the License, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program. If not, see . */ /* As a special exception, you may create a larger work that contains part or all of the Bison parser skeleton and distribute that work under terms of your choice, so long as that work isn't itself a parser generator using the skeleton or a modified version thereof as a parser skeleton. Alternatively, if you modify or redistribute the parser skeleton itself, you may (at your option) remove this special exception, which will cause the skeleton and the resulting Bison output files to be licensed under the GNU General Public License without this special exception. This special exception was added by the Free Software Foundation in version 2.2 of Bison. */ /* Tokens. */ #ifndef YYTOKENTYPE # define YYTOKENTYPE /* Put the tokens into the symbol table, so that GDB and other debuggers know about them. */ enum yytokentype { PRIMITIVE = 258, PRIM_ID = 259, NUMBER = 260, ID = 261, LITERAL = 262, WSPACE = 263 }; #endif /* Tokens. */ #define PRIMITIVE 258 #define PRIM_ID 259 #define NUMBER 260 #define ID 261 #define LITERAL 262 #define WSPACE 263 #if ! defined YYSTYPE && ! defined YYSTYPE_IS_DECLARED typedef union YYSTYPE { /* Line 2068 of yacc.c */ #line 118 "genpr-parse.y" Filament *fil; char *text; int id; /* Line 2068 of yacc.c */ #line 74 "genpr-parse.h" } YYSTYPE; # define YYSTYPE_IS_TRIVIAL 1 # define yystype YYSTYPE /* obsolescent; will be withdrawn */ # define YYSTYPE_IS_DECLARED 1 #endif extern YYSTYPE yylval; smalltalk-3.2.5/libgst/security.h0000644000175000017500000000544012130343734013735 00000000000000/******************************** -*- C -*- **************************** * * Security-related routine definitions. * * ***********************************************************************/ /*********************************************************************** * * Copyright 2003, 2006 Free Software Foundation, Inc. * Written by Paolo Bonzini. * * This file is part of GNU Smalltalk. * * GNU Smalltalk is free software; you can redistribute it and/or modify it * under the terms of the GNU General Public License as published by the Free * Software Foundation; either version 2, or (at your option) any later * version. * * Linking GNU Smalltalk statically or dynamically with other modules is * making a combined work based on GNU Smalltalk. Thus, the terms and * conditions of the GNU General Public License cover the whole * combination. * * In addition, as a special exception, the Free Software Foundation * give you permission to combine GNU Smalltalk with free software * programs or libraries that are released under the GNU LGPL and with * independent programs running under the GNU Smalltalk virtual machine. * * You may copy and distribute such a system following the terms of the * GNU GPL for GNU Smalltalk and the licenses of the other code * concerned, provided that you include the source code of that other * code when and as the GNU GPL requires distribution of source code. * * Note that people who make modified versions of GNU Smalltalk are not * obligated to grant this special exception for their modified * versions; it is their choice whether to do so. The GNU General * Public License gives permission to release a modified version without * this exception; this exception also makes it possible to release a * modified version which carries forward this exception. * * GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or * FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for * more details. * * You should have received a copy of the GNU General Public License along with * GNU Smalltalk; see the file COPYING. If not, write to the Free Software * Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * ***********************************************************************/ #ifndef GST_SECURITY_H #define GST_SECURITY_H typedef struct gst_permission { OBJ_HEADER; OOP name; OOP actions; OOP target; OOP positive; } *gst_permission; typedef struct gst_security_policy { OBJ_HEADER; OOP dictionary; OOP owner; } *gst_security_policy; mst_Boolean _gst_check_permission (OOP contextOOP, OOP nameOOP, OOP targetOOP, OOP actionOOP) ATTRIBUTE_HIDDEN; #endif /* GST_SECURITY_H */ smalltalk-3.2.5/libgst/gstpub.h0000644000175000017500000003063312130343734013374 00000000000000/******************************** -*- C -*- **************************** * * Public definitions for extensions to Smalltalk. * * ***********************************************************************/ /*********************************************************************** * * Copyright 1988,89,90,91,92,94,95,99,2000,2001,2002,2006,2008,2009 * Free Software Foundation, Inc. * Written by Steve Byrne and Paolo Bonzini. * * This file is part of GNU Smalltalk. * * GNU Smalltalk is free software; you can redistribute it and/or modify it * under the terms of the GNU General Public License as published by the Free * Software Foundation; either version 2, or (at your option) any later * version. * * Linking GNU Smalltalk statically or dynamically with other modules is * making a combined work based on GNU Smalltalk. Thus, the terms and * conditions of the GNU General Public License cover the whole * combination. * * In addition, as a special exception, the Free Software Foundation * give you permission to combine GNU Smalltalk with free software * programs or libraries that are released under the GNU LGPL and with * independent programs running under the GNU Smalltalk virtual machine. * * You may copy and distribute such a system following the terms of the * GNU GPL for GNU Smalltalk and the licenses of the other code * concerned, provided that you include the source code of that other * code when and as the GNU GPL requires distribution of source code. * * Note that people who make modified versions of GNU Smalltalk are not * obligated to grant this special exception for their modified * versions; it is their choice whether to do so. The GNU General * Public License gives permission to release a modified version without * this exception; this exception also makes it possible to release a * modified version which carries forward this exception. * * GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or * FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for * more details. * * You should have received a copy of the GNU General Public License along with * GNU Smalltalk; see the file COPYING. If not, write to the Free Software * Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * ***********************************************************************/ #ifndef GST_GSTPUB_H #define GST_GSTPUB_H /* cfront 1.2 defines "c_plusplus" instead of "__cplusplus" */ #if defined(c_plusplus) && !defined(__cplusplus) #define __cplusplus c_plusplus #endif #ifdef __cplusplus #include #include extern "C" { #else #include #include #endif #include "gst.h" typedef struct VMProxy { OOP nilOOP, trueOOP, falseOOP; OOP (*msgSend) (OOP receiver, OOP selector, ...); OOP (*vmsgSend) (OOP receiver, OOP selector, OOP * args); OOP (*nvmsgSend) (OOP receiver, OOP selector, OOP * args, int nargs); OOP (*strMsgSend) (OOP receiver, const char * selector, ...); void (*msgSendf) (PTR resultPtr, const char *fmt, ...); OOP (*evalExpr) (const char *str); void (*evalCode) (const char *str); OOP (*objectAlloc) (OOP classOOP, int size); int (*basicSize) (OOP oop); /* Actually funcAddr is a function pointer, but we don't know the returned type so we must declare it as PTR */ void (*defineCFunc) (const char *funcName, PTR funcAddr); OOP (*registerOOP) (OOP oop); void (*unregisterOOP) (OOP oop); /* Convert C datatypes to Smalltalk types */ OOP (*idToOOP) (long i); OOP (*intToOOP) (long i); OOP (*floatToOOP) (double f); OOP (*boolToOOP) (int b); OOP (*charToOOP) (char c); OOP (*classNameToOOP) (const char *name); OOP (*stringToOOP) (const char *str); OOP (*byteArrayToOOP) (const char *str, int n); OOP (*symbolToOOP) (const char *str); OOP (*cObjectToOOP) (PTR co); OOP (*typeNameToOOP) (const char *name); void (*setCObject) (OOP oop, PTR co); /* Convert Smalltalk datatypes to C data types */ long (*OOPToC) (OOP oop); /* sometimes answers a PTR */ long (*OOPToId) (OOP oop); long (*OOPToInt) (OOP oop); double (*OOPToFloat) (OOP oop); int (*OOPToBool) (OOP oop); char (*OOPToChar) (OOP oop); char *(*OOPToString) (OOP oop); char *(*OOPToByteArray) (OOP oop); PTR (*OOPToCObject) (OOP oop); /* Smalltalk process support */ void (*asyncSignal) (OOP semaphoreOOP); void (*syncWait) (OOP semaphoreOOP); void (*asyncSignalAndUnregister) (OOP semaphoreOOP); /* Array-of-OOP registry support. Move these above when we break binary compatibility. */ void (*registerOOPArray) (OOP **first, OOP **last); void (*unregisterOOPArray) (OOP **first); /* More conversions. */ long double (*OOPToLongDouble) (OOP oop); OOP (*longDoubleToOOP) (long double f); /* More functions, added in 2.2. */ OOP (*getObjectClass) (OOP oop); OOP (*getSuperclass) (OOP oop); mst_Boolean (*classIsKindOf) (OOP oop, OOP candidate); mst_Boolean (*objectIsKindOf) (OOP oop, OOP candidate); OOP (*perform) (OOP oop, OOP selector); OOP (*performWith) (OOP oop, OOP selector, OOP arg); mst_Boolean (*classImplementsSelector) (OOP classOOP, OOP selector); mst_Boolean (*classCanUnderstand) (OOP classOOP, OOP selector); mst_Boolean (*respondsTo) (OOP oop, OOP selector); size_t (*OOPSize) (OOP oop); OOP (*OOPAt) (OOP oop, size_t index); OOP (*OOPAtPut) (OOP oop, size_t index, OOP newOOP); /* Some system classes. */ OOP objectClass, arrayClass, stringClass, characterClass, smallIntegerClass, floatDClass, floatEClass, byteArrayClass, objectMemoryClass, classClass, behaviorClass, blockClosureClass, contextPartClass, blockContextClass, methodContextClass, compiledMethodClass, compiledBlockClass, fileDescriptorClass, fileStreamClass, processClass, semaphoreClass, cObjectClass; /* More system objects. */ OOP processorOOP; /* More functions, added in 2.3. */ OOP (*wcharToOOP) (wchar_t wc); OOP (*wstringToOOP) (const wchar_t *str); wchar_t (*OOPToWChar) (OOP oop); wchar_t *(*OOPToWString) (OOP oop); /* 3.0+ functions. */ void (*processStdin) (const char *); mst_Boolean (*processFile) (const char *fileName, enum gst_file_dir dir); int (*getVar) (enum gst_var_index index); int (*setVar) (enum gst_var_index index, int value); void (*invokeHook) (enum gst_vm_hook); /* 3.1+ functions. */ char *(*relocatePath) (const char *); void *(*OOPIndexedBase) (OOP oop); enum gst_indexed_kind (*OOPIndexedKind) (OOP oop); void (*asyncCall) (void (*func) (OOP), OOP argOOP); mst_Boolean (*syncSignal) (OOP semaphoreOOP, mst_Boolean incrIfEmpty); void (*showBacktrace) (FILE *fp); /* 3.2+ functions. */ mst_Boolean (*dlOpen) (const char *filename, mst_Boolean module); void (*dlAddSearchDir) (const char *dir); void (*dlPushSearchPath) (void); void (*dlPopSearchPath) (void); void (*wakeUp) (void); /* 3.2.5+ functions. */ OOP (*uintToOOP) (unsigned long i); } VMProxy; /* Compatibility section */ #define indexedWord(obj, n) INDEXED_WORD(obj, n) #define indexedByte(obj, n) INDEXED_BYTE(obj, n) #define indexedOOP(obj, n) INDEXED_OOP(obj, n) #define arrayOOPAt(obj, n) ARRAY_OOP_AT(obj, n) #define stringOOPAt(obj, n) STRING_OOP_AT(obj, n) #define oopToObj(oop) OOP_TO_OBJ(oop) #define oopClass(oop) OOP_CLASS(oop) #define isInt(oop) IS_INT(oop) #define isOOP(oop) IS_OOP(oop) /* These are extern in case one wants to link to libgst.a; these are not meant to be called by a module, which is brought up by GNU Smalltalk when the VM is already up and running. */ /* These are the library counterparts of the functions in files.h. */ extern void gst_smalltalk_args (int argc, const char **argv); extern int gst_initialize (const char *kernel_dir, const char *image_file, int flags); /* Functions in input.h. */ extern void gst_process_stdin (const char *prompt); extern mst_Boolean gst_process_file (const char *fileName, enum gst_file_dir dir); /* Functions in interp.h. */ extern int gst_get_var (enum gst_var_index index); extern int gst_set_var (enum gst_var_index index, int value); /* Functions in comp.h. */ extern void gst_invoke_hook (enum gst_vm_hook); /* Functions in sysdep.h. */ extern void gst_set_executable_path (const char *); extern char *gst_relocate_path (const char *); /* Functions in cint.h. */ extern mst_Boolean gst_dlopen (const char *filename, mst_Boolean module); /* Add DIR at the beginning of the libltdl search path. */ extern void gst_dladdsearchdir (const char *dir); /* Push the current libltdl search path. */ extern void gst_dlpushsearchpath (void); /* Pop the saved search path into the current libltdl search path. */ extern void gst_dlpopsearchpath (void); /* These are the library counterparts of the functions in gst_vm_proxy. */ extern OOP gst_msg_send (OOP receiver, OOP selector, ...); extern OOP gst_vmsg_send (OOP receiver, OOP selector, OOP * args); extern OOP gst_nvmsg_send (OOP receiver, OOP selector, OOP * args, int nargs); extern OOP gst_str_msg_send (OOP receiver, const char * selector, ...); extern void gst_msg_sendf (PTR result_ptr, const char *fmt, ...); extern OOP gst_eval_expr (const char *str); extern void gst_eval_code (const char *str); extern OOP gst_object_alloc (OOP class_oop, int size); extern int gst_basic_size (OOP oop); extern void gst_define_cfunc (const char *func_name, PTR func_addr); extern OOP gst_register_oop (OOP oop); extern void gst_unregister_oop (OOP oop); extern OOP gst_id_to_oop (long i); extern OOP gst_int_to_oop (long i); extern OOP gst_uint_to_oop (unsigned long i); extern OOP gst_float_to_oop (double f); extern OOP gst_bool_to_oop (int b); extern OOP gst_char_to_oop (char c); extern OOP gst_class_name_to_oop (const char *name); extern OOP gst_string_to_oop (const char *str); extern OOP gst_byte_array_to_oop (const char *str, int n); extern OOP gst_symbol_to_oop (const char *str); extern OOP gst_c_object_to_oop (PTR co); extern OOP gst_type_name_to_oop (const char *name); extern void gst_set_c_o_bject (OOP oop, PTR co); extern long gst_oop_to_c (OOP oop); /* sometimes answers a PTR */ extern long gst_oop_to_id (OOP oop); extern long gst_oop_to_int (OOP oop); extern double gst_oop_to_float (OOP oop); extern int gst_oop_to_bool (OOP oop); extern char gst_oop_to_char (OOP oop); extern char *gst_oop_to_string (OOP oop); extern char *gst_oop_to_byte_array (OOP oop); extern PTR gst_oop_to_c_object (OOP oop); extern void gst_async_signal (OOP semaphore_oop); extern void gst_async_call (void (*func) (OOP), OOP arg_oop); extern mst_Boolean gst_sync_signal (OOP semaphore_oop, mst_Boolean incr_if_empty); extern void gst_sync_wait (OOP semaphore_oop); extern void gst_wakeup (void); extern void gst_show_backtrace (FILE *fp); extern void gst_async_signal_and_unregister (OOP semaphore_oop); extern void gst_register_oop_array (OOP **first, OOP **last); extern void gst_unregister_oop_array (OOP **first); extern long double gst_oop_to_long_double (OOP oop); extern OOP gst_long_double_to_oop (long double f); extern OOP gst_get_object_class (OOP oop); extern OOP gst_get_superclass (OOP oop); extern mst_Boolean gst_class_is_kind_of (OOP oop, OOP candidate); extern mst_Boolean gst_object_is_kind_of (OOP oop, OOP candidate); extern void gst_set_c_object (OOP oop, PTR co); extern OOP gst_perform (OOP oop, OOP selector); extern OOP gst_perform_with (OOP oop, OOP selector, OOP arg); extern mst_Boolean gst_class_implements_selector (OOP class_oop, OOP selector); extern mst_Boolean gst_class_can_understand (OOP class_oop, OOP selector); extern mst_Boolean gst_responds_to (OOP oop, OOP selector); extern size_t gst_oop_size (OOP oop); extern OOP gst_oop_at (OOP oop, size_t index); extern OOP gst_oop_at_put (OOP oop, size_t index, OOP new_oop); extern void *gst_oop_indexed_base (OOP oop); extern enum gst_indexed_kind gst_oop_indexed_kind (OOP oop); extern OOP gst_wchar_to_oop (wchar_t c); extern OOP gst_wstring_to_oop (const wchar_t *str); extern wchar_t gst_oop_to_wchar (OOP oop); extern wchar_t *gst_oop_to_wstring (OOP oop); /* This is exclusively for programs who link with libgst.a; plugins should not use this VMProxy but rather the one they receive in gst_initModule. */ extern VMProxy gst_interpreter_proxy; #ifdef __cplusplus } #endif #endif /* GST_GSTPUB_H */ smalltalk-3.2.5/libgst/dict.c0000644000175000017500000020216312130343734013005 00000000000000/******************************** -*- C -*- **************************** * * Dictionary Support Module. * * ***********************************************************************/ /*********************************************************************** * * Copyright 1988,89,90,91,92,94,95,99,2000,2001,2002,2003,2005,2006,2007,2008,2009 * Free Software Foundation, Inc. * Written by Steve Byrne. * * This file is part of GNU Smalltalk. * * GNU Smalltalk is free software; you can redistribute it and/or modify it * under the terms of the GNU General Public License as published by the Free * Software Foundation; either version 2, or (at your option) any later * version. * * Linking GNU Smalltalk statically or dynamically with other modules is * making a combined work based on GNU Smalltalk. Thus, the terms and * conditions of the GNU General Public License cover the whole * combination. * * In addition, as a special exception, the Free Software Foundation * give you permission to combine GNU Smalltalk with free software * programs or libraries that are released under the GNU LGPL and with * independent programs running under the GNU Smalltalk virtual machine. * * You may copy and distribute such a system following the terms of the * GNU GPL for GNU Smalltalk and the licenses of the other code * concerned, provided that you include the source code of that other * code when and as the GNU GPL requires distribution of source code. * * Note that people who make modified versions of GNU Smalltalk are not * obligated to grant this special exception for their modified * versions; it is their choice whether to do so. The GNU General * Public License gives permission to release a modified version without * this exception; this exception also makes it possible to release a * modified version which carries forward this exception. * * GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or * FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for * more details. * * You should have received a copy of the GNU General Public License along with * GNU Smalltalk; see the file COPYING. If not, write to the Free Software * Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * ***********************************************************************/ #include "gstpriv.h" /* this must be big enough that the Smalltalk dictionary does not have to grow between the time gst_dictionary is loaded and the time the kernel is initialized. Otherwise some of the methods needed to grow the dictionary might not be defined yet!! */ #define INITIAL_SMALLTALK_SIZE 512 typedef struct class_definition { OOP *classVar; OOP *superClassPtr; intptr_t instanceSpec; mst_Boolean reloadAddress; int numFixedFields; const char *name; const char *instVarNames; const char *classVarNames; const char *sharedPoolNames; } class_definition; /* Primary class variables. These variables hold the class objects for most of the builtin classes in the system */ OOP _gst_abstract_namespace_class = NULL; OOP _gst_array_class = NULL; OOP _gst_arrayed_collection_class = NULL; OOP _gst_association_class = NULL; OOP _gst_behavior_class = NULL; OOP _gst_binding_dictionary_class = NULL; OOP _gst_block_closure_class = NULL; OOP _gst_block_context_class = NULL; OOP _gst_boolean_class = NULL; OOP _gst_byte_array_class = NULL; OOP _gst_c_callable_class = NULL; OOP _gst_c_callback_descriptor_class = NULL; OOP _gst_c_func_descriptor_class = NULL; OOP _gst_c_object_class = NULL; OOP _gst_c_type_class = NULL; OOP _gst_callin_process_class = NULL; OOP _gst_char_class = NULL; OOP _gst_character_array_class = NULL; OOP _gst_class_class = NULL; OOP _gst_class_description_class = NULL; OOP _gst_collection_class = NULL; OOP _gst_compiled_block_class = NULL; OOP _gst_compiled_code_class = NULL; OOP _gst_compiled_method_class = NULL; OOP _gst_context_part_class = NULL; OOP _gst_continuation_class = NULL; OOP _gst_date_class = NULL; OOP _gst_deferred_variable_binding_class = NULL; OOP _gst_dictionary_class = NULL; OOP _gst_directed_message_class = NULL; OOP _gst_false_class = NULL; OOP _gst_file_descriptor_class = NULL; OOP _gst_file_segment_class = NULL; OOP _gst_file_stream_class = NULL; OOP _gst_float_class = NULL; OOP _gst_floatd_class = NULL; OOP _gst_floate_class = NULL; OOP _gst_floatq_class = NULL; OOP _gst_fraction_class = NULL; OOP _gst_hashed_collection_class = NULL; OOP _gst_homed_association_class = NULL; OOP _gst_identity_dictionary_class = NULL; OOP _gst_identity_set_class = NULL; OOP _gst_integer_class = NULL; OOP _gst_interval_class = NULL; OOP _gst_iterable_class = NULL; OOP _gst_large_integer_class = NULL; OOP _gst_large_negative_integer_class = NULL; OOP _gst_large_positive_integer_class = NULL; OOP _gst_large_zero_integer_class = NULL; OOP _gst_link_class = NULL; OOP _gst_linked_list_class = NULL; OOP _gst_lookup_key_class = NULL; OOP _gst_lookup_table_class = NULL; OOP _gst_magnitude_class = NULL; OOP _gst_memory_class = NULL; OOP _gst_message_class = NULL; OOP _gst_metaclass_class = NULL; OOP _gst_method_context_class = NULL; OOP _gst_method_dictionary_class = NULL; OOP _gst_method_info_class = NULL; OOP _gst_namespace_class = NULL; OOP _gst_number_class = NULL; OOP _gst_object_class = NULL; OOP _gst_object_memory_class = NULL; OOP _gst_ordered_collection_class = NULL; OOP _gst_permission_class = NULL; OOP _gst_positionable_stream_class = NULL; OOP _gst_process_class = NULL; OOP _gst_processor_scheduler_class = NULL; OOP _gst_read_stream_class = NULL; OOP _gst_read_write_stream_class = NULL; OOP _gst_root_namespace_class = NULL; OOP _gst_security_policy_class = NULL; OOP _gst_semaphore_class = NULL; OOP _gst_sequenceable_collection_class = NULL; OOP _gst_set_class = NULL; OOP _gst_small_integer_class = NULL; OOP _gst_smalltalk_dictionary = NULL; OOP _gst_sorted_collection_class = NULL; OOP _gst_stream_class = NULL; OOP _gst_string_class = NULL; OOP _gst_sym_link_class = NULL; OOP _gst_symbol_class = NULL; OOP _gst_system_dictionary_class = NULL; OOP _gst_time_class = NULL; OOP _gst_true_class = NULL; OOP _gst_undefined_object_class = NULL; OOP _gst_unicode_character_class = NULL; OOP _gst_unicode_string_class = NULL; OOP _gst_variable_binding_class = NULL; OOP _gst_weak_array_class = NULL; OOP _gst_weak_set_class = NULL; OOP _gst_weak_key_dictionary_class = NULL; OOP _gst_weak_value_lookup_table_class = NULL; OOP _gst_weak_identity_set_class = NULL; OOP _gst_weak_key_identity_dictionary_class = NULL; OOP _gst_weak_value_identity_dictionary_class = NULL; OOP _gst_write_stream_class = NULL; OOP _gst_processor_oop = NULL; /* Answer the number of slots that are in a dictionary of OLDNUMFIELDS items after growing it. */ static size_t new_num_fields (size_t oldNumFields); /* Instantiate the OOPs that are created before the first classes (true, false, nil, the Smalltalk dictionary, the symbol table and Processor, the sole instance of ProcessorScheduler. */ static void init_proto_oops (void); /* Look for the index at which KEYOOP resides in IDENTITYDICTIONARYOOP and answer it or, if not found, answer -1. */ static ssize_t identity_dictionary_find_key (OOP identityDictionaryOOP, OOP keyOOP); /* Look for the index at which KEYOOP resides in IDENTITYDICTIONARYOOP or, if not found, find a nil slot which can be replaced by that key. */ static size_t identity_dictionary_find_key_or_nil (OOP identityDictionaryOOP, OOP keyOOP); /* assume the value is an integer already or key does not exist, increase the value by inc or set the value to inc */ static int _gst_identity_dictionary_at_inc (OOP identityDictionaryOOP, OOP keyOOP, int inc); /* Create a new instance of CLASSOOP (an IdentityDictionary subclass) and answer it. */ static OOP identity_dictionary_new (OOP classOOP, int size); /* Create a new instance of Namespace with the given SIZE, NAME and superspace (SUPERSPACEOOP). */ static OOP namespace_new (int size, const char *name, OOP superspaceOOP); /* Create new class whose instances have a shape defined by CI. */ static void create_class (const class_definition *ci); /* Create a new metaclass for CLASS_OOP; reserve space for NUMSUBCLASSES classes in the instance variable "subclasses" of the class, and for NUMMETACLASSSUBCLASSES in the instance variable "subclasses" of the metaclass. */ static void create_metaclass (OOP class_oop, int numSubClasses, int numMetaclassSubClasses); /* Finish initializing the metaclass METACLASSOOP. */ static void init_metaclass (OOP metaclassOOP); /* Finish initializing the class CLASSOOP, using information from CI. */ static void init_class (OOP classOOP, const class_definition *ci); /* This creates the SystemDictionary called Smalltalk and initializes some of the variables in it. */ static void init_smalltalk_dictionary (void); /* This fills MAP so that it associates primitive numbers in the saved image to primitive numbers in this VM. */ static void prepare_primitive_numbers_table (void); /* Add a global named GLOBALNAME and give it the value GLOBALVALUE. Return GLOBALVALUE. */ static OOP add_smalltalk (const char *globalName, OOP globalValue); /* Create N class objects described in the array starting at CI, establishing the instance shape and the link between a class and its superclass. */ static void create_classes_pass1 (const class_definition *ci, int n); /* Create the subclasses variable of the N classes described in the array starting at CI (which being an Array must be created after the class objects are stored in the global variables). Also create the metaclass hierarchy and make the class objects point to it. */ static void create_classes_pass2 (const class_definition *ci, int n); /* Add a subclass SUBCLASSOOP to the subclasses array of SUPERCLASSOOP. Subclasses are stored from the last index to the first, and the first slot of the Array indicates the index of the last free slot. */ static void add_subclass (OOP superClassOOP, OOP subClassOOP); /* Adds to Smalltalk a global named FILEOBJECTNAME which is a FileStream referring to file descriptor FD. */ static void add_file_stream_object (int fd, int access, const char *fileObjectName); /* Creates the Symbols that the VM knows about, and initializes the globals in the Smalltalk dictionary. */ static void init_runtime_objects (void); /* Creates the VMPrimitives dictionary, which maps primitive names to primitive numbers. */ static void init_primitives_dictionary (void); /* Creates the CSymbols pool dictionary, which gives access from Smalltalk to some definitions in float.h and config.h. */ static void init_c_symbols (void); static const char *feature_strings[] = { #ifdef ENABLE_DLD "DLD", #endif NULL }; /* The class definition structure. From this structure, the initial set of Smalltalk classes are defined. */ static const class_definition class_info[] = { {&_gst_object_class, &_gst_nil_oop, GST_ISP_FIXED, true, 0, "Object", NULL, "Dependencies FinalizableObjects", "VMPrimitives" }, {&_gst_object_memory_class, &_gst_object_class, GST_ISP_FIXED, true, 34, "ObjectMemory", "bytesPerOOP bytesPerOTE " "edenSize survSpaceSize oldSpaceSize fixedSpaceSize " "edenUsedBytes survSpaceUsedBytes oldSpaceUsedBytes " "fixedSpaceUsedBytes rememberedTableEntries " "numScavenges numGlobalGCs numCompactions numGrowths " "numOldOOPs numFixedOOPs numWeakOOPs numOTEs numFreeOTEs " "timeBetweenScavenges timeBetweenGlobalGCs timeBetweenGrowths " "timeToScavenge timeToCollect timeToCompact " "reclaimedBytesPerScavenge tenuredBytesPerScavenge " "reclaimedBytesPerGlobalGC reclaimedPercentPerScavenge " "allocFailures allocMatches allocSplits allocProbes", NULL, NULL }, {&_gst_message_class, &_gst_object_class, GST_ISP_FIXED, true, 2, "Message", "selector args", NULL, NULL }, {&_gst_directed_message_class, &_gst_message_class, GST_ISP_FIXED, false, 1, "DirectedMessage", "receiver", NULL, NULL }, {&_gst_magnitude_class, &_gst_object_class, GST_ISP_FIXED, false, 0, "Magnitude", NULL, NULL, NULL }, {&_gst_char_class, &_gst_magnitude_class, GST_ISP_FIXED, true, 1, "Character", "codePoint", "Table UpperTable LowerTable", NULL }, {&_gst_unicode_character_class, &_gst_char_class, GST_ISP_FIXED, true, 0, "UnicodeCharacter", NULL, NULL, NULL }, {&_gst_time_class, &_gst_magnitude_class, GST_ISP_FIXED, false, 1, "Time", "seconds", "SecondClockAdjustment ClockOnStartup ClockOnImageSave", NULL }, {&_gst_date_class, &_gst_magnitude_class, GST_ISP_FIXED, false, 4, "Date", "days day month year", "DayNameDict MonthNameDict", NULL }, {&_gst_number_class, &_gst_magnitude_class, GST_ISP_FIXED, false, 0, "Number", NULL, NULL, NULL }, {&_gst_float_class, &_gst_number_class, GST_ISP_UCHAR, true, 0, "Float", NULL, NULL, "CSymbols" }, {&_gst_floatd_class, &_gst_float_class, GST_ISP_UCHAR, true, 0, "FloatD", NULL, NULL, "CSymbols" }, {&_gst_floate_class, &_gst_float_class, GST_ISP_UCHAR, true, 0, "FloatE", NULL, NULL, "CSymbols" }, {&_gst_floatq_class, &_gst_float_class, GST_ISP_UCHAR, true, 0, "FloatQ", NULL, NULL, "CSymbols" }, {&_gst_fraction_class, &_gst_number_class, GST_ISP_FIXED, false, 2, "Fraction", "numerator denominator", "Zero One", NULL }, {&_gst_integer_class, &_gst_number_class, GST_ISP_FIXED, true, 0, "Integer", NULL, NULL, "CSymbols" }, {&_gst_small_integer_class, &_gst_integer_class, GST_ISP_FIXED, true, 0, "SmallInteger", NULL, NULL, NULL }, {&_gst_large_integer_class, &_gst_integer_class, /* these four classes added by */ GST_ISP_UCHAR, true, 0, /* pb Sep 10 18:06:49 1998 */ "LargeInteger", NULL, "Zero One ZeroBytes OneBytes LeadingZeros TrailingZeros", NULL }, {&_gst_large_positive_integer_class, &_gst_large_integer_class, GST_ISP_UCHAR, true, 0, "LargePositiveInteger", NULL, NULL, NULL }, {&_gst_large_zero_integer_class, &_gst_large_positive_integer_class, GST_ISP_UCHAR, true, 0, "LargeZeroInteger", NULL, NULL, NULL }, {&_gst_large_negative_integer_class, &_gst_large_integer_class, GST_ISP_UCHAR, true, 0, "LargeNegativeInteger", NULL, NULL, NULL }, {&_gst_lookup_key_class, &_gst_magnitude_class, GST_ISP_FIXED, true, 1, "LookupKey", "key", NULL, NULL }, {&_gst_deferred_variable_binding_class, &_gst_lookup_key_class, GST_ISP_FIXED, true, 4, "DeferredVariableBinding", "class defaultDictionary association path", NULL, NULL }, {&_gst_association_class, &_gst_lookup_key_class, GST_ISP_FIXED, true, 1, "Association", "value", NULL, NULL }, {&_gst_homed_association_class, &_gst_association_class, GST_ISP_FIXED, false, 1, "HomedAssociation", "environment", NULL, NULL }, {&_gst_variable_binding_class, &_gst_homed_association_class, GST_ISP_FIXED, true, 0, "VariableBinding", NULL, NULL, NULL }, {&_gst_link_class, &_gst_object_class, GST_ISP_FIXED, false, 1, "Link", "nextLink", NULL, NULL }, {&_gst_process_class, &_gst_link_class, GST_ISP_FIXED, true, 7, "Process", "suspendedContext priority myList name environment interrupts interruptLock", NULL, NULL }, {&_gst_callin_process_class, &_gst_process_class, GST_ISP_FIXED, true, 1, "CallinProcess", "returnedValue", NULL, NULL }, {&_gst_sym_link_class, &_gst_link_class, GST_ISP_FIXED, true, 1, "SymLink", "symbol", NULL, NULL }, {&_gst_iterable_class, &_gst_object_class, GST_ISP_FIXED, false, 0, "Iterable", NULL, NULL, NULL }, {&_gst_collection_class, &_gst_iterable_class, GST_ISP_FIXED, false, 0, "Collection", NULL, NULL, NULL }, {&_gst_sequenceable_collection_class, &_gst_collection_class, GST_ISP_FIXED, false, 0, "SequenceableCollection", NULL, NULL, NULL }, {&_gst_linked_list_class, &_gst_sequenceable_collection_class, GST_ISP_FIXED, false, 2, "LinkedList", "firstLink lastLink", NULL, NULL }, {&_gst_semaphore_class, &_gst_linked_list_class, GST_ISP_FIXED, true, 2, "Semaphore", "signals name", NULL, NULL }, {&_gst_arrayed_collection_class, &_gst_sequenceable_collection_class, GST_ISP_POINTER, false, 0, "ArrayedCollection", NULL, NULL, NULL }, {&_gst_array_class, &_gst_arrayed_collection_class, GST_ISP_POINTER, true, 0, "Array", NULL, NULL, NULL }, {&_gst_weak_array_class, &_gst_array_class, GST_ISP_FIXED, false, 2, "WeakArray", "values nilValues", NULL, NULL }, {&_gst_character_array_class, &_gst_arrayed_collection_class, GST_ISP_ULONG, false, 0, "CharacterArray", NULL, NULL, NULL }, {&_gst_string_class, &_gst_character_array_class, GST_ISP_CHARACTER, true, 0, "String", NULL, NULL, NULL }, {&_gst_unicode_string_class, &_gst_character_array_class, GST_ISP_UTF32, true, 0, "UnicodeString", NULL, NULL, NULL }, {&_gst_symbol_class, &_gst_string_class, GST_ISP_CHARACTER, true, 0, "Symbol", NULL, NULL, NULL }, {&_gst_byte_array_class, &_gst_arrayed_collection_class, GST_ISP_UCHAR, true, 0, "ByteArray", NULL, NULL, "CSymbols" }, {&_gst_compiled_code_class, &_gst_arrayed_collection_class, GST_ISP_UCHAR, false, 2, "CompiledCode", "literals header", NULL, NULL }, {&_gst_compiled_block_class, &_gst_compiled_code_class, GST_ISP_UCHAR, true, 1, "CompiledBlock", "method", NULL, NULL }, {&_gst_compiled_method_class, &_gst_compiled_code_class, GST_ISP_UCHAR, true, 1, "CompiledMethod", "descriptor ", NULL, NULL }, {&_gst_interval_class, &_gst_arrayed_collection_class, GST_ISP_FIXED, true, 3, "Interval", "start stop step", NULL, NULL }, {&_gst_ordered_collection_class, &_gst_sequenceable_collection_class, GST_ISP_POINTER, false, 2, "OrderedCollection", "firstIndex lastIndex", NULL, NULL }, {&_gst_sorted_collection_class, &_gst_ordered_collection_class, GST_ISP_POINTER, false, 3, "SortedCollection", "lastOrdered sorted sortBlock", "DefaultSortBlock", NULL }, {&_gst_hashed_collection_class, &_gst_collection_class, GST_ISP_POINTER, false, 1, "HashedCollection", "tally", NULL, NULL }, {&_gst_set_class, &_gst_hashed_collection_class, GST_ISP_POINTER, false, 0, "Set", NULL, NULL, NULL }, {&_gst_weak_set_class, &_gst_set_class, GST_ISP_POINTER, false, 0, "WeakSet", NULL, NULL, NULL }, {&_gst_identity_set_class, &_gst_set_class, GST_ISP_POINTER, false, 0, "IdentitySet", NULL, NULL, NULL }, {&_gst_weak_identity_set_class, &_gst_weak_set_class, GST_ISP_POINTER, false, 0, "WeakIdentitySet", NULL, NULL, NULL }, {&_gst_dictionary_class, &_gst_hashed_collection_class, GST_ISP_POINTER, true, 0, "Dictionary", NULL, NULL, NULL }, {&_gst_weak_key_dictionary_class, &_gst_dictionary_class, GST_ISP_POINTER, false, 1, "WeakKeyDictionary", "keys", NULL, NULL }, {&_gst_weak_key_identity_dictionary_class, &_gst_weak_key_dictionary_class, GST_ISP_POINTER, false, 0, "WeakKeyIdentityDictionary", NULL, NULL, NULL }, {&_gst_lookup_table_class, &_gst_dictionary_class, GST_ISP_POINTER, false, 0, "LookupTable", NULL, NULL, NULL }, {&_gst_weak_value_lookup_table_class, &_gst_lookup_table_class, GST_ISP_POINTER, false, 1, "WeakValueLookupTable", "values", NULL, NULL }, {&_gst_weak_value_identity_dictionary_class, &_gst_weak_value_lookup_table_class, GST_ISP_POINTER, false, 0, "WeakValueIdentityDictionary", NULL, NULL, NULL }, {&_gst_identity_dictionary_class, &_gst_lookup_table_class, GST_ISP_POINTER, true, 0, "IdentityDictionary", NULL, NULL, NULL }, {&_gst_method_dictionary_class, &_gst_identity_dictionary_class, GST_ISP_POINTER, true, 0, "MethodDictionary", NULL, NULL, NULL }, /* These five MUST have the same structure as dictionary; they're used interchangeably within the C portion of the system */ {&_gst_binding_dictionary_class, &_gst_dictionary_class, GST_ISP_POINTER, true, 1, "BindingDictionary", "environment", NULL, NULL }, {&_gst_abstract_namespace_class, &_gst_binding_dictionary_class, GST_ISP_POINTER, true, 3, "AbstractNamespace", "name subspaces sharedPools", NULL, NULL }, {&_gst_root_namespace_class, &_gst_abstract_namespace_class, GST_ISP_POINTER, false, 0, "RootNamespace", NULL, NULL, NULL }, {&_gst_namespace_class, &_gst_abstract_namespace_class, GST_ISP_POINTER, true, 0, "Namespace", NULL, "Current", NULL }, {&_gst_system_dictionary_class, &_gst_root_namespace_class, GST_ISP_POINTER, false, 0, "SystemDictionary", NULL, NULL, NULL }, {&_gst_stream_class, &_gst_iterable_class, GST_ISP_FIXED, false, 0, "Stream", NULL, NULL, NULL }, {&_gst_positionable_stream_class, &_gst_stream_class, GST_ISP_FIXED, false, 4, "PositionableStream", "collection ptr endPtr access", NULL, NULL }, {&_gst_read_stream_class, &_gst_positionable_stream_class, GST_ISP_FIXED, false, 0, "ReadStream", NULL, NULL, NULL }, {&_gst_write_stream_class, &_gst_positionable_stream_class, GST_ISP_FIXED, false, 0, "WriteStream", NULL, NULL, NULL }, {&_gst_read_write_stream_class, &_gst_write_stream_class, GST_ISP_FIXED, false, 0, "ReadWriteStream", NULL, NULL, NULL }, {&_gst_file_descriptor_class, &_gst_stream_class, GST_ISP_FIXED, true, 6, "FileDescriptor", "access fd file isPipe atEnd peek", "AllOpenFiles", NULL }, {&_gst_file_stream_class, &_gst_file_descriptor_class, GST_ISP_FIXED, true, 5, "FileStream", "collection ptr endPtr writePtr writeEnd", "Verbose Record Includes", NULL }, {&_gst_undefined_object_class, &_gst_object_class, GST_ISP_FIXED, true, 0, "UndefinedObject", NULL, NULL, NULL }, {&_gst_boolean_class, &_gst_object_class, GST_ISP_FIXED, true, 0, "Boolean", NULL, NULL, NULL }, {&_gst_false_class, &_gst_boolean_class, GST_ISP_FIXED, true, 1, "False", "truthValue", NULL, NULL }, {&_gst_true_class, &_gst_boolean_class, GST_ISP_FIXED, true, 1, "True", "truthValue", NULL, NULL }, {&_gst_processor_scheduler_class, &_gst_object_class, GST_ISP_FIXED, false, 6, "ProcessorScheduler", "processLists activeProcess idleTasks processTimeslice gcSemaphore gcArray", NULL, NULL }, /* Change this, classDescription, or gst_class, and you must change the implementaion of new_metaclass some */ {&_gst_behavior_class, &_gst_object_class, GST_ISP_FIXED, true, 5, "Behavior", "superClass methodDictionary instanceSpec subClasses instanceVariables", NULL, NULL }, {&_gst_class_description_class, &_gst_behavior_class, GST_ISP_FIXED, true, 0, "ClassDescription", NULL, NULL, NULL }, {&_gst_class_class, &_gst_class_description_class, GST_ISP_FIXED, true, 8, "Class", "name comment category environment classVariables sharedPools " "securityPolicy pragmaHandlers", NULL, NULL }, {&_gst_metaclass_class, &_gst_class_description_class, GST_ISP_FIXED, true, 1, "Metaclass", "instanceClass", NULL, NULL }, {&_gst_context_part_class, &_gst_object_class, GST_ISP_POINTER, true, 6, "ContextPart", "parent nativeIP ip sp receiver method ", NULL, NULL }, {&_gst_method_context_class, &_gst_context_part_class, GST_ISP_POINTER, true, 1, "MethodContext", "flags ", NULL, NULL }, {&_gst_block_context_class, &_gst_context_part_class, GST_ISP_POINTER, true, 1, "BlockContext", "outerContext ", NULL, NULL }, {&_gst_continuation_class, &_gst_object_class, GST_ISP_FIXED, true, 1, "Continuation", "stack ", NULL, NULL }, {&_gst_block_closure_class, &_gst_object_class, GST_ISP_FIXED, true, 3, "BlockClosure", "outerContext block receiver", NULL, NULL }, {&_gst_permission_class, &_gst_object_class, GST_ISP_FIXED, true, 4, "Permission", "name actions target positive", NULL, NULL }, {&_gst_security_policy_class, &_gst_object_class, GST_ISP_FIXED, true, 2, "SecurityPolicy", "dictionary owner", NULL, NULL }, {&_gst_c_object_class, &_gst_object_class, GST_ISP_ULONG, true, 2, "CObject", "type storage", NULL, "CSymbols" }, {&_gst_c_type_class, &_gst_object_class, GST_ISP_FIXED, true, 1, "CType", "cObjectType", NULL, NULL }, {&_gst_c_callable_class, &_gst_c_object_class, GST_ISP_ULONG, true, 2, "CCallable", "returnType argTypes", NULL, NULL }, {&_gst_c_func_descriptor_class, &_gst_c_callable_class, GST_ISP_ULONG, false, 1, "CFunctionDescriptor", "cFunctionName", NULL, NULL }, {&_gst_c_callback_descriptor_class, &_gst_c_callable_class, GST_ISP_ULONG, true, 1, "CCallbackDescriptor", "block", NULL, NULL }, {&_gst_memory_class, &_gst_object_class, GST_ISP_FIXED, false, 0, "Memory", NULL, NULL, NULL }, {&_gst_method_info_class, &_gst_object_class, GST_ISP_POINTER, true, 4, "MethodInfo", "sourceCode category class selector", NULL, NULL }, {&_gst_file_segment_class, &_gst_object_class, GST_ISP_FIXED, true, 3, "FileSegment", "file startPos size", NULL, NULL } /* Classes not defined here (like Point/Rectangle/RunArray) are defined after the kernel has been fully initialized. */ }; signed char _gst_log2_sizes[32] = { 0, -1, 0, -1, 0, -1, 1, -1, 1, -1, 2, -1, 2, -1, 2, -1, 3, -1, 3, -1, 3, -1, 2, -1, -1, -1, -1, -1, -1, -1, sizeof (long) == 4 ? 2 : 3, -1 }; void init_proto_oops() { gst_namespace smalltalkDictionary; gst_object symbolTable, processorScheduler; int numWords; /* We can do this now that the classes are defined */ _gst_init_builtin_objects_classes (); /* Also finish the creation of the OOPs with reserved indices in oop.h */ /* the symbol table ... */ numWords = OBJ_HEADER_SIZE_WORDS + SYMBOL_TABLE_SIZE; symbolTable = _gst_alloc_words (numWords); SET_OOP_OBJECT (_gst_symbol_table, symbolTable); symbolTable->objClass = _gst_array_class; nil_fill (symbolTable->data, numWords - OBJ_HEADER_SIZE_WORDS); /* 5 is the # of fixed instvars in gst_namespace */ numWords = OBJ_HEADER_SIZE_WORDS + INITIAL_SMALLTALK_SIZE + 5; /* ... now the Smalltalk dictionary ... */ smalltalkDictionary = (gst_namespace) _gst_alloc_words (numWords); SET_OOP_OBJECT (_gst_smalltalk_dictionary, smalltalkDictionary); smalltalkDictionary->objClass = _gst_system_dictionary_class; smalltalkDictionary->tally = FROM_INT(0); smalltalkDictionary->name = _gst_smalltalk_namespace_symbol; smalltalkDictionary->superspace = _gst_nil_oop; smalltalkDictionary->subspaces = _gst_nil_oop; smalltalkDictionary->sharedPools = _gst_nil_oop; nil_fill (smalltalkDictionary->assoc, INITIAL_SMALLTALK_SIZE); /* ... and finally Processor */ numWords = sizeof (struct gst_processor_scheduler) / sizeof (PTR); processorScheduler = _gst_alloc_words (numWords); SET_OOP_OBJECT (_gst_processor_oop, processorScheduler); processorScheduler->objClass = _gst_processor_scheduler_class; nil_fill (processorScheduler->data, numWords - OBJ_HEADER_SIZE_WORDS); } void _gst_init_dictionary (void) { memcpy (_gst_primitive_table, _gst_default_primitive_table, sizeof (_gst_primitive_table)); /* The order of this must match the indices defined in oop.h!! */ _gst_smalltalk_dictionary = alloc_oop (NULL, _gst_mem.active_flag); _gst_processor_oop = alloc_oop (NULL, _gst_mem.active_flag); _gst_symbol_table = alloc_oop (NULL, _gst_mem.active_flag); _gst_init_symbols_pass1 (); create_classes_pass1 (class_info, sizeof (class_info) / sizeof (class_info[0])); init_proto_oops(); _gst_init_symbols_pass2 (); init_smalltalk_dictionary (); create_classes_pass2 (class_info, sizeof (class_info) / sizeof (class_info[0])); init_runtime_objects (); _gst_tenure_all_survivors (); } void create_classes_pass1 (const class_definition *ci, int n) { OOP superClassOOP; int nilSubclasses; gst_class classObj, superclass; for (nilSubclasses = 0; n--; ci++) { superClassOOP = *ci->superClassPtr; create_class (ci); if (IS_NIL (superClassOOP)) nilSubclasses++; else { superclass = (gst_class) OOP_TO_OBJ (superClassOOP); superclass->subClasses = FROM_INT (TO_INT (superclass->subClasses) + 1); } } /* Object class being a subclass of gst_class is not an apparent link, and so the index which is the number of subclasses of the class is off by the number of subclasses of nil. We correct that here. On the other hand, we don't want the meta class to have a subclass (`Class class' and `Class' are unique in that they don't have the same number of subclasses), so since we have the information here, we special case the Class class and create its metaclass here. */ classObj = (gst_class) OOP_TO_OBJ (_gst_class_class); create_metaclass (_gst_class_class, TO_INT (classObj->subClasses), TO_INT (classObj->subClasses) + nilSubclasses); } void create_classes_pass2 (const class_definition *ci, int n) { OOP class_oop; gst_class class; int numSubclasses; for (; n--; ci++) { class_oop = *ci->classVar; class = (gst_class) OOP_TO_OBJ (class_oop); if (!class->objClass) { numSubclasses = TO_INT (class->subClasses); create_metaclass (class_oop, numSubclasses, numSubclasses); } init_metaclass (class->objClass); init_class (class_oop, ci); } } void create_metaclass (OOP class_oop, int numMetaclassSubClasses, int numSubClasses) { gst_class class; gst_metaclass metaclass; gst_object subClasses; class = (gst_class) OOP_TO_OBJ (class_oop); metaclass = (gst_metaclass) new_instance (_gst_metaclass_class, &class->objClass); metaclass->instanceClass = class_oop; subClasses = new_instance_with (_gst_array_class, numSubClasses, &class->subClasses); if (numSubClasses > 0) subClasses->data[0] = FROM_INT (numSubClasses); subClasses = new_instance_with (_gst_array_class, numMetaclassSubClasses, &metaclass->subClasses); if (numMetaclassSubClasses > 0) subClasses->data[0] = FROM_INT (numMetaclassSubClasses); } void init_metaclass (OOP metaclassOOP) { gst_metaclass metaclass; OOP class_oop, superClassOOP; metaclass = (gst_metaclass) OOP_TO_OBJ (metaclassOOP); class_oop = metaclass->instanceClass; superClassOOP = SUPERCLASS (class_oop); if (IS_NIL (superClassOOP)) /* Object case: make this be gst_class to close the circularity */ metaclass->superclass = _gst_class_class; else metaclass->superclass = OOP_CLASS (superClassOOP); add_subclass (metaclass->superclass, metaclassOOP); /* the specifications here should match what a class should have: instance variable names, the right number of instance variables, etc. We could take three passes, and use the instance variable spec for classes once it's established, but it's easier to create them here by hand */ metaclass->instanceVariables = _gst_make_instance_variable_array (_gst_nil_oop, "superClass methodDictionary instanceSpec subClasses " "instanceVariables name comment category environment " "classVariables sharedPools securityPolicy " "pragmaHandlers"); metaclass->instanceSpec = GST_ISP_INTMARK | GST_ISP_FIXED | (((sizeof (struct gst_class) - sizeof (gst_object_header)) / sizeof (OOP)) << ISP_NUMFIXEDFIELDS); metaclass->methodDictionary = _gst_nil_oop; } void init_class (OOP class_oop, const class_definition *ci) { gst_class class; class = (gst_class) OOP_TO_OBJ (class_oop); class->name = _gst_intern_string (ci->name); add_smalltalk (ci->name, class_oop); if (!IS_NIL (class->superclass)) add_subclass (class->superclass, class_oop); class->environment = _gst_smalltalk_dictionary; class->instanceVariables = _gst_make_instance_variable_array (class->superclass, ci->instVarNames); class->classVariables = _gst_make_class_variable_dictionary (ci->classVarNames, class_oop); class->sharedPools = _gst_make_pool_array (ci->sharedPoolNames); /* Other fields are set by the Smalltalk code. */ class->methodDictionary = _gst_nil_oop; class->comment = _gst_nil_oop; class->category = _gst_nil_oop; class->securityPolicy = _gst_nil_oop; class->pragmaHandlers = _gst_nil_oop; } void add_subclass (OOP superClassOOP, OOP subClassOOP) { gst_class_description superclass; int index; superclass = (gst_class_description) OOP_TO_OBJ (superClassOOP); #ifndef OPTIMIZE if (NUM_WORDS (OOP_TO_OBJ (superclass->subClasses)) == 0) { _gst_errorf ("Attempt to add subclass to zero sized class"); abort (); } #endif index = TO_INT (ARRAY_AT (superclass->subClasses, 1)); ARRAY_AT_PUT (superclass->subClasses, 1, FROM_INT (index - 1)); ARRAY_AT_PUT (superclass->subClasses, index, subClassOOP); } void init_smalltalk_dictionary (void) { OOP featuresArrayOOP; gst_object featuresArray; char fullVersionString[200]; int i, numFeatures; _gst_current_namespace = _gst_smalltalk_dictionary; for (numFeatures = 0; feature_strings[numFeatures]; numFeatures++); featuresArray = new_instance_with (_gst_array_class, numFeatures, &featuresArrayOOP); for (i = 0; i < numFeatures; i++) featuresArray->data[i] = _gst_intern_string (feature_strings[i]); sprintf (fullVersionString, "GNU Smalltalk version %s", VERSION PACKAGE_GIT_REVISION); add_smalltalk ("Smalltalk", _gst_smalltalk_dictionary); add_smalltalk ("Version", _gst_string_new (fullVersionString)); add_smalltalk ("KernelFilePath", _gst_string_new (_gst_kernel_file_path)); add_smalltalk ("KernelInitialized", _gst_false_oop); add_smalltalk ("SymbolTable", _gst_symbol_table); add_smalltalk ("Processor", _gst_processor_oop); add_smalltalk ("Features", featuresArrayOOP); /* Add subspaces */ add_smalltalk ("CSymbols", namespace_new (32, "CSymbols", _gst_smalltalk_dictionary)); init_primitives_dictionary (); add_smalltalk ("Undeclared", namespace_new (32, "Undeclared", _gst_nil_oop)); add_smalltalk ("SystemExceptions", namespace_new (32, "SystemExceptions", _gst_smalltalk_dictionary)); add_smalltalk ("NetClients", namespace_new (32, "NetClients", _gst_smalltalk_dictionary)); add_smalltalk ("VFS", namespace_new (32, "VFS", _gst_smalltalk_dictionary)); _gst_init_process_system (); } static OOP add_smalltalk (const char *globalName, OOP globalValue) { NAMESPACE_AT_PUT (_gst_smalltalk_dictionary, _gst_intern_string (globalName), globalValue); return globalValue; } static OOP relocate_path_oop (const char *s) { OOP resultOOP; char *path = _gst_relocate_path (s); if (path) resultOOP = _gst_string_new (path); else resultOOP = _gst_nil_oop; free (path); return resultOOP; } void init_runtime_objects (void) { add_smalltalk ("UserFileBasePath", _gst_string_new (_gst_user_file_base_path)); add_smalltalk ("SystemKernelPath", relocate_path_oop (KERNEL_PATH)); add_smalltalk ("ModulePath", relocate_path_oop (MODULE_PATH)); add_smalltalk ("LibexecPath", relocate_path_oop (LIBEXEC_PATH)); add_smalltalk ("Prefix", relocate_path_oop (PREFIX)); add_smalltalk ("ExecPrefix", relocate_path_oop (EXEC_PREFIX)); add_smalltalk ("ImageFilePath", _gst_string_new (_gst_image_file_path)); add_smalltalk ("ExecutableFileName", _gst_string_new (_gst_executable_path)); add_smalltalk ("ImageFileName", _gst_string_new (_gst_binary_image_name)); add_smalltalk ("OutputVerbosity", FROM_INT (_gst_verbosity)); add_smalltalk ("RegressionTesting", _gst_regression_testing ? _gst_true_oop : _gst_false_oop); #ifdef WORDS_BIGENDIAN add_smalltalk ("Bigendian", _gst_true_oop); #else add_smalltalk ("Bigendian", _gst_false_oop); #endif add_file_stream_object (0, O_RDONLY, "stdin"); add_file_stream_object (1, O_WRONLY, "stdout"); add_file_stream_object (2, O_WRONLY, "stderr"); init_c_symbols (); /* Add the root among the roots :-) to the root set */ _gst_register_oop (_gst_smalltalk_dictionary); } void init_c_symbols () { OOP cSymbolsOOP = dictionary_at (_gst_smalltalk_dictionary, _gst_intern_string ("CSymbols")); NAMESPACE_AT_PUT (cSymbolsOOP, _gst_intern_string ("HostSystem"), _gst_string_new (HOST_SYSTEM)); NAMESPACE_AT_PUT (cSymbolsOOP, _gst_intern_string ("CIntSize"), FROM_INT (sizeof (int))); NAMESPACE_AT_PUT (cSymbolsOOP, _gst_intern_string ("CShortSize"), FROM_INT (sizeof (short))); NAMESPACE_AT_PUT (cSymbolsOOP, _gst_intern_string ("CLongSize"), FROM_INT (sizeof (long))); NAMESPACE_AT_PUT (cSymbolsOOP, _gst_intern_string ("CFloatSize"), FROM_INT (sizeof (float))); NAMESPACE_AT_PUT (cSymbolsOOP, _gst_intern_string ("CDoubleSize"), FROM_INT (sizeof (double))); NAMESPACE_AT_PUT (cSymbolsOOP, _gst_intern_string ("CLongDoubleSize"), FROM_INT (sizeof (long double))); NAMESPACE_AT_PUT (cSymbolsOOP, _gst_intern_string ("CPtrSize"), FROM_INT (sizeof (PTR))); #ifndef INFINITY #define INFINITY LDBL_MAX * 2 #endif #ifndef NAN #define NAN (0.0 / 0.0) #endif #if defined WIN32 && !defined __CYGWIN__ NAMESPACE_AT_PUT (cSymbolsOOP, _gst_intern_string ("PathSeparator"), CHAR_OOP_AT ('\\')); #else NAMESPACE_AT_PUT (cSymbolsOOP, _gst_intern_string ("PathSeparator"), CHAR_OOP_AT ('/')); #endif NAMESPACE_AT_PUT (cSymbolsOOP, _gst_intern_string ("CDoubleMin"), floatd_new (DBL_MIN)); NAMESPACE_AT_PUT (cSymbolsOOP, _gst_intern_string ("CDoubleMax"), floatd_new (DBL_MAX)); NAMESPACE_AT_PUT (cSymbolsOOP, _gst_intern_string ("CDoublePInf"), floatd_new ((double) INFINITY)); NAMESPACE_AT_PUT (cSymbolsOOP, _gst_intern_string ("CDoubleNInf"), floatd_new ((double) -INFINITY)); NAMESPACE_AT_PUT (cSymbolsOOP, _gst_intern_string ("CDoubleNaN"), floatd_new ((double) NAN)); NAMESPACE_AT_PUT (cSymbolsOOP, _gst_intern_string ("CDoubleDigits"), FROM_INT (ceil (DBL_MANT_DIG * 0.301029995663981))); NAMESPACE_AT_PUT (cSymbolsOOP, _gst_intern_string ("CDoubleBinaryDigits"), FROM_INT (DBL_MANT_DIG)); NAMESPACE_AT_PUT (cSymbolsOOP, _gst_intern_string ("CDoubleMinExp"), FROM_INT (DBL_MIN_EXP)); NAMESPACE_AT_PUT (cSymbolsOOP, _gst_intern_string ("CDoubleMaxExp"), FROM_INT (DBL_MAX_EXP)); NAMESPACE_AT_PUT (cSymbolsOOP, _gst_intern_string ("CDoubleAlignment"), FROM_INT (ALIGNOF_DOUBLE)); NAMESPACE_AT_PUT (cSymbolsOOP, _gst_intern_string ("CLongLongAlignment"), FROM_INT (ALIGNOF_LONG_LONG)); NAMESPACE_AT_PUT (cSymbolsOOP, _gst_intern_string ("CFloatPInf"), floate_new ((float) INFINITY)); NAMESPACE_AT_PUT (cSymbolsOOP, _gst_intern_string ("CFloatNInf"), floate_new ((float) -INFINITY)); NAMESPACE_AT_PUT (cSymbolsOOP, _gst_intern_string ("CFloatNaN"), floate_new ((float) NAN)); NAMESPACE_AT_PUT (cSymbolsOOP, _gst_intern_string ("CFloatMin"), floate_new (FLT_MIN)); NAMESPACE_AT_PUT (cSymbolsOOP, _gst_intern_string ("CFloatMax"), floate_new (FLT_MAX)); NAMESPACE_AT_PUT (cSymbolsOOP, _gst_intern_string ("CFloatDigits"), FROM_INT (ceil (FLT_MANT_DIG * 0.301029995663981))); NAMESPACE_AT_PUT (cSymbolsOOP, _gst_intern_string ("CFloatBinaryDigits"), FROM_INT (FLT_MANT_DIG)); NAMESPACE_AT_PUT (cSymbolsOOP, _gst_intern_string ("CFloatMinExp"), FROM_INT (FLT_MIN_EXP)); NAMESPACE_AT_PUT (cSymbolsOOP, _gst_intern_string ("CFloatMaxExp"), FROM_INT (FLT_MAX_EXP)); NAMESPACE_AT_PUT (cSymbolsOOP, _gst_intern_string ("CFloatAlignment"), FROM_INT (sizeof (float))); NAMESPACE_AT_PUT (cSymbolsOOP, _gst_intern_string ("CLongDoublePInf"), floatq_new ((long double) INFINITY)); NAMESPACE_AT_PUT (cSymbolsOOP, _gst_intern_string ("CLongDoubleNInf"), floatq_new ((long double) -INFINITY)); NAMESPACE_AT_PUT (cSymbolsOOP, _gst_intern_string ("CLongDoubleNaN"), floatq_new ((long double) NAN)); NAMESPACE_AT_PUT (cSymbolsOOP, _gst_intern_string ("CLongDoubleMin"), floatq_new (LDBL_MIN)); NAMESPACE_AT_PUT (cSymbolsOOP, _gst_intern_string ("CLongDoubleMax"), floatq_new (LDBL_MAX)); NAMESPACE_AT_PUT (cSymbolsOOP, _gst_intern_string ("CLongDoubleDigits"), FROM_INT (ceil (LDBL_MANT_DIG * 0.301029995663981))); NAMESPACE_AT_PUT (cSymbolsOOP, _gst_intern_string ("CLongDoubleBinaryDigits"), FROM_INT (LDBL_MANT_DIG)); NAMESPACE_AT_PUT (cSymbolsOOP, _gst_intern_string ("CLongDoubleMinExp"), FROM_INT (LDBL_MIN_EXP)); NAMESPACE_AT_PUT (cSymbolsOOP, _gst_intern_string ("CLongDoubleMaxExp"), FROM_INT (LDBL_MAX_EXP)); NAMESPACE_AT_PUT (cSymbolsOOP, _gst_intern_string ("CLongDoubleAlignment"), FROM_INT (ALIGNOF_LONG_DOUBLE)); } void init_primitives_dictionary () { OOP primDictionaryOOP = _gst_dictionary_new (512); int i; add_smalltalk ("VMPrimitives", primDictionaryOOP); for (i = 0; i < NUM_PRIMITIVES; i++) { prim_table_entry *pte = _gst_get_primitive_attributes (i); if (pte->name) { OOP keyOOP = _gst_intern_string (pte->name); OOP valueOOP = FROM_INT (i); DICTIONARY_AT_PUT (primDictionaryOOP, keyOOP, valueOOP); } } } void add_file_stream_object (int fd, int access, const char *fileObjectName) { OOP fileStreamOOP; OOP keyOOP; keyOOP = _gst_intern_string (fileObjectName); fileStreamOOP = dictionary_at (_gst_smalltalk_dictionary, keyOOP); if (IS_NIL (fileStreamOOP)) instantiate (_gst_file_stream_class, &fileStreamOOP); _gst_set_file_stream_file (fileStreamOOP, fd, _gst_string_new (fileObjectName), _gst_is_pipe (fd), access, true); add_smalltalk (fileObjectName, fileStreamOOP); } void create_class (const class_definition *ci) { gst_class class; intptr_t superInstanceSpec; OOP classOOP, superClassOOP; int numFixedFields; numFixedFields = ci->numFixedFields; superClassOOP = *ci->superClassPtr; if (!IS_NIL (superClassOOP)) { /* adjust the number of instance variables to account for inheritance */ superInstanceSpec = CLASS_INSTANCE_SPEC (superClassOOP); numFixedFields += superInstanceSpec >> ISP_NUMFIXEDFIELDS; } class = (gst_class) _gst_alloc_obj (sizeof (struct gst_class), &classOOP); class->objClass = NULL; class->superclass = superClassOOP; class->instanceSpec = GST_ISP_INTMARK | ci->instanceSpec | (numFixedFields << ISP_NUMFIXEDFIELDS); class->subClasses = FROM_INT (0); *ci->classVar = classOOP; } mst_Boolean _gst_init_dictionary_on_image_load (mst_Boolean prim_table_matches) { const class_definition *ci; _gst_smalltalk_dictionary = OOP_AT (SMALLTALK_OOP_INDEX); _gst_processor_oop = OOP_AT (PROCESSOR_OOP_INDEX); _gst_symbol_table = OOP_AT (SYM_TABLE_OOP_INDEX); if (IS_NIL (_gst_processor_oop) || IS_NIL (_gst_symbol_table) || IS_NIL (_gst_smalltalk_dictionary)) return (false); _gst_restore_symbols (); for (ci = class_info; ci < class_info + sizeof(class_info) / sizeof(class_definition); ci++) if (ci->reloadAddress) { *ci->classVar = dictionary_at (_gst_smalltalk_dictionary, _gst_intern_string (ci->name)); if UNCOMMON (IS_NIL (*ci->classVar)) return (false); } _gst_current_namespace = dictionary_at (_gst_class_variable_dictionary (_gst_namespace_class), _gst_intern_string ("Current")); _gst_init_builtin_objects_classes (); /* Important: this is called *after* _gst_init_symbols fills in _gst_vm_primitives_symbol! */ if (prim_table_matches) memcpy (_gst_primitive_table, _gst_default_primitive_table, sizeof (_gst_primitive_table)); else prepare_primitive_numbers_table (); init_runtime_objects (); return (true); } void prepare_primitive_numbers_table () { int i; OOP primitivesDictionaryOOP; primitivesDictionaryOOP = dictionary_at (_gst_smalltalk_dictionary, _gst_vm_primitives_symbol); for (i = 0; i < NUM_PRIMITIVES; i++) _gst_set_primitive_attributes (i, NULL); for (i = 0; i < NUM_PRIMITIVES; i++) { prim_table_entry *pte = _gst_get_primitive_attributes (i); OOP symbolOOP, valueOOP; int old_index; if (!pte->name) continue; symbolOOP = _gst_intern_string (pte->name); valueOOP = dictionary_at (primitivesDictionaryOOP, symbolOOP); /* Do nothing if the primitive is unknown to the image. */ if (IS_NIL (valueOOP)) continue; old_index = TO_INT (valueOOP); _gst_set_primitive_attributes (old_index, pte); } } OOP _gst_get_class_symbol (OOP class_oop) { gst_class class; class = (gst_class) OOP_TO_OBJ (class_oop); return (class->name); /* this is the case when we have a metaclass, ??? I don't think that this is right, but I don't know what else to do here */ } OOP _gst_find_class (OOP classNameOOP) { return (dictionary_at (_gst_smalltalk_dictionary, classNameOOP)); } OOP _gst_valid_class_method_dictionary (OOP class_oop) { gst_class class; /* ??? check for non-class objects */ class = (gst_class) OOP_TO_OBJ (class_oop); if (IS_NIL (class->methodDictionary)) { OOP identDict; identDict = identity_dictionary_new (_gst_method_dictionary_class, 32); class = (gst_class) OOP_TO_OBJ (class_oop); class->methodDictionary = identDict; } return (class->methodDictionary); } OOP _gst_find_class_method (OOP class_oop, OOP selector) { gst_class class; gst_identity_dictionary methodDictionary; OOP method_dictionary_oop; int index; class = (gst_class) OOP_TO_OBJ (class_oop); method_dictionary_oop = class->methodDictionary; if (IS_NIL (method_dictionary_oop)) return (_gst_nil_oop); index = identity_dictionary_find_key (method_dictionary_oop, selector); if (index < 0) return (_gst_nil_oop); methodDictionary = (gst_identity_dictionary) OOP_TO_OBJ (method_dictionary_oop); return (methodDictionary->keys[index]); } OOP _gst_class_variable_dictionary (OOP class_oop) { gst_class class; /* ??? check for non-class objects */ class = (gst_class) OOP_TO_OBJ (class_oop); return (class->classVariables); } OOP _gst_instance_variable_array (OOP class_oop) { gst_class class; /* ??? check for non-class objects */ class = (gst_class) OOP_TO_OBJ (class_oop); return (class->instanceVariables); } OOP _gst_shared_pool_dictionary (OOP class_oop) { gst_class class; /* ??? check for non-class objects */ class = (gst_class) OOP_TO_OBJ (class_oop); return (class->sharedPools); } OOP _gst_namespace_association_at (OOP poolOOP, OOP symbol) { OOP assocOOP; gst_namespace pool; if (is_a_kind_of (OOP_CLASS (poolOOP), _gst_class_class)) poolOOP = _gst_class_variable_dictionary (poolOOP); for (;;) { if (!is_a_kind_of (OOP_CLASS (poolOOP), _gst_dictionary_class)) return (_gst_nil_oop); assocOOP = dictionary_association_at (poolOOP, symbol); if (!IS_NIL (assocOOP)) return (assocOOP); /* Try to find a super-namespace */ if (!is_a_kind_of (OOP_CLASS (poolOOP), _gst_abstract_namespace_class)) return (_gst_nil_oop); pool = (gst_namespace) OOP_TO_OBJ (poolOOP); poolOOP = pool->superspace; } } OOP _gst_namespace_at (OOP poolOOP, OOP symbol) { OOP assocOOP = _gst_namespace_association_at (poolOOP, symbol); if (IS_NIL (assocOOP)) return assocOOP; else return ASSOCIATION_VALUE (assocOOP); } size_t new_num_fields (size_t oldNumFields) { /* Find a power of two that is larger than oldNumFields */ int n = 1; /* Already a power of two? duplicate the size */ if COMMON ((oldNumFields & (oldNumFields - 1)) == 0) return oldNumFields * 2; /* Find the next power of two by setting all bits to the right of the leftmost 1 bit to 1, and then incrementing. */ for (; oldNumFields & (oldNumFields + 1); n <<= 1) oldNumFields |= oldNumFields >> n; return oldNumFields + 1; } static int find_key_or_nil (OOP dictionaryOOP, OOP keyOOP) { size_t count, numFields, numFixedFields; intptr_t index; gst_object dictionary; OOP associationOOP; gst_association association; dictionary = (gst_object) OOP_TO_OBJ (dictionaryOOP); numFixedFields = OOP_FIXED_FIELDS (dictionaryOOP); numFields = NUM_WORDS (dictionary) - numFixedFields; index = scramble (OOP_INDEX (keyOOP)); count = numFields; for (; count; count--) { index &= numFields - 1; associationOOP = dictionary->data[numFixedFields + index]; if COMMON (IS_NIL (associationOOP)) return (index); association = (gst_association) OOP_TO_OBJ (associationOOP); if (association->key == keyOOP) return (index); /* linear reprobe -- it is simple and guaranteed */ index++; } _gst_errorf ("Error - searching dictionary for nil, but it is full!\n"); abort (); } gst_object _gst_grow_dictionary (OOP oldDictionaryOOP) { gst_object oldDictionary, dictionary; size_t oldNumFields, numFields, i, index, numFixedFields; OOP associationOOP; gst_association association; OOP dictionaryOOP; oldDictionary = OOP_TO_OBJ (oldDictionaryOOP); numFixedFields = OOP_FIXED_FIELDS (oldDictionaryOOP); oldNumFields = NUM_WORDS (oldDictionary) - numFixedFields; numFields = new_num_fields (oldNumFields); /* no need to use the incubator here. We are instantiating just one object, the new dictionary itself */ dictionary = instantiate_with (OOP_CLASS (oldDictionaryOOP), numFields, &dictionaryOOP); memcpy (dictionary->data, oldDictionary->data, sizeof (PTR) * numFixedFields); oldDictionary = OOP_TO_OBJ (oldDictionaryOOP); /* rehash all associations from old dictionary into new one */ for (i = 0; i < oldNumFields; i++) { associationOOP = oldDictionary->data[numFixedFields + i]; if COMMON (!IS_NIL (associationOOP)) { association = (gst_association) OOP_TO_OBJ (associationOOP); index = find_key_or_nil (dictionaryOOP, association->key); dictionary->data[numFixedFields + index] = associationOOP; } } _gst_swap_objects (dictionaryOOP, oldDictionaryOOP); return (OOP_TO_OBJ (oldDictionaryOOP)); } gst_identity_dictionary _gst_grow_identity_dictionary (OOP oldIdentityDictionaryOOP) { gst_identity_dictionary oldIdentityDictionary, identityDictionary; OOP key, identityDictionaryOOP; size_t oldNumFields, numFields, i, index; oldIdentityDictionary = (gst_identity_dictionary) OOP_TO_OBJ (oldIdentityDictionaryOOP); oldNumFields = (NUM_WORDS (oldIdentityDictionary) - 1) / 2; numFields = new_num_fields (oldNumFields); identityDictionary = (gst_identity_dictionary) instantiate_with (OOP_CLASS (oldIdentityDictionaryOOP), numFields * 2, &identityDictionaryOOP); oldIdentityDictionary = (gst_identity_dictionary) OOP_TO_OBJ (oldIdentityDictionaryOOP); identityDictionary->tally = oldIdentityDictionary->tally; /* rehash all associations from old dictionary into new one */ for (i = 0; i < oldNumFields; i++) { key = oldIdentityDictionary->keys[i * 2]; if COMMON (!IS_NIL (key)) { index = identity_dictionary_find_key_or_nil (identityDictionaryOOP, key); identityDictionary->keys[index - 1] = key; identityDictionary->keys[index] = oldIdentityDictionary->keys[i*2+1]; } } _gst_swap_objects (identityDictionaryOOP, oldIdentityDictionaryOOP); return ((gst_identity_dictionary) OOP_TO_OBJ (oldIdentityDictionaryOOP)); } ssize_t identity_dictionary_find_key (OOP identityDictionaryOOP, OOP keyOOP) { gst_identity_dictionary identityDictionary; size_t index, count, numFields; identityDictionary = (gst_identity_dictionary) OOP_TO_OBJ (identityDictionaryOOP); numFields = NUM_WORDS (identityDictionary) - 1; index = scramble (OOP_INDEX (keyOOP)) * 2; count = numFields / 2; /* printf ("%d %d %O\n", count, index & numFields - 1, keyOOP); */ while (count--) { index &= numFields - 1; if COMMON (IS_NIL (identityDictionary->keys[index])) return (-1); if COMMON (identityDictionary->keys[index] == keyOOP) return (index + 1); /* linear reprobe -- it is simple and guaranteed */ index += 2; } _gst_errorf ("Error - searching IdentityDictionary for nil, but it is full!\n"); abort (); } size_t identity_dictionary_find_key_or_nil (OOP identityDictionaryOOP, OOP keyOOP) { gst_identity_dictionary identityDictionary; size_t index, count, numFields; identityDictionary = (gst_identity_dictionary) OOP_TO_OBJ (identityDictionaryOOP); numFields = NUM_WORDS (identityDictionary) - 1; index = scramble (OOP_INDEX (keyOOP)) * 2; count = numFields / 2; /* printf ("%d %d %O\n", count, index & numFields - 1, keyOOP); */ while (count--) { index &= numFields - 1; if COMMON (IS_NIL (identityDictionary->keys[index])) return (index + 1); if COMMON (identityDictionary->keys[index] == keyOOP) return (index + 1); /* linear reprobe -- it is simple and guaranteed */ index += 2; } _gst_errorf ("Error - searching IdentityDictionary for nil, but it is full!\n"); abort (); } OOP identity_dictionary_new (OOP classOOP, int size) { gst_identity_dictionary identityDictionary; OOP identityDictionaryOOP; size = new_num_fields (size); identityDictionary = (gst_identity_dictionary) instantiate_with (classOOP, size * 2, &identityDictionaryOOP); identityDictionary->tally = FROM_INT (0); return (identityDictionaryOOP); } OOP _gst_identity_dictionary_at_put (OOP identityDictionaryOOP, OOP keyOOP, OOP valueOOP) { gst_identity_dictionary identityDictionary; intptr_t index; OOP oldValueOOP; identityDictionary = (gst_identity_dictionary) OOP_TO_OBJ (identityDictionaryOOP); /* Never make dictionaries too full! For simplicity, we do this even if the key is present in the dictionary (because it will most likely resolve some collisions and make things faster). */ if UNCOMMON (TO_INT (identityDictionary->tally) >= TO_INT (identityDictionary->objSize) * 3 / 8) identityDictionary = _gst_grow_identity_dictionary (identityDictionaryOOP); index = identity_dictionary_find_key_or_nil (identityDictionaryOOP, keyOOP); if COMMON (IS_NIL (identityDictionary->keys[index - 1])) identityDictionary->tally = INCR_INT (identityDictionary->tally); identityDictionary->keys[index - 1] = keyOOP; oldValueOOP = identityDictionary->keys[index]; identityDictionary->keys[index] = valueOOP; return (oldValueOOP); } OOP _gst_identity_dictionary_at (OOP identityDictionaryOOP, OOP keyOOP) { gst_identity_dictionary identityDictionary; intptr_t index; identityDictionary = (gst_identity_dictionary) OOP_TO_OBJ (identityDictionaryOOP); index = identity_dictionary_find_key_or_nil (identityDictionaryOOP, keyOOP); return identityDictionary->keys[index]; } OOP namespace_new (int size, const char *name, OOP superspaceOOP) { gst_namespace ns; OOP namespaceOOP, classOOP; size = new_num_fields (size); classOOP = IS_NIL (superspaceOOP) ? _gst_root_namespace_class : _gst_namespace_class; ns = (gst_namespace) instantiate_with (classOOP, size, &namespaceOOP); ns->tally = FROM_INT (0); ns->superspace = superspaceOOP; ns->subspaces = _gst_nil_oop; ns->name = _gst_intern_string (name); return (namespaceOOP); } OOP _gst_dictionary_new (int size) { gst_dictionary dictionary; OOP dictionaryOOP; size = new_num_fields (size); dictionary = (gst_dictionary) instantiate_with (_gst_dictionary_class, size, &dictionaryOOP); dictionary->tally = FROM_INT (0); return (dictionaryOOP); } OOP _gst_binding_dictionary_new (int size, OOP environmentOOP) { gst_binding_dictionary dictionary; OOP dictionaryOOP; size = new_num_fields (size); dictionary = (gst_binding_dictionary) instantiate_with (_gst_binding_dictionary_class, size, &dictionaryOOP); dictionary->tally = FROM_INT (0); dictionary->environment = environmentOOP; return (dictionaryOOP); } OOP _gst_dictionary_add (OOP dictionaryOOP, OOP associationOOP) { intptr_t index; gst_association association; gst_object dictionary; gst_dictionary dict; OOP value; inc_ptr incPtr; /* I'm not sure clients are protecting association OOP */ incPtr = INC_SAVE_POINTER (); INC_ADD_OOP (associationOOP); association = (gst_association) OOP_TO_OBJ (associationOOP); dictionary = OOP_TO_OBJ (dictionaryOOP); dict = (gst_dictionary) dictionary; if UNCOMMON (TO_INT (dict->tally) >= TO_INT (dict->objSize) * 3 / 4) { dictionary = _gst_grow_dictionary (dictionaryOOP); dict = (gst_dictionary) dictionary; } index = find_key_or_nil (dictionaryOOP, association->key); index += OOP_FIXED_FIELDS (dictionaryOOP); if COMMON (IS_NIL (dictionary->data[index])) { dict->tally = INCR_INT (dict->tally); dictionary->data[index] = associationOOP; } else { value = ASSOCIATION_VALUE (associationOOP); associationOOP = dictionary->data[index]; SET_ASSOCIATION_VALUE (associationOOP, value); } INC_RESTORE_POINTER (incPtr); return (associationOOP); } OOP _gst_object_copy (OOP oop) { gst_object old, new; OOP newOOP; size_t numFields; if UNCOMMON (IS_INT(oop) || IS_BUILTIN_OOP (oop)) return (oop); numFields = NUM_INDEXABLE_FIELDS (oop); new = instantiate_with (OOP_CLASS (oop), numFields, &newOOP); old = OOP_TO_OBJ (oop); memcpy (new, old, SIZE_TO_BYTES (TO_INT (old->objSize))); newOOP->flags |= (oop->flags & F_CONTEXT); return (newOOP); } OOP _gst_new_string (size_t len) { OOP stringOOP; new_instance_with (_gst_string_class, len, &stringOOP); return (stringOOP); } OOP _gst_string_new (const char *s) { gst_string string; size_t len; OOP stringOOP; if (s) { len = strlen (s); string = (gst_string) new_instance_with (_gst_string_class, len, &stringOOP); memcpy (string->chars, s, len); } else string = (gst_string) new_instance_with (_gst_string_class, 0, &stringOOP); return (stringOOP); } OOP _gst_unicode_string_new (const wchar_t *s) { int i; gst_unicode_string string; size_t len; OOP stringOOP; if (s) { len = wcslen (s); string = (gst_unicode_string) new_instance_with (_gst_unicode_string_class, len, &stringOOP); if (sizeof (wchar_t) == sizeof (string->chars[0])) memcpy (string->chars, s, len * sizeof (wchar_t)); else for (i = 0; i < len; i++) string->chars[i] = *s++; } else string = (gst_unicode_string) new_instance_with (_gst_unicode_string_class, 0, &stringOOP); return (stringOOP); } OOP _gst_counted_string_new (const char *s, size_t len) { gst_string string; OOP stringOOP; string = (gst_string) new_instance_with (_gst_string_class, len, &stringOOP); if (len) memcpy (string->chars, s, len); return (stringOOP); } void _gst_set_oopstring (OOP stringOOP, const char *s) { OOP newStringOOP; newStringOOP = _gst_string_new (s); _gst_swap_objects (stringOOP, newStringOOP); } void _gst_set_oop_unicode_string (OOP unicodeStringOOP, const wchar_t *s) { OOP newStringOOP; newStringOOP = _gst_unicode_string_new (s); _gst_swap_objects (unicodeStringOOP, newStringOOP); } char * _gst_to_cstring (OOP stringOOP) { char *result; size_t len; gst_string string; string = (gst_string) OOP_TO_OBJ (stringOOP); len = oop_num_fields (stringOOP); result = (char *) xmalloc (len + 1); memcpy (result, string->chars, len); result[len] = '\0'; return (result); } wchar_t * _gst_to_wide_cstring (OOP stringOOP) { wchar_t *result, *p; size_t len; gst_unicode_string string; int i; string = (gst_unicode_string) OOP_TO_OBJ (stringOOP); len = oop_num_fields (stringOOP); result = (wchar_t *) xmalloc (len + 1); if (sizeof (wchar_t) == 4) memcpy (result, string->chars, len * sizeof (wchar_t)); else for (p = result, i = 0; i < len; i++) *p++ = string->chars[i]; result[len] = '\0'; return (result); } OOP _gst_byte_array_new (const gst_uchar * bytes, size_t len) { gst_byte_array byteArray; OOP byteArrayOOP; byteArray = (gst_byte_array) new_instance_with (_gst_byte_array_class, len, &byteArrayOOP); memcpy (byteArray->bytes, bytes, len); return (byteArrayOOP); } gst_uchar * _gst_to_byte_array (OOP byteArrayOOP) { gst_uchar *result; size_t len; gst_byte_array byteArray; byteArray = (gst_byte_array) OOP_TO_OBJ (byteArrayOOP); len = oop_num_fields (byteArrayOOP); result = (gst_uchar *) xmalloc (len); memcpy (result, byteArray->bytes, len); return (result); } void _gst_set_oop_bytes (OOP byteArrayOOP, gst_uchar * bytes) { gst_byte_array byteArray; size_t len; len = oop_num_fields (byteArrayOOP); byteArray = (gst_byte_array) OOP_TO_OBJ (byteArrayOOP); memcpy (byteArray->bytes, bytes, len); } OOP _gst_message_new_args (OOP selectorOOP, OOP argsArray) { gst_message message; OOP messageOOP; message = (gst_message) new_instance (_gst_message_class, &messageOOP); message->selector = selectorOOP; message->args = argsArray; return (messageOOP); } OOP _gst_c_object_new_base (OOP baseOOP, uintptr_t cObjOfs, OOP typeOOP, OOP defaultClassOOP) { gst_cobject cObject; gst_ctype cType; OOP cObjectOOP; OOP classOOP; if (!IS_NIL (typeOOP)) { cType = (gst_ctype) OOP_TO_OBJ (typeOOP); classOOP = ASSOCIATION_VALUE (cType->cObjectType); } else classOOP = defaultClassOOP; cObject = (gst_cobject) instantiate_with (classOOP, 1, &cObjectOOP); cObject->type = typeOOP; cObject->storage = baseOOP; SET_COBJECT_OFFSET_OBJ (cObject, cObjOfs); return (cObjectOOP); } void _gst_free_cobject (OOP cObjOOP) { gst_cobject cObject; cObject = (gst_cobject) OOP_TO_OBJ (cObjOOP); if (!IS_NIL (cObject->storage)) cObject->storage = _gst_nil_oop; else xfree ((PTR) COBJECT_OFFSET_OBJ (cObject)); /* make it not point to falsely valid storage */ SET_COBJECT_OFFSET_OBJ (cObject, NULL); } void _gst_set_file_stream_file (OOP fileStreamOOP, int fd, OOP fileNameOOP, mst_Boolean isPipe, int access, mst_Boolean buffered) { gst_file_stream fileStream; fileStream = (gst_file_stream) OOP_TO_OBJ (fileStreamOOP); switch (access & O_ACCMODE) { case O_RDONLY: fileStream->access = FROM_INT (1); break; case O_WRONLY: fileStream->access = FROM_INT (2); break; case O_RDWR: fileStream->access = FROM_INT (3); break; } if (buffered) { char buffer[1024]; memset (buffer, 0, sizeof (buffer)); fileStream->collection = _gst_counted_string_new (buffer, sizeof (buffer)); fileStream->ptr = FROM_INT (1); fileStream->endPtr = FROM_INT (0); fileStream->writePtr = _gst_nil_oop; fileStream->writeEnd = _gst_nil_oop; } fileStream->fd = FROM_INT (fd); fileStream->file = fileNameOOP; fileStream->isPipe = isPipe == -1 ? _gst_nil_oop : isPipe ? _gst_true_oop : _gst_false_oop; } /* Profiling callback. The profiler use a simple data structure to store the cost and the call graph, which is a 2 level IdentityDictionary. First level keys are the CompiledMethod or CompiledBlock, and the second level key is the CompiledMethod or CompiledBlock that it calls. Values are the number of calls made. There is a special key "true" in the second level whose corresponding value is the accumulative cost for this method. */ void _gst_record_profile (OOP oldMethod, OOP newMethod, int ipOffset) { OOP profile; inc_ptr incPtr; /* Protect oldMethod from GC here to avoid complicating the fast path in interp-bc.inl. */ incPtr = INC_SAVE_POINTER (); INC_ADD_OOP (oldMethod); profile = _gst_identity_dictionary_at (_gst_raw_profile, oldMethod); if UNCOMMON (IS_NIL (profile)) { profile = identity_dictionary_new (_gst_identity_dictionary_class, 6); _gst_identity_dictionary_at_put (_gst_raw_profile, oldMethod, profile); } _gst_identity_dictionary_at_inc (profile, _gst_true_oop, _gst_bytecode_counter - _gst_saved_bytecode_counter); _gst_saved_bytecode_counter = _gst_bytecode_counter; /* if ipOffset is 0 then it is a callin and not a return, so we also record the call. */ if (ipOffset == 0) _gst_identity_dictionary_at_inc (profile, newMethod, 1); INC_RESTORE_POINTER (incPtr); } /* Assume the value for KEYOOP is an integer already or the key does not exist; increase the value by INC or set it to INC if it does not exist. */ int _gst_identity_dictionary_at_inc (OOP identityDictionaryOOP, OOP keyOOP, int inc) { gst_identity_dictionary identityDictionary; intptr_t index; int oldValue; identityDictionary = (gst_identity_dictionary) OOP_TO_OBJ (identityDictionaryOOP); /* Never make dictionaries too full! For simplicity, we do this even if the key is present in the dictionary (because it will most likely resolve some collisions and make things faster). */ if UNCOMMON (TO_INT (identityDictionary->tally) >= TO_INT (identityDictionary->objSize) * 3 / 8) identityDictionary = _gst_grow_identity_dictionary (identityDictionaryOOP); index = identity_dictionary_find_key_or_nil (identityDictionaryOOP, keyOOP); if UNCOMMON (IS_NIL (identityDictionary->keys[index - 1])) { identityDictionary->tally = INCR_INT (identityDictionary->tally); oldValue = 0; } else oldValue = TO_INT(identityDictionary->keys[index]); identityDictionary->keys[index - 1] = keyOOP; identityDictionary->keys[index] = FROM_INT(inc+oldValue); return (oldValue); } smalltalk-3.2.5/libgst/print.c0000644000175000017500000002641012123404352013211 00000000000000/******************************** -*- C -*- **************************** * * OOP printing and debugging module * * ***********************************************************************/ /*********************************************************************** * * Copyright 1988,89,90,91,92,94,95,99,2000,2001,2002,2003,2006,2009 * Free Software Foundation, Inc. * Written by Steve Byrne. * * This file is part of GNU Smalltalk. * * GNU Smalltalk is free software; you can redistribute it and/or modify it * under the terms of the GNU General Public License as published by the Free * Software Foundation; either version 2, or (at your option) any later * version. * * Linking GNU Smalltalk statically or dynamically with other modules is * making a combined work based on GNU Smalltalk. Thus, the terms and * conditions of the GNU General Public License cover the whole * combination. * * In addition, as a special exception, the Free Software Foundation * give you permission to combine GNU Smalltalk with free software * programs or libraries that are released under the GNU LGPL and with * independent programs running under the GNU Smalltalk virtual machine. * * You may copy and distribute such a system following the terms of the * GNU GPL for GNU Smalltalk and the licenses of the other code * concerned, provided that you include the source code of that other * code when and as the GNU GPL requires distribution of source code. * * Note that people who make modified versions of GNU Smalltalk are not * obligated to grant this special exception for their modified * versions; it is their choice whether to do so. The GNU General * Public License gives permission to release a modified version without * this exception; this exception also makes it possible to release a * modified version which carries forward this exception. * * GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or * FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for * more details. * * You should have received a copy of the GNU General Public License along with * GNU Smalltalk; see the file COPYING. If not, write to the Free Software * Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * ***********************************************************************/ #include "gstpriv.h" #include "snprintfv/mem.h" /* Print a Character OOP to a snprintfv stream, STREAM. */ static void print_char_to_stream (STREAM *stream, OOP oop); /* Print a String OOP to a snprintfv stream, STREAM. */ static void print_string_to_stream (STREAM *stream, OOP string); /* Print an Association OOP's key to a snprintfv stream, STREAM. */ static void print_association_key_to_stream (STREAM *stream, OOP associationOOP); /* Print a Class OOP's name to a snprintfv stream, STREAM. */ static void print_class_name_to_stream (STREAM *stream, OOP class_oop); /* Print a brief description of an OOP to a snprintfv stream, STREAM. */ static void print_oop_constructor_to_stream (STREAM *stream, OOP oop); /* The main routine to handle the %O modifier to printf. %#O prints Strings and Symbols without the leading # or the enclosing single quotes, while %+O expects that an Association is passed and prints its key. */ static void printf_oop (STREAM *stream, struct printf_info *info, const void *const *args); static int printf_oop_arginfo (struct printf_info *info, size_t n, int *argtypes); void _gst_print_object (OOP oop) { printf ("%O", oop); fflush (stdout); } void print_char_to_stream (STREAM *stream, OOP oop) { int val = CHAR_OOP_VALUE (oop); if (OOP_CLASS (oop) == _gst_char_class && val > 127) stream_printf (stream, "Character value: 16r%02X", val); else if (val >= 32 && val <= 126) stream_printf (stream, "$%c", val); else if (val < 32) stream_printf (stream, "$<%d>", val); else stream_printf (stream, "$<16r%04X>", val); } void print_string_to_stream (STREAM *stream, OOP string) { int len; len = _gst_string_oop_len (string); if (!len) return; stream_printf (stream, "%.*s", len, (char *) (OOP_TO_OBJ (string)->data)); } void print_association_key_to_stream (STREAM *stream, OOP associationOOP) { gst_association association; if (!IS_OOP (associationOOP) || !is_a_kind_of (OOP_CLASS(associationOOP), _gst_lookup_key_class)) { stream_printf (stream, "", associationOOP); return; } association = (gst_association) OOP_TO_OBJ (associationOOP); if (OOP_CLASS (association->key) != _gst_symbol_class) stream_printf (stream, ""); else stream_printf (stream, "%#O", association->key); } void print_class_name_to_stream (STREAM *stream, OOP class_oop) { gst_class class; class = (gst_class) OOP_TO_OBJ (class_oop); if (IS_A_CLASS (class_oop) && !IS_NIL (class->name)) print_string_to_stream (stream, class->name); else if (IS_A_CLASS (OOP_CLASS (class_oop))) { stream_printf (stream, ""); } else stream_printf (stream, ""); } void print_oop_constructor_to_stream (STREAM *stream, OOP oop) { intptr_t instanceSpec; OOP class_oop; class_oop = OOP_CLASS (oop); print_class_name_to_stream (stream, class_oop); instanceSpec = CLASS_INSTANCE_SPEC (class_oop); if (instanceSpec & ISP_ISINDEXABLE) stream_printf (stream, " new: %zu ", NUM_INDEXABLE_FIELDS (oop)); else stream_printf (stream, " new "); if (_gst_regression_testing) stream_printf (stream, "\"<0>\""); else stream_printf (stream, "\"<%p>\"", oop); } void printf_oop (STREAM *stream, struct printf_info *info, const void *const *args) { OOP oop = (OOP) (args[0]); if (info->showsign) { print_association_key_to_stream (stream, oop); return; } if (IS_INT (oop)) stream_printf (stream, "%td", TO_INT (oop)); else if (IS_NIL (oop)) stream_printf (stream, "nil"); else if (oop == _gst_true_oop) stream_printf (stream, "true"); else if (oop == _gst_false_oop) stream_printf (stream, "false"); else if (OOP_CLASS (oop) == _gst_char_class || OOP_CLASS (oop) == _gst_unicode_character_class) print_char_to_stream (stream, oop); else if (OOP_CLASS (oop) == _gst_floatd_class) { double f = FLOATD_OOP_VALUE (oop); char buf[100], *p; p = buf + sprintf (buf, "%#.*g", (_gst_regression_testing ? 6 : DBL_DIG), f); for (; p >= buf; p--) if (*p == 'e') { *p = 'd'; break; } stream_puts (buf, stream); } else if (OOP_CLASS (oop) == _gst_floate_class) { double f = FLOATE_OOP_VALUE (oop); stream_printf (stream, "%#.*g", (_gst_regression_testing ? 6 : FLT_DIG), f); } else if (OOP_CLASS (oop) == _gst_floatq_class) { long double f = FLOATQ_OOP_VALUE (oop); char buf[100], *p; p = buf + sprintf (buf, "%#.*Lg", (_gst_regression_testing ? 6 : LDBL_DIG), f); for (; p >= buf; p--) if (*p == 'e') { *p = 'q'; break; } stream_puts (buf, stream); } else if (OOP_CLASS (oop) == _gst_symbol_class) { if (!info->alt) stream_printf (stream, "#"); print_string_to_stream (stream, oop); } else if (OOP_CLASS (oop) == _gst_string_class) { /* ### have to quote embedded quote chars */ if (!info->alt) stream_printf (stream, "'"); print_string_to_stream (stream, oop); if (!info->alt) stream_printf (stream, "'"); } else if (IS_A_METACLASS (oop)) { OOP class_oop = _gst_find_an_instance (oop); if (IS_NIL (class_oop)) print_oop_constructor_to_stream (stream, oop); else { print_class_name_to_stream (stream, class_oop); stream_printf (stream, " class"); } } else if (IS_A_CLASS (oop)) print_class_name_to_stream (stream, oop); else print_oop_constructor_to_stream (stream, oop); fflush (stdout); } int printf_oop_arginfo (struct printf_info *info, size_t n, int *argtypes) { /* We always take exactly one argument and this is a pointer to the structure. */ if (n > 0) argtypes[0] = PA_POINTER; return 1; } void _gst_classify_addr (void *addr) { if (IS_INT (addr)) printf ("Smalltalk SmallInteger %td\n", TO_INT (addr)); else if (IS_OOP_ADDR (addr)) _gst_display_oop (addr); else _gst_display_object (addr); fflush (stdout); } void _gst_display_oop_short (OOP oop) { if (IS_OOP_FREE (oop)) printf ("%-10p Free\n", oop); else { printf ("%-10p %-10p %-10s %-10s %-10s\n", oop, oop->object, oop->flags & F_CONTEXT ? "Context" : oop->flags & F_WEAK ? "Weak" : oop->flags & F_EPHEMERON ? "Ephemeron" : "", oop->flags & F_FIXED ? "Fixed" : oop->flags & F_LOADED ? "Permanent" : oop->flags & F_OLD ? "Old" : oop->flags & _gst_mem.active_flag ? "To-space" : "From-space", IS_EDEN_ADDR (oop->object) ? "Eden" : IS_SURVIVOR_ADDR (oop->object, 0) ? "Surv (Even)" : IS_SURVIVOR_ADDR (oop->object, 1) ? "Surv (Odd)" : oop->flags & F_POOLED ? "Pooled" : oop->flags & F_REACHABLE ? "Old/marked" : "Old"); } } void _gst_display_oop (OOP oop) { if (!IS_OOP_ADDR (oop)) { printf ("Parameter %p does not appear to be an OOP!\n", oop); return; } if (IS_OOP_FREE (oop)) printf ("%-10p Free\n", oop); else { printf ("%-10p %-10p %-10s %-10s %-10s", oop, oop->object, oop->flags & F_CONTEXT ? "Context" : oop->flags & F_WEAK ? "Weak" : oop->flags & F_EPHEMERON ? "Ephemeron" : "", oop->flags & F_FIXED ? "Fixed" : oop->flags & F_LOADED ? "Permanent" : oop->flags & F_OLD ? "Old" : oop->flags & _gst_mem.active_flag ? "To-space" : "From-space", IS_EDEN_ADDR (oop->object) ? "Eden" : IS_SURVIVOR_ADDR (oop->object, 0) ? "Surv (Even)" : IS_SURVIVOR_ADDR (oop->object, 1) ? "Surv (Odd)" : oop->flags & F_POOLED ? "Pooled" : oop->flags & F_REACHABLE ? "Old/marked" : "Old"); if (IS_OOP_ADDR (oop->object->objClass)) printf (" %O (%O)\n", oop->object->objClass, oop->object->objSize); else printf (" (invalid class)\n"); } } void _gst_display_object (gst_object obj) { if (IS_OOP_ADDR (obj)) { printf ("Parameter %p appears to be an OOP!\n", obj); return; } printf ("Object at %p (%s)", obj, IS_EDEN_ADDR (obj) ? "Eden" : IS_SURVIVOR_ADDR (obj, 0) ? "Even" : IS_SURVIVOR_ADDR (obj, 1) ? "Odd" : "Old"); if (IS_OOP_ADDR (obj->objClass)) printf (", size %O (%zu OOPs), class %O\n", obj->objSize, NUM_OOPS (obj), obj->objClass); else printf (", contains invalid data\n"); } void _gst_init_snprintfv () { spec_entry *spec; snv_malloc = xmalloc; snv_realloc = xrealloc; snv_free = xfree; spec = register_printf_function ('O', printf_generic, printf_oop_arginfo); spec->user = printf_oop; } smalltalk-3.2.5/libgst/interp-bc.inl0000644000175000017500000005016012123404352014277 00000000000000/******************************** -*- C -*- **************************** * * Byte Code Interpreter Module. * This interprets the compiled bytecodes of a method. * * ***********************************************************************/ /*********************************************************************** * * Copyright 2001, 2002, 2003, 2006, 2007, 2008, 2009 * Free Software Foundation, Inc. * Written by Steve Byrne. * * This file is part of GNU Smalltalk. * * GNU Smalltalk is free software; you can redistribute it and/or modify it * under the terms of the GNU General Public License as published by the Free * Software Foundation; either version 2, or (at your option) any later * version. * * Linking GNU Smalltalk statically or dynamically with other modules is * making a combined work based on GNU Smalltalk. Thus, the terms and * conditions of the GNU General Public License cover the whole * combination. * * In addition, as a special exception, the Free Software Foundation * give you permission to combine GNU Smalltalk with free software * programs or libraries that are released under the GNU LGPL and with * independent programs running under the GNU Smalltalk virtual machine. * * You may copy and distribute such a system following the terms of the * GNU GPL for GNU Smalltalk and the licenses of the other code * concerned, provided that you include the source code of that other * code when and as the GNU GPL requires distribution of source code. * * Note that people who make modified versions of GNU Smalltalk are not * obligated to grant this special exception for their modified * versions; it is their choice whether to do so. The GNU General * Public License gives permission to release a modified version without * this exception; this exception also makes it possible to release a * modified version which carries forward this exception. * * GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or * FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for * more details. * * You should have received a copy of the GNU General Public License along with * GNU Smalltalk; see the file COPYING. If not, write to the Free Software * Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * ***********************************************************************/ /* This is basically how the interpreter works: The interpreter expects to be called in an environment where there already exists a well-defined method context. The instruction pointer, stored in the global variable "ip", and the stack pointer, stored in the global variable "sp", should be set up to point into the current method and gst_method_context. Other global variables, such as "_gst_this_method", "_gst_self", "_gst_temporaries", etc. should also be setup. See the routine _gst_prepare_execution_environment for details. The interpreter checks to see if any change in its state is required, such as switching to a new process, dealing with an asynchronous signal and printing out the byte codes that are being executed, if that was requested by the user. After that, the byte code that ip points to is fetched and decoded. Some byte codes perform jumps, which are performed by merely adjusting the value of ip. Some are message sends, which are described in more detail below. Some instructions require more than one byte code to perform their work; ip is advanced as needed and the extension byte codes are fetched. The code for the bytecode interpreter is automatically generated by the genvm program starting from the description in vm.def: since most bytecodes are actually combinations of other bytecodes, genvm avoids unnecessary stack pointer movement while synthesizing these bytecodes. After dispatching the byte code, the interpreter loops around to execute another byte code. A particular bytecode signals that the execution of the method is over, and that the interpreter should return to its caller. This bytecode is never generated by the compiler, it is only present in a private #'__terminate' method that is generated when bootstrapping. Note that the interpreter is not called recursively to implement message sends. Rather the state of the interpreter is saved away in the currently executing context, and a new context is created and the global variables such as ip, sp, and _gst_temporaries are initialized accordingly. When a message send occurs, the _gst_send_message_internal routine is invoked. It determines the class of the receiver, and checks to see if it already has cached the method definition for the given selector and receiver class. If so, that method is used, and if not, the receiver's method dictionary is searched for a method with the proper selector. If it's not found in that method dictionary, the method dictionary of the classes parent is examined, and on up the hierarchy, until a matching selector is found. If no selector is found, the receiver is sent a #doesNotUnderstand: message to indicate that a matching method could not be found. The stack is modified, pushing a gst_message object that embeds information about the original selector and arguments, and _gst_send_message_internal calls itself recursively to look up #doesNotUnderstand:. Note that if the object does not understand in turn the #doesNotUnderstand: message, a crash is extremely likely; things like this are however to be expected, since you're really playing a bad game and going against some logical things that the VM assumes for speed. If a method is found, it is examined for some special cases. The special cases are primitive return of _gst_self, return of an instance variable, return of a literal object, or execution of a primitive method definition. This latter operation is performed by the execute_primitive_operation routine. If the execution of this primitive interpreter fails, the normal message send operation is performed. If the found method is not one of the special cases, or if it is a primitive that failed to execute, a "normal" message send is performed. This basically entails saving away what state the interpreter has, such as the values of ip, and sp, being careful to save their relative locations and not their physical addresses, because one or more garbage collections could occur before the method context is returned to, and the absolute pointers would be invalid. The SEND_MESSAGE routine then creates a new gst_method_context object, makes its parent be the currently executing gst_method_context, and sets up the interpreters global variables to reference the new method and new gst_method_context. Once those variables are set, SEND_MESSAGE returns to the interpreter, which cheerfully begins executing the new method, totally unaware that the method that it was executing has changed. When a method returns, the context that called it is examined to restore the interpreter's global variables to the state that they were in before the callee was invoked. The values of ip and sp are restored to their absolute address values, and the other global state variables are restored accordingly. After the state has been restored, the interpreter continues execution, again totally oblivious to the fact that it's not running the same method it was on its previous byte code. Blocks are similarly implemented by send_block_value, which is simpler than _gst_send_message_internal however, because it contains no check for special cases, and no method lookup logic. Unlike the Blue Book, GNU Smalltalk stores bytecodes for blocks into separate CompiledBlock objects, not into the same CompiledMethods that holds the containing bytecodes. send_block_value expects to find a BlockClosure on the stack, and this BlockClosure object points to the CompiledBlock object to be activated. */ #define GET_CONTEXT_IP(ctx) TO_INT((ctx)->ipOffset) #define SET_THIS_METHOD(method, ipOffset) do { \ OOP old_method_oop = _gst_this_method; \ gst_compiled_method _method = (gst_compiled_method) \ OOP_TO_OBJ (_gst_this_method = (method)); \ \ method_base = _method->bytecodes; \ _gst_literals = OOP_TO_OBJ (_method->literals)->data; \ ip = method_base + (ipOffset); \ if UNCOMMON (_gst_raw_profile) \ _gst_record_profile (old_method_oop, method, ipOffset); \ } while(0) void _gst_send_message_internal (OOP sendSelector, int sendArgs, OOP receiver, OOP method_class) { int hashIndex; OOP methodOOP; method_cache_entry * methodData; gst_method_context newContext; method_header header; /* hash the selector and the class of the receiver together using XOR. Since both are addresses in the object table, and since object table entries are 2 longs in size, shift over by 3 bits (4 on 64-bit architectures) to remove the useless low order zeros. */ _gst_sample_counter++; hashIndex = METHOD_CACHE_HASH (sendSelector, method_class); methodData = &method_cache[hashIndex]; if UNCOMMON (methodData->selectorOOP != sendSelector || methodData->startingClassOOP != method_class) { /* :-( cache miss )-: */ if (!lookup_method (sendSelector, methodData, sendArgs, method_class)) { _gst_send_message_internal (_gst_does_not_understand_symbol, 1, receiver, method_class); return; } if (!IS_OOP_VERIFIED (methodData->methodOOP)) _gst_verify_sent_method (methodData->methodOOP); } /* Note that execute_primitive_operation might invoke a call-in, and which might in turn modify the method cache in general and corrupt methodData in particular. So, load everything before this can happen. */ header = methodData->methodHeader; methodOOP = methodData->methodOOP; #ifndef OPTIMIZE #ifdef DEBUG_CODE_FLOW { #else /* !DEBUG_CODE_FLOW */ if (header.numArgs != (unsigned) sendArgs) { #endif /* !DEBUG_CODE_FLOW */ OOP receiverClass; receiverClass = OOP_INT_CLASS (receiver); if (methodData->methodClassOOP == receiverClass) printf ("%O>>%O\n", receiverClass, sendSelector); else printf ("%O(%O)>>%O\n", receiverClass, methodData->methodClassOOP, sendSelector); if (header.numArgs != (unsigned) sendArgs) { _gst_errorf ("invalid number of arguments %d, expecting %d", sendArgs, header.numArgs); abort (); } } #endif /* !OPTIMIZE */ if UNCOMMON (header.headerFlag) { switch (header.headerFlag) { case MTH_RETURN_SELF: /* 1, return the receiver - _gst_self is already on the stack...so we leave it */ _gst_self_returns++; return; case MTH_RETURN_INSTVAR: { int primIndex = header.primitiveIndex; /* 2, return instance variable */ /* replace receiver with the returned instance variable */ SET_STACKTOP (INSTANCE_VARIABLE (receiver, primIndex)); _gst_inst_var_returns++; return; } case MTH_RETURN_LITERAL: { int primIndex = header.primitiveIndex; /* 3, return literal constant */ /* replace receiver with the returned literal constant */ SET_STACKTOP (GET_METHOD_LITERALS (methodOOP)[primIndex]); _gst_literal_returns++; return; } case MTH_PRIMITIVE: if COMMON (!execute_primitive_operation(header.primitiveIndex, sendArgs)) /* primitive succeeded. Continue with the parent context */ return; /* primitive failed. Invoke the normal method. */ last_primitive = 0; break; case MTH_USER_DEFINED: { OOP argsArrayOOP = create_args_array (sendArgs); (void) POP_OOP (); /* pop the receiver */ PUSH_OOP (methodData->methodOOP); PUSH_OOP (receiver); PUSH_OOP (argsArrayOOP); SEND_MESSAGE (_gst_value_with_rec_with_args_symbol, 2); return; } case MTH_NORMAL: case MTH_ANNOTATED: case MTH_UNUSED: default: break; } } /* Prepare new state. */ newContext = activate_new_context (header.stack_depth, sendArgs); newContext->flags = MCF_IS_METHOD_CONTEXT; /* push args and temps, set sp and _gst_temporaries */ prepare_context ((gst_context_part) newContext, sendArgs, header.numTemps); _gst_self = receiver; SET_THIS_METHOD (methodOOP, 0); } void _gst_send_method (OOP methodOOP) { int sendArgs; OOP receiver; method_header header; REGISTER (1, gst_compiled_method method); REGISTER (2, gst_method_context newContext); _gst_sample_counter++; if (!IS_OOP_VERIFIED (methodOOP)) _gst_verify_sent_method (methodOOP); method = (gst_compiled_method) OOP_TO_OBJ (methodOOP); header = method->header; sendArgs = header.numArgs; receiver = STACK_AT (sendArgs); if UNCOMMON (header.headerFlag) { switch (header.headerFlag) { case MTH_RETURN_SELF: /* 1, return the receiver - _gst_self is already on the stack...so we leave it */ _gst_self_returns++; return; case MTH_RETURN_INSTVAR: { int primIndex = header.primitiveIndex; /* 2, return instance variable */ /* replace receiver with the returned instance variable */ SET_STACKTOP (INSTANCE_VARIABLE (receiver, primIndex)); _gst_inst_var_returns++; return; } case MTH_RETURN_LITERAL: { int primIndex = header.primitiveIndex; /* 3, return literal constant */ /* replace receiver with the returned literal constant */ SET_STACKTOP (GET_METHOD_LITERALS (methodOOP)[primIndex]); _gst_literal_returns++; return; } case MTH_PRIMITIVE: if COMMON (!execute_primitive_operation(header.primitiveIndex, sendArgs)) /* primitive succeeded. Continue with the parent context */ return; /* primitive failed. Invoke the normal method. */ last_primitive = 0; break; case MTH_USER_DEFINED: { OOP argsArrayOOP = create_args_array (sendArgs); (void) POP_OOP (); /* pop the receiver */ PUSH_OOP (methodOOP); PUSH_OOP (receiver); PUSH_OOP (argsArrayOOP); SEND_MESSAGE (_gst_value_with_rec_with_args_symbol, 2); return; } case MTH_NORMAL: /* only here so that the compiler skips a range check */ case MTH_ANNOTATED: case MTH_UNUSED: default: break; } } /* prepare new state */ newContext = activate_new_context (header.stack_depth, sendArgs); newContext->flags = MCF_IS_METHOD_CONTEXT; /* push args and temps, set sp and _gst_temporaries */ prepare_context ((gst_context_part) newContext, sendArgs, header.numTemps); _gst_self = receiver; SET_THIS_METHOD (methodOOP, 0); } static mst_Boolean send_block_value (int numArgs, int cull_up_to) { OOP closureOOP; block_header header; REGISTER (1, gst_block_context blockContext); REGISTER (2, gst_block_closure closure); closureOOP = STACK_AT (numArgs); closure = (gst_block_closure) OOP_TO_OBJ (closureOOP); header = ((gst_compiled_block) OOP_TO_OBJ (closure->block))->header; /* Check numArgs. Remove up to CULL_UP_TO extra arguments if needed. */ if UNCOMMON (numArgs != header.numArgs) { if (numArgs < header.numArgs || numArgs > header.numArgs + cull_up_to) return (true); POP_N_OOPS (numArgs - header.numArgs); numArgs = header.numArgs; } /* prepare the new state, loading data from the closure */ /* gc might happen - so reload everything. */ blockContext = (gst_block_context) activate_new_context (header.depth, numArgs); closure = (gst_block_closure) OOP_TO_OBJ (closureOOP); blockContext->outerContext = closure->outerContext; /* push args and temps */ prepare_context ((gst_context_part) blockContext, numArgs, header.numTemps); _gst_self = closure->receiver; SET_THIS_METHOD (closure->block, 0); return (false); } void _gst_validate_method_cache_entries (void) { } OOP _gst_interpret (OOP processOOP) { interp_jmp_buf jb; gst_callin_process process; #ifdef LOCAL_REGS # undef sp # undef ip #if REG_AVAILABILITY == 0 # define LOCAL_COUNTER _gst_bytecode_counter # define EXPORT_REGS() (_gst_sp = sp, _gst_ip = ip) #else int LOCAL_COUNTER = 0; # define EXPORT_REGS() (_gst_sp = sp, _gst_ip = ip, \ _gst_bytecode_counter += LOCAL_COUNTER, \ LOCAL_COUNTER = 0) #endif /* If we have a good quantity of registers, activate more caching mechanisms. */ #if REG_AVAILABILITY >= 2 OOP self_cache, *temp_cache, *lit_cache; OOP my_nil_oop = _gst_nil_oop, my_true_oop = _gst_true_oop, my_false_oop = _gst_false_oop; # define _gst_nil_oop my_nil_oop # define _gst_true_oop my_true_oop # define _gst_false_oop my_false_oop # define IMPORT_REGS() (sp = _gst_sp, ip = _gst_ip, \ self_cache = _gst_self, temp_cache = _gst_temporaries, \ lit_cache = _gst_literals) #else # define IMPORT_REGS() (sp = _gst_sp, ip = _gst_ip) #endif REGISTER (1, ip_type ip); REGISTER (2, OOP * sp); REGISTER (3, intptr_t arg); #else /* !LOCAL_REGS */ # define EXPORT_REGS() # define IMPORT_REGS() #endif /* !LOCAL_REGS */ #ifdef PIPELINING gst_uchar b2, arg2, b4; /* pre-fetch queue */ void *t2; /* pre-decode queue */ BRANCH_REGISTER (t); #elif REG_AVAILABILITY >= 1 #ifdef BRANCH_REGISTER BRANCH_REGISTER(prefetch); #else void *prefetch; #endif #endif /* !PIPELINING */ #include "vm.inl" /* Global pointers to the bytecode routines are used to interrupt the bytecode interpreter "from the outside" and divert it to monitor_byte_codes. */ global_normal_bytecodes = normal_byte_codes; global_monitored_bytecodes = monitored_byte_codes; dispatch_vec = normal_byte_codes; /* Prime the interpreter's registers. */ IMPORT_REGS (); push_jmp_buf (&jb, true, processOOP); if (setjmp (jb.jmpBuf) == 0) goto monitor_byte_codes; else goto return_value; /* The code blocks that follow are executed in threaded-code style. */ monitor_byte_codes: SET_EXCEPT_FLAG (false); /* First, deal with any async signals. */ if (async_queue_enabled) empty_async_queue (); if UNCOMMON (time_to_preempt) ACTIVE_PROCESS_YIELD (); if UNCOMMON (!IS_NIL (switch_to_process)) { EXPORT_REGS (); change_process_context (switch_to_process); IMPORT_REGS (); if UNCOMMON (single_step_semaphore) { _gst_async_signal (single_step_semaphore); single_step_semaphore = NULL; } } if (is_process_terminating (processOOP)) goto return_value; if UNCOMMON (_gst_abort_execution) { OOP selectorOOP; selectorOOP = _gst_intern_string ((char *) _gst_abort_execution); _gst_abort_execution = NULL; SEND_MESSAGE (selectorOOP, 0); IMPORT_REGS (); } if UNCOMMON (_gst_execution_tracing) { if (verbose_exec_tracing) { if (sp >= _gst_temporaries) printf ("\t [%2td] --> %O\n", (ptrdiff_t) (sp - _gst_temporaries), STACKTOP ()); else printf ("\t self --> %O\n", _gst_self); } printf ("%5td:", (ptrdiff_t) (ip - method_base)); _gst_print_bytecode_name (ip, ip - method_base, _gst_literals, ""); SET_EXCEPT_FLAG (true); } if UNCOMMON (time_to_preempt) set_preemption_timer (); FETCH_VEC (normal_byte_codes); /* Some more routines we need... */ lookahead_failed_true: PUSH_OOP (_gst_true_oop); DISPATCH (normal_byte_codes); lookahead_dup_true: PREFETCH_VEC (true_byte_codes); PUSH_OOP (_gst_true_oop); NEXT_BC_VEC (true_byte_codes); lookahead_failed_false: PUSH_OOP (_gst_false_oop); DISPATCH (normal_byte_codes); lookahead_dup_false: PREFETCH_VEC (false_byte_codes); PUSH_OOP (_gst_false_oop); NEXT_BC_VEC (false_byte_codes); return_value: process = (gst_callin_process) OOP_TO_OBJ (processOOP); if (pop_jmp_buf ()) stop_execution (); return (process->returnedValue); } /* Always use outer ip/sp outside _gst_interpret */ #ifdef LOCAL_REGS # define ip _gst_ip # define sp _gst_sp # if REG_AVAILABILITY >= 2 # undef _gst_nil_oop # undef _gst_true_oop # undef _gst_false_oop # endif # if REG_AVAILABILITY == 0 # undef LOCAL_COUNTER # endif #endif smalltalk-3.2.5/libgst/oop.c0000644000175000017500000017360412130343734012666 00000000000000/******************************** -*- C -*- **************************** * * Object Table maintenance module. * * ***********************************************************************/ /*********************************************************************** * * Copyright 1988,89,90,91,92,94,95,99,2000,2001,2002,2006,2007,2008,2009 * Free Software Foundation, Inc. * Written by Steve Byrne and Paolo Bonzini. * * This file is part of GNU Smalltalk. * * GNU Smalltalk is free software; you can redistribute it and/or modify it * under the terms of the GNU General Public License as published by the Free * Software Foundation; either version 2, or (at your option) any later * version. * * Linking GNU Smalltalk statically or dynamically with other modules is * making a combined work based on GNU Smalltalk. Thus, the terms and * conditions of the GNU General Public License cover the whole * combination. * * In addition, as a special exception, the Free Software Foundation * give you permission to combine GNU Smalltalk with free software * programs or libraries that are released under the GNU LGPL and with * independent programs running under the GNU Smalltalk virtual machine. * * You may copy and distribute such a system following the terms of the * GNU GPL for GNU Smalltalk and the licenses of the other code * concerned, provided that you include the source code of that other * code when and as the GNU GPL requires distribution of source code. * * Note that people who make modified versions of GNU Smalltalk are not * obligated to grant this special exception for their modified * versions; it is their choice whether to do so. The GNU General * Public License gives permission to release a modified version without * this exception; this exception also makes it possible to release a * modified version which carries forward this exception. * * GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or * FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for * more details. * * You should have received a copy of the GNU General Public License along with * GNU Smalltalk; see the file COPYING. If not, write to the Free Software * Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * ***********************************************************************/ #include "gstpriv.h" #define K 1024 #define INIT_NUM_INCUBATOR_OOPS 50 #define INCUBATOR_CHUNK_SIZE 20 /* The number of OOPs that are swept on each incremental GC step. */ #define INCREMENTAL_SWEEP_STEP 100 /* Define this flag to turn on debugging dumps for garbage collection */ /* #define GC_DEBUG_OUTPUT */ /* Define this flag to turn on debugging code for OOP table management */ /* #define GC_DEBUGGING */ /* Define this flag to disable incremental garbage collection */ /* #define NO_INCREMENTAL_GC */ /* Define this flag to turn on debugging code for oldspace management */ /* #define MMAN_DEBUG_OUTPUT */ #if defined(GC_DEBUG_OUTPUT) #define GC_DEBUGGING #endif #if !defined(OPTIMIZE) #define GC_DEBUGGING #endif /* These are the real OOPS for nil, true, and false */ OOP _gst_nil_oop = NULL; OOP _gst_true_oop = NULL; OOP _gst_false_oop = NULL; /* This is true to show a message whenever a GC happens. */ int _gst_gc_message = true; /* This is != 0 in the middle of a GC. */ int _gst_gc_running = 0; /* This is the memory area which holds the object table. */ static heap oop_heap; /* This vector holds the storage for all the Character objects in the system. Since all character objects are unique, we pre-allocate space for 256 of them, and treat them as special built-ins when doing garbage collection. */ static struct gst_character _gst_char_object_table[NUM_CHAR_OBJECTS]; /* This is "nil" object in the system. That is, the single instance of the UndefinedObject class, which is called "nil". */ static struct gst_undefined_object _gst_nil_object; /* These represent the two boolean objects in the system, true and false. This is the object storage for those two objects. false == &_gst_boolean_objects[0], true == &_gst_boolean_objects[1] */ static struct gst_boolean _gst_boolean_objects[2]; /* This variable represents information about the memory space. _gst_mem holds the required information: basically the pointer to the base and top of the space, and the pointers into it for allocation and copying. */ struct memory_space _gst_mem; /* Data to compute the statistics in _gst_mem. */ struct statistical_data { int reclaimedOldSpaceBytesSinceLastGlobalGC; unsigned long timeOfLastScavenge, timeOfLastGlobalGC, timeOfLastGrowth, timeOfLastCompaction; } stats; /* Allocates a table for OOPs of SIZE bytes, and store pointers to the builtin OOPs into _gst_nil_oop et al. */ static void alloc_oop_table (size_t); /* Free N slots from the beginning of the queue Q and return a pointer to their base. */ static OOP *queue_get (surv_space *q, int n); /* Allocate N slots at the end of the queue Q and return a pointer to their base. */ static OOP *queue_put (surv_space *q, OOP *src, int n); /* Move an object from survivor space to oldspace. */ static void tenure_one_object (); /* Initialize an allocation heap with the oldspace hooks set. */ static heap_data *init_old_space (size_t size); /* Initialize a surv_space structure. */ static void init_survivor_space (struct surv_space *space, size_t size); /* Raise the oldspace size limit to SIZE bytes without compacting it. */ static void grow_memory_no_compact (size_t size); /* Reset a surv_space structure (same as init, but without allocating memory. */ static void reset_survivor_space (struct surv_space *space); /* Return whether the incremental collector is running. */ static inline mst_Boolean incremental_gc_running (void); /* Restart the incremental collector. Objects before FIRSTOOP are assumed to be alive (currently the base of the OOP table is always passed, but you never know). */ static void reset_incremental_gc (OOP firstOOP); /* Compact the old objects. Grow oldspace to NEWSIZE bytes. */ static void compact (size_t new_heap_limit); /* Allocate and return space for an oldspace object of SIZE bytes. The pointer to the object data is returned, the OOP is stored in P_OOP. */ static gst_object alloc_old_obj (size_t size, OOP *p_oop); /* Gather statistics. */ static void update_stats (unsigned long *last, double *between, double *duration); /* The copying collector. */ static inline void copy_oops (void); /* Grey ranges are generated in two cases. The standard one is when we write to oldspace; another one is when we copy objects to the destination semispace faster than the scanner can go past them. When this happens, tenure_one_object puts the object onto a special list of old objects that are to be scanned. What this function does is to consume this last list. (It also completes the special treatment of ephemeron objects). */ static void scan_grey_objects (); /* The treatment of grey pages is different from grey objects. Since some new objects might not be tenured, grey pages might still hold some pointers to new objects. For this reason, and to avoid the cost of delivering two signals, a grey page is *not* removed from the tree until no new object is found in it. */ static void scan_grey_pages (); /* Greys a page worth of pointers starting at BASE. */ static void add_to_grey_list (OOP *base, int n); /* Greys the object OOP. */ static void add_grey_object (OOP oop); /* Do the breadth-first scanning of copied objects. */ static void cheney_scan (void); /* Hook that allows pages to be created grey. */ static void oldspace_after_allocating (heap_data *h, heap_block *blk, size_t sz); /* Hook that discards freed pages from the remembered table. */ static void oldspace_before_freeing (heap_data *h, heap_block *blk, size_t sz); #ifndef NO_SIGSEGV_HANDLING /* The a global SIGSEGV handler. */ static int oldspace_sigsegv_handler (void* fault_address, int serious); #endif /* Hook that triggers garbage collection. */ static heap_data *oldspace_nomemory (heap_data *h, size_t sz); /* Answer the number of fields to be scanned in the object starting at OBJ, with the given FLAGS on its OOP. */ static int scanned_fields_in (gst_object obj, int flags) ATTRIBUTE_PURE; /* The mark phase of oldspace GC. */ static inline void mark_oops (void); /* Communicate to the finalization thread which objects have to be sent the #mourn message. When one of the objects pointed to by a weak object have no other references, the slot of the weak object is replaced by a zero and the #mourn message is sent to it. Ephemerons' keys are checked for reachability after non-ephemerons are marked, and if no objects outside the ephemeron refer to it, the ephemeron is sent #mourn as well. */ static inline void mourn_objects (void); /* Mark the ephemeron objects. This is done after other objects are marked. */ static inline void mark_ephemeron_oops (void); /* Walks the instance variables of weak objects and zeroes out those that are not surviving the garbage collection. Called by preare_for_sweep. */ static inline void check_weak_refs (); void init_survivor_space (struct surv_space *space, size_t size) { space->totalSize = size; space->minPtr = (OOP *) xmalloc (size); space->maxPtr = (OOP *) ((char *)space->minPtr + size); reset_survivor_space (space); } heap_data * init_old_space (size_t size) { heap_data *h = _gst_mem_new_heap (0, size); h->after_prim_allocating = oldspace_after_allocating; h->before_prim_freeing = oldspace_before_freeing; h->nomemory = oldspace_nomemory; return h; } void _gst_init_mem_default () { _gst_init_mem (0, 0, 0, 0, 0, 0); } void _gst_init_mem (size_t eden, size_t survivor, size_t old, size_t big_object_threshold, int grow_threshold_percent, int space_grow_rate) { if (!_gst_mem.old) { #ifndef NO_SIGSEGV_HANDLING sigsegv_install_handler (oldspace_sigsegv_handler); #endif if (!eden) eden = 3 * K * K; if (!survivor) survivor = 128 * K; if (!old) old = 4 * K * K; if (!big_object_threshold) big_object_threshold = 4 * K; if (!grow_threshold_percent) grow_threshold_percent = 80; if (!space_grow_rate) space_grow_rate = 30; } else { if (eden || survivor) _gst_scavenge (); if (survivor) _gst_tenure_all_survivors (); if (old && old != _gst_mem.old->heap_total) _gst_grow_memory_to (old); } if (eden) { _gst_mem.eden.totalSize = eden; _gst_mem.eden.minPtr = (OOP *) xmalloc (eden); _gst_mem.eden.allocPtr = _gst_mem.eden.minPtr; _gst_mem.eden.maxPtr = (OOP *) ((char *)_gst_mem.eden.minPtr + eden); } if (survivor) { init_survivor_space (&_gst_mem.surv[0], survivor); init_survivor_space (&_gst_mem.surv[1], survivor); init_survivor_space (&_gst_mem.tenuring_queue, survivor / OBJ_HEADER_SIZE_WORDS); } if (big_object_threshold) _gst_mem.big_object_threshold = big_object_threshold; if (_gst_mem.eden.totalSize < _gst_mem.big_object_threshold) _gst_mem.big_object_threshold = _gst_mem.eden.totalSize; if (grow_threshold_percent) _gst_mem.grow_threshold_percent = grow_threshold_percent; if (space_grow_rate) _gst_mem.space_grow_rate = space_grow_rate; if (!_gst_mem.old) { if (old) { _gst_mem.old = init_old_space (old); _gst_mem.fixed = init_old_space (old); } _gst_mem.active_half = &_gst_mem.surv[0]; _gst_mem.active_flag = F_EVEN; _gst_mem.live_flags = F_EVEN | F_OLD; stats.timeOfLastScavenge = stats.timeOfLastGlobalGC = stats.timeOfLastGrowth = stats.timeOfLastCompaction = _gst_get_milli_time (); _gst_mem.factor = 0.4; _gst_inc_init_registry (); } _gst_mem.markQueue = (struct mark_queue *) xcalloc (8 * K, sizeof (struct mark_queue)); _gst_mem.lastMarkQueue = &_gst_mem.markQueue[8 * K]; } void _gst_update_object_memory_oop (OOP oop) { gst_object_memory data; /* Ensure the statistics are coherent. */ for (;;) { OOP floatOOP; data = (gst_object_memory) OOP_TO_OBJ (oop); data->bytesPerOOP = FROM_INT (sizeof (PTR)); data->bytesPerOTE = FROM_INT (sizeof (struct oop_s) + sizeof (gst_object_header)); data->edenSize = FROM_INT (_gst_mem.eden.totalSize); data->survSpaceSize = FROM_INT (_gst_mem.active_half->totalSize); data->oldSpaceSize = FROM_INT (_gst_mem.old->heap_limit); data->fixedSpaceSize = FROM_INT (_gst_mem.fixed->heap_limit); data->edenUsedBytes = FROM_INT ((char *)_gst_mem.eden.allocPtr - (char *)_gst_mem.eden.minPtr); data->survSpaceUsedBytes = FROM_INT (_gst_mem.active_half->filled); data->oldSpaceUsedBytes = FROM_INT (_gst_mem.old->heap_total); data->fixedSpaceUsedBytes = FROM_INT (_gst_mem.fixed->heap_total); data->rememberedTableEntries = FROM_INT (_gst_mem.rememberedTableEntries); data->numScavenges = FROM_INT (_gst_mem.numScavenges); data->numGlobalGCs = FROM_INT (_gst_mem.numGlobalGCs); data->numCompactions = FROM_INT (_gst_mem.numCompactions); data->numGrowths = FROM_INT (_gst_mem.numGrowths); data->numOldOOPs = FROM_INT (_gst_mem.numOldOOPs); data->numFixedOOPs = FROM_INT (_gst_mem.numFixedOOPs); data->numWeakOOPs = FROM_INT (_gst_mem.numWeakOOPs); data->numOTEs = FROM_INT (_gst_mem.ot_size); data->numFreeOTEs = FROM_INT (_gst_mem.num_free_oops); data->allocFailures = FROM_INT (_gst_mem.old->failures + _gst_mem.fixed->failures); data->allocMatches = FROM_INT (_gst_mem.old->matches + _gst_mem.fixed->matches); data->allocSplits = FROM_INT (_gst_mem.old->splits + _gst_mem.fixed->splits); data->allocProbes = FROM_INT (_gst_mem.old->probes + _gst_mem.fixed->probes); /* Every allocation of a FloatD might cause a garbage collection! */ #define SET_FIELD(x) \ floatOOP = floatd_new (_gst_mem.x); \ if (data != (gst_object_memory) OOP_TO_OBJ (oop)) continue; \ data->x = floatOOP; SET_FIELD (timeBetweenScavenges); SET_FIELD (timeBetweenGlobalGCs); SET_FIELD (timeBetweenGrowths); SET_FIELD (timeToScavenge); SET_FIELD (timeToCollect); SET_FIELD (timeToCompact); SET_FIELD (reclaimedBytesPerScavenge); SET_FIELD (tenuredBytesPerScavenge); SET_FIELD (reclaimedBytesPerGlobalGC); SET_FIELD (reclaimedPercentPerScavenge); #undef SET_FIELD break; } } void _gst_init_oop_table (PTR address, size_t size) { int i; oop_heap = NULL; for (i = MAX_OOP_TABLE_SIZE; i && !oop_heap; i >>= 1) oop_heap = _gst_heap_create (address, i * sizeof (struct oop_s)); if (!oop_heap) nomemory (true); alloc_oop_table (size); _gst_nil_oop->flags = F_READONLY | F_OLD | F_REACHABLE; _gst_nil_oop->object = (gst_object) & _gst_nil_object; _gst_nil_object.objSize = FROM_INT (ROUNDED_WORDS (sizeof (struct gst_undefined_object))); _gst_true_oop->flags = F_READONLY | F_OLD | F_REACHABLE; _gst_true_oop->object = (gst_object) & _gst_boolean_objects[0]; _gst_false_oop->flags = F_READONLY | F_OLD | F_REACHABLE; _gst_false_oop->object = (gst_object) & _gst_boolean_objects[1]; _gst_boolean_objects[0].objSize = FROM_INT (ROUNDED_WORDS (sizeof (struct gst_boolean))); _gst_boolean_objects[1].objSize = FROM_INT (ROUNDED_WORDS (sizeof (struct gst_boolean))); _gst_boolean_objects[0].booleanValue = _gst_true_oop; _gst_boolean_objects[1].booleanValue = _gst_false_oop; for (i = 0; i < NUM_CHAR_OBJECTS; i++) { _gst_char_object_table[i].objSize = FROM_INT (ROUNDED_WORDS (sizeof (struct gst_character))); _gst_char_object_table[i].charVal = FROM_INT (i); _gst_mem.ot[i + CHAR_OBJECT_BASE].object = (gst_object) & _gst_char_object_table[i]; _gst_mem.ot[i + CHAR_OBJECT_BASE].flags = F_READONLY | F_OLD | F_REACHABLE; } } void alloc_oop_table (size_t size) { size_t bytes; _gst_mem.ot_size = size; bytes = (size - FIRST_OOP_INDEX) * sizeof (struct oop_s); _gst_mem.ot_base = (struct oop_s *) _gst_heap_sbrk (oop_heap, bytes); if (!_gst_mem.ot_base) nomemory (true); _gst_mem.ot = &_gst_mem.ot_base[-FIRST_OOP_INDEX]; _gst_nil_oop = &_gst_mem.ot[NIL_OOP_INDEX]; _gst_true_oop = &_gst_mem.ot[TRUE_OOP_INDEX]; _gst_false_oop = &_gst_mem.ot[FALSE_OOP_INDEX]; _gst_mem.num_free_oops = size; _gst_mem.last_allocated_oop = _gst_mem.last_swept_oop = _gst_mem.ot - 1; _gst_mem.next_oop_to_sweep = _gst_mem.ot - 1; } mst_Boolean _gst_realloc_oop_table (size_t newSize) { size_t bytes; bytes = (newSize - _gst_mem.ot_size) * sizeof (struct oop_s); if (bytes < 0) return (true); if (!_gst_heap_sbrk (oop_heap, bytes)) { /* try to recover. Note that we cannot move the OOP table like we do with the object data. */ nomemory (false); return (false); } _gst_mem.num_free_oops += newSize - _gst_mem.ot_size; _gst_mem.ot_size = newSize; return (true); } void _gst_dump_oop_table() { OOP oop; for (oop = _gst_mem.ot; oop <= _gst_mem.last_allocated_oop; oop++) if (!IS_OOP_FREE (oop)) { if (IS_OOP_VALID (oop)) _gst_display_oop (oop); else _gst_display_oop_short (oop); } } void _gst_dump_owners (OOP oop) { OOP oop2, lastOOP; for (oop2 = _gst_mem.ot_base, lastOOP = &_gst_mem.ot[_gst_mem.ot_size]; oop2 < lastOOP; oop2++) if UNCOMMON (IS_OOP_VALID (oop2) && is_owner(oop2, oop)) _gst_display_oop (oop2); } void _gst_check_oop_table () { OOP oop, lastOOP; for (oop = _gst_mem.ot_base, lastOOP = &_gst_mem.ot[_gst_mem.ot_size]; oop < lastOOP; oop++) { gst_object object; OOP *scanPtr; int n; if (!IS_OOP_VALID_GC (oop)) continue; object = OOP_TO_OBJ (oop); scanPtr = &object->objClass; if (oop->flags & F_CONTEXT) { gst_method_context ctx; intptr_t methodSP; ctx = (gst_method_context) object; methodSP = TO_INT (ctx->spOffset); n = ctx->contextStack + methodSP + 1 - object->data; } else n = NUM_OOPS (object) + 1; while (n--) { OOP pointedOOP = *scanPtr++; if (IS_OOP (pointedOOP) && (!IS_OOP_ADDR (pointedOOP) || !IS_OOP_VALID_GC (pointedOOP))) abort (); } } } void _gst_init_builtin_objects_classes (void) { int i; _gst_nil_object.objClass = _gst_undefined_object_class; _gst_boolean_objects[0].objClass = _gst_true_class; _gst_boolean_objects[1].objClass = _gst_false_class; for (i = 0; i < NUM_CHAR_OBJECTS; i++) _gst_char_object_table[i].objClass = _gst_char_class; } OOP _gst_find_an_instance (OOP class_oop) { OOP oop; PREFETCH_START (_gst_mem.ot, PREF_READ | PREF_NTA); for (oop = _gst_mem.ot; oop <= _gst_mem.last_allocated_oop; oop++) { PREFETCH_LOOP (oop, PREF_READ | PREF_NTA); if (IS_OOP_VALID (oop) && (OOP_CLASS (oop) == class_oop)) return (oop); } return (_gst_nil_oop); } void _gst_make_oop_non_weak (OOP oop) { weak_area_tree *entry = _gst_mem.weak_areas; oop->flags &= ~F_WEAK; _gst_mem.numWeakOOPs--; while (entry) { if (entry->oop == oop) { rb_erase (&entry->rb, (rb_node_t **) &_gst_mem.weak_areas); xfree (entry); break; } entry = (weak_area_tree *) (oop < entry->oop ? entry->rb.rb_left : entry->rb.rb_right); } } void _gst_make_oop_weak (OOP oop) { weak_area_tree *entry; weak_area_tree *node = NULL; rb_node_t **p = (rb_node_t **) &_gst_mem.weak_areas; oop->flags |= F_WEAK; _gst_mem.numWeakOOPs++; while (*p) { node = (weak_area_tree *) *p; if (oop < node->oop) p = &(*p)->rb_left; else if (oop > node->oop) p = &(*p)->rb_right; else return; } entry = (weak_area_tree *) xmalloc (sizeof (weak_area_tree)); entry->oop = oop; entry->rb.rb_parent = &node->rb; entry->rb.rb_left = entry->rb.rb_right = NULL; *p = &(entry->rb); rb_rebalance (&entry->rb, (rb_node_t **) &_gst_mem.weak_areas); } void _gst_swap_objects (OOP oop1, OOP oop2) { struct oop_s tempOOP; if (oop2->flags & F_WEAK) _gst_make_oop_non_weak (oop2); if (oop1->flags & F_WEAK) _gst_make_oop_non_weak (oop1); /* Put the two objects in the same generation. FIXME: this can be a cause of early tenuring, especially since one of them is often garbage! */ if ((oop1->flags & F_OLD) ^ (oop2->flags & F_OLD)) _gst_tenure_oop ((oop1->flags & F_OLD) ? oop2 : oop1); #ifdef ENABLE_JIT_TRANSLATION /* We may exchange the translations, but it is very likely that one of the objects does not have one yet, and the other one will never be needed anymore (the object becomes garbage). */ if (oop1->flags & F_XLAT) _gst_discard_native_code (oop1); if (oop2->flags & F_XLAT) _gst_discard_native_code (oop2); #endif tempOOP = *oop2; /* note structure assignment going on here */ *oop2 = *oop1; *oop1 = tempOOP; /* If the incremental GC has reached oop1 but not oop2 (or vice versa), this flag will end up in the wrong OOP, i.e. in the one that has already been scanned by the incremental GC. Restore things. */ if ((oop1->flags & F_REACHABLE) ^ (oop2->flags & F_REACHABLE)) { oop1->flags ^= F_REACHABLE; oop2->flags ^= F_REACHABLE; } if (oop2->flags & F_WEAK) _gst_make_oop_weak (oop2); if (oop1->flags & F_WEAK) _gst_make_oop_weak (oop1); } void _gst_make_oop_fixed (OOP oop) { gst_object newObj; int size; if (oop->flags & F_FIXED) return; if ((oop->flags & F_LOADED) == 0) { size = SIZE_TO_BYTES (TO_INT(oop->object->objSize)); newObj = (gst_object) _gst_mem_alloc (_gst_mem.fixed, size); if (!newObj) abort (); memcpy (newObj, oop->object, size); if ((oop->flags & F_OLD) == 0) _gst_mem.numOldOOPs++; else _gst_mem_free (_gst_mem.old, oop->object); oop->object = newObj; } oop->flags &= ~(F_SPACES | F_POOLED); oop->flags |= F_OLD | F_FIXED; } void _gst_tenure_oop (OOP oop) { gst_object newObj; if (oop->flags & F_OLD) return; if (!(oop->flags & F_FIXED)) { int size = SIZE_TO_BYTES (TO_INT(oop->object->objSize)); newObj = (gst_object) _gst_mem_alloc (_gst_mem.old, size); if (!newObj) abort (); memcpy (newObj, oop->object, size); _gst_mem.numOldOOPs++; oop->object = newObj; } oop->flags &= ~(F_SPACES | F_POOLED); oop->flags |= F_OLD; } gst_object _gst_alloc_obj (size_t size, OOP *p_oop) { OOP *newAllocPtr; gst_object p_instance; size = ROUNDED_BYTES (size); /* We don't want to have allocPtr pointing to the wrong thing during GC, so we use a local var to hold its new value */ newAllocPtr = _gst_mem.eden.allocPtr + BYTES_TO_SIZE (size); if UNCOMMON (size >= _gst_mem.big_object_threshold) return alloc_old_obj (size, p_oop); if UNCOMMON (newAllocPtr >= _gst_mem.eden.maxPtr) { _gst_scavenge (); newAllocPtr = _gst_mem.eden.allocPtr + size; } p_instance = (gst_object) _gst_mem.eden.allocPtr; _gst_mem.eden.allocPtr = newAllocPtr; *p_oop = alloc_oop (p_instance, _gst_mem.active_flag); p_instance->objSize = FROM_INT (BYTES_TO_SIZE (size)); return p_instance; } gst_object alloc_old_obj (size_t size, OOP *p_oop) { gst_object p_instance; size = ROUNDED_BYTES (size); /* If the object is big enough, we put it directly in oldspace. */ p_instance = (gst_object) _gst_mem_alloc (_gst_mem.old, size); if COMMON (p_instance) goto ok; _gst_global_gc (size); p_instance = (gst_object) _gst_mem_alloc (_gst_mem.old, size); if COMMON (p_instance) goto ok; compact (0); p_instance = (gst_object) _gst_mem_alloc (_gst_mem.old, size); if UNCOMMON (!p_instance) { /* !!! do something more reasonable in the future */ _gst_errorf ("Cannot recover, exiting..."); exit (1); } ok: *p_oop = alloc_oop (p_instance, F_OLD); p_instance->objSize = FROM_INT (BYTES_TO_SIZE (size)); return p_instance; } gst_object _gst_alloc_words (size_t size) { OOP *newAllocPtr; gst_object p_instance; /* We don't want to have allocPtr pointing to the wrong thing during GC, so we use a local var to hold its new value */ newAllocPtr = _gst_mem.eden.allocPtr + size; if UNCOMMON (newAllocPtr >= _gst_mem.eden.maxPtr) { nomemory (0); abort (); } if UNCOMMON (size >= _gst_mem.big_object_threshold) abort (); p_instance = (gst_object) _gst_mem.eden.allocPtr; _gst_mem.eden.allocPtr = newAllocPtr; p_instance->objSize = FROM_INT (size); return p_instance; } void reset_survivor_space (surv_space *space) { space->allocated = space->filled = 0; space->tenurePtr = space->allocPtr = space->topPtr = space->minPtr; } void oldspace_after_allocating (heap_data *h, heap_block *blk, size_t sz) { #ifdef MMAN_DEBUG_OUTPUT printf ("Allocating oldspace page at %p (%d)\n", blk, sz); #endif add_to_grey_list ((OOP *) blk, sz / sizeof (PTR)); _gst_mem.rememberedTableEntries++; } void oldspace_before_freeing (heap_data *h, heap_block *blk, size_t sz) { grey_area_node *node, *last, **next; #ifdef MMAN_DEBUG_OUTPUT printf ("Freeing oldspace page at %p (%d)\n", blk, sz); #endif /* Remove related entries from the remembered table. */ for (last = NULL, next = &_gst_mem.grey_pages.head; (node = *next); ) if (node->base >= (OOP *)blk && node->base + node->n <= (OOP *)( ((char *)blk) + sz)) { #ifdef MMAN_DEBUG_OUTPUT printf (" Remembered table entry removed %p..%p\n", node->base, node->base+node->n); #endif _gst_mem.rememberedTableEntries--; *next = node->next; xfree (node); } else { last = node; next = &(node->next); } _gst_mem.grey_pages.tail = last; _gst_mem_protect ((PTR) blk, sz, PROT_READ | PROT_WRITE); } heap_data * oldspace_nomemory (heap_data *h, size_t sz) { heap_data **p_heap; assert (h == _gst_mem.old || h == _gst_mem.fixed); p_heap = (h == _gst_mem.old ? &_gst_mem.old : &_gst_mem.fixed); if (!_gst_gc_running) _gst_global_gc (sz); else { /* Already garbage collecting, emergency growth just to satisfy tenuring necessities. */ int grow_amount_to_satisfy_rate = h->heap_limit * (100.0 + _gst_mem.space_grow_rate) / 100; int grow_amount_to_satisfy_threshold = (sz + h->heap_total) * 100.0 /_gst_mem.grow_threshold_percent; h->heap_limit = MAX (grow_amount_to_satisfy_rate, grow_amount_to_satisfy_threshold); } return *p_heap; } #ifndef NO_SIGSEGV_HANDLING int oldspace_sigsegv_handler (void* fault_address, int serious) { static int reentering, reentered; void *page; if UNCOMMON (reentering) { reentered = 1; abort(); } else { reentered = 0; reentering = 1; } page = (char *) fault_address - ((intptr_t) fault_address & (getpagesize() - 1)); errno = 0; if (_gst_mem_protect (page, getpagesize(), PROT_READ | PROT_WRITE) == -1 && (errno == ENOMEM || errno == EFAULT || errno == EACCES || errno == EINVAL)) { #if defined (MMAN_DEBUG_OUTPUT) printf ("Plain old segmentation violation -- address = %p\n", page); #endif reentering = 0; abort(); } /* Try accessing the page */ (void) *(volatile char *) fault_address; reentering = 0; #if defined (MMAN_DEBUG_OUTPUT) printf ("Unprotected %p (SIGSEGV at %p)\n", page, fault_address); #endif _gst_mem.rememberedTableEntries++; add_to_grey_list ((PTR) page, getpagesize() / sizeof (PTR)); return !reentered; } #endif void update_stats (unsigned long *last, double *between, double *duration) { unsigned long now = _gst_get_milli_time (); unsigned long since = now - *last; if (between) *between = _gst_mem.factor * *between + (1 - _gst_mem.factor) * since; if (duration) *duration = _gst_mem.factor * *duration + (1 - _gst_mem.factor) * since; else *last = now; } void _gst_grow_memory_to (size_t spaceSize) { compact (spaceSize); } void grow_memory_no_compact (size_t new_heap_limit) { _gst_mem.old->heap_limit = new_heap_limit; _gst_mem.fixed->heap_limit = new_heap_limit; _gst_mem.numGrowths++; update_stats (&stats.timeOfLastGrowth, &_gst_mem.timeBetweenGrowths, NULL); } void compact (size_t new_heap_limit) { OOP oop; heap_data *new_heap = init_old_space ( new_heap_limit ? new_heap_limit : _gst_mem.old->heap_limit); if (new_heap_limit) { _gst_mem.fixed->heap_limit = new_heap_limit; _gst_mem.numGrowths++; update_stats (&stats.timeOfLastGrowth, &_gst_mem.timeBetweenGrowths, NULL); stats.timeOfLastCompaction = stats.timeOfLastGrowth; } else { /* Do not copy garbage. */ _gst_finish_incremental_gc (); _gst_mem.numCompactions++; update_stats (&stats.timeOfLastCompaction, NULL, NULL); } _gst_fixup_object_pointers (); /* Now do the copying loop which will compact oldspace. */ PREFETCH_START (_gst_mem.ot, PREF_READ | PREF_NTA); for (oop = _gst_mem.ot; oop < &_gst_mem.ot[_gst_mem.ot_size]; oop++) { PREFETCH_LOOP (oop, PREF_READ | PREF_NTA); if ((oop->flags & (F_OLD | F_FIXED | F_LOADED)) == F_OLD) { gst_object new; size_t size = SIZE_TO_BYTES (TO_INT (oop->object->objSize)); new = _gst_mem_alloc (new_heap, size); memcpy (new, oop->object, size); _gst_mem_free (_gst_mem.old, oop->object); oop->object = new; } } xfree (_gst_mem.old); _gst_mem.old = new_heap; new_heap->nomemory = oldspace_nomemory; _gst_restore_object_pointers (); update_stats (&stats.timeOfLastCompaction, NULL, &_gst_mem.timeToCompact); } void _gst_global_compact () { _gst_global_gc (0); compact (0); } void _gst_global_gc (int next_allocation) { const char *s; int old_limit; _gst_mem.numGlobalGCs++; old_limit = _gst_mem.old->heap_limit; _gst_mem.old->heap_limit = 0; if (!_gst_gc_running++ && _gst_gc_message && _gst_verbosity >= 2 && !_gst_regression_testing) { /* print the first part of this message before we finish scanning oop table for live ones, so that the delay caused by this scanning is apparent. Note the use of stderr for the printed message. The idea here was that generated output could be treated as Smalltalk code, HTML or whatever else you want without harm. */ fflush (stdout); fprintf (stderr, "\"Global garbage collection... "); fflush (stderr); } update_stats (&stats.timeOfLastGlobalGC, &_gst_mem.timeBetweenGlobalGCs, NULL); _gst_finish_incremental_gc (); _gst_fixup_object_pointers (); copy_oops (); _gst_tenure_all_survivors (); mark_oops (); _gst_mem.live_flags &= ~F_OLD; _gst_mem.live_flags |= F_REACHABLE; check_weak_refs (); _gst_restore_object_pointers (); #if defined (GC_DEBUGGING) _gst_check_oop_table (); #endif reset_incremental_gc (_gst_mem.ot); update_stats (&stats.timeOfLastGlobalGC, NULL, &_gst_mem.timeToCollect); s = "done"; /* Compaction and growth tests are only done during the outermost GC (well I am not sure that GC's can nest...) */ if (old_limit) { old_limit = MAX (old_limit, _gst_mem.old->heap_total); /* if memory is still low, go all the way on sweeping */ if UNCOMMON ((next_allocation + _gst_mem.old->heap_total) * 100.0 / old_limit > _gst_mem.grow_threshold_percent) { int target_limit; _gst_finish_incremental_gc (); /* Check if it's time to compact the heap. Compaction make the most sense if there were lots of garbage. And the heap limit is shrunk to avoid excessive garbage accumulation in the next round */ target_limit = MAX(_gst_mem.eden.totalSize, ((next_allocation + _gst_mem.old->heap_total) * (100.0 + _gst_mem.space_grow_rate) / _gst_mem.grow_threshold_percent)); if (target_limit < old_limit) { s = "done, heap compacted"; compact (0); grow_memory_no_compact (target_limit); } } /* Check if it's time to grow the heap. */ if UNCOMMON ((next_allocation + _gst_mem.old->heap_total) * 100.0 / old_limit > _gst_mem.grow_threshold_percent || (next_allocation + _gst_mem.fixed->heap_total) * 100.0 / _gst_mem.fixed->heap_limit > _gst_mem.grow_threshold_percent) { int grow_amount_to_satisfy_rate = old_limit * (100.0 + _gst_mem.space_grow_rate) / 100; int grow_amount_to_satisfy_threshold = (next_allocation + _gst_mem.old->heap_total) * 100.0 /_gst_mem.grow_threshold_percent; s = "done, heap grown"; grow_memory_no_compact (MAX (grow_amount_to_satisfy_rate, grow_amount_to_satisfy_threshold)); } } if (!--_gst_gc_running && _gst_gc_message && _gst_verbosity >= 2 && !_gst_regression_testing) { fprintf (stderr, "%s\"\n", s); fflush (stderr); } /* If the heap was grown, don't reset the old limit! */ if (!_gst_mem.old->heap_limit) _gst_mem.old->heap_limit = old_limit; _gst_invalidate_croutine_cache (); mourn_objects (); } void _gst_scavenge (void) { int oldBytes, reclaimedBytes, tenuredBytes, reclaimedPercent; /* Check if oldspace had to be grown in emergency. */ size_t prev_heap_limit = _gst_mem.old->heap_limit; /* Force a GC as soon as possible if we're low on OOPs or memory. */ if UNCOMMON (_gst_mem.num_free_oops < LOW_WATER_OOP_THRESHOLD || _gst_mem.old->heap_total * 100.0 / _gst_mem.old->heap_limit > _gst_mem.grow_threshold_percent || _gst_mem.fixed->heap_total * 100.0 / _gst_mem.fixed->heap_limit > _gst_mem.grow_threshold_percent) { _gst_global_gc (0); _gst_incremental_gc_step (); return; } if (!_gst_gc_running++ && _gst_gc_message && _gst_verbosity > 2 && !_gst_regression_testing) { /* print the first part of this message before we finish scanning oop table for live ones, so that the delay caused by this scanning is apparent. Note the use of stderr for the printed message. The idea here was that generated output could be treated as Smalltalk code, HTML or whatever else you want without harm. */ fflush (stdout); fprintf (stderr, "\"Scavenging... "); fflush (stderr); } oldBytes = (char *) _gst_mem.eden.allocPtr - (char *) _gst_mem.eden.minPtr + _gst_mem.active_half->filled; _gst_mem.numScavenges++; update_stats (&stats.timeOfLastScavenge, &_gst_mem.timeBetweenScavenges, NULL); _gst_finish_incremental_gc (); _gst_fixup_object_pointers (); copy_oops (); check_weak_refs (); _gst_restore_object_pointers (); reset_incremental_gc (_gst_mem.ot); update_stats (&stats.timeOfLastScavenge, NULL, &_gst_mem.timeToScavenge); reclaimedBytes = oldBytes - _gst_mem.active_half->allocated; if (reclaimedBytes < 0) reclaimedBytes = 0; tenuredBytes = _gst_mem.active_half->allocated - _gst_mem.active_half->filled; reclaimedPercent = 100.0 * reclaimedBytes / oldBytes; if (!--_gst_gc_running && _gst_gc_message && _gst_verbosity > 2 && !_gst_regression_testing) { fprintf (stderr, "%d%% reclaimed, done\"\n", reclaimedPercent); fflush (stderr); } _gst_mem.reclaimedBytesPerScavenge = _gst_mem.factor * reclaimedBytes + (1 - _gst_mem.factor) * _gst_mem.reclaimedBytesPerScavenge; _gst_mem.reclaimedPercentPerScavenge = _gst_mem.factor * reclaimedPercent + (1 - _gst_mem.factor) * _gst_mem.reclaimedPercentPerScavenge; _gst_mem.tenuredBytesPerScavenge = _gst_mem.factor * tenuredBytes + (1 - _gst_mem.factor) * _gst_mem.tenuredBytesPerScavenge; _gst_invalidate_croutine_cache (); mourn_objects (); /* If tenuring had to grow oldspace, do a global garbage collection now. */ if (_gst_mem.old->heap_limit > prev_heap_limit) { _gst_global_gc (0); _gst_incremental_gc_step (); return; } } mst_Boolean incremental_gc_running () { return (_gst_mem.next_oop_to_sweep > _gst_mem.last_swept_oop); } void _gst_finish_incremental_gc () { OOP oop, firstOOP; #if defined (GC_DEBUG_OUTPUT) printf ("Completing sweep (%p...%p), validity flags %x\n", _gst_mem.last_swept_oop, _gst_mem.next_oop_to_sweep, _gst_mem.live_flags); #endif PREFETCH_START (_gst_mem.next_oop_to_sweep, PREF_BACKWARDS | PREF_READ | PREF_NTA); for (oop = _gst_mem.next_oop_to_sweep, firstOOP = _gst_mem.last_swept_oop; oop > firstOOP; oop--) { PREFETCH_LOOP (oop, PREF_BACKWARDS | PREF_READ | PREF_NTA); if (IS_OOP_VALID_GC (oop)) { maybe_release_xlat (oop); oop->flags &= ~F_REACHABLE; } else { _gst_sweep_oop (oop); _gst_mem.num_free_oops++; if (oop == _gst_mem.last_allocated_oop) _gst_mem.last_allocated_oop--; } } _gst_mem.next_oop_to_sweep = oop; _gst_finished_incremental_gc (); } void _gst_finished_incremental_gc (void) { if (_gst_mem.live_flags & F_OLD) return; _gst_mem.live_flags &= ~F_REACHABLE; _gst_mem.live_flags |= F_OLD; if (stats.reclaimedOldSpaceBytesSinceLastGlobalGC) { _gst_mem.reclaimedBytesPerGlobalGC = _gst_mem.factor * stats.reclaimedOldSpaceBytesSinceLastGlobalGC + (1 - _gst_mem.factor) * _gst_mem.reclaimedBytesPerGlobalGC; stats.reclaimedOldSpaceBytesSinceLastGlobalGC = 0; } #ifdef ENABLE_JIT_TRANSLATION /* Go and really free the blocks associated to garbage collected native code. */ _gst_free_released_native_code (); #endif } mst_Boolean _gst_incremental_gc_step () { OOP oop, firstOOP; int i; if (!incremental_gc_running ()) return true; i = 0; firstOOP = _gst_mem.last_swept_oop; for (oop = _gst_mem.next_oop_to_sweep; oop > firstOOP; oop--) { if (IS_OOP_VALID_GC (oop)) { maybe_release_xlat (oop); oop->flags &= ~F_REACHABLE; } else { _gst_sweep_oop (oop); _gst_mem.num_free_oops++; if (oop == _gst_mem.last_allocated_oop) _gst_mem.last_allocated_oop--; if (++i == INCREMENTAL_SWEEP_STEP) { _gst_mem.next_oop_to_sweep = oop - 1; return false; } } } _gst_mem.next_oop_to_sweep = oop; _gst_finished_incremental_gc (); return true; } void reset_incremental_gc (OOP firstOOP) { OOP oop; /* This loop is the same as that in alloc_oop. Skip low OOPs that are allocated */ for (oop = firstOOP; IS_OOP_VALID_GC (oop); oop->flags &= ~F_REACHABLE, oop++) #if defined(ENABLE_JIT_TRANSLATION) if (oop->flags & F_XLAT) { if (oop->flags & F_XLAT_REACHABLE) /* Reachable, and referenced by active contexts. Keep it around. */ oop->flags &= ~F_XLAT_2NDCHANCE; else { /* Reachable, but not referenced by active contexts. We give it a second chance... */ if (oop->flags & F_XLAT_2NDCHANCE) _gst_release_native_code (oop); oop->flags ^= F_XLAT_2NDCHANCE; } } #else ; #endif /* Initialize these here so that IS_OOP_VALID works correctly. */ _gst_mem.next_oop_to_sweep = _gst_mem.last_allocated_oop; _gst_mem.last_swept_oop = oop - 1; #ifdef NO_INCREMENTAL_GC _gst_finish_incremental_gc (); #else /* Skip high OOPs that are unallocated. */ for (oop = _gst_mem.last_allocated_oop; !IS_OOP_VALID (oop); oop--) _gst_sweep_oop (oop); _gst_mem.last_allocated_oop = oop; _gst_mem.next_oop_to_sweep = oop; #endif _gst_mem.num_free_oops = _gst_mem.ot_size - (_gst_mem.last_allocated_oop - _gst_mem.ot); /* Check if it's time to grow the OOP table. */ if (_gst_mem.num_free_oops * 100.0 / _gst_mem.ot_size < 100 - _gst_mem.grow_threshold_percent) _gst_realloc_oop_table (_gst_mem.ot_size * (100 + _gst_mem.space_grow_rate) / 100); #if defined (GC_DEBUG_OUTPUT) printf ("Last allocated OOP %p\n" "Next OOP swept top to bottom %p, highest swept bottom to top %p\n", _gst_mem.last_allocated_oop, _gst_mem.next_oop_to_sweep, _gst_mem.last_swept_oop); #endif } void _gst_sweep_oop (OOP oop) { if (IS_OOP_FREE (oop)) return; #ifdef ENABLE_JIT_TRANSLATION if (oop->flags & F_XLAT) /* Unreachable, always free the native code. It is *not* optional to free the code in this case -- and I'm not talking about memory leaks: a different method could use the same OOP as this one and the old method would be executed instead of the new one! */ _gst_release_native_code (oop); #endif if UNCOMMON (oop->flags & F_WEAK) _gst_make_oop_non_weak (oop); /* Free unreachable oldspace objects. */ if UNCOMMON (oop->flags & F_FIXED) { _gst_mem.numOldOOPs--; stats.reclaimedOldSpaceBytesSinceLastGlobalGC += SIZE_TO_BYTES (TO_INT (OOP_TO_OBJ (oop)->objSize)); if ((oop->flags & F_LOADED) == 0) _gst_mem_free (_gst_mem.fixed, oop->object); } else if UNCOMMON (oop->flags & F_OLD) { _gst_mem.numOldOOPs--; stats.reclaimedOldSpaceBytesSinceLastGlobalGC += SIZE_TO_BYTES (TO_INT (OOP_TO_OBJ (oop)->objSize)); if ((oop->flags & F_LOADED) == 0) _gst_mem_free (_gst_mem.old, oop->object); } oop->flags = 0; } void mourn_objects (void) { gst_object array; long size; gst_processor_scheduler processor; size = _gst_buffer_size () / sizeof (OOP); if (!size) return; processor = (gst_processor_scheduler) OOP_TO_OBJ (_gst_processor_oop); if (!IS_NIL (processor->gcArray)) { _gst_errorf ("Too many garbage collections, finalizers missed!"); _gst_errorf ("This is a bug, please report."); } else { /* Copy the buffer into an Array */ array = new_instance_with (_gst_array_class, size, &processor->gcArray); _gst_copy_buffer (array->data); if (!IS_NIL (processor->gcSemaphore)) { static async_queue_entry e; e.func = _gst_do_async_signal; e.data = processor->gcSemaphore; _gst_async_call_internal (&e); } else { _gst_errorf ("Running finalizers before initialization."); abort (); } } } #define IS_QUEUE_SPLIT(q) ((q)->topPtr != (q)->allocPtr) OOP * queue_get (surv_space *q, int n) { OOP *result = q->tenurePtr; q->filled -= n * sizeof (PTR); q->tenurePtr += n; /* Check if the read pointer has to wrap. */ if (q->tenurePtr == q->topPtr) { q->tenurePtr = q->minPtr; q->topPtr = q->allocPtr; } return result; } OOP * queue_put (surv_space *q, OOP *src, int n) { OOP *result, *newAlloc; for (;;) { result = q->allocPtr; newAlloc = q->allocPtr + n; #if defined(GC_DEBUG_OUTPUT) printf ("Top %p alloc %p tenure %p\n", q->topPtr, q->allocPtr, q->tenurePtr); #endif if (IS_QUEUE_SPLIT (q) && UNCOMMON (newAlloc > q->tenurePtr)) /* We tenure old objects as we copy more objects into the circular survivor space. */ { #if defined(GC_DEBUG_OUTPUT) printf ("Tenure: current max %p, needed %p\n", q->tenurePtr, newAlloc); #endif tenure_one_object(); continue; } if UNCOMMON (newAlloc > q->maxPtr) { #if defined(GC_DEBUG_OUTPUT) printf ("Wrap: survivor space ends at %p, needed %p\n", q->maxPtr, newAlloc); #endif q->topPtr = q->allocPtr; q->allocPtr = q->minPtr; continue; } break; } if (!IS_QUEUE_SPLIT (q)) /* We are still extending towards the top. Push further the valid area (which is space...topPtr and minPtr...allocPtr if topPtr != allocPtr (not circular yet), space...allocPtr if topPtr == allocPtr (circular). */ q->topPtr = newAlloc; q->filled += n * sizeof (PTR); q->allocated += n * sizeof (PTR); q->allocPtr = newAlloc; memcpy (result, src, n * sizeof (PTR)); return result; } void tenure_one_object () { OOP oop; oop = *_gst_mem.tenuring_queue.tenurePtr; #if defined(GC_DEBUG_OUTPUT) printf (" "); _gst_display_oop (oop); #endif if (_gst_mem.scan.current == oop) { #if defined(GC_DEBUG_OUTPUT) printf ("Tenured OOP %p was being scanned\n", oop); #endif _gst_tenure_oop (oop); _gst_mem.scan.at = (OOP *) oop->object; } else if (_gst_mem.scan.queue_at == _gst_mem.tenuring_queue.tenurePtr) { #if defined(GC_DEBUG_OUTPUT) printf ("Tenured OOP %p had not been scanned yet\n", oop); #endif /* Since tenurePtr is going to advance by a place, we must keep the Cheney scan pointer up to date. Check if it has to wrap! */ _gst_mem.scan.queue_at++; if (_gst_mem.scan.queue_at >= _gst_mem.tenuring_queue.topPtr && IS_QUEUE_SPLIT (&_gst_mem.tenuring_queue)) _gst_mem.scan.queue_at = _gst_mem.tenuring_queue.minPtr; _gst_tenure_oop (oop); add_grey_object (oop); } else _gst_tenure_oop (oop); queue_get (&_gst_mem.tenuring_queue, 1); queue_get (_gst_mem.active_half, TO_INT (oop->object->objSize)); } void _gst_grey_oop_range (PTR from, size_t size) { volatile char *last, *page; for (last = ((char *)from) + size, page = ((char *)from) - ((intptr_t) from & (getpagesize() - 1)); page < last; page += getpagesize()) *page = *page; } void add_grey_object (OOP oop) { grey_area_node *entry; gst_object obj = OOP_TO_OBJ (oop); int numFields = scanned_fields_in (obj, oop->flags); OOP *base = &(obj->objClass); if (!numFields) return; /* For ephemeron, skip the first field and the class. */ if (oop->flags & F_EPHEMERON) { numFields -= &(obj->data[1]) - base; base = &(obj->data[1]); } entry = (grey_area_node *) xmalloc (sizeof (grey_area_node)); entry->base = base; entry->n = numFields; entry->oop = oop; entry->next = NULL; if (_gst_mem.grey_areas.tail) _gst_mem.grey_areas.tail->next = entry; else _gst_mem.grey_areas.head = entry; _gst_mem.grey_areas.tail = entry; } void add_to_grey_list (OOP *base, int n) { grey_area_node *entry = (grey_area_node *) xmalloc (sizeof (grey_area_node)); entry->base = base; entry->n = n; entry->oop = NULL; entry->next = NULL; if (_gst_mem.grey_pages.tail) _gst_mem.grey_pages.tail->next = entry; else _gst_mem.grey_pages.head = entry; _gst_mem.grey_pages.tail = entry; } void _gst_tenure_all_survivors () { OOP oop; while (_gst_mem.tenuring_queue.filled) { oop = *queue_get (&_gst_mem.tenuring_queue, 1); _gst_tenure_oop (oop); } } void check_weak_refs () { rb_node_t *node; rb_traverse_t t; for (node = rb_first(&(_gst_mem.weak_areas->rb), &t); node; node = rb_next (&t)) { weak_area_tree *area = (weak_area_tree *) node; mst_Boolean mourn = false; OOP *field, oop; int n; oop = area->oop; if (!IS_OOP_VALID_GC (oop)) continue; for (field = (OOP *) oop->object + OBJ_HEADER_SIZE_WORDS, n = NUM_OOPS (oop->object); n--; field++) { OOP oop = *field; if (IS_INT (oop)) continue; if (!IS_OOP_VALID_GC (oop)) { mourn = true; *field = _gst_nil_oop; } } if (mourn) _gst_add_buf_pointer (area->oop); } } void copy_oops (void) { _gst_reset_buffer (); /* Do the flip! */ _gst_mem.live_flags ^= F_SPACES; _gst_mem.active_flag ^= F_SPACES; _gst_mem.active_half = &_gst_mem.surv[_gst_mem.active_flag == F_ODD]; reset_survivor_space (_gst_mem.active_half); reset_survivor_space (&_gst_mem.tenuring_queue); /* And the pointer for Cheney scanning. */ _gst_mem.scan.queue_at = _gst_mem.tenuring_queue.tenurePtr; /* Do these first, they are more likely to stay around for long, so it makes sense to make their tenuring more likely (the first copied objects are also tenured first). */ scan_grey_pages (); _gst_copy_registered_oops (); cheney_scan (); /* Do these last since they are often alive only till the next scavenge. */ _gst_copy_processor_registers (); cheney_scan (); scan_grey_objects (); /* Reset the new-space pointers */ _gst_empty_context_pool (); _gst_mem.eden.allocPtr = _gst_mem.eden.minPtr; } void _gst_print_grey_list (mst_Boolean check_pointers) { grey_area_node *node; OOP *pOOP, oop; int i, n; for (n = 0, node = _gst_mem.grey_pages.head; node; node = node->next, n++) { int new_pointers = 0; if (check_pointers) for (new_pointers = 0, pOOP = node->base, i = node->n; i--; pOOP++) { PREFETCH_LOOP (pOOP, PREF_READ | PREF_NTA); oop = *pOOP; /* Not all addresses are known to contain valid OOPs! */ if (!IS_OOP_ADDR (oop)) continue; if (!IS_OOP_NEW (oop)) continue; new_pointers++; } printf ("%11p%c ", node->base, new_pointers == 0 ? ' ' : '*'); if ((n & 3) == 3) putchar ('\n'); } if (_gst_mem.grey_pages.tail) printf (" (tail = %12p)", _gst_mem.grey_pages.tail->base); printf ("\n"); } void scan_grey_pages () { grey_area_node *node, **next, *last; OOP *pOOP, oop; int i, n; #if defined (MMAN_DEBUG_OUTPUT) printf ("Pages on the grey list:\n"); _gst_print_grey_list (true); #endif for (last = NULL, next = &_gst_mem.grey_pages.head; (node = *next); ) { #if defined(GC_DEBUG_OUTPUT) || defined(MMAN_DEBUG_OUTPUT) printf ("Scanning grey page %p...%p ", node->base, node->base + node->n); #if defined(GC_DEBUG_OUTPUT) putchar ('\n'); #else fflush (stdout); #endif #endif PREFETCH_START (node->base, PREF_READ | PREF_NTA); for (n = 0, pOOP = node->base, i = node->n; i--; pOOP++) { PREFETCH_LOOP (pOOP, PREF_READ | PREF_NTA); oop = *pOOP; /* Not all addresses are known to contain valid OOPs! */ if (!IS_OOP_ADDR (oop)) continue; if (!IS_OOP_NEW (oop)) continue; n++; if (!IS_OOP_COPIED (oop)) _gst_copy_an_oop (oop); } #if !defined (NO_SIGSEGV_HANDLING) if (!n) { /* The entry was temporary, or we found no new-space pointers in it. Delete it and make the page read-only. */ #if defined (MMAN_DEBUG_OUTPUT) printf ("Protecting %p\n", node->base); #endif _gst_mem.rememberedTableEntries--; _gst_mem_protect ((PTR) node->base, node->n * sizeof(OOP), PROT_READ); *next = node->next; xfree (node); } else #endif { #if defined (MMAN_DEBUG_OUTPUT) printf ("Found %d pointers\n", n); #endif last = node; next = &(node->next); } cheney_scan (); } _gst_mem.grey_pages.tail = last; #if defined (MMAN_DEBUG_OUTPUT) printf ("Pages left on the grey list:\n"); _gst_print_grey_list (false); #endif } void scan_grey_objects() { grey_area_node *node, *next; OOP oop; gst_object obj; for (next = _gst_mem.grey_areas.head; (node = next); ) { oop = node->oop; obj = OOP_TO_OBJ (oop); if (oop->flags & F_EPHEMERON) /* Objects might have moved, so update node->base. */ node->base = (OOP *) &obj->data[1]; #if defined(GC_DEBUG_OUTPUT) printf ("Scanning grey range %p...%p (%p)\n", node->base, node->base + node->n, oop); #endif _gst_copy_oop_range (node->base, node->base + node->n); if (oop->flags & F_EPHEMERON) { OOP key = obj->data[0]; /* Copy the key, mourn the object if it was not reachable. */ if (!IS_OOP_COPIED (key)) { _gst_copy_an_oop (key); _gst_add_buf_pointer (oop); } } _gst_mem.grey_areas.head = next = node->next; xfree (node); if (!next) _gst_mem.grey_areas.tail = NULL; cheney_scan (); /* The scan might have greyed more areas. */ if (!next) next = _gst_mem.grey_areas.head; } } int scanned_fields_in (gst_object object, int flags) { if COMMON (!(flags & (F_WEAK | F_CONTEXT))) { int size = NUM_OOPS (object); return object->data + size - &object->objClass; } if COMMON (flags & F_CONTEXT) { gst_method_context ctx; intptr_t methodSP; ctx = (gst_method_context) object; methodSP = TO_INT (ctx->spOffset); return ctx->contextStack + methodSP + 1 - &ctx->objClass; } /* Weak object, only mark the class. */ return 1; } void cheney_scan (void) { #if defined(GC_DEBUG_OUTPUT) printf ("Starting Cheney scan\n"); #endif while (_gst_mem.scan.queue_at != _gst_mem.tenuring_queue.allocPtr) { OOP oop; int i, numFields; if (_gst_mem.scan.queue_at >= _gst_mem.tenuring_queue.topPtr) _gst_mem.scan.queue_at = _gst_mem.tenuring_queue.minPtr; if (_gst_mem.scan.queue_at == _gst_mem.tenuring_queue.allocPtr) break; oop = *_gst_mem.scan.queue_at; #if defined(GC_DEBUGGING) if (!IS_OOP_ADDR (oop)) abort(); #endif #if defined(GC_DEBUG_OUTPUT) printf (">Scan "); _gst_display_oop (oop); #endif _gst_mem.scan.current = oop; _gst_mem.scan.queue_at++; if (oop->flags & F_EPHEMERON) continue; _gst_mem.scan.at = (OOP *) OOP_TO_OBJ (oop); numFields = scanned_fields_in (OOP_TO_OBJ (oop), oop->flags); /* The +1 below is to skip the size field. */ for (i = 0; i < numFields; i++) MAYBE_COPY_OOP (_gst_mem.scan.at[i+1]); } #if defined(GC_DEBUG_OUTPUT) printf ("Ending Cheney scan\n"); #endif } void _gst_copy_oop_range (OOP *curOOP, OOP *atEndOOP) { OOP *pOOP; for (pOOP = curOOP; pOOP < atEndOOP; pOOP++) MAYBE_COPY_OOP (*pOOP); } void _gst_copy_an_oop (OOP oop) { int i, n; do { gst_object obj; OOP *pData; obj = OOP_TO_OBJ (oop); pData = (OOP *) obj; #if defined(GC_DEBUG_OUTPUT) printf (">Copy "); _gst_display_oop (oop); #endif #if defined (GC_DEBUGGING) if UNCOMMON (!IS_INT (obj->objSize)) { printf ("Size not an integer in OOP %p (%p)\n", oop, obj); abort (); } if UNCOMMON (TO_INT (obj->objSize) < 2) { printf ("Invalid size for OOP %p (%p)\n", oop, obj); abort (); } if UNCOMMON (oop->flags == 0) { printf ("Free OOP %p was referenced\n", oop); abort (); } if UNCOMMON ((oop->flags & F_OLD) || IS_SURVIVOR_ADDR(obj, _gst_mem.active_half == &_gst_mem.surv[1])) { printf ("Copying an already copied object\n"); abort (); return; } #endif queue_put (&_gst_mem.tenuring_queue, &oop, 1); obj = oop->object = (gst_object) queue_put (_gst_mem.active_half, pData, TO_INT (obj->objSize)); oop->flags &= ~(F_SPACES | F_POOLED); oop->flags |= _gst_mem.active_flag; /* Look for a child that has not been copied and move it near the object. This improves the locality of reference. We do not copy the class (that's the reason for the -1 here). */ n = scanned_fields_in (obj, oop->flags) - 1; if (oop->flags & F_EPHEMERON) { /* For ephemerons, do the work later. */ add_grey_object (oop); return; } for (i = 0; i < n; i++) { OOP newOOP = obj->data[i]; if (!IS_OOP_COPIED (newOOP)) { oop = newOOP; break; } } } while (i < n); } void mark_oops (void) { _gst_reset_buffer (); _gst_mark_registered_oops (); _gst_mark_processor_registers (); mark_ephemeron_oops (); } void mark_ephemeron_oops (void) { OOP *pOOP, *pDeadOOP, *base; int i, size; /* Make a local copy of the buffer */ size = _gst_buffer_size (); base = alloca (size); _gst_copy_buffer (base); _gst_reset_buffer (); size /= sizeof (PTR); /* First pass: distinguish objects whose key was reachable from the outside by clearing their F_EPHEMERON bit. */ for (pOOP = base, i = size; i--; pOOP++) { OOP oop = *pOOP; gst_object obj = OOP_TO_OBJ(oop); OOP key = obj->data[0]; if (key->flags & F_REACHABLE) oop->flags &= ~F_EPHEMERON; key->flags |= F_REACHABLE; } for (pOOP = pDeadOOP = base, i = size; i--; ) { OOP oop = *pOOP++; gst_object obj = OOP_TO_OBJ(oop); OOP key = obj->data[0]; int num = NUM_OOPS(obj); int j; /* Find if the key is reachable from the objects (so that we can mourn the ephemeron if this is not so). */ key->flags &= ~F_REACHABLE; for (j = 1; j < num; j++) MAYBE_MARK_OOP (obj->data[j]); /* Remember that above we cleared F_EPHEMERON if the key is alive. */ if (!IS_OOP_MARKED (key) && (oop->flags & F_EPHEMERON)) *pDeadOOP++ = oop; /* Ok, now mark the key. */ MAYBE_MARK_OOP (key); /* Restore the flag in case it was cleared. */ oop->flags |= F_EPHEMERON; } /* If more ephemerons were reachable from the object, go on... */ if (_gst_buffer_size ()) mark_ephemeron_oops (); _gst_add_buf_data (base, (char *) pDeadOOP - (char *) base); } #define TAIL_MARK_OOP(newOOP) do { \ PREFETCH_ADDR ((newOOP)->object, PREF_READ | PREF_NTA); \ oop = (newOOP); \ goto markOne; /* tail recurse!!! */ \ } while(0) #define TAIL_MARK_OOPRANGE(firstOOP, oopAtEnd) do { \ PREFETCH_START (firstOOP, PREF_READ | PREF_NTA); \ curOOP = (OOP *)(firstOOP); \ atEndOOP = (OOP *)(oopAtEnd); \ oop = NULL; \ goto markRange; \ } while(0) void _gst_mark_an_oop_internal (OOP oop) { OOP *curOOP, *atEndOOP; struct mark_queue *markQueue = _gst_mem.markQueue; struct mark_queue *lastMarkQueue = _gst_mem.lastMarkQueue; struct mark_queue *currentMarkQueue = markQueue; goto markOne; markRange: { OOP firstOOP = NULL; /* The first unmarked OOP is used for tail recursion. */ while (curOOP < atEndOOP) { oop = *curOOP++; if (IS_OOP (oop) && !IS_OOP_MARKED (oop)) { oop->flags |= F_REACHABLE; firstOOP = oop; break; } } /* The second unmarked OOP is the first that is placed on the mark queue. TODO: split REACHABLE and VISITED flags. An object is marked REACHABLE here, and REACHABLE|VISITED in the markOne label. At the end of GC, all REACHABLE objects are also VISITED. The above loop should seek an object that is not VISITED so that it can be marked. For the loop below, however, REACHABLE objects are known to be somewhere else on the mark stack, and can be skipped. Skipping objects after the first unmarked OOP is still useful, because it keeps the stack size a bit lower in the relatively common case of many integer or nil instance variables. */ while (curOOP < atEndOOP) { oop = *curOOP; if (IS_OOP (oop) && !IS_OOP_MARKED (oop)) { if (currentMarkQueue == lastMarkQueue) { const size_t size = lastMarkQueue - markQueue; _gst_mem.markQueue = (struct mark_queue *) xrealloc (_gst_mem.markQueue, 2 * size * sizeof (struct mark_queue)); _gst_mem.lastMarkQueue = &_gst_mem.markQueue[2 * size]; markQueue = _gst_mem.markQueue; lastMarkQueue = _gst_mem.lastMarkQueue; currentMarkQueue = &_gst_mem.markQueue[size]; } currentMarkQueue->firstOOP = curOOP; currentMarkQueue->endOOP = atEndOOP; currentMarkQueue++; break; } curOOP++; } if (!firstOOP) goto pop; TAIL_MARK_OOP (firstOOP); } markOne: { OOP objClass; gst_object object; uintptr_t size; #if defined (GC_DEBUGGING) if UNCOMMON (IS_OOP_FREE (oop)) { printf ("Error! Free OOP %p is being marked!\n", oop); abort (); return; } #endif #if defined(GC_DEBUG_OUTPUT) printf (">Mark "); _gst_display_oop (oop); #endif /* see if the object has pointers, set up to copy them if so. */ oop->flags |= F_REACHABLE; object = OOP_TO_OBJ (oop); objClass = object->objClass; if UNCOMMON (oop->flags & F_CONTEXT) { gst_method_context ctx; intptr_t methodSP; ctx = (gst_method_context) object; methodSP = TO_INT (ctx->spOffset); /* printf("setting up for loop on context %x, sp = %d\n", ctx, methodSP); */ TAIL_MARK_OOPRANGE (&ctx->objClass, ctx->contextStack + methodSP + 1); } else if UNCOMMON (oop->flags & (F_EPHEMERON | F_WEAK)) { if (oop->flags & F_EPHEMERON) _gst_add_buf_pointer (oop); /* In general, there will be many instances of a class, but only the first time will it be unmarked. So I'm marking this as uncommon. */ if UNCOMMON (!IS_OOP_MARKED (objClass)) TAIL_MARK_OOP (objClass); } else { size = NUM_OOPS (object); if COMMON (size) TAIL_MARK_OOPRANGE (&object->objClass, object->data + size); else if UNCOMMON (!IS_OOP_MARKED (objClass)) TAIL_MARK_OOP (objClass); } } pop: { if (currentMarkQueue > markQueue) { currentMarkQueue--; TAIL_MARK_OOPRANGE (currentMarkQueue->firstOOP, currentMarkQueue->endOOP); } } } void _gst_mark_oop_range (OOP *curOOP, OOP *atEndOOP) { OOP *pOOP; for (pOOP = curOOP; pOOP < atEndOOP; pOOP++) MAYBE_MARK_OOP (*pOOP); } void _gst_inc_init_registry (void) { _gst_mem.inc_base = (OOP *) xmalloc (INIT_NUM_INCUBATOR_OOPS * sizeof (OOP *)); _gst_mem.inc_ptr = _gst_mem.inc_base; _gst_mem.inc_end = _gst_mem.inc_base + INIT_NUM_INCUBATOR_OOPS; /* Make the incubated objects part of the root set */ _gst_register_oop_array (&_gst_mem.inc_base, &_gst_mem.inc_ptr); } void _gst_inc_grow_registry (void) { unsigned oldPtrOffset; unsigned oldRegistrySize, newRegistrySize; oldPtrOffset = _gst_mem.inc_ptr - _gst_mem.inc_base; oldRegistrySize = _gst_mem.inc_end - _gst_mem.inc_base; newRegistrySize = oldRegistrySize + INCUBATOR_CHUNK_SIZE; _gst_mem.inc_base = (OOP *) xrealloc (_gst_mem.inc_base, newRegistrySize * sizeof (OOP *)); _gst_mem.inc_ptr = _gst_mem.inc_base + oldPtrOffset; _gst_mem.inc_end = _gst_mem.inc_base + newRegistrySize; } smalltalk-3.2.5/libgst/gst-parse.h0000644000175000017500000001106412130343734013772 00000000000000/******************************** -*- C -*- **************************** * * GNU Smalltalk language grammar definition * ***********************************************************************/ /*********************************************************************** * * Copyright 2005, 2006, 2007, 2008 Free Software Foundation, Inc. * Written by Paolo Bonzini. * * This file is part of GNU Smalltalk. * * GNU Smalltalk is free software; you can redistribute it and/or modify it * under the terms of the GNU General Public License as published by the Free * Software Foundation; either version 2, or (at your option) any later * version. * * Linking GNU Smalltalk statically or dynamically with other modules is * making a combined work based on GNU Smalltalk. Thus, the terms and * conditions of the GNU General Public License cover the whole * combination. * * In addition, as a special exception, the Free Software Foundation * give you permission to combine GNU Smalltalk with free software * programs or libraries that are released under the GNU LGPL and with * independent programs running under the GNU Smalltalk virtual machine. * * You may copy and distribute such a system following the terms of the * GNU GPL for GNU Smalltalk and the licenses of the other code * concerned, provided that you include the source code of that other * code when and as the GNU GPL requires distribution of source code. * * Note that people who make modified versions of GNU Smalltalk are not * obligated to grant this special exception for their modified * versions; it is their choice whether to do so. The GNU General * Public License gives permission to release a modified version without * this exception; this exception also makes it possible to release a * modified version which carries forward this exception. * * GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or * FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for * more details. * * You should have received a copy of the GNU General Public License along with * GNU Smalltalk; see the file COPYING. If not, write to the Free Software * Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * ***********************************************************************/ #ifndef GST_PARSE_H #define GST_PARSE_H #define TOKEN_DEFS \ TOKEN_DEF (SCOPE_SEPARATOR, 261, "'.' or '::'", -1) \ TOKEN_DEF (ASSIGNMENT, 262, "'_' or ':='", -1) \ TOKEN_DEF (SHEBANG, 263, "'#!'", -1) \ TOKEN_DEF (IDENTIFIER, 264, "identifier", -1) \ TOKEN_DEF (BINOP, 265, "binary operator", -1) \ TOKEN_DEF (KEYWORD, 266, "keyword", -1) \ TOKEN_DEF (STRING_LITERAL, 267, "string literal", -1) \ TOKEN_DEF (SYMBOL_LITERAL, 268, "symbol literal", -1) \ TOKEN_DEF (INTEGER_LITERAL, 269, "integer literal", -1) \ TOKEN_DEF (LARGE_INTEGER_LITERAL, 270, "integer literal", 269) \ TOKEN_DEF (BYTE_LITERAL, 271, "small integer literal", 269) \ TOKEN_DEF (FLOATD_LITERAL, 272, "floating-point literal", -1) \ TOKEN_DEF (FLOATE_LITERAL, 273, "floating-point literal", 272) \ TOKEN_DEF (FLOATQ_LITERAL, 274, "floating-point literal", 272) \ TOKEN_DEF (SCALED_DECIMAL_LITERAL, 275, "decimal literal", -1) \ TOKEN_DEF (CHAR_LITERAL, 276, "character literal", -1) \ TOKEN_DEF (ERROR_RECOVERY, 277, "newline", -1) #define FIRST_TOKEN (SCOPE_SEPARATOR) #define NUM_TOKENS (CHAR_LITERAL - SCOPE_SEPARATOR + 1) #define TOKEN_DEF(name, val, str, subsume) \ name = val, enum yytokentype { TOKEN_DEFS FIRST_UNUSED_TOKEN }; #undef TOKEN_DEF typedef union YYSTYPE { long double fval; intptr_t ival; char *sval; byte_object boval; OOP oval; tree_node node; } YYSTYPE; typedef struct YYLTYPE { int first_line; int first_column; int64_t file_offset; } YYLTYPE; enum parser_state { PARSE_METHOD, PARSE_METHOD_LIST, PARSE_DOIT }; typedef struct gst_lookahead { int token; YYSTYPE val; YYLTYPE loc; } gst_lookahead; typedef struct gst_parser { gst_lookahead la [4]; int la_size; int la_first; enum parser_state state; jmp_buf recover; } gst_parser; /* This is necessary so that the grammar knows when it must switch to compile mode */ extern gst_parser *_gst_current_parser ATTRIBUTE_HIDDEN; /* Invoke the recursive descent parser. */ extern void _gst_parse_method (void) ATTRIBUTE_HIDDEN; extern void _gst_parse_chunks (void) ATTRIBUTE_HIDDEN; extern void _gst_print_tokens (gst_parser *p) ATTRIBUTE_HIDDEN; #endif smalltalk-3.2.5/libgst/genvm-scan.l0000644000175000017500000001352012123404352014122 00000000000000/******************************** -*- C -*- **************************** * * GNU Smalltalk genvm tool - lexical analyzer * ***********************************************************************/ /*********************************************************************** * * Copyright 2003, 2006 Free Software Foundation, Inc. * Written by Paolo Bonzini. * * This file is part of GNU Smalltalk. * * GNU Smalltalk is free software; you can redistribute it and/or modify it * under the terms of the GNU General Public License as published by the Free * Software Foundation; either version 2, or (at your option) any later * version. * * Linking GNU Smalltalk statically or dynamically with other modules is * making a combined work based on GNU Smalltalk. Thus, the terms and * conditions of the GNU General Public License cover the whole * combination. * * In addition, as a special exception, the Free Software Foundation * give you permission to combine GNU Smalltalk with free software * programs or libraries that are released under the GNU LGPL and with * independent programs running under the GNU Smalltalk virtual machine. * * You may copy and distribute such a system following the terms of the * GNU GPL for GNU Smalltalk and the licenses of the other code * concerned, provided that you include the source code of that other * code when and as the GNU GPL requires distribution of source code. * * Note that people who make modified versions of GNU Smalltalk are not * obligated to grant this special exception for their modified * versions; it is their choice whether to do so. The GNU General * Public License gives permission to release a modified version without * this exception; this exception also makes it possible to release a * modified version which carries forward this exception. * * GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or * FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for * more details. * * You should have received a copy of the GNU General Public License along with * GNU Smalltalk; see the file COPYING. If not, write to the Free Software * Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * ***********************************************************************/ %x C_ARGS %x C_CODE %x C_COMMENT %x C_STRING %x C_CHAR %x CPP_CODE %option nounput %option noyywrap %option never-interactive %{ #include "genvm.h" #include "genvm-parse.h" static int from = 0, depth = 0; #if !defined YY_FLEX_SUBMINOR_VERSION || YY_FLEX_SUBMINOR_VERSION < 31 int yylineno = 1; #endif %} %% { /* All states know how to count lines. */ \n+ { yylineno += yyleng; } [ \t\f]+ { } } { table return VM_TABLE; operation return VM_OPERATION; bytecode return VM_BYTECODE; ^[ \t]*# { printf ("%s", yytext); from = YY_START; BEGIN (CPP_CODE); } "/*" { from = YY_START; BEGIN (C_COMMENT); } [1-9][0-9]* | 0x[0-9A-Fa-f]+ | 0[0-7]* { yylval.num = strtol(yytext, NULL, 0); return (NUMBER); } \.\. return VM_DOTS; -- return VM_MINUSMINUS; [a-zA-Z_][a-zA-Z_0-9]* yylval.text = strdup (yytext); return ID; "(" { yylval.ctext = "("; if (c_args_on_paren) BEGIN (C_ARGS); c_args_on_paren = false; depth = 1; return '('; } "{"[\n]* { yylineno += yyleng - 1; yylval.ctext = "{\n "; if (c_code_on_brace) BEGIN (C_CODE); c_code_on_brace = false; depth = 1; return '{'; } . return *yytext; } { /* Learn how to skip strings. */ "'" { yylval.text = yytext; from = YY_START; BEGIN (C_CHAR); return (EXPR); } "\"" { yylval.text = yytext; from = YY_START; BEGIN (C_STRING); return (EXPR); } } { [ \t]*"(" { depth++; yylval.ctext = yytext; return EXPR; } ","[ \t]* { yylval.ctext = yytext; return ','; } ")"[ \t]* { if (!--depth) { BEGIN (INITIAL); return ')'; } yylval.ctext = yytext; return EXPR; } [^(,)'"\n]* { yylval.ctext = yytext; return (EXPR); } } { [ \t]*"{" { depth++; yylval.ctext = yytext; return EXPR; } [ \t]*"}" { if (!--depth) { BEGIN (INITIAL); return '}'; } yylval.ctext = yytext; return EXPR; } \n { yylineno++; yylval.ctext = "\n "; return (EXPR); } [^{}'"\n]* { yylval.ctext = yytext; return (EXPR); } } { /* Characters and strings have different terminations... */ "'" { yylval.text = yytext; BEGIN (from); return (EXPR); } } { "\"" { yylval.text = yytext; BEGIN (from); return (EXPR); } } { /* ... but otherwise they're the same. */ \\. { yylineno += (yytext[1] == '\n'); yylval.text = yytext; return (EXPR); } . { yylineno += (yytext[0] == '\n'); yylval.text = yytext; return (EXPR); } } { /* And so are comments. */ [^*\n]*"*"*\n { yylineno++; } [^*\n]*"*"+[^/*] { } [^*\n]*"*"+"/" { BEGIN (from); } } { /* And preprocessor code; this however is printed to stdout. */ [^\n]*"\\"[ \t]*\n? { printf("%s", yytext); yylineno += yytext[yyleng - 1] == '\n'; } [^\n]+$ { printf("%s", yytext); } \n+ { printf("%s", yytext); yylineno += yyleng; BEGIN (from); } } %% smalltalk-3.2.5/libgst/ChangeLog0000644000175000017500000120275412130343734013477 000000000000002013-01-17 Gwenael Casaccio * libgst/sysdep/win32/timer.c: Correct the function signature. 2012-12-29 Paolo Bonzini * libgst/oop.h: MAX_OOP_TABLE_SIZE is expressed in OOPs, not bytes. Reported by Holger Freyther. 2012-12-29 Holger Hans Peter Freyther * libgst/alloc.c: _gst_heap_sbrk returns NULL and not MMAP_FAILED on allocation failure. * libgst/heap.c: Return NULL on allocation failure. 2012-09-09 Paolo Bonzini * libgst/sysdep/posix/events.c: Register the fd with gst before polling. 2012-07-15 Paolo Bonzini * libgst/opt.c: Fix error in compute_jump_length that could lead to verification errors after optimization. 2012-06-15 Thomas Girard * libgst/dict.inl: Add IS_C_LONGLONG and IS_C_ULONGLONG macros. * libgst/cint.c: Add missing long long and unsigned long long types to _gst_c_type_size. Use new macros. * libgst/prims.def: Use IS_C_ULONG in VMpr_CObject_atPut. Use new macros. 2012-06-04 Thomas Girard * libgst/dict.inl: Add FROM_C_LONGLONG and FROM_C_ULONGLONG macros. * libgst/cint.c: Add missing mappings from (unsigned) long long. 2012-05-19 Paolo Bonzini * libgst/prims.def: Another fix for the new primitive. 2012-05-19 Paolo Bonzini * libgst/prims.def: Fix class test for new primitive. 2012-05-19 Paolo Bonzini * libgst/events.h: Adjust prototype for _gst_async_timed_wait. * libgst/prims.def: Switch VMpr_Processor_signalAtMillisecondClockValue to nanosecond precision, adjust call to _gst_async_timed_wait. * libgst/sysdep.h: Adjust prototype for _gst_sigalrm_at. * libgst/sysdep/cygwin/timer.c: Switch _gst_sigalrm_at to nanosecond precision. * libgst/sysdep/posix/timer.c: Switch _gst_sigalrm_at to nanosecond precision. * libgst/sysdep/win32/events.c: Switch _gst_async_timed_wait to nanosecond precision. 2012-05-19 Paolo Bonzini * libgst/events.h: Adjust prototype for _gst_async_timed_wait. * libgst/interp.c: Use _gst_sigvtalrm_every. * libgst/prims.def: Pass absolute time to _gst_async_timed_wait. * libgst/sysdep.h: Remove _gst_signal_after, add _gst_sigvtalrm_every and _gst_sigalrm_at. * libgst/sysdep/cygwin/timer.c: Remove _gst_signal_after, add _gst_sigvtalrm_every and _gst_sigalrm_at. * libgst/sysdep/posix/events.c: Use _gst_sigalrm_at. * libgst/sysdep/posix/timer.c: Remove _gst_signal_after, add _gst_sigvtalrm_every and _gst_sigalrm_at. * libgst/sysdep/win32/events.c: Get absolute time in _gst_async_timed_wait. * libgst/sysdep/win32/timer.c: Do not abort on _gst_sigvtalrm_every, just do nothing. 2012-05-19 Paolo Bonzini * libgst/prims.def: Support the new primitive VMpr_Processor_signalAtMillisecondClockValue. 2012-05-19 Paolo Bonzini * libgst/prims.def: Add VMpr_Time_nanosecondClock. * libgst/sysdep.h: Add _gst_get_ns_time. * libgst/sysdep/common/time.c: Add _gst_get_milli_time. * libgst/sysdep/posix/time.c: Change _gst_get_milli_time to _gst_get_ns_time. * libgst/sysdep/win32/time.c: Likewise. 2012-03-30 Paolo Bonzini * libgst/oop.h: Remove _gst_compact and _gst_alloc_old_obj. * libgst/oop.c: Make them static. 2012-03-30 Gwenael Casaccio * libgst/alloc.c: Allocate heaps with xcalloc. * libgst/oop.c: Let oldspace_before_freeing remove grey pages when compacting. 2012-03-29 Paolo Bonzini * libgst/gst-parse.c: Do not call _gst_free_tree in the presence of lookahead, or add assertions that we can do so. Reported by Gwenael Casaccio. 2012-03-29 Paolo Bonzini * libgst/lex.c: Report location of EOF token. 2012-03-23 Paolo Bonzini * libgst/oop.c: Fix weak objects thinko in Gwen's patch. 2012-03-14 Paolo Bonzini * libgst/oop.c: Return fixedspace from oldspace_nomemory when appropriate. 2012-02-22 Gwenael Casaccio * libgst/oop.c: Fix weak objects with pointer and byte parts. 2012-03-01 Paolo Bonzini * libgst/oop.c: Remove premature optimization. 2012-02-22 Paolo Bonzini * libgst/gstpriv.h: Include crt_externs.h if present. 2012-02-22 Gwenael Casaccio * libgst/opt.c: Account for two line number bytecodes. 2011-02-02 Paolo Bonzini * libgst/sysdep/posix/events.c: Fix signal handling race. Reported by Derek Zhou. 2012-02-02 Gwenael Casaccio Paolo Bonzini * libgst/interp.c: Use remove_process_from_list consistently. 2011-12-14 Paolo Bonzini * libgst/gst-parse.c: Only increase lookahead by one token at a time, so that we do not lookahead past EOF. 2011-11-14 Mehul Sanghvi * libgst/cint.c: Add get_environ and pass it to Smalltalk. 2011-09-26 Tony Garnock-Jones * libgst/cint.c: Try .dylib as a last resort on Mac OS X. 2011-09-22 Paolo Bonzini * libgst/save.c: Close file descriptors upon image save. 2011-09-22 Paolo Bonzini * libgst/dict.c: Add the ClockOnImageSave class variable to time. 2011-08-13 Paolo Bonzini * libgst/prims.def: Atomically nil the file descriptor field when closing a FileDescriptor or socket. 2011-08-13 Paolo Bonzini * libgst/prims.def: Wrap #snapshot in push_jmp_buf/pop_jmp_buf, since it will do call-ins via _gst_invoke_hook. Suggested by Gwenael Casaccio. 2011-08-05 Holger Freyther * libgst/byte.h: Make smatch happy and add parameters to the function. 2011-08-01 Mathieu Suen * libgst/cint.c: Add long long support for calls. * libgst/cint.h: Add CDATA_LONGLONG and CDATA_ULONGLONG. * libgst/dict.c: Pass CLongLongAlignment to Smalltalk. * libgst/prims.def: Add long long support for memory access. 2011-07-27 Gwenael Casaccio Paolo Bonzini * libgst/oop.c: Use mark stack. * libgst/oop.h: Define mark stack data structures. 2011-07-27 Paolo Bonzini * libgst/oop.c: Clean up reset_incremental_gc. * libgst/oop.h: Remove first_allocated_oop. 2011-07-27 Paolo Bonzini * libgst/oop.c: Do not sweep below _gst_mem.last_swept_oop when initializing the incremental GC. 2011-07-23 Paolo Bonzini * libgst/sym.c: Remove _gst_symbol_as_string. Suggested by Gwenael Casaccio. * libgst/sym.h: Likewise. 2011-07-04 Paolo Bonzini Gwenael Casaccio * libgst/prims.def: Handle fixed instance variables in VMpr_ArrayedCollection_replaceFromToWithStartingAt, keeping existing failure conditions when the receiver has no fixed instance variables. 2011-07-04 Paolo Bonzini * libgst/events.c: Change _gst_sem_int_vec to async_queue_entry. Adjust uses. Enqueue it with _gst_async_call_internal. * libgst/events.h: Change declaration. * libgst/gstpriv.h: Remove dummy __sync_synchronize. Add __sync_swap and barrier(). Include events.h later. * libgst/interp-bc.inl: Use empty_async_queue. * libgst/interp-jit.inl: Likewise. * libgst/interp.c: Remove async_queue_entry. Change async signal vectors to lists. Export do_async_signal and add the new function _gst_do_async_signal_and_unregister. Add gst_async_call_internal. Remove async-signal safe stuff from _gst_async_call, and always allocate an async_queue_entry; use a lockless stack (which is also async-signal-safe, so the same algorithms can be used in both cases). Rewrite _gst_have_pending_async_calls and add empty_async_queue. Adjust copying and marking of the lists. * libgst/interp.h: Put async_queue_entry here, adding a next pointer. Add declarations for the new functions. * libgst/oop.c: Use _gst_async_call_internal. * libgst/prims.def: Set exception flag when reenabling interrupts. * libgst/sysdep.c: Include pthread header. * libgst/cygwin/timer.c: Add void argument list. * libgst/posix/events.c: Add no_opt to fix removed volatile qualifier. Adjust access to _gst_sem_int_vec. Enqueue the file polling call with _gst_async_call_internal. 2011-06-07 Paolo Bonzini * libgst/callin.c: Fix type of _gst_uint_to_oop argument. * libgst/callin.h: Fix type of _gst_uint_to_oop argument. * libgst/gstpub.c: Fix type of gst_uint_to_oop argument. * libgst/gstpub.h: Fix type of gst_uint_to_oop argument. 2011-05-26 Gwenael Casaccio * libgst/dict.c: Fix superclass of MethodDictionary. 2011-05-19 Paolo Bonzini * libgst/dict.inl: Fix conversion to/from 64-bit values on 32-bit platforms. Reported by Holger Hans Peter Freyther. * libgst/prims.def: Ensure conversion between epochs is done with 64-bit math. 2011-05-19 Paolo Bonzini * libgst/prims.def: Fix conversion between Smalltalk and Unix epoch. 2011-05-19 Paolo Bonzini * libgst/prims.def: Implement one-argument VMpr_Time_timezoneBias. 2011-05-18 Mathieu Suen * libgst/gst-parse.c: Allow creating unary pragmas. 2011-05-18 Paolo Bonzini * libgst/gst-parse.c: Move creation of ATTRIBUTE_LIST contents here... * libgst/tree.c: ... from here. * libgst/tree.h: Adjust documentation. 2011-04-29 Paolo Bonzini * libgst/callin.c: Use FROM_C_INT and FROM_C_LONG properly. Add _gst_uint_to_oop. * libgst/callin.h: Declare _gst_uint_to_oop. * libgst/gstpub.c: Add _gst_uint_to_oop to proxy, add gst_uint_to_oop. * libgst/gstpub.h: Add matching declarations. 2011-04-29 Paolo Bonzini * libgst/sym.c: Fix argument count of selectors starting with _. Reported by Mathieu Suen. 2011-04-10 Holger Hans Peter Freyther * libgst/cint.c: Free #string, #byteArray, #symbol, #wstring converted arguments. 2011-03-28 Holger Hans Peter Freyther * libgst/prims.def: Set errno for VMpr_FileDescriptor_socketOp. 2011-03-25 Paolo Bonzini * libgst/prims.def: Fix crashes with unexpected integer arguments. 2011-03-24 Paolo Bonzini * libgst/interp.inl: Fix brokenness on non-x86 platforms. 2011-03-12 Paolo Bonzini * libgst/callin.c: Remove dead code signaled by clang analyzer. * libgst/cint.c: Likewise. * libgst/comp.c: Likewise, and add missing INC_RESTORE_POINTER. * libgst/dict.c: Likewise. * libgst/interp.c: Likewise. * libgst/mpz.c: Likewise. * libgst/oop.c: Likewise. * libgst/opt.c: Likewise. * libgst/re.c: Likewise. 2011-03-08 Paolo Bonzini * libgst/opt.c: Add missing verification rule. 2011-02-28 Paolo Bonzini * libgst/dict.inl: Fix creation of FloatQ's on non-x86 platforms. 2011-02-24 Paolo Bonzini * libgst/interp.c: Fix GC bug reported by Gwenael Casaccio. 2011-02-14 Holger Hans Peter Freyther * libgst/interp.c: Always inline unwind_context. 2011-02-11 Paolo Bonzini * libgst/cint.c: Fix previous patch. Add printf for coverage of variadic functions. 2011-02-04 Holger Hans Peter Freyther * libgst/cint.c: Propagate type conversion failures. 2011-02-04 Holger Hans Peter Freyther * libgst/sockets.c: Add size check for the socket addr. 2011-01-27 Paolo Bonzini * libgst/gstpriv.h: Return boolean values from IS_OOP_*. * libgst/oop.inl: Likewise. 2011-01-14 Paolo Bonzini * libgst/cint.c: Accept UndefinedObject for #cObjectPtr. 2011-01-10 Paolo Bonzini * libgst/files.c: Load Autoload.st last. 2011-01-10 Paolo Bonzini Mathiue Suen * libgst/dict.inl: Fix 32-bit #int and 64-bit #uint limits. 2010-12-05 Paolo Bonzini * lib-src/sockets.c: Use O_NONBLOCK from socketx.h. 2010-12-04 Paolo Bonzini * libgst/dict.inl: Avoid crash on #changeClassTo: and UnicodeString. 2010-11-10 Paolo Bonzini * libgst/heap.c: Detect out-of-memory. 2010-11-10 Paolo Bonzini * libgst/interp.c: Change the stack top to nil in _gst_sync_wait and put the semaphore back in _gst_sync_signal. This allows Smalltalk code to distinguish interruptions from successful waits. 2010-11-08 Paolo Bonzini * libgst/memzero.h: Remove. * libgst/dict.c: Replace memzero with memset. * libgst/dict.inl: Replace memzero with memset. * libgst/gstpriv.h: Replace memzero with memset. * libgst/heap.c: Replace memzero with memset. * libgst/lex.c: Replace memzero with memset. * libgst/mpz.c: Replace memzero with memset. * libgst/opt.c: Replace memzero with memset. * libgst/prims.def: Replace memzero with memset. * libgst/save.c: Replace memzero with memset. * libgst/xlat.c: Replace memzero with memset. 2010-11-08 Paolo Bonzini * libgst/interp.c: Streamline unwind_context even more. The compiler can do enough optimization that we can use the free_lifo_context global directly. Also, _gst_nil_oop is kept in a register so icache-wise it pays to always do the store into parentContext. 2010-11-08 Paolo Bonzini * libgst/dict.inl: Add instantiate_numbytes, use it for instantiate and non-pointer instantiate_with; do not unroll nil initialization since N is usually small here. Rewrite nil_fill. * libgst/interp.c: Unroll the first few itertaions of prepare_context. Do not use nil_fill. * libgst/md-config.h: Remove loop unrolling macros. 2010-11-02 Paolo Bonzini * libgst/md-config.h: Tune for x86-64. 2010-11-02 Paolo Bonzini * libgst/interp.inl: Add optimized x86 versions of tagged arithmetic operations. 2010-11-02 Paolo Bonzini * libgst/interp.inl: Add here functions for SmallInteger OOP arithmetic. * libgst/prims.def: Use the new functions. * libgst/vm.def: Use the new functions. 2010-11-02 Paolo Bonzini * libgst/comp.c: Reorder printing of statistics so that the results are not influenced by printing the result and by the #afterEval hooks. 2010-10-31 Paolo Bonzini * libgst/sysdep/posix/events.c: Remove pthread_in_use. 2010-10-30 Paolo Bonzini * libgst/sysdep/posix/events.c: Include pthread.h if using pthreads. 2010-10-17 Paolo Bonzini * libgst/prims.def: NULL-terminate the output of VMpr_String_asCData. Suggested by Holger Hans Peter Freyther. 2010-10-08 Paolo Bonzini * libgst/cint.c: Retrieve CCallbackDescriptor on image load. 2010-09-27 Holger Hans Peter Freyther * libgst/oop.c: Fix a typo. 2010-09-27 Paolo Bonzini * libgst/gst-parse.c: Correctly handle scoped methods within a class block. 2010-09-27 Paolo Bonzini * libgst/gst-parse.c: Fix NULL pointer dereference. 2010-09-25 Gwenael Casaccio * libgst/gst-parse.c: Support multi-keyword class attributes. 2010-07-27 Paolo Bonzini * libgst/sysdep.h: Correctly use size_t/ssize_t. * libgst/sysdep/common/files.c: Likewise. * libgst/prims.def: Likewise. Remove duplicate checks. 2010-07-27 Paolo Bonzini * libgst/sysdep.h: Remove _gst_full_write. * libgst/sysdep/common/files.c: Move _gst_full_write... * libgst/save.c: ... here. longjmp out to _gst_save_to_file when it fails. 2010-07-27 Paolo Bonzini * libgst/cint.c: Fix warnings. * libgst/real.c: Fix out-of-bounds array access (which is actually unreachable, but GCC still warns). * libgst/prims.def: Fix two warnings. * libgst/sysdep/win32/signals.c: Fix warning. 2010-07-04 Paolo Bonzini * libgst/oop.c: Fix GC_DEBUGGING compilation. Fix GC bug in "ObjectMemory current". 2010-06-13 Paolo Bonzini * libgst/callin.c: Use _gst_copy_oop_range and _gst_mark_oop_range. * libgst/oop.c: Rewrite tail recursion in _gst_mark_an_oop_internal. Add _gst_mark_oop_range. * libgst/oop.h: Add _gst_mark_oop_range, change prototype of _gst_mark_an_oop_internal. * libgst/oop.inl: Remove COPY_OOP_RANGE and MARK_OOP_RANGE, adjust MAYBE_MARK_OOP. 2010-06-13 Paolo Bonzini * libgst/sockets.c: "Touch" all pointer arguments to socket system calls to avoid EFAULT. 2010-06-06 Paolo Bonzini * libgst/sysdep/posix/time.c: Fix previous change for millisecond vs. microsecond confusion. 2010-05-28 Paolo Bonzini * libgst/sysdep/posix/time.c: Prefer using nanosleep to usleep. usleep is totally broken under Solaris 8 and 9. Reported by Rick Flower. 2010-05-21 Paolo Bonzini * libgst/files.c: Load DynVariable.st. 2010-05-18 Paolo Bonzini * libgst/comp.c: Flush aggressively around _gst_execute_statements. * libgst/gst-parse.c: Likewise. 2010-04-21 Paolo Bonzini * libgst/sockets.c: Fix previous commit. 2010-04-19 Paolo Bonzini * libgst/sockets.c: Make connect return int. 2010-04-17 Paolo Bonzini * libgst/input.c: Remove dead code. 2010-04-11 Paolo Bonzini * libgst/sysdep/win32/events.c: Ahem, this really could not work. 2010-04-11 Paolo Bonzini * libgst/cint.c: Fix warnings on platforms with no lstat. 2010-03-25 Paolo Bonzini * libgst/sockets.c: Fix logic for no SOCK_CLOEXEC or no accept4. 2010-02-20 Paolo Bonzini * libgst/files.c: Adjust for AnsiExcept.st rename. 2010-02-18 Paolo Bonzini * libgst/vm.def: Make EXIT_INTERPRETER safer since we now can fork CallinProcesses to Processes. 2010-02-18 Paolo Bonzini * libgst/comp.c: Compile the termination method with an infinite loop to avoid falling off the last context. 2010-02-05 Gwenael Casaccio * libgst/sysdep/posix/events.c: Fix initialization of waiting_thread. 2010-01-11 Paolo Bonzini * libgst/genbc-decl.y: Embarrassing typo. 2010-01-08 Paolo Bonzini * libgst/mpz.c: Hack to build with GMP 5. 2010-01-01 Paolo Bonzini * Update copyright years. 2009-12-11 Gwenael Casaccio * libgst/prims.def: Fix bug in similarityTo:. 2009-12-09 Alexey Zakhlestin * libgst/gstpriv.h: Include sockets.h. * libgst/print.c: Fix printf. * libgst/socklen.c: Use socklen_t where appropriate. * libgst/sym.c: Remove useless cast. * libgst/sysdep/common/files.c: Fix 64-bit cleanliness problems. * libgst/sysdep/posix/findexec.c: Likewise. 2009-12-05 Paolo Bonzini * libgst/byte.c: Add LN_ABSOLUTE, emit relative line number bytecodes together with _following_ bytecode. * libgst/byte.h: Add LN_ABSOLUTE. * libgst/comp.c: Emit absolute line number for the line with the selector. * libgst/opt.c: Remove now useless two-line-numbers optimization. 2009-11-26 Lee Duhem * libgst/comp.c: Make formatted source of Behavior>>methodsFor: look better. 2009-11-12 Paolo Bonzini * libgst/dict.c: Pass PREFIX and EXEC_PREFIX. 2009-11-02 Paolo Bonzini * libgst/prims.def: Do not fail on pow(0.0, 0.0). 2009-11-01 Paolo Bonzini * libgst/comp.c: Fix computation of jump lengths. 2009-10-28 Paolo Bonzini * libgst/gstpub.c: Move init_vmproxy and _gst_get_vmproxy... * libgst/callin.c: ... here. Make_gst_init_vmproxy public, do not call it from _gst_get_vmproxy. * libgst/callin.h: Declare them here... * libgst/files.h: ... not here. * libgst/files.c: Call _gst_init_vmproxy. 2009-10-17 Paolo Bonzini * libgst/sysdep/win32/events.c: Implement pause/wakeup. 2009-10-21 Paolo Bonzini * libgst/sockets.c: Fix !HAVE_IPV6 compilation, and other Cygwin problems. 2009-10-13 Nigel Williams * libgst/cint.c: Always open with lt_dlopen first, then try lt_dlopenext. 2009-10-13 Eli Green * libgst/events.h: Fix multiply defined symbols on Mac OS X. 2009-10-06 Paolo Bonzini * libgst/prims.def: Fix #becomeForward: to look at LIFO contexts. 2009-10-04 Paolo Bonzini * libgst/prims.def: Allow reusing #at: primitive for #at:ifAbsent:. 2009-10-04 Paolo Bonzini * libgst/prims.def: Implement memchr primitive. 2009-09-07 Paolo Bonzini * libgst/sysdep/win32/signals.c: Simplify given known set of valid signals. 2009-09-07 Paolo Bonzini * libgst/events.h: Add _gst_get_fd_error. * libgst/sysdep/win32/events.c: Implement it. * libgst/sysdep/posix/events.c: Implement it as a stub. * libgst/sockets.c: Use it in getSoError. 2009-09-07 Paolo Bonzini * libgst/sysdep/win32/events.c: Extract select-based polling from poll_thread, use it in _gst_sync_file_polling and _gst_async_file_polling, save error conditions returned by WSAEnumNetworkEvents. 2009-09-03 Paolo Bonzini * libgst/gst-parse.c: Fix crash on invalid class variable definitions. 2009-08-26 Paolo Bonzini Complete transition from events.c to sysdep/*/events.c, moving the common parts back outside sysdep/ and adding a stab at the Win32 version. This lets us throw Makefile/lib-src hacks away. * libgst/gstpriv.h: Include signal.h, do not include poll.h. * libgst/events.h: Add _gst_register_socket. * libgst/sysdep.h: Add _gst_wait_for_input. Remove TIMER_REAL, TIMER_PROCESS. * libgst/input.c: Use _gst_wait_for_input and _gst_sync_file_polling. * libgst/sockets.c: Use gstpriv.h. Do _gst_register_socket. Do not warn under mingw. * libgst/interp.c: Cope with nonexistent SIGUSR1. Avoid useless abstraction in _gst_signal_after. * libgst/sysdep/common/files.c: Cope with nonexistent SIGPIPE. * libgst/sysdep/cygwin/timer.c: Adjust for changes in sysdep.h. * libgst/sysdep/posix/timer.c: Adjust for changes in sysdep.h. * libgst/sysdep/win32/timer.c: Adjust for changes in sysdep.h. * libgst/sysdep/win32/events.c: Rewrite. * libgst/sysdep/win32/signals.c: Remove signals not found under mingw. * libgst/sysdep/posix/events.c: Add _gst_register_socket and _gst_wait_for_input. Adjust to move OS-independent parts... * libgst/events.c: ... here. 2009-08-25 Paolo Bonzini * libgst/dict.c: Just skip primitives that are unknown to the image. 2009-08-25 Paolo Bonzini * libgst/sockets.c: Move from packages/sockets/. * libgst/sockets.h: New. * libgst/files.c: Initialize sockets. 2009-08-24 Paolo Bonzini Nicolas Petton * libgst/dict.inl: Add num_valid_oops. * libgst/prims.def: Add becomeForward primitive. 2009-08-23 Paolo Bonzini * libgst/oop.inl: Fix ??? comment. 2009-08-23 Paolo Bonzini * libgst/oop.c: Export finished_incremental_gc. * libgst/oop.h: Declare _gst_finished_incremental_gc. Use maybe_release_xlat. * libgst/oop.inl: Fix bottom-to-top incremental collector. 2009-08-23 Paolo Bonzini * libgst/oop.c: Rename highest_swept_oop to next_oop_to_sweep, shift it down by one. 2009-08-23 Paolo Bonzini * libgst/oop.c: Always do _gst_finish_incremental_gc so that finished_incremental_gc is called. 2009-08-21 Paolo Bonzini * libgst/events.h: Declare it. * libgst/sysdep/posix/events.c: Add _gst_wakeup. * libgst/sysdep/win32/events.c: Ditto. * libgst/gstpub.c: Add it to VMproxy and add gst_wakeup. * libgst/gstpub.h: Add wakeUp to VMproxy, add gst_wakeup. * libgst/interp.c: Call _gst_wakeup from _gst_async_call. 2009-08-22 Paolo Bonzini * libgst/sysdep.h: Tweak. * libgst/sysdep.c: Split into... * libgst/sysdep/common/files.c, libgst/sysdep/common/time.c, libgst/sysdep/cygwin/files.c, libgst/sysdep/cygwin/findexec.c, libgst/sysdep/cygwin/mem.c, libgst/sysdep/cygwin/signals.c, libgst/sysdep/cygwin/time.c, libgst/sysdep/cygwin/timer.c, libgst/sysdep/posix/files.c, libgst/sysdep/posix/findexec.c, libgst/sysdep/posix/mem.c, libgst/sysdep/posix/signals.c, libgst/sysdep/posix/time.c, libgst/sysdep/posix/timer.c, libgst/sysdep/win32/files.c, libgst/sysdep/win32/findexec.c, libgst/sysdep/win32/mem.c, libgst/sysdep/win32/signals.c, libgst/sysdep/win32/time.c, libgst/sysdep/win32/timer.c: ... all these. * libgst/events.c: Copy to... * libgst/sysdep/posix/events.c: ... this... * libgst/sysdep/win32/events.c: ... and this. * libgst/sysdep/cygwin/events.c: New. 2009-08-21 Paolo Bonzini * libgst/events.c: Add _gst_pause. * libgst/events.h: Declare it. * libgst/interp.c: Add active_process_yield. * libgst/prims.def: Use it. Remove sleeping from VMpr_Processor_yield. Add VMpr_Processor_pause. Return whether incremental GC has finished in the VMpr_ObjectMemory_incrementalGCStep primitive. * libgst/sysdep.c: Add _gst_usleep. * libgst/sysdep.h: Declare it. 2009-08-21 Paolo Bonzini * libgst/oop.c: Track correctly the bottom-to-top sweeping of OOPs. Return from _gst_incremental_gc_step whether incr. GC has finished. * libgst/oop.h: Adjust prototype. * libgst/oop.inl: Track here the bottom-to-top sweeping of OOPs. 2009-08-18 Paolo Bonzini * libgst/cint.c: Add dlopen functions for modules. * libgst/cint.h: Declare them. * libgst/gstpub.c: Implement public variants and add to VMProxy. * libgst/gstpub.h: Declare public variants. 2009-08-01 Paolo Bonzini * libgst/interp.c: Do not create gcSemaphore. * libgst/oop.c: Abort upon absence of gcSemaphore. 2009-08-01 Paolo Bonzini * libgst/dict.c: Remove Delay, SharedQueue, MappedCollection, Bag. * libgst/dict.h: Likewise. * libgst/files.c: Move them after initialization. 2009-07-28 Paolo Bonzini * libgst/dict.c: Add git revision number to Version contents. 2009-07-26 Paolo Bonzini * libgst/genbc-parse.y: Fix uninitialized memory use that "interestingly" triggered only under Wine. 2009-07-25 Paolo Bonzini * libgst/sysdep.h: Return 64-bit millisecond clock. * libgst/sysdep.c: Return 64-bit millisecond clock, use monotonic clock_gettime if available. * libgst/prims.def: Return 64-bit millisecond clock. 2009-07-23 Paolo Bonzini * libgst/gstpriv.h: Add optimization barrier. * libgst/vm.def: Use it. * libgst/prims.def: Eliminate uninitialized variable. 2009-07-22 Paolo Bonzini * libgst/sysdep.c: Small cleanup. 2009-07-20 Paolo Bonzini * libgst/genpr-parse.y: Fix for newer bison. 2009-07-11 Paolo Bonzini * libgst/lex.c: Use new real.c interface. * libgst/real.c: New. * libgst/real.h: New. 2009-07-02 Paolo Bonzini * libgst/input.c: Include all symbols after popular demand for completion. 2009-06-19 Paolo Bonzini * libgst/lex.c: Fix my own snafu. 2009-06-18 Paolo Bonzini * libgst/comp.c: Check for infinite recursion of #doesNotUnderstand: before printing the result of an evaluation. 2009-06-15 Paolo Bonzini * libgst/dict.inl: Pad long doubles to 16 bytes. 2009-06-15 Paolo Bonzini * libgst/lex.c: Fix parsing of 16r2.ABCDEFd. 2009-06-15 Paolo Bonzini * libgst/prims.def: Fix typo. 2009-06-08 Paolo Bonzini * libgst/mpz.c: Return whether large integer->float conversion was exact. * libgst/mpz.h: Adjust prototypes. * libgst/prims.def: Fail on inexact conversions. 2009-03-30 Derek Zhou Paolo Bonzini * libgst/comp.c: Do not reset counters if profiling is on. * libgst/interp-bc.inl: Make state consistent when profiling callbacks might be called. * libgst/interp.c: Likewise. * libgst/dict.c: Add profiling callback. * libgst/dict.h: Add profiling callback. * libgst/interp-bc.inl: Call it. * libgst/interp.c: Declare variables. * libgst/interp.h: Declare variables. * libgst/prims.def: Add profiling primitive. 2009-03-05 Paolo Bonzini * libgst/files.c: Load RecursionLock.st before Transcript.st. 2009-02-19 Paolo Bonzini * libgst/dict.c: Fix off-by-one in _gst_identity_dictionary_at_put. 2009-01-23 Derek Zhou * libgst/oop.c: Allow shrinking the heap down to the eden's size. 2009-01-21 Derek Zhou * libgst/oop.c: Only compact if there were lots of garbage, shrinking the heap limit at the same time. 2009-01-19 Paolo Bonzini Derek Zhou * libgst/oop.c: Always call _gst_finish_incremental_gc before a non-growing compaction of the heap. 2009-01-07 Paolo Bonzini * libgst/cint.c: Add chown. 2008-12-30 Paolo Bonzini * libgst/cint.c: Discard EPIPE too, it is caught by POLLHUP. 2008-12-07 Paolo Bonzini * libgst/oop.c: Resize the oldspace if tenuring needs more space than we would have liked to have, but then do a GC if this happens. 2008-11-18 Paolo Bonzini * libgst/alloc.c: Use fixed values for MMAP_AREA_SIZE and MMAP_THRESHOLD. 2008-10-23 Paolo Bonzini * libgst/comp.c: Do not modify already-complete blocks. * libgst/interp-bc.inl: Sync _gst_send_method and _gst_send_message_internal. 2008-10-21 Paolo Bonzini * libgst/xlat.c: Fix ISO C99-ism. 2008-10-20 Paolo Bonzini * libgst/interp-jit.inl: Fix compilation error. 2008-10-18 Paolo Bonzini * libgst/dict.h: Remove ATTRIBUTE_PURE from functions that are CSEable, but write to memory (typically by memoizing values or allocating OOPs). * libgst/input.h: Likewise. * libgst/interp.c: Likewise. * libgst/opt.h: Likewise. * libgst/sym.h: Likewise. * libgst/opt.c: Change compute_jump_length to be const. 2008-09-22 Paolo Bonzini * cint.c: Fix ia64 cobjects.st failure by always using a ffi_arg-sized field. 2008-09-22 Paolo Bonzini * genpr-parse.c: Rename strupr. * genpr-parse.h: Rename strupr. * genpr-parse.y: Rename strupr. 2008-09-22 Paolo Bonzini * input.c: Revert 2008-09-18 change. Check whether get_cur_file() returns nil instead. 2008-09-21 Paolo Bonzini * alloc.h: Change nomemory hook prototype. * alloc.c: Use return value of nomemory hook. * oop.c: Pass new oldspace heap back from nomemory hook. 2008-09-20 Paolo Bonzini * cint.c: Adjust calls to _gst_show_backtrace. * gstpub.c: Add gst_show_backtrace and declare it in VMProxy. * gstpub.h: Likewise. * interp.c: Adjust calls to _gst_show_backtrace, add FILE * argument there. * interp.h: Adjust prototype of _gst_show_backtrace. * prims.def: Adjust calls to _gst_show_backtrace. 2008-09-18 Paolo Bonzini * input.c: Do not create FileSegments for non-FileStream streams. 2008-09-14 Paolo Bonzini * cint.c: Fix possible GC bugs. 2008-09-02 Paolo Bonzini * prims.def: Do not use closesocket, close is now emulated on Windows. 2008-08-18 Paolo Bonzini * libgst/comp.c: Mark the termination method as annotated. 2008-08-17 Paolo Bonzini * libgst/prims.def: Add socket<->fd conversions. * libgst/sysdep.c: Likewise. 2008-08-17 Paolo Bonzini * libgst/sysdep.c: Emulate FD_CLOEXEC on MinGW. 2008-08-11 Paolo Bonzini * libgst/cint.c: Do not pass POLLHUP errors to Smalltalk. 2008-08-08 Samuel Tardieu * libgst/sysdep.c (do_interrupts): Remove unused prototype. (DISABLED_MASK): Add SIGQUIT. 2008-08-08 Samuel Tardieu * libgst/sysdep.c (_gst_open_pipe): Remove unused variable. 2008-08-08 Samuel Tardieu * libgst/sysdep.c (find_executable): Correctly zero-terminate "location" before returning it. 2008-08-07 Paolo Bonzini * gstpriv.h: Define __sync_synchronize. * interp.h: Do not export _gst_except_flag if not JIT. * interp.c: Use a separate queue for async calls scheduled from a signal handler. Protect other async call queue accesses with a lock. Add memory barriers. * interp-bc.inl: Protect async call queue accesses with a lock. Add memory barriers. * interp-jit.inl: Protect async call queue accesses with a lock. Add memory barriers. Reset _gst_except_flag earlier. Use the return value of _gst_run_native_code to check if the termination method was invoked. * sysdep.h: Define _gst_signal_count. * sysdep.c: Use it instead of a static variable. 2008-08-06 Paolo Bonzini * events.c: Reset errno if _gst_sync_file_polling finds POLLHUP, POLLERR or POLLNVAL. * events.h: Document this. 2008-08-06 Paolo Bonzini * events.c: Use _gst_{dis,en}able_interrupts (true); make a worker function for _gst_remove_fd_polling_handlers and file_polling_handler. Call it asynchronously from file_polling_handler. Do not disable interrupts from _gst_async_file_polling. * gstpub.c: Export _gst_async_call and _gst_sync_signal. * gstpub.h: Likewise. * interp-bc.inl: Perform asynchronous calls. * interp-jit.inl: Perform asynchronous calls. * interp.c: Adjust async_queue_entry for asynchronous calls. Export sync_signal. Adjust calls to _gst_{dis,en}able_interrupts. * interp.h: Declare _gst_async_call and _gst_sync_signal. * sysdep.c: Rewrite _gst_{dis,en}able_interrupts to rely on sigaction setting the mask on POSIX systems. Set up the mask in _gst_set_signal_handler. * sysdep.h: Adjust prototypes, adjust documentation of _gst_set_signal_handler. 2008-08-06 Paolo Bonzini * interp-bc.inl: Change disable_preemption to async_queue_enabled. * interp-jit.inl: Likewise. * interp.c: Make queued_async_signals a dynamic array. Make sync_signal able to behave like Semaphore>>#notify. Do not disable/enable interrupts on behalf of the Smalltalk program; async_queue_enabled already fakes that. Do not disable/enable interrupts in the synchronized wait/signal functions. * prims.def: Do not disable/enable interrupts around the synchronized wait/signal functions. 2008-08-06 Paolo Bonzini * input.c: Do not use #nextHunk. 2008-08-05 Paolo Bonzini * dict.c: Adjust layout of FileDescriptor and FileStream. Do not fill in FileStream variables in FileDescriptors. * dict.h: Likewise. * prims.def: Adjust uses of gst_file_stream. 2008-08-05 Paolo Bonzini * dict.c: Remove _gst_byte_stream_class. Change superclass of FileDescriptor. * dict.h: Likewise. * files.c: Do not load ByteStream.st. 2008-08-05 Paolo Bonzini * dict.c: Add _gst_iterable_class. Change superclass of Collection and Stream. * dict.h: Likewise. * files.c: Load Iterable.st. 2008-08-04 Paolo Bonzini * interp.c: Move ignored signals... * sysdep.c: ... here. Reset them for exec-ed executables. 2008-08-01 Paolo Bonzini * sysdep.c: Use O_CLOEXEC if available instead of FD_CLOEXEC. 2008-08-01 Paolo Bonzini * sysdep.c: Always set SIGCHLD handler, and invoke the file interrupt handler from it. This makes sure that all children are reaped. 2008-08-01 Paolo Bonzini * sysdep.c: Fix off-by-one errors involving readlink(2). 2008-07-28 Paolo Bonzini * gst-parse.c: Parse negative numbers as unary minus + number. * lex.c: Add _gst_negate_yylval and simplify _gst_scan_number. * lex.h: Declare _gst_negate_yylval. 2008-07-24 Paolo Bonzini * libgst/byte.c: Modify _gst_line_number to store the line offset and emit the first line number as absolute. * libgst/byte.h: Add LN_RESET and LN_FORCE. * libgst/comp.c: Use new _gst_line_number functionality instead of line_offset. * libgst/opt.c: Rewrite is_simple_return to account for line numbers that are >= 256. 2008-07-18 Paolo Bonzini * libgst/gstpriv.h: Change HAVE_INET_SOCKETS to HAVE_SOCKETS. * libgst/prims.def: Change HAVE_INET_SOCKETS to HAVE_SOCKETS. * libgst/sysdep.c: Change HAVE_INET_SOCKETS to HAVE_SOCKETS. 2008-07-14 Paolo Bonzini * libgst/opt.c: Enable jump superoperators. 2008-07-14 Paolo Bonzini * libgst/interp-bc.inl: Replace FETCH with FETCH_VEC. * libgst/vm.def: Use ADVANCE instead of PREFETCH also for jump superoperators. Move "ip += 2" to ADVANCE. Remove argument to FETCH (it was always dispatch_vec), add PREPARE_STACK to jump bytecodes. 2008-07-14 Paolo Bonzini * libgst/opt.c: Rewrite _gst_optimize_bytecodes to build a CFG and reassemble the method at the end of the optimization. 2008-07-10 Paolo Bonzini * libgst/dict.c: Fix order of instance variables for metaclass. 2008-06-04 Paolo Bonzini * libgst/interp-bc.inl: Create a jmp_buf for _gst_interpret. * libgst/interp-jit.inl: Likewise. * libgst/interp.c: Rewrite handling of interp_jmp_buf and signals. Use the jmp_buf from _gst_interpret when SIGINT is sent but the current process is terminated. * libgst/prims.def: Use push_jmp_buf and pop_jmp_buf. Propagate interruptions until the interpreter is reached. 2008-06-02 Paolo Bonzini * libgst/cint.c: Return the receiver, not nil, if the returned type is #void. 2008-05-30 Paolo Bonzini * libgst/callin.c: Fix %w in _gst_msg_sendf. 2008-05-27 Paolo Bonzini * libgst/prims.def: Add VMpr_ArrayedCollection_equal. 2008-05-22 Paolo Bonzini * libgst/oop.c: Don't pin weak objects to a fixed location. * libgst/oop.h: Remove now unused fields. 2008-05-22 Paolo Bonzini * libgst/cint.h: Declare _gst_invalidate_croutine_cache. * libgst/cint.c: Define it. Replace cache validity boolean with a cache generation number. * libgst/oop.c: Call it after GC. 2008-05-22 Paolo Bonzini * libgst/prims.def: Make VMpr_ByteArray_replaceFromToWithStartingAt more generic. 2008-05-21 Paolo Bonzini * libgst/cint.c: Extract part of push_smalltalk_obj into c_to_smalltalk. Add closure support. * libgst/cint.h: Declare functions for closures. * libgst/dict.c: Add CCallbackDescriptor. * libgst/dict.h: Add CCallbackDescriptor. * libgst/files.c: Load CCallback.st. * libgst/prims.def: Declare closure primitives. 2008-05-21 Paolo Bonzini * libgst/callin.c: Support '%B' for the receiver in msgSendf. * libgst/interp.c: Callins evaluate blocks if the selector is NULL. 2008-05-21 Paolo Bonzini * libgst/cint.c: Replace CFunctionDescriptor references with CCallable. Allow OOPs in the argument vector and parse them as #cObject. * libgst/cint.h: Likewise. * libgst/dict.c: Add _gst_c_callable_class and definition of CCallable. * libgst/dict.h: Add _gst_c_callable_class. * libgst/files.c: Load CCallable.st. * libgst/save.c: Replace CFunctionDescriptor references with CCallable. 2008-05-20 Paolo Bonzini * libgst/cint.c: Remove symbol_type_map, type_map, classify_type_symbol, _gst_make_descriptor. Make lookup_function global. * libgst/cint.h: Declare _gst_lookup_function instead of _gst_make_descriptor. * libgst/prims.def: Replace VMpr_CFuncDescriptor_create with VMpr_CFuncDescriptor_addressOf. 2008-05-20 Paolo Bonzini * libgst/cint.c: Make CFunctionDescriptor a subclass of CObject, moving in turn the indexed instance variables into an array. * libgst/dict.c: Adjust definition. Change uninitialized creation in _gst_cobject_new_base to initialized. * libgst/save.c: Adjust saving. 2008-05-20 Paolo Bonzini * libgst/cint.c: Complete 2008-04-01 change by splitting part of c_func_info in a cache accessed with a pointer_map. This way, the CFunctionDescriptor can store the function pointer instead of the pointer to the c_func_info. 2008-05-18 Paolo Bonzini * libgst/sym.c: Improve comment on TwistedPools wrt namespace imports. 2008-05-18 Stephen Compall * libgst/gst-parse.c: Refactor pragma evaluation into new function, and use it to support namespace pragmas. 2008-05-17 Stephen Compall * libgst/dict.h: Add `sharedPools' instvar to gst_namespace. * libgst/dict.c: Likewise. * libgst/sym.c: Import shared pools from namespaces as they are visited, and expand the comment on TwistedPools to document this. 2008-05-17 Paolo Bonzini * libgst/callin.c: Fix _gst_oop_indexed_base. 2008-05-16 Paolo Bonzini * libgst/callin.c: Allow ints in OOP->float conversions. 2008-05-15 Paolo Bonzini * libgst/cint.c: Allow passing any object with non-pointer indexed instance variables as a #cObject. 2008-05-14 Paolo Bonzini * libgst/oop.c: Add ephemerons to buffer before marking their class (else, if the class actually has to be marked, we won't add them to the buffer at all). 2008-05-13 Paolo Bonzini * libgst/callin.h: Add _gst_oop_indexed_base and _gst_oop_indexed_kind. * libgst/callin.c: Implement them. * libgst/gstpub.h: Add them to the VMProxy and to the public API. * libgst/gstpub.c: Implement the public API wrappers. 2008-05-13 Paolo Bonzini * libgst/gstpriv.h: Move ISP_* constants... * libgst/dict.h: ... here... * libgst/gst.h: ... and here. Prefix these with GST_. * libgst/dict.c: Adjust uses. * libgst/dict.inl: Adjust uses. * libgst/prims.def: Adjust uses. * libgst/xlat.c: Adjust uses. 2008-05-12 Paolo Bonzini * libgst/interp.c: Adjust send_block_value prototype. * libgst/interp-bc.inl: Support block argument culling. * libgst/interp-jit.inl: Support block argument culling. * libgst/prims.def: Add primitives for block argument culling. * libgst/vm.def: Adjust calls to send_block_value. 2008-05-06 Paolo Bonzini * libgst/callin.c: Adjust calls to COBJECT_NEW, COBJECT_VALUE, SET_COBJECT_VALUE. * libgst/cint.c: Likewise. Add _gst_c_type_size. * libgst/cint.h: Declare _gst_c_type_size. * libgst/dict.c: Likewise. Rename _gst_c_object_new to _gst_c_object_new_base, add new instance variable to CObject. Make CObject absolute in _gst_free_cobject. * libgst/dict.h: Adjust struct gst_cobject and rename prototype of _gst_c_object_new to _gst_c_object_new_base. * libgst/dict.inl: Add cobject_value, set_cobject_value, cobject_index_check. Adjust COBJECT_NEW. Rename COBJECT_VALUE_OBJ and SET_COBJECT_VALUE_OBJ to COBJECT_OFFSET_OBJ and SET_COBJECT_OFFSET_OBJ, respectively. * libgst/prims.def: Adjust calls to COBJECT_NEW, COBJECT_VALUE, SET_COBJECT_VALUE. Add calls to cobject_index_check. Handle derefAt:type: from a garbage-collected CObject specially, and otherwise preserve the base when casting a CObject. 2008-05-06 Paolo Bonzini * libgst/prims.def: Eliminate VMpr_CObject_derefAtPut, restrict VMpr_CObject_derefAt to CObject types. 2008-04-25 Paolo Bonzini Stephen Compall * libgst/sym.c: Document (prose by Stephen Compall) and implement TwistedPools, using a linearized list of pool dictionaries for the lookup. 2008-04-10 Paolo Bonzini * libgst/dict.c: Put fundamental instance variables of Behavior at the beginning. * libgst/dict.h: Likewise. 2008-04-07 Paolo Bonzini * libgst/dict.c: Rename name variable of FileDescriptor to file. Support non-existent relocated paths by setting the variable to nil. * libgst/files.c: Load FilePath.st. * libgst/input.c: Support separate filename (for printing errors) and File object (for FileSegments). * libgst/input.h: Adjust prototypes. * libgst/prims.def: Add fourth optional argument to filein primitive. 2008-04-07 Paolo Bonzini * libgst/dict.c: Likewise. 2008-04-01 Paolo Bonzini * libgst/cint.c: Don't use numFixedArgs instance variable of a CFunctionDescriptor. Add classOOP parameters to _gst_make_descriptor. Return NULL if there is a problem instead of printing an error. * libgst/cint.h: Rename numFixedArgs field of gst_cfunc_descriptor to tagOOP. Adjust prototype of _gst_make_descriptor. * libgst/dict.c Rename numFixedArgs variable to tag here too. * libgst/prims.def: Create subclasses of CFunctionDescriptor if VMpr_CFuncDescriptor_create is sent to a subclass. Fail if _gst_make_descriptor returns NULL. 2008-04-01 Paolo Bonzini * libgst/dict.c: Rename unwindPoints variable of Process to environment. * libgst/files.c: Load ProcEnv.st. 2008-04-01 Paolo Bonzini * libgst/interp.c: Correct output for execution environment contexts that have a parent. 2008-03-26 Paolo Bonzini * libgst/cint.c: Add stat/lstat versions that return an object. * libgst/dict.inl: Move from/to off_t conversion here... * libgst/prims.def: ... from here. 2008-03-25 Paolo Bonzini * libgst/prims.def: Make #fileIn primitive fail if the filename is bad. 2008-03-25 Paolo Bonzini * libgst/callin.c: Never register the "nil" object, it is useless. 2008-03-19 Paolo Bonzini * libgst/prims.def: Mark VMpr_Process_suspend as a possible source of interrupts. 2008-03-19 Paolo Bonzini * libgst/files.c: Load BlockClosure before the first closures are executed (by the JIT). 2008-03-15 Paolo Bonzini * libgst/dict.c: Add SystemKernelPath. * libgst/files.c: Call `FileSegment relocate' before loading pre-image files. 2008-03-15 Paolo Bonzini * libgst/cint.c: Relocate MODULE_PATH. * libgst/dict.c: Relocate paths placed in the Smalltalk dictionary. * libgst/files.c: Relocate image and kernel paths. Apply default executable path. * libgst/files.h: Remove _gst_executable_path. * libgst/gstpub.c: Add gst_relocate_path, gst_set_executable_path. * libgst/gstpub.h: Add gst_relocate_path, gst_set_executable_path. * libgst/sysdep.c: Add _gst_relocate_path, _gst_set_executable_path. * libgst/sysdep.h: Add _gst_relocate_path, _gst_set_executable_path. 2008-03-04 Paolo Bonzini * libgst/prims.def: Avoid mixed declarations and code. 2008-02-26 Paolo Bonzini * libgst/events.c: Add _gst_remove_fd_polling_handlers. * libgst/events.h: Declare it. * libgst/prims.def: Use it. 2008-02-19 Paolo Bonzini * libgst/cint.c: Don't specify the path to ffi.h. 2008-02-13 Paolo Bonzini * libgst/re.c: Don't convert read-only strings to Regexes, convert mutable strings instead. 2008-02-12 Paolo Bonzini * libgst/lex.c: Improve the precision of reading 0.1. 2008-02-11 Paolo Bonzini * libgst/oop.c: Move inclusion of sigsegv.h... * libgst/gstpriv.h: ... here. 2008-02-11 Paolo Bonzini * libgst/vm.def: Microoptimization of + and - (avoid shifts). * libgst/gstpriv.h: Microoptimization of integer overflow detection. 2008-01-25 Paolo Bonzini * libgst/mpz.c: Fix #divExact: for huge numerator and small denominator. 2008-01-17 Tony Garnock-Jones * libgst/prims.def: Differentiate the return value for the two processes. 2008-01-15 Paolo Bonzini * libgst/prims.def: Do not pop arguments that end up in an object that the primitive creates. 2008-01-14 Paolo Bonzini * libgst/prims.def: Fix #signal:atMilliseconds: for negative argument. 2008-01-07 Paolo Bonzini * libgst/save.c: Disable copy-on-write if libsigsegv is not available. 2008-01-07 Paolo Bonzini * libgst/oop.c: Move definition of NO_SIGSEGV_HANDLING... * libgst/oop.h: ... here. 2008-01-07 Paolo Bonzini * libgst/mpz.c: Don't fail for 0 divExact: x. 2008-01-06 Paolo Bonzini * libgst/prims.def: Use gst_invoke_hook. 2008-01-05 Paolo Bonzini * libgst/comp.c: Remove _gst_had_error. * libgst/comp.h: Remove _gst_had_error. * libgst/lex.c: Add _gst_had_error and _gst_error_recovery, use the latter in scan_newline. * libgst/lex.h: Add _gst_had_error and _gst_error_recovery. * libgst/gst-parse.c: Nest error recovery jmp_bufs when _gst_push_temporaries_dictionary is used. Don't call _gst_free_tree when an error is recovered. Set _gst_error_recovery in recover_error and look for ERROR_RECOVERY tokens too. Don't define TOKEN_SEP. * libgst/gst-parse.h: Remove need for TOKEN_SEP definition. Add ERROR_RECOVERY token. 2008-01-03 Paolo Bonzini * libgst/lex.c: Do not imply '.' after assignment operator. 2007-12-18 Paolo Bonzini * libgst/prims.def: Fix right #bitShift: with high RHS and LHS<0. * libgst/vm.def: Fix right #bitShift: with high RHS and LHS<0. 2007-12-17 Paolo Bonzini * libgst/oop.c (check_weak_refs): Undo part, only fix the thinko. (sweep_oop): Undo previous change. 2007-12-17 Paolo Bonzini * libgst/oop.c (check_weak_refs): Make dead weak objects non-weak, fix thinko. (sweep_oop): Don't make dead weak objects non-weak. 2007-12-17 Paolo Bonzini * libgst/genpr-parse.y: Declare _gst_primitives_md5 as unsigned char. * libgst/interp.h: Ditto. 2007-12-10 Paolo Bonzini * libgst/gstpub.h: Declare functions only accessible via the VMProxy. * libgst/gstpub.c: Define them. 2007-12-10 Paolo Bonzini * libgst/alloc.c: Never override malloc. * libgst/heap.c: Never defer to sbrk. 2007-12-10 Paolo Bonzini * libgst/interp.c: Don't yield in resume_process. 2007-12-10 Paolo Bonzini * libgst/md-config.h: Disable third register variable for i386. 2007-12-09 Paolo Bonzini * libgst/xlat.c: Fix code generation for DeferredVariableBinding store. 2007-12-09 Paolo Bonzini * libgst/xlat.c: Fix IR generation for DeferredVariableBinding store. 2007-12-06 Paolo Bonzini * libgst/interp.c: Extract part of suspend_process into remove_process_from_list. Use it in resume_process if the process is active. Yield the active process. * libgst/prims.def: Add VMpr_Process_suspend. 2007-11-29 Paolo Bonzini * libgst/dict.inl: Loosen tests of usage of instantiate and instantiate_with. 2007-11-22 Paolo Bonzini * gst-tool.c: Test both EXEEXT and ARGV_EXEEXT. * libgst/cint.c: Fix my_mkdir for Cygwin. Reported by Freddie Akeroyd. 2007-11-19 Paolo Bonzini * libgst/sysdep.c: Provide a default MAXSYMLINKS, for Cygwin. Reported by Freddie Akeroyd. 2007-11-18 Paolo Bonzini Freddie Akeroyd * gst-tool.c: Use EXEEXT. Look for backslashes as directory separators. * libgst/cint.c: Add my_mkdir and my_mkdtemp. * libgst/sysdep.c: Fix syntax error under Win32. 2007-11-18 Paolo Bonzini * main.c: Don't use asprintf. 2007-11-13 Paolo Bonzini * libgst/prims.def: Use pow/powl. 2007-11-11 Paolo Bonzini * libgst/files.c: Use _gst_file_is_newer. * libgst/sysdep.c: Remove _gst__gst_get_file_modify_time, add _gst_file_is_newer. * libgst/sysdep.h: Likewise. 2007-11-09 Paolo Bonzini * libgst/input.c: Return false if file cannot be opened by gst_process_file, and set errno appropriately. * libgst/files.c: Use errno on return from gst_process_file. * main.c: Use errno on return from gst_process_file. * gst-tool.c: Use errno on return from gst_process_file. 2007-10-25 Paolo Bonzini * libgst/re.c: Call init_re from exported functions. 2007-10-21 Paolo Bonzini * libgst/comp.c: Add brackets to source code of #methodsFor:. Set isOldSyntax bit of the CompiledMethod header. * libgst/comp.h: Add isOldSyntax bit. * libgst/gst-parse.c: Parse isolated methods with new syntax. * libgst/tree.c: Add isOldSyntax argument to _gst_make_method. * libgst/tree.h: Likewise, and add it to AST. 2007-10-12 Paolo Bonzini * libgst/gst-parse.c: Don't replace instance variables except in the first declaration inside a subclass declaration. 2007-10-12 Paolo Bonzini * libgst/dict.inl: Use another scramble function suggested by Andres Valloud. 2007-10-09 Paolo Bonzini * libgst/save.c: Break hard links when saving. 2007-10-09 Paolo Bonzini * libgst/dict.inl: Do rotations correctly in scramble. 2007-10-08 Paolo Bonzini * libgst/dict.c: Add necessary class variables for rewrite. 2007-10-01 Stephen Compall * libgst/re.c: Add init_re, registering ASCII case table. 2007-09-27 Freddie Akeroyd Paolo Bonzini * libgst/cint.c: Wrap symlink to avoid errors in case the prototype is absent. * libgst/prims.def: Disable ENOTSOCK checking if constant not defined. 2007-09-27 Paolo Bonzini * libgst/gst-parse.c: Strengthen error checking for wrong "Class >> method [ ... ]" stanzas. 2007-09-25 Paolo Bonzini * libgst/re.c: Cache any read-only string literal. 2007-09-24 Paolo Bonzini * libgst/gst-parse.c: Fix NULL dereference on Smalltalk subclass: Foo [ ]. 2007-09-24 Paolo Bonzini * libgst/md-config.h: Disable register allocation tricks if not optimizing, as well as third register on Apple compilers. 2007-09-19 Paolo Bonzini * libgst/re.c: Yet another GC problem. 2007-09-17 Paolo Bonzini * libgst/comp.c: Fix GC problem with attributes. 2007-09-15 Paolo Bonzini * libgst/oop.h: Move NO_SIGSEGV_HANDLING... * libgst/oop.c: ... here. * libgst/save.c: Make writable mmap if defined. 2007-09-13 Paolo Bonzini * libgst/interp.inl: Fix 64-bit cleanliness error. 2007-09-12 Paolo Bonzini * libgst/save.c: Open image file with r+ and truncate it afterwards. * libgst/sysdep.c: Use O_CREAT for r+. 2007-09-03 Paolo Bonzini * libgst/input.c: Adjust by fileOffset when generating source string with _gst_counted_string_new. 2007-08-24 Paolo Bonzini * libgst/comp.c: Create deferred variable bindings with a path. Adjust calls to _gst_find_variable_binding. * libgst/dict.c: Add path variable to DeferredVariableBinding. * libgst/dict.h: Add path variable to struct gst_deferred_variable_binding. * libgst/sym.h: Remove last parameter from _gst_find_variable_binding. * libgst/sym.c: Assume last parameter of _gst_find_variable_binding to be true. Adjust call to _gst_make_deferred_binding_constant. * libgst/tree.h: Adjust last parameter of _gst_make_deferred_binding_constant. * libgst/tree.c: Turn last parameter of _gst_find_variable_binding into a tree. Support new constant types in _gst_print_tree. 2007-08-20 Paolo Bonzini * libgst/superop1.inl: Regenerate. * libgst/superop2.inl: Regenerate. * libgst/byte.def: Regenerate. * libgst/vm.def: Reenable superoperators. * libgst/opt.c: Reenable superoperators. 2007-08-20 Paolo Bonzini * libgst/comp.c: Make make_constant_oop global, adjust for new return value of _gst_find_variable_binding, create DeferredVariableBinding objects. Compile store-into- variable to store+pop+push. Adjust equal_constant to support CONST_DEFERRED_BINDING and adjusting for the new return value of _gst_find_variable_binding. * libgst/comp.h: Declare _gst_find_variable_binding. * libgst/dict.c: Add DeferredVariableBinding. * libgst/dict.h: Add DeferredVariableBinding and struct gst_deferred_variable_binding. * libgst/files.c: Add DeferBinding.st, load LookupKey hierarchy early. * libgst/opt.c: Temporarily disable superoperators. Pass LookupKeys in the verifier. * libgst/sym.c: Return a tree_node from _gst_find_variable_binding, adjust _gst_find_variable, add _gst_get_undeclared_dictionary. * libgst/sym.h: Adjust declarations. * libgst/tree.c: Add _gst_make_deferred_binding_constant. * libgst/tree.h: Add _gst_make_deferred_binding_constant. 2007-08-19 Paolo Bonzini * libgst/vm.def: Support non-Associations storing global variables. * libgst/xlat.c: Support non-Associations storing global variables. * libgst/print.c: Support LookupKeys storing global variables. * libgst/dict.c: Reload _gst_lookup_key_class on startup. 2007-08-13 Paolo Bonzini * libgst/dict.c: Dereference the VariableBinding stored in a CType. 2007-08-13 Paolo Bonzini * libgst/cint.c: Remove enum cdata_type, moved to cint.h. Reorder c_type_name and type_map accordingly. Add CDATA_UCHAR, CDATA_SHORT, and CDATA_USHORT. Convert from/to them appropriately in push_smalltalk_obj, get_ffi_type. * libgst/cint.h: Add enum cdata_type. * libgst/prims.def: Use enum cdata_type values. * libgst/sym.c: Add symbols for #short, #uShort, #uChar. * libgst/sym.h: Add symbols for #short, #uShort, #uChar. 2007-08-13 Paolo Bonzini * libgst/interp.c: Fix GC bug in _gst_prepare_execution_environment. 2007-08-13 Paolo Bonzini * libgst/callin.c: Use _gst_c_object_new instead of _gst_c_object_new_typed. * libgst/cint.c: Likewise. * libgst/dict.inl: Likewise. * libgst/dict.c: Remove _gst_c_object_type_ctype and _gst_c_type_new. Add a new parameter to _gst_c_object_new_typed and call it _gst_c_object_new; dereference the binding of the TYPEOOP. Remove _gst_alloc_cobject. * libgst/prims.def: Remove VMpr_CObject_alloc. Check receiver type for VMpr_CObject_allocType. Use _gst_c_object_new instead of _gst_c_object_new_typed. 2007-08-12 Paolo Bonzini * libgst/comp.c: Make literals read-only in make_oop_constant. * libgst/dict.inl: Make Float* and Character literals read-only. 2007-07-20 Paolo Bonzini * libgst/files.c: Load VFSZip.st. 2007-07-20 Paolo Bonzini * libgst/input.h: Fix prototype declaration when readline is not available. 2007-07-19 Paolo Bonzini * libgst/input.h: Turn second parameter of _gst_set_stream_info to OOP. * libgst/input.c: Likewise. * libgst/prims.def: Remove fileIn primitive. Remove check on file validity from fileInLine primitive. Adjust call to _gst_set_stream_info. 2007-07-17 Stephen Compall * libgst/prims.def: Rename compileString primitives to primCompile. * libgst/xlat.c: Mention #primCompile:. 2007-07-12 Paolo Bonzini * libgst/oop.c: When compacting, do not discard grey pages from the loaded space. Add _gst_print_grey_list. * libgst/oop.h: Add fields to delimit loaded space to struct memory_space. * libgst/save.c: Fill them in. 2007-07-12 Paolo Bonzini * libgst/dict.c: Fix pasto in _gst_grow_dictionary. 2007-07-11 Paolo Bonzini * libgst/interp-bc.inl: Reset _gst_except_flag to false at beginning of monitor_byte_codes. 2007-07-10 Paolo Bonzini * libgst/interp.c: Add break. 2007-07-10 Paolo Bonzini * libgst/lib.c: Rename... * libgst/files.c: ... to this. * libgst/files.c: Change "gst_" functions to "_gst_". * libgst/callin.c: Move gst_interpreter_proxy and _gst_init_vmproxy... * libgst/gstpub.c: ... here (new file). Add "gst_*" functions. * libgst/callin.h: Rename *cobject functions to *c_object. * libgst/interp.c: Change bool_addr_index to _gst_{get,set}_var. * libgst/prims.def: Switch to new interface. * libgst/files.c: Rename find_kernel_file to _gst_find_file, drop second parameter. * libgst/input.c: Add _gst_process_stdin, _gst_process_file. * libgst/gstpub.c: Add public and VMProxy counterparts. * libgst/comp.c: Turn _gst_invoke_hook parameter into an enum. * libgst/files.c: Turn _gst_invoke_hook parameter into an enum. * libgst/save.c: Turn _gst_invoke_hook parameter into an enum. * libgst/gstpub.c: Add public and VMProxy counterparts. * libgst/input.c: Add _gst_no_tty and turn "prompt" field into char *. * libgst/files.c: Remove --emacs-process and -S handling. * libgst/files.c: Create _gst_initialize out of init_paths and _gst_init_smalltalk, remove SMALLTALK_KERNEL and SMALLTALK_IMAGE handling out of init_paths, remove option handling, always derive image path from image file. * libgst/callin.c: Change _gst_init_smalltalk calls to _gst_initialize. * libgst/gst.h: Add enums for above changes. 2007-07-05 Paolo Bonzini * libgst/prims.def: Fix "==" vs. "=" typo. * libgst/sysdep.c: Fix previous change for Linux. 2007-07-05 Paolo Bonzini * libgst/lib.c: Add _gst_executable_path. * libgst/lib.h: Set it in gst_smalltalk_args. * libgst/dict.c: Set CSymbols.ExecutableFileName. * libgst/sysdep.c: Add _gst_find_executable. * libgst/sysdep.h: Declare _gst_find_executable. 2007-07-04 Paolo Bonzini * libgst/cint.c: Add binding for mkdtemp and chmod. 2007-07-03 Freddie Akeroyd Paolo Bonzini * libgst/alloc.c: Remove #undef small. * libgst/alloc.h: Move it here. * libgst/prims.def: Flush stdio files before quitting. * libgst/sysdep.c: Implement _gst_recv with recvfrom. 2007-07-03 Paolo Bonzini * libgst/dict.c: Export LibexecPath. 2007-07-01 Paolo Bonzini * libgst/prims.def: Remove bogus check on file in of FileDescriptor objects. 2007-06-28 Paolo Bonzini * libgst/lib.c: Ensure null termination of _gst_image_file_path. 2007-06-25 Paolo Bonzini * libgst/lex.c: Don't lose on integer literals followed by identifiers. 2007-06-24 Paolo Bonzini * libgst/lib.c: Put full path names into kernel/image paths and into the image file name. * libgst/lib.h: Adjust constness. 2007-06-19 Paolo Bonzini * libgst/sysdep.c: Use GetFullPathName under Windows. 2007-06-18 Paolo Bonzini * libgst/sysdep.c: Use utime if utimes missing. * tests/fileext.st: Run tests using Unix file separator. 2007-06-15 Freddie Akeroyd Paolo Bonzini * libgst/cint.c: Remove my_utime. * libgst/sysdep.c: Move it here as _gst_set_file_access_times. * libgst/sysdep.h: Declare it. * libgst/dict.c: Add CSymbols.PathSeparator. 2007-06-14 Paolo Bonzini * libgst/sysdep.c: Try VirtualAlloc with NULL address if a fixed address fails. 2007-06-11 Paolo Bonzini * libgst/cint.c: Add symlink function. 2007-06-07 Paolo Bonzini * libgst/comp.c: Initialize an attribute's arguments array before filling it, a GC may trigger while it is being created. 2007-06-06 Paolo Bonzini * libgst/dict.c: Add Continuation class. * libgst/dict.h: Add Continuation class. * libgst/interp.c: Add resume_suspended_context, extracted from change_process_context. * libgst/interp.h: Add Continuation class definition. * libgst/prims.def: Add a primitive for continuations. * libgst/lib.c: Add Continuation.st and Generator.st. 2007-06-06 Paolo Bonzini * libgst/input.c: Be quiet, but still automatically add periods, when in Emacs mode. * libgst/comp.c: Likewise. 2007-06-05 Paolo Bonzini * libgst/interp.h: Add PRIM_SHUTDOWN_WRITE. * libgst/interp.c: Implement it. Fix bug in PRIM_MK_TEMP. * libgst/sysdep.c: Use pipes/sockets instead of pty's. 2007-06-01 Paolo Bonzini * libgst/lib.c: Load StreamOps.st. 2007-05-31 Paolo Bonzini * libgst/gst-parse.c: Support [:arg1 :arg2] syntax for blocks. 2007-05-29 Paolo Bonzini * libgst/gst-parse.c: Revert meaning of the last parameter to parse_doit. Skip over the final '!' in parse_chunks, don't do so in parse_doit and parse_method_list. Exit parse_namespace_definition upon finding a '!'. 2007-05-26 Paolo Bonzini * libgst/lex.c: Pass radix when converting ScaledDecimals like 2r1.1s. * libgst/sym.c: Change #asScaledDecimal:scale: to #asScaledDecimal:radix:scale:. * libgst/sym.h: Likewise. 2007-05-25 Daniele Sciascia * libgst/dict.c: Turn _gst_find_shared_pool_variable into _gst_namespace_association_at, add _gst_namespace_at. * libgst/dict.h: Declare it. * libgst/gst-parse.c: Support attributes both before and after temporaries. Improve error recovery. Set the correct namespace when extending a class. Fix error locations. Support class definition in a namespace definition. Replace "Class protocol" with "Foo class". Support subclassing nil. Lookup classes in the superspaces too. * libgst/sym.c: Use _gst_namespace_association_at. 2007-05-24 Paolo Bonzini * libgst/dict.c: Don't trust {FLT,DBL,LDBL}_DIG. 2007-05-23 Paolo Bonzini * libgst/lib.c: Remove TokenStream.st. Fix pasto. * libgst/dict.c: Remove TokenStream and _gst_token_stream_class. * libgst/dict.h: Remove _gst_token_stream_class. 2007-05-07 Stephen Compall * libgst/sysdep.c: Fix return value of anon_mmap_commit. 2007-04-18 Paolo Bonzini * libgst/md-config.h: Fix spelling of __PIC__. 2007-04-17 Paolo Bonzini * libgst/comp.c: Move all FileSegment stuff to input.c * libgst/input.c: Rename _gst_get_cur_string to _gst_get_source_string and return FileSegments or substrings here. Concatenate pieces of readline input like in a STREAM_OOP. * libgst/input.h: Adjust _gst_get_cur_string prototype. 2007-04-17 Paolo Bonzini * libgst/input.c: More Smalltalk Stream fixes. 2007-04-17 Paolo Bonzini * libgst/lex.c: Load SysDict.st early in the bootstrap process. * libgst/prims.def: Remove VMpr_Dictionary_atPut. 2007-04-17 Paolo Bonzini * libgst/input.c: Fix latent bug with Smalltalk Stream parsing. 2007-04-17 Paolo Bonzini * libgst/lex.c: Fix bug if first line entered at REPL is empty. 2007-04-16 Paolo Bonzini * libgst/interp-bc.inl: Fix building on s390. 2007-04-11 Daniele Sciascia * libgst/gst-parse.c: Fix locations in error messages. * libgst/lex.c: Reset parentheses only when showing prompts. 2007-04-11 Daniele Sciascia * libgst/gst-parse.c: Fix parsing of "Eval [ foo := ]". 2007-04-11 Paolo Bonzini Daniele Sciascia * libgst/gst-parse.c: Improved error recovery. 2007-04-11 Paolo Bonzini Daniele Sciascia * libgst/gst-parse.c: Fix parsing when expressions were required but not found. 2007-04-11 Paolo Bonzini Daniele Sciascia * libgst/dict.c: Load _gst_binding_dictionary_class on runtime. * libgst/gst-parse.c: Fix setting up class variables. 2007-04-11 Daniele Sciascia * libgst/comp.c: Make compute_keyword_selector public. * libgst/comp.h: Likewise. * libgst/gst-parse.c: Lots of cool new stuff. * libgst/gst-parse.h: Provide prototype for _gst_print_tokens. 2007-04-11 Paolo Bonzini * libgst/comp.c: Add undeclared parameter to _gst_exeecute_statements. Make a statement list if necessary. Adjust callers. Add CONST_BINDING case to equal_constant and make_constant_oop. * libgst/comp.h: Adjust prototypes. * libgst/gst-parse.c: Rewrite parse_doit. Set undeclared parsing around method compilation. Don't check errors from _gst_make_binding_constant * libgst/gstpriv.h: Load sym.h early. * libgst/input.c: Don't return true in _gst_get_cur_stream_prompt for emacs mode. * libgst/interp.c: Remove bogus comment. * libgst/interp.h: Reword bogus comment. * libgst/lex.c: Guess if a period should be added at end of line. * libgst/lib.c: Set undeclared parsing around file loading. * libgst/prims.def: Fix warning. Set undeclared parsing around filein. * libgst/sym.c: Add possibility to store undeclared variablers into a custom dictionary. * libgst/sym.h: Add related definitions. * libgst/tree.c: Create a CONST_BINDING in _gst_make_binding_constant. * libgst/tree.h: Add CONST_BINDING to const_type enum. 2007-03-30 Paolo Bonzini * libgst/comp.c: Change _gst_declare_tracing to int, use value of 2 for tracing variables intead _gst_trace_kernel_*. * libgst/comp.h: Likewise. * libgst/interp.c: Likewise. Adapt bool_addr_index to return int *. * libgst/interp.h: Likewise. * libgst/prims.def: Support passing/returning an int in trace flag get/set primitives. * libgst/lib.c: Remove -d, -e options, and map old -[de] to new -[DE], allowing the user to specify them multiple times. Keep only long version of -p, make option -Q synonym of -q (it was in the documentation). Kill _gst_trace_kernel_*. Only valid verbosity values are now 1/2/3. * libgst/oop.h: Change _gst_gc_message to int. * libgst/oop.c: Likewise, adapting to changes to the verbosity values. 2007-03-28 Paolo Bonzini * libgst/gstpriv.h: Support MacOS X/PPC macros to use lwbrx. * libgst/save.c: Fix primitive table checksum for 64-biy systems. 2007-03-28 Paolo Bonzini * libgst/lex.c: Fix parsing of #-123. 2007-03-20 Paolo Bonzini * libgst/comp.c: Look for attribute, write result in this_method_category, pick it in _gst_make_new_method. Add a default category argument to _gst_make_new_method. Always create a MethodInfo object in _gst_make_new_method. * libgst/comp.h: Adjust _gst_make_new_method prototype. * libgst/prims.def: Adjust _gst_make_new_method prototype. * libgst/sym.c: Add _gst_category_symbol. * libgst/sym.h: Add _gst_category_symbol. 2007-03-19 Paolo Bonzini * libgst/lib.c: Load Random.st after system is initialized. * libgst/dict.c: Remove Random class and _gst_random_class. * libgst/dict.h: Remove _gst_random_class. 2007-03-12 Paolo Bonzini * libgst/comp.c: Fix off-by-one error. * libgst/input.c: Fix line/column assignment. Don't provide method source for readline stream. 2007-03-08 Paolo Bonzini * libgst/comp.c: Create FileSegment and MethodInfo object in _gst_make_new_method, pass the MethodInfo down to method_new. 2007-02-22 Paolo Bonzini * libgst/oop.c: Remove two unused variables. * libgst/comp.c: Add start/end position parameters to method_new, method_info_new, file_segment_new, _gst_make_new_method. Adjust callers. Get ending location of the method in _gst_execute_statements. * libgst/comp.h: Adjust prototype of _gst_make_new_method. * libgst/gst-parse.c: Don't call _gst_clear_method_start_pos. Get ending location of the method in parse_method. * libgst/gst-parse.h: Add file_offset field to YYLTYPE. * libgst/input.c: Initialize fileOffset to -1 for a new stream, and with lseek for a new file stream. Update it when reading from a file into the buffer. Use it to avoid lseeking during the parsing, so that _gst_get_location can quickly compute the file offset and store it into the YYLTYPE. Make _gst_get_location return the YYLTYPE. Remove _gst_get_cur_file_pos, _gst_get_method_start_pos and _gst_clear_method_start_pos, and the field they used in struct stream. * libgst/input.h: Remove _gst_get_cur_file_pos, _gst_get_method_start_pos and _gst_clear_method_start_pos, update the prototype of _gst_get_location and make it pure. * libgst/lex.c: Adjust calls to _gst_get_location. * libgst/prims.def: Adjust call to _gst_make_new_method. * libgst/tree.c: Accept ending location in _gst_make_method. * libgst/tree.h: Add new field to struct method_node and prototype of _gst_make_method. 2007-02-10 Paolo Bonzini * libgst/dict.c: Remove KernelFileLocalPath. Don't touch KernelFilePath on reload. Export KernelFileUserPath. * libgst/lib.c: Add --image-directory and --kernel-directory. Add a struct loaded_file used to store files given on the command line. Find path of user init/user pre/site pre files in init_paths, delete load_user_init_file and load_user_pre_image_file. Call init_paths after parse_args. Rewrite find_kernel_file, place kernel override files in ~/.st too (if one needs per-image overrides they can use --kernel-directory). Remove some variables that are now unused. Simplify ok_to_load_binary as the new semantics remove the need for some checks. Export the path to ~/.st in _gst_user_file_base_path. * libgst/lib.h: Export _gst_user_file_base_path. * libgst/sysdep.c: Canonicalize path in _gst_get_full_file_name. 2007-02-05 Paolo Bonzini * libgst/dict.c: Add variables and declarations for weak objects. * libgst/dict.h: Add variables for weak objects. * libgst/lib.c: Load WeakObjects.st as part of the kernel classes. 2007-01-29 Paolo Bonzini * libgst/lex.c: Rename ipowl to mul_powl, support gradual underflow. 2007-01-28 Paolo Bonzini * libgst/prims.def: Use truncl and lrint to implement conversion from float to integer. 2007-01-28 Paolo Bonzini * libgst/mpz.c: Fix right shift bug. 2007-01-27 Paolo Bonzini * libgst/lex.c: Clear obstack after parsing radix. 2007-01-15 Paolo Bonzini * libgst/prims.def: Fix error checking in previous check in. 2007-01-11 Paolo Bonzini * libgst/prims.def: When changing an object's class, allow the new class to not be a kind of Behavior, as long as the superclass flagged in it is. 2007-01-03 Paolo Bonzini * libgst/events.c: Avoid infinite loop. 2006-12-28 Paolo Bonzini * libgst/dict.c: Change _gst_init_dictionary_on_image_load to be whether the primitive table's checksum is ok. If it is, just copy the default primitive table just like in _gst_init_dictionary. * libgst/dict.h: Adjust for above change. * libgst/genpr-parse.y: Compute MD5 of DEF_FIL as checksum and print it. * libgst/interp.h: Declare _gst_primitives_md5. * libgst/save.c: Save its contents, and compare it to pass the new flag to _gst_init_dictionary_on_image_load. Move checks from load_snapshot to load_file_version. 2006-12-28 Paolo Bonzini * libgst/gstpriv.h: Remove F_FREE. * libgst/oop.c: Remove loops setting flags to F_FREE. Set flags to 0 instead of F_FREE elsewhere. * libgst/oop.h: Fix wrong comment. * libgst/oop.inl: Adjust IS_OOP_FREE. * libgst/print.c: Use IS_OOP_FREE. * libgst/save.c: Set flags to 0 instead of F_FREE. Use IS_OOP_FREE. Remove wrong comment. 2006-12-28 Paolo Bonzini * libgst/builtins.gperf: Remove _COLON from the enum for special bytecodes. * libgst/byte.def: Likewise. * libgst/vm.def: Likewise. * libgst/xlat.c: Likewise. * libgst/comp.c: Remove the possibility to inline #perform:. * libgst/byte.c: Turn _gst_builtin_selectors into an array of structs (instead of pointers). * libgst/opt.c: Likewise. * libgst/sym.c: Likewise. * libgst/vm.def: Use _gst_builtin_selectors instead of symbols defined in sym.c (not slower with the change above). * libgst/xlat.c: Only store the opcode in special_send_bytecodes and use _gst_builtin_selectors for the other pieces of information. * libgst/dict.c: Don't reload the _gst_*_class variables unless necessary. Pass the class to identity_dictionary_new and adjust the sole caller, _gst_valid_class_method_dictionary. Split the creation of symbols in two parts (creating symbols, and populating the symbol table with SymLink objects); call _gst_restore_symbols when loading the image. Remove _gst_directed_message_new_args. * libgst/interp.c: Remove commented out code to start call-ins through Process>>#startExecution:. * libgst/sym.c: Remove symbols for the special selectors. New functions alloc_symbol_oop and alloc_symlink to support two-phase creation of symbols in the image. Add _gst_smalltalk_namespace_symbol. New functions intern_string_fast and _gst_restore_symbols to support fast reloading of symbols when loading the image. * libgst/sym.h: Adjust for changes to sym.c. * libgst/genvm-parse.y: Add const qualifier to yyprint. 2006-12-28 Paolo Bonzini * libgst/mpz.c: Fix warnings in _gst_mpz_divexact. 2006-12-28 Paolo Bonzini * libgst/gstpriv.h: Reserve three less bits to runtime flags, add F_LOADED. * libgst/oop.c: The address of loaded objects never changes, and they're always old. Never compact loaded objects. Never free them too. * libgst/print.c: Print loaded OOPs correctly. * libgst/save.c: Define and use buffer_advance. Try reusing the mmap-ed area in load_normal_oops; free buffer in load_normal_oops only if copy-on-write is not used. Mmap all the file in a single step, and using MAP_PRIVATE, and only do the "read" method in buffer_fill. Rename use_mmap to buf_used_mmap. Save objects with the old bit set and without the F_RUNTIME flags. 2006-12-22 Paolo Bonzini * libgst/mpz.c: Fix a bug in _gst_mpz_divexact, causing memory corruption sometimes. 2006-12-22 Paolo Bonzini * libgst/lex.c: Previous change not 64-bit clean, obstack_chunk_size returns unsigned rather than int or size_t. 2006-12-21 Paolo Bonzini * libgst/lex.c: Build strings on obstack instead of the str.c buffer. Otherwise the buffer could be cleared out by oop.c when it uses it to store the live ephemeron OOPs. * libgst/str.c: Remove dead functions. * libgst/str.h: Likewise. 2006-12-19 Paolo Bonzini * libgst/heap.c: Remove arithmetic on void *. * libgst/sym.c: Remove unused symbols. * libgst/sym.h: Remove unused symbols. * libgst/vm.def: Use _gst_must_be_boolean_symbol. * libgst/vm.inl: Regenerate. 2006-12-18 Paolo Bonzini * libgst/save.c: Don't uselessly mark unused OOPs as free. 2006-12-18 Paolo Bonzini * libgst/save.c: Miscellaneous speed-ups, including caching the number of free OOPs in the saved file. 2006-12-18 Paolo Bonzini * libgst/alloc.c: Adjust calls to _gst_heap_create. * libgst/lib.c: Likewise. * libgst/oop.c: Likewise. * libgst/save.c: Likewise. * libgst/heap.c: Add address parameter to _gst_heap_create. * libgst/heap.h: Likewise for declaration. * libgst/oop.h: Likewise for _gst_init_oop_table declaration. * libgst/sysdep.c: Add address parameter to _gst_osmem_reserve and to the implementations of the function. Support MAP_AUTORESRV as a synonym of MAP_NORESERVE. * libgst/sysdep.h: Likewise for declaration. 2006-12-15 Paolo Bonzini * libgst/alloc.c: Remove assertions if !OPTIMIZE. Increase default allocation granularity. 2006-12-15 Paolo Bonzini * libgst/save.c: Store object table base in the image, adjust based on the delta upon loading. Inline functions that are not used anymore upon saving due to the previous change. Reset nativeIP upon saving rather than upon loading. 2006-12-14 Paolo Bonzini * libgst/cint.c: Move gst_cfunc_descriptor to cint.h. Accept a nil cFunction inside a descriptor (now happens upon image load), remove _gst_restore_cfunc_descriptor. * libgst/cint.h: Adjust for cint.c changes. * libgst/comp.c: Remove _gst_restore_primitive_number. * libgst/comp.h: Remove _gst_restore_primitive_number. * libgst/dict.c: Initialize primitive table from default in _gst_init_dictionary, and from the image in prepare_primitives_table (which replaces prepare_primitive_numbers_map). Don't reset the VMPrimitives dictionary upon image load, and don't walk the OOP table. * libgst/genpr-parse.y: Initialize _gst_default_primitive_table instead of _gst_primitive_table. * libgst/interp.c: Use _gst_default_primitive_table in _gst_get_primitive_attributes, add _gst_set_primitive_attributes. Make the primitive tables public. * libgst/interp.h: Adjust for the above. * libgst/save.c: Allocate temporary storage for the object that are about to be saved. Massage the CallinProcess, Process, Semaphore and CFunctionDescriptor instances in that temporary storage rather than at load time. 2006-12-14 Paolo Bonzini * libgst/input.c: Initialize completions only when a readline stream is pushed. 2006-12-12 Paolo Bonzini * libgst/oop.c: Proceed recursively if marking the ephemerons' slots finds more ephemerons. Add more debugging functions. Rename GC_DEBUGGING and MMAN_DEBUGGING to GC_DEBUG_OUTPUT and MMAN_DEBUG_OUTPUT. Preprocessor symbol GC_DEBUGGING now enables sanity checks. 2006-12-07 Paolo Bonzini * libgst/mpz.c: Use mpn_cmp, mpn_scan1, mpn_bdivmod. * libgst/mpz.h: Export _gst_mpz_divexact. * libgst/prims.def: Add primitive for _gst_mpz_divexact. 2006-12-07 Paolo Bonzini * libgst/cint.c: Don't push self for anything but CDATA_SELF and CDATA_SELF_OOP. 2006-12-05 Paolo Bonzini *** Version 2.3 released. 2006-12-05 Paolo Bonzini * libgst/lex.c: Reject character literals above 128. 2006-12-02 Paolo Bonzini * libgst/mpz.c: Make 64-bit clean. 2006-12-01 Paolo Bonzini * libgst/re.c: Remove ISO C99-ism. 2006-11-30 Paolo Bonzini * libgst/interp.c: Remove misleading comment. * libgst/xlat.c: Export SP in gen_dirty_block around the function call, as it may cause a GC. 2006-11-27 Paolo Bonzini * libgst/xlat.c: Use _p variants appropriately. 2006-11-21 Paolo Bonzini * libgst/re.c: Add make_re_results. Remove _gst_re_free_registers. * libgst/re.h: Remove _gst_re_free_registers. * libgst/cint.c: Remove _gst_re_free_registers. * libgst/callin.c (_gst_class_name_to_oop): Support namespaces. (_gst_oop_at_put): Fix off-by-one bug. 2006-11-21 Paolo Bonzini * libgst/alloc.c: Add GPL exception. * libgst/alloc.h: Add GPL exception. * libgst/byte.c: Add GPL exception. * libgst/byte.def: Add GPL exception. * libgst/byte.h: Add GPL exception. * libgst/callin.c: Add GPL exception. * libgst/callin.h: Add GPL exception. * libgst/cint.c: Add GPL exception. * libgst/cint.h: Add GPL exception. * libgst/comp.c: Add GPL exception. * libgst/comp.h: Add GPL exception. * libgst/comp.inl: Add GPL exception. * libgst/dict.c: Add GPL exception. * libgst/dict.h: Add GPL exception. * libgst/dict.inl: Add GPL exception. * libgst/events.c: Add GPL exception. * libgst/events.h: Add GPL exception. * libgst/genbc-decl.y: Add GPL exception. * libgst/genbc-impl.y: Add GPL exception. * libgst/genbc-scan.c: Add GPL exception. * libgst/genbc-scan.l: Add GPL exception. * libgst/genbc.c: Add GPL exception. * libgst/genbc.h: Add GPL exception. * libgst/genpr-parse.y: Add GPL exception. * libgst/genpr-scan.c: Add GPL exception. * libgst/genpr-scan.l: Add GPL exception. * libgst/genprims.h: Add GPL exception. * libgst/genvm-parse.y: Add GPL exception. * libgst/genvm-scan.c: Add GPL exception. * libgst/genvm-scan.l: Add GPL exception. * libgst/genvm.h: Add GPL exception. * libgst/gst-parse.c: Add GPL exception. * libgst/gst-parse.h: Add GPL exception. * libgst/gst.h: Add GPL exception. * libgst/gstpriv.h: Add GPL exception. * libgst/gstpub.h: Add GPL exception. * libgst/heap.c: Add GPL exception. * libgst/heap.h: Add GPL exception. * libgst/input.c: Add GPL exception. * libgst/input.h: Add GPL exception. * libgst/interp-bc.inl: Add GPL exception. * libgst/interp-jit.inl: Add GPL exception. * libgst/interp.c: Add GPL exception. * libgst/interp.h: Add GPL exception. * libgst/interp.inl: Add GPL exception. * libgst/jitpriv.h: Add GPL exception. * libgst/lex.c: Add GPL exception. * libgst/lex.h: Add GPL exception. * libgst/lib.c: Add GPL exception. * libgst/lib.h: Add GPL exception. * libgst/md-config.h: Add GPL exception. * libgst/memzero.h: Add GPL exception. * libgst/oop.c: Add GPL exception. * libgst/oop.h: Add GPL exception. * libgst/oop.inl: Add GPL exception. * libgst/opt.c: Add GPL exception. * libgst/opt.h: Add GPL exception. * libgst/prims.def: Add GPL exception. * libgst/print.c: Add GPL exception. * libgst/print.h: Add GPL exception. * libgst/re.c: Add GPL exception. * libgst/re.h: Add GPL exception. * libgst/save.c: Add GPL exception. * libgst/save.h: Add GPL exception. * libgst/security.c: Add GPL exception. * libgst/security.h: Add GPL exception. * libgst/str.c: Add GPL exception. * libgst/str.h: Add GPL exception. * libgst/sym.c: Add GPL exception. * libgst/sym.h: Add GPL exception. * libgst/sysdep.c: Add GPL exception. * libgst/sysdep.h: Add GPL exception. * libgst/tree.c: Add GPL exception. * libgst/tree.h: Add GPL exception. * libgst/vm.def: Add GPL exception. * libgst/xlat.c: Add GPL exception. * libgst/xlat.h: Add GPL exception. * main.c: Add GPL exception. 2006-11-19 Paolo Bonzini * libgst/prims.def: Fetch receiver from _gst_self when passing _gst_this_context_oop to the C call-out primitives. Suspend current process before quitting. 2006-11-15 Paolo Bonzini * libgst/builtins.gperf: Rename #callFrom:into: into #callInto:. * libgst/builtins.inl: Regenerate. * libgst/prims.def: Support not passing the context to C call-out primitives, and a "nil" paramter to #callInto:. 2006-11-03 Paolo Bonzini * libgst/gst.h: Compile on C++. Rename mst_Object to gst_object. * libgst/gstpub.h: Likewise. * libgst/comp.c: Rename mst_Object to gst_object. * libgst/interp.c: Likewise. * libgst/lex.c: Likewise. * libgst/oop.c: Likewise. * libgst/oop.h: Likewise. * libgst/print.c: Likewise. * libgst/print.h: Likewise. * libgst/dict.c: Likewise. * libgst/save.c: Likewise. * libgst/security.c: Likewise. * libgst/sym.c: Likewise. * libgst/dict.h: Likewise. * libgst/tree.c: Likewise. * libgst/xlat.c: Likewise. * libgst/comp.inl: Likewise. * libgst/dict.inl: Likewise. * libgst/oop.inl: Likewise. * libgst/prims.def: Likewise. 2006-11-03 Paolo Bonzini * libgst/interp.c: Check if we hit the bottom of the stack in disable_non_unwind_contexts, and percolate a return value of true through unwind_to up to unwind_method. Otherwise return false from both disable_non_unwind_contexts and unwind_to. 2006-11-02 Paolo Bonzini * libgst/opt.c: Fix verification of {{}}. 2006-10-31 Paolo Bonzini * libgst/events.c: Look for events (especially POLLHUP) even if poll returns 0. 2006-10-31 Paolo Bonzini * libgst/prims.def: Make CObject primitives more resilient to bad contents of the CType. 2006-10-25 Paolo Bonzini * libgst/gst-parse.c: Extract parse_variable_primary_1 out of parse_variable_primary. 2006-10-16 Paolo Bonzini * libgst/xlat.c: Update gen_send for new super-send implementation. Disallow deferred super sends. Fix bug in String>>#at: inlining and in compiling a gen_push_self+gen_alt_self sequence. Remove C99-ism in emit_method_prolog. * libgst/xlat.h: Fix IS_VALID_IP for methodStart == 0. 2006-10-16 Roman Zippel * libgst/alloc.h: Add padding to the bitfields. 2006-10-11 Paolo Bonzini * libgst/cint.c: Avoid buffer overflow on empty variadic argument. 2006-10-05 Paolo Bonzini * libgst/lib.c: Improve help message to document -f. 2006-10-05 Paolo Bonzini * libgst/interp.c: Make less verbose on backtraces. * libgst/oop.c: Make less verbose on scavenging. 2006-09-29 Paolo Bonzini * libgst/comp.c: Use _gst_get_method_start_pos to find if we can use _gst_get_cur_file_pos. * libgst/input.c: Track file offset of FileStream objects. Extend buffers when a new hunk is needed, shrink it on _gst_get_cur_string. Use buffer and file offset tracking it to support _gst_get_cur_file_pos and _gst_get_cur_string for STREAM_OOP streams. Delete _gst_get_cur_readline as it is the same as _gst_get_cur_string * libgst/input.h: Delete _gst_get_cur_readline. 2006-09-24 Paolo Bonzini * libgst/dict.inl: Fix checking builds. 2006-09-22 Paolo Bonzini * libgst/interp-bc.inl: Shut up compiler warnings. * libgst/cint.c: Declare regex functions. * libgst/re.c, libgst/re.h: Move from examples. Adapt since it ` is not anymore a module. * libgst/lib.c: Add Regex.st. 2006-09-15 Paolo Bonzini * libgst/byte.c: Include match.h. * libgst/opt.c: Include match.h. * libgst/xlat.c: Include match.h. * libgst/gstpriv.h: Don't. * libgst/cint.c: Avoid stupid warning. * libgst/dict.inl: Make IS_A_CLASS/IS_A_METACLASS more robust. * libgst/opt.c: Detect invalid sends to super. * libgst/comp.c: Push class, not superclass for send to super. * libgst/vm.def: Adapt. 2006-09-13 Paolo Bonzini * libgst/comp.c (compile_send): Compile receiver superclass for sends to super. * libgst/opt.c: Add receiver class to balance for send to super. Replace "+= -x" with "-= x" throughout. * libgst/tree.h: Adjust _gst_make_oop_constant comment. * libgst/vm.def (SEND_SUPER, SEND_SUPER_IMMEDIATE): Pop class OOP. (SEND_TO_SUPER): Get methodClass argument. 2006-09-08 Paolo Bonzini * libgst/cint.c: Wrap utime. 2006-09-05 Paolo Bonzini * libgst/dict.c, libgst/dict.inl, libgst/gstpriv.h, libgst/gst-parse.c: Adjust macro names for upgrade to Autoconf 2.60. 2006-07-20 Paolo Bonzini * libgst/lib.c: Load Getopt.st. 2006-07-20 Paolo Bonzini * libgst/input.c: Merge my_close into _gst_pop_stream. Always free memory. Initialize fileNameOOP for FileDescriptors in _gst_push_stream_oop. Clear the fileName field in push_new_stream. Fix STREAM_OOP case in my_getc. Use fileNameOOP to print error messages. * libgst/prims.def: New primitives VMpr_Stream_fileIn and VMpr_Stream_fileInLine, extracted from the fileOp primitive. 2006-07-20 Paolo Bonzini * libgst/dict.c: Add 'peek' variable to FileDescriptor. * libgst/dict.h: Add 'peek' variable to struct gst_file_stream. * libgst/input.c: Leave poll_and_read upon POLLHUP. * libgst/interp.h: Add PRIM_GET_CHARS_AT and PRIM_PUT_CHARS_AT. * libgst/prims.def: Remove useless fstat call, accept any byte or character class in read/write primitives, implement pread and pwrite primitives. 2006-07-18 Paolo Bonzini * libgst/callin.c: Support wchars and wstrings. * libgst/callin.h: Likewise. * libgst/cint.c: Likewise. * libgst/gstpub.h: Likewise. * libgst/sym.c: Add new symbols. * libgst/sym.h: Likewise. * libgst/comp.c: Support CONST_CHAR in equal_constant and make_constant_oop. * libgst/dict.c: Add UnicodeCharacter and UnicodeString. Change instance and class variable names for Character. Add #utf32 shape element size in _gst_log2_sizes. Add helper functions for callin.c and cint.c changes above. * libgst/dict.h: Add gst_char and gst_unicode_string, and declare the helper functions. * libgst/dict.inl: Move here CHAR_OOP_AT from oop.inl; provide CHAR_OOP_VALUE here with a new definition. Add char_new. Support #utf32 shape. * libgst/gst-parse.c: Drop BYTE_LITERAL tokens. Check range of integers instead. Support $< INTEGER_LITERAL > tokens. * libgst/gst-parse.h: Remove cval from YYSTYPE. * libgst/gstpriv.h: Add ISP_UTF32; include wchar.h. * libgst/lex.c: Match the gst-parse.c changes. Use ival instead of cval. Support printing non-ASCII CHAR_LITERALs with their code points. * libgst/lib.c: Load UniChar.st and UniString.st. * libgst/oop.c: Fix a comment's spacing. * libgst/oop.inl: Remove CHAR_OOP_AT and CHAR_OOP_VALUE. * libgst/prims.def: Define VMpr_CharacterArray_valueAt, VMpr_CharacterArray_valueAtPut, VMpr_UnicodeCharacter_create, VMpr_Character_equal. Accept some UnicodeCharacters in VMpr_Memory_atPut and VMpr_CObject_atPut. * libgst/print.c: Print non-ASCII Characters and UnicodeCharacters with their code points. * libgst/tree.c: Make a CONST_CHAR in _gst_make_char_constant, not a CONST_OOP (partly undoing 2000-09-09 change), and accept an int. * libgst/tree.h: Add back CONST_CHAR. 2006-07-13 Paolo Bonzini * libgst/events.c (_gst_sync_file_polling): Prepare pfd.revents by zeroing it. 2006-04-26 Paolo Bonzini * libgst/gst-parse.c (parse_doit): Do not read other tokens after an EOF. 2006-04-18 Paolo Bonzini * libgst/gst-parse.c (parse_array_constructor): Do not crash on {} or on an invalid attribute like in 'a <3 4>'. 2006-02-12 Paolo Bonzini * libgst/comp.c (equal_constant): Compare floating point constants with memcmp. 2005-11-30 Paolo Bonzini * libgst/vm.def: Refine previous change using OOP_CLASS instead of IS_CLASS. 2005-11-30 Paolo Bonzini * libgst/vm.def: Shortcut FloatD/Integer mixed math, and FloatD division. 2005-11-30 Paolo Bonzini * libgst/xlat.c: Fix ISP_CHARACTER typo. 2005-11-29 Paolo Bonzini * libgst/vm.def: Make the #at: and #at:put: cache store the spec, and only work on primitives 60/61. * libgst/interp.c: Adjust. New functions cached_index_oop_primitive and cached_index_oop_put_primitive. 2005-11-29 Paolo Bonzini * libgst/dict.c (class_info): Use ISP_CHARACTER shape for String and Symbol. (_gst_log2_sizes): Adjust for ISP_CHARACTER. * libgst/dict.inl (index_oop_put_spec, index_oop_spec): New, from index_oop_put and index_oop. Fix typos in handling of ISP_FLOAT and ISP_DOUBLE. Handle ISP_CHARACTER. (index_oop_put, index_oop): Use them. (index_string_oop_put, index_string_oop): Delete. * libgst/gstpriv.h: Define ISP_CHARACTER. * libgst/prims.def (VMpr_String_basicAt, VMpr_String_basicAtPut): Delete. (VMpr_String_similarityTo): Accept ISP_CHARACTER shaped classes. (VMpr_ByteArray_replaceFromToWithStartingAt): Accept ISP_SCHAR and ISP_CHARACTER shaped classes as well. * libgst/xlat.c (emit_basic_size_in_r0): Accept ISP_SCHAR and ISP_CHARACTER shaped classes as well. (emit_inlined_primitive): Accept ISP_SCHAR and ISP_CHARACTER shaped classes as well. 2005-11-29 Paolo Bonzini * libgst/interp.h (execute_primitive_operation): Do not declare. * libgst/interp.c (execute_primitive_operation): New name of _gst_execute_primitive_operation. Make static and inline. * libgst/interp-bc.inl: Adjust. * libgst/interp-jit.inl: Adjust. * libgst/vm.def: Adjust. 2005-11-21 Paolo Bonzini * libgst/dict.c (_gst_string_new, _gst_counted_string_new): Handle zero-length strings. * libgst/interp.c (_gst_init_signals): Handle SIGTERM. (interrupt_handler): Exit on SIGINT or SIGTERM. 2005-09-18 Paolo Bonzini * libgst/callin.h: New methods for the interpreter proxy. * libgst/callin.c: New methods for the interpreter proxy. * libgst/gstpub.h: New methods for the interpreter proxy. * libgst/interp.h: New function _gst_find_method, moved from interp.c. Declare method_cache_entry. * libgst/interp.c: Rename find_method to _gst_find_method, remove declarations of find_method and method_cache_entry. 2005-09-12 Mike Anderson * libgst/events.c: Fix bug with pollfds being lost if a previous one has an error. 2005-09-05 Paolo Bonzini * libgst/gst-parse.c: Do not crash on #[]. 2005-09-02 Paolo Bonzini * libgst/save.c: Use a better #! sequence. 2005-08-30 Paolo Bonzini * libgst/oop.c: Fix pasto (SIZEOF_LONG instead of SIZEOF_OOP). * libgst/comp.c: Do not emit PUSH_INTEGER for integers equal or bigger than 2^31. * libgst/byte.h: Change final argument of compile_byte to int. * libgst/byte.c: Likewise. 2005-08-30 Paolo Bonzini * libgst/mpz.c: Fix 64-bit cleanliness problem. 2005-08-28 Paolo Bonzini * libgst/gst-parse.c: Remove last parameter to parse_cascaded_messages. 2005-08-28 Paolo Bonzini * libgst/gstpriv.h: Define ENABLE_SECURITY. * libgst/gst-parse.c: Fix warnings. * libgst/opt.c: Reenable verifier. 2005-08-28 Paolo Bonzini * libgst/input.c: Add to input_stream a method_start_pos member. Clear it in push_new_stream and _gst_set_stream_info. Set it in _gst_get_location. Move _gst_get_method_start_pos and _gst_clear_method_start_pos here from lex.c. * libgst/lex.c: Remove the aforementioned two functions and the code mentioning the local variable method_start_pos. * libgst/lex.h: Move the functions from here... * libgst/input.h: ... to here and make _gst_get_method_start_pos and _gst_get_cur_file_pos return off_t. * libgst/comp.c: Make usage of these two functions 64-bit safe. 2005-08-14 Paolo Bonzini * libgst/cint.c: Add lstat. 2005-08-07 Paolo Bonzini * libgst/cint.c: Do my math correctly. 2005-06-17 Paolo Bonzini * libgst/cint.c: Do not use ffi_type_slong, it is a 64-bit type! * libgst/gst-parse.c: Fix more bugs in creation of FileSegments. 2005-06-16 Paolo Bonzini * libgst/lex.c: Fix bugs in creation of FileSegments. * libgst/gst-parse.c: Fix bugs in creation of FileSegments. * libgst/gstpriv.h: Fixes for GCC 4.0.0. 2005-04-09 Paolo Bonzini * libgst/gst-parse.c (expected): Fix spacing. (parse_block): Fix "expected" error message. (parse_block_variables): Remove useless check for EOF. 2005-04-04 Paolo Bonzini * libgst/callin.c (_gst_eval_code, _gst_eval_expr): Do not use _gst_compile_code for communication to _gst_parse_stream, use a parameter to it instead. * libgst/comp.c (_gst_set_compilation_class): Extract out of _gst_set_compilation_category. (_gst_install_initial_methods, _gst_execute_statements): Adjust. (_gst_make_attribute): Execute statements for the arguments here. * comp.h (_gst_set_compilation_class): New prototype. (_gst_set_compilation_category): Adjust prototype. * libgst/gst-parse.c: Rewritten. * libgst/gst-parse.h: Rewritten based on Bison output. * libgst/gstpriv.h: Include gst-parse.h. * libgst/interp.c (parse_stream_with_protection): Add new parameter of _gst_parse_stream and forward it. * libgst/lex.c (parse_*): Rename to scan_*. (_gst_compile_code): Remove. (_gst_parse_stream): Add parameter to pick top production. (_gst_yylex): Remove INTERNAL_TOKEN hacks. Do not compute last_line and last_column. (print_token): Remove INTERNAL_TOKEN. * libgst/lex.h (_gst_compile_code, _gst_yydebug): Remove. (_gst_parse_stream): Adjust prototype. * libgst/lib.c (help_text, parse_args, long_options): Remove -y. (process_stdin, process_file): Adjust call to _gst_parse_stream. * libgst/prims.def: Adjust for changes to _gst_set_compilation_category and parse_stream_with_protection. Do not use _gst_compile_code, refer to _gst_current_parser->state instead and fail if methodsFor is used while not parsing. * libgst/tree.c (_gst_add_node): Support case where N1 is NULL. * libgst/tree.h (_gst_add_node): Return a tree_node. * libgst/gst-parse.y: Remove. * libgst/Makefile.am: Replace it with gst-parse.c. 2005-03-25 Paolo Bonzini * libgst/comp.c (_gst_make_attribute): Use make_constant_oop. * libgst/gst-parse.y (attribute_body): Do not include keyword. (attribute_argument): Add it here. Do not go through _gst_execute_statements for TREE_CONST_EXPRs (greatly speeds up C call-outs). 2005-03-25 Paolo Bonzini * libgst/comp.c (install_method): Evaluate pragma handlers. Make CompiledMethod read-only. (method_new): Do not make CompiledMethod read-only here. * libgst/dict.c (class_info): Include pragmaHandlers instance variable for Class. (init_class): Initialize it here. * libgst/dict.h (gst_class): Include pragmaHandlers instance variable. * libgst/sym.c (_gst_find_pragma_handler): New. * libgst/sym.h (_gst_find_pragma_handler): Declare it. 2005-03-24 Paolo Bonzini Fix bug when an ephemeron was tenured directly from eden to oldspace. * libgst/oop.c (add_to_grey_list): Remove last parameter. (add_grey_object): New function, for when the OOP parameter of add_to_grey_list was non-nil. Call scanned_fields_in from here. (_gst_copy_an_oop, tenure_one_object): Use add_grey_object. 2005-03-24 Paolo Bonzini * libgst/callin.c: Remove out-of-date comment. 2005-03-24 Paolo Bonzini * libgst/lib.c: Load Transcript.st earlier. 2005-02-02 Paolo Bonzini * libgst/alloc.c (NO_MALLOC_OVERRIDE): New define. (malloc, realloc, free, calloc): Define only if NO_MALLOC_OVERRIDE is not defined. (morecore): Do not use the system heap (sbrk) if NO_MALLOC_OVERRIDE is defined. 2004-12-20 Paolo Bonzini * libgst/sysdep.h (O_NONBLOCK): Unused, remove. 2004-11-25 Paolo Bonzini * libgst/xlat.c (gen_dirty_block): Return value is not in JIT_R0 except on x86. 2004-11-25 Paolo Bonzini * libgst/oop.c: Catch more errors out of mprotect. 2004-11-25 Paolo Bonzini * libgst/alloc.h: Use char for the type of large.data in struct heap_block. 2004-11-13 Paolo Bonzini * libgst/lib.c: Always print "file not found" error. * libgst/gstpriv.h: Use autoconf test to look for availability of __attribute__ ((visibility ("hidden"))). 2004-09-24 Paolo Bonzini * libgst/save.c: Remove code left by mistake. 2004-09-07 Paolo Bonzini * libgst/lex.c: Scan initial shebang as comment. * libgst/gst-parse.y: Parse initial shebang as comment. * libgst/lib.c: Add -f option. 2004-08-29 Paolo Bonzini * libgst/comp.h: SIZEOF_INTPTR_T => SIZEOF_OOP. * libgst/dict.inl: SIZEOF_INTPTR_T => SIZEOF_OOP. * libgst/gstpriv.h: SIZEOF_INTPTR_T => SIZEOF_OOP. * libgst/save.c: SIZEOF_INTPTR_T => SIZEOF_OOP. * libgst/xlat.c: SIZEOF_INTPTR_T => SIZEOF_OOP. 2004-08-21 Paolo Bonzini * libgst/gstpriv.h: Enforce long double alignment for obstacks. * libgst/alloc.c: Support 16k pages and long double alignment of malloc-ed blocks. * libgst/alloc.h: Likewise. 2004-03-25 Paolo Bonzini * libgst/prims.def: Fix C99-ism. * libgst/lib.c: Simplify handling of -a. 2004-01-19 Paolo Bonzini * libgst/xlat.c: Do not compile body of method if primitive cannot fail. Reserve space for emitting #valueWithReceiver:withArguments:. 2004-01-18 Paolo Bonzini * libgst/oop.c: Discard the translations of objects that #become: swaps. * libgst/opt.c: Rewritten compute_stack_positions, factor code that is common with the verifier. * libgst/xlat.c: Reset sp before translating user-defined method callers (subclasses of CompiledMethod with flags=6). Emit extras in emit_code_tree, not in gen_nothing. Add objectReg parameter to emit_basic_size_in_r0, use it to speed up #javaAsInt and #javaAsLong. 2004-01-15 Paolo Bonzini * libgst/prims.def: Set class of created CompiledMethod and CompiledBlock objects. * libgst/comp.c: Incubate attributes properly. * libgst/dict.c: Return nil if searching a pool variable in a non-Dictionary class. * libgst/xlat.c: Translate #javaAsInt and #javaAsLong. 2004-01-08 Paolo Bonzini * libgst/dict.c: Do not scavenge before the interpreter is activated. * libgst/interp.c: Check for IS_NIL (_gst_this_context_oop), not for ip != NULL, to see if a process is active. * libgst/interp-jit.inl: Refresh native IP of processes if the method they are executing is not translated anymore. * libgst/xlat.c: Fix bit-rot. Basically removed all places in which the code generators were decoding the bytecodes, and fixed some places that did not account for superoperators. 2003-12-11 Paolo Bonzini * libgst/comp.c: Add experimental code to inline #perform: and friends. * libgst/genbc-decl.y: Initialize all generated variables. * libgst/genbc-scan.l: Update for flex 2.5.31. * libgst/genpr-scan.l: Update for flex 2.5.31. * libgst/genvm-scan.l: Update for flex 2.5.31. * libgst/comp.c: Remove _colon_ from variable names where not ambiguous. * libgst/interp.c: Likewise. * libgst/lex.c: Likewise. * libgst/security.c: Likewise. * libgst/sym.c: Likewise. * libgst/sym.h: Likewise. * libgst/vm.def: Likewise. * libgst/xlat.c: Likewise. 2003-12-10 Paolo Bonzini * libgst/comp.c: Check _gst_verbosity * libgst/dict.c: Publish _gst_verbosity as OutputVerbosity * libgst/lib.c: Replace no_errors with _gst_verbosity == 0, _gst_quiet_execution with _gst_verbosity == 1, _gst_verbose with _gst_verbosity == 3, don't set _gst_gc_message on -Q. * libgst/oop.c: Don't print gc messages if _gst_quiet_execution == 0. 2003-11-27 Paolo Bonzini * libgst/byte.def: New bytecodes 25 and 26 (#javaAsInt, #javaAsLong). * libgst/byte.h: New bytecodes 25 and 26 * libgst/vm.def: Likewise * libgst/builtins.gperf: Likewise * libgst/sym.c: Declare _gst_java_as_int_symbol and _gst_java_as_long_symbol. * libgst/sym.h: Declare _gst_java_as_int_symbol and _gst_java_as_long_symbol. 2003-11-25 Paolo Bonzini * libgst/input.c: New function poll_and_read. 2003-11-21 Paolo Bonzini * libgst/byte.def: Suppress uninitialized variable warning on arg_lsb. * libgst/dict.c: Support multiple class shapes * libgst/dict.inl: Likewise * libgst/gstpriv.h: Likewise * libgst/prims.def: Likewise * libgst/xlat.c: Put an abort on blatantly broken code. 2003-11-20 Paolo Bonzini * libgst/opt.c: Be more precise in detecting jumps over a push that land on a pop. 2003-11-18 Paolo Bonzini * libgst/dict.c: Add break statements to _gst_set_file_stream_file (ouch!). * libgst/prims.def: Allow ByteArrays in get/put primitives, and integers as opening modes. 2003-11-13 Paolo Bonzini * libgst/comp.c: Raise errors on duplicate arguments or temporaries. * libgst/sym.c: Add third parameter to _gst_declare_name, use it in _gst_declare_arguments or _gst_declare_temporaries * libgst/sym.h: Adjust declaration of _gst_declare_name. 2003-11-12 Paolo Bonzini * libgst/alloc.h: Hide all internal symbols. * libgst/byte.h: Hide all internal symbols. * libgst/callin.h: Hide all internal symbols. * libgst/cint.h: Hide all internal symbols. * libgst/comp.h: Hide all internal symbols. * libgst/dict.h: Hide all internal symbols. * libgst/events.h: Hide all internal symbols. * libgst/gstpriv.h: Hide all internal symbols. * libgst/heap.h: Hide all internal symbols. * libgst/input.h: Hide all internal symbols. * libgst/interp.h: Hide all internal symbols. * libgst/jitpriv.h: Hide all internal symbols. * libgst/lex.h: Hide all internal symbols. * libgst/lib.h: Hide all internal symbols. * libgst/match.h: Hide all internal symbols. * libgst/md-config.h: Hide all internal symbols. * libgst/memzero.h: Hide all internal symbols. * libgst/mpz.h: Hide all internal symbols. * libgst/oop.h: Hide all internal symbols. * libgst/opt.h: Hide all internal symbols. * libgst/print.h: Hide all internal symbols. * libgst/save.h: Hide all internal symbols. * libgst/security.h: Hide all internal symbols. * libgst/str.h: Hide all internal symbols. * libgst/sym.h: Hide all internal symbols. * libgst/sysdep.h: Hide all internal symbols. * libgst/tree.h: Hide all internal symbols. * libgst/xlat.h: Hide all internal symbols. * libgst/interp.h: Declare _gst_abort_execution here. * libgst/xlat.c: Don't declare it as extern here. * libgst/oop.c: Make grow_memory_no_capact and oop_heap static. * libgst/sym.c: Make check_symbol_chain static. * libgst/sym.c: Initialize global variables so as to make them uncommon. * libgst/comp.c: Likewise. * libgst/lib.c: Likewise. * libgst/save.c: Likewise. * libgst/oop.c: Likewise. * libgst/dict.c: Likewise. * libgst/interp.c: Likewise. * libgst/cint.c: Likewise. * libgst/lex.c: Likewise. 2003-11-11 Paolo Bonzini * libgst/input.c: Avoid SIGSEGV if character in range 128..255 is pushed back by the lexer. * libgst/lex.c: Tweak output of invalid characters. * libgst/alloc.c: Tweak pool sizes to obtain cacheline alignment. * libgst/lib.c: Tweak for more shared library friendliness. * libgst/tree.c: Tweak for more shared library friendliness. * libgst/builtins.inl: Rebuild for shared library friendliness. * libgst/sym.c: Adapt. 2003-11-07 Paolo Bonzini * libgst/lex.c: Allow dollars (!) in the middle of identifiers. * libgst/dict.inl: Require that the second argument of is_a_kind_of is not nil, avoid a test if we are testing for the exact class. * libgst/prims.def: Allow #perform: of a subclass of CompiledMethod. 2003-11-04 Paolo Bonzini * libgst/gstpriv.h: Define prefetching macros. * libgst/oop.c: Use prefetches. * libgst/oop.inl: Use prefetches. * libgst/prims.def: Use nanosleep instead of usleep. Use prefetches. * libgst/save.c: Use prefetches. 2003-11-03 Paolo Bonzini * libgst/lex.c: Handle 1+-2 as "1 + -2" rather than as "1 +- 2". 2003-10-24 Paolo Bonzini * libgst/dict.c: Publish HOST_SYSTEM into CSymbols.hostSystem. 2003-10-17 Paolo Bonzini * libgst/lex.c: New function parse_sharp; extract SYMBOL_KEYWORDs (now called SYMBOL_LITERAL) into it instead of lexing them in parse_ident. Simplify parse_ident. * libgst/gst-parse.y: Use new lexer symbol SYMBOL_LITERAL which sums up every symbol constant. 2003-10-07 Paolo Bonzini * libgst/comp.c: Rename untrusted_methods to _gst_untrusted_methods, don't declare it here... * libgst/comp.h: ...and do it here instead * libgst/sym.c: Use it. * libgst/dict.c: Define _gst_identity_dictionary_at * libgst/dict.h: Declare it * libgst/comp.c: Don't accept to override an trusted method with an untrusted one. 2003-09-29 Paolo Bonzini * libgst/interp.c: New function find_method. Use it within check_send_correctness. When #perform: is used with an absent method, send #doesNotUnderstand: even if the number of arguments is wrong -- this is needed so that non-standard selector names can be used. 2003-09-24 Paolo Bonzini * libgst/comp.c: Define _gst_process_attributes_array, split process_attribute out of process_attributes, rename this one to process_attributes_tree. * libgst/comp.h: Declare process_attributes * libgst/prims.def: Use _gst_process_attributes_array, accepting an array of Messages instead of a primitive number in VMpr_CompiledMethod_create. 2003-09-20 Paolo Bonzini * libgst/lib.c: Exit with status 1 if a wrong option is specified. 2003-09-18 Paolo Bonzini * libgst/interp-bc.inl: Only set last_primitive for succeeded primitives. 2003-09-15 Paolo Bonzini * libgst/interp-bc.inl: Search #doesNotUnderstand: in superclass if searching for a message fails during a send to super. * libgst/comp.c: Sending to super from a root class is now an error. * libgst/byte.h: Retouch the encoding of PUSH_SPECIAL in order to simplify the implementation * libgst/vm.def: Fix it * libgst/byte.c: Fix the MATCH_BYTECODES occurrences * libgst/opt.c: Fix the MATCH_BYTECODES occurrences * libgst/xlat.c: Fix the MATCH_BYTECODES occurrences * libgst/interp-bc.inl: Simplify most of the macro cruft. * libgst/vm.def: Move the rest here. 2003-09-14 Paolo Bonzini * libgst/vm.def: Reimplement jump lookahead * libgst/interp-bc.inl: With some code here too. 2003-09-12 Paolo Bonzini * libgst/byte.def: Add superoperators * libgst/vm.def: Add superoperators * libgst/opt.c: Fix latent bugs exposed by superoperators * libgst/interp.c: Get rid of the useless third parameter to SEND_MESSAGE * libgst/interp-bc.inl: Likewise * libgst/interp-jit.inl: Likewise * libgst/prims.def: Likewise * libgst/vm.def: Likewise 2003-09-11 Paolo Bonzini * libgst/comp.c: Compile #and:/#or: to a shorter sequence * libgst/genvm-parse.y: One more little language, ... * libgst/genvm-scan.l: ... with its scanner, ... * libgst/genvm.h: ... its header file, ... * libgst/vm.def: ... its source code, ... * libgst/vm.inl: ... and its output, ... * libgst/interp-bc.inl: ... which is included here. 2003-09-09 Paolo Bonzini * libgst/opt.c: Support superoperator synthesis. * libgst/superop1.inl: New automatically generated file. * libgst/superop2.inl: New automatically generated file. 2003-09-08 Paolo Bonzini * libgst/genbc-decl.y: Support multiple dispatch statements. 2003-09-07 Paolo Bonzini * libgst/dict.c: Create CSymbols as an instance of Namespace. 2003-09-05 Paolo Bonzini * libgst/opt.c: Fix peephole optimizer's jump fixup pass for new bytecode set. Verify jumping in range and jumping past an extension bytecode. 2003-09-04 Paolo Bonzini * libgst/byte.def: Modify for new syntax and bytecode set * libgst/genbc-scan.l: Modify for new syntax * libgst/genbc-decl.y: Modify for new syntax * libgst/byte.c: Accept two parameters in _gst_compile_byte * libgst/byte.h: Modify for new bytecode set * libgst/comp.c: Modify for new bytecode set, death to many functions * libgst/interp-bc.inl: Modify for new bytecode set * libgst/opt.c: Modify for new bytecode set, momentary death to peephole optimizer (will come back new and improved...) * libgst/builtins.gperf: New file. * libgst/builtins.inl: New automatically generated file. * libgst/sym.c: Include builtins.gperf's hash function * libgst/sym.h: Declare it 2003-09-02 Paolo Bonzini * libgst/comp.c: Don't rely on _gst_is_kernel_file * libgst/input.c: Death to _gst_store_no_source and _gst_is_kernel_file * libgst/input.h: Death to _gst_store_no_source and _gst_is_kernel_file * libgst/lib.c: Death to _gst_store_no_source and -s. * libgst/interp.c: Don't let the current process die on image reload. 2003-08-25 Paolo Bonzini * libgst/cint.c: Fix variadic functions. * libgst/opt.c: Fix verification of nested array constructors. 2003-08-09 Paolo Bonzini * libgst/security.c: New file * libgst/security.h: New file * libgst/lib.c: Load Security.st * libgst/dict.inl: Provide OrderedCollection accessors 2003-07-21 Paolo Bonzini * libgst/cint.c: Allow to pass integers as float or doubles (but not vice versa). 2003-07-13 Paolo Bonzini * libgst/dict.c: Make Character not indexed. * libgst/oop.c: Make Character's asciiValue an OOP. * libgst/oop.h: Make Character's asciiValue an OOP. * libgst/prims.def: Remove Character>>#asciiValue primitive. 2003-07-10 Paolo Bonzini * libgst/comp.c: Recalculate number of temporaries used by a block after it is compiled. 2003-07-09 Paolo Bonzini * libgst/oop.c: Don't scavenge before allocating big objects. * libgst/prims.def: Use _gst_init_mem to set GC parameters. 2003-07-08 Paolo Bonzini * libgst/interp.c: Initialize Processor's gcSemaphore * libgst/interp.h: Define gcSemaphore and gcArray * libgst/dict.c: Likewise * libgst/oop.c: Use it to mourn objects * libgst/sym.h: No mourn symbol anymore * libgst/sym.c: No mourn symbol anymore * libgst/dict.c: Use IS_OOP_VALID_GC during image load * libgst/oop.c: Use IS_OOP_VALID_GC during the GC * libgst/oop.inl: Complicate validity test to take into account incremental GC-ing of old objects. * libgst/save.c: Use IS_OOP_VALID_GC since we finish the incremental GC before saving. 2003-07-07 Paolo Bonzini * libgst/mpz.c: *_si routines accept a signed integer, not an unsigned. * libgst/xlat.c: Inline the class primitive, don't inline #class * libgst/interp-bc.inl: Don't inline #class but cache it. * libgst/interp.c: Cache primitives for #class. 2003-07-04 Paolo Bonzini * libgst/genbc-impl.y: Output a small comment with the file and line where each MATCH_BYTECODES block was defined. * libgst/xlat.c: Use genbc here too... -500 lines, gotta like this :-) 2003-07-03 Paolo Bonzini * libgst/comp.h: Define MTH_USER_DEFINED * libgst/comp.inl: Define GET_METHOD_NUM_ARGS * libgst/interp-bc.inl: Support user-defined methods * libgst/opt.c: Fix fall-out in the JIT from the introduction of genbc, support subclasses of CompiledMethod * libgst/str.c: Fix fall-out from the size_t-ification of max_buf_len * libgst/sym.c: Define a new symbol for #valueWithReceiver:withArguments: * libgst/sym.h: Likewise * libgst/xlat.c: Fix fall-out in the JIT from the new meaning of bytecode 200, and support user-defined methods 2003-06-27 Paolo Bonzini * libgst/opt.c: Verify sends to super 2003-06-25 Paolo Bonzini * libgst/dict.c: Remove values instance variable, store key/value pairs in adjacent slots. * libgst/dict.h: Ditto * libgst/dict.inl: Ditto * libgst/opt.c: Check for Array bounds in verifier * libgst/lib.c: Initialize compiler after interpreter * libgst/comp.c: Store attributes in MethodInfo objects * libgst/comp.h: Add attributes field to gst_method_info * libgst/dict.c: Make MethodInfo indexable 2003-06-23 Paolo Bonzini * libgst/comp.c: Death to _gst_get_method_descriptor and _gst_set_method_descriptor. * libgst/alloc.h: Remove last occurrences of the register keyword * libgst/byte.h: Remove last occurrences of the register keyword * libgst/oop.h: Remove last occurrences of the register keyword * libgst/comp.c: Apply untrusted attribute to CompiledMethods and CompiledBlocks as well. * libgst/opt.c: Check untrusted attribute for CompiledMethods. * libgst/prims.def: New primitive VMpr_CompiledCode_verificationResult 2003-06-22 Paolo Bonzini * libgst/comp.c: Constify _gst_display_compilation_trace and _gst_invoke_hook * libgst/comp.h: Constify _gst_display_compilation_trace and _gst_invoke_hook * libgst/dict.c: Constify class_definition and several functions * libgst/interp.h: Constify prim_table_entry * libgst/interp.c: Constify stop_executing * libgst/lib.c: Constify several variables * libgst/lib.h: Constify several variables * libgst/gst-parse.y: Constify several variables * libgst/sym.c: Constify several variables and functions * libgst/sym.h: Constify several variables and functions * libgst/tree.c: Constify several variables and functions * libgst/tree.h: Constify several variables and functions * libgst/sysdep.c: Use #elif * libgst/sym.c: Trusted instance variables of an untrusted class are read-only. Same goes for class variables. The instance variables array is scanned backwards (faster and more correct). 2003-06-20 Paolo Bonzini * libgst/opt.c: Death to stack_balance_table and jump_offsets 2003-06-19 Paolo Bonzini * libgst/genbc-decl.y, libgst/genbc-impl.y, libgst/genbc-scan.l libgst/genbc.c, libgst/genbc.h, libgst/byte.def: new files * libgst/byte.c: Use genbc's facilities * libgst/opt.c: Use genbc's facilities * libgst/gstpriv.h: Include match.h 2003-06-17 Paolo Bonzini * libgst/comp.inl: Define NUM_METHOD_LITERALS * libgst/gstpriv.h: Define F_VERIFIED and IS_OOP_VERIFIED * libgst/interp-bc.inl: Invoke bytecode verifier * libgst/xlat.c: Ditto * libgst/opt.c: Include bytecode verifier. Set stack balance for return opcodes to -1. Be less forgiving in _gst_compute_stack_position (abort instead of giving errors) since the bytecode verifier should have tested the assertions. 2003-06-15 Paolo Bonzini * libgst/xlat.c: New function _gst_reset_inline_caches; prefix _gst_ to global functions * libgst/xlat.h: Ditto * libgst/interp.c: Invoke _gst_reset_inline_caches * libgst/comp.c: Callers adjusted. * libgst/oop.c: Callers adjusted. * libgst/oop.inl: Callers adjusted. * libgst/prims.def: Callers adjusted. 2003-06-11 Paolo Bonzini * libgst/gstpriv.h: Check for SmallIntegers in read-only accessors. * libgst/prims.def: Use the above to simplify some checks. * libgst/interp.c: Implement trustedness of contexts. * libgst/prims.def: Implement trustedness primitives. * libgst/gstpriv.h: Implement trustedness accessors. * libgst/comp.c: Don't allow primitives in untrusted classes. 2003-06-10 Paolo Bonzini * libgst/dict.c: Allow creating multiple subclasses of nil at bootstrap. Store bits of the instance specification directly in the class_definition structures. * libgst/oop.c: Death to _gst_fixup_metaclass_objects. * libgst/oop.h: Ditto. 2003-06-09 Paolo Bonzini * libgst/interp-bc.inl: REGISTER with structs is not good. * libgst/interp-jit.inl: REGISTER with structs is not good. * libgst/xlat.c: Now that thisContext is no more, represent storing into thisContext as TREE_STORE | TREE_POP_INTO_ARRAY, not TREE_SEND | TREE_POP_INTO_ARRAY. 2003-06-08 Paolo Bonzini * libgst/comp.c: Push thisContext as "ContextPart thisContext" * libgst/byte.h: Death to the push thisContext bytecode * libgst/interp-bc.inl: Ditto * libgst/opt.c: Ditto * libgst/xlat.c: Ditto * libgst/byte.h: BLOCK_COPY_SPECIAL --> MAKE_DIRTY_BLOCK * libgst/comp.c: Adjust. Don't push nil or thisContext before making a dirty block. Don't treat #blockCopy: as a special selector. * libgst/opt.c: Blocks accessing thisContext are dirty * libgst/interp.c: New function _gst_make_dirty_block. * libgst/interp.h: Declare it * libgst/interp-bc.inl: Call it from bytecode 200 * libgst/xlat.c: Don't treat bytecode 200 as a special send, but as an all-of-its-own operation, call this function from the code generated in gen_dirty_block. * libgst/prims.def: Remove VMpr_CompiledBlock_blockCopy * libgst/jitpriv.h: Remove it from the internal functions * libgst/interp-jit.inl: Ditto * libgst/sym.c: Remove _gst_block_copy_symbol * libgst/sym.h: Ditto 2003-06-05 Paolo Bonzini * libgst/comp.c: For non-clean blocks, store CompiledBlocks directly in the method. * libgst/prims.def: Implement #blockCopy: for CompiledBlocks. * libgst/interp-bc.inl: Open code #blockCopy: for CompiledBlocks. * libgst/xlat.c: Inline #blockCopy: for CompiledBlocks. * libgst/oop.c: Check for out of range _gst_mem.scan.queue_at while scanning, not in QUEUE_NEXT. * libgst/comp.h: Define constants for the possible value of CompiledMethod flags. * libgst/comp.c: Use them * libgst/opt.c: Use them * libgst/interp-bc.inl: Ditto * libgst/xlat.c: Ditto; rewrite the handling of shortcut CompiledMethods to use a switch statement. 2003-06-04 Paolo Bonzini * libgst/comp.c: Flag duplicate primitives or bad primitive numbers as errors. * libgst/genpr-parse.y: Start primitive numbers from 1. 2003-05-30 Paolo Bonzini * libgst/lib.c: Remove logging mechanism * libgst/input.c: Ditto * libgst/input.h: Ditto 2003-05-30 Paolo Bonzini Replace primitives with generic attributes. * libgst/comp.c: Walk through the attribute list in compile_method. Added _gst_make_attribute. Return NULL from _gst_execute_statements if there was a compilation error. Define the termination method before #methodsFor:. * libgst/comp.h: Declare this function * libgst/tree.c: Added _gst_make_attribute_list, and pretty printing of attributes * libgst/tree.h: Declare this function * libgst/dict.c: Moved _gst_resolve_primitive_name to inside prepare_primitive_numbers_map. Added VMPrimitives as a pool dictionary of Object, so make it a Dictionary and initialize it in init_smalltalk_dictionary. * libgst/dict.h: Removed _gst_resolve_primitive_name * libgst/gst-parse.y: Modified the grammar. Adjust for the change to _gst_execute_statements, above. * libgst/lex.c: Removed PRIMITIVE_START, added '<' and '>' as separate tokens. * libgst/sym.c: Added _gst_primitive_symbol and its initializer * libgst/sym.h: Added _gst_primitive_symbol 2003-05-27 Paolo Bonzini * libgst/prims.def: Add VMpr_Object_allOwners * libgst/dict.inl: Implement is_owner * libgst/dict.c: Terminate CallinProcesses when resuming from a snapshot. * libgst/interp.c: Made terminate_process extern, renamed to _gst_terminate_process. 2003-05-16 Paolo Bonzini * libgst/prims.def: Add more C->String primitives * libgst/cint.c: Support long doubles and #cObjectPtr. * libgst/sym.h: Add _gst_long_double_symbol * libgst/sym.c: Add _gst_long_double_symbol * libgst/prims.def: Add long double access * libgst/callin.c: Add long double accessors * libgst/callin.h: Add long double accessors * libgst/gstpriv.h: Add long double accessors 2003-05-14 Paolo Bonzini * libgst/cint.c: Switch to libffi. General reorganization. * libgst/cint.h: Remove _gst_lookup_function. * libgst/interp.c: Fix some printf formats * libgst/print.c: Fix some printf formats 2003-05-12 Paolo Bonzini * libgst/comp.c: Remove _gst_compiled_method_at and _gst_compiled_method_at_put (unused). * libgst/comp.h: Ditto. * libgst/dict.inl: Merge find_key and dictionary_association_at. 2003-05-10 Paolo Bonzini * libgst all files: Use intptr_t, size_t, ptrdiff_t, time_t, int32_t, uint32_t more widely * libgst/gstpriv.h: Include stdintx.h 2003-05-09 Paolo Bonzini *** Version 2.1.2 released. * libgst/alloc.c: Rationalize inclusions * libgst/byte.c: Rationalize inclusions * libgst/callin.c: Rationalize inclusions * libgst/cint.c: Rationalize inclusions * libgst/comp.c: Rationalize inclusions * libgst/dict.c: Rationalize inclusions * libgst/dict.inl: Rationalize inclusions * libgst/events.c: Rationalize inclusions * libgst/gstpriv.h: Add more inclusions * libgst/heap.c: Rationalize inclusions * libgst/input.c: Rationalize inclusions * libgst/interp-bc.inl: Rationalize inclusions * libgst/interp.c: Rationalize inclusions * libgst/interp.inl: Rationalize inclusions * libgst/lex.c: Rationalize inclusions * libgst/lib.c: Rationalize inclusions * libgst/mpz.c: Rationalize inclusions * libgst/oop.c: Rationalize inclusions * libgst/opt.c: Rationalize inclusions * libgst/print.c: Rationalize inclusions * libgst/save.c: Rationalize inclusions * libgst/str.c: Rationalize inclusions * libgst/sym.c: Rationalize inclusions * libgst/sysdep.c: Rationalize inclusions * libgst/tree.c: Rationalize inclusions * libgst/xlat.c: Rationalize inclusions * libgst/comp.h: Rationalize inclusions * libgst/opt.h: Rationalize inclusions * libgst/interp.h: Rationalize inclusions 2003-05-06 Paolo Bonzini * libgst/interp.c: Define PROTECT_CURRENT_PROCESS_WITH and PROTECT_FROM_INTERRUPT_WITH. Use them in parse_stream_with_protection * libgst/prims.def: Use them. * libgst/cint.h: Declare _gst_errno and _gst_set_errno * libgst/cint.c: Saved_errno -> _gst_errno, implement _gst_set_errno * libgst/prims.def: The VMpr_ObjectMemory_snapshot primitive can fail; use _gst_set_errno * libgst/save.c: Invoke hook after opening the file. 2003-04-28 Paolo Bonzini * libgst/input.c: Don't advance the pointer in a STREAM_STRING after EOF; don't unread an EOF as _gst_next_char will return an EOF again. * libgst/lex.c: Change the lexing functions to accept an int so that EOF and 255 are not confused. 2003-04-27 Paolo Bonzini * libgst/sysdep.c: Return ENOMEM properly under Win32. Separate detection of availability of a particular technique and reservation of memory. find_heap_base renamed to anon_mmap_check. 2003-04-17 Paolo Bonzini *** Version 2.1.1 (stable) released. * libgst/sysdep.c: Allow MAP_NORESERVE even if MAP_ANON is not available. Encapsulate opening /dev/zero into a macro which is used the same way when MAP_ANON is used and when it is not. 2003-04-16 Paolo Bonzini * libgst/genpr-parse.y: Add ATTRIBUTE_UNUSED attributes to the primitives' arguments. * libgst/input.c: Use newer function rl_completion_matches instead of completion_matches. * libgst/alloc.c: Fix for Cygwin, always #undef small * libgst/sysdep.c: Fix for Cygwin, include process.h and don't do setsid if HAVE_SPAWNL * libgst/lib.c: Don't load .stinit in regression testing mode, disable regression testing mode when loading .stpre. 2003-04-12 Paolo Bonzini *** Version 2.1 (stable) released. 2003-04-09 Paolo Bonzini * libgst/interp-bc.inl: EndExecution must FLUSH, not END (this broke the IA64). 2003-04-08 Paolo Bonzini * libgst/interp.inl: Add definitions to support broken inttypes.h like FreeBSD's. * libgst/sysdep.c: Move the declaration of the FD static variable before _gst_osmem_alloc. 2003-04-07 Paolo Bonzini * libgst/dict.c: Fix mismatch between sizeof argument and actual type. 2003-03-30 Paolo Bonzini * libgst/lex.c: Strdup -> xstrdup * libgst/alloc.c: Define xstrdup * libgst/alloc.h: Define xstrdup * libgst/input.c: Strdup -> xstrdup * libgst/lex.c: Strdup -> xstrdup * libgst/lib.c: Strdup -> xstrdup * libgst/sysdep.c: Strdup -> xstrdup 2003-03-26 Paolo Bonzini * libgst/byte.c: Remove checks on availability of bytecode array. Make explicit calls to allocate bytecode array. * libgst/comp.c: Make explicit calls to allocate bytecode array. * libgst/opt.c: Likewise. * libgst/comp.c: Associate stack depth to each bytecode array. Fix bugs along the way. * libgst/byte.c: Add support for saving and restoring stack depth. * libgst/byte.h: Fix declarations. Move stack depth modification macros here from comp.c. * libgst/comp.c: Count depth from 0, not from argCount+tempCount, and sum the number of arguments only at the end (because the tempCount might change if there are #to:do: loops!) * libgst/save.c: Check for file version <= VERSION_REQUIRED, not ==. 2003-03-23 Paolo Bonzini * libgst/prims.def: Extract a loop invariant from VMpr_Behavior_someInstance 2003-03-21 Paolo Bonzini * libgst/sysdep.c: Added _gst_full_write * libgst/input.c: Use it instead of _gst_write * libgst/save.c: Use it instead of _gst_write 2003-03-19 Paolo Bonzini * libgst/sysdep.c: Always provide _gst_recv & _gst_send * libgst/sysdep.h: Always declare them * libgst/save.c: Include socketx.h 2003-03-15 Paolo Bonzini * libgst/dict.inl: Fix initialization of word subclasses. 2003-03-14 Paolo Bonzini * libgst/sysdep.c: Make _gst_read and _gst_write abort on EFAULT * libgst/prims.def: Use them * libgst/input.c: Use them 2003-03-04 Paolo Bonzini * libgst/lib.c: Load exception handling before VFS. * libgst/sysdep.c: Redisorganize _gst_open_pipe into separate functions. Use spawnl and Win32 pipes if available. 2003-03-02 Paolo Bonzini * libgst/oop.c: Don't reset the heap_limit if the heap was grown. 2003-03-01 Paolo Bonzini * libgst/heap.c: Move system dependent stuff... * libgst/sysdep.c: ...here * libgst/sysdep.h: Make it public. * libgst/prims.def: Move enum with file operations... * libgst/interp.h: ...here. * libgst/prims.def: Define primitive for sockets. * libgst/sysdep.c: Define _gst_full_send. * libgst/sysdep.h: Declare _gst_full_send. * libgst/heap.c: Define routines for mmap/munmap. * libgst/heap.h: Declare them. * libgst/alloc.c: Use them. 2003-02-28 Paolo Bonzini * libgst/events.c: Include signalx.h. * libgst/heap.c: Include signalx.h. * libgst/interp.c: Include signalx.h. * libgst/sysdep.c: Include signalx.h. 2003-02-28 Paolo Bonzini * libgst/sysdep.c: Cook up a simple mechanism to disable and enable signals where the OS does not provide that (again, MinGW32). Fix semicolons in DISABLE and ENABLE. Don't block fatal errors. 2003-02-27 Paolo Bonzini * libgst/cint.c: Turn malloc to xmalloc * libgst/save.c: Turn malloc to xmalloc * libgst/sym.c: Turn free to xfree * libgst/alloc.c: Disable usage as system malloc under MinGW32. * libgst/sysdep.c: Include process.h if we have it (MinGW32) * libgst/events.c: Likewise * libgst/sysdep.c: Implement _gst_mem_protect * libgst/sysdep.h: Declare it and PROT_* * libgst/oop.c: Use it 2003-02-25 Paolo Bonzini * libgst/oop.c: Avoid out-of-memory while compacting * libgst/print.c: Tweak the precision for FloatE's, FloatD's and FloatQ's depending on float.h, except in regression testing mode. 2003-02-15 Paolo Bonzini * libgst/heap.c: Support !HAVE_SBRK * libgst/prims.def: Support !HAVE_USLEEP * libgst/sysdep.c: Use _beginthread under MinGW32 instead of CreateThread * libgst/interp.c: Use raise instead of kill * libgst/sysdep.c: Ditto * libgst/events.c: Ditto 2003-02-13 Paolo Bonzini * libgst/gst.h: Tweak a little the definition of alloca * libgst/heap.c: Fix typos, add WIN32_LEAN_AND_MEAN * libgst/oop.c: Add cast to fix gcc 2.95 warning * libgst/prims.def: Use POP_N_OOPS to fix gcc 2.95 warning * libgst/save.c: Disable mmap-ing under WIN32 * libgst/sysdep.c: Add WIN32_LEAN_AND_MEAN 2003-03-09 Paolo Bonzini * libgst/interp.c: Don't print C backtrace during compilation if SIGINT is received. 2003-02-07 Paolo Bonzini * libgst/heap.c: Fix brokenness of Win32 implementation. * libgst/alloc.c: Add a very basic logging mechanism. * libgst/interp.c: Add a very basic backtracing mechanism to the signal handlers. Trap SIGILL when JIT-compiling. Fix mismatch between process operation of JIT compiler and bytecode interpreter. * libgst/print.c: Print FloatD and FloatQ objects with the correct letter for the exponent 2003-02-06 Paolo Bonzini * libgst/alloc.c: Abort on an evident double free (two frees of the same object without any free on the same page in the middle). * libgst/oop.c: Add notice about bad interaction between SIGSEGV trapping and valgrind. * libgst/events.c: Use pointer to tail's next pointer instead of pointer to tail. Suggested by Carlos Moran. 2003-02-03 Paolo Bonzini * libgst/alloc.c: Allow one to free the NULL pointer liberally. * libgst/opt.c: Drop broken code. * libgst/opt.h: Adjust prototypes * libgst/xlat.c: Adjust users 2003-01-20 Paolo Bonzini * libgst/comp.c: Keep the returned value of a doit in the incubator until after the #afterEvaluation hook is completed. 2003-01-17 Paolo Bonzini * libgst/interp-jit.inl: Check for code not having been compiled yet moved before check for native_ip == 0 2003-01-16 Paolo Bonzini * libgst/lib.c: While loading standard files disable _gst_regression_testing. * libgst/input.c: Define _gst_warningf and _gst_warningf_at * libgst/input.h: Declare them * libgst/gst-parse.y: Use them; don't trigger a warning when *defining* a method named #true, #false and the like * libgst/save.c: Never read past the end of the file 2003-01-12 Paolo Bonzini * libgst/sysdep.c: Make child process a session group leader 2003-01-09 Paolo Bonzini * libgst/comp.c: Fix bug in _gst_execute_statements * libgst/sym.c: Define _gst_pop_all_scopes * libgst/sym.h: Declare it * libgst/comp.c: Use it 2003-01-02 Paolo Bonzini * libgst/gst-parse.y: Get rid of right recursion and shift/reduce conflicts. * libgst/tree.c: TREE_STATEMENT_LIST now a list node * libgst/tree.h: Adjust documentation * libgst/comp.c: Adjust functions that compile statement lists. * libgst/lib.c: Bump copyright year * libgst/interp-jit.inl: Cleanup #if 0 sections * libgst/prims.def: ValueAndResumeOnUnwind loses the cache_new_ip attribute. 2002-12-31 Paolo Bonzini * libgst/prims.def: Always use PUSH_OOP to push the result in VMpr_CObject_at. Thanks to David Forster. 2002-12-29 Paolo Bonzini * libgst/cint.c: Strdup the name of the function in _gst_define_cunc (it is freed when the call happens from Smalltalk). Thanks to David Forster. 2002-12-27 Paolo Bonzini *** Version 2.0g released * libgst/prims.def: Fix ISO C99-ism * libgst/input.c: Fix compilation error when readline is not there 2002-12-19 Paolo Bonzini * libgst/oop.c: Don't print negative percentages * libgst/prims.def: Add ObjectMemory>>#abort primitive * libgst/interp-bc.inl: Fix single step mode * libgst/interp-jit.inl: Fix single step mode 2002-12-15 Paolo Bonzini * libgst/callin.c: Incubate everything sent through _gst_msg_sendf. 2002-12-12 Paolo Bonzini *** Version 2.0.10 released * libgst/input.c: Register the file name object in _gst_get_cur_file_name, unregister it in my_close * libgst/oop.c: Add more assertions * libgst/save.c: Add more assertions 2002-12-11 Paolo Bonzini * libgst/gst-parse.y: New name of gst.y * libgst/tree.h: Adjust * libgst/genpr-scan.l: New file * libgst/genpr-parse.y: New file * libgst/genprims.h: New file * libgst/prims.def: Merge with prims.inl again, but with genprims' syntax * libgst/interp.c: Remove cruft for multiple inclusions of prims.def, we only include the generated prims.inl 2002-12-05 Paolo Bonzini *** Version 2.0.9 (stable) and 2.0f (development) released * libgst/interp.c: Add _gst_check_process_state * libgst/interp.h: Add _gst_check_process_state * libgst/interp.c: Do suspend_process correctly when the process is in the middle of the process list. 2002-12-04 Paolo Bonzini * libgst/alloc.c: Abort instead of asserting * libgst/save.c: Likewise * libgst/dict.c: Abort instead of calling _gst_debug * libgst/dict.inl: Likewise * libgst/gstpriv.h: Likewise * libgst/oop.c: Likewise * libgst/sym.c: Likewise * libgst/interp.c: Likewise * libgst/xlat.c: Likewise * libgst/prims.inl: Abort on a bootstrapping error * libgst/interp.c: Catch SIGABRT instead of SIGSEGV 2002-12-01 Paolo Bonzini * libgst/heap.c: Provide a fallback whenever MAP_NORESERVE is used. 2002-11-29 Paolo Bonzini * libgst/gst.y: Fix a couple of shift/reduce conflicts * libgst/gstpriv.h: Min->MIN, max->MAX, abs->ABS * libgst/mpz.c: Adjusted * libgst/opt.c: Adjusted * libgst/oop.c: Adjusted * libgst/save.c: Adjusted * libgst/oop.c: Remove warning * libgst/prims.inl: Implement asynchronous call-out. * libgst/prims.def: Implement asynchronous call-out. 2002-11-19 Paolo Bonzini *** Version 2.0e released * libgst/oop.c: Add _gst_grey_oop_range * libgst/oop.h: Declare it * libgst/prims.inl: Check for EFAULT and abort if so. 2002-11-16 Paolo Bonzini * libgst/sysdep.c: Always do the F_SETOWN fcntl after F_SETFL for the benefit of FreeBSD (thanks to Danilo Fiorenzano). And always do the F_SETFL fcntl before FIOASYNC for the benefit of Cygwin. 2002-11-15 Paolo Bonzini *** Version 2.0.8 (stable) released * libgst/comp.c: Optionally make the method return the last value in _gst_compile_method, use that in _gst_execute_statements, don't free the trees in _gst_compile_method * libgst/gst.y: Adjust callers of _gst_compile_method and _gst_execute_statements, support ##(...) for compile-time-constants, free the trees here * libgst/tree.c: Remove parameter from _gst_free_tree * libgst/tree.h: Adjust _gst_free_tree * libgst/dict.c: Get rid of CFunctionDescs 2002-11-14 Paolo Bonzini * libgst/prims.inl: New C callout primitive, removed methodOOP parameter from primitives * libgst/interp.c: Adjusted * libgst/interp.h: Adjusted * libgst/interp-bc.inl: Adjusted * libgst/interp-jit.inl: Adjusted * libgst/cint.c: Adjusted * libgst/cint.h: Adjusted * libgst/lib.c: Load additional core classes *before* the C interface since it now uses ValueHolder. 2002-11-13 Paolo Bonzini * libgst/dict.inl: Define identity_dictionary_find_key * libgst/dict.c: Use it * libgst/prims.inl: Moved parts to interp.c and prims.def * libgst/prims.def: Created from prims.inl * libgst/interp.c: Added parts of prims.inl 2002-11-12 Paolo Bonzini * libgst/prims.inl: Add VMpr_Semaphore_lock 2002-11-09 Paolo Bonzini * libgst/interp.c: Start a new process in _gst_prepare_execution_environment, implement _gst_nvmsg_send here, added suspend_process and terminate_process, refine detection of "No runnable process" condition * libgst/prims.inl: Handle the call-in chain * libgst/interp-bc.inl: New argument and return value for _gst_interpret * libgst/interp-jit.inl: New argument and return value for _gst_interpret * libgst/interp.h: Added _gst_nvmsg_send * libgst/comp.c: Use _gst_nvmsg_send to call #executeStatements * libgst/callin.c: Base everything on _gst_nvmsg_send * libgst/dict.c: Add DirectedMessage-related stuff and _gst_callin_process_class * libgst/dict.h: Likewise * libgst/lib.c: Load DirMessage.st early, and CallinProcess.st * libgst/alloc.c: Don't move reallocated objects that get smaller (code produced by the JIT is not position independent!) * libgst/xlat.c: Fix some bit-rot * libgst/opt.c: Fix off-by-one error in _gst_compute_stack_positions 2002-11-08 Paolo Bonzini * libgst/heap.c: Use MAP_NORESERVE if available. * libgst/alloc.c: Resort to mmap-ed areas once we cannot use sbrk anymore. 2002-11-06 Paolo Bonzini * libgst/oop.c: Unprotect freed pages, fix bug in removing pages from remembered table upon freeing. Blox up and running with generational and incremental GC. * libgst/save.c: Use buffered I/O. 2002-11-05 Paolo Bonzini * libgst/input.c: Strdup in _gst_push_string_stream * libgst/callin.c: So we have to close the streams * libgst/comp.c: Here as well * libgst/alloc.c: Ensure a block has already been touched (written to) before doing free-list operations. Otherwise, the SIGSEGV handler might allocate memory while the free-lists are not consistent. * libgst/oop.c: For #become:, ensure the two swapped objects are in the same generation. Otherwise, references to the new-space object that used to point to the old-space object are not recorded in the remembered set. 2002-11-04 Paolo Bonzini *** Version 2.0e (development) released 2002-10-26 Paolo Bonzini * libgst/alloc.c: More hooks * libgst/oop.c: Use them 2002-10-25 Paolo Bonzini * libgst/interp-bc.inl: Fix an obscure re-entrancy bug in _gst_send_message_internal, which was commonly triggered by the new garbage collector in the ANSI test suite. 2002-10-23 Paolo Bonzini * libgst/oop.c: Put back support for growing the OOP table. 2002-10-22 Paolo Bonzini * libgst/sym.c: Add more consts * libgst/sym.h: Likewise * libgst/cint.c: Likewise * libgst/cint.h: Likewise * libgst/callin.c: Likewise * libgst/callin.h: Likewise * libgst/gstpub.h: Likewise 2002-10-22 Mike Castle * libgst/callin.c: Fixes for Tcl 8.4.0 (add some consts) * libgst/callin.h: Fixes for Tcl 8.4.0 (add some consts) * libgst/dict.c: Fixes for Tcl 8.4.0 (add some consts) * libgst/dict.h: Fixes for Tcl 8.4.0 (add some consts) * libgst/gstpub.h: Fixes for Tcl 8.4.0 (add some consts) 2002-10-21 Paolo Bonzini * libgst/alloc.c: Collect statistics * libgst/dict.c: Add instance variables to ObjectMemory * libgst/oop.c: Collect statistics * libgst/oop.h: Declare functions to export statistics * libgst/prims.inl: Adjust for statistic collection 2002-10-17 Paolo Bonzini *** Version 2.0.7 (stable) released * libgst/alloc.c: Add some hooking abilities * libgst/oop.c: Big rewrite for switch to generational GC * libgst/oop.h: Likewise * libgst/oop.inl: Likewise * libgst/save.c: Likewise * libgst/print.c: Likewise (debugging functions) * libgst/gstpriv.h: Moved parts to oop.inl or oop.h, changed many flags for the new generational collector. * libgst/dict.c: Adjust for changes in variable names * libgst/prims.inl: Adjust for changes in variable names * libgst/gstpriv.h: define checks for !OPTIMIZE. * libgst/input.c: define readline_getc only if readline is used. * libgst/interp-bc.inl: fix syntax error for !OPTIMIZE. * libgst/lib.c: load FileDescr.st before ObjectMemory. 2002-10-15 Paolo Bonzini * libgst/lib.c: Print "GNU Smalltalk ready" only before reading from stdin. `verbose' --> _gst_verbose. * libgst/lib.h: Declare _gst_verbose. * libgst/comp.c: Conditionalize printing of stats and explanations on _gst_verbose and _gst_regression_testing. * libgst/comp.h: Remove `quiet' parameter to _gst_execute_statements. * libgst/gst.y: Caller adjusted. 2002-10-13 Paolo Bonzini * libgst/interp.c: Include strspell.h. * libgst/prims.inl: Define VMpr_String_similarityTo. 2002-10-08 Paolo Bonzini * libgst/print.c: Don't segfault when printing a Metaclass that has no class yet. 2002-10-06 Paolo Bonzini * libgst/input.c: Add the period to the word-termination characters. * libgst/dict.c: Declare AbstractNamespace and BindingDictionary; support arbitrary number of instance variables in dictionaries * libgst/dict.h: Likewise * libgst/dict.inl: Likewise * libgst/lib.c: Load AbstNamespace.st and BindingDict.st * libgst/byte.h: Add LINE_NUMBER_BYTECODE; declared _gst_line_number * libgst/byte.c: Print it; added _gst_line_number * libgst/comp.c: Use _gst_line_number * libgst/gst.y: Track locations * libgst/lex.c: Track locations * libgst/input.h: Added _gst_get_location * libgst/input.c: Implemented it * libgst/tree.h: Added location field to trees * libgst/tree.c: Store locations in trees * libgst/interp-bc.c: Treat LINE_NUMBER_BYTECODE as nop * libgst/xlat.c: Treat LINE_NUMBER_BYTECODE as nop 2002-10-05 Paolo Bonzini * libgst/xlat.c: Set F_XLAT_REACHABLE in the method and block prolog. * libgst/oop.c: GC unused JITted code. 2002-10-02 Paolo Bonzini * libgst/heap.c: Use EFAULT as an addition to SIGSEGV instead of an alternative method to detect unmapped memory areas. * libgst/interp-bc.inl: Don't use [ a ... b ] initializers because Apple's gcc is actually an Objective C compiler. 2002-09-29 Paolo Bonzini * libgst/alloc.c: New file, from lib-src. * libgst/alloc.h: New file, from lib-src. 2002-09-28 Paolo Bonzini * libgst/dict.c: Added HomedAssociation and associated declarations * libgst/dict.h: Added _gst_homed_association_class * libgst/lib.c: Load it * libgst/gstpriv.h: Remove finalization and add ephemerons * libgst/oop.c: Likewise * libgst/prims.inl: Likewise * libgst/sym.c: Remove #finalize symbol and add #mourn * libgst/sym.h: Likewise * libgst/lib.c: Set line-based buffering for stdout in regression testing mode. 2002-09-26 Paolo Bonzini * libgst/dict.inl: Simplify inst_var_at and inst_var_at_put * libgst/prims.inl: Inst_var_at_put now void, adjust caller. 2002-09-25 Paolo Bonzini * libgst/gst.y: Better error recovery 2002-09-23 Paolo Bonzini * libgst/dict.inl: Do memcpy to char * instead of to double * (because that does not solve double unalignment problems). * libgst/input.c: My_getc reads unsigned chars. 2002-09-19 Paolo Bonzini * libgst/dict.c: Added interruptLock variable to Process * libgst/interp.h: Added interruptLock field to gst_process * libgst/interp.c: Semaphore_new() accepts a parameter for the initial number of signals. Create the interruptLock when a new Process is created. 2002-09-18 Paolo Bonzini * libgst/interp.c: The highest priority process was being put in the process list for priority 4 even if it did not belong there. 2002-09-13 Paolo Bonzini *** Versions 2.0c (development) and 2.0.6 (stable) released * libgst/prims.inl: Allow specifying a class as the current namespace 2002-09-11 Paolo Bonzini * libgst/lex.c: support :: As well as . to separate namespaces * libgst/gst.y: Do corresponding changes in the grammar as well as changes to support compile-time namespace resolution * libgst/dict.c: Allow specifying a class as a pool dictionary and create namespaces at bootstrap * libgst/sym.c: Extend VARIABLE_NODE treatment in _gst_find_variable to support compile-time namespace resolution * libgst/sym.h: _gst_find_variable accepts a tree_node * libgst/comp.c: Callers adjusted * libgst/tree.h: Split tree node type TREE_VARIABLE_LIST into TREE_VAR_DECL_LIST and TREE_VAR_ASSIGN_LIST * libgst/tree.c: Likewise * libgst/dict.c: Give interrupt state to Processes * libgst/interp.h: Likewise * libgst/interp.c: Use it * libgst/prims.inl: Implement interrupt-handling primitives * libgst/lib.c: Load RecursionLock.st, drop short names * libgst/dict.c: Give a name to Semaphores * libgst/interp.h: Likewise * libgst/sysdep.h: _gst_disable_interrupts and _gst_enable_interrupts hold their state internally * libgst/sysdep.c: Implement this * libgst/events.c: Callers adjusted * libgst/interp-bc.inl: Callers adjusted * libgst/interp-jit.inl: Callers adjusted * libgst/prims.inl: Callers adjusted * libgst/interp.c: Callers adjusted 2002-09-10 Paolo Bonzini * libgst/comp.c: Compute stack depth correctly in the presence of cascades. * libgst/oop.c: Add valgrind hooks after OOPs are swept, fix _gst_alloc_words (was not always converting size from words to bytes) 2002-09-09 Paolo Bonzini * libgst/dict.c: Pass flags to alloc_oop * libgst/interp.c: Pass flags to alloc_oop * libgst/oop.c: Pass flags to alloc_oop, check for opportunities to grow the OOP table in sweep_oop * libgst/oop.inl: Receive flags in alloc_oop, force a GC as soon as possible (instead of triggering it) in low-water conditions * libgst/print.c: Print subclasses of Association as Associations. * libgst/dict.h: Declared _gst_variable_binding_class * libgst/dict.c: Declared _gst_variable_binding_class, use NAMESPACE_AT_PUT * libgst/dict.inl: New function variable_binding_new and macro NAMESPACE_AT_PUT * libgst/sym.c: Use NAMESPACE_AT_PUT * libgst/lib.c: Load VarBinding.st 2002-09-05 Paolo Bonzini * libgst/xlat.c: Support push 8-bit value bytecodes * libgst/opt.c: Support push 8-bit value bytecodes * libgst/interp-bc.inl: Support push 8-bit value bytecodes * libgst/byte.c: Support push 8-bit value bytecodes * libgst/byte.h: Support push 8-bit value bytecodes * libgst/comp.c: Support push 8-bit value bytecodes * libgst/interp.c: Add the alwaysPreempt parameter to resume_process. Callers and documentation adjusted. * libgst/interp-bc.inl: Support single step mode. * libgst/interp-jit.inl: Support single step mode. * libgst/prims.inl: Add single stepping primitive. 2002-08-21 Paolo Bonzini * libgst/oop.c: Walk the OOP table forwards in sweep_pooled_contexts. Correct off-by-one error in _gst_oop_index_valid. * libgst/prims.inl: Added branch hits. Fix bug where a too short replacement collection caused the String>>#replaceFrom:to:with:startingAt: primitive to succeed without making changes to the receiver. 2002-08-20 Paolo Bonzini * libgst/sysdep.c: Pass SIGCHLD to the signal handler for asynchronous file polling, as it might reveal a POLLHUP event. 2002-08-19 Paolo Bonzini * libgst/dict.c: Accept -1 for isPipe in _gst_set_file_stream_file * libgst/prims.inl: Try to lseek to the end of the file descriptor to check if it behaves like a pipe, and consider EINVAL the same as ESPIPE. This hack makes FileDescriptor and FileStream consider /proc entries as pipes. 2002-08-18 Paolo Bonzini * libgst/gst.y: Give an error message if a binding to an undeclared class is used. 2002-08-14 Paolo Bonzini *** Version 2.0.5 (stable) released * libgst/lib.c: Return `int' from _gst_init_smalltalk instead of exiting; give an error message if a non-existent file is given for -I. * libgst/gstpub.h: Adjust documentation and prototype * main.c: Adjust caller 2002-08-12 Paolo Bonzini *** Version 2.0b (development) released 2002-08-07 Paolo Bonzini *** Versions 2.0a (development) and 2.0.4 (stable) released 2002-07-24 Paolo Bonzini * libgst/prims.inl: Added missing `break' statement 2002-07-22 Paolo Bonzini * libgst/lib.c: Don't load Browser.st 2002-07-17 Paolo Bonzini *** Version 2.0.3 released 2002-07-15 Paolo Bonzini * libgst/xlat.c: Don't do class checks on global variables (they refer to the associations!) 2002-07-11 Paolo Bonzini *** Version 2.0.2 released 2002-07-05 Paolo Bonzini * libgst/dict.c: Define _gst_object_copy instead of _gst_dictionary_copy * libgst/prims.inl: Define a fast VMpr_Object_shallowCopy 2002-07-04 Paolo Bonzini * libgst/interp.h: Define MCF_ flags * libgst/prims.inl: Define VMpr_BlockClosure_valueAndResumeOnUnwind and VMpr_ContextPart_continue * libgst/interp.c: Complicate unwind_context, unwind_method, and define unwind_to to implement #ensure: correctly in the presence of non-local returns. * libgst/interp-bc.inl: Use MCF_ flags * libgst/xlat.c: Use MCF_ flags 2002-07-02 Paolo Bonzini * libgst/lex.c: Parse negative scaled decimal constants as negative; in general, parse them exactly without floating point errors. * libgst/prims.inl: Large-integer primitives pass when they receive LargeIntegerZero * libgst/mpz.c: Ensure the most significant limb of the gst_mpz objects is not zero * libgst/dict.c: Fix GC bug in _gst_grow_identity_dictionary 2002-06-25 Paolo Bonzini * libgst/lib.c: Load FloatD.st/FloatE.st/FloatQ.st * libgst/lex.c: Parse floats as long doubles, distinguish FloatD/FloatE/FloatQ literals. * libgst/comp.c: Distinguish FloatD/FloatE/FloatQ trees * libgst/tree.c: Add TYPE parameter to _gst_make_float_constant * libgst/tree.h: Adjust prototype, define CONST_FLOATD/CONST_FLOATE CONST_FLOATQ * libgst/gst.y: Pass TYPE parameter to _gst_make_float_constant * libgst/cint.c: Use FloatD/FloatE/FloatQ * libgst/callin.c: Use FloatD/FloatE/FloatQ * libgst/dict.c: Declared FloatD/FloatE/FloatQ * libgst/dict.h: Declared FloatD/FloatE/FloatQ * libgst/dict.inl: Declared functions to box and unbox FloatE's and FloatQ's * libgst/mpz.c: Defined _gst_mpz_get_ld * libgst/mpz.h: Declared _gst_mpz_get_ld * libgst/prims.inl: Define primitives on FloatE/FloatQ * libgst/interp-bc.inl: Change open-coded math operations to use FloatD 2002-06-28 Paolo Bonzini *** Version 2.0.1 released 2002-06-27 Paolo Bonzini * libgst/lib.c: Don't require the image directory to be world-writable. * libgst/xlat.c: Fixed embarrassing syntax error. * libgst/tree.c: Use %O. * libgst/sym.c: Likewise. * libgst/prims.inl: Likewise. * libgst/byte.c: Likewise. * libgst/comp.c: Likewise. * libgst/dict.c: Likewise. * libgst/dict.h: Likewise. * libgst/interp-bc.inl: Likewise. * libgst/interp.c: Likewise. * libgst/xlat.c: Likewise. 2002-06-26 Paolo Bonzini * libgst/oop.c: Remove printing functions. * libgst/oop.h: Likewise. * libgst/dict.c: Likewise. * libgst/dict.h: Likewise. * libgst/sym.c: Likewise. * libgst/sym.h: Likewise. * libgst/print.c: Move them here... * libgst/print.h: ... and here. * libgst/lib.c: Call _gst_init_snprintfv. 2002-06-25 Paolo Bonzini *** Version 2.0 released 2002-06-19 Paolo Bonzini * libgst/dict.c: Removed exceptionHandlers variable from the Process class. * libgst/lib.c: Search in the class namespace before looking in the class pools 2002-06-13 Paolo Bonzini * libgst/lib.c: reformat help message 2002-06-06 Paolo Bonzini * libgst/dict.inl: Always define 32-bit and 64-bit int<->OOP conversion functions * libgst/cint.c: Caller fixed * libgst/prims.inl: Support 64-bit file offsets * libgst/interp-bc.inl: Added more branch prediction hints 2002-06-02 Paolo Bonzini * libgst/callin.c: Define _gst_set_c_object * libgst/callin.h: Declare _gst_set_c_object * libgst/gstpub.h: Define setCObject in the VMProxy struct 2002-05-30 Paolo Bonzini * libgst/save.c: Made some functions inline; remove amount of checks on wrong_endianness; store number of pointer instance variables in advance in the OOP if < 127. A small improvement in image loading time, and an example of using F_COUNT (which will be used by GC in 2.1 to drop the recursive calls in the mark phase). 2002-05-30 Paolo Bonzini * libgst/save.c: Loop in the used part of the OOP table only (+15% average speedup on image loading time). * libgst/dict.c: Likewise * libgst/dict.h: Adapted prototype of _gst_init_dictionary_on_image_load * libgst/lex.c: Use character literals for 1-char tokens * libgst/gst.y: Likewise * libgst/jitpriv.h: New name of internal.h * libgst/xlat.c: Include jitpriv.h * libgst/interp-jit.inl: Include jitpriv.h instead of internal.h * libgst/gstpriv.h: Don't include internal.h 2002-05-28 Paolo Bonzini * libgst/dict.c: Don't cache the VMPrimitives dictionary, it causes bugs. 2002-05-23 Paolo Bonzini * libgst/comp.h: Changed _gst_invoke_init_block to _gst_invoke_hook. * libgst/comp.c: Trace exection of the hooks only if -E is specified; changed _gst_invoke_init_block to _gst_invoke_hook. * libgst/lib.c: Use _gst_invoke_hook * libgst/oop.c: Ditto * libgst/prims.inl: Ditto * libgst/save.c: Ditto * libgst/dict.c: Keep dictionary sizes a power of two and scramble the bits * libgst/dict.inl: Keep dictionary sizes a power of two and scramble the bits * libgst/prims.inl: Declare a primitive to scramble the bits of a SmallInteger * libgst/sym.h: Keep symbol table size a power of two * libgst/sym.c: Use a simpler hash and scramble its bits 2002-05-14 Paolo Bonzini * libgst/mpz.c: Fix multiple evaluation of arguments of BYTE_INVERT; work around misinterpretation of mpn_?shift documentation * libgst/oop.c: Hardcode printing of infinite and nan values in _gst_print_object, to avoid false regressions due to libc differences 2002-05-12 Paolo Bonzini * libgst/comp.c: Fire ObjectMemory events before and after evaluation in _gst_execute_statements * libgst/lib.h: Declared _gst_kernel_initialized * libgst/lib.c: Set _gst_kernel_initialized before invoking the #returnFromSnapshot event. 2002-05-11 Paolo Bonzini *** Version 1.96.6 released 2002-05-10 Paolo Bonzini * libgst/input.c: Fix spurious error from my_close when stdin is passed on the command line (via -) 2002-05-08 Paolo Bonzini * libgst/internal.h: _gst_internal_funcs now const * libgst/interp.c: Always mark thisContext (at worst, it is nil) * libgst/xlat.c: Include lightning.h, removed by mistake when switching to gstpriv.h; add const in dcd_send_special 2002-05-05 Paolo Bonzini * libgst/gst.h: ObjSize now an OOP * libgst/dict.inl: Likewise * libgst/xlat.c: Likewise * libgst/save.c: Likewise * libgst/oop.c: Likewise * libgst/mpz.c: Likewise * libgst/interp.c: Likewise * libgst/dict.c: Likewise * libgst/comp.c: Likewise 2002-05-02 Paolo Bonzini * libgst/gstpriv.h: Declare macros for branch prediction hints * libgst/interp-bc.inl: Use them * libgst/interp-jit.inl: Use them * libgst/interp.c: Use them * libgst/interp.inl: Use them * libgst/md-config.h: Use them * libgst/oop.c: Use them * libgst/oop.inl: Use them * libgst/oop.c: Allocate objects outside the main heap in _gst_alloc_obj * libgst/oop.h: Declare _gst_big_objects_threshold * libgst/prims.inl: Added primitives to tune threshold for in-heap allocation * libgst/oop.c: Modify calling convention for _gst_alloc_obj, in preparation for allocating outside the main heap * libgst/oop.h: Declaration adjusted. * libgst/dict.c: Callers adjusted. * libgst/oop.c: Callers adjusted. * libgst/dict.inl: Modify calling convention for instantiation functions, to account for the change to _gst_alloc_obj and in preparation for allocating outside the main heap. * libgst/interp.c: Callers adjusted. * libgst/comp.c: Callers adjusted. * libgst/callin.c: Callers adjusted. * libgst/sym.c: Callers adjusted. * libgst/dict.c: Callers adjusted. * libgst/prims.inl: Callers adjusted. 2002-05-01 Paolo Bonzini * libgst/dict.c: Move C...Size et al. into CSymbols, refer to CSymbols as to a pool dictionary of ByteArray, CObject, Float, Integer. Drop class comments, they are not needed here. Create a RegressionTesting global variable that suppresses more sources of variance. 2002-04-18 Paolo Bonzini * libgst/dict.c: Don't set writePtr and writeEnd for FileDescriptors in _gst_set_stream_file 2002-04-16 Paolo Bonzini * libgst/prims.inl: Return NaN when transcendental functions fail. Removed VMpr_LargeInteger_divide. 2002-04-14 Paolo Bonzini *** Version 1.96.5 released 2002-04-13 Paolo Bonzini * libgst/interp.c: Print a backtrace on SIGUSR1 * libgst/oop.c: Gc_running -> _gst_gc_running * libgst/oop.h: Declare _gst_gc_running 2002-04-06 Paolo Bonzini * libgst/interp-bc.inl: Properly check for overflows on bitshifts (used to return 0 instead of 16r-80000000) * libgst/prims.inl: Likewise 2002-03-27 Paolo Bonzini * libgst/mpz.c: New file * libgst/mpz.h: New file * libgst/prims.inl: Implemented primitives for large integers 2002-03-25 Paolo Bonzini * libgst/md-config.h: Added cacheline definitions * libgst/interp.c: Added cacheline definitions * libgst/oop.c: Added cacheline definitions * libgst/xlat.c: Added cacheline definitions * libgst/interp.inl: Use inttypes.h rather than stdint.h 2002-03-21 Paolo Bonzini * libgst/events.c: Don't include sys/select.h, we don't need it * libgst/gstpub.h: Don't include sys/select.h, we don't need it * libgst/sysdep.c: Support HP/UX's FIOSSAIOSTAT and FIOSSAIOOWN ioctls to setup asynchronous I/O * libgst/input.c: Check for EINTR when reading from a file * libgst/prims.inl: Check for EINTR when reading from a file * libgst/lex.c: Skip _ inside numeric literals 2002-03-17 Paolo Bonzini * libgst/lib.c: Updated list of files for virtual filesystem layer * libgst/prims.inl: Implement the PRIM_MK_TEMP file operation. 2002-03-16 Paolo Bonzini * libgst/input.h: Added _gst_push_stream_oop * libgst/input.c: Implement stream operations for arbitrary OOP's. * libgst/prims.inl: Remove checks for String-ness in compilation primitives. 2002-03-12 Paolo Bonzini *** Version 1.96.4 released 2002-03-10 Paolo Bonzini * libgst/oop.h: _gst_gc_flip -> _gst_scavenge, _gst_minor_gcflip -> _gst_minor_scavenge * libgst/oop.c: Likewise * libgst/oop.inl: Likewise * libgst/save.c: Likewise * libgst/prims.inl: Likewise * libgst/interp.c: Likewise * libgst/oop.c: GC flip -> scavenging 2002-02-28 Paolo Bonzini * libgst/gst.h: Removed private stuff * libgst/gstpriv.h: Private stuff from gst.h + inclusion of all the other headers * byte.c: Include gstpriv.h * callin.c: Include gstpriv.h * cint.c: Include gstpriv.h * comp.c: Include gstpriv.h * dict.c: Include gstpriv.h * events.c: Include gstpriv.h * gst.tab.c: Include gstpriv.h * heap.c: Include gstpriv.h * input.c: Include gstpriv.h * interp.c: Include gstpriv.h * lex.c: Include gstpriv.h * lib.c: Include gstpriv.h * oop.c: Include gstpriv.h * opt.c: Include gstpriv.h * save.c: Include gstpriv.h * str.c: Include gstpriv.h * sym.c: Include gstpriv.h * sysdep.c: Include gstpriv.h * tree.c: Include gstpriv.h * xlat.c: Include gstpriv.h 2002-02-26 Paolo Bonzini * libgst/xlat.c: Fixed a code generation bug for {} array constructors (two consecutive updates of the stack pointer). 2002-02-26 Paolo Bonzini Named primitives: interpreter changes ------------------------------------- * libgst/prims.inl: Implement named primitives (vs. numbered) * libgst/interp.h: Reflect changes in the interface for named primitives * libgst/interp-bc.inl: Call the appropriate named primitive in MAYBE_PRIMITIVE * libgst/interp.c: Include prims.inl before interp-bc.inl or interp-jit.inl * libgst/internal.h: Include VMpr_BlockClosure_blockCopy in the internal functions * libgst/interp-jit.inl: Include VMpr_BlockClosure_blockCopy in the internal functions * libgst/xlat.c: Adapt to changes in the interface for named primitives Named primitives: compiler changes ---------------------------------- * libgst/gst.y: Declare primitive as type * libgst/tree.h: PrimitiveIndex -> primitiveName * libgst/tree.c: Likewise * libgst/dict.h: Declared _gst_resolve_primitive_name * libgst/dict.c: Added _gst_resolve_primitive_name and init_primitives_dictionary * libgst/comp.c: Use _gst_resolve_primitive_name Named primitives: image loading ------------------------------- * libgst/dict.c: Added prepare_primitive_number_map, removed bit of init_runtime_objects to initialize the symbols and calling _gst_init_symbols instead. * libgst/sym.c: Added _gst_init_symbols, symbol_list not extern anymore * libgst/sym.h: Added _gst_init_symbols, symbol_list not extern anymore * libgst/comp.c: Added _gst_restore_primitive_number * libgst/comp.h: Declared _gst_restore_primitive_number 2002-02-26 Paolo Bonzini * libgst/callin.c: Implemented _gst_register_oop_array & co * libgst/callin.h: Declared _gst_register_oop_array & co * libgst/gstpub.h: Added registerOOPArray to the VMProxy * libgst/comp.c: Use pointers rather than indices to implement the literal vector, to be compatible with _gst_register_oop_array's conventions. Use _gst_register_oop_array to register the literal vector, in init_compiler. * libgst/oop.c: Replaced mark_incubator_oops with a call to _gst_register_oop_array. * libgst/dict.c: Removed CFunctionDescs from the list of pool dictionaries for Object. * libgst/interp-bc.inl: Fixed a rare bug by invalidating last_primitive before exiting the interpreter. 2002-02-25 Paolo Bonzini * libgst/cint.c: Use AVL trees for the C function registry; get rid of _gst_init_cfunc_vec. * libgst/callin.c: Use red-black trees for the OOP registry; get rid of _gst_init_oopregistry. * libgst/lib.c: Get rid of _gst_init_oopregistry * libgst/callin.h: Get rid of _gst_init_oopregistry * libgst/dict.c: Register the Smalltalk dictionary in init_runtime_objects * libgst/comp.c: Keep _gst_this_class & co. into the registry. Got rid of _gst_mark_compile_context. * libgst/comp.h: Removed _gst_mark_compile_context. * libgst/events.c: Removed _gst_mark_events_semaphores, use the registry instead. * libgst/events.h: Removed _gst_mark_events_semaphores * libgst/interp.c: Don't call _gst_mark_events_semaphores * libgst/oop.c: Remove the hooks in mark_oops that have been replaced by the registry (now that it is a tree it is also faster) * libgst/interp.h: Declared _gst_async_signal_and_unregister * libgst/gstpub.h: Declared asyncSignalAndUnregister in the VMProxy * libgst/interp.c: Implemented _gst_async_signal_and_unregister * libgst/interp-bc.inl: Added glue for _gst_async_signal_and_unregister * libgst/interp-jit.inl: Added glue for _gst_async_signal_and_unregister 2002-02-23 Paolo Bonzini * libgst/lex.c: Document the functions and variables * libgst/lex.h: Likewise * libgst/input.c: Likewise * libgst/input.h: Likewise * libgst/sym.c: Likewise * libgst/sym.h: Likewise * libgst/sysdep.c: Likewise * libgst/sysdep.h: Likewise * libgst/sym.c: Allow _ for variable names in the bootstrapping declarations. 2002-02-22 Paolo Bonzini * libgst/oop.c: Remove the routines to disable the GC * libgst/oop.h: Remove the routines to disable the GC * libgst/save.c: Remove the calls to disable the GC since the variable was never checked * libgst/oop.c: Document the functions and variables * libgst/oop.h: Likewise * libgst/oop.inl: Likewise 2002-02-21 Paolo Bonzini * libgst/comp.c: Document the functions and variables * libgst/comp.inl: Likewise * libgst/byte.c: Likewise * libgst/byte.h: Likewise * libgst/dict.inl: Likewise * libgst/dict.c: Likewise * libgst/dict.h: Likewise 2002-02-20 Paolo Bonzini * libgst/comp.c: Document the functions and variables * libgst/comp.h: Likewise * libgst/input.c: Flush stdout after printing the prompt, if readline is not used. 2002-02-19 Paolo Bonzini * libgst/callin.c: Remove conditional on PICKY_VA_ARG, ANSI says it should really be picky (i.e. not accept a char type) * libgst/interp.inl: Try to use long long or intmax_t to check overflow on multiplication * libgst/interp-jit.inl: When refreshing the native IPs, special case the termination method so that its native instruction pointer is the special code to yield control back to _gst_interpret. * libgst/interp.h: Document the functions and variables * libgst/interp-bc.inl: Likewise * libgst/interp-jit.inl: Likewise * libgst/prims.inl: Likewise * libgst/opt.c: Likewise * libgst/opt.h: Likewise * libgst/callin.c: Likewise * libgst/callin.h: Likewise * libgst/cint.c: Likewise * libgst/cint.h: Likewise 2002-02-16 Paolo Bonzini * libgst/interp.c: Document the functions and variables 2002-02-15 Paolo Bonzini * libgst/save.c: Document the functions and variables * libgst/save.h: Likewise * libgst/str.c: Likewise * libgst/str.h: Likewise * libgst/events.c: Likewise * libgst/events.h: Likewise * libgst/tree.c: Likewise * libgst/tree.h: Likewise * libgst/heap.c: Likewise * libgst/heap.h: Likewise * libgst/lib.c: Likewise * libgst/lib.h: Likewise * libgst/gst.h: Likewise * libgst/gstpub.h: Likewise * libgst/byte.h: Remove leading double underscores from the guard * libgst/callin.h: Likewise * libgst/cint.h: Likewise * libgst/comp.h: Likewise * libgst/dict.h: Likewise * libgst/events.h: Likewise * libgst/gst.h: Likewise * libgst/gst.tab.h: Likewise * libgst/gstpub.h: Likewise * libgst/heap.h: Likewise * libgst/input.h: Likewise * libgst/internal.h: Likewise * libgst/interp.h: Likewise * libgst/lex.h: Likewise * libgst/lib.h: Likewise * libgst/md-config.h: Likewise * libgst/memzero.h: Likewise * libgst/oop.h: Likewise * libgst/opt.h: Likewise * libgst/save.h: Likewise * libgst/str.h: Likewise * libgst/sym.h: Likewise * libgst/sysdep.h: Likewise * libgst/tree.h: Likewise * libgst/xlat.h: Likewise * libgst/comp.inl: Remove the useless guard * libgst/dict.inl: Likewise * libgst/interp.inl: Likewise * libgst/oop.inl: Likewise 2002-02-07 Paolo Bonzini * libgst/lib.c: Show only the last copyright year. * libgst/events.c: Major reengineering to avoid race conditions and dangling pointers... gee, how bad the code was before this! :-( * libgst/sysdep.c: To avoid cluttering the straces, don't set the same signal handlers as the last time in _gst_set_file_interrupt * libgst/interp-bc.inl: Protect interrupts while accessing async_queue_index (even though it is volatile) * libgst/interp-jit.inl: Likewise 2002-01-29 Paolo Bonzini *** Version 1.96.3 released. * libgst/opt.c: Convert arguments to qsort and bsearch to accept two void *'s. * libgst/input.c: Likewise 2002-01-23 Paolo Bonzini * main.c: Converted to ANSI C and to the GNU coding standards * libgst/byte.c: Likewise * libgst/callin.c: Likewise * libgst/cint.c: Likewise * libgst/comp.c: Likewise * libgst/dict.c: Likewise * libgst/events.c: Likewise * libgst/gst.tab.c: Likewise * libgst/heap.c: Likewise * libgst/input.c: Likewise * libgst/interp.c: Likewise * libgst/lex.c: Likewise * libgst/lib.c: Likewise * libgst/oop.c: Likewise * libgst/opt.c: Likewise * libgst/save.c: Likewise * libgst/str.c: Likewise * libgst/sym.c: Likewise * libgst/sysdep.c: Likewise * libgst/tree.c: Likewise * libgst/xlat.c: Likewise * libgst/byte.h: Likewise * libgst/callin.h: Likewise * libgst/cint.h: Likewise * libgst/comp.h: Likewise * libgst/dict.h: Likewise * libgst/events.h: Likewise * libgst/gst.h: Likewise * libgst/gst.tab.h: Likewise * libgst/gstpub.h: Likewise * libgst/heap.h: Likewise * libgst/input.h: Likewise * libgst/internal.h: Likewise * libgst/interp.h: Likewise * libgst/lex.h: Likewise * libgst/lib.h: Likewise * libgst/md-config.h: Likewise * libgst/memzero.h: Likewise * libgst/oop.h: Likewise * libgst/opt.h: Likewise * libgst/save.h: Likewise * libgst/str.h: Likewise * libgst/sym.h: Likewise * libgst/sysdep.h: Likewise * libgst/tree.h: Likewise * libgst/xlat.h: Likewise * libgst/comp.inl: Likewise * libgst/dict.inl: Likewise * libgst/interp-bc.inl: Likewise * libgst/interp-jit.inl: Likewise * libgst/interp.inl: Likewise * libgst/oop.inl: Likewise * libgst/prims.inl: Likewise 2002-01-22 Paolo Bonzini * libgst/gst.y: Signal a warning if self, super, true, false, nil, or thisContext are sent. General reformatting of the source code. 2002-01-18 Paolo Bonzini * libgst/dict.c: Removed initialization blocks 2002-01-17 Nigel Williams * libgst/dict.c: Added atEnd variable to FileDescriptor * libgst/prims.inl: Provide a primitive to check if a descriptor is a pipe or a file. * libgst/dict.c: Added timeSlice variable to ProcessorScheduler * libgst/events.c: Pass a third parameter to signalAfter * libgst/interp-bc.inl: Call setPreemptionTimer once the timer has been fired and acknowledged * libgst/interp-jit.inl: Call setPreemptionTimer once the timer has been fired and acknowledged * libgst/interp.c: New functions related to preemptive multitasking * libgst/interp.h: Added timeSlice variable to ProcessorScheduler * libgst/sysdep.h: Added support for process-time timers (like ITIMER_VIRTUAL) * libgst/sysdep.c: Added support for process-time timers (like ITIMER_VIRTUAL) 2002-01-15 Paolo Bonzini * libgst/lib.c: Ensure that the image path is the directory from which we loaded the image, rather than the default image path. 2002-01-04 Paolo Bonzini *** Version 1.96.2 released 2002-01-02 Paolo Bonzini * libgst/dict.c: Add the Source class variable to the Random class. * libgst/input.c: Don't use readline unless stdin is a TTY. * libgst/lib.c: Changed banner to "GNU Smalltalk ready" (lowercase r) 2001-12-12 Paolo Bonzini * libgst/events.c: Poll until there are no pending events 2001-11-20 Paolo Bonzini *** Version 1.96.1 released 2001-11-13 Paolo Bonzini * libgst/gst.y: Implement #(true false nil) as per the ANSI standard. 2001-10-24 Paolo Bonzini * libgst/sysdep.c: Define O_ASYNC as FASYNC if not found. 2001-10-17 David Forster * libgst/cint.c: Add uInt and uLong support for C interface. Change longType return to use fromCLong. * libgst/sym.c: Add uIntSymbol and uLongSymbol. 2001-10-16 Paolo Bonzini *** Version 1.95.5 released. * libgst/lib.c: Observe quietExecution when loading .stinit and .stpre. 2001-10-06 Paolo Bonzini * libgst/lib.c: Fixed bugs after applying the two patches below. 2001-10-06 Nigel Williams * libgst/lib.c: Show error message if file not found 2001-08-28 Carlo Dapor * libgst/lex.c: Reset floating point exception mask under FreeBSD. * libgst/lib.c: Switch to getopt_long for parsing long command line options. 2001-07-14 Paolo Bonzini * libgst/gst.h: Gee, what a hiatus! Fixed for C++. * libgst/gstpub.h: Likewise 2001-06-16 Paolo Bonzini * libgst/interp.h: Defined PRIM_CHECK_INTERRUPT * libgst/prims.inl: Added PRIM_CHECK_INTERRUPT where required * libgst/xlat.c: EmitInterruptCheck called from emitPrimitive only if PRIM_CHECK_INTERRUPT 2001-06-13 Paolo Bonzini * libgst/xlat.c: Create the IPMap when translating. Defined mapVirtualIP. Store the IP at every possible synchronization point (emitInterruptCheck). * libgst/xlat.h: Declared mapVirtualIP. * libgst/str.c: Declared addBufData * libgst/str.h: Defined addBufData * libgst/xlat.c: Generate an interrupt check as part of the prolog rather than of the return bytecodes. 2001-06-12 Paolo Bonzini * libgst/interp-jit.inl: Defined refreshNativeIPs. * libgst/interp.c: ReturnIP --> nativeIP * libgst/interp.h: ReturnIP --> nativeIP * libgst/dict.c: ReturnIP --> nativeIP * libgst/save.c: Reset a context's nativeIP upon image load. 2001-06-08 Paolo Bonzini * libgst/sysdep.c: Open the slave pty before forking 2001-06-06 Paolo Bonzini * libgst/md-config.h: Define BRANCH_REGISTER for every architecture * libgst/interp-bc.inl: Put the prefetched address into a branch register. * libgst/dict.c: Include sysdep.h * libgst/input.c: Removed unused variable in pushUNIXFile * libgst/prims.inl: Removed unused variable in primitive 254 * libgst/sysdep.h: Declared fullWrite 2001-06-05 Paolo Bonzini * libgst/xlat.c: GetMethodBase became initTranslator * libgst/xlat.h: Likewise * libgst/interp.c: Got rid of the nativeBase * libgst/interp-jit.inl: Got rid of the nativeBase * libgst/sysdep.c: Set the CLOEXEC flag in openFile 2001-06-01 Paolo Bonzini * libgst/events.c: Use poll(2) instead of select(2), I am told it is more scalable. * libgst/input.c: Likewise, for coherency. 2001-05-26 Paolo Bonzini * libgst/sysdep.c: Use ptys to create a pipe; when setting file interrupt with SIOCSGRP and FIOASYNC, check that both ioctls succeed. 2001-05-24 Paolo Bonzini * libgst/interp.c: Make unwindMethod return whether the return was successful * libgst/interp-bc.inl: Send #badReturnError if return from method was unsuccessful * libgst/xlat.c: Likewise * libgst/interp-jit.inl: Added a comment re. the only serious bug remaining. 2001-05-23 Paolo Bonzini * libgst/heap.c: _WIN32 --> WIN32 * libgst/gst.h: Define WIN32 if __CYGWIN__ or __CYGWIN32__ * libgst/sysdep.c: _WIN32 --> WIN32 2001-05-22 Paolo Bonzini * libgst/xlat.c: Added support for inlined primitives * libgst/prims.inl: Marked a few primitives as inlined * libgst/dict.inl: Added accessors for the ISP_ISWORDS bit. 2001-05-20 Paolo Bonzini * libgst/lib.c: Remove calls to moncontrol; will be replaced by new profiling stuff. * libgst/prims.inl: Temporarily embed the moncontrol primitive into #if 0. 2001-05-17 Paolo Bonzini * libgst/dict.c: Recycle existing std{in,out,err}. * libgst/input.c: Wait for a character to be available before returning to Readline. * libgst/prims.inl: Reset errno to 0 after calling lseek. 2001-05-15 Paolo Bonzini * libgst/interp-jit.inl: In sendMessageInternal force a call to getNativeCode upon a cache miss 2001-05-11 Paolo Bonzini * libgst/xlat.c: Fixes for PowerPC (sizeof(jit_insn) > 1) 2001-05-04 Paolo Bonzini * libgst/cint.c: Support selfSmalltalk and variadicSmalltalk as additional parameter types * libgst/sym.c: Defined selfSmalltalkSymbol and variadicSmalltalkSymbol * libgst/sym.h: Declared selfSmalltalkSymbol and variadicSmalltalkSymbol 2001-04-30 Paolo Bonzini * libgst/prims.inl: Fixed buffer overflows involving oopVec. 2001-04-28 Paolo Bonzini * libgst/sysdep.h: Fixed isFinite, it reported -2.0 as infinite! * libgst/callin.h: Declared basicSize * libgst/callin.c: Defined basicSize * libgst/gstpub.h: Added basicSize to the InterpreterProxy 2001-04-23 Paolo Bonzini * libgst/interp.c: Extrapolated a part of it into events.c, include events.h * libgst/prims.inl: Turn some primitives into calls to functions in events.c * libgst/events.c: New file * libgst/events.h: New file * libgst/interp.h: Declared syncWait * libgst/interp.c: Defined syncWait from primitive 86's code * libgst/prims.inl: Primitive 86 now calls syncWait * libgst/gstpub.h: Declared syncWait in the interpreterProxy * libgst/callin.c: Likewise * libgst/sysdep.c: Use socketpair to create a pipe 2001-04-16 Paolo Bonzini * libgst/dict.h: Declared fileDescriptorClass * libgst/dict.c: Declared fileDescriptorClass * libgst/lib.c: Load FileDescr.st * libgst/opt.c: fix incorrect peephole optimization: Of two equal `pop/store into instance variable of new stack top' bytecodes, the second became a `duplicate stack top' bytecode 2001-04-15 Paolo Bonzini * libgst/callin.c: Use incAddOOP everywhere instead of registerOOP. Added objectAlloc to the interpreterProxy * libgst/callin.h: Declared objectAlloc in the interpreterProxy * libgst/cint.c: InvokeCFunction now includes an incSavePointer and incRestorePointer pair. * libgst/gst.h: Make incAddOOP a single statement instead of a C block. * libgst/cint.c: In pushSmalltalkObj, use the incubator rather than the registry. * libgst/cint.h: Removed declaration of enableGC, since the above change left it unused. * libgst/prims.inl: Removed primitive 264 (#enableGC:) 2001-04-02 Paolo Bonzini * libgst/dict.c: Declared objectMemoryClass * libgst/dict.h: Declared objectMemoryClass * libgst/lib.c: Load ObjMemory.st, not initialize.st * libgst/save.c: Raise ObjectMemory events * libgst/comp.c: Raise ObjectMemory events * libgst/oop.c: Raise ObjectMemory events * libgst/prims.inl: Raise ObjectMemory events 2001-03-31 Paolo Bonzini * libgst/callin.c: Implemented byteArrayToOOP and OOPToByteArray * libgst/gstpub.h: Declared byteArrayToOOP and OOPToByteArray in the VMProxy. * libgst/sysdep.c: Removed code to set the LANG environment variable on Win32 systems. 2001-03-28 Paolo Bonzini * libgst/dict.c: Added an `access' parameter to setFileStreamFile * libgst/prims.inl: Pass the `access' parameter to setFileStreamFile from primitive 254 2001-03-20 Paolo Bonzini * libgst/dict.c: Set up FileStream for new buffering scheme, and updated setFileStreamFile. * libgst/prims.inl: Implemented primitive 254 for new buffering scheme. Incorporated primitives 247/248 (file-in) into 254. 2001-03-17 Paolo Bonzini * libgst/input.c: Implemented pushUNIXFile & co. in terms of file descriptors. * libgst/prims.inl: Implement FileStream in terms of file descriptors. * libgst/save.c: Use file descriptors. * libgst/sysdep.c: Modified openFile/openPipe to use file descriptors. 2001-03-05 Paolo Bonzini * libgst/comp.c: Bindings are simple oopConsts now. * libgst/tree.c: Resolve bindings as oopConsts. * libgst/tree.h: Removed bindingConst. * libgst/gst.y: Raise an error on an invalid binding. * libgst/comp.c: initCompiler is now public. * libgst/comp.h: initCompiler is now public. * libgst/lib.c: Call initCompiler. 2001-03-01 Paolo Bonzini * libgst/md-config.h: Fixed typo in register allocation for the SPARC. 2001-03-01 Dirk Sondermann * libgst/md-config.h: Disable register allocation on the SPARC (possibly temporary change). 2001-02-23 Paolo Bonzini *** Released version 1.95.3 2001-02-19 Paolo Bonzini * libgst/interp.h: Declare sendMethod. * libgst/interp.c: Added sendMethod to list of routines implemented by plug-ins. * libgst/interp-bc.inl: Added sendMethod. * libgst/interp-jit.inl: Added sendMethod. * libgst/prims.inl: Support sending methods in the #perform: and #perform:withArguments: primitive. * libgst/comp.c: Add `install' parameter to compileMethod; set latestCompiledMethod in compileMethod; use sendMethod in executeStatements. * libgst/gst.y: Pass `install' parameter to compileMethod 2001-02-17 Paolo Bonzini * libgst/input.c: Made from complete.c and part of lex.c * libgst/input.h: Made from complete.h and part of lex.h * libgst/gst.y: Include input.h * libgst/byte.c: Include input.h instead of lex.h * libgst/cint.c: Ditto * libgst/comp.c: Ditto * libgst/dict.c: Ditto * libgst/heap.c: Ditto * libgst/input.c: Ditto * libgst/interp.c: Ditto * libgst/lex.c: Ditto * libgst/lib.c: Ditto * libgst/oop.c: Ditto * libgst/opt.c: Ditto * libgst/sym.c: Ditto * libgst/tree.c: Ditto * libgst/comp.c: Removed emacsProcess from here * libgst/tree.c: Removed hadError from here * libgst/input.c: Moved emacsProcess and hadError here * libgst/comp.h: Removed emacsProcess from here * libgst/tree.h: Removed hadError from here * libgst/input.h: Moved emacsProcess and hadError here 2001-02-17 Dirk Sondermann * libgst/heap.c: Fixed for Solaris 2001-02-16 Paolo Bonzini * libgst/complete.c: New file * libgst/complete.h: New file * libgst/lex.c: Moved initializeReadline to readline.c * libgst/lib.c: Call initializeReadline after we loaded the image, because addAllSymbolCompletions needs the full symbol table. * libgst/sym.c: Call addSymbolCompletion in internCountedString, added addAllSymbolCompletions. * libgst/sym.h: Declared addAllSymbolCompletions 2001-02-15 Paolo Bonzini * libgst/cint.c: Made invokeCRoutine return whether the call-out was successful. * libgst/cint.h: Made invokeCRoutine return a boolean. * libgst/prims.inl: On invalid C call-outs, primitive 255 fails. 2001-02-14 Paolo Bonzini * libgst/prims.inl: In primitive 255 (C call-out) check that we were not called from the at-cache. 2001-02-13 Paolo Bonzini * libgst/dict.c: Keep dictionaries no more than 75% full, * libgst/dict.h: Ditto * libgst/dict.c: Keep dictionary sizes prime (new function newNumFields). 2001-02-12 Paolo Bonzini * libgst/gst.h: Moved F_FINALIZE into the runtime flags (not preserved between the time an image is saved and the time it is loaded) 2001-02-06 Paolo Bonzini * libgst/lex.c: PushReadlineString became pushStdinString, and calls pushUNIXFile if emacsProcess is true or readline is not available * libgst/lex.h: Declare pushStdinString * libgst/lib.c: Instead of using #ifdef to decide between pushReadlineString or pushUNIXFile, use pushStdinString. 2001-02-02 Paolo Bonzini * libgst/callin.c: Added idToOOP/OOPToId, declaration of interpreterProxy * libgst/gstpub.h: Declared idToOOP/OOPToId, VMProxyStruct * libgst/callin.h: Moved old contents of gstpub.h here * libgst/lib.c: Don't call gst_dld_init * libgst/cint.c: Don't call initUserCFuncs; merged with dld_gst.c. In gst_dld_open automatically call gst_initModule for the shared library; and always use libltdl. * libgst/cfuncs.c: Removed. * libgst/dld*: Removed. * libgst/cint.c: Search the cFuncInfo array backwards, so that new definitions override the old ones. 2001-01-31 Paolo Bonzini * libgst/cint.c: Declared a wrapper around opendir, which returns ENOSYS under Linux! Also declared isExecutable * libgst/lib.c: Load OtherArrays.st * libgst/sysdep.h: Declared fileIsExecutable * libgst/sysdep.c: Defined fileIsExecutable 2001-01-31 Paolo Bonzini * libgst/comp.c: Compile bindingConsts. * libgst/gst.y: Added #{...} literals * libgst/sym.c: Defined findVariableBinding * libgst/sym.h: Declared findVariableBinding * libgst/tree.c: Defined makeBindingConstant * libgst/tree.h: Declared makeBindingConstant and bindingConst 2001-01-30 Paolo Bonzini * libgst/dict.c: Define KernelFileSystemPath in initDictionaryOnImageLoad, and KernelFilePath in initDictionary 2001-01-30 Paolo Bonzini *** Released version 1.95.1 2001-01-16 Paolo Bonzini * libgst/interp-bc.inl: Define different optimization levels depending on REG_AVAILABILITY. * libgst/dict.inl: Include md-config.h instead of register.h * libgst/interp.c: Include md-config.h instead of register.h * libgst/md-config.h: New name of register.h 2001-01-14 Paolo Bonzini * libgst/comp.c: Use incubator in makeBlockClosure. * libgst/oop.inl: IsObjAddr returns false if the address lies beyond the allocPtr (used to be beyond the maxPtr) 2001-01-12 Paolo Bonzini * libgst/interp-bc.inl: Fixed pipelining bugs; added more caching opportunities 2001-01-09 Paolo Bonzini * libgst/interp-bc.inl: Implementation of pipelining * libgst/interp.c: Defined and explained PIPELINING 2001-01-08 Paolo Bonzini * libgst/dict.inl: Added cast to arrayNew to work on 64-bit machines. * libgst/gst.h: Removed warning for 64-bit machines. * libgst/interp.c: Fixed prepareContext to work on 64-bit machines (num is now a long). * libgst/oop.c: Make data spaces twice as big on 64-bit machines. * libgst/oop.h: Make data spaces twice as big on 64-bit machines. * libgst/register.h: Removed warning for unsupported architectures, was much more a burden than I had expected. 2000-12-16 Paolo Bonzini * libgst/opt.c: Finished first draft of type inferencing. * libgst/xlat.c: Adapted to use opt.c; nothing was broken for disabled type inferencing. 2000-12-05 Paolo Bonzini * libgst/heap.c: Moved the process of guessing the heap base from configure.in to here. * libgst/sysdep.h: Declared SigHandler * libgst/sysdep.c: Made setSignalHandler return the previous signal handler. 2000-11-01 Paolo Bonzini * libgst/lib.c: Changed bug reporting address 2000-10-14 GertJan Kersten (GertJan.Kersten@bolesian.nl) * libgst/cint.c: Fix brokenness in Cygwin's stat and chdir (which set errno even if the function succeeds). 2000-09-12 Paolo Bonzini * libgst/opt.c: Started implementation of type inferencing (have basic block detection now). Finally succeded in passing Physics yesterday. 2000-09-10 Paolo Bonzini * libgst/interp.h: Added declarations for primitive attributes. * libgst/prims.inl: Added primitive attributes. * libgst/xlat.c: Use primitive attributes in emitPrimitive. 2000-09-09 Paolo Bonzini * libgst/xlat.c: Added discardNativeCode and modified other function to use the `discarded' list. * libgst/xlat.h: Added declaration for discardNativeCode. * libgst/dict.c: In identityDictionaryAtPut, return the old value associated to the key. * libgst/comp.c: Include xlat.h; call discardNativeCode on the old method if a method is replacing another. * libgst/prims.inl: Primitive 90, instead of returning the native code for a method, discards the method (completely different semantics -- but the old one had no use since the Smalltalk program had no interesting use of the result). 2000-09-09 Paolo Bonzini * libgst/byte.c: Modified bytecode 134 for pop-into-array * libgst/byte.h: Modified bytecode 134 for pop-into-array * libgst/interp-bc.inl: Modified bytecode 134 for pop-into-array * libgst/opt.c: Modified computeStackPositions for pop-into-array * libgst/xlat.c: Modified bytecode 134 for pop-into-array, added gen_popIntoArray * libgst/comp.c: Added compileArrayConstructor and modified according to the changes to tree.c below * libgst/lex.c: Recognize { and } * libgst/gst.y: Recognize { ... } syntax * libgst/tree.c: Removed charConst, symbolConst -> oopConst, implemented makeArrayConstructor * libgst/tree.h: Declared makeArrayConstructor, added arrayConstructorType, removed charConst, symbolConst -> oopConst 2000-09-08 Paolo Bonzini * libgst/interp.c: Method cache is no longer static; moved MethodCacheEntry declaration to interp.h. Also found bug in lookupMethod which prevented the method cache from being fully exploited (startingClassOOP was set to the methodClass). * libgst/interp.h: Declared MethodCacheEntry * libgst/interp.inl: Defined checkSendCorrectness * libgst/prims.inl: Used checkSendCorrectness * libgst/xlat.c: Included compilation of == into gen_intComparison (now called gen_binaryBool); renamed gen_intOperation to gen_binaryInt and TREE_ARIT_* to TREE_BINARY_* 2000-09-07 Paolo Bonzini *** Version 1.8.3 released * libgst/dict.c: Removed ByteMemory and WordMemory declarations. * libgst/dict.h: Removed ByteMemory and WordMemory declarations. * libgst/lib.c: Don't load ByteMemory and WordMemory definitions. * libgst/prims.inl: Removed ByteMemory primitives. 2000-09-07 Nigel Williams * libgst/cint.c: Allow to pass nil for stringOut, byteArray and byteArrayOut too. 2000-09-01 Nigel Williams * libgst/prims.inl: Corrected class check for primitive 203/204. 2000-08-15 Paolo Bonzini * libgst/opt.c: Added stub implementation of inferSmallIntegerOps. * libgst/opt.h: Declare inferSmallIntegerOps and the constants it uses. * libgst/xlat.c: Added support for inferSmallIntegerOps and ability to omit overflow checks if the result of an inlined operation is known to be a SmallInteger. 2000-08-08 Paolo Bonzini * libgst/comp.c: Renamed compileSubexpressionWithGoto to compileSubexpressionAndJump * libgst/dict.inl: Only have 8 case's (instead of 9) in nilFill * libgst/interp.c: Only have 8 case's (instead of 9) in prepareContext * libgst/save.c: Moved most of loadFromFile to loadSnapshot; removed goto statements (my life is passing through a phase of structured programming mania). 2000-08-06 Paolo Bonzini * libgst/byte.c: Moved part to opt.c * libgst/byte.h: Moved part to opt.h * libgst/opt.c: Created from byte.c. As the JIT compiler will get more sophisticated this part is going to get bigger. * libgst/opt.h: Created from byte.h * libgst/comp.c: Include opt.h. Also, don't generate unreachable jumps in `... ifTrue: [ ^true ]' (or an analogous pattern with #ifTrue:ifFalse:). This pleases computeStackPositions enough to run the Prolog and Lisp interpreters. * libgst/xlat.c: Include opt.h * libgst/gst.h: Added F_FIXED. * libgst/oop.h: Declared makeFixedOOP. * libgst/oop.c: Added makeFixedOOP, deal with fixed objects in prepareForSweep. * libgst/prims.inl: Added primitive 170-172 to deal with fixed objects. * libgst/save.c: Always clear F_RUNTIME flags, not only when the endianness is wrong!!! This caused the GC to try to release the native code version of methods that had indeed been compiled when the image was saved, but were not compiled when GC was invoked. Also implemented saving F_FIXED objects. 2000-07-10 Paolo Bonzini * libgst/lib.c: Allow usage of Undeclared in the kernel's source 2000-07-04 Paolo Bonzini * libgst/heap.c: Support MAP_ANON and MAP_ANONYMOUS (thanks to John David Anglin) * libgst/oop.c: In gcFlip, modify numFreeOOPs so that allocOOPs allocates its OOPs merrily, even if we're below the low-water threshold. * libgst/oop.h: Defined LOW_WATER_OOP_THRESHOLD * libgst/oop.inl: In allocOOP, check low-water condition by looking at numFreeOOPs, not firstFreeOOP. 2000-07-02 Paolo Bonzini * libgst/gst.y: Add `oval' to the union, and define (and parse) SCALED_DECIMAL_LITERAL * libgst/lex.c: Parse ScaledDecimal literals * libgst/sym.c: Declared asScaledDecimalSymbol * libgst/sym.h: Defined asScaledDecimalSymbol * libgst/tree.c: Defined makeOOPConstant * libgst/tree.h: Declared makeOOPConstant 2000-07-01 Paolo Bonzini * libgst/interp.c: Don't overwrite the method cache until we are sure that the receiver understands the message (lookupMethod) * libgst/lib.c: Load AnsiDates.st and ScaledDec.st too * libgst/prims.inl: Handle case where the receiver is a `Float' but the argument is a `SmallInteger' directly in the 41-to-50 primitives. * libgst/xlat.c: Another fix to the strength-reduced division algorithm. If adjust is true, fixing the dividend if the signs mismatch produces an incorrect result. 2000-06-26 Paolo Bonzini * libgst/prims.inl: Restored divide-by-zero check in //, \\ and / (removed by mistake June 21st) * libgst/xlat.c: Removed interrupt check from the method prolog, moved it to the `return' bytecodes and to after a primitive; this fixed processes. Also INLINED_CONDITIONAL now adjusts the stack top in V2 and then resets spDelta instead of simply decrementing spDelta: this caused incorrect compilation of #ifTrue:ifFalse: if the receiver was inlined and the returned value was used as a parameter to a message. There are no regressions with respect to the bytecode interpreter now. 2000-06-21 Paolo Bonzini * libgst/comp.c: When compiling a #repeat loop, add a dummy `push nil' bytecode at the end to please the JIT compiler (which said its stack had underflowed -- it was right, but it was compiling unreachable code...). * libgst/interp.h: Made the primitiveTable `const' * libgst/interp-bc.inl: Use primitives for //, \\ and / if both arguments are integers * libgst/interp-jit.inl: First fixes to add processes to the JIT compiler * libgst/prims.inl: Fixed meaning of // and \\ for negative divisors; in primitive 90, use getReturnIP (defined in interp-jit.inl). * libgst/xlat.c: Fixed meaning of // and \\ for negative divisors; fixed overflow detection in multiplication; align interrupt checks to 4 bytes. 2000-06-18 Paolo Bonzini * libgst/dict.c: Added to SortedCollection two instance variables needed to be able to amortize sorting cost (through heaps & merging). 2000-06-17 Paolo Bonzini * libgst/xlat.c: Fixed doesNotUnderstand 2000-06-17 Paolo Bonzini *** Released versions 1.95 (development) and 1.7.5 (stable) 2000-06-10 Paolo Bonzini * libgst/byte.c: Fixed bug in optimizeByteCodes (|| was there instead of &&) which upset the JIT compiler * libgst/comp.c: If a method is a primitive return of a BlockClosure, initialize the BlockClosure in methodNew. * libgst/oop.c: Call releaseNativeCode instead of freeNativeCode in prepareForSweep, at the end call freeNativeCode * libgst/xlat.c: Removed definition of MethodEntry, renamed freeNativeCode to releaseNativeCode, added freeNativeCode * libgst/xlat.h: Added definition of MethodEntry, declared releaseNativeCode * libgst/interp.h: Declare validateMethodCacheEntries * libgst/interp-bc.inl: Added validateMethodCacheEntries (no-op) * libgst/interp-jit.inl: Added validateMethodCacheEntries 2000-06-07 Paolo Bonzini * libgst/interp.c: Fixed behavior of emptyContextStack with regard to the returnIP field. * libgst/interp-jit.inl: Don't look at the header flag in sendMessageInternal. * libgst/xlat.c: Added inlining of arithmetic operations. declared TREE_ALT_PUSH and implemented the gen_alt* functions. Still missing: processes, doesNotUnderstand: 2000-06-06 Paolo Bonzini * libgst/prims.inl: Use a huge table of functions instead of a huge switch statement * libgst/interp.h: Declare table of functions for the primitives * libgst/internal.h: Removed PTR_EXEC_PRIM_OP * libgst/interp-jit.inl: Same as above. * libgst/interp-bc.inl: Use primitiveTable instead of executePrimitiveOperation * libgst/xlat.c: Same as above. 2000-06-04 Paolo Bonzini * libgst/byte.c: New function computeStackPositions. * libgst/byte.h: Declared computeStackPositions. * libgst/xlat.c: Don't call prepareContext in the prologs if the method has no arguments and no temporaries. Plus, use computeStackPositions. 2000-06-03 Paolo Bonzini * libgst/xlat.c: Support #valueWithArguments: and other primitives (other than 81) which use sendBlockValue. Wrote the code for compiling deferred sends. Working inlined comparisons. * libgst/prims.inl: Added primitive 90 to retrieve the native code for a method. 2000-06-02 Paolo Bonzini * libgst/comp.c: If USE_JIT_TRANSLATION is defined, executeStatements skips some values which aren't mantained in that case. * libgst/xlat.c: Fixed error in pushing thisContext (wrong register used, R1 instead of V1). Fixed problems when the stack was empty in setTopNodeExtra. The method hash table was broken -- did not initialize current->receiverClass. Also check in the block's prolog, if code for the right CompiledBlock is being executed. * libgst/interp-jit.inl: Reset the exceptFlag after execution of JIT-compiled native code is interrupted. The interpreter is now able to create an image and then restore it. 2000-06-01 Paolo Bonzini * libgst/callin.c: Support losing systems which don't allow va_arg(..., char) * libgst/dld_beos.c: New file. 2000-05-29 Paolo Bonzini * libgst/xlat.c: Added some inlining (==, isNil, notNil, blockCopy:); modified suboperation codes so that `2' is reserved to literals (which aids a lot when inlining). Blocks done, they were easy. 2000-05-28 Paolo Bonzini * libgst/comp.c: Moved here a ChangeLog comment that actually described the code; gave a category to Behavior>>#methodsFor: * libgst/xlat.c: Usual tons of fixes. Crashes at initialize.st. Among others: - save the returnIP in the parent context, not in the newly created context (that is before activateNewContext rather than afterwards). - fixed the method prolog to update the `self' variable, which I had forgotten - labels did not work (had missed a *) - do EXPORT_SP_CODE in crucial points, including basic block boundaries * libgst/interp.c: New procedure showStackContents * libgst/interp.h: Declared showStackContents * libgst/prims.inl: Use showStackContents in the temporary definition of #error: and #doesNotUnderstand: (useful for debugging) 2000-05-24 Paolo Bonzini * lib/xlat.c: More tons of fixes. Crashes at Character.st * lib/xlat.h: Export returnFromNativeCode * lib/heap.c: Switched to Doug Lea's malloc (only an hour's effort!) * lib/interp.c: Fixed behavior of `execution environment' contexts with the JIT compiler. 2000-05-24 Paolo Bonzini * lib/xlat.c: Tons of fixes; renamed from lib/dynamic.c 2000-05-17 Paolo Bonzini * lib/gst.h: Added a couple of flags (F_XLAT_2NDCHANCE and F_XLAT_REACHABLE) for dealing with the changes to lib/oop.c. * lib/interp-jit.inl: Removed unwindContext and changeProcessContext, added getContextIP & setThisMethod * lib/interp-bc.inl: Moved unwindContext and changeProcessContext back to interp.c, added getContextIP * lib/interp.c: Restored unwindContext and changeProcessContext from interp-bc.inl, used getContextIP instead of toInt(...->ipOffset) * lib/oop.c: Implemented a `second chance' algorithm for disposing of methods whose native code translations are not referenced by any context. 2000-05-13 Paolo Bonzini * lib/alloc.c: Moved to lib-src * lib/alloc.h: Moved to lib-src * lib/alloca.c: Moved to lib-src * lib/getdtablesize.c: Moved to lib-src * lib/getpagesize.c: Moved to lib-src * lib/memmove.c: Moved to lib-src * lib/obstack.c: Moved to lib-src * lib/obstack.h: Moved to lib-src * lib/putenv.c: Moved to lib-src * lib/qsort.c: Moved to lib-src * lib/strdup.c: Moved to lib-src * lib/strerror.c: Moved to lib-src * lib/strtoul: Moved to lib-src * lib/usleep.c: Moved to lib-src * lib/waitpid.c: Moved to lib-src 2000-05-12 Paolo Bonzini * lib/heap.c: Derive baseaddr by trying to mmap a page, rather than blindly getting sbrk(0) 2000-05-09 Paolo Bonzini * lib/comp.c: Abort compilation if a method turns out to be too complex for the bytecode set (i.e. if it jumps too far). * lib/putenv.c: Strdup the added string 2000-05-04 *X*X* (aldomel@ix.netcom.com) * lib/sym.h: Added #include gst.h * lib/lib.c: Better error message when the Kernel files can't be found (image bootstrap failed). 2000-05-04 Paolo Bonzini *** Version 1.94.90 released 2000-05-02 Paolo Bonzini * lib/gst.y: Fixed errors in parsing #( () ) and #[]; the former was parsed to (Array with: nil), the last crashed (!) * lib/getpagesize.c: Created from part of sysdep.c * lib/getdtablesize.c: Created from part of sysdep.c * lib/usleep.c: Created from part of sysdep.c * lib/sysdep.c: Added code to set the `LANG' environment variable under Win32. 2000-04-27 Paolo Bonzini * lib/register.h: Issue the #warning only if using GCC Wed Apr 26 14:42.52 2000 Paolo Bonzini * lib/sysdep.h: Relinquish -> usleep, added getpagesize * lib/sysdep.c: Same as above * lib/prims.inl: Relinquish -> usleep 2000-04-23 Paolo Bonzini * lib/dict.c: Changed `length' variable to `size' in FileSegment 2000-04-12 Paolo Bonzini *** Version 1.7.4 released 2000-04-01 Paolo Bonzini * lib/oop.c: Completed switch to heaps, using heap_sbrk instead of heap_malloc and heap_realloc. Removed maxSpaceSize variable. * lib/save.c: Use memSpace.totalSize instead of maxSpaceSize. 2000-03-31 Hideoki Saito (saito@densan.co.jp) * lib/comp.h: Fixed bogus error on big-endian machines 2000-03-25 Paolo Bonzini * lib/byte.c: Added bytecode 134 (for lots of instance variables). * lib/byte.h: Added bytecode 134. * lib/comp.c: Added bytecode 134. * lib/dynamic.c: Added bytecode 134. * lib/interp-bc.inl: Added bytecode 134. 2000-03-24 Paolo Bonzini * lib/alloc.c: Removed code for the BSD memory allocator. * lib/heap.c: Added. * lib/heap.h: Added. * lib/oop.c: Use heaps to allow the OOP table to grow. 2000-03-23 Paolo Bonzini *** Version 1.7.3 released 2000-03-22 Paolo Bonzini * lib/gst.h: Added F_XLAT and F_RUNTIME * lib/save.c: Remove F_RUNTIME flags upon image load 2000-03-21 Paolo Bonzini * lib/comp.h: Include comp.inl * lib/comp.inl: Created * lib/dict.c: Added returnIP to ContextParts * lib/dynamic.c: All but blocks is in place... * lib/interp.c: Moved a few functions to interp-bc.inl * lib/interp.h: Added returnIP to ContextPart structs * lib/interp-bc.inl: (new name of bytecode.inl) moved here a few functions that are different for the bytecode and JIT interpreter (sendMessageInternal, unwindContext, changeProcessContext, ...) * lib/interp-jit.inl: Created * lib/sym.c: Added mustBeBooleanSymbol and badReturnErrorSymbol * lib/sym.h: Added mustBeBooleanSymbol and badReturnErrorSymbol 2000-03-16 Paolo Bonzini * lib/byte.h: Since I added atSignSymbol, I put atSignSpecial here. * lib/bytecode.inl: Since I added atSignSymbol, I use it instead of internString("@"). * lib/comp.c: Since I added atSignSymbol, I generate bytecode 187 even if it has little use... * lib/dynamic.c: Shape is getting clearer and clearer... * lib/sym.c: Added atSignSymbol (for JIT). * lib/sym.h: Added atSignSymbol (for JIT). 2000-03-11 Paolo Bonzini *** Version 1.7.2 released * lib/byte.c: IsPush -> isPushTable; added isSendTable * lib/byte.h: Added isPushByteCode & isSendByteCode * lib/dynamic.c: Began implementing new version * lib/dynamic.h: New version 2000-02-25 Paolo Bonzini * lib/lib.c: Use the Undeclared dictionary for files loaded from the command line too. 2000-02-24 Paolo Bonzini * lib/cint.c: Better output from badType. Plus, ByteArrays passed as Strings are considered null-terminated, and Strings passed as ByteArrays are not. * lib/interp.c: ShowBacktrace not static anymore. Fixed crash on sends to super from a block. * lib/interp.h: Declare showBacktrace. 2000-02-22 Paolo Bonzini *** Version 1.7.1 released 2000-02-22 Paolo Bonzini * lib/cint.c: Added defineCFuncs to test file accessing modes. 2000-02-21 Paolo Bonzini * lib/prims.inl: Added time-zone primitives for Time * lib/sysdep.c: Added currentTimeZoneName * lib/sysdep.h: Added currentTimeZoneName 2000-02-17 Paolo Bonzini * lib/bytecode.inl: Fixed crash on blocks returning from non-existent method contexts; fixed bug in detecting overflows on bit shifts. * lib/prims.inl: Fixed bug in detecting overflows on bit shifts. 2000-02-15 Paolo Bonzini *** Version 1.7 released 2000-02-06 Thorsten Klein * lib/dld_gst.c: Missing asterisk in `i' for loop (second expression was `i', now is `*i'). Caused SIGSEGV when a missing library name was passed. 2000-02-01 Paolo Bonzini * lib/byte.h: Subsumed bytecodes 132 and 134 (a whole byte for the argument count is way too much, and it does not matter if it's a bit slower because these bytecodes are rare indeed). * lib/byte.c: Print bytecode 132 according to the new coding * lib/bytecode.inl: Interpret new coding for bytecode 132 * lib/comp.c: Emit new coding for bytecode 132 2000-01-31 Paolo Bonzini *** Sixth beta of 1.7 (labeled 1.6.85) released 2000-01-31 Paolo Bonzini * lib/interp.c: Worked out bugs in call-ins that were added after the introduction of the `terminate interpreter' bytecode (Jan 8th) and which prevented Blox from working. prepareExecutionEnvironment was stacking a context with an OOP from the main OOP table over some lifoContexts. * lib/oop.c: Moved debug() to sysdep.c * lib/oop.h: Moved debug() to sysdep.h * lib/sysdep.c: Moved debug() here from oop.c * lib/sysdep.h: Moved debug() here from oop.h 2000-01-28 Paolo Bonzini * lib/comp.c: Fixed bug with double-freeing of block bytecodes (this is also due to a very permissive allocator) * lib/lex.c: Fixed bug in parsePrimitive (xfree without matching xmalloc) -- strangely enough, it didn't show up on all systems! * lib/prims.inl: Fixed Memory primitives to return and accept LargeIntegers for addresses when needed. 2000-01-24 Paolo Bonzini * lib/byte.c: Changed the clean block detection machinery to work with CompiledBlocks. Previously, we emitted a fixed sequence of bytecodes for blocks, then we made a pass on the bytecodes before optimization patching already generated code in case we found the block to be clean. Now, instead, we compute information on the block's cleanness before we create the CompiledBlock object, we embed the information in the CompiledBlock's header, and then use that information to directly emit optimized bytecodes in case the block is clean (instead of applying patches later). * lib/comp.c: Moved `class' and `selector' fields to MethodInfo. Blocks are compiled to CompiledBlocks. * lib/comp.h: Removed `class' and `selector' fields from [Compiled]Method * lib/dict.c: New definitions of MethodInfo, CompiledCode, CompiledMethod, CompiledBlock; declaration of compiledCodeClass and compiledBlockClass. * lib/dict.h: Declaration of compiledCodeClass and compiledBlockClass * lib/interp.c: Execute blocks from CompiledBlocks. * lib/lib.c: Load CompildCode.st and CompiledBlk.st * lib/prims.inl: Added primitive 68 to create CompiledBlocks. 2000-01-20 Paolo Bonzini * lib/byte.c: Fixed crash on methods whose last act was returning a clean block. It turned out that evaluating those blocks was GST's last act, either... * lib/cint.c: Enable passing 32-bit LargeIntegers in C call- outs. Looks like I had forgotten about it on Sep 10 1999. Also, introduced a `pVoidFunc' typedef to avoid Lisp-like abundance of parentheses when passing C function addresses. 2000-01-20 Paolo Bonzini * lib/bytecode.inl: IntegerClass -> smallIntegerClass * lib/dict.c: IntegerClass -> smallIntegerClass, plus added definition of SmallInteger * lib/dict.h: Added declaration of SmallInteger * lib/gst.h: IntegerClass -> smallIntegerClass * lib/interp.c: IntegerClass -> smallIntegerClass * lib/interp.inl: IntegerClass -> smallIntegerClass * lib/lib.c: Load SmallInt.st too. * lib/prims.inl: IntegerClass -> smallIntegerClass 2000-01-15 Paolo Bonzini * lib/comp.c: Adapted large integer compilation stuff in makeConstantOOP to compile ByteArrays too. * lib/gst.y: Added rules for ByteArray literals and arrays like #(1 2 3 #(4 5 6)) -- i.e. with the sharp inside the parentheses * lib/lex.c: Make parseNumber return BYTE_LITERAL for integers between 0 and 255 * lib/tree.c: Added makeByteArrayConstant 2000-01-09 Paolo Bonzini * lib/lex.c: CurStrBuf -> obstack_curStrBuf; plus, added the compilationObstack variable which is initialized in parseStream. * lib/lex.h: Added declaration of compilationObstack * lib/str.c: Added obstack_curStrBuf * lib/str.h: Declared obstack_curStrBuf * lib/tree.c: Heavily simplified destruction code by using obstacks * lib/lib.c: Solved SIGSEGV when gst.im was not in the current directory and SMALLTALK_IMAGE was not set. 2000-01-09 Paolo Bonzini * lib/comp.c: Added code to create Smalltalk LargeInteger objects from large integer ConstNodes in makeConstantOOP. * lib/gst.y: Handle large integer literals in the grammar * lib/lex.c: Added code to parse large integer literals * lib/tree.c: Added code to create large integer ConstNodes * lib/tree.h: Added declaration of the LargeInteger struct and of large integer ConstNodes 2000-01-08 Paolo Bonzini * lib/byte.h: Added `exitInterpreter' bytecode. * lib/comp.h: Declared `getTerminationMethod'. * lib/comp.c: Implemented `getTerminationMethod', and added code to installInitialMethods which installs a termination method which executes the new bytecode above. * lib/bytecode.inl: Implemented `exitInterpreter' bytecode. * lib/interp.c: Contexts created by prepareExecutionEnvironment no longer have to be special cased in unwindLastContext. * lib/sym.c: Added terminateSymbol. * lib/sym.h: Added terminateSymbol. 2000-01-02 Paolo Bonzini * lib/interp.c: Gst enters the new millennium!!! (yeah, I know it actually starts in 2001 but I don't want to wait another year... ;-) and it does by getting rid of the free lists for contexts -- it is faster to use the memory chunks like a stack. Also, I replaced tests for `isNil(thisContextOOP)' with tests for `!ip'. * lib/strerror.c: Added. * lib/sysdep.c: Win32 implementation of getMilliTime now more precise * lib/sysdep.h: Added macros for frexp and ldexp where they aren't available 1999-12-28 Paolo Bonzini *** Fifth beta of 1.7 (labeled 1.6.84) released * lib/byte.c: New functions checkKindOfBlock and patchCleanBlocks. * lib/byte.h: Declaration of patchCleanBlocks. 1999-12-27 Paolo Bonzini * lib/byte.c: New function fixupBlockClosures. * lib/comp.c: New way of compiling blocks. * lib/bytecode.inl: Bytecode 200 is now #blockCopy: (same as the Blue Book, but the primitive is implemented differently of course). * lib/prims.inl: New implementation of primitive 80 (blockCopy) * lib/sym.c: Removed #blockCopy:temporaries: (replaced with #blockCopy:), added machinery to reveal `clean' blocks * lib/sym.h: Removed #blockCopy:temporaries: (replaced with #blockCopy:) 1999-12-27 Paolo Bonzini * lib/dict.c: Added method to BlockClosure, changed to new context structure (methodClass/selector retrieved from the compiledMethod, method only there for MethodContexts) * lib/interp.c: Changed to new context and BlockClosure structure * lib/prims.inl: Changed to new BlockClosure structure 1999-12-26 Paolo Bonzini * lib/comp.c: Store the class and selector in the created CompiledMethods. A first step towards leaner context objects (i.e. more speed when sending messages!) and more powerful constructs such as `clean' block closures (which do not need to be created at run-time because are isolated from the outer contexts). * lib/comp.h: Added `class' and `selector' to struct Method. * lib/dict.c: Added `class' and `selector' to CompiledMethod. * lib/prims.inl: Pass class and selector to makeNewMethod. 1999-12-19 Paolo Bonzini * lib/bytecode.inl: Removed hasBlock (can be replaced with a test on whether the context lies in the main OOP table); this simplified both sends and returns. I also made the structure of method and block context objects more similar, resulting in simpler and faster code (except for block returns), and opening doors to optimizations such as delayed filling of the `method' and `receiver' slots of context objects. The overall improvement obtained since the Dec 17 change amounts to 9-10%. * lib/dict.c: Same as above * lib/interp.c: Same as above * lib/interp.h: Same as above * lib/prims.inl: Same as above 1999-12-17 Paolo Bonzini * lib/interp.c: Various changes, notably to getMethodContext and its users, to avoid using oopToObj more than once on the same object. 1999-12-17 Paolo Bonzini * lib/gst.h: Nil is now 0L (used to be 0), which is better when used as a pointer. * lib/interp.c: As long as we're sure that the execution order is LIFO (i.e. as long as no blocks are involved), allocate OOPs for the contexts outside of the main OOP table; this is because allocOOP is slower than picking a pre-built OOP out of a stack. This partly resembles the design of 1.1.5 (introduced Jan 1, 1991 and modified Oct 18, 1998), but has the advantage that when a BlockClosure is created we only have to allocate the OOPs that we tried to avoid -- 1.1.5 copied the whole objects to the main heap, causing way too many GCs. 1999-12-16 Paolo Bonzini * lib/gst.h: F_FAKE --> F_POOLED, isFake --> isPooled * lib/interp.h: ResetFakeContexts --> emptyContextsPool * lib/interp.c: (de)allocFakeContext --> (de)allocPoolContext, fakeList --> contextPool, plus changes above * lib/oop.c: RealizeOOPs --> sweepPooledObjects, plus changes above 1999-12-15 Paolo Bonzini * lib/sym.c: Modified hashString to reduce likeliness that hash be zero. 1999-12-14 Paolo Bonzini * lib/bytecode.inl: Use the new procedures below * lib/comp.c: Allocated one more bit for the method flags. If there is a primitive index, the flags are now 4 (used to be 0). * lib/interp.c: The old `returnWithValue' procedure was split in two, unwindToContext and unwindLastContext -- one is used upon an explicit `return from method', the other does less job and returns to the parent context upon a `return from context' 1999-12-11 Paolo Bonzini * lib/dict.c: Moved findClassMethod here from lib/dict.inl * lib/dict.h: Restored declaration of findClassMethod * lib/dict.inl: Moved findClassMethod here to lib/dict.c -- it is used rarely (only for method cache misses) and was bloating sendMessageInternal's code. * lib/bytecode.inl: Simple one-byte bytecodes prefetch the next address to jump to (hoping to save address generation interlocks) * lib/interp.c: Support for prefetching 1999-12-06 Paolo Bonzini * lib/bytecode.inl: Hard-code register allocation of ivar2 and tempOOP only where they are actually used * lib/dict.inl: Hard-coded register allocation in nilFill * lib/interp.c: Hard-coded register allocation now relies on register.h and is used in sendMessageInternal/sendBlockValue. * lib/register.h: Created 1999-12-05 Paolo Bonzini * lib/byte.c: ReturnMethodStackTop became returnContextStackTop in isSimpleReturn. * lib/cint.c: Declare the strerror C function. * lib/gst.h: ANSI asks for 65535 instance variables, so I shifted the instance specification's `number of instance vars' field right by three bits (now 262143 variables are possible). * lib/lex.c: Parse stuff like 1.0d53 and 1.0q212 correctly even though FloatD/FloatE/FloatQ is not supported yet. * lib/memzero.h: Removed a conditional by using LONG_SHIFT in the generic version of memzero. 1999-12-05 Paolo Bonzini * lib/bytecode.inl: The `hasBlock' instance variable in a context is now an integer (0 or 1). This eliminated several lookups for the `trueOOP' and `falseOOP' globals. * lib/interp.c: Same as above * lib/prims.inl: Same as above 1999-11-26 Paolo Bonzini *** Fourth beta of 1.7 (labeled 1.6.83) released * lib/bytecode.inl: Added caching of primitive numbers for sends of #at:, #at:put: and #size * lib/interp.c: Same as above * lib/prims.inl: Same as above 1999-11-22 Paolo Bonzini * lib/interp.c: Fixed floating-point exception on operations with infinity and NaN, under FreeBSD. 1999-11-21 Paolo Bonzini * lib/alloc.c: Use memzero instead of memset; also, xmalloc doesn't zero memory * lib/byte.c: Use memzero instead of memset * lib/dict.inl: Use memzero instead of memset * lib/dynamic.c: Use memzero instead of memset * lib/gst.h: Include memzero.h * lib/memzero.h: Added * lib/oop.c: Don't update numFreeOOPs on allocate/free oop. It is only used after a GC (to check whether the OOP table must be resized), so it is sufficient that it be correct after a GC. 1999-11-20 Paolo Bonzini * lib/dict.c: RestoreCFuncDescriptor was called at the wrong time in save.c -- before the xxxClass variables were loaded (Oct 20 change). So now it is called here. * lib/save.c: See above for lib/dict.c 1999-11-20 P. Lecoanet * lib/bytecode.inl: Special case #blockCopy:temporaries: for context objects and #value/#value: for BlockClosure objects. Also, no need to push and pop the object for the `return self/true/false/nil' bytecodes -- a simple assignment will do. 1999-11-19 Paolo Bonzini * lib/dict.c: Removed initNilVec and nilVec * lib/dict.inl: Implemented nilFill as an unrolled loop (memcpy is sloooow) * lib/interp.c: Arguments are moved between contexts with an unrolled loop (memcpy is sloooow); pushNNils now sets up the whole context stack (arguments+temporaries) and is called prepareContext. Another +10% for this on send-heavy benchmark!!! 1999-11-18 Paolo Bonzini * lib/byte.h: ReturnBlockStackTop became returnContextStackTop * lib/comp.c: Compile returns from methods as returnContextStackTop (should be a bit faster) * lib/bytecode.inl: `return self' and other similar bytecodes fall into returnContextStackTop, not returnMethodStackTop. 1999-11-18 Paolo Bonzini * lib/comp.c: Changed to account for removal of cacheHits and messagesSent. * lib/comp.h: Removed messagesSent. * lib/interp.c: Removed cacheHits and messagesSent, which can be deducted from other statistics. * lib/interp.h: Removed cacheHits. * lib/prims.inl: New implementation of mutation does not need primitive 263 (#specialBasicAt:). 1999-11-17 Paolo Bonzini * lib/dict.inl: Access functions test subscript bounds -- this eliminates an instanceSpec lookup. * lib/prims.inl: No need to call checkIndexableBoundsOf on access primitives (#at:*, #basicAt:*) * lib/gst.y: Support for the #(1 2 3 #a #b #'cdef' 45) syntax ^^ ^^ ^^^^^^^ 1999-11-14 Paolo Bonzini * lib/comp.c: `return instance variable' stores index in the `primitive' field of the method header (allows more optimizations and better register allocation in sendMessageInternal) * lib/comp.h: Move flag bits to high end of the methodHeader, so that there is place for two additional bits if needed * lib/dict.c: BlockContexts now hold the receiver and the BlockClosure instead of the number of arguments and temporaries. * lib/interp.c: Same as comp.c and dict.c above; plus, removed code for ACCESSOR_DEBUGGING. * lib/interp.h: Same as dict.c above 1999-11-13 Paolo Bonzini * lib/dict.c: NilVec contains now 128 OOPs * lib/dict.inl: NilVec contains now 128 OOPs * lib/interp.c: Doc fixes; cleaned up unused variables in the code handling fake contexts; finally, the method cache now includes the method header (+5/10% performance). 1999-11-11 Paolo Bonzini * lib/dynamic.c: Move method whose threaded code representation is requested to the head of the methodsTable. * lib/lex.c: USE_MONCONTROL only affects the interpreter, not the lexer. * lib/lib.c: Disable execution tracing options when the dynamic translator is being used. * lib/oop.c: Removed code for ACCESSOR_DEBUGGING, which I found more bug-prone than useful in more than a year; added lines explaining GC_TORTURE. * lib/oop.inl: Removed the few lines that implemented the ACCESSOR_DEBUGGING preprocessor symbol and explained what it was for. 1999-11-10 Paolo Bonzini * lib/bytecode.inl: In most bytecodes that are implemented with a switch statement, the switch statement is resolved at translation time. Also, added `default' clauses to such switch statements so that the compiler can produce better code. * lib/dynamic.c: Same as above * lib/dynamic.h: Same as above * lib/interp.c: Same as above * lib/gst.h: Removed declarations of TreeNode, thisClass and regressionTesting, which are already declared elsewhere (respectively in tree.h, comp.h and lib.h). Also removed declaration of Stream which is needed only in lex.c and is therefore moved there. * lib/lex.c: Moved declaration of Stream from gst.h 1999-11-09 Paolo Bonzini * lib/dynamic.c: Invalidating the macro opcode cache is now separated from invalidating the threaded code cache. Also, convert from threaded code ip to bytecode ip before invalidating the threaded code cache; reload the methodBase and the threaded ip after having invalidated it (in invalidateMethodCache). Everything works if no optimization options are set when compiling. 1999-11-09 Paolo Bonzini * lib/callin.c: SelectorNumArgs used; in addition, the result is checked to be the `nil' object in msgSendf is checked and, if so, 0 (or some variation of it, like 0.0 and NULL) is returned. * lib/interp.c: Added DEBUG_CODE_FLOW preprocessor symbol that prints every message that is sent in the same form used by backtraces (e.g. `Integer(Object)>>#retry:coercing:'). * lib/prims.inl: SelectorNumArgs used in implementation of #perform:... * lib/sym.c: Added selectorNumArgs * lib/sym.h: Added selectorNumArgs 1999-11-08 Paolo Bonzini * lib/byte.c: Fixed bug in makeDestinationTable that caused macro-opcode inlining to lose as soon as a jump was found. * lib/dynamic.c: Had mistyped an = for an == grrr... 2 days to find it! Now runs up to WeakObjects.st both with and without macro-opcode inlining, so macro opcodes should be reasonably bug-free (except for problems arising from inlining code optimized by GCC, which I have not tackled yet). 1999-11-06 Paolo Bonzini * lib/bytecode.inl: Jump bytecodes must be `PROTECT' bytecodes, isNil and notNil sends need not. Found two unused variables. * lib/cint.c: Moved `extern' declaration of enableGC into cint.h, the actual declaration of the variable came here from interp.c * lib/cint.h: Moved `extern' declaration of enableGC from cint.c * lib/interp.c: Moved getMethodLiterals to interp.inl and enableGC to cint.c * lib/interp.inl: Moved getMethodLiterals from interp.c 1999-11-05 Paolo Bonzini * lib/byte.c: Can print bytecodes without a vector of literals * lib/dynamic.c: Added debugging support; offsetToFill was not reset when a non-inlinable opcode was found (fixed by setting it in newOpcodeEntry) -- now runs up to the first jump bytecode (#initialize in Character.st), or up to MethodDict.st with macro-opcode inlining disabled. 1999-11-02 Paolo Bonzini * lib/dynamic.c: Work on the dynamic translator restarted. The first correct dynamically code was generated today: a small step for humanity, a big step for me (hmmm... maybe it was the other way round...) -- runs up to the first `inlined opcode-non inlined opcode- inlined opcode' pattern (line 1358 of Builtins.st) * lib/interp.c: Work on the dynamic translator restarted 1999-10-31 Paolo Bonzini * lib/comp.c: Fixed bug when compiling an integer constant that did not fit in the first 31 literals (`push instance variable[x]' was emitted instead of `push literal[x]') 1999-10-31 Paolo Bonzini *** Third beta of 1.7 (labeled 1.6.82) released 1999-10-30 Paolo Bonzini * lib/interp.c: A few bytecodes were still sending #booleanRequired instead of #mustBeBoolean (see May 3rd change). 1999-10-22 Paolo Bonzini * lib/save.c: Ensure that upon load the heap is at least 50% free. 1999-10-21 Paolo Bonzini * lib/dict.c: Added characterArrayClass * lib/dict.h: Added characterArrayClass * lib/lib.c: Added CharArray.st 1999-10-20 Paolo Bonzini * lib/dict.c: The new startup sequence (Oct 9) allowed to make the dictInit function (now called initNilVec) static. So that has been done since dictInit was just a hack: it initialized variables in dict.c like initDictionary, but while the latter is called from lib.c, dictInit had to be called from initOOPTable and loadFromFile). * lib/dict.h: Removed declaration of dictInit. * lib/oop.c: Removed call to dictInit. 1999-10-12 Paolo Bonzini * lib/dld_hpux.c: `return 0' was missing in gst_dld_init * lib/lib.c: Put the image in the local directory if the image directory is missing or not writeable. * lib/sysdep.c: Added fileIsWriteable, plus usage of time_t; strdup was erroneously declared in getFullFileName. 1999-10-11 Paolo Bonzini * lib/comp.c: Removed addForcedSelector (a copy of addForcedObject). Open coding of #whileTrue, #whileFalse, #repeat; removed open coding of #yourself. * lib/dict.c: Restored lookupKeyClass and its definition as I finally understood what it was meant to do; modified Association's definition (doesn't include key instance variable anymore). * lib/dict.h: Same as above 1999-10-10 Paolo Bonzini * lib/oop.c: Added reallocOOPTable. * lib/oop.inl: Call reallocOOPTable instead of exiting when ran out of OOP table slots. * lib/save.c: FixupObject, restoreObject, restoreInstanceVars accept an gst_object instead of an OOP; more coherent with their names and a bit more efficient too. Also moved updating of CFunctionDescriptors from restoreInstanceVars to fixupOOPInstanceVars (it is not needed when saving, only when loading, and was the only part of the code that required the parameters to be OOPs). * lib/save.h: FixupObject and restoreObject are now public. 1999-10-10 Paolo Bonzini * lib/gst.h: Define the `min' and `max' macros. * lib/lib.c: Used oopTableSize instead of OOP_TABLE_SIZE; use additional parameter to initOOPTable. * lib/oop.c: Added to initOOPTable a parameter to specify the table size; defined oopTableSize and used instead of OOP_TABLE_SIZE. * lib/oop.h: OOP_TABLE_SIZE became INITIAL_OOP_TABLE_SIZE; declared oopTableSize. * lib/oop.inl: Used oopTableSize instead of OOP_TABLE_SIZE * lib/prims.inl: Used oopTableSize instead of OOP_TABLE_SIZE * lib/save.c: Used oopTableSize instead of OOP_TABLE_SIZE; use additional parameter to initOOPTable. 1999-10-10 Paolo Bonzini * lib/oop.c: Moved builtin objects at the front of the oop table; this is a first step towards a variable-sized oop table (believe it or not, I did it in less than half an hour!!). * lib/oop.h: Same as above. * lib/oop.inl: Same as above. * lib/prims.inl: Same as above. * lib/save.c: Same as above. * lib/sym.c: Same as above. 1999-10-09 Paolo Bonzini *** Second beta of 1.7 (labeled 1.6.81) released * lib/bytecode.inl: Added a few experimental branch labels for the dynamic translator. * lib/prims.inl: Added primitive 90 to flush the dynamic translator's code cache. * lib/dict.c: Added code to reinitialize the global OOPs (which are not saved anymore so that the image is more compatible). Also, the OOP indices associated to Smalltalk, Processor and the SymbolTable are fixed so that we know them without storing them in the image file. Finally, declare the `Undeclared' dictionary in initSmalltalkDictionary(). * lib/oop.c: Removed markGlobalOOPs (instead, just mark the `Smalltalk' dictionary). * lib/save.c: Removed the global OOPs; they are reinitialized every time in dict.c. * lib/save.h: Removed the global OOPs * lib/sym.c: Added undeclaredSymbol, and used in findClassVariable. * lib/sym.h: Added undeclaredSymbol. 1999-10-07 Paolo Bonzini * lib/dict.c: Restored old MethodDictionary class (see March 29th, 1989 entry!) It was needed after all. * lib/dict.h: Same as above * lib/lib.c: Same as above * lib/save.c: Same as above * lib/sysdep.c: Fixed faked closePipe to return status of child process. 1999-10-02 Paolo Bonzini * lib/comp.c: Was trimming the last character of the method's source code in FileSegments. * lib/lex.c: Was trimming the last character of the method's source code when creating Strings from source code read from a file. * lib/lib.c: Added -K option, don't crash on -I/-L/-K without mandatory argument. 1999-09-26 Paolo Bonzini * lib/interp.c: InitProcessSystem removed the initial process from its own process list -- result: as soon as `Processor yield' was called, highestPriorityProcess did not know that the active process was active! * lib/prims.inl: Relinquish control to other processes on #yield. * lib/lib.c: `gst -a' caused a segmentation violation * lib/sysdep.h: Declaration of `relinquish'. * lib/sysdep.c: Implemented `relinquish'. 1999-09-25 Paolo Bonzini *** First beta of 1.7 (labeled 1.6.80) released * lib/bytecode.inl: Use areInts in open-coded operators. * lib/gst.h: Added areInts, removed F_FINALIZING. * lib/oop.c: Store objects to be finalized in a buffer, to avoid an OOP table scan. * lib/str.h: Added declaration of generic buffer functions * lib/str.c: Added generic buffer functions (not limited to chars) * lib/dld_aix.c: Added * lib/waitpid.c: Added * lib/strtoul.c: Added 1999-09-23 Paolo Bonzini * lib/dynamic.c: Created. * lib/dynamic.h: Created. * lib/obstack.c: Added, fixed to use _obstack_memcpy. * lib/obstack.h: Added. * lib/sysdep.h: Added flushCode. * lib/sysdep.c: Added flushCode & signalAfter implementation using fork()+getMilliTime(). 1999-09-19 Paolo Bonzini * lib/dict.c: Declare lookupTableClass * lib/dict.h: Declare lookupTableClass * lib/lib.c: Load LookupTbl.st and WeakObjects.st 1999-09-18 Paolo Bonzini * lib/gst.y: Include "lib.h", define YYPRINT * lib/lex.c: Define yyprint * lib/lex.h: Declare yyprint * lib/lib.h: Added declaration of "quietExecution", previously only in lib.c 1999-09-15 Paolo Bonzini * lib/cint.c: Added mkdir declaration. 1999-09-14 Paolo Bonzini * lib/dict.c: Added DefaultSortBlock to SortedCollection. * lib/lex.c: Fixed bug; 8-bit characters *outside* string literals crashed the lexer. * lib/sysdep.c: Use getcwd if HAVE_GETCWD (new symbol) is set and getwd otherwise. Old behavior was to use getcwd if HAVE_UNISTD_H was set and getwd if HAVE_GETWD was set 1999-09-13 Paolo Bonzini * lib/comp.c: Compile doits in UndefinedObject. 1999-09-12 Paolo Bonzini * lib/dict.c: Moved variables from ClassDescription; instanceVariables to Behavior; name/comment/category/environment to Class (they make no sense in Metaclass!). * lib/dict.h: Same as above. 1999-09-11 Paolo Bonzini * lib/comp.c: Changes for namespaces (execute doits in the current namespace). * lib/dict.c: Same as above (shared pool variable search algorithm, new `environment' variable, declaration of currentNamespace). * lib/dict.h: Same as above (added `environment' variable to ClassDescription, declaration of currentNamespace). * lib/dict.inl: Same as above (setClassEnvironment). * lib/prims.c: Same as above (primitive 250 to tell the compiler about the current namespace). * lib/save.c: Same as above (added uppercaseSuperSymbol, currentNamespace). * lib/sym.c: Same as above (shared pool variable search algorithm). * lib/sym.h: Same as above (added uppercaseSuperSymbol). 1999-09-10 Paolo Bonzini * lib/dict.c: VariableWordSubclasses use accessors for 32-bit integers. BlockClosures are now variableWordSubclasses since the previous encoding was incompatible with the code to switch the endianness in a saved image. * lib/dict.inl: Added accessors for 32-bit integers (64-bit on Alphas). * lib/gst.h: Added warning that says Alphas are not ok yet. * lib/gst.y: Shell was unusable after a parse error -- solved. * lib/interp.h: New encoding of BlockClosures (see above). * lib/prims.inl: C object and memory address primitives use the above accessors. 1999-09-08 Paolo Bonzini * lib/prims.inl: Flush the FileStream before reading its size. 1999-09-06 Paolo Bonzini * lib/dict.c: Added idleTasks variable to ProcessorScheduler. * lib/interp.h: Added idleTasks variable to ProcessorScheduler. * lib/lib.c: Allowed -- to stop option parsing, to comply with getopt. * lib/sysdep.c: Added POSIX interrupt handling (sigprocmask); Win32 code for alarms now uses kill(2) instead of manually calling the handler. 1999-09-02 Paolo Bonzini * lib/gst.y: Added support for [ :a :b || temp1 temp2 | ]. * lib/lex.c: UnreadChar not static anymore. Also removed scanStringoid and moved its code to stringLiteral. Parsing a comment does not actually require to store the whole comment in memory, so it is a conceptually different operation. Fixed for the change to str.c below. Removed memory leak in printToken (not so important since it's just debugging code, but it's a bug). * lib/lex.h: UnreadChar is now extern. * lib/lib.c: Removed references to resizeString. * lib/str.c: Removed resizeString, curStrBuf now returns a copy of the string (previously it was a chore left to its caller through strdup). 1999-08-31 Paolo Bonzini * lib/interp.c: Registers where the interpreter's ip and sp stay are hard-coded for most architectures. Added definitions for the high speed interpreter with dynamic translation. * lib/interp.inl: Moved internal accessors to interp.c; moved object equality and hashing functions to dict.inl (the only places where they were actually used). 1999-08-30 Paolo Bonzini * lib/bytecode.inl: Created from part of interp.c * lib/gst.h: Removed `extern' definition of the instruction pointer. * lib/interp.c: Made the instruction pointer static; prepared for the new bytecode.inl file; relativeByteIndex is replaced by currentBytecodeIndex; added definitions of the latter macro. * lib/interp.inl: Removed relativeByteIndex. * lib/prims.inl: RelativeByteIndex is replaced by currentBytecodeIndex. 1999-08-29 Paolo Bonzini *** Version 1.6.2 released. 1999-08-27 Paolo Bonzini * lib/cint.c: Always define DLD functions (at worst they're stubs) * lib/dld_none.c: Created. * lib/lib.c: Always load DLD.st (at worst it refers to C stubs) 1999-08-26 Paolo Bonzini * lib/dict.c: Put CDoubleMin and CDoubleMax in the Smalltalk dictionary. * lib/interp.c: NEXT_BYTECODE was not defined for old (switch statement) dispatching. 1999-08-08 Paolo Bonzini * lib/dict.c: In initRuntimeObjects, define the ImageFileName global as equal to binaryImageName. * lib/lib.c: Load .stpre only when creating local image files. Removed findImageFile. Option -v shows the hard-coded kernel and image paths. binaryImageName is not static anymore, defaultImageName is. * lib/lib.h: Removed findImageFile. binaryImageName is now declared here as an extern symbol, and defaultImageName is not. * lib/prims.inl: `Smalltalk snapshot' primitive (250) removed -- the new ImageFileName global makes it redundant. * lib/save.c: LoadFromFile now expects a full path to the image just like saveToFile, does not call findImageFile. 1999-08-07 Paolo Bonzini * lib/cint.c: Declare `unlink' (valid only for files) instead of `remove' (which nukes whole directories too) to be used to implement File class>>#primRemove: * lib/sysdep.c: Added simulation of popen and pclose in openPipe and closePipe. 1999-08-07 Paolo Bonzini * lib/dict.h: InitSTDIOObjects became initRuntimeObjects * lib/dict.c: InitSTDIOObjects became initRuntimeObjects, and various initializations (Features, KernelPath, ImagePath) were moved here from initSmalltalkDictionary. This completes the change made on July 14th. * lib/lib.c: InitSTDIOObjects became initRuntimeObjects 1999-08-06 Paolo Bonzini * lib/interp.inl: RelativeByteIndex now explicitly casts to int for Alpha compatibility. * lib/sym.c: Switched from int to long when dealing with differences between addresses, for Alpha compatibility. * lib/dict.c: Switched from int to long when dealing with differences between addresses, for Alpha compatibility. 1999-07-15 Paolo Bonzini * lib/dld_gnu.c: Added gst_dld_exts (.o, .a) * lib/dld_gst.h: Added gst_dld_exts * lib/dld_gst.c: Added gst_dld_openext * lib/dld_hpux.c: Added gst_dld_exts (.sl) * lib/dld_ltdl.c: Added gst_dld_exts (dummy) * lib/dld_libdl.c: Added gst_dld_exts (.so, .a) * lib/dld_win32.c: Added gst_dld_exts (.dll, .exe) 1999-07-14 Paolo Bonzini * lib/gst.h: Added F_BYTE, used while saving to ease reloading if the endianness changes. * lib/save.c: Added ability to load images from machines with different endianness and to recognize (and reject) images from machines with different sizeof(long). This change unveiled a bug in GNU C 2.7.2!!! * lib/dld_ltdl.c: Created (thanks to Alexander Shinn for pointing me to libtool!) 1999-07-10 Paolo Bonzini * lib/interp.c: InterruptHandler should set again the handler for SIGINT * lib/sysdep.c: Fixed syntax error. Also, sigaction should use SA_RESETHAND if available because signal is supposed to work that way. * lib/sysdep.c: #define SIGALRM if not provided by C headers. 1999-07-05 Paolo Bonzini * gstconf.h.in: Changed USE_READLINE to HAVE_READLINE (more coherent) * gstconf.h: Same as above * lib/comp.c: Same as above * lib/lex.c: Same as above * lib/lex.h: Same as above * lib/lib.c: Same as above 1999-07-04 Paolo Bonzini * lib/sysdep.c: Renamed dprintf to debugf. glibc 2.0 defines a different prototype for a function with the same name (glibc 2.1 only defines it if __USE_GNU is defined and does not break gst). 1999-06-28 Paolo Bonzini * lib/qsort.c: Added standard stuff to make alloca work. * lib/gstpub.h: Moved inclusion of gst.h *inside* `extern "C"' 1999-06-25 Paolo Bonzini *** Bug-fixing version 1.6.1 released. 1999-06-21 Paolo Bonzini * lib/alloc.c: In xrealloc, we must call malloc explicitly when the first argument is 0, since some reallocs don't do this. * lib/cint.c: Fix for Solaris' brokenness (in their stat.h, they use `#define st_atime st_atim.tv_sec') * lib/qsort.c: Added (from GCC). 1999-06-17 Mark Elbrecht *** Version 1.6 released. * lib/lex.c: Fix crash when using drive letters in isKernelFile. * lib/lib.c: For DOS, use '_stinit' and '_stpre' as init files since DOS doesn't allow a period to start a filename. 1999-06-09 Pahi Andras * lib/cint.c: DefineCFunc makes a private copy with strdup of the C function's name. The problem is likely to root to the pre-DLD days (1989-1990) when only string constants were passed to defineCFunc, so strdup was unnecessary. 1999-06-03 Paolo Bonzini * lib/comp.c: Added displayCompilationTrace * lib/comp.h: Added declaration of displayCompilationTrace * lib/prims.inl: If declaration tracing is on, shows new categories as encountered. 1999-05-30 Paolo Bonzini * lib/gst.h: Added default values for the definitions that used to be in gstpaths.h * lib/gstpaths.h: Removed since configure did not create it properly after the installer was fixed * lib/Makefile.in: Added definitions to be used in place of gstpaths.h * lib/lib.c: If the the paths cannot be located, try using the local directory * lib/lib.h: DefaultImageName is now a variable * lib/str.c: Added resizeString 1999-05-28 Paolo Bonzini * lib/cint.c: Object passed as `unknown' or `self', whose class is not recognized, are now passed as an OOP (they used to be skipped). * lib/interp.c: the open-coded // was rounding like quo: Does. * lib/prims.inl: The base date for secondClock was 2 Jan 2000 instead of 1 Jan 2000. This was apparent after the fix above. 1999-05-20 Paolo Bonzini * lib/alloc.c: Moved platform-dependent definitions here. Modified so that, if we replace libc's allocator, we define calloc too (see glibc's manual). Also modified so that xmalloc exits if it fails. * lib/alloc.h: Removed platform-dependent definitions. Now this file only contains extern declarations (correctly). 1999-05-15 Paolo Bonzini * lib/gst.h: Added code to #define `volatile' to nothing if it is not supported. * lib/interp.c: Modified to pass through -Wall when optimization is on. This highlighted a possible (although never observed) bug in sendMessageInternal: the setjmp/longjmps in executePrimitiveOperation could have clobbered methodOOP, which is now declared volatile. 1999-05-14 Paolo Bonzini * lib/byte.c: Modified to (almost) pass through -Wall. * lib/cint.c: Modified to pass through -Wall. * lib/comp.c: Modified to pass through -Wall. * lib/dict.c: Modified to pass through -Wall. * lib/dict.inl: Modified to pass through -Wall. * lib/gstpub.h: Added C++ `extern "C"' guard. * lib/interp.c: Modified to pass through -Wall. * lib/interp.inl: Modified to pass through -Wall. * lib/lex.c: Modified to pass through -Wall. * lib/oop.c: Modified to pass through -Wall. * lib/save.c: Modified to pass through -Wall. * lib/sym.c: Modified to pass through -Wall. 1999-05-13 Paolo Bonzini * lib/callin.c: Added objectAlloc. * lib/gst.h: Added guards to avoid including heavily implementation dependent stuff when gst.h is included by gstpub.h * lib/gstpub.h: Changed to use those guards. * lib/dld_hpux.c: Created. * lib/dld_libdl.c: New name of dld_sun.c * lib/lex.c: Stream description for readline streams is not `a Readline string' anymore, but `stdin' (since that's where we actually get the string). Also, when readline is used I also include now; and I disable readline's auto- completion feature, not supported by gst (initializeReadline). 1999-05-11 Paolo Bonzini * lib/comp.c: Various performance counters are now unsigned longs. * lib/comp.h: Various performance counters are now unsigned longs. * lib/interp.c: #mustBeBoolean is now sent to the object that should have been a Boolean, as the Blue Book says. Plus, same as above. * lib/interp.h: Various performance counters are now unsigned longs. 1999-05-09 Paolo Bonzini * lib/id.c: Removed -- I'm very sorry to do it, since it was created 10 1/2 years ago, but it was a copy of str.c * lib/id.h: Removed -- I'm very sorry to do it, since it was created 10 1/2 years ago, but it was a copy of str.h * lib/lex.c: Removed references to function that used to be in poor id.c; changed references to copyStr to use strdup. * lib/prims.inl: Added code to test for infinity, NaNs and other failures in mathematical functions (exp/ln/sqrt/trigonometry). * lib/str.c: Removed copyStr. * lib/sysdep.h: Added portable macros to test for nan and infinity. Not all libc's have isnan, isinfinity and the like. 1999-05-08 Paolo Bonzini * lib/comp.c: fixed bug when compiling to:do:/to:by:do: And the loop index temporary was in position 15 (a 2-byte push was erroneously compiled, since a 1-byte push can be used). * lib/interp.c: Did not trap divides by zero on open-coded // messages. * lib/lib.c: Added Transcript.st to the list of kernel files. * lib/oop.c: Character objects' objSize field was uninitialized. Fixed. * lib/prims.inl: fixed SIGSEGV on (IndexableClass new: ANegativeNumber). 1999-05-06 Paolo Bonzini * lib/dict.c: Added exceptionHandlers variable to Process. * lib/gst.y: Fixed bug with conditional compilation -- conditional exclusion was not disabled by the double bang sequence. * lib/interp.h: Added exceptionHandlers variable to Process. 1999-05-03 Paolo Bonzini * lib/interp.c: Changed the system message #booleanRequired to #mustBeBoolean for coherence with the Blue Book (I had not noted that passage). Fixed async signals (actually, I just removed the error messages -- they seem to work as they are and their implementation is exactly the same as in the book...) and changed the signal handling routines to use them instead of separate variables. Added asyncSignal(). * lib/interp.h: Added declarations for asyncSignal(). * lib/interp.inl: Fixed unparenthesized arguments in the `equal' macro. * lib/gstpub.h: Added declarations for asyncSignal(). * lib/lib.c: Search for a local copy of the kernel files in the `kernel' subdirectory of the local directory; always save the kernel sources as FileSegments. This way, GNU Smalltalk works both if a) it is installed and the kernel lies in /usr/local/share b) it is not installed and everything is done inside the user's home directory c) it is not installed, we are under Windows and everything is done inside the current directory (maybe I'll switch to the executable directory in the future...) 1999-04-29 Paolo Bonzini * lib/comp.c: Now does compile correctly optimized selectors whose block arguments have arguments or temporaries. In fact I simply don't optimize them -- but maybe I will sooner or later. Also, #timesRepeat:, #to:do: and #to:by:do: are now open-coded. Finally, I fixed the fact that the bytecodes for an erroneous method were put at the beginning of the next syntactically valid method. * lib/lib.c: The `Smalltalk Ready' banner is now `GNU Smalltalk Ready'. * lib/save.c: Added timesRepeatColonSymbol, toColonDoColonSymbol and toColonByColonDoColonSymbol. * lib/sym.c: Same as above. * lib/sym.h: Same as above. 1999-04-27 Paolo Bonzini *** Version 1.5.beta3 released. * lib/alloc.c: Added inclusion of stdlib.h (or malloc.h for old C's) when the custom allocator is not used. * lib/byte.c: Fixed optimization of pushIndexed. * lib/dld_sun.c: Added missing semicolon. * lib/interp.c: Finished new GCC implementation at last -- now we only have to do a single goto for EVERY bytecode. Maybe something better could be done by caching dispatchVec in a register... Auto- matic #undef-ining of USE_OLD_DISPATCH is now based on the new gstconf.h definition HAVE_GOTO_VOID_P (used to simply check __GNUC__). 1999-04-25 Paolo Bonzini * lib/byte.c: Added optimization of nopBytecode. Added `replace stack top' bytecodes 140-142 in optimizeBasicBlock. * lib/byte.h: Added `replace stack top' bytecodes. * lib/comp.c: Added yourselfSymbol in whichBuiltinSelector (yourself is now open-coded). * lib/interp.c: Added `replace stack top' bytecodes. * lib/prims.inl: Changed GC-tuning primitives (spaceGrowRate and growThreshold) to accept integers too. * lib/sym.h: Added yourselfSymbol. * lib/sym.c: Added yourselfSymbol. * lib/save.c: Added yourselfSymbol. 1999-04-23 Paolo Bonzini * lib/gst.h: Cleaned up some definitions for ANSI features which can be checked by autoconf -- the old #ifdef method only makes things cumbersome. Also renamed config.h to gstconf.h, so that it can be installed without filename clashes. * lib/interp.c: Changed verbose execution tracing to print the stack top *BEFORE* the bytecode -- the output is easier to follow. Added jump lookahead (see definition of JUMP_LOOKAHEAD). * lib/oop.c: Began switching to something resembling a generational collector. Changed GC-tuning variables (spaceGrowRate/growThreshold) to be integers -- because they are now checked in allocObj and doubles are more expensive in busy code, I think. 1999-04-22 Paolo Bonzini * lib/byte.h: Merged bytecodes 138-139 (push/store outer temp) into a single bytecode 138, which can also do a `pop and store outer temp'. * lib/byte.c: Same as above. The new bytecode behaves much like bytecode 126, so the code for that bytecode in the optimizer can be used by the new bytecode too. Added more cases in the peephole optimizer. * lib/comp.c: Same as above. * lib/interp.c: Same as above. Moved various optimization #define's at the top of the file. 1999-04-20 Paolo Bonzini * lib/byte.c: Optimizer in and working. Fixed challenging cases in the flow analyzer which were apparent now because the peephole optimizer does some `interesting' changes to the bytecode -- previously the changes were not `interesting' enough for these bugs to show up. Performance +5-10%, but some interesting optimizations are not there yet (e.g. pop-store/push --> store, and push/push --> dup). 1999-04-19 Paolo Bonzini * lib/byte.c: Added to the flow analysis some support for optimizing #ifTrue: and #ifFalse: in the common case where their result is discarded. Added a first peephole optimizer in optimizeBasicBlock. * lib/byte.h: Added nop bytecode 139 * lib/comp.c: Changed the compilatation of #ifTrue:/#ifFalse: to one which is more optimizable if the result is discarded. #and:/#or: are left as they were because their result is usually kept. Also ALWAYS put a pop bytecode at the end of a statement -- it makes flow analysis simpler and is removed by the peephole optimizer if unnecessary. * lib/interp.c: Added nop bytecode 139 1999-04-18 Paolo Bonzini * lib/byte.c: The new optimization scheme proved to be easily extendable (which is what I wanted). I added jump optimization (10 lines of code) and unreachable code elimination (5 lines) -- no big speed improvements, but now I have moer experience with optimization and will approach peepholing. * lib/byte.c: Modified various internal functions to avoid continuous reallocation of bytecodes. For instance, reallocByteCodes uses xrealloc() -- it was always malloc-ing everything from scratch -- and allocByteCodes and reallocByteCodes have a parameter with the amount of memory to be allocated. * lib/cint.c: Call initDldLib if HAVE_DLD is defined. 1999-04-16 Paolo Bonzini * lib/dld_gst.c: Created from old cxtnsn/dld.c * lib/dld_gst.h: Created * lib/dld_gnu.c: Created * lib/dld_sun.c: Created * lib/dld_win32.c: Created * lib/byte.c: Changed the algorithm for optimizeByteCodes. Instead of doing a single scan on the bytecodes and fixing up jumps the hard way, I'm now dividing the bytecodes into basic blocks, optimizing each of them one at a time in optimizeBasicBlock. * lib/dict.c: Moved hasBlock to ContextPart, yanked it out from BlockContext and MethodContext. * lib/interp.c: Moved hasBlock to the fourth position (inside MethodContexts and BlockContexts) so that we can put it in ContextPart. * lib/lib.c: Load DLD.st from kernel if HAVE_DLD is defined. 1999-04-12 Paolo Bonzini * lib/sysdep.c: Functions handling time_t's now use signed longs. * lib/sysdep.c: Stole more portable implementations of adjustTimeZone and currentTimeZoneBias from GNU Emacs. Added support for broken versions of localTime(3) that cache the time zone. * lib/sysdep.h: Functions handling time_t's now use signed longs. 1999-04-10 Paolo Bonzini *** Version 1.5.beta2 released. * lib/cint.c: My_stat now adjusts file times to local times. * lib/sysdep.c: Added adjustTimeZone and currentTimeZoneBias. * lib/sysdep.h: Added adjustTimeZone and currentTimeZoneBias. 1999-04-09 Paolo Bonzini * lib/cint.c: Fixed my_stat to return times relative to 1/1/2000 to avoid possible overflows (which would have happened around 2004 on 32-bit machine, and around 8.000.000.000 AD on 64-bit ones...). 1999-04-08 Paolo Bonzini * lib/interp.c: Fixed bug in sendMessageInternal and sendBlockValue. Basically, we now make sure that sp and thisContext->spOffset are consistent whenever a GC could happen; otherwise, fixupObjectPointers recomputes thisContext->spOffset from sp, storing an erroneous value into the former. 1999-03-29 Paolo Bonzini * lib/gst.h: Added definition of WIN32 because Cygwin only defines _WIN32, but many programs rely on WIN32 instead. 1999-03-22 Paolo Bonzini * lib/sysdep.c: Fixed Win32 version of Delays, which was buggy if a delay had to cancel the previous one. The new version is also much more precise. 1999-03-21 Paolo Bonzini * lib/interp.c: Changed Integer relational operators to not do a toInt() (instead we use a simple typecast). 1999-03-15 Paolo Bonzini *** Version 1.5.beta1 released. * lib/dict.c: Changed to use setCObjectValueObj and cObjectValueObj. * lib/dict.h: Doc fixes for CObject. * lib/dict.inl: Added setCObjectValueObj and cObjectValueObj. Now, the address pointed by the CObject is the LAST instance variable (including indexed ones), not always the SECOND (which could still be a fixed one). For currently defined CObject subclasses this was not a problem, but it could have been a serious one if a CObject subclass declared additional instance variables. * lib/prims.inl: Changed to use setCObjectValueObj and cObjectValueObj. 1999-03-13 Paolo Bonzini * lib/cint.c: Was crashing if a call-out to a non-existent function was attempted. * lib/comp.c: Fixed a strange bug I'm not sure I understood well. It seems that, if an error occurred in a method with literals, and if an immediately following method had literals, the literal array contained bogus data and GST would lose. I don't think it was there before my March 3rd change... 1999-03-11 Paolo Bonzini * lib/lib.c: Added --silent as a synonim of --quiet and -q. 1999-03-03 Paolo Bonzini * lib/comp.c: Added stack depth tracing (variables and macros containing stackDepth). Made makeNewMethod public, to avoid lots of duplicate code for the C and Smalltalk compiler. * lib/prims.inl: Added primitive 79, which maps to makeNewMethod. * lib/interp.c: Added support for mixed size contexts. Added resetFakeContexts. * lib/interp.c: The change above unveiled lots of bugs - especially uninitialized pointers here and there. In particular: a) GST would core dump when you did a send to super from a class without a superclass; b) prepareExecutionEnvironment set the stack pointer of the context to 0 instead of -1 so markAnOOPInternal would try to mark an additional stack slot. * lib/oop.c: In minorGCFlip, call resetFakeContexts at the end instead of using deallocFakeContext for every context. 1999-02-28 Paolo Bonzini * lib/comp.c: Modified compileAssignments to use preferrably the `storeIndexed' bytecode. This is faster and also makes the task of an eventual bytecode optimizer a bit simpler. * lib/byte.c: Added truncateByteCodes. Moved optimizeByteCodes here and made it extern (it was a static in lib/comp.c), and added it some (working but currently not used) code. * lib/byte.h: Added optimizeByteCodes and truncateByteCodes 1999-02-27 Paolo Bonzini * lib/prims.inl: Added primitive 101 (ProcessorScheduler>> isTimeoutProgrammed). * lib/dict.c: Added DelayProcess and IdleProcess as Delay's class variables * lib/interp.c: In initProcessSystem, leave the processes the way they were unless we get here after a deadlock. 1999-02-26 Paolo Bonzini * lib/interp.c: Changes to have an error-free compile with -pedantic. Also fixed highestPriorityProcess to return the active process if it is not waiting on a semaphore (because `Processor yield' must not stop execution if the only runnable process is the active one). * lib/lex.c: Added support for -s command line option in isKernelFile. * lib/lib.c: Added -s command line option. * lib/oop.c: Removed arithmetics on void * in realizeOOPs. 1999-02-23 Paolo Bonzini * lib/gst.y: Added #'abcd' symbols (not in Smalltalk-80, but ANSI and common in many commercial Smalltalk implementations). 1999-02-22 Paolo Bonzini * lib/lib.c: Moved some initializations *after* parsing the command line (obviously *before* loading user files), so that parameters on the cmdline can influence the initialization process. 1999-02-21 Paolo Bonzini * lib/interp.c: Added printing of what is the erroneous method in sendMessageInternal. Also renamed global SP/IP to outerSP and outerIP (which are then #defined to ip and sp in gst.h), so that there is no name collision between the local IP/SP and the global ones; and eliminating ipAddr/spAddr we get some more speed. But remember this when using GDB!! 1999-02-18 Paolo Bonzini * lib/interp.c: Struggled to make the process system work as intended; it still has a few bugs but it mostly works (for example, philosophers now work). 1999-02-16 Paolo Bonzini * lib/oop.c: Started switching to generational GC!! In short, minor GCs only take care of fake contexts and are faster because no sweeping happens; major GCs don't bother of fake contexts (they assume there are none) and deal with removing real unused objects. 1999-02-15 Paolo Bonzini * lib/byte.h: Added bigLiteral bytecode. * lib/comp.c: Changed so that methods are normal objects - no more variable classes and variable byte classes at the same time. Now, the header does not include the number of literals, so I also added code to use the new 126 bytecode. * lib/interp.c: Changed so that methods are normal objects - no more variable classes and variable byte classes at the same time. * lib/interp.inl: Changed so that methods are normal objects - no more variable classes and variable byte classes at the same time. * lib/prims.inl: Now methods are normal objects - no more variable classes and variable byte classes at the same time. So I removed primitives 68/69/79. * lib/save.c: Changed so that methods are normal objects - no more variable classes and variable byte classes at the same time. 1999-02-14 Paolo Bonzini * lib/oop.c: Experimentally moved markGlobalOOPs at the START of the marking phase, so that by the time the other objects in the root set are dealt with, many objects will have been marked. This might improve a bit GC locality of reference. * lib/save.c: Experimentally reorganized the global OOPs. smalltalkDictionary and the symbols at the END of the global OOP table, so that by the time they are marked other objects will have been dealt with and recursion will be more shallow; this might improve a bit GC locality of reference. 1999-02-13 Paolo Bonzini * lib/sysdep.c: Using setSignalHandler() inside signalAfter(). 1999-02-12 Paolo Bonzini * lib/sysdep.c: GetCurDirName, now performs special error handling when getcwd is used (code stolen from the gettext library's source code, by David MacKenzie). 1999-02-09 Paolo Bonzini * lib/gst.h: Moved incubator here from oop.h so that it is public * lib/oop.h: Moved incubator to gst.h so that it is public (see comment in GST 1.1.5 - "it is likely that this interface will be moved..." 1999-02-08 Paolo Bonzini * lib/byte.c: Print new bytecode 126 for many literals, > 64. * lib/cint.c: Removed code to print "function not registered" message - Smalltalk code handles that now. * lib/lib.c: CFuncs.st is now loaded *after* CObject and CType - a logical choice since C function declarations could use CTypes. Added PkgLoader. 1999-02-06 Paolo Bonzini * lib/prims.inl: Sped up nextInstance by avoiding to search in the unused OOPs. 1999-02-05 Paolo Bonzini * lib/interp.c: Added callbacks #booleanRequired and #interrupt. Implemented bytecode 126 for many literals, > 64. * lib/prims.inl: Primitive 255 now does not blindly set inCCode to false if a C callout made a callin which in turn made a callout. 1999-02-04 Paolo Bonzini * lib/lex.c: Modified so that a bang is not part of a binary op. It's just a one-char token like [ and #. Needs fixing, though. 1999-02-03 Paolo Bonzini * lib/callin.c: Changed calls to yyparse() to parseStream(). * lib/comp.c: Changed calls to yyparse() to parseStream(). * lib/interp.c: Changed calls to yyparse() to parseStream(). * lib/gst.y: More attempts at simplifying things around: now an expression invoking methodsFor: can be as complex as desired. In addition I changed temporaries and primitive to have a default value, so that almost-duplicated rules (e.g. `statements', `temporaries primitive statements', `temporaries statements', `temporaries primitive') can be put into a single one. Alas this causes 4 shift/reduce conflicts (2 in state 0, 2 in state 6) but Bison gracefully handles them and it makes the grammar more readable IMO. * lib/lex.c: Moved lex debugging here. In addition, now you can compile this with NO_PARSE so that no parsing occurs - only lexical analysis. To accomplish this, the callers need to call a function in lib/lex.c (parseStream) instead of yyparse(). * lib/lib.c: Updated lex debugging and moved it to lex.c 1999-02-02 Paolo Bonzini * lib/alloc.c: Added custom allocator, currently used only under Win32. See comment in the file. * lib/alloc.h: Added custom allocator, currently used only under Win32. See comment in the file. * lib/sym.c: internCountedString: The symbol OOP is now read only. 1999-02-01 Paolo Bonzini * lib/oop.c: Fix in growMemory. Now it seems to work right - previously, it failed if thisContext was not a fake and the heap moved. 1999-01-29 Paolo Bonzini * lib/byte.c: Modified isSimpleReturn so that a "return literal[0]" method is optimized. * lib/comp.c: Modified isSimpleReturn (in byte.c) so that a "return literal[0]" method is optimized. The "primitive must be executed" case, which was previously identified by flags == 3, is now identified by primitiveIndex != 0. 1999-01-28 Paolo Bonzini * lib/comp.c: Moved regressionTesting to lib.c; it seems more logical to me. * lib/gst.h: fix in incrInt/decrInt: It was not converting the OOP to a long before adding 2 - so it was actually adding sizeof(OOP)*2 = 16! * lib/lib.c: To make -S work when -i was specified too. * lib/oop.c: NilOOP, trueOOP and falseOOP are now initialized in allocOOPTable(), not initOOPTable(). Actually I can't guess why they weren't there in the first place. * lib/prims.inl: Added check for already closed file in fileOp: (if fileStream->file = nilOOP, fail). Added flushPrim and getBytePrim. * lib/save.c: Removed experimentally the code that saves and restores nil, true, false and the characters: why can't we initialize them just like if we were initializing the system from scratch, without an image? * lib/sysdep.c: OpenFile, removed references to BINARY_MODE_NEEDED (I had to remove it from the configure script because it did not work correctly, at least under Cygnus' Win32 port. 1999-01-27 Paolo Bonzini * lib/dict.c: Smalltalk dictionary is now created with a larger size than it used to be (see the definition of INITIAL_SMALLTALK_SIZE). * lib/interp.c: Made the method cache an array of a struct instead of five different arrays. A "return literal" method is optimized like "return self" and "return inst. var". 1999-01-26 Paolo Bonzini * lib/comp.c: Removed code for evaluating (parse last statement as return) - not needed since Smalltalk code implements evaluate: Also changed references to findVariable to prevent assignments into arguments. * lib/gst.y: Removed code to parse last statement as return - not needed since Smalltalk code implements evaluate: * lib/lex.c: Modified to have a variable indicating the name of the log file. * lib/lib.c: Changed -v to exit after the output, like --version. Added -l and -L to log to a file. Added long options. * lib/sym.c: Modified findVariable and localVarIndex so that assignments to arguments are detected. 1999-01-25 Paolo Bonzini * lib/dict.inl: Spiffed it up with a few register clauses. Also removed modulus operator (%) when possible. This increased performance (especially in message sends) only by 5%, but it was so easy I could not but do it! 1999-01-24 Paolo Bonzini * lib/alloc.c: Added this banner. * lib/alloc.h: Created. * lib/lex.c: Fixed lineStamp() so that the format is consistent with GCC and other GNU programs: for example, "Integer.st:115: parse error") 1999-01-22 Paolo Bonzini * lib/gst.h: Moved SIG_ARG_TYPE from sysdep.c here. Added paranoic checking of memset arguments when bzero is used. * lib/interp.c: Moved SIG_ARG_TYPE to gst.h * lib/sysdep.c: Moved SIG_ARG_TYPE to gst.h 1999-01-18 Paolo Bonzini * lib/interp.inl: Fixed bug in large integers. I was not considering that the product of the low-order 15 bits could exceed 15 bits! 1999-01-16 Paolo Bonzini * lib/dict.h: Added byteStreamClass. * lib/interp.c: Yesterday I removed maxSize instance variable from WriteStream, so I had to remove it from the FileStream struct, either. * lib/lib.c: Added ByteStream.st. * lib/save.c: Added byteStreamClass. 1999-01-15 Paolo Bonzini * lib/dict.c: Removed maxSize instance variable from WriteStream. Fixed missing isPipe parameter in addSTDIOObject. Added ByteStream. Added CShortSize global. 1999-01-13 Paolo Bonzini * lib/cint.c: Added getArgc and getArgv * lib/lib.c: Added ability to get argc/argv from Smalltalk code. * lib/sysdep.c: Fixed a small & invisible error, a 'start of comment' misplaced for a 'end of comment' (note by Paolo Bonzini : congratulations for your sharp eye!!) 1999-01-11 Paolo Bonzini * lib/dict.c: Yeah! Removed bitfields from InstanceSpec!! * lib/dict.h: Yeah! Removed bitfields from InstanceSpec!! * lib/dict.inl: Yeah! Removed bitfields from InstanceSpec!! * lib/gst.h: Yeah! Removed bitfields from InstanceSpec!! * lib/prims.inl: Yeah! Removed bitfields from InstanceSpec!! 1999-01-10 Paolo Bonzini * lib/interp.c: Good!! First change in 1999!! Optimized out send to super. I renamed sendMessage to sendMessageInternal and created two macros (sendMessage and sendToSuper) in interp.inl * lib/interp.h: Good!! First change in 1999!! Optimized out send to super. I renamed sendMessage to sendMessageInternal and created two macros (sendMessage and sendToSuper) in interp.inl * lib/interp.inl: Good!! First change in 1999!! Optimized out send to super. I renamed sendMessage to sendMessageInternal in interp.c and created two macros (sendMessage and sendToSuper) here. 1998-12-09 Paolo Bonzini * lib/cint.c: Added my_stat for portability * lib/oop.c: Moved the code to nil out weak references *before* sweeping is done. This is needed so that finalize methods which refer to weak objects already see nils. 1998-12-03 Paolo Bonzini * lib/prims.inl: Added ability to create subclasses of CompiledMethod (for now, cannot add instance variables) 1998-11-28 Paolo Bonzini * lib/comp.c: The method cache was not properly updated: test is 1 to: 5 do: [ :i | Object compile: 'foo ^', i printString. (nil foo) printNl] Now I'm using invalidateMethodCache instead of updateMethodCache (see interp.c). * lib/interp.c: fix: Since updateMethodCache did not always work I replaced it with invalidateMethodCache, which is not as gentle but works (anyway compiles are not so frequent and it takes nothing to rebuild a good cache). Also, thisContext's ip and sp (in sendMessage and sendBlockValue) are now updated *after* thisContextOOP is set to the newly created context. The previous implementation caused mess if allocFakeContext() triggered a GC. 1998-11-27 Paolo Bonzini * lib/dict.c: Added the Table class variable to Character. * lib/gst.h: Added finalization. * lib/oop.c: Added finalization. Also added lastUsedOOP which is used to shorten the loops on the OOP table at GC time It was needed because the OOP table was scanned three times: once to mark dependents of finalizable objects, once to reverse pointers (prepareForSweep), once to scan for objects to be finalized. Now the whole GC is on average 50% faster than it used to be BEFORE having to add all these cycles. * lib/oop.inl: Created * lib/prims.inl: Added finalization primitives 256-257 * lib/sym.c: Added finalizeSymbol. * lib/sym.h: Added finalizeSymbol 1998-11-26 Paolo Bonzini * lib/interp.inl: Created 1998-11-25 Paolo Bonzini * lib/dict.c: Moved many routines to dict.inl for speed. Changed BlockClosure to a byte-subclass to save eight bytes. * lib/dict.h: Moved most things to gst.h, added dict.inl * lib/dict.inl: Created * lib/interp.c: Added primitive 104 (String hash function), inlined many things around. * lib/oop.c: Changed the way the marking system works. Instead of two entry points (markAnOOP and markOOPRange) both relying on markAnOOPInternal and passing parameters to it through the copy stack, I have two macros (maybeMarkOOP and markOOPRange) which pass parameters to markAnOOPInternal through function arguments. markAnOOPInternal does its job calling itself recursively, doing everything on the stack without expensive mallocs. This makes the code neater, since the whole marking system resides in a single function. * lib/prims.inl: Created from interp.c * lib/sym.c: Modified hashString to be more effective. 1998-11-24 Paolo Bonzini * lib/lib.c: Added ContextPart.st, changed to try loading .stinit and .stpre from the current directory if the HOME environment variable is not found (fix for Win32). 1998-11-11 Paolo Bonzini * lib/interp.c: Fixed bug in asObject primitive. Was erroneously using oopAt(arg1-1) instead of oopAt(arg1). 1998-11-10 Paolo Bonzini * lib/lex.c: Fixed so that _ *inside* an identifier is OK. 1998-11-08 Paolo Bonzini * lib/byte.c: Added notNilSymbol and isNilSymbol. * lib/byte.h: Added notNilSymbol and isNilSymbol * lib/interp.c: Fixed bugs in returnWithValue (they had been there since 18 Oct...): contexts were returned to the free fake list even if they were not fake anymore (which happened if you did a snapshot). Sooner or later, a normal object contended the same heap space with these contexts, wreaking havoc on the image. Also turned noParentContext to a macro and added notNil/isNil as bytecodes 206 and 207; these are optimized out to gain speed in some operations (e.g. Sets and Dictionaries). * lib/save.c: Added notNilSymbol and isNilSymbol * lib/sym.c: Added notNilSymbol and isNilSymbol. * lib/sym.h: Added notNilSymbol and isNilSymbol 1998-11-01 Paolo Bonzini * lib/callin.c: Added vmsgSend. Moved mstMalloc and mstGetCData here. 1998-10-26 Paolo Bonzini * lib/gstpub.h: Added vmsgSend. 1998-10-18 Paolo Bonzini * lib/interp.c: Changed fake OOPs so that they have entries in the real OOP table. This allows me to never realize the fake contexts unless a snapshot is being done. Less GC = more speed!! * lib/oop.c: Fake OOPs are now in the main OOP table. Changed setOOPObject to a macro for SPEED!! * lib/oop.h: Added freeOOP(), realizeAllOOPs() 1998-10-16 Paolo Bonzini * lib/cint.c: Added stringOut return type (frees string) 1998-10-15 Paolo Bonzini * lib/interp.c: Added type 9 for CObjects and Memory (smalltalk OOP) 1998-10-12 Paolo Bonzini * lib/dict.c: Added BlockClosure. Changed BlockContext to reflect new architecture. Changed Float to a variable byte class. * lib/interp.c: Added support for blocks as closures (partly I wrote it, part I stole it from Steve Byrne 's never made public 1.1.6 version). Started adding support for fake block contexts (see 1 Jan 91) 1998-10-10 Paolo Bonzini * lib/interp.c: Added support for read-only objects (prims 233-234) 1998-09-26 Paolo Bonzini * lib/dict.c: Fixed allocCObject. Added IdentitySet. 1998-09-25 Paolo Bonzini * lib/interp.c: Added a few register clauses. Also changed implementation of "send ==" so it doesn't actually do the message sends, since == should not be overridden. * lib/lib.c: Added ValueAdapt.st, File.st, Directory.st, IdentitySet.st * lib/oop.c: Added a free list to OOP table. This yielded, in general, good performance boosts, up to ten-fold for snippets that heavily allocate objects!! (on average, the number of bytecodes per second doubled) * lib/oop.h: Added refreshOOPFreeList(), to be used by save.c 1998-09-18 Paolo Bonzini * lib/gst.h: Started adding support for read-only objects. * lib/interp.c: Removed last vestiges of previous garbage collectors. Removing loops that were not optimized out by compilers caused a 30% performance increase (not joking!). Y2K change... Time>>secondClock was about to overflow. Also fixed sendBlockValue to check argument count. * lib/oop.c: Removed all vestiges of previous GC algorithms. This was a pity because it was really instructive but I was not able to read anything before ;-). * lib/oop.h: Fixed incubator bug (incAddOOP not in braces), removed maybeMoveOOP and localMaybeMoveOOP. 1998-09-10 Paolo Bonzini * lib/dict.c: Added LargeIntegers and Fractions. Tried to make nilFill faster. * lib/lib.c: Added LargeInteger.st, removed changes.st since its changes are incorporated in Fraction.st 1998-09-09 Paolo Bonzini * lib/interp.c: Started adding support for LargeIntegers!!! 1998-09-07 Paolo Bonzini * lib/interp.c: Added Behavior>>#flushCache (primitive 89, as in the Blue Book). Added bounds checking to spaceGrowRate: (between 0 and 500) 1998-09-06 Paolo Bonzini * lib/interp.c: FileStream>>nextPutAll: Primitive was giving access violations (!) if Integers were passed... definitely too greedy! I've updated the Smalltalk code too, so that it handles the case, but anyway now the primitive fails. On 3 Sep 98 I had broken Floats; fixed. 1998-09-03 Paolo Bonzini * lib/dict.c: Added extensions to Date, modified Collection and SequenceableCollection so they are not indexable. Removed LookupKey. * lib/interp.c: Switched to openFile; corrected bug in floating point arithmetic primitives which never failed. basicPrint doesn't output new-line. Also corrected so that, when aborting execution, dead contexts are ignored and don't cause "Block returning to non-existent method context" errors. * lib/lib.c: Modified to use openFile, added a few loaded modules. 1998-09-02 Paolo Bonzini *** Began development of version 1.6 * lib/save.c: Switched to using openFile to open files * lib/sysdep.c: Added openFile, support for Cygnus Win32 added. A note on this is important. Reluctantly I used Win32 functions here and there. I was not happy about that, but since it's the only way to do some things in an environment that does not fully comply to POSIX, I had to. 1995-12-16 Steve Byrne * lib/comp.c: Changed name to blockCopyColonTemporariesColonSymbol. * lib/sym.c: Changed name to blockCopyColonTemporariesColonSymbol. * lib/sym.h: Changed name to blockCopyColonTemporariesColonSymbol. 1995-11-04 Steve Byrne * lib/oop.c: Fixed allocObj to have what I think is the *right* algorithm -- simple, grows when needed. 1995-11-02 Steve Byrne * lib/oop.c: Fixed allocObj to properly grow when not enough space is required, and to terminate if the allocation cannot succeed. 1995-10-15 Steve Byrne * lib/byte.h: Added pushOuterTempVariable and storeOuterTempVariable byte codes. * lib/sym.c: Converted to the new architecture; introduced the notion of scopes. * lib/sym.h: Converted to new architecture; introduced the notion of scopes. 1995-10-14 Steve Byrne * lib/gst.y: Began adding block temporary syntax. * lib/tree.c: Added support for block node type for new architecture. * lib/tree.h: Added block node type for new architecture support. 1995-09-30 Steve Byrne *** Version 1.1.5 released. 1995-09-16 Steve Byrne * lib/interp.c: Moved lots of system dependent functions out to sysdep. * lib/sysdep.h: Added openPipe, closePipe, getOpenFileSize. 1995-09-10 Steve Byrne * lib/interp.c: Switched to fileIsReadable sysdep routine. * lib/lib.c: Added -g command line flag to suppress printing of GC messages. * lib/oop.c: Added GC torture test. Heh heh heh! * lib/sym.c: Added incubator usage. * lib/sysdep.c: Added fileIsReadable, also setSignalHandler, and initSysdep. 1995-09-09 Steve Byrne * lib/callin.c: Added incubator usage. * lib/cint.c: Added incubator support for created objects. * lib/cint.c: Removed Sun Windows hacks from the file. * lib/interp.c: Added code to use the object incubator support. * lib/interp.c: Experimentally tried to next jmp_bufs so enable proper handling of reentering the interpreter from C callout code and then calling out to more C code. 1995-09-08 Steve Byrne * lib/dict.c: Added incubator support for newly created objects. 1995-09-07 Steve Byrne * lib/comp.c: Added usage of OOP incubator. * lib/oop.c: Added incubator support. * lib/oop.h: Added incubator support. 1995-08-30 Steve Byrne * lib/gst.h: Merged in Visual C++ changes. * lib/oop.c: Merged NT changes back in. Code now contains some unnecessary casting and unrolled expressions (*= becomes = *) to shut the Visual C++ compiler's warnings off. 1995-08-26 Steve Byrne * lib/comp.c: Merged Brad Diller's changes for dealing with parsing specially in the browser. * lib/dict.c: Added kernel and image file paths as Smalltalk accessible variables. * lib/lib.h: Added kernelFileDefaultPath and imageFileDefaultPath as exported symbols. * lib/sysdep.c: Fixed to have the __cursigmask definition be conditional on HAVE_SIGHOLD. 1995-08-20 Steve Byrne * lib/oop.c: Added growMemoryTo(); it's a variant of growTo which does not involve the garbage collector. * lib/oop.c: Fixed alignSize to not double align (we don't preserve that property during GC anymore anyway, and the floating point accessing functions in dict.c which were the initial reason for having it are now sensitive to whether aligned access to doubles is required by the hardware or not. * lib/oop.h: Added growMemoryTo(). * lib/save.c: Switched to using growMemoryTo in loadFromFile so that if the saved image space is larger than the normal memory space, the space is grown to fit. 1995-07-26 Steve Byrne * lib/cint.c: Fixed the makeDescriptor function to issue an error if it cannot find a named C function. Already located some bugs in UnixStream.st which have been there since it's inception. 1995-07-23 Steve Byrne * lib/comp.c: Removed apostrophes in comments -- OS/2 doesnt like them (incredible!). * lib/dict.c: Added CIntSize so that C struct can understand int size. * lib/gst.h: Removed mstconfig.h!!! Code is now not conditional on the presence of config.h. * lib/interp.c: Merged in OS/2 diffs, and removed apostrophes from preprocessed-out code (OS/2's preprocessor doesn't understand backslash quoting. * lib/oop.c: Fixed #ifdefed out code to not have apostrophes (OS/2 doesn't understand). * lib/save.c: Removed extra stdio.h include 1995-07-13 Steve Byrne * lib/comp.c: Removed HAVE_ALLOCA_H. * lib/save.c: Removed HAVE_ALLOCA_H include of alloca.h (done in gst.h now). * lib/sym.c: Removed HAVE_ALLOCA_H. 1995-07-11 Steve Byrne * lib/cint.c: Added John Stanhope (jehu@vt.edu)'s changes for Objective-C calling (Thanks John!!!) * lib/gstpub.h: Added defineCFunc. * lib/save.c: Added John Stanhope (jehu@vt.edu)'s changes for Objective-C calling (Thanks John!!!) * lib/sym.c: Added John Stanhope (jehu@vt.edu)'s changes for Objective-C calling (Thanks John!!!) * lib/sym.h: Added John Stanhope (jehu@vt.edu)'s changes for Objective-C calling (Thanks John!!!) 1995-07-09 Steve Byrne * lib/byte.c: Fixed to include proper headers. * lib/callin.c: Fixed to include correct header files. * lib/comp.c: Fixed to include proper headers and have explicit declarations. * lib/dict.c: Fixed to explictly declare functions and include proper files. * lib/interp.c: Fixed to have explicit function declarations and correct include files. * lib/lex.c: Fixed to include proper headers and have functions declared explictly. * lib/oop.h: Added lots of new externs. * lib/save.c: Fixed to have proper inclues and explicit function declarations. * lib/tree.c: Fixed to include correct files. 1995-07-08 Steve Byrne * lib/lib.c: Fixed a bunch of declarations and includes so that functions are now explictly declared always. 1995-06-29 Steve Byrne * lib/sym.c: Fixed pool dictionary allocation to not allocate a large number of immediately thrown away arrays. 1995-06-26 Steve Byrne * lib/gst.h: Switched EMPTY_BYTES to be 8 byte into the word instead of the low bytes to make the low bytes unused for use with the mark/sweep GC. 1995-06-23 Steve Byrne * lib/cint.h: Switched guard prefix to GST * lib/comp.h: Switched to GST guard prefix * lib/dict.h: Switched to GST guard prefix * lib/gst.h: Switched to GST header guard. * lib/gstpaths.h: Switched to GST header guard prefix. * lib/gstpub.h: Switched to GST header guard prefix. * lib/id.h: Switched to GST header guard prefix. * lib/interp.h: Switched to GST header guard prefix. * lib/lex.h: Switched to GST header guard prefix. * lib/lib.h: Switched to GST header guard prefix. * lib/oop.h: Switched to GST header guard prefix. * lib/save.h: Switched to GST header guard prefix. * lib/str.h: Switched to GST header guard prefix. * lib/sym.h: Switched to GST header guard prefix. * lib/sysdep.h: Switched to GST header guard prefix. * lib/tree.h: Switched to GST header guard prefix. 1995-06-15 Brad Diller * lib/comp.c: Modified executeStatements() to support browser expression evaluation. Added getByteCodeForSpecialSelector() to support some browser operations. * lib/comp.c: Store in memory the source code derived from .st files loaded outside the kernel directory. * lib/comp.h: Added getByteCodeForSpecialSelector() to support some browser operations. * lib/lex.c: Added isKernelFile() and getMethodSourceFromCurFile(). These routines were provided to solve certain data integrity problem caused by accessing the source code indirectly from saved file information. * lib/lex.h: Added isKernelFile() and getMethodSourceFromCurFile(). 1995-06-09 Steve Byrne * lib/oop.c: Began switching to compacting mark & sweep gc. * lib/oop.h: Began the conversion to single GC space. 1995-06-06 Steve Byrne * lib/byte.c: Switched to new file naming scheme. * lib/callin.c: Switched to new file naming scheme. * lib/cfuncs.c: Switched to new file naming scheme. * lib/cint.c: Switched to new file naming scheme. * lib/comp.c: Switched to new naming scheme. * lib/comp.h: Switched to new file naming scheme. * lib/dict.c: Switched to new file naming scheme. * lib/gstpub.h: Switched to new file naming scheme. * lib/id.c: Switched to new file naming scheme. * lib/interp.c: Switched to new file naming scheme. * lib/lex.c: Switched to new file naming scheme. * lib/lib.c: Switched to new naming scheme. * lib/lib.h: Switched to new file naming scheme. * lib/oop.c: Switched to new file naming scheme. * lib/save.c: Switched to new file naming scheme. * lib/str.c: Switched to new file naming scheme. * lib/sym.c: Switched to new file naming scheme. * lib/sysdep.c: Switched to new file naming scheme. * lib/tree.c: Switched to new file naming scheme. 1995-06-05 Steve Byrne * lib/mstpub.h: Merged in Brad Diller's changes. 1995-05-31 Steve Byrne * lib/mstcint.c: Fixed cFuncInfo to grow dynamically. * lib/mst.h: Boolean replaced with mst_Boolean, objectClass => mst_objectClass, Object => gst_object. This thanks to the foresightful guys at the X consortium. Thanks guys for wantonly chewing up name space. * lib/mst.h: Removed the old sysVersionMajor etc definitions -- they are now defined in configure.in. 1995-05-30 Steve Byrne * lib/mstcomp.c: Replaced objectClass with mst_objectClass. Boolean => mst_Boolean. * lib/mstcomp.h: Boolean switched to mst_Boolean. * lib/mstdict.c: Replaced objectClass with mst_objectClass to avoid conflicts with X (grrr!). Boolean replaced with mst_Boolean. Object replaced with gst_object. * lib/mstdict.h: Replaced objectClass with mst_objectClass to avoid conflicts with X. Boolean => mst_Boolean. Object => gst_object. * lib/mstinterp.c: Replaced objectClass with mst_objectClass. Boolean => mst_Boolean. * lib/mstinterp.h: Boolean => mst_Boolean. * lib/mstlex.c: Boolean => mst_Boolean. * lib/mstlex.h: Boolean => mst_Boolean (darn X!). * lib/mstlib.c: Boolean => mst_Boolean. * lib/mstlib.h: Boolean renamed to mst_Boolean. * lib/mstoop.c: Boolean => mst_Boolean. * lib/mstoop.h: Boolean => mst_Boolean. Object => gst_object. * lib/mstsave.c: Boolean => mst_Boolean. Object => gst_object. * lib/mstsave.h: Boolean => mst_Boolean. * lib/mstsym.c: Boolean => mst_Boolean. * lib/msttree.h: Boolean => mst_Boolean. 1995-05-28 Steve Byrne * lib/mstdict.c: Finally hacked floatNew to deal properly on architectures where double alignment requirements are different from those of long. * lib/mstsysdep.c: Added getdtablesize for those systems such as HP which do not have this useful function. * lib/mstsysdep.c: Fixed getCurDirName to selectively use getwd or getcwd depending on what is supported. 1995-05-15 Brad Diller * lib/mstinterp.c: Added primitives 256-264 to support expression evaluation and other functions for the class browser. 1995-05-07 Steve Byrne * lib/mstdict.c: Added more machine specific datatype constants (size and alignment). * lib/msttree.h: Removed trailing comma from NodeType enum literals list -- some compilers are picky. 1995-04-29 Steve Byrne * lib/mstdict.c: Added CDoubleAlignment as a 'global' value for the required alignment of C type 'double'. * lib/mstlib.c: Moved CType to after CObject in the load order to better reflect the type (and symbol definition) dependencies. 1995-03-31 Steve Byrne * lib/mstcomp.c: Compiler now uses the initEmptyBytes macro to set the empty bytes of the byte code length of a method. * lib/mst.h: Adjusted EMPTY_BYTES related constants to vary with hardware architecture. * lib/mstinterp.c: Fixed branching backward to use signed arithmetic it was doing the computation as unsigned ints without sign extension when it was added ot a 64 bit pointer. * lib/mstoop.c: Added fflush(stdout) to some debugging funcs * lib/mstsym.c: Adjusted a reference to the empty bytes to use the new, architecture independent macro definitions. 1995-03-19 Brad Diller * lib/mstcint.c: Conditionally enable GC of Smalltalk objects referenced in callouts. 1995-03-15 Brad Diller * lib/mstdict.c: Added mstMalloc mstGetCData. 1995-03-01 Steve Byrne * lib/mstcomp.c: Fixed makeConstantOOP to handle NIL which is passed in from empty array literals. 1995-01-21 Steve Byrne * lib/mstlex.c: Some changes for architectural independence (64 bit). 1995-01-20 Steve Byrne * lib/mstdict.h: Added 64 bit support. * lib/mst.h: More changes for DEC Alpha 64bit architecture. * lib/mstinterp.c: Adjusted for DEC Alpha 64bit architecture. * lib/mstinterp.h: Added padding for 64bit architectures. 1995-01-14 Steve Byrne * cxtnsn/dld.c: Changed the name from DLD to USE_DLD to avoid conflicts with symbols defined by the DLD package in the future. 1995-01-05 Steve Byrne * lib/mstinterp.c: Fixed a bug when copying a fake method context (ip wasn't being updated, and so was pointing to dead storage). 1995-01-02 Steve Byrne * lib/mstdict.c: Fixed CType to use the new type model. * lib/mstdict.h: Switched to the new CType model. * lib/mstinterp.c: Removed primitives 147 & 148 -- they were obsolete anyway, and now with the new CType model they no longer function. 1994-12-03 Steve Byrne * lib/mstinterp.c: Added code stubs for asCData: Primitives. 1994-11-16 Steve Byrne * lib/mstinterp.c: Finally tracked down some problems with prims 183-185 -- they were using the wrong variable to access the contents of the cobject, and it was just luck that it worked on Linux. 1994-10-08 Steve Byrne * lib/mstcomp.c: Fixed some bugs related to getting a GC during compilation (literals during compilation are part of the root set, etc.). * lib/mstinterp.c: Added SystemDictionary>>growTo: And moved a few builtins around. * lib/mstsym.c: Fixed the internCountedString bug by deferring OOP allocation until all instances have ben allocated. 1994-10-02 Steve Byrne * lib/mstoop.c: Made sure to turn off the free bit in moveOOP (no sense in moving an object that's freed, and moveOOP will not be called on a truly freed object; this change "repairs the damage" in cases where there is an accidental freeing occurring. * lib/mstsym.c: Fixed a bug in internCountedString that occurs other places where there is the possibility of doing a garbage collection just after a newly allocated object which has not been added to a root-set-reachable object. The GC sees that there are no references to the new object, and marks its oop free and does not copy the just allocated object into the new current semispace. This problem can occur anywhere these conditions occur. Given that allocOOP moves the object to the current space if it's not already there, for this case to really occur, you have to have done the allocOOP before you call the second instantiate or other allocation primitive. 1994-09-20 Steve Byrne * lib/mstinterp.c: Added empty statement to the tail of a case statement. 1994-09-15 Steve Byrne *** Version 1.2.alpha1 released. 1994-09-04 Steve Byrne * lib/mstcomp.c: Fixed some of the printing at the end of executeStatements to avoid dividing by zero. * lib/mstdict.c: Switched out last bzero call. * lib/mst.h: More changes -- removed some old bcopy macro definitions, and switched more towards the autoconf based implementation. 1994-09-03 Steve Byrne * lib/cfuncs.c: Created. * lib/cfuncs.c: This is the first file in the distribution to not start with "mst". This is the precursor to having short file names so that primitive operating systems can deal with an advanced system like Smalltalk :-) :-) :-). * lib/mstcint.c: Factored out initUserCFuncs to enable easier extension by developers. * lib/mstcint.c: Yanked out DLD -- it's now in the parent directory. * lib/mst.h: Switched double size out, switched to use RETSIGTYPE, and WORDS_BIGENDIAN. * lib/mst.h: Switched to having version defines coming from the config.h file, and added the edit prefix string. 1994-08-31 Steve Byrne * lib/mst.h: Began switching to autoconf based approach. 1994-08-24 Steve Byrne * lib/mst.h: Added symbolic constants for max and min integer values representable in a Smalltalk Integer object. * lib/mstinterp.c: Fixed Float>>truncated to do range checking and fail if converting a number that is outside the range of integers. 1994-08-21 Steve Byrne * lib/mstcomp.h: Switched to using low bit int marking. * lib/mstdict.h: Switched to low order bit for int flagging. * lib/mst.h: Switched to low order bit for int flagging. 1994-07-10 Steve Byrne * lib/mstlex.c: Reinstated the use of changes (it was dyked out) as an optional mechanism. 1994-07-09 Steve Byrne * lib/mstdict.c: Fixed findKey to check all elements even when the dictionary is full. Previously it would check all but the last one, which caused some bizarre compilation behavior (the last class declared didn't seem to be there as far as the compiler was concerned). 1994-06-22 Steve Byrne * lib/mstcint.c: Added support for cObjectPtr type, to allow for passing CObject parameters by reference. It is up to the client to ensure that the passed CObject type corresponds to the desired C datatype. 1994-06-20 Steve Byrne * lib/mstcint.c: Fixed stringInfo to be local to the call stack, instead of using a static, to allow recursive invocations. 1994-06-11 Steve Byrne * lib/mstinterp.c: Added new-style CObject accessors functions, currently in the range 182 -- 189. * lib/mstsym.c: Added cObjectPtrSymbol for new call by value parameter passing mode. * lib/mstsym.h: Added cObjectPtrSymbol. 1994-04-30 Steve Byrne * lib/mstinterp.c: Added CPtr incrBy: 1994-03-19 Steve Byrne * lib/mstcallin.c: Added %t and %T for more direct control over types. Also, added typeNameToOOP for mapping string type names to actual CType subclass instances. 1993-10-16 Steve Byrne * lib/mstinterp.h: Changed to have 9 priority levels, as part of the fix for ProcessorScheduler>>yield. 1993-10-10 Steve Byrne * lib/mstinterp.c: Doing some experimental hacks on the process system to try to recover from the case where there are no runnable processes. * lib/mstinterp.h: Fixed definition of initProcessSystem. 1993-04-04 Steve Byrne * lib/mstdict.c: Made printAssociationKey more bullet-proof when passed a non-association. 1992-11-22 Steve Byrne * lib/mstdict.c: Added isPipe member to FileStream. * lib/mstinterp.c: Fixed FileStream to have a buffer instance variable, and added knowledge of whether the file stream was a regular file or a pipe, so FileStream>>close could do the right thing. 1992-07-18 Steve Byrne * lib/mstdict.c: Added byteArrayNew. * lib/mstdict.c: Added countedStringNew. 1992-07-16 Steve Byrne * lib/mstdict.c: Added freeCObject. 1992-05-25 Steve Byrne * lib/mstdict.c: Added support for Emacs caching class names. * lib/mstinterp.c: Made system interruptable when non-interactive (interrupts work, that is). 1992-02-23 Steve Byrne * lib/mstcint.c: Added support for reading and writing scalar types. 1992-01-01 Steve Byrne * lib/mstcallin.c: Fixed to auto-initialize Smalltalk when the public routines are invoked. * lib/mstpub.h: Created. * lib/mstlib.c: Converted to be callable as a library. * lib/mstlib.h: Renamed from mstmain.h * main.c: Created from old mstmain.c (now mstlib.c) 1991-12-31 Steve Byrne * mstcallin.c: Created. * mstcallin.h: Created. * mstlex.c: Began adding support for having a changes file and pointing methods to that instead of the actual source file (which can get out of sync, and cause recompiles to lose). * mstoop.c: Added registered oops to root set. * mstoop.c: OopTable now allocated from memory instead of being stored as part of the executable. 1991-12-29 Steve Byrne * mstlex.c: Added support for readline's conditional .inputrc definitions, keyed off of "Smalltalk". 1991-12-22 P. Lecoanet * mstbyte.c: Fixed byteCodeLength failing to return 0 1991-12-08 Steve Byrne * mstoop.c: Changed oopValid to only check the FREE bit, instead of worrying about the even odd flags, which may not be valid. 1991-11-29 Steve Byrne * mstlex.c: Added fileNameOOP to hold full path name for files, so that all methods share the same file name string. Also, adjusted getCurFileName to return the full path name. 1991-11-28 Steve Byrne * mstinterp.c: Added SystemDictionary byteCodeCounter primitive. * mstsysdep.c: Added getCurDirName() for allowing compiler to record the full file name that is used. 1991-11-24 Steve Byrne * mstinterp.h: Context size increased to 64 (still not enough), to prevent inadvertent stomping of memory past the end of the stack. 1991-11-09 Steve Byrne * mstinterp.c: Fixed new: To indicate failure when failure occurs. 1991-11-02 Steve Byrne * mstinterp.c: Altered the logic in the primitive replace from code -- I don't think it was really wrong, but it wasn't as clear as it might have been. * mstinterp.c: Fixed instVarAt: To obey real stack conventions (was pushing instead of setting the stack top). 1991-10-20 Steve Byrne * mstinterp.c: Added support for user level control of memory space growth rate parameters. * mstoop.c: Support for growing now fully operational (and no, it hasn't taken me over a month to track down the problems; free time has been nil). Also removed more vestiges of the incremental GC. 1991-09-15 Steve Byrne * mstdict.c: Fixed dictionaryAssociationAt: To not loop when the dictionary is full. Thanks to Michael Richardson for the fix! * mstinterp.c: Added quitPrimitive: To allow for non-zero exit statuses. * mstoop.c: Added support for loading larger semispaces from saved images. 1991-09-14 Steve Byrne * mstdict.c: Switched to global version string. * mst.h: Added edit version support. * mstinterp.h: Increased number of literals to 256, number of temporaries to 64, and number of allowable primitives to 1024 (overkill?) * mstmain.c: Added edit version support. * mstmain.h: Added edit version support. * mstsave.c: Added support for edit version. 1991-09-12 Steve Byrne * mstmain.c: Fixed -I argument parsing code to properly gobble up the file name. 1991-08-04 Steve Byrne * mstoop.c: Removed more vestiges of the incremental GC, began switchover to automatically growing semi-spaces. 1991-07-19 Steve Byrne * mstcint.c: Started adding support for the DLD package. * mstmain.c: Started adding conditional support for the DLD package. 1991-07-06 Steve Byrne * mstdict.c: Added newString (create uninitialized string of a given length). 1991-07-05 Steve Byrne * mstinterp.c: Added primitive 248: `FileStream fileInLine: LineNum fileName: aString at: charPosInt'; this helps improve things for the emacs interface by making recorded information accurate, and making error locations also be accurate. * mstinterp.c: Added support for primitive 105, which is the basic fast support for doing replacement within strings. * mstlex.c: Added setStreamInfo so that stuff filed in from Emacs can have more accurate information such as the line number in the buffer instead of the line number in the temporary file. 1991-07-02 Steve Byrne * mstinterp.c: Fixed handling of jump true and jump false opcodes: they now issue an error if invoked with non trueOOP or falseOOP. 1991-04-19 Steve Byrne * mstcomp.c: Added skipCompilation boolean, for conditional compilation. * mstinterp.c: Added primitive to support conditional compilation. 1991-04-13 Steve Byrne * mstdict.c: Added Features global variable. This allows for conditional execution based on operating system or machine architecture, and at some point, conditional compilation. 1991-03-25 Steve Byrne * mstlex.c: Added -> operator. 1991-03-24 Steve Byrne * mstdict.c: Float's class definition said that it was not pointers, not words, and not indexable. When new instances were created, they were 2 BYTES large, instead of 2 words. Changed to have the words flag * mstlex.c: Fixed lexing of foo:= to be seen as foo :=. * mstmain.c: Added loading of changes.st 1991-03-23 Steve Byrne * mstinterp.c: Fixed a bug with process switching: You can't depend on objects gotten with oopToObj after a prepareToStore into the parent object: it may have moved, and you're storing into dead storage. * mstinterp.c: Improved speed another 50% by "inlining" many of the special selectors that the compiler uses. 1991-03-17 Steve Byrne * mstinterp.c: Added support for C-style interrupts (signals) and timed interrupts to help with time slicing. 1991-02-16 Steve Byrne * mstcomp.c: Recursive calls to equalConstant had the arguments reversed. 1991-01-27 Steve Byrne * mstinterp.c: Modified the definition of the inline-controlling macro so that inlining is always selected when compiling for debugging. * mstoop.h: Force ACCESSOR_DEBUGGING off when optimizing. 1991-01-22 Steve Byrne * mstcint.c: Added putenv(). 1991-01-05 Steve Byrne * mstinterp.c: Converted executePrimitiveOperation to do returns as soon as possible, to not use the failed variable, and to not do double switching on int and float operations. This simple change increased performance from ~130K bytecodes/sec (SS1+ optim) to > 200k bytecodes/sec (simple code, builtins and primitives only, no real method invocation). * mstsysdep.c: Added getMilliTime(). 1991-01-01 Steve Byrne * mstinterp.c: Switched to not creating MethodContexts always...just use a cache of pre-made fake method contexts and only create real method contexts when someone will get a reference to one of the method contexts. 1990-11-26 Steve Byrne * mstcomp.c: Fixed whileTrue: and whileFalse: To loop only if the value returned by the receiver is the expected one, instead of if it's the boolean not of the expected value. 1990-11-24 Steve Byrne * mstmain.c: Fixed to set quietExecution using || instead of | (HP doesn't like it otherwise). 1990-11-17 Steve Byrne * mstcint.c: Added support for UnixStream primitives. * mstmain.c: Added UnixStream and IOCtl to kernel files. 1990-11-10 Steve Byrne * mstcomp.c: Added support for retaining the latest compiled method so the interpreter can return it from the compile: primitive. * mstcomp.h: Added latestCompiledMethod, so that some of the compile methods can get the method that they just compiled and set its category. 1990-11-06 Steve Byrne * mstmain.c: Added the per-user pre-image file...this may turn into a kind of site defaults thing, but this is what I've wanted for a while. 1990-10-13 Steve Byrne * mstoop.c: Converted to use bit masks instead of bit fields, hoping to improve performance somewhat. 1990-10-02 Steve Byrne * mstmain.c: Fixed okToLoadBinary so that it returns false if there is a Smalltalk file found locally, but there is no image file locally (the stix problem). * mstmain.h: FindImageFile was changed to return Boolean. 1990-09-21 Steve Byrne * mstcomp.c: Fixed so that a block that contains no statements properly returns nil. 1990-08-21 Steve Byrne * mstinterp.c: Added support for subtypes of CObject to provide direct access to C data. 1990-08-11 Steve Byrne * mstcint.c: Added knowledge of byteArrayOut type. 1990-08-03 Steve Byrne * mstdict.c: Added allocCObject. * mstinterp.c: Added support for primitive C object allocation routine. 1990-05-22 Steve Byrne *** Version 1.1.1 released (I think. I added this on May 10th, 1999... --- pb) * mstmain.c: Improved on Doug's mapping with macro to improve readability. * mstmain.c: Short name stuff added, thanks to Doug McCallum. 1990-05-20 Steve Byrne * mstcomp.c: Improved error handling...compiler errors set a flag, and execution does not occur if the expression to be executed has compilation errors. * mstinterp.c: Improved error handling when error: Or doesNotUnderstand: occurs. Also, added ^C handling to abort execution. 1990-05-17 Steve Byrne * mstsysdep.c: Added enableInterrupts and disableInterrupts. System V.3 code signal support from Doug McCallum (thanks, Doug!). 1990-05-16 Steve Byrne * mstcomp.c: Added usage of emacsProcess. * mstsym.c: Changed usages of "entry" to "ent" to prevent collisions with C compilers which have this identifier as a reserved word. * mstsysdep.c: Created. * mstsysdep.h: Created. 1990-04-24 Steve Byrne * mstinterp.c: Improved error handling for fopen/popen primitives. * mstlex.c: Error checking for integers too large. 1990-04-21 Steve Byrne * mstdict.c: Added toByteArray. * mstsym.c: Addded byteArraySymbol. 1990-04-20 Steve Byrne * mstbyte.c: Added initByteCodes to fix a robustness issue with the compiler. * mstcomp.c: Fixed compiler to reset the byte code system before using it. The problem was if an error occurred, the old byte code stream was still in use, and further compilations were losing in a big way. * mstinterp.c: Make fileIn not close the stream that it's reading from; this is taken care of by the caller, and causes very strange behavior if we try to close it twice! * mstlex.c: Added the closeIt argument to popStream so that the closing behavior could be separated from the popping behavior (in particular, for fileIn). 1990-04-17 Steve Byrne * mstsave.c: Fixing binary save to save only to the maximum used OOP slot, instead of saving the entire OOP table. This should improve load time and decrease disk storage requirements. 1990-04-08 Steve Byrne * mstoop.c: Changed oopFree to oopValid to fix the bug with someInstance losing after GC's due to objects that have non-free OOP table entries, but point to freed objects. * mstoop.h: Changed oopFree to oopValid to better reflect the semantics. 1990-04-07 Steve Byrne * mstinterp.c: Added declaration tracing primitive. * mstinterp.c: Fixed fileIn: To check for existence of the file before trying to open it. Returns failure if the file cannot be accessed. * mstlex.c: Character lexing routines (such as nextChar) now return ints to get around problems on implementations that don't sign extend characters by default. * mstoop.c: Increased mem space size to 4M. This can be decreased as necessary. 1990-03-25 Steve Byrne * mstcomp.c: Changed cache hit ratio reporting to check for divide by zero, and to cast the byte counter to double (it was casting to float and relying on promotion). * mstinterp.c: Minor change for AtariSt: Decrease size of ASYNC queue size. * mstmain.c: ProcessorScheduler is too long of a name for the Atari; there are uniqueness problems. Shortened to ProcScheduler. Also, fixed quietExecution; wasn't set when reading from the terminal; should have been set to false (since the loading of the quiet things is over). 1990-02-24 Steve Byrne * mstoop.c: Update to change log: There are no longer any explicitly allocated OOPs due to the new symbol table structure; the September 20th, 1989 comment below is now a noop. 1990-02-15 Steve Byrne * mstlex.c: Added support for := as alternative assignment operator. 1990-02-11 Steve Byrne * mstsave.c: Changed the header to record the size of the oop table, since trying to load back into a system with a different sized oop table loses bigtime. 1990-01-13 Steve Byrne * mstcomp.c: Added support for "thisContext" as a compiler built-in variable. * mstsym.c: Added thisContextSymbol. * mstsym.h: Added thisContextSymbol. 1990-01-07 Steve Byrne * mstdict.c: Added more commentary to classes, added new global Smalltalk variable: Bigendian, which allows code to be conditional based on the architecture type. 1989-12-28 Steve Byrne * mstcomp.c: Compiled methods now record their exact number of byte codes. Previously, if the byte codes didn't exactly fill to a word-boundary, there was no way to distinguish that case. Now, with the advent of dumping byte codes from within Smalltalk, this has become a necessity. 1989-12-27 Steve Byrne * mstcomp.c: Realloc literal vec wasn't reallocing in units of sizeof(OOP), so after a while, the literal vector wasn't big enough. Typically most methods don't have a lot of literals, so this was not a problem. 1989-12-19 Steve Byrne * mstinterp.c: Added suport for primitive filein (for use with autoload -- "12 gauge autoloader", A. Swartzenegger, The Terminator) * mstsym.c: Rebuilt symbol table. Used to use the main OOP table as a symbol table, due to issues involving initial bootstrapping of the system. Now using open hash table built of arrays and linked lists, so that no special precautions need be taken by the GC system or the image save/restore facility. 1989-10-15 Steve Byrne * mstpaths.h: Created. * mstmain.c: Added support for creating an "installed" version of Smalltalk. There is now an include file that the installer can customize for his site that provides default locations to be checked for the kernel .st files and the binary image file, but these can be overidden in two ways: a) by a file of the same name in the user's current directory, or b) environment variables SMALLTALK_KERNEL and SMALLTALK_IMAGE. 1989-10-02 Steve Byrne * mstcomp.c: Fixed a bug with compilation of cascaded messages. see HACK ALERT in the file. 1989-09-23 Steve Byrne * mst.h: Modifications to support operation on a DECstation 3100. 1989-09-21 Steve Byrne * mstcomp.c: Made compilation of methods from strings record the source string. 1989-09-20 Steve Byrne * mstoop.c: Added oop table slot GC'ing. I'm not dealing with oop table slots that are explictly allocated; I believe that most OOP slots are not explicitly chosen and so not running the incremental reclaimer for that case shouldn't hurt us. 1989-09-13 Steve Byrne * mstcomp.c: Various changes for garbage collector. * mst.h: Sigh!!! modified pushOOP and setStackTop to move the objects that they refer to to toSpace...good bye performance! 1989-09-12 Steve Byrne * mstoop.c: Much of the garbage collector's operation depends on the fact that only 1 flip will occur between any two operations (such as a compilation, or a byte-code). The code would be much more complex if this were not the case, and I'm not sure that things would even be possible if this were not the case. Anyway, there is code in this routine to check for that eventuality and to halt the system if it occurs. 1989-09-07 Steve Byrne * mstdict.c: Started adding garbage collection support. 1989-09-06 Steve Byrne * mstoop.c: Started implementing the garbage collector (YAY!!!) 1989-09-03 Steve Byrne * mstlex.c: Added getCurFileName * mstlex.h: Added getCurFileName 1989-09-02 Steve Byrne * mstcomp.c: Began adding support for the method descriptor instance variable. * mstcomp.h: Moved common compiled method structure definition here, so that the interpeter could share. * mstcomp.h: Added descriptor support * mstinterp.c: Process primitives in and working...starting to switch to compiled methods with descriptor instance variable in addition to header. 1989-08-30 Steve Byrne * mstlex.c: Fixed a bug in parseIdent which was parsing foo:2 note no space) not as foo: and 2, but as a mixed up token. 1989-08-09 Steve Byrne * mstinterp.c: Conversion completed. Performance now 40k bytecodes/sec; was 43k bytecodes/sec. 1989-07-25 Steve Byrne * mstsym.c: Changed undeclareName to take a parameter that controls whether the frame index is decremented or not. It appears that each block gets its own, non-shared temporaries/arguments, so that if the block is used in a process, other blocks won't have strange things happening to their arguments. 1989-07-18 Steve Byrne * mstinterp.c: Began conversion from stack based method contexts and blocks to more traditional method contexts and blocks. This change was done 1) to make call in from C easier, 2) to make processs possible (they could have been implemented using stack based contexts, but somewhat space-wastefully), and 3) to conform with the more traditional definition of method contexts and block contexts. 1989-07-08 Steve Byrne * mstlex.c: Added prompt when input is a terminal. This should help Emacs's shell mode determine what has been typed as input to the system. 1989-07-04 Steve Byrne * mstmain.c: Added support for user init files (in ~/.stinit), which are invoked on every startup. Also, added support for initBlocks, which are blocks that are stored in the system and invoked on each startup (these could be used, for example, as an interim measure for declaring C callouts until the callout descriptor is converted to a Smalltalk object). 1989-06-04 Steve Byrne * mstcint.c: Added Smalltalk data conversion type. 1989-05-29 Steve Byrne * mstcint.c: Created. * mstcint.h: Created. * mstdict.c: Added the memory classes. Added the FileStream about a week ago. 1989-05-26 Steve Byrne * mstinterp.c: Added method cache! Why didn't I spend the 1/2 hour sooner? 1989-05-14 Steve Byrne * mstlex.h: Created. 1989-04-29 Steve Byrne * mstdict.c: Author changed from single to married. 1989-04-05 Steve Byrne * mstdict.c: Restructured Class and Metaclass creation. Is now table driven, and metaclasses are created containing the proper information. * mstsave.c: Modified to reflect change in classes: Now their name is a Smalltalk string; before, it was a C string that had to be saved specially. 1989-03-29 Steve Byrne * mstdict.c: Removed MethodDictionary as a separate type; it is an IdentityDictionary. 1989-03-11 Steve Byrne * mstdict.c: Smalltalk is now an instance of SystemDictionary. 1989-03-10 Steve Byrne * mstmain.c: Added support for automatically loading image file if it's newer than and of the system source files. 1989-03-04 Steve Byrne * mstmain.h: Created. * mstsave.c: Created. * mstsave.h: Created. 1989-01-24 Steve Byrne * mstlex.c: Added 2 chars of push back, because 3. needs to look ahead one more character to see if its 3.DIGIT or 3. next statement. 1989-01-13 Steve Byrne * mstdict.c: Created. * mstdict.h: Created. * mstoop.c: Created. * mstoop.h: Created. 1989-01-07 Steve Byrne * mstinterp.c: Created. * mstinterp.h: Created. 1989-01-05 Steve Byrne * mstsym.c: Created. 1989-01-02 Steve Byrne * mstbyte.h: Created. 1989-01-01 Steve Byrne * mstcomp.c: Created. * mstcomp.h: Created. * mstsym.h: Created. 1988-12-30 Steve Byrne * msttree.c: Created. * msttree.h: Created. 1988-12-29 Steve Byrne * mst.h: Created. 1988-12-27 Steve Byrne * mstbyte.c: Created. * mstid.c: Created. * mstid.h: Created. * mstlex.c: Created. * mstmain.c: Created. * mststr.c: Created. * mststr.h: Created. smalltalk-3.2.5/libgst/genvm.h0000644000175000017500000000522712123404352013201 00000000000000/******************************** -*- C -*- **************************** * * GNU Smalltalk genvm tool * ***********************************************************************/ /*********************************************************************** * * Copyright 2003, 2006 Free Software Foundation, Inc. * Written by Paolo Bonzini. * * This file is part of GNU Smalltalk. * * GNU Smalltalk is free software; you can redistribute it and/or modify it * under the terms of the GNU General Public License as published by the Free * Software Foundation; either version 2, or (at your option) any later * version. * * Linking GNU Smalltalk statically or dynamically with other modules is * making a combined work based on GNU Smalltalk. Thus, the terms and * conditions of the GNU General Public License cover the whole * combination. * * In addition, as a special exception, the Free Software Foundation * give you permission to combine GNU Smalltalk with free software * programs or libraries that are released under the GNU LGPL and with * independent programs running under the GNU Smalltalk virtual machine. * * You may copy and distribute such a system following the terms of the * GNU GPL for GNU Smalltalk and the licenses of the other code * concerned, provided that you include the source code of that other * code when and as the GNU GPL requires distribution of source code. * * Note that people who make modified versions of GNU Smalltalk are not * obligated to grant this special exception for their modified * versions; it is their choice whether to do so. The GNU General * Public License gives permission to release a modified version without * this exception; this exception also makes it possible to release a * modified version which carries forward this exception. * * GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or * FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for * more details. * * You should have received a copy of the GNU General Public License along with * GNU Smalltalk; see the file COPYING. If not, write to the Free Software * Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * ***********************************************************************/ #ifdef HAVE_CONFIG_H #include "config.h" #endif #include #include #include #include "snprintfv/filament.h" #include "snprintfv/printf.h" extern int c_code_on_brace; extern int c_args_on_paren; enum { false, true }; /* genvm-scan.l declarations */ int yylex (void); extern int yylineno; smalltalk-3.2.5/libgst/cint.c0000644000175000017500000011662512123404352013022 00000000000000/******************************** -*- C -*- **************************** * * C - Smalltalk Interface module * * ***********************************************************************/ /*********************************************************************** * * Copyright 1988,89,90,91,92,94,95,99,2000,2001,2002,2003,2005,2006,2007,2008,2009,2011 * Free Software Foundation, Inc. * Written by Steve Byrne. * * This file is part of GNU Smalltalk. * * GNU Smalltalk is free software; you can redistribute it and/or modify it * under the terms of the GNU General Public License as published by the Free * Software Foundation; either version 2, or (at your option) any later * version. * * Linking GNU Smalltalk statically or dynamically with other modules is * making a combined work based on GNU Smalltalk. Thus, the terms and * conditions of the GNU General Public License cover the whole * combination. * * In addition, as a special exception, the Free Software Foundation * give you permission to combine GNU Smalltalk with free software * programs or libraries that are released under the GNU LGPL and with * independent programs running under the GNU Smalltalk virtual machine. * * You may copy and distribute such a system following the terms of the * GNU GPL for GNU Smalltalk and the licenses of the other code * concerned, provided that you include the source code of that other * code when and as the GNU GPL requires distribution of source code. * * Note that people who make modified versions of GNU Smalltalk are not * obligated to grant this special exception for their modified * versions; it is their choice whether to do so. The GNU General * Public License gives permission to release a modified version without * this exception; this exception also makes it possible to release a * modified version which carries forward this exception. * * GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or * FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for * more details. * * You should have received a copy of the GNU General Public License along with * GNU Smalltalk; see the file COPYING. If not, write to the Free Software * Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * ***********************************************************************/ #include "gstpriv.h" #include "re.h" #include "pointer-set.h" #include "ffi.h" #include #ifdef HAVE_GETGRNAM #include #endif #ifdef HAVE_GETPWNAM #include #endif typedef struct cparam { union { long longVal; PTR ptrVal; float floatVal; double doubleVal; long double longDoubleVal; long long longLongVal; struct { PTR pPtrVal; PTR ptrVal; } cObjectPtrVal; } u; OOP oop; cdata_type cType; } cparam; /* Holds onto the pointer to a C function and caches data about its calling interface. Used in _gst_invoke_croutine and push_smalltalk_obj. */ typedef struct cfunc_info { avl_node_t avl; const char *funcName; void (*funcAddr) (); } cfunc_info; typedef struct cfunc_cif_cache { unsigned cacheGeneration; /* Is the function called with variadic parms? */ ffi_cif cacheCif; /* cached ffi_cif representation */ int types_size; int arg_idx; cparam *args; ffi_type **types; } cfunc_cif_cache; typedef struct gst_ffi_closure { // This field must come first, since the address of this field will // be the same as the address of the overall structure. This is due // to disabling interior pointers in the GC. ffi_closure closure; void *address; OOP callbackOOP; ffi_cif cif; ffi_type *return_type; ffi_type *arg_types[1]; } gst_ffi_closure; struct gst_stat_struct { unsigned short st_mode; /* protection */ long st_size; /* total size, in bytes */ long st_aTime; /* time of last access */ long st_mTime; /* time of last modification */ long st_cTime; /* time of last change */ }; typedef struct gst_stat { OBJ_HEADER; OOP st_mode; /* protection */ OOP st_size; /* total size, in bytes */ OOP st_aTime; /* time of last access */ OOP st_mTime; /* time of last modification */ OOP st_cTime; /* time of last change */ } *gst_stat; /* Test/example C function and tribute to the original author :-) */ static void marli (int n); /* Prints an error message... this should really make the primitive fail so that a WrongClass exception is generated (FIXME) */ static void bad_type (OOP class_oop, cdata_type cType); /* Determines the appropriate C mapping for OOP and stores it. This returns 1 in case the type could not be converted. */ static mst_Boolean push_smalltalk_obj (OOP oop, cdata_type cType); /* Converts the return type as stored in RESULT to an OOP, based on the RETURNTYPEOOP that is stored in the descriptor. #void is converted to RECEIVEROOP. */ static OOP c_to_smalltalk (cparam *result, OOP receiverOOP, OOP returnTypeOOP); /* Converts the return type CTYPE, stored in a descriptor to a libffi type. */ static ffi_type *get_ffi_type (OOP returnTypeOOP); /* Initializes libltdl and defines the functions to access it. */ static void init_dld (void); /* Wrapper around lt_dlopenext that invokes gst_initModule if it is found in the library. */ static PTR dld_open (const char *filename); /* Callout to tests callins and callbacks. */ static void test_callin (OOP oop, int(*callback)(const char *)); /* Callout to test the CString class */ static void test_cstring (char **string); /* Callout to test #cObjectPtr parameters */ static void test_cobject_ptr (const void **string); /* Return the errno on output from the last callout. */ static int get_errno (void); /* Encapsulate binary incompatibilities between various C libraries. */ static int my_stat_old (const char *name, struct gst_stat_struct * out); static int my_stat (const char *name, OOP out); #ifdef HAVE_LSTAT static int my_lstat_old (const char *name, struct gst_stat_struct * out); static int my_lstat (const char *name, OOP out); #endif static int my_putenv (const char *str); static char **get_environ (void); static int my_chdir (const char *str); static int my_chown (const char *file, const char *owner, const char *group); static int my_symlink (const char* oldpath, const char* newpath); static char *my_mkdtemp (char* template); static int my_mkdir (const char* name, int mode); static DIR *my_opendir (const char *str); static char *extract_dirent_name (struct dirent *dir); /* Provide access to the arguments passed via -a. */ static int get_argc (void); static const char *get_argv (int n); /* The binary tree of function names vs. function addresses. */ static cfunc_info *c_func_root = NULL; /* The binary tree of function names vs. function addresses. */ static struct pointer_map_t *cif_cache = NULL; /* Used to invalidate the cache upon GC. */ static unsigned cif_cache_generation = 1; /* The cfunc_cif_cache that's being filled in. */ static cfunc_cif_cache *c_func_cur = NULL; /* printable names for corresponding C types */ static const char *c_type_name[] = { "char", /* CDATA_CHAR */ "unsigned char", /* CDATA_UCHAR */ "short", /* CDATA_SHORT */ "unsigned short", /* CDATA_USHORT */ "long", /* CDATA_LONG */ "unsigned long", /* CDATA_ULONG */ "float", /* CDATA_FLOAT */ "double", /* CDATA_DOUBLE */ "char *", /* CDATA_STRING */ "OOP", /* CDATA_OOP */ "int", /* CDATA_INT */ "unsigned int", /* CDATA_UINT */ "long double", /* CDATA_LONG_DOUBLE */ "void?", /* CDATA_UNKNOWN */ "char *", /* CDATA_STRING_OUT */ "char *", /* CDATA_SYMBOL */ "char *", /* CDATA_BYTEARRAY */ "char *", /* CDATA_BYTEARRAY_OUT */ "int", /* CDATA_BOOLEAN */ "void?", /* CDATA_VOID */ "...", /* CDATA_VARIADIC */ "...", /* CDATA_VARIADIC_OOP */ "void *", /* CDATA_COBJECT -- this is misleading */ "void **", /* CDATA_COBJECT_PTR */ "void?", /* CDATA_SELF */ "OOP", /* CDATA_SELF_OOP */ "wchar_t", /* CDATA_WCHAR */ "wchar_t *", /* CDATA_WSTRING */ "wchar_t *", /* CDATA_WSTRING_OUT */ "char *", /* CDATA_SYMBOL_OUT */ "long long", /* CDATA_LONGLONG */ "unsigned long long", /* CDATA_ULONGLONG */ }; /* The errno on output from a callout */ int _gst_errno = 0; void marli (int n) { int i; for (i = 0; i < n; i++) printf ("Marli loves Steve!!!\n"); } int get_errno (void) { int old; old = _gst_errno; _gst_errno = 0; /* When we get one of these, we don't return an error. However, the primitive still fails and the file/socket is closed by the Smalltalk code. */ if (old == ESHUTDOWN || old == ECONNRESET || old == ECONNABORTED || old == ENETRESET || old == EPIPE) return 0; else return (old); } static inline int adjust_time (time_t t) { return _gst_adjust_time_zone (t) - 86400 * 10957; } static inline int my_stat_old (const char *name, struct gst_stat_struct * out) { int result; struct stat statOut; result = stat (name, &statOut); if (!result) { errno = 0; out->st_mode = statOut.st_mode; out->st_size = statOut.st_size; out->st_aTime = adjust_time (statOut.st_atime); out->st_mTime = adjust_time (statOut.st_mtime); out->st_cTime = adjust_time (statOut.st_ctime); } return (result); } int my_stat (const char *name, OOP out) { int result; struct stat statOut; result = stat (name, &statOut); if (!result) { gst_stat obj = (gst_stat) OOP_TO_OBJ (out); errno = 0; obj->st_mode = FROM_INT (statOut.st_mode); obj->st_aTime = FROM_INT (adjust_time (statOut.st_atime)); obj->st_mTime = FROM_INT (adjust_time (statOut.st_mtime)); obj->st_cTime = FROM_INT (adjust_time (statOut.st_ctime)); obj->st_size = FROM_OFF_T (statOut.st_size); } return (result); } #ifdef HAVE_LSTAT static inline int my_lstat_old (const char *name, struct gst_stat_struct * out) { int result; struct stat statOut; result = lstat (name, &statOut); if (!result) { errno = 0; out->st_mode = statOut.st_mode; out->st_size = statOut.st_size; out->st_aTime = adjust_time (statOut.st_atime); out->st_mTime = adjust_time (statOut.st_mtime); out->st_cTime = adjust_time (statOut.st_ctime); } return (result); } int my_lstat (const char *name, OOP out) { int result; struct stat statOut; result = lstat (name, &statOut); if (!result) { gst_stat obj = (gst_stat) OOP_TO_OBJ (out); errno = 0; obj->st_mode = FROM_INT (statOut.st_mode); obj->st_aTime = FROM_INT (adjust_time (statOut.st_atime)); obj->st_mTime = FROM_INT (adjust_time (statOut.st_mtime)); obj->st_cTime = FROM_INT (adjust_time (statOut.st_ctime)); obj->st_size = FROM_OFF_T (statOut.st_size); } return (result); } #else #define my_lstat my_stat #define my_lstat_old my_stat_old #endif int my_putenv (const char *str) { char *clone; int len; len = strlen (str) + 1; /* hold the null */ clone = (char *) xmalloc (len); strcpy (clone, str); return (putenv (clone)); } static char ** get_environ (void) { return environ; } int my_chdir (const char *dir) { int status; status = chdir (dir); if (status == 0) errno = 0; return (status); } static int my_mkdir (const char* name, int mode) { int retstat; #ifdef __MSVCRT__ retstat = mkdir (name); if (retstat == 0) retstat = chmod (name, mode); #else retstat = mkdir (name, mode); #endif return retstat; } DIR * my_opendir (const char *dir) { DIR *result; result = opendir (dir); if (result != 0) errno = 0; return (result); } long long test_longlong (long long aVerylongInt) { printf ("Getting a long long 0x%llx\n", aVerylongInt); return aVerylongInt; } void test_callin (OOP oop, int(*callback)(const char *)) { OOP o; double f; int i; _gst_str_msg_send (oop, "printNl", NULL); o = _gst_string_to_oop ("abc"); _gst_str_msg_send (_gst_str_msg_send (o, ",", o, NULL), "printNl", NULL); i = callback ("this is a test"); _gst_msg_sendf (&f, "%f %i + %f", i, 4.7); printf ("result = %f\n", f); } void test_cstring (char **string) { printf ("The string is %s\n", *string); } void test_cobject_ptr (const void **string) { *string = "this is a test"; } char * extract_dirent_name (struct dirent *dir) { return (dir->d_name); } int get_argc (void) { return (_gst_smalltalk_passed_argc); } const char * get_argv (int n) { return (n >= 1 && n <= _gst_smalltalk_passed_argc ? _gst_smalltalk_passed_argv[n - 1] : NULL); } PTR dld_open (const char *filename) { #ifdef ENABLE_DLD lt_dlhandle handle; void (*initModule) (struct VMProxy *); /* Not all shared libraries have .xyz extensions! */ handle = lt_dlopen (filename); if (!handle) handle = lt_dlopenext (filename); #ifdef __APPLE__ if (!handle) { /* For some reason, lt_dlopenext on OS X doesn't try ".dylib" as a possible extension, so we're left with trying it here. */ char *full_filename; asprintf(&full_filename, "%s.dylib", filename); handle = lt_dlopen (full_filename); free (full_filename); } #endif if (handle) { initModule = lt_dlsym (handle, "gst_initModule"); if (initModule) initModule (_gst_get_vmproxy ()); } return (handle); #else return (NULL); #endif } struct search_path_stack { char *saved_search_path; struct search_path_stack *next; }; struct search_path_stack *search_paths; mst_Boolean _gst_dlopen (const char *path, mst_Boolean module) { PTR h = dld_open (path); if (h && !module) _gst_msg_sendf (NULL, "%v %o addLibraryHandle: %C", _gst_class_name_to_oop ("DLD"), h); return !!h; } void _gst_dladdsearchdir (const char *dir) { lt_dlinsertsearchdir (lt_dlgetsearchpath (), dir); } void _gst_dlpushsearchpath (void) { struct search_path_stack *entry = xmalloc (sizeof (struct search_path_stack)); const char *path = lt_dlgetsearchpath (); entry->saved_search_path = path ? strdup (path) : NULL; entry->next = search_paths; search_paths = entry; } void _gst_dlpopsearchpath (void) { struct search_path_stack *path = search_paths; if (!path) return; lt_dlsetsearchpath (path->saved_search_path); search_paths = path->next; free (path->saved_search_path); free (path); } void init_dld (void) { char *modules; lt_dlinit (); modules = _gst_relocate_path (MODULE_PATH); lt_dladdsearchdir (modules); free (modules); if ((modules = getenv ("SMALLTALK_MODULES"))) lt_dladdsearchdir (modules); /* Too hard to support dlpreopen... LTDL_SET_PRELOADED_SYMBOLS(); */ _gst_define_cfunc ("defineCFunc", _gst_define_cfunc); _gst_define_cfunc ("dldLink", dld_open); _gst_define_cfunc ("dldGetFunc", lt_dlsym); _gst_define_cfunc ("dldError", lt_dlerror); } void _gst_init_cfuncs (void) { extern char *getenv (const char *); cif_cache = pointer_map_create (); /* Access to command line args */ _gst_define_cfunc ("getArgc", get_argc); _gst_define_cfunc ("getArgv", get_argv); /* Test functions */ _gst_define_cfunc ("testLongLong", test_longlong); _gst_define_cfunc ("testCallin", test_callin); _gst_define_cfunc ("testCString", test_cstring); _gst_define_cfunc ("testCObjectPtr", test_cobject_ptr); /* Access to C library */ _gst_define_cfunc ("system", system); _gst_define_cfunc ("getenv", getenv); _gst_define_cfunc ("environ", get_environ); _gst_define_cfunc ("putenv", my_putenv); _gst_define_cfunc ("printf", printf); _gst_define_cfunc ("errno", get_errno); _gst_define_cfunc ("strerror", strerror); _gst_define_cfunc ("stat", my_stat_old); _gst_define_cfunc ("lstat", my_lstat_old); _gst_define_cfunc ("stat_obj", my_stat); _gst_define_cfunc ("lstat_obj", my_lstat); _gst_define_cfunc ("utime", _gst_set_file_access_times); _gst_define_cfunc ("chmod", chmod); _gst_define_cfunc ("chown", my_chown); _gst_define_cfunc ("opendir", my_opendir); _gst_define_cfunc ("closedir", closedir); _gst_define_cfunc ("readdir", readdir); _gst_define_cfunc ("rewinddir", rewinddir); _gst_define_cfunc ("extractDirentName", extract_dirent_name); _gst_define_cfunc ("symlink", my_symlink); _gst_define_cfunc ("unlink", unlink); _gst_define_cfunc ("rename", rename); _gst_define_cfunc ("rmdir", rmdir); _gst_define_cfunc ("chdir", my_chdir); _gst_define_cfunc ("mkdir", my_mkdir); _gst_define_cfunc ("mkdtemp", my_mkdtemp); _gst_define_cfunc ("getCurDirName", _gst_get_cur_dir_name); _gst_define_cfunc ("fileIsReadable", _gst_file_is_readable); _gst_define_cfunc ("fileIsWriteable", _gst_file_is_writeable); _gst_define_cfunc ("fileIsExecutable", _gst_file_is_executable); init_dld (); /* regex routines */ _gst_define_cfunc ("reh_search", _gst_re_search); _gst_define_cfunc ("reh_match", _gst_re_match); _gst_define_cfunc ("reh_make_cacheable", _gst_re_make_cacheable); /* Non standard routines */ _gst_define_cfunc ("marli", marli); } void _gst_define_cfunc (const char *funcName, PTR funcAddr) { avl_node_t **p = (avl_node_t **) &c_func_root; cfunc_info *node; cfunc_info *cfi = NULL; while (*p) { int cmp; cfi = (cfunc_info *) *p; cmp = strcmp(funcName, cfi->funcName); if (cmp < 0) p = &(*p)->avl_left; else if (cmp > 0) p = &(*p)->avl_right; else { cfi->funcAddr = funcAddr; return; } } node = (cfunc_info *) xcalloc(sizeof(cfunc_info), 1); node->avl.avl_parent = (avl_node_t *) cfi; node->avl.avl_left = node->avl.avl_right = NULL; node->funcName = strdup (funcName); node->funcAddr = funcAddr; *p = &(node->avl); avl_rebalance(&node->avl, (avl_node_t **) &c_func_root); } PTR _gst_lookup_function (const char *funcName) { cfunc_info *cfi = c_func_root; while (cfi) { int cmp; cmp = strcmp(funcName, cfi->funcName); if (cmp == 0) return (PTR) cfi->funcAddr; cfi = (cfunc_info *) (cmp < 0 ? cfi->avl.avl_left : cfi->avl.avl_right); } return NULL; } int _gst_c_type_size (int type) { switch (type) { case CDATA_CHAR: return sizeof (char); case CDATA_UCHAR: return sizeof (unsigned char); case CDATA_SHORT: return sizeof (short); case CDATA_USHORT: return sizeof (unsigned short); case CDATA_INT: return sizeof (int); case CDATA_UINT: return sizeof (unsigned int); case CDATA_LONG: return sizeof (long); case CDATA_ULONG: return sizeof (unsigned long); case CDATA_LONGLONG: return sizeof (long long); case CDATA_ULONGLONG: return sizeof (unsigned long long); case CDATA_FLOAT: return sizeof (float); case CDATA_DOUBLE: return sizeof (double); case CDATA_LONG_DOUBLE: return sizeof (long double); case CDATA_OOP: return sizeof (OOP); case CDATA_WCHAR: return sizeof (wchar_t); case CDATA_WSTRING: return sizeof (wchar_t *); case CDATA_STRING: case CDATA_STRING_OUT: case CDATA_SYMBOL: case CDATA_BYTEARRAY: case CDATA_BYTEARRAY_OUT: case CDATA_SYMBOL_OUT: return sizeof (char *); case CDATA_COBJECT: return sizeof (void *); case CDATA_COBJECT_PTR: return sizeof (void **); default: return 0; } } void _gst_invalidate_croutine_cache (void) { /* May want to delete and recreate completely upon global GC, and do the cheap invalidation only for scavenging? For now, we do the simplest thing. Incrementing by 2 makes sure that the generation number is never 0. */ cif_cache_generation += 2; } OOP _gst_invoke_croutine (OOP cFuncOOP, OOP receiver, OOP *args) { gst_c_callable desc; cdata_type cType; cparam result, *local_arg_vec, *arg; void *funcAddr, **p_slot, **ffi_arg_vec; OOP *argTypes, oop; int i, si, fixedArgs, totalArgs, filledArgs; mst_Boolean haveVariadic, needPostprocessing; inc_ptr incPtr; incPtr = INC_SAVE_POINTER (); /* Make sure the parameters do not die. */ INC_ADD_OOP (cFuncOOP); INC_ADD_OOP (receiver); funcAddr = cobject_value (cFuncOOP); if (!funcAddr) return (NULL); p_slot = pointer_map_insert (cif_cache, cFuncOOP); if (!*p_slot) *p_slot = xcalloc (1, sizeof (cfunc_cif_cache)); desc = (gst_c_callable) OOP_TO_OBJ (cFuncOOP); argTypes = OOP_TO_OBJ (desc->argTypesOOP)->data; c_func_cur = *p_slot; fixedArgs = NUM_INDEXABLE_FIELDS (desc->argTypesOOP); totalArgs = 0; haveVariadic = needPostprocessing = false; for (si = i = 0; i < fixedArgs; i++) { cType = IS_OOP (argTypes[i]) ? CDATA_COBJECT : TO_INT (argTypes[i]); switch (cType) { case CDATA_VOID: break; case CDATA_VARIADIC: case CDATA_VARIADIC_OOP: oop = args[si++]; totalArgs += NUM_WORDS (OOP_TO_OBJ (oop)); haveVariadic = true; break; case CDATA_SELF: case CDATA_SELF_OOP: totalArgs++; break; case CDATA_COBJECT_PTR: case CDATA_WSTRING_OUT: case CDATA_STRING_OUT: case CDATA_BYTEARRAY_OUT: case CDATA_SYMBOL_OUT: case CDATA_STRING: case CDATA_BYTEARRAY: case CDATA_SYMBOL: case CDATA_WSTRING: needPostprocessing = true; /* fall through */ default: totalArgs++; si++; break; } } ffi_arg_vec = (void **) alloca (totalArgs * sizeof (void *)); c_func_cur->args = local_arg_vec = (cparam *) alloca (totalArgs * sizeof (cparam)); /* The ffi_cif holds a pointer to this, so we must malloc it. */ if (c_func_cur->types_size < totalArgs) { c_func_cur->types = (ffi_type **) realloc (c_func_cur->types, totalArgs * sizeof (ffi_type *)); c_func_cur->types_size = totalArgs; } c_func_cur->arg_idx = 0; for (i = 0; i < totalArgs; i++) ffi_arg_vec[i] = &local_arg_vec[i].u; /* Push the arguments */ for (si = i = 0; i < fixedArgs; i++) { mst_Boolean res; cType = IS_OOP (argTypes[i]) ? CDATA_COBJECT : TO_INT (argTypes[i]); if (cType == CDATA_VOID) continue; else if (cType == CDATA_SELF || cType == CDATA_SELF_OOP) res = push_smalltalk_obj (receiver, cType == CDATA_SELF ? CDATA_UNKNOWN : CDATA_OOP); else /* Do nothing if it is a void */ res = push_smalltalk_obj (args[si++], cType); if (!res) { oop = NULL; filledArgs = c_func_cur->arg_idx; goto out; } } /* If the previous call was done through the same function descriptor, the ffi_cif is already ok. */ if (c_func_cur->cacheGeneration != cif_cache_generation) { ffi_prep_cif (&c_func_cur->cacheCif, FFI_DEFAULT_ABI, totalArgs, get_ffi_type (desc->returnTypeOOP), c_func_cur->types); /* For variadic functions, we cannot cache the ffi_cif because the argument types change every time. */ if (!haveVariadic) c_func_cur->cacheGeneration = cif_cache_generation; } errno = 0; filledArgs = c_func_cur->arg_idx; assert (filledArgs == totalArgs); ffi_call (&c_func_cur->cacheCif, FFI_FN (funcAddr), &result.u, ffi_arg_vec); _gst_set_errno (errno); desc = (gst_c_callable) OOP_TO_OBJ (cFuncOOP); oop = c_to_smalltalk (&result, receiver, desc->returnTypeOOP); INC_ADD_OOP (oop); out: /* Fixup all returned string variables */ if (needPostprocessing) for (i = 0, arg = local_arg_vec; i < filledArgs; i++, arg++) { if (!arg->oop) continue; switch (arg->cType) { case CDATA_COBJECT_PTR: if (oop) set_cobject_value (arg->oop, arg->u.cObjectPtrVal.ptrVal); continue; case CDATA_WSTRING_OUT: if (oop) _gst_set_oop_unicode_string (arg->oop, arg->u.ptrVal); break; case CDATA_STRING_OUT: if (oop) _gst_set_oopstring (arg->oop, arg->u.ptrVal); break; case CDATA_BYTEARRAY_OUT: if (oop) _gst_set_oop_bytes (arg->oop, arg->u.ptrVal); break; default: break; } xfree (arg->u.ptrVal); } INC_RESTORE_POINTER (incPtr); return (oop); } ffi_type * get_ffi_type (OOP returnTypeOOP) { if (!IS_INT (returnTypeOOP)) return &ffi_type_pointer; switch (TO_INT (returnTypeOOP)) { case CDATA_OOP: case CDATA_COBJECT: case CDATA_COBJECT_PTR: case CDATA_SYMBOL: case CDATA_SYMBOL_OUT: case CDATA_WSTRING: case CDATA_WSTRING_OUT: case CDATA_STRING: case CDATA_STRING_OUT: case CDATA_BYTEARRAY: case CDATA_BYTEARRAY_OUT: default: return &ffi_type_pointer; case CDATA_LONG: case CDATA_ULONG: #if LONG_MAX == 2147483647 return &ffi_type_sint32; #else return &ffi_type_sint64; #endif case CDATA_LONGLONG: case CDATA_ULONGLONG: return &ffi_type_sint64; case CDATA_VOID: case CDATA_INT: case CDATA_CHAR: case CDATA_SHORT: case CDATA_WCHAR: case CDATA_BOOLEAN: return &ffi_type_sint; case CDATA_UINT: case CDATA_UCHAR: case CDATA_USHORT: return &ffi_type_uint; case CDATA_FLOAT: return &ffi_type_float; case CDATA_DOUBLE: return &ffi_type_double; case CDATA_LONG_DOUBLE: return &ffi_type_longdouble; case CDATA_VARIADIC: case CDATA_VARIADIC_OOP: case CDATA_SELF: case CDATA_SELF_OOP: case CDATA_UNKNOWN: /* TODO: less brutal */ abort (); } } ffi_type * smalltalk_to_c (OOP oop, cparam *cp, cdata_type cType) { OOP class = OOP_INT_CLASS (oop); if (cType == CDATA_UNKNOWN) cType = (oop == _gst_true_oop || oop == _gst_false_oop) ? CDATA_BOOLEAN : oop == _gst_nil_oop ? CDATA_COBJECT : class == _gst_char_class ? CDATA_CHAR : class == _gst_unicode_character_class ? CDATA_WCHAR : class == _gst_byte_array_class ? CDATA_BYTEARRAY : is_a_kind_of (class, _gst_integer_class) ? CDATA_LONG : is_a_kind_of (class, _gst_string_class) ? CDATA_STRING : is_a_kind_of (class, _gst_unicode_string_class) ? CDATA_WSTRING : is_a_kind_of (class, _gst_c_object_class) ? CDATA_COBJECT : is_a_kind_of (class, _gst_float_class) ? CDATA_DOUBLE : CDATA_OOP; memset (cp, 0, sizeof (cparam)); cp->cType = cType; if (cType == CDATA_OOP) { cp->u.ptrVal = (PTR) oop; INC_ADD_OOP (oop); /* make sure it doesn't get gc'd */ return &ffi_type_pointer; } else if (is_a_kind_of (class, _gst_integer_class)) { switch (cType) { case CDATA_LONGLONG: case CDATA_ULONGLONG: cp->u.longLongVal = to_c_int_64 (oop); return &ffi_type_sint64; case CDATA_LONG: case CDATA_ULONG: cp->u.longVal = TO_C_LONG (oop); #if LONG_MAX == 2147483647 return &ffi_type_sint32; #else return &ffi_type_sint64; #endif case CDATA_INT: cp->u.longVal = (int) TO_C_INT (oop); return &ffi_type_sint; case CDATA_UINT: cp->u.longVal = (unsigned int) TO_C_INT (oop); return &ffi_type_sint; case CDATA_CHAR: cp->u.longVal = (char) TO_C_INT (oop); return &ffi_type_sint; case CDATA_UCHAR: cp->u.longVal = (unsigned char) TO_C_INT (oop); return &ffi_type_sint; case CDATA_SHORT: cp->u.longVal = (short) TO_C_INT (oop); return &ffi_type_sint; case CDATA_USHORT: cp->u.longVal = (unsigned short) TO_C_INT (oop); return &ffi_type_sint; case CDATA_DOUBLE: cp->u.doubleVal = (double) TO_C_LONG (oop); return &ffi_type_double; case CDATA_FLOAT: cp->u.floatVal = (float) TO_C_LONG (oop); return &ffi_type_float; } } else if (oop == _gst_true_oop || oop == _gst_false_oop) { switch (cType) { case CDATA_LONGLONG: case CDATA_ULONGLONG: cp->u.longLongVal = (long long)(oop == _gst_true_oop); return &ffi_type_sint64; case CDATA_LONG: case CDATA_ULONG: cp->u.longVal = (oop == _gst_true_oop); #if LONG_MAX == 2147483647 return &ffi_type_sint32; #else return &ffi_type_sint64; #endif case CDATA_INT: case CDATA_UINT: case CDATA_CHAR: case CDATA_UCHAR: case CDATA_SHORT: case CDATA_USHORT: case CDATA_BOOLEAN: cp->u.longVal = (oop == _gst_true_oop); return &ffi_type_sint; } } else if ((class == _gst_char_class && (cType == CDATA_CHAR || cType == CDATA_UCHAR || cType == CDATA_WCHAR)) || (class == _gst_unicode_character_class && cType == CDATA_WCHAR)) { cp->u.longVal = CHAR_OOP_VALUE (oop); return &ffi_type_sint; } else if (((class == _gst_string_class || class == _gst_byte_array_class) && (cType == CDATA_STRING || cType == CDATA_STRING_OUT || cType == CDATA_BYTEARRAY || cType == CDATA_BYTEARRAY_OUT)) || (class == _gst_symbol_class && (cType == CDATA_SYMBOL || cType == CDATA_STRING))) { cp->oop = oop; if (cp->cType == CDATA_BYTEARRAY || cp->cType == CDATA_BYTEARRAY_OUT) cp->u.ptrVal = _gst_to_byte_array (oop); else cp->u.ptrVal = (gst_uchar *) _gst_to_cstring (oop); return &ffi_type_pointer; } else if (class == _gst_unicode_string_class && (cType == CDATA_WSTRING || cType == CDATA_WSTRING_OUT)) { cp->oop = oop; cp->u.ptrVal = (gst_uchar *) _gst_to_wide_cstring (oop); return &ffi_type_pointer; } else if (is_a_kind_of (class, _gst_float_class)) { switch (cType) { case CDATA_LONG_DOUBLE: cp->u.longDoubleVal = _gst_oop_to_float (oop); return &ffi_type_longdouble; case CDATA_DOUBLE: cp->u.doubleVal = _gst_oop_to_float (oop); return &ffi_type_double; case CDATA_FLOAT: cp->u.floatVal = (float) _gst_oop_to_float (oop); return &ffi_type_float; } } else if (is_a_kind_of (class, _gst_c_object_class)) { switch (cType) { case CDATA_COBJECT_PTR: /* Set up an indirect pointer to protect against the OOP moving during the call-out. */ cp->u.cObjectPtrVal.pPtrVal = &cp->u.cObjectPtrVal.ptrVal; cp->u.cObjectPtrVal.ptrVal = cobject_value (oop); cp->oop = oop; return &ffi_type_pointer; case CDATA_COBJECT: cp->u.ptrVal = cobject_value (oop); return &ffi_type_pointer; } } else if (class == _gst_undefined_object_class) { /* how to encode nil */ switch (cType) { case CDATA_COBJECT_PTR: case CDATA_COBJECT: case CDATA_BYTEARRAY: case CDATA_BYTEARRAY_OUT: case CDATA_STRING: case CDATA_STRING_OUT: case CDATA_SYMBOL: cp->u.ptrVal = NULL; return &ffi_type_pointer; } } /* #cObject can pass every object with non-pointer indexed instance variables. */ if (cType == CDATA_COBJECT) { switch (CLASS_INSTANCE_SPEC (class) & ISP_INDEXEDVARS) { case GST_ISP_FIXED: case GST_ISP_POINTER: break; default: /* Byte indexed variables, pass the pointer through. */ cp->u.ptrVal = OOP_TO_OBJ (oop)->data + CLASS_FIXED_FIELDS (class); return &ffi_type_pointer; } } bad_type (class, cType); return NULL; } mst_Boolean push_smalltalk_obj (OOP oop, cdata_type cType) { if (cType == CDATA_VARIADIC || cType == CDATA_VARIADIC_OOP) { int i; if (OOP_INT_CLASS (oop) != _gst_array_class) { bad_type (OOP_INT_CLASS (oop), cType); return false; } cType = (cType == CDATA_VARIADIC) ? CDATA_UNKNOWN : CDATA_OOP; for (i = 1; i <= NUM_WORDS (OOP_TO_OBJ (oop)); i++) if (!push_smalltalk_obj (ARRAY_AT (oop, i), cType)) return false; } else { cparam *cp = &c_func_cur->args[c_func_cur->arg_idx]; ffi_type *type = smalltalk_to_c (oop, cp, cType); if (cp->oop && !IS_NIL (cp->oop)) INC_ADD_OOP (cp->oop); if (type) c_func_cur->types[c_func_cur->arg_idx++] = type; else return false; } return true; } OOP c_to_smalltalk (cparam *result, OOP receiverOOP, OOP returnTypeOOP) { cdata_type returnType; OOP resultOOP; if (IS_INT (returnTypeOOP)) returnType = (cdata_type) TO_INT (returnTypeOOP); else returnType = CDATA_COBJECT; switch (returnType) { case CDATA_VOID: resultOOP = receiverOOP; break; case CDATA_CHAR: case CDATA_UCHAR: resultOOP = CHAR_OOP_AT ((gst_uchar) result->u.longVal); break; case CDATA_WCHAR: resultOOP = char_new ((wchar_t) result->u.longVal); break; case CDATA_BOOLEAN: resultOOP = result->u.longVal ? _gst_true_oop : _gst_false_oop; break; case CDATA_INT: resultOOP = FROM_C_INT ((int) result->u.longVal); break; case CDATA_UINT: resultOOP = FROM_C_UINT ((unsigned int) result->u.longVal); break; case CDATA_SHORT: resultOOP = FROM_INT ((short) result->u.longVal); break; case CDATA_USHORT: resultOOP = FROM_INT ((unsigned short) result->u.longVal); break; case CDATA_LONG: resultOOP = FROM_C_LONG (result->u.longVal); break; case CDATA_ULONG: resultOOP = FROM_C_ULONG (result->u.longVal); break; case CDATA_LONGLONG: resultOOP = FROM_C_LONGLONG (result->u.longLongVal); break; case CDATA_ULONGLONG: resultOOP = FROM_C_ULONGLONG (result->u.longLongVal); break; case CDATA_STRING: case CDATA_STRING_OUT: case CDATA_WSTRING: case CDATA_WSTRING_OUT: case CDATA_SYMBOL: case CDATA_SYMBOL_OUT: case CDATA_COBJECT: case CDATA_OOP: if (!result->u.ptrVal) resultOOP = _gst_nil_oop; else if (returnType == CDATA_OOP) resultOOP = (OOP) result->u.ptrVal; else if (returnType == CDATA_SYMBOL || returnType == CDATA_SYMBOL_OUT) { resultOOP = _gst_intern_string ((char *) result->u.ptrVal); if (returnType == CDATA_SYMBOL_OUT) xfree (result->u.ptrVal); } else if (returnType == CDATA_COBJECT) { if (IS_INT (returnTypeOOP)) returnTypeOOP = _gst_nil_oop; resultOOP = COBJECT_NEW (result->u.ptrVal, returnTypeOOP, _gst_c_object_class); } else if (returnType == CDATA_STRING || returnType == CDATA_STRING_OUT) { resultOOP = _gst_string_new ((char *) result->u.ptrVal); if (returnType == CDATA_STRING_OUT) xfree (result->u.ptrVal); } else if (returnType == CDATA_WSTRING || returnType == CDATA_WSTRING_OUT) { resultOOP = _gst_unicode_string_new ((wchar_t *) result->u.ptrVal); if (returnType == CDATA_WSTRING_OUT) xfree (result->u.ptrVal); } else abort (); break; case CDATA_DOUBLE: resultOOP = floatd_new (result->u.doubleVal); break; case CDATA_FLOAT: resultOOP = floate_new (result->u.doubleVal); break; default: _gst_errorf ("Invalid C function return type specified, index %d\n", returnType); resultOOP = _gst_nil_oop; break; } return resultOOP; } void bad_type (OOP class_oop, cdata_type cType) { if (IS_A_METACLASS (class_oop)) _gst_errorf ("Attempt to pass the %O object as a %s", class_oop, c_type_name[cType]); else _gst_errorf ("Attempt to pass an instance of %O as a %s", class_oop, c_type_name[cType]); } /* This function does the unmarshaling of the libffi arguments to Smalltalk, and calls the block that is stored in the CCallbackDescriptor. */ static void closure_msg_send (ffi_cif* cif, void* result, void** args, void* userdata) { gst_ffi_closure *closure = userdata; OOP callbackOOP = closure->callbackOOP; gst_c_callable desc; int numArgs, i; OOP *argsOOP, *argTypes, resultOOP; cdata_type cType; cparam cp; desc = (gst_c_callable) OOP_TO_OBJ (callbackOOP); numArgs = NUM_INDEXABLE_FIELDS (desc->argTypesOOP); argsOOP = alloca (sizeof (OOP) * numArgs); for (i = 0; i < numArgs; i++) { memcpy (&cp.u, args[i], sizeof (ffi_arg)); desc = (gst_c_callable) OOP_TO_OBJ (callbackOOP); argTypes = OOP_TO_OBJ (desc->argTypesOOP)->data; argsOOP[i] = c_to_smalltalk (&cp, _gst_nil_oop, argTypes[i]); } desc = (gst_c_callable) OOP_TO_OBJ (callbackOOP); resultOOP = _gst_nvmsg_send (desc->blockOOP, NULL, argsOOP, numArgs); desc = (gst_c_callable) OOP_TO_OBJ (callbackOOP); cType = IS_OOP (desc->returnTypeOOP) ? CDATA_COBJECT : TO_INT (desc->returnTypeOOP); if (cType != CDATA_VOID && smalltalk_to_c (resultOOP, &cp, cType)) memcpy (result, &cp.u, sizeof (ffi_arg)); else memset (result, 0, sizeof (ffi_arg)); } void _gst_make_closure (OOP callbackOOP) { gst_c_callable desc; OOP *argTypes; void *code; gst_ffi_closure *closure; int numArgs, i; if (cobject_value (callbackOOP)) return; desc = (gst_c_callable) OOP_TO_OBJ (callbackOOP); numArgs = NUM_INDEXABLE_FIELDS (desc->argTypesOOP); argTypes = OOP_TO_OBJ (desc->argTypesOOP)->data; closure = (gst_ffi_closure *) ffi_closure_alloc ( sizeof (gst_ffi_closure) + sizeof(ffi_type *) * (numArgs - 1), &code); closure->address = closure; closure->callbackOOP = callbackOOP; closure->return_type = get_ffi_type (desc->returnTypeOOP); for (i = 0; i < numArgs; i++) closure->arg_types[i] = get_ffi_type (argTypes[i]); ffi_prep_cif (&closure->cif, FFI_DEFAULT_ABI, numArgs, closure->return_type, closure->arg_types); ffi_prep_closure_loc (&closure->closure, &closure->cif, closure_msg_send, closure, code); set_cobject_value (callbackOOP, code); } void _gst_free_closure (OOP callbackOOP) { gst_ffi_closure *exec_closure = cobject_value (callbackOOP); ffi_closure_free (exec_closure->address); set_cobject_value (callbackOOP, NULL); } void _gst_set_errno(int errnum) { /* ENOTEMPTY and EEXIST are synonymous; some systems use one, and some use the other. We always uses EEXIST which is provided by all systems. */ #ifdef ENOTEMPTY _gst_errno = (errnum == ENOTEMPTY) ? EEXIST : errnum; #else _gst_errno = errnum; #endif } int my_chown (const char *file, const char *user, const char *group) { #if defined HAVE_CHOWN && defined HAVE_GETGRNAM && defined HAVE_GETPWNAM static char *save_user, *save_group; static uid_t save_uid; static gid_t save_gid; static int recursive_depth; uid_t uid, gid; if (!file && !user && !group) { recursive_depth--; if (recursive_depth == 0) { #if defined HAVE_SETGROUPENT && defined HAVE_ENDGRENT endgrent (); #endif #if defined HAVE_SETPASSENT && defined HAVE_ENDPWENT endpwent (); #endif } free (save_user); free (save_group); save_user = save_group = NULL; return 0; } if (!file) { recursive_depth++; if (recursive_depth == 1) { #if defined HAVE_SETGROUPENT && defined HAVE_ENDGRENT setgroupent (1); #endif #if defined HAVE_SETPASSENT && defined HAVE_ENDPWENT setpassent (1); #endif } } if (!user) uid = -1; else if (save_user && !strcmp (save_user, user)) uid = save_uid; else { struct passwd *pw; pw = getpwnam (user); if (!pw) { errno = EINVAL; return -1; } uid = pw->pw_uid; if (recursive_depth) { if (save_user) free (save_user); save_user = strdup (user); save_uid = uid; } } if (!group) gid = -1; else if (save_group && !strcmp (save_group, group)) gid = save_gid; else { struct group *gr; gr = getgrnam (group); if (!gr) { errno = EINVAL; return -1; } gid = gr->gr_gid; if (recursive_depth) { if (save_group) free (save_group); save_group = strdup (group); save_gid = gid; } } if (!file) return 0; else return chown (file, uid, gid); #else return 0; #endif } /* TODO: check if this can be changed to an extern declaration and/or an AC_CHECK_DECLS test. */ int my_symlink (const char* oldpath, const char* newpath) { return symlink (oldpath, newpath); } char* my_mkdtemp(char* template) { return mkdtemp(template); } smalltalk-3.2.5/libgst/alloc.c0000644000175000017500000004454212123404352013155 00000000000000/******************************** -*- C -*- **************************** * * Memory allocation for Smalltalk * * ***********************************************************************/ /*********************************************************************** * * Copyright 2002, 2003, 2004, 2005, 2006, 2007, 2008 Free Software Foundation, Inc. * Written by Paolo Bonzini. Ideas based on Mike Haertel's malloc. * * This file is part of GNU Smalltalk. * * GNU Smalltalk is free software; you can redistribute it and/or modify it * under the terms of the GNU General Public License as published by the Free * Software Foundation; either version 2, or (at your option) any later * version. * * Linking GNU Smalltalk statically or dynamically with other modules is * making a combined work based on GNU Smalltalk. Thus, the terms and * conditions of the GNU General Public License cover the whole * combination. * * In addition, as a special exception, the Free Software Foundation * give you permission to combine GNU Smalltalk with free software * programs or libraries that are released under the GNU LGPL and with * independent programs running under the GNU Smalltalk virtual machine. * * You may copy and distribute such a system following the terms of the * GNU GPL for GNU Smalltalk and the licenses of the other code * concerned, provided that you include the source code of that other * code when and as the GNU GPL requires distribution of source code. * * Note that people who make modified versions of GNU Smalltalk are not * obligated to grant this special exception for their modified * versions; it is their choice whether to do so. The GNU General * Public License gives permission to release a modified version without * this exception; this exception also makes it possible to release a * modified version which carries forward this exception. * * GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or * FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for * more details. * * You should have received a copy of the GNU General Public License along with * GNU Smalltalk; see the file COPYING. If not, write to the Free Software * Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. ***********************************************************************/ #include "gstpriv.h" #define SMALL2FREE(B, N) ((heap_freeobj*)(((char *)(B)->vSmall.data) + (N)*(B)->size)) #define MEM2BLOCK(M) ((heap_block*)(((intptr_t)(M)) & -pagesize)) #define MEM2FREE(M) ((heap_freeobj*)(M)) #define BLOCKEND(B) ((heap_block*)(((unsigned char*)(B)) + (B)->size)) #define MAX_SMALL_OBJ_SIZE 16384 #define IS_SMALL_SIZE(S) ((S) <= max_small_object_size) #define MEMALIGN 8 #define ROUNDUPALIGN(V) (((intptr_t)(V) + MEMALIGN - 1) & -MEMALIGN) #define ROUNDUPPAGESIZE(V) (((intptr_t)(V) + pagesize - 1) & -pagesize) #define OBJECT_SIZE(M) (MEM2BLOCK(M)->size) #define MMAP_AREA_SIZE (sizeof (long) << 26) /* 256/512 Mb */ #define MMAP_THRESHOLD (sizeof (long) << 15) /* 128/256 kb */ /* Depending on the architecture, heap_block->vSmall.data could be counted as 1 or 4 bytes. This formula gets it right. */ #define offset_of(field, type) \ (((char *) &( ((type *) 8) -> field )) - (char *) 8) #define SMALL_OBJ_HEADER_SIZE offset_of (vSmall.data, heap_block) #define LARGE_OBJ_HEADER_SIZE offset_of (vLarge.data, heap_block) static void init_heap (heap_data *h, size_t heap_allocation_size, size_t heap_limit); #define vSmall var.small #define vLarge var.large #define vFree var.free static heap_block *heap_small_block (heap_data *h, size_t); static heap_block *heap_large_block (heap_data *h, size_t); static void heap_system_alloc (heap_data *h, size_t); static heap_block *heap_primitive_alloc (heap_data *h, size_t); static void heap_add_to_free_list (heap_data *h, heap_block *); static void heap_primitive_free (heap_data *h, heap_block *); static PTR morecore (size_t); /* This list was produced by this command echo 'for (i = (4072 + 7) / 32; i >= 1; i--) (4072 / i) / 32 * 32; 0' | bc | uniq | sed '$!s/$/,/' | fmt -60 for 32-bit machines, and similarly with 4064 instead of 4072 for 64-bit machines. 8 and 16 were added manually. */ static unsigned short freelist_size[NUM_FREELISTS + 1] = { 8, 16, 32, 64, 96, 128, 160, 192, 224, 256, 288, 320, 352, 384, 448, 480, 576, 672, 800, 992, 1344, 2016, 4096 - SMALL_OBJ_HEADER_SIZE, 8192 - SMALL_OBJ_HEADER_SIZE, 16384 - SMALL_OBJ_HEADER_SIZE, 0 }; static unsigned short sztable[MAX_SMALL_OBJ_SIZE + 1]; static heap_block *heap_prim_freelist = NULL; static size_t max_small_object_size; static size_t pagesize; /* Create a new memory heap */ heap_data * _gst_mem_new_heap (size_t heap_allocation_size, size_t heap_limit) { heap_data *h = (heap_data *) xcalloc (1, sizeof (*h)); init_heap (h, heap_allocation_size, heap_limit); return h; } /* Initialize a memory heap */ static void init_heap (heap_data *h, size_t heap_allocation_size, size_t heap_limit) { int sz; int i; if (!pagesize) { pagesize = getpagesize (); /* Use the preinitialized freelist table to initialize the sztable. */ for (sz = i = 0; freelist_size[i] > 0 && freelist_size[i] < pagesize; i++) for (; sz <= freelist_size[i]; sz++) sztable[sz] = i; max_small_object_size = sz - 1; } for (i = 0; freelist_size[i] > 0; i++) h->freelist[i] = NULL; h->heap_allocation_size = (heap_allocation_size ? ROUNDUPPAGESIZE (heap_allocation_size) : MMAP_THRESHOLD); h->heap_limit = heap_limit; h->mmap_count = 0; h->heap_total = 0; h->probes = h->splits = h->matches = h->failures = 0; h->after_allocating = NULL; h->after_prim_allocating = NULL; h->before_prim_freeing = NULL; h->nomemory = NULL; } /* _gst_mem_alloc Allocate a piece of memory. */ PTR _gst_mem_alloc (heap_data *h, size_t sz) { size_t lnr; heap_freeobj *mem; heap_block **mptr; heap_block *blk; size_t nsz; int times; times = 0; rerun: times++; if (IS_SMALL_SIZE (sz)) { /* Translate size to object free list */ sz = ROUNDUPALIGN (sz); lnr = sztable[sz]; nsz = freelist_size[lnr]; /* No available objects? Allocate some more */ mptr = &h->freelist[lnr]; blk = *mptr; if (!blk) { blk = heap_small_block (h, nsz); if (!blk) { nsz = pagesize; goto nospace; } #ifndef OPTIMIZE if (((intptr_t) blk) & (pagesize - 1)) abort (); #endif blk->vSmall.nfree = *mptr; *mptr = blk; } /* Unlink free one and return it */ mem = blk->vSmall.free; #ifndef OPTIMIZE if (!blk->vSmall.free || !blk->vSmall.avail) abort (); if (((intptr_t) mem <= (intptr_t) blk) || ((intptr_t) mem >= (intptr_t) blk + pagesize)) abort (); #endif blk->vSmall.free = mem->next; /* Once we use all the sub-blocks up, remove the whole block from the freelist. */ blk->vSmall.avail--; if (!blk->vSmall.free) *mptr = blk->vSmall.nfree; } else { nsz = sz; blk = heap_large_block (h, nsz); nsz += LARGE_OBJ_HEADER_SIZE; nsz = ROUNDUPPAGESIZE (nsz); if (blk == 0) goto nospace; mem = (heap_freeobj *) blk->vLarge.data; } #ifndef OPTIMIZE if (OBJECT_SIZE (mem) < sz) abort (); #endif if (h->after_allocating) h->after_allocating (h, blk, sz); return (mem); nospace: /* Failed to find space in any freelists. Must try to get the memory from somewhere. */ switch (times) { case 1: /* Try asking the program to free some memory, but only if it's worth doing. */ if (h->heap_limit && h->heap_total <= h->heap_limit && h->heap_total + nsz > h->heap_limit && h->nomemory) { h = h->nomemory (h, nsz); if (h) break; else return NULL; } case 2: /* Get from the system */ if (!h->heap_limit || h->heap_total < h->heap_limit) { if (nsz < h->heap_allocation_size) nsz = h->heap_allocation_size; heap_system_alloc (h, nsz); h->failures++; break; } default: return (NULL); } /* Try again */ goto rerun; } PTR _gst_mem_realloc (heap_data *h, PTR mem, size_t size) { heap_block *info; int pages_to_free; unsigned mmap_block; if (mem == NULL) return _gst_mem_alloc (h, size); if (size == 0) { _gst_mem_free (h, mem); return NULL; } info = MEM2BLOCK (mem); if (size > info->size) { PTR p; p = _gst_mem_alloc (h, size); memcpy (p, mem, info->size); _gst_mem_free (h, mem); return p; } if (IS_SMALL_SIZE (info->size)) return mem; mmap_block = info->mmap_block; pages_to_free = (info->size - size) / pagesize; if (!pages_to_free) return mem; info->size -= pages_to_free * pagesize; /* Split into a busy and a free block */ info = (heap_block *) &info->vLarge.data[info->size]; info->size = pages_to_free * pagesize; info->mmap_block = mmap_block; heap_primitive_free (h, info); return mem; } /* Free a piece of memory. */ void _gst_mem_free (heap_data *h, PTR mem) { heap_block *info; heap_freeobj *obj; int lnr; int msz; if (!mem) return; info = MEM2BLOCK (mem); msz = info->size; if (IS_SMALL_SIZE (msz)) { lnr = sztable[msz]; /* If this block contains no free sub-blocks yet, attach it to freelist. */ if (++info->vSmall.avail == 1) { #ifndef OPTIMIZE if ( ((intptr_t) info) & (pagesize - 1)) abort (); #endif info->vSmall.nfree = h->freelist[lnr]; h->freelist[lnr] = info; } obj = MEM2FREE (mem); obj->next = info->vSmall.free; info->vSmall.free = obj; #ifndef OPTIMIZE if ((intptr_t) obj < (intptr_t) info || (intptr_t) obj >= (intptr_t) info + pagesize || (intptr_t) obj == (intptr_t) (obj->next)) abort (); if (info->vSmall.avail > info->vSmall.nr) abort (); #endif /* If we free all sub-blocks, free the block */ if (info->vSmall.avail == info->vSmall.nr) { heap_block **finfo = &h->freelist[lnr]; for (;;) { if (*finfo == info) { (*finfo) = info->vSmall.nfree; info->size = pagesize; heap_primitive_free (h, info); break; } finfo = &(*finfo)->vSmall.nfree; #ifndef OPTIMIZE if (!*finfo) abort (); #endif } } } else { /* Calculate true size of block */ msz += LARGE_OBJ_HEADER_SIZE; msz = ROUNDUPPAGESIZE (msz); info->size = msz; h->mmap_count -= info->mmap_block; heap_primitive_free (h, info); } } /* Allocate a new block of memory. The block will contain 'nr' objects each of 'sz' bytes. */ static heap_block * heap_small_block (heap_data *h, size_t sz) { heap_block *info; int i; int nr; info = heap_primitive_alloc (h, pagesize); if (!info) return (NULL); /* Calculate number of objects in this block */ nr = (pagesize - SMALL_OBJ_HEADER_SIZE) / sz; /* Setup the meta-data for the block */ info->size = sz; info->vSmall.nr = nr; info->vSmall.avail = nr; /* Build the objects into a free list */ for (i = nr - 1; i >= 0; i--) SMALL2FREE (info, i)->next = SMALL2FREE (info, i + 1); SMALL2FREE (info, nr - 1)->next = 0; info->vSmall.free = SMALL2FREE (info, 0); return (info); } /* Allocate a new block of memory. The block will contain one object */ static heap_block * heap_large_block (heap_data *h, size_t sz) { heap_block *info; size_t msz; /* Add in management overhead */ msz = sz + LARGE_OBJ_HEADER_SIZE; /* Round size up to a number of pages */ msz = ROUNDUPPAGESIZE (msz); info = heap_primitive_alloc (h, msz); if (!info) return (NULL); info->size = msz - LARGE_OBJ_HEADER_SIZE; return (info); } /* Allocate a block of memory from the free list or, failing that, the system pool. */ static heap_block * heap_primitive_alloc (heap_data *h, size_t sz) { heap_block *ptr; heap_block **pptr; /* If we will pass the heap boundary, return 0 to indicate that we're run out. */ if (h->heap_limit && h->heap_total <= h->heap_limit && h->heap_total + sz > h->heap_limit) return (NULL); #ifndef OPTIMIZE if (sz & (pagesize - 1)) abort (); #endif if (sz > MMAP_THRESHOLD) { ptr = _gst_osmem_alloc (sz); if (ptr) { if (h->after_prim_allocating) h->after_prim_allocating (h, ptr, sz); h->heap_total += sz; h->mmap_count++; /* Setup the meta-data for the block */ ptr->mmap_block = 1; ptr->user = 0; ptr->size = sz; if (((intptr_t) ptr) & (pagesize - 1)) abort (); return ptr; } } for (pptr = &heap_prim_freelist; (ptr = *pptr); pptr = &(ptr->vFree.next)) { h->probes++; #ifndef OPTIMIZE if (((intptr_t) ptr) & (pagesize - 1)) abort (); if (ptr->size & (pagesize - 1)) abort (); #endif /* First fit */ if (sz <= ptr->size) { size_t left; /* If there's more than a page left, split it */ left = ptr->size - sz; if (left >= pagesize) { heap_block *nptr; ptr->size = sz; nptr = BLOCKEND (ptr); nptr->size = left; nptr->vFree.next = ptr->vFree.next; ptr->vFree.next = nptr; h->splits++; } else h->matches++; *pptr = ptr->vFree.next; ptr->mmap_block = 0; ptr->user = 0; h->heap_total += sz; if (h->after_prim_allocating) h->after_prim_allocating (h, ptr, sz); return (ptr); } } /* Nothing found on free list */ return (NULL); } /* Return a block of memory to the free list. */ static void heap_primitive_free (heap_data *h, heap_block *mem) { #ifndef OPTIMIZE if (mem->size & (pagesize - 1)) abort (); #endif if (h->before_prim_freeing) h->before_prim_freeing (h, mem, mem->size); h->heap_total -= mem->size; if (mem->mmap_block) { _gst_osmem_free (mem, mem->size); return; } heap_add_to_free_list (h, mem); } static void heap_add_to_free_list (heap_data *h, heap_block *mem) { heap_block *lptr; heap_block *nptr; #ifndef OPTIMIZE if (((intptr_t) mem) & (pagesize - 1)) abort (); if (mem->size & (pagesize - 1)) abort (); #endif if (mem < heap_prim_freelist || heap_prim_freelist == 0) { /* If this block is directly before the first block on the freelist, merge it into that block. Otherwise just attach it to the beginning. */ if (BLOCKEND (mem) == heap_prim_freelist) { mem->size += heap_prim_freelist->size; mem->vFree.next = heap_prim_freelist->vFree.next; } else mem->vFree.next = heap_prim_freelist; heap_prim_freelist = mem; return; } /* Search the freelist for the logical place to put this block */ lptr = heap_prim_freelist; while (lptr->vFree.next != 0) { #ifndef OPTIMIZE if (lptr->size & (pagesize - 1)) abort (); #endif nptr = lptr->vFree.next; if (mem > lptr && mem < nptr) { /* Block goes here in the logical scheme of things. Work out how to merge it with those which come before and after. */ if (BLOCKEND (lptr) == mem) { if (BLOCKEND (mem) == nptr) { /* Merge with last and next */ lptr->size += mem->size + nptr->size; lptr->vFree.next = nptr->vFree.next; } else /* Merge with last but not next */ lptr->size += mem->size; } else { if (BLOCKEND (mem) == nptr) { /* Merge with next but not last */ mem->size += nptr->size; mem->vFree.next = nptr->vFree.next; lptr->vFree.next = mem; } else { /* Wont merge with either */ mem->vFree.next = nptr; lptr->vFree.next = mem; } } return; } lptr = nptr; } /* If 'mem' goes directly after the last block, merge it in. Otherwise, just add in onto the list at the end. */ mem->vFree.next = NULL; if (BLOCKEND (lptr) == mem) lptr->size += mem->size; else lptr->vFree.next = mem; } static void heap_system_alloc (heap_data *h, size_t sz) { heap_block * mem; #ifndef OPTIMIZE if (sz & (pagesize - 1)) abort (); #endif mem = (heap_block *) morecore (sz); if (!mem) nomemory(1); mem->mmap_block = 0; mem->size = sz; /* Free block into the system */ heap_add_to_free_list (h, mem); } PTR morecore (size_t size) { heap just_allocated_heap = NULL; /* _gst_heap_sbrk is actually the same as sbrk as long as current_heap is NULL. But we cannot do that unless we can replace malloc (which we cannot do on MacOS X, see above). */ static heap current_heap = NULL; if (current_heap == NULL) { just_allocated_heap = _gst_heap_create (NULL, MMAP_AREA_SIZE); if (!just_allocated_heap) return (NULL); current_heap = just_allocated_heap; } for (;;) { char *ptr = _gst_heap_sbrk (current_heap, size); if (ptr != NULL) { if (((intptr_t) ptr & (pagesize - 1)) > 0) { /* Oops, we have to align to a page. */ int missed = pagesize - ((intptr_t) ptr & (pagesize - 1)); _gst_heap_sbrk (current_heap, -size + missed); ptr = _gst_heap_sbrk (current_heap, size); } if (ptr != NULL) return (ptr); } /* The data segment we're using might bang against an mmap-ed area (the sbrk segment for example cannot grow more than 960M on Linux). We try using a new mmap-ed area, but be careful not to loop! */ if (just_allocated_heap) return (NULL); just_allocated_heap = _gst_heap_create (NULL, MMAP_AREA_SIZE); if (!just_allocated_heap) return (NULL); current_heap = just_allocated_heap; } } char * xstrdup (const char *str) { int length = strlen (str) + 1; char *newstr = (char *) xmalloc (length); memcpy(newstr, str, length); return (newstr); } PTR xmalloc (size_t n) { PTR block; block = malloc(n); if (!block && n) nomemory(1); return (block); } PTR xcalloc (size_t n, size_t s) { PTR block; block = calloc(n, s); if (!block && n && s) nomemory(1); return (block); } PTR xrealloc (PTR p, size_t n) { PTR block; block = realloc(p, n); if (!block && n) nomemory(1); return (block); } void xfree (PTR p) { if (p) free(p); } void nomemory (int fatal) { fputs ("\n\n[Memory allocation failure]" "\nCan't allocate enough memory to continue.\n", stderr); if (fatal) exit (1); } smalltalk-3.2.5/libgst/print.h0000644000175000017500000000712112123404352013214 00000000000000/******************************** -*- C -*- **************************** * * OOP printing and debugging declarations * * ***********************************************************************/ /*********************************************************************** * * Copyright 1988,89,90,91,92,94,95,99,2000,2001,2002,2006 * Free Software Foundation, Inc. * Written by Steve Byrne. * * This file is part of GNU Smalltalk. * * GNU Smalltalk is free software; you can redistribute it and/or modify it * under the terms of the GNU General Public License as published by the Free * Software Foundation; either version 2, or (at your option) any later * version. * * Linking GNU Smalltalk statically or dynamically with other modules is * making a combined work based on GNU Smalltalk. Thus, the terms and * conditions of the GNU General Public License cover the whole * combination. * * In addition, as a special exception, the Free Software Foundation * give you permission to combine GNU Smalltalk with free software * programs or libraries that are released under the GNU LGPL and with * independent programs running under the GNU Smalltalk virtual machine. * * You may copy and distribute such a system following the terms of the * GNU GPL for GNU Smalltalk and the licenses of the other code * concerned, provided that you include the source code of that other * code when and as the GNU GPL requires distribution of source code. * * Note that people who make modified versions of GNU Smalltalk are not * obligated to grant this special exception for their modified * versions; it is their choice whether to do so. The GNU General * Public License gives permission to release a modified version without * this exception; this exception also makes it possible to release a * modified version which carries forward this exception. * * GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or * FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for * more details. * * You should have received a copy of the GNU General Public License along with * GNU Smalltalk; see the file COPYING. If not, write to the Free Software * Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * ***********************************************************************/ #ifndef GST_PRINT_H #define GST_PRINT_H /* Print a representation of OOP on stdout. For Strings, Symbols, Floats and SmallIntegers, this is the #storeString; for other objects it is a generic representation including the pointer to the OOP. */ extern void _gst_print_object (OOP oop) ATTRIBUTE_HIDDEN; /* Show information about the contents of the pointer ADDR, deciding what kind of Smalltalk entity it is. Mainly provided for debugging. */ void _gst_classify_addr (void *addr) ATTRIBUTE_HIDDEN; /* Show information about the contents of the given OOP. Mainly provided for debugging. */ void _gst_display_oop (OOP oop) ATTRIBUTE_HIDDEN; /* Show information about the contents of the given OOP without dereferencing the pointer to the object data and to the class. Mainly provided for debugging. */ void _gst_display_oop_short (OOP oop) ATTRIBUTE_HIDDEN; /* Show information about the contents of the OBJ object. Mainly provided for debugging. */ void _gst_display_object (gst_object obj) ATTRIBUTE_HIDDEN; /* Initialize the snprintfv library with hooks to print GNU Smalltalk OOPs. */ extern void _gst_init_snprintfv () ATTRIBUTE_HIDDEN; #endif /* GST_OOP_H */ smalltalk-3.2.5/libgst/genbc-decl.c0000644000175000017500000017313112130455565014055 00000000000000/* A Bison parser, made by GNU Bison 2.5. */ /* Bison implementation for Yacc-like parsers in C Copyright (C) 1984, 1989-1990, 2000-2011 Free Software Foundation, Inc. This program is free software: you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation, either version 3 of the License, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program. If not, see . */ /* As a special exception, you may create a larger work that contains part or all of the Bison parser skeleton and distribute that work under terms of your choice, so long as that work isn't itself a parser generator using the skeleton or a modified version thereof as a parser skeleton. Alternatively, if you modify or redistribute the parser skeleton itself, you may (at your option) remove this special exception, which will cause the skeleton and the resulting Bison output files to be licensed under the GNU General Public License without this special exception. This special exception was added by the Free Software Foundation in version 2.2 of Bison. */ /* C LALR(1) parser skeleton written by Richard Stallman, by simplifying the original so-called "semantic" parser. */ /* All symbols defined below should begin with yy or YY, to avoid infringing on user name space. This should be done even for local variables, as they might otherwise be expanded by user macros. There are some unavoidable exceptions within include files to define necessary library symbols; they are noted "INFRINGES ON USER NAME SPACE" below. */ /* Identify Bison output. */ #define YYBISON 1 /* Bison version. */ #define YYBISON_VERSION "2.5" /* Skeleton name. */ #define YYSKELETON_NAME "yacc.c" /* Pure parsers. */ #define YYPURE 0 /* Push parsers. */ #define YYPUSH 0 /* Pull parsers. */ #define YYPULL 1 /* Using locations. */ #define YYLSP_NEEDED 0 /* Copy the first part of user declarations. */ /* Line 268 of yacc.c */ #line 55 "genbc-decl.y" #include "genbc.h" #include "avltrees.h" #define yyparse decl_yyparse #define yydebug decl_yydebug #define YYERROR_VERBOSE #define YYPRINT yyprint typedef struct bytecode_info { avl_node_t avl; const char *name; struct field_info *fields; } bytecode_info; typedef struct field_info { struct field_info *next, **pnext; const char *name; } field_info; typedef struct var_info { avl_node_t avl; const char *name; } var_info; typedef struct opcode { struct opcode *next; int first; int last; char *code; } opcode; static void define_decl (int first, int last, char *code); static void define_bytecode (const char *id, field_info *fields); static void define_var (const char *id); static void define_field (const char *id, int bits); static char *extraction_code (int bits); static void emit_var_names (var_info *node, const char *prefix, const char *suffix, const char *next_prefix); static int filprintf (Filament *fil, const char *format, ...); static bytecode_info *get_bytecode (const char *name); int curr_bit_offset = 0, synthetic = 256; bytecode_info *bytecode_root, *curr_bytecode; field_info *curr_field; var_info *var_root; opcode *first = NULL, **p_next = &first; Filament *curr_fil; char *begin_code, *end_code; /* Line 268 of yacc.c */ #line 123 "genbc-decl.c" /* Enabling traces. */ #ifndef YYDEBUG # define YYDEBUG 1 #endif /* Enabling verbose error messages. */ #ifdef YYERROR_VERBOSE # undef YYERROR_VERBOSE # define YYERROR_VERBOSE 1 #else # define YYERROR_VERBOSE 0 #endif /* Enabling the token table. */ #ifndef YYTOKEN_TABLE # define YYTOKEN_TABLE 0 #endif /* Tokens. */ #ifndef YYTOKENTYPE # define YYTOKENTYPE /* Put the tokens into the symbol table, so that GDB and other debuggers know about them. */ enum yytokentype { MATCH_BYTECODES = 258, DECL_BEGIN = 259, DECL_END = 260, DECL_BREAK = 261, DECL_CONTINUE = 262, DECL_DISPATCH = 263, DECL_EXTRACT = 264, DECL_DOTS = 265, NUMBER = 266, ID = 267, EXPR = 268 }; #endif /* Tokens. */ #define MATCH_BYTECODES 258 #define DECL_BEGIN 259 #define DECL_END 260 #define DECL_BREAK 261 #define DECL_CONTINUE 262 #define DECL_DISPATCH 263 #define DECL_EXTRACT 264 #define DECL_DOTS 265 #define NUMBER 266 #define ID 267 #define EXPR 268 #if ! defined YYSTYPE && ! defined YYSTYPE_IS_DECLARED typedef union YYSTYPE { /* Line 293 of yacc.c */ #line 110 "genbc-decl.y" struct field_info *field; const char *ctext; char *text; int num; /* Line 293 of yacc.c */ #line 194 "genbc-decl.c" } YYSTYPE; # define YYSTYPE_IS_TRIVIAL 1 # define yystype YYSTYPE /* obsolescent; will be withdrawn */ # define YYSTYPE_IS_DECLARED 1 #endif /* Copy the second part of user declarations. */ /* Line 343 of yacc.c */ #line 206 "genbc-decl.c" #ifdef short # undef short #endif #ifdef YYTYPE_UINT8 typedef YYTYPE_UINT8 yytype_uint8; #else typedef unsigned char yytype_uint8; #endif #ifdef YYTYPE_INT8 typedef YYTYPE_INT8 yytype_int8; #elif (defined __STDC__ || defined __C99__FUNC__ \ || defined __cplusplus || defined _MSC_VER) typedef signed char yytype_int8; #else typedef short int yytype_int8; #endif #ifdef YYTYPE_UINT16 typedef YYTYPE_UINT16 yytype_uint16; #else typedef unsigned short int yytype_uint16; #endif #ifdef YYTYPE_INT16 typedef YYTYPE_INT16 yytype_int16; #else typedef short int yytype_int16; #endif #ifndef YYSIZE_T # ifdef __SIZE_TYPE__ # define YYSIZE_T __SIZE_TYPE__ # elif defined size_t # define YYSIZE_T size_t # elif ! defined YYSIZE_T && (defined __STDC__ || defined __C99__FUNC__ \ || defined __cplusplus || defined _MSC_VER) # include /* INFRINGES ON USER NAME SPACE */ # define YYSIZE_T size_t # else # define YYSIZE_T unsigned int # endif #endif #define YYSIZE_MAXIMUM ((YYSIZE_T) -1) #ifndef YY_ # if defined YYENABLE_NLS && YYENABLE_NLS # if ENABLE_NLS # include /* INFRINGES ON USER NAME SPACE */ # define YY_(msgid) dgettext ("bison-runtime", msgid) # endif # endif # ifndef YY_ # define YY_(msgid) msgid # endif #endif /* Suppress unused-variable warnings by "using" E. */ #if ! defined lint || defined __GNUC__ # define YYUSE(e) ((void) (e)) #else # define YYUSE(e) /* empty */ #endif /* Identity function, used to suppress warnings about constant conditions. */ #ifndef lint # define YYID(n) (n) #else #if (defined __STDC__ || defined __C99__FUNC__ \ || defined __cplusplus || defined _MSC_VER) static int YYID (int yyi) #else static int YYID (yyi) int yyi; #endif { return yyi; } #endif #if ! defined yyoverflow || YYERROR_VERBOSE /* The parser invokes alloca or malloc; define the necessary symbols. */ # ifdef YYSTACK_USE_ALLOCA # if YYSTACK_USE_ALLOCA # ifdef __GNUC__ # define YYSTACK_ALLOC __builtin_alloca # elif defined __BUILTIN_VA_ARG_INCR # include /* INFRINGES ON USER NAME SPACE */ # elif defined _AIX # define YYSTACK_ALLOC __alloca # elif defined _MSC_VER # include /* INFRINGES ON USER NAME SPACE */ # define alloca _alloca # else # define YYSTACK_ALLOC alloca # if ! defined _ALLOCA_H && ! defined EXIT_SUCCESS && (defined __STDC__ || defined __C99__FUNC__ \ || defined __cplusplus || defined _MSC_VER) # include /* INFRINGES ON USER NAME SPACE */ # ifndef EXIT_SUCCESS # define EXIT_SUCCESS 0 # endif # endif # endif # endif # endif # ifdef YYSTACK_ALLOC /* Pacify GCC's `empty if-body' warning. */ # define YYSTACK_FREE(Ptr) do { /* empty */; } while (YYID (0)) # ifndef YYSTACK_ALLOC_MAXIMUM /* The OS might guarantee only one guard page at the bottom of the stack, and a page size can be as small as 4096 bytes. So we cannot safely invoke alloca (N) if N exceeds 4096. Use a slightly smaller number to allow for a few compiler-allocated temporary stack slots. */ # define YYSTACK_ALLOC_MAXIMUM 4032 /* reasonable circa 2006 */ # endif # else # define YYSTACK_ALLOC YYMALLOC # define YYSTACK_FREE YYFREE # ifndef YYSTACK_ALLOC_MAXIMUM # define YYSTACK_ALLOC_MAXIMUM YYSIZE_MAXIMUM # endif # if (defined __cplusplus && ! defined EXIT_SUCCESS \ && ! ((defined YYMALLOC || defined malloc) \ && (defined YYFREE || defined free))) # include /* INFRINGES ON USER NAME SPACE */ # ifndef EXIT_SUCCESS # define EXIT_SUCCESS 0 # endif # endif # ifndef YYMALLOC # define YYMALLOC malloc # if ! defined malloc && ! defined EXIT_SUCCESS && (defined __STDC__ || defined __C99__FUNC__ \ || defined __cplusplus || defined _MSC_VER) void *malloc (YYSIZE_T); /* INFRINGES ON USER NAME SPACE */ # endif # endif # ifndef YYFREE # define YYFREE free # if ! defined free && ! defined EXIT_SUCCESS && (defined __STDC__ || defined __C99__FUNC__ \ || defined __cplusplus || defined _MSC_VER) void free (void *); /* INFRINGES ON USER NAME SPACE */ # endif # endif # endif #endif /* ! defined yyoverflow || YYERROR_VERBOSE */ #if (! defined yyoverflow \ && (! defined __cplusplus \ || (defined YYSTYPE_IS_TRIVIAL && YYSTYPE_IS_TRIVIAL))) /* A type that is properly aligned for any stack member. */ union yyalloc { yytype_int16 yyss_alloc; YYSTYPE yyvs_alloc; }; /* The size of the maximum gap between one aligned stack and the next. */ # define YYSTACK_GAP_MAXIMUM (sizeof (union yyalloc) - 1) /* The size of an array large to enough to hold all stacks, each with N elements. */ # define YYSTACK_BYTES(N) \ ((N) * (sizeof (yytype_int16) + sizeof (YYSTYPE)) \ + YYSTACK_GAP_MAXIMUM) # define YYCOPY_NEEDED 1 /* Relocate STACK from its old location to the new one. The local variables YYSIZE and YYSTACKSIZE give the old and new number of elements in the stack, and YYPTR gives the new location of the stack. Advance YYPTR to a properly aligned location for the next stack. */ # define YYSTACK_RELOCATE(Stack_alloc, Stack) \ do \ { \ YYSIZE_T yynewbytes; \ YYCOPY (&yyptr->Stack_alloc, Stack, yysize); \ Stack = &yyptr->Stack_alloc; \ yynewbytes = yystacksize * sizeof (*Stack) + YYSTACK_GAP_MAXIMUM; \ yyptr += yynewbytes / sizeof (*yyptr); \ } \ while (YYID (0)) #endif #if defined YYCOPY_NEEDED && YYCOPY_NEEDED /* Copy COUNT objects from FROM to TO. The source and destination do not overlap. */ # ifndef YYCOPY # if defined __GNUC__ && 1 < __GNUC__ # define YYCOPY(To, From, Count) \ __builtin_memcpy (To, From, (Count) * sizeof (*(From))) # else # define YYCOPY(To, From, Count) \ do \ { \ YYSIZE_T yyi; \ for (yyi = 0; yyi < (Count); yyi++) \ (To)[yyi] = (From)[yyi]; \ } \ while (YYID (0)) # endif # endif #endif /* !YYCOPY_NEEDED */ /* YYFINAL -- State number of the termination state. */ #define YYFINAL 13 /* YYLAST -- Last index in YYTABLE. */ #define YYLAST 75 /* YYNTOKENS -- Number of terminals. */ #define YYNTOKENS 21 /* YYNNTS -- Number of nonterminals. */ #define YYNNTS 24 /* YYNRULES -- Number of rules. */ #define YYNRULES 47 /* YYNRULES -- Number of states. */ #define YYNSTATES 73 /* YYTRANSLATE(YYLEX) -- Bison symbol number corresponding to YYLEX. */ #define YYUNDEFTOK 2 #define YYMAXUTOK 268 #define YYTRANSLATE(YYX) \ ((unsigned int) (YYX) <= YYMAXUTOK ? yytranslate[YYX] : YYUNDEFTOK) /* YYTRANSLATE[YYLEX] -- Bison symbol number corresponding to YYLEX. */ static const yytype_uint8 yytranslate[] = { 0, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 17, 18, 2, 2, 19, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 14, 2, 20, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 15, 2, 16, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 1, 2, 3, 4, 5, 6, 7, 8, 9, 10, 11, 12, 13 }; #if YYDEBUG /* YYPRHS[YYN] -- Index of the first RHS symbol of rule number YYN in YYRHS. */ static const yytype_uint8 yyprhs[] = { 0, 0, 3, 6, 8, 12, 17, 22, 27, 34, 38, 39, 43, 45, 46, 49, 52, 53, 55, 56, 61, 63, 65, 67, 70, 71, 73, 75, 76, 79, 82, 83, 85, 87, 89, 90, 95, 98, 102, 103, 107, 109, 110, 113, 117, 118, 122, 124 }; /* YYRHS -- A `-1'-separated list of the rules' RHS. */ static const yytype_int8 yyrhs[] = { 22, 0, -1, 22, 23, -1, 23, -1, 12, 24, 14, -1, 4, 15, 26, 16, -1, 5, 15, 26, 16, -1, 11, 15, 33, 16, -1, 11, 10, 11, 15, 33, 16, -1, 17, 25, 18, -1, -1, 25, 19, 12, -1, 12, -1, -1, 27, 31, -1, 28, 29, -1, -1, 20, -1, -1, 17, 30, 31, 18, -1, 12, -1, 11, -1, 13, -1, 31, 32, -1, -1, 29, -1, 19, -1, -1, 34, 35, -1, 35, 36, -1, -1, 32, -1, 6, -1, 7, -1, -1, 8, 12, 37, 38, -1, 9, 43, -1, 17, 39, 18, -1, -1, 39, 19, 40, -1, 40, -1, -1, 41, 28, -1, 17, 11, 18, -1, -1, 43, 19, 44, -1, 44, -1, 12, 42, -1 }; /* YYRLINE[YYN] -- source line where rule number YYN was defined. */ static const yytype_uint16 yyrline[] = { 0, 139, 139, 140, 144, 146, 148, 150, 152, 157, 160, 164, 173, 184, 184, 190, 191, 194, 197, 196, 200, 202, 204, 209, 210, 213, 214, 219, 219, 226, 227, 230, 231, 233, 236, 235, 256, 265, 266, 270, 271, 275, 275, 288, 289, 293, 294, 298 }; #endif #if YYDEBUG || YYERROR_VERBOSE || YYTOKEN_TABLE /* YYTNAME[SYMBOL-NUM] -- String name of the symbol SYMBOL-NUM. First, the terminals, then, starting at YYNTOKENS, nonterminals. */ static const char *const yytname[] = { "$end", "error", "$undefined", "\"MATCH_BYTECODES\"", "\"BEGIN\"", "\"END\"", "\"break\"", "\"continue\"", "\"dispatch\"", "\"extract\"", "\"..\"", "\"number\"", "\"identifier\"", "\"expression\"", "';'", "'{'", "'}'", "'('", "')'", "','", "'='", "$accept", "decls", "decl", "opt_field_list", "field_list", "c_code", "$@1", "c_code_expr_body", "c_code_expr_item", "$@2", "c_code_body", "c_code_item", "code", "$@3", "code_body", "code_item", "$@4", "opt_dispatch_args", "dispatch_args", "dispatch_arg", "$@5", "opt_size", "bitfields", "bitfield", 0 }; #endif # ifdef YYPRINT /* YYTOKNUM[YYLEX-NUM] -- Internal token number corresponding to token YYLEX-NUM. */ static const yytype_uint16 yytoknum[] = { 0, 256, 257, 258, 259, 260, 261, 262, 263, 264, 265, 266, 267, 268, 59, 123, 125, 40, 41, 44, 61 }; # endif /* YYR1[YYN] -- Symbol number of symbol that rule YYN derives. */ static const yytype_uint8 yyr1[] = { 0, 21, 22, 22, 23, 23, 23, 23, 23, 24, 24, 25, 25, 27, 26, 28, 28, 29, 30, 29, 29, 29, 29, 31, 31, 32, 32, 34, 33, 35, 35, 36, 36, 36, 37, 36, 36, 38, 38, 39, 39, 41, 40, 42, 42, 43, 43, 44 }; /* YYR2[YYN] -- Number of symbols composing right hand side of rule YYN. */ static const yytype_uint8 yyr2[] = { 0, 2, 2, 1, 3, 4, 4, 4, 6, 3, 0, 3, 1, 0, 2, 2, 0, 1, 0, 4, 1, 1, 1, 2, 0, 1, 1, 0, 2, 2, 0, 1, 1, 1, 0, 4, 2, 3, 0, 3, 1, 0, 2, 3, 0, 3, 1, 2 }; /* YYDEFACT[STATE-NAME] -- Default reduction number in state STATE-NUM. Performed when YYTABLE doesn't specify something else to do. Zero means the default is an error. */ static const yytype_uint8 yydefact[] = { 0, 0, 0, 0, 10, 0, 3, 13, 13, 0, 27, 0, 0, 1, 2, 0, 24, 0, 0, 0, 30, 12, 0, 4, 5, 14, 6, 27, 7, 28, 9, 0, 21, 20, 22, 18, 26, 17, 25, 23, 0, 32, 33, 0, 0, 31, 29, 11, 24, 8, 34, 44, 36, 46, 0, 38, 0, 47, 0, 19, 41, 35, 0, 45, 0, 40, 16, 43, 37, 41, 42, 39, 15 }; /* YYDEFGOTO[NTERM-NUM]. */ static const yytype_int8 yydefgoto[] = { -1, 5, 6, 12, 22, 15, 16, 70, 38, 48, 25, 39, 19, 20, 29, 46, 55, 61, 64, 65, 66, 57, 52, 53 }; /* YYPACT[STATE-NUM] -- Index in YYTABLE of the portion describing STATE-NUM. */ #define YYPACT_NINF -8 static const yytype_int8 yypact[] = { 36, -5, -3, 34, 5, 4, -8, -8, -8, 21, -8, 22, 28, -8, -8, 29, -8, 35, 37, 38, -8, -8, 2, -8, -8, 16, -8, -8, -8, -6, -8, 41, -8, -8, -8, -8, -8, -8, -8, -8, 39, -8, -8, 44, 45, -8, -8, -8, -8, -8, -8, 33, 40, -8, 6, 43, 47, -8, 45, -8, -8, -8, 46, -8, 12, -8, -8, -8, -8, -8, 26, -8, -8 }; /* YYPGOTO[NTERM-NUM]. */ static const yytype_int8 yypgoto[] = { -8, -8, 56, -8, -8, 54, -8, -8, -7, -8, 17, 42, 48, -8, -8, -8, -8, -8, -8, -2, -8, -8, -8, 8 }; /* YYTABLE[YYPACT[STATE-NUM]]. What to do in state STATE-NUM. If positive, shift that token. If negative, reduce the rule which number is the opposite. If YYTABLE_NINF, syntax error. */ #define YYTABLE_NINF -1 static const yytype_uint8 yytable[] = { 41, 42, 43, 44, 13, 32, 33, 34, 1, 2, 7, 35, 8, 36, 37, 3, 4, 32, 33, 34, 30, 31, 11, 35, 59, 36, 37, 32, 33, 34, 68, 69, 18, 35, 21, 36, 37, 32, 33, 34, 1, 2, 23, 35, 9, 24, 37, 3, 4, 10, 56, 26, 27, 47, 28, 49, 50, 51, 62, 58, 60, 14, 17, 72, 67, 54, 63, 71, 0, 0, 0, 45, 0, 0, 0, 40 }; #define yypact_value_is_default(yystate) \ ((yystate) == (-8)) #define yytable_value_is_error(yytable_value) \ YYID (0) static const yytype_int8 yycheck[] = { 6, 7, 8, 9, 0, 11, 12, 13, 4, 5, 15, 17, 15, 19, 20, 11, 12, 11, 12, 13, 18, 19, 17, 17, 18, 19, 20, 11, 12, 13, 18, 19, 11, 17, 12, 19, 20, 11, 12, 13, 4, 5, 14, 17, 10, 16, 20, 11, 12, 15, 17, 16, 15, 12, 16, 16, 12, 12, 11, 19, 17, 5, 8, 70, 18, 48, 58, 69, -1, -1, -1, 29, -1, -1, -1, 27 }; /* YYSTOS[STATE-NUM] -- The (internal number of the) accessing symbol of state STATE-NUM. */ static const yytype_uint8 yystos[] = { 0, 4, 5, 11, 12, 22, 23, 15, 15, 10, 15, 17, 24, 0, 23, 26, 27, 26, 11, 33, 34, 12, 25, 14, 16, 31, 16, 15, 16, 35, 18, 19, 11, 12, 13, 17, 19, 20, 29, 32, 33, 6, 7, 8, 9, 32, 36, 12, 30, 16, 12, 12, 43, 44, 31, 37, 17, 42, 19, 18, 17, 38, 11, 44, 39, 40, 41, 18, 18, 19, 28, 40, 29 }; #define yyerrok (yyerrstatus = 0) #define yyclearin (yychar = YYEMPTY) #define YYEMPTY (-2) #define YYEOF 0 #define YYACCEPT goto yyacceptlab #define YYABORT goto yyabortlab #define YYERROR goto yyerrorlab /* Like YYERROR except do call yyerror. This remains here temporarily to ease the transition to the new meaning of YYERROR, for GCC. Once GCC version 2 has supplanted version 1, this can go. However, YYFAIL appears to be in use. Nevertheless, it is formally deprecated in Bison 2.4.2's NEWS entry, where a plan to phase it out is discussed. */ #define YYFAIL goto yyerrlab #if defined YYFAIL /* This is here to suppress warnings from the GCC cpp's -Wunused-macros. Normally we don't worry about that warning, but some users do, and we want to make it easy for users to remove YYFAIL uses, which will produce warnings from Bison 2.5. */ #endif #define YYRECOVERING() (!!yyerrstatus) #define YYBACKUP(Token, Value) \ do \ if (yychar == YYEMPTY && yylen == 1) \ { \ yychar = (Token); \ yylval = (Value); \ YYPOPSTACK (1); \ goto yybackup; \ } \ else \ { \ yyerror (YY_("syntax error: cannot back up")); \ YYERROR; \ } \ while (YYID (0)) #define YYTERROR 1 #define YYERRCODE 256 /* YYLLOC_DEFAULT -- Set CURRENT to span from RHS[1] to RHS[N]. If N is 0, then set CURRENT to the empty location which ends the previous symbol: RHS[0] (always defined). */ #define YYRHSLOC(Rhs, K) ((Rhs)[K]) #ifndef YYLLOC_DEFAULT # define YYLLOC_DEFAULT(Current, Rhs, N) \ do \ if (YYID (N)) \ { \ (Current).first_line = YYRHSLOC (Rhs, 1).first_line; \ (Current).first_column = YYRHSLOC (Rhs, 1).first_column; \ (Current).last_line = YYRHSLOC (Rhs, N).last_line; \ (Current).last_column = YYRHSLOC (Rhs, N).last_column; \ } \ else \ { \ (Current).first_line = (Current).last_line = \ YYRHSLOC (Rhs, 0).last_line; \ (Current).first_column = (Current).last_column = \ YYRHSLOC (Rhs, 0).last_column; \ } \ while (YYID (0)) #endif /* This macro is provided for backward compatibility. */ #ifndef YY_LOCATION_PRINT # define YY_LOCATION_PRINT(File, Loc) ((void) 0) #endif /* YYLEX -- calling `yylex' with the right arguments. */ #ifdef YYLEX_PARAM # define YYLEX yylex (YYLEX_PARAM) #else # define YYLEX yylex () #endif /* Enable debugging if requested. */ #if YYDEBUG # ifndef YYFPRINTF # include /* INFRINGES ON USER NAME SPACE */ # define YYFPRINTF fprintf # endif # define YYDPRINTF(Args) \ do { \ if (yydebug) \ YYFPRINTF Args; \ } while (YYID (0)) # define YY_SYMBOL_PRINT(Title, Type, Value, Location) \ do { \ if (yydebug) \ { \ YYFPRINTF (stderr, "%s ", Title); \ yy_symbol_print (stderr, \ Type, Value); \ YYFPRINTF (stderr, "\n"); \ } \ } while (YYID (0)) /*--------------------------------. | Print this symbol on YYOUTPUT. | `--------------------------------*/ /*ARGSUSED*/ #if (defined __STDC__ || defined __C99__FUNC__ \ || defined __cplusplus || defined _MSC_VER) static void yy_symbol_value_print (FILE *yyoutput, int yytype, YYSTYPE const * const yyvaluep) #else static void yy_symbol_value_print (yyoutput, yytype, yyvaluep) FILE *yyoutput; int yytype; YYSTYPE const * const yyvaluep; #endif { if (!yyvaluep) return; # ifdef YYPRINT if (yytype < YYNTOKENS) YYPRINT (yyoutput, yytoknum[yytype], *yyvaluep); # else YYUSE (yyoutput); # endif switch (yytype) { default: break; } } /*--------------------------------. | Print this symbol on YYOUTPUT. | `--------------------------------*/ #if (defined __STDC__ || defined __C99__FUNC__ \ || defined __cplusplus || defined _MSC_VER) static void yy_symbol_print (FILE *yyoutput, int yytype, YYSTYPE const * const yyvaluep) #else static void yy_symbol_print (yyoutput, yytype, yyvaluep) FILE *yyoutput; int yytype; YYSTYPE const * const yyvaluep; #endif { if (yytype < YYNTOKENS) YYFPRINTF (yyoutput, "token %s (", yytname[yytype]); else YYFPRINTF (yyoutput, "nterm %s (", yytname[yytype]); yy_symbol_value_print (yyoutput, yytype, yyvaluep); YYFPRINTF (yyoutput, ")"); } /*------------------------------------------------------------------. | yy_stack_print -- Print the state stack from its BOTTOM up to its | | TOP (included). | `------------------------------------------------------------------*/ #if (defined __STDC__ || defined __C99__FUNC__ \ || defined __cplusplus || defined _MSC_VER) static void yy_stack_print (yytype_int16 *yybottom, yytype_int16 *yytop) #else static void yy_stack_print (yybottom, yytop) yytype_int16 *yybottom; yytype_int16 *yytop; #endif { YYFPRINTF (stderr, "Stack now"); for (; yybottom <= yytop; yybottom++) { int yybot = *yybottom; YYFPRINTF (stderr, " %d", yybot); } YYFPRINTF (stderr, "\n"); } # define YY_STACK_PRINT(Bottom, Top) \ do { \ if (yydebug) \ yy_stack_print ((Bottom), (Top)); \ } while (YYID (0)) /*------------------------------------------------. | Report that the YYRULE is going to be reduced. | `------------------------------------------------*/ #if (defined __STDC__ || defined __C99__FUNC__ \ || defined __cplusplus || defined _MSC_VER) static void yy_reduce_print (YYSTYPE *yyvsp, int yyrule) #else static void yy_reduce_print (yyvsp, yyrule) YYSTYPE *yyvsp; int yyrule; #endif { int yynrhs = yyr2[yyrule]; int yyi; unsigned long int yylno = yyrline[yyrule]; YYFPRINTF (stderr, "Reducing stack by rule %d (line %lu):\n", yyrule - 1, yylno); /* The symbols being reduced. */ for (yyi = 0; yyi < yynrhs; yyi++) { YYFPRINTF (stderr, " $%d = ", yyi + 1); yy_symbol_print (stderr, yyrhs[yyprhs[yyrule] + yyi], &(yyvsp[(yyi + 1) - (yynrhs)]) ); YYFPRINTF (stderr, "\n"); } } # define YY_REDUCE_PRINT(Rule) \ do { \ if (yydebug) \ yy_reduce_print (yyvsp, Rule); \ } while (YYID (0)) /* Nonzero means print parse trace. It is left uninitialized so that multiple parsers can coexist. */ int yydebug; #else /* !YYDEBUG */ # define YYDPRINTF(Args) # define YY_SYMBOL_PRINT(Title, Type, Value, Location) # define YY_STACK_PRINT(Bottom, Top) # define YY_REDUCE_PRINT(Rule) #endif /* !YYDEBUG */ /* YYINITDEPTH -- initial size of the parser's stacks. */ #ifndef YYINITDEPTH # define YYINITDEPTH 200 #endif /* YYMAXDEPTH -- maximum size the stacks can grow to (effective only if the built-in stack extension method is used). Do not make this value too large; the results are undefined if YYSTACK_ALLOC_MAXIMUM < YYSTACK_BYTES (YYMAXDEPTH) evaluated with infinite-precision integer arithmetic. */ #ifndef YYMAXDEPTH # define YYMAXDEPTH 10000 #endif #if YYERROR_VERBOSE # ifndef yystrlen # if defined __GLIBC__ && defined _STRING_H # define yystrlen strlen # else /* Return the length of YYSTR. */ #if (defined __STDC__ || defined __C99__FUNC__ \ || defined __cplusplus || defined _MSC_VER) static YYSIZE_T yystrlen (const char *yystr) #else static YYSIZE_T yystrlen (yystr) const char *yystr; #endif { YYSIZE_T yylen; for (yylen = 0; yystr[yylen]; yylen++) continue; return yylen; } # endif # endif # ifndef yystpcpy # if defined __GLIBC__ && defined _STRING_H && defined _GNU_SOURCE # define yystpcpy stpcpy # else /* Copy YYSRC to YYDEST, returning the address of the terminating '\0' in YYDEST. */ #if (defined __STDC__ || defined __C99__FUNC__ \ || defined __cplusplus || defined _MSC_VER) static char * yystpcpy (char *yydest, const char *yysrc) #else static char * yystpcpy (yydest, yysrc) char *yydest; const char *yysrc; #endif { char *yyd = yydest; const char *yys = yysrc; while ((*yyd++ = *yys++) != '\0') continue; return yyd - 1; } # endif # endif # ifndef yytnamerr /* Copy to YYRES the contents of YYSTR after stripping away unnecessary quotes and backslashes, so that it's suitable for yyerror. The heuristic is that double-quoting is unnecessary unless the string contains an apostrophe, a comma, or backslash (other than backslash-backslash). YYSTR is taken from yytname. If YYRES is null, do not copy; instead, return the length of what the result would have been. */ static YYSIZE_T yytnamerr (char *yyres, const char *yystr) { if (*yystr == '"') { YYSIZE_T yyn = 0; char const *yyp = yystr; for (;;) switch (*++yyp) { case '\'': case ',': goto do_not_strip_quotes; case '\\': if (*++yyp != '\\') goto do_not_strip_quotes; /* Fall through. */ default: if (yyres) yyres[yyn] = *yyp; yyn++; break; case '"': if (yyres) yyres[yyn] = '\0'; return yyn; } do_not_strip_quotes: ; } if (! yyres) return yystrlen (yystr); return yystpcpy (yyres, yystr) - yyres; } # endif /* Copy into *YYMSG, which is of size *YYMSG_ALLOC, an error message about the unexpected token YYTOKEN for the state stack whose top is YYSSP. Return 0 if *YYMSG was successfully written. Return 1 if *YYMSG is not large enough to hold the message. In that case, also set *YYMSG_ALLOC to the required number of bytes. Return 2 if the required number of bytes is too large to store. */ static int yysyntax_error (YYSIZE_T *yymsg_alloc, char **yymsg, yytype_int16 *yyssp, int yytoken) { YYSIZE_T yysize0 = yytnamerr (0, yytname[yytoken]); YYSIZE_T yysize = yysize0; YYSIZE_T yysize1; enum { YYERROR_VERBOSE_ARGS_MAXIMUM = 5 }; /* Internationalized format string. */ const char *yyformat = 0; /* Arguments of yyformat. */ char const *yyarg[YYERROR_VERBOSE_ARGS_MAXIMUM]; /* Number of reported tokens (one for the "unexpected", one per "expected"). */ int yycount = 0; /* There are many possibilities here to consider: - Assume YYFAIL is not used. It's too flawed to consider. See for details. YYERROR is fine as it does not invoke this function. - If this state is a consistent state with a default action, then the only way this function was invoked is if the default action is an error action. In that case, don't check for expected tokens because there are none. - The only way there can be no lookahead present (in yychar) is if this state is a consistent state with a default action. Thus, detecting the absence of a lookahead is sufficient to determine that there is no unexpected or expected token to report. In that case, just report a simple "syntax error". - Don't assume there isn't a lookahead just because this state is a consistent state with a default action. There might have been a previous inconsistent state, consistent state with a non-default action, or user semantic action that manipulated yychar. - Of course, the expected token list depends on states to have correct lookahead information, and it depends on the parser not to perform extra reductions after fetching a lookahead from the scanner and before detecting a syntax error. Thus, state merging (from LALR or IELR) and default reductions corrupt the expected token list. However, the list is correct for canonical LR with one exception: it will still contain any token that will not be accepted due to an error action in a later state. */ if (yytoken != YYEMPTY) { int yyn = yypact[*yyssp]; yyarg[yycount++] = yytname[yytoken]; if (!yypact_value_is_default (yyn)) { /* Start YYX at -YYN if negative to avoid negative indexes in YYCHECK. In other words, skip the first -YYN actions for this state because they are default actions. */ int yyxbegin = yyn < 0 ? -yyn : 0; /* Stay within bounds of both yycheck and yytname. */ int yychecklim = YYLAST - yyn + 1; int yyxend = yychecklim < YYNTOKENS ? yychecklim : YYNTOKENS; int yyx; for (yyx = yyxbegin; yyx < yyxend; ++yyx) if (yycheck[yyx + yyn] == yyx && yyx != YYTERROR && !yytable_value_is_error (yytable[yyx + yyn])) { if (yycount == YYERROR_VERBOSE_ARGS_MAXIMUM) { yycount = 1; yysize = yysize0; break; } yyarg[yycount++] = yytname[yyx]; yysize1 = yysize + yytnamerr (0, yytname[yyx]); if (! (yysize <= yysize1 && yysize1 <= YYSTACK_ALLOC_MAXIMUM)) return 2; yysize = yysize1; } } } switch (yycount) { # define YYCASE_(N, S) \ case N: \ yyformat = S; \ break YYCASE_(0, YY_("syntax error")); YYCASE_(1, YY_("syntax error, unexpected %s")); YYCASE_(2, YY_("syntax error, unexpected %s, expecting %s")); YYCASE_(3, YY_("syntax error, unexpected %s, expecting %s or %s")); YYCASE_(4, YY_("syntax error, unexpected %s, expecting %s or %s or %s")); YYCASE_(5, YY_("syntax error, unexpected %s, expecting %s or %s or %s or %s")); # undef YYCASE_ } yysize1 = yysize + yystrlen (yyformat); if (! (yysize <= yysize1 && yysize1 <= YYSTACK_ALLOC_MAXIMUM)) return 2; yysize = yysize1; if (*yymsg_alloc < yysize) { *yymsg_alloc = 2 * yysize; if (! (yysize <= *yymsg_alloc && *yymsg_alloc <= YYSTACK_ALLOC_MAXIMUM)) *yymsg_alloc = YYSTACK_ALLOC_MAXIMUM; return 1; } /* Avoid sprintf, as that infringes on the user's name space. Don't have undefined behavior even if the translation produced a string with the wrong number of "%s"s. */ { char *yyp = *yymsg; int yyi = 0; while ((*yyp = *yyformat) != '\0') if (*yyp == '%' && yyformat[1] == 's' && yyi < yycount) { yyp += yytnamerr (yyp, yyarg[yyi++]); yyformat += 2; } else { yyp++; yyformat++; } } return 0; } #endif /* YYERROR_VERBOSE */ /*-----------------------------------------------. | Release the memory associated to this symbol. | `-----------------------------------------------*/ /*ARGSUSED*/ #if (defined __STDC__ || defined __C99__FUNC__ \ || defined __cplusplus || defined _MSC_VER) static void yydestruct (const char *yymsg, int yytype, YYSTYPE *yyvaluep) #else static void yydestruct (yymsg, yytype, yyvaluep) const char *yymsg; int yytype; YYSTYPE *yyvaluep; #endif { YYUSE (yyvaluep); if (!yymsg) yymsg = "Deleting"; YY_SYMBOL_PRINT (yymsg, yytype, yyvaluep, yylocationp); switch (yytype) { default: break; } } /* Prevent warnings from -Wmissing-prototypes. */ #ifdef YYPARSE_PARAM #if defined __STDC__ || defined __cplusplus int yyparse (void *YYPARSE_PARAM); #else int yyparse (); #endif #else /* ! YYPARSE_PARAM */ #if defined __STDC__ || defined __cplusplus int yyparse (void); #else int yyparse (); #endif #endif /* ! YYPARSE_PARAM */ /* The lookahead symbol. */ int yychar; /* The semantic value of the lookahead symbol. */ YYSTYPE yylval; /* Number of syntax errors so far. */ int yynerrs; /*----------. | yyparse. | `----------*/ #ifdef YYPARSE_PARAM #if (defined __STDC__ || defined __C99__FUNC__ \ || defined __cplusplus || defined _MSC_VER) int yyparse (void *YYPARSE_PARAM) #else int yyparse (YYPARSE_PARAM) void *YYPARSE_PARAM; #endif #else /* ! YYPARSE_PARAM */ #if (defined __STDC__ || defined __C99__FUNC__ \ || defined __cplusplus || defined _MSC_VER) int yyparse (void) #else int yyparse () #endif #endif { int yystate; /* Number of tokens to shift before error messages enabled. */ int yyerrstatus; /* The stacks and their tools: `yyss': related to states. `yyvs': related to semantic values. Refer to the stacks thru separate pointers, to allow yyoverflow to reallocate them elsewhere. */ /* The state stack. */ yytype_int16 yyssa[YYINITDEPTH]; yytype_int16 *yyss; yytype_int16 *yyssp; /* The semantic value stack. */ YYSTYPE yyvsa[YYINITDEPTH]; YYSTYPE *yyvs; YYSTYPE *yyvsp; YYSIZE_T yystacksize; int yyn; int yyresult; /* Lookahead token as an internal (translated) token number. */ int yytoken; /* The variables used to return semantic value and location from the action routines. */ YYSTYPE yyval; #if YYERROR_VERBOSE /* Buffer for error messages, and its allocated size. */ char yymsgbuf[128]; char *yymsg = yymsgbuf; YYSIZE_T yymsg_alloc = sizeof yymsgbuf; #endif #define YYPOPSTACK(N) (yyvsp -= (N), yyssp -= (N)) /* The number of symbols on the RHS of the reduced rule. Keep to zero when no symbol should be popped. */ int yylen = 0; yytoken = 0; yyss = yyssa; yyvs = yyvsa; yystacksize = YYINITDEPTH; YYDPRINTF ((stderr, "Starting parse\n")); yystate = 0; yyerrstatus = 0; yynerrs = 0; yychar = YYEMPTY; /* Cause a token to be read. */ /* Initialize stack pointers. Waste one element of value and location stack so that they stay on the same level as the state stack. The wasted elements are never initialized. */ yyssp = yyss; yyvsp = yyvs; goto yysetstate; /*------------------------------------------------------------. | yynewstate -- Push a new state, which is found in yystate. | `------------------------------------------------------------*/ yynewstate: /* In all cases, when you get here, the value and location stacks have just been pushed. So pushing a state here evens the stacks. */ yyssp++; yysetstate: *yyssp = yystate; if (yyss + yystacksize - 1 <= yyssp) { /* Get the current used size of the three stacks, in elements. */ YYSIZE_T yysize = yyssp - yyss + 1; #ifdef yyoverflow { /* Give user a chance to reallocate the stack. Use copies of these so that the &'s don't force the real ones into memory. */ YYSTYPE *yyvs1 = yyvs; yytype_int16 *yyss1 = yyss; /* Each stack pointer address is followed by the size of the data in use in that stack, in bytes. This used to be a conditional around just the two extra args, but that might be undefined if yyoverflow is a macro. */ yyoverflow (YY_("memory exhausted"), &yyss1, yysize * sizeof (*yyssp), &yyvs1, yysize * sizeof (*yyvsp), &yystacksize); yyss = yyss1; yyvs = yyvs1; } #else /* no yyoverflow */ # ifndef YYSTACK_RELOCATE goto yyexhaustedlab; # else /* Extend the stack our own way. */ if (YYMAXDEPTH <= yystacksize) goto yyexhaustedlab; yystacksize *= 2; if (YYMAXDEPTH < yystacksize) yystacksize = YYMAXDEPTH; { yytype_int16 *yyss1 = yyss; union yyalloc *yyptr = (union yyalloc *) YYSTACK_ALLOC (YYSTACK_BYTES (yystacksize)); if (! yyptr) goto yyexhaustedlab; YYSTACK_RELOCATE (yyss_alloc, yyss); YYSTACK_RELOCATE (yyvs_alloc, yyvs); # undef YYSTACK_RELOCATE if (yyss1 != yyssa) YYSTACK_FREE (yyss1); } # endif #endif /* no yyoverflow */ yyssp = yyss + yysize - 1; yyvsp = yyvs + yysize - 1; YYDPRINTF ((stderr, "Stack size increased to %lu\n", (unsigned long int) yystacksize)); if (yyss + yystacksize - 1 <= yyssp) YYABORT; } YYDPRINTF ((stderr, "Entering state %d\n", yystate)); if (yystate == YYFINAL) YYACCEPT; goto yybackup; /*-----------. | yybackup. | `-----------*/ yybackup: /* Do appropriate processing given the current state. Read a lookahead token if we need one and don't already have one. */ /* First try to decide what to do without reference to lookahead token. */ yyn = yypact[yystate]; if (yypact_value_is_default (yyn)) goto yydefault; /* Not known => get a lookahead token if don't already have one. */ /* YYCHAR is either YYEMPTY or YYEOF or a valid lookahead symbol. */ if (yychar == YYEMPTY) { YYDPRINTF ((stderr, "Reading a token: ")); yychar = YYLEX; } if (yychar <= YYEOF) { yychar = yytoken = YYEOF; YYDPRINTF ((stderr, "Now at end of input.\n")); } else { yytoken = YYTRANSLATE (yychar); YY_SYMBOL_PRINT ("Next token is", yytoken, &yylval, &yylloc); } /* If the proper action on seeing token YYTOKEN is to reduce or to detect an error, take that action. */ yyn += yytoken; if (yyn < 0 || YYLAST < yyn || yycheck[yyn] != yytoken) goto yydefault; yyn = yytable[yyn]; if (yyn <= 0) { if (yytable_value_is_error (yyn)) goto yyerrlab; yyn = -yyn; goto yyreduce; } /* Count tokens shifted since error; after three, turn off error status. */ if (yyerrstatus) yyerrstatus--; /* Shift the lookahead token. */ YY_SYMBOL_PRINT ("Shifting", yytoken, &yylval, &yylloc); /* Discard the shifted token. */ yychar = YYEMPTY; yystate = yyn; *++yyvsp = yylval; goto yynewstate; /*-----------------------------------------------------------. | yydefault -- do the default action for the current state. | `-----------------------------------------------------------*/ yydefault: yyn = yydefact[yystate]; if (yyn == 0) goto yyerrlab; goto yyreduce; /*-----------------------------. | yyreduce -- Do a reduction. | `-----------------------------*/ yyreduce: /* yyn is the number of a rule to reduce with. */ yylen = yyr2[yyn]; /* If YYLEN is nonzero, implement the default value of the action: `$$ = $1'. Otherwise, the following line sets YYVAL to garbage. This behavior is undocumented and Bison users should not rely upon it. Assigning to YYVAL unconditionally makes the parser a bit smaller, and it avoids a GCC warning that YYVAL may be used uninitialized. */ yyval = yyvsp[1-yylen]; YY_REDUCE_PRINT (yyn); switch (yyn) { case 4: /* Line 1806 of yacc.c */ #line 145 "genbc-decl.y" { define_bytecode ((yyvsp[(1) - (3)].text), (yyvsp[(2) - (3)].field)); } break; case 5: /* Line 1806 of yacc.c */ #line 147 "genbc-decl.y" { begin_code = (yyvsp[(3) - (4)].text); } break; case 6: /* Line 1806 of yacc.c */ #line 149 "genbc-decl.y" { end_code = (yyvsp[(3) - (4)].text); } break; case 7: /* Line 1806 of yacc.c */ #line 151 "genbc-decl.y" { define_decl ((yyvsp[(1) - (4)].num), (yyvsp[(1) - (4)].num), (yyvsp[(3) - (4)].text)); } break; case 8: /* Line 1806 of yacc.c */ #line 153 "genbc-decl.y" { define_decl ((yyvsp[(1) - (6)].num), (yyvsp[(3) - (6)].num), (yyvsp[(5) - (6)].text)); } break; case 9: /* Line 1806 of yacc.c */ #line 158 "genbc-decl.y" { (yyval.field) = (yyvsp[(2) - (3)].field); } break; case 10: /* Line 1806 of yacc.c */ #line 160 "genbc-decl.y" { (yyval.field) = NULL; } break; case 11: /* Line 1806 of yacc.c */ #line 165 "genbc-decl.y" { struct field_info *f = malloc (sizeof (struct field_info)); define_var ((yyvsp[(3) - (3)].text)); f->name = (yyvsp[(3) - (3)].text); f->next = NULL; *((yyvsp[(1) - (3)].field)->pnext) = f; (yyval.field) = (yyvsp[(1) - (3)].field); (yyval.field)->pnext = &(f->next); } break; case 12: /* Line 1806 of yacc.c */ #line 174 "genbc-decl.y" { struct field_info *f = malloc (sizeof (struct field_info)); define_var ((yyvsp[(1) - (1)].text)); f->name = (yyvsp[(1) - (1)].text); f->next = NULL; (yyval.field) = f; (yyval.field)->pnext = &(f->next); } break; case 13: /* Line 1806 of yacc.c */ #line 184 "genbc-decl.y" { curr_fil = filnew (NULL, 0); } break; case 14: /* Line 1806 of yacc.c */ #line 186 "genbc-decl.y" { (yyval.text) = fildelete (curr_fil); } break; case 17: /* Line 1806 of yacc.c */ #line 195 "genbc-decl.y" { filccat (curr_fil, '='); } break; case 18: /* Line 1806 of yacc.c */ #line 197 "genbc-decl.y" { filccat (curr_fil, '('); } break; case 19: /* Line 1806 of yacc.c */ #line 199 "genbc-decl.y" { filccat (curr_fil, ')'); } break; case 20: /* Line 1806 of yacc.c */ #line 201 "genbc-decl.y" { filcat (curr_fil, (yyvsp[(1) - (1)].text)); free ((yyvsp[(1) - (1)].text)); } break; case 21: /* Line 1806 of yacc.c */ #line 203 "genbc-decl.y" { filprintf (curr_fil, "%d", (yyvsp[(1) - (1)].num)); } break; case 22: /* Line 1806 of yacc.c */ #line 205 "genbc-decl.y" { filcat (curr_fil, (yyvsp[(1) - (1)].ctext)); } break; case 26: /* Line 1806 of yacc.c */ #line 215 "genbc-decl.y" { filccat (curr_fil, ','); } break; case 27: /* Line 1806 of yacc.c */ #line 219 "genbc-decl.y" { curr_fil = filnew (NULL, 0); } break; case 28: /* Line 1806 of yacc.c */ #line 221 "genbc-decl.y" { filcat (curr_fil, " goto MATCH_BYTECODES_END_##name_; "); (yyval.text) = fildelete (curr_fil); } break; case 32: /* Line 1806 of yacc.c */ #line 232 "genbc-decl.y" { filcat (curr_fil, "goto MATCH_BYTECODES_END_##name_;"); } break; case 33: /* Line 1806 of yacc.c */ #line 234 "genbc-decl.y" { filcat (curr_fil, "goto MATCH_BYTECODES_START_##name_;"); } break; case 34: /* Line 1806 of yacc.c */ #line 236 "genbc-decl.y" { filprintf (curr_fil, "do { \\\n" "\topcode_ = %d; \\\n", synthetic); curr_bytecode = get_bytecode ((yyvsp[(2) - (2)].text)); if (!curr_bytecode) { curr_field = NULL; yyerror ("bad bytecode name"); } else curr_field = curr_bytecode->fields; } break; case 35: /* Line 1806 of yacc.c */ #line 248 "genbc-decl.y" { if (curr_field) yyerror ("expected field in dispatch"); filprintf (curr_fil, "\tgoto MATCH_BYTECODES_##name_##_%s; \\\n", (yyvsp[(2) - (4)].text)); filprintf (curr_fil, " case %d: \\\n" "\t; \\\n" " } while (0)", synthetic++); free ((yyvsp[(2) - (4)].text)); } break; case 36: /* Line 1806 of yacc.c */ #line 257 "genbc-decl.y" { if ((yyvsp[(2) - (2)].num) % 8) yyerror ("must extract an integer number of bytes"); else filprintf (curr_fil, "bp_ = (IP += %d)", (yyvsp[(2) - (2)].num) / 8); } break; case 41: /* Line 1806 of yacc.c */ #line 275 "genbc-decl.y" { if (curr_field) { filprintf (curr_fil, "\t%s = ", curr_field->name); curr_field = curr_field->next; } else yyerror ("extra field in dispatch"); } break; case 42: /* Line 1806 of yacc.c */ #line 284 "genbc-decl.y" { filprintf (curr_fil, "; \\\n"); } break; case 43: /* Line 1806 of yacc.c */ #line 288 "genbc-decl.y" { (yyval.num) = (yyvsp[(2) - (3)].num); } break; case 44: /* Line 1806 of yacc.c */ #line 289 "genbc-decl.y" { (yyval.num) = 8; } break; case 45: /* Line 1806 of yacc.c */ #line 293 "genbc-decl.y" { (yyval.num) = (yyvsp[(1) - (3)].num) + (yyvsp[(3) - (3)].num); } break; case 46: /* Line 1806 of yacc.c */ #line 294 "genbc-decl.y" { (yyval.num) = (yyvsp[(1) - (1)].num); } break; case 47: /* Line 1806 of yacc.c */ #line 299 "genbc-decl.y" { define_field ((yyvsp[(1) - (2)].text), (yyvsp[(2) - (2)].num)); (yyval.num) = (yyvsp[(2) - (2)].num); } break; /* Line 1806 of yacc.c */ #line 1757 "genbc-decl.c" default: break; } /* User semantic actions sometimes alter yychar, and that requires that yytoken be updated with the new translation. We take the approach of translating immediately before every use of yytoken. One alternative is translating here after every semantic action, but that translation would be missed if the semantic action invokes YYABORT, YYACCEPT, or YYERROR immediately after altering yychar or if it invokes YYBACKUP. In the case of YYABORT or YYACCEPT, an incorrect destructor might then be invoked immediately. In the case of YYERROR or YYBACKUP, subsequent parser actions might lead to an incorrect destructor call or verbose syntax error message before the lookahead is translated. */ YY_SYMBOL_PRINT ("-> $$ =", yyr1[yyn], &yyval, &yyloc); YYPOPSTACK (yylen); yylen = 0; YY_STACK_PRINT (yyss, yyssp); *++yyvsp = yyval; /* Now `shift' the result of the reduction. Determine what state that goes to, based on the state we popped back to and the rule number reduced by. */ yyn = yyr1[yyn]; yystate = yypgoto[yyn - YYNTOKENS] + *yyssp; if (0 <= yystate && yystate <= YYLAST && yycheck[yystate] == *yyssp) yystate = yytable[yystate]; else yystate = yydefgoto[yyn - YYNTOKENS]; goto yynewstate; /*------------------------------------. | yyerrlab -- here on detecting error | `------------------------------------*/ yyerrlab: /* Make sure we have latest lookahead translation. See comments at user semantic actions for why this is necessary. */ yytoken = yychar == YYEMPTY ? YYEMPTY : YYTRANSLATE (yychar); /* If not already recovering from an error, report this error. */ if (!yyerrstatus) { ++yynerrs; #if ! YYERROR_VERBOSE yyerror (YY_("syntax error")); #else # define YYSYNTAX_ERROR yysyntax_error (&yymsg_alloc, &yymsg, \ yyssp, yytoken) { char const *yymsgp = YY_("syntax error"); int yysyntax_error_status; yysyntax_error_status = YYSYNTAX_ERROR; if (yysyntax_error_status == 0) yymsgp = yymsg; else if (yysyntax_error_status == 1) { if (yymsg != yymsgbuf) YYSTACK_FREE (yymsg); yymsg = (char *) YYSTACK_ALLOC (yymsg_alloc); if (!yymsg) { yymsg = yymsgbuf; yymsg_alloc = sizeof yymsgbuf; yysyntax_error_status = 2; } else { yysyntax_error_status = YYSYNTAX_ERROR; yymsgp = yymsg; } } yyerror (yymsgp); if (yysyntax_error_status == 2) goto yyexhaustedlab; } # undef YYSYNTAX_ERROR #endif } if (yyerrstatus == 3) { /* If just tried and failed to reuse lookahead token after an error, discard it. */ if (yychar <= YYEOF) { /* Return failure if at end of input. */ if (yychar == YYEOF) YYABORT; } else { yydestruct ("Error: discarding", yytoken, &yylval); yychar = YYEMPTY; } } /* Else will try to reuse lookahead token after shifting the error token. */ goto yyerrlab1; /*---------------------------------------------------. | yyerrorlab -- error raised explicitly by YYERROR. | `---------------------------------------------------*/ yyerrorlab: /* Pacify compilers like GCC when the user code never invokes YYERROR and the label yyerrorlab therefore never appears in user code. */ if (/*CONSTCOND*/ 0) goto yyerrorlab; /* Do not reclaim the symbols of the rule which action triggered this YYERROR. */ YYPOPSTACK (yylen); yylen = 0; YY_STACK_PRINT (yyss, yyssp); yystate = *yyssp; goto yyerrlab1; /*-------------------------------------------------------------. | yyerrlab1 -- common code for both syntax error and YYERROR. | `-------------------------------------------------------------*/ yyerrlab1: yyerrstatus = 3; /* Each real token shifted decrements this. */ for (;;) { yyn = yypact[yystate]; if (!yypact_value_is_default (yyn)) { yyn += YYTERROR; if (0 <= yyn && yyn <= YYLAST && yycheck[yyn] == YYTERROR) { yyn = yytable[yyn]; if (0 < yyn) break; } } /* Pop the current state because it cannot handle the error token. */ if (yyssp == yyss) YYABORT; yydestruct ("Error: popping", yystos[yystate], yyvsp); YYPOPSTACK (1); yystate = *yyssp; YY_STACK_PRINT (yyss, yyssp); } *++yyvsp = yylval; /* Shift the error token. */ YY_SYMBOL_PRINT ("Shifting", yystos[yyn], yyvsp, yylsp); yystate = yyn; goto yynewstate; /*-------------------------------------. | yyacceptlab -- YYACCEPT comes here. | `-------------------------------------*/ yyacceptlab: yyresult = 0; goto yyreturn; /*-----------------------------------. | yyabortlab -- YYABORT comes here. | `-----------------------------------*/ yyabortlab: yyresult = 1; goto yyreturn; #if !defined(yyoverflow) || YYERROR_VERBOSE /*-------------------------------------------------. | yyexhaustedlab -- memory exhaustion comes here. | `-------------------------------------------------*/ yyexhaustedlab: yyerror (YY_("memory exhausted")); yyresult = 2; /* Fall through. */ #endif yyreturn: if (yychar != YYEMPTY) { /* Make sure we have latest lookahead translation. See comments at user semantic actions for why this is necessary. */ yytoken = YYTRANSLATE (yychar); yydestruct ("Cleanup: discarding lookahead", yytoken, &yylval); } /* Do not reclaim the symbols of the rule which action triggered this YYABORT or YYACCEPT. */ YYPOPSTACK (yylen); YY_STACK_PRINT (yyss, yyssp); while (yyssp != yyss) { yydestruct ("Cleanup: popping", yystos[*yyssp], yyvsp); YYPOPSTACK (1); } #ifndef yyoverflow if (yyss != yyssa) YYSTACK_FREE (yyss); #endif #if YYERROR_VERBOSE if (yymsg != yymsgbuf) YYSTACK_FREE (yymsg); #endif /* Make sure YYID is used. */ return YYID (yyresult); } /* Line 2067 of yacc.c */ #line 302 "genbc-decl.y" int filprintf (Filament *fil, const char *format, ...) { va_list ap; STREAM *out = stream_new (fil, SNV_UNLIMITED, NULL, snv_filputc); int result; va_start (ap, format); result = stream_vprintf (out, format, ap); va_end (ap); stream_delete (out); return result; } /* Advance the pointer by BITS bits and return the code to extract those bits. */ char * extraction_code (int bits) { char *s; int n_bit = curr_bit_offset % 8; int n_byte = curr_bit_offset / 8; if (n_bit + bits <= 8) { int rshift = 8 - (n_bit + bits); int mask = (1 << bits) - 1; curr_bit_offset += bits; if (n_bit && rshift) return my_asprintf ("(IP[%d] >> %d) & %d", n_byte, rshift, mask); if (rshift) return my_asprintf ("IP[%d] >> %d", n_byte, rshift); if (n_bit) return my_asprintf ("IP[%d] & %d", n_byte, mask); else return my_asprintf ("IP[%d]", n_byte); } /* Else, multi-byte extraction. */ if (curr_bit_offset % 8) /* Complete the current byte... */ { int n = 8 - (curr_bit_offset % 8); s = extraction_code (n); bits -= n; n_bit = 0; n_byte++; } else /* ... or do a new one. */ { s = my_asprintf ("IP[%d]", n_byte++); curr_bit_offset += 8; bits -= 8; } /* Add entire bytes as long as possible. */ while (bits >= 8) { char *new_s = my_asprintf ("((%s) << 8) | IP[%d]", s, n_byte++); free (s); s = new_s; curr_bit_offset += 8; bits -= 8; } /* And finally any spare bits. */ if (bits) { char *new_s = my_asprintf ("((%s) << 8) | %s", s, extraction_code (bits)); free (s); s = new_s; } return (s); } /* Define a bytecode that is used as an operand to dispatch. We use an AVL tree to store them so that we can do fast searches, and we can detect duplicates. */ bytecode_info * get_bytecode (const char *name) { avl_node_t **p = (avl_node_t **) &bytecode_root; bytecode_info *bytecode = NULL; while (*p) { int cmp; bytecode = (bytecode_info *) *p; cmp = strcmp(name, bytecode->name); if (cmp < 0) p = &(*p)->avl_left; else if (cmp > 0) p = &(*p)->avl_right; else return bytecode; } return NULL; } /* Define a bytecode that is used as an operand to dispatch. We use an AVL tree to store them so that we can do fast searches, and we can detect duplicates. */ void define_bytecode (const char *name, field_info *fields) { avl_node_t **p = (avl_node_t **) &bytecode_root; bytecode_info *node; bytecode_info *bytecode = NULL; while (*p) { int cmp; bytecode = (bytecode_info *) *p; cmp = strcmp(name, bytecode->name); if (cmp < 0) p = &(*p)->avl_left; else if (cmp > 0) p = &(*p)->avl_right; else { yyerror ("duplicate bytecode name"); return; } } node = (bytecode_info *) calloc(1, sizeof(struct bytecode_info)); node->avl.avl_parent = (avl_node_t *) bytecode; node->avl.avl_left = node->avl.avl_right = NULL; node->name = name; node->fields = fields; *p = &(node->avl); avl_rebalance(&node->avl, (avl_node_t **) &bytecode_root); } /* Define a variable that is used to pass the operands of the bytecode. We use an AVL tree to store them so that we can output them nicely sorted, and we can eliminate duplicates. */ void define_var (const char *name) { avl_node_t **p = (avl_node_t **) &var_root; var_info *node; var_info *var = NULL; while (*p) { int cmp; var = (var_info *) *p; cmp = strcmp(name, var->name); if (cmp < 0) p = &(*p)->avl_left; else if (cmp > 0) p = &(*p)->avl_right; else return; } node = (var_info *) calloc(1, sizeof(struct var_info)); node->avl.avl_parent = (avl_node_t *) var; node->avl.avl_left = node->avl.avl_right = NULL; node->name = name; *p = &(node->avl); avl_rebalance(&node->avl, (avl_node_t **) &var_root); } /* Define an operation that is BITS bits wide and whose opcodes start at OPCODE) and does the ID operation. */ void define_decl (int first, int last, char *code) { struct opcode *curr = calloc (1, sizeof (struct opcode)); curr->first = first; curr->last = last; curr->code = code; *p_next = curr; p_next = &(curr->next); if ((unsigned) (first | last) > 255) yyerror ("Invalid opcode specification"); curr_bit_offset = 0; } /* Define a BITS bits-wide operand named NAME of the current bytecode. */ void define_field (const char *name, int bits) { char *s = extraction_code (bits); define_var (name); filprintf (curr_fil, "%s = %s; \\\n ", name, s); free (s); } /* Emit the declarations for the variable names. NODE is the root of the tree, PREFIX ("int" or ",") is emitted before the first variable, SUFFIX after every variable, NEXT_PREFIX before every variable but the first. */ void emit_var_names (var_info *node, const char *prefix, const char *suffix, const char *next_prefix) { if (node->avl.avl_left) { emit_var_names ((var_info *) node->avl.avl_left, prefix, suffix, next_prefix); prefix = next_prefix; } printf ("%s%s%s", prefix, node->name, suffix); if (node->avl.avl_right) emit_var_names ((var_info *) node->avl.avl_right, next_prefix, suffix, next_prefix); } /* Emit the decision tree for the bytecodes. */ void emit_opcodes () { int n; struct opcode *op; define_var ("opcode_"); emit_var_names (var_root, " int ", "", ", "); printf ("; \\\n"); printf (" unsigned char *IP = bp_; \\\n"); printf (" unsigned char ATTRIBUTE_UNUSED *IP0 = bp_; \\\n"); emit_var_names (var_root, " ", " ", "= "); printf ("= 0; \\\n"); if (begin_code) printf (" { \\\n" " %s \\\n" " } \\\n", begin_code); printf ("MATCH_BYTECODES_START_##name_: \\\n" " opcode_ = *IP; \\\n" "MATCH_BYTECODES_SWITCH_##name_: \\\n" " switch (opcode_) { \\\n"); for (op = first; op; op = op->next) { int first_val = op->first; int last_val = op->last; for (n = 0; first_val <= last_val; first_val++, n++) { if (!(n & 3)) printf ("%s ", n ? "\\\n" : ""); printf ("case %d: ", first_val); } printf ("\\\n" " %s\\\n", op->code); } printf (" } \\\n" " MATCH_BYTECODES_DISPATCH(MATCH_BYTECODES_##name_) \\\n" "MATCH_BYTECODES_END_##name_: \\\n" "%s", end_code ? end_code : " ;"); } smalltalk-3.2.5/libgst/xlat.h0000644000175000017500000000721612123404352013035 00000000000000/******************************** -*- C -*- **************************** * * Translator to native code declarations. * * ***********************************************************************/ /*********************************************************************** * * Copyright 2001, 2002, 2006 Free Software Foundation, Inc. * Written by Paolo Bonzini. * * This file is part of GNU Smalltalk. * * GNU Smalltalk is free software; you can redistribute it and/or modify it * under the terms of the GNU General Public License as published by the Free * Software Foundation; either version 2, or (at your option) any later * version. * * Linking GNU Smalltalk statically or dynamically with other modules is * making a combined work based on GNU Smalltalk. Thus, the terms and * conditions of the GNU General Public License cover the whole * combination. * * In addition, as a special exception, the Free Software Foundation * give you permission to combine GNU Smalltalk with free software * programs or libraries that are released under the GNU LGPL and with * independent programs running under the GNU Smalltalk virtual machine. * * You may copy and distribute such a system following the terms of the * GNU GPL for GNU Smalltalk and the licenses of the other code * concerned, provided that you include the source code of that other * code when and as the GNU GPL requires distribution of source code. * * Note that people who make modified versions of GNU Smalltalk are not * obligated to grant this special exception for their modified * versions; it is their choice whether to do so. The GNU General * Public License gives permission to release a modified version without * this exception; this exception also makes it possible to release a * modified version which carries forward this exception. * * GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or * FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for * more details. * * You should have received a copy of the GNU General Public License along with * GNU Smalltalk; see the file COPYING. If not, write to the Free Software * Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * ***********************************************************************/ #ifndef GST_XLAT_H #define GST_XLAT_H #ifdef ENABLE_JIT_TRANSLATION struct inline_cache; struct ip_map; typedef struct method_entry { struct method_entry *next; OOP methodOOP; OOP receiverClass; struct inline_cache *inlineCaches; struct ip_map *ipMap; int nativeCode[1]; /* type chosen randomly */ } method_entry; extern void _gst_reset_inline_caches () ATTRIBUTE_HIDDEN; extern PTR _gst_get_native_code (OOP methodOOP, OOP receiverClass) ATTRIBUTE_HIDDEN; extern PTR _gst_map_virtual_ip (OOP methodOOP, OOP receiverClass, int ip) ATTRIBUTE_HIDDEN; extern void _gst_free_released_native_code (void) ATTRIBUTE_HIDDEN; extern void _gst_release_native_code (OOP methodOOP) ATTRIBUTE_HIDDEN; extern void _gst_discard_native_code (OOP methodOOP) ATTRIBUTE_HIDDEN; extern void _gst_init_translator (void) ATTRIBUTE_HIDDEN; extern PTR (*_gst_run_native_code) () ATTRIBUTE_HIDDEN; extern PTR (*_gst_return_from_native_code) () ATTRIBUTE_HIDDEN; #define GET_METHOD_ENTRY(nativeCodeStart) ((method_entry *) ( \ ((char *) nativeCodeStart) - (sizeof(method_entry) - sizeof(int)) )) #define IS_VALID_IP(nativeCodeStart) \ ((nativeCodeStart) && GET_METHOD_ENTRY((nativeCodeStart))->receiverClass) #endif /* ENABLE_JIT_TRANSLATION */ #endif /* GST_XLAT_H */ smalltalk-3.2.5/libgst/lex.h0000644000175000017500000001021312130343734012650 00000000000000/******************************** -*- C -*- **************************** * * External definitions for the Lexer module. * * ***********************************************************************/ /*********************************************************************** * * Copyright 1988,89,90,91,92,94,95,99,2000,2001,2002,2006,2007,2008 * Free Software Foundation, Inc. * Written by Steve Byrne. * * This file is part of GNU Smalltalk. * * GNU Smalltalk is free software; you can redistribute it and/or modify it * under the terms of the GNU General Public License as published by the Free * Software Foundation; either version 2, or (at your option) any later * version. * * Linking GNU Smalltalk statically or dynamically with other modules is * making a combined work based on GNU Smalltalk. Thus, the terms and * conditions of the GNU General Public License cover the whole * combination. * * In addition, as a special exception, the Free Software Foundation * give you permission to combine GNU Smalltalk with free software * programs or libraries that are released under the GNU LGPL and with * independent programs running under the GNU Smalltalk virtual machine. * * You may copy and distribute such a system following the terms of the * GNU GPL for GNU Smalltalk and the licenses of the other code * concerned, provided that you include the source code of that other * code when and as the GNU GPL requires distribution of source code. * * Note that people who make modified versions of GNU Smalltalk are not * obligated to grant this special exception for their modified * versions; it is their choice whether to do so. The GNU General * Public License gives permission to release a modified version without * this exception; this exception also makes it possible to release a * modified version which carries forward this exception. * * GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or * FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for * more details. * * You should have received a copy of the GNU General Public License along with * GNU Smalltalk; see the file COPYING. If not, write to the Free Software * Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * ***********************************************************************/ #ifndef GST_LEX_H #define GST_LEX_H /* True if errors must be reported to the standard error, false if errors should instead stored so that they are passed to Smalltalk code. */ extern mst_Boolean _gst_report_errors ATTRIBUTE_HIDDEN; /* This is set to true by the parser or the compiler if an error (respectively, a parse error or a semantic error) is found, and avoids that _gst_execute_statements tries to execute the result of the compilation. */ extern mst_Boolean _gst_had_error ATTRIBUTE_HIDDEN; /* This is set to true by the parser if error recovery is going on. In this case ERROR_RECOVERY tokens are generated. */ extern mst_Boolean _gst_error_recovery ATTRIBUTE_HIDDEN; /* The location of the first error reported, stored here so that compilation primitives can pass them to Smalltalk code. */ extern char *_gst_first_error_str ATTRIBUTE_HIDDEN, *_gst_first_error_file ATTRIBUTE_HIDDEN; extern int _gst_first_error_line ATTRIBUTE_HIDDEN; /* The obstack containing parse tree nodes. */ extern struct obstack *_gst_compilation_obstack ATTRIBUTE_HIDDEN; /* Parse the topmost stream in the stack. */ extern void _gst_parse_stream (mst_Boolean method) ATTRIBUTE_HIDDEN; /* Lexer interface to the lexer. */ extern int _gst_yylex (PTR lvalp, YYLTYPE *llocp) ATTRIBUTE_HIDDEN; /* Print on file FILE a description of TOKEN, with auxiliary data stored in LVAL. */ extern void _gst_yyprint (FILE * file, int token, PTR lval) ATTRIBUTE_HIDDEN; /* Negate the semantic value YYLVAL, which must be a numeric token of type TOKEN. Returns true if YYLVAL is positive, false if it is negative. */ extern mst_Boolean _gst_negate_yylval (int token, YYSTYPE *yylval); #endif /* GST_LEX_H */ smalltalk-3.2.5/libgst/genvm-parse.y0000644000175000017500000004560712123404352014340 00000000000000/******************************** -*- C -*- **************************** * * GNU Smalltalk genvm tool * ***********************************************************************/ /*********************************************************************** * * Copyright 2003, 2006 Free Software Foundation, Inc. * Written by Paolo Bonzini. * * This file is part of GNU Smalltalk. * * GNU Smalltalk is free software; you can redistribute it and/or modify it * under the terms of the GNU General Public License as published by the Free * Software Foundation; either version 2, or (at your option) any later * version. * * Linking GNU Smalltalk statically or dynamically with other modules is * making a combined work based on GNU Smalltalk. Thus, the terms and * conditions of the GNU General Public License cover the whole * combination. * * In addition, as a special exception, the Free Software Foundation * give you permission to combine GNU Smalltalk with free software * programs or libraries that are released under the GNU LGPL and with * independent programs running under the GNU Smalltalk virtual machine. * * You may copy and distribute such a system following the terms of the * GNU GPL for GNU Smalltalk and the licenses of the other code * concerned, provided that you include the source code of that other * code when and as the GNU GPL requires distribution of source code. * * Note that people who make modified versions of GNU Smalltalk are not * obligated to grant this special exception for their modified * versions; it is their choice whether to do so. The GNU General * Public License gives permission to release a modified version without * this exception; this exception also makes it possible to release a * modified version which carries forward this exception. * * GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or * FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for * more details. * * You should have received a copy of the GNU General Public License along with * GNU Smalltalk; see the file COPYING. If not, write to the Free Software * Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * ***********************************************************************/ %{ #include "avltrees.h" #include "genvm.h" #include "genvm-parse.h" #define YYERROR_VERBOSE 1 typedef struct id_list { struct id_list *next; struct id_list **pnext; char id[1]; } id_list; typedef struct operation_info { avl_node_t avl; const char *name; struct id_list *args; struct id_list *in, *out, *read; int n_in, n_out, n_read; int needs_prepare_stack; int needs_branch_label; int instantiations; const char *code; } operation_info; typedef struct operation_list { struct operation_list *next; struct operation_list **pnext; operation_info *op; id_list *args; } operation_list; typedef struct table_info { char *name; char *entry[256]; id_list *pool; } table_info; #define YYPRINT(fp, tok, val) yyprint (fp, tok, &val) static int filprintf (Filament *fil, const char *format, ...); static void yyprint (FILE *fp, int tok, const YYSTYPE *val); static void yyerror (const char *s); static operation_info *define_operation (const char *name); static void set_curr_op_stack (id_list *in, id_list *out); static operation_list *append_to_operation_list (operation_list *list, const char *name, id_list *args); static id_list *append_to_id_list (id_list *list, const char *id); static int emit_id_list (const id_list *list, const char *sep, const char *before, const char *after); static void set_table (table_info *t, int from, int to, char *value); static void free_id_list (id_list *list); static void emit_var_declarations (const char *base, const char *type, int i, int n); static void emit_var_defines (id_list *list, int sp); static void emit_operation_invocation (operation_info *op, id_list *args, int sp, int deepest_write); static void emit_operation_list (operation_list *list); static void emit_stack_update (int sp, int deepest_write, const char *before, const char *after); static void free_operation_list (operation_list *list); static table_info *define_table (char *name); static void emit_table (table_info *t); static void free_table (table_info *t); int counter = 0; int c_code_on_brace = 0; int c_args_on_paren = 0; int errors = 0; Filament *curr_fil, *out_fil; operation_info *curr_op, *op_root; table_info *curr_table; int from, to; %} %debug %defines %union { struct operation_list *oplist; struct operation_info *op; struct table_info *tab; struct id_list *id; const char *ctext; char *text; int num; } /* single definite characters */ %token ID "identifier" %token EXPR "C expression" %token NUMBER "number" %token VM_OPERATION "operation" %token VM_TABLE "table" %token VM_BYTECODE "bytecode" %token VM_DOTS ".." %token VM_MINUSMINUS "--" %type ids c_args opt_c_args %type opt_id c_arg bytecode %type table %type operation_list %type operation %% script: script table | script operation | script bytecode { free ($2); } | /* empty */ ; table: VM_TABLE ID { curr_table = define_table ($2); } '{' table_items '}' { emit_table (curr_table); free_table (curr_table); } ; table_items: table_items.label | table_items.descr ; table_items.label: table_items.label ',' label | table_items.descr label | label ; table_items.descr: table_items.label ',' description | table_items.descr description | description ; subscripts: NUMBER '=' { from = to = $1; if (from < 0 || from > 255) { yyerror ("invalid table index"); from = 0, to = -1; } } | NUMBER VM_DOTS NUMBER '=' { from = $1, to = $3; if (from < 0 || to < 0 || from > 255 || to > 255) { yyerror ("invalid table index"); from = 0, to = -1; } } ; label: subscripts ID { set_table (curr_table, from, to, $2); free ($2); } ; description: subscripts bytecode { set_table (curr_table, from, to, $2); free ($2); } bytecode: VM_BYTECODE opt_id { filprintf (out_fil, "%s:\n", $2); } '{' operation_list '}' { emit_operation_list ($5); free_operation_list ($5); filprintf (out_fil, " NEXT_BC;\n"); $$ = $2; } ; operation_list: operation_list ID { c_args_on_paren = 1; } '(' opt_c_args ')' ';' { $$ = append_to_operation_list ($1, $2, $5); } | /* empty */ { $$ = NULL; } ; opt_c_args: c_args { $$ = $1; } | /* empty */ { $$ = NULL; } ; c_args: c_args ',' c_arg { $$ = append_to_id_list ($1, $3); free ($3); } | c_arg { $$ = append_to_id_list (NULL, $1); free ($1); } ; c_arg: { curr_fil = filnew (NULL, 0); } c_arg_body { $$ = fildelete (curr_fil); } ; c_arg_body: c_arg_body EXPR { filcat (curr_fil, $2); } | EXPR { filcat (curr_fil, $1); } | c_arg_body '(' { filcat (curr_fil, "("); } c_arg_body ')' { filcat (curr_fil, ")"); } ; opt_id: ID { $$ = $1; } | /* empty */ { asprintf (&$$, "label%d", ++counter); } ; operation: VM_OPERATION ID { curr_op = define_operation ($2); c_code_on_brace = true; } ids stack_balance { curr_fil = filnew (NULL, 0); filprintf (curr_fil, "#line %d \"vm.def\"\n ", yylineno + 1); } '{' c_code '}' { filprintf (curr_fil, "\n#line __oline__ \"vm.inl\""); if (curr_op) { curr_op->args = $4; curr_op->code = fildelete (curr_fil); curr_op->needs_prepare_stack = strstr(curr_op->code, "PREPARE_STACK") != NULL; curr_op->needs_branch_label = strstr(curr_op->code, "BRANCH_LABEL") != NULL; } $$ = curr_op; } ; ids: ids ID { $$ = append_to_id_list ($1, $2); free ($2); } | /* empty */ { $$ = NULL; } ; stack_balance: '(' ids VM_MINUSMINUS ids ')' { set_curr_op_stack ($2, $4); } c_code: c_code EXPR { filcat (curr_fil, $2); } | /* empty */ ; %% void yyprint (FILE *fp, int tok, const YYSTYPE *val) { switch (tok) { case NUMBER: fprintf (fp, "%d", (val)->num); break; case ID: case EXPR: fprintf (fp, "%s", (val)->text); break; } } void yyerror (const char *s) { errors = 1; fprintf (stderr, "vm.def:%d: %s\n", yylineno, s); } /* Define an operation that is used into a bytecode declaration. We use an AVL tree to store them so that we can do fast searches, and we can detect duplicates. */ operation_info * define_operation (const char *name) { avl_node_t **p = (avl_node_t **) &op_root; operation_info *node; operation_info *operation = NULL; while (*p) { int cmp; operation = (operation_info *) *p; cmp = strcmp(name, operation->name); if (cmp < 0) p = &(*p)->avl_left; else if (cmp > 0) p = &(*p)->avl_right; else { yyerror ("duplicate operation"); return NULL; } } node = (operation_info *) calloc(1, sizeof(operation_info)); node->avl.avl_parent = (avl_node_t *) operation; node->avl.avl_left = node->avl.avl_right = NULL; node->name = name; *p = &(node->avl); avl_rebalance(&node->avl, (avl_node_t **) &op_root); return node; } operation_info * get_operation (const char *name) { avl_node_t **p = (avl_node_t **) &op_root; operation_info *operation = NULL; while (*p) { int cmp; operation = (operation_info *) *p; cmp = strcmp(name, operation->name); if (cmp < 0) p = &(*p)->avl_left; else if (cmp > 0) p = &(*p)->avl_right; else return operation; } return NULL; } operation_list * append_to_operation_list (operation_list *list, const char *name, id_list *args) { operation_list *node, *result; operation_info *op = get_operation (name); if (!op) { yyerror ("undefined operation"); return list; } node = calloc (1, sizeof (operation_list)); if (!list) result = node; else { result = list; *(result->pnext) = node; } node->op = op; node->args = args; result->pnext = &(node->next); return result; } id_list * append_to_id_list (id_list *list, const char *name) { int len = strlen (name); id_list *node = calloc (1, sizeof (id_list) + len); id_list *result; memcpy (node->id, name, len); if (!list) result = node; else { result = list; *(result->pnext) = node; } result->pnext = &(node->next); return result; } int emit_id_list (const id_list *list, const char *sep, const char *before, const char *after) { int n = 0; if (!list) return 0; filcat (out_fil, before); while (list) { filcat (out_fil, list->id); list = list->next; filcat (out_fil, list ? sep : after); n++; } return n; } void free_id_list (id_list *list) { id_list *next; while (list) { next = list->next; free (list); list = next; } } void set_curr_op_stack (id_list *in, id_list *out) { id_list *read = in; id_list *list; id_list *last_read = NULL; if (!curr_op) return; /* Find the names that are a common prefix for the input and output stack, and move them to the READ list. */ while (in && out && !strcmp (in->id, out->id)) { id_list *next; next = out->next; free (out); out = next; /* The in nodes are still referenced through READ. */ last_read = in; in = in->next; } if (last_read) { if (in) in->pnext = read->pnext; last_read->next = NULL; read->pnext = &(last_read->next); } else /* The slots are all read and written, none is just read. */ read = NULL; curr_op->in = in; curr_op->out = out; curr_op->read = read; /* Compute and save the count, we'll use it to combine the stack effects. */ for (curr_op->n_in = 0, list = curr_op->in; list; list = list->next, curr_op->n_in++); for (curr_op->n_out = 0, list = curr_op->out; list; list = list->next, curr_op->n_out++); for (curr_op->n_read = 0, list = curr_op->read; list; list = list->next, curr_op->n_read++); } void free_operation_list (operation_list *list) { operation_list *next; while (list) { next = list->next; free_id_list (list->args); free (list); list = next; } } void emit_var_declarations (const char *base, const char *type, int first, int n) { int i; if (!n) return; for (i = first; n--; i++) filprintf (out_fil, "%s %s%d", i == first ? type : ",", base, i); filprintf (out_fil, ";\n"); } void emit_var_defines (id_list *list, int sp) { for (; list; list = list->next, sp++) filprintf (out_fil, "#define %s %s%d\n", list->id, (sp <= 0 ? "_stack" : "_extra"), (sp < 0 ? -sp : sp)); } void emit_operation_list (operation_list *oplist) { operation_list *list; int deepest_read = 0, deepest_write = 0, sp, max_height = 0, deepest_write_so_far = 0, i; if (!oplist) return; filprintf (out_fil, " {\n"); /* Compute the overall effect on the stack of the superoperator. The number of elements that are read is usually op->n_read + op->n_in, but in the presence of many operations we need to adjust this for the balance left by previous operations; the same also holds for the number of written elements, which is usually op->in. We also track the maximum height of the stack which is the number of _EXTRA variables that we need. */ for (sp = 0, list = oplist; list; list = list->next) { operation_info *op = list->op; int balance = op->n_out - op->n_in; deepest_read = MAX (deepest_read, op->n_read + op->n_in - sp); deepest_write = MAX (deepest_write, op->n_in - sp); sp += balance; max_height = MAX (max_height, sp); } /* Declare the variables. */ emit_var_declarations ("_stack", " OOP", 0, deepest_read); emit_var_declarations ("_extra", " OOP", 1, max_height); /* Read the input items from the stack. */ for (i = deepest_read; --i >= 0; ) filprintf (out_fil, " _stack%d = STACK_AT (%d);\n", i, i); /* We keep track of the stack effect here too: we pass the current balance to emit_operation_invocation so that it can assign the correct _STACK/_EXTRA variables to the operands of OP, and we pass the number of dirty _STACK variables (tracked by DEEPEST_WRITE_SO_FAR) so that it can emit the PREPARE_STACK macro if necessary. */ for (sp = 0, list = oplist; list; list = list->next) { operation_info *op = list->op; int balance = op->n_out - op->n_in; emit_operation_invocation (op, list->args, sp, deepest_write_so_far); deepest_write_so_far = MAX (deepest_write_so_far, op->n_in - sp); sp += balance; } /* Write back to the stack the items that were overwritten, and emit pushes/pops if the height of the stack has changed. */ emit_stack_update (sp, deepest_write, " ", ";"); filprintf (out_fil, " }\n"); } void emit_operation_invocation (operation_info *op, struct id_list *args, int sp, int deepest_write) { id_list *list, *actual; filprintf (out_fil, " /* %s (", op->name); emit_id_list (op->read, " ", " ", " |"); emit_id_list (op->in, " ", " ", ""); filprintf (out_fil, " --"); emit_id_list (op->read, " ", " ", " |"); emit_id_list (op->out, " ", " ", ""); filprintf (out_fil, " ) */\n"); filprintf (out_fil, " do\n"); filprintf (out_fil, " {\n"); /* Evaluate the arguments. */ for (list = op->args, actual = args; list && actual; list = list->next, actual = actual->next) filprintf (out_fil, "\tint %s = %s;\n", list->id, actual->id); if (list) yyerror ("too few parameters"); if (actual) yyerror ("too many parameters"); if (op->needs_prepare_stack) { filprintf (out_fil, "#define PREPARE_STACK() do { \\\n"); emit_stack_update (sp, deepest_write, " ", "; \\"); filprintf (out_fil, " } while (0)\n"); } if (op->needs_branch_label) filprintf (out_fil, "#define BRANCH_LABEL(local_label) %s_%d_##local_label\n", op->name, op->instantiations++); /* Associate the temporary variables to the stack positions. */ emit_var_defines (op->read, sp - op->n_read - op->n_in + 1); emit_var_defines (op->in, sp - op->n_in + 1); emit_var_defines (op->out, sp - op->n_in + 1); filprintf (out_fil, "%s\n", op->code); /* Leave things clean. */ if (op->needs_branch_label) filprintf (out_fil, "#undef BRANCH_LABEL\n\n"); if (op->needs_prepare_stack) filprintf (out_fil, "#undef PREPARE_STACK\n"); emit_id_list (op->read, "\n#undef ", "#undef ", "\n"); emit_id_list (op->in, "\n#undef ", "#undef ", "\n"); emit_id_list (op->out, "\n#undef ", "#undef ", "\n"); filprintf (out_fil, " }\n"); filprintf (out_fil, " while (0);\n"); } void emit_stack_update (int sp, int deepest_write, const char *before, const char *after) { int i; for (i = deepest_write; --i >= MAX(0, -sp); ) filprintf (out_fil, "%sSTACK_AT (%d) = _stack%d%s\n", before, i, i, after); /* Either pop the input items in excess, or push the output ones. */ if (sp < 0) filprintf (out_fil, "%sPOP_N_OOPS (%d)%s\n", before, -sp, after); else for (i = 1; i <= sp; i++) filprintf (out_fil, "%sPUSH_OOP (_extra%d)%s\n", before, i, after); } void emit_table (table_info *t) { int i; printf (" static void *%s[256] = {\n", t->name); for (i = 0; i < 256; i += 4) printf (" %s%s, %s%s, %s%s, %s%s%c /* %3d */\n", t->entry[i] ? "&&" : "", t->entry[i] ? t->entry[i] : "NULL", t->entry[i+1] ? "&&" : "", t->entry[i+1] ? t->entry[i+1] : "NULL", t->entry[i+2] ? "&&" : "", t->entry[i+2] ? t->entry[i+2] : "NULL", t->entry[i+3] ? "&&" : "", t->entry[i+3] ? t->entry[i+3] : "NULL", i + 4 == 256 ? ' ' : ',', i); printf (" };\n\n"); } table_info * define_table (char *name) { table_info *t = (table_info *) calloc(1, sizeof(table_info)); t->name = name; return t; } void set_table (table_info *t, int from, int to, char *value) { int i; id_list **p_last = t->pool ? t->pool->pnext : &t->pool; id_list *last; t->pool = append_to_id_list (t->pool, value); last = *p_last; for (i = from; i <= to; i++) t->entry[i] = last->id; } void free_table (table_info *t) { free_id_list (t->pool); free (t->name); free (t); } int filprintf (Filament *fil, const char *format, ...) { va_list ap; STREAM *out = stream_new (fil, SNV_UNLIMITED, NULL, snv_filputc); int result; va_start (ap, format); result = stream_vprintf (out, format, ap); va_end (ap); stream_delete (out); return result; } int main () { char *code; errors = 0; printf ("/* Automatically generated by genvm, do not edit! */\n"); out_fil = filnew (NULL, 0); if (yyparse () || errors) exit (1); printf (" goto jump_around;\n"); code = fildelete (out_fil); fputs (code, stdout); printf ("jump_around:\n ;\n"); exit (0); } smalltalk-3.2.5/libgst/oop.inl0000644000175000017500000001626212123404352013216 00000000000000/******************************** -*- C -*- **************************** * * Object table module Inlines. * * ***********************************************************************/ /*********************************************************************** * * Copyright 2000, 2001, 2002, 2006, 2009 Free Software Foundation, Inc. * Written by Steve Byrne. * * This file is part of GNU Smalltalk. * * GNU Smalltalk is free software; you can redistribute it and/or modify it * under the terms of the GNU General Public License as published by the Free * Software Foundation; either version 2, or (at your option) any later * version. * * Linking GNU Smalltalk statically or dynamically with other modules is * making a combined work based on GNU Smalltalk. Thus, the terms and * conditions of the GNU General Public License cover the whole * combination. * * In addition, as a special exception, the Free Software Foundation * give you permission to combine GNU Smalltalk with free software * programs or libraries that are released under the GNU LGPL and with * independent programs running under the GNU Smalltalk virtual machine. * * You may copy and distribute such a system following the terms of the * GNU GPL for GNU Smalltalk and the licenses of the other code * concerned, provided that you include the source code of that other * code when and as the GNU GPL requires distribution of source code. * * Note that people who make modified versions of GNU Smalltalk are not * obligated to grant this special exception for their modified * versions; it is their choice whether to do so. The GNU General * Public License gives permission to release a modified version without * this exception; this exception also makes it possible to release a * modified version which carries forward this exception. * * GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or * FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for * more details. * * You should have received a copy of the GNU General Public License along with * GNU Smalltalk; see the file COPYING. If not, write to the Free Software * Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * ***********************************************************************/ static inline OOP alloc_oop (PTR obj, intptr_t flags); /* Copy the OOP object because it is part of the root set. Integers and already-copied OOPs are not processed silently. */ #define MAYBE_COPY_OOP(oop) do { \ if (!IS_OOP_COPIED(oop)) { \ _gst_copy_an_oop(oop); \ } \ } while(0) /* Mark the OOP object because it is part of the root set. Integers and already-marked OOPs are not processed silently. */ #define MAYBE_MARK_OOP(oop) do { \ if (IS_OOP(oop) && !IS_OOP_MARKED(oop)) { \ _gst_mark_an_oop_internal((oop)); \ } \ } while(0) #define IS_OOP_COPIED(oop) \ (IS_INT(oop) || IS_OOP_VALID_GC (oop)) #define IS_OOP_NEW(oop) \ (((oop)->flags & F_SPACES) != 0) /* This can only be used at the start or the end of an incremental GC cycle. */ #define IS_OOP_VALID_GC(oop) \ (((oop)->flags & _gst_mem.live_flags) != 0) /* After a global GC, the live_flags say that an object is live if it is marked reachable. Old objects that have already survived the incremental sweep pass, however, are not marked as reachable. */ #define IS_OOP_VALID(oop) \ ((oop)->flags & _gst_mem.live_flags \ || (((oop)->flags & F_OLD) \ && ((oop) <= _gst_mem.last_swept_oop \ || (oop) > _gst_mem.next_oop_to_sweep))) #define IS_OOP_MARKED(oop) \ (((oop)->flags & F_REACHABLE) != 0) #define IS_OOP_FREE(oop) \ ((oop)->flags == 0) /* Checks to see if INDEX (a long index into the OOP table, 1 based due to being called from Smalltalk via a primitive) represents a valid OOP. Returns true if so. */ #define OOP_INDEX_VALID(index) \ ((index) >= FIRST_OOP_INDEX && (index) < _gst_mem.ot_size) /* Answer the INDEX-th OOP in the table. */ #define OOP_AT(index) \ ( &_gst_mem.ot[index] ) /* Answer the index of OOP in the table. */ #define OOP_INDEX(oop) \ ( (OOP)(oop) - _gst_mem.ot ) /* Answer whether OOP is a builtin OOP (a Character, true, false, nil). */ #define IS_BUILTIN_OOP(oop) \ ( (OOP)(oop) - _gst_mem.ot < 0 ) /* Set the indirect object pointer OOP to point to OBJ. */ #define SET_OOP_OBJECT(oop, obj) do { \ (oop)->object = (gst_object) (obj); \ } while(0) /* Answer whether ADDR is part of the OOP table. */ #define IS_OOP_ADDR(addr) \ ((OOP)(addr) >= _gst_mem.ot_base \ && (OOP)(addr) <= _gst_mem.last_allocated_oop \ && (((intptr_t)addr & (sizeof (struct oop_s) - 1)) == 0)) /* Answer whether ADDR is part of newspace. */ #define IS_EDEN_ADDR(addr) \ ((OOP *)(addr) >= _gst_mem.eden.minPtr && \ (OOP *)(addr) < _gst_mem.eden.maxPtr) /* Answer whether ADDR is part of survivor space N. */ #define IS_SURVIVOR_ADDR(addr, n) \ ((OOP *)(addr) >= _gst_mem.surv[(n)].minPtr && \ (OOP *)(addr) < _gst_mem.surv[(n)].maxPtr) #define INC_ADD_OOP(oop) \ ((_gst_mem.inc_ptr >= _gst_mem.inc_end ? \ _gst_inc_grow_registry() : (void)0), \ *_gst_mem.inc_ptr++ = (oop)) #define INC_SAVE_POINTER() \ (_gst_mem.inc_ptr - _gst_mem.inc_base) #define INC_RESTORE_POINTER(ptr) \ _gst_mem.inc_ptr = (ptr) + _gst_mem.inc_base; static inline void maybe_release_xlat (OOP oop) { #if defined(ENABLE_JIT_TRANSLATION) if (oop->flags & F_XLAT) { if (oop->flags & F_XLAT_REACHABLE) /* Reachable, and referenced by active contexts. Keep it around. */ oop->flags &= ~F_XLAT_2NDCHANCE; else { /* Reachable, but not referenced by active contexts. We give it a second chance... */ if (oop->flags & F_XLAT_2NDCHANCE) _gst_release_native_code (oop); oop->flags ^= F_XLAT_2NDCHANCE; } } #endif } /* Given an object OBJ, allocate an OOP table slot for it and returns it. It marks the OOP so that it indicates the object is in new space, and that the oop has been referenced on this pass (to keep the OOP table reaper from reclaiming this OOP). */ static inline OOP alloc_oop (PTR objData, intptr_t flags) { REGISTER (1, OOP oop); REGISTER (2, OOP lastOOP); oop = _gst_mem.last_swept_oop + 1; lastOOP = _gst_mem.next_oop_to_sweep; if (COMMON (oop <= lastOOP)) { while (IS_OOP_VALID_GC (oop)) { maybe_release_xlat (oop); oop->flags &= ~F_REACHABLE; if (oop >= lastOOP) { _gst_finished_incremental_gc (); goto fast; } oop++; } _gst_sweep_oop (oop); if (oop >= lastOOP) _gst_finished_incremental_gc (); } else while (IS_OOP_VALID_GC (oop)) { fast: oop++; } _gst_mem.last_swept_oop = oop; PREFETCH_LOOP (oop, PREF_READ); /* Force a GC as soon as possible if we're low on OOPs. */ if UNCOMMON (_gst_mem.num_free_oops-- < LOW_WATER_OOP_THRESHOLD) _gst_mem.eden.maxPtr = _gst_mem.eden.allocPtr; if (oop > _gst_mem.last_allocated_oop) _gst_mem.last_allocated_oop = oop; oop->object = (gst_object) objData; oop->flags = flags; return (oop); } smalltalk-3.2.5/libgst/gstpriv.h0000644000175000017500000004647012130343734013574 00000000000000/******************************** -*- C -*- **************************** * * GNU Smalltalk generic inclusions. * * ***********************************************************************/ /*********************************************************************** * * Copyright 1988,89,90,91,92,94,95,99,2000,2001,2002,2006,2008,2009 * Free Software Foundation, Inc. * Written by Steve Byrne. * * This file is part of GNU Smalltalk. * * GNU Smalltalk is free software; you can redistribute it and/or modify it * under the terms of the GNU General Public License as published by the Free * Software Foundation; either version 2, or (at your option) any later * version. * * Linking GNU Smalltalk statically or dynamically with other modules is * making a combined work based on GNU Smalltalk. Thus, the terms and * conditions of the GNU General Public License cover the whole * combination. * * In addition, as a special exception, the Free Software Foundation * give you permission to combine GNU Smalltalk with free software * programs or libraries that are released under the GNU LGPL and with * independent programs running under the GNU Smalltalk virtual machine. * * You may copy and distribute such a system following the terms of the * GNU GPL for GNU Smalltalk and the licenses of the other code * concerned, provided that you include the source code of that other * code when and as the GNU GPL requires distribution of source code. * * Note that people who make modified versions of GNU Smalltalk are not * obligated to grant this special exception for their modified * versions; it is their choice whether to do so. The GNU General * Public License gives permission to release a modified version without * this exception; this exception also makes it possible to release a * modified version which carries forward this exception. * * GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or * FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for * more details. * * You should have received a copy of the GNU General Public License along with * GNU Smalltalk; see the file COPYING. If not, write to the Free Software * Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * ***********************************************************************/ #ifndef GST_GSTPRIV_H #define GST_GSTPRIV_H #include "config.h" #include #include #include #include #include #include #include #include #include #include #include #include #include #include #include #include #include #include #include #include #include #ifdef HAVE_CRT_EXTERNS_H #include #endif #ifdef HAVE_SYS_RESOURCE_H #include #endif #ifdef HAVE_EXECINFO_H #include #endif #ifdef HAVE_SYS_FILE_H #include #endif #ifdef HAVE_UNISTD_H #include #endif #ifdef HAVE_SYS_MMAN_H #include #endif #ifdef HAVE_STDINT_H #include #endif #ifdef HAVE_INTTYPES_H #include #endif #ifdef HAVE_SIGSEGV_H #include "sigsegv.h" #endif #include "gst.h" /* Convenience macros to test the versions of GCC. Note - they won't work for GCC1, since the _MINOR macros were not defined then, but we don't have anything interesting to test for that. :-) */ #if defined __GNUC__ && defined __GNUC_MINOR__ # define GNUC_PREREQ(maj, min) \ ((__GNUC__ << 16) + __GNUC_MINOR__ >= ((maj) << 16) + (min)) #else # define GNUC_PREREQ(maj, min) 0 #endif /* For internal functions, we can use the ELF hidden attribute to improve code generation. Unluckily, this is only in GCC 3.2 and later */ #ifdef HAVE_VISIBILITY_HIDDEN #define ATTRIBUTE_HIDDEN __attribute__ ((visibility ("hidden"))) #else #define ATTRIBUTE_HIDDEN #endif /* At some point during the GCC 2.96 development the `pure' attribute for functions was introduced. We don't want to use it unconditionally (although this would be possible) since it generates warnings. GCC 2.96 also introduced branch prediction hints for basic block reordering. We use a shorter syntax than the wordy one that GCC wants. */ #if GNUC_PREREQ (2, 96) #define UNCOMMON(x) (__builtin_expect ((x) != 0, 0)) #define COMMON(x) (__builtin_expect ((x) != 0, 1)) #else #define UNCOMMON(x) (x) #define COMMON(x) (x) #endif /* Prefetching macros. The NTA version is for a read that has no temporal locality. The second argument is the kind of prefetch we want, using the flags that follow (T0, T1, T2, NTA follow the names of the instructions in the SSE instruction set). The flags are hints, there is no guarantee that the instruction set has the combination that you ask for -- just trust the compiler. There are three macros. PREFETCH_ADDR is for isolated prefetches, for example it is used in the garbage collector's marking loop to be reasonably sure that OOPs are in the cache before they're marked. PREFETCH_START and PREFETCH_LOOP usually go together, one in the header of the loop and one in the middle. However, you may use PREFETCH_START only for small loops, and PREFETCH_LOOP only if you know that the loop is invoked often (this is done for alloc_oop, for example, to keep the next allocated OOPs in the cache). PREF_BACKWARDS is for use with PREFETCH_START/PREFETCH_LOOP. */ #define PREF_READ 0 #define PREF_WRITE 1 #define PREF_BACKWARDS 2 #define PREF_T0 0 #define PREF_T1 4 #define PREF_T2 8 #define PREF_NTA 12 #if GNUC_PREREQ (3, 1) #define DO_PREFETCH(x, distance, k) \ __builtin_prefetch (((char *) (x)) \ + (((k) & PREF_BACKWARDS ? -(distance) : (distance)) \ << L1_CACHE_SHIFT), \ (k) & PREF_WRITE, \ 3 - (k) / (PREF_NTA / 3)) #else #define DO_PREFETCH(x, distance, kind) ((void)(x)) #endif #define PREFETCH_START(x, k) do { \ const char *__addr = (const char *) (x); \ DO_PREFETCH (__addr, 0, (k)); \ if (L1_CACHE_SHIFT >= 7) break; \ DO_PREFETCH (__addr, 1, (k)); \ if (L1_CACHE_SHIFT == 6) break; \ DO_PREFETCH (__addr, 2, (k)); \ DO_PREFETCH (__addr, 3, (k)); \ } while (0) #define PREFETCH_LOOP(x, k) \ DO_PREFETCH ((x), (L1_CACHE_SHIFT >= 7 ? 1 : 128 >> L1_CACHE_SHIFT), (k)); #define PREFETCH_ADDR(x, k) \ DO_PREFETCH ((x), 0, (k)); /* Synchronization primitives. */ #define __sync_swap(ptr, val) \ ({ __typeof__ (*(ptr)) _x; \ do _x = *(ptr); while (!__sync_bool_compare_and_swap ((ptr), (_x), (val))); \ _x; }) /* Kill a warning when using GNU C. Note that this allows using break or continue inside a macro, unlike do...while(0) */ #ifdef __GNUC__ #define BEGIN_MACRO ((void) ( #define END_MACRO )) #else #define BEGIN_MACRO if (1) #define END_MACRO else (void)0 #endif /* ENABLE_SECURITY enables security checks in the primitives as well as special marking of untrusted objects. Note that the code in the class library to perform the security checks will be present notwithstanding the setting of this flag, but they will be disabled because the corresponding primitives will be made non-working. We define it here with no configure-time options because it causes testsuite failures. */ #define ENABLE_SECURITY /* OPTIMIZE disables many checks, including consistency checks at GC time and bounds checking on instance variable accesses (not on #at: and #at:put: which would violate language semantics). It can a) greatly speed up code by simplifying the interpreter's code b) make debugging painful because you know of a bug only when it's too late. It is undefined because the Makefiles take care of defining it for optimized builds. Bounds-checking and other errors will call abort(). */ /* #define OPTIMIZE */ typedef unsigned char gst_uchar; #ifdef NO_INLINES #define inline #else # if defined (__GNUC__) # undef inline # define inline __inline__ /* let's not lose when --ansi is specified */ # endif #endif /* If they have no const, they're likely to have no volatile, either. */ #ifdef const #define volatile #endif #ifndef HAVE_STRDUP extern char *strdup (); /* else it is in string.h */ #endif /* Run-time flags are allocated from the top, while those that live across image saves/restores are allocated from the bottom. bit 0-3: reserved for distinguishing byte objects and saving their size. bit 4-11: non-volatile bits (special kinds of objects). bit 12-23: volatile bits (GC/JIT-related). bit 24-30: reserved for counting things. bit 31: unused to avoid signedness mess. */ enum { /* Place to save various OOP counts (how many fields we have marked in the object, how many pointer instance variables there are, etc.). Here is a distribution of frequencies in a standard image: 2 to 31 words 24798 objects (96.10%) 32 to 63 words 816 objects ( 3.16%) 64 to 95 words 82 objects ( 0.32%) 96 to 127 words 54 objects ( 0.21%) 128 or more words 54 objects ( 0.21%) which I hope justifies the choice :-) */ F_COUNT = (int) 0x7F000000U, F_COUNT_SHIFT = 24, /* Set if the object is reachable, during the mark phases of oldspace garbage collection. */ F_REACHABLE = 0x800000U, /* Set if a translation to native code is available, when running with the JIT compiler enabled. */ F_XLAT = 0x400000U, /* Set if a translation to native code is used by the currently reachable contexts. */ F_XLAT_REACHABLE = 0x200000U, /* Set if a translation to native code is available but not used by the reachable contexts at the time of the last GC. We give another chance to the object, but if the translation is not used for two consecutive GCs we discard it. */ F_XLAT_2NDCHANCE = 0x100000U, /* Set if a translation to native code was discarded for this object (either because the programmer asked for this, or because the method conflicted with a newly-installed method). */ F_XLAT_DISCARDED = 0x80000U, /* One of this is set for objects that live in newspace. */ F_SPACES = 0x60000U, F_EVEN = 0x40000U, F_ODD = 0x20000U, /* Set if the OOP is allocated by the pools of contexts maintained in interp.c (maybe it belongs above...) */ F_POOLED = 0x10000U, /* Set if the bytecodes in the method have been verified. */ F_VERIFIED = 0x8000U, /* The grouping of all the flags which are not valid across image saves and loads. */ F_RUNTIME = 0xFF8000U, /* Set if the references to the instance variables of the object are weak. */ F_WEAK = 0x10U, /* Set if the object is read-only. */ F_READONLY = 0x20U, /* Set if the object is a context and hence its instance variables are only valid up to the stack pointer. */ F_CONTEXT = 0x40U, /* Answer whether we want to mark the key based on references found outside the object. */ F_EPHEMERON = 0x80U, /* Set for objects that live in oldspace. */ F_OLD = 0x100U, /* Set together with F_OLD for objects that live in fixedspace. */ F_FIXED = 0x200U, /* Set for untrusted classes, instances of untrusted classes, and contexts whose receiver is untrusted. */ F_UNTRUSTED = 0x400U, /* Set for objects that were loaded from the image. We never garbage collect their contents, only the OOPs. */ F_LOADED = 0x800U, /* Set to the number of bytes unused in an object with byte-sized instance variables. Note that this field and the following one should be initialized only by INIT_UNALIGNED_OBJECT (not really aesthetic but...) */ EMPTY_BYTES = (sizeof (PTR) - 1), /* A bit more than what is identified by EMPTY_BYTES. Selects some bits that are never zero if and only if this OOP identifies an object with byte instance variables. */ F_BYTE = 15 }; /* Answer whether a method, OOP, has already been verified. */ #define IS_OOP_VERIFIED(oop) \ (((oop)->flags & F_VERIFIED) != 0) /* Answer whether an object, OOP, is weak. */ #define IS_OOP_WEAK(oop) \ (((oop)->flags & F_WEAK) != 0) /* Answer whether an object, OOP, is readonly. */ #define IS_OOP_READONLY(oop) \ (IS_INT ((oop)) || ((oop)->flags & F_READONLY)) /* Set whether an object, OOP, is readonly or readwrite. */ #define MAKE_OOP_READONLY(oop, ro) \ (((oop)->flags &= ~F_READONLY), \ ((oop)->flags |= (ro) ? F_READONLY : 0)) #ifdef ENABLE_SECURITY /* Answer whether an object, OOP, is untrusted. */ #define IS_OOP_UNTRUSTED(oop) \ (!IS_INT ((oop)) && ((oop)->flags & F_UNTRUSTED)) /* Set whether an object, OOP, is trusted or untrusted. */ #define MAKE_OOP_UNTRUSTED(oop, untr) \ (((oop)->flags &= ~F_UNTRUSTED), \ ((oop)->flags |= (untr) ? F_UNTRUSTED : 0)) #else #define IS_OOP_UNTRUSTED(oop) (false) #define MAKE_OOP_UNTRUSTED(oop, untr) ((void)0) #endif /* Set whether an object, OOP, has ephemeron semantics. */ #define MAKE_OOP_EPHEMERON(oop) \ (oop)->flags |= F_EPHEMERON; /* the current execution stack pointer */ #ifndef ENABLE_JIT_TRANSLATION # define sp _gst_sp #endif /* The VM's stack pointer */ extern OOP *sp ATTRIBUTE_HIDDEN; /* Some useful constants */ extern OOP _gst_nil_oop ATTRIBUTE_HIDDEN, _gst_true_oop ATTRIBUTE_HIDDEN, _gst_false_oop ATTRIBUTE_HIDDEN; /* Some stack operations */ #define UNCHECKED_PUSH_OOP(oop) \ (*++sp = (oop)) #define UNCHECKED_SET_TOP(oop) \ (*sp = (oop)) #ifndef OPTIMIZE #define PUSH_OOP(oop) \ do { \ OOP __pushOOP = (oop); \ if (IS_OOP (__pushOOP) && !IS_OOP_VALID (__pushOOP)) \ abort (); \ UNCHECKED_PUSH_OOP (__pushOOP); \ } while (0) #else #define PUSH_OOP(oop) \ do { \ OOP __pushOOP = (oop); \ UNCHECKED_PUSH_OOP (__pushOOP); \ } while (0) #endif #define POP_OOP() \ (*sp--) #define POP_N_OOPS(n) \ (sp -= (n)) #define UNPOP(n) \ (sp += (n)) #define STACKTOP() \ (*sp) #ifndef OPTIMIZE #define SET_STACKTOP(oop) \ do { \ OOP __pushOOP = (oop); \ if (IS_OOP (__pushOOP) && !IS_OOP_VALID (__pushOOP)) \ abort (); \ UNCHECKED_SET_TOP(__pushOOP); \ } while (0) #else #define SET_STACKTOP(oop) \ do { \ OOP __pushOOP = (oop); \ UNCHECKED_SET_TOP(__pushOOP); \ } while (0) #endif #define SET_STACKTOP_INT(i) \ UNCHECKED_SET_TOP(FROM_INT(i)) #define SET_STACKTOP_BOOLEAN(exp) \ UNCHECKED_SET_TOP((exp) ? _gst_true_oop : _gst_false_oop) #define STACK_AT(i) \ (sp[-(i)]) #define PUSH_INT(i) \ UNCHECKED_PUSH_OOP(FROM_INT(i)) #define POP_INT() \ TO_INT(POP_OOP()) #define PUSH_BOOLEAN(exp) \ PUSH_OOP((exp) ? _gst_true_oop : _gst_false_oop) /* Answer whether CLASS is the class that the object pointed to by OOP belongs to. OOP can also be a SmallInteger. */ #define IS_CLASS(oop, class) \ (OOP_INT_CLASS(oop) == class) /* Answer the CLASS that the object pointed to by OOP belongs to. OOP can also be a SmallInteger. */ #define OOP_INT_CLASS(oop) \ (IS_INT(oop) ? _gst_small_integer_class : OOP_CLASS(oop)) /* Answer whether OOP is nil. */ #define IS_NIL(oop) \ ((OOP)(oop) == _gst_nil_oop) /* This macro should only be used right after an alloc_oop, when the emptyBytes field is guaranteed to be zero. Note that F_BYTE is a bit more than EMPTY_BYTES, so that if value is a multiple of sizeof (PTR) the flags identified by F_BYTE are not zero. */ #define INIT_UNALIGNED_OBJECT(oop, value) \ ((oop)->flags |= sizeof (PTR) | (value)) /* Generally useful conversion functions */ #define SIZE_TO_BYTES(size) \ ((size) * sizeof (PTR)) #define BYTES_TO_SIZE(bytes) \ ((bytes) / sizeof (PTR)) #ifdef __GNUC__ #define no_opt(x) ({ __typeof__ ((x)) _result; \ asm ("" : "=r" (_result) : "0" ((x))); _result; }) #define barrier() asm ("") #else #define no_opt(x) (x) #define barrier() #endif /* integer conversions and some information on SmallIntegers. */ #define TO_INT(oop) \ ((intptr_t)(oop) >> 1) #define FROM_INT(i) \ (OOP)( ((intptr_t)(i) << 1) + 1) #define ST_INT_SIZE ((sizeof (PTR) * 8) - 2) #define MAX_ST_INT ((1L << ST_INT_SIZE) - 1) #define MIN_ST_INT ( ~MAX_ST_INT) #define INT_OVERFLOW(i) (((i) ^ ((i) << 1)) < 0) #define OVERFLOWING_INT (MAX_ST_INT + 1) #define INCR_INT(i) ((OOP) (((intptr_t)i) + 2)) /* 1 << 1 */ #define DECR_INT(i) ((OOP) (((intptr_t)i) - 2)) /* 1 << 1 */ /* Endian conversions, using networking functions if they do the correct job (that is, on 32-bit little-endian systems) because they are likely to be optimized. */ #if SIZEOF_OOP == 4 # if !defined(WORDS_BIGENDIAN) && defined (HAVE_SOCKETS) # define BYTE_INVERT(x) htonl((x)) # elif defined _OS_OSBYTEORDERPPC_H # define BYTE_INVERT(x) OSReadSwapInt32(&(x), 0) # else # define BYTE_INVERT(x) \ ((uintptr_t)((((uintptr_t)(x) & 0x000000ffU) << 24) | \ (((uintptr_t)(x) & 0x0000ff00U) << 8) | \ (((uintptr_t)(x) & 0x00ff0000U) >> 8) | \ (((uintptr_t)(x) & 0xff000000U) >> 24))) # endif #else /* SIZEOF_OOP == 8 */ # if defined _OS_OSBYTEORDERPPC_H # define BYTE_INVERT(x) OSReadSwapInt64(&(x), 0) # else # define BYTE_INVERT(x) \ ((uintptr_t)((((uintptr_t)(x) & 0x00000000000000ffU) << 56) | \ (((uintptr_t)(x) & 0x000000000000ff00U) << 40) | \ (((uintptr_t)(x) & 0x0000000000ff0000U) << 24) | \ (((uintptr_t)(x) & 0x00000000ff000000U) << 8) | \ (((uintptr_t)(x) & 0x000000ff00000000U) >> 8) | \ (((uintptr_t)(x) & 0x0000ff0000000000U) >> 24) | \ (((uintptr_t)(x) & 0x00ff000000000000U) >> 40) | \ (((uintptr_t)(x) & 0xff00000000000000U) >> 56))) # endif #endif /* SIZEOF_OOP == 8 */ /* The standard min/max macros... */ #ifndef ABS #define ABS(x) (x >= 0 ? x : -x) #endif #ifndef MAX #define MAX(x, y) ( ((x) > (y)) ? (x) : (y) ) #endif #ifndef MIN #define MIN(x, y) ( ((x) > (y)) ? (y) : (x) ) #endif #include "ansidecl.h" #include "mathl.h" #include "socketx.h" #include "strspell.h" #include "alloc.h" #include "md-config.h" #include "avltrees.h" #include "rbtrees.h" #include "tree.h" #include "files.h" #include "input.h" #include "callin.h" #include "cint.h" #include "dict.h" #include "heap.h" #include "lex.h" #include "gst-parse.h" #include "oop.h" #include "byte.h" #include "sym.h" #include "comp.h" #include "interp.h" #include "events.h" #include "opt.h" #include "save.h" #include "str.h" #include "sysdep.h" #include "xlat.h" #include "mpz.h" #include "print.h" #include "security.h" #include "real.h" #include "sockets.h" /* Include this last, it has the bad habit of #defining printf and this fools gcc's __attribute__ (format) */ #include "snprintfv/printf.h" #undef obstack_init #define obstack_init(h) \ _obstack_begin ((h), 0, ALIGNOF_LONG_DOUBLE, \ (void *(*) (long)) obstack_chunk_alloc, \ (void (*) (void *)) obstack_chunk_free) #undef obstack_begin #define obstack_begin(h, size) \ _obstack_begin ((h), (size), ALIGNOF_LONG_DOUBLE, \ (void *(*) (long)) obstack_chunk_alloc, \ (void (*) (void *)) obstack_chunk_free) #include "oop.inl" #include "dict.inl" #include "interp.inl" #include "comp.inl" #endif /* GST_GSTPRIV_H */ smalltalk-3.2.5/libgst/re.h0000644000175000017500000000525612123404352012475 00000000000000/*********************************************************************** * * Regular expression interface definitions for GNU Smalltalk * * ***********************************************************************/ /*********************************************************************** * * Copyright 2001, 2002, 2006 Free Software Foundation, Inc. * Written by Paolo Bonzini and Dragomir Milevojevic. * * This file is part of GNU Smalltalk. * * GNU Smalltalk is free software; you can redistribute it and/or modify it * under the terms of the GNU General Public License as published by the Free * Software Foundation; either version 2, or (at your option) any later * version. * * Linking GNU Smalltalk statically or dynamically with other modules is * making a combined work based on GNU Smalltalk. Thus, the terms and * conditions of the GNU General Public License cover the whole * combination. * * In addition, as a special exception, the Free Software Foundation * give you permission to combine GNU Smalltalk with free software * programs or libraries that are released under the GNU LGPL and with * independent programs running under the GNU Smalltalk virtual machine. * * You may copy and distribute such a system following the terms of the * GNU GPL for GNU Smalltalk and the licenses of the other code * concerned, provided that you include the source code of that other * code when and as the GNU GPL requires distribution of source code. * * Note that people who make modified versions of GNU Smalltalk are not * obligated to grant this special exception for their modified * versions; it is their choice whether to do so. The GNU General * Public License gives permission to release a modified version without * this exception; this exception also makes it possible to release a * modified version which carries forward this exception. * * GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or * FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for * more details. * * You should have received a copy of the GNU General Public License along with * GNU Smalltalk; see the file COPYING. If not, write to the Free Software * Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * ***********************************************************************/ /* Functions exported to Smalltalk */ OOP _gst_re_make_cacheable (OOP patternOOP) ATTRIBUTE_HIDDEN; OOP _gst_re_search (OOP srcOOP, OOP patternOOP, int from, int to) ATTRIBUTE_HIDDEN; int _gst_re_match (OOP srcOOP, OOP patternOOP, int from, int to) ATTRIBUTE_HIDDEN; smalltalk-3.2.5/libgst/jitpriv.h0000644000175000017500000000611512123404352013551 00000000000000/******************************** -*- C -*- **************************** * * A few functions that only xlat.c needs to have access to * * ***********************************************************************/ /*********************************************************************** * * Copyright 2001, 2002, 2006 Free Software Foundation, Inc. * Written by Paolo Bonzini. * * This file is part of GNU Smalltalk. * * GNU Smalltalk is free software; you can redistribute it and/or modify it * under the terms of the GNU General Public License as published by the Free * Software Foundation; either version 2, or (at your option) any later * version. * * Linking GNU Smalltalk statically or dynamically with other modules is * making a combined work based on GNU Smalltalk. Thus, the terms and * conditions of the GNU General Public License cover the whole * combination. * * In addition, as a special exception, the Free Software Foundation * give you permission to combine GNU Smalltalk with free software * programs or libraries that are released under the GNU LGPL and with * independent programs running under the GNU Smalltalk virtual machine. * * You may copy and distribute such a system following the terms of the * GNU GPL for GNU Smalltalk and the licenses of the other code * concerned, provided that you include the source code of that other * code when and as the GNU GPL requires distribution of source code. * * Note that people who make modified versions of GNU Smalltalk are not * obligated to grant this special exception for their modified * versions; it is their choice whether to do so. The GNU General * Public License gives permission to release a modified version without * this exception; this exception also makes it possible to release a * modified version which carries forward this exception. * * GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or * FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for * more details. * * You should have received a copy of the GNU General Public License along with * GNU Smalltalk; see the file COPYING. If not, write to the Free Software * Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * ***********************************************************************/ #ifndef GST_INTERNAL_H #define GST_INTERNAL_H #ifdef ENABLE_JIT_TRANSLATION /* These are functions that are called by the JIT-compiled code and yet are internal to interp.c. xlat.c needs their addresses so that it can store them in the compiled code it generates. */ typedef void (*internal_func) (); extern const internal_func _gst_internal_funcs[6]; #define PTR_UNWIND_CONTEXT _gst_internal_funcs[0] #define PTR_UNWIND_METHOD _gst_internal_funcs[1] #define PTR_ACTIVATE_NEW_CONTEXT _gst_internal_funcs[2] #define PTR_PREPARE_CONTEXT _gst_internal_funcs[3] #define PTR_EMPTY_CONTEXT_STACK _gst_internal_funcs[4] #define PTR_LOOKUP_NATIVE_IP _gst_internal_funcs[5] #endif #endif /* GST_INTERNAL_H */ smalltalk-3.2.5/libgst/gstpub.c0000644000175000017500000002652712130343734013376 00000000000000/******************************** -*- C -*- **************************** * * Public entry points * * This module provides public routines with a "gst_" prefix. * These are exported by the dynamic library. * * ***********************************************************************/ /*********************************************************************** * * Copyright 2007, 2008, 2009 Free Software Foundation, Inc. * Written by Steve Byrne. * * This file is part of GNU Smalltalk. * * GNU Smalltalk is free software; you can redistribute it and/or modify it * under the terms of the GNU General Public License as published by the Free * Software Foundation; either version 2, or (at your option) any later * version. * * Linking GNU Smalltalk statically or dynamically with other modules is * making a combined work based on GNU Smalltalk. Thus, the terms and * conditions of the GNU General Public License cover the whole * combination. * * In addition, as a special exception, the Free Software Foundation * give you permission to combine GNU Smalltalk with free software * programs or libraries that are released under the GNU LGPL and with * independent programs running under the GNU Smalltalk virtual machine. * * You may copy and distribute such a system following the terms of the * GNU GPL for GNU Smalltalk and the licenses of the other code * concerned, provided that you include the source code of that other * code when and as the GNU GPL requires distribution of source code. * * Note that people who make modified versions of GNU Smalltalk are not * obligated to grant this special exception for their modified * versions; it is their choice whether to do so. The GNU General * Public License gives permission to release a modified version without * this exception; this exception also makes it possible to release a * modified version which carries forward this exception. * * GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or * FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for * more details. * * You should have received a copy of the GNU General Public License along with * GNU Smalltalk; see the file COPYING. If not, write to the Free Software * Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * return ***********************************************************************/ #include "gstpriv.h" /* By not including this file anywhere else, we make sure that _gst functions are always called, and don't create unnecessary PLA entries. */ #include "gstpub.h" VMProxy gst_interpreter_proxy = { NULL, NULL, NULL, _gst_msg_send, _gst_vmsg_send, _gst_nvmsg_send, _gst_str_msg_send, _gst_msg_sendf, _gst_eval_expr, _gst_eval_code, _gst_object_alloc, _gst_basic_size, _gst_define_cfunc, _gst_register_oop, _gst_unregister_oop, /* Convert C datatypes to Smalltalk types */ _gst_id_to_oop, _gst_int_to_oop, _gst_float_to_oop, _gst_bool_to_oop, _gst_char_to_oop, _gst_class_name_to_oop, _gst_string_to_oop, _gst_byte_array_to_oop, _gst_symbol_to_oop, _gst_c_object_to_oop, _gst_type_name_to_oop, _gst_set_c_object, /* Convert Smalltalk datatypes to C data types */ _gst_oop_to_c, _gst_oop_to_id, _gst_oop_to_int, _gst_oop_to_float, _gst_oop_to_bool, _gst_oop_to_char, _gst_oop_to_string, _gst_oop_to_byte_array, _gst_oop_to_c_object, /* Smalltalk process support */ _gst_async_signal, _gst_sync_wait, _gst_async_signal_and_unregister, _gst_register_oop_array, _gst_unregister_oop_array, /* Convert Smalltalk datatypes to C data types (2) */ _gst_oop_to_long_double, _gst_long_double_to_oop, _gst_get_object_class, _gst_get_superclass, _gst_class_is_kind_of, _gst_object_is_kind_of, _gst_perform, _gst_perform_with, _gst_class_implements_selector, _gst_class_can_understand, _gst_responds_to, _gst_oop_size, _gst_oop_at, _gst_oop_at_put, /* System objects. */ NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, NULL, /* New in 2.3. */ _gst_wchar_to_oop, _gst_wstring_to_oop, _gst_oop_to_wchar, _gst_oop_to_wstring, /* New in 3.0. */ _gst_process_stdin, _gst_process_file, _gst_get_var, _gst_set_var, _gst_invoke_hook, /* New in 3.1. */ _gst_relocate_path, _gst_oop_indexed_base, _gst_oop_indexed_kind, _gst_async_call, _gst_sync_signal, _gst_show_backtrace, /* New in 3.2. */ _gst_dlopen, _gst_dladdsearchdir, _gst_dlpushsearchpath, _gst_dlpopsearchpath, _gst_wakeup, /* New in 3.2.5. */ _gst_uint_to_oop }; /* Functions in comp.h. */ void gst_invoke_hook (enum gst_vm_hook hook) { _gst_invoke_hook (hook); } void gst_smalltalk_args (int argc, const char **argv) { _gst_smalltalk_args (argc, argv); } int gst_initialize (const char *kernel_dir, const char *image_file, int flags) { return _gst_initialize (kernel_dir, image_file, flags); } void gst_process_stdin (const char *prompt) { _gst_process_stdin (prompt); } mst_Boolean gst_process_file (const char *fileName, enum gst_file_dir dir) { return _gst_process_file (fileName, dir); } int gst_get_var (enum gst_var_index index) { return _gst_get_var (index); } int gst_set_var (enum gst_var_index index, int value) { return _gst_set_var (index, value); } OOP gst_msg_send (OOP receiver, OOP selector, ...) { va_list ap; va_start (ap, selector); return _gst_va_msg_send (receiver, selector, ap); } OOP gst_vmsg_send (OOP receiver, OOP selector, OOP * args) { return _gst_vmsg_send (receiver, selector, args); } OOP gst_nvmsg_send (OOP receiver, OOP selector, OOP * args, int nargs) { return _gst_nvmsg_send (receiver, selector, args, nargs); } OOP gst_str_msg_send (OOP receiver, const char *sel, ...) { va_list ap; OOP selector = _gst_symbol_to_oop (sel); va_start (ap, sel); return _gst_va_msg_send (receiver, selector, ap); } void gst_msg_sendf (PTR result_ptr, const char *fmt, ...) { va_list ap; va_start (ap, fmt); _gst_va_msg_sendf (result_ptr, fmt, ap); } OOP gst_eval_expr (const char *str) { return _gst_eval_expr (str); } void gst_eval_code (const char *str) { _gst_eval_code (str); } OOP gst_object_alloc (OOP class_oop, int size) { return _gst_object_alloc (class_oop, size); } int gst_basic_size (OOP oop) { return _gst_basic_size (oop); } void gst_define_cfunc (const char *func_name, PTR func_addr) { _gst_define_cfunc (func_name, func_addr); } OOP gst_register_oop (OOP oop) { return _gst_register_oop (oop); } void gst_unregister_oop (OOP oop) { _gst_unregister_oop (oop); } OOP gst_id_to_oop (long i) { return _gst_id_to_oop (i); } OOP gst_int_to_oop (long i) { return _gst_int_to_oop (i); } OOP gst_uint_to_oop (unsigned long i) { return _gst_uint_to_oop (i); } OOP gst_float_to_oop (double f) { return _gst_float_to_oop (f); } OOP gst_bool_to_oop (int b) { return _gst_bool_to_oop (b); } OOP gst_char_to_oop (char c) { return _gst_char_to_oop (c); } OOP gst_class_name_to_oop (const char *name) { return _gst_class_name_to_oop (name); } OOP gst_string_to_oop (const char *str) { return _gst_string_to_oop (str); } OOP gst_byte_array_to_oop (const char *str, int n) { return _gst_byte_array_to_oop (str, n); } OOP gst_symbol_to_oop (const char *str) { return _gst_symbol_to_oop (str); } OOP gst_c_object_to_oop (PTR co) { return _gst_c_object_to_oop (co); } OOP gst_type_name_to_oop (const char *name) { return _gst_type_name_to_oop (name); } void gst_set_c_object (OOP oop, PTR co) { _gst_set_c_object (oop, co); } long gst_oop_to_c (OOP oop) { return _gst_oop_to_c (oop); } /*sometimes answers a PTR */ long gst_oop_to_id (OOP oop) { return _gst_oop_to_id (oop); } long gst_oop_to_int (OOP oop) { return _gst_oop_to_int (oop); } double gst_oop_to_float (OOP oop) { return _gst_oop_to_float (oop); } int gst_oop_to_bool (OOP oop) { return _gst_oop_to_bool (oop); } char gst_oop_to_char (OOP oop) { return _gst_oop_to_char (oop); } char * gst_oop_to_string (OOP oop) { return _gst_oop_to_string (oop); } char * gst_oop_to_byte_array (OOP oop) { return _gst_oop_to_byte_array (oop); } PTR gst_oop_to_c_object (OOP oop) { return _gst_oop_to_c_object (oop); } void gst_async_signal (OOP semaphore_oop) { _gst_async_signal (semaphore_oop); } void gst_sync_wait (OOP semaphore_oop) { _gst_sync_wait (semaphore_oop); } void gst_async_signal_and_unregister (OOP semaphore_oop) { _gst_async_signal_and_unregister (semaphore_oop); } mst_Boolean gst_sync_signal (OOP semaphore_oop, mst_Boolean incr_if_empty) { return _gst_sync_signal (semaphore_oop, incr_if_empty); } void gst_async_call (void (*func) (OOP), OOP semaphore_oop) { _gst_async_call (func, semaphore_oop); } void gst_show_backtrace (FILE *fp) { _gst_show_backtrace (fp); } mst_Boolean gst_dlopen (const char *filename, mst_Boolean module) { return _gst_dlopen (filename, module); } void gst_dladdsearchdir (const char *dir) { _gst_dladdsearchdir (dir); } void gst_dlpushsearchpath (void) { _gst_dlpushsearchpath (); } void gst_dlpopsearchpath (void) { _gst_dlpopsearchpath (); } void gst_wakeup () { _gst_wakeup (); } void gst_register_oop_array (OOP **first, OOP **last) { _gst_register_oop_array (first, last); } void gst_unregister_oop_array (OOP **first) { _gst_unregister_oop_array (first); } long double gst_oop_to_long_double (OOP oop) { return _gst_oop_to_long_double (oop); } OOP gst_long_double_to_oop (long double f) { return _gst_long_double_to_oop (f); } OOP gst_wchar_to_oop (wchar_t c) { return _gst_wchar_to_oop (c); } OOP gst_wstring_to_oop (const wchar_t *str) { return _gst_wstring_to_oop (str); } wchar_t gst_oop_to_wchar (OOP oop) { return _gst_oop_to_wchar (oop); } wchar_t * gst_oop_to_wstring (OOP oop) { return _gst_oop_to_wstring (oop); } OOP gst_get_object_class (OOP oop) { return _gst_get_object_class (oop); } OOP gst_get_superclass (OOP oop) { return _gst_get_superclass (oop); } mst_Boolean gst_class_is_kind_of (OOP oop, OOP candidate) { return _gst_class_is_kind_of (oop, candidate); } mst_Boolean gst_object_is_kind_of (OOP oop, OOP candidate) { return _gst_object_is_kind_of (oop, candidate); } OOP gst_perform (OOP oop, OOP selector) { return _gst_perform (oop, selector); } OOP gst_perform_with (OOP oop, OOP selector, OOP arg) { return _gst_perform_with (oop, selector, arg); } mst_Boolean gst_class_implements_selector (OOP class_oop, OOP selector) { return _gst_class_implements_selector (class_oop, selector); } mst_Boolean gst_class_can_understand (OOP class_oop, OOP selector) { return _gst_class_can_understand (class_oop, selector); } mst_Boolean gst_responds_to (OOP oop, OOP selector) { return _gst_responds_to (oop, selector); } size_t gst_oop_size (OOP oop) { return _gst_oop_size (oop); } OOP gst_oop_at (OOP oop, size_t index) { return _gst_oop_at (oop, index); } OOP gst_oop_at_put (OOP oop, size_t index, OOP new_oop) { return _gst_oop_at_put (oop, index, new_oop); } enum gst_indexed_kind gst_oop_indexed_kind (OOP oop) { return _gst_oop_indexed_kind (oop); } void * gst_oop_indexed_base (OOP oop) { return _gst_oop_indexed_base (oop); } /* Functions in sysdep.h. */ void gst_set_executable_path (const char *argv0) { _gst_set_executable_path (argv0); } char * gst_relocate_path (const char *path) { return _gst_relocate_path (path); } smalltalk-3.2.5/libgst/Makefile.am0000644000175000017500000001435512130343734013756 00000000000000LEX_OUTPUT_ROOT = lex.yy ## CFLAGS=-O0 -g AM_CFLAGS = $(LIBGST_CFLAGS) AM_LFLAGS = -Cfe -o$(LEX_OUTPUT_ROOT).c AM_YFLAGS = -vy AM_CPPFLAGS = $(RELOC_CPPFLAGS) \ -I$(top_srcdir)/lib-src -I$(top_builddir)/lib-src \ $(INCFFI) $(INCLIGHTNING) $(INCSNPRINTFV) $(INCSIGSEGV) $(INCLTDL) if !HAVE_INSTALLED_LIGHTNING AM_CPPFLAGS += -I$(top_srcdir)/lightning -I$(top_builddir)/lightning \ -I$(top_srcdir) -I$(top_builddir) endif include_HEADERS = gstpub.h gst.h lib_LTLIBRARIES = libgst.la EXTRA_PROGRAMS = genprims genbc genvm CLEANFILES = genprims$(EXEEXT) genbc$(EXEEXT) genvm$(EXEEXT) \ genbc-decl.stamp genbc-impl.stamp genpr-parse.stamp genvm-parse.stamp # definitions for libgst.la libgst_la_LIBADD=$(top_builddir)/lib-src/library.la \ $(LIBSIGSEGV) $(LIBFFI) $(LIBSNPRINTFV) $(LIBREADLINE) $(LIBLTDL) \ $(LIBGMP) $(LIBTHREAD) libgst_la_DEPENDENCIES=$(top_builddir)/lib-src/library.la $(LIBSNPRINTFV) libgst_la_LDFLAGS = -version-info $(VERSION_INFO) -no-undefined \ -export-symbols-regex "^gst_.*" -bindir $(bindir) libgst_la_SOURCES = \ gstpub.c files.c gst-parse.c lex.c \ str.c tree.c byte.c comp.c \ sym.c dict.c oop.c opt.c \ save.c cint.c heap.c input.c \ sysdep.c callin.c xlat.c mpz.c \ print.c alloc.c security.c re.c \ interp.c real.c sockets.c events.c # definitions for genprims genprims_SOURCES = \ genpr-parse.y genpr-scan.l genprims_LDADD = @LIBSNPRINTFV@ $(top_builddir)/lib-src/library.la # definitions for genbc genbc_SOURCES = \ genbc-decl.y genbc-impl.y genbc-scan.l genbc.c genbc_LDADD = @LIBSNPRINTFV@ $(top_builddir)/lib-src/library.la # definitions for genvm genvm_SOURCES = \ genvm-parse.y genvm-scan.l genvm_LDADD = @LIBSNPRINTFV@ $(top_builddir)/lib-src/library.la # manually give dependencies involving BUILT_SOURCES. The input .l/.y files # change rarely, so do not bother changing the timestamp file only if the # output changed. genbc-decl.stamp: genbc-decl.c genbc-decl.y; echo stamp > $@ genbc-impl.stamp: genbc-impl.c genbc-impl.y; echo stamp > $@ genpr-parse.stamp: genpr-parse.c genpr-parse.y; echo stamp > $@ genvm-parse.stamp: genvm-parse.c genvm-parse.y; echo stamp > $@ genbc.o: genbc-decl.stamp genbc-impl.stamp genbc-scan.o: genbc-decl.stamp genbc-impl.stamp genbc-decl.o: genbc-decl.stamp genbc-impl.stamp genbc-impl.o: genbc-decl.stamp genbc-impl.stamp genpr-scan.o: genpr-parse.stamp genvm-scan.o: genvm-parse.stamp BUILT_SOURCES = prims.inl match.h builtins.inl vm.inl \ genbc-decl.c genbc-impl.c genbc-scan.c genbc-decl.h genbc-impl.h \ genpr-parse.c genpr-scan.c genpr-parse.h \ genvm-parse.c genvm-scan.c genvm-parse.h dist_noinst_DATA = valgrind.supp prims.def byte.def vm.def builtins.gperf STAMP_FILES = prims.stamp match.stamp vm.stamp noinst_HEADERS = \ gstpriv.h files.h lex.h str.h re.h \ tree.h byte.h interp.h comp.h \ sym.h dict.h oop.h save.h cint.h xlat.h \ sysdep.h callin.h gstpub.h opt.h mpz.h \ md-config.h heap.h real.h jitpriv.h oop.inl \ dict.inl interp.inl interp-bc.inl interp-jit.inl \ sockets.h comp.inl input.h events.h \ print.h alloc.h genprims.h gst-parse.h \ genpr-parse.h genbc.h genbc-decl.h \ genbc-impl.h genvm-parse.h genvm.h \ security.h superop1.inl superop2.inl \ sysdep/common/files.c sysdep/common/time.c sysdep/cygwin/files.c \ sysdep/cygwin/findexec.c sysdep/cygwin/mem.c sysdep/cygwin/signals.c \ sysdep/cygwin/time.c sysdep/cygwin/timer.c sysdep/posix/files.c \ sysdep/posix/findexec.c sysdep/posix/mem.c sysdep/posix/signals.c \ sysdep/posix/time.c sysdep/posix/timer.c sysdep/win32/files.c \ sysdep/win32/findexec.c sysdep/win32/mem.c sysdep/win32/signals.c \ sysdep/win32/time.c sysdep/win32/timer.c sysdep/posix/events.c \ sysdep/win32/events.c sysdep/cygwin/events.c \ $(BUILT_SOURCES) # rules for invoking genbc # Try to economize in the rebuilds, by avoiding unnecessary # changes to the timestamp of match.h $(srcdir)/match.h: $(srcdir)/match.stamp @: $(srcdir)/match.stamp: byte.def byte.c opt.c xlat.c @$(MAKE) genbc$(EXEEXT) @echo "./genbc$(EXEEXT) $(srcdir)/byte.def $(srcdir)/byte.c $(srcdir)/opt.c $(srcdir)/xlat.c > match.h"; \ ./genbc$(EXEEXT) $(srcdir)/byte.def $(srcdir)/byte.c $(srcdir)/opt.c $(srcdir)/xlat.c > _match.h @if cmp _match.h $(srcdir)/match.h > /dev/null 2>&1; then \ echo match.h is unchanged; \ rm _match.h; \ else \ mv _match.h $(srcdir)/match.h; \ fi @echo timestamp > $(srcdir)/match.stamp # rules for invoking genprims # Try to economize in the rebuilds, by avoiding unnecessary # changes to the timestamp of prims.inl $(srcdir)/prims.inl: $(srcdir)/prims.stamp @: $(srcdir)/prims.stamp: prims.def @$(MAKE) genprims$(EXEEXT) @echo "./genprims$(EXEEXT) < $(srcdir)/prims.def > prims.inl"; \ ./genprims$(EXEEXT) < $(srcdir)/prims.def > _prims.inl @if cmp _prims.inl $(srcdir)/prims.inl > /dev/null 2>&1; then \ echo prims.inl is unchanged; \ rm _prims.inl; \ else \ mv _prims.inl $(srcdir)/prims.inl; \ fi @echo timestamp > $(srcdir)/prims.stamp # rules for invoking genvm # Try to economize in the rebuilds, by avoiding unnecessary # changes to the timestamp of vm.inl $(srcdir)/vm.inl: $(srcdir)/vm.stamp @: $(srcdir)/vm.stamp: vm.def @$(MAKE) genvm$(EXEEXT) @echo "./genvm$(EXEEXT) < $(srcdir)/vm.def | awk '{ /^#/ && gsub(/__oline__/,NR+1); print }' > vm.inl"; \ ./genvm$(EXEEXT) < $(srcdir)/vm.def | awk '{ /^#/ && gsub(/__oline__/,NR+1); print }' > _vm.inl @if cmp _vm.inl $(srcdir)/vm.inl > /dev/null 2>&1; then \ echo vm.inl is unchanged; \ rm _vm.inl; \ else \ mv _vm.inl $(srcdir)/vm.inl; \ fi @echo timestamp > $(srcdir)/vm.stamp # rules for invoking gperf # not fully idiot-proof but only to be run by maintainers %.inl: %.gperf @opts="$< `$(SED) -ne /.*gperf/!d -e s///p -e q $< | \ $(SED) 's,$$(srcdir),$(srcdir),g'`"; \ echo $(GPERF) $$opts " > $@"; \ for i in a b c d e f g h j; do \ if test $$i = j; then \ eval $(GPERF) $$opts > $@ && break; \ else \ eval $(GPERF) $$opts > $@ 2>/dev/null && break; \ echo Retrying...; sleep 1; \ fi; \ done builtins.inl: builtins.gperf dist-hook: for i in $(STAMP_FILES); do \ echo timestamp > $(distdir)/$$i; \ done smalltalk-3.2.5/libgst/genbc-impl.h0000644000175000017500000000514412130455565014112 00000000000000/* A Bison parser, made by GNU Bison 2.5. */ /* Bison interface for Yacc-like parsers in C Copyright (C) 1984, 1989-1990, 2000-2011 Free Software Foundation, Inc. This program is free software: you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation, either version 3 of the License, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program. If not, see . */ /* As a special exception, you may create a larger work that contains part or all of the Bison parser skeleton and distribute that work under terms of your choice, so long as that work isn't itself a parser generator using the skeleton or a modified version thereof as a parser skeleton. Alternatively, if you modify or redistribute the parser skeleton itself, you may (at your option) remove this special exception, which will cause the skeleton and the resulting Bison output files to be licensed under the GNU General Public License without this special exception. This special exception was added by the Free Software Foundation in version 2.2 of Bison. */ /* Tokens. */ #ifndef YYTOKENTYPE # define YYTOKENTYPE /* Put the tokens into the symbol table, so that GDB and other debuggers know about them. */ enum yytokentype { MATCH_BYTECODES = 258, DECL_BEGIN = 259, DECL_END = 260, DECL_BREAK = 261, DECL_CONTINUE = 262, DECL_DISPATCH = 263, DECL_EXTRACT = 264, DECL_DOTS = 265, NUMBER = 266, ID = 267, EXPR = 268 }; #endif /* Tokens. */ #define MATCH_BYTECODES 258 #define DECL_BEGIN 259 #define DECL_END 260 #define DECL_BREAK 261 #define DECL_CONTINUE 262 #define DECL_DISPATCH 263 #define DECL_EXTRACT 264 #define DECL_DOTS 265 #define NUMBER 266 #define ID 267 #define EXPR 268 #if ! defined YYSTYPE && ! defined YYSTYPE_IS_DECLARED typedef union YYSTYPE { /* Line 2068 of yacc.c */ #line 69 "genbc-impl.y" struct field_info *field; const char *ctext; char *text; int num; /* Line 2068 of yacc.c */ #line 85 "genbc-impl.h" } YYSTYPE; # define YYSTYPE_IS_TRIVIAL 1 # define yystype YYSTYPE /* obsolescent; will be withdrawn */ # define YYSTYPE_IS_DECLARED 1 #endif extern YYSTYPE yylval; smalltalk-3.2.5/libgst/xlat.c0000644000175000017500000031567012123404352013036 00000000000000/******************************** -*- C -*- **************************** * * Translator to native code. * * ***********************************************************************/ /*********************************************************************** * * Copyright 2001, 2002, 2003, 2004, 2006, 2008 Free Software Foundation, Inc. * Written by Paolo Bonzini. * * This file is part of GNU Smalltalk. * * GNU Smalltalk is free software; you can redistribute it and/or modify it * under the terms of the GNU General Public License as published by the Free * Software Foundation; either version 2, or (at your option) any later * version. * * Linking GNU Smalltalk statically or dynamically with other modules is * making a combined work based on GNU Smalltalk. Thus, the terms and * conditions of the GNU General Public License cover the whole * combination. * * In addition, as a special exception, the Free Software Foundation * give you permission to combine GNU Smalltalk with free software * programs or libraries that are released under the GNU LGPL and with * independent programs running under the GNU Smalltalk virtual machine. * * You may copy and distribute such a system following the terms of the * GNU GPL for GNU Smalltalk and the licenses of the other code * concerned, provided that you include the source code of that other * code when and as the GNU GPL requires distribution of source code. * * Note that people who make modified versions of GNU Smalltalk are not * obligated to grant this special exception for their modified * versions; it is their choice whether to do so. The GNU General * Public License gives permission to release a modified version without * this exception; this exception also makes it possible to release a * modified version which carries forward this exception. * * GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or * FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for * more details. * * You should have received a copy of the GNU General Public License along with * GNU Smalltalk; see the file COPYING. If not, write to the Free Software * Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * ***********************************************************************/ #include "gstpriv.h" #include "match.h" #ifdef ENABLE_JIT_TRANSLATION #include "lightning.h" #include "jitpriv.h" #ifdef __GNUC__ #warning .--------------------------------------- #warning | do not worry if you get lots of #warning | 'value computed is not used' warnings #warning `--------------------------------------- #endif /* This file implements GNU Smalltalk's just-in-time compiler to native code. It is inspired by techniques shown in Ian Piumarta's PhD thesis "Delayed code generation in a Smalltalk-80 compiler" (available online at http://www-sor.inria.fr/~piumarta), with quite a few modifications: - we target a RISC architecture (GNU lightning) instead of the CISC Motorola 68020 architecture used in the thesis. - we use inline caching (only discussed briefly in the thesis) - block implementation is radically different - we don't work directly on a parse tree. Rather, we recreate a tree structure from bytecodes that constitute a statement. - a few parts that were left back in the thesis (doesNotUnderstand:, non local returns, primitives, etc.) are fully implemented The aim of the code in this file is to generate pretty good code, as fast as possible, and without requiring too much memory and information (Self's 64MB requirement comes to mind...). Nothing less, nothing more. All bottlenecks and inefficiencies should be due to the generic nature of GNU lightning's architecture and to interp.c, not to the compiler. */ /* These two small structures are used to store information on labels and forward references. */ typedef struct label_use { jit_insn *addr; /* addr of client insn */ struct label_use *next; /* next label use or 0 */ } label_use; typedef struct label { jit_insn *addr; /* defined address of label or 0 (forward) */ label_use *uses; /* list of uses while forward */ } label; /* This structure represents an n-tree. Children of a node are connected by a linked list. It is probably the most important for the operation of the translator. The translator operates on blocks of bytecodes that constitute a statement, and represents what the block does on a stack. The stack, however, does not contain results of the execution, but rather code_trees that store how the value in that stack slot was computed; these code_trees are built by dcd_* functions. When a statement boundary is found (i.e. a result on the stack is discarded, a jump is encountered, or a jump destination is reached), the code_trees that are currently on the stack are walked (calling recursively the gen_* functions depending on the contents of the 'operation' field), resulting in the generation of native code. */ typedef struct code_tree { struct code_tree *child, *next; int operation; PTR data; label *jumpDest; gst_uchar *bp; } code_tree, *code_stack_element, **code_stack_pointer; /* This structure represents a message send. A sequence of inline_cache objects is allocated on the heap and initialized as the code_tree is constructed. Inline caches have two roles: a) avoiding that data is stored in the methodsTableObstack, therefore making it easier to guess the size of the produced native code b) improving execution speed by lowering the number of global cache lookups to be done. A pointer to an inline_cache is used for the 'data' field in message send code_trees. */ typedef struct inline_cache { OOP selector; jit_insn *cachedIP; jit_insn *native_ip; char imm; /* For short sends, the selector number. */ char numArgs; char more; char is_super; } inline_cache; typedef struct ip_map { jit_insn *native_ip; int virtualIP; } ip_map; /* This structure forms a list that remembers which message sends were inlined directly into the instruction flow. The list is walked by emit_deferred_sends after the last bytecode has been compiled, and recovery code that performs real message sends is written. */ typedef struct deferred_send { code_tree *tree; label *trueDest; label *falseDest; label *address; int reg0, reg1; OOP oop; struct deferred_send *next; } deferred_send; /* To reduce multiplies and divides to shifts */ #define LONG_SHIFT (sizeof (long) == 4 ? 2 : 3) /* An arbitrary value */ #define MAX_BYTES_PER_BYTECODE (100 * sizeof(jit_insn)) /* These are for the hash table of translations */ #define HASH_TABLE_SIZE (8192) #define METHOD_HEADER_SIZE (sizeof(method_entry) - sizeof(jit_insn)) /* Here is where the dynamically compiled stuff goes */ static method_entry *methods_table[HASH_TABLE_SIZE+1], *released; #define discarded methods_table[HASH_TABLE_SIZE] /* Current status of the translator at the method level */ static method_entry *current; static struct obstack aux_data_obstack; static inline_cache *curr_inline_cache; static deferred_send *deferred_head; static label **labels, **this_label; static gst_uchar *bc; static OOP *literals; static OOP method_class; static code_stack_element t_stack[MAX_DEPTH]; static code_stack_pointer t_sp; /* Current status of the code generator */ static mst_Boolean self_cached, rec_var_cached; static int sp_delta, self_class_check, stack_cached; /* These are pieces of native code that are used by the run-time. */ static jit_insn *do_send_code, *do_super_code, *non_boolean_code, *bad_return_code, *does_not_understand_code; PTR (*_gst_run_native_code) (); PTR (*_gst_return_from_native_code) (); /* Kinds of functions used in function tables */ typedef void (*emit_func) (code_tree *); typedef mst_Boolean (*decode_func) (gst_uchar b, gst_uchar *bp); /* Constants used in the reconstruction of the parse tree (operation field) .---------------. .--------------.-----------.--------------. | bits 12-13 |.| bits 6-8 | bits 3-5 | bits 0-2 | |---------------|.|--------------|-----------|--------------| | class check |.| jump, pop & | operation | suboperation | | SmallInteger |.| return flags | | | '---------------' '--------------'-----------'--------------' \ \__ 3 unused bits */ /* operations ** value of tree->data */ #define TREE_OP 00070 #define TREE_SEND 00000 /* points to an inline_cache */ #define TREE_STORE 00010 /* see below */ #define TREE_PUSH 00020 /* see below */ #define TREE_ALT_PUSH 00030 /* see below */ #define TREE_SET_TOP 00040 /* see below */ #define TREE_NOP 00050 /* unused */ /* suboperations for TREE_SEND */ #define TREE_SUBOP 00007 #define TREE_NORMAL 00000 #define TREE_BINARY_INT 00001 #define TREE_BINARY_BOOL 00003 /* 2 skipped - reserved to LIT_CONST */ #define TREE_UNARY_SPECIAL 00004 #define TREE_UNARY_BOOL 00005 #define TREE_STORE_LIT_VAR 00006 /* receiver in V1 */ #define TREE_DIRTY_BLOCK 00007 /* doesn't use tree->data! */ /* stack suboperations value of tree->data */ #define TREE_REC_VAR 00000 /* variable number */ #define TREE_TEMP 00001 /* variable number */ #define TREE_LIT_CONST 00002 /* literal to be pushed */ #define TREE_LIT_VAR 00003 /* An gst_association object */ #define TREE_DUP 00004 /* unused */ #define TREE_SELF 00005 /* unused */ #define TREE_OUTER_TEMP 00006 /* unused */ #define TREE_POP_INTO_ARRAY 00007 /* index */ /* suboperations for TREE_NOP */ #define TREE_ALREADY_EMITTED 00000 #define TREE_TWO_EXTRAS 00001 /* extra operations */ #define TREE_EXTRA 00700 #define TREE_EXTRA_NONE 00000 #define TREE_EXTRA_JMP_TRUE 00100 #define TREE_EXTRA_JMP_FALSE 00200 #define TREE_EXTRA_JMP_ALWAYS 00300 #define TREE_EXTRA_RETURN 00400 #define TREE_EXTRA_METHOD_RET 00500 #define TREE_EXTRA_POP 00600 /* class check flags */ #define TREE_CLASS_CHECKS 0x03000L #define TREE_IS_INTEGER 0x01000L #define TREE_IS_NOT_INTEGER 0x02000L /* testing macros */ #define NOT_INTEGER(tree) ( (tree)->operation & TREE_IS_NOT_INTEGER) #define IS_INTEGER(tree) ( (tree)->operation & TREE_IS_INTEGER) #define IS_PUSH(tree) ( ((tree)->operation & TREE_OP) == TREE_PUSH) #define IS_SEND(tree) ( ((tree)->operation & TREE_OP) == TREE_SEND) #define IS_STORE(tree) ( ((tree)->operation & TREE_OP) == TREE_STORE) #define IS_SET_TOP(tree) ( ((tree)->operation & TREE_OP) == TREE_SET_TOP) #define IS_LITERAL(tree) ( ((tree)->operation & TREE_SUBOP) == TREE_LIT_CONST) /* Strength reduction */ static inline int analyze_factor (int x); static inline void analyze_dividend (int imm, int *shift, mst_Boolean *adjust, uintptr_t *factor); /* label handling */ static inline label *lbl_new (void); static inline jit_insn *lbl_get (label *lbl); static inline void lbl_use (label *lbl, jit_insn *result); static inline mst_Boolean lbl_define (label *lbl); static inline void define_ip_map_entry (int virtualIP); /* Inlining (deferred sends) */ static void defer_send (code_tree *tree, mst_Boolean isBool, jit_insn *address, int reg0, int reg1, OOP oop); static inline label *last_deferred_send (void); static inline void emit_deferred_sends (deferred_send *ds); static inline void finish_deferred_send (void); /* CompiledMethod hash table handling */ static method_entry *find_method_entry (OOP methodOOP, OOP receiverClass); static inline void new_method_entry (OOP methodOOP, OOP receiverClass, int size); static inline method_entry *finish_method_entry (void); /* code_tree handling */ static inline code_tree *push_tree_node (gst_uchar *bp, code_tree *firstChild, int operation, PTR data); static inline code_tree *push_tree_node_oop (gst_uchar *bp, code_tree *firstChild, int operation, OOP literal); static inline code_tree *pop_tree_node (code_tree *linkedChild); static inline code_tree *push_send_node (gst_uchar *bp, OOP selector, int numArgs, mst_Boolean super, int operation, int imm); static inline void set_top_node_extra (int extra, int jumpOffset); static inline gst_uchar *decode_bytecode (gst_uchar *bp); static inline void emit_code (void); static void emit_code_tree (code_tree *tree); /* Non-bytecode specific code generation functions */ static inline void emit_user_defined_method_call (OOP methodOOP, int numArgs, gst_compiled_method method); static inline mst_Boolean emit_method_prolog (OOP methodOOP, gst_compiled_method method); static inline mst_Boolean emit_block_prolog (OOP blockOOP, gst_compiled_block block); static inline mst_Boolean emit_inlined_primitive (int primitive, int numArgs, int attr); static inline mst_Boolean emit_primitive (int primitive, int numArgs); static inline void emit_interrupt_check (int restartReg); static inline void generate_run_time_code (void); static inline void translate_method (OOP methodOOP, OOP receiverClass, int size); static void emit_basic_size_in_r0 (OOP classOOP, mst_Boolean tagged, int objectReg); /* Code generation functions for bytecodes */ static void gen_send (code_tree *tree); static void gen_binary_int (code_tree *tree); static void gen_pop_into_array (code_tree *tree); static void gen_binary_bool (code_tree *tree); static void gen_send_store_lit_var (code_tree *tree); static void gen_dirty_block (code_tree *tree); static void gen_unary_special (code_tree *tree); static void gen_unary_bool (code_tree *tree); static void gen_store_rec_var (code_tree *tree); static void gen_store_temp (code_tree *tree); static void gen_store_lit_var (code_tree *tree); static void gen_store_outer (code_tree *tree); static void gen_push_rec_var (code_tree *tree); static void gen_push_temp (code_tree *tree); static void gen_push_lit_const (code_tree *tree); static void gen_push_lit_var (code_tree *tree); static void gen_dup_top (code_tree *tree); static void gen_push_self (code_tree *tree); static void gen_push_outer (code_tree *tree); static void gen_top_rec_var (code_tree *tree); static void gen_top_temp (code_tree *tree); static void gen_top_self (code_tree *tree); static void gen_top_outer (code_tree *tree); static void gen_alt_rec_var (code_tree *tree); static void gen_alt_temp (code_tree *tree); static void gen_alt_lit_const (code_tree *tree); static void gen_alt_lit_var (code_tree *tree); static void gen_get_top (code_tree *tree); static void gen_alt_self (code_tree *tree); static void gen_alt_outer (code_tree *tree); static void gen_top_lit_const (code_tree *tree); static void gen_top_lit_var (code_tree *tree); static void gen_nothing (code_tree *tree); static void gen_two_extras (code_tree *tree); static void gen_invalid (code_tree *tree); /* Function table for the code generator */ static const emit_func emit_operation_funcs[96] = { gen_send, gen_binary_int, gen_invalid, gen_binary_bool, gen_unary_special, gen_unary_bool, gen_send_store_lit_var, gen_dirty_block, gen_store_rec_var, gen_store_temp, gen_invalid, gen_store_lit_var, gen_invalid, gen_invalid, gen_store_outer, gen_pop_into_array, gen_push_rec_var, gen_push_temp, gen_push_lit_const, gen_push_lit_var, gen_dup_top, gen_push_self, gen_push_outer, gen_invalid, gen_alt_rec_var, gen_alt_temp, gen_alt_lit_const, gen_alt_lit_var, gen_get_top, gen_alt_self, gen_alt_outer, gen_invalid, gen_top_rec_var, gen_top_temp, gen_top_lit_const, gen_top_lit_var, gen_invalid, gen_top_self, gen_top_outer, gen_invalid, gen_nothing, gen_two_extras, gen_invalid, gen_invalid, gen_invalid, gen_invalid, gen_invalid, gen_invalid }; static const int special_send_bytecodes[32] = { TREE_SEND | TREE_BINARY_INT, /* PLUS_SPECIAL */ TREE_SEND | TREE_BINARY_INT, /* MINUS_SPECIAL */ TREE_SEND | TREE_BINARY_BOOL, /* LESS_THAN_SPECIAL */ TREE_SEND | TREE_BINARY_BOOL, /* GREATER_THAN_SPECIAL */ TREE_SEND | TREE_BINARY_BOOL, /* LESS_EQUAL_SPECIAL */ TREE_SEND | TREE_BINARY_BOOL, /* GREATER_EQUAL_SPECIAL */ TREE_SEND | TREE_BINARY_BOOL, /* EQUAL_SPECIAL */ TREE_SEND | TREE_BINARY_BOOL, /* NOT_EQUAL_SPECIAL */ TREE_SEND | TREE_BINARY_INT, /* TIMES_SPECIAL */ TREE_SEND | TREE_NORMAL, /* DIVIDE_SPECIAL */ TREE_SEND | TREE_NORMAL, /* REMAINDER_SPECIAL */ TREE_SEND | TREE_BINARY_INT, /* BIT_XOR_SPECIAL */ TREE_SEND | TREE_NORMAL, /* BIT_SHIFT_SPECIAL */ TREE_SEND | TREE_BINARY_INT, /* INTEGER_DIVIDE_SPECIAL */ TREE_SEND | TREE_BINARY_INT, /* BIT_AND_SPECIAL */ TREE_SEND | TREE_BINARY_INT, /* BIT_OR_SPECIAL */ TREE_SEND | TREE_NORMAL, /* AT_SPECIAL */ TREE_SEND | TREE_NORMAL, /* AT_PUT_SPECIAL */ TREE_SEND | TREE_NORMAL, /* SIZE_SPECIAL */ TREE_SEND | TREE_NORMAL, /* CLASS_SPECIAL */ TREE_SEND | TREE_UNARY_BOOL, /* IS_NIL_SPECIAL */ TREE_SEND | TREE_UNARY_BOOL, /* NOT_NIL_SPECIAL */ TREE_SEND | TREE_NORMAL, /* VALUE_SPECIAL */ TREE_SEND | TREE_NORMAL, /* VALUE_COLON_SPECIAL */ TREE_SEND | TREE_BINARY_BOOL, /* SAME_OBJECT_SPECIAL */ TREE_SEND | TREE_UNARY_SPECIAL, /* JAVA_AS_INT_SPECIAL */ TREE_SEND | TREE_UNARY_SPECIAL, /* JAVA_AS_LONG_SPECIAL */ }; /* Runtime support code */ static void generate_run_native_code (void) { static inline_cache ic; static int arg; jit_prolog (1); arg = jit_arg_p (); jit_getarg_p (JIT_R0, arg); jit_movi_p (JIT_V1, &ic); jit_ldi_p (JIT_V2, &sp); jit_jmpr (JIT_R0); jit_align (2); ic.native_ip = jit_get_label (); jit_ret (); } static void generate_dnu_code (void) { /* send #doesNotUnderstand: If the method is not understood, the stack is changed to the format needed by #doesNotUnderstand: in lookup_native_ip; no inline caching must take place because we have modify the stack each time they try to send the message. */ jit_ldi_p (JIT_V2, &sp); /* changed by lookup_method!! */ jit_movi_l (JIT_R2, 1); jit_ldi_p (JIT_R0, &_gst_does_not_understand_symbol); jit_ldxi_p (JIT_R1, JIT_V2, -sizeof (PTR)); jit_prepare (4); jit_pusharg_p (JIT_V0); /* method_class */ jit_pusharg_p (JIT_R1); /* receiver */ jit_pusharg_i (JIT_R2); /* numArgs */ jit_pusharg_p (JIT_R0); /* selector */ jit_finish (PTR_LOOKUP_NATIVE_IP); jit_retval (JIT_R0); /* Could crash if again #doesNotUnderstand: -- probably better than an infinite loop. */ jit_jmpr (JIT_R0); } static void generate_bad_return_code (void) { jit_insn *jmp; jit_ldi_p (JIT_V2, &sp); jit_movi_l (JIT_R2, 0); jit_ldi_p (JIT_R0, &_gst_bad_return_error_symbol); jit_ldr_p (JIT_R1, JIT_V2); /* load the class of the receiver (which is in R1) */ jit_movi_p (JIT_V0, _gst_small_integer_class); jmp = jit_bmsi_l (jit_forward (), JIT_R1, 1); jit_ldxi_p (JIT_V0, JIT_R1, jit_ptr_field (OOP, object)); jit_ldxi_p (JIT_V0, JIT_V0, jit_ptr_field (gst_object, objClass)); jit_patch (jmp); jit_prepare (4); jit_pusharg_p (JIT_V0); /* method_class */ jit_pusharg_p (JIT_R1); /* receiver */ jit_pusharg_i (JIT_R2); /* numArgs */ jit_pusharg_p (JIT_R0); /* selector */ jit_finish (PTR_LOOKUP_NATIVE_IP); jit_retval (JIT_R0); /* Might not be understood... how broken they are :-) */ jit_beqi_l (does_not_understand_code, JIT_R0, 0); jit_jmpr (JIT_R0); } static void generate_non_boolean_code (void) { static char methodName[] = "mustBeBoolean"; jit_ldi_p (JIT_V2, &sp); /* push R0 on the */ jit_stxi_p (sizeof (PTR), JIT_V2, JIT_R0); /* Smalltalk stack */ jit_addi_p (JIT_V2, JIT_V2, sizeof (PTR)); jit_movi_p (JIT_R1, methodName); jit_sti_p (&sp, JIT_V2); /* update SP */ jit_sti_p (&_gst_abort_execution, JIT_R1); jit_ret (); } static void generate_do_super_code (void) { /* load other args into R1/R2 */ jit_ldi_l (JIT_R1, &_gst_self); jit_ldxi_uc (JIT_R2, JIT_V1, jit_field (inline_cache, numArgs)); jit_ldxi_p (JIT_R0, JIT_V1, jit_field (inline_cache, selector)); jit_prepare (4); jit_pusharg_p (JIT_V0); /* method_class */ jit_pusharg_p (JIT_R1); /* receiver */ jit_pusharg_i (JIT_R2); /* numArgs */ jit_pusharg_p (JIT_R0); /* selector */ jit_finish (PTR_LOOKUP_NATIVE_IP); jit_retval (JIT_R0); /* store the address in the inline cache if not #doesNotUnderstand: */ jit_beqi_l (does_not_understand_code, JIT_R0, 0); jit_stxi_p (jit_field (inline_cache, cachedIP), JIT_V1, JIT_R0); jit_jmpr (JIT_R0); } static void generate_do_send_code (void) { jit_insn *jmp; /* load other parameters into R0/R2 */ jit_ldxi_uc (JIT_R2, JIT_V1, jit_field (inline_cache, numArgs)); jit_ldxi_p (JIT_R0, JIT_V1, jit_field (inline_cache, selector)); /* load _gst_self into R1 */ jit_lshi_l (JIT_R1, JIT_R2, LONG_SHIFT); jit_negr_l (JIT_R1, JIT_R1); jit_ldxr_l (JIT_R1, JIT_V2, JIT_R1); /* method class */ jit_movi_p (JIT_V0, _gst_small_integer_class); jmp = jit_bmsi_l (jit_forward (), JIT_R1, 1); jit_ldxi_p (JIT_V0, JIT_R1, jit_ptr_field (OOP, object)); jit_ldxi_p (JIT_V0, JIT_V0, jit_ptr_field (gst_object, objClass)); jit_patch (jmp); jit_prepare (4); jit_pusharg_p (JIT_V0); /* method_class */ jit_pusharg_p (JIT_R1); /* receiver */ jit_pusharg_i (JIT_R2); /* numArgs */ jit_pusharg_p (JIT_R0); /* selector */ jit_finish (PTR_LOOKUP_NATIVE_IP); jit_retval (JIT_R0); /* store the address in the inline cache if not #doesNotUnderstand: */ jit_beqi_l (does_not_understand_code, JIT_R0, 0); jit_stxi_p (jit_field (inline_cache, cachedIP), JIT_V1, JIT_R0); jit_jmpr (JIT_R0); } void generate_run_time_code (void) { PTR area = xmalloc (10000); _gst_run_native_code = jit_set_ip (area).pptr; generate_run_native_code (); jit_align (2); does_not_understand_code = jit_get_label (); jit_prolog (1); jit_set_ip (does_not_understand_code); generate_dnu_code (); /* send #badReturnError. No inline caching must take place because this is called upon a return, not upon a send. */ jit_align (2); bad_return_code = jit_get_label (); jit_prolog (1); jit_set_ip (bad_return_code); generate_bad_return_code (); jit_align (2); non_boolean_code = jit_get_label (); jit_prolog (1); jit_set_ip (non_boolean_code); generate_non_boolean_code (); jit_align (2); do_super_code = jit_get_label (); jit_prolog (1); jit_set_ip (do_super_code); generate_do_super_code (); jit_align (2); do_send_code = jit_get_label (); jit_prolog (1); jit_set_ip (do_send_code); generate_do_send_code (); jit_align (2); _gst_return_from_native_code = jit_get_ip ().pptr; jit_prolog (1); jit_set_ip ((void *) _gst_return_from_native_code); jit_movi_i (JIT_RET, 0); jit_ret (); } /* Functions for managing the translated methods' hash table */ void new_method_entry (OOP methodOOP, OOP receiverClass, int size) { if (!size) size = GET_METHOD_NUM_ARGS (methodOOP) * 2 + 10; current = (method_entry *) xmalloc (MAX_BYTES_PER_BYTECODE * (size + 2)); current->methodOOP = methodOOP; current->receiverClass = receiverClass; current->inlineCaches = NULL; methodOOP->flags |= F_XLAT; /* The buffer functions in str.c are used to deal with the ip_map. */ _gst_reset_buffer (); obstack_init (&aux_data_obstack); jit_set_ip (current->nativeCode); /* We need to compile a dummy prolog, which we'll overwrite, to make GNU lightning's status consistent with that when the trampolineCode was written. */ jit_prolog (1); jit_set_ip (current->nativeCode); } method_entry * finish_method_entry (void) { unsigned int hashEntry; char *codePtr; method_entry *result; int size; /* Shrink the method, and store it into the hash table */ codePtr = (char *) jit_get_label (); jit_flush_code (current->nativeCode, codePtr); result = (method_entry *) xrealloc (current, codePtr - (char *) current); current = NULL; /* Copy the IP map, adding a final dummy entry */ define_ip_map_entry (-1); size = _gst_buffer_size (); result->ipMap = (ip_map *) xmalloc (size); _gst_copy_buffer (result->ipMap); hashEntry = OOP_INDEX (result->methodOOP) % HASH_TABLE_SIZE; result->next = methods_table[hashEntry]; methods_table[hashEntry] = result; obstack_free (&aux_data_obstack, NULL); return result; } /* Functions for managing the code_tree */ code_tree * push_tree_node (gst_uchar *bp, code_tree *firstChild, int operation, PTR data) { code_tree *node = obstack_alloc (&aux_data_obstack, sizeof (code_tree)); node->child = firstChild; node->next = NULL; node->operation = operation; node->data = data; node->bp = bp; *t_sp++ = node; return (node); } code_tree * push_tree_node_oop (gst_uchar *bp, code_tree *firstChild, int operation, OOP literal) { int classCheck; if (IS_INT (literal)) classCheck = TREE_IS_INTEGER; else classCheck = TREE_IS_NOT_INTEGER; return push_tree_node (bp, firstChild, operation | classCheck, literal); } code_tree * pop_tree_node (code_tree *linkedChild) { if (t_sp <= t_stack) { /* Stack underflow (note that it can be legal in a few cases, such as for return stack top bytecodes) */ return (NULL); } else { code_tree *node = *--t_sp; node->next = linkedChild; return (node); } } void set_top_node_extra (int extra, int jumpOffset) { code_tree *node; #ifndef OPTIMIZE if (extra == TREE_EXTRA_JMP_ALWAYS || extra == TREE_EXTRA_JMP_TRUE || extra == TREE_EXTRA_JMP_FALSE) assert (this_label[jumpOffset] != NULL); #endif if (t_sp <= t_stack) { /* Stack is currently empty -- generate the code directly */ if (extra != TREE_EXTRA_JMP_ALWAYS) { OOP selector = GET_METHOD_SELECTOR (current->methodOOP); if (method_class == current->receiverClass) _gst_errorf ("Stack underflow in JIT compilation %O>>%O", current->receiverClass, selector); else _gst_errorf ("Stack underflow in JIT compilation %O(%O)>>%O", current->receiverClass, method_class, selector); abort (); } node = alloca (sizeof (code_tree)); node->child = node->next = NULL; node->operation = TREE_NOP | TREE_ALREADY_EMITTED | extra; node->jumpDest = this_label[jumpOffset]; emit_code_tree (node); return; } node = t_sp[-1]; if (node->operation & TREE_EXTRA) { /* More than one extra operation -- add a fake node */ node = obstack_alloc (&aux_data_obstack, sizeof (code_tree)); node->child = NULL; node->next = t_sp[-1]; node->operation = TREE_NOP | TREE_TWO_EXTRAS; t_sp[-1] = node; } node->operation |= extra; node->jumpDest = this_label[jumpOffset]; } static inline inline_cache * set_inline_cache (OOP selector, int numArgs, mst_Boolean super, int operation, int imm) { curr_inline_cache->numArgs = numArgs; curr_inline_cache->selector = selector; curr_inline_cache->cachedIP = super ? do_super_code : do_send_code; curr_inline_cache->is_super = super; curr_inline_cache->more = true; curr_inline_cache->imm = imm; return curr_inline_cache++; } code_tree * push_send_node (gst_uchar *bp, OOP selector, int numArgs, mst_Boolean super, int operation, int imm) { code_tree *args, *node; int tot_args; inline_cache *ic = set_inline_cache (selector, numArgs, super, operation, imm); /* Remember that we must pop an extra node for the receiver! */ tot_args = numArgs + (super ? 2 : 1); for (args = NULL; tot_args--;) args = pop_tree_node (args); node = push_tree_node (bp, args, operation, (PTR) ic); return (node); } void emit_code (void) { code_tree **pTree, *tree; for (pTree = t_stack; pTree < t_sp; pTree++) { tree = *pTree; emit_code_tree (tree); } rec_var_cached = false; stack_cached = -1; self_cached = false; } /* A couple of commodities for strength reduction */ int analyze_factor (int x) { int a; int b, c; a = x & (x - 1); /* clear lowest bit */ a &= a - 1; /* again */ if (a) /* more than two bits are set to 1 */ return 0; /* don't attempt strength reduction */ for (b = 0; (x & 1) == 0; b++, x >>= 1); if (x == 1) return b; /* a single bit was set */ for (c = b + 1; (x & 2) == 0; c++, x >>= 1); return b | (c << 8); } void analyze_dividend (int imm, int *shift, mst_Boolean *adjust, uintptr_t *factor) { int x, b, r; double f; *adjust = 0; /* compute floor(log2 imm) */ for (r = 0, x = imm >> 1; x; r++, x >>= 1); if (!(imm & (imm - 1))) { /* x is a power of two */ *shift = r; *factor = 0; return; } r += 31; f = ldexp (((double) 1.0) / imm, r); b = (int) floor (f); if ((f - (double) b) < 0.5) /* round f down to nearest integer, compute ((x + 1) * f) >> r */ ++*adjust; else /* round f up to nearest integer, compute (x * f) >> r */ ++b; /* Try to shift less bits */ while ((r >= 32) && ((b & 1) == 0)) { r--; b >>= 1; } *factor = b; *shift = r - 32; } /* Functions for managing labels and forward references */ label * lbl_new (void) { label *lbl = obstack_alloc (&aux_data_obstack, sizeof (label)); lbl->addr = NULL; lbl->uses = NULL; #ifdef DEBUG_LABELS printf ("Defined reference at %p\n", lbl); #endif return lbl; } jit_insn * lbl_get (label *lbl) { return lbl->addr ? lbl->addr : jit_forward (); } void lbl_use (label *lbl, jit_insn *result) { if (!lbl->addr) { /* forward reference */ label_use *use = obstack_alloc (&aux_data_obstack, sizeof (label_use)); #ifdef DEBUG_LABELS printf ("Forward reference at %p to %p (next = %p)\n", result, lbl, lbl->uses); #endif use->addr = result; use->next = lbl->uses; lbl->uses = use; } #ifdef DEBUG_LABELS else printf ("Backward reference at %p to %p (%p)\n", result, lbl->addr, lbl); #endif } mst_Boolean lbl_define (label *lbl) { label_use *use = lbl->uses; mst_Boolean used; jit_align (2); lbl->addr = jit_get_label (); used = (use != NULL); #ifdef DEBUG_LABELS printf ("Defined label at %p (%p)\n", lbl->addr, lbl); #endif while (use) { label_use *next = use->next; #ifdef DEBUG_LABELS printf ("Resolving forward reference at %p\n", use->addr); #endif jit_patch (use->addr); use = next; } return (used); } void define_ip_map_entry (int virtualIP) { ip_map mapEntry; mapEntry.virtualIP = virtualIP; mapEntry.native_ip = jit_get_label (); _gst_add_buf_data (&mapEntry, sizeof (mapEntry)); } void finish_deferred_send (void) { if (!deferred_head->trueDest) { deferred_head->trueDest = lbl_new (); lbl_define (deferred_head->trueDest); if (!deferred_head->falseDest) deferred_head->falseDest = deferred_head->trueDest; } else if (!deferred_head->falseDest) { deferred_head->falseDest = lbl_new (); lbl_define (deferred_head->falseDest); } } label * last_deferred_send (void) { return deferred_head->address; } void defer_send (code_tree *tree, mst_Boolean isBool, jit_insn *address, int reg0, int reg1, OOP oop) { deferred_send *ds = obstack_alloc (&aux_data_obstack, sizeof (deferred_send)); if (isBool) { switch (tree->operation & TREE_EXTRA) { case TREE_EXTRA_NONE: case TREE_EXTRA_POP: case TREE_EXTRA_RETURN: case TREE_EXTRA_METHOD_RET: case TREE_EXTRA_JMP_ALWAYS: isBool = false; } } ds->next = deferred_head; ds->tree = tree; ds->reg0 = reg0; ds->reg1 = reg1; ds->oop = oop; ds->address = lbl_new (); if (address) lbl_use (ds->address, address); if (isBool) { if ((tree->operation & TREE_EXTRA) == TREE_EXTRA_JMP_TRUE) { ds->trueDest = tree->jumpDest; ds->falseDest = NULL; } else { ds->falseDest = tree->jumpDest; ds->trueDest = NULL; } } else ds->trueDest = ds->falseDest = NULL; deferred_head = ds; } /* Register usage: * R0 scratch * R1 cached address of 1st instance variable * R2 scratch * V0 stack top * V1 cache address of 1st temporary or an outer context * (also) pointer to the inline_cache upon a send * V2 stack pointer */ /* Common pieces of code for generating stack operations */ /* Save the old stack top if it was cached in V0 */ #define BEFORE_PUSH(reg) do { \ sp_delta += sizeof (PTR); \ if (sp_delta > 0) { \ jit_stxi_p(sp_delta, JIT_V2, (reg)); \ } \ } while(0) /* Generate code to evaluate the value to be replaced. Generate * a `pop' by decrementing V2 unless the stack top is cached in V0 -- in * this case we can simply overwrite it. */ #define BEFORE_SET_TOP do { \ if (tree->child) { \ emit_code_tree(tree->child); \ } \ if (sp_delta < 0) { \ jit_subi_p(JIT_V2, JIT_V2, sizeof (PTR)); /* pop stack top */ \ sp_delta += sizeof (PTR); \ } \ } while(0) /* Generate code to evaluate the value to be stored, and have it loaded * in V0. */ #define BEFORE_STORE do { \ emit_code_tree(tree->child); \ if (sp_delta < 0) { \ jit_ldr_p(JIT_V0, JIT_V2); \ jit_subi_p(JIT_V2, JIT_V2, sizeof (PTR)); /* pop stack top */ \ sp_delta += sizeof (PTR); \ } \ } while(0) /* Common pieces of code for generating & caching addresses */ #define TEMP_OFS(tree) (sizeof (PTR) * (((intptr_t) ((tree)->data)) & 255)) #define REC_VAR_OFS(tree) jit_ptr_field(gst_object, data[(intptr_t) ((tree)->data)]) #define STACK_OFS(tree) (jit_ptr_field(gst_block_context, contextStack) + \ TEMP_OFS (tree)) /* Cache the address of the first instance variable in R1 */ #define CACHE_REC_VAR do { \ if (!rec_var_cached) { /* in R1 */ \ if (!self_cached) { /* in V0 */ \ jit_ldi_p(JIT_R1, &_gst_self); \ jit_ldxi_p(JIT_R1, JIT_R1, jit_ptr_field(OOP, object)); \ } else { \ jit_ldxi_p(JIT_R1, JIT_V0, jit_ptr_field(OOP, object)); \ } \ rec_var_cached = true; \ } \ } while(0) /* Cache the address of the first temporary variable in V1 */ #define CACHE_TEMP do { \ if (stack_cached != 0) { /* in V1 */ \ jit_ldi_p(JIT_V1, &_gst_temporaries); \ stack_cached = 0; \ } \ } while(0) #define CACHE_NOTHING do { \ rec_var_cached = false; \ stack_cached = -1; \ self_cached = false; \ } while(0) /* Cache into V1 the address of the outer context specified by the code_tree. If the address of another outer context (whose depth is lower) is currently cached, avoid walking the list of outer contexts from the start. This optimizes bytecode sequences such as push outer variable, n = 1, index = 2 store outer variable, n = 2, index = 0 Remember that stack_cached = 0 means `cache the address of the first temporary' (the address of the Context's first *indexed* instance variable), while stack_cached > 0 means `cache the address of the n-th outer context' (i.e. the address of the Context's first *fixed* instance variable). Although confusing, this was done because the VM provides the address of the first indexed instance variable for thisContext into the `_gst_temporaries' variable. */ #define CACHE_OUTER_CONTEXT do { \ int scopes; \ scopes = ((int) tree->data) >> 8; \ if (stack_cached <= 0 || stack_cached > scopes) { \ jit_ldi_p(JIT_V1, &_gst_this_context_oop); \ jit_ldxi_p(JIT_V1, JIT_V1, jit_ptr_field(OOP, object)); \ stack_cached = scopes; \ } else { \ scopes -= stack_cached; \ stack_cached += scopes; \ } \ while (scopes--) { \ jit_ldxi_p(JIT_V1, JIT_V1, jit_ptr_field(gst_block_context, outerContext)); \ jit_ldxi_p(JIT_V1, JIT_V1, jit_ptr_field(OOP, object)); \ } \ } while(0) /* Miscellaneous pieces of code */ /* Push the children on the stack -- needed for sends */ #define PUSH_CHILDREN do { \ code_tree *child; \ \ /* Emit code to generate the receiver and the arguments */ \ for(child = tree->child; child; child = child->next) { \ emit_code_tree(child); \ } \ } while(0) /* Remember that the stack top is cached in V0, and import V2 (the * stack pointer) from the sp variable. */ #define KEEP_V0_IMPORT_SP do { \ jit_ldi_p(JIT_V2, &sp); \ sp_delta = 0; \ } while(0) /* Remember that the stack top is *not* cached in V0, and import V2 (the * stack pointer) from the sp variable. */ #define IMPORT_SP do { \ jit_ldi_p(JIT_V2, &sp); \ sp_delta = -sizeof (PTR); \ } while(0) /* Export V2 (the stack pointer) into the sp variable; the top of the * stack is assured to be in *sp, not in V0. */ #define EXPORT_SP(reg) do { \ if (sp_delta >= 0) { \ sp_delta += sizeof (PTR); \ jit_stxi_p(sp_delta, JIT_V2, (reg)); \ jit_addi_p(JIT_V2, JIT_V2, sp_delta); \ jit_sti_p(&sp, JIT_V2); \ sp_delta = -sizeof (PTR); \ } \ } while(0) /* Export V2 (the stack pointer) into the sp variable; the top of the * stack is assured to be in *sp AND in V0. */ #define CACHE_STACK_TOP do { \ if (sp_delta < 0) { \ jit_ldr_p(JIT_V0, JIT_V2); \ } else { \ EXPORT_SP (JIT_V0); \ } \ } while(0) /* Export V2 (the stack pointer) into the sp variable, without pushing * the value cached in V0. */ #define KEEP_V0_EXPORT_SP do { \ if (sp_delta < 0) { \ jit_ldr_p(JIT_V0, JIT_V2); \ } \ if (sp_delta != 0) { \ jit_addi_p(JIT_V2, JIT_V2, sp_delta); \ } \ jit_sti_p(&sp, JIT_V2); \ sp_delta = -sizeof (PTR); \ } while(0) /* Export V2 (the stack pointer) into the sp variable, without * saving the old stack top if it was cached in V0. */ #define POP_EXPORT_SP do { \ if (sp_delta) { \ jit_addi_p(JIT_V2, JIT_V2, sp_delta); \ } \ jit_sti_p(&sp, JIT_V2); \ jit_ldr_p(JIT_V0, JIT_V2); \ sp_delta = -sizeof (PTR); \ } while(0) /* Do a conditional jump to tree->jumpDest if the top of the stack * is successOOP, or to non_boolean_code if it is anything but failOOP. */ #define CONDITIONAL_JUMP(successOOP, failOOP) do { \ jit_insn *addr; \ \ /* Save the value of the top of the stack */ \ if (sp_delta < 0) { \ jit_ldr_p(JIT_R0, JIT_V2); \ } else { \ jit_movr_p(JIT_R0, JIT_V0); \ } \ POP_EXPORT_SP; \ \ addr = lbl_get(tree->jumpDest); \ addr = jit_beqi_p(addr, JIT_R0, successOOP); \ lbl_use(tree->jumpDest, addr); \ jit_bnei_p(non_boolean_code, JIT_R0, failOOP); \ \ CACHE_NOTHING; \ } while(0) /* Pieces of code for inlining */ /* Don't inline if doing a send to super */ #define DONT_INLINE_SUPER do { \ if(ic->is_super) { \ gen_send(tree); \ return; \ } \ } while(0) /* Don't attempt to inline an arithmetic operation if one of its * argument is known not to be a SmallInteger. */ #define DONT_INLINE_NONINTEGER do { \ if (NOT_INTEGER(tree->child) || NOT_INTEGER(tree->child->next)) { \ gen_send(tree); \ return; \ } \ } while(0) /* Create a `true' or `false' oop if the value is required `as is'; else * compile a `jump if true' or `jump if false' native opcode. This is * the equivalent of the `jump lookahead' option in the bytecode interpreter. */ #define INLINED_CONDITIONAL do { \ jit_insn *addr; \ \ switch (tree->operation & TREE_EXTRA) { \ case TREE_EXTRA_NONE: \ case TREE_EXTRA_POP: \ case TREE_EXTRA_RETURN: \ case TREE_EXTRA_METHOD_RET: \ case TREE_EXTRA_JMP_ALWAYS: \ FALSE_SET(JIT_R0); \ jit_lshi_i(JIT_R0, JIT_R0, LONG_SHIFT+1); \ jit_addi_p(JIT_V0, JIT_R0, _gst_true_oop); \ break; \ \ case TREE_EXTRA_JMP_TRUE: \ case TREE_EXTRA_JMP_FALSE: \ if (sp_delta) { \ jit_addi_p(JIT_V2, JIT_V2, sp_delta); \ } \ sp_delta = -sizeof (PTR); \ addr = lbl_get(tree->jumpDest); \ if ((tree->operation & TREE_EXTRA) == TREE_EXTRA_JMP_TRUE) { \ TRUE_BRANCH(addr); \ } else { \ FALSE_BRANCH(addr); \ } \ lbl_use(tree->jumpDest, addr); \ \ /* Change the code_tree's operation to TREE_ALREADY_EMITTED */ \ tree->operation &= TREE_CLASS_CHECKS; \ tree->operation |= TREE_NOP | TREE_ALREADY_EMITTED; \ break; \ } \ } while(0) /* Generate code for the only argument, and get the argument in V0. * Think twice about it, it is the same as the code needed to compile * a store! */ #define GET_UNARY_ARG BEFORE_STORE /* Load the two arguments of an inlined binary message, optimizing the * common case when the second one is a literal (a == 5, a + 2). * reg0 and reg1 will contain the registers in which the arguments have * been loaded. */ #define GET_BINARY_ARGS do { \ code_tree *second = tree->child->next; \ \ emit_code_tree(tree->child); \ oop = NULL; \ reg0 = JIT_V0; \ reg1 = JIT_V1; \ if (IS_LITERAL(second)) { \ if (sp_delta < 0) { \ jit_ldr_p(JIT_V0, JIT_V2); \ } \ reg1 = JIT_NOREG; \ oop = (OOP) second->data; \ } else if (IS_PUSH(second)) { \ if (sp_delta < 0) { \ jit_ldr_p(JIT_V0, JIT_V2); \ jit_addi_p(JIT_V2, JIT_V2, sp_delta); \ sp_delta = 0; \ } \ /* Load the second operand into V1 */ \ second->operation ^= TREE_PUSH ^ TREE_ALT_PUSH; \ emit_code_tree(second); \ } else { \ emit_code_tree(second); \ if (sp_delta < 0) { \ /* We load the 2nd argument and then the 1st */ \ jit_ldr_p(JIT_V1, JIT_V2); \ jit_ldxi_p(JIT_V0, JIT_V2, -sizeof (PTR)); \ } else { \ /* We load the 1st argument; the 2nd is already in V0 */ \ jit_ldxi_p(JIT_V1, JIT_V2, sp_delta); \ reg0 = JIT_V1; \ reg1 = JIT_V0; \ } \ /* "Pop" the 2nd argument */ \ sp_delta -= sizeof (PTR); \ } \ \ if (sp_delta) { \ jit_addi_p(JIT_V2, JIT_V2, sp_delta); \ sp_delta = 0; \ } \ CACHE_NOTHING; \ } while(0) /* jump out of the instruction flow (to a send whose compilation is * deferred to after we compiled the method bytecodes) if one or both * arguments are not SmallIntegers. */ #define ENSURE_INT_ARGS(isBool, overflow) do { \ jit_insn *classCheck; \ \ if (IS_INTEGER(tree->child) && IS_INTEGER(tree->child->next)) { \ if (isBool || IS_INTEGER(tree)) { \ /* No need to do class checks & deferred sends */ \ overflow = NULL; \ break; \ } \ classCheck = NULL; \ } else if (IS_INTEGER(tree->child)) { \ classCheck = jit_bmci_ul(jit_forward(), reg1, 1); \ } else if (IS_INTEGER(tree->child->next)) { \ classCheck = jit_bmci_ul(jit_forward(), reg0, 1); \ } else { \ jit_andr_ul(JIT_R2, JIT_V0, JIT_V1); \ classCheck = jit_bmci_ul(jit_forward(), JIT_R2, 1); \ } \ \ defer_send(tree, isBool, classCheck, reg0, reg1, oop); \ overflow = last_deferred_send(); \ } while(0) /* These are used to simplify the inlining code, as they group the * `second operand is a literal' and `second operand is a register' * cases in a single statement. */ #define EXPAND_(what) what #define IMM_OR_REG(opcode, a) \ ((reg1 != JIT_NOREG) \ ? EXPAND_(jit_##opcode##r_l(a, reg0, reg1)) \ : EXPAND_(jit_##opcode##i_l(a, reg0, (intptr_t) oop))) /* gst_message sends */ void gen_send (code_tree *tree) { inline_cache *ic = (inline_cache *) tree->data; PUSH_CHILDREN; jit_movi_p (JIT_V1, ic); if (ic->is_super) KEEP_V0_EXPORT_SP; else EXPORT_SP (JIT_V0); jit_movi_ul (JIT_R0, tree->bp - bc + BYTECODE_SIZE); jit_ldxi_p (JIT_R1, JIT_V1, jit_field (inline_cache, cachedIP)); jit_sti_ul (&ip, JIT_R0); jit_jmpr (JIT_R1); jit_align (2); ic->native_ip = jit_get_label (); define_ip_map_entry (tree->bp - bc + BYTECODE_SIZE); IMPORT_SP; CACHE_NOTHING; } void gen_binary_int (code_tree *tree) { inline_cache *ic = (inline_cache *) tree->data; label *overflow; int reg0, reg1; OOP oop; intptr_t imm; jit_insn *addr; DONT_INLINE_SUPER; DONT_INLINE_NONINTEGER; GET_BINARY_ARGS; ENSURE_INT_ARGS (false, overflow); imm = (intptr_t) oop; /* Now generate the code for the inlined operation. Don't touch reg0/reg1 until we are sure that no overflow happens! */ switch (ic->imm) { case PLUS_SPECIAL: if (reg1 == JIT_NOREG) { imm--; /* strip tag bit */ if (imm == 0) { if (reg0 != JIT_V0) { jit_movr_l (JIT_V0, reg0); } break; } if (overflow) { jit_movr_l (JIT_R0, reg0); addr = lbl_get (overflow); addr = jit_boaddi_l (addr, JIT_R0, imm); lbl_use (overflow, addr); jit_movr_l (JIT_V0, JIT_R0); } else jit_addi_l (JIT_V0, reg0, imm); } else { jit_subi_l (JIT_R0, reg0, 1); /* remove the tag bit */ if (overflow) { addr = lbl_get (overflow); addr = jit_boaddr_l (addr, JIT_R0, reg1); lbl_use (overflow, addr); jit_movr_l (JIT_V0, JIT_R0); } else jit_addr_l (JIT_V0, reg0, reg1); } break; case MINUS_SPECIAL: if (reg1 == JIT_NOREG) { imm--; /* strip tag bit */ if (imm == 0) { if (reg0 != JIT_V0) { jit_movr_l (JIT_V0, reg0); } break; } if (overflow) { jit_movr_l (JIT_R0, reg0); addr = lbl_get (overflow); addr = jit_bosubi_l (addr, JIT_R0, imm); lbl_use (overflow, addr); jit_movr_l (JIT_V0, JIT_R0); } else jit_subi_l (JIT_V0, reg0, imm); } else { if (overflow) { jit_movr_l (JIT_R0, reg0); addr = lbl_get (overflow); addr = jit_bosubr_l (addr, JIT_R0, reg1); lbl_use (overflow, addr); jit_addi_l (JIT_V0, JIT_R0, 1); /* add back the tag bit */ } else { jit_subr_l (JIT_V0, reg0, reg1); jit_addi_l (JIT_V0, JIT_V0, 1); /* add back the tag bit */ } } break; case TIMES_SPECIAL: if (reg1 == JIT_NOREG) { jit_insn *addr1, *addr2; int reduce; imm >>= 1; if (imm == 0) { jit_movi_p (JIT_V0, FROM_INT (0)); break; } else if (imm == 1) { if (reg0 != JIT_V0) jit_movr_p (JIT_V0, reg0); break; } else if (imm == -1) { if (overflow) { addr = lbl_get (overflow); addr = jit_beqi_p (addr, reg0, FROM_INT (MIN_ST_INT)); lbl_use (overflow, addr); } jit_rsbi_l (JIT_V0, reg0, 2); break; } if (overflow) { addr = lbl_get (overflow); if (imm < 0) { addr1 = jit_blti_p (addr, reg0, FROM_INT (MIN_ST_INT / -imm)); addr2 = jit_bgti_p (addr, reg0, FROM_INT (MAX_ST_INT / -imm)); } else { addr1 = jit_blti_p (addr, reg0, FROM_INT (MIN_ST_INT / imm)); addr2 = jit_bgti_p (addr, reg0, FROM_INT (MAX_ST_INT / imm)); } lbl_use (overflow, addr1); lbl_use (overflow, addr2); } /* Do some strength reduction... */ reduce = analyze_factor (imm); if (reduce == 0) jit_muli_l (JIT_V0, reg0, imm); else if ((reduce & 0x00FF00) == 0) jit_lshi_l (JIT_V0, reg0, reduce); else if (reduce & 255) { jit_lshi_l (JIT_R0, reg0, reduce & 255); jit_lshi_l (JIT_V0, reg0, reduce >> 8); jit_addr_l (JIT_V0, JIT_V0, JIT_R0); } else { jit_lshi_l (JIT_R0, reg0, reduce >> 8); jit_addr_l (JIT_V0, reg0, JIT_R0); } /* remove the excess due to the tag bit: ((x-1) / 2 * imm) * 2 + 1 = x * imm - imm + 1 = (x*imm) - (imm-1) */ jit_subi_l (JIT_V0, reg0, imm - 1); } else { jit_rshi_l (JIT_R1, reg0, 1); jit_rshi_l (JIT_R0, reg1, 1); jit_mulr_l (JIT_R2, JIT_R0, JIT_R1); if (overflow) { jit_hmulr_l (JIT_R0, JIT_R0, JIT_R1); /* compute high bits */ /* check for sensible bits of the result in R0, and in bits 30-31 of R2 */ jit_rshi_i (JIT_R1, JIT_R0, sizeof (PTR) * 8 - 1); addr = lbl_get (overflow); addr = jit_bner_l (addr, JIT_R0, JIT_R1); lbl_use (overflow, addr); jit_xorr_i (JIT_R1, JIT_R0, JIT_R2); addr = lbl_get (overflow); addr = jit_bmsi_l (addr, JIT_R1, 3 << (sizeof (PTR) * 8 - 2)); lbl_use (overflow, addr); } jit_addr_l (JIT_V0, JIT_R2, JIT_R2); jit_ori_l (JIT_V0, JIT_V0, 1); } break; case INTEGER_DIVIDE_SPECIAL: if (reg1 == JIT_NOREG) { int shift; mst_Boolean adjust; uintptr_t factor; imm >>= 1; if (imm == 0) { addr = lbl_get (overflow); addr = jit_jmpi (addr); lbl_use (overflow, addr); break; } else if (imm == 1) { if (reg0 != JIT_V0) jit_movr_p (JIT_V0, reg0); break; } else if (imm == -1) { if (overflow) { addr = lbl_get (overflow); addr = jit_beqi_p (addr, reg0, FROM_INT (MIN_ST_INT)); lbl_use (overflow, addr); } jit_rsbi_l (JIT_V0, reg0, 2); break; } jit_rshi_l (reg0, reg0, 1); if (imm < 0) { jit_negr_l (reg0, reg0); imm = -imm; } /* Fix the sign of the result: reg0 = imm - _gst_self - 1 if reg0 < 0 All these instructions are no-ops if reg0 > 0, because R0=R1=0 */ jit_rshi_l (JIT_R0, reg0, 8 * sizeof (PTR) - 1); jit_andi_l (JIT_R1, JIT_R0, imm - 1); /* if reg0 < 0, reg0 is... */ jit_subr_l (reg0, reg0, JIT_R1); /* _gst_self - imm + 1 */ jit_xorr_l (reg0, reg0, JIT_R0); /* imm - _gst_self - 2 */ jit_subr_l (reg0, reg0, JIT_R0); /* imm - _gst_self - 1 */ /* Do some strength reduction... */ analyze_dividend (imm, &shift, &adjust, &factor); if (adjust) { /* If adjust is true, we have to sum 1 here, and the carry after the multiplication. */ jit_movi_l (JIT_R1, 0); jit_addci_l (reg0, reg0, 1); jit_addxi_l (JIT_R1, JIT_R1, 0); } shift--; /* for the tag bit */ if (factor) jit_hmuli_l (reg0, reg0, factor); if (shift < 0) jit_lshi_l (reg0, reg0, -shift); else if (shift > 0) jit_rshi_l (reg0, reg0, shift); if (adjust) jit_subr_l (reg0, reg0, JIT_R1); /* negate the result if the signs were different */ jit_xorr_l (reg0, reg0, JIT_R0); jit_subr_l (reg0, reg0, JIT_R0); /* now add the tag bit */ jit_ori_l (JIT_V0, reg0, 1); } else { if (overflow) { addr = lbl_get (overflow); addr = jit_beqi_p (addr, reg1, FROM_INT (0)); lbl_use (overflow, addr); } jit_rshi_l (reg1, reg1, 1); jit_rshi_l (reg0, reg0, 1); /* Make the divisor positive */ jit_rshi_l (JIT_R0, reg1, 8 * sizeof (PTR) - 1); jit_xorr_l (reg0, reg0, JIT_R0); jit_xorr_l (reg1, reg1, JIT_R0); jit_subr_l (reg0, reg0, JIT_R0); jit_subr_l (reg1, reg1, JIT_R0); /* Fix the result if signs differ: reg0 -= reg1-1 */ jit_rshi_l (JIT_R1, reg0, 8 * sizeof (PTR) - 1); jit_subi_l (JIT_R0, reg1, 1); jit_andr_l (JIT_R0, JIT_R0, JIT_R1); /* if reg0 < 0, reg0 is... */ jit_subr_l (reg0, reg0, JIT_R0); /* _gst_self - imm + 1 */ jit_xorr_l (reg0, reg0, JIT_R1); /* imm - _gst_self - 2 */ jit_subr_l (reg0, reg0, JIT_R1); /* imm - _gst_self - 1 */ /* divide, then negate the result if the signs were different */ jit_divr_l (JIT_R0, reg0, reg1); jit_xorr_l (JIT_R0, JIT_R0, JIT_R1); jit_subr_l (JIT_R0, JIT_R0, JIT_R1); /* add the tag bit */ jit_addr_l (JIT_V0, JIT_R0, JIT_R0); jit_ori_l (JIT_V0, JIT_V0, 1); } break; case REMAINDER_SPECIAL: case BIT_SHIFT_SPECIAL: /* not yet */ addr = lbl_get (overflow); addr = jit_jmpi (addr); lbl_use (overflow, addr); break; case BIT_AND_SPECIAL: IMM_OR_REG (and, JIT_V0); break; case BIT_OR_SPECIAL: IMM_OR_REG (or, JIT_V0); break; case BIT_XOR_SPECIAL: /* For XOR, the tag bits of the two operands cancel (unlike AND and OR), so we cannot simply use the IMM_OR_REG macro. */ if (reg1 != JIT_NOREG) { jit_xorr_l(JIT_V0, reg0, reg1); jit_addi_l(JIT_V0, JIT_V0, 1); /* Put back the tag bit. */ } else { imm--; /* Strip the tag bit. */ jit_xori_l(JIT_V0, reg0, imm); } break; } EXPORT_SP (JIT_V0); if (overflow) finish_deferred_send (); } void gen_binary_bool (code_tree *tree) { inline_cache *ic = (inline_cache *) tree->data; label *deferredSend; int reg0, reg1; OOP oop; DONT_INLINE_SUPER; if (ic->imm != SAME_OBJECT_SPECIAL) DONT_INLINE_NONINTEGER; GET_BINARY_ARGS; if (ic->imm != SAME_OBJECT_SPECIAL) ENSURE_INT_ARGS (true, deferredSend); else deferredSend = NULL; #define TRUE_BRANCH(addr) \ switch(ic->imm) { \ case LESS_THAN_SPECIAL: addr = IMM_OR_REG(blt, addr); break; \ case GREATER_THAN_SPECIAL: addr = IMM_OR_REG(bgt, addr); break; \ case LESS_EQUAL_SPECIAL: addr = IMM_OR_REG(ble, addr); break; \ case GREATER_EQUAL_SPECIAL: addr = IMM_OR_REG(bge, addr); break; \ case SAME_OBJECT_SPECIAL: \ case EQUAL_SPECIAL: addr = IMM_OR_REG(beq, addr); break; \ case NOT_EQUAL_SPECIAL: addr = IMM_OR_REG(bne, addr); break; \ } #define FALSE_BRANCH(addr) \ switch(ic->imm) { \ case LESS_THAN_SPECIAL: addr = IMM_OR_REG(bge, addr); break; \ case GREATER_THAN_SPECIAL: addr = IMM_OR_REG(ble, addr); break; \ case LESS_EQUAL_SPECIAL: addr = IMM_OR_REG(bgt, addr); break; \ case GREATER_EQUAL_SPECIAL: addr = IMM_OR_REG(blt, addr); break; \ case SAME_OBJECT_SPECIAL: \ case EQUAL_SPECIAL: addr = IMM_OR_REG(bne, addr); break; \ case NOT_EQUAL_SPECIAL: addr = IMM_OR_REG(beq, addr); break; \ } #define FALSE_SET(reg) \ switch(ic->imm) { \ case LESS_THAN_SPECIAL: IMM_OR_REG(ge, reg); break; \ case GREATER_THAN_SPECIAL: IMM_OR_REG(le, reg); break; \ case LESS_EQUAL_SPECIAL: IMM_OR_REG(gt, reg); break; \ case GREATER_EQUAL_SPECIAL: IMM_OR_REG(lt, reg); break; \ case SAME_OBJECT_SPECIAL: \ case EQUAL_SPECIAL: IMM_OR_REG(ne, reg); break; \ case NOT_EQUAL_SPECIAL: IMM_OR_REG(eq, reg); break; \ } INLINED_CONDITIONAL; #undef TRUE_BRANCH #undef FALSE_BRANCH #undef FALSE_SET EXPORT_SP (JIT_V0); if (deferredSend) finish_deferred_send (); } void gen_send_store_lit_var (code_tree *tree) { inline_cache *ic = (inline_cache *) tree->data; label *overflow; int reg0, reg1; OOP oop; intptr_t imm; jit_insn *addr; /* tree->child = value tree->child->next = var. */ BEFORE_STORE; emit_code_tree(tree->child->next); BEFORE_PUSH (JIT_V1); EXPORT_SP (JIT_V0); gen_send (tree); } void gen_dirty_block (code_tree *tree) { GET_UNARY_ARG; KEEP_V0_EXPORT_SP; jit_prepare (1); jit_pusharg_p (JIT_V0); jit_finish (_gst_make_block_closure); jit_retval (JIT_V0); KEEP_V0_IMPORT_SP; CACHE_NOTHING; } #if 0 void gen_fetch_class (code_tree *tree) { inline_cache *ic = (inline_cache *) tree->data; DONT_INLINE_SUPER; GET_UNARY_ARG; if (IS_INTEGER (tree->child)) jit_movi_p (JIT_V0, _gst_small_integer_class); else if (NOT_INTEGER (tree->child)) { jit_ldxi_p (JIT_V0, JIT_V0, jit_ptr_field (OOP, object)); jit_ldxi_p (JIT_V0, JIT_V0, jit_ptr_field (gst_object, objClass)); } else { jit_insn *jmp; jit_movi_p (JIT_R0, _gst_small_integer_class); jmp = jit_bmsi_ul (jit_forward (), JIT_V0, 1); jit_ldxi_p (JIT_R0, JIT_V0, jit_ptr_field (OOP, object)); jit_ldxi_p (JIT_R0, JIT_R0, jit_ptr_field (gst_object, objClass)); jit_patch (jmp); jit_movr_p (JIT_V0, JIT_R0); } self_cached = false; } #endif void gen_unary_special (code_tree *tree) { inline_cache *ic = (inline_cache *) tree->data; jit_insn *ok1 = NULL, *bad1, *ok2, *ok3; int sz; DONT_INLINE_SUPER; switch (ic->imm) { case JAVA_AS_INT_SPECIAL: case JAVA_AS_LONG_SPECIAL: emit_code_tree(tree->child); if (IS_INTEGER (tree->child)) break; /* In order to prepare for emitting the send, we have to export the top of the stack here. We won't emit anything in gen_send, though. */ CACHE_STACK_TOP; if (!NOT_INTEGER (tree->child)) ok1 = jit_bmsi_ul (jit_forward (), JIT_V0, 1); sz = (ic->imm == JAVA_AS_LONG_SPECIAL) ? 8 : 4; jit_ldr_p (JIT_R2, JIT_V0); /* Check if it belongs to the wrong class... */ jit_ldxi_p (JIT_R0, JIT_R2, jit_ptr_field (gst_object, objClass)); jit_subi_p (JIT_R0, JIT_R0, _gst_large_positive_integer_class); ok2 = jit_beqi_p (jit_forward (), JIT_R0, NULL); bad1 = jit_bnei_p (jit_forward (), JIT_R0, ((char *) _gst_large_negative_integer_class) - ((char *) _gst_large_positive_integer_class)); /* Look for too big an integer... */ jit_patch (ok2); if (SIZEOF_OOP > 4) { emit_basic_size_in_r0 (_gst_large_positive_integer_class, false, JIT_R2); ok3 = jit_blei_ui (jit_forward (), JIT_R0, sz); } else { /* We can check the size field directly. */ jit_ldxi_p (JIT_R0, JIT_R2, jit_ptr_field (gst_object, objSize)); ok3 = jit_blei_p (jit_forward (), JIT_R0, FROM_INT (OBJ_HEADER_SIZE_WORDS + sz / SIZEOF_OOP)); } jit_patch (bad1); gen_send (tree); jit_patch (ok3); if (ok1) jit_patch (ok1); self_cached = false; return; default: GET_UNARY_ARG; abort (); } } void gen_unary_bool (code_tree *tree) { inline_cache *ic = (inline_cache *) tree->data; mst_Boolean compileIsNil = ic->imm == IS_NIL_SPECIAL; DONT_INLINE_SUPER; GET_UNARY_ARG; #define TRUE_BRANCH(addr) addr = compileIsNil ? jit_beqi_p((addr), JIT_V0, _gst_nil_oop) \ : jit_bnei_p((addr), JIT_V0, _gst_nil_oop) #define FALSE_BRANCH(addr) addr = compileIsNil ? jit_bnei_p((addr), JIT_V0, _gst_nil_oop) \ : jit_beqi_p((addr), JIT_V0, _gst_nil_oop) #define FALSE_SET(reg) compileIsNil ? jit_nei_p ((reg), JIT_V0, _gst_nil_oop) \ : jit_eqi_p ((reg), JIT_V0, _gst_nil_oop) INLINED_CONDITIONAL; #undef TRUE_BRANCH #undef FALSE_BRANCH #undef FALSE_SET } void gen_pop_into_array (code_tree *tree) { mst_Boolean useCachedR0; code_tree *array, *value; int index; array = tree->child; value = array->next; index = (int) tree->data; useCachedR0 = (array->operation & (TREE_OP | TREE_SUBOP)) == (TREE_STORE | TREE_POP_INTO_ARRAY); /* This code is the same as GET_BINARY_ARGS, but it forces the first parameter in V0 and the second in V1. This is because the bytecode leaves the first parameter in the stack top */ emit_code_tree (array); if (IS_PUSH (value)) { if (sp_delta < 0) { jit_ldr_p (JIT_V0, JIT_V2); jit_addi_p (JIT_V2, JIT_V2, sp_delta); sp_delta = 0; } /* Load the value operand into V1 */ value->operation ^= TREE_PUSH ^ TREE_ALT_PUSH; emit_code_tree (value); } else { emit_code_tree (value); if (sp_delta < 0) { /* We load the 2nd argument and then the 1st */ jit_ldr_p (JIT_V1, JIT_V2); jit_ldxi_p (JIT_V0, JIT_V2, -sizeof (PTR)); } else { /* The 2nd argument is already in V0, move it in V1 */ jit_movr_p (JIT_V1, JIT_V0); jit_ldxi_p (JIT_V0, JIT_V2, sp_delta); } /* "Pop" the 2nd argument */ sp_delta -= sizeof (PTR); useCachedR0 = false; } if (sp_delta) { jit_addi_p (JIT_V2, JIT_V2, sp_delta); sp_delta = 0; } if (!useCachedR0) { /* Dereference the OOP into R0 */ jit_ldxi_p (JIT_R0, JIT_V0, jit_ptr_field (OOP, object)); } jit_stxi_p (jit_ptr_field (gst_object, data[index]), JIT_R0, JIT_V1); } /* Stores */ void gen_store_rec_var (code_tree *tree) { BEFORE_STORE; CACHE_REC_VAR; jit_stxi_p (REC_VAR_OFS (tree), JIT_R1, JIT_V0); } void gen_store_temp (code_tree *tree) { BEFORE_STORE; CACHE_TEMP; jit_stxi_p (TEMP_OFS (tree), JIT_V1, JIT_V0); } void gen_store_lit_var (code_tree *tree) { char *assocOOP = ((char *) tree->data) + jit_ptr_field (OOP, object); BEFORE_STORE; jit_ldi_p (JIT_R0, assocOOP); jit_stxi_p (jit_ptr_field (gst_association, value), JIT_R0, JIT_V0); } void gen_store_outer (code_tree *tree) { BEFORE_STORE; CACHE_OUTER_CONTEXT; jit_stxi_p (STACK_OFS (tree), JIT_V1, JIT_V0); } /* Pushes */ void gen_push_rec_var (code_tree *tree) { BEFORE_PUSH (JIT_V0); CACHE_REC_VAR; jit_ldxi_p (JIT_V0, JIT_R1, REC_VAR_OFS (tree)); self_cached = false; } void gen_push_temp (code_tree *tree) { BEFORE_PUSH (JIT_V0); CACHE_TEMP; jit_ldxi_p (JIT_V0, JIT_V1, TEMP_OFS (tree)); self_cached = false; } void gen_push_lit_const (code_tree *tree) { BEFORE_PUSH (JIT_V0); jit_movi_p (JIT_V0, tree->data); self_cached = false; } void gen_push_lit_var (code_tree *tree) { char *assocOOP = ((char *) tree->data) + jit_ptr_field (OOP, object); BEFORE_PUSH (JIT_V0); jit_ldi_p (JIT_V0, assocOOP); jit_ldxi_p (JIT_V0, JIT_V0, jit_ptr_field (gst_association, value)); self_cached = false; } void gen_dup_top (code_tree *tree) { if (sp_delta < 0) jit_ldr_p (JIT_V0, JIT_V2); BEFORE_PUSH (JIT_V0); } void gen_push_self (code_tree *tree) { BEFORE_PUSH (JIT_V0); if (!self_cached) jit_ldi_p (JIT_V0, &_gst_self); self_cached = true; } void gen_push_outer (code_tree *tree) { BEFORE_PUSH (JIT_V0); CACHE_OUTER_CONTEXT; jit_ldxi_p (JIT_V0, JIT_V1, STACK_OFS (tree)); self_cached = false; } /* Moves to V1 (alternative push) */ void gen_alt_rec_var (code_tree *tree) { CACHE_REC_VAR; jit_ldxi_p (JIT_V1, JIT_R1, REC_VAR_OFS (tree)); stack_cached = -1; } void gen_alt_temp (code_tree *tree) { CACHE_TEMP; jit_ldxi_p (JIT_V1, JIT_V1, TEMP_OFS (tree)); stack_cached = -1; } void gen_alt_lit_const (code_tree *tree) { jit_movi_p (JIT_V1, tree->data); stack_cached = -1; } void gen_alt_lit_var (code_tree *tree) { char *assocOOP = ((char *) tree->data) + jit_ptr_field (OOP, object); jit_ldi_p (JIT_V1, assocOOP); jit_ldxi_p (JIT_V1, JIT_V1, jit_ptr_field (gst_association, value)); stack_cached = -1; } void gen_get_top (code_tree *tree) { if (sp_delta < 0) jit_ldr_p (JIT_V1, JIT_V2); else jit_movr_p (JIT_V1, JIT_V0); stack_cached = -1; } void gen_alt_self (code_tree *tree) { if (!self_cached) jit_ldi_p (JIT_V1, &_gst_self); else jit_movr_p (JIT_V1, JIT_V0); stack_cached = -1; } void gen_alt_outer (code_tree *tree) { CACHE_OUTER_CONTEXT; jit_ldxi_p (JIT_V1, JIT_V1, STACK_OFS (tree)); stack_cached = -1; } /* Set top */ void gen_top_rec_var (code_tree *tree) { BEFORE_SET_TOP; CACHE_REC_VAR; jit_ldxi_p (JIT_V0, JIT_R1, REC_VAR_OFS (tree)); self_cached = false; } void gen_top_temp (code_tree *tree) { BEFORE_SET_TOP; CACHE_TEMP; jit_ldxi_p (JIT_V0, JIT_V1, TEMP_OFS (tree)); self_cached = false; } void gen_top_self (code_tree *tree) { BEFORE_SET_TOP; if (!self_cached) jit_ldi_p (JIT_V0, &_gst_self); self_cached = true; } void gen_top_outer (code_tree *tree) { int index; BEFORE_SET_TOP; CACHE_OUTER_CONTEXT; index = ((gst_uchar *) tree->data)[0]; jit_ldxi_p (JIT_V0, JIT_V1, STACK_OFS (tree)); self_cached = false; } void gen_top_lit_const (code_tree *tree) { BEFORE_SET_TOP; jit_movi_p (JIT_V0, tree->data); self_cached = false; } void gen_top_lit_var (code_tree *tree) { char *assocOOP = ((char *) tree->data) + jit_ptr_field (OOP, object); BEFORE_SET_TOP; jit_ldi_p (JIT_V0, assocOOP); jit_ldxi_p (JIT_V0, JIT_V0, jit_ptr_field (gst_association, value)); self_cached = false; } void gen_invalid (code_tree *tree) { printf ("Invalid operation %o in the code tree", tree->operation); abort (); } void gen_nothing (code_tree *tree) { } void gen_two_extras (code_tree *tree) { /* Emit code for the real node and the first extra; emit_code_tree will take care of the second extra held by TREE. */ emit_code_tree (tree->next); /* emit the code for the real node */ } void emit_code_tree (code_tree *tree) { int operation; operation = tree->operation & (TREE_OP | TREE_SUBOP); emit_operation_funcs[operation] (tree); /* Now emit the extras. */ switch (tree->operation & TREE_EXTRA) { case TREE_EXTRA_NONE: break; case TREE_EXTRA_POP: POP_EXPORT_SP; break; case TREE_EXTRA_RETURN: CACHE_STACK_TOP; jit_calli (PTR_UNWIND_CONTEXT); IMPORT_SP; jit_ldi_p (JIT_R0, &native_ip); jit_str_p (JIT_V2, JIT_V0); jit_jmpr (JIT_R0); break; case TREE_EXTRA_METHOD_RET: CACHE_STACK_TOP; jit_calli (PTR_UNWIND_METHOD); jit_retval (JIT_R0); jit_beqi_i (bad_return_code, JIT_R0, false); IMPORT_SP; jit_ldi_p (JIT_R0, &native_ip); jit_str_p (JIT_V2, JIT_V0); jit_jmpr (JIT_R0); break; case TREE_EXTRA_JMP_ALWAYS: { jit_insn *addr; CACHE_STACK_TOP; addr = lbl_get (tree->jumpDest); addr = jit_jmpi (addr); lbl_use (tree->jumpDest, addr); break; } case TREE_EXTRA_JMP_TRUE: CONDITIONAL_JUMP (_gst_true_oop, _gst_false_oop); break; case TREE_EXTRA_JMP_FALSE: CONDITIONAL_JUMP (_gst_false_oop, _gst_true_oop); break; } /* Change the code_tree's operation field to TREE_ALREADY_EMITTED, and null the extra op. field */ tree->operation &= TREE_CLASS_CHECKS; tree->operation |= TREE_NOP | TREE_ALREADY_EMITTED; } /* Initialization and other code generation (prologs, interrupt checks) */ void emit_deferred_sends (deferred_send *ds) { jit_insn *addr; code_tree *tree; inline_cache *ic; if (!ds) return; emit_deferred_sends (ds->next); tree = ds->tree; ic = (inline_cache *) tree->data; assert (!ic->is_super); lbl_define (ds->address); if (ds->reg1 == JIT_NOREG) { jit_movi_p (JIT_R0, ds->oop); ds->reg1 = JIT_R0; } jit_stxi_p (sizeof (PTR) * 1, JIT_V2, ds->reg0); jit_stxi_p (sizeof (PTR) * 2, JIT_V2, ds->reg1); jit_addi_p (JIT_V2, JIT_V2, sizeof (PTR) * 2); jit_movi_p (JIT_V1, ic); jit_sti_p (&sp, JIT_V2); jit_movi_ul (JIT_V0, tree->bp - bc); jit_ldxi_p (JIT_R1, JIT_V1, jit_field (inline_cache, cachedIP)); jit_sti_ul (&ip, JIT_V0); jit_jmpr (JIT_R1); jit_align (2); ic->native_ip = jit_get_label (); define_ip_map_entry (tree->bp - bc); IMPORT_SP; if (ds->trueDest == ds->falseDest) { /* This was an arithmetic deferred send. */ jit_ldr_p (JIT_V0, JIT_V2); addr = lbl_get (ds->trueDest); addr = jit_jmpi (addr); lbl_use (ds->trueDest, addr); } else { /* This was a boolean deferred send. */ jit_ldr_p (JIT_R0, JIT_V2); jit_subi_p (JIT_V2, JIT_V2, sizeof (PTR)); jit_ldr_p (JIT_V0, JIT_V2); addr = lbl_get (ds->trueDest); addr = jit_beqi_p (addr, JIT_R0, _gst_true_oop); lbl_use (ds->trueDest, addr); addr = lbl_get (ds->falseDest); addr = jit_beqi_p (addr, JIT_R0, _gst_false_oop); lbl_use (ds->falseDest, addr); jit_jmpi (non_boolean_code); } } void emit_interrupt_check (int restartReg) { jit_insn *jmp, *begin; jit_align (2); begin = jit_get_label (); jit_ldi_i (JIT_R2, &_gst_except_flag); jmp = jit_beqi_i (jit_forward (), JIT_R2, 0); if (restartReg == JIT_NOREG) jit_movi_p (JIT_RET, begin); else jit_movr_p (JIT_RET, restartReg); jit_ret (); jit_patch (jmp); } /* Auxiliary function for inlined primitives. Retrieves the receiver's * basicSize in R0, expects the pointer to the object data in objectReg. * Destroys V1. */ void emit_basic_size_in_r0 (OOP classOOP, mst_Boolean tagged, int objectReg) { int adjust; int shape = CLASS_INSTANCE_SPEC (classOOP) & ISP_INDEXEDVARS; if (!CLASS_IS_INDEXABLE (classOOP)) { jit_movi_p (JIT_R0, FROM_INT (0)); return; } /* Not yet implemented. */ if (shape != GST_ISP_POINTER && shape != GST_ISP_SCHAR && shape != GST_ISP_CHARACTER && shape != GST_ISP_UCHAR) abort (); adjust = CLASS_FIXED_FIELDS (classOOP) + sizeof (gst_object_header) / sizeof (PTR); if (objectReg == JIT_NOREG) { jit_ldxi_p (JIT_R2, JIT_V0, jit_ptr_field (OOP, object)); objectReg = JIT_R2; } jit_ldxi_l (JIT_R0, objectReg, jit_ptr_field (gst_object, objSize)); if (shape != GST_ISP_POINTER) jit_ldxi_p (JIT_V1, JIT_V0, jit_ptr_field (OOP, flags)); if (!tagged) /* Remove the tag bit */ jit_rshi_l (JIT_R0, JIT_R0, 1); else adjust = adjust * 2; if (shape != GST_ISP_POINTER) { jit_andi_l (JIT_V1, JIT_V1, EMPTY_BYTES); jit_lshi_l (JIT_R0, JIT_R0, LONG_SHIFT); jit_subr_l (JIT_R0, JIT_R0, JIT_V1); adjust *= sizeof (PTR); if (tagged) { jit_subr_l (JIT_R0, JIT_R0, JIT_V1); /* Move the tag bit back to bit 0 after the long shift above */ adjust += sizeof (PTR) - 1; } } if (adjust) jit_subi_l (JIT_R0, JIT_R0, adjust); } /* This takes care of emitting the code for inlined primitives. Returns a new set of attributes which applies to the inlined code. */ mst_Boolean emit_inlined_primitive (int primitive, int numArgs, int attr) { switch (primitive) { case 60: { jit_insn *fail1, *fail2; OOP charBase = CHAR_OOP_AT (0); int numFixed = CLASS_FIXED_FIELDS (current->receiverClass) + sizeof (gst_object_header) / sizeof (PTR); int shape = CLASS_INSTANCE_SPEC (current->receiverClass) & ISP_INDEXEDVARS; if (numArgs != 1) break; if (!shape) { /* return failure */ jit_movi_p (JIT_R0, -1); return PRIM_FAIL | PRIM_INLINED; } else if (shape != GST_ISP_POINTER && shape != GST_ISP_UCHAR && shape != GST_ISP_SCHAR && shape != GST_ISP_CHARACTER) /* too complicated to return LargeIntegers */ break; jit_ldi_p (JIT_R1, &sp); emit_basic_size_in_r0 (current->receiverClass, false, JIT_NOREG); /* Point R2 to the first indexed slot */ jit_addi_ui (JIT_R2, JIT_R2, numFixed * sizeof (PTR)); /* Load the index and test it: remove tag bit, then check if (unsigned) (V1 - 1) >= R0 */ jit_ldr_l (JIT_V1, JIT_R1); fail1 = jit_bmci_l (jit_get_label (), JIT_V1, 1); jit_rshi_ul (JIT_V1, JIT_V1, 1); jit_subi_ul (JIT_V1, JIT_V1, 1); fail2 = jit_bger_ul (jit_get_label (), JIT_V1, JIT_R0); /* adjust stack top */ jit_subi_l (JIT_R1, JIT_R1, sizeof (PTR)); /* Now R2 + V1 << SOMETHING contains the pointer to the slot (SOMETHING depends on the shape). */ switch (shape) { case GST_ISP_POINTER: jit_lshi_ul (JIT_V1, JIT_V1, LONG_SHIFT); jit_ldxr_p (JIT_R0, JIT_R2, JIT_V1); break; case GST_ISP_UCHAR: jit_ldxr_uc (JIT_R0, JIT_R2, JIT_V1); /* Tag the byte we read */ jit_addr_ul (JIT_R0, JIT_R0, JIT_R0); jit_addi_ul (JIT_R0, JIT_R0, 1); break; case GST_ISP_SCHAR: jit_ldxr_c (JIT_R0, JIT_R2, JIT_V1); /* Tag the byte we read */ jit_addr_ul (JIT_R0, JIT_R0, JIT_R0); jit_addi_ul (JIT_R0, JIT_R0, 1); break; case GST_ISP_CHARACTER: { jit_ldxr_uc (JIT_R0, JIT_R2, JIT_V1); /* Convert to a character */ jit_lshi_l (JIT_R0, JIT_R0, LONG_SHIFT + 1); jit_addi_p (JIT_R0, JIT_R0, charBase); } } /* Store the result and the new stack pointer */ jit_str_p (JIT_R1, JIT_R0); jit_sti_p (&sp, JIT_R1); jit_movi_l (JIT_R0, -1); jit_patch (fail1); jit_patch (fail2); /* We get here with the _gst_basic_size in R0 upon failure, with -1 upon success. We need to get 0 upon success and -1 upon failure. */ jit_rshi_l (JIT_R0, JIT_R0, 31); jit_notr_l (JIT_R0, JIT_R0); return PRIM_FAIL | PRIM_SUCCEED | PRIM_INLINED; } break; case 61: { jit_insn *fail0, *fail1, *fail2, *fail3, *fail4; OOP charBase = CHAR_OOP_AT (0); int numFixed = CLASS_FIXED_FIELDS (current->receiverClass) + sizeof (gst_object_header) / sizeof (PTR); int shape = CLASS_INSTANCE_SPEC (current->receiverClass) & ISP_INDEXEDVARS; if (numArgs != 2) break; if (!shape) { /* return failure */ jit_movi_p (JIT_R0, -1); return PRIM_FAIL | PRIM_INLINED; } if (shape != GST_ISP_UCHAR && shape != GST_ISP_POINTER) /* too complicated to convert LargeIntegers */ break; jit_ldxi_ul (JIT_V1, JIT_V0, jit_ptr_field (OOP, flags)); fail0 = jit_bmsi_ul (jit_get_label (), JIT_V1, F_READONLY); jit_ldi_p (JIT_R1, &sp); emit_basic_size_in_r0 (current->receiverClass, false, JIT_NOREG); /* Point R2 to the first indexed slot */ jit_addi_ui (JIT_R2, JIT_R2, numFixed * sizeof (PTR)); /* Load the index and test it: remove tag bit, then check if (unsigned) (V1 - 1) >= R0 */ jit_ldxi_l (JIT_V1, JIT_R1, -sizeof (PTR)); fail1 = jit_bmci_l (jit_get_label (), JIT_V1, 1); jit_rshi_ul (JIT_V1, JIT_V1, 1); jit_subi_ul (JIT_V1, JIT_V1, 1); fail2 = jit_bger_ul (jit_get_label (), JIT_V1, JIT_R0); if (shape == GST_ISP_POINTER) jit_lshi_ul (JIT_V1, JIT_V1, LONG_SHIFT); /* Compute the effective address to free V1 for the operand */ jit_addr_l (JIT_R2, JIT_R2, JIT_V1); jit_ldr_l (JIT_V1, JIT_R1); switch (shape) { case GST_ISP_UCHAR: /* Check and untag the byte we store */ fail3 = jit_bmci_l (jit_get_label (), JIT_V1, 1); jit_rshi_ul (JIT_R0, JIT_V1, 1); fail4 = jit_bmsi_ul (jit_get_label (), JIT_R0, ~255); jit_str_uc (JIT_R2, JIT_R0); break; case GST_ISP_CHARACTER: /* Check the character we store */ fail3 = jit_bmsi_l (jit_get_label (), JIT_V1, 1); jit_subi_p (JIT_R0, JIT_V1, charBase); jit_rshi_ul (JIT_R0, JIT_R0, LONG_SHIFT + 1); fail4 = jit_bmsi_ul (jit_get_label (), JIT_R0, ~255); jit_str_uc (JIT_R2, JIT_R0); break; case GST_ISP_POINTER: fail3 = fail4 = NULL; jit_str_p (JIT_R2, JIT_V1); } /* Store the result and the new stack pointer */ jit_subi_l (JIT_R1, JIT_R1, sizeof (PTR) * 2); jit_str_p (JIT_R1, JIT_V1); jit_sti_p (&sp, JIT_R1); jit_movi_l (JIT_R0, -1); jit_patch (fail0); jit_patch (fail1); jit_patch (fail2); if (fail3) { jit_patch (fail3); jit_patch (fail4); } /* We get here with the _gst_basic_size in R0 upon failure, with -1 upon success. We need to get 0 upon success and -1 upon failure. */ jit_rshi_l (JIT_R0, JIT_R0, 31); jit_notr_l (JIT_R0, JIT_R0); return PRIM_FAIL | PRIM_SUCCEED | PRIM_INLINED; } break; case 62: { int shape = CLASS_INSTANCE_SPEC (current->receiverClass) & ISP_INDEXEDVARS; if (numArgs != 0) break; if (shape != 0 && shape != GST_ISP_UCHAR && shape != GST_ISP_POINTER) /* too complicated to convert LargeIntegers */ break; jit_ldi_p (JIT_R1, &sp); emit_basic_size_in_r0 (current->receiverClass, true, JIT_NOREG); jit_str_p (JIT_R1, JIT_R0); return (PRIM_SUCCEED | PRIM_INLINED); } #if 0 case 70: { OOP class_oop; if (numArgs != 0) break; if (!is_a_kind_of (current->receiverClass, _gst_class_class)) break; class_oop = METACLASS_INSTANCE (current->receiverClass); if (CLASS_IS_INDEXABLE (class_oop)) { /* return failure */ jit_movi_p (JIT_R0, -1); return PRIM_FAIL | PRIM_INLINED; } /* SET_STACKTOP (alloc_oop (instantiate (_gst_self))) */ jit_prepare (1); jit_pusharg_p (JIT_V0); jit_finish (instantiate); jit_retval (JIT_R0); jit_prepare (1); jit_pusharg_p (JIT_R0); jit_finish (alloc_oop); jit_ldi_p (JIT_V1, &sp); jit_retval (JIT_R0); jit_str_p (JIT_V1, JIT_R0); return (PRIM_SUCCEED | PRIM_INLINED); } case 71: { OOP class_oop; jit_insn *fail1, *fail2; if (numArgs != 1) break; if (!is_a_kind_of (current->receiverClass, _gst_class_class)) break; class_oop = METACLASS_INSTANCE (current->receiverClass); if (!CLASS_IS_INDEXABLE (class_oop)) { /* return failure */ jit_movi_p (JIT_R0, -1); return PRIM_FAIL | PRIM_INLINED; } jit_ldi_p (JIT_V1, &sp); jit_ldr_p (JIT_R1, JIT_V1); /* load the argument */ jit_movi_i (JIT_R0, -1); /* failure */ fail2 = jit_bmci_l (jit_get_label (), JIT_R1, 1); fail1 = jit_blti_p (jit_get_label (), JIT_R1, FROM_INT (0)); jit_rshi_l (JIT_R1, JIT_R1, 1); /* clear tag bit */ jit_subi_l (JIT_V1, JIT_V1, sizeof (PTR)); /* set new stack top */ /* SET_STACKTOP (instantiate_oopwith (_gst_self, POP_OOP())) */ jit_prepare (2); jit_pusharg_p (JIT_R1); jit_pusharg_p (JIT_V0); jit_finish (instantiate_oopwith); jit_retval (JIT_R0); /* Store the result and the new stack pointer */ jit_str_p (JIT_V1, JIT_R0); jit_sti_p (&sp, JIT_V1); jit_movi_i (JIT_R0, 0); /* success */ jit_patch (fail2); jit_patch (fail1); return (PRIM_SUCCEED | PRIM_FAIL | PRIM_INLINED); } #endif case 110: if (numArgs != 1) break; jit_ldi_p (JIT_V1, &sp); jit_ldr_p (JIT_R1, JIT_V1); /* load the argument */ jit_ner_p (JIT_R0, JIT_R1, JIT_V0); jit_subi_l (JIT_V1, JIT_V1, sizeof (PTR)); /* set new stack top */ jit_lshi_i (JIT_V0, JIT_R0, LONG_SHIFT + 1); jit_movi_i (JIT_R0, 0); /* success */ jit_addi_p (JIT_V0, JIT_V0, _gst_true_oop); /* Store the result and the new stack pointer */ jit_str_p (JIT_V1, JIT_V0); jit_sti_p (&sp, JIT_V1); return (PRIM_SUCCEED | PRIM_INLINED); case 111: { jit_insn *jmp; if (numArgs != 0) break; jit_ldi_p (JIT_V1, &sp); jit_movi_p (JIT_R0, _gst_small_integer_class); jmp = jit_bmsi_ul (jit_forward (), JIT_V0, 1); jit_ldxi_p (JIT_R0, JIT_V0, jit_ptr_field (OOP, object)); jit_ldxi_p (JIT_R0, JIT_R0, jit_ptr_field (gst_object, objClass)); jit_patch (jmp); /* Store the result and the new stack pointer */ jit_movi_i (JIT_R0, 0); /* success */ jit_str_p (JIT_V1, JIT_V0); return (PRIM_SUCCEED | PRIM_INLINED); } } return (attr & ~PRIM_INLINED); } mst_Boolean emit_primitive (int primitive, int numArgs) { /* primitive */ jit_insn *fail, *succeed; prim_table_entry *pte = _gst_get_primitive_attributes (primitive); int attr = pte->attributes; if (attr & PRIM_INLINED) attr = emit_inlined_primitive (pte->id, numArgs, attr); if (!(attr & PRIM_INLINED)) { jit_prepare (2); jit_movi_p (JIT_R1, numArgs); jit_movi_p (JIT_R2, pte->id); jit_pusharg_i (JIT_R1); jit_pusharg_i (JIT_R2); jit_finish (pte->func); jit_retval (JIT_R0); } fail = ((attr & PRIM_FAIL) && (attr & (PRIM_SUCCEED | PRIM_RELOAD_IP))) ? jit_beqi_i (jit_forward (), JIT_R0, -1) : NULL; if (attr & PRIM_RELOAD_IP) { succeed = (attr & PRIM_SUCCEED) ? jit_beqi_i (jit_forward (), JIT_R0, 0) : NULL; /* BlockClosure>>#value saves the native code's IP in the inline cache */ if (attr & PRIM_CACHE_NEW_IP) jit_stxi_p (jit_field (inline_cache, cachedIP), JIT_V1, JIT_R0); jit_movr_p (JIT_V2, JIT_R0); if (succeed) jit_patch (succeed); } if (attr & (PRIM_SUCCEED | PRIM_RELOAD_IP)) { if (attr & PRIM_CHECK_INTERRUPT) emit_interrupt_check (JIT_V2); jit_jmpr (JIT_V2); } if (fail) jit_patch (fail); return !(attr & PRIM_FAIL); } void emit_context_setup (int numArgs, int numTemps) { if (numArgs > 3 || numTemps > 3) { /* Call through a loop written in C */ jit_movi_i (JIT_V1, numTemps); jit_prepare (3); jit_pusharg_p (JIT_V1); /* numTemps */ jit_pusharg_p (JIT_V2); /* numArgs */ jit_pusharg_p (JIT_R0); /* newContext */ jit_finish (PTR_PREPARE_CONTEXT); IMPORT_SP; return; } /* Generate unrolled code to set up the frame -- this is done for about 95% of the methods. */ if (numArgs || numTemps) { int ofs; IMPORT_SP; switch (numArgs) { case 3: jit_ldxi_p (JIT_V0, JIT_V2, -2 * sizeof (PTR)); case 2: jit_ldxi_p (JIT_R2, JIT_V2, -1 * sizeof (PTR)); case 1: jit_ldr_p (JIT_R1, JIT_V2); case 0: break; } if (numTemps) jit_movi_p (JIT_V1, _gst_nil_oop); jit_addi_p (JIT_V2, JIT_R0, jit_ptr_field (gst_method_context, contextStack)); jit_sti_p (&_gst_temporaries, JIT_V2); ofs = 0; switch (numArgs) { case 3: jit_stxi_p (ofs, JIT_V2, JIT_V0); ofs += sizeof (PTR); case 2: jit_stxi_p (ofs, JIT_V2, JIT_R2); ofs += sizeof (PTR); case 1: jit_stxi_p (ofs, JIT_V2, JIT_R1); ofs += sizeof (PTR); case 0: break; } switch (numTemps) { case 3: jit_stxi_p (ofs, JIT_V2, JIT_V1); ofs += sizeof (PTR); case 2: jit_stxi_p (ofs, JIT_V2, JIT_V1); ofs += sizeof (PTR); case 1: jit_stxi_p (ofs, JIT_V2, JIT_V1); ofs += sizeof (PTR); case 0: break; } jit_addi_p (JIT_V2, JIT_V2, ofs - sizeof (PTR)); } else { jit_addi_p (JIT_V2, JIT_R0, jit_ptr_field (gst_method_context, contextStack[-1])); } jit_sti_p (&sp, JIT_V2); } void emit_user_defined_method_call (OOP methodOOP, int numArgs, gst_compiled_method method) { int i; char *bp = method->bytecodes; static OOP arrayAssociation; current->inlineCaches = curr_inline_cache = (inline_cache *) xmalloc (2 * sizeof (inline_cache)); /* Emit code similar to valueWithReceiver: withArguments: { arg1. arg2. ... } */ if (!arrayAssociation) { arrayAssociation = dictionary_association_at (_gst_smalltalk_dictionary, _gst_intern_string ("Array")); } t_sp = t_stack; push_tree_node_oop (bp, NULL, TREE_PUSH | TREE_LIT_CONST, methodOOP); push_tree_node (bp, NULL, TREE_PUSH | TREE_SELF, NULL); /* TODO: use instantiate_oop_with instead. */ push_tree_node_oop (bp, NULL, TREE_PUSH | TREE_LIT_VAR, arrayAssociation); push_tree_node_oop (bp, NULL, TREE_PUSH | TREE_LIT_CONST, FROM_INT (numArgs)); push_send_node (bp, _gst_intern_string ("new:"), 1, false, TREE_SEND | TREE_NORMAL, NEW_COLON_SPECIAL); for (i = 0; i < numArgs; i++) { push_tree_node (bp, NULL, TREE_PUSH | TREE_TEMP, (PTR) (uintptr_t) i); push_tree_node (bp, pop_tree_node (pop_tree_node (NULL)), TREE_STORE | TREE_POP_INTO_ARRAY, (PTR) (uintptr_t) i); } push_send_node (bp, _gst_value_with_rec_with_args_symbol, 2, false, TREE_SEND | TREE_NORMAL, 0); set_top_node_extra (TREE_EXTRA_RETURN, 0); emit_code (); curr_inline_cache[-1].more = false; } mst_Boolean emit_method_prolog (OOP methodOOP, gst_compiled_method method) { method_header header; int flag, stack_depth; OOP receiverClass; header = method->header; flag = header.headerFlag; receiverClass = current->receiverClass; if (flag == MTH_USER_DEFINED) /* Include enough stack slots for the arguments, the first two parameters of #valueWithReceiver:withArguments:, the Array class, and the parameter to #new:. */ stack_depth = ((header.numArgs + 4) + (1 << DEPTH_SCALE) - 1) >> DEPTH_SCALE; else stack_depth = header.stack_depth; jit_ldxi_p (JIT_V0, JIT_V2, sizeof (PTR) * -header.numArgs); if (receiverClass == _gst_small_integer_class) jit_bmci_ul (do_send_code, JIT_V0, 1); else { jit_bmsi_ul (do_send_code, JIT_V0, 1); jit_ldxi_p (JIT_R2, JIT_V0, jit_ptr_field (OOP, object)); jit_ldxi_p (JIT_R1, JIT_R2, jit_ptr_field (gst_object, objClass)); jit_bnei_p (do_send_code, JIT_R1, receiverClass); } /* Mark the translation as used *before* a GC can be triggered. */ jit_ldi_ul (JIT_R0, &(methodOOP->flags)); jit_ori_ul (JIT_R0, JIT_R0, F_XLAT_REACHABLE); jit_sti_ul (&(methodOOP->flags), JIT_R0); switch (flag) { case MTH_RETURN_SELF: jit_ldxi_p (JIT_V1, JIT_V1, jit_field (inline_cache, native_ip)); jit_jmpr (JIT_V1); return (true); case MTH_RETURN_INSTVAR: { int ofs = jit_ptr_field (gst_object, data[header.primitiveIndex]); jit_ldxi_p (JIT_V1, JIT_V1, jit_field (inline_cache, native_ip)); jit_ldxi_p (JIT_R2, JIT_R2, ofs); /* Remember? R2 is _gst_self->object */ jit_str_p (JIT_V2, JIT_R2); /* Make it the stack top */ jit_jmpr (JIT_V1); return (true); } case MTH_RETURN_LITERAL: { OOP literal = OOP_TO_OBJ (method->literals)->data[header.primitiveIndex]; jit_ldxi_p (JIT_V1, JIT_V1, jit_field (inline_cache, native_ip)); jit_movi_p (JIT_R2, literal); jit_str_p (JIT_V2, JIT_R2); /* Make it the stack top */ jit_jmpr (JIT_V1); return (true); } default: break; } jit_ldxi_p (JIT_V2, JIT_V1, jit_field (inline_cache, native_ip)); if (flag == MTH_PRIMITIVE) if (emit_primitive (header.primitiveIndex, header.numArgs)) return (true); /* Save the return IP */ jit_ldi_p (JIT_R0, &_gst_this_context_oop); jit_ldxi_p (JIT_R0, JIT_R0, jit_ptr_field (OOP, object)); jit_addi_p (JIT_V2, JIT_V2, 1); jit_stxi_p (jit_ptr_field (gst_method_context, native_ip), JIT_R0, JIT_V2); /* Prepare new state */ jit_movi_i (JIT_R0, stack_depth); jit_movi_i (JIT_V2, header.numArgs); jit_prepare (2); jit_pusharg_p (JIT_V2); jit_pusharg_p (JIT_R0); jit_finish (PTR_ACTIVATE_NEW_CONTEXT); jit_retval (JIT_R0); /* Remember? V0 was loaded with _gst_self for the inline cache test */ jit_sti_p (&_gst_self, JIT_V0); /* Set the new context's flags, and _gst_this_method */ jit_movi_p (JIT_V0, current->methodOOP); jit_movi_l (JIT_V1, MCF_IS_METHOD_CONTEXT); jit_sti_p (&_gst_this_method, JIT_V0); jit_stxi_p (jit_ptr_field (gst_method_context, flags), JIT_R0, JIT_V1); /* Move the arguments and nil the temporaries */ emit_context_setup (header.numArgs, header.numTemps); define_ip_map_entry (0); emit_interrupt_check (JIT_NOREG); /* For simplicity, we emit user-defined methods by creating a code_tree for the acrual send of #valueWithReceiver:withArguments: that they do. This requires creating the context, so we translate it now; otherwise it is very similar to a non-failing primitive. */ if (flag == MTH_USER_DEFINED) { emit_user_defined_method_call (methodOOP, header.numArgs, method); return (true); } return (false); } mst_Boolean emit_block_prolog (OOP blockOOP, gst_compiled_block block) { block_header header; OOP receiverClass; jit_insn *x; header = block->header; receiverClass = current->receiverClass; /* Check if the number of arguments matches ours */ jit_ldxi_uc (JIT_R2, JIT_V1, jit_field (inline_cache, numArgs)); x = jit_beqi_ui (jit_forward (), JIT_R2, header.numArgs); /* If they don't, check if we came here because somebody called send_block_value. In this case, the number of arguments is surely valid and the inline cache's numArgs is bogus. This handles #valueWithArguments:, #primCompile:ifError: and other primitives in which send_block_value is used. */ jit_ldi_p (JIT_R2, &native_ip); jit_bnei_p (do_send_code, JIT_R2, current->nativeCode); jit_patch (x); /* Check if a block evaluation was indeed requested, and if the BlockClosure really points to this CompiledBlock */ jit_ldxi_p (JIT_R1, JIT_V2, sizeof (PTR) * -header.numArgs); jit_bmsi_ul (do_send_code, JIT_R1, 1); jit_ldxi_p (JIT_R1, JIT_R1, jit_ptr_field (OOP, object)); jit_ldxi_p (JIT_R0, JIT_R1, jit_ptr_field (gst_object, objClass)); jit_ldxi_p (JIT_R2, JIT_R1, jit_ptr_field (gst_block_closure, block)); jit_bnei_p (do_send_code, JIT_R0, _gst_block_closure_class); jit_bnei_p (do_send_code, JIT_R2, current->methodOOP); /* Now, the standard class check. Always load _gst_self, but don't check the receiver's class for clean blocks. */ jit_ldxi_p (JIT_V0, JIT_R1, jit_ptr_field (gst_block_closure, receiver)); if (block->header.clean != 0) { if (receiverClass == _gst_small_integer_class) { jit_bmci_ul (do_send_code, JIT_V0, 1); } else { jit_bmsi_ul (do_send_code, JIT_V0, 1); jit_ldxi_p (JIT_R0, JIT_V0, jit_ptr_field (OOP, object)); jit_ldxi_p (JIT_R0, JIT_R0, jit_ptr_field (gst_object, objClass)); jit_bnei_p (do_send_code, JIT_R0, receiverClass); } } /* Mark the translation as used *before* a GC can be triggered. */ jit_ldi_ul (JIT_R0, &(blockOOP->flags)); jit_ori_ul (JIT_R0, JIT_R0, F_XLAT_REACHABLE); jit_sti_ul (&(blockOOP->flags), JIT_R0); /* All tests passed. Now save the return IP */ jit_ldxi_p (JIT_V2, JIT_V1, jit_field (inline_cache, native_ip)); jit_ldi_p (JIT_R0, &_gst_this_context_oop); jit_ldxi_p (JIT_R0, JIT_R0, jit_ptr_field (OOP, object)); jit_addi_p (JIT_V2, JIT_V2, 1); jit_stxi_p (jit_ptr_field (gst_method_context, native_ip), JIT_R0, JIT_V2); /* Get the outer context in a callee-preserved register... */ jit_ldxi_p (JIT_V1, JIT_R1, jit_ptr_field (gst_block_closure, outerContext)); /* prepare new state */ jit_movi_i (JIT_R0, header.depth); jit_movi_i (JIT_V2, header.numArgs); jit_prepare (2); jit_pusharg_p (JIT_V2); jit_pusharg_p (JIT_R0); jit_finish (PTR_ACTIVATE_NEW_CONTEXT); jit_retval (JIT_R0); /* Remember? V0 was loaded with _gst_self for the inline cache test. Also initialize _gst_this_method and the pointer to the outerContext. */ jit_movi_p (JIT_R1, current->methodOOP); jit_sti_p (&_gst_self, JIT_V0); jit_sti_p (&_gst_this_method, JIT_R1); jit_stxi_p (jit_ptr_field (gst_block_context, outerContext), JIT_R0, JIT_V1); /* Move the arguments and nil the temporaries */ emit_context_setup (header.numArgs, header.numTemps); define_ip_map_entry (0); emit_interrupt_check (JIT_NOREG); return (false); } /* Code tree creation */ gst_uchar * decode_bytecode (gst_uchar *bp) { static OOP *specialOOPs[] = { &_gst_nil_oop, &_gst_true_oop, &_gst_false_oop }; MATCH_BYTECODES (XLAT_BUILD_CODE_TREE, bp, ( PUSH_RECEIVER_VARIABLE { push_tree_node (IP0, NULL, TREE_PUSH | TREE_REC_VAR, (PTR) (uintptr_t) n); } PUSH_TEMPORARY_VARIABLE { push_tree_node (IP0, NULL, TREE_PUSH | TREE_TEMP, (PTR) (uintptr_t) n); } PUSH_LIT_CONSTANT { push_tree_node_oop (IP0, NULL, TREE_PUSH | TREE_LIT_CONST, literals[n]); } PUSH_LIT_VARIABLE { if (is_a_kind_of (OOP_INT_CLASS (literals[n]), _gst_association_class)) push_tree_node_oop (IP0, NULL, TREE_PUSH | TREE_LIT_VAR, literals[n]); else { push_tree_node_oop (IP0, NULL, TREE_PUSH | TREE_LIT_CONST, literals[n]); push_send_node (IP0, _gst_builtin_selectors[VALUE_SPECIAL].symbol, 0, false, TREE_SEND, 0); } } PUSH_SELF { push_tree_node (IP0, NULL, TREE_PUSH | TREE_SELF | self_class_check, NULL); } PUSH_SPECIAL { push_tree_node_oop (IP0, NULL, TREE_PUSH | TREE_LIT_CONST, *specialOOPs[n]); } PUSH_INTEGER { push_tree_node_oop (IP0, NULL, TREE_PUSH | TREE_LIT_CONST, FROM_INT (n)); } RETURN_METHOD_STACK_TOP { set_top_node_extra (TREE_EXTRA_METHOD_RET, 0); emit_code (); } RETURN_CONTEXT_STACK_TOP { set_top_node_extra (TREE_EXTRA_RETURN, 0); emit_code (); } LINE_NUMBER_BYTECODE { } STORE_RECEIVER_VARIABLE { push_tree_node (IP0, pop_tree_node (NULL), TREE_STORE | TREE_REC_VAR, (PTR) (uintptr_t) n); } STORE_TEMPORARY_VARIABLE { push_tree_node (IP0, pop_tree_node (NULL), TREE_STORE | TREE_TEMP, (PTR) (uintptr_t) n); } STORE_LIT_VARIABLE { if (is_a_kind_of (OOP_INT_CLASS (literals[n]), _gst_association_class)) push_tree_node_oop (IP0, pop_tree_node (NULL), TREE_STORE | TREE_LIT_VAR, literals[n]); else { code_tree *value, *var; inline_cache *ic; push_tree_node_oop (IP0, NULL, TREE_ALT_PUSH | TREE_LIT_CONST, literals[n]); ic = set_inline_cache (_gst_builtin_selectors[VALUE_COLON_SPECIAL].symbol, 1, false, TREE_SEND, 0); var = pop_tree_node (NULL); value = pop_tree_node (var); push_tree_node (IP0, value, TREE_SEND | TREE_STORE_LIT_VAR, (PTR) ic); } } SEND { push_send_node (IP0, literals[n], num_args, super, TREE_SEND, 0); } POP_INTO_NEW_STACKTOP { push_tree_node (IP0, pop_tree_node (pop_tree_node (NULL)), TREE_STORE | TREE_POP_INTO_ARRAY, (PTR) (uintptr_t) n); } POP_STACK_TOP { set_top_node_extra (TREE_EXTRA_POP, 0); emit_code (); /* This is very important! If we do not adjust T_SP here, we miscompile superoperators that include a POP/PUSH sequence. */ t_sp--; } DUP_STACK_TOP { push_tree_node (IP0, NULL, TREE_PUSH | TREE_DUP, NULL); } PUSH_OUTER_TEMP { push_tree_node (IP0, NULL, TREE_PUSH | TREE_OUTER_TEMP, (PTR) (uintptr_t) ((scopes << 8) | n)); } STORE_OUTER_TEMP { push_tree_node (IP0, pop_tree_node (NULL), TREE_STORE | TREE_OUTER_TEMP, (PTR) (uintptr_t) ((scopes << 8) | n)); } JUMP { set_top_node_extra (TREE_EXTRA_JMP_ALWAYS, ofs); emit_code (); } POP_JUMP_TRUE { set_top_node_extra (TREE_EXTRA_JMP_TRUE, ofs); emit_code (); } POP_JUMP_FALSE { set_top_node_extra (TREE_EXTRA_JMP_FALSE, ofs); emit_code (); } SEND_ARITH { int op = special_send_bytecodes[n]; const struct builtin_selector *bs = &_gst_builtin_selectors[n]; push_send_node (IP0, bs->symbol, bs->numArgs, false, op, n); } SEND_SPECIAL { int op = special_send_bytecodes[n + 16]; const struct builtin_selector *bs = &_gst_builtin_selectors[n + 16]; push_send_node (IP0, bs->symbol, bs->numArgs, false, op, n + 16); } SEND_IMMEDIATE { const struct builtin_selector *bs = &_gst_builtin_selectors[n]; push_send_node (IP0, bs->symbol, bs->numArgs, super, TREE_SEND | TREE_NORMAL, n); } MAKE_DIRTY_BLOCK { code_tree *arg; arg = pop_tree_node (NULL); push_tree_node (IP0, arg, TREE_SEND | TREE_DIRTY_BLOCK, NULL); } EXIT_INTERPRETER, INVALID { abort (); } )); #if 0 /* These used to be here but we do not produce them anymore. It would speed up the code a bit, so they are kept here as a remainder. */ REPLACE_SELF { push_tree_node (IP0, pop_tree_node (NULL), TREE_SET_TOP | TREE_SELF | self_class_check, NULL); emit_code (); } REPLACE_ONE { push_tree_node_oop (IP0, pop_tree_node (NULL), TREE_SET_TOP | TREE_LIT_CONST, FROM_INT (1)); emit_code (); } REPLACE_RECEIVER_VARIABLE { push_tree_node (IP0, pop_tree_node (NULL), TREE_SET_TOP | TREE_REC_VAR, (PTR) (uintptr_t) n); emit_code (); } REPLACE_TEMPORARY_VARIABLE { push_tree_node (IP0, pop_tree_node (NULL), TREE_SET_TOP | TREE_TEMP, (PTR) (uintptr_t) n); emit_code (); } REPLACE_LIT_CONSTANT { push_tree_node (IP0, pop_tree_node (NULL), TREE_SET_TOP | TREE_LIT_CONST, literals[n]); emit_code (); } REPLACE_LIT_VARIABLE { push_tree_node (IP0, pop_tree_node (NULL), TREE_SET_TOP | TREE_LIT_VAR, literals[n]); emit_code (); } #endif return bp; } /* Main translator loop */ void translate_method (OOP methodOOP, OOP receiverClass, int size) { gst_uchar *end, *bp, *bp_first; int inlineCacheCount; char *destinations; code_stack_pointer *stackPos; int i; rec_var_cached = self_cached = false; stack_cached = -1; sp_delta = -sizeof (PTR); deferred_head = NULL; method_class = GET_METHOD_CLASS (methodOOP); bc = GET_METHOD_BYTECODES (methodOOP); literals = GET_METHOD_LITERALS (methodOOP); end = bc + size; if (receiverClass == _gst_small_integer_class) self_class_check = TREE_IS_INTEGER; else self_class_check = TREE_IS_NOT_INTEGER; /* Emit the prolog of the compiled code. */ jit_ldi_p (JIT_V2, &sp); if (OOP_CLASS (methodOOP) == _gst_compiled_block_class) { if (emit_block_prolog (methodOOP, (gst_compiled_block) OOP_TO_OBJ (methodOOP))) return; } else { if (emit_method_prolog (methodOOP, (gst_compiled_method) OOP_TO_OBJ (methodOOP))) return; } /* Count the space for the inline caches */ for (inlineCacheCount = 0, bp = bc; bp < end; ) MATCH_BYTECODES (XLAT_COUNT_SENDS, bp, ( PUSH_RECEIVER_VARIABLE, PUSH_TEMPORARY_VARIABLE, PUSH_LIT_CONSTANT, PUSH_SELF, PUSH_SPECIAL, PUSH_INTEGER, RETURN_METHOD_STACK_TOP, RETURN_CONTEXT_STACK_TOP, LINE_NUMBER_BYTECODE, STORE_RECEIVER_VARIABLE, STORE_TEMPORARY_VARIABLE, POP_INTO_NEW_STACKTOP, POP_STACK_TOP, DUP_STACK_TOP, PUSH_OUTER_TEMP, STORE_OUTER_TEMP, JUMP, POP_JUMP_TRUE, POP_JUMP_FALSE, MAKE_DIRTY_BLOCK, EXIT_INTERPRETER, INVALID { } PUSH_LIT_VARIABLE, STORE_LIT_VARIABLE { if (!is_a_kind_of (OOP_INT_CLASS (literals[n]), _gst_association_class)) inlineCacheCount++; } SEND_ARITH, SEND_SPECIAL, SEND_IMMEDIATE, SEND { inlineCacheCount++; } )); if (inlineCacheCount) { current->inlineCaches = curr_inline_cache = (inline_cache *) xmalloc (inlineCacheCount * sizeof (inline_cache)); } stackPos = alloca ((1 + size) * sizeof (code_stack_pointer *)); labels = alloca ((1 + size) * sizeof (label *)); destinations = (char *) labels; _gst_compute_stack_positions (bc, size, (PTR *) t_stack, (PTR **) stackPos); _gst_analyze_bytecodes (methodOOP, size, destinations); /* Create labels for bytecodes on which a jump lands */ for (i = size; --i >= 0;) labels[i] = destinations[i] ? lbl_new () : NULL; /* Now, go through the main translation loop */ for (bp = bc, this_label = labels; bp < end; ) { if (!*stackPos) { assert (!*this_label); this_label += 2; stackPos += 2; continue; } /* Updating the t_sp in push_tree_node/pop_tree_node is not enough, because if two basic blocks are mutually exclusive the SP at the second block's entrance must be the same as the SP at the first block's entrance, even if the blocks have a non-zero stack balance. */ t_sp = *stackPos; if (*this_label) { /* A basic block ends here. Compile it. */ emit_code (); CACHE_STACK_TOP; /* If the label was not used yet, it will be used for a backward jump. A backward jump could be used to code an infinite loop such as `[] repeat', so we test _gst_except_flag here. */ if (!lbl_define (*this_label)) { define_ip_map_entry (bp - bc); jit_movi_ul (JIT_V0, bp - bc); jit_sti_ul (&ip, JIT_V0); emit_interrupt_check (JIT_NOREG); } } bp_first = bp; bp = decode_bytecode (bp); this_label += bp - bp_first; stackPos += bp - bp_first; } emit_code (); emit_deferred_sends (deferred_head); if (inlineCacheCount) curr_inline_cache[-1].more = false; } /* External interfacing */ void _gst_init_translator (void) { static mst_Boolean initialized = false; if (!initialized) { initialized = true; generate_run_time_code (); memset (methods_table, 0, sizeof (methods_table)); } } PTR _gst_map_virtual_ip (OOP methodOOP, OOP receiverClass, int ip) { ip_map *map; method_entry *method; method = find_method_entry (methodOOP, receiverClass); map = method->ipMap; if (!map) return NULL; do if (map->virtualIP == ip) return map->native_ip; while ((++map)->native_ip); return NULL; } PTR _gst_get_native_code (OOP methodOOP, OOP receiverClass) { if (!IS_OOP_VERIFIED (methodOOP)) _gst_verify_sent_method (methodOOP); return find_method_entry (methodOOP, receiverClass)->nativeCode; } method_entry * find_method_entry (OOP methodOOP, OOP receiverClass) { method_entry *method, *prev; unsigned int hashEntry; int size; if (IS_NIL (methodOOP)) return (NULL); hashEntry = OOP_INDEX (methodOOP) % HASH_TABLE_SIZE; if ((method = methods_table[hashEntry])) { if (method->methodOOP == methodOOP && method->receiverClass == receiverClass) return method; for (prev = method; (method = method->next); prev = method) { if (method->methodOOP != methodOOP || method->receiverClass != receiverClass) continue; prev->next = method->next; method->next = methods_table[hashEntry]; methods_table[hashEntry] = method; return method; } } size = NUM_INDEXABLE_FIELDS (methodOOP); new_method_entry (methodOOP, receiverClass, size); translate_method (methodOOP, receiverClass, size); return (finish_method_entry ()); } void reset_invalidated_inline_caches () { method_entry *method, **hashEntry; inline_cache *ic; jit_insn *lookupIP; for (hashEntry = methods_table; hashEntry <= &discarded; hashEntry++) for (method = *hashEntry; method; method = method->next) { ic = method->inlineCaches; if (!ic) continue; do { lookupIP = ic->is_super ? do_super_code : do_send_code; if (ic->cachedIP != lookupIP && !IS_VALID_IP (ic->cachedIP)) ic->cachedIP = lookupIP; } while ((ic++)->more); } } void _gst_reset_inline_caches () { method_entry *method, **hashEntry; inline_cache *ic; for (hashEntry = methods_table; hashEntry <= &discarded; hashEntry++) for (method = *hashEntry; method; method = method->next) { ic = method->inlineCaches; if (!ic) continue; do ic->cachedIP = ic->is_super ? do_super_code : do_send_code; while ((ic++)->more); } } void _gst_free_released_native_code (void) { method_entry *method; if (!released) return; reset_invalidated_inline_caches (); _gst_validate_method_cache_entries (); /* now free the list */ while ((method = released)) { released = released->next; xfree (method); } } void walk_and_remove_method (OOP methodOOP, method_entry **ptrNext) { method_entry *method; while ((method = *ptrNext)) { if (method->methodOOP != methodOOP) { /* Move ptrNext forward */ ptrNext = &(method->next); continue; } /* Adjust the list */ *ptrNext = method->next; method->next = released; released = method; /* Mark the method as freed */ if (method->inlineCaches) xfree (method->inlineCaches); method->receiverClass = NULL; method->inlineCaches = NULL; } /* Terminate the list */ *ptrNext = NULL; } void _gst_release_native_code (OOP methodOOP) { unsigned int hashEntry; hashEntry = OOP_INDEX (methodOOP) % HASH_TABLE_SIZE; walk_and_remove_method (methodOOP, &methods_table[hashEntry]); methodOOP->flags &= ~F_XLAT; if (methodOOP->flags & F_XLAT_DISCARDED) { walk_and_remove_method (methodOOP, &discarded); methodOOP->flags &= ~F_XLAT_DISCARDED; } } void _gst_discard_native_code (OOP methodOOP) { method_entry *method, **ptrNext; unsigned int hashEntry; methodOOP->flags |= F_XLAT_DISCARDED; hashEntry = OOP_INDEX (methodOOP) % HASH_TABLE_SIZE; ptrNext = &methods_table[hashEntry]; while ((method = *ptrNext)) { if (method->methodOOP != methodOOP) { /* Move ptrNext forward */ ptrNext = &(method->next); continue; } assert (methodOOP->flags & F_XLAT); /* Move to the `discarded' list */ *ptrNext = method->next; method->next = discarded; discarded = method; } /* Terminate the list */ *ptrNext = NULL; } #endif /* ENABLE_JIT_TRANSLATION */ smalltalk-3.2.5/libgst/genpr-scan.c0000644000175000017500000022177212130455565014134 00000000000000#line 2 "genpr-scan.c" #line 4 "genpr-scan.c" #define YY_INT_ALIGNED short int /* A lexical scanner generated by flex */ #define FLEX_SCANNER #define YY_FLEX_MAJOR_VERSION 2 #define YY_FLEX_MINOR_VERSION 5 #define YY_FLEX_SUBMINOR_VERSION 35 #if YY_FLEX_SUBMINOR_VERSION > 0 #define FLEX_BETA #endif /* First, we deal with platform-specific or compiler-specific issues. */ /* begin standard C headers. */ #include #include #include #include /* end standard C headers. */ /* flex integer type definitions */ #ifndef FLEXINT_H #define FLEXINT_H /* C99 systems have . Non-C99 systems may or may not. */ #if defined (__STDC_VERSION__) && __STDC_VERSION__ >= 199901L /* C99 says to define __STDC_LIMIT_MACROS before including stdint.h, * if you want the limit (max/min) macros for int types. */ #ifndef __STDC_LIMIT_MACROS #define __STDC_LIMIT_MACROS 1 #endif #include typedef int8_t flex_int8_t; typedef uint8_t flex_uint8_t; typedef int16_t flex_int16_t; typedef uint16_t flex_uint16_t; typedef int32_t flex_int32_t; typedef uint32_t flex_uint32_t; #else typedef signed char flex_int8_t; typedef short int flex_int16_t; typedef int flex_int32_t; typedef unsigned char flex_uint8_t; typedef unsigned short int flex_uint16_t; typedef unsigned int flex_uint32_t; /* Limits of integral types. */ #ifndef INT8_MIN #define INT8_MIN (-128) #endif #ifndef INT16_MIN #define INT16_MIN (-32767-1) #endif #ifndef INT32_MIN #define INT32_MIN (-2147483647-1) #endif #ifndef INT8_MAX #define INT8_MAX (127) #endif #ifndef INT16_MAX #define INT16_MAX (32767) #endif #ifndef INT32_MAX #define INT32_MAX (2147483647) #endif #ifndef UINT8_MAX #define UINT8_MAX (255U) #endif #ifndef UINT16_MAX #define UINT16_MAX (65535U) #endif #ifndef UINT32_MAX #define UINT32_MAX (4294967295U) #endif #endif /* ! C99 */ #endif /* ! FLEXINT_H */ #ifdef __cplusplus /* The "const" storage-class-modifier is valid. */ #define YY_USE_CONST #else /* ! __cplusplus */ /* C99 requires __STDC__ to be defined as 1. */ #if defined (__STDC__) #define YY_USE_CONST #endif /* defined (__STDC__) */ #endif /* ! __cplusplus */ #ifdef YY_USE_CONST #define yyconst const #else #define yyconst #endif /* Returned upon end-of-file. */ #define YY_NULL 0 /* Promotes a possibly negative, possibly signed char to an unsigned * integer for use as an array index. If the signed char is negative, * we want to instead treat it as an 8-bit unsigned char, hence the * double cast. */ #define YY_SC_TO_UI(c) ((unsigned int) (unsigned char) c) /* Enter a start condition. This macro really ought to take a parameter, * but we do it the disgusting crufty way forced on us by the ()-less * definition of BEGIN. */ #define BEGIN (yy_start) = 1 + 2 * /* Translate the current start state into a value that can be later handed * to BEGIN to return to the state. The YYSTATE alias is for lex * compatibility. */ #define YY_START (((yy_start) - 1) / 2) #define YYSTATE YY_START /* Action number for EOF rule of a given start state. */ #define YY_STATE_EOF(state) (YY_END_OF_BUFFER + state + 1) /* Special action meaning "start processing a new file". */ #define YY_NEW_FILE yyrestart(yyin ) #define YY_END_OF_BUFFER_CHAR 0 /* Size of default input buffer. */ #ifndef YY_BUF_SIZE #ifdef __ia64__ /* On IA-64, the buffer size is 16k, not 8k. * Moreover, YY_BUF_SIZE is 2*YY_READ_BUF_SIZE in the general case. * Ditto for the __ia64__ case accordingly. */ #define YY_BUF_SIZE 32768 #else #define YY_BUF_SIZE 16384 #endif /* __ia64__ */ #endif /* The state buf must be large enough to hold one state per character in the main buffer. */ #define YY_STATE_BUF_SIZE ((YY_BUF_SIZE + 2) * sizeof(yy_state_type)) #ifndef YY_TYPEDEF_YY_BUFFER_STATE #define YY_TYPEDEF_YY_BUFFER_STATE typedef struct yy_buffer_state *YY_BUFFER_STATE; #endif extern int yyleng; extern FILE *yyin, *yyout; #define EOB_ACT_CONTINUE_SCAN 0 #define EOB_ACT_END_OF_FILE 1 #define EOB_ACT_LAST_MATCH 2 #define YY_LESS_LINENO(n) /* Return all but the first "n" matched characters back to the input stream. */ #define yyless(n) \ do \ { \ /* Undo effects of setting up yytext. */ \ int yyless_macro_arg = (n); \ YY_LESS_LINENO(yyless_macro_arg);\ *yy_cp = (yy_hold_char); \ YY_RESTORE_YY_MORE_OFFSET \ (yy_c_buf_p) = yy_cp = yy_bp + yyless_macro_arg - YY_MORE_ADJ; \ YY_DO_BEFORE_ACTION; /* set up yytext again */ \ } \ while ( 0 ) #define unput(c) yyunput( c, (yytext_ptr) ) #ifndef YY_TYPEDEF_YY_SIZE_T #define YY_TYPEDEF_YY_SIZE_T typedef size_t yy_size_t; #endif #ifndef YY_STRUCT_YY_BUFFER_STATE #define YY_STRUCT_YY_BUFFER_STATE struct yy_buffer_state { FILE *yy_input_file; char *yy_ch_buf; /* input buffer */ char *yy_buf_pos; /* current position in input buffer */ /* Size of input buffer in bytes, not including room for EOB * characters. */ yy_size_t yy_buf_size; /* Number of characters read into yy_ch_buf, not including EOB * characters. */ int yy_n_chars; /* Whether we "own" the buffer - i.e., we know we created it, * and can realloc() it to grow it, and should free() it to * delete it. */ int yy_is_our_buffer; /* Whether this is an "interactive" input source; if so, and * if we're using stdio for input, then we want to use getc() * instead of fread(), to make sure we stop fetching input after * each newline. */ int yy_is_interactive; /* Whether we're considered to be at the beginning of a line. * If so, '^' rules will be active on the next match, otherwise * not. */ int yy_at_bol; int yy_bs_lineno; /**< The line count. */ int yy_bs_column; /**< The column count. */ /* Whether to try to fill the input buffer when we reach the * end of it. */ int yy_fill_buffer; int yy_buffer_status; #define YY_BUFFER_NEW 0 #define YY_BUFFER_NORMAL 1 /* When an EOF's been seen but there's still some text to process * then we mark the buffer as YY_EOF_PENDING, to indicate that we * shouldn't try reading from the input source any more. We might * still have a bunch of tokens to match, though, because of * possible backing-up. * * When we actually see the EOF, we change the status to "new" * (via yyrestart()), so that the user can continue scanning by * just pointing yyin at a new input file. */ #define YY_BUFFER_EOF_PENDING 2 }; #endif /* !YY_STRUCT_YY_BUFFER_STATE */ /* Stack of input buffers. */ static size_t yy_buffer_stack_top = 0; /**< index of top of stack. */ static size_t yy_buffer_stack_max = 0; /**< capacity of stack. */ static YY_BUFFER_STATE * yy_buffer_stack = 0; /**< Stack as an array. */ /* We provide macros for accessing buffer states in case in the * future we want to put the buffer states in a more general * "scanner state". * * Returns the top of the stack, or NULL. */ #define YY_CURRENT_BUFFER ( (yy_buffer_stack) \ ? (yy_buffer_stack)[(yy_buffer_stack_top)] \ : NULL) /* Same as previous macro, but useful when we know that the buffer stack is not * NULL or when we need an lvalue. For internal use only. */ #define YY_CURRENT_BUFFER_LVALUE (yy_buffer_stack)[(yy_buffer_stack_top)] /* yy_hold_char holds the character lost when yytext is formed. */ static char yy_hold_char; static int yy_n_chars; /* number of characters read into yy_ch_buf */ int yyleng; /* Points to current character in buffer. */ static char *yy_c_buf_p = (char *) 0; static int yy_init = 0; /* whether we need to initialize */ static int yy_start = 0; /* start state number */ /* Flag which is used to allow yywrap()'s to do buffer switches * instead of setting up a fresh yyin. A bit of a hack ... */ static int yy_did_buffer_switch_on_eof; void yyrestart (FILE *input_file ); void yy_switch_to_buffer (YY_BUFFER_STATE new_buffer ); YY_BUFFER_STATE yy_create_buffer (FILE *file,int size ); void yy_delete_buffer (YY_BUFFER_STATE b ); void yy_flush_buffer (YY_BUFFER_STATE b ); void yypush_buffer_state (YY_BUFFER_STATE new_buffer ); void yypop_buffer_state (void ); static void yyensure_buffer_stack (void ); static void yy_load_buffer_state (void ); static void yy_init_buffer (YY_BUFFER_STATE b,FILE *file ); #define YY_FLUSH_BUFFER yy_flush_buffer(YY_CURRENT_BUFFER ) YY_BUFFER_STATE yy_scan_buffer (char *base,yy_size_t size ); YY_BUFFER_STATE yy_scan_string (yyconst char *yy_str ); YY_BUFFER_STATE yy_scan_bytes (yyconst char *bytes,int len ); void *yyalloc (yy_size_t ); void *yyrealloc (void *,yy_size_t ); void yyfree (void * ); #define yy_new_buffer yy_create_buffer #define yy_set_interactive(is_interactive) \ { \ if ( ! YY_CURRENT_BUFFER ){ \ yyensure_buffer_stack (); \ YY_CURRENT_BUFFER_LVALUE = \ yy_create_buffer(yyin,YY_BUF_SIZE ); \ } \ YY_CURRENT_BUFFER_LVALUE->yy_is_interactive = is_interactive; \ } #define yy_set_bol(at_bol) \ { \ if ( ! YY_CURRENT_BUFFER ){\ yyensure_buffer_stack (); \ YY_CURRENT_BUFFER_LVALUE = \ yy_create_buffer(yyin,YY_BUF_SIZE ); \ } \ YY_CURRENT_BUFFER_LVALUE->yy_at_bol = at_bol; \ } #define YY_AT_BOL() (YY_CURRENT_BUFFER_LVALUE->yy_at_bol) #define yywrap(n) 1 #define YY_SKIP_YYWRAP typedef unsigned char YY_CHAR; FILE *yyin = (FILE *) 0, *yyout = (FILE *) 0; typedef int yy_state_type; extern int yylineno; int yylineno = 1; extern char *yytext; #define yytext_ptr yytext static yyconst flex_int16_t yy_nxt[][35] = { { 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0 }, { 13, 14, 15, 16, 15, 17, 14, 18, 19, 20, 14, 21, 22, 23, 24, 24, 25, 26, 27, 27, 28, 14, 29, 27, 27, 27, 27, 27, 30, 27, 27, 27, 27, 31, 14 }, { 13, 14, 32, 16, 15, 17, 33, 18, 19, 20, 14, 21, 22, 23, 24, 24, 25, 26, 27, 27, 28, 14, 29, 27, 27, 27, 27, 27, 30, 27, 27, 27, 27, 31, 14 }, { 13, 34, 35, 36, 35, 34, 34, 34, 34, 34, 37, 34, 34, 34, 34, 34, 34, 34, 34, 34, 34, 34, 34, 34, 34, 34, 34, 34, 34, 34, 34, 34, 34, 34, 34 }, { 13, 34, 35, 36, 35, 34, 34, 34, 34, 34, 37, 34, 34, 34, 34, 34, 34, 34, 34, 34, 34, 34, 34, 34, 34, 34, 34, 34, 34, 34, 34, 34, 34, 34, 34 }, { 13, 38, 39, 16, 39, 38, 38, 40, 38, 38, 38, 38, 38, 38, 38, 38, 38, 38, 38, 38, 38, 41, 38, 38, 38, 38, 38, 38, 38, 38, 38, 38, 38, 38, 38 }, { 13, 38, 39, 16, 39, 38, 38, 40, 38, 38, 38, 38, 38, 38, 38, 38, 38, 38, 38, 38, 38, 41, 38, 38, 38, 38, 38, 38, 38, 38, 38, 38, 38, 38, 38 }, { 13, 38, 39, 16, 39, 42, 38, 38, 38, 38, 38, 38, 38, 38, 38, 38, 38, 38, 38, 38, 38, 41, 38, 38, 38, 38, 38, 38, 38, 38, 38, 38, 38, 38, 38 }, { 13, 38, 39, 16, 39, 42, 38, 38, 38, 38, 38, 38, 38, 38, 38, 38, 38, 38, 38, 38, 38, 41, 38, 38, 38, 38, 38, 38, 38, 38, 38, 38, 38, 38, 38 }, { 13, 43, 44, 45, 44, 43, 43, 43, 43, 43, 43, 43, 43, 43, 43, 43, 43, 43, 43, 43, 43, 46, 43, 43, 43, 43, 43, 43, 43, 43, 43, 43, 43, 43, 43 }, { 13, 43, 44, 45, 44, 43, 43, 43, 43, 43, 43, 43, 43, 43, 43, 43, 43, 43, 43, 43, 43, 46, 43, 43, 43, 43, 43, 43, 43, 43, 43, 43, 43, 43, 43 }, { 13, 47, 48, 16, 48, 49, 47, 50, 51, 52, 47, 47, 53, 54, 55, 55, 47, 47, 56, 56, 47, 47, 47, 56, 56, 56, 56, 56, 57, 56, 56, 56, 56, 58, 59 }, { 13, 47, 60, 16, 48, 49, 61, 50, 51, 52, 47, 47, 53, 54, 55, 55, 47, 47, 56, 56, 47, 47, 47, 56, 56, 56, 56, 56, 57, 56, 56, 56, 56, 58, 59 }, { -13, -13, -13, -13, -13, -13, -13, -13, -13, -13, -13, -13, -13, -13, -13, -13, -13, -13, -13, -13, -13, -13, -13, -13, -13, -13, -13, -13, -13, -13, -13, -13, -13, -13, -13 }, { 13, -14, -14, -14, -14, -14, -14, -14, -14, -14, -14, -14, -14, -14, -14, -14, -14, -14, -14, -14, -14, -14, -14, -14, -14, -14, -14, -14, -14, -14, -14, -14, -14, -14, -14 }, { 13, -15, 62, -15, 62, -15, -15, -15, -15, -15, -15, -15, -15, -15, -15, -15, -15, -15, -15, -15, -15, -15, -15, -15, -15, -15, -15, -15, -15, -15, -15, -15, -15, -15, -15 }, { 13, -16, -16, 63, -16, -16, -16, -16, -16, -16, -16, -16, -16, -16, -16, -16, -16, -16, -16, -16, -16, -16, -16, -16, -16, -16, -16, -16, -16, -16, -16, -16, -16, -16, -16 }, { 13, -17, -17, -17, -17, -17, -17, -17, -17, -17, -17, -17, -17, -17, -17, -17, -17, -17, -17, -17, -17, -17, -17, -17, -17, -17, -17, -17, -17, -17, -17, -17, -17, -17, -17 }, { 13, -18, -18, -18, -18, -18, -18, -18, -18, -18, -18, -18, -18, -18, -18, -18, -18, -18, -18, -18, -18, -18, -18, -18, -18, -18, -18, -18, -18, -18, -18, -18, -18, -18, -18 }, { 13, -19, -19, -19, -19, -19, -19, -19, -19, -19, -19, -19, -19, -19, -19, -19, -19, -19, -19, -19, -19, -19, -19, -19, -19, -19, -19, -19, -19, -19, -19, -19, -19, -19, -19 }, { 13, -20, -20, -20, -20, -20, -20, -20, -20, -20, -20, -20, -20, -20, -20, -20, -20, -20, -20, -20, -20, -20, -20, -20, -20, -20, -20, -20, -20, -20, -20, -20, -20, -20, -20 }, { 13, -21, -21, -21, -21, -21, -21, -21, -21, -21, -21, -21, -21, -21, -21, -21, -21, -21, -21, -21, -21, -21, -21, -21, -21, -21, -21, -21, -21, -21, -21, -21, -21, -21, -21 }, { 13, -22, -22, -22, -22, -22, -22, -22, -22, -22, 64, -22, -22, -22, -22, -22, -22, -22, -22, -22, -22, -22, -22, -22, -22, -22, -22, -22, -22, -22, -22, -22, -22, -22, -22 }, { 13, -23, -23, -23, -23, -23, -23, -23, -23, -23, -23, -23, -23, 65, 65, -23, -23, -23, -23, -23, -23, -23, -23, -23, -23, -23, -23, -23, -23, -23, -23, -23, 66, -23, -23 }, { 13, -24, -24, -24, -24, -24, -24, -24, -24, -24, -24, -24, -24, 67, 67, 67, -24, -24, -24, -24, -24, -24, -24, -24, -24, -24, -24, -24, -24, -24, -24, -24, -24, -24, -24 }, { 13, -25, -25, -25, -25, -25, -25, -25, -25, -25, -25, -25, -25, -25, -25, -25, -25, -25, -25, -25, -25, -25, -25, -25, -25, -25, -25, -25, -25, -25, -25, -25, -25, -25, -25 }, { 13, -26, -26, -26, -26, -26, -26, -26, -26, -26, -26, -26, -26, -26, -26, -26, -26, -26, -26, -26, -26, -26, -26, -26, -26, -26, -26, -26, -26, -26, -26, -26, -26, -26, -26 }, { 13, -27, -27, -27, -27, -27, -27, -27, -27, -27, -27, -27, -27, 68, 68, 68, -27, -27, 68, 68, -27, -27, -27, 68, 68, 68, 68, 68, 68, 68, 68, 68, 68, -27, -27 }, { 13, -28, -28, -28, -28, -28, -28, -28, -28, -28, -28, -28, -28, -28, -28, -28, -28, -28, -28, -28, -28, -28, -28, -28, -28, -28, -28, -28, -28, -28, -28, -28, -28, -28, -28 }, { 13, -29, -29, -29, -29, -29, -29, -29, -29, -29, -29, -29, -29, -29, -29, -29, -29, -29, -29, -29, -29, -29, -29, -29, -29, -29, -29, -29, -29, -29, -29, -29, -29, -29, -29 }, { 13, -30, -30, -30, -30, -30, -30, -30, -30, -30, -30, -30, -30, 68, 68, 68, -30, -30, 68, 68, -30, -30, -30, 68, 68, 68, 68, 68, 68, 69, 68, 68, 68, -30, -30 }, { 13, -31, -31, -31, -31, -31, -31, -31, -31, -31, -31, -31, -31, -31, -31, -31, -31, -31, -31, -31, -31, -31, -31, -31, -31, -31, -31, -31, -31, -31, -31, -31, -31, -31, -31 }, { 13, -32, 70, -32, 62, -32, 71, -32, -32, -32, -32, -32, -32, -32, -32, -32, -32, -32, -32, -32, -32, -32, -32, -32, -32, -32, -32, -32, -32, -32, -32, -32, -32, -32, -32 }, { 13, -33, -33, -33, -33, -33, -33, -33, -33, -33, -33, -33, -33, -33, -33, -33, -33, -33, -33, -33, -33, -33, -33, -33, -33, -33, -33, -33, -33, -33, -33, -33, -33, -33, -33 }, { 13, 72, 72, 73, 72, 72, 72, 72, 72, 72, 74, 72, 72, 72, 72, 72, 72, 72, 72, 72, 72, 72, 72, 72, 72, 72, 72, 72, 72, 72, 72, 72, 72, 72, 72 }, { 13, 72, 75, 73, 75, 72, 72, 72, 72, 72, 74, 72, 72, 72, 72, 72, 72, 72, 72, 72, 72, 72, 72, 72, 72, 72, 72, 72, 72, 72, 72, 72, 72, 72, 72 }, { 13, -36, -36, 63, -36, -36, -36, -36, -36, -36, -36, -36, -36, -36, -36, -36, -36, -36, -36, -36, -36, -36, -36, -36, -36, -36, -36, -36, -36, -36, -36, -36, -36, -36, -36 }, { 13, 76, 76, 77, 76, 76, 76, 76, 76, 76, 74, 76, 78, 76, 76, 76, 76, 76, 76, 76, 76, 76, 76, 76, 76, 76, 76, 76, 76, 76, 76, 76, 76, 76, 76 }, { 13, -38, -38, -38, -38, -38, -38, -38, -38, -38, -38, -38, -38, -38, -38, -38, -38, -38, -38, -38, -38, -38, -38, -38, -38, -38, -38, -38, -38, -38, -38, -38, -38, -38, -38 }, { 13, -39, 62, -39, 62, -39, -39, -39, -39, -39, -39, -39, -39, -39, -39, -39, -39, -39, -39, -39, -39, -39, -39, -39, -39, -39, -39, -39, -39, -39, -39, -39, -39, -39, -39 }, { 13, -40, -40, -40, -40, -40, -40, -40, -40, -40, -40, -40, -40, -40, -40, -40, -40, -40, -40, -40, -40, -40, -40, -40, -40, -40, -40, -40, -40, -40, -40, -40, -40, -40, -40 }, { 13, 79, 79, -41, 79, 79, 79, 79, 79, 79, 79, 79, 79, 79, 79, 79, 79, 79, 79, 79, 79, 79, 79, 79, 79, 79, 79, 79, 79, 79, 79, 79, 79, 79, 79 }, { 13, -42, -42, -42, -42, -42, -42, -42, -42, -42, -42, -42, -42, -42, -42, -42, -42, -42, -42, -42, -42, -42, -42, -42, -42, -42, -42, -42, -42, -42, -42, -42, -42, -42, -42 }, { 13, 80, 80, 81, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 82, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80 }, { 13, 80, 83, 81, 83, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 82, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80 }, { 13, -45, -45, 63, -45, -45, -45, -45, -45, -45, -45, -45, -45, -45, -45, -45, -45, -45, -45, -45, -45, -45, -45, -45, -45, -45, -45, -45, -45, -45, -45, -45, -45, -45, -45 }, { 13, 80, 84, 85, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 82, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80 }, { 13, -47, -47, -47, -47, -47, -47, -47, -47, -47, -47, -47, -47, -47, -47, -47, -47, -47, -47, -47, -47, -47, -47, -47, -47, -47, -47, -47, -47, -47, -47, -47, -47, -47, -47 }, { 13, -48, 62, -48, 62, -48, -48, -48, -48, -48, -48, -48, -48, -48, -48, -48, -48, -48, -48, -48, -48, -48, -48, -48, -48, -48, -48, -48, -48, -48, -48, -48, -48, -48, -48 }, { 13, -49, -49, -49, -49, -49, -49, -49, -49, -49, -49, -49, -49, -49, -49, -49, -49, -49, -49, -49, -49, -49, -49, -49, -49, -49, -49, -49, -49, -49, -49, -49, -49, -49, -49 }, { 13, -50, -50, -50, -50, -50, -50, -50, -50, -50, -50, -50, -50, -50, -50, -50, -50, -50, -50, -50, -50, -50, -50, -50, -50, -50, -50, -50, -50, -50, -50, -50, -50, -50, -50 }, { 13, -51, -51, -51, -51, -51, -51, -51, -51, -51, -51, -51, -51, -51, -51, -51, -51, -51, -51, -51, -51, -51, -51, -51, -51, -51, -51, -51, -51, -51, -51, -51, -51, -51, -51 }, { 13, -52, -52, -52, -52, -52, -52, -52, -52, -52, -52, -52, -52, -52, -52, -52, -52, -52, -52, -52, -52, -52, -52, -52, -52, -52, -52, -52, -52, -52, -52, -52, -52, -52, -52 }, { 13, -53, -53, -53, -53, -53, -53, -53, -53, -53, 64, -53, -53, -53, -53, -53, -53, -53, -53, -53, -53, -53, -53, -53, -53, -53, -53, -53, -53, -53, -53, -53, -53, -53, -53 }, { 13, -54, -54, -54, -54, -54, -54, -54, -54, -54, -54, -54, -54, 65, 65, -54, -54, -54, -54, -54, -54, -54, -54, -54, -54, -54, -54, -54, -54, -54, -54, -54, 66, -54, -54 }, { 13, -55, -55, -55, -55, -55, -55, -55, -55, -55, -55, -55, -55, 67, 67, 67, -55, -55, -55, -55, -55, -55, -55, -55, -55, -55, -55, -55, -55, -55, -55, -55, -55, -55, -55 }, { 13, -56, -56, -56, -56, -56, -56, -56, -56, -56, -56, -56, -56, 68, 68, 68, -56, -56, 68, 68, -56, -56, -56, 68, 68, 68, 68, 68, 68, 68, 68, 68, 68, -56, -56 }, { 13, -57, -57, -57, -57, -57, -57, -57, -57, -57, -57, -57, -57, 68, 68, 68, -57, -57, 68, 68, -57, -57, -57, 68, 68, 68, 68, 68, 68, 86, 68, 68, 68, -57, -57 }, { 13, -58, -58, -58, -58, -58, -58, -58, -58, -58, -58, -58, -58, -58, -58, -58, -58, -58, -58, -58, -58, -58, -58, -58, -58, -58, -58, -58, -58, -58, -58, -58, -58, -58, -58 }, { 13, -59, -59, -59, -59, -59, -59, -59, -59, -59, -59, -59, -59, -59, -59, -59, -59, -59, -59, -59, -59, -59, -59, -59, -59, -59, -59, -59, -59, -59, -59, -59, -59, -59, -59 }, { 13, -60, 70, -60, 62, -60, 71, -60, -60, -60, -60, -60, -60, -60, -60, -60, -60, -60, -60, -60, -60, -60, -60, -60, -60, -60, -60, -60, -60, -60, -60, -60, -60, -60, -60 }, { 13, -61, -61, -61, -61, -61, -61, -61, -61, -61, -61, -61, -61, -61, -61, -61, -61, -61, -61, -61, -61, -61, -61, -61, -61, -61, -61, -61, -61, -61, -61, -61, -61, -61, -61 }, { 13, -62, 62, -62, 62, -62, -62, -62, -62, -62, -62, -62, -62, -62, -62, -62, -62, -62, -62, -62, -62, -62, -62, -62, -62, -62, -62, -62, -62, -62, -62, -62, -62, -62, -62 }, { 13, -63, -63, 63, -63, -63, -63, -63, -63, -63, -63, -63, -63, -63, -63, -63, -63, -63, -63, -63, -63, -63, -63, -63, -63, -63, -63, -63, -63, -63, -63, -63, -63, -63, -63 }, { 13, -64, -64, -64, -64, -64, -64, -64, -64, -64, -64, -64, -64, -64, -64, -64, -64, -64, -64, -64, -64, -64, -64, -64, -64, -64, -64, -64, -64, -64, -64, -64, -64, -64, -64 }, { 13, -65, -65, -65, -65, -65, -65, -65, -65, -65, -65, -65, -65, 65, 65, -65, -65, -65, -65, -65, -65, -65, -65, -65, -65, -65, -65, -65, -65, -65, -65, -65, -65, -65, -65 }, { 13, -66, -66, -66, -66, -66, -66, -66, -66, -66, -66, -66, -66, 87, 87, 87, -66, -66, 87, -66, -66, -66, -66, -66, 87, 87, -66, -66, -66, -66, -66, -66, -66, -66, -66 }, { 13, -67, -67, -67, -67, -67, -67, -67, -67, -67, -67, -67, -67, 67, 67, 67, -67, -67, -67, -67, -67, -67, -67, -67, -67, -67, -67, -67, -67, -67, -67, -67, -67, -67, -67 }, { 13, -68, -68, -68, -68, -68, -68, -68, -68, -68, -68, -68, -68, 68, 68, 68, -68, -68, 68, 68, -68, -68, -68, 68, 68, 68, 68, 68, 68, 68, 68, 68, 68, -68, -68 }, { 13, -69, -69, -69, -69, -69, -69, -69, -69, -69, -69, -69, -69, 68, 68, 68, -69, -69, 68, 68, -69, -69, -69, 68, 68, 68, 88, 68, 68, 68, 68, 68, 68, -69, -69 }, { 13, -70, 70, -70, 62, -70, 71, -70, -70, -70, -70, -70, -70, -70, -70, -70, -70, -70, -70, -70, -70, -70, -70, -70, -70, -70, -70, -70, -70, -70, -70, -70, -70, -70, -70 }, { 13, -71, -71, -71, -71, -71, -71, -71, -71, -71, -71, -71, -71, -71, -71, -71, -71, -71, -71, -71, -71, -71, -71, -71, -71, -71, -71, -71, -71, -71, -71, -71, -71, -71, -71 }, { 13, 72, 72, 73, 72, 72, 72, 72, 72, 72, 74, 72, 72, 72, 72, 72, 72, 72, 72, 72, 72, 72, 72, 72, 72, 72, 72, 72, 72, 72, 72, 72, 72, 72, 72 }, { 13, -73, -73, -73, -73, -73, -73, -73, -73, -73, -73, -73, -73, -73, -73, -73, -73, -73, -73, -73, -73, -73, -73, -73, -73, -73, -73, -73, -73, -73, -73, -73, -73, -73, -73 }, { 13, 76, 76, 77, 76, 76, 76, 76, 76, 76, 74, 76, 78, 76, 76, 76, 76, 76, 76, 76, 76, 76, 76, 76, 76, 76, 76, 76, 76, 76, 76, 76, 76, 76, 76 }, { 13, 72, 75, 73, 75, 72, 72, 72, 72, 72, 74, 72, 72, 72, 72, 72, 72, 72, 72, 72, 72, 72, 72, 72, 72, 72, 72, 72, 72, 72, 72, 72, 72, 72, 72 }, { 13, -76, -76, -76, -76, -76, -76, -76, -76, -76, -76, -76, -76, -76, -76, -76, -76, -76, -76, -76, -76, -76, -76, -76, -76, -76, -76, -76, -76, -76, -76, -76, -76, -76, -76 }, { 13, -77, -77, -77, -77, -77, -77, -77, -77, -77, -77, -77, -77, -77, -77, -77, -77, -77, -77, -77, -77, -77, -77, -77, -77, -77, -77, -77, -77, -77, -77, -77, -77, -77, -77 }, { 13, -78, -78, -78, -78, -78, -78, -78, -78, -78, -78, -78, -78, -78, -78, -78, -78, -78, -78, -78, -78, -78, -78, -78, -78, -78, -78, -78, -78, -78, -78, -78, -78, -78, -78 }, { 13, -79, -79, -79, -79, -79, -79, -79, -79, -79, -79, -79, -79, -79, -79, -79, -79, -79, -79, -79, -79, -79, -79, -79, -79, -79, -79, -79, -79, -79, -79, -79, -79, -79, -79 }, { 13, 80, 80, 81, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 82, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80 }, { 13, -81, -81, -81, -81, -81, -81, -81, -81, -81, -81, -81, -81, -81, -81, -81, -81, -81, -81, -81, -81, -81, -81, -81, -81, -81, -81, -81, -81, -81, -81, -81, -81, -81, -81 }, { 13, 80, 84, 85, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 82, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80 }, { 13, 80, 83, 81, 83, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 82, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80 }, { 13, 80, 84, 85, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 82, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80 }, { 13, -85, -85, -85, -85, -85, -85, -85, -85, -85, -85, -85, -85, -85, -85, -85, -85, -85, -85, -85, -85, -85, -85, -85, -85, -85, -85, -85, -85, -85, -85, -85, -85, -85, -85 }, { 13, -86, -86, -86, -86, -86, -86, -86, -86, -86, -86, -86, -86, 68, 68, 68, -86, -86, 68, 68, -86, -86, -86, 68, 68, 68, 89, 68, 68, 68, 68, 68, 68, -86, -86 }, { 13, -87, -87, -87, -87, -87, -87, -87, -87, -87, -87, -87, -87, 87, 87, 87, -87, -87, 87, -87, -87, -87, -87, -87, 87, 87, -87, -87, -87, -87, -87, -87, -87, -87, -87 }, { 13, -88, -88, -88, -88, -88, -88, -88, -88, -88, -88, -88, -88, 68, 68, 68, -88, -88, 68, 68, -88, -88, -88, 68, 68, 68, 68, 90, 68, 68, 68, 68, 68, -88, -88 }, { 13, -89, -89, -89, -89, -89, -89, -89, -89, -89, -89, -89, -89, 68, 68, 68, -89, -89, 68, 68, -89, -89, -89, 68, 68, 68, 68, 91, 68, 68, 68, 68, 68, -89, -89 }, { 13, -90, -90, -90, -90, -90, -90, -90, -90, -90, -90, -90, -90, 68, 68, 68, -90, -90, 68, 68, -90, -90, -90, 92, 68, 68, 93, 68, 68, 68, 68, 68, 68, -90, -90 }, { 13, -91, -91, -91, -91, -91, -91, -91, -91, -91, -91, -91, -91, 68, 68, 68, -91, -91, 68, 68, -91, -91, -91, 92, 68, 68, 68, 68, 68, 68, 68, 68, 68, -91, -91 }, { 13, -92, -92, -92, -92, -92, -92, -92, -92, -92, -92, -92, -92, 68, 68, 68, -92, -92, 68, 68, -92, -92, -92, 68, 68, 68, 94, 68, 68, 68, 68, 68, 68, -92, -92 }, { 13, -93, -93, -93, -93, -93, -93, -93, -93, -93, -93, -93, -93, 68, 68, 68, -93, -93, 68, 68, -93, -93, -93, 68, 68, 68, 68, 68, 68, 68, 95, 68, 68, -93, -93 }, { 13, -94, -94, -94, -94, -94, -94, -94, -94, -94, -94, -94, -94, 68, 68, 68, -94, -94, 68, 68, -94, -94, -94, 68, 96, 68, 68, 68, 68, 68, 68, 68, 68, -94, -94 }, { 13, -95, -95, -95, -95, -95, -95, -95, -95, -95, -95, -95, -95, 68, 68, 68, -95, -95, 68, 68, -95, -95, -95, 68, 68, 68, 97, 68, 68, 68, 68, 68, 68, -95, -95 }, { 13, -96, -96, -96, -96, -96, -96, -96, -96, -96, -96, -96, -96, 68, 68, 68, -96, -96, 68, 68, -96, -96, -96, 68, 68, 68, 68, 68, 68, 68, 68, 68, 68, -96, -96 }, { 13, -97, -97, -97, -97, -97, -97, -97, -97, -97, -97, -97, -97, 68, 68, 68, -97, -97, 68, 68, -97, -97, -97, 68, 68, 68, 68, 68, 68, 68, 68, 98, 68, -97, -97 }, { 13, -98, -98, -98, -98, -98, -98, -98, -98, -98, -98, -98, -98, 68, 68, 68, -98, -98, 68, 68, -98, -98, -98, 68, 68, 99, 68, 68, 68, 68, 68, 68, 68, -98, -98 }, { 13, -99, -99, -99, -99, -99, -99, -99, -99, -99, -99, -99, -99, 68, 68, 68, -99, -99, 68, 68, -99, -99, -99, 68, 68, 68, 68, 68, 68, 68, 68, 68, 68, -99, -99 }, } ; static yy_state_type yy_get_previous_state (void ); static yy_state_type yy_try_NUL_trans (yy_state_type current_state ); static int yy_get_next_buffer (void ); static void yy_fatal_error (yyconst char msg[] ); /* Done after the current pattern has been matched and before the * corresponding action - sets up yytext. */ #define YY_DO_BEFORE_ACTION \ (yytext_ptr) = yy_bp; \ yyleng = (size_t) (yy_cp - yy_bp); \ (yy_hold_char) = *yy_cp; \ *yy_cp = '\0'; \ (yy_c_buf_p) = yy_cp; #define YY_NUM_RULES 33 #define YY_END_OF_BUFFER 34 /* This struct is not used in this scanner, but its presence is necessary. */ struct yy_trans_info { flex_int32_t yy_verify; flex_int32_t yy_nxt; }; static yyconst flex_int16_t yy_accept[100] = { 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 34, 33, 2, 1, 11, 10, 14, 15, 6, 33, 33, 17, 8, 7, 20, 4, 5, 20, 9, 2, 13, 33, 2, 1, 33, 30, 2, 27, 30, 28, 33, 2, 1, 33, 23, 2, 11, 10, 14, 15, 23, 23, 17, 20, 20, 21, 22, 2, 13, 2, 1, 12, 19, 0, 17, 20, 20, 2, 13, 0, 24, 0, 2, 25, 24, 26, 29, 0, 32, 0, 2, 0, 31, 20, 18, 20, 20, 20, 20, 20, 20, 20, 20, 16, 20, 20, 3 } ; static yyconst flex_int32_t yy_ec[256] = { 0, 1, 1, 1, 1, 1, 1, 1, 1, 2, 3, 1, 4, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 2, 1, 5, 6, 1, 1, 1, 7, 8, 9, 10, 1, 11, 1, 1, 12, 13, 14, 14, 14, 14, 14, 14, 14, 15, 15, 16, 1, 1, 17, 1, 1, 1, 18, 18, 18, 18, 18, 18, 19, 19, 19, 19, 19, 19, 19, 19, 19, 19, 19, 19, 19, 19, 19, 19, 19, 19, 19, 19, 20, 21, 22, 1, 23, 1, 18, 18, 18, 24, 25, 18, 19, 19, 26, 19, 19, 19, 27, 19, 19, 28, 19, 29, 19, 30, 19, 31, 19, 32, 19, 19, 33, 1, 34, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1 } ; static yy_state_type yy_last_accepting_state; static char *yy_last_accepting_cpos; extern int yy_flex_debug; int yy_flex_debug = 0; /* The intent behind this definition is that it'll catch * any uses of REJECT which flex missed. */ #define REJECT reject_used_but_not_detected #define yymore() yymore_used_but_not_detected #define YY_MORE_ADJ 0 #define YY_RESTORE_YY_MORE_OFFSET char *yytext; #line 1 "genpr-scan.l" /******************************** -*- C -*- **************************** * * GNU Smalltalk genprims tool - lexical analyzer * ***********************************************************************/ /*********************************************************************** * * Copyright 2002, 2006 Free Software Foundation, Inc. * Written by Paolo Bonzini. * * This file is part of GNU Smalltalk. * * GNU Smalltalk is free software; you can redistribute it and/or modify it * under the terms of the GNU General Public License as published by the Free * Software Foundation; either version 2, or (at your option) any later * version. * * Linking GNU Smalltalk statically or dynamically with other modules is * making a combined work based on GNU Smalltalk. Thus, the terms and * conditions of the GNU General Public License cover the whole * combination. * * In addition, as a special exception, the Free Software Foundation * give you permission to combine GNU Smalltalk with free software * programs or libraries that are released under the GNU LGPL and with * independent programs running under the GNU Smalltalk virtual machine. * * You may copy and distribute such a system following the terms of the * GNU GPL for GNU Smalltalk and the licenses of the other code * concerned, provided that you include the source code of that other * code when and as the GNU GPL requires distribution of source code. * * Note that people who make modified versions of GNU Smalltalk are not * obligated to grant this special exception for their modified * versions; it is their choice whether to do so. The GNU General * Public License gives permission to release a modified version without * this exception; this exception also makes it possible to release a * modified version which carries forward this exception. * * GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or * FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for * more details. * * You should have received a copy of the GNU General Public License along with * GNU Smalltalk; see the file COPYING. If not, write to the Free Software * Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * ***********************************************************************/ #line 63 "genpr-scan.l" #include "genprims.h" #include "genpr-parse.h" static int from = 0, depth = 0; #if !defined YY_FLEX_SUBMINOR_VERSION || YY_FLEX_SUBMINOR_VERSION < 31 int yylineno = 1; #endif /* This file implements a bit more than a lexical analyzer: it also writes literal tokens to the output until a reserved word is found. This is done by this macro which decides whether to return the token to yyparse and whether to append it to a filament (these two things are not mutually exclusive, because braces are both written and returned, for example). Note that whitespace should be written to the literal_fil filament, but not returned to yyparse when there is no active literal_fil. Also note that the ifs are resolved at compile time. */ #define IS_TOKEN(tok) \ do { \ if (literal_fil) \ { \ if (tok != PRIMITIVE && tok != PRIM_ID) \ filcat (literal_fil, yytext); \ else \ literal_fil = NULL; \ if (tok == PRIMITIVE || tok == PRIM_ID || tok == '{' || tok == '}') \ return tok; \ } \ else \ { \ if (tok == '{') \ literal_fil = stmt_fil; \ if (tok != WSPACE) \ return tok; \ } \ } while(0) #line 1280 "genpr-scan.c" #define INITIAL 0 #define C_COMMENT 1 #define C_CHAR 2 #define C_STRING 3 #define CPP_CODE 4 #define C_CODE 5 #ifndef YY_NO_UNISTD_H /* Special case for "unistd.h", since it is non-ANSI. We include it way * down here because we want the user's section 1 to have been scanned first. * The user has a chance to override it with an option. */ #include #endif #ifndef YY_EXTRA_TYPE #define YY_EXTRA_TYPE void * #endif static int yy_init_globals (void ); /* Accessor methods to globals. These are made visible to non-reentrant scanners for convenience. */ int yylex_destroy (void ); int yyget_debug (void ); void yyset_debug (int debug_flag ); YY_EXTRA_TYPE yyget_extra (void ); void yyset_extra (YY_EXTRA_TYPE user_defined ); FILE *yyget_in (void ); void yyset_in (FILE * in_str ); FILE *yyget_out (void ); void yyset_out (FILE * out_str ); int yyget_leng (void ); char *yyget_text (void ); int yyget_lineno (void ); void yyset_lineno (int line_number ); /* Macros after this point can all be overridden by user definitions in * section 1. */ #ifndef YY_SKIP_YYWRAP #ifdef __cplusplus extern "C" int yywrap (void ); #else extern int yywrap (void ); #endif #endif #ifndef yytext_ptr static void yy_flex_strncpy (char *,yyconst char *,int ); #endif #ifdef YY_NEED_STRLEN static int yy_flex_strlen (yyconst char * ); #endif #ifndef YY_NO_INPUT #ifdef __cplusplus static int yyinput (void ); #else static int input (void ); #endif #endif /* Amount of stuff to slurp up with each read. */ #ifndef YY_READ_BUF_SIZE #ifdef __ia64__ /* On IA-64, the buffer size is 16k, not 8k */ #define YY_READ_BUF_SIZE 16384 #else #define YY_READ_BUF_SIZE 8192 #endif /* __ia64__ */ #endif /* Copy whatever the last rule matched to the standard output. */ #ifndef ECHO /* This used to be an fputs(), but since the string might contain NUL's, * we now use fwrite(). */ #define ECHO do { if (fwrite( yytext, yyleng, 1, yyout )) {} } while (0) #endif /* Gets input and stuffs it into "buf". number of characters read, or YY_NULL, * is returned in "result". */ #ifndef YY_INPUT #define YY_INPUT(buf,result,max_size) \ if ( YY_CURRENT_BUFFER_LVALUE->yy_is_interactive ) \ { \ int c = '*'; \ size_t n; \ for ( n = 0; n < max_size && \ (c = getc( yyin )) != EOF && c != '\n'; ++n ) \ buf[n] = (char) c; \ if ( c == '\n' ) \ buf[n++] = (char) c; \ if ( c == EOF && ferror( yyin ) ) \ YY_FATAL_ERROR( "input in flex scanner failed" ); \ result = n; \ } \ else \ { \ errno=0; \ while ( (result = fread(buf, 1, max_size, yyin))==0 && ferror(yyin)) \ { \ if( errno != EINTR) \ { \ YY_FATAL_ERROR( "input in flex scanner failed" ); \ break; \ } \ errno=0; \ clearerr(yyin); \ } \ }\ \ #endif /* No semi-colon after return; correct usage is to write "yyterminate();" - * we don't want an extra ';' after the "return" because that will cause * some compilers to complain about unreachable statements. */ #ifndef yyterminate #define yyterminate() return YY_NULL #endif /* Number of entries by which start-condition stack grows. */ #ifndef YY_START_STACK_INCR #define YY_START_STACK_INCR 25 #endif /* Report a fatal error. */ #ifndef YY_FATAL_ERROR #define YY_FATAL_ERROR(msg) yy_fatal_error( msg ) #endif /* end tables serialization structures and prototypes */ /* Default declaration of generated scanner - a define so the user can * easily add parameters. */ #ifndef YY_DECL #define YY_DECL_IS_OURS 1 extern int yylex (void); #define YY_DECL int yylex (void) #endif /* !YY_DECL */ /* Code executed at the beginning of each rule, after yytext and yyleng * have been set up. */ #ifndef YY_USER_ACTION #define YY_USER_ACTION #endif /* Code executed at the end of each rule. */ #ifndef YY_BREAK #define YY_BREAK break; #endif #define YY_RULE_SETUP \ if ( yyleng > 0 ) \ YY_CURRENT_BUFFER_LVALUE->yy_at_bol = \ (yytext[yyleng - 1] == '\n'); \ YY_USER_ACTION /** The main scanner function which does all the work. */ YY_DECL { register yy_state_type yy_current_state; register char *yy_cp, *yy_bp; register int yy_act; #line 101 "genpr-scan.l" #line 1476 "genpr-scan.c" if ( !(yy_init) ) { (yy_init) = 1; #ifdef YY_USER_INIT YY_USER_INIT; #endif if ( ! (yy_start) ) (yy_start) = 1; /* first start state */ if ( ! yyin ) yyin = stdin; if ( ! yyout ) yyout = stdout; if ( ! YY_CURRENT_BUFFER ) { yyensure_buffer_stack (); YY_CURRENT_BUFFER_LVALUE = yy_create_buffer(yyin,YY_BUF_SIZE ); } yy_load_buffer_state( ); } while ( 1 ) /* loops until end-of-file is reached */ { yy_cp = (yy_c_buf_p); /* Support of yytext. */ *yy_cp = (yy_hold_char); /* yy_bp points to the position in yy_ch_buf of the start of * the current run. */ yy_bp = yy_cp; yy_current_state = (yy_start); yy_current_state += YY_AT_BOL(); yy_match: while ( (yy_current_state = yy_nxt[yy_current_state][ yy_ec[YY_SC_TO_UI(*yy_cp)] ]) > 0 ) { if ( yy_accept[yy_current_state] ) { (yy_last_accepting_state) = yy_current_state; (yy_last_accepting_cpos) = yy_cp; } ++yy_cp; } yy_current_state = -yy_current_state; yy_find_action: yy_act = yy_accept[yy_current_state]; YY_DO_BEFORE_ACTION; do_action: /* This label is used only to access EOF actions. */ switch ( yy_act ) { /* beginning of action switch */ case 0: /* must back up */ /* undo the effects of YY_DO_BEFORE_ACTION */ *yy_cp = (yy_hold_char); yy_cp = (yy_last_accepting_cpos) + 1; yy_current_state = (yy_last_accepting_state); goto yy_find_action; case 1: /* rule 1 can match eol */ YY_RULE_SETUP #line 104 "genpr-scan.l" { yylval.text = yytext; yylineno += yyleng; IS_TOKEN (WSPACE); } YY_BREAK case 2: YY_RULE_SETUP #line 109 "genpr-scan.l" { yylval.text = yytext; IS_TOKEN (WSPACE); } YY_BREAK case 3: YY_RULE_SETUP #line 117 "genpr-scan.l" { yylval.text = yytext; IS_TOKEN (PRIMITIVE); } YY_BREAK case 4: YY_RULE_SETUP #line 122 "genpr-scan.l" { yylval.text = yytext; IS_TOKEN ('['); } YY_BREAK case 5: YY_RULE_SETUP #line 127 "genpr-scan.l" { yylval.text = yytext; IS_TOKEN (']'); } YY_BREAK case 6: YY_RULE_SETUP #line 132 "genpr-scan.l" { yylval.text = yytext; IS_TOKEN (','); } YY_BREAK case 7: YY_RULE_SETUP #line 137 "genpr-scan.l" { yylval.text = yytext; IS_TOKEN ('='); } YY_BREAK case 8: YY_RULE_SETUP #line 142 "genpr-scan.l" { yylval.text = yytext; IS_TOKEN (':'); } YY_BREAK case 9: YY_RULE_SETUP #line 147 "genpr-scan.l" { yylval.text = yytext; depth = 1; BEGIN (C_CODE); IS_TOKEN ('{'); } YY_BREAK case 10: YY_RULE_SETUP #line 157 "genpr-scan.l" { yylval.text = yytext; from = YY_START; BEGIN (C_CHAR); IS_TOKEN (LITERAL); } YY_BREAK case 11: YY_RULE_SETUP #line 164 "genpr-scan.l" { yylval.text = yytext; from = YY_START; BEGIN (C_STRING); IS_TOKEN (LITERAL); } YY_BREAK case 12: YY_RULE_SETUP #line 171 "genpr-scan.l" { yylval.text = yytext; from = YY_START; BEGIN (C_COMMENT); IS_TOKEN (WSPACE); } YY_BREAK case 13: YY_RULE_SETUP #line 179 "genpr-scan.l" { yylval.text = yytext; from = YY_START; BEGIN (CPP_CODE); IS_TOKEN (LITERAL); } YY_BREAK case 14: YY_RULE_SETUP #line 186 "genpr-scan.l" { yylval.text = yytext; IS_TOKEN ('('); } YY_BREAK case 15: YY_RULE_SETUP #line 191 "genpr-scan.l" { yylval.text = yytext; IS_TOKEN (')'); } YY_BREAK case 16: YY_RULE_SETUP #line 196 "genpr-scan.l" { yylval.text = yytext; IS_TOKEN (PRIM_ID); } YY_BREAK case 17: #line 202 "genpr-scan.l" case 18: #line 203 "genpr-scan.l" case 19: YY_RULE_SETUP #line 203 "genpr-scan.l" { yylval.text = yytext; IS_TOKEN (NUMBER); } YY_BREAK case 20: YY_RULE_SETUP #line 208 "genpr-scan.l" { yylval.text = yytext; IS_TOKEN (ID); } YY_BREAK case 21: YY_RULE_SETUP #line 216 "genpr-scan.l" { yylval.text = yytext; depth++; IS_TOKEN (LITERAL); } YY_BREAK case 22: YY_RULE_SETUP #line 222 "genpr-scan.l" { yylval.text = yytext; if (--depth) IS_TOKEN (LITERAL); else { BEGIN (INITIAL); IS_TOKEN ('}'); } } YY_BREAK case 23: YY_RULE_SETUP #line 233 "genpr-scan.l" { yylval.text = yytext; IS_TOKEN (LITERAL); } YY_BREAK case 24: /* rule 24 can match eol */ YY_RULE_SETUP #line 241 "genpr-scan.l" { yylval.text = yytext; yylineno++; IS_TOKEN (WSPACE); } YY_BREAK case 25: /* rule 25 can match eol */ YY_RULE_SETUP #line 247 "genpr-scan.l" { yylval.text = yytext; IS_TOKEN (WSPACE); } YY_BREAK case 26: YY_RULE_SETUP #line 252 "genpr-scan.l" { yylval.text = yytext; BEGIN (from); IS_TOKEN (WSPACE); } YY_BREAK case 27: YY_RULE_SETUP #line 261 "genpr-scan.l" { yylval.text = yytext; BEGIN (from); IS_TOKEN (LITERAL); } YY_BREAK case 28: YY_RULE_SETUP #line 269 "genpr-scan.l" { yylval.text = yytext; BEGIN (from); IS_TOKEN (LITERAL); } YY_BREAK case 29: YY_RULE_SETUP #line 277 "genpr-scan.l" { yylineno += (yytext[1] == '\n'); yylval.text = yytext; IS_TOKEN (LITERAL); } YY_BREAK case 30: YY_RULE_SETUP #line 283 "genpr-scan.l" { yylineno += (yytext[0] == '\n'); yylval.text = yytext; IS_TOKEN (LITERAL); } YY_BREAK case 31: *yy_cp = (yy_hold_char); /* undo effects of setting up yytext */ (yy_c_buf_p) = yy_cp -= 1; YY_DO_BEFORE_ACTION; /* set up yytext again */ YY_RULE_SETUP #line 291 "genpr-scan.l" { yylval.text = yytext; IS_TOKEN (LITERAL); } YY_BREAK case 32: *yy_cp = (yy_hold_char); /* undo effects of setting up yytext */ (yy_c_buf_p) = yy_cp -= 1; YY_DO_BEFORE_ACTION; /* set up yytext again */ YY_RULE_SETUP #line 296 "genpr-scan.l" { yylval.text = yytext; BEGIN (from); IS_TOKEN (LITERAL); } YY_BREAK case 33: YY_RULE_SETUP #line 303 "genpr-scan.l" ECHO; YY_BREAK #line 1849 "genpr-scan.c" case YY_STATE_EOF(INITIAL): case YY_STATE_EOF(C_COMMENT): case YY_STATE_EOF(C_CHAR): case YY_STATE_EOF(C_STRING): case YY_STATE_EOF(CPP_CODE): case YY_STATE_EOF(C_CODE): yyterminate(); case YY_END_OF_BUFFER: { /* Amount of text matched not including the EOB char. */ int yy_amount_of_matched_text = (int) (yy_cp - (yytext_ptr)) - 1; /* Undo the effects of YY_DO_BEFORE_ACTION. */ *yy_cp = (yy_hold_char); YY_RESTORE_YY_MORE_OFFSET if ( YY_CURRENT_BUFFER_LVALUE->yy_buffer_status == YY_BUFFER_NEW ) { /* We're scanning a new file or input source. It's * possible that this happened because the user * just pointed yyin at a new source and called * yylex(). If so, then we have to assure * consistency between YY_CURRENT_BUFFER and our * globals. Here is the right place to do so, because * this is the first action (other than possibly a * back-up) that will match for the new input source. */ (yy_n_chars) = YY_CURRENT_BUFFER_LVALUE->yy_n_chars; YY_CURRENT_BUFFER_LVALUE->yy_input_file = yyin; YY_CURRENT_BUFFER_LVALUE->yy_buffer_status = YY_BUFFER_NORMAL; } /* Note that here we test for yy_c_buf_p "<=" to the position * of the first EOB in the buffer, since yy_c_buf_p will * already have been incremented past the NUL character * (since all states make transitions on EOB to the * end-of-buffer state). Contrast this with the test * in input(). */ if ( (yy_c_buf_p) <= &YY_CURRENT_BUFFER_LVALUE->yy_ch_buf[(yy_n_chars)] ) { /* This was really a NUL. */ yy_state_type yy_next_state; (yy_c_buf_p) = (yytext_ptr) + yy_amount_of_matched_text; yy_current_state = yy_get_previous_state( ); /* Okay, we're now positioned to make the NUL * transition. We couldn't have * yy_get_previous_state() go ahead and do it * for us because it doesn't know how to deal * with the possibility of jamming (and we don't * want to build jamming into it because then it * will run more slowly). */ yy_next_state = yy_try_NUL_trans( yy_current_state ); yy_bp = (yytext_ptr) + YY_MORE_ADJ; if ( yy_next_state ) { /* Consume the NUL. */ yy_cp = ++(yy_c_buf_p); yy_current_state = yy_next_state; goto yy_match; } else { yy_cp = (yy_c_buf_p); goto yy_find_action; } } else switch ( yy_get_next_buffer( ) ) { case EOB_ACT_END_OF_FILE: { (yy_did_buffer_switch_on_eof) = 0; if ( yywrap( ) ) { /* Note: because we've taken care in * yy_get_next_buffer() to have set up * yytext, we can now set up * yy_c_buf_p so that if some total * hoser (like flex itself) wants to * call the scanner after we return the * YY_NULL, it'll still work - another * YY_NULL will get returned. */ (yy_c_buf_p) = (yytext_ptr) + YY_MORE_ADJ; yy_act = YY_STATE_EOF(YY_START); goto do_action; } else { if ( ! (yy_did_buffer_switch_on_eof) ) YY_NEW_FILE; } break; } case EOB_ACT_CONTINUE_SCAN: (yy_c_buf_p) = (yytext_ptr) + yy_amount_of_matched_text; yy_current_state = yy_get_previous_state( ); yy_cp = (yy_c_buf_p); yy_bp = (yytext_ptr) + YY_MORE_ADJ; goto yy_match; case EOB_ACT_LAST_MATCH: (yy_c_buf_p) = &YY_CURRENT_BUFFER_LVALUE->yy_ch_buf[(yy_n_chars)]; yy_current_state = yy_get_previous_state( ); yy_cp = (yy_c_buf_p); yy_bp = (yytext_ptr) + YY_MORE_ADJ; goto yy_find_action; } break; } default: YY_FATAL_ERROR( "fatal flex scanner internal error--no action found" ); } /* end of action switch */ } /* end of scanning one token */ } /* end of yylex */ /* yy_get_next_buffer - try to read in a new buffer * * Returns a code representing an action: * EOB_ACT_LAST_MATCH - * EOB_ACT_CONTINUE_SCAN - continue scanning from current position * EOB_ACT_END_OF_FILE - end of file */ static int yy_get_next_buffer (void) { register char *dest = YY_CURRENT_BUFFER_LVALUE->yy_ch_buf; register char *source = (yytext_ptr); register int number_to_move, i; int ret_val; if ( (yy_c_buf_p) > &YY_CURRENT_BUFFER_LVALUE->yy_ch_buf[(yy_n_chars) + 1] ) YY_FATAL_ERROR( "fatal flex scanner internal error--end of buffer missed" ); if ( YY_CURRENT_BUFFER_LVALUE->yy_fill_buffer == 0 ) { /* Don't try to fill the buffer, so this is an EOF. */ if ( (yy_c_buf_p) - (yytext_ptr) - YY_MORE_ADJ == 1 ) { /* We matched a single character, the EOB, so * treat this as a final EOF. */ return EOB_ACT_END_OF_FILE; } else { /* We matched some text prior to the EOB, first * process it. */ return EOB_ACT_LAST_MATCH; } } /* Try to read more data. */ /* First move last chars to start of buffer. */ number_to_move = (int) ((yy_c_buf_p) - (yytext_ptr)) - 1; for ( i = 0; i < number_to_move; ++i ) *(dest++) = *(source++); if ( YY_CURRENT_BUFFER_LVALUE->yy_buffer_status == YY_BUFFER_EOF_PENDING ) /* don't do the read, it's not guaranteed to return an EOF, * just force an EOF */ YY_CURRENT_BUFFER_LVALUE->yy_n_chars = (yy_n_chars) = 0; else { int num_to_read = YY_CURRENT_BUFFER_LVALUE->yy_buf_size - number_to_move - 1; while ( num_to_read <= 0 ) { /* Not enough room in the buffer - grow it. */ /* just a shorter name for the current buffer */ YY_BUFFER_STATE b = YY_CURRENT_BUFFER; int yy_c_buf_p_offset = (int) ((yy_c_buf_p) - b->yy_ch_buf); if ( b->yy_is_our_buffer ) { int new_size = b->yy_buf_size * 2; if ( new_size <= 0 ) b->yy_buf_size += b->yy_buf_size / 8; else b->yy_buf_size *= 2; b->yy_ch_buf = (char *) /* Include room in for 2 EOB chars. */ yyrealloc((void *) b->yy_ch_buf,b->yy_buf_size + 2 ); } else /* Can't grow it, we don't own it. */ b->yy_ch_buf = 0; if ( ! b->yy_ch_buf ) YY_FATAL_ERROR( "fatal error - scanner input buffer overflow" ); (yy_c_buf_p) = &b->yy_ch_buf[yy_c_buf_p_offset]; num_to_read = YY_CURRENT_BUFFER_LVALUE->yy_buf_size - number_to_move - 1; } if ( num_to_read > YY_READ_BUF_SIZE ) num_to_read = YY_READ_BUF_SIZE; /* Read in more data. */ YY_INPUT( (&YY_CURRENT_BUFFER_LVALUE->yy_ch_buf[number_to_move]), (yy_n_chars), (size_t) num_to_read ); YY_CURRENT_BUFFER_LVALUE->yy_n_chars = (yy_n_chars); } if ( (yy_n_chars) == 0 ) { if ( number_to_move == YY_MORE_ADJ ) { ret_val = EOB_ACT_END_OF_FILE; yyrestart(yyin ); } else { ret_val = EOB_ACT_LAST_MATCH; YY_CURRENT_BUFFER_LVALUE->yy_buffer_status = YY_BUFFER_EOF_PENDING; } } else ret_val = EOB_ACT_CONTINUE_SCAN; if ((yy_size_t) ((yy_n_chars) + number_to_move) > YY_CURRENT_BUFFER_LVALUE->yy_buf_size) { /* Extend the array by 50%, plus the number we really need. */ yy_size_t new_size = (yy_n_chars) + number_to_move + ((yy_n_chars) >> 1); YY_CURRENT_BUFFER_LVALUE->yy_ch_buf = (char *) yyrealloc((void *) YY_CURRENT_BUFFER_LVALUE->yy_ch_buf,new_size ); if ( ! YY_CURRENT_BUFFER_LVALUE->yy_ch_buf ) YY_FATAL_ERROR( "out of dynamic memory in yy_get_next_buffer()" ); } (yy_n_chars) += number_to_move; YY_CURRENT_BUFFER_LVALUE->yy_ch_buf[(yy_n_chars)] = YY_END_OF_BUFFER_CHAR; YY_CURRENT_BUFFER_LVALUE->yy_ch_buf[(yy_n_chars) + 1] = YY_END_OF_BUFFER_CHAR; (yytext_ptr) = &YY_CURRENT_BUFFER_LVALUE->yy_ch_buf[0]; return ret_val; } /* yy_get_previous_state - get the state just before the EOB char was reached */ static yy_state_type yy_get_previous_state (void) { register yy_state_type yy_current_state; register char *yy_cp; yy_current_state = (yy_start); yy_current_state += YY_AT_BOL(); for ( yy_cp = (yytext_ptr) + YY_MORE_ADJ; yy_cp < (yy_c_buf_p); ++yy_cp ) { yy_current_state = yy_nxt[yy_current_state][(*yy_cp ? yy_ec[YY_SC_TO_UI(*yy_cp)] : 1)]; if ( yy_accept[yy_current_state] ) { (yy_last_accepting_state) = yy_current_state; (yy_last_accepting_cpos) = yy_cp; } } return yy_current_state; } /* yy_try_NUL_trans - try to make a transition on the NUL character * * synopsis * next_state = yy_try_NUL_trans( current_state ); */ static yy_state_type yy_try_NUL_trans (yy_state_type yy_current_state ) { register int yy_is_jam; register char *yy_cp = (yy_c_buf_p); yy_current_state = yy_nxt[yy_current_state][1]; yy_is_jam = (yy_current_state <= 0); if ( ! yy_is_jam ) { if ( yy_accept[yy_current_state] ) { (yy_last_accepting_state) = yy_current_state; (yy_last_accepting_cpos) = yy_cp; } } return yy_is_jam ? 0 : yy_current_state; } #ifndef YY_NO_INPUT #ifdef __cplusplus static int yyinput (void) #else static int input (void) #endif { int c; *(yy_c_buf_p) = (yy_hold_char); if ( *(yy_c_buf_p) == YY_END_OF_BUFFER_CHAR ) { /* yy_c_buf_p now points to the character we want to return. * If this occurs *before* the EOB characters, then it's a * valid NUL; if not, then we've hit the end of the buffer. */ if ( (yy_c_buf_p) < &YY_CURRENT_BUFFER_LVALUE->yy_ch_buf[(yy_n_chars)] ) /* This was really a NUL. */ *(yy_c_buf_p) = '\0'; else { /* need more input */ int offset = (yy_c_buf_p) - (yytext_ptr); ++(yy_c_buf_p); switch ( yy_get_next_buffer( ) ) { case EOB_ACT_LAST_MATCH: /* This happens because yy_g_n_b() * sees that we've accumulated a * token and flags that we need to * try matching the token before * proceeding. But for input(), * there's no matching to consider. * So convert the EOB_ACT_LAST_MATCH * to EOB_ACT_END_OF_FILE. */ /* Reset buffer status. */ yyrestart(yyin ); /*FALLTHROUGH*/ case EOB_ACT_END_OF_FILE: { if ( yywrap( ) ) return EOF; if ( ! (yy_did_buffer_switch_on_eof) ) YY_NEW_FILE; #ifdef __cplusplus return yyinput(); #else return input(); #endif } case EOB_ACT_CONTINUE_SCAN: (yy_c_buf_p) = (yytext_ptr) + offset; break; } } } c = *(unsigned char *) (yy_c_buf_p); /* cast for 8-bit char's */ *(yy_c_buf_p) = '\0'; /* preserve yytext */ (yy_hold_char) = *++(yy_c_buf_p); YY_CURRENT_BUFFER_LVALUE->yy_at_bol = (c == '\n'); return c; } #endif /* ifndef YY_NO_INPUT */ /** Immediately switch to a different input stream. * @param input_file A readable stream. * * @note This function does not reset the start condition to @c INITIAL . */ void yyrestart (FILE * input_file ) { if ( ! YY_CURRENT_BUFFER ){ yyensure_buffer_stack (); YY_CURRENT_BUFFER_LVALUE = yy_create_buffer(yyin,YY_BUF_SIZE ); } yy_init_buffer(YY_CURRENT_BUFFER,input_file ); yy_load_buffer_state( ); } /** Switch to a different input buffer. * @param new_buffer The new input buffer. * */ void yy_switch_to_buffer (YY_BUFFER_STATE new_buffer ) { /* TODO. We should be able to replace this entire function body * with * yypop_buffer_state(); * yypush_buffer_state(new_buffer); */ yyensure_buffer_stack (); if ( YY_CURRENT_BUFFER == new_buffer ) return; if ( YY_CURRENT_BUFFER ) { /* Flush out information for old buffer. */ *(yy_c_buf_p) = (yy_hold_char); YY_CURRENT_BUFFER_LVALUE->yy_buf_pos = (yy_c_buf_p); YY_CURRENT_BUFFER_LVALUE->yy_n_chars = (yy_n_chars); } YY_CURRENT_BUFFER_LVALUE = new_buffer; yy_load_buffer_state( ); /* We don't actually know whether we did this switch during * EOF (yywrap()) processing, but the only time this flag * is looked at is after yywrap() is called, so it's safe * to go ahead and always set it. */ (yy_did_buffer_switch_on_eof) = 1; } static void yy_load_buffer_state (void) { (yy_n_chars) = YY_CURRENT_BUFFER_LVALUE->yy_n_chars; (yytext_ptr) = (yy_c_buf_p) = YY_CURRENT_BUFFER_LVALUE->yy_buf_pos; yyin = YY_CURRENT_BUFFER_LVALUE->yy_input_file; (yy_hold_char) = *(yy_c_buf_p); } /** Allocate and initialize an input buffer state. * @param file A readable stream. * @param size The character buffer size in bytes. When in doubt, use @c YY_BUF_SIZE. * * @return the allocated buffer state. */ YY_BUFFER_STATE yy_create_buffer (FILE * file, int size ) { YY_BUFFER_STATE b; b = (YY_BUFFER_STATE) yyalloc(sizeof( struct yy_buffer_state ) ); if ( ! b ) YY_FATAL_ERROR( "out of dynamic memory in yy_create_buffer()" ); b->yy_buf_size = size; /* yy_ch_buf has to be 2 characters longer than the size given because * we need to put in 2 end-of-buffer characters. */ b->yy_ch_buf = (char *) yyalloc(b->yy_buf_size + 2 ); if ( ! b->yy_ch_buf ) YY_FATAL_ERROR( "out of dynamic memory in yy_create_buffer()" ); b->yy_is_our_buffer = 1; yy_init_buffer(b,file ); return b; } /** Destroy the buffer. * @param b a buffer created with yy_create_buffer() * */ void yy_delete_buffer (YY_BUFFER_STATE b ) { if ( ! b ) return; if ( b == YY_CURRENT_BUFFER ) /* Not sure if we should pop here. */ YY_CURRENT_BUFFER_LVALUE = (YY_BUFFER_STATE) 0; if ( b->yy_is_our_buffer ) yyfree((void *) b->yy_ch_buf ); yyfree((void *) b ); } /* Initializes or reinitializes a buffer. * This function is sometimes called more than once on the same buffer, * such as during a yyrestart() or at EOF. */ static void yy_init_buffer (YY_BUFFER_STATE b, FILE * file ) { int oerrno = errno; yy_flush_buffer(b ); b->yy_input_file = file; b->yy_fill_buffer = 1; /* If b is the current buffer, then yy_init_buffer was _probably_ * called from yyrestart() or through yy_get_next_buffer. * In that case, we don't want to reset the lineno or column. */ if (b != YY_CURRENT_BUFFER){ b->yy_bs_lineno = 1; b->yy_bs_column = 0; } b->yy_is_interactive = 0; errno = oerrno; } /** Discard all buffered characters. On the next scan, YY_INPUT will be called. * @param b the buffer state to be flushed, usually @c YY_CURRENT_BUFFER. * */ void yy_flush_buffer (YY_BUFFER_STATE b ) { if ( ! b ) return; b->yy_n_chars = 0; /* We always need two end-of-buffer characters. The first causes * a transition to the end-of-buffer state. The second causes * a jam in that state. */ b->yy_ch_buf[0] = YY_END_OF_BUFFER_CHAR; b->yy_ch_buf[1] = YY_END_OF_BUFFER_CHAR; b->yy_buf_pos = &b->yy_ch_buf[0]; b->yy_at_bol = 1; b->yy_buffer_status = YY_BUFFER_NEW; if ( b == YY_CURRENT_BUFFER ) yy_load_buffer_state( ); } /** Pushes the new state onto the stack. The new state becomes * the current state. This function will allocate the stack * if necessary. * @param new_buffer The new state. * */ void yypush_buffer_state (YY_BUFFER_STATE new_buffer ) { if (new_buffer == NULL) return; yyensure_buffer_stack(); /* This block is copied from yy_switch_to_buffer. */ if ( YY_CURRENT_BUFFER ) { /* Flush out information for old buffer. */ *(yy_c_buf_p) = (yy_hold_char); YY_CURRENT_BUFFER_LVALUE->yy_buf_pos = (yy_c_buf_p); YY_CURRENT_BUFFER_LVALUE->yy_n_chars = (yy_n_chars); } /* Only push if top exists. Otherwise, replace top. */ if (YY_CURRENT_BUFFER) (yy_buffer_stack_top)++; YY_CURRENT_BUFFER_LVALUE = new_buffer; /* copied from yy_switch_to_buffer. */ yy_load_buffer_state( ); (yy_did_buffer_switch_on_eof) = 1; } /** Removes and deletes the top of the stack, if present. * The next element becomes the new top. * */ void yypop_buffer_state (void) { if (!YY_CURRENT_BUFFER) return; yy_delete_buffer(YY_CURRENT_BUFFER ); YY_CURRENT_BUFFER_LVALUE = NULL; if ((yy_buffer_stack_top) > 0) --(yy_buffer_stack_top); if (YY_CURRENT_BUFFER) { yy_load_buffer_state( ); (yy_did_buffer_switch_on_eof) = 1; } } /* Allocates the stack if it does not exist. * Guarantees space for at least one push. */ static void yyensure_buffer_stack (void) { int num_to_alloc; if (!(yy_buffer_stack)) { /* First allocation is just for 2 elements, since we don't know if this * scanner will even need a stack. We use 2 instead of 1 to avoid an * immediate realloc on the next call. */ num_to_alloc = 1; (yy_buffer_stack) = (struct yy_buffer_state**)yyalloc (num_to_alloc * sizeof(struct yy_buffer_state*) ); if ( ! (yy_buffer_stack) ) YY_FATAL_ERROR( "out of dynamic memory in yyensure_buffer_stack()" ); memset((yy_buffer_stack), 0, num_to_alloc * sizeof(struct yy_buffer_state*)); (yy_buffer_stack_max) = num_to_alloc; (yy_buffer_stack_top) = 0; return; } if ((yy_buffer_stack_top) >= ((yy_buffer_stack_max)) - 1){ /* Increase the buffer to prepare for a possible push. */ int grow_size = 8 /* arbitrary grow size */; num_to_alloc = (yy_buffer_stack_max) + grow_size; (yy_buffer_stack) = (struct yy_buffer_state**)yyrealloc ((yy_buffer_stack), num_to_alloc * sizeof(struct yy_buffer_state*) ); if ( ! (yy_buffer_stack) ) YY_FATAL_ERROR( "out of dynamic memory in yyensure_buffer_stack()" ); /* zero only the new slots.*/ memset((yy_buffer_stack) + (yy_buffer_stack_max), 0, grow_size * sizeof(struct yy_buffer_state*)); (yy_buffer_stack_max) = num_to_alloc; } } /** Setup the input buffer state to scan directly from a user-specified character buffer. * @param base the character buffer * @param size the size in bytes of the character buffer * * @return the newly allocated buffer state object. */ YY_BUFFER_STATE yy_scan_buffer (char * base, yy_size_t size ) { YY_BUFFER_STATE b; if ( size < 2 || base[size-2] != YY_END_OF_BUFFER_CHAR || base[size-1] != YY_END_OF_BUFFER_CHAR ) /* They forgot to leave room for the EOB's. */ return 0; b = (YY_BUFFER_STATE) yyalloc(sizeof( struct yy_buffer_state ) ); if ( ! b ) YY_FATAL_ERROR( "out of dynamic memory in yy_scan_buffer()" ); b->yy_buf_size = size - 2; /* "- 2" to take care of EOB's */ b->yy_buf_pos = b->yy_ch_buf = base; b->yy_is_our_buffer = 0; b->yy_input_file = 0; b->yy_n_chars = b->yy_buf_size; b->yy_is_interactive = 0; b->yy_at_bol = 1; b->yy_fill_buffer = 0; b->yy_buffer_status = YY_BUFFER_NEW; yy_switch_to_buffer(b ); return b; } /** Setup the input buffer state to scan a string. The next call to yylex() will * scan from a @e copy of @a str. * @param yystr a NUL-terminated string to scan * * @return the newly allocated buffer state object. * @note If you want to scan bytes that may contain NUL values, then use * yy_scan_bytes() instead. */ YY_BUFFER_STATE yy_scan_string (yyconst char * yystr ) { return yy_scan_bytes(yystr,strlen(yystr) ); } /** Setup the input buffer state to scan the given bytes. The next call to yylex() will * scan from a @e copy of @a bytes. * @param yybytes the byte buffer to scan * @param _yybytes_len the number of bytes in the buffer pointed to by @a bytes. * * @return the newly allocated buffer state object. */ YY_BUFFER_STATE yy_scan_bytes (yyconst char * yybytes, int _yybytes_len ) { YY_BUFFER_STATE b; char *buf; yy_size_t n; int i; /* Get memory for full buffer, including space for trailing EOB's. */ n = _yybytes_len + 2; buf = (char *) yyalloc(n ); if ( ! buf ) YY_FATAL_ERROR( "out of dynamic memory in yy_scan_bytes()" ); for ( i = 0; i < _yybytes_len; ++i ) buf[i] = yybytes[i]; buf[_yybytes_len] = buf[_yybytes_len+1] = YY_END_OF_BUFFER_CHAR; b = yy_scan_buffer(buf,n ); if ( ! b ) YY_FATAL_ERROR( "bad buffer in yy_scan_bytes()" ); /* It's okay to grow etc. this buffer, and we should throw it * away when we're done. */ b->yy_is_our_buffer = 1; return b; } #ifndef YY_EXIT_FAILURE #define YY_EXIT_FAILURE 2 #endif static void yy_fatal_error (yyconst char* msg ) { (void) fprintf( stderr, "%s\n", msg ); exit( YY_EXIT_FAILURE ); } /* Redefine yyless() so it works in section 3 code. */ #undef yyless #define yyless(n) \ do \ { \ /* Undo effects of setting up yytext. */ \ int yyless_macro_arg = (n); \ YY_LESS_LINENO(yyless_macro_arg);\ yytext[yyleng] = (yy_hold_char); \ (yy_c_buf_p) = yytext + yyless_macro_arg; \ (yy_hold_char) = *(yy_c_buf_p); \ *(yy_c_buf_p) = '\0'; \ yyleng = yyless_macro_arg; \ } \ while ( 0 ) /* Accessor methods (get/set functions) to struct members. */ /** Get the current line number. * */ int yyget_lineno (void) { return yylineno; } /** Get the input stream. * */ FILE *yyget_in (void) { return yyin; } /** Get the output stream. * */ FILE *yyget_out (void) { return yyout; } /** Get the length of the current token. * */ int yyget_leng (void) { return yyleng; } /** Get the current token. * */ char *yyget_text (void) { return yytext; } /** Set the current line number. * @param line_number * */ void yyset_lineno (int line_number ) { yylineno = line_number; } /** Set the input stream. This does not discard the current * input buffer. * @param in_str A readable stream. * * @see yy_switch_to_buffer */ void yyset_in (FILE * in_str ) { yyin = in_str ; } void yyset_out (FILE * out_str ) { yyout = out_str ; } int yyget_debug (void) { return yy_flex_debug; } void yyset_debug (int bdebug ) { yy_flex_debug = bdebug ; } static int yy_init_globals (void) { /* Initialization is the same as for the non-reentrant scanner. * This function is called from yylex_destroy(), so don't allocate here. */ (yy_buffer_stack) = 0; (yy_buffer_stack_top) = 0; (yy_buffer_stack_max) = 0; (yy_c_buf_p) = (char *) 0; (yy_init) = 0; (yy_start) = 0; /* Defined in main.c */ #ifdef YY_STDINIT yyin = stdin; yyout = stdout; #else yyin = (FILE *) 0; yyout = (FILE *) 0; #endif /* For future reference: Set errno on error, since we are called by * yylex_init() */ return 0; } /* yylex_destroy is for both reentrant and non-reentrant scanners. */ int yylex_destroy (void) { /* Pop the buffer stack, destroying each element. */ while(YY_CURRENT_BUFFER){ yy_delete_buffer(YY_CURRENT_BUFFER ); YY_CURRENT_BUFFER_LVALUE = NULL; yypop_buffer_state(); } /* Destroy the stack itself. */ yyfree((yy_buffer_stack) ); (yy_buffer_stack) = NULL; /* Reset the globals. This is important in a non-reentrant scanner so the next time * yylex() is called, initialization will occur. */ yy_init_globals( ); return 0; } /* * Internal utility routines. */ #ifndef yytext_ptr static void yy_flex_strncpy (char* s1, yyconst char * s2, int n ) { register int i; for ( i = 0; i < n; ++i ) s1[i] = s2[i]; } #endif #ifdef YY_NEED_STRLEN static int yy_flex_strlen (yyconst char * s ) { register int n; for ( n = 0; s[n]; ++n ) ; return n; } #endif void *yyalloc (yy_size_t size ) { return (void *) malloc( size ); } void *yyrealloc (void * ptr, yy_size_t size ) { /* The cast to (char *) in the following accommodates both * implementations that use char* generic pointers, and those * that use void* generic pointers. It works with the latter * because both ANSI C and C++ allow castless assignment from * any pointer type to void*, and deal with argument conversions * as though doing an assignment. */ return (void *) realloc( (char *) ptr, size ); } void yyfree (void * ptr ) { free( (char *) ptr ); /* see yyrealloc() for (char *) cast */ } #define YYTABLES_NAME "yytables" #line 303 "genpr-scan.l" smalltalk-3.2.5/libgst/events.c0000644000175000017500000000701012130343734013360 00000000000000/******************************** -*- C -*- **************************** * * Asynchronous events handling. * * ***********************************************************************/ /*********************************************************************** * * Copyright 2001,2002,2003,2005,2006,2008,2009 Free Software Foundation, Inc. * Free Software Foundation, Inc. * Written by Paolo Bonzini. * * This file is part of GNU Smalltalk. * * GNU Smalltalk is free software; you can redistribute it and/or modify it * under the terms of the GNU General Public License as published by the Free * Software Foundation; either version 2, or (at your option) any later * version. * * Linking GNU Smalltalk statically or dynamically with other modules is * making a combined work based on GNU Smalltalk. Thus, the terms and * conditions of the GNU General Public License cover the whole * combination. * * In addition, as a special exception, the Free Software Foundation * give you permission to combine GNU Smalltalk with free software * programs or libraries that are released under the GNU LGPL and with * independent programs running under the GNU Smalltalk virtual machine. * * You may copy and distribute such a system following the terms of the * GNU GPL for GNU Smalltalk and the licenses of the other code * concerned, provided that you include the source code of that other * code when and as the GNU GPL requires distribution of source code. * * Note that people who make modified versions of GNU Smalltalk are not * obligated to grant this special exception for their modified * versions; it is their choice whether to do so. The GNU General * Public License gives permission to release a modified version without * this exception; this exception also makes it possible to release a * modified version which carries forward this exception. * * GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or * FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for * more details. * * You should have received a copy of the GNU General Public License along with * GNU Smalltalk; see the file COPYING. If not, write to the Free Software * Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * ***********************************************************************/ #include "gstpriv.h" /* Holds the semaphores to be signaled when the operating system sends us a C-style signal. */ async_queue_entry _gst_sem_int_vec[NSIG]; /* Signals _gst_sem_int_vec[SIG] and removes the semaphore from the vector (because C-style signal handlers are one-shot). */ static RETSIGTYPE signal_handler (int sig); RETSIGTYPE signal_handler (int sig) { if (_gst_sem_int_vec[sig].data) { if (IS_CLASS (_gst_sem_int_vec[sig].data, _gst_semaphore_class)) _gst_async_call_internal (&_gst_sem_int_vec[sig]); else { _gst_errorf ("C signal trapped, but no semaphore was waiting"); raise (sig); } } _gst_set_signal_handler (sig, SIG_DFL); _gst_wakeup (); } void _gst_async_interrupt_wait (OOP semaphoreOOP, int sig) { if (sig < 0 || sig >= NSIG) return; _gst_register_oop (semaphoreOOP); _gst_sem_int_vec[sig].func = _gst_do_async_signal_and_unregister; _gst_sem_int_vec[sig].data = semaphoreOOP; _gst_set_signal_handler (sig, signal_handler); /* should probably package up the old interrupt state here for return so that it can be undone */ } smalltalk-3.2.5/libgst/real.h0000644000175000017500000000755112123404352013012 00000000000000/******************************** -*- C -*- **************************** * * Simple floating-point data type * * ***********************************************************************/ /*********************************************************************** * * Copyright 2009 Free Software Foundation, Inc. * Written by Paolo Bonzini. * * This file is part of GNU Smalltalk. * * GNU Smalltalk is free software; you can redistribute it and/or modify it * under the terms of the GNU General Public License as published by the Free * Software Foundation; either version 2, or (at your option) any later * version. * * Linking GNU Smalltalk statically or dynamically with other modules is * making a combined work based on GNU Smalltalk. Thus, the terms and * conditions of the GNU General Public License cover the whole * combination. * * In addition, as a special exception, the Free Software Foundation * give you permission to combine GNU Smalltalk with free software * programs or libraries that are released under the GNU LGPL and with * independent programs running under the GNU Smalltalk virtual machine. * * You may copy and distribute such a system following the terms of the * GNU GPL for GNU Smalltalk and the licenses of the other code * concerned, provided that you include the source code of that other * code when and as the GNU GPL requires distribution of source code. * * Note that people who make modified versions of GNU Smalltalk are not * obligated to grant this special exception for their modified * versions; it is their choice whether to do so. The GNU General * Public License gives permission to release a modified version without * this exception; this exception also makes it possible to release a * modified version which carries forward this exception. * * GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or * FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for * more details. * * You should have received a copy of the GNU General Public License along with * GNU Smalltalk; see the file COPYING. If not, write to the Free Software * Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * ***********************************************************************/ #ifndef GST_REAL_H #define GST_REAL_H #define SIGSZ 10 struct real { /* Little-endian significant. sig[0] is the least significant part. The 1 is not implicit, so in a normalized real sig[9] == 0 means the value is zero. sig[9]'s MSB has weight 2^exp. */ unsigned short sig[SIGSZ]; int exp; int sign; }; /* Convert an integer number S to floating point and move it to OUT. */ extern void _gst_real_from_int (struct real *out, int s); /* Sum S to R and store the result into R. */ extern void _gst_real_add_int (struct real *r, int s) ATTRIBUTE_HIDDEN; /* Multiply R by S and store the result into R. */ extern void _gst_real_mul_int (struct real *r, int s) ATTRIBUTE_HIDDEN; /* Compute R^S and store the result into R. */ extern void _gst_real_powi (struct real *out, struct real *r, int s) ATTRIBUTE_HIDDEN; /* Sum S to R and store the result into R. */ extern void _gst_real_add (struct real *r, struct real *s) ATTRIBUTE_HIDDEN; /* Multiply R by S and store the result into R. */ extern void _gst_real_mul (struct real *r, struct real *s) ATTRIBUTE_HIDDEN; /* Divide R by S and store the result into OUT. */ extern void _gst_real_div (struct real *out, struct real *r, struct real *s) ATTRIBUTE_HIDDEN; /* Compute the inverse of R and store it into OUT (OUT and R can overlap). */ extern void _gst_real_inv (struct real *out, struct real *r) ATTRIBUTE_HIDDEN; /* Convert R to a long double and return it. */ extern long double _gst_real_get_ld (struct real *r) ATTRIBUTE_HIDDEN; #endif smalltalk-3.2.5/libgst/tree.c0000644000175000017500000005254612130343734013031 00000000000000/******************************** -*- C -*- **************************** * * Semantic Tree manipulation module. * * ***********************************************************************/ /*********************************************************************** * * Copyright 1988,89,90,91,92,94,95,99,2000,2001,2002,2003,2006 * Free Software Foundation, Inc. * Written by Steve Byrne. * * This file is part of GNU Smalltalk. * * GNU Smalltalk is free software; you can redistribute it and/or modify it * under the terms of the GNU General Public License as published by the Free * Software Foundation; either version 2, or (at your option) any later * version. * * Linking GNU Smalltalk statically or dynamically with other modules is * making a combined work based on GNU Smalltalk. Thus, the terms and * conditions of the GNU General Public License cover the whole * combination. * * In addition, as a special exception, the Free Software Foundation * give you permission to combine GNU Smalltalk with free software * programs or libraries that are released under the GNU LGPL and with * independent programs running under the GNU Smalltalk virtual machine. * * You may copy and distribute such a system following the terms of the * GNU GPL for GNU Smalltalk and the licenses of the other code * concerned, provided that you include the source code of that other * code when and as the GNU GPL requires distribution of source code. * * Note that people who make modified versions of GNU Smalltalk are not * obligated to grant this special exception for their modified * versions; it is their choice whether to do so. The GNU General * Public License gives permission to release a modified version without * this exception; this exception also makes it possible to release a * modified version which carries forward this exception. * * GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or * FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for * more details. * * You should have received a copy of the GNU General Public License along with * GNU Smalltalk; see the file COPYING. If not, write to the Free Software * Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * ***********************************************************************/ #include "gstpriv.h" /* Make a tree_node made up of the NODETYPE type-tag and a list_node representing the head of the list, for NAME and VALUE. */ static inline tree_node make_list_node (YYLTYPE *location, node_type nodeType, const char *name, tree_node value); /* Make a expr_node made up of the NODETYPE type-tag and an expr_node with given RECEIVER, SELECTOR and EXPRESSION. */ static inline tree_node make_expr_node (YYLTYPE *location, node_type nodeType, tree_node receiver, OOP selector, tree_node expression); /* Allocate from the compilation obstack a node and assign it the NODETYPE type-tag. */ static inline tree_node make_tree_node (YYLTYPE *location, node_type nodeType); /* Print the NODE method_node with LEVEL spaces of indentation. */ static void print_method_node (tree_node node, int level); /* Print the NODE method_node with LEVEL spaces of indentation. */ static void print_block_node (tree_node node, int level); /* Print the NODE expr_node with LEVEL spaces of indentation. */ static void print_expr_node (tree_node node, int level); /* Print the NODE list_node with LEVEL spaces of indentation. */ static void print_list_node (tree_node node, int level); /* Print the NODE list_node with LEVEL spaces of indentation, assuming it is a attribute. */ static void print_attribute_list_node (tree_node node, int level); /* Print the NODE const_node with LEVEL spaces of indentation. */ static void print_const_node (tree_node node, int level); /* Print the NODE list_node with LEVEL spaces of indentation, discarding the NAME of each node (hence the distinction between this and print_list_node). */ static void print_array_constructor_node (tree_node node, int level); /* Print LEVEL spaces of indentation. */ static void indent (int level); tree_node _gst_make_array_elt (YYLTYPE *location, tree_node elt) { return (make_list_node (location, TREE_ARRAY_ELT_LIST, NULL, elt)); } tree_node _gst_make_method (YYLTYPE *location, YYLTYPE *endLocation, tree_node selectorExpr, tree_node temporaries, tree_node attributes, tree_node statements, int isOldSyntax) { tree_node result; result = make_tree_node (location, TREE_METHOD_NODE); result->v_method.endPos = endLocation->file_offset; result->v_method.selectorExpr = selectorExpr; result->v_method.temporaries = temporaries; result->v_method.attributes = attributes; result->v_method.statements = statements; result->v_method.isOldSyntax = isOldSyntax; return (result); } tree_node _gst_make_cascaded_message (YYLTYPE *location, tree_node messageExpr, tree_node cascadedMessages) { return (make_expr_node (location, TREE_CASCADE_EXPR, messageExpr, NULL, cascadedMessages)); } tree_node _gst_make_unary_expr (YYLTYPE *location, tree_node receiver, const char *unarySelectorExpr) { OOP selector; /* selectors, being interned symbols, don't need to be incubated -- symbols once created are always referenced */ selector = _gst_intern_string (unarySelectorExpr); return (make_expr_node (location, TREE_UNARY_EXPR, receiver, selector, NULL)); } tree_node _gst_intern_ident (YYLTYPE *location, const char *ident) { return (make_expr_node (location, TREE_SYMBOL_NODE, NULL, _gst_intern_string (ident), NULL)); } tree_node _gst_make_return (YYLTYPE *location, tree_node expression) { return (make_expr_node (location, TREE_RETURN_EXPR, expression, _gst_nil_oop, NULL)); } tree_node _gst_make_keyword_expr (YYLTYPE *location, tree_node receiver, tree_node keywordMessage) { return (make_expr_node (location, TREE_KEYWORD_EXPR, receiver, _gst_nil_oop, keywordMessage)); } tree_node _gst_make_assign (YYLTYPE *location, tree_node variables, tree_node expression) { return (make_expr_node (location, TREE_ASSIGN_EXPR, variables, _gst_nil_oop, expression)); } tree_node _gst_make_statement_list (YYLTYPE *location, tree_node expression) { return (make_list_node (location, TREE_STATEMENT_LIST, NULL, expression)); } tree_node _gst_make_attribute_list (YYLTYPE *location, tree_node constant) { return (make_list_node (location, TREE_ATTRIBUTE_LIST, NULL, constant)); } tree_node _gst_make_keyword_list (YYLTYPE *location, const char *keyword, tree_node expression) { return (make_list_node (location, TREE_KEYWORD_LIST, keyword, expression)); } tree_node _gst_make_variable_list (YYLTYPE *location, tree_node variable) { /* Actually, we rely on the fact that a variable is represented as a tree node of type list_node, so all we do is change the node tag to TREE_VAR_DECL_LIST. */ variable->nodeType = TREE_VAR_DECL_LIST; return (variable); } tree_node _gst_make_assignment_list (YYLTYPE *location, tree_node variable) { /* Actually, we rely on the fact that a variable is represented as a tree node of type list_node, so all we do is change the node tag to TREE_VAR_DECL_LIST. */ return (make_list_node (location, TREE_VAR_ASSIGN_LIST, NULL, variable)); } tree_node _gst_make_binary_expr (YYLTYPE *location, tree_node receiver, const char *binaryOp, tree_node argument) { OOP selector; selector = _gst_intern_string (binaryOp); return (make_expr_node (location, TREE_BINARY_EXPR, receiver, selector, argument)); } tree_node _gst_make_message_list (YYLTYPE *location, tree_node messageElt) { return (make_list_node (location, TREE_MESSAGE_LIST, NULL, messageElt)); } tree_node _gst_make_block (YYLTYPE *location, tree_node arguments, tree_node temporaries, tree_node statements) { tree_node result; result = make_tree_node (location, TREE_BLOCK_NODE); result->v_block.arguments = arguments; result->v_block.temporaries = temporaries; result->v_block.statements = statements; return (result); } tree_node _gst_make_variable (YYLTYPE *location, const char *name) { return (make_list_node (location, TREE_VARIABLE_NODE, name, NULL)); } tree_node _gst_make_int_constant (YYLTYPE *location, intptr_t ival) { tree_node result; result = make_tree_node (location, TREE_CONST_EXPR); result->v_const.constType = CONST_INT; result->v_const.val.iVal = ival; return (result); } tree_node _gst_make_byte_object_constant (YYLTYPE *location, byte_object boval) { tree_node result; result = make_tree_node (location, TREE_CONST_EXPR); result->v_const.constType = CONST_BYTE_OBJECT; result->v_const.val.boVal = boval; return (result); } tree_node _gst_make_float_constant (YYLTYPE *location, long double fval, int type) { tree_node result; result = make_tree_node (location, TREE_CONST_EXPR); result->v_const.constType = type; result->v_const.val.fVal = fval; return (result); } tree_node _gst_make_string_constant (YYLTYPE *location, const char *sval) { tree_node result; result = make_tree_node (location, TREE_CONST_EXPR); result->v_const.constType = CONST_STRING; result->v_const.val.sVal = sval; return (result); } tree_node _gst_make_deferred_binding_constant (YYLTYPE *location, tree_node varNode) { tree_node result; result = make_tree_node (location, TREE_CONST_EXPR); result->v_const.constType = CONST_DEFERRED_BINDING; result->v_const.val.aVal = varNode; return (result); } tree_node _gst_make_oop_constant (YYLTYPE *location, OOP oval) { tree_node result; result = make_tree_node (location, TREE_CONST_EXPR); result->v_const.constType = CONST_OOP; result->v_const.val.oopVal = oval; INC_ADD_OOP (oval); return (result); } tree_node _gst_make_char_constant (YYLTYPE *location, int ival) { tree_node result; result = make_tree_node (location, TREE_CONST_EXPR); result->v_const.constType = CONST_CHAR; result->v_const.val.iVal = ival; return (result); } tree_node _gst_make_symbol_constant (YYLTYPE *location, tree_node symbolNode) { tree_node result; result = make_tree_node (location, TREE_CONST_EXPR); result->v_const.constType = CONST_OOP; if (symbolNode) result->v_const.val.oopVal = symbolNode->v_expr.selector; else result->v_const.val.oopVal = _gst_nil_oop; return (result); } /* This function converts an gst_array constant's format (linked list of its * elements) to a gst_byte_array constant's format (byte_object struct). The code * itself is awful and the list is extremely space inefficient, but consider * that: * a) it makes the parser simpler (Arrays and ByteArrays are treated in almost * the same way; only, the latter call this function and the former don't). * b) a list is indeed an elegant solution because we don't know the size of * the byte array until we have parsed it all (that is, until we call this * function. * c) the byte_object is the best format for ByteArrays: first, it is the one * which makes it easiest to make a full-fledged object out of the parse * tree; second, it is logical to choose it since LargeIntegers use it, * and ByteArrays are represented exactly the same as LargeIntegers. */ tree_node _gst_make_byte_array_constant (YYLTYPE *location, tree_node aval) { tree_node arrayElt, ival; int len; byte_object bo; gst_uchar *data; for (len = 0, arrayElt = aval; arrayElt; len++, arrayElt = arrayElt->v_list.next); bo = (byte_object) obstack_alloc (_gst_compilation_obstack, sizeof (struct byte_object) + len); bo->class = _gst_byte_array_class; bo->size = len; data = bo->body; /* Now extract the node for each integer constant, storing its value into the byte_object */ for (arrayElt = aval; arrayElt; arrayElt = arrayElt->v_list.next) { ival = arrayElt->v_list.value; *data++ = ival->v_const.val.iVal; } return (_gst_make_byte_object_constant (location, bo)); } tree_node _gst_make_array_constant (YYLTYPE *location, tree_node aval) { tree_node result; result = make_tree_node (location, TREE_CONST_EXPR); result->v_const.constType = CONST_ARRAY; result->v_const.val.aVal = aval; return (result); } tree_node _gst_make_array_constructor (YYLTYPE *location, tree_node statements) { tree_node result; result = make_tree_node (location, TREE_ARRAY_CONSTRUCTOR); result->v_const.constType = CONST_ARRAY; result->v_const.val.aVal = statements; return (result); } tree_node _gst_make_binding_constant (YYLTYPE *location, tree_node variables) { tree_node result; result = make_tree_node (location, TREE_CONST_EXPR); result->v_const.constType = CONST_BINDING; result->v_const.val.aVal = variables; return (result); } tree_node _gst_add_node (tree_node n1, tree_node n2) { if (n1 == NULL) return n2; *(n1->v_list.nextAddr) = n2; n1->v_list.nextAddr = n2->v_list.nextAddr; return n1; } void _gst_free_tree () { obstack_free (_gst_compilation_obstack, NULL); obstack_init (_gst_compilation_obstack); } /*********************************************************************** * * Internal tree construction routines. * ***********************************************************************/ static tree_node make_list_node (YYLTYPE *location, node_type nodeType, const char *name, tree_node value) { tree_node result; result = make_tree_node (location, nodeType); result->v_list.name = name; result->v_list.value = value; result->v_list.next = NULL; result->v_list.nextAddr = &result->v_list.next; return (result); } static tree_node make_expr_node (YYLTYPE *location, node_type nodeType, tree_node receiver, OOP selector, tree_node expression) { tree_node result; result = make_tree_node (location, nodeType); result->v_expr.receiver = receiver; result->v_expr.selector = selector; result->v_expr.expression = expression; return (result); } static tree_node make_tree_node (YYLTYPE *location, node_type nodeType) { tree_node result; result = (tree_node) obstack_alloc (_gst_compilation_obstack, sizeof (struct tree_node)); result->nodeType = nodeType; result->location = *location; return (result); } /*********************************************************************** * * Printing routines. * ***********************************************************************/ void _gst_print_tree (tree_node node, int level) { const char *name; if (node == NULL) { printf ("(nil)\n"); return; } if (node->nodeType < TREE_FIRST || node->nodeType > TREE_LAST) { printf ("Unknown tree node type %d\n", node->nodeType); return; } switch (node->nodeType) { case TREE_METHOD_NODE: name = "TREE_METHOD_NODE"; break; case TREE_UNARY_EXPR: name = "TREE_UNARY_EXPR"; break; case TREE_BINARY_EXPR: name = "TREE_BINARY_EXPR"; break; case TREE_KEYWORD_EXPR: name = "TREE_KEYWORD_EXPR"; break; case TREE_VARIABLE_NODE: name = "TREE_VARIABLE_NODE"; break; case TREE_ATTRIBUTE_LIST: name = "TREE_ATTRIBUTE_LIST"; break; case TREE_KEYWORD_LIST: name = "TREE_KEYWORD_LIST"; break; case TREE_VAR_DECL_LIST: name = "TREE_VAR_DECL_LIST"; break; case TREE_VAR_ASSIGN_LIST: name = "TREE_VAR_ASSIGN_LIST"; break; case TREE_STATEMENT_LIST: name = "TREE_STATEMENT_LIST"; break; case TREE_RETURN_EXPR: name = "TREE_RETURN_EXPR"; break; case TREE_ASSIGN_EXPR: name = "TREE_ASSIGN_EXPR"; break; case TREE_CONST_EXPR: name = "TREE_CONST_EXPR"; break; case TREE_SYMBOL_NODE: name = "TREE_SYMBOL_NODE"; break; case TREE_ARRAY_ELT_LIST: name = "TREE_ARRAY_ELT_LIST"; break; case TREE_BLOCK_NODE: name = "TREE_BLOCK_NODE"; break; case TREE_CASCADE_EXPR: name = "TREE_CASCADE_EXPR"; break; case TREE_MESSAGE_LIST: name = "TREE_MESSAGE_LIST"; break; case TREE_ARRAY_CONSTRUCTOR: name = "TREE_ARRAY_CONSTRUCTOR"; break; default: abort (); } printf ("%s\n", name); switch (node->nodeType) { case TREE_METHOD_NODE: print_method_node (node, level + 2); break; case TREE_BLOCK_NODE: print_block_node (node, level + 2); break; case TREE_SYMBOL_NODE: case TREE_UNARY_EXPR: case TREE_BINARY_EXPR: case TREE_KEYWORD_EXPR: case TREE_CASCADE_EXPR: case TREE_RETURN_EXPR: case TREE_ASSIGN_EXPR: print_expr_node (node, level + 2); break; case TREE_VARIABLE_NODE: case TREE_KEYWORD_LIST: case TREE_ARRAY_ELT_LIST: case TREE_MESSAGE_LIST: case TREE_STATEMENT_LIST: case TREE_VAR_DECL_LIST: case TREE_VAR_ASSIGN_LIST: print_list_node (node, level + 2); break; case TREE_ARRAY_CONSTRUCTOR: print_array_constructor_node (node, level + 2); break; case TREE_CONST_EXPR: print_const_node (node, level + 2); break; case TREE_ATTRIBUTE_LIST: print_attribute_list_node (node, level + 2); break; default: abort (); } } static void print_array_constructor_node (tree_node node, int level) { indent (level); _gst_print_tree (node->v_const.val.aVal, level); } static void print_list_node (tree_node node, int level) { indent (level); printf ("name: %s\n", node->v_list.name ? node->v_list.name : "(nil)"); indent (level); printf ("value: "); _gst_print_tree (node->v_list.value, level + 7); if (node->v_list.next) { indent (level - 2); _gst_print_tree (node->v_list.next, level - 2); } } static void print_expr_node (tree_node node, int level) { indent (level); printf ("selector: %#O\n", node->v_expr.selector); indent (level); printf ("receiver: "); _gst_print_tree (node->v_expr.receiver, level + 10); /* ??? don't print the expression for unary type things, and don't print the receiver for symbol nodes */ indent (level); printf ("expression: "); _gst_print_tree (node->v_expr.expression, level + 12); } static void print_method_node (tree_node node, int level) { indent (level); printf ("selectorExpr: "); _gst_print_tree (node->v_method.selectorExpr, level + 14); indent (level); printf ("temporaries: "); _gst_print_tree (node->v_method.temporaries, level + 13); indent (level); printf ("attributes: "); _gst_print_tree (node->v_method.attributes, level + 9); indent (level); printf ("statements: "); _gst_print_tree (node->v_method.statements, level + 12); indent (level); if (node->v_method.isOldSyntax) printf ("old syntax\n"); else printf ("new syntax\n"); } static void print_block_node (tree_node node, int level) { indent (level); printf ("arguments: "); _gst_print_tree (node->v_block.arguments, level + 11); indent (level); printf ("temporaries: "); _gst_print_tree (node->v_block.temporaries, level + 13); indent (level); printf ("statements: "); _gst_print_tree (node->v_block.statements, level + 12); } static void print_const_node (tree_node node, int level) { indent (level); switch (node->v_const.constType) { case CONST_INT: printf ("int: %ld\n", node->v_const.val.iVal); break; case CONST_FLOATD: printf ("floatd: %g\n", (float) node->v_const.val.fVal); break; case CONST_FLOATE: printf ("floate: %g\n", (double) node->v_const.val.fVal); break; case CONST_FLOATQ: printf ("floatq: %Lg\n", node->v_const.val.fVal); break; case CONST_STRING: printf ("string: \"%s\"\n", node->v_const.val.sVal); break; case CONST_OOP: printf ("oop: %O\n", node->v_const.val.oopVal); break; case CONST_ARRAY: printf ("array: "); _gst_print_tree (node->v_const.val.aVal, level + 7); break; case CONST_DEFERRED_BINDING: printf ("deferred variable binding: "); _gst_print_tree (node->v_const.val.aVal, level + 27); break; case CONST_BINDING: printf ("variable binding: "); _gst_print_tree (node->v_const.val.aVal, level + 18); break; default: _gst_errorf ("Unknown constant type %d", node->v_const.constType); } } static void print_attribute_list_node (tree_node node, int level) { tree_node value = node->v_list.value; OOP messageOOP = value->v_const.val.oopVal; gst_message message = (gst_message) OOP_TO_OBJ (messageOOP); OOP selectorOOP = message->selector; gst_string selector = (gst_string) OOP_TO_OBJ (selectorOOP); OOP argumentsOOP = message->args; gst_object arguments = OOP_TO_OBJ (argumentsOOP); const char *sel = selector->chars; char *name = alloca (oop_num_fields (selectorOOP) + 1); int numArgs = oop_num_fields (argumentsOOP); int i; char sep; indent (level); printf ("value: "); for (sep = '<', i = 0; i < numArgs; sep = ' ', i++) { /* Find the end of this keyword and print it together with its argument. */ const char *end = strchr (sel, ':'); memcpy (name, sel, end - sel); name[end - sel] = 0; sel = end + 1; printf ("%c%s: %O", sep, name, arguments->data[i]); } printf (">\n"); if (node->v_list.next) { indent (level - 2); _gst_print_tree (node->v_list.next, level - 2); } } static void indent (int level) { printf ("%*s", level, ""); } smalltalk-3.2.5/libgst/genbc-decl.h0000644000175000017500000000514512130455565014061 00000000000000/* A Bison parser, made by GNU Bison 2.5. */ /* Bison interface for Yacc-like parsers in C Copyright (C) 1984, 1989-1990, 2000-2011 Free Software Foundation, Inc. This program is free software: you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation, either version 3 of the License, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program. If not, see . */ /* As a special exception, you may create a larger work that contains part or all of the Bison parser skeleton and distribute that work under terms of your choice, so long as that work isn't itself a parser generator using the skeleton or a modified version thereof as a parser skeleton. Alternatively, if you modify or redistribute the parser skeleton itself, you may (at your option) remove this special exception, which will cause the skeleton and the resulting Bison output files to be licensed under the GNU General Public License without this special exception. This special exception was added by the Free Software Foundation in version 2.2 of Bison. */ /* Tokens. */ #ifndef YYTOKENTYPE # define YYTOKENTYPE /* Put the tokens into the symbol table, so that GDB and other debuggers know about them. */ enum yytokentype { MATCH_BYTECODES = 258, DECL_BEGIN = 259, DECL_END = 260, DECL_BREAK = 261, DECL_CONTINUE = 262, DECL_DISPATCH = 263, DECL_EXTRACT = 264, DECL_DOTS = 265, NUMBER = 266, ID = 267, EXPR = 268 }; #endif /* Tokens. */ #define MATCH_BYTECODES 258 #define DECL_BEGIN 259 #define DECL_END 260 #define DECL_BREAK 261 #define DECL_CONTINUE 262 #define DECL_DISPATCH 263 #define DECL_EXTRACT 264 #define DECL_DOTS 265 #define NUMBER 266 #define ID 267 #define EXPR 268 #if ! defined YYSTYPE && ! defined YYSTYPE_IS_DECLARED typedef union YYSTYPE { /* Line 2068 of yacc.c */ #line 110 "genbc-decl.y" struct field_info *field; const char *ctext; char *text; int num; /* Line 2068 of yacc.c */ #line 85 "genbc-decl.h" } YYSTYPE; # define YYSTYPE_IS_TRIVIAL 1 # define yystype YYSTYPE /* obsolescent; will be withdrawn */ # define YYSTYPE_IS_DECLARED 1 #endif extern YYSTYPE yylval; smalltalk-3.2.5/libgst/genvm-scan.c0000644000175000017500000023070312130455565014127 00000000000000#line 2 "genvm-scan.c" #line 4 "genvm-scan.c" #define YY_INT_ALIGNED short int /* A lexical scanner generated by flex */ #define FLEX_SCANNER #define YY_FLEX_MAJOR_VERSION 2 #define YY_FLEX_MINOR_VERSION 5 #define YY_FLEX_SUBMINOR_VERSION 35 #if YY_FLEX_SUBMINOR_VERSION > 0 #define FLEX_BETA #endif /* First, we deal with platform-specific or compiler-specific issues. */ /* begin standard C headers. */ #include #include #include #include /* end standard C headers. */ /* flex integer type definitions */ #ifndef FLEXINT_H #define FLEXINT_H /* C99 systems have . Non-C99 systems may or may not. */ #if defined (__STDC_VERSION__) && __STDC_VERSION__ >= 199901L /* C99 says to define __STDC_LIMIT_MACROS before including stdint.h, * if you want the limit (max/min) macros for int types. */ #ifndef __STDC_LIMIT_MACROS #define __STDC_LIMIT_MACROS 1 #endif #include typedef int8_t flex_int8_t; typedef uint8_t flex_uint8_t; typedef int16_t flex_int16_t; typedef uint16_t flex_uint16_t; typedef int32_t flex_int32_t; typedef uint32_t flex_uint32_t; #else typedef signed char flex_int8_t; typedef short int flex_int16_t; typedef int flex_int32_t; typedef unsigned char flex_uint8_t; typedef unsigned short int flex_uint16_t; typedef unsigned int flex_uint32_t; /* Limits of integral types. */ #ifndef INT8_MIN #define INT8_MIN (-128) #endif #ifndef INT16_MIN #define INT16_MIN (-32767-1) #endif #ifndef INT32_MIN #define INT32_MIN (-2147483647-1) #endif #ifndef INT8_MAX #define INT8_MAX (127) #endif #ifndef INT16_MAX #define INT16_MAX (32767) #endif #ifndef INT32_MAX #define INT32_MAX (2147483647) #endif #ifndef UINT8_MAX #define UINT8_MAX (255U) #endif #ifndef UINT16_MAX #define UINT16_MAX (65535U) #endif #ifndef UINT32_MAX #define UINT32_MAX (4294967295U) #endif #endif /* ! C99 */ #endif /* ! FLEXINT_H */ #ifdef __cplusplus /* The "const" storage-class-modifier is valid. */ #define YY_USE_CONST #else /* ! __cplusplus */ /* C99 requires __STDC__ to be defined as 1. */ #if defined (__STDC__) #define YY_USE_CONST #endif /* defined (__STDC__) */ #endif /* ! __cplusplus */ #ifdef YY_USE_CONST #define yyconst const #else #define yyconst #endif /* Returned upon end-of-file. */ #define YY_NULL 0 /* Promotes a possibly negative, possibly signed char to an unsigned * integer for use as an array index. If the signed char is negative, * we want to instead treat it as an 8-bit unsigned char, hence the * double cast. */ #define YY_SC_TO_UI(c) ((unsigned int) (unsigned char) c) /* Enter a start condition. This macro really ought to take a parameter, * but we do it the disgusting crufty way forced on us by the ()-less * definition of BEGIN. */ #define BEGIN (yy_start) = 1 + 2 * /* Translate the current start state into a value that can be later handed * to BEGIN to return to the state. The YYSTATE alias is for lex * compatibility. */ #define YY_START (((yy_start) - 1) / 2) #define YYSTATE YY_START /* Action number for EOF rule of a given start state. */ #define YY_STATE_EOF(state) (YY_END_OF_BUFFER + state + 1) /* Special action meaning "start processing a new file". */ #define YY_NEW_FILE yyrestart(yyin ) #define YY_END_OF_BUFFER_CHAR 0 /* Size of default input buffer. */ #ifndef YY_BUF_SIZE #ifdef __ia64__ /* On IA-64, the buffer size is 16k, not 8k. * Moreover, YY_BUF_SIZE is 2*YY_READ_BUF_SIZE in the general case. * Ditto for the __ia64__ case accordingly. */ #define YY_BUF_SIZE 32768 #else #define YY_BUF_SIZE 16384 #endif /* __ia64__ */ #endif /* The state buf must be large enough to hold one state per character in the main buffer. */ #define YY_STATE_BUF_SIZE ((YY_BUF_SIZE + 2) * sizeof(yy_state_type)) #ifndef YY_TYPEDEF_YY_BUFFER_STATE #define YY_TYPEDEF_YY_BUFFER_STATE typedef struct yy_buffer_state *YY_BUFFER_STATE; #endif extern int yyleng; extern FILE *yyin, *yyout; #define EOB_ACT_CONTINUE_SCAN 0 #define EOB_ACT_END_OF_FILE 1 #define EOB_ACT_LAST_MATCH 2 #define YY_LESS_LINENO(n) /* Return all but the first "n" matched characters back to the input stream. */ #define yyless(n) \ do \ { \ /* Undo effects of setting up yytext. */ \ int yyless_macro_arg = (n); \ YY_LESS_LINENO(yyless_macro_arg);\ *yy_cp = (yy_hold_char); \ YY_RESTORE_YY_MORE_OFFSET \ (yy_c_buf_p) = yy_cp = yy_bp + yyless_macro_arg - YY_MORE_ADJ; \ YY_DO_BEFORE_ACTION; /* set up yytext again */ \ } \ while ( 0 ) #define unput(c) yyunput( c, (yytext_ptr) ) #ifndef YY_TYPEDEF_YY_SIZE_T #define YY_TYPEDEF_YY_SIZE_T typedef size_t yy_size_t; #endif #ifndef YY_STRUCT_YY_BUFFER_STATE #define YY_STRUCT_YY_BUFFER_STATE struct yy_buffer_state { FILE *yy_input_file; char *yy_ch_buf; /* input buffer */ char *yy_buf_pos; /* current position in input buffer */ /* Size of input buffer in bytes, not including room for EOB * characters. */ yy_size_t yy_buf_size; /* Number of characters read into yy_ch_buf, not including EOB * characters. */ int yy_n_chars; /* Whether we "own" the buffer - i.e., we know we created it, * and can realloc() it to grow it, and should free() it to * delete it. */ int yy_is_our_buffer; /* Whether this is an "interactive" input source; if so, and * if we're using stdio for input, then we want to use getc() * instead of fread(), to make sure we stop fetching input after * each newline. */ int yy_is_interactive; /* Whether we're considered to be at the beginning of a line. * If so, '^' rules will be active on the next match, otherwise * not. */ int yy_at_bol; int yy_bs_lineno; /**< The line count. */ int yy_bs_column; /**< The column count. */ /* Whether to try to fill the input buffer when we reach the * end of it. */ int yy_fill_buffer; int yy_buffer_status; #define YY_BUFFER_NEW 0 #define YY_BUFFER_NORMAL 1 /* When an EOF's been seen but there's still some text to process * then we mark the buffer as YY_EOF_PENDING, to indicate that we * shouldn't try reading from the input source any more. We might * still have a bunch of tokens to match, though, because of * possible backing-up. * * When we actually see the EOF, we change the status to "new" * (via yyrestart()), so that the user can continue scanning by * just pointing yyin at a new input file. */ #define YY_BUFFER_EOF_PENDING 2 }; #endif /* !YY_STRUCT_YY_BUFFER_STATE */ /* Stack of input buffers. */ static size_t yy_buffer_stack_top = 0; /**< index of top of stack. */ static size_t yy_buffer_stack_max = 0; /**< capacity of stack. */ static YY_BUFFER_STATE * yy_buffer_stack = 0; /**< Stack as an array. */ /* We provide macros for accessing buffer states in case in the * future we want to put the buffer states in a more general * "scanner state". * * Returns the top of the stack, or NULL. */ #define YY_CURRENT_BUFFER ( (yy_buffer_stack) \ ? (yy_buffer_stack)[(yy_buffer_stack_top)] \ : NULL) /* Same as previous macro, but useful when we know that the buffer stack is not * NULL or when we need an lvalue. For internal use only. */ #define YY_CURRENT_BUFFER_LVALUE (yy_buffer_stack)[(yy_buffer_stack_top)] /* yy_hold_char holds the character lost when yytext is formed. */ static char yy_hold_char; static int yy_n_chars; /* number of characters read into yy_ch_buf */ int yyleng; /* Points to current character in buffer. */ static char *yy_c_buf_p = (char *) 0; static int yy_init = 0; /* whether we need to initialize */ static int yy_start = 0; /* start state number */ /* Flag which is used to allow yywrap()'s to do buffer switches * instead of setting up a fresh yyin. A bit of a hack ... */ static int yy_did_buffer_switch_on_eof; void yyrestart (FILE *input_file ); void yy_switch_to_buffer (YY_BUFFER_STATE new_buffer ); YY_BUFFER_STATE yy_create_buffer (FILE *file,int size ); void yy_delete_buffer (YY_BUFFER_STATE b ); void yy_flush_buffer (YY_BUFFER_STATE b ); void yypush_buffer_state (YY_BUFFER_STATE new_buffer ); void yypop_buffer_state (void ); static void yyensure_buffer_stack (void ); static void yy_load_buffer_state (void ); static void yy_init_buffer (YY_BUFFER_STATE b,FILE *file ); #define YY_FLUSH_BUFFER yy_flush_buffer(YY_CURRENT_BUFFER ) YY_BUFFER_STATE yy_scan_buffer (char *base,yy_size_t size ); YY_BUFFER_STATE yy_scan_string (yyconst char *yy_str ); YY_BUFFER_STATE yy_scan_bytes (yyconst char *bytes,int len ); void *yyalloc (yy_size_t ); void *yyrealloc (void *,yy_size_t ); void yyfree (void * ); #define yy_new_buffer yy_create_buffer #define yy_set_interactive(is_interactive) \ { \ if ( ! YY_CURRENT_BUFFER ){ \ yyensure_buffer_stack (); \ YY_CURRENT_BUFFER_LVALUE = \ yy_create_buffer(yyin,YY_BUF_SIZE ); \ } \ YY_CURRENT_BUFFER_LVALUE->yy_is_interactive = is_interactive; \ } #define yy_set_bol(at_bol) \ { \ if ( ! YY_CURRENT_BUFFER ){\ yyensure_buffer_stack (); \ YY_CURRENT_BUFFER_LVALUE = \ yy_create_buffer(yyin,YY_BUF_SIZE ); \ } \ YY_CURRENT_BUFFER_LVALUE->yy_at_bol = at_bol; \ } #define YY_AT_BOL() (YY_CURRENT_BUFFER_LVALUE->yy_at_bol) /* Begin user sect3 */ #define yywrap(n) 1 #define YY_SKIP_YYWRAP typedef unsigned char YY_CHAR; FILE *yyin = (FILE *) 0, *yyout = (FILE *) 0; typedef int yy_state_type; extern int yylineno; int yylineno = 1; extern char *yytext; #define yytext_ptr yytext static yyconst flex_int16_t yy_nxt[][37] = { { 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0, 0 }, { 15, 16, 17, 18, 17, 16, 16, 16, 19, 16, 16, 16, 20, 21, 22, 23, 24, 24, 25, 25, 16, 25, 26, 25, 25, 25, 25, 25, 25, 27, 25, 25, 28, 25, 25, 29, 16 }, { 15, 16, 30, 18, 17, 16, 31, 16, 19, 16, 16, 16, 20, 21, 22, 23, 24, 24, 25, 25, 16, 25, 26, 25, 25, 25, 25, 25, 25, 27, 25, 25, 28, 25, 25, 29, 16 }, { 15, 32, 33, 34, 32, 35, 32, 36, 37, 38, 32, 39, 32, 32, 32, 32, 32, 32, 32, 32, 32, 32, 32, 32, 32, 32, 32, 32, 32, 32, 32, 32, 32, 32, 32, 32, 32 }, { 15, 32, 33, 34, 32, 35, 32, 36, 37, 38, 32, 39, 32, 32, 32, 32, 32, 32, 32, 32, 32, 32, 32, 32, 32, 32, 32, 32, 32, 32, 32, 32, 32, 32, 32, 32, 32 }, { 15, 40, 41, 42, 40, 35, 40, 36, 40, 40, 40, 40, 40, 40, 40, 40, 40, 40, 40, 40, 40, 40, 40, 40, 40, 40, 40, 40, 40, 40, 40, 40, 40, 40, 40, 43, 44 }, { 15, 40, 41, 42, 40, 35, 40, 36, 40, 40, 40, 40, 40, 40, 40, 40, 40, 40, 40, 40, 40, 40, 40, 40, 40, 40, 40, 40, 40, 40, 40, 40, 40, 40, 40, 43, 44 }, { 15, 45, 46, 47, 46, 45, 45, 45, 45, 45, 48, 45, 45, 45, 45, 45, 45, 45, 45, 45, 45, 45, 45, 45, 45, 45, 45, 45, 45, 45, 45, 45, 45, 45, 45, 45, 45 }, { 15, 45, 46, 47, 46, 45, 45, 45, 45, 45, 48, 45, 45, 45, 45, 45, 45, 45, 45, 45, 45, 45, 45, 45, 45, 45, 45, 45, 45, 45, 45, 45, 45, 45, 45, 45, 45 }, { 15, 49, 49, 34, 49, 50, 49, 49, 49, 49, 49, 49, 49, 49, 49, 49, 49, 49, 49, 49, 51, 49, 49, 49, 49, 49, 49, 49, 49, 49, 49, 49, 49, 49, 49, 49, 49 }, { 15, 49, 49, 34, 49, 50, 49, 49, 49, 49, 49, 49, 49, 49, 49, 49, 49, 49, 49, 49, 51, 49, 49, 49, 49, 49, 49, 49, 49, 49, 49, 49, 49, 49, 49, 49, 49 }, { 15, 49, 49, 34, 49, 49, 49, 52, 49, 49, 49, 49, 49, 49, 49, 49, 49, 49, 49, 49, 51, 49, 49, 49, 49, 49, 49, 49, 49, 49, 49, 49, 49, 49, 49, 49, 49 }, { 15, 49, 49, 34, 49, 49, 49, 52, 49, 49, 49, 49, 49, 49, 49, 49, 49, 49, 49, 49, 51, 49, 49, 49, 49, 49, 49, 49, 49, 49, 49, 49, 49, 49, 49, 49, 49 }, { 15, 53, 53, 54, 53, 53, 53, 53, 53, 53, 53, 53, 53, 53, 53, 53, 53, 53, 53, 53, 55, 53, 53, 53, 53, 53, 53, 53, 53, 53, 53, 53, 53, 53, 53, 53, 53 }, { 15, 53, 53, 54, 53, 53, 53, 53, 53, 53, 53, 53, 53, 53, 53, 53, 53, 53, 53, 53, 55, 53, 53, 53, 53, 53, 53, 53, 53, 53, 53, 53, 53, 53, 53, 53, 53 }, { -15, -15, -15, -15, -15, -15, -15, -15, -15, -15, -15, -15, -15, -15, -15, -15, -15, -15, -15, -15, -15, -15, -15, -15, -15, -15, -15, -15, -15, -15, -15, -15, -15, -15, -15, -15, -15 }, { 15, -16, -16, -16, -16, -16, -16, -16, -16, -16, -16, -16, -16, -16, -16, -16, -16, -16, -16, -16, -16, -16, -16, -16, -16, -16, -16, -16, -16, -16, -16, -16, -16, -16, -16, -16, -16 }, { 15, -17, 56, -17, 56, -17, -17, -17, -17, -17, -17, -17, -17, -17, -17, -17, -17, -17, -17, -17, -17, -17, -17, -17, -17, -17, -17, -17, -17, -17, -17, -17, -17, -17, -17, -17, -17 }, { 15, -18, -18, 57, -18, -18, -18, -18, -18, -18, -18, -18, -18, -18, -18, -18, -18, -18, -18, -18, -18, -18, -18, -18, -18, -18, -18, -18, -18, -18, -18, -18, -18, -18, -18, -18, -18 }, { 15, -19, -19, -19, -19, -19, -19, -19, -19, -19, -19, -19, -19, -19, -19, -19, -19, -19, -19, -19, -19, -19, -19, -19, -19, -19, -19, -19, -19, -19, -19, -19, -19, -19, -19, -19, -19 }, { 15, -20, -20, -20, -20, -20, -20, -20, -20, -20, -20, -20, 58, -20, -20, -20, -20, -20, -20, -20, -20, -20, -20, -20, -20, -20, -20, -20, -20, -20, -20, -20, -20, -20, -20, -20, -20 }, { 15, -21, -21, -21, -21, -21, -21, -21, -21, -21, -21, -21, -21, 59, -21, -21, -21, -21, -21, -21, -21, -21, -21, -21, -21, -21, -21, -21, -21, -21, -21, -21, -21, -21, -21, -21, -21 }, { 15, -22, -22, -22, -22, -22, -22, -22, -22, -22, 60, -22, -22, -22, -22, -22, -22, -22, -22, -22, -22, -22, -22, -22, -22, -22, -22, -22, -22, -22, -22, -22, -22, -22, -22, -22, -22 }, { 15, -23, -23, -23, -23, -23, -23, -23, -23, -23, -23, -23, -23, -23, -23, 61, 61, -23, -23, -23, -23, -23, -23, -23, -23, -23, -23, -23, -23, -23, -23, -23, -23, 62, -23, -23, -23 }, { 15, -24, -24, -24, -24, -24, -24, -24, -24, -24, -24, -24, -24, -24, -24, 63, 63, 63, -24, -24, -24, -24, -24, -24, -24, -24, -24, -24, -24, -24, -24, -24, -24, -24, -24, -24, -24 }, { 15, -25, -25, -25, -25, -25, -25, -25, -25, -25, -25, -25, -25, -25, -25, 64, 64, 64, 64, 64, -25, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, -25, -25 }, { 15, -26, -26, -26, -26, -26, -26, -26, -26, -26, -26, -26, -26, -26, -26, 64, 64, 64, 64, 64, -26, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 65, -26, -26 }, { 15, -27, -27, -27, -27, -27, -27, -27, -27, -27, -27, -27, -27, -27, -27, 64, 64, 64, 64, 64, -27, 64, 64, 64, 64, 64, 64, 64, 64, 64, 66, 64, 64, 64, 64, -27, -27 }, { 15, -28, -28, -28, -28, -28, -28, -28, -28, -28, -28, -28, -28, -28, -28, 64, 64, 64, 64, 64, -28, 67, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, -28, -28 }, { 15, -29, -29, 68, -29, -29, -29, -29, -29, -29, -29, -29, -29, -29, -29, -29, -29, -29, -29, -29, -29, -29, -29, -29, -29, -29, -29, -29, -29, -29, -29, -29, -29, -29, -29, -29, -29 }, { 15, -30, 69, -30, 56, -30, 70, -30, -30, -30, -30, -30, -30, -30, -30, -30, -30, -30, -30, -30, -30, -30, -30, -30, -30, -30, -30, -30, -30, -30, -30, -30, -30, -30, -30, -30, -30 }, { 15, -31, -31, -31, -31, -31, -31, -31, -31, -31, -31, -31, -31, -31, -31, -31, -31, -31, -31, -31, -31, -31, -31, -31, -31, -31, -31, -31, -31, -31, -31, -31, -31, -31, -31, -31, -31 }, { 15, 71, 71, -32, 71, -32, 71, -32, -32, -32, 71, -32, 71, 71, 71, 71, 71, 71, 71, 71, 71, 71, 71, 71, 71, 71, 71, 71, 71, 71, 71, 71, 71, 71, 71, 71, 71 }, { 15, 71, 72, -33, 71, -33, 71, -33, 73, -33, 71, -33, 71, 71, 71, 71, 71, 71, 71, 71, 71, 71, 71, 71, 71, 71, 71, 71, 71, 71, 71, 71, 71, 71, 71, 71, 71 }, { 15, -34, -34, -34, -34, -34, -34, -34, -34, -34, -34, -34, -34, -34, -34, -34, -34, -34, -34, -34, -34, -34, -34, -34, -34, -34, -34, -34, -34, -34, -34, -34, -34, -34, -34, -34, -34 }, { 15, -35, -35, -35, -35, -35, -35, -35, -35, -35, -35, -35, -35, -35, -35, -35, -35, -35, -35, -35, -35, -35, -35, -35, -35, -35, -35, -35, -35, -35, -35, -35, -35, -35, -35, -35, -35 }, { 15, -36, -36, -36, -36, -36, -36, -36, -36, -36, -36, -36, -36, -36, -36, -36, -36, -36, -36, -36, -36, -36, -36, -36, -36, -36, -36, -36, -36, -36, -36, -36, -36, -36, -36, -36, -36 }, { 15, -37, -37, -37, -37, -37, -37, -37, -37, -37, -37, -37, -37, -37, -37, -37, -37, -37, -37, -37, -37, -37, -37, -37, -37, -37, -37, -37, -37, -37, -37, -37, -37, -37, -37, -37, -37 }, { 15, -38, 74, -38, -38, -38, -38, -38, -38, -38, -38, -38, -38, -38, -38, -38, -38, -38, -38, -38, -38, -38, -38, -38, -38, -38, -38, -38, -38, -38, -38, -38, -38, -38, -38, -38, -38 }, { 15, -39, 75, -39, -39, -39, -39, -39, -39, -39, -39, -39, -39, -39, -39, -39, -39, -39, -39, -39, -39, -39, -39, -39, -39, -39, -39, -39, -39, -39, -39, -39, -39, -39, -39, -39, -39 }, { 15, 76, 76, -40, 76, -40, 76, -40, 76, 76, 76, 76, 76, 76, 76, 76, 76, 76, 76, 76, 76, 76, 76, 76, 76, 76, 76, 76, 76, 76, 76, 76, 76, 76, 76, -40, -40 }, { 15, 76, 77, -41, 76, -41, 76, -41, 76, 76, 76, 76, 76, 76, 76, 76, 76, 76, 76, 76, 76, 76, 76, 76, 76, 76, 76, 76, 76, 76, 76, 76, 76, 76, 76, 78, 79 }, { 15, -42, -42, -42, -42, -42, -42, -42, -42, -42, -42, -42, -42, -42, -42, -42, -42, -42, -42, -42, -42, -42, -42, -42, -42, -42, -42, -42, -42, -42, -42, -42, -42, -42, -42, -42, -42 }, { 15, -43, -43, -43, -43, -43, -43, -43, -43, -43, -43, -43, -43, -43, -43, -43, -43, -43, -43, -43, -43, -43, -43, -43, -43, -43, -43, -43, -43, -43, -43, -43, -43, -43, -43, -43, -43 }, { 15, -44, -44, -44, -44, -44, -44, -44, -44, -44, -44, -44, -44, -44, -44, -44, -44, -44, -44, -44, -44, -44, -44, -44, -44, -44, -44, -44, -44, -44, -44, -44, -44, -44, -44, -44, -44 }, { 15, 80, 80, 81, 80, 80, 80, 80, 80, 80, 82, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80 }, { 15, 80, 83, 81, 83, 80, 80, 80, 80, 80, 82, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80 }, { 15, -47, -47, 57, -47, -47, -47, -47, -47, -47, -47, -47, -47, -47, -47, -47, -47, -47, -47, -47, -47, -47, -47, -47, -47, -47, -47, -47, -47, -47, -47, -47, -47, -47, -47, -47, -47 }, { 15, 84, 84, 85, 84, 84, 84, 84, 84, 84, 82, 84, 84, 84, 86, 84, 84, 84, 84, 84, 84, 84, 84, 84, 84, 84, 84, 84, 84, 84, 84, 84, 84, 84, 84, 84, 84 }, { 15, -49, -49, -49, -49, -49, -49, -49, -49, -49, -49, -49, -49, -49, -49, -49, -49, -49, -49, -49, -49, -49, -49, -49, -49, -49, -49, -49, -49, -49, -49, -49, -49, -49, -49, -49, -49 }, { 15, -50, -50, -50, -50, -50, -50, -50, -50, -50, -50, -50, -50, -50, -50, -50, -50, -50, -50, -50, -50, -50, -50, -50, -50, -50, -50, -50, -50, -50, -50, -50, -50, -50, -50, -50, -50 }, { 15, 87, 87, -51, 87, 87, 87, 87, 87, 87, 87, 87, 87, 87, 87, 87, 87, 87, 87, 87, 87, 87, 87, 87, 87, 87, 87, 87, 87, 87, 87, 87, 87, 87, 87, 87, 87 }, { 15, -52, -52, -52, -52, -52, -52, -52, -52, -52, -52, -52, -52, -52, -52, -52, -52, -52, -52, -52, -52, -52, -52, -52, -52, -52, -52, -52, -52, -52, -52, -52, -52, -52, -52, -52, -52 }, { 15, 88, 88, 89, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 90, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88 }, { 15, -54, -54, 91, -54, -54, -54, -54, -54, -54, -54, -54, -54, -54, -54, -54, -54, -54, -54, -54, -54, -54, -54, -54, -54, -54, -54, -54, -54, -54, -54, -54, -54, -54, -54, -54, -54 }, { 15, 88, 92, 93, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 90, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88 }, { 15, -56, 56, -56, 56, -56, -56, -56, -56, -56, -56, -56, -56, -56, -56, -56, -56, -56, -56, -56, -56, -56, -56, -56, -56, -56, -56, -56, -56, -56, -56, -56, -56, -56, -56, -56, -56 }, { 15, -57, -57, 57, -57, -57, -57, -57, -57, -57, -57, -57, -57, -57, -57, -57, -57, -57, -57, -57, -57, -57, -57, -57, -57, -57, -57, -57, -57, -57, -57, -57, -57, -57, -57, -57, -57 }, { 15, -58, -58, -58, -58, -58, -58, -58, -58, -58, -58, -58, -58, -58, -58, -58, -58, -58, -58, -58, -58, -58, -58, -58, -58, -58, -58, -58, -58, -58, -58, -58, -58, -58, -58, -58, -58 }, { 15, -59, -59, -59, -59, -59, -59, -59, -59, -59, -59, -59, -59, -59, -59, -59, -59, -59, -59, -59, -59, -59, -59, -59, -59, -59, -59, -59, -59, -59, -59, -59, -59, -59, -59, -59, -59 }, { 15, -60, -60, -60, -60, -60, -60, -60, -60, -60, -60, -60, -60, -60, -60, -60, -60, -60, -60, -60, -60, -60, -60, -60, -60, -60, -60, -60, -60, -60, -60, -60, -60, -60, -60, -60, -60 }, { 15, -61, -61, -61, -61, -61, -61, -61, -61, -61, -61, -61, -61, -61, -61, 61, 61, -61, -61, -61, -61, -61, -61, -61, -61, -61, -61, -61, -61, -61, -61, -61, -61, -61, -61, -61, -61 }, { 15, -62, -62, -62, -62, -62, -62, -62, -62, -62, -62, -62, -62, -62, -62, 94, 94, 94, 94, -62, -62, 94, 94, 94, 94, 94, -62, -62, -62, -62, -62, -62, -62, -62, -62, -62, -62 }, { 15, -63, -63, -63, -63, -63, -63, -63, -63, -63, -63, -63, -63, -63, -63, 63, 63, 63, -63, -63, -63, -63, -63, -63, -63, -63, -63, -63, -63, -63, -63, -63, -63, -63, -63, -63, -63 }, { 15, -64, -64, -64, -64, -64, -64, -64, -64, -64, -64, -64, -64, -64, -64, 64, 64, 64, 64, 64, -64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, -64, -64 }, { 15, -65, -65, -65, -65, -65, -65, -65, -65, -65, -65, -65, -65, -65, -65, 64, 64, 64, 64, 64, -65, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 95, 64, 64, -65, -65 }, { 15, -66, -66, -66, -66, -66, -66, -66, -66, -66, -66, -66, -66, -66, -66, 64, 64, 64, 64, 64, -66, 64, 64, 64, 64, 96, 64, 64, 64, 64, 64, 64, 64, 64, 64, -66, -66 }, { 15, -67, -67, -67, -67, -67, -67, -67, -67, -67, -67, -67, -67, -67, -67, 64, 64, 64, 64, 64, -67, 64, 97, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, -67, -67 }, { 15, -68, -68, 68, -68, -68, -68, -68, -68, -68, -68, -68, -68, -68, -68, -68, -68, -68, -68, -68, -68, -68, -68, -68, -68, -68, -68, -68, -68, -68, -68, -68, -68, -68, -68, -68, -68 }, { 15, -69, 69, -69, 56, -69, 70, -69, -69, -69, -69, -69, -69, -69, -69, -69, -69, -69, -69, -69, -69, -69, -69, -69, -69, -69, -69, -69, -69, -69, -69, -69, -69, -69, -69, -69, -69 }, { 15, -70, -70, -70, -70, -70, -70, -70, -70, -70, -70, -70, -70, -70, -70, -70, -70, -70, -70, -70, -70, -70, -70, -70, -70, -70, -70, -70, -70, -70, -70, -70, -70, -70, -70, -70, -70 }, { 15, 71, 71, -71, 71, -71, 71, -71, -71, -71, 71, -71, 71, 71, 71, 71, 71, 71, 71, 71, 71, 71, 71, 71, 71, 71, 71, 71, 71, 71, 71, 71, 71, 71, 71, 71, 71 }, { 15, 71, 72, -72, 71, -72, 71, -72, 73, -72, 71, -72, 71, 71, 71, 71, 71, 71, 71, 71, 71, 71, 71, 71, 71, 71, 71, 71, 71, 71, 71, 71, 71, 71, 71, 71, 71 }, { 15, -73, -73, -73, -73, -73, -73, -73, -73, -73, -73, -73, -73, -73, -73, -73, -73, -73, -73, -73, -73, -73, -73, -73, -73, -73, -73, -73, -73, -73, -73, -73, -73, -73, -73, -73, -73 }, { 15, -74, 74, -74, -74, -74, -74, -74, -74, -74, -74, -74, -74, -74, -74, -74, -74, -74, -74, -74, -74, -74, -74, -74, -74, -74, -74, -74, -74, -74, -74, -74, -74, -74, -74, -74, -74 }, { 15, -75, 75, -75, -75, -75, -75, -75, -75, -75, -75, -75, -75, -75, -75, -75, -75, -75, -75, -75, -75, -75, -75, -75, -75, -75, -75, -75, -75, -75, -75, -75, -75, -75, -75, -75, -75 }, { 15, 76, 76, -76, 76, -76, 76, -76, 76, 76, 76, 76, 76, 76, 76, 76, 76, 76, 76, 76, 76, 76, 76, 76, 76, 76, 76, 76, 76, 76, 76, 76, 76, 76, 76, -76, -76 }, { 15, 76, 77, -77, 76, -77, 76, -77, 76, 76, 76, 76, 76, 76, 76, 76, 76, 76, 76, 76, 76, 76, 76, 76, 76, 76, 76, 76, 76, 76, 76, 76, 76, 76, 76, 78, 79 }, { 15, -78, -78, -78, -78, -78, -78, -78, -78, -78, -78, -78, -78, -78, -78, -78, -78, -78, -78, -78, -78, -78, -78, -78, -78, -78, -78, -78, -78, -78, -78, -78, -78, -78, -78, -78, -78 }, { 15, -79, -79, -79, -79, -79, -79, -79, -79, -79, -79, -79, -79, -79, -79, -79, -79, -79, -79, -79, -79, -79, -79, -79, -79, -79, -79, -79, -79, -79, -79, -79, -79, -79, -79, -79, -79 }, { 15, 80, 80, 81, 80, 80, 80, 80, 80, 80, 82, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80 }, { 15, -81, -81, -81, -81, -81, -81, -81, -81, -81, -81, -81, -81, -81, -81, -81, -81, -81, -81, -81, -81, -81, -81, -81, -81, -81, -81, -81, -81, -81, -81, -81, -81, -81, -81, -81, -81 }, { 15, 84, 84, 85, 84, 84, 84, 84, 84, 84, 82, 84, 84, 84, 86, 84, 84, 84, 84, 84, 84, 84, 84, 84, 84, 84, 84, 84, 84, 84, 84, 84, 84, 84, 84, 84, 84 }, { 15, 80, 83, 81, 83, 80, 80, 80, 80, 80, 82, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80, 80 }, { 15, -84, -84, -84, -84, -84, -84, -84, -84, -84, -84, -84, -84, -84, -84, -84, -84, -84, -84, -84, -84, -84, -84, -84, -84, -84, -84, -84, -84, -84, -84, -84, -84, -84, -84, -84, -84 }, { 15, -85, -85, -85, -85, -85, -85, -85, -85, -85, -85, -85, -85, -85, -85, -85, -85, -85, -85, -85, -85, -85, -85, -85, -85, -85, -85, -85, -85, -85, -85, -85, -85, -85, -85, -85, -85 }, { 15, -86, -86, -86, -86, -86, -86, -86, -86, -86, -86, -86, -86, -86, -86, -86, -86, -86, -86, -86, -86, -86, -86, -86, -86, -86, -86, -86, -86, -86, -86, -86, -86, -86, -86, -86, -86 }, { 15, -87, -87, -87, -87, -87, -87, -87, -87, -87, -87, -87, -87, -87, -87, -87, -87, -87, -87, -87, -87, -87, -87, -87, -87, -87, -87, -87, -87, -87, -87, -87, -87, -87, -87, -87, -87 }, { 15, 88, 88, 89, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 90, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88 }, { 15, -89, -89, -89, -89, -89, -89, -89, -89, -89, -89, -89, -89, -89, -89, -89, -89, -89, -89, -89, -89, -89, -89, -89, -89, -89, -89, -89, -89, -89, -89, -89, -89, -89, -89, -89, -89 }, { 15, 88, 92, 93, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 90, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88 }, { 15, -91, -91, 91, -91, -91, -91, -91, -91, -91, -91, -91, -91, -91, -91, -91, -91, -91, -91, -91, -91, -91, -91, -91, -91, -91, -91, -91, -91, -91, -91, -91, -91, -91, -91, -91, -91 }, { 15, 88, 92, 93, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 90, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88, 88 }, { 15, -93, -93, -93, -93, -93, -93, -93, -93, -93, -93, -93, -93, -93, -93, -93, -93, -93, -93, -93, -93, -93, -93, -93, -93, -93, -93, -93, -93, -93, -93, -93, -93, -93, -93, -93, -93 }, { 15, -94, -94, -94, -94, -94, -94, -94, -94, -94, -94, -94, -94, -94, -94, 94, 94, 94, 94, -94, -94, 94, 94, 94, 94, 94, -94, -94, -94, -94, -94, -94, -94, -94, -94, -94, -94 }, { 15, -95, -95, -95, -95, -95, -95, -95, -95, -95, -95, -95, -95, -95, -95, 64, 64, 64, 64, 64, -95, 64, 64, 64, 64, 98, 64, 64, 64, 64, 64, 64, 64, 64, 64, -95, -95 }, { 15, -96, -96, -96, -96, -96, -96, -96, -96, -96, -96, -96, -96, -96, -96, 64, 64, 64, 64, 64, -96, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 99, 64, 64, 64, -96, -96 }, { 15, -97, -97, -97, -97, -97, -97, -97, -97, -97, -97, -97, -97, -97, -97, 64, 64, 64, 64, 64, -97, 64, 64, 64, 64, 64, 64, 100, 64, 64, 64, 64, 64, 64, 64, -97, -97 }, { 15, -98, -98, -98, -98, -98, -98, -98, -98, -98, -98, -98, -98, -98, -98, 64, 64, 64, 64, 64, -98, 64, 64, 101, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, -98, -98 }, { 15, -99, -99, -99, -99, -99, -99, -99, -99, -99, -99, -99, -99, -99, -99, 64, 64, 64, 64, 64, -99, 102, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, -99, -99 }, { 15, -100, -100, -100, -100, -100, -100, -100, -100, -100, -100, -100, -100, -100, -100, 64, 64, 64, 64, 64, -100, 64, 64, 64, 64, 103, 64, 64, 64, 64, 64, 64, 64, 64, 64, -100, -100 }, { 15, -101, -101, -101, -101, -101, -101, -101, -101, -101, -101, -101, -101, -101, -101, 64, 64, 64, 64, 64, -101, 64, 64, 64, 64, 64, 64, 64, 64, 104, 64, 64, 64, 64, 64, -101, -101 }, { 15, -102, -102, -102, -102, -102, -102, -102, -102, -102, -102, -102, -102, -102, -102, 64, 64, 64, 64, 64, -102, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 105, 64, 64, -102, -102 }, { 15, -103, -103, -103, -103, -103, -103, -103, -103, -103, -103, -103, -103, -103, -103, 64, 64, 64, 64, 64, -103, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, -103, -103 }, { 15, -104, -104, -104, -104, -104, -104, -104, -104, -104, -104, -104, -104, -104, -104, 64, 64, 64, 64, 64, -104, 64, 64, 64, 106, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, -104, -104 }, { 15, -105, -105, -105, -105, -105, -105, -105, -105, -105, -105, -105, -105, -105, -105, 64, 64, 64, 64, 64, -105, 64, 64, 64, 64, 64, 107, 64, 64, 64, 64, 64, 64, 64, 64, -105, -105 }, { 15, -106, -106, -106, -106, -106, -106, -106, -106, -106, -106, -106, -106, -106, -106, 64, 64, 64, 64, 64, -106, 64, 64, 64, 64, 108, 64, 64, 64, 64, 64, 64, 64, 64, 64, -106, -106 }, { 15, -107, -107, -107, -107, -107, -107, -107, -107, -107, -107, -107, -107, -107, -107, 64, 64, 64, 64, 64, -107, 64, 64, 64, 64, 64, 64, 64, 64, 109, 64, 64, 64, 64, 64, -107, -107 }, { 15, -108, -108, -108, -108, -108, -108, -108, -108, -108, -108, -108, -108, -108, -108, 64, 64, 64, 64, 64, -108, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, -108, -108 }, { 15, -109, -109, -109, -109, -109, -109, -109, -109, -109, -109, -109, -109, -109, -109, 64, 64, 64, 64, 64, -109, 64, 64, 64, 64, 64, 64, 64, 110, 64, 64, 64, 64, 64, 64, -109, -109 }, { 15, -110, -110, -110, -110, -110, -110, -110, -110, -110, -110, -110, -110, -110, -110, 64, 64, 64, 64, 64, -110, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, 64, -110, -110 }, } ; static yy_state_type yy_get_previous_state (void ); static yy_state_type yy_try_NUL_trans (yy_state_type current_state ); static int yy_get_next_buffer (void ); static void yy_fatal_error (yyconst char msg[] ); /* Done after the current pattern has been matched and before the * corresponding action - sets up yytext. */ #define YY_DO_BEFORE_ACTION \ (yytext_ptr) = yy_bp; \ yyleng = (size_t) (yy_cp - yy_bp); \ (yy_hold_char) = *yy_cp; \ *yy_cp = '\0'; \ (yy_c_buf_p) = yy_cp; #define YY_NUM_RULES 37 #define YY_END_OF_BUFFER 38 /* This struct is not used in this scanner, but its presence is necessary. */ struct yy_trans_info { flex_int32_t yy_verify; flex_int32_t yy_nxt; }; static yyconst flex_int16_t yy_accept[111] = { 0, 0, 0, 22, 22, 26, 26, 0, 0, 0, 0, 0, 0, 0, 0, 38, 16, 2, 1, 14, 16, 16, 16, 10, 8, 13, 13, 13, 13, 15, 2, 6, 22, 22, 37, 18, 17, 19, 21, 20, 26, 26, 25, 23, 24, 37, 2, 1, 37, 30, 28, 30, 27, 37, 36, 34, 2, 1, 12, 11, 7, 10, 0, 8, 13, 13, 13, 13, 15, 2, 6, 22, 22, 19, 21, 20, 26, 26, 23, 24, 0, 31, 0, 2, 32, 31, 33, 29, 0, 35, 34, 36, 34, 34, 9, 13, 13, 13, 13, 13, 13, 13, 13, 3, 13, 13, 13, 13, 5, 13, 4 } ; static yyconst flex_int32_t yy_ec[256] = { 0, 1, 1, 1, 1, 1, 1, 1, 1, 2, 3, 1, 4, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 2, 1, 5, 6, 1, 1, 1, 7, 8, 9, 10, 1, 11, 12, 13, 14, 15, 16, 16, 16, 16, 16, 16, 16, 17, 17, 1, 1, 1, 1, 1, 1, 1, 18, 18, 18, 18, 18, 18, 19, 19, 19, 19, 19, 19, 19, 19, 19, 19, 19, 19, 19, 19, 19, 19, 19, 19, 19, 19, 1, 20, 1, 1, 19, 1, 21, 22, 23, 24, 25, 18, 19, 19, 26, 19, 19, 27, 19, 28, 29, 30, 19, 31, 19, 32, 19, 19, 19, 33, 34, 19, 35, 1, 36, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1, 1 } ; static yy_state_type yy_last_accepting_state; static char *yy_last_accepting_cpos; extern int yy_flex_debug; int yy_flex_debug = 0; /* The intent behind this definition is that it'll catch * any uses of REJECT which flex missed. */ #define REJECT reject_used_but_not_detected #define yymore() yymore_used_but_not_detected #define YY_MORE_ADJ 0 #define YY_RESTORE_YY_MORE_OFFSET char *yytext; #line 1 "genvm-scan.l" /******************************** -*- C -*- **************************** * * GNU Smalltalk genvm tool - lexical analyzer * ***********************************************************************/ /*********************************************************************** * * Copyright 2003, 2006 Free Software Foundation, Inc. * Written by Paolo Bonzini. * * This file is part of GNU Smalltalk. * * GNU Smalltalk is free software; you can redistribute it and/or modify it * under the terms of the GNU General Public License as published by the Free * Software Foundation; either version 2, or (at your option) any later * version. * * Linking GNU Smalltalk statically or dynamically with other modules is * making a combined work based on GNU Smalltalk. Thus, the terms and * conditions of the GNU General Public License cover the whole * combination. * * In addition, as a special exception, the Free Software Foundation * give you permission to combine GNU Smalltalk with free software * programs or libraries that are released under the GNU LGPL and with * independent programs running under the GNU Smalltalk virtual machine. * * You may copy and distribute such a system following the terms of the * GNU GPL for GNU Smalltalk and the licenses of the other code * concerned, provided that you include the source code of that other * code when and as the GNU GPL requires distribution of source code. * * Note that people who make modified versions of GNU Smalltalk are not * obligated to grant this special exception for their modified * versions; it is their choice whether to do so. The GNU General * Public License gives permission to release a modified version without * this exception; this exception also makes it possible to release a * modified version which carries forward this exception. * * GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or * FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for * more details. * * You should have received a copy of the GNU General Public License along with * GNU Smalltalk; see the file COPYING. If not, write to the Free Software * Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * ***********************************************************************/ #line 64 "genvm-scan.l" #include "genvm.h" #include "genvm-parse.h" static int from = 0, depth = 0; #if !defined YY_FLEX_SUBMINOR_VERSION || YY_FLEX_SUBMINOR_VERSION < 31 int yylineno = 1; #endif #line 1335 "genvm-scan.c" #define INITIAL 0 #define C_ARGS 1 #define C_CODE 2 #define C_COMMENT 3 #define C_STRING 4 #define C_CHAR 5 #define CPP_CODE 6 #ifndef YY_NO_UNISTD_H /* Special case for "unistd.h", since it is non-ANSI. We include it way * down here because we want the user's section 1 to have been scanned first. * The user has a chance to override it with an option. */ #include #endif #ifndef YY_EXTRA_TYPE #define YY_EXTRA_TYPE void * #endif static int yy_init_globals (void ); /* Accessor methods to globals. These are made visible to non-reentrant scanners for convenience. */ int yylex_destroy (void ); int yyget_debug (void ); void yyset_debug (int debug_flag ); YY_EXTRA_TYPE yyget_extra (void ); void yyset_extra (YY_EXTRA_TYPE user_defined ); FILE *yyget_in (void ); void yyset_in (FILE * in_str ); FILE *yyget_out (void ); void yyset_out (FILE * out_str ); int yyget_leng (void ); char *yyget_text (void ); int yyget_lineno (void ); void yyset_lineno (int line_number ); /* Macros after this point can all be overridden by user definitions in * section 1. */ #ifndef YY_SKIP_YYWRAP #ifdef __cplusplus extern "C" int yywrap (void ); #else extern int yywrap (void ); #endif #endif #ifndef yytext_ptr static void yy_flex_strncpy (char *,yyconst char *,int ); #endif #ifdef YY_NEED_STRLEN static int yy_flex_strlen (yyconst char * ); #endif #ifndef YY_NO_INPUT #ifdef __cplusplus static int yyinput (void ); #else static int input (void ); #endif #endif /* Amount of stuff to slurp up with each read. */ #ifndef YY_READ_BUF_SIZE #ifdef __ia64__ /* On IA-64, the buffer size is 16k, not 8k */ #define YY_READ_BUF_SIZE 16384 #else #define YY_READ_BUF_SIZE 8192 #endif /* __ia64__ */ #endif /* Copy whatever the last rule matched to the standard output. */ #ifndef ECHO /* This used to be an fputs(), but since the string might contain NUL's, * we now use fwrite(). */ #define ECHO do { if (fwrite( yytext, yyleng, 1, yyout )) {} } while (0) #endif /* Gets input and stuffs it into "buf". number of characters read, or YY_NULL, * is returned in "result". */ #ifndef YY_INPUT #define YY_INPUT(buf,result,max_size) \ if ( YY_CURRENT_BUFFER_LVALUE->yy_is_interactive ) \ { \ int c = '*'; \ size_t n; \ for ( n = 0; n < max_size && \ (c = getc( yyin )) != EOF && c != '\n'; ++n ) \ buf[n] = (char) c; \ if ( c == '\n' ) \ buf[n++] = (char) c; \ if ( c == EOF && ferror( yyin ) ) \ YY_FATAL_ERROR( "input in flex scanner failed" ); \ result = n; \ } \ else \ { \ errno=0; \ while ( (result = fread(buf, 1, max_size, yyin))==0 && ferror(yyin)) \ { \ if( errno != EINTR) \ { \ YY_FATAL_ERROR( "input in flex scanner failed" ); \ break; \ } \ errno=0; \ clearerr(yyin); \ } \ }\ \ #endif /* No semi-colon after return; correct usage is to write "yyterminate();" - * we don't want an extra ';' after the "return" because that will cause * some compilers to complain about unreachable statements. */ #ifndef yyterminate #define yyterminate() return YY_NULL #endif /* Number of entries by which start-condition stack grows. */ #ifndef YY_START_STACK_INCR #define YY_START_STACK_INCR 25 #endif /* Report a fatal error. */ #ifndef YY_FATAL_ERROR #define YY_FATAL_ERROR(msg) yy_fatal_error( msg ) #endif /* end tables serialization structures and prototypes */ /* Default declaration of generated scanner - a define so the user can * easily add parameters. */ #ifndef YY_DECL #define YY_DECL_IS_OURS 1 extern int yylex (void); #define YY_DECL int yylex (void) #endif /* !YY_DECL */ /* Code executed at the beginning of each rule, after yytext and yyleng * have been set up. */ #ifndef YY_USER_ACTION #define YY_USER_ACTION #endif /* Code executed at the end of each rule. */ #ifndef YY_BREAK #define YY_BREAK break; #endif #define YY_RULE_SETUP \ if ( yyleng > 0 ) \ YY_CURRENT_BUFFER_LVALUE->yy_at_bol = \ (yytext[yyleng - 1] == '\n'); \ YY_USER_ACTION /** The main scanner function which does all the work. */ YY_DECL { register yy_state_type yy_current_state; register char *yy_cp, *yy_bp; register int yy_act; #line 73 "genvm-scan.l" #line 1532 "genvm-scan.c" if ( !(yy_init) ) { (yy_init) = 1; #ifdef YY_USER_INIT YY_USER_INIT; #endif if ( ! (yy_start) ) (yy_start) = 1; /* first start state */ if ( ! yyin ) yyin = stdin; if ( ! yyout ) yyout = stdout; if ( ! YY_CURRENT_BUFFER ) { yyensure_buffer_stack (); YY_CURRENT_BUFFER_LVALUE = yy_create_buffer(yyin,YY_BUF_SIZE ); } yy_load_buffer_state( ); } while ( 1 ) /* loops until end-of-file is reached */ { yy_cp = (yy_c_buf_p); /* Support of yytext. */ *yy_cp = (yy_hold_char); /* yy_bp points to the position in yy_ch_buf of the start of * the current run. */ yy_bp = yy_cp; yy_current_state = (yy_start); yy_current_state += YY_AT_BOL(); yy_match: while ( (yy_current_state = yy_nxt[yy_current_state][ yy_ec[YY_SC_TO_UI(*yy_cp)] ]) > 0 ) { if ( yy_accept[yy_current_state] ) { (yy_last_accepting_state) = yy_current_state; (yy_last_accepting_cpos) = yy_cp; } ++yy_cp; } yy_current_state = -yy_current_state; yy_find_action: yy_act = yy_accept[yy_current_state]; YY_DO_BEFORE_ACTION; do_action: /* This label is used only to access EOF actions. */ switch ( yy_act ) { /* beginning of action switch */ case 0: /* must back up */ /* undo the effects of YY_DO_BEFORE_ACTION */ *yy_cp = (yy_hold_char); yy_cp = (yy_last_accepting_cpos) + 1; yy_current_state = (yy_last_accepting_state); goto yy_find_action; /* All states know how to count lines. */ case 1: /* rule 1 can match eol */ YY_RULE_SETUP #line 77 "genvm-scan.l" { yylineno += yyleng; } YY_BREAK case 2: YY_RULE_SETUP #line 81 "genvm-scan.l" { } YY_BREAK case 3: YY_RULE_SETUP #line 86 "genvm-scan.l" return VM_TABLE; YY_BREAK case 4: YY_RULE_SETUP #line 87 "genvm-scan.l" return VM_OPERATION; YY_BREAK case 5: YY_RULE_SETUP #line 88 "genvm-scan.l" return VM_BYTECODE; YY_BREAK case 6: YY_RULE_SETUP #line 90 "genvm-scan.l" { printf ("%s", yytext); from = YY_START; BEGIN (CPP_CODE); } YY_BREAK case 7: YY_RULE_SETUP #line 96 "genvm-scan.l" { from = YY_START; BEGIN (C_COMMENT); } YY_BREAK case 8: #line 102 "genvm-scan.l" case 9: #line 103 "genvm-scan.l" case 10: YY_RULE_SETUP #line 103 "genvm-scan.l" { yylval.num = strtol(yytext, NULL, 0); return (NUMBER); } YY_BREAK case 11: YY_RULE_SETUP #line 108 "genvm-scan.l" return VM_DOTS; YY_BREAK case 12: YY_RULE_SETUP #line 109 "genvm-scan.l" return VM_MINUSMINUS; YY_BREAK case 13: YY_RULE_SETUP #line 111 "genvm-scan.l" yylval.text = strdup (yytext); return ID; YY_BREAK case 14: YY_RULE_SETUP #line 113 "genvm-scan.l" { yylval.ctext = "("; if (c_args_on_paren) BEGIN (C_ARGS); c_args_on_paren = false; depth = 1; return '('; } YY_BREAK case 15: /* rule 15 can match eol */ YY_RULE_SETUP #line 122 "genvm-scan.l" { yylineno += yyleng - 1; yylval.ctext = "{\n "; if (c_code_on_brace) BEGIN (C_CODE); c_code_on_brace = false; depth = 1; return '{'; } YY_BREAK case 16: YY_RULE_SETUP #line 132 "genvm-scan.l" return *yytext; YY_BREAK /* Learn how to skip strings. */ case 17: YY_RULE_SETUP #line 137 "genvm-scan.l" { yylval.text = yytext; from = YY_START; BEGIN (C_CHAR); return (EXPR); } YY_BREAK case 18: YY_RULE_SETUP #line 144 "genvm-scan.l" { yylval.text = yytext; from = YY_START; BEGIN (C_STRING); return (EXPR); } YY_BREAK case 19: YY_RULE_SETUP #line 153 "genvm-scan.l" { depth++; yylval.ctext = yytext; return EXPR; } YY_BREAK case 20: YY_RULE_SETUP #line 159 "genvm-scan.l" { yylval.ctext = yytext; return ','; } YY_BREAK case 21: YY_RULE_SETUP #line 164 "genvm-scan.l" { if (!--depth) { BEGIN (INITIAL); return ')'; } yylval.ctext = yytext; return EXPR; } YY_BREAK case 22: YY_RULE_SETUP #line 175 "genvm-scan.l" { yylval.ctext = yytext; return (EXPR); } YY_BREAK case 23: YY_RULE_SETUP #line 182 "genvm-scan.l" { depth++; yylval.ctext = yytext; return EXPR; } YY_BREAK case 24: YY_RULE_SETUP #line 188 "genvm-scan.l" { if (!--depth) { BEGIN (INITIAL); return '}'; } yylval.ctext = yytext; return EXPR; } YY_BREAK case 25: /* rule 25 can match eol */ YY_RULE_SETUP #line 199 "genvm-scan.l" { yylineno++; yylval.ctext = "\n "; return (EXPR); } YY_BREAK case 26: YY_RULE_SETUP #line 205 "genvm-scan.l" { yylval.ctext = yytext; return (EXPR); } YY_BREAK /* Characters and strings have different terminations... */ case 27: YY_RULE_SETUP #line 213 "genvm-scan.l" { yylval.text = yytext; BEGIN (from); return (EXPR); } YY_BREAK case 28: YY_RULE_SETUP #line 221 "genvm-scan.l" { yylval.text = yytext; BEGIN (from); return (EXPR); } YY_BREAK /* ... but otherwise they're the same. */ case 29: YY_RULE_SETUP #line 230 "genvm-scan.l" { yylineno += (yytext[1] == '\n'); yylval.text = yytext; return (EXPR); } YY_BREAK case 30: YY_RULE_SETUP #line 236 "genvm-scan.l" { yylineno += (yytext[0] == '\n'); yylval.text = yytext; return (EXPR); } YY_BREAK /* And so are comments. */ case 31: /* rule 31 can match eol */ YY_RULE_SETUP #line 245 "genvm-scan.l" { yylineno++; } YY_BREAK case 32: /* rule 32 can match eol */ YY_RULE_SETUP #line 249 "genvm-scan.l" { } YY_BREAK case 33: YY_RULE_SETUP #line 252 "genvm-scan.l" { BEGIN (from); } YY_BREAK /* And preprocessor code; this however is printed to stdout. */ case 34: /* rule 34 can match eol */ YY_RULE_SETUP #line 259 "genvm-scan.l" { printf("%s", yytext); yylineno += yytext[yyleng - 1] == '\n'; } YY_BREAK case 35: *yy_cp = (yy_hold_char); /* undo effects of setting up yytext */ (yy_c_buf_p) = yy_cp -= 1; YY_DO_BEFORE_ACTION; /* set up yytext again */ YY_RULE_SETUP #line 263 "genvm-scan.l" { printf("%s", yytext); } YY_BREAK case 36: /* rule 36 can match eol */ YY_RULE_SETUP #line 266 "genvm-scan.l" { printf("%s", yytext); yylineno += yyleng; BEGIN (from); } YY_BREAK case 37: YY_RULE_SETUP #line 273 "genvm-scan.l" ECHO; YY_BREAK #line 1925 "genvm-scan.c" case YY_STATE_EOF(INITIAL): case YY_STATE_EOF(C_ARGS): case YY_STATE_EOF(C_CODE): case YY_STATE_EOF(C_COMMENT): case YY_STATE_EOF(C_STRING): case YY_STATE_EOF(C_CHAR): case YY_STATE_EOF(CPP_CODE): yyterminate(); case YY_END_OF_BUFFER: { /* Amount of text matched not including the EOB char. */ int yy_amount_of_matched_text = (int) (yy_cp - (yytext_ptr)) - 1; /* Undo the effects of YY_DO_BEFORE_ACTION. */ *yy_cp = (yy_hold_char); YY_RESTORE_YY_MORE_OFFSET if ( YY_CURRENT_BUFFER_LVALUE->yy_buffer_status == YY_BUFFER_NEW ) { /* We're scanning a new file or input source. It's * possible that this happened because the user * just pointed yyin at a new source and called * yylex(). If so, then we have to assure * consistency between YY_CURRENT_BUFFER and our * globals. Here is the right place to do so, because * this is the first action (other than possibly a * back-up) that will match for the new input source. */ (yy_n_chars) = YY_CURRENT_BUFFER_LVALUE->yy_n_chars; YY_CURRENT_BUFFER_LVALUE->yy_input_file = yyin; YY_CURRENT_BUFFER_LVALUE->yy_buffer_status = YY_BUFFER_NORMAL; } /* Note that here we test for yy_c_buf_p "<=" to the position * of the first EOB in the buffer, since yy_c_buf_p will * already have been incremented past the NUL character * (since all states make transitions on EOB to the * end-of-buffer state). Contrast this with the test * in input(). */ if ( (yy_c_buf_p) <= &YY_CURRENT_BUFFER_LVALUE->yy_ch_buf[(yy_n_chars)] ) { /* This was really a NUL. */ yy_state_type yy_next_state; (yy_c_buf_p) = (yytext_ptr) + yy_amount_of_matched_text; yy_current_state = yy_get_previous_state( ); /* Okay, we're now positioned to make the NUL * transition. We couldn't have * yy_get_previous_state() go ahead and do it * for us because it doesn't know how to deal * with the possibility of jamming (and we don't * want to build jamming into it because then it * will run more slowly). */ yy_next_state = yy_try_NUL_trans( yy_current_state ); yy_bp = (yytext_ptr) + YY_MORE_ADJ; if ( yy_next_state ) { /* Consume the NUL. */ yy_cp = ++(yy_c_buf_p); yy_current_state = yy_next_state; goto yy_match; } else { yy_cp = (yy_c_buf_p); goto yy_find_action; } } else switch ( yy_get_next_buffer( ) ) { case EOB_ACT_END_OF_FILE: { (yy_did_buffer_switch_on_eof) = 0; if ( yywrap( ) ) { /* Note: because we've taken care in * yy_get_next_buffer() to have set up * yytext, we can now set up * yy_c_buf_p so that if some total * hoser (like flex itself) wants to * call the scanner after we return the * YY_NULL, it'll still work - another * YY_NULL will get returned. */ (yy_c_buf_p) = (yytext_ptr) + YY_MORE_ADJ; yy_act = YY_STATE_EOF(YY_START); goto do_action; } else { if ( ! (yy_did_buffer_switch_on_eof) ) YY_NEW_FILE; } break; } case EOB_ACT_CONTINUE_SCAN: (yy_c_buf_p) = (yytext_ptr) + yy_amount_of_matched_text; yy_current_state = yy_get_previous_state( ); yy_cp = (yy_c_buf_p); yy_bp = (yytext_ptr) + YY_MORE_ADJ; goto yy_match; case EOB_ACT_LAST_MATCH: (yy_c_buf_p) = &YY_CURRENT_BUFFER_LVALUE->yy_ch_buf[(yy_n_chars)]; yy_current_state = yy_get_previous_state( ); yy_cp = (yy_c_buf_p); yy_bp = (yytext_ptr) + YY_MORE_ADJ; goto yy_find_action; } break; } default: YY_FATAL_ERROR( "fatal flex scanner internal error--no action found" ); } /* end of action switch */ } /* end of scanning one token */ } /* end of yylex */ /* yy_get_next_buffer - try to read in a new buffer * * Returns a code representing an action: * EOB_ACT_LAST_MATCH - * EOB_ACT_CONTINUE_SCAN - continue scanning from current position * EOB_ACT_END_OF_FILE - end of file */ static int yy_get_next_buffer (void) { register char *dest = YY_CURRENT_BUFFER_LVALUE->yy_ch_buf; register char *source = (yytext_ptr); register int number_to_move, i; int ret_val; if ( (yy_c_buf_p) > &YY_CURRENT_BUFFER_LVALUE->yy_ch_buf[(yy_n_chars) + 1] ) YY_FATAL_ERROR( "fatal flex scanner internal error--end of buffer missed" ); if ( YY_CURRENT_BUFFER_LVALUE->yy_fill_buffer == 0 ) { /* Don't try to fill the buffer, so this is an EOF. */ if ( (yy_c_buf_p) - (yytext_ptr) - YY_MORE_ADJ == 1 ) { /* We matched a single character, the EOB, so * treat this as a final EOF. */ return EOB_ACT_END_OF_FILE; } else { /* We matched some text prior to the EOB, first * process it. */ return EOB_ACT_LAST_MATCH; } } /* Try to read more data. */ /* First move last chars to start of buffer. */ number_to_move = (int) ((yy_c_buf_p) - (yytext_ptr)) - 1; for ( i = 0; i < number_to_move; ++i ) *(dest++) = *(source++); if ( YY_CURRENT_BUFFER_LVALUE->yy_buffer_status == YY_BUFFER_EOF_PENDING ) /* don't do the read, it's not guaranteed to return an EOF, * just force an EOF */ YY_CURRENT_BUFFER_LVALUE->yy_n_chars = (yy_n_chars) = 0; else { int num_to_read = YY_CURRENT_BUFFER_LVALUE->yy_buf_size - number_to_move - 1; while ( num_to_read <= 0 ) { /* Not enough room in the buffer - grow it. */ /* just a shorter name for the current buffer */ YY_BUFFER_STATE b = YY_CURRENT_BUFFER; int yy_c_buf_p_offset = (int) ((yy_c_buf_p) - b->yy_ch_buf); if ( b->yy_is_our_buffer ) { int new_size = b->yy_buf_size * 2; if ( new_size <= 0 ) b->yy_buf_size += b->yy_buf_size / 8; else b->yy_buf_size *= 2; b->yy_ch_buf = (char *) /* Include room in for 2 EOB chars. */ yyrealloc((void *) b->yy_ch_buf,b->yy_buf_size + 2 ); } else /* Can't grow it, we don't own it. */ b->yy_ch_buf = 0; if ( ! b->yy_ch_buf ) YY_FATAL_ERROR( "fatal error - scanner input buffer overflow" ); (yy_c_buf_p) = &b->yy_ch_buf[yy_c_buf_p_offset]; num_to_read = YY_CURRENT_BUFFER_LVALUE->yy_buf_size - number_to_move - 1; } if ( num_to_read > YY_READ_BUF_SIZE ) num_to_read = YY_READ_BUF_SIZE; /* Read in more data. */ YY_INPUT( (&YY_CURRENT_BUFFER_LVALUE->yy_ch_buf[number_to_move]), (yy_n_chars), (size_t) num_to_read ); YY_CURRENT_BUFFER_LVALUE->yy_n_chars = (yy_n_chars); } if ( (yy_n_chars) == 0 ) { if ( number_to_move == YY_MORE_ADJ ) { ret_val = EOB_ACT_END_OF_FILE; yyrestart(yyin ); } else { ret_val = EOB_ACT_LAST_MATCH; YY_CURRENT_BUFFER_LVALUE->yy_buffer_status = YY_BUFFER_EOF_PENDING; } } else ret_val = EOB_ACT_CONTINUE_SCAN; if ((yy_size_t) ((yy_n_chars) + number_to_move) > YY_CURRENT_BUFFER_LVALUE->yy_buf_size) { /* Extend the array by 50%, plus the number we really need. */ yy_size_t new_size = (yy_n_chars) + number_to_move + ((yy_n_chars) >> 1); YY_CURRENT_BUFFER_LVALUE->yy_ch_buf = (char *) yyrealloc((void *) YY_CURRENT_BUFFER_LVALUE->yy_ch_buf,new_size ); if ( ! YY_CURRENT_BUFFER_LVALUE->yy_ch_buf ) YY_FATAL_ERROR( "out of dynamic memory in yy_get_next_buffer()" ); } (yy_n_chars) += number_to_move; YY_CURRENT_BUFFER_LVALUE->yy_ch_buf[(yy_n_chars)] = YY_END_OF_BUFFER_CHAR; YY_CURRENT_BUFFER_LVALUE->yy_ch_buf[(yy_n_chars) + 1] = YY_END_OF_BUFFER_CHAR; (yytext_ptr) = &YY_CURRENT_BUFFER_LVALUE->yy_ch_buf[0]; return ret_val; } /* yy_get_previous_state - get the state just before the EOB char was reached */ static yy_state_type yy_get_previous_state (void) { register yy_state_type yy_current_state; register char *yy_cp; yy_current_state = (yy_start); yy_current_state += YY_AT_BOL(); for ( yy_cp = (yytext_ptr) + YY_MORE_ADJ; yy_cp < (yy_c_buf_p); ++yy_cp ) { yy_current_state = yy_nxt[yy_current_state][(*yy_cp ? yy_ec[YY_SC_TO_UI(*yy_cp)] : 1)]; if ( yy_accept[yy_current_state] ) { (yy_last_accepting_state) = yy_current_state; (yy_last_accepting_cpos) = yy_cp; } } return yy_current_state; } /* yy_try_NUL_trans - try to make a transition on the NUL character * * synopsis * next_state = yy_try_NUL_trans( current_state ); */ static yy_state_type yy_try_NUL_trans (yy_state_type yy_current_state ) { register int yy_is_jam; register char *yy_cp = (yy_c_buf_p); yy_current_state = yy_nxt[yy_current_state][1]; yy_is_jam = (yy_current_state <= 0); if ( ! yy_is_jam ) { if ( yy_accept[yy_current_state] ) { (yy_last_accepting_state) = yy_current_state; (yy_last_accepting_cpos) = yy_cp; } } return yy_is_jam ? 0 : yy_current_state; } #ifndef YY_NO_INPUT #ifdef __cplusplus static int yyinput (void) #else static int input (void) #endif { int c; *(yy_c_buf_p) = (yy_hold_char); if ( *(yy_c_buf_p) == YY_END_OF_BUFFER_CHAR ) { /* yy_c_buf_p now points to the character we want to return. * If this occurs *before* the EOB characters, then it's a * valid NUL; if not, then we've hit the end of the buffer. */ if ( (yy_c_buf_p) < &YY_CURRENT_BUFFER_LVALUE->yy_ch_buf[(yy_n_chars)] ) /* This was really a NUL. */ *(yy_c_buf_p) = '\0'; else { /* need more input */ int offset = (yy_c_buf_p) - (yytext_ptr); ++(yy_c_buf_p); switch ( yy_get_next_buffer( ) ) { case EOB_ACT_LAST_MATCH: /* This happens because yy_g_n_b() * sees that we've accumulated a * token and flags that we need to * try matching the token before * proceeding. But for input(), * there's no matching to consider. * So convert the EOB_ACT_LAST_MATCH * to EOB_ACT_END_OF_FILE. */ /* Reset buffer status. */ yyrestart(yyin ); /*FALLTHROUGH*/ case EOB_ACT_END_OF_FILE: { if ( yywrap( ) ) return EOF; if ( ! (yy_did_buffer_switch_on_eof) ) YY_NEW_FILE; #ifdef __cplusplus return yyinput(); #else return input(); #endif } case EOB_ACT_CONTINUE_SCAN: (yy_c_buf_p) = (yytext_ptr) + offset; break; } } } c = *(unsigned char *) (yy_c_buf_p); /* cast for 8-bit char's */ *(yy_c_buf_p) = '\0'; /* preserve yytext */ (yy_hold_char) = *++(yy_c_buf_p); YY_CURRENT_BUFFER_LVALUE->yy_at_bol = (c == '\n'); return c; } #endif /* ifndef YY_NO_INPUT */ /** Immediately switch to a different input stream. * @param input_file A readable stream. * * @note This function does not reset the start condition to @c INITIAL . */ void yyrestart (FILE * input_file ) { if ( ! YY_CURRENT_BUFFER ){ yyensure_buffer_stack (); YY_CURRENT_BUFFER_LVALUE = yy_create_buffer(yyin,YY_BUF_SIZE ); } yy_init_buffer(YY_CURRENT_BUFFER,input_file ); yy_load_buffer_state( ); } /** Switch to a different input buffer. * @param new_buffer The new input buffer. * */ void yy_switch_to_buffer (YY_BUFFER_STATE new_buffer ) { /* TODO. We should be able to replace this entire function body * with * yypop_buffer_state(); * yypush_buffer_state(new_buffer); */ yyensure_buffer_stack (); if ( YY_CURRENT_BUFFER == new_buffer ) return; if ( YY_CURRENT_BUFFER ) { /* Flush out information for old buffer. */ *(yy_c_buf_p) = (yy_hold_char); YY_CURRENT_BUFFER_LVALUE->yy_buf_pos = (yy_c_buf_p); YY_CURRENT_BUFFER_LVALUE->yy_n_chars = (yy_n_chars); } YY_CURRENT_BUFFER_LVALUE = new_buffer; yy_load_buffer_state( ); /* We don't actually know whether we did this switch during * EOF (yywrap()) processing, but the only time this flag * is looked at is after yywrap() is called, so it's safe * to go ahead and always set it. */ (yy_did_buffer_switch_on_eof) = 1; } static void yy_load_buffer_state (void) { (yy_n_chars) = YY_CURRENT_BUFFER_LVALUE->yy_n_chars; (yytext_ptr) = (yy_c_buf_p) = YY_CURRENT_BUFFER_LVALUE->yy_buf_pos; yyin = YY_CURRENT_BUFFER_LVALUE->yy_input_file; (yy_hold_char) = *(yy_c_buf_p); } /** Allocate and initialize an input buffer state. * @param file A readable stream. * @param size The character buffer size in bytes. When in doubt, use @c YY_BUF_SIZE. * * @return the allocated buffer state. */ YY_BUFFER_STATE yy_create_buffer (FILE * file, int size ) { YY_BUFFER_STATE b; b = (YY_BUFFER_STATE) yyalloc(sizeof( struct yy_buffer_state ) ); if ( ! b ) YY_FATAL_ERROR( "out of dynamic memory in yy_create_buffer()" ); b->yy_buf_size = size; /* yy_ch_buf has to be 2 characters longer than the size given because * we need to put in 2 end-of-buffer characters. */ b->yy_ch_buf = (char *) yyalloc(b->yy_buf_size + 2 ); if ( ! b->yy_ch_buf ) YY_FATAL_ERROR( "out of dynamic memory in yy_create_buffer()" ); b->yy_is_our_buffer = 1; yy_init_buffer(b,file ); return b; } /** Destroy the buffer. * @param b a buffer created with yy_create_buffer() * */ void yy_delete_buffer (YY_BUFFER_STATE b ) { if ( ! b ) return; if ( b == YY_CURRENT_BUFFER ) /* Not sure if we should pop here. */ YY_CURRENT_BUFFER_LVALUE = (YY_BUFFER_STATE) 0; if ( b->yy_is_our_buffer ) yyfree((void *) b->yy_ch_buf ); yyfree((void *) b ); } /* Initializes or reinitializes a buffer. * This function is sometimes called more than once on the same buffer, * such as during a yyrestart() or at EOF. */ static void yy_init_buffer (YY_BUFFER_STATE b, FILE * file ) { int oerrno = errno; yy_flush_buffer(b ); b->yy_input_file = file; b->yy_fill_buffer = 1; /* If b is the current buffer, then yy_init_buffer was _probably_ * called from yyrestart() or through yy_get_next_buffer. * In that case, we don't want to reset the lineno or column. */ if (b != YY_CURRENT_BUFFER){ b->yy_bs_lineno = 1; b->yy_bs_column = 0; } b->yy_is_interactive = 0; errno = oerrno; } /** Discard all buffered characters. On the next scan, YY_INPUT will be called. * @param b the buffer state to be flushed, usually @c YY_CURRENT_BUFFER. * */ void yy_flush_buffer (YY_BUFFER_STATE b ) { if ( ! b ) return; b->yy_n_chars = 0; /* We always need two end-of-buffer characters. The first causes * a transition to the end-of-buffer state. The second causes * a jam in that state. */ b->yy_ch_buf[0] = YY_END_OF_BUFFER_CHAR; b->yy_ch_buf[1] = YY_END_OF_BUFFER_CHAR; b->yy_buf_pos = &b->yy_ch_buf[0]; b->yy_at_bol = 1; b->yy_buffer_status = YY_BUFFER_NEW; if ( b == YY_CURRENT_BUFFER ) yy_load_buffer_state( ); } /** Pushes the new state onto the stack. The new state becomes * the current state. This function will allocate the stack * if necessary. * @param new_buffer The new state. * */ void yypush_buffer_state (YY_BUFFER_STATE new_buffer ) { if (new_buffer == NULL) return; yyensure_buffer_stack(); /* This block is copied from yy_switch_to_buffer. */ if ( YY_CURRENT_BUFFER ) { /* Flush out information for old buffer. */ *(yy_c_buf_p) = (yy_hold_char); YY_CURRENT_BUFFER_LVALUE->yy_buf_pos = (yy_c_buf_p); YY_CURRENT_BUFFER_LVALUE->yy_n_chars = (yy_n_chars); } /* Only push if top exists. Otherwise, replace top. */ if (YY_CURRENT_BUFFER) (yy_buffer_stack_top)++; YY_CURRENT_BUFFER_LVALUE = new_buffer; /* copied from yy_switch_to_buffer. */ yy_load_buffer_state( ); (yy_did_buffer_switch_on_eof) = 1; } /** Removes and deletes the top of the stack, if present. * The next element becomes the new top. * */ void yypop_buffer_state (void) { if (!YY_CURRENT_BUFFER) return; yy_delete_buffer(YY_CURRENT_BUFFER ); YY_CURRENT_BUFFER_LVALUE = NULL; if ((yy_buffer_stack_top) > 0) --(yy_buffer_stack_top); if (YY_CURRENT_BUFFER) { yy_load_buffer_state( ); (yy_did_buffer_switch_on_eof) = 1; } } /* Allocates the stack if it does not exist. * Guarantees space for at least one push. */ static void yyensure_buffer_stack (void) { int num_to_alloc; if (!(yy_buffer_stack)) { /* First allocation is just for 2 elements, since we don't know if this * scanner will even need a stack. We use 2 instead of 1 to avoid an * immediate realloc on the next call. */ num_to_alloc = 1; (yy_buffer_stack) = (struct yy_buffer_state**)yyalloc (num_to_alloc * sizeof(struct yy_buffer_state*) ); if ( ! (yy_buffer_stack) ) YY_FATAL_ERROR( "out of dynamic memory in yyensure_buffer_stack()" ); memset((yy_buffer_stack), 0, num_to_alloc * sizeof(struct yy_buffer_state*)); (yy_buffer_stack_max) = num_to_alloc; (yy_buffer_stack_top) = 0; return; } if ((yy_buffer_stack_top) >= ((yy_buffer_stack_max)) - 1){ /* Increase the buffer to prepare for a possible push. */ int grow_size = 8 /* arbitrary grow size */; num_to_alloc = (yy_buffer_stack_max) + grow_size; (yy_buffer_stack) = (struct yy_buffer_state**)yyrealloc ((yy_buffer_stack), num_to_alloc * sizeof(struct yy_buffer_state*) ); if ( ! (yy_buffer_stack) ) YY_FATAL_ERROR( "out of dynamic memory in yyensure_buffer_stack()" ); /* zero only the new slots.*/ memset((yy_buffer_stack) + (yy_buffer_stack_max), 0, grow_size * sizeof(struct yy_buffer_state*)); (yy_buffer_stack_max) = num_to_alloc; } } /** Setup the input buffer state to scan directly from a user-specified character buffer. * @param base the character buffer * @param size the size in bytes of the character buffer * * @return the newly allocated buffer state object. */ YY_BUFFER_STATE yy_scan_buffer (char * base, yy_size_t size ) { YY_BUFFER_STATE b; if ( size < 2 || base[size-2] != YY_END_OF_BUFFER_CHAR || base[size-1] != YY_END_OF_BUFFER_CHAR ) /* They forgot to leave room for the EOB's. */ return 0; b = (YY_BUFFER_STATE) yyalloc(sizeof( struct yy_buffer_state ) ); if ( ! b ) YY_FATAL_ERROR( "out of dynamic memory in yy_scan_buffer()" ); b->yy_buf_size = size - 2; /* "- 2" to take care of EOB's */ b->yy_buf_pos = b->yy_ch_buf = base; b->yy_is_our_buffer = 0; b->yy_input_file = 0; b->yy_n_chars = b->yy_buf_size; b->yy_is_interactive = 0; b->yy_at_bol = 1; b->yy_fill_buffer = 0; b->yy_buffer_status = YY_BUFFER_NEW; yy_switch_to_buffer(b ); return b; } /** Setup the input buffer state to scan a string. The next call to yylex() will * scan from a @e copy of @a str. * @param yystr a NUL-terminated string to scan * * @return the newly allocated buffer state object. * @note If you want to scan bytes that may contain NUL values, then use * yy_scan_bytes() instead. */ YY_BUFFER_STATE yy_scan_string (yyconst char * yystr ) { return yy_scan_bytes(yystr,strlen(yystr) ); } /** Setup the input buffer state to scan the given bytes. The next call to yylex() will * scan from a @e copy of @a bytes. * @param yybytes the byte buffer to scan * @param _yybytes_len the number of bytes in the buffer pointed to by @a bytes. * * @return the newly allocated buffer state object. */ YY_BUFFER_STATE yy_scan_bytes (yyconst char * yybytes, int _yybytes_len ) { YY_BUFFER_STATE b; char *buf; yy_size_t n; int i; /* Get memory for full buffer, including space for trailing EOB's. */ n = _yybytes_len + 2; buf = (char *) yyalloc(n ); if ( ! buf ) YY_FATAL_ERROR( "out of dynamic memory in yy_scan_bytes()" ); for ( i = 0; i < _yybytes_len; ++i ) buf[i] = yybytes[i]; buf[_yybytes_len] = buf[_yybytes_len+1] = YY_END_OF_BUFFER_CHAR; b = yy_scan_buffer(buf,n ); if ( ! b ) YY_FATAL_ERROR( "bad buffer in yy_scan_bytes()" ); /* It's okay to grow etc. this buffer, and we should throw it * away when we're done. */ b->yy_is_our_buffer = 1; return b; } #ifndef YY_EXIT_FAILURE #define YY_EXIT_FAILURE 2 #endif static void yy_fatal_error (yyconst char* msg ) { (void) fprintf( stderr, "%s\n", msg ); exit( YY_EXIT_FAILURE ); } /* Redefine yyless() so it works in section 3 code. */ #undef yyless #define yyless(n) \ do \ { \ /* Undo effects of setting up yytext. */ \ int yyless_macro_arg = (n); \ YY_LESS_LINENO(yyless_macro_arg);\ yytext[yyleng] = (yy_hold_char); \ (yy_c_buf_p) = yytext + yyless_macro_arg; \ (yy_hold_char) = *(yy_c_buf_p); \ *(yy_c_buf_p) = '\0'; \ yyleng = yyless_macro_arg; \ } \ while ( 0 ) /* Accessor methods (get/set functions) to struct members. */ /** Get the current line number. * */ int yyget_lineno (void) { return yylineno; } /** Get the input stream. * */ FILE *yyget_in (void) { return yyin; } /** Get the output stream. * */ FILE *yyget_out (void) { return yyout; } /** Get the length of the current token. * */ int yyget_leng (void) { return yyleng; } /** Get the current token. * */ char *yyget_text (void) { return yytext; } /** Set the current line number. * @param line_number * */ void yyset_lineno (int line_number ) { yylineno = line_number; } /** Set the input stream. This does not discard the current * input buffer. * @param in_str A readable stream. * * @see yy_switch_to_buffer */ void yyset_in (FILE * in_str ) { yyin = in_str ; } void yyset_out (FILE * out_str ) { yyout = out_str ; } int yyget_debug (void) { return yy_flex_debug; } void yyset_debug (int bdebug ) { yy_flex_debug = bdebug ; } static int yy_init_globals (void) { /* Initialization is the same as for the non-reentrant scanner. * This function is called from yylex_destroy(), so don't allocate here. */ (yy_buffer_stack) = 0; (yy_buffer_stack_top) = 0; (yy_buffer_stack_max) = 0; (yy_c_buf_p) = (char *) 0; (yy_init) = 0; (yy_start) = 0; /* Defined in main.c */ #ifdef YY_STDINIT yyin = stdin; yyout = stdout; #else yyin = (FILE *) 0; yyout = (FILE *) 0; #endif /* For future reference: Set errno on error, since we are called by * yylex_init() */ return 0; } /* yylex_destroy is for both reentrant and non-reentrant scanners. */ int yylex_destroy (void) { /* Pop the buffer stack, destroying each element. */ while(YY_CURRENT_BUFFER){ yy_delete_buffer(YY_CURRENT_BUFFER ); YY_CURRENT_BUFFER_LVALUE = NULL; yypop_buffer_state(); } /* Destroy the stack itself. */ yyfree((yy_buffer_stack) ); (yy_buffer_stack) = NULL; /* Reset the globals. This is important in a non-reentrant scanner so the next time * yylex() is called, initialization will occur. */ yy_init_globals( ); return 0; } /* * Internal utility routines. */ #ifndef yytext_ptr static void yy_flex_strncpy (char* s1, yyconst char * s2, int n ) { register int i; for ( i = 0; i < n; ++i ) s1[i] = s2[i]; } #endif #ifdef YY_NEED_STRLEN static int yy_flex_strlen (yyconst char * s ) { register int n; for ( n = 0; s[n]; ++n ) ; return n; } #endif void *yyalloc (yy_size_t size ) { return (void *) malloc( size ); } void *yyrealloc (void * ptr, yy_size_t size ) { /* The cast to (char *) in the following accommodates both * implementations that use char* generic pointers, and those * that use void* generic pointers. It works with the latter * because both ANSI C and C++ allow castless assignment from * any pointer type to void*, and deal with argument conversions * as though doing an assignment. */ return (void *) realloc( (char *) ptr, size ); } void yyfree (void * ptr ) { free( (char *) ptr ); /* see yyrealloc() for (char *) cast */ } #define YYTABLES_NAME "yytables" #line 273 "genvm-scan.l" smalltalk-3.2.5/libgst/sysdep.c0000644000175000017500000000664012123404352013367 00000000000000/******************************** -*- C -*- **************************** * * System specific implementation module. * * This module contains implementations of various operating system * specific routines. This module should encapsulate most (or all) * of these calls so that the rest of the code is portable. * * ***********************************************************************/ /*********************************************************************** * * Copyright 1988,89,90,91,92,94,95,99,2000,2001,2002,2003,2006,2007,2008,2009 * Free Software Foundation, Inc. * Written by Steve Byrne. * * This file is part of GNU Smalltalk. * * GNU Smalltalk is free software; you can redistribute it and/or modify it * under the terms of the GNU General Public License as published by the Free * Software Foundation; either version 2, or (at your option) any later * version. * * Linking GNU Smalltalk statically or dynamically with other modules is * making a combined work based on GNU Smalltalk. Thus, the terms and * conditions of the GNU General Public License cover the whole * combination. * * In addition, as a special exception, the Free Software Foundation * give you permission to combine GNU Smalltalk with free software * programs or libraries that are released under the GNU LGPL and with * independent programs running under the GNU Smalltalk virtual machine. * * You may copy and distribute such a system following the terms of the * GNU GPL for GNU Smalltalk and the licenses of the other code * concerned, provided that you include the source code of that other * code when and as the GNU GPL requires distribution of source code. * * Note that people who make modified versions of GNU Smalltalk are not * obligated to grant this special exception for their modified * versions; it is their choice whether to do so. The GNU General * Public License gives permission to release a modified version without * this exception; this exception also makes it possible to release a * modified version which carries forward this exception. * * GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or * FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for * more details. * * You should have received a copy of the GNU General Public License along with * GNU Smalltalk; see the file COPYING. If not, write to the Free Software * Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * ***********************************************************************/ #include "sysdep/common/time.c" #include "sysdep/common/files.c" #if defined __CYGWIN__ #include "sysdep/cygwin/findexec.c" #include "sysdep/cygwin/timer.c" #include "sysdep/cygwin/signals.c" #include "sysdep/cygwin/events.c" #include "sysdep/cygwin/time.c" #include "sysdep/cygwin/files.c" #include "sysdep/cygwin/mem.c" #elif !defined WIN32 #include #include "sysdep/posix/findexec.c" #include "sysdep/posix/timer.c" #include "sysdep/posix/signals.c" #include "sysdep/posix/events.c" #include "sysdep/posix/time.c" #include "sysdep/posix/files.c" #include "sysdep/posix/mem.c" #else #include "sysdep/win32/findexec.c" #include "sysdep/win32/timer.c" #include "sysdep/win32/signals.c" #include "sysdep/win32/events.c" #include "sysdep/win32/time.c" #include "sysdep/win32/files.c" #include "sysdep/win32/mem.c" #endif smalltalk-3.2.5/libgst/str.c0000644000175000017500000000733012123404352012665 00000000000000/******************************** -*- C -*- **************************** * * Simple String Functions * * ***********************************************************************/ /*********************************************************************** * * Copyright 1988,89,90,91,92,94,95,99,2000,2001,2002,2006 * Free Software Foundation, Inc. * Written by Steve Byrne. * * This file is part of GNU Smalltalk. * * GNU Smalltalk is free software; you can redistribute it and/or modify it * under the terms of the GNU General Public License as published by the Free * Software Foundation; either version 2, or (at your option) any later * version. * * Linking GNU Smalltalk statically or dynamically with other modules is * making a combined work based on GNU Smalltalk. Thus, the terms and * conditions of the GNU General Public License cover the whole * combination. * * In addition, as a special exception, the Free Software Foundation * give you permission to combine GNU Smalltalk with free software * programs or libraries that are released under the GNU LGPL and with * independent programs running under the GNU Smalltalk virtual machine. * * You may copy and distribute such a system following the terms of the * GNU GPL for GNU Smalltalk and the licenses of the other code * concerned, provided that you include the source code of that other * code when and as the GNU GPL requires distribution of source code. * * Note that people who make modified versions of GNU Smalltalk are not * obligated to grant this special exception for their modified * versions; it is their choice whether to do so. The GNU General * Public License gives permission to release a modified version without * this exception; this exception also makes it possible to release a * modified version which carries forward this exception. * * GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or * FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for * more details. * * You should have received a copy of the GNU General Public License along with * GNU Smalltalk; see the file COPYING. If not, write to the Free Software * Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * ***********************************************************************/ #include "gstpriv.h" #define STRING_BASE_SIZE 128 /* This variable holds the base of the buffer maintained by this module. */ static char *buf_base = NULL; /* This variable holds the size of the currently filled part of the buffer. */ static size_t cur_len = 0; /* This variable holds the current size of the buffer. */ static size_t max_buf_len = 0; void _gst_add_buf_pointer (PTR ptr) { if (cur_len + sizeof (PTR) > max_buf_len) { if (max_buf_len) { max_buf_len += (max_buf_len / 2) + sizeof (PTR); buf_base = (char *) xrealloc (buf_base, max_buf_len); } else { max_buf_len = STRING_BASE_SIZE; buf_base = (char *) xmalloc (max_buf_len); } } *((PTR *) (buf_base + cur_len)) = ptr; cur_len += sizeof (PTR); } void _gst_add_buf_data (PTR ptr, int n) { if (cur_len + n > max_buf_len) { if (max_buf_len) { max_buf_len += (max_buf_len / 2) + n; buf_base = (char *) xrealloc (buf_base, max_buf_len); } else { max_buf_len = STRING_BASE_SIZE + n; buf_base = (char *) xmalloc (max_buf_len); } } memcpy ((PTR *) (buf_base + cur_len), ptr, n); cur_len += n; } PTR _gst_copy_buffer (PTR where) { memcpy (where, buf_base, cur_len); cur_len = 0; return (where); } void _gst_reset_buffer (void) { cur_len = 0; } size_t _gst_buffer_size (void) { return (cur_len); } smalltalk-3.2.5/libgst/genbc-impl.c0000644000175000017500000013343312130455565014110 00000000000000/* A Bison parser, made by GNU Bison 2.5. */ /* Bison implementation for Yacc-like parsers in C Copyright (C) 1984, 1989-1990, 2000-2011 Free Software Foundation, Inc. This program is free software: you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation, either version 3 of the License, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program. If not, see . */ /* As a special exception, you may create a larger work that contains part or all of the Bison parser skeleton and distribute that work under terms of your choice, so long as that work isn't itself a parser generator using the skeleton or a modified version thereof as a parser skeleton. Alternatively, if you modify or redistribute the parser skeleton itself, you may (at your option) remove this special exception, which will cause the skeleton and the resulting Bison output files to be licensed under the GNU General Public License without this special exception. This special exception was added by the Free Software Foundation in version 2.2 of Bison. */ /* C LALR(1) parser skeleton written by Richard Stallman, by simplifying the original so-called "semantic" parser. */ /* All symbols defined below should begin with yy or YY, to avoid infringing on user name space. This should be done even for local variables, as they might otherwise be expanded by user macros. There are some unavoidable exceptions within include files to define necessary library symbols; they are noted "INFRINGES ON USER NAME SPACE" below. */ /* Identify Bison output. */ #define YYBISON 1 /* Bison version. */ #define YYBISON_VERSION "2.5" /* Skeleton name. */ #define YYSKELETON_NAME "yacc.c" /* Pure parsers. */ #define YYPURE 0 /* Push parsers. */ #define YYPUSH 0 /* Pull parsers. */ #define YYPULL 1 /* Using locations. */ #define YYLSP_NEEDED 0 /* Copy the first part of user declarations. */ /* Line 268 of yacc.c */ #line 56 "genbc-impl.y" #include "genbc.h" #define yyparse impl_yyparse #define yydebug impl_yydebug #define YYERROR_VERBOSE #define YYPRINT yyprint char *current_id; /* Line 268 of yacc.c */ #line 82 "genbc-impl.c" /* Enabling traces. */ #ifndef YYDEBUG # define YYDEBUG 1 #endif /* Enabling verbose error messages. */ #ifdef YYERROR_VERBOSE # undef YYERROR_VERBOSE # define YYERROR_VERBOSE 1 #else # define YYERROR_VERBOSE 0 #endif /* Enabling the token table. */ #ifndef YYTOKEN_TABLE # define YYTOKEN_TABLE 0 #endif /* Tokens. */ #ifndef YYTOKENTYPE # define YYTOKENTYPE /* Put the tokens into the symbol table, so that GDB and other debuggers know about them. */ enum yytokentype { MATCH_BYTECODES = 258, DECL_BEGIN = 259, DECL_END = 260, DECL_BREAK = 261, DECL_CONTINUE = 262, DECL_DISPATCH = 263, DECL_EXTRACT = 264, DECL_DOTS = 265, NUMBER = 266, ID = 267, EXPR = 268 }; #endif /* Tokens. */ #define MATCH_BYTECODES 258 #define DECL_BEGIN 259 #define DECL_END 260 #define DECL_BREAK 261 #define DECL_CONTINUE 262 #define DECL_DISPATCH 263 #define DECL_EXTRACT 264 #define DECL_DOTS 265 #define NUMBER 266 #define ID 267 #define EXPR 268 #if ! defined YYSTYPE && ! defined YYSTYPE_IS_DECLARED typedef union YYSTYPE { /* Line 293 of yacc.c */ #line 69 "genbc-impl.y" struct field_info *field; const char *ctext; char *text; int num; /* Line 293 of yacc.c */ #line 153 "genbc-impl.c" } YYSTYPE; # define YYSTYPE_IS_TRIVIAL 1 # define yystype YYSTYPE /* obsolescent; will be withdrawn */ # define YYSTYPE_IS_DECLARED 1 #endif /* Copy the second part of user declarations. */ /* Line 343 of yacc.c */ #line 165 "genbc-impl.c" #ifdef short # undef short #endif #ifdef YYTYPE_UINT8 typedef YYTYPE_UINT8 yytype_uint8; #else typedef unsigned char yytype_uint8; #endif #ifdef YYTYPE_INT8 typedef YYTYPE_INT8 yytype_int8; #elif (defined __STDC__ || defined __C99__FUNC__ \ || defined __cplusplus || defined _MSC_VER) typedef signed char yytype_int8; #else typedef short int yytype_int8; #endif #ifdef YYTYPE_UINT16 typedef YYTYPE_UINT16 yytype_uint16; #else typedef unsigned short int yytype_uint16; #endif #ifdef YYTYPE_INT16 typedef YYTYPE_INT16 yytype_int16; #else typedef short int yytype_int16; #endif #ifndef YYSIZE_T # ifdef __SIZE_TYPE__ # define YYSIZE_T __SIZE_TYPE__ # elif defined size_t # define YYSIZE_T size_t # elif ! defined YYSIZE_T && (defined __STDC__ || defined __C99__FUNC__ \ || defined __cplusplus || defined _MSC_VER) # include /* INFRINGES ON USER NAME SPACE */ # define YYSIZE_T size_t # else # define YYSIZE_T unsigned int # endif #endif #define YYSIZE_MAXIMUM ((YYSIZE_T) -1) #ifndef YY_ # if defined YYENABLE_NLS && YYENABLE_NLS # if ENABLE_NLS # include /* INFRINGES ON USER NAME SPACE */ # define YY_(msgid) dgettext ("bison-runtime", msgid) # endif # endif # ifndef YY_ # define YY_(msgid) msgid # endif #endif /* Suppress unused-variable warnings by "using" E. */ #if ! defined lint || defined __GNUC__ # define YYUSE(e) ((void) (e)) #else # define YYUSE(e) /* empty */ #endif /* Identity function, used to suppress warnings about constant conditions. */ #ifndef lint # define YYID(n) (n) #else #if (defined __STDC__ || defined __C99__FUNC__ \ || defined __cplusplus || defined _MSC_VER) static int YYID (int yyi) #else static int YYID (yyi) int yyi; #endif { return yyi; } #endif #if ! defined yyoverflow || YYERROR_VERBOSE /* The parser invokes alloca or malloc; define the necessary symbols. */ # ifdef YYSTACK_USE_ALLOCA # if YYSTACK_USE_ALLOCA # ifdef __GNUC__ # define YYSTACK_ALLOC __builtin_alloca # elif defined __BUILTIN_VA_ARG_INCR # include /* INFRINGES ON USER NAME SPACE */ # elif defined _AIX # define YYSTACK_ALLOC __alloca # elif defined _MSC_VER # include /* INFRINGES ON USER NAME SPACE */ # define alloca _alloca # else # define YYSTACK_ALLOC alloca # if ! defined _ALLOCA_H && ! defined EXIT_SUCCESS && (defined __STDC__ || defined __C99__FUNC__ \ || defined __cplusplus || defined _MSC_VER) # include /* INFRINGES ON USER NAME SPACE */ # ifndef EXIT_SUCCESS # define EXIT_SUCCESS 0 # endif # endif # endif # endif # endif # ifdef YYSTACK_ALLOC /* Pacify GCC's `empty if-body' warning. */ # define YYSTACK_FREE(Ptr) do { /* empty */; } while (YYID (0)) # ifndef YYSTACK_ALLOC_MAXIMUM /* The OS might guarantee only one guard page at the bottom of the stack, and a page size can be as small as 4096 bytes. So we cannot safely invoke alloca (N) if N exceeds 4096. Use a slightly smaller number to allow for a few compiler-allocated temporary stack slots. */ # define YYSTACK_ALLOC_MAXIMUM 4032 /* reasonable circa 2006 */ # endif # else # define YYSTACK_ALLOC YYMALLOC # define YYSTACK_FREE YYFREE # ifndef YYSTACK_ALLOC_MAXIMUM # define YYSTACK_ALLOC_MAXIMUM YYSIZE_MAXIMUM # endif # if (defined __cplusplus && ! defined EXIT_SUCCESS \ && ! ((defined YYMALLOC || defined malloc) \ && (defined YYFREE || defined free))) # include /* INFRINGES ON USER NAME SPACE */ # ifndef EXIT_SUCCESS # define EXIT_SUCCESS 0 # endif # endif # ifndef YYMALLOC # define YYMALLOC malloc # if ! defined malloc && ! defined EXIT_SUCCESS && (defined __STDC__ || defined __C99__FUNC__ \ || defined __cplusplus || defined _MSC_VER) void *malloc (YYSIZE_T); /* INFRINGES ON USER NAME SPACE */ # endif # endif # ifndef YYFREE # define YYFREE free # if ! defined free && ! defined EXIT_SUCCESS && (defined __STDC__ || defined __C99__FUNC__ \ || defined __cplusplus || defined _MSC_VER) void free (void *); /* INFRINGES ON USER NAME SPACE */ # endif # endif # endif #endif /* ! defined yyoverflow || YYERROR_VERBOSE */ #if (! defined yyoverflow \ && (! defined __cplusplus \ || (defined YYSTYPE_IS_TRIVIAL && YYSTYPE_IS_TRIVIAL))) /* A type that is properly aligned for any stack member. */ union yyalloc { yytype_int16 yyss_alloc; YYSTYPE yyvs_alloc; }; /* The size of the maximum gap between one aligned stack and the next. */ # define YYSTACK_GAP_MAXIMUM (sizeof (union yyalloc) - 1) /* The size of an array large to enough to hold all stacks, each with N elements. */ # define YYSTACK_BYTES(N) \ ((N) * (sizeof (yytype_int16) + sizeof (YYSTYPE)) \ + YYSTACK_GAP_MAXIMUM) # define YYCOPY_NEEDED 1 /* Relocate STACK from its old location to the new one. The local variables YYSIZE and YYSTACKSIZE give the old and new number of elements in the stack, and YYPTR gives the new location of the stack. Advance YYPTR to a properly aligned location for the next stack. */ # define YYSTACK_RELOCATE(Stack_alloc, Stack) \ do \ { \ YYSIZE_T yynewbytes; \ YYCOPY (&yyptr->Stack_alloc, Stack, yysize); \ Stack = &yyptr->Stack_alloc; \ yynewbytes = yystacksize * sizeof (*Stack) + YYSTACK_GAP_MAXIMUM; \ yyptr += yynewbytes / sizeof (*yyptr); \ } \ while (YYID (0)) #endif #if defined YYCOPY_NEEDED && YYCOPY_NEEDED /* Copy COUNT objects from FROM to TO. The source and destination do not overlap. */ # ifndef YYCOPY # if defined __GNUC__ && 1 < __GNUC__ # define YYCOPY(To, From, Count) \ __builtin_memcpy (To, From, (Count) * sizeof (*(From))) # else # define YYCOPY(To, From, Count) \ do \ { \ YYSIZE_T yyi; \ for (yyi = 0; yyi < (Count); yyi++) \ (To)[yyi] = (From)[yyi]; \ } \ while (YYID (0)) # endif # endif #endif /* !YYCOPY_NEEDED */ /* YYFINAL -- State number of the termination state. */ #define YYFINAL 2 /* YYLAST -- Last index in YYTABLE. */ #define YYLAST 21 /* YYNTOKENS -- Number of terminals. */ #define YYNTOKENS 17 /* YYNNTS -- Number of nonterminals. */ #define YYNNTS 9 /* YYNRULES -- Number of rules. */ #define YYNRULES 12 /* YYNRULES -- Number of states. */ #define YYNSTATES 24 /* YYTRANSLATE(YYLEX) -- Bison symbol number corresponding to YYLEX. */ #define YYUNDEFTOK 2 #define YYMAXUTOK 268 #define YYTRANSLATE(YYX) \ ((unsigned int) (YYX) <= YYMAXUTOK ? yytranslate[YYX] : YYUNDEFTOK) /* YYTRANSLATE[YYLEX] -- Bison symbol number corresponding to YYLEX. */ static const yytype_uint8 yytranslate[] = { 0, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 14, 16, 2, 2, 15, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 1, 2, 3, 4, 5, 6, 7, 8, 9, 10, 11, 12, 13 }; #if YYDEBUG /* YYPRHS[YYN] -- Index of the first RHS symbol of rule number YYN in YYRHS. */ static const yytype_uint8 yyprhs[] = { 0, 0, 3, 6, 7, 8, 20, 22, 23, 27, 30, 34, 36 }; /* YYRHS -- A `-1'-separated list of the rules' RHS. */ static const yytype_int8 yyrhs[] = { 18, 0, -1, 18, 19, -1, -1, -1, 3, 14, 12, 15, 12, 15, 14, 20, 21, 16, 16, -1, 23, -1, -1, 21, 22, 23, -1, 24, 13, -1, 24, 15, 25, -1, 25, -1, 12, -1 }; /* YYRLINE[YYN] -- source line where rule number YYN was defined. */ static const yytype_uint8 yyrline[] = { 0, 91, 91, 92, 97, 96, 112, 113, 113, 117, 127, 128, 132 }; #endif #if YYDEBUG || YYERROR_VERBOSE || YYTOKEN_TABLE /* YYTNAME[SYMBOL-NUM] -- String name of the symbol SYMBOL-NUM. First, the terminals, then, starting at YYNTOKENS, nonterminals. */ static const char *const yytname[] = { "$end", "error", "$undefined", "\"MATCH_BYTECODES\"", "\"BEGIN\"", "\"END\"", "\"break\"", "\"continue\"", "\"dispatch\"", "\"extract\"", "\"..\"", "\"number\"", "\"identifier\"", "\"expression\"", "'('", "','", "')'", "$accept", "program", "matcher", "$@1", "cases", "$@2", "case", "ids", "id", 0 }; #endif # ifdef YYPRINT /* YYTOKNUM[YYLEX-NUM] -- Internal token number corresponding to token YYLEX-NUM. */ static const yytype_uint16 yytoknum[] = { 0, 256, 257, 258, 259, 260, 261, 262, 263, 264, 265, 266, 267, 268, 40, 44, 41 }; # endif /* YYR1[YYN] -- Symbol number of symbol that rule YYN derives. */ static const yytype_uint8 yyr1[] = { 0, 17, 18, 18, 20, 19, 21, 22, 21, 23, 24, 24, 25 }; /* YYR2[YYN] -- Number of symbols composing right hand side of rule YYN. */ static const yytype_uint8 yyr2[] = { 0, 2, 2, 0, 0, 11, 1, 0, 3, 2, 3, 1, 1 }; /* YYDEFACT[STATE-NAME] -- Default reduction number in state STATE-NUM. Performed when YYTABLE doesn't specify something else to do. Zero means the default is an error. */ static const yytype_uint8 yydefact[] = { 3, 0, 1, 0, 2, 0, 0, 0, 0, 0, 4, 0, 12, 7, 6, 0, 11, 0, 0, 9, 0, 5, 8, 10 }; /* YYDEFGOTO[NTERM-NUM]. */ static const yytype_int8 yydefgoto[] = { -1, 1, 4, 11, 13, 18, 14, 15, 16 }; /* YYPACT[STATE-NUM] -- Index in YYTABLE of the portion describing STATE-NUM. */ #define YYPACT_NINF -14 static const yytype_int8 yypact[] = { -14, 0, -14, -13, -14, -7, -9, -5, -6, -4, -14, -1, -14, -8, -14, -11, -14, -3, -1, -14, -1, -14, -14, -14 }; /* YYPGOTO[NTERM-NUM]. */ static const yytype_int8 yypgoto[] = { -14, -14, -14, -14, -14, -14, -2, -14, 1 }; /* YYTABLE[YYPACT[STATE-NUM]]. What to do in state STATE-NUM. If positive, shift that token. If negative, reduce the rule which number is the opposite. If YYTABLE_NINF, syntax error. */ #define YYTABLE_NINF -1 static const yytype_uint8 yytable[] = { 2, 5, 19, 3, 20, 6, 7, 8, 17, 9, 10, 12, 0, 21, 0, 0, 22, 0, 0, 0, 0, 23 }; #define yypact_value_is_default(yystate) \ ((yystate) == (-14)) #define yytable_value_is_error(yytable_value) \ YYID (0) static const yytype_int8 yycheck[] = { 0, 14, 13, 3, 15, 12, 15, 12, 16, 15, 14, 12, -1, 16, -1, -1, 18, -1, -1, -1, -1, 20 }; /* YYSTOS[STATE-NUM] -- The (internal number of the) accessing symbol of state STATE-NUM. */ static const yytype_uint8 yystos[] = { 0, 18, 0, 3, 19, 14, 12, 15, 12, 15, 14, 20, 12, 21, 23, 24, 25, 16, 22, 13, 15, 16, 23, 25 }; #define yyerrok (yyerrstatus = 0) #define yyclearin (yychar = YYEMPTY) #define YYEMPTY (-2) #define YYEOF 0 #define YYACCEPT goto yyacceptlab #define YYABORT goto yyabortlab #define YYERROR goto yyerrorlab /* Like YYERROR except do call yyerror. This remains here temporarily to ease the transition to the new meaning of YYERROR, for GCC. Once GCC version 2 has supplanted version 1, this can go. However, YYFAIL appears to be in use. Nevertheless, it is formally deprecated in Bison 2.4.2's NEWS entry, where a plan to phase it out is discussed. */ #define YYFAIL goto yyerrlab #if defined YYFAIL /* This is here to suppress warnings from the GCC cpp's -Wunused-macros. Normally we don't worry about that warning, but some users do, and we want to make it easy for users to remove YYFAIL uses, which will produce warnings from Bison 2.5. */ #endif #define YYRECOVERING() (!!yyerrstatus) #define YYBACKUP(Token, Value) \ do \ if (yychar == YYEMPTY && yylen == 1) \ { \ yychar = (Token); \ yylval = (Value); \ YYPOPSTACK (1); \ goto yybackup; \ } \ else \ { \ yyerror (YY_("syntax error: cannot back up")); \ YYERROR; \ } \ while (YYID (0)) #define YYTERROR 1 #define YYERRCODE 256 /* YYLLOC_DEFAULT -- Set CURRENT to span from RHS[1] to RHS[N]. If N is 0, then set CURRENT to the empty location which ends the previous symbol: RHS[0] (always defined). */ #define YYRHSLOC(Rhs, K) ((Rhs)[K]) #ifndef YYLLOC_DEFAULT # define YYLLOC_DEFAULT(Current, Rhs, N) \ do \ if (YYID (N)) \ { \ (Current).first_line = YYRHSLOC (Rhs, 1).first_line; \ (Current).first_column = YYRHSLOC (Rhs, 1).first_column; \ (Current).last_line = YYRHSLOC (Rhs, N).last_line; \ (Current).last_column = YYRHSLOC (Rhs, N).last_column; \ } \ else \ { \ (Current).first_line = (Current).last_line = \ YYRHSLOC (Rhs, 0).last_line; \ (Current).first_column = (Current).last_column = \ YYRHSLOC (Rhs, 0).last_column; \ } \ while (YYID (0)) #endif /* This macro is provided for backward compatibility. */ #ifndef YY_LOCATION_PRINT # define YY_LOCATION_PRINT(File, Loc) ((void) 0) #endif /* YYLEX -- calling `yylex' with the right arguments. */ #ifdef YYLEX_PARAM # define YYLEX yylex (YYLEX_PARAM) #else # define YYLEX yylex () #endif /* Enable debugging if requested. */ #if YYDEBUG # ifndef YYFPRINTF # include /* INFRINGES ON USER NAME SPACE */ # define YYFPRINTF fprintf # endif # define YYDPRINTF(Args) \ do { \ if (yydebug) \ YYFPRINTF Args; \ } while (YYID (0)) # define YY_SYMBOL_PRINT(Title, Type, Value, Location) \ do { \ if (yydebug) \ { \ YYFPRINTF (stderr, "%s ", Title); \ yy_symbol_print (stderr, \ Type, Value); \ YYFPRINTF (stderr, "\n"); \ } \ } while (YYID (0)) /*--------------------------------. | Print this symbol on YYOUTPUT. | `--------------------------------*/ /*ARGSUSED*/ #if (defined __STDC__ || defined __C99__FUNC__ \ || defined __cplusplus || defined _MSC_VER) static void yy_symbol_value_print (FILE *yyoutput, int yytype, YYSTYPE const * const yyvaluep) #else static void yy_symbol_value_print (yyoutput, yytype, yyvaluep) FILE *yyoutput; int yytype; YYSTYPE const * const yyvaluep; #endif { if (!yyvaluep) return; # ifdef YYPRINT if (yytype < YYNTOKENS) YYPRINT (yyoutput, yytoknum[yytype], *yyvaluep); # else YYUSE (yyoutput); # endif switch (yytype) { default: break; } } /*--------------------------------. | Print this symbol on YYOUTPUT. | `--------------------------------*/ #if (defined __STDC__ || defined __C99__FUNC__ \ || defined __cplusplus || defined _MSC_VER) static void yy_symbol_print (FILE *yyoutput, int yytype, YYSTYPE const * const yyvaluep) #else static void yy_symbol_print (yyoutput, yytype, yyvaluep) FILE *yyoutput; int yytype; YYSTYPE const * const yyvaluep; #endif { if (yytype < YYNTOKENS) YYFPRINTF (yyoutput, "token %s (", yytname[yytype]); else YYFPRINTF (yyoutput, "nterm %s (", yytname[yytype]); yy_symbol_value_print (yyoutput, yytype, yyvaluep); YYFPRINTF (yyoutput, ")"); } /*------------------------------------------------------------------. | yy_stack_print -- Print the state stack from its BOTTOM up to its | | TOP (included). | `------------------------------------------------------------------*/ #if (defined __STDC__ || defined __C99__FUNC__ \ || defined __cplusplus || defined _MSC_VER) static void yy_stack_print (yytype_int16 *yybottom, yytype_int16 *yytop) #else static void yy_stack_print (yybottom, yytop) yytype_int16 *yybottom; yytype_int16 *yytop; #endif { YYFPRINTF (stderr, "Stack now"); for (; yybottom <= yytop; yybottom++) { int yybot = *yybottom; YYFPRINTF (stderr, " %d", yybot); } YYFPRINTF (stderr, "\n"); } # define YY_STACK_PRINT(Bottom, Top) \ do { \ if (yydebug) \ yy_stack_print ((Bottom), (Top)); \ } while (YYID (0)) /*------------------------------------------------. | Report that the YYRULE is going to be reduced. | `------------------------------------------------*/ #if (defined __STDC__ || defined __C99__FUNC__ \ || defined __cplusplus || defined _MSC_VER) static void yy_reduce_print (YYSTYPE *yyvsp, int yyrule) #else static void yy_reduce_print (yyvsp, yyrule) YYSTYPE *yyvsp; int yyrule; #endif { int yynrhs = yyr2[yyrule]; int yyi; unsigned long int yylno = yyrline[yyrule]; YYFPRINTF (stderr, "Reducing stack by rule %d (line %lu):\n", yyrule - 1, yylno); /* The symbols being reduced. */ for (yyi = 0; yyi < yynrhs; yyi++) { YYFPRINTF (stderr, " $%d = ", yyi + 1); yy_symbol_print (stderr, yyrhs[yyprhs[yyrule] + yyi], &(yyvsp[(yyi + 1) - (yynrhs)]) ); YYFPRINTF (stderr, "\n"); } } # define YY_REDUCE_PRINT(Rule) \ do { \ if (yydebug) \ yy_reduce_print (yyvsp, Rule); \ } while (YYID (0)) /* Nonzero means print parse trace. It is left uninitialized so that multiple parsers can coexist. */ int yydebug; #else /* !YYDEBUG */ # define YYDPRINTF(Args) # define YY_SYMBOL_PRINT(Title, Type, Value, Location) # define YY_STACK_PRINT(Bottom, Top) # define YY_REDUCE_PRINT(Rule) #endif /* !YYDEBUG */ /* YYINITDEPTH -- initial size of the parser's stacks. */ #ifndef YYINITDEPTH # define YYINITDEPTH 200 #endif /* YYMAXDEPTH -- maximum size the stacks can grow to (effective only if the built-in stack extension method is used). Do not make this value too large; the results are undefined if YYSTACK_ALLOC_MAXIMUM < YYSTACK_BYTES (YYMAXDEPTH) evaluated with infinite-precision integer arithmetic. */ #ifndef YYMAXDEPTH # define YYMAXDEPTH 10000 #endif #if YYERROR_VERBOSE # ifndef yystrlen # if defined __GLIBC__ && defined _STRING_H # define yystrlen strlen # else /* Return the length of YYSTR. */ #if (defined __STDC__ || defined __C99__FUNC__ \ || defined __cplusplus || defined _MSC_VER) static YYSIZE_T yystrlen (const char *yystr) #else static YYSIZE_T yystrlen (yystr) const char *yystr; #endif { YYSIZE_T yylen; for (yylen = 0; yystr[yylen]; yylen++) continue; return yylen; } # endif # endif # ifndef yystpcpy # if defined __GLIBC__ && defined _STRING_H && defined _GNU_SOURCE # define yystpcpy stpcpy # else /* Copy YYSRC to YYDEST, returning the address of the terminating '\0' in YYDEST. */ #if (defined __STDC__ || defined __C99__FUNC__ \ || defined __cplusplus || defined _MSC_VER) static char * yystpcpy (char *yydest, const char *yysrc) #else static char * yystpcpy (yydest, yysrc) char *yydest; const char *yysrc; #endif { char *yyd = yydest; const char *yys = yysrc; while ((*yyd++ = *yys++) != '\0') continue; return yyd - 1; } # endif # endif # ifndef yytnamerr /* Copy to YYRES the contents of YYSTR after stripping away unnecessary quotes and backslashes, so that it's suitable for yyerror. The heuristic is that double-quoting is unnecessary unless the string contains an apostrophe, a comma, or backslash (other than backslash-backslash). YYSTR is taken from yytname. If YYRES is null, do not copy; instead, return the length of what the result would have been. */ static YYSIZE_T yytnamerr (char *yyres, const char *yystr) { if (*yystr == '"') { YYSIZE_T yyn = 0; char const *yyp = yystr; for (;;) switch (*++yyp) { case '\'': case ',': goto do_not_strip_quotes; case '\\': if (*++yyp != '\\') goto do_not_strip_quotes; /* Fall through. */ default: if (yyres) yyres[yyn] = *yyp; yyn++; break; case '"': if (yyres) yyres[yyn] = '\0'; return yyn; } do_not_strip_quotes: ; } if (! yyres) return yystrlen (yystr); return yystpcpy (yyres, yystr) - yyres; } # endif /* Copy into *YYMSG, which is of size *YYMSG_ALLOC, an error message about the unexpected token YYTOKEN for the state stack whose top is YYSSP. Return 0 if *YYMSG was successfully written. Return 1 if *YYMSG is not large enough to hold the message. In that case, also set *YYMSG_ALLOC to the required number of bytes. Return 2 if the required number of bytes is too large to store. */ static int yysyntax_error (YYSIZE_T *yymsg_alloc, char **yymsg, yytype_int16 *yyssp, int yytoken) { YYSIZE_T yysize0 = yytnamerr (0, yytname[yytoken]); YYSIZE_T yysize = yysize0; YYSIZE_T yysize1; enum { YYERROR_VERBOSE_ARGS_MAXIMUM = 5 }; /* Internationalized format string. */ const char *yyformat = 0; /* Arguments of yyformat. */ char const *yyarg[YYERROR_VERBOSE_ARGS_MAXIMUM]; /* Number of reported tokens (one for the "unexpected", one per "expected"). */ int yycount = 0; /* There are many possibilities here to consider: - Assume YYFAIL is not used. It's too flawed to consider. See for details. YYERROR is fine as it does not invoke this function. - If this state is a consistent state with a default action, then the only way this function was invoked is if the default action is an error action. In that case, don't check for expected tokens because there are none. - The only way there can be no lookahead present (in yychar) is if this state is a consistent state with a default action. Thus, detecting the absence of a lookahead is sufficient to determine that there is no unexpected or expected token to report. In that case, just report a simple "syntax error". - Don't assume there isn't a lookahead just because this state is a consistent state with a default action. There might have been a previous inconsistent state, consistent state with a non-default action, or user semantic action that manipulated yychar. - Of course, the expected token list depends on states to have correct lookahead information, and it depends on the parser not to perform extra reductions after fetching a lookahead from the scanner and before detecting a syntax error. Thus, state merging (from LALR or IELR) and default reductions corrupt the expected token list. However, the list is correct for canonical LR with one exception: it will still contain any token that will not be accepted due to an error action in a later state. */ if (yytoken != YYEMPTY) { int yyn = yypact[*yyssp]; yyarg[yycount++] = yytname[yytoken]; if (!yypact_value_is_default (yyn)) { /* Start YYX at -YYN if negative to avoid negative indexes in YYCHECK. In other words, skip the first -YYN actions for this state because they are default actions. */ int yyxbegin = yyn < 0 ? -yyn : 0; /* Stay within bounds of both yycheck and yytname. */ int yychecklim = YYLAST - yyn + 1; int yyxend = yychecklim < YYNTOKENS ? yychecklim : YYNTOKENS; int yyx; for (yyx = yyxbegin; yyx < yyxend; ++yyx) if (yycheck[yyx + yyn] == yyx && yyx != YYTERROR && !yytable_value_is_error (yytable[yyx + yyn])) { if (yycount == YYERROR_VERBOSE_ARGS_MAXIMUM) { yycount = 1; yysize = yysize0; break; } yyarg[yycount++] = yytname[yyx]; yysize1 = yysize + yytnamerr (0, yytname[yyx]); if (! (yysize <= yysize1 && yysize1 <= YYSTACK_ALLOC_MAXIMUM)) return 2; yysize = yysize1; } } } switch (yycount) { # define YYCASE_(N, S) \ case N: \ yyformat = S; \ break YYCASE_(0, YY_("syntax error")); YYCASE_(1, YY_("syntax error, unexpected %s")); YYCASE_(2, YY_("syntax error, unexpected %s, expecting %s")); YYCASE_(3, YY_("syntax error, unexpected %s, expecting %s or %s")); YYCASE_(4, YY_("syntax error, unexpected %s, expecting %s or %s or %s")); YYCASE_(5, YY_("syntax error, unexpected %s, expecting %s or %s or %s or %s")); # undef YYCASE_ } yysize1 = yysize + yystrlen (yyformat); if (! (yysize <= yysize1 && yysize1 <= YYSTACK_ALLOC_MAXIMUM)) return 2; yysize = yysize1; if (*yymsg_alloc < yysize) { *yymsg_alloc = 2 * yysize; if (! (yysize <= *yymsg_alloc && *yymsg_alloc <= YYSTACK_ALLOC_MAXIMUM)) *yymsg_alloc = YYSTACK_ALLOC_MAXIMUM; return 1; } /* Avoid sprintf, as that infringes on the user's name space. Don't have undefined behavior even if the translation produced a string with the wrong number of "%s"s. */ { char *yyp = *yymsg; int yyi = 0; while ((*yyp = *yyformat) != '\0') if (*yyp == '%' && yyformat[1] == 's' && yyi < yycount) { yyp += yytnamerr (yyp, yyarg[yyi++]); yyformat += 2; } else { yyp++; yyformat++; } } return 0; } #endif /* YYERROR_VERBOSE */ /*-----------------------------------------------. | Release the memory associated to this symbol. | `-----------------------------------------------*/ /*ARGSUSED*/ #if (defined __STDC__ || defined __C99__FUNC__ \ || defined __cplusplus || defined _MSC_VER) static void yydestruct (const char *yymsg, int yytype, YYSTYPE *yyvaluep) #else static void yydestruct (yymsg, yytype, yyvaluep) const char *yymsg; int yytype; YYSTYPE *yyvaluep; #endif { YYUSE (yyvaluep); if (!yymsg) yymsg = "Deleting"; YY_SYMBOL_PRINT (yymsg, yytype, yyvaluep, yylocationp); switch (yytype) { default: break; } } /* Prevent warnings from -Wmissing-prototypes. */ #ifdef YYPARSE_PARAM #if defined __STDC__ || defined __cplusplus int yyparse (void *YYPARSE_PARAM); #else int yyparse (); #endif #else /* ! YYPARSE_PARAM */ #if defined __STDC__ || defined __cplusplus int yyparse (void); #else int yyparse (); #endif #endif /* ! YYPARSE_PARAM */ /* The lookahead symbol. */ int yychar; /* The semantic value of the lookahead symbol. */ YYSTYPE yylval; /* Number of syntax errors so far. */ int yynerrs; /*----------. | yyparse. | `----------*/ #ifdef YYPARSE_PARAM #if (defined __STDC__ || defined __C99__FUNC__ \ || defined __cplusplus || defined _MSC_VER) int yyparse (void *YYPARSE_PARAM) #else int yyparse (YYPARSE_PARAM) void *YYPARSE_PARAM; #endif #else /* ! YYPARSE_PARAM */ #if (defined __STDC__ || defined __C99__FUNC__ \ || defined __cplusplus || defined _MSC_VER) int yyparse (void) #else int yyparse () #endif #endif { int yystate; /* Number of tokens to shift before error messages enabled. */ int yyerrstatus; /* The stacks and their tools: `yyss': related to states. `yyvs': related to semantic values. Refer to the stacks thru separate pointers, to allow yyoverflow to reallocate them elsewhere. */ /* The state stack. */ yytype_int16 yyssa[YYINITDEPTH]; yytype_int16 *yyss; yytype_int16 *yyssp; /* The semantic value stack. */ YYSTYPE yyvsa[YYINITDEPTH]; YYSTYPE *yyvs; YYSTYPE *yyvsp; YYSIZE_T yystacksize; int yyn; int yyresult; /* Lookahead token as an internal (translated) token number. */ int yytoken; /* The variables used to return semantic value and location from the action routines. */ YYSTYPE yyval; #if YYERROR_VERBOSE /* Buffer for error messages, and its allocated size. */ char yymsgbuf[128]; char *yymsg = yymsgbuf; YYSIZE_T yymsg_alloc = sizeof yymsgbuf; #endif #define YYPOPSTACK(N) (yyvsp -= (N), yyssp -= (N)) /* The number of symbols on the RHS of the reduced rule. Keep to zero when no symbol should be popped. */ int yylen = 0; yytoken = 0; yyss = yyssa; yyvs = yyvsa; yystacksize = YYINITDEPTH; YYDPRINTF ((stderr, "Starting parse\n")); yystate = 0; yyerrstatus = 0; yynerrs = 0; yychar = YYEMPTY; /* Cause a token to be read. */ /* Initialize stack pointers. Waste one element of value and location stack so that they stay on the same level as the state stack. The wasted elements are never initialized. */ yyssp = yyss; yyvsp = yyvs; goto yysetstate; /*------------------------------------------------------------. | yynewstate -- Push a new state, which is found in yystate. | `------------------------------------------------------------*/ yynewstate: /* In all cases, when you get here, the value and location stacks have just been pushed. So pushing a state here evens the stacks. */ yyssp++; yysetstate: *yyssp = yystate; if (yyss + yystacksize - 1 <= yyssp) { /* Get the current used size of the three stacks, in elements. */ YYSIZE_T yysize = yyssp - yyss + 1; #ifdef yyoverflow { /* Give user a chance to reallocate the stack. Use copies of these so that the &'s don't force the real ones into memory. */ YYSTYPE *yyvs1 = yyvs; yytype_int16 *yyss1 = yyss; /* Each stack pointer address is followed by the size of the data in use in that stack, in bytes. This used to be a conditional around just the two extra args, but that might be undefined if yyoverflow is a macro. */ yyoverflow (YY_("memory exhausted"), &yyss1, yysize * sizeof (*yyssp), &yyvs1, yysize * sizeof (*yyvsp), &yystacksize); yyss = yyss1; yyvs = yyvs1; } #else /* no yyoverflow */ # ifndef YYSTACK_RELOCATE goto yyexhaustedlab; # else /* Extend the stack our own way. */ if (YYMAXDEPTH <= yystacksize) goto yyexhaustedlab; yystacksize *= 2; if (YYMAXDEPTH < yystacksize) yystacksize = YYMAXDEPTH; { yytype_int16 *yyss1 = yyss; union yyalloc *yyptr = (union yyalloc *) YYSTACK_ALLOC (YYSTACK_BYTES (yystacksize)); if (! yyptr) goto yyexhaustedlab; YYSTACK_RELOCATE (yyss_alloc, yyss); YYSTACK_RELOCATE (yyvs_alloc, yyvs); # undef YYSTACK_RELOCATE if (yyss1 != yyssa) YYSTACK_FREE (yyss1); } # endif #endif /* no yyoverflow */ yyssp = yyss + yysize - 1; yyvsp = yyvs + yysize - 1; YYDPRINTF ((stderr, "Stack size increased to %lu\n", (unsigned long int) yystacksize)); if (yyss + yystacksize - 1 <= yyssp) YYABORT; } YYDPRINTF ((stderr, "Entering state %d\n", yystate)); if (yystate == YYFINAL) YYACCEPT; goto yybackup; /*-----------. | yybackup. | `-----------*/ yybackup: /* Do appropriate processing given the current state. Read a lookahead token if we need one and don't already have one. */ /* First try to decide what to do without reference to lookahead token. */ yyn = yypact[yystate]; if (yypact_value_is_default (yyn)) goto yydefault; /* Not known => get a lookahead token if don't already have one. */ /* YYCHAR is either YYEMPTY or YYEOF or a valid lookahead symbol. */ if (yychar == YYEMPTY) { YYDPRINTF ((stderr, "Reading a token: ")); yychar = YYLEX; } if (yychar <= YYEOF) { yychar = yytoken = YYEOF; YYDPRINTF ((stderr, "Now at end of input.\n")); } else { yytoken = YYTRANSLATE (yychar); YY_SYMBOL_PRINT ("Next token is", yytoken, &yylval, &yylloc); } /* If the proper action on seeing token YYTOKEN is to reduce or to detect an error, take that action. */ yyn += yytoken; if (yyn < 0 || YYLAST < yyn || yycheck[yyn] != yytoken) goto yydefault; yyn = yytable[yyn]; if (yyn <= 0) { if (yytable_value_is_error (yyn)) goto yyerrlab; yyn = -yyn; goto yyreduce; } /* Count tokens shifted since error; after three, turn off error status. */ if (yyerrstatus) yyerrstatus--; /* Shift the lookahead token. */ YY_SYMBOL_PRINT ("Shifting", yytoken, &yylval, &yylloc); /* Discard the shifted token. */ yychar = YYEMPTY; yystate = yyn; *++yyvsp = yylval; goto yynewstate; /*-----------------------------------------------------------. | yydefault -- do the default action for the current state. | `-----------------------------------------------------------*/ yydefault: yyn = yydefact[yystate]; if (yyn == 0) goto yyerrlab; goto yyreduce; /*-----------------------------. | yyreduce -- Do a reduction. | `-----------------------------*/ yyreduce: /* yyn is the number of a rule to reduce with. */ yylen = yyr2[yyn]; /* If YYLEN is nonzero, implement the default value of the action: `$$ = $1'. Otherwise, the following line sets YYVAL to garbage. This behavior is undocumented and Bison users should not rely upon it. Assigning to YYVAL unconditionally makes the parser a bit smaller, and it avoids a GCC warning that YYVAL may be used uninitialized. */ yyval = yyvsp[1-yylen]; YY_REDUCE_PRINT (yyn); switch (yyn) { case 4: /* Line 1806 of yacc.c */ #line 97 "genbc-impl.y" { current_id = (yyvsp[(3) - (7)].text); printf ("\n"); #if 0 printf ("/* %s:%d */\n", current_file, yylineno); #endif printf ("#define MATCH_BYTECODES_%s \\\n", (yyvsp[(3) - (7)].text)); } break; case 5: /* Line 1806 of yacc.c */ #line 106 "genbc-impl.y" { free ((yyvsp[(3) - (11)].text)); printf ("\n"); } break; case 7: /* Line 1806 of yacc.c */ #line 113 "genbc-impl.y" { printf (" \\\n"); } break; case 9: /* Line 1806 of yacc.c */ #line 118 "genbc-impl.y" { printf (" %s \\\n" " goto MATCH_BYTECODES_SWITCH_%s;", (yyvsp[(2) - (2)].text), current_id); free ((yyvsp[(2) - (2)].text)); } break; case 12: /* Line 1806 of yacc.c */ #line 133 "genbc-impl.y" { printf (" MATCH_BYTECODES_%s_%s: \\\n", current_id, (yyvsp[(1) - (1)].text)); free ((yyvsp[(1) - (1)].text)); } break; /* Line 1806 of yacc.c */ #line 1450 "genbc-impl.c" default: break; } /* User semantic actions sometimes alter yychar, and that requires that yytoken be updated with the new translation. We take the approach of translating immediately before every use of yytoken. One alternative is translating here after every semantic action, but that translation would be missed if the semantic action invokes YYABORT, YYACCEPT, or YYERROR immediately after altering yychar or if it invokes YYBACKUP. In the case of YYABORT or YYACCEPT, an incorrect destructor might then be invoked immediately. In the case of YYERROR or YYBACKUP, subsequent parser actions might lead to an incorrect destructor call or verbose syntax error message before the lookahead is translated. */ YY_SYMBOL_PRINT ("-> $$ =", yyr1[yyn], &yyval, &yyloc); YYPOPSTACK (yylen); yylen = 0; YY_STACK_PRINT (yyss, yyssp); *++yyvsp = yyval; /* Now `shift' the result of the reduction. Determine what state that goes to, based on the state we popped back to and the rule number reduced by. */ yyn = yyr1[yyn]; yystate = yypgoto[yyn - YYNTOKENS] + *yyssp; if (0 <= yystate && yystate <= YYLAST && yycheck[yystate] == *yyssp) yystate = yytable[yystate]; else yystate = yydefgoto[yyn - YYNTOKENS]; goto yynewstate; /*------------------------------------. | yyerrlab -- here on detecting error | `------------------------------------*/ yyerrlab: /* Make sure we have latest lookahead translation. See comments at user semantic actions for why this is necessary. */ yytoken = yychar == YYEMPTY ? YYEMPTY : YYTRANSLATE (yychar); /* If not already recovering from an error, report this error. */ if (!yyerrstatus) { ++yynerrs; #if ! YYERROR_VERBOSE yyerror (YY_("syntax error")); #else # define YYSYNTAX_ERROR yysyntax_error (&yymsg_alloc, &yymsg, \ yyssp, yytoken) { char const *yymsgp = YY_("syntax error"); int yysyntax_error_status; yysyntax_error_status = YYSYNTAX_ERROR; if (yysyntax_error_status == 0) yymsgp = yymsg; else if (yysyntax_error_status == 1) { if (yymsg != yymsgbuf) YYSTACK_FREE (yymsg); yymsg = (char *) YYSTACK_ALLOC (yymsg_alloc); if (!yymsg) { yymsg = yymsgbuf; yymsg_alloc = sizeof yymsgbuf; yysyntax_error_status = 2; } else { yysyntax_error_status = YYSYNTAX_ERROR; yymsgp = yymsg; } } yyerror (yymsgp); if (yysyntax_error_status == 2) goto yyexhaustedlab; } # undef YYSYNTAX_ERROR #endif } if (yyerrstatus == 3) { /* If just tried and failed to reuse lookahead token after an error, discard it. */ if (yychar <= YYEOF) { /* Return failure if at end of input. */ if (yychar == YYEOF) YYABORT; } else { yydestruct ("Error: discarding", yytoken, &yylval); yychar = YYEMPTY; } } /* Else will try to reuse lookahead token after shifting the error token. */ goto yyerrlab1; /*---------------------------------------------------. | yyerrorlab -- error raised explicitly by YYERROR. | `---------------------------------------------------*/ yyerrorlab: /* Pacify compilers like GCC when the user code never invokes YYERROR and the label yyerrorlab therefore never appears in user code. */ if (/*CONSTCOND*/ 0) goto yyerrorlab; /* Do not reclaim the symbols of the rule which action triggered this YYERROR. */ YYPOPSTACK (yylen); yylen = 0; YY_STACK_PRINT (yyss, yyssp); yystate = *yyssp; goto yyerrlab1; /*-------------------------------------------------------------. | yyerrlab1 -- common code for both syntax error and YYERROR. | `-------------------------------------------------------------*/ yyerrlab1: yyerrstatus = 3; /* Each real token shifted decrements this. */ for (;;) { yyn = yypact[yystate]; if (!yypact_value_is_default (yyn)) { yyn += YYTERROR; if (0 <= yyn && yyn <= YYLAST && yycheck[yyn] == YYTERROR) { yyn = yytable[yyn]; if (0 < yyn) break; } } /* Pop the current state because it cannot handle the error token. */ if (yyssp == yyss) YYABORT; yydestruct ("Error: popping", yystos[yystate], yyvsp); YYPOPSTACK (1); yystate = *yyssp; YY_STACK_PRINT (yyss, yyssp); } *++yyvsp = yylval; /* Shift the error token. */ YY_SYMBOL_PRINT ("Shifting", yystos[yyn], yyvsp, yylsp); yystate = yyn; goto yynewstate; /*-------------------------------------. | yyacceptlab -- YYACCEPT comes here. | `-------------------------------------*/ yyacceptlab: yyresult = 0; goto yyreturn; /*-----------------------------------. | yyabortlab -- YYABORT comes here. | `-----------------------------------*/ yyabortlab: yyresult = 1; goto yyreturn; #if !defined(yyoverflow) || YYERROR_VERBOSE /*-------------------------------------------------. | yyexhaustedlab -- memory exhaustion comes here. | `-------------------------------------------------*/ yyexhaustedlab: yyerror (YY_("memory exhausted")); yyresult = 2; /* Fall through. */ #endif yyreturn: if (yychar != YYEMPTY) { /* Make sure we have latest lookahead translation. See comments at user semantic actions for why this is necessary. */ yytoken = YYTRANSLATE (yychar); yydestruct ("Cleanup: discarding lookahead", yytoken, &yylval); } /* Do not reclaim the symbols of the rule which action triggered this YYABORT or YYACCEPT. */ YYPOPSTACK (yylen); YY_STACK_PRINT (yyss, yyssp); while (yyssp != yyss) { yydestruct ("Cleanup: popping", yystos[*yyssp], yyvsp); YYPOPSTACK (1); } #ifndef yyoverflow if (yyss != yyssa) YYSTACK_FREE (yyss); #endif #if YYERROR_VERBOSE if (yymsg != yymsgbuf) YYSTACK_FREE (yymsg); #endif /* Make sure YYID is used. */ return YYID (yyresult); } /* Line 2067 of yacc.c */ #line 137 "genbc-impl.y" smalltalk-3.2.5/libgst/mpz.c0000644000175000017500000012301712123404352012664 00000000000000/******************************** -*- C -*- **************************** * * Multiple precision operations for GNU Smalltalk's LargeIntegers * * ***********************************************************************/ /*********************************************************************** * * Copyright 1991, 2002, 2006, 2007, 2008, 2009 Free Software Foundation, Inc. * * This file is derived from an absurdly old version of the GNU MP Library. * * The GNU MP library is free software; you can redistribute it and/or * modify it under the terms of the GNU General Public License as * published by the Free Software Foundation; either version 2, or (at * your option) any later version. * * The GNU MP Library is distributed in the hope that it will be * useful, but WITHOUT ANY WARRANTY; without even the implied warranty * of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the * GNU General Public License for more details. * * You should have received a copy of the GNU General Public License * along with the GNU MP library; see the file COPYING. If not, write * to the Free Software Foundation, 51 Franklin Street, Fifth Floor, * Boston, MA 02110-1301, USA. * ***********************************************************************/ #include "gstpriv.h" #if HAVE_GMP #include #define BITS_PER_MP_LIMB (8 * SIZEOF_MP_LIMB_T) /* Copy NLIMBS *limbs* from SRC to DST. */ #define MPN_COPY(DST, SRC, NLIMBS) \ memmove((DST), (SRC), (NLIMBS) * SIZEOF_MP_LIMB_T) /* Zero NLIMBS *limbs* AT DST. */ #define MPN_ZERO(DST, NLIMBS) \ memset((DST), 0, (NLIMBS) * SIZEOF_MP_LIMB_T) /* Initialize the gst_mpz X with space for NLIMBS limbs. X should be a temporary variable, and it will be automatically cleared out when the running function returns. */ #define MPZ_TMP_INIT(X, NLIMBS) \ do { \ (X)->alloc = 0; \ (X)->d = (mp_ptr) alloca ((NLIMBS) * SIZEOF_MP_LIMB_T); \ } while (0) /* gst_mpz_realloc -- make the gst_mpz have NEW_SIZE digits allocated. */ static void *gst_mpz_realloc (gst_mpz *m, mp_size_t new_size); static void gst_mpz_sub_ui (gst_mpz *dif, const gst_mpz *min, mp_limb_t sub); static void * gst_mpz_realloc (gst_mpz *m, mp_size_t new_size) { /* Never allocate zero space. */ if (new_size == 0) new_size = 1; if (new_size > m->alloc) { m->alloc = new_size; m->d = (mp_ptr) xrealloc (m->d, new_size * SIZEOF_MP_LIMB_T); } return (void *) m->d; } /* mpz_sub_ui -- Subtract an unsigned one-word integer from an gst_mpz. */ static void gst_mpz_sub_ui (gst_mpz *dif, const gst_mpz *min, mp_limb_t sub) { mp_srcptr minp; mp_ptr difp; mp_size_t minsize, difsize; mp_size_t abs_minsize; minsize = min->size; abs_minsize = ABS (minsize); /* If not space for SUM (and possible carry), increase space. */ difsize = abs_minsize + 1; if (dif->alloc < difsize) gst_mpz_realloc (dif, difsize); /* These must be after realloc (ADD1 may be the same as SUM). */ minp = min->d; difp = dif->d; if (sub == 0) { MPN_COPY (difp, minp, abs_minsize); dif->size = minsize; return; } if (abs_minsize == 0) { difp[0] = sub; dif->size = -1; return; } if (minsize < 0) { difsize = mpn_add_1 (difp, minp, abs_minsize, sub); if (difsize != 0) difp[abs_minsize] = 1; difsize = -(difsize + abs_minsize); } else { /* The signs are different. Need exact comparision to determine which operand to subtract from which. */ if (abs_minsize == 1 && minp[0] < sub) difsize = -(abs_minsize + mpn_sub_1 (difp, &sub, 1, *minp)); else difsize = (abs_minsize + mpn_sub_1 (difp, minp, abs_minsize, sub)); } dif->size = difsize; } void _gst_mpz_clear (gst_mpz *m) { if (m->alloc) xfree (m->d); } void _gst_mpz_add (gst_mpz *sum, const gst_mpz *u, const gst_mpz *v) { mp_srcptr up, vp; mp_ptr sump; mp_size_t usize, vsize, sumsize; mp_size_t abs_usize; mp_size_t abs_vsize; usize = u->size; vsize = v->size; abs_usize = ABS (usize); abs_vsize = ABS (vsize); if (abs_usize < abs_vsize) { /* Swap U and V. */ {const gst_mpz *t = u; u = v; v = t;} {mp_size_t t = usize; usize = vsize; vsize = t;} {mp_size_t t = abs_usize; abs_usize = abs_vsize; abs_vsize = t;} } /* True: abs(USIZE) >= abs(VSIZE) */ /* If not space for sum (and possible carry), increase space. */ sumsize = abs_usize + 1; if (sum->alloc < sumsize) gst_mpz_realloc (sum, sumsize); /* These must be after realloc (u or v may be the same as sum). */ up = u->d; vp = v->d; sump = sum->d; if (usize >= 0) { if (vsize >= 0) { sumsize = mpn_add (sump, up, abs_usize, vp, abs_vsize); if (sumsize != 0) sump[abs_usize] = 1; sumsize = sumsize + abs_usize; } else { /* The signs are different. Need exact comparision to determine which operand to subtract from which. */ if (abs_usize == abs_vsize && mpn_cmp (up, vp, abs_usize) < 0) sumsize = -(abs_usize + mpn_sub (sump, vp, abs_usize, up, abs_usize)); else sumsize = (abs_usize + mpn_sub (sump, up, abs_usize, vp, abs_vsize)); } } else { if (vsize >= 0) { /* The signs are different. Need exact comparision to determine which operand to subtract from which. */ if (abs_usize == abs_vsize && mpn_cmp (up, vp, abs_usize) < 0) sumsize = (abs_usize + mpn_sub (sump, vp, abs_usize, up, abs_usize)); else sumsize = -(abs_usize + mpn_sub (sump, up, abs_usize, vp, abs_vsize)); } else { sumsize = mpn_add (sump, up, abs_usize, vp, abs_vsize); if (sumsize != 0) sump[abs_usize] = 1; sumsize = -(sumsize + abs_usize); } } sum->size = sumsize; } int _gst_mpz_cmp (const gst_mpz *u, const gst_mpz *v) { mp_size_t usize = u->size; mp_size_t vsize = v->size; mp_size_t size; if (usize != vsize) return usize - vsize; if (usize == 0) return 0; size = ABS (usize); if (usize < 0) return mpn_cmp (v->d, u->d, size); else return mpn_cmp (u->d, v->d, size); } void _gst_mpz_com (gst_mpz *dst, const gst_mpz *src) { mp_size_t size = src->size; mp_srcptr src_ptr; mp_ptr dst_ptr; if (size >= 0) { /* As with infinite precision: one's complement, two's complement. But this can be simplified using the identity -x = ~x + 1. So we're going to compute (~~x) + 1 = x + 1! */ if (dst->alloc < size + 1) gst_mpz_realloc (dst, size + 1); src_ptr = src->d; dst_ptr = dst->d; if (size == 0) { /* Special case, as mpn_add wants the first arg's size >= the second arg's size. */ dst_ptr[0] = 1; dst->size = -1; return; } { int cy; cy = mpn_add_1 (dst_ptr, src_ptr, size, 1); if (cy) { dst_ptr[size] = cy; size++; } } /* Store a negative size, to indicate ones-extension. */ dst->size = -size; } else { /* As with infinite precision: two's complement, then one's complement. But that can be simplified using the identity -x = ~(x - 1). So we're going to compute ~~(x - 1) = x - 1! */ size = -size; if (dst->alloc < size) gst_mpz_realloc (dst, size); src_ptr = src->d; dst_ptr = dst->d; size += mpn_sub_1 (dst_ptr, src_ptr, size, 1); /* Store a positive size, to indicate zero-extension. */ dst->size = size; } } void _gst_mpz_div_2exp (gst_mpz *w, const gst_mpz *u, unsigned cnt) { mp_size_t usize = u->size; mp_size_t wsize; mp_size_t abs_usize = ABS (usize); mp_size_t limb_cnt; limb_cnt = cnt / BITS_PER_MP_LIMB; wsize = abs_usize - limb_cnt; if (wsize <= 0) wsize = 0; else { if (w->alloc < wsize) gst_mpz_realloc (w, wsize); if (cnt % BITS_PER_MP_LIMB) mpn_rshift (w->d, u->d + limb_cnt, abs_usize - limb_cnt, cnt % BITS_PER_MP_LIMB); else MPN_COPY (w->d, u->d + limb_cnt, abs_usize - limb_cnt); wsize -= w->d[wsize - 1] == 0; } w->size = (usize >= 0) ? wsize : -wsize; } void _gst_mpz_tdiv_qr (gst_mpz *quot, gst_mpz *rem, const gst_mpz *num, const gst_mpz *den) { mp_ptr np, dp; mp_ptr qp, rp; mp_size_t nsize = num->size; mp_size_t dsize = den->size; mp_size_t qsize; mp_size_t sign_remainder = nsize; mp_size_t sign_quotient = nsize ^ dsize; nsize = ABS (nsize); dsize = ABS (dsize); /* Ensure space is enough for quotient and remainder. */ qsize = nsize - dsize + 1; /* qsize cannot be bigger than this. */ if (qsize <= 0) { if (num != rem) { gst_mpz_realloc (rem, nsize); rem->size = num->size; MPN_COPY (rem->d, num->d, nsize); } quot->size = 0; return; } if (quot->alloc < qsize) gst_mpz_realloc (quot, qsize); if (rem->alloc < dsize) gst_mpz_realloc (rem, dsize); qp = quot->d; np = num->d; dp = den->d; rp = rem->d; /* Copy denominator to temporary space if it overlaps with the quotient or remainder. */ if (dp == rp || dp == qp) { mp_ptr tp; tp = (mp_ptr) alloca (dsize * SIZEOF_MP_LIMB_T); MPN_COPY (tp, dp, dsize); dp = tp; } /* Copy numerator to temporary space if it overlaps with the quotient or remainder. */ if (np == rp || np == qp) { mp_ptr tp; tp = (mp_ptr) alloca (nsize * SIZEOF_MP_LIMB_T); MPN_COPY (tp, np, nsize); np = tp; } mpn_tdiv_qr (qp, rp, 0L, np, nsize, dp, dsize); qsize -= qp[qsize - 1] == 0; quot->size = sign_quotient >= 0 ? qsize : -qsize; rem->size = sign_remainder >= 0 ? dsize : -dsize; alloca (0); } static void _gst_mpz_tdiv_q_ui (gst_mpz *quot, const gst_mpz *num, mp_limb_t den) { mp_ptr np; mp_ptr qp; mp_size_t nsize = num->size; mp_size_t sign_quotient = nsize; nsize = ABS (nsize); if (nsize == 0) { quot->size = 0; return; } if (quot->alloc < nsize) gst_mpz_realloc (quot, nsize); qp = quot->d; np = num->d; /* Copy numerator to temporary space if it overlaps with the quotient. */ if (np == qp) { mp_ptr tp; tp = (mp_ptr) alloca (nsize * SIZEOF_MP_LIMB_T); MPN_COPY (tp, np, nsize); np = tp; } mpn_divrem_1 (qp, 0L, np, nsize, den); nsize -= qp[nsize - 1] == 0; quot->size = sign_quotient >= 0 ? nsize : -nsize; alloca (0); } mp_limb_t _gst_mpz_tdiv_qr_si (gst_mpz *quot, const gst_mpz *num, intptr_t den) { mp_ptr np; mp_ptr qp; mp_size_t nsize = num->size; mp_size_t sign_remainder = nsize; mp_size_t sign_quotient = nsize ^ den; mp_limb_t rem; nsize = ABS (nsize); if (nsize == 0) { quot->size = 0; return 0; } if (quot->alloc < nsize) gst_mpz_realloc (quot, nsize); qp = quot->d; np = num->d; /* Copy numerator to temporary space if it overlaps with the quotient. */ if (np == qp) { mp_ptr tp; tp = (mp_ptr) alloca (nsize * SIZEOF_MP_LIMB_T); MPN_COPY (tp, np, nsize); np = tp; } rem = mpn_divrem_1 (qp, 0L, np, nsize, ABS(den)); nsize -= qp[nsize - 1] == 0; quot->size = sign_quotient >= 0 ? nsize : -nsize; alloca (0); return sign_remainder >= 0 ? rem : -rem; } static inline void gst_mpz_copy_abs (gst_mpz *d, const gst_mpz *s) { d->size = ABS (s->size); if (d != s) { if (d->alloc < d->size) gst_mpz_realloc (d, d->size); MPN_COPY (d->d, s->d, d->size); } } void _gst_mpz_gcd (gst_mpz *g, const gst_mpz *u, const gst_mpz *v) { int g_zero_bits, u_zero_bits, v_zero_bits; mp_size_t g_zero_limbs, u_zero_limbs, v_zero_limbs; mp_ptr tp; mp_ptr up = u->d; mp_size_t usize = ABS (u->size); mp_ptr vp = v->d; mp_size_t vsize = ABS (v->size); mp_size_t gsize; /* GCD(0, V) == GCD (U, 1) == V. */ if (usize == 0 || (vsize == 1 && vp[0] == 1)) { gst_mpz_copy_abs (g, v); return; } /* GCD(U, 0) == GCD (1, V) == U. */ if (vsize == 0 || (usize == 1 && up[0] == 1)) { gst_mpz_copy_abs (g, u); return; } if (usize == 1) { gst_mpz_realloc (g, 1); g->size = 1; g->d[0] = mpn_gcd_1 (vp, vsize, up[0]); return; } if (vsize == 1) { gst_mpz_realloc (g, 1); g->size = 1; g->d[0] = mpn_gcd_1 (up, usize, vp[0]); return; } /* Eliminate low zero bits from U and V and move to temporary storage. */ u_zero_bits = mpn_scan1 (up, 0); u_zero_limbs = u_zero_bits / BITS_PER_MP_LIMB; u_zero_bits &= BITS_PER_MP_LIMB - 1; up += u_zero_limbs; usize -= u_zero_limbs; /* Operands could be destroyed for big-endian case, but let's be tidy. */ tp = up; up = (mp_ptr) alloca (usize * SIZEOF_MP_LIMB_T); if (u_zero_bits != 0) { mpn_rshift (up, tp, usize, u_zero_bits); usize -= up[usize - 1] == 0; } else MPN_COPY (up, tp, usize); v_zero_bits = mpn_scan1 (vp, 0); v_zero_limbs = v_zero_bits / BITS_PER_MP_LIMB; v_zero_bits &= BITS_PER_MP_LIMB - 1; vp += v_zero_limbs; vsize -= v_zero_limbs; /* Operands could be destroyed for big-endian case, but let's be tidy. */ tp = vp; vp = (mp_ptr) alloca (vsize * SIZEOF_MP_LIMB_T); if (v_zero_bits != 0) { mpn_rshift (vp, tp, vsize, v_zero_bits); vsize -= vp[vsize - 1] == 0; } else MPN_COPY (vp, tp, vsize); if (u_zero_limbs > v_zero_limbs) { g_zero_limbs = v_zero_limbs; g_zero_bits = v_zero_bits; } else if (u_zero_limbs < v_zero_limbs) { g_zero_limbs = u_zero_limbs; g_zero_bits = u_zero_bits; } else /* Equal. */ { g_zero_limbs = u_zero_limbs; g_zero_bits = MIN (u_zero_bits, v_zero_bits); } /* Call mpn_gcd. The 2nd argument must not have more bits than the 1st. */ vsize = (usize < vsize || (usize == vsize && up[usize-1] < vp[vsize-1])) ? mpn_gcd (vp, vp, vsize, up, usize) : mpn_gcd (vp, up, usize, vp, vsize); /* Here G <-- V << (g_zero_limbs*BITS_PER_MP_LIMB + g_zero_bits). */ gsize = vsize + g_zero_limbs; if (g_zero_bits != 0) { mp_limb_t cy_limb; gsize += (vp[vsize - 1] >> (BITS_PER_MP_LIMB - g_zero_bits)) != 0; if (g->alloc < gsize) gst_mpz_realloc (g, gsize); MPN_ZERO (g->d, g_zero_limbs); tp = g->d + g_zero_limbs; cy_limb = mpn_lshift (tp, vp, vsize, g_zero_bits); if (cy_limb != 0) tp[vsize] = cy_limb; } else { if (g->alloc < gsize) gst_mpz_realloc (g, gsize); MPN_ZERO (g->d, g_zero_limbs); MPN_COPY (g->d + g_zero_limbs, vp, vsize); } g->size = gsize; alloca (0); } void _gst_mpz_fdiv_qr (gst_mpz *quot, gst_mpz *rem, const gst_mpz *dividend, const gst_mpz *divisor) { if ((dividend->size ^ divisor->size) >= 0) { /* When the dividend and the divisor has same sign, this function gives same result as _gst_mpz_tdiv_qr. */ _gst_mpz_tdiv_qr (quot, rem, dividend, divisor); } else { gst_mpz temp_divisor; /* N.B.: lives until function returns! */ /* We need the original value of the divisor after the quotient and remainder have been preliminary calculated. We have to copy it to temporary space if it's the same variable as either QUOT or REM. */ if (quot == divisor || rem == divisor) { MPZ_TMP_INIT (&temp_divisor, ABS (divisor->size)); _gst_mpz_set (&temp_divisor, divisor); divisor = &temp_divisor; } _gst_mpz_tdiv_qr (quot, rem, dividend, divisor); if (rem->size != 0) { gst_mpz_sub_ui (quot, quot, 1); _gst_mpz_add (rem, rem, divisor); } } } mp_limb_t _gst_mpz_fdiv_qr_si (gst_mpz *quot, const gst_mpz *dividend, intptr_t divisor) { mp_limb_t rem = _gst_mpz_tdiv_qr_si (quot, dividend, divisor); /* When the dividend and the divisor has same sign, or if the division is exact, this function gives same result as _gst_mpz_tdiv_qr_si. */ if ((dividend->size ^ divisor) < 0 && rem != 0) { gst_mpz_sub_ui (quot, quot, 1); rem += divisor; } return rem; } void _gst_mpz_mul (gst_mpz *w, const gst_mpz *u, const gst_mpz *v) { mp_size_t usize = u->size; mp_size_t vsize = v->size; mp_size_t wsize; mp_size_t sign_product; mp_ptr up, vp; mp_ptr wp; mp_ptr free_me = NULL; sign_product = usize ^ vsize; usize = ABS (usize); vsize = ABS (vsize); if (usize < vsize) { /* Swap U and V. */ {const gst_mpz *t = u; u = v; v = t;} {mp_size_t t = usize; usize = vsize; vsize = t;} } up = u->d; vp = v->d; wp = w->d; /* Ensure W has space enough to store the result. */ wsize = usize + vsize; if (w->alloc < wsize) { if (wp == up || wp == vp) free_me = wp; else xfree (wp); w->alloc = wsize; wp = (mp_ptr) xmalloc (wsize * SIZEOF_MP_LIMB_T); w->d = wp; } else { /* Make U and V not overlap with W. */ if (wp == up) { /* W and U are identical. Allocate temporary space for U. */ up = (mp_ptr) alloca (usize * SIZEOF_MP_LIMB_T); /* Is V identical too? Keep it identical with U. */ if (wp == vp) vp = up; /* Copy to the temporary space. */ MPN_COPY (up, wp, usize); } else if (wp == vp) { /* W and V are identical. Allocate temporary space for V. */ vp = (mp_ptr) alloca (vsize * SIZEOF_MP_LIMB_T); /* Copy to the temporary space. */ MPN_COPY (vp, wp, vsize); } } mpn_mul (wp, up, usize, vp, vsize); w->size = sign_product < 0 ? -wsize : wsize; if (free_me != NULL) xfree (free_me); alloca (0); } void _gst_mpz_mul_2exp (gst_mpz *w, const gst_mpz *u, unsigned cnt) { mp_size_t usize = u->size; mp_size_t abs_usize = ABS (usize); mp_size_t wsize; mp_size_t limb_cnt; mp_ptr wp; mp_limb_t wdigit; if (usize == 0) { w->size = 0; return; } limb_cnt = cnt / BITS_PER_MP_LIMB; wsize = abs_usize + limb_cnt + 1; if (w->alloc < wsize) gst_mpz_realloc (w, wsize); wp = w->d; if (cnt % BITS_PER_MP_LIMB) { wdigit = mpn_lshift (wp + limb_cnt, u->d, abs_usize, cnt % BITS_PER_MP_LIMB); wsize = abs_usize + limb_cnt; if (wdigit != 0) { wp[wsize] = wdigit; wsize++; } } else { MPN_COPY (wp + limb_cnt, u->d, abs_usize); wsize = abs_usize + limb_cnt; } /* Zero all whole digits at low end. Do it here and not before calling mpn_lshift, not to loose for U == W. */ MPN_ZERO (wp, limb_cnt); w->size = (usize >= 0) ? wsize : -wsize; } void _gst_mpz_set (gst_mpz *w, const gst_mpz *u) { mp_size_t usize; mp_size_t abs_usize; usize = u->size; abs_usize = ABS (usize); /* If not space for sum (and possible carry), increase space. */ if (w->alloc < abs_usize) gst_mpz_realloc (w, abs_usize); w->size = usize; MPN_COPY (w->d, u->d, abs_usize); } void _gst_mpz_sub (gst_mpz *w, const gst_mpz *u, const gst_mpz *v) { mp_srcptr up, vp; mp_ptr wp; mp_size_t usize, vsize, wsize; mp_size_t abs_usize; mp_size_t abs_vsize; usize = u->size; vsize = -v->size; /* The "-" makes the difference from _gst_mpz_add */ abs_usize = ABS (usize); abs_vsize = ABS (vsize); if (abs_usize < abs_vsize) { /* Swap U and V. */ {const gst_mpz *t = u; u = v; v = t;} {mp_size_t t = usize; usize = vsize; vsize = t;} {mp_size_t t = abs_usize; abs_usize = abs_vsize; abs_vsize = t;} } /* True: abs(USIZE) >= abs(VSIZE) */ /* If not space for sum (and possible carry), increase space. */ wsize = abs_usize + 1; if (w->alloc < wsize) gst_mpz_realloc (w, wsize); /* These must be after realloc (u or v may be the same as w). */ up = u->d; vp = v->d; wp = w->d; if (usize >= 0) { if (vsize >= 0) { wsize = mpn_add (wp, up, abs_usize, vp, abs_vsize); if (wsize != 0) wp[abs_usize] = 1; wsize = wsize + abs_usize; } else { /* The signs are different. Need exact comparision to determine which operand to subtract from which. */ if (abs_usize == abs_vsize && mpn_cmp (up, vp, abs_usize) < 0) wsize = -(abs_usize + mpn_sub (wp, vp, abs_usize, up, abs_usize)); else wsize = abs_usize + mpn_sub (wp, up, abs_usize, vp, abs_vsize); } } else { if (vsize >= 0) { /* The signs are different. Need exact comparision to determine which operand to subtract from which. */ if (abs_usize == abs_vsize && mpn_cmp (up, vp, abs_usize) < 0) wsize = abs_usize + mpn_sub (wp, vp, abs_usize, up, abs_usize); else wsize = -(abs_usize + mpn_sub (wp, up, abs_usize, vp, abs_vsize)); } else { wsize = mpn_add (wp, up, abs_usize, vp, abs_vsize); if (wsize != 0) wp[abs_usize] = 1; wsize = -(wsize + abs_usize); } } w->size = wsize; } mst_Boolean _gst_mpz_get_d(const gst_mpz *mpz, double *p_d) { double d, old; int n; n = mpz->size; while (mpz->d[--n] == 0) ; d = 0.0; for (; n >= 0; n--) { old = ldexp (d, 8 * SIZEOF_MP_LIMB_T); d = old + mpz->d[n]; if (d - old < mpz->d[n]) /* Lost some bytes of precision, exit now. */ return false; } *p_d = d; return true; } mst_Boolean _gst_mpz_get_ld(const gst_mpz *mpz, long double *p_ld) { long double d, old; int n; n = mpz->size; while (mpz->d[--n] == 0) ; d = 0.0; for (; n >= 0; n--) { old = ldexpl (d, 8 * SIZEOF_MP_LIMB_T); d = old + mpz->d[n]; if (d - old < mpz->d[n]) /* Lost some bytes of precision, exit now. */ return false; } *p_ld = d; return true; } void _gst_mpz_and (gst_mpz *res, const gst_mpz *op1, const gst_mpz *op2) { mp_srcptr op1_ptr, op2_ptr; mp_size_t op1_size, op2_size; mp_ptr res_ptr; mp_size_t res_size; mp_size_t i; op1_size = op1->size; op2_size = op2->size; op1_ptr = op1->d; op2_ptr = op2->d; res_ptr = res->d; if (op1_size >= 0) { if (op2_size >= 0) { res_size = MIN (op1_size, op2_size); /* First loop finds the size of the result. */ for (i = res_size - 1; i >= 0; i--) if ((op1_ptr[i] & op2_ptr[i]) != 0) break; res_size = i + 1; /* Handle allocation, now then we know exactly how much space is needed for the result. */ if (res->alloc < res_size) { gst_mpz_realloc (res, res_size); op1_ptr = op1->d; op2_ptr = op2->d; res_ptr = res->d; } /* Second loop computes the real result. */ for (i = res_size - 1; i >= 0; i--) res_ptr[i] = op1_ptr[i] & op2_ptr[i]; res->size = res_size; return; } else /* op2_size < 0 */ { /* Fall through to the code at the end of the function. */ } } else { if (op2_size < 0) { mp_ptr opx; mp_limb_t cy; mp_size_t res_alloc; /* Both operands are negative, so will be the result. -((-OP1) & (-OP2)) = -(~(OP1 - 1) & ~(OP2 - 1)) = = ~(~(OP1 - 1) & ~(OP2 - 1)) + 1 = = ((OP1 - 1) | (OP2 - 1)) + 1 */ /* It might seem as we could end up with an (invalid) result with a leading zero-limb here when one of the operands is of the type 1,,0,,..,,.0. But some analysis shows that we surely would get carry into the zero-limb in this situation... */ op1_size = -op1_size; op2_size = -op2_size; res_alloc = 1 + MAX (op1_size, op2_size); opx = (mp_ptr) alloca (op1_size * SIZEOF_MP_LIMB_T); mpn_sub_1 (opx, op1_ptr, op1_size, (mp_limb_t) 1); op1_ptr = opx; opx = (mp_ptr) alloca (op2_size * SIZEOF_MP_LIMB_T); mpn_sub_1 (opx, op2_ptr, op2_size, (mp_limb_t) 1); op2_ptr = opx; if (res->alloc < res_alloc) { gst_mpz_realloc (res, res_alloc); res_ptr = res->d; /* Don't re-read OP1_PTR and OP2_PTR. They point to temporary space--never to the space RES->d used to point to before reallocation. */ } if (op1_size >= op2_size) { MPN_COPY (res_ptr + op2_size, op1_ptr + op2_size, op1_size - op2_size); for (i = op2_size - 1; i >= 0; i--) res_ptr[i] = op1_ptr[i] | op2_ptr[i]; res_size = op1_size; } else { MPN_COPY (res_ptr + op1_size, op2_ptr + op1_size, op2_size - op1_size); for (i = op1_size - 1; i >= 0; i--) res_ptr[i] = op1_ptr[i] | op2_ptr[i]; res_size = op2_size; } cy = mpn_add_1 (res_ptr, res_ptr, res_size, (mp_limb_t) 1); if (cy) { res_ptr[res_size] = cy; res_size++; } res->size = -res_size; return; } else { /* We should compute -OP1 & OP2. Swap OP1 and OP2 and fall through to the code that handles OP1 & -OP2. */ {const gst_mpz *t = op1; op1 = op2; op2 = t;} {const mp_limb_t *t = op1_ptr; op1_ptr = op2_ptr; op2_ptr = t;} {const mp_size_t t = op1_size; op1_size = op2_size; op2_size = t;} } } { /* OP1 is positive and zero-extended, OP2 is negative and ones-extended. The result will be positive. OP1 & -OP2 = OP1 & ~(OP2 - 1). */ mp_ptr opx; op2_size = -op2_size; opx = (mp_ptr) alloca (op2_size * SIZEOF_MP_LIMB_T); mpn_sub_1 (opx, op2_ptr, op2_size, (mp_limb_t) 1); op2_ptr = opx; if (op1_size > op2_size) { /* The result has the same size as OP1, since OP1 is normalized and longer than the ones-extended OP2. */ res_size = op1_size; /* Handle allocation, now then we know exactly how much space is needed for the result. */ if (res->alloc < res_size) { gst_mpz_realloc (res, res_size); res_ptr = res->d; op1_ptr = op1->d; /* Don't re-read OP2_PTR. It points to temporary space--never to the space RES->d used to point to before reallocation. */ } MPN_COPY (res_ptr + op2_size, op1_ptr + op2_size, res_size - op2_size); for (i = op2_size - 1; i >= 0; i--) res_ptr[i] = op1_ptr[i] & ~op2_ptr[i]; res->size = res_size; } else { /* Find out the exact result size. Ignore the high limbs of OP2, OP1 is zero-extended and would make the result zero. */ for (i = op1_size - 1; i >= 0; i--) if ((op1_ptr[i] & ~op2_ptr[i]) != 0) break; res_size = i + 1; /* Handle allocation, now then we know exactly how much space is needed for the result. */ if (res->alloc < res_size) { gst_mpz_realloc (res, res_size); res_ptr = res->d; op1_ptr = op1->d; /* Don't re-read OP2_PTR. It points to temporary space--never to the space RES->d used to point to before reallocation. */ } for (i = res_size - 1; i >= 0; i--) res_ptr[i] = op1_ptr[i] & ~op2_ptr[i]; res->size = res_size; } } } void _gst_mpz_ior (gst_mpz *res, const gst_mpz *op1, const gst_mpz *op2) { mp_srcptr op1_ptr, op2_ptr; mp_size_t op1_size, op2_size; mp_ptr res_ptr; mp_size_t res_size; mp_size_t i; op1_size = op1->size; op2_size = op2->size; op1_ptr = op1->d; op2_ptr = op2->d; res_ptr = res->d; if (op1_size >= 0) { if (op2_size >= 0) { if (op1_size >= op2_size) { if (res->alloc < op1_size) { gst_mpz_realloc (res, op1_size); op1_ptr = op1->d; op2_ptr = op2->d; res_ptr = res->d; } if (res_ptr != op1_ptr) MPN_COPY (res_ptr + op2_size, op1_ptr + op2_size, op1_size - op2_size); for (i = op2_size - 1; i >= 0; i--) res_ptr[i] = op1_ptr[i] | op2_ptr[i]; res_size = op1_size; } else { if (res->alloc < op2_size) { gst_mpz_realloc (res, op2_size); op1_ptr = op1->d; op2_ptr = op2->d; res_ptr = res->d; } if (res_ptr != op2_ptr) MPN_COPY (res_ptr + op1_size, op2_ptr + op1_size, op2_size - op1_size); for (i = op1_size - 1; i >= 0; i--) res_ptr[i] = op1_ptr[i] | op2_ptr[i]; res_size = op2_size; } res->size = res_size; return; } else /* op2_size < 0 */ { /* Fall through to the code at the end of the function. */ } } else { if (op2_size < 0) { mp_ptr opx; mp_limb_t cy; /* Both operands are negative, so will be the result. -((-OP1) | (-OP2)) = -(~(OP1 - 1) | ~(OP2 - 1)) = = ~(~(OP1 - 1) | ~(OP2 - 1)) + 1 = = ((OP1 - 1) & (OP2 - 1)) + 1 */ op1_size = -op1_size; op2_size = -op2_size; res_size = MIN (op1_size, op2_size); /* Possible optimization: Decrease mpn_sub precision, as we won't use the entire res of both. */ opx = (mp_ptr) alloca (res_size * SIZEOF_MP_LIMB_T); mpn_sub_1 (opx, op1_ptr, res_size, (mp_limb_t) 1); op1_ptr = opx; opx = (mp_ptr) alloca (res_size * SIZEOF_MP_LIMB_T); mpn_sub_1 (opx, op2_ptr, res_size, (mp_limb_t) 1); op2_ptr = opx; if (res->alloc < res_size) { gst_mpz_realloc (res, res_size); res_ptr = res->d; /* Don't re-read OP1_PTR and OP2_PTR. They point to temporary space--never to the space RES->d used to point to before reallocation. */ } /* First loop finds the size of the result. */ for (i = res_size - 1; i >= 0; i--) if ((op1_ptr[i] & op2_ptr[i]) != 0) break; res_size = i + 1; if (res_size != 0) { /* Second loop computes the real result. */ for (i = res_size - 1; i >= 0; i--) res_ptr[i] = op1_ptr[i] & op2_ptr[i]; cy = mpn_add_1 (res_ptr, res_ptr, res_size, (mp_limb_t) 1); if (cy) { res_ptr[res_size] = cy; res_size++; } } else { res_ptr[0] = 1; res_size = 1; } res->size = -res_size; return; } else { /* We should compute -OP1 | OP2. Swap OP1 and OP2 and fall through to the code that handles OP1 | -OP2. */ {const gst_mpz *t = op1; op1 = op2; op2 = t;} {const mp_limb_t *t = op1_ptr; op1_ptr = op2_ptr; op2_ptr = t;} {const mp_size_t t = op1_size; op1_size = op2_size; op2_size = t;} } } { mp_ptr opx; mp_limb_t cy; mp_size_t res_alloc; mp_size_t count; /* Operand 2 negative, so will be the result. -(OP1 | (-OP2)) = -(OP1 | ~(OP2 - 1)) = = ~(OP1 | ~(OP2 - 1)) + 1 = = (~OP1 & (OP2 - 1)) + 1 */ op2_size = -op2_size; res_alloc = op2_size; opx = (mp_ptr) alloca (op2_size * SIZEOF_MP_LIMB_T); mpn_sub_1 (opx, op2_ptr, op2_size, (mp_limb_t) 1); op2_ptr = opx; op2_size -= op2_ptr[op2_size - 1] == 0; if (res->alloc < res_alloc) { gst_mpz_realloc (res, res_alloc); op1_ptr = op1->d; res_ptr = res->d; /* Don't re-read OP2_PTR. It points to temporary space--never to the space RES->d used to point to before reallocation. */ } if (op1_size >= op2_size) { /* We can just ignore the part of OP1 that stretches above OP2, because the result limbs are zero there. */ /* First loop finds the size of the result. */ for (i = op2_size - 1; i >= 0; i--) if ((~op1_ptr[i] & op2_ptr[i]) != 0) break; res_size = i + 1; count = res_size; } else { res_size = op2_size; /* Copy the part of OP2 that stretches above OP1, to RES. */ MPN_COPY (res_ptr + op1_size, op2_ptr + op1_size, op2_size - op1_size); count = op1_size; } if (res_size != 0) { /* Second loop computes the real result. */ for (i = count - 1; i >= 0; i--) res_ptr[i] = ~op1_ptr[i] & op2_ptr[i]; cy = mpn_add_1 (res_ptr, res_ptr, res_size, (mp_limb_t) 1); if (cy) { res_ptr[res_size] = cy; res_size++; } } else { res_ptr[0] = 1; res_size = 1; } res->size = -res_size; } } void _gst_mpz_xor (gst_mpz *res, const gst_mpz *op1, const gst_mpz *op2) { mp_srcptr op1_ptr, op2_ptr; mp_size_t op1_size, op2_size; mp_ptr res_ptr; mp_size_t res_size, res_alloc; mp_size_t i; op1_size = op1->size; op2_size = op2->size; op1_ptr = op1->d; op2_ptr = op2->d; res_ptr = res->d; if (op1_size >= 0) { if (op2_size >= 0) { if (op1_size >= op2_size) { if (res->alloc < op1_size) { gst_mpz_realloc (res, op1_size); op1_ptr = op1->d; op2_ptr = op2->d; res_ptr = res->d; } if (res_ptr != op1_ptr) MPN_COPY (res_ptr + op2_size, op1_ptr + op2_size, op1_size - op2_size); for (i = op2_size - 1; i >= 0; i--) res_ptr[i] = op1_ptr[i] ^ op2_ptr[i]; res_size = op1_size; } else { if (res->alloc < op2_size) { gst_mpz_realloc (res, op2_size); op1_ptr = op1->d; op2_ptr = op2->d; res_ptr = res->d; } if (res_ptr != op2_ptr) MPN_COPY (res_ptr + op1_size, op2_ptr + op1_size, op2_size - op1_size); for (i = op1_size - 1; i >= 0; i--) res_ptr[i] = op1_ptr[i] ^ op2_ptr[i]; res_size = op2_size; } res->size = res_size; return; } else /* op2_size < 0 */ { /* Fall through to the code at the end of the function. */ } } else { if (op2_size < 0) { mp_ptr opx; /* Both operands are negative, the result will be positive. (-OP1) ^ (-OP2) = = ~(OP1 - 1) ^ ~(OP2 - 1) = = (OP1 - 1) ^ (OP2 - 1) */ op1_size = -op1_size; op2_size = -op2_size; /* Possible optimization: Decrease mpn_sub precision, as we won't use the entire res of both. */ opx = (mp_ptr) alloca (op1_size * SIZEOF_MP_LIMB_T); mpn_sub_1 (opx, op1_ptr, op1_size, (mp_limb_t) 1); op1_ptr = opx; opx = (mp_ptr) alloca (op2_size * SIZEOF_MP_LIMB_T); mpn_sub_1 (opx, op2_ptr, op2_size, (mp_limb_t) 1); op2_ptr = opx; res_alloc = MAX (op1_size, op2_size); if (res->alloc < res_alloc) { gst_mpz_realloc (res, res_alloc); res_ptr = res->d; /* Don't re-read OP1_PTR and OP2_PTR. They point to temporary space--never to the space RES->d used to point to before reallocation. */ } if (op1_size > op2_size) { MPN_COPY (res_ptr + op2_size, op1_ptr + op2_size, op1_size - op2_size); for (i = op2_size - 1; i >= 0; i--) res_ptr[i] = op1_ptr[i] ^ op2_ptr[i]; res_size = op1_size; } else { MPN_COPY (res_ptr + op1_size, op2_ptr + op1_size, op2_size - op1_size); for (i = op1_size - 1; i >= 0; i--) res_ptr[i] = op1_ptr[i] ^ op2_ptr[i]; res_size = op2_size; } res->size = res_size; return; } else { /* We should compute -OP1 ^ OP2. Swap OP1 and OP2 and fall through to the code that handles OP1 ^ -OP2. */ {const gst_mpz *t = op1; op1 = op2; op2 = t;} {const mp_limb_t *t = op1_ptr; op1_ptr = op2_ptr; op2_ptr = t;} {const mp_size_t t = op1_size; op1_size = op2_size; op2_size = t;} } } { mp_ptr opx; mp_limb_t cy; /* Operand 2 negative, so will be the result. -(OP1 ^ (-OP2)) = -(OP1 ^ ~(OP2 - 1)) = = ~(OP1 ^ ~(OP2 - 1)) + 1 = = (OP1 ^ (OP2 - 1)) + 1 */ op2_size = -op2_size; opx = (mp_ptr) alloca (op2_size * SIZEOF_MP_LIMB_T); mpn_sub_1 (opx, op2_ptr, op2_size, (mp_limb_t) 1); op2_ptr = opx; res_alloc = MAX (op1_size, op2_size) + 1; if (res->alloc < res_alloc) { gst_mpz_realloc (res, res_alloc); op1_ptr = op1->d; res_ptr = res->d; /* Don't re-read OP2_PTR. It points to temporary space--never to the space RES->d used to point to before reallocation. */ } if (op1_size > op2_size) { MPN_COPY (res_ptr + op2_size, op1_ptr + op2_size, op1_size - op2_size); for (i = op2_size - 1; i >= 0; i--) res_ptr[i] = op1_ptr[i] ^ op2_ptr[i]; res_size = op1_size; } else { MPN_COPY (res_ptr + op1_size, op2_ptr + op1_size, op2_size - op1_size); for (i = op1_size - 1; i >= 0; i--) res_ptr[i] = op1_ptr[i] ^ op2_ptr[i]; res_size = op2_size; } cy = mpn_add_1 (res_ptr, res_ptr, res_size, (mp_limb_t) 1); if (cy) { res_ptr[res_size] = cy; res_size++; } res->size = -res_size; } } #if __GNU_MP_VERSION >= 5 extern void __gmpn_divexact (mp_ptr, mp_srcptr, mp_size_t, mp_srcptr, mp_size_t); #endif void _gst_mpz_divexact (gst_mpz *quot, const gst_mpz *num, const gst_mpz *den) { mp_ptr qp; mp_srcptr np, dp; mp_size_t nsize, dsize, qsize; #if __GNU_MP_VERSION < 5 mp_ptr tp; mp_size_t d_zero_limbs; int d_zero_bits; #endif nsize = ABS (num->size); dsize = ABS (den->size); np = num->d; dp = den->d; if (nsize == 0 || (nsize == 1 && np[0] == 0)) { quot->size = 0; return; } /* Check if newer GMP makes mpn_divexact_1 public. */ if (dsize == 1) { _gst_mpz_tdiv_q_ui (quot, num, dp[0]); if (den->size < 0) quot->size = -quot->size; return; } #if __GNU_MP_VERSION < 5 /* Avoid quadratic behaviour, but do it conservatively. */ if (nsize - dsize > 1500) { gst_mpz r = { 0, 0, NULL }; gst_mpz_realloc (&r, dsize + 1); _gst_mpz_tdiv_qr (quot, &r, num, den); _gst_mpz_clear (&r); return; } /* QUOT <-- NUM/2^r, T <-- DEN/2^r where = r number of twos in DEN. */ d_zero_bits = mpn_scan1 (dp, 0); d_zero_limbs = d_zero_bits / BITS_PER_MP_LIMB; d_zero_bits &= BITS_PER_MP_LIMB - 1; dp += d_zero_limbs; dsize -= d_zero_limbs; np += d_zero_limbs; nsize -= d_zero_limbs; #endif /* Allocate where we place the result. It must be nsize limbs big because it also acts as a temporary area. */ if (quot->alloc < nsize) gst_mpz_realloc (quot, nsize); qp = quot->d; #if __GNU_MP_VERSION < 5 if (d_zero_bits != 0) { tp = (mp_ptr) alloca (dsize * SIZEOF_MP_LIMB_T); mpn_rshift (tp, dp, dsize, d_zero_bits); mpn_rshift (qp, np, nsize, d_zero_bits); dsize -= tp[dsize - 1] == 0; nsize -= qp[nsize - 1] == 0; dp = tp; } else MPN_COPY(qp, np, nsize); #endif qsize = nsize - dsize + 1; #if __GNU_MP_VERSION < 5 mpn_bdivmod (qp, qp, nsize, dp, dsize, qsize * GMP_NUMB_BITS); #else __gmpn_divexact (qp, np, nsize, dp, dsize); #endif quot->size = (num->size ^ den->size) >= 0 ? qsize : -qsize; } void _gst_mpz_from_oop(gst_mpz *mpz, OOP srcOOP) { OOP srcClass; gst_byte_array ba; mp_limb_t *src, *dest, adjust; int n; if (IS_INT(srcOOP)) { intptr_t i = TO_INT(srcOOP); gst_mpz_realloc (mpz, 1); mpz->size = i < 0 ? -1 : 1; mpz->d[0] = i < 0 ? -i : i; return; } ba = (gst_byte_array) OOP_TO_OBJ(srcOOP); n = TO_INT (ba->objSize) - OBJ_HEADER_SIZE_WORDS; srcClass = OOP_CLASS(srcOOP); src = (mp_limb_t *) ba->bytes; if (srcClass == _gst_large_zero_integer_class) { gst_mpz_realloc (mpz, 1); mpz->size = 1; mpz->d[0] = 0; return; } adjust = ((mp_limb_t) ~0UL) >> (8 * (srcOOP->flags & EMPTY_BYTES)); #ifdef WORDS_BIGENDIAN /* Big-endian code, we cannot optimize anything... */ gst_mpz_realloc(mpz, n); dest = mpz->d; if (srcClass == _gst_large_negative_integer_class) { mpz->size = -n; while (n-- && *src == 0) *dest++ = *src++; *dest++ = -BYTE_INVERT(*src), src++; while (n--) *dest++ = ~BYTE_INVERT(*src), src++; } else { mpz->size = n; while (n--) *dest++ = BYTE_INVERT(*src), src++; } #else /* Little-endian code, we can optimize positive integers. */ if (srcClass == _gst_large_negative_integer_class) { gst_mpz_realloc(mpz, n); mpz->size = -n; dest = mpz->d; while (n-- && *src == 0) *dest++ = *src++; *dest++ = -*src++; while (n--) *dest++ = ~*src++; } else if (n % (sizeof (mp_limb_t) / sizeof (PTR))) { /* We have half a limb in the LargeInteger, so we cannot work directly in the object data. */ mpz->size = n; while (n--) *dest++ = ~*src++; } else { /* Point directly in the bytes */ xfree (mpz->d); mpz->alloc = 0; mpz->size = n; mpz->d = src; dest = src + n; } #endif /* DEST now points past the limbs in the new gst_mpz. Don't do gratuitous writes to avoid over-GCing. */ if (dest[-1] & ~adjust) dest[-1] &= adjust; /* A few functions require that the most significant limb be >0. */ if (mpz->size < 0 && mpz->d[-mpz->size-1] == 0) mpz->size++; else if (mpz->size > 0 && mpz->d[mpz->size-1] == 0) mpz->size--; } OOP _gst_oop_from_mpz(gst_mpz *mpz) { gst_uchar *bytes; mp_limb_t *limbs; mst_Boolean neg; int n; OOP oop; gst_byte_array ba; /* Convert to the absolute value (for ease in referencing mpz->size) and remove leading zero bytes. */ if (mpz->size < 0) { mpz->size = -mpz->size; neg = true; } else neg = false; while (mpz->size && mpz->d[mpz->size-1] == 0) mpz->size--; if (mpz->size == 0) return FROM_INT (0); /* Convert to two's complement form and create the object */ if (neg) { if (mpz->size == 1 && mpz->d[0] <= (mp_limb_t) -MIN_ST_INT) return FROM_INT(-(mp_limb_t) mpz->d[0]); n = mpz->size; limbs = mpz->d; while (n-- && *limbs == 0) limbs++; *limbs = -*limbs; for (limbs++; n--; limbs++) *limbs = ~*limbs; } else { if (mpz->size == 1 && mpz->d[0] <= (mp_limb_t) MAX_ST_INT) return FROM_INT ((mp_limb_t) mpz->d[0]); } #if WORDS_BIGENDIAN /* Convert to little-endian */ for (limbs = mpz->d, n = mpz->size; n--; limbs++) *limbs = BYTE_INVERT(*limbs); #endif /* Fill in the object */ n = SIZEOF_MP_LIMB_T * mpz->size; bytes = (gst_uchar *) mpz->d; if (neg) { /* Search where the number really ends -- discard trailing 111... bytes but remember, the most significant bit of the last digit must be 1! */ while (bytes[--n] == 255); if (bytes[n] < 128) n++; ba = (gst_byte_array) new_instance_with (_gst_large_negative_integer_class, ++n, &oop); } else { /* Search where the number really ends -- discard trailing 000... bytes but remember, the most significant bit of the last digit must be 0! */ while (bytes[--n] == 0); if (bytes[n] >= 128) n++; ba = (gst_byte_array) new_instance_with (_gst_large_positive_integer_class, ++n, &oop); } /* If the last byte was not in our internal object (this is possible, for example 16r80000000 fits a single limb but uses a 5-byte object) fill in the last byte. */ if (n > SIZEOF_MP_LIMB_T * mpz->size) ba->bytes[--n] = neg ? 255 : 0; memcpy (ba->bytes, bytes, n); return oop; } #endif smalltalk-3.2.5/libgst/cint.h0000644000175000017500000001525412123404352013023 00000000000000/******************************** -*- C -*- **************************** * * External definitions for C - Smalltalk interface module * * ***********************************************************************/ /*********************************************************************** * * Copyright 1988,89,90,91,92,94,95,99,2000,2001,2002,2006,2008,2009 * Free Software Foundation, Inc. * Written by Steve Byrne. * * This file is part of GNU Smalltalk. * * GNU Smalltalk is free software; you can redistribute it and/or modify it * under the terms of the GNU General Public License as published by the Free * Software Foundation; either version 2, or (at your option) any later * version. * * Linking GNU Smalltalk statically or dynamically with other modules is * making a combined work based on GNU Smalltalk. Thus, the terms and * conditions of the GNU General Public License cover the whole * combination. * * In addition, as a special exception, the Free Software Foundation * give you permission to combine GNU Smalltalk with free software * programs or libraries that are released under the GNU LGPL and with * independent programs running under the GNU Smalltalk virtual machine. * * You may copy and distribute such a system following the terms of the * GNU GPL for GNU Smalltalk and the licenses of the other code * concerned, provided that you include the source code of that other * code when and as the GNU GPL requires distribution of source code. * * Note that people who make modified versions of GNU Smalltalk are not * obligated to grant this special exception for their modified * versions; it is their choice whether to do so. The GNU General * Public License gives permission to release a modified version without * this exception; this exception also makes it possible to release a * modified version which carries forward this exception. * * GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or * FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for * more details. * * You should have received a copy of the GNU General Public License along with * GNU Smalltalk; see the file COPYING. If not, write to the Free Software * Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * ***********************************************************************/ #ifndef GST_CINT_H #define GST_CINT_H typedef enum { /* types for C parameters */ CDATA_CHAR, CDATA_UCHAR, CDATA_SHORT, CDATA_USHORT, CDATA_LONG, CDATA_ULONG, CDATA_FLOAT, CDATA_DOUBLE, CDATA_STRING, CDATA_OOP, /* no conversion to-from C (OOP) */ CDATA_INT, CDATA_UINT, CDATA_LONG_DOUBLE, CDATA_UNKNOWN, /* when there is no type a priori */ CDATA_STRING_OUT, /* for things that modify string params */ CDATA_SYMBOL, CDATA_BYTEARRAY, CDATA_BYTEARRAY_OUT, CDATA_BOOLEAN, CDATA_VOID, /* valid only as a return type */ CDATA_VARIADIC, /* for parameters, this param is an array to be interpreted as arguments. Note that only simple conversions are performed in this case. */ CDATA_VARIADIC_OOP, /* for parameters, this param is an array whose elements are OOPs to be passed. */ CDATA_COBJECT, /* a C object is being passed */ CDATA_COBJECT_PTR, /* a C object pointer is being passed */ CDATA_SELF, /* pass self as the corresponding argument */ CDATA_SELF_OOP, /* pass self as an OOP */ CDATA_WCHAR, CDATA_WSTRING, CDATA_WSTRING_OUT, CDATA_SYMBOL_OUT, CDATA_LONGLONG, CDATA_ULONGLONG } cdata_type; /* Value of errno which is checked by the Smalltalk base classes. */ extern int _gst_errno ATTRIBUTE_HIDDEN; typedef struct gst_c_callable { OBJ_HEADER; OOP typeOOP; /* CObject fields */ OOP storageOOP; /* CObject fields */ OOP returnTypeOOP; /* Smalltalk return type */ OOP argTypesOOP; /* array of argument types */ OOP blockOOP; /* only for CCallbackDescriptor */ } *gst_c_callable; /* Returns the size of an object passed to a C routine with type TYPE. */ extern int _gst_c_type_size (int type); /* Called after GC to invalidate the cache for the libffi representation of CFunctionDescriptors. */ extern void _gst_invalidate_croutine_cache (void); /* Invokes a C routine. Arguments passed from Smalltalk are stored starting from ARGS, and the object to which the message that called-out was sent is RECEIVER. CFUNCOOP is the C function descriptor used to control the mapping of argument types from Smalltalk to C types and determines the mapping of the C function's return type into a Smalltalk type. The result is NULL if the call was not successful, an OOP holding the result otherwise. */ extern OOP _gst_invoke_croutine (OOP cFuncOOP, OOP receiver, OOP *args) ATTRIBUTE_HIDDEN; /* Defines the mapping between a string function name FUNCNAME and the address FUNCADDR of that function, for later use in lookup_function. The mapping table will expand as needed to hold new entries as they are added. */ extern void _gst_define_cfunc (const char *funcName, PTR funcAddr) ATTRIBUTE_HIDDEN; /* Adds to the mapping table the standard C functions supported by GNU Smalltalk. */ extern void _gst_init_cfuncs (void) ATTRIBUTE_HIDDEN; /* Set the value of errno which is checked by Smalltalk to be errnum. */ extern void _gst_set_errno(int errnum) ATTRIBUTE_HIDDEN; /* Returns the address for the latest C function which has been registered using _gst_define_cfunc with the name FUNCNAME. Returns NULL if there is no such function. */ extern PTR _gst_lookup_function (const char *funcName) ATTRIBUTE_HIDDEN; /* Creates a closure for the CCallbackDescriptor CALLBACKOOP and stores it in the object. */ extern void _gst_make_closure (OOP callbackOOP) ATTRIBUTE_HIDDEN; /* Frees the info for the closure in the CCallbackDescriptor CALLBACKOOP. */ extern void _gst_free_closure (OOP callbackOOP) ATTRIBUTE_HIDDEN; /* Call lt_dlopenext with FILENAME, and invoke gst_initModule if it is found in the library. If MODULE is false, add the file to the list of libraries that Smalltalk searches for external symbols. */ extern mst_Boolean _gst_dlopen (const char *filename, mst_Boolean module); /* Add DIR at the beginning of the libltdl search path. */ extern void _gst_dladdsearchdir (const char *dir) ATTRIBUTE_HIDDEN; /* Push the current libltdl search path. */ extern void _gst_dlpushsearchpath (void) ATTRIBUTE_HIDDEN; /* Pop the saved search path into the current libltdl search path. */ extern void _gst_dlpopsearchpath (void) ATTRIBUTE_HIDDEN; #endif /* GST_CINT_H */ smalltalk-3.2.5/libgst/byte.h0000644000175000017500000002307112123404352013025 00000000000000/******************************** -*- C -*- **************************** * * Byte Code definitions. * * ***********************************************************************/ /*********************************************************************** * * Copyright 1988,89,90,91,92,94,95,99,2000,2001,2002,2006,2008,2009 * Free Software Foundation, Inc. * Written by Steve Byrne. * * This file is part of GNU Smalltalk. * * GNU Smalltalk is free software; you can redistribute it and/or modify it * under the terms of the GNU General Public License as published by the Free * Software Foundation; either version 2, or (at your option) any later * version. * * Linking GNU Smalltalk statically or dynamically with other modules is * making a combined work based on GNU Smalltalk. Thus, the terms and * conditions of the GNU General Public License cover the whole * combination. * * In addition, as a special exception, the Free Software Foundation * give you permission to combine GNU Smalltalk with free software * programs or libraries that are released under the GNU LGPL and with * independent programs running under the GNU Smalltalk virtual machine. * * You may copy and distribute such a system following the terms of the * GNU GPL for GNU Smalltalk and the licenses of the other code * concerned, provided that you include the source code of that other * code when and as the GNU GPL requires distribution of source code. * * Note that people who make modified versions of GNU Smalltalk are not * obligated to grant this special exception for their modified * versions; it is their choice whether to do so. The GNU General * Public License gives permission to release a modified version without * this exception; this exception also makes it possible to release a * modified version which carries forward this exception. * * GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or * FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for * more details. * * You should have received a copy of the GNU General Public License along with * GNU Smalltalk; see the file COPYING. If not, write to the Free Software * Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * ***********************************************************************/ #ifndef GST_BYTE_H #define GST_BYTE_H enum { PLUS_SPECIAL = 0, MINUS_SPECIAL = 1, LESS_THAN_SPECIAL = 2, GREATER_THAN_SPECIAL = 3, LESS_EQUAL_SPECIAL = 4, GREATER_EQUAL_SPECIAL = 5, EQUAL_SPECIAL = 6, NOT_EQUAL_SPECIAL = 7, TIMES_SPECIAL = 8, DIVIDE_SPECIAL = 9, REMAINDER_SPECIAL = 10, BIT_XOR_SPECIAL = 11, BIT_SHIFT_SPECIAL = 12, INTEGER_DIVIDE_SPECIAL = 13, BIT_AND_SPECIAL = 14, BIT_OR_SPECIAL = 15, AT_SPECIAL = 16, AT_PUT_SPECIAL = 17, SIZE_SPECIAL = 18, CLASS_SPECIAL = 19, IS_NIL_SPECIAL = 20, NOT_NIL_SPECIAL = 21, VALUE_SPECIAL = 22, VALUE_COLON_SPECIAL = 23, SAME_OBJECT_SPECIAL = 24, JAVA_AS_INT_SPECIAL = 25, JAVA_AS_LONG_SPECIAL = 26, NEW_COLON_SPECIAL = 32, THIS_CONTEXT_SPECIAL = 33, SEND = 28, SEND_SUPER = 29, SEND_IMMEDIATE = 30, SEND_SUPER_IMMEDIATE = 31, PUSH_TEMPORARY_VARIABLE = 32, PUSH_OUTER_TEMP = 33, PUSH_LIT_VARIABLE = 34, PUSH_RECEIVER_VARIABLE = 35, STORE_TEMPORARY_VARIABLE = 36, STORE_OUTER_TEMP = 37, STORE_LIT_VARIABLE = 38, STORE_RECEIVER_VARIABLE = 39, JUMP_BACK = 40, JUMP = 41, POP_JUMP_TRUE = 42, POP_JUMP_FALSE = 43, PUSH_INTEGER = 44, PUSH_SPECIAL = 45, PUSH_LIT_CONSTANT = 46, POP_INTO_NEW_STACKTOP = 47, POP_STACK_TOP = 48, MAKE_DIRTY_BLOCK = 49, RETURN_METHOD_STACK_TOP = 50, RETURN_CONTEXT_STACK_TOP = 51, DUP_STACK_TOP = 52, EXIT_INTERPRETER = 53, LINE_NUMBER_BYTECODE = 54, EXT_BYTE = 55, PUSH_SELF = 56, NIL_INDEX = 0, TRUE_INDEX = TRUE_OOP_INDEX - NIL_OOP_INDEX, FALSE_INDEX = FALSE_OOP_INDEX - NIL_OOP_INDEX, THIS_CONTEXT_INDEX = -128, RECEIVER_INDEX = -129 }; enum { /* Causes _gst_line_number to always emit a line number bytecode. */ LN_FORCE = 1, /* If LN_ABSOLUTE is also set, causes _gst_line_number to emit an absolute ine number and use that line number as the offset. If not, _gst_line_number will emit line numbers relatives to that line. */ LN_RESET = 2, /* See above for description. */ LN_ABSOLUTE = 4 }; typedef struct bytecode_array { gst_uchar *base; /* base of the byte code array */ gst_uchar *ptr; /* current byte+1 of byte code array */ int maxLen; /* max allocated len of byte code array */ int stack_depth; int max_stack_depth; } *bc_vector; extern bc_vector _gst_cur_bytecodes ATTRIBUTE_HIDDEN; /* Add 1 to the current stack depth and adjust the maximum depth accordingly. */ #define INCR_STACK_DEPTH() do { \ if (++_gst_cur_bytecodes->stack_depth > \ _gst_cur_bytecodes->max_stack_depth) \ _gst_cur_bytecodes->max_stack_depth++; \ } while (0) /* Add N to the current stack depth and adjust the maximum depth accordingly. */ #define ADD_STACK_DEPTH(n) do { \ _gst_cur_bytecodes->stack_depth += (n); \ if (_gst_cur_bytecodes->stack_depth > _gst_cur_bytecodes->max_stack_depth) \ _gst_cur_bytecodes->max_stack_depth = _gst_cur_bytecodes->stack_depth; \ } while (0) /* Subtract N from the current stack depth. */ #define SUB_STACK_DEPTH(n) \ (assert (_gst_cur_bytecodes->stack_depth >= (n)), \ _gst_cur_bytecodes->stack_depth -= (n)) /* Subtract N from the current stack depth. */ #define GET_STACK_DEPTH() \ (_gst_cur_bytecodes->max_stack_depth) /* Allocate a new array of bytecodes. */ extern void _gst_alloc_bytecodes () ATTRIBUTE_HIDDEN; /* Called when byte code compilation is complete, this routine returns the set of byte codes that were compiled. Since compilation is complete, this routine also resets the internal state of the byte code compiler in preparation for next time. */ extern bc_vector _gst_get_bytecodes (void) ATTRIBUTE_HIDDEN; /* Called to save the set of byte codes currently being compiled and prepare for a new compilation of byte codes. The current set of byte codes being compiled is returned for the caller to keep and to later use in a _gst_restore_bytecode_array call. */ extern bc_vector _gst_save_bytecode_array () ATTRIBUTE_HIDDEN; /* Restores the internal state of the byte code compiler so that it can continue compiling byte codes into the byte code array BYTECODES, which should have been returned at some previous point from _gst_save_bytecode_array(). Return the TAG that was passed to _gst_save_bytecode_array. */ extern void _gst_restore_bytecode_array (bc_vector) ATTRIBUTE_HIDDEN; /* This copies the byte instance variables out of the Smalltalk ByteArray object, BYTEARRAYOOP, and creates a bytecodes structure for it. This is used when a method is created by Smalltalk code. */ extern bc_vector _gst_extract_bytecodes (OOP byteArrayOOP) ATTRIBUTE_HIDDEN; /* This eliminates all the bytecodes in the array starting at the one pointed to by HERE. */ extern void _gst_truncate_bytecodes (gst_uchar * here, bc_vector bytecodes) ATTRIBUTE_HIDDEN; /* This compiles a LINE_NUMBER_BYTECODE if line is different from the last line we compiled, or if FORCE is true. */ extern void _gst_line_number (int line, int flags) ATTRIBUTE_HIDDEN; /* This tacks the bytecode BYTE, with argument ARG, at the end of the current bytecode array. */ extern void _gst_compile_byte (gst_uchar byte, int arg) ATTRIBUTE_HIDDEN; /* This tacks the contents of the BYTECODES array at the end of the current bytecode array, and then frees the array. */ extern void _gst_compile_and_free_bytecodes (bc_vector bytecodes) ATTRIBUTE_HIDDEN; /* This tacks the bytes starting at FROM (included) and ending at TO (excluded) at the end of the current bytecode array. */ extern void _gst_compile_bytecodes (gst_uchar * from, gst_uchar * to) ATTRIBUTE_HIDDEN; /* This frees the BYTECODES data structure. */ extern void _gst_free_bytecodes (bc_vector bytecodes) ATTRIBUTE_HIDDEN; /* This copies the contents of the bytecode array, BYTECODES, to the memory starting at DEST. */ extern void _gst_copy_bytecodes (gst_uchar * dest, bc_vector bytecodes) ATTRIBUTE_HIDDEN; /* This prints the bytecode pointed to by BP, using IP to resolve the offsets for the relative jumps. LITERAL_VEC is used to print the literals pointed to by the bytecodes. The first line is preceded by a tab character, subsequent lines are preceded by PREFIX and a tab. */ extern gst_uchar *_gst_print_bytecode_name (gst_uchar * bp, int ip, OOP * literal_vec, const char *prefix) ATTRIBUTE_HIDDEN; /* This prints the bytecode array, using LITERAL_VEC is used to print the literals pointed to by the bytecodes. */ extern void _gst_print_bytecodes (bc_vector bytecodes, OOP * literal_vec) ATTRIBUTE_HIDDEN; /* This returns the current number of bytecodes that have been compiled (the size of the current bytecode array). */ extern int _gst_current_bytecode_length (void) ATTRIBUTE_HIDDEN; /* This returns the number of bytecdoes compiled into the BYTECODES array. */ extern int _gst_bytecode_length (bc_vector bytecodes) ATTRIBUTE_HIDDEN; /* Returns the size of each bytecode, including the arguments. */ #define BYTECODE_SIZE 2 #endif /* GST_BYTE_H */ smalltalk-3.2.5/libgst/tree.h0000644000175000017500000003516712130343734013036 00000000000000/******************************** -*- C -*- **************************** * * Semantic Tree information declarations. * * ***********************************************************************/ /*********************************************************************** * * Copyright 1988,89,90,91,92,94,95,99,2000,2001,2002,2003,2006 * Free Software Foundation, Inc. * Written by Steve Byrne. * * This file is part of GNU Smalltalk. * * GNU Smalltalk is free software; you can redistribute it and/or modify it * under the terms of the GNU General Public License as published by the Free * Software Foundation; either version 2, or (at your option) any later * version. * * Linking GNU Smalltalk statically or dynamically with other modules is * making a combined work based on GNU Smalltalk. Thus, the terms and * conditions of the GNU General Public License cover the whole * combination. * * In addition, as a special exception, the Free Software Foundation * give you permission to combine GNU Smalltalk with free software * programs or libraries that are released under the GNU LGPL and with * independent programs running under the GNU Smalltalk virtual machine. * * You may copy and distribute such a system following the terms of the * GNU GPL for GNU Smalltalk and the licenses of the other code * concerned, provided that you include the source code of that other * code when and as the GNU GPL requires distribution of source code. * * Note that people who make modified versions of GNU Smalltalk are not * obligated to grant this special exception for their modified * versions; it is their choice whether to do so. The GNU General * Public License gives permission to release a modified version without * this exception; this exception also makes it possible to release a * modified version which carries forward this exception. * * GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or * FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for * more details. * * You should have received a copy of the GNU General Public License along with * GNU Smalltalk; see the file COPYING. If not, write to the Free Software * Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * ***********************************************************************/ #ifndef GST_TREE_H #define GST_TREE_H /* These are the possible types of parse-tree nodes */ typedef enum { TREE_METHOD_NODE, TREE_UNARY_EXPR, TREE_BINARY_EXPR, TREE_KEYWORD_EXPR, TREE_VARIABLE_NODE, TREE_ATTRIBUTE_LIST, TREE_KEYWORD_LIST, TREE_VAR_DECL_LIST, TREE_VAR_ASSIGN_LIST, TREE_STATEMENT_LIST, TREE_RETURN_EXPR, TREE_ASSIGN_EXPR, TREE_CONST_EXPR, TREE_SYMBOL_NODE, TREE_ARRAY_ELT_LIST, TREE_BLOCK_NODE, TREE_CASCADE_EXPR, TREE_MESSAGE_LIST, TREE_ARRAY_CONSTRUCTOR, TREE_FIRST = TREE_METHOD_NODE, TREE_LAST = TREE_ARRAY_CONSTRUCTOR } node_type; /* A structure holding a constant for objects having byte-sized indexed instance variables (ByteArrays and LargeIntegers). */ typedef struct byte_object { OOP class; int size; gst_uchar body[1]; } *byte_object; /* A forward declaration. */ typedef struct tree_node *tree_node; #include "gst-parse.h" /* A generic kind of parse-tree node that stores a list of nodes. In particular, NEXTADDR points to the last NEXT pointer in the list so that tail adds are easier. These nodes are also used for variables by storing their name in the NAME member and by setting an appropriate node type like TREE_VARIABLE_NODE (when the variable is an argument or the receiver of a message) or TREE_VAR_DECL_LIST (when the nodes is a list of arguments or temporaries). */ typedef struct list_node { const char *name; tree_node value; tree_node next; tree_node *nextAddr; } list_node; /* A parse-tree node for a message send. EXPRESSION is a list_node containing the arguments. The same data structure is also used for assignments (TREE_ASSIGN_EXPR) and in this case RECEIVER is the list of assigned-to variables, SELECTOR is dummy and EXPRESSION is the assigned value. */ typedef struct expr_node { tree_node receiver; OOP selector; tree_node expression; } expr_node; /* The different kinds of constants that can be stored in a const_node. */ typedef enum { CONST_BYTE_OBJECT, CONST_INT, CONST_CHAR, CONST_FLOATD, CONST_FLOATE, CONST_FLOATQ, CONST_STRING, CONST_OOP, CONST_BINDING, CONST_DEFERRED_BINDING, CONST_ARRAY } const_type; /* A parse-tree node holding a constant. CONSTTYPE identifies which kind of constant is stored, the VAL union can include an intptr_t, a double, a string (char *), an OOP (typically a Symbol, Association or ScaledDecimal), an array (stored as a list_node) or a byte_object struct (for ByteArrays and LargeIntegers). */ typedef struct const_node { const_type constType; union { intptr_t iVal; long double fVal; const char *sVal; OOP oopVal; tree_node aVal; byte_object boVal; } val; } const_node; /* A parse-tree node defining a method. SELECTOREXPR is an expr_node with a nil receiver, holding the selector for the method and a list_node (of type TREE_VAR_DECL_LIST) for the arguments. The method's temporaries and statements are also held in list_nodes (respectively, of course, TEMPORARIES and STATEMENTS). The final field is the ending position of the method in the current stream, or -1 if the stream is not file-based. */ typedef struct method_node { tree_node selectorExpr; tree_node temporaries; tree_node attributes; tree_node statements; int64_t endPos; mst_Boolean isOldSyntax; } method_node; /* A parse-tree node defining a block. Not having a name, blocks hold arguments in a simple list_node as well. */ typedef struct block_node { tree_node arguments; tree_node temporaries; tree_node statements; } block_node; /* A generic parse-tree node has a field marking the kind of node (NODETYPE) and a union holding the five different kinds of node (list_nodes, expr_nodes, const_node, method_nodes and block_nodes). */ struct tree_node { node_type nodeType; YYLTYPE location; union { list_node nvList; expr_node nvExpr; const_node nvConst; method_node nvMethod; block_node nvBlock; } nodeVal; }; #define v_block nodeVal.nvBlock #define v_list nodeVal.nvList #define v_expr nodeVal.nvExpr #define v_const nodeVal.nvConst #define v_method nodeVal.nvMethod /* Create a method_node with the given fields (see description under struct method_node). TEMPORARIES can possibly be NULL. If the method has any attributes associated with it, then they are in ATTRIBUTES. */ extern tree_node _gst_make_method (YYLTYPE *startLocation, YYLTYPE *endLocation, tree_node selectorExpr, tree_node temporaries, tree_node attributes, tree_node statements, int isOldSyntax) ATTRIBUTE_HIDDEN; /* Create an expr_node to be passed to _gst_make_method for a unary selector, or representing a send of a unary message UNARYSELECTOREXPR to the object identified by RECEIVER. */ extern tree_node _gst_make_unary_expr (YYLTYPE *location, tree_node receiver, const char *unarySelectorExpr) ATTRIBUTE_HIDDEN; /* Create an expr_node to be passed to _gst_make_method for a binary selector, or representing a send of a binary message BINARYOP to the object identified by RECEIVER, with the given ARGUMENT. */ extern tree_node _gst_make_binary_expr (YYLTYPE *location, tree_node receiver, const char *binaryOp, tree_node argument) ATTRIBUTE_HIDDEN; /* Create an expr_node to be passed to _gst_make_method for a keyword selector, or representing a send of a keyword message identified by KEYWORDMESSAGE to the object identified by RECEIVER. The selector is split across the different list_nodes making up KEYWORDMESSAGE and joined at compilation time. */ extern tree_node _gst_make_keyword_expr (YYLTYPE *location, tree_node receiver, tree_node keywordMessage) ATTRIBUTE_HIDDEN; /* Create a list_node that represents a variable called NAME (it does not matter if it is a global, local, or instance variable, or an argument). */ extern tree_node _gst_make_variable (YYLTYPE *location, const char *name) ATTRIBUTE_HIDDEN; /* Create a list_node that represents a part of a keyword selector, KEYWORD, together with the corresponding argument EXPRESSION. */ extern tree_node _gst_make_keyword_list (YYLTYPE *location, const char *keyword, tree_node expression) ATTRIBUTE_HIDDEN; /* Given a constant node, create an ATTRIBUTE_LIST node. */ extern tree_node _gst_make_attribute_list (YYLTYPE *location, tree_node constant) ATTRIBUTE_HIDDEN; /* Given a variable tree node, convert it to a variable list tree node with a NULL next link. */ extern tree_node _gst_make_variable_list (YYLTYPE *location, tree_node variable) ATTRIBUTE_HIDDEN; /* Given a variable tree node, convert it to an assignment list tree node with a NULL next link. */ extern tree_node _gst_make_assignment_list (YYLTYPE *location, tree_node variable) ATTRIBUTE_HIDDEN; /* Create an expr_node of type TREE_ASSIGN_EXPR. */ extern tree_node _gst_make_assign (YYLTYPE *location, tree_node variables, tree_node expression) ATTRIBUTE_HIDDEN; /* Create an expr_node of type TREE_RETURN_EXPR where the returned EXPRESSION is stored in the RECEIVER field of the node. */ extern tree_node _gst_make_return (YYLTYPE *location, tree_node expression) ATTRIBUTE_HIDDEN; /* Create a const_node storing an intptr_t, IVAL. */ extern tree_node _gst_make_int_constant (YYLTYPE *location, intptr_t ival) ATTRIBUTE_HIDDEN; /* Create a const_node storing a double, FVAL. The type (FloatD, FloatE, FloatQ) is given by TYPE. */ extern tree_node _gst_make_float_constant (YYLTYPE *location, long double fval, int type) ATTRIBUTE_HIDDEN; /* Create a const_node storing a char, IVAL. */ extern tree_node _gst_make_char_constant (YYLTYPE *location, int ival) ATTRIBUTE_HIDDEN; /* Create a const_node storing a symbol, pointed to by the SYMBOLNODE's NAME member. The symbol is interned and the const_node is created with its OOP. */ extern tree_node _gst_make_symbol_constant (YYLTYPE *location, tree_node symbolNode) ATTRIBUTE_HIDDEN; /* Create a const_node storing a string, pointed to by SVAL. */ extern tree_node _gst_make_string_constant (YYLTYPE *location, const char *sval) ATTRIBUTE_HIDDEN; /* Create a const_node storing a deferred variable binding, whose key is the variable VARNODE. */ extern tree_node _gst_make_deferred_binding_constant (YYLTYPE *location, tree_node varNode) ATTRIBUTE_HIDDEN; /* Create a const_node for an array whose elements are described by the nodes in the list, AVAL. */ extern tree_node _gst_make_array_constant (YYLTYPE *location, tree_node aval) ATTRIBUTE_HIDDEN; /* Create a const_node for the byte_object BOVAL (a LargeInteger). */ extern tree_node _gst_make_byte_object_constant (YYLTYPE *location, byte_object boval) ATTRIBUTE_HIDDEN; /* Create a const_node for a ByteArray object, creating a byteObjectConst out of the single elements which are stored in AVAL as a list_node. That is, this method converts from CONST_ARRAY format to byteObjectConst format and answer the resulting const_node. */ extern tree_node _gst_make_byte_array_constant (YYLTYPE *location, tree_node aval) ATTRIBUTE_HIDDEN; /* Create a const_node for an object, OVAL, which is typically a Class or ScaledDecimal. */ extern tree_node _gst_make_oop_constant (YYLTYPE *location, OOP oval) ATTRIBUTE_HIDDEN; /* Create an TREE_ARRAY_CONSTRUCTOR node, that is a const_node whose aVal does not contain other constants, but rather statements to be evaluated at run-time and whose results are to put each in an element of the array. */ extern tree_node _gst_make_array_constructor (YYLTYPE *location, tree_node statements) ATTRIBUTE_HIDDEN; /* Resolve the variable binding to an association and create a const_node of CONST_OOP type. */ extern tree_node _gst_make_binding_constant (YYLTYPE *location, tree_node variables) ATTRIBUTE_HIDDEN; /* Create a TREE_SYMBOL_NODE describing an identifier (variable, unary/binary selector or symbol constant, it doesn't patter) pointed to by IDENT. */ extern tree_node _gst_intern_ident (YYLTYPE *location, const char *ident) ATTRIBUTE_HIDDEN; /* Create an element of an array constant, which is a list type object. Return the element with the next field NILed out and pointing to the first element, ELT. */ extern tree_node _gst_make_array_elt (YYLTYPE *location, tree_node elt) ATTRIBUTE_HIDDEN; /* Creates a block tree node with the given ARGUMENTS, TEMPORARIES and STATEMENTS. */ extern tree_node _gst_make_block (YYLTYPE *location, tree_node arguments, tree_node temporaries, tree_node statements) ATTRIBUTE_HIDDEN; /* Creates a node for holding a list of cascaded messages (basically an expr_node that isn't using its symbol. MESSAGEEXPR is the expression invoke first as it computes the receiver. Then the remaining CASCADEDMESSAGES are sent to that same receiver. */ extern tree_node _gst_make_cascaded_message (YYLTYPE *location, tree_node messageExpr, tree_node cascadedMessages) ATTRIBUTE_HIDDEN; /* Create a node of type TREE_STATEMENT_LIST, where the first node is EXPRESSION. */ extern tree_node _gst_make_statement_list (YYLTYPE *location, tree_node expression) ATTRIBUTE_HIDDEN; /* Create a TREE_MESSAGE_LIST which is used as the second parameter to _gst_make_cascaded_message -- that is, it represents the sends after the first. */ extern tree_node _gst_make_message_list (YYLTYPE *location, tree_node messageElt) ATTRIBUTE_HIDDEN; /* Adds node N2 onto a list of nodes headed by N1. N1 contains the address of the last NEXT field in the chain, so storing N2 into there indirectly and then making that NEXT field point to N2's NEXT field works properly. */ extern tree_node _gst_add_node (tree_node n1, tree_node n2) ATTRIBUTE_HIDDEN; /* Free the objects on the compilation obstack. */ extern void _gst_free_tree () ATTRIBUTE_HIDDEN; /* Print the NODE with LEVEL spaces of indentation. */ extern void _gst_print_tree (tree_node node, int level) ATTRIBUTE_HIDDEN; #endif /* GST_TREE_H */ smalltalk-3.2.5/libgst/match.h0000644000175000017500000045007612130455567013203 00000000000000#ifndef GST_MATCH_H #define GST_MATCH_H #define MATCH_BYTECODES(name_, bp_, code_) BEGIN_MACRO { \ int arg, arg_lsb, n, num_args, ofs, opcode, opcode_, scopes, super; \ unsigned char *IP = bp_; \ unsigned char ATTRIBUTE_UNUSED *IP0 = bp_; \ arg = arg_lsb = n = num_args = ofs = opcode = opcode_ = scopes = super = 0; \ MATCH_BYTECODES_START_##name_: \ opcode_ = *IP; \ MATCH_BYTECODES_SWITCH_##name_: \ switch (opcode_) { \ case 0: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 256; \ n = 0; \ goto MATCH_BYTECODES_##name_##_SEND_ARITH; \ case 256: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 1: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 257; \ n = 1; \ goto MATCH_BYTECODES_##name_##_SEND_ARITH; \ case 257: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 2: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 258; \ n = 2; \ goto MATCH_BYTECODES_##name_##_SEND_ARITH; \ case 258: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 3: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 259; \ n = 3; \ goto MATCH_BYTECODES_##name_##_SEND_ARITH; \ case 259: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 4: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 260; \ n = 4; \ goto MATCH_BYTECODES_##name_##_SEND_ARITH; \ case 260: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 5: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 261; \ n = 5; \ goto MATCH_BYTECODES_##name_##_SEND_ARITH; \ case 261: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 6: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 262; \ n = 6; \ goto MATCH_BYTECODES_##name_##_SEND_ARITH; \ case 262: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 7: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 263; \ n = 7; \ goto MATCH_BYTECODES_##name_##_SEND_ARITH; \ case 263: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 8: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 264; \ n = 8; \ goto MATCH_BYTECODES_##name_##_SEND_ARITH; \ case 264: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 9: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 265; \ n = 9; \ goto MATCH_BYTECODES_##name_##_SEND_ARITH; \ case 265: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 10: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 266; \ n = 10; \ goto MATCH_BYTECODES_##name_##_SEND_ARITH; \ case 266: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 11: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 267; \ n = 11; \ goto MATCH_BYTECODES_##name_##_SEND_ARITH; \ case 267: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 12: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 268; \ n = 12; \ goto MATCH_BYTECODES_##name_##_SEND_ARITH; \ case 268: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 13: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 269; \ n = 13; \ goto MATCH_BYTECODES_##name_##_SEND_ARITH; \ case 269: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 14: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 270; \ n = 14; \ goto MATCH_BYTECODES_##name_##_SEND_ARITH; \ case 270: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 15: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 271; \ n = 15; \ goto MATCH_BYTECODES_##name_##_SEND_ARITH; \ case 271: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 16: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 272; \ n = 0; \ goto MATCH_BYTECODES_##name_##_SEND_SPECIAL; \ case 272: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 17: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 273; \ n = 1; \ goto MATCH_BYTECODES_##name_##_SEND_SPECIAL; \ case 273: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 18: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 274; \ n = 2; \ goto MATCH_BYTECODES_##name_##_SEND_SPECIAL; \ case 274: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 19: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 275; \ n = 3; \ goto MATCH_BYTECODES_##name_##_SEND_SPECIAL; \ case 275: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 20: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 276; \ n = 4; \ goto MATCH_BYTECODES_##name_##_SEND_SPECIAL; \ case 276: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 21: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 277; \ n = 5; \ goto MATCH_BYTECODES_##name_##_SEND_SPECIAL; \ case 277: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 22: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 278; \ n = 6; \ goto MATCH_BYTECODES_##name_##_SEND_SPECIAL; \ case 278: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 23: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 279; \ n = 7; \ goto MATCH_BYTECODES_##name_##_SEND_SPECIAL; \ case 279: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 24: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 280; \ n = 8; \ goto MATCH_BYTECODES_##name_##_SEND_SPECIAL; \ case 280: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 25: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 281; \ n = 9; \ goto MATCH_BYTECODES_##name_##_SEND_SPECIAL; \ case 281: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 26: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 282; \ n = 10; \ goto MATCH_BYTECODES_##name_##_SEND_SPECIAL; \ case 282: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 27: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 283; \ opcode = 27; \ arg = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_INVALID; \ case 283: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 28: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 284; \ n = arg >> 8; \ super = 0; \ num_args = arg_lsb; \ goto MATCH_BYTECODES_##name_##_SEND; \ case 284: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 29: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 285; \ n = arg >> 8; \ super = 1; \ num_args = arg_lsb; \ goto MATCH_BYTECODES_##name_##_SEND; \ case 285: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 30: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 286; \ n = arg | arg_lsb; \ super = 0; \ goto MATCH_BYTECODES_##name_##_SEND_IMMEDIATE; \ case 286: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 31: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 287; \ n = arg | arg_lsb; \ super = 1; \ goto MATCH_BYTECODES_##name_##_SEND_IMMEDIATE; \ case 287: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 32: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 288; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_PUSH_TEMPORARY_VARIABLE; \ case 288: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 33: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 289; \ n = arg >> 8; \ scopes = arg_lsb; \ goto MATCH_BYTECODES_##name_##_PUSH_OUTER_TEMP; \ case 289: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 34: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 290; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_PUSH_LIT_VARIABLE; \ case 290: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 35: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 291; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_PUSH_RECEIVER_VARIABLE; \ case 291: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 36: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 292; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_STORE_TEMPORARY_VARIABLE; \ case 292: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 37: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 293; \ n = arg >> 8; \ scopes = arg_lsb; \ goto MATCH_BYTECODES_##name_##_STORE_OUTER_TEMP; \ case 293: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 38: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 294; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_STORE_LIT_VARIABLE; \ case 294: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 39: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 295; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_STORE_RECEIVER_VARIABLE; \ case 295: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 40: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 296; \ ofs = IP - IP0 - (arg | arg_lsb); \ goto MATCH_BYTECODES_##name_##_JUMP; \ case 296: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 41: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 297; \ ofs = IP - IP0 + (arg | arg_lsb); \ goto MATCH_BYTECODES_##name_##_JUMP; \ case 297: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 42: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 298; \ ofs = IP - IP0 + (arg | arg_lsb); \ goto MATCH_BYTECODES_##name_##_POP_JUMP_TRUE; \ case 298: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 43: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 299; \ ofs = IP - IP0 + (arg | arg_lsb); \ goto MATCH_BYTECODES_##name_##_POP_JUMP_FALSE; \ case 299: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 44: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 300; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_PUSH_INTEGER; \ case 300: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 45: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 301; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_PUSH_SPECIAL; \ case 301: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 46: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 302; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_PUSH_LIT_CONSTANT; \ case 302: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 47: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 303; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_POP_INTO_NEW_STACKTOP; \ case 303: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 48: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 304; \ goto MATCH_BYTECODES_##name_##_POP_STACK_TOP; \ case 304: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 49: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 305; \ goto MATCH_BYTECODES_##name_##_MAKE_DIRTY_BLOCK; \ case 305: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 50: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 306; \ goto MATCH_BYTECODES_##name_##_RETURN_METHOD_STACK_TOP; \ case 306: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 51: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 307; \ goto MATCH_BYTECODES_##name_##_RETURN_CONTEXT_STACK_TOP; \ case 307: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 52: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 308; \ goto MATCH_BYTECODES_##name_##_DUP_STACK_TOP; \ case 308: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 53: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 309; \ goto MATCH_BYTECODES_##name_##_EXIT_INTERPRETER; \ case 309: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 54: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 310; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_LINE_NUMBER_BYTECODE; \ case 310: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 55: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ arg=(arg | arg_lsb)<< 8; \ goto MATCH_BYTECODES_START_##name_; \ goto MATCH_BYTECODES_END_##name_; \ case 56: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 311; \ goto MATCH_BYTECODES_##name_##_PUSH_SELF; \ case 311: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 57: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 312; \ opcode = 57; \ arg = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_INVALID; \ case 312: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 58: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 313; \ opcode = 58; \ arg = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_INVALID; \ case 313: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 59: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 314; \ opcode = 59; \ arg = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_INVALID; \ case 314: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 60: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 315; \ opcode = 60; \ arg = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_INVALID; \ case 315: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 61: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 316; \ opcode = 61; \ arg = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_INVALID; \ case 316: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 62: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 317; \ opcode = 62; \ arg = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_INVALID; \ case 317: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 63: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 318; \ opcode = 63; \ arg = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_INVALID; \ case 318: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 64: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 319; \ n = arg | arg_lsb; \ super = 0; \ num_args = 1; \ goto MATCH_BYTECODES_##name_##_SEND; \ case 319: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 65: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 320; \ n = arg | arg_lsb; \ super = 0; \ num_args = 0; \ goto MATCH_BYTECODES_##name_##_SEND; \ case 320: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 66: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 321; \ goto MATCH_BYTECODES_##name_##_PUSH_SELF; \ case 321: \ ; \ } while (0); \ do { \ opcode_ = 322; \ goto MATCH_BYTECODES_##name_##_RETURN_CONTEXT_STACK_TOP; \ case 322: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 67: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 323; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_LINE_NUMBER_BYTECODE; \ case 323: \ ; \ } while (0); \ do { \ opcode_ = 324; \ goto MATCH_BYTECODES_##name_##_PUSH_SELF; \ case 324: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 68: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 325; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_LINE_NUMBER_BYTECODE; \ case 325: \ ; \ } while (0); \ do { \ opcode_ = 326; \ goto MATCH_BYTECODES_##name_##_POP_STACK_TOP; \ case 326: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 69: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 327; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_LINE_NUMBER_BYTECODE; \ case 327: \ ; \ } while (0); \ do { \ opcode_ = 328; \ n = 0; \ goto MATCH_BYTECODES_##name_##_PUSH_TEMPORARY_VARIABLE; \ case 328: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 70: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 329; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_PUSH_LIT_CONSTANT; \ case 329: \ ; \ } while (0); \ do { \ opcode_ = 330; \ goto MATCH_BYTECODES_##name_##_MAKE_DIRTY_BLOCK; \ case 330: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 71: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 331; \ n = arg | arg_lsb; \ super = 0; \ num_args = 2; \ goto MATCH_BYTECODES_##name_##_SEND; \ case 331: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 72: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 332; \ goto MATCH_BYTECODES_##name_##_POP_STACK_TOP; \ case 332: \ ; \ } while (0); \ do { \ opcode_ = 333; \ goto MATCH_BYTECODES_##name_##_DUP_STACK_TOP; \ case 333: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 73: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 334; \ n = 0; \ goto MATCH_BYTECODES_##name_##_PUSH_TEMPORARY_VARIABLE; \ case 334: \ ; \ } while (0); \ do { \ opcode_ = 335; \ n = arg | arg_lsb; \ super = 0; \ goto MATCH_BYTECODES_##name_##_SEND_IMMEDIATE; \ case 335: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 74: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 336; \ goto MATCH_BYTECODES_##name_##_PUSH_SELF; \ case 336: \ ; \ } while (0); \ do { \ opcode_ = 337; \ n = arg | arg_lsb; \ super = 0; \ num_args = 0; \ goto MATCH_BYTECODES_##name_##_SEND; \ case 337: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 75: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 338; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_PUSH_SPECIAL; \ case 338: \ ; \ } while (0); \ do { \ opcode_ = 339; \ goto MATCH_BYTECODES_##name_##_RETURN_CONTEXT_STACK_TOP; \ case 339: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 76: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 340; \ goto MATCH_BYTECODES_##name_##_PUSH_SELF; \ case 340: \ ; \ } while (0); \ do { \ opcode_ = 341; \ n = arg | arg_lsb; \ super = 0; \ goto MATCH_BYTECODES_##name_##_SEND_IMMEDIATE; \ case 341: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 77: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 342; \ n = arg | arg_lsb; \ scopes = 1; \ goto MATCH_BYTECODES_##name_##_PUSH_OUTER_TEMP; \ case 342: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 78: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 343; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_STORE_TEMPORARY_VARIABLE; \ case 343: \ ; \ } while (0); \ do { \ opcode_ = 344; \ goto MATCH_BYTECODES_##name_##_POP_STACK_TOP; \ case 344: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 79: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 345; \ goto MATCH_BYTECODES_##name_##_PUSH_SELF; \ case 345: \ ; \ } while (0); \ do { \ opcode_ = 346; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_PUSH_TEMPORARY_VARIABLE; \ case 346: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 80: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 347; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_STORE_RECEIVER_VARIABLE; \ case 347: \ ; \ } while (0); \ do { \ opcode_ = 348; \ goto MATCH_BYTECODES_##name_##_PUSH_SELF; \ case 348: \ ; \ } while (0); \ do { \ opcode_ = 349; \ goto MATCH_BYTECODES_##name_##_RETURN_CONTEXT_STACK_TOP; \ case 349: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 81: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 350; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_PUSH_INTEGER; \ case 350: \ ; \ } while (0); \ do { \ opcode_ = 351; \ n = 0; \ goto MATCH_BYTECODES_##name_##_SEND_ARITH; \ case 351: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 82: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 352; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_LINE_NUMBER_BYTECODE; \ case 352: \ ; \ } while (0); \ do { \ opcode_ = 353; \ n = 0; \ goto MATCH_BYTECODES_##name_##_PUSH_LIT_VARIABLE; \ case 353: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 83: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 354; \ n = 0; \ goto MATCH_BYTECODES_##name_##_PUSH_TEMPORARY_VARIABLE; \ case 354: \ ; \ } while (0); \ do { \ opcode_ = 355; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_PUSH_TEMPORARY_VARIABLE; \ case 355: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 84: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 356; \ n = 0; \ goto MATCH_BYTECODES_##name_##_PUSH_TEMPORARY_VARIABLE; \ case 356: \ ; \ } while (0); \ do { \ opcode_ = 357; \ n = arg >> 8; \ super = 0; \ num_args = arg_lsb; \ goto MATCH_BYTECODES_##name_##_SEND; \ case 357: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 85: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 358; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_LINE_NUMBER_BYTECODE; \ case 358: \ ; \ } while (0); \ do { \ opcode_ = 359; \ n = 1; \ goto MATCH_BYTECODES_##name_##_PUSH_TEMPORARY_VARIABLE; \ case 359: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 86: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 360; \ n = 4; \ goto MATCH_BYTECODES_##name_##_SEND_SPECIAL; \ case 360: \ ; \ } while (0); \ do { \ opcode_ = 361; \ ofs = IP - IP0 + (arg | arg_lsb); \ goto MATCH_BYTECODES_##name_##_POP_JUMP_FALSE; \ case 361: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 87: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 362; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_PUSH_INTEGER; \ case 362: \ ; \ } while (0); \ do { \ opcode_ = 363; \ n = 6; \ goto MATCH_BYTECODES_##name_##_SEND_ARITH; \ case 363: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 88: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 364; \ n = arg | arg_lsb; \ super = 0; \ num_args = 3; \ goto MATCH_BYTECODES_##name_##_SEND; \ case 364: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 89: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 365; \ n = 0; \ goto MATCH_BYTECODES_##name_##_PUSH_TEMPORARY_VARIABLE; \ case 365: \ ; \ } while (0); \ do { \ opcode_ = 366; \ n = arg | arg_lsb; \ super = 0; \ num_args = 1; \ goto MATCH_BYTECODES_##name_##_SEND; \ case 366: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 90: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 367; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_LINE_NUMBER_BYTECODE; \ case 367: \ ; \ } while (0); \ do { \ opcode_ = 368; \ goto MATCH_BYTECODES_##name_##_PUSH_SELF; \ case 368: \ ; \ } while (0); \ do { \ opcode_ = 369; \ n = 0; \ super = 0; \ num_args = 0; \ goto MATCH_BYTECODES_##name_##_SEND; \ case 369: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 91: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 370; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_PUSH_TEMPORARY_VARIABLE; \ case 370: \ ; \ } while (0); \ do { \ opcode_ = 371; \ goto MATCH_BYTECODES_##name_##_RETURN_CONTEXT_STACK_TOP; \ case 371: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 92: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 372; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_PUSH_LIT_CONSTANT; \ case 372: \ ; \ } while (0); \ do { \ opcode_ = 373; \ n = 36; \ super = 0; \ goto MATCH_BYTECODES_##name_##_SEND_IMMEDIATE; \ case 373: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 93: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 374; \ n = 8; \ goto MATCH_BYTECODES_##name_##_SEND_SPECIAL; \ case 374: \ ; \ } while (0); \ do { \ opcode_ = 375; \ ofs = IP - IP0 + (arg | arg_lsb); \ goto MATCH_BYTECODES_##name_##_POP_JUMP_FALSE; \ case 375: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 94: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 376; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_PUSH_LIT_CONSTANT; \ case 376: \ ; \ } while (0); \ do { \ opcode_ = 377; \ n = 1; \ super = 0; \ num_args = 1; \ goto MATCH_BYTECODES_##name_##_SEND; \ case 377: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 95: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 378; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_LINE_NUMBER_BYTECODE; \ case 378: \ ; \ } while (0); \ do { \ opcode_ = 379; \ goto MATCH_BYTECODES_##name_##_POP_STACK_TOP; \ case 379: \ ; \ } while (0); \ do { \ opcode_ = 380; \ goto MATCH_BYTECODES_##name_##_PUSH_SELF; \ case 380: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 96: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 381; \ goto MATCH_BYTECODES_##name_##_POP_STACK_TOP; \ case 381: \ ; \ } while (0); \ do { \ opcode_ = 382; \ goto MATCH_BYTECODES_##name_##_DUP_STACK_TOP; \ case 382: \ ; \ } while (0); \ do { \ opcode_ = 383; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_LINE_NUMBER_BYTECODE; \ case 383: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 97: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 384; \ n = 0; \ goto MATCH_BYTECODES_##name_##_PUSH_TEMPORARY_VARIABLE; \ case 384: \ ; \ } while (0); \ do { \ opcode_ = 385; \ n = arg | arg_lsb; \ super = 0; \ num_args = 0; \ goto MATCH_BYTECODES_##name_##_SEND; \ case 385: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 98: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 386; \ n = 1; \ goto MATCH_BYTECODES_##name_##_PUSH_TEMPORARY_VARIABLE; \ case 386: \ ; \ } while (0); \ do { \ opcode_ = 387; \ n = arg | arg_lsb; \ super = 0; \ goto MATCH_BYTECODES_##name_##_SEND_IMMEDIATE; \ case 387: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 99: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 388; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_PUSH_LIT_CONSTANT; \ case 388: \ ; \ } while (0); \ do { \ opcode_ = 389; \ n = 6; \ goto MATCH_BYTECODES_##name_##_SEND_ARITH; \ case 389: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 100: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 390; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_PUSH_INTEGER; \ case 390: \ ; \ } while (0); \ do { \ opcode_ = 391; \ n = 1; \ goto MATCH_BYTECODES_##name_##_SEND_ARITH; \ case 391: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 101: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 392; \ goto MATCH_BYTECODES_##name_##_DUP_STACK_TOP; \ case 392: \ ; \ } while (0); \ do { \ opcode_ = 393; \ ofs = IP - IP0 + (arg | arg_lsb); \ goto MATCH_BYTECODES_##name_##_POP_JUMP_FALSE; \ case 393: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 102: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 394; \ goto MATCH_BYTECODES_##name_##_POP_STACK_TOP; \ case 394: \ ; \ } while (0); \ do { \ opcode_ = 395; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_LINE_NUMBER_BYTECODE; \ case 395: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 103: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 396; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_PUSH_INTEGER; \ case 396: \ ; \ } while (0); \ do { \ opcode_ = 397; \ n = 32; \ super = 0; \ goto MATCH_BYTECODES_##name_##_SEND_IMMEDIATE; \ case 397: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 104: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 398; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_PUSH_TEMPORARY_VARIABLE; \ case 398: \ ; \ } while (0); \ do { \ opcode_ = 399; \ n = 2; \ goto MATCH_BYTECODES_##name_##_SEND_SPECIAL; \ case 399: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 105: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 400; \ goto MATCH_BYTECODES_##name_##_PUSH_SELF; \ case 400: \ ; \ } while (0); \ do { \ opcode_ = 401; \ n = arg >> 8; \ super = 0; \ num_args = arg_lsb; \ goto MATCH_BYTECODES_##name_##_SEND; \ case 401: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 106: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 402; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_LINE_NUMBER_BYTECODE; \ case 402: \ ; \ } while (0); \ do { \ opcode_ = 403; \ n = 2; \ goto MATCH_BYTECODES_##name_##_PUSH_TEMPORARY_VARIABLE; \ case 403: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 107: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 404; \ goto MATCH_BYTECODES_##name_##_POP_STACK_TOP; \ case 404: \ ; \ } while (0); \ do { \ opcode_ = 405; \ n = arg | arg_lsb; \ super = 0; \ goto MATCH_BYTECODES_##name_##_SEND_IMMEDIATE; \ case 405: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 108: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 406; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_PUSH_TEMPORARY_VARIABLE; \ case 406: \ ; \ } while (0); \ do { \ opcode_ = 407; \ n = 1; \ goto MATCH_BYTECODES_##name_##_PUSH_INTEGER; \ case 407: \ ; \ } while (0); \ do { \ opcode_ = 408; \ n = 0; \ goto MATCH_BYTECODES_##name_##_SEND_ARITH; \ case 408: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 109: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 409; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_LINE_NUMBER_BYTECODE; \ case 409: \ ; \ } while (0); \ do { \ opcode_ = 410; \ n = 0; \ goto MATCH_BYTECODES_##name_##_PUSH_RECEIVER_VARIABLE; \ case 410: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 110: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 411; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_PUSH_LIT_CONSTANT; \ case 411: \ ; \ } while (0); \ do { \ opcode_ = 412; \ n = 38; \ super = 0; \ goto MATCH_BYTECODES_##name_##_SEND_IMMEDIATE; \ case 412: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 111: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 413; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_PUSH_INTEGER; \ case 413: \ ; \ } while (0); \ do { \ opcode_ = 414; \ n = 0; \ goto MATCH_BYTECODES_##name_##_SEND_SPECIAL; \ case 414: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 112: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 415; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_LINE_NUMBER_BYTECODE; \ case 415: \ ; \ } while (0); \ do { \ opcode_ = 416; \ n = 1; \ goto MATCH_BYTECODES_##name_##_PUSH_RECEIVER_VARIABLE; \ case 416: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 113: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 417; \ n = 0; \ goto MATCH_BYTECODES_##name_##_PUSH_TEMPORARY_VARIABLE; \ case 417: \ ; \ } while (0); \ do { \ opcode_ = 418; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_PUSH_LIT_CONSTANT; \ case 418: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 114: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 419; \ goto MATCH_BYTECODES_##name_##_DUP_STACK_TOP; \ case 419: \ ; \ } while (0); \ do { \ opcode_ = 420; \ ofs = IP - IP0 + (arg | arg_lsb); \ goto MATCH_BYTECODES_##name_##_POP_JUMP_TRUE; \ case 420: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 115: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 421; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_PUSH_TEMPORARY_VARIABLE; \ case 421: \ ; \ } while (0); \ do { \ opcode_ = 422; \ n = 0; \ goto MATCH_BYTECODES_##name_##_SEND_SPECIAL; \ case 422: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 116: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 423; \ n = 2; \ goto MATCH_BYTECODES_##name_##_PUSH_TEMPORARY_VARIABLE; \ case 423: \ ; \ } while (0); \ do { \ opcode_ = 424; \ n = arg | arg_lsb; \ super = 0; \ goto MATCH_BYTECODES_##name_##_SEND_IMMEDIATE; \ case 424: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 117: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 425; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_PUSH_LIT_CONSTANT; \ case 425: \ ; \ } while (0); \ do { \ opcode_ = 426; \ n = 49; \ super = 0; \ goto MATCH_BYTECODES_##name_##_SEND_IMMEDIATE; \ case 426: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 118: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 427; \ n = 1; \ goto MATCH_BYTECODES_##name_##_STORE_TEMPORARY_VARIABLE; \ case 427: \ ; \ } while (0); \ do { \ opcode_ = 428; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_LINE_NUMBER_BYTECODE; \ case 428: \ ; \ } while (0); \ do { \ opcode_ = 429; \ goto MATCH_BYTECODES_##name_##_POP_STACK_TOP; \ case 429: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 119: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 430; \ n = 1; \ goto MATCH_BYTECODES_##name_##_PUSH_TEMPORARY_VARIABLE; \ case 430: \ ; \ } while (0); \ do { \ opcode_ = 431; \ n = arg | arg_lsb; \ super = 0; \ num_args = 1; \ goto MATCH_BYTECODES_##name_##_SEND; \ case 431: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 120: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 432; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_STORE_RECEIVER_VARIABLE; \ case 432: \ ; \ } while (0); \ do { \ opcode_ = 433; \ goto MATCH_BYTECODES_##name_##_POP_STACK_TOP; \ case 433: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 121: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 434; \ n = arg | arg_lsb; \ scopes = 1; \ goto MATCH_BYTECODES_##name_##_STORE_OUTER_TEMP; \ case 434: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 122: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 435; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_PUSH_INTEGER; \ case 435: \ ; \ } while (0); \ do { \ opcode_ = 436; \ n = 96; \ super = 0; \ goto MATCH_BYTECODES_##name_##_SEND_IMMEDIATE; \ case 436: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 123: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 437; \ goto MATCH_BYTECODES_##name_##_POP_STACK_TOP; \ case 437: \ ; \ } while (0); \ do { \ opcode_ = 438; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_PUSH_TEMPORARY_VARIABLE; \ case 438: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 124: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 439; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_PUSH_RECEIVER_VARIABLE; \ case 439: \ ; \ } while (0); \ do { \ opcode_ = 440; \ goto MATCH_BYTECODES_##name_##_RETURN_CONTEXT_STACK_TOP; \ case 440: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 125: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 441; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_LINE_NUMBER_BYTECODE; \ case 441: \ ; \ } while (0); \ do { \ opcode_ = 442; \ goto MATCH_BYTECODES_##name_##_POP_STACK_TOP; \ case 442: \ ; \ } while (0); \ do { \ opcode_ = 443; \ n = 1; \ goto MATCH_BYTECODES_##name_##_PUSH_TEMPORARY_VARIABLE; \ case 443: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 126: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 444; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_LINE_NUMBER_BYTECODE; \ case 444: \ ; \ } while (0); \ do { \ opcode_ = 445; \ goto MATCH_BYTECODES_##name_##_POP_STACK_TOP; \ case 445: \ ; \ } while (0); \ do { \ opcode_ = 446; \ n = 0; \ goto MATCH_BYTECODES_##name_##_PUSH_TEMPORARY_VARIABLE; \ case 446: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 127: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 447; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_LINE_NUMBER_BYTECODE; \ case 447: \ ; \ } while (0); \ do { \ opcode_ = 448; \ goto MATCH_BYTECODES_##name_##_PUSH_SELF; \ case 448: \ ; \ } while (0); \ do { \ opcode_ = 449; \ n = 0; \ goto MATCH_BYTECODES_##name_##_PUSH_LIT_CONSTANT; \ case 449: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 128: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 450; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_PUSH_LIT_CONSTANT; \ case 450: \ ; \ } while (0); \ do { \ opcode_ = 451; \ goto MATCH_BYTECODES_##name_##_RETURN_CONTEXT_STACK_TOP; \ case 451: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 129: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 452; \ goto MATCH_BYTECODES_##name_##_PUSH_SELF; \ case 452: \ ; \ } while (0); \ do { \ opcode_ = 453; \ n = 2; \ goto MATCH_BYTECODES_##name_##_SEND_SPECIAL; \ case 453: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 130: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 454; \ n = 4; \ goto MATCH_BYTECODES_##name_##_SEND_SPECIAL; \ case 454: \ ; \ } while (0); \ do { \ opcode_ = 455; \ ofs = IP - IP0 + (arg | arg_lsb); \ goto MATCH_BYTECODES_##name_##_POP_JUMP_TRUE; \ case 455: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 131: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 456; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_PUSH_TEMPORARY_VARIABLE; \ case 456: \ ; \ } while (0); \ do { \ opcode_ = 457; \ n = 1; \ goto MATCH_BYTECODES_##name_##_SEND_SPECIAL; \ case 457: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 132: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 458; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_LINE_NUMBER_BYTECODE; \ case 458: \ ; \ } while (0); \ do { \ opcode_ = 459; \ n = 1; \ goto MATCH_BYTECODES_##name_##_PUSH_LIT_VARIABLE; \ case 459: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 133: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 460; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_PUSH_TEMPORARY_VARIABLE; \ case 460: \ ; \ } while (0); \ do { \ opcode_ = 461; \ n = 0; \ goto MATCH_BYTECODES_##name_##_SEND_ARITH; \ case 461: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 134: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 462; \ goto MATCH_BYTECODES_##name_##_POP_STACK_TOP; \ case 462: \ ; \ } while (0); \ do { \ opcode_ = 463; \ ofs = IP - IP0 - (arg | arg_lsb); \ goto MATCH_BYTECODES_##name_##_JUMP; \ case 463: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 135: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 464; \ goto MATCH_BYTECODES_##name_##_POP_STACK_TOP; \ case 464: \ ; \ } while (0); \ do { \ opcode_ = 465; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_PUSH_LIT_VARIABLE; \ case 465: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 136: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 466; \ n = 1; \ goto MATCH_BYTECODES_##name_##_PUSH_INTEGER; \ case 466: \ ; \ } while (0); \ do { \ opcode_ = 467; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_STORE_TEMPORARY_VARIABLE; \ case 467: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 137: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 468; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_PUSH_LIT_CONSTANT; \ case 468: \ ; \ } while (0); \ do { \ opcode_ = 469; \ n = 2; \ super = 0; \ num_args = 1; \ goto MATCH_BYTECODES_##name_##_SEND; \ case 469: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 138: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 470; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_LINE_NUMBER_BYTECODE; \ case 470: \ ; \ } while (0); \ do { \ opcode_ = 471; \ n = 3; \ goto MATCH_BYTECODES_##name_##_PUSH_TEMPORARY_VARIABLE; \ case 471: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 139: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 472; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_LINE_NUMBER_BYTECODE; \ case 472: \ ; \ } while (0); \ do { \ opcode_ = 473; \ n = 0; \ scopes = 1; \ goto MATCH_BYTECODES_##name_##_PUSH_OUTER_TEMP; \ case 473: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 140: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 474; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_PUSH_RECEIVER_VARIABLE; \ case 474: \ ; \ } while (0); \ do { \ opcode_ = 475; \ n = 0; \ super = 0; \ num_args = 0; \ goto MATCH_BYTECODES_##name_##_SEND; \ case 475: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 141: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 476; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_PUSH_INTEGER; \ case 476: \ ; \ } while (0); \ do { \ opcode_ = 477; \ n = 3; \ goto MATCH_BYTECODES_##name_##_SEND_ARITH; \ case 477: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 142: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 478; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_PUSH_TEMPORARY_VARIABLE; \ case 478: \ ; \ } while (0); \ do { \ opcode_ = 479; \ n = 6; \ goto MATCH_BYTECODES_##name_##_SEND_SPECIAL; \ case 479: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 143: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 480; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_PUSH_TEMPORARY_VARIABLE; \ case 480: \ ; \ } while (0); \ do { \ opcode_ = 481; \ n = 1; \ goto MATCH_BYTECODES_##name_##_SEND_ARITH; \ case 481: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 144: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 482; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_PUSH_LIT_CONSTANT; \ case 482: \ ; \ } while (0); \ do { \ opcode_ = 483; \ n = 3; \ super = 0; \ num_args = 1; \ goto MATCH_BYTECODES_##name_##_SEND; \ case 483: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 145: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 484; \ n = 0; \ goto MATCH_BYTECODES_##name_##_PUSH_SPECIAL; \ case 484: \ ; \ } while (0); \ do { \ opcode_ = 485; \ n = 8; \ goto MATCH_BYTECODES_##name_##_SEND_SPECIAL; \ case 485: \ ; \ } while (0); \ do { \ opcode_ = 486; \ ofs = IP - IP0 + (arg | arg_lsb); \ goto MATCH_BYTECODES_##name_##_POP_JUMP_FALSE; \ case 486: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 146: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 487; \ n = 2; \ goto MATCH_BYTECODES_##name_##_STORE_TEMPORARY_VARIABLE; \ case 487: \ ; \ } while (0); \ do { \ opcode_ = 488; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_LINE_NUMBER_BYTECODE; \ case 488: \ ; \ } while (0); \ do { \ opcode_ = 489; \ goto MATCH_BYTECODES_##name_##_POP_STACK_TOP; \ case 489: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 147: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 490; \ n = 8; \ goto MATCH_BYTECODES_##name_##_SEND_SPECIAL; \ case 490: \ ; \ } while (0); \ do { \ opcode_ = 491; \ ofs = IP - IP0 + (arg | arg_lsb); \ goto MATCH_BYTECODES_##name_##_POP_JUMP_TRUE; \ case 491: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 148: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 492; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_PUSH_INTEGER; \ case 492: \ ; \ } while (0); \ do { \ opcode_ = 493; \ n = 8; \ goto MATCH_BYTECODES_##name_##_SEND_ARITH; \ case 493: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 149: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 494; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_LINE_NUMBER_BYTECODE; \ case 494: \ ; \ } while (0); \ do { \ opcode_ = 495; \ n = 2; \ goto MATCH_BYTECODES_##name_##_PUSH_RECEIVER_VARIABLE; \ case 495: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 150: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 496; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_PUSH_INTEGER; \ case 496: \ ; \ } while (0); \ do { \ opcode_ = 497; \ n = 2; \ goto MATCH_BYTECODES_##name_##_SEND_ARITH; \ case 497: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 151: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 498; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_PUSH_LIT_CONSTANT; \ case 498: \ ; \ } while (0); \ do { \ opcode_ = 499; \ n = 1; \ goto MATCH_BYTECODES_##name_##_SEND_SPECIAL; \ case 499: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 152: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 500; \ n = arg | arg_lsb; \ scopes = 2; \ goto MATCH_BYTECODES_##name_##_PUSH_OUTER_TEMP; \ case 500: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 153: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 501; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_LINE_NUMBER_BYTECODE; \ case 501: \ ; \ } while (0); \ do { \ opcode_ = 502; \ goto MATCH_BYTECODES_##name_##_PUSH_SELF; \ case 502: \ ; \ } while (0); \ do { \ opcode_ = 503; \ n = 0; \ goto MATCH_BYTECODES_##name_##_PUSH_TEMPORARY_VARIABLE; \ case 503: \ ; \ } while (0); \ do { \ opcode_ = 504; \ n = 0; \ super = 0; \ num_args = 1; \ goto MATCH_BYTECODES_##name_##_SEND; \ case 504: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 154: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 505; \ goto MATCH_BYTECODES_##name_##_PUSH_SELF; \ case 505: \ ; \ } while (0); \ do { \ opcode_ = 506; \ n = 0; \ goto MATCH_BYTECODES_##name_##_PUSH_TEMPORARY_VARIABLE; \ case 506: \ ; \ } while (0); \ do { \ opcode_ = 507; \ n = arg | arg_lsb; \ super = 0; \ num_args = 1; \ goto MATCH_BYTECODES_##name_##_SEND; \ case 507: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 155: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 508; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_LINE_NUMBER_BYTECODE; \ case 508: \ ; \ } while (0); \ do { \ opcode_ = 509; \ goto MATCH_BYTECODES_##name_##_PUSH_SELF; \ case 509: \ ; \ } while (0); \ do { \ opcode_ = 510; \ n = 40; \ super = 0; \ goto MATCH_BYTECODES_##name_##_SEND_IMMEDIATE; \ case 510: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 156: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 511; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_PUSH_TEMPORARY_VARIABLE; \ case 511: \ ; \ } while (0); \ do { \ opcode_ = 512; \ n = 3; \ goto MATCH_BYTECODES_##name_##_PUSH_TEMPORARY_VARIABLE; \ case 512: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 157: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 513; \ n = 1; \ goto MATCH_BYTECODES_##name_##_STORE_TEMPORARY_VARIABLE; \ case 513: \ ; \ } while (0); \ do { \ opcode_ = 514; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_LINE_NUMBER_BYTECODE; \ case 514: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 158: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 515; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_LINE_NUMBER_BYTECODE; \ case 515: \ ; \ } while (0); \ do { \ opcode_ = 516; \ n = 0; \ goto MATCH_BYTECODES_##name_##_PUSH_TEMPORARY_VARIABLE; \ case 516: \ ; \ } while (0); \ do { \ opcode_ = 517; \ n = 0; \ super = 0; \ num_args = 0; \ goto MATCH_BYTECODES_##name_##_SEND; \ case 517: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 159: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 518; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_PUSH_INTEGER; \ case 518: \ ; \ } while (0); \ do { \ opcode_ = 519; \ n = 14; \ goto MATCH_BYTECODES_##name_##_SEND_ARITH; \ case 519: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 160: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 520; \ n = 2; \ goto MATCH_BYTECODES_##name_##_PUSH_TEMPORARY_VARIABLE; \ case 520: \ ; \ } while (0); \ do { \ opcode_ = 521; \ n = arg | arg_lsb; \ super = 0; \ num_args = 0; \ goto MATCH_BYTECODES_##name_##_SEND; \ case 521: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 161: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 522; \ n = 0; \ goto MATCH_BYTECODES_##name_##_PUSH_TEMPORARY_VARIABLE; \ case 522: \ ; \ } while (0); \ do { \ opcode_ = 523; \ n = 1; \ goto MATCH_BYTECODES_##name_##_PUSH_TEMPORARY_VARIABLE; \ case 523: \ ; \ } while (0); \ do { \ opcode_ = 524; \ n = arg >> 8; \ super = 0; \ num_args = arg_lsb; \ goto MATCH_BYTECODES_##name_##_SEND; \ case 524: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 162: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 525; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_LINE_NUMBER_BYTECODE; \ case 525: \ ; \ } while (0); \ do { \ opcode_ = 526; \ goto MATCH_BYTECODES_##name_##_PUSH_SELF; \ case 526: \ ; \ } while (0); \ do { \ opcode_ = 527; \ n = 0; \ goto MATCH_BYTECODES_##name_##_PUSH_TEMPORARY_VARIABLE; \ case 527: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 163: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 528; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_LINE_NUMBER_BYTECODE; \ case 528: \ ; \ } while (0); \ do { \ opcode_ = 529; \ n = 3; \ goto MATCH_BYTECODES_##name_##_PUSH_RECEIVER_VARIABLE; \ case 529: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 164: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 530; \ n = 2; \ goto MATCH_BYTECODES_##name_##_PUSH_TEMPORARY_VARIABLE; \ case 530: \ ; \ } while (0); \ do { \ opcode_ = 531; \ n = arg | arg_lsb; \ super = 0; \ num_args = 1; \ goto MATCH_BYTECODES_##name_##_SEND; \ case 531: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 165: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 532; \ n = 5; \ goto MATCH_BYTECODES_##name_##_SEND_SPECIAL; \ case 532: \ ; \ } while (0); \ do { \ opcode_ = 533; \ ofs = IP - IP0 + (arg | arg_lsb); \ goto MATCH_BYTECODES_##name_##_POP_JUMP_FALSE; \ case 533: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 166: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 534; \ n = 2; \ goto MATCH_BYTECODES_##name_##_STORE_TEMPORARY_VARIABLE; \ case 534: \ ; \ } while (0); \ do { \ opcode_ = 535; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_LINE_NUMBER_BYTECODE; \ case 535: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 167: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 536; \ n = 3; \ goto MATCH_BYTECODES_##name_##_STORE_TEMPORARY_VARIABLE; \ case 536: \ ; \ } while (0); \ do { \ opcode_ = 537; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_LINE_NUMBER_BYTECODE; \ case 537: \ ; \ } while (0); \ do { \ opcode_ = 538; \ goto MATCH_BYTECODES_##name_##_POP_STACK_TOP; \ case 538: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 168: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 539; \ n = 1; \ goto MATCH_BYTECODES_##name_##_PUSH_LIT_CONSTANT; \ case 539: \ ; \ } while (0); \ do { \ opcode_ = 540; \ n = arg | arg_lsb; \ super = 0; \ goto MATCH_BYTECODES_##name_##_SEND_IMMEDIATE; \ case 540: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 169: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 541; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_PUSH_TEMPORARY_VARIABLE; \ case 541: \ ; \ } while (0); \ do { \ opcode_ = 542; \ n = 6; \ goto MATCH_BYTECODES_##name_##_SEND_ARITH; \ case 542: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 170: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 543; \ goto MATCH_BYTECODES_##name_##_POP_STACK_TOP; \ case 543: \ ; \ } while (0); \ do { \ opcode_ = 544; \ goto MATCH_BYTECODES_##name_##_DUP_STACK_TOP; \ case 544: \ ; \ } while (0); \ do { \ opcode_ = 545; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_PUSH_TEMPORARY_VARIABLE; \ case 545: \ ; \ } while (0); \ do { \ opcode_ = 546; \ n = 1; \ goto MATCH_BYTECODES_##name_##_PUSH_INTEGER; \ case 546: \ ; \ } while (0); \ do { \ opcode_ = 547; \ n = 0; \ goto MATCH_BYTECODES_##name_##_SEND_ARITH; \ case 547: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 171: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 548; \ goto MATCH_BYTECODES_##name_##_PUSH_SELF; \ case 548: \ ; \ } while (0); \ do { \ opcode_ = 549; \ n = arg | arg_lsb; \ super = 0; \ num_args = 1; \ goto MATCH_BYTECODES_##name_##_SEND; \ case 549: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 172: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 550; \ n = 0; \ goto MATCH_BYTECODES_##name_##_STORE_TEMPORARY_VARIABLE; \ case 550: \ ; \ } while (0); \ do { \ opcode_ = 551; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_LINE_NUMBER_BYTECODE; \ case 551: \ ; \ } while (0); \ do { \ opcode_ = 552; \ goto MATCH_BYTECODES_##name_##_POP_STACK_TOP; \ case 552: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 173: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 553; \ goto MATCH_BYTECODES_##name_##_DUP_STACK_TOP; \ case 553: \ ; \ } while (0); \ do { \ opcode_ = 554; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_LINE_NUMBER_BYTECODE; \ case 554: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 174: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 555; \ goto MATCH_BYTECODES_##name_##_PUSH_SELF; \ case 555: \ ; \ } while (0); \ do { \ opcode_ = 556; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_PUSH_LIT_CONSTANT; \ case 556: \ ; \ } while (0); \ do { \ opcode_ = 557; \ n = 49; \ super = 0; \ goto MATCH_BYTECODES_##name_##_SEND_IMMEDIATE; \ case 557: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 175: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 558; \ goto MATCH_BYTECODES_##name_##_POP_STACK_TOP; \ case 558: \ ; \ } while (0); \ do { \ opcode_ = 559; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_PUSH_RECEIVER_VARIABLE; \ case 559: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 176: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 560; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_LINE_NUMBER_BYTECODE; \ case 560: \ ; \ } while (0); \ do { \ opcode_ = 561; \ goto MATCH_BYTECODES_##name_##_PUSH_SELF; \ case 561: \ ; \ } while (0); \ do { \ opcode_ = 562; \ n = 84; \ super = 0; \ goto MATCH_BYTECODES_##name_##_SEND_IMMEDIATE; \ case 562: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 177: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 563; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_LINE_NUMBER_BYTECODE; \ case 563: \ ; \ } while (0); \ do { \ opcode_ = 564; \ n = 2; \ goto MATCH_BYTECODES_##name_##_PUSH_LIT_VARIABLE; \ case 564: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 178: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 565; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_PUSH_LIT_CONSTANT; \ case 565: \ ; \ } while (0); \ do { \ opcode_ = 566; \ goto MATCH_BYTECODES_##name_##_MAKE_DIRTY_BLOCK; \ case 566: \ ; \ } while (0); \ do { \ opcode_ = 567; \ n = 3; \ super = 0; \ num_args = 1; \ goto MATCH_BYTECODES_##name_##_SEND; \ case 567: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 179: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 568; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_LINE_NUMBER_BYTECODE; \ case 568: \ ; \ } while (0); \ do { \ opcode_ = 569; \ n = 0; \ goto MATCH_BYTECODES_##name_##_PUSH_LIT_CONSTANT; \ case 569: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 180: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 570; \ goto MATCH_BYTECODES_##name_##_DUP_STACK_TOP; \ case 570: \ ; \ } while (0); \ do { \ opcode_ = 571; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_PUSH_LIT_CONSTANT; \ case 571: \ ; \ } while (0); \ do { \ opcode_ = 572; \ n = 36; \ super = 0; \ goto MATCH_BYTECODES_##name_##_SEND_IMMEDIATE; \ case 572: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 181: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 573; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_LINE_NUMBER_BYTECODE; \ case 573: \ ; \ } while (0); \ do { \ opcode_ = 574; \ n = 1; \ scopes = 1; \ goto MATCH_BYTECODES_##name_##_PUSH_OUTER_TEMP; \ case 574: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 182: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 575; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_PUSH_INTEGER; \ case 575: \ ; \ } while (0); \ do { \ opcode_ = 576; \ n = 13; \ goto MATCH_BYTECODES_##name_##_SEND_ARITH; \ case 576: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 183: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 577; \ n = 1; \ goto MATCH_BYTECODES_##name_##_PUSH_LIT_CONSTANT; \ case 577: \ ; \ } while (0); \ do { \ opcode_ = 578; \ goto MATCH_BYTECODES_##name_##_MAKE_DIRTY_BLOCK; \ case 578: \ ; \ } while (0); \ do { \ opcode_ = 579; \ n = arg | arg_lsb; \ super = 0; \ goto MATCH_BYTECODES_##name_##_SEND_IMMEDIATE; \ case 579: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 184: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 580; \ n = 3; \ goto MATCH_BYTECODES_##name_##_PUSH_TEMPORARY_VARIABLE; \ case 580: \ ; \ } while (0); \ do { \ opcode_ = 581; \ n = arg | arg_lsb; \ super = 0; \ goto MATCH_BYTECODES_##name_##_SEND_IMMEDIATE; \ case 581: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 185: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 582; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_LINE_NUMBER_BYTECODE; \ case 582: \ ; \ } while (0); \ do { \ opcode_ = 583; \ n = 0; \ goto MATCH_BYTECODES_##name_##_PUSH_SPECIAL; \ case 583: \ ; \ } while (0); \ do { \ opcode_ = 584; \ goto MATCH_BYTECODES_##name_##_RETURN_CONTEXT_STACK_TOP; \ case 584: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 186: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 585; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_LINE_NUMBER_BYTECODE; \ case 585: \ ; \ } while (0); \ do { \ opcode_ = 586; \ n = 5; \ goto MATCH_BYTECODES_##name_##_PUSH_RECEIVER_VARIABLE; \ case 586: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 187: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 587; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_PUSH_LIT_CONSTANT; \ case 587: \ ; \ } while (0); \ do { \ opcode_ = 588; \ goto MATCH_BYTECODES_##name_##_MAKE_DIRTY_BLOCK; \ case 588: \ ; \ } while (0); \ do { \ opcode_ = 589; \ n = 2; \ super = 0; \ num_args = 1; \ goto MATCH_BYTECODES_##name_##_SEND; \ case 589: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 188: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 590; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_PUSH_TEMPORARY_VARIABLE; \ case 590: \ ; \ } while (0); \ do { \ opcode_ = 591; \ n = 7; \ goto MATCH_BYTECODES_##name_##_SEND_SPECIAL; \ case 591: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 189: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 592; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_PUSH_INTEGER; \ case 592: \ ; \ } while (0); \ do { \ opcode_ = 593; \ goto MATCH_BYTECODES_##name_##_RETURN_CONTEXT_STACK_TOP; \ case 593: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 190: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 594; \ n = 0; \ goto MATCH_BYTECODES_##name_##_PUSH_TEMPORARY_VARIABLE; \ case 594: \ ; \ } while (0); \ do { \ opcode_ = 595; \ n = arg | arg_lsb; \ super = 0; \ num_args = 2; \ goto MATCH_BYTECODES_##name_##_SEND; \ case 595: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 191: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 596; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_PUSH_TEMPORARY_VARIABLE; \ case 596: \ ; \ } while (0); \ do { \ opcode_ = 597; \ n = 1; \ goto MATCH_BYTECODES_##name_##_PUSH_INTEGER; \ case 597: \ ; \ } while (0); \ do { \ opcode_ = 598; \ n = 1; \ goto MATCH_BYTECODES_##name_##_SEND_ARITH; \ case 598: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 192: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 599; \ goto MATCH_BYTECODES_##name_##_PUSH_SELF; \ case 599: \ ; \ } while (0); \ do { \ opcode_ = 600; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_PUSH_LIT_CONSTANT; \ case 600: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 193: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 601; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_LINE_NUMBER_BYTECODE; \ case 601: \ ; \ } while (0); \ do { \ opcode_ = 602; \ n = 4; \ goto MATCH_BYTECODES_##name_##_PUSH_RECEIVER_VARIABLE; \ case 602: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 194: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 603; \ n = 0; \ scopes = 1; \ goto MATCH_BYTECODES_##name_##_PUSH_OUTER_TEMP; \ case 603: \ ; \ } while (0); \ do { \ opcode_ = 604; \ n = arg | arg_lsb; \ super = 0; \ goto MATCH_BYTECODES_##name_##_SEND_IMMEDIATE; \ case 604: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 195: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 605; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_LINE_NUMBER_BYTECODE; \ case 605: \ ; \ } while (0); \ do { \ opcode_ = 606; \ goto MATCH_BYTECODES_##name_##_PUSH_SELF; \ case 606: \ ; \ } while (0); \ do { \ opcode_ = 607; \ n = 1; \ super = 0; \ num_args = 0; \ goto MATCH_BYTECODES_##name_##_SEND; \ case 607: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 196: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 608; \ n = 0; \ scopes = 1; \ goto MATCH_BYTECODES_##name_##_PUSH_OUTER_TEMP; \ case 608: \ ; \ } while (0); \ do { \ opcode_ = 609; \ n = arg | arg_lsb; \ super = 0; \ num_args = 1; \ goto MATCH_BYTECODES_##name_##_SEND; \ case 609: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 197: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 610; \ n = 4; \ goto MATCH_BYTECODES_##name_##_PUSH_TEMPORARY_VARIABLE; \ case 610: \ ; \ } while (0); \ do { \ opcode_ = 611; \ n = arg | arg_lsb; \ super = 0; \ goto MATCH_BYTECODES_##name_##_SEND_IMMEDIATE; \ case 611: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 198: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 612; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_PUSH_INTEGER; \ case 612: \ ; \ } while (0); \ do { \ opcode_ = 613; \ n = 41; \ super = 0; \ goto MATCH_BYTECODES_##name_##_SEND_IMMEDIATE; \ case 613: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 199: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 614; \ n = arg | arg_lsb; \ super = 0; \ num_args = 4; \ goto MATCH_BYTECODES_##name_##_SEND; \ case 614: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 200: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 615; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_PUSH_TEMPORARY_VARIABLE; \ case 615: \ ; \ } while (0); \ do { \ opcode_ = 616; \ n = 2; \ goto MATCH_BYTECODES_##name_##_PUSH_TEMPORARY_VARIABLE; \ case 616: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 201: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 617; \ goto MATCH_BYTECODES_##name_##_PUSH_SELF; \ case 617: \ ; \ } while (0); \ do { \ opcode_ = 618; \ n = 3; \ goto MATCH_BYTECODES_##name_##_SEND_SPECIAL; \ case 618: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 202: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 619; \ n = 1; \ goto MATCH_BYTECODES_##name_##_PUSH_TEMPORARY_VARIABLE; \ case 619: \ ; \ } while (0); \ do { \ opcode_ = 620; \ n = arg >> 8; \ super = 0; \ num_args = arg_lsb; \ goto MATCH_BYTECODES_##name_##_SEND; \ case 620: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 203: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 621; \ goto MATCH_BYTECODES_##name_##_PUSH_SELF; \ case 621: \ ; \ } while (0); \ do { \ opcode_ = 622; \ n = 1; \ goto MATCH_BYTECODES_##name_##_PUSH_TEMPORARY_VARIABLE; \ case 622: \ ; \ } while (0); \ do { \ opcode_ = 623; \ n = arg | arg_lsb; \ super = 0; \ num_args = 1; \ goto MATCH_BYTECODES_##name_##_SEND; \ case 623: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 204: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 624; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_PUSH_LIT_CONSTANT; \ case 624: \ ; \ } while (0); \ do { \ opcode_ = 625; \ n = 4; \ super = 0; \ num_args = 1; \ goto MATCH_BYTECODES_##name_##_SEND; \ case 625: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 205: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 626; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_PUSH_INTEGER; \ case 626: \ ; \ } while (0); \ do { \ opcode_ = 627; \ n = 0; \ super = 0; \ num_args = 1; \ goto MATCH_BYTECODES_##name_##_SEND; \ case 627: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 206: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 628; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_PUSH_RECEIVER_VARIABLE; \ case 628: \ ; \ } while (0); \ do { \ opcode_ = 629; \ n = 2; \ goto MATCH_BYTECODES_##name_##_SEND_SPECIAL; \ case 629: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 207: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 630; \ n = 1; \ goto MATCH_BYTECODES_##name_##_PUSH_TEMPORARY_VARIABLE; \ case 630: \ ; \ } while (0); \ do { \ opcode_ = 631; \ n = arg | arg_lsb; \ super = 0; \ num_args = 2; \ goto MATCH_BYTECODES_##name_##_SEND; \ case 631: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 208: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 632; \ n = 0; \ goto MATCH_BYTECODES_##name_##_PUSH_TEMPORARY_VARIABLE; \ case 632: \ ; \ } while (0); \ do { \ opcode_ = 633; \ n = 1; \ goto MATCH_BYTECODES_##name_##_PUSH_TEMPORARY_VARIABLE; \ case 633: \ ; \ } while (0); \ do { \ opcode_ = 634; \ n = arg | arg_lsb; \ super = 0; \ num_args = 2; \ goto MATCH_BYTECODES_##name_##_SEND; \ case 634: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 209: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 635; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_PUSH_TEMPORARY_VARIABLE; \ case 635: \ ; \ } while (0); \ do { \ opcode_ = 636; \ n = 0; \ goto MATCH_BYTECODES_##name_##_POP_INTO_NEW_STACKTOP; \ case 636: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 210: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 637; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_PUSH_LIT_CONSTANT; \ case 637: \ ; \ } while (0); \ do { \ opcode_ = 638; \ goto MATCH_BYTECODES_##name_##_MAKE_DIRTY_BLOCK; \ case 638: \ ; \ } while (0); \ do { \ opcode_ = 639; \ n = 5; \ super = 0; \ num_args = 1; \ goto MATCH_BYTECODES_##name_##_SEND; \ case 639: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 211: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 640; \ n = arg | arg_lsb; \ super = 1; \ num_args = 1; \ goto MATCH_BYTECODES_##name_##_SEND; \ case 640: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 212: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 641; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_PUSH_LIT_CONSTANT; \ case 641: \ ; \ } while (0); \ do { \ opcode_ = 642; \ goto MATCH_BYTECODES_##name_##_MAKE_DIRTY_BLOCK; \ case 642: \ ; \ } while (0); \ do { \ opcode_ = 643; \ n = 4; \ super = 0; \ num_args = 1; \ goto MATCH_BYTECODES_##name_##_SEND; \ case 643: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 213: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 644; \ n = 1; \ goto MATCH_BYTECODES_##name_##_PUSH_RECEIVER_VARIABLE; \ case 644: \ ; \ } while (0); \ do { \ opcode_ = 645; \ n = arg | arg_lsb; \ super = 0; \ goto MATCH_BYTECODES_##name_##_SEND_IMMEDIATE; \ case 645: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 214: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 646; \ n = arg | arg_lsb; \ scopes = 1; \ goto MATCH_BYTECODES_##name_##_STORE_OUTER_TEMP; \ case 646: \ ; \ } while (0); \ do { \ opcode_ = 647; \ goto MATCH_BYTECODES_##name_##_RETURN_CONTEXT_STACK_TOP; \ case 647: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 215: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 648; \ goto MATCH_BYTECODES_##name_##_POP_STACK_TOP; \ case 648: \ ; \ } while (0); \ do { \ opcode_ = 649; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_LINE_NUMBER_BYTECODE; \ case 649: \ ; \ } while (0); \ do { \ opcode_ = 650; \ n = 37; \ super = 0; \ goto MATCH_BYTECODES_##name_##_SEND_IMMEDIATE; \ case 650: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 216: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 651; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_LINE_NUMBER_BYTECODE; \ case 651: \ ; \ } while (0); \ do { \ opcode_ = 652; \ goto MATCH_BYTECODES_##name_##_PUSH_SELF; \ case 652: \ ; \ } while (0); \ do { \ opcode_ = 653; \ n = 3; \ goto MATCH_BYTECODES_##name_##_SEND_SPECIAL; \ case 653: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 217: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 654; \ n = 1; \ goto MATCH_BYTECODES_##name_##_PUSH_TEMPORARY_VARIABLE; \ case 654: \ ; \ } while (0); \ do { \ opcode_ = 655; \ n = arg | arg_lsb; \ super = 0; \ num_args = 0; \ goto MATCH_BYTECODES_##name_##_SEND; \ case 655: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 218: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 656; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_LINE_NUMBER_BYTECODE; \ case 656: \ ; \ } while (0); \ do { \ opcode_ = 657; \ goto MATCH_BYTECODES_##name_##_PUSH_SELF; \ case 657: \ ; \ } while (0); \ do { \ opcode_ = 658; \ n = 130; \ super = 0; \ goto MATCH_BYTECODES_##name_##_SEND_IMMEDIATE; \ case 658: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 219: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 659; \ n = 0; \ goto MATCH_BYTECODES_##name_##_PUSH_RECEIVER_VARIABLE; \ case 659: \ ; \ } while (0); \ do { \ opcode_ = 660; \ n = arg | arg_lsb; \ super = 0; \ goto MATCH_BYTECODES_##name_##_SEND_IMMEDIATE; \ case 660: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 220: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 661; \ n = 0; \ goto MATCH_BYTECODES_##name_##_PUSH_TEMPORARY_VARIABLE; \ case 661: \ ; \ } while (0); \ do { \ opcode_ = 662; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_PUSH_LIT_VARIABLE; \ case 662: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 221: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 663; \ n = 0; \ goto MATCH_BYTECODES_##name_##_STORE_TEMPORARY_VARIABLE; \ case 663: \ ; \ } while (0); \ do { \ opcode_ = 664; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_LINE_NUMBER_BYTECODE; \ case 664: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 222: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 665; \ n = 2; \ goto MATCH_BYTECODES_##name_##_PUSH_RECEIVER_VARIABLE; \ case 665: \ ; \ } while (0); \ do { \ opcode_ = 666; \ n = arg | arg_lsb; \ super = 0; \ goto MATCH_BYTECODES_##name_##_SEND_IMMEDIATE; \ case 666: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 223: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 667; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_LINE_NUMBER_BYTECODE; \ case 667: \ ; \ } while (0); \ do { \ opcode_ = 668; \ goto MATCH_BYTECODES_##name_##_PUSH_SELF; \ case 668: \ ; \ } while (0); \ do { \ opcode_ = 669; \ n = 2; \ super = 0; \ num_args = 0; \ goto MATCH_BYTECODES_##name_##_SEND; \ case 669: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 224: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 670; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_LINE_NUMBER_BYTECODE; \ case 670: \ ; \ } while (0); \ do { \ opcode_ = 671; \ goto MATCH_BYTECODES_##name_##_POP_STACK_TOP; \ case 671: \ ; \ } while (0); \ do { \ opcode_ = 672; \ n = 2; \ goto MATCH_BYTECODES_##name_##_PUSH_TEMPORARY_VARIABLE; \ case 672: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 225: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 673; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_PUSH_LIT_CONSTANT; \ case 673: \ ; \ } while (0); \ do { \ opcode_ = 674; \ goto MATCH_BYTECODES_##name_##_MAKE_DIRTY_BLOCK; \ case 674: \ ; \ } while (0); \ do { \ opcode_ = 675; \ n = 6; \ super = 0; \ num_args = 1; \ goto MATCH_BYTECODES_##name_##_SEND; \ case 675: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 226: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 676; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_PUSH_SPECIAL; \ case 676: \ ; \ } while (0); \ do { \ opcode_ = 677; \ goto MATCH_BYTECODES_##name_##_RETURN_METHOD_STACK_TOP; \ case 677: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 227: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 678; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_PUSH_INTEGER; \ case 678: \ ; \ } while (0); \ do { \ opcode_ = 679; \ n = 5; \ goto MATCH_BYTECODES_##name_##_SEND_ARITH; \ case 679: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 228: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 680; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_LINE_NUMBER_BYTECODE; \ case 680: \ ; \ } while (0); \ do { \ opcode_ = 681; \ goto MATCH_BYTECODES_##name_##_POP_STACK_TOP; \ case 681: \ ; \ } while (0); \ do { \ opcode_ = 682; \ n = 1; \ goto MATCH_BYTECODES_##name_##_PUSH_RECEIVER_VARIABLE; \ case 682: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 229: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 683; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_LINE_NUMBER_BYTECODE; \ case 683: \ ; \ } while (0); \ do { \ opcode_ = 684; \ n = 3; \ goto MATCH_BYTECODES_##name_##_PUSH_LIT_VARIABLE; \ case 684: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 230: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 685; \ n = 2; \ goto MATCH_BYTECODES_##name_##_PUSH_LIT_CONSTANT; \ case 685: \ ; \ } while (0); \ do { \ opcode_ = 686; \ n = arg | arg_lsb; \ super = 0; \ goto MATCH_BYTECODES_##name_##_SEND_IMMEDIATE; \ case 686: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 231: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 687; \ n = arg | arg_lsb; \ super = 1; \ num_args = 0; \ goto MATCH_BYTECODES_##name_##_SEND; \ case 687: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 232: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 688; \ n = 0; \ goto MATCH_BYTECODES_##name_##_PUSH_SPECIAL; \ case 688: \ ; \ } while (0); \ do { \ opcode_ = 689; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_STORE_RECEIVER_VARIABLE; \ case 689: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 233: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 690; \ goto MATCH_BYTECODES_##name_##_PUSH_SELF; \ case 690: \ ; \ } while (0); \ do { \ opcode_ = 691; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_PUSH_TEMPORARY_VARIABLE; \ case 691: \ ; \ } while (0); \ do { \ opcode_ = 692; \ n = 0; \ super = 0; \ num_args = 1; \ goto MATCH_BYTECODES_##name_##_SEND; \ case 692: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 234: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 693; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_LINE_NUMBER_BYTECODE; \ case 693: \ ; \ } while (0); \ do { \ opcode_ = 694; \ goto MATCH_BYTECODES_##name_##_POP_STACK_TOP; \ case 694: \ ; \ } while (0); \ do { \ opcode_ = 695; \ n = 0; \ goto MATCH_BYTECODES_##name_##_PUSH_TEMPORARY_VARIABLE; \ case 695: \ ; \ } while (0); \ do { \ opcode_ = 696; \ goto MATCH_BYTECODES_##name_##_RETURN_CONTEXT_STACK_TOP; \ case 696: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 235: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 697; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_PUSH_LIT_CONSTANT; \ case 697: \ ; \ } while (0); \ do { \ opcode_ = 698; \ n = 8; \ goto MATCH_BYTECODES_##name_##_SEND_SPECIAL; \ case 698: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 236: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 699; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_PUSH_LIT_CONSTANT; \ case 699: \ ; \ } while (0); \ do { \ opcode_ = 700; \ goto MATCH_BYTECODES_##name_##_MAKE_DIRTY_BLOCK; \ case 700: \ ; \ } while (0); \ do { \ opcode_ = 701; \ n = 1; \ super = 0; \ num_args = 1; \ goto MATCH_BYTECODES_##name_##_SEND; \ case 701: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 237: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 702; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_LINE_NUMBER_BYTECODE; \ case 702: \ ; \ } while (0); \ do { \ opcode_ = 703; \ goto MATCH_BYTECODES_##name_##_POP_STACK_TOP; \ case 703: \ ; \ } while (0); \ do { \ opcode_ = 704; \ n = 3; \ goto MATCH_BYTECODES_##name_##_PUSH_TEMPORARY_VARIABLE; \ case 704: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 238: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 705; \ goto MATCH_BYTECODES_##name_##_POP_STACK_TOP; \ case 705: \ ; \ } while (0); \ do { \ opcode_ = 706; \ goto MATCH_BYTECODES_##name_##_DUP_STACK_TOP; \ case 706: \ ; \ } while (0); \ do { \ opcode_ = 707; \ n = arg | arg_lsb; \ super = 0; \ goto MATCH_BYTECODES_##name_##_SEND_IMMEDIATE; \ case 707: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 239: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 708; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_PUSH_LIT_CONSTANT; \ case 708: \ ; \ } while (0); \ do { \ opcode_ = 709; \ n = 0; \ goto MATCH_BYTECODES_##name_##_PUSH_TEMPORARY_VARIABLE; \ case 709: \ ; \ } while (0); \ do { \ opcode_ = 710; \ n = 1; \ goto MATCH_BYTECODES_##name_##_SEND_SPECIAL; \ case 710: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 240: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 711; \ goto MATCH_BYTECODES_##name_##_DUP_STACK_TOP; \ case 711: \ ; \ } while (0); \ do { \ opcode_ = 712; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_PUSH_TEMPORARY_VARIABLE; \ case 712: \ ; \ } while (0); \ do { \ opcode_ = 713; \ n = 1; \ goto MATCH_BYTECODES_##name_##_PUSH_INTEGER; \ case 713: \ ; \ } while (0); \ do { \ opcode_ = 714; \ n = 0; \ goto MATCH_BYTECODES_##name_##_SEND_ARITH; \ case 714: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 241: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 715; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_LINE_NUMBER_BYTECODE; \ case 715: \ ; \ } while (0); \ do { \ opcode_ = 716; \ n = 4; \ goto MATCH_BYTECODES_##name_##_PUSH_TEMPORARY_VARIABLE; \ case 716: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 242: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 717; \ goto MATCH_BYTECODES_##name_##_POP_STACK_TOP; \ case 717: \ ; \ } while (0); \ do { \ opcode_ = 718; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_LINE_NUMBER_BYTECODE; \ case 718: \ ; \ } while (0); \ do { \ opcode_ = 719; \ n = 1; \ goto MATCH_BYTECODES_##name_##_PUSH_LIT_VARIABLE; \ case 719: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 243: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 720; \ goto MATCH_BYTECODES_##name_##_DUP_STACK_TOP; \ case 720: \ ; \ } while (0); \ do { \ opcode_ = 721; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_PUSH_LIT_CONSTANT; \ case 721: \ ; \ } while (0); \ do { \ opcode_ = 722; \ n = 1; \ super = 0; \ num_args = 1; \ goto MATCH_BYTECODES_##name_##_SEND; \ case 722: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 244: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 723; \ n = 1; \ goto MATCH_BYTECODES_##name_##_POP_INTO_NEW_STACKTOP; \ case 723: \ ; \ } while (0); \ do { \ opcode_ = 724; \ n = arg | arg_lsb; \ super = 0; \ num_args = 1; \ goto MATCH_BYTECODES_##name_##_SEND; \ case 724: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 245: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 725; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_LINE_NUMBER_BYTECODE; \ case 725: \ ; \ } while (0); \ do { \ opcode_ = 726; \ goto MATCH_BYTECODES_##name_##_POP_STACK_TOP; \ case 726: \ ; \ } while (0); \ do { \ opcode_ = 727; \ n = 1; \ goto MATCH_BYTECODES_##name_##_PUSH_TEMPORARY_VARIABLE; \ case 727: \ ; \ } while (0); \ do { \ opcode_ = 728; \ goto MATCH_BYTECODES_##name_##_RETURN_CONTEXT_STACK_TOP; \ case 728: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 246: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 729; \ n = 3; \ goto MATCH_BYTECODES_##name_##_STORE_TEMPORARY_VARIABLE; \ case 729: \ ; \ } while (0); \ do { \ opcode_ = 730; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_LINE_NUMBER_BYTECODE; \ case 730: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 247: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 731; \ goto MATCH_BYTECODES_##name_##_DUP_STACK_TOP; \ case 731: \ ; \ } while (0); \ do { \ opcode_ = 732; \ n = arg | arg_lsb; \ super = 0; \ num_args = 0; \ goto MATCH_BYTECODES_##name_##_SEND; \ case 732: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 248: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 733; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_STORE_RECEIVER_VARIABLE; \ case 733: \ ; \ } while (0); \ do { \ opcode_ = 734; \ goto MATCH_BYTECODES_##name_##_RETURN_CONTEXT_STACK_TOP; \ case 734: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 249: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 735; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_LINE_NUMBER_BYTECODE; \ case 735: \ ; \ } while (0); \ do { \ opcode_ = 736; \ goto MATCH_BYTECODES_##name_##_PUSH_SELF; \ case 736: \ ; \ } while (0); \ do { \ opcode_ = 737; \ n = 3; \ super = 0; \ num_args = 0; \ goto MATCH_BYTECODES_##name_##_SEND; \ case 737: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 250: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 738; \ n = 5; \ goto MATCH_BYTECODES_##name_##_SEND_SPECIAL; \ case 738: \ ; \ } while (0); \ do { \ opcode_ = 739; \ goto MATCH_BYTECODES_##name_##_DUP_STACK_TOP; \ case 739: \ ; \ } while (0); \ do { \ opcode_ = 740; \ ofs = IP - IP0 + (arg | arg_lsb); \ goto MATCH_BYTECODES_##name_##_POP_JUMP_FALSE; \ case 740: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 251: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 741; \ goto MATCH_BYTECODES_##name_##_DUP_STACK_TOP; \ case 741: \ ; \ } while (0); \ do { \ opcode_ = 742; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_PUSH_LIT_CONSTANT; \ case 742: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 252: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 743; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_LINE_NUMBER_BYTECODE; \ case 743: \ ; \ } while (0); \ do { \ opcode_ = 744; \ n = 0; \ goto MATCH_BYTECODES_##name_##_PUSH_TEMPORARY_VARIABLE; \ case 744: \ ; \ } while (0); \ do { \ opcode_ = 745; \ goto MATCH_BYTECODES_##name_##_RETURN_CONTEXT_STACK_TOP; \ case 745: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 253: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 746; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_PUSH_INTEGER; \ case 746: \ ; \ } while (0); \ do { \ opcode_ = 747; \ n = 1; \ goto MATCH_BYTECODES_##name_##_SEND_SPECIAL; \ case 747: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 254: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 748; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_PUSH_TEMPORARY_VARIABLE; \ case 748: \ ; \ } while (0); \ do { \ opcode_ = 749; \ n = 3; \ goto MATCH_BYTECODES_##name_##_SEND_SPECIAL; \ case 749: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ case 255: \ opcode = IP[0]; \ arg_lsb = IP[1]; \ bp_ = (IP += 2); \ do { \ opcode_ = 750; \ n = arg | arg_lsb; \ goto MATCH_BYTECODES_##name_##_LINE_NUMBER_BYTECODE; \ case 750: \ ; \ } while (0); \ do { \ opcode_ = 751; \ n = 2; \ scopes = 1; \ goto MATCH_BYTECODES_##name_##_PUSH_OUTER_TEMP; \ case 751: \ ; \ } while (0); \ goto MATCH_BYTECODES_END_##name_; \ } \ MATCH_BYTECODES_DISPATCH(MATCH_BYTECODES_##name_) \ MATCH_BYTECODES_END_##name_: \ ;} END_MACRO #define MATCH_BYTECODES_DISPATCH(name) name #define MATCH_BYTECODES_PRINT_BYTECODE_NAME \ MATCH_BYTECODES_PRINT_BYTECODE_NAME_PUSH_RECEIVER_VARIABLE: \ { \ printf ("%s\tpush Instance Variable[%d]\n", prefix, n); \ prefix = pref; \ } \ goto MATCH_BYTECODES_SWITCH_PRINT_BYTECODE_NAME; \ MATCH_BYTECODES_PRINT_BYTECODE_NAME_PUSH_TEMPORARY_VARIABLE: \ { \ printf ("%s\tpush Temporary Variable[%d]\n", prefix, n); \ prefix = pref; \ } \ goto MATCH_BYTECODES_SWITCH_PRINT_BYTECODE_NAME; \ MATCH_BYTECODES_PRINT_BYTECODE_NAME_PUSH_LIT_CONSTANT: \ { \ printf ("%s\tpush Literal[%d]", prefix, n); \ if (literal_vec) \ printf (" = %O", literal_vec[n]); \ printf ("\n"); \ prefix = pref; \ } \ goto MATCH_BYTECODES_SWITCH_PRINT_BYTECODE_NAME; \ MATCH_BYTECODES_PRINT_BYTECODE_NAME_PUSH_LIT_VARIABLE: \ { \ printf ("%s\tpush Global Variable[%d]", prefix, n); \ if (literal_vec) \ printf (" = %+O", literal_vec[n]); \ printf ("\n"); \ prefix = pref; \ } \ goto MATCH_BYTECODES_SWITCH_PRINT_BYTECODE_NAME; \ MATCH_BYTECODES_PRINT_BYTECODE_NAME_PUSH_SELF: \ { \ printf ("%s\tpush self\n", prefix); \ prefix = pref; \ } \ goto MATCH_BYTECODES_SWITCH_PRINT_BYTECODE_NAME; \ MATCH_BYTECODES_PRINT_BYTECODE_NAME_PUSH_SPECIAL: \ { \ switch (n) { \ case TRUE_INDEX: printf ("%s\tpush true\n", prefix); break; \ case FALSE_INDEX: printf ("%s\tpush false\n", prefix); break; \ case NIL_INDEX: printf ("%s\tpush nil\n", prefix); break; \ } \ prefix = pref; \ } \ goto MATCH_BYTECODES_SWITCH_PRINT_BYTECODE_NAME; \ MATCH_BYTECODES_PRINT_BYTECODE_NAME_PUSH_INTEGER: \ { \ printf ("%s\tpush %d\n", prefix, n); \ prefix = pref; \ } \ goto MATCH_BYTECODES_SWITCH_PRINT_BYTECODE_NAME; \ MATCH_BYTECODES_PRINT_BYTECODE_NAME_RETURN_METHOD_STACK_TOP: \ { \ printf ("%s\treturn explicitly from method\n", prefix); \ prefix = pref; \ } \ goto MATCH_BYTECODES_SWITCH_PRINT_BYTECODE_NAME; \ MATCH_BYTECODES_PRINT_BYTECODE_NAME_RETURN_CONTEXT_STACK_TOP: \ { \ printf ("%s\treturn stack top\n", prefix); \ prefix = pref; \ } \ goto MATCH_BYTECODES_SWITCH_PRINT_BYTECODE_NAME; \ MATCH_BYTECODES_PRINT_BYTECODE_NAME_LINE_NUMBER_BYTECODE: \ { \ printf ("%s\tsource line %d\n", prefix, n); \ prefix = pref; \ } \ goto MATCH_BYTECODES_SWITCH_PRINT_BYTECODE_NAME; \ MATCH_BYTECODES_PRINT_BYTECODE_NAME_STORE_RECEIVER_VARIABLE: \ { \ printf ("%s\tstore into Instance Variable[%d]\n", prefix, n); \ prefix = pref; \ } \ goto MATCH_BYTECODES_SWITCH_PRINT_BYTECODE_NAME; \ MATCH_BYTECODES_PRINT_BYTECODE_NAME_STORE_TEMPORARY_VARIABLE: \ { \ printf ("%s\tstore into Temporary Variable[%d]\n", prefix, n); \ prefix = pref; \ } \ goto MATCH_BYTECODES_SWITCH_PRINT_BYTECODE_NAME; \ MATCH_BYTECODES_PRINT_BYTECODE_NAME_STORE_LIT_VARIABLE: \ { \ printf ("%s\tstore into Global Variable[%d]", prefix, n); \ if (literal_vec) \ printf (" = %+O", literal_vec[n]); \ printf ("\n"); \ prefix = pref; \ } \ goto MATCH_BYTECODES_SWITCH_PRINT_BYTECODE_NAME; \ MATCH_BYTECODES_PRINT_BYTECODE_NAME_SEND: \ { \ printf ("%s\tsend selector %d%s, %d args", prefix, n, super ? " to super" : "", num_args); \ if (literal_vec) \ printf (" = %O", literal_vec[n]); \ printf ("\n"); \ prefix = pref; \ } \ goto MATCH_BYTECODES_SWITCH_PRINT_BYTECODE_NAME; \ MATCH_BYTECODES_PRINT_BYTECODE_NAME_POP_INTO_NEW_STACKTOP: \ { \ printf ("%s\tpop and store into Instance Variable[%d] of new stack top\n", prefix, n); \ prefix = pref; \ } \ goto MATCH_BYTECODES_SWITCH_PRINT_BYTECODE_NAME; \ MATCH_BYTECODES_PRINT_BYTECODE_NAME_POP_STACK_TOP: \ { \ printf ("%s\tpop stack top\n", prefix); \ prefix = pref; \ } \ goto MATCH_BYTECODES_SWITCH_PRINT_BYTECODE_NAME; \ MATCH_BYTECODES_PRINT_BYTECODE_NAME_DUP_STACK_TOP: \ { \ printf ("%s\tduplicate stack top\n", prefix); \ prefix = pref; \ } \ goto MATCH_BYTECODES_SWITCH_PRINT_BYTECODE_NAME; \ MATCH_BYTECODES_PRINT_BYTECODE_NAME_PUSH_OUTER_TEMP: \ { \ printf ("%s\tpush outer var scopes = %d varIndex = %d\n", prefix, scopes, n); \ prefix = pref; \ } \ goto MATCH_BYTECODES_SWITCH_PRINT_BYTECODE_NAME; \ MATCH_BYTECODES_PRINT_BYTECODE_NAME_STORE_OUTER_TEMP: \ { \ printf ("%s\tstore outer var scopes = %d varIndex = %d\n", prefix, scopes, n); \ prefix = pref; \ } \ goto MATCH_BYTECODES_SWITCH_PRINT_BYTECODE_NAME; \ MATCH_BYTECODES_PRINT_BYTECODE_NAME_EXIT_INTERPRETER: \ { \ printf ("%s\tterminate interpreter\n", prefix); \ prefix = pref; \ } \ goto MATCH_BYTECODES_SWITCH_PRINT_BYTECODE_NAME; \ MATCH_BYTECODES_PRINT_BYTECODE_NAME_JUMP: \ { \ printf ("%s\tjump to %d\n", prefix, ip + ofs); \ prefix = pref; \ } \ goto MATCH_BYTECODES_SWITCH_PRINT_BYTECODE_NAME; \ MATCH_BYTECODES_PRINT_BYTECODE_NAME_POP_JUMP_TRUE: \ { \ printf ("%s\tpop and jump to %d if true\n", prefix, ip + ofs); \ prefix = pref; \ } \ goto MATCH_BYTECODES_SWITCH_PRINT_BYTECODE_NAME; \ MATCH_BYTECODES_PRINT_BYTECODE_NAME_POP_JUMP_FALSE: \ { \ printf ("%s\tpop and jump to %d if false\n", prefix, ip + ofs); \ prefix = pref; \ } \ goto MATCH_BYTECODES_SWITCH_PRINT_BYTECODE_NAME; \ MATCH_BYTECODES_PRINT_BYTECODE_NAME_SEND_ARITH: \ { \ printf ("%s\tsend arithmetic message %O\n", prefix, \ _gst_builtin_selectors[n].symbol); \ prefix = pref; \ } \ goto MATCH_BYTECODES_SWITCH_PRINT_BYTECODE_NAME; \ MATCH_BYTECODES_PRINT_BYTECODE_NAME_SEND_SPECIAL: \ { \ printf ("%s\tsend special message %O\n", prefix, \ _gst_builtin_selectors[n + 16].symbol); \ prefix = pref; \ } \ goto MATCH_BYTECODES_SWITCH_PRINT_BYTECODE_NAME; \ MATCH_BYTECODES_PRINT_BYTECODE_NAME_MAKE_DIRTY_BLOCK: \ { \ printf ("%s\tmake dirty block\n", prefix); \ prefix = pref; \ } \ goto MATCH_BYTECODES_SWITCH_PRINT_BYTECODE_NAME; \ MATCH_BYTECODES_PRINT_BYTECODE_NAME_SEND_IMMEDIATE: \ { \ printf ("%s\tsend special message %O%s\n", prefix, \ _gst_builtin_selectors[n].symbol, \ super ? " to super" : ""); \ prefix = pref; \ } \ goto MATCH_BYTECODES_SWITCH_PRINT_BYTECODE_NAME; \ MATCH_BYTECODES_PRINT_BYTECODE_NAME_INVALID: \ { \ printf ("%s\tINVALID BYTECODE %d(%d)\n", prefix, b, arg); \ prefix = pref; \ } \ goto MATCH_BYTECODES_SWITCH_PRINT_BYTECODE_NAME; #define MATCH_BYTECODES_IS_SIMPLE_RETURN \ MATCH_BYTECODES_IS_SIMPLE_RETURN_PUSH_SELF: \ { maybe = MTH_RETURN_SELF; } \ goto MATCH_BYTECODES_SWITCH_IS_SIMPLE_RETURN; \ MATCH_BYTECODES_IS_SIMPLE_RETURN_PUSH_RECEIVER_VARIABLE: \ { maybe = (n << 8) | MTH_RETURN_INSTVAR; } \ goto MATCH_BYTECODES_SWITCH_IS_SIMPLE_RETURN; \ MATCH_BYTECODES_IS_SIMPLE_RETURN_PUSH_LIT_CONSTANT: \ { maybe = (n << 8) | MTH_RETURN_LITERAL; } \ goto MATCH_BYTECODES_SWITCH_IS_SIMPLE_RETURN; \ MATCH_BYTECODES_IS_SIMPLE_RETURN_PUSH_INTEGER: \ { maybe_object = FROM_INT (n); maybe = MTH_RETURN_LITERAL; } \ goto MATCH_BYTECODES_SWITCH_IS_SIMPLE_RETURN; \ MATCH_BYTECODES_IS_SIMPLE_RETURN_PUSH_SPECIAL: \ { \ maybe = MTH_RETURN_LITERAL; \ switch (n) \ { \ case NIL_INDEX: maybe_object = _gst_nil_oop; break; \ case TRUE_INDEX: maybe_object = _gst_true_oop; break; \ case FALSE_INDEX: maybe_object = _gst_false_oop; break; \ default: abort (); \ } \ } \ goto MATCH_BYTECODES_SWITCH_IS_SIMPLE_RETURN; \ MATCH_BYTECODES_IS_SIMPLE_RETURN_LINE_NUMBER_BYTECODE: \ { } \ goto MATCH_BYTECODES_SWITCH_IS_SIMPLE_RETURN; \ MATCH_BYTECODES_IS_SIMPLE_RETURN_RETURN_CONTEXT_STACK_TOP: \ { \ if (maybe_object) \ _gst_add_forced_object (maybe_object); \ return maybe; \ } \ goto MATCH_BYTECODES_SWITCH_IS_SIMPLE_RETURN; \ MATCH_BYTECODES_IS_SIMPLE_RETURN_STORE_RECEIVER_VARIABLE: \ MATCH_BYTECODES_IS_SIMPLE_RETURN_PUSH_OUTER_TEMP: \ MATCH_BYTECODES_IS_SIMPLE_RETURN_STORE_OUTER_TEMP: \ MATCH_BYTECODES_IS_SIMPLE_RETURN_JUMP: \ MATCH_BYTECODES_IS_SIMPLE_RETURN_POP_JUMP_TRUE: \ MATCH_BYTECODES_IS_SIMPLE_RETURN_POP_JUMP_FALSE: \ MATCH_BYTECODES_IS_SIMPLE_RETURN_PUSH_TEMPORARY_VARIABLE: \ MATCH_BYTECODES_IS_SIMPLE_RETURN_PUSH_LIT_VARIABLE: \ MATCH_BYTECODES_IS_SIMPLE_RETURN_STORE_TEMPORARY_VARIABLE: \ MATCH_BYTECODES_IS_SIMPLE_RETURN_STORE_LIT_VARIABLE: \ MATCH_BYTECODES_IS_SIMPLE_RETURN_SEND: \ MATCH_BYTECODES_IS_SIMPLE_RETURN_POP_INTO_NEW_STACKTOP: \ MATCH_BYTECODES_IS_SIMPLE_RETURN_POP_STACK_TOP: \ MATCH_BYTECODES_IS_SIMPLE_RETURN_DUP_STACK_TOP: \ MATCH_BYTECODES_IS_SIMPLE_RETURN_SEND_IMMEDIATE: \ MATCH_BYTECODES_IS_SIMPLE_RETURN_EXIT_INTERPRETER: \ MATCH_BYTECODES_IS_SIMPLE_RETURN_SEND_ARITH: \ MATCH_BYTECODES_IS_SIMPLE_RETURN_SEND_SPECIAL: \ MATCH_BYTECODES_IS_SIMPLE_RETURN_MAKE_DIRTY_BLOCK: \ MATCH_BYTECODES_IS_SIMPLE_RETURN_RETURN_METHOD_STACK_TOP: \ { return (MTH_NORMAL); } \ goto MATCH_BYTECODES_SWITCH_IS_SIMPLE_RETURN; \ MATCH_BYTECODES_IS_SIMPLE_RETURN_INVALID: \ { abort(); } \ goto MATCH_BYTECODES_SWITCH_IS_SIMPLE_RETURN; #define MATCH_BYTECODES_CHECK_KIND_OF_BLOCK \ MATCH_BYTECODES_CHECK_KIND_OF_BLOCK_PUSH_SELF: \ MATCH_BYTECODES_CHECK_KIND_OF_BLOCK_PUSH_RECEIVER_VARIABLE: \ MATCH_BYTECODES_CHECK_KIND_OF_BLOCK_STORE_RECEIVER_VARIABLE: \ { \ if (status == 0) \ status = 1; \ } \ goto MATCH_BYTECODES_SWITCH_CHECK_KIND_OF_BLOCK; \ MATCH_BYTECODES_CHECK_KIND_OF_BLOCK_PUSH_LIT_CONSTANT: \ { \ newStatus = check_inner_block (literals[n]); \ if (newStatus > status) \ { \ if (newStatus == 31) \ return (31); \ status = newStatus; \ } \ } \ goto MATCH_BYTECODES_SWITCH_CHECK_KIND_OF_BLOCK; \ MATCH_BYTECODES_CHECK_KIND_OF_BLOCK_PUSH_OUTER_TEMP: \ MATCH_BYTECODES_CHECK_KIND_OF_BLOCK_STORE_OUTER_TEMP: \ { \ if (status < 1 + scopes) status = 1 + scopes; \ if (status > 31) \ /* ouch! how deep!! */ \ return (31); \ } \ goto MATCH_BYTECODES_SWITCH_CHECK_KIND_OF_BLOCK; \ MATCH_BYTECODES_CHECK_KIND_OF_BLOCK_JUMP: \ MATCH_BYTECODES_CHECK_KIND_OF_BLOCK_POP_JUMP_TRUE: \ MATCH_BYTECODES_CHECK_KIND_OF_BLOCK_POP_JUMP_FALSE: \ MATCH_BYTECODES_CHECK_KIND_OF_BLOCK_PUSH_TEMPORARY_VARIABLE: \ MATCH_BYTECODES_CHECK_KIND_OF_BLOCK_PUSH_LIT_VARIABLE: \ MATCH_BYTECODES_CHECK_KIND_OF_BLOCK_PUSH_SPECIAL: \ MATCH_BYTECODES_CHECK_KIND_OF_BLOCK_PUSH_INTEGER: \ MATCH_BYTECODES_CHECK_KIND_OF_BLOCK_RETURN_CONTEXT_STACK_TOP: \ MATCH_BYTECODES_CHECK_KIND_OF_BLOCK_LINE_NUMBER_BYTECODE: \ MATCH_BYTECODES_CHECK_KIND_OF_BLOCK_STORE_TEMPORARY_VARIABLE: \ MATCH_BYTECODES_CHECK_KIND_OF_BLOCK_STORE_LIT_VARIABLE: \ MATCH_BYTECODES_CHECK_KIND_OF_BLOCK_SEND: \ MATCH_BYTECODES_CHECK_KIND_OF_BLOCK_POP_INTO_NEW_STACKTOP: \ MATCH_BYTECODES_CHECK_KIND_OF_BLOCK_POP_STACK_TOP: \ MATCH_BYTECODES_CHECK_KIND_OF_BLOCK_DUP_STACK_TOP: \ MATCH_BYTECODES_CHECK_KIND_OF_BLOCK_EXIT_INTERPRETER: \ MATCH_BYTECODES_CHECK_KIND_OF_BLOCK_SEND_ARITH: \ MATCH_BYTECODES_CHECK_KIND_OF_BLOCK_SEND_SPECIAL: \ MATCH_BYTECODES_CHECK_KIND_OF_BLOCK_SEND_IMMEDIATE: \ MATCH_BYTECODES_CHECK_KIND_OF_BLOCK_MAKE_DIRTY_BLOCK: \ { } \ goto MATCH_BYTECODES_SWITCH_CHECK_KIND_OF_BLOCK; \ MATCH_BYTECODES_CHECK_KIND_OF_BLOCK_RETURN_METHOD_STACK_TOP: \ { return (31); } \ goto MATCH_BYTECODES_SWITCH_CHECK_KIND_OF_BLOCK; \ MATCH_BYTECODES_CHECK_KIND_OF_BLOCK_INVALID: \ { abort(); } \ goto MATCH_BYTECODES_SWITCH_CHECK_KIND_OF_BLOCK; #define MATCH_BYTECODES_THREAD_JUMPS \ MATCH_BYTECODES_THREAD_JUMPS_MAKE_DIRTY_BLOCK: \ MATCH_BYTECODES_THREAD_JUMPS_SEND_SPECIAL: \ MATCH_BYTECODES_THREAD_JUMPS_SEND_ARITH: \ MATCH_BYTECODES_THREAD_JUMPS_SEND_IMMEDIATE: \ MATCH_BYTECODES_THREAD_JUMPS_PUSH_RECEIVER_VARIABLE: \ MATCH_BYTECODES_THREAD_JUMPS_PUSH_TEMPORARY_VARIABLE: \ MATCH_BYTECODES_THREAD_JUMPS_PUSH_LIT_CONSTANT: \ MATCH_BYTECODES_THREAD_JUMPS_PUSH_LIT_VARIABLE: \ MATCH_BYTECODES_THREAD_JUMPS_PUSH_SELF: \ MATCH_BYTECODES_THREAD_JUMPS_PUSH_SPECIAL: \ MATCH_BYTECODES_THREAD_JUMPS_PUSH_INTEGER: \ MATCH_BYTECODES_THREAD_JUMPS_LINE_NUMBER_BYTECODE: \ MATCH_BYTECODES_THREAD_JUMPS_STORE_RECEIVER_VARIABLE: \ MATCH_BYTECODES_THREAD_JUMPS_STORE_TEMPORARY_VARIABLE: \ MATCH_BYTECODES_THREAD_JUMPS_STORE_LIT_VARIABLE: \ MATCH_BYTECODES_THREAD_JUMPS_SEND: \ MATCH_BYTECODES_THREAD_JUMPS_POP_INTO_NEW_STACKTOP: \ MATCH_BYTECODES_THREAD_JUMPS_POP_STACK_TOP: \ MATCH_BYTECODES_THREAD_JUMPS_DUP_STACK_TOP: \ MATCH_BYTECODES_THREAD_JUMPS_PUSH_OUTER_TEMP: \ MATCH_BYTECODES_THREAD_JUMPS_STORE_OUTER_TEMP: \ MATCH_BYTECODES_THREAD_JUMPS_EXIT_INTERPRETER: \ { } \ goto MATCH_BYTECODES_SWITCH_THREAD_JUMPS; \ MATCH_BYTECODES_THREAD_JUMPS_JUMP: \ { \ if (ofs == 2 \ && dest[0] == LINE_NUMBER_BYTECODE) \ { \ /* This could not be optimized to a nop, cause the \ jump and line number bytecodes lie in different \ basic blocks! So we rewrite it to a functionally \ equivalent but optimizable bytecode sequence. */ \ dest[-2] = dest[0]; \ dest[-1] = dest[1]; \ } \ else if (ofs == 4 \ && IS_PUSH_BYTECODE (dest[0]) \ && dest[2] == POP_STACK_TOP) \ { \ /* This could not be optimized to a single pop, \ cause the push and pop bytecodes lie in different \ basic blocks! Again, rewrite to an optimizable \ sequence. */ \ dest[-2] = POP_STACK_TOP; \ dest[-1] = 0; \ } \ else \ { \ /* Don't optimize jumps that have extension bytes. But if we \ jump to a return, we can safely optimize: returns are \ never extended, and the interpreter ignores the extension \ byte. TODO: check if this is still true. */ \ canOptimizeJump = (*IP0 != EXT_BYTE); \ kind = IP[-2]; \ dest_ip0 = dest = IP0 + ofs; \ canOptimizeJump |= IS_RETURN_BYTECODE (*dest); \ split = true; \ } \ } \ goto MATCH_BYTECODES_SWITCH_THREAD_JUMPS; \ MATCH_BYTECODES_THREAD_JUMPS_POP_JUMP_TRUE: \ MATCH_BYTECODES_THREAD_JUMPS_POP_JUMP_FALSE: \ { \ if (ofs == 0) \ { \ dest[-2] = POP_STACK_TOP; \ dest[-1] = 0; \ } \ \ /* Jumps to CONDITIONAL jumps must not be touched, either because \ they were unconditional or because they pop the stack top! */ \ else if (dest_ip0 == bp) \ { \ kind = IP[-2]; \ dest_ip0 = dest = IP0 + ofs; \ split = true; \ } \ } \ goto MATCH_BYTECODES_SWITCH_THREAD_JUMPS; \ MATCH_BYTECODES_THREAD_JUMPS_RETURN_METHOD_STACK_TOP: \ MATCH_BYTECODES_THREAD_JUMPS_RETURN_CONTEXT_STACK_TOP: \ { \ /* Return bytecodes - patch the original jump to return \ directly */ \ bp[0] = dest[-2]; \ bp[1] = 0; \ \ /* This in fact eliminated the jump, don't split in basic \ blocks */ \ split = false; \ } \ goto MATCH_BYTECODES_SWITCH_THREAD_JUMPS; \ MATCH_BYTECODES_THREAD_JUMPS_INVALID: \ { abort (); } \ goto MATCH_BYTECODES_SWITCH_THREAD_JUMPS; #define MATCH_BYTECODES_COMPUTE_STACK_POS \ MATCH_BYTECODES_COMPUTE_STACK_POS_RETURN_METHOD_STACK_TOP: \ MATCH_BYTECODES_COMPUTE_STACK_POS_RETURN_CONTEXT_STACK_TOP: \ { \ bc_len = bp - bp_first; \ \ /* We cannot fill the basic block right now because the \ stack height might be different. */ \ if (!bb_start[bc_len]) \ { \ ALLOCA_BASIC_BLOCK (bb_start + bc_len, 0, \ bp_first + bc_len, curr_sp + balance); \ bb_start[bc_len]->suspended = true; \ bb_start[bc_len]->next = NULL; \ *susp_tail = bb_start[bc_len]; \ susp_tail = &(bb_start[bc_len]->next); \ } \ } \ goto MATCH_BYTECODES_SWITCH_COMPUTE_STACK_POS; \ MATCH_BYTECODES_COMPUTE_STACK_POS_POP_INTO_NEW_STACKTOP: \ MATCH_BYTECODES_COMPUTE_STACK_POS_POP_STACK_TOP: \ { balance--; } \ goto MATCH_BYTECODES_SWITCH_COMPUTE_STACK_POS; \ MATCH_BYTECODES_COMPUTE_STACK_POS_PUSH_RECEIVER_VARIABLE: \ MATCH_BYTECODES_COMPUTE_STACK_POS_PUSH_TEMPORARY_VARIABLE: \ MATCH_BYTECODES_COMPUTE_STACK_POS_PUSH_LIT_CONSTANT: \ MATCH_BYTECODES_COMPUTE_STACK_POS_PUSH_LIT_VARIABLE: \ MATCH_BYTECODES_COMPUTE_STACK_POS_PUSH_SELF: \ MATCH_BYTECODES_COMPUTE_STACK_POS_PUSH_SPECIAL: \ MATCH_BYTECODES_COMPUTE_STACK_POS_PUSH_INTEGER: \ MATCH_BYTECODES_COMPUTE_STACK_POS_DUP_STACK_TOP: \ MATCH_BYTECODES_COMPUTE_STACK_POS_PUSH_OUTER_TEMP: \ { balance++; } \ goto MATCH_BYTECODES_SWITCH_COMPUTE_STACK_POS; \ MATCH_BYTECODES_COMPUTE_STACK_POS_LINE_NUMBER_BYTECODE: \ MATCH_BYTECODES_COMPUTE_STACK_POS_STORE_RECEIVER_VARIABLE: \ MATCH_BYTECODES_COMPUTE_STACK_POS_STORE_TEMPORARY_VARIABLE: \ MATCH_BYTECODES_COMPUTE_STACK_POS_STORE_LIT_VARIABLE: \ MATCH_BYTECODES_COMPUTE_STACK_POS_STORE_OUTER_TEMP: \ MATCH_BYTECODES_COMPUTE_STACK_POS_EXIT_INTERPRETER: \ MATCH_BYTECODES_COMPUTE_STACK_POS_MAKE_DIRTY_BLOCK: \ { } \ goto MATCH_BYTECODES_SWITCH_COMPUTE_STACK_POS; \ MATCH_BYTECODES_COMPUTE_STACK_POS_SEND: \ { \ balance -= super + num_args; \ } \ goto MATCH_BYTECODES_SWITCH_COMPUTE_STACK_POS; \ MATCH_BYTECODES_COMPUTE_STACK_POS_SEND_ARITH: \ { \ balance -= _gst_builtin_selectors[n].numArgs; \ } \ goto MATCH_BYTECODES_SWITCH_COMPUTE_STACK_POS; \ MATCH_BYTECODES_COMPUTE_STACK_POS_SEND_IMMEDIATE: \ { \ balance -= super + _gst_builtin_selectors[n].numArgs; \ } \ goto MATCH_BYTECODES_SWITCH_COMPUTE_STACK_POS; \ MATCH_BYTECODES_COMPUTE_STACK_POS_SEND_SPECIAL: \ { \ balance -= _gst_builtin_selectors[n + 16].numArgs; \ } \ goto MATCH_BYTECODES_SWITCH_COMPUTE_STACK_POS; \ MATCH_BYTECODES_COMPUTE_STACK_POS_INVALID: \ { \ abort (); \ } \ goto MATCH_BYTECODES_SWITCH_COMPUTE_STACK_POS; \ MATCH_BYTECODES_COMPUTE_STACK_POS_JUMP: \ { \ bc_len = bp - bp_first; \ \ /* We cannot fill the basic block right now because the \ stack height might be different. */ \ if (!bb_start[bc_len]) \ { \ ALLOCA_BASIC_BLOCK (bb_start + bc_len, 0, \ bp_first + bc_len, 0); \ bb_start[bc_len]->suspended = true; \ bb_start[bc_len]->next = NULL; \ *susp_tail = bb_start[bc_len]; \ susp_tail = &(bb_start[bc_len]->next); \ } \ \ if (!bb_start[ofs]) \ { \ ALLOCA_BASIC_BLOCK (bb_start + ofs, 0, \ bp_first + ofs, curr_sp + balance); \ bb_start[ofs]->next = worklist; \ worklist = bb_start[ofs]; \ } \ else if (bb_start[ofs]->suspended) \ { \ bb_start[ofs]->suspended = false; \ bb_start[ofs]->sp = curr_sp + balance; \ } \ else if (curr_sp + balance != bb_start[ofs]->sp) \ abort (); \ } \ goto MATCH_BYTECODES_SWITCH_COMPUTE_STACK_POS; \ MATCH_BYTECODES_COMPUTE_STACK_POS_POP_JUMP_TRUE: \ MATCH_BYTECODES_COMPUTE_STACK_POS_POP_JUMP_FALSE: \ { \ balance--; \ bc_len = bp - bp_first; \ if (!bb_start[bc_len]) \ { \ ALLOCA_BASIC_BLOCK (bb_start + bc_len, 0, \ bp_first + bc_len, curr_sp + balance); \ bb_start[bc_len]->next = worklist; \ worklist = bb_start[bc_len]; \ } \ else if (bb_start[bc_len]->suspended) \ { \ bb_start[bc_len]->suspended = false; \ bb_start[bc_len]->sp = curr_sp + balance; \ } \ else if (curr_sp + balance != bb_start[bc_len]->sp) \ abort (); \ \ if (!bb_start[ofs]) \ { \ ALLOCA_BASIC_BLOCK (bb_start + ofs, 0, \ bp_first + ofs, curr_sp + balance); \ bb_start[ofs]->next = worklist; \ worklist = bb_start[ofs]; \ } \ else if (bb_start[ofs]->suspended) \ { \ bb_start[ofs]->suspended = false; \ bb_start[ofs]->sp = curr_sp + balance; \ } \ else if (curr_sp + balance != bb_start[ofs]->sp) \ abort (); \ } \ goto MATCH_BYTECODES_SWITCH_COMPUTE_STACK_POS; #define MATCH_BYTECODES_MAKE_DEST_TABLE \ MATCH_BYTECODES_MAKE_DEST_TABLE_PUSH_RECEIVER_VARIABLE: \ MATCH_BYTECODES_MAKE_DEST_TABLE_PUSH_TEMPORARY_VARIABLE: \ MATCH_BYTECODES_MAKE_DEST_TABLE_PUSH_LIT_CONSTANT: \ MATCH_BYTECODES_MAKE_DEST_TABLE_PUSH_LIT_VARIABLE: \ MATCH_BYTECODES_MAKE_DEST_TABLE_PUSH_SELF: \ MATCH_BYTECODES_MAKE_DEST_TABLE_PUSH_SPECIAL: \ MATCH_BYTECODES_MAKE_DEST_TABLE_PUSH_INTEGER: \ MATCH_BYTECODES_MAKE_DEST_TABLE_RETURN_METHOD_STACK_TOP: \ MATCH_BYTECODES_MAKE_DEST_TABLE_RETURN_CONTEXT_STACK_TOP: \ MATCH_BYTECODES_MAKE_DEST_TABLE_LINE_NUMBER_BYTECODE: \ MATCH_BYTECODES_MAKE_DEST_TABLE_STORE_RECEIVER_VARIABLE: \ MATCH_BYTECODES_MAKE_DEST_TABLE_STORE_TEMPORARY_VARIABLE: \ MATCH_BYTECODES_MAKE_DEST_TABLE_STORE_LIT_VARIABLE: \ MATCH_BYTECODES_MAKE_DEST_TABLE_SEND: \ MATCH_BYTECODES_MAKE_DEST_TABLE_POP_INTO_NEW_STACKTOP: \ MATCH_BYTECODES_MAKE_DEST_TABLE_POP_STACK_TOP: \ MATCH_BYTECODES_MAKE_DEST_TABLE_DUP_STACK_TOP: \ MATCH_BYTECODES_MAKE_DEST_TABLE_PUSH_OUTER_TEMP: \ MATCH_BYTECODES_MAKE_DEST_TABLE_STORE_OUTER_TEMP: \ MATCH_BYTECODES_MAKE_DEST_TABLE_EXIT_INTERPRETER: \ MATCH_BYTECODES_MAKE_DEST_TABLE_SEND_ARITH: \ MATCH_BYTECODES_MAKE_DEST_TABLE_SEND_SPECIAL: \ MATCH_BYTECODES_MAKE_DEST_TABLE_SEND_IMMEDIATE: \ MATCH_BYTECODES_MAKE_DEST_TABLE_MAKE_DIRTY_BLOCK: \ { } \ goto MATCH_BYTECODES_SWITCH_MAKE_DEST_TABLE; \ MATCH_BYTECODES_MAKE_DEST_TABLE_INVALID: \ { abort(); } \ goto MATCH_BYTECODES_SWITCH_MAKE_DEST_TABLE; \ MATCH_BYTECODES_MAKE_DEST_TABLE_JUMP: \ MATCH_BYTECODES_MAKE_DEST_TABLE_POP_JUMP_TRUE: \ MATCH_BYTECODES_MAKE_DEST_TABLE_POP_JUMP_FALSE: \ { \ dest[ofs] = ofs > 0 ? 1 : -1; \ count++; \ } \ goto MATCH_BYTECODES_SWITCH_MAKE_DEST_TABLE; #define MATCH_BYTECODES_CREATE_BASIC_BLOCKS \ MATCH_BYTECODES_CREATE_BASIC_BLOCKS_RETURN_METHOD_STACK_TOP: \ MATCH_BYTECODES_CREATE_BASIC_BLOCKS_RETURN_CONTEXT_STACK_TOP: \ { \ bc_len = bp - bp_first; \ \ /* We cannot fill the basic block right now because the \ stack height might be different. */ \ if (!bb_start[bc_len]) \ { \ ALLOCA_BASIC_BLOCK (bb_start + bc_len, stack_depth, \ bp_first + bc_len, curr_sp + balance); \ bb_start[bc_len]->suspended = true; \ bb_start[bc_len]->next = NULL; \ *susp_tail = bb_start[bc_len]; \ susp_tail = &(bb_start[bc_len]->next); \ } \ } \ goto MATCH_BYTECODES_SWITCH_CREATE_BASIC_BLOCKS; \ MATCH_BYTECODES_CREATE_BASIC_BLOCKS_POP_STACK_TOP: \ { balance--; } \ goto MATCH_BYTECODES_SWITCH_CREATE_BASIC_BLOCKS; \ MATCH_BYTECODES_CREATE_BASIC_BLOCKS_PUSH_RECEIVER_VARIABLE: \ MATCH_BYTECODES_CREATE_BASIC_BLOCKS_PUSH_TEMPORARY_VARIABLE: \ MATCH_BYTECODES_CREATE_BASIC_BLOCKS_PUSH_LIT_CONSTANT: \ MATCH_BYTECODES_CREATE_BASIC_BLOCKS_PUSH_LIT_VARIABLE: \ MATCH_BYTECODES_CREATE_BASIC_BLOCKS_PUSH_SELF: \ MATCH_BYTECODES_CREATE_BASIC_BLOCKS_PUSH_SPECIAL: \ MATCH_BYTECODES_CREATE_BASIC_BLOCKS_PUSH_INTEGER: \ MATCH_BYTECODES_CREATE_BASIC_BLOCKS_PUSH_OUTER_TEMP: \ { balance++; } \ goto MATCH_BYTECODES_SWITCH_CREATE_BASIC_BLOCKS; \ MATCH_BYTECODES_CREATE_BASIC_BLOCKS_LINE_NUMBER_BYTECODE: \ MATCH_BYTECODES_CREATE_BASIC_BLOCKS_STORE_RECEIVER_VARIABLE: \ MATCH_BYTECODES_CREATE_BASIC_BLOCKS_STORE_TEMPORARY_VARIABLE: \ MATCH_BYTECODES_CREATE_BASIC_BLOCKS_STORE_LIT_VARIABLE: \ MATCH_BYTECODES_CREATE_BASIC_BLOCKS_STORE_OUTER_TEMP: \ MATCH_BYTECODES_CREATE_BASIC_BLOCKS_EXIT_INTERPRETER: \ MATCH_BYTECODES_CREATE_BASIC_BLOCKS_MAKE_DIRTY_BLOCK: \ { } \ goto MATCH_BYTECODES_SWITCH_CREATE_BASIC_BLOCKS; \ MATCH_BYTECODES_CREATE_BASIC_BLOCKS_SEND: \ { \ balance -= super + num_args; \ \ /* Sends touch the new stack top, so they require an extra slot. */ \ if (curr_sp + balance < 1) \ return ("stack underflow"); \ } \ goto MATCH_BYTECODES_SWITCH_CREATE_BASIC_BLOCKS; \ MATCH_BYTECODES_CREATE_BASIC_BLOCKS_SEND_ARITH: \ { \ if (!_gst_builtin_selectors[n].symbol) \ return ("invalid immediate send"); \ \ balance -= _gst_builtin_selectors[n].numArgs; \ \ /* Sends touch the new stack top, so they require an extra slot. */ \ if (curr_sp + balance < 1) \ return ("stack underflow"); \ } \ goto MATCH_BYTECODES_SWITCH_CREATE_BASIC_BLOCKS; \ MATCH_BYTECODES_CREATE_BASIC_BLOCKS_SEND_SPECIAL: \ { \ if (!_gst_builtin_selectors[n + 16].symbol) \ return ("invalid immediate send"); \ \ balance -= _gst_builtin_selectors[n + 16].numArgs; \ \ /* Sends touch the new stack top, so they require an extra slot. */ \ if (curr_sp + balance < 1) \ return ("stack underflow"); \ } \ goto MATCH_BYTECODES_SWITCH_CREATE_BASIC_BLOCKS; \ MATCH_BYTECODES_CREATE_BASIC_BLOCKS_SEND_IMMEDIATE: \ { \ if (!_gst_builtin_selectors[n].symbol) \ return ("invalid immediate send"); \ \ balance -= super + _gst_builtin_selectors[n].numArgs; \ \ /* Sends touch the new stack top, so they require an extra slot. */ \ if (curr_sp + balance < 1) \ return ("stack underflow"); \ } \ goto MATCH_BYTECODES_SWITCH_CREATE_BASIC_BLOCKS; \ MATCH_BYTECODES_CREATE_BASIC_BLOCKS_POP_INTO_NEW_STACKTOP: \ { \ balance--; \ \ /* Sends touch the new stack top, so they require an extra slot. */ \ if (curr_sp + balance < 1) \ return ("stack underflow"); \ } \ goto MATCH_BYTECODES_SWITCH_CREATE_BASIC_BLOCKS; \ MATCH_BYTECODES_CREATE_BASIC_BLOCKS_DUP_STACK_TOP: \ { \ balance++; \ } \ goto MATCH_BYTECODES_SWITCH_CREATE_BASIC_BLOCKS; \ MATCH_BYTECODES_CREATE_BASIC_BLOCKS_INVALID: \ { \ return ("invalid bytecode"); \ } \ goto MATCH_BYTECODES_SWITCH_CREATE_BASIC_BLOCKS; \ MATCH_BYTECODES_CREATE_BASIC_BLOCKS_JUMP: \ { \ if (ofs & 1) \ return ("jump to odd offset"); \ \ if (ofs + curr_ip < 0 || ofs + curr_ip > size) \ return ("jump out of range"); \ \ if (ofs + curr_ip > 0 && bp_first[ofs - 2] == EXT_BYTE) \ return ("jump skips extension bytecode"); \ \ bc_len = bp - bp_first; \ \ /* We cannot fill the basic block right now because the \ stack height might be different. */ \ if (!bb_start[bc_len]) \ { \ ALLOCA_BASIC_BLOCK (bb_start + bc_len, stack_depth, \ bp_first + bc_len, 0); \ bb_start[bc_len]->suspended = true; \ bb_start[bc_len]->next = NULL; \ *susp_tail = bb_start[bc_len]; \ susp_tail = &(bb_start[bc_len]->next); \ } \ \ if (!bb_start[ofs]) \ { \ ALLOCA_BASIC_BLOCK (bb_start + ofs, stack_depth, \ bp_first + ofs, curr_sp + balance); \ \ bb_start[ofs]->next = worklist; \ worklist = bb_start[ofs]; \ INIT_BASIC_BLOCK (worklist, num_temps); \ } \ else if (bb_start[ofs]->suspended) \ { \ bb_start[ofs]->suspended = false; \ bb_start[ofs]->sp = curr_sp + balance; \ INIT_BASIC_BLOCK (bb_start[ofs], num_temps); \ } \ else if (curr_sp + balance != bb_start[ofs]->sp) \ return ("stack height mismatch"); \ } \ goto MATCH_BYTECODES_SWITCH_CREATE_BASIC_BLOCKS; \ MATCH_BYTECODES_CREATE_BASIC_BLOCKS_POP_JUMP_TRUE: \ MATCH_BYTECODES_CREATE_BASIC_BLOCKS_POP_JUMP_FALSE: \ { \ balance--; \ if (ofs & 1) \ return ("jump to odd offset"); \ \ if (ofs + curr_ip < 0 || ofs + curr_ip > size) \ return ("jump out of range"); \ \ if (ofs + curr_ip > 0 && bp_first[ofs - 2] == EXT_BYTE) \ return ("jump skips extension bytecode"); \ \ bc_len = bp - bp_first; \ if (!bb_start[bc_len]) \ { \ ALLOCA_BASIC_BLOCK (bb_start + bc_len, stack_depth, \ bp_first + bc_len, curr_sp + balance); \ \ bb_start[bc_len]->next = worklist; \ worklist = bb_start[bc_len]; \ INIT_BASIC_BLOCK (worklist, num_temps); \ } \ else if (bb_start[bc_len]->suspended) \ { \ bb_start[bc_len]->suspended = false; \ bb_start[bc_len]->sp = curr_sp + balance; \ INIT_BASIC_BLOCK (bb_start[bc_len], num_temps); \ } \ else if (curr_sp + balance != bb_start[bc_len]->sp) \ return ("stack height mismatch"); \ \ if (!bb_start[ofs]) \ { \ ALLOCA_BASIC_BLOCK (bb_start + ofs, stack_depth, \ bp_first + ofs, curr_sp + balance); \ \ bb_start[ofs]->next = worklist; \ worklist = bb_start[ofs]; \ INIT_BASIC_BLOCK (worklist, num_temps); \ } \ else if (bb_start[ofs]->suspended) \ { \ bb_start[ofs]->suspended = false; \ bb_start[ofs]->sp = curr_sp + balance; \ INIT_BASIC_BLOCK (bb_start[ofs], num_temps); \ } \ else if (curr_sp + balance != bb_start[ofs]->sp) \ return ("stack height mismatch"); \ } \ goto MATCH_BYTECODES_SWITCH_CREATE_BASIC_BLOCKS; #define MATCH_BYTECODES_EXEC_BASIC_BLOCK \ MATCH_BYTECODES_EXEC_BASIC_BLOCK_PUSH_RECEIVER_VARIABLE: \ { \ CHECK_REC_VAR (0, n); \ *sp++ = FROM_INT (VARYING); \ } \ goto MATCH_BYTECODES_SWITCH_EXEC_BASIC_BLOCK; \ MATCH_BYTECODES_EXEC_BASIC_BLOCK_PUSH_TEMPORARY_VARIABLE: \ { \ CHECK_TEMP (n); \ *sp++ = stack[n]; \ } \ goto MATCH_BYTECODES_SWITCH_EXEC_BASIC_BLOCK; \ MATCH_BYTECODES_EXEC_BASIC_BLOCK_PUSH_LIT_CONSTANT: \ { \ CHECK_LITERAL (n); \ *sp++ = LITERAL_CLASS (n); \ } \ goto MATCH_BYTECODES_SWITCH_EXEC_BASIC_BLOCK; \ MATCH_BYTECODES_EXEC_BASIC_BLOCK_PUSH_LIT_VARIABLE: \ { \ CHECK_LIT_VARIABLE (false, n); \ *sp++ = LIT_VARIABLE_CLASS (n); \ } \ goto MATCH_BYTECODES_SWITCH_EXEC_BASIC_BLOCK; \ MATCH_BYTECODES_EXEC_BASIC_BLOCK_PUSH_SELF: \ { \ last_used_literal = NULL; \ *sp++ = FROM_INT (SELF); \ } \ goto MATCH_BYTECODES_SWITCH_EXEC_BASIC_BLOCK; \ MATCH_BYTECODES_EXEC_BASIC_BLOCK_PUSH_SPECIAL: \ { \ switch (n) \ { \ case NIL_INDEX: last_used_literal = _gst_nil_oop; break; \ case TRUE_INDEX: last_used_literal = _gst_true_oop; break; \ case FALSE_INDEX: last_used_literal = _gst_false_oop; break; \ default: return "invalid special object index"; \ } \ \ *sp++ = OOP_CLASS (last_used_literal); \ } \ goto MATCH_BYTECODES_SWITCH_EXEC_BASIC_BLOCK; \ MATCH_BYTECODES_EXEC_BASIC_BLOCK_PUSH_INTEGER: \ { \ last_used_literal = FROM_INT (n); \ *sp++ = _gst_small_integer_class; \ } \ goto MATCH_BYTECODES_SWITCH_EXEC_BASIC_BLOCK; \ MATCH_BYTECODES_EXEC_BASIC_BLOCK_RETURN_METHOD_STACK_TOP: \ { \ block_header header; \ if (OOP_CLASS (methodOOP) != _gst_compiled_block_class) \ return "invalid return from method"; \ \ header = GET_BLOCK_HEADER (methodOOP); \ if (header.clean != (1 << BLK_CLEAN_BITS) - 1) \ return "invalid return from clean block"; \ \ break; \ } \ goto MATCH_BYTECODES_SWITCH_EXEC_BASIC_BLOCK; \ MATCH_BYTECODES_EXEC_BASIC_BLOCK_RETURN_CONTEXT_STACK_TOP: \ { break; } \ goto MATCH_BYTECODES_SWITCH_EXEC_BASIC_BLOCK; \ MATCH_BYTECODES_EXEC_BASIC_BLOCK_LINE_NUMBER_BYTECODE: \ { } \ goto MATCH_BYTECODES_SWITCH_EXEC_BASIC_BLOCK; \ MATCH_BYTECODES_EXEC_BASIC_BLOCK_STORE_RECEIVER_VARIABLE: \ { \ CHECK_REC_VAR (num_ro_rec_vars, n); \ } \ goto MATCH_BYTECODES_SWITCH_EXEC_BASIC_BLOCK; \ MATCH_BYTECODES_EXEC_BASIC_BLOCK_STORE_TEMPORARY_VARIABLE: \ { \ CHECK_TEMP (n); \ } \ goto MATCH_BYTECODES_SWITCH_EXEC_BASIC_BLOCK; \ MATCH_BYTECODES_EXEC_BASIC_BLOCK_STORE_LIT_VARIABLE: \ { \ CHECK_LIT_VARIABLE (true, n); \ } \ goto MATCH_BYTECODES_SWITCH_EXEC_BASIC_BLOCK; \ MATCH_BYTECODES_EXEC_BASIC_BLOCK_SEND: \ { \ if (super \ && (!last_used_literal \ || (!IS_A_CLASS (last_used_literal) \ && !IS_A_METACLASS (last_used_literal)) \ || !is_a_kind_of (methodClass, last_used_literal))) \ return ("Invalid send to super"); \ \ last_used_literal = NULL; \ sp -= super + num_args; \ if (super && sp[-1] != FROM_INT (SELF)) \ return ("Invalid send to super"); \ \ sp[-1] = FROM_INT (VARYING); \ } \ goto MATCH_BYTECODES_SWITCH_EXEC_BASIC_BLOCK; \ MATCH_BYTECODES_EXEC_BASIC_BLOCK_POP_INTO_NEW_STACKTOP: \ { \ if (sp[-2] != _gst_array_class) \ return ("Array expected"); \ \ if (!arrays || &sp[-2] - stack != arrays->sp) \ return ("Invalid Array constructor"); \ \ if (n >= arrays->size) \ return ("Out of bounds Array access"); \ \ /* Discard arrays whose construction has ended. */ \ if (n == arrays->size - 1) \ { \ partially_constructed_array *next = arrays->next; \ arrays->next = arrays_pool; \ arrays_pool = arrays; \ arrays = next; \ } \ \ last_used_literal = NULL; \ sp--; \ } \ goto MATCH_BYTECODES_SWITCH_EXEC_BASIC_BLOCK; \ MATCH_BYTECODES_EXEC_BASIC_BLOCK_POP_STACK_TOP: \ { \ last_used_literal = NULL; \ sp--; \ } \ goto MATCH_BYTECODES_SWITCH_EXEC_BASIC_BLOCK; \ MATCH_BYTECODES_EXEC_BASIC_BLOCK_DUP_STACK_TOP: \ { \ sp++; \ sp[-1] = sp[-2]; \ } \ goto MATCH_BYTECODES_SWITCH_EXEC_BASIC_BLOCK; \ MATCH_BYTECODES_EXEC_BASIC_BLOCK_PUSH_OUTER_TEMP: \ { \ if (scopes == 0 || scopes > depth || n >= num_outer_temps[scopes]) \ return ("temporary out of range"); \ \ last_used_literal = NULL; \ *sp++ = FROM_INT (VARYING); \ } \ goto MATCH_BYTECODES_SWITCH_EXEC_BASIC_BLOCK; \ MATCH_BYTECODES_EXEC_BASIC_BLOCK_STORE_OUTER_TEMP: \ { \ if (scopes == 0 || scopes > depth || n >= num_outer_temps[scopes]) \ return ("temporary out of range"); \ } \ goto MATCH_BYTECODES_SWITCH_EXEC_BASIC_BLOCK; \ MATCH_BYTECODES_EXEC_BASIC_BLOCK_EXIT_INTERPRETER: \ { \ if (size != 4 \ || IP0 != GET_METHOD_BYTECODES (methodOOP) \ || *bp != RETURN_CONTEXT_STACK_TOP) \ return ("bad termination method"); \ } \ goto MATCH_BYTECODES_SWITCH_EXEC_BASIC_BLOCK; \ MATCH_BYTECODES_EXEC_BASIC_BLOCK_JUMP: \ { \ if (merge_stacks (stack, sp - stack, bb_start[ofs]->stack, \ bb_start[ofs]->sp)) \ bb_start[ofs]->next = worklist, worklist = bb_start[ofs]; \ } \ goto MATCH_BYTECODES_SWITCH_EXEC_BASIC_BLOCK; \ MATCH_BYTECODES_EXEC_BASIC_BLOCK_POP_JUMP_TRUE: \ MATCH_BYTECODES_EXEC_BASIC_BLOCK_POP_JUMP_FALSE: \ { \ sp--; \ bc_len = bp - bp_first; \ if (merge_stacks (stack, sp - stack, bb_start[bc_len]->stack, \ bb_start[bc_len]->sp)) \ bb_start[bc_len]->next = worklist, worklist = bb_start[bc_len]; \ \ if (merge_stacks (stack, sp - stack, bb_start[ofs]->stack, \ bb_start[ofs]->sp)) \ bb_start[ofs]->next = worklist, worklist = bb_start[ofs]; \ } \ goto MATCH_BYTECODES_SWITCH_EXEC_BASIC_BLOCK; \ MATCH_BYTECODES_EXEC_BASIC_BLOCK_SEND_ARITH: \ { \ sp -= _gst_builtin_selectors[n].numArgs; \ sp[-1] = FROM_INT (VARYING); \ } \ goto MATCH_BYTECODES_SWITCH_EXEC_BASIC_BLOCK; \ MATCH_BYTECODES_EXEC_BASIC_BLOCK_SEND_SPECIAL: \ { \ sp -= _gst_builtin_selectors[n + 16].numArgs; \ sp[-1] = FROM_INT (VARYING); \ } \ goto MATCH_BYTECODES_SWITCH_EXEC_BASIC_BLOCK; \ MATCH_BYTECODES_EXEC_BASIC_BLOCK_SEND_IMMEDIATE: \ { \ if (n == NEW_COLON_SPECIAL \ && IS_INT (last_used_literal) \ && last_used_literal != FROM_INT (0) \ && sp[-2] == OOP_CLASS (_gst_array_class)) \ { \ partially_constructed_array *a; \ sp--; \ \ /* If possible, reuse an existing struct, else allocate a new one. */ \ if (arrays_pool) \ { \ a = arrays_pool; \ arrays_pool = arrays_pool->next; \ } \ else \ a = alloca (sizeof (partially_constructed_array)); \ \ a->size = TO_INT (last_used_literal); \ a->sp = &sp[-1] - stack; \ a->next = arrays; \ arrays = a; \ \ sp[-1] = _gst_array_class; \ } \ else \ { \ if (super \ && (!last_used_literal \ || (!IS_A_CLASS (last_used_literal) \ && !IS_A_METACLASS (last_used_literal)) \ || !is_a_kind_of (methodClass, last_used_literal))) \ return (_gst_debug (), "Invalid send to super"); \ \ last_used_literal = NULL; \ sp -= super + _gst_builtin_selectors[n].numArgs; \ if (super && sp[-1] != FROM_INT (SELF)) \ return ("Invalid send to super"); \ \ sp[-1] = FROM_INT (VARYING); \ } \ } \ goto MATCH_BYTECODES_SWITCH_EXEC_BASIC_BLOCK; \ MATCH_BYTECODES_EXEC_BASIC_BLOCK_MAKE_DIRTY_BLOCK: \ { \ if (sp[-1] != _gst_compiled_block_class \ || !last_used_literal) \ return ("CompiledBlock expected"); \ \ error = _gst_verify_method (last_used_literal, num_outer_temps, depth); \ if (error) \ return (error); \ } \ goto MATCH_BYTECODES_SWITCH_EXEC_BASIC_BLOCK; \ MATCH_BYTECODES_EXEC_BASIC_BLOCK_INVALID: \ { \ abort (); \ } \ goto MATCH_BYTECODES_SWITCH_EXEC_BASIC_BLOCK; #define MATCH_BYTECODES_XLAT_BUILD_CODE_TREE \ MATCH_BYTECODES_XLAT_BUILD_CODE_TREE_PUSH_RECEIVER_VARIABLE: \ { \ push_tree_node (IP0, NULL, TREE_PUSH | TREE_REC_VAR, \ (PTR) (uintptr_t) n); \ } \ goto MATCH_BYTECODES_SWITCH_XLAT_BUILD_CODE_TREE; \ MATCH_BYTECODES_XLAT_BUILD_CODE_TREE_PUSH_TEMPORARY_VARIABLE: \ { \ push_tree_node (IP0, NULL, TREE_PUSH | TREE_TEMP, \ (PTR) (uintptr_t) n); \ } \ goto MATCH_BYTECODES_SWITCH_XLAT_BUILD_CODE_TREE; \ MATCH_BYTECODES_XLAT_BUILD_CODE_TREE_PUSH_LIT_CONSTANT: \ { \ push_tree_node_oop (IP0, NULL, TREE_PUSH | TREE_LIT_CONST, \ literals[n]); \ } \ goto MATCH_BYTECODES_SWITCH_XLAT_BUILD_CODE_TREE; \ MATCH_BYTECODES_XLAT_BUILD_CODE_TREE_PUSH_LIT_VARIABLE: \ { \ if (is_a_kind_of (OOP_INT_CLASS (literals[n]), _gst_association_class)) \ push_tree_node_oop (IP0, NULL, TREE_PUSH | TREE_LIT_VAR, \ literals[n]); \ else \ { \ push_tree_node_oop (IP0, NULL, TREE_PUSH | TREE_LIT_CONST, \ literals[n]); \ push_send_node (IP0, _gst_builtin_selectors[VALUE_SPECIAL].symbol, \ 0, false, TREE_SEND, 0); \ } \ } \ goto MATCH_BYTECODES_SWITCH_XLAT_BUILD_CODE_TREE; \ MATCH_BYTECODES_XLAT_BUILD_CODE_TREE_PUSH_SELF: \ { \ push_tree_node (IP0, NULL, \ TREE_PUSH | TREE_SELF | self_class_check, NULL); \ } \ goto MATCH_BYTECODES_SWITCH_XLAT_BUILD_CODE_TREE; \ MATCH_BYTECODES_XLAT_BUILD_CODE_TREE_PUSH_SPECIAL: \ { \ push_tree_node_oop (IP0, NULL, TREE_PUSH | TREE_LIT_CONST, \ *specialOOPs[n]); \ } \ goto MATCH_BYTECODES_SWITCH_XLAT_BUILD_CODE_TREE; \ MATCH_BYTECODES_XLAT_BUILD_CODE_TREE_PUSH_INTEGER: \ { \ push_tree_node_oop (IP0, NULL, TREE_PUSH | TREE_LIT_CONST, \ FROM_INT (n)); \ } \ goto MATCH_BYTECODES_SWITCH_XLAT_BUILD_CODE_TREE; \ MATCH_BYTECODES_XLAT_BUILD_CODE_TREE_RETURN_METHOD_STACK_TOP: \ { \ set_top_node_extra (TREE_EXTRA_METHOD_RET, 0); \ emit_code (); \ } \ goto MATCH_BYTECODES_SWITCH_XLAT_BUILD_CODE_TREE; \ MATCH_BYTECODES_XLAT_BUILD_CODE_TREE_RETURN_CONTEXT_STACK_TOP: \ { \ set_top_node_extra (TREE_EXTRA_RETURN, 0); \ emit_code (); \ } \ goto MATCH_BYTECODES_SWITCH_XLAT_BUILD_CODE_TREE; \ MATCH_BYTECODES_XLAT_BUILD_CODE_TREE_LINE_NUMBER_BYTECODE: \ { \ } \ goto MATCH_BYTECODES_SWITCH_XLAT_BUILD_CODE_TREE; \ MATCH_BYTECODES_XLAT_BUILD_CODE_TREE_STORE_RECEIVER_VARIABLE: \ { \ push_tree_node (IP0, pop_tree_node (NULL), \ TREE_STORE | TREE_REC_VAR, \ (PTR) (uintptr_t) n); \ } \ goto MATCH_BYTECODES_SWITCH_XLAT_BUILD_CODE_TREE; \ MATCH_BYTECODES_XLAT_BUILD_CODE_TREE_STORE_TEMPORARY_VARIABLE: \ { \ push_tree_node (IP0, pop_tree_node (NULL), \ TREE_STORE | TREE_TEMP, \ (PTR) (uintptr_t) n); \ } \ goto MATCH_BYTECODES_SWITCH_XLAT_BUILD_CODE_TREE; \ MATCH_BYTECODES_XLAT_BUILD_CODE_TREE_STORE_LIT_VARIABLE: \ { \ if (is_a_kind_of (OOP_INT_CLASS (literals[n]), _gst_association_class)) \ push_tree_node_oop (IP0, pop_tree_node (NULL), \ TREE_STORE | TREE_LIT_VAR, literals[n]); \ else \ { \ code_tree *value, *var; \ inline_cache *ic; \ \ push_tree_node_oop (IP0, NULL, \ TREE_ALT_PUSH | TREE_LIT_CONST, literals[n]); \ ic = set_inline_cache (_gst_builtin_selectors[VALUE_COLON_SPECIAL].symbol, \ 1, false, TREE_SEND, 0); \ \ var = pop_tree_node (NULL); \ value = pop_tree_node (var); \ push_tree_node (IP0, value, TREE_SEND | TREE_STORE_LIT_VAR, (PTR) ic); \ } \ } \ goto MATCH_BYTECODES_SWITCH_XLAT_BUILD_CODE_TREE; \ MATCH_BYTECODES_XLAT_BUILD_CODE_TREE_SEND: \ { \ push_send_node (IP0, literals[n], num_args, super, TREE_SEND, 0); \ } \ goto MATCH_BYTECODES_SWITCH_XLAT_BUILD_CODE_TREE; \ MATCH_BYTECODES_XLAT_BUILD_CODE_TREE_POP_INTO_NEW_STACKTOP: \ { \ push_tree_node (IP0, \ pop_tree_node (pop_tree_node (NULL)), \ TREE_STORE | TREE_POP_INTO_ARRAY, \ (PTR) (uintptr_t) n); \ } \ goto MATCH_BYTECODES_SWITCH_XLAT_BUILD_CODE_TREE; \ MATCH_BYTECODES_XLAT_BUILD_CODE_TREE_POP_STACK_TOP: \ { \ set_top_node_extra (TREE_EXTRA_POP, 0); \ emit_code (); \ \ /* This is very important! If we do not adjust T_SP here, we \ miscompile superoperators that include a POP/PUSH sequence. */ \ t_sp--; \ } \ goto MATCH_BYTECODES_SWITCH_XLAT_BUILD_CODE_TREE; \ MATCH_BYTECODES_XLAT_BUILD_CODE_TREE_DUP_STACK_TOP: \ { \ push_tree_node (IP0, NULL, TREE_PUSH | TREE_DUP, NULL); \ } \ goto MATCH_BYTECODES_SWITCH_XLAT_BUILD_CODE_TREE; \ MATCH_BYTECODES_XLAT_BUILD_CODE_TREE_PUSH_OUTER_TEMP: \ { \ push_tree_node (IP0, NULL, TREE_PUSH | TREE_OUTER_TEMP, \ (PTR) (uintptr_t) ((scopes << 8) | n)); \ } \ goto MATCH_BYTECODES_SWITCH_XLAT_BUILD_CODE_TREE; \ MATCH_BYTECODES_XLAT_BUILD_CODE_TREE_STORE_OUTER_TEMP: \ { \ push_tree_node (IP0, \ pop_tree_node (NULL), \ TREE_STORE | TREE_OUTER_TEMP, \ (PTR) (uintptr_t) ((scopes << 8) | n)); \ } \ goto MATCH_BYTECODES_SWITCH_XLAT_BUILD_CODE_TREE; \ MATCH_BYTECODES_XLAT_BUILD_CODE_TREE_JUMP: \ { \ set_top_node_extra (TREE_EXTRA_JMP_ALWAYS, ofs); \ \ emit_code (); \ } \ goto MATCH_BYTECODES_SWITCH_XLAT_BUILD_CODE_TREE; \ MATCH_BYTECODES_XLAT_BUILD_CODE_TREE_POP_JUMP_TRUE: \ { \ set_top_node_extra (TREE_EXTRA_JMP_TRUE, ofs); \ \ emit_code (); \ } \ goto MATCH_BYTECODES_SWITCH_XLAT_BUILD_CODE_TREE; \ MATCH_BYTECODES_XLAT_BUILD_CODE_TREE_POP_JUMP_FALSE: \ { \ set_top_node_extra (TREE_EXTRA_JMP_FALSE, ofs); \ \ emit_code (); \ } \ goto MATCH_BYTECODES_SWITCH_XLAT_BUILD_CODE_TREE; \ MATCH_BYTECODES_XLAT_BUILD_CODE_TREE_SEND_ARITH: \ { \ int op = special_send_bytecodes[n]; \ const struct builtin_selector *bs = &_gst_builtin_selectors[n]; \ push_send_node (IP0, bs->symbol, bs->numArgs, false, op, n); \ } \ goto MATCH_BYTECODES_SWITCH_XLAT_BUILD_CODE_TREE; \ MATCH_BYTECODES_XLAT_BUILD_CODE_TREE_SEND_SPECIAL: \ { \ int op = special_send_bytecodes[n + 16]; \ const struct builtin_selector *bs = &_gst_builtin_selectors[n + 16]; \ push_send_node (IP0, bs->symbol, bs->numArgs, false, op, n + 16); \ } \ goto MATCH_BYTECODES_SWITCH_XLAT_BUILD_CODE_TREE; \ MATCH_BYTECODES_XLAT_BUILD_CODE_TREE_SEND_IMMEDIATE: \ { \ const struct builtin_selector *bs = &_gst_builtin_selectors[n]; \ push_send_node (IP0, bs->symbol, bs->numArgs, super, \ TREE_SEND | TREE_NORMAL, n); \ } \ goto MATCH_BYTECODES_SWITCH_XLAT_BUILD_CODE_TREE; \ MATCH_BYTECODES_XLAT_BUILD_CODE_TREE_MAKE_DIRTY_BLOCK: \ { \ code_tree *arg; \ arg = pop_tree_node (NULL); \ push_tree_node (IP0, arg, TREE_SEND | TREE_DIRTY_BLOCK, NULL); \ } \ goto MATCH_BYTECODES_SWITCH_XLAT_BUILD_CODE_TREE; \ MATCH_BYTECODES_XLAT_BUILD_CODE_TREE_EXIT_INTERPRETER: \ MATCH_BYTECODES_XLAT_BUILD_CODE_TREE_INVALID: \ { \ abort (); \ } \ goto MATCH_BYTECODES_SWITCH_XLAT_BUILD_CODE_TREE; #define MATCH_BYTECODES_XLAT_COUNT_SENDS \ MATCH_BYTECODES_XLAT_COUNT_SENDS_PUSH_RECEIVER_VARIABLE: \ MATCH_BYTECODES_XLAT_COUNT_SENDS_PUSH_TEMPORARY_VARIABLE: \ MATCH_BYTECODES_XLAT_COUNT_SENDS_PUSH_LIT_CONSTANT: \ MATCH_BYTECODES_XLAT_COUNT_SENDS_PUSH_SELF: \ MATCH_BYTECODES_XLAT_COUNT_SENDS_PUSH_SPECIAL: \ MATCH_BYTECODES_XLAT_COUNT_SENDS_PUSH_INTEGER: \ MATCH_BYTECODES_XLAT_COUNT_SENDS_RETURN_METHOD_STACK_TOP: \ MATCH_BYTECODES_XLAT_COUNT_SENDS_RETURN_CONTEXT_STACK_TOP: \ MATCH_BYTECODES_XLAT_COUNT_SENDS_LINE_NUMBER_BYTECODE: \ MATCH_BYTECODES_XLAT_COUNT_SENDS_STORE_RECEIVER_VARIABLE: \ MATCH_BYTECODES_XLAT_COUNT_SENDS_STORE_TEMPORARY_VARIABLE: \ MATCH_BYTECODES_XLAT_COUNT_SENDS_POP_INTO_NEW_STACKTOP: \ MATCH_BYTECODES_XLAT_COUNT_SENDS_POP_STACK_TOP: \ MATCH_BYTECODES_XLAT_COUNT_SENDS_DUP_STACK_TOP: \ MATCH_BYTECODES_XLAT_COUNT_SENDS_PUSH_OUTER_TEMP: \ MATCH_BYTECODES_XLAT_COUNT_SENDS_STORE_OUTER_TEMP: \ MATCH_BYTECODES_XLAT_COUNT_SENDS_JUMP: \ MATCH_BYTECODES_XLAT_COUNT_SENDS_POP_JUMP_TRUE: \ MATCH_BYTECODES_XLAT_COUNT_SENDS_POP_JUMP_FALSE: \ MATCH_BYTECODES_XLAT_COUNT_SENDS_MAKE_DIRTY_BLOCK: \ MATCH_BYTECODES_XLAT_COUNT_SENDS_EXIT_INTERPRETER: \ MATCH_BYTECODES_XLAT_COUNT_SENDS_INVALID: \ { } \ goto MATCH_BYTECODES_SWITCH_XLAT_COUNT_SENDS; \ MATCH_BYTECODES_XLAT_COUNT_SENDS_PUSH_LIT_VARIABLE: \ MATCH_BYTECODES_XLAT_COUNT_SENDS_STORE_LIT_VARIABLE: \ { \ if (!is_a_kind_of (OOP_INT_CLASS (literals[n]), _gst_association_class)) \ inlineCacheCount++; \ } \ goto MATCH_BYTECODES_SWITCH_XLAT_COUNT_SENDS; \ MATCH_BYTECODES_XLAT_COUNT_SENDS_SEND_ARITH: \ MATCH_BYTECODES_XLAT_COUNT_SENDS_SEND_SPECIAL: \ MATCH_BYTECODES_XLAT_COUNT_SENDS_SEND_IMMEDIATE: \ MATCH_BYTECODES_XLAT_COUNT_SENDS_SEND: \ { \ inlineCacheCount++; \ } \ goto MATCH_BYTECODES_SWITCH_XLAT_COUNT_SENDS; #endif smalltalk-3.2.5/libgst/vm.stamp0000644000175000017500000000001212130456004013366 00000000000000timestamp smalltalk-3.2.5/libgst/interp.h0000644000175000017500000005665012130343734013400 00000000000000/******************************** -*- C -*- **************************** * * Byte Code interpreter declarations. * * ***********************************************************************/ /*********************************************************************** * * Copyright 1988,89,90,91,92,94,95,99,2000,2001,2002,2006,2007,2008,2009 * Free Software Foundation, Inc. * Written by Steve Byrne. * * This file is part of GNU Smalltalk. * * GNU Smalltalk is free software; you can redistribute it and/or modify it * under the terms of the GNU General Public License as published by the Free * Software Foundation; either version 2, or (at your option) any later * version. * * Linking GNU Smalltalk statically or dynamically with other modules is * making a combined work based on GNU Smalltalk. Thus, the terms and * conditions of the GNU General Public License cover the whole * combination. * * In addition, as a special exception, the Free Software Foundation * give you permission to combine GNU Smalltalk with free software * programs or libraries that are released under the GNU LGPL and with * independent programs running under the GNU Smalltalk virtual machine. * * You may copy and distribute such a system following the terms of the * GNU GPL for GNU Smalltalk and the licenses of the other code * concerned, provided that you include the source code of that other * code when and as the GNU GPL requires distribution of source code. * * Note that people who make modified versions of GNU Smalltalk are not * obligated to grant this special exception for their modified * versions; it is their choice whether to do so. The GNU General * Public License gives permission to release a modified version without * this exception; this exception also makes it possible to release a * modified version which carries forward this exception. * * GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or * FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for * more details. * * You should have received a copy of the GNU General Public License along with * GNU Smalltalk; see the file COPYING. If not, write to the Free Software * Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * ***********************************************************************/ #ifndef GST_INTERP_H #define GST_INTERP_H /* The number of available process priorities */ #define NUM_PRIORITIES 9 #define USER_SCHEDULING_PRIORITY 4 /* Ordering of file operations must match that used in FileStream.st */ enum { PRIM_OPEN_FILE, /* open:mode: */ PRIM_CLOSE_FILE, /* no args */ PRIM_PUT_CHARS, /* data:from:to: */ PRIM_GET_CHARS, /* data:from:to: */ PRIM_FSEEK_SET, /* position: */ PRIM_FTELL, /* no args */ PRIM_FEOF, /* no args */ PRIM_OPEN_PIPE, /* open:mode: */ PRIM_FSEEK_CUR, /* skip: */ PRIM_FSIZE, /* no args */ PRIM_FTRUNCATE, /* no args */ PRIM_FILEIN, /* no args */ PRIM_FILEIN_AT, /* line:file:charPos: */ PRIM_SYNC_POLL, /* read/write/exception */ PRIM_ASYNC_POLL, /* operation:semaphore: */ PRIM_IS_PIPE, /* no args */ PRIM_MK_TEMP, /* base: */ PRIM_GET_CHARS_AT, /* data:from:to:absOfs: */ PRIM_PUT_CHARS_AT, /* data:from:to:absOfs: */ PRIM_SHUTDOWN_WRITE /* shutdown */ }; /* These macros are used to quickly compute the number of words needed for a context with a maximum allowable stack depth of DEPTH. */ #define FIXED_CTX_SIZE (sizeof(struct gst_method_context) / sizeof(PTR) - 1) #define CTX_SIZE(depth) (((depth) << DEPTH_SCALE) + FIXED_CTX_SIZE) #define DUMMY_NATIVE_IP FROM_INT(0) /* The structure of execution context objects. */ typedef struct gst_context_part { OBJ_HEADER; OOP parentContext; OOP native_ip; /* used by JIT */ OOP ipOffset; /* an integer byte index into method */ OOP spOffset; /* an integer index into cur context stack */ OOP receiver; /* the receiver OOP */ OOP method; /* the method that we're executing */ OOP x; /* depends on the subclass */ OOP contextStack[1]; } *gst_context_part; typedef struct gst_method_context { OBJ_HEADER; OOP parentContext; OOP native_ip; /* used by JIT */ OOP ipOffset; /* an integer byte index into method */ OOP spOffset; /* an integer index into cur context stack */ OOP receiver; /* the receiver OOP */ OOP method; /* the method that we're executing */ intptr_t flags; /* must be an int to distinguish gst_compiled_block/gst_method_context */ OOP contextStack[1]; } *gst_method_context; /* CompiledMethod cache (see descriptions in interp-bc.inl and interp-jit.inl) */ typedef struct method_cache_entry { OOP selectorOOP; OOP startingClassOOP; OOP methodOOP; OOP methodClassOOP; method_header methodHeader; #ifdef ENABLE_JIT_TRANSLATION OOP receiverClass; PTR nativeCode; PTR dummy; /* 32 bytes are usually a sweet spot */ #endif } method_cache_entry; /* MCF stands for MethodContext Flag. */ /* This is always set so that Smalltalk sees the flags member as a SmallInteger. BlockContexts store the outer context there, so it is never a SmallInteger. */ #define MCF_IS_METHOD_CONTEXT 1 /* Answer whether this context must be skipped when doing a local method return. Contexts are marked this way when an exception occurs or if there is a non-local method return and there are active #ensure: calls. */ #define MCF_IS_DISABLED_CONTEXT 2 /* Answer whether this context must not be discarded upon a non-local method return. Contexts evaluating #ensure: and/or #ifCurtailed: are marked this way. */ #define MCF_IS_UNWIND_CONTEXT 4 /* Answer whether execution started from this context (this kind of MethodContext is used to mark call-ins from C to Smalltalk and is placed on top of the context that was executing at the time of the call-in, and is the parent of the called-in method). */ #define MCF_IS_EXECUTION_ENVIRONMENT 8 typedef struct gst_block_context { OBJ_HEADER; OOP parentContext; OOP native_ip; /* used by JIT */ OOP ipOffset; /* an integer byte index into method */ OOP spOffset; /* an integer index into cur context stack */ OOP receiver; /* the receiver OOP */ OOP method; /* the method that we're executing */ OOP outerContext; /* the parent gst_block_context or gst_method_context */ OOP contextStack[1]; } *gst_block_context; typedef struct gst_continuation { OBJ_HEADER; OOP stack; } *gst_continuation; /* The structure of various objects related to the process system. */ typedef struct gst_semaphore { OBJ_HEADER; OOP firstLink; OOP lastLink; OOP signals; OOP name; } *gst_semaphore; #define PROCESS_HEADER \ OBJ_HEADER; \ OOP nextLink; \ OOP suspendedContext; \ OOP priority; \ OOP myList; \ OOP name; \ OOP unwindPoints; \ OOP interrupts; \ OOP interruptLock typedef struct gst_process { PROCESS_HEADER; } *gst_process; typedef struct gst_callin_process { PROCESS_HEADER; OOP returnedValue; } *gst_callin_process; typedef struct gst_processor_scheduler { OBJ_HEADER; OOP processLists; OOP activeProcess; OOP idleTasks; OOP processTimeslice; OOP gcSemaphore; OOP gcArray; } *gst_processor_scheduler; /* Some performance counters from the interpreter: these count the number of special returns. */ extern unsigned long _gst_literal_returns ATTRIBUTE_HIDDEN, _gst_inst_var_returns ATTRIBUTE_HIDDEN, _gst_self_returns ATTRIBUTE_HIDDEN; /* The number of primitives executed. */ extern unsigned long _gst_primitives_executed ATTRIBUTE_HIDDEN; /* The number of bytecodes executed. */ extern unsigned long _gst_bytecode_counter ATTRIBUTE_HIDDEN; /* The number of method cache misses */ extern unsigned long _gst_cache_misses ATTRIBUTE_HIDDEN; /* The number of cache lookups - either hits or misses */ extern unsigned long _gst_sample_counter ATTRIBUTE_HIDDEN; /* If this is true, for each byte code that is executed, we print on stdout the byte index within the current gst_compiled_method and a decoded interpretation of the byte code. If > 1, it applies also to code not invoked by the user. */ extern int _gst_execution_tracing ATTRIBUTE_HIDDEN; /* When this is true, and an interrupt occurs (such as SIGSEGV), Smalltalk will terminate itself by making a core dump (normally it produces a backtrace). */ extern mst_Boolean _gst_make_core_file ATTRIBUTE_HIDDEN; /* When true, this indicates that there is no top level loop for control to return to, so it causes the system to exit. */ extern mst_Boolean _gst_non_interactive ATTRIBUTE_HIDDEN; /* The OOP for a gst_compiled_method or gst_compiled_block that is the currently executing method. */ extern OOP _gst_this_method ATTRIBUTE_HIDDEN; /* Physical address of the base of the method temporary variables. Typically a small number of bytes (multiple of 4 since it points to OOPs) lower than sp. */ extern OOP *_gst_temporaries ATTRIBUTE_HIDDEN; /* Physical address of the base of the method literals. */ extern OOP *_gst_literals ATTRIBUTE_HIDDEN; /* An OOP that is the current receiver of the current message. */ extern OOP _gst_self ATTRIBUTE_HIDDEN; /* A gst_block_context or gst_method_context that indicates the context that the interpreter is currently running in. */ extern OOP _gst_this_context_oop ATTRIBUTE_HIDDEN; /* The OOP for an IdentityDictionary that stores the raw profile. */ extern OOP _gst_raw_profile ATTRIBUTE_HIDDEN; /* A bytecode counter value used while profiling. */ extern unsigned long _gst_saved_bytecode_counter ATTRIBUTE_HIDDEN; /* The type used to hold the instruction pointer. For the JIT, this is an offset from a location which is deemed the `base' of native-compiled methods (because this way it will fit in a SmallInteger and can be stored in the returnIP field of the context objects); for the interpreter, this is the physical address of the next executed bytecode (note: the global is usually synchronized at sequence points only). */ #ifdef ENABLE_JIT_TRANSLATION typedef int ip_type; extern char *native_ip; #else /* plain bytecode interpreter */ typedef gst_uchar *ip_type; #endif #define ip _gst_ip extern ip_type ip ATTRIBUTE_HIDDEN; typedef struct async_queue_entry { void (*func) (OOP); OOP data; struct async_queue_entry *next; } async_queue_entry; /* When not NULL, this causes the byte code interpreter to immediately send the message whose selector is here to the current stack top. */ extern const char *_gst_abort_execution ATTRIBUTE_HIDDEN; /* Set to true when some special action must be done at the next sequence point. */ #ifdef ENABLE_JIT_TRANSLATION extern mst_Boolean _gst_except_flag ATTRIBUTE_HIDDEN; #endif /* Create a new Process on the top of the stack, which is specially marked so that it stops the interpreter's execution. This kind of MethodContext is used to mark call-ins from C to Smalltalk and is the parent of the called-in method. Return the Process. */ extern OOP _gst_prepare_execution_environment (void) ATTRIBUTE_HIDDEN; /* Sends SELECTOR (which should be a Symbol, otherwise _gst_nil_oop is returned) to RECEIVER. The message arguments should also be OOPs (otherwise, an access violation exception is pretty likely) and are passed in an array ARGS of size NARGS. The value returned from the method is passed back as an OOP to the C program as the result of the function, or _gst_nil_oop if the number of arguments is wrong. */ extern OOP _gst_nvmsg_send (OOP receiver, OOP selector, OOP *args, int nArgs) ATTRIBUTE_HIDDEN; /* Start the interpreter, and go on until we terminate PROCESSOOP. */ extern OOP _gst_interpret (OOP processOOP) ATTRIBUTE_HIDDEN; /* Internal function for SEND_MESSAGE and for sends to super; send SENDSELECTOR, with SENDARGS arguments, to RECEIVER. Start looking for the method in METHOD_CLASS. On entry to this routine, the stack should have the receiver and the arguments pushed on the stack. We need to get a new context, setup things like the IP, SP, and Temporary pointers, and then return. Note that this routine DOES NOT invoke the interpreter; it merely sets up a new context so that calling (or, more typically, returning to) the interpreter will operate properly. This kind of sending is for normal messages only. Things like sending a "value" message to a block context are handled by primitives which do similar things, but they use information from gst_block_closure objects that we don't have available (nor need) here. */ extern void _gst_send_message_internal (OOP sendSelector, int sendArgs, OOP receiver, OOP method_class) ATTRIBUTE_HIDDEN; /* Prepare the data structures held by the interpreter. */ extern void _gst_init_interpreter (void) ATTRIBUTE_HIDDEN; /* Reset the fast allocator for context objects, telling it that all contexts living there have been tenured and thus the space can be reused. */ extern void _gst_empty_context_pool (void) ATTRIBUTE_HIDDEN; /* Return whether there are pending asynchronous calls. */ extern mst_Boolean _gst_have_pending_async_calls (void) ATTRIBUTE_HIDDEN; /* Set up so that FUNC will be called, with ARGOOP as its argument, as soon as the next sequence point is reached. */ extern void _gst_async_call (void (*func) (OOP), OOP argOOP) ATTRIBUTE_HIDDEN; /* Worker functions for _gst_async_call_internal. */; extern void _gst_do_async_signal (OOP semaphoreOOP) ATTRIBUTE_HIDDEN; extern void _gst_do_async_signal_and_unregister (OOP semaphoreOOP) ATTRIBUTE_HIDDEN; /* Set up so that ENTRY->FUNC will be called, with ENTRY->DATA as its argument, as soon as the next sequence point is reached. Async-signal safe version. */ extern void _gst_async_call_internal (async_queue_entry *entry) ATTRIBUTE_HIDDEN; /* Signal SEMAPHOREOOP so that one of the processes waiting on that semaphore is waken up. Since a Smalltalk call-in is not an atomic operation, the correct way to signal a semaphore is not to send #signal to the object but, rather, to use this function. The signal request will be processed as soon as the next sequence point is reached. */ extern void _gst_async_signal (OOP semaphoreOOP) ATTRIBUTE_HIDDEN; /* Signal SEMAPHOREOOP so that one of the processes waiting on that semaphore is waken up, and remove it from the registry. Since a Smalltalk call-in is not an atomic operation, the correct way to signal a semaphore is not to send #signal to the object but, rather, to use this function. The signal request will be processed as soon as the next sequence point is reached. */ extern void _gst_async_signal_and_unregister (OOP semaphoreOOP) ATTRIBUTE_HIDDEN; /* Invalidate all the cached CompiledMethod lookups. This does NOT include inline caches when the JIT compiler is active. */ extern void _gst_invalidate_method_cache (void) ATTRIBUTE_HIDDEN; /* Show a backtrace of the current state of the stack of execution contexts. */ extern void _gst_show_backtrace (FILE *) ATTRIBUTE_HIDDEN; /* Trap the signals that we care about, basically SIGBUS and SIGSEGV. */ extern void _gst_init_signals (void) ATTRIBUTE_HIDDEN; /* Store the context of the VM registers into the currently executing contexts. Since the contexts store relative addresses, these are valid across GCs and we can count on them and on the OOPs (which do not move) to adjust the interior pointers that the VM uses. Note that normally fields such as SP or IP are not valid for the currently executing contexts (they are only used after a message send) so we need a special function to ensure that even that context has the information saved in it. */ extern void _gst_fixup_object_pointers (void) ATTRIBUTE_HIDDEN; /* Complementary to _gst_fixup_object_pointers, this function picks the relative addresses stored in the current context and uses them to adjust the VM registers after the heap is compacted or grown. */ extern void _gst_restore_object_pointers (void) ATTRIBUTE_HIDDEN; /* This runs before every evaluation and before GC turned on. It creates an initial process if no process is ready to run or if no process has been created yet. */ extern void _gst_init_process_system (void) ATTRIBUTE_HIDDEN; /* These function mark or copy all the objects that the interpreter keeps in the root set. These are the semaphores that are held to be signaled by an asynchronous event (note that they *are* in the root set because they could be the only way from which we can get to the suspended process!), the semaphores that are queued to be signaled at the next sequence point (_gst_async_signals queues them) and the currently executing context. Everything else is supposedly reachable from the current context (including the current method, the receiver, the receiver class even if it does not live in a namespace, and all the context on the execution stack) or from Processor (including the current process and the other active processes). Processor itself is reachable from the Smalltalk dictionary. */ extern void _gst_mark_processor_registers (void) ATTRIBUTE_HIDDEN; extern void _gst_copy_processor_registers (void) ATTRIBUTE_HIDDEN; /* Print the current state of the lists of ready to run processes for each priority, for debugging purposes. */ extern void _gst_print_process_state (void) ATTRIBUTE_HIDDEN; /* Sanity check the process lists that the sole instance of ProcessorScheduler holds. */ extern void _gst_check_process_state (void) ATTRIBUTE_HIDDEN; /* Print the objects currently on the stack, for debugging purposes. */ extern void _gst_show_stack_contents (void) ATTRIBUTE_HIDDEN; /* Called after the mark phase, but before the sweep phase, so that if a method cache entry is not valid anymore it is cleared. This is because in the JIT case a method cache entry is invalidated not only if the related method does not exist anymore (and this is done by the Smalltalk implementation of the MethodDictionary class) but also if the translation to native code for the method is garbage collected. In particular, this function is called *after* the unused method translations are marked as such, and *before* they are actually freed. */ extern void _gst_validate_method_cache_entries (void) ATTRIBUTE_HIDDEN; /* Terminate execution of the given PROCESSOOP. */ extern void _gst_terminate_process (OOP processOOP) ATTRIBUTE_HIDDEN; /* This is a further simplified lookup_method which does not care about preparing for #doesNotUnderstand:. */ extern mst_Boolean _gst_find_method (OOP classOOP, OOP sendSelector, method_cache_entry *mce) ATTRIBUTE_HIDDEN; /* Similar to _gst_send_message_internal, but forces the specified CompiledMethod to be sent. If it is not valid for the current receiver, well, you are looking for trouble and well deserve it. The number of arguments is looked in METHODOOP. */ extern void _gst_send_method (OOP methodOOP) ATTRIBUTE_HIDDEN; /* This functions accepts an OOP for a Semaphore object and puts the current process to sleep, unless the semaphore has excess signals on it. Since a Smalltalk call-in is not an atomic operation, the correct way to signal a semaphore is not to send the wait method to the object but, rather, to use _gst_sync_wait. The `sync' in the name of this function distinguishes it from _gst_async_signal, in that it cannot be called from within a signal handler. */ extern void _gst_sync_wait (OOP semaphoreOOP) ATTRIBUTE_HIDDEN; /* Signal the given SEMAPHOREOOP and if processes were queued on it resume the one that has waited for the longest time and is still alive. If INCR is true, increment its value if no processes were queued. Return true if a process was woken. This functions also cannot be called from within a signal handler. It can be called from a function that is registered with _gst_async_call, though. */ extern mst_Boolean _gst_sync_signal (OOP semaphoreOOP, mst_Boolean incr_if_empty) ATTRIBUTE_HIDDEN; /* Take a CompiledBlock and turn it into a BlockClosure that references thisContext as its static link. */ extern OOP _gst_make_block_closure (OOP blockOOP) ATTRIBUTE_HIDDEN; /************************************************* PRIMITIVES ****************/ /* The type for a routine providing the definition for one or more primitive methods in the GNU Smalltalk system. They normally remove the arguments to the primitive methods from the stack, but if the primitive fails, the arguments are put back onto the stack and the routine returns true (-1 for the JIT), indicating failure to invoke the primitive. Such a function must execute a primitive, aided in the choice of which by the user-defined parameter ID, popping NUMARGS methods off the stack if they succeed. */ typedef intptr_t (*primitive_func) (int primitive, volatile int numArgs); /* Table of primitives, including a primitive and its attributes. */ typedef struct prim_table_entry { const char *name; primitive_func func; int attributes; int id; } prim_table_entry; #define PRIM_SUCCEED 0x0001 #define PRIM_FAIL 0x0002 #define PRIM_RELOAD_IP 0x0004 #define PRIM_OUTCOMES 0x0007 #define PRIM_CACHE_NEW_IP 0x0008 #define PRIM_INLINED 0x0010 #define PRIM_CHECK_INTERRUPT 0x0020 #define PRIM_RETURN_SMALL_INTEGER 0x0100 /* 31 or 63 bits */ #define PRIM_RETURN_SMALL_SMALLINTEGER 0x0300 /* 30 or 62 bits */ /* The checksum of the table of primitive numbers. Right now it is an MD5, computed from part of the C source code of prims.inl. We compare it when loading an image, to avoid having to reload the primitive table. */ extern unsigned char _gst_primitives_md5[16]; /* The table of functions that implement the primitives. */ extern prim_table_entry _gst_primitive_table[NUM_PRIMITIVES]; extern prim_table_entry _gst_default_primitive_table[NUM_PRIMITIVES]; /* This can be used to obtain information on a particular primitive operations in the GNU Smalltalk system. */ extern prim_table_entry * _gst_get_primitive_attributes (int primitive) ATTRIBUTE_PURE ATTRIBUTE_HIDDEN; /* Dually, this maps the primitive number that will be used for running the image, to the entry which was returned by _gst_get_primitive_attributes. If PTE is NULL, the primitive will be invalid. */ extern void _gst_set_primitive_attributes (int primitive, prim_table_entry *pte) ATTRIBUTE_HIDDEN; /* Initialize the table of primitives. */ extern void _gst_init_primitives () ATTRIBUTE_HIDDEN; /* Get the value of internal variable whose number is INDEX; the list of valid variables is in gstpub.h. Return -1 if the index is invalid. */ extern int _gst_get_var (enum gst_var_index index) ATTRIBUTE_HIDDEN; /* Set the value of internal variable whose number is INDEX; the list of valid variables is in gstpub.h. Return -1 if the index is invalid or the value is negative, otherwise return the previous value. */ extern int _gst_set_var (enum gst_var_index index, int value) ATTRIBUTE_HIDDEN; #endif /* GST_INTERP_H */ smalltalk-3.2.5/libgst/Makefile.in0000644000175000017500000010202212130455425013755 00000000000000# Makefile.in generated by automake 1.11.6 from Makefile.am. # @configure_input@ # Copyright (C) 1994, 1995, 1996, 1997, 1998, 1999, 2000, 2001, 2002, # 2003, 2004, 2005, 2006, 2007, 2008, 2009, 2010, 2011 Free Software # Foundation, Inc. # This Makefile.in is free software; the Free Software Foundation # gives unlimited permission to copy and/or distribute it, # with or without modifications, as long as this notice is preserved. # This program is distributed in the hope that it will be useful, # but WITHOUT ANY WARRANTY, to the extent permitted by law; without # even the implied warranty of MERCHANTABILITY or FITNESS FOR A # PARTICULAR PURPOSE. @SET_MAKE@ VPATH = @srcdir@ am__make_dryrun = \ { \ am__dry=no; \ case $$MAKEFLAGS in \ *\\[\ \ ]*) \ echo 'am--echo: ; @echo "AM" OK' | $(MAKE) -f - 2>/dev/null \ | grep '^AM OK$$' >/dev/null || am__dry=yes;; \ *) \ for am__flg in $$MAKEFLAGS; do \ case $$am__flg in \ *=*|--*) ;; \ *n*) am__dry=yes; break;; \ esac; \ done;; \ esac; \ test $$am__dry = yes; \ } pkgdatadir = $(datadir)/@PACKAGE@ pkgincludedir = $(includedir)/@PACKAGE@ pkglibdir = $(libdir)/@PACKAGE@ pkglibexecdir = $(libexecdir)/@PACKAGE@ am__cd = CDPATH="$${ZSH_VERSION+.}$(PATH_SEPARATOR)" && cd install_sh_DATA = $(install_sh) -c -m 644 install_sh_PROGRAM = $(install_sh) -c install_sh_SCRIPT = $(install_sh) -c INSTALL_HEADER = $(INSTALL_DATA) transform = $(program_transform_name) NORMAL_INSTALL = : PRE_INSTALL = : POST_INSTALL = : NORMAL_UNINSTALL = : PRE_UNINSTALL = : POST_UNINSTALL = : build_triplet = @build@ host_triplet = @host@ @HAVE_INSTALLED_LIGHTNING_FALSE@am__append_1 = -I$(top_srcdir)/lightning -I$(top_builddir)/lightning \ @HAVE_INSTALLED_LIGHTNING_FALSE@ -I$(top_srcdir) -I$(top_builddir) EXTRA_PROGRAMS = genprims$(EXEEXT) genbc$(EXEEXT) genvm$(EXEEXT) subdir = libgst DIST_COMMON = $(dist_noinst_DATA) $(include_HEADERS) $(noinst_HEADERS) \ $(srcdir)/Makefile.am $(srcdir)/Makefile.in ChangeLog \ genbc-decl.c genbc-impl.c genbc-scan.c genpr-parse.c \ genpr-scan.c genvm-parse.c genvm-scan.c ACLOCAL_M4 = $(top_srcdir)/aclocal.m4 am__aclocal_m4_deps = $(top_srcdir)/build-aux/bold.m4 \ $(top_srcdir)/build-aux/codeset.m4 \ $(top_srcdir)/build-aux/emacs-pkg.m4 \ $(top_srcdir)/build-aux/emacs-site-start.m4 \ $(top_srcdir)/build-aux/ext_goto.m4 \ $(top_srcdir)/build-aux/gawk.m4 $(top_srcdir)/build-aux/gcc.m4 \ $(top_srcdir)/build-aux/gl.m4 \ $(top_srcdir)/build-aux/glib-2.0.m4 \ $(top_srcdir)/build-aux/glut.m4 $(top_srcdir)/build-aux/gmp.m4 \ $(top_srcdir)/build-aux/gst-package.m4 \ $(top_srcdir)/build-aux/gtk-2.0.m4 \ $(top_srcdir)/build-aux/iconv.m4 \ $(top_srcdir)/build-aux/lib-ld.m4 \ $(top_srcdir)/build-aux/lib-link.m4 \ $(top_srcdir)/build-aux/lib-prefix.m4 \ $(top_srcdir)/build-aux/lib.m4 \ $(top_srcdir)/build-aux/libc-so-name.m4 \ $(top_srcdir)/build-aux/libtool.m4 \ $(top_srcdir)/build-aux/lightning.m4 \ $(top_srcdir)/build-aux/ln.m4 \ $(top_srcdir)/build-aux/localtime.m4 \ $(top_srcdir)/build-aux/lock.m4 \ $(top_srcdir)/build-aux/long-double.m4 \ $(top_srcdir)/build-aux/lrint.m4 \ $(top_srcdir)/build-aux/ltdl-gst.m4 \ $(top_srcdir)/build-aux/ltoptions.m4 \ $(top_srcdir)/build-aux/ltsugar.m4 \ $(top_srcdir)/build-aux/ltversion.m4 \ $(top_srcdir)/build-aux/lt~obsolete.m4 \ $(top_srcdir)/build-aux/modules.m4 \ $(top_srcdir)/build-aux/pkg.m4 $(top_srcdir)/build-aux/poll.m4 \ $(top_srcdir)/build-aux/readline.m4 \ $(top_srcdir)/build-aux/relocatable.m4 \ $(top_srcdir)/build-aux/setenv.m4 \ $(top_srcdir)/build-aux/snprintfv.m4 \ $(top_srcdir)/build-aux/sockets.m4 \ $(top_srcdir)/build-aux/sockpfaf.m4 \ $(top_srcdir)/build-aux/strtoul.m4 \ $(top_srcdir)/build-aux/sync-builtins.m4 \ $(top_srcdir)/build-aux/tcltk.m4 \ $(top_srcdir)/build-aux/version.m4 \ $(top_srcdir)/build-aux/vis-hidden.m4 \ $(top_srcdir)/build-aux/wine.m4 $(top_srcdir)/configure.ac am__configure_deps = $(am__aclocal_m4_deps) $(CONFIGURE_DEPENDENCIES) \ $(ACLOCAL_M4) mkinstalldirs = $(install_sh) -d CONFIG_HEADER = $(top_builddir)/config.h CONFIG_CLEAN_FILES = CONFIG_CLEAN_VPATH_FILES = am__vpath_adj_setup = srcdirstrip=`echo "$(srcdir)" | sed 's|.|.|g'`; am__vpath_adj = case $$p in \ $(srcdir)/*) f=`echo "$$p" | sed "s|^$$srcdirstrip/||"`;; \ *) f=$$p;; \ esac; am__strip_dir = f=`echo $$p | sed -e 's|^.*/||'`; am__install_max = 40 am__nobase_strip_setup = \ srcdirstrip=`echo "$(srcdir)" | sed 's/[].[^$$\\*|]/\\\\&/g'` am__nobase_strip = \ for p in $$list; do echo "$$p"; done | sed -e "s|$$srcdirstrip/||" am__nobase_list = $(am__nobase_strip_setup); \ for p in $$list; do echo "$$p $$p"; done | \ sed "s| $$srcdirstrip/| |;"' / .*\//!s/ .*/ ./; s,\( .*\)/[^/]*$$,\1,' | \ $(AWK) 'BEGIN { files["."] = "" } { files[$$2] = files[$$2] " " $$1; \ if (++n[$$2] == $(am__install_max)) \ { print $$2, files[$$2]; n[$$2] = 0; files[$$2] = "" } } \ END { for (dir in files) print dir, files[dir] }' am__base_list = \ sed '$$!N;$$!N;$$!N;$$!N;$$!N;$$!N;$$!N;s/\n/ /g' | \ sed '$$!N;$$!N;$$!N;$$!N;s/\n/ /g' am__uninstall_files_from_dir = { \ test -z "$$files" \ || { test ! -d "$$dir" && test ! -f "$$dir" && test ! -r "$$dir"; } \ || { echo " ( cd '$$dir' && rm -f" $$files ")"; \ $(am__cd) "$$dir" && rm -f $$files; }; \ } am__installdirs = "$(DESTDIR)$(libdir)" "$(DESTDIR)$(includedir)" LTLIBRARIES = $(lib_LTLIBRARIES) am__DEPENDENCIES_1 = am_libgst_la_OBJECTS = gstpub.lo files.lo gst-parse.lo lex.lo str.lo \ tree.lo byte.lo comp.lo sym.lo dict.lo oop.lo opt.lo save.lo \ cint.lo heap.lo input.lo sysdep.lo callin.lo xlat.lo mpz.lo \ print.lo alloc.lo security.lo re.lo interp.lo real.lo \ sockets.lo events.lo libgst_la_OBJECTS = $(am_libgst_la_OBJECTS) libgst_la_LINK = $(LIBTOOL) --tag=CC $(AM_LIBTOOLFLAGS) \ $(LIBTOOLFLAGS) --mode=link $(CCLD) $(AM_CFLAGS) $(CFLAGS) \ $(libgst_la_LDFLAGS) $(LDFLAGS) -o $@ am_genbc_OBJECTS = genbc-decl.$(OBJEXT) genbc-impl.$(OBJEXT) \ genbc-scan.$(OBJEXT) genbc.$(OBJEXT) genbc_OBJECTS = $(am_genbc_OBJECTS) genbc_DEPENDENCIES = $(top_builddir)/lib-src/library.la am_genprims_OBJECTS = genpr-parse.$(OBJEXT) genpr-scan.$(OBJEXT) genprims_OBJECTS = $(am_genprims_OBJECTS) genprims_DEPENDENCIES = $(top_builddir)/lib-src/library.la am_genvm_OBJECTS = genvm-parse.$(OBJEXT) genvm-scan.$(OBJEXT) genvm_OBJECTS = $(am_genvm_OBJECTS) genvm_DEPENDENCIES = $(top_builddir)/lib-src/library.la DEFAULT_INCLUDES = -I.@am__isrc@ -I$(top_builddir) depcomp = $(SHELL) $(top_srcdir)/build-aux/depcomp am__depfiles_maybe = depfiles am__mv = mv -f COMPILE = $(CC) $(DEFS) $(DEFAULT_INCLUDES) $(INCLUDES) $(AM_CPPFLAGS) \ $(CPPFLAGS) $(AM_CFLAGS) $(CFLAGS) LTCOMPILE = $(LIBTOOL) --tag=CC $(AM_LIBTOOLFLAGS) $(LIBTOOLFLAGS) \ --mode=compile $(CC) $(DEFS) $(DEFAULT_INCLUDES) $(INCLUDES) \ $(AM_CPPFLAGS) $(CPPFLAGS) $(AM_CFLAGS) $(CFLAGS) CCLD = $(CC) LINK = $(LIBTOOL) --tag=CC $(AM_LIBTOOLFLAGS) $(LIBTOOLFLAGS) \ --mode=link $(CCLD) $(AM_CFLAGS) $(CFLAGS) $(AM_LDFLAGS) \ $(LDFLAGS) -o $@ LEXCOMPILE = $(LEX) $(AM_LFLAGS) $(LFLAGS) LTLEXCOMPILE = $(LIBTOOL) $(AM_LIBTOOLFLAGS) $(LIBTOOLFLAGS) \ --mode=compile $(LEX) $(AM_LFLAGS) $(LFLAGS) YLWRAP = $(top_srcdir)/build-aux/ylwrap YACCCOMPILE = $(YACC) $(AM_YFLAGS) $(YFLAGS) LTYACCCOMPILE = $(LIBTOOL) $(AM_LIBTOOLFLAGS) $(LIBTOOLFLAGS) \ --mode=compile $(YACC) $(AM_YFLAGS) $(YFLAGS) SOURCES = $(libgst_la_SOURCES) $(genbc_SOURCES) $(genprims_SOURCES) \ $(genvm_SOURCES) DIST_SOURCES = $(libgst_la_SOURCES) $(genbc_SOURCES) \ $(genprims_SOURCES) $(genvm_SOURCES) am__can_run_installinfo = \ case $$AM_UPDATE_INFO_DIR in \ n|no|NO) false;; \ *) (install-info --version) >/dev/null 2>&1;; \ esac DATA = $(dist_noinst_DATA) HEADERS = $(include_HEADERS) $(noinst_HEADERS) ETAGS = etags CTAGS = ctags DISTFILES = $(DIST_COMMON) $(DIST_SOURCES) $(TEXINFOS) $(EXTRA_DIST) ACLOCAL = @ACLOCAL@ ALLOCA = @ALLOCA@ ALL_PACKAGES = @ALL_PACKAGES@ AMTAR = @AMTAR@ AR = @AR@ AS = @AS@ ATK_CFLAGS = @ATK_CFLAGS@ ATK_LIBS = @ATK_LIBS@ AUTOCONF = @AUTOCONF@ AUTOHEADER = @AUTOHEADER@ AUTOM4TE = @AUTOM4TE@ AUTOMAKE = @AUTOMAKE@ AWK = @AWK@ BLOX_IMPLEMENTATION = @BLOX_IMPLEMENTATION@ BUILT_PACKAGES = @BUILT_PACKAGES@ CAIRO_CFLAGS = @CAIRO_CFLAGS@ CAIRO_LIBS = @CAIRO_LIBS@ CC = @CC@ CCDEPMODE = @CCDEPMODE@ CFLAGS = @CFLAGS@ CPP = @CPP@ CPPFLAGS = @CPPFLAGS@ CYGPATH_W = @CYGPATH_W@ DEFS = @DEFS@ DEPDIR = @DEPDIR@ DLLTOOL = @DLLTOOL@ DSYMUTIL = @DSYMUTIL@ DUMPBIN = @DUMPBIN@ ECHO_C = @ECHO_C@ ECHO_N = @ECHO_N@ ECHO_T = @ECHO_T@ EGREP = @EGREP@ EMACS = @EMACS@ EMACSLOADPATH = @EMACSLOADPATH@ EXEEXT = @EXEEXT@ FGREP = @FGREP@ GLIB_CFLAGS = @GLIB_CFLAGS@ GLIB_GENMARSHAL = @GLIB_GENMARSHAL@ GLIB_LIBS = @GLIB_LIBS@ GLIB_MKENUMS = @GLIB_MKENUMS@ GNUTLS_CFLAGS = @GNUTLS_CFLAGS@ GNUTLS_LIBS = @GNUTLS_LIBS@ GOBJECT_QUERY = @GOBJECT_QUERY@ GPERF = @GPERF@ GREP = @GREP@ GST_RUN = @GST_RUN@ GTHREAD_CFLAGS = @GTHREAD_CFLAGS@ GTHREAD_LIBS = @GTHREAD_LIBS@ GTK_CFLAGS = @GTK_CFLAGS@ GTK_LIBS = @GTK_LIBS@ ICON = @ICON@ INCFFI = @INCFFI@ INCLTDL = @INCLTDL@ INCSIGSEGV = @INCSIGSEGV@ INCSNPRINTFV = @INCSNPRINTFV@ INCTCLTK = @INCTCLTK@ INSTALL = @INSTALL@ INSTALL_DATA = @INSTALL_DATA@ INSTALL_INFO = @INSTALL_INFO@ INSTALL_PROGRAM = @INSTALL_PROGRAM@ INSTALL_SCRIPT = @INSTALL_SCRIPT@ INSTALL_STRIP_PROGRAM = @INSTALL_STRIP_PROGRAM@ LD = @LD@ LDFLAGS = @LDFLAGS@ LEX = @LEX@ LIBADD_DL = @LIBADD_DL@ LIBC_SO_DIR = @LIBC_SO_DIR@ LIBC_SO_NAME = @LIBC_SO_NAME@ LIBFFI = @LIBFFI@ LIBFFI_CFLAGS = @LIBFFI_CFLAGS@ LIBFFI_EXECUTABLE_LDFLAGS = @LIBFFI_EXECUTABLE_LDFLAGS@ LIBFFI_LIBS = @LIBFFI_LIBS@ LIBGLUT = @LIBGLUT@ LIBGMP = @LIBGMP@ LIBGST_CFLAGS = @LIBGST_CFLAGS@ LIBICONV = @LIBICONV@ LIBLTDL = @LIBLTDL@ LIBOBJS = @LIBOBJS@ LIBOPENGL = @LIBOPENGL@ LIBREADLINE = @LIBREADLINE@ LIBS = @LIBS@ LIBSIGSEGV = @LIBSIGSEGV@ LIBSNPRINTFV = @LIBSNPRINTFV@ LIBTCLTK = @LIBTCLTK@ LIBTHREAD = @LIBTHREAD@ LIBTOOL = @LIBTOOL@ LIPO = @LIPO@ LN = @LN@ LN_S = @LN_S@ LTALLOCA = @LTALLOCA@ LTLIBICONV = @LTLIBICONV@ LTLIBOBJS = @LTLIBOBJS@ MAINTAINER = @MAINTAINER@ MAKEINFO = @MAKEINFO@ MANIFEST_TOOL = @MANIFEST_TOOL@ MKDIR_P = @MKDIR_P@ MODULES = @MODULES@ NM = @NM@ NMEDIT = @NMEDIT@ OBJC = @OBJC@ OBJCDEPMODE = @OBJCDEPMODE@ OBJCFLAGS = @OBJCFLAGS@ OBJDUMP = @OBJDUMP@ OBJEXT = @OBJEXT@ OTOOL = @OTOOL@ OTOOL64 = @OTOOL64@ PACKAGE = @PACKAGE@ PACKAGE_BUGREPORT = @PACKAGE_BUGREPORT@ PACKAGE_DLOPEN_FLAGS = @PACKAGE_DLOPEN_FLAGS@ PACKAGE_NAME = @PACKAGE_NAME@ PACKAGE_STRING = @PACKAGE_STRING@ PACKAGE_TARNAME = @PACKAGE_TARNAME@ PACKAGE_URL = @PACKAGE_URL@ PACKAGE_VERSION = @PACKAGE_VERSION@ PANGO_CFLAGS = @PANGO_CFLAGS@ PANGO_LIBS = @PANGO_LIBS@ PATH_SEPARATOR = @PATH_SEPARATOR@ PKG_CONFIG = @PKG_CONFIG@ RANLIB = @RANLIB@ RELOCATABLE = @RELOCATABLE@ RELOC_CPPFLAGS = @RELOC_CPPFLAGS@ RELOC_LDFLAGS = @RELOC_LDFLAGS@ SDL_CFLAGS = @SDL_CFLAGS@ SDL_LIBS = @SDL_LIBS@ SED = @SED@ SET_MAKE = @SET_MAKE@ SHELL = @SHELL@ SOCKET_LIBS = @SOCKET_LIBS@ STRIP = @STRIP@ SYNC_CFLAGS = @SYNC_CFLAGS@ TCLSH = @TCLSH@ TIMEOUT = @TIMEOUT@ VERSION = @VERSION@ VERSION_INFO = @VERSION_INFO@ WINDRES = @WINDRES@ WINEWRAPPER = @WINEWRAPPER@ WINEWRAPPERDEP = @WINEWRAPPERDEP@ XMKMF = @XMKMF@ XZIP = @XZIP@ X_CFLAGS = @X_CFLAGS@ X_EXTRA_LIBS = @X_EXTRA_LIBS@ X_LIBS = @X_LIBS@ X_PRE_LIBS = @X_PRE_LIBS@ YACC = @YACC@ ZIP = @ZIP@ abs_builddir = @abs_builddir@ abs_srcdir = @abs_srcdir@ abs_top_builddir = @abs_top_builddir@ abs_top_srcdir = @abs_top_srcdir@ ac_ct_AR = @ac_ct_AR@ ac_ct_CC = @ac_ct_CC@ ac_ct_DUMPBIN = @ac_ct_DUMPBIN@ am__include = @am__include@ am__leading_dot = @am__leading_dot@ am__quote = @am__quote@ am__tar = @am__tar@ am__untar = @am__untar@ bindir = @bindir@ build = @build@ build_alias = @build_alias@ build_cpu = @build_cpu@ build_os = @build_os@ build_vendor = @build_vendor@ builddir = @builddir@ datadir = @datadir@ datarootdir = @datarootdir@ docdir = @docdir@ dvidir = @dvidir@ enable_mysql_tests = @enable_mysql_tests@ exec_prefix = @exec_prefix@ host = @host@ host_alias = @host_alias@ host_cpu = @host_cpu@ host_os = @host_os@ host_vendor = @host_vendor@ htmldir = @htmldir@ imagedir = @imagedir@ includedir = @includedir@ infodir = @infodir@ install_sh = @install_sh@ libdir = @libdir@ libexecdir = @libexecdir@ lispdir = @lispdir@ lispstartdir = @lispstartdir@ localedir = @localedir@ localstatedir = @localstatedir@ mandir = @mandir@ mkdir_p = @mkdir_p@ moduledir = @moduledir@ moduleexecdir = @moduleexecdir@ oldincludedir = @oldincludedir@ pdfdir = @pdfdir@ prefix = @prefix@ program_transform_name = @program_transform_name@ psdir = @psdir@ sbindir = @sbindir@ sharedstatedir = @sharedstatedir@ srcdir = @srcdir@ subdirs = @subdirs@ sysconfdir = @sysconfdir@ target_alias = @target_alias@ top_build_prefix = @top_build_prefix@ top_builddir = @top_builddir@ top_srcdir = @top_srcdir@ LEX_OUTPUT_ROOT = lex.yy AM_CFLAGS = $(LIBGST_CFLAGS) AM_LFLAGS = -Cfe -o$(LEX_OUTPUT_ROOT).c AM_YFLAGS = -vy AM_CPPFLAGS = $(RELOC_CPPFLAGS) -I$(top_srcdir)/lib-src \ -I$(top_builddir)/lib-src $(INCFFI) $(INCLIGHTNING) \ $(INCSNPRINTFV) $(INCSIGSEGV) $(INCLTDL) $(am__append_1) include_HEADERS = gstpub.h gst.h lib_LTLIBRARIES = libgst.la CLEANFILES = genprims$(EXEEXT) genbc$(EXEEXT) genvm$(EXEEXT) \ genbc-decl.stamp genbc-impl.stamp genpr-parse.stamp genvm-parse.stamp # definitions for libgst.la libgst_la_LIBADD = $(top_builddir)/lib-src/library.la \ $(LIBSIGSEGV) $(LIBFFI) $(LIBSNPRINTFV) $(LIBREADLINE) $(LIBLTDL) \ $(LIBGMP) $(LIBTHREAD) libgst_la_DEPENDENCIES = $(top_builddir)/lib-src/library.la $(LIBSNPRINTFV) libgst_la_LDFLAGS = -version-info $(VERSION_INFO) -no-undefined \ -export-symbols-regex "^gst_.*" -bindir $(bindir) libgst_la_SOURCES = \ gstpub.c files.c gst-parse.c lex.c \ str.c tree.c byte.c comp.c \ sym.c dict.c oop.c opt.c \ save.c cint.c heap.c input.c \ sysdep.c callin.c xlat.c mpz.c \ print.c alloc.c security.c re.c \ interp.c real.c sockets.c events.c # definitions for genprims genprims_SOURCES = \ genpr-parse.y genpr-scan.l genprims_LDADD = @LIBSNPRINTFV@ $(top_builddir)/lib-src/library.la # definitions for genbc genbc_SOURCES = \ genbc-decl.y genbc-impl.y genbc-scan.l genbc.c genbc_LDADD = @LIBSNPRINTFV@ $(top_builddir)/lib-src/library.la # definitions for genvm genvm_SOURCES = \ genvm-parse.y genvm-scan.l genvm_LDADD = @LIBSNPRINTFV@ $(top_builddir)/lib-src/library.la BUILT_SOURCES = prims.inl match.h builtins.inl vm.inl \ genbc-decl.c genbc-impl.c genbc-scan.c genbc-decl.h genbc-impl.h \ genpr-parse.c genpr-scan.c genpr-parse.h \ genvm-parse.c genvm-scan.c genvm-parse.h dist_noinst_DATA = valgrind.supp prims.def byte.def vm.def builtins.gperf STAMP_FILES = prims.stamp match.stamp vm.stamp noinst_HEADERS = \ gstpriv.h files.h lex.h str.h re.h \ tree.h byte.h interp.h comp.h \ sym.h dict.h oop.h save.h cint.h xlat.h \ sysdep.h callin.h gstpub.h opt.h mpz.h \ md-config.h heap.h real.h jitpriv.h oop.inl \ dict.inl interp.inl interp-bc.inl interp-jit.inl \ sockets.h comp.inl input.h events.h \ print.h alloc.h genprims.h gst-parse.h \ genpr-parse.h genbc.h genbc-decl.h \ genbc-impl.h genvm-parse.h genvm.h \ security.h superop1.inl superop2.inl \ sysdep/common/files.c sysdep/common/time.c sysdep/cygwin/files.c \ sysdep/cygwin/findexec.c sysdep/cygwin/mem.c sysdep/cygwin/signals.c \ sysdep/cygwin/time.c sysdep/cygwin/timer.c sysdep/posix/files.c \ sysdep/posix/findexec.c sysdep/posix/mem.c sysdep/posix/signals.c \ sysdep/posix/time.c sysdep/posix/timer.c sysdep/win32/files.c \ sysdep/win32/findexec.c sysdep/win32/mem.c sysdep/win32/signals.c \ sysdep/win32/time.c sysdep/win32/timer.c sysdep/posix/events.c \ sysdep/win32/events.c sysdep/cygwin/events.c \ $(BUILT_SOURCES) all: $(BUILT_SOURCES) $(MAKE) $(AM_MAKEFLAGS) all-am .SUFFIXES: .SUFFIXES: .c .l .lo .o .obj .y $(srcdir)/Makefile.in: $(srcdir)/Makefile.am $(am__configure_deps) @for dep in $?; do \ case '$(am__configure_deps)' in \ *$$dep*) \ ( cd $(top_builddir) && $(MAKE) $(AM_MAKEFLAGS) am--refresh ) \ && { if test -f $@; then exit 0; else break; fi; }; \ exit 1;; \ esac; \ done; \ echo ' cd $(top_srcdir) && $(AUTOMAKE) --gnu libgst/Makefile'; \ $(am__cd) $(top_srcdir) && \ $(AUTOMAKE) --gnu libgst/Makefile .PRECIOUS: Makefile Makefile: $(srcdir)/Makefile.in $(top_builddir)/config.status @case '$?' in \ *config.status*) \ cd $(top_builddir) && $(MAKE) $(AM_MAKEFLAGS) am--refresh;; \ *) \ echo ' cd $(top_builddir) && $(SHELL) ./config.status $(subdir)/$@ $(am__depfiles_maybe)'; \ cd $(top_builddir) && $(SHELL) ./config.status $(subdir)/$@ $(am__depfiles_maybe);; \ esac; $(top_builddir)/config.status: $(top_srcdir)/configure $(CONFIG_STATUS_DEPENDENCIES) cd $(top_builddir) && $(MAKE) $(AM_MAKEFLAGS) am--refresh $(top_srcdir)/configure: $(am__configure_deps) cd $(top_builddir) && $(MAKE) $(AM_MAKEFLAGS) am--refresh $(ACLOCAL_M4): $(am__aclocal_m4_deps) cd $(top_builddir) && $(MAKE) $(AM_MAKEFLAGS) am--refresh $(am__aclocal_m4_deps): install-libLTLIBRARIES: $(lib_LTLIBRARIES) @$(NORMAL_INSTALL) @list='$(lib_LTLIBRARIES)'; test -n "$(libdir)" || list=; \ list2=; for p in $$list; do \ if test -f $$p; then \ list2="$$list2 $$p"; \ else :; fi; \ done; \ test -z "$$list2" || { \ echo " $(MKDIR_P) '$(DESTDIR)$(libdir)'"; \ $(MKDIR_P) "$(DESTDIR)$(libdir)" || exit 1; \ echo " $(LIBTOOL) $(AM_LIBTOOLFLAGS) $(LIBTOOLFLAGS) --mode=install $(INSTALL) $(INSTALL_STRIP_FLAG) $$list2 '$(DESTDIR)$(libdir)'"; \ $(LIBTOOL) $(AM_LIBTOOLFLAGS) $(LIBTOOLFLAGS) --mode=install $(INSTALL) $(INSTALL_STRIP_FLAG) $$list2 "$(DESTDIR)$(libdir)"; \ } uninstall-libLTLIBRARIES: @$(NORMAL_UNINSTALL) @list='$(lib_LTLIBRARIES)'; test -n "$(libdir)" || list=; \ for p in $$list; do \ $(am__strip_dir) \ echo " $(LIBTOOL) $(AM_LIBTOOLFLAGS) $(LIBTOOLFLAGS) --mode=uninstall rm -f '$(DESTDIR)$(libdir)/$$f'"; \ $(LIBTOOL) $(AM_LIBTOOLFLAGS) $(LIBTOOLFLAGS) --mode=uninstall rm -f "$(DESTDIR)$(libdir)/$$f"; \ done clean-libLTLIBRARIES: -test -z "$(lib_LTLIBRARIES)" || rm -f $(lib_LTLIBRARIES) @list='$(lib_LTLIBRARIES)'; for p in $$list; do \ dir="`echo $$p | sed -e 's|/[^/]*$$||'`"; \ test "$$dir" != "$$p" || dir=.; \ echo "rm -f \"$${dir}/so_locations\""; \ rm -f "$${dir}/so_locations"; \ done libgst.la: $(libgst_la_OBJECTS) $(libgst_la_DEPENDENCIES) $(EXTRA_libgst_la_DEPENDENCIES) $(libgst_la_LINK) -rpath $(libdir) $(libgst_la_OBJECTS) $(libgst_la_LIBADD) $(LIBS) genbc$(EXEEXT): $(genbc_OBJECTS) $(genbc_DEPENDENCIES) $(EXTRA_genbc_DEPENDENCIES) @rm -f genbc$(EXEEXT) $(LINK) $(genbc_OBJECTS) $(genbc_LDADD) $(LIBS) genprims$(EXEEXT): $(genprims_OBJECTS) $(genprims_DEPENDENCIES) $(EXTRA_genprims_DEPENDENCIES) @rm -f genprims$(EXEEXT) $(LINK) $(genprims_OBJECTS) $(genprims_LDADD) $(LIBS) genvm$(EXEEXT): $(genvm_OBJECTS) $(genvm_DEPENDENCIES) $(EXTRA_genvm_DEPENDENCIES) @rm -f genvm$(EXEEXT) $(LINK) $(genvm_OBJECTS) $(genvm_LDADD) $(LIBS) mostlyclean-compile: -rm -f *.$(OBJEXT) distclean-compile: -rm -f *.tab.c @AMDEP_TRUE@@am__include@ @am__quote@./$(DEPDIR)/alloc.Plo@am__quote@ @AMDEP_TRUE@@am__include@ @am__quote@./$(DEPDIR)/byte.Plo@am__quote@ @AMDEP_TRUE@@am__include@ @am__quote@./$(DEPDIR)/callin.Plo@am__quote@ @AMDEP_TRUE@@am__include@ @am__quote@./$(DEPDIR)/cint.Plo@am__quote@ @AMDEP_TRUE@@am__include@ @am__quote@./$(DEPDIR)/comp.Plo@am__quote@ @AMDEP_TRUE@@am__include@ @am__quote@./$(DEPDIR)/dict.Plo@am__quote@ @AMDEP_TRUE@@am__include@ @am__quote@./$(DEPDIR)/events.Plo@am__quote@ @AMDEP_TRUE@@am__include@ @am__quote@./$(DEPDIR)/files.Plo@am__quote@ @AMDEP_TRUE@@am__include@ @am__quote@./$(DEPDIR)/genbc-decl.Po@am__quote@ @AMDEP_TRUE@@am__include@ @am__quote@./$(DEPDIR)/genbc-impl.Po@am__quote@ @AMDEP_TRUE@@am__include@ @am__quote@./$(DEPDIR)/genbc-scan.Po@am__quote@ @AMDEP_TRUE@@am__include@ @am__quote@./$(DEPDIR)/genbc.Po@am__quote@ @AMDEP_TRUE@@am__include@ @am__quote@./$(DEPDIR)/genpr-parse.Po@am__quote@ @AMDEP_TRUE@@am__include@ @am__quote@./$(DEPDIR)/genpr-scan.Po@am__quote@ @AMDEP_TRUE@@am__include@ @am__quote@./$(DEPDIR)/genvm-parse.Po@am__quote@ @AMDEP_TRUE@@am__include@ @am__quote@./$(DEPDIR)/genvm-scan.Po@am__quote@ @AMDEP_TRUE@@am__include@ @am__quote@./$(DEPDIR)/gst-parse.Plo@am__quote@ @AMDEP_TRUE@@am__include@ @am__quote@./$(DEPDIR)/gstpub.Plo@am__quote@ @AMDEP_TRUE@@am__include@ @am__quote@./$(DEPDIR)/heap.Plo@am__quote@ @AMDEP_TRUE@@am__include@ @am__quote@./$(DEPDIR)/input.Plo@am__quote@ @AMDEP_TRUE@@am__include@ @am__quote@./$(DEPDIR)/interp.Plo@am__quote@ @AMDEP_TRUE@@am__include@ @am__quote@./$(DEPDIR)/lex.Plo@am__quote@ @AMDEP_TRUE@@am__include@ @am__quote@./$(DEPDIR)/mpz.Plo@am__quote@ @AMDEP_TRUE@@am__include@ @am__quote@./$(DEPDIR)/oop.Plo@am__quote@ @AMDEP_TRUE@@am__include@ @am__quote@./$(DEPDIR)/opt.Plo@am__quote@ @AMDEP_TRUE@@am__include@ @am__quote@./$(DEPDIR)/print.Plo@am__quote@ @AMDEP_TRUE@@am__include@ @am__quote@./$(DEPDIR)/re.Plo@am__quote@ @AMDEP_TRUE@@am__include@ @am__quote@./$(DEPDIR)/real.Plo@am__quote@ @AMDEP_TRUE@@am__include@ @am__quote@./$(DEPDIR)/save.Plo@am__quote@ @AMDEP_TRUE@@am__include@ @am__quote@./$(DEPDIR)/security.Plo@am__quote@ @AMDEP_TRUE@@am__include@ @am__quote@./$(DEPDIR)/sockets.Plo@am__quote@ @AMDEP_TRUE@@am__include@ @am__quote@./$(DEPDIR)/str.Plo@am__quote@ @AMDEP_TRUE@@am__include@ @am__quote@./$(DEPDIR)/sym.Plo@am__quote@ @AMDEP_TRUE@@am__include@ @am__quote@./$(DEPDIR)/sysdep.Plo@am__quote@ @AMDEP_TRUE@@am__include@ @am__quote@./$(DEPDIR)/tree.Plo@am__quote@ @AMDEP_TRUE@@am__include@ @am__quote@./$(DEPDIR)/xlat.Plo@am__quote@ .c.o: @am__fastdepCC_TRUE@ $(COMPILE) -MT $@ -MD -MP -MF $(DEPDIR)/$*.Tpo -c -o $@ $< @am__fastdepCC_TRUE@ $(am__mv) $(DEPDIR)/$*.Tpo $(DEPDIR)/$*.Po @AMDEP_TRUE@@am__fastdepCC_FALSE@ source='$<' object='$@' libtool=no @AMDEPBACKSLASH@ @AMDEP_TRUE@@am__fastdepCC_FALSE@ DEPDIR=$(DEPDIR) $(CCDEPMODE) $(depcomp) @AMDEPBACKSLASH@ @am__fastdepCC_FALSE@ $(COMPILE) -c $< .c.obj: @am__fastdepCC_TRUE@ $(COMPILE) -MT $@ -MD -MP -MF $(DEPDIR)/$*.Tpo -c -o $@ `$(CYGPATH_W) '$<'` @am__fastdepCC_TRUE@ $(am__mv) $(DEPDIR)/$*.Tpo $(DEPDIR)/$*.Po @AMDEP_TRUE@@am__fastdepCC_FALSE@ source='$<' object='$@' libtool=no @AMDEPBACKSLASH@ @AMDEP_TRUE@@am__fastdepCC_FALSE@ DEPDIR=$(DEPDIR) $(CCDEPMODE) $(depcomp) @AMDEPBACKSLASH@ @am__fastdepCC_FALSE@ $(COMPILE) -c `$(CYGPATH_W) '$<'` .c.lo: @am__fastdepCC_TRUE@ $(LTCOMPILE) -MT $@ -MD -MP -MF $(DEPDIR)/$*.Tpo -c -o $@ $< @am__fastdepCC_TRUE@ $(am__mv) $(DEPDIR)/$*.Tpo $(DEPDIR)/$*.Plo @AMDEP_TRUE@@am__fastdepCC_FALSE@ source='$<' object='$@' libtool=yes @AMDEPBACKSLASH@ @AMDEP_TRUE@@am__fastdepCC_FALSE@ DEPDIR=$(DEPDIR) $(CCDEPMODE) $(depcomp) @AMDEPBACKSLASH@ @am__fastdepCC_FALSE@ $(LTCOMPILE) -c -o $@ $< .l.c: $(am__skiplex) $(SHELL) $(YLWRAP) $< $(LEX_OUTPUT_ROOT).c $@ -- $(LEXCOMPILE) .y.c: $(am__skipyacc) $(SHELL) $(YLWRAP) $< y.tab.c $@ y.tab.h $*.h y.output $*.output -- $(YACCCOMPILE) mostlyclean-libtool: -rm -f *.lo clean-libtool: -rm -rf .libs _libs install-includeHEADERS: $(include_HEADERS) @$(NORMAL_INSTALL) @list='$(include_HEADERS)'; test -n "$(includedir)" || list=; \ if test -n "$$list"; then \ echo " $(MKDIR_P) '$(DESTDIR)$(includedir)'"; \ $(MKDIR_P) "$(DESTDIR)$(includedir)" || exit 1; \ fi; \ for p in $$list; do \ if test -f "$$p"; then d=; else d="$(srcdir)/"; fi; \ echo "$$d$$p"; \ done | $(am__base_list) | \ while read files; do \ echo " $(INSTALL_HEADER) $$files '$(DESTDIR)$(includedir)'"; \ $(INSTALL_HEADER) $$files "$(DESTDIR)$(includedir)" || exit $$?; \ done uninstall-includeHEADERS: @$(NORMAL_UNINSTALL) @list='$(include_HEADERS)'; test -n "$(includedir)" || list=; \ files=`for p in $$list; do echo $$p; done | sed -e 's|^.*/||'`; \ dir='$(DESTDIR)$(includedir)'; $(am__uninstall_files_from_dir) ID: $(HEADERS) $(SOURCES) $(LISP) $(TAGS_FILES) list='$(SOURCES) $(HEADERS) $(LISP) $(TAGS_FILES)'; \ unique=`for i in $$list; do \ if test -f "$$i"; then echo $$i; else echo $(srcdir)/$$i; fi; \ done | \ $(AWK) '{ files[$$0] = 1; nonempty = 1; } \ END { if (nonempty) { for (i in files) print i; }; }'`; \ mkid -fID $$unique tags: TAGS TAGS: $(HEADERS) $(SOURCES) $(TAGS_DEPENDENCIES) \ $(TAGS_FILES) $(LISP) set x; \ here=`pwd`; \ list='$(SOURCES) $(HEADERS) $(LISP) $(TAGS_FILES)'; \ unique=`for i in $$list; do \ if test -f "$$i"; then echo $$i; else echo $(srcdir)/$$i; fi; \ done | \ $(AWK) '{ files[$$0] = 1; nonempty = 1; } \ END { if (nonempty) { for (i in files) print i; }; }'`; \ shift; \ if test -z "$(ETAGS_ARGS)$$*$$unique"; then :; else \ test -n "$$unique" || unique=$$empty_fix; \ if test $$# -gt 0; then \ $(ETAGS) $(ETAGSFLAGS) $(AM_ETAGSFLAGS) $(ETAGS_ARGS) \ "$$@" $$unique; \ else \ $(ETAGS) $(ETAGSFLAGS) $(AM_ETAGSFLAGS) $(ETAGS_ARGS) \ $$unique; \ fi; \ fi ctags: CTAGS CTAGS: $(HEADERS) $(SOURCES) $(TAGS_DEPENDENCIES) \ $(TAGS_FILES) $(LISP) list='$(SOURCES) $(HEADERS) $(LISP) $(TAGS_FILES)'; \ unique=`for i in $$list; do \ if test -f "$$i"; then echo $$i; else echo $(srcdir)/$$i; fi; \ done | \ $(AWK) '{ files[$$0] = 1; nonempty = 1; } \ END { if (nonempty) { for (i in files) print i; }; }'`; \ test -z "$(CTAGS_ARGS)$$unique" \ || $(CTAGS) $(CTAGSFLAGS) $(AM_CTAGSFLAGS) $(CTAGS_ARGS) \ $$unique GTAGS: here=`$(am__cd) $(top_builddir) && pwd` \ && $(am__cd) $(top_srcdir) \ && gtags -i $(GTAGS_ARGS) "$$here" distclean-tags: -rm -f TAGS ID GTAGS GRTAGS GSYMS GPATH tags distdir: $(DISTFILES) @srcdirstrip=`echo "$(srcdir)" | sed 's/[].[^$$\\*]/\\\\&/g'`; \ topsrcdirstrip=`echo "$(top_srcdir)" | sed 's/[].[^$$\\*]/\\\\&/g'`; \ list='$(DISTFILES)'; \ dist_files=`for file in $$list; do echo $$file; done | \ sed -e "s|^$$srcdirstrip/||;t" \ -e "s|^$$topsrcdirstrip/|$(top_builddir)/|;t"`; \ case $$dist_files in \ */*) $(MKDIR_P) `echo "$$dist_files" | \ sed '/\//!d;s|^|$(distdir)/|;s,/[^/]*$$,,' | \ sort -u` ;; \ esac; \ for file in $$dist_files; do \ if test -f $$file || test -d $$file; then d=.; else d=$(srcdir); fi; \ if test -d $$d/$$file; then \ dir=`echo "/$$file" | sed -e 's,/[^/]*$$,,'`; \ if test -d "$(distdir)/$$file"; then \ find "$(distdir)/$$file" -type d ! -perm -700 -exec chmod u+rwx {} \;; \ fi; \ if test -d $(srcdir)/$$file && test $$d != $(srcdir); then \ cp -fpR $(srcdir)/$$file "$(distdir)$$dir" || exit 1; \ find "$(distdir)/$$file" -type d ! -perm -700 -exec chmod u+rwx {} \;; \ fi; \ cp -fpR $$d/$$file "$(distdir)$$dir" || exit 1; \ else \ test -f "$(distdir)/$$file" \ || cp -p $$d/$$file "$(distdir)/$$file" \ || exit 1; \ fi; \ done $(MAKE) $(AM_MAKEFLAGS) \ top_distdir="$(top_distdir)" distdir="$(distdir)" \ dist-hook check-am: all-am check: $(BUILT_SOURCES) $(MAKE) $(AM_MAKEFLAGS) check-am all-am: Makefile $(LTLIBRARIES) $(DATA) $(HEADERS) installdirs: for dir in "$(DESTDIR)$(libdir)" "$(DESTDIR)$(includedir)"; do \ test -z "$$dir" || $(MKDIR_P) "$$dir"; \ done install: $(BUILT_SOURCES) $(MAKE) $(AM_MAKEFLAGS) install-am install-exec: install-exec-am install-data: install-data-am uninstall: uninstall-am install-am: all-am @$(MAKE) $(AM_MAKEFLAGS) install-exec-am install-data-am installcheck: installcheck-am install-strip: if test -z '$(STRIP)'; then \ $(MAKE) $(AM_MAKEFLAGS) INSTALL_PROGRAM="$(INSTALL_STRIP_PROGRAM)" \ install_sh_PROGRAM="$(INSTALL_STRIP_PROGRAM)" INSTALL_STRIP_FLAG=-s \ install; \ else \ $(MAKE) $(AM_MAKEFLAGS) INSTALL_PROGRAM="$(INSTALL_STRIP_PROGRAM)" \ install_sh_PROGRAM="$(INSTALL_STRIP_PROGRAM)" INSTALL_STRIP_FLAG=-s \ "INSTALL_PROGRAM_ENV=STRIPPROG='$(STRIP)'" install; \ fi mostlyclean-generic: clean-generic: -test -z "$(CLEANFILES)" || rm -f $(CLEANFILES) distclean-generic: -test -z "$(CONFIG_CLEAN_FILES)" || rm -f $(CONFIG_CLEAN_FILES) -test . = "$(srcdir)" || test -z "$(CONFIG_CLEAN_VPATH_FILES)" || rm -f $(CONFIG_CLEAN_VPATH_FILES) maintainer-clean-generic: @echo "This command is intended for maintainers to use" @echo "it deletes files that may require special tools to rebuild." -rm -f genbc-decl.c -rm -f genbc-impl.c -rm -f genbc-scan.c -rm -f genpr-parse.c -rm -f genpr-scan.c -rm -f genvm-parse.c -rm -f genvm-scan.c -test -z "$(BUILT_SOURCES)" || rm -f $(BUILT_SOURCES) clean: clean-am clean-am: clean-generic clean-libLTLIBRARIES clean-libtool \ mostlyclean-am distclean: distclean-am -rm -rf ./$(DEPDIR) -rm -f Makefile distclean-am: clean-am distclean-compile distclean-generic \ distclean-tags dvi: dvi-am dvi-am: html: html-am html-am: info: info-am info-am: install-data-am: install-includeHEADERS install-dvi: install-dvi-am install-dvi-am: install-exec-am: install-libLTLIBRARIES install-html: install-html-am install-html-am: install-info: install-info-am install-info-am: install-man: install-pdf: install-pdf-am install-pdf-am: install-ps: install-ps-am install-ps-am: installcheck-am: maintainer-clean: maintainer-clean-am -rm -rf ./$(DEPDIR) -rm -f Makefile maintainer-clean-am: distclean-am maintainer-clean-generic mostlyclean: mostlyclean-am mostlyclean-am: mostlyclean-compile mostlyclean-generic \ mostlyclean-libtool pdf: pdf-am pdf-am: ps: ps-am ps-am: uninstall-am: uninstall-includeHEADERS uninstall-libLTLIBRARIES .MAKE: all check install install-am install-strip .PHONY: CTAGS GTAGS all all-am check check-am clean clean-generic \ clean-libLTLIBRARIES clean-libtool ctags dist-hook distclean \ distclean-compile distclean-generic distclean-libtool \ distclean-tags distdir dvi dvi-am html html-am info info-am \ install install-am install-data install-data-am install-dvi \ install-dvi-am install-exec install-exec-am install-html \ install-html-am install-includeHEADERS install-info \ install-info-am install-libLTLIBRARIES install-man install-pdf \ install-pdf-am install-ps install-ps-am install-strip \ installcheck installcheck-am installdirs maintainer-clean \ maintainer-clean-generic mostlyclean mostlyclean-compile \ mostlyclean-generic mostlyclean-libtool pdf pdf-am ps ps-am \ tags uninstall uninstall-am uninstall-includeHEADERS \ uninstall-libLTLIBRARIES # manually give dependencies involving BUILT_SOURCES. The input .l/.y files # change rarely, so do not bother changing the timestamp file only if the # output changed. genbc-decl.stamp: genbc-decl.c genbc-decl.y; echo stamp > $@ genbc-impl.stamp: genbc-impl.c genbc-impl.y; echo stamp > $@ genpr-parse.stamp: genpr-parse.c genpr-parse.y; echo stamp > $@ genvm-parse.stamp: genvm-parse.c genvm-parse.y; echo stamp > $@ genbc.o: genbc-decl.stamp genbc-impl.stamp genbc-scan.o: genbc-decl.stamp genbc-impl.stamp genbc-decl.o: genbc-decl.stamp genbc-impl.stamp genbc-impl.o: genbc-decl.stamp genbc-impl.stamp genpr-scan.o: genpr-parse.stamp genvm-scan.o: genvm-parse.stamp # rules for invoking genbc # Try to economize in the rebuilds, by avoiding unnecessary # changes to the timestamp of match.h $(srcdir)/match.h: $(srcdir)/match.stamp @: $(srcdir)/match.stamp: byte.def byte.c opt.c xlat.c @$(MAKE) genbc$(EXEEXT) @echo "./genbc$(EXEEXT) $(srcdir)/byte.def $(srcdir)/byte.c $(srcdir)/opt.c $(srcdir)/xlat.c > match.h"; \ ./genbc$(EXEEXT) $(srcdir)/byte.def $(srcdir)/byte.c $(srcdir)/opt.c $(srcdir)/xlat.c > _match.h @if cmp _match.h $(srcdir)/match.h > /dev/null 2>&1; then \ echo match.h is unchanged; \ rm _match.h; \ else \ mv _match.h $(srcdir)/match.h; \ fi @echo timestamp > $(srcdir)/match.stamp # rules for invoking genprims # Try to economize in the rebuilds, by avoiding unnecessary # changes to the timestamp of prims.inl $(srcdir)/prims.inl: $(srcdir)/prims.stamp @: $(srcdir)/prims.stamp: prims.def @$(MAKE) genprims$(EXEEXT) @echo "./genprims$(EXEEXT) < $(srcdir)/prims.def > prims.inl"; \ ./genprims$(EXEEXT) < $(srcdir)/prims.def > _prims.inl @if cmp _prims.inl $(srcdir)/prims.inl > /dev/null 2>&1; then \ echo prims.inl is unchanged; \ rm _prims.inl; \ else \ mv _prims.inl $(srcdir)/prims.inl; \ fi @echo timestamp > $(srcdir)/prims.stamp # rules for invoking genvm # Try to economize in the rebuilds, by avoiding unnecessary # changes to the timestamp of vm.inl $(srcdir)/vm.inl: $(srcdir)/vm.stamp @: $(srcdir)/vm.stamp: vm.def @$(MAKE) genvm$(EXEEXT) @echo "./genvm$(EXEEXT) < $(srcdir)/vm.def | awk '{ /^#/ && gsub(/__oline__/,NR+1); print }' > vm.inl"; \ ./genvm$(EXEEXT) < $(srcdir)/vm.def | awk '{ /^#/ && gsub(/__oline__/,NR+1); print }' > _vm.inl @if cmp _vm.inl $(srcdir)/vm.inl > /dev/null 2>&1; then \ echo vm.inl is unchanged; \ rm _vm.inl; \ else \ mv _vm.inl $(srcdir)/vm.inl; \ fi @echo timestamp > $(srcdir)/vm.stamp # rules for invoking gperf # not fully idiot-proof but only to be run by maintainers %.inl: %.gperf @opts="$< `$(SED) -ne /.*gperf/!d -e s///p -e q $< | \ $(SED) 's,$$(srcdir),$(srcdir),g'`"; \ echo $(GPERF) $$opts " > $@"; \ for i in a b c d e f g h j; do \ if test $$i = j; then \ eval $(GPERF) $$opts > $@ && break; \ else \ eval $(GPERF) $$opts > $@ 2>/dev/null && break; \ echo Retrying...; sleep 1; \ fi; \ done builtins.inl: builtins.gperf dist-hook: for i in $(STAMP_FILES); do \ echo timestamp > $(distdir)/$$i; \ done # Tell versions [3.59,3.63) of GNU make to not export all variables. # Otherwise a system limit (for SysV at least) may be exceeded. .NOEXPORT: smalltalk-3.2.5/libgst/genprims.h0000644000175000017500000000536312123404352013712 00000000000000/******************************** -*- C -*- **************************** * * GNU Smalltalk genprims tool * ***********************************************************************/ /*********************************************************************** * * Copyright 2002, 2006 Free Software Foundation, Inc. * Written by Paolo Bonzini. * * This file is part of GNU Smalltalk. * * GNU Smalltalk is free software; you can redistribute it and/or modify it * under the terms of the GNU General Public License as published by the Free * Software Foundation; either version 2, or (at your option) any later * version. * * Linking GNU Smalltalk statically or dynamically with other modules is * making a combined work based on GNU Smalltalk. Thus, the terms and * conditions of the GNU General Public License cover the whole * combination. * * In addition, as a special exception, the Free Software Foundation * give you permission to combine GNU Smalltalk with free software * programs or libraries that are released under the GNU LGPL and with * independent programs running under the GNU Smalltalk virtual machine. * * You may copy and distribute such a system following the terms of the * GNU GPL for GNU Smalltalk and the licenses of the other code * concerned, provided that you include the source code of that other * code when and as the GNU GPL requires distribution of source code. * * Note that people who make modified versions of GNU Smalltalk are not * obligated to grant this special exception for their modified * versions; it is their choice whether to do so. The GNU General * Public License gives permission to release a modified version without * this exception; this exception also makes it possible to release a * modified version which carries forward this exception. * * GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or * FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for * more details. * * You should have received a copy of the GNU General Public License along with * GNU Smalltalk; see the file COPYING. If not, write to the Free Software * Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * ***********************************************************************/ #ifdef HAVE_CONFIG_H #include "config.h" #endif #include #include #include #include #include "snprintfv/filament.h" #include "snprintfv/printf.h" /* genprims.l declarations */ int yylex (void); extern int yylineno; /* genprims.y declarations */ int filprintf (Filament * fil, const char *format, ...); extern Filament *proto_fil, *stmt_fil, *def_fil, *literal_fil; smalltalk-3.2.5/libgst/callin.h0000644000175000017500000002540412123404352013326 00000000000000/******************************** -*- C -*- **************************** * * External definitions for C callin module * * ***********************************************************************/ /*********************************************************************** * * Copyright 1988,89,90,91,92,94,95,99,2000,2001,2002,2006,2008,2009 * Free Software Foundation, Inc. * Written by Steve Byrne. * * This file is part of GNU Smalltalk. * * GNU Smalltalk is free software; you can redistribute it and/or modify it * under the terms of the GNU General Public License as published by the Free * Software Foundation; either version 2, or (at your option) any later * version. * * Linking GNU Smalltalk statically or dynamically with other modules is * making a combined work based on GNU Smalltalk. Thus, the terms and * conditions of the GNU General Public License cover the whole * combination. * * In addition, as a special exception, the Free Software Foundation * give you permission to combine GNU Smalltalk with free software * programs or libraries that are released under the GNU LGPL and with * independent programs running under the GNU Smalltalk virtual machine. * * You may copy and distribute such a system following the terms of the * GNU GPL for GNU Smalltalk and the licenses of the other code * concerned, provided that you include the source code of that other * code when and as the GNU GPL requires distribution of source code. * * Note that people who make modified versions of GNU Smalltalk are not * obligated to grant this special exception for their modified * versions; it is their choice whether to do so. The GNU General * Public License gives permission to release a modified version without * this exception; this exception also makes it possible to release a * modified version which carries forward this exception. * * GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or * FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for * more details. * * You should have received a copy of the GNU General Public License along with * GNU Smalltalk; see the file COPYING. If not, write to the Free Software * Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * ***********************************************************************/ #ifndef GST_CALLIN_H #define GST_CALLIN_H /* Sends SELECTOR (which should be a Symbol, otherwise _gst_nil_oop is returned) to RECEIVER. The message arguments pointed to by AP should also be OOPs (otherwise, an access violation exception is pretty likely) and are passed in a NULL-terminated list after the selector. The value returned from the method is passed back as an OOP to the C program as the result of the function, or _gst_nil_oop if the number of arguments is wrong. */ extern OOP _gst_va_msg_send (OOP receiver, OOP selector, va_list ap) ATTRIBUTE_HIDDEN; /* Sends SELECTOR (which should be a Symbol, otherwise _gst_nil_oop is returned) to RECEIVER. The message arguments should also be OOPs (otherwise, an access violation exception is pretty likely) and are passed in a NULL-terminated list after the selector. The value returned from the method is passed back as an OOP to the C program as the result of the function, or _gst_nil_oop if the number of arguments is wrong. */ extern OOP _gst_msg_send (OOP receiver, OOP selector, ...) ATTRIBUTE_HIDDEN; /* Sends SELECTOR (which should be a Symbol, otherwise _gst_nil_oop is returned) to RECEIVER. The message arguments should also be OOPs (otherwise, an access violation exception is pretty likely) and are passed in a NULL-terminated list pointed to by ARGS. The value returned from the method is passed back as an OOP to the C program as the result of the function, or _gst_nil_oop if the number of arguments is wrong. */ extern OOP _gst_vmsg_send (OOP receiver, OOP selector, OOP * args) ATTRIBUTE_HIDDEN; /* Sends the SEL selector to RECEIVER. The message arguments should also be OOPs (otherwise, an access violation exception is pretty likely) and are passed in a NULL-terminated list after the selector. The value returned from the method is passed back as an OOP to the C program as the result of the function, or _gst_nil_oop if the number of arguments is wrong. */ extern OOP _gst_str_msg_send (OOP receiver, const char * sel, ...) ATTRIBUTE_HIDDEN; /* See manual; basically it takes care of the conversion from C to Smalltalk data types. */ extern void _gst_va_msg_sendf (PTR resultPtr, const char * fmt, va_list ap) ATTRIBUTE_HIDDEN; /* See manual; basically it takes care of the conversion from C to Smalltalk data types. */ extern void _gst_msg_sendf (PTR resultPtr, const char * fmt, ...) ATTRIBUTE_HIDDEN; /* Evaluate the Smalltalk code in STR and return the result as an OOP. STR is a Smalltalk method body which can have local variables, but no parameters. This is much like the immediate expression evaluation that the command interpreter provides. */ extern OOP _gst_eval_expr (const char *str) ATTRIBUTE_HIDDEN; /* Evaluate the Smalltalk code in STR, a Smalltalk method body which can have local variables, but no parameters. This is much like the immediate expression evaluation that the command interpreter provides. */ extern void _gst_eval_code (const char *str) ATTRIBUTE_HIDDEN; /* Puts the given OOP in the registry. If you register an object multiple times, you will need to unregister it the same number of times. You may want to register objects returned by Smalltalk call-ins. */ extern OOP _gst_register_oop (OOP oop) ATTRIBUTE_HIDDEN; /* Removes an occurrence of the given OOP from the registry. */ extern void _gst_unregister_oop (OOP oop) ATTRIBUTE_HIDDEN; /* Remember that an array of OOPs must be made part of the root set. The two parameters, FIRST and LAST, point to two variables containing respectively the base and the top of the array: the double indirection allows one to move the array freely in memory, for example using realloc. */ extern void _gst_register_oop_array (OOP **first, OOP **last) ATTRIBUTE_HIDDEN; /* Unregister the given array of OOPs from the root set. FIRST points to a variables containing the base of the array: the double indirection allows one to move the array freely in memory, for example using realloc. */ extern void _gst_unregister_oop_array (OOP **first) ATTRIBUTE_HIDDEN; /* Allocates an OOP for a newly created instance of the class whose OOP is passed as the first parameter; if that parameter is not a class the results are undefined (for now, read as ``the program will most likely core dump'', but that could change in a future version). The second parameter is used only if the class is an indexable one, otherwise it is discarded: it contains the number of indexed instance variables in the object that is going to be created. */ extern OOP _gst_object_alloc (OOP class_oop, int size) ATTRIBUTE_HIDDEN; /* Returns the number of indexed instance variables in OOP */ extern int _gst_basic_size (OOP oop) ATTRIBUTE_HIDDEN; /* Convert C datatypes to Smalltalk types */ extern OOP _gst_id_to_oop (long i) ATTRIBUTE_HIDDEN; extern OOP _gst_int_to_oop (long i) ATTRIBUTE_HIDDEN; extern OOP _gst_uint_to_oop (unsigned long i) ATTRIBUTE_HIDDEN; extern OOP _gst_float_to_oop (double f) ATTRIBUTE_HIDDEN; extern OOP _gst_bool_to_oop (int b) ATTRIBUTE_HIDDEN; extern OOP _gst_char_to_oop (char c) ATTRIBUTE_HIDDEN; extern OOP _gst_wchar_to_oop (wchar_t c) ATTRIBUTE_HIDDEN; extern OOP _gst_class_name_to_oop (const char *name) ATTRIBUTE_HIDDEN; extern OOP _gst_string_to_oop (const char *str) ATTRIBUTE_HIDDEN; extern OOP _gst_wstring_to_oop (const wchar_t *str) ATTRIBUTE_HIDDEN; extern OOP _gst_byte_array_to_oop (const char *str, int n) ATTRIBUTE_HIDDEN; extern OOP _gst_symbol_to_oop (const char *str) ATTRIBUTE_HIDDEN; extern OOP _gst_c_object_to_oop (PTR co) ATTRIBUTE_HIDDEN; extern OOP _gst_type_name_to_oop (const char *name) ATTRIBUTE_HIDDEN; extern void _gst_set_c_object (OOP oop, PTR co) ATTRIBUTE_HIDDEN; extern OOP _gst_long_double_to_oop (long double f) ATTRIBUTE_HIDDEN; /* Convert Smalltalk datatypes to C data types */ extern long _gst_oop_to_c (OOP oop) ATTRIBUTE_HIDDEN; /* sometimes answers a PTR */ extern long _gst_oop_to_id (OOP oop) ATTRIBUTE_HIDDEN; extern long _gst_oop_to_int (OOP oop) ATTRIBUTE_HIDDEN; extern double _gst_oop_to_float (OOP oop) ATTRIBUTE_HIDDEN; extern int _gst_oop_to_bool (OOP oop) ATTRIBUTE_HIDDEN; extern char _gst_oop_to_char (OOP oop) ATTRIBUTE_HIDDEN; extern wchar_t _gst_oop_to_wchar (OOP oop) ATTRIBUTE_HIDDEN; extern char *_gst_oop_to_string (OOP oop) ATTRIBUTE_HIDDEN; extern wchar_t *_gst_oop_to_wstring (OOP oop) ATTRIBUTE_HIDDEN; extern char *_gst_oop_to_byte_array (OOP oop) ATTRIBUTE_HIDDEN; extern PTR _gst_oop_to_c_object (OOP oop) ATTRIBUTE_HIDDEN; extern long double _gst_oop_to_long_double (OOP oop) ATTRIBUTE_HIDDEN; extern OOP _gst_get_object_class (OOP oop) ATTRIBUTE_HIDDEN; extern OOP _gst_get_superclass (OOP oop) ATTRIBUTE_HIDDEN; extern mst_Boolean _gst_class_is_kind_of (OOP candidate, OOP superclass) ATTRIBUTE_HIDDEN; extern mst_Boolean _gst_object_is_kind_of (OOP candidate, OOP superclass) ATTRIBUTE_HIDDEN; extern OOP _gst_perform (OOP receiver, OOP selector) ATTRIBUTE_HIDDEN; extern OOP _gst_perform_with (OOP receiver, OOP selector, OOP arg) ATTRIBUTE_HIDDEN; extern mst_Boolean _gst_class_implements_selector (OOP classOOP, OOP selector) ATTRIBUTE_HIDDEN; extern mst_Boolean _gst_class_can_understand (OOP classOOP, OOP selector) ATTRIBUTE_HIDDEN; extern mst_Boolean _gst_responds_to (OOP oop, OOP selector) ATTRIBUTE_HIDDEN; extern size_t _gst_oop_size (OOP oop) ATTRIBUTE_HIDDEN; extern OOP _gst_oop_at (OOP oop, size_t index) ATTRIBUTE_HIDDEN; extern OOP _gst_oop_at_put (OOP oop, size_t index, OOP new) ATTRIBUTE_HIDDEN; extern void *_gst_oop_indexed_base (OOP oop) ATTRIBUTE_HIDDEN; extern enum gst_indexed_kind _gst_oop_indexed_kind (OOP oop) ATTRIBUTE_HIDDEN; /* Marks/copies the registered OOPs (they are part of the rootset by definition) */ extern void _gst_mark_registered_oops (void) ATTRIBUTE_HIDDEN; extern void _gst_copy_registered_oops (void) ATTRIBUTE_HIDDEN; /* Initializes the registry of OOPs which some C code is holding. */ extern void _gst_init_oopregistry (void) ATTRIBUTE_HIDDEN; /* Returns a copy of the VMProxy. */ extern struct VMProxy *_gst_get_vmproxy (void) ATTRIBUTE_HIDDEN; /* Initialize the VMProxy. */ extern void _gst_init_vmproxy (void) ATTRIBUTE_HIDDEN; #endif /* GST_CALLIN_H */ smalltalk-3.2.5/libgst/comp.h0000644000175000017500000003403012130343734013021 00000000000000/******************************** -*- C -*- **************************** * * Declarations for the byte code compiler. * * ***********************************************************************/ /*********************************************************************** * * Copyright 1988,89,90,91,92,94,95,99,2000,2001,2002,2006,2007,2008 * Free Software Foundation, Inc. * Written by Steve Byrne. * * This file is part of GNU Smalltalk. * * GNU Smalltalk is free software; you can redistribute it and/or modify it * under the terms of the GNU General Public License as published by the Free * Software Foundation; either version 2, or (at your option) any later * version. * * Linking GNU Smalltalk statically or dynamically with other modules is * making a combined work based on GNU Smalltalk. Thus, the terms and * conditions of the GNU General Public License cover the whole * combination. * * In addition, as a special exception, the Free Software Foundation * give you permission to combine GNU Smalltalk with free software * programs or libraries that are released under the GNU LGPL and with * independent programs running under the GNU Smalltalk virtual machine. * * You may copy and distribute such a system following the terms of the * GNU GPL for GNU Smalltalk and the licenses of the other code * concerned, provided that you include the source code of that other * code when and as the GNU GPL requires distribution of source code. * * Note that people who make modified versions of GNU Smalltalk are not * obligated to grant this special exception for their modified * versions; it is their choice whether to do so. The GNU General * Public License gives permission to release a modified version without * this exception; this exception also makes it possible to release a * modified version which carries forward this exception. * * GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or * FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for * more details. * * You should have received a copy of the GNU General Public License along with * GNU Smalltalk; see the file COPYING. If not, write to the Free Software * Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * ***********************************************************************/ #ifndef GST_COMP_H #define GST_COMP_H /* These next three defines are the number of bits in a method header for the number of stack bits, the number of _gst_temporaries, and the number of arguments that the method takes. If the representation is changed, these definitions need to be altered too */ #define DEPTH_SCALE 2 #define MAX_DEPTH (((1 << MTH_DEPTH_BITS) - 1) << DEPTH_SCALE) #define MAX_NUM_TEMPS ((1 << MTH_TEMPS_BITS) - 1) #define MAX_NUM_ARGS ((1 << MTH_ARGS_BITS) - 1) #define NUM_PRIMITIVES (1 << MTH_PRIM_BITS) /* * This is the organization of a method header. The 1 bit in the high end of * the word indicates that this is an integer, so that the GC won't be tempted * to try to scan the contents of this field, and so we can do bitwise operations * on this value to extract component pieces. * * 3 2 1 * 1 0 9 8 7 6 5 4 3 2 1 0 9 8 7 6 5 4 3 2 1 0 9 8 7 6 5 4 3 2 1 0 * +-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+ * |.|flags| prim index | #temps | depth | #args |1| * +-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+ * * flags (30-28) * flags 0 -- nothing * flags 1 -- return _gst_self * flags 2 -- return instance variable (# in primitive index) * flags 3 -- return literal * flags 4 -- primitive index */ #define MTH_DEPTH_BITS 6 #define MTH_TEMPS_BITS 6 #define MTH_ARGS_BITS 5 #define MTH_PRIM_BITS 9 #define MTH_FLAG_BITS 3 #define MTH_NORMAL 0 #define MTH_RETURN_SELF 1 #define MTH_RETURN_INSTVAR 2 #define MTH_RETURN_LITERAL 3 #define MTH_PRIMITIVE 4 #define MTH_ANNOTATED 5 #define MTH_USER_DEFINED 6 #define MTH_UNUSED 7 typedef struct method_header { #ifdef WORDS_BIGENDIAN #if SIZEOF_OOP == 8 unsigned :32; /* unused */ #endif unsigned :1; /* sign - must be 0 */ unsigned headerFlag:MTH_FLAG_BITS; /* prim _gst_self, etc. */ unsigned isOldSyntax:1; unsigned primitiveIndex:MTH_PRIM_BITS; /* index of primitive, or 0 */ unsigned numTemps:MTH_TEMPS_BITS; unsigned stack_depth:MTH_DEPTH_BITS; unsigned numArgs:MTH_ARGS_BITS; unsigned intMark:1; /* flag this as an Int */ #else unsigned intMark:1; /* flag this as an Int */ unsigned numArgs:MTH_ARGS_BITS; unsigned stack_depth:MTH_DEPTH_BITS; unsigned numTemps:MTH_TEMPS_BITS; unsigned primitiveIndex:MTH_PRIM_BITS; /* index of primitve, or 0 */ unsigned isOldSyntax:1; unsigned headerFlag:MTH_FLAG_BITS; /* prim _gst_self, etc. */ unsigned :1; /* sign - must be 0 */ #if SIZEOF_OOP == 8 unsigned :32; /* unused */ #endif #endif /* WORDS_BIGENDIAN */ } method_header; typedef struct gst_compiled_method { OBJ_HEADER; OOP literals; method_header header; OOP descriptor; gst_uchar bytecodes[1]; } *gst_compiled_method; typedef struct gst_method_info { OBJ_HEADER; OOP sourceCode; OOP category; OOP class; OOP selector; OOP attributes[1]; } *gst_method_info; /* * These definition parallel the above ones, but they are for blocks. Here is * the organization of a block header. * * 3 2 1 * 1 0 9 8 7 6 5 4 3 2 1 0 9 8 7 6 5 4 3 2 1 0 9 8 7 6 5 4 3 2 1 0 * +-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+ * |.| #args | #temps | depth | unused | clean |1| * +-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+ * */ #define BLK_DEPTH_BITS 6 #define BLK_TEMPS_BITS 5 #define BLK_ARGS_BITS 5 #define BLK_CLEAN_BITS 5 #define BLK_UNUSED_BITS 9 typedef struct block_header { #ifdef WORDS_BIGENDIAN #if SIZEOF_OOP == 8 unsigned :32; /* unused */ #endif unsigned :1; /* sign - must be 0 */ unsigned numArgs:BLK_ARGS_BITS; /* number of arguments we have */ unsigned numTemps:BLK_TEMPS_BITS; /* number of _gst_temporaries we have */ unsigned depth:BLK_DEPTH_BITS; /* number of stack slots needed */ unsigned :BLK_UNUSED_BITS; unsigned clean:BLK_CLEAN_BITS; /* behavior of block */ unsigned intMark:1; /* flag this as an Int */ #else unsigned intMark:1; /* flag this as an Int */ unsigned clean:BLK_CLEAN_BITS; /* behavior of block */ unsigned :BLK_UNUSED_BITS; unsigned depth:BLK_DEPTH_BITS; /* number of stack slots needed */ unsigned numTemps:BLK_TEMPS_BITS; /* number of _gst_temporaries we have */ unsigned numArgs:BLK_ARGS_BITS; /* number of arguments we have */ unsigned :1; /* sign - must be 0 */ #if SIZEOF_OOP == 8 unsigned :32; /* unused */ #endif #endif } block_header; typedef struct gst_compiled_block { OBJ_HEADER; OOP literals; block_header header; OOP method; gst_uchar bytecodes[1]; } *gst_compiled_block; typedef struct gst_block_closure { OBJ_HEADER; OOP outerContext; /* the parent gst_block_context or gst_method_context */ OOP block; /* the gst_compiled_block */ OOP receiver; /* the receiver in which the closure lives */ } *gst_block_closure; /* These hold the compiler's notions of the current class for compilations, and the current category that compiled methods are to be placed into */ extern OOP _gst_this_class ATTRIBUTE_HIDDEN; extern OOP _gst_this_category ATTRIBUTE_HIDDEN; extern OOP _gst_latest_compiled_method ATTRIBUTE_HIDDEN; /* This is the value most recently returned by _gst_execute_statements. It is used to communicate the returned value past a _gst_parse_stream call, without pushing something on the called context stack in the case of nested invocations of _gst_prepare_execution_environment/_gst_finish_execution_environment. Most often, the caller does not care about the returned value, since it often is called from a radically different context. */ extern OOP _gst_last_returned_value ATTRIBUTE_HIDDEN; /* This flag controls whether byte codes are printed after compilation. If > 1, it applies also to code not invoked by the user. */ extern int _gst_declare_tracing ATTRIBUTE_HIDDEN; /* If true, the compilation of a set of methods will be skipped completely; only syntax will be checked. Set by primitive, cleared by grammar. */ extern mst_Boolean _gst_skip_compilation ATTRIBUTE_HIDDEN; /* This holds whether the compiler should make the compiled methods untrusted. */ extern mst_Boolean _gst_untrusted_methods ATTRIBUTE_HIDDEN; /* Given a tree_node of type TREE_KEYWORD_LIST, pick out and concatenate the keywords, turn them into a symbol OOP and return that symbol. */ extern OOP _gst_compute_keyword_selector (tree_node selectorExpr) ATTRIBUTE_HIDDEN; /* Given CONSTEXPR, a section of the syntax tree that represents a Smalltalk constant, this routine creates and returns an OOP to be stored as a method literal in the method that's currently being compiled. */ extern OOP _gst_make_constant_oop (tree_node constExpr); /* Called to compile and execute an "immediate expression"; i.e. a Smalltalk statement that is not part of a method definition and where temporaries are declared automatically. The parse trees are in TEMPS and STATEMENTS. Return the object that was returned by the expression. */ extern OOP _gst_execute_statements (tree_node temps, tree_node statement, enum undeclared_strategy undeclared, mst_Boolean quiet) ATTRIBUTE_HIDDEN; /* This function will print a message describing the method category and class being compiled. The message can have the form "STRING _GST_THIS_CATEGORY for _GST_THIS_CLASS" or "STRING for _GST_THIS_CLASS", depending on the value of CATEGORY. */ extern void _gst_display_compilation_trace (const char *string, mst_Boolean category) ATTRIBUTE_HIDDEN; /* This routine does a very interesting thing. It installs the inital method, which is the primitive for "methodsFor:". It does this by creating a string that contains the method definition and then passing this to the parser as an expression to be parsed and compiled. Once this has been installed, we can go ahead and begin loading the rest of the Smalltalk method definitions, but until the "methodsFor:" method is defined, we cannot begin to deal with !Object methodsFor: 'primitives'! In addition, we also define the special UndefinedObject>>#__terminate method here, because bytecode 143 cannot be compiled by parsing Smalltalk code. */ extern void _gst_install_initial_methods (void) ATTRIBUTE_HIDDEN; /* Sets the compiler's notion of the class to compile methods into. */ extern void _gst_set_compilation_class (OOP class_oop) ATTRIBUTE_HIDDEN; /* Sets the compiler's notion of the category to compile methods into. */ extern void _gst_set_compilation_category (OOP categoryOOP) ATTRIBUTE_HIDDEN; /* Clears the compiler's notion of the class and category to compile methods into. */ extern void _gst_reset_compilation_category () ATTRIBUTE_HIDDEN; /* This function will send a message to ObjectMemory (a system class) asking it to broadcast the event named HOOK. */ extern void _gst_invoke_hook (enum gst_vm_hook hook) ATTRIBUTE_HIDDEN; /* Prepares the compiler for execution, initializing some variables. */ extern void _gst_init_compiler (void) ATTRIBUTE_HIDDEN; /* Compile the code for a complete method definition. This basically walks the METHOD parse tree, but in addition it special cases for methods that don't return a value explicitly by returning "self". Also creates the CompiledMethod object and, if INSTALL is true, installs it in the current method dictionary with the selector derived from the method expression. */ extern OOP _gst_compile_method (tree_node method, mst_Boolean returnLast, mst_Boolean install) ATTRIBUTE_HIDDEN; /* Constructs and returns a new CompiledMethod instance. It computes the method header based on its arguments, and on the contents of the method's byte codes (setting up the flags to optimize returns). LITERALS is a Smalltalk Array containing the literals, or nil if we retrieve it from the array internal to comp.c */ extern OOP _gst_make_new_method (int primitiveIndex, int numArgs, int numTemps, int maximumStackDepth, OOP literals, bc_vector bytecodes, OOP class, OOP selector, OOP defaultCategoryOOP, int64_t startPos, int64_t endPos) ATTRIBUTE_HIDDEN; /* This function looks for the UndefinedObject>>#__terminate method (if it is not cached already) and answers it. This method is executed by contexts created with _gst_prepare_execution_environment. */ extern OOP _gst_get_termination_method (void) ATTRIBUTE_PURE ATTRIBUTE_HIDDEN; /* Creates and returns a CompiledBlock. The object is not completely filled in, as we only know the method literals and enclosing method when we create the outer CompiledMethod; the header is however filled, analyzing the BYTECODES to check the block's cleanness. */ extern OOP _gst_block_new (int numArgs, int numTemps, bc_vector bytecodes, int depth, OOP * literals) ATTRIBUTE_HIDDEN; /* Adds OOP to the literal vector that's being created, unless it's already there. "Already there" is defined as the exact same object is present in the literal vector. The answer is the index into the literal vector where the object was stored. */ extern int _gst_add_forced_object (OOP oop) ATTRIBUTE_HIDDEN; /* Transform the ATTRIBUTE_KEYWORDS node (a TREE_ATTRIBUTE_LIST) into a Message object, and return it. */ extern OOP _gst_make_attribute (tree_node attribute_keywords) ATTRIBUTE_HIDDEN; /* Process the attributes in ARRAYOOP, return the primitive number (so far, this is the only attribute we honor), or -1 for a bad primitive number. */ extern int _gst_process_attributes_array (OOP arrayOOP) ATTRIBUTE_HIDDEN; #endif /* GST_COMP_H */ smalltalk-3.2.5/libgst/superop2.inl0000644000175000017500000001673512123404352014205 00000000000000/* Automagically generated by superops, do not edit! */ enum { MIN_HASH_VALUE = 50, MAX_HASH_VALUE = 336 }; static const unsigned short asso_values[] = { 44, 101, 68, 85, 71, 116, 117, 337, 111, 337, 337, 337, 337, 69, 5, 337, 88, 123, 19, 99, 337, 337, 50, 65, 87, 337, 337, 337, 93, 123, 7, 337, 123, 45, 108, 48, 104, 88, 94, 2, 3, 104, 337, 337, 91, 63, 64, 59, 4, 17, 86, 52, 337, 337, 89, 81, 121, 337, 337, 337, 337, 337, 337, 337, 23, 19, 92, 120, 25, 39, 60, 337, 337, 337, 337, 3, 337, 16, 337, 101, 337, 5, 337, 337, 86, 337, 337, 337, 337, 337, 337, 30, 337, 337, 337, 337, 17, 337, 337, 337, 112, 337, 34, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 4, 337, 337, 337, 337, 337, 337, 337, 337, 62, 69, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337, 337 }; static const struct superop_with_fixed_arg_2_type keylist[] = { {{ 39, 48, 0}, 120}, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{ 46, 30, 49}, 117}, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{ 39, 51, 0}, 248}, {{ 68, 91, 0}, 234}, {{ 121, 51, 0}, 214}, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{ 35, 18, 0}, 206}, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{ 44, 30, 96}, 122}, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{ 46, 49, 0}, 70}, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{ 102, 30, 37}, 215}, {{ 67, 30, 40}, 155}, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{ 69, 51, 0}, 252}, {{ 54, 75, 0}, 185}, {{ 54, 48, 0}, 68}, {{ 39, 66, 0}, 80}, {{}, -1 }, {{ 44, 14, 0}, 159}, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{ 35, 51, 0}, 124}, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{ 70, 64, 2}, 187}, {{ 36, 48, 0}, 78}, {{}, -1 }, {{ 70, 64, 4}, 212}, {{ 46, 64, 2}, 137}, {{ 68, 91, 1}, 245}, {{}, -1 }, {{ 46, 64, 4}, 204}, {{ 45, 51, 0}, 75}, {{ 46, 51, 0}, 128}, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{ 46, 30, 38}, 110}, {{}, -1 }, {{}, -1 }, {{ 70, 64, 3}, 178}, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{ 46, 64, 3}, 144}, {{ 54, 77, 2}, 255}, {{ 68, 35, 1}, 228}, {{ 46, 30, 36}, 92}, {{ 69, 28, 0}, 158}, {{ 46, 131, 0}, 239}, {{}, -1 }, {{ 44, 0}, 81}, {{}, -1 }, {{ 54, 35, 0}, 109}, {{}, -1 }, {{}, -1 }, {{ 70, 64, 1}, 236}, {{ 35, 28, 0}, 140}, {{ 32, 18, 0}, 104}, {{ 44, 51, 0}, 189}, {{ 46, 64, 1}, 94}, {{ 67, 30, 130}, 218}, {{ 68, 56, 0}, 95}, {{}, -1 }, {{ 68, 32, 0}, 126}, {{ 45, 50, 0}, 226}, {{ 55, 33, 2}, 152}, {{ 46, 24, 0}, 235}, {{}, -1 }, {{ 54, 46, 0}, 179}, {{}, -1 }, {{ 70, 64, 5}, 210}, {{ 70, 64, 6}, 225}, {{}, -1 }, {{ 44, 30, 41}, 198}, {{ 44, 2, 0}, 150}, {{ 44, 13, 0}, 182}, {{ 54, 35, 2}, 149}, {{ 54, 77, 1}, 181}, {{ 67, 65, 2}, 223}, {{ 54, 35, 4}, 193}, {{}, -1 }, {{}, -1 }, {{ 32, 0}, 133}, {{}, -1 }, {{ 67, 30, 84}, 176}, {{}, -1 }, {{}, -1 }, {{ 68, 32, 2}, 224}, {{ 32, 22, 0}, 142}, {{ 55, 28, 0}, 65}, {{ 32, 51, 0}, 91}, {{ 44, 3, 0}, 141}, {{ 44, 30, 32}, 103}, {{ 54, 35, 3}, 163}, {{ 44, 16, 0}, 111}, {{ 67, 65, 3}, 249}, {{ 46, 6, 0}, 99}, {{ 32, 47, 0}, 209}, {{ 55, 33, 1}, 77}, {{ 67, 46, 0}, 127}, {{ 32, 81, 1}, 108}, {{}, -1 }, {{ 46, 17, 0}, 151}, {{ 32, 23, 0}, 188}, {{ 68, 32, 3}, 237}, {{}, -1 }, {{ 54, 33, 1}, 139}, {{ 44, 1, 0}, 100}, {{}, -1 }, {{ 54, 35, 1}, 112}, {{}, -1 }, {{ 67, 65, 1}, 195}, {{ 54, 34, 0}, 82}, {{ 55, 28, 2}, 71}, {{ 102, 34, 1}, 242}, {{}, -1 }, {{ 55, 28, 4}, 199}, {{ 44, 8, 0}, 148}, {{}, -1 }, {{ 55, 29, 0}, 231}, {{ 68, 32, 1}, 125}, {{}, -1 }, {{ 44, 5, 0}, 227}, {{ 44, 6, 0}, 87}, {{ 54, 35, 5}, 186}, {{ 54, 56, 0}, 67}, {{ 32, 16, 0}, 115}, {{ 54, 32, 0}, 69}, {{ 67, 28, 0}, 90}, {{ 44, 17, 0}, 253}, {{ 55, 28, 3}, 88}, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{ 67, 19, 0}, 216}, {{}, -1 }, {{ 54, 34, 2}, 177}, {{ 32, 19, 0}, 254}, {{}, -1 }, {{ 32, 1, 0}, 143}, {{}, -1 }, {{ 55, 37, 1}, 121}, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{ 55, 28, 1}, 64}, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{ 54, 32, 2}, 106}, {{}, -1 }, {{ 54, 34, 3}, 229}, {{ 54, 32, 4}, 241}, {{ 32, 6, 0}, 169}, {{ 44, 28, 1}, 205}, {{}, -1 }, {{ 67, 32, 0}, 162}, {{}, -1 }, {{}, -1 }, {{ 32, 17, 0}, 131}, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{ 79, 28, 1}, 233}, {{}, -1 }, {{ 54, 32, 3}, 138}, {{ 54, 34, 1}, 132}, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{ 55, 29, 1}, 211}, {{}, -1 }, {{ 67, 84, 1}, 153}, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{ 54, 32, 1}, 85}, {{ 32, 32, 2}, 200}, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{ 32, 32, 3}, 156}, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{ 32, 100, 1}, 191} }; smalltalk-3.2.5/libgst/alloc.h0000644000175000017500000001405412123404352013155 00000000000000/******************************** -*- C -*- **************************** * * Memory allocation for Smalltalk * * ***********************************************************************/ /*********************************************************************** * * Copyright 2002, 2004, 2006, 2007, 2008 Free Software Foundation, Inc. * Written by Paolo Bonzini. * * This file is part of GNU Smalltalk. * * GNU Smalltalk is free software; you can redistribute it and/or modify it * under the terms of the GNU General Public License as published by the Free * Software Foundation; either version 2, or (at your option) any later * version. * * Linking GNU Smalltalk statically or dynamically with other modules is * making a combined work based on GNU Smalltalk. Thus, the terms and * conditions of the GNU General Public License cover the whole * combination. * * In addition, as a special exception, the Free Software Foundation * give you permission to combine GNU Smalltalk with free software * programs or libraries that are released under the GNU LGPL and with * independent programs running under the GNU Smalltalk virtual machine. * * You may copy and distribute such a system following the terms of the * GNU GPL for GNU Smalltalk and the licenses of the other code * concerned, provided that you include the source code of that other * code when and as the GNU GPL requires distribution of source code. * * Note that people who make modified versions of GNU Smalltalk are not * obligated to grant this special exception for their modified * versions; it is their choice whether to do so. The GNU General * Public License gives permission to release a modified version without * this exception; this exception also makes it possible to release a * modified version which carries forward this exception. * * GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or * FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for * more details. * * You should have received a copy of the GNU General Public License along with * GNU Smalltalk; see the file COPYING. If not, write to the Free Software * Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. ***********************************************************************/ #ifndef GST_ALLOC_H #define GST_ALLOC_H #define NUM_FREELISTS 47 /* Oh my God, how broken things sometimes are! */ #if defined small # undef small #endif typedef struct heap_freeobj { struct heap_freeobj *next; } heap_freeobj; typedef struct heap_block { size_t size; /* Size of objects in this block */ unsigned mmap_block : 1; /* Whether the block was mmap-ed */ unsigned user : 1; unsigned pad : 30; /* needed for linux/m68k? */ union { struct { int nr; /* Nr of objects in block */ int avail; /* Nr of objects available in block */ struct heap_freeobj *free; /* Next free sub-block */ struct heap_block *nfree; /* Next block on sub-freelist */ long double data[1]; /* Give appropriate alignment */ } small; struct { struct heap_block *next; /* Next block in freelist */ } free; union { long double align; /* Give appropriate alignment */ char data[1]; } large; } var; } heap_block; #define vSmall var.small #define vLarge var.large #define vFree var.free typedef struct heap_data heap_data; typedef void (*allocating_hook_t) (heap_data *, heap_block *, size_t); typedef heap_data *(*nomemory_hook_t) (heap_data *, size_t); struct heap_data { heap_block *freelist[NUM_FREELISTS]; int mmap_count; size_t heap_total, heap_allocation_size, heap_limit; int probes, failures, splits, matches; allocating_hook_t after_allocating, before_prim_freeing, after_prim_allocating; nomemory_hook_t nomemory; }; /* Allocate a chunk of N bytes from the independent heap H. Invoke the out-of-memory hook if the heap's limit is reached, and return NULL if memory cannot be allocated even after the hook returned. */ extern PTR _gst_mem_alloc (heap_data *h, size_t n) ATTRIBUTE_HIDDEN; /* Free the memory chunk pointed to by P, which was allocated from the independent heap H. */ extern void _gst_mem_free (heap_data *h, PTR p) ATTRIBUTE_HIDDEN; /* Resize the memory chunk pointed to by P, which was allocated from the independent heap H, so that its size becomes N. Return the new pointer. Invoke the out-of-memory hook if the heap's limit is reached, and return NULL if memory cannot be allocated even after the hook returned. */ extern PTR _gst_mem_realloc (heap_data *h, PTR p, size_t n) ATTRIBUTE_HIDDEN; /* Allocate a new, independent heap which allocates from the OS chunks of HEAP_ALLOCATION_SIZE bytes, up to a limit of HEAP_LIMIT bytes. */ extern heap_data *_gst_mem_new_heap (size_t heap_allocation_size, size_t heap_limit) ATTRIBUTE_HIDDEN; /* Allocate a chunk of N bytes using malloc. Exit if this amount of memory cannot be allocated. */ extern PTR xmalloc (size_t n) ATTRIBUTE_HIDDEN; /* Allocate a chunk of S*N bytes using malloc, clear it and return a pointer to its base. Exit if memory cannot be allocated. */ extern PTR xcalloc (size_t n, size_t s) ATTRIBUTE_HIDDEN; /* Resize the memory chunk pointed to by P, which was allocated using malloc, so that its size becomes N. Return the new pointer, or exit if the memory cannot be allocated. */ extern PTR xrealloc (PTR p, size_t n) ATTRIBUTE_HIDDEN; /* Allocate memory for a copy of the null-terminated string S using malloc, duplicate the contents of S, and return the pointer to the copy. Exit if the memory cannot be allocated. */ extern char *xstrdup (const char *s) ATTRIBUTE_HIDDEN; /* Free the chunk pointed to by P, which was allocated using malloc. */ extern void xfree (PTR p) ATTRIBUTE_HIDDEN; /* Print an error message, and exit if FATAL is non-zero. */ extern void nomemory (int fatal) ATTRIBUTE_HIDDEN; #define obstack_chunk_alloc xmalloc #define obstack_chunk_free xfree #endif smalltalk-3.2.5/libgst/sysdep.h0000644000175000017500000002434612123404352013377 00000000000000/******************************** -*- C -*- **************************** * * System specific module declarations * * ***********************************************************************/ /*********************************************************************** * * Copyright 1988,89,90,91,92,94,95,99,2000,2001,2002,2006,2007,2008,2009 * Free Software Foundation, Inc. * Written by Steve Byrne. * * This file is part of GNU Smalltalk. * * GNU Smalltalk is free software; you can redistribute it and/or modify it * under the terms of the GNU General Public License as published by the Free * Software Foundation; either version 2, or (at your option) any later * version. * * Linking GNU Smalltalk statically or dynamically with other modules is * making a combined work based on GNU Smalltalk. Thus, the terms and * conditions of the GNU General Public License cover the whole * combination. * * In addition, as a special exception, the Free Software Foundation * give you permission to combine GNU Smalltalk with free software * programs or libraries that are released under the GNU LGPL and with * independent programs running under the GNU Smalltalk virtual machine. * * You may copy and distribute such a system following the terms of the * GNU GPL for GNU Smalltalk and the licenses of the other code * concerned, provided that you include the source code of that other * code when and as the GNU GPL requires distribution of source code. * * Note that people who make modified versions of GNU Smalltalk are not * obligated to grant this special exception for their modified * versions; it is their choice whether to do so. The GNU General * Public License gives permission to release a modified version without * this exception; this exception also makes it possible to release a * modified version which carries forward this exception. * * GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or * FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for * more details. * * You should have received a copy of the GNU General Public License along with * GNU Smalltalk; see the file COPYING. If not, write to the Free Software * Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * ***********************************************************************/ #ifndef GST_SYSDEP_H #define GST_SYSDEP_H #ifdef sgi # define _BSD_SIGNALS #endif #ifndef SEEK_SET #define SEEK_SET 0 #define SEEK_CUR 1 #define SEEK_END 2 #endif #ifndef HAVE_SYS_MMAN_H #define PROT_READ 0x1 /* Page can be read. */ #define PROT_WRITE 0x2 /* Page can be written. */ #define PROT_EXEC 0x4 /* Page can be executed. */ #define PROT_NONE 0x0 /* Page can not be accessed. */ #endif /* These nice tests are simple, guaranteed and independent of byte order. */ #define IS_FINITE(dbl) (!IS_NAN((dbl) * 0.0)) #define IS_NAN(dbl) ((dbl) != (dbl)) typedef RETSIGTYPE (*SigHandler) (); /* The path to the executable. */ extern const char *_gst_executable_path; /* The count of nested _gst_disable_interrupts calls. */ extern int _gst_signal_count; /* Saves and returns the current state of the software interrupt system. Disables all interrupts. */ extern void _gst_disable_interrupts (mst_Boolean fromSignalHandler) ATTRIBUTE_HIDDEN; /* Restores the state of the interrupt system to that which it had when _gst_disable_interrupts was last invoked. */ extern void _gst_enable_interrupts (mst_Boolean fromSignalHandler) ATTRIBUTE_HIDDEN; /* Set the signal handler for signal SIGNUM to be HANDLERFUNC. Further interrupts are blocked within the signal if supported. (The signal handler should still call _gst_disable_interrupts and _gst_enable_interrupts passing true to fromSignalHandler). */ extern SigHandler _gst_set_signal_handler (int signum, SigHandler handlerFunc) ATTRIBUTE_HIDDEN; /* Establish FUNC to be called when DELTAMILLI milliseconds of process time have passed. */ extern void _gst_sigvtalrm_every (int deltaMilli, SigHandler func) ATTRIBUTE_HIDDEN; /* Establish SIGALRM to be called when the nanosecond clock reaches NSTIME nanoseconds. */ extern void _gst_sigalrm_at (int64_t nsTime) ATTRIBUTE_HIDDEN; /* Initialize system dependent stuff. */ extern void _gst_init_sysdep (void) ATTRIBUTE_HIDDEN; extern void _gst_init_sysdep_timer (void) ATTRIBUTE_HIDDEN; /* Arrange so that FUNC is called when I/O becomes possible on registered file descriptors, and set up FD to trigger the signal. */ extern void _gst_set_file_interrupt (int fd, SigHandler func) ATTRIBUTE_HIDDEN; /* Used for debugging. You set a breakpoint in the _gst_debug routine in the debugger, and have code call it when you want it to stop. Performs no action normally. */ extern void _gst_debug (void) ATTRIBUTE_HIDDEN; /* Sleeps for US milliseconds. */ extern void _gst_usleep (int us) ATTRIBUTE_HIDDEN; /* Returns a (hopefully) monotonic time value in milliseconds */ extern uint64_t _gst_get_milli_time (void) ATTRIBUTE_HIDDEN; /* Returns a (hopefully) monotonic time value in nanoseconds */ extern uint64_t _gst_get_ns_time (void) ATTRIBUTE_HIDDEN; /* Returns the time in seconds since midnight Jan 1, 1970 (standard UNIX type time). */ extern time_t _gst_get_time (void) ATTRIBUTE_HIDDEN; /* Returns whether FILE1 is newer (or last modified at the same time as) FILE2. Returns true if FILE2 is not readable, false if FILE1 is not readable. */ extern mst_Boolean _gst_file_is_newer (const char *file1, const char *file2) ATTRIBUTE_HIDDEN; /* Sets the time when FILENAME was last modified. The times are in seconds, relative to 1 Jan 2000. */ extern int _gst_set_file_access_times (const char *name, long new_atime, long new_mtime) ATTRIBUTE_HIDDEN; /* Converts the given time (expressed in seconds since midnight Jan 1, 1970, and in Universal Coordinated Time) into a local time. */ extern time_t _gst_adjust_time_zone (time_t t) ATTRIBUTE_HIDDEN; /* Answer the current bias in seconds between UTC and local time */ extern long _gst_current_time_zone_bias (void) ATTRIBUTE_HIDDEN; /* Returns the full path name for a given file. */ extern char *_gst_get_full_file_name (const char *fileName) ATTRIBUTE_HIDDEN; /* Returns the path name for the current directory, without trailing delimiter. The return value is a pointer to allocated string for current path name. Caller has responsibility for freeing the returned value when through. */ extern char *_gst_get_cur_dir_name (void) ATTRIBUTE_HIDDEN; /* Returns the name of the current time zone. */ extern char *_gst_current_time_zone_name (void) ATTRIBUTE_HIDDEN; /* Portable implementation of mprotect. The implementation does not necessarily support PROT_EXEC or PROT_WRITE without PROT_READ. The only guarantees are that no writing will be allowed without PROT_WRITE and no access will be allowed for PROT_NONE. */ extern int _gst_mem_protect (PTR addr, size_t len, int prot) ATTRIBUTE_HIDDEN; /* Returns true if the file named FILENAME exists has the given permission for the current user. Returns false otherwise. */ extern mst_Boolean _gst_file_is_readable (const char *fileName) ATTRIBUTE_HIDDEN; extern mst_Boolean _gst_file_is_writeable (const char *fileName) ATTRIBUTE_HIDDEN; extern mst_Boolean _gst_file_is_executable (const char *fileName) ATTRIBUTE_HIDDEN; /* Return a path to the executable given argv[0]. */ extern void _gst_set_executable_path (const char *argv0) ATTRIBUTE_HIDDEN; /* Return the absolute path for PATH, interpreted relative to the executable. */ char *_gst_relocate_path (const char *path) ATTRIBUTE_HIDDEN; /* Answer true if the file descriptor FD is associated to a pipe (it cannot be seeked through). */ extern mst_Boolean _gst_is_pipe (int fd) ATTRIBUTE_HIDDEN; /* Similar to popen, but supports two-way pipes (achieved through tty's) and returns a file descriptor. */ extern int _gst_open_pipe (const char *command, const char *mode) ATTRIBUTE_HIDDEN; /* Similar to fopen, but returns a file descriptor. */ extern int _gst_open_file (const char *filename, const char *mode) ATTRIBUTE_HIDDEN; /* Read SIZE bytes into BUFFER from the file descriptor, FD. */ extern ssize_t _gst_read (int fd, PTR buffer, size_t size) ATTRIBUTE_HIDDEN; /* Write SIZE bytes of BUFFER into the file descriptor, FD. */ extern ssize_t _gst_write (int fd, PTR buffer, size_t size) ATTRIBUTE_HIDDEN; /* Read SIZE bytes into BUFFER from the file descriptor for a socket, FD. */ extern ssize_t _gst_recv (int fd, PTR buffer, size_t size, int flags) ATTRIBUTE_HIDDEN; /* Write SIZE bytes of BUFFER into the file descriptor for a socket, FD. */ extern ssize_t _gst_send (int fd, PTR buffer, size_t size, int flags) ATTRIBUTE_HIDDEN; /* Writes a debug message with the given formatting. */ extern void _gst_debugf (const char *, ...) ATTRIBUTE_PRINTF_1 ATTRIBUTE_HIDDEN; /* Do an anonymous memory map of SIZE bytes. */ extern PTR _gst_osmem_alloc (size_t size) ATTRIBUTE_HIDDEN; /* Unmap the SIZE bytes at PTR. */ extern void _gst_osmem_free (PTR ptr, size_t size) ATTRIBUTE_HIDDEN; /* Reserve SIZE bytes of the address space without allocating them. */ extern PTR _gst_osmem_reserve (PTR base, size_t size) ATTRIBUTE_HIDDEN; /* Release SIZE bytes of the address space starting from BASE. */ extern void _gst_osmem_release (PTR base, size_t size) ATTRIBUTE_HIDDEN; /* Actually allocate SIZE bytes of address space, starting from BASE, that have already been reserved. */ extern PTR _gst_osmem_commit (PTR base, size_t size) ATTRIBUTE_HIDDEN; /* Free the memory used by SIZE bytes of address space, starting from BASE, but keep the addresses reserved. */ extern void _gst_osmem_decommit (PTR base, size_t size) ATTRIBUTE_HIDDEN; /* Synchronously wait for FD to have input on it. */ extern void _gst_wait_for_input (int fd) ATTRIBUTE_HIDDEN; #endif /* GST_SYSDEP_H */ smalltalk-3.2.5/libgst/byte.def0000644000175000017500000013330312123404352013334 00000000000000/******************************** -*- C -*- **************************** * * Byte Code definitions. * * ***********************************************************************/ /*********************************************************************** * * Copyright 2003, 2006 Free Software Foundation, Inc. * Written by Paolo Bonzini. * * This file is part of GNU Smalltalk. * * GNU Smalltalk is free software; you can redistribute it and/or modify it * under the terms of the GNU General Public License as published by the Free * Software Foundation; either version 2, or (at your option) any later * version. * * Linking GNU Smalltalk statically or dynamically with other modules is * making a combined work based on GNU Smalltalk. Thus, the terms and * conditions of the GNU General Public License cover the whole * combination. * * In addition, as a special exception, the Free Software Foundation * give you permission to combine GNU Smalltalk with free software * programs or libraries that are released under the GNU LGPL and with * independent programs running under the GNU Smalltalk virtual machine. * * You may copy and distribute such a system following the terms of the * GNU GPL for GNU Smalltalk and the licenses of the other code * concerned, provided that you include the source code of that other * code when and as the GNU GPL requires distribution of source code. * * Note that people who make modified versions of GNU Smalltalk are not * obligated to grant this special exception for their modified * versions; it is their choice whether to do so. The GNU General * Public License gives permission to release a modified version without * this exception; this exception also makes it possible to release a * modified version which carries forward this exception. * * GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or * FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for * more details. * * You should have received a copy of the GNU General Public License along with * GNU Smalltalk; see the file COPYING. If not, write to the Free Software * Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * ***********************************************************************/ /* This is C code which is wrapped within patterns; the patterns can be BEGIN/END a la awk, numbers, or ranges of numbers separated by ``..''. Patterns don't fall through, unlike C's switch statements. There are special keywords: extract advances the instruction pointer and reads bits from it; dispatch goes to the named section of the MATCH_BYTECODES occurrence; break gets out of the MATCH_BYTECODES block; continue matches the next bytecode without executing anything in the MATCH_BYTECODES occurrence. In awk tradition, we also have a couple of predefined variables whose name is in uppercase... :-) these are IP which is the current instruction pointer (including the bytecodes that were dissected with extract), and IP0 which is the value of the instruction pointer on entrance to MATCH_BYTECODES (it is never changed, not even by continue statements). You can see them used in the jump patterns below (40..43) */ /* Define the bytecodes and their arguments */ SEND_ARITH (n); SEND_SPECIAL (n); SEND (n, super, num_args); SEND_IMMEDIATE (n, super); PUSH_TEMPORARY_VARIABLE (n); PUSH_OUTER_TEMP (n, scopes); PUSH_LIT_VARIABLE (n); PUSH_RECEIVER_VARIABLE (n); STORE_TEMPORARY_VARIABLE (n); STORE_OUTER_TEMP (n, scopes); STORE_LIT_VARIABLE (n); STORE_RECEIVER_VARIABLE (n); JUMP (ofs); POP_JUMP_TRUE (ofs); POP_JUMP_FALSE (ofs); PUSH_INTEGER (n); PUSH_SELF; PUSH_SPECIAL (n); PUSH_LIT_CONSTANT (n); POP_INTO_NEW_STACKTOP (n); POP_STACK_TOP; MAKE_DIRTY_BLOCK; RETURN_METHOD_STACK_TOP; RETURN_CONTEXT_STACK_TOP; DUP_STACK_TOP; EXIT_INTERPRETER; LINE_NUMBER_BYTECODE (n); INVALID (opcode, arg); /* Automatically generated by superops. Do not modify past this line! */ /* PLUS_SPECIAL(*) */ 0 { extract opcode (8), arg_lsb (8); dispatch SEND_ARITH (0); } /* MINUS_SPECIAL(*) */ 1 { extract opcode (8), arg_lsb (8); dispatch SEND_ARITH (1); } /* LESS_THAN_SPECIAL(*) */ 2 { extract opcode (8), arg_lsb (8); dispatch SEND_ARITH (2); } /* GREATER_THAN_SPECIAL(*) */ 3 { extract opcode (8), arg_lsb (8); dispatch SEND_ARITH (3); } /* LESS_EQUAL_SPECIAL(*) */ 4 { extract opcode (8), arg_lsb (8); dispatch SEND_ARITH (4); } /* GREATER_EQUAL_SPECIAL(*) */ 5 { extract opcode (8), arg_lsb (8); dispatch SEND_ARITH (5); } /* EQUAL_SPECIAL(*) */ 6 { extract opcode (8), arg_lsb (8); dispatch SEND_ARITH (6); } /* NOT_EQUAL_SPECIAL(*) */ 7 { extract opcode (8), arg_lsb (8); dispatch SEND_ARITH (7); } /* TIMES_SPECIAL(*) */ 8 { extract opcode (8), arg_lsb (8); dispatch SEND_ARITH (8); } /* DIVIDE_SPECIAL(*) */ 9 { extract opcode (8), arg_lsb (8); dispatch SEND_ARITH (9); } /* REMAINDER_SPECIAL(*) */ 10 { extract opcode (8), arg_lsb (8); dispatch SEND_ARITH (10); } /* BIT_XOR_SPECIAL(*) */ 11 { extract opcode (8), arg_lsb (8); dispatch SEND_ARITH (11); } /* BIT_SHIFT_SPECIAL(*) */ 12 { extract opcode (8), arg_lsb (8); dispatch SEND_ARITH (12); } /* INTEGER_DIVIDE_SPECIAL(*) */ 13 { extract opcode (8), arg_lsb (8); dispatch SEND_ARITH (13); } /* BIT_AND_SPECIAL(*) */ 14 { extract opcode (8), arg_lsb (8); dispatch SEND_ARITH (14); } /* BIT_OR_SPECIAL(*) */ 15 { extract opcode (8), arg_lsb (8); dispatch SEND_ARITH (15); } /* AT_SPECIAL(*) */ 16 { extract opcode (8), arg_lsb (8); dispatch SEND_SPECIAL (0); } /* AT_PUT_SPECIAL(*) */ 17 { extract opcode (8), arg_lsb (8); dispatch SEND_SPECIAL (1); } /* SIZE_SPECIAL(*) */ 18 { extract opcode (8), arg_lsb (8); dispatch SEND_SPECIAL (2); } /* CLASS_SPECIAL(*) */ 19 { extract opcode (8), arg_lsb (8); dispatch SEND_SPECIAL (3); } /* IS_NIL_SPECIAL(*) */ 20 { extract opcode (8), arg_lsb (8); dispatch SEND_SPECIAL (4); } /* NOT_NIL_SPECIAL(*) */ 21 { extract opcode (8), arg_lsb (8); dispatch SEND_SPECIAL (5); } /* VALUE_SPECIAL(*) */ 22 { extract opcode (8), arg_lsb (8); dispatch SEND_SPECIAL (6); } /* VALUE_COLON_SPECIAL(*) */ 23 { extract opcode (8), arg_lsb (8); dispatch SEND_SPECIAL (7); } /* SAME_OBJECT_SPECIAL(*) */ 24 { extract opcode (8), arg_lsb (8); dispatch SEND_SPECIAL (8); } /* JAVA_AS_INT_SPECIAL(*) */ 25 { extract opcode (8), arg_lsb (8); dispatch SEND_SPECIAL (9); } /* JAVA_AS_LONG_SPECIAL(*) */ 26 { extract opcode (8), arg_lsb (8); dispatch SEND_SPECIAL (10); } /* invalid bytecode */ 27 { extract opcode (8), arg_lsb (8); dispatch INVALID (27, arg | arg_lsb); } /* SEND(*) */ 28 { extract opcode (8), arg_lsb (8); dispatch SEND (arg >> 8, 0, arg_lsb); } /* SEND_SUPER(*) */ 29 { extract opcode (8), arg_lsb (8); dispatch SEND (arg >> 8, 1, arg_lsb); } /* SEND_IMMEDIATE(*) */ 30 { extract opcode (8), arg_lsb (8); dispatch SEND_IMMEDIATE (arg | arg_lsb, 0); } /* SEND_SUPER_IMMEDIATE(*) */ 31 { extract opcode (8), arg_lsb (8); dispatch SEND_IMMEDIATE (arg | arg_lsb, 1); } /* PUSH_TEMPORARY_VARIABLE(*) */ 32 { extract opcode (8), arg_lsb (8); dispatch PUSH_TEMPORARY_VARIABLE (arg | arg_lsb); } /* PUSH_OUTER_TEMP(*) */ 33 { extract opcode (8), arg_lsb (8); dispatch PUSH_OUTER_TEMP (arg >> 8, arg_lsb); } /* PUSH_LIT_VARIABLE(*) */ 34 { extract opcode (8), arg_lsb (8); dispatch PUSH_LIT_VARIABLE (arg | arg_lsb); } /* PUSH_RECEIVER_VARIABLE(*) */ 35 { extract opcode (8), arg_lsb (8); dispatch PUSH_RECEIVER_VARIABLE (arg | arg_lsb); } /* STORE_TEMPORARY_VARIABLE(*) */ 36 { extract opcode (8), arg_lsb (8); dispatch STORE_TEMPORARY_VARIABLE (arg | arg_lsb); } /* STORE_OUTER_TEMP(*) */ 37 { extract opcode (8), arg_lsb (8); dispatch STORE_OUTER_TEMP (arg >> 8, arg_lsb); } /* STORE_LIT_VARIABLE(*) */ 38 { extract opcode (8), arg_lsb (8); dispatch STORE_LIT_VARIABLE (arg | arg_lsb); } /* STORE_RECEIVER_VARIABLE(*) */ 39 { extract opcode (8), arg_lsb (8); dispatch STORE_RECEIVER_VARIABLE (arg | arg_lsb); } /* JUMP_BACK(*) */ 40 { extract opcode (8), arg_lsb (8); dispatch JUMP (IP - IP0 - (arg | arg_lsb)); } /* JUMP(*) */ 41 { extract opcode (8), arg_lsb (8); dispatch JUMP (IP - IP0 + (arg | arg_lsb)); } /* POP_JUMP_TRUE(*) */ 42 { extract opcode (8), arg_lsb (8); dispatch POP_JUMP_TRUE (IP - IP0 + (arg | arg_lsb)); } /* POP_JUMP_FALSE(*) */ 43 { extract opcode (8), arg_lsb (8); dispatch POP_JUMP_FALSE (IP - IP0 + (arg | arg_lsb)); } /* PUSH_INTEGER(*) */ 44 { extract opcode (8), arg_lsb (8); dispatch PUSH_INTEGER (arg | arg_lsb); } /* PUSH_SPECIAL(*) */ 45 { extract opcode (8), arg_lsb (8); dispatch PUSH_SPECIAL (arg | arg_lsb); } /* PUSH_LIT_CONSTANT(*) */ 46 { extract opcode (8), arg_lsb (8); dispatch PUSH_LIT_CONSTANT (arg | arg_lsb); } /* POP_INTO_NEW_STACKTOP(*) */ 47 { extract opcode (8), arg_lsb (8); dispatch POP_INTO_NEW_STACKTOP (arg | arg_lsb); } /* POP_STACK_TOP(*) */ 48 { extract opcode (8), arg_lsb (8); dispatch POP_STACK_TOP; } /* MAKE_DIRTY_BLOCK(*) */ 49 { extract opcode (8), arg_lsb (8); dispatch MAKE_DIRTY_BLOCK; } /* RETURN_METHOD_STACK_TOP(*) */ 50 { extract opcode (8), arg_lsb (8); dispatch RETURN_METHOD_STACK_TOP; } /* RETURN_CONTEXT_STACK_TOP(*) */ 51 { extract opcode (8), arg_lsb (8); dispatch RETURN_CONTEXT_STACK_TOP; } /* DUP_STACK_TOP(*) */ 52 { extract opcode (8), arg_lsb (8); dispatch DUP_STACK_TOP; } /* EXIT_INTERPRETER(*) */ 53 { extract opcode (8), arg_lsb (8); dispatch EXIT_INTERPRETER; } /* LINE_NUMBER_BYTECODE(*) */ 54 { extract opcode (8), arg_lsb (8); dispatch LINE_NUMBER_BYTECODE (arg | arg_lsb); } /* EXT_BYTE(*) */ 55 { extract opcode (8), arg_lsb (8); arg = (arg | arg_lsb) << 8; continue; } /* PUSH_SELF(*) */ 56 { extract opcode (8), arg_lsb (8); dispatch PUSH_SELF; } /* invalid bytecode */ 57 { extract opcode (8), arg_lsb (8); dispatch INVALID (57, arg | arg_lsb); } /* invalid bytecode */ 58 { extract opcode (8), arg_lsb (8); dispatch INVALID (58, arg | arg_lsb); } /* invalid bytecode */ 59 { extract opcode (8), arg_lsb (8); dispatch INVALID (59, arg | arg_lsb); } /* invalid bytecode */ 60 { extract opcode (8), arg_lsb (8); dispatch INVALID (60, arg | arg_lsb); } /* invalid bytecode */ 61 { extract opcode (8), arg_lsb (8); dispatch INVALID (61, arg | arg_lsb); } /* invalid bytecode */ 62 { extract opcode (8), arg_lsb (8); dispatch INVALID (62, arg | arg_lsb); } /* invalid bytecode */ 63 { extract opcode (8), arg_lsb (8); dispatch INVALID (63, arg | arg_lsb); } /* EXT_BYTE(*) SEND(1) */ 64 { extract opcode (8), arg_lsb (8); dispatch SEND (arg | arg_lsb, 0, 1); } /* EXT_BYTE(*) SEND(0) */ 65 { extract opcode (8), arg_lsb (8); dispatch SEND (arg | arg_lsb, 0, 0); } /* PUSH_SELF(0) RETURN_CONTEXT_STACK_TOP(*) */ 66 { extract opcode (8), arg_lsb (8); dispatch PUSH_SELF; dispatch RETURN_CONTEXT_STACK_TOP; } /* LINE_NUMBER_BYTECODE(*) PUSH_SELF(0) */ 67 { extract opcode (8), arg_lsb (8); dispatch LINE_NUMBER_BYTECODE (arg | arg_lsb); dispatch PUSH_SELF; } /* LINE_NUMBER_BYTECODE(*) POP_STACK_TOP(0) */ 68 { extract opcode (8), arg_lsb (8); dispatch LINE_NUMBER_BYTECODE (arg | arg_lsb); dispatch POP_STACK_TOP; } /* LINE_NUMBER_BYTECODE(*) PUSH_TEMPORARY_VARIABLE(0) */ 69 { extract opcode (8), arg_lsb (8); dispatch LINE_NUMBER_BYTECODE (arg | arg_lsb); dispatch PUSH_TEMPORARY_VARIABLE (0); } /* PUSH_LIT_CONSTANT(*) MAKE_DIRTY_BLOCK(0) */ 70 { extract opcode (8), arg_lsb (8); dispatch PUSH_LIT_CONSTANT (arg | arg_lsb); dispatch MAKE_DIRTY_BLOCK; } /* EXT_BYTE(*) SEND(2) */ 71 { extract opcode (8), arg_lsb (8); dispatch SEND (arg | arg_lsb, 0, 2); } /* POP_STACK_TOP(0) DUP_STACK_TOP(*) */ 72 { extract opcode (8), arg_lsb (8); dispatch POP_STACK_TOP; dispatch DUP_STACK_TOP; } /* PUSH_TEMPORARY_VARIABLE(0) SEND_IMMEDIATE(*) */ 73 { extract opcode (8), arg_lsb (8); dispatch PUSH_TEMPORARY_VARIABLE (0); dispatch SEND_IMMEDIATE (arg | arg_lsb, 0); } /* PUSH_SELF(0) EXT_BYTE(*) SEND(0) */ 74 { extract opcode (8), arg_lsb (8); dispatch PUSH_SELF; dispatch SEND (arg | arg_lsb, 0, 0); } /* PUSH_SPECIAL(*) RETURN_CONTEXT_STACK_TOP(0) */ 75 { extract opcode (8), arg_lsb (8); dispatch PUSH_SPECIAL (arg | arg_lsb); dispatch RETURN_CONTEXT_STACK_TOP; } /* PUSH_SELF(0) SEND_IMMEDIATE(*) */ 76 { extract opcode (8), arg_lsb (8); dispatch PUSH_SELF; dispatch SEND_IMMEDIATE (arg | arg_lsb, 0); } /* EXT_BYTE(*) PUSH_OUTER_TEMP(1) */ 77 { extract opcode (8), arg_lsb (8); dispatch PUSH_OUTER_TEMP (arg | arg_lsb, 1); } /* STORE_TEMPORARY_VARIABLE(*) POP_STACK_TOP(0) */ 78 { extract opcode (8), arg_lsb (8); dispatch STORE_TEMPORARY_VARIABLE (arg | arg_lsb); dispatch POP_STACK_TOP; } /* PUSH_SELF(0) PUSH_TEMPORARY_VARIABLE(*) */ 79 { extract opcode (8), arg_lsb (8); dispatch PUSH_SELF; dispatch PUSH_TEMPORARY_VARIABLE (arg | arg_lsb); } /* STORE_RECEIVER_VARIABLE(*) PUSH_SELF(0) RETURN_CONTEXT_STACK_TOP(0) */ 80 { extract opcode (8), arg_lsb (8); dispatch STORE_RECEIVER_VARIABLE (arg | arg_lsb); dispatch PUSH_SELF; dispatch RETURN_CONTEXT_STACK_TOP; } /* PUSH_INTEGER(*) PLUS_SPECIAL(0) */ 81 { extract opcode (8), arg_lsb (8); dispatch PUSH_INTEGER (arg | arg_lsb); dispatch SEND_ARITH (0); } /* LINE_NUMBER_BYTECODE(*) PUSH_LIT_VARIABLE(0) */ 82 { extract opcode (8), arg_lsb (8); dispatch LINE_NUMBER_BYTECODE (arg | arg_lsb); dispatch PUSH_LIT_VARIABLE (0); } /* PUSH_TEMPORARY_VARIABLE(0) PUSH_TEMPORARY_VARIABLE(*) */ 83 { extract opcode (8), arg_lsb (8); dispatch PUSH_TEMPORARY_VARIABLE (0); dispatch PUSH_TEMPORARY_VARIABLE (arg | arg_lsb); } /* PUSH_TEMPORARY_VARIABLE(0) SEND(*) */ 84 { extract opcode (8), arg_lsb (8); dispatch PUSH_TEMPORARY_VARIABLE (0); dispatch SEND (arg >> 8, 0, arg_lsb); } /* LINE_NUMBER_BYTECODE(*) PUSH_TEMPORARY_VARIABLE(1) */ 85 { extract opcode (8), arg_lsb (8); dispatch LINE_NUMBER_BYTECODE (arg | arg_lsb); dispatch PUSH_TEMPORARY_VARIABLE (1); } /* IS_NIL_SPECIAL(0) POP_JUMP_FALSE(*) */ 86 { extract opcode (8), arg_lsb (8); dispatch SEND_SPECIAL (4); dispatch POP_JUMP_FALSE (IP - IP0 + (arg | arg_lsb)); } /* PUSH_INTEGER(*) EQUAL_SPECIAL(0) */ 87 { extract opcode (8), arg_lsb (8); dispatch PUSH_INTEGER (arg | arg_lsb); dispatch SEND_ARITH (6); } /* EXT_BYTE(*) SEND(3) */ 88 { extract opcode (8), arg_lsb (8); dispatch SEND (arg | arg_lsb, 0, 3); } /* PUSH_TEMPORARY_VARIABLE(0) EXT_BYTE(*) SEND(1) */ 89 { extract opcode (8), arg_lsb (8); dispatch PUSH_TEMPORARY_VARIABLE (0); dispatch SEND (arg | arg_lsb, 0, 1); } /* LINE_NUMBER_BYTECODE(*) PUSH_SELF(0) SEND(0) */ 90 { extract opcode (8), arg_lsb (8); dispatch LINE_NUMBER_BYTECODE (arg | arg_lsb); dispatch PUSH_SELF; dispatch SEND (0, 0, 0); } /* PUSH_TEMPORARY_VARIABLE(*) RETURN_CONTEXT_STACK_TOP(0) */ 91 { extract opcode (8), arg_lsb (8); dispatch PUSH_TEMPORARY_VARIABLE (arg | arg_lsb); dispatch RETURN_CONTEXT_STACK_TOP; } /* PUSH_LIT_CONSTANT(*) SEND_IMMEDIATE(36) */ 92 { extract opcode (8), arg_lsb (8); dispatch PUSH_LIT_CONSTANT (arg | arg_lsb); dispatch SEND_IMMEDIATE (36, 0); } /* SAME_OBJECT_SPECIAL(0) POP_JUMP_FALSE(*) */ 93 { extract opcode (8), arg_lsb (8); dispatch SEND_SPECIAL (8); dispatch POP_JUMP_FALSE (IP - IP0 + (arg | arg_lsb)); } /* PUSH_LIT_CONSTANT(*) EXT_BYTE(1) SEND(1) */ 94 { extract opcode (8), arg_lsb (8); dispatch PUSH_LIT_CONSTANT (arg | arg_lsb); dispatch SEND (1, 0, 1); } /* LINE_NUMBER_BYTECODE(*) POP_STACK_TOP(0) PUSH_SELF(0) */ 95 { extract opcode (8), arg_lsb (8); dispatch LINE_NUMBER_BYTECODE (arg | arg_lsb); dispatch POP_STACK_TOP; dispatch PUSH_SELF; } /* POP_STACK_TOP(0) DUP_STACK_TOP(0) LINE_NUMBER_BYTECODE(*) */ 96 { extract opcode (8), arg_lsb (8); dispatch POP_STACK_TOP; dispatch DUP_STACK_TOP; dispatch LINE_NUMBER_BYTECODE (arg | arg_lsb); } /* PUSH_TEMPORARY_VARIABLE(0) EXT_BYTE(*) SEND(0) */ 97 { extract opcode (8), arg_lsb (8); dispatch PUSH_TEMPORARY_VARIABLE (0); dispatch SEND (arg | arg_lsb, 0, 0); } /* PUSH_TEMPORARY_VARIABLE(1) SEND_IMMEDIATE(*) */ 98 { extract opcode (8), arg_lsb (8); dispatch PUSH_TEMPORARY_VARIABLE (1); dispatch SEND_IMMEDIATE (arg | arg_lsb, 0); } /* PUSH_LIT_CONSTANT(*) EQUAL_SPECIAL(0) */ 99 { extract opcode (8), arg_lsb (8); dispatch PUSH_LIT_CONSTANT (arg | arg_lsb); dispatch SEND_ARITH (6); } /* PUSH_INTEGER(*) MINUS_SPECIAL(0) */ 100 { extract opcode (8), arg_lsb (8); dispatch PUSH_INTEGER (arg | arg_lsb); dispatch SEND_ARITH (1); } /* DUP_STACK_TOP(0) POP_JUMP_FALSE(*) */ 101 { extract opcode (8), arg_lsb (8); dispatch DUP_STACK_TOP; dispatch POP_JUMP_FALSE (IP - IP0 + (arg | arg_lsb)); } /* POP_STACK_TOP(0) LINE_NUMBER_BYTECODE(*) */ 102 { extract opcode (8), arg_lsb (8); dispatch POP_STACK_TOP; dispatch LINE_NUMBER_BYTECODE (arg | arg_lsb); } /* PUSH_INTEGER(*) SEND_IMMEDIATE(32) */ 103 { extract opcode (8), arg_lsb (8); dispatch PUSH_INTEGER (arg | arg_lsb); dispatch SEND_IMMEDIATE (32, 0); } /* PUSH_TEMPORARY_VARIABLE(*) SIZE_SPECIAL(0) */ 104 { extract opcode (8), arg_lsb (8); dispatch PUSH_TEMPORARY_VARIABLE (arg | arg_lsb); dispatch SEND_SPECIAL (2); } /* PUSH_SELF(0) SEND(*) */ 105 { extract opcode (8), arg_lsb (8); dispatch PUSH_SELF; dispatch SEND (arg >> 8, 0, arg_lsb); } /* LINE_NUMBER_BYTECODE(*) PUSH_TEMPORARY_VARIABLE(2) */ 106 { extract opcode (8), arg_lsb (8); dispatch LINE_NUMBER_BYTECODE (arg | arg_lsb); dispatch PUSH_TEMPORARY_VARIABLE (2); } /* POP_STACK_TOP(0) SEND_IMMEDIATE(*) */ 107 { extract opcode (8), arg_lsb (8); dispatch POP_STACK_TOP; dispatch SEND_IMMEDIATE (arg | arg_lsb, 0); } /* PUSH_TEMPORARY_VARIABLE(*) PUSH_INTEGER(1) PLUS_SPECIAL(0) */ 108 { extract opcode (8), arg_lsb (8); dispatch PUSH_TEMPORARY_VARIABLE (arg | arg_lsb); dispatch PUSH_INTEGER (1); dispatch SEND_ARITH (0); } /* LINE_NUMBER_BYTECODE(*) PUSH_RECEIVER_VARIABLE(0) */ 109 { extract opcode (8), arg_lsb (8); dispatch LINE_NUMBER_BYTECODE (arg | arg_lsb); dispatch PUSH_RECEIVER_VARIABLE (0); } /* PUSH_LIT_CONSTANT(*) SEND_IMMEDIATE(38) */ 110 { extract opcode (8), arg_lsb (8); dispatch PUSH_LIT_CONSTANT (arg | arg_lsb); dispatch SEND_IMMEDIATE (38, 0); } /* PUSH_INTEGER(*) AT_SPECIAL(0) */ 111 { extract opcode (8), arg_lsb (8); dispatch PUSH_INTEGER (arg | arg_lsb); dispatch SEND_SPECIAL (0); } /* LINE_NUMBER_BYTECODE(*) PUSH_RECEIVER_VARIABLE(1) */ 112 { extract opcode (8), arg_lsb (8); dispatch LINE_NUMBER_BYTECODE (arg | arg_lsb); dispatch PUSH_RECEIVER_VARIABLE (1); } /* PUSH_TEMPORARY_VARIABLE(0) PUSH_LIT_CONSTANT(*) */ 113 { extract opcode (8), arg_lsb (8); dispatch PUSH_TEMPORARY_VARIABLE (0); dispatch PUSH_LIT_CONSTANT (arg | arg_lsb); } /* DUP_STACK_TOP(0) POP_JUMP_TRUE(*) */ 114 { extract opcode (8), arg_lsb (8); dispatch DUP_STACK_TOP; dispatch POP_JUMP_TRUE (IP - IP0 + (arg | arg_lsb)); } /* PUSH_TEMPORARY_VARIABLE(*) AT_SPECIAL(0) */ 115 { extract opcode (8), arg_lsb (8); dispatch PUSH_TEMPORARY_VARIABLE (arg | arg_lsb); dispatch SEND_SPECIAL (0); } /* PUSH_TEMPORARY_VARIABLE(2) SEND_IMMEDIATE(*) */ 116 { extract opcode (8), arg_lsb (8); dispatch PUSH_TEMPORARY_VARIABLE (2); dispatch SEND_IMMEDIATE (arg | arg_lsb, 0); } /* PUSH_LIT_CONSTANT(*) SEND_IMMEDIATE(49) */ 117 { extract opcode (8), arg_lsb (8); dispatch PUSH_LIT_CONSTANT (arg | arg_lsb); dispatch SEND_IMMEDIATE (49, 0); } /* STORE_TEMPORARY_VARIABLE(1) LINE_NUMBER_BYTECODE(*) POP_STACK_TOP(0) */ 118 { extract opcode (8), arg_lsb (8); dispatch STORE_TEMPORARY_VARIABLE (1); dispatch LINE_NUMBER_BYTECODE (arg | arg_lsb); dispatch POP_STACK_TOP; } /* PUSH_TEMPORARY_VARIABLE(1) EXT_BYTE(*) SEND(1) */ 119 { extract opcode (8), arg_lsb (8); dispatch PUSH_TEMPORARY_VARIABLE (1); dispatch SEND (arg | arg_lsb, 0, 1); } /* STORE_RECEIVER_VARIABLE(*) POP_STACK_TOP(0) */ 120 { extract opcode (8), arg_lsb (8); dispatch STORE_RECEIVER_VARIABLE (arg | arg_lsb); dispatch POP_STACK_TOP; } /* EXT_BYTE(*) STORE_OUTER_TEMP(1) */ 121 { extract opcode (8), arg_lsb (8); dispatch STORE_OUTER_TEMP (arg | arg_lsb, 1); } /* PUSH_INTEGER(*) SEND_IMMEDIATE(96) */ 122 { extract opcode (8), arg_lsb (8); dispatch PUSH_INTEGER (arg | arg_lsb); dispatch SEND_IMMEDIATE (96, 0); } /* POP_STACK_TOP(0) PUSH_TEMPORARY_VARIABLE(*) */ 123 { extract opcode (8), arg_lsb (8); dispatch POP_STACK_TOP; dispatch PUSH_TEMPORARY_VARIABLE (arg | arg_lsb); } /* PUSH_RECEIVER_VARIABLE(*) RETURN_CONTEXT_STACK_TOP(0) */ 124 { extract opcode (8), arg_lsb (8); dispatch PUSH_RECEIVER_VARIABLE (arg | arg_lsb); dispatch RETURN_CONTEXT_STACK_TOP; } /* LINE_NUMBER_BYTECODE(*) POP_STACK_TOP(0) PUSH_TEMPORARY_VARIABLE(1) */ 125 { extract opcode (8), arg_lsb (8); dispatch LINE_NUMBER_BYTECODE (arg | arg_lsb); dispatch POP_STACK_TOP; dispatch PUSH_TEMPORARY_VARIABLE (1); } /* LINE_NUMBER_BYTECODE(*) POP_STACK_TOP(0) PUSH_TEMPORARY_VARIABLE(0) */ 126 { extract opcode (8), arg_lsb (8); dispatch LINE_NUMBER_BYTECODE (arg | arg_lsb); dispatch POP_STACK_TOP; dispatch PUSH_TEMPORARY_VARIABLE (0); } /* LINE_NUMBER_BYTECODE(*) PUSH_SELF(0) PUSH_LIT_CONSTANT(0) */ 127 { extract opcode (8), arg_lsb (8); dispatch LINE_NUMBER_BYTECODE (arg | arg_lsb); dispatch PUSH_SELF; dispatch PUSH_LIT_CONSTANT (0); } /* PUSH_LIT_CONSTANT(*) RETURN_CONTEXT_STACK_TOP(0) */ 128 { extract opcode (8), arg_lsb (8); dispatch PUSH_LIT_CONSTANT (arg | arg_lsb); dispatch RETURN_CONTEXT_STACK_TOP; } /* PUSH_SELF(0) SIZE_SPECIAL(*) */ 129 { extract opcode (8), arg_lsb (8); dispatch PUSH_SELF; dispatch SEND_SPECIAL (2); } /* IS_NIL_SPECIAL(0) POP_JUMP_TRUE(*) */ 130 { extract opcode (8), arg_lsb (8); dispatch SEND_SPECIAL (4); dispatch POP_JUMP_TRUE (IP - IP0 + (arg | arg_lsb)); } /* PUSH_TEMPORARY_VARIABLE(*) AT_PUT_SPECIAL(0) */ 131 { extract opcode (8), arg_lsb (8); dispatch PUSH_TEMPORARY_VARIABLE (arg | arg_lsb); dispatch SEND_SPECIAL (1); } /* LINE_NUMBER_BYTECODE(*) PUSH_LIT_VARIABLE(1) */ 132 { extract opcode (8), arg_lsb (8); dispatch LINE_NUMBER_BYTECODE (arg | arg_lsb); dispatch PUSH_LIT_VARIABLE (1); } /* PUSH_TEMPORARY_VARIABLE(*) PLUS_SPECIAL(0) */ 133 { extract opcode (8), arg_lsb (8); dispatch PUSH_TEMPORARY_VARIABLE (arg | arg_lsb); dispatch SEND_ARITH (0); } /* POP_STACK_TOP(0) JUMP_BACK(*) */ 134 { extract opcode (8), arg_lsb (8); dispatch POP_STACK_TOP; dispatch JUMP (IP - IP0 - (arg | arg_lsb)); } /* POP_STACK_TOP(0) PUSH_LIT_VARIABLE(*) */ 135 { extract opcode (8), arg_lsb (8); dispatch POP_STACK_TOP; dispatch PUSH_LIT_VARIABLE (arg | arg_lsb); } /* PUSH_INTEGER(1) STORE_TEMPORARY_VARIABLE(*) */ 136 { extract opcode (8), arg_lsb (8); dispatch PUSH_INTEGER (1); dispatch STORE_TEMPORARY_VARIABLE (arg | arg_lsb); } /* PUSH_LIT_CONSTANT(*) EXT_BYTE(2) SEND(1) */ 137 { extract opcode (8), arg_lsb (8); dispatch PUSH_LIT_CONSTANT (arg | arg_lsb); dispatch SEND (2, 0, 1); } /* LINE_NUMBER_BYTECODE(*) PUSH_TEMPORARY_VARIABLE(3) */ 138 { extract opcode (8), arg_lsb (8); dispatch LINE_NUMBER_BYTECODE (arg | arg_lsb); dispatch PUSH_TEMPORARY_VARIABLE (3); } /* LINE_NUMBER_BYTECODE(*) PUSH_OUTER_TEMP(1) */ 139 { extract opcode (8), arg_lsb (8); dispatch LINE_NUMBER_BYTECODE (arg | arg_lsb); dispatch PUSH_OUTER_TEMP (0, 1); } /* PUSH_RECEIVER_VARIABLE(*) SEND(0) */ 140 { extract opcode (8), arg_lsb (8); dispatch PUSH_RECEIVER_VARIABLE (arg | arg_lsb); dispatch SEND (0, 0, 0); } /* PUSH_INTEGER(*) GREATER_THAN_SPECIAL(0) */ 141 { extract opcode (8), arg_lsb (8); dispatch PUSH_INTEGER (arg | arg_lsb); dispatch SEND_ARITH (3); } /* PUSH_TEMPORARY_VARIABLE(*) VALUE_SPECIAL(0) */ 142 { extract opcode (8), arg_lsb (8); dispatch PUSH_TEMPORARY_VARIABLE (arg | arg_lsb); dispatch SEND_SPECIAL (6); } /* PUSH_TEMPORARY_VARIABLE(*) MINUS_SPECIAL(0) */ 143 { extract opcode (8), arg_lsb (8); dispatch PUSH_TEMPORARY_VARIABLE (arg | arg_lsb); dispatch SEND_ARITH (1); } /* PUSH_LIT_CONSTANT(*) EXT_BYTE(3) SEND(1) */ 144 { extract opcode (8), arg_lsb (8); dispatch PUSH_LIT_CONSTANT (arg | arg_lsb); dispatch SEND (3, 0, 1); } /* PUSH_SPECIAL(0) SAME_OBJECT_SPECIAL(0) POP_JUMP_FALSE(*) */ 145 { extract opcode (8), arg_lsb (8); dispatch PUSH_SPECIAL (0); dispatch SEND_SPECIAL (8); dispatch POP_JUMP_FALSE (IP - IP0 + (arg | arg_lsb)); } /* STORE_TEMPORARY_VARIABLE(2) LINE_NUMBER_BYTECODE(*) POP_STACK_TOP(0) */ 146 { extract opcode (8), arg_lsb (8); dispatch STORE_TEMPORARY_VARIABLE (2); dispatch LINE_NUMBER_BYTECODE (arg | arg_lsb); dispatch POP_STACK_TOP; } /* SAME_OBJECT_SPECIAL(0) POP_JUMP_TRUE(*) */ 147 { extract opcode (8), arg_lsb (8); dispatch SEND_SPECIAL (8); dispatch POP_JUMP_TRUE (IP - IP0 + (arg | arg_lsb)); } /* PUSH_INTEGER(*) TIMES_SPECIAL(0) */ 148 { extract opcode (8), arg_lsb (8); dispatch PUSH_INTEGER (arg | arg_lsb); dispatch SEND_ARITH (8); } /* LINE_NUMBER_BYTECODE(*) PUSH_RECEIVER_VARIABLE(2) */ 149 { extract opcode (8), arg_lsb (8); dispatch LINE_NUMBER_BYTECODE (arg | arg_lsb); dispatch PUSH_RECEIVER_VARIABLE (2); } /* PUSH_INTEGER(*) LESS_THAN_SPECIAL(0) */ 150 { extract opcode (8), arg_lsb (8); dispatch PUSH_INTEGER (arg | arg_lsb); dispatch SEND_ARITH (2); } /* PUSH_LIT_CONSTANT(*) AT_PUT_SPECIAL(0) */ 151 { extract opcode (8), arg_lsb (8); dispatch PUSH_LIT_CONSTANT (arg | arg_lsb); dispatch SEND_SPECIAL (1); } /* EXT_BYTE(*) PUSH_OUTER_TEMP(2) */ 152 { extract opcode (8), arg_lsb (8); dispatch PUSH_OUTER_TEMP (arg | arg_lsb, 2); } /* LINE_NUMBER_BYTECODE(*) PUSH_SELF(0) PUSH_TEMPORARY_VARIABLE(0) SEND(1) */ 153 { extract opcode (8), arg_lsb (8); dispatch LINE_NUMBER_BYTECODE (arg | arg_lsb); dispatch PUSH_SELF; dispatch PUSH_TEMPORARY_VARIABLE (0); dispatch SEND (0, 0, 1); } /* PUSH_SELF(0) PUSH_TEMPORARY_VARIABLE(0) EXT_BYTE(*) SEND(1) */ 154 { extract opcode (8), arg_lsb (8); dispatch PUSH_SELF; dispatch PUSH_TEMPORARY_VARIABLE (0); dispatch SEND (arg | arg_lsb, 0, 1); } /* LINE_NUMBER_BYTECODE(*) PUSH_SELF(0) SEND_IMMEDIATE(40) */ 155 { extract opcode (8), arg_lsb (8); dispatch LINE_NUMBER_BYTECODE (arg | arg_lsb); dispatch PUSH_SELF; dispatch SEND_IMMEDIATE (40, 0); } /* PUSH_TEMPORARY_VARIABLE(*) PUSH_TEMPORARY_VARIABLE(3) */ 156 { extract opcode (8), arg_lsb (8); dispatch PUSH_TEMPORARY_VARIABLE (arg | arg_lsb); dispatch PUSH_TEMPORARY_VARIABLE (3); } /* STORE_TEMPORARY_VARIABLE(1) LINE_NUMBER_BYTECODE(*) */ 157 { extract opcode (8), arg_lsb (8); dispatch STORE_TEMPORARY_VARIABLE (1); dispatch LINE_NUMBER_BYTECODE (arg | arg_lsb); } /* LINE_NUMBER_BYTECODE(*) PUSH_TEMPORARY_VARIABLE(0) SEND(0) */ 158 { extract opcode (8), arg_lsb (8); dispatch LINE_NUMBER_BYTECODE (arg | arg_lsb); dispatch PUSH_TEMPORARY_VARIABLE (0); dispatch SEND (0, 0, 0); } /* PUSH_INTEGER(*) BIT_AND_SPECIAL(0) */ 159 { extract opcode (8), arg_lsb (8); dispatch PUSH_INTEGER (arg | arg_lsb); dispatch SEND_ARITH (14); } /* PUSH_TEMPORARY_VARIABLE(2) EXT_BYTE(*) SEND(0) */ 160 { extract opcode (8), arg_lsb (8); dispatch PUSH_TEMPORARY_VARIABLE (2); dispatch SEND (arg | arg_lsb, 0, 0); } /* PUSH_TEMPORARY_VARIABLE(0) PUSH_TEMPORARY_VARIABLE(1) SEND(*) */ 161 { extract opcode (8), arg_lsb (8); dispatch PUSH_TEMPORARY_VARIABLE (0); dispatch PUSH_TEMPORARY_VARIABLE (1); dispatch SEND (arg >> 8, 0, arg_lsb); } /* LINE_NUMBER_BYTECODE(*) PUSH_SELF(0) PUSH_TEMPORARY_VARIABLE(0) */ 162 { extract opcode (8), arg_lsb (8); dispatch LINE_NUMBER_BYTECODE (arg | arg_lsb); dispatch PUSH_SELF; dispatch PUSH_TEMPORARY_VARIABLE (0); } /* LINE_NUMBER_BYTECODE(*) PUSH_RECEIVER_VARIABLE(3) */ 163 { extract opcode (8), arg_lsb (8); dispatch LINE_NUMBER_BYTECODE (arg | arg_lsb); dispatch PUSH_RECEIVER_VARIABLE (3); } /* PUSH_TEMPORARY_VARIABLE(2) EXT_BYTE(*) SEND(1) */ 164 { extract opcode (8), arg_lsb (8); dispatch PUSH_TEMPORARY_VARIABLE (2); dispatch SEND (arg | arg_lsb, 0, 1); } /* NOT_NIL_SPECIAL(0) POP_JUMP_FALSE(*) */ 165 { extract opcode (8), arg_lsb (8); dispatch SEND_SPECIAL (5); dispatch POP_JUMP_FALSE (IP - IP0 + (arg | arg_lsb)); } /* STORE_TEMPORARY_VARIABLE(2) LINE_NUMBER_BYTECODE(*) */ 166 { extract opcode (8), arg_lsb (8); dispatch STORE_TEMPORARY_VARIABLE (2); dispatch LINE_NUMBER_BYTECODE (arg | arg_lsb); } /* STORE_TEMPORARY_VARIABLE(3) LINE_NUMBER_BYTECODE(*) POP_STACK_TOP(0) */ 167 { extract opcode (8), arg_lsb (8); dispatch STORE_TEMPORARY_VARIABLE (3); dispatch LINE_NUMBER_BYTECODE (arg | arg_lsb); dispatch POP_STACK_TOP; } /* PUSH_LIT_CONSTANT(1) SEND_IMMEDIATE(*) */ 168 { extract opcode (8), arg_lsb (8); dispatch PUSH_LIT_CONSTANT (1); dispatch SEND_IMMEDIATE (arg | arg_lsb, 0); } /* PUSH_TEMPORARY_VARIABLE(*) EQUAL_SPECIAL(0) */ 169 { extract opcode (8), arg_lsb (8); dispatch PUSH_TEMPORARY_VARIABLE (arg | arg_lsb); dispatch SEND_ARITH (6); } /* POP_STACK_TOP(0) DUP_STACK_TOP(0) PUSH_TEMPORARY_VARIABLE(*) PUSH_INTEGER(1) PLUS_SPECIAL(0) */ 170 { extract opcode (8), arg_lsb (8); dispatch POP_STACK_TOP; dispatch DUP_STACK_TOP; dispatch PUSH_TEMPORARY_VARIABLE (arg | arg_lsb); dispatch PUSH_INTEGER (1); dispatch SEND_ARITH (0); } /* PUSH_SELF(0) EXT_BYTE(*) SEND(1) */ 171 { extract opcode (8), arg_lsb (8); dispatch PUSH_SELF; dispatch SEND (arg | arg_lsb, 0, 1); } /* STORE_TEMPORARY_VARIABLE(0) LINE_NUMBER_BYTECODE(*) POP_STACK_TOP(0) */ 172 { extract opcode (8), arg_lsb (8); dispatch STORE_TEMPORARY_VARIABLE (0); dispatch LINE_NUMBER_BYTECODE (arg | arg_lsb); dispatch POP_STACK_TOP; } /* DUP_STACK_TOP(0) LINE_NUMBER_BYTECODE(*) */ 173 { extract opcode (8), arg_lsb (8); dispatch DUP_STACK_TOP; dispatch LINE_NUMBER_BYTECODE (arg | arg_lsb); } /* PUSH_SELF(0) PUSH_LIT_CONSTANT(*) SEND_IMMEDIATE(49) */ 174 { extract opcode (8), arg_lsb (8); dispatch PUSH_SELF; dispatch PUSH_LIT_CONSTANT (arg | arg_lsb); dispatch SEND_IMMEDIATE (49, 0); } /* POP_STACK_TOP(0) PUSH_RECEIVER_VARIABLE(*) */ 175 { extract opcode (8), arg_lsb (8); dispatch POP_STACK_TOP; dispatch PUSH_RECEIVER_VARIABLE (arg | arg_lsb); } /* LINE_NUMBER_BYTECODE(*) PUSH_SELF(0) SEND_IMMEDIATE(84) */ 176 { extract opcode (8), arg_lsb (8); dispatch LINE_NUMBER_BYTECODE (arg | arg_lsb); dispatch PUSH_SELF; dispatch SEND_IMMEDIATE (84, 0); } /* LINE_NUMBER_BYTECODE(*) PUSH_LIT_VARIABLE(2) */ 177 { extract opcode (8), arg_lsb (8); dispatch LINE_NUMBER_BYTECODE (arg | arg_lsb); dispatch PUSH_LIT_VARIABLE (2); } /* PUSH_LIT_CONSTANT(*) MAKE_DIRTY_BLOCK(0) EXT_BYTE(3) SEND(1) */ 178 { extract opcode (8), arg_lsb (8); dispatch PUSH_LIT_CONSTANT (arg | arg_lsb); dispatch MAKE_DIRTY_BLOCK; dispatch SEND (3, 0, 1); } /* LINE_NUMBER_BYTECODE(*) PUSH_LIT_CONSTANT(0) */ 179 { extract opcode (8), arg_lsb (8); dispatch LINE_NUMBER_BYTECODE (arg | arg_lsb); dispatch PUSH_LIT_CONSTANT (0); } /* DUP_STACK_TOP(0) PUSH_LIT_CONSTANT(*) SEND_IMMEDIATE(36) */ 180 { extract opcode (8), arg_lsb (8); dispatch DUP_STACK_TOP; dispatch PUSH_LIT_CONSTANT (arg | arg_lsb); dispatch SEND_IMMEDIATE (36, 0); } /* LINE_NUMBER_BYTECODE(*) EXT_BYTE(1) PUSH_OUTER_TEMP(1) */ 181 { extract opcode (8), arg_lsb (8); dispatch LINE_NUMBER_BYTECODE (arg | arg_lsb); dispatch PUSH_OUTER_TEMP (1, 1); } /* PUSH_INTEGER(*) INTEGER_DIVIDE_SPECIAL(0) */ 182 { extract opcode (8), arg_lsb (8); dispatch PUSH_INTEGER (arg | arg_lsb); dispatch SEND_ARITH (13); } /* PUSH_LIT_CONSTANT(1) MAKE_DIRTY_BLOCK(0) SEND_IMMEDIATE(*) */ 183 { extract opcode (8), arg_lsb (8); dispatch PUSH_LIT_CONSTANT (1); dispatch MAKE_DIRTY_BLOCK; dispatch SEND_IMMEDIATE (arg | arg_lsb, 0); } /* PUSH_TEMPORARY_VARIABLE(3) SEND_IMMEDIATE(*) */ 184 { extract opcode (8), arg_lsb (8); dispatch PUSH_TEMPORARY_VARIABLE (3); dispatch SEND_IMMEDIATE (arg | arg_lsb, 0); } /* LINE_NUMBER_BYTECODE(*) PUSH_SPECIAL(0) RETURN_CONTEXT_STACK_TOP(0) */ 185 { extract opcode (8), arg_lsb (8); dispatch LINE_NUMBER_BYTECODE (arg | arg_lsb); dispatch PUSH_SPECIAL (0); dispatch RETURN_CONTEXT_STACK_TOP; } /* LINE_NUMBER_BYTECODE(*) PUSH_RECEIVER_VARIABLE(5) */ 186 { extract opcode (8), arg_lsb (8); dispatch LINE_NUMBER_BYTECODE (arg | arg_lsb); dispatch PUSH_RECEIVER_VARIABLE (5); } /* PUSH_LIT_CONSTANT(*) MAKE_DIRTY_BLOCK(0) EXT_BYTE(2) SEND(1) */ 187 { extract opcode (8), arg_lsb (8); dispatch PUSH_LIT_CONSTANT (arg | arg_lsb); dispatch MAKE_DIRTY_BLOCK; dispatch SEND (2, 0, 1); } /* PUSH_TEMPORARY_VARIABLE(*) VALUE_COLON_SPECIAL(0) */ 188 { extract opcode (8), arg_lsb (8); dispatch PUSH_TEMPORARY_VARIABLE (arg | arg_lsb); dispatch SEND_SPECIAL (7); } /* PUSH_INTEGER(*) RETURN_CONTEXT_STACK_TOP(0) */ 189 { extract opcode (8), arg_lsb (8); dispatch PUSH_INTEGER (arg | arg_lsb); dispatch RETURN_CONTEXT_STACK_TOP; } /* PUSH_TEMPORARY_VARIABLE(0) EXT_BYTE(*) SEND(2) */ 190 { extract opcode (8), arg_lsb (8); dispatch PUSH_TEMPORARY_VARIABLE (0); dispatch SEND (arg | arg_lsb, 0, 2); } /* PUSH_TEMPORARY_VARIABLE(*) PUSH_INTEGER(1) MINUS_SPECIAL(0) */ 191 { extract opcode (8), arg_lsb (8); dispatch PUSH_TEMPORARY_VARIABLE (arg | arg_lsb); dispatch PUSH_INTEGER (1); dispatch SEND_ARITH (1); } /* PUSH_SELF(0) PUSH_LIT_CONSTANT(*) */ 192 { extract opcode (8), arg_lsb (8); dispatch PUSH_SELF; dispatch PUSH_LIT_CONSTANT (arg | arg_lsb); } /* LINE_NUMBER_BYTECODE(*) PUSH_RECEIVER_VARIABLE(4) */ 193 { extract opcode (8), arg_lsb (8); dispatch LINE_NUMBER_BYTECODE (arg | arg_lsb); dispatch PUSH_RECEIVER_VARIABLE (4); } /* PUSH_OUTER_TEMP(1) SEND_IMMEDIATE(*) */ 194 { extract opcode (8), arg_lsb (8); dispatch PUSH_OUTER_TEMP (0, 1); dispatch SEND_IMMEDIATE (arg | arg_lsb, 0); } /* LINE_NUMBER_BYTECODE(*) PUSH_SELF(0) EXT_BYTE(1) SEND(0) */ 195 { extract opcode (8), arg_lsb (8); dispatch LINE_NUMBER_BYTECODE (arg | arg_lsb); dispatch PUSH_SELF; dispatch SEND (1, 0, 0); } /* PUSH_OUTER_TEMP(1) EXT_BYTE(*) SEND(1) */ 196 { extract opcode (8), arg_lsb (8); dispatch PUSH_OUTER_TEMP (0, 1); dispatch SEND (arg | arg_lsb, 0, 1); } /* PUSH_TEMPORARY_VARIABLE(4) SEND_IMMEDIATE(*) */ 197 { extract opcode (8), arg_lsb (8); dispatch PUSH_TEMPORARY_VARIABLE (4); dispatch SEND_IMMEDIATE (arg | arg_lsb, 0); } /* PUSH_INTEGER(*) SEND_IMMEDIATE(41) */ 198 { extract opcode (8), arg_lsb (8); dispatch PUSH_INTEGER (arg | arg_lsb); dispatch SEND_IMMEDIATE (41, 0); } /* EXT_BYTE(*) SEND(4) */ 199 { extract opcode (8), arg_lsb (8); dispatch SEND (arg | arg_lsb, 0, 4); } /* PUSH_TEMPORARY_VARIABLE(*) PUSH_TEMPORARY_VARIABLE(2) */ 200 { extract opcode (8), arg_lsb (8); dispatch PUSH_TEMPORARY_VARIABLE (arg | arg_lsb); dispatch PUSH_TEMPORARY_VARIABLE (2); } /* PUSH_SELF(0) CLASS_SPECIAL(*) */ 201 { extract opcode (8), arg_lsb (8); dispatch PUSH_SELF; dispatch SEND_SPECIAL (3); } /* PUSH_TEMPORARY_VARIABLE(1) SEND(*) */ 202 { extract opcode (8), arg_lsb (8); dispatch PUSH_TEMPORARY_VARIABLE (1); dispatch SEND (arg >> 8, 0, arg_lsb); } /* PUSH_SELF(0) PUSH_TEMPORARY_VARIABLE(1) EXT_BYTE(*) SEND(1) */ 203 { extract opcode (8), arg_lsb (8); dispatch PUSH_SELF; dispatch PUSH_TEMPORARY_VARIABLE (1); dispatch SEND (arg | arg_lsb, 0, 1); } /* PUSH_LIT_CONSTANT(*) EXT_BYTE(4) SEND(1) */ 204 { extract opcode (8), arg_lsb (8); dispatch PUSH_LIT_CONSTANT (arg | arg_lsb); dispatch SEND (4, 0, 1); } /* PUSH_INTEGER(*) SEND(1) */ 205 { extract opcode (8), arg_lsb (8); dispatch PUSH_INTEGER (arg | arg_lsb); dispatch SEND (0, 0, 1); } /* PUSH_RECEIVER_VARIABLE(*) SIZE_SPECIAL(0) */ 206 { extract opcode (8), arg_lsb (8); dispatch PUSH_RECEIVER_VARIABLE (arg | arg_lsb); dispatch SEND_SPECIAL (2); } /* PUSH_TEMPORARY_VARIABLE(1) EXT_BYTE(*) SEND(2) */ 207 { extract opcode (8), arg_lsb (8); dispatch PUSH_TEMPORARY_VARIABLE (1); dispatch SEND (arg | arg_lsb, 0, 2); } /* PUSH_TEMPORARY_VARIABLE(0) PUSH_TEMPORARY_VARIABLE(1) EXT_BYTE(*) SEND(2) */ 208 { extract opcode (8), arg_lsb (8); dispatch PUSH_TEMPORARY_VARIABLE (0); dispatch PUSH_TEMPORARY_VARIABLE (1); dispatch SEND (arg | arg_lsb, 0, 2); } /* PUSH_TEMPORARY_VARIABLE(*) POP_INTO_NEW_STACKTOP(0) */ 209 { extract opcode (8), arg_lsb (8); dispatch PUSH_TEMPORARY_VARIABLE (arg | arg_lsb); dispatch POP_INTO_NEW_STACKTOP (0); } /* PUSH_LIT_CONSTANT(*) MAKE_DIRTY_BLOCK(0) EXT_BYTE(5) SEND(1) */ 210 { extract opcode (8), arg_lsb (8); dispatch PUSH_LIT_CONSTANT (arg | arg_lsb); dispatch MAKE_DIRTY_BLOCK; dispatch SEND (5, 0, 1); } /* EXT_BYTE(*) SEND_SUPER(1) */ 211 { extract opcode (8), arg_lsb (8); dispatch SEND (arg | arg_lsb, 1, 1); } /* PUSH_LIT_CONSTANT(*) MAKE_DIRTY_BLOCK(0) EXT_BYTE(4) SEND(1) */ 212 { extract opcode (8), arg_lsb (8); dispatch PUSH_LIT_CONSTANT (arg | arg_lsb); dispatch MAKE_DIRTY_BLOCK; dispatch SEND (4, 0, 1); } /* PUSH_RECEIVER_VARIABLE(1) SEND_IMMEDIATE(*) */ 213 { extract opcode (8), arg_lsb (8); dispatch PUSH_RECEIVER_VARIABLE (1); dispatch SEND_IMMEDIATE (arg | arg_lsb, 0); } /* EXT_BYTE(*) STORE_OUTER_TEMP(1) RETURN_CONTEXT_STACK_TOP(0) */ 214 { extract opcode (8), arg_lsb (8); dispatch STORE_OUTER_TEMP (arg | arg_lsb, 1); dispatch RETURN_CONTEXT_STACK_TOP; } /* POP_STACK_TOP(0) LINE_NUMBER_BYTECODE(*) SEND_IMMEDIATE(37) */ 215 { extract opcode (8), arg_lsb (8); dispatch POP_STACK_TOP; dispatch LINE_NUMBER_BYTECODE (arg | arg_lsb); dispatch SEND_IMMEDIATE (37, 0); } /* LINE_NUMBER_BYTECODE(*) PUSH_SELF(0) CLASS_SPECIAL(0) */ 216 { extract opcode (8), arg_lsb (8); dispatch LINE_NUMBER_BYTECODE (arg | arg_lsb); dispatch PUSH_SELF; dispatch SEND_SPECIAL (3); } /* PUSH_TEMPORARY_VARIABLE(1) EXT_BYTE(*) SEND(0) */ 217 { extract opcode (8), arg_lsb (8); dispatch PUSH_TEMPORARY_VARIABLE (1); dispatch SEND (arg | arg_lsb, 0, 0); } /* LINE_NUMBER_BYTECODE(*) PUSH_SELF(0) SEND_IMMEDIATE(130) */ 218 { extract opcode (8), arg_lsb (8); dispatch LINE_NUMBER_BYTECODE (arg | arg_lsb); dispatch PUSH_SELF; dispatch SEND_IMMEDIATE (130, 0); } /* PUSH_RECEIVER_VARIABLE(0) SEND_IMMEDIATE(*) */ 219 { extract opcode (8), arg_lsb (8); dispatch PUSH_RECEIVER_VARIABLE (0); dispatch SEND_IMMEDIATE (arg | arg_lsb, 0); } /* PUSH_TEMPORARY_VARIABLE(0) PUSH_LIT_VARIABLE(*) */ 220 { extract opcode (8), arg_lsb (8); dispatch PUSH_TEMPORARY_VARIABLE (0); dispatch PUSH_LIT_VARIABLE (arg | arg_lsb); } /* STORE_TEMPORARY_VARIABLE(0) LINE_NUMBER_BYTECODE(*) */ 221 { extract opcode (8), arg_lsb (8); dispatch STORE_TEMPORARY_VARIABLE (0); dispatch LINE_NUMBER_BYTECODE (arg | arg_lsb); } /* PUSH_RECEIVER_VARIABLE(2) SEND_IMMEDIATE(*) */ 222 { extract opcode (8), arg_lsb (8); dispatch PUSH_RECEIVER_VARIABLE (2); dispatch SEND_IMMEDIATE (arg | arg_lsb, 0); } /* LINE_NUMBER_BYTECODE(*) PUSH_SELF(0) EXT_BYTE(2) SEND(0) */ 223 { extract opcode (8), arg_lsb (8); dispatch LINE_NUMBER_BYTECODE (arg | arg_lsb); dispatch PUSH_SELF; dispatch SEND (2, 0, 0); } /* LINE_NUMBER_BYTECODE(*) POP_STACK_TOP(0) PUSH_TEMPORARY_VARIABLE(2) */ 224 { extract opcode (8), arg_lsb (8); dispatch LINE_NUMBER_BYTECODE (arg | arg_lsb); dispatch POP_STACK_TOP; dispatch PUSH_TEMPORARY_VARIABLE (2); } /* PUSH_LIT_CONSTANT(*) MAKE_DIRTY_BLOCK(0) EXT_BYTE(6) SEND(1) */ 225 { extract opcode (8), arg_lsb (8); dispatch PUSH_LIT_CONSTANT (arg | arg_lsb); dispatch MAKE_DIRTY_BLOCK; dispatch SEND (6, 0, 1); } /* PUSH_SPECIAL(*) RETURN_METHOD_STACK_TOP(0) */ 226 { extract opcode (8), arg_lsb (8); dispatch PUSH_SPECIAL (arg | arg_lsb); dispatch RETURN_METHOD_STACK_TOP; } /* PUSH_INTEGER(*) GREATER_EQUAL_SPECIAL(0) */ 227 { extract opcode (8), arg_lsb (8); dispatch PUSH_INTEGER (arg | arg_lsb); dispatch SEND_ARITH (5); } /* LINE_NUMBER_BYTECODE(*) POP_STACK_TOP(0) PUSH_RECEIVER_VARIABLE(1) */ 228 { extract opcode (8), arg_lsb (8); dispatch LINE_NUMBER_BYTECODE (arg | arg_lsb); dispatch POP_STACK_TOP; dispatch PUSH_RECEIVER_VARIABLE (1); } /* LINE_NUMBER_BYTECODE(*) PUSH_LIT_VARIABLE(3) */ 229 { extract opcode (8), arg_lsb (8); dispatch LINE_NUMBER_BYTECODE (arg | arg_lsb); dispatch PUSH_LIT_VARIABLE (3); } /* PUSH_LIT_CONSTANT(2) SEND_IMMEDIATE(*) */ 230 { extract opcode (8), arg_lsb (8); dispatch PUSH_LIT_CONSTANT (2); dispatch SEND_IMMEDIATE (arg | arg_lsb, 0); } /* EXT_BYTE(*) SEND_SUPER(0) */ 231 { extract opcode (8), arg_lsb (8); dispatch SEND (arg | arg_lsb, 1, 0); } /* PUSH_SPECIAL(0) STORE_RECEIVER_VARIABLE(*) */ 232 { extract opcode (8), arg_lsb (8); dispatch PUSH_SPECIAL (0); dispatch STORE_RECEIVER_VARIABLE (arg | arg_lsb); } /* PUSH_SELF(0) PUSH_TEMPORARY_VARIABLE(*) SEND(1) */ 233 { extract opcode (8), arg_lsb (8); dispatch PUSH_SELF; dispatch PUSH_TEMPORARY_VARIABLE (arg | arg_lsb); dispatch SEND (0, 0, 1); } /* LINE_NUMBER_BYTECODE(*) POP_STACK_TOP(0) PUSH_TEMPORARY_VARIABLE(0) RETURN_CONTEXT_STACK_TOP(0) */ 234 { extract opcode (8), arg_lsb (8); dispatch LINE_NUMBER_BYTECODE (arg | arg_lsb); dispatch POP_STACK_TOP; dispatch PUSH_TEMPORARY_VARIABLE (0); dispatch RETURN_CONTEXT_STACK_TOP; } /* PUSH_LIT_CONSTANT(*) SAME_OBJECT_SPECIAL(0) */ 235 { extract opcode (8), arg_lsb (8); dispatch PUSH_LIT_CONSTANT (arg | arg_lsb); dispatch SEND_SPECIAL (8); } /* PUSH_LIT_CONSTANT(*) MAKE_DIRTY_BLOCK(0) EXT_BYTE(1) SEND(1) */ 236 { extract opcode (8), arg_lsb (8); dispatch PUSH_LIT_CONSTANT (arg | arg_lsb); dispatch MAKE_DIRTY_BLOCK; dispatch SEND (1, 0, 1); } /* LINE_NUMBER_BYTECODE(*) POP_STACK_TOP(0) PUSH_TEMPORARY_VARIABLE(3) */ 237 { extract opcode (8), arg_lsb (8); dispatch LINE_NUMBER_BYTECODE (arg | arg_lsb); dispatch POP_STACK_TOP; dispatch PUSH_TEMPORARY_VARIABLE (3); } /* POP_STACK_TOP(0) DUP_STACK_TOP(0) SEND_IMMEDIATE(*) */ 238 { extract opcode (8), arg_lsb (8); dispatch POP_STACK_TOP; dispatch DUP_STACK_TOP; dispatch SEND_IMMEDIATE (arg | arg_lsb, 0); } /* PUSH_LIT_CONSTANT(*) PUSH_TEMPORARY_VARIABLE(0) AT_PUT_SPECIAL(0) */ 239 { extract opcode (8), arg_lsb (8); dispatch PUSH_LIT_CONSTANT (arg | arg_lsb); dispatch PUSH_TEMPORARY_VARIABLE (0); dispatch SEND_SPECIAL (1); } /* DUP_STACK_TOP(0) PUSH_TEMPORARY_VARIABLE(*) PUSH_INTEGER(1) PLUS_SPECIAL(0) */ 240 { extract opcode (8), arg_lsb (8); dispatch DUP_STACK_TOP; dispatch PUSH_TEMPORARY_VARIABLE (arg | arg_lsb); dispatch PUSH_INTEGER (1); dispatch SEND_ARITH (0); } /* LINE_NUMBER_BYTECODE(*) PUSH_TEMPORARY_VARIABLE(4) */ 241 { extract opcode (8), arg_lsb (8); dispatch LINE_NUMBER_BYTECODE (arg | arg_lsb); dispatch PUSH_TEMPORARY_VARIABLE (4); } /* POP_STACK_TOP(0) LINE_NUMBER_BYTECODE(*) PUSH_LIT_VARIABLE(1) */ 242 { extract opcode (8), arg_lsb (8); dispatch POP_STACK_TOP; dispatch LINE_NUMBER_BYTECODE (arg | arg_lsb); dispatch PUSH_LIT_VARIABLE (1); } /* DUP_STACK_TOP(0) PUSH_LIT_CONSTANT(*) EXT_BYTE(1) SEND(1) */ 243 { extract opcode (8), arg_lsb (8); dispatch DUP_STACK_TOP; dispatch PUSH_LIT_CONSTANT (arg | arg_lsb); dispatch SEND (1, 0, 1); } /* POP_INTO_NEW_STACKTOP(1) EXT_BYTE(*) SEND(1) */ 244 { extract opcode (8), arg_lsb (8); dispatch POP_INTO_NEW_STACKTOP (1); dispatch SEND (arg | arg_lsb, 0, 1); } /* LINE_NUMBER_BYTECODE(*) POP_STACK_TOP(0) PUSH_TEMPORARY_VARIABLE(1) RETURN_CONTEXT_STACK_TOP(0) */ 245 { extract opcode (8), arg_lsb (8); dispatch LINE_NUMBER_BYTECODE (arg | arg_lsb); dispatch POP_STACK_TOP; dispatch PUSH_TEMPORARY_VARIABLE (1); dispatch RETURN_CONTEXT_STACK_TOP; } /* STORE_TEMPORARY_VARIABLE(3) LINE_NUMBER_BYTECODE(*) */ 246 { extract opcode (8), arg_lsb (8); dispatch STORE_TEMPORARY_VARIABLE (3); dispatch LINE_NUMBER_BYTECODE (arg | arg_lsb); } /* DUP_STACK_TOP(0) EXT_BYTE(*) SEND(0) */ 247 { extract opcode (8), arg_lsb (8); dispatch DUP_STACK_TOP; dispatch SEND (arg | arg_lsb, 0, 0); } /* STORE_RECEIVER_VARIABLE(*) RETURN_CONTEXT_STACK_TOP(0) */ 248 { extract opcode (8), arg_lsb (8); dispatch STORE_RECEIVER_VARIABLE (arg | arg_lsb); dispatch RETURN_CONTEXT_STACK_TOP; } /* LINE_NUMBER_BYTECODE(*) PUSH_SELF(0) EXT_BYTE(3) SEND(0) */ 249 { extract opcode (8), arg_lsb (8); dispatch LINE_NUMBER_BYTECODE (arg | arg_lsb); dispatch PUSH_SELF; dispatch SEND (3, 0, 0); } /* NOT_NIL_SPECIAL(0) DUP_STACK_TOP(0) POP_JUMP_FALSE(*) */ 250 { extract opcode (8), arg_lsb (8); dispatch SEND_SPECIAL (5); dispatch DUP_STACK_TOP; dispatch POP_JUMP_FALSE (IP - IP0 + (arg | arg_lsb)); } /* DUP_STACK_TOP(0) PUSH_LIT_CONSTANT(*) */ 251 { extract opcode (8), arg_lsb (8); dispatch DUP_STACK_TOP; dispatch PUSH_LIT_CONSTANT (arg | arg_lsb); } /* LINE_NUMBER_BYTECODE(*) PUSH_TEMPORARY_VARIABLE(0) RETURN_CONTEXT_STACK_TOP(0) */ 252 { extract opcode (8), arg_lsb (8); dispatch LINE_NUMBER_BYTECODE (arg | arg_lsb); dispatch PUSH_TEMPORARY_VARIABLE (0); dispatch RETURN_CONTEXT_STACK_TOP; } /* PUSH_INTEGER(*) AT_PUT_SPECIAL(0) */ 253 { extract opcode (8), arg_lsb (8); dispatch PUSH_INTEGER (arg | arg_lsb); dispatch SEND_SPECIAL (1); } /* PUSH_TEMPORARY_VARIABLE(*) CLASS_SPECIAL(0) */ 254 { extract opcode (8), arg_lsb (8); dispatch PUSH_TEMPORARY_VARIABLE (arg | arg_lsb); dispatch SEND_SPECIAL (3); } /* LINE_NUMBER_BYTECODE(*) EXT_BYTE(2) PUSH_OUTER_TEMP(1) */ 255 { extract opcode (8), arg_lsb (8); dispatch LINE_NUMBER_BYTECODE (arg | arg_lsb); dispatch PUSH_OUTER_TEMP (2, 1); } smalltalk-3.2.5/libgst/heap.h0000644000175000017500000000704412123404352013001 00000000000000/******************************** -*- C -*- **************************** * * Header for memory allocation within separate mmap'ed regions * * ***********************************************************************/ /*********************************************************************** * * Copyright 2000, 2001, 2002, 2006 Free Software Foundation, Inc. * Written by Paolo Bonzini. * * This file is part of GNU Smalltalk. * * GNU Smalltalk is free software; you can redistribute it and/or modify it * under the terms of the GNU General Public License as published by the Free * Software Foundation; either version 2, or (at your option) any later * version. * * Linking GNU Smalltalk statically or dynamically with other modules is * making a combined work based on GNU Smalltalk. Thus, the terms and * conditions of the GNU General Public License cover the whole * combination. * * In addition, as a special exception, the Free Software Foundation * give you permission to combine GNU Smalltalk with free software * programs or libraries that are released under the GNU LGPL and with * independent programs running under the GNU Smalltalk virtual machine. * * You may copy and distribute such a system following the terms of the * GNU GPL for GNU Smalltalk and the licenses of the other code * concerned, provided that you include the source code of that other * code when and as the GNU GPL requires distribution of source code. * * Note that people who make modified versions of GNU Smalltalk are not * obligated to grant this special exception for their modified * versions; it is their choice whether to do so. The GNU General * Public License gives permission to release a modified version without * this exception; this exception also makes it possible to release a * modified version which carries forward this exception. * * GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or * FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for * more details. * * You should have received a copy of the GNU General Public License along with * GNU Smalltalk; see the file COPYING. If not, write to the Free Software * Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. ***********************************************************************/ #ifndef GST_HEAP_H #define GST_HEAP_H typedef char *heap; /* Initialize access to a heap managed region of the given SIZE, trying to put it at the specified address. On success, returns a "heap descriptor" which is used in subsequent calls to other heap package functions. It is explicitly "char *" so that users of the package don't have to worry about the actual implementation details. On failure returns NULL. */ extern heap _gst_heap_create (PTR address, int size) ATTRIBUTE_HIDDEN; /* Terminate access to a heap managed region by unmapping all memory pages associated with the region, and closing the file descriptor if it is one that we opened. Returns NULL on success. Returns the heap descriptor on failure, which can subsequently be used for further action. */ extern heap _gst_heap_destroy (heap hd) ATTRIBUTE_HIDDEN; /* Get core for the memory region specified by HD, using SIZE as the amount to either add to or subtract from the existing region. Works like sbrk(), but using mmap() if HD is not NULL. */ extern PTR _gst_heap_sbrk (heap hd, size_t size) ATTRIBUTE_HIDDEN; #endif /* GST_HEAP_H */ smalltalk-3.2.5/libgst/re.c0000644000175000017500000002751512123404352012472 00000000000000/*********************************************************************** * * Regular expression interface definitions for GNU Smalltalk * * ***********************************************************************/ /*********************************************************************** * * Copyright 2001, 2002, 2006, 2008 Free Software Foundation, Inc. * Written by Paolo Bonzini and Dragomir Milevojevic. * * This file is part of GNU Smalltalk. * * GNU Smalltalk is free software; you can redistribute it and/or modify it * under the terms of the GNU General Public License as published by the Free * Software Foundation; either version 2, or (at your option) any later * version. * * Linking GNU Smalltalk statically or dynamically with other modules is * making a combined work based on GNU Smalltalk. Thus, the terms and * conditions of the GNU General Public License cover the whole * combination. * * In addition, as a special exception, the Free Software Foundation * give you permission to combine GNU Smalltalk with free software * programs or libraries that are released under the GNU LGPL and with * independent programs running under the GNU Smalltalk virtual machine. * * You may copy and distribute such a system following the terms of the * GNU GPL for GNU Smalltalk and the licenses of the other code * concerned, provided that you include the source code of that other * code when and as the GNU GPL requires distribution of source code. * * Note that people who make modified versions of GNU Smalltalk are not * obligated to grant this special exception for their modified * versions; it is their choice whether to do so. The GNU General * Public License gives permission to release a modified version without * this exception; this exception also makes it possible to release a * modified version which carries forward this exception. * * GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or * FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for * more details. * * You should have received a copy of the GNU General Public License along with * GNU Smalltalk; see the file COPYING. If not, write to the Free Software * Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * ***********************************************************************/ #ifdef HAVE_CONFIG_H #include "config.h" #endif #include "gstpriv.h" #include "regex.h" #include "re.h" #if STDC_HEADERS #include #include #endif /* Regex caching facility */ #define REGEX_CACHE_SIZE 10 typedef enum RegexCachingEnum { REGEX_NOT_CACHED, REGEX_CACHE_HIT, REGEX_CACHE_MISS } RegexCaching; typedef struct RegexCacheEntry { OOP patternOOP; struct pre_pattern_buffer *regex; } RegexCacheEntry; static RegexCaching lookupRegex (OOP patternOOP, struct pre_pattern_buffer **pRegex); static const char *compileRegex (OOP patternOOP, struct pre_pattern_buffer *regex); static struct pre_pattern_buffer *allocateNewRegex (void); static void markRegexAsMRU (int i); static void init_re (void); static RegexCacheEntry cache[REGEX_CACHE_SIZE]; /* Smalltalk globals */ static OOP regexClassOOP, resultsClassOOP; /* Allocate a buffer to be passed to the regular expression matcher */ struct pre_pattern_buffer * allocateNewRegex (void) { struct pre_pattern_buffer *regex; regex = (struct pre_pattern_buffer *) calloc (1, sizeof (struct pre_pattern_buffer)); regex->allocated = 0; regex->fastmap = malloc (1 << BYTEWIDTH); return regex; } /* Compile a pattern that's stored into an OOP. Answer an error, or NULL. */ const char * compileRegex (OOP patternOOP, struct pre_pattern_buffer *regex) { int patternLength; const char *pattern; const char *ress; pattern = &STRING_OOP_AT (OOP_TO_OBJ (patternOOP), 1); patternLength = _gst_basic_size (patternOOP); /* compile pattern */ ress = pre_compile_pattern (pattern, patternLength, regex); return ress; } /* Move the i-th entry of the cache to the first position */ void markRegexAsMRU (int i) { RegexCacheEntry saved; int j; saved = cache[i]; for (j = i; j > 0; j--) cache[j] = cache[j - 1]; cache[0] = saved; } /* If patternOOP is not a Regex, answer REGEX_NOT_CACHED. Else look it up in the cache and move it to its top (so that it is marked as most recently used). Answer REGEX_CACHE_HIT if it is found, or REGEX_CACHE_MISS if it is not. pRegex will point to the compiled regex if there is a cache hit, else lookupRegex will only initialize it, and it will be the caller's responsibility to compile the regex into the buffer that is returned. If the patternOOP is not a Regex (i.e. REGEX_NOT_CACHED returned), the caller will also have to free the buffer pointed to by pRegex. */ RegexCaching lookupRegex (OOP patternOOP, struct pre_pattern_buffer **pRegex) { int i; RegexCaching result; if (!IS_OOP_READONLY (patternOOP)) { *pRegex = allocateNewRegex (); return REGEX_NOT_CACHED; } /* Search for the Regex object in the cache */ for (i = 0; i < REGEX_CACHE_SIZE; i++) if (cache[i].patternOOP == patternOOP) break; if (i < REGEX_CACHE_SIZE) result = REGEX_CACHE_HIT; else { /* Kick out the least recently used regexp */ i--; result = REGEX_CACHE_MISS; /* Register the objects we're caching with the virtual machine */ if (cache[i].patternOOP) _gst_unregister_oop (cache[i].patternOOP); _gst_register_oop (patternOOP); cache[i].patternOOP = patternOOP; } /* Mark the object as most recently used */ if (!cache[i].regex) cache[i].regex = allocateNewRegex (); markRegexAsMRU (i); *pRegex = cache[0].regex; return result; } /* Create a Regex object. We look for one that points to the same string in the cache (so that we can optimize a loop that repeatedly calls asRegex; if none is found, we create one ex-novo. Note that Regex and String objects have the same layout; only, Regexes are read-only so that we can support this kind of "interning" them. */ OOP _gst_re_make_cacheable (OOP patternOOP) { OOP regexOOP; const char *pattern; char *regex; struct pre_pattern_buffer *compiled; int patternLength; int i; if (!regexClassOOP) init_re (); if (IS_OOP_READONLY (patternOOP)) return patternOOP; /* Search in the cache */ patternLength = _gst_basic_size (patternOOP); pattern = &STRING_OOP_AT (OOP_TO_OBJ (patternOOP), 1); for (i = 0; i < REGEX_CACHE_SIZE; i++) { if (!cache[i].regex) break; regexOOP = cache[i].patternOOP; regex = &STRING_OOP_AT (OOP_TO_OBJ (regexOOP), 1); if (_gst_basic_size (regexOOP) == patternLength && memcmp (regex, pattern, patternLength) == 0) { markRegexAsMRU (i); return regexOOP; } } /* No way, must allocate a new Regex object */ regexOOP = _gst_object_alloc (regexClassOOP, patternLength); regex = &STRING_OOP_AT (OOP_TO_OBJ (regexOOP), 1); memcpy (regex, pattern, patternLength); /* Put it in the cache (we must compile it to check that it * is well-formed). */ lookupRegex (regexOOP, &compiled); if (compileRegex (patternOOP, compiled) != NULL) return _gst_nil_oop; else return regexOOP; } typedef struct _gst_interval { OBJ_HEADER; OOP fromOOP; OOP toOOP; OOP stepOOP; } *gst_interval; typedef struct _gst_registers { OBJ_HEADER; OOP subjectOOP; OOP fromOOP; OOP toOOP; OOP registersOOP; OOP matchOOP; OOP cacheOOP; } *gst_registers; static OOP make_re_results (OOP srcOOP, struct pre_registers *regs) { OOP resultsOOP; gst_registers results; int i; if (!regs->beg || regs->beg[0] == -1) return _gst_nil_oop; resultsOOP = _gst_object_alloc (resultsClassOOP, 0); results = (gst_registers) OOP_TO_OBJ (resultsOOP); results->subjectOOP = srcOOP; results->fromOOP = FROM_INT (regs->beg[0] + 1); results->toOOP = FROM_INT (regs->end[0]); if (regs->num_regs > 1) { OOP registersOOP = _gst_object_alloc (_gst_array_class, regs->num_regs - 1); results = (gst_registers) OOP_TO_OBJ (resultsOOP); results->registersOOP = registersOOP; } for (i = 1; i < regs->num_regs; i++) { OOP intervalOOP; if (regs->beg[i] == -1) intervalOOP = _gst_nil_oop; else { gst_interval interval; intervalOOP = _gst_object_alloc (_gst_interval_class, 0); interval = (gst_interval) OOP_TO_OBJ (intervalOOP); interval->fromOOP = FROM_INT (regs->beg[i] + 1); interval->toOOP = FROM_INT (regs->end[i]); interval->stepOOP = FROM_INT (1); } /* We need to reload results as it may be invalidated by GC. */ results = (gst_registers) OOP_TO_OBJ (resultsOOP); _gst_oop_at_put (results->registersOOP, i - 1, intervalOOP); } return resultsOOP; } /* Search helper function */ OOP _gst_re_search (OOP srcOOP, OOP patternOOP, int from, int to) { const char *src; struct pre_pattern_buffer *regex; struct pre_registers *regs; RegexCaching caching; OOP resultOOP; if (!regexClassOOP) init_re (); caching = lookupRegex (patternOOP, ®ex); if (caching != REGEX_CACHE_HIT && compileRegex (patternOOP, regex) != NULL) return NULL; /* now search */ src = &STRING_OOP_AT (OOP_TO_OBJ (srcOOP), 1); regs = (struct pre_registers *) calloc (1, sizeof (struct pre_registers)); pre_search (regex, src, to, from - 1, to - from + 1, regs); if (caching == REGEX_NOT_CACHED) pre_free_pattern (regex); resultOOP = make_re_results (srcOOP, regs); pre_free_registers(regs); free(regs); return resultOOP; } /* Match helper function */ int _gst_re_match (OOP srcOOP, OOP patternOOP, int from, int to) { int res = 0; const char *src; struct pre_pattern_buffer *regex; RegexCaching caching; if (!regexClassOOP) init_re (); caching = lookupRegex (patternOOP, ®ex); if (caching != REGEX_CACHE_HIT && compileRegex (patternOOP, regex) != NULL) return -100; /* now search */ src = &STRING_OOP_AT (OOP_TO_OBJ (srcOOP), 1); res = pre_match (regex, src, to, from - 1, NULL); if (caching == REGEX_NOT_CACHED) pre_free_pattern (regex); return res; } /* Initialize regex.c */ static void init_re (void) { /* This is a ASCII downcase-table. We don't make any assumptions about what bytes >=128 are, so can't downcase them. */ static const char casetable[256] = {0, 1, 2, 3, 4, 5, 6, 7, 8, 9, 10, 11, 12, 13, 14, 15, 16, 17, 18, 19, 20, 21, 22, 23, 24, 25, 26, 27, 28, 29, 30, 31, ' ', '!', '"', '#', '$', '%', '&', '\'', '(', ')', '*', '+', ',', '-', '.', '/', '0', '1', '2', '3', '4', '5', '6', '7', '8', '9', ':', ';', '<', '=', '>', '?', '@', 'a', 'b', 'c', 'd', 'e', 'f', 'g', 'h', 'i', 'j', 'k', 'l', 'm', 'n', 'o', 'p', 'q', 'r', 's', 't', 'u', 'v', 'w', 'x', 'y', 'z', '[', '\\', ']', '^', '_', '`', 'a', 'b', 'c', 'd', 'e', 'f', 'g', 'h', 'i', 'j', 'k', 'l', 'm', 'n', 'o', 'p', 'q', 'r', 's', 't', 'u', 'v', 'w', 'x', 'y', 'z', '{', '|', '}', '~', 127, 128, 129, 130, 131, 132, 133, 134, 135, 136, 137, 138, 139, 140, 141, 142, 143, 144, 145, 146, 147, 148, 149, 150, 151, 152, 153, 154, 155, 156, 157, 158, 159, 160, 161, 162, 163, 164, 165, 166, 167, 168, 169, 170, 171, 172, 173, 174, 175, 176, 177, 178, 179, 180, 181, 182, 183, 184, 185, 186, 187, 188, 189, 190, 191, 192, 193, 194, 195, 196, 197, 198, 199, 200, 201, 202, 203, 204, 205, 206, 207, 208, 209, 210, 211, 212, 213, 214, 215, 216, 217, 218, 219, 220, 221, 222, 223, 224, 225, 226, 227, 228, 229, 230, 231, 232, 233, 234, 235, 236, 237, 238, 239, 240, 241, 242, 243, 244, 245, 246, 247, 248, 249, 250, 251, 252, 253, 254, 255}; pre_set_casetable (casetable); regexClassOOP = _gst_class_name_to_oop ("Regex"); resultsClassOOP = _gst_class_name_to_oop ("Kernel.MatchingRegexResults"); } smalltalk-3.2.5/libgst/builtins.gperf0000644000175000017500000002755112123404352014576 00000000000000%delimiters=";" %null-strings %struct-type %pic %define initializer-suffix ,NULL,-1,-1 %define slot-name offset %define hash-function-name _gst_hash_selector %define lookup-function-name _gst_lookup_builtin_selector %define string-pool-name _gst_builtin_selectors_names %define word-array-name _gst_builtin_selectors_hash %compare-lengths %enum %global-table %omit-struct-type %{ /* Process with gperf -k'1-3,6,$' -r This table was generated starting from a 5 megabyte image including Blox (TK), the GTK bindings, the Browser (and hence the parser), TCP, NetClients, I18N, NumericalMethods, GDBM, MD5, and MySQL, starting from the output of this script | b | b := Bag new. CompiledMethod allInstances do: [ :each || n | each literals do: [ :each | each isSymbol ifTrue: [ b add: each ] ]. ]. Transcript nl. b sortedByCount from: 1 to: 226 keysAndValuesDo: [ :i :each | ('%1; NULL, %2, %3' bindWith: each value with: each value numArgs with: i + 31) displayNl ]! */ %} struct builtin_selector { int offset; OOP symbol; int numArgs; int bytecode; }; %% +; NULL, 1, PLUS_SPECIAL -; NULL, 1, MINUS_SPECIAL <; NULL, 1, LESS_THAN_SPECIAL >; NULL, 1, GREATER_THAN_SPECIAL <=; NULL, 1, LESS_EQUAL_SPECIAL >=; NULL, 1, GREATER_EQUAL_SPECIAL =; NULL, 1, EQUAL_SPECIAL ~=; NULL, 1, NOT_EQUAL_SPECIAL *; NULL, 1, TIMES_SPECIAL /; NULL, 1, DIVIDE_SPECIAL \\; NULL, 1, REMAINDER_SPECIAL bitXor:; NULL, 1, BIT_XOR_SPECIAL bitShift:; NULL, 1, BIT_SHIFT_SPECIAL //; NULL, 1, INTEGER_DIVIDE_SPECIAL bitAnd:; NULL, 1, BIT_AND_SPECIAL bitOr:; NULL, 1, BIT_OR_SPECIAL at:; NULL, 1, AT_SPECIAL at:put:; NULL, 2, AT_PUT_SPECIAL size; NULL, 0, SIZE_SPECIAL class; NULL, 0, CLASS_SPECIAL isNil; NULL, 0, IS_NIL_SPECIAL notNil; NULL, 0, NOT_NIL_SPECIAL value; NULL, 0, VALUE_SPECIAL value:; NULL, 1, VALUE_COLON_SPECIAL ==; NULL, 1, SAME_OBJECT_SPECIAL javaAsInt; NULL, 0, JAVA_AS_INT_SPECIAL javaAsLong; NULL, 0, JAVA_AS_LONG_SPECIAL new:; NULL, 1, NEW_COLON_SPECIAL thisContext; NULL, 0, THIS_CONTEXT_SPECIAL callInto:; NULL, 1, 34 narrow; NULL, 0, 35 nextPutAll:; NULL, 1, 36 yourself; NULL, 0, 37 ,; NULL, 1, 38 on:; NULL, 1, 39 subclassResponsibility; NULL, 0, 40 add:; NULL, 1, 41 nl; NULL, 0, 42 printString; NULL, 0, 43 contents; NULL, 0, 44 name; NULL, 0, 45 isEmpty; NULL, 0, 46 properties; NULL, 0, 47 container; NULL, 0, 48 error:; NULL, 1, 49 first; NULL, 0, 50 tclEval:; NULL, 1, 51 collect:; NULL, 1, 52 tclResult; NULL, 0, 53 key; NULL, 0, 54 asTkString; NULL, 0, 55 abs; NULL, 0, 56 basicNew; NULL, 0, 57 negated; NULL, 0, 58 not; NULL, 0, 59 close; NULL, 0, 60 includes:; NULL, 1, 61 at:ifAbsent:; NULL, 2, 62 asSymbol; NULL, 0, 63 with:; NULL, 1, 64 copy; NULL, 0, 65 copyFrom:to:; NULL, 2, 66 print:; NULL, 1, 67 last; NULL, 0, 68 initialize; NULL, 0, 69 tclEval:with:with:; NULL, 3, 70 assert:; NULL, 1, 71 primitiveFailed; NULL, 0, 72 initialize:; NULL, 1, 73 asString; NULL, 0, 74 cr; NULL, 0, 75 should:; NULL, 1, 76 arguments; NULL, 0, 77 x; NULL, 0, 78 readStream; NULL, 0, 79 y; NULL, 0, 80 tclEval:with:with:with:; NULL, 4, 81 asInteger; NULL, 0, 82 space; NULL, 0, 83 new; NULL, 0, 84 shouldNotImplement; NULL, 0, 85 ->; NULL, 1, 86 numArgs; NULL, 0, 87 with:with:; NULL, 2, 88 species; NULL, 0, 89 blox; NULL, 0, 90 step; NULL, 0, 91 signal; NULL, 0, 92 parent; NULL, 0, 93 selector; NULL, 0, 94 at:ifPresent:; NULL, 2, 95 to:; NULL, 1, 96 addLast:; NULL, 1, 97 squared; NULL, 0, 98 generality; NULL, 0, 99 signalOn:mustBe:; NULL, 2, 100 ensure:; NULL, 1, 101 body; NULL, 0, 102 max:; NULL, 1, 103 keysAndValuesDo:; NULL, 1, 104 printOn:; NULL, 1, 105 isKindOf:; NULL, 1, 106 visitNode:; NULL, 1, 107 addAll:; NULL, 1, 108 isInteger; NULL, 0, 109 name:; NULL, 1, 110 hash; NULL, 0, 111 sqrt; NULL, 0, 112 beep; NULL, 0, 113 primAt:; NULL, 1, 114 environment; NULL, 0, 115 position; NULL, 0, 116 at:ifAbsentPut:; NULL, 2, 117 signal:; NULL, 1, 118 postCopy; NULL, 0, 119 readFrom:; NULL, 1, 120 coefficients:; NULL, 1, 121 clientPI; NULL, 0, 122 flush; NULL, 0, 123 value:value:; NULL, 2, 124 asFloatD; NULL, 0, 125 on:do:; NULL, 2, 126 basicAt:put:; NULL, 2, 127 primSize; NULL, 0, 128 evaluate; NULL, 0, 129 connected; NULL, 0, 130 reset; NULL, 0, 131 copyEmpty:; NULL, 1, 132 start; NULL, 0, 133 signalOn:; NULL, 1, 134 basicAt:; NULL, 1, 135 asClass; NULL, 0, 136 ln; NULL, 0, 137 implementation; NULL, 0, 138 checkResponse; NULL, 0, 139 average; NULL, 0, 140 upTo:; NULL, 1, 141 receiver; NULL, 0, 142 peek; NULL, 0, 143 basicSize; NULL, 0, 144 x:y:; NULL, 2, 145 foregroundColor:; NULL, 1, 146 rows:; NULL, 1, 147 text; NULL, 0, 148 exp; NULL, 0, 149 statements; NULL, 0, 150 body:; NULL, 1, 151 |; NULL, 1, 152 sizeof; NULL, 0, 153 includesKey:; NULL, 1, 154 pi; NULL, 0, 155 completedSuccessfully; NULL, 0, 156 writeStream; NULL, 0, 157 superclass; NULL, 0, 158 arguments:; NULL, 1, 159 state; NULL, 0, 160 truncated; NULL, 0, 161 inject:into:; NULL, 2, 162 replaceFrom:to:with:startingAt:; NULL, 4, 163 current; NULL, 0, 164 between:and:; NULL, 2, 165 retryRelationalOp:coercing:; NULL, 2, 166 connectIfClosed; NULL, 0, 167 detect:ifNone:; NULL, 2, 168 checkError; NULL, 0, 169 executeAndWait:arguments:; NULL, 2, 170 min:; NULL, 1, 171 width; NULL, 0, 172 parentContext; NULL, 0, 173 removeLast; NULL, 0, 174 zero; NULL, 0, 175 bindWith:with:; NULL, 2, 176 temporaries; NULL, 0, 177 asOop; NULL, 0, 178 width:height:; NULL, 2, 179 methodDictionary; NULL, 0, 180 accumulate:; NULL, 1, 181 count; NULL, 0, 182 asLowercase; NULL, 0, 183 asArray; NULL, 0, 184 exists; NULL, 0, 185 signalOn:what:; NULL, 2, 186 select:; NULL, 1, 187 parent:; NULL, 1, 188 selector:; NULL, 1, 189 signalOn:withIndex:; NULL, 2, 190 bind:to:of:parameters:; NULL, 4, 191 return:; NULL, 1, 192 ~~; NULL, 1, 193 changeState:; NULL, 1, 194 sign; NULL, 0, 195 variance; NULL, 0, 196 asVector; NULL, 0, 197 getResponse; NULL, 0, 198 wait; NULL, 0, 199 instanceClass; NULL, 0, 200 asOrderedCollection; NULL, 0, 201 keys; NULL, 0, 202 asFloat; NULL, 0, 203 random; NULL, 0, 204 origin; NULL, 0, 205 superspace; NULL, 0, 206 stop; NULL, 0, 207 perform:; NULL, 1, 208 backgroundColor:; NULL, 1, 209 login; NULL, 0, 210 data:; NULL, 1, 211 nextToken; NULL, 0, 212 primAt:put:; NULL, 2, 213 method; NULL, 0, 214 allSatisfy:; NULL, 1, 215 position:; NULL, 1, 216 default; NULL, 0, 217 atAllPut:; NULL, 1, 218 asSortedCollection; NULL, 0, 219 invalidArgsError:; NULL, 1, 220 nameIn:; NULL, 1, 221 allSubclassesDo:; NULL, 1, 222 signalError; NULL, 0, 223 height; NULL, 0, 224 source; NULL, 0, 225 asNumber; NULL, 0, 226 primitive; NULL, 0, 227 store:; NULL, 1, 228 updateViews; NULL, 0, 229 errorContents:; NULL, 1, 230 displayString; NULL, 0, 231 skipSeparators; NULL, 0, 232 origin:corner:; NULL, 2, 233 activeProcess; NULL, 0, 234 bindWith:; NULL, 1, 235 beConsistent; NULL, 0, 236 at:type:; NULL, 2, 237 skip:; NULL, 1, 238 days; NULL, 0, 239 tclEval:with:; NULL, 2, 240 fromSeconds:; NULL, 1, 241 &; NULL, 1, 242 upToEnd; NULL, 0, 243 variable; NULL, 0, 244 become:; NULL, 1, 245 with:do:; NULL, 2, 246 findIndexOrNil:; NULL, 1, 247 asSeconds; NULL, 0, 248 copyWith:; NULL, 1, 249 background; NULL, 0, 250 status; NULL, 0, 251 selectors:receiver:argument:; NULL, 3, 252 create:; NULL, 1, 253 coerce:; NULL, 1, 254 bytecodeAt:; NULL, 1, 255 smalltalk-3.2.5/libgst/security.c0000644000175000017500000002125512130343734013732 00000000000000/******************************** -*- C -*- **************************** * * Security-related routines. * * ***********************************************************************/ /*********************************************************************** * * Copyright 2003, 2006 Free Software Foundation, Inc. * Written by Paolo Bonzini. * * This file is part of GNU Smalltalk. * * GNU Smalltalk is free software; you can redistribute it and/or modify it * under the terms of the GNU General Public License as published by the Free * Software Foundation; either version 2, or (at your option) any later * version. * * Linking GNU Smalltalk statically or dynamically with other modules is * making a combined work based on GNU Smalltalk. Thus, the terms and * conditions of the GNU General Public License cover the whole * combination. * * In addition, as a special exception, the Free Software Foundation * give you permission to combine GNU Smalltalk with free software * programs or libraries that are released under the GNU LGPL and with * independent programs running under the GNU Smalltalk virtual machine. * * You may copy and distribute such a system following the terms of the * GNU GPL for GNU Smalltalk and the licenses of the other code * concerned, provided that you include the source code of that other * code when and as the GNU GPL requires distribution of source code. * * Note that people who make modified versions of GNU Smalltalk are not * obligated to grant this special exception for their modified * versions; it is their choice whether to do so. The GNU General * Public License gives permission to release a modified version without * this exception; this exception also makes it possible to release a * modified version which carries forward this exception. * * GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or * FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for * more details. * * You should have received a copy of the GNU General Public License along with * GNU Smalltalk; see the file COPYING. If not, write to the Free Software * Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * ***********************************************************************/ #include "gstpriv.h" /* Answer whether the permission permissionOOP (typically found in a SecurityPolicy object) implies the (name,target,action) tuple (which a primitive asks to test). */ static mst_Boolean check_against_permission (OOP permissionOOP, OOP nameOOP, OOP targetOOP, OOP actionOOP); static mst_Boolean string_match (char *pattern, char *string, int plen, int slen); static mst_Boolean permission_is_allowing (OOP permissionOOP); /* Answer whether the permission permissionOOP (typically found in a SecurityPolicy object) implies the (name,target,action) tuple (which a primitive asks to test). */ static mst_Boolean check_against_policy (OOP policyOOP, OOP ownerOOP, OOP nameOOP, OOP targetOOP, OOP actionOOP); static mst_Boolean check_static_permission (OOP receiverOOP, OOP nameOOP, OOP targetOOP, OOP actionOOP); mst_Boolean check_against_permission (OOP permissionOOP, OOP nameOOP, OOP targetOOP, OOP actionOOP) { gst_permission perm = (gst_permission) OOP_TO_OBJ (permissionOOP); gst_object actionArray = OOP_TO_OBJ (perm->actions); if (perm->name != nameOOP) return (false); if (!IS_NIL (perm->target) && !IS_NIL (targetOOP)) { mst_Boolean match_target; match_target = (targetOOP == perm->target); if (!match_target && (OOP_CLASS (targetOOP) != _gst_symbol_class || OOP_CLASS (perm->target) != _gst_symbol_class) && (OOP_CLASS (targetOOP) == _gst_string_class || OOP_CLASS (targetOOP) == _gst_symbol_class) && (OOP_CLASS (perm->target) == _gst_string_class || OOP_CLASS (perm->target) == _gst_symbol_class)) match_target = string_match ((char *) OOP_TO_OBJ (perm->target)->data, (char *) OOP_TO_OBJ (targetOOP)->data, oop_num_fields (perm->target), oop_num_fields (targetOOP)); if (!match_target) return (false); } if (!IS_NIL (perm->actions) && !IS_NIL (actionOOP)) { int n = oop_num_fields (perm->actions); int i; for (i = 0; ;) { if (actionArray->data[i] == actionOOP) break; if (++i == n) return (false); } } return (true); } mst_Boolean string_match (char *pattern, char *string, int plen, int slen) { int i; for (;;) { /* If the string has ended, try to match trailing *'s in the pattern. */ if (slen == 0) { while (plen > 0 && *pattern == '*') pattern++, plen--; return (plen == 0); } /* If the pattern has ended, fail, because we know that slen > 0. */ if (plen == 0) return (false); switch (*pattern) { case '*': /* Skip multiple * wildcards, they don't matter. */ do pattern++, plen--; while (*pattern == '*'); /* Try to be greedy at first, then try shorter matches. */ for (i = slen; i > 0; i--) if (string_match (pattern, string + i, plen, slen - i)) return (true); /* Continue with a void match for the *'s. */ break; default: /* Not a wildcard, match a single character. */ if (*pattern != *string) return (false); /* fall through */ case '#': pattern++, string++, plen--, slen--; break; } } } mst_Boolean permission_is_allowing (OOP permissionOOP) { gst_permission perm = (gst_permission) OOP_TO_OBJ (permissionOOP); return perm->positive != _gst_false_oop; } mst_Boolean check_against_policy (OOP policyOOP, OOP ownerOOP, OOP nameOOP, OOP targetOOP, OOP actionOOP) { gst_security_policy policy; OOP *first, *last; OOP ocOOP; mst_Boolean result; if (IS_NIL (policyOOP)) return (true); policy = (gst_security_policy) OOP_TO_OBJ (policyOOP); ocOOP = dictionary_at (policy->dictionary, nameOOP); result = !IS_OOP_UNTRUSTED (ownerOOP); if (IS_NIL (ocOOP)) return result; first = ordered_collection_begin (ocOOP); last = ordered_collection_end (ocOOP); for (; first < last; first++) if (check_against_permission (*first, nameOOP, targetOOP, actionOOP)) result = permission_is_allowing (*first); return result; } mst_Boolean check_static_permission (OOP receiverOOP, OOP nameOOP, OOP targetOOP, OOP actionOOP) { OOP classOOP = _gst_get_class_object (OOP_CLASS (receiverOOP)); gst_class class = (gst_class) OOP_TO_OBJ (classOOP); OOP policyOOP = class->securityPolicy; return check_against_policy (policyOOP, classOOP, nameOOP, targetOOP, actionOOP); } mst_Boolean _gst_check_permission (OOP contextOOP, OOP nameOOP, OOP targetOOP, OOP actionOOP) { gst_method_context context; mst_Boolean state, found_annotation; do { OOP infoOOP; gst_method_info info; int num_attributes, i; context = (gst_method_context) OOP_TO_OBJ (contextOOP); state = check_static_permission (context->receiver, nameOOP, targetOOP, actionOOP); if (!state) break; infoOOP = get_method_info (context->method); info = (gst_method_info) OOP_TO_OBJ (infoOOP); num_attributes = NUM_INDEXABLE_FIELDS (infoOOP); found_annotation = false; for (i = 0; i < num_attributes; i++) { gst_message attr = (gst_message) OOP_TO_OBJ (info->attributes[i]); gst_object attr_args; OOP permissionOOP; if (attr->selector != _gst_permission_symbol) continue; attr_args = OOP_TO_OBJ (attr->args); permissionOOP = attr_args->data[0]; if (check_against_permission (permissionOOP, nameOOP, targetOOP, actionOOP)) { /* Should we check if the granted permission is statically available? Of course, you can only grant permissions if you own them statically, so the real question is, should we check perm or newPerm? The answer is perm (which has already been found to be available), hence we can skip an expensive static permission check. Suppose we have a method that grants access to all files: it makes more sense if it means ``grant access to all files allowed by the class security policy'', rather than ``grant access to all files if the security policy allows it, else do not grant access to any file''. */ state = permission_is_allowing (permissionOOP); found_annotation = false; } } if (found_annotation) break; contextOOP = context->parentContext; } while (!IS_NIL (contextOOP)); return (state); } smalltalk-3.2.5/libgst/superop1.inl0000644000175000017500000001601712123404352014175 00000000000000/* Automagically generated by superops, do not edit! */ enum { MIN_HASH_VALUE = 109, MAX_HASH_VALUE = 346 }; static const unsigned short asso_values[] = { 101, 68, 85, 108, 17, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 112, 122, 54, 17, 347, 347, 11, 347, 347, 347, 52, 347, 48, 347, 44, 55, 96, 88, 28, 347, 347, 62, 79, 347, 91, 7, 88, 84, 86, 123, 81, 347, 347, 104, 66, 347, 69, 347, 123, 347, 347, 347, 347, 347, 347, 347, 89, 25, 347, 347, 50, 347, 93, 95, 107, 347, 347, 347, 347, 347, 347, 0, 347, 347, 347, 60, 347, 347, 347, 347, 347, 347, 347, 347, 29, 9, 2, 347, 347, 347, 347, 347, 347, 4, 347, 347, 347, 347, 347, 347, 24, 347, 347, 347, 347, 347, 347, 347, 347, 116, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347, 347 }; static const struct superop_with_fixed_arg_1_type keylist[] = { {{ 32, 30, 4}, 197}, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{ 24, 43, 0}, 93}, {{}, -1 }, {{}, -1 }, {{ 21, 101, 0}, 250}, {{}, -1 }, {{}, -1 }, {{ 21, 43, 0}, 165}, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{ 32, 65, 1}, 217}, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{ 36, 68, 1}, 118}, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{ 32, 65, 2}, 160}, {{}, -1 }, {{}, -1 }, {{ 79, 64, 1}, 203}, {{}, -1 }, {{}, -1 }, {{ 32, 30, 1}, 98}, {{}, -1 }, {{ 20, 43, 0}, 86}, {{ 36, 68, 2}, 146}, {{ 32, 28, 1}, 202}, {{ 36, 54, 1}, 157}, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{ 52, 94, 0}, 243}, {{ 32, 65, 0}, 97}, {{ 33, 30, 1}, 194}, {{}, -1 }, {{}, -1 }, {{ 52, 43, 0}, 101}, {{}, -1 }, {{}, -1 }, {{ 32, 30, 2}, 116}, {{}, -1 }, {{ 36, 68, 0}, 172}, {{ 83, 28, 1}, 161}, {{}, -1 }, {{ 36, 54, 2}, 166}, {{}, -1 }, {{ 44, 36, 1}, 136}, {{}, -1 }, {{ 36, 68, 3}, 167}, {{}, -1 }, {{}, -1 }, {{ 32, 32, 0}, 83}, {{ 79, 64, 0}, 154}, {{ 52, 108, 0}, 240}, {{ 52, 65, 0}, 247}, {{ 32, 30, 0}, 73}, {{ 45, 93, 0}, 145}, {{}, -1 }, {{ 52, 92, 0}, 180}, {{ 32, 28, 0}, 84}, {{ 36, 54, 0}, 221}, {{}, -1 }, {{ 32, 30, 3}, 184}, {{ 32, 64, 1}, 119}, {{ 46, 30, 1}, 168}, {{ 24, 42, 0}, 147}, {{ 35, 30, 1}, 213}, {{ 36, 54, 3}, 246}, {{}, -1 }, {{ 32, 71, 1}, 207}, {{}, -1 }, {{ 70, 30, 1}, 183}, {{}, -1 }, {{}, -1 }, {{ 33, 64, 1}, 196}, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{ 32, 64, 2}, 164}, {{ 46, 30, 2}, 230}, {{}, -1 }, {{ 35, 30, 2}, 222}, {{}, -1 }, {{ 83, 71, 1}, 208}, {{}, -1 }, {{}, -1 }, {{ 48, 32, 0}, 123}, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{ 48, 30, 0}, 107}, {{ 32, 46, 0}, 113}, {{ 72, 108, 0}, 170}, {{}, -1 }, {{ 32, 64, 0}, 89}, {{}, -1 }, {{ 52, 54, 0}, 173}, {{ 35, 30, 0}, 219}, {{}, -1 }, {{}, -1 }, {{ 32, 71, 0}, 190}, {{ 32, 34, 0}, 220}, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{ 20, 42, 0}, 130}, {{ 45, 39, 0}, 232}, {{ 48, 52, 0}, 72}, {{ 56, 65, 0}, 74}, {{}, -1 }, {{ 48, 54, 0}, 102}, {{}, -1 }, {{ 52, 46, 0}, 251}, {{}, -1 }, {{}, -1 }, {{ 72, 30, 0}, 238}, {{}, -1 }, {{ 52, 42, 0}, 114}, {{}, -1 }, {{}, -1 }, {{ 48, 40, 0}, 134}, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{ 56, 32, 0}, 79}, {{}, -1 }, {{ 48, 35, 0}, 175}, {{}, -1 }, {{ 56, 30, 0}, 76}, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{ 56, 28, 0}, 105}, {{ 72, 54, 0}, 96}, {{ 48, 34, 0}, 135}, {{}, -1 }, {{ 47, 64, 1}, 244}, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{ 56, 46, 0}, 192}, {{}, -1 }, {{}, -1 }, {{ 56, 64, 0}, 171}, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{ 56, 51, 0}, 66}, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{ 56, 18, 0}, 129}, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{ 56, 117, 0}, 174}, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{}, -1 }, {{ 56, 19, 0}, 201} }; smalltalk-3.2.5/libgst/prims.inl0000644000175000017500000071751612130455566013600 00000000000000/******************************** -*- C -*- **************************** * * Byte code interpreter primitives include file * * ***********************************************************************/ /*********************************************************************** * * Copyright 1988,89,90,91,92,94,95,99,2000,2001,2002,2003,2006,2007,2008,2009 * Free Software Foundation, Inc. * Written by Steve Byrne. * * This file is part of GNU Smalltalk. * * GNU Smalltalk is free software; you can redistribute it and/or modify it * under the terms of the GNU General Public License as published by the Free * Software Foundation; either version 2, or (at your option) any later * version. * * Linking GNU Smalltalk statically or dynamically with other modules is * making a combined work based on GNU Smalltalk. Thus, the terms and * conditions of the GNU General Public License cover the whole * combination. * * In addition, as a special exception, the Free Software Foundation * give you permission to combine GNU Smalltalk with free software * programs or libraries that are released under the GNU LGPL and with * independent programs running under the GNU Smalltalk virtual machine. * * You may copy and distribute such a system following the terms of the * GNU GPL for GNU Smalltalk and the licenses of the other code * concerned, provided that you include the source code of that other * code when and as the GNU GPL requires distribution of source code. * * Note that people who make modified versions of GNU Smalltalk are not * obligated to grant this special exception for their modified * versions; it is their choice whether to do so. The GNU General * Public License gives permission to release a modified version without * this exception; this exception also makes it possible to release a * modified version which carries forward this exception. * * GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or * FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for * more details. * * You should have received a copy of the GNU General Public License along with * GNU Smalltalk; see the file COPYING. If not, write to the Free Software * Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * ***********************************************************************/ #ifdef OPTIMIZE #define RECEIVER_IS_INT(x) (true) #define RECEIVER_IS_OOP(x) (true) #define RECEIVER_IS_CLASS(x, y) (true) #define RECEIVER_IS_A_KIND_OF(x, y) (true) #define PRIM_CHECKS_RECEIVER PRIM_SUCCEED #else #define RECEIVER_IS_INT(x) IS_INT((x)) #define RECEIVER_IS_OOP(x) IS_OOP((x)) #define RECEIVER_IS_CLASS(x, y) IS_CLASS((x), (y)) #define RECEIVER_IS_A_KIND_OF(x, y) is_a_kind_of((x), (y)) #define PRIM_CHECKS_RECEIVER (PRIM_SUCCEED | PRIM_FAIL) #endif #ifdef HAVE_GMP #define PRIM_USES_GMP (PRIM_SUCCEED | PRIM_FAIL) #else #define PRIM_USES_GMP PRIM_FAIL #endif #ifdef ENABLE_JIT_TRANSLATION #define PRIM_FAILED return ((intptr_t) -1) #define PRIM_SUCCEEDED return ((intptr_t) 0) #define PRIM_SUCCEEDED_RELOAD_IP return ((intptr_t) native_ip) #else #define PRIM_FAILED return (true) #define PRIM_SUCCEEDED return (false) #define PRIM_SUCCEEDED_RELOAD_IP return (false) #endif #define INT_BIN_OP(op, noOverflow) { \ OOP oop1; \ OOP oop2; \ mst_Boolean overflow; \ oop2 = POP_OOP(); \ oop1 = POP_OOP(); \ if COMMON (RECEIVER_IS_INT(oop1) && IS_INT(oop2)) {\ intptr_t iarg1, iarg2; \ iarg1 = TO_INT(oop1); \ iarg2 = TO_INT(oop2); \ \ oop1 = op; \ if COMMON (noOverflow || !overflow) { \ PUSH_OOP(oop1); \ PRIM_SUCCEEDED; \ } \ } \ UNPOP(2); \ PRIM_FAILED; \ } #define BOOL_BIN_OP(operator) { \ OOP oop1; \ OOP oop2; \ oop2 = POP_OOP(); \ oop1 = POP_OOP(); \ if COMMON (RECEIVER_IS_INT(oop1) && IS_INT(oop2)) { \ PUSH_BOOLEAN( ((intptr_t)oop1) operator ((intptr_t)oop2) ); \ PRIM_SUCCEEDED; \ } \ UNPOP(2); \ PRIM_FAILED; \ } /* SmallInteger + arg */ static intptr_t VMpr_SmallInteger_plus (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_SmallInteger_minus (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_SmallInteger_lt (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_SmallInteger_gt (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_SmallInteger_le (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_SmallInteger_ge (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_SmallInteger_eq (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_SmallInteger_ne (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_SmallInteger_times (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_SmallInteger_divide (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_SmallInteger_modulo (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_SmallInteger_intDiv (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_SmallInteger_quo (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_SmallInteger_bitAnd (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_SmallInteger_bitOr (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_SmallInteger_bitXor (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_SmallInteger_bitShift (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_SmallInteger_scramble (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_SmallInteger_asFloatD (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_SmallInteger_asFloatE (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_SmallInteger_asFloatQ (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_LargeInteger_eq (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_LargeInteger_ne (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_LargeInteger_lt (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_LargeInteger_le (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_LargeInteger_gt (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_LargeInteger_ge (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_LargeInteger_times (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_LargeInteger_intDiv (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_LargeInteger_modulo (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_LargeInteger_divExact (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_LargeInteger_quo (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_LargeInteger_rem (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_LargeInteger_negated (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_LargeInteger_bitAnd (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_LargeInteger_bitOr (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_LargeInteger_bitXor (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_LargeInteger_bitInvert (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_LargeInteger_bitShift (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_LargeInteger_plus (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_LargeInteger_minus (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_LargeInteger_gcd (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_LargeInteger_asFloatD (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_LargeInteger_asFloatE (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_LargeInteger_asFloatQ (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_FloatD_arith (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_FloatD_truncated (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_FloatD_fractionPart (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_FloatD_exponent (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_FloatD_timesTwoPower (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_FloatD_asFloatE (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_FloatD_asFloatQ (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_FloatE_arith (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_FloatE_truncated (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_FloatE_fractionPart (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_FloatE_exponent (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_FloatE_timesTwoPower (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_FloatE_asFloatD (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_FloatE_asFloatQ (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_FloatQ_arith (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_FloatQ_truncated (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_FloatQ_fractionPart (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_FloatQ_exponent (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_FloatQ_timesTwoPower (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_FloatQ_asFloatD (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_FloatQ_asFloatE (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_Object_basicAt (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_Object_basicAtPut (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_Object_basicSize (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_CharacterArray_valueAt (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_CharacterArray_valueAtPut (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_CompiledCode_verificationResult (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_CompiledBlock_create (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_CompiledMethod_create (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_Object_shallowCopy (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_Behavior_basicNew (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_Behavior_basicNewColon (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_Object_become (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_Object_instVarAt (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_Object_instVarAtPut (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_Object_hash (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_SmallInteger_asObject (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_SmallInteger_nextValidOop (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_Behavior_someInstance (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_Object_nextInstance (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_Object_becomeForward (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_Object_allOwners (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_ContextPart_thisContext (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_ContextPart_continue (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_Continuation_resume (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_BlockClosure_value (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_BlockClosure_cull (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_BlockClosure_valueAndResumeOnUnwind (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_BlockClosure_valueWithArguments (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_Object_perform (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_Object_performWithArguments (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_Semaphore_notifyAll (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_Semaphore_signalNotify (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_Semaphore_lock (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_Semaphore_wait (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_Semaphore_waitAfterSignalling (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_Process_suspend (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_Process_resume (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_Process_singleStepWaitingOn (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_Process_yield (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_Processor_pause (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_Behavior_flushCache (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_CompiledCode_discardTranslation (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_Object_changeClassTo (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_Time_timezoneBias (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_Time_timezone (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_Time_secondClock (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_Time_nanosecondClock (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_Time_millisecondClock (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_Processor_signalAt (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_Processor_isTimeoutProgrammed (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_String_similarityTo (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_String_hash (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_ArrayedCollection_equal (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_ArrayedCollection_indexOfStartingAt (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_ArrayedCollection_replaceFromToWithStartingAt (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_Object_identity (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_Object_class (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_ObjectMemory_quit (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_ObjectMemory_abort (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_Dictionary_at (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_Object_bootstrapException (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_Character_create (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_UnicodeCharacter_create (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_Character_equal (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_Symbol_intern (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_Dictionary_new (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_Memory_addressOfOOP (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_Memory_addressOf (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_SystemDictionary_backtrace (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_SystemDictionary_getTraceFlag (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_SystemDictionary_setTraceFlag (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_Memory_at (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_Memory_atPut (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_Behavior_methodsFor (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_Behavior_methodsForIfTrue (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_Processor_disableEnableInterrupts (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_Processor_signalOnInterrupt (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_ObjectMemory_getSpaceGrowRate (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_ObjectMemory_setSpaceGrowRate (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_ObjectMemory_getSmoothingFactor (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_ObjectMemory_setSmoothingFactor (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_ObjectMemory_getGrowThresholdPercent (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_ObjectMemory_setGrowThresholdPercent (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_ObjectMemory_getBigObjectThreshold (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_ObjectMemory_setBigObjectThreshold (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_ObjectMemory_growTo (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_ObjectMemory_update (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_CObject_allocType (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_Float_sin (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_Float_cos (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_Float_tan (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_Float_arcSin (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_Float_arcCos (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_Float_arcTan (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_Float_exp (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_Float_ln (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_Float_pow (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_CObject_free (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_Float_sqrt (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_Float_ceil_floor (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_Behavior_basicNewFixed (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_Behavior_basicNewFixedColon (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_Object_tenure (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_Object_makeFixed (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_CObject_at (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_CObject_atPut (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_CObject_address (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_CObject_addressColon (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_CString_replaceWith (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_ByteArray_fromCData_size (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_String_fromCData_size (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_String_fromCData (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_String_ByteArray_asCData (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_SystemDictionary_byteCodeCounter (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_SystemDictionary_debug (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_Object_isUntrusted (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_Object_makeUntrusted (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_Object_isReadOnly (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_Object_makeReadOnly (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_Behavior_primCompile (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_Behavior_primCompileIfError (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_CCallbackDescriptor_link (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_CFuncDescriptor_addressOf (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_ObjectMemory_snapshot (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_Object_basicPrint (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_Object_makeWeak (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_Stream_fileInLine (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_FileDescriptor_fileOp (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_FileDescriptor_socketOp (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_CFuncDescriptor_asyncCall (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_CFuncDescriptor_call (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_Object_makeEphemeron (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_Namespace_setCurrent (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_ObjectMemory_gcPrimitives (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_SystemDictionary_rawProfile (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); static intptr_t VMpr_HOLE (int id ATTRIBUTE_UNUSED, volatile int numArgs ATTRIBUTE_UNUSED); intptr_t VMpr_SmallInteger_plus (int id, volatile int numArgs) #line 121 "prims.def" { _gst_primitives_executed++; INT_BIN_OP (add_with_check (oop1, oop2, &overflow), false); } /* SmallInteger - arg */ intptr_t VMpr_SmallInteger_minus (int id, volatile int numArgs) #line 128 "prims.def" { _gst_primitives_executed++; INT_BIN_OP (sub_with_check (oop1, oop2, &overflow), false); } /* SmallInteger < arg */ intptr_t VMpr_SmallInteger_lt (int id, volatile int numArgs) #line 135 "prims.def" { _gst_primitives_executed++; BOOL_BIN_OP (<); } /* SmallInteger > arg */ intptr_t VMpr_SmallInteger_gt (int id, volatile int numArgs) #line 142 "prims.def" { _gst_primitives_executed++; BOOL_BIN_OP (>); } /* SmallInteger <= arg */ intptr_t VMpr_SmallInteger_le (int id, volatile int numArgs) #line 149 "prims.def" { _gst_primitives_executed++; BOOL_BIN_OP (<=); } /* SmallInteger >= arg */ intptr_t VMpr_SmallInteger_ge (int id, volatile int numArgs) #line 156 "prims.def" { _gst_primitives_executed++; BOOL_BIN_OP (>=); } /* SmallInteger =, == arg */ intptr_t VMpr_SmallInteger_eq (int id, volatile int numArgs) #line 163 "prims.def" { _gst_primitives_executed++; BOOL_BIN_OP ( ==); } /* SmallInteger ~=, ~~ arg */ intptr_t VMpr_SmallInteger_ne (int id, volatile int numArgs) #line 170 "prims.def" { _gst_primitives_executed++; BOOL_BIN_OP (!=); } /* SmallInteger * arg */ intptr_t VMpr_SmallInteger_times (int id, volatile int numArgs) #line 177 "prims.def" { _gst_primitives_executed++; INT_BIN_OP (mul_with_check (oop1, oop2, &overflow), false); } /* SmallInteger / arg */ /* quotient as exact as possible */ intptr_t VMpr_SmallInteger_divide (int id, volatile int numArgs) #line 185 "prims.def" { OOP oop1; OOP oop2; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = POP_OOP (); if (RECEIVER_IS_INT (oop1) && IS_INT (oop2) && oop2 != FROM_INT (0)) { intptr_t iarg1, iarg2, result; iarg1 = TO_INT (oop1); iarg2 = TO_INT (oop2); result = iarg1 / iarg2; iarg2 *= result; if COMMON (iarg1 == iarg2) { PUSH_INT (result); PRIM_SUCCEEDED; } } UNPOP (2); PRIM_FAILED; } /* SmallInteger \\ arg */ /* remainder truncated towards -infinity */ intptr_t VMpr_SmallInteger_modulo (int id, volatile int numArgs) #line 212 "prims.def" { OOP oop1; OOP oop2; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = POP_OOP (); if COMMON (RECEIVER_IS_INT (oop1) && IS_INT (oop2) && oop2 != FROM_INT (0)) { intptr_t iarg1, iarg2, result; iarg1 = TO_INT (oop1); iarg2 = TO_INT (oop2); result = iarg1 % iarg2; PUSH_INT (result && ((result ^ iarg2) < 0) ? result + iarg2 : result); PRIM_SUCCEEDED; } UNPOP (2); PRIM_FAILED; } /* SmallInteger // arg */ /* quotient truncated towards -infinity */ intptr_t VMpr_SmallInteger_intDiv (int id, volatile int numArgs) #line 236 "prims.def" { OOP oop1; OOP oop2; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = POP_OOP (); if COMMON (RECEIVER_IS_INT (oop1) && IS_INT (oop2) && oop2 != FROM_INT (0)) { intptr_t iarg1, iarg2; iarg1 = TO_INT (oop1); iarg2 = TO_INT (oop2); if (iarg2 < 0) { /* make the divisor positive */ iarg1 = -iarg1; iarg2 = -iarg2; } if (iarg1 < 0) /* differing signs => use black magic */ PUSH_INT (-((iarg2 - 1 - iarg1) / iarg2)); else PUSH_INT (iarg1 / iarg2); PRIM_SUCCEEDED; } UNPOP (2); PRIM_FAILED; } /* SmallInteger quo: arg */ /* quotient truncated towards 0 */ intptr_t VMpr_SmallInteger_quo (int id, volatile int numArgs) #line 267 "prims.def" { OOP oop1; OOP oop2; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = POP_OOP (); if COMMON (RECEIVER_IS_INT (oop1) && IS_INT (oop2)) { intptr_t iarg1, iarg2; iarg1 = TO_INT (oop1); iarg2 = TO_INT (oop2); if COMMON (iarg2 != 0) { PUSH_INT (iarg1 / iarg2); PRIM_SUCCEEDED; } } UNPOP (2); PRIM_FAILED; } /* SmallInteger bitAnd: arg */ intptr_t VMpr_SmallInteger_bitAnd (int id, volatile int numArgs) #line 291 "prims.def" { _gst_primitives_executed++; INT_BIN_OP (tagged_and (oop1, oop2), true); } /* SmallInteger bitOr: arg */ intptr_t VMpr_SmallInteger_bitOr (int id, volatile int numArgs) #line 298 "prims.def" { _gst_primitives_executed++; INT_BIN_OP (tagged_or (oop1, oop2), true); } /* SmallInteger bitXor: arg */ intptr_t VMpr_SmallInteger_bitXor (int id, volatile int numArgs) #line 305 "prims.def" { _gst_primitives_executed++; INT_BIN_OP (tagged_xor (oop1, oop2), true); } /* SmallInteger bitShift: arg */ intptr_t VMpr_SmallInteger_bitShift (int id, volatile int numArgs) #line 312 "prims.def" { OOP oop1; OOP oop2; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = POP_OOP (); if COMMON (RECEIVER_IS_INT (oop1) && IS_INT (oop2)) { intptr_t iarg1; intptr_t iarg2; iarg1 = TO_INT (oop1); iarg2 = TO_INT (oop2); if (iarg2 < 0) { if (iarg2 >= -ST_INT_SIZE) PUSH_INT (iarg1 >> -iarg2); else PUSH_INT (iarg1 >> ST_INT_SIZE); PRIM_SUCCEEDED; } if COMMON (iarg2 < ST_INT_SIZE) { intptr_t result = iarg1 << iarg2; if ((result >> iarg2) == iarg1 && !INT_OVERFLOW(result)) { PUSH_INT (result); PRIM_SUCCEEDED; } } } UNPOP (2); PRIM_FAILED; } /* SmallInteger scramble */ intptr_t VMpr_SmallInteger_scramble (int id, volatile int numArgs) #line 351 "prims.def" { OOP oop1; _gst_primitives_executed++; oop1 = POP_OOP (); if COMMON (RECEIVER_IS_INT (oop1)) { PUSH_INT (scramble (TO_INT (oop1))); PRIM_SUCCEEDED; } UNPOP (1); PRIM_FAILED; } /* SmallInteger asFloatD */ intptr_t VMpr_SmallInteger_asFloatD (int id, volatile int numArgs) #line 369 "prims.def" { OOP oop1; _gst_primitives_executed++; oop1 = POP_OOP (); if COMMON (RECEIVER_IS_INT (oop1)) { PUSH_OOP (floatd_new ((double) TO_INT (oop1))); PRIM_SUCCEEDED; } UNPOP (1); PRIM_FAILED; } /* SmallInteger asFloatE */ intptr_t VMpr_SmallInteger_asFloatE (int id, volatile int numArgs) #line 386 "prims.def" { OOP oop1; _gst_primitives_executed++; oop1 = POP_OOP (); if COMMON (RECEIVER_IS_INT (oop1)) { PUSH_OOP (floate_new ((float) TO_INT (oop1))); PRIM_SUCCEEDED; } UNPOP (1); PRIM_FAILED; } /* SmallInteger asFloatQ */ intptr_t VMpr_SmallInteger_asFloatQ (int id, volatile int numArgs) #line 403 "prims.def" { OOP oop1; _gst_primitives_executed++; oop1 = POP_OOP (); if COMMON (RECEIVER_IS_INT (oop1)) { PUSH_OOP (floatq_new ((long double) TO_INT (oop1))); PRIM_SUCCEEDED; } UNPOP (1); PRIM_FAILED; } intptr_t VMpr_LargeInteger_eq (int id, volatile int numArgs) #line 418 "prims.def" { #ifdef HAVE_GMP gst_mpz a = { 0, 0, NULL }; gst_mpz b = { 0, 0, NULL }; OOP oop1, oop2; int result; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = POP_OOP (); if COMMON (IS_INT (oop1) || SUPERCLASS (OOP_CLASS (oop1)) == _gst_large_integer_class || OOP_CLASS (oop1) == _gst_large_zero_integer_class) _gst_mpz_from_oop (&a, oop1); else { UNPOP (2); PRIM_FAILED; } if COMMON (IS_INT (oop2) || SUPERCLASS (OOP_CLASS (oop2)) == _gst_large_integer_class || OOP_CLASS (oop2) == _gst_large_zero_integer_class) _gst_mpz_from_oop (&b, oop2); else { _gst_mpz_clear (&a); UNPOP (2); PRIM_FAILED; } result = _gst_mpz_cmp (&a, &b); _gst_mpz_clear (&a); _gst_mpz_clear (&b); PUSH_BOOLEAN (result == 0); PRIM_SUCCEEDED; #else PRIM_FAILED; #endif } intptr_t VMpr_LargeInteger_ne (int id, volatile int numArgs) #line 460 "prims.def" { #ifdef HAVE_GMP gst_mpz a = { 0, 0, NULL }; gst_mpz b = { 0, 0, NULL }; OOP oop1, oop2; int result; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = POP_OOP (); if COMMON (IS_INT (oop1) || SUPERCLASS (OOP_CLASS (oop1)) == _gst_large_integer_class || OOP_CLASS (oop1) == _gst_large_zero_integer_class) _gst_mpz_from_oop (&a, oop1); else { UNPOP (2); PRIM_FAILED; } if COMMON (IS_INT (oop2) || SUPERCLASS (OOP_CLASS (oop2)) == _gst_large_integer_class || OOP_CLASS (oop2) == _gst_large_zero_integer_class) _gst_mpz_from_oop (&b, oop2); else { _gst_mpz_clear (&a); UNPOP (2); PRIM_FAILED; } result = _gst_mpz_cmp (&a, &b); _gst_mpz_clear (&a); _gst_mpz_clear (&b); PUSH_BOOLEAN (result != 0); PRIM_SUCCEEDED; #else PRIM_FAILED; #endif } intptr_t VMpr_LargeInteger_lt (int id, volatile int numArgs) #line 503 "prims.def" { #ifdef HAVE_GMP gst_mpz a = { 0, 0, NULL }; gst_mpz b = { 0, 0, NULL }; OOP oop1, oop2; int result; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = POP_OOP (); if COMMON (IS_INT (oop1) || SUPERCLASS (OOP_CLASS (oop1)) == _gst_large_integer_class || OOP_CLASS (oop1) == _gst_large_zero_integer_class) _gst_mpz_from_oop (&a, oop1); else { UNPOP (2); PRIM_FAILED; } if COMMON (IS_INT (oop2) || SUPERCLASS (OOP_CLASS (oop2)) == _gst_large_integer_class || OOP_CLASS (oop2) == _gst_large_zero_integer_class) _gst_mpz_from_oop (&b, oop2); else { _gst_mpz_clear (&a); UNPOP (2); PRIM_FAILED; } result = _gst_mpz_cmp (&a, &b); _gst_mpz_clear (&a); _gst_mpz_clear (&b); PUSH_BOOLEAN (result < 0); PRIM_SUCCEEDED; #else PRIM_FAILED; #endif } intptr_t VMpr_LargeInteger_le (int id, volatile int numArgs) #line 546 "prims.def" { #ifdef HAVE_GMP gst_mpz a = { 0, 0, NULL }; gst_mpz b = { 0, 0, NULL }; OOP oop1, oop2; int result; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = POP_OOP (); if COMMON (IS_INT (oop1) || SUPERCLASS (OOP_CLASS (oop1)) == _gst_large_integer_class || OOP_CLASS (oop1) == _gst_large_zero_integer_class) _gst_mpz_from_oop (&a, oop1); else { UNPOP (2); PRIM_FAILED; } if COMMON (IS_INT (oop2) || SUPERCLASS (OOP_CLASS (oop2)) == _gst_large_integer_class || OOP_CLASS (oop2) == _gst_large_zero_integer_class) _gst_mpz_from_oop (&b, oop2); else { _gst_mpz_clear (&a); UNPOP (2); PRIM_FAILED; } result = _gst_mpz_cmp (&a, &b); _gst_mpz_clear (&a); _gst_mpz_clear (&b); PUSH_BOOLEAN (result <= 0); PRIM_SUCCEEDED; #else PRIM_FAILED; #endif } intptr_t VMpr_LargeInteger_gt (int id, volatile int numArgs) #line 589 "prims.def" { #ifdef HAVE_GMP gst_mpz a = { 0, 0, NULL }; gst_mpz b = { 0, 0, NULL }; OOP oop1, oop2; int result; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = POP_OOP (); if COMMON (IS_INT (oop1) || SUPERCLASS (OOP_CLASS (oop1)) == _gst_large_integer_class || OOP_CLASS (oop1) == _gst_large_zero_integer_class) _gst_mpz_from_oop (&a, oop1); else { UNPOP (2); PRIM_FAILED; } if COMMON (IS_INT (oop2) || SUPERCLASS (OOP_CLASS (oop2)) == _gst_large_integer_class || OOP_CLASS (oop2) == _gst_large_zero_integer_class) _gst_mpz_from_oop (&b, oop2); else { _gst_mpz_clear (&a); UNPOP (2); PRIM_FAILED; } result = _gst_mpz_cmp (&a, &b); _gst_mpz_clear (&a); _gst_mpz_clear (&b); PUSH_BOOLEAN (result > 0); PRIM_SUCCEEDED; #else PRIM_FAILED; #endif } intptr_t VMpr_LargeInteger_ge (int id, volatile int numArgs) #line 632 "prims.def" { #ifdef HAVE_GMP gst_mpz a = { 0, 0, NULL }; gst_mpz b = { 0, 0, NULL }; OOP oop1, oop2; int result; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = POP_OOP (); if COMMON (IS_INT (oop1) || SUPERCLASS (OOP_CLASS (oop1)) == _gst_large_integer_class || OOP_CLASS (oop1) == _gst_large_zero_integer_class) _gst_mpz_from_oop (&a, oop1); else { UNPOP (2); PRIM_FAILED; } if COMMON (IS_INT (oop2) || SUPERCLASS (OOP_CLASS (oop2)) == _gst_large_integer_class || OOP_CLASS (oop2) == _gst_large_zero_integer_class) _gst_mpz_from_oop (&b, oop2); else { _gst_mpz_clear (&a); UNPOP (2); PRIM_FAILED; } result = _gst_mpz_cmp (&a, &b); _gst_mpz_clear (&a); _gst_mpz_clear (&b); PUSH_BOOLEAN (result >= 0); PRIM_SUCCEEDED; #else PRIM_FAILED; #endif } intptr_t VMpr_LargeInteger_times (int id, volatile int numArgs) #line 675 "prims.def" { #ifdef HAVE_GMP gst_mpz a = { 0, 0, NULL }; gst_mpz b = { 0, 0, NULL }; gst_mpz c = { 0, 0, NULL }; OOP oop1, oop2, oop3; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = POP_OOP (); if COMMON (IS_INT (oop1) || SUPERCLASS (OOP_CLASS (oop1)) == _gst_large_integer_class || OOP_CLASS (oop1) == _gst_large_zero_integer_class) _gst_mpz_from_oop (&a, oop1); else { UNPOP (2); PRIM_FAILED; } if COMMON (IS_INT (oop2) || SUPERCLASS (OOP_CLASS (oop2)) == _gst_large_integer_class || OOP_CLASS (oop2) == _gst_large_zero_integer_class) _gst_mpz_from_oop (&b, oop2); else { _gst_mpz_clear (&a); UNPOP (2); PRIM_FAILED; } _gst_mpz_mul (&c, &a, &b); oop3 = _gst_oop_from_mpz (&c); _gst_mpz_clear (&a); _gst_mpz_clear (&b); _gst_mpz_clear (&c); PUSH_OOP (oop3); PRIM_SUCCEEDED; #else PRIM_FAILED; #endif } intptr_t VMpr_LargeInteger_intDiv (int id, volatile int numArgs) #line 721 "prims.def" { #ifdef HAVE_GMP gst_mpz a = { 0, 0, NULL }; gst_mpz b = { 0, 0, NULL }; gst_mpz q = { 0, 0, NULL }; gst_mpz r = { 0, 0, NULL }; OOP oop1, oop2, oop3; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = POP_OOP (); if COMMON (IS_INT (oop1) || SUPERCLASS (OOP_CLASS (oop1)) == _gst_large_integer_class || OOP_CLASS (oop1) == _gst_large_zero_integer_class) _gst_mpz_from_oop (&a, oop1); else { UNPOP (2); PRIM_FAILED; } if COMMON (IS_INT (oop2) && oop2 != FROM_INT (0)) _gst_mpz_fdiv_qr_si (&q, &a, TO_INT(oop2)); else if (IS_OOP (oop2) && SUPERCLASS (OOP_CLASS (oop2)) == _gst_large_integer_class) { _gst_mpz_from_oop (&b, oop2); _gst_mpz_fdiv_qr (&q, &r, &a, &b); _gst_mpz_clear (&r); _gst_mpz_clear (&b); } else { _gst_mpz_clear (&a); UNPOP (2); PRIM_FAILED; } oop3 = _gst_oop_from_mpz (&q); _gst_mpz_clear (&a); _gst_mpz_clear (&q); PUSH_OOP (oop3); PRIM_SUCCEEDED; #else PRIM_FAILED; #endif } intptr_t VMpr_LargeInteger_modulo (int id, volatile int numArgs) #line 771 "prims.def" { #ifdef HAVE_GMP gst_mpz a = { 0, 0, NULL }; gst_mpz b = { 0, 0, NULL }; gst_mpz q = { 0, 0, NULL }; gst_mpz r = { 0, 0, NULL }; OOP oop1, oop2, oop3; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = POP_OOP (); if COMMON (IS_INT (oop1) || SUPERCLASS (OOP_CLASS (oop1)) == _gst_large_integer_class || OOP_CLASS (oop1) == _gst_large_zero_integer_class) _gst_mpz_from_oop (&a, oop1); else { UNPOP (2); PRIM_FAILED; } if COMMON (IS_INT (oop2) && oop2 != FROM_INT (0)) { mp_limb_t rem = _gst_mpz_fdiv_qr_si (&q, &a, TO_INT(oop2)); oop3 = FROM_INT (rem); } else if (IS_OOP (oop2) && SUPERCLASS (OOP_CLASS (oop2)) == _gst_large_integer_class) { _gst_mpz_from_oop (&b, oop2); _gst_mpz_fdiv_qr (&q, &r, &a, &b); oop3 = _gst_oop_from_mpz (&r); _gst_mpz_clear (&r); _gst_mpz_clear (&b); } else { _gst_mpz_clear (&a); UNPOP (2); PRIM_FAILED; } _gst_mpz_clear (&a); _gst_mpz_clear (&q); PUSH_OOP (oop3); PRIM_SUCCEEDED; #else PRIM_FAILED; #endif } intptr_t VMpr_LargeInteger_divExact (int id, volatile int numArgs) #line 824 "prims.def" { #ifdef HAVE_GMP gst_mpz a = { 0, 0, NULL }; gst_mpz b = { 0, 0, NULL }; gst_mpz q = { 0, 0, NULL }; OOP oop1, oop2, oop3; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = POP_OOP (); if COMMON (IS_INT (oop1) || SUPERCLASS (OOP_CLASS (oop1)) == _gst_large_integer_class || OOP_CLASS (oop1) == _gst_large_zero_integer_class) _gst_mpz_from_oop (&a, oop1); else { UNPOP (2); PRIM_FAILED; } if COMMON (IS_INT (oop2) && oop2 != FROM_INT (0)) _gst_mpz_tdiv_qr_si (&q, &a, TO_INT(oop2)); else if (IS_OOP (oop2) && SUPERCLASS (OOP_CLASS (oop2)) == _gst_large_integer_class) { _gst_mpz_from_oop (&b, oop2); _gst_mpz_divexact (&q, &a, &b); _gst_mpz_clear (&b); } else { _gst_mpz_clear (&a); UNPOP (2); PRIM_FAILED; } oop3 = _gst_oop_from_mpz (&q); _gst_mpz_clear (&a); _gst_mpz_clear (&q); PUSH_OOP (oop3); PRIM_SUCCEEDED; #else PRIM_FAILED; #endif } intptr_t VMpr_LargeInteger_quo (int id, volatile int numArgs) #line 871 "prims.def" { #ifdef HAVE_GMP gst_mpz a = { 0, 0, NULL }; gst_mpz b = { 0, 0, NULL }; gst_mpz q = { 0, 0, NULL }; gst_mpz r = { 0, 0, NULL }; OOP oop1, oop2, oop3; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = POP_OOP (); if COMMON (IS_INT (oop1) || SUPERCLASS (OOP_CLASS (oop1)) == _gst_large_integer_class || OOP_CLASS (oop1) == _gst_large_zero_integer_class) _gst_mpz_from_oop (&a, oop1); else { UNPOP (2); PRIM_FAILED; } if COMMON (IS_INT (oop2) && oop2 != FROM_INT (0)) _gst_mpz_tdiv_qr_si (&q, &a, TO_INT(oop2)); else if (IS_OOP (oop2) && SUPERCLASS (OOP_CLASS (oop2)) == _gst_large_integer_class) { _gst_mpz_from_oop (&b, oop2); _gst_mpz_tdiv_qr (&q, &r, &a, &b); _gst_mpz_clear (&r); _gst_mpz_clear (&b); } else { _gst_mpz_clear (&a); UNPOP (2); PRIM_FAILED; } oop3 = _gst_oop_from_mpz (&q); _gst_mpz_clear (&a); _gst_mpz_clear (&q); PUSH_OOP (oop3); PRIM_SUCCEEDED; #else PRIM_FAILED; #endif } intptr_t VMpr_LargeInteger_rem (int id, volatile int numArgs) #line 921 "prims.def" { #ifdef HAVE_GMP gst_mpz a = { 0, 0, NULL }; gst_mpz b = { 0, 0, NULL }; gst_mpz q = { 0, 0, NULL }; gst_mpz r = { 0, 0, NULL }; OOP oop1, oop2, oop3; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = POP_OOP (); if COMMON (IS_INT (oop1) || SUPERCLASS (OOP_CLASS (oop1)) == _gst_large_integer_class || OOP_CLASS (oop1) == _gst_large_zero_integer_class) _gst_mpz_from_oop (&a, oop1); else { UNPOP (2); PRIM_FAILED; } if COMMON (IS_INT (oop2) && oop2 != FROM_INT (0)) { mp_limb_t rem = _gst_mpz_tdiv_qr_si (&q, &a, TO_INT(oop2)); oop3 = FROM_INT (rem); } else if (IS_OOP (oop2) && SUPERCLASS (OOP_CLASS (oop2)) == _gst_large_integer_class) { _gst_mpz_from_oop (&b, oop2); _gst_mpz_tdiv_qr (&q, &r, &a, &b); oop3 = _gst_oop_from_mpz (&r); _gst_mpz_clear (&r); _gst_mpz_clear (&b); } else { _gst_mpz_clear (&a); UNPOP (2); PRIM_FAILED; } _gst_mpz_clear (&a); _gst_mpz_clear (&q); PUSH_OOP (oop3); PRIM_SUCCEEDED; #else PRIM_FAILED; #endif } intptr_t VMpr_LargeInteger_negated (int id, volatile int numArgs) #line 974 "prims.def" { #ifdef HAVE_GMP gst_mpz a = { 0, 0, NULL }; gst_mpz b = { 0, 0, NULL }; gst_mpz c = { 0, 0, NULL }; OOP oop2, oop3; _gst_primitives_executed++; oop2 = POP_OOP (); if COMMON (IS_INT (oop2) || SUPERCLASS (OOP_CLASS (oop2)) == _gst_large_integer_class || OOP_CLASS (oop2) == _gst_large_zero_integer_class) _gst_mpz_from_oop (&b, oop2); else { UNPOP (2); PRIM_FAILED; } _gst_mpz_sub (&c, &a, &b); oop3 = _gst_oop_from_mpz (&c); _gst_mpz_clear (&b); _gst_mpz_clear (&c); PUSH_OOP (oop3); PRIM_SUCCEEDED; #else PRIM_FAILED; #endif } intptr_t VMpr_LargeInteger_bitAnd (int id, volatile int numArgs) #line 1006 "prims.def" { #ifdef HAVE_GMP gst_mpz a = { 0, 0, NULL }; gst_mpz b = { 0, 0, NULL }; gst_mpz c = { 0, 0, NULL }; OOP oop1, oop2, oop3; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = POP_OOP (); if COMMON (IS_INT (oop1) || SUPERCLASS (OOP_CLASS (oop1)) == _gst_large_integer_class || OOP_CLASS (oop1) == _gst_large_zero_integer_class) _gst_mpz_from_oop (&a, oop1); else { UNPOP (2); PRIM_FAILED; } if COMMON (IS_INT (oop2) || SUPERCLASS (OOP_CLASS (oop2)) == _gst_large_integer_class || OOP_CLASS (oop2) == _gst_large_zero_integer_class) _gst_mpz_from_oop (&b, oop2); else { _gst_mpz_clear (&a); UNPOP (2); PRIM_FAILED; } _gst_mpz_and (&c, &a, &b); oop3 = _gst_oop_from_mpz (&c); _gst_mpz_clear (&a); _gst_mpz_clear (&b); _gst_mpz_clear (&c); PUSH_OOP (oop3); PRIM_SUCCEEDED; #else PRIM_FAILED; #endif } intptr_t VMpr_LargeInteger_bitOr (int id, volatile int numArgs) #line 1051 "prims.def" { #ifdef HAVE_GMP gst_mpz a = { 0, 0, NULL }; gst_mpz b = { 0, 0, NULL }; gst_mpz c = { 0, 0, NULL }; OOP oop1, oop2, oop3; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = POP_OOP (); if COMMON (IS_INT (oop1) || SUPERCLASS (OOP_CLASS (oop1)) == _gst_large_integer_class || OOP_CLASS (oop1) == _gst_large_zero_integer_class) _gst_mpz_from_oop (&a, oop1); else { UNPOP (2); PRIM_FAILED; } if COMMON (IS_INT (oop2) || SUPERCLASS (OOP_CLASS (oop2)) == _gst_large_integer_class || OOP_CLASS (oop2) == _gst_large_zero_integer_class) _gst_mpz_from_oop (&b, oop2); else { _gst_mpz_clear (&a); UNPOP (2); PRIM_FAILED; } _gst_mpz_ior (&c, &a, &b); oop3 = _gst_oop_from_mpz (&c); _gst_mpz_clear (&a); _gst_mpz_clear (&b); _gst_mpz_clear (&c); PUSH_OOP (oop3); PRIM_SUCCEEDED; #else PRIM_FAILED; #endif } intptr_t VMpr_LargeInteger_bitXor (int id, volatile int numArgs) #line 1096 "prims.def" { #ifdef HAVE_GMP gst_mpz a = { 0, 0, NULL }; gst_mpz b = { 0, 0, NULL }; gst_mpz c = { 0, 0, NULL }; OOP oop1, oop2, oop3; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = POP_OOP (); if COMMON (IS_INT (oop1) || SUPERCLASS (OOP_CLASS (oop1)) == _gst_large_integer_class || OOP_CLASS (oop1) == _gst_large_zero_integer_class) _gst_mpz_from_oop (&a, oop1); else { UNPOP (2); PRIM_FAILED; } if COMMON (IS_INT (oop2) || SUPERCLASS (OOP_CLASS (oop2)) == _gst_large_integer_class || OOP_CLASS (oop2) == _gst_large_zero_integer_class) _gst_mpz_from_oop (&b, oop2); else { _gst_mpz_clear (&a); UNPOP (2); PRIM_FAILED; } _gst_mpz_xor (&c, &a, &b); oop3 = _gst_oop_from_mpz (&c); _gst_mpz_clear (&a); _gst_mpz_clear (&b); _gst_mpz_clear (&c); PUSH_OOP (oop3); PRIM_SUCCEEDED; #else PRIM_FAILED; #endif } intptr_t VMpr_LargeInteger_bitInvert (int id, volatile int numArgs) #line 1141 "prims.def" { #ifdef HAVE_GMP gst_mpz a = { 0, 0, NULL }; gst_mpz c = { 0, 0, NULL }; OOP oop2, oop3; _gst_primitives_executed++; oop2 = POP_OOP (); if COMMON (IS_INT (oop2) || SUPERCLASS (OOP_CLASS (oop2)) == _gst_large_integer_class || OOP_CLASS (oop2) == _gst_large_zero_integer_class) _gst_mpz_from_oop (&a, oop2); else { UNPOP (2); PRIM_FAILED; } _gst_mpz_com (&c, &a); oop3 = _gst_oop_from_mpz (&c); _gst_mpz_clear (&a); _gst_mpz_clear (&c); PUSH_OOP (oop3); PRIM_SUCCEEDED; #else PRIM_FAILED; #endif } intptr_t VMpr_LargeInteger_bitShift (int id, volatile int numArgs) #line 1172 "prims.def" { #ifdef HAVE_GMP int n; gst_mpz a = { 0, 0, NULL }; gst_mpz c = { 0, 0, NULL }; OOP oop1, oop2, oop3; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = POP_OOP (); if COMMON (IS_INT (oop2)) n = TO_INT (oop2); else { UNPOP (2); PRIM_FAILED; } if COMMON (IS_INT (oop1) || SUPERCLASS (OOP_CLASS (oop1)) == _gst_large_integer_class || OOP_CLASS (oop1) == _gst_large_zero_integer_class) _gst_mpz_from_oop (&a, oop1); else { UNPOP (2); PRIM_FAILED; } if (n > 0) _gst_mpz_mul_2exp (&c, &a, n); else _gst_mpz_div_2exp (&c, &a, -n); oop3 = _gst_oop_from_mpz (&c); _gst_mpz_clear (&a); _gst_mpz_clear (&c); PUSH_OOP (oop3); PRIM_SUCCEEDED; #endif PRIM_FAILED; } intptr_t VMpr_LargeInteger_plus (int id, volatile int numArgs) #line 1216 "prims.def" { #ifdef HAVE_GMP gst_mpz a = { 0, 0, NULL }; gst_mpz b = { 0, 0, NULL }; gst_mpz c = { 0, 0, NULL }; OOP oop1, oop2, oop3; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = POP_OOP (); if COMMON (IS_INT (oop1) || SUPERCLASS (OOP_CLASS (oop1)) == _gst_large_integer_class || OOP_CLASS (oop1) == _gst_large_zero_integer_class) _gst_mpz_from_oop (&a, oop1); else { UNPOP (2); PRIM_FAILED; } if COMMON (IS_INT (oop2) || SUPERCLASS (OOP_CLASS (oop2)) == _gst_large_integer_class || OOP_CLASS (oop2) == _gst_large_zero_integer_class) _gst_mpz_from_oop (&b, oop2); else { _gst_mpz_clear (&a); UNPOP (2); PRIM_FAILED; } _gst_mpz_add (&c, &a, &b); oop3 = _gst_oop_from_mpz (&c); _gst_mpz_clear (&a); _gst_mpz_clear (&b); _gst_mpz_clear (&c); PUSH_OOP (oop3); PRIM_SUCCEEDED; #else PRIM_FAILED; #endif } intptr_t VMpr_LargeInteger_minus (int id, volatile int numArgs) #line 1261 "prims.def" { #ifdef HAVE_GMP gst_mpz a = { 0, 0, NULL }; gst_mpz b = { 0, 0, NULL }; gst_mpz c = { 0, 0, NULL }; OOP oop1, oop2, oop3; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = POP_OOP (); if COMMON (IS_INT (oop1) || SUPERCLASS (OOP_CLASS (oop1)) == _gst_large_integer_class || OOP_CLASS (oop1) == _gst_large_zero_integer_class) _gst_mpz_from_oop (&a, oop1); else { UNPOP (2); PRIM_FAILED; } if COMMON (IS_INT (oop2) || SUPERCLASS (OOP_CLASS (oop2)) == _gst_large_integer_class || OOP_CLASS (oop2) == _gst_large_zero_integer_class) _gst_mpz_from_oop (&b, oop2); else { _gst_mpz_clear (&a); UNPOP (2); PRIM_FAILED; } _gst_mpz_sub (&c, &a, &b); oop3 = _gst_oop_from_mpz (&c); _gst_mpz_clear (&a); _gst_mpz_clear (&b); _gst_mpz_clear (&c); PUSH_OOP (oop3); PRIM_SUCCEEDED; #else PRIM_FAILED; #endif } intptr_t VMpr_LargeInteger_gcd (int id, volatile int numArgs) #line 1306 "prims.def" { #ifdef HAVE_GMP gst_mpz a = { 0, 0, NULL }; gst_mpz b = { 0, 0, NULL }; gst_mpz c = { 0, 0, NULL }; OOP oop1, oop2, oop3; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = POP_OOP (); if COMMON (IS_INT (oop1) || SUPERCLASS (OOP_CLASS (oop1)) == _gst_large_integer_class || OOP_CLASS (oop1) == _gst_large_zero_integer_class) _gst_mpz_from_oop (&a, oop1); else { UNPOP (2); PRIM_FAILED; } if COMMON (IS_INT (oop2) || SUPERCLASS (OOP_CLASS (oop2)) == _gst_large_integer_class || OOP_CLASS (oop2) == _gst_large_zero_integer_class) _gst_mpz_from_oop (&b, oop2); else { _gst_mpz_clear (&a); UNPOP (2); PRIM_FAILED; } if (oop1 == FROM_INT(0) || oop2 == FROM_INT(0) || (IS_OOP(oop1) && OOP_CLASS (oop1) == _gst_large_zero_integer_class) || (IS_OOP(oop2) && OOP_CLASS (oop2) == _gst_large_zero_integer_class)) /* Return the non-zero number between a and b */ _gst_mpz_add (&c, &a, &b); else _gst_mpz_gcd (&c, &a, &b); oop3 = _gst_oop_from_mpz (&c); _gst_mpz_clear (&a); _gst_mpz_clear (&b); _gst_mpz_clear (&c); PUSH_OOP (oop3); PRIM_SUCCEEDED; #else PRIM_FAILED; #endif } intptr_t VMpr_LargeInteger_asFloatD (int id, volatile int numArgs) #line 1358 "prims.def" { #ifdef HAVE_GMP gst_mpz a = { 0, 0, NULL }; OOP oop1, oop2; double d; _gst_primitives_executed++; oop1 = POP_OOP (); if COMMON (IS_INT (oop1) || SUPERCLASS (OOP_CLASS (oop1)) == _gst_large_integer_class || OOP_CLASS (oop1) == _gst_large_zero_integer_class) _gst_mpz_from_oop (&a, oop1); else { UNPOP (1); PRIM_FAILED; } if (_gst_mpz_get_d (&a, &d)) { oop2 = floatd_new (d); _gst_mpz_clear (&a); PUSH_OOP (oop2); PRIM_SUCCEEDED; } UNPOP (1); #endif PRIM_FAILED; } intptr_t VMpr_LargeInteger_asFloatE (int id, volatile int numArgs) #line 1391 "prims.def" { #ifdef HAVE_GMP gst_mpz a = { 0, 0, NULL }; OOP oop1, oop2; double d; _gst_primitives_executed++; oop1 = POP_OOP (); if COMMON (IS_INT (oop1) || SUPERCLASS (OOP_CLASS (oop1)) == _gst_large_integer_class || OOP_CLASS (oop1) == _gst_large_zero_integer_class) _gst_mpz_from_oop (&a, oop1); else { UNPOP (1); PRIM_FAILED; } if (_gst_mpz_get_d (&a, &d) && (double) (float) d == d) { oop2 = floate_new (d); _gst_mpz_clear (&a); PUSH_OOP (oop2); PRIM_SUCCEEDED; } UNPOP (1); #endif PRIM_FAILED; } intptr_t VMpr_LargeInteger_asFloatQ (int id, volatile int numArgs) #line 1424 "prims.def" { #ifdef HAVE_GMP gst_mpz a = { 0, 0, NULL }; OOP oop1, oop2; long double d; _gst_primitives_executed++; oop1 = POP_OOP (); if COMMON (IS_INT (oop1) || SUPERCLASS (OOP_CLASS (oop1)) == _gst_large_integer_class || OOP_CLASS (oop1) == _gst_large_zero_integer_class) _gst_mpz_from_oop (&a, oop1); else { UNPOP (1); PRIM_FAILED; } if (_gst_mpz_get_ld (&a, &d) && (long double) (float) d == d) { oop2 = floatq_new (d); _gst_mpz_clear (&a); PUSH_OOP (oop2); PRIM_SUCCEEDED; } UNPOP (1); #endif PRIM_FAILED; } intptr_t VMpr_FloatD_arith (int id, volatile int numArgs) #line 1466 "prims.def" { double farg2; OOP oop1; OOP oop2; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = POP_OOP (); if (IS_CLASS (oop2, _gst_floatd_class)) farg2 = FLOATD_OOP_VALUE (oop2); else if (IS_INT (oop2)) farg2 = (double) TO_INT (oop2); else { UNPOP (2); PRIM_FAILED; } if COMMON (RECEIVER_IS_CLASS (oop1, _gst_floatd_class)) { double farg1; farg1 = FLOATD_OOP_VALUE (oop1); switch (id) { case 0: PUSH_OOP (floatd_new (farg1 + farg2)); break; case -1: PUSH_OOP (floatd_new (farg1 - farg2)); break; case -2: PUSH_BOOLEAN (farg1 < farg2); break; case -3: PUSH_BOOLEAN (farg1 > farg2); break; case -4: PUSH_BOOLEAN (farg1 <= farg2); break; case -5: PUSH_BOOLEAN (farg1 >= farg2); break; case -6: PUSH_BOOLEAN (farg1 == farg2); break; case -7: PUSH_BOOLEAN (farg1 != farg2); break; case -8: PUSH_OOP (floatd_new (farg1 * farg2)); break; case -9: PUSH_OOP (floatd_new (farg1 / farg2)); break; } PRIM_SUCCEEDED; } UNPOP (2); PRIM_FAILED; } /* FloatD truncated */ intptr_t VMpr_FloatD_truncated (int id, volatile int numArgs) #line 1530 "prims.def" { OOP oop1; _gst_primitives_executed++; oop1 = POP_OOP (); if COMMON (RECEIVER_IS_CLASS (oop1, _gst_floatd_class)) { double oopValue = FLOATD_OOP_VALUE (oop1); if COMMON (oopValue >= MIN_ST_INT && oopValue <= MAX_ST_INT) { PUSH_INT (lrint (trunc (oopValue))); PRIM_SUCCEEDED; } } UNPOP (1); PRIM_FAILED; } /* FloatD fractionPart */ intptr_t VMpr_FloatD_fractionPart (int id, volatile int numArgs) #line 1550 "prims.def" { OOP oop1; _gst_primitives_executed++; oop1 = POP_OOP (); if COMMON (RECEIVER_IS_CLASS (oop1, _gst_floatd_class)) { double farg1; farg1 = FLOATD_OOP_VALUE (oop1); farg1 -= (farg1 < 0.0) ? ceil (farg1) : floor (farg1); PUSH_OOP (floatd_new (farg1)); PRIM_SUCCEEDED; } UNPOP (1); PRIM_FAILED; } /* FloatD exponent */ intptr_t VMpr_FloatD_exponent (int id, volatile int numArgs) #line 1570 "prims.def" { OOP oop1; _gst_primitives_executed++; oop1 = POP_OOP (); if COMMON (RECEIVER_IS_CLASS (oop1, _gst_floatd_class)) { double farg1; int intArg1; farg1 = FLOATD_OOP_VALUE (oop1); if (farg1 == 0.0) intArg1 = 1; else { frexp (FLOATD_OOP_VALUE (oop1), &intArg1); intArg1--; } PUSH_INT (intArg1); PRIM_SUCCEEDED; } UNPOP (1); PRIM_FAILED; } /* FloatD timesTwoPower: */ intptr_t VMpr_FloatD_timesTwoPower (int id, volatile int numArgs) #line 1597 "prims.def" { OOP oop1; OOP oop2; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = POP_OOP (); if (RECEIVER_IS_CLASS (oop1, _gst_floatd_class) && IS_INT (oop2)) { double farg1; intptr_t iarg2; farg1 = FLOATD_OOP_VALUE (oop1); iarg2 = TO_INT (oop2); PUSH_OOP (floatd_new (ldexp (farg1, iarg2))); PRIM_SUCCEEDED; } UNPOP (2); PRIM_FAILED; } /* FloatD asFloatE */ intptr_t VMpr_FloatD_asFloatE (int id, volatile int numArgs) #line 1620 "prims.def" { OOP oop1; _gst_primitives_executed++; oop1 = POP_OOP (); if COMMON (RECEIVER_IS_CLASS (oop1, _gst_floatd_class)) { PUSH_OOP (floate_new (FLOATD_OOP_VALUE (oop1))); PRIM_SUCCEEDED; } UNPOP (1); PRIM_FAILED; } /* FloatD asFloatQ */ intptr_t VMpr_FloatD_asFloatQ (int id, volatile int numArgs) #line 1637 "prims.def" { OOP oop1; _gst_primitives_executed++; oop1 = POP_OOP (); if COMMON (RECEIVER_IS_CLASS (oop1, _gst_floatd_class)) { PUSH_OOP (floatq_new (FLOATD_OOP_VALUE (oop1))); PRIM_SUCCEEDED; } UNPOP (1); PRIM_FAILED; } intptr_t VMpr_FloatE_arith (int id, volatile int numArgs) #line 1662 "prims.def" { double farg2; OOP oop1; OOP oop2; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = POP_OOP (); if (IS_CLASS (oop2, _gst_floate_class)) farg2 = FLOATE_OOP_VALUE (oop2); else if (IS_INT (oop2)) farg2 = (double) TO_INT (oop2); else { UNPOP (2); PRIM_FAILED; } if COMMON (RECEIVER_IS_CLASS (oop1, _gst_floate_class)) { double farg1; farg1 = FLOATE_OOP_VALUE (oop1); switch (id) { case 0: PUSH_OOP (floate_new (farg1 + farg2)); break; case -1: PUSH_OOP (floate_new (farg1 - farg2)); break; case -2: PUSH_BOOLEAN (farg1 < farg2); break; case -3: PUSH_BOOLEAN (farg1 > farg2); break; case -4: PUSH_BOOLEAN (farg1 <= farg2); break; case -5: PUSH_BOOLEAN (farg1 >= farg2); break; case -6: PUSH_BOOLEAN (farg1 == farg2); break; case -7: PUSH_BOOLEAN (farg1 != farg2); break; case -8: PUSH_OOP (floate_new (farg1 * farg2)); break; case -9: PUSH_OOP (floate_new (farg1 / farg2)); break; } PRIM_SUCCEEDED; } UNPOP (2); PRIM_FAILED; } /* FloatD truncated */ intptr_t VMpr_FloatE_truncated (int id, volatile int numArgs) #line 1726 "prims.def" { OOP oop1; _gst_primitives_executed++; oop1 = POP_OOP (); if COMMON (RECEIVER_IS_CLASS (oop1, _gst_floate_class)) { double oopValue = FLOATE_OOP_VALUE (oop1); if COMMON (oopValue >= MIN_ST_INT && oopValue <= MAX_ST_INT) { PUSH_INT (lrintf (truncf (oopValue))); PRIM_SUCCEEDED; } } UNPOP (1); PRIM_FAILED; } /* FloatD fractionPart */ intptr_t VMpr_FloatE_fractionPart (int id, volatile int numArgs) #line 1746 "prims.def" { OOP oop1; _gst_primitives_executed++; oop1 = POP_OOP (); if COMMON (RECEIVER_IS_CLASS (oop1, _gst_floate_class)) { double farg1; farg1 = FLOATE_OOP_VALUE (oop1); farg1 -= (farg1 < 0.0) ? ceil (farg1) : floor (farg1); PUSH_OOP (floate_new (farg1)); PRIM_SUCCEEDED; } UNPOP (1); PRIM_FAILED; } /* FloatD exponent */ intptr_t VMpr_FloatE_exponent (int id, volatile int numArgs) #line 1766 "prims.def" { OOP oop1; _gst_primitives_executed++; oop1 = POP_OOP (); if COMMON (RECEIVER_IS_CLASS (oop1, _gst_floate_class)) { double farg1; int intArg1; farg1 = FLOATE_OOP_VALUE (oop1); if (farg1 == 0.0) intArg1 = 1; else { frexp (FLOATE_OOP_VALUE (oop1), &intArg1); intArg1--; } PUSH_INT (intArg1); PRIM_SUCCEEDED; } UNPOP (1); PRIM_FAILED; } /* FloatD timesTwoPower: */ intptr_t VMpr_FloatE_timesTwoPower (int id, volatile int numArgs) #line 1793 "prims.def" { OOP oop1; OOP oop2; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = POP_OOP (); if (RECEIVER_IS_CLASS (oop1, _gst_floate_class) && IS_INT (oop2)) { double farg1; intptr_t iarg2; farg1 = FLOATE_OOP_VALUE (oop1); iarg2 = TO_INT (oop2); PUSH_OOP (floate_new (ldexp (farg1, iarg2))); PRIM_SUCCEEDED; } UNPOP (2); PRIM_FAILED; } /* FloatE asFloatD */ intptr_t VMpr_FloatE_asFloatD (int id, volatile int numArgs) #line 1816 "prims.def" { OOP oop1; _gst_primitives_executed++; oop1 = POP_OOP (); if COMMON (RECEIVER_IS_CLASS (oop1, _gst_floate_class)) { PUSH_OOP (floatd_new (FLOATE_OOP_VALUE (oop1))); PRIM_SUCCEEDED; } UNPOP (1); PRIM_FAILED; } /* FloatD asFloatQ */ intptr_t VMpr_FloatE_asFloatQ (int id, volatile int numArgs) #line 1833 "prims.def" { OOP oop1; _gst_primitives_executed++; oop1 = POP_OOP (); if COMMON (RECEIVER_IS_CLASS (oop1, _gst_floate_class)) { PUSH_OOP (floatq_new (FLOATE_OOP_VALUE (oop1))); PRIM_SUCCEEDED; } UNPOP (1); PRIM_FAILED; } intptr_t VMpr_FloatQ_arith (int id, volatile int numArgs) #line 1858 "prims.def" { long double farg2; OOP oop1; OOP oop2; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = POP_OOP (); if (IS_CLASS (oop2, _gst_floatq_class)) farg2 = FLOATQ_OOP_VALUE (oop2); else if (IS_INT (oop2)) farg2 = (long double) TO_INT (oop2); else { UNPOP (2); PRIM_FAILED; } if COMMON (RECEIVER_IS_CLASS (oop1, _gst_floatq_class)) { long double farg1; farg1 = FLOATQ_OOP_VALUE (oop1); switch (id) { case 0: PUSH_OOP (floatq_new (farg1 + farg2)); break; case -1: PUSH_OOP (floatq_new (farg1 - farg2)); break; case -2: PUSH_BOOLEAN (farg1 < farg2); break; case -3: PUSH_BOOLEAN (farg1 > farg2); break; case -4: PUSH_BOOLEAN (farg1 <= farg2); break; case -5: PUSH_BOOLEAN (farg1 >= farg2); break; case -6: PUSH_BOOLEAN (farg1 == farg2); break; case -7: PUSH_BOOLEAN (farg1 != farg2); break; case -8: PUSH_OOP (floatq_new (farg1 * farg2)); break; case -9: PUSH_OOP (floatq_new (farg1 / farg2)); break; } PRIM_SUCCEEDED; } UNPOP (2); PRIM_FAILED; } /* FloatD truncated */ intptr_t VMpr_FloatQ_truncated (int id, volatile int numArgs) #line 1922 "prims.def" { OOP oop1; _gst_primitives_executed++; oop1 = POP_OOP (); if COMMON (RECEIVER_IS_CLASS (oop1, _gst_floatq_class)) { long double oopValue = FLOATQ_OOP_VALUE (oop1); if COMMON (oopValue >= MIN_ST_INT && oopValue <= MAX_ST_INT) { PUSH_INT (lrintl (truncl (oopValue))); PRIM_SUCCEEDED; } } UNPOP (1); PRIM_FAILED; } /* FloatD fractionPart */ intptr_t VMpr_FloatQ_fractionPart (int id, volatile int numArgs) #line 1942 "prims.def" { OOP oop1; _gst_primitives_executed++; oop1 = POP_OOP (); if COMMON (RECEIVER_IS_CLASS (oop1, _gst_floatq_class)) { long double farg1; farg1 = FLOATQ_OOP_VALUE (oop1); farg1 -= (farg1 < 0.0) ? ceill (farg1) : floorl (farg1); PUSH_OOP (floatq_new (farg1)); PRIM_SUCCEEDED; } UNPOP (1); PRIM_FAILED; } /* FloatD exponent */ intptr_t VMpr_FloatQ_exponent (int id, volatile int numArgs) #line 1962 "prims.def" { OOP oop1; _gst_primitives_executed++; oop1 = POP_OOP (); if COMMON (RECEIVER_IS_CLASS (oop1, _gst_floatq_class)) { long double farg1; int intArg1; farg1 = FLOATQ_OOP_VALUE (oop1); if (farg1 == 0.0) intArg1 = 1; else { frexpl (FLOATQ_OOP_VALUE (oop1), &intArg1); intArg1--; } PUSH_INT (intArg1); PRIM_SUCCEEDED; } UNPOP (1); PRIM_FAILED; } /* FloatD timesTwoPower: */ intptr_t VMpr_FloatQ_timesTwoPower (int id, volatile int numArgs) #line 1989 "prims.def" { OOP oop1; OOP oop2; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = POP_OOP (); if (RECEIVER_IS_CLASS (oop1, _gst_floatq_class) && IS_INT (oop2)) { long double farg1; intptr_t iarg2; farg1 = FLOATQ_OOP_VALUE (oop1); iarg2 = TO_INT (oop2); PUSH_OOP (floatq_new (ldexpl (farg1, iarg2))); PRIM_SUCCEEDED; } UNPOP (2); PRIM_FAILED; } /* FloatQ asFloatD */ intptr_t VMpr_FloatQ_asFloatD (int id, volatile int numArgs) #line 2012 "prims.def" { OOP oop1; _gst_primitives_executed++; oop1 = POP_OOP (); if COMMON (RECEIVER_IS_CLASS (oop1, _gst_floatq_class)) { PUSH_OOP (floatd_new (FLOATQ_OOP_VALUE (oop1))); PRIM_SUCCEEDED; } UNPOP (1); PRIM_FAILED; } /* FloatD asFloatQ */ intptr_t VMpr_FloatQ_asFloatE (int id, volatile int numArgs) #line 2029 "prims.def" { OOP oop1; _gst_primitives_executed++; oop1 = POP_OOP (); if COMMON (RECEIVER_IS_CLASS (oop1, _gst_floatq_class)) { PUSH_OOP (floate_new (FLOATQ_OOP_VALUE (oop1))); PRIM_SUCCEEDED; } UNPOP (1); PRIM_FAILED; } /* Object at:, Object basicAt: */ intptr_t VMpr_Object_basicAt (int id, volatile int numArgs) #line 2048 "prims.def" { OOP oop1; OOP oop2; _gst_primitives_executed++; POP_N_OOPS (numArgs - 1); oop2 = POP_OOP (); oop1 = STACKTOP (); if COMMON (IS_INT (oop2)) { intptr_t arg2; arg2 = TO_INT (oop2); oop1 = index_oop (oop1, arg2); if COMMON (oop1) { SET_STACKTOP (oop1); PRIM_SUCCEEDED; } } UNPOP (numArgs); PRIM_FAILED; } /* Object at:put:, Object basicAt:put: */ intptr_t VMpr_Object_basicAtPut (int id, volatile int numArgs) #line 2073 "prims.def" { OOP oop1; OOP oop2; OOP oop3; _gst_primitives_executed++; oop3 = POP_OOP (); oop2 = POP_OOP (); oop1 = STACKTOP (); if COMMON (IS_INT (oop2) && !IS_OOP_READONLY (oop1)) { intptr_t arg2; arg2 = TO_INT (oop2); if COMMON (index_oop_put (oop1, arg2, oop3)) { SET_STACKTOP (oop3); PRIM_SUCCEEDED; } } UNPOP (2); PRIM_FAILED; } /* Object basicSize; Object size; String size */ intptr_t VMpr_Object_basicSize (int id, volatile int numArgs) #line 2099 "prims.def" { OOP oop1; _gst_primitives_executed++; oop1 = POP_OOP (); PUSH_INT (NUM_INDEXABLE_FIELDS (oop1)); PRIM_SUCCEEDED; } /* CharacterArray valueAt: */ intptr_t VMpr_CharacterArray_valueAt (int id, volatile int numArgs) #line 2111 "prims.def" { OOP oop1; OOP oop2; intptr_t spec; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = STACKTOP (); spec = CLASS_INSTANCE_SPEC (OOP_CLASS (oop1)); switch (spec & ISP_INDEXEDVARS) { case GST_ISP_CHARACTER: spec ^= GST_ISP_CHARACTER ^ GST_ISP_UCHAR; break; case GST_ISP_UTF32: spec ^= GST_ISP_UTF32 ^ GST_ISP_UINT; break; default: UNPOP (1); PRIM_FAILED; } if COMMON (IS_INT (oop2)) { intptr_t arg2; arg2 = TO_INT (oop2); oop1 = index_oop_spec (oop1, OOP_TO_OBJ (oop1), arg2, spec); if COMMON (oop1) { SET_STACKTOP (oop1); PRIM_SUCCEEDED; } } UNPOP (1); PRIM_FAILED; } /* CharacterArray valueAt:put: */ intptr_t VMpr_CharacterArray_valueAtPut (int id, volatile int numArgs) #line 2152 "prims.def" { OOP oop1; OOP oop2; OOP oop3; intptr_t spec; _gst_primitives_executed++; oop3 = POP_OOP (); oop2 = POP_OOP (); oop1 = STACKTOP (); spec = CLASS_INSTANCE_SPEC (OOP_CLASS (oop1)); switch (spec & ISP_INDEXEDVARS) { case GST_ISP_CHARACTER: spec ^= GST_ISP_CHARACTER ^ GST_ISP_UCHAR; break; case GST_ISP_UTF32: spec ^= GST_ISP_UTF32 ^ GST_ISP_UINT; break; default: UNPOP (2); PRIM_FAILED; } if COMMON (IS_INT (oop2) && !IS_OOP_READONLY (oop1)) { intptr_t arg2; arg2 = TO_INT (oop2); if COMMON (index_oop_put_spec (oop1, OOP_TO_OBJ (oop1), arg2, oop3, spec)) { SET_STACKTOP (oop3); PRIM_SUCCEEDED; } } UNPOP (2); PRIM_FAILED; } /* CompiledCode verificationResult */ intptr_t VMpr_CompiledCode_verificationResult (int id, volatile int numArgs) #line 2196 "prims.def" { OOP oop1 = STACKTOP (); const char *result = _gst_verify_method (oop1, NULL, 0); OOP resultOOP = result ? _gst_string_new (result) : _gst_nil_oop; SET_STACKTOP (resultOOP); PRIM_SUCCEEDED; } /* CompiledBlock numArgs:numTemps:bytecodes:depth:literals: */ intptr_t VMpr_CompiledBlock_create (int id, volatile int numArgs) #line 2207 "prims.def" { OOP *_gst_literals = OOP_TO_OBJ (STACK_AT (0))->data; int depth = TO_INT (STACK_AT (1)); OOP bytecodesOOP = STACK_AT (2); int blockTemps = TO_INT (STACK_AT (3)); int blockArgs = TO_INT (STACK_AT (4)); bc_vector bytecodes = _gst_extract_bytecodes (bytecodesOOP); OOP block = _gst_block_new (blockArgs, blockTemps, bytecodes, depth, _gst_literals); POP_N_OOPS (5); OOP_CLASS(block) = STACKTOP (); _gst_primitives_executed++; SET_STACKTOP (block); PRIM_SUCCEEDED; } /* CompiledMethod literals:numArgs:numTemps:attributes:bytecodes:depth: */ intptr_t VMpr_CompiledMethod_create (int id, volatile int numArgs) #line 2228 "prims.def" { int depth = TO_INT (STACK_AT (0)); OOP bytecodesOOP = STACK_AT (1); OOP attributesOOP = STACK_AT (2); int methodTemps = TO_INT (STACK_AT (3)); int methodArgs = TO_INT (STACK_AT (4)); OOP literals = STACK_AT (5); bc_vector bytecodes = _gst_extract_bytecodes (bytecodesOOP); int primitive = _gst_process_attributes_array (attributesOOP); OOP method; if (primitive == -1) PRIM_FAILED; method = _gst_make_new_method (primitive, methodArgs, methodTemps, depth, literals, bytecodes, _gst_nil_oop, _gst_nil_oop, _gst_nil_oop, -1, -1); POP_N_OOPS(6); OOP_CLASS(method) = STACKTOP (); _gst_primitives_executed++; SET_STACKTOP (method); PRIM_SUCCEEDED; } /* Object shallowCopy */ intptr_t VMpr_Object_shallowCopy (int id, volatile int numArgs) #line 2255 "prims.def" { OOP oop1; _gst_primitives_executed++; oop1 = STACKTOP (); oop1 = _gst_object_copy (oop1); SET_STACKTOP (oop1); PRIM_SUCCEEDED; } /* Behavior basicNew; Behavior new; */ intptr_t VMpr_Behavior_basicNew (int id, volatile int numArgs) #line 2267 "prims.def" { OOP oop1; _gst_primitives_executed++; oop1 = STACKTOP (); if COMMON (RECEIVER_IS_OOP (oop1)) { if COMMON (!CLASS_IS_INDEXABLE (oop1)) { /* Note: you cannot pass &STACKTOP() because if the stack moves it ain't valid anymore by the time it is set!!! */ OOP result; instantiate (oop1, &result); SET_STACKTOP (result); PRIM_SUCCEEDED; } } PRIM_FAILED; } /* Behavior new:; Behavior basicNew: */ intptr_t VMpr_Behavior_basicNewColon (int id, volatile int numArgs) #line 2289 "prims.def" { OOP oop1; OOP oop2; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = STACKTOP (); if COMMON (RECEIVER_IS_OOP (oop1) && IS_INT (oop2)) { if COMMON (CLASS_IS_INDEXABLE (oop1)) { intptr_t arg2; arg2 = TO_INT (oop2); if (arg2 >= 0) { OOP result; instantiate_with (oop1, arg2, &result); SET_STACKTOP (result); PRIM_SUCCEEDED; } } } UNPOP (1); PRIM_FAILED; } /* Object become: */ intptr_t VMpr_Object_become (int id, volatile int numArgs) #line 2318 "prims.def" { OOP oop1; OOP oop2; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = STACKTOP (); if COMMON (!IS_OOP_READONLY (oop1) && !IS_OOP_READONLY (oop2)) { _gst_swap_objects (oop1, oop2); PRIM_SUCCEEDED; } UNPOP (1); PRIM_FAILED; } /* Object instVarAt: */ intptr_t VMpr_Object_instVarAt (int id, volatile int numArgs) #line 2338 "prims.def" { OOP oop1; OOP oop2; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = STACKTOP (); if COMMON (IS_INT (oop2)) { intptr_t arg2; arg2 = TO_INT (oop2); if COMMON (CHECK_BOUNDS_OF (oop1, arg2)) { SET_STACKTOP (inst_var_at (oop1, arg2)); PRIM_SUCCEEDED; } } UNPOP (1); PRIM_FAILED; } /* Object inst_var_at:put: */ intptr_t VMpr_Object_instVarAtPut (int id, volatile int numArgs) #line 2361 "prims.def" { OOP oop1; OOP oop2; OOP oop3; _gst_primitives_executed++; oop3 = POP_OOP (); oop2 = POP_OOP (); oop1 = STACKTOP (); if COMMON (IS_INT (oop2)) { intptr_t arg2; arg2 = TO_INT (oop2); if COMMON (CHECK_BOUNDS_OF (oop1, arg2)) { inst_var_at_put (oop1, arg2, oop3); PRIM_SUCCEEDED; } } UNPOP (2); PRIM_FAILED; } /* Object asOop; Object hash; Symbol hash */ intptr_t VMpr_Object_hash (int id, volatile int numArgs) #line 2386 "prims.def" { OOP oop1; _gst_primitives_executed++; oop1 = POP_OOP (); if COMMON (IS_OOP (oop1)) { PUSH_INT (OOP_INDEX (oop1)); PRIM_SUCCEEDED; } UNPOP (1); PRIM_FAILED; } /* SmallInteger asObject; SmallInteger asObjectNoFail */ intptr_t VMpr_SmallInteger_asObject (int id, volatile int numArgs) #line 2402 "prims.def" { OOP oop1; intptr_t arg1; _gst_primitives_executed++; oop1 = STACKTOP (); arg1 = TO_INT (oop1); if COMMON (OOP_INDEX_VALID (arg1)) { oop1 = OOP_AT (arg1); if (!IS_OOP_VALID (oop1)) oop1 = _gst_nil_oop; SET_STACKTOP (oop1); PRIM_SUCCEEDED; } PRIM_FAILED; } /* SmallInteger nextValidOop */ intptr_t VMpr_SmallInteger_nextValidOop (int id, volatile int numArgs) #line 2424 "prims.def" { OOP oop1; intptr_t arg1; _gst_primitives_executed++; oop1 = STACKTOP (); arg1 = TO_INT (oop1); while (OOP_INDEX_VALID (++arg1)) { oop1 = OOP_AT (arg1); if (IS_OOP_VALID (oop1)) { SET_STACKTOP_INT (arg1); PRIM_SUCCEEDED; } } PRIM_FAILED; } /* Behavior someInstance */ intptr_t VMpr_Behavior_someInstance (int id, volatile int numArgs) #line 2446 "prims.def" { OOP oop1; OOP oop2, lastOOP; _gst_primitives_executed++; oop1 = STACKTOP (); PREFETCH_START (_gst_mem.ot_base, PREF_READ | PREF_NTA); for (oop2 = _gst_mem.ot_base, lastOOP = &_gst_mem.ot[_gst_mem.ot_size]; oop2 < lastOOP; oop2++) { PREFETCH_LOOP (oop2, PREF_READ | PREF_NTA); if UNCOMMON (IS_OOP_VALID (oop2) && oop1 == OOP_CLASS (oop2)) { SET_STACKTOP (oop2); PRIM_SUCCEEDED; } } PRIM_FAILED; } /* Object nextInstance */ intptr_t VMpr_Object_nextInstance (int id, volatile int numArgs) #line 2468 "prims.def" { OOP oop1; _gst_primitives_executed++; oop1 = STACKTOP (); if (OOP_CLASS (oop1) == _gst_char_class) { /* Characters are one after another - at the end there is _gst_nil_oop */ oop1++; if (_gst_char_class == OOP_CLASS (oop1)) { SET_STACKTOP (oop1); PRIM_SUCCEEDED; } } else if (IS_OOP (oop1) && oop1 >= _gst_mem.ot) { /* There is just one copy of all other builtin objects, so fail for a builtin */ OOP class_oop = OOP_CLASS (oop1); for (++oop1; oop1 <= _gst_mem.last_allocated_oop; oop1++) { PREFETCH_LOOP (oop1, PREF_READ | PREF_NTA); if (IS_OOP_VALID (oop1) && class_oop == OOP_CLASS (oop1)) { SET_STACKTOP (oop1); PRIM_SUCCEEDED; } } } PRIM_FAILED; } /* Object becomeForward: */ intptr_t VMpr_Object_becomeForward (int id, volatile int numArgs) #line 2504 "prims.def" { OOP oop1, ownerOOP; OOP oop2, lastOOP; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = STACKTOP (); if COMMON (IS_INT (oop1) || IS_OOP_READONLY (oop1)) { UNPOP (1); PRIM_FAILED; } /* Search also on LIFO contexts. */ empty_context_stack (); PREFETCH_START (_gst_mem.ot_base, PREF_READ | PREF_NTA); for (ownerOOP = _gst_mem.ot_base, lastOOP = &_gst_mem.ot[_gst_mem.ot_size]; ownerOOP < lastOOP; ownerOOP++) { gst_object object; OOP *scanPtr; int n; PREFETCH_LOOP (ownerOOP, PREF_READ | PREF_NTA); if COMMON (!IS_OOP_VALID (ownerOOP)) continue; object = OOP_TO_OBJ (ownerOOP); n = num_valid_oops (ownerOOP); if UNCOMMON (object->objClass == oop1) object->objClass = oop2; for (scanPtr = object->data; n--; scanPtr++) if UNCOMMON (*scanPtr == oop1) *scanPtr = oop2; } /* The above loop changed the reference to oop1 in the stacktop, so we have to set it back manually! */ SET_STACKTOP (oop1); PRIM_SUCCEEDED; } /* Object allOwners */ intptr_t VMpr_Object_allOwners (int id, volatile int numArgs) #line 2549 "prims.def" { OOP oop1; OOP oop2, lastOOP; OOP result; gst_object object; _gst_primitives_executed++; oop1 = STACKTOP (); _gst_reset_buffer (); PREFETCH_START (_gst_mem.ot_base, PREF_READ | PREF_NTA); for (oop2 = _gst_mem.ot_base, lastOOP = &_gst_mem.ot[_gst_mem.ot_size]; oop2 < lastOOP; oop2++) { PREFETCH_LOOP (oop2, PREF_READ | PREF_NTA); if UNCOMMON (IS_OOP_VALID (oop2) && is_owner(oop2, oop1)) _gst_add_buf_pointer (oop2); } object = new_instance_with (_gst_array_class, _gst_buffer_size() / sizeof (PTR), &result); _gst_copy_buffer (object->data); SET_STACKTOP (result); PRIM_SUCCEEDED; } intptr_t VMpr_ContextPart_thisContext (int id, volatile int numArgs) #line 2579 "prims.def" { _gst_primitives_executed++; empty_context_stack (); SET_STACKTOP (_gst_this_context_oop); PRIM_SUCCEEDED; } intptr_t VMpr_ContextPart_continue (int id, volatile int numArgs) #line 2587 "prims.def" { OOP oop2; OOP oop1; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = STACKTOP (); if COMMON (RECEIVER_IS_A_KIND_OF (OOP_CLASS (oop1), _gst_context_part_class)) { unwind_to (oop1); SET_STACKTOP (oop2); PRIM_SUCCEEDED_RELOAD_IP; } else { UNPOP (1); PRIM_FAILED; } } /* Continuation resume:nextContinuation: */ intptr_t VMpr_Continuation_resume (int id, volatile int numArgs) #line 2610 "prims.def" { OOP oop1, oop2, oop3; _gst_primitives_executed++; oop3 = POP_OOP (); oop2 = POP_OOP (); oop1 = STACKTOP (); if COMMON (RECEIVER_IS_A_KIND_OF (OOP_CLASS (oop1), _gst_continuation_class)) { gst_continuation cc = (gst_continuation) OOP_TO_OBJ (oop1); if (COMMON (!IS_NIL (cc->stack))) { resume_suspended_context (cc->stack); cc->stack = oop3; SET_STACKTOP (oop2); PRIM_SUCCEEDED_RELOAD_IP; } } UNPOP (2); PRIM_FAILED; } /* BlockClosure value BlockClosure value: BlockClosure value:value: BlockClosure value:value:value: */ intptr_t VMpr_BlockClosure_value (int id, volatile int numArgs) #line 2638 "prims.def" { _gst_primitives_executed++; if UNCOMMON (send_block_value (numArgs, 0)) PRIM_FAILED; else PRIM_SUCCEEDED_RELOAD_IP; } /* BlockClosure cull: BlockClosure cull:cull: BlockClosure cull:cull:cull: */ intptr_t VMpr_BlockClosure_cull (int id, volatile int numArgs) #line 2650 "prims.def" { _gst_primitives_executed++; if UNCOMMON (send_block_value (numArgs, numArgs)) PRIM_FAILED; else PRIM_SUCCEEDED_RELOAD_IP; } /* We cannot cache the IP here, otherwise calls to #valueAndResumeOnUnwind don't actually make the context an unwind context. If we make a provision for that in xlat.c, we can set the cache_new_ip attribute. */ intptr_t VMpr_BlockClosure_valueAndResumeOnUnwind (int id, volatile int numArgs) #line 2662 "prims.def" { gst_method_context context; _gst_primitives_executed++; context = (gst_method_context) OOP_TO_OBJ (_gst_this_context_oop); context->flags |= MCF_IS_UNWIND_CONTEXT; if UNCOMMON (send_block_value (numArgs, 0)) PRIM_FAILED; else PRIM_SUCCEEDED_RELOAD_IP; } /* BlockClosure valueWithArguments: */ intptr_t VMpr_BlockClosure_valueWithArguments (int id, volatile int numArgs) #line 2678 "prims.def" { OOP oop1; OOP oop2; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = STACKTOP (); if (IS_CLASS (oop2, _gst_array_class)) { int i; numArgs = NUM_INDEXABLE_FIELDS (oop2); for (i = 1; i <= numArgs; i++) PUSH_OOP (ARRAY_AT (oop2, i)); if UNCOMMON (send_block_value (numArgs, 0)) { POP_N_OOPS (numArgs); PUSH_OOP (oop2); PRIM_FAILED; } else PRIM_SUCCEEDED_RELOAD_IP; } UNPOP (1); PRIM_FAILED; } /* Object perform: Object perform:with: Object perform:with:with: Object perform:with:with:with: */ intptr_t VMpr_Object_perform (int id, volatile int numArgs) #line 2710 "prims.def" { OOP oop1; OOP *oopVec = alloca (numArgs * sizeof (OOP)); int i; _gst_primitives_executed++; /* pop off the arguments (if any) */ numArgs--; for (i = 0; i < numArgs; i++) oopVec[i] = POP_OOP (); oop1 = POP_OOP (); /* the selector */ if COMMON (IS_CLASS (oop1, _gst_symbol_class) && check_send_correctness (STACKTOP (), oop1, numArgs)) { /* push the args back onto the stack */ while (--i >= 0) PUSH_OOP (oopVec[i]); SEND_MESSAGE (oop1, numArgs); PRIM_SUCCEEDED_RELOAD_IP; } if COMMON (is_a_kind_of (OOP_CLASS (oop1), _gst_compiled_method_class)) { gst_compiled_method method; method_header header; method = (gst_compiled_method) OOP_TO_OBJ (oop1); header = method->header; if (header.numArgs == numArgs) { /* push the args back onto the stack */ while (--i >= 0) PUSH_OOP (oopVec[i]); _gst_send_method (oop1); PRIM_SUCCEEDED_RELOAD_IP; } } UNPOP (numArgs + 1); PRIM_FAILED; } /* Object perform:withArguments: */ intptr_t VMpr_Object_performWithArguments (int id, volatile int numArgs) #line 2758 "prims.def" { OOP oop1; OOP oop2; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = POP_OOP (); numArgs = NUM_INDEXABLE_FIELDS (oop2); if UNCOMMON (!IS_CLASS (oop2, _gst_array_class)) /* fall through to UNPOP and PRIM_FAILED */ ; else if COMMON (IS_CLASS (oop1, _gst_symbol_class) && check_send_correctness (STACKTOP (), oop1, numArgs)) { int i; for (i = 1; i <= numArgs; i++) PUSH_OOP (ARRAY_AT (oop2, i)); SEND_MESSAGE (oop1, numArgs); PRIM_SUCCEEDED_RELOAD_IP; } else if COMMON (is_a_kind_of (OOP_CLASS (oop1), _gst_compiled_method_class)) { gst_compiled_method method; method_header header; method = (gst_compiled_method) OOP_TO_OBJ (oop1); header = method->header; if COMMON (header.numArgs == numArgs) { int i; for (i = 1; i <= numArgs; i++) PUSH_OOP (ARRAY_AT (oop2, i)); _gst_send_method (oop1); PRIM_SUCCEEDED_RELOAD_IP; } } UNPOP (2); PRIM_FAILED; } /* Semaphore notifyAll */ intptr_t VMpr_Semaphore_notifyAll (int id, volatile int numArgs) #line 2807 "prims.def" { OOP oop1; _gst_primitives_executed++; oop1 = STACKTOP (); while (_gst_sync_signal (oop1, false)) ; PRIM_SUCCEEDED; } /* Semaphore signal (id = 0) or Semaphore notify (id = 1) */ intptr_t VMpr_Semaphore_signalNotify (int id, volatile int numArgs) #line 2822 "prims.def" { OOP oop1; _gst_primitives_executed++; oop1 = STACKTOP (); _gst_sync_signal (oop1, id == 0); PRIM_SUCCEEDED; } /* Semaphore wait lock */ intptr_t VMpr_Semaphore_lock (int id, volatile int numArgs) #line 2833 "prims.def" { OOP oop1; gst_semaphore sem; _gst_primitives_executed++; oop1 = STACKTOP (); sem = (gst_semaphore) OOP_TO_OBJ (oop1); SET_STACKTOP_BOOLEAN (TO_INT (sem->signals) > 0); sem->signals = FROM_INT (0); PRIM_SUCCEEDED; } /* Semaphore wait */ intptr_t VMpr_Semaphore_wait (int id, volatile int numArgs) #line 2847 "prims.def" { OOP oop1; _gst_primitives_executed++; oop1 = STACKTOP (); _gst_sync_wait (oop1); PRIM_SUCCEEDED; } /* Semaphore waitAfterSignalling: aSemaphore */ intptr_t VMpr_Semaphore_waitAfterSignalling (int id, volatile int numArgs) #line 2858 "prims.def" { OOP oop1, oop2; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = STACKTOP (); _gst_sync_signal (oop2, true); _gst_sync_wait (oop1); PRIM_SUCCEEDED; } /* Process suspend */ intptr_t VMpr_Process_suspend (int id, volatile int numArgs) #line 2871 "prims.def" { OOP oop1; _gst_primitives_executed++; oop1 = STACKTOP (); suspend_process (oop1); PRIM_SUCCEEDED; } /* Process resume */ intptr_t VMpr_Process_resume (int id, volatile int numArgs) #line 2882 "prims.def" { OOP oop1; _gst_primitives_executed++; oop1 = STACKTOP (); if (resume_process (oop1, false)) PRIM_SUCCEEDED; else PRIM_FAILED; } /* Process singleStepWaitingOn: */ intptr_t VMpr_Process_singleStepWaitingOn (int id, volatile int numArgs) #line 2895 "prims.def" { OOP oop1; OOP oop2; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = POP_OOP (); if (is_process_ready (oop1) || is_process_terminating (oop1)) { UNPOP (2); PRIM_FAILED; } /* Put the current process to sleep, switch execution to the new one, and set up the VM to signal the semaphore as soon as possible. */ _gst_sync_wait (oop2); resume_process (oop1, true); single_step_semaphore = oop2; PRIM_SUCCEEDED; } /* Process yield */ intptr_t VMpr_Process_yield (int id, volatile int numArgs) #line 2921 "prims.def" { OOP oop1; _gst_primitives_executed++; oop1 = STACKTOP (); if (oop1 == get_active_process ()) { SET_STACKTOP (_gst_nil_oop); /* this is our return value */ active_process_yield (); } PRIM_SUCCEEDED; } /* Processor pause: waitForSignal */ intptr_t VMpr_Processor_pause (int id, volatile int numArgs) #line 2936 "prims.def" { OOP oop1; _gst_primitives_executed++; oop1 = POP_OOP (); if (would_reschedule_process ()) { if (oop1 == _gst_true_oop) _gst_pause (); else _gst_usleep (20000); } active_process_yield (); PRIM_SUCCEEDED; } /* Behavior flushCache */ intptr_t VMpr_Behavior_flushCache (int id, volatile int numArgs) #line 2957 "prims.def" { _gst_primitives_executed++; _gst_invalidate_method_cache (); PRIM_SUCCEEDED; } /* CompiledCode discardTranslation */ intptr_t VMpr_CompiledCode_discardTranslation (int id, volatile int numArgs) #line 2965 "prims.def" { _gst_primitives_executed++; #ifdef ENABLE_JIT_TRANSLATION _gst_discard_native_code (STACKTOP ()); #endif PRIM_SUCCEEDED; } /* Object changeClassTo: */ intptr_t VMpr_Object_changeClassTo (int id, volatile int numArgs) #line 2975 "prims.def" { OOP oop1, oop2; gst_object obj1, obj2; _gst_primitives_executed++; oop1 = POP_OOP (); oop2 = STACKTOP (); obj1 = OOP_TO_OBJ (oop1); obj2 = OOP_TO_OBJ (oop2); if (NUM_WORDS (obj1) > 0 && !IS_INT (obj1->data[0]) && (IS_NIL (obj1->data[0]) || is_a_kind_of (OOP_CLASS (obj1->data[0]), _gst_behavior_class))) { obj2->objClass = oop1; PRIM_SUCCEEDED; } UNPOP (1); /* trying to do Bad Things */ PRIM_FAILED; } /* Time class timezoneBias */ intptr_t VMpr_Time_timezoneBias (int id, volatile int numArgs) #line 2998 "prims.def" { OOP oop1; uint64_t t; _gst_primitives_executed++; if (numArgs == 1) { if (!is_c_int_64 (STACKTOP ())) PRIM_FAILED; oop1 = POP_OOP (); /* 25202 = days between 1901 and 1970 */ t = to_c_int_64 (oop1) - (int64_t)86400 * 25202; t = _gst_adjust_time_zone (t) - t; SET_STACKTOP_INT (t); } else SET_STACKTOP_INT (_gst_current_time_zone_bias ()); PRIM_SUCCEEDED; } /* Time class timezone */ intptr_t VMpr_Time_timezone (int id, volatile int numArgs) #line 3022 "prims.def" { OOP oop1; char *result; _gst_primitives_executed++; result = _gst_current_time_zone_name (); oop1 = _gst_string_new (result); SET_STACKTOP (oop1); xfree (result); PRIM_SUCCEEDED; } /* Time class secondClock -- note: this primitive has different semantics from those defined in the book. This primitive returns the seconds since/to Jan 1, 2000 00:00:00 instead of Jan 1,1901. */ intptr_t VMpr_Time_secondClock (int id, volatile int numArgs) #line 3041 "prims.def" { _gst_primitives_executed++; /* 10957 = days between 1970 and 2000 */ SET_STACKTOP_INT (_gst_get_time () - 86400 * 10957); PRIM_SUCCEEDED; } /* Time class nanosecondClock. */ intptr_t VMpr_Time_nanosecondClock (int id, volatile int numArgs) #line 3050 "prims.def" { OOP nsOOP; uint64_t ns; _gst_primitives_executed++; ns = _gst_get_ns_time (); nsOOP = from_c_int_64 (ns); SET_STACKTOP (nsOOP); PRIM_SUCCEEDED; } /* Time class millisecondClock. */ intptr_t VMpr_Time_millisecondClock (int id, volatile int numArgs) #line 3062 "prims.def" { OOP milliOOP; uint64_t milli; _gst_primitives_executed++; milli = _gst_get_milli_time (); milliOOP = from_c_int_64 (milli); SET_STACKTOP (milliOOP); PRIM_SUCCEEDED; } /* Processor signal: semaphore atMilliseconds: deltaMilliseconds Processor signal: semaphore atNanosecondClockValue: absNanoseconds */ intptr_t VMpr_Processor_signalAt (int id, volatile int numArgs) #line 3078 "prims.def" { OOP oop1; OOP oop2; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = POP_OOP (); if (is_c_int_64 (oop2)) { int64_t arg2 = to_c_int_64 (oop2); uint64_t ns = _gst_get_ns_time (); if (id == 0) arg2 = (arg2 * 1000000) + ns; if (arg2 <= ns) _gst_sync_signal (oop1, true); else _gst_async_timed_wait (oop1, arg2); PRIM_SUCCEEDED; } UNPOP (2); PRIM_FAILED; } /* Processor isTimeoutProgrammed */ intptr_t VMpr_Processor_isTimeoutProgrammed (int id, volatile int numArgs) #line 3104 "prims.def" { _gst_primitives_executed++; SET_STACKTOP_BOOLEAN (_gst_is_timeout_programmed ()); PRIM_SUCCEEDED; } /* String similarityTo: */ intptr_t VMpr_String_similarityTo (int id, volatile int numArgs) #line 3113 "prims.def" { int result, l1, l2; gst_uchar *s1, *s2; OOP oop1, oop2; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = STACKTOP (); if (IS_INT(oop2) || OOP_FIXED_FIELDS (oop2) || (OOP_INSTANCE_SPEC (oop2) & ISP_INDEXEDVARS) != GST_ISP_CHARACTER) PRIM_FAILED; #ifndef OPTIMIZE if (IS_INT(oop1) || OOP_FIXED_FIELDS (oop1) || (OOP_INSTANCE_SPEC (oop1) & ISP_INDEXEDVARS) != GST_ISP_CHARACTER) PRIM_FAILED; #endif s1 = STRING_OOP_CHARS (oop1); s2 = STRING_OOP_CHARS (oop2); l1 = NUM_INDEXABLE_FIELDS (oop1); l2 = NUM_INDEXABLE_FIELDS (oop2); /* Weights are: substitution, case change, insert, delete. Invert the sign so that differences are reported as negative numbers. */ result = -strnspell (s1, s2, l1, l2, 7, 3, 4, 4); SET_STACKTOP_INT (result); PRIM_SUCCEEDED; } /* String hash */ intptr_t VMpr_String_hash (int id, volatile int numArgs) #line 3149 "prims.def" { uintptr_t hash; gst_uchar *base; OOP oop1; _gst_primitives_executed++; oop1 = STACKTOP (); #ifndef OPTIMIZE if (!CLASS_IS_SCALAR (OOP_CLASS (oop1))) PRIM_FAILED; #endif base = STRING_OOP_CHARS (oop1); hash = _gst_hash_string (base, NUM_INDEXABLE_FIELDS (oop1)); SET_STACKTOP_INT (hash); PRIM_SUCCEEDED; } /* LargeInteger = ByteArray = String = Array = */ intptr_t VMpr_ArrayedCollection_equal (int id, volatile int numArgs) #line 3172 "prims.def" { OOP srcOOP, dstOOP; int dstLen, srcLen; gst_uchar *dstBase, *srcBase; _gst_primitives_executed++; srcOOP = POP_OOP (); dstOOP = STACKTOP (); if COMMON (OOP_INT_CLASS (srcOOP) == OOP_INT_CLASS (dstOOP)) { intptr_t spec = OOP_INSTANCE_SPEC (srcOOP); if (spec & (~0 << ISP_NUMFIXEDFIELDS)) goto bad; /* dstEnd is inclusive: (1 to: 1) has length 1 */ dstLen = NUM_INDEXABLE_FIELDS (dstOOP); srcLen = NUM_INDEXABLE_FIELDS (srcOOP); if (dstLen != srcLen) SET_STACKTOP_BOOLEAN (false); else if UNCOMMON (dstLen == 0) SET_STACKTOP_BOOLEAN (true); else { /* do the comparison */ dstBase = (gst_uchar *) OOP_TO_OBJ (dstOOP)->data; srcBase = (gst_uchar *) OOP_TO_OBJ (srcOOP)->data; dstLen <<= _gst_log2_sizes[spec & ISP_SHAPE]; SET_STACKTOP_BOOLEAN (!memcmp (dstBase, srcBase, dstLen)); } PRIM_SUCCEEDED; } bad: UNPOP (1); PRIM_FAILED; } /* ByteArray indexOf:startingAt: ByteArray indexOf:startingAt:ifAbsent: String indexOf:startingAt: String indexOf:startingAt:ifAbsent: */ intptr_t VMpr_ArrayedCollection_indexOfStartingAt (int id, volatile int numArgs) #line 3215 "prims.def" { OOP srcIndexOOP, srcOOP, targetOOP; int srcIndex, srcLen, target; gst_uchar *srcBase, *srcTarget; _gst_primitives_executed++; POP_N_OOPS (numArgs - 2); srcIndexOOP = POP_OOP (); targetOOP = POP_OOP (); srcOOP = STACKTOP (); if COMMON ((IS_INT (targetOOP) || OOP_CLASS (targetOOP) == _gst_char_class) && IS_INT (srcIndexOOP) && !IS_INT (srcOOP)) { intptr_t srcSpec = OOP_INSTANCE_SPEC (srcOOP); if (srcSpec & (~0 << ISP_NUMFIXEDFIELDS)) goto bad; /* Check compatibility. */ if (_gst_log2_sizes[srcSpec & ISP_SHAPE] != 0) goto bad; target = IS_INT (targetOOP) ? TO_INT (targetOOP) : CHAR_OOP_VALUE (targetOOP); srcIndex = TO_INT (srcIndexOOP); srcLen = NUM_INDEXABLE_FIELDS (srcOOP) - srcIndex + 1; if UNCOMMON (srcLen < 0) goto bad; srcBase = (gst_uchar *) OOP_TO_OBJ (srcOOP)->data; srcTarget = memchr (&srcBase[srcIndex - 1], target, srcLen); if (!srcTarget) goto bad; SET_STACKTOP_INT (srcTarget - srcBase + 1); PRIM_SUCCEEDED; } bad: UNPOP (numArgs); PRIM_FAILED; } /* LargeInteger primReplaceFrom:to:with:startingAt ByteArray replaceFrom:to:withString:startingAt: String replaceFrom:to:withByteArray:startingAt: Array replaceFrom:to:with:startingAt:*/ intptr_t VMpr_ArrayedCollection_replaceFromToWithStartingAt (int id, volatile int numArgs) #line 3262 "prims.def" { OOP srcIndexOOP, srcOOP, dstEndIndexOOP, dstStartIndexOOP, dstOOP; int dstEndIndex, dstStartIndex, srcIndex, dstLen, srcLen, dstRangeLen; gst_uchar *dstBase, *srcBase; _gst_primitives_executed++; srcIndexOOP = POP_OOP (); srcOOP = POP_OOP (); dstEndIndexOOP = POP_OOP (); dstStartIndexOOP = POP_OOP (); dstOOP = STACKTOP (); if COMMON (IS_INT (srcIndexOOP) && IS_INT (dstStartIndexOOP) && IS_INT (dstEndIndexOOP) && !IS_INT (srcOOP)) { uintptr_t srcSpec = OOP_INSTANCE_SPEC (srcOOP); uintptr_t dstSpec = OOP_INSTANCE_SPEC (dstOOP); int srcOffset = srcSpec >> ISP_NUMFIXEDFIELDS; int dstOffset = dstSpec >> ISP_NUMFIXEDFIELDS; int size; /* Assume the receiver knows what it is doing for collections that are not simple arrays. Typically the primitive will not be exposed to the user in that case. Instead, be strict when dstOffset == 0. */ if (srcOffset && !dstOffset) goto bad; /* Check compatibility. */ size = _gst_log2_sizes[srcSpec & ISP_SHAPE]; if (size != _gst_log2_sizes[dstSpec & ISP_SHAPE]) goto bad; if (((srcSpec & ISP_INDEXEDVARS) == GST_ISP_POINTER) != ((dstSpec & ISP_INDEXEDVARS) == GST_ISP_POINTER)) goto bad; /* dstEnd is inclusive: (1 to: 1) has length 1 */ dstEndIndex = TO_INT (dstEndIndexOOP); dstStartIndex = TO_INT (dstStartIndexOOP); srcIndex = TO_INT (srcIndexOOP); dstOOP = STACKTOP (); dstLen = NUM_INDEXABLE_FIELDS (dstOOP); srcLen = NUM_INDEXABLE_FIELDS (srcOOP); dstRangeLen = dstEndIndex - dstStartIndex + 1; if UNCOMMON (dstRangeLen < 0 || dstEndIndex > dstLen || dstStartIndex <= 0 || srcIndex + dstRangeLen - 1 > srcLen || (srcIndex <= 0 && dstRangeLen > 0)) goto bad; /* don't do it unless there's something to copy */ if COMMON (dstRangeLen > 0) { /* do the copy */ dstBase = (gst_uchar *) &(OOP_TO_OBJ (dstOOP)->data[dstOffset]); srcBase = (gst_uchar *) &(OOP_TO_OBJ (srcOOP)->data[srcOffset]); dstStartIndex = (dstStartIndex - 1) << size; srcIndex = (srcIndex - 1) << size; dstRangeLen <<= size; memmove (&dstBase[dstStartIndex], &srcBase[srcIndex], dstRangeLen); } PRIM_SUCCEEDED; } bad: UNPOP (4); PRIM_FAILED; } /* Object == */ intptr_t VMpr_Object_identity (int id, volatile int numArgs) #line 3334 "prims.def" { OOP oop1; OOP oop2; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = POP_OOP (); PUSH_BOOLEAN (oop1 == oop2); PRIM_SUCCEEDED; } /* Object class */ intptr_t VMpr_Object_class (int id, volatile int numArgs) #line 3347 "prims.def" { OOP oop1; _gst_primitives_executed++; oop1 = POP_OOP (); if (IS_INT (oop1)) PUSH_OOP (_gst_small_integer_class); else PUSH_OOP (OOP_CLASS (oop1)); PRIM_SUCCEEDED; } /* ------- GNU Smalltalk specific primitives begin here -------------------- */ /* quit: status Always fail because if it succeeds we don't return */ intptr_t VMpr_ObjectMemory_quit (int id, volatile int numArgs) #line 3365 "prims.def" { OOP oop1; intptr_t arg1; _gst_primitives_executed++; oop1 = STACKTOP (); if (IS_INT (oop1)) { suspend_process (get_scheduled_process ()); fflush (stdout); fflush (stderr); _gst_invoke_hook (GST_ABOUT_TO_QUIT); arg1 = TO_INT (oop1); exit (arg1); } PRIM_FAILED; } /* abort */ intptr_t VMpr_ObjectMemory_abort (int id, volatile int numArgs) #line 3385 "prims.def" { _gst_primitives_executed++; abort (); } /* Dictionary at: */ intptr_t VMpr_Dictionary_at (int id, volatile int numArgs) #line 3393 "prims.def" { OOP oop1; OOP oop2; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = STACKTOP (); SET_STACKTOP (dictionary_at (oop1, oop2)); PRIM_SUCCEEDED; } /* This is not defined in terms of #error: in a .st file because some of the required functionality may not be present when it gets first invoked, say during the loading of the first kernel files. We'll redefine it later. */ /* Object doesNotUnderstand: * Object error: */ intptr_t VMpr_Object_bootstrapException (int id, volatile int numArgs) #line 3415 "prims.def" { OOP oop1; OOP oop2; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = STACKTOP (); if (id == -1) printf ("%O did not understand selector %O\n\n", oop1, MESSAGE_SELECTOR (oop2)); else printf ("%O error: %#O\n\n", oop1, oop2); _gst_show_backtrace (stdout); _gst_show_stack_contents (); abort (); } /* Character class value: */ intptr_t VMpr_Character_create (int id, volatile int numArgs) #line 3437 "prims.def" { OOP oop1; OOP oop2; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = STACKTOP (); if (IS_INT (oop2)) { intptr_t arg2; arg2 = TO_INT (oop2); if (arg2 >= 0 && arg2 <= 255) { SET_STACKTOP (CHAR_OOP_AT (arg2)); PRIM_SUCCEEDED; } } UNPOP (1); PRIM_FAILED; } /* UnicodeCharacter class value: */ intptr_t VMpr_UnicodeCharacter_create (int id, volatile int numArgs) #line 3461 "prims.def" { OOP oop1; OOP oop2; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = STACKTOP (); if (IS_INT (oop2)) { intptr_t arg2; arg2 = TO_INT (oop2); if (arg2 >= 0 && arg2 <= 0x10FFFF) { SET_STACKTOP (char_new (arg2)); PRIM_SUCCEEDED; } } UNPOP (1); PRIM_FAILED; } /* Character = */ intptr_t VMpr_Character_equal (int id, volatile int numArgs) #line 3484 "prims.def" { OOP oop1; OOP oop2; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = POP_OOP (); PUSH_BOOLEAN (IS_OOP (oop2) && is_a_kind_of (OOP_CLASS (oop2), _gst_char_class) && CHAR_OOP_VALUE (oop2) == CHAR_OOP_VALUE (oop1) && (CHAR_OOP_VALUE (oop1) <= 127 || OOP_CLASS (oop2) == OOP_CLASS (oop1))); PRIM_SUCCEEDED; } /* Symbol class intern: aString */ intptr_t VMpr_Symbol_intern (int id, volatile int numArgs) #line 3500 "prims.def" { OOP oop2; _gst_primitives_executed++; oop2 = STACKTOP (); /* keeps this guy referenced while being interned */ if (IS_CLASS (oop2, _gst_string_class)) { OOP internedString; internedString = _gst_intern_string_oop (oop2); POP_N_OOPS (1); SET_STACKTOP (internedString); PRIM_SUCCEEDED; } UNPOP (1); PRIM_FAILED; } /* Dictionary new */ intptr_t VMpr_Dictionary_new (int id, volatile int numArgs) #line 3521 "prims.def" { OOP oop1, dictionaryOOP; _gst_primitives_executed++; oop1 = STACKTOP(); dictionaryOOP = _gst_dictionary_new (32); dictionaryOOP->object->objClass = oop1; SET_STACKTOP (dictionaryOOP); PRIM_SUCCEEDED; } /* Memory addressOfOOP: oop */ intptr_t VMpr_Memory_addressOfOOP (int id, volatile int numArgs) #line 3534 "prims.def" { OOP oop1; OOP oop2; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = POP_OOP (); if (IS_OOP (oop2)) { PUSH_OOP (FROM_C_ULONG ((uintptr_t) oop2)); PRIM_SUCCEEDED; } UNPOP (2); PRIM_FAILED; } /* Memory addressOf: oop */ intptr_t VMpr_Memory_addressOf (int id, volatile int numArgs) #line 3552 "prims.def" { OOP oop1; OOP oop2; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = POP_OOP (); if (IS_OOP (oop2)) { PUSH_OOP (FROM_C_ULONG ((uintptr_t) OOP_TO_OBJ (oop2))); PRIM_SUCCEEDED; } UNPOP (2); PRIM_FAILED; } /* SystemDictionary backtrace */ intptr_t VMpr_SystemDictionary_backtrace (int id, volatile int numArgs) #line 3572 "prims.def" { _gst_primitives_executed++; _gst_show_backtrace (stdout); PRIM_SUCCEEDED; } /* SystemDictionary getTraceFlag: anIndex */ intptr_t VMpr_SystemDictionary_getTraceFlag (int id, volatile int numArgs) #line 3580 "prims.def" { OOP oop1; OOP oop2; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = POP_OOP (); if (IS_INT (oop2)) { intptr_t arg2; int value; arg2 = TO_INT (oop2); value = _gst_get_var (arg2); if (value != -1) { oop1 = (value > 1 ? FROM_INT (oop2 ) : (value ? _gst_true_oop : _gst_false_oop)); PUSH_OOP (oop1); PRIM_SUCCEEDED; } } UNPOP (2); PRIM_FAILED; } /* SystemDictionary setTraceFlag: anIndex to: aBoolean */ intptr_t VMpr_SystemDictionary_setTraceFlag (int id, volatile int numArgs) #line 3608 "prims.def" { OOP oop1; OOP oop2; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = POP_OOP (); if (IS_INT (oop1)) { intptr_t arg1 = TO_INT (oop1); intptr_t old_value = _gst_set_var (arg1, IS_INT (oop2) ? TO_INT (oop2) : oop2 == _gst_true_oop); if (old_value != -1) { SET_EXCEPT_FLAG (true); PRIM_SUCCEEDED; } } UNPOP (2); PRIM_FAILED; } /* Memory type: aType at: anAddress */ intptr_t VMpr_Memory_at (int id, volatile int numArgs) #line 3636 "prims.def" { OOP oop1; OOP oop2; OOP oop3; _gst_primitives_executed++; oop3 = POP_OOP (); oop2 = POP_OOP (); oop1 = POP_OOP (); if (IS_C_LONG (oop3) && IS_INT (oop2)) { intptr_t arg1, arg2; arg1 = TO_INT (oop2); arg2 = TO_C_LONG (oop3); switch (arg1) { case CDATA_CHAR: /* char */ case CDATA_UCHAR: /* unsigned char */ PUSH_OOP (CHAR_OOP_AT (*(unsigned char *) arg2)); PRIM_SUCCEEDED; case CDATA_SHORT: /* short */ PUSH_INT (*(short *) arg2); PRIM_SUCCEEDED; case CDATA_USHORT: /* unsigned short */ PUSH_INT (*(unsigned short *) arg2); PRIM_SUCCEEDED; case CDATA_LONG: /* long */ PUSH_OOP (FROM_C_LONG (*(long *) arg2)); PRIM_SUCCEEDED; case CDATA_ULONG: /* unsigned long */ PUSH_OOP (FROM_C_ULONG (*(unsigned long *) arg2)); PRIM_SUCCEEDED; case CDATA_LONGLONG: /* long long */ PUSH_OOP (from_c_int_64 (*(long long *) arg2)); PRIM_SUCCEEDED; case CDATA_ULONGLONG: /* unsigned long long */ PUSH_OOP (from_c_uint_64 (*(unsigned long long *) arg2)); PRIM_SUCCEEDED; case CDATA_FLOAT: /* float */ PUSH_OOP (floate_new (*(float *) arg2)); PRIM_SUCCEEDED; case CDATA_DOUBLE: /* double */ PUSH_OOP (floatd_new (*(double *) arg2)); PRIM_SUCCEEDED; case CDATA_STRING: /* string */ if (*(char **) arg2) PUSH_OOP (_gst_string_new (*(char **) arg2)); else PUSH_OOP (_gst_nil_oop); PRIM_SUCCEEDED; case CDATA_OOP: /* OOP */ PUSH_OOP (*(OOP *) arg2); PRIM_SUCCEEDED; case CDATA_INT: /* int */ PUSH_OOP (FROM_C_INT (*(int *) arg2)); PRIM_SUCCEEDED; case CDATA_UINT: /* unsigned int */ PUSH_OOP (FROM_C_UINT (*(unsigned int *) arg2)); PRIM_SUCCEEDED; case CDATA_LONG_DOUBLE: /* long double */ PUSH_OOP (floatq_new (*(long double *) arg2)); PRIM_SUCCEEDED; } } UNPOP (3); PRIM_FAILED; } /* Memory type: aType at: anAddress put: aValue */ intptr_t VMpr_Memory_atPut (int id, volatile int numArgs) #line 3708 "prims.def" { OOP oop4; OOP oop3; OOP oop2; _gst_primitives_executed++; oop4 = POP_OOP (); oop3 = POP_OOP (); oop2 = POP_OOP (); /* don't pop the receiver */ if (IS_C_LONG (oop3) && IS_INT (oop2)) { intptr_t arg1, arg2; arg1 = TO_INT (oop2); arg2 = TO_C_LONG (oop3); switch (arg1) { case CDATA_CHAR: /* char */ case CDATA_UCHAR: /* unsigned char */ /* may want to use Character instead? */ if (IS_CLASS (oop3, _gst_char_class) || (IS_CLASS (oop3, _gst_unicode_character_class) && CHAR_OOP_VALUE (oop3) <= 127)) { *(char *) arg2 = CHAR_OOP_VALUE (oop4); PRIM_SUCCEEDED; } else if (IS_INT (oop4)) { *(char *) arg2 = (char) TO_INT (oop4); PRIM_SUCCEEDED; } break; case CDATA_SHORT: /* short */ case CDATA_USHORT: /* unsigned short */ if (IS_INT (oop4)) { *(short *) arg2 = (short) TO_INT (oop4); PRIM_SUCCEEDED; } break; case CDATA_LONG: /* long */ case CDATA_ULONG: /* unsigned long */ if (IS_C_LONG (oop4) || IS_C_ULONG (oop4)) { *(long *) arg2 = TO_C_LONG (oop4); PRIM_SUCCEEDED; } break; case CDATA_LONGLONG: /* long long */ case CDATA_ULONGLONG: /* unsigned long long */ if (IS_C_LONGLONG (oop4) || IS_C_ULONGLONG (oop4)) { *(long long *) arg2 = to_c_int_64 (oop4); PRIM_SUCCEEDED; } break; case CDATA_FLOAT: /* float */ if (IS_CLASS (oop4, _gst_floatd_class)) { *(float *) arg2 = (float) FLOATD_OOP_VALUE (oop4); PRIM_SUCCEEDED; } else if (IS_CLASS (oop4, _gst_floate_class)) { *(float *) arg2 = FLOATE_OOP_VALUE (oop4); PRIM_SUCCEEDED; } else if (IS_CLASS (oop4, _gst_floatq_class)) { *(float *) arg2 = (float) FLOATQ_OOP_VALUE (oop4); PRIM_SUCCEEDED; } break; case CDATA_DOUBLE: /* double */ if (IS_CLASS (oop4, _gst_floatd_class)) { *(double *) arg2 = FLOATD_OOP_VALUE (oop4); PRIM_SUCCEEDED; } else if (IS_CLASS (oop4, _gst_floate_class)) { *(double *) arg2 = (double) FLOATE_OOP_VALUE (oop4); PRIM_SUCCEEDED; } else if (IS_CLASS (oop4, _gst_floatq_class)) { *(double *) arg2 = (double) FLOATQ_OOP_VALUE (oop4); PRIM_SUCCEEDED; } break; case CDATA_STRING: /* string */ if (IS_CLASS (oop4, _gst_string_class) || IS_CLASS (oop4, _gst_symbol_class)) { /* Char* cast on the right side needed because _gst_to_cstring returns gst_uchar * */ *(char **) arg2 = (char *) _gst_to_cstring (oop4); PRIM_SUCCEEDED; } break; case CDATA_OOP: /* OOP */ *(OOP *) arg2 = oop4; PRIM_SUCCEEDED; case CDATA_INT: /* int */ case CDATA_UINT: /* unsigned int */ if (IS_C_INT (oop4) || is_c_uint_32 (oop4)) { *(int *) arg2 = TO_C_INT (oop4); PRIM_SUCCEEDED; } break; case CDATA_LONG_DOUBLE: /* long double */ if (IS_CLASS (oop4, _gst_floatd_class)) { *(long double *) arg2 = (long double) FLOATD_OOP_VALUE (oop4); PRIM_SUCCEEDED; } else if (IS_CLASS (oop4, _gst_floate_class)) { *(long double *) arg2 = (long double) FLOATE_OOP_VALUE (oop4); PRIM_SUCCEEDED; } else if (IS_CLASS (oop4, _gst_floatq_class)) { *(long double *) arg2 = FLOATQ_OOP_VALUE (oop4); PRIM_SUCCEEDED; } break; } } UNPOP (3); PRIM_FAILED; } /* methodsFor: category */ intptr_t VMpr_Behavior_methodsFor (int id, volatile int numArgs) #line 3847 "prims.def" { OOP oop2 = POP_OOP (); OOP oop1 = STACKTOP (); _gst_primitives_executed++; if (!_gst_current_parser || _gst_current_parser->state != PARSE_DOIT) PRIM_FAILED; _gst_set_compilation_class (oop1); _gst_set_compilation_category (oop2); _gst_display_compilation_trace ("Compiling", true); _gst_current_parser->state = PARSE_METHOD_LIST; PRIM_SUCCEEDED; } /* methodsFor: category ifTrue: condition */ intptr_t VMpr_Behavior_methodsForIfTrue (int id, volatile int numArgs) #line 3864 "prims.def" { OOP oop3 = POP_OOP (); OOP oop2 = POP_OOP (); OOP oop1 = STACKTOP (); _gst_primitives_executed++; if (!_gst_current_parser || _gst_current_parser->state != PARSE_DOIT) PRIM_FAILED; _gst_set_compilation_class (oop1); _gst_set_compilation_category (oop2); if (oop3 == _gst_true_oop) _gst_display_compilation_trace ("Conditionally compiling", true); else { _gst_skip_compilation = true; _gst_display_compilation_trace ("Conditionally skipping", true); } _gst_current_parser->state = PARSE_METHOD_LIST; PRIM_SUCCEEDED; } intptr_t VMpr_Processor_disableEnableInterrupts (int id, volatile int numArgs) #line 3890 "prims.def" { OOP processOOP; gst_process process; gst_processor_scheduler processor; int count; _gst_primitives_executed++; processor = (gst_processor_scheduler) OOP_TO_OBJ (_gst_processor_oop); processOOP = processor->activeProcess; process = (gst_process) OOP_TO_OBJ (processOOP); count = IS_NIL (process->interrupts) ? 0 : TO_INT (process->interrupts); if (id == 0 && count++ == 0) async_queue_enabled = false; else if (id == -1 && --count == 0) { async_queue_enabled = true; SET_EXCEPT_FLAG (true); } process->interrupts = FROM_INT (count); PRIM_SUCCEEDED; } /* ProcessorScheduler signal: aSemaphore onInterrupt: anInteger */ intptr_t VMpr_Processor_signalOnInterrupt (int id, volatile int numArgs) #line 3918 "prims.def" { OOP oop1; OOP oop2; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = POP_OOP (); if (IS_INT (oop2)) { intptr_t arg2; arg2 = TO_INT (oop2); _gst_async_interrupt_wait (oop1, arg2); PRIM_SUCCEEDED; } UNPOP (2); PRIM_FAILED; } /* ObjectMemory spaceGrowRate */ intptr_t VMpr_ObjectMemory_getSpaceGrowRate (int id, volatile int numArgs) #line 3940 "prims.def" { _gst_primitives_executed++; SET_STACKTOP (floatd_new ((double) _gst_mem.space_grow_rate)); PRIM_SUCCEEDED; } /* ObjectMemory spaceGrowRate: */ intptr_t VMpr_ObjectMemory_setSpaceGrowRate (int id, volatile int numArgs) #line 3948 "prims.def" { intptr_t arg1; OOP oop1; _gst_primitives_executed++; oop1 = POP_OOP (); if (IS_CLASS (oop1, _gst_floatd_class)) arg1 = (int) FLOATD_OOP_VALUE (oop1); else if (IS_CLASS (oop1, _gst_floate_class)) arg1 = (int) FLOATE_OOP_VALUE (oop1); else if (IS_CLASS (oop1, _gst_floatq_class)) arg1 = (int) FLOATQ_OOP_VALUE (oop1); else if (IS_INT (oop1)) arg1 = TO_INT (oop1); else { UNPOP (1); PRIM_FAILED; } if (arg1 > 0 && arg1 <= 500) { _gst_init_mem (0, 0, 0, 0, 0, arg1); PRIM_SUCCEEDED; } UNPOP (1); PRIM_FAILED; } /* ObjectMemory smoothingFactor */ intptr_t VMpr_ObjectMemory_getSmoothingFactor (int id, volatile int numArgs) #line 3980 "prims.def" { _gst_primitives_executed++; SET_STACKTOP (floatd_new ((double) _gst_mem.factor)); PRIM_SUCCEEDED; } /* ObjectMemory smoothingFactor: */ intptr_t VMpr_ObjectMemory_setSmoothingFactor (int id, volatile int numArgs) #line 3988 "prims.def" { OOP oop1; intptr_t arg1; _gst_primitives_executed++; oop1 = POP_OOP (); if (IS_CLASS (oop1, _gst_floatd_class)) arg1 = (int) FLOATD_OOP_VALUE (oop1); else if (IS_CLASS (oop1, _gst_floate_class)) arg1 = (int) FLOATE_OOP_VALUE (oop1); else if (IS_CLASS (oop1, _gst_floatq_class)) arg1 = (int) FLOATQ_OOP_VALUE (oop1); else if (IS_INT (oop1)) arg1 = TO_INT (oop1); else { UNPOP (1); PRIM_FAILED; } if (arg1 >= 0 && arg1 <= 1) { _gst_mem.factor = arg1; PRIM_SUCCEEDED; } UNPOP (1); PRIM_FAILED; } /* ObjectMemory growThresholdPercent */ intptr_t VMpr_ObjectMemory_getGrowThresholdPercent (int id, volatile int numArgs) #line 4019 "prims.def" { _gst_primitives_executed++; SET_STACKTOP (floatd_new ((double) _gst_mem.grow_threshold_percent)); PRIM_SUCCEEDED; } /* ObjectMemory growThresholdPercent: */ intptr_t VMpr_ObjectMemory_setGrowThresholdPercent (int id, volatile int numArgs) #line 4027 "prims.def" { OOP oop1; intptr_t arg1; _gst_primitives_executed++; oop1 = POP_OOP (); if (IS_CLASS (oop1, _gst_floatd_class)) arg1 = (int) FLOATD_OOP_VALUE (oop1); else if (IS_CLASS (oop1, _gst_floate_class)) arg1 = (int) FLOATE_OOP_VALUE (oop1); else if (IS_CLASS (oop1, _gst_floatq_class)) arg1 = (int) FLOATQ_OOP_VALUE (oop1); else if (IS_INT (oop1)) arg1 = TO_INT (oop1); else { UNPOP (1); PRIM_FAILED; } if (arg1 > 0 && arg1 < 100) { _gst_init_mem (0, 0, 0, 0, arg1, 0); PRIM_SUCCEEDED; } UNPOP (1); PRIM_FAILED; } /* ObjectMemory bigObjectThreshold */ intptr_t VMpr_ObjectMemory_getBigObjectThreshold (int id, volatile int numArgs) #line 4058 "prims.def" { _gst_primitives_executed++; SET_STACKTOP_INT (_gst_mem.big_object_threshold); PRIM_SUCCEEDED; } /* ObjectMemory bigObjectThreshold: */ intptr_t VMpr_ObjectMemory_setBigObjectThreshold (int id, volatile int numArgs) #line 4066 "prims.def" { OOP oop1; intptr_t arg1; _gst_primitives_executed++; oop1 = POP_OOP (); if (IS_NIL (oop1)) arg1 = INT_MAX < MAX_ST_INT ? INT_MAX : MAX_ST_INT; else if (IS_INT (oop1)) arg1 = TO_INT (oop1); else { UNPOP (1); PRIM_FAILED; } if (arg1 >= 0) { _gst_init_mem (0, 0, 0, arg1, 0, 0); PRIM_SUCCEEDED; } UNPOP (1); PRIM_FAILED; } /* ObjectMemory growTo: numBytes */ intptr_t VMpr_ObjectMemory_growTo (int id, volatile int numArgs) #line 4094 "prims.def" { OOP oop1; intptr_t arg1; _gst_primitives_executed++; oop1 = POP_OOP (); if (IS_INT (oop1)) { arg1 = TO_INT (oop1); _gst_grow_memory_to (arg1); PRIM_SUCCEEDED; } UNPOP (1); PRIM_FAILED; } /* ObjectMemory update */ intptr_t VMpr_ObjectMemory_update (int id, volatile int numArgs) #line 4113 "prims.def" { _gst_primitives_executed++; #ifndef OPTIMIZE if (OOP_CLASS (STACKTOP ()) != _gst_object_memory_class) PRIM_FAILED; #endif _gst_update_object_memory_oop (STACKTOP ()); PRIM_SUCCEEDED; } /* CObject class alloc: nbytes type: aType */ intptr_t VMpr_CObject_allocType (int id, volatile int numArgs) #line 4128 "prims.def" { OOP oop1; OOP oop2; OOP oop3; _gst_primitives_executed++; oop1 = STACK_AT (0); oop2 = STACK_AT (1); oop3 = STACK_AT (2); if (IS_INT (oop2) && (IS_NIL (oop1) || is_a_kind_of (OOP_CLASS (oop1), _gst_c_type_class)) && COMMON (RECEIVER_IS_A_KIND_OF (oop3, _gst_c_object_class))) { intptr_t arg2 = TO_INT (oop2); PTR ptr = xmalloc (arg2); OOP cObjectOOP = COBJECT_NEW (ptr, oop1, oop3); POP_N_OOPS (2); SET_STACKTOP (cObjectOOP); PRIM_SUCCEEDED; } PRIM_FAILED; } /* sin */ intptr_t VMpr_Float_sin (int id, volatile int numArgs) #line 4154 "prims.def" { OOP oop1; _gst_primitives_executed++; oop1 = STACKTOP (); if (IS_CLASS (oop1, _gst_floatd_class)) { double farg1 = FLOATD_OOP_VALUE (oop1); SET_STACKTOP (floatd_new (sin (farg1))); PRIM_SUCCEEDED; } else if (IS_CLASS (oop1, _gst_floate_class)) { double farg1 = (double) FLOATE_OOP_VALUE (oop1); SET_STACKTOP (floate_new (sin (farg1))); PRIM_SUCCEEDED; } else if (IS_CLASS (oop1, _gst_floatq_class)) { long double farg1 = FLOATQ_OOP_VALUE (oop1); SET_STACKTOP (floatq_new (sinl (farg1))); PRIM_SUCCEEDED; } PRIM_FAILED; } /* cos */ intptr_t VMpr_Float_cos (int id, volatile int numArgs) #line 4182 "prims.def" { OOP oop1; _gst_primitives_executed++; oop1 = STACKTOP (); if (IS_CLASS (oop1, _gst_floatd_class)) { double farg1 = FLOATD_OOP_VALUE (oop1); SET_STACKTOP (floatd_new (cos (farg1))); PRIM_SUCCEEDED; } else if (IS_CLASS (oop1, _gst_floate_class)) { double farg1 = (double) FLOATE_OOP_VALUE (oop1); SET_STACKTOP (floate_new (cos (farg1))); PRIM_SUCCEEDED; } else if (IS_CLASS (oop1, _gst_floatq_class)) { long double farg1 = FLOATQ_OOP_VALUE (oop1); SET_STACKTOP (floatq_new (cosl (farg1))); PRIM_SUCCEEDED; } PRIM_FAILED; } /* tan */ intptr_t VMpr_Float_tan (int id, volatile int numArgs) #line 4210 "prims.def" { OOP oop1; _gst_primitives_executed++; oop1 = STACKTOP (); if (IS_CLASS (oop1, _gst_floatd_class)) { double farg1 = FLOATD_OOP_VALUE (oop1); SET_STACKTOP (floatd_new (tan (farg1))); PRIM_SUCCEEDED; } else if (IS_CLASS (oop1, _gst_floate_class)) { double farg1 = (double) FLOATE_OOP_VALUE (oop1); SET_STACKTOP (floate_new (tan (farg1))); PRIM_SUCCEEDED; } else if (IS_CLASS (oop1, _gst_floatq_class)) { long double farg1 = FLOATQ_OOP_VALUE (oop1); SET_STACKTOP (floatq_new (tanl (farg1))); PRIM_SUCCEEDED; } PRIM_FAILED; } /* arcSin */ intptr_t VMpr_Float_arcSin (int id, volatile int numArgs) #line 4238 "prims.def" { OOP oop1; _gst_primitives_executed++; oop1 = STACKTOP (); if (IS_CLASS (oop1, _gst_floatd_class)) { double farg1 = FLOATD_OOP_VALUE (oop1); SET_STACKTOP (floatd_new (asin (farg1))); PRIM_SUCCEEDED; } else if (IS_CLASS (oop1, _gst_floate_class)) { double farg1 = (double) FLOATE_OOP_VALUE (oop1); SET_STACKTOP (floate_new (asin (farg1))); PRIM_SUCCEEDED; } else if (IS_CLASS (oop1, _gst_floatq_class)) { long double farg1 = FLOATQ_OOP_VALUE (oop1); SET_STACKTOP (floatq_new (asinl (farg1))); PRIM_SUCCEEDED; } PRIM_FAILED; } /* arcCos */ intptr_t VMpr_Float_arcCos (int id, volatile int numArgs) #line 4266 "prims.def" { OOP oop1; _gst_primitives_executed++; oop1 = STACKTOP (); if (IS_CLASS (oop1, _gst_floatd_class)) { double farg1 = FLOATD_OOP_VALUE (oop1); SET_STACKTOP (floatd_new (acos (farg1))); PRIM_SUCCEEDED; } else if (IS_CLASS (oop1, _gst_floate_class)) { double farg1 = (double) FLOATE_OOP_VALUE (oop1); SET_STACKTOP (floate_new (acos (farg1))); PRIM_SUCCEEDED; } else if (IS_CLASS (oop1, _gst_floatq_class)) { long double farg1 = FLOATQ_OOP_VALUE (oop1); SET_STACKTOP (floatq_new (acosl (farg1))); PRIM_SUCCEEDED; } PRIM_FAILED; } /* arcTan */ intptr_t VMpr_Float_arcTan (int id, volatile int numArgs) #line 4294 "prims.def" { OOP oop1; _gst_primitives_executed++; oop1 = STACKTOP (); if (IS_CLASS (oop1, _gst_floatd_class)) { double farg1 = FLOATD_OOP_VALUE (oop1); SET_STACKTOP (floatd_new (atan (farg1))); PRIM_SUCCEEDED; } else if (IS_CLASS (oop1, _gst_floate_class)) { double farg1 = (double) FLOATE_OOP_VALUE (oop1); SET_STACKTOP (floate_new (atan (farg1))); PRIM_SUCCEEDED; } else if (IS_CLASS (oop1, _gst_floatq_class)) { long double farg1 = FLOATQ_OOP_VALUE (oop1); SET_STACKTOP (floatq_new (atanl (farg1))); PRIM_SUCCEEDED; } PRIM_FAILED; } /* exp */ intptr_t VMpr_Float_exp (int id, volatile int numArgs) #line 4322 "prims.def" { OOP oop1; _gst_primitives_executed++; oop1 = STACKTOP (); if (IS_CLASS (oop1, _gst_floatd_class)) { double farg1 = FLOATD_OOP_VALUE (oop1); SET_STACKTOP (floatd_new (exp (farg1))); PRIM_SUCCEEDED; } else if (IS_CLASS (oop1, _gst_floate_class)) { double farg1 = (double) FLOATE_OOP_VALUE (oop1); SET_STACKTOP (floate_new (exp (farg1))); PRIM_SUCCEEDED; } else if (IS_CLASS (oop1, _gst_floatq_class)) { long double farg1 = FLOATQ_OOP_VALUE (oop1); SET_STACKTOP (floatq_new (expl (farg1))); PRIM_SUCCEEDED; } PRIM_FAILED; } /* ln */ intptr_t VMpr_Float_ln (int id, volatile int numArgs) #line 4350 "prims.def" { OOP oop1; _gst_primitives_executed++; oop1 = STACKTOP (); if (IS_CLASS (oop1, _gst_floatd_class)) { double farg1 = FLOATD_OOP_VALUE (oop1); SET_STACKTOP (floatd_new (log (farg1))); PRIM_SUCCEEDED; } else if (IS_CLASS (oop1, _gst_floate_class)) { double farg1 = (double) FLOATE_OOP_VALUE (oop1); SET_STACKTOP (floate_new (log (farg1))); PRIM_SUCCEEDED; } else if (IS_CLASS (oop1, _gst_floatq_class)) { long double farg1 = FLOATQ_OOP_VALUE (oop1); SET_STACKTOP (floatq_new (logl (farg1))); PRIM_SUCCEEDED; } PRIM_FAILED; } /* raisedTo: aNumber -- receiver ** aNumber */ intptr_t VMpr_Float_pow (int id, volatile int numArgs) #line 4378 "prims.def" { OOP oop1; OOP oop2; double farg1, farg2; long double lfarg1, lfarg2; mst_Boolean long_double = false; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = STACKTOP (); if (IS_CLASS (oop1, _gst_floatd_class)) lfarg1 = farg1 = FLOATD_OOP_VALUE (oop1); else if (IS_CLASS (oop1, _gst_floate_class)) lfarg1 = farg1 = FLOATE_OOP_VALUE (oop1); else if (IS_CLASS (oop1, _gst_floatq_class)) { long_double = true; lfarg1 = farg1 = FLOATQ_OOP_VALUE (oop1); } else { UNPOP (1); PRIM_FAILED; } if (IS_CLASS (oop2, _gst_floatd_class)) lfarg2 = farg2 = FLOATD_OOP_VALUE (oop2); else if (IS_CLASS (oop2, _gst_floate_class)) lfarg2 = farg2 = FLOATE_OOP_VALUE (oop2); else if (IS_CLASS (oop2, _gst_floatq_class)) { long_double = true; lfarg2 = farg2 = FLOATQ_OOP_VALUE (oop2); } else { UNPOP (1); PRIM_FAILED; } if ((lfarg1 == 0.0 && lfarg2 < 0.0) || lfarg1 < 0.0) { UNPOP (1); PRIM_FAILED; } if (long_double) { if (IS_NAN (lfarg1) || IS_NAN (lfarg2)) /* The C99 standard mandates that pow(1, NaN) = 1.0 and pow (NaN, 0.0) = 1.0, which is plain wrong. We take the liberty to make these results be NaN. */ SET_STACKTOP (floatq_new (lfarg1 + lfarg2)); else SET_STACKTOP (floatq_new (powl (lfarg1, lfarg2))); } else { if (IS_NAN (farg1) || IS_NAN (farg2)) /* The C99 standard mandates that pow(1, NaN) = 1.0 and pow (NaN, 0.0) = 1.0, which is plain wrong. We take the liberty to make these results be NaN. */ SET_STACKTOP (floatd_new (farg1 + farg2)); else SET_STACKTOP (floatd_new (pow (farg1, farg2))); } PRIM_SUCCEEDED; } /* CObject free */ intptr_t VMpr_CObject_free (int id, volatile int numArgs) #line 4452 "prims.def" { OOP oop1; _gst_primitives_executed++; oop1 = STACKTOP (); if COMMON (is_a_kind_of (OOP_CLASS (oop1), _gst_c_callback_descriptor_class)) { _gst_free_closure (oop1); SET_STACKTOP (_gst_nil_oop); PRIM_SUCCEEDED; } else if COMMON (RECEIVER_IS_A_KIND_OF (OOP_CLASS (oop1), _gst_c_object_class)) { _gst_free_cobject (oop1); /* free allocated space */ SET_STACKTOP (_gst_nil_oop); PRIM_SUCCEEDED; } PRIM_FAILED; } /* sqrt */ intptr_t VMpr_Float_sqrt (int id, volatile int numArgs) #line 4475 "prims.def" { OOP oop1; _gst_primitives_executed++; oop1 = STACKTOP (); if (IS_CLASS (oop1, _gst_floatd_class)) { double farg1 = FLOATD_OOP_VALUE (oop1); SET_STACKTOP (floatd_new (sqrt (farg1))); PRIM_SUCCEEDED; } else if (IS_CLASS (oop1, _gst_floate_class)) { double farg1 = FLOATE_OOP_VALUE (oop1); SET_STACKTOP (floate_new (sqrt (farg1))); PRIM_SUCCEEDED; } else if (IS_CLASS (oop1, _gst_floatq_class)) { long double farg1 = FLOATQ_OOP_VALUE (oop1); SET_STACKTOP (floatq_new (sqrtl (farg1))); PRIM_SUCCEEDED; } PRIM_FAILED; } /* ceiling, floor */ intptr_t VMpr_Float_ceil_floor (int id, volatile int numArgs) #line 4505 "prims.def" { OOP oop1; double farg1; _gst_primitives_executed++; oop1 = STACKTOP (); if (IS_CLASS (oop1, _gst_floatd_class)) farg1 = FLOATD_OOP_VALUE (oop1); else if (IS_CLASS (oop1, _gst_floate_class)) farg1 = (double) FLOATE_OOP_VALUE (oop1); else if (IS_CLASS (oop1, _gst_floatq_class)) farg1 = (double) FLOATQ_OOP_VALUE (oop1); else PRIM_FAILED; if COMMON ((farg1 > MIN_ST_INT) && farg1 < MAX_ST_INT) { switch (id) { case 0: SET_STACKTOP_INT ((intptr_t) ceil (farg1)); PRIM_SUCCEEDED; case -1: SET_STACKTOP_INT ((intptr_t) floor (farg1)); PRIM_SUCCEEDED; } } PRIM_FAILED; } /* Behavior basicNewInFixedSpace */ intptr_t VMpr_Behavior_basicNewFixed (int id, volatile int numArgs) #line 4538 "prims.def" { OOP oop1; _gst_primitives_executed++; oop1 = STACKTOP (); if (IS_OOP (oop1)) { if (!CLASS_IS_INDEXABLE (oop1)) { OOP result; instantiate (oop1, &result); _gst_make_oop_fixed (result); SET_STACKTOP (result); PRIM_SUCCEEDED; } } PRIM_FAILED; } /* Behavior basicNewInFixedSpace: */ intptr_t VMpr_Behavior_basicNewFixedColon (int id, volatile int numArgs) #line 4559 "prims.def" { OOP oop1; OOP oop2; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = STACKTOP (); if (IS_OOP (oop1) && IS_INT (oop2)) { if (CLASS_IS_INDEXABLE (oop1)) { intptr_t arg2; arg2 = TO_INT (oop2); if (arg2 >= 0) { OOP result; instantiate_with (oop1, arg2, &result); _gst_make_oop_fixed (result); SET_STACKTOP (result); PRIM_SUCCEEDED; } } } UNPOP (1); PRIM_FAILED; } intptr_t VMpr_Object_tenure (int id, volatile int numArgs) #line 4588 "prims.def" { OOP oop1; _gst_primitives_executed++; oop1 = STACKTOP (); if (IS_OOP (oop1)) { _gst_tenure_oop (oop1); PRIM_SUCCEEDED; } PRIM_FAILED; } intptr_t VMpr_Object_makeFixed (int id, volatile int numArgs) #line 4603 "prims.def" { OOP oop1; _gst_primitives_executed++; oop1 = STACKTOP (); if (IS_OOP (oop1)) { _gst_make_oop_fixed (oop1); PRIM_SUCCEEDED; } PRIM_FAILED; } /* CObject at: byteoffset type: aType */ intptr_t VMpr_CObject_at (int id, volatile int numArgs) #line 4623 "prims.def" { OOP oop1; OOP oop2; OOP oop3; _gst_primitives_executed++; oop3 = POP_OOP (); oop2 = POP_OOP (); oop1 = STACKTOP (); if (IS_INT (oop2) && ((IS_INT (oop3) && id == -1) || is_a_kind_of (OOP_CLASS (oop3), _gst_c_type_class))) { char *addr; intptr_t arg2; arg2 = TO_INT (oop2); if (IS_INT (oop3)) { /* int type spec means a scalar type */ intptr_t arg3 = TO_INT (oop3); if (!cobject_index_check (oop1, arg2, _gst_c_type_size (arg3))) goto fail; addr = ((char *) cobject_value (oop1)) + arg2; switch (arg3) { case CDATA_CHAR: case CDATA_UCHAR: SET_STACKTOP (CHAR_OOP_AT (*(gst_uchar *) addr)); PRIM_SUCCEEDED; case CDATA_SHORT: SET_STACKTOP_INT (*(short *) addr); PRIM_SUCCEEDED; case CDATA_USHORT: SET_STACKTOP_INT (*(unsigned short *) addr); PRIM_SUCCEEDED; case CDATA_LONGLONG: SET_STACKTOP (from_c_int_64 (*(long long *) addr)); PRIM_SUCCEEDED; case CDATA_ULONGLONG: SET_STACKTOP (from_c_uint_64 (*(unsigned long long *) addr)); PRIM_SUCCEEDED; case CDATA_LONG: SET_STACKTOP (FROM_C_LONG (*(long *) addr)); PRIM_SUCCEEDED; case CDATA_ULONG: SET_STACKTOP (FROM_C_ULONG (*(unsigned long *) addr)); PRIM_SUCCEEDED; case CDATA_FLOAT: SET_STACKTOP (floate_new (*(float *) addr)); PRIM_SUCCEEDED; case CDATA_DOUBLE: SET_STACKTOP (floatd_new (*(double *) addr)); PRIM_SUCCEEDED; case CDATA_STRING: { char **strAddr; strAddr = (char **) addr; if (*strAddr) { SET_STACKTOP (_gst_string_new (*strAddr)); PRIM_SUCCEEDED; } else { SET_STACKTOP (_gst_nil_oop); PRIM_SUCCEEDED; } } case CDATA_OOP: SET_STACKTOP (*(OOP *) addr); PRIM_SUCCEEDED; case CDATA_INT: SET_STACKTOP (FROM_C_INT (*(int *) addr)); PRIM_SUCCEEDED; case CDATA_UINT: SET_STACKTOP (FROM_C_UINT (*(unsigned int *) addr)); PRIM_SUCCEEDED; case CDATA_LONG_DOUBLE: SET_STACKTOP (floatq_new (*(long double *) addr)); PRIM_SUCCEEDED; } } else { OOP baseOOP; uintptr_t ofs; inc_ptr incPtr; /* Non-integer oop3: use it as the type of the effective address. */ if (id == 0) { if (!cobject_index_check (oop1, arg2, sizeof (uintptr_t))) goto fail; ofs = *(uintptr_t *) (((char *)cobject_value (oop1)) + arg2); baseOOP = _gst_nil_oop; if (ofs == 0) { SET_STACKTOP (_gst_nil_oop); PRIM_SUCCEEDED; } } else { /* No need to enforce bounds here (if we ever will, remember that a pointer that is one-past the end of the object is valid!). */ gst_cobject cObj = (gst_cobject) OOP_TO_OBJ (oop1); baseOOP = cObj->storage; ofs = COBJECT_OFFSET_OBJ (cObj) + arg2; } /* oop3 could get GC'ed out of existence before it gets used: it is not on the stack, and _gst_c_object_new_base could cause a GC */ incPtr = INC_SAVE_POINTER (); INC_ADD_OOP (baseOOP); INC_ADD_OOP (oop3); SET_STACKTOP (_gst_c_object_new_base (baseOOP, ofs, oop3, _gst_c_object_class)); INC_RESTORE_POINTER (incPtr); PRIM_SUCCEEDED; } } fail: UNPOP (2); PRIM_FAILED; } /* CObject at: byteOffset put: aValue type: aType */ intptr_t VMpr_CObject_atPut (int id, volatile int numArgs) #line 4768 "prims.def" { OOP oop1; OOP oop2; OOP oop3; OOP oop4; _gst_primitives_executed++; oop4 = POP_OOP (); oop3 = POP_OOP (); oop2 = POP_OOP (); oop1 = STACKTOP (); if (IS_INT (oop2) && IS_INT (oop4)) { char *addr; intptr_t arg2 = TO_INT (oop2); intptr_t arg4 = TO_INT (oop4); if (!cobject_index_check (oop1, arg2, _gst_c_type_size (arg4))) goto fail; addr = ((char *) cobject_value (oop1)) + arg2; switch (arg4) { case CDATA_CHAR: /* char */ case CDATA_UCHAR: /* uchar */ if (IS_CLASS (oop3, _gst_char_class) || (IS_CLASS (oop3, _gst_unicode_character_class) && CHAR_OOP_VALUE (oop3) <= 127)) { *addr = CHAR_OOP_VALUE (oop3); PRIM_SUCCEEDED; } else if (IS_INT (oop3)) { *(char *) addr = (char) TO_INT (oop3); PRIM_SUCCEEDED; } break; case CDATA_SHORT: /* short */ case CDATA_USHORT: /* ushort */ if (IS_INT (oop3)) { *(short *) addr = (short) TO_INT (oop3); PRIM_SUCCEEDED; } break; case CDATA_LONG: /* long */ case CDATA_ULONG: /* ulong */ if (IS_C_LONG (oop3) || IS_C_ULONG (oop3)) { *(long *) addr = (long) TO_C_LONG (oop3); PRIM_SUCCEEDED; } break; case CDATA_LONGLONG: /* long long */ case CDATA_ULONGLONG: /* unsigned long long */ if (IS_C_LONGLONG (oop3) || IS_C_ULONGLONG (oop3)) { *(long long *) addr = (long long) to_c_int_64 (oop3); PRIM_SUCCEEDED; } break; case CDATA_FLOAT: { float *floatAddr; floatAddr = (float *) addr; if (IS_INT (oop3)) { *floatAddr = (float) TO_INT (oop3); PRIM_SUCCEEDED; } else if (IS_CLASS (oop3, _gst_floatd_class)) { *floatAddr = (float) FLOATD_OOP_VALUE (oop3); PRIM_SUCCEEDED; } else if (IS_CLASS (oop3, _gst_floate_class)) { *floatAddr = (float) FLOATE_OOP_VALUE (oop3); PRIM_SUCCEEDED; } else if (IS_CLASS (oop3, _gst_floatq_class)) { *floatAddr = (float) FLOATQ_OOP_VALUE (oop3); PRIM_SUCCEEDED; } } break; case CDATA_DOUBLE: /* double */ { double *doubleAddr; doubleAddr = (double *) addr; if (IS_INT (oop3)) { *doubleAddr = TO_INT (oop3); PRIM_SUCCEEDED; } else if (IS_CLASS (oop3, _gst_floatd_class)) { *doubleAddr = FLOATD_OOP_VALUE (oop3); PRIM_SUCCEEDED; } else if (IS_CLASS (oop3, _gst_floate_class)) { *doubleAddr = FLOATE_OOP_VALUE (oop3); PRIM_SUCCEEDED; } else if (IS_CLASS (oop3, _gst_floatq_class)) { *doubleAddr = FLOATQ_OOP_VALUE (oop3); PRIM_SUCCEEDED; } } break; case CDATA_STRING: /* string */ { /* note that this does not allow for replacemnt in place */ /* to replace in place, use replaceFrom: */ char **strAddr; strAddr = (char **) addr; if (oop3 == _gst_nil_oop) { *strAddr = (char *) 0; PRIM_SUCCEEDED; } else if (is_a_kind_of (OOP_CLASS (oop3), _gst_string_class)) { *strAddr = (char *) _gst_to_cstring (oop3); PRIM_SUCCEEDED; } break; } case CDATA_OOP: *(OOP *) addr = oop3; PRIM_SUCCEEDED; case CDATA_INT: /* int */ case CDATA_UINT: /* uint */ if (IS_C_INT (oop3)) { *(int *) addr = (int) TO_C_INT (oop3); PRIM_SUCCEEDED; } break; case CDATA_LONG_DOUBLE: /* long double */ { long double *longDoubleAddr; longDoubleAddr = (long double *) addr; if (IS_INT (oop3)) { *longDoubleAddr = TO_INT (oop3); PRIM_SUCCEEDED; } else if (IS_CLASS (oop3, _gst_floatd_class)) { *longDoubleAddr = FLOATD_OOP_VALUE (oop3); PRIM_SUCCEEDED; } else if (IS_CLASS (oop3, _gst_floate_class)) { *longDoubleAddr = FLOATE_OOP_VALUE (oop3); PRIM_SUCCEEDED; } else if (IS_CLASS (oop3, _gst_floatq_class)) { *longDoubleAddr = FLOATQ_OOP_VALUE (oop3); PRIM_SUCCEEDED; } } break; } } fail: UNPOP (3); PRIM_FAILED; } /* CObject address */ intptr_t VMpr_CObject_address (int id, volatile int numArgs) #line 4956 "prims.def" { OOP oop1; gst_cobject cObj; uintptr_t ptr; _gst_primitives_executed++; oop1 = STACKTOP (); cObj = (gst_cobject) OOP_TO_OBJ (oop1); ptr = (uintptr_t) COBJECT_OFFSET_OBJ (cObj); if (IS_NIL (cObj->storage)) SET_STACKTOP (FROM_C_ULONG (ptr)); else SET_STACKTOP (FROM_C_LONG (ptr)); PRIM_SUCCEEDED; } /* CObject address: */ intptr_t VMpr_CObject_addressColon (int id, volatile int numArgs) #line 4977 "prims.def" { OOP oop1, oop2; gst_cobject cObj; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = STACKTOP (); cObj = (gst_cobject) OOP_TO_OBJ (oop1); if (IS_NIL (cObj->storage) ? IS_C_ULONG (oop2) : IS_C_LONG (oop2)) { SET_COBJECT_OFFSET_OBJ (cObj, TO_C_LONG (oop2)); PRIM_SUCCEEDED; } UNPOP (1); PRIM_FAILED; } /* CString replaceWith: aString */ intptr_t VMpr_CString_replaceWith (int id, volatile int numArgs) #line 4998 "prims.def" { OOP oop1; OOP oop2; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = STACKTOP (); /* assumes the receiver is already pointing at an area of memory that is the correct size; does not (re)allocate receiver's string at all. */ if (IS_CLASS (oop2, _gst_string_class) || IS_CLASS (oop2, _gst_byte_array_class)) { size_t srcLen; gst_uchar *dstBase, *srcBase; srcBase = STRING_OOP_CHARS (oop2); srcLen = NUM_INDEXABLE_FIELDS (oop2); dstBase = *(gst_uchar **) cobject_value (oop1); memcpy (dstBase, srcBase, srcLen); dstBase[srcLen] = '\0'; /* since it's a CString type, we NUL term it */ PRIM_SUCCEEDED; } UNPOP (1); PRIM_FAILED; } /* ByteArray class fromCdata: aCObject size: anInteger */ intptr_t VMpr_ByteArray_fromCData_size (int id, volatile int numArgs) #line 5030 "prims.def" { OOP oop1; OOP oop2; OOP oop3; _gst_primitives_executed++; oop3 = POP_OOP (); oop2 = POP_OOP (); oop1 = STACKTOP (); if (IS_INT (oop3)) { intptr_t arg3 = TO_INT (oop3); OOP byteArrayOOP = _gst_byte_array_new (cobject_value (oop2), arg3); SET_STACKTOP (byteArrayOOP); PRIM_SUCCEEDED; } UNPOP (2); PRIM_FAILED; } /* String class fromCdata: aCObject size: anInteger */ intptr_t VMpr_String_fromCData_size (int id, volatile int numArgs) #line 5053 "prims.def" { OOP oop1; OOP oop2; OOP oop3; _gst_primitives_executed++; oop3 = POP_OOP (); oop2 = POP_OOP (); oop1 = STACKTOP (); if (IS_INT (oop3)) { intptr_t arg3 = TO_INT (oop3); OOP stringOOP = _gst_counted_string_new (cobject_value (oop2), arg3); SET_STACKTOP (stringOOP); PRIM_SUCCEEDED; } UNPOP (2); PRIM_FAILED; } /* String class fromCdata: aCObject */ intptr_t VMpr_String_fromCData (int id, volatile int numArgs) #line 5076 "prims.def" { OOP oop1; OOP oop2; OOP stringOOP; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = STACKTOP (); stringOOP = _gst_string_new (cobject_value (oop2)); SET_STACKTOP (stringOOP); PRIM_SUCCEEDED; } /* String asCdata: aCType * ByteArray asCdata: aCType */ intptr_t VMpr_String_ByteArray_asCData (int id, volatile int numArgs) #line 5094 "prims.def" { OOP oop1; OOP oop2; _gst_primitives_executed++; oop2 = STACK_AT (0); oop1 = STACK_AT (1); if (is_a_kind_of (OOP_CLASS (oop2), _gst_c_type_class)) { int size = NUM_INDEXABLE_FIELDS (oop1); int alloc_size = (id == 0) ? size + 1 : size; char *data = xmalloc (alloc_size); OOP cObjectOOP = COBJECT_NEW (data, oop2, _gst_c_object_class); memcpy (data, OOP_TO_OBJ (oop1)->data, size); if (id == 0) data[size] = 0; POP_N_OOPS (1); SET_STACKTOP (cObjectOOP); PRIM_SUCCEEDED; } PRIM_FAILED; } /* SystemDictionary byteCodeCounter */ intptr_t VMpr_SystemDictionary_byteCodeCounter (int id, volatile int numArgs) #line 5120 "prims.def" { _gst_primitives_executed++; SET_STACKTOP_INT (_gst_bytecode_counter); PRIM_SUCCEEDED; } /* SystemDictionary debug */ intptr_t VMpr_SystemDictionary_debug (int id, volatile int numArgs) #line 5128 "prims.def" { _gst_primitives_executed++; _gst_debug (); /* used to allow gdb to stop based on Smalltalk execution paths. */ PRIM_SUCCEEDED; } /* Object isUntrusted */ intptr_t VMpr_Object_isUntrusted (int id, volatile int numArgs) #line 5138 "prims.def" { OOP oop1; _gst_primitives_executed++; oop1 = STACKTOP (); SET_STACKTOP_BOOLEAN (IS_OOP_UNTRUSTED (oop1)); PRIM_SUCCEEDED; } /* Object makeUntrusted: */ intptr_t VMpr_Object_makeUntrusted (int id, volatile int numArgs) #line 5149 "prims.def" { OOP oop1; OOP oop2; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = STACKTOP (); if (oop2 == _gst_true_oop) { MAKE_OOP_UNTRUSTED (oop1, true); PRIM_SUCCEEDED; } else if (oop2 == _gst_false_oop) { MAKE_OOP_UNTRUSTED (oop1, false); PRIM_SUCCEEDED; } UNPOP (1); PRIM_FAILED; } /* Object isReadOnly */ intptr_t VMpr_Object_isReadOnly (int id, volatile int numArgs) #line 5173 "prims.def" { OOP oop1; _gst_primitives_executed++; oop1 = STACKTOP (); SET_STACKTOP_BOOLEAN (IS_OOP_READONLY (oop1)); PRIM_SUCCEEDED; } /* Object makeReadOnly: */ intptr_t VMpr_Object_makeReadOnly (int id, volatile int numArgs) #line 5184 "prims.def" { OOP oop1; OOP oop2; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = STACKTOP (); if (IS_OOP (oop1)) { if (oop2 == _gst_true_oop) { MAKE_OOP_READONLY (oop1, true); PRIM_SUCCEEDED; } else if (oop2 == _gst_false_oop) { MAKE_OOP_READONLY (oop1, false); PRIM_SUCCEEDED; } } UNPOP (1); PRIM_FAILED; } /* Behavior primCompile: aString */ intptr_t VMpr_Behavior_primCompile (int id, volatile int numArgs) #line 5212 "prims.def" { OOP oop1; OOP oop2; mst_Boolean interrupted; _gst_primitives_executed++; oop2 = POP_OOP (); oop1 = POP_OOP (); if (IS_CLASS (oop2, _gst_string_class)) _gst_push_smalltalk_string (oop2); else _gst_push_stream_oop (oop2); _gst_set_compilation_class (oop1); _gst_set_compilation_category (_gst_string_new ("still unclassified")); interrupted = parse_stream_with_protection (true); _gst_pop_stream (true); PUSH_OOP (_gst_latest_compiled_method); if (interrupted) stop_execution (); PRIM_SUCCEEDED; } /* Behavior primCompile: aString ifError: aBlock */ intptr_t VMpr_Behavior_primCompileIfError (int id, volatile int numArgs) #line 5239 "prims.def" { OOP oop1; OOP oop2; OOP oop3; _gst_primitives_executed++; oop3 = POP_OOP (); oop2 = POP_OOP (); oop1 = POP_OOP (); if (IS_CLASS (oop3, _gst_block_closure_class)) { mst_Boolean oldReportErrors = _gst_report_errors; mst_Boolean interrupted; if (oldReportErrors) { /* only clear out these guys on first transition */ _gst_first_error_str = _gst_first_error_file = NULL; } _gst_report_errors = false; if (IS_CLASS (oop2, _gst_string_class)) _gst_push_smalltalk_string (oop2); else _gst_push_stream_oop (oop2); _gst_set_compilation_class (oop1); _gst_set_compilation_category (_gst_string_new ("still unclassified")); interrupted = parse_stream_with_protection (true); _gst_pop_stream (true); _gst_report_errors = oldReportErrors; PUSH_OOP (_gst_latest_compiled_method); if (interrupted) stop_execution (); else if (_gst_first_error_str != NULL) { SET_STACKTOP (oop3); /* block context */ if (_gst_first_error_file != NULL) { PUSH_OOP (_gst_string_new (_gst_first_error_file)); xfree (_gst_first_error_file); } else PUSH_OOP (_gst_nil_oop); PUSH_INT (_gst_first_error_line); PUSH_OOP (_gst_string_new (_gst_first_error_str)); xfree (_gst_first_error_str); _gst_first_error_str = _gst_first_error_file = NULL; _gst_report_errors = oldReportErrors; if (send_block_value (3, 3)) PRIM_FAILED; else PRIM_SUCCEEDED_RELOAD_IP; } PRIM_SUCCEEDED; } UNPOP (3); PRIM_FAILED; } /* CCallbackDescriptor link */ intptr_t VMpr_CCallbackDescriptor_link (int id, volatile int numArgs) #line 5304 "prims.def" { OOP oop1; _gst_primitives_executed++; oop1 = STACKTOP (); _gst_make_closure (oop1); /* Always fail so as to run the Smalltalk code that finishes the setup. */ PRIM_FAILED; } /* CFunctionDescriptor addressOf: funcNameString */ intptr_t VMpr_CFuncDescriptor_addressOf (int id, volatile int numArgs) #line 5317 "prims.def" { OOP oop1; _gst_primitives_executed++; oop1 = STACKTOP (); if (IS_CLASS (oop1, _gst_string_class)) { char *funcName = (char *) _gst_to_cstring (oop1); void *funcAddr = _gst_lookup_function (funcName); if (funcAddr) { POP_N_OOPS (1); SET_STACKTOP (COBJECT_NEW (funcAddr, _gst_nil_oop, _gst_c_object_class)); PRIM_SUCCEEDED; } } PRIM_FAILED; } /* Object snapshot: aString */ intptr_t VMpr_ObjectMemory_snapshot (int id, volatile int numArgs) #line 5340 "prims.def" { char *fileName; OOP oop2; interp_jmp_buf jb; _gst_primitives_executed++; oop2 = POP_OOP (); if (IS_CLASS (oop2, _gst_string_class)) { mst_Boolean success; fileName = _gst_to_cstring (oop2); errno = 0; /* first overwrite the stack top with true. When we resume from the save, the stack will be in this state. See below. */ SET_STACKTOP (_gst_true_oop); push_jmp_buf (&jb, false, get_active_process ()); if (setjmp (jb.jmpBuf) == 0) success = _gst_save_to_file (fileName); else { success = false; errno = EINTR; } xfree (fileName); if (pop_jmp_buf ()) { stop_execution (); PRIM_SUCCEEDED; } else if (success) { /* We're returning in the parent, not resuming from save. Overwite the stack top again, with false this time, to let the caller know which side of the fork we're on. */ SET_STACKTOP (_gst_false_oop); PRIM_SUCCEEDED; } else _gst_set_errno (errno); } UNPOP (1); PRIM_FAILED; } /* Object basicPrint */ intptr_t VMpr_Object_basicPrint (int id, volatile int numArgs) #line 5389 "prims.def" { _gst_primitives_executed++; printf ("Object: %O", STACKTOP ()); fflush (stdout); PRIM_SUCCEEDED; } /* Object makeWeak */ intptr_t VMpr_Object_makeWeak (int id, volatile int numArgs) #line 5398 "prims.def" { OOP oop1 = STACKTOP (); _gst_primitives_executed++; if (IS_INT (oop1)) PRIM_FAILED; if (!IS_OOP_WEAK (oop1)) _gst_make_oop_weak (oop1); PRIM_SUCCEEDED; } /* Stream fileInLine: lineNum fileName: aString at: charPosInt */ intptr_t VMpr_Stream_fileInLine (int id, volatile int numArgs) #line 5414 "prims.def" { OOP oop4 = POP_OOP (); OOP oop3 = POP_OOP (); OOP oop2 = (numArgs == 4 ? POP_OOP () : oop3); OOP oop1 = POP_OOP (); OOP streamOOP = STACKTOP (); enum undeclared_strategy old; if (!RECEIVER_IS_OOP (streamOOP)) PRIM_FAILED; if (IS_INT (oop1) && (IS_NIL (oop3) || (IS_CLASS (oop3, _gst_string_class) && IS_INT (oop4)))) { mst_Boolean interrupted; intptr_t arg1 = TO_INT (oop1); intptr_t arg4 = TO_INT (oop4); _gst_push_stream_oop (streamOOP); _gst_set_stream_info (arg1, oop2, oop3, arg4); old = _gst_set_undeclared (UNDECLARED_GLOBALS); interrupted = parse_stream_with_protection (false); _gst_set_undeclared (old); _gst_pop_stream (false); if (interrupted) stop_execution (); PRIM_SUCCEEDED; } PRIM_FAILED; } /* FileDescriptor>>#fileOp..., variadic */ intptr_t VMpr_FileDescriptor_fileOp (int id, volatile int numArgs) #line 5451 "prims.def" { char *fileName, *fileName2; gst_file_stream fileStream; int fd, rc; OOP oop1; OOP *oopVec = alloca (numArgs * sizeof (OOP)); int i; intptr_t arg1; OOP resultOOP; _gst_primitives_executed++; for (i = numArgs; --i >= 0;) oopVec[i] = POP_OOP (); resultOOP = oop1 = STACKTOP (); UNPOP (numArgs); if (!IS_INT (oopVec[0])) goto fail; arg1 = TO_INT (oopVec[0]); switch (arg1) { case PRIM_OPEN_FILE: case PRIM_OPEN_PIPE: { int is_pipe = false; char *fileMode = NULL; int access = 0; struct stat st; /* open: fileName[1] mode: mode[2] or popen: command[1] dir: direction[2] */ fileName = _gst_to_cstring (oopVec[1]); if (IS_INT (oopVec[2]) && arg1 == PRIM_OPEN_FILE) { fd = open ((char *) fileName, TO_INT (oopVec[2])); access = TO_INT (oopVec[2]) && (O_RDONLY | O_WRONLY | O_RDWR); } else if (!is_a_kind_of (OOP_CLASS (oopVec[1]), _gst_string_class)) fd = -1; else if (arg1 == PRIM_OPEN_FILE) { fileMode = _gst_to_cstring (oopVec[2]); fd = _gst_open_file ((char *) fileName, (char *) fileMode); memset (&st, 0, sizeof (st)); fstat (fd, &st); is_pipe = S_ISFIFO(st.st_mode) ? true : S_ISREG(st.st_mode) && st.st_size > 0 ? false : -1; } else { fileMode = _gst_to_cstring (oopVec[2]); fd = _gst_open_pipe (fileName, fileMode); is_pipe = true; } if (fileMode) { access = strchr (fileMode, '+') ? O_RDWR : (fileMode[0] == 'r') ? O_RDONLY : O_WRONLY; xfree (fileMode); } xfree (fileName); if (fd < 0) goto fail; _gst_set_file_stream_file (oop1, fd, oopVec[1], is_pipe, access, false); goto succeed; } case PRIM_MK_TEMP: fileName = _gst_to_cstring (oopVec[1]); asprintf (&fileName2, "%sXXXXXX", fileName); fd = mkstemp ((char *) fileName2); xfree (fileName); if (fd < 0) { xfree (fileName2); goto fail; } _gst_set_file_stream_file (oop1, fd, _gst_string_new (fileName2), false, O_RDWR, false); xfree (fileName2); goto succeed; } fileStream = (gst_file_stream) OOP_TO_OBJ (oop1); if (!IS_INT (fileStream->fd)) goto fail; fd = TO_INT (fileStream->fd); switch (arg1) { case PRIM_CLOSE_FILE: /* FileDescriptor close */ _gst_remove_fd_polling_handlers (fd); rc = close (fd); if (rc == 0) fileStream->fd = _gst_nil_oop; resultOOP = FROM_INT (rc); goto succeed; case PRIM_FSEEK_SET: /* FileDescriptor position: position */ if (IS_OFF_T (oopVec[1]) && lseek (fd, TO_OFF_T (oopVec[1]), SEEK_SET) < 0) { errno = 0; break; } else goto succeed; case PRIM_FTELL: /* FileDescriptor position */ { off_t off = lseek(fd, 0, SEEK_CUR); if (off < 0) { errno = 0; break; } resultOOP = FROM_OFF_T (off); goto succeed; } case PRIM_FEOF: { /* FileDescriptor atEnd */ off_t oldPos; oldPos = lseek (fd, 0, SEEK_CUR); if (oldPos >= 0 && lseek (fd, 0, SEEK_END) == oldPos) resultOOP = _gst_true_oop; else { resultOOP = _gst_false_oop; if (oldPos >= 0) lseek (fd, oldPos, SEEK_SET); } errno = 0; goto succeed; } case PRIM_FSIZE: { struct stat statBuf; if (fstat (fd, &statBuf) < 0) { errno = 0; break; } resultOOP = FROM_INT (statBuf.st_size); goto succeed; } case PRIM_PUT_CHARS: if (!IS_INT(oopVec[1]) && (OOP_INSTANCE_SPEC (oopVec[1]) & ISP_INDEXEDVARS) != GST_ISP_FIXED && _gst_log2_sizes[OOP_INSTANCE_SPEC (oopVec[1]) & ISP_SHAPE] == 0) { char *data = STRING_OOP_CHARS (oopVec[1]); intptr_t from = TO_INT (oopVec[2]); intptr_t to = TO_INT (oopVec[3]); ssize_t result; if (to >= from - 1 && from > 0 && to <= NUM_INDEXABLE_FIELDS (oopVec[1])) { result = _gst_write (fd, data + from - 1, to - from + 1); if (result != -1) { resultOOP = FROM_C_ULONG ((size_t) result); goto succeed; } } } break; case PRIM_GET_CHARS: /* only works for strings */ if (!IS_INT(oopVec[1]) && (OOP_INSTANCE_SPEC (oopVec[1]) & ISP_INDEXEDVARS) != GST_ISP_FIXED && _gst_log2_sizes[OOP_INSTANCE_SPEC (oopVec[1]) & ISP_SHAPE] == 0) { char *data = STRING_OOP_CHARS (oopVec[1]); intptr_t from = TO_INT (oopVec[2]); intptr_t to = TO_INT (oopVec[3]); ssize_t result; if (to >= from - 1 && from > 0 && to <= NUM_INDEXABLE_FIELDS (oopVec[1])) { /* Parameters to system calls are not guaranteed to generate a SIGSEGV and for this reason we must touch them manually. */ _gst_grey_oop_range (data + from - 1, to - from + 1); result = _gst_read (fd, data + from - 1, to - from + 1); if (result != -1) { resultOOP = FROM_C_ULONG ((size_t) result); goto succeed; } } } break; case PRIM_GET_CHARS_AT: if (!IS_INT(oopVec[1]) && (OOP_INSTANCE_SPEC (oopVec[1]) & ISP_INDEXEDVARS) != GST_ISP_FIXED && _gst_log2_sizes[OOP_INSTANCE_SPEC (oopVec[1]) & ISP_SHAPE] == 0 && IS_OFF_T (oopVec[4])) { char *data = STRING_OOP_CHARS (oopVec[1]); intptr_t from = TO_INT (oopVec[2]); intptr_t to = TO_INT (oopVec[3]); off_t ofs = TO_OFF_T (oopVec[4]); ssize_t result; if (to >= from - 1 && from > 0 && to <= NUM_INDEXABLE_FIELDS (oopVec[1])) { /* Parameters to system calls are not guaranteed to generate a SIGSEGV and for this reason we must touch them manually. */ _gst_grey_oop_range (data + from - 1, to - from + 1); #if HAVE_PREAD result = pread (fd, data + from - 1, to - from + 1, ofs); #else { off_t save = lseek (fd, ofs, SEEK_SET); if (save != -1) { result = _gst_read (fd, data + from - 1, to - from + 1); lseek (fd, save, SEEK_SET); } else result = -1; } #endif if (result != -1) { resultOOP = FROM_C_ULONG ((size_t) result); goto succeed; } } } break; case PRIM_PUT_CHARS_AT: if (!IS_INT(oopVec[1]) && (OOP_INSTANCE_SPEC (oopVec[1]) & ISP_INDEXEDVARS) != GST_ISP_FIXED && _gst_log2_sizes[OOP_INSTANCE_SPEC (oopVec[1]) & ISP_SHAPE] == 0 && IS_OFF_T (oopVec[4])) { char *data = STRING_OOP_CHARS (oopVec[1]); intptr_t from = TO_INT (oopVec[2]); intptr_t to = TO_INT (oopVec[3]); off_t ofs = TO_OFF_T (oopVec[4]); ssize_t result; if (to >= from - 1 && from > 0 && to <= NUM_INDEXABLE_FIELDS (oopVec[1])) { /* Parameters to system calls are not guaranteed to generate a SIGSEGV and for this reason we must touch them manually. */ _gst_grey_oop_range (data + from - 1, to - from + 1); #if HAVE_PWRITE result = pwrite (fd, data + from - 1, to - from + 1, ofs); #else { off_t save = lseek (fd, ofs, SEEK_SET); if (save != -1) { result = _gst_write (fd, data + from - 1, to - from + 1); lseek (fd, save, SEEK_SET); } else result = -1; } #endif if (result != -1) { resultOOP = FROM_C_ULONG ((size_t) result); goto succeed; } } } break; case PRIM_FTRUNCATE: { off_t pos; pos = lseek (fd, 0, SEEK_CUR); if (pos < 0) break; ftruncate (fd, pos); goto succeed; } case PRIM_FSEEK_CUR: /* FileDescriptor skip: */ if (IS_OFF_T (oopVec[1]) && lseek (fd, TO_OFF_T (oopVec[1]), SEEK_CUR) < 0) break; else goto succeed; case PRIM_SYNC_POLL: { int result; result = _gst_sync_file_polling (fd, TO_INT (oopVec[1])); if (result >= 0) { resultOOP = FROM_INT (result); goto succeed; } } break; case PRIM_ASYNC_POLL: { int result; result = _gst_async_file_polling (fd, TO_INT (oopVec[1]), oopVec[2]); if (result >= 0) goto succeed; } break; case PRIM_IS_PIPE: { off_t result; result = lseek (fd, 0, SEEK_END); if (result != -1) { lseek (fd, result, SEEK_SET); resultOOP = _gst_false_oop; goto succeed; } else if (errno == ESPIPE || errno == EINVAL) { resultOOP = _gst_true_oop; errno = 0; goto succeed; } goto fail; } case PRIM_SHUTDOWN_WRITE: shutdown (FD_TO_SOCKET (fd), 1); #ifdef ENOTSOCK if (errno == ENOTSOCK && isatty (fd)) { char buf[1]; write (fd, buf, 0); errno = 0; } #endif goto succeed; } fail: if (errno) _gst_set_errno (errno); PRIM_FAILED; succeed: POP_N_OOPS (numArgs); SET_STACKTOP (resultOOP); PRIM_SUCCEEDED; } /* FileDescriptor>>#socketOp..., socket version, variadic */ intptr_t VMpr_FileDescriptor_socketOp (int id, volatile int numArgs) #line 5841 "prims.def" { gst_file_stream fileStream; int fd, rc; OOP oop1, resultOOP; OOP *oopVec = alloca (numArgs * sizeof (OOP)); int i; intptr_t arg1; _gst_primitives_executed++; #ifdef HAVE_SOCKETS for (i = numArgs; --i >= 0;) oopVec[i] = POP_OOP (); resultOOP = oop1 = STACKTOP (); UNPOP (numArgs); if (!IS_INT (oopVec[0])) goto fail; arg1 = TO_INT (oopVec[0]); fileStream = (gst_file_stream) OOP_TO_OBJ (oop1); if (IS_NIL (fileStream->fd)) goto fail; fd = TO_INT (fileStream->fd); switch (arg1) { case PRIM_CLOSE_FILE: /* FileDescriptor close */ { int result; _gst_remove_fd_polling_handlers (fd); rc = close (fd); if (rc == 0) fileStream->fd = _gst_nil_oop; resultOOP = FROM_INT (rc); goto succeed; } case PRIM_PUT_CHARS: if (!IS_INT(oopVec[1]) && (OOP_INSTANCE_SPEC (oopVec[1]) & ISP_INDEXEDVARS) != GST_ISP_FIXED && _gst_log2_sizes[OOP_INSTANCE_SPEC (oopVec[1]) & ISP_SHAPE] == 0) { char *data = STRING_OOP_CHARS (oopVec[1]); intptr_t from = TO_INT (oopVec[2]); intptr_t to = TO_INT (oopVec[3]); ssize_t result; if (to >= from - 1 && from > 0 && to <= NUM_INDEXABLE_FIELDS (oopVec[1])) { clear_socket_error (); result = _gst_send (fd, data + from - 1, to - from + 1, 0); if (result != -1) { resultOOP = FROM_C_ULONG ((size_t) result); goto succeed; } } } break; case PRIM_GET_CHARS: /* only works for strings */ if (!IS_INT(oopVec[1]) && (OOP_INSTANCE_SPEC (oopVec[1]) & ISP_INDEXEDVARS) != GST_ISP_FIXED && _gst_log2_sizes[OOP_INSTANCE_SPEC (oopVec[1]) & ISP_SHAPE] == 0) { char *data = STRING_OOP_CHARS (oopVec[1]); intptr_t from = TO_INT (oopVec[2]); intptr_t to = TO_INT (oopVec[3]); ssize_t result; if (to >= from - 1 && from > 0 && to <= NUM_INDEXABLE_FIELDS (oopVec[1])) { /* Parameters to system calls are not guaranteed to generate a SIGSEGV and for this reason we must touch them manually. */ _gst_grey_oop_range (data + from - 1, to - from + 1); clear_socket_error (); result = _gst_recv (fd, data + from - 1, to - from + 1, 0); if (result != -1) { resultOOP = FROM_C_ULONG ((size_t) result); goto succeed; } } } break; case PRIM_SYNC_POLL: { int result; result = _gst_sync_file_polling (fd, TO_INT (oopVec[1])); if (result >= 0) { resultOOP = FROM_INT (result); goto succeed; } } break; case PRIM_ASYNC_POLL: { int result; result = _gst_async_file_polling (fd, TO_INT (oopVec[1]), oopVec[2]); if (result >= 0) goto succeed; } break; case PRIM_IS_PIPE: resultOOP =_gst_true_oop; goto succeed; break; } #endif fail: if (errno) _gst_set_errno (errno); PRIM_FAILED; succeed: POP_N_OOPS (numArgs); SET_STACKTOP (resultOOP); PRIM_SUCCEEDED; } /* C callout primitives. */ intptr_t VMpr_CFuncDescriptor_asyncCall (int id, volatile int numArgs) #line 5976 "prims.def" { OOP resultOOP; volatile gst_method_context context; OOP contextOOP, cFuncOOP, receiverOOP; interp_jmp_buf jb; _gst_primitives_executed++; if (numArgs == 1) { contextOOP = POP_OOP (); context = (gst_method_context) OOP_TO_OBJ (contextOOP); receiverOOP = context->receiver; } else { contextOOP = _gst_this_context_oop; context = (gst_method_context) OOP_TO_OBJ (contextOOP); receiverOOP = _gst_self; } cFuncOOP = STACKTOP (); push_jmp_buf (&jb, false, _gst_nil_oop); if (setjmp (jb.jmpBuf) == 0) resultOOP = _gst_invoke_croutine (cFuncOOP, receiverOOP, context->contextStack); else resultOOP = NULL; if (pop_jmp_buf ()) { stop_execution (); PRIM_SUCCEEDED; } else if (resultOOP) { SET_EXCEPT_FLAG (true); PRIM_SUCCEEDED; } if (numArgs == 1) UNPOP (1); PRIM_FAILED; } intptr_t VMpr_CFuncDescriptor_call (int id, volatile int numArgs) #line 6023 "prims.def" { volatile gst_method_context context; gst_object resultHolderObj; OOP receiverOOP, contextOOP, cFuncOOP, resultOOP; volatile OOP resultHolderOOP; interp_jmp_buf jb; _gst_primitives_executed++; resultHolderOOP = POP_OOP (); if (numArgs == 2) { contextOOP = POP_OOP (); context = (gst_method_context) OOP_TO_OBJ (contextOOP); receiverOOP = context->receiver; } else { contextOOP = _gst_this_context_oop; context = (gst_method_context) OOP_TO_OBJ (contextOOP); receiverOOP = _gst_self; } cFuncOOP = POP_OOP (); /* Make the result reachable, and also push it before the active process can change. */ PUSH_OOP (resultHolderOOP); push_jmp_buf (&jb, false, get_active_process ()); if (setjmp (jb.jmpBuf) == 0) resultOOP = _gst_invoke_croutine (cFuncOOP, receiverOOP, context->contextStack); else resultOOP = NULL; if (pop_jmp_buf ()) { stop_execution (); PRIM_SUCCEEDED; } else if (resultOOP) { if (!IS_NIL (resultHolderOOP)) { resultHolderObj = OOP_TO_OBJ (resultHolderOOP); resultHolderObj->data[0] = resultOOP; } SET_EXCEPT_FLAG (true); PRIM_SUCCEEDED; } /* Undo changes to the stack made above */ POP_N_OOPS (1); PUSH_OOP (cFuncOOP); if (numArgs == 2) PUSH_OOP (contextOOP); PUSH_OOP (resultHolderOOP); PRIM_FAILED; } intptr_t VMpr_Object_makeEphemeron (int id, volatile int numArgs) #line 6087 "prims.def" { _gst_primitives_executed++; if (NUM_OOPS (OOP_TO_OBJ (STACKTOP ())) == 0) PRIM_FAILED; MAKE_OOP_EPHEMERON (STACKTOP ()); PRIM_SUCCEEDED; } /* Namespace current: aNamespace */ intptr_t VMpr_Namespace_setCurrent (int id, volatile int numArgs) #line 6098 "prims.def" { OOP oop1; _gst_primitives_executed++; oop1 = STACKTOP (); if (is_a_kind_of (OOP_CLASS (oop1), _gst_dictionary_class)) _gst_current_namespace = oop1; else if (is_a_kind_of (OOP_CLASS (oop1), _gst_class_class)) _gst_current_namespace = _gst_class_variable_dictionary (oop1); /* Always fail */ PRIM_FAILED; } intptr_t VMpr_ObjectMemory_gcPrimitives (int id, volatile int numArgs) #line 6118 "prims.def" { _gst_primitives_executed++; switch (id) { case 0: _gst_scavenge (); break; case -1: _gst_global_compact (); break; case -2: _gst_global_gc (0); break; case -3: SET_STACKTOP_BOOLEAN (_gst_incremental_gc_step ()); break; case -4: _gst_finish_incremental_gc (); break; } PRIM_SUCCEEDED; } /* SystemDictionary profilerOn */ intptr_t VMpr_SystemDictionary_rawProfile (int id, volatile int numArgs) #line 6148 "prims.def" { OOP oop1 = POP_OOP (); if (_gst_raw_profile) { _gst_record_profile (_gst_this_method, NULL, -1); SET_STACKTOP (_gst_raw_profile); _gst_unregister_oop (_gst_raw_profile); } else SET_STACKTOP (_gst_nil_oop); if (IS_NIL (oop1)) _gst_raw_profile = NULL; else { _gst_raw_profile = oop1; _gst_register_oop (_gst_raw_profile); _gst_saved_bytecode_counter = _gst_bytecode_counter; } PRIM_SUCCEEDED; } #undef INT_BIN_OP #undef BOOL_BIN_OP intptr_t VMpr_HOLE (int id, volatile int numArgs) { _gst_primitives_executed++; _gst_errorf ("Unhandled primitive operation %d", id); UNPOP (numArgs); PRIM_FAILED; } unsigned char _gst_primitives_md5[16] = { 78, 223, 239, 67, 83, 13, 166, 89, 53, 6, 254, 212, 55, 193, 107, 135 }; void _gst_init_primitives() { int i; _gst_default_primitive_table[1].name = "VMpr_SmallInteger_plus"; _gst_default_primitive_table[1].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[1].id = 0; _gst_default_primitive_table[1].func = VMpr_SmallInteger_plus; _gst_default_primitive_table[2].name = "VMpr_SmallInteger_minus"; _gst_default_primitive_table[2].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[2].id = 0; _gst_default_primitive_table[2].func = VMpr_SmallInteger_minus; _gst_default_primitive_table[3].name = "VMpr_SmallInteger_lt"; _gst_default_primitive_table[3].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[3].id = 0; _gst_default_primitive_table[3].func = VMpr_SmallInteger_lt; _gst_default_primitive_table[4].name = "VMpr_SmallInteger_gt"; _gst_default_primitive_table[4].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[4].id = 0; _gst_default_primitive_table[4].func = VMpr_SmallInteger_gt; _gst_default_primitive_table[5].name = "VMpr_SmallInteger_le"; _gst_default_primitive_table[5].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[5].id = 0; _gst_default_primitive_table[5].func = VMpr_SmallInteger_le; _gst_default_primitive_table[6].name = "VMpr_SmallInteger_ge"; _gst_default_primitive_table[6].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[6].id = 0; _gst_default_primitive_table[6].func = VMpr_SmallInteger_ge; _gst_default_primitive_table[7].name = "VMpr_SmallInteger_eq"; _gst_default_primitive_table[7].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[7].id = 0; _gst_default_primitive_table[7].func = VMpr_SmallInteger_eq; _gst_default_primitive_table[8].name = "VMpr_SmallInteger_ne"; _gst_default_primitive_table[8].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[8].id = 0; _gst_default_primitive_table[8].func = VMpr_SmallInteger_ne; _gst_default_primitive_table[9].name = "VMpr_SmallInteger_times"; _gst_default_primitive_table[9].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[9].id = 0; _gst_default_primitive_table[9].func = VMpr_SmallInteger_times; _gst_default_primitive_table[10].name = "VMpr_SmallInteger_divide"; _gst_default_primitive_table[10].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[10].id = 0; _gst_default_primitive_table[10].func = VMpr_SmallInteger_divide; _gst_default_primitive_table[11].name = "VMpr_SmallInteger_modulo"; _gst_default_primitive_table[11].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[11].id = 0; _gst_default_primitive_table[11].func = VMpr_SmallInteger_modulo; _gst_default_primitive_table[12].name = "VMpr_SmallInteger_intDiv"; _gst_default_primitive_table[12].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[12].id = 0; _gst_default_primitive_table[12].func = VMpr_SmallInteger_intDiv; _gst_default_primitive_table[13].name = "VMpr_SmallInteger_quo"; _gst_default_primitive_table[13].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[13].id = 0; _gst_default_primitive_table[13].func = VMpr_SmallInteger_quo; _gst_default_primitive_table[14].name = "VMpr_SmallInteger_bitAnd"; _gst_default_primitive_table[14].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[14].id = 0; _gst_default_primitive_table[14].func = VMpr_SmallInteger_bitAnd; _gst_default_primitive_table[15].name = "VMpr_SmallInteger_bitOr"; _gst_default_primitive_table[15].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[15].id = 0; _gst_default_primitive_table[15].func = VMpr_SmallInteger_bitOr; _gst_default_primitive_table[16].name = "VMpr_SmallInteger_bitXor"; _gst_default_primitive_table[16].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[16].id = 0; _gst_default_primitive_table[16].func = VMpr_SmallInteger_bitXor; _gst_default_primitive_table[17].name = "VMpr_SmallInteger_bitShift"; _gst_default_primitive_table[17].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[17].id = 0; _gst_default_primitive_table[17].func = VMpr_SmallInteger_bitShift; _gst_default_primitive_table[18].name = "VMpr_SmallInteger_scramble"; _gst_default_primitive_table[18].attributes = PRIM_CHECKS_RECEIVER; _gst_default_primitive_table[18].id = 0; _gst_default_primitive_table[18].func = VMpr_SmallInteger_scramble; _gst_default_primitive_table[19].name = "VMpr_SmallInteger_asFloatD"; _gst_default_primitive_table[19].attributes = PRIM_CHECKS_RECEIVER; _gst_default_primitive_table[19].id = 0; _gst_default_primitive_table[19].func = VMpr_SmallInteger_asFloatD; _gst_default_primitive_table[20].name = "VMpr_SmallInteger_asFloatE"; _gst_default_primitive_table[20].attributes = PRIM_CHECKS_RECEIVER; _gst_default_primitive_table[20].id = 0; _gst_default_primitive_table[20].func = VMpr_SmallInteger_asFloatE; _gst_default_primitive_table[21].name = "VMpr_SmallInteger_asFloatQ"; _gst_default_primitive_table[21].attributes = PRIM_CHECKS_RECEIVER; _gst_default_primitive_table[21].id = 0; _gst_default_primitive_table[21].func = VMpr_SmallInteger_asFloatQ; _gst_default_primitive_table[22].name = "VMpr_LargeInteger_eq"; _gst_default_primitive_table[22].attributes = PRIM_USES_GMP; _gst_default_primitive_table[22].id = 0; _gst_default_primitive_table[22].func = VMpr_LargeInteger_eq; _gst_default_primitive_table[23].name = "VMpr_LargeInteger_ne"; _gst_default_primitive_table[23].attributes = PRIM_USES_GMP; _gst_default_primitive_table[23].id = 0; _gst_default_primitive_table[23].func = VMpr_LargeInteger_ne; _gst_default_primitive_table[24].name = "VMpr_LargeInteger_lt"; _gst_default_primitive_table[24].attributes = PRIM_USES_GMP; _gst_default_primitive_table[24].id = 0; _gst_default_primitive_table[24].func = VMpr_LargeInteger_lt; _gst_default_primitive_table[25].name = "VMpr_LargeInteger_le"; _gst_default_primitive_table[25].attributes = PRIM_USES_GMP; _gst_default_primitive_table[25].id = 0; _gst_default_primitive_table[25].func = VMpr_LargeInteger_le; _gst_default_primitive_table[26].name = "VMpr_LargeInteger_gt"; _gst_default_primitive_table[26].attributes = PRIM_USES_GMP; _gst_default_primitive_table[26].id = 0; _gst_default_primitive_table[26].func = VMpr_LargeInteger_gt; _gst_default_primitive_table[27].name = "VMpr_LargeInteger_ge"; _gst_default_primitive_table[27].attributes = PRIM_USES_GMP; _gst_default_primitive_table[27].id = 0; _gst_default_primitive_table[27].func = VMpr_LargeInteger_ge; _gst_default_primitive_table[28].name = "VMpr_LargeInteger_times"; _gst_default_primitive_table[28].attributes = PRIM_USES_GMP; _gst_default_primitive_table[28].id = 0; _gst_default_primitive_table[28].func = VMpr_LargeInteger_times; _gst_default_primitive_table[29].name = "VMpr_LargeInteger_intDiv"; _gst_default_primitive_table[29].attributes = PRIM_USES_GMP; _gst_default_primitive_table[29].id = 0; _gst_default_primitive_table[29].func = VMpr_LargeInteger_intDiv; _gst_default_primitive_table[30].name = "VMpr_LargeInteger_modulo"; _gst_default_primitive_table[30].attributes = PRIM_USES_GMP; _gst_default_primitive_table[30].id = 0; _gst_default_primitive_table[30].func = VMpr_LargeInteger_modulo; _gst_default_primitive_table[31].name = "VMpr_LargeInteger_divExact"; _gst_default_primitive_table[31].attributes = PRIM_USES_GMP; _gst_default_primitive_table[31].id = 0; _gst_default_primitive_table[31].func = VMpr_LargeInteger_divExact; _gst_default_primitive_table[32].name = "VMpr_LargeInteger_quo"; _gst_default_primitive_table[32].attributes = PRIM_USES_GMP; _gst_default_primitive_table[32].id = 0; _gst_default_primitive_table[32].func = VMpr_LargeInteger_quo; _gst_default_primitive_table[33].name = "VMpr_LargeInteger_rem"; _gst_default_primitive_table[33].attributes = PRIM_USES_GMP; _gst_default_primitive_table[33].id = 0; _gst_default_primitive_table[33].func = VMpr_LargeInteger_rem; _gst_default_primitive_table[34].name = "VMpr_LargeInteger_negated"; _gst_default_primitive_table[34].attributes = PRIM_USES_GMP; _gst_default_primitive_table[34].id = 0; _gst_default_primitive_table[34].func = VMpr_LargeInteger_negated; _gst_default_primitive_table[35].name = "VMpr_LargeInteger_bitAnd"; _gst_default_primitive_table[35].attributes = PRIM_USES_GMP; _gst_default_primitive_table[35].id = 0; _gst_default_primitive_table[35].func = VMpr_LargeInteger_bitAnd; _gst_default_primitive_table[36].name = "VMpr_LargeInteger_bitOr"; _gst_default_primitive_table[36].attributes = PRIM_USES_GMP; _gst_default_primitive_table[36].id = 0; _gst_default_primitive_table[36].func = VMpr_LargeInteger_bitOr; _gst_default_primitive_table[37].name = "VMpr_LargeInteger_bitXor"; _gst_default_primitive_table[37].attributes = PRIM_USES_GMP; _gst_default_primitive_table[37].id = 0; _gst_default_primitive_table[37].func = VMpr_LargeInteger_bitXor; _gst_default_primitive_table[38].name = "VMpr_LargeInteger_bitInvert"; _gst_default_primitive_table[38].attributes = PRIM_USES_GMP; _gst_default_primitive_table[38].id = 0; _gst_default_primitive_table[38].func = VMpr_LargeInteger_bitInvert; _gst_default_primitive_table[39].name = "VMpr_LargeInteger_bitShift"; _gst_default_primitive_table[39].attributes = PRIM_USES_GMP; _gst_default_primitive_table[39].id = 0; _gst_default_primitive_table[39].func = VMpr_LargeInteger_bitShift; _gst_default_primitive_table[40].name = "VMpr_LargeInteger_plus"; _gst_default_primitive_table[40].attributes = PRIM_USES_GMP; _gst_default_primitive_table[40].id = 0; _gst_default_primitive_table[40].func = VMpr_LargeInteger_plus; _gst_default_primitive_table[41].name = "VMpr_LargeInteger_minus"; _gst_default_primitive_table[41].attributes = PRIM_USES_GMP; _gst_default_primitive_table[41].id = 0; _gst_default_primitive_table[41].func = VMpr_LargeInteger_minus; _gst_default_primitive_table[42].name = "VMpr_LargeInteger_gcd"; _gst_default_primitive_table[42].attributes = PRIM_USES_GMP; _gst_default_primitive_table[42].id = 0; _gst_default_primitive_table[42].func = VMpr_LargeInteger_gcd; _gst_default_primitive_table[43].name = "VMpr_LargeInteger_asFloatD"; _gst_default_primitive_table[43].attributes = PRIM_USES_GMP; _gst_default_primitive_table[43].id = 0; _gst_default_primitive_table[43].func = VMpr_LargeInteger_asFloatD; _gst_default_primitive_table[44].name = "VMpr_LargeInteger_asFloatE"; _gst_default_primitive_table[44].attributes = PRIM_USES_GMP; _gst_default_primitive_table[44].id = 0; _gst_default_primitive_table[44].func = VMpr_LargeInteger_asFloatE; _gst_default_primitive_table[45].name = "VMpr_LargeInteger_asFloatQ"; _gst_default_primitive_table[45].attributes = PRIM_USES_GMP; _gst_default_primitive_table[45].id = 0; _gst_default_primitive_table[45].func = VMpr_LargeInteger_asFloatQ; _gst_default_primitive_table[46].name = "VMpr_FloatD_plus"; _gst_default_primitive_table[46].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[46].id = 0; _gst_default_primitive_table[46].func = VMpr_FloatD_arith; _gst_default_primitive_table[47].name = "VMpr_FloatD_minus"; _gst_default_primitive_table[47].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[47].id = -1; _gst_default_primitive_table[47].func = VMpr_FloatD_arith; _gst_default_primitive_table[48].name = "VMpr_FloatD_lt"; _gst_default_primitive_table[48].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[48].id = -2; _gst_default_primitive_table[48].func = VMpr_FloatD_arith; _gst_default_primitive_table[49].name = "VMpr_FloatD_gt"; _gst_default_primitive_table[49].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[49].id = -3; _gst_default_primitive_table[49].func = VMpr_FloatD_arith; _gst_default_primitive_table[50].name = "VMpr_FloatD_le"; _gst_default_primitive_table[50].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[50].id = -4; _gst_default_primitive_table[50].func = VMpr_FloatD_arith; _gst_default_primitive_table[51].name = "VMpr_FloatD_ge"; _gst_default_primitive_table[51].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[51].id = -5; _gst_default_primitive_table[51].func = VMpr_FloatD_arith; _gst_default_primitive_table[52].name = "VMpr_FloatD_eq"; _gst_default_primitive_table[52].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[52].id = -6; _gst_default_primitive_table[52].func = VMpr_FloatD_arith; _gst_default_primitive_table[53].name = "VMpr_FloatD_ne"; _gst_default_primitive_table[53].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[53].id = -7; _gst_default_primitive_table[53].func = VMpr_FloatD_arith; _gst_default_primitive_table[54].name = "VMpr_FloatD_times"; _gst_default_primitive_table[54].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[54].id = -8; _gst_default_primitive_table[54].func = VMpr_FloatD_arith; _gst_default_primitive_table[55].name = "VMpr_FloatD_divide"; _gst_default_primitive_table[55].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[55].id = -9; _gst_default_primitive_table[55].func = VMpr_FloatD_arith; _gst_default_primitive_table[56].name = "VMpr_FloatD_truncated"; _gst_default_primitive_table[56].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[56].id = 0; _gst_default_primitive_table[56].func = VMpr_FloatD_truncated; _gst_default_primitive_table[57].name = "VMpr_FloatD_fractionPart"; _gst_default_primitive_table[57].attributes = PRIM_CHECKS_RECEIVER; _gst_default_primitive_table[57].id = 0; _gst_default_primitive_table[57].func = VMpr_FloatD_fractionPart; _gst_default_primitive_table[58].name = "VMpr_FloatD_exponent"; _gst_default_primitive_table[58].attributes = PRIM_CHECKS_RECEIVER | PRIM_RETURN_SMALL_SMALLINTEGER; _gst_default_primitive_table[58].id = 0; _gst_default_primitive_table[58].func = VMpr_FloatD_exponent; _gst_default_primitive_table[59].name = "VMpr_FloatD_timesTwoPower"; _gst_default_primitive_table[59].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[59].id = 0; _gst_default_primitive_table[59].func = VMpr_FloatD_timesTwoPower; _gst_default_primitive_table[60].name = "VMpr_FloatD_asFloatE"; _gst_default_primitive_table[60].attributes = PRIM_CHECKS_RECEIVER; _gst_default_primitive_table[60].id = 0; _gst_default_primitive_table[60].func = VMpr_FloatD_asFloatE; _gst_default_primitive_table[61].name = "VMpr_FloatD_asFloatQ"; _gst_default_primitive_table[61].attributes = PRIM_CHECKS_RECEIVER; _gst_default_primitive_table[61].id = 0; _gst_default_primitive_table[61].func = VMpr_FloatD_asFloatQ; _gst_default_primitive_table[62].name = "VMpr_FloatE_plus"; _gst_default_primitive_table[62].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[62].id = 0; _gst_default_primitive_table[62].func = VMpr_FloatE_arith; _gst_default_primitive_table[63].name = "VMpr_FloatE_minus"; _gst_default_primitive_table[63].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[63].id = -1; _gst_default_primitive_table[63].func = VMpr_FloatE_arith; _gst_default_primitive_table[64].name = "VMpr_FloatE_lt"; _gst_default_primitive_table[64].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[64].id = -2; _gst_default_primitive_table[64].func = VMpr_FloatE_arith; _gst_default_primitive_table[65].name = "VMpr_FloatE_gt"; _gst_default_primitive_table[65].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[65].id = -3; _gst_default_primitive_table[65].func = VMpr_FloatE_arith; _gst_default_primitive_table[66].name = "VMpr_FloatE_le"; _gst_default_primitive_table[66].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[66].id = -4; _gst_default_primitive_table[66].func = VMpr_FloatE_arith; _gst_default_primitive_table[67].name = "VMpr_FloatE_ge"; _gst_default_primitive_table[67].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[67].id = -5; _gst_default_primitive_table[67].func = VMpr_FloatE_arith; _gst_default_primitive_table[68].name = "VMpr_FloatE_eq"; _gst_default_primitive_table[68].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[68].id = -6; _gst_default_primitive_table[68].func = VMpr_FloatE_arith; _gst_default_primitive_table[69].name = "VMpr_FloatE_ne"; _gst_default_primitive_table[69].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[69].id = -7; _gst_default_primitive_table[69].func = VMpr_FloatE_arith; _gst_default_primitive_table[70].name = "VMpr_FloatE_times"; _gst_default_primitive_table[70].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[70].id = -8; _gst_default_primitive_table[70].func = VMpr_FloatE_arith; _gst_default_primitive_table[71].name = "VMpr_FloatE_divide"; _gst_default_primitive_table[71].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[71].id = -9; _gst_default_primitive_table[71].func = VMpr_FloatE_arith; _gst_default_primitive_table[72].name = "VMpr_FloatE_truncated"; _gst_default_primitive_table[72].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[72].id = 0; _gst_default_primitive_table[72].func = VMpr_FloatE_truncated; _gst_default_primitive_table[73].name = "VMpr_FloatE_fractionPart"; _gst_default_primitive_table[73].attributes = PRIM_CHECKS_RECEIVER; _gst_default_primitive_table[73].id = 0; _gst_default_primitive_table[73].func = VMpr_FloatE_fractionPart; _gst_default_primitive_table[74].name = "VMpr_FloatE_exponent"; _gst_default_primitive_table[74].attributes = PRIM_CHECKS_RECEIVER | PRIM_RETURN_SMALL_SMALLINTEGER; _gst_default_primitive_table[74].id = 0; _gst_default_primitive_table[74].func = VMpr_FloatE_exponent; _gst_default_primitive_table[75].name = "VMpr_FloatE_timesTwoPower"; _gst_default_primitive_table[75].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[75].id = 0; _gst_default_primitive_table[75].func = VMpr_FloatE_timesTwoPower; _gst_default_primitive_table[76].name = "VMpr_FloatE_asFloatD"; _gst_default_primitive_table[76].attributes = PRIM_CHECKS_RECEIVER; _gst_default_primitive_table[76].id = 0; _gst_default_primitive_table[76].func = VMpr_FloatE_asFloatD; _gst_default_primitive_table[77].name = "VMpr_FloatE_asFloatQ"; _gst_default_primitive_table[77].attributes = PRIM_CHECKS_RECEIVER; _gst_default_primitive_table[77].id = 0; _gst_default_primitive_table[77].func = VMpr_FloatE_asFloatQ; _gst_default_primitive_table[78].name = "VMpr_FloatQ_plus"; _gst_default_primitive_table[78].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[78].id = 0; _gst_default_primitive_table[78].func = VMpr_FloatQ_arith; _gst_default_primitive_table[79].name = "VMpr_FloatQ_minus"; _gst_default_primitive_table[79].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[79].id = -1; _gst_default_primitive_table[79].func = VMpr_FloatQ_arith; _gst_default_primitive_table[80].name = "VMpr_FloatQ_lt"; _gst_default_primitive_table[80].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[80].id = -2; _gst_default_primitive_table[80].func = VMpr_FloatQ_arith; _gst_default_primitive_table[81].name = "VMpr_FloatQ_gt"; _gst_default_primitive_table[81].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[81].id = -3; _gst_default_primitive_table[81].func = VMpr_FloatQ_arith; _gst_default_primitive_table[82].name = "VMpr_FloatQ_le"; _gst_default_primitive_table[82].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[82].id = -4; _gst_default_primitive_table[82].func = VMpr_FloatQ_arith; _gst_default_primitive_table[83].name = "VMpr_FloatQ_ge"; _gst_default_primitive_table[83].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[83].id = -5; _gst_default_primitive_table[83].func = VMpr_FloatQ_arith; _gst_default_primitive_table[84].name = "VMpr_FloatQ_eq"; _gst_default_primitive_table[84].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[84].id = -6; _gst_default_primitive_table[84].func = VMpr_FloatQ_arith; _gst_default_primitive_table[85].name = "VMpr_FloatQ_ne"; _gst_default_primitive_table[85].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[85].id = -7; _gst_default_primitive_table[85].func = VMpr_FloatQ_arith; _gst_default_primitive_table[86].name = "VMpr_FloatQ_times"; _gst_default_primitive_table[86].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[86].id = -8; _gst_default_primitive_table[86].func = VMpr_FloatQ_arith; _gst_default_primitive_table[87].name = "VMpr_FloatQ_divide"; _gst_default_primitive_table[87].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[87].id = -9; _gst_default_primitive_table[87].func = VMpr_FloatQ_arith; _gst_default_primitive_table[88].name = "VMpr_FloatQ_truncated"; _gst_default_primitive_table[88].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[88].id = 0; _gst_default_primitive_table[88].func = VMpr_FloatQ_truncated; _gst_default_primitive_table[89].name = "VMpr_FloatQ_fractionPart"; _gst_default_primitive_table[89].attributes = PRIM_CHECKS_RECEIVER; _gst_default_primitive_table[89].id = 0; _gst_default_primitive_table[89].func = VMpr_FloatQ_fractionPart; _gst_default_primitive_table[90].name = "VMpr_FloatQ_exponent"; _gst_default_primitive_table[90].attributes = PRIM_CHECKS_RECEIVER | PRIM_RETURN_SMALL_SMALLINTEGER; _gst_default_primitive_table[90].id = 0; _gst_default_primitive_table[90].func = VMpr_FloatQ_exponent; _gst_default_primitive_table[91].name = "VMpr_FloatQ_timesTwoPower"; _gst_default_primitive_table[91].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[91].id = 0; _gst_default_primitive_table[91].func = VMpr_FloatQ_timesTwoPower; _gst_default_primitive_table[92].name = "VMpr_FloatQ_asFloatD"; _gst_default_primitive_table[92].attributes = PRIM_CHECKS_RECEIVER; _gst_default_primitive_table[92].id = 0; _gst_default_primitive_table[92].func = VMpr_FloatQ_asFloatD; _gst_default_primitive_table[93].name = "VMpr_FloatQ_asFloatE"; _gst_default_primitive_table[93].attributes = PRIM_CHECKS_RECEIVER; _gst_default_primitive_table[93].id = 0; _gst_default_primitive_table[93].func = VMpr_FloatQ_asFloatE; _gst_default_primitive_table[94].name = "VMpr_Object_basicAt"; _gst_default_primitive_table[94].attributes = PRIM_SUCCEED | PRIM_FAIL | PRIM_INLINED; _gst_default_primitive_table[94].id = 60; _gst_default_primitive_table[94].func = VMpr_Object_basicAt; _gst_default_primitive_table[95].name = "VMpr_Object_basicAtPut"; _gst_default_primitive_table[95].attributes = PRIM_SUCCEED | PRIM_FAIL | PRIM_INLINED; _gst_default_primitive_table[95].id = 61; _gst_default_primitive_table[95].func = VMpr_Object_basicAtPut; _gst_default_primitive_table[96].name = "VMpr_Object_basicSize"; _gst_default_primitive_table[96].attributes = PRIM_SUCCEED | PRIM_RETURN_SMALL_SMALLINTEGER | PRIM_INLINED; _gst_default_primitive_table[96].id = 62; _gst_default_primitive_table[96].func = VMpr_Object_basicSize; _gst_default_primitive_table[97].name = "VMpr_CharacterArray_valueAt"; _gst_default_primitive_table[97].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[97].id = 60; _gst_default_primitive_table[97].func = VMpr_CharacterArray_valueAt; _gst_default_primitive_table[98].name = "VMpr_CharacterArray_valueAtPut"; _gst_default_primitive_table[98].attributes = PRIM_SUCCEED | PRIM_FAIL | PRIM_INLINED; _gst_default_primitive_table[98].id = 61; _gst_default_primitive_table[98].func = VMpr_CharacterArray_valueAtPut; _gst_default_primitive_table[99].name = "VMpr_CompiledCode_verificationResult"; _gst_default_primitive_table[99].attributes = PRIM_SUCCEED; _gst_default_primitive_table[99].id = 0; _gst_default_primitive_table[99].func = VMpr_CompiledCode_verificationResult; _gst_default_primitive_table[100].name = "VMpr_CompiledBlock_create"; _gst_default_primitive_table[100].attributes = PRIM_SUCCEED; _gst_default_primitive_table[100].id = 0; _gst_default_primitive_table[100].func = VMpr_CompiledBlock_create; _gst_default_primitive_table[101].name = "VMpr_CompiledMethod_create"; _gst_default_primitive_table[101].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[101].id = 0; _gst_default_primitive_table[101].func = VMpr_CompiledMethod_create; _gst_default_primitive_table[102].name = "VMpr_Object_shallowCopy"; _gst_default_primitive_table[102].attributes = PRIM_SUCCEED; _gst_default_primitive_table[102].id = 0; _gst_default_primitive_table[102].func = VMpr_Object_shallowCopy; _gst_default_primitive_table[103].name = "VMpr_Behavior_basicNew"; _gst_default_primitive_table[103].attributes = PRIM_SUCCEED | PRIM_FAIL | PRIM_INLINED; _gst_default_primitive_table[103].id = 70; _gst_default_primitive_table[103].func = VMpr_Behavior_basicNew; _gst_default_primitive_table[104].name = "VMpr_Behavior_basicNewColon"; _gst_default_primitive_table[104].attributes = PRIM_SUCCEED | PRIM_FAIL | PRIM_INLINED; _gst_default_primitive_table[104].id = 71; _gst_default_primitive_table[104].func = VMpr_Behavior_basicNewColon; _gst_default_primitive_table[105].name = "VMpr_Object_become"; _gst_default_primitive_table[105].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[105].id = 0; _gst_default_primitive_table[105].func = VMpr_Object_become; _gst_default_primitive_table[106].name = "VMpr_Object_instVarAt"; _gst_default_primitive_table[106].attributes = PRIM_SUCCEED | PRIM_FAIL | PRIM_INLINED; _gst_default_primitive_table[106].id = 73; _gst_default_primitive_table[106].func = VMpr_Object_instVarAt; _gst_default_primitive_table[107].name = "VMpr_Object_instVarAtPut"; _gst_default_primitive_table[107].attributes = PRIM_SUCCEED | PRIM_FAIL | PRIM_INLINED; _gst_default_primitive_table[107].id = 74; _gst_default_primitive_table[107].func = VMpr_Object_instVarAtPut; _gst_default_primitive_table[108].name = "VMpr_Object_hash"; _gst_default_primitive_table[108].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[108].id = 0; _gst_default_primitive_table[108].func = VMpr_Object_hash; _gst_default_primitive_table[109].name = "VMpr_SmallInteger_asObject"; _gst_default_primitive_table[109].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[109].id = 0; _gst_default_primitive_table[109].func = VMpr_SmallInteger_asObject; _gst_default_primitive_table[110].name = "VMpr_SmallInteger_nextValidOop"; _gst_default_primitive_table[110].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[110].id = 0; _gst_default_primitive_table[110].func = VMpr_SmallInteger_nextValidOop; _gst_default_primitive_table[111].name = "VMpr_Behavior_someInstance"; _gst_default_primitive_table[111].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[111].id = 0; _gst_default_primitive_table[111].func = VMpr_Behavior_someInstance; _gst_default_primitive_table[112].name = "VMpr_Object_nextInstance"; _gst_default_primitive_table[112].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[112].id = 0; _gst_default_primitive_table[112].func = VMpr_Object_nextInstance; _gst_default_primitive_table[113].name = "VMpr_Object_becomeForward"; _gst_default_primitive_table[113].attributes = PRIM_SUCCEED; _gst_default_primitive_table[113].id = 0; _gst_default_primitive_table[113].func = VMpr_Object_becomeForward; _gst_default_primitive_table[114].name = "VMpr_Object_allOwners"; _gst_default_primitive_table[114].attributes = PRIM_SUCCEED; _gst_default_primitive_table[114].id = 0; _gst_default_primitive_table[114].func = VMpr_Object_allOwners; _gst_default_primitive_table[115].name = "VMpr_ContextPart_thisContext"; _gst_default_primitive_table[115].attributes = PRIM_SUCCEED; _gst_default_primitive_table[115].id = 0; _gst_default_primitive_table[115].func = VMpr_ContextPart_thisContext; _gst_default_primitive_table[116].name = "VMpr_ContextPart_continue"; _gst_default_primitive_table[116].attributes = PRIM_CHECKS_RECEIVER | PRIM_RELOAD_IP; _gst_default_primitive_table[116].id = 0; _gst_default_primitive_table[116].func = VMpr_ContextPart_continue; _gst_default_primitive_table[117].name = "VMpr_Continuation_resume"; _gst_default_primitive_table[117].attributes = PRIM_FAIL | PRIM_RELOAD_IP; _gst_default_primitive_table[117].id = 0; _gst_default_primitive_table[117].func = VMpr_Continuation_resume; _gst_default_primitive_table[118].name = "VMpr_BlockClosure_value"; _gst_default_primitive_table[118].attributes = PRIM_FAIL | PRIM_RELOAD_IP | PRIM_CACHE_NEW_IP; _gst_default_primitive_table[118].id = 0; _gst_default_primitive_table[118].func = VMpr_BlockClosure_value; _gst_default_primitive_table[119].name = "VMpr_BlockClosure_cull"; _gst_default_primitive_table[119].attributes = PRIM_FAIL | PRIM_RELOAD_IP; _gst_default_primitive_table[119].id = 0; _gst_default_primitive_table[119].func = VMpr_BlockClosure_cull; _gst_default_primitive_table[120].name = "VMpr_BlockClosure_valueAndResumeOnUnwind"; _gst_default_primitive_table[120].attributes = PRIM_FAIL | PRIM_RELOAD_IP; _gst_default_primitive_table[120].id = 0; _gst_default_primitive_table[120].func = VMpr_BlockClosure_valueAndResumeOnUnwind; _gst_default_primitive_table[121].name = "VMpr_BlockClosure_valueWithArguments"; _gst_default_primitive_table[121].attributes = PRIM_FAIL | PRIM_RELOAD_IP; _gst_default_primitive_table[121].id = 0; _gst_default_primitive_table[121].func = VMpr_BlockClosure_valueWithArguments; _gst_default_primitive_table[122].name = "VMpr_Object_perform"; _gst_default_primitive_table[122].attributes = PRIM_FAIL | PRIM_RELOAD_IP; _gst_default_primitive_table[122].id = 0; _gst_default_primitive_table[122].func = VMpr_Object_perform; _gst_default_primitive_table[123].name = "VMpr_Object_performWithArguments"; _gst_default_primitive_table[123].attributes = PRIM_FAIL | PRIM_RELOAD_IP; _gst_default_primitive_table[123].id = 0; _gst_default_primitive_table[123].func = VMpr_Object_performWithArguments; _gst_default_primitive_table[124].name = "VMpr_Semaphore_notifyAll"; _gst_default_primitive_table[124].attributes = PRIM_SUCCEED | PRIM_CHECK_INTERRUPT; _gst_default_primitive_table[124].id = 0; _gst_default_primitive_table[124].func = VMpr_Semaphore_notifyAll; _gst_default_primitive_table[125].name = "VMpr_Semaphore_signal"; _gst_default_primitive_table[125].attributes = PRIM_SUCCEED | PRIM_CHECK_INTERRUPT; _gst_default_primitive_table[125].id = 0; _gst_default_primitive_table[125].func = VMpr_Semaphore_signalNotify; _gst_default_primitive_table[126].name = "VMpr_Semaphore_notify"; _gst_default_primitive_table[126].attributes = PRIM_SUCCEED | PRIM_CHECK_INTERRUPT; _gst_default_primitive_table[126].id = -1; _gst_default_primitive_table[126].func = VMpr_Semaphore_signalNotify; _gst_default_primitive_table[127].name = "VMpr_Semaphore_lock"; _gst_default_primitive_table[127].attributes = PRIM_SUCCEED | PRIM_CHECK_INTERRUPT; _gst_default_primitive_table[127].id = 0; _gst_default_primitive_table[127].func = VMpr_Semaphore_lock; _gst_default_primitive_table[128].name = "VMpr_Semaphore_wait"; _gst_default_primitive_table[128].attributes = PRIM_SUCCEED | PRIM_CHECK_INTERRUPT; _gst_default_primitive_table[128].id = 0; _gst_default_primitive_table[128].func = VMpr_Semaphore_wait; _gst_default_primitive_table[129].name = "VMpr_Semaphore_waitAfterSignalling"; _gst_default_primitive_table[129].attributes = PRIM_SUCCEED | PRIM_CHECK_INTERRUPT; _gst_default_primitive_table[129].id = 0; _gst_default_primitive_table[129].func = VMpr_Semaphore_waitAfterSignalling; _gst_default_primitive_table[130].name = "VMpr_Process_suspend"; _gst_default_primitive_table[130].attributes = PRIM_SUCCEED | PRIM_CHECK_INTERRUPT; _gst_default_primitive_table[130].id = 0; _gst_default_primitive_table[130].func = VMpr_Process_suspend; _gst_default_primitive_table[131].name = "VMpr_Process_resume"; _gst_default_primitive_table[131].attributes = PRIM_SUCCEED | PRIM_FAIL | PRIM_CHECK_INTERRUPT; _gst_default_primitive_table[131].id = 0; _gst_default_primitive_table[131].func = VMpr_Process_resume; _gst_default_primitive_table[132].name = "VMpr_Process_singleStepWaitingOn"; _gst_default_primitive_table[132].attributes = PRIM_SUCCEED; _gst_default_primitive_table[132].id = 0; _gst_default_primitive_table[132].func = VMpr_Process_singleStepWaitingOn; _gst_default_primitive_table[133].name = "VMpr_Process_yield"; _gst_default_primitive_table[133].attributes = PRIM_SUCCEED | PRIM_CHECK_INTERRUPT; _gst_default_primitive_table[133].id = 0; _gst_default_primitive_table[133].func = VMpr_Process_yield; _gst_default_primitive_table[134].name = "VMpr_Processor_pause"; _gst_default_primitive_table[134].attributes = PRIM_SUCCEED | PRIM_CHECK_INTERRUPT; _gst_default_primitive_table[134].id = 0; _gst_default_primitive_table[134].func = VMpr_Processor_pause; _gst_default_primitive_table[135].name = "VMpr_Behavior_flushCache"; _gst_default_primitive_table[135].attributes = PRIM_SUCCEED; _gst_default_primitive_table[135].id = 0; _gst_default_primitive_table[135].func = VMpr_Behavior_flushCache; _gst_default_primitive_table[136].name = "VMpr_CompiledCode_discardTranslation"; _gst_default_primitive_table[136].attributes = PRIM_SUCCEED; _gst_default_primitive_table[136].id = 0; _gst_default_primitive_table[136].func = VMpr_CompiledCode_discardTranslation; _gst_default_primitive_table[137].name = "VMpr_Object_changeClassTo"; _gst_default_primitive_table[137].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[137].id = 0; _gst_default_primitive_table[137].func = VMpr_Object_changeClassTo; _gst_default_primitive_table[138].name = "VMpr_Time_timezoneBias"; _gst_default_primitive_table[138].attributes = PRIM_SUCCEED; _gst_default_primitive_table[138].id = 0; _gst_default_primitive_table[138].func = VMpr_Time_timezoneBias; _gst_default_primitive_table[139].name = "VMpr_Time_timezone"; _gst_default_primitive_table[139].attributes = PRIM_SUCCEED; _gst_default_primitive_table[139].id = 0; _gst_default_primitive_table[139].func = VMpr_Time_timezone; _gst_default_primitive_table[140].name = "VMpr_Time_secondClock"; _gst_default_primitive_table[140].attributes = PRIM_SUCCEED; _gst_default_primitive_table[140].id = 0; _gst_default_primitive_table[140].func = VMpr_Time_secondClock; _gst_default_primitive_table[141].name = "VMpr_Time_nanosecondClock"; _gst_default_primitive_table[141].attributes = PRIM_SUCCEED; _gst_default_primitive_table[141].id = 0; _gst_default_primitive_table[141].func = VMpr_Time_nanosecondClock; _gst_default_primitive_table[142].name = "VMpr_Time_millisecondClock"; _gst_default_primitive_table[142].attributes = PRIM_SUCCEED; _gst_default_primitive_table[142].id = 0; _gst_default_primitive_table[142].func = VMpr_Time_millisecondClock; _gst_default_primitive_table[143].name = "VMpr_Processor_signalAtMilliseconds"; _gst_default_primitive_table[143].attributes = PRIM_SUCCEED | PRIM_FAIL | PRIM_CHECK_INTERRUPT; _gst_default_primitive_table[143].id = 0; _gst_default_primitive_table[143].func = VMpr_Processor_signalAt; _gst_default_primitive_table[144].name = "VMpr_Processor_signalAtNanosecondClockValue"; _gst_default_primitive_table[144].attributes = PRIM_SUCCEED | PRIM_FAIL | PRIM_CHECK_INTERRUPT; _gst_default_primitive_table[144].id = -1; _gst_default_primitive_table[144].func = VMpr_Processor_signalAt; _gst_default_primitive_table[145].name = "VMpr_Processor_isTimeoutProgrammed"; _gst_default_primitive_table[145].attributes = PRIM_SUCCEED; _gst_default_primitive_table[145].id = 0; _gst_default_primitive_table[145].func = VMpr_Processor_isTimeoutProgrammed; _gst_default_primitive_table[146].name = "VMpr_String_similarityTo"; _gst_default_primitive_table[146].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[146].id = 0; _gst_default_primitive_table[146].func = VMpr_String_similarityTo; _gst_default_primitive_table[147].name = "VMpr_String_hash"; _gst_default_primitive_table[147].attributes = PRIM_CHECKS_RECEIVER; _gst_default_primitive_table[147].id = 0; _gst_default_primitive_table[147].func = VMpr_String_hash; _gst_default_primitive_table[148].name = "VMpr_ArrayedCollection_equal"; _gst_default_primitive_table[148].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[148].id = 0; _gst_default_primitive_table[148].func = VMpr_ArrayedCollection_equal; _gst_default_primitive_table[149].name = "VMpr_ArrayedCollection_indexOfStartingAt"; _gst_default_primitive_table[149].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[149].id = 0; _gst_default_primitive_table[149].func = VMpr_ArrayedCollection_indexOfStartingAt; _gst_default_primitive_table[150].name = "VMpr_ArrayedCollection_replaceFromToWithStartingAt"; _gst_default_primitive_table[150].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[150].id = 0; _gst_default_primitive_table[150].func = VMpr_ArrayedCollection_replaceFromToWithStartingAt; _gst_default_primitive_table[151].name = "VMpr_Object_identity"; _gst_default_primitive_table[151].attributes = PRIM_SUCCEED | PRIM_INLINED; _gst_default_primitive_table[151].id = 110; _gst_default_primitive_table[151].func = VMpr_Object_identity; _gst_default_primitive_table[152].name = "VMpr_Object_class"; _gst_default_primitive_table[152].attributes = PRIM_SUCCEED; _gst_default_primitive_table[152].id = 111; _gst_default_primitive_table[152].func = VMpr_Object_class; _gst_default_primitive_table[153].name = "VMpr_ObjectMemory_quit"; _gst_default_primitive_table[153].attributes = PRIM_FAIL; _gst_default_primitive_table[153].id = 0; _gst_default_primitive_table[153].func = VMpr_ObjectMemory_quit; _gst_default_primitive_table[154].name = "VMpr_ObjectMemory_abort"; _gst_default_primitive_table[154].attributes = PRIM_FAIL; _gst_default_primitive_table[154].id = 0; _gst_default_primitive_table[154].func = VMpr_ObjectMemory_abort; _gst_default_primitive_table[155].name = "VMpr_Dictionary_at"; _gst_default_primitive_table[155].attributes = PRIM_SUCCEED; _gst_default_primitive_table[155].id = 0; _gst_default_primitive_table[155].func = VMpr_Dictionary_at; _gst_default_primitive_table[156].name = "VMpr_Object_bootstrapError"; _gst_default_primitive_table[156].attributes = PRIM_SUCCEED; _gst_default_primitive_table[156].id = 0; _gst_default_primitive_table[156].func = VMpr_Object_bootstrapException; _gst_default_primitive_table[157].name = "VMpr_Object_bootstrapDNU"; _gst_default_primitive_table[157].attributes = PRIM_SUCCEED; _gst_default_primitive_table[157].id = -1; _gst_default_primitive_table[157].func = VMpr_Object_bootstrapException; _gst_default_primitive_table[158].name = "VMpr_Character_create"; _gst_default_primitive_table[158].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[158].id = 0; _gst_default_primitive_table[158].func = VMpr_Character_create; _gst_default_primitive_table[159].name = "VMpr_UnicodeCharacter_create"; _gst_default_primitive_table[159].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[159].id = 0; _gst_default_primitive_table[159].func = VMpr_UnicodeCharacter_create; _gst_default_primitive_table[160].name = "VMpr_Character_equal"; _gst_default_primitive_table[160].attributes = PRIM_SUCCEED; _gst_default_primitive_table[160].id = 0; _gst_default_primitive_table[160].func = VMpr_Character_equal; _gst_default_primitive_table[161].name = "VMpr_Symbol_intern"; _gst_default_primitive_table[161].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[161].id = 0; _gst_default_primitive_table[161].func = VMpr_Symbol_intern; _gst_default_primitive_table[162].name = "VMpr_Dictionary_new"; _gst_default_primitive_table[162].attributes = PRIM_SUCCEED; _gst_default_primitive_table[162].id = 0; _gst_default_primitive_table[162].func = VMpr_Dictionary_new; _gst_default_primitive_table[163].name = "VMpr_Memory_addressOfOOP"; _gst_default_primitive_table[163].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[163].id = 0; _gst_default_primitive_table[163].func = VMpr_Memory_addressOfOOP; _gst_default_primitive_table[164].name = "VMpr_Memory_addressOf"; _gst_default_primitive_table[164].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[164].id = 0; _gst_default_primitive_table[164].func = VMpr_Memory_addressOf; _gst_default_primitive_table[165].name = "VMpr_SystemDictionary_backtrace"; _gst_default_primitive_table[165].attributes = PRIM_SUCCEED; _gst_default_primitive_table[165].id = 0; _gst_default_primitive_table[165].func = VMpr_SystemDictionary_backtrace; _gst_default_primitive_table[166].name = "VMpr_SystemDictionary_getTraceFlag"; _gst_default_primitive_table[166].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[166].id = 0; _gst_default_primitive_table[166].func = VMpr_SystemDictionary_getTraceFlag; _gst_default_primitive_table[167].name = "VMpr_SystemDictionary_setTraceFlag"; _gst_default_primitive_table[167].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[167].id = 0; _gst_default_primitive_table[167].func = VMpr_SystemDictionary_setTraceFlag; _gst_default_primitive_table[168].name = "VMpr_Memory_at"; _gst_default_primitive_table[168].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[168].id = 0; _gst_default_primitive_table[168].func = VMpr_Memory_at; _gst_default_primitive_table[169].name = "VMpr_Memory_atPut"; _gst_default_primitive_table[169].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[169].id = 0; _gst_default_primitive_table[169].func = VMpr_Memory_atPut; _gst_default_primitive_table[170].name = "VMpr_Behavior_methodsFor"; _gst_default_primitive_table[170].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[170].id = 0; _gst_default_primitive_table[170].func = VMpr_Behavior_methodsFor; _gst_default_primitive_table[171].name = "VMpr_Behavior_methodsForIfTrue"; _gst_default_primitive_table[171].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[171].id = 0; _gst_default_primitive_table[171].func = VMpr_Behavior_methodsForIfTrue; _gst_default_primitive_table[172].name = "VMpr_Processor_disableInterrupts"; _gst_default_primitive_table[172].attributes = PRIM_SUCCEED; _gst_default_primitive_table[172].id = 0; _gst_default_primitive_table[172].func = VMpr_Processor_disableEnableInterrupts; _gst_default_primitive_table[173].name = "VMpr_Processor_enableInterrupts"; _gst_default_primitive_table[173].attributes = PRIM_SUCCEED; _gst_default_primitive_table[173].id = -1; _gst_default_primitive_table[173].func = VMpr_Processor_disableEnableInterrupts; _gst_default_primitive_table[174].name = "VMpr_Processor_signalOnInterrupt"; _gst_default_primitive_table[174].attributes = PRIM_SUCCEED | PRIM_FAIL | PRIM_CHECK_INTERRUPT; _gst_default_primitive_table[174].id = 0; _gst_default_primitive_table[174].func = VMpr_Processor_signalOnInterrupt; _gst_default_primitive_table[175].name = "VMpr_ObjectMemory_getSpaceGrowRate"; _gst_default_primitive_table[175].attributes = PRIM_SUCCEED; _gst_default_primitive_table[175].id = 0; _gst_default_primitive_table[175].func = VMpr_ObjectMemory_getSpaceGrowRate; _gst_default_primitive_table[176].name = "VMpr_ObjectMemory_setSpaceGrowRate"; _gst_default_primitive_table[176].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[176].id = 0; _gst_default_primitive_table[176].func = VMpr_ObjectMemory_setSpaceGrowRate; _gst_default_primitive_table[177].name = "VMpr_ObjectMemory_getSmoothingFactor"; _gst_default_primitive_table[177].attributes = PRIM_SUCCEED; _gst_default_primitive_table[177].id = 0; _gst_default_primitive_table[177].func = VMpr_ObjectMemory_getSmoothingFactor; _gst_default_primitive_table[178].name = "VMpr_ObjectMemory_setSmoothingFactor"; _gst_default_primitive_table[178].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[178].id = 0; _gst_default_primitive_table[178].func = VMpr_ObjectMemory_setSmoothingFactor; _gst_default_primitive_table[179].name = "VMpr_ObjectMemory_getGrowThresholdPercent"; _gst_default_primitive_table[179].attributes = PRIM_SUCCEED; _gst_default_primitive_table[179].id = 0; _gst_default_primitive_table[179].func = VMpr_ObjectMemory_getGrowThresholdPercent; _gst_default_primitive_table[180].name = "VMpr_ObjectMemory_setGrowThresholdPercent"; _gst_default_primitive_table[180].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[180].id = 0; _gst_default_primitive_table[180].func = VMpr_ObjectMemory_setGrowThresholdPercent; _gst_default_primitive_table[181].name = "VMpr_ObjectMemory_getBigObjectThreshold"; _gst_default_primitive_table[181].attributes = PRIM_SUCCEED; _gst_default_primitive_table[181].id = 0; _gst_default_primitive_table[181].func = VMpr_ObjectMemory_getBigObjectThreshold; _gst_default_primitive_table[182].name = "VMpr_ObjectMemory_setBigObjectThreshold"; _gst_default_primitive_table[182].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[182].id = 0; _gst_default_primitive_table[182].func = VMpr_ObjectMemory_setBigObjectThreshold; _gst_default_primitive_table[183].name = "VMpr_ObjectMemory_growTo"; _gst_default_primitive_table[183].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[183].id = 0; _gst_default_primitive_table[183].func = VMpr_ObjectMemory_growTo; _gst_default_primitive_table[184].name = "VMpr_ObjectMemory_update"; _gst_default_primitive_table[184].attributes = PRIM_CHECKS_RECEIVER; _gst_default_primitive_table[184].id = 0; _gst_default_primitive_table[184].func = VMpr_ObjectMemory_update; _gst_default_primitive_table[185].name = "VMpr_CObject_allocType"; _gst_default_primitive_table[185].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[185].id = 0; _gst_default_primitive_table[185].func = VMpr_CObject_allocType; _gst_default_primitive_table[186].name = "VMpr_Float_sin"; _gst_default_primitive_table[186].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[186].id = 0; _gst_default_primitive_table[186].func = VMpr_Float_sin; _gst_default_primitive_table[187].name = "VMpr_Float_cos"; _gst_default_primitive_table[187].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[187].id = 0; _gst_default_primitive_table[187].func = VMpr_Float_cos; _gst_default_primitive_table[188].name = "VMpr_Float_tan"; _gst_default_primitive_table[188].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[188].id = 0; _gst_default_primitive_table[188].func = VMpr_Float_tan; _gst_default_primitive_table[189].name = "VMpr_Float_arcSin"; _gst_default_primitive_table[189].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[189].id = 0; _gst_default_primitive_table[189].func = VMpr_Float_arcSin; _gst_default_primitive_table[190].name = "VMpr_Float_arcCos"; _gst_default_primitive_table[190].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[190].id = 0; _gst_default_primitive_table[190].func = VMpr_Float_arcCos; _gst_default_primitive_table[191].name = "VMpr_Float_arcTan"; _gst_default_primitive_table[191].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[191].id = 0; _gst_default_primitive_table[191].func = VMpr_Float_arcTan; _gst_default_primitive_table[192].name = "VMpr_Float_exp"; _gst_default_primitive_table[192].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[192].id = 0; _gst_default_primitive_table[192].func = VMpr_Float_exp; _gst_default_primitive_table[193].name = "VMpr_Float_ln"; _gst_default_primitive_table[193].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[193].id = 0; _gst_default_primitive_table[193].func = VMpr_Float_ln; _gst_default_primitive_table[194].name = "VMpr_Float_pow"; _gst_default_primitive_table[194].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[194].id = 0; _gst_default_primitive_table[194].func = VMpr_Float_pow; _gst_default_primitive_table[195].name = "VMpr_CObject_free"; _gst_default_primitive_table[195].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[195].id = 0; _gst_default_primitive_table[195].func = VMpr_CObject_free; _gst_default_primitive_table[196].name = "VMpr_Float_sqrt"; _gst_default_primitive_table[196].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[196].id = 0; _gst_default_primitive_table[196].func = VMpr_Float_sqrt; _gst_default_primitive_table[197].name = "VMpr_Float_ceil"; _gst_default_primitive_table[197].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[197].id = 0; _gst_default_primitive_table[197].func = VMpr_Float_ceil_floor; _gst_default_primitive_table[198].name = "VMpr_Float_floor"; _gst_default_primitive_table[198].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[198].id = -1; _gst_default_primitive_table[198].func = VMpr_Float_ceil_floor; _gst_default_primitive_table[199].name = "VMpr_Behavior_basicNewFixed"; _gst_default_primitive_table[199].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[199].id = 0; _gst_default_primitive_table[199].func = VMpr_Behavior_basicNewFixed; _gst_default_primitive_table[200].name = "VMpr_Behavior_basicNewFixedColon"; _gst_default_primitive_table[200].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[200].id = 0; _gst_default_primitive_table[200].func = VMpr_Behavior_basicNewFixedColon; _gst_default_primitive_table[201].name = "VMpr_Object_tenure"; _gst_default_primitive_table[201].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[201].id = 0; _gst_default_primitive_table[201].func = VMpr_Object_tenure; _gst_default_primitive_table[202].name = "VMpr_Object_makeFixed"; _gst_default_primitive_table[202].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[202].id = 0; _gst_default_primitive_table[202].func = VMpr_Object_makeFixed; _gst_default_primitive_table[203].name = "VMpr_CObject_derefAt"; _gst_default_primitive_table[203].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[203].id = 0; _gst_default_primitive_table[203].func = VMpr_CObject_at; _gst_default_primitive_table[204].name = "VMpr_CObject_at"; _gst_default_primitive_table[204].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[204].id = -1; _gst_default_primitive_table[204].func = VMpr_CObject_at; _gst_default_primitive_table[205].name = "VMpr_CObject_atPut"; _gst_default_primitive_table[205].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[205].id = 0; _gst_default_primitive_table[205].func = VMpr_CObject_atPut; _gst_default_primitive_table[206].name = "VMpr_CObject_address"; _gst_default_primitive_table[206].attributes = PRIM_SUCCEED; _gst_default_primitive_table[206].id = 0; _gst_default_primitive_table[206].func = VMpr_CObject_address; _gst_default_primitive_table[207].name = "VMpr_CObject_addressColon"; _gst_default_primitive_table[207].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[207].id = 0; _gst_default_primitive_table[207].func = VMpr_CObject_addressColon; _gst_default_primitive_table[208].name = "VMpr_CString_replaceWith"; _gst_default_primitive_table[208].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[208].id = 0; _gst_default_primitive_table[208].func = VMpr_CString_replaceWith; _gst_default_primitive_table[209].name = "VMpr_ByteArray_fromCData_size"; _gst_default_primitive_table[209].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[209].id = 0; _gst_default_primitive_table[209].func = VMpr_ByteArray_fromCData_size; _gst_default_primitive_table[210].name = "VMpr_String_fromCData_size"; _gst_default_primitive_table[210].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[210].id = 0; _gst_default_primitive_table[210].func = VMpr_String_fromCData_size; _gst_default_primitive_table[211].name = "VMpr_String_fromCData"; _gst_default_primitive_table[211].attributes = PRIM_SUCCEED; _gst_default_primitive_table[211].id = 0; _gst_default_primitive_table[211].func = VMpr_String_fromCData; _gst_default_primitive_table[212].name = "VMpr_String_asCData"; _gst_default_primitive_table[212].attributes = PRIM_CHECKS_RECEIVER; _gst_default_primitive_table[212].id = 0; _gst_default_primitive_table[212].func = VMpr_String_ByteArray_asCData; _gst_default_primitive_table[213].name = "VMpr_ByteArray_asCData"; _gst_default_primitive_table[213].attributes = PRIM_CHECKS_RECEIVER; _gst_default_primitive_table[213].id = -1; _gst_default_primitive_table[213].func = VMpr_String_ByteArray_asCData; _gst_default_primitive_table[214].name = "VMpr_SystemDictionary_byteCodeCounter"; _gst_default_primitive_table[214].attributes = PRIM_SUCCEED; _gst_default_primitive_table[214].id = 0; _gst_default_primitive_table[214].func = VMpr_SystemDictionary_byteCodeCounter; _gst_default_primitive_table[215].name = "VMpr_SystemDictionary_debug"; _gst_default_primitive_table[215].attributes = PRIM_SUCCEED; _gst_default_primitive_table[215].id = 0; _gst_default_primitive_table[215].func = VMpr_SystemDictionary_debug; _gst_default_primitive_table[216].name = "VMpr_Object_isUntrusted"; _gst_default_primitive_table[216].attributes = PRIM_SUCCEED; _gst_default_primitive_table[216].id = 0; _gst_default_primitive_table[216].func = VMpr_Object_isUntrusted; _gst_default_primitive_table[217].name = "VMpr_Object_makeUntrusted"; _gst_default_primitive_table[217].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[217].id = 0; _gst_default_primitive_table[217].func = VMpr_Object_makeUntrusted; _gst_default_primitive_table[218].name = "VMpr_Object_isReadOnly"; _gst_default_primitive_table[218].attributes = PRIM_SUCCEED; _gst_default_primitive_table[218].id = 0; _gst_default_primitive_table[218].func = VMpr_Object_isReadOnly; _gst_default_primitive_table[219].name = "VMpr_Object_makeReadOnly"; _gst_default_primitive_table[219].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[219].id = 0; _gst_default_primitive_table[219].func = VMpr_Object_makeReadOnly; _gst_default_primitive_table[220].name = "VMpr_Behavior_primCompile"; _gst_default_primitive_table[220].attributes = PRIM_SUCCEED; _gst_default_primitive_table[220].id = 0; _gst_default_primitive_table[220].func = VMpr_Behavior_primCompile; _gst_default_primitive_table[221].name = "VMpr_Behavior_primCompileIfError"; _gst_default_primitive_table[221].attributes = PRIM_FAIL | PRIM_SUCCEED | PRIM_RELOAD_IP; _gst_default_primitive_table[221].id = 0; _gst_default_primitive_table[221].func = VMpr_Behavior_primCompileIfError; _gst_default_primitive_table[222].name = "VMpr_CCallbackDescriptor_link"; _gst_default_primitive_table[222].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[222].id = 0; _gst_default_primitive_table[222].func = VMpr_CCallbackDescriptor_link; _gst_default_primitive_table[223].name = "VMpr_CFuncDescriptor_addressOf"; _gst_default_primitive_table[223].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[223].id = 0; _gst_default_primitive_table[223].func = VMpr_CFuncDescriptor_addressOf; _gst_default_primitive_table[224].name = "VMpr_ObjectMemory_snapshot"; _gst_default_primitive_table[224].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[224].id = 0; _gst_default_primitive_table[224].func = VMpr_ObjectMemory_snapshot; _gst_default_primitive_table[225].name = "VMpr_Object_basicPrint"; _gst_default_primitive_table[225].attributes = PRIM_SUCCEED; _gst_default_primitive_table[225].id = 0; _gst_default_primitive_table[225].func = VMpr_Object_basicPrint; _gst_default_primitive_table[226].name = "VMpr_Object_makeWeak"; _gst_default_primitive_table[226].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[226].id = 0; _gst_default_primitive_table[226].func = VMpr_Object_makeWeak; _gst_default_primitive_table[227].name = "VMpr_Stream_fileInLine"; _gst_default_primitive_table[227].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[227].id = 0; _gst_default_primitive_table[227].func = VMpr_Stream_fileInLine; _gst_default_primitive_table[228].name = "VMpr_FileDescriptor_fileOp"; _gst_default_primitive_table[228].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[228].id = 0; _gst_default_primitive_table[228].func = VMpr_FileDescriptor_fileOp; _gst_default_primitive_table[229].name = "VMpr_FileDescriptor_socketOp"; _gst_default_primitive_table[229].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[229].id = 0; _gst_default_primitive_table[229].func = VMpr_FileDescriptor_socketOp; _gst_default_primitive_table[230].name = "VMpr_CFuncDescriptor_asyncCall"; _gst_default_primitive_table[230].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[230].id = 0; _gst_default_primitive_table[230].func = VMpr_CFuncDescriptor_asyncCall; _gst_default_primitive_table[231].name = "VMpr_CFuncDescriptor_call"; _gst_default_primitive_table[231].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[231].id = 0; _gst_default_primitive_table[231].func = VMpr_CFuncDescriptor_call; _gst_default_primitive_table[232].name = "VMpr_Object_makeEphemeron"; _gst_default_primitive_table[232].attributes = PRIM_SUCCEED | PRIM_FAIL; _gst_default_primitive_table[232].id = 0; _gst_default_primitive_table[232].func = VMpr_Object_makeEphemeron; _gst_default_primitive_table[233].name = "VMpr_Namespace_setCurrent"; _gst_default_primitive_table[233].attributes = PRIM_FAIL; _gst_default_primitive_table[233].id = 0; _gst_default_primitive_table[233].func = VMpr_Namespace_setCurrent; _gst_default_primitive_table[234].name = "VMpr_ObjectMemory_scavenge"; _gst_default_primitive_table[234].attributes = PRIM_SUCCEED; _gst_default_primitive_table[234].id = 0; _gst_default_primitive_table[234].func = VMpr_ObjectMemory_gcPrimitives; _gst_default_primitive_table[235].name = "VMpr_ObjectMemory_compact"; _gst_default_primitive_table[235].attributes = PRIM_SUCCEED; _gst_default_primitive_table[235].id = -1; _gst_default_primitive_table[235].func = VMpr_ObjectMemory_gcPrimitives; _gst_default_primitive_table[236].name = "VMpr_ObjectMemory_globalGarbageCollect"; _gst_default_primitive_table[236].attributes = PRIM_SUCCEED; _gst_default_primitive_table[236].id = -2; _gst_default_primitive_table[236].func = VMpr_ObjectMemory_gcPrimitives; _gst_default_primitive_table[237].name = "VMpr_ObjectMemory_incrementalGCStep"; _gst_default_primitive_table[237].attributes = PRIM_SUCCEED; _gst_default_primitive_table[237].id = -3; _gst_default_primitive_table[237].func = VMpr_ObjectMemory_gcPrimitives; _gst_default_primitive_table[238].name = "VMpr_ObjectMemory_finishIncrementalGC"; _gst_default_primitive_table[238].attributes = PRIM_SUCCEED; _gst_default_primitive_table[238].id = -4; _gst_default_primitive_table[238].func = VMpr_ObjectMemory_gcPrimitives; _gst_default_primitive_table[239].name = "VMpr_SystemDictionary_rawProfile"; _gst_default_primitive_table[239].attributes = PRIM_SUCCEED; _gst_default_primitive_table[239].id = 0; _gst_default_primitive_table[239].func = VMpr_SystemDictionary_rawProfile; for (i = 240; i < NUM_PRIMITIVES; i++) { _gst_default_primitive_table[i].name = NULL; _gst_default_primitive_table[i].attributes = PRIM_FAIL; _gst_default_primitive_table[i].id = i; _gst_default_primitive_table[i].func = VMpr_HOLE; } } smalltalk-3.2.5/libgst/md-config.h0000644000175000017500000001265312123404352013731 00000000000000/******************************** -*- C -*- **************************** * * Definitions to squeeze out every % of speed * ***********************************************************************/ /*********************************************************************** * * Copyright 2000, 2001, 2002, 2006 Free Software Foundation, Inc. * Written by Paolo Bonzini. * * This file is part of GNU Smalltalk. * * GNU Smalltalk is free software; you can redistribute it and/or modify it * under the terms of the GNU General Public License as published by the Free * Software Foundation; either version 2, or (at your option) any later * version. * * Linking GNU Smalltalk statically or dynamically with other modules is * making a combined work based on GNU Smalltalk. Thus, the terms and * conditions of the GNU General Public License cover the whole * combination. * * In addition, as a special exception, the Free Software Foundation * give you permission to combine GNU Smalltalk with free software * programs or libraries that are released under the GNU LGPL and with * independent programs running under the GNU Smalltalk virtual machine. * * You may copy and distribute such a system following the terms of the * GNU GPL for GNU Smalltalk and the licenses of the other code * concerned, provided that you include the source code of that other * code when and as the GNU GPL requires distribution of source code. * * Note that people who make modified versions of GNU Smalltalk are not * obligated to grant this special exception for their modified * versions; it is their choice whether to do so. The GNU General * Public License gives permission to release a modified version without * this exception; this exception also makes it possible to release a * modified version which carries forward this exception. * * GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or * FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for * more details. * * You should have received a copy of the GNU General Public License along with * GNU Smalltalk; see the file COPYING. If not, write to the Free Software * Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * */ #ifndef GST_MD_CONFIG_H #define GST_MD_CONFIG_H #if defined(__mips__) # define REG_AVAILABILITY 2 # define __DECL_REG1 __asm("$16") # define __DECL_REG2 __asm("$17") # define __DECL_REG3 __asm("$18") #endif #if !defined(__DECL_REG1) && defined(__sparc__) # define REG_AVAILABILITY 1 # define __DECL_REG1 __asm("%l0") # define __DECL_REG2 __asm("%l1") # define __DECL_REG3 __asm("%l2") #endif #if !defined(__DECL_REG1) && defined(__alpha__) # define REG_AVAILABILITY 2 /* Note: REG3 causes compile problems when trying to fit 64-bit stuff in * registers. */ # ifdef __CRAY__ # define __DECL_REG1 __asm("r9") # define __DECL_REG2 __asm("r10") # define __DECL_REG3 /* __asm("r11") */ # else # define __DECL_REG1 __asm("$9") # define __DECL_REG2 __asm("$10") # define __DECL_REG3 /* __asm("$11") */ # endif # define L1_CACHE_SHIFT 6 #endif #if !defined(__DECL_REG1) && defined(__i386__) # define REG_AVAILABILITY 0 # define __DECL_REG1 __asm("%esi") # define __DECL_REG2 __asm("%edi") # define __DECL_REG3 /* no more caller-save regs if PIC is in use! */ #endif #if !defined(__DECL_REG1) && defined(__x86_64__) # define REG_AVAILABILITY 1 # define __DECL_REG1 __asm("%r12") # define __DECL_REG2 __asm("%r13") # define __DECL_REG3 __asm("%rbx") # define L1_CACHE_SHIFT 6 #endif #if !defined(__DECL_REG1) && defined(PPC) || defined(_POWER) || defined(_IBMR2) # define REG_AVAILABILITY 2 # define __DECL_REG1 __asm("26") # define __DECL_REG2 __asm("27") # define __DECL_REG3 __asm("28") #endif #if !defined(__DECL_REG1) && defined(__hppa__) # define REG_AVAILABILITY 2 # define __DECL_REG1 __asm("%r16") # define __DECL_REG2 __asm("%r17") # define __DECL_REG3 __asm("%r18") #endif #if !defined(__DECL_REG1) && defined(__mc68000__) /* Has lots of registers, but REG_AVAILABILITY == 1 currently * helps on RISC machines only. Things might change however. */ # define REG_AVAILABILITY 0 # define __DECL_REG1 __asm("a5") # define __DECL_REG2 __asm("a4") # define __DECL_REG3 __asm("d7") # define L1_CACHE_SHIFT 4 #endif #if defined(__ia64) && defined(__GNUC__) # define REG_AVAILABILITY 3 # define BRANCH_REGISTER(name) register void *name __asm("b4") # define L1_CACHE_SHIFT 7 #endif #if defined(__s390__) # define REG_AVAILABILITY 2 # define L1_CACHE_SHIFT 7 #endif /* Define a way to align cache-sensitive data on the proper boundaries */ #ifndef L1_CACHE_SHIFT # define L1_CACHE_SHIFT 5 #endif #if defined(__GNUC__) # define CACHELINE_ALIGNED __attribute__((__aligned__(1 << L1_CACHE_SHIFT))) #else # define CACHELINE_ALIGNED #endif /* Some compilers underestimate the use of the local variables and and don't put them in hardware registers, or (especially) do unneeded spills and reloads. This slows down the interpreter considerably. For GCC, this provides the ability to hand-assign hardware registers for several common architectures. */ #ifndef REG_AVAILABILITY # define REG_AVAILABILITY 1 #endif #if !defined(__GNUC__) || !defined(__DECL_REG1) || !defined(__OPTIMIZE__) # define REGISTER(reg, decl) register decl #else # define __DECL_REG(k) k # define REGISTER(reg, decl) register decl __DECL_REG(__DECL_REG##reg) #endif #endif /* GST_MD_CONFIG_H */ smalltalk-3.2.5/libgst/interp-jit.inl0000644000175000017500000004016312123404352014503 00000000000000/******************************** -*- C -*- **************************** * * Interpreter employing a bytecode->native code translator. * * ***********************************************************************/ /*********************************************************************** * * Copyright 2001, 2002, 2003, 2004, 2006, 2008 Free Software Foundation, Inc. * Written by Paolo Bonzini. * * This file is part of GNU Smalltalk. * * GNU Smalltalk is free software; you can redistribute it and/or modify it * under the terms of the GNU General Public License as published by the Free * Software Foundation; either version 2, or (at your option) any later * version. * * Linking GNU Smalltalk statically or dynamically with other modules is * making a combined work based on GNU Smalltalk. Thus, the terms and * conditions of the GNU General Public License cover the whole * combination. * * In addition, as a special exception, the Free Software Foundation * give you permission to combine GNU Smalltalk with free software * programs or libraries that are released under the GNU LGPL and with * independent programs running under the GNU Smalltalk virtual machine. * * You may copy and distribute such a system following the terms of the * GNU GPL for GNU Smalltalk and the licenses of the other code * concerned, provided that you include the source code of that other * code when and as the GNU GPL requires distribution of source code. * * Note that people who make modified versions of GNU Smalltalk are not * obligated to grant this special exception for their modified * versions; it is their choice whether to do so. The GNU General * Public License gives permission to release a modified version without * this exception; this exception also makes it possible to release a * modified version which carries forward this exception. * * GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or * FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for * more details. * * You should have received a copy of the GNU General Public License along with * GNU Smalltalk; see the file COPYING. If not, write to the Free Software * Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * ***********************************************************************/ /* This is basically how the interpreter works. The interpreter expects to be called in an environment where there already exists a well-defined method context. The instruction pointer, stored in the global variable "native_ip", and the stack pointer, stored in the global variable "sp", should be set up to point into the current method and gst_method_context. Other global variables, such as "_gst_this_method", _gst_self", "_gst_temporaries", etc. should also be setup; see the routine _gst_prepare_execution_environment for details. `_gst_interpret' immediately calls `_gst_run_native_code' (coded with GNU lightning in xlat.c) and starts executing compiled code. Every now and then, the compiled code checks to see if any change in its state is required, such as switching to a new process, dealing with an asynchronous signal and printing out the byte codes that are being executed, if that was requested by the user. If so, it returns to `_gst_interpret', telling where to restart execution. `_gst_interpret' handles the event and passes control back to the compiled code. Control is returned to `_gst_interpret' also when the private #__terminate method is executed. When a message send occurs for the first time, an internal routine (either doSend or doSuper) is invoked (these routines are coded with GNU lightning in xlat.c); this routine calls lookup_native_ip, which looks for the method in a cache like the one used by the standard interpreter, and if it is not found, asks xlat.c to return the address; in turn, xlat.c looks for the code into an hash table (which handles collisions unlike lookup_native_ip's cache) before compiling it. doSend then saves the returned address so that it will be used the next time the message is sent, then it jumps to the address. If no selector is found, doSend calls lookup_native_ip again, asking for the address of the #doesNotUnderstand: method. Note that lookup_native_ip had modified the stack, pushing a gst_message object that embeds information about the original selector and arguments. If #doesNotUnderstand: is not understood, a crash is extremely likely; things like this are however to be expected, since you're really playing a bad game and going against some logical things that the VM assumes for speed. After the first time, doSend is not called: instead, the previous address is used to guess the likely address where the code to be called lies. Of course, the `guessed' address might be wrong, because the receiver's class might have changed. So the prolog of every compiled method checks for this eventuality and, if so, performs a standard lookup by jumping back to doSend. Note that this cannot happen with doSuper, because super sends always go to the same receiver (which is the `_gst_self' object). Methods can be marked as doing special things. These are returning self, returning an instance variable, return a literal object, or executing a primitive method definition. In the first three cases, the method does not create a context, and immediately jumps back to the caller. In the latter case, the method calls execute_primitive_operation, examines its return value, and does one of three things: - jumping back to the caller - creating a context and executing the Smalltalk code (failure) - load a new native_ip and jump there BlockClosure>>#value is special-cased in that the new native_ip is cached in the same way that doSend caches the address of a method. When a method returns, the context that called it is examined to restore the interpreter's global variables to the state that they were in before the callee was invoked. After the state has been restored, the callee jumps back to the caller, almost oblivious to the fact that millions of instructions could have been executed since control was left. Note that the microprocessor's CALL and RETURN instructions are not used. Instead, once the _gst_run_native_code function is called, control threads from one method to another, without creating any stack frames, mantaining all the information partly inside ContextPart objects and partly inside inline_cache structures (see xlat.c): the latter also act as continuations that are passed to the callee, which stores the continuation info in the ContextPart. This allows an extremely easy implementation of non-local returns. */ /* This is the bridge between the interpreter and Just-In-Time code generation. It works the same as _gst_send_message_internal, but it only looks up the IP for the native code (compiling the bytecode on demand if it is not available yet) and returns it to the caller. This is because the caller will often be JIT-compiled code which likes to set up the execution contexts and to execute primitives on its own. */ static PTR lookup_native_ip (OOP sendSelector, int sendArgs, OOP receiver, OOP method_class); /* This walks the context stack starting at CONTEXTOOP, compiling on demand all the methods for which native code is not available yet, and restoring the native instruction pointers that are not set (for example because the context was restored from a saved image and has not been executed since the snapshot was restored). */ static void refresh_native_ips (OOP contextOOP); #include "jitpriv.h" /* The functions that are called by the JIT-compiled code. */ const internal_func _gst_internal_funcs[] = { (internal_func) unwind_context, (internal_func) unwind_method, (internal_func) activate_new_context, (internal_func) prepare_context, (internal_func) empty_context_stack, (internal_func) lookup_native_ip, }; #define GET_CONTEXT_IP(ctx) ((char *) (((uintptr_t) ((ctx)->native_ip)) - 1)) #define GET_NATIVE_IP(ipOffset) ((OOP) (((uintptr_t) ipOffset) + 1)) #define SET_THIS_METHOD(method, ipOffset) { \ _gst_this_method = (method); \ native_ip = (ipOffset); \ } PTR lookup_native_ip (OOP sendSelector, int sendArgs, OOP receiver, OOP method_class) /* the class in which to start the search */ { REGISTER (1, int hashIndex); REGISTER (2, method_cache_entry * methodData); REGISTER (3, OOP receiverClass); /* hash the selector and the class of the receiver together using XOR. Since both are addresses in the object table, and since object table entries are 2 longs in size, shift over by 3 bits (4 on 64-bit architectures) to remove the useless low order zeros. */ _gst_sample_counter++; hashIndex = METHOD_CACHE_HASH (sendSelector, method_class); methodData = &method_cache[hashIndex]; if (methodData->selectorOOP != sendSelector || methodData->startingClassOOP != method_class) { /* :-( cache miss )-: */ if (!lookup_method (sendSelector, methodData, sendArgs, method_class)) return (NULL); else /* The next test cannot succeed */ methodData->receiverClass = NULL; } receiverClass = OOP_INT_CLASS (receiver); if (methodData->receiverClass == receiverClass) return (methodData->nativeCode); methodData->receiverClass = receiverClass; methodData->nativeCode = _gst_get_native_code (methodData->methodOOP, receiverClass); return (methodData->nativeCode); } void _gst_send_message_internal (OOP sendSelector, int sendArgs, OOP receiver, OOP method_class) /* the class in which to start the search */ { int hashIndex; method_header header; REGISTER (1, OOP receiverClass); REGISTER (2, method_cache_entry * methodData); /* hash the selector and the class of the receiver together using XOR. Since both are addresses in the object table, and since object table entries are 2 longs in size, shift over by 3 bits (4 on 64-bit architectures) to remove the useless low order zeros. */ _gst_sample_counter++; hashIndex = METHOD_CACHE_HASH (sendSelector, method_class); methodData = &method_cache[hashIndex]; if (methodData->selectorOOP != sendSelector || methodData->startingClassOOP != method_class) { /* :-( cache miss )-: */ if (!lookup_method (sendSelector, methodData, sendArgs, method_class)) { SEND_MESSAGE (_gst_does_not_understand_symbol, 1); return; } else /* The test on the receiverClass will not succeed */ methodData->receiverClass = NULL; } header = methodData->methodHeader; receiverClass = OOP_INT_CLASS (receiver); if (methodData->receiverClass != receiverClass) { methodData->receiverClass = receiverClass; methodData->nativeCode = _gst_get_native_code (methodData->methodOOP, receiverClass); } native_ip = methodData->nativeCode; } void _gst_send_method (OOP methodOOP) { OOP receiverClass; method_header header; REGISTER (1, gst_compiled_method method); REGISTER (2, OOP receiver); REGISTER (3, int sendArgs); _gst_sample_counter++; method = (gst_compiled_method) OOP_TO_OBJ (methodOOP); header = method->header; sendArgs = header.numArgs; receiver = STACK_AT (sendArgs); receiverClass = OOP_INT_CLASS (receiver); native_ip = _gst_get_native_code (methodOOP, receiverClass); } static mst_Boolean send_block_value (int numArgs, int cull_up_to) { OOP closureOOP; OOP receiverClass; block_header header; REGISTER (2, gst_block_closure closure); closureOOP = STACK_AT (numArgs); closure = (gst_block_closure) OOP_TO_OBJ (closureOOP); header = ((gst_compiled_block) OOP_TO_OBJ (closure->block))->header; /* Check numArgs. Remove up to CULL_UP_TO extra arguments if needed. */ if UNCOMMON (numArgs != header.numArgs) { if (numArgs < header.numArgs || numArgs > header.numArgs + cull_up_to) return (true); POP_N_OOPS (numArgs - header.numArgs); numArgs = header.numArgs; } receiverClass = IS_INT (closure->receiver) ? _gst_small_integer_class : OOP_CLASS (closure->receiver); native_ip = _gst_get_native_code (closure->block, receiverClass); return (false); } void _gst_validate_method_cache_entries (void) { int i; method_cache_entry *mc; for (i = 0; i < METHOD_CACHE_SIZE; i++) { mc = &method_cache[i]; if (mc->selectorOOP && !IS_VALID_IP (mc->nativeCode)) /* invalidate this entry */ mc->selectorOOP = NULL; } } void refresh_native_ips (OOP contextOOP) { OOP receiver, receiverClass; int virtualIP; gst_method_context context; PTR native_ip; context = (gst_method_context) OOP_TO_OBJ (contextOOP); do { receiver = context->receiver; receiverClass = OOP_INT_CLASS (receiver); if (context->method == _gst_get_termination_method ()) native_ip = (char *) _gst_return_from_native_code; else { /* Go get the native IP! */ virtualIP = TO_INT (context->ipOffset); native_ip = _gst_map_virtual_ip (context->method, receiverClass, virtualIP); #ifndef OPTIMIZE if (!native_ip) { /* This problem *might* (I'm not even sure) happen if you restore a non-JITted snapshot with the JIT enabled. It should be easy to fix the interpreter so that a process can be suspended at message sends only. */ printf ("Context's IP is not a sequence point!"); abort (); } #endif } context->native_ip = GET_NATIVE_IP (native_ip); contextOOP = context->parentContext; context = (gst_method_context) OOP_TO_OBJ (contextOOP); } while (!IS_NIL (contextOOP) && context->native_ip == DUMMY_NATIVE_IP); } OOP _gst_interpret (OOP processOOP) { interp_jmp_buf jb; gst_callin_process process; push_jmp_buf (&jb, true, processOOP); if (setjmp (jb.jmpBuf) == 0) for (;;) { gst_method_context thisContext; if (!native_ip) return (_gst_nil_oop); native_ip = _gst_run_native_code (native_ip); if (!native_ip) { OOP activeProcessOOP = get_scheduled_process (); gst_callin_process process = (gst_callin_process) OOP_TO_OBJ (activeProcessOOP); process->returnedValue = POP_OOP (); _gst_terminate_process (activeProcessOOP); } SET_EXCEPT_FLAG (false); if UNCOMMON (_gst_abort_execution) { OOP selectorOOP; selectorOOP = _gst_intern_string ((char *)_gst_abort_execution); _gst_abort_execution = NULL; SEND_MESSAGE (selectorOOP, 0); } /* First, deal with any async signals. */ if (async_queue_enabled) empty_async_queue (); thisContext = (gst_method_context) OOP_TO_OBJ (_gst_this_context_oop); thisContext->native_ip = GET_NATIVE_IP (native_ip); if UNCOMMON (!IS_NIL (switch_to_process)) { change_process_context (switch_to_process); if UNCOMMON (single_step_semaphore) { _gst_async_signal (single_step_semaphore); single_step_semaphore = NULL; } } else if UNCOMMON (time_to_preempt) ACTIVE_PROCESS_YIELD (); if (is_process_terminating (processOOP)) break; /* If the native_ip in the context is not valid, this is a process that we have not restarted yet! Get a fresh native_ip for each context in the chain, recompiling methods if needed. */ thisContext = (gst_method_context) OOP_TO_OBJ (_gst_this_context_oop); if (!(_gst_this_method->flags & F_XLAT) || thisContext->native_ip == DUMMY_NATIVE_IP) { refresh_native_ips (_gst_this_context_oop); native_ip = GET_CONTEXT_IP (thisContext); } if UNCOMMON (time_to_preempt) set_preemption_timer (); } if (!IS_NIL (switch_to_process)) change_process_context (switch_to_process); process = (gst_callin_process) OOP_TO_OBJ (processOOP); if (pop_jmp_buf ()) stop_execution (); return (process->returnedValue); } smalltalk-3.2.5/libgst/genpr-parse.c0000644000175000017500000015247012130455565014320 00000000000000/* A Bison parser, made by GNU Bison 2.5. */ /* Bison implementation for Yacc-like parsers in C Copyright (C) 1984, 1989-1990, 2000-2011 Free Software Foundation, Inc. This program is free software: you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation, either version 3 of the License, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program. If not, see . */ /* As a special exception, you may create a larger work that contains part or all of the Bison parser skeleton and distribute that work under terms of your choice, so long as that work isn't itself a parser generator using the skeleton or a modified version thereof as a parser skeleton. Alternatively, if you modify or redistribute the parser skeleton itself, you may (at your option) remove this special exception, which will cause the skeleton and the resulting Bison output files to be licensed under the GNU General Public License without this special exception. This special exception was added by the Free Software Foundation in version 2.2 of Bison. */ /* C LALR(1) parser skeleton written by Richard Stallman, by simplifying the original so-called "semantic" parser. */ /* All symbols defined below should begin with yy or YY, to avoid infringing on user name space. This should be done even for local variables, as they might otherwise be expanded by user macros. There are some unavoidable exceptions within include files to define necessary library symbols; they are noted "INFRINGES ON USER NAME SPACE" below. */ /* Identify Bison output. */ #define YYBISON 1 /* Bison version. */ #define YYBISON_VERSION "2.5" /* Skeleton name. */ #define YYSKELETON_NAME "yacc.c" /* Pure parsers. */ #define YYPURE 0 /* Push parsers. */ #define YYPUSH 0 /* Pull parsers. */ #define YYPULL 1 /* Using locations. */ #define YYLSP_NEEDED 0 /* Copy the first part of user declarations. */ /* Line 268 of yacc.c */ #line 52 "genpr-parse.y" #include "genprims.h" #include "md5.h" /* This program finds declarations of the form: primitive NAME[ATTRS] or primitive NAME : prim_id NAME[ATTRS], prim_id NAME[ATTRS], prim_id NAME[ATTRS] and creates a function for each primitive declaration, and an entry in _gst_init_primitives for each prim_id declaration (note that the former is just a shorthand for primitive NAME : prim_id NAME[ATTRS] and so creates both the function and an entry). The brackets are literal [ and ], and the name can be an identifier or ID = NUMBER, in which case the id that is given to the primitive is set by the programmer (this is usually done for primitives inlined by the JIT compiler). In addition, the C code is examined to see instances of expressions like prim_id(NAME), which are replaced with the identifier given (either manually or automatically) to the named primitive. Everything else is copied verbatim to the output stream. */ #define YYERROR_VERBOSE 1 static void yyerror (const char *s); static void gen_proto (const char *s); static void gen_prim_decl (const char *s); static void gen_prim_id (const char *name, int id, const char *attrs); static int lookup_prim_id (const char *s); static void free_data (); static void output (); static char *strtoupper (char *s); #define YYPRINT(fp, tok, val) fprintf (fp, "%s", val); Filament *proto_fil, *stmt_fil, *def_fil, *literal_fil; typedef struct string_list { char *name; int id; struct string_list *next; } string_list; static char *current_func_name; static int prim_no; static int current_id; static int errors; static string_list *current_ids; #define NOT_FOUND INT_MIN /* Line 268 of yacc.c */ #line 135 "genpr-parse.c" /* Enabling traces. */ #ifndef YYDEBUG # define YYDEBUG 1 #endif /* Enabling verbose error messages. */ #ifdef YYERROR_VERBOSE # undef YYERROR_VERBOSE # define YYERROR_VERBOSE 1 #else # define YYERROR_VERBOSE 0 #endif /* Enabling the token table. */ #ifndef YYTOKEN_TABLE # define YYTOKEN_TABLE 0 #endif /* Tokens. */ #ifndef YYTOKENTYPE # define YYTOKENTYPE /* Put the tokens into the symbol table, so that GDB and other debuggers know about them. */ enum yytokentype { PRIMITIVE = 258, PRIM_ID = 259, NUMBER = 260, ID = 261, LITERAL = 262, WSPACE = 263 }; #endif /* Tokens. */ #define PRIMITIVE 258 #define PRIM_ID 259 #define NUMBER 260 #define ID 261 #define LITERAL 262 #define WSPACE 263 #if ! defined YYSTYPE && ! defined YYSTYPE_IS_DECLARED typedef union YYSTYPE { /* Line 293 of yacc.c */ #line 118 "genpr-parse.y" Filament *fil; char *text; int id; /* Line 293 of yacc.c */ #line 195 "genpr-parse.c" } YYSTYPE; # define YYSTYPE_IS_TRIVIAL 1 # define yystype YYSTYPE /* obsolescent; will be withdrawn */ # define YYSTYPE_IS_DECLARED 1 #endif /* Copy the second part of user declarations. */ /* Line 343 of yacc.c */ #line 207 "genpr-parse.c" #ifdef short # undef short #endif #ifdef YYTYPE_UINT8 typedef YYTYPE_UINT8 yytype_uint8; #else typedef unsigned char yytype_uint8; #endif #ifdef YYTYPE_INT8 typedef YYTYPE_INT8 yytype_int8; #elif (defined __STDC__ || defined __C99__FUNC__ \ || defined __cplusplus || defined _MSC_VER) typedef signed char yytype_int8; #else typedef short int yytype_int8; #endif #ifdef YYTYPE_UINT16 typedef YYTYPE_UINT16 yytype_uint16; #else typedef unsigned short int yytype_uint16; #endif #ifdef YYTYPE_INT16 typedef YYTYPE_INT16 yytype_int16; #else typedef short int yytype_int16; #endif #ifndef YYSIZE_T # ifdef __SIZE_TYPE__ # define YYSIZE_T __SIZE_TYPE__ # elif defined size_t # define YYSIZE_T size_t # elif ! defined YYSIZE_T && (defined __STDC__ || defined __C99__FUNC__ \ || defined __cplusplus || defined _MSC_VER) # include /* INFRINGES ON USER NAME SPACE */ # define YYSIZE_T size_t # else # define YYSIZE_T unsigned int # endif #endif #define YYSIZE_MAXIMUM ((YYSIZE_T) -1) #ifndef YY_ # if defined YYENABLE_NLS && YYENABLE_NLS # if ENABLE_NLS # include /* INFRINGES ON USER NAME SPACE */ # define YY_(msgid) dgettext ("bison-runtime", msgid) # endif # endif # ifndef YY_ # define YY_(msgid) msgid # endif #endif /* Suppress unused-variable warnings by "using" E. */ #if ! defined lint || defined __GNUC__ # define YYUSE(e) ((void) (e)) #else # define YYUSE(e) /* empty */ #endif /* Identity function, used to suppress warnings about constant conditions. */ #ifndef lint # define YYID(n) (n) #else #if (defined __STDC__ || defined __C99__FUNC__ \ || defined __cplusplus || defined _MSC_VER) static int YYID (int yyi) #else static int YYID (yyi) int yyi; #endif { return yyi; } #endif #if ! defined yyoverflow || YYERROR_VERBOSE /* The parser invokes alloca or malloc; define the necessary symbols. */ # ifdef YYSTACK_USE_ALLOCA # if YYSTACK_USE_ALLOCA # ifdef __GNUC__ # define YYSTACK_ALLOC __builtin_alloca # elif defined __BUILTIN_VA_ARG_INCR # include /* INFRINGES ON USER NAME SPACE */ # elif defined _AIX # define YYSTACK_ALLOC __alloca # elif defined _MSC_VER # include /* INFRINGES ON USER NAME SPACE */ # define alloca _alloca # else # define YYSTACK_ALLOC alloca # if ! defined _ALLOCA_H && ! defined EXIT_SUCCESS && (defined __STDC__ || defined __C99__FUNC__ \ || defined __cplusplus || defined _MSC_VER) # include /* INFRINGES ON USER NAME SPACE */ # ifndef EXIT_SUCCESS # define EXIT_SUCCESS 0 # endif # endif # endif # endif # endif # ifdef YYSTACK_ALLOC /* Pacify GCC's `empty if-body' warning. */ # define YYSTACK_FREE(Ptr) do { /* empty */; } while (YYID (0)) # ifndef YYSTACK_ALLOC_MAXIMUM /* The OS might guarantee only one guard page at the bottom of the stack, and a page size can be as small as 4096 bytes. So we cannot safely invoke alloca (N) if N exceeds 4096. Use a slightly smaller number to allow for a few compiler-allocated temporary stack slots. */ # define YYSTACK_ALLOC_MAXIMUM 4032 /* reasonable circa 2006 */ # endif # else # define YYSTACK_ALLOC YYMALLOC # define YYSTACK_FREE YYFREE # ifndef YYSTACK_ALLOC_MAXIMUM # define YYSTACK_ALLOC_MAXIMUM YYSIZE_MAXIMUM # endif # if (defined __cplusplus && ! defined EXIT_SUCCESS \ && ! ((defined YYMALLOC || defined malloc) \ && (defined YYFREE || defined free))) # include /* INFRINGES ON USER NAME SPACE */ # ifndef EXIT_SUCCESS # define EXIT_SUCCESS 0 # endif # endif # ifndef YYMALLOC # define YYMALLOC malloc # if ! defined malloc && ! defined EXIT_SUCCESS && (defined __STDC__ || defined __C99__FUNC__ \ || defined __cplusplus || defined _MSC_VER) void *malloc (YYSIZE_T); /* INFRINGES ON USER NAME SPACE */ # endif # endif # ifndef YYFREE # define YYFREE free # if ! defined free && ! defined EXIT_SUCCESS && (defined __STDC__ || defined __C99__FUNC__ \ || defined __cplusplus || defined _MSC_VER) void free (void *); /* INFRINGES ON USER NAME SPACE */ # endif # endif # endif #endif /* ! defined yyoverflow || YYERROR_VERBOSE */ #if (! defined yyoverflow \ && (! defined __cplusplus \ || (defined YYSTYPE_IS_TRIVIAL && YYSTYPE_IS_TRIVIAL))) /* A type that is properly aligned for any stack member. */ union yyalloc { yytype_int16 yyss_alloc; YYSTYPE yyvs_alloc; }; /* The size of the maximum gap between one aligned stack and the next. */ # define YYSTACK_GAP_MAXIMUM (sizeof (union yyalloc) - 1) /* The size of an array large to enough to hold all stacks, each with N elements. */ # define YYSTACK_BYTES(N) \ ((N) * (sizeof (yytype_int16) + sizeof (YYSTYPE)) \ + YYSTACK_GAP_MAXIMUM) # define YYCOPY_NEEDED 1 /* Relocate STACK from its old location to the new one. The local variables YYSIZE and YYSTACKSIZE give the old and new number of elements in the stack, and YYPTR gives the new location of the stack. Advance YYPTR to a properly aligned location for the next stack. */ # define YYSTACK_RELOCATE(Stack_alloc, Stack) \ do \ { \ YYSIZE_T yynewbytes; \ YYCOPY (&yyptr->Stack_alloc, Stack, yysize); \ Stack = &yyptr->Stack_alloc; \ yynewbytes = yystacksize * sizeof (*Stack) + YYSTACK_GAP_MAXIMUM; \ yyptr += yynewbytes / sizeof (*yyptr); \ } \ while (YYID (0)) #endif #if defined YYCOPY_NEEDED && YYCOPY_NEEDED /* Copy COUNT objects from FROM to TO. The source and destination do not overlap. */ # ifndef YYCOPY # if defined __GNUC__ && 1 < __GNUC__ # define YYCOPY(To, From, Count) \ __builtin_memcpy (To, From, (Count) * sizeof (*(From))) # else # define YYCOPY(To, From, Count) \ do \ { \ YYSIZE_T yyi; \ for (yyi = 0; yyi < (Count); yyi++) \ (To)[yyi] = (From)[yyi]; \ } \ while (YYID (0)) # endif # endif #endif /* !YYCOPY_NEEDED */ /* YYFINAL -- State number of the termination state. */ #define YYFINAL 2 /* YYLAST -- Last index in YYTABLE. */ #define YYLAST 23 /* YYNTOKENS -- Number of terminals. */ #define YYNTOKENS 18 /* YYNNTS -- Number of nonterminals. */ #define YYNNTS 15 /* YYNRULES -- Number of rules. */ #define YYNRULES 21 /* YYNRULES -- Number of states. */ #define YYNSTATES 38 /* YYTRANSLATE(YYLEX) -- Bison symbol number corresponding to YYLEX. */ #define YYUNDEFTOK 2 #define YYMAXUTOK 263 #define YYTRANSLATE(YYX) \ ((unsigned int) (YYX) <= YYMAXUTOK ? yytranslate[YYX] : YYUNDEFTOK) /* YYTRANSLATE[YYLEX] -- Bison symbol number corresponding to YYLEX. */ static const yytype_uint8 yytranslate[] = { 0, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 9, 10, 2, 2, 13, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 15, 2, 2, 14, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 7, 2, 8, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 11, 2, 12, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 1, 2, 3, 4, 5, 6, 16, 17 }; #if YYDEBUG /* YYPRHS[YYN] -- Index of the first RHS symbol of rule number YYN in YYRHS. */ static const yytype_uint8 yyprhs[] = { 0, 0, 3, 4, 11, 12, 13, 18, 21, 24, 27, 28, 32, 34, 38, 42, 44, 45, 51, 54, 55, 56 }; /* YYRHS -- A `-1'-separated list of the rules' RHS. */ static const yytype_int8 yyrhs[] = { 19, 0, -1, -1, 19, 21, 11, 20, 30, 12, -1, -1, -1, 3, 6, 22, 23, -1, 24, 25, -1, 15, 27, -1, 14, 5, -1, -1, 7, 26, 8, -1, 6, -1, 26, 13, 6, -1, 27, 13, 28, -1, 28, -1, -1, 4, 6, 29, 24, 25, -1, 30, 31, -1, -1, -1, 4, 9, 6, 32, 10, -1 }; /* YYRLINE[YYN] -- source line where rule number YYN was defined. */ static const yytype_uint8 yyrline[] = { 0, 141, 141, 140, 149, 155, 154, 167, 172, 178, 183, 189, 197, 202, 211, 214, 221, 220, 233, 237, 242, 241 }; #endif #if YYDEBUG || YYERROR_VERBOSE || YYTOKEN_TABLE /* YYTNAME[SYMBOL-NUM] -- String name of the symbol SYMBOL-NUM. First, the terminals, then, starting at YYNTOKENS, nonterminals. */ static const char *const yytname[] = { "$end", "error", "$undefined", "\"primitive\"", "\"prim_id\"", "\"number\"", "\"identifier\"", "'['", "']'", "'('", "')'", "'{'", "'}'", "','", "'='", "':'", "LITERAL", "WSPACE", "$accept", "input", "$@1", "primitive_decl", "$@2", "primitive_decl_2", "primitive_number", "primitive_attrs", "primitive_attr_list", "prim_id_decls", "prim_id_decl", "@3", "body", "prim_id_ref", "@4", 0 }; #endif # ifdef YYPRINT /* YYTOKNUM[YYLEX-NUM] -- Internal token number corresponding to token YYLEX-NUM. */ static const yytype_uint16 yytoknum[] = { 0, 256, 257, 258, 259, 260, 261, 91, 93, 40, 41, 123, 125, 44, 61, 58, 262, 263 }; # endif /* YYR1[YYN] -- Symbol number of symbol that rule YYN derives. */ static const yytype_uint8 yyr1[] = { 0, 18, 20, 19, 19, 22, 21, 23, 23, 24, 24, 25, 26, 26, 27, 27, 29, 28, 30, 30, 32, 31 }; /* YYR2[YYN] -- Number of symbols composing right hand side of rule YYN. */ static const yytype_uint8 yyr2[] = { 0, 2, 0, 6, 0, 0, 4, 2, 2, 2, 0, 3, 1, 3, 3, 1, 0, 5, 2, 0, 0, 5 }; /* YYDEFACT[STATE-NAME] -- Default reduction number in state STATE-NUM. Performed when YYTABLE doesn't specify something else to do. Zero means the default is an error. */ static const yytype_uint8 yydefact[] = { 4, 0, 1, 0, 0, 5, 2, 10, 19, 0, 0, 6, 0, 0, 9, 0, 8, 15, 0, 7, 0, 3, 18, 16, 0, 12, 0, 0, 10, 14, 11, 0, 20, 0, 13, 0, 17, 21 }; /* YYDEFGOTO[NTERM-NUM]. */ static const yytype_int8 yydefgoto[] = { -1, 1, 8, 4, 7, 11, 12, 19, 26, 16, 17, 28, 13, 22, 35 }; /* YYPACT[STATE-NUM] -- Index in YYTABLE of the portion describing STATE-NUM. */ #define YYPACT_NINF -13 static const yytype_int8 yypact[] = { -13, 2, -13, 1, -2, -13, -13, -11, -13, 5, 7, -13, 6, -4, -13, 8, -1, -13, 9, -13, 10, -13, -13, -13, 7, -13, -7, 11, 4, -13, -13, 14, -13, 6, -13, 12, -13, -13 }; /* YYPGOTO[NTERM-NUM]. */ static const yytype_int8 yypgoto[] = { -13, -13, -13, -13, -13, -13, -12, -10, -13, -13, -3, -13, -13, -13, -13 }; /* YYTABLE[YYPACT[STATE-NUM]]. What to do in state STATE-NUM. If positive, shift that token. If negative, reduce the rule which number is the opposite. If YYTABLE_NINF, syntax error. */ #define YYTABLE_NINF -1 static const yytype_uint8 yytable[] = { 20, 30, 2, 9, 10, 3, 31, 5, 21, 6, 14, 15, 24, 18, 23, 25, 33, 32, 9, 27, 34, 29, 37, 36 }; #define yypact_value_is_default(yystate) \ ((yystate) == (-13)) #define yytable_value_is_error(yytable_value) \ YYID (0) static const yytype_uint8 yycheck[] = { 4, 8, 0, 14, 15, 3, 13, 6, 12, 11, 5, 4, 13, 7, 6, 6, 28, 6, 14, 9, 6, 24, 10, 33 }; /* YYSTOS[STATE-NUM] -- The (internal number of the) accessing symbol of state STATE-NUM. */ static const yytype_uint8 yystos[] = { 0, 19, 0, 3, 21, 6, 11, 22, 20, 14, 15, 23, 24, 30, 5, 4, 27, 28, 7, 25, 4, 12, 31, 6, 13, 6, 26, 9, 29, 28, 8, 13, 6, 24, 6, 32, 25, 10 }; #define yyerrok (yyerrstatus = 0) #define yyclearin (yychar = YYEMPTY) #define YYEMPTY (-2) #define YYEOF 0 #define YYACCEPT goto yyacceptlab #define YYABORT goto yyabortlab #define YYERROR goto yyerrorlab /* Like YYERROR except do call yyerror. This remains here temporarily to ease the transition to the new meaning of YYERROR, for GCC. Once GCC version 2 has supplanted version 1, this can go. However, YYFAIL appears to be in use. Nevertheless, it is formally deprecated in Bison 2.4.2's NEWS entry, where a plan to phase it out is discussed. */ #define YYFAIL goto yyerrlab #if defined YYFAIL /* This is here to suppress warnings from the GCC cpp's -Wunused-macros. Normally we don't worry about that warning, but some users do, and we want to make it easy for users to remove YYFAIL uses, which will produce warnings from Bison 2.5. */ #endif #define YYRECOVERING() (!!yyerrstatus) #define YYBACKUP(Token, Value) \ do \ if (yychar == YYEMPTY && yylen == 1) \ { \ yychar = (Token); \ yylval = (Value); \ YYPOPSTACK (1); \ goto yybackup; \ } \ else \ { \ yyerror (YY_("syntax error: cannot back up")); \ YYERROR; \ } \ while (YYID (0)) #define YYTERROR 1 #define YYERRCODE 256 /* YYLLOC_DEFAULT -- Set CURRENT to span from RHS[1] to RHS[N]. If N is 0, then set CURRENT to the empty location which ends the previous symbol: RHS[0] (always defined). */ #define YYRHSLOC(Rhs, K) ((Rhs)[K]) #ifndef YYLLOC_DEFAULT # define YYLLOC_DEFAULT(Current, Rhs, N) \ do \ if (YYID (N)) \ { \ (Current).first_line = YYRHSLOC (Rhs, 1).first_line; \ (Current).first_column = YYRHSLOC (Rhs, 1).first_column; \ (Current).last_line = YYRHSLOC (Rhs, N).last_line; \ (Current).last_column = YYRHSLOC (Rhs, N).last_column; \ } \ else \ { \ (Current).first_line = (Current).last_line = \ YYRHSLOC (Rhs, 0).last_line; \ (Current).first_column = (Current).last_column = \ YYRHSLOC (Rhs, 0).last_column; \ } \ while (YYID (0)) #endif /* This macro is provided for backward compatibility. */ #ifndef YY_LOCATION_PRINT # define YY_LOCATION_PRINT(File, Loc) ((void) 0) #endif /* YYLEX -- calling `yylex' with the right arguments. */ #ifdef YYLEX_PARAM # define YYLEX yylex (YYLEX_PARAM) #else # define YYLEX yylex () #endif /* Enable debugging if requested. */ #if YYDEBUG # ifndef YYFPRINTF # include /* INFRINGES ON USER NAME SPACE */ # define YYFPRINTF fprintf # endif # define YYDPRINTF(Args) \ do { \ if (yydebug) \ YYFPRINTF Args; \ } while (YYID (0)) # define YY_SYMBOL_PRINT(Title, Type, Value, Location) \ do { \ if (yydebug) \ { \ YYFPRINTF (stderr, "%s ", Title); \ yy_symbol_print (stderr, \ Type, Value); \ YYFPRINTF (stderr, "\n"); \ } \ } while (YYID (0)) /*--------------------------------. | Print this symbol on YYOUTPUT. | `--------------------------------*/ /*ARGSUSED*/ #if (defined __STDC__ || defined __C99__FUNC__ \ || defined __cplusplus || defined _MSC_VER) static void yy_symbol_value_print (FILE *yyoutput, int yytype, YYSTYPE const * const yyvaluep) #else static void yy_symbol_value_print (yyoutput, yytype, yyvaluep) FILE *yyoutput; int yytype; YYSTYPE const * const yyvaluep; #endif { if (!yyvaluep) return; # ifdef YYPRINT if (yytype < YYNTOKENS) YYPRINT (yyoutput, yytoknum[yytype], *yyvaluep); # else YYUSE (yyoutput); # endif switch (yytype) { default: break; } } /*--------------------------------. | Print this symbol on YYOUTPUT. | `--------------------------------*/ #if (defined __STDC__ || defined __C99__FUNC__ \ || defined __cplusplus || defined _MSC_VER) static void yy_symbol_print (FILE *yyoutput, int yytype, YYSTYPE const * const yyvaluep) #else static void yy_symbol_print (yyoutput, yytype, yyvaluep) FILE *yyoutput; int yytype; YYSTYPE const * const yyvaluep; #endif { if (yytype < YYNTOKENS) YYFPRINTF (yyoutput, "token %s (", yytname[yytype]); else YYFPRINTF (yyoutput, "nterm %s (", yytname[yytype]); yy_symbol_value_print (yyoutput, yytype, yyvaluep); YYFPRINTF (yyoutput, ")"); } /*------------------------------------------------------------------. | yy_stack_print -- Print the state stack from its BOTTOM up to its | | TOP (included). | `------------------------------------------------------------------*/ #if (defined __STDC__ || defined __C99__FUNC__ \ || defined __cplusplus || defined _MSC_VER) static void yy_stack_print (yytype_int16 *yybottom, yytype_int16 *yytop) #else static void yy_stack_print (yybottom, yytop) yytype_int16 *yybottom; yytype_int16 *yytop; #endif { YYFPRINTF (stderr, "Stack now"); for (; yybottom <= yytop; yybottom++) { int yybot = *yybottom; YYFPRINTF (stderr, " %d", yybot); } YYFPRINTF (stderr, "\n"); } # define YY_STACK_PRINT(Bottom, Top) \ do { \ if (yydebug) \ yy_stack_print ((Bottom), (Top)); \ } while (YYID (0)) /*------------------------------------------------. | Report that the YYRULE is going to be reduced. | `------------------------------------------------*/ #if (defined __STDC__ || defined __C99__FUNC__ \ || defined __cplusplus || defined _MSC_VER) static void yy_reduce_print (YYSTYPE *yyvsp, int yyrule) #else static void yy_reduce_print (yyvsp, yyrule) YYSTYPE *yyvsp; int yyrule; #endif { int yynrhs = yyr2[yyrule]; int yyi; unsigned long int yylno = yyrline[yyrule]; YYFPRINTF (stderr, "Reducing stack by rule %d (line %lu):\n", yyrule - 1, yylno); /* The symbols being reduced. */ for (yyi = 0; yyi < yynrhs; yyi++) { YYFPRINTF (stderr, " $%d = ", yyi + 1); yy_symbol_print (stderr, yyrhs[yyprhs[yyrule] + yyi], &(yyvsp[(yyi + 1) - (yynrhs)]) ); YYFPRINTF (stderr, "\n"); } } # define YY_REDUCE_PRINT(Rule) \ do { \ if (yydebug) \ yy_reduce_print (yyvsp, Rule); \ } while (YYID (0)) /* Nonzero means print parse trace. It is left uninitialized so that multiple parsers can coexist. */ int yydebug; #else /* !YYDEBUG */ # define YYDPRINTF(Args) # define YY_SYMBOL_PRINT(Title, Type, Value, Location) # define YY_STACK_PRINT(Bottom, Top) # define YY_REDUCE_PRINT(Rule) #endif /* !YYDEBUG */ /* YYINITDEPTH -- initial size of the parser's stacks. */ #ifndef YYINITDEPTH # define YYINITDEPTH 200 #endif /* YYMAXDEPTH -- maximum size the stacks can grow to (effective only if the built-in stack extension method is used). Do not make this value too large; the results are undefined if YYSTACK_ALLOC_MAXIMUM < YYSTACK_BYTES (YYMAXDEPTH) evaluated with infinite-precision integer arithmetic. */ #ifndef YYMAXDEPTH # define YYMAXDEPTH 10000 #endif #if YYERROR_VERBOSE # ifndef yystrlen # if defined __GLIBC__ && defined _STRING_H # define yystrlen strlen # else /* Return the length of YYSTR. */ #if (defined __STDC__ || defined __C99__FUNC__ \ || defined __cplusplus || defined _MSC_VER) static YYSIZE_T yystrlen (const char *yystr) #else static YYSIZE_T yystrlen (yystr) const char *yystr; #endif { YYSIZE_T yylen; for (yylen = 0; yystr[yylen]; yylen++) continue; return yylen; } # endif # endif # ifndef yystpcpy # if defined __GLIBC__ && defined _STRING_H && defined _GNU_SOURCE # define yystpcpy stpcpy # else /* Copy YYSRC to YYDEST, returning the address of the terminating '\0' in YYDEST. */ #if (defined __STDC__ || defined __C99__FUNC__ \ || defined __cplusplus || defined _MSC_VER) static char * yystpcpy (char *yydest, const char *yysrc) #else static char * yystpcpy (yydest, yysrc) char *yydest; const char *yysrc; #endif { char *yyd = yydest; const char *yys = yysrc; while ((*yyd++ = *yys++) != '\0') continue; return yyd - 1; } # endif # endif # ifndef yytnamerr /* Copy to YYRES the contents of YYSTR after stripping away unnecessary quotes and backslashes, so that it's suitable for yyerror. The heuristic is that double-quoting is unnecessary unless the string contains an apostrophe, a comma, or backslash (other than backslash-backslash). YYSTR is taken from yytname. If YYRES is null, do not copy; instead, return the length of what the result would have been. */ static YYSIZE_T yytnamerr (char *yyres, const char *yystr) { if (*yystr == '"') { YYSIZE_T yyn = 0; char const *yyp = yystr; for (;;) switch (*++yyp) { case '\'': case ',': goto do_not_strip_quotes; case '\\': if (*++yyp != '\\') goto do_not_strip_quotes; /* Fall through. */ default: if (yyres) yyres[yyn] = *yyp; yyn++; break; case '"': if (yyres) yyres[yyn] = '\0'; return yyn; } do_not_strip_quotes: ; } if (! yyres) return yystrlen (yystr); return yystpcpy (yyres, yystr) - yyres; } # endif /* Copy into *YYMSG, which is of size *YYMSG_ALLOC, an error message about the unexpected token YYTOKEN for the state stack whose top is YYSSP. Return 0 if *YYMSG was successfully written. Return 1 if *YYMSG is not large enough to hold the message. In that case, also set *YYMSG_ALLOC to the required number of bytes. Return 2 if the required number of bytes is too large to store. */ static int yysyntax_error (YYSIZE_T *yymsg_alloc, char **yymsg, yytype_int16 *yyssp, int yytoken) { YYSIZE_T yysize0 = yytnamerr (0, yytname[yytoken]); YYSIZE_T yysize = yysize0; YYSIZE_T yysize1; enum { YYERROR_VERBOSE_ARGS_MAXIMUM = 5 }; /* Internationalized format string. */ const char *yyformat = 0; /* Arguments of yyformat. */ char const *yyarg[YYERROR_VERBOSE_ARGS_MAXIMUM]; /* Number of reported tokens (one for the "unexpected", one per "expected"). */ int yycount = 0; /* There are many possibilities here to consider: - Assume YYFAIL is not used. It's too flawed to consider. See for details. YYERROR is fine as it does not invoke this function. - If this state is a consistent state with a default action, then the only way this function was invoked is if the default action is an error action. In that case, don't check for expected tokens because there are none. - The only way there can be no lookahead present (in yychar) is if this state is a consistent state with a default action. Thus, detecting the absence of a lookahead is sufficient to determine that there is no unexpected or expected token to report. In that case, just report a simple "syntax error". - Don't assume there isn't a lookahead just because this state is a consistent state with a default action. There might have been a previous inconsistent state, consistent state with a non-default action, or user semantic action that manipulated yychar. - Of course, the expected token list depends on states to have correct lookahead information, and it depends on the parser not to perform extra reductions after fetching a lookahead from the scanner and before detecting a syntax error. Thus, state merging (from LALR or IELR) and default reductions corrupt the expected token list. However, the list is correct for canonical LR with one exception: it will still contain any token that will not be accepted due to an error action in a later state. */ if (yytoken != YYEMPTY) { int yyn = yypact[*yyssp]; yyarg[yycount++] = yytname[yytoken]; if (!yypact_value_is_default (yyn)) { /* Start YYX at -YYN if negative to avoid negative indexes in YYCHECK. In other words, skip the first -YYN actions for this state because they are default actions. */ int yyxbegin = yyn < 0 ? -yyn : 0; /* Stay within bounds of both yycheck and yytname. */ int yychecklim = YYLAST - yyn + 1; int yyxend = yychecklim < YYNTOKENS ? yychecklim : YYNTOKENS; int yyx; for (yyx = yyxbegin; yyx < yyxend; ++yyx) if (yycheck[yyx + yyn] == yyx && yyx != YYTERROR && !yytable_value_is_error (yytable[yyx + yyn])) { if (yycount == YYERROR_VERBOSE_ARGS_MAXIMUM) { yycount = 1; yysize = yysize0; break; } yyarg[yycount++] = yytname[yyx]; yysize1 = yysize + yytnamerr (0, yytname[yyx]); if (! (yysize <= yysize1 && yysize1 <= YYSTACK_ALLOC_MAXIMUM)) return 2; yysize = yysize1; } } } switch (yycount) { # define YYCASE_(N, S) \ case N: \ yyformat = S; \ break YYCASE_(0, YY_("syntax error")); YYCASE_(1, YY_("syntax error, unexpected %s")); YYCASE_(2, YY_("syntax error, unexpected %s, expecting %s")); YYCASE_(3, YY_("syntax error, unexpected %s, expecting %s or %s")); YYCASE_(4, YY_("syntax error, unexpected %s, expecting %s or %s or %s")); YYCASE_(5, YY_("syntax error, unexpected %s, expecting %s or %s or %s or %s")); # undef YYCASE_ } yysize1 = yysize + yystrlen (yyformat); if (! (yysize <= yysize1 && yysize1 <= YYSTACK_ALLOC_MAXIMUM)) return 2; yysize = yysize1; if (*yymsg_alloc < yysize) { *yymsg_alloc = 2 * yysize; if (! (yysize <= *yymsg_alloc && *yymsg_alloc <= YYSTACK_ALLOC_MAXIMUM)) *yymsg_alloc = YYSTACK_ALLOC_MAXIMUM; return 1; } /* Avoid sprintf, as that infringes on the user's name space. Don't have undefined behavior even if the translation produced a string with the wrong number of "%s"s. */ { char *yyp = *yymsg; int yyi = 0; while ((*yyp = *yyformat) != '\0') if (*yyp == '%' && yyformat[1] == 's' && yyi < yycount) { yyp += yytnamerr (yyp, yyarg[yyi++]); yyformat += 2; } else { yyp++; yyformat++; } } return 0; } #endif /* YYERROR_VERBOSE */ /*-----------------------------------------------. | Release the memory associated to this symbol. | `-----------------------------------------------*/ /*ARGSUSED*/ #if (defined __STDC__ || defined __C99__FUNC__ \ || defined __cplusplus || defined _MSC_VER) static void yydestruct (const char *yymsg, int yytype, YYSTYPE *yyvaluep) #else static void yydestruct (yymsg, yytype, yyvaluep) const char *yymsg; int yytype; YYSTYPE *yyvaluep; #endif { YYUSE (yyvaluep); if (!yymsg) yymsg = "Deleting"; YY_SYMBOL_PRINT (yymsg, yytype, yyvaluep, yylocationp); switch (yytype) { default: break; } } /* Prevent warnings from -Wmissing-prototypes. */ #ifdef YYPARSE_PARAM #if defined __STDC__ || defined __cplusplus int yyparse (void *YYPARSE_PARAM); #else int yyparse (); #endif #else /* ! YYPARSE_PARAM */ #if defined __STDC__ || defined __cplusplus int yyparse (void); #else int yyparse (); #endif #endif /* ! YYPARSE_PARAM */ /* The lookahead symbol. */ int yychar; /* The semantic value of the lookahead symbol. */ YYSTYPE yylval; /* Number of syntax errors so far. */ int yynerrs; /*----------. | yyparse. | `----------*/ #ifdef YYPARSE_PARAM #if (defined __STDC__ || defined __C99__FUNC__ \ || defined __cplusplus || defined _MSC_VER) int yyparse (void *YYPARSE_PARAM) #else int yyparse (YYPARSE_PARAM) void *YYPARSE_PARAM; #endif #else /* ! YYPARSE_PARAM */ #if (defined __STDC__ || defined __C99__FUNC__ \ || defined __cplusplus || defined _MSC_VER) int yyparse (void) #else int yyparse () #endif #endif { int yystate; /* Number of tokens to shift before error messages enabled. */ int yyerrstatus; /* The stacks and their tools: `yyss': related to states. `yyvs': related to semantic values. Refer to the stacks thru separate pointers, to allow yyoverflow to reallocate them elsewhere. */ /* The state stack. */ yytype_int16 yyssa[YYINITDEPTH]; yytype_int16 *yyss; yytype_int16 *yyssp; /* The semantic value stack. */ YYSTYPE yyvsa[YYINITDEPTH]; YYSTYPE *yyvs; YYSTYPE *yyvsp; YYSIZE_T yystacksize; int yyn; int yyresult; /* Lookahead token as an internal (translated) token number. */ int yytoken; /* The variables used to return semantic value and location from the action routines. */ YYSTYPE yyval; #if YYERROR_VERBOSE /* Buffer for error messages, and its allocated size. */ char yymsgbuf[128]; char *yymsg = yymsgbuf; YYSIZE_T yymsg_alloc = sizeof yymsgbuf; #endif #define YYPOPSTACK(N) (yyvsp -= (N), yyssp -= (N)) /* The number of symbols on the RHS of the reduced rule. Keep to zero when no symbol should be popped. */ int yylen = 0; yytoken = 0; yyss = yyssa; yyvs = yyvsa; yystacksize = YYINITDEPTH; YYDPRINTF ((stderr, "Starting parse\n")); yystate = 0; yyerrstatus = 0; yynerrs = 0; yychar = YYEMPTY; /* Cause a token to be read. */ /* Initialize stack pointers. Waste one element of value and location stack so that they stay on the same level as the state stack. The wasted elements are never initialized. */ yyssp = yyss; yyvsp = yyvs; goto yysetstate; /*------------------------------------------------------------. | yynewstate -- Push a new state, which is found in yystate. | `------------------------------------------------------------*/ yynewstate: /* In all cases, when you get here, the value and location stacks have just been pushed. So pushing a state here evens the stacks. */ yyssp++; yysetstate: *yyssp = yystate; if (yyss + yystacksize - 1 <= yyssp) { /* Get the current used size of the three stacks, in elements. */ YYSIZE_T yysize = yyssp - yyss + 1; #ifdef yyoverflow { /* Give user a chance to reallocate the stack. Use copies of these so that the &'s don't force the real ones into memory. */ YYSTYPE *yyvs1 = yyvs; yytype_int16 *yyss1 = yyss; /* Each stack pointer address is followed by the size of the data in use in that stack, in bytes. This used to be a conditional around just the two extra args, but that might be undefined if yyoverflow is a macro. */ yyoverflow (YY_("memory exhausted"), &yyss1, yysize * sizeof (*yyssp), &yyvs1, yysize * sizeof (*yyvsp), &yystacksize); yyss = yyss1; yyvs = yyvs1; } #else /* no yyoverflow */ # ifndef YYSTACK_RELOCATE goto yyexhaustedlab; # else /* Extend the stack our own way. */ if (YYMAXDEPTH <= yystacksize) goto yyexhaustedlab; yystacksize *= 2; if (YYMAXDEPTH < yystacksize) yystacksize = YYMAXDEPTH; { yytype_int16 *yyss1 = yyss; union yyalloc *yyptr = (union yyalloc *) YYSTACK_ALLOC (YYSTACK_BYTES (yystacksize)); if (! yyptr) goto yyexhaustedlab; YYSTACK_RELOCATE (yyss_alloc, yyss); YYSTACK_RELOCATE (yyvs_alloc, yyvs); # undef YYSTACK_RELOCATE if (yyss1 != yyssa) YYSTACK_FREE (yyss1); } # endif #endif /* no yyoverflow */ yyssp = yyss + yysize - 1; yyvsp = yyvs + yysize - 1; YYDPRINTF ((stderr, "Stack size increased to %lu\n", (unsigned long int) yystacksize)); if (yyss + yystacksize - 1 <= yyssp) YYABORT; } YYDPRINTF ((stderr, "Entering state %d\n", yystate)); if (yystate == YYFINAL) YYACCEPT; goto yybackup; /*-----------. | yybackup. | `-----------*/ yybackup: /* Do appropriate processing given the current state. Read a lookahead token if we need one and don't already have one. */ /* First try to decide what to do without reference to lookahead token. */ yyn = yypact[yystate]; if (yypact_value_is_default (yyn)) goto yydefault; /* Not known => get a lookahead token if don't already have one. */ /* YYCHAR is either YYEMPTY or YYEOF or a valid lookahead symbol. */ if (yychar == YYEMPTY) { YYDPRINTF ((stderr, "Reading a token: ")); yychar = YYLEX; } if (yychar <= YYEOF) { yychar = yytoken = YYEOF; YYDPRINTF ((stderr, "Now at end of input.\n")); } else { yytoken = YYTRANSLATE (yychar); YY_SYMBOL_PRINT ("Next token is", yytoken, &yylval, &yylloc); } /* If the proper action on seeing token YYTOKEN is to reduce or to detect an error, take that action. */ yyn += yytoken; if (yyn < 0 || YYLAST < yyn || yycheck[yyn] != yytoken) goto yydefault; yyn = yytable[yyn]; if (yyn <= 0) { if (yytable_value_is_error (yyn)) goto yyerrlab; yyn = -yyn; goto yyreduce; } /* Count tokens shifted since error; after three, turn off error status. */ if (yyerrstatus) yyerrstatus--; /* Shift the lookahead token. */ YY_SYMBOL_PRINT ("Shifting", yytoken, &yylval, &yylloc); /* Discard the shifted token. */ yychar = YYEMPTY; yystate = yyn; *++yyvsp = yylval; goto yynewstate; /*-----------------------------------------------------------. | yydefault -- do the default action for the current state. | `-----------------------------------------------------------*/ yydefault: yyn = yydefact[yystate]; if (yyn == 0) goto yyerrlab; goto yyreduce; /*-----------------------------. | yyreduce -- Do a reduction. | `-----------------------------*/ yyreduce: /* yyn is the number of a rule to reduce with. */ yylen = yyr2[yyn]; /* If YYLEN is nonzero, implement the default value of the action: `$$ = $1'. Otherwise, the following line sets YYVAL to garbage. This behavior is undocumented and Bison users should not rely upon it. Assigning to YYVAL unconditionally makes the parser a bit smaller, and it avoids a GCC warning that YYVAL may be used uninitialized. */ yyval = yyvsp[1-yylen]; YY_REDUCE_PRINT (yyn); switch (yyn) { case 2: /* Line 1806 of yacc.c */ #line 141 "genpr-parse.y" { filprintf (stmt_fil, "#line %d \"prims.def\"\n{", yylineno); } break; case 3: /* Line 1806 of yacc.c */ #line 145 "genpr-parse.y" { free_data (); } break; case 4: /* Line 1806 of yacc.c */ #line 149 "genpr-parse.y" { } break; case 5: /* Line 1806 of yacc.c */ #line 155 "genpr-parse.y" { current_id = 0; current_func_name = strdup ((yyvsp[(2) - (2)].text)); gen_proto ((yyvsp[(2) - (2)].text)); gen_prim_decl ((yyvsp[(2) - (2)].text)); } break; case 6: /* Line 1806 of yacc.c */ #line 162 "genpr-parse.y" { } break; case 7: /* Line 1806 of yacc.c */ #line 168 "genpr-parse.y" { gen_prim_id (current_func_name, (yyvsp[(1) - (2)].id), (yyvsp[(2) - (2)].text)); free ((yyvsp[(2) - (2)].text)); } break; case 8: /* Line 1806 of yacc.c */ #line 173 "genpr-parse.y" { } break; case 9: /* Line 1806 of yacc.c */ #line 179 "genpr-parse.y" { (yyval.id) = strtoul ((yyvsp[(2) - (2)].text), NULL, 10); } break; case 10: /* Line 1806 of yacc.c */ #line 183 "genpr-parse.y" { (yyval.id) = current_id--; } break; case 11: /* Line 1806 of yacc.c */ #line 190 "genpr-parse.y" { (yyval.text) = fildelete ((yyvsp[(2) - (3)].fil)); strtoupper ((yyval.text)); } break; case 12: /* Line 1806 of yacc.c */ #line 198 "genpr-parse.y" { (yyval.fil) = filnew ("PRIM_", 5); filcat ((yyval.fil), (yyvsp[(1) - (1)].text)); } break; case 13: /* Line 1806 of yacc.c */ #line 203 "genpr-parse.y" { (yyval.fil) = (yyvsp[(1) - (3)].fil); filcat ((yyval.fil), " | PRIM_"); filcat ((yyval.fil), (yyvsp[(3) - (3)].text)); } break; case 14: /* Line 1806 of yacc.c */ #line 212 "genpr-parse.y" { } break; case 15: /* Line 1806 of yacc.c */ #line 215 "genpr-parse.y" { } break; case 16: /* Line 1806 of yacc.c */ #line 221 "genpr-parse.y" { (yyval.text) = strdup((yyvsp[(2) - (2)].text)); } break; case 17: /* Line 1806 of yacc.c */ #line 225 "genpr-parse.y" { gen_prim_id ((yyvsp[(3) - (5)].text), (yyvsp[(4) - (5)].id), (yyvsp[(5) - (5)].text)); free ((yyvsp[(3) - (5)].text)); free ((yyvsp[(5) - (5)].text)); } break; case 18: /* Line 1806 of yacc.c */ #line 234 "genpr-parse.y" { filprintf (stmt_fil, "%d", (yyvsp[(2) - (2)].id)); } break; case 20: /* Line 1806 of yacc.c */ #line 242 "genpr-parse.y" { (yyval.id) = lookup_prim_id ((yyvsp[(3) - (3)].text)); if ((yyval.id) == NOT_FOUND) yyerror ("Invalid primitive id"); } break; case 21: /* Line 1806 of yacc.c */ #line 248 "genpr-parse.y" { (yyval.id) = (yyvsp[(4) - (5)].id); literal_fil = stmt_fil; } break; /* Line 1806 of yacc.c */ #line 1630 "genpr-parse.c" default: break; } /* User semantic actions sometimes alter yychar, and that requires that yytoken be updated with the new translation. We take the approach of translating immediately before every use of yytoken. One alternative is translating here after every semantic action, but that translation would be missed if the semantic action invokes YYABORT, YYACCEPT, or YYERROR immediately after altering yychar or if it invokes YYBACKUP. In the case of YYABORT or YYACCEPT, an incorrect destructor might then be invoked immediately. In the case of YYERROR or YYBACKUP, subsequent parser actions might lead to an incorrect destructor call or verbose syntax error message before the lookahead is translated. */ YY_SYMBOL_PRINT ("-> $$ =", yyr1[yyn], &yyval, &yyloc); YYPOPSTACK (yylen); yylen = 0; YY_STACK_PRINT (yyss, yyssp); *++yyvsp = yyval; /* Now `shift' the result of the reduction. Determine what state that goes to, based on the state we popped back to and the rule number reduced by. */ yyn = yyr1[yyn]; yystate = yypgoto[yyn - YYNTOKENS] + *yyssp; if (0 <= yystate && yystate <= YYLAST && yycheck[yystate] == *yyssp) yystate = yytable[yystate]; else yystate = yydefgoto[yyn - YYNTOKENS]; goto yynewstate; /*------------------------------------. | yyerrlab -- here on detecting error | `------------------------------------*/ yyerrlab: /* Make sure we have latest lookahead translation. See comments at user semantic actions for why this is necessary. */ yytoken = yychar == YYEMPTY ? YYEMPTY : YYTRANSLATE (yychar); /* If not already recovering from an error, report this error. */ if (!yyerrstatus) { ++yynerrs; #if ! YYERROR_VERBOSE yyerror (YY_("syntax error")); #else # define YYSYNTAX_ERROR yysyntax_error (&yymsg_alloc, &yymsg, \ yyssp, yytoken) { char const *yymsgp = YY_("syntax error"); int yysyntax_error_status; yysyntax_error_status = YYSYNTAX_ERROR; if (yysyntax_error_status == 0) yymsgp = yymsg; else if (yysyntax_error_status == 1) { if (yymsg != yymsgbuf) YYSTACK_FREE (yymsg); yymsg = (char *) YYSTACK_ALLOC (yymsg_alloc); if (!yymsg) { yymsg = yymsgbuf; yymsg_alloc = sizeof yymsgbuf; yysyntax_error_status = 2; } else { yysyntax_error_status = YYSYNTAX_ERROR; yymsgp = yymsg; } } yyerror (yymsgp); if (yysyntax_error_status == 2) goto yyexhaustedlab; } # undef YYSYNTAX_ERROR #endif } if (yyerrstatus == 3) { /* If just tried and failed to reuse lookahead token after an error, discard it. */ if (yychar <= YYEOF) { /* Return failure if at end of input. */ if (yychar == YYEOF) YYABORT; } else { yydestruct ("Error: discarding", yytoken, &yylval); yychar = YYEMPTY; } } /* Else will try to reuse lookahead token after shifting the error token. */ goto yyerrlab1; /*---------------------------------------------------. | yyerrorlab -- error raised explicitly by YYERROR. | `---------------------------------------------------*/ yyerrorlab: /* Pacify compilers like GCC when the user code never invokes YYERROR and the label yyerrorlab therefore never appears in user code. */ if (/*CONSTCOND*/ 0) goto yyerrorlab; /* Do not reclaim the symbols of the rule which action triggered this YYERROR. */ YYPOPSTACK (yylen); yylen = 0; YY_STACK_PRINT (yyss, yyssp); yystate = *yyssp; goto yyerrlab1; /*-------------------------------------------------------------. | yyerrlab1 -- common code for both syntax error and YYERROR. | `-------------------------------------------------------------*/ yyerrlab1: yyerrstatus = 3; /* Each real token shifted decrements this. */ for (;;) { yyn = yypact[yystate]; if (!yypact_value_is_default (yyn)) { yyn += YYTERROR; if (0 <= yyn && yyn <= YYLAST && yycheck[yyn] == YYTERROR) { yyn = yytable[yyn]; if (0 < yyn) break; } } /* Pop the current state because it cannot handle the error token. */ if (yyssp == yyss) YYABORT; yydestruct ("Error: popping", yystos[yystate], yyvsp); YYPOPSTACK (1); yystate = *yyssp; YY_STACK_PRINT (yyss, yyssp); } *++yyvsp = yylval; /* Shift the error token. */ YY_SYMBOL_PRINT ("Shifting", yystos[yyn], yyvsp, yylsp); yystate = yyn; goto yynewstate; /*-------------------------------------. | yyacceptlab -- YYACCEPT comes here. | `-------------------------------------*/ yyacceptlab: yyresult = 0; goto yyreturn; /*-----------------------------------. | yyabortlab -- YYABORT comes here. | `-----------------------------------*/ yyabortlab: yyresult = 1; goto yyreturn; #if !defined(yyoverflow) || YYERROR_VERBOSE /*-------------------------------------------------. | yyexhaustedlab -- memory exhaustion comes here. | `-------------------------------------------------*/ yyexhaustedlab: yyerror (YY_("memory exhausted")); yyresult = 2; /* Fall through. */ #endif yyreturn: if (yychar != YYEMPTY) { /* Make sure we have latest lookahead translation. See comments at user semantic actions for why this is necessary. */ yytoken = YYTRANSLATE (yychar); yydestruct ("Cleanup: discarding lookahead", yytoken, &yylval); } /* Do not reclaim the symbols of the rule which action triggered this YYABORT or YYACCEPT. */ YYPOPSTACK (yylen); YY_STACK_PRINT (yyss, yyssp); while (yyssp != yyss) { yydestruct ("Cleanup: popping", yystos[*yyssp], yyvsp); YYPOPSTACK (1); } #ifndef yyoverflow if (yyss != yyssa) YYSTACK_FREE (yyss); #endif #if YYERROR_VERBOSE if (yymsg != yymsgbuf) YYSTACK_FREE (yymsg); #endif /* Make sure YYID is used. */ return YYID (yyresult); } /* Line 2067 of yacc.c */ #line 254 "genpr-parse.y" void yyerror (const char *s) { errors = 1; fprintf (stderr, "prims.def:%d: %s\n", yylineno, s); } int filprintf (Filament *fil, const char *format, ...) { va_list ap; STREAM *out = stream_new (fil, SNV_UNLIMITED, NULL, snv_filputc); int result; va_start (ap, format); result = stream_vprintf (out, format, ap); va_end (ap); stream_delete (out); return result; } void gen_proto (const char *s) { filprintf (proto_fil, "static intptr_t\n" "%s (int id ATTRIBUTE_UNUSED,\n" "%*svolatile int numArgs ATTRIBUTE_UNUSED);\n\n", s, 2 + strlen(s), ""); } static void gen_prim_decl (const char *s) { filprintf (stmt_fil, "intptr_t\n" "%s (int id,\n" "%*svolatile int numArgs)\n", s, 2 + strlen(s), ""); } char * strtoupper (char *s) { char *base = s; while (*s) *s = toupper (*s), s++; return base; } void gen_prim_id (const char *name, int id, const char *attrs) { string_list *node; node = (string_list *) malloc (sizeof (string_list)); node->name = strdup (name); node->id = id; node->next = current_ids; current_ids = node; prim_no++; filprintf (def_fil, " _gst_default_primitive_table[%d].name = \"%s\";\n" " _gst_default_primitive_table[%d].attributes = %s;\n" " _gst_default_primitive_table[%d].id = %d;\n" " _gst_default_primitive_table[%d].func = %s;\n", prim_no, name, prim_no, attrs, prim_no, id, prim_no, current_func_name); } int lookup_prim_id (const char *s) { string_list *node; for (node = current_ids; node && strcmp (s, node->name); node = node->next); return node ? node->id : NOT_FOUND; } void free_data () { string_list *first, *next; if (current_func_name) free (current_func_name); for (first = current_ids; first; first = next) { next = first->next; free (first->name); free (first); } current_ids = NULL; } void output() { char *proto, *stmt, *def; unsigned char md5[16]; gen_proto ("VMpr_HOLE"); proto = fildelete (proto_fil); stmt = fildelete (stmt_fil); def = fildelete (def_fil); md5_buffer (def, strlen (def), md5); printf ("%s\n" "%s\n" "intptr_t\n" "VMpr_HOLE (int id,\n" " volatile int numArgs)\n" "{\n" " _gst_primitives_executed++;\n" " _gst_errorf (\"Unhandled primitive operation %%d\", id);\n" "\n" " UNPOP (numArgs);\n" " PRIM_FAILED;\n" "}\n" "\n" "unsigned char\n" "_gst_primitives_md5[16] = { %d, %d, %d, %d, %d, %d, %d, %d,\n" " %d, %d, %d, %d, %d, %d, %d, %d };\n" "\n" "void\n" "_gst_init_primitives()\n" "{\n" " int i;\n" "%s" "\n" " for (i = %d; i < NUM_PRIMITIVES; i++)\n" " {\n" " _gst_default_primitive_table[i].name = NULL;\n" " _gst_default_primitive_table[i].attributes = PRIM_FAIL;\n" " _gst_default_primitive_table[i].id = i;\n" " _gst_default_primitive_table[i].func = VMpr_HOLE;\n" " }\n" "}\n" "\n", proto, stmt, md5[0], md5[1], md5[2], md5[3], md5[4], md5[5], md5[6], md5[7], md5[8], md5[9], md5[10], md5[11], md5[12], md5[13], md5[14], md5[15], def, prim_no + 1); free (proto); free (stmt); free (def); } int main () { proto_fil = filnew (NULL, 0); stmt_fil = filnew (NULL, 0); def_fil = filnew (NULL, 0); literal_fil = proto_fil; errors = 0; if (yyparse () || errors) exit (1); output (); exit (0); } smalltalk-3.2.5/libgst/vm.def0000644000175000017500000014440612123404352013021 00000000000000/******************************** -*- C -*- **************************** * * Interpreter definitions. * * ***********************************************************************/ /*********************************************************************** * * Copyright 2003, 2006, 2008, 2009 Free Software Foundation, Inc. * Written by Steve Byrne and Paolo Bonzini. * * This file is part of GNU Smalltalk. * * GNU Smalltalk is free software; you can redistribute it and/or modify it * under the terms of the GNU General Public License as published by the Free * Software Foundation; either version 2, or (at your option) any later * version. * * Linking GNU Smalltalk statically or dynamically with other modules is * making a combined work based on GNU Smalltalk. Thus, the terms and * conditions of the GNU General Public License cover the whole * combination. * * In addition, as a special exception, the Free Software Foundation * give you permission to combine GNU Smalltalk with free software * programs or libraries that are released under the GNU LGPL and with * independent programs running under the GNU Smalltalk virtual machine. * * You may copy and distribute such a system following the terms of the * GNU GPL for GNU Smalltalk and the licenses of the other code * concerned, provided that you include the source code of that other * code when and as the GNU GPL requires distribution of source code. * * Note that people who make modified versions of GNU Smalltalk are not * obligated to grant this special exception for their modified * versions; it is their choice whether to do so. The GNU General * Public License gives permission to release a modified version without * this exception; this exception also makes it possible to release a * modified version which carries forward this exception. * * GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or * FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for * more details. * * You should have received a copy of the GNU General Public License along with * GNU Smalltalk; see the file COPYING. If not, write to the Free Software * Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * ***********************************************************************/ /* This has two kinds of declarations: - operations are C code together with the stack effect that it should have; so far, this is used only to avoid specifying pushes and pops, but it might be used to combine the accesses to the stack and do some great optimization of the superoperators. `break' inside an operation has the nice effect of getting out of it. They can have parameters which are specified between the name and the stack effect. Both the formal parameters, and the stack slots, are guaranteed to be lvalues. - tables are, well, dispatching tables for bytecodes expressed in a short, useful syntax. Inside tables one defines bytecodes, which are sequences of operations which expand the operations and use the input code stream to pass them actual parameters. Preprocessor statements are passed through without any change. */ #define SEND_TO_SUPER(sendSelector, sendArgs, methodClass) \ _gst_send_message_internal(sendSelector, sendArgs, _gst_self, methodClass) #if REG_AVAILABILITY >= 2 && defined(LOCAL_REGS) #define RECEIVER_VARIABLE(index) INSTANCE_VARIABLE (self_cache, index) #define METHOD_TEMPORARY(index) temp_cache[index] #define METHOD_LITERAL(index) lit_cache[index] #define STORE_RECEIVER_VARIABLE(index, oop) STORE_INSTANCE_VARIABLE (self_cache, index, oop) #define STORE_METHOD_TEMPORARY(index, oop) temp_cache[index] = (oop) #define STORE_METHOD_LITERAL(index, oop) lit_cache[index] = (oop) #else #define RECEIVER_VARIABLE(index) INSTANCE_VARIABLE (_gst_self, index) #define METHOD_TEMPORARY(index) _gst_temporaries[index] #define METHOD_LITERAL(index) _gst_literals[index] #define STORE_RECEIVER_VARIABLE(index, oop) STORE_INSTANCE_VARIABLE (_gst_self, index, oop) #define STORE_METHOD_TEMPORARY(index, oop) _gst_temporaries[index] = (oop) #define STORE_METHOD_LITERAL(index, oop) _gst_literals[index] = (oop) #endif #ifndef OPEN_CODE_MATH #define RAW_INT_OP(op, op1, op2, iop) #define RAW_FLOATD_OP(op, op1, op2, fop) #define INTERP_BASIC_OP(op, op1, op2, iop, fop) #define INTERP_BASIC_BOOL(op, op1, op2, operator) #else #define RAW_INT_OP(op, op1, op2, iop) \ { \ mst_Boolean overflow; \ OOP result = iop; \ if(COMMON (!overflow)) { \ op = result; \ break; \ } \ } #define RAW_FLOATD_OP(op, op1, op2, fop) \ { \ double farg1, farg2; \ farg1 = IS_INT (op1) ? TO_INT (op1) : FLOATD_OOP_VALUE(op1); \ farg2 = IS_INT (op2) ? TO_INT (op2) : FLOATD_OOP_VALUE(op2); \ EXPORT_REGS(); \ op = floatd_new(fop); \ IMPORT_REGS(); \ break; \ } #define INTERP_BASIC_OP(op, op1, op2, iop, fop) { \ if COMMON (ARE_INTS(op1, op2)) { \ RAW_INT_OP(op, op1, op2, iop); \ } else if COMMON ((IS_INT (op1) || OOP_CLASS(op1) == _gst_floatd_class) \ && (IS_INT (op2) || OOP_CLASS(op2) == _gst_floatd_class)) \ RAW_FLOATD_OP(op, op1, op2, fop); \ } #define INTERP_BASIC_BOOL(op, op1, op2, operator) { \ if COMMON (ARE_INTS(op1, op2)) { \ POP_N_OOPS (2); \ if (((intptr_t) op1) operator ((intptr_t) op2)) \ DISPATCH(true_byte_codes); \ else \ DISPATCH(false_byte_codes); \ } else if COMMON ((IS_INT (op1) || OOP_CLASS(op1) == _gst_floatd_class) \ && (IS_INT (op2) || OOP_CLASS(op2) == _gst_floatd_class)) { \ double farg1 = IS_INT (op1) ? TO_INT (op1) : FLOATD_OOP_VALUE(op1); \ double farg2 = IS_INT (op2) ? TO_INT (op2) : FLOATD_OOP_VALUE(op2); \ POP_N_OOPS (2); \ if (farg1 operator farg2) \ DISPATCH(true_byte_codes); \ else \ DISPATCH(false_byte_codes); \ } \ } #endif /* FETCH loads the whole queue. FETCH_VEC does the same, but uses the given vector to execute the next bytecode. DISPATCH keeps the current queue and dispatches the next bytecode to its execution routine. PREFETCH prepares to execute the next bytecode, including advancing ip. PREFETCH_VEC does the same, but uses the given vector to execute the next bytecode. NEXT_BC assumes that the next bytecode was prefetched, loads its argument and dispatches it to the current dispatch vector. NEXT_BC_VEC assumes that the next bytecode was prefetched with PREFETCH_VEC, loads its argument and dispatches it to the current dispatch vector. NEXT_BC_NO_ARG does the same, and avoids loading the argument for the next bytecode. GET_ARG holds a pointer to the (possibly prefetched) argument of the next bytecode. */ #ifdef PIPELINING #define FETCH goto *(t = dispatch_vec[*ip], b2 = ip[2], b4 = ip[4], \ arg = ip[1], arg2 = ip[3], t2 = dispatch_vec[b2], t) #define FETCH_VEC(v) goto *(t = (v)[*ip], b2 = ip[2], b4 = ip[4], \ arg = ip[1], arg2 = ip[3], t2 = dispatch_vec[b2], t) #define PREFETCH (t = t2, t2 = dispatch_vec[b4], \ arg2 = ip[3], b2 = b4, b4 = ip[6], \ ip += 2) #define PREFETCH_VEC(v) (t = (v)[b2], t2 = dispatch_vec[b4], \ arg2 = ip[3], b2 = b4, b4 = ip[6], \ ip += 2) #define NEXT_BC goto *(arg = GET_ARG, t) #define NEXT_BC_VEC(v) goto *(arg = GET_ARG, t) #define NEXT_BC_NO_ARG(v) goto *t #define GET_ARG arg2 #elif REG_AVAILABILITY >= 1 #define FETCH goto *(arg = GET_ARG, dispatch_vec[*ip]) #define FETCH_VEC(v) goto *(arg = GET_ARG, (v)[*ip]) #define PREFETCH (ip += 2, prefetch = dispatch_vec[*ip]) #define PREFETCH_VEC(v) (ip += 2, prefetch = (v)[*ip]) #define NEXT_BC goto *(arg = GET_ARG, prefetch) #define NEXT_BC_VEC(v) goto *(arg = GET_ARG, prefetch) #define NEXT_BC_NO_ARG(v) goto *prefetch #define GET_ARG (ip[1]) #else #define FETCH NEXT_BC #define FETCH_VEC(v) NEXT_BC_VEC(v) #define PREFETCH (ip += 2) #define PREFETCH_VEC(v) (ip += 2) #define NEXT_BC goto *(arg = GET_ARG, dispatch_vec[*ip]) #define NEXT_BC_VEC(v) goto *(arg = GET_ARG, (v)[*ip]) #define NEXT_BC_NO_ARG(v) goto *(v)[*ip] #define GET_ARG (ip[1]) #endif #define DISPATCH(v) goto *(arg = GET_ARG, (v)[*ip]) operation PREFETCH ( -- ) { PREFETCH; LOCAL_COUNTER++; } operation ADVANCE ( -- ) { ip += 2; LOCAL_COUNTER++; } /* EXT_BYTE extends the argument of the next bytecode; it includes a separate prefetching routine which avoids interrupts (because the two are effectively a single bytecode). */ operation EXT_BYTE ( -- ) { PREFETCH_VEC (normal_byte_codes); arg = (arg << 8) | GET_ARG; NEXT_BC_NO_ARG (normal_byte_codes); } operation INVALID arg ( -- ) { _gst_errorf ("Invalid bytecode %d(%d) found!", ip[-1], arg); } operation PLUS_SPECIAL ( op1 op2 -- op ) { INTERP_BASIC_OP (op, op1, op2, add_with_check (op1, op2, &overflow), farg1 + farg2); PREPARE_STACK (); EXPORT_REGS (); SEND_MESSAGE (_gst_builtin_selectors[PLUS_SPECIAL].symbol, 1); IMPORT_REGS (); FETCH; } operation MINUS_SPECIAL ( op1 op2 -- op ) { INTERP_BASIC_OP (op, op1, op2, sub_with_check (op1, op2, &overflow), farg1 - farg2); PREPARE_STACK (); EXPORT_REGS (); SEND_MESSAGE (_gst_builtin_selectors[MINUS_SPECIAL].symbol, 1); IMPORT_REGS (); FETCH; } operation LESS_THAN_SPECIAL ( op1 op2 -- op ) { PREPARE_STACK (); INTERP_BASIC_BOOL (op, op1, op2, <); EXPORT_REGS (); SEND_MESSAGE (_gst_builtin_selectors[LESS_THAN_SPECIAL].symbol, 1); IMPORT_REGS (); FETCH; } operation GREATER_THAN_SPECIAL ( op1 op2 -- op ) { PREPARE_STACK (); INTERP_BASIC_BOOL (op, op1, op2, >); EXPORT_REGS (); SEND_MESSAGE (_gst_builtin_selectors[GREATER_THAN_SPECIAL].symbol, 1); IMPORT_REGS (); FETCH; } operation LESS_EQUAL_SPECIAL ( op1 op2 -- op ) { PREPARE_STACK (); INTERP_BASIC_BOOL (op, op1, op2, <=); EXPORT_REGS (); SEND_MESSAGE (_gst_builtin_selectors[LESS_EQUAL_SPECIAL].symbol, 1); IMPORT_REGS (); FETCH; } operation GREATER_EQUAL_SPECIAL ( op1 op2 -- op ) { PREPARE_STACK (); INTERP_BASIC_BOOL (op, op1, op2, >=); EXPORT_REGS (); SEND_MESSAGE (_gst_builtin_selectors[GREATER_EQUAL_SPECIAL].symbol, 1); IMPORT_REGS (); FETCH; } operation EQUAL_SPECIAL ( op1 op2 -- op ) { PREPARE_STACK (); INTERP_BASIC_BOOL (op, op1, op2, ==); EXPORT_REGS (); SEND_MESSAGE (_gst_builtin_selectors[EQUAL_SPECIAL].symbol, 1); IMPORT_REGS (); FETCH; } operation NOT_EQUAL_SPECIAL ( op1 op2 -- op ) { PREPARE_STACK (); INTERP_BASIC_BOOL (op, op1, op2, !=); EXPORT_REGS (); SEND_MESSAGE (_gst_builtin_selectors[NOT_EQUAL_SPECIAL].symbol, 1); IMPORT_REGS (); FETCH; } operation TIMES_SPECIAL ( op1 op2 -- op ) { INTERP_BASIC_OP (op, op1, op2, mul_with_check (op1, op2, &overflow), farg1 * farg2); PREPARE_STACK (); EXPORT_REGS (); SEND_MESSAGE (_gst_builtin_selectors[TIMES_SPECIAL].symbol, 1); IMPORT_REGS (); FETCH; } operation DIVIDE_SPECIAL ( op1 op2 -- op ) { if COMMON (!ARE_INTS (op1, op2) && (IS_INT (op1) || OOP_CLASS(op1) == _gst_floatd_class) && (IS_INT (op2) || OOP_CLASS(op2) == _gst_floatd_class)) { RAW_FLOATD_OP(op, op1, op2, farg1 / farg2); } PREPARE_STACK (); EXPORT_REGS(); if (COMMON (ARE_INTS (op1, op2))) { if (!VMpr_SmallInteger_divide (10, 1)) { IMPORT_REGS (); NEXT_BC; } } SEND_MESSAGE (_gst_builtin_selectors[DIVIDE_SPECIAL].symbol, 1); IMPORT_REGS (); FETCH; } operation REMAINDER_SPECIAL ( op1 op2 -- op ) { PREPARE_STACK (); EXPORT_REGS(); if (IS_INT (op1) && IS_INT (op2) && !VMpr_SmallInteger_modulo (11, 1)) { IMPORT_REGS (); NEXT_BC; } SEND_MESSAGE (_gst_builtin_selectors[REMAINDER_SPECIAL].symbol, 1); IMPORT_REGS (); FETCH; } operation BIT_XOR_SPECIAL ( op1 op2 -- op ) { if COMMON (ARE_INTS (op1, op2)) { op = tagged_xor (op1, op2); break; } PREPARE_STACK (); EXPORT_REGS (); SEND_MESSAGE (_gst_builtin_selectors[BIT_XOR_SPECIAL].symbol, 1); IMPORT_REGS (); FETCH; } operation BIT_SHIFT_SPECIAL ( op1 op2 -- op ) { if COMMON (IS_INT (op2) && IS_INT (op1)) { intptr_t iarg1, iarg2; iarg1 = TO_INT (op1); iarg2 = TO_INT (op2); if (iarg2 < 0) { if COMMON (iarg2 >= -ST_INT_SIZE) op = FROM_INT (iarg1 >> -iarg2); else op = FROM_INT (iarg1 >> ST_INT_SIZE); break; } else if COMMON (iarg2 < ST_INT_SIZE) { intptr_t result = iarg1 << iarg2; if COMMON ((result >> iarg2) == iarg1 && !INT_OVERFLOW(result)) { op = FROM_INT (result); break; } } } PREPARE_STACK (); EXPORT_REGS (); SEND_MESSAGE (_gst_builtin_selectors[BIT_SHIFT_SPECIAL].symbol, 1); IMPORT_REGS (); FETCH; } operation INTEGER_DIVIDE_SPECIAL ( op1 op2 -- op1 op2 ) { PREPARE_STACK (); EXPORT_REGS(); if (IS_INT (op1) && IS_INT (op2) && !VMpr_SmallInteger_intDiv (12, 1)) { IMPORT_REGS (); NEXT_BC; } SEND_MESSAGE (_gst_builtin_selectors[INTEGER_DIVIDE_SPECIAL].symbol, 1); IMPORT_REGS (); FETCH; } operation BIT_AND_SPECIAL ( op1 op2 -- op ) { op = tagged_and (op1, op2); if COMMON (IS_INT (op)) break; PREPARE_STACK (); EXPORT_REGS (); SEND_MESSAGE (_gst_builtin_selectors[BIT_AND_SPECIAL].symbol, 1); IMPORT_REGS (); FETCH; } operation BIT_OR_SPECIAL ( op1 op2 -- op ) { if COMMON (ARE_INTS (op1, op2)) { op = tagged_or (op1, op2); break; } PREPARE_STACK (); EXPORT_REGS (); SEND_MESSAGE (_gst_builtin_selectors[BIT_OR_SPECIAL].symbol, 1); IMPORT_REGS (); FETCH; } operation AT_SPECIAL ( rec idx -- val ) { OOP classOOP; PREPARE_STACK (); EXPORT_REGS (); if UNCOMMON (IS_INT (rec)) { SEND_MESSAGE (_gst_builtin_selectors[AT_SPECIAL].symbol, 1); IMPORT_REGS (); FETCH; } if COMMON (at_cache_class == (classOOP = OOP_CLASS (rec)) && !cached_index_oop_primitive (rec, idx, at_cache_spec)) { IMPORT_REGS (); NEXT_BC; } /* Not the same class that is in the cache, or the primitive failed -- send the message, and modify the cache if the send is resolved to a primitive. */ last_primitive = 0; SEND_MESSAGE (_gst_builtin_selectors[AT_SPECIAL].symbol, 1); IMPORT_REGS (); if (_gst_primitive_table[last_primitive].id == 60) { at_cache_spec = CLASS_INSTANCE_SPEC (classOOP); at_cache_class = classOOP; NEXT_BC; } FETCH; } operation AT_PUT_SPECIAL ( rec idx val -- res ) { OOP classOOP; PREPARE_STACK (); EXPORT_REGS (); if UNCOMMON (IS_INT (rec)) { SEND_MESSAGE (_gst_builtin_selectors[AT_PUT_SPECIAL].symbol, 2); IMPORT_REGS (); FETCH; } if COMMON (at_put_cache_class == (classOOP = OOP_CLASS (rec)) && !cached_index_oop_put_primitive (rec, idx, val, at_put_cache_spec)) { IMPORT_REGS (); NEXT_BC; } /* Not the same class that is in the cache, or the primitive failed -- send the message, and modify the cache if the send is resolved to a primitive. */ last_primitive = 0; SEND_MESSAGE (_gst_builtin_selectors[AT_PUT_SPECIAL].symbol, 2); IMPORT_REGS (); if (_gst_primitive_table[last_primitive].id == 61) { at_put_cache_spec = CLASS_INSTANCE_SPEC (classOOP); at_put_cache_class = classOOP; NEXT_BC; } FETCH; } operation SIZE_SPECIAL ( rec -- val ) { OOP classOOP; PREPARE_STACK (); EXPORT_REGS (); if UNCOMMON (IS_INT (rec)) { SEND_MESSAGE (_gst_builtin_selectors[SIZE_SPECIAL].symbol, 0); IMPORT_REGS (); FETCH; } if COMMON (size_cache_class == (classOOP = OOP_CLASS (rec)) && !execute_primitive_operation (size_cache_prim, 0)) { IMPORT_REGS (); NEXT_BC; } /* Not the same class that is in the cache, or the primitive failed -- send the message, and modify the cache if the send is resolved to a primitive. */ last_primitive = 0; SEND_MESSAGE (_gst_builtin_selectors[SIZE_SPECIAL].symbol, 0); IMPORT_REGS (); if COMMON (last_primitive) { size_cache_prim = last_primitive; size_cache_class = classOOP; NEXT_BC; } FETCH; } operation CLASS_SPECIAL ( rec -- val ) { OOP classOOP; PREPARE_STACK (); EXPORT_REGS (); if UNCOMMON (IS_INT (rec)) { SEND_MESSAGE (_gst_builtin_selectors[CLASS_SPECIAL].symbol, 0); IMPORT_REGS (); FETCH; } if COMMON (class_cache_class == (classOOP = OOP_CLASS (rec)) && !execute_primitive_operation (class_cache_prim, 1)) { IMPORT_REGS (); NEXT_BC; } /* Not the same class that is in the cache, or the primitive failed -- send the message, and modify the cache if the send is resolved to a primitive. */ last_primitive = 0; SEND_MESSAGE (_gst_builtin_selectors[CLASS_SPECIAL].symbol, 0); IMPORT_REGS (); if COMMON (last_primitive) { class_cache_prim = last_primitive; class_cache_class = classOOP; NEXT_BC; } FETCH; } operation IS_NIL_SPECIAL ( rec -- val ) { /* DO_JUMP_LOOKAHEAD (rec == _gst_nil_oop); */ val = rec == _gst_nil_oop ? _gst_true_oop : _gst_false_oop; } operation NOT_NIL_SPECIAL ( rec -- val ) { /* DO_JUMP_LOOKAHEAD (rec != _gst_nil_oop); */ val = rec != _gst_nil_oop ? _gst_true_oop : _gst_false_oop; } operation VALUE_SPECIAL ( rec -- rec ) { PREPARE_STACK (); EXPORT_REGS (); if (UNCOMMON (IS_INT (rec)) || UNCOMMON (OOP_CLASS (rec) != _gst_block_closure_class) || UNCOMMON (send_block_value (0, 0))) SEND_MESSAGE (_gst_builtin_selectors[VALUE_SPECIAL].symbol, 0); IMPORT_REGS (); FETCH; } operation VALUE_COLON_SPECIAL ( rec blk_arg -- rec blk_arg ) { PREPARE_STACK (); EXPORT_REGS (); if (UNCOMMON (IS_INT (rec)) || UNCOMMON (OOP_CLASS (rec) != _gst_block_closure_class) || UNCOMMON (send_block_value (1, 0))) SEND_MESSAGE (_gst_builtin_selectors[VALUE_COLON_SPECIAL].symbol, 1); IMPORT_REGS (); FETCH; } operation SAME_OBJECT_SPECIAL ( op1 op2 -- op ) { /* DO_JUMP_LOOKAHEAD (op1 == op2); */ op = (op1 == op2) ? _gst_true_oop : _gst_false_oop; } operation JAVA_AS_INT_SPECIAL ( rec -- val ) { if COMMON (IS_INT (rec) || is_c_int_32 (rec)) { val = rec; break; } PREPARE_STACK (); EXPORT_REGS (); SEND_MESSAGE (_gst_builtin_selectors[JAVA_AS_INT_SPECIAL].symbol, 0); IMPORT_REGS (); FETCH; } operation JAVA_AS_LONG_SPECIAL ( rec -- val ) { if COMMON (IS_INT (rec) || is_c_int_64 (rec)) { val = rec; break; } PREPARE_STACK (); EXPORT_REGS (); SEND_MESSAGE (_gst_builtin_selectors[JAVA_AS_LONG_SPECIAL].symbol, 0); IMPORT_REGS (); FETCH; } operation SEND sel n ( -- ) { PREPARE_STACK (); EXPORT_REGS (); SEND_MESSAGE (METHOD_LITERAL (sel), n); IMPORT_REGS (); FETCH; } operation SEND_SUPER sel n ( -- ) { OOP classOOP; PREPARE_STACK (); classOOP = POP_OOP (); EXPORT_REGS (); SEND_TO_SUPER (METHOD_LITERAL (sel), n, classOOP); IMPORT_REGS (); FETCH; } operation SEND_IMMEDIATE n ( -- ) { const struct builtin_selector *bs = &_gst_builtin_selectors[n]; PREPARE_STACK (); EXPORT_REGS (); SEND_MESSAGE (bs->symbol, bs->numArgs); IMPORT_REGS (); FETCH; } operation SEND_SUPER_IMMEDIATE n ( -- ) { OOP classOOP; const struct builtin_selector *bs = &_gst_builtin_selectors[n]; PREPARE_STACK (); classOOP = POP_OOP (); EXPORT_REGS (); SEND_TO_SUPER (bs->symbol, bs->numArgs, classOOP); IMPORT_REGS (); FETCH; } operation PUSH_TEMPORARY_VARIABLE n ( -- tos ) { tos = METHOD_TEMPORARY (n); } operation PUSH_OUTER_TEMP n scopes ( -- tos ) { OOP contextOOP; gst_block_context context; context = (gst_block_context) OOP_TO_OBJ (_gst_this_context_oop); do { contextOOP = context->outerContext; context = (gst_block_context) OOP_TO_OBJ (contextOOP); } while (--scopes); tos = context->contextStack[n]; } operation PUSH_LIT_VARIABLE n ( -- tos ) { tos = METHOD_LITERAL (n); if (UNCOMMON (IS_INT (tos)) || UNCOMMON (!is_a_kind_of (OOP_CLASS (tos), _gst_association_class))) { PREPARE_STACK (); PUSH_OOP (tos); EXPORT_REGS (); SEND_MESSAGE (_gst_builtin_selectors[VALUE_SPECIAL].symbol, 0); IMPORT_REGS (); FETCH; } else tos = ASSOCIATION_VALUE (tos); } operation PUSH_RECEIVER_VARIABLE n ( -- tos ) { tos = RECEIVER_VARIABLE (n); } operation STORE_TEMPORARY_VARIABLE n ( tos -- tos ) { STORE_METHOD_TEMPORARY (n, tos); } operation STORE_OUTER_TEMP n scopes ( tos -- tos ) { OOP contextOOP; gst_block_context context; context = (gst_block_context) OOP_TO_OBJ (_gst_this_context_oop); do { contextOOP = context->outerContext; context = (gst_block_context) OOP_TO_OBJ (contextOOP); } while (--scopes); context->contextStack[n] = tos; } operation STORE_LIT_VARIABLE n ( tos -- tos ) { OOP var = METHOD_LITERAL (n), value = tos; if (UNCOMMON (IS_INT (var)) || UNCOMMON (!is_a_kind_of (OOP_CLASS (var), _gst_association_class))) { PREPARE_STACK (); SET_STACKTOP (var); PUSH_OOP (value); EXPORT_REGS (); SEND_MESSAGE (_gst_builtin_selectors[VALUE_COLON_SPECIAL].symbol, 1); IMPORT_REGS (); FETCH; } else SET_ASSOCIATION_VALUE (var, value); } operation STORE_RECEIVER_VARIABLE n ( tos -- tos ) { STORE_RECEIVER_VARIABLE (n, tos); } operation JUMP_BACK n ( -- ) { PREPARE_STACK (); ip -= n; FETCH; } operation JUMP n ( -- ) { PREPARE_STACK (); ip += n; FETCH; } operation POP_JUMP_FALSE n ( tos -- ) { if UNCOMMON (tos == _gst_false_oop) { PREPARE_STACK (); POP_N_OOPS(1); ip += n; FETCH; } else if UNCOMMON (tos != _gst_true_oop) { ip += n; PREPARE_STACK (); EXPORT_REGS(); SEND_MESSAGE(_gst_must_be_boolean_symbol, 0); IMPORT_REGS(); FETCH; } } operation POP_JUMP_TRUE n ( tos -- ) { if UNCOMMON (tos == _gst_true_oop) { PREPARE_STACK (); POP_N_OOPS(1); ip += n; FETCH; } else if UNCOMMON (tos != _gst_false_oop) { ip += n; PREPARE_STACK (); EXPORT_REGS(); SEND_MESSAGE(_gst_must_be_boolean_symbol, 0); IMPORT_REGS(); FETCH; } } operation PUSH_INTEGER n ( -- tos ) { tos = FROM_INT (n); } operation PUSH_SPECIAL n ( -- tos ) { tos = _gst_nil_oop + (n - NIL_INDEX); } operation PUSH_LIT_CONSTANT n ( -- tos ) { tos = METHOD_LITERAL (n); } operation POP_INTO_NEW_STACKTOP n ( obj val -- obj ) { STORE_INSTANCE_VARIABLE (obj, n, val); } operation POP_STACK_TOP ( tos -- ) { } operation MAKE_DIRTY_BLOCK ( block -- closure ) { EXPORT_REGS (); closure = _gst_make_block_closure (block); IMPORT_REGS(); } operation RETURN_METHOD_STACK_TOP ( val -- val ) { EXPORT_REGS (); if UNCOMMON (!unwind_method ()) { SEND_MESSAGE (_gst_bad_return_error_symbol, 0); IMPORT_REGS (); } else { IMPORT_REGS (); SET_STACKTOP (val); } FETCH; } operation RETURN_CONTEXT_STACK_TOP ( val -- val ) { EXPORT_REGS (); unwind_context (); IMPORT_REGS (); SET_STACKTOP (val); FETCH; } operation DUP_STACK_TOP ( tos -- tos tos2 ) { tos2 = tos; } operation EXIT_INTERPRETER ( val -- val ) { /* This fixes a very rare condition, but it can happen: GC can happen because send_message_internal allocates a context while the interpreter is checking last_primitive to fill the special cache for #at:, #at:put: and #size. If there are finalizable objects, the finalization callins might change last_primitive to a bogus value. To fix the problem, we invalidate last_primitive every time the interpreter exits. */ last_primitive = 0; { OOP activeProcessOOP = get_scheduled_process (); gst_callin_process process = (gst_callin_process) OOP_TO_OBJ (activeProcessOOP); if (IS_NIL (activeProcessOOP)) abort (); if (process->objClass == _gst_callin_process_class) process->returnedValue = val; _gst_terminate_process (activeProcessOOP); if (processOOP == activeProcessOOP) SET_EXCEPT_FLAG (true); } FETCH; } operation LINE_NUMBER_BYTECODE ( -- ) { } operation PUSH_SELF ( -- tos ) { tos = _gst_self; } table monitored_byte_codes { 0..255 = monitor_byte_codes } /* for jump lookahead */ table true_byte_codes { 0..41 = lookahead_failed_true, 42 = bc41, /* pop/jump if true ==> jump */ 43 = bc54, /* pop/jump if false ==> nop */ 44..51 = lookahead_failed_true, 52 = lookahead_dup_true, 53..255 = lookahead_failed_true } table false_byte_codes { 0..41 = lookahead_failed_false, 42 = bc54, /* pop/jump if true ==> nop */ 43 = bc41, /* pop/jump if false ==> jump */ 44..51 = lookahead_failed_false, 52 = lookahead_dup_false, 53..255 = lookahead_failed_false } /* Automatically generated by superops. Do not modify past this line! */ table normal_byte_codes { 0 = bytecode bc0 { PREFETCH (); PLUS_SPECIAL (); } 1 = bytecode bc1 { PREFETCH (); MINUS_SPECIAL (); } 2 = bytecode bc2 { PREFETCH (); LESS_THAN_SPECIAL (); } 3 = bytecode bc3 { PREFETCH (); GREATER_THAN_SPECIAL (); } 4 = bytecode bc4 { PREFETCH (); LESS_EQUAL_SPECIAL (); } 5 = bytecode bc5 { PREFETCH (); GREATER_EQUAL_SPECIAL (); } 6 = bytecode bc6 { PREFETCH (); EQUAL_SPECIAL (); } 7 = bytecode bc7 { PREFETCH (); NOT_EQUAL_SPECIAL (); } 8 = bytecode bc8 { PREFETCH (); TIMES_SPECIAL (); } 9 = bytecode bc9 { PREFETCH (); DIVIDE_SPECIAL (); } 10 = bytecode bc10 { PREFETCH (); REMAINDER_SPECIAL (); } 11 = bytecode bc11 { PREFETCH (); BIT_XOR_SPECIAL (); } 12 = bytecode bc12 { PREFETCH (); BIT_SHIFT_SPECIAL (); } 13 = bytecode bc13 { PREFETCH (); INTEGER_DIVIDE_SPECIAL (); } 14 = bytecode bc14 { PREFETCH (); BIT_AND_SPECIAL (); } 15 = bytecode bc15 { PREFETCH (); BIT_OR_SPECIAL (); } 16 = bytecode bc16 { PREFETCH (); AT_SPECIAL (); } 17 = bytecode bc17 { PREFETCH (); AT_PUT_SPECIAL (); } 18 = bytecode bc18 { PREFETCH (); SIZE_SPECIAL (); } 19 = bytecode bc19 { PREFETCH (); CLASS_SPECIAL (); } 20 = bytecode bc20 { PREFETCH (); IS_NIL_SPECIAL (); } 21 = bytecode bc21 { PREFETCH (); NOT_NIL_SPECIAL (); } 22 = bytecode bc22 { PREFETCH (); VALUE_SPECIAL (); } 23 = bytecode bc23 { PREFETCH (); VALUE_COLON_SPECIAL (); } 24 = bytecode bc24 { PREFETCH (); SAME_OBJECT_SPECIAL (); } 25 = bytecode bc25 { PREFETCH (); JAVA_AS_INT_SPECIAL (); } 26 = bytecode bc26 { PREFETCH (); JAVA_AS_LONG_SPECIAL (); } 27 = bytecode bc27 { PREFETCH (); INVALID (arg); } 28 = bytecode bc28 { PREFETCH (); SEND (arg >> 8, arg & 255); } 29 = bytecode bc29 { PREFETCH (); SEND_SUPER (arg >> 8, arg & 255); } 30 = bytecode bc30 { PREFETCH (); SEND_IMMEDIATE (arg); } 31 = bytecode bc31 { PREFETCH (); SEND_SUPER_IMMEDIATE (arg); } 32 = bytecode bc32 { PREFETCH (); PUSH_TEMPORARY_VARIABLE (arg); } 33 = bytecode bc33 { PREFETCH (); PUSH_OUTER_TEMP (arg >> 8, arg & 255); } 34 = bytecode bc34 { PREFETCH (); PUSH_LIT_VARIABLE (arg); } 35 = bytecode bc35 { PREFETCH (); PUSH_RECEIVER_VARIABLE (arg); } 36 = bytecode bc36 { PREFETCH (); STORE_TEMPORARY_VARIABLE (arg); } 37 = bytecode bc37 { PREFETCH (); STORE_OUTER_TEMP (arg >> 8, arg & 255); } 38 = bytecode bc38 { PREFETCH (); STORE_LIT_VARIABLE (arg); } 39 = bytecode bc39 { PREFETCH (); STORE_RECEIVER_VARIABLE (arg); } 40 = bytecode bc40 { ADVANCE (); JUMP_BACK (arg); } 41 = bytecode bc41 { ADVANCE (); JUMP (arg); } 42 = bytecode bc42 { PREFETCH (); POP_JUMP_TRUE (arg); } 43 = bytecode bc43 { PREFETCH (); POP_JUMP_FALSE (arg); } 44 = bytecode bc44 { PREFETCH (); PUSH_INTEGER (arg); } 45 = bytecode bc45 { PREFETCH (); PUSH_SPECIAL (arg); } 46 = bytecode bc46 { PREFETCH (); PUSH_LIT_CONSTANT (arg); } 47 = bytecode bc47 { PREFETCH (); POP_INTO_NEW_STACKTOP (arg); } 48 = bytecode bc48 { PREFETCH (); POP_STACK_TOP (); } 49 = bytecode bc49 { PREFETCH (); MAKE_DIRTY_BLOCK (); } 50 = bytecode bc50 { PREFETCH (); RETURN_METHOD_STACK_TOP (); } 51 = bytecode bc51 { PREFETCH (); RETURN_CONTEXT_STACK_TOP (); } 52 = bytecode bc52 { PREFETCH (); DUP_STACK_TOP (); } 53 = bytecode bc53 { PREFETCH (); EXIT_INTERPRETER (); } 54 = bytecode bc54 { PREFETCH (); LINE_NUMBER_BYTECODE (); } 55 = bytecode bc55 { EXT_BYTE (); } 56 = bytecode bc56 { PREFETCH (); PUSH_SELF (); } 57 = bytecode bc57 { PREFETCH (); INVALID (arg); } 58 = bytecode bc58 { PREFETCH (); INVALID (arg); } 59 = bytecode bc59 { PREFETCH (); INVALID (arg); } 60 = bytecode bc60 { PREFETCH (); INVALID (arg); } 61 = bytecode bc61 { PREFETCH (); INVALID (arg); } 62 = bytecode bc62 { PREFETCH (); INVALID (arg); } 63 = bytecode bc63 { PREFETCH (); INVALID (arg); } 64 = bytecode bc64 { PREFETCH (); SEND (arg, 1); } 65 = bytecode bc65 { PREFETCH (); SEND (arg, 0); } 66 = bytecode bc66 { PREFETCH (); PUSH_SELF (); RETURN_CONTEXT_STACK_TOP (); } 67 = bytecode bc67 { PREFETCH (); LINE_NUMBER_BYTECODE (); PUSH_SELF (); } 68 = bytecode bc68 { PREFETCH (); LINE_NUMBER_BYTECODE (); POP_STACK_TOP (); } 69 = bytecode bc69 { PREFETCH (); LINE_NUMBER_BYTECODE (); PUSH_TEMPORARY_VARIABLE (0); } 70 = bytecode bc70 { PREFETCH (); PUSH_LIT_CONSTANT (arg); MAKE_DIRTY_BLOCK (); } 71 = bytecode bc71 { PREFETCH (); SEND (arg, 2); } 72 = bytecode bc72 { PREFETCH (); POP_STACK_TOP (); DUP_STACK_TOP (); } 73 = bytecode bc73 { PREFETCH (); PUSH_TEMPORARY_VARIABLE (0); SEND_IMMEDIATE (arg); } 74 = bytecode bc74 { PREFETCH (); PUSH_SELF (); SEND (arg, 0); } 75 = bytecode bc75 { PREFETCH (); PUSH_SPECIAL (arg); RETURN_CONTEXT_STACK_TOP (); } 76 = bytecode bc76 { PREFETCH (); PUSH_SELF (); SEND_IMMEDIATE (arg); } 77 = bytecode bc77 { PREFETCH (); PUSH_OUTER_TEMP (arg, 1); } 78 = bytecode bc78 { PREFETCH (); STORE_TEMPORARY_VARIABLE (arg); POP_STACK_TOP (); } 79 = bytecode bc79 { PREFETCH (); PUSH_SELF (); PUSH_TEMPORARY_VARIABLE (arg); } 80 = bytecode bc80 { PREFETCH (); STORE_RECEIVER_VARIABLE (arg); PUSH_SELF (); RETURN_CONTEXT_STACK_TOP (); } 81 = bytecode bc81 { PREFETCH (); PUSH_INTEGER (arg); PLUS_SPECIAL (); } 82 = bytecode bc82 { PREFETCH (); LINE_NUMBER_BYTECODE (); PUSH_LIT_VARIABLE (0); } 83 = bytecode bc83 { PREFETCH (); PUSH_TEMPORARY_VARIABLE (0); PUSH_TEMPORARY_VARIABLE (arg); } 84 = bytecode bc84 { PREFETCH (); PUSH_TEMPORARY_VARIABLE (0); SEND (arg >> 8, arg & 255); } 85 = bytecode bc85 { PREFETCH (); LINE_NUMBER_BYTECODE (); PUSH_TEMPORARY_VARIABLE (1); } 86 = bytecode bc86 { PREFETCH (); IS_NIL_SPECIAL (); POP_JUMP_FALSE (arg); } 87 = bytecode bc87 { PREFETCH (); PUSH_INTEGER (arg); EQUAL_SPECIAL (); } 88 = bytecode bc88 { PREFETCH (); SEND (arg, 3); } 89 = bytecode bc89 { PREFETCH (); PUSH_TEMPORARY_VARIABLE (0); SEND (arg, 1); } 90 = bytecode bc90 { PREFETCH (); LINE_NUMBER_BYTECODE (); PUSH_SELF (); SEND (0, 0); } 91 = bytecode bc91 { PREFETCH (); PUSH_TEMPORARY_VARIABLE (arg); RETURN_CONTEXT_STACK_TOP (); } 92 = bytecode bc92 { PREFETCH (); PUSH_LIT_CONSTANT (arg); SEND_IMMEDIATE (36); } 93 = bytecode bc93 { PREFETCH (); SAME_OBJECT_SPECIAL (); POP_JUMP_FALSE (arg); } 94 = bytecode bc94 { PREFETCH (); PUSH_LIT_CONSTANT (arg); SEND (1, 1); } 95 = bytecode bc95 { PREFETCH (); LINE_NUMBER_BYTECODE (); POP_STACK_TOP (); PUSH_SELF (); } 96 = bytecode bc96 { PREFETCH (); POP_STACK_TOP (); DUP_STACK_TOP (); LINE_NUMBER_BYTECODE (); } 97 = bytecode bc97 { PREFETCH (); PUSH_TEMPORARY_VARIABLE (0); SEND (arg, 0); } 98 = bytecode bc98 { PREFETCH (); PUSH_TEMPORARY_VARIABLE (1); SEND_IMMEDIATE (arg); } 99 = bytecode bc99 { PREFETCH (); PUSH_LIT_CONSTANT (arg); EQUAL_SPECIAL (); } 100 = bytecode bc100 { PREFETCH (); PUSH_INTEGER (arg); MINUS_SPECIAL (); } 101 = bytecode bc101 { PREFETCH (); DUP_STACK_TOP (); POP_JUMP_FALSE (arg); } 102 = bytecode bc102 { PREFETCH (); POP_STACK_TOP (); LINE_NUMBER_BYTECODE (); } 103 = bytecode bc103 { PREFETCH (); PUSH_INTEGER (arg); SEND_IMMEDIATE (32); } 104 = bytecode bc104 { PREFETCH (); PUSH_TEMPORARY_VARIABLE (arg); SIZE_SPECIAL (); } 105 = bytecode bc105 { PREFETCH (); PUSH_SELF (); SEND (arg >> 8, arg & 255); } 106 = bytecode bc106 { PREFETCH (); LINE_NUMBER_BYTECODE (); PUSH_TEMPORARY_VARIABLE (2); } 107 = bytecode bc107 { PREFETCH (); POP_STACK_TOP (); SEND_IMMEDIATE (arg); } 108 = bytecode bc108 { PREFETCH (); PUSH_TEMPORARY_VARIABLE (arg); PUSH_INTEGER (1); PLUS_SPECIAL (); } 109 = bytecode bc109 { PREFETCH (); LINE_NUMBER_BYTECODE (); PUSH_RECEIVER_VARIABLE (0); } 110 = bytecode bc110 { PREFETCH (); PUSH_LIT_CONSTANT (arg); SEND_IMMEDIATE (38); } 111 = bytecode bc111 { PREFETCH (); PUSH_INTEGER (arg); AT_SPECIAL (); } 112 = bytecode bc112 { PREFETCH (); LINE_NUMBER_BYTECODE (); PUSH_RECEIVER_VARIABLE (1); } 113 = bytecode bc113 { PREFETCH (); PUSH_TEMPORARY_VARIABLE (0); PUSH_LIT_CONSTANT (arg); } 114 = bytecode bc114 { PREFETCH (); DUP_STACK_TOP (); POP_JUMP_TRUE (arg); } 115 = bytecode bc115 { PREFETCH (); PUSH_TEMPORARY_VARIABLE (arg); AT_SPECIAL (); } 116 = bytecode bc116 { PREFETCH (); PUSH_TEMPORARY_VARIABLE (2); SEND_IMMEDIATE (arg); } 117 = bytecode bc117 { PREFETCH (); PUSH_LIT_CONSTANT (arg); SEND_IMMEDIATE (49); } 118 = bytecode bc118 { PREFETCH (); STORE_TEMPORARY_VARIABLE (1); LINE_NUMBER_BYTECODE (); POP_STACK_TOP (); } 119 = bytecode bc119 { PREFETCH (); PUSH_TEMPORARY_VARIABLE (1); SEND (arg, 1); } 120 = bytecode bc120 { PREFETCH (); STORE_RECEIVER_VARIABLE (arg); POP_STACK_TOP (); } 121 = bytecode bc121 { PREFETCH (); STORE_OUTER_TEMP (arg, 1); } 122 = bytecode bc122 { PREFETCH (); PUSH_INTEGER (arg); SEND_IMMEDIATE (96); } 123 = bytecode bc123 { PREFETCH (); POP_STACK_TOP (); PUSH_TEMPORARY_VARIABLE (arg); } 124 = bytecode bc124 { PREFETCH (); PUSH_RECEIVER_VARIABLE (arg); RETURN_CONTEXT_STACK_TOP (); } 125 = bytecode bc125 { PREFETCH (); LINE_NUMBER_BYTECODE (); POP_STACK_TOP (); PUSH_TEMPORARY_VARIABLE (1); } 126 = bytecode bc126 { PREFETCH (); LINE_NUMBER_BYTECODE (); POP_STACK_TOP (); PUSH_TEMPORARY_VARIABLE (0); } 127 = bytecode bc127 { PREFETCH (); LINE_NUMBER_BYTECODE (); PUSH_SELF (); PUSH_LIT_CONSTANT (0); } 128 = bytecode bc128 { PREFETCH (); PUSH_LIT_CONSTANT (arg); RETURN_CONTEXT_STACK_TOP (); } 129 = bytecode bc129 { PREFETCH (); PUSH_SELF (); SIZE_SPECIAL (); } 130 = bytecode bc130 { PREFETCH (); IS_NIL_SPECIAL (); POP_JUMP_TRUE (arg); } 131 = bytecode bc131 { PREFETCH (); PUSH_TEMPORARY_VARIABLE (arg); AT_PUT_SPECIAL (); } 132 = bytecode bc132 { PREFETCH (); LINE_NUMBER_BYTECODE (); PUSH_LIT_VARIABLE (1); } 133 = bytecode bc133 { PREFETCH (); PUSH_TEMPORARY_VARIABLE (arg); PLUS_SPECIAL (); } 134 = bytecode bc134 { ADVANCE (); POP_STACK_TOP (); JUMP_BACK (arg); } 135 = bytecode bc135 { PREFETCH (); POP_STACK_TOP (); PUSH_LIT_VARIABLE (arg); } 136 = bytecode bc136 { PREFETCH (); PUSH_INTEGER (1); STORE_TEMPORARY_VARIABLE (arg); } 137 = bytecode bc137 { PREFETCH (); PUSH_LIT_CONSTANT (arg); SEND (2, 1); } 138 = bytecode bc138 { PREFETCH (); LINE_NUMBER_BYTECODE (); PUSH_TEMPORARY_VARIABLE (3); } 139 = bytecode bc139 { PREFETCH (); LINE_NUMBER_BYTECODE (); PUSH_OUTER_TEMP (0, 1); } 140 = bytecode bc140 { PREFETCH (); PUSH_RECEIVER_VARIABLE (arg); SEND (0, 0); } 141 = bytecode bc141 { PREFETCH (); PUSH_INTEGER (arg); GREATER_THAN_SPECIAL (); } 142 = bytecode bc142 { PREFETCH (); PUSH_TEMPORARY_VARIABLE (arg); VALUE_SPECIAL (); } 143 = bytecode bc143 { PREFETCH (); PUSH_TEMPORARY_VARIABLE (arg); MINUS_SPECIAL (); } 144 = bytecode bc144 { PREFETCH (); PUSH_LIT_CONSTANT (arg); SEND (3, 1); } 145 = bytecode bc145 { PREFETCH (); PUSH_SPECIAL (0); SAME_OBJECT_SPECIAL (); POP_JUMP_FALSE (arg); } 146 = bytecode bc146 { PREFETCH (); STORE_TEMPORARY_VARIABLE (2); LINE_NUMBER_BYTECODE (); POP_STACK_TOP (); } 147 = bytecode bc147 { PREFETCH (); SAME_OBJECT_SPECIAL (); POP_JUMP_TRUE (arg); } 148 = bytecode bc148 { PREFETCH (); PUSH_INTEGER (arg); TIMES_SPECIAL (); } 149 = bytecode bc149 { PREFETCH (); LINE_NUMBER_BYTECODE (); PUSH_RECEIVER_VARIABLE (2); } 150 = bytecode bc150 { PREFETCH (); PUSH_INTEGER (arg); LESS_THAN_SPECIAL (); } 151 = bytecode bc151 { PREFETCH (); PUSH_LIT_CONSTANT (arg); AT_PUT_SPECIAL (); } 152 = bytecode bc152 { PREFETCH (); PUSH_OUTER_TEMP (arg, 2); } 153 = bytecode bc153 { PREFETCH (); LINE_NUMBER_BYTECODE (); PUSH_SELF (); PUSH_TEMPORARY_VARIABLE (0); SEND (0, 1); } 154 = bytecode bc154 { PREFETCH (); PUSH_SELF (); PUSH_TEMPORARY_VARIABLE (0); SEND (arg, 1); } 155 = bytecode bc155 { PREFETCH (); LINE_NUMBER_BYTECODE (); PUSH_SELF (); SEND_IMMEDIATE (40); } 156 = bytecode bc156 { PREFETCH (); PUSH_TEMPORARY_VARIABLE (arg); PUSH_TEMPORARY_VARIABLE (3); } 157 = bytecode bc157 { PREFETCH (); STORE_TEMPORARY_VARIABLE (1); LINE_NUMBER_BYTECODE (); } 158 = bytecode bc158 { PREFETCH (); LINE_NUMBER_BYTECODE (); PUSH_TEMPORARY_VARIABLE (0); SEND (0, 0); } 159 = bytecode bc159 { PREFETCH (); PUSH_INTEGER (arg); BIT_AND_SPECIAL (); } 160 = bytecode bc160 { PREFETCH (); PUSH_TEMPORARY_VARIABLE (2); SEND (arg, 0); } 161 = bytecode bc161 { PREFETCH (); PUSH_TEMPORARY_VARIABLE (0); PUSH_TEMPORARY_VARIABLE (1); SEND (arg >> 8, arg & 255); } 162 = bytecode bc162 { PREFETCH (); LINE_NUMBER_BYTECODE (); PUSH_SELF (); PUSH_TEMPORARY_VARIABLE (0); } 163 = bytecode bc163 { PREFETCH (); LINE_NUMBER_BYTECODE (); PUSH_RECEIVER_VARIABLE (3); } 164 = bytecode bc164 { PREFETCH (); PUSH_TEMPORARY_VARIABLE (2); SEND (arg, 1); } 165 = bytecode bc165 { PREFETCH (); NOT_NIL_SPECIAL (); POP_JUMP_FALSE (arg); } 166 = bytecode bc166 { PREFETCH (); STORE_TEMPORARY_VARIABLE (2); LINE_NUMBER_BYTECODE (); } 167 = bytecode bc167 { PREFETCH (); STORE_TEMPORARY_VARIABLE (3); LINE_NUMBER_BYTECODE (); POP_STACK_TOP (); } 168 = bytecode bc168 { PREFETCH (); PUSH_LIT_CONSTANT (1); SEND_IMMEDIATE (arg); } 169 = bytecode bc169 { PREFETCH (); PUSH_TEMPORARY_VARIABLE (arg); EQUAL_SPECIAL (); } 170 = bytecode bc170 { PREFETCH (); POP_STACK_TOP (); DUP_STACK_TOP (); PUSH_TEMPORARY_VARIABLE (arg); PUSH_INTEGER (1); PLUS_SPECIAL (); } 171 = bytecode bc171 { PREFETCH (); PUSH_SELF (); SEND (arg, 1); } 172 = bytecode bc172 { PREFETCH (); STORE_TEMPORARY_VARIABLE (0); LINE_NUMBER_BYTECODE (); POP_STACK_TOP (); } 173 = bytecode bc173 { PREFETCH (); DUP_STACK_TOP (); LINE_NUMBER_BYTECODE (); } 174 = bytecode bc174 { PREFETCH (); PUSH_SELF (); PUSH_LIT_CONSTANT (arg); SEND_IMMEDIATE (49); } 175 = bytecode bc175 { PREFETCH (); POP_STACK_TOP (); PUSH_RECEIVER_VARIABLE (arg); } 176 = bytecode bc176 { PREFETCH (); LINE_NUMBER_BYTECODE (); PUSH_SELF (); SEND_IMMEDIATE (84); } 177 = bytecode bc177 { PREFETCH (); LINE_NUMBER_BYTECODE (); PUSH_LIT_VARIABLE (2); } 178 = bytecode bc178 { PREFETCH (); PUSH_LIT_CONSTANT (arg); MAKE_DIRTY_BLOCK (); SEND (3, 1); } 179 = bytecode bc179 { PREFETCH (); LINE_NUMBER_BYTECODE (); PUSH_LIT_CONSTANT (0); } 180 = bytecode bc180 { PREFETCH (); DUP_STACK_TOP (); PUSH_LIT_CONSTANT (arg); SEND_IMMEDIATE (36); } 181 = bytecode bc181 { PREFETCH (); LINE_NUMBER_BYTECODE (); PUSH_OUTER_TEMP (1, 1); } 182 = bytecode bc182 { PREFETCH (); PUSH_INTEGER (arg); INTEGER_DIVIDE_SPECIAL (); } 183 = bytecode bc183 { PREFETCH (); PUSH_LIT_CONSTANT (1); MAKE_DIRTY_BLOCK (); SEND_IMMEDIATE (arg); } 184 = bytecode bc184 { PREFETCH (); PUSH_TEMPORARY_VARIABLE (3); SEND_IMMEDIATE (arg); } 185 = bytecode bc185 { PREFETCH (); LINE_NUMBER_BYTECODE (); PUSH_SPECIAL (0); RETURN_CONTEXT_STACK_TOP (); } 186 = bytecode bc186 { PREFETCH (); LINE_NUMBER_BYTECODE (); PUSH_RECEIVER_VARIABLE (5); } 187 = bytecode bc187 { PREFETCH (); PUSH_LIT_CONSTANT (arg); MAKE_DIRTY_BLOCK (); SEND (2, 1); } 188 = bytecode bc188 { PREFETCH (); PUSH_TEMPORARY_VARIABLE (arg); VALUE_COLON_SPECIAL (); } 189 = bytecode bc189 { PREFETCH (); PUSH_INTEGER (arg); RETURN_CONTEXT_STACK_TOP (); } 190 = bytecode bc190 { PREFETCH (); PUSH_TEMPORARY_VARIABLE (0); SEND (arg, 2); } 191 = bytecode bc191 { PREFETCH (); PUSH_TEMPORARY_VARIABLE (arg); PUSH_INTEGER (1); MINUS_SPECIAL (); } 192 = bytecode bc192 { PREFETCH (); PUSH_SELF (); PUSH_LIT_CONSTANT (arg); } 193 = bytecode bc193 { PREFETCH (); LINE_NUMBER_BYTECODE (); PUSH_RECEIVER_VARIABLE (4); } 194 = bytecode bc194 { PREFETCH (); PUSH_OUTER_TEMP (0, 1); SEND_IMMEDIATE (arg); } 195 = bytecode bc195 { PREFETCH (); LINE_NUMBER_BYTECODE (); PUSH_SELF (); SEND (1, 0); } 196 = bytecode bc196 { PREFETCH (); PUSH_OUTER_TEMP (0, 1); SEND (arg, 1); } 197 = bytecode bc197 { PREFETCH (); PUSH_TEMPORARY_VARIABLE (4); SEND_IMMEDIATE (arg); } 198 = bytecode bc198 { PREFETCH (); PUSH_INTEGER (arg); SEND_IMMEDIATE (41); } 199 = bytecode bc199 { PREFETCH (); SEND (arg, 4); } 200 = bytecode bc200 { PREFETCH (); PUSH_TEMPORARY_VARIABLE (arg); PUSH_TEMPORARY_VARIABLE (2); } 201 = bytecode bc201 { PREFETCH (); PUSH_SELF (); CLASS_SPECIAL (); } 202 = bytecode bc202 { PREFETCH (); PUSH_TEMPORARY_VARIABLE (1); SEND (arg >> 8, arg & 255); } 203 = bytecode bc203 { PREFETCH (); PUSH_SELF (); PUSH_TEMPORARY_VARIABLE (1); SEND (arg, 1); } 204 = bytecode bc204 { PREFETCH (); PUSH_LIT_CONSTANT (arg); SEND (4, 1); } 205 = bytecode bc205 { PREFETCH (); PUSH_INTEGER (arg); SEND (0, 1); } 206 = bytecode bc206 { PREFETCH (); PUSH_RECEIVER_VARIABLE (arg); SIZE_SPECIAL (); } 207 = bytecode bc207 { PREFETCH (); PUSH_TEMPORARY_VARIABLE (1); SEND (arg, 2); } 208 = bytecode bc208 { PREFETCH (); PUSH_TEMPORARY_VARIABLE (0); PUSH_TEMPORARY_VARIABLE (1); SEND (arg, 2); } 209 = bytecode bc209 { PREFETCH (); PUSH_TEMPORARY_VARIABLE (arg); POP_INTO_NEW_STACKTOP (0); } 210 = bytecode bc210 { PREFETCH (); PUSH_LIT_CONSTANT (arg); MAKE_DIRTY_BLOCK (); SEND (5, 1); } 211 = bytecode bc211 { PREFETCH (); SEND_SUPER (arg, 1); } 212 = bytecode bc212 { PREFETCH (); PUSH_LIT_CONSTANT (arg); MAKE_DIRTY_BLOCK (); SEND (4, 1); } 213 = bytecode bc213 { PREFETCH (); PUSH_RECEIVER_VARIABLE (1); SEND_IMMEDIATE (arg); } 214 = bytecode bc214 { PREFETCH (); STORE_OUTER_TEMP (arg, 1); RETURN_CONTEXT_STACK_TOP (); } 215 = bytecode bc215 { PREFETCH (); POP_STACK_TOP (); LINE_NUMBER_BYTECODE (); SEND_IMMEDIATE (37); } 216 = bytecode bc216 { PREFETCH (); LINE_NUMBER_BYTECODE (); PUSH_SELF (); CLASS_SPECIAL (); } 217 = bytecode bc217 { PREFETCH (); PUSH_TEMPORARY_VARIABLE (1); SEND (arg, 0); } 218 = bytecode bc218 { PREFETCH (); LINE_NUMBER_BYTECODE (); PUSH_SELF (); SEND_IMMEDIATE (130); } 219 = bytecode bc219 { PREFETCH (); PUSH_RECEIVER_VARIABLE (0); SEND_IMMEDIATE (arg); } 220 = bytecode bc220 { PREFETCH (); PUSH_TEMPORARY_VARIABLE (0); PUSH_LIT_VARIABLE (arg); } 221 = bytecode bc221 { PREFETCH (); STORE_TEMPORARY_VARIABLE (0); LINE_NUMBER_BYTECODE (); } 222 = bytecode bc222 { PREFETCH (); PUSH_RECEIVER_VARIABLE (2); SEND_IMMEDIATE (arg); } 223 = bytecode bc223 { PREFETCH (); LINE_NUMBER_BYTECODE (); PUSH_SELF (); SEND (2, 0); } 224 = bytecode bc224 { PREFETCH (); LINE_NUMBER_BYTECODE (); POP_STACK_TOP (); PUSH_TEMPORARY_VARIABLE (2); } 225 = bytecode bc225 { PREFETCH (); PUSH_LIT_CONSTANT (arg); MAKE_DIRTY_BLOCK (); SEND (6, 1); } 226 = bytecode bc226 { PREFETCH (); PUSH_SPECIAL (arg); RETURN_METHOD_STACK_TOP (); } 227 = bytecode bc227 { PREFETCH (); PUSH_INTEGER (arg); GREATER_EQUAL_SPECIAL (); } 228 = bytecode bc228 { PREFETCH (); LINE_NUMBER_BYTECODE (); POP_STACK_TOP (); PUSH_RECEIVER_VARIABLE (1); } 229 = bytecode bc229 { PREFETCH (); LINE_NUMBER_BYTECODE (); PUSH_LIT_VARIABLE (3); } 230 = bytecode bc230 { PREFETCH (); PUSH_LIT_CONSTANT (2); SEND_IMMEDIATE (arg); } 231 = bytecode bc231 { PREFETCH (); SEND_SUPER (arg, 0); } 232 = bytecode bc232 { PREFETCH (); PUSH_SPECIAL (0); STORE_RECEIVER_VARIABLE (arg); } 233 = bytecode bc233 { PREFETCH (); PUSH_SELF (); PUSH_TEMPORARY_VARIABLE (arg); SEND (0, 1); } 234 = bytecode bc234 { PREFETCH (); LINE_NUMBER_BYTECODE (); POP_STACK_TOP (); PUSH_TEMPORARY_VARIABLE (0); RETURN_CONTEXT_STACK_TOP (); } 235 = bytecode bc235 { PREFETCH (); PUSH_LIT_CONSTANT (arg); SAME_OBJECT_SPECIAL (); } 236 = bytecode bc236 { PREFETCH (); PUSH_LIT_CONSTANT (arg); MAKE_DIRTY_BLOCK (); SEND (1, 1); } 237 = bytecode bc237 { PREFETCH (); LINE_NUMBER_BYTECODE (); POP_STACK_TOP (); PUSH_TEMPORARY_VARIABLE (3); } 238 = bytecode bc238 { PREFETCH (); POP_STACK_TOP (); DUP_STACK_TOP (); SEND_IMMEDIATE (arg); } 239 = bytecode bc239 { PREFETCH (); PUSH_LIT_CONSTANT (arg); PUSH_TEMPORARY_VARIABLE (0); AT_PUT_SPECIAL (); } 240 = bytecode bc240 { PREFETCH (); DUP_STACK_TOP (); PUSH_TEMPORARY_VARIABLE (arg); PUSH_INTEGER (1); PLUS_SPECIAL (); } 241 = bytecode bc241 { PREFETCH (); LINE_NUMBER_BYTECODE (); PUSH_TEMPORARY_VARIABLE (4); } 242 = bytecode bc242 { PREFETCH (); POP_STACK_TOP (); LINE_NUMBER_BYTECODE (); PUSH_LIT_VARIABLE (1); } 243 = bytecode bc243 { PREFETCH (); DUP_STACK_TOP (); PUSH_LIT_CONSTANT (arg); SEND (1, 1); } 244 = bytecode bc244 { PREFETCH (); POP_INTO_NEW_STACKTOP (1); SEND (arg, 1); } 245 = bytecode bc245 { PREFETCH (); LINE_NUMBER_BYTECODE (); POP_STACK_TOP (); PUSH_TEMPORARY_VARIABLE (1); RETURN_CONTEXT_STACK_TOP (); } 246 = bytecode bc246 { PREFETCH (); STORE_TEMPORARY_VARIABLE (3); LINE_NUMBER_BYTECODE (); } 247 = bytecode bc247 { PREFETCH (); DUP_STACK_TOP (); SEND (arg, 0); } 248 = bytecode bc248 { PREFETCH (); STORE_RECEIVER_VARIABLE (arg); RETURN_CONTEXT_STACK_TOP (); } 249 = bytecode bc249 { PREFETCH (); LINE_NUMBER_BYTECODE (); PUSH_SELF (); SEND (3, 0); } 250 = bytecode bc250 { PREFETCH (); NOT_NIL_SPECIAL (); DUP_STACK_TOP (); POP_JUMP_FALSE (arg); } 251 = bytecode bc251 { PREFETCH (); DUP_STACK_TOP (); PUSH_LIT_CONSTANT (arg); } 252 = bytecode bc252 { PREFETCH (); LINE_NUMBER_BYTECODE (); PUSH_TEMPORARY_VARIABLE (0); RETURN_CONTEXT_STACK_TOP (); } 253 = bytecode bc253 { PREFETCH (); PUSH_INTEGER (arg); AT_PUT_SPECIAL (); } 254 = bytecode bc254 { PREFETCH (); PUSH_TEMPORARY_VARIABLE (arg); CLASS_SPECIAL (); } 255 = bytecode bc255 { PREFETCH (); LINE_NUMBER_BYTECODE (); PUSH_OUTER_TEMP (2, 1); } } smalltalk-3.2.5/libgst/gst.h0000644000175000017500000001573312123404352012665 00000000000000/******************************** -*- C -*- **************************** * * GNU Smalltalk generic inclusions. * * ***********************************************************************/ /*********************************************************************** * * Copyright 1988,89,90,91,92,94,95,99,2000,2001,2002,2006,2008 * Free Software Foundation, Inc. * Written by Steve Byrne. * * This file is part of GNU Smalltalk. * * GNU Smalltalk is free software; you can redistribute it and/or modify it * under the terms of the GNU General Public License as published by the Free * Software Foundation; either version 2, or (at your option) any later * version. * * Linking GNU Smalltalk statically or dynamically with other modules is * making a combined work based on GNU Smalltalk. Thus, the terms and * conditions of the GNU General Public License cover the whole * combination. * * In addition, as a special exception, the Free Software Foundation * give you permission to combine GNU Smalltalk with free software * programs or libraries that are released under the GNU LGPL and with * independent programs running under the GNU Smalltalk virtual machine. * * You may copy and distribute such a system following the terms of the * GNU GPL for GNU Smalltalk and the licenses of the other code * concerned, provided that you include the source code of that other * code when and as the GNU GPL requires distribution of source code. * * Note that people who make modified versions of GNU Smalltalk are not * obligated to grant this special exception for their modified * versions; it is their choice whether to do so. The GNU General * Public License gives permission to release a modified version without * this exception; this exception also makes it possible to release a * modified version which carries forward this exception. * * GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or * FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for * more details. * * You should have received a copy of the GNU General Public License along with * GNU Smalltalk; see the file COPYING. If not, write to the Free Software * Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * ***********************************************************************/ #ifndef GST_GST_H #define GST_GST_H /* AIX is so broken that requires this to be the first thing in the file. */ #if defined(_AIX) #pragma alloca #else # if !defined(alloca) /* predefined by HP cc +Olibcalls */ # ifdef __GNUC__ # define alloca(size) __builtin_alloca(size) # else # if HAVE_ALLOCA_H # include # else # if defined(__hpux) void *alloca (); # else # if !defined(__OS2__) && !defined(WIN32) char *alloca (); # else # include /* OS/2 defines alloca in here */ # endif # endif # endif # endif # endif #endif /* Some compilers use different win32 definitions. Define WIN32 so we have only to check for one symbol. */ #if defined(_WIN32) || defined(__CYGWIN32__) || defined(__CYGWIN__) || defined(Win32) || defined(__WIN32) #ifndef WIN32 #define WIN32 1 #endif #endif #ifdef _MSC_VER /* Visual C++ does not define STDC */ #define __STDC__ 1 #endif /* Defined as char * in traditional compilers, void * in standard-compliant compilers. */ #ifndef PTR #if !defined(__STDC__) #define PTR char * #else #define PTR void * #endif #endif /* A boolean type */ #ifdef __cplusplus typedef bool mst_Boolean; #else typedef enum { false, true } mst_Boolean; #endif /* An indirect pointer to object data. */ typedef struct oop_s *OOP; /* A direct pointer to the object data. */ typedef struct object_s *gst_object, *mst_Object; /* The contents of an indirect pointer to object data. */ struct oop_s { gst_object object; unsigned long flags; /* FIXME, use uintptr_t */ }; /* The header of all objects in the system. Note how structural inheritance is achieved without adding extra levels of nested structures. */ #define OBJ_HEADER \ OOP objSize; \ OOP objClass /* Just for symbolic use in sizeof's */ typedef struct gst_object_header { OBJ_HEADER; } gst_object_header; #define OBJ_HEADER_SIZE_WORDS (sizeof(gst_object_header) / sizeof(PTR)) /* A bare-knuckles accessor for real objects */ struct object_s { OBJ_HEADER; OOP data[1]; /* variable length, may not be objects, but will always be at least this big. */ }; /* Convert an OOP (indirect pointer to an object) to the real object data. */ #define OOP_TO_OBJ(oop) \ ((oop)->object) /* Retrieve the class for the object pointed to by OOP. OOP must be a real pointer, not a SmallInteger. */ #define OOP_CLASS(oop) \ (OOP_TO_OBJ(oop)->objClass) /* Answer whether OOP is a SmallInteger or a `real' object pointer. */ #define IS_INT(oop) \ ((intptr_t)(oop) & 1) /* Answer whether both OOP1 and OOP2 are SmallIntegers, or rather at least one of them a `real' object pointer. */ #define ARE_INTS(oop1, oop2) \ ((intptr_t)(oop1) & (intptr_t)(oop2) & 1) /* Answer whether OOP is a `real' object pointer or rather a SmallInteger. */ #define IS_OOP(oop) \ (! IS_INT(oop) ) /* Keep these in sync with _gst_sizes, in dict.c. FIXME: these should be exported in a pool dictionary. */ enum gst_indexed_kind { GST_ISP_FIXED = 0, GST_ISP_SCHAR = 32, GST_ISP_UCHAR = 34, GST_ISP_CHARACTER = 36, GST_ISP_SHORT = 38, GST_ISP_USHORT = 40, GST_ISP_INT = 42, GST_ISP_UINT = 44, GST_ISP_FLOAT = 46, GST_ISP_INT64 = 48, GST_ISP_UINT64 = 50, GST_ISP_DOUBLE = 52, GST_ISP_UTF32 = 54, GST_ISP_LAST_SCALAR = 54, GST_ISP_POINTER = 62, #if SIZEOF_OOP == 8 GST_ISP_LONG = GST_ISP_INT64, GST_ISP_ULONG = GST_ISP_UINT64, GST_ISP_LAST_UNALIGNED = GST_ISP_FLOAT, #else GST_ISP_LONG = GST_ISP_INT, GST_ISP_ULONG = GST_ISP_UINT, GST_ISP_LAST_UNALIGNED = GST_ISP_USHORT, #endif }; /* enum types used by the public APIs. */ enum gst_file_dir { GST_DIR_ABS, GST_DIR_KERNEL_SYSTEM, GST_DIR_KERNEL, GST_DIR_BASE }; enum gst_var_index { GST_DECLARE_TRACING, GST_EXECUTION_TRACING, GST_EXECUTION_TRACING_VERBOSE, GST_GC_MESSAGE, GST_VERBOSITY, GST_MAKE_CORE_FILE, GST_REGRESSION_TESTING }; enum gst_init_flags { GST_REBUILD_IMAGE = 1, GST_MAYBE_REBUILD_IMAGE = 2, GST_IGNORE_USER_FILES = 4, GST_IGNORE_BAD_IMAGE_PATH = 8, GST_IGNORE_BAD_KERNEL_PATH = 16, GST_NO_TTY = 32, }; enum gst_vm_hook { GST_BEFORE_EVAL, GST_AFTER_EVAL, GST_RETURN_FROM_SNAPSHOT, GST_ABOUT_TO_QUIT, GST_ABOUT_TO_SNAPSHOT, GST_FINISHED_SNAPSHOT }; #define INDEXED_WORD(obj, n) ( ((long *) ((obj) + 1)) [(n)-1] ) #define INDEXED_BYTE(obj, n) ( ((char *) ((obj) + 1)) [(n)-1] ) #define INDEXED_OOP(obj, n) ( ((OOP *) ((obj) + 1)) [(n)-1] ) #define ARRAY_OOP_AT(obj, n) ( ((OOP *) ((gst_object) obj)->data) [(n)-1] ) #define STRING_OOP_AT(obj, n) ( ((char *) ((gst_object) obj)->data) [(n)-1] ) #endif /* GST_GST_H */ smalltalk-3.2.5/libgst/match.stamp0000644000175000017500000000001212130456004014040 00000000000000timestamp smalltalk-3.2.5/libgst/genbc.c0000644000175000017500000001017312123404352013132 00000000000000/******************************** -*- C -*- **************************** * * GNU Smalltalk genbc tool * ***********************************************************************/ /*********************************************************************** * * Copyright 2003, 2006 Free Software Foundation, Inc. * Written by Paolo Bonzini. * * This file is part of GNU Smalltalk. * * GNU Smalltalk is free software; you can redistribute it and/or modify it * under the terms of the GNU General Public License as published by the Free * Software Foundation; either version 2, or (at your option) any later * version. * * Linking GNU Smalltalk statically or dynamically with other modules is * making a combined work based on GNU Smalltalk. Thus, the terms and * conditions of the GNU General Public License cover the whole * combination. * * In addition, as a special exception, the Free Software Foundation * give you permission to combine GNU Smalltalk with free software * programs or libraries that are released under the GNU LGPL and with * independent programs running under the GNU Smalltalk virtual machine. * * You may copy and distribute such a system following the terms of the * GNU GPL for GNU Smalltalk and the licenses of the other code * concerned, provided that you include the source code of that other * code when and as the GNU GPL requires distribution of source code. * * Note that people who make modified versions of GNU Smalltalk are not * obligated to grant this special exception for their modified * versions; it is their choice whether to do so. The GNU General * Public License gives permission to release a modified version without * this exception; this exception also makes it possible to release a * modified version which carries forward this exception. * * GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or * FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for * more details. * * You should have received a copy of the GNU General Public License along with * GNU Smalltalk; see the file COPYING. If not, write to the Free Software * Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * ***********************************************************************/ #include "genbc.h" int errors = 0; const char *current_file; void yyprint (FILE *file, int type, YYSTYPE yylval) { switch (type) { case NUMBER: fprintf (file, "%d", yylval.num); break; case ID: case EXPR: fprintf (file, "%s", yylval.text); break; default: break; } } void yyerror (const char *s) { errors = 1; fprintf (stderr, "%s:%d: %s\n", current_file, yylineno, s); } /* Same as asprintf, but return the allocated string directly. */ char * my_asprintf (const char *fmt, ...) { va_list ap; char *s; va_start (ap, fmt); vasprintf (&s, fmt, ap); va_end (ap); return s; } int main(int argc, char **argv) { int i; if (argc < 2) { fprintf (stderr, "Usage: genbc ...\n"); errors = 1; } else { parse_declarations (argv[1]); if (errors) exit (errors); /* Emit the header guard. */ printf ("#ifndef GST_MATCH_H\n"); printf ("#define GST_MATCH_H\n\n"); /* Matchers are invoked by expanding a macro. The code for the matcher itself is similar enough to C that the preprocessor is not upset -- and the compiler never sees it. The MATCH_BYTECODES macro expands to the decoding code (which is common to all invocations of MATCH_BYTECODES), followed (via MATCH_BYTECODES_DISPATCH) by the action code that is specific to each occurrence of MATCH_BYTECODES. */ printf ("#define MATCH_BYTECODES(name_, bp_, code_) BEGIN_MACRO { \\\n"); emit_opcodes (); printf ("} END_MACRO\n"); printf ("\n"); printf ("#define MATCH_BYTECODES_DISPATCH(name) name\n"); for (i = 2; i < argc && !errors; i++) parse_implementation (argv[i]); /* End the header guard. */ printf ("#endif\n"); } exit (errors); } smalltalk-3.2.5/libgst/genvm-parse.c0000644000175000017500000020413412130455565014314 00000000000000/* A Bison parser, made by GNU Bison 2.5. */ /* Bison implementation for Yacc-like parsers in C Copyright (C) 1984, 1989-1990, 2000-2011 Free Software Foundation, Inc. This program is free software: you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation, either version 3 of the License, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program. If not, see . */ /* As a special exception, you may create a larger work that contains part or all of the Bison parser skeleton and distribute that work under terms of your choice, so long as that work isn't itself a parser generator using the skeleton or a modified version thereof as a parser skeleton. Alternatively, if you modify or redistribute the parser skeleton itself, you may (at your option) remove this special exception, which will cause the skeleton and the resulting Bison output files to be licensed under the GNU General Public License without this special exception. This special exception was added by the Free Software Foundation in version 2.2 of Bison. */ /* C LALR(1) parser skeleton written by Richard Stallman, by simplifying the original so-called "semantic" parser. */ /* All symbols defined below should begin with yy or YY, to avoid infringing on user name space. This should be done even for local variables, as they might otherwise be expanded by user macros. There are some unavoidable exceptions within include files to define necessary library symbols; they are noted "INFRINGES ON USER NAME SPACE" below. */ /* Identify Bison output. */ #define YYBISON 1 /* Bison version. */ #define YYBISON_VERSION "2.5" /* Skeleton name. */ #define YYSKELETON_NAME "yacc.c" /* Pure parsers. */ #define YYPURE 0 /* Push parsers. */ #define YYPUSH 0 /* Pull parsers. */ #define YYPULL 1 /* Using locations. */ #define YYLSP_NEEDED 0 /* Copy the first part of user declarations. */ /* Line 268 of yacc.c */ #line 53 "genvm-parse.y" #include "avltrees.h" #include "genvm.h" #include "genvm-parse.h" #define YYERROR_VERBOSE 1 typedef struct id_list { struct id_list *next; struct id_list **pnext; char id[1]; } id_list; typedef struct operation_info { avl_node_t avl; const char *name; struct id_list *args; struct id_list *in, *out, *read; int n_in, n_out, n_read; int needs_prepare_stack; int needs_branch_label; int instantiations; const char *code; } operation_info; typedef struct operation_list { struct operation_list *next; struct operation_list **pnext; operation_info *op; id_list *args; } operation_list; typedef struct table_info { char *name; char *entry[256]; id_list *pool; } table_info; #define YYPRINT(fp, tok, val) yyprint (fp, tok, &val) static int filprintf (Filament *fil, const char *format, ...); static void yyprint (FILE *fp, int tok, const YYSTYPE *val); static void yyerror (const char *s); static operation_info *define_operation (const char *name); static void set_curr_op_stack (id_list *in, id_list *out); static operation_list *append_to_operation_list (operation_list *list, const char *name, id_list *args); static id_list *append_to_id_list (id_list *list, const char *id); static int emit_id_list (const id_list *list, const char *sep, const char *before, const char *after); static void set_table (table_info *t, int from, int to, char *value); static void free_id_list (id_list *list); static void emit_var_declarations (const char *base, const char *type, int i, int n); static void emit_var_defines (id_list *list, int sp); static void emit_operation_invocation (operation_info *op, id_list *args, int sp, int deepest_write); static void emit_operation_list (operation_list *list); static void emit_stack_update (int sp, int deepest_write, const char *before, const char *after); static void free_operation_list (operation_list *list); static table_info *define_table (char *name); static void emit_table (table_info *t); static void free_table (table_info *t); int counter = 0; int c_code_on_brace = 0; int c_args_on_paren = 0; int errors = 0; Filament *curr_fil, *out_fil; operation_info *curr_op, *op_root; table_info *curr_table; int from, to; /* Line 268 of yacc.c */ #line 143 "genvm-parse.c" /* Enabling traces. */ #ifndef YYDEBUG # define YYDEBUG 1 #endif /* Enabling verbose error messages. */ #ifdef YYERROR_VERBOSE # undef YYERROR_VERBOSE # define YYERROR_VERBOSE 1 #else # define YYERROR_VERBOSE 0 #endif /* Enabling the token table. */ #ifndef YYTOKEN_TABLE # define YYTOKEN_TABLE 0 #endif /* Tokens. */ #ifndef YYTOKENTYPE # define YYTOKENTYPE /* Put the tokens into the symbol table, so that GDB and other debuggers know about them. */ enum yytokentype { ID = 258, EXPR = 259, NUMBER = 260, VM_OPERATION = 261, VM_TABLE = 262, VM_BYTECODE = 263, VM_DOTS = 264, VM_MINUSMINUS = 265 }; #endif /* Tokens. */ #define ID 258 #define EXPR 259 #define NUMBER 260 #define VM_OPERATION 261 #define VM_TABLE 262 #define VM_BYTECODE 263 #define VM_DOTS 264 #define VM_MINUSMINUS 265 #if ! defined YYSTYPE && ! defined YYSTYPE_IS_DECLARED typedef union YYSTYPE { /* Line 293 of yacc.c */ #line 127 "genvm-parse.y" struct operation_list *oplist; struct operation_info *op; struct table_info *tab; struct id_list *id; const char *ctext; char *text; int num; /* Line 293 of yacc.c */ #line 211 "genvm-parse.c" } YYSTYPE; # define YYSTYPE_IS_TRIVIAL 1 # define yystype YYSTYPE /* obsolescent; will be withdrawn */ # define YYSTYPE_IS_DECLARED 1 #endif /* Copy the second part of user declarations. */ /* Line 343 of yacc.c */ #line 223 "genvm-parse.c" #ifdef short # undef short #endif #ifdef YYTYPE_UINT8 typedef YYTYPE_UINT8 yytype_uint8; #else typedef unsigned char yytype_uint8; #endif #ifdef YYTYPE_INT8 typedef YYTYPE_INT8 yytype_int8; #elif (defined __STDC__ || defined __C99__FUNC__ \ || defined __cplusplus || defined _MSC_VER) typedef signed char yytype_int8; #else typedef short int yytype_int8; #endif #ifdef YYTYPE_UINT16 typedef YYTYPE_UINT16 yytype_uint16; #else typedef unsigned short int yytype_uint16; #endif #ifdef YYTYPE_INT16 typedef YYTYPE_INT16 yytype_int16; #else typedef short int yytype_int16; #endif #ifndef YYSIZE_T # ifdef __SIZE_TYPE__ # define YYSIZE_T __SIZE_TYPE__ # elif defined size_t # define YYSIZE_T size_t # elif ! defined YYSIZE_T && (defined __STDC__ || defined __C99__FUNC__ \ || defined __cplusplus || defined _MSC_VER) # include /* INFRINGES ON USER NAME SPACE */ # define YYSIZE_T size_t # else # define YYSIZE_T unsigned int # endif #endif #define YYSIZE_MAXIMUM ((YYSIZE_T) -1) #ifndef YY_ # if defined YYENABLE_NLS && YYENABLE_NLS # if ENABLE_NLS # include /* INFRINGES ON USER NAME SPACE */ # define YY_(msgid) dgettext ("bison-runtime", msgid) # endif # endif # ifndef YY_ # define YY_(msgid) msgid # endif #endif /* Suppress unused-variable warnings by "using" E. */ #if ! defined lint || defined __GNUC__ # define YYUSE(e) ((void) (e)) #else # define YYUSE(e) /* empty */ #endif /* Identity function, used to suppress warnings about constant conditions. */ #ifndef lint # define YYID(n) (n) #else #if (defined __STDC__ || defined __C99__FUNC__ \ || defined __cplusplus || defined _MSC_VER) static int YYID (int yyi) #else static int YYID (yyi) int yyi; #endif { return yyi; } #endif #if ! defined yyoverflow || YYERROR_VERBOSE /* The parser invokes alloca or malloc; define the necessary symbols. */ # ifdef YYSTACK_USE_ALLOCA # if YYSTACK_USE_ALLOCA # ifdef __GNUC__ # define YYSTACK_ALLOC __builtin_alloca # elif defined __BUILTIN_VA_ARG_INCR # include /* INFRINGES ON USER NAME SPACE */ # elif defined _AIX # define YYSTACK_ALLOC __alloca # elif defined _MSC_VER # include /* INFRINGES ON USER NAME SPACE */ # define alloca _alloca # else # define YYSTACK_ALLOC alloca # if ! defined _ALLOCA_H && ! defined EXIT_SUCCESS && (defined __STDC__ || defined __C99__FUNC__ \ || defined __cplusplus || defined _MSC_VER) # include /* INFRINGES ON USER NAME SPACE */ # ifndef EXIT_SUCCESS # define EXIT_SUCCESS 0 # endif # endif # endif # endif # endif # ifdef YYSTACK_ALLOC /* Pacify GCC's `empty if-body' warning. */ # define YYSTACK_FREE(Ptr) do { /* empty */; } while (YYID (0)) # ifndef YYSTACK_ALLOC_MAXIMUM /* The OS might guarantee only one guard page at the bottom of the stack, and a page size can be as small as 4096 bytes. So we cannot safely invoke alloca (N) if N exceeds 4096. Use a slightly smaller number to allow for a few compiler-allocated temporary stack slots. */ # define YYSTACK_ALLOC_MAXIMUM 4032 /* reasonable circa 2006 */ # endif # else # define YYSTACK_ALLOC YYMALLOC # define YYSTACK_FREE YYFREE # ifndef YYSTACK_ALLOC_MAXIMUM # define YYSTACK_ALLOC_MAXIMUM YYSIZE_MAXIMUM # endif # if (defined __cplusplus && ! defined EXIT_SUCCESS \ && ! ((defined YYMALLOC || defined malloc) \ && (defined YYFREE || defined free))) # include /* INFRINGES ON USER NAME SPACE */ # ifndef EXIT_SUCCESS # define EXIT_SUCCESS 0 # endif # endif # ifndef YYMALLOC # define YYMALLOC malloc # if ! defined malloc && ! defined EXIT_SUCCESS && (defined __STDC__ || defined __C99__FUNC__ \ || defined __cplusplus || defined _MSC_VER) void *malloc (YYSIZE_T); /* INFRINGES ON USER NAME SPACE */ # endif # endif # ifndef YYFREE # define YYFREE free # if ! defined free && ! defined EXIT_SUCCESS && (defined __STDC__ || defined __C99__FUNC__ \ || defined __cplusplus || defined _MSC_VER) void free (void *); /* INFRINGES ON USER NAME SPACE */ # endif # endif # endif #endif /* ! defined yyoverflow || YYERROR_VERBOSE */ #if (! defined yyoverflow \ && (! defined __cplusplus \ || (defined YYSTYPE_IS_TRIVIAL && YYSTYPE_IS_TRIVIAL))) /* A type that is properly aligned for any stack member. */ union yyalloc { yytype_int16 yyss_alloc; YYSTYPE yyvs_alloc; }; /* The size of the maximum gap between one aligned stack and the next. */ # define YYSTACK_GAP_MAXIMUM (sizeof (union yyalloc) - 1) /* The size of an array large to enough to hold all stacks, each with N elements. */ # define YYSTACK_BYTES(N) \ ((N) * (sizeof (yytype_int16) + sizeof (YYSTYPE)) \ + YYSTACK_GAP_MAXIMUM) # define YYCOPY_NEEDED 1 /* Relocate STACK from its old location to the new one. The local variables YYSIZE and YYSTACKSIZE give the old and new number of elements in the stack, and YYPTR gives the new location of the stack. Advance YYPTR to a properly aligned location for the next stack. */ # define YYSTACK_RELOCATE(Stack_alloc, Stack) \ do \ { \ YYSIZE_T yynewbytes; \ YYCOPY (&yyptr->Stack_alloc, Stack, yysize); \ Stack = &yyptr->Stack_alloc; \ yynewbytes = yystacksize * sizeof (*Stack) + YYSTACK_GAP_MAXIMUM; \ yyptr += yynewbytes / sizeof (*yyptr); \ } \ while (YYID (0)) #endif #if defined YYCOPY_NEEDED && YYCOPY_NEEDED /* Copy COUNT objects from FROM to TO. The source and destination do not overlap. */ # ifndef YYCOPY # if defined __GNUC__ && 1 < __GNUC__ # define YYCOPY(To, From, Count) \ __builtin_memcpy (To, From, (Count) * sizeof (*(From))) # else # define YYCOPY(To, From, Count) \ do \ { \ YYSIZE_T yyi; \ for (yyi = 0; yyi < (Count); yyi++) \ (To)[yyi] = (From)[yyi]; \ } \ while (YYID (0)) # endif # endif #endif /* !YYCOPY_NEEDED */ /* YYFINAL -- State number of the termination state. */ #define YYFINAL 2 /* YYLAST -- Last index in YYTABLE. */ #define YYLAST 50 /* YYNTOKENS -- Number of terminals. */ #define YYNTOKENS 18 /* YYNNTS -- Number of nonterminals. */ #define YYNNTS 27 /* YYNRULES -- Number of rules. */ #define YYNRULES 44 /* YYNRULES -- Number of states. */ #define YYNSTATES 70 /* YYTRANSLATE(YYLEX) -- Bison symbol number corresponding to YYLEX. */ #define YYUNDEFTOK 2 #define YYMAXUTOK 265 #define YYTRANSLATE(YYX) \ ((unsigned int) (YYX) <= YYMAXUTOK ? yytranslate[YYX] : YYUNDEFTOK) /* YYTRANSLATE[YYLEX] -- Bison symbol number corresponding to YYLEX. */ static const yytype_uint8 yytranslate[] = { 0, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 15, 16, 2, 2, 13, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 17, 2, 14, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 11, 2, 12, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 2, 1, 2, 3, 4, 5, 6, 7, 8, 9, 10 }; #if YYDEBUG /* YYPRHS[YYN] -- Index of the first RHS symbol of rule number YYN in YYRHS. */ static const yytype_uint8 yyprhs[] = { 0, 0, 3, 6, 9, 12, 13, 14, 21, 23, 25, 29, 32, 34, 38, 41, 43, 46, 51, 54, 57, 58, 65, 66, 74, 75, 77, 78, 82, 84, 85, 88, 91, 93, 94, 100, 102, 103, 104, 105, 115, 118, 119, 125, 128 }; /* YYRHS -- A `-1'-separated list of the rules' RHS. */ static const yytype_int8 yyrhs[] = { 19, 0, -1, 19, 20, -1, 19, 39, -1, 19, 28, -1, -1, -1, 7, 3, 21, 11, 22, 12, -1, 23, -1, 24, -1, 23, 13, 26, -1, 24, 26, -1, 26, -1, 23, 13, 27, -1, 24, 27, -1, 27, -1, 5, 14, -1, 5, 9, 5, 14, -1, 25, 3, -1, 25, 28, -1, -1, 8, 38, 29, 11, 30, 12, -1, -1, 30, 3, 31, 15, 32, 16, 17, -1, -1, 33, -1, -1, 33, 13, 34, -1, 34, -1, -1, 35, 36, -1, 36, 4, -1, 4, -1, -1, 36, 15, 37, 36, 16, -1, 3, -1, -1, -1, -1, 6, 3, 40, 42, 43, 41, 11, 44, 12, -1, 42, 3, -1, -1, 15, 42, 10, 42, 16, -1, 44, 4, -1, -1 }; /* YYRLINE[YYN] -- source line where rule number YYN was defined. */ static const yytype_uint16 yyrline[] = { 0, 155, 155, 156, 157, 159, 163, 162, 168, 169, 172, 173, 174, 177, 178, 179, 182, 190, 200, 206, 212, 211, 221, 221, 224, 227, 230, 234, 236, 241, 241, 246, 248, 251, 250, 256, 259, 264, 266, 263, 284, 287, 290, 293, 295 }; #endif #if YYDEBUG || YYERROR_VERBOSE || YYTOKEN_TABLE /* YYTNAME[SYMBOL-NUM] -- String name of the symbol SYMBOL-NUM. First, the terminals, then, starting at YYNTOKENS, nonterminals. */ static const char *const yytname[] = { "$end", "error", "$undefined", "\"identifier\"", "\"C expression\"", "\"number\"", "\"operation\"", "\"table\"", "\"bytecode\"", "\"..\"", "\"--\"", "'{'", "'}'", "','", "'='", "'('", "')'", "';'", "$accept", "script", "table", "$@1", "table_items", "table_items.label", "table_items.descr", "subscripts", "label", "description", "bytecode", "$@2", "operation_list", "$@3", "opt_c_args", "c_args", "c_arg", "$@4", "c_arg_body", "$@5", "opt_id", "operation", "$@6", "$@7", "ids", "stack_balance", "c_code", 0 }; #endif # ifdef YYPRINT /* YYTOKNUM[YYLEX-NUM] -- Internal token number corresponding to token YYLEX-NUM. */ static const yytype_uint16 yytoknum[] = { 0, 256, 257, 258, 259, 260, 261, 262, 263, 264, 265, 123, 125, 44, 61, 40, 41, 59 }; # endif /* YYR1[YYN] -- Symbol number of symbol that rule YYN derives. */ static const yytype_uint8 yyr1[] = { 0, 18, 19, 19, 19, 19, 21, 20, 22, 22, 23, 23, 23, 24, 24, 24, 25, 25, 26, 27, 29, 28, 31, 30, 30, 32, 32, 33, 33, 35, 34, 36, 36, 37, 36, 38, 38, 40, 41, 39, 42, 42, 43, 44, 44 }; /* YYR2[YYN] -- Number of symbols composing right hand side of rule YYN. */ static const yytype_uint8 yyr2[] = { 0, 2, 2, 2, 2, 0, 0, 6, 1, 1, 3, 2, 1, 3, 2, 1, 2, 4, 2, 2, 0, 6, 0, 7, 0, 1, 0, 3, 1, 0, 2, 2, 1, 0, 5, 1, 0, 0, 0, 9, 2, 0, 5, 2, 0 }; /* YYDEFACT[STATE-NAME] -- Default reduction number in state STATE-NUM. Performed when YYTABLE doesn't specify something else to do. Zero means the default is an error. */ static const yytype_uint8 yydefact[] = { 5, 0, 1, 0, 0, 36, 2, 4, 3, 37, 6, 35, 20, 41, 0, 0, 0, 0, 24, 40, 41, 38, 0, 0, 8, 9, 0, 12, 15, 0, 0, 0, 0, 16, 7, 0, 11, 14, 18, 19, 22, 21, 41, 44, 0, 10, 13, 0, 0, 0, 17, 26, 42, 43, 39, 0, 25, 28, 0, 0, 29, 32, 30, 23, 27, 31, 33, 0, 0, 34 }; /* YYDEFGOTO[NTERM-NUM]. */ static const yytype_int8 yydefgoto[] = { -1, 1, 6, 14, 23, 24, 25, 26, 27, 28, 7, 15, 29, 47, 55, 56, 57, 58, 62, 67, 12, 8, 13, 31, 16, 21, 49 }; /* YYPACT[STATE-NUM] -- Index in YYTABLE of the portion describing STATE-NUM. */ #define YYPACT_NINF -24 static const yytype_int8 yypact[] = { -24, 20, -24, 5, 6, 29, -24, -24, -24, -24, -24, -24, -24, -24, 12, 23, 2, 28, -24, -24, -24, -24, -3, 24, 25, 28, 22, -24, -24, 7, 21, 26, 30, -24, -24, 28, -24, -24, -24, -24, -24, -24, -24, -24, 27, -24, -24, 31, -2, 17, -24, 35, -24, -24, -24, 32, 34, -24, 36, 33, -24, -24, 3, -24, -24, -24, -24, 36, 0, -24 }; /* YYPGOTO[NTERM-NUM]. */ static const yytype_int8 yypgoto[] = { -24, -24, -24, -24, -24, -24, -24, -24, -23, -22, 16, -24, -24, -24, -24, -24, -17, -24, -18, -24, -24, -24, -24, -24, -20, -24, -24 }; /* YYTABLE[YYPACT[STATE-NUM]]. What to do in state STATE-NUM. If positive, shift that token. If negative, reduce the rule which number is the opposite. If YYTABLE_NINF, syntax error. */ #define YYTABLE_NINF -30 static const yytype_int8 yytable[] = { 30, 19, 36, 37, 65, 19, 32, 65, 9, 10, 40, 33, 45, 46, 52, 66, 69, 20, 66, 41, 2, 53, 48, 17, 19, 38, 3, 4, 5, 54, 5, 42, 11, 22, 18, 44, 34, 43, 35, -29, 61, 50, 39, 64, 0, 0, 51, 60, 59, 68, 63 }; #define yypact_value_is_default(yystate) \ ((yystate) == (-24)) #define yytable_value_is_error(yytable_value) \ YYID (0) static const yytype_int8 yycheck[] = { 20, 3, 25, 25, 4, 3, 9, 4, 3, 3, 3, 14, 35, 35, 16, 15, 16, 15, 15, 12, 0, 4, 42, 11, 3, 3, 6, 7, 8, 12, 8, 10, 3, 5, 11, 5, 12, 11, 13, 4, 4, 14, 26, 60, -1, -1, 15, 13, 16, 67, 17 }; /* YYSTOS[STATE-NUM] -- The (internal number of the) accessing symbol of state STATE-NUM. */ static const yytype_uint8 yystos[] = { 0, 19, 0, 6, 7, 8, 20, 28, 39, 3, 3, 3, 38, 40, 21, 29, 42, 11, 11, 3, 15, 43, 5, 22, 23, 24, 25, 26, 27, 30, 42, 41, 9, 14, 12, 13, 26, 27, 3, 28, 3, 12, 10, 11, 5, 26, 27, 31, 42, 44, 14, 15, 16, 4, 12, 32, 33, 34, 35, 16, 13, 4, 36, 17, 34, 4, 15, 37, 36, 16 }; #define yyerrok (yyerrstatus = 0) #define yyclearin (yychar = YYEMPTY) #define YYEMPTY (-2) #define YYEOF 0 #define YYACCEPT goto yyacceptlab #define YYABORT goto yyabortlab #define YYERROR goto yyerrorlab /* Like YYERROR except do call yyerror. This remains here temporarily to ease the transition to the new meaning of YYERROR, for GCC. Once GCC version 2 has supplanted version 1, this can go. However, YYFAIL appears to be in use. Nevertheless, it is formally deprecated in Bison 2.4.2's NEWS entry, where a plan to phase it out is discussed. */ #define YYFAIL goto yyerrlab #if defined YYFAIL /* This is here to suppress warnings from the GCC cpp's -Wunused-macros. Normally we don't worry about that warning, but some users do, and we want to make it easy for users to remove YYFAIL uses, which will produce warnings from Bison 2.5. */ #endif #define YYRECOVERING() (!!yyerrstatus) #define YYBACKUP(Token, Value) \ do \ if (yychar == YYEMPTY && yylen == 1) \ { \ yychar = (Token); \ yylval = (Value); \ YYPOPSTACK (1); \ goto yybackup; \ } \ else \ { \ yyerror (YY_("syntax error: cannot back up")); \ YYERROR; \ } \ while (YYID (0)) #define YYTERROR 1 #define YYERRCODE 256 /* YYLLOC_DEFAULT -- Set CURRENT to span from RHS[1] to RHS[N]. If N is 0, then set CURRENT to the empty location which ends the previous symbol: RHS[0] (always defined). */ #define YYRHSLOC(Rhs, K) ((Rhs)[K]) #ifndef YYLLOC_DEFAULT # define YYLLOC_DEFAULT(Current, Rhs, N) \ do \ if (YYID (N)) \ { \ (Current).first_line = YYRHSLOC (Rhs, 1).first_line; \ (Current).first_column = YYRHSLOC (Rhs, 1).first_column; \ (Current).last_line = YYRHSLOC (Rhs, N).last_line; \ (Current).last_column = YYRHSLOC (Rhs, N).last_column; \ } \ else \ { \ (Current).first_line = (Current).last_line = \ YYRHSLOC (Rhs, 0).last_line; \ (Current).first_column = (Current).last_column = \ YYRHSLOC (Rhs, 0).last_column; \ } \ while (YYID (0)) #endif /* This macro is provided for backward compatibility. */ #ifndef YY_LOCATION_PRINT # define YY_LOCATION_PRINT(File, Loc) ((void) 0) #endif /* YYLEX -- calling `yylex' with the right arguments. */ #ifdef YYLEX_PARAM # define YYLEX yylex (YYLEX_PARAM) #else # define YYLEX yylex () #endif /* Enable debugging if requested. */ #if YYDEBUG # ifndef YYFPRINTF # include /* INFRINGES ON USER NAME SPACE */ # define YYFPRINTF fprintf # endif # define YYDPRINTF(Args) \ do { \ if (yydebug) \ YYFPRINTF Args; \ } while (YYID (0)) # define YY_SYMBOL_PRINT(Title, Type, Value, Location) \ do { \ if (yydebug) \ { \ YYFPRINTF (stderr, "%s ", Title); \ yy_symbol_print (stderr, \ Type, Value); \ YYFPRINTF (stderr, "\n"); \ } \ } while (YYID (0)) /*--------------------------------. | Print this symbol on YYOUTPUT. | `--------------------------------*/ /*ARGSUSED*/ #if (defined __STDC__ || defined __C99__FUNC__ \ || defined __cplusplus || defined _MSC_VER) static void yy_symbol_value_print (FILE *yyoutput, int yytype, YYSTYPE const * const yyvaluep) #else static void yy_symbol_value_print (yyoutput, yytype, yyvaluep) FILE *yyoutput; int yytype; YYSTYPE const * const yyvaluep; #endif { if (!yyvaluep) return; # ifdef YYPRINT if (yytype < YYNTOKENS) YYPRINT (yyoutput, yytoknum[yytype], *yyvaluep); # else YYUSE (yyoutput); # endif switch (yytype) { default: break; } } /*--------------------------------. | Print this symbol on YYOUTPUT. | `--------------------------------*/ #if (defined __STDC__ || defined __C99__FUNC__ \ || defined __cplusplus || defined _MSC_VER) static void yy_symbol_print (FILE *yyoutput, int yytype, YYSTYPE const * const yyvaluep) #else static void yy_symbol_print (yyoutput, yytype, yyvaluep) FILE *yyoutput; int yytype; YYSTYPE const * const yyvaluep; #endif { if (yytype < YYNTOKENS) YYFPRINTF (yyoutput, "token %s (", yytname[yytype]); else YYFPRINTF (yyoutput, "nterm %s (", yytname[yytype]); yy_symbol_value_print (yyoutput, yytype, yyvaluep); YYFPRINTF (yyoutput, ")"); } /*------------------------------------------------------------------. | yy_stack_print -- Print the state stack from its BOTTOM up to its | | TOP (included). | `------------------------------------------------------------------*/ #if (defined __STDC__ || defined __C99__FUNC__ \ || defined __cplusplus || defined _MSC_VER) static void yy_stack_print (yytype_int16 *yybottom, yytype_int16 *yytop) #else static void yy_stack_print (yybottom, yytop) yytype_int16 *yybottom; yytype_int16 *yytop; #endif { YYFPRINTF (stderr, "Stack now"); for (; yybottom <= yytop; yybottom++) { int yybot = *yybottom; YYFPRINTF (stderr, " %d", yybot); } YYFPRINTF (stderr, "\n"); } # define YY_STACK_PRINT(Bottom, Top) \ do { \ if (yydebug) \ yy_stack_print ((Bottom), (Top)); \ } while (YYID (0)) /*------------------------------------------------. | Report that the YYRULE is going to be reduced. | `------------------------------------------------*/ #if (defined __STDC__ || defined __C99__FUNC__ \ || defined __cplusplus || defined _MSC_VER) static void yy_reduce_print (YYSTYPE *yyvsp, int yyrule) #else static void yy_reduce_print (yyvsp, yyrule) YYSTYPE *yyvsp; int yyrule; #endif { int yynrhs = yyr2[yyrule]; int yyi; unsigned long int yylno = yyrline[yyrule]; YYFPRINTF (stderr, "Reducing stack by rule %d (line %lu):\n", yyrule - 1, yylno); /* The symbols being reduced. */ for (yyi = 0; yyi < yynrhs; yyi++) { YYFPRINTF (stderr, " $%d = ", yyi + 1); yy_symbol_print (stderr, yyrhs[yyprhs[yyrule] + yyi], &(yyvsp[(yyi + 1) - (yynrhs)]) ); YYFPRINTF (stderr, "\n"); } } # define YY_REDUCE_PRINT(Rule) \ do { \ if (yydebug) \ yy_reduce_print (yyvsp, Rule); \ } while (YYID (0)) /* Nonzero means print parse trace. It is left uninitialized so that multiple parsers can coexist. */ int yydebug; #else /* !YYDEBUG */ # define YYDPRINTF(Args) # define YY_SYMBOL_PRINT(Title, Type, Value, Location) # define YY_STACK_PRINT(Bottom, Top) # define YY_REDUCE_PRINT(Rule) #endif /* !YYDEBUG */ /* YYINITDEPTH -- initial size of the parser's stacks. */ #ifndef YYINITDEPTH # define YYINITDEPTH 200 #endif /* YYMAXDEPTH -- maximum size the stacks can grow to (effective only if the built-in stack extension method is used). Do not make this value too large; the results are undefined if YYSTACK_ALLOC_MAXIMUM < YYSTACK_BYTES (YYMAXDEPTH) evaluated with infinite-precision integer arithmetic. */ #ifndef YYMAXDEPTH # define YYMAXDEPTH 10000 #endif #if YYERROR_VERBOSE # ifndef yystrlen # if defined __GLIBC__ && defined _STRING_H # define yystrlen strlen # else /* Return the length of YYSTR. */ #if (defined __STDC__ || defined __C99__FUNC__ \ || defined __cplusplus || defined _MSC_VER) static YYSIZE_T yystrlen (const char *yystr) #else static YYSIZE_T yystrlen (yystr) const char *yystr; #endif { YYSIZE_T yylen; for (yylen = 0; yystr[yylen]; yylen++) continue; return yylen; } # endif # endif # ifndef yystpcpy # if defined __GLIBC__ && defined _STRING_H && defined _GNU_SOURCE # define yystpcpy stpcpy # else /* Copy YYSRC to YYDEST, returning the address of the terminating '\0' in YYDEST. */ #if (defined __STDC__ || defined __C99__FUNC__ \ || defined __cplusplus || defined _MSC_VER) static char * yystpcpy (char *yydest, const char *yysrc) #else static char * yystpcpy (yydest, yysrc) char *yydest; const char *yysrc; #endif { char *yyd = yydest; const char *yys = yysrc; while ((*yyd++ = *yys++) != '\0') continue; return yyd - 1; } # endif # endif # ifndef yytnamerr /* Copy to YYRES the contents of YYSTR after stripping away unnecessary quotes and backslashes, so that it's suitable for yyerror. The heuristic is that double-quoting is unnecessary unless the string contains an apostrophe, a comma, or backslash (other than backslash-backslash). YYSTR is taken from yytname. If YYRES is null, do not copy; instead, return the length of what the result would have been. */ static YYSIZE_T yytnamerr (char *yyres, const char *yystr) { if (*yystr == '"') { YYSIZE_T yyn = 0; char const *yyp = yystr; for (;;) switch (*++yyp) { case '\'': case ',': goto do_not_strip_quotes; case '\\': if (*++yyp != '\\') goto do_not_strip_quotes; /* Fall through. */ default: if (yyres) yyres[yyn] = *yyp; yyn++; break; case '"': if (yyres) yyres[yyn] = '\0'; return yyn; } do_not_strip_quotes: ; } if (! yyres) return yystrlen (yystr); return yystpcpy (yyres, yystr) - yyres; } # endif /* Copy into *YYMSG, which is of size *YYMSG_ALLOC, an error message about the unexpected token YYTOKEN for the state stack whose top is YYSSP. Return 0 if *YYMSG was successfully written. Return 1 if *YYMSG is not large enough to hold the message. In that case, also set *YYMSG_ALLOC to the required number of bytes. Return 2 if the required number of bytes is too large to store. */ static int yysyntax_error (YYSIZE_T *yymsg_alloc, char **yymsg, yytype_int16 *yyssp, int yytoken) { YYSIZE_T yysize0 = yytnamerr (0, yytname[yytoken]); YYSIZE_T yysize = yysize0; YYSIZE_T yysize1; enum { YYERROR_VERBOSE_ARGS_MAXIMUM = 5 }; /* Internationalized format string. */ const char *yyformat = 0; /* Arguments of yyformat. */ char const *yyarg[YYERROR_VERBOSE_ARGS_MAXIMUM]; /* Number of reported tokens (one for the "unexpected", one per "expected"). */ int yycount = 0; /* There are many possibilities here to consider: - Assume YYFAIL is not used. It's too flawed to consider. See for details. YYERROR is fine as it does not invoke this function. - If this state is a consistent state with a default action, then the only way this function was invoked is if the default action is an error action. In that case, don't check for expected tokens because there are none. - The only way there can be no lookahead present (in yychar) is if this state is a consistent state with a default action. Thus, detecting the absence of a lookahead is sufficient to determine that there is no unexpected or expected token to report. In that case, just report a simple "syntax error". - Don't assume there isn't a lookahead just because this state is a consistent state with a default action. There might have been a previous inconsistent state, consistent state with a non-default action, or user semantic action that manipulated yychar. - Of course, the expected token list depends on states to have correct lookahead information, and it depends on the parser not to perform extra reductions after fetching a lookahead from the scanner and before detecting a syntax error. Thus, state merging (from LALR or IELR) and default reductions corrupt the expected token list. However, the list is correct for canonical LR with one exception: it will still contain any token that will not be accepted due to an error action in a later state. */ if (yytoken != YYEMPTY) { int yyn = yypact[*yyssp]; yyarg[yycount++] = yytname[yytoken]; if (!yypact_value_is_default (yyn)) { /* Start YYX at -YYN if negative to avoid negative indexes in YYCHECK. In other words, skip the first -YYN actions for this state because they are default actions. */ int yyxbegin = yyn < 0 ? -yyn : 0; /* Stay within bounds of both yycheck and yytname. */ int yychecklim = YYLAST - yyn + 1; int yyxend = yychecklim < YYNTOKENS ? yychecklim : YYNTOKENS; int yyx; for (yyx = yyxbegin; yyx < yyxend; ++yyx) if (yycheck[yyx + yyn] == yyx && yyx != YYTERROR && !yytable_value_is_error (yytable[yyx + yyn])) { if (yycount == YYERROR_VERBOSE_ARGS_MAXIMUM) { yycount = 1; yysize = yysize0; break; } yyarg[yycount++] = yytname[yyx]; yysize1 = yysize + yytnamerr (0, yytname[yyx]); if (! (yysize <= yysize1 && yysize1 <= YYSTACK_ALLOC_MAXIMUM)) return 2; yysize = yysize1; } } } switch (yycount) { # define YYCASE_(N, S) \ case N: \ yyformat = S; \ break YYCASE_(0, YY_("syntax error")); YYCASE_(1, YY_("syntax error, unexpected %s")); YYCASE_(2, YY_("syntax error, unexpected %s, expecting %s")); YYCASE_(3, YY_("syntax error, unexpected %s, expecting %s or %s")); YYCASE_(4, YY_("syntax error, unexpected %s, expecting %s or %s or %s")); YYCASE_(5, YY_("syntax error, unexpected %s, expecting %s or %s or %s or %s")); # undef YYCASE_ } yysize1 = yysize + yystrlen (yyformat); if (! (yysize <= yysize1 && yysize1 <= YYSTACK_ALLOC_MAXIMUM)) return 2; yysize = yysize1; if (*yymsg_alloc < yysize) { *yymsg_alloc = 2 * yysize; if (! (yysize <= *yymsg_alloc && *yymsg_alloc <= YYSTACK_ALLOC_MAXIMUM)) *yymsg_alloc = YYSTACK_ALLOC_MAXIMUM; return 1; } /* Avoid sprintf, as that infringes on the user's name space. Don't have undefined behavior even if the translation produced a string with the wrong number of "%s"s. */ { char *yyp = *yymsg; int yyi = 0; while ((*yyp = *yyformat) != '\0') if (*yyp == '%' && yyformat[1] == 's' && yyi < yycount) { yyp += yytnamerr (yyp, yyarg[yyi++]); yyformat += 2; } else { yyp++; yyformat++; } } return 0; } #endif /* YYERROR_VERBOSE */ /*-----------------------------------------------. | Release the memory associated to this symbol. | `-----------------------------------------------*/ /*ARGSUSED*/ #if (defined __STDC__ || defined __C99__FUNC__ \ || defined __cplusplus || defined _MSC_VER) static void yydestruct (const char *yymsg, int yytype, YYSTYPE *yyvaluep) #else static void yydestruct (yymsg, yytype, yyvaluep) const char *yymsg; int yytype; YYSTYPE *yyvaluep; #endif { YYUSE (yyvaluep); if (!yymsg) yymsg = "Deleting"; YY_SYMBOL_PRINT (yymsg, yytype, yyvaluep, yylocationp); switch (yytype) { default: break; } } /* Prevent warnings from -Wmissing-prototypes. */ #ifdef YYPARSE_PARAM #if defined __STDC__ || defined __cplusplus int yyparse (void *YYPARSE_PARAM); #else int yyparse (); #endif #else /* ! YYPARSE_PARAM */ #if defined __STDC__ || defined __cplusplus int yyparse (void); #else int yyparse (); #endif #endif /* ! YYPARSE_PARAM */ /* The lookahead symbol. */ int yychar; /* The semantic value of the lookahead symbol. */ YYSTYPE yylval; /* Number of syntax errors so far. */ int yynerrs; /*----------. | yyparse. | `----------*/ #ifdef YYPARSE_PARAM #if (defined __STDC__ || defined __C99__FUNC__ \ || defined __cplusplus || defined _MSC_VER) int yyparse (void *YYPARSE_PARAM) #else int yyparse (YYPARSE_PARAM) void *YYPARSE_PARAM; #endif #else /* ! YYPARSE_PARAM */ #if (defined __STDC__ || defined __C99__FUNC__ \ || defined __cplusplus || defined _MSC_VER) int yyparse (void) #else int yyparse () #endif #endif { int yystate; /* Number of tokens to shift before error messages enabled. */ int yyerrstatus; /* The stacks and their tools: `yyss': related to states. `yyvs': related to semantic values. Refer to the stacks thru separate pointers, to allow yyoverflow to reallocate them elsewhere. */ /* The state stack. */ yytype_int16 yyssa[YYINITDEPTH]; yytype_int16 *yyss; yytype_int16 *yyssp; /* The semantic value stack. */ YYSTYPE yyvsa[YYINITDEPTH]; YYSTYPE *yyvs; YYSTYPE *yyvsp; YYSIZE_T yystacksize; int yyn; int yyresult; /* Lookahead token as an internal (translated) token number. */ int yytoken; /* The variables used to return semantic value and location from the action routines. */ YYSTYPE yyval; #if YYERROR_VERBOSE /* Buffer for error messages, and its allocated size. */ char yymsgbuf[128]; char *yymsg = yymsgbuf; YYSIZE_T yymsg_alloc = sizeof yymsgbuf; #endif #define YYPOPSTACK(N) (yyvsp -= (N), yyssp -= (N)) /* The number of symbols on the RHS of the reduced rule. Keep to zero when no symbol should be popped. */ int yylen = 0; yytoken = 0; yyss = yyssa; yyvs = yyvsa; yystacksize = YYINITDEPTH; YYDPRINTF ((stderr, "Starting parse\n")); yystate = 0; yyerrstatus = 0; yynerrs = 0; yychar = YYEMPTY; /* Cause a token to be read. */ /* Initialize stack pointers. Waste one element of value and location stack so that they stay on the same level as the state stack. The wasted elements are never initialized. */ yyssp = yyss; yyvsp = yyvs; goto yysetstate; /*------------------------------------------------------------. | yynewstate -- Push a new state, which is found in yystate. | `------------------------------------------------------------*/ yynewstate: /* In all cases, when you get here, the value and location stacks have just been pushed. So pushing a state here evens the stacks. */ yyssp++; yysetstate: *yyssp = yystate; if (yyss + yystacksize - 1 <= yyssp) { /* Get the current used size of the three stacks, in elements. */ YYSIZE_T yysize = yyssp - yyss + 1; #ifdef yyoverflow { /* Give user a chance to reallocate the stack. Use copies of these so that the &'s don't force the real ones into memory. */ YYSTYPE *yyvs1 = yyvs; yytype_int16 *yyss1 = yyss; /* Each stack pointer address is followed by the size of the data in use in that stack, in bytes. This used to be a conditional around just the two extra args, but that might be undefined if yyoverflow is a macro. */ yyoverflow (YY_("memory exhausted"), &yyss1, yysize * sizeof (*yyssp), &yyvs1, yysize * sizeof (*yyvsp), &yystacksize); yyss = yyss1; yyvs = yyvs1; } #else /* no yyoverflow */ # ifndef YYSTACK_RELOCATE goto yyexhaustedlab; # else /* Extend the stack our own way. */ if (YYMAXDEPTH <= yystacksize) goto yyexhaustedlab; yystacksize *= 2; if (YYMAXDEPTH < yystacksize) yystacksize = YYMAXDEPTH; { yytype_int16 *yyss1 = yyss; union yyalloc *yyptr = (union yyalloc *) YYSTACK_ALLOC (YYSTACK_BYTES (yystacksize)); if (! yyptr) goto yyexhaustedlab; YYSTACK_RELOCATE (yyss_alloc, yyss); YYSTACK_RELOCATE (yyvs_alloc, yyvs); # undef YYSTACK_RELOCATE if (yyss1 != yyssa) YYSTACK_FREE (yyss1); } # endif #endif /* no yyoverflow */ yyssp = yyss + yysize - 1; yyvsp = yyvs + yysize - 1; YYDPRINTF ((stderr, "Stack size increased to %lu\n", (unsigned long int) yystacksize)); if (yyss + yystacksize - 1 <= yyssp) YYABORT; } YYDPRINTF ((stderr, "Entering state %d\n", yystate)); if (yystate == YYFINAL) YYACCEPT; goto yybackup; /*-----------. | yybackup. | `-----------*/ yybackup: /* Do appropriate processing given the current state. Read a lookahead token if we need one and don't already have one. */ /* First try to decide what to do without reference to lookahead token. */ yyn = yypact[yystate]; if (yypact_value_is_default (yyn)) goto yydefault; /* Not known => get a lookahead token if don't already have one. */ /* YYCHAR is either YYEMPTY or YYEOF or a valid lookahead symbol. */ if (yychar == YYEMPTY) { YYDPRINTF ((stderr, "Reading a token: ")); yychar = YYLEX; } if (yychar <= YYEOF) { yychar = yytoken = YYEOF; YYDPRINTF ((stderr, "Now at end of input.\n")); } else { yytoken = YYTRANSLATE (yychar); YY_SYMBOL_PRINT ("Next token is", yytoken, &yylval, &yylloc); } /* If the proper action on seeing token YYTOKEN is to reduce or to detect an error, take that action. */ yyn += yytoken; if (yyn < 0 || YYLAST < yyn || yycheck[yyn] != yytoken) goto yydefault; yyn = yytable[yyn]; if (yyn <= 0) { if (yytable_value_is_error (yyn)) goto yyerrlab; yyn = -yyn; goto yyreduce; } /* Count tokens shifted since error; after three, turn off error status. */ if (yyerrstatus) yyerrstatus--; /* Shift the lookahead token. */ YY_SYMBOL_PRINT ("Shifting", yytoken, &yylval, &yylloc); /* Discard the shifted token. */ yychar = YYEMPTY; yystate = yyn; *++yyvsp = yylval; goto yynewstate; /*-----------------------------------------------------------. | yydefault -- do the default action for the current state. | `-----------------------------------------------------------*/ yydefault: yyn = yydefact[yystate]; if (yyn == 0) goto yyerrlab; goto yyreduce; /*-----------------------------. | yyreduce -- Do a reduction. | `-----------------------------*/ yyreduce: /* yyn is the number of a rule to reduce with. */ yylen = yyr2[yyn]; /* If YYLEN is nonzero, implement the default value of the action: `$$ = $1'. Otherwise, the following line sets YYVAL to garbage. This behavior is undocumented and Bison users should not rely upon it. Assigning to YYVAL unconditionally makes the parser a bit smaller, and it avoids a GCC warning that YYVAL may be used uninitialized. */ yyval = yyvsp[1-yylen]; YY_REDUCE_PRINT (yyn); switch (yyn) { case 4: /* Line 1806 of yacc.c */ #line 158 "genvm-parse.y" { free ((yyvsp[(2) - (2)].text)); } break; case 6: /* Line 1806 of yacc.c */ #line 163 "genvm-parse.y" { curr_table = define_table ((yyvsp[(2) - (2)].text)); } break; case 7: /* Line 1806 of yacc.c */ #line 165 "genvm-parse.y" { emit_table (curr_table); free_table (curr_table); } break; case 16: /* Line 1806 of yacc.c */ #line 183 "genvm-parse.y" { from = to = (yyvsp[(1) - (2)].num); if (from < 0 || from > 255) { yyerror ("invalid table index"); from = 0, to = -1; } } break; case 17: /* Line 1806 of yacc.c */ #line 191 "genvm-parse.y" { from = (yyvsp[(1) - (4)].num), to = (yyvsp[(3) - (4)].num); if (from < 0 || to < 0 || from > 255 || to > 255) { yyerror ("invalid table index"); from = 0, to = -1; } } break; case 18: /* Line 1806 of yacc.c */ #line 201 "genvm-parse.y" { set_table (curr_table, from, to, (yyvsp[(2) - (2)].text)); free ((yyvsp[(2) - (2)].text)); } break; case 19: /* Line 1806 of yacc.c */ #line 207 "genvm-parse.y" { set_table (curr_table, from, to, (yyvsp[(2) - (2)].text)); free ((yyvsp[(2) - (2)].text)); } break; case 20: /* Line 1806 of yacc.c */ #line 212 "genvm-parse.y" { filprintf (out_fil, "%s:\n", (yyvsp[(2) - (2)].text)); } break; case 21: /* Line 1806 of yacc.c */ #line 214 "genvm-parse.y" { emit_operation_list ((yyvsp[(5) - (6)].oplist)); free_operation_list ((yyvsp[(5) - (6)].oplist)); filprintf (out_fil, " NEXT_BC;\n"); (yyval.text) = (yyvsp[(2) - (6)].text); } break; case 22: /* Line 1806 of yacc.c */ #line 221 "genvm-parse.y" { c_args_on_paren = 1; } break; case 23: /* Line 1806 of yacc.c */ #line 222 "genvm-parse.y" { (yyval.oplist) = append_to_operation_list ((yyvsp[(1) - (7)].oplist), (yyvsp[(2) - (7)].text), (yyvsp[(5) - (7)].id)); } break; case 24: /* Line 1806 of yacc.c */ #line 224 "genvm-parse.y" { (yyval.oplist) = NULL; } break; case 25: /* Line 1806 of yacc.c */ #line 228 "genvm-parse.y" { (yyval.id) = (yyvsp[(1) - (1)].id); } break; case 26: /* Line 1806 of yacc.c */ #line 230 "genvm-parse.y" { (yyval.id) = NULL; } break; case 27: /* Line 1806 of yacc.c */ #line 235 "genvm-parse.y" { (yyval.id) = append_to_id_list ((yyvsp[(1) - (3)].id), (yyvsp[(3) - (3)].text)); free ((yyvsp[(3) - (3)].text)); } break; case 28: /* Line 1806 of yacc.c */ #line 237 "genvm-parse.y" { (yyval.id) = append_to_id_list (NULL, (yyvsp[(1) - (1)].text)); free ((yyvsp[(1) - (1)].text)); } break; case 29: /* Line 1806 of yacc.c */ #line 241 "genvm-parse.y" { curr_fil = filnew (NULL, 0); } break; case 30: /* Line 1806 of yacc.c */ #line 243 "genvm-parse.y" { (yyval.text) = fildelete (curr_fil); } break; case 31: /* Line 1806 of yacc.c */ #line 247 "genvm-parse.y" { filcat (curr_fil, (yyvsp[(2) - (2)].text)); } break; case 32: /* Line 1806 of yacc.c */ #line 249 "genvm-parse.y" { filcat (curr_fil, (yyvsp[(1) - (1)].text)); } break; case 33: /* Line 1806 of yacc.c */ #line 251 "genvm-parse.y" { filcat (curr_fil, "("); } break; case 34: /* Line 1806 of yacc.c */ #line 253 "genvm-parse.y" { filcat (curr_fil, ")"); } break; case 35: /* Line 1806 of yacc.c */ #line 257 "genvm-parse.y" { (yyval.text) = (yyvsp[(1) - (1)].text); } break; case 36: /* Line 1806 of yacc.c */ #line 259 "genvm-parse.y" { asprintf (&(yyval.text), "label%d", ++counter); } break; case 37: /* Line 1806 of yacc.c */ #line 264 "genvm-parse.y" { curr_op = define_operation ((yyvsp[(2) - (2)].text)); c_code_on_brace = true; } break; case 38: /* Line 1806 of yacc.c */ #line 266 "genvm-parse.y" { curr_fil = filnew (NULL, 0); filprintf (curr_fil, "#line %d \"vm.def\"\n ", yylineno + 1); } break; case 39: /* Line 1806 of yacc.c */ #line 270 "genvm-parse.y" { filprintf (curr_fil, "\n#line __oline__ \"vm.inl\""); if (curr_op) { curr_op->args = (yyvsp[(4) - (9)].id); curr_op->code = fildelete (curr_fil); curr_op->needs_prepare_stack = strstr(curr_op->code, "PREPARE_STACK") != NULL; curr_op->needs_branch_label = strstr(curr_op->code, "BRANCH_LABEL") != NULL; } (yyval.op) = curr_op; } break; case 40: /* Line 1806 of yacc.c */ #line 285 "genvm-parse.y" { (yyval.id) = append_to_id_list ((yyvsp[(1) - (2)].id), (yyvsp[(2) - (2)].text)); free ((yyvsp[(2) - (2)].text)); } break; case 41: /* Line 1806 of yacc.c */ #line 287 "genvm-parse.y" { (yyval.id) = NULL; } break; case 42: /* Line 1806 of yacc.c */ #line 291 "genvm-parse.y" { set_curr_op_stack ((yyvsp[(2) - (5)].id), (yyvsp[(4) - (5)].id)); } break; case 43: /* Line 1806 of yacc.c */ #line 294 "genvm-parse.y" { filcat (curr_fil, (yyvsp[(2) - (2)].text)); } break; /* Line 1806 of yacc.c */ #line 1750 "genvm-parse.c" default: break; } /* User semantic actions sometimes alter yychar, and that requires that yytoken be updated with the new translation. We take the approach of translating immediately before every use of yytoken. One alternative is translating here after every semantic action, but that translation would be missed if the semantic action invokes YYABORT, YYACCEPT, or YYERROR immediately after altering yychar or if it invokes YYBACKUP. In the case of YYABORT or YYACCEPT, an incorrect destructor might then be invoked immediately. In the case of YYERROR or YYBACKUP, subsequent parser actions might lead to an incorrect destructor call or verbose syntax error message before the lookahead is translated. */ YY_SYMBOL_PRINT ("-> $$ =", yyr1[yyn], &yyval, &yyloc); YYPOPSTACK (yylen); yylen = 0; YY_STACK_PRINT (yyss, yyssp); *++yyvsp = yyval; /* Now `shift' the result of the reduction. Determine what state that goes to, based on the state we popped back to and the rule number reduced by. */ yyn = yyr1[yyn]; yystate = yypgoto[yyn - YYNTOKENS] + *yyssp; if (0 <= yystate && yystate <= YYLAST && yycheck[yystate] == *yyssp) yystate = yytable[yystate]; else yystate = yydefgoto[yyn - YYNTOKENS]; goto yynewstate; /*------------------------------------. | yyerrlab -- here on detecting error | `------------------------------------*/ yyerrlab: /* Make sure we have latest lookahead translation. See comments at user semantic actions for why this is necessary. */ yytoken = yychar == YYEMPTY ? YYEMPTY : YYTRANSLATE (yychar); /* If not already recovering from an error, report this error. */ if (!yyerrstatus) { ++yynerrs; #if ! YYERROR_VERBOSE yyerror (YY_("syntax error")); #else # define YYSYNTAX_ERROR yysyntax_error (&yymsg_alloc, &yymsg, \ yyssp, yytoken) { char const *yymsgp = YY_("syntax error"); int yysyntax_error_status; yysyntax_error_status = YYSYNTAX_ERROR; if (yysyntax_error_status == 0) yymsgp = yymsg; else if (yysyntax_error_status == 1) { if (yymsg != yymsgbuf) YYSTACK_FREE (yymsg); yymsg = (char *) YYSTACK_ALLOC (yymsg_alloc); if (!yymsg) { yymsg = yymsgbuf; yymsg_alloc = sizeof yymsgbuf; yysyntax_error_status = 2; } else { yysyntax_error_status = YYSYNTAX_ERROR; yymsgp = yymsg; } } yyerror (yymsgp); if (yysyntax_error_status == 2) goto yyexhaustedlab; } # undef YYSYNTAX_ERROR #endif } if (yyerrstatus == 3) { /* If just tried and failed to reuse lookahead token after an error, discard it. */ if (yychar <= YYEOF) { /* Return failure if at end of input. */ if (yychar == YYEOF) YYABORT; } else { yydestruct ("Error: discarding", yytoken, &yylval); yychar = YYEMPTY; } } /* Else will try to reuse lookahead token after shifting the error token. */ goto yyerrlab1; /*---------------------------------------------------. | yyerrorlab -- error raised explicitly by YYERROR. | `---------------------------------------------------*/ yyerrorlab: /* Pacify compilers like GCC when the user code never invokes YYERROR and the label yyerrorlab therefore never appears in user code. */ if (/*CONSTCOND*/ 0) goto yyerrorlab; /* Do not reclaim the symbols of the rule which action triggered this YYERROR. */ YYPOPSTACK (yylen); yylen = 0; YY_STACK_PRINT (yyss, yyssp); yystate = *yyssp; goto yyerrlab1; /*-------------------------------------------------------------. | yyerrlab1 -- common code for both syntax error and YYERROR. | `-------------------------------------------------------------*/ yyerrlab1: yyerrstatus = 3; /* Each real token shifted decrements this. */ for (;;) { yyn = yypact[yystate]; if (!yypact_value_is_default (yyn)) { yyn += YYTERROR; if (0 <= yyn && yyn <= YYLAST && yycheck[yyn] == YYTERROR) { yyn = yytable[yyn]; if (0 < yyn) break; } } /* Pop the current state because it cannot handle the error token. */ if (yyssp == yyss) YYABORT; yydestruct ("Error: popping", yystos[yystate], yyvsp); YYPOPSTACK (1); yystate = *yyssp; YY_STACK_PRINT (yyss, yyssp); } *++yyvsp = yylval; /* Shift the error token. */ YY_SYMBOL_PRINT ("Shifting", yystos[yyn], yyvsp, yylsp); yystate = yyn; goto yynewstate; /*-------------------------------------. | yyacceptlab -- YYACCEPT comes here. | `-------------------------------------*/ yyacceptlab: yyresult = 0; goto yyreturn; /*-----------------------------------. | yyabortlab -- YYABORT comes here. | `-----------------------------------*/ yyabortlab: yyresult = 1; goto yyreturn; #if !defined(yyoverflow) || YYERROR_VERBOSE /*-------------------------------------------------. | yyexhaustedlab -- memory exhaustion comes here. | `-------------------------------------------------*/ yyexhaustedlab: yyerror (YY_("memory exhausted")); yyresult = 2; /* Fall through. */ #endif yyreturn: if (yychar != YYEMPTY) { /* Make sure we have latest lookahead translation. See comments at user semantic actions for why this is necessary. */ yytoken = YYTRANSLATE (yychar); yydestruct ("Cleanup: discarding lookahead", yytoken, &yylval); } /* Do not reclaim the symbols of the rule which action triggered this YYABORT or YYACCEPT. */ YYPOPSTACK (yylen); YY_STACK_PRINT (yyss, yyssp); while (yyssp != yyss) { yydestruct ("Cleanup: popping", yystos[*yyssp], yyvsp); YYPOPSTACK (1); } #ifndef yyoverflow if (yyss != yyssa) YYSTACK_FREE (yyss); #endif #if YYERROR_VERBOSE if (yymsg != yymsgbuf) YYSTACK_FREE (yymsg); #endif /* Make sure YYID is used. */ return YYID (yyresult); } /* Line 2067 of yacc.c */ #line 298 "genvm-parse.y" void yyprint (FILE *fp, int tok, const YYSTYPE *val) { switch (tok) { case NUMBER: fprintf (fp, "%d", (val)->num); break; case ID: case EXPR: fprintf (fp, "%s", (val)->text); break; } } void yyerror (const char *s) { errors = 1; fprintf (stderr, "vm.def:%d: %s\n", yylineno, s); } /* Define an operation that is used into a bytecode declaration. We use an AVL tree to store them so that we can do fast searches, and we can detect duplicates. */ operation_info * define_operation (const char *name) { avl_node_t **p = (avl_node_t **) &op_root; operation_info *node; operation_info *operation = NULL; while (*p) { int cmp; operation = (operation_info *) *p; cmp = strcmp(name, operation->name); if (cmp < 0) p = &(*p)->avl_left; else if (cmp > 0) p = &(*p)->avl_right; else { yyerror ("duplicate operation"); return NULL; } } node = (operation_info *) calloc(1, sizeof(operation_info)); node->avl.avl_parent = (avl_node_t *) operation; node->avl.avl_left = node->avl.avl_right = NULL; node->name = name; *p = &(node->avl); avl_rebalance(&node->avl, (avl_node_t **) &op_root); return node; } operation_info * get_operation (const char *name) { avl_node_t **p = (avl_node_t **) &op_root; operation_info *operation = NULL; while (*p) { int cmp; operation = (operation_info *) *p; cmp = strcmp(name, operation->name); if (cmp < 0) p = &(*p)->avl_left; else if (cmp > 0) p = &(*p)->avl_right; else return operation; } return NULL; } operation_list * append_to_operation_list (operation_list *list, const char *name, id_list *args) { operation_list *node, *result; operation_info *op = get_operation (name); if (!op) { yyerror ("undefined operation"); return list; } node = calloc (1, sizeof (operation_list)); if (!list) result = node; else { result = list; *(result->pnext) = node; } node->op = op; node->args = args; result->pnext = &(node->next); return result; } id_list * append_to_id_list (id_list *list, const char *name) { int len = strlen (name); id_list *node = calloc (1, sizeof (id_list) + len); id_list *result; memcpy (node->id, name, len); if (!list) result = node; else { result = list; *(result->pnext) = node; } result->pnext = &(node->next); return result; } int emit_id_list (const id_list *list, const char *sep, const char *before, const char *after) { int n = 0; if (!list) return 0; filcat (out_fil, before); while (list) { filcat (out_fil, list->id); list = list->next; filcat (out_fil, list ? sep : after); n++; } return n; } void free_id_list (id_list *list) { id_list *next; while (list) { next = list->next; free (list); list = next; } } void set_curr_op_stack (id_list *in, id_list *out) { id_list *read = in; id_list *list; id_list *last_read = NULL; if (!curr_op) return; /* Find the names that are a common prefix for the input and output stack, and move them to the READ list. */ while (in && out && !strcmp (in->id, out->id)) { id_list *next; next = out->next; free (out); out = next; /* The in nodes are still referenced through READ. */ last_read = in; in = in->next; } if (last_read) { if (in) in->pnext = read->pnext; last_read->next = NULL; read->pnext = &(last_read->next); } else /* The slots are all read and written, none is just read. */ read = NULL; curr_op->in = in; curr_op->out = out; curr_op->read = read; /* Compute and save the count, we'll use it to combine the stack effects. */ for (curr_op->n_in = 0, list = curr_op->in; list; list = list->next, curr_op->n_in++); for (curr_op->n_out = 0, list = curr_op->out; list; list = list->next, curr_op->n_out++); for (curr_op->n_read = 0, list = curr_op->read; list; list = list->next, curr_op->n_read++); } void free_operation_list (operation_list *list) { operation_list *next; while (list) { next = list->next; free_id_list (list->args); free (list); list = next; } } void emit_var_declarations (const char *base, const char *type, int first, int n) { int i; if (!n) return; for (i = first; n--; i++) filprintf (out_fil, "%s %s%d", i == first ? type : ",", base, i); filprintf (out_fil, ";\n"); } void emit_var_defines (id_list *list, int sp) { for (; list; list = list->next, sp++) filprintf (out_fil, "#define %s %s%d\n", list->id, (sp <= 0 ? "_stack" : "_extra"), (sp < 0 ? -sp : sp)); } void emit_operation_list (operation_list *oplist) { operation_list *list; int deepest_read = 0, deepest_write = 0, sp, max_height = 0, deepest_write_so_far = 0, i; if (!oplist) return; filprintf (out_fil, " {\n"); /* Compute the overall effect on the stack of the superoperator. The number of elements that are read is usually op->n_read + op->n_in, but in the presence of many operations we need to adjust this for the balance left by previous operations; the same also holds for the number of written elements, which is usually op->in. We also track the maximum height of the stack which is the number of _EXTRA variables that we need. */ for (sp = 0, list = oplist; list; list = list->next) { operation_info *op = list->op; int balance = op->n_out - op->n_in; deepest_read = MAX (deepest_read, op->n_read + op->n_in - sp); deepest_write = MAX (deepest_write, op->n_in - sp); sp += balance; max_height = MAX (max_height, sp); } /* Declare the variables. */ emit_var_declarations ("_stack", " OOP", 0, deepest_read); emit_var_declarations ("_extra", " OOP", 1, max_height); /* Read the input items from the stack. */ for (i = deepest_read; --i >= 0; ) filprintf (out_fil, " _stack%d = STACK_AT (%d);\n", i, i); /* We keep track of the stack effect here too: we pass the current balance to emit_operation_invocation so that it can assign the correct _STACK/_EXTRA variables to the operands of OP, and we pass the number of dirty _STACK variables (tracked by DEEPEST_WRITE_SO_FAR) so that it can emit the PREPARE_STACK macro if necessary. */ for (sp = 0, list = oplist; list; list = list->next) { operation_info *op = list->op; int balance = op->n_out - op->n_in; emit_operation_invocation (op, list->args, sp, deepest_write_so_far); deepest_write_so_far = MAX (deepest_write_so_far, op->n_in - sp); sp += balance; } /* Write back to the stack the items that were overwritten, and emit pushes/pops if the height of the stack has changed. */ emit_stack_update (sp, deepest_write, " ", ";"); filprintf (out_fil, " }\n"); } void emit_operation_invocation (operation_info *op, struct id_list *args, int sp, int deepest_write) { id_list *list, *actual; filprintf (out_fil, " /* %s (", op->name); emit_id_list (op->read, " ", " ", " |"); emit_id_list (op->in, " ", " ", ""); filprintf (out_fil, " --"); emit_id_list (op->read, " ", " ", " |"); emit_id_list (op->out, " ", " ", ""); filprintf (out_fil, " ) */\n"); filprintf (out_fil, " do\n"); filprintf (out_fil, " {\n"); /* Evaluate the arguments. */ for (list = op->args, actual = args; list && actual; list = list->next, actual = actual->next) filprintf (out_fil, "\tint %s = %s;\n", list->id, actual->id); if (list) yyerror ("too few parameters"); if (actual) yyerror ("too many parameters"); if (op->needs_prepare_stack) { filprintf (out_fil, "#define PREPARE_STACK() do { \\\n"); emit_stack_update (sp, deepest_write, " ", "; \\"); filprintf (out_fil, " } while (0)\n"); } if (op->needs_branch_label) filprintf (out_fil, "#define BRANCH_LABEL(local_label) %s_%d_##local_label\n", op->name, op->instantiations++); /* Associate the temporary variables to the stack positions. */ emit_var_defines (op->read, sp - op->n_read - op->n_in + 1); emit_var_defines (op->in, sp - op->n_in + 1); emit_var_defines (op->out, sp - op->n_in + 1); filprintf (out_fil, "%s\n", op->code); /* Leave things clean. */ if (op->needs_branch_label) filprintf (out_fil, "#undef BRANCH_LABEL\n\n"); if (op->needs_prepare_stack) filprintf (out_fil, "#undef PREPARE_STACK\n"); emit_id_list (op->read, "\n#undef ", "#undef ", "\n"); emit_id_list (op->in, "\n#undef ", "#undef ", "\n"); emit_id_list (op->out, "\n#undef ", "#undef ", "\n"); filprintf (out_fil, " }\n"); filprintf (out_fil, " while (0);\n"); } void emit_stack_update (int sp, int deepest_write, const char *before, const char *after) { int i; for (i = deepest_write; --i >= MAX(0, -sp); ) filprintf (out_fil, "%sSTACK_AT (%d) = _stack%d%s\n", before, i, i, after); /* Either pop the input items in excess, or push the output ones. */ if (sp < 0) filprintf (out_fil, "%sPOP_N_OOPS (%d)%s\n", before, -sp, after); else for (i = 1; i <= sp; i++) filprintf (out_fil, "%sPUSH_OOP (_extra%d)%s\n", before, i, after); } void emit_table (table_info *t) { int i; printf (" static void *%s[256] = {\n", t->name); for (i = 0; i < 256; i += 4) printf (" %s%s, %s%s, %s%s, %s%s%c /* %3d */\n", t->entry[i] ? "&&" : "", t->entry[i] ? t->entry[i] : "NULL", t->entry[i+1] ? "&&" : "", t->entry[i+1] ? t->entry[i+1] : "NULL", t->entry[i+2] ? "&&" : "", t->entry[i+2] ? t->entry[i+2] : "NULL", t->entry[i+3] ? "&&" : "", t->entry[i+3] ? t->entry[i+3] : "NULL", i + 4 == 256 ? ' ' : ',', i); printf (" };\n\n"); } table_info * define_table (char *name) { table_info *t = (table_info *) calloc(1, sizeof(table_info)); t->name = name; return t; } void set_table (table_info *t, int from, int to, char *value) { int i; id_list **p_last = t->pool ? t->pool->pnext : &t->pool; id_list *last; t->pool = append_to_id_list (t->pool, value); last = *p_last; for (i = from; i <= to; i++) t->entry[i] = last->id; } void free_table (table_info *t) { free_id_list (t->pool); free (t->name); free (t); } int filprintf (Filament *fil, const char *format, ...) { va_list ap; STREAM *out = stream_new (fil, SNV_UNLIMITED, NULL, snv_filputc); int result; va_start (ap, format); result = stream_vprintf (out, format, ap); va_end (ap); stream_delete (out); return result; } int main () { char *code; errors = 0; printf ("/* Automatically generated by genvm, do not edit! */\n"); out_fil = filnew (NULL, 0); if (yyparse () || errors) exit (1); printf (" goto jump_around;\n"); code = fildelete (out_fil); fputs (code, stdout); printf ("jump_around:\n ;\n"); exit (0); } smalltalk-3.2.5/libgst/sym.c0000644000175000017500000013374412130343734012702 00000000000000/******************************** -*- C -*- **************************** * * Symbol Table module. * * ***********************************************************************/ /*********************************************************************** * * Copyright 1988,89,90,91,92,94,95,99,2000,2001,2002,2003, * 2005,2006,2007,2008,2009 Free Software Foundation, Inc. * Written by Steve Byrne. * * This file is part of GNU Smalltalk. * * GNU Smalltalk is free software; you can redistribute it and/or modify it * under the terms of the GNU General Public License as published by the Free * Software Foundation; either version 2, or (at your option) any later * version. * * Linking GNU Smalltalk statically or dynamically with other modules is * making a combined work based on GNU Smalltalk. Thus, the terms and * conditions of the GNU General Public License cover the whole * combination. * * In addition, as a special exception, the Free Software Foundation * give you permission to combine GNU Smalltalk with free software * programs or libraries that are released under the GNU LGPL and with * independent programs running under the GNU Smalltalk virtual machine. * * You may copy and distribute such a system following the terms of the * GNU GPL for GNU Smalltalk and the licenses of the other code * concerned, provided that you include the source code of that other * code when and as the GNU GPL requires distribution of source code. * * Note that people who make modified versions of GNU Smalltalk are not * obligated to grant this special exception for their modified * versions; it is their choice whether to do so. The GNU General * Public License gives permission to release a modified version without * this exception; this exception also makes it possible to release a * modified version which carries forward this exception. * * GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or * FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for * more details. * * You should have received a copy of the GNU General Public License along with * GNU Smalltalk; see the file COPYING. If not, write to the Free Software * Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * ***********************************************************************/ #include "gstpriv.h" #include "pointer-set.h" typedef struct { OBJ_HEADER; OOP nextLink; OOP symbol; } *sym_link; typedef struct symbol_list *symbol_list; struct symbol_list { OOP symbol; mst_Boolean readOnly; int index; symbol_list prevSymbol; }; /* Represents all the identifiers, both arguments and temporaries, which are declared in a given scope. Nested scopes result in nested instances of the scope struct, with the current scope always being the innermost at any point during the compilation. */ typedef struct scope *scope; struct scope { scope prevScope; unsigned int numArguments; unsigned int numTemporaries; symbol_list symbols; }; /* Represents all the pools (namespaces) which are declared in the current scope. This information is relatively complex to compute, so it's kept cached. */ typedef struct pool_list *pool_list; struct pool_list { OOP poolOOP; pool_list next; }; typedef struct symbol_info { OOP *symbolVar; const char *value; } symbol_info; /* These variables hold various symbols needed mostly by the compiler and the C interface. It is important that these symbols are *not* included in the builtin selectors list (builtins.gperf) because of the way we create symbols in _gst_init_symbols_pass1. */ OOP _gst_and_symbol = NULL; OOP _gst_as_scaled_decimal_radix_scale_symbol = NULL; OOP _gst_bad_return_error_symbol = NULL; OOP _gst_boolean_symbol = NULL; OOP _gst_byte_array_out_symbol = NULL; OOP _gst_byte_array_symbol = NULL; OOP _gst_c_object_ptr_symbol = NULL; OOP _gst_c_object_symbol = NULL; OOP _gst_category_symbol = NULL; OOP _gst_char_symbol = NULL; OOP _gst_does_not_understand_symbol = NULL; OOP _gst_double_symbol = NULL; OOP _gst_false_symbol = NULL; OOP _gst_float_symbol = NULL; OOP _gst_if_false_if_true_symbol = NULL; OOP _gst_if_false_symbol = NULL; OOP _gst_if_true_if_false_symbol = NULL; OOP _gst_if_true_symbol = NULL; OOP _gst_int_symbol = NULL; OOP _gst_long_double_symbol = NULL; OOP _gst_long_symbol = NULL; OOP _gst_must_be_boolean_symbol = NULL; OOP _gst_nil_symbol = NULL; OOP _gst_or_symbol = NULL; OOP _gst_permission_symbol = NULL; OOP _gst_primitive_symbol = NULL; OOP _gst_repeat_symbol = NULL; OOP _gst_self_smalltalk_symbol = NULL; OOP _gst_self_symbol = NULL; OOP _gst_short_symbol = NULL; OOP _gst_smalltalk_symbol = NULL; OOP _gst_smalltalk_namespace_symbol = NULL; OOP _gst_start_execution_symbol = NULL; OOP _gst_string_out_symbol = NULL; OOP _gst_string_symbol = NULL; OOP _gst_super_symbol = NULL; OOP _gst_symbol_symbol = NULL; OOP _gst_symbol_out_symbol = NULL; OOP _gst_symbol_table = NULL; OOP _gst_terminate_symbol = NULL; OOP _gst_times_repeat_symbol = NULL; OOP _gst_to_by_do_symbol = NULL; OOP _gst_to_do_symbol = NULL; OOP _gst_true_symbol = NULL; OOP _gst_uchar_symbol = NULL; OOP _gst_uint_symbol = NULL; OOP _gst_ulong_symbol = NULL; OOP _gst_ushort_symbol = NULL; OOP _gst_undeclared_symbol = NULL; OOP _gst_unknown_symbol = NULL; OOP _gst_value_with_rec_with_args_symbol = NULL; OOP _gst_variadic_smalltalk_symbol = NULL; OOP _gst_variadic_symbol = NULL; OOP _gst_vm_primitives_symbol = NULL; OOP _gst_void_symbol = NULL; OOP _gst_wchar_symbol = NULL; OOP _gst_wstring_symbol = NULL; OOP _gst_wstring_out_symbol = NULL; OOP _gst_while_false_colon_symbol = NULL; OOP _gst_while_false_symbol = NULL; OOP _gst_while_true_colon_symbol = NULL; OOP _gst_while_true_symbol = NULL; OOP _gst_current_namespace = NULL; OOP temporaries_dictionary = NULL; /* The list of selectors for the send immediate bytecode. */ struct builtin_selector _gst_builtin_selectors[256] = {}; /* True if undeclared globals can be considered forward references. */ enum undeclared_strategy _gst_use_undeclared = UNDECLARED_TEMPORARIES; /* Answer whether OOP is a Smalltalk String LEN characters long and these characters match the first LEN characters of STR (which must not have embedded NULs). */ static mst_Boolean is_same_string (const char *str, OOP oop, int len); /* Allocate memory for a symbol of length LEN and whose contents are STR. This function does not fill in the object's class because it is called upon image loading, when the classes have not been initialized yet. */ static OOP alloc_symbol_oop (const char *str, int len); /* Link SYMBOLOOP into the symbol table (using the given hash table index), and fill the class slot of the symbol. */ static OOP alloc_symlink (OOP symbolOOP, uintptr_t index); /* Answer whether C is considered a white space character in Smalltalk programs. */ static mst_Boolean is_white_space (char c); /* Free the list of symbols declared in the given SCOPE. */ static void free_scope_symbols (scope scope); /* Scans a variable name (letters and digits, initial letter), and return a symbol for it. PP is a pointer to a pointer to the start of the string to be scanned, which may be pointing at either whitespace or start of variable. At end, it points to the first character after the initial whitespace, if any. ENDP instead is initialized by the function to point to first character after the parsed variable name, which may be NUL. */ static void parse_variable_name (const char ** pp, const char ** endp); /* This fills ENT's fields with the contents of its parameters. */ static void fill_symbol_entry (symbol_entry * ent, scope_type scope, mst_Boolean readOnly, OOP symbol, int index, unsigned int scopeDistance); /* Scans a variable name (letters and digits, initial letter), and return a symbol for it. PP is a pointer to a pointer to the start of the string to be scanned. May be pointing at either whitespace or start of variable. At end, points to first character after the parsed variable name, which may be NUL. The output is a Smalltalk Symbol, _gst_nil_oop if no variable name is found. */ static OOP scan_name (const char ** pp); /* This creates a Symbol containing LEN bytes starting at STR and puts it in the symbol list, or returns an existing one if it is found. */ static OOP intern_counted_string (const char *str, int len); /* This is a hack. It is the same as _gst_intern_string except that, if the given symbol is pointed to by PTESTOOP, we increment PTESTOOP and return the old value. This works and speeds up image loading, because we are careful to create the same symbols in _gst_init_symbols_passN and _gst_restore_symbols. */ static inline OOP intern_string_fast (const char *str, OOP *pTestOOP); /* This looks for SYMBOL among the instance variables that the current class declares, and returns the index of the variable if one is found. */ static int instance_variable_index (OOP symbol); /* This checks if the INDEX-th instance variable among those that the current class declares is read-only. Read-only index variables are those that are declared by a trusted super-class of an untrusted subclass. */ static mst_Boolean is_instance_variable_read_only (int index); /* This looks for SYMBOL among the arguments and temporary variables that the current scope sees, and returns the entry in the symbol list for the variable if it is found. */ static symbol_list find_local_var (scope scope, OOP symbol); /* This looks for SYMBOL among the global variables that the current scope sees, including superspaces if any, and returns the entry in the symbol list for the variable if it is found. */ static OOP find_class_variable (OOP varName); static scope cur_scope = NULL; static pool_list linearized_pools = NULL; /* This is an array of symbols which the virtual machine knows about, and is used to restore the global variables upon image load. */ static const symbol_info sym_info[] = { {&_gst_and_symbol, "and:"}, {&_gst_as_scaled_decimal_radix_scale_symbol, "asScaledDecimal:radix:scale:"}, {&_gst_bad_return_error_symbol, "badReturnError"}, {&_gst_byte_array_symbol, "byteArray"}, {&_gst_byte_array_out_symbol, "byteArrayOut"}, {&_gst_boolean_symbol, "boolean"}, {&_gst_c_object_symbol, "cObject"}, {&_gst_c_object_ptr_symbol, "cObjectPtr"}, {&_gst_category_symbol, "category:"}, {&_gst_char_symbol, "char"}, {&_gst_uchar_symbol, "uChar"}, {&_gst_does_not_understand_symbol, "doesNotUnderstand:"}, {&_gst_float_symbol, "float"}, {&_gst_double_symbol, "double"}, {&_gst_false_symbol, "false"}, {&_gst_if_false_if_true_symbol, "ifFalse:ifTrue:"}, {&_gst_if_false_symbol, "ifFalse:"}, {&_gst_if_true_if_false_symbol, "ifTrue:ifFalse:"}, {&_gst_if_true_symbol, "ifTrue:"}, {&_gst_int_symbol, "int"}, {&_gst_uint_symbol, "uInt"}, {&_gst_long_double_symbol, "longDouble"}, {&_gst_long_symbol, "long"}, {&_gst_ulong_symbol, "uLong"}, {&_gst_must_be_boolean_symbol, "mustBeBoolean"}, {&_gst_nil_symbol, "nil"}, {&_gst_or_symbol, "or:"}, {&_gst_primitive_symbol, "primitive:"}, {&_gst_repeat_symbol, "repeat"}, {&_gst_self_symbol, "self"}, {&_gst_self_smalltalk_symbol, "selfSmalltalk"}, {&_gst_short_symbol, "short"}, {&_gst_ushort_symbol, "uShort"}, {&_gst_smalltalk_symbol, "smalltalk"}, {&_gst_smalltalk_namespace_symbol, "Smalltalk"}, {&_gst_start_execution_symbol, "startExecution:"}, {&_gst_string_out_symbol, "stringOut"}, {&_gst_string_symbol, "string"}, {&_gst_super_symbol, "super"}, {&_gst_symbol_symbol, "symbol"}, {&_gst_symbol_out_symbol, "symbolOut"}, {&_gst_terminate_symbol, "__terminate"}, {&_gst_times_repeat_symbol, "timesRepeat:"}, {&_gst_to_by_do_symbol, "to:by:do:"}, {&_gst_to_do_symbol, "to:do:"}, {&_gst_true_symbol, "true"}, {&_gst_undeclared_symbol, "Undeclared"}, {&_gst_unknown_symbol, "unknown"}, {&_gst_value_with_rec_with_args_symbol, "valueWithReceiver:withArguments:"}, {&_gst_variadic_symbol, "variadic"}, {&_gst_variadic_smalltalk_symbol, "variadicSmalltalk"}, {&_gst_vm_primitives_symbol, "VMPrimitives"}, {&_gst_void_symbol, "void"}, {&_gst_wchar_symbol, "wchar"}, {&_gst_wstring_symbol, "wstring"}, {&_gst_wstring_out_symbol, "wstringOut"}, {&_gst_while_false_colon_symbol, "whileFalse:"}, {&_gst_while_false_symbol, "whileFalse"}, {&_gst_while_true_colon_symbol, "whileTrue:"}, {&_gst_while_true_symbol, "whileTrue"}, {NULL, NULL}, }; const char * _gst_get_scope_kind (scope_type scope) { switch (scope) { case SCOPE_TEMPORARY: return "argument"; case SCOPE_RECEIVER: return "instance variable"; case SCOPE_GLOBAL: return "global variable"; case SCOPE_SPECIAL: return "special variable"; default: abort (); } } int _gst_get_arg_count (void) { return (cur_scope->numArguments); } int _gst_get_temp_count (void) { return (cur_scope->numTemporaries); } void _gst_push_new_scope (void) { scope newScope; newScope = (scope) xmalloc (sizeof (*newScope)); newScope->prevScope = cur_scope; newScope->symbols = NULL; newScope->numArguments = 0; newScope->numTemporaries = 0; cur_scope = newScope; } void _gst_pop_old_scope (void) { scope oldScope; oldScope = cur_scope; cur_scope = cur_scope->prevScope; free_scope_symbols (oldScope); xfree (oldScope); } void _gst_pop_all_scopes (void) { pool_list next; while (cur_scope) _gst_pop_old_scope (); while (linearized_pools) { next = linearized_pools->next; xfree (linearized_pools); linearized_pools = next; } } int _gst_declare_arguments (tree_node args) { if (args->nodeType == TREE_UNARY_EXPR) return (0); else if (args->nodeType == TREE_BINARY_EXPR) _gst_declare_name (args->v_expr.expression->v_list.name, false, false); else { for (args = args->v_expr.expression; args != NULL; args = args->v_list.next) if (_gst_declare_name (args->v_list.value->v_list.name, false, false) == -1) return -1; } /* Arguments are always declared first! */ cur_scope->numArguments = cur_scope->numTemporaries; cur_scope->numTemporaries = 0; return (cur_scope->numArguments); } int _gst_declare_temporaries (tree_node temps) { int n; for (n = 0; temps != NULL; n++, temps = temps->v_list.next) if (_gst_declare_name (temps->v_list.name, true, false) == -1) return -1; return (n); } int _gst_declare_block_arguments (tree_node args) { for (; args != NULL; args = args->v_list.next) if (_gst_declare_name (args->v_list.name, false, false) == -1) return -1; /* Arguments are always declared first! */ cur_scope->numArguments = cur_scope->numTemporaries; cur_scope->numTemporaries = 0; return (cur_scope->numArguments); } void _gst_undeclare_name (void) { symbol_list oldList; oldList = cur_scope->symbols; cur_scope->symbols = cur_scope->symbols->prevSymbol; xfree (oldList); } int _gst_declare_name (const char *name, mst_Boolean writeable, mst_Boolean allowDup) { symbol_list newList; OOP symbol = _gst_intern_string (name); if (!allowDup && find_local_var (cur_scope, symbol) != NULL) return -1; newList = (symbol_list) xmalloc (sizeof (struct symbol_list)); newList->symbol = symbol; newList->index = cur_scope->numArguments + cur_scope->numTemporaries; newList->readOnly = !writeable; newList->prevSymbol = cur_scope->symbols; /* Arguments are always declared first, so we can assume it is a temporary -- if it is not, _gst_declare_arguments and _gst_declare_block_arguments will fix it. */ cur_scope->numTemporaries++; cur_scope->symbols = newList; return (newList->index); } static void free_scope_symbols (scope scope) { symbol_list oldList; for (oldList = scope->symbols; oldList != NULL; oldList = scope->symbols) { scope->symbols = oldList->prevSymbol; xfree (oldList); } } /* Here are some notes on the design of the shared pool resolution order, codenamed "TwistedPools". The design should maintain a sense of containment within namespaces, while still allowing reference to all inherited environments, as is traditionally expected. The fundamental problem is that when a subclass is not in the same namespace as the superclass, we want to give a higher priority to the symbols in the namespaces imported by the subclass, than to the symbols in the superclass namespaces. As such, no simple series of walks up the inheritance tree paired with pool-adds will give us a good search order. Instead, we build a complete linearization of the namespaces (including the superspaces) and look up a symbol in each namespace locally, without looking at the superspaces. This is the essential variable search algorithm for TwistedPools. 1. Given a class, starting with the method-owning class: a. Search the class pool. b. Search this class's shared pools in topological order, left-to-right, skipping any pools that are any of this class's namespace or superspaces. c. Search this class's namespace and each superspace in turn before first encounter of a namespace that contains, directly or indirectly, the superclass. This means that if the superclass is in the same namespace or a subspace, no namespaces are searched. 2. Move to the superclass, and repeat from #1. Combination details =================== While the add-namespaces step above could be less eager to add namespaces, by allowing any superclass to stop the namespace crawl, rather than just the direct superclasses, it is already less eager than the shared pool manager. The topological sort is an obviously good choice, but why not allow superclasses' namespaces to provide deletions as well as the pool-containing class? While both alternatives have benefits, an eager import of all superspaces, besides those that already contain the pool-containing class, would most closely match what's expected. An argument could also be made that by adding a namespace to shared pools, you expect all superspaces to be included. However, consider the usual case of namespaces in shared pools: imports. While you would want it to completely load an alternate namespace hierarchy, I think you would not want it to inject Smalltalk early into the variable search. Consider this diagram: Smalltalk | MyCompany / \ / \ MyProject MyLibrary / / \ / ModA ModB MyLibModule If you were to use ModB as a pool in a class in MyLibModule, I think it is most reasonable that ModB and MyLibrary be immediately imported, but MyCompany and Smalltalk wait until you reach that point in the namespace walk. In other words, pools only add that part of themselves, which would not be otherwise reachable via the class environment. (Note that, as a side effect, adding MyCompany as a pool will have no effect). Another argument could be made to delay further the namespace walk, waiting to resolve until no superclass is contained in a given namespace, based on the idea of exiting a namespace hierarchy while walking superclasses, then reentering it. Disregarding the unlikelihood of such an organization, it probably would be less confusing to resolve the hierarchy being left first, in case the interloping hierarchy introduces conflicting symbols of its own. There is no objective argument regarding the above points of contention, and no formal proofs, because convenient global name resolution is entirely a matter of feeling, because a formal programmer could always explicitly spell out the path to every variable. Namespaces also have imports (shared pools) of their own, thereby allowing users to import external namespaces for every class in a namespace, rather than each class. These shared pools should also twist nicely. Here is how I think it would best work: after searching any namespace, combine its shared pools as classes' shared pools are combined, removing all elements that are any of this namespace or its superspaces, and search the combination from left to right. There is one important difference between namespace-sharedpools and class-sharedpools: while class sharedpools export their imports to subclasses, namespaces should not reexport bindings made available by way of shared pools. As such, the bindings provided by a namespace are only available when compiling methods that actually exist in that namespace (including its subspaces). */ OOP _gst_get_class_object (OOP classOOP) { if (OOP_CLASS (classOOP) == _gst_metaclass_class) classOOP = METACLASS_INSTANCE (classOOP); while (OOP_CLASS (classOOP) == _gst_behavior_class || OOP_CLASS (classOOP) == _gst_class_description_class) classOOP = SUPERCLASS (classOOP); return classOOP; } /* Add poolOOP after the node whose next pointer is in P_END. Return the new next node (actually its next pointer). */ static pool_list * add_pool (OOP poolOOP, pool_list *p_end) { pool_list entry; if (IS_NIL (poolOOP)) return p_end; entry = xmalloc (sizeof (struct pool_list)); entry->poolOOP = poolOOP; entry->next = NULL; *p_end = entry; return &entry->next; } /* Make a pointer set with POOLOOP and all of its superspaces. */ static struct pointer_set_t * make_with_all_superspaces_set (OOP poolOOP) { struct pointer_set_t *pset = pointer_set_create (); if (is_a_kind_of (OOP_CLASS (poolOOP), _gst_class_class)) poolOOP = _gst_class_variable_dictionary (poolOOP); while (is_a_kind_of (OOP_CLASS (poolOOP), _gst_abstract_namespace_class)) { gst_namespace pool; pointer_set_insert (pset, poolOOP); pool = (gst_namespace) OOP_TO_OBJ (poolOOP); poolOOP = pool->superspace; } /* Add the last if not nil. */ if (is_a_kind_of (OOP_CLASS (poolOOP), _gst_dictionary_class)) pointer_set_insert (pset, poolOOP); return pset; } /* predeclared for add_namespace */ static pool_list *combine_local_pools (OOP sharedPoolsOOP, struct pointer_set_t *white, pool_list *p_end); /* Add, after the node whose next pointer is in P_END, the namespace POOLOOP and all of its superspaces except those in EXCEPT. The new last node is returned (actually its next pointer). */ static pool_list * add_namespace (OOP poolOOP, struct pointer_set_t *except, pool_list *p_end) { if (is_a_kind_of (OOP_CLASS (poolOOP), _gst_class_class)) poolOOP = _gst_class_variable_dictionary (poolOOP); for (;;) { gst_namespace pool; OOP importsOOP; if (!is_a_kind_of (OOP_CLASS (poolOOP), _gst_dictionary_class)) return p_end; if (!except || !pointer_set_contains (except, poolOOP)) p_end = add_pool (poolOOP, p_end); /* Add imports and try to find a super-namespace */ if (!is_a_kind_of (OOP_CLASS (poolOOP), _gst_abstract_namespace_class)) return p_end; pool = (gst_namespace) OOP_TO_OBJ (poolOOP); importsOOP = pool->sharedPools; if (NUM_OOPS (OOP_TO_OBJ (importsOOP))) { struct pointer_set_t *pset; pset = make_with_all_superspaces_set (poolOOP); p_end = combine_local_pools (importsOOP, pset, p_end); pointer_set_destroy (pset); } poolOOP = pool->superspace; } } /* Add POOLOOP and all of its superspaces to the list in the right order: 1. Start a new list. 2. From right to left, descend into each given pool not visited. 3. Recursively visit the superspace, then... 4. Mark this pool as visited, and add to the beginning of #1's list. 5. After all recursions exit, the list is appended at the end of the linearized list of pools. This function takes care of 3-4. These two steps implement a topological sort on the reverse of the namespace tree; it is explicitly modeled after CLOS class precedence. */ static void visit_pool (OOP poolOOP, struct pointer_set_t *grey, struct pointer_set_t *white, pool_list *p_head, pool_list *p_tail) { pool_list entry; if (is_a_kind_of (OOP_CLASS (poolOOP), _gst_class_class)) poolOOP = _gst_class_variable_dictionary (poolOOP); if (!is_a_kind_of (OOP_CLASS (poolOOP), _gst_dictionary_class)) return; if (pointer_set_contains (white, poolOOP)) return; if (pointer_set_contains (grey, poolOOP)) { _gst_errorf ("circular dependency in pool dictionaries"); return; } /* Visit the super-namespace first, this amounts to processing the hierarchy in reverse order (see Class>>#allSharedPoolDictionariesDo:). */ pointer_set_insert (grey, poolOOP); if (is_a_kind_of (OOP_CLASS (poolOOP), _gst_abstract_namespace_class)) { gst_namespace pool = (gst_namespace) OOP_TO_OBJ (poolOOP); if (!IS_NIL (pool->superspace)) visit_pool (pool->superspace, grey, white, p_head, p_tail); } pointer_set_insert (white, poolOOP); /* Add an entry for this one at the beginning of the list. We need to maintain the tail too, because combine_local_pools must return it. */ entry = xmalloc (sizeof (struct pool_list)); entry->poolOOP = poolOOP; entry->next = *p_head; *p_head = entry; if (!*p_tail) *p_tail = entry; } /* Run visit_pool on all the shared pools, starting with WHITE as the visited set so that those are not added. The resulting list is built separately, and at the end all of the namespaces in the list are tacked after the node whose next pointer is in P_END. The new last node is returned (actually its next pointer). */ static pool_list * combine_local_pools (OOP sharedPoolsOOP, struct pointer_set_t *white, pool_list *p_end) { struct pointer_set_t *grey = pointer_set_create (); pool_list head = NULL; pool_list tail = NULL; int numPools, i; /* Visit right-to-left because visit_pool adds to the beginning. */ numPools = NUM_OOPS (OOP_TO_OBJ (sharedPoolsOOP)); for (i = numPools; --i >= 0; ) { OOP poolDictionaryOOP = ARRAY_AT (sharedPoolsOOP, i + 1); visit_pool (poolDictionaryOOP, grey, white, &head, &tail); } pointer_set_destroy (grey); if (head) { /* If anything was found, tack the list after P_END and return the new tail. */ *p_end = head; return &tail->next; } else return p_end; } /* Add the list of resolved pools for CLASS_OOP. This includes: 1) its class pool; 2) its shared pools as added by combine_local_pools, and excluding those found from the environment; 3) the environment and its superspaces, excluding those reachable also from the environment of the superclass. */ static pool_list * add_local_pool_resolution (OOP class_oop, pool_list *p_end) { OOP environmentOOP; gst_class class; struct pointer_set_t *pset; /* First search in the class pool. */ p_end = add_pool (_gst_class_variable_dictionary (class_oop), p_end); /* Then in all the imports not reachable from the environment. */ class = (gst_class) OOP_TO_OBJ (class_oop); environmentOOP = class->environment; pset = make_with_all_superspaces_set (environmentOOP); p_end = combine_local_pools (class->sharedPools, pset, p_end); pointer_set_destroy (pset); /* Then search in the `environments', except those that are already reachable from the superclass. */ class_oop = SUPERCLASS (class_oop); class = (gst_class) OOP_TO_OBJ (class_oop); if (!IS_NIL (class_oop)) pset = make_with_all_superspaces_set (class->environment); else pset = NULL; p_end = add_namespace (environmentOOP, pset, p_end); if (pset) pointer_set_destroy (pset); return p_end; } OOP find_class_variable (OOP varName) { pool_list pool; OOP assocOOP; if (!linearized_pools) { pool_list *p_end = &linearized_pools; OOP myClass; /* Add pools separately for each class. */ for (myClass = _gst_get_class_object (_gst_this_class); !IS_NIL (myClass); myClass = SUPERCLASS (myClass)) p_end = add_local_pool_resolution (myClass, p_end); } for (pool = linearized_pools; pool; pool = pool->next) { assocOOP = dictionary_association_at (pool->poolOOP, varName); if (!IS_NIL (assocOOP)) return (assocOOP); } return (_gst_nil_oop); } int _gst_set_undeclared (enum undeclared_strategy new) { enum undeclared_strategy old = _gst_use_undeclared; if (new != UNDECLARED_CURRENT) _gst_use_undeclared = new; return old; } OOP _gst_push_temporaries_dictionary (void) { OOP old = temporaries_dictionary; temporaries_dictionary = _gst_dictionary_new (8); _gst_register_oop (temporaries_dictionary); return old; } void _gst_pop_temporaries_dictionary (OOP dictionaryOOP) { _gst_unregister_oop (temporaries_dictionary); temporaries_dictionary = dictionaryOOP; } tree_node _gst_find_variable_binding (tree_node list) { OOP symbol, root, assocOOP; tree_node elt; symbol = _gst_intern_string (list->v_list.name); assocOOP = find_class_variable (symbol); for (elt = list; assocOOP != _gst_nil_oop && (elt = elt->v_list.next); ) { root = ASSOCIATION_VALUE (assocOOP); symbol = _gst_intern_string (elt->v_list.name); assocOOP = _gst_namespace_association_at (root, symbol); } if (!IS_NIL (assocOOP)) return _gst_make_oop_constant (&list->location, assocOOP); else if (_gst_use_undeclared == UNDECLARED_GLOBALS && !elt->v_list.next && isupper (*STRING_OOP_CHARS (symbol))) { OOP dictOOP = dictionary_at (_gst_smalltalk_dictionary, _gst_undeclared_symbol); assocOOP = _gst_namespace_association_at (dictOOP, symbol); if (IS_NIL (assocOOP)) assocOOP = NAMESPACE_AT_PUT (dictOOP, symbol, _gst_nil_oop); return _gst_make_oop_constant (&list->location, assocOOP); } /* For temporaries, make a deferred binding so that we can try using a global variable. Unlike namespaces, the temporaries dictionary does not know anything about Undeclared. */ else if (_gst_use_undeclared == UNDECLARED_TEMPORARIES) return _gst_make_deferred_binding_constant (&list->location, list); else return NULL; } OOP _gst_get_undeclared_dictionary () { assert (_gst_use_undeclared == UNDECLARED_TEMPORARIES); return temporaries_dictionary; } mst_Boolean _gst_find_variable (symbol_entry * se, tree_node list) { tree_node resolved; int index; unsigned int scopeDistance; scope scope; symbol_list s; OOP varAssoc; OOP symbol; symbol = _gst_intern_string (list->v_list.name); if (symbol == _gst_self_symbol || symbol == _gst_super_symbol) { fill_symbol_entry (se, SCOPE_SPECIAL, true, symbol, RECEIVER_INDEX, 0); return (true); } else if (symbol == _gst_true_symbol) { fill_symbol_entry (se, SCOPE_SPECIAL, true, symbol, TRUE_INDEX, 0); return (true); } else if (symbol == _gst_false_symbol) { fill_symbol_entry (se, SCOPE_SPECIAL, true, symbol, FALSE_INDEX, 0); return (true); } else if (symbol == _gst_nil_symbol) { fill_symbol_entry (se, SCOPE_SPECIAL, true, symbol, NIL_INDEX, 0); return (true); } else if (symbol == _gst_builtin_selectors[THIS_CONTEXT_SPECIAL].symbol) { fill_symbol_entry (se, SCOPE_SPECIAL, true, symbol, THIS_CONTEXT_INDEX, 0); return (true); } for (scope = cur_scope, scopeDistance = 0; scope != NULL; scope = scope->prevScope, scopeDistance++) { s = find_local_var (scope, symbol); if (s) { fill_symbol_entry (se, SCOPE_TEMPORARY, s->readOnly, symbol, s->index, scopeDistance); return (true); } } index = instance_variable_index (symbol); if (index >= 0) { fill_symbol_entry (se, SCOPE_RECEIVER, is_instance_variable_read_only (index), symbol, index, 0); return (true); } resolved = _gst_find_variable_binding (list); if (!resolved) return (false); varAssoc = _gst_make_constant_oop (resolved); index = _gst_add_forced_object (varAssoc); fill_symbol_entry (se, SCOPE_GLOBAL, _gst_untrusted_methods && !IS_OOP_UNTRUSTED (varAssoc), varAssoc, index, 0); return (true); } static mst_Boolean is_instance_variable_read_only (int index) { int numVars; OOP class_oop; if (!_gst_untrusted_methods) return (false); for (class_oop = _gst_this_class; IS_OOP_UNTRUSTED (class_oop); class_oop = SUPERCLASS (class_oop)) ; numVars = CLASS_FIXED_FIELDS (class_oop); return index + 1 <= numVars; } static int instance_variable_index (OOP symbol) { OOP arrayOOP; int index, numVars; arrayOOP = _gst_instance_variable_array (_gst_this_class); numVars = NUM_OOPS (OOP_TO_OBJ (arrayOOP)); for (index = numVars; index >= 1; index--) if (ARRAY_AT (arrayOOP, index) == symbol) return (index - 1); return (-1); } static symbol_list find_local_var (scope scope, OOP symbol) { symbol_list s; for (s = scope->symbols; s != NULL && symbol != s->symbol; s = s->prevSymbol); return (s); } static void fill_symbol_entry (symbol_entry * ent, scope_type scope, mst_Boolean readOnly, OOP symbol, int index, unsigned int scopeDistance) { ent->scope = scope; ent->readOnly = readOnly; ent->symbol = symbol; ent->varIndex = index; ent->scopeDistance = scopeDistance; } void _gst_print_symbol_entry (symbol_entry * ent) { printf ("%#O", ent->symbol); switch (ent->scope) { case SCOPE_RECEIVER: printf (" (inst.var. #%d)", ent->varIndex); break; case SCOPE_GLOBAL: printf (" (global)"); break; case SCOPE_TEMPORARY: printf (" (temp.var. #"); if (ent->scopeDistance) printf ("%d.", ent->scopeDistance); printf ("%d)", ent->varIndex); break; case SCOPE_SPECIAL: printf (" (special)"); break; } } OOP _gst_find_pragma_handler (OOP classOOP, OOP symbolOOP) { OOP class_oop, myClass; myClass = _gst_get_class_object (_gst_this_class); /* Now search in the class pools */ for (class_oop = myClass; !IS_NIL (class_oop); class_oop = SUPERCLASS (class_oop)) { gst_class class = (gst_class) OOP_TO_OBJ (class_oop); OOP handlerOOP; if (IS_NIL (class->pragmaHandlers)) continue; handlerOOP = _gst_identity_dictionary_at (class->pragmaHandlers, symbolOOP); if (!IS_NIL (handlerOOP)) return handlerOOP; } return (_gst_nil_oop); } OOP _gst_make_instance_variable_array (OOP superclassOOP, const char * variableString) { OOP arrayOOP, superArrayOOP, name; int index, numInstanceVars, superInstanceVars; const char *p; inc_ptr incPtr; gst_object array; if (variableString == NULL) variableString = ""; if (IS_NIL (superclassOOP)) { superArrayOOP = _gst_nil_oop; superInstanceVars = numInstanceVars = 0; } else { superArrayOOP = _gst_instance_variable_array (superclassOOP); superInstanceVars = numInstanceVars = NUM_OOPS (OOP_TO_OBJ (superArrayOOP)); } for (p = variableString; *p;) { /* skip intervening whitespace */ name = scan_name (&p); if (!IS_NIL (name)) numInstanceVars++; } if (numInstanceVars == 0) return (_gst_nil_oop); /* no instances here */ incPtr = INC_SAVE_POINTER (); array = instantiate_with (_gst_array_class, numInstanceVars, &arrayOOP); INC_ADD_OOP (arrayOOP); /* inherit variables from parent */ for (index = 1; index <= superInstanceVars; index++) array->data[index - 1] = ARRAY_AT (superArrayOOP, index); /* now add our own variables */ for (p = variableString; *p; index++) { /* skip intervening whitespace */ name = scan_name (&p); /* don't need to add name to incubator -- it's a symbol so it's already held onto */ array = OOP_TO_OBJ (arrayOOP); if (!IS_NIL (name)) array->data[index - 1] = name; } INC_RESTORE_POINTER (incPtr); return (arrayOOP); } OOP _gst_make_class_variable_dictionary (const char *variableNames, OOP classOOP) { OOP dictionaryOOP, name; const char *p; inc_ptr incPtr; if (variableNames == NULL) variableNames = ""; incPtr = INC_SAVE_POINTER (); dictionaryOOP = _gst_nil_oop; for (p = variableNames; *p;) { name = scan_name (&p); if (!IS_NIL (name)) { if (IS_NIL (dictionaryOOP)) { dictionaryOOP = _gst_binding_dictionary_new (8, classOOP); INC_ADD_OOP (dictionaryOOP); } /* ### error if already exists */ /* don't need to add name to incubator -- it's a symbol so it's already held onto */ NAMESPACE_AT_PUT (dictionaryOOP, name, _gst_nil_oop); } } INC_RESTORE_POINTER (incPtr); return (dictionaryOOP); } OOP _gst_make_pool_array (const char * poolNames) { OOP poolsOOP, name; gst_object pools; int numPools, i; const char *p, *e; inc_ptr incPtr; if (poolNames == NULL) poolNames = (char *) ""; /* count the number of new pool names */ for (p = poolNames, numPools = 0; *p;) { parse_variable_name (&p, &e); if (p != e) { numPools++; p = e; } } incPtr = INC_SAVE_POINTER (); poolsOOP = _gst_nil_oop; /* ### maybe change this to leave empty array */ for (p = poolNames, i = 0; *p; i++) { name = scan_name (&p); if (!IS_NIL (name)) { /* don't need to add name to incubator -- it's a symbol so it's already held onto. */ /* ### error if already exists in parent?, or if value isn't a dictionary */ /* ### should I keep these as names? or associations? Should I look up the names somewhere other than in the smalltalk dictionary? Need to check for undefineds? */ if (poolsOOP == _gst_nil_oop) { instantiate_with (_gst_array_class, numPools, &poolsOOP); INC_ADD_OOP (poolsOOP); } pools = OOP_TO_OBJ (poolsOOP); pools->data[i] = dictionary_at (_gst_smalltalk_dictionary, name); } } INC_RESTORE_POINTER (incPtr); return (poolsOOP); } static OOP scan_name (const char ** pp) { const char *end; char *str; size_t len; parse_variable_name (pp, &end); len = end - *pp; if (len == 0) return (_gst_nil_oop); str = (char *) alloca (len + 1); strncpy (str, *pp, len); str[len] = '\0'; *pp = end; return (_gst_intern_string (str)); } static void parse_variable_name (const char ** pp, const char ** endp) { const char *p, *e; p = *pp; while (is_white_space (*p)) p++; *pp = p; /* check for non-null here and not alnum; we've jammed on a bogus char and it's an error */ if (isalpha (*p)) { /* variable name extends from p to e-1 */ for (e = p; *e; e++) if (!isalnum (*e) && *e != '_') break; *endp = e; } else *endp = p; } static mst_Boolean is_white_space (char c) { return (c == ' ' || c == '\r' || c == '\t' || c == '\n' || c == '\f'); } OOP _gst_intern_string_oop (OOP stringOOP) { unsigned int len; char copyBuf[100], *copyPtr; OOP symbolOOP; len = _gst_string_oop_len (stringOOP); /* do this slightly more complicated bit of code because: 1) we don't want to call malloc/free if we can help it 2) if we just used STRING_OOP_CHARS (as we used to), we pass the *dereferenced* value of the stringOOP. intern_counted_string can do allocations. If it allocates, and the gc runs, stringOOP can move, meaning the dereferenced set of chars becomes invalid. So instead we make a non-moving copy and use that. */ if (len < sizeof (copyBuf)) copyPtr = copyBuf; else copyPtr = (char *) xmalloc (len); memcpy (copyPtr, STRING_OOP_CHARS (stringOOP), len); symbolOOP = intern_counted_string (copyPtr, len); if (len >= sizeof (copyBuf)) xfree (copyPtr); return symbolOOP; } OOP _gst_intern_string (const char *str) { int len; len = strlen (str); return (intern_counted_string (str, len)); } static uintptr_t hash_symbol (const char *str, int len) { uintptr_t index = scramble (_gst_hash_string (str, len)); return (index & (SYMBOL_TABLE_SIZE - 1)) + 1; } static OOP alloc_symlink (OOP symbolOOP, uintptr_t index) { gst_symbol symbol; sym_link link; OOP linkOOP; symbol = (gst_symbol) OOP_TO_OBJ (symbolOOP); symbol->objClass = _gst_symbol_class; link = (sym_link) new_instance (_gst_sym_link_class, &linkOOP); link->nextLink = ARRAY_AT (_gst_symbol_table, index); link->symbol = symbolOOP; ARRAY_AT_PUT (_gst_symbol_table, index, linkOOP); return (symbolOOP); } static OOP intern_counted_string (const char *str, int len) { uintptr_t index; OOP symbolOOP, linkOOP; sym_link link; inc_ptr incPtr; index = hash_symbol (str, len); for (linkOOP = ARRAY_AT (_gst_symbol_table, index); !IS_NIL (linkOOP); linkOOP = link->nextLink) { link = (sym_link) OOP_TO_OBJ (linkOOP); if (is_same_string (str, link->symbol, len)) return (link->symbol); } /* no match, have to add it to head of list */ #ifdef HAVE_READLINE _gst_add_symbol_completion (str, len); #endif incPtr = INC_SAVE_POINTER (); symbolOOP = alloc_symbol_oop (str, len); INC_ADD_OOP (symbolOOP); alloc_symlink (symbolOOP, index); INC_RESTORE_POINTER (incPtr); return (symbolOOP); } static OOP alloc_symbol_oop (const char *str, int len) { int numBytes, alignedBytes; gst_symbol symbol; OOP symbolOOP; numBytes = sizeof(gst_object_header) + len; alignedBytes = ROUNDED_BYTES (numBytes); symbol = (gst_symbol) _gst_alloc_obj (alignedBytes, &symbolOOP); INIT_UNALIGNED_OBJECT (symbolOOP, alignedBytes - numBytes); memcpy (symbol->symString, str, len); symbolOOP->flags |= F_READONLY; return symbolOOP; } static mst_Boolean is_same_string (const char *str, OOP oop, int len) { if (_gst_string_oop_len (oop) == len) return (strncmp (str, ((gst_symbol) OOP_TO_OBJ (oop))->symString, len) == 0); return (false); } int _gst_string_oop_len (OOP oop) { return (OOP_SIZE_BYTES (oop) - (oop->flags & EMPTY_BYTES)); } uintptr_t _gst_hash_string (const char *str, int len) { uintptr_t hashVal = 1497032417; /* arbitrary value */ while (len--) { hashVal += *str++; hashVal += (hashVal << 10); hashVal ^= (hashVal >> 6); } return hashVal & MAX_ST_INT; } void _gst_check_symbol_chain (void) { int i; for (i = 1; i <= SYMBOL_TABLE_SIZE; i++) { sym_link link; OOP linkOOP; for (linkOOP = ARRAY_AT (_gst_symbol_table, i); !IS_NIL (linkOOP); linkOOP = link->nextLink) { link = (sym_link) OOP_TO_OBJ (linkOOP); if (OOP_CLASS (linkOOP) != _gst_sym_link_class || OOP_CLASS (link->symbol) != _gst_symbol_class) { printf ("Bad symbol %p\n", linkOOP); abort (); } } } } #ifdef HAVE_READLINE void _gst_add_all_symbol_completions (void) { int i; for (i = 1; i <= SYMBOL_TABLE_SIZE; i++) { sym_link link; OOP linkOOP; char *string; int len; for (linkOOP = ARRAY_AT (_gst_symbol_table, i); !IS_NIL (linkOOP); linkOOP = link->nextLink) { link = (sym_link) OOP_TO_OBJ (linkOOP); string = _gst_to_cstring (link->symbol); len = _gst_string_oop_len (link->symbol); _gst_add_symbol_completion (string, len); xfree (string); } } } #endif int _gst_selector_num_args (OOP symbolOOP) { char *bytes; int numArgs, len; len = _gst_string_oop_len (symbolOOP); bytes = (char *) (OOP_TO_OBJ (symbolOOP)->data); if ((bytes[0] >= 'A' && bytes[0] <= 'Z') || (bytes[0] >= 'a' && bytes[0] <= 'z') || bytes[0] == '_') { for (numArgs = 0; len;) if (bytes[--len] == ':') numArgs++; } else numArgs = 1; return (numArgs); } #include "builtins.inl" void _gst_init_symbols_pass1 (void) { const symbol_info *si; struct builtin_selector *bs; for (si = sym_info; si->symbolVar; si++) *si->symbolVar = alloc_symbol_oop (si->value, strlen (si->value)); /* Complete gperf's generated table with each symbol's OOP, and prepare a kind of reverse mapping from the 256 bytecodes to the hash table entries. */ for (bs = _gst_builtin_selectors_hash; bs - _gst_builtin_selectors_hash < sizeof (_gst_builtin_selectors_hash) / sizeof (_gst_builtin_selectors_hash[0]); bs++) if (bs->offset != -1) { const char *name = bs->offset + _gst_builtin_selectors_names; bs->symbol = alloc_symbol_oop (name, strlen (name)); _gst_builtin_selectors[bs->bytecode] = *bs; } } void _gst_init_symbols_pass2 (void) { const symbol_info *si; struct builtin_selector *bs; for (si = sym_info; si->symbolVar; si++) alloc_symlink (*si->symbolVar, hash_symbol (si->value, strlen (si->value))); /* Complete gperf's generated table with each symbol's OOP, and prepare a kind of reverse mapping from the 256 bytecodes to the hash table entries. */ for (bs = _gst_builtin_selectors_hash; bs - _gst_builtin_selectors_hash < sizeof (_gst_builtin_selectors_hash) / sizeof (_gst_builtin_selectors_hash[0]); bs++) if (bs->offset != -1) { const char *name = bs->offset + _gst_builtin_selectors_names; alloc_symlink (bs->symbol, hash_symbol (name, strlen (name))); } } static inline OOP intern_string_fast (const char *str, OOP *pTestOOP) { int len = strlen (str); OOP testOOP = *pTestOOP; if (is_same_string (str, testOOP, len)) { (*pTestOOP)++; return testOOP; } else return intern_counted_string (str, len); } void _gst_restore_symbols (void) { const symbol_info *si; struct builtin_selector *bs; OOP currentOOP = _gst_symbol_table + 1; for (si = sym_info; si->symbolVar; si++) *si->symbolVar = intern_string_fast (si->value, ¤tOOP); /* Complete gperf's generated table with each symbol's OOP, and prepare a kind of reverse mapping from the 256 bytecodes to the hash table entries. */ for (bs = _gst_builtin_selectors_hash; bs - _gst_builtin_selectors_hash < sizeof (_gst_builtin_selectors_hash) / sizeof (_gst_builtin_selectors_hash[0]); bs++) if (bs->offset != -1) { const char *name = bs->offset + _gst_builtin_selectors_names; bs->symbol = intern_string_fast (name, ¤tOOP); _gst_builtin_selectors[bs->bytecode] = *bs; } } smalltalk-3.2.5/libgst/prims.stamp0000644000175000017500000000001212130456004014076 00000000000000timestamp smalltalk-3.2.5/libgst/files.h0000644000175000017500000001347412123404352013172 00000000000000/******************************** -*- C -*- **************************** * * Public interface for main module. * * ***********************************************************************/ /*********************************************************************** * * Copyright 1988,89,90,91,92,94,95,99,2000,2001,2002,2006,2008,2009 * Free Software Foundation, Inc. * Written by Steve Byrne. * * This file is part of GNU Smalltalk. * * GNU Smalltalk is free software; you can redistribute it and/or modify it * under the terms of the GNU General Public License as published by the Free * Software Foundation; either version 2, or (at your option) any later * version. * * Linking GNU Smalltalk statically or dynamically with other modules is * making a combined work based on GNU Smalltalk. Thus, the terms and * conditions of the GNU General Public License cover the whole * combination. * * In addition, as a special exception, the Free Software Foundation * give you permission to combine GNU Smalltalk with free software * programs or libraries that are released under the GNU LGPL and with * independent programs running under the GNU Smalltalk virtual machine. * * You may copy and distribute such a system following the terms of the * GNU GPL for GNU Smalltalk and the licenses of the other code * concerned, provided that you include the source code of that other * code when and as the GNU GPL requires distribution of source code. * * Note that people who make modified versions of GNU Smalltalk are not * obligated to grant this special exception for their modified * versions; it is their choice whether to do so. The GNU General * Public License gives permission to release a modified version without * this exception; this exception also makes it possible to release a * modified version which carries forward this exception. * * GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or * FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for * more details. * * You should have received a copy of the GNU General Public License along with * GNU Smalltalk; see the file COPYING. If not, write to the Free Software * Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * ***********************************************************************/ #ifndef GST_LIB_H #define GST_LIB_H /* These contain the default path that was picked (after looking at the environment variables) for the kernel files and the image. */ extern const char *_gst_kernel_file_path ATTRIBUTE_HIDDEN; extern const char *_gst_image_file_path ATTRIBUTE_HIDDEN; /* The ".st" directory, in the current directory or in the user's home directory. */ extern const char *_gst_user_file_base_path; /* This is the name of the binary image to load. If it is not NULL after the command line is parsed, the checking of the dates of the kernel source files against the image file date is overridden. If it is NULL, it is set to default_image_name. */ extern const char *_gst_binary_image_name ATTRIBUTE_HIDDEN; /* This is TRUE if we are doing regression testing, and causes whatever sources of variance to be suppressed (such as printing out execution statistics). */ extern mst_Boolean _gst_regression_testing ATTRIBUTE_HIDDEN; /* The standard value of this flag is 2. The four possible values (0 to 3) correspond respectively to -Q, -q, nothing, and -V. When set to 3, this flag enables the printing of execution statistics. When set to 1 or lower, this flag suppresses the printing of execution-related messages, such as the result of do-its. When set to 0, Smalltalk does not print any sort of version banner at the startup of the interpreter. This makes Smalltalk usable as a filter, or as a pure producer of content (such as the main program in a cgi-bin script). */ extern int _gst_verbosity ATTRIBUTE_HIDDEN; /* The argc and argv that are made available to Smalltalk programs through the -a option. */ extern int _gst_smalltalk_passed_argc ATTRIBUTE_HIDDEN; extern const char **_gst_smalltalk_passed_argv ATTRIBUTE_HIDDEN; /* This is used to avoid doing complicated things (currently, this includes call-ins before and after _gst_execute_statements) before the system is ready to do them. */ extern mst_Boolean _gst_kernel_initialized ATTRIBUTE_HIDDEN; /* Set by cmd line flag. If true, Smalltalk is more verbose about what it's doing. */ extern mst_Boolean _gst_verbose ATTRIBUTE_HIDDEN; /* This is true if the image initialization has already been started. */ extern mst_Boolean _gst_smalltalk_initialized ATTRIBUTE_HIDDEN; /* This sets the arguments to be passed to the Smalltalk library, which are the same that are available by the `gst' executable. */ extern void _gst_smalltalk_args (int argc, const char **argv) ATTRIBUTE_HIDDEN; /* Set the fundamental paths for the Smalltalk VM and initialize it. */ extern int _gst_initialize (const char *kernel_dir, const char *image_file, int flags) ATTRIBUTE_HIDDEN; /* This processes files passed to gst_smalltalk_args and, if none was passed, stdin is looked for input. */ extern void _gst_top_level_loop (void) ATTRIBUTE_HIDDEN; /* Attempts to find a viable kernel Smalltalk file (.st file). FILENAME is a simple file name, sans directory; the file name to use for the particular kernel file is returned. If there is a file in the .stkernel directory with name FILENAME, that is returned; otherwise the kernel path is prepended to FILENAME (separated by a slash, of course) and that is stored in the string that is returned. */ extern char *_gst_find_file (const char *fileName, enum gst_file_dir dir) ATTRIBUTE_HIDDEN; #endif /* GST_LIB_H */ smalltalk-3.2.5/libgst/dict.inl0000644000175000017500000013220412130343734013343 00000000000000/******************************** -*- C -*- **************************** * * Dictionary Support Module Inlines. * * ***********************************************************************/ /*********************************************************************** * * Copyright 2000, 2001, 2002, 2003, 2006, 2007, 2008, 2009 * Free Software Foundation, Inc. * Written by Steve Byrne. * * This file is part of GNU Smalltalk. * * GNU Smalltalk is free software; you can redistribute it and/or modify it * under the terms of the GNU General Public License as published by the Free * Software Foundation; either version 2, or (at your option) any later * version. * * Linking GNU Smalltalk statically or dynamically with other modules is * making a combined work based on GNU Smalltalk. Thus, the terms and * conditions of the GNU General Public License cover the whole * combination. * * In addition, as a special exception, the Free Software Foundation * give you permission to combine GNU Smalltalk with free software * programs or libraries that are released under the GNU LGPL and with * independent programs running under the GNU Smalltalk virtual machine. * * You may copy and distribute such a system following the terms of the * GNU GPL for GNU Smalltalk and the licenses of the other code * concerned, provided that you include the source code of that other * code when and as the GNU GPL requires distribution of source code. * * Note that people who make modified versions of GNU Smalltalk are not * obligated to grant this special exception for their modified * versions; it is their choice whether to do so. The GNU General * Public License gives permission to release a modified version without * this exception; this exception also makes it possible to release a * modified version which carries forward this exception. * * GNU Smalltalk is distributed in the hope that it will be usefui, but WITHOUT * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or * FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for * more details. * * You shouid have received a copy of the GNU General Public License along with * GNU Smalltalk; see the file COPYING. If not, write to the Free Software * Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * ***********************************************************************/ /* Scramble the bits of X. */ static inline uintptr_t scramble (uintptr_t x); /* Return a pointer to the first item in the OrderedCollection, ORDEREDCOLLECTIONOOP. */ static inline OOP *ordered_collection_begin (OOP orderedCollectionOOP); /* Return a pointer just beyond the last item in the OrderedCollection, ORDEREDCOLLECTIONOOP. */ static inline OOP *ordered_collection_end (OOP orderedCollectionOOP); /* Checks to see if TESTEDOOP is a subclass of CLASS_OOP, returning true if it is. */ static inline mst_Boolean is_a_kind_of (OOP testedOOP, OOP class_oop); /* Stores the VALUE Object (which must be an appropriate Integer for byte or word objects) into the INDEX-th indexed instance variable of the Object pointed to by OOP. Returns whether the INDEX is correct and the VALUE has the appropriate class and/or range. */ static inline mst_Boolean index_oop_put_spec (OOP oop, gst_object object, size_t index, OOP value, intptr_t instanceSpec); /* Stores the VALUE Object (which must be an appropriate Integer for byte or word objects) into the INDEX-th indexed instance variable of the Object pointed to by OOP. Returns whether the INDEX is correct and the VALUE has the appropriate class and/or range. */ static inline mst_Boolean index_oop_put (OOP oop, size_t index, OOP value); /* Stores the VALUE Object (which must be an appropriate Integer for byte or word objects and if accessing indexed instance variables) into the INDEX-th instance variable of the Object pointed to by OOP. */ static inline void inst_var_at_put (OOP oop, int index, OOP value); /* Returns the INDEX-th instance variable of the Object pointed to by OOP. No range checks are done in INDEX. */ static inline OOP inst_var_at (OOP oop, int index); /* Returns the number of instance variables (both fixed and indexed) in OOP. */ static inline int oop_num_fields (OOP oop); /* Fill OOPCOUNT pointers to OOPs, starting at OOPPTR, with OOPs for the NIL object. */ static inline void nil_fill (OOP * oopPtr, size_t oopCount); /* Returns a new, uninitialized instance of CLASS_OOP with NUMINDEXFIELDS indexable fields. Returns an OOP for a newly allocated instance of CLASS_OOP, with NUMINDEXFIELDS fields. The object data is returned, the OOP is stored in P_OOP. The OOP is adjusted to reflect any variance in size (such as a string that's shorter than a word boundary). */ static inline gst_object new_instance_with (OOP class_oop, size_t numIndexFields, OOP *p_oop); /* Creates a new instance of class CLASS_OOP. The space is allocated, the class and size fields of the class are filled in, and the instance is returned. Its fields are NOT INITIALIZED. CLASS_OOP must represent a class with no indexable fields. An OOP will be allocated and stored in P_OOP. */ static inline gst_object new_instance (OOP class_oop, OOP *p_oop); /* Returns a new, initialized instance of CLASS_OOP within an object of size NUMBYTES. INSTANCESPEC is used to find the number of fixed instance variables and initialize them to _gst_nil_oop. The pointer to the object data is returned, the OOP is stored in P_OOP. The OOP is not adjusted to reflect any variance in size (such as a string that's shorter than a word boundary). */ static inline gst_object instantiate_numbytes (OOP class_oop, OOP *p_oop, intptr_t instanceSpec, size_t numBytes); /* Returns a new, initialized instance of CLASS_OOP with NUMINDEXFIELDS indexable fields. If the instance contains pointers, they are initialized to _gst_nil_oop, else they are set to the SmallInteger 0. The pointer to the object data is returned, the OOP is stored in P_OOP. The OOP is adjusted to reflect any variance in size (such as a string that's shorter than a word boundary). */ static inline gst_object instantiate_with (OOP class_oop, size_t numIndexFields, OOP *p_oop); /* Create and return a new instance of class CLASS_OOP. CLASS_OOP must be a class with no indexable fields. The named instance variables of the new instance are initialized to _gst_nil_oop, since fixed-field-only objects can only have pointers. The pointer to the object data is returned, the OOP is stored in P_OOP. */ static inline gst_object instantiate (OOP class_oop, OOP *p_oop); /* Return the Character object for the Unicode value C. */ static inline OOP char_new (unsigned codePoint); /* Answer the associated containing KEYOOP in the Dictionary (or a subclass having the same representation) DICTIONARYOOP. */ static inline OOP dictionary_association_at (OOP dictionaryOOP, OOP keyOOP); /* Answer the value associated to KEYOOP in the Dictionary (or a subclass having the same representation) DICTIONARYOOP. */ static inline OOP dictionary_at (OOP dictionaryOOP, OOP keyOOP); /* Creates a new Association object having the specified KEY and VALUE. */ static inline OOP association_new (OOP key, OOP value); /* Creates a new VariableBinding object having the specified KEY and VALUE. */ static inline OOP variable_binding_new (OOP key, OOP value, OOP environment); /* Returns an Object (an Integer for byte or word objects) containing the value of the INDEX-th indexed instance variable of the Object pointed to by OOP. Range checks are done in INDEX and NULL is returned if this is the checking fails. */ static inline OOP index_oop (OOP oop, size_t index); /* Returns an Object (an Integer for byte or word objects) containing the value of the INDEX-th indexed instance variable of the Object pointed to by OOP. Range checks are done in INDEX and NULL is returned if this is the checking fails. OBJECT and INSTANCESPEC are cached out of OOP and its class. */ static inline OOP index_oop_spec (OOP oop, gst_object object, size_t index, intptr_t instanceSpec); /* Returns the number of valid object instance variables in OOP. */ static inline int num_valid_oops (OOP oop); /* Returns whether the SCANNEDOOP points to TARGETOOP. */ static inline mst_Boolean is_owner (OOP scannedOOP, OOP targetOOP); /* Converts F to a Smalltalk FloatD, taking care of avoiding alignment problems. */ static inline OOP floatd_new (double f); /* Converts F to a Smalltalk FloatE. */ static inline OOP floate_new (double f); /* Converts F to a Smalltalk FloatQ, taking care of avoiding alignment problems. */ static inline OOP floatq_new (long double f); /* Returns the address of the data stored in a CObject. */ static inline PTR cobject_value (OOP oop); /* Sets the address of the data stored in a CObject. */ static inline void set_cobject_value (OOP oop, PTR val); /* Return whether the address of the data stored in a CObject, offsetted by OFFSET bytes, is still in bounds. */ static inline mst_Boolean cobject_index_check (OOP oop, intptr_t offset, size_t size); /* Answer true if OOP is a SmallInteger or a LargeInteger of an appropriate size. */ static inline mst_Boolean is_c_int_32 (OOP oop); /* Answer true if OOP is a SmallInteger or a LargeInteger of an appropriate size. */ static inline mst_Boolean is_c_uint_32 (OOP oop); /* Converts the 32-bit int I to the appropriate SmallInteger or LargeInteger. */ static inline OOP from_c_int_32 (int32_t i); /* Converts the long int LNG to the appropriate SmallInteger or LargePositiveInteger. */ static inline OOP from_c_uint_32 (uint32_t ui); /* Converts the OOP (which must be a SmallInteger or a small enough LargeInteger) to a long int. If the OOP was for an unsigned long, you can simply cast the result to an unsigned long. */ static inline int32_t to_c_int_32 (OOP oop); /* Answer true if OOP is a SmallInteger or a LargeInteger of an appropriate size. */ static inline mst_Boolean is_c_int_64 (OOP oop); /* Answer true if OOP is a SmallInteger or a LargeInteger of an appropriate size. */ static inline mst_Boolean is_c_uint_64 (OOP oop); /* Converts the 64-bit int I to the appropriate SmallInteger or LargeInteger. */ static inline OOP from_c_int_64 (int64_t i); /* Converts the long int LNG to the appropriate SmallInteger or LargePositiveInteger. */ static inline OOP from_c_uint_64 (uint64_t ui); /* Converts the OOP (which must be a SmallInteger or a small enough LargeInteger) to a 64-bit signed integer. */ static inline int64_t to_c_int_64 (OOP oop); /* Converts the OOP (which must be a SmallInteger or a small enough LargeInteger) to a 64-bit unsigned integer. */ static inline uint64_t to_c_uint_64 (OOP oop); #define TO_C_INT(integer) to_c_int_32(integer) #define IS_C_INT(oop) is_c_int_32(oop) #define IS_C_LONGLONG(oop) is_c_int_64(oop) #define IS_C_ULONGLONG(oop) is_c_uint_64(oop) #define FROM_C_LONGLONG(integ) from_c_int_64(integ) #define FROM_C_ULONGLONG(integ) from_c_uint_64(integ) #if SIZEOF_OOP == 4 #define FROM_C_INT(integer) FROM_C_LONG((intptr_t) (signed) integer) #define FROM_C_UINT(integer) FROM_C_ULONG((uintptr_t) (unsigned) integer) #define FROM_C_LONG(integer) from_c_int_32(integer) #define FROM_C_ULONG(integer) from_c_uint_32(integer) #define TO_C_LONG(integer) to_c_int_32(integer) #define IS_C_LONG(oop) is_c_int_32(oop) #define IS_C_ULONG(oop) is_c_uint_32(oop) #else #define FROM_C_INT(integer) FROM_INT((intptr_t) (signed) integer) #define FROM_C_UINT(integer) FROM_INT((intptr_t) (unsigned) integer) #define FROM_C_LONG(integer) from_c_int_64(integer) #define FROM_C_ULONG(integer) from_c_uint_64(integer) #define TO_C_LONG(integer) to_c_int_64(integer) #define IS_C_LONG(oop) is_c_int_64(oop) #define IS_C_ULONG(oop) is_c_uint_64(oop) #endif #if SIZEOF_OFF_T == 4 #define FROM_OFF_T(integer) from_c_int_32(integer) #define TO_OFF_T(integer) to_c_int_32(integer) #define IS_OFF_T(oop) is_c_int_32(oop) #else #define FROM_OFF_T(integer) from_c_int_64(integer) #define TO_OFF_T(integer) to_c_int_64(integer) #define IS_OFF_T(oop) is_c_int_64(oop) #endif /* Answer the INDEX'th instance variable of RECEIVER. */ #define INSTANCE_VARIABLE(receiver, index) \ (OOP_TO_OBJ (receiver)->data[index]) /* Store OOP in the INDEX'th instance variable of RECEIVER. */ #define STORE_INSTANCE_VARIABLE(receiver, index, oop) \ OOP_TO_OBJ (receiver)->data[index] = (oop) #define IS_SYMBOL(oop) \ ( !IS_NIL(oop) && (OOP_CLASS(oop) == _gst_symbol_class) ) /* Return the Character object for ASCII value C. */ #define CHAR_OOP_AT(c) (&_gst_mem.ot[(int)(c) + CHAR_OBJECT_BASE]) /* Answer the code point of the character OOP, charOOP. */ #define CHAR_OOP_VALUE(charOOP) \ TO_INT (((gst_char)OOP_TO_OBJ (charOOP))->codePoint) /* Answer a pointer to the first character of STRINGOOP. */ #define STRING_OOP_CHARS(stringOOP) \ ((gst_uchar *)((gst_string)OOP_TO_OBJ(stringOOP))->chars) /* Answer the selector extracted by the Message, MESSAGEOOP. */ #define MESSAGE_SELECTOR(messageOOP) \ (((gst_message)OOP_TO_OBJ(messageOOP))->selector) /* Answer the array of arguments extracted by the Message, MESSAGEOOP. */ #define MESSAGE_ARGS(messageOOP) \ (((gst_message)OOP_TO_OBJ(messageOOP))->args) /* Answer a new CObject pointing to COBJPTR. */ #define COBJECT_NEW(cObjPtr, typeOOP, defaultClassOOP) \ (_gst_c_object_new_base(_gst_nil_oop, (uintptr_t) cObjPtr, \ typeOOP, defaultClassOOP)) /* Answer the offset component of the a CObject, COBJ (*not* an OOP, but an object pointer). */ #define COBJECT_OFFSET_OBJ(cObj) \ ( ((uintptr_t *) cObj) [TO_INT(cObj->objSize) - 1]) /* Sets to VALUE the offset component of the CObject, COBJ (*not* an OOP, but an object pointer). */ #define SET_COBJECT_OFFSET_OBJ(cObj, value) \ ( ((uintptr_t *) cObj) [TO_INT(cObj->objSize) - 1] = (uintptr_t)(value)) /* Answer the superclass of the Behavior, CLASS_OOP. */ #define SUPERCLASS(class_oop) \ (((gst_class)OOP_TO_OBJ(class_oop))->superclass) /* Answer the number of fixed instance variables in OOP. */ #define OOP_FIXED_FIELDS(oop) \ (OOP_INSTANCE_SPEC(oop) >> ISP_NUMFIXEDFIELDS) /* Answer the number of fixed instance variables in instances of OOP. */ #define CLASS_FIXED_FIELDS(oop) \ (CLASS_INSTANCE_SPEC(oop) >> ISP_NUMFIXEDFIELDS) /* Answer the number of indexed instance variables in OOP (if any). */ #define NUM_INDEXABLE_FIELDS(oop) \ (IS_INT(oop) ? 0 : oop_num_fields(oop) - OOP_FIXED_FIELDS(oop)) /* Answer the INDEX-th indexed instance variable in ARRAYOOP. */ #define ARRAY_AT(arrayOOP, index) \ ( OOP_TO_OBJ(arrayOOP)->data[(index)-1] ) /* Store VALUE as the INDEX-th indexed instance variable of ARRAYOOP. */ #define ARRAY_AT_PUT(arrayOOP, index, value) \ ( OOP_TO_OBJ(arrayOOP)->data[index-1] = value ) /* Answer the number of associations stored in DICTIONARYOOP. */ #define DICTIONARY_SIZE(dictionaryOOP) \ (TO_INT(((gst_dictionary)OOP_TO_OBJ(dictionaryOOP))->tally)) /* Adds the key KEYOOP, associated with VALUEOOP, to the Dictionary (or a subclass sharing the same representation) DICTIONARYOOP. */ #define DICTIONARY_AT_PUT(dictionaryOOP, keyOOP, valueOOP) \ (_gst_dictionary_add((dictionaryOOP), association_new((keyOOP), (valueOOP)))) /* Adds the key KEYOOP, associated with VALUEOOP, to the Dictionary (or a subclass sharing the same representation) DICTIONARYOOP. */ #define NAMESPACE_AT_PUT(dictionaryOOP, keyOOP, valueOOP) \ (_gst_dictionary_add((dictionaryOOP), \ variable_binding_new((keyOOP), (valueOOP), (dictionaryOOP)))) /* Adds the key KEYOOP, associated with VALUEOOP, to the Dictionary (or a subclass sharing the same representation) DICTIONARYOOP. */ #define DICTIONARY_AT_PUT(dictionaryOOP, keyOOP, valueOOP) \ (_gst_dictionary_add((dictionaryOOP), \ association_new((keyOOP), (valueOOP)))) /* Answer whether OOP is a metaclass. */ #define IS_A_METACLASS(oop) \ (IS_OOP(oop) && OOP_CLASS(oop) == _gst_metaclass_class) /* Answer whether OOP is a class, that is, the instance of the metaclass. */ #define IS_A_CLASS(oop) \ (IS_OOP(oop) && \ IS_OOP(OOP_CLASS(oop)) && \ OOP_CLASS(OOP_CLASS(oop)) == _gst_metaclass_class) /* Answer the sole instance of the metaclass, METACLASSOOP. */ #define METACLASS_INSTANCE(metaclassOOP) \ (((gst_metaclass)OOP_TO_OBJ(metaclassOOP))->instanceClass) /* Answer the value stored in the Association, ASSOCIATIONOOP. */ #define ASSOCIATION_VALUE(associationOOP) \ (((gst_association)OOP_TO_OBJ(associationOOP))->value) /* Change the value stored in the Association, ASSOCIATIONOOP, to VALUEOOP. */ #define SET_ASSOCIATION_VALUE(associationOOP, valueOOP) \ (((gst_association)OOP_TO_OBJ(associationOOP))->value = valueOOP) /* Set NAMESPACEOOP to be the namespace in which references to globals from methods of CLASS_OOP are resolved. */ #define SET_CLASS_ENVIRONMENT(class_oop, namespaceOOP) \ (((gst_class)OOP_TO_OBJ(class_oop))->environment = namespaceOOP) /* Answer the instance specification for instances of CLASS_OOP. */ #define CLASS_INSTANCE_SPEC(class_oop) \ (((gst_class)OOP_TO_OBJ(class_oop))->instanceSpec) /* Answer the instance specification of the object OBJ (*not* an OOP). */ #define GET_INSTANCE_SPEC(obj) \ CLASS_INSTANCE_SPEC((obj)->objClass) /* Answer the instance specification of OOP. */ #define OOP_INSTANCE_SPEC(oop) \ CLASS_INSTANCE_SPEC(OOP_CLASS(oop)) /* Answer whether INDEX is in-bounds for accessing fixed instance variables of OOP. */ #define CHECK_BOUNDS_OF(oop, index) \ (IS_OOP(oop) && (index >= 1 && index <= OOP_FIXED_FIELDS(oop))) /* Answer whether indexed instance variables for instances of CLASS_OOP are pointers. */ #define CLASS_IS_UNALIGNED(class_oop) \ ((CLASS_INSTANCE_SPEC(class_oop) & ISP_ISINDEXABLE) \ && (CLASS_INSTANCE_SPEC(class_oop) & ISP_INDEXEDVARS) <= GST_ISP_LAST_UNALIGNED) /* Answer whether instances of CLASS_OOP have indexed instance variables. */ #define CLASS_IS_INDEXABLE(class_oop) \ (CLASS_INSTANCE_SPEC(class_oop) & ISP_ISINDEXABLE) /* Answer whether instances of CLASS_OOP have indexed instance variables. */ #define CLASS_IS_SCALAR(class_oop) \ ((CLASS_INSTANCE_SPEC(class_oop) & ISP_ISINDEXABLE) \ && (CLASS_INSTANCE_SPEC(class_oop) & ISP_INDEXEDVARS) <= GST_ISP_LAST_SCALAR) /* Answer the size in bytes of the object data for OOP. */ #define OBJECT_SIZE_BYTES(obj) \ (SIZE_TO_BYTES (TO_INT (obj->objSize)) - sizeof (gst_object_header)) /* Answer the size in bytes of the object data for OOP. */ #define OOP_SIZE_BYTES(oop) \ OBJECT_SIZE_BYTES (OOP_TO_OBJ (oop)) /* Return the number of word-addressed (pointers or words) instance variables, both fixed and indexed), in OOP. Use instead of NUM_OOPS if you know OOP is not a byte object. */ #define NUM_WORDS(obj) \ ((size_t) (TO_INT((obj)->objSize) - OBJ_HEADER_SIZE_WORDS)) /* Return the number of pointer instance variables (both fixed and indexed), in the object OBJ. */ #define NUM_OOPS(obj) \ ((size_t) (COMMON (CLASS_IS_SCALAR ((obj)->objClass)) \ ? (CLASS_INSTANCE_SPEC((obj)->objClass) >> ISP_NUMFIXEDFIELDS) \ : NUM_WORDS(obj) \ )) #define FLOATE_OOP_VALUE(floatOOP) \ (((gst_floate)OOP_TO_OBJ(floatOOP))->value) OOP floate_new (double f) { gst_floate floatObject; OOP floatOOP; floatObject = (gst_floate) new_instance_with (_gst_floate_class, sizeof (float), &floatOOP); floatObject->value = f; MAKE_OOP_READONLY (floatOOP, true); return (floatOOP); } #if (ALIGNOF_DOUBLE <= SIZEOF_OOP) #define FLOATD_OOP_VALUE(floatOOP) \ (((gst_floatd)OOP_TO_OBJ(floatOOP))->value) #else #define FLOATD_OOP_VALUE(floatOOP) \ floatd_oop_value(floatOOP) static inline double floatd_oop_value (floatOOP) OOP floatOOP; { gst_object obj; double d; /* we may not be aligned properly...fetch things out the hard way */ obj = OOP_TO_OBJ (floatOOP); memcpy (&d, obj->data, sizeof (double)); return (d); } #endif OOP floatd_new (double f) { OOP floatOOP; #if (ALIGNOF_DOUBLE <= SIZEOF_OOP) gst_floatd floatObject; floatObject = (gst_floatd) new_instance_with (_gst_floatd_class, sizeof (double), &floatOOP); floatObject->value = f; #else gst_object obj; obj = new_instance_with (_gst_floatd_class, sizeof (double), &floatOOP); memcpy (&obj->data, &f, sizeof (double)); #endif MAKE_OOP_READONLY (floatOOP, true); return (floatOOP); } #if (ALIGNOF_LONG_DOUBLE <= SIZEOF_OOP) #define FLOATQ_OOP_VALUE(floatOOP) \ (((gst_floatq)OOP_TO_OBJ(floatOOP))->value) #else #define FLOATQ_OOP_VALUE(floatOOP) \ floatq_oop_value(floatOOP) static inline long double floatq_oop_value (floatOOP) OOP floatOOP; { gst_object obj; long double d; /* we may not be aligned properly...fetch things out the hard way */ obj = OOP_TO_OBJ (floatOOP); memcpy (&d, obj->data, sizeof (long double)); return (d); } #endif OOP floatq_new (long double f) { OOP floatOOP; gst_object obj = new_instance_with (_gst_floatq_class, 16, &floatOOP); #if defined __i386__ || defined __x86_64__ /* Two bytes (six on x86-64) of 80-bit long doubles are unused. */ memcpy (&obj->data, &f, 10); memset (((char *)obj->data) + 10, 0, 6); #else memcpy (&obj->data, &f, sizeof (long double)); memset (((char *)obj->data) + sizeof (long double), 0, 16 - sizeof (long double)); #endif MAKE_OOP_READONLY (floatOOP, true); return (floatOOP); } OOP char_new (unsigned codePoint) { gst_char charObject; OOP charOOP; if (codePoint <= 127) return CHAR_OOP_AT (codePoint); if UNCOMMON (codePoint > 0x10FFFF) codePoint = 0xFFFD; charObject = (gst_char) new_instance (_gst_unicode_character_class, &charOOP); charObject->codePoint = FROM_INT (codePoint); MAKE_OOP_READONLY (charOOP, true); return (charOOP); } uintptr_t scramble (uintptr_t x) { #if SIZEOF_OOP == 8 x ^= (x >> 31) | ( x << 33); #endif x ^= (x << 10) | (x >> 22); x ^= (x << 6) | (x >> 26); x ^= (x << 16) | (x >> 16); return x & MAX_ST_INT; } mst_Boolean is_a_kind_of (OOP testedOOP, OOP class_oop) { do { if (testedOOP == class_oop) return (true); testedOOP = SUPERCLASS (testedOOP); } while (!IS_NIL (testedOOP)); return (false); } void nil_fill (OOP * oopPtr, size_t oopCount) { REGISTER (3, OOP nilObj); nilObj = _gst_nil_oop; while (oopCount >= 8) { oopPtr[0] = oopPtr[1] = oopPtr[2] = oopPtr[3] = oopPtr[4] = oopPtr[5] = oopPtr[6] = oopPtr[7] = nilObj; oopPtr += 8; oopCount -= 8; } if (oopCount & 4) { oopPtr[0] = oopPtr[1] = oopPtr[2] = oopPtr[3] = nilObj; oopPtr += 4; } if (oopCount & 2) { oopPtr[0] = oopPtr[1] = nilObj; oopPtr += 2; } if (oopCount & 1) oopPtr[0] = nilObj; } gst_object new_instance_with (OOP class_oop, size_t numIndexFields, OOP *p_oop) { size_t numBytes, alignedBytes; intptr_t instanceSpec; gst_object p_instance; instanceSpec = CLASS_INSTANCE_SPEC (class_oop); numBytes = sizeof (gst_object_header) + SIZE_TO_BYTES(instanceSpec >> ISP_NUMFIXEDFIELDS) + (numIndexFields << _gst_log2_sizes[instanceSpec & ISP_SHAPE]); alignedBytes = ROUNDED_BYTES (numBytes); p_instance = _gst_alloc_obj (alignedBytes, p_oop); INIT_UNALIGNED_OBJECT (*p_oop, alignedBytes - numBytes); p_instance->objClass = class_oop; (*p_oop)->flags |= (class_oop->flags & F_UNTRUSTED); return p_instance; } gst_object new_instance (OOP class_oop, OOP *p_oop) { size_t numBytes; intptr_t instanceSpec; gst_object p_instance; instanceSpec = CLASS_INSTANCE_SPEC (class_oop); numBytes = sizeof (gst_object_header) + SIZE_TO_BYTES(instanceSpec >> ISP_NUMFIXEDFIELDS); p_instance = _gst_alloc_obj (numBytes, p_oop); p_instance->objClass = class_oop; (*p_oop)->flags |= (class_oop->flags & F_UNTRUSTED); return p_instance; } gst_object instantiate_numbytes (OOP class_oop, OOP *p_oop, intptr_t instanceSpec, size_t numBytes) { gst_object p_instance; int n; OOP src, *dest; p_instance = _gst_alloc_obj (numBytes, p_oop); p_instance->objClass = class_oop; (*p_oop)->flags |= (class_oop->flags & F_UNTRUSTED); n = instanceSpec >> ISP_NUMFIXEDFIELDS; if UNCOMMON (n == 0) return p_instance; src = _gst_nil_oop; dest = p_instance->data; dest[0] = src; if UNCOMMON (n == 1) return p_instance; dest[1] = src; if UNCOMMON (n == 2) return p_instance; dest[2] = src; if UNCOMMON (n == 3) return p_instance; dest += 3; n -= 3; do *dest++ = src; while (--n > 0); return p_instance; } gst_object instantiate_with (OOP class_oop, size_t numIndexFields, OOP *p_oop) { size_t numBytes, indexedBytes, alignedBytes; intptr_t instanceSpec; gst_object p_instance; instanceSpec = CLASS_INSTANCE_SPEC (class_oop); #ifndef OPTIMIZE if (!(instanceSpec & ISP_ISINDEXABLE) && numIndexFields != 0) _gst_errorf ("class without indexed instance variables passed to instantiate_with"); #endif indexedBytes = numIndexFields << _gst_log2_sizes[instanceSpec & ISP_SHAPE]; numBytes = sizeof (gst_object_header) + SIZE_TO_BYTES(instanceSpec >> ISP_NUMFIXEDFIELDS) + indexedBytes; if COMMON ((instanceSpec & ISP_INDEXEDVARS) == GST_ISP_POINTER) { p_instance = _gst_alloc_obj (numBytes, p_oop); p_instance->objClass = class_oop; (*p_oop)->flags |= (class_oop->flags & F_UNTRUSTED); nil_fill (p_instance->data, (instanceSpec >> ISP_NUMFIXEDFIELDS) + numIndexFields); } else { alignedBytes = ROUNDED_BYTES (numBytes); p_instance = instantiate_numbytes (class_oop, p_oop, instanceSpec, alignedBytes); INIT_UNALIGNED_OBJECT (*p_oop, alignedBytes - numBytes); memset (&p_instance->data[instanceSpec >> ISP_NUMFIXEDFIELDS], 0, indexedBytes); } return p_instance; } gst_object instantiate (OOP class_oop, OOP *p_oop) { size_t numBytes; intptr_t instanceSpec; instanceSpec = CLASS_INSTANCE_SPEC (class_oop); numBytes = sizeof (gst_object_header) + SIZE_TO_BYTES(instanceSpec >> ISP_NUMFIXEDFIELDS); return instantiate_numbytes (class_oop, p_oop, instanceSpec, numBytes); } OOP * ordered_collection_begin (OOP orderedCollectionOOP) { gst_ordered_collection oc; oc = (gst_ordered_collection) OOP_TO_OBJ (orderedCollectionOOP); return &oc->data[TO_INT (oc->firstIndex) - 1]; } OOP * ordered_collection_end (OOP orderedCollectionOOP) { gst_ordered_collection oc; oc = (gst_ordered_collection) OOP_TO_OBJ (orderedCollectionOOP); return &oc->data[TO_INT (oc->lastIndex)]; } OOP dictionary_association_at (OOP dictionaryOOP, OOP keyOOP) { gst_object dictionary; size_t index, count, numFields, numFixedFields; OOP associationOOP; gst_association association; if UNCOMMON (IS_NIL (dictionaryOOP)) return (_gst_nil_oop); dictionary = OOP_TO_OBJ (dictionaryOOP); numFixedFields = OOP_FIXED_FIELDS (dictionaryOOP); numFields = NUM_WORDS (dictionary) - numFixedFields; index = scramble (OOP_INDEX (keyOOP)); count = numFields; while (count--) { index &= numFields - 1; associationOOP = dictionary->data[numFixedFields + index]; if COMMON (IS_NIL (associationOOP)) return (_gst_nil_oop); association = (gst_association) OOP_TO_OBJ (associationOOP); if COMMON (association->key == keyOOP) return (associationOOP); /* linear reprobe -- it is simple and guaranteed */ index++; } _gst_errorf ("Error - searching Dictionary for nil, but it is full!\n"); abort (); } OOP dictionary_at (OOP dictionaryOOP, OOP keyOOP) { OOP assocOOP; assocOOP = dictionary_association_at (dictionaryOOP, keyOOP); if UNCOMMON (IS_NIL (assocOOP)) return (_gst_nil_oop); else return (ASSOCIATION_VALUE (assocOOP)); } OOP association_new (OOP key, OOP value) { gst_association association; OOP associationOOP; association = (gst_association) new_instance (_gst_association_class, &associationOOP); association->key = key; association->value = value; return (associationOOP); } OOP variable_binding_new (OOP key, OOP value, OOP environment) { gst_variable_binding binding; OOP bindingOOP; binding = (gst_variable_binding) new_instance (_gst_variable_binding_class, &bindingOOP); binding->key = key; binding->value = value; binding->environment = environment; return (bindingOOP); } int oop_num_fields (OOP oop) { gst_object object; intptr_t instanceSpec; size_t words, dataBytes, fixed; object = OOP_TO_OBJ (oop); words = NUM_WORDS (object); if COMMON (!(oop->flags & F_BYTE)) return words; instanceSpec = GET_INSTANCE_SPEC (object); fixed = instanceSpec >> ISP_NUMFIXEDFIELDS; words -= fixed; dataBytes = SIZE_TO_BYTES (words) - (oop->flags & EMPTY_BYTES); return fixed + (dataBytes >> _gst_log2_sizes[instanceSpec & ISP_SHAPE]); } static int num_valid_oops (OOP oop) { gst_object object; object = OOP_TO_OBJ (oop); if UNCOMMON (oop->flags & F_CONTEXT) { gst_method_context ctx; intptr_t methodSP; ctx = (gst_method_context) object; methodSP = TO_INT (ctx->spOffset); return ctx->contextStack + methodSP + 1 - object->data; } else return NUM_OOPS (object); } /* Returns whether the SCANNEDOOP points to TARGETOOP. */ mst_Boolean is_owner (OOP scannedOOP, OOP targetOOP) { gst_object object; OOP *scanPtr; int n; object = OOP_TO_OBJ (scannedOOP); if UNCOMMON (object->objClass == targetOOP) return true; n = num_valid_oops (scannedOOP); /* Peel a couple of iterations for optimization. */ if (n--) { scanPtr = object->data; if UNCOMMON (*scanPtr++ == targetOOP) return true; if (n--) do if UNCOMMON (*scanPtr++ == targetOOP) return true; while (n--); } return false; } OOP index_oop (OOP oop, size_t index) { gst_object object = OOP_TO_OBJ (oop); intptr_t instanceSpec = GET_INSTANCE_SPEC (object); return index_oop_spec (oop, object, index, instanceSpec); } OOP index_oop_spec (OOP oop, gst_object object, size_t index, intptr_t instanceSpec) { size_t maxIndex, maxByte; char *src; if UNCOMMON (index < 1) return (NULL); index--; #define DO_INDEX_OOP(type, dest) \ /* Find the number of bytes in the object. */ \ maxByte = NUM_WORDS (object) * sizeof (PTR); \ if (sizeof (type) <= sizeof (PTR)) \ maxByte -= (oop->flags & EMPTY_BYTES); \ \ index = \ index * sizeof(type) \ + (instanceSpec >> ISP_NUMFIXEDFIELDS) * sizeof (PTR); \ \ /* Check that we're on bounds. */ \ if UNCOMMON (index + sizeof(type) > maxByte) \ return (NULL); \ \ /* Use a cast if unaligned accesses are supported, else memcpy. */ \ src = ((char *) object->data) + index; \ if (sizeof (type) <= sizeof (PTR)) \ (dest) = *(type *) src; \ else \ memcpy ((char *) &(dest), src, sizeof (type)); switch (instanceSpec & ISP_INDEXEDVARS) { case GST_ISP_SCHAR: { int8_t i; DO_INDEX_OOP (int8_t, i); return FROM_INT (i); } case GST_ISP_UCHAR: { uint8_t i; DO_INDEX_OOP (uint8_t, i); return FROM_INT (i); } case GST_ISP_CHARACTER: { uint8_t i; DO_INDEX_OOP (uint8_t, i); return CHAR_OOP_AT (i); } case GST_ISP_SHORT: { uint16_t i; DO_INDEX_OOP (int16_t, i); return FROM_INT (i); } case GST_ISP_USHORT: { uint16_t i; DO_INDEX_OOP (uint16_t, i); return FROM_INT (i); } case GST_ISP_INT: { uint32_t i; DO_INDEX_OOP (int32_t, i); return from_c_int_32 (i); } case GST_ISP_UINT: { uint32_t i; DO_INDEX_OOP (uint32_t, i); return from_c_uint_32 (i); } case GST_ISP_FLOAT: { float f; DO_INDEX_OOP (float, f); return floate_new (f); } case GST_ISP_INT64: { uint64_t i; DO_INDEX_OOP (int64_t, i); return from_c_int_64 (i); } case GST_ISP_UINT64: { uint64_t i; DO_INDEX_OOP (uint64_t, i); return from_c_uint_64 (i); } case GST_ISP_DOUBLE: { double d; DO_INDEX_OOP (double, d); return floatd_new (d); } case GST_ISP_UTF32: { uint32_t i; DO_INDEX_OOP (uint32_t, i); return char_new (i); } case GST_ISP_POINTER: maxIndex = NUM_WORDS (object); index += instanceSpec >> ISP_NUMFIXEDFIELDS; if UNCOMMON (index >= maxIndex) return (NULL); return (object->data[index]); } #undef DO_INDEX_OOP return (NULL); } mst_Boolean index_oop_put (OOP oop, size_t index, OOP value) { gst_object object = OOP_TO_OBJ (oop); intptr_t instanceSpec = GET_INSTANCE_SPEC (object); return index_oop_put_spec (oop, object, index, value, instanceSpec); } mst_Boolean index_oop_put_spec (OOP oop, gst_object object, size_t index, OOP value, intptr_t instanceSpec) { size_t maxIndex; if UNCOMMON (index < 1) return (false); index--; #define DO_INDEX_OOP_PUT(type, cond, src) \ if COMMON (cond) \ { \ /* Find the number of bytes in the object. */ \ size_t maxByte = NUM_WORDS (object) * sizeof (PTR); \ if (sizeof (type) <= sizeof (PTR)) \ maxByte -= (oop->flags & EMPTY_BYTES); \ \ index = \ index * sizeof(type) \ + (instanceSpec >> ISP_NUMFIXEDFIELDS) * sizeof (PTR); \ \ /* Check that we're on bounds. */ \ if UNCOMMON (index + sizeof(type) > maxByte) \ return (false); \ \ /* Use a cast if unaligned accesses are ok, else memcpy. */ \ if (sizeof (type) <= sizeof (PTR)) \ { \ type *destAddr = (type *) (((char *) object->data) + index);\ *destAddr = (type) (src); \ } \ else \ { \ char *destAddr = ((char *) object->data) + index; \ type src_ = (type) (src); \ memcpy (destAddr, (char *) &src_, sizeof (type)); \ } \ return (true); \ } switch (instanceSpec & ISP_INDEXEDVARS) { case GST_ISP_SCHAR: { DO_INDEX_OOP_PUT (int8_t, IS_INT (value) && TO_INT (value) >= -128 && TO_INT (value) <= 127, TO_INT (value)); return (false); } case GST_ISP_UCHAR: { DO_INDEX_OOP_PUT (uint8_t, IS_INT (value) && TO_INT (value) >= 0 && TO_INT (value) <= 255, TO_INT (value)); return (false); } case GST_ISP_CHARACTER: { DO_INDEX_OOP_PUT (uint8_t, !IS_INT (value) && OOP_CLASS (value) == _gst_char_class, CHAR_OOP_VALUE (value)); return (false); } case GST_ISP_SHORT: { DO_INDEX_OOP_PUT (uint16_t, IS_INT (value) && TO_INT (value) >= -32768 && TO_INT (value) <= 32767, TO_INT (value)); return (false); } case GST_ISP_USHORT: { DO_INDEX_OOP_PUT (uint16_t, IS_INT (value) && TO_INT (value) >= 0 && TO_INT (value) <= 65535, TO_INT (value)); return (false); } case GST_ISP_INT: { DO_INDEX_OOP_PUT (int32_t, is_c_int_32 (value), to_c_int_32 (value)); return (false); } case GST_ISP_UINT: { DO_INDEX_OOP_PUT (uint32_t, is_c_uint_32 (value), to_c_int_32 (value)); return (false); } case GST_ISP_FLOAT: { DO_INDEX_OOP_PUT (float, IS_INT (value), TO_INT (value)); DO_INDEX_OOP_PUT (float, OOP_CLASS (value) == _gst_floate_class, FLOATE_OOP_VALUE (value)); DO_INDEX_OOP_PUT (float, OOP_CLASS (value) == _gst_floatd_class, FLOATD_OOP_VALUE (value)); DO_INDEX_OOP_PUT (float, OOP_CLASS (value) == _gst_floatq_class, FLOATQ_OOP_VALUE (value)); return (false); } case GST_ISP_INT64: { DO_INDEX_OOP_PUT (int64_t, is_c_int_64 (value), to_c_int_64 (value)); return (false); } case GST_ISP_UINT64: { DO_INDEX_OOP_PUT (uint64_t, is_c_uint_64 (value), to_c_uint_64 (value)); return (false); } case GST_ISP_DOUBLE: { DO_INDEX_OOP_PUT (double, IS_INT (value), TO_INT (value)); DO_INDEX_OOP_PUT (double, OOP_CLASS (value) == _gst_floatd_class, FLOATD_OOP_VALUE (value)); DO_INDEX_OOP_PUT (double, OOP_CLASS (value) == _gst_floate_class, FLOATE_OOP_VALUE (value)); DO_INDEX_OOP_PUT (double, OOP_CLASS (value) == _gst_floatq_class, FLOATQ_OOP_VALUE (value)); return (false); } case GST_ISP_UTF32: { DO_INDEX_OOP_PUT (uint32_t, !IS_INT (value) && (OOP_CLASS (value) == _gst_unicode_character_class || (OOP_CLASS (value) == _gst_char_class && CHAR_OOP_VALUE (value) <= 127)), CHAR_OOP_VALUE (value)); return (false); } case GST_ISP_POINTER: maxIndex = NUM_WORDS (object); index += instanceSpec >> ISP_NUMFIXEDFIELDS; if UNCOMMON (index >= maxIndex) return (false); object->data[index] = value; return (true); } #undef DO_INDEX_OOP_PUT return (false); } OOP inst_var_at (OOP oop, int index) { gst_object object; object = OOP_TO_OBJ (oop); return (object->data[index - 1]); } void inst_var_at_put (OOP oop, int index, OOP value) { gst_object object; object = OOP_TO_OBJ (oop); object->data[index - 1] = value; } mst_Boolean is_c_int_32 (OOP oop) { gst_byte_array ba; if COMMON (IS_INT (oop)) #if SIZEOF_OOP == 4 return (true); #else return (TO_INT (oop) >= INT_MIN && TO_INT (oop) < INT_MAX); #endif ba = (gst_byte_array) OOP_TO_OBJ (oop); if (COMMON (ba->objClass == _gst_large_positive_integer_class) || ba->objClass == _gst_large_negative_integer_class) return (NUM_INDEXABLE_FIELDS (oop) == 4); return (false); } mst_Boolean is_c_uint_32 (OOP oop) { gst_byte_array ba; if COMMON (IS_INT (oop)) #if SIZEOF_OOP == 4 return (TO_INT (oop) >= 0); #else return (TO_INT (oop) >= 0 && TO_INT (oop) < UINT_MAX); #endif ba = (gst_byte_array) OOP_TO_OBJ (oop); if COMMON (ba->objClass == _gst_large_positive_integer_class) { switch (NUM_INDEXABLE_FIELDS (oop)) { case 4: return (true); case 5: return (ba->bytes[4] == 0); } } return (false); } int32_t to_c_int_32 (OOP oop) { gst_byte_array ba; if COMMON (IS_INT (oop)) return (TO_INT (oop)); ba = (gst_byte_array) OOP_TO_OBJ (oop); return ((int32_t) ((((uint32_t) ba->bytes[3]) << 24) + (((uint32_t) ba->bytes[2]) << 16) + (((uint32_t) ba->bytes[1]) << 8) + ((uint32_t) ba->bytes[0]))); } OOP from_c_int_32 (int32_t i) { gst_byte_array ba; OOP oop; const uint32_t ui = (uint32_t) i; if COMMON (i >= MIN_ST_INT && i <= MAX_ST_INT) return (FROM_INT (i)); if (i < 0) ba = (gst_byte_array) new_instance_with (_gst_large_negative_integer_class, 4, &oop); else ba = (gst_byte_array) new_instance_with (_gst_large_positive_integer_class, 4, &oop); ba->bytes[0] = (gst_uchar) ui; ba->bytes[1] = (gst_uchar) (ui >> 8); ba->bytes[2] = (gst_uchar) (ui >> 16); ba->bytes[3] = (gst_uchar) (ui >> 24); return (oop); } OOP from_c_uint_32 (uint32_t ui) { gst_byte_array ba; OOP oop; if COMMON (ui <= MAX_ST_INT) return (FROM_INT (ui)); if UNCOMMON (((intptr_t) ui) < 0) { ba = (gst_byte_array) new_instance_with (_gst_large_positive_integer_class, 5, &oop); ba->bytes[4] = 0; } else ba = (gst_byte_array) new_instance_with (_gst_large_positive_integer_class, 4, &oop); ba->bytes[0] = (gst_uchar) ui; ba->bytes[1] = (gst_uchar) (ui >> 8); ba->bytes[2] = (gst_uchar) (ui >> 16); ba->bytes[3] = (gst_uchar) (ui >> 24); return (oop); } mst_Boolean is_c_int_64 (OOP oop) { gst_byte_array ba; if COMMON (IS_INT (oop)) return (true); ba = (gst_byte_array) OOP_TO_OBJ (oop); if COMMON (ba->objClass == _gst_large_negative_integer_class || ba->objClass == _gst_large_positive_integer_class) { switch (NUM_INDEXABLE_FIELDS (oop)) { case 4: case 5: case 6: case 7: case 8: return (true); } } return (false); } mst_Boolean is_c_uint_64 (OOP oop) { gst_byte_array ba; if COMMON (IS_INT (oop)) return (TO_INT (oop) >= 0); ba = (gst_byte_array) OOP_TO_OBJ (oop); if COMMON (ba->objClass == _gst_large_positive_integer_class) { switch (NUM_INDEXABLE_FIELDS (oop)) { case 4: case 5: case 6: case 7: case 8: return (true); case 9: return (ba->bytes[8] == 0); } } return (false); } uint64_t to_c_uint_64 (OOP oop) { gst_byte_array ba; uint64_t result, mask; if COMMON (IS_INT (oop)) return (TO_INT (oop)); ba = (gst_byte_array) OOP_TO_OBJ (oop); mask = (((uint64_t)2) << (NUM_INDEXABLE_FIELDS (oop) * 8 - 1)) - 1; result = ((int64_t) ( (((uint64_t) ba->bytes[3]) << 24) + (((uint64_t) ba->bytes[2]) << 16) + (((uint64_t) ba->bytes[1]) << 8) + ((uint64_t) ba->bytes[0]))); if (NUM_INDEXABLE_FIELDS (oop) > 4) result |= mask & ((int64_t) ( (((uint64_t) ba->bytes[7]) << 56) + (((uint64_t) ba->bytes[6]) << 48) + (((uint64_t) ba->bytes[5]) << 40) + (((uint64_t) ba->bytes[4]) << 32))); return result; } int64_t to_c_int_64 (OOP oop) { gst_byte_array ba; int64_t result, mask; if COMMON (IS_INT (oop)) return (TO_INT (oop)); ba = (gst_byte_array) OOP_TO_OBJ (oop); mask = (((uint64_t)2) << (NUM_INDEXABLE_FIELDS (oop) * 8 - 1)) - 1; result = (ba->objClass == _gst_large_negative_integer_class) ? ~mask : 0; result |= ((int64_t) ( (((uint64_t) ba->bytes[3]) << 24) + (((uint64_t) ba->bytes[2]) << 16) + (((uint64_t) ba->bytes[1]) << 8) + ((uint64_t) ba->bytes[0]))); if (NUM_INDEXABLE_FIELDS (oop) > 4) result |= mask & ((int64_t) ( (((uint64_t) ba->bytes[7]) << 56) + (((uint64_t) ba->bytes[6]) << 48) + (((uint64_t) ba->bytes[5]) << 40) + (((uint64_t) ba->bytes[4]) << 32))); return result; } OOP from_c_int_64 (int64_t i) { gst_byte_array ba; OOP oop; const uint64_t ui = (uint64_t) i; if COMMON (i >= MIN_ST_INT && i <= MAX_ST_INT) return (FROM_INT (i)); if (i < 0) ba = (gst_byte_array) new_instance_with (_gst_large_negative_integer_class, 8, &oop); else ba = (gst_byte_array) new_instance_with (_gst_large_positive_integer_class, 8, &oop); ba->bytes[0] = (gst_uchar) ui; ba->bytes[1] = (gst_uchar) (ui >> 8); ba->bytes[2] = (gst_uchar) (ui >> 16); ba->bytes[3] = (gst_uchar) (ui >> 24); ba->bytes[4] = (gst_uchar) (ui >> 32); ba->bytes[5] = (gst_uchar) (ui >> 40); ba->bytes[6] = (gst_uchar) (ui >> 48); ba->bytes[7] = (gst_uchar) (ui >> 56); return (oop); } OOP from_c_uint_64 (uint64_t ui) { gst_byte_array ba; OOP oop; if COMMON (ui <= MAX_ST_INT) return (FROM_INT (ui)); if UNCOMMON (((int64_t) ui) < 0) { ba = (gst_byte_array) new_instance_with (_gst_large_positive_integer_class, 9, &oop); ba->bytes[8] = 0; } else ba = (gst_byte_array) new_instance_with (_gst_large_positive_integer_class, 8, &oop); ba->bytes[0] = (gst_uchar) ui; ba->bytes[1] = (gst_uchar) (ui >> 8); ba->bytes[2] = (gst_uchar) (ui >> 16); ba->bytes[3] = (gst_uchar) (ui >> 24); ba->bytes[4] = (gst_uchar) (ui >> 32); ba->bytes[5] = (gst_uchar) (ui >> 40); ba->bytes[6] = (gst_uchar) (ui >> 48); ba->bytes[7] = (gst_uchar) (ui >> 56); return (oop); } static inline PTR cobject_value (OOP oop) { gst_cobject cObj = (gst_cobject) OOP_TO_OBJ (oop); if (IS_NIL (cObj->storage)) return (PTR) COBJECT_OFFSET_OBJ (cObj); else { gst_uchar *baseAddr = ((gst_byte_array) OOP_TO_OBJ (cObj->storage))->bytes; return (PTR) (baseAddr + COBJECT_OFFSET_OBJ (cObj)); } } /* Sets the address of the data stored in a CObject. */ static inline void set_cobject_value (OOP oop, PTR val) { gst_cobject cObj = (gst_cobject) OOP_TO_OBJ (oop); cObj->storage = _gst_nil_oop; SET_COBJECT_OFFSET_OBJ (cObj, (uintptr_t) val); } /* Return whether the address of the data stored in a CObject, offsetted by OFFSET bytes, is still in bounds. */ static inline mst_Boolean cobject_index_check (OOP oop, intptr_t offset, size_t size) { gst_cobject cObj = (gst_cobject) OOP_TO_OBJ (oop); OOP baseOOP = cObj->storage; intptr_t maxOffset; if (IS_NIL (baseOOP)) return true; offset += COBJECT_OFFSET_OBJ (cObj); if (offset < 0) return false; maxOffset = SIZE_TO_BYTES (NUM_WORDS (OOP_TO_OBJ (baseOOP))); if (baseOOP->flags & F_BYTE) maxOffset -= (baseOOP->flags & EMPTY_BYTES); return (offset + size - 1 < maxOffset); } smalltalk-3.2.5/libgst/interp.inl0000644000175000017500000001365112130343734013725 00000000000000/******************************** -*- C -*- **************************** * * Byte code interpreter inlines * * ***********************************************************************/ /*********************************************************************** * * Copyright 2000, 2001, 2002, 2006 Free Software Foundation, Inc. * Written by Steve Byrne. * * This file is part of GNU Smalltalk. * * GNU Smalltalk is free software; you can redistribute it and/or modify it * under the terms of the GNU General Public License as published by the Free * Software Foundation; either version 2, or (at your option) any later * version. * * Linking GNU Smalltalk statically or dynamically with other modules is * making a combined work based on GNU Smalltalk. Thus, the terms and * conditions of the GNU General Public License cover the whole * combination. * * In addition, as a special exception, the Free Software Foundation * give you permission to combine GNU Smalltalk with free software * programs or libraries that are released under the GNU LGPL and with * independent programs running under the GNU Smalltalk virtual machine. * * You may copy and distribute such a system following the terms of the * GNU GPL for GNU Smalltalk and the licenses of the other code * concerned, provided that you include the source code of that other * code when and as the GNU GPL requires distribution of source code. * * Note that people who make modified versions of GNU Smalltalk are not * obligated to grant this special exception for their modified * versions; it is their choice whether to do so. The GNU General * Public License gives permission to release a modified version without * this exception; this exception also makes it possible to release a * modified version which carries forward this exception. * * GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or * FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for * more details. * * You should have received a copy of the GNU General Public License along with * GNU Smalltalk; see the file COPYING. If not, write to the Free Software * Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * ***********************************************************************/ /* Do an arithmetic operation between A and B and set OVERFLOW to false or true depending on overflow. */ static inline OOP add_with_check (OOP op1, OOP op2, mst_Boolean *overflow); static inline OOP sub_with_check (OOP op1, OOP op2, mst_Boolean *overflow); static inline OOP mul_with_check (OOP op1, OOP op2, mst_Boolean *overflow); /* These do not need overflow checking. */ static inline OOP tagged_and (OOP op1, OOP op2); static inline OOP tagged_or (OOP op1, OOP op2); static inline OOP tagged_xor (OOP op1, OOP op2); /* using STACK_AT is correct: numArgs == 0 means that there's just the * receiver on the stack, at 0. numArgs = 1 means that at location 0 is * the arg, location 1 is the receiver. And so on. */ #define SEND_MESSAGE(sendSelector, sendArgs) do { \ OOP _receiver; \ _receiver = STACK_AT(sendArgs); \ _gst_send_message_internal(sendSelector, sendArgs, _receiver, \ OOP_INT_CLASS(_receiver)); \ } while(0) #if defined __i386__ #define OP_SUFFIX "l" #define OP_CONSTRAINT "rmi" #else #define OP_SUFFIX "q" #define OP_CONSTRAINT "rme" #endif OOP tagged_and (OOP op1, OOP op2) { intptr_t iop1 = (intptr_t) op1; intptr_t iop2 = (intptr_t) op2; return (OOP) (iop1 & iop2); } OOP tagged_or (OOP op1, OOP op2) { intptr_t iop1 = (intptr_t) op1; intptr_t iop2 = (intptr_t) op2; return (OOP) (iop1 | iop2); } OOP tagged_xor (OOP op1, OOP op2) { intptr_t iop1 = (intptr_t) op1; intptr_t iop2 = ((intptr_t) op2) - 1; return (OOP) (iop1 ^ iop2); } OOP add_with_check (OOP op1, OOP op2, mst_Boolean *overflow) { intptr_t iop1 = (intptr_t) op1; intptr_t iop2 = (intptr_t) op2; intptr_t iresult; #if (defined __i386__ || defined __x86_64__) && !defined NO_OPTIMIZED_SMALLINTEGERS int of = 0; iop2--; asm ("add" OP_SUFFIX " %3, %2\n" "seto %b1" : "=r" (iresult), "+&q" (of) : "0" (iop1), OP_CONSTRAINT (iop2)); *overflow = of; #else iresult = no_opt (iop1 + (iop2 - 1)); *overflow = false; if (COMMON ((iop1 ^ iop2) >= 0) && UNCOMMON ((iop1 ^ iresult) < 0)) *overflow = true; #endif return (OOP) iresult; } OOP sub_with_check (OOP op1, OOP op2, mst_Boolean *overflow) { intptr_t iop1 = (intptr_t) op1; intptr_t iop2 = (intptr_t) op2; intptr_t iresult; #if (defined __i386__ || defined __x86_64__) && !defined NO_OPTIMIZED_SMALLINTEGERS int of = 0; iop2--; asm ("sub" OP_SUFFIX " %3, %2\n" "seto %b1" : "=r" (iresult), "+&q" (of) : "0" (iop1), OP_CONSTRAINT (iop2)); *overflow = of; #else iresult = no_opt (iop1 - (iop2 - 1)); *overflow = false; if (UNCOMMON ((iop1 ^ iop2) < 0) && UNCOMMON ((iop1 ^ iresult) < 0)) *overflow = true; #endif return (OOP) iresult; } OOP mul_with_check (OOP op1, OOP op2, mst_Boolean *overflow) { intptr_t a = TO_INT (op1); intptr_t b = TO_INT (op2); intmax_t result = (intmax_t)a * b; *overflow = false; /* We define the largest int type in stdintx.h, but we can only use it if it is two times the width of an intptr_t. */ if (sizeof (intmax_t) >= 2 * sizeof (intptr_t)) { if UNCOMMON (result > MAX_ST_INT || result < MIN_ST_INT) *overflow = true; else return FROM_INT (result); } /* This fallback method uses a division to do overflow check */ else { if COMMON ((((uintptr_t) (a | b)) < (1L << (ST_INT_SIZE / 2)) || b == 0 || result / b == a) && !INT_OVERFLOW (result)) return FROM_INT (result); else *overflow = true; } return FROM_INT (0); } smalltalk-3.2.5/libgst/genpr-scan.l0000644000175000017500000001450112123404352014121 00000000000000/******************************** -*- C -*- **************************** * * GNU Smalltalk genprims tool - lexical analyzer * ***********************************************************************/ /*********************************************************************** * * Copyright 2002, 2006 Free Software Foundation, Inc. * Written by Paolo Bonzini. * * This file is part of GNU Smalltalk. * * GNU Smalltalk is free software; you can redistribute it and/or modify it * under the terms of the GNU General Public License as published by the Free * Software Foundation; either version 2, or (at your option) any later * version. * * Linking GNU Smalltalk statically or dynamically with other modules is * making a combined work based on GNU Smalltalk. Thus, the terms and * conditions of the GNU General Public License cover the whole * combination. * * In addition, as a special exception, the Free Software Foundation * give you permission to combine GNU Smalltalk with free software * programs or libraries that are released under the GNU LGPL and with * independent programs running under the GNU Smalltalk virtual machine. * * You may copy and distribute such a system following the terms of the * GNU GPL for GNU Smalltalk and the licenses of the other code * concerned, provided that you include the source code of that other * code when and as the GNU GPL requires distribution of source code. * * Note that people who make modified versions of GNU Smalltalk are not * obligated to grant this special exception for their modified * versions; it is their choice whether to do so. The GNU General * Public License gives permission to release a modified version without * this exception; this exception also makes it possible to release a * modified version which carries forward this exception. * * GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or * FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for * more details. * * You should have received a copy of the GNU General Public License along with * GNU Smalltalk; see the file COPYING. If not, write to the Free Software * Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * ***********************************************************************/ %x C_COMMENT %x C_CHAR %x C_STRING %x CPP_CODE %x C_CODE %option nounput %option noyywrap %option never-interactive %{ #include "genprims.h" #include "genpr-parse.h" static int from = 0, depth = 0; #if !defined YY_FLEX_SUBMINOR_VERSION || YY_FLEX_SUBMINOR_VERSION < 31 int yylineno = 1; #endif /* This file implements a bit more than a lexical analyzer: it also writes literal tokens to the output until a reserved word is found. This is done by this macro which decides whether to return the token to yyparse and whether to append it to a filament (these two things are not mutually exclusive, because braces are both written and returned, for example). Note that whitespace should be written to the literal_fil filament, but not returned to yyparse when there is no active literal_fil. Also note that the ifs are resolved at compile time. */ #define IS_TOKEN(tok) \ do { \ if (literal_fil) \ { \ if (tok != PRIMITIVE && tok != PRIM_ID) \ filcat (literal_fil, yytext); \ else \ literal_fil = NULL; \ if (tok == PRIMITIVE || tok == PRIM_ID || tok == '{' || tok == '}') \ return tok; \ } \ else \ { \ if (tok == '{') \ literal_fil = stmt_fil; \ if (tok != WSPACE) \ return tok; \ } \ } while(0) %} %% { \n+ { yylval.text = yytext; yylineno += yyleng; IS_TOKEN (WSPACE); } [ \f]+ { yylval.text = yytext; IS_TOKEN (WSPACE); } } { primitive { yylval.text = yytext; IS_TOKEN (PRIMITIVE); } "[" { yylval.text = yytext; IS_TOKEN ('['); } "]" { yylval.text = yytext; IS_TOKEN (']'); } "," { yylval.text = yytext; IS_TOKEN (','); } "=" { yylval.text = yytext; IS_TOKEN ('='); } ":" { yylval.text = yytext; IS_TOKEN (':'); } "{" { yylval.text = yytext; depth = 1; BEGIN (C_CODE); IS_TOKEN ('{'); } } { "'" { yylval.text = yytext; from = YY_START; BEGIN (C_CHAR); IS_TOKEN (LITERAL); } "\"" { yylval.text = yytext; from = YY_START; BEGIN (C_STRING); IS_TOKEN (LITERAL); } "/*" { yylval.text = yytext; from = YY_START; BEGIN (C_COMMENT); IS_TOKEN (WSPACE); } ^[ ]*# { yylval.text = yytext; from = YY_START; BEGIN (CPP_CODE); IS_TOKEN (LITERAL); } "(" { yylval.text = yytext; IS_TOKEN ('('); } ")" { yylval.text = yytext; IS_TOKEN (')'); } prim_id { yylval.text = yytext; IS_TOKEN (PRIM_ID); } [1-9][0-9]* | 0x[0-9A-Fa-f]+ | 0[0-7]+ { yylval.text = yytext; IS_TOKEN (NUMBER); } [a-zA-Z_][a-zA-Z0-9_]* { yylval.text = yytext; IS_TOKEN (ID); } } { "{" { yylval.text = yytext; depth++; IS_TOKEN (LITERAL); } "}" { yylval.text = yytext; if (--depth) IS_TOKEN (LITERAL); else { BEGIN (INITIAL); IS_TOKEN ('}'); } } . { yylval.text = yytext; IS_TOKEN (LITERAL); } } { [^*\n]*"*"*\n { yylval.text = yytext; yylineno++; IS_TOKEN (WSPACE); } [^*\n]*"*"+[^/*] { yylval.text = yytext; IS_TOKEN (WSPACE); } [^*\n]*"*"+"/" { yylval.text = yytext; BEGIN (from); IS_TOKEN (WSPACE); } } { "'" { yylval.text = yytext; BEGIN (from); IS_TOKEN (LITERAL); } } { "\"" { yylval.text = yytext; BEGIN (from); IS_TOKEN (LITERAL); } } { \\. { yylineno += (yytext[1] == '\n'); yylval.text = yytext; IS_TOKEN (LITERAL); } . { yylineno += (yytext[0] == '\n'); yylval.text = yytext; IS_TOKEN (LITERAL); } } { [^\n]*"\\"[ ]*$ { yylval.text = yytext; IS_TOKEN (LITERAL); } [^\n]*$ { yylval.text = yytext; BEGIN (from); IS_TOKEN (LITERAL); } } smalltalk-3.2.5/libgst/opt.h0000644000175000017500000001355112130343734012672 00000000000000/******************************** -*- C -*- **************************** * * Byte Code optimization & analysis definitions. * * ***********************************************************************/ /*********************************************************************** * * Copyright 2000, 2001, 2002, 2006, 2008 Free Software Foundation, Inc. * Written by Paolo Bonzini. * * This file is part of GNU Smalltalk. * * GNU Smalltalk is free software; you can redistribute it and/or modify it * under the terms of the GNU General Public License as published by the Free * Software Foundation; either version 2, or (at your option) any later * version. * * Linking GNU Smalltalk statically or dynamically with other modules is * making a combined work based on GNU Smalltalk. Thus, the terms and * conditions of the GNU General Public License cover the whole * combination. * * In addition, as a special exception, the Free Software Foundation * give you permission to combine GNU Smalltalk with free software * programs or libraries that are released under the GNU LGPL and with * independent programs running under the GNU Smalltalk virtual machine. * * You may copy and distribute such a system following the terms of the * GNU GPL for GNU Smalltalk and the licenses of the other code * concerned, provided that you include the source code of that other * code when and as the GNU GPL requires distribution of source code. * * Note that people who make modified versions of GNU Smalltalk are not * obligated to grant this special exception for their modified * versions; it is their choice whether to do so. The GNU General * Public License gives permission to release a modified version without * this exception; this exception also makes it possible to release a * modified version which carries forward this exception. * * GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or * FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for * more details. * * You should have received a copy of the GNU General Public License along with * GNU Smalltalk; see the file COPYING. If not, write to the Free Software * Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * ***********************************************************************/ #ifndef GST_OPT_H #define GST_OPT_H /* This divides the byte codes of a method in basic blocks, optimizes each one, joins the optimized blocks and return a new vector of byte codes that contains the stream of optimized byte codes. Actual optimization of the basic blocks is optimize_basic_block's task; this function takes care of handling basic blocks and optimizing jumps (because they span multiple basic blocks). On output, BYTECODES is freed and another vector of bytecodes is answered. */ extern bc_vector _gst_optimize_bytecodes (bc_vector bytecodes) ATTRIBUTE_HIDDEN; /* This fills a table that says which stack slot is touched by each bytecode. BP points to SIZE bytecodes, POS points to an array that is filled with pointers relative to BASE. In other words, if bp[x] writes in the first stack slot, we put pos[x] == &base[0]; if bp[x] writes in the second stack slot, we put pos[x] == &base[1], etc. */ extern void _gst_compute_stack_positions (gst_uchar * bp, int size, PTR * base, PTR ** pos) ATTRIBUTE_HIDDEN; /* METHODOOP is the OOP for a CompiledMethod or CompiledBlock to be analyzed, having SIZE bytecodes. DEST is an array of SIZE items, which on output has non-zero items for jump destinations only: in particular, it is positive for a forward jump and negative for a backward jump. */ extern void _gst_analyze_bytecodes (OOP methodOOP, int size, char *dest) ATTRIBUTE_HIDDEN; /* Look at METHODOOP and checks if it is well formed. If it is an inner block, the external methods are examined. Abort if the process fails. */ extern void _gst_verify_sent_method (OOP methodOOP) ATTRIBUTE_HIDDEN; /* Look at METHODOOP and checks if it is well formed. If it is an inner block, DEPTH is the length of the static chain and NUM_OUTER_TEMPS is the number of temporaries available in the first outer context, the second, and so on; if they are NULL, the CompiledMethod that holds the block is verified. Return NULL or an error message. */ extern const char *_gst_verify_method (OOP methodOOP, int *num_outer_temps, int depth) ATTRIBUTE_HIDDEN; /* This looks at BYTECODES and checks if they could be replaced with an optimized return of self, of an instance variable or of a literal. */ extern int _gst_is_simple_return (bc_vector bytecodes) ATTRIBUTE_HIDDEN; /* This decides whether the block compiled to the BC bytecodes can be optimized; LITERALS contains the literals for the given block, and is used to check nested blocks: if there are any, they must already have had their cleanness set by a call to _gst_check_kind_of_block. The answer is a number that identifies the possibility to optimize the block: 0 for clean blocks, 1 for a self-contained block (no accesses to outer contexts) which however needs to know about self, 31 for a block containing a method return or a reference to thisContext, and another number N for a block that accesses the (N-1)th outer context. */ extern int _gst_check_kind_of_block (bc_vector bc, OOP * literals) ATTRIBUTE_HIDDEN; #define IS_RETURN_BYTECODE(b) ((b) == RETURN_METHOD_STACK_TOP || \ (b) == RETURN_CONTEXT_STACK_TOP) #define IS_SEND_BYTECODE(b) ((int) (b) < PUSH_TEMPORARY_VARIABLE) #define IS_PUSH_BYTECODE(b) (((b) >= PUSH_TEMPORARY_VARIABLE \ && (b) <= PUSH_RECEIVER_VARIABLE) \ || ((b) >= PUSH_INTEGER \ && (b) <= PUSH_LIT_CONSTANT)) #endif /* GST_OPT_H */ smalltalk-3.2.5/libgst/save.h0000644000175000017500000000554212123404352013023 00000000000000/******************************** -*- C -*- **************************** * * Public interface for binary save/restore module. * * ***********************************************************************/ /*********************************************************************** * * Copyright 1988,89,90,91,92,94,95,99,2000,2001,2002,2006 * Free Software Foundation, Inc. * Written by Steve Byrne. * * This file is part of GNU Smalltalk. * * GNU Smalltalk is free software; you can redistribute it and/or modify it * under the terms of the GNU General Public License as published by the Free * Software Foundation; either version 2, or (at your option) any later * version. * * Linking GNU Smalltalk statically or dynamically with other modules is * making a combined work based on GNU Smalltalk. Thus, the terms and * conditions of the GNU General Public License cover the whole * combination. * * In addition, as a special exception, the Free Software Foundation * give you permission to combine GNU Smalltalk with free software * programs or libraries that are released under the GNU LGPL and with * independent programs running under the GNU Smalltalk virtual machine. * * You may copy and distribute such a system following the terms of the * GNU GPL for GNU Smalltalk and the licenses of the other code * concerned, provided that you include the source code of that other * code when and as the GNU GPL requires distribution of source code. * * Note that people who make modified versions of GNU Smalltalk are not * obligated to grant this special exception for their modified * versions; it is their choice whether to do so. The GNU General * Public License gives permission to release a modified version without * this exception; this exception also makes it possible to release a * modified version which carries forward this exception. * * GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or * FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for * more details. * * You should have received a copy of the GNU General Public License along with * GNU Smalltalk; see the file COPYING. If not, write to the Free Software * Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * ***********************************************************************/ #ifndef GST_SAVE_H #define GST_SAVE_H /* Try to open FILENAME for output and writing a snapshot to it, and return whether the operation succeeded. */ extern mst_Boolean _gst_save_to_file (const char *fileName) ATTRIBUTE_HIDDEN; /* Try to open FILENAME for input and loading a snapshot from it, and return whether the operation succeeded. */ extern mst_Boolean _gst_load_from_file (const char *fileName) ATTRIBUTE_HIDDEN; #endif /* GST_SAVE_H */ smalltalk-3.2.5/libgst/comp.inl0000644000175000017500000001067612123404352013362 00000000000000/******************************** -*- C -*- **************************** * * Byte code compiler inlines * * ***********************************************************************/ /*********************************************************************** * * Copyright 2000, 2001, 2002, 2006 Free Software Foundation, Inc. * Written by Steve Byrne. * * This file is part of GNU Smalltalk. * * GNU Smalltalk is free software; you can redistribute it and/or modify it * under the terms of the GNU General Public License as published by the Free * Software Foundation; either version 2, or (at your option) any later * version. * * Linking GNU Smalltalk statically or dynamically with other modules is * making a combined work based on GNU Smalltalk. Thus, the terms and * conditions of the GNU General Public License cover the whole * combination. * * In addition, as a special exception, the Free Software Foundation * give you permission to combine GNU Smalltalk with free software * programs or libraries that are released under the GNU LGPL and with * independent programs running under the GNU Smalltalk virtual machine. * * You may copy and distribute such a system following the terms of the * GNU GPL for GNU Smalltalk and the licenses of the other code * concerned, provided that you include the source code of that other * code when and as the GNU GPL requires distribution of source code. * * Note that people who make modified versions of GNU Smalltalk are not * obligated to grant this special exception for their modified * versions; it is their choice whether to do so. The GNU General * Public License gives permission to release a modified version without * this exception; this exception also makes it possible to release a * modified version which carries forward this exception. * * GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or * FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for * more details. * * You should have received a copy of the GNU General Public License along with * GNU Smalltalk; see the file COPYING. If not, write to the Free Software * Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * ***********************************************************************/ /* Returns the bytecodes of the CompiledMethod or CompiledBlock, METHODOOP */ #define GET_METHOD_BYTECODES(methodOOP) \ ( ((gst_compiled_method)OOP_TO_OBJ(methodOOP))->bytecodes ) /* Returns the number of literals in the CompiledMethod or CompiledBlock, METHODOOP */ #define NUM_METHOD_LITERALS(methodOOP) \ NUM_WORDS (OOP_TO_OBJ(((gst_compiled_method)OOP_TO_OBJ(methodOOP))->literals)) /* Returns the literals of the CompiledMethod or CompiledBlock, METHODOOP */ #define GET_METHOD_LITERALS(methodOOP) \ ( OOP_TO_OBJ(((gst_compiled_method)OOP_TO_OBJ(methodOOP))->literals)->data ) /* Returns the header of the CompiledMethod, METHODOOP */ #define GET_METHOD_HEADER(methodOOP) \ (((gst_compiled_method)OOP_TO_OBJ(methodOOP))->header) /* Returns the class in which the CompiledMethod or CompiledBlock, METHODOOP, was defined */ #define GET_METHOD_CLASS(methodOOP) \ (((gst_method_info)OOP_TO_OBJ(get_method_info(methodOOP)))->class) /* Returns the selector under which the CompiledMethod or CompiledBlock, METHODOOP, was defined */ #define GET_METHOD_SELECTOR(methodOOP) \ (((gst_method_info)OOP_TO_OBJ(get_method_info(methodOOP)))->selector) /* Returns the header of the CompiledBlock, BLOCKOOP */ #define GET_BLOCK_HEADER(blockOOP) \ (((gst_compiled_block)OOP_TO_OBJ(blockOOP))->header) /* Returns the method for the CompiledBlock, BLOCKOOP */ #define GET_BLOCK_METHOD(blockOOP) \ (((gst_compiled_block)OOP_TO_OBJ(blockOOP))->method) /* Returns the number of arguments of the CompiledMethod or CompiledBlock pointed to by METHODOOP */ #define GET_METHOD_NUM_ARGS(methodOOP) \ (GET_METHOD_HEADER (methodOOP).numArgs) /* Returns the method descriptor of OOP (either the CompiledMethod's descriptor or the descriptor of the home method if a CompiledBlock). */ static inline OOP get_method_info (OOP oop); OOP get_method_info (OOP oop) { gst_object obj; obj = OOP_TO_OBJ (oop); if UNCOMMON (obj->objClass == _gst_compiled_block_class) { oop = ((gst_compiled_block) obj)->method; obj = OOP_TO_OBJ (oop); } return ((gst_compiled_method) obj)->descriptor; } smalltalk-3.2.5/libgst/heap.c0000644000175000017500000001702412123404352012773 00000000000000/******************************** -*- C -*- **************************** * * sbrk-like behavior for separate mmap'ed regions * * ***********************************************************************/ /*********************************************************************** * * Copyright 2000, 2001, 2002, 2003, 2006 Free Software Foundation, Inc. * Written by Paolo Bonzini (redisorganization of GNU mmalloc). * * This file is part of GNU Smalltalk. * * GNU Smalltalk is free software; you can redistribute it and/or modify it * under the terms of the GNU General Public License as published by the Free * Software Foundation; either version 2, or (at your option) any later * version. * * Linking GNU Smalltalk statically or dynamically with other modules is * making a combined work based on GNU Smalltalk. Thus, the terms and * conditions of the GNU General Public License cover the whole * combination. * * In addition, as a special exception, the Free Software Foundation * give you permission to combine GNU Smalltalk with free software * programs or libraries that are released under the GNU LGPL and with * independent programs running under the GNU Smalltalk virtual machine. * * You may copy and distribute such a system following the terms of the * GNU GPL for GNU Smalltalk and the licenses of the other code * concerned, provided that you include the source code of that other * code when and as the GNU GPL requires distribution of source code. * * Note that people who make modified versions of GNU Smalltalk are not * obligated to grant this special exception for their modified * versions; it is their choice whether to do so. The GNU General * Public License gives permission to release a modified version without * this exception; this exception also makes it possible to release a * modified version which carries forward this exception. * * GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or * FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for * more details. * * You should have received a copy of the GNU General Public License along with * GNU Smalltalk; see the file COPYING. If not, write to the Free Software * Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. ***********************************************************************/ #include "gstpriv.h" struct heap; /* Internal structure that defines the format of the heap descriptor. This gets written to the base address of the region that we are managing. */ struct heap { size_t areasize; /* The base address of the memory region for this malloc heap. This is the location where the bookkeeping data for mmap and for malloc begins. */ char *base; /* The current location in the memory region for this malloc heap which represents the end of memory in use. */ char *breakval; /* The end of the current memory region for this malloc heap. This is the first location past the end of mapped memory. */ char *top; }; /* This is the internal function for heap_sbrk which receives a struct heap instead of the pointer to the base location available to clients. */ static PTR heap_sbrk_internal (struct heap *hdp, int size); /* Cache pagesize-1 for the current host machine. Note that if the host does not readily provide a getpagesize() function, we need to emulate it elsewhere, not clutter up this file with lots of kluges to try to figure it out. */ static size_t pageround, pagesize; #ifndef HAVE_GETPAGESIZE extern int getpagesize (); #endif #define PAGE_ALIGN(addr) ((PTR) (((intptr_t)(addr) + pageround) & ~pageround)) /* We allocate extra pages for the heap descriptor and answer an address that is HEAP_DELTA bytes past the actual beginning of the allocation. */ #define HEAP_DELTA ((intptr_t) PAGE_ALIGN(sizeof (struct heap))) heap _gst_heap_create (PTR address, int size) { struct heap mtemp; struct heap *hdp; heap hd; if (!pageround) { pagesize = getpagesize (); pageround = pagesize - 1; } if (address) address = (char *) address - HEAP_DELTA; /* We start off with the heap descriptor allocated on the stack, until we build it up enough to call heap_sbrk_internal() to allocate the first page of the region and copy it there. Ensure that it is zero'd and then initialize the fields that we know values for. */ hdp = &mtemp; memset ((char *) hdp, 0, sizeof (mtemp)); hdp->areasize = size; hdp->base = _gst_osmem_reserve (address, size); if (!hdp->base) return NULL; /* Now try to map in the first page, copy the heap descriptor structure there, and arrange to return a pointer to this new copy. If the mapping fails, then close the file descriptor if it was opened by us, and arrange to return a NULL. */ hdp->top = hdp->breakval = hdp->base; if ((hdp = heap_sbrk_internal (hdp, HEAP_DELTA)) != NULL) { hd = ((char *) hdp) + HEAP_DELTA; memcpy (hdp, &mtemp, sizeof (mtemp)); } else { hd = NULL; _gst_osmem_release (hdp->base, hdp->areasize); } return hd; } heap _gst_heap_destroy (heap hd) { struct heap mtemp; assert (hd); /* The heap descriptor that we are using is currently located in region we are about to unmap, so we first make a local copy of it on the stack and use the copy. */ mtemp = *(struct heap *) (hd - HEAP_DELTA); /* Now unmap all the pages associated with this region by asking for a negative increment equal to the current size of the region. */ if ((heap_sbrk_internal (&mtemp, mtemp.base - mtemp.top)) == NULL) /* Update the original heap descriptor with any changes */ *(struct heap *) (hd - HEAP_DELTA) = mtemp; else { _gst_osmem_release (mtemp.base, mtemp.areasize); hd = NULL; } return (hd); } PTR _gst_heap_sbrk (heap hd, size_t size) { struct heap *hdp; assert (hd); hdp = (struct heap *) (hd - HEAP_DELTA); return heap_sbrk_internal (hdp, size); } PTR heap_sbrk_internal (struct heap * hdp, int size) { char *result = NULL; size_t mapbytes; /* Number of bytes to map */ char *moveto; /* Address where we wish to move "break value" to */ char *mapto; /* Address we actually mapped to */ if (size == 0) /* Just return the current "break" value. */ result = hdp->breakval; else if (size < 0) { /* We are deallocating memory. If the amount requested would cause us to try to deallocate back past the base of the mmap'd region then do nothing, and return NULL. Otherwise, deallocate the memory and return the old break value. */ if (hdp->breakval + size >= hdp->base) { result = (PTR) hdp->breakval; hdp->breakval += size; moveto = PAGE_ALIGN (hdp->breakval); _gst_osmem_decommit (moveto, (size_t) (hdp->top - moveto)); hdp->top = moveto; } } else if (hdp->breakval + size > hdp->top) { if (hdp->breakval - hdp->base + size > hdp->areasize) { /* this heap is full? */ errno = ENOMEM; return NULL; } moveto = PAGE_ALIGN (hdp->breakval + size); mapbytes = moveto - hdp->top; mapto = _gst_osmem_commit (hdp->top, mapbytes); if (!mapto) errno = ENOMEM; else { hdp->top = moveto; result = (PTR) hdp->breakval; hdp->breakval += size; } } else { result = (PTR) hdp->breakval; hdp->breakval += size; } return (result); } smalltalk-3.2.5/libgst/vm.inl0000644000175000017500000075421212130455566013062 00000000000000/* Automatically generated by genvm, do not edit! */ #define SEND_TO_SUPER(sendSelector, sendArgs, methodClass) \ _gst_send_message_internal(sendSelector, sendArgs, _gst_self, methodClass) #if REG_AVAILABILITY >= 2 && defined(LOCAL_REGS) #define RECEIVER_VARIABLE(index) INSTANCE_VARIABLE (self_cache, index) #define METHOD_TEMPORARY(index) temp_cache[index] #define METHOD_LITERAL(index) lit_cache[index] #define STORE_RECEIVER_VARIABLE(index, oop) STORE_INSTANCE_VARIABLE (self_cache, index, oop) #define STORE_METHOD_TEMPORARY(index, oop) temp_cache[index] = (oop) #define STORE_METHOD_LITERAL(index, oop) lit_cache[index] = (oop) #else #define RECEIVER_VARIABLE(index) INSTANCE_VARIABLE (_gst_self, index) #define METHOD_TEMPORARY(index) _gst_temporaries[index] #define METHOD_LITERAL(index) _gst_literals[index] #define STORE_RECEIVER_VARIABLE(index, oop) STORE_INSTANCE_VARIABLE (_gst_self, index, oop) #define STORE_METHOD_TEMPORARY(index, oop) _gst_temporaries[index] = (oop) #define STORE_METHOD_LITERAL(index, oop) _gst_literals[index] = (oop) #endif #ifndef OPEN_CODE_MATH #define RAW_INT_OP(op, op1, op2, iop) #define RAW_FLOATD_OP(op, op1, op2, fop) #define INTERP_BASIC_OP(op, op1, op2, iop, fop) #define INTERP_BASIC_BOOL(op, op1, op2, operator) #else #define RAW_INT_OP(op, op1, op2, iop) \ { \ mst_Boolean overflow; \ OOP result = iop; \ if(COMMON (!overflow)) { \ op = result; \ break; \ } \ } #define RAW_FLOATD_OP(op, op1, op2, fop) \ { \ double farg1, farg2; \ farg1 = IS_INT (op1) ? TO_INT (op1) : FLOATD_OOP_VALUE(op1); \ farg2 = IS_INT (op2) ? TO_INT (op2) : FLOATD_OOP_VALUE(op2); \ EXPORT_REGS(); \ op = floatd_new(fop); \ IMPORT_REGS(); \ break; \ } #define INTERP_BASIC_OP(op, op1, op2, iop, fop) { \ if COMMON (ARE_INTS(op1, op2)) { \ RAW_INT_OP(op, op1, op2, iop); \ } else if COMMON ((IS_INT (op1) || OOP_CLASS(op1) == _gst_floatd_class) \ && (IS_INT (op2) || OOP_CLASS(op2) == _gst_floatd_class)) \ RAW_FLOATD_OP(op, op1, op2, fop); \ } #define INTERP_BASIC_BOOL(op, op1, op2, operator) { \ if COMMON (ARE_INTS(op1, op2)) { \ POP_N_OOPS (2); \ if (((intptr_t) op1) operator ((intptr_t) op2)) \ DISPATCH(true_byte_codes); \ else \ DISPATCH(false_byte_codes); \ } else if COMMON ((IS_INT (op1) || OOP_CLASS(op1) == _gst_floatd_class) \ && (IS_INT (op2) || OOP_CLASS(op2) == _gst_floatd_class)) { \ double farg1 = IS_INT (op1) ? TO_INT (op1) : FLOATD_OOP_VALUE(op1); \ double farg2 = IS_INT (op2) ? TO_INT (op2) : FLOATD_OOP_VALUE(op2); \ POP_N_OOPS (2); \ if (farg1 operator farg2) \ DISPATCH(true_byte_codes); \ else \ DISPATCH(false_byte_codes); \ } \ } #endif #ifdef PIPELINING #define FETCH goto *(t = dispatch_vec[*ip], b2 = ip[2], b4 = ip[4], \ arg = ip[1], arg2 = ip[3], t2 = dispatch_vec[b2], t) #define FETCH_VEC(v) goto *(t = (v)[*ip], b2 = ip[2], b4 = ip[4], \ arg = ip[1], arg2 = ip[3], t2 = dispatch_vec[b2], t) #define PREFETCH (t = t2, t2 = dispatch_vec[b4], \ arg2 = ip[3], b2 = b4, b4 = ip[6], \ ip += 2) #define PREFETCH_VEC(v) (t = (v)[b2], t2 = dispatch_vec[b4], \ arg2 = ip[3], b2 = b4, b4 = ip[6], \ ip += 2) #define NEXT_BC goto *(arg = GET_ARG, t) #define NEXT_BC_VEC(v) goto *(arg = GET_ARG, t) #define NEXT_BC_NO_ARG(v) goto *t #define GET_ARG arg2 #elif REG_AVAILABILITY >= 1 #define FETCH goto *(arg = GET_ARG, dispatch_vec[*ip]) #define FETCH_VEC(v) goto *(arg = GET_ARG, (v)[*ip]) #define PREFETCH (ip += 2, prefetch = dispatch_vec[*ip]) #define PREFETCH_VEC(v) (ip += 2, prefetch = (v)[*ip]) #define NEXT_BC goto *(arg = GET_ARG, prefetch) #define NEXT_BC_VEC(v) goto *(arg = GET_ARG, prefetch) #define NEXT_BC_NO_ARG(v) goto *prefetch #define GET_ARG (ip[1]) #else #define FETCH NEXT_BC #define FETCH_VEC(v) NEXT_BC_VEC(v) #define PREFETCH (ip += 2) #define PREFETCH_VEC(v) (ip += 2) #define NEXT_BC goto *(arg = GET_ARG, dispatch_vec[*ip]) #define NEXT_BC_VEC(v) goto *(arg = GET_ARG, (v)[*ip]) #define NEXT_BC_NO_ARG(v) goto *(v)[*ip] #define GET_ARG (ip[1]) #endif #define DISPATCH(v) goto *(arg = GET_ARG, (v)[*ip]) static void *monitored_byte_codes[256] = { &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, /* 0 */ &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, /* 4 */ &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, /* 8 */ &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, /* 12 */ &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, /* 16 */ &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, /* 20 */ &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, /* 24 */ &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, /* 28 */ &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, /* 32 */ &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, /* 36 */ &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, /* 40 */ &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, /* 44 */ &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, /* 48 */ &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, /* 52 */ &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, /* 56 */ &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, /* 60 */ &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, /* 64 */ &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, /* 68 */ &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, /* 72 */ &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, /* 76 */ &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, /* 80 */ &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, /* 84 */ &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, /* 88 */ &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, /* 92 */ &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, /* 96 */ &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, /* 100 */ &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, /* 104 */ &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, /* 108 */ &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, /* 112 */ &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, /* 116 */ &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, /* 120 */ &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, /* 124 */ &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, /* 128 */ &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, /* 132 */ &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, /* 136 */ &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, /* 140 */ &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, /* 144 */ &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, /* 148 */ &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, /* 152 */ &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, /* 156 */ &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, /* 160 */ &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, /* 164 */ &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, /* 168 */ &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, /* 172 */ &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, /* 176 */ &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, /* 180 */ &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, /* 184 */ &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, /* 188 */ &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, /* 192 */ &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, /* 196 */ &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, /* 200 */ &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, /* 204 */ &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, /* 208 */ &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, /* 212 */ &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, /* 216 */ &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, /* 220 */ &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, /* 224 */ &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, /* 228 */ &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, /* 232 */ &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, /* 236 */ &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, /* 240 */ &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, /* 244 */ &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, /* 248 */ &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes, &&monitor_byte_codes /* 252 */ }; static void *true_byte_codes[256] = { &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, /* 0 */ &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, /* 4 */ &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, /* 8 */ &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, /* 12 */ &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, /* 16 */ &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, /* 20 */ &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, /* 24 */ &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, /* 28 */ &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, /* 32 */ &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, /* 36 */ &&lookahead_failed_true, &&lookahead_failed_true, &&bc41, &&bc54, /* 40 */ &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, /* 44 */ &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, /* 48 */ &&lookahead_dup_true, &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, /* 52 */ &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, /* 56 */ &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, /* 60 */ &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, /* 64 */ &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, /* 68 */ &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, /* 72 */ &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, /* 76 */ &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, /* 80 */ &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, /* 84 */ &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, /* 88 */ &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, /* 92 */ &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, /* 96 */ &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, /* 100 */ &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, /* 104 */ &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, /* 108 */ &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, /* 112 */ &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, /* 116 */ &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, /* 120 */ &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, /* 124 */ &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, /* 128 */ &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, /* 132 */ &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, /* 136 */ &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, /* 140 */ &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, /* 144 */ &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, /* 148 */ &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, /* 152 */ &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, /* 156 */ &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, /* 160 */ &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, /* 164 */ &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, /* 168 */ &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, /* 172 */ &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, /* 176 */ &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, /* 180 */ &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, /* 184 */ &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, /* 188 */ &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, /* 192 */ &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, /* 196 */ &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, /* 200 */ &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, /* 204 */ &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, /* 208 */ &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, /* 212 */ &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, /* 216 */ &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, /* 220 */ &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, /* 224 */ &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, /* 228 */ &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, /* 232 */ &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, /* 236 */ &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, /* 240 */ &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, /* 244 */ &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, /* 248 */ &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true, &&lookahead_failed_true /* 252 */ }; static void *false_byte_codes[256] = { &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, /* 0 */ &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, /* 4 */ &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, /* 8 */ &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, /* 12 */ &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, /* 16 */ &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, /* 20 */ &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, /* 24 */ &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, /* 28 */ &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, /* 32 */ &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, /* 36 */ &&lookahead_failed_false, &&lookahead_failed_false, &&bc54, &&bc41, /* 40 */ &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, /* 44 */ &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, /* 48 */ &&lookahead_dup_false, &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, /* 52 */ &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, /* 56 */ &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, /* 60 */ &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, /* 64 */ &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, /* 68 */ &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, /* 72 */ &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, /* 76 */ &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, /* 80 */ &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, /* 84 */ &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, /* 88 */ &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, /* 92 */ &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, /* 96 */ &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, /* 100 */ &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, /* 104 */ &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, /* 108 */ &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, /* 112 */ &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, /* 116 */ &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, /* 120 */ &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, /* 124 */ &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, /* 128 */ &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, /* 132 */ &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, /* 136 */ &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, /* 140 */ &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, /* 144 */ &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, /* 148 */ &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, /* 152 */ &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, /* 156 */ &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, /* 160 */ &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, /* 164 */ &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, /* 168 */ &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, /* 172 */ &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, /* 176 */ &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, /* 180 */ &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, /* 184 */ &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, /* 188 */ &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, /* 192 */ &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, /* 196 */ &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, /* 200 */ &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, /* 204 */ &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, /* 208 */ &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, /* 212 */ &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, /* 216 */ &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, /* 220 */ &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, /* 224 */ &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, /* 228 */ &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, /* 232 */ &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, /* 236 */ &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, /* 240 */ &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, /* 244 */ &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, /* 248 */ &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false, &&lookahead_failed_false /* 252 */ }; static void *normal_byte_codes[256] = { &&bc0, &&bc1, &&bc2, &&bc3, /* 0 */ &&bc4, &&bc5, &&bc6, &&bc7, /* 4 */ &&bc8, &&bc9, &&bc10, &&bc11, /* 8 */ &&bc12, &&bc13, &&bc14, &&bc15, /* 12 */ &&bc16, &&bc17, &&bc18, &&bc19, /* 16 */ &&bc20, &&bc21, &&bc22, &&bc23, /* 20 */ &&bc24, &&bc25, &&bc26, &&bc27, /* 24 */ &&bc28, &&bc29, &&bc30, &&bc31, /* 28 */ &&bc32, &&bc33, &&bc34, &&bc35, /* 32 */ &&bc36, &&bc37, &&bc38, &&bc39, /* 36 */ &&bc40, &&bc41, &&bc42, &&bc43, /* 40 */ &&bc44, &&bc45, &&bc46, &&bc47, /* 44 */ &&bc48, &&bc49, &&bc50, &&bc51, /* 48 */ &&bc52, &&bc53, &&bc54, &&bc55, /* 52 */ &&bc56, &&bc57, &&bc58, &&bc59, /* 56 */ &&bc60, &&bc61, &&bc62, &&bc63, /* 60 */ &&bc64, &&bc65, &&bc66, &&bc67, /* 64 */ &&bc68, &&bc69, &&bc70, &&bc71, /* 68 */ &&bc72, &&bc73, &&bc74, &&bc75, /* 72 */ &&bc76, &&bc77, &&bc78, &&bc79, /* 76 */ &&bc80, &&bc81, &&bc82, &&bc83, /* 80 */ &&bc84, &&bc85, &&bc86, &&bc87, /* 84 */ &&bc88, &&bc89, &&bc90, &&bc91, /* 88 */ &&bc92, &&bc93, &&bc94, &&bc95, /* 92 */ &&bc96, &&bc97, &&bc98, &&bc99, /* 96 */ &&bc100, &&bc101, &&bc102, &&bc103, /* 100 */ &&bc104, &&bc105, &&bc106, &&bc107, /* 104 */ &&bc108, &&bc109, &&bc110, &&bc111, /* 108 */ &&bc112, &&bc113, &&bc114, &&bc115, /* 112 */ &&bc116, &&bc117, &&bc118, &&bc119, /* 116 */ &&bc120, &&bc121, &&bc122, &&bc123, /* 120 */ &&bc124, &&bc125, &&bc126, &&bc127, /* 124 */ &&bc128, &&bc129, &&bc130, &&bc131, /* 128 */ &&bc132, &&bc133, &&bc134, &&bc135, /* 132 */ &&bc136, &&bc137, &&bc138, &&bc139, /* 136 */ &&bc140, &&bc141, &&bc142, &&bc143, /* 140 */ &&bc144, &&bc145, &&bc146, &&bc147, /* 144 */ &&bc148, &&bc149, &&bc150, &&bc151, /* 148 */ &&bc152, &&bc153, &&bc154, &&bc155, /* 152 */ &&bc156, &&bc157, &&bc158, &&bc159, /* 156 */ &&bc160, &&bc161, &&bc162, &&bc163, /* 160 */ &&bc164, &&bc165, &&bc166, &&bc167, /* 164 */ &&bc168, &&bc169, &&bc170, &&bc171, /* 168 */ &&bc172, &&bc173, &&bc174, &&bc175, /* 172 */ &&bc176, &&bc177, &&bc178, &&bc179, /* 176 */ &&bc180, &&bc181, &&bc182, &&bc183, /* 180 */ &&bc184, &&bc185, &&bc186, &&bc187, /* 184 */ &&bc188, &&bc189, &&bc190, &&bc191, /* 188 */ &&bc192, &&bc193, &&bc194, &&bc195, /* 192 */ &&bc196, &&bc197, &&bc198, &&bc199, /* 196 */ &&bc200, &&bc201, &&bc202, &&bc203, /* 200 */ &&bc204, &&bc205, &&bc206, &&bc207, /* 204 */ &&bc208, &&bc209, &&bc210, &&bc211, /* 208 */ &&bc212, &&bc213, &&bc214, &&bc215, /* 212 */ &&bc216, &&bc217, &&bc218, &&bc219, /* 216 */ &&bc220, &&bc221, &&bc222, &&bc223, /* 220 */ &&bc224, &&bc225, &&bc226, &&bc227, /* 224 */ &&bc228, &&bc229, &&bc230, &&bc231, /* 228 */ &&bc232, &&bc233, &&bc234, &&bc235, /* 232 */ &&bc236, &&bc237, &&bc238, &&bc239, /* 236 */ &&bc240, &&bc241, &&bc242, &&bc243, /* 240 */ &&bc244, &&bc245, &&bc246, &&bc247, /* 244 */ &&bc248, &&bc249, &&bc250, &&bc251, /* 248 */ &&bc252, &&bc253, &&bc254, &&bc255 /* 252 */ }; goto jump_around; bc0: { OOP _stack0, _stack1; _stack1 = STACK_AT (1); _stack0 = STACK_AT (0); /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 402 "vm.inl" } while (0); /* PLUS_SPECIAL ( op1 op2 -- op ) */ do { #define PREPARE_STACK() do { \ } while (0) #define op1 _stack1 #define op2 _stack0 #define op _stack1 #line 230 "vm.def" INTERP_BASIC_OP (op, op1, op2, add_with_check (op1, op2, &overflow), farg1 + farg2); PREPARE_STACK (); EXPORT_REGS (); SEND_MESSAGE (_gst_builtin_selectors[PLUS_SPECIAL].symbol, 1); IMPORT_REGS (); FETCH; #line 423 "vm.inl" #undef PREPARE_STACK #undef op1 #undef op2 #undef op } while (0); STACK_AT (1) = _stack1; POP_N_OOPS (1); } NEXT_BC; bc1: { OOP _stack0, _stack1; _stack1 = STACK_AT (1); _stack0 = STACK_AT (0); /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 446 "vm.inl" } while (0); /* MINUS_SPECIAL ( op1 op2 -- op ) */ do { #define PREPARE_STACK() do { \ } while (0) #define op1 _stack1 #define op2 _stack0 #define op _stack1 #line 241 "vm.def" INTERP_BASIC_OP (op, op1, op2, sub_with_check (op1, op2, &overflow), farg1 - farg2); PREPARE_STACK (); EXPORT_REGS (); SEND_MESSAGE (_gst_builtin_selectors[MINUS_SPECIAL].symbol, 1); IMPORT_REGS (); FETCH; #line 467 "vm.inl" #undef PREPARE_STACK #undef op1 #undef op2 #undef op } while (0); STACK_AT (1) = _stack1; POP_N_OOPS (1); } NEXT_BC; bc2: { OOP _stack0, _stack1; _stack1 = STACK_AT (1); _stack0 = STACK_AT (0); /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 490 "vm.inl" } while (0); /* LESS_THAN_SPECIAL ( op1 op2 -- op ) */ do { #define PREPARE_STACK() do { \ } while (0) #define op1 _stack1 #define op2 _stack0 #define op _stack1 #line 252 "vm.def" PREPARE_STACK (); INTERP_BASIC_BOOL (op, op1, op2, <); EXPORT_REGS (); SEND_MESSAGE (_gst_builtin_selectors[LESS_THAN_SPECIAL].symbol, 1); IMPORT_REGS (); FETCH; #line 509 "vm.inl" #undef PREPARE_STACK #undef op1 #undef op2 #undef op } while (0); STACK_AT (1) = _stack1; POP_N_OOPS (1); } NEXT_BC; bc3: { OOP _stack0, _stack1; _stack1 = STACK_AT (1); _stack0 = STACK_AT (0); /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 532 "vm.inl" } while (0); /* GREATER_THAN_SPECIAL ( op1 op2 -- op ) */ do { #define PREPARE_STACK() do { \ } while (0) #define op1 _stack1 #define op2 _stack0 #define op _stack1 #line 261 "vm.def" PREPARE_STACK (); INTERP_BASIC_BOOL (op, op1, op2, >); EXPORT_REGS (); SEND_MESSAGE (_gst_builtin_selectors[GREATER_THAN_SPECIAL].symbol, 1); IMPORT_REGS (); FETCH; #line 551 "vm.inl" #undef PREPARE_STACK #undef op1 #undef op2 #undef op } while (0); STACK_AT (1) = _stack1; POP_N_OOPS (1); } NEXT_BC; bc4: { OOP _stack0, _stack1; _stack1 = STACK_AT (1); _stack0 = STACK_AT (0); /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 574 "vm.inl" } while (0); /* LESS_EQUAL_SPECIAL ( op1 op2 -- op ) */ do { #define PREPARE_STACK() do { \ } while (0) #define op1 _stack1 #define op2 _stack0 #define op _stack1 #line 270 "vm.def" PREPARE_STACK (); INTERP_BASIC_BOOL (op, op1, op2, <=); EXPORT_REGS (); SEND_MESSAGE (_gst_builtin_selectors[LESS_EQUAL_SPECIAL].symbol, 1); IMPORT_REGS (); FETCH; #line 593 "vm.inl" #undef PREPARE_STACK #undef op1 #undef op2 #undef op } while (0); STACK_AT (1) = _stack1; POP_N_OOPS (1); } NEXT_BC; bc5: { OOP _stack0, _stack1; _stack1 = STACK_AT (1); _stack0 = STACK_AT (0); /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 616 "vm.inl" } while (0); /* GREATER_EQUAL_SPECIAL ( op1 op2 -- op ) */ do { #define PREPARE_STACK() do { \ } while (0) #define op1 _stack1 #define op2 _stack0 #define op _stack1 #line 279 "vm.def" PREPARE_STACK (); INTERP_BASIC_BOOL (op, op1, op2, >=); EXPORT_REGS (); SEND_MESSAGE (_gst_builtin_selectors[GREATER_EQUAL_SPECIAL].symbol, 1); IMPORT_REGS (); FETCH; #line 635 "vm.inl" #undef PREPARE_STACK #undef op1 #undef op2 #undef op } while (0); STACK_AT (1) = _stack1; POP_N_OOPS (1); } NEXT_BC; bc6: { OOP _stack0, _stack1; _stack1 = STACK_AT (1); _stack0 = STACK_AT (0); /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 658 "vm.inl" } while (0); /* EQUAL_SPECIAL ( op1 op2 -- op ) */ do { #define PREPARE_STACK() do { \ } while (0) #define op1 _stack1 #define op2 _stack0 #define op _stack1 #line 288 "vm.def" PREPARE_STACK (); INTERP_BASIC_BOOL (op, op1, op2, ==); EXPORT_REGS (); SEND_MESSAGE (_gst_builtin_selectors[EQUAL_SPECIAL].symbol, 1); IMPORT_REGS (); FETCH; #line 677 "vm.inl" #undef PREPARE_STACK #undef op1 #undef op2 #undef op } while (0); STACK_AT (1) = _stack1; POP_N_OOPS (1); } NEXT_BC; bc7: { OOP _stack0, _stack1; _stack1 = STACK_AT (1); _stack0 = STACK_AT (0); /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 700 "vm.inl" } while (0); /* NOT_EQUAL_SPECIAL ( op1 op2 -- op ) */ do { #define PREPARE_STACK() do { \ } while (0) #define op1 _stack1 #define op2 _stack0 #define op _stack1 #line 297 "vm.def" PREPARE_STACK (); INTERP_BASIC_BOOL (op, op1, op2, !=); EXPORT_REGS (); SEND_MESSAGE (_gst_builtin_selectors[NOT_EQUAL_SPECIAL].symbol, 1); IMPORT_REGS (); FETCH; #line 719 "vm.inl" #undef PREPARE_STACK #undef op1 #undef op2 #undef op } while (0); STACK_AT (1) = _stack1; POP_N_OOPS (1); } NEXT_BC; bc8: { OOP _stack0, _stack1; _stack1 = STACK_AT (1); _stack0 = STACK_AT (0); /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 742 "vm.inl" } while (0); /* TIMES_SPECIAL ( op1 op2 -- op ) */ do { #define PREPARE_STACK() do { \ } while (0) #define op1 _stack1 #define op2 _stack0 #define op _stack1 #line 306 "vm.def" INTERP_BASIC_OP (op, op1, op2, mul_with_check (op1, op2, &overflow), farg1 * farg2); PREPARE_STACK (); EXPORT_REGS (); SEND_MESSAGE (_gst_builtin_selectors[TIMES_SPECIAL].symbol, 1); IMPORT_REGS (); FETCH; #line 763 "vm.inl" #undef PREPARE_STACK #undef op1 #undef op2 #undef op } while (0); STACK_AT (1) = _stack1; POP_N_OOPS (1); } NEXT_BC; bc9: { OOP _stack0, _stack1; _stack1 = STACK_AT (1); _stack0 = STACK_AT (0); /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 786 "vm.inl" } while (0); /* DIVIDE_SPECIAL ( op1 op2 -- op ) */ do { #define PREPARE_STACK() do { \ } while (0) #define op1 _stack1 #define op2 _stack0 #define op _stack1 #line 317 "vm.def" if COMMON (!ARE_INTS (op1, op2) && (IS_INT (op1) || OOP_CLASS(op1) == _gst_floatd_class) && (IS_INT (op2) || OOP_CLASS(op2) == _gst_floatd_class)) { RAW_FLOATD_OP(op, op1, op2, farg1 / farg2); } PREPARE_STACK (); EXPORT_REGS(); if (COMMON (ARE_INTS (op1, op2))) { if (!VMpr_SmallInteger_divide (10, 1)) { IMPORT_REGS (); NEXT_BC; } } SEND_MESSAGE (_gst_builtin_selectors[DIVIDE_SPECIAL].symbol, 1); IMPORT_REGS (); FETCH; #line 820 "vm.inl" #undef PREPARE_STACK #undef op1 #undef op2 #undef op } while (0); STACK_AT (1) = _stack1; POP_N_OOPS (1); } NEXT_BC; bc10: { OOP _stack0, _stack1; _stack1 = STACK_AT (1); _stack0 = STACK_AT (0); /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 843 "vm.inl" } while (0); /* REMAINDER_SPECIAL ( op1 op2 -- op ) */ do { #define PREPARE_STACK() do { \ } while (0) #define op1 _stack1 #define op2 _stack0 #define op _stack1 #line 341 "vm.def" PREPARE_STACK (); EXPORT_REGS(); if (IS_INT (op1) && IS_INT (op2) && !VMpr_SmallInteger_modulo (11, 1)) { IMPORT_REGS (); NEXT_BC; } SEND_MESSAGE (_gst_builtin_selectors[REMAINDER_SPECIAL].symbol, 1); IMPORT_REGS (); FETCH; #line 868 "vm.inl" #undef PREPARE_STACK #undef op1 #undef op2 #undef op } while (0); STACK_AT (1) = _stack1; POP_N_OOPS (1); } NEXT_BC; bc11: { OOP _stack0, _stack1; _stack1 = STACK_AT (1); _stack0 = STACK_AT (0); /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 891 "vm.inl" } while (0); /* BIT_XOR_SPECIAL ( op1 op2 -- op ) */ do { #define PREPARE_STACK() do { \ } while (0) #define op1 _stack1 #define op2 _stack0 #define op _stack1 #line 356 "vm.def" if COMMON (ARE_INTS (op1, op2)) { op = tagged_xor (op1, op2); break; } PREPARE_STACK (); EXPORT_REGS (); SEND_MESSAGE (_gst_builtin_selectors[BIT_XOR_SPECIAL].symbol, 1); IMPORT_REGS (); FETCH; #line 915 "vm.inl" #undef PREPARE_STACK #undef op1 #undef op2 #undef op } while (0); STACK_AT (1) = _stack1; POP_N_OOPS (1); } NEXT_BC; bc12: { OOP _stack0, _stack1; _stack1 = STACK_AT (1); _stack0 = STACK_AT (0); /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 938 "vm.inl" } while (0); /* BIT_SHIFT_SPECIAL ( op1 op2 -- op ) */ do { #define PREPARE_STACK() do { \ } while (0) #define op1 _stack1 #define op2 _stack0 #define op _stack1 #line 370 "vm.def" if COMMON (IS_INT (op2) && IS_INT (op1)) { intptr_t iarg1, iarg2; iarg1 = TO_INT (op1); iarg2 = TO_INT (op2); if (iarg2 < 0) { if COMMON (iarg2 >= -ST_INT_SIZE) op = FROM_INT (iarg1 >> -iarg2); else op = FROM_INT (iarg1 >> ST_INT_SIZE); break; } else if COMMON (iarg2 < ST_INT_SIZE) { intptr_t result = iarg1 << iarg2; if COMMON ((result >> iarg2) == iarg1 && !INT_OVERFLOW(result)) { op = FROM_INT (result); break; } } } PREPARE_STACK (); EXPORT_REGS (); SEND_MESSAGE (_gst_builtin_selectors[BIT_SHIFT_SPECIAL].symbol, 1); IMPORT_REGS (); FETCH; #line 981 "vm.inl" #undef PREPARE_STACK #undef op1 #undef op2 #undef op } while (0); STACK_AT (1) = _stack1; POP_N_OOPS (1); } NEXT_BC; bc13: { OOP _stack0, _stack1; _stack1 = STACK_AT (1); _stack0 = STACK_AT (0); /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 1004 "vm.inl" } while (0); /* INTEGER_DIVIDE_SPECIAL ( op1 op2 | -- op1 op2 | ) */ do { #define PREPARE_STACK() do { \ } while (0) #define op1 _stack1 #define op2 _stack0 #line 403 "vm.def" PREPARE_STACK (); EXPORT_REGS(); if (IS_INT (op1) && IS_INT (op2) && !VMpr_SmallInteger_intDiv (12, 1)) { IMPORT_REGS (); NEXT_BC; } SEND_MESSAGE (_gst_builtin_selectors[INTEGER_DIVIDE_SPECIAL].symbol, 1); IMPORT_REGS (); FETCH; #line 1028 "vm.inl" #undef PREPARE_STACK #undef op1 #undef op2 } while (0); } NEXT_BC; bc14: { OOP _stack0, _stack1; _stack1 = STACK_AT (1); _stack0 = STACK_AT (0); /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 1048 "vm.inl" } while (0); /* BIT_AND_SPECIAL ( op1 op2 -- op ) */ do { #define PREPARE_STACK() do { \ } while (0) #define op1 _stack1 #define op2 _stack0 #define op _stack1 #line 418 "vm.def" op = tagged_and (op1, op2); if COMMON (IS_INT (op)) break; PREPARE_STACK (); EXPORT_REGS (); SEND_MESSAGE (_gst_builtin_selectors[BIT_AND_SPECIAL].symbol, 1); IMPORT_REGS (); FETCH; #line 1070 "vm.inl" #undef PREPARE_STACK #undef op1 #undef op2 #undef op } while (0); STACK_AT (1) = _stack1; POP_N_OOPS (1); } NEXT_BC; bc15: { OOP _stack0, _stack1; _stack1 = STACK_AT (1); _stack0 = STACK_AT (0); /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 1093 "vm.inl" } while (0); /* BIT_OR_SPECIAL ( op1 op2 -- op ) */ do { #define PREPARE_STACK() do { \ } while (0) #define op1 _stack1 #define op2 _stack0 #define op _stack1 #line 430 "vm.def" if COMMON (ARE_INTS (op1, op2)) { op = tagged_or (op1, op2); break; } PREPARE_STACK (); EXPORT_REGS (); SEND_MESSAGE (_gst_builtin_selectors[BIT_OR_SPECIAL].symbol, 1); IMPORT_REGS (); FETCH; #line 1117 "vm.inl" #undef PREPARE_STACK #undef op1 #undef op2 #undef op } while (0); STACK_AT (1) = _stack1; POP_N_OOPS (1); } NEXT_BC; bc16: { OOP _stack0, _stack1; _stack1 = STACK_AT (1); _stack0 = STACK_AT (0); /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 1140 "vm.inl" } while (0); /* AT_SPECIAL ( rec idx -- val ) */ do { #define PREPARE_STACK() do { \ } while (0) #define rec _stack1 #define idx _stack0 #define val _stack1 #line 444 "vm.def" OOP classOOP; PREPARE_STACK (); EXPORT_REGS (); if UNCOMMON (IS_INT (rec)) { SEND_MESSAGE (_gst_builtin_selectors[AT_SPECIAL].symbol, 1); IMPORT_REGS (); FETCH; } if COMMON (at_cache_class == (classOOP = OOP_CLASS (rec)) && !cached_index_oop_primitive (rec, idx, at_cache_spec)) { IMPORT_REGS (); NEXT_BC; } /* Not the same class that is in the cache, or the primitive failed -- send the message, and modify the cache if the send is resolved to a primitive. */ last_primitive = 0; SEND_MESSAGE (_gst_builtin_selectors[AT_SPECIAL].symbol, 1); IMPORT_REGS (); if (_gst_primitive_table[last_primitive].id == 60) { at_cache_spec = CLASS_INSTANCE_SPEC (classOOP); at_cache_class = classOOP; NEXT_BC; } FETCH; #line 1183 "vm.inl" #undef PREPARE_STACK #undef rec #undef idx #undef val } while (0); STACK_AT (1) = _stack1; POP_N_OOPS (1); } NEXT_BC; bc17: { OOP _stack0, _stack1, _stack2; _stack2 = STACK_AT (2); _stack1 = STACK_AT (1); _stack0 = STACK_AT (0); /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 1207 "vm.inl" } while (0); /* AT_PUT_SPECIAL ( rec idx val -- res ) */ do { #define PREPARE_STACK() do { \ } while (0) #define rec _stack2 #define idx _stack1 #define val _stack0 #define res _stack2 #line 477 "vm.def" OOP classOOP; PREPARE_STACK (); EXPORT_REGS (); if UNCOMMON (IS_INT (rec)) { SEND_MESSAGE (_gst_builtin_selectors[AT_PUT_SPECIAL].symbol, 2); IMPORT_REGS (); FETCH; } if COMMON (at_put_cache_class == (classOOP = OOP_CLASS (rec)) && !cached_index_oop_put_primitive (rec, idx, val, at_put_cache_spec)) { IMPORT_REGS (); NEXT_BC; } /* Not the same class that is in the cache, or the primitive failed -- send the message, and modify the cache if the send is resolved to a primitive. */ last_primitive = 0; SEND_MESSAGE (_gst_builtin_selectors[AT_PUT_SPECIAL].symbol, 2); IMPORT_REGS (); if (_gst_primitive_table[last_primitive].id == 61) { at_put_cache_spec = CLASS_INSTANCE_SPEC (classOOP); at_put_cache_class = classOOP; NEXT_BC; } FETCH; #line 1251 "vm.inl" #undef PREPARE_STACK #undef rec #undef idx #undef val #undef res } while (0); STACK_AT (2) = _stack2; POP_N_OOPS (2); } NEXT_BC; bc18: { OOP _stack0; _stack0 = STACK_AT (0); /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 1274 "vm.inl" } while (0); /* SIZE_SPECIAL ( rec -- val ) */ do { #define PREPARE_STACK() do { \ } while (0) #define rec _stack0 #define val _stack0 #line 510 "vm.def" OOP classOOP; PREPARE_STACK (); EXPORT_REGS (); if UNCOMMON (IS_INT (rec)) { SEND_MESSAGE (_gst_builtin_selectors[SIZE_SPECIAL].symbol, 0); IMPORT_REGS (); FETCH; } if COMMON (size_cache_class == (classOOP = OOP_CLASS (rec)) && !execute_primitive_operation (size_cache_prim, 0)) { IMPORT_REGS (); NEXT_BC; } /* Not the same class that is in the cache, or the primitive failed -- send the message, and modify the cache if the send is resolved to a primitive. */ last_primitive = 0; SEND_MESSAGE (_gst_builtin_selectors[SIZE_SPECIAL].symbol, 0); IMPORT_REGS (); if COMMON (last_primitive) { size_cache_prim = last_primitive; size_cache_class = classOOP; NEXT_BC; } FETCH; #line 1316 "vm.inl" #undef PREPARE_STACK #undef rec #undef val } while (0); STACK_AT (0) = _stack0; } NEXT_BC; bc19: { OOP _stack0; _stack0 = STACK_AT (0); /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 1336 "vm.inl" } while (0); /* CLASS_SPECIAL ( rec -- val ) */ do { #define PREPARE_STACK() do { \ } while (0) #define rec _stack0 #define val _stack0 #line 543 "vm.def" OOP classOOP; PREPARE_STACK (); EXPORT_REGS (); if UNCOMMON (IS_INT (rec)) { SEND_MESSAGE (_gst_builtin_selectors[CLASS_SPECIAL].symbol, 0); IMPORT_REGS (); FETCH; } if COMMON (class_cache_class == (classOOP = OOP_CLASS (rec)) && !execute_primitive_operation (class_cache_prim, 1)) { IMPORT_REGS (); NEXT_BC; } /* Not the same class that is in the cache, or the primitive failed -- send the message, and modify the cache if the send is resolved to a primitive. */ last_primitive = 0; SEND_MESSAGE (_gst_builtin_selectors[CLASS_SPECIAL].symbol, 0); IMPORT_REGS (); if COMMON (last_primitive) { class_cache_prim = last_primitive; class_cache_class = classOOP; NEXT_BC; } FETCH; #line 1378 "vm.inl" #undef PREPARE_STACK #undef rec #undef val } while (0); STACK_AT (0) = _stack0; } NEXT_BC; bc20: { OOP _stack0; _stack0 = STACK_AT (0); /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 1398 "vm.inl" } while (0); /* IS_NIL_SPECIAL ( rec -- val ) */ do { #define rec _stack0 #define val _stack0 #line 576 "vm.def" /* DO_JUMP_LOOKAHEAD (rec == _gst_nil_oop); */ val = rec == _gst_nil_oop ? _gst_true_oop : _gst_false_oop; #line 1410 "vm.inl" #undef rec #undef val } while (0); STACK_AT (0) = _stack0; } NEXT_BC; bc21: { OOP _stack0; _stack0 = STACK_AT (0); /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 1429 "vm.inl" } while (0); /* NOT_NIL_SPECIAL ( rec -- val ) */ do { #define rec _stack0 #define val _stack0 #line 581 "vm.def" /* DO_JUMP_LOOKAHEAD (rec != _gst_nil_oop); */ val = rec != _gst_nil_oop ? _gst_true_oop : _gst_false_oop; #line 1441 "vm.inl" #undef rec #undef val } while (0); STACK_AT (0) = _stack0; } NEXT_BC; bc22: { OOP _stack0; _stack0 = STACK_AT (0); /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 1460 "vm.inl" } while (0); /* VALUE_SPECIAL ( rec | -- rec | ) */ do { #define PREPARE_STACK() do { \ } while (0) #define rec _stack0 #line 586 "vm.def" PREPARE_STACK (); EXPORT_REGS (); if (UNCOMMON (IS_INT (rec)) || UNCOMMON (OOP_CLASS (rec) != _gst_block_closure_class) || UNCOMMON (send_block_value (0, 0))) SEND_MESSAGE (_gst_builtin_selectors[VALUE_SPECIAL].symbol, 0); IMPORT_REGS (); FETCH; #line 1480 "vm.inl" #undef PREPARE_STACK #undef rec } while (0); } NEXT_BC; bc23: { OOP _stack0, _stack1; _stack1 = STACK_AT (1); _stack0 = STACK_AT (0); /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 1499 "vm.inl" } while (0); /* VALUE_COLON_SPECIAL ( rec blk_arg | -- rec blk_arg | ) */ do { #define PREPARE_STACK() do { \ } while (0) #define rec _stack1 #define blk_arg _stack0 #line 598 "vm.def" PREPARE_STACK (); EXPORT_REGS (); if (UNCOMMON (IS_INT (rec)) || UNCOMMON (OOP_CLASS (rec) != _gst_block_closure_class) || UNCOMMON (send_block_value (1, 0))) SEND_MESSAGE (_gst_builtin_selectors[VALUE_COLON_SPECIAL].symbol, 1); IMPORT_REGS (); FETCH; #line 1520 "vm.inl" #undef PREPARE_STACK #undef rec #undef blk_arg } while (0); } NEXT_BC; bc24: { OOP _stack0, _stack1; _stack1 = STACK_AT (1); _stack0 = STACK_AT (0); /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 1540 "vm.inl" } while (0); /* SAME_OBJECT_SPECIAL ( op1 op2 -- op ) */ do { #define op1 _stack1 #define op2 _stack0 #define op _stack1 #line 610 "vm.def" /* DO_JUMP_LOOKAHEAD (op1 == op2); */ op = (op1 == op2) ? _gst_true_oop : _gst_false_oop; #line 1553 "vm.inl" #undef op1 #undef op2 #undef op } while (0); STACK_AT (1) = _stack1; POP_N_OOPS (1); } NEXT_BC; bc25: { OOP _stack0; _stack0 = STACK_AT (0); /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 1574 "vm.inl" } while (0); /* JAVA_AS_INT_SPECIAL ( rec -- val ) */ do { #define PREPARE_STACK() do { \ } while (0) #define rec _stack0 #define val _stack0 #line 615 "vm.def" if COMMON (IS_INT (rec) || is_c_int_32 (rec)) { val = rec; break; } PREPARE_STACK (); EXPORT_REGS (); SEND_MESSAGE (_gst_builtin_selectors[JAVA_AS_INT_SPECIAL].symbol, 0); IMPORT_REGS (); FETCH; #line 1597 "vm.inl" #undef PREPARE_STACK #undef rec #undef val } while (0); STACK_AT (0) = _stack0; } NEXT_BC; bc26: { OOP _stack0; _stack0 = STACK_AT (0); /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 1617 "vm.inl" } while (0); /* JAVA_AS_LONG_SPECIAL ( rec -- val ) */ do { #define PREPARE_STACK() do { \ } while (0) #define rec _stack0 #define val _stack0 #line 629 "vm.def" if COMMON (IS_INT (rec) || is_c_int_64 (rec)) { val = rec; break; } PREPARE_STACK (); EXPORT_REGS (); SEND_MESSAGE (_gst_builtin_selectors[JAVA_AS_LONG_SPECIAL].symbol, 0); IMPORT_REGS (); FETCH; #line 1640 "vm.inl" #undef PREPARE_STACK #undef rec #undef val } while (0); STACK_AT (0) = _stack0; } NEXT_BC; bc27: { /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 1658 "vm.inl" } while (0); /* INVALID ( -- ) */ do { int arg = arg; #line 226 "vm.def" _gst_errorf ("Invalid bytecode %d(%d) found!", ip[-1], arg); #line 1668 "vm.inl" } while (0); } NEXT_BC; bc28: { /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 1682 "vm.inl" } while (0); /* SEND ( -- ) */ do { int sel = arg >> 8; int n = arg & 255; #define PREPARE_STACK() do { \ } while (0) #line 643 "vm.def" PREPARE_STACK (); EXPORT_REGS (); SEND_MESSAGE (METHOD_LITERAL (sel), n); IMPORT_REGS (); FETCH; #line 1699 "vm.inl" #undef PREPARE_STACK } while (0); } NEXT_BC; bc29: { /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 1714 "vm.inl" } while (0); /* SEND_SUPER ( -- ) */ do { int sel = arg >> 8; int n = arg & 255; #define PREPARE_STACK() do { \ } while (0) #line 651 "vm.def" OOP classOOP; PREPARE_STACK (); classOOP = POP_OOP (); EXPORT_REGS (); SEND_TO_SUPER (METHOD_LITERAL (sel), n, classOOP); IMPORT_REGS (); FETCH; #line 1734 "vm.inl" #undef PREPARE_STACK } while (0); } NEXT_BC; bc30: { /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 1749 "vm.inl" } while (0); /* SEND_IMMEDIATE ( -- ) */ do { int n = arg; #define PREPARE_STACK() do { \ } while (0) #line 662 "vm.def" const struct builtin_selector *bs = &_gst_builtin_selectors[n]; PREPARE_STACK (); EXPORT_REGS (); SEND_MESSAGE (bs->symbol, bs->numArgs); IMPORT_REGS (); FETCH; #line 1766 "vm.inl" #undef PREPARE_STACK } while (0); } NEXT_BC; bc31: { /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 1781 "vm.inl" } while (0); /* SEND_SUPER_IMMEDIATE ( -- ) */ do { int n = arg; #define PREPARE_STACK() do { \ } while (0) #line 671 "vm.def" OOP classOOP; const struct builtin_selector *bs = &_gst_builtin_selectors[n]; PREPARE_STACK (); classOOP = POP_OOP (); EXPORT_REGS (); SEND_TO_SUPER (bs->symbol, bs->numArgs, classOOP); IMPORT_REGS (); FETCH; #line 1801 "vm.inl" #undef PREPARE_STACK } while (0); } NEXT_BC; bc32: { OOP _extra1; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 1817 "vm.inl" } while (0); /* PUSH_TEMPORARY_VARIABLE ( -- tos ) */ do { int n = arg; #define tos _extra1 #line 683 "vm.def" tos = METHOD_TEMPORARY (n); #line 1828 "vm.inl" #undef tos } while (0); PUSH_OOP (_extra1); } NEXT_BC; bc33: { OOP _extra1; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 1845 "vm.inl" } while (0); /* PUSH_OUTER_TEMP ( -- tos ) */ do { int n = arg >> 8; int scopes = arg & 255; #define tos _extra1 #line 687 "vm.def" OOP contextOOP; gst_block_context context; context = (gst_block_context) OOP_TO_OBJ (_gst_this_context_oop); do { contextOOP = context->outerContext; context = (gst_block_context) OOP_TO_OBJ (contextOOP); } while (--scopes); tos = context->contextStack[n]; #line 1868 "vm.inl" #undef tos } while (0); PUSH_OOP (_extra1); } NEXT_BC; bc34: { OOP _extra1; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 1885 "vm.inl" } while (0); /* PUSH_LIT_VARIABLE ( -- tos ) */ do { int n = arg; #define PREPARE_STACK() do { \ } while (0) #define tos _extra1 #line 702 "vm.def" tos = METHOD_LITERAL (n); if (UNCOMMON (IS_INT (tos)) || UNCOMMON (!is_a_kind_of (OOP_CLASS (tos), _gst_association_class))) { PREPARE_STACK (); PUSH_OOP (tos); EXPORT_REGS (); SEND_MESSAGE (_gst_builtin_selectors[VALUE_SPECIAL].symbol, 0); IMPORT_REGS (); FETCH; } else tos = ASSOCIATION_VALUE (tos); #line 1910 "vm.inl" #undef PREPARE_STACK #undef tos } while (0); PUSH_OOP (_extra1); } NEXT_BC; bc35: { OOP _extra1; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 1928 "vm.inl" } while (0); /* PUSH_RECEIVER_VARIABLE ( -- tos ) */ do { int n = arg; #define tos _extra1 #line 718 "vm.def" tos = RECEIVER_VARIABLE (n); #line 1939 "vm.inl" #undef tos } while (0); PUSH_OOP (_extra1); } NEXT_BC; bc36: { OOP _stack0; _stack0 = STACK_AT (0); /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 1957 "vm.inl" } while (0); /* STORE_TEMPORARY_VARIABLE ( tos | -- tos | ) */ do { int n = arg; #define tos _stack0 #line 722 "vm.def" STORE_METHOD_TEMPORARY (n, tos); #line 1968 "vm.inl" #undef tos } while (0); } NEXT_BC; bc37: { OOP _stack0; _stack0 = STACK_AT (0); /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 1985 "vm.inl" } while (0); /* STORE_OUTER_TEMP ( tos | -- tos | ) */ do { int n = arg >> 8; int scopes = arg & 255; #define tos _stack0 #line 726 "vm.def" OOP contextOOP; gst_block_context context; context = (gst_block_context) OOP_TO_OBJ (_gst_this_context_oop); do { contextOOP = context->outerContext; context = (gst_block_context) OOP_TO_OBJ (contextOOP); } while (--scopes); context->contextStack[n] = tos; #line 2008 "vm.inl" #undef tos } while (0); } NEXT_BC; bc38: { OOP _stack0; _stack0 = STACK_AT (0); /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 2025 "vm.inl" } while (0); /* STORE_LIT_VARIABLE ( tos | -- tos | ) */ do { int n = arg; #define PREPARE_STACK() do { \ } while (0) #define tos _stack0 #line 741 "vm.def" OOP var = METHOD_LITERAL (n), value = tos; if (UNCOMMON (IS_INT (var)) || UNCOMMON (!is_a_kind_of (OOP_CLASS (var), _gst_association_class))) { PREPARE_STACK (); SET_STACKTOP (var); PUSH_OOP (value); EXPORT_REGS (); SEND_MESSAGE (_gst_builtin_selectors[VALUE_COLON_SPECIAL].symbol, 1); IMPORT_REGS (); FETCH; } else SET_ASSOCIATION_VALUE (var, value); #line 2051 "vm.inl" #undef PREPARE_STACK #undef tos } while (0); } NEXT_BC; bc39: { OOP _stack0; _stack0 = STACK_AT (0); /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 2069 "vm.inl" } while (0); /* STORE_RECEIVER_VARIABLE ( tos | -- tos | ) */ do { int n = arg; #define tos _stack0 #line 758 "vm.def" STORE_RECEIVER_VARIABLE (n, tos); #line 2080 "vm.inl" #undef tos } while (0); } NEXT_BC; bc40: { /* ADVANCE ( -- ) */ do { #line 212 "vm.def" ip += 2; LOCAL_COUNTER++; #line 2095 "vm.inl" } while (0); /* JUMP_BACK ( -- ) */ do { int n = arg; #define PREPARE_STACK() do { \ } while (0) #line 762 "vm.def" PREPARE_STACK (); ip -= n; FETCH; #line 2109 "vm.inl" #undef PREPARE_STACK } while (0); } NEXT_BC; bc41: { /* ADVANCE ( -- ) */ do { #line 212 "vm.def" ip += 2; LOCAL_COUNTER++; #line 2124 "vm.inl" } while (0); /* JUMP ( -- ) */ do { int n = arg; #define PREPARE_STACK() do { \ } while (0) #line 768 "vm.def" PREPARE_STACK (); ip += n; FETCH; #line 2138 "vm.inl" #undef PREPARE_STACK } while (0); } NEXT_BC; bc42: { OOP _stack0; _stack0 = STACK_AT (0); /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 2155 "vm.inl" } while (0); /* POP_JUMP_TRUE ( tos -- ) */ do { int n = arg; #define PREPARE_STACK() do { \ } while (0) #define tos _stack0 #line 793 "vm.def" if UNCOMMON (tos == _gst_true_oop) { PREPARE_STACK (); POP_N_OOPS(1); ip += n; FETCH; } else if UNCOMMON (tos != _gst_false_oop) { ip += n; PREPARE_STACK (); EXPORT_REGS(); SEND_MESSAGE(_gst_must_be_boolean_symbol, 0); IMPORT_REGS(); FETCH; } #line 2183 "vm.inl" #undef PREPARE_STACK #undef tos } while (0); POP_N_OOPS (1); } NEXT_BC; bc43: { OOP _stack0; _stack0 = STACK_AT (0); /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 2202 "vm.inl" } while (0); /* POP_JUMP_FALSE ( tos -- ) */ do { int n = arg; #define PREPARE_STACK() do { \ } while (0) #define tos _stack0 #line 774 "vm.def" if UNCOMMON (tos == _gst_false_oop) { PREPARE_STACK (); POP_N_OOPS(1); ip += n; FETCH; } else if UNCOMMON (tos != _gst_true_oop) { ip += n; PREPARE_STACK (); EXPORT_REGS(); SEND_MESSAGE(_gst_must_be_boolean_symbol, 0); IMPORT_REGS(); FETCH; } #line 2230 "vm.inl" #undef PREPARE_STACK #undef tos } while (0); POP_N_OOPS (1); } NEXT_BC; bc44: { OOP _extra1; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 2248 "vm.inl" } while (0); /* PUSH_INTEGER ( -- tos ) */ do { int n = arg; #define tos _extra1 #line 812 "vm.def" tos = FROM_INT (n); #line 2259 "vm.inl" #undef tos } while (0); PUSH_OOP (_extra1); } NEXT_BC; bc45: { OOP _extra1; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 2276 "vm.inl" } while (0); /* PUSH_SPECIAL ( -- tos ) */ do { int n = arg; #define tos _extra1 #line 816 "vm.def" tos = _gst_nil_oop + (n - NIL_INDEX); #line 2287 "vm.inl" #undef tos } while (0); PUSH_OOP (_extra1); } NEXT_BC; bc46: { OOP _extra1; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 2304 "vm.inl" } while (0); /* PUSH_LIT_CONSTANT ( -- tos ) */ do { int n = arg; #define tos _extra1 #line 820 "vm.def" tos = METHOD_LITERAL (n); #line 2315 "vm.inl" #undef tos } while (0); PUSH_OOP (_extra1); } NEXT_BC; bc47: { OOP _stack0, _stack1; _stack1 = STACK_AT (1); _stack0 = STACK_AT (0); /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 2334 "vm.inl" } while (0); /* POP_INTO_NEW_STACKTOP ( obj | val -- obj | ) */ do { int n = arg; #define obj _stack1 #define val _stack0 #line 824 "vm.def" STORE_INSTANCE_VARIABLE (obj, n, val); #line 2346 "vm.inl" #undef obj #undef val } while (0); POP_N_OOPS (1); } NEXT_BC; bc48: { OOP _stack0; _stack0 = STACK_AT (0); /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 2365 "vm.inl" } while (0); /* POP_STACK_TOP ( tos -- ) */ do { #define tos _stack0 #line 828 "vm.def" #line 2374 "vm.inl" #undef tos } while (0); POP_N_OOPS (1); } NEXT_BC; bc49: { OOP _stack0; _stack0 = STACK_AT (0); /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 2392 "vm.inl" } while (0); /* MAKE_DIRTY_BLOCK ( block -- closure ) */ do { #define block _stack0 #define closure _stack0 #line 831 "vm.def" EXPORT_REGS (); closure = _gst_make_block_closure (block); IMPORT_REGS(); #line 2405 "vm.inl" #undef block #undef closure } while (0); STACK_AT (0) = _stack0; } NEXT_BC; bc50: { OOP _stack0; _stack0 = STACK_AT (0); /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 2424 "vm.inl" } while (0); /* RETURN_METHOD_STACK_TOP ( val | -- val | ) */ do { #define val _stack0 #line 837 "vm.def" EXPORT_REGS (); if UNCOMMON (!unwind_method ()) { SEND_MESSAGE (_gst_bad_return_error_symbol, 0); IMPORT_REGS (); } else { IMPORT_REGS (); SET_STACKTOP (val); } FETCH; #line 2445 "vm.inl" #undef val } while (0); } NEXT_BC; bc51: { OOP _stack0; _stack0 = STACK_AT (0); /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 2462 "vm.inl" } while (0); /* RETURN_CONTEXT_STACK_TOP ( val | -- val | ) */ do { #define val _stack0 #line 852 "vm.def" EXPORT_REGS (); unwind_context (); IMPORT_REGS (); SET_STACKTOP (val); FETCH; #line 2476 "vm.inl" #undef val } while (0); } NEXT_BC; bc52: { OOP _stack0; OOP _extra1; _stack0 = STACK_AT (0); /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 2494 "vm.inl" } while (0); /* DUP_STACK_TOP ( tos | -- tos | tos2 ) */ do { #define tos _stack0 #define tos2 _extra1 #line 860 "vm.def" tos2 = tos; #line 2505 "vm.inl" #undef tos #undef tos2 } while (0); PUSH_OOP (_extra1); } NEXT_BC; bc53: { OOP _stack0; _stack0 = STACK_AT (0); /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 2524 "vm.inl" } while (0); /* EXIT_INTERPRETER ( val | -- val | ) */ do { #define val _stack0 #line 864 "vm.def" /* This fixes a very rare condition, but it can happen: GC can happen because send_message_internal allocates a context while the interpreter is checking last_primitive to fill the special cache for #at:, #at:put: and #size. If there are finalizable objects, the finalization callins might change last_primitive to a bogus value. To fix the problem, we invalidate last_primitive every time the interpreter exits. */ last_primitive = 0; { OOP activeProcessOOP = get_scheduled_process (); gst_callin_process process = (gst_callin_process) OOP_TO_OBJ (activeProcessOOP); if (IS_NIL (activeProcessOOP)) abort (); if (process->objClass == _gst_callin_process_class) process->returnedValue = val; _gst_terminate_process (activeProcessOOP); if (processOOP == activeProcessOOP) SET_EXCEPT_FLAG (true); } FETCH; #line 2556 "vm.inl" #undef val } while (0); } NEXT_BC; bc54: { /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 2571 "vm.inl" } while (0); /* LINE_NUMBER_BYTECODE ( -- ) */ do { #line 890 "vm.def" #line 2579 "vm.inl" } while (0); } NEXT_BC; bc55: { /* EXT_BYTE ( -- ) */ do { #line 220 "vm.def" PREFETCH_VEC (normal_byte_codes); arg = (arg << 8) | GET_ARG; NEXT_BC_NO_ARG (normal_byte_codes); #line 2594 "vm.inl" } while (0); } NEXT_BC; bc56: { OOP _extra1; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 2609 "vm.inl" } while (0); /* PUSH_SELF ( -- tos ) */ do { #define tos _extra1 #line 893 "vm.def" tos = _gst_self; #line 2619 "vm.inl" #undef tos } while (0); PUSH_OOP (_extra1); } NEXT_BC; bc57: { /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 2635 "vm.inl" } while (0); /* INVALID ( -- ) */ do { int arg = arg; #line 226 "vm.def" _gst_errorf ("Invalid bytecode %d(%d) found!", ip[-1], arg); #line 2645 "vm.inl" } while (0); } NEXT_BC; bc58: { /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 2659 "vm.inl" } while (0); /* INVALID ( -- ) */ do { int arg = arg; #line 226 "vm.def" _gst_errorf ("Invalid bytecode %d(%d) found!", ip[-1], arg); #line 2669 "vm.inl" } while (0); } NEXT_BC; bc59: { /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 2683 "vm.inl" } while (0); /* INVALID ( -- ) */ do { int arg = arg; #line 226 "vm.def" _gst_errorf ("Invalid bytecode %d(%d) found!", ip[-1], arg); #line 2693 "vm.inl" } while (0); } NEXT_BC; bc60: { /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 2707 "vm.inl" } while (0); /* INVALID ( -- ) */ do { int arg = arg; #line 226 "vm.def" _gst_errorf ("Invalid bytecode %d(%d) found!", ip[-1], arg); #line 2717 "vm.inl" } while (0); } NEXT_BC; bc61: { /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 2731 "vm.inl" } while (0); /* INVALID ( -- ) */ do { int arg = arg; #line 226 "vm.def" _gst_errorf ("Invalid bytecode %d(%d) found!", ip[-1], arg); #line 2741 "vm.inl" } while (0); } NEXT_BC; bc62: { /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 2755 "vm.inl" } while (0); /* INVALID ( -- ) */ do { int arg = arg; #line 226 "vm.def" _gst_errorf ("Invalid bytecode %d(%d) found!", ip[-1], arg); #line 2765 "vm.inl" } while (0); } NEXT_BC; bc63: { /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 2779 "vm.inl" } while (0); /* INVALID ( -- ) */ do { int arg = arg; #line 226 "vm.def" _gst_errorf ("Invalid bytecode %d(%d) found!", ip[-1], arg); #line 2789 "vm.inl" } while (0); } NEXT_BC; bc64: { /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 2803 "vm.inl" } while (0); /* SEND ( -- ) */ do { int sel = arg; int n = 1; #define PREPARE_STACK() do { \ } while (0) #line 643 "vm.def" PREPARE_STACK (); EXPORT_REGS (); SEND_MESSAGE (METHOD_LITERAL (sel), n); IMPORT_REGS (); FETCH; #line 2820 "vm.inl" #undef PREPARE_STACK } while (0); } NEXT_BC; bc65: { /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 2835 "vm.inl" } while (0); /* SEND ( -- ) */ do { int sel = arg; int n = 0; #define PREPARE_STACK() do { \ } while (0) #line 643 "vm.def" PREPARE_STACK (); EXPORT_REGS (); SEND_MESSAGE (METHOD_LITERAL (sel), n); IMPORT_REGS (); FETCH; #line 2852 "vm.inl" #undef PREPARE_STACK } while (0); } NEXT_BC; bc66: { OOP _extra1; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 2868 "vm.inl" } while (0); /* PUSH_SELF ( -- tos ) */ do { #define tos _extra1 #line 893 "vm.def" tos = _gst_self; #line 2878 "vm.inl" #undef tos } while (0); /* RETURN_CONTEXT_STACK_TOP ( val | -- val | ) */ do { #define val _extra1 #line 852 "vm.def" EXPORT_REGS (); unwind_context (); IMPORT_REGS (); SET_STACKTOP (val); FETCH; #line 2893 "vm.inl" #undef val } while (0); PUSH_OOP (_extra1); } NEXT_BC; bc67: { OOP _extra1; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 2910 "vm.inl" } while (0); /* LINE_NUMBER_BYTECODE ( -- ) */ do { #line 890 "vm.def" #line 2918 "vm.inl" } while (0); /* PUSH_SELF ( -- tos ) */ do { #define tos _extra1 #line 893 "vm.def" tos = _gst_self; #line 2928 "vm.inl" #undef tos } while (0); PUSH_OOP (_extra1); } NEXT_BC; bc68: { OOP _stack0; _stack0 = STACK_AT (0); /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 2946 "vm.inl" } while (0); /* LINE_NUMBER_BYTECODE ( -- ) */ do { #line 890 "vm.def" #line 2954 "vm.inl" } while (0); /* POP_STACK_TOP ( tos -- ) */ do { #define tos _stack0 #line 828 "vm.def" #line 2963 "vm.inl" #undef tos } while (0); POP_N_OOPS (1); } NEXT_BC; bc69: { OOP _extra1; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 2980 "vm.inl" } while (0); /* LINE_NUMBER_BYTECODE ( -- ) */ do { #line 890 "vm.def" #line 2988 "vm.inl" } while (0); /* PUSH_TEMPORARY_VARIABLE ( -- tos ) */ do { int n = 0; #define tos _extra1 #line 683 "vm.def" tos = METHOD_TEMPORARY (n); #line 2999 "vm.inl" #undef tos } while (0); PUSH_OOP (_extra1); } NEXT_BC; bc70: { OOP _extra1; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 3016 "vm.inl" } while (0); /* PUSH_LIT_CONSTANT ( -- tos ) */ do { int n = arg; #define tos _extra1 #line 820 "vm.def" tos = METHOD_LITERAL (n); #line 3027 "vm.inl" #undef tos } while (0); /* MAKE_DIRTY_BLOCK ( block -- closure ) */ do { #define block _extra1 #define closure _extra1 #line 831 "vm.def" EXPORT_REGS (); closure = _gst_make_block_closure (block); IMPORT_REGS(); #line 3041 "vm.inl" #undef block #undef closure } while (0); PUSH_OOP (_extra1); } NEXT_BC; bc71: { /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 3058 "vm.inl" } while (0); /* SEND ( -- ) */ do { int sel = arg; int n = 2; #define PREPARE_STACK() do { \ } while (0) #line 643 "vm.def" PREPARE_STACK (); EXPORT_REGS (); SEND_MESSAGE (METHOD_LITERAL (sel), n); IMPORT_REGS (); FETCH; #line 3075 "vm.inl" #undef PREPARE_STACK } while (0); } NEXT_BC; bc72: { OOP _stack0, _stack1; _stack1 = STACK_AT (1); _stack0 = STACK_AT (0); /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 3093 "vm.inl" } while (0); /* POP_STACK_TOP ( tos -- ) */ do { #define tos _stack0 #line 828 "vm.def" #line 3102 "vm.inl" #undef tos } while (0); /* DUP_STACK_TOP ( tos | -- tos | tos2 ) */ do { #define tos _stack1 #define tos2 _stack0 #line 860 "vm.def" tos2 = tos; #line 3114 "vm.inl" #undef tos #undef tos2 } while (0); STACK_AT (0) = _stack0; } NEXT_BC; bc73: { OOP _extra1; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 3132 "vm.inl" } while (0); /* PUSH_TEMPORARY_VARIABLE ( -- tos ) */ do { int n = 0; #define tos _extra1 #line 683 "vm.def" tos = METHOD_TEMPORARY (n); #line 3143 "vm.inl" #undef tos } while (0); /* SEND_IMMEDIATE ( -- ) */ do { int n = arg; #define PREPARE_STACK() do { \ PUSH_OOP (_extra1); \ } while (0) #line 662 "vm.def" const struct builtin_selector *bs = &_gst_builtin_selectors[n]; PREPARE_STACK (); EXPORT_REGS (); SEND_MESSAGE (bs->symbol, bs->numArgs); IMPORT_REGS (); FETCH; #line 3162 "vm.inl" #undef PREPARE_STACK } while (0); PUSH_OOP (_extra1); } NEXT_BC; bc74: { OOP _extra1; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 3179 "vm.inl" } while (0); /* PUSH_SELF ( -- tos ) */ do { #define tos _extra1 #line 893 "vm.def" tos = _gst_self; #line 3189 "vm.inl" #undef tos } while (0); /* SEND ( -- ) */ do { int sel = arg; int n = 0; #define PREPARE_STACK() do { \ PUSH_OOP (_extra1); \ } while (0) #line 643 "vm.def" PREPARE_STACK (); EXPORT_REGS (); SEND_MESSAGE (METHOD_LITERAL (sel), n); IMPORT_REGS (); FETCH; #line 3208 "vm.inl" #undef PREPARE_STACK } while (0); PUSH_OOP (_extra1); } NEXT_BC; bc75: { OOP _extra1; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 3225 "vm.inl" } while (0); /* PUSH_SPECIAL ( -- tos ) */ do { int n = arg; #define tos _extra1 #line 816 "vm.def" tos = _gst_nil_oop + (n - NIL_INDEX); #line 3236 "vm.inl" #undef tos } while (0); /* RETURN_CONTEXT_STACK_TOP ( val | -- val | ) */ do { #define val _extra1 #line 852 "vm.def" EXPORT_REGS (); unwind_context (); IMPORT_REGS (); SET_STACKTOP (val); FETCH; #line 3251 "vm.inl" #undef val } while (0); PUSH_OOP (_extra1); } NEXT_BC; bc76: { OOP _extra1; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 3268 "vm.inl" } while (0); /* PUSH_SELF ( -- tos ) */ do { #define tos _extra1 #line 893 "vm.def" tos = _gst_self; #line 3278 "vm.inl" #undef tos } while (0); /* SEND_IMMEDIATE ( -- ) */ do { int n = arg; #define PREPARE_STACK() do { \ PUSH_OOP (_extra1); \ } while (0) #line 662 "vm.def" const struct builtin_selector *bs = &_gst_builtin_selectors[n]; PREPARE_STACK (); EXPORT_REGS (); SEND_MESSAGE (bs->symbol, bs->numArgs); IMPORT_REGS (); FETCH; #line 3297 "vm.inl" #undef PREPARE_STACK } while (0); PUSH_OOP (_extra1); } NEXT_BC; bc77: { OOP _extra1; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 3314 "vm.inl" } while (0); /* PUSH_OUTER_TEMP ( -- tos ) */ do { int n = arg; int scopes = 1; #define tos _extra1 #line 687 "vm.def" OOP contextOOP; gst_block_context context; context = (gst_block_context) OOP_TO_OBJ (_gst_this_context_oop); do { contextOOP = context->outerContext; context = (gst_block_context) OOP_TO_OBJ (contextOOP); } while (--scopes); tos = context->contextStack[n]; #line 3337 "vm.inl" #undef tos } while (0); PUSH_OOP (_extra1); } NEXT_BC; bc78: { OOP _stack0; _stack0 = STACK_AT (0); /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 3355 "vm.inl" } while (0); /* STORE_TEMPORARY_VARIABLE ( tos | -- tos | ) */ do { int n = arg; #define tos _stack0 #line 722 "vm.def" STORE_METHOD_TEMPORARY (n, tos); #line 3366 "vm.inl" #undef tos } while (0); /* POP_STACK_TOP ( tos -- ) */ do { #define tos _stack0 #line 828 "vm.def" #line 3376 "vm.inl" #undef tos } while (0); POP_N_OOPS (1); } NEXT_BC; bc79: { OOP _extra1, _extra2; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 3393 "vm.inl" } while (0); /* PUSH_SELF ( -- tos ) */ do { #define tos _extra1 #line 893 "vm.def" tos = _gst_self; #line 3403 "vm.inl" #undef tos } while (0); /* PUSH_TEMPORARY_VARIABLE ( -- tos ) */ do { int n = arg; #define tos _extra2 #line 683 "vm.def" tos = METHOD_TEMPORARY (n); #line 3415 "vm.inl" #undef tos } while (0); PUSH_OOP (_extra1); PUSH_OOP (_extra2); } NEXT_BC; bc80: { OOP _stack0; OOP _extra1; _stack0 = STACK_AT (0); /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 3435 "vm.inl" } while (0); /* STORE_RECEIVER_VARIABLE ( tos | -- tos | ) */ do { int n = arg; #define tos _stack0 #line 758 "vm.def" STORE_RECEIVER_VARIABLE (n, tos); #line 3446 "vm.inl" #undef tos } while (0); /* PUSH_SELF ( -- tos ) */ do { #define tos _extra1 #line 893 "vm.def" tos = _gst_self; #line 3457 "vm.inl" #undef tos } while (0); /* RETURN_CONTEXT_STACK_TOP ( val | -- val | ) */ do { #define val _extra1 #line 852 "vm.def" EXPORT_REGS (); unwind_context (); IMPORT_REGS (); SET_STACKTOP (val); FETCH; #line 3472 "vm.inl" #undef val } while (0); PUSH_OOP (_extra1); } NEXT_BC; bc81: { OOP _stack0; OOP _extra1; _stack0 = STACK_AT (0); /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 3491 "vm.inl" } while (0); /* PUSH_INTEGER ( -- tos ) */ do { int n = arg; #define tos _extra1 #line 812 "vm.def" tos = FROM_INT (n); #line 3502 "vm.inl" #undef tos } while (0); /* PLUS_SPECIAL ( op1 op2 -- op ) */ do { #define PREPARE_STACK() do { \ PUSH_OOP (_extra1); \ } while (0) #define op1 _stack0 #define op2 _extra1 #define op _stack0 #line 230 "vm.def" INTERP_BASIC_OP (op, op1, op2, add_with_check (op1, op2, &overflow), farg1 + farg2); PREPARE_STACK (); EXPORT_REGS (); SEND_MESSAGE (_gst_builtin_selectors[PLUS_SPECIAL].symbol, 1); IMPORT_REGS (); FETCH; #line 3525 "vm.inl" #undef PREPARE_STACK #undef op1 #undef op2 #undef op } while (0); STACK_AT (0) = _stack0; } NEXT_BC; bc82: { OOP _extra1; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 3545 "vm.inl" } while (0); /* LINE_NUMBER_BYTECODE ( -- ) */ do { #line 890 "vm.def" #line 3553 "vm.inl" } while (0); /* PUSH_LIT_VARIABLE ( -- tos ) */ do { int n = 0; #define PREPARE_STACK() do { \ } while (0) #define tos _extra1 #line 702 "vm.def" tos = METHOD_LITERAL (n); if (UNCOMMON (IS_INT (tos)) || UNCOMMON (!is_a_kind_of (OOP_CLASS (tos), _gst_association_class))) { PREPARE_STACK (); PUSH_OOP (tos); EXPORT_REGS (); SEND_MESSAGE (_gst_builtin_selectors[VALUE_SPECIAL].symbol, 0); IMPORT_REGS (); FETCH; } else tos = ASSOCIATION_VALUE (tos); #line 3578 "vm.inl" #undef PREPARE_STACK #undef tos } while (0); PUSH_OOP (_extra1); } NEXT_BC; bc83: { OOP _extra1, _extra2; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 3596 "vm.inl" } while (0); /* PUSH_TEMPORARY_VARIABLE ( -- tos ) */ do { int n = 0; #define tos _extra1 #line 683 "vm.def" tos = METHOD_TEMPORARY (n); #line 3607 "vm.inl" #undef tos } while (0); /* PUSH_TEMPORARY_VARIABLE ( -- tos ) */ do { int n = arg; #define tos _extra2 #line 683 "vm.def" tos = METHOD_TEMPORARY (n); #line 3619 "vm.inl" #undef tos } while (0); PUSH_OOP (_extra1); PUSH_OOP (_extra2); } NEXT_BC; bc84: { OOP _extra1; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 3637 "vm.inl" } while (0); /* PUSH_TEMPORARY_VARIABLE ( -- tos ) */ do { int n = 0; #define tos _extra1 #line 683 "vm.def" tos = METHOD_TEMPORARY (n); #line 3648 "vm.inl" #undef tos } while (0); /* SEND ( -- ) */ do { int sel = arg >> 8; int n = arg & 255; #define PREPARE_STACK() do { \ PUSH_OOP (_extra1); \ } while (0) #line 643 "vm.def" PREPARE_STACK (); EXPORT_REGS (); SEND_MESSAGE (METHOD_LITERAL (sel), n); IMPORT_REGS (); FETCH; #line 3667 "vm.inl" #undef PREPARE_STACK } while (0); PUSH_OOP (_extra1); } NEXT_BC; bc85: { OOP _extra1; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 3684 "vm.inl" } while (0); /* LINE_NUMBER_BYTECODE ( -- ) */ do { #line 890 "vm.def" #line 3692 "vm.inl" } while (0); /* PUSH_TEMPORARY_VARIABLE ( -- tos ) */ do { int n = 1; #define tos _extra1 #line 683 "vm.def" tos = METHOD_TEMPORARY (n); #line 3703 "vm.inl" #undef tos } while (0); PUSH_OOP (_extra1); } NEXT_BC; bc86: { OOP _stack0; _stack0 = STACK_AT (0); /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 3721 "vm.inl" } while (0); /* IS_NIL_SPECIAL ( rec -- val ) */ do { #define rec _stack0 #define val _stack0 #line 576 "vm.def" /* DO_JUMP_LOOKAHEAD (rec == _gst_nil_oop); */ val = rec == _gst_nil_oop ? _gst_true_oop : _gst_false_oop; #line 3733 "vm.inl" #undef rec #undef val } while (0); /* POP_JUMP_FALSE ( tos -- ) */ do { int n = arg; #define PREPARE_STACK() do { \ STACK_AT (0) = _stack0; \ } while (0) #define tos _stack0 #line 774 "vm.def" if UNCOMMON (tos == _gst_false_oop) { PREPARE_STACK (); POP_N_OOPS(1); ip += n; FETCH; } else if UNCOMMON (tos != _gst_true_oop) { ip += n; PREPARE_STACK (); EXPORT_REGS(); SEND_MESSAGE(_gst_must_be_boolean_symbol, 0); IMPORT_REGS(); FETCH; } #line 3764 "vm.inl" #undef PREPARE_STACK #undef tos } while (0); POP_N_OOPS (1); } NEXT_BC; bc87: { OOP _stack0; OOP _extra1; _stack0 = STACK_AT (0); /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 3784 "vm.inl" } while (0); /* PUSH_INTEGER ( -- tos ) */ do { int n = arg; #define tos _extra1 #line 812 "vm.def" tos = FROM_INT (n); #line 3795 "vm.inl" #undef tos } while (0); /* EQUAL_SPECIAL ( op1 op2 -- op ) */ do { #define PREPARE_STACK() do { \ PUSH_OOP (_extra1); \ } while (0) #define op1 _stack0 #define op2 _extra1 #define op _stack0 #line 288 "vm.def" PREPARE_STACK (); INTERP_BASIC_BOOL (op, op1, op2, ==); EXPORT_REGS (); SEND_MESSAGE (_gst_builtin_selectors[EQUAL_SPECIAL].symbol, 1); IMPORT_REGS (); FETCH; #line 3816 "vm.inl" #undef PREPARE_STACK #undef op1 #undef op2 #undef op } while (0); STACK_AT (0) = _stack0; } NEXT_BC; bc88: { /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 3835 "vm.inl" } while (0); /* SEND ( -- ) */ do { int sel = arg; int n = 3; #define PREPARE_STACK() do { \ } while (0) #line 643 "vm.def" PREPARE_STACK (); EXPORT_REGS (); SEND_MESSAGE (METHOD_LITERAL (sel), n); IMPORT_REGS (); FETCH; #line 3852 "vm.inl" #undef PREPARE_STACK } while (0); } NEXT_BC; bc89: { OOP _extra1; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 3868 "vm.inl" } while (0); /* PUSH_TEMPORARY_VARIABLE ( -- tos ) */ do { int n = 0; #define tos _extra1 #line 683 "vm.def" tos = METHOD_TEMPORARY (n); #line 3879 "vm.inl" #undef tos } while (0); /* SEND ( -- ) */ do { int sel = arg; int n = 1; #define PREPARE_STACK() do { \ PUSH_OOP (_extra1); \ } while (0) #line 643 "vm.def" PREPARE_STACK (); EXPORT_REGS (); SEND_MESSAGE (METHOD_LITERAL (sel), n); IMPORT_REGS (); FETCH; #line 3898 "vm.inl" #undef PREPARE_STACK } while (0); PUSH_OOP (_extra1); } NEXT_BC; bc90: { OOP _extra1; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 3915 "vm.inl" } while (0); /* LINE_NUMBER_BYTECODE ( -- ) */ do { #line 890 "vm.def" #line 3923 "vm.inl" } while (0); /* PUSH_SELF ( -- tos ) */ do { #define tos _extra1 #line 893 "vm.def" tos = _gst_self; #line 3933 "vm.inl" #undef tos } while (0); /* SEND ( -- ) */ do { int sel = 0; int n = 0; #define PREPARE_STACK() do { \ PUSH_OOP (_extra1); \ } while (0) #line 643 "vm.def" PREPARE_STACK (); EXPORT_REGS (); SEND_MESSAGE (METHOD_LITERAL (sel), n); IMPORT_REGS (); FETCH; #line 3952 "vm.inl" #undef PREPARE_STACK } while (0); PUSH_OOP (_extra1); } NEXT_BC; bc91: { OOP _extra1; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 3969 "vm.inl" } while (0); /* PUSH_TEMPORARY_VARIABLE ( -- tos ) */ do { int n = arg; #define tos _extra1 #line 683 "vm.def" tos = METHOD_TEMPORARY (n); #line 3980 "vm.inl" #undef tos } while (0); /* RETURN_CONTEXT_STACK_TOP ( val | -- val | ) */ do { #define val _extra1 #line 852 "vm.def" EXPORT_REGS (); unwind_context (); IMPORT_REGS (); SET_STACKTOP (val); FETCH; #line 3995 "vm.inl" #undef val } while (0); PUSH_OOP (_extra1); } NEXT_BC; bc92: { OOP _extra1; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 4012 "vm.inl" } while (0); /* PUSH_LIT_CONSTANT ( -- tos ) */ do { int n = arg; #define tos _extra1 #line 820 "vm.def" tos = METHOD_LITERAL (n); #line 4023 "vm.inl" #undef tos } while (0); /* SEND_IMMEDIATE ( -- ) */ do { int n = 36; #define PREPARE_STACK() do { \ PUSH_OOP (_extra1); \ } while (0) #line 662 "vm.def" const struct builtin_selector *bs = &_gst_builtin_selectors[n]; PREPARE_STACK (); EXPORT_REGS (); SEND_MESSAGE (bs->symbol, bs->numArgs); IMPORT_REGS (); FETCH; #line 4042 "vm.inl" #undef PREPARE_STACK } while (0); PUSH_OOP (_extra1); } NEXT_BC; bc93: { OOP _stack0, _stack1; _stack1 = STACK_AT (1); _stack0 = STACK_AT (0); /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 4061 "vm.inl" } while (0); /* SAME_OBJECT_SPECIAL ( op1 op2 -- op ) */ do { #define op1 _stack1 #define op2 _stack0 #define op _stack1 #line 610 "vm.def" /* DO_JUMP_LOOKAHEAD (op1 == op2); */ op = (op1 == op2) ? _gst_true_oop : _gst_false_oop; #line 4074 "vm.inl" #undef op1 #undef op2 #undef op } while (0); /* POP_JUMP_FALSE ( tos -- ) */ do { int n = arg; #define PREPARE_STACK() do { \ STACK_AT (1) = _stack1; \ POP_N_OOPS (1); \ } while (0) #define tos _stack1 #line 774 "vm.def" if UNCOMMON (tos == _gst_false_oop) { PREPARE_STACK (); POP_N_OOPS(1); ip += n; FETCH; } else if UNCOMMON (tos != _gst_true_oop) { ip += n; PREPARE_STACK (); EXPORT_REGS(); SEND_MESSAGE(_gst_must_be_boolean_symbol, 0); IMPORT_REGS(); FETCH; } #line 4107 "vm.inl" #undef PREPARE_STACK #undef tos } while (0); POP_N_OOPS (2); } NEXT_BC; bc94: { OOP _extra1; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 4125 "vm.inl" } while (0); /* PUSH_LIT_CONSTANT ( -- tos ) */ do { int n = arg; #define tos _extra1 #line 820 "vm.def" tos = METHOD_LITERAL (n); #line 4136 "vm.inl" #undef tos } while (0); /* SEND ( -- ) */ do { int sel = 1; int n = 1; #define PREPARE_STACK() do { \ PUSH_OOP (_extra1); \ } while (0) #line 643 "vm.def" PREPARE_STACK (); EXPORT_REGS (); SEND_MESSAGE (METHOD_LITERAL (sel), n); IMPORT_REGS (); FETCH; #line 4155 "vm.inl" #undef PREPARE_STACK } while (0); PUSH_OOP (_extra1); } NEXT_BC; bc95: { OOP _stack0; _stack0 = STACK_AT (0); /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 4173 "vm.inl" } while (0); /* LINE_NUMBER_BYTECODE ( -- ) */ do { #line 890 "vm.def" #line 4181 "vm.inl" } while (0); /* POP_STACK_TOP ( tos -- ) */ do { #define tos _stack0 #line 828 "vm.def" #line 4190 "vm.inl" #undef tos } while (0); /* PUSH_SELF ( -- tos ) */ do { #define tos _stack0 #line 893 "vm.def" tos = _gst_self; #line 4201 "vm.inl" #undef tos } while (0); STACK_AT (0) = _stack0; } NEXT_BC; bc96: { OOP _stack0, _stack1; _stack1 = STACK_AT (1); _stack0 = STACK_AT (0); /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 4220 "vm.inl" } while (0); /* POP_STACK_TOP ( tos -- ) */ do { #define tos _stack0 #line 828 "vm.def" #line 4229 "vm.inl" #undef tos } while (0); /* DUP_STACK_TOP ( tos | -- tos | tos2 ) */ do { #define tos _stack1 #define tos2 _stack0 #line 860 "vm.def" tos2 = tos; #line 4241 "vm.inl" #undef tos #undef tos2 } while (0); /* LINE_NUMBER_BYTECODE ( -- ) */ do { #line 890 "vm.def" #line 4251 "vm.inl" } while (0); STACK_AT (0) = _stack0; } NEXT_BC; bc97: { OOP _extra1; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 4267 "vm.inl" } while (0); /* PUSH_TEMPORARY_VARIABLE ( -- tos ) */ do { int n = 0; #define tos _extra1 #line 683 "vm.def" tos = METHOD_TEMPORARY (n); #line 4278 "vm.inl" #undef tos } while (0); /* SEND ( -- ) */ do { int sel = arg; int n = 0; #define PREPARE_STACK() do { \ PUSH_OOP (_extra1); \ } while (0) #line 643 "vm.def" PREPARE_STACK (); EXPORT_REGS (); SEND_MESSAGE (METHOD_LITERAL (sel), n); IMPORT_REGS (); FETCH; #line 4297 "vm.inl" #undef PREPARE_STACK } while (0); PUSH_OOP (_extra1); } NEXT_BC; bc98: { OOP _extra1; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 4314 "vm.inl" } while (0); /* PUSH_TEMPORARY_VARIABLE ( -- tos ) */ do { int n = 1; #define tos _extra1 #line 683 "vm.def" tos = METHOD_TEMPORARY (n); #line 4325 "vm.inl" #undef tos } while (0); /* SEND_IMMEDIATE ( -- ) */ do { int n = arg; #define PREPARE_STACK() do { \ PUSH_OOP (_extra1); \ } while (0) #line 662 "vm.def" const struct builtin_selector *bs = &_gst_builtin_selectors[n]; PREPARE_STACK (); EXPORT_REGS (); SEND_MESSAGE (bs->symbol, bs->numArgs); IMPORT_REGS (); FETCH; #line 4344 "vm.inl" #undef PREPARE_STACK } while (0); PUSH_OOP (_extra1); } NEXT_BC; bc99: { OOP _stack0; OOP _extra1; _stack0 = STACK_AT (0); /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 4363 "vm.inl" } while (0); /* PUSH_LIT_CONSTANT ( -- tos ) */ do { int n = arg; #define tos _extra1 #line 820 "vm.def" tos = METHOD_LITERAL (n); #line 4374 "vm.inl" #undef tos } while (0); /* EQUAL_SPECIAL ( op1 op2 -- op ) */ do { #define PREPARE_STACK() do { \ PUSH_OOP (_extra1); \ } while (0) #define op1 _stack0 #define op2 _extra1 #define op _stack0 #line 288 "vm.def" PREPARE_STACK (); INTERP_BASIC_BOOL (op, op1, op2, ==); EXPORT_REGS (); SEND_MESSAGE (_gst_builtin_selectors[EQUAL_SPECIAL].symbol, 1); IMPORT_REGS (); FETCH; #line 4395 "vm.inl" #undef PREPARE_STACK #undef op1 #undef op2 #undef op } while (0); STACK_AT (0) = _stack0; } NEXT_BC; bc100: { OOP _stack0; OOP _extra1; _stack0 = STACK_AT (0); /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 4417 "vm.inl" } while (0); /* PUSH_INTEGER ( -- tos ) */ do { int n = arg; #define tos _extra1 #line 812 "vm.def" tos = FROM_INT (n); #line 4428 "vm.inl" #undef tos } while (0); /* MINUS_SPECIAL ( op1 op2 -- op ) */ do { #define PREPARE_STACK() do { \ PUSH_OOP (_extra1); \ } while (0) #define op1 _stack0 #define op2 _extra1 #define op _stack0 #line 241 "vm.def" INTERP_BASIC_OP (op, op1, op2, sub_with_check (op1, op2, &overflow), farg1 - farg2); PREPARE_STACK (); EXPORT_REGS (); SEND_MESSAGE (_gst_builtin_selectors[MINUS_SPECIAL].symbol, 1); IMPORT_REGS (); FETCH; #line 4451 "vm.inl" #undef PREPARE_STACK #undef op1 #undef op2 #undef op } while (0); STACK_AT (0) = _stack0; } NEXT_BC; bc101: { OOP _stack0; OOP _extra1; _stack0 = STACK_AT (0); /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 4473 "vm.inl" } while (0); /* DUP_STACK_TOP ( tos | -- tos | tos2 ) */ do { #define tos _stack0 #define tos2 _extra1 #line 860 "vm.def" tos2 = tos; #line 4484 "vm.inl" #undef tos #undef tos2 } while (0); /* POP_JUMP_FALSE ( tos -- ) */ do { int n = arg; #define PREPARE_STACK() do { \ PUSH_OOP (_extra1); \ } while (0) #define tos _extra1 #line 774 "vm.def" if UNCOMMON (tos == _gst_false_oop) { PREPARE_STACK (); POP_N_OOPS(1); ip += n; FETCH; } else if UNCOMMON (tos != _gst_true_oop) { ip += n; PREPARE_STACK (); EXPORT_REGS(); SEND_MESSAGE(_gst_must_be_boolean_symbol, 0); IMPORT_REGS(); FETCH; } #line 4515 "vm.inl" #undef PREPARE_STACK #undef tos } while (0); } NEXT_BC; bc102: { OOP _stack0; _stack0 = STACK_AT (0); /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 4533 "vm.inl" } while (0); /* POP_STACK_TOP ( tos -- ) */ do { #define tos _stack0 #line 828 "vm.def" #line 4542 "vm.inl" #undef tos } while (0); /* LINE_NUMBER_BYTECODE ( -- ) */ do { #line 890 "vm.def" #line 4551 "vm.inl" } while (0); POP_N_OOPS (1); } NEXT_BC; bc103: { OOP _extra1; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 4567 "vm.inl" } while (0); /* PUSH_INTEGER ( -- tos ) */ do { int n = arg; #define tos _extra1 #line 812 "vm.def" tos = FROM_INT (n); #line 4578 "vm.inl" #undef tos } while (0); /* SEND_IMMEDIATE ( -- ) */ do { int n = 32; #define PREPARE_STACK() do { \ PUSH_OOP (_extra1); \ } while (0) #line 662 "vm.def" const struct builtin_selector *bs = &_gst_builtin_selectors[n]; PREPARE_STACK (); EXPORT_REGS (); SEND_MESSAGE (bs->symbol, bs->numArgs); IMPORT_REGS (); FETCH; #line 4597 "vm.inl" #undef PREPARE_STACK } while (0); PUSH_OOP (_extra1); } NEXT_BC; bc104: { OOP _extra1; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 4614 "vm.inl" } while (0); /* PUSH_TEMPORARY_VARIABLE ( -- tos ) */ do { int n = arg; #define tos _extra1 #line 683 "vm.def" tos = METHOD_TEMPORARY (n); #line 4625 "vm.inl" #undef tos } while (0); /* SIZE_SPECIAL ( rec -- val ) */ do { #define PREPARE_STACK() do { \ PUSH_OOP (_extra1); \ } while (0) #define rec _extra1 #define val _extra1 #line 510 "vm.def" OOP classOOP; PREPARE_STACK (); EXPORT_REGS (); if UNCOMMON (IS_INT (rec)) { SEND_MESSAGE (_gst_builtin_selectors[SIZE_SPECIAL].symbol, 0); IMPORT_REGS (); FETCH; } if COMMON (size_cache_class == (classOOP = OOP_CLASS (rec)) && !execute_primitive_operation (size_cache_prim, 0)) { IMPORT_REGS (); NEXT_BC; } /* Not the same class that is in the cache, or the primitive failed -- send the message, and modify the cache if the send is resolved to a primitive. */ last_primitive = 0; SEND_MESSAGE (_gst_builtin_selectors[SIZE_SPECIAL].symbol, 0); IMPORT_REGS (); if COMMON (last_primitive) { size_cache_prim = last_primitive; size_cache_class = classOOP; NEXT_BC; } FETCH; #line 4669 "vm.inl" #undef PREPARE_STACK #undef rec #undef val } while (0); PUSH_OOP (_extra1); } NEXT_BC; bc105: { OOP _extra1; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 4688 "vm.inl" } while (0); /* PUSH_SELF ( -- tos ) */ do { #define tos _extra1 #line 893 "vm.def" tos = _gst_self; #line 4698 "vm.inl" #undef tos } while (0); /* SEND ( -- ) */ do { int sel = arg >> 8; int n = arg & 255; #define PREPARE_STACK() do { \ PUSH_OOP (_extra1); \ } while (0) #line 643 "vm.def" PREPARE_STACK (); EXPORT_REGS (); SEND_MESSAGE (METHOD_LITERAL (sel), n); IMPORT_REGS (); FETCH; #line 4717 "vm.inl" #undef PREPARE_STACK } while (0); PUSH_OOP (_extra1); } NEXT_BC; bc106: { OOP _extra1; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 4734 "vm.inl" } while (0); /* LINE_NUMBER_BYTECODE ( -- ) */ do { #line 890 "vm.def" #line 4742 "vm.inl" } while (0); /* PUSH_TEMPORARY_VARIABLE ( -- tos ) */ do { int n = 2; #define tos _extra1 #line 683 "vm.def" tos = METHOD_TEMPORARY (n); #line 4753 "vm.inl" #undef tos } while (0); PUSH_OOP (_extra1); } NEXT_BC; bc107: { OOP _stack0; _stack0 = STACK_AT (0); /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 4771 "vm.inl" } while (0); /* POP_STACK_TOP ( tos -- ) */ do { #define tos _stack0 #line 828 "vm.def" #line 4780 "vm.inl" #undef tos } while (0); /* SEND_IMMEDIATE ( -- ) */ do { int n = arg; #define PREPARE_STACK() do { \ POP_N_OOPS (1); \ } while (0) #line 662 "vm.def" const struct builtin_selector *bs = &_gst_builtin_selectors[n]; PREPARE_STACK (); EXPORT_REGS (); SEND_MESSAGE (bs->symbol, bs->numArgs); IMPORT_REGS (); FETCH; #line 4799 "vm.inl" #undef PREPARE_STACK } while (0); POP_N_OOPS (1); } NEXT_BC; bc108: { OOP _extra1, _extra2; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 4816 "vm.inl" } while (0); /* PUSH_TEMPORARY_VARIABLE ( -- tos ) */ do { int n = arg; #define tos _extra1 #line 683 "vm.def" tos = METHOD_TEMPORARY (n); #line 4827 "vm.inl" #undef tos } while (0); /* PUSH_INTEGER ( -- tos ) */ do { int n = 1; #define tos _extra2 #line 812 "vm.def" tos = FROM_INT (n); #line 4839 "vm.inl" #undef tos } while (0); /* PLUS_SPECIAL ( op1 op2 -- op ) */ do { #define PREPARE_STACK() do { \ PUSH_OOP (_extra1); \ PUSH_OOP (_extra2); \ } while (0) #define op1 _extra1 #define op2 _extra2 #define op _extra1 #line 230 "vm.def" INTERP_BASIC_OP (op, op1, op2, add_with_check (op1, op2, &overflow), farg1 + farg2); PREPARE_STACK (); EXPORT_REGS (); SEND_MESSAGE (_gst_builtin_selectors[PLUS_SPECIAL].symbol, 1); IMPORT_REGS (); FETCH; #line 4863 "vm.inl" #undef PREPARE_STACK #undef op1 #undef op2 #undef op } while (0); PUSH_OOP (_extra1); } NEXT_BC; bc109: { OOP _extra1; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 4883 "vm.inl" } while (0); /* LINE_NUMBER_BYTECODE ( -- ) */ do { #line 890 "vm.def" #line 4891 "vm.inl" } while (0); /* PUSH_RECEIVER_VARIABLE ( -- tos ) */ do { int n = 0; #define tos _extra1 #line 718 "vm.def" tos = RECEIVER_VARIABLE (n); #line 4902 "vm.inl" #undef tos } while (0); PUSH_OOP (_extra1); } NEXT_BC; bc110: { OOP _extra1; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 4919 "vm.inl" } while (0); /* PUSH_LIT_CONSTANT ( -- tos ) */ do { int n = arg; #define tos _extra1 #line 820 "vm.def" tos = METHOD_LITERAL (n); #line 4930 "vm.inl" #undef tos } while (0); /* SEND_IMMEDIATE ( -- ) */ do { int n = 38; #define PREPARE_STACK() do { \ PUSH_OOP (_extra1); \ } while (0) #line 662 "vm.def" const struct builtin_selector *bs = &_gst_builtin_selectors[n]; PREPARE_STACK (); EXPORT_REGS (); SEND_MESSAGE (bs->symbol, bs->numArgs); IMPORT_REGS (); FETCH; #line 4949 "vm.inl" #undef PREPARE_STACK } while (0); PUSH_OOP (_extra1); } NEXT_BC; bc111: { OOP _stack0; OOP _extra1; _stack0 = STACK_AT (0); /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 4968 "vm.inl" } while (0); /* PUSH_INTEGER ( -- tos ) */ do { int n = arg; #define tos _extra1 #line 812 "vm.def" tos = FROM_INT (n); #line 4979 "vm.inl" #undef tos } while (0); /* AT_SPECIAL ( rec idx -- val ) */ do { #define PREPARE_STACK() do { \ PUSH_OOP (_extra1); \ } while (0) #define rec _stack0 #define idx _extra1 #define val _stack0 #line 444 "vm.def" OOP classOOP; PREPARE_STACK (); EXPORT_REGS (); if UNCOMMON (IS_INT (rec)) { SEND_MESSAGE (_gst_builtin_selectors[AT_SPECIAL].symbol, 1); IMPORT_REGS (); FETCH; } if COMMON (at_cache_class == (classOOP = OOP_CLASS (rec)) && !cached_index_oop_primitive (rec, idx, at_cache_spec)) { IMPORT_REGS (); NEXT_BC; } /* Not the same class that is in the cache, or the primitive failed -- send the message, and modify the cache if the send is resolved to a primitive. */ last_primitive = 0; SEND_MESSAGE (_gst_builtin_selectors[AT_SPECIAL].symbol, 1); IMPORT_REGS (); if (_gst_primitive_table[last_primitive].id == 60) { at_cache_spec = CLASS_INSTANCE_SPEC (classOOP); at_cache_class = classOOP; NEXT_BC; } FETCH; #line 5024 "vm.inl" #undef PREPARE_STACK #undef rec #undef idx #undef val } while (0); STACK_AT (0) = _stack0; } NEXT_BC; bc112: { OOP _extra1; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 5044 "vm.inl" } while (0); /* LINE_NUMBER_BYTECODE ( -- ) */ do { #line 890 "vm.def" #line 5052 "vm.inl" } while (0); /* PUSH_RECEIVER_VARIABLE ( -- tos ) */ do { int n = 1; #define tos _extra1 #line 718 "vm.def" tos = RECEIVER_VARIABLE (n); #line 5063 "vm.inl" #undef tos } while (0); PUSH_OOP (_extra1); } NEXT_BC; bc113: { OOP _extra1, _extra2; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 5080 "vm.inl" } while (0); /* PUSH_TEMPORARY_VARIABLE ( -- tos ) */ do { int n = 0; #define tos _extra1 #line 683 "vm.def" tos = METHOD_TEMPORARY (n); #line 5091 "vm.inl" #undef tos } while (0); /* PUSH_LIT_CONSTANT ( -- tos ) */ do { int n = arg; #define tos _extra2 #line 820 "vm.def" tos = METHOD_LITERAL (n); #line 5103 "vm.inl" #undef tos } while (0); PUSH_OOP (_extra1); PUSH_OOP (_extra2); } NEXT_BC; bc114: { OOP _stack0; OOP _extra1; _stack0 = STACK_AT (0); /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 5123 "vm.inl" } while (0); /* DUP_STACK_TOP ( tos | -- tos | tos2 ) */ do { #define tos _stack0 #define tos2 _extra1 #line 860 "vm.def" tos2 = tos; #line 5134 "vm.inl" #undef tos #undef tos2 } while (0); /* POP_JUMP_TRUE ( tos -- ) */ do { int n = arg; #define PREPARE_STACK() do { \ PUSH_OOP (_extra1); \ } while (0) #define tos _extra1 #line 793 "vm.def" if UNCOMMON (tos == _gst_true_oop) { PREPARE_STACK (); POP_N_OOPS(1); ip += n; FETCH; } else if UNCOMMON (tos != _gst_false_oop) { ip += n; PREPARE_STACK (); EXPORT_REGS(); SEND_MESSAGE(_gst_must_be_boolean_symbol, 0); IMPORT_REGS(); FETCH; } #line 5165 "vm.inl" #undef PREPARE_STACK #undef tos } while (0); } NEXT_BC; bc115: { OOP _stack0; OOP _extra1; _stack0 = STACK_AT (0); /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 5184 "vm.inl" } while (0); /* PUSH_TEMPORARY_VARIABLE ( -- tos ) */ do { int n = arg; #define tos _extra1 #line 683 "vm.def" tos = METHOD_TEMPORARY (n); #line 5195 "vm.inl" #undef tos } while (0); /* AT_SPECIAL ( rec idx -- val ) */ do { #define PREPARE_STACK() do { \ PUSH_OOP (_extra1); \ } while (0) #define rec _stack0 #define idx _extra1 #define val _stack0 #line 444 "vm.def" OOP classOOP; PREPARE_STACK (); EXPORT_REGS (); if UNCOMMON (IS_INT (rec)) { SEND_MESSAGE (_gst_builtin_selectors[AT_SPECIAL].symbol, 1); IMPORT_REGS (); FETCH; } if COMMON (at_cache_class == (classOOP = OOP_CLASS (rec)) && !cached_index_oop_primitive (rec, idx, at_cache_spec)) { IMPORT_REGS (); NEXT_BC; } /* Not the same class that is in the cache, or the primitive failed -- send the message, and modify the cache if the send is resolved to a primitive. */ last_primitive = 0; SEND_MESSAGE (_gst_builtin_selectors[AT_SPECIAL].symbol, 1); IMPORT_REGS (); if (_gst_primitive_table[last_primitive].id == 60) { at_cache_spec = CLASS_INSTANCE_SPEC (classOOP); at_cache_class = classOOP; NEXT_BC; } FETCH; #line 5240 "vm.inl" #undef PREPARE_STACK #undef rec #undef idx #undef val } while (0); STACK_AT (0) = _stack0; } NEXT_BC; bc116: { OOP _extra1; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 5260 "vm.inl" } while (0); /* PUSH_TEMPORARY_VARIABLE ( -- tos ) */ do { int n = 2; #define tos _extra1 #line 683 "vm.def" tos = METHOD_TEMPORARY (n); #line 5271 "vm.inl" #undef tos } while (0); /* SEND_IMMEDIATE ( -- ) */ do { int n = arg; #define PREPARE_STACK() do { \ PUSH_OOP (_extra1); \ } while (0) #line 662 "vm.def" const struct builtin_selector *bs = &_gst_builtin_selectors[n]; PREPARE_STACK (); EXPORT_REGS (); SEND_MESSAGE (bs->symbol, bs->numArgs); IMPORT_REGS (); FETCH; #line 5290 "vm.inl" #undef PREPARE_STACK } while (0); PUSH_OOP (_extra1); } NEXT_BC; bc117: { OOP _extra1; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 5307 "vm.inl" } while (0); /* PUSH_LIT_CONSTANT ( -- tos ) */ do { int n = arg; #define tos _extra1 #line 820 "vm.def" tos = METHOD_LITERAL (n); #line 5318 "vm.inl" #undef tos } while (0); /* SEND_IMMEDIATE ( -- ) */ do { int n = 49; #define PREPARE_STACK() do { \ PUSH_OOP (_extra1); \ } while (0) #line 662 "vm.def" const struct builtin_selector *bs = &_gst_builtin_selectors[n]; PREPARE_STACK (); EXPORT_REGS (); SEND_MESSAGE (bs->symbol, bs->numArgs); IMPORT_REGS (); FETCH; #line 5337 "vm.inl" #undef PREPARE_STACK } while (0); PUSH_OOP (_extra1); } NEXT_BC; bc118: { OOP _stack0; _stack0 = STACK_AT (0); /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 5355 "vm.inl" } while (0); /* STORE_TEMPORARY_VARIABLE ( tos | -- tos | ) */ do { int n = 1; #define tos _stack0 #line 722 "vm.def" STORE_METHOD_TEMPORARY (n, tos); #line 5366 "vm.inl" #undef tos } while (0); /* LINE_NUMBER_BYTECODE ( -- ) */ do { #line 890 "vm.def" #line 5375 "vm.inl" } while (0); /* POP_STACK_TOP ( tos -- ) */ do { #define tos _stack0 #line 828 "vm.def" #line 5384 "vm.inl" #undef tos } while (0); POP_N_OOPS (1); } NEXT_BC; bc119: { OOP _extra1; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 5401 "vm.inl" } while (0); /* PUSH_TEMPORARY_VARIABLE ( -- tos ) */ do { int n = 1; #define tos _extra1 #line 683 "vm.def" tos = METHOD_TEMPORARY (n); #line 5412 "vm.inl" #undef tos } while (0); /* SEND ( -- ) */ do { int sel = arg; int n = 1; #define PREPARE_STACK() do { \ PUSH_OOP (_extra1); \ } while (0) #line 643 "vm.def" PREPARE_STACK (); EXPORT_REGS (); SEND_MESSAGE (METHOD_LITERAL (sel), n); IMPORT_REGS (); FETCH; #line 5431 "vm.inl" #undef PREPARE_STACK } while (0); PUSH_OOP (_extra1); } NEXT_BC; bc120: { OOP _stack0; _stack0 = STACK_AT (0); /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 5449 "vm.inl" } while (0); /* STORE_RECEIVER_VARIABLE ( tos | -- tos | ) */ do { int n = arg; #define tos _stack0 #line 758 "vm.def" STORE_RECEIVER_VARIABLE (n, tos); #line 5460 "vm.inl" #undef tos } while (0); /* POP_STACK_TOP ( tos -- ) */ do { #define tos _stack0 #line 828 "vm.def" #line 5470 "vm.inl" #undef tos } while (0); POP_N_OOPS (1); } NEXT_BC; bc121: { OOP _stack0; _stack0 = STACK_AT (0); /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 5488 "vm.inl" } while (0); /* STORE_OUTER_TEMP ( tos | -- tos | ) */ do { int n = arg; int scopes = 1; #define tos _stack0 #line 726 "vm.def" OOP contextOOP; gst_block_context context; context = (gst_block_context) OOP_TO_OBJ (_gst_this_context_oop); do { contextOOP = context->outerContext; context = (gst_block_context) OOP_TO_OBJ (contextOOP); } while (--scopes); context->contextStack[n] = tos; #line 5511 "vm.inl" #undef tos } while (0); } NEXT_BC; bc122: { OOP _extra1; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 5527 "vm.inl" } while (0); /* PUSH_INTEGER ( -- tos ) */ do { int n = arg; #define tos _extra1 #line 812 "vm.def" tos = FROM_INT (n); #line 5538 "vm.inl" #undef tos } while (0); /* SEND_IMMEDIATE ( -- ) */ do { int n = 96; #define PREPARE_STACK() do { \ PUSH_OOP (_extra1); \ } while (0) #line 662 "vm.def" const struct builtin_selector *bs = &_gst_builtin_selectors[n]; PREPARE_STACK (); EXPORT_REGS (); SEND_MESSAGE (bs->symbol, bs->numArgs); IMPORT_REGS (); FETCH; #line 5557 "vm.inl" #undef PREPARE_STACK } while (0); PUSH_OOP (_extra1); } NEXT_BC; bc123: { OOP _stack0; _stack0 = STACK_AT (0); /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 5575 "vm.inl" } while (0); /* POP_STACK_TOP ( tos -- ) */ do { #define tos _stack0 #line 828 "vm.def" #line 5584 "vm.inl" #undef tos } while (0); /* PUSH_TEMPORARY_VARIABLE ( -- tos ) */ do { int n = arg; #define tos _stack0 #line 683 "vm.def" tos = METHOD_TEMPORARY (n); #line 5596 "vm.inl" #undef tos } while (0); STACK_AT (0) = _stack0; } NEXT_BC; bc124: { OOP _extra1; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 5613 "vm.inl" } while (0); /* PUSH_RECEIVER_VARIABLE ( -- tos ) */ do { int n = arg; #define tos _extra1 #line 718 "vm.def" tos = RECEIVER_VARIABLE (n); #line 5624 "vm.inl" #undef tos } while (0); /* RETURN_CONTEXT_STACK_TOP ( val | -- val | ) */ do { #define val _extra1 #line 852 "vm.def" EXPORT_REGS (); unwind_context (); IMPORT_REGS (); SET_STACKTOP (val); FETCH; #line 5639 "vm.inl" #undef val } while (0); PUSH_OOP (_extra1); } NEXT_BC; bc125: { OOP _stack0; _stack0 = STACK_AT (0); /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 5657 "vm.inl" } while (0); /* LINE_NUMBER_BYTECODE ( -- ) */ do { #line 890 "vm.def" #line 5665 "vm.inl" } while (0); /* POP_STACK_TOP ( tos -- ) */ do { #define tos _stack0 #line 828 "vm.def" #line 5674 "vm.inl" #undef tos } while (0); /* PUSH_TEMPORARY_VARIABLE ( -- tos ) */ do { int n = 1; #define tos _stack0 #line 683 "vm.def" tos = METHOD_TEMPORARY (n); #line 5686 "vm.inl" #undef tos } while (0); STACK_AT (0) = _stack0; } NEXT_BC; bc126: { OOP _stack0; _stack0 = STACK_AT (0); /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 5704 "vm.inl" } while (0); /* LINE_NUMBER_BYTECODE ( -- ) */ do { #line 890 "vm.def" #line 5712 "vm.inl" } while (0); /* POP_STACK_TOP ( tos -- ) */ do { #define tos _stack0 #line 828 "vm.def" #line 5721 "vm.inl" #undef tos } while (0); /* PUSH_TEMPORARY_VARIABLE ( -- tos ) */ do { int n = 0; #define tos _stack0 #line 683 "vm.def" tos = METHOD_TEMPORARY (n); #line 5733 "vm.inl" #undef tos } while (0); STACK_AT (0) = _stack0; } NEXT_BC; bc127: { OOP _extra1, _extra2; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 5750 "vm.inl" } while (0); /* LINE_NUMBER_BYTECODE ( -- ) */ do { #line 890 "vm.def" #line 5758 "vm.inl" } while (0); /* PUSH_SELF ( -- tos ) */ do { #define tos _extra1 #line 893 "vm.def" tos = _gst_self; #line 5768 "vm.inl" #undef tos } while (0); /* PUSH_LIT_CONSTANT ( -- tos ) */ do { int n = 0; #define tos _extra2 #line 820 "vm.def" tos = METHOD_LITERAL (n); #line 5780 "vm.inl" #undef tos } while (0); PUSH_OOP (_extra1); PUSH_OOP (_extra2); } NEXT_BC; bc128: { OOP _extra1; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 5798 "vm.inl" } while (0); /* PUSH_LIT_CONSTANT ( -- tos ) */ do { int n = arg; #define tos _extra1 #line 820 "vm.def" tos = METHOD_LITERAL (n); #line 5809 "vm.inl" #undef tos } while (0); /* RETURN_CONTEXT_STACK_TOP ( val | -- val | ) */ do { #define val _extra1 #line 852 "vm.def" EXPORT_REGS (); unwind_context (); IMPORT_REGS (); SET_STACKTOP (val); FETCH; #line 5824 "vm.inl" #undef val } while (0); PUSH_OOP (_extra1); } NEXT_BC; bc129: { OOP _extra1; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 5841 "vm.inl" } while (0); /* PUSH_SELF ( -- tos ) */ do { #define tos _extra1 #line 893 "vm.def" tos = _gst_self; #line 5851 "vm.inl" #undef tos } while (0); /* SIZE_SPECIAL ( rec -- val ) */ do { #define PREPARE_STACK() do { \ PUSH_OOP (_extra1); \ } while (0) #define rec _extra1 #define val _extra1 #line 510 "vm.def" OOP classOOP; PREPARE_STACK (); EXPORT_REGS (); if UNCOMMON (IS_INT (rec)) { SEND_MESSAGE (_gst_builtin_selectors[SIZE_SPECIAL].symbol, 0); IMPORT_REGS (); FETCH; } if COMMON (size_cache_class == (classOOP = OOP_CLASS (rec)) && !execute_primitive_operation (size_cache_prim, 0)) { IMPORT_REGS (); NEXT_BC; } /* Not the same class that is in the cache, or the primitive failed -- send the message, and modify the cache if the send is resolved to a primitive. */ last_primitive = 0; SEND_MESSAGE (_gst_builtin_selectors[SIZE_SPECIAL].symbol, 0); IMPORT_REGS (); if COMMON (last_primitive) { size_cache_prim = last_primitive; size_cache_class = classOOP; NEXT_BC; } FETCH; #line 5895 "vm.inl" #undef PREPARE_STACK #undef rec #undef val } while (0); PUSH_OOP (_extra1); } NEXT_BC; bc130: { OOP _stack0; _stack0 = STACK_AT (0); /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 5915 "vm.inl" } while (0); /* IS_NIL_SPECIAL ( rec -- val ) */ do { #define rec _stack0 #define val _stack0 #line 576 "vm.def" /* DO_JUMP_LOOKAHEAD (rec == _gst_nil_oop); */ val = rec == _gst_nil_oop ? _gst_true_oop : _gst_false_oop; #line 5927 "vm.inl" #undef rec #undef val } while (0); /* POP_JUMP_TRUE ( tos -- ) */ do { int n = arg; #define PREPARE_STACK() do { \ STACK_AT (0) = _stack0; \ } while (0) #define tos _stack0 #line 793 "vm.def" if UNCOMMON (tos == _gst_true_oop) { PREPARE_STACK (); POP_N_OOPS(1); ip += n; FETCH; } else if UNCOMMON (tos != _gst_false_oop) { ip += n; PREPARE_STACK (); EXPORT_REGS(); SEND_MESSAGE(_gst_must_be_boolean_symbol, 0); IMPORT_REGS(); FETCH; } #line 5958 "vm.inl" #undef PREPARE_STACK #undef tos } while (0); POP_N_OOPS (1); } NEXT_BC; bc131: { OOP _stack0, _stack1; OOP _extra1; _stack1 = STACK_AT (1); _stack0 = STACK_AT (0); /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 5979 "vm.inl" } while (0); /* PUSH_TEMPORARY_VARIABLE ( -- tos ) */ do { int n = arg; #define tos _extra1 #line 683 "vm.def" tos = METHOD_TEMPORARY (n); #line 5990 "vm.inl" #undef tos } while (0); /* AT_PUT_SPECIAL ( rec idx val -- res ) */ do { #define PREPARE_STACK() do { \ PUSH_OOP (_extra1); \ } while (0) #define rec _stack1 #define idx _stack0 #define val _extra1 #define res _stack1 #line 477 "vm.def" OOP classOOP; PREPARE_STACK (); EXPORT_REGS (); if UNCOMMON (IS_INT (rec)) { SEND_MESSAGE (_gst_builtin_selectors[AT_PUT_SPECIAL].symbol, 2); IMPORT_REGS (); FETCH; } if COMMON (at_put_cache_class == (classOOP = OOP_CLASS (rec)) && !cached_index_oop_put_primitive (rec, idx, val, at_put_cache_spec)) { IMPORT_REGS (); NEXT_BC; } /* Not the same class that is in the cache, or the primitive failed -- send the message, and modify the cache if the send is resolved to a primitive. */ last_primitive = 0; SEND_MESSAGE (_gst_builtin_selectors[AT_PUT_SPECIAL].symbol, 2); IMPORT_REGS (); if (_gst_primitive_table[last_primitive].id == 61) { at_put_cache_spec = CLASS_INSTANCE_SPEC (classOOP); at_put_cache_class = classOOP; NEXT_BC; } FETCH; #line 6036 "vm.inl" #undef PREPARE_STACK #undef rec #undef idx #undef val #undef res } while (0); STACK_AT (1) = _stack1; POP_N_OOPS (1); } NEXT_BC; bc132: { OOP _extra1; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 6058 "vm.inl" } while (0); /* LINE_NUMBER_BYTECODE ( -- ) */ do { #line 890 "vm.def" #line 6066 "vm.inl" } while (0); /* PUSH_LIT_VARIABLE ( -- tos ) */ do { int n = 1; #define PREPARE_STACK() do { \ } while (0) #define tos _extra1 #line 702 "vm.def" tos = METHOD_LITERAL (n); if (UNCOMMON (IS_INT (tos)) || UNCOMMON (!is_a_kind_of (OOP_CLASS (tos), _gst_association_class))) { PREPARE_STACK (); PUSH_OOP (tos); EXPORT_REGS (); SEND_MESSAGE (_gst_builtin_selectors[VALUE_SPECIAL].symbol, 0); IMPORT_REGS (); FETCH; } else tos = ASSOCIATION_VALUE (tos); #line 6091 "vm.inl" #undef PREPARE_STACK #undef tos } while (0); PUSH_OOP (_extra1); } NEXT_BC; bc133: { OOP _stack0; OOP _extra1; _stack0 = STACK_AT (0); /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 6111 "vm.inl" } while (0); /* PUSH_TEMPORARY_VARIABLE ( -- tos ) */ do { int n = arg; #define tos _extra1 #line 683 "vm.def" tos = METHOD_TEMPORARY (n); #line 6122 "vm.inl" #undef tos } while (0); /* PLUS_SPECIAL ( op1 op2 -- op ) */ do { #define PREPARE_STACK() do { \ PUSH_OOP (_extra1); \ } while (0) #define op1 _stack0 #define op2 _extra1 #define op _stack0 #line 230 "vm.def" INTERP_BASIC_OP (op, op1, op2, add_with_check (op1, op2, &overflow), farg1 + farg2); PREPARE_STACK (); EXPORT_REGS (); SEND_MESSAGE (_gst_builtin_selectors[PLUS_SPECIAL].symbol, 1); IMPORT_REGS (); FETCH; #line 6145 "vm.inl" #undef PREPARE_STACK #undef op1 #undef op2 #undef op } while (0); STACK_AT (0) = _stack0; } NEXT_BC; bc134: { OOP _stack0; _stack0 = STACK_AT (0); /* ADVANCE ( -- ) */ do { #line 212 "vm.def" ip += 2; LOCAL_COUNTER++; #line 6166 "vm.inl" } while (0); /* POP_STACK_TOP ( tos -- ) */ do { #define tos _stack0 #line 828 "vm.def" #line 6175 "vm.inl" #undef tos } while (0); /* JUMP_BACK ( -- ) */ do { int n = arg; #define PREPARE_STACK() do { \ POP_N_OOPS (1); \ } while (0) #line 762 "vm.def" PREPARE_STACK (); ip -= n; FETCH; #line 6191 "vm.inl" #undef PREPARE_STACK } while (0); POP_N_OOPS (1); } NEXT_BC; bc135: { OOP _stack0; _stack0 = STACK_AT (0); /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 6209 "vm.inl" } while (0); /* POP_STACK_TOP ( tos -- ) */ do { #define tos _stack0 #line 828 "vm.def" #line 6218 "vm.inl" #undef tos } while (0); /* PUSH_LIT_VARIABLE ( -- tos ) */ do { int n = arg; #define PREPARE_STACK() do { \ POP_N_OOPS (1); \ } while (0) #define tos _stack0 #line 702 "vm.def" tos = METHOD_LITERAL (n); if (UNCOMMON (IS_INT (tos)) || UNCOMMON (!is_a_kind_of (OOP_CLASS (tos), _gst_association_class))) { PREPARE_STACK (); PUSH_OOP (tos); EXPORT_REGS (); SEND_MESSAGE (_gst_builtin_selectors[VALUE_SPECIAL].symbol, 0); IMPORT_REGS (); FETCH; } else tos = ASSOCIATION_VALUE (tos); #line 6245 "vm.inl" #undef PREPARE_STACK #undef tos } while (0); STACK_AT (0) = _stack0; } NEXT_BC; bc136: { OOP _extra1; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 6263 "vm.inl" } while (0); /* PUSH_INTEGER ( -- tos ) */ do { int n = 1; #define tos _extra1 #line 812 "vm.def" tos = FROM_INT (n); #line 6274 "vm.inl" #undef tos } while (0); /* STORE_TEMPORARY_VARIABLE ( tos | -- tos | ) */ do { int n = arg; #define tos _extra1 #line 722 "vm.def" STORE_METHOD_TEMPORARY (n, tos); #line 6286 "vm.inl" #undef tos } while (0); PUSH_OOP (_extra1); } NEXT_BC; bc137: { OOP _extra1; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 6303 "vm.inl" } while (0); /* PUSH_LIT_CONSTANT ( -- tos ) */ do { int n = arg; #define tos _extra1 #line 820 "vm.def" tos = METHOD_LITERAL (n); #line 6314 "vm.inl" #undef tos } while (0); /* SEND ( -- ) */ do { int sel = 2; int n = 1; #define PREPARE_STACK() do { \ PUSH_OOP (_extra1); \ } while (0) #line 643 "vm.def" PREPARE_STACK (); EXPORT_REGS (); SEND_MESSAGE (METHOD_LITERAL (sel), n); IMPORT_REGS (); FETCH; #line 6333 "vm.inl" #undef PREPARE_STACK } while (0); PUSH_OOP (_extra1); } NEXT_BC; bc138: { OOP _extra1; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 6350 "vm.inl" } while (0); /* LINE_NUMBER_BYTECODE ( -- ) */ do { #line 890 "vm.def" #line 6358 "vm.inl" } while (0); /* PUSH_TEMPORARY_VARIABLE ( -- tos ) */ do { int n = 3; #define tos _extra1 #line 683 "vm.def" tos = METHOD_TEMPORARY (n); #line 6369 "vm.inl" #undef tos } while (0); PUSH_OOP (_extra1); } NEXT_BC; bc139: { OOP _extra1; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 6386 "vm.inl" } while (0); /* LINE_NUMBER_BYTECODE ( -- ) */ do { #line 890 "vm.def" #line 6394 "vm.inl" } while (0); /* PUSH_OUTER_TEMP ( -- tos ) */ do { int n = 0; int scopes = 1; #define tos _extra1 #line 687 "vm.def" OOP contextOOP; gst_block_context context; context = (gst_block_context) OOP_TO_OBJ (_gst_this_context_oop); do { contextOOP = context->outerContext; context = (gst_block_context) OOP_TO_OBJ (contextOOP); } while (--scopes); tos = context->contextStack[n]; #line 6417 "vm.inl" #undef tos } while (0); PUSH_OOP (_extra1); } NEXT_BC; bc140: { OOP _extra1; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 6434 "vm.inl" } while (0); /* PUSH_RECEIVER_VARIABLE ( -- tos ) */ do { int n = arg; #define tos _extra1 #line 718 "vm.def" tos = RECEIVER_VARIABLE (n); #line 6445 "vm.inl" #undef tos } while (0); /* SEND ( -- ) */ do { int sel = 0; int n = 0; #define PREPARE_STACK() do { \ PUSH_OOP (_extra1); \ } while (0) #line 643 "vm.def" PREPARE_STACK (); EXPORT_REGS (); SEND_MESSAGE (METHOD_LITERAL (sel), n); IMPORT_REGS (); FETCH; #line 6464 "vm.inl" #undef PREPARE_STACK } while (0); PUSH_OOP (_extra1); } NEXT_BC; bc141: { OOP _stack0; OOP _extra1; _stack0 = STACK_AT (0); /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 6483 "vm.inl" } while (0); /* PUSH_INTEGER ( -- tos ) */ do { int n = arg; #define tos _extra1 #line 812 "vm.def" tos = FROM_INT (n); #line 6494 "vm.inl" #undef tos } while (0); /* GREATER_THAN_SPECIAL ( op1 op2 -- op ) */ do { #define PREPARE_STACK() do { \ PUSH_OOP (_extra1); \ } while (0) #define op1 _stack0 #define op2 _extra1 #define op _stack0 #line 261 "vm.def" PREPARE_STACK (); INTERP_BASIC_BOOL (op, op1, op2, >); EXPORT_REGS (); SEND_MESSAGE (_gst_builtin_selectors[GREATER_THAN_SPECIAL].symbol, 1); IMPORT_REGS (); FETCH; #line 6515 "vm.inl" #undef PREPARE_STACK #undef op1 #undef op2 #undef op } while (0); STACK_AT (0) = _stack0; } NEXT_BC; bc142: { OOP _extra1; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 6535 "vm.inl" } while (0); /* PUSH_TEMPORARY_VARIABLE ( -- tos ) */ do { int n = arg; #define tos _extra1 #line 683 "vm.def" tos = METHOD_TEMPORARY (n); #line 6546 "vm.inl" #undef tos } while (0); /* VALUE_SPECIAL ( rec | -- rec | ) */ do { #define PREPARE_STACK() do { \ PUSH_OOP (_extra1); \ } while (0) #define rec _extra1 #line 586 "vm.def" PREPARE_STACK (); EXPORT_REGS (); if (UNCOMMON (IS_INT (rec)) || UNCOMMON (OOP_CLASS (rec) != _gst_block_closure_class) || UNCOMMON (send_block_value (0, 0))) SEND_MESSAGE (_gst_builtin_selectors[VALUE_SPECIAL].symbol, 0); IMPORT_REGS (); FETCH; #line 6568 "vm.inl" #undef PREPARE_STACK #undef rec } while (0); PUSH_OOP (_extra1); } NEXT_BC; bc143: { OOP _stack0; OOP _extra1; _stack0 = STACK_AT (0); /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 6588 "vm.inl" } while (0); /* PUSH_TEMPORARY_VARIABLE ( -- tos ) */ do { int n = arg; #define tos _extra1 #line 683 "vm.def" tos = METHOD_TEMPORARY (n); #line 6599 "vm.inl" #undef tos } while (0); /* MINUS_SPECIAL ( op1 op2 -- op ) */ do { #define PREPARE_STACK() do { \ PUSH_OOP (_extra1); \ } while (0) #define op1 _stack0 #define op2 _extra1 #define op _stack0 #line 241 "vm.def" INTERP_BASIC_OP (op, op1, op2, sub_with_check (op1, op2, &overflow), farg1 - farg2); PREPARE_STACK (); EXPORT_REGS (); SEND_MESSAGE (_gst_builtin_selectors[MINUS_SPECIAL].symbol, 1); IMPORT_REGS (); FETCH; #line 6622 "vm.inl" #undef PREPARE_STACK #undef op1 #undef op2 #undef op } while (0); STACK_AT (0) = _stack0; } NEXT_BC; bc144: { OOP _extra1; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 6642 "vm.inl" } while (0); /* PUSH_LIT_CONSTANT ( -- tos ) */ do { int n = arg; #define tos _extra1 #line 820 "vm.def" tos = METHOD_LITERAL (n); #line 6653 "vm.inl" #undef tos } while (0); /* SEND ( -- ) */ do { int sel = 3; int n = 1; #define PREPARE_STACK() do { \ PUSH_OOP (_extra1); \ } while (0) #line 643 "vm.def" PREPARE_STACK (); EXPORT_REGS (); SEND_MESSAGE (METHOD_LITERAL (sel), n); IMPORT_REGS (); FETCH; #line 6672 "vm.inl" #undef PREPARE_STACK } while (0); PUSH_OOP (_extra1); } NEXT_BC; bc145: { OOP _stack0; OOP _extra1; _stack0 = STACK_AT (0); /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 6691 "vm.inl" } while (0); /* PUSH_SPECIAL ( -- tos ) */ do { int n = 0; #define tos _extra1 #line 816 "vm.def" tos = _gst_nil_oop + (n - NIL_INDEX); #line 6702 "vm.inl" #undef tos } while (0); /* SAME_OBJECT_SPECIAL ( op1 op2 -- op ) */ do { #define op1 _stack0 #define op2 _extra1 #define op _stack0 #line 610 "vm.def" /* DO_JUMP_LOOKAHEAD (op1 == op2); */ op = (op1 == op2) ? _gst_true_oop : _gst_false_oop; #line 6716 "vm.inl" #undef op1 #undef op2 #undef op } while (0); /* POP_JUMP_FALSE ( tos -- ) */ do { int n = arg; #define PREPARE_STACK() do { \ STACK_AT (0) = _stack0; \ } while (0) #define tos _stack0 #line 774 "vm.def" if UNCOMMON (tos == _gst_false_oop) { PREPARE_STACK (); POP_N_OOPS(1); ip += n; FETCH; } else if UNCOMMON (tos != _gst_true_oop) { ip += n; PREPARE_STACK (); EXPORT_REGS(); SEND_MESSAGE(_gst_must_be_boolean_symbol, 0); IMPORT_REGS(); FETCH; } #line 6748 "vm.inl" #undef PREPARE_STACK #undef tos } while (0); POP_N_OOPS (1); } NEXT_BC; bc146: { OOP _stack0; _stack0 = STACK_AT (0); /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 6767 "vm.inl" } while (0); /* STORE_TEMPORARY_VARIABLE ( tos | -- tos | ) */ do { int n = 2; #define tos _stack0 #line 722 "vm.def" STORE_METHOD_TEMPORARY (n, tos); #line 6778 "vm.inl" #undef tos } while (0); /* LINE_NUMBER_BYTECODE ( -- ) */ do { #line 890 "vm.def" #line 6787 "vm.inl" } while (0); /* POP_STACK_TOP ( tos -- ) */ do { #define tos _stack0 #line 828 "vm.def" #line 6796 "vm.inl" #undef tos } while (0); POP_N_OOPS (1); } NEXT_BC; bc147: { OOP _stack0, _stack1; _stack1 = STACK_AT (1); _stack0 = STACK_AT (0); /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 6815 "vm.inl" } while (0); /* SAME_OBJECT_SPECIAL ( op1 op2 -- op ) */ do { #define op1 _stack1 #define op2 _stack0 #define op _stack1 #line 610 "vm.def" /* DO_JUMP_LOOKAHEAD (op1 == op2); */ op = (op1 == op2) ? _gst_true_oop : _gst_false_oop; #line 6828 "vm.inl" #undef op1 #undef op2 #undef op } while (0); /* POP_JUMP_TRUE ( tos -- ) */ do { int n = arg; #define PREPARE_STACK() do { \ STACK_AT (1) = _stack1; \ POP_N_OOPS (1); \ } while (0) #define tos _stack1 #line 793 "vm.def" if UNCOMMON (tos == _gst_true_oop) { PREPARE_STACK (); POP_N_OOPS(1); ip += n; FETCH; } else if UNCOMMON (tos != _gst_false_oop) { ip += n; PREPARE_STACK (); EXPORT_REGS(); SEND_MESSAGE(_gst_must_be_boolean_symbol, 0); IMPORT_REGS(); FETCH; } #line 6861 "vm.inl" #undef PREPARE_STACK #undef tos } while (0); POP_N_OOPS (2); } NEXT_BC; bc148: { OOP _stack0; OOP _extra1; _stack0 = STACK_AT (0); /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 6881 "vm.inl" } while (0); /* PUSH_INTEGER ( -- tos ) */ do { int n = arg; #define tos _extra1 #line 812 "vm.def" tos = FROM_INT (n); #line 6892 "vm.inl" #undef tos } while (0); /* TIMES_SPECIAL ( op1 op2 -- op ) */ do { #define PREPARE_STACK() do { \ PUSH_OOP (_extra1); \ } while (0) #define op1 _stack0 #define op2 _extra1 #define op _stack0 #line 306 "vm.def" INTERP_BASIC_OP (op, op1, op2, mul_with_check (op1, op2, &overflow), farg1 * farg2); PREPARE_STACK (); EXPORT_REGS (); SEND_MESSAGE (_gst_builtin_selectors[TIMES_SPECIAL].symbol, 1); IMPORT_REGS (); FETCH; #line 6915 "vm.inl" #undef PREPARE_STACK #undef op1 #undef op2 #undef op } while (0); STACK_AT (0) = _stack0; } NEXT_BC; bc149: { OOP _extra1; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 6935 "vm.inl" } while (0); /* LINE_NUMBER_BYTECODE ( -- ) */ do { #line 890 "vm.def" #line 6943 "vm.inl" } while (0); /* PUSH_RECEIVER_VARIABLE ( -- tos ) */ do { int n = 2; #define tos _extra1 #line 718 "vm.def" tos = RECEIVER_VARIABLE (n); #line 6954 "vm.inl" #undef tos } while (0); PUSH_OOP (_extra1); } NEXT_BC; bc150: { OOP _stack0; OOP _extra1; _stack0 = STACK_AT (0); /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 6973 "vm.inl" } while (0); /* PUSH_INTEGER ( -- tos ) */ do { int n = arg; #define tos _extra1 #line 812 "vm.def" tos = FROM_INT (n); #line 6984 "vm.inl" #undef tos } while (0); /* LESS_THAN_SPECIAL ( op1 op2 -- op ) */ do { #define PREPARE_STACK() do { \ PUSH_OOP (_extra1); \ } while (0) #define op1 _stack0 #define op2 _extra1 #define op _stack0 #line 252 "vm.def" PREPARE_STACK (); INTERP_BASIC_BOOL (op, op1, op2, <); EXPORT_REGS (); SEND_MESSAGE (_gst_builtin_selectors[LESS_THAN_SPECIAL].symbol, 1); IMPORT_REGS (); FETCH; #line 7005 "vm.inl" #undef PREPARE_STACK #undef op1 #undef op2 #undef op } while (0); STACK_AT (0) = _stack0; } NEXT_BC; bc151: { OOP _stack0, _stack1; OOP _extra1; _stack1 = STACK_AT (1); _stack0 = STACK_AT (0); /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 7028 "vm.inl" } while (0); /* PUSH_LIT_CONSTANT ( -- tos ) */ do { int n = arg; #define tos _extra1 #line 820 "vm.def" tos = METHOD_LITERAL (n); #line 7039 "vm.inl" #undef tos } while (0); /* AT_PUT_SPECIAL ( rec idx val -- res ) */ do { #define PREPARE_STACK() do { \ PUSH_OOP (_extra1); \ } while (0) #define rec _stack1 #define idx _stack0 #define val _extra1 #define res _stack1 #line 477 "vm.def" OOP classOOP; PREPARE_STACK (); EXPORT_REGS (); if UNCOMMON (IS_INT (rec)) { SEND_MESSAGE (_gst_builtin_selectors[AT_PUT_SPECIAL].symbol, 2); IMPORT_REGS (); FETCH; } if COMMON (at_put_cache_class == (classOOP = OOP_CLASS (rec)) && !cached_index_oop_put_primitive (rec, idx, val, at_put_cache_spec)) { IMPORT_REGS (); NEXT_BC; } /* Not the same class that is in the cache, or the primitive failed -- send the message, and modify the cache if the send is resolved to a primitive. */ last_primitive = 0; SEND_MESSAGE (_gst_builtin_selectors[AT_PUT_SPECIAL].symbol, 2); IMPORT_REGS (); if (_gst_primitive_table[last_primitive].id == 61) { at_put_cache_spec = CLASS_INSTANCE_SPEC (classOOP); at_put_cache_class = classOOP; NEXT_BC; } FETCH; #line 7085 "vm.inl" #undef PREPARE_STACK #undef rec #undef idx #undef val #undef res } while (0); STACK_AT (1) = _stack1; POP_N_OOPS (1); } NEXT_BC; bc152: { OOP _extra1; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 7107 "vm.inl" } while (0); /* PUSH_OUTER_TEMP ( -- tos ) */ do { int n = arg; int scopes = 2; #define tos _extra1 #line 687 "vm.def" OOP contextOOP; gst_block_context context; context = (gst_block_context) OOP_TO_OBJ (_gst_this_context_oop); do { contextOOP = context->outerContext; context = (gst_block_context) OOP_TO_OBJ (contextOOP); } while (--scopes); tos = context->contextStack[n]; #line 7130 "vm.inl" #undef tos } while (0); PUSH_OOP (_extra1); } NEXT_BC; bc153: { OOP _extra1, _extra2; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 7147 "vm.inl" } while (0); /* LINE_NUMBER_BYTECODE ( -- ) */ do { #line 890 "vm.def" #line 7155 "vm.inl" } while (0); /* PUSH_SELF ( -- tos ) */ do { #define tos _extra1 #line 893 "vm.def" tos = _gst_self; #line 7165 "vm.inl" #undef tos } while (0); /* PUSH_TEMPORARY_VARIABLE ( -- tos ) */ do { int n = 0; #define tos _extra2 #line 683 "vm.def" tos = METHOD_TEMPORARY (n); #line 7177 "vm.inl" #undef tos } while (0); /* SEND ( -- ) */ do { int sel = 0; int n = 1; #define PREPARE_STACK() do { \ PUSH_OOP (_extra1); \ PUSH_OOP (_extra2); \ } while (0) #line 643 "vm.def" PREPARE_STACK (); EXPORT_REGS (); SEND_MESSAGE (METHOD_LITERAL (sel), n); IMPORT_REGS (); FETCH; #line 7197 "vm.inl" #undef PREPARE_STACK } while (0); PUSH_OOP (_extra1); PUSH_OOP (_extra2); } NEXT_BC; bc154: { OOP _extra1, _extra2; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 7215 "vm.inl" } while (0); /* PUSH_SELF ( -- tos ) */ do { #define tos _extra1 #line 893 "vm.def" tos = _gst_self; #line 7225 "vm.inl" #undef tos } while (0); /* PUSH_TEMPORARY_VARIABLE ( -- tos ) */ do { int n = 0; #define tos _extra2 #line 683 "vm.def" tos = METHOD_TEMPORARY (n); #line 7237 "vm.inl" #undef tos } while (0); /* SEND ( -- ) */ do { int sel = arg; int n = 1; #define PREPARE_STACK() do { \ PUSH_OOP (_extra1); \ PUSH_OOP (_extra2); \ } while (0) #line 643 "vm.def" PREPARE_STACK (); EXPORT_REGS (); SEND_MESSAGE (METHOD_LITERAL (sel), n); IMPORT_REGS (); FETCH; #line 7257 "vm.inl" #undef PREPARE_STACK } while (0); PUSH_OOP (_extra1); PUSH_OOP (_extra2); } NEXT_BC; bc155: { OOP _extra1; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 7275 "vm.inl" } while (0); /* LINE_NUMBER_BYTECODE ( -- ) */ do { #line 890 "vm.def" #line 7283 "vm.inl" } while (0); /* PUSH_SELF ( -- tos ) */ do { #define tos _extra1 #line 893 "vm.def" tos = _gst_self; #line 7293 "vm.inl" #undef tos } while (0); /* SEND_IMMEDIATE ( -- ) */ do { int n = 40; #define PREPARE_STACK() do { \ PUSH_OOP (_extra1); \ } while (0) #line 662 "vm.def" const struct builtin_selector *bs = &_gst_builtin_selectors[n]; PREPARE_STACK (); EXPORT_REGS (); SEND_MESSAGE (bs->symbol, bs->numArgs); IMPORT_REGS (); FETCH; #line 7312 "vm.inl" #undef PREPARE_STACK } while (0); PUSH_OOP (_extra1); } NEXT_BC; bc156: { OOP _extra1, _extra2; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 7329 "vm.inl" } while (0); /* PUSH_TEMPORARY_VARIABLE ( -- tos ) */ do { int n = arg; #define tos _extra1 #line 683 "vm.def" tos = METHOD_TEMPORARY (n); #line 7340 "vm.inl" #undef tos } while (0); /* PUSH_TEMPORARY_VARIABLE ( -- tos ) */ do { int n = 3; #define tos _extra2 #line 683 "vm.def" tos = METHOD_TEMPORARY (n); #line 7352 "vm.inl" #undef tos } while (0); PUSH_OOP (_extra1); PUSH_OOP (_extra2); } NEXT_BC; bc157: { OOP _stack0; _stack0 = STACK_AT (0); /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 7371 "vm.inl" } while (0); /* STORE_TEMPORARY_VARIABLE ( tos | -- tos | ) */ do { int n = 1; #define tos _stack0 #line 722 "vm.def" STORE_METHOD_TEMPORARY (n, tos); #line 7382 "vm.inl" #undef tos } while (0); /* LINE_NUMBER_BYTECODE ( -- ) */ do { #line 890 "vm.def" #line 7391 "vm.inl" } while (0); } NEXT_BC; bc158: { OOP _extra1; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 7406 "vm.inl" } while (0); /* LINE_NUMBER_BYTECODE ( -- ) */ do { #line 890 "vm.def" #line 7414 "vm.inl" } while (0); /* PUSH_TEMPORARY_VARIABLE ( -- tos ) */ do { int n = 0; #define tos _extra1 #line 683 "vm.def" tos = METHOD_TEMPORARY (n); #line 7425 "vm.inl" #undef tos } while (0); /* SEND ( -- ) */ do { int sel = 0; int n = 0; #define PREPARE_STACK() do { \ PUSH_OOP (_extra1); \ } while (0) #line 643 "vm.def" PREPARE_STACK (); EXPORT_REGS (); SEND_MESSAGE (METHOD_LITERAL (sel), n); IMPORT_REGS (); FETCH; #line 7444 "vm.inl" #undef PREPARE_STACK } while (0); PUSH_OOP (_extra1); } NEXT_BC; bc159: { OOP _stack0; OOP _extra1; _stack0 = STACK_AT (0); /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 7463 "vm.inl" } while (0); /* PUSH_INTEGER ( -- tos ) */ do { int n = arg; #define tos _extra1 #line 812 "vm.def" tos = FROM_INT (n); #line 7474 "vm.inl" #undef tos } while (0); /* BIT_AND_SPECIAL ( op1 op2 -- op ) */ do { #define PREPARE_STACK() do { \ PUSH_OOP (_extra1); \ } while (0) #define op1 _stack0 #define op2 _extra1 #define op _stack0 #line 418 "vm.def" op = tagged_and (op1, op2); if COMMON (IS_INT (op)) break; PREPARE_STACK (); EXPORT_REGS (); SEND_MESSAGE (_gst_builtin_selectors[BIT_AND_SPECIAL].symbol, 1); IMPORT_REGS (); FETCH; #line 7498 "vm.inl" #undef PREPARE_STACK #undef op1 #undef op2 #undef op } while (0); STACK_AT (0) = _stack0; } NEXT_BC; bc160: { OOP _extra1; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 7518 "vm.inl" } while (0); /* PUSH_TEMPORARY_VARIABLE ( -- tos ) */ do { int n = 2; #define tos _extra1 #line 683 "vm.def" tos = METHOD_TEMPORARY (n); #line 7529 "vm.inl" #undef tos } while (0); /* SEND ( -- ) */ do { int sel = arg; int n = 0; #define PREPARE_STACK() do { \ PUSH_OOP (_extra1); \ } while (0) #line 643 "vm.def" PREPARE_STACK (); EXPORT_REGS (); SEND_MESSAGE (METHOD_LITERAL (sel), n); IMPORT_REGS (); FETCH; #line 7548 "vm.inl" #undef PREPARE_STACK } while (0); PUSH_OOP (_extra1); } NEXT_BC; bc161: { OOP _extra1, _extra2; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 7565 "vm.inl" } while (0); /* PUSH_TEMPORARY_VARIABLE ( -- tos ) */ do { int n = 0; #define tos _extra1 #line 683 "vm.def" tos = METHOD_TEMPORARY (n); #line 7576 "vm.inl" #undef tos } while (0); /* PUSH_TEMPORARY_VARIABLE ( -- tos ) */ do { int n = 1; #define tos _extra2 #line 683 "vm.def" tos = METHOD_TEMPORARY (n); #line 7588 "vm.inl" #undef tos } while (0); /* SEND ( -- ) */ do { int sel = arg >> 8; int n = arg & 255; #define PREPARE_STACK() do { \ PUSH_OOP (_extra1); \ PUSH_OOP (_extra2); \ } while (0) #line 643 "vm.def" PREPARE_STACK (); EXPORT_REGS (); SEND_MESSAGE (METHOD_LITERAL (sel), n); IMPORT_REGS (); FETCH; #line 7608 "vm.inl" #undef PREPARE_STACK } while (0); PUSH_OOP (_extra1); PUSH_OOP (_extra2); } NEXT_BC; bc162: { OOP _extra1, _extra2; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 7626 "vm.inl" } while (0); /* LINE_NUMBER_BYTECODE ( -- ) */ do { #line 890 "vm.def" #line 7634 "vm.inl" } while (0); /* PUSH_SELF ( -- tos ) */ do { #define tos _extra1 #line 893 "vm.def" tos = _gst_self; #line 7644 "vm.inl" #undef tos } while (0); /* PUSH_TEMPORARY_VARIABLE ( -- tos ) */ do { int n = 0; #define tos _extra2 #line 683 "vm.def" tos = METHOD_TEMPORARY (n); #line 7656 "vm.inl" #undef tos } while (0); PUSH_OOP (_extra1); PUSH_OOP (_extra2); } NEXT_BC; bc163: { OOP _extra1; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 7674 "vm.inl" } while (0); /* LINE_NUMBER_BYTECODE ( -- ) */ do { #line 890 "vm.def" #line 7682 "vm.inl" } while (0); /* PUSH_RECEIVER_VARIABLE ( -- tos ) */ do { int n = 3; #define tos _extra1 #line 718 "vm.def" tos = RECEIVER_VARIABLE (n); #line 7693 "vm.inl" #undef tos } while (0); PUSH_OOP (_extra1); } NEXT_BC; bc164: { OOP _extra1; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 7710 "vm.inl" } while (0); /* PUSH_TEMPORARY_VARIABLE ( -- tos ) */ do { int n = 2; #define tos _extra1 #line 683 "vm.def" tos = METHOD_TEMPORARY (n); #line 7721 "vm.inl" #undef tos } while (0); /* SEND ( -- ) */ do { int sel = arg; int n = 1; #define PREPARE_STACK() do { \ PUSH_OOP (_extra1); \ } while (0) #line 643 "vm.def" PREPARE_STACK (); EXPORT_REGS (); SEND_MESSAGE (METHOD_LITERAL (sel), n); IMPORT_REGS (); FETCH; #line 7740 "vm.inl" #undef PREPARE_STACK } while (0); PUSH_OOP (_extra1); } NEXT_BC; bc165: { OOP _stack0; _stack0 = STACK_AT (0); /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 7758 "vm.inl" } while (0); /* NOT_NIL_SPECIAL ( rec -- val ) */ do { #define rec _stack0 #define val _stack0 #line 581 "vm.def" /* DO_JUMP_LOOKAHEAD (rec != _gst_nil_oop); */ val = rec != _gst_nil_oop ? _gst_true_oop : _gst_false_oop; #line 7770 "vm.inl" #undef rec #undef val } while (0); /* POP_JUMP_FALSE ( tos -- ) */ do { int n = arg; #define PREPARE_STACK() do { \ STACK_AT (0) = _stack0; \ } while (0) #define tos _stack0 #line 774 "vm.def" if UNCOMMON (tos == _gst_false_oop) { PREPARE_STACK (); POP_N_OOPS(1); ip += n; FETCH; } else if UNCOMMON (tos != _gst_true_oop) { ip += n; PREPARE_STACK (); EXPORT_REGS(); SEND_MESSAGE(_gst_must_be_boolean_symbol, 0); IMPORT_REGS(); FETCH; } #line 7801 "vm.inl" #undef PREPARE_STACK #undef tos } while (0); POP_N_OOPS (1); } NEXT_BC; bc166: { OOP _stack0; _stack0 = STACK_AT (0); /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 7820 "vm.inl" } while (0); /* STORE_TEMPORARY_VARIABLE ( tos | -- tos | ) */ do { int n = 2; #define tos _stack0 #line 722 "vm.def" STORE_METHOD_TEMPORARY (n, tos); #line 7831 "vm.inl" #undef tos } while (0); /* LINE_NUMBER_BYTECODE ( -- ) */ do { #line 890 "vm.def" #line 7840 "vm.inl" } while (0); } NEXT_BC; bc167: { OOP _stack0; _stack0 = STACK_AT (0); /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 7856 "vm.inl" } while (0); /* STORE_TEMPORARY_VARIABLE ( tos | -- tos | ) */ do { int n = 3; #define tos _stack0 #line 722 "vm.def" STORE_METHOD_TEMPORARY (n, tos); #line 7867 "vm.inl" #undef tos } while (0); /* LINE_NUMBER_BYTECODE ( -- ) */ do { #line 890 "vm.def" #line 7876 "vm.inl" } while (0); /* POP_STACK_TOP ( tos -- ) */ do { #define tos _stack0 #line 828 "vm.def" #line 7885 "vm.inl" #undef tos } while (0); POP_N_OOPS (1); } NEXT_BC; bc168: { OOP _extra1; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 7902 "vm.inl" } while (0); /* PUSH_LIT_CONSTANT ( -- tos ) */ do { int n = 1; #define tos _extra1 #line 820 "vm.def" tos = METHOD_LITERAL (n); #line 7913 "vm.inl" #undef tos } while (0); /* SEND_IMMEDIATE ( -- ) */ do { int n = arg; #define PREPARE_STACK() do { \ PUSH_OOP (_extra1); \ } while (0) #line 662 "vm.def" const struct builtin_selector *bs = &_gst_builtin_selectors[n]; PREPARE_STACK (); EXPORT_REGS (); SEND_MESSAGE (bs->symbol, bs->numArgs); IMPORT_REGS (); FETCH; #line 7932 "vm.inl" #undef PREPARE_STACK } while (0); PUSH_OOP (_extra1); } NEXT_BC; bc169: { OOP _stack0; OOP _extra1; _stack0 = STACK_AT (0); /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 7951 "vm.inl" } while (0); /* PUSH_TEMPORARY_VARIABLE ( -- tos ) */ do { int n = arg; #define tos _extra1 #line 683 "vm.def" tos = METHOD_TEMPORARY (n); #line 7962 "vm.inl" #undef tos } while (0); /* EQUAL_SPECIAL ( op1 op2 -- op ) */ do { #define PREPARE_STACK() do { \ PUSH_OOP (_extra1); \ } while (0) #define op1 _stack0 #define op2 _extra1 #define op _stack0 #line 288 "vm.def" PREPARE_STACK (); INTERP_BASIC_BOOL (op, op1, op2, ==); EXPORT_REGS (); SEND_MESSAGE (_gst_builtin_selectors[EQUAL_SPECIAL].symbol, 1); IMPORT_REGS (); FETCH; #line 7983 "vm.inl" #undef PREPARE_STACK #undef op1 #undef op2 #undef op } while (0); STACK_AT (0) = _stack0; } NEXT_BC; bc170: { OOP _stack0, _stack1; OOP _extra1, _extra2; _stack1 = STACK_AT (1); _stack0 = STACK_AT (0); /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 8006 "vm.inl" } while (0); /* POP_STACK_TOP ( tos -- ) */ do { #define tos _stack0 #line 828 "vm.def" #line 8015 "vm.inl" #undef tos } while (0); /* DUP_STACK_TOP ( tos | -- tos | tos2 ) */ do { #define tos _stack1 #define tos2 _stack0 #line 860 "vm.def" tos2 = tos; #line 8027 "vm.inl" #undef tos #undef tos2 } while (0); /* PUSH_TEMPORARY_VARIABLE ( -- tos ) */ do { int n = arg; #define tos _extra1 #line 683 "vm.def" tos = METHOD_TEMPORARY (n); #line 8040 "vm.inl" #undef tos } while (0); /* PUSH_INTEGER ( -- tos ) */ do { int n = 1; #define tos _extra2 #line 812 "vm.def" tos = FROM_INT (n); #line 8052 "vm.inl" #undef tos } while (0); /* PLUS_SPECIAL ( op1 op2 -- op ) */ do { #define PREPARE_STACK() do { \ STACK_AT (0) = _stack0; \ PUSH_OOP (_extra1); \ PUSH_OOP (_extra2); \ } while (0) #define op1 _extra1 #define op2 _extra2 #define op _extra1 #line 230 "vm.def" INTERP_BASIC_OP (op, op1, op2, add_with_check (op1, op2, &overflow), farg1 + farg2); PREPARE_STACK (); EXPORT_REGS (); SEND_MESSAGE (_gst_builtin_selectors[PLUS_SPECIAL].symbol, 1); IMPORT_REGS (); FETCH; #line 8077 "vm.inl" #undef PREPARE_STACK #undef op1 #undef op2 #undef op } while (0); STACK_AT (0) = _stack0; PUSH_OOP (_extra1); } NEXT_BC; bc171: { OOP _extra1; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 8098 "vm.inl" } while (0); /* PUSH_SELF ( -- tos ) */ do { #define tos _extra1 #line 893 "vm.def" tos = _gst_self; #line 8108 "vm.inl" #undef tos } while (0); /* SEND ( -- ) */ do { int sel = arg; int n = 1; #define PREPARE_STACK() do { \ PUSH_OOP (_extra1); \ } while (0) #line 643 "vm.def" PREPARE_STACK (); EXPORT_REGS (); SEND_MESSAGE (METHOD_LITERAL (sel), n); IMPORT_REGS (); FETCH; #line 8127 "vm.inl" #undef PREPARE_STACK } while (0); PUSH_OOP (_extra1); } NEXT_BC; bc172: { OOP _stack0; _stack0 = STACK_AT (0); /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 8145 "vm.inl" } while (0); /* STORE_TEMPORARY_VARIABLE ( tos | -- tos | ) */ do { int n = 0; #define tos _stack0 #line 722 "vm.def" STORE_METHOD_TEMPORARY (n, tos); #line 8156 "vm.inl" #undef tos } while (0); /* LINE_NUMBER_BYTECODE ( -- ) */ do { #line 890 "vm.def" #line 8165 "vm.inl" } while (0); /* POP_STACK_TOP ( tos -- ) */ do { #define tos _stack0 #line 828 "vm.def" #line 8174 "vm.inl" #undef tos } while (0); POP_N_OOPS (1); } NEXT_BC; bc173: { OOP _stack0; OOP _extra1; _stack0 = STACK_AT (0); /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 8193 "vm.inl" } while (0); /* DUP_STACK_TOP ( tos | -- tos | tos2 ) */ do { #define tos _stack0 #define tos2 _extra1 #line 860 "vm.def" tos2 = tos; #line 8204 "vm.inl" #undef tos #undef tos2 } while (0); /* LINE_NUMBER_BYTECODE ( -- ) */ do { #line 890 "vm.def" #line 8214 "vm.inl" } while (0); PUSH_OOP (_extra1); } NEXT_BC; bc174: { OOP _extra1, _extra2; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 8230 "vm.inl" } while (0); /* PUSH_SELF ( -- tos ) */ do { #define tos _extra1 #line 893 "vm.def" tos = _gst_self; #line 8240 "vm.inl" #undef tos } while (0); /* PUSH_LIT_CONSTANT ( -- tos ) */ do { int n = arg; #define tos _extra2 #line 820 "vm.def" tos = METHOD_LITERAL (n); #line 8252 "vm.inl" #undef tos } while (0); /* SEND_IMMEDIATE ( -- ) */ do { int n = 49; #define PREPARE_STACK() do { \ PUSH_OOP (_extra1); \ PUSH_OOP (_extra2); \ } while (0) #line 662 "vm.def" const struct builtin_selector *bs = &_gst_builtin_selectors[n]; PREPARE_STACK (); EXPORT_REGS (); SEND_MESSAGE (bs->symbol, bs->numArgs); IMPORT_REGS (); FETCH; #line 8272 "vm.inl" #undef PREPARE_STACK } while (0); PUSH_OOP (_extra1); PUSH_OOP (_extra2); } NEXT_BC; bc175: { OOP _stack0; _stack0 = STACK_AT (0); /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 8291 "vm.inl" } while (0); /* POP_STACK_TOP ( tos -- ) */ do { #define tos _stack0 #line 828 "vm.def" #line 8300 "vm.inl" #undef tos } while (0); /* PUSH_RECEIVER_VARIABLE ( -- tos ) */ do { int n = arg; #define tos _stack0 #line 718 "vm.def" tos = RECEIVER_VARIABLE (n); #line 8312 "vm.inl" #undef tos } while (0); STACK_AT (0) = _stack0; } NEXT_BC; bc176: { OOP _extra1; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 8329 "vm.inl" } while (0); /* LINE_NUMBER_BYTECODE ( -- ) */ do { #line 890 "vm.def" #line 8337 "vm.inl" } while (0); /* PUSH_SELF ( -- tos ) */ do { #define tos _extra1 #line 893 "vm.def" tos = _gst_self; #line 8347 "vm.inl" #undef tos } while (0); /* SEND_IMMEDIATE ( -- ) */ do { int n = 84; #define PREPARE_STACK() do { \ PUSH_OOP (_extra1); \ } while (0) #line 662 "vm.def" const struct builtin_selector *bs = &_gst_builtin_selectors[n]; PREPARE_STACK (); EXPORT_REGS (); SEND_MESSAGE (bs->symbol, bs->numArgs); IMPORT_REGS (); FETCH; #line 8366 "vm.inl" #undef PREPARE_STACK } while (0); PUSH_OOP (_extra1); } NEXT_BC; bc177: { OOP _extra1; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 8383 "vm.inl" } while (0); /* LINE_NUMBER_BYTECODE ( -- ) */ do { #line 890 "vm.def" #line 8391 "vm.inl" } while (0); /* PUSH_LIT_VARIABLE ( -- tos ) */ do { int n = 2; #define PREPARE_STACK() do { \ } while (0) #define tos _extra1 #line 702 "vm.def" tos = METHOD_LITERAL (n); if (UNCOMMON (IS_INT (tos)) || UNCOMMON (!is_a_kind_of (OOP_CLASS (tos), _gst_association_class))) { PREPARE_STACK (); PUSH_OOP (tos); EXPORT_REGS (); SEND_MESSAGE (_gst_builtin_selectors[VALUE_SPECIAL].symbol, 0); IMPORT_REGS (); FETCH; } else tos = ASSOCIATION_VALUE (tos); #line 8416 "vm.inl" #undef PREPARE_STACK #undef tos } while (0); PUSH_OOP (_extra1); } NEXT_BC; bc178: { OOP _extra1; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 8434 "vm.inl" } while (0); /* PUSH_LIT_CONSTANT ( -- tos ) */ do { int n = arg; #define tos _extra1 #line 820 "vm.def" tos = METHOD_LITERAL (n); #line 8445 "vm.inl" #undef tos } while (0); /* MAKE_DIRTY_BLOCK ( block -- closure ) */ do { #define block _extra1 #define closure _extra1 #line 831 "vm.def" EXPORT_REGS (); closure = _gst_make_block_closure (block); IMPORT_REGS(); #line 8459 "vm.inl" #undef block #undef closure } while (0); /* SEND ( -- ) */ do { int sel = 3; int n = 1; #define PREPARE_STACK() do { \ PUSH_OOP (_extra1); \ } while (0) #line 643 "vm.def" PREPARE_STACK (); EXPORT_REGS (); SEND_MESSAGE (METHOD_LITERAL (sel), n); IMPORT_REGS (); FETCH; #line 8479 "vm.inl" #undef PREPARE_STACK } while (0); PUSH_OOP (_extra1); } NEXT_BC; bc179: { OOP _extra1; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 8496 "vm.inl" } while (0); /* LINE_NUMBER_BYTECODE ( -- ) */ do { #line 890 "vm.def" #line 8504 "vm.inl" } while (0); /* PUSH_LIT_CONSTANT ( -- tos ) */ do { int n = 0; #define tos _extra1 #line 820 "vm.def" tos = METHOD_LITERAL (n); #line 8515 "vm.inl" #undef tos } while (0); PUSH_OOP (_extra1); } NEXT_BC; bc180: { OOP _stack0; OOP _extra1, _extra2; _stack0 = STACK_AT (0); /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 8534 "vm.inl" } while (0); /* DUP_STACK_TOP ( tos | -- tos | tos2 ) */ do { #define tos _stack0 #define tos2 _extra1 #line 860 "vm.def" tos2 = tos; #line 8545 "vm.inl" #undef tos #undef tos2 } while (0); /* PUSH_LIT_CONSTANT ( -- tos ) */ do { int n = arg; #define tos _extra2 #line 820 "vm.def" tos = METHOD_LITERAL (n); #line 8558 "vm.inl" #undef tos } while (0); /* SEND_IMMEDIATE ( -- ) */ do { int n = 36; #define PREPARE_STACK() do { \ PUSH_OOP (_extra1); \ PUSH_OOP (_extra2); \ } while (0) #line 662 "vm.def" const struct builtin_selector *bs = &_gst_builtin_selectors[n]; PREPARE_STACK (); EXPORT_REGS (); SEND_MESSAGE (bs->symbol, bs->numArgs); IMPORT_REGS (); FETCH; #line 8578 "vm.inl" #undef PREPARE_STACK } while (0); PUSH_OOP (_extra1); PUSH_OOP (_extra2); } NEXT_BC; bc181: { OOP _extra1; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 8596 "vm.inl" } while (0); /* LINE_NUMBER_BYTECODE ( -- ) */ do { #line 890 "vm.def" #line 8604 "vm.inl" } while (0); /* PUSH_OUTER_TEMP ( -- tos ) */ do { int n = 1; int scopes = 1; #define tos _extra1 #line 687 "vm.def" OOP contextOOP; gst_block_context context; context = (gst_block_context) OOP_TO_OBJ (_gst_this_context_oop); do { contextOOP = context->outerContext; context = (gst_block_context) OOP_TO_OBJ (contextOOP); } while (--scopes); tos = context->contextStack[n]; #line 8627 "vm.inl" #undef tos } while (0); PUSH_OOP (_extra1); } NEXT_BC; bc182: { OOP _stack0; OOP _extra1; _stack0 = STACK_AT (0); /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 8646 "vm.inl" } while (0); /* PUSH_INTEGER ( -- tos ) */ do { int n = arg; #define tos _extra1 #line 812 "vm.def" tos = FROM_INT (n); #line 8657 "vm.inl" #undef tos } while (0); /* INTEGER_DIVIDE_SPECIAL ( op1 op2 | -- op1 op2 | ) */ do { #define PREPARE_STACK() do { \ PUSH_OOP (_extra1); \ } while (0) #define op1 _stack0 #define op2 _extra1 #line 403 "vm.def" PREPARE_STACK (); EXPORT_REGS(); if (IS_INT (op1) && IS_INT (op2) && !VMpr_SmallInteger_intDiv (12, 1)) { IMPORT_REGS (); NEXT_BC; } SEND_MESSAGE (_gst_builtin_selectors[INTEGER_DIVIDE_SPECIAL].symbol, 1); IMPORT_REGS (); FETCH; #line 8683 "vm.inl" #undef PREPARE_STACK #undef op1 #undef op2 } while (0); PUSH_OOP (_extra1); } NEXT_BC; bc183: { OOP _extra1; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 8702 "vm.inl" } while (0); /* PUSH_LIT_CONSTANT ( -- tos ) */ do { int n = 1; #define tos _extra1 #line 820 "vm.def" tos = METHOD_LITERAL (n); #line 8713 "vm.inl" #undef tos } while (0); /* MAKE_DIRTY_BLOCK ( block -- closure ) */ do { #define block _extra1 #define closure _extra1 #line 831 "vm.def" EXPORT_REGS (); closure = _gst_make_block_closure (block); IMPORT_REGS(); #line 8727 "vm.inl" #undef block #undef closure } while (0); /* SEND_IMMEDIATE ( -- ) */ do { int n = arg; #define PREPARE_STACK() do { \ PUSH_OOP (_extra1); \ } while (0) #line 662 "vm.def" const struct builtin_selector *bs = &_gst_builtin_selectors[n]; PREPARE_STACK (); EXPORT_REGS (); SEND_MESSAGE (bs->symbol, bs->numArgs); IMPORT_REGS (); FETCH; #line 8747 "vm.inl" #undef PREPARE_STACK } while (0); PUSH_OOP (_extra1); } NEXT_BC; bc184: { OOP _extra1; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 8764 "vm.inl" } while (0); /* PUSH_TEMPORARY_VARIABLE ( -- tos ) */ do { int n = 3; #define tos _extra1 #line 683 "vm.def" tos = METHOD_TEMPORARY (n); #line 8775 "vm.inl" #undef tos } while (0); /* SEND_IMMEDIATE ( -- ) */ do { int n = arg; #define PREPARE_STACK() do { \ PUSH_OOP (_extra1); \ } while (0) #line 662 "vm.def" const struct builtin_selector *bs = &_gst_builtin_selectors[n]; PREPARE_STACK (); EXPORT_REGS (); SEND_MESSAGE (bs->symbol, bs->numArgs); IMPORT_REGS (); FETCH; #line 8794 "vm.inl" #undef PREPARE_STACK } while (0); PUSH_OOP (_extra1); } NEXT_BC; bc185: { OOP _extra1; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 8811 "vm.inl" } while (0); /* LINE_NUMBER_BYTECODE ( -- ) */ do { #line 890 "vm.def" #line 8819 "vm.inl" } while (0); /* PUSH_SPECIAL ( -- tos ) */ do { int n = 0; #define tos _extra1 #line 816 "vm.def" tos = _gst_nil_oop + (n - NIL_INDEX); #line 8830 "vm.inl" #undef tos } while (0); /* RETURN_CONTEXT_STACK_TOP ( val | -- val | ) */ do { #define val _extra1 #line 852 "vm.def" EXPORT_REGS (); unwind_context (); IMPORT_REGS (); SET_STACKTOP (val); FETCH; #line 8845 "vm.inl" #undef val } while (0); PUSH_OOP (_extra1); } NEXT_BC; bc186: { OOP _extra1; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 8862 "vm.inl" } while (0); /* LINE_NUMBER_BYTECODE ( -- ) */ do { #line 890 "vm.def" #line 8870 "vm.inl" } while (0); /* PUSH_RECEIVER_VARIABLE ( -- tos ) */ do { int n = 5; #define tos _extra1 #line 718 "vm.def" tos = RECEIVER_VARIABLE (n); #line 8881 "vm.inl" #undef tos } while (0); PUSH_OOP (_extra1); } NEXT_BC; bc187: { OOP _extra1; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 8898 "vm.inl" } while (0); /* PUSH_LIT_CONSTANT ( -- tos ) */ do { int n = arg; #define tos _extra1 #line 820 "vm.def" tos = METHOD_LITERAL (n); #line 8909 "vm.inl" #undef tos } while (0); /* MAKE_DIRTY_BLOCK ( block -- closure ) */ do { #define block _extra1 #define closure _extra1 #line 831 "vm.def" EXPORT_REGS (); closure = _gst_make_block_closure (block); IMPORT_REGS(); #line 8923 "vm.inl" #undef block #undef closure } while (0); /* SEND ( -- ) */ do { int sel = 2; int n = 1; #define PREPARE_STACK() do { \ PUSH_OOP (_extra1); \ } while (0) #line 643 "vm.def" PREPARE_STACK (); EXPORT_REGS (); SEND_MESSAGE (METHOD_LITERAL (sel), n); IMPORT_REGS (); FETCH; #line 8943 "vm.inl" #undef PREPARE_STACK } while (0); PUSH_OOP (_extra1); } NEXT_BC; bc188: { OOP _stack0; OOP _extra1; _stack0 = STACK_AT (0); /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 8962 "vm.inl" } while (0); /* PUSH_TEMPORARY_VARIABLE ( -- tos ) */ do { int n = arg; #define tos _extra1 #line 683 "vm.def" tos = METHOD_TEMPORARY (n); #line 8973 "vm.inl" #undef tos } while (0); /* VALUE_COLON_SPECIAL ( rec blk_arg | -- rec blk_arg | ) */ do { #define PREPARE_STACK() do { \ PUSH_OOP (_extra1); \ } while (0) #define rec _stack0 #define blk_arg _extra1 #line 598 "vm.def" PREPARE_STACK (); EXPORT_REGS (); if (UNCOMMON (IS_INT (rec)) || UNCOMMON (OOP_CLASS (rec) != _gst_block_closure_class) || UNCOMMON (send_block_value (1, 0))) SEND_MESSAGE (_gst_builtin_selectors[VALUE_COLON_SPECIAL].symbol, 1); IMPORT_REGS (); FETCH; #line 8996 "vm.inl" #undef PREPARE_STACK #undef rec #undef blk_arg } while (0); PUSH_OOP (_extra1); } NEXT_BC; bc189: { OOP _extra1; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 9015 "vm.inl" } while (0); /* PUSH_INTEGER ( -- tos ) */ do { int n = arg; #define tos _extra1 #line 812 "vm.def" tos = FROM_INT (n); #line 9026 "vm.inl" #undef tos } while (0); /* RETURN_CONTEXT_STACK_TOP ( val | -- val | ) */ do { #define val _extra1 #line 852 "vm.def" EXPORT_REGS (); unwind_context (); IMPORT_REGS (); SET_STACKTOP (val); FETCH; #line 9041 "vm.inl" #undef val } while (0); PUSH_OOP (_extra1); } NEXT_BC; bc190: { OOP _extra1; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 9058 "vm.inl" } while (0); /* PUSH_TEMPORARY_VARIABLE ( -- tos ) */ do { int n = 0; #define tos _extra1 #line 683 "vm.def" tos = METHOD_TEMPORARY (n); #line 9069 "vm.inl" #undef tos } while (0); /* SEND ( -- ) */ do { int sel = arg; int n = 2; #define PREPARE_STACK() do { \ PUSH_OOP (_extra1); \ } while (0) #line 643 "vm.def" PREPARE_STACK (); EXPORT_REGS (); SEND_MESSAGE (METHOD_LITERAL (sel), n); IMPORT_REGS (); FETCH; #line 9088 "vm.inl" #undef PREPARE_STACK } while (0); PUSH_OOP (_extra1); } NEXT_BC; bc191: { OOP _extra1, _extra2; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 9105 "vm.inl" } while (0); /* PUSH_TEMPORARY_VARIABLE ( -- tos ) */ do { int n = arg; #define tos _extra1 #line 683 "vm.def" tos = METHOD_TEMPORARY (n); #line 9116 "vm.inl" #undef tos } while (0); /* PUSH_INTEGER ( -- tos ) */ do { int n = 1; #define tos _extra2 #line 812 "vm.def" tos = FROM_INT (n); #line 9128 "vm.inl" #undef tos } while (0); /* MINUS_SPECIAL ( op1 op2 -- op ) */ do { #define PREPARE_STACK() do { \ PUSH_OOP (_extra1); \ PUSH_OOP (_extra2); \ } while (0) #define op1 _extra1 #define op2 _extra2 #define op _extra1 #line 241 "vm.def" INTERP_BASIC_OP (op, op1, op2, sub_with_check (op1, op2, &overflow), farg1 - farg2); PREPARE_STACK (); EXPORT_REGS (); SEND_MESSAGE (_gst_builtin_selectors[MINUS_SPECIAL].symbol, 1); IMPORT_REGS (); FETCH; #line 9152 "vm.inl" #undef PREPARE_STACK #undef op1 #undef op2 #undef op } while (0); PUSH_OOP (_extra1); } NEXT_BC; bc192: { OOP _extra1, _extra2; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 9172 "vm.inl" } while (0); /* PUSH_SELF ( -- tos ) */ do { #define tos _extra1 #line 893 "vm.def" tos = _gst_self; #line 9182 "vm.inl" #undef tos } while (0); /* PUSH_LIT_CONSTANT ( -- tos ) */ do { int n = arg; #define tos _extra2 #line 820 "vm.def" tos = METHOD_LITERAL (n); #line 9194 "vm.inl" #undef tos } while (0); PUSH_OOP (_extra1); PUSH_OOP (_extra2); } NEXT_BC; bc193: { OOP _extra1; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 9212 "vm.inl" } while (0); /* LINE_NUMBER_BYTECODE ( -- ) */ do { #line 890 "vm.def" #line 9220 "vm.inl" } while (0); /* PUSH_RECEIVER_VARIABLE ( -- tos ) */ do { int n = 4; #define tos _extra1 #line 718 "vm.def" tos = RECEIVER_VARIABLE (n); #line 9231 "vm.inl" #undef tos } while (0); PUSH_OOP (_extra1); } NEXT_BC; bc194: { OOP _extra1; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 9248 "vm.inl" } while (0); /* PUSH_OUTER_TEMP ( -- tos ) */ do { int n = 0; int scopes = 1; #define tos _extra1 #line 687 "vm.def" OOP contextOOP; gst_block_context context; context = (gst_block_context) OOP_TO_OBJ (_gst_this_context_oop); do { contextOOP = context->outerContext; context = (gst_block_context) OOP_TO_OBJ (contextOOP); } while (--scopes); tos = context->contextStack[n]; #line 9271 "vm.inl" #undef tos } while (0); /* SEND_IMMEDIATE ( -- ) */ do { int n = arg; #define PREPARE_STACK() do { \ PUSH_OOP (_extra1); \ } while (0) #line 662 "vm.def" const struct builtin_selector *bs = &_gst_builtin_selectors[n]; PREPARE_STACK (); EXPORT_REGS (); SEND_MESSAGE (bs->symbol, bs->numArgs); IMPORT_REGS (); FETCH; #line 9290 "vm.inl" #undef PREPARE_STACK } while (0); PUSH_OOP (_extra1); } NEXT_BC; bc195: { OOP _extra1; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 9307 "vm.inl" } while (0); /* LINE_NUMBER_BYTECODE ( -- ) */ do { #line 890 "vm.def" #line 9315 "vm.inl" } while (0); /* PUSH_SELF ( -- tos ) */ do { #define tos _extra1 #line 893 "vm.def" tos = _gst_self; #line 9325 "vm.inl" #undef tos } while (0); /* SEND ( -- ) */ do { int sel = 1; int n = 0; #define PREPARE_STACK() do { \ PUSH_OOP (_extra1); \ } while (0) #line 643 "vm.def" PREPARE_STACK (); EXPORT_REGS (); SEND_MESSAGE (METHOD_LITERAL (sel), n); IMPORT_REGS (); FETCH; #line 9344 "vm.inl" #undef PREPARE_STACK } while (0); PUSH_OOP (_extra1); } NEXT_BC; bc196: { OOP _extra1; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 9361 "vm.inl" } while (0); /* PUSH_OUTER_TEMP ( -- tos ) */ do { int n = 0; int scopes = 1; #define tos _extra1 #line 687 "vm.def" OOP contextOOP; gst_block_context context; context = (gst_block_context) OOP_TO_OBJ (_gst_this_context_oop); do { contextOOP = context->outerContext; context = (gst_block_context) OOP_TO_OBJ (contextOOP); } while (--scopes); tos = context->contextStack[n]; #line 9384 "vm.inl" #undef tos } while (0); /* SEND ( -- ) */ do { int sel = arg; int n = 1; #define PREPARE_STACK() do { \ PUSH_OOP (_extra1); \ } while (0) #line 643 "vm.def" PREPARE_STACK (); EXPORT_REGS (); SEND_MESSAGE (METHOD_LITERAL (sel), n); IMPORT_REGS (); FETCH; #line 9403 "vm.inl" #undef PREPARE_STACK } while (0); PUSH_OOP (_extra1); } NEXT_BC; bc197: { OOP _extra1; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 9420 "vm.inl" } while (0); /* PUSH_TEMPORARY_VARIABLE ( -- tos ) */ do { int n = 4; #define tos _extra1 #line 683 "vm.def" tos = METHOD_TEMPORARY (n); #line 9431 "vm.inl" #undef tos } while (0); /* SEND_IMMEDIATE ( -- ) */ do { int n = arg; #define PREPARE_STACK() do { \ PUSH_OOP (_extra1); \ } while (0) #line 662 "vm.def" const struct builtin_selector *bs = &_gst_builtin_selectors[n]; PREPARE_STACK (); EXPORT_REGS (); SEND_MESSAGE (bs->symbol, bs->numArgs); IMPORT_REGS (); FETCH; #line 9450 "vm.inl" #undef PREPARE_STACK } while (0); PUSH_OOP (_extra1); } NEXT_BC; bc198: { OOP _extra1; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 9467 "vm.inl" } while (0); /* PUSH_INTEGER ( -- tos ) */ do { int n = arg; #define tos _extra1 #line 812 "vm.def" tos = FROM_INT (n); #line 9478 "vm.inl" #undef tos } while (0); /* SEND_IMMEDIATE ( -- ) */ do { int n = 41; #define PREPARE_STACK() do { \ PUSH_OOP (_extra1); \ } while (0) #line 662 "vm.def" const struct builtin_selector *bs = &_gst_builtin_selectors[n]; PREPARE_STACK (); EXPORT_REGS (); SEND_MESSAGE (bs->symbol, bs->numArgs); IMPORT_REGS (); FETCH; #line 9497 "vm.inl" #undef PREPARE_STACK } while (0); PUSH_OOP (_extra1); } NEXT_BC; bc199: { /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 9513 "vm.inl" } while (0); /* SEND ( -- ) */ do { int sel = arg; int n = 4; #define PREPARE_STACK() do { \ } while (0) #line 643 "vm.def" PREPARE_STACK (); EXPORT_REGS (); SEND_MESSAGE (METHOD_LITERAL (sel), n); IMPORT_REGS (); FETCH; #line 9530 "vm.inl" #undef PREPARE_STACK } while (0); } NEXT_BC; bc200: { OOP _extra1, _extra2; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 9546 "vm.inl" } while (0); /* PUSH_TEMPORARY_VARIABLE ( -- tos ) */ do { int n = arg; #define tos _extra1 #line 683 "vm.def" tos = METHOD_TEMPORARY (n); #line 9557 "vm.inl" #undef tos } while (0); /* PUSH_TEMPORARY_VARIABLE ( -- tos ) */ do { int n = 2; #define tos _extra2 #line 683 "vm.def" tos = METHOD_TEMPORARY (n); #line 9569 "vm.inl" #undef tos } while (0); PUSH_OOP (_extra1); PUSH_OOP (_extra2); } NEXT_BC; bc201: { OOP _extra1; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 9587 "vm.inl" } while (0); /* PUSH_SELF ( -- tos ) */ do { #define tos _extra1 #line 893 "vm.def" tos = _gst_self; #line 9597 "vm.inl" #undef tos } while (0); /* CLASS_SPECIAL ( rec -- val ) */ do { #define PREPARE_STACK() do { \ PUSH_OOP (_extra1); \ } while (0) #define rec _extra1 #define val _extra1 #line 543 "vm.def" OOP classOOP; PREPARE_STACK (); EXPORT_REGS (); if UNCOMMON (IS_INT (rec)) { SEND_MESSAGE (_gst_builtin_selectors[CLASS_SPECIAL].symbol, 0); IMPORT_REGS (); FETCH; } if COMMON (class_cache_class == (classOOP = OOP_CLASS (rec)) && !execute_primitive_operation (class_cache_prim, 1)) { IMPORT_REGS (); NEXT_BC; } /* Not the same class that is in the cache, or the primitive failed -- send the message, and modify the cache if the send is resolved to a primitive. */ last_primitive = 0; SEND_MESSAGE (_gst_builtin_selectors[CLASS_SPECIAL].symbol, 0); IMPORT_REGS (); if COMMON (last_primitive) { class_cache_prim = last_primitive; class_cache_class = classOOP; NEXT_BC; } FETCH; #line 9641 "vm.inl" #undef PREPARE_STACK #undef rec #undef val } while (0); PUSH_OOP (_extra1); } NEXT_BC; bc202: { OOP _extra1; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 9660 "vm.inl" } while (0); /* PUSH_TEMPORARY_VARIABLE ( -- tos ) */ do { int n = 1; #define tos _extra1 #line 683 "vm.def" tos = METHOD_TEMPORARY (n); #line 9671 "vm.inl" #undef tos } while (0); /* SEND ( -- ) */ do { int sel = arg >> 8; int n = arg & 255; #define PREPARE_STACK() do { \ PUSH_OOP (_extra1); \ } while (0) #line 643 "vm.def" PREPARE_STACK (); EXPORT_REGS (); SEND_MESSAGE (METHOD_LITERAL (sel), n); IMPORT_REGS (); FETCH; #line 9690 "vm.inl" #undef PREPARE_STACK } while (0); PUSH_OOP (_extra1); } NEXT_BC; bc203: { OOP _extra1, _extra2; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 9707 "vm.inl" } while (0); /* PUSH_SELF ( -- tos ) */ do { #define tos _extra1 #line 893 "vm.def" tos = _gst_self; #line 9717 "vm.inl" #undef tos } while (0); /* PUSH_TEMPORARY_VARIABLE ( -- tos ) */ do { int n = 1; #define tos _extra2 #line 683 "vm.def" tos = METHOD_TEMPORARY (n); #line 9729 "vm.inl" #undef tos } while (0); /* SEND ( -- ) */ do { int sel = arg; int n = 1; #define PREPARE_STACK() do { \ PUSH_OOP (_extra1); \ PUSH_OOP (_extra2); \ } while (0) #line 643 "vm.def" PREPARE_STACK (); EXPORT_REGS (); SEND_MESSAGE (METHOD_LITERAL (sel), n); IMPORT_REGS (); FETCH; #line 9749 "vm.inl" #undef PREPARE_STACK } while (0); PUSH_OOP (_extra1); PUSH_OOP (_extra2); } NEXT_BC; bc204: { OOP _extra1; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 9767 "vm.inl" } while (0); /* PUSH_LIT_CONSTANT ( -- tos ) */ do { int n = arg; #define tos _extra1 #line 820 "vm.def" tos = METHOD_LITERAL (n); #line 9778 "vm.inl" #undef tos } while (0); /* SEND ( -- ) */ do { int sel = 4; int n = 1; #define PREPARE_STACK() do { \ PUSH_OOP (_extra1); \ } while (0) #line 643 "vm.def" PREPARE_STACK (); EXPORT_REGS (); SEND_MESSAGE (METHOD_LITERAL (sel), n); IMPORT_REGS (); FETCH; #line 9797 "vm.inl" #undef PREPARE_STACK } while (0); PUSH_OOP (_extra1); } NEXT_BC; bc205: { OOP _extra1; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 9814 "vm.inl" } while (0); /* PUSH_INTEGER ( -- tos ) */ do { int n = arg; #define tos _extra1 #line 812 "vm.def" tos = FROM_INT (n); #line 9825 "vm.inl" #undef tos } while (0); /* SEND ( -- ) */ do { int sel = 0; int n = 1; #define PREPARE_STACK() do { \ PUSH_OOP (_extra1); \ } while (0) #line 643 "vm.def" PREPARE_STACK (); EXPORT_REGS (); SEND_MESSAGE (METHOD_LITERAL (sel), n); IMPORT_REGS (); FETCH; #line 9844 "vm.inl" #undef PREPARE_STACK } while (0); PUSH_OOP (_extra1); } NEXT_BC; bc206: { OOP _extra1; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 9861 "vm.inl" } while (0); /* PUSH_RECEIVER_VARIABLE ( -- tos ) */ do { int n = arg; #define tos _extra1 #line 718 "vm.def" tos = RECEIVER_VARIABLE (n); #line 9872 "vm.inl" #undef tos } while (0); /* SIZE_SPECIAL ( rec -- val ) */ do { #define PREPARE_STACK() do { \ PUSH_OOP (_extra1); \ } while (0) #define rec _extra1 #define val _extra1 #line 510 "vm.def" OOP classOOP; PREPARE_STACK (); EXPORT_REGS (); if UNCOMMON (IS_INT (rec)) { SEND_MESSAGE (_gst_builtin_selectors[SIZE_SPECIAL].symbol, 0); IMPORT_REGS (); FETCH; } if COMMON (size_cache_class == (classOOP = OOP_CLASS (rec)) && !execute_primitive_operation (size_cache_prim, 0)) { IMPORT_REGS (); NEXT_BC; } /* Not the same class that is in the cache, or the primitive failed -- send the message, and modify the cache if the send is resolved to a primitive. */ last_primitive = 0; SEND_MESSAGE (_gst_builtin_selectors[SIZE_SPECIAL].symbol, 0); IMPORT_REGS (); if COMMON (last_primitive) { size_cache_prim = last_primitive; size_cache_class = classOOP; NEXT_BC; } FETCH; #line 9916 "vm.inl" #undef PREPARE_STACK #undef rec #undef val } while (0); PUSH_OOP (_extra1); } NEXT_BC; bc207: { OOP _extra1; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 9935 "vm.inl" } while (0); /* PUSH_TEMPORARY_VARIABLE ( -- tos ) */ do { int n = 1; #define tos _extra1 #line 683 "vm.def" tos = METHOD_TEMPORARY (n); #line 9946 "vm.inl" #undef tos } while (0); /* SEND ( -- ) */ do { int sel = arg; int n = 2; #define PREPARE_STACK() do { \ PUSH_OOP (_extra1); \ } while (0) #line 643 "vm.def" PREPARE_STACK (); EXPORT_REGS (); SEND_MESSAGE (METHOD_LITERAL (sel), n); IMPORT_REGS (); FETCH; #line 9965 "vm.inl" #undef PREPARE_STACK } while (0); PUSH_OOP (_extra1); } NEXT_BC; bc208: { OOP _extra1, _extra2; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 9982 "vm.inl" } while (0); /* PUSH_TEMPORARY_VARIABLE ( -- tos ) */ do { int n = 0; #define tos _extra1 #line 683 "vm.def" tos = METHOD_TEMPORARY (n); #line 9993 "vm.inl" #undef tos } while (0); /* PUSH_TEMPORARY_VARIABLE ( -- tos ) */ do { int n = 1; #define tos _extra2 #line 683 "vm.def" tos = METHOD_TEMPORARY (n); #line 10005 "vm.inl" #undef tos } while (0); /* SEND ( -- ) */ do { int sel = arg; int n = 2; #define PREPARE_STACK() do { \ PUSH_OOP (_extra1); \ PUSH_OOP (_extra2); \ } while (0) #line 643 "vm.def" PREPARE_STACK (); EXPORT_REGS (); SEND_MESSAGE (METHOD_LITERAL (sel), n); IMPORT_REGS (); FETCH; #line 10025 "vm.inl" #undef PREPARE_STACK } while (0); PUSH_OOP (_extra1); PUSH_OOP (_extra2); } NEXT_BC; bc209: { OOP _stack0; OOP _extra1; _stack0 = STACK_AT (0); /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 10045 "vm.inl" } while (0); /* PUSH_TEMPORARY_VARIABLE ( -- tos ) */ do { int n = arg; #define tos _extra1 #line 683 "vm.def" tos = METHOD_TEMPORARY (n); #line 10056 "vm.inl" #undef tos } while (0); /* POP_INTO_NEW_STACKTOP ( obj | val -- obj | ) */ do { int n = 0; #define obj _stack0 #define val _extra1 #line 824 "vm.def" STORE_INSTANCE_VARIABLE (obj, n, val); #line 10069 "vm.inl" #undef obj #undef val } while (0); } NEXT_BC; bc210: { OOP _extra1; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 10086 "vm.inl" } while (0); /* PUSH_LIT_CONSTANT ( -- tos ) */ do { int n = arg; #define tos _extra1 #line 820 "vm.def" tos = METHOD_LITERAL (n); #line 10097 "vm.inl" #undef tos } while (0); /* MAKE_DIRTY_BLOCK ( block -- closure ) */ do { #define block _extra1 #define closure _extra1 #line 831 "vm.def" EXPORT_REGS (); closure = _gst_make_block_closure (block); IMPORT_REGS(); #line 10111 "vm.inl" #undef block #undef closure } while (0); /* SEND ( -- ) */ do { int sel = 5; int n = 1; #define PREPARE_STACK() do { \ PUSH_OOP (_extra1); \ } while (0) #line 643 "vm.def" PREPARE_STACK (); EXPORT_REGS (); SEND_MESSAGE (METHOD_LITERAL (sel), n); IMPORT_REGS (); FETCH; #line 10131 "vm.inl" #undef PREPARE_STACK } while (0); PUSH_OOP (_extra1); } NEXT_BC; bc211: { /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 10147 "vm.inl" } while (0); /* SEND_SUPER ( -- ) */ do { int sel = arg; int n = 1; #define PREPARE_STACK() do { \ } while (0) #line 651 "vm.def" OOP classOOP; PREPARE_STACK (); classOOP = POP_OOP (); EXPORT_REGS (); SEND_TO_SUPER (METHOD_LITERAL (sel), n, classOOP); IMPORT_REGS (); FETCH; #line 10167 "vm.inl" #undef PREPARE_STACK } while (0); } NEXT_BC; bc212: { OOP _extra1; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 10183 "vm.inl" } while (0); /* PUSH_LIT_CONSTANT ( -- tos ) */ do { int n = arg; #define tos _extra1 #line 820 "vm.def" tos = METHOD_LITERAL (n); #line 10194 "vm.inl" #undef tos } while (0); /* MAKE_DIRTY_BLOCK ( block -- closure ) */ do { #define block _extra1 #define closure _extra1 #line 831 "vm.def" EXPORT_REGS (); closure = _gst_make_block_closure (block); IMPORT_REGS(); #line 10208 "vm.inl" #undef block #undef closure } while (0); /* SEND ( -- ) */ do { int sel = 4; int n = 1; #define PREPARE_STACK() do { \ PUSH_OOP (_extra1); \ } while (0) #line 643 "vm.def" PREPARE_STACK (); EXPORT_REGS (); SEND_MESSAGE (METHOD_LITERAL (sel), n); IMPORT_REGS (); FETCH; #line 10228 "vm.inl" #undef PREPARE_STACK } while (0); PUSH_OOP (_extra1); } NEXT_BC; bc213: { OOP _extra1; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 10245 "vm.inl" } while (0); /* PUSH_RECEIVER_VARIABLE ( -- tos ) */ do { int n = 1; #define tos _extra1 #line 718 "vm.def" tos = RECEIVER_VARIABLE (n); #line 10256 "vm.inl" #undef tos } while (0); /* SEND_IMMEDIATE ( -- ) */ do { int n = arg; #define PREPARE_STACK() do { \ PUSH_OOP (_extra1); \ } while (0) #line 662 "vm.def" const struct builtin_selector *bs = &_gst_builtin_selectors[n]; PREPARE_STACK (); EXPORT_REGS (); SEND_MESSAGE (bs->symbol, bs->numArgs); IMPORT_REGS (); FETCH; #line 10275 "vm.inl" #undef PREPARE_STACK } while (0); PUSH_OOP (_extra1); } NEXT_BC; bc214: { OOP _stack0; _stack0 = STACK_AT (0); /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 10293 "vm.inl" } while (0); /* STORE_OUTER_TEMP ( tos | -- tos | ) */ do { int n = arg; int scopes = 1; #define tos _stack0 #line 726 "vm.def" OOP contextOOP; gst_block_context context; context = (gst_block_context) OOP_TO_OBJ (_gst_this_context_oop); do { contextOOP = context->outerContext; context = (gst_block_context) OOP_TO_OBJ (contextOOP); } while (--scopes); context->contextStack[n] = tos; #line 10316 "vm.inl" #undef tos } while (0); /* RETURN_CONTEXT_STACK_TOP ( val | -- val | ) */ do { #define val _stack0 #line 852 "vm.def" EXPORT_REGS (); unwind_context (); IMPORT_REGS (); SET_STACKTOP (val); FETCH; #line 10331 "vm.inl" #undef val } while (0); } NEXT_BC; bc215: { OOP _stack0; _stack0 = STACK_AT (0); /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 10348 "vm.inl" } while (0); /* POP_STACK_TOP ( tos -- ) */ do { #define tos _stack0 #line 828 "vm.def" #line 10357 "vm.inl" #undef tos } while (0); /* LINE_NUMBER_BYTECODE ( -- ) */ do { #line 890 "vm.def" #line 10366 "vm.inl" } while (0); /* SEND_IMMEDIATE ( -- ) */ do { int n = 37; #define PREPARE_STACK() do { \ POP_N_OOPS (1); \ } while (0) #line 662 "vm.def" const struct builtin_selector *bs = &_gst_builtin_selectors[n]; PREPARE_STACK (); EXPORT_REGS (); SEND_MESSAGE (bs->symbol, bs->numArgs); IMPORT_REGS (); FETCH; #line 10384 "vm.inl" #undef PREPARE_STACK } while (0); POP_N_OOPS (1); } NEXT_BC; bc216: { OOP _extra1; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 10401 "vm.inl" } while (0); /* LINE_NUMBER_BYTECODE ( -- ) */ do { #line 890 "vm.def" #line 10409 "vm.inl" } while (0); /* PUSH_SELF ( -- tos ) */ do { #define tos _extra1 #line 893 "vm.def" tos = _gst_self; #line 10419 "vm.inl" #undef tos } while (0); /* CLASS_SPECIAL ( rec -- val ) */ do { #define PREPARE_STACK() do { \ PUSH_OOP (_extra1); \ } while (0) #define rec _extra1 #define val _extra1 #line 543 "vm.def" OOP classOOP; PREPARE_STACK (); EXPORT_REGS (); if UNCOMMON (IS_INT (rec)) { SEND_MESSAGE (_gst_builtin_selectors[CLASS_SPECIAL].symbol, 0); IMPORT_REGS (); FETCH; } if COMMON (class_cache_class == (classOOP = OOP_CLASS (rec)) && !execute_primitive_operation (class_cache_prim, 1)) { IMPORT_REGS (); NEXT_BC; } /* Not the same class that is in the cache, or the primitive failed -- send the message, and modify the cache if the send is resolved to a primitive. */ last_primitive = 0; SEND_MESSAGE (_gst_builtin_selectors[CLASS_SPECIAL].symbol, 0); IMPORT_REGS (); if COMMON (last_primitive) { class_cache_prim = last_primitive; class_cache_class = classOOP; NEXT_BC; } FETCH; #line 10463 "vm.inl" #undef PREPARE_STACK #undef rec #undef val } while (0); PUSH_OOP (_extra1); } NEXT_BC; bc217: { OOP _extra1; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 10482 "vm.inl" } while (0); /* PUSH_TEMPORARY_VARIABLE ( -- tos ) */ do { int n = 1; #define tos _extra1 #line 683 "vm.def" tos = METHOD_TEMPORARY (n); #line 10493 "vm.inl" #undef tos } while (0); /* SEND ( -- ) */ do { int sel = arg; int n = 0; #define PREPARE_STACK() do { \ PUSH_OOP (_extra1); \ } while (0) #line 643 "vm.def" PREPARE_STACK (); EXPORT_REGS (); SEND_MESSAGE (METHOD_LITERAL (sel), n); IMPORT_REGS (); FETCH; #line 10512 "vm.inl" #undef PREPARE_STACK } while (0); PUSH_OOP (_extra1); } NEXT_BC; bc218: { OOP _extra1; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 10529 "vm.inl" } while (0); /* LINE_NUMBER_BYTECODE ( -- ) */ do { #line 890 "vm.def" #line 10537 "vm.inl" } while (0); /* PUSH_SELF ( -- tos ) */ do { #define tos _extra1 #line 893 "vm.def" tos = _gst_self; #line 10547 "vm.inl" #undef tos } while (0); /* SEND_IMMEDIATE ( -- ) */ do { int n = 130; #define PREPARE_STACK() do { \ PUSH_OOP (_extra1); \ } while (0) #line 662 "vm.def" const struct builtin_selector *bs = &_gst_builtin_selectors[n]; PREPARE_STACK (); EXPORT_REGS (); SEND_MESSAGE (bs->symbol, bs->numArgs); IMPORT_REGS (); FETCH; #line 10566 "vm.inl" #undef PREPARE_STACK } while (0); PUSH_OOP (_extra1); } NEXT_BC; bc219: { OOP _extra1; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 10583 "vm.inl" } while (0); /* PUSH_RECEIVER_VARIABLE ( -- tos ) */ do { int n = 0; #define tos _extra1 #line 718 "vm.def" tos = RECEIVER_VARIABLE (n); #line 10594 "vm.inl" #undef tos } while (0); /* SEND_IMMEDIATE ( -- ) */ do { int n = arg; #define PREPARE_STACK() do { \ PUSH_OOP (_extra1); \ } while (0) #line 662 "vm.def" const struct builtin_selector *bs = &_gst_builtin_selectors[n]; PREPARE_STACK (); EXPORT_REGS (); SEND_MESSAGE (bs->symbol, bs->numArgs); IMPORT_REGS (); FETCH; #line 10613 "vm.inl" #undef PREPARE_STACK } while (0); PUSH_OOP (_extra1); } NEXT_BC; bc220: { OOP _extra1, _extra2; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 10630 "vm.inl" } while (0); /* PUSH_TEMPORARY_VARIABLE ( -- tos ) */ do { int n = 0; #define tos _extra1 #line 683 "vm.def" tos = METHOD_TEMPORARY (n); #line 10641 "vm.inl" #undef tos } while (0); /* PUSH_LIT_VARIABLE ( -- tos ) */ do { int n = arg; #define PREPARE_STACK() do { \ PUSH_OOP (_extra1); \ } while (0) #define tos _extra2 #line 702 "vm.def" tos = METHOD_LITERAL (n); if (UNCOMMON (IS_INT (tos)) || UNCOMMON (!is_a_kind_of (OOP_CLASS (tos), _gst_association_class))) { PREPARE_STACK (); PUSH_OOP (tos); EXPORT_REGS (); SEND_MESSAGE (_gst_builtin_selectors[VALUE_SPECIAL].symbol, 0); IMPORT_REGS (); FETCH; } else tos = ASSOCIATION_VALUE (tos); #line 10668 "vm.inl" #undef PREPARE_STACK #undef tos } while (0); PUSH_OOP (_extra1); PUSH_OOP (_extra2); } NEXT_BC; bc221: { OOP _stack0; _stack0 = STACK_AT (0); /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 10688 "vm.inl" } while (0); /* STORE_TEMPORARY_VARIABLE ( tos | -- tos | ) */ do { int n = 0; #define tos _stack0 #line 722 "vm.def" STORE_METHOD_TEMPORARY (n, tos); #line 10699 "vm.inl" #undef tos } while (0); /* LINE_NUMBER_BYTECODE ( -- ) */ do { #line 890 "vm.def" #line 10708 "vm.inl" } while (0); } NEXT_BC; bc222: { OOP _extra1; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 10723 "vm.inl" } while (0); /* PUSH_RECEIVER_VARIABLE ( -- tos ) */ do { int n = 2; #define tos _extra1 #line 718 "vm.def" tos = RECEIVER_VARIABLE (n); #line 10734 "vm.inl" #undef tos } while (0); /* SEND_IMMEDIATE ( -- ) */ do { int n = arg; #define PREPARE_STACK() do { \ PUSH_OOP (_extra1); \ } while (0) #line 662 "vm.def" const struct builtin_selector *bs = &_gst_builtin_selectors[n]; PREPARE_STACK (); EXPORT_REGS (); SEND_MESSAGE (bs->symbol, bs->numArgs); IMPORT_REGS (); FETCH; #line 10753 "vm.inl" #undef PREPARE_STACK } while (0); PUSH_OOP (_extra1); } NEXT_BC; bc223: { OOP _extra1; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 10770 "vm.inl" } while (0); /* LINE_NUMBER_BYTECODE ( -- ) */ do { #line 890 "vm.def" #line 10778 "vm.inl" } while (0); /* PUSH_SELF ( -- tos ) */ do { #define tos _extra1 #line 893 "vm.def" tos = _gst_self; #line 10788 "vm.inl" #undef tos } while (0); /* SEND ( -- ) */ do { int sel = 2; int n = 0; #define PREPARE_STACK() do { \ PUSH_OOP (_extra1); \ } while (0) #line 643 "vm.def" PREPARE_STACK (); EXPORT_REGS (); SEND_MESSAGE (METHOD_LITERAL (sel), n); IMPORT_REGS (); FETCH; #line 10807 "vm.inl" #undef PREPARE_STACK } while (0); PUSH_OOP (_extra1); } NEXT_BC; bc224: { OOP _stack0; _stack0 = STACK_AT (0); /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 10825 "vm.inl" } while (0); /* LINE_NUMBER_BYTECODE ( -- ) */ do { #line 890 "vm.def" #line 10833 "vm.inl" } while (0); /* POP_STACK_TOP ( tos -- ) */ do { #define tos _stack0 #line 828 "vm.def" #line 10842 "vm.inl" #undef tos } while (0); /* PUSH_TEMPORARY_VARIABLE ( -- tos ) */ do { int n = 2; #define tos _stack0 #line 683 "vm.def" tos = METHOD_TEMPORARY (n); #line 10854 "vm.inl" #undef tos } while (0); STACK_AT (0) = _stack0; } NEXT_BC; bc225: { OOP _extra1; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 10871 "vm.inl" } while (0); /* PUSH_LIT_CONSTANT ( -- tos ) */ do { int n = arg; #define tos _extra1 #line 820 "vm.def" tos = METHOD_LITERAL (n); #line 10882 "vm.inl" #undef tos } while (0); /* MAKE_DIRTY_BLOCK ( block -- closure ) */ do { #define block _extra1 #define closure _extra1 #line 831 "vm.def" EXPORT_REGS (); closure = _gst_make_block_closure (block); IMPORT_REGS(); #line 10896 "vm.inl" #undef block #undef closure } while (0); /* SEND ( -- ) */ do { int sel = 6; int n = 1; #define PREPARE_STACK() do { \ PUSH_OOP (_extra1); \ } while (0) #line 643 "vm.def" PREPARE_STACK (); EXPORT_REGS (); SEND_MESSAGE (METHOD_LITERAL (sel), n); IMPORT_REGS (); FETCH; #line 10916 "vm.inl" #undef PREPARE_STACK } while (0); PUSH_OOP (_extra1); } NEXT_BC; bc226: { OOP _extra1; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 10933 "vm.inl" } while (0); /* PUSH_SPECIAL ( -- tos ) */ do { int n = arg; #define tos _extra1 #line 816 "vm.def" tos = _gst_nil_oop + (n - NIL_INDEX); #line 10944 "vm.inl" #undef tos } while (0); /* RETURN_METHOD_STACK_TOP ( val | -- val | ) */ do { #define val _extra1 #line 837 "vm.def" EXPORT_REGS (); if UNCOMMON (!unwind_method ()) { SEND_MESSAGE (_gst_bad_return_error_symbol, 0); IMPORT_REGS (); } else { IMPORT_REGS (); SET_STACKTOP (val); } FETCH; #line 10966 "vm.inl" #undef val } while (0); PUSH_OOP (_extra1); } NEXT_BC; bc227: { OOP _stack0; OOP _extra1; _stack0 = STACK_AT (0); /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 10985 "vm.inl" } while (0); /* PUSH_INTEGER ( -- tos ) */ do { int n = arg; #define tos _extra1 #line 812 "vm.def" tos = FROM_INT (n); #line 10996 "vm.inl" #undef tos } while (0); /* GREATER_EQUAL_SPECIAL ( op1 op2 -- op ) */ do { #define PREPARE_STACK() do { \ PUSH_OOP (_extra1); \ } while (0) #define op1 _stack0 #define op2 _extra1 #define op _stack0 #line 279 "vm.def" PREPARE_STACK (); INTERP_BASIC_BOOL (op, op1, op2, >=); EXPORT_REGS (); SEND_MESSAGE (_gst_builtin_selectors[GREATER_EQUAL_SPECIAL].symbol, 1); IMPORT_REGS (); FETCH; #line 11017 "vm.inl" #undef PREPARE_STACK #undef op1 #undef op2 #undef op } while (0); STACK_AT (0) = _stack0; } NEXT_BC; bc228: { OOP _stack0; _stack0 = STACK_AT (0); /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 11038 "vm.inl" } while (0); /* LINE_NUMBER_BYTECODE ( -- ) */ do { #line 890 "vm.def" #line 11046 "vm.inl" } while (0); /* POP_STACK_TOP ( tos -- ) */ do { #define tos _stack0 #line 828 "vm.def" #line 11055 "vm.inl" #undef tos } while (0); /* PUSH_RECEIVER_VARIABLE ( -- tos ) */ do { int n = 1; #define tos _stack0 #line 718 "vm.def" tos = RECEIVER_VARIABLE (n); #line 11067 "vm.inl" #undef tos } while (0); STACK_AT (0) = _stack0; } NEXT_BC; bc229: { OOP _extra1; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 11084 "vm.inl" } while (0); /* LINE_NUMBER_BYTECODE ( -- ) */ do { #line 890 "vm.def" #line 11092 "vm.inl" } while (0); /* PUSH_LIT_VARIABLE ( -- tos ) */ do { int n = 3; #define PREPARE_STACK() do { \ } while (0) #define tos _extra1 #line 702 "vm.def" tos = METHOD_LITERAL (n); if (UNCOMMON (IS_INT (tos)) || UNCOMMON (!is_a_kind_of (OOP_CLASS (tos), _gst_association_class))) { PREPARE_STACK (); PUSH_OOP (tos); EXPORT_REGS (); SEND_MESSAGE (_gst_builtin_selectors[VALUE_SPECIAL].symbol, 0); IMPORT_REGS (); FETCH; } else tos = ASSOCIATION_VALUE (tos); #line 11117 "vm.inl" #undef PREPARE_STACK #undef tos } while (0); PUSH_OOP (_extra1); } NEXT_BC; bc230: { OOP _extra1; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 11135 "vm.inl" } while (0); /* PUSH_LIT_CONSTANT ( -- tos ) */ do { int n = 2; #define tos _extra1 #line 820 "vm.def" tos = METHOD_LITERAL (n); #line 11146 "vm.inl" #undef tos } while (0); /* SEND_IMMEDIATE ( -- ) */ do { int n = arg; #define PREPARE_STACK() do { \ PUSH_OOP (_extra1); \ } while (0) #line 662 "vm.def" const struct builtin_selector *bs = &_gst_builtin_selectors[n]; PREPARE_STACK (); EXPORT_REGS (); SEND_MESSAGE (bs->symbol, bs->numArgs); IMPORT_REGS (); FETCH; #line 11165 "vm.inl" #undef PREPARE_STACK } while (0); PUSH_OOP (_extra1); } NEXT_BC; bc231: { /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 11181 "vm.inl" } while (0); /* SEND_SUPER ( -- ) */ do { int sel = arg; int n = 0; #define PREPARE_STACK() do { \ } while (0) #line 651 "vm.def" OOP classOOP; PREPARE_STACK (); classOOP = POP_OOP (); EXPORT_REGS (); SEND_TO_SUPER (METHOD_LITERAL (sel), n, classOOP); IMPORT_REGS (); FETCH; #line 11201 "vm.inl" #undef PREPARE_STACK } while (0); } NEXT_BC; bc232: { OOP _extra1; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 11217 "vm.inl" } while (0); /* PUSH_SPECIAL ( -- tos ) */ do { int n = 0; #define tos _extra1 #line 816 "vm.def" tos = _gst_nil_oop + (n - NIL_INDEX); #line 11228 "vm.inl" #undef tos } while (0); /* STORE_RECEIVER_VARIABLE ( tos | -- tos | ) */ do { int n = arg; #define tos _extra1 #line 758 "vm.def" STORE_RECEIVER_VARIABLE (n, tos); #line 11240 "vm.inl" #undef tos } while (0); PUSH_OOP (_extra1); } NEXT_BC; bc233: { OOP _extra1, _extra2; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 11257 "vm.inl" } while (0); /* PUSH_SELF ( -- tos ) */ do { #define tos _extra1 #line 893 "vm.def" tos = _gst_self; #line 11267 "vm.inl" #undef tos } while (0); /* PUSH_TEMPORARY_VARIABLE ( -- tos ) */ do { int n = arg; #define tos _extra2 #line 683 "vm.def" tos = METHOD_TEMPORARY (n); #line 11279 "vm.inl" #undef tos } while (0); /* SEND ( -- ) */ do { int sel = 0; int n = 1; #define PREPARE_STACK() do { \ PUSH_OOP (_extra1); \ PUSH_OOP (_extra2); \ } while (0) #line 643 "vm.def" PREPARE_STACK (); EXPORT_REGS (); SEND_MESSAGE (METHOD_LITERAL (sel), n); IMPORT_REGS (); FETCH; #line 11299 "vm.inl" #undef PREPARE_STACK } while (0); PUSH_OOP (_extra1); PUSH_OOP (_extra2); } NEXT_BC; bc234: { OOP _stack0; _stack0 = STACK_AT (0); /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 11318 "vm.inl" } while (0); /* LINE_NUMBER_BYTECODE ( -- ) */ do { #line 890 "vm.def" #line 11326 "vm.inl" } while (0); /* POP_STACK_TOP ( tos -- ) */ do { #define tos _stack0 #line 828 "vm.def" #line 11335 "vm.inl" #undef tos } while (0); /* PUSH_TEMPORARY_VARIABLE ( -- tos ) */ do { int n = 0; #define tos _stack0 #line 683 "vm.def" tos = METHOD_TEMPORARY (n); #line 11347 "vm.inl" #undef tos } while (0); /* RETURN_CONTEXT_STACK_TOP ( val | -- val | ) */ do { #define val _stack0 #line 852 "vm.def" EXPORT_REGS (); unwind_context (); IMPORT_REGS (); SET_STACKTOP (val); FETCH; #line 11362 "vm.inl" #undef val } while (0); STACK_AT (0) = _stack0; } NEXT_BC; bc235: { OOP _stack0; OOP _extra1; _stack0 = STACK_AT (0); /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 11381 "vm.inl" } while (0); /* PUSH_LIT_CONSTANT ( -- tos ) */ do { int n = arg; #define tos _extra1 #line 820 "vm.def" tos = METHOD_LITERAL (n); #line 11392 "vm.inl" #undef tos } while (0); /* SAME_OBJECT_SPECIAL ( op1 op2 -- op ) */ do { #define op1 _stack0 #define op2 _extra1 #define op _stack0 #line 610 "vm.def" /* DO_JUMP_LOOKAHEAD (op1 == op2); */ op = (op1 == op2) ? _gst_true_oop : _gst_false_oop; #line 11406 "vm.inl" #undef op1 #undef op2 #undef op } while (0); STACK_AT (0) = _stack0; } NEXT_BC; bc236: { OOP _extra1; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 11425 "vm.inl" } while (0); /* PUSH_LIT_CONSTANT ( -- tos ) */ do { int n = arg; #define tos _extra1 #line 820 "vm.def" tos = METHOD_LITERAL (n); #line 11436 "vm.inl" #undef tos } while (0); /* MAKE_DIRTY_BLOCK ( block -- closure ) */ do { #define block _extra1 #define closure _extra1 #line 831 "vm.def" EXPORT_REGS (); closure = _gst_make_block_closure (block); IMPORT_REGS(); #line 11450 "vm.inl" #undef block #undef closure } while (0); /* SEND ( -- ) */ do { int sel = 1; int n = 1; #define PREPARE_STACK() do { \ PUSH_OOP (_extra1); \ } while (0) #line 643 "vm.def" PREPARE_STACK (); EXPORT_REGS (); SEND_MESSAGE (METHOD_LITERAL (sel), n); IMPORT_REGS (); FETCH; #line 11470 "vm.inl" #undef PREPARE_STACK } while (0); PUSH_OOP (_extra1); } NEXT_BC; bc237: { OOP _stack0; _stack0 = STACK_AT (0); /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 11488 "vm.inl" } while (0); /* LINE_NUMBER_BYTECODE ( -- ) */ do { #line 890 "vm.def" #line 11496 "vm.inl" } while (0); /* POP_STACK_TOP ( tos -- ) */ do { #define tos _stack0 #line 828 "vm.def" #line 11505 "vm.inl" #undef tos } while (0); /* PUSH_TEMPORARY_VARIABLE ( -- tos ) */ do { int n = 3; #define tos _stack0 #line 683 "vm.def" tos = METHOD_TEMPORARY (n); #line 11517 "vm.inl" #undef tos } while (0); STACK_AT (0) = _stack0; } NEXT_BC; bc238: { OOP _stack0, _stack1; _stack1 = STACK_AT (1); _stack0 = STACK_AT (0); /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 11536 "vm.inl" } while (0); /* POP_STACK_TOP ( tos -- ) */ do { #define tos _stack0 #line 828 "vm.def" #line 11545 "vm.inl" #undef tos } while (0); /* DUP_STACK_TOP ( tos | -- tos | tos2 ) */ do { #define tos _stack1 #define tos2 _stack0 #line 860 "vm.def" tos2 = tos; #line 11557 "vm.inl" #undef tos #undef tos2 } while (0); /* SEND_IMMEDIATE ( -- ) */ do { int n = arg; #define PREPARE_STACK() do { \ STACK_AT (0) = _stack0; \ } while (0) #line 662 "vm.def" const struct builtin_selector *bs = &_gst_builtin_selectors[n]; PREPARE_STACK (); EXPORT_REGS (); SEND_MESSAGE (bs->symbol, bs->numArgs); IMPORT_REGS (); FETCH; #line 11577 "vm.inl" #undef PREPARE_STACK } while (0); STACK_AT (0) = _stack0; } NEXT_BC; bc239: { OOP _stack0; OOP _extra1, _extra2; _stack0 = STACK_AT (0); /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 11596 "vm.inl" } while (0); /* PUSH_LIT_CONSTANT ( -- tos ) */ do { int n = arg; #define tos _extra1 #line 820 "vm.def" tos = METHOD_LITERAL (n); #line 11607 "vm.inl" #undef tos } while (0); /* PUSH_TEMPORARY_VARIABLE ( -- tos ) */ do { int n = 0; #define tos _extra2 #line 683 "vm.def" tos = METHOD_TEMPORARY (n); #line 11619 "vm.inl" #undef tos } while (0); /* AT_PUT_SPECIAL ( rec idx val -- res ) */ do { #define PREPARE_STACK() do { \ PUSH_OOP (_extra1); \ PUSH_OOP (_extra2); \ } while (0) #define rec _stack0 #define idx _extra1 #define val _extra2 #define res _stack0 #line 477 "vm.def" OOP classOOP; PREPARE_STACK (); EXPORT_REGS (); if UNCOMMON (IS_INT (rec)) { SEND_MESSAGE (_gst_builtin_selectors[AT_PUT_SPECIAL].symbol, 2); IMPORT_REGS (); FETCH; } if COMMON (at_put_cache_class == (classOOP = OOP_CLASS (rec)) && !cached_index_oop_put_primitive (rec, idx, val, at_put_cache_spec)) { IMPORT_REGS (); NEXT_BC; } /* Not the same class that is in the cache, or the primitive failed -- send the message, and modify the cache if the send is resolved to a primitive. */ last_primitive = 0; SEND_MESSAGE (_gst_builtin_selectors[AT_PUT_SPECIAL].symbol, 2); IMPORT_REGS (); if (_gst_primitive_table[last_primitive].id == 61) { at_put_cache_spec = CLASS_INSTANCE_SPEC (classOOP); at_put_cache_class = classOOP; NEXT_BC; } FETCH; #line 11666 "vm.inl" #undef PREPARE_STACK #undef rec #undef idx #undef val #undef res } while (0); STACK_AT (0) = _stack0; } NEXT_BC; bc240: { OOP _stack0; OOP _extra1, _extra2, _extra3; _stack0 = STACK_AT (0); /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 11689 "vm.inl" } while (0); /* DUP_STACK_TOP ( tos | -- tos | tos2 ) */ do { #define tos _stack0 #define tos2 _extra1 #line 860 "vm.def" tos2 = tos; #line 11700 "vm.inl" #undef tos #undef tos2 } while (0); /* PUSH_TEMPORARY_VARIABLE ( -- tos ) */ do { int n = arg; #define tos _extra2 #line 683 "vm.def" tos = METHOD_TEMPORARY (n); #line 11713 "vm.inl" #undef tos } while (0); /* PUSH_INTEGER ( -- tos ) */ do { int n = 1; #define tos _extra3 #line 812 "vm.def" tos = FROM_INT (n); #line 11725 "vm.inl" #undef tos } while (0); /* PLUS_SPECIAL ( op1 op2 -- op ) */ do { #define PREPARE_STACK() do { \ PUSH_OOP (_extra1); \ PUSH_OOP (_extra2); \ PUSH_OOP (_extra3); \ } while (0) #define op1 _extra2 #define op2 _extra3 #define op _extra2 #line 230 "vm.def" INTERP_BASIC_OP (op, op1, op2, add_with_check (op1, op2, &overflow), farg1 + farg2); PREPARE_STACK (); EXPORT_REGS (); SEND_MESSAGE (_gst_builtin_selectors[PLUS_SPECIAL].symbol, 1); IMPORT_REGS (); FETCH; #line 11750 "vm.inl" #undef PREPARE_STACK #undef op1 #undef op2 #undef op } while (0); PUSH_OOP (_extra1); PUSH_OOP (_extra2); } NEXT_BC; bc241: { OOP _extra1; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 11771 "vm.inl" } while (0); /* LINE_NUMBER_BYTECODE ( -- ) */ do { #line 890 "vm.def" #line 11779 "vm.inl" } while (0); /* PUSH_TEMPORARY_VARIABLE ( -- tos ) */ do { int n = 4; #define tos _extra1 #line 683 "vm.def" tos = METHOD_TEMPORARY (n); #line 11790 "vm.inl" #undef tos } while (0); PUSH_OOP (_extra1); } NEXT_BC; bc242: { OOP _stack0; _stack0 = STACK_AT (0); /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 11808 "vm.inl" } while (0); /* POP_STACK_TOP ( tos -- ) */ do { #define tos _stack0 #line 828 "vm.def" #line 11817 "vm.inl" #undef tos } while (0); /* LINE_NUMBER_BYTECODE ( -- ) */ do { #line 890 "vm.def" #line 11826 "vm.inl" } while (0); /* PUSH_LIT_VARIABLE ( -- tos ) */ do { int n = 1; #define PREPARE_STACK() do { \ POP_N_OOPS (1); \ } while (0) #define tos _stack0 #line 702 "vm.def" tos = METHOD_LITERAL (n); if (UNCOMMON (IS_INT (tos)) || UNCOMMON (!is_a_kind_of (OOP_CLASS (tos), _gst_association_class))) { PREPARE_STACK (); PUSH_OOP (tos); EXPORT_REGS (); SEND_MESSAGE (_gst_builtin_selectors[VALUE_SPECIAL].symbol, 0); IMPORT_REGS (); FETCH; } else tos = ASSOCIATION_VALUE (tos); #line 11852 "vm.inl" #undef PREPARE_STACK #undef tos } while (0); STACK_AT (0) = _stack0; } NEXT_BC; bc243: { OOP _stack0; OOP _extra1, _extra2; _stack0 = STACK_AT (0); /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 11872 "vm.inl" } while (0); /* DUP_STACK_TOP ( tos | -- tos | tos2 ) */ do { #define tos _stack0 #define tos2 _extra1 #line 860 "vm.def" tos2 = tos; #line 11883 "vm.inl" #undef tos #undef tos2 } while (0); /* PUSH_LIT_CONSTANT ( -- tos ) */ do { int n = arg; #define tos _extra2 #line 820 "vm.def" tos = METHOD_LITERAL (n); #line 11896 "vm.inl" #undef tos } while (0); /* SEND ( -- ) */ do { int sel = 1; int n = 1; #define PREPARE_STACK() do { \ PUSH_OOP (_extra1); \ PUSH_OOP (_extra2); \ } while (0) #line 643 "vm.def" PREPARE_STACK (); EXPORT_REGS (); SEND_MESSAGE (METHOD_LITERAL (sel), n); IMPORT_REGS (); FETCH; #line 11916 "vm.inl" #undef PREPARE_STACK } while (0); PUSH_OOP (_extra1); PUSH_OOP (_extra2); } NEXT_BC; bc244: { OOP _stack0, _stack1; _stack1 = STACK_AT (1); _stack0 = STACK_AT (0); /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 11936 "vm.inl" } while (0); /* POP_INTO_NEW_STACKTOP ( obj | val -- obj | ) */ do { int n = 1; #define obj _stack1 #define val _stack0 #line 824 "vm.def" STORE_INSTANCE_VARIABLE (obj, n, val); #line 11948 "vm.inl" #undef obj #undef val } while (0); /* SEND ( -- ) */ do { int sel = arg; int n = 1; #define PREPARE_STACK() do { \ POP_N_OOPS (1); \ } while (0) #line 643 "vm.def" PREPARE_STACK (); EXPORT_REGS (); SEND_MESSAGE (METHOD_LITERAL (sel), n); IMPORT_REGS (); FETCH; #line 11968 "vm.inl" #undef PREPARE_STACK } while (0); POP_N_OOPS (1); } NEXT_BC; bc245: { OOP _stack0; _stack0 = STACK_AT (0); /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 11986 "vm.inl" } while (0); /* LINE_NUMBER_BYTECODE ( -- ) */ do { #line 890 "vm.def" #line 11994 "vm.inl" } while (0); /* POP_STACK_TOP ( tos -- ) */ do { #define tos _stack0 #line 828 "vm.def" #line 12003 "vm.inl" #undef tos } while (0); /* PUSH_TEMPORARY_VARIABLE ( -- tos ) */ do { int n = 1; #define tos _stack0 #line 683 "vm.def" tos = METHOD_TEMPORARY (n); #line 12015 "vm.inl" #undef tos } while (0); /* RETURN_CONTEXT_STACK_TOP ( val | -- val | ) */ do { #define val _stack0 #line 852 "vm.def" EXPORT_REGS (); unwind_context (); IMPORT_REGS (); SET_STACKTOP (val); FETCH; #line 12030 "vm.inl" #undef val } while (0); STACK_AT (0) = _stack0; } NEXT_BC; bc246: { OOP _stack0; _stack0 = STACK_AT (0); /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 12048 "vm.inl" } while (0); /* STORE_TEMPORARY_VARIABLE ( tos | -- tos | ) */ do { int n = 3; #define tos _stack0 #line 722 "vm.def" STORE_METHOD_TEMPORARY (n, tos); #line 12059 "vm.inl" #undef tos } while (0); /* LINE_NUMBER_BYTECODE ( -- ) */ do { #line 890 "vm.def" #line 12068 "vm.inl" } while (0); } NEXT_BC; bc247: { OOP _stack0; OOP _extra1; _stack0 = STACK_AT (0); /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 12085 "vm.inl" } while (0); /* DUP_STACK_TOP ( tos | -- tos | tos2 ) */ do { #define tos _stack0 #define tos2 _extra1 #line 860 "vm.def" tos2 = tos; #line 12096 "vm.inl" #undef tos #undef tos2 } while (0); /* SEND ( -- ) */ do { int sel = arg; int n = 0; #define PREPARE_STACK() do { \ PUSH_OOP (_extra1); \ } while (0) #line 643 "vm.def" PREPARE_STACK (); EXPORT_REGS (); SEND_MESSAGE (METHOD_LITERAL (sel), n); IMPORT_REGS (); FETCH; #line 12116 "vm.inl" #undef PREPARE_STACK } while (0); PUSH_OOP (_extra1); } NEXT_BC; bc248: { OOP _stack0; _stack0 = STACK_AT (0); /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 12134 "vm.inl" } while (0); /* STORE_RECEIVER_VARIABLE ( tos | -- tos | ) */ do { int n = arg; #define tos _stack0 #line 758 "vm.def" STORE_RECEIVER_VARIABLE (n, tos); #line 12145 "vm.inl" #undef tos } while (0); /* RETURN_CONTEXT_STACK_TOP ( val | -- val | ) */ do { #define val _stack0 #line 852 "vm.def" EXPORT_REGS (); unwind_context (); IMPORT_REGS (); SET_STACKTOP (val); FETCH; #line 12160 "vm.inl" #undef val } while (0); } NEXT_BC; bc249: { OOP _extra1; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 12176 "vm.inl" } while (0); /* LINE_NUMBER_BYTECODE ( -- ) */ do { #line 890 "vm.def" #line 12184 "vm.inl" } while (0); /* PUSH_SELF ( -- tos ) */ do { #define tos _extra1 #line 893 "vm.def" tos = _gst_self; #line 12194 "vm.inl" #undef tos } while (0); /* SEND ( -- ) */ do { int sel = 3; int n = 0; #define PREPARE_STACK() do { \ PUSH_OOP (_extra1); \ } while (0) #line 643 "vm.def" PREPARE_STACK (); EXPORT_REGS (); SEND_MESSAGE (METHOD_LITERAL (sel), n); IMPORT_REGS (); FETCH; #line 12213 "vm.inl" #undef PREPARE_STACK } while (0); PUSH_OOP (_extra1); } NEXT_BC; bc250: { OOP _stack0; OOP _extra1; _stack0 = STACK_AT (0); /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 12232 "vm.inl" } while (0); /* NOT_NIL_SPECIAL ( rec -- val ) */ do { #define rec _stack0 #define val _stack0 #line 581 "vm.def" /* DO_JUMP_LOOKAHEAD (rec != _gst_nil_oop); */ val = rec != _gst_nil_oop ? _gst_true_oop : _gst_false_oop; #line 12244 "vm.inl" #undef rec #undef val } while (0); /* DUP_STACK_TOP ( tos | -- tos | tos2 ) */ do { #define tos _stack0 #define tos2 _extra1 #line 860 "vm.def" tos2 = tos; #line 12257 "vm.inl" #undef tos #undef tos2 } while (0); /* POP_JUMP_FALSE ( tos -- ) */ do { int n = arg; #define PREPARE_STACK() do { \ STACK_AT (0) = _stack0; \ PUSH_OOP (_extra1); \ } while (0) #define tos _extra1 #line 774 "vm.def" if UNCOMMON (tos == _gst_false_oop) { PREPARE_STACK (); POP_N_OOPS(1); ip += n; FETCH; } else if UNCOMMON (tos != _gst_true_oop) { ip += n; PREPARE_STACK (); EXPORT_REGS(); SEND_MESSAGE(_gst_must_be_boolean_symbol, 0); IMPORT_REGS(); FETCH; } #line 12289 "vm.inl" #undef PREPARE_STACK #undef tos } while (0); STACK_AT (0) = _stack0; } NEXT_BC; bc251: { OOP _stack0; OOP _extra1, _extra2; _stack0 = STACK_AT (0); /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 12309 "vm.inl" } while (0); /* DUP_STACK_TOP ( tos | -- tos | tos2 ) */ do { #define tos _stack0 #define tos2 _extra1 #line 860 "vm.def" tos2 = tos; #line 12320 "vm.inl" #undef tos #undef tos2 } while (0); /* PUSH_LIT_CONSTANT ( -- tos ) */ do { int n = arg; #define tos _extra2 #line 820 "vm.def" tos = METHOD_LITERAL (n); #line 12333 "vm.inl" #undef tos } while (0); PUSH_OOP (_extra1); PUSH_OOP (_extra2); } NEXT_BC; bc252: { OOP _extra1; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 12351 "vm.inl" } while (0); /* LINE_NUMBER_BYTECODE ( -- ) */ do { #line 890 "vm.def" #line 12359 "vm.inl" } while (0); /* PUSH_TEMPORARY_VARIABLE ( -- tos ) */ do { int n = 0; #define tos _extra1 #line 683 "vm.def" tos = METHOD_TEMPORARY (n); #line 12370 "vm.inl" #undef tos } while (0); /* RETURN_CONTEXT_STACK_TOP ( val | -- val | ) */ do { #define val _extra1 #line 852 "vm.def" EXPORT_REGS (); unwind_context (); IMPORT_REGS (); SET_STACKTOP (val); FETCH; #line 12385 "vm.inl" #undef val } while (0); PUSH_OOP (_extra1); } NEXT_BC; bc253: { OOP _stack0, _stack1; OOP _extra1; _stack1 = STACK_AT (1); _stack0 = STACK_AT (0); /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 12405 "vm.inl" } while (0); /* PUSH_INTEGER ( -- tos ) */ do { int n = arg; #define tos _extra1 #line 812 "vm.def" tos = FROM_INT (n); #line 12416 "vm.inl" #undef tos } while (0); /* AT_PUT_SPECIAL ( rec idx val -- res ) */ do { #define PREPARE_STACK() do { \ PUSH_OOP (_extra1); \ } while (0) #define rec _stack1 #define idx _stack0 #define val _extra1 #define res _stack1 #line 477 "vm.def" OOP classOOP; PREPARE_STACK (); EXPORT_REGS (); if UNCOMMON (IS_INT (rec)) { SEND_MESSAGE (_gst_builtin_selectors[AT_PUT_SPECIAL].symbol, 2); IMPORT_REGS (); FETCH; } if COMMON (at_put_cache_class == (classOOP = OOP_CLASS (rec)) && !cached_index_oop_put_primitive (rec, idx, val, at_put_cache_spec)) { IMPORT_REGS (); NEXT_BC; } /* Not the same class that is in the cache, or the primitive failed -- send the message, and modify the cache if the send is resolved to a primitive. */ last_primitive = 0; SEND_MESSAGE (_gst_builtin_selectors[AT_PUT_SPECIAL].symbol, 2); IMPORT_REGS (); if (_gst_primitive_table[last_primitive].id == 61) { at_put_cache_spec = CLASS_INSTANCE_SPEC (classOOP); at_put_cache_class = classOOP; NEXT_BC; } FETCH; #line 12462 "vm.inl" #undef PREPARE_STACK #undef rec #undef idx #undef val #undef res } while (0); STACK_AT (1) = _stack1; POP_N_OOPS (1); } NEXT_BC; bc254: { OOP _extra1; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 12484 "vm.inl" } while (0); /* PUSH_TEMPORARY_VARIABLE ( -- tos ) */ do { int n = arg; #define tos _extra1 #line 683 "vm.def" tos = METHOD_TEMPORARY (n); #line 12495 "vm.inl" #undef tos } while (0); /* CLASS_SPECIAL ( rec -- val ) */ do { #define PREPARE_STACK() do { \ PUSH_OOP (_extra1); \ } while (0) #define rec _extra1 #define val _extra1 #line 543 "vm.def" OOP classOOP; PREPARE_STACK (); EXPORT_REGS (); if UNCOMMON (IS_INT (rec)) { SEND_MESSAGE (_gst_builtin_selectors[CLASS_SPECIAL].symbol, 0); IMPORT_REGS (); FETCH; } if COMMON (class_cache_class == (classOOP = OOP_CLASS (rec)) && !execute_primitive_operation (class_cache_prim, 1)) { IMPORT_REGS (); NEXT_BC; } /* Not the same class that is in the cache, or the primitive failed -- send the message, and modify the cache if the send is resolved to a primitive. */ last_primitive = 0; SEND_MESSAGE (_gst_builtin_selectors[CLASS_SPECIAL].symbol, 0); IMPORT_REGS (); if COMMON (last_primitive) { class_cache_prim = last_primitive; class_cache_class = classOOP; NEXT_BC; } FETCH; #line 12539 "vm.inl" #undef PREPARE_STACK #undef rec #undef val } while (0); PUSH_OOP (_extra1); } NEXT_BC; bc255: { OOP _extra1; /* PREFETCH ( -- ) */ do { #line 207 "vm.def" PREFETCH; LOCAL_COUNTER++; #line 12558 "vm.inl" } while (0); /* LINE_NUMBER_BYTECODE ( -- ) */ do { #line 890 "vm.def" #line 12566 "vm.inl" } while (0); /* PUSH_OUTER_TEMP ( -- tos ) */ do { int n = 2; int scopes = 1; #define tos _extra1 #line 687 "vm.def" OOP contextOOP; gst_block_context context; context = (gst_block_context) OOP_TO_OBJ (_gst_this_context_oop); do { contextOOP = context->outerContext; context = (gst_block_context) OOP_TO_OBJ (contextOOP); } while (--scopes); tos = context->contextStack[n]; #line 12589 "vm.inl" #undef tos } while (0); PUSH_OOP (_extra1); } NEXT_BC; jump_around: ; smalltalk-3.2.5/kernel/0000755000175000017500000000000012130456010011756 500000000000000smalltalk-3.2.5/kernel/Makefile.frag0000644000175000017500000000011112130344111014243 00000000000000$(srcdir)/kernel/stamp-classes: \ touch $(srcdir)/kernel/stamp-classes smalltalk-3.2.5/kernel/SeqCollect.st0000644000175000017500000007775512130343734014341 00000000000000"====================================================================== | | SequenceableCollection Method Definitions | | ======================================================================" "====================================================================== | | Copyright 1988,92,94,95,99,2000,2001,2002,2003,2006,2007,2008,2009 | Free Software Foundation, Inc. | Written by Steve Byrne. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" Collection subclass: SequenceableCollection [ SequenceableCollection class >> join: aCollection separatedBy: sepCollection [ "Where aCollection is a collection of SequenceableCollections, answer a new instance with all the elements therein, in order, each separated by an occurrence of sepCollection." | newInst start | aCollection isEmpty ifTrue: [^self new: 0]. newInst := self new: (aCollection inject: sepCollection size * (aCollection size - 1) into: [:size :each | size + each size]). aCollection do: [:subColl | newInst addAll: subColl] separatedBy: [newInst addAll: sepCollection]. ^newInst ] examineOn: aStream [ "Print all the instance variables and context of the receiver on aStream" | instVars object output | self beConsistent. aStream nextPutAll: 'An instance of '; print: self class; nl. instVars := self class allInstVarNames. 1 to: instVars size do: [:i | object := self instVarAt: i. output := [object printString] on: Error do: [:ex | ex return: '%1 %2' % {object class article. object class name asString}]. aStream nextPutAll: ' '; nextPutAll: (instVars at: i); nextPutAll: ': '; nextPutAll: output; nl]. aStream nextPutAll: ' contents: ['; nl. self keysAndValuesDo: [:i :obj | | output | output := [obj printString] on: Error do: [:ex | ex return: '%1 %2' % {obj class article. obj class name asString}]. aStream nextPutAll: ' ['; print: i; nextPutAll: ']: '; nextPutAll: output; nl]. aStream nextPutAll: ' ]'; nl ] isSequenceable [ "Answer whether the receiver can be accessed by a numeric index with #at:/#at:put:." ^true ] = aCollection [ "Answer whether the receiver's items match those in aCollection" self class == aCollection class ifFalse: [^false]. self size = aCollection size ifFalse: [^false]. 1 to: self size do: [:i | (self at: i) = (aCollection at: i) ifFalse: [^false]]. ^true ] hash [ "Answer an hash value for the receiver" "Don't like this hash function; it can be made much better" | hash carry | hash := self size. self do: [:element | carry := (hash bitAnd: 536870912) > 0. hash := hash bitAnd: 536870911. hash := hash bitShift: 1. carry ifTrue: [hash := hash bitOr: 1]. hash := hash bitXor: element hash]. ^hash ] endsWith: aSequenceableCollection [ "Returns true if the receiver ends with the same characters as aSequenceableCollection." | delta | delta := self size - aSequenceableCollection size. delta >= 0 ifFalse: [ ^false ]. aSequenceableCollection keysAndValuesDo: [:i :each | (self at: i + delta) = each ifFalse: [^false]]. ^true ] startsWith: aSequenceableCollection [ "Returns true if the receiver starts with the same characters as aSequenceableCollection." self size >= aSequenceableCollection size ifFalse: [ ^false ]. aSequenceableCollection keysAndValuesDo: [:i :each | (self at: i) = each ifFalse: [^false]]. ^true ] at: anIndex ifAbsent: aBlock [ "Answer the anIndex-th item of the collection, or evaluate aBlock and answer the result if the index is out of range" (anIndex between: 1 and: self size) ifFalse: [^aBlock value]. ^self at: anIndex ] atRandom [ "Return a random item of the receiver." ^self at: (Random between: 1 and: self size) ] atAll: keyCollection [ "Answer a collection of the same kind returned by #collect:, that only includes the values at the given indices. Fail if any of the values in keyCollection is out of bounds for the receiver." | result | result := self copyEmptyForCollect: keyCollection size. keyCollection do: [:key | result add: (self at: key)]. ^result ] atAll: aCollection put: anObject [ "Put anObject at every index contained in aCollection" aCollection do: [:index | self at: index put: anObject] ] atAllPut: anObject [ "Put anObject at every index in the receiver" | to size | "Unroll completely for small collections..." (size := self size) = 0 ifTrue: [ ^self ]. self at: 1 put: anObject. size = 1 ifTrue: [ ^self ]. self at: 2 put: anObject. size = 2 ifTrue: [ ^self ]. self at: 3 put: anObject. size = 3 ifTrue: [ ^self ]. self at: 4 put: anObject. to := 4. "... and use memcpy repeatedly for larger ones." [ size > to ] whileTrue: [ self replaceFrom: to + 1 to: ((to := to + to) min: size) with: self startingAt: 1 ]. ] after: oldObject [ "Return the element after oldObject. Error if oldObject not found or if no following object is available" | i | i := self indexOf: oldObject. i = 0 ifTrue: [^SystemExceptions.NotFound signalOn: oldObject what: 'object']. ^self at: i + 1 ] before: oldObject [ "Return the element before oldObject. Error if oldObject not found or if no preceding object is available" | i | i := self indexOf: oldObject. i = 0 ifTrue: [^SystemExceptions.NotFound signalOn: oldObject what: 'object']. ^self at: i - 1 ] allButFirst [ "Answer a copy of the receiver without the first object." ^self copyFrom: 2 ] allButFirst: n [ "Answer a copy of the receiver without the first n objects." ^self copyFrom: n + 1 ] allButLast [ "Answer a copy of the receiver without the last object." ^self copyFrom: 1 to: self size - 1 ] allButLast: n [ "Answer a copy of the receiver without the last n objects." ^self copyFrom: 1 to: self size - n ] first [ "Answer the first item in the receiver" ^self at: 1 ] second [ "Answer the second item in the receiver" ^self at: 2 ] third [ "Answer the third item in the receiver" ^self at: 3 ] fourth [ "Answer the fourth item in the receiver" ^self at: 4 ] first: n [ "Answer the first n items in the receiver" ^self copyFrom: 1 to: n ] last: n [ "Answer the last n items in the receiver" ^self copyFrom: self size - n + 1 ] last [ "Answer the last item in the receiver" ^self at: self size ] includes: anObject [ "Answer whether we include anObject" "Reimplemented to avoid an expensive full-block" 1 to: self size do: [:index | anObject = (self at: index) ifTrue: [^true]]. ^false ] identityIncludes: anObject [ "Answer whether we include the anObject object" "Reimplemented to avoid an expensive full-block" 1 to: self size do: [:index | anObject == (self at: index) ifTrue: [^true]]. ^false ] indexOfSubCollection: aSubCollection startingAt: anIndex ifAbsent: exceptionBlock [ "Answer the first index > anIndex at which starts a sequence of items matching aSubCollection. Invoke exceptionBlock and answer its result if no such sequence is found" | selfSize subSize | subSize := aSubCollection size. subSize = 0 ifTrue: [ ^anIndex ]. selfSize := self size. anIndex + subSize - 1 <= selfSize ifTrue: [anIndex to: selfSize - subSize + 1 do: [:index | (self at: index) = (aSubCollection at: 1) ifTrue: [(self matchSubCollection: aSubCollection startingAt: index) ifTrue: [^index]]]]. ^exceptionBlock value ] indexOfSubCollection: aSubCollection startingAt: anIndex [ "Answer the first index > anIndex at which starts a sequence of items matching aSubCollection. Answer 0 if no such sequence is found." ^self indexOfSubCollection: aSubCollection startingAt: anIndex ifAbsent: [^0] ] indexOf: anElement startingAt: anIndex ifAbsent: exceptionBlock [ "Answer the first index > anIndex which contains anElement. Invoke exceptionBlock and answer its result if no item is found" anIndex < 1 | (anIndex > self size) ifTrue: ["If anIndex is just past the end of the collection, don't raise an error (this is the most generic solution that avoids that #indexOf: fails when the collection is empty." anIndex = (self size + 1) ifTrue: [^exceptionBlock value] ifFalse: [^self checkIndexableBounds: anIndex]]. anIndex to: self size do: [:index | (self at: index) = anElement ifTrue: [^index]]. ^exceptionBlock value ] identityIndexOf: anObject startingAt: anIndex ifAbsent: exceptionBlock [ "Answer the first index > anIndex which contains an object exactly identical to anObject. Invoke exceptionBlock and answer its result if no item is found" anIndex < 1 | (anIndex > self size) ifTrue: ["If anIndex is just past the end of the collection, don't raise an error (this is the most generic solution that avoids that #indexOf: fails when the collection is empty." anIndex = (self size + 1) ifTrue: [^exceptionBlock value] ifFalse: [^self checkIndexableBounds: anIndex]]. anIndex to: self size do: [:index | (self at: index) == anObject ifTrue: [^index]]. ^exceptionBlock value ] indexOfSubCollection: aSubCollection [ "Answer the first index > anIndex at which starts a sequence of items matching aSubCollection. Answer 0 if no such sequence is found." ^self indexOfSubCollection: aSubCollection startingAt: 1 ifAbsent: [^0] ] indexOfSubCollection: aSubCollection ifAbsent: exceptionBlock [ "Answer the first index > anIndex at which starts a sequence of items matching aSubCollection. Answer 0 if no such sequence is found." ^self indexOfSubCollection: aSubCollection startingAt: 1 ifAbsent: exceptionBlock ] indexOf: anElement startingAt: anIndex [ "Answer the first index > anIndex which contains anElement. Answer 0 if no item is found" ^self indexOf: anElement startingAt: anIndex ifAbsent: [^0] ] identityIndexOfLast: anElement ifAbsent: exceptionBlock [ "Answer the last index which contains an object identical to anElement. Invoke exceptionBlock and answer its result if no item is found" self size to: 1 by: -1 do: [:index | (self at: index) == anElement ifTrue: [^index]]. ^exceptionBlock value ] indexOfLast: anElement ifAbsent: exceptionBlock [ "Answer the last index which contains anElement. Invoke exceptionBlock and answer its result if no item is found" self size to: 1 by: -1 do: [:index | (self at: index) = anElement ifTrue: [^index]]. ^exceptionBlock value ] indexOf: anElement ifAbsent: exceptionBlock [ "Answer the index of the first occurrence of anElement in the receiver. Invoke exceptionBlock and answer its result if no item is found" ^self indexOf: anElement startingAt: 1 ifAbsent: exceptionBlock ] indexOf: anElement [ "Answer the index of the first occurrence of anElement in the receiver. Answer 0 if no item is found" ^self indexOf: anElement startingAt: 1 ifAbsent: [^0] ] identityIndexOf: anElement startingAt: anIndex [ "Answer the first index > anIndex which contains an object identical to anElement. Answer 0 if no item is found" ^self identityIndexOf: anElement startingAt: anIndex ifAbsent: [^0] ] identityIndexOf: anElement ifAbsent: exceptionBlock [ "Answer the index of the first occurrence of an object identical to anElement in the receiver. Invoke exceptionBlock and answer its result if no item is found" ^self identityIndexOf: anElement startingAt: 1 ifAbsent: exceptionBlock ] identityIndexOf: anElement [ "Answer the index of the first occurrence of an object identical to anElement in the receiver. Answer 0 if no item is found" ^self identityIndexOf: anElement startingAt: 1 ifAbsent: [^0] ] replaceAll: anObject with: anotherObject [ "In the receiver, replace every occurrence of anObject with anotherObject." 1 to: self size do: [:index | (self at: index) = anObject ifTrue: [self at: index put: anotherObject]] ] replaceFrom: start to: stop with: replacementCollection startingAt: repStart [ "Replace the items from start to stop with replacementCollection's items from repStart to repStart+stop-start" | delta maxStop minStop | minStop := start - 1. maxStop := self size min: minStop + replacementCollection size. (minStop <= stop and: [stop <= maxStop]) ifFalse: [^SystemExceptions.ArgumentOutOfRange signalOn: stop mustBeBetween: minStop and: maxStop]. delta := start - repStart. repStart > start ifTrue: [ start to: stop do: [:i | self at: i put: (replacementCollection at: i - delta)] ] ifFalse: [ stop to: start by: -1 do: [:i | self at: i put: (replacementCollection at: i - delta)] ] ] replaceFrom: start to: stop with: replacementCollection [ "Replace the items from start to stop with replacementCollection's items from 1 to stop-start+1 (in unexpected order if the collection is not sequenceable)." | i | i := start - 1. stop - i = replacementCollection size ifFalse: [^SystemExceptions.InvalidSize signalOn: replacementCollection size]. replacementCollection isSequenceable ifTrue: [ ^self replaceFrom: start to: stop with: replacementCollection startingAt: 1 ]. replacementCollection do: [:each | self at: (i := i + 1) put: each] ] replaceFrom: anIndex to: stopIndex withObject: replacementObject [ "Replace every item from start to stop with replacementObject." stopIndex - anIndex < -1 ifTrue: [^SystemExceptions.ArgumentOutOfRange signalOn: stopIndex mustBeBetween: anIndex and: self size]. anIndex to: stopIndex do: [:index | self at: index put: replacementObject] ] copyAfter: anObject [ "Answer a new collection holding all the elements of the receiver after the first occurrence of anObject, up to the last." ^self copyFrom: (self indexOf: anObject ifAbsent: [self size]) + 1 ] copyAfterLast: anObject [ "Answer a new collection holding all the elements of the receiver after the last occurrence of anObject, up to the last." ^self copyFrom: (self indexOfLast: anObject ifAbsent: [self size]) + 1 ] copyUpTo: anObject [ "Answer a new collection holding all the elements of the receiver from the first up to the first occurrence of anObject, excluded." ^self copyFrom: 1 to: (self indexOf: anObject ifAbsent: [self size + 1]) - 1 ] copyUpToLast: anObject [ "Answer a new collection holding all the elements of the receiver from the first up to the last occurrence of anObject, excluded." ^self copyFrom: 1 to: (self indexOfLast: anObject ifAbsent: [self size + 1]) - 1 ] copyReplaceFrom: start to: stop withObject: anObject [ "Answer a new collection of the same class as the receiver that contains the same elements as the receiver, in the same order, except for elements from index `start' to index `stop'. If start < stop, these are replaced by stop-start+1 copies of anObject. Instead, If start = (stop + 1), then every element of the receiver will be present in the answered copy; the operation will be an append if stop is equal to the size of the receiver or, if it is not, an insert before index `start'." | newSize repSize result | stop - start < -1 ifTrue: [^SystemExceptions.ArgumentOutOfRange signalOn: stop mustBeBetween: start - 1 and: self size]. stop >= start ifTrue: [^(self copy) atAll: (start to: stop) put: anObject; yourself]. newSize := self size - (stop - start). result := self copyEmpty: newSize. start > 1 ifTrue: [self from: 1 to: start - 1 do: [:each | result add: each]]. result add: anObject. stop < self size ifTrue: [self from: stop + 1 to: self size do: [:each | result add: each]]. ^result ] copyWithFirst: anObject [ "Answer a new collection holding all the elements of the receiver after the first occurrence of anObject, up to the last." ^self copyReplaceFrom: 1 to: 0 withObject: anObject ] copyFrom: start [ "Answer a new collection containing all the items in the receiver from the start-th." ^self copyFrom: start to: self size ] copyFrom: start to: stop [ "Answer a new collection containing all the items in the receiver from the start-th and to the stop-th" | len coll | stop < start ifTrue: [stop = (start - 1) ifTrue: [^self copyEmpty: 0]. ^SystemExceptions.ArgumentOutOfRange signalOn: stop mustBeBetween: start - 1 and: self size]. len := stop - start + 1. coll := self copyEmpty: len + 10. self from: start to: stop do: [:each | coll add: each]. ^coll ] copyReplaceAll: oldSubCollection with: newSubCollection [ "Answer a new collection in which all the sequences matching oldSubCollection are replaced with newSubCollection" | numOld newCollection sizeDifference newSubSize oldSubSize oldStart copySize index | numOld := self countSubCollectionOccurrencesOf: oldSubCollection. newSubSize := newSubCollection size. oldSubSize := oldSubCollection size. sizeDifference := newSubSize - oldSubSize. newCollection := self copyEmpty: self size + (sizeDifference * numOld). oldStart := 1. [index := self indexOfSubCollection: oldSubCollection startingAt: oldStart ifAbsent: ["Copy the remaining part of self onto the tail of the new collection." self from: oldStart to: self size do: [:each | newCollection add: each]. ^newCollection]. copySize := index - oldStart. self from: oldStart to: oldStart + copySize - 1 do: [:each | newCollection add: each]. newCollection addAll: newSubCollection. oldStart := oldStart + copySize + oldSubSize] repeat ] copyReplaceFrom: start to: stop with: replacementCollection [ "Answer a new collection of the same class as the receiver that contains the same elements as the receiver, in the same order, except for elements from index `start' to index `stop'. If start < stop, these are replaced by the contents of the replacementCollection. Instead, If start = (stop + 1), like in `copyReplaceFrom: 4 to: 3 with: anArray', then every element of the receiver will be present in the answered copy; the operation will be an append if stop is equal to the size of the receiver or, if it is not, an insert before index `start'." | newSize repSize result | stop - start < -1 ifTrue: [^SystemExceptions.ArgumentOutOfRange signalOn: stop mustBeBetween: start - 1 and: self size]. repSize := replacementCollection size. newSize := self size + repSize - (stop - start + 1). result := self copyEmpty: newSize. start > 1 ifTrue: [self from: 1 to: start - 1 do: [:each | result add: each]]. result addAll: replacementCollection. stop < self size ifTrue: [self from: stop + 1 to: self size do: [:each | result add: each]]. ^result ] join: sepCollection [ "Answer a new collection like my first element, with all the elements (in order) of all my elements (which should be collections) separated by sepCollection. I use my first element instead of myself as a prototype because my elements are more likely to share the desired properties than I am, such as in: #('hello,' 'world') join: ' ' => 'hello, world'" ^self isEmpty ifTrue: [#()] ifFalse: [self first species join: self separatedBy: sepCollection] ] nextPutAllOn: aStream [ "Write all the objects in the receiver to aStream" aStream next: self size putAll: self startingAt: 1 ] readStream [ "Answer a ReadStream streaming on the receiver" ^ReadStream on: self ] readWriteStream [ "Answer a ReadWriteStream which streams on the receiver" ^ReadWriteStream on: self ] anyOne [ "Answer an unspecified element of the collection." ^self first ] do: aBlock [ "Evaluate aBlock for all the elements in the sequenceable collection" 1 to: self size do: [:i | aBlock value: (self at: i)] ] do: aBlock separatedBy: sepBlock [ "Evaluate aBlock for all the elements in the sequenceable collection. Between each element, evaluate sepBlock without parameters." self isEmpty ifTrue: [^self]. aBlock value: (self at: 1). 2 to: self size do: [:i | sepBlock value. aBlock value: (self at: i)] ] doWithIndex: aBlock [ "Evaluate aBlock for all the elements in the sequenceable collection, passing the index of each element as the second parameter. This method is mantained for backwards compatibility and is not mandated by the ANSI standard; use #keysAndValuesDo:" 1 to: self size do: [:i | aBlock value: (self at: i) value: i] ] fold: binaryBlock [ "First, pass to binaryBlock the first and second elements of the receiver; for each subsequent element, pass the result of the previous evaluation and an element. Answer the result of the last invocation, or the first element if the collection has size 1. Fail if the collection is empty." "This method is redefined from Collection for efficiency only" | result | self isEmpty ifTrue: [^SystemExceptions.EmptyCollection signalOn: self]. result := self at: 1. self from: 2 to: self size do: [:element | result := binaryBlock value: result value: element]. ^result ] keys [ "Return an Interval corresponding to the valid indices in the receiver." ^1 to: self size ] keysAndValuesDo: aBlock [ "Evaluate aBlock for all the elements in the sequenceable collection, passing the index of each element as the first parameter and the element as the second." 1 to: self size do: [:i | aBlock value: i value: (self at: i)] ] from: startIndex to: stopIndex do: aBlock [ "Evaluate aBlock for all the elements in the sequenceable collection whose indices are in the range index to stopIndex" startIndex to: stopIndex do: [:i | aBlock value: (self at: i)] ] from: startIndex to: stopIndex doWithIndex: aBlock [ "Evaluate aBlock for all the elements in the sequenceable collection whose indices are in the range index to stopIndex, passing the index of each element as the second parameter. This method is mantained for backwards compatibility and is not mandated by the ANSI standard; use #from:to:keysAndValuesDo:" startIndex to: stopIndex do: [:i | aBlock value: (self at: i) value: i] ] from: startIndex to: stopIndex keysAndValuesDo: aBlock [ "Evaluate aBlock for all the elements in the sequenceable collection whose indices are in the range index to stopIndex, passing the index of each element as the first parameter and the element as the second." startIndex to: stopIndex do: [:i | aBlock value: i value: (self at: i)] ] findFirst: aBlock [ "Returns the index of the first element of the sequenceable collection for which aBlock returns true, or 0 if none" self doWithIndex: [:each :i | (aBlock value: each) ifTrue: [^i]]. ^0 ] findLast: aBlock [ "Returns the index of the last element of the sequenceable collection for which aBlock returns true, or 0 if none does" | i | i := self size. self reverseDo: [:each | (aBlock value: each) ifTrue: [^i]. i := i - 1]. ^0 ] reverse [ "Answer the receivers' contents in reverse order" | result | result := self copyEmptyForCollect. self reverseDo: [:each | result add: each]. ^result ] reverseDo: aBlock [ "Evaluate aBlock for all elements in the sequenceable collection, from the last to the first." self size to: 1 by: -1 do: [:i | aBlock value: (self at: i)] ] with: aSequenceableCollection do: aBlock [ "Evaluate aBlock for each pair of elements took respectively from the receiver and from aSequenceableCollection. Fail if the receiver has not the same size as aSequenceableCollection." self size = aSequenceableCollection size ifFalse: [^SystemExceptions.InvalidSize signalOn: aSequenceableCollection]. 1 to: self size do: [:i | aBlock value: (self at: i) value: (aSequenceableCollection at: i)] ] with: aSequenceableCollection collect: aBlock [ "Evaluate aBlock for each pair of elements took respectively from the receiver and from aSequenceableCollection; answer a collection of the same kind of the receiver, made with the block's return values. Fail if the receiver has not the same size as aSequenceableCollection." | newCollection | self size = aSequenceableCollection size ifFalse: [^SystemExceptions.InvalidSize signalOn: aSequenceableCollection]. newCollection := self copyEmptyForCollect. 1 to: self size do: [:i | newCollection add: (aBlock value: (self at: i) value: (aSequenceableCollection at: i))]. ^newCollection ] with: aSequenceableCollection [ "Return an Array with the same size as the receiver and aSequenceableCollection, each element of which is a 2-element Arrays including one element from the receiver and one from aSequenceableCollection." self size = aSequenceableCollection size ifFalse: [^SystemExceptions.InvalidSize signalOn: aSequenceableCollection]. ^1 to: self size collect: [ :each | { self at: each. aSequenceableCollection at: each } ] ] with: seqColl1 with: seqColl2 [ "Return an Array with the same size as the receiver and the arguments, each element of which is a 3-element Arrays including one element from the receiver and one from each argument." self size = seqColl1 size ifFalse: [^SystemExceptions.InvalidSize signalOn: seqColl1]. self size = seqColl2 size ifFalse: [^SystemExceptions.InvalidSize signalOn: seqColl2]. ^1 to: self size collect: [ :each | { self at: each. seqColl1 at: each. seqColl2 at: each } ] ] with: seqColl1 with: seqColl2 with: seqColl3 [ "Return an Array with the same size as the receiver and the arguments, each element of which is a 4-element Arrays including one element from the receiver and one from each argument." self size = seqColl1 size ifFalse: [^SystemExceptions.InvalidSize signalOn: seqColl1]. self size = seqColl2 size ifFalse: [^SystemExceptions.InvalidSize signalOn: seqColl2]. self size = seqColl3 size ifFalse: [^SystemExceptions.InvalidSize signalOn: seqColl3]. ^1 to: self size collect: [ :each | { self at: each. seqColl1 at: each. seqColl2 at: each. seqColl3 at: each } ] ] sorted [ "Return a copy of the receiver sorted according to the default sort block, which uses #<= to compare items." ^(self copyEmptyForCollect: self size) addAll: self asSortedCollection; yourself ] sorted: sortBlock [ "Return a copy of the receiver sorted according to the given sort block, which accepts pair of items and returns true if the first item is less than the second one." ^(self copyEmptyForCollect: self size) addAll: (self asSortedCollection: sortBlock); yourself ] sort [ "Sort the contents of the receiver according to the default sort block, which uses #<= to compare items." self replaceFrom: 1 to: self size with: self asSortedCollection startingAt: 1 ] sort: sortBlock [ "Sort the contents of the receiver according to the given sort block, which accepts pair of items and returns true if the first item is less than the second one." self replaceFrom: 1 to: self size with: (self asSortedCollection: sortBlock) startingAt: 1 ] matchSubCollection: aSubCollection startingAt: anIndex [ "Private - Answer whether the items from index anIndex match those in aSubCollection. The first item is ignored" | ourIndex | ourIndex := anIndex. 2 to: aSubCollection size do: [:index | ourIndex := ourIndex + 1. (self at: ourIndex) = (aSubCollection at: index) ifFalse: [^false]]. ^true ] countSubCollectionOccurrencesOf: aSubCollection [ | colIndex subColIndex count | colIndex := 1. count := 0. [subColIndex := self indexOfSubCollection: aSubCollection startingAt: colIndex. subColIndex > 0] whileTrue: [count := count + 1. colIndex := subColIndex + aSubCollection size]. ^count ] size [ "Answer a dummy size of 0, so that SequenceableCollection>>#do: works." ^0 ] growSize [ ^(self size max: 8) ] swap: anIndex with: anotherIndex [ "Swap the item at index anIndex with the item at index another index" | saved | saved := self at: anIndex. self at: anIndex put: (self at: anotherIndex). self at: anotherIndex put: saved ] ] smalltalk-3.2.5/kernel/ArrayColl.st0000644000175000017500000003713112123404352014147 00000000000000"====================================================================== | | ArrayedCollection Method Definitions | | ======================================================================" "====================================================================== | | Copyright 1988,92,94,95,99,2000,2001,2002,2006,2007,2008,2009 | Free Software Foundation, Inc. | Written by Steve Byrne. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" SequenceableCollection subclass: ArrayedCollection [ ArrayedCollection class >> new: size withAll: anObject [ "Answer a collection with the given size, whose elements are all set to anObject" ^(self new: size) atAllPut: anObject; yourself ] ArrayedCollection class >> streamContents: aBlock [ "Create a ReadWriteStream on an empty instance of the receiver; pass the stream to aBlock, then retrieve its contents and answer them." | stream | stream := ReadWriteStream on: (self new: 10). stream truncate. aBlock value: stream. ^stream contents ] ArrayedCollection class >> withAll: aCollection [ "Answer a collection whose elements are the same as those in aCollection" | anArrayedCollection index | anArrayedCollection := self new: aCollection size. index := 1. aCollection do: [:each | anArrayedCollection at: index put: each. index := index + 1]. ^anArrayedCollection ] ArrayedCollection class >> with: element1 [ "Answer a collection whose only element is element1" ^(self new: 1) at: 1 put: element1; yourself ] ArrayedCollection class >> with: element1 with: element2 [ "Answer a collection whose only elements are the parameters in the order they were passed" ^(self new: 2) at: 1 put: element1; at: 2 put: element2; yourself ] ArrayedCollection class >> with: element1 with: element2 with: element3 [ "Answer a collection whose only elements are the parameters in the order they were passed" ^(self new: 3) at: 1 put: element1; at: 2 put: element2; at: 3 put: element3; yourself ] ArrayedCollection class >> with: element1 with: element2 with: element3 with: element4 [ "Answer a collection whose only elements are the parameters in the order they were passed" ^(self new: 4) at: 1 put: element1; at: 2 put: element2; at: 3 put: element3; at: 4 put: element4; yourself ] ArrayedCollection class >> with: element1 with: element2 with: element3 with: element4 with: element5 [ "Answer a collection whose only elements are the parameters in the order they were passed" ^(self new: 5) at: 1 put: element1; at: 2 put: element2; at: 3 put: element3; at: 4 put: element4; at: 5 put: element5; yourself ] ArrayedCollection class >> join: aCollection [ "Where aCollection is a collection of SequenceableCollections, answer a new instance with all the elements therein, in order." | newInst start | newInst := self new: (aCollection inject: 0 into: [:size :each | size + each size]). start := 1. aCollection do: [:subColl | newInst replaceFrom: start to: (start := start + subColl size) - 1 with: subColl]. ^newInst ] ArrayedCollection class >> join: aCollection separatedBy: sepCollection [ "Where aCollection is a collection of SequenceableCollections, answer a new instance with all the elements therein, in order, each separated by an occurrence of sepCollection." | newInst start | aCollection isEmpty ifTrue: [^self new: 0]. newInst := self new: (aCollection inject: sepCollection size * (aCollection size - 1) into: [:size :each | size + each size]). start := 1. aCollection do: [:subColl | newInst replaceFrom: start to: (start := start + subColl size) - 1 with: subColl] separatedBy: [newInst replaceFrom: start to: (start := start + sepCollection size) - 1 with: sepCollection]. ^newInst ] add: value [ self shouldNotImplement ] , aSequenceableCollection [ "Answer a new instance of an ArrayedCollection containing all the elements in the receiver, followed by all the elements in aSequenceableCollection" ^(self copyEmpty: self size + aSequenceableCollection size) replaceFrom: 1 to: self size with: self startingAt: 1; replaceFrom: self size + 1 to: self size + aSequenceableCollection size with: aSequenceableCollection startingAt: 1; yourself ] atAll: keyCollection [ "Answer a collection of the same kind returned by #collect:, that only includes the values at the given indices. Fail if any of the values in keyCollection is out of bounds for the receiver." | result i | result := self copyEmptyForCollect: keyCollection size. i := 0. keyCollection do: [:key | result at: (i := i + 1) put: (self at: key)]. ^result ] copyFrom: start to: stop [ "Answer a new collection containing all the items in the receiver from the start-th and to the stop-th" | len | stop < start ifTrue: [stop = (start - 1) ifTrue: [^self copyEmpty: 0]. ^SystemExceptions.ArgumentOutOfRange signalOn: stop mustBeBetween: start - 1 and: self size]. len := stop - start + 1. ^(self copyEmpty: len) replaceFrom: 1 to: len with: self startingAt: start; yourself ] copyWithout: oldElement [ "Answer a copy of the receiver to which all occurrences of oldElement are removed" | newCollection numOccurrences i | numOccurrences := 0. self do: [:element | element = oldElement ifTrue: [numOccurrences := numOccurrences + 1]]. newCollection := self copyEmpty: self size - numOccurrences. i := 1. self do: [:element | element = oldElement ifFalse: [newCollection at: i put: element. i := i + 1]]. ^newCollection ] copyWith: anElement [ "Answer a new instance of an ArrayedCollection containing all the elements in the receiver, followed by the single item anElement" | result | ^(self copyEmpty: self size + 1) replaceFrom: 1 to: self size with: self startingAt: 1; at: self size + 1 put: anElement; yourself ] select: aBlock [ "Answer a new instance of an ArrayedCollection containing all the elements in the receiver which, when passed to aBlock, answer true" | newCollection | newCollection := WriteStream on: self copyEmpty. self do: [:element | (aBlock value: element) ifTrue: [newCollection nextPut: element]]. ^newCollection contents ] reject: aBlock [ "Answer a new instance of an ArrayedCollection containing all the elements in the receiver which, when passed to aBlock, answer false" | newCollection | newCollection := WriteStream on: self copyEmpty. self do: [:element | (aBlock value: element) ifFalse: [newCollection nextPut: element]]. ^newCollection contents ] collect: aBlock [ "Answer a new instance of an ArrayedCollection containing all the results of evaluating aBlock passing each of the receiver's elements" | newCollection | newCollection := self copyEmptyForCollect. 1 to: self size do: [:i | newCollection at: i put: (aBlock value: (self at: i))]. ^newCollection ] with: aSequenceableCollection collect: aBlock [ "Evaluate aBlock for each pair of elements took respectively from the receiver and from aSequenceableCollection; answer a collection of the same kind of the receiver, made with the block's return values. Fail if the receiver has not the same size as aSequenceableCollection." | newCollection | self size = aSequenceableCollection size ifFalse: [^SystemExceptions.InvalidSize signalOn: aSequenceableCollection]. newCollection := self copyEmpty. 1 to: self size do: [:i | newCollection at: i put: (aBlock value: (self at: i) value: (aSequenceableCollection at: i))]. ^newCollection ] copyReplaceFrom: start to: stop withObject: anObject [ "Answer a new collection of the same class as the receiver that contains the same elements as the receiver, in the same order, except for elements from index `start' to index `stop'. If start < stop, these are replaced by stop-start+1 copies of anObject. Instead, If start = (stop + 1), then every element of the receiver will be present in the answered copy; the operation will be an append if stop is equal to the size of the receiver or, if it is not, an insert before index `start'." | newSize end result | stop - start < -1 ifTrue: [^SystemExceptions.ArgumentOutOfRange signalOn: stop mustBeBetween: start - 1 and: self size]. end := stop >= start ifTrue: [ stop ] ifFalse: [ start ]. ^(self copyEmpty: (newSize := end + (self size - stop))) replaceFrom: 1 to: start - 1 with: self startingAt: 1; replaceFrom: start to: end withObject: anObject; replaceFrom: end + 1 to: newSize with: self startingAt: stop + 1; yourself ] copyReplaceAll: oldSubCollection with: newSubCollection [ "Answer a new collection in which all the sequences matching oldSubCollection are replaced with newSubCollection" | numOld newCollection sizeDifference newSubSize oldSubSize newStart oldStart copySize index | numOld := self countSubCollectionOccurrencesOf: oldSubCollection. newSubSize := newSubCollection size. oldSubSize := oldSubCollection size. sizeDifference := newSubSize - oldSubSize. newCollection := self copyEmpty: self size + (sizeDifference * numOld). oldStart := newStart := 1. [index := self indexOfSubCollection: oldSubCollection startingAt: oldStart ifAbsent: ["Copy the remaining part of self onto the tail of the new collection." newCollection replaceFrom: newStart to: newCollection size with: self startingAt: oldStart. ^newCollection]. copySize := index - oldStart. newCollection replaceFrom: newStart to: newStart + copySize - 1 with: self startingAt: oldStart. newStart := newStart + copySize. newCollection replaceFrom: newStart to: newStart + newSubSize - 1 with: newSubCollection startingAt: 1. oldStart := oldStart + copySize + oldSubSize. newStart := newStart + newSubSize] repeat ] copyReplaceFrom: start to: stop with: replacementCollection [ "Answer a new collection of the same class as the receiver that contains the same elements as the receiver, in the same order, except for elements from index `start' to index `stop'. If start < stop, these are replaced by the contents of the replacementCollection. Instead, If start = (stop + 1), like in `copyReplaceFrom: 4 to: 3 with: anArray', then every element of the receiver will be present in the answered copy; the operation will be an append if stop is equal to the size of the receiver or, if it is not, an insert before index `start'." | newSize repSize | stop - start < -1 ifTrue: [^SystemExceptions.ArgumentOutOfRange signalOn: stop mustBeBetween: start - 1 and: self size]. repSize := replacementCollection size. newSize := self size + repSize - (stop - start + 1). ^(self copyEmpty: newSize) replaceFrom: 1 to: start - 1 with: self startingAt: 1; replaceFrom: start to: start + repSize - 1 with: replacementCollection; replaceFrom: start + repSize to: newSize with: self startingAt: stop + 1; yourself ] reverse [ "Answer the receivers' contents in reverse order" | result complement | result := self copyEmpty. complement := self size + 1. 1 to: self size do: [:i | result at: i put: (self at: complement - i)]. ^result ] sorted [ "Return a copy of the receiver sorted according to the default sort block, which uses #<= to compare items." ^self copyEmpty replaceFrom: 1 to: self size with: self asSortedCollection startingAt: 1 ] sorted: sortBlock [ "Return a copy of the receiver sorted according to the given sort block, which accepts pair of items and returns true if the first item is less than the second one." ^self copyEmpty replaceFrom: 1 to: self size with: (self asSortedCollection: sortBlock) startingAt: 1 ] storeOn: aStream [ "Store Smalltalk code compiling to the receiver on aStream" | index | aStream nextPutAll: '(('; nextPutAll: self class storeString; nextPutAll: ' basicNew: '. self basicSize printOn: aStream. aStream nextPut: $). index := 1. self do: [:element | aStream nextPutAll: ' at: '. index printOn: aStream. aStream nextPutAll: ' put: '. element storeOn: aStream. aStream nextPut: $;. index := index + 1]. index > 1 ifTrue: [aStream nextPutAll: ' yourself']. aStream nextPut: $) ] copyEmpty [ "Answer an empty copy of the receiver" ^self copyEmpty: self size ] grow [ "Private - Grow by some amount" self growBy: self growSize ] copyGrowTo: newSize [ "Private - Answer a copy of the receiver grown to newSize elements" | newCollection | newCollection := self copyEmpty: newSize. newCollection replaceFrom: 1 to: self size with: self startingAt: 1. ^newCollection ] growBy: delta [ "Private - Make the receiver grow by delta elements" ^self become: (self copyGrowTo: self basicSize + delta) ] growTo: newSize [ "Private - Make the receiver grow to a size of newSize" ^self become: (self copyGrowTo: newSize) ] writeStream [ "Answer a WriteStream streaming on the receiver" ^WriteStream on: self ] size [ "Answer the size of the receiver" ] ] smalltalk-3.2.5/kernel/PkgLoader.st0000644000175000017500000014315312123404352014131 00000000000000"====================================================================== | | PackageLoader Method Definitions | | ======================================================================" "====================================================================== | | Copyright 1999,2000,2001,2002,2003,2004,2005,2007,2008,2009 | Free Software Foundation, Inc. | Written by Paolo Bonzini. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" Namespace current: Kernel [ Notification subclass: PackageSkip [ ] ] Namespace current: SystemExceptions [ NotFound subclass: PackageNotAvailable [ PackageNotAvailable class >> signal: aString [ "Signal an exception saying that the package named aString can't be found." ^super signalOn: aString what: 'package' ] PackageNotAvailable class >> signal: package reason: reason [ "Signal an exception saying that be package named package can't be found because the reason named reason." ^super signalOn: package reason: reason ] isResumable [ "Answer true. Package unavailability is resumable, because the package files might just lie elsewhere." ^true ] ] ] Namespace current: Kernel [ Object subclass: PackageGroup [ printOn: aStream [ "Print the XML source code for the information that the PackageLoader holds on aStream." aStream nextPutAll: ''; nl. self do: [:each | aStream space: 2. each printOn: aStream indent: 2. aStream nl] separatedBy: [aStream nl]. aStream nextPutAll: '' ] at: aString [ ^self at: aString ifAbsent: [SystemExceptions.PackageNotAvailable signal: aString] ] at: aString ifAbsent: aBlock [ self subclassResponsibility ] do: aBlock [ self keys do: [:each | aBlock value: (self at: each)] ] do: aBlock separatedBy: sepBlock [ self keys do: [:each | aBlock value: (self at: each)] separatedBy: sepBlock ] keys [ self subclassResponsibility ] includesKey: aString [ self subclassResponsibility ] extractDependenciesFor: packagesList ifMissing: aBlock [ "Answer an OrderedCollection containing all the packages which you have to load to enable the packages in packagesList, in an appropriate order. For example PackageLoader extractDependenciesFor: #('BloxTestSuite' 'Blox' 'Browser') on a newly built image will evaluate to an OrderedCollection containing 'Kernel', 'Blox', 'BloxTestSuite' and 'Browser'. Note that Blox has been moved before BloxTestSuite. Pass an error message to aBlock if one or more packages need prerequisites which are not available." | toBeLoaded featuresFound dependencies allPrereq allFeatures | featuresFound := Set withAll: Smalltalk.Features. featuresFound := featuresFound collect: [:each | each asString]. toBeLoaded := packagesList asOrderedCollection. toBeLoaded := toBeLoaded collect: [:each | each asString]. toBeLoaded removeAll: featuresFound ifAbsent: [:doesNotMatter | ]. dependencies := packagesList collect: [:each | each asString]. [allPrereq := Set new. allFeatures := Set new. dependencies do: [:name | | package | (featuresFound includes: name) ifFalse: [package := self at: name ifAbsent: [^aBlock value: name]. allPrereq addAll: package prerequisites. allFeatures addAll: package features]]. "I don't think there will never be lots of packages in newDep (say more than 5), so I think it is acceptable to remove duplicates this naive way. Note that we remove duplicates from toBeLoaded so that prerequisites are always loaded *before*." toBeLoaded removeAll: allPrereq ifAbsent: [:doesNotMatter | ]. toBeLoaded removeAll: allFeatures ifAbsent: [:doesNotMatter | ]. allPrereq removeAll: allFeatures ifAbsent: [:doesNotMatter | ]. featuresFound addAll: allFeatures. toBeLoaded addAllFirst: allPrereq. "Proceed recursively with the prerequisites for allPrereq" dependencies := allPrereq. dependencies notEmpty] whileTrue. ^toBeLoaded ] refresh [ self refresh: ##(Date newDay: 1 month: #jan year: 1900) ] refresh: aLoadDate [ self subclassResponsibility ] ] ] Namespace current: Kernel [ PackageGroup subclass: PackageDirectories [ | dirs | PackageDirectories class >> new [ ^super new initialize ] postCopy [ dirs := dirs copy ] add: aDirectory [ ^dirs add: aDirectory ] at: aString ifAbsent: aBlock [ dirs do: [:each | | package | package := each at: aString ifAbsent: [nil]. package isNil ifFalse: [^package]]. ^aBlock value ] keys [ | keys | keys := Set new. dirs do: [:each | keys addAll: each keys]. ^keys ] includesKey: aString [ ^dirs anySatisfy: [:each | each includesKey: aString] ] refresh: aLoadDate [ dirs do: [:each | each refresh: aLoadDate] ] initialize [ dirs := OrderedCollection new ] ] ] Namespace current: Kernel [ PackageGroup subclass: PackageContainer [ | packages file | file [ ^file ] fileName [ ^self file name ] file: aFile [ file := aFile ] packages [ packages isNil ifTrue: [packages := LookupTable new]. ^packages ] packages: aDictionary [ packages := aDictionary ] at: aString ifAbsent: aBlock [ ^self packages at: aString asString ifAbsent: aBlock ] keys [ ^self packages keys ] includesKey: aString [ ^self packages includesKey: aString ] baseDirectoriesFor: aPackage [ self subclassResponsibility ] refresh: loadDate [ "Private - Process the XML source in the packages file, creating Package objects along the way." self subclassResponsibility ] parse: file [ | open ch cdata tag package allPackages | open := false. allPackages := OrderedCollection new. [cdata := cdata isNil ifTrue: [file upTo: $<] ifFalse: [cdata , (file upTo: $<)]. file atEnd] whileFalse: [cdata trimSeparators isEmpty ifFalse: [^self error: 'unexpected character data']. ch := file peek. ch == $! ifTrue: [file skipTo: $>]. ch == $/ ifTrue: [file next. (tag := file upTo: $>) = 'packages' ifTrue: [^self]. ^self error: 'unmatched end tag ' , tag]. ch isAlphaNumeric ifTrue: [open ifFalse: [tag := file upTo: $>. tag = 'package' ifTrue: [package := Package new parse: file tag: 'package'] ifFalse: [tag = 'packages' ifFalse: [^self error: 'expected packages tag']. open := true]] ifTrue: [file skip: -1. package := Package parse: file]. package notNil ifTrue: [package name isNil ifTrue: [^self error: 'missing package name in ' , self fileName]. [self testPackageValidity: package. self packages at: package name put: package. allPackages add: package] on: PackageSkip do: [:ex | ex return]. open ifFalse: [^allPackages]]. package := nil]]. ^allPackages ] testPackageValidity: package [ package baseDirectories: (self baseDirectoriesFor: package). ] ] ] Namespace current: Kernel [ PackageContainer subclass: PackageDirectory [ | baseDirectories baseDirCache | PackageContainer class >> on: aFile baseDirectories: aBlock [ ^(super new) file: aFile; baseDirectories: aBlock ] baseDirectoriesFor: aPacakge [ baseDirCache isNil ifTrue: [self refresh]. ^baseDirCache ] baseDirectories: aBlock [ baseDirectories := aBlock ] refresh: loadDate [ "Private - Process the XML source in the packages file, creating Package objects along the way." | dir allDirs | dir := self file parent. allDirs := Smalltalk imageLocal ifTrue: [{Directory image} , baseDirectories value] ifFalse: [baseDirectories value]. ((self file exists and: [self file lastModifyTime > loadDate]) or: [(dir exists and: [dir lastModifyTime > loadDate]) or: [allDirs ~= baseDirCache]]) ifTrue: [baseDirCache := allDirs. self refreshPackageList. self refreshStarList: dir] ] refreshPackageList [ baseDirCache isEmpty ifTrue: [^self]. self file exists ifFalse: [^self]. self file withReadStreamDo: [ :fileStream | [self parse: fileStream] on: SystemExceptions.PackageNotAvailable do: [:ex | ex resignalAs: PackageSkip new]]. self packages: (self packages reject: [:each | each isDisabled]) ] refreshStarList: dir [ dir exists ifFalse: [^self]. dir filesMatching: '*.star' do: [:starFile | | package | package := Kernel.StarPackage file: starFile. self packages at: package name put: package] ] ] ] Namespace current: Kernel [ Object subclass: PackageInfo [ | name | createNamespace [ "Create the path of namespaces indicated by our namespace field in dot notation, and answer the final namespace" | ns | ns := Smalltalk. self namespace isNil ifTrue: [^ns]. (self namespace subStrings: $.) do: [:each | | key | key := each asSymbol. (ns includesKey: key) ifFalse: [ns addSubspace: key]. ns := ns at: key]. ^ns ] fileIn [ "File in the given package and its dependencies." self name isNil ifTrue: ["Other packages cannot be dependent on this one." PackageLoader fileInPackages: self prerequisites. self primFileIn] ifFalse: [PackageLoader fileInPackage: self name] ] fullPathsOf: aCollection [ "Resolve the names in aCollection according to the base directories in baseDirectories, and return the collection with the FilePaths. Raise a PackageNotAvailable exception if no directory was found for one or more files in aCollection." ^aCollection collect: [:fileName | self fullPathOf: fileName] ] / fileName [ "Resolve the file name according to the base directories in baseDirectories, and return a FilePath for the full filename. Raise a PackageNotAvailable exception if no directory was found for fileName." ^self fullPathOf: fileName ] fullPathOf: fileName [ self subclassResponsibility ] isDisabled [ ^false ] printXmlOn: aStream collection: aCollection tag: aString indent: indent [ "Private - Print aCollection on aStream as a sequence of aString tags." aCollection do: [:each | aStream nextPutAll: ' <'; nextPutAll: aString; nextPut: $>; nextPutAll: each; nextPutAll: '; nl; space: indent] ] printOn: aStream [ self printOn: aStream indent: 0 ] printOn: aStream indent: indent [ self printOn: aStream tag: 'package' indent: indent ] printOn: aStream tag: tag indent: indent [ "Print a representation of the receiver on aStream (it happens to be XML." aStream nextPut: $<; nextPutAll: tag; nextPut: $>; nl; space: indent. self name isNil ifFalse: [aStream nextPutAll: ' '; nextPutAll: self name; nextPutAll: ''; nl; space: indent]. self url isNil ifFalse: [aStream nextPutAll: ' '; nextPutAll: self url; nextPutAll: ''; nl; space: indent]. self namespace isNil ifFalse: [aStream nextPutAll: ' '; nextPutAll: self namespace; nextPutAll: ''; nl; space: indent]. self test isNil ifFalse: [aStream space: 2. self test printOn: aStream tag: 'test' indent: indent + 2. aStream nl; space: indent]. self printXmlOn: aStream collection: self features asSortedCollection tag: 'provides' indent: indent. self printXmlOn: aStream collection: self prerequisites asSortedCollection tag: 'prereq' indent: indent. self printXmlOn: aStream collection: self sunitScripts tag: 'sunit' indent: indent. self printXmlOn: aStream collection: self callouts asSortedCollection tag: 'callout' indent: indent. self printXmlOn: aStream collection: self libraries asSortedCollection tag: 'library' indent: indent. self printXmlOn: aStream collection: self modules asSortedCollection tag: 'module' indent: indent. self relativeDirectory isNil ifFalse: [aStream nextPutAll: ' '; nextPutAll: self relativeDirectory; nextPutAll: ''; nl; space: indent]. self files size + self builtFiles size > 1 ifTrue: [aStream nl; space: indent]. self printXmlOn: aStream collection: self fileIns tag: 'filein' indent: indent. self printXmlOn: aStream collection: (self files copy removeAll: self fileIns ifAbsent: []; yourself) tag: 'file' indent: indent. self printXmlOn: aStream collection: self builtFiles tag: 'built-file' indent: indent. self startScript isNil ifFalse: [aStream nextPutAll: ' '; nextPutAll: self startScript; nextPutAll: ''; nl; space: indent]. self stopScript isNil ifFalse: [aStream nextPutAll: ' '; nextPutAll: self stopScript; nextPutAll: ''; nl; space: indent]. aStream nextPutAll: ' ] name [ "Answer the name of the package." ^name ] name: aString [ "Set to aString the name of the package." name := aString ] url [ "Answer the URL at which the package repository can be found." self subclassResponsibility ] namespace [ "Answer the namespace in which the package is loaded." self subclassResponsibility ] features [ "Answer a (modifiable) Set of features provided by the package." self subclassResponsibility ] prerequisites [ "Answer a (modifiable) Set of prerequisites." self subclassResponsibility ] builtFiles [ "Answer a (modifiable) OrderedCollection of files that are part of the package but are not distributed." self subclassResponsibility ] files [ "Answer a (modifiable) OrderedCollection of files that are part of the package." self subclassResponsibility ] allFiles [ "Answer an OrderedCollection of all the files, both built and distributed, that are part of the package." | result | result := self files , self builtFiles. self test isNil ifFalse: [result := result , (self test allFiles: self test relativeDirectory)]. ^result ] allDistFiles [ "Answer an OrderedCollection of all the files, both built and distributed, that are part of the package." | result | result := self files. self test isNil ifFalse: [result := result , (self test allDistFiles: self test relativeDirectory)]. ^result ] fileIns [ "Answer a (modifiable) OrderedCollections of files that are to be filed-in to load the package. This is usually a subset of `files' and `builtFiles'." self subclassResponsibility ] libraries [ "Answer a (modifiable) Set of shared library names that are required to load the package." self subclassResponsibility ] modules [ "Answer a (modifiable) Set of modules that are required to load the package." self subclassResponsibility ] sunitScript [ "Answer a String containing a SUnit script that describes the package's test suite." self sunitScripts isEmpty ifTrue: [^'']. ^self sunitScripts fold: [:a :b | a , ' ' , b] ] sunitScripts [ "Answer a (modifiable) OrderedCollection of SUnit scripts that compose the package's test suite." self subclassResponsibility ] startScript [ "Answer the start script for the package." self subclassResponsibility ] stopScript [ "Answer the stop script for the package." self subclassResponsibility ] callouts [ "Answer a (modifiable) Set of call-outs that are required to load the package. Their presence is checked after the libraries and modules are loaded so that you can do a kind of versioning." self subclassResponsibility ] relativeDirectory [ "Answer the directory from which to load the package, relative to the package file." self subclassResponsibility ] directory [ "Answer the base directory from which to load the package." self subclassResponsibility ] loaded [ ^self name notNil and: [Smalltalk hasFeatures: self name] ] start [ "File in the receiver and evaluate its start script, passing nil as the argument." self fileIn. self startScript isNil ifTrue: [ ^self ]. ('Eval [', (self startScript % {'nil'}), ']') readStream fileIn. ] start: anObject [ "File in the receiver and evaluate its start script, passing anObject's displayString as the argument." self fileIn. self startScript isNil ifTrue: [ ^self ]. ('Eval [', (self startScript % { anObject displayString storeString }), ']') readStream fileIn. ] stop [ "Evaluate the stop script of the receiver, passing nil as the argument." self loaded ifFalse: [ ^self ]. self stopScript isNil ifTrue: [ ^self ]. ('Eval [', (self stopScript % {'nil'}), ']') readStream fileIn. ] stop: anObject [ "Evaluate the stop script of the receiver, passing anObject's displayString as the argument." self loaded ifFalse: [ ^self ]. self stopScript isNil ifTrue: [ ^self ]. ('Eval [', (self stopScript % { anObject displayString storeString }), ']') readStream fileIn. ] allFiles: prefix [ prefix isNil ifTrue: [^self allFiles]. ^self allFiles collect: [:each | File append: each to: prefix] ] allDistFiles: prefix [ prefix isNil ifTrue: [^self allDistFiles]. ^self allDistFiles collect: [:each | File append: each to: prefix] ] ] ] Namespace current: Kernel [ PackageInfo subclass: StarPackage [ | file loadedPackage | StarPackage class >> file: file [ ^(self new) file: file; name: (File stripPathFrom: (File stripExtensionFrom: file name)); yourself ] fullPathOf: fileName [ "Try appending 'self directory' and fileName to each of the directory in baseDirectories, and return the path to the first tried filename that exists. Raise a PackageNotAvailable exception if no directory is found that contains the file." ^self loadedPackage fullPathOf: fileName ] test [ "Answer the test subpackage for this package." ^self loadedPackage test ] url [ "Answer the URL at which the package repository can be found." ^self loadedPackage url ] namespace [ "Answer the namespace in which the package is loaded." ^self loadedPackage namespace ] features [ "Answer a (modifiable) Set of features provided by the package." ^self loadedPackage features ] prerequisites [ "Answer a (modifiable) Set of prerequisites." ^self loadedPackage prerequisites ] builtFiles [ "Answer a (modifiable) OrderedCollection of files that are part of the package but are not distributed." ^self loadedPackage builtFiles ] files [ "Answer a (modifiable) OrderedCollection of files that are part of the package." ^self loadedPackage files ] fileIns [ "Answer a (modifiable) OrderedCollections of files that are to be filed-in to load the package. This is usually a subset of `files' and `builtFiles'." ^self loadedPackage fileIns ] libraries [ "Answer a (modifiable) Set of shared library names that are required to load the package." ^self loadedPackage libraries ] modules [ "Answer a (modifiable) Set of modules that are required to load the package." ^self loadedPackage modules ] startScript [ "Answer the start script for the package." ^self loadedPackage startScript ] stopScript [ "Answer the stop script for the package." ^self loadedPackage stopScript ] sunitScripts [ "Answer a (modifiable) OrderedCollection of SUnit scripts that compose the package's test suite." ^self loadedPackage sunitScripts ] callouts [ "Answer a (modifiable) Set of call-outs that are required to load the package. Their presence is checked after the libraries and modules are loaded so that you can do a kind of versioning." ^self loadedPackage callouts ] relativeDirectory [ ^nil ] directory [ ^(File name: self fileName) zip ] file [ ^file ] fileName [ ^self file name ] file: aFile [ file := aFile ] primFileIn [ self loadedPackage primFileIn ] loadedPackage [ | file package | loadedPackage isNil ifFalse: [^loadedPackage]. package := self file zip / 'package.xml' withReadStreamDo: [ :fileStream | Package parse: fileStream]. package isNil ifTrue: [^self error: 'invalid disabled-package tag inside a star file']. package relativeDirectory: self relativeDirectory. package baseDirectories: {self directory}. package name isNil ifTrue: [package name: self name] ifFalse: [package name = self name ifFalse: [self error: 'invalid package name in package.xml']]. loadedPackage := package. ^loadedPackage ] ] ] Namespace current: Kernel [ Object subclass: Version [ | major minor patch | Version class >> fromString: aString [ | result | result := aString searchRegex: '^(\d+)\.(\d+)(?:\.(\d+))?' . result ifNotMatched: [ self error: 'Bad version format ', aString, ' should be xx.yy(.zz)'. ^ nil ]. ^ self major: (result at: 1) asInteger minor: (result at: 2) asInteger patch: ((result at: 3) ifNil: [ 0 ]) asInteger ] Version class >> major: major minor: minor patch: patch [ ^ self new major: major minor: minor patch: patch ] major: major minor: minor patch: patch [ self major: major; minor: minor; patch: patch ] major [ ^ major ] major: anInteger [ major := anInteger ] minor [ ^ minor ] minor: anInteger [ minor := anInteger ] patch [ ^ patch ] patch: anInteger [ patch := anInteger ] ] ] Kernel.PackageInfo subclass: Package [ | features prerequisites builtFiles files fileIns relativeDirectory baseDirectories libraries modules callouts url namespace sunitScripts startScript stopScript test version path | Package class [ | Tags | ] Package class >> tags [ ^ Tags ifNil: [ Tags := Dictionary from: { 'file' -> #addFile:. 'filein' -> #addFileIn:. 'prereq' -> #addPrerequisite:. 'provides' -> #addFeature:. 'module' -> #addModule:. 'directory' -> #relativeDirectory:. 'name' -> #name:. 'url' -> #url:. 'version' -> #parseVersion:. 'namespace' -> #namespace:. 'library' -> #addLibrary:. 'built-file' -> #addBuiltFile:. 'sunit' -> #addSunitScript:. 'start' -> #startScript:. 'stop' -> #stopScript:. 'callout' -> #addCallout: } ] ] Package class >> parse: file [ "Answer a package from the XML description in file." | ch tag | [(file upTo: $<) trimSeparators isEmpty ifFalse: [self error: 'unexpected cdata']. file atEnd ifTrue: [self error: 'expected start tag']. ch := file peek. ch == $! ifTrue: [file skipTo: $>]. ch == $/ ifTrue: [self error: 'unexpected end tag ']. ch isAlphaNumeric ifTrue: [tag := file upTo: $>. tag = 'package' ifTrue: [^Package new parse: file tag: tag]. tag = 'disabled-package' ifTrue: [^DisabledPackage new parse: file tag: tag]]] repeat ] test [ "Answer the test sub-package." ^test ] test: aPackage [ "Set the test sub-package to be aPackage." aPackage test isNil ifFalse: [self error: 'test packages must not be nested']. aPackage name isNil ifFalse: [self error: 'test package must not have names']. (aPackage prerequisites) add: 'SUnit'; add: self name. aPackage owner: self. test := aPackage ] startScript [ "Answer the start script for the package." ^startScript ] startScript: aString [ "Set the start script for the package to aString." startScript := aString ] stopScript [ "Answer the start script for the package." ^stopScript ] stopScript: aString [ "Set the stop script for the package to aString." stopScript := aString ] url [ "Answer the URL at which the package repository can be found." ^url ] url: aString [ "Set to aString the URL at which the package repository can be found." url := aString ] namespace [ "Answer the namespace in which the package is loaded." ^namespace ] namespace: aString [ "Set to aString the namespace in which the package is loaded." namespace := aString ] addFeature: aString [ self path isEmpty ifFalse: [self error: 'unexpected inside tag']. self features add: aString ] features [ "Answer a (modifiable) Set of features provided by the package." features isNil ifTrue: [features := Set new]. ^features ] addPrerequisite: aString [ self path isEmpty ifFalse: [self error: 'unexpected inside tag']. self prerequisites add: aString ] prerequisites [ "Answer a (modifiable) Set of prerequisites." prerequisites isNil ifTrue: [prerequisites := Set new]. ^prerequisites ] addBuiltFile: aString [ self builtFiles add: self path, aString ] builtFiles [ "Answer a (modifiable) OrderedCollection of files that are part of the package but are not distributed." builtFiles isNil ifTrue: [builtFiles := OrderedCollection new]. ^builtFiles ] addFile: aString [ files isNil ifTrue: [files := OrderedCollection new]. files add: self path, aString ] files [ "Answer a (modifiable) OrderedCollection of files that are part of the package." | f | f := self fileIns copy. f removeAll: self builtFiles ifAbsent: []. files isNil ifFalse: [ f removeAll: files ifAbsent: []. f addAll: files ]. ^f ] addFileIn: aString [ self fileIns add: self path, aString ] fileIns [ "Answer a (modifiable) OrderedCollections of files that are to be filed-in to load the package. This is usually a subset of `files' and `builtFiles'." fileIns isNil ifTrue: [fileIns := OrderedCollection new]. ^fileIns ] addLibrary: aString [ self path isEmpty ifFalse: [self error: 'unexpected inside tag']. self libraries add: aString ] libraries [ "Answer a (modifiable) Set of shared library names that are required to load the package." libraries isNil ifTrue: [libraries := Set new]. ^libraries ] addModule: aString [ self path isEmpty ifFalse: [self error: 'unexpected inside tag']. self modules add: aString ] modules [ "Answer a (modifiable) Set of modules that are required to load the package." modules isNil ifTrue: [modules := Set new]. ^modules ] addSunitScript: aString [ self path isEmpty ifFalse: [self error: 'unexpected inside tag']. self sunitScripts add: aString ] sunitScripts [ "Answer a (modifiable) OrderedCollection of SUnit scripts that compose the package's test suite." sunitScripts isNil ifTrue: [sunitScripts := OrderedCollection new]. ^sunitScripts ] addCallout: aString [ self path isEmpty ifFalse: [self error: 'unexpected inside tag']. self callouts add: aString ] callouts [ "Answer a (modifiable) Set of call-outs that are required to load the package. Their presence is checked after the libraries and modules are loaded so that you can do a kind of versioning." callouts isNil ifTrue: [callouts := Set new]. ^callouts ] baseDirectories [ ^baseDirectories ] baseDirectories: aCollection [ "Check if it's possible to resolve the names in the package according to the base directories in baseDirectories, which depend on where the packages.xml is found: the three possible places are 1) the system kernel directory's parent directory, 2) the local kernel directory's parent directory, 3) the local image directory (in order of decreasing priority). For a packages.xml found in the system kernel directory's parent directory, all three directories are searched. For a packages.xml found in the local kernel directory's parent directory, only directories 2 and 3 are searched. For a packages.xml directory in the local image directory, instead, only directory 3 is searched." baseDirectories := aCollection. self fullPathsOf: self files. "self fullPathsOf: self fileIns." "self fullPathsOf: self builtFiles." self directory. self test notNil ifTrue: [self test baseDirectories: aCollection] ] fullPathOf: fileName [ "Try appending 'self directory' and fileName to each of the directory in baseDirectories, and return the path to the first tried filename that exists. Raise a PackageNotAvailable exception if no directory is found that contains the file." baseDirectories do: [:baseDir || dir file | dir := baseDir. self relativeDirectory isNil ifFalse: [dir := dir / self relativeDirectory]. file := dir / fileName. file exists ifTrue: [^file]]. SystemExceptions.PackageNotAvailable signal: self name reason: (fileName printString , ' does not exist in ' , baseDirectories printString) ] directory [ "Answer the base directory from which to load the package." self relativeDirectory isNil ifTrue: [^nil]. self baseDirectories do: [:baseDir || dir | dir := baseDir / relativeDirectory. dir exists ifTrue: [^dir]]. SystemExceptions.PackageNotAvailable signal: self name ] relativeDirectory [ "Answer the directory, relative to the packages file, from which to load the package." ^relativeDirectory ] relativeDirectory: dir [ "Set the directory, relative to the packages file, from which to load the package, to dir." relativeDirectory := dir ] version [ ^ version ] version: aVersion [ version := aVersion ] parseVersion: aString [ self version: (Version fromString: aString) ] primFileIn [ "Private - File in the given package without paying attention at dependencies and C callout availability" | dir namespace | self loaded ifTrue: [^self]. dir := Directory working. namespace := Namespace current. [| loadedFiles | Namespace current: self createNamespace. self directory isNil ifFalse: [Directory working: self directory]. self libraries do: [:each | DLD addLibrary: each]. self modules do: [:each | DLD addModule: each]. PackageLoader ignoreCallouts ifFalse: [self callouts do: [:func | (CFunctionDescriptor isFunction: func) ifFalse: [^self error: 'C callout not available: ' , func]]]. loadedFiles := self fullPathsOf: self fileIns. loadedFiles do: [:each | each fileIn]. self name isNil ifFalse: [Smalltalk addFeature: self name]. self features do: [:each | Smalltalk addFeature: each]] ensure: [Directory working: dir. Namespace current: namespace] ] path [ ^ path ifNil: [ path := '' ] ] path: aString [ path := aString ] isInPath [ ^ self path ~= '' ] checkTagIfInPath: aString [ self isInPath ifFalse: [ ^ self ]. (aString = 'file' or: [ aString = 'filein' or: [ aString = 'built-file' ] ]) ifFalse: [ self error: 'invalid tag in a dir tag ', aString ] ] dir: file tag: aDictionary [ | oldPath newPath | newPath := aDictionary at: 'name' ifAbsent: [ self error: 'name attribute is not present in a dir tag' ]. newPath isEmpty ifTrue: [ self error: 'name attribute is empty' ]. oldPath := self path. newPath := oldPath, newPath. (newPath notEmpty and: [newPath last isPathSeparator not]) ifTrue: [ newPath := newPath, Directory pathSeparatorString]. self path: newPath. self parse: file tag: 'dir'. self path: oldPath. ] parseAttributes: aString [ | attribute args key value terminator ch | attribute := ReadStream on: aString. args := LookupTable new. [ attribute atEnd ifTrue: [^args]. attribute peek isSeparator ifFalse: [ self error: 'expected separator']. [ attribute next. attribute atEnd ifTrue: [^args]. attribute peek isSeparator ] whileTrue. attribute peek isAlphaNumeric ifFalse: [ self error: 'expected attribute']. key := String streamContents: [ :s | [ attribute atEnd ifTrue: [ self error: 'expected attribute']. ch := attribute next. ch = $= ] whileFalse: [ ch isAlphaNumeric ifFalse: [ self error: 'invalid attribute name']. s nextPut: ch ] ]. terminator := attribute next. (terminator = $' or: [terminator = $"]) ifFalse: [ self error: 'expected single or double quote']. value := String streamContents: [ :s | [ attribute atEnd ifTrue: [ self error: 'expected %1' % { terminator }]. ch := attribute next. ch = terminator ] whileFalse: [ s nextPut: ch ] ]. args at: key put: value. ] repeat ] parse: file tag: openingTag [ | stack cdata ch tag testPackage words | stack := OrderedCollection new. stack addLast: openingTag. [ [cdata := cdata isNil ifTrue: [file upTo: $<] ifFalse: [cdata , (file upTo: $<)]. file atEnd] whileFalse: [ch := file peek. ch == $! ifTrue: [file skipTo: $>]. ch == $/ ifTrue: [tag := stack removeLast. file next. (file upTo: $>) = tag ifFalse: [^self error: 'error in packages file: unmatched end tag ' , tag ]. tag = openingTag ifTrue: [ ^ self ]. self checkTagIfInPath: tag. self perform: (self class tags at: tag ifAbsent: [ self error: 'invalid tag ', tag ]) with: cdata. cdata := nil ]. ch isAlphaNumeric ifTrue: [tag := file upTo: $>. words := tag substrings. words first = 'dir' ifTrue: [ self dir: file tag: (self parseAttributes: (tag copyFrom: words first size + 1)) ] ifFalse: [ words first = 'test' ifTrue: [self test: (TestPackage new parse: file tag: tag)] ifFalse: [stack addLast: tag] ]. cdata trimSeparators isEmpty ifFalse: [^self error: 'unexpected character data']. cdata := nil]]] ensure: [stack isEmpty ifFalse: [self error: 'error in packages file: unmatched start tags' , stack asArray printString]] ] ] Namespace current: Kernel [ Package subclass: DisabledPackage [ printOn: aStream indent: indent [ self printOn: aStream tag: 'disabled-package' indent: indent ] isDisabled [ ^true ] ] ] Namespace current: Kernel [ Smalltalk.Package subclass: TestPackage [ | owner | owner: aPackage [ "Set the Package I test." owner := aPackage ] url [ "Answer the URL at which the package repository can be found." ^super url ifNil: [owner url] ] namespace [ "Answer the namespace in which the package is loaded." ^super namespace ifNil: [owner namespace] ] baseDirectories [ "Answer the directories in which package files are sought." ^super baseDirectories ifNil: [owner baseDirectories collect: [:each | each / owner relativeDirectory]] ] ] ] Object subclass: PackageLoader [ PackageLoader class [ | root loadDate ignoreCallouts | ] PackageLoader class >> packageAt: package ifAbsent: aBlock [ "Answer a Package object for the given package" self refresh. ^root at: package asString ifAbsent: aBlock ] PackageLoader class >> packageAt: package [ "Answer a Package object for the given package" self refresh. ^root at: package asString ] PackageLoader class >> directoryFor: package [ "Answer a Directory object to the given package's files" ^(self packageAt: package) directory ] PackageLoader class >> builtFilesFor: package [ "Answer a Set of Strings containing the filenames of the given package's machine-generated files (relative to the directory answered by #directoryFor:)" ^(self packageAt: package) builtFiles ] PackageLoader class >> filesFor: package [ "Answer a Set of Strings containing the filenames of the given package's files (relative to the directory answered by #directoryFor:)" ^(self packageAt: package) files ] PackageLoader class >> fileInsFor: package [ "Answer a Set of Strings containing the filenames of the given package's file-ins (relative to the directory answered by #directoryFor:)" ^(self packageAt: package) fileIns ] PackageLoader class >> sunitScriptFor: package [ "Answer a Strings containing a SUnit script that describes the package's test suite." ^(self packageAt: package) sunitScript ] PackageLoader class >> calloutsFor: package [ "Answer a Set of Strings containing the filenames of the given package's required callouts (relative to the directory answered by #directoryFor:)" ^(self packageAt: package) callouts ] PackageLoader class >> librariesFor: package [ "Answer a Set of Strings containing the filenames of the given package's libraries (relative to the directory answered by #directoryFor:)" ^(self packageAt: package) libraries ] PackageLoader class >> modulesFor: package [ "Answer a Set of Strings containing the filenames of the given package's modules (relative to the directory answered by #directoryFor:)" ^(self packageAt: package) modules ] PackageLoader class >> featuresFor: package [ "Answer a Set of Strings containing the features provided by the given package." ^(self packageAt: package) features ] PackageLoader class >> prerequisitesFor: package [ "Answer a Set of Strings containing the prerequisites for the given package" ^(self packageAt: package) prerequisites ] PackageLoader class >> ignoreCallouts [ "Answer whether unavailable C callouts must generate errors or not." ignoreCallouts isNil ifTrue: [ignoreCallouts := false]. ^ignoreCallouts ] PackageLoader class >> ignoreCallouts: aBoolean [ "Set whether unavailable C callouts must generate errors or not." ignoreCallouts := aBoolean ] PackageLoader class >> flush [ "Set to reload the `packages.xml' file the next time it is needed." root := nil. loadDate := ##(Date newDay: 1 month: #jan year: 1900) ] PackageLoader class >> refresh [ "Reload the `packages.xml' file in the image and kernel directories. The three possible places are 1) the kernel directory's parent directory, 2) the `.st' subdirectory of the user's home directory, 3) the local image directory (in order of decreasing priority). For a packages.xml found in the kernel directory's parent directory, all three directories are searched. For a packages.xml found in the `.st' subdirectory, only directories 2 and 3 are searched. For a packages.xml directory in the local image directory, finally, only directory 3 is searched." | state | root isNil ifTrue: [self flush. root := Kernel.PackageDirectories new. root add: (Kernel.PackageDirectory on: self packageFile baseDirectories: [ {Directory userBase. Directory kernel / '..'}]). root add: (Kernel.PackageDirectory on: self sitePackageFile baseDirectories: [ {Directory userBase. Directory kernel / '../site-packages'}]). root add: (Kernel.PackageDirectory on: self userPackageFile baseDirectories: [{Directory userBase}]). root add: (Kernel.PackageDirectory on: self localPackageFile baseDirectories: [#()])]. root refresh: loadDate. loadDate := Date dateAndTimeNow ] PackageLoader class >> fileInPackage: package [ "File in the given package into GNU Smalltalk." self fileInPackages: {package} ] PackageLoader class >> fileInPackages: packagesList [ "File in all the packages in packagesList into GNU Smalltalk." | toBeLoaded | packagesList isEmpty ifTrue: [^self]. self refresh. toBeLoaded := root extractDependenciesFor: packagesList ifMissing: [:name | SystemExceptions.PackageNotAvailable signal: name]. toBeLoaded do: [:each | OutputVerbosity > 0 ifTrue: [Transcript nextPutAll: 'Loading package ' , each; nl]. (self packageAt: each) primFileIn] ] PackageLoader class >> canLoad: package [ "Answer whether all the needed pre-requisites for package are available." self extractDependenciesFor: {package} ifMissing: [:name | ^false]. ^true ] PackageLoader class >> isLoadable: feature [ "Private - Answer whether the packages file includes an entry for `feature'" self refresh. ^root includesKey: feature asString ] PackageLoader class >> packageFile [ ^Directory kernel / '../packages.xml' ] PackageLoader class >> sitePackageFile [ ^Directory kernel / '../site-packages/packages.xml' ] PackageLoader class >> userPackageFile [ ^Directory userBase / 'packages.xml' ] PackageLoader class >> localPackageFile [ ^Directory image / 'packages.xml' ] PackageLoader class >> rebuildPackageFile [ "Recreate the XML file from the information that the PackageLoader holds. This is a dangerous method, also because the PackageLoader does not know about disabled packages." | file | self refresh. Directory image / 'packages.xml' withWriteStreamDo: [ :file | file nextPutAll: ''. file nl; nl. root printOn: file] ] ] smalltalk-3.2.5/kernel/IdentitySet.st0000644000175000017500000000455212130343734014531 00000000000000"====================================================================== | | IdentitySet Method Definitions | | ======================================================================" "====================================================================== | | Copyright 1999, 2000, 2001 Free Software Foundation, Inc. | Written by Paolo Bonzini. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" Set subclass: IdentitySet [ identityIncludes: anObject [ "Answer whether we include the anObject object; for IdentitySets this is identical to #includes:" ^self includes: anObject ] hashFor: anObject [ "Return an hash value for the item, anObject" ^anObject identityHash ] findIndex: anObject [ "Tries to see if anObject exists as an indexed variable. As soon as nil or anObject is found, the index of that slot is answered" | index size element | self beConsistent. "Sorry for the lack of readability, but I want speed... :-)" index := (anObject identityHash scramble bitAnd: (size := self primSize) - 1) + 1. [((element := self primAt: index) isNil or: [element == anObject]) ifTrue: [^index]. index == size ifTrue: [index := 1] ifFalse: [index := index + 1]] repeat ] ] smalltalk-3.2.5/kernel/RWStream.st0000644000175000017500000000562512123404352013766 00000000000000"====================================================================== | | ReadWriteStream Method Definitions | | ======================================================================" "====================================================================== | | Copyright 1988,92,94,95,99,2000,2001,2006,2007 | Free Software Foundation, Inc. | Written by Steve Byrne. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" WriteStream subclass: ReadWriteStream [ ReadWriteStream class >> on: aCollection [ "Answer a new stream working on aCollection from its start. The stream starts at the front of aCollection." ^(super on: aCollection) beReadWrite; limit: aCollection size ] ReadWriteStream class >> on: aCollection from: firstIndex to: lastIndex [ "Answer an instance of the receiver streaming from the firstIndex-th item of aCollection to the lastIndex-th" firstIndex = 1 ifFalse: [^super on: aCollection from: firstIndex to: lastIndex]. lastIndex > aCollection size ifTrue: [^SystemExceptions.IndexOutOfRange signalOn: self withIndex: lastIndex]. ^(super on: aCollection) beReadWrite; limit: lastIndex ] ReadWriteStream class >> with: aCollection [ "Answer a new instance of the receiver which streams from the end of aCollection." ^(super with: aCollection) beReadWrite ] contents [ "Unlike WriteStreams, ReadWriteStreams return the whole contents of the underlying collection." ^collection copyFrom: 1 to: endPtr ] limit: anInteger [ "Private - Makes sure that the contents message to this object returns anInteger objects, not just what has been written so far." endPtr := collection size ] ] smalltalk-3.2.5/kernel/PosStream.st0000644000175000017500000002216312123404352014173 00000000000000"====================================================================== | | PositionableStream Method Definitions | | ======================================================================" "====================================================================== | | Copyright 1988,92,94,95,99,2000,2001,2002,2006,2007,2008,2009 | Free Software Foundation, Inc. | Written by Steve Byrne. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" Stream subclass: PositionableStream [ | collection ptr endPtr access | PositionableStream class >> on: aCollection [ "Answer an instance of the receiver streaming on the whole contents of aCollection" self subclassResponsibility ] PositionableStream class >> on: aCollection from: firstIndex to: lastIndex [ "Answer an instance of the receiver streaming from the firstIndex-th item of aCollection to the lastIndex-th" ^self on: (aCollection copyFrom: firstIndex to: lastIndex) ] close [ "Disassociate a stream from its backing store." self flush. collection := nil. endPtr := nil. ptr := nil. access := nil ] next [ "Answer the next item of the receiver. Returns nil when at end of stream." | element | (access bitAnd: 1) = 0 ifTrue: [^self shouldNotImplement]. ptr > endPtr ifTrue: [^self pastEnd]. element := collection at: ptr. ptr := ptr + 1. ^element ] nextPutAllOn: aStream [ "Write all the objects in the receiver to aStream." | n | (access bitAnd: 1) = 0 ifTrue: [^self shouldNotImplement]. n := endPtr - ptr + 1. aStream next: n putAll: collection startingAt: ptr. ptr := ptr + n. ] nextAvailable: anInteger putAllOn: aStream [ "Copy up to anInteger objects from the receiver into aStream, stopping if no more data is available." | n | (access bitAnd: 1) = 0 ifTrue: [^self shouldNotImplement]. n := anInteger min: endPtr - ptr + 1. aStream next: n putAll: collection startingAt: ptr. ptr := ptr + n. ^n ] nextAvailable: anInteger into: aCollection startingAt: pos [ "Place up to anInteger objects from the receiver into aCollection, starting from position pos in the collection and stopping if no more data is available." | n | (access bitAnd: 1) = 0 ifTrue: [^self shouldNotImplement]. n := anInteger min: endPtr - ptr + 1. aCollection replaceFrom: pos to: pos + n - 1 with: collection startingAt: ptr. ptr := ptr + n. ^n ] peek [ "Returns the next element of the stream without moving the pointer. Returns nil when at end of stream." (access bitAnd: 1) = 0 ifTrue: [^self shouldNotImplement]. ptr > endPtr ifTrue: [^nil]. ^collection at: ptr ] peekFor: anObject [ "Returns true and gobbles the next element from the stream of it is equal to anObject, returns false and doesn't gobble the next element if the next element is not equal to anObject." self atEnd ifTrue: [^false]. ^self next = anObject ifTrue: [true] ifFalse: [self skip: -1. false] ] copyFrom: start to: end [ "Answer the data on which the receiver is streaming, from the start-th item to the end-th. Note that this method is 0-based, unlike the one in Collection, because a Stream's #position method returns 0-based values." ^collection copyFrom: start + 1 to: end + 1 ] contents [ "Returns a collection of the same type that the stream accesses, up to and including the final element." ^collection copyFrom: 1 to: endPtr ] readStream [ "Answer a ReadStream on the same contents as the receiver" ^ReadStream on: collection from: 1 to: endPtr ] reverseContents [ "Returns a collection of the same type that the stream accesses, up to and including the final element, but in reverse order." | newCollection | newCollection := collection copyEmpty: endPtr. 1 to: endPtr do: [:i | newCollection at: i put: (collection at: endPtr - i + 1)]. ^newCollection ] atEnd [ "Answer whether the objects in the stream have reached an end" ^ptr > endPtr ] basicAtEnd [ "Answer whether the objects in the stream have reached an end. This method must NOT be overridden." ^ptr > endPtr ] isEmpty [ "Answer whether the stream has no objects" ^endPtr = 0 ] truncate [ "Truncate the receiver to the current position - only valid for writing streams" (access bitAnd: 2) = 0 ifTrue: [self shouldNotImplement] ifFalse: [endPtr := ptr - 1] ] position [ "Answer the current value of the stream pointer" ^ptr - 1 ] position: anInteger [ "Move the stream pointer to the anInteger-th object" (anInteger between: 0 and: self size) ifTrue: [ptr := anInteger + 1] ifFalse: [SystemExceptions.IndexOutOfRange signalOn: self withIndex: anInteger] ] basicPosition: anInteger [ "Move the stream pointer to the anInteger-th object" (anInteger between: 0 and: self size) ifTrue: [ptr := anInteger + 1] ifFalse: [SystemExceptions.IndexOutOfRange signalOn: self withIndex: anInteger] ] reset [ "Move the stream back to its first element. For write-only streams, the stream is truncated there." self position: 0 ] setToEnd [ "Move the current position to the end of the stream." self position: self size ] size [ "Answer the size of data on which we are streaming." ^endPtr ] isPositionable [ "Answer true if the stream supports moving backwards with #skip:." ^true ] skip: anInteger [ "Move the current position by anInteger places, either forwards or backwards." self position: ((self position + anInteger max: 0) min: endPtr) ] beReadOnly [ access := 1 ] beWriteOnly [ access := 2 ] beReadWrite [ access := 3 ] collection [ ^collection ] status: aString [ "When working with a stream on strings, this method can be useful! Format of the output: 'ABCDEFG' aString ^" Transcript print: (collection copyFrom: 1 to: endPtr); nextPutAll: ' '; nextPutAll: aString; nl; next: self position put: Character space; nextPut: $^; nl ] isExternalStream [ "We stream on a collection residing in the image, so answer false" ^false ] species [ "Return the type of the collections returned by #upTo: etc., which are the same kind as those returned by the collection with methods such as #select:." ^collection species ] upToEnd [ "Returns a collection of the same type that the stream accesses, containing the entire rest of the stream's contents." ^self next: endPtr - ptr + 1. ] upTo: anObject [ "Returns a collection of the same type that the stream accesses, up to but not including the object anObject. Returns the entire rest of the stream's contents if anObject is not present." | result r ws | r := collection indexOf: anObject startingAt: ptr ifAbsent: [0]. ^r = 0 ifTrue: [self upToEnd] ifFalse: [result := self next: r - ptr. self next. ^result]. ] ] smalltalk-3.2.5/kernel/CompiledBlk.st0000644000175000017500000001603412123404352014443 00000000000000"====================================================================== | | CompiledBlock Method Definitions | | ======================================================================" "====================================================================== | | Copyright 2000, 2001, 2003, 2008 Free Software Foundation, Inc. | Written by Paolo Bonzini. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" CompiledCode subclass: CompiledBlock [ | method | CompiledBlock class >> numArgs: args numTemps: temps bytecodes: bytecodes depth: depth literals: literalArray [ "Answer an (almost) full fledged CompiledBlock. To make it complete, you must either set the new object's `method' variable, or put it into a BlockClosure and put the BlockClosure into a CompiledMethod's literals. The clean-ness of the block is automatically computed." self primitiveFailed ] CompiledBlock class >> new: numBytecodes header: anInteger method: outerMethod [ "Answer a new instance of the receiver with room for the given number of bytecodes and the given header." ^(self new: numBytecodes header: anInteger literals: outerMethod literals) method: outerMethod ] methodCategory [ "Answer the method category" ^method methodCategory ] sourceCodeLinesDelta [ "Answer the delta from the numbers in LINE_NUMBER bytecodes to source code line numbers." ^method sourceCodeLinesDelta ] sourceCodeMap [ "Answer an array which maps bytecode indices to source code line numbers. 0 values represent invalid instruction pointer indices." | map line | map := ByteArray new: self size. line := 1. self allByteCodeIndicesDo: [:each :byte :operand | (self class bytecodeInfoTable at: byte * 4 + 4) >= 128 ifTrue: [line := operand. operand > 255 ifTrue: [map := map asArray]]. map at: each put: line]. ^map ] methodCategory: aCategory [ "Set the method category to the given string" method methodCategory: aCategory ] methodSourceCode [ "Answer the method source code (a FileSegment or String or nil)" ^method methodSourceCode ] methodSourceString [ "Answer the method source code as a string" ^method methodSourceString ] methodSourceFile [ "Answer the file where the method source code is stored" ^method methodSourceFile ] methodSourcePos [ "Answer the location where the method source code is stored in the methodSourceFile" ^method methodSourcePos ] = aMethod [ "Answer whether the receiver and aMethod are equal" self == aMethod ifTrue: [^true]. ^super = aMethod and: [method = aMethod method] ] method [ "Answer the CompiledMethod in which the receiver lies" ^method ] methodClass [ "Answer the class in which the receiver is installed." ^method methodClass ] methodClass: methodClass [ "Set the receiver's class instance variable" method methodClass: methodClass ] selector: aSymbol [ "Set the selector through which the method is called" method selector: aSymbol ] selector [ "Answer the selector through which the method is called" ^method selector ] flags [ "Answer the `cleanness' of the block. 0 = clean; 1 = access to receiver variables and/or self; 2-30 = access to variables that are 1-29 contexts away; 31 = return from method or push thisContext" ^header bitAnd: 31 ] numArgs [ "Answer the number of arguments passed to the receiver" ^(header bitShift: -25) bitAnd: 31 ] numTemps [ "Answer the number of temporary variables used by the receiver" ^(header bitShift: -20) bitAnd: 31 ] stackDepth [ "Answer the number of stack slots needed for the receiver" ^((header bitShift: -14) bitAnd: 63) * 4 ] numLiterals [ "Answer the number of literals for the receiver" ^literals size ] printOn: aStream [ "Print the receiver's class and selector on aStream" aStream nextPutAll: '[] in '; print: method ] printHeaderOn: aStream [ "Private - Disassemble the method header to aStream" aStream nextPutAll: ' clean-ness flags: '; print: self flags; nl; nextPutAll: ' number of arguments: '; print: self numArgs; nl; nextPutAll: ' number of temporaries: '; print: self numTemps; nl; nextPutAll: ' number of literals: '; print: self numLiterals; nl; nextPutAll: ' needed stack slots: '; print: self stackDepth; nl ] header: hdr literals: lits [ "Implementation note: here is the use of the header bits: - bits 0-4 = clean-ness flags - bits 5-13 = unused - bits 14-19 = stack depth - bits 20-24 = number of temps - byte 25-29 = number of args" header := hdr. literals := lits. Behavior flushCache ] binaryRepresentationObject [ "This method is implemented to allow for a PluggableProxy to be used with CompiledBlocks. Answer a DirectedMessage which sends #blockAt: to the CompiledMethod containing the receiver." | literalNumber | self literals keysAndValuesDo: [:i :lit | lit == self ifTrue: [^DirectedMessage selector: #blockAt: arguments: (Array with: i) receiver: self method]. (lit class == BlockClosure and: [lit block == self]) ifTrue: [^DirectedMessage selector: #blockAt: arguments: (Array with: i) receiver: self method]]. self error: 'object cannot be dumped' ] ] smalltalk-3.2.5/kernel/FloatD.st0000644000175000017500000001705512123404352013433 00000000000000"====================================================================== | | FloatD Method Definitions | | ======================================================================" "====================================================================== | | Copyright 2002, 2009 Free Software Foundation, Inc. | Written by Paolo Bonzini. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" Float subclass: FloatD [ FloatD class >> coerce: aNumber [ "Answer aNumber converted to a FloatD" ^aNumber asFloatD ] FloatD class >> signByte [ "Answer the byte of the receiver that contains the sign bit" ^##(| n k | n := -2.0. 1 to: n size do: [:i | (n at: i) >= 128 ifTrue: [k := i]]. k) ] FloatD class >> fromBytes: aByteArray [ "Answer a float with the bytes in aByteArray, which are in big-endian format." | b permutation | permutation := ##(| signByte perm | signByte := FloatD signByte. signByte = 1 ifTrue: [ perm := #[1 2 3 4 5 6 7 8] ]. signByte = 4 ifTrue: [ perm := #[4 3 2 1 8 7 6 5] ]. signByte = 5 ifTrue: [ perm := #[5 6 7 8 1 2 3 4] ]. signByte = 8 ifTrue: [ perm := #[8 7 6 5 4 3 2 1] ]. perm). b := FloatD new: 8. 1 to: 8 do: [ :i | b at: i put: (aByteArray at: (permutation at: i)) ]. b makeReadOnly: true. ^b ] FloatD class >> precision [ "Answer the number of bits in the mantissa. 1 + (2^-precision) = 1" ^CDoubleBinaryDigits ] FloatD class >> fminNormalized [ "Return the smallest normalized FloatD that is > 0" ^CDoubleMin ] FloatD class >> fmax [ "Return the largest normalized FloatD that is not infinite." ^CDoubleMax ] FloatD class >> emax [ "Return the maximum allowable exponent for a FloatD that is finite." ^CDoubleMaxExp ] FloatD class >> emin [ "Return the maximum allowable exponent for a FloatD that is finite." ^CDoubleMinExp ] FloatD class >> decimalDigits [ "Return the number of decimal digits of precision for a FloatD. Technically, if P is the precision for the representation, then the decimal precision Q is the maximum number of decimal digits such that any floating point number with Q base 10 digits can be rounded to a floating point number with P base 2 digits and back again, without change to the Q decimal digits." ^CDoubleDigits ] FloatD class >> infinity [ "Return a FloatD that represents positive infinity." ^CDoublePInf ] FloatD class >> negativeInfinity [ "Return a FloatD that represents negative infinity." ^CDoubleNInf ] FloatD class >> nan [ "Return a FloatD that represents a mathematically indeterminate value (e.g. Inf - Inf, Inf / Inf)." ^CDoubleNaN ] zero [ "Coerce 0 to the receiver's class" ^0.0 ] half [ "Coerce 0.5 to the receiver's class" ^0.5 ] unity [ "Coerce 1 to the receiver's class" ^1.0 ] coerce: aNumber [ "Coerce aNumber to the receiver's class" ^aNumber asFloatD ] generality [ "Answer the receiver's generality" ^410 ] asFloatD [ "Just defined for completeness. Return the receiver." ^self ] ten [ "Private - Return 10, converted to the receiver's class." ^10.0 ] exponentLetter [ "Private - Return the letter to be printed just before the exponent" ^$d ] + arg [ "Sum the receiver and arg and answer another Number" ^self retrySumCoercing: arg ] - arg [ "Subtract arg from the receiver and answer another Number" ^self retryDifferenceCoercing: arg ] < arg [ "Answer whether the receiver is less than arg" ^self retryRelationalOp: #< coercing: arg ] > arg [ "Answer whether the receiver is greater than arg" ^self retryRelationalOp: #> coercing: arg ] <= arg [ "Answer whether the receiver is less than or equal to arg" ^self retryRelationalOp: #<= coercing: arg ] >= arg [ "Answer whether the receiver is greater than or equal to arg" ^self retryRelationalOp: #>= coercing: arg ] = arg [ "Answer whether the receiver is equal to arg" ^self retryEqualityCoercing: arg ] ~= arg [ "Answer whether the receiver is not equal to arg" ^self retryInequalityCoercing: arg ] * arg [ "Multiply the receiver and arg and answer another Number" ^self retryMultiplicationCoercing: arg ] / arg [ "Divide the receiver by arg and answer another FloatD" ^self generality = arg generality ifTrue: [self zeroDivide] ifFalse: [self retryDivisionCoercing: arg] ] asFloatE [ "Answer the receiver converted to a FloatE" self primitiveFailed ] asFloatQ [ "Answer the receiver converted to a FloatQ" self primitiveFailed ] truncated [ "Truncate the receiver towards zero and answer the result" ^super truncated ] fractionPart [ "Answer the fractional part of the receiver" self checkCoercion. ^self primitiveFailed ] exponent [ "Answer the exponent of the receiver in mantissa*2^exponent representation ( |mantissa|<=1 )" ] timesTwoPower: arg [ "Answer the receiver multiplied by 2^arg" ] ] smalltalk-3.2.5/kernel/CObject.st0000644000175000017500000010316712123404352013573 00000000000000"====================================================================== | | C object basic data type definitions. | | ======================================================================" "====================================================================== | | Copyright 1988,92,94,95,99,2000,2001,2002,2003,2004,2008,2009 | Free Software Foundation, Inc. | Written by Steve Byrne. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" Object subclass: CObject [ | type storage | CObject class [ | defaultType | ] CObject class >> inheritShape [ "Answer whether subclasses will have by default the same shape as this class. The default is true for the CObject hierarchy." ^true ] CObject class >> alloc: nBytes type: cTypeObject [ "Allocate nBytes bytes and return a CObject of the given type" nBytes isInteger ifFalse: [^SystemExceptions.WrongClass signalOn: nBytes mustBe: SmallInteger]. ^SystemExceptions.WrongClass signalOn: cTypeObject mustBe: CType ] CObject class >> gcAlloc: nBytes type: cTypeObject [ "Allocate nBytes bytes and return a CObject of the given type" | class | class := cTypeObject isNil ifTrue: [ self ] ifFalse: [ cTypeObject cObjectType ]. ^(class address: 0) type: cTypeObject; storage: (ByteArray new: nBytes); yourself ] CObject class >> alloc: nBytes [ "Allocate nBytes bytes and return an instance of the receiver" ^self alloc: nBytes type: nil ] CObject class >> gcAlloc: nBytes [ "Allocate nBytes bytes and return an instance of the receiver" ^self gcAlloc: nBytes type: nil ] CObject class >> gcNew: nBytes [ "Allocate nBytes bytes and return an instance of the receiver" ^self gcAlloc: nBytes type: nil ] CObject class >> new: nBytes [ "Allocate nBytes bytes and return an instance of the receiver" ^self alloc: nBytes type: nil ] CObject class >> address: anInteger [ "Answer a new object pointing to the passed address, anInteger" ^(self basicNew: 1) address: anInteger ] CObject class >> new [ "Answer a new object pointing to NULL." ^self address: 0 ] CObject class >> type [ "Nothing special in the default case - answer a CType for the receiver" defaultType isNil ifTrue: [defaultType := CType cObjectType: self]. ^defaultType ] CObject class >> cObjStoredType [ "Private - Provide a conversion from a CObject to a Smalltalk object to be stored by #at:put:" ^nil ] = anObject [ "Return true if the receiver and aCObject are equal." ^self class == anObject class and: [ self type = anObject type and: [ self storage == anObject storage and: [ self address = anObject address ]]] ] hash [ "Return a hash value for anObject." | addr | addr := self address bitAnd: SmallInteger largest. ^self type hash bitXor: (self storage identityHash * self storage size + addr) ] finalize [ "To make the VM call this, use #addToBeFinalized. It frees automatically any memory pointed to by the CObject. It is not automatically enabled because big trouble hits you if you use #free and the receiver doesn't point to the base of a malloc-ed area." self free ] addressAt: anIndex [ "Return a new CObject of the element type, corresponding to an object that is anIndex places past the receiver (remember that CObjects represent pointers and that C pointers behave like arrays). anIndex is zero-based, just like with all other C-style accessing." | dereferencedType | dereferencedType := self dereferencedType. ^self at: anIndex * dereferencedType sizeof type: dereferencedType ] at: anIndex [ "Dereference a pointer that is anIndex places past the receiver (remember that CObjects represent pointers and that C pointers behave like arrays). anIndex is zero-based, just like with all other C-style accessing." | dereferencedType offset valueType | dereferencedType := self dereferencedType. offset := anIndex * dereferencedType sizeof. valueType := dereferencedType valueType. ^valueType isInteger ifTrue: [self at: offset type: valueType] ifFalse: [(self at: offset type: dereferencedType) value] ] at: anIndex put: aValue [ "Store anIndex places past the receiver the passed Smalltalk object or CObject `aValue'; if it is a CObject is dereferenced: that is, this method is equivalent either to cobj[anIndex]=aValue or cobj[anIndex]=*aValue. anIndex is zero-based, just like with all other C-style accessing. In both cases, aValue should be of the element type or of the corresponding Smalltalk type (that is, a String is ok for an array of CStrings) to avoid typing problems which however will not be signaled because C is untyped." | dereferencedType offset valueType | dereferencedType := self dereferencedType. offset := anIndex * dereferencedType sizeof. valueType := dereferencedType valueType. valueType isInteger ifTrue: [self at: offset put: aValue type: valueType] ifFalse: [(self at: offset type: dereferencedType) value: aValue]. ^aValue ] isNull [ "Return true if the receiver points to NULL." ^self address = 0 and: [ self isAbsolute ] ] isCObject [ ^true ] incr [ "Adjust the pointer by sizeof(dereferencedType) bytes up (i.e. ++receiver)" self adjPtrBy: self dereferencedType sizeof ] decr [ "Adjust the pointer by sizeof(dereferencedType) bytes down (i.e. --receiver)" self adjPtrBy: self dereferencedType sizeof negated ] incrBy: anInteger [ "Adjust the pointer by anInteger elements up (i.e. receiver += anInteger)" self adjPtrBy: self dereferencedType sizeof * anInteger ] decrBy: anInteger [ "Adjust the pointer by anInteger elements down (i.e. receiver -= anInteger)" self adjPtrBy: self dereferencedType sizeof * anInteger negated ] + anInteger [ "Return another instance of the receiver's class which points at &receiver[anInteger] (or, if you prefer, what `receiver + anInteger' does in C)." | dereferencedType | dereferencedType := self dereferencedType. ^self at: anInteger * dereferencedType sizeof type: self type ] - intOrPtr [ "If intOrPtr is an integer, return another instance of the receiver's class pointing at &receiver[-anInteger] (or, if you prefer, what `receiver - anInteger' does in C). If it is the same class as the receiver, return the difference in chars, i.e. in bytes, between the two pointed addresses (or, if you prefer, what `receiver - anotherCharPtr' does in C)" | dereferencedType | intOrPtr isInteger ifTrue: [^self + intOrPtr negated]. dereferencedType := self dereferencedType. intOrPtr dereferencedType = dereferencedType ifFalse: [^SystemExceptions.InvalidArgument signalOn: intOrPtr reason: 'arithmetic between pointers to different types']. ^((self addressAt: 0) address - (intOrPtr addressAt: 0) address) // dereferencedType sizeof ] castTo: aType [ "Answer another CObject, pointing to the same address as the receiver, but belonging to the aType CType." ^self at: 0 type: aType ] narrow [ "This method is called on CObjects returned by a C call-out whose return type is specified as a CType; it mostly allows one to change the class of the returned CObject. By default it does nothing, and that's why it is not called when #cObject is used to specify the return type." ] type [ "Answer a CType for the receiver" type isNil ifTrue: [type := self class type]. ^type ] isAbsolute [ "Answer whether the object points into a garbage-collected Smalltalk storage, or it is an absolute address." ^storage isNil ] storage [ "Answer the storage that the receiver is pointing into, or nil if the address is absolute." ^storage ] storage: anObject [ "Change the receiver to point to the storage of anObject." storage := anObject. ] address [ "Answer the address the receiver is pointing to. The address can be absolute if the storage is nil, or relative to the Smalltalk object in #storage. In this case, an address of 0 corresponds to the first instance variable." ^self basicAt: self basicSize ] address: anInteger [ "Set the receiver to point to the passed address, anInteger" SystemExceptions.WrongClass signalOn: anInteger mustBe: Integer ] printOn: aStream [ "Print a representation of the receiver" aStream print: self class; nextPut: $(. self isAbsolute ifTrue: [ aStream nextPutAll: (self address printStringRadix: 16) ] ifFalse: [ self storage do: [ :each | aStream print: each; space ]. aStream nextPutAll: '@ '; print: self address ]. aStream nextPut: $) ] type: aCType [ "Set the receiver's type to aCType." type := aCType ] adjPtrBy: byteOffset [ self address: self address + byteOffset ] dereferencedType [ ^self type ] cObjStoredType [ "Private - Provide a conversion from a CObject to a Smalltalk object to be stored by #at:put:" ^nil ] cObjStoredValue [ "Private - Provide a conversion from a CObject to a Smalltalk object to be stored by #at:put:" ^self value ] at: byteOffset type: aType [ "Answer some data of the given type from byteOffset bytes after the pointer stored in the receiver" byteOffset isInteger ifFalse: [^SystemExceptions.WrongClass signalOn: byteOffset mustBe: SmallInteger]. (self isAbsolute not and: [ aType isInteger ]) ifTrue: [ ^SystemExceptions.InvalidArgument signalOn: self address + byteOffset reason: 'offset out of range' ]. ^SystemExceptions.WrongClass signalOn: aType ] at: byteOffset put: aValue type: aType [ "Store aValue as data of the given type from byteOffset bytes after the pointer stored in the receiver" | type | (self isAbsolute not and: [ aValue isCObject not ]) ifTrue: [ ^SystemExceptions.InvalidArgument signalOn: self address + byteOffset reason: 'offset out of range' ]. type := aValue cObjStoredType. "Attempt to store something meaningful from another CObject" type isNil ifTrue: [type := aType]. ^self at: byteOffset noCObjectsPut: aValue cObjStoredValue type: type ] free [ "Free the receiver's pointer and set it to null. Big trouble hits you if the receiver doesn't point to the base of a malloc-ed area." ^self primitiveFailed ] at: byteOffset noCObjectsPut: aValue type: aType [ "Private - Store aValue as data of the given type from byteOffset bytes after the pointer stored in the receiver. This version refuses CObjects for `aValue'." byteOffset isInteger ifFalse: [^SystemExceptions.WrongClass signalOn: byteOffset mustBe: SmallInteger]. (aType isInteger or: [aType isKindOf: CType]) ifFalse: [^SystemExceptions.WrongClass signalOn: byteOffset mustBe: SmallInteger]. ^SystemExceptions.WrongClass signalOn: aValue ] derefAt: byteOffset type: aType [ byteOffset isInteger ifFalse: [^SystemExceptions.WrongClass signalOn: byteOffset mustBe: SmallInteger]. ^SystemExceptions.WrongClass signalOn: aType ] ] CObject subclass: CScalar [ CScalar class >> value: anObject [ "Answer a newly allocated CObject containing the passed value, anObject. Remember to call #addToBeFinalized if you want the CObject to be automatically freed" | cObject | cObject := self type new. cObject value: anObject. ^cObject ] CScalar class >> gcValue: anObject [ "Answer a newly allocated CObject containing the passed value, anObject, in garbage-collected storage." | cObject | cObject := self type gcNew. cObject value: anObject. ^cObject ] CScalar class >> type [ "Answer a CType for the receiver---for example, CByteType if the receiver is CByte." ^self environment at: (self name , 'Type') asGlobalKey ] CScalar class >> cObjStoredType [ "Private - Provide a conversion from a CObject to a Smalltalk object to be stored by #at:put:" self subclassResponsibility ] cObjStoredType [ "Private - Provide a conversion from a CObject to a Smalltalk object to be stored by #at:put:" self subclassResponsibility ] value [ "Answer the value the receiver is pointing to. The exact returned value depends on the receiver's class" ^self at: 0 type: self cObjStoredType ] value: aValue [ "Set the receiver to point to the value, aValue. The exact meaning of aValue depends on the receiver's class" self at: 0 put: aValue type: self cObjStoredType ] ] CScalar subclass: CSmalltalk [ CSmalltalk class >> sizeof [ "Answer the receiver's instances size" ^CPtrSize ] CSmalltalk class >> alignof [ "Answer the receiver's instances required aligment" ^CPtrSize ] CSmalltalk class >> cObjStoredType [ "Private - Answer an index referring to the receiver's instances scalar type" ^9 ] sizeof [ "Answer the receiver's size" ^CPtrSize ] alignof [ "Answer the receiver's required aligment" ^CPtrSize ] cObjStoredType [ "Private - Answer an index referring to the receiver's scalar type" ^9 ] ] CScalar subclass: CLongLong [ CLongLong class >> sizeof [ "Answer the receiver's instances size" ^8 ] CLongLong class >> alignof [ "Answer the receiver's instances required aligment" ^CLongLongAlignment ] CLongLong class >> cObjStoredType [ "Private - Answer an index referring to the receiver's instances scalar type" ^30 ] sizeof [ "Answer the receiver's size" ^8 ] alignof [ "Answer the receiver's required aligment" ^CLongLongAlignment ] cObjStoredType [ "Private - Answer an index referring to the receiver's scalar type" ^30 ] ] CScalar subclass: CULongLong [ CULongLong class >> sizeof [ "Answer the receiver's instances size" ^8 ] CULongLong class >> alignof [ "Answer the receiver's instances required aligment" ^CLongLongAlignment ] CULongLong class >> cObjStoredType [ "Private - Answer an index referring to the receiver's instances scalar type" ^31 ] sizeof [ "Answer the receiver's size" ^8 ] alignof [ "Answer the receiver's required aligment" ^CLongLongAlignment ] cObjStoredType [ "Private - Answer an index referring to the receiver's scalar type" ^31 ] ] CScalar subclass: CLong [ CLong class >> sizeof [ "Answer the receiver's instances size" ^CLongSize ] CLong class >> alignof [ "Answer the receiver's instances required aligment" ^CLongSize ] CLong class >> cObjStoredType [ "Private - Answer an index referring to the receiver's instances scalar type" ^4 ] sizeof [ "Answer the receiver's size" ^CLongSize ] alignof [ "Answer the receiver's required aligment" ^CLongSize ] cObjStoredType [ "Private - Answer an index referring to the receiver's scalar type" ^4 ] ] CScalar subclass: CULong [ CULong class >> sizeof [ "Answer the receiver's instances size" ^CLongSize ] CULong class >> alignof [ "Answer the receiver's instances required aligment" ^CLongSize ] CULong class >> cObjStoredType [ "Private - Answer an index referring to the receiver's instances scalar type" ^5 ] sizeof [ "Answer the receiver's size" ^CLongSize ] alignof [ "Answer the receiver's required aligment" ^CLongSize ] cObjStoredType [ "Private - Answer an index referring to the receiver's scalar type" ^5 ] ] CScalar subclass: CInt [ CInt class >> sizeof [ "Answer the receiver's size" ^CIntSize ] CInt class >> alignof [ "Answer the receiver's required aligment" ^CIntSize ] CInt class >> cObjStoredType [ "Private - Answer an index referring to the receiver's instances scalar type" ^10 ] sizeof [ "Answer the receiver's instances size" ^CIntSize ] alignof [ "Answer the receiver's instances required aligment" ^CIntSize ] cObjStoredType [ "Private - Answer an index referring to the receiver's scalar type" ^10 ] ] CScalar subclass: CUInt [ CUInt class >> sizeof [ "Answer the receiver's instances size" ^CIntSize ] CUInt class >> alignof [ "Answer the receiver's instances required aligment" ^CIntSize ] CUInt class >> cObjStoredType [ "Private - Answer an index referring to the receiver's instances scalar type" ^11 ] sizeof [ "Answer the receiver's size" ^CIntSize ] alignof [ "Answer the receiver's required aligment" ^CIntSize ] cObjStoredType [ "Private - Answer an index referring to the receiver's scalar type" ^11 ] ] CScalar subclass: CShort [ CShort class >> sizeof [ "Answer the receiver's instances size" ^CShortSize ] CShort class >> alignof [ "Answer the receiver's instances required aligment" ^CShortSize ] CShort class >> cObjStoredType [ "Private - Answer an index referring to the receiver's instances scalar type" ^2 ] sizeof [ "Answer the receiver's size" ^CShortSize ] alignof [ "Answer the receiver's required aligment" ^CShortSize ] cObjStoredType [ "Private - Answer an index referring to the receiver's scalar type" ^2 ] ] CScalar subclass: CUShort [ CUShort class >> sizeof [ "Answer the receiver's instances size" ^CShortSize ] CUShort class >> alignof [ "Answer the receiver's instances required aligment" ^CShortSize ] CUShort class >> cObjStoredType [ "Private - Answer an index referring to the receiver's instances scalar type" ^3 ] sizeof [ "Answer the receiver's size" ^CShortSize ] alignof [ "Answer the receiver's required aligment" ^CShortSize ] cObjStoredType [ "Private - Answer an index referring to the receiver's scalar type" ^3 ] ] CScalar subclass: CChar [ CChar class >> sizeof [ "Answer the receiver's instances size" ^1 ] CChar class >> alignof [ "Answer the receiver's instances required aligment" ^1 ] CChar class >> cObjStoredType [ "Private - Answer an index referring to the receiver's instances scalar type" ^0 ] asByteArray: size [ "Convert size bytes pointed to by the receiver to a String" ^ByteArray fromCData: self size: size ] asString [ "Convert the data pointed to by the receiver, up to the first NULL byte, to a String" ^String fromCData: self ] asString: size [ "Convert size bytes pointed to by the receiver to a String" ^String fromCData: self size: size ] sizeof [ "Answer the receiver's size" ^1 ] alignof [ "Answer the receiver's required aligment" ^1 ] cObjStoredType [ "Private - Answer an index referring to the receiver's scalar type" ^0 ] ] CScalar subclass: CUChar [ CUChar class >> sizeof [ "Answer the receiver's instances size" ^1 ] CUChar class >> alignof [ "Answer the receiver's instances required aligment" ^1 ] CUChar class >> cObjStoredType [ "Private - Answer an index referring to the receiver's instances scalar type" ^1 ] sizeof [ "Answer the receiver's size" ^1 ] alignof [ "Answer the receiver's required aligment" ^1 ] cObjStoredType [ "Private - Answer an index referring to the receiver's scalar type" ^1 ] ] CScalar subclass: CFloat [ CFloat class >> sizeof [ "Answer the receiver's instances size" ^CFloatSize ] CFloat class >> alignof [ "Answer the receiver's instances required aligment" ^CFloatSize ] CFloat class >> cObjStoredType [ "Private - Answer an index referring to the receiver's instances scalar type" ^6 ] sizeof [ "Answer the receiver's size" ^CFloatSize ] alignof [ "Answer the receiver's required aligment" ^CFloatSize ] cObjStoredType [ "Private - Answer an index referring to the receiver's scalar type" ^6 ] ] CScalar subclass: CDouble [ CDouble class >> sizeof [ "Answer the receiver's instances size" ^CDoubleSize ] CDouble class >> alignof [ "Answer the receiver's instances required aligment" ^CDoubleAlignment ] CDouble class >> cObjStoredType [ "Private - Answer an index referring to the receiver's instances scalar type" ^7 ] sizeof [ "Answer the receiver's size" ^CDoubleSize ] alignof [ "Answer the receiver's required aligment" ^CDoubleAlignment ] cObjStoredType [ "Private - Answer an index referring to the receiver's scalar type" ^7 ] ] CScalar subclass: CLongDouble [ CLongDouble class >> sizeof [ "Answer the receiver's instances size" ^CLongDoubleSize ] CLongDouble class >> alignof [ "Answer the receiver's instances required aligment" ^CLongDoubleAlignment ] CLongDouble class >> cObjStoredType [ "Private - Answer an index referring to the receiver's instances scalar type" ^12 ] sizeof [ "Answer the receiver's size" ^CLongDoubleSize ] alignof [ "Answer the receiver's required aligment" ^CLongDoubleAlignment ] cObjStoredType [ "Private - Answer an index referring to the receiver's scalar type" ^12 ] ] CObject subclass: CAggregate [ CAggregate class >> sizeof [ "Answer the receiver's instances size" "This is the closest possible guess for CArrays" ^CPtrSize ] CAggregate class >> alignof [ "Answer the receiver's instances required aligment" "This is the closest possible guess for CArrays" ^CPtrSize ] elementType [ "Answer the type over which the receiver is constructed." ^self type elementType ] ] CAggregate subclass: CArray [ sizeof [ "Answer the receiver's size" ^self type numberOfElements * self elementType sizeof ] alignof [ "Answer the receiver's required aligment" ^self elementType alignof ] dereferencedType [ ^self type elementType ] cObjStoredType [ "Private - Provide a conversion from a CObject to a Smalltalk object to be stored by #at:put:" "If they want to store the receiver with #at:put:, they store the address (of the first character) without dereferencing the pointer." ^CLong cObjStoredType ] cObjStoredValue [ "Private - Provide a conversion from a CObject to a Smalltalk object to be stored by #at:put:" "If they want to store the receiver with #at:put:, they store the address without dereferencing the pointer." ^self address ] ] CAggregate subclass: CPtr [ sizeof [ "Answer the receiver's size" ^CPtrSize ] alignof [ "Answer the receiver's required aligment" ^CPtrSize ] value [ "Answer the address of the location pointed to by the receiver." ^self derefAt: 0 type: self type elementType ] value: anObject [ "Set the address of the location pointed to by the receiver to anObject, which can be either an Integer or a CObject. if anObject is an Integer, it is interpreted as a 32-bit or 64-bit address. If it is a CObject, its address is stored." anObject isInteger ifTrue: [^self at: 0 put: anObject type: CLong cObjStoredType]. self at: 0 put: anObject address type: CLong cObjStoredType ] ] CPtr subclass: CString [ >#asString. In general, I behave like a cross between an array of characters and a pointer to a character. I provide the protocol for both data types. My #value method returns a Smalltalk String, as you would expect for a scalar datatype. '> CString class >> value: anObject [ "Answer a newly allocated CObject containing the passed value, anObject. Remember to call #addToBeFinalized if you want the CObject to be automatically freed" | cObject | cObject := self type new. cObject value: anObject. ^cObject ] CString class >> type [ "Answer a CType for the receiver---for example, CByteType if the receiver is CByte." ^CStringType ] CString class >> cObjStoredType [ "Private - Provide a conversion from a CObject to a Smalltalk object to be stored by #at:put:" ^8 ] cObjStoredType [ "Private - Provide a conversion from a CObject to a Smalltalk object to be stored by #at:put:" ^8 ] value [ "Answer the value the receiver is pointing to. The exact returned value depends on the receiver's class" ^self at: 0 type: 8 ] value: aValue [ "Set the receiver to point to the value, aValue. The exact meaning of aValue depends on the receiver's class" self at: 0 put: aValue type: 8 ] ] CUChar subclass: CByte [ CByte class >> cObjStoredType [ "Nothing special in the default case - answer a CType for the receiver" ^self type ] CByte class >> type [ "Answer a CType for the receiver" ^CByteType ] cObjStoredType [ "Nothing special in the default case - answer the receiver's CType" ^self type ] value [ "Answer the value the receiver is pointing to. The returned value is a SmallInteger" ^(self at: 0 type: super cObjStoredType) value ] value: aValue [ "Set the receiver to point to the value, aValue (a SmallInteger)." self at: 0 put: (Character value: aValue) type: super cObjStoredType ] ] CByte subclass: CBoolean [ CBoolean class >> type [ "Answer a CType for the receiver" ^CBooleanType ] value [ "Get the receiver's value - answer true if it is != 0, false if it is 0." ^super value > 0 ] value: aBoolean [ "Set the receiver's value - it's the same as for CBytes, but we get a Boolean, not a Character" ^super value: aBoolean asCBooleanValue ] ] "Forward define CType instances" Eval [ Smalltalk at: #CCharType put: nil. Smalltalk at: #CStringType put: nil ] UndefinedObject extend [ free [ "Do nothing, a NULL pointer can be safely freed." ] narrow [ "Return the receiver: a NULL pointer is always nil, whatever its type." ^self ] ] smalltalk-3.2.5/kernel/Regex.st0000644000175000017500000006635212123404352013340 00000000000000"====================================================================== | | String manipulation and regular expression resolver | | ======================================================================" "====================================================================== | | Copyright 2001, 2003, 2005, 2006, 2007, 2008, 2009 | Free Software Foundation, Inc. | Written by Dragomir Milevojevic, Paolo Bonzini, Mike Anderson. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LESSER. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" Object subclass: Regex [ Regex class >> fromString: aString [ "Like `aString asRegex'." ] Regex class >> new [ "Do not send this message." self error: 'please use #fromString: to create instances' ] at: anIndex put: anObject [ "Fail. Regex objects are read-only." self shouldNotImplement ] copy [ "Answer the receiver; instances of Regex are identity objects because their only purpose is to ease caching, and we obtain better caching if we avoid copying Regex objects" ^self ] asRegex [ "Answer the receiver, which *is* a Regex!" ^self ] asString [ "Answer the receiver, converted back to a String" ^(String new: self size) replaceFrom: 1 to: self size with: self startingAt: 1; yourself ] species [ ^String ] displayString [ "Answer a String representing the receiver. For most objects this is simply its #printString, but for strings and characters, superfluous dollars or extra pair of quotes are stripped." | stream | stream := WriteStream on: (String new: 0). self displayOn: stream. ^stream contents ] displayOn: aStream [ "Print a represention of the receiver on aStream. For most objects this is simply its #printOn: representation, but for strings and characters, superfluous dollars or extra pairs of quotes are stripped." self printOn: aStream ] printOn: aStream [ "Print a represention of the receiver on aStream." aStream nextPut: $/. self asString do: [:each | each = $/ ifTrue: [ aStream nextPut: $\ ]. aStream nextPut: each]. aStream nextPut: $/ ] ] Object subclass: RegexResults [ matched [ "Answer whether the regular expression was matched" self subclassResponsibility ] ifMatched: oneArgBlock ifNotMatched: zeroArgBlock [ "If the regular expression was matched, evaluate oneArgBlock with the receiver as the argument. If it was not, evaluate zeroArgBlock. Answer the result of the block's evaluation." self subclassResponsibility ] ifNotMatched: zeroArgBlock ifMatched: oneArgBlock [ "If the regular expression was matched, evaluate oneArgBlock with the receiver as the argument. If it was not, evaluate zeroArgBlock. Answer the result of the block's evaluation." self subclassResponsibility ] ifNotMatched: zeroArgBlock [ "If the regular expression was matched, return the receiver. If it was not, evaluate zeroArgBlock and return its result." ^self ifNotMatched: zeroArgBlock ifMatched: [] ] ifMatched: oneArgBlock [ "If the regular expression was matched, pass the receiver to oneArgBlock and return its result. Otherwise, return nil." ^self ifNotMatched: [] ifMatched: oneArgBlock ] size [ "If the regular expression was matched, return the number of subexpressions that were present in the regular expression." self subclassResponsibility ] asArray [ "If the regular expression was matched, return an Array with the subexpressions that were present in the regular expression." ^1 to: self size collect: [ :each | self at: each ] ] subject [ "If the regular expression was matched, return the text that was matched against it." self subclassResponsibility ] from [ "If the regular expression was matched, return the index of the first character in the successful match." self subclassResponsibility ] fromAt: anIndex [ "If the regular expression was matched, return the index of the first character of the anIndex-th subexpression in the successful match." self subclassResponsibility ] to [ "If the regular expression was matched, return the index of the last character in the successful match." self subclassResponsibility ] toAt: anIndex [ "If the regular expression was matched, return the index of the last character of the anIndex-th subexpression in the successful match." self subclassResponsibility ] match [ "If the regular expression was matched, return the text of the successful match." self subclassResponsibility ] matchInterval [ "If the regular expression was matched, return an Interval for the range of indices of the successful match." self subclassResponsibility ] at: anIndex [ "If the regular expression was matched, return the text of the anIndex-th subexpression in the successful match." self subclassResponsibility ] intervalAt: anIndex [ "If the regular expression was matched, return an Interval for the range of indices in the anIndex-th subexpression of the successful match." self subclassResponsibility ] ] Namespace current: Kernel [ RegexResults subclass: MatchingRegexResults [ | subject from to registers match cache | printOn: aStream [ "Print a represention of the receiver on aStream." | ch | aStream nextPutAll: self class name; nextPut: $:; print: self match. ch := $(. 1 to: self size do: [:each | aStream nextPut: ch; print: (self at: each). ch := $,]. self size > 0 ifTrue: [aStream nextPut: $)] ] matched [ ^true ] ifMatched: oneArgBlock ifNotMatched: zeroArgBlock [ ^oneArgBlock cull: self ] ifNotMatched: zeroArgBlock ifMatched: oneArgBlock [ ^oneArgBlock cull: self ] size [ ^registers size ] subject [ ^subject ] from [ ^from ] fromAt: anIndex [ | reg | anIndex = 0 ifTrue: [^from]. reg := registers at: anIndex. ^reg isNil ifTrue: [nil] ifFalse: [reg first] ] to [ ^to ] toAt: anIndex [ | reg | anIndex = 0 ifTrue: [^from]. reg := registers at: anIndex. ^reg isNil ifTrue: [nil] ifFalse: [reg last] ] match [ match isNil ifTrue: [match := self subject copyFrom: from to: to]. ^match ] matchInterval [ ^from to: to ] at: anIndex [ | reg text | anIndex = 0 ifTrue: [^self match]. cache isNil ifTrue: [cache := Array new: registers size]. (cache at: anIndex) isNil ifTrue: [reg := registers at: anIndex. text := reg isNil ifTrue: [nil] ifFalse: [self subject copyFrom: reg first to: reg last]. cache at: anIndex put: text]. ^cache at: anIndex ] intervalAt: anIndex [ ^anIndex = 0 ifTrue: [from to: to] ifFalse: [registers at: anIndex] ] ] ] Namespace current: Kernel [ RegexResults subclass: FailedMatchRegexResults [ FailedMatchRegexResults class [ | uniqueInstance | ] FailedMatchRegexResults class >> uniqueInstance [ ^uniqueInstance isNil ifTrue: [uniqueInstance := self new] ifFalse: [uniqueInstance] ] matched [ ^false ] ifMatched: oneArgBlock ifNotMatched: zeroArgBlock [ ^zeroArgBlock cull: self ] ifNotMatched: zeroArgBlock ifMatched: oneArgBlock [ ^zeroArgBlock cull: self ] size [ self shouldNotImplement ] subject [ self shouldNotImplement ] from [ self shouldNotImplement ] fromAt: anIndex [ self shouldNotImplement ] to [ self shouldNotImplement ] toAt: anIndex [ self shouldNotImplement ] match [ self shouldNotImplement ] matchInterval [ self shouldNotImplement ] at: anIndex [ self shouldNotImplement ] intervalAt: anIndex [ self shouldNotImplement ] ] ] String extend [ lengthOfRegexMatch: pattern from: from to: to [ ] searchRegexInternal: pattern from: from to: to [ ] asRegex [ "Answer the receiver, converted to a Regex object." ^Regex fromString: self ] ~ pattern [ "Answer whether the receiver matched against the Regex or String object pattern." | regs | regs := self searchRegexInternal: pattern from: 1 to: self size. ^regs notNil ] =~ pattern [ "Answer a RegexResults object for matching the receiver against the Regex or String object pattern." | regs | regs := self searchRegexInternal: pattern from: 1 to: self size. ^regs isNil ifTrue: [Kernel.FailedMatchRegexResults uniqueInstance] ifFalse: [regs] ] searchRegex: pattern [ "A synonym for #=~. Answer a RegexResults object for matching the receiver against the Regex or String object pattern." | regs | regs := self searchRegexInternal: pattern from: 1 to: self size. ^regs isNil ifTrue: [Kernel.FailedMatchRegexResults uniqueInstance] ifFalse: [regs] ] searchRegex: pattern startingAt: anIndex [ "Answer a RegexResults object for matching the receiver against the Regex or String object pattern, starting the match at index anIndex." | regs | regs := self searchRegexInternal: pattern from: anIndex to: self size. ^regs isNil ifTrue: [Kernel.FailedMatchRegexResults uniqueInstance] ifFalse: [regs] ] searchRegex: pattern from: from to: to [ "Answer a RegexResults object for matching the receiver against the Regex or String object pattern, restricting the match to the specified range of indices." | regs | regs := self searchRegexInternal: pattern from: from to: to. ^regs isNil ifTrue: [Kernel.FailedMatchRegexResults uniqueInstance] ifFalse: [regs] ] indexOfRegex: regexString ifAbsent: excBlock [ "If an occurrence of the regex is present in the receiver, return the Interval corresponding to the leftmost-longest match. Otherwise, evaluate excBlock and return the result." | regs | regs := self searchRegexInternal: regexString from: 1 to: self size. ^regs isNil ifFalse: [regs matchInterval] ifTrue: [excBlock value] ] indexOfRegex: regexString startingAt: index ifAbsent: excBlock [ "If an occurrence of the regex is present in the receiver, return the Interval corresponding to the leftmost-longest match starting after the given index. Otherwise, evaluate excBlock and return the result." | regs | regs := self searchRegexInternal: regexString from: index to: self size. ^regs isNil ifFalse: [regs matchInterval] ifTrue: [excBlock value] ] indexOfRegex: regexString from: from to: to ifAbsent: excBlock [ "If an occurrence of the regex is present in the receiver, return the Interval corresponding to the leftmost-longest match occurring within the given indices. Otherwise, evaluate excBlock and return the result." | regs | regs := self searchRegexInternal: regexString from: from to: to. ^regs isNil ifFalse: [regs matchInterval] ifTrue: [excBlock value] ] indexOfRegex: regexString [ "If an occurrence of the regex is present in the receiver, return the Interval corresponding to the leftmost-longest match. Otherwise return nil." | regs | regs := self searchRegexInternal: regexString from: 1 to: self size. ^regs isNil ifFalse: [regs matchInterval] ] indexOfRegex: regexString startingAt: index [ "If an occurrence of the regex is present in the receiver, return the Interval corresponding to the leftmost-longest match starting after the given index. Otherwise return nil." | regs | regs := self searchRegexInternal: regexString from: index to: self size. ^regs isNil ifFalse: [regs matchInterval] ] indexOfRegex: regexString from: from to: to [ "If an occurrence of the regex is present in the receiver, return the Interval corresponding to the leftmost-longest match occurring within the given range of indices. Otherwise return nil." | regs | regs := self searchRegexInternal: regexString from: from to: to. ^regs isNil ifFalse: [regs matchInterval] ] matchRegex: pattern [ "Answer whether the receiver is an exact match for the pattern. This means that the pattern is implicitly anchored at the beginning and the end." ^(self lengthOfRegexMatch: pattern from: 1 to: self size) = self size ] matchRegex: pattern from: from to: to [ "Answer whether the given range of indices is an exact match for the pattern. This means that there is a match starting at from and ending at to (which is not necessarily the longest match starting at from)." ^(self lengthOfRegexMatch: pattern from: from to: to) = (to - from + 1) ] occurrencesOfRegex: pattern from: from to: to [ "Return a count of how many times pattern repeats in the receiver within the given range of index." | res idx regex regs | regex := pattern asRegex. res := 0. idx := from. [regs := self searchRegexInternal: regex from: idx to: to. regs notNil] whileTrue: [idx := regs to max: regs from + 1. res := res + 1]. ^res ] occurrencesOfRegex: pattern startingAt: index [ "Returns count of how many times pattern repeats in the receiver, starting the search at the given index." ^self occurrencesOfRegex: pattern from: index to: self size ] occurrencesOfRegex: pattern [ "Returns count of how many times pattern repeats in the receiver." ^self occurrencesOfRegex: pattern from: 1 to: self size ] allOccurrencesOfRegex: pattern from: from to: to [ "Find all the matches of pattern within the receiver and within the given range of indices. Collect them into an OrderedCollection, which is then returned." | result | result := OrderedCollection new. self allOccurrencesOfRegex: pattern from: from to: to do: [ :each | result add: each match ]. ^result ] allOccurrencesOfRegex: pattern [ "Find all the matches of pattern within the receiver and collect them into an OrderedCollection." ^self allOccurrencesOfRegex: pattern from: 1 to: self size ] allOccurrencesOfRegex: pattern from: from to: to do: aBlock [ "Find all the matches of pattern within the receiver and within the given range of indices. For each match, pass the RegexResults object to aBlock." | idx regex regs beg end emptyOk | regex := pattern asRegex. idx := from. emptyOk := true. [regs := self searchRegexInternal: regex from: idx to: to. regs isNil] whileFalse: [beg := regs from. end := regs to. (beg <= end or: [ beg > idx or: [ emptyOk ]]) ifTrue: [ aBlock value: regs. emptyOk := false. idx := end + 1] ifFalse: [ beg <= to ifFalse: [^self]. emptyOk := true. idx := beg + 1]]. ] allOccurrencesOfRegex: pattern do: aBlock [ "Find all the matches of pattern within the receiver and pass the RegexResults objects to aBlock." ^self allOccurrencesOfRegex: pattern from: 1 to: self size do: aBlock ] replacingRegex: pattern with: aStringOrBlock [ "Returns the receiver if the pattern has no match in it. If it has a match, it is replaced using aStringOrBlock as follows: if it is a block, a RegexResults object is passed, while if it is a string, %n sequences are replaced with the captured subexpressions of the match (as in #%)." | regs beg end repl res | regs := self searchRegexInternal: pattern from: 1 to: self size. regs isNil ifTrue: [^self]. beg := regs from. end := regs to. repl := aStringOrBlock isString ifTrue: [ aStringOrBlock % regs ] ifFalse: [ aStringOrBlock value: regs ]. ^(res := self species new: self size - (end - beg + 1) + repl size) replaceFrom: 1 to: beg - 1 with: self startingAt: 1; replaceFrom: beg to: beg + repl size - 1 with: repl startingAt: 1; replaceFrom: beg + repl size to: res size with: self startingAt: end + 1 ] replacingAllRegex: pattern with: aStringOrBlock [ "Returns the receiver if the pattern has no match in it. Otherwise, any match of pattern in that part of the string is replaced using aStringOrBlock as follows: if it is a block, a RegexResults object is passed, while if it is a string, %n sequences are replaced with the captured subexpressions of the match (as in #%)." | res idx regex beg end regs repl | regex := pattern asRegex. regs := self searchRegexInternal: regex from: 1 to: self size. regs isNil ifTrue: [^self]. res := WriteStream on: (String new: self size). idx := 1. repl := aStringOrBlock isString ifTrue: [ [ :regs | aStringOrBlock % regs ] ] ifFalse: [ aStringOrBlock ]. [beg := regs from. end := regs to. res next: beg - idx putAll: self startingAt: idx. res nextPutAll: (repl value: regs). idx := end + 1. beg > end ifTrue: [res nextPut: (self at: idx). idx := idx + 1]. idx > self size ifTrue: [^res contents]. regs := self searchRegexInternal: regex from: idx to: self size. regs isNil] whileFalse. res next: self size - idx + 1 putAll: self startingAt: idx. ^res contents ] copyFrom: from to: to replacingRegex: pattern with: aStringOrBlock [ "Returns the substring of the receiver between from and to. If pattern has a match in that part of the string, the match is replaced using aStringOrBlock as follows: if it is a block, a RegexResults object is passed, while if it is a string, %n sequences are replaced with the captured subexpressions of the match (as in #%)." | regs beg end repl res | regs := self searchRegexInternal: pattern from: from to: to. regs isNil ifFalse: [beg := regs from. end := regs to. repl := aStringOrBlock isString ifTrue: [ aStringOrBlock % regs ] ifFalse: [ aStringOrBlock value: regs ]. res := self species new: to - from - (end - beg) + repl size. res replaceFrom: 1 to: beg - from with: self startingAt: from. res replaceFrom: beg - from + 1 to: beg - from + repl size with: repl. res replaceFrom: beg - from + repl size + 1 to: res size with: self startingAt: end - from + 2] ifTrue: [res := self copyFrom: from to: to]. ^res ] copyReplacingRegex: pattern with: aStringOrBlock [ "Returns the receiver after replacing the first match of pattern (if any) using aStringOrBlock as follows: if it is a block, a RegexResults object is passed, while if it is a string, %n sequences are replaced with the captured subexpressions of the match (as in #%)." ^self copyFrom: 1 to: self size replacingRegex: pattern with: aStringOrBlock ] copyFrom: from to: to replacingAllRegex: pattern with: aStringOrBlock [ "Returns the substring of the receiver between from and to. Any match of pattern in that part of the string is replaced using aStringOrBlock as follows: if it is a block, a RegexResults object is passed, while if it is a string, %n sequences are replaced with the captured subexpressions of the match (as in #%)." | res idx regex beg end regs emptyOk repl | regex := pattern asRegex. res := WriteStream on: (String new: to - from + 1). idx := from. emptyOk := true. repl := aStringOrBlock isString ifTrue: [ [ :regs | aStringOrBlock % regs ] ] ifFalse: [ aStringOrBlock ]. [regs := self searchRegexInternal: regex from: idx to: to. regs isNil] whileFalse: [beg := regs from. end := regs to. (beg <= end or: [ beg > idx or: [ emptyOk ]]) ifTrue: [ emptyOk := false. res next: beg - idx putAll: self startingAt: idx. res nextPutAll: (repl value: regs). idx := end + 1] ifFalse: [ beg <= to ifFalse: [^res contents]. emptyOk := true. res nextPut: (self at: beg). idx := beg + 1]]. res next: to - idx + 1 putAll: self startingAt: idx. ^res contents ] copyReplacingAllRegex: pattern with: aStringOrBlock [ "Returns the receiver after replacing all the matches of pattern (if any) using aStringOrBlock as follows: if it is a block, a RegexResults object is passed, while if it is a string, %n sequences are replaced with the captured subexpressions of the match (as in #%)." ^self copyFrom: 1 to: self size replacingAllRegex: pattern with: aStringOrBlock ] onOccurrencesOfRegex: pattern from: from to: to do: aBlock [ "Find all the matches of pattern within the receiver and within the given range of indices. For each match, pass the RegexResults object to aBlock." | idx regex regs | regex := pattern asRegex. idx := from. [regs := self searchRegexInternal: regex from: idx to: to. regs notNil] whileTrue: [aBlock value: regs. idx := regs to + 1 max: regs from + 1]. ] onOccurrencesOfRegex: pattern do: body [ "Find all the matches of pattern within the receiver and, for each match, pass the RegexResults object to aBlock." ^self onOccurrencesOfRegex: pattern from: 1 to: self size do: body ] tokenize: pattern from: from to: to [ "Split the receiver at every occurrence of pattern (considering only the indices between from and to). All parts that do not match pattern are separated and stored into an Array of Strings that is returned." | res idx tokStart regex regs beg end emptyOk | regex := pattern asRegex. res := WriteStream on: (Array new: 10). idx := tokStart := from. emptyOk := false. [regs := self searchRegexInternal: regex from: idx to: to. regs notNil] whileTrue: [beg := regs from. end := regs to. (beg <= end or: [ beg > idx or: [ emptyOk ]]) ifTrue: [ emptyOk := false. res nextPut: (self copyFrom: tokStart to: beg - 1). idx := tokStart := end + 1 ] ifFalse: [ "If we reach the end of the string exit without adding the token. tokStart must have been set above to TO + 1 (it was set above just before setting emptyOk to false), so we'd add an empty token we don't want." beg <= to ifFalse: [^res contents]. emptyOk := true. "By not updating tokStart we put the character in the next token." idx := beg + 1]]. (tokStart <= to or: [ emptyOk ]) ifTrue: [ res nextPut: (self copyFrom: tokStart to: to) ]. ^res contents ] tokenize: pattern [ "Split the receiver at every occurrence of pattern. All parts that do not match pattern are separated and stored into an Array of Strings that is returned." ^self tokenize: pattern from: 1 to: self size ] escapeRegex [ "Answer the receiver with all regex special characters escaped by a backslash." ^self copyReplacingAllRegex: '([][?*+\\()^$|])' with: '\%1'. ] ] Eval [ Kernel.FailedMatchRegexResults initialize ] smalltalk-3.2.5/kernel/True.st0000644000175000017500000000565612123404352013205 00000000000000"====================================================================== | | True Method Definitions | | ======================================================================" "====================================================================== | | Copyright 1988,92,94,95,99,2000,2001 | Free Software Foundation, Inc. | Written by Steve Byrne. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" Boolean subclass: True [ | truthValue | asCBooleanValue [ ^1 ] ifTrue: trueBlock ifFalse: falseBlock [ "We are true -- evaluate trueBlock" ^trueBlock value ] ifFalse: falseBlock ifTrue: trueBlock [ "We are true -- evaluate trueBlock" ^trueBlock value ] ifTrue: trueBlock [ "We are true -- evaluate trueBlock" ^trueBlock value ] ifFalse: falseBlock [ "We are true -- answer nil" ^nil ] not [ "We are true -- answer false" ^false ] & aBoolean [ "We are true -- anded with anything, we always answer the other operand" ^aBoolean ] | aBoolean [ "We are true -- ored with anything, we always answer true" ^true ] eqv: aBoolean [ "Answer whether the receiver and aBoolean represent the same boolean value" ^aBoolean ] xor: aBoolean [ "Answer whether the receiver and aBoolean represent different boolean values" ^aBoolean not ] and: aBlock [ "We are true -- anded with anything, we always answer the other operand, so evaluate aBlock" ^aBlock value ] or: aBlock [ "We are true -- ored with anything, we always answer true" ^true ] printOn: aStream [ "Print a representation of the receiver on aStream" aStream nextPutAll: 'true' ] ] smalltalk-3.2.5/kernel/SmallInt.st0000644000175000017500000002640012123404352013777 00000000000000"====================================================================== | | SmallInteger Method Definitions | | ======================================================================" "====================================================================== | | Copyright 2000, 2001, 2002, 2007, 2008 Free Software Foundation, Inc. | Written by Paolo Bonzini. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" Integer subclass: SmallInteger [ SmallInteger class >> isIdentity [ "Answer whether x = y implies x == y for instances of the receiver" ^true ] SmallInteger class >> bits [ "Answer the number of bits (excluding the sign) that can be represented directly in an object pointer" ^CLongSize * 8 - 3 ] SmallInteger class >> largest [ "Answer the largest integer represented directly in an object pointer" | maxBit | maxBit := 1 bitShift: CLongSize * 8 - 3. ^maxBit - 1 + maxBit ] SmallInteger class >> smallest [ "Answer the smallest integer represented directly in an object pointer" | maxBit | maxBit := 1 bitShift: CLongSize * 8 - 3. ^maxBit negated - maxBit ] zero [ "Coerce 0 to the receiver's class" ^0 ] unity [ "Coerce 1 to the receiver's class" ^1 ] generality [ "Return the receiver's generality" ^100 ] lowBit [ "Return the index of the lowest order 1 bit of the receiver." | n bit | self = 0 ifTrue: [^0]. n := self. "The result is 1-based, but we start from 2 to compensate with the subtraction in the final line." bit := 2. (n bitAnd: 1073741823) = 0 ifTrue: [bit := bit + 30. n := n bitShift: -30]. (n bitAnd: 65535) = 0 ifTrue: [bit := bit + 16. n := n bitShift: -16]. (n bitAnd: 255) = 0 ifTrue: [bit := bit + 8. n := n bitShift: -8]. (n bitAnd: 15) = 0 ifTrue: [bit := bit + 4. n := n bitShift: -4]. (n bitAnd: 3) = 0 ifTrue: [bit := bit + 2. n := n bitShift: -2]. ^bit - (n bitAnd: 1) ] highBit [ "Return the index of the highest order 1 bit of the receiver" | n bit | self = 0 ifTrue: [^0]. bit := 0. self < 0 ifTrue: ["Increment the result by one if not a power of two" n := self negated. (n bitAnd: self) = n ifFalse: [bit := 1]] ifFalse: [n := self. bit := 0]. [n > 1073741823] whileTrue: [bit := bit + 30. n := n bitShift: -30]. n > 65535 ifTrue: [bit := bit + 16. n := n bitShift: -16]. n > 255 ifTrue: [bit := bit + 8. n := n bitShift: -8]. n > 15 ifTrue: [bit := bit + 4. n := n bitShift: -4]. n > 3 ifTrue: [bit := bit + 2. n := n bitShift: -2]. n > 1 ifTrue: [bit := bit + 1. n := n bitShift: -1]. ^n + bit ] isSmallInteger [ ^true ] + arg [ "Sum the receiver and arg and answer another Number" ^self generality == arg generality ifFalse: [self retrySumCoercing: arg] ifTrue: [(LargeInteger fromInteger: self) + (LargeInteger fromInteger: arg)] ] - arg [ "Subtract arg from the receiver and answer another Number" ^self generality == arg generality ifFalse: [self retryDifferenceCoercing: arg] ifTrue: [(LargeInteger fromInteger: self) - (LargeInteger fromInteger: arg)] ] < arg [ "Answer whether the receiver is less than arg" ^self retryRelationalOp: #< coercing: arg ] > arg [ "Answer whether the receiver is greater than arg" ^self retryRelationalOp: #> coercing: arg ] <= arg [ "Answer whether the receiver is less than or equal to arg" ^self retryRelationalOp: #<= coercing: arg ] >= arg [ "Answer whether the receiver is greater than or equal to arg" ^self retryRelationalOp: #>= coercing: arg ] = arg [ "Answer whether the receiver is equal to arg" ^self retryEqualityCoercing: arg ] == arg [ "Answer whether the receiver is the same object as arg" "if they aren't = by the primitive, they're not ==" ^false ] ~= arg [ "Answer whether the receiver is not equal to arg" ^self retryInequalityCoercing: arg ] ~~ arg [ "Answer whether the receiver is not the same object as arg" ^true "see comment above for ==" ] * arg [ "Multiply the receiver and arg and answer another Number" ^self generality == arg generality ifFalse: [self retryMultiplicationCoercing: arg] ifTrue: [(LargeInteger fromInteger: self) * (LargeInteger fromInteger: arg)] ] / arg [ "Divide the receiver by arg and answer another Integer or Fraction" "Create a Fraction when it's appropriate" arg = 0 ifTrue: [^self zeroDivide]. ^arg class == self class ifTrue: [(Fraction numerator: self denominator: arg) reduce] ifFalse: [self retryDivisionCoercing: arg] ] \\ arg [ "Calculate the remainder of dividing receiver by arg (with truncation towards -infinity) and answer it" arg = 0 ifTrue: [^self zeroDivide]. ^self retry: #\\ coercing: arg ] // arg [ "Dividing receiver by arg (with truncation towards -infinity) and answer the result" arg = 0 ifTrue: [^self zeroDivide]. ^self retry: #// coercing: arg ] divExact: arg [ "Dividing receiver by arg assuming that the remainder is zero, and answer the result" "Use quo:, no speed to gain fom SmallIntegers." self = 0 ifTrue: [^0]. arg = 0 ifTrue: [^self zeroDivide]. ^self retry: #divExact: coercing: arg ] quo: arg [ "Dividing receiver by arg (with truncation towards zero) and answer the result" arg = 0 ifTrue: [^self zeroDivide]. ^self retry: #quo: coercing: arg ] bitAnd: arg [ "Do a bitwise AND between the receiver and arg, answer the result" ^arg isInteger ifFalse: [SystemExceptions.WrongClass signalOn: arg mustBe: Integer] ifTrue: [(LargeInteger fromInteger: self) bitAnd: arg] ] bitOr: arg [ "Do a bitwise OR between the receiver and arg, answer the result" ^arg isInteger ifFalse: [SystemExceptions.WrongClass signalOn: arg mustBe: Integer] ifTrue: [(LargeInteger fromInteger: self) bitOr: arg] ] bitXor: arg [ "Do a bitwise XOR between the receiver and arg, answer the result" ^arg isInteger ifFalse: [SystemExceptions.WrongClass signalOn: arg mustBe: Integer] ifTrue: [(LargeInteger fromInteger: self) bitXor: arg] ] bitShift: arg [ "Shift the receiver by arg places to the left if arg > 0, by arg places to the right if arg < 0, answer another Number" ^arg isSmallInteger ifFalse: [SystemExceptions.WrongClass signalOn: arg mustBe: Integer] ifTrue: [(LargeInteger fromInteger: self) bitShift: arg] ] asCNumber [ "Convert the receiver to a kind of number that is understood by the C call-out mechanism." ^self ] asFloatD [ "Convert the receiver to a FloatD, answer the result" self primitiveFailed ] asFloatE [ "Convert the receiver to a FloatE, answer the result" self primitiveFailed ] asFloatQ [ "Convert the receiver to a FloatQ, answer the result" self primitiveFailed ] asObject [ "Answer the object whose index is in the receiver, nil if there is a free object, fail if index is out of bounds" self primitiveFailed ] nextValidOop [ "Answer the index of the first non-free OOP after the receiver. This is used internally; it is placed here to avoid polluting Object." ^nil ] asObjectNoFail [ "Answer the object whose index is in the receiver, or nil if no object is found at that index" ^nil ] scramble [ "Answer the receiver with its bits mixed and matched." self primitiveFailed ] at: anIndex [ "Answer the index-th indexed instance variable of the receiver. This method always fails." SystemExceptions.NotIndexable signalOn: self ] basicAt: anIndex [ "Answer the index-th indexed instance variable of the receiver. This method always fails." SystemExceptions.NotIndexable signalOn: self ] at: anIndex put: value [ "Store value in the index-th indexed instance variable of the receiver This method always fails." SystemExceptions.NotIndexable signalOn: self ] basicAt: anIndex put: value [ "Store value in the index-th indexed instance variable of the receiver This method always fails." SystemExceptions.NotIndexable signalOn: self ] ] smalltalk-3.2.5/kernel/MappedColl.st0000644000175000017500000001357312123404352014303 00000000000000"====================================================================== | | MappedCollection Method Definitions | | ======================================================================" "====================================================================== | | Copyright 1988,92,94,95,99,2000,2001,2002,2006,2007,2008 | Free Software Foundation, Inc. | Written by Steve Byrne. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" Collection subclass: MappedCollection [ | domain map | MappedCollection class >> collection: aCollection map: aMap [ "Answer a new MappedCollection using the given domain (aCollection) and map" ^self basicNew setCollection: aCollection andMap: aMap ] MappedCollection class >> new [ "This method should not be used; instead, use #collection:map: to create MappedCollection." SystemExceptions.WrongMessageSent signalOn: #new useInstead: #collection:map: ] at: key [ "Answer the object at the given key" ^domain at: (map at: key) ] atAll: keyCollection [ "Answer a new MappedCollection that only includes the given keys. The new MappedCollection might use keyCollection or consecutive integers for the keys, depending on the map's type. Fail if any of them is not found in the map." ^self class collection: domain map: (map atAll: keyCollection) ] at: key put: value [ "Store value at the given key" ^domain at: (map at: key) put: value ] domain [ "Answer the receiver's domain" ^domain ] map [ "Answer the receiver's map" ^map ] size [ "Answer the receiver's size" ^map size ] add: anObject [ self shouldNotImplement ] contents [ "Answer a bag with the receiver's values" | aBag | aBag := Bag new. map do: [:value | aBag add: (domain at: value)]. ^aBag ] copyFrom: a to: b [ "Answer a new collection containing all the items in the receiver from the a-th to the b-th." ^domain atAll: (map atAll: (a to: b)) ] do: aBlock [ "Evaluate aBlock for each object" map do: [:value | aBlock value: (domain at: value)] ] keys [ "Answer the keys that can be used to access this collection." ^map keys ] keysAndValuesDo: aBlock [ "Evaluate aBlock passing two arguments, one being a key that can be used to access this collection, and the other one being the value." map do: [:key | aBlock value: key value: (self at: key)] ] keysDo: aBlock [ "Evaluate aBlock on the keys that can be used to access this collection." map keysDo: aBlock ] collect: aBlock [ "Answer a Collection with the same keys as the map, where accessing a key yields the value obtained by passing through aBlock the value accessible from the key in the receiver. The result need not be another MappedCollection" "This is tricky. Optimize the operation in order to perform the minimal number of evaluation of aBlock" ^domain size > map size ifTrue: [map collect: [:key | aBlock value: (self at: key)]] ifFalse: [self class collection: (domain collect: aBlock) map: map copy] ] reject: aBlock [ "Answer the objects in the domain for which aBlock returns false" | newMap | newMap := newMap reject: [:key | aBlock value: (self at: key)]. ^self class collection: domain map: newMap ] select: aBlock [ "Answer the objects in the domain for which aBlock returns true" | newMap | newMap := newMap select: [:key | aBlock value: (self at: key)]. ^self class collection: domain map: newMap ] setCollection: aCollection andMap: aMap [ domain := aCollection. map := aMap ] species [ ^self class ] ] smalltalk-3.2.5/kernel/BlkContext.st0000644000175000017500000001256612123404352014341 00000000000000"====================================================================== | | BlockContext Method Definitions | | ======================================================================" "====================================================================== | | Copyright 1988,89,90,91,92,94,95,99,2000,2001,2002,2008 | Free Software Foundation, Inc. | Written by Steve Byrne. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" ContextPart subclass: BlockContext [ | outerContext | BlockContext class >> fromClosure: aBlockClosure parent: parentContext [ "Private - Make a real block context from the given BlockClosure." | cloneTheContextAndFoolTheVM | cloneTheContextAndFoolTheVM := [| ctx | ctx := thisContext parentContext copy. ctx parentContext: parentContext. "This value is returned by #fromClosure:parent:!" ^ctx]. "The returned context has its ip (or returnIP for the JIT) pointing after the first line, so starting execution in that context has the effect of evaluating the block. Simply initializing the context's instance variable is not enough, because even if we had a way to get the initial native-code IP, the prolog code would need access to the inline cache data. Such data is most easily provided if the block's evaluation is started by sending #value. Effectively, we are returning a continuation." cloneTheContextAndFoolTheVM value. ^aBlockClosure value ] printOn: aStream [ "Print a representation for the receiver on aStream" | home | (home := self home) isNil ifTrue: [ aStream nextPutAll: 'optimized '; display: self method; nextPutAll: ' ('; display: self currentFileName; nextPut: $:; display: self currentLineInFile; nextPut: $) ] ifFalse: [ aStream nextPutAll: '[] in '. home printOn: aStream line: self currentLineInFile] ] isInternalExceptionHandlingContext [ "Answer whether the receiver is a context that should be hidden to the user when presenting a backtrace. Such contexts are never blocks, but check the rest of the chain." ^self parentContext notNil and: [self parentContext isInternalExceptionHandlingContext] ] caller [ "Answer the context that called the receiver" ^self parentContext ] isDisabled [ "Answers false, because contexts that are skipped when doing a return are always MethodContexts. BlockContexts are removed from the chain whenever a non-local return is done, while MethodContexts need to stay there in case there is a non-local return from the #ensure: block." ^false ] isUnwind [ "Answers whether the context must continue execution even after a non-local return (a return from the enclosing method of a block, or a call to the #continue: method of ContextPart). Such contexts are created only by #ensure: and are always MethodContexts." ^false ] isEnvironment [ "To create a valid execution environment for the interpreter even before it starts, GST creates a fake context whose selector is nil and which can be used as a marker for the current execution environment. Answer whether the receiver is that kind of context (always false, since those contexts are always MethodContexts)." ^false ] outerContext [ "Answer the outer block/method context for the receiver" ^outerContext ] nthOuterContext: n [ "Answer the n-th outer block/method context for the receiver" | ctx | ctx := self. n timesRepeat: [ctx := ctx outerContext]. ^ctx ] isBlock [ "Answer whether the receiver is a block context" ^true ] home [ "Answer the MethodContext to which the receiver refers, or nil if it has been optimized away" ^outerContext isNil ifTrue: [nil] ifFalse: [outerContext home] ] ] smalltalk-3.2.5/kernel/Getopt.st0000644000175000017500000003465712123404352013533 00000000000000"====================================================================== | | Smalltalk command-line parser | | ======================================================================" "====================================================================== | | Copyright 2006 Free Software Foundation, Inc. | Written by Paolo Bonzini. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" Object subclass: Getopt [ | options longOptions prefixes args currentArg actionBlock errorBlock | Getopt class >> parse: args with: pattern do: actionBlock [ "Parse the command-line arguments in args according to the syntax specified in pattern. For every command-line option found, the two-argument block actionBlock is evaluated passing the option name and the argument. For file names (or in general, other command-line arguments than options) the block's first argument will be nil. For options without arguments, or with unspecified optional arguments, the block's second argument will be nil. The option name will be passed as a character object for short options, and as a string for long options. If an error is found, nil is returned. For more information on the syntax of pattern, see #parse:with:do:ifError:." ^(self new) parsePattern: pattern; actionBlock: actionBlock; errorBlock: [^nil]; parse: args ] Getopt class >> parse: args with: pattern do: actionBlock ifError: errorBlock [ "Parse the command-line arguments in args according to the syntax specified in pattern. For every command-line option found, the two-argument block actionBlock is evaluated passing the option name and the argument. For file names (or in general, other command-line arguments than options) the block's first argument will be nil. For options without arguments, or with unspecified optional arguments, the block's second argument will be nil. The option name will be passed as a character object for short options, and as a string for long options. If an error is found, the parsing is interrupted, errorBlock is evaluated, and the returned value is answered. Every whitespace-separated part (`word') of pattern specifies a command-line option. If a word ends with a colon, the option will have a mandatory argument. If a word ends with two colons, the option will have an optional argument. Before the colons, multiple option names (either short names like `-l' or long names like `--long') can be specified. Before passing the option to actionBlock, the name will be canonicalized to the last one. Prefixes of long options are accepted as long as they're unique, and they are canonicalized to the full name before passing it to actionBlock. Additionally, the full name of an option is accepted even if it is the prefix of a longer option. Mandatory arguments can appear in the next argument, or in the same argument (separated by an = for arguments to long options). Optional arguments must appear in the same argument." ^(self new) parsePattern: pattern; actionBlock: actionBlock; errorBlock: [^errorBlock value]; parse: args ] fullOptionName: aString [ "Answer the full name of a long option, expanding the prefixes to the complete name. If the option is invalid, errorBlock is evaluated." (prefixes includes: aString) ifFalse: [errorBlock value]. ^longOptions detect: [:k | k startsWith: aString] ] optionKind: aString [ "Answer the kind of option for aString. The result is #noArg, #mandatoryArg, or #optionArg. If the option is invalid, errorBlock is evaluated." | kindOrString | kindOrString := options at: aString ifAbsent: errorBlock. ^kindOrString isSymbol ifTrue: [kindOrString] ifFalse: [options at: kindOrString] ] optionName: aString [ "Answer the canonicalized name of the option for aString. If the option is invalid, errorBlock is evaluated." | kindOrString | kindOrString := options at: aString ifAbsent: errorBlock. ^kindOrString isSymbol ifTrue: [aString] ifFalse: [kindOrString] ] parseRemainingArguments [ "Parse the remaining arguments as non-options, invoking actionBlock repeatedly." [args atEnd] whileFalse: [actionBlock value: nil value: args next] ] parseOption: name kind: kind with: arg [ "Look at kind and arg to see if we have to fetch the mandatory argument from args. Then invoke actionBlock with the given option name." | theArg fullName | theArg := arg. (kind = #mandatoryArg and: [arg isNil]) ifTrue: [args atEnd ifTrue: [errorBlock value]. theArg := args next]. (kind = #noArg and: [theArg notNil]) ifTrue: [errorBlock value]. fullName := self optionName: name. actionBlock value: fullName value: theArg ] parseLongOption: argStream [ "Parse the long option found in argStream. argStream is pointing just after the second minus." | name kind haveArg arg | name := argStream upTo: $=. argStream skip: -1. name := self fullOptionName: name. kind := self optionKind: name. haveArg := argStream nextMatchFor: $=. arg := haveArg ifTrue: [argStream upToEnd] ifFalse: [nil]. self parseOption: name kind: kind with: arg ] parseShortOptions: argStream [ "Parse all the short options found in argStream. argStream is pointing just after the first minus." | ch kind haveArg arg | [argStream atEnd] whileFalse: [ch := argStream next. kind := self optionKind: ch. haveArg := kind ~~ #noArg and: [argStream atEnd not]. arg := haveArg ifTrue: [argStream upToEnd] ifFalse: [nil]. self parseOption: ch kind: kind with: arg] ] parseOneArgument [ "Parse one command-line argument. Actually note that if the argument starts with -, that could be a) many short options for the one argument b) one argument for the options, plus one argument for an option's mandatory argument c) one argument with '--' that is silently eaten, plus an arbitrary number of non-option arguments." | arg argStream | arg := args next. arg = '--' ifTrue: [^self parseRemainingArguments]. arg ~ '\A(-?$|[^-])' ifTrue: [^actionBlock value: nil value: arg]. argStream := arg readStream. (arg at: 2) = $- ifTrue: [argStream next: 2. self parseLongOption: argStream] ifFalse: [argStream next. self parseShortOptions: argStream] ] parse [ "Parse all the arguments in the commandline." [args atEnd] whileFalse: [self parseOneArgument] ] addLongOption: option [ "Add the given long option name. All the prefixes are kept in the prefixes instance variable, including those that are common to more than one option." longOptions add: option. 1 to: option size do: [:length | prefixes add: (option copyFrom: 1 to: length)] ] rejectBadPrefixes [ "Remove from prefixes those that are common to more than one long option -- except if they aren't prefixes, but really the full long option names. Also turn longOptions into a sorted collection, so that when we look for valid long option names, we see --foo before --foobar." prefixes := prefixes asSet select: [:each | (prefixes occurrencesOf: each) == 1 or: [longOptions includes: each]]. "Using this weird sort block would not be absolutely necessary, but it is cool and emphasizes that we care only about seeing shorter options first." longOptions := longOptions asSortedCollection: [:a :b | a size <= b size] ] initialize [ options := Dictionary new. longOptions := Set new. prefixes := Bag new ] checkSynonyms: synonyms [ "Check that the list of synonyms is made of valid options." (synonyms allSatisfy: [:each | each startsWith: '-']) ifFalse: [^self error: 'expected -']. (synonyms anySatisfy: [:each | each size < 2 or: [each = '--']]) ifTrue: [^self error: 'expected option name']. synonyms do: [:each | ((each startsWith: '--') and: [each includes: $=]) ifTrue: [^self error: 'unexpected = inside long option']] ] colonsToKind: colons [ "Make a symbol stored in the options dictionary, based on the number of colons at the end of a pattern." colons = 0 ifTrue: [^#noArg]. colons = 1 ifTrue: [^#mandatoryArg]. colons = 2 ifTrue: [^#optionalArg]. ^self error: 'too many colons, don''t know what to do with them...' ] atSynonym: synonym put: kindOrName [ "Store the given option name into the options dictionary. '-B' uses $B as the key, '--long' uses 'long'. Answer the key." | key | synonym size = 2 ifTrue: [key := synonym at: 2] ifFalse: [key := synonym copyFrom: 3. self addLongOption: key]. (options includes: key) ifTrue: [self error: 'duplicate option']. options at: key put: kindOrName. ^key ] atAllSynonyms: synonyms put: kind [ "Associate the list of synonym option names with the given kind. The last synonym is made the canonical name." "Store the kind (a Symbol) only for the canonical name." | last | last := self atSynonym: synonyms last put: kind. "For the others, store the canonical name (a String)." synonyms from: 1 to: synonyms size - 1 do: [:each | self atSynonym: each put: last] ] parseOption: opt [ "Parse one word of the option description syntax." "Remove the colons" | colons optNames synonyms kind | optNames := opt copyWithout: $:. colons := opt size - optNames size. "Check that they were at the end." opt from: optNames size + 1 to: opt size do: [:ch | ch = $: ifFalse: [^self error: 'invalid pattern, colons are hosed']]. "Now complete the parsing." kind := self colonsToKind: colons. synonyms := optNames subStrings: $|. self checkSynonyms: synonyms. self atAllSynonyms: synonyms put: kind ] parsePattern: pattern [ "Parse the given option description syntax." self initialize. pattern subStrings do: [:opt | self parseOption: opt]. self rejectBadPrefixes ] actionBlock: aBlock [ actionBlock := aBlock ] errorBlock: aBlock [ errorBlock := aBlock ] parse: argsArray [ args := argsArray readStream. self parse ] ] SystemDictionary extend [ arguments: pattern do: actionBlock [ "Parse the command-line arguments according to the syntax specified in pattern. For every command-line option found, the two-argument block actionBlock is evaluated passing the option name and the argument. For file names (or in general, other command-line arguments than options) the block's first argument will be nil. For options without arguments, or with unspecified optional arguments, the block's second argument will be nil. The option name will be passed as a character object for short options, and as a string for long options. If an error is found, nil is returned. For more information on the syntax of pattern, see #arguments:do:ifError:." Getopt parse: self arguments with: pattern do: actionBlock ifError: [^nil] ] arguments: pattern do: actionBlock ifError: errorBlock [ "Parse the command-line arguments according to the syntax specified in pattern. For every command-line option found, the two-argument block actionBlock is evaluated passing the option name and the argument. For file names (or in general, other command-line arguments than options) the block's first argument will be nil. For options without arguments, or with unspecified optional arguments, the block's second argument will be nil. The option name will be passed as a character object for short options, and as a string for long options. If an error is found, the parsing is interrupted, errorBlock is evaluated, and the returned value is answered. Every whitespace-separated part (`word') of pattern specifies a command-line option. If a word ends with a colon, the option will have a mandatory argument. If a word ends with two colons, the option will have an optional argument. Before the colons, multiple option names (either short names like `-l' or long names like `--long') can be specified. Before passing the option to actionBlock, the name will be canonicalized to the last one. Prefixes of long options are accepted as long as they're unique, and they are canonicalized to the full name before passing it to actionBlock. Additionally, the full name of an option is accepted even if it is the prefix of a longer option. Mandatory arguments can appear in the next argument, or in the same argument (separated by an = for arguments to long options). Optional arguments must appear in the same argument." Getopt parse: self arguments with: pattern do: actionBlock ifError: [^errorBlock value] ] ] smalltalk-3.2.5/kernel/AnsiDates.st0000644000175000017500000005037012123404352014132 00000000000000"====================================================================== | | DateTime and Duration Method Definitions | | ======================================================================" "====================================================================== | | Copyright 2000, 2001, 2002, 2008, 2009 Free Software Foundation, Inc. | Written by Paolo Bonzini. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" Date subclass: DateTime [ | seconds offset | ClockPrecision := nil. DateTime class >> initialize [ "Initialize the receiver's class variables" ClockPrecision := Duration seconds: 1 ] DateTime class >> clockPrecision [ ^ClockPrecision ] DateTime class >> fromSeconds: secs offset: ofs [ "Answer a DateTime denoting the given date and time (as seconds since January 1, 1901 midnight). Set the offset field to ofs (a Duration)." ^self fromDays: 0 seconds: secs offset: ofs ] DateTime class >> fromSeconds: secs [ "Answer a DateTime denoting the given date and time (as seconds since January 1, 1901 midnight UTC)." ^self fromDays: 0 seconds: secs offset: Duration zero ] DateTime class >> fromDays: days seconds: secs [ "Answer a DateTime denoting the given date (as days since January 1, 1901) and time (as seconds since UTC midnight)." ^self fromDays: days seconds: secs offset: Duration zero ] DateTime class >> fromDays: days seconds: secs offset: ofs [ "Answer a DateTime denoting the given date (as days since January 1, 1901) and time (as seconds since midnight). Set the offset field to ofs (a Duration)." ^(self fromDays: days + (secs // 86400)) setSeconds: secs \\ 86400; setOffset: ofs ] DateTime class >> date: aDate time: aTime offset: ofs [ "Answer a DateTime denoting the given date and time. Set the offset field to ofs (a Duration)." ^(self fromDays: aDate days) setSeconds: aTime asSeconds; setOffset: ofs ] DateTime class >> date: aDate time: aTime [ "Answer a DateTime denoting the given date and time. Set the offset field to ofs (a Duration)." ^(self fromDays: aDate days) setSeconds: aTime asSeconds; setOffset: Duration zero ] DateTime class >> readFrom: aStream [ "Parse an instance of the receiver from aStream" | date time ofs ch | date := super readFrom: aStream. (aStream peekFor: $T) ifFalse: [aStream skipSeparators]. time := (aStream atEnd or: [aStream peek isDigit]) ifTrue: [Duration readFrom: aStream] ifFalse: [Duration zero]. aStream skipSeparators. ch := aStream peek. (ch = $+ or: [ch = $-]) ifFalse: [^date + time]. ofs := Duration readFrom: aStream. ^(date + time) setOffset: ofs ] DateTime class >> today [ "Answer an instance of the receiver referring to midnight of today in local time." | t seconds secondsAtMidnight biasNow biasAtMidnight | t := self now. seconds := t asSeconds. secondsAtMidnight := seconds - t seconds. biasAtMidnight := Time timezoneBias: secondsAtMidnight. ^DateTime fromSeconds: secondsAtMidnight offset: (Duration fromSeconds: biasAtMidnight) ] DateTime class >> now [ "Answer an instance of the receiver referring to the current date and time." ^self dateAndTimeNow ] DateTime class >> year: y month: m day: d hour: h minute: min second: s [ "Answer a DateTime denoting the d-th day of the given (as a number) month and year, setting the time part to the given hour, minute, and second" ^(super year: y month: m day: d hour: h minute: min second: s) setSeconds: (h * 60 + min) * 60 + s ] DateTime class >> year: y day: d hour: h minute: min second: s [ "Answer a DateTime denoting the d-th day of the given year, and setting the time part to the given hour, minute, and second" ^(super year: y day: d hour: h minute: min second: s) setSeconds: (h * 60 + min) * 60 + s ] DateTime class >> year: y month: m day: d hour: h minute: min second: s offset: ofs [ "Answer a DateTime denoting the d-th day of the given (as a number) month and year. Set the offset field to ofs (a Duration), and the the time part to the given hour, minute, and second" ^(super year: y month: m day: d hour: h minute: min second: s) setSeconds: (h * 60 + min) * 60 + s; setOffset: ofs ] DateTime class >> year: y day: d hour: h minute: min second: s offset: ofs [ "Answer a DateTime denoting the d-th day of the given year. Set the offset field to ofs (a Duration), and the time part to the given hour, minute, and second" ^(super year: y day: d hour: h minute: min second: s) setSeconds: (h * 60 + min) * 60 + s; setOffset: ofs ] < aDateTime [ "Answer whether the receiver indicates a date preceding aDate" self offset = aDateTime offset ifFalse: [^self asUTC < aDateTime asUTC]. ^super < aDateTime or: [super = aDateTime and: [seconds < aDateTime seconds]] ] = aDateTime [ "Answer whether the receiver indicates the same date as aDate" self class == aDateTime class ifFalse: [^false]. self offset = aDateTime offset ifFalse: [^self asUTC = aDateTime asUTC]. ^super = aDateTime and: [seconds = aDateTime seconds] ] hash [ "Answer an hash value for the receievr" ^super hash * 37 + (self seconds - self offset seconds) ] + aDuration [ "Answer a new Date pointing aDuration time past the receiver" | newSecs | newSecs := self seconds + (aDuration asSeconds rem: 86400). ^newSecs > 86400 ifTrue: [DateTime fromDays: self days + aDuration days + 1 seconds: newSecs - 86400 offset: self offset] ifFalse: [DateTime fromDays: self days + aDuration days seconds: newSecs offset: self offset] ] - aDateTimeOrDuration [ "Answer a new Date pointing dayCount before the receiver" | newSecs resultClass | aDateTimeOrDuration class == self class ifTrue: [self offset = aDateTimeOrDuration offset ifFalse: [^self asUTC - aDateTimeOrDuration asUTC]. resultClass := Duration. newSecs := self seconds - aDateTimeOrDuration seconds] ifFalse: [resultClass := DateTime. newSecs := self seconds - (aDateTimeOrDuration asSeconds rem: 86400)]. ^newSecs < 0 ifTrue: [resultClass fromDays: self days - aDateTimeOrDuration days - 1 seconds: newSecs + 86400 offset: self offset] ifFalse: [resultClass fromDays: self days - aDateTimeOrDuration days seconds: newSecs offset: self offset] ] asSeconds [ "Answer the date as the number of seconds from 1/1/1901." ^super asSeconds + seconds ] dayOfWeek [ "Answer the day of week of the receiver. Unlike Dates, DateAndTimes have 1 = Sunday, 7 = Saturday" ^#(2 3 4 5 6 7 1) at: super dayOfWeek ] hour [ "Answer the hour in a 24-hour clock" ^seconds // 3600 ] hour12 [ "Answer the hour in a 12-hour clock" | h | h := self hour \\ 12. ^h = 0 ifTrue: [12] ifFalse: [h] ] hour24 [ "Answer the hour in a 24-hour clock" ^self hour ] meridianAbbreviation [ "Answer either #AM (for anti-meridian) or #PM (for post-meridian)" ^self hour < 12 ifTrue: [#AM] ifFalse: [#PM] ] minute [ "Answer the minute" ^seconds // 60 \\ 60 ] second [ "Answer the month represented by the receiver" ^seconds \\ 60 ] at: anIndex [ "Since in the past timestamps were referred to as Arrays containing a Date and a Time (in this order), this method provides access to DateTime objects like if they were two-element Arrays." anIndex = 1 ifTrue: [^self asDate]. anIndex = 2 ifTrue: [^self asTime]. SystemExceptions.IndexOutOfRange signalOn: self withIndex: anIndex ] asDate [ "Answer a Date referring to the same day as the receiver" ^Date fromDays: self days ] asTime [ "Answer a Time referring to the same time (from midnight) as the receiver" ^Time fromSeconds: seconds ] asLocal [ "Answer the receiver, since DateTime objects store themselves in Local time" | utcSecs offset | utcSecs := self asSeconds - self offset asSeconds. offset := Time timezoneBias: utcSecs. ^DateTime fromSeconds: utcSecs + offset offset: (Duration fromSeconds: offset) ] asUTC [ "Convert the receiver to UTC time, and answer a new DateTime object." | newSecs | self offset asSeconds = 0 ifTrue: [ ^self ]. newSecs := self seconds - self offset asSeconds. ^newSecs < 0 ifTrue: [DateTime fromDays: self days + offset days - 1 seconds: newSecs + 86400 offset: Duration zero] ifFalse: [DateTime fromDays: self days + offset days seconds: newSecs offset: Duration zero] ] offset [ "Answer the receiver's offset from UTC to local time (e.g. +3600 seconds for Central Europe Time, -3600*6 seconds for Eastern Standard Time). The offset is expressed as a Duration" ^offset ] offset: anOffset [ "Answer a copy of the receiver with the offset from UTC to local time changed to anOffset (a Duration)." anOffset = offset ifTrue: [^self]. ^(self copy) setOffset: anOffset; yourself ] timeZoneAbbreviation [ "Answer an abbreviated indication of the receiver's offset, expressed as `shhmm', where `hh' is the number of hours and `mm' is the number of minutes between UTC and local time, and `s' can be `+' for the Eastern hemisphere and `-' for the Western hemisphere." ^String with: (self offset positive ifTrue: [$+] ifFalse: [$-]) with: (self offset hour // 10) digitValue with: (self offset hour \\ 10) digitValue with: (self offset minute // 10) digitValue with: (self offset minute \\ 10) digitValue ] timeZoneName [ "Answer the time zone name for the receiver (currently, it is simply `GMT +xxxx', where `xxxx' is the receiver's #timeZoneAbbreviation)." ^'GMT ' , self timeZoneAbbreviation ] printOn: aStream [ "Print a representation for the receiver on aStream" aStream nextPut: (self year < 0 ifTrue: [$-] ifFalse: [Character space]); next: 3 - (self year abs log: 10) floor put: $0; print: self year abs; nextPut: $-; next: (self month < 10 ifTrue: [1] ifFalse: [0]) put: $0; print: self month; nextPut: $-; next: (self day < 10 ifTrue: [1] ifFalse: [0]) put: $0; print: self day; nextPut: $T; next: (self hour < 10 ifTrue: [1] ifFalse: [0]) put: $0; print: self hour; nextPut: $:; next: (self minute < 10 ifTrue: [1] ifFalse: [0]) put: $0; print: self minute; nextPut: $:; next: (self second < 10 ifTrue: [1] ifFalse: [0]) put: $0; print: self second; nextPut: (self offset negative ifTrue: [$-] ifFalse: [$+]); next: (self offset hours abs < 10 ifTrue: [1] ifFalse: [0]) put: $0; print: self offset hours abs; nextPut: $:; next: (self offset minutes abs < 10 ifTrue: [1] ifFalse: [0]) put: $0; print: self offset minutes abs. self offset seconds = 0 ifTrue: [^self]. aStream nextPut: $:; print: self offset seconds ] storeOn: aStream [ "Store on aStream Smalltalk code compiling to the receiver" aStream nextPut: $(; nextPutAll: self class storeString; nextPutAll: ' year: '; store: self year; nextPutAll: ' month: '; store: self month; nextPutAll: ' day: '; store: self day; nextPutAll: ' hour: '; store: self hour; nextPutAll: ' minute: '; store: self minute; nextPutAll: ' second: '; store: self second. self offset = Duration zero ifFalse: [ aStream nextPutAll: ' offset: '; store: self offset ]. aStream nextPut: $) ] setDay: dayOfMonth monthIndex: monthIndex year: yearInteger [ "Private - Set the receiver to the given date parts" seconds := 0. offset := Duration zero. ^super setDay: dayOfMonth monthIndex: monthIndex year: yearInteger ] setDays: dayCount [ "Private - Compute the date parts from the given dayCount and initialize the receiver" seconds := 0. offset := Duration zero. ^super setDays: dayCount ] seconds [ ^seconds ] setSeconds: secondsCount [ seconds := secondsCount ] setOffset: offsetDuration [ offset := offsetDuration ] ] Time subclass: Duration [ Zero := nil. Duration class >> fromDays: days seconds: secs offset: unused [ "Answer a duration of `d' days and `secs' seconds. The last parameter is unused; this message is available for interoperability with the DateTime class." ^self fromSeconds: days * 86400 + secs ] Duration class >> milliseconds: msec [ "Answer a duration of `msec' milliseconds" ^self fromSeconds: msec / 1000 ] Duration class >> weeks: w [ "Answer a duration of `w' weeks" ^self fromSeconds: w * ##(86400 * 7) ] Duration class >> days: d [ "Answer a duration of `d' days" ^self fromSeconds: d * 86400 ] Duration class >> days: d hours: h minutes: m seconds: s [ "Answer a duration of `d' days and the given number of hours, minutes, and seconds." ^self fromSeconds: ((d * 24 + h) * 60 + m) * 60 + s ] Duration class >> readFrom: aStream [ "Parse an instance of the receiver (hours/minutes/seconds) from aStream" | sign sec hms i ch ws | hms := {0. 0. 0}. sign := (aStream peekFor: $-) ifTrue: [-1] ifFalse: [aStream peekFor: $+. 1]. i := 1. ch := $:. [aStream atEnd not and: [ch isSeparator not and: [ ch ~= $+ and: [ch ~= $- and: [ i > 1 ifTrue: [aStream next]. i <= 4 and: [(ch := aStream peek) isDigit]]]]]] whileTrue: [ ws := WriteStream on: (String new: 10). [ws nextPut: aStream next. aStream atEnd not and: [(ch := aStream peek) isDigit]] whileTrue. i = 4 ifTrue: [ hms := { (hms at: 1) * 24 + (hms at: 2). hms at: 3. ws contents asNumber}] ifFalse: [ hms at: i put: ws contents asNumber]. i := i + 1]. sec := ((hms at: 1) * 3600 + ((hms at: 2) * 60) + (hms at: 3)) * sign. ^self fromSeconds: sec ] Duration class >> initialize [ "Initialize the receiver's instance variables" Zero := self new ] Duration class >> zero [ "Answer a duration of zero seconds." ^Zero ] * factor [ "Answer a Duration that is `factor' times longer than the receiver" ^Duration fromSeconds: self asSeconds * factor ] / factorOrDuration [ "If the parameter is a Duration, answer the ratio between the receiver and factorOrDuration. Else divide the receiver by factorOrDuration (a Number) and answer a new Duration that is correspondingly shorter." ^factorOrDuration isNumber ifFalse: [self asSeconds / factorOrDuration asSeconds] ifTrue: [Duration fromSeconds: self asSeconds / factorOrDuration] ] + aDuration [ "Answer a Duration that is the sum of the receiver and aDuration's lengths." ^Duration fromSeconds: self asSeconds + aDuration asSeconds ] - aDuration [ "Answer a Duration that is the difference of the receiver and aDuration's lengths." ^Duration fromSeconds: self asSeconds - aDuration asSeconds ] isZero [ "Answer whether the receiver correspond to a duration of zero seconds." ^self asSeconds = 0 ] abs [ "Answer a Duration that is as long as the receiver, but always in the future." ^Duration fromSeconds: self asSeconds abs ] days [ "Answer the number of days in the receiver" ^self asSeconds quo: 86400 ] negated [ "Answer a Duration that is as long as the receiver, but with past and future exchanged." ^Duration fromSeconds: self asSeconds negated ] storeOn: aStream [ "Store on aStream Smalltalk code compiling to the receiver" aStream nextPut: $(; nextPutAll: self class storeString; nextPutAll: ' days: '; store: self days; nextPutAll: ' hours: '; store: self hours; nextPutAll: ' minutes: '; store: self minutes; nextPutAll: ' seconds: '; store: self seconds; nextPut: $) ] negative [ "Answer whether the receiver is in the past." ^self asSeconds < 0 ] positive [ "Answer whether the receiver is a zero-second duration or is in the future." ^self asSeconds >= 0 ] printOn: aStream [ "Print a represention of the receiver on aStream." self negative ifTrue: [aStream nextPut: $-; print: self negated. ^self]. aStream print: self days; nextPut: $:; next: (self hours < 10 ifTrue: [1] ifFalse: [0]) put: $0; print: self hours; nextPut: $:; next: (self minutes < 10 ifTrue: [1] ifFalse: [0]) put: $0; print: self minutes; nextPut: $:; next: (self seconds < 10 ifTrue: [1] ifFalse: [0]) put: $0; print: self seconds ] setSeconds: secs [ seconds := secs ] wait [ "Answer a Delay waiting for the amount of time represented by the receiver and start waiting on it." ^(Delay forMilliseconds: self asSeconds * 1000) wait ] ] Eval [ Duration initialize ] smalltalk-3.2.5/kernel/FilePath.st0000644000175000017500000006173212123404352013757 00000000000000"====================================================================== | | FilePath Method Definitions | | ======================================================================" "====================================================================== | | Copyright 2008, 2009 Free Software Foundation, Inc. | Written by Paolo Bonzini. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" Object subclass: FilePath [ FilePath class >> append: fileName to: directory [ "Answer the name of a file named `fileName' which resides in a directory named `directory'." | dir fname | dir := directory. fname := fileName. Directory pathSeparator == $\ ifTrue: [ dir := dir copyReplacing: $/ withObject: $\. fname := fname copyReplacing: $/ withObject: $\ ]. dir isEmpty ifTrue: [^fname]. fname isEmpty ifTrue: [ SystemExceptions.InvalidArgument signalOn: fname reason: 'empty filenames are invalid' ]. Directory pathSeparator == $\ ifFalse: [(fname at: 1) isPathSeparator ifTrue: [^fname]] ifTrue: [(fname at: 1) isPathSeparator ifTrue: [^(dir size >= 2 and: [(dir at: 2) = $:]) ifTrue: ['%1:%2' % {dir first. fname}] ifFalse: [fname]]. (fname size >= 2 and: [(fname at: 2) = $:]) ifTrue: [^fname]]. ^(dir at: dir size) isPathSeparator ifTrue: [dir , fname] ifFalse: [dir , Directory pathSeparatorString , fname] ] FilePath class >> extensionFor: aString [ "Answer the extension of a file named `aString'. Note: the extension includes an initial dot." | index str | aString isEmpty ifTrue: [^'']. str := aString. Directory pathSeparator = $\ ifTrue: [ str := str copyReplacing: $/ withObject: $\ ]. index := str findLast: [:each | each = Directory pathSeparator ifTrue: [^'']. each = $.]. "Special case foo, .foo and /bar/.foo, all of which have no extension" index <= 1 ifTrue: [^'']. (str at: index - 1) = Directory pathSeparator ifTrue: [^'']. ^str copyFrom: index ] FilePath class >> stripExtensionFrom: aString [ "Remove the extension from the name of a file called `aString', and answer the result." | index str | aString isEmpty ifTrue: [^'']. str := aString. Directory pathSeparator = $\ ifTrue: [ str := str copyReplacing: $/ withObject: $\ ]. index := str findLast: [:each | each = Directory pathSeparator ifTrue: [^str]. each = $.]. "Special case foo, .foo and /bar/.foo, all of which have no extension" index <= 1 ifTrue: [^str]. (str at: index - 1) = Directory pathSeparator ifTrue: [^str]. ^str copyFrom: 1 to: index - 1 ] FilePath class >> stripPathFrom: aString [ "Remove the path from the name of a file called `aString', and answer the file name plus extension." | index str | aString isEmpty ifTrue: [^'']. str := aString. Directory pathSeparator = $\ ifTrue: [ str := str copyReplacing: $/ withObject: $\ ]. index := aString findLast: [:each | each = Directory pathSeparator]. ^str copyFrom: index + 1 ] FilePath class >> pathFor: aString ifNone: aBlock [ "Determine the path of the name of a file called `aString', and answer the result. With the exception of the root directory, the final slash is stripped. If there is no path, evaluate aBlock and return the result." | index str | str := aString. Directory pathSeparator = $\ ifTrue: [ str := str copyReplacing: $/ withObject: $\ ]. index := str findLast: [:each | each = Directory pathSeparator]. index = 0 ifTrue: [^aBlock value]. index = 1 ifTrue: [^Directory pathSeparatorString]. ^str copyFrom: 1 to: index - 1 ] FilePath class >> pathFor: aString [ "Determine the path of the name of a file called `aString', and answer the result. With the exception of the root directory, the final slash is stripped." ^self pathFor: aString ifNone: [''] ] FilePath class >> stripFileNameFor: aString [ "Determine the path of the name of a file called `aString', and answer the result as a directory name including the final slash." | index str | aString isEmpty ifTrue: [^'./']. str := aString. Directory pathSeparator = $\ ifTrue: [ str := str copyReplacing: $/ withObject: $\ ]. index := str findLast: [:each | each = Directory pathSeparator]. index = 0 ifTrue: [^'./']. index = 1 ifTrue: [^Directory pathSeparatorString]. ^str copyFrom: 1 to: index ] FilePath class >> isAbsolute: aString [ "Answer whether aString is an absolute ptah." (aString at: 1) isPathSeparator ifTrue: [ ^true ]. Directory pathSeparator == $\ ifFalse: [ ^false ]. "Windows paths starting X:/ are absolute" ^aString size >= 3 and: [ (aString at: 2) = $: and: [(aString at: 3) isPathSeparator]] ] FilePath class >> fullNameFor: aString [ "Answer the full path to a file called `aString', resolving the `.' and `..' directory entries, and answer the result. `/..' is the same as '/'." | path canonical result isWindows | isWindows := Directory pathSeparator == $\. "Windows paths starting X:/ are absolute" path := OrderedCollection new. (self isAbsolute: aString) ifFalse: [path addAll: (Directory workingName subStrings: Directory pathSeparator)]. "A Windows path may contain both / and \ separators. Clean it up to allow easy parsing" canonical := Directory pathSeparator = $/ ifTrue: [aString] ifFalse: [aString copyReplacing: $/ withObject: $\]. (canonical subStrings: Directory pathSeparator) do: [:each | each = '.' ifFalse: [each = '..' ifTrue: [path isEmpty ifFalse: [path removeLast]] ifFalse: [path add: each]]]. path isEmpty ifTrue: [^Directory pathSeparatorString]. result := path inject: '' into: [:old :each | old , Directory pathSeparatorString , each]. "Remove initial / from /C:/" (isWindows and: [result size >= 3 and: [(result at: 1) isPathSeparator and: [(result at: 3) = $: and: [result size = 3 ifTrue: [result := result, '\']. (result at: 4) isPathSeparator]]]]) ifTrue: [^result copyFrom: 2]. "Restore UNC paths." (isWindows and: [(aString at: 1) isPathSeparator and: [ (aString at: 2) isPathSeparator]]) ifTrue: [^'\', result]. ^result ] FilePath class >> pathFrom: srcName to: destName [ "Answer the relative path to destName when the current directory is srcName's directory." ^self computePathFrom: (File fullNameFor: srcName asString) to: (File fullNameFor: destName asString) ] FilePath class >> computePathFrom: srcName to: destName [ | src dest srcCanon destCanon srcUNC destUNC path isUnix | "A Windows path may contain both / and \ separators. Clean it up to allow easy parsing" isUnix := Directory pathSeparator = $/. srcCanon := isUnix ifTrue: [srcName] ifFalse: [srcName copyReplacing: $/ withObject: $\]. destCanon := isUnix ifTrue: [destName] ifFalse: [destName copyReplacing: $/ withObject: $\]. src := srcCanon subStrings: Directory pathSeparator. dest := destCanon subStrings: Directory pathSeparator. src := src asOrderedCollection. dest := dest asOrderedCollection. src removeLast. dest isEmpty ifTrue: [dest addLast: '']. "\abc\def and \\abc\def are different!" srcUNC := isUnix not and: [ srcCanon startsWith: '\\' ]. destUNC := isUnix not and: [ destCanon startsWith: '\\' ]. path := (src isEmpty or: [src first = dest first and: [srcUNC = destUNC]]) ifFalse: [ srcUNC ifTrue: [ src addFirst: '' ]. destUNC ifTrue: [ dest addFirst: '' ]. "Don't prepend a \ if the destination path has a disk letter." (isUnix or: [ (dest first at: 2 ifAbsent: [ nil ]) ~= $: ]) ifTrue: [OrderedCollection with: ''] ifFalse: [OrderedCollection new]] ifTrue: [[src isEmpty or: [dest size = 1 or: [src first ~= dest first]]] whileFalse: [src removeFirst. dest removeFirst]. src collect: [:each | '..']]. path addAllLast: dest. ^path fold: [:a :b | a , Directory pathSeparatorString , b] ] asFile [ "Answer the receiver." ^self ] asString [ "Print a representation of the receiver on aStream." self subclassResponsibility ] displayOn: aStream [ "Print a representation of the receiver on aStream." aStream nextPutAll: self asString withShellEscapes ] withShellEscapes [ "Return the representation of the receiver with shell characters escaped." ^self asString withShellEscapes ] printOn: aStream [ "Print a representation of the receiver on aStream." aStream nextPut: $<; print: self class; space; display: self; nextPut: $> ] mode [ "Answer the permission bits for the file identified by the receiver" self subclassResponsibility ] size [ "Answer the size of the file identified by the receiver" self subclassResponsibility ] mode: anInteger [ "Set the permission bits for the file identified by the receiver to be anInteger." self subclassResponsibility ] owner: ownerString group: groupString [ "Set the owner and group of the file identified by the receiver to be aString." self subclassResponsibility ] group: aString [ "Set the group of the file identified by the receiver to be aString." self owner: nil group: aString ] owner: aString [ "Set the owner of the file identified by the receiver to be aString." self owner: aString group: nil ] lastAccessTime: aDateTime [ "Update the last access time of the file corresponding to the receiver, to be aDateTime." self lastAccessTime: aDateTime lastModifyTime: self lastModifyTime ] lastAccessTime: accessDateTime lastModifyTime: modifyDateTime [ "Update the timestamps of the file corresponding to the receiver, to be accessDateTime and modifyDateTime." self subclassResponsibility ] lastAccessTime [ "Answer the last access time of the file identified by the receiver" self subclassResponsibility ] lastChangeTime [ "Answer the last change time of the file identified by the receiver (the `last change time' has to do with permissions, ownership and the like). On some operating systems, this could actually be the file creation time." self subclassResponsibility ] creationTime [ "Answer the creation time of the file identified by the receiver. On some operating systems, this could actually be the last change time (the `last change time' has to do with permissions, ownership and the like)." self subclassResponsibility ] lastModifyTime: aDateTime [ "Update the last modification timestamp of the file corresponding to the receiver, to be aDateTime." self lastAccessTime: self lastAccessTime lastModifyTime: aDateTime ] lastModifyTime [ "Answer the last modify time of the file identified by the receiver (the `last modify time' has to do with the actual file contents)." self subclassResponsibility ] refresh [ "Refresh the statistics for the receiver" ] exists [ "Answer whether a file with the name contained in the receiver does exist." self subclassResponsibility ] isSymbolicLink [ "Answer whether a file with the name contained in the receiver does exist and identifies a symbolic link." self subclassResponsibility ] isDirectory [ "Answer whether a file with the name contained in the receiver does exist and identifies a directory." self subclassResponsibility ] isFile [ "Answer whether a file with the name contained in the receiver does exist and does not identify a directory." ^self exists and: [ self isDirectory not ] ] isRelative [ "Answer whether the receiver identifies a relative path." ^self isAbsolute not ] isAbsolute [ "Answer whether the receiver identifies an absolute path." self subclassResponsibility ] isReadable [ "Answer whether a file with the name contained in the receiver does exist and is readable" self subclassResponsibility ] isWriteable [ "Answer whether a file with the name contained in the receiver does exist and is writeable" self subclassResponsibility ] isExecutable [ "Answer whether a file with the name contained in the receiver does exist and is executable" self subclassResponsibility ] isAccessible [ "Answer whether a directory with the name contained in the receiver does exist and can be accessed" self subclassResponsibility ] isFileSystemPath [ "Answer whether the receiver corresponds to a real filesystem path." ^false ] extension [ "Answer the extension of the receiver" ^File extensionFor: self name ] stripExtension [ "Answer the path (if any) and file name of the receiver" ^File stripExtensionFrom: self name ] stripPath [ "Answer the file name and extension (if any) of the receiver" ^File stripPathFrom: self name ] directory [ "Answer the Directory object for the receiver's path" ^self parent ] parent [ "Answer the Directory object for the receiver's path" ^self class path: (File pathFor: self name ifNone: [ '.' ]) ] fullName [ "Answer a String with the full path to the receiver (same as #name; it is useless to override this method)." ^self name ] name [ "Answer String with the full path to the receiver (same as #fullName)." self subclassResponsibility ] path [ "Answer the path (if any) of the receiver" ^File pathFor: self name ] stripFileName [ "Answer the path of the receiver, always including a directory name (possibly `.') and the final directory separator" ^File stripFileNameFor: self name ] full [ "Answer the full name of the receiver, resolving the `.' and `..' directory entries, and answer the result. Answer nil if the name is invalid (such as '/usr/../../badname')" self subclassResponsibility ] contents [ "Open a read-only FileStream on the receiver, read its contents, close the stream and answer the contents" | stream contents | stream := self readStream. contents := stream contents. stream close. ^contents ] touch [ "Update the timestamp of the file corresponding to the receiver." | now | self exists ifTrue: [now := DateTime now. self lastAccessTime: now lastModifyTime: now] ifFalse: [(self open: FileStream append) close] ] open: mode [ "Open the receiver in the given mode (as answered by FileStream's class constant methods)" ^self open: mode ifFail: [SystemExceptions.FileError signal: 'could not open ' , self name] ] openDescriptor: mode [ "Open the receiver in the given mode (as answered by FileStream's class constant methods)" ^self openDescriptor: mode ifFail: [SystemExceptions.FileError signal: 'could not open ' , self name] ] open: mode ifFail: aBlock [ "Open the receiver in the given mode (as answered by FileStream's class constant methods). Upon failure, evaluate aBlock." ^self open: FileStream mode: mode ifFail: aBlock ] openDescriptor: mode ifFail: aBlock [ "Open the receiver in the given mode (as answered by FileStream's class constant methods). Upon failure, evaluate aBlock." ^self open: FileDescriptor mode: mode ifFail: aBlock ] open: class mode: mode ifFail: aBlock [ "Open the receiver in the given mode (as answered by FileStream's class constant methods)" self subclassResponsibility ] withReadStreamDo: aBlock [ "Answer the result of invoking aBlock with a reading stream open on me, closing it when the dynamic extent of aBlock ends." | stream | stream := self readStream. ^[aBlock value: stream] ensure: [stream close] ] fileIn [ "File in the receiver" self withReadStreamDo: [ :fs | fs fileIn ] ] readStream [ "Open a read-only FileStream on the receiver" ^self open: FileStream read ] withWriteStreamDo: aBlock [ "Answer the result of invoking aBlock with a writing stream open on me, closing it when the dynamic extent of aBlock ends." | stream | stream := self writeStream. ^[aBlock value: stream] ensure: [stream close] ] writeStream [ "Open a write-only FileStream on the receiver" ^self open: FileStream write ] symlinkAs: destName [ "Create destName as a symbolic link of the receiver. The appropriate relative path is computed automatically." self subclassResponsibility ] pathFrom: dirName [ "Compute the relative path from the directory dirName to the receiver" self subclassResponsibility ] symlinkFrom: srcName [ "Create the receiver as a symbolic link from srcName (relative to the path of the receiver)." self subclassResponsibility ] remove [ "Remove the file identified by the receiver" self subclassResponsibility ] renameTo: newName [ "Rename the file identified by the receiver to newName" self subclassResponsibility ] pathTo: destName [ "Compute the relative path from the receiver to destName." self subclassResponsibility ] / aName [ "Answer a File or Directory object as appropriate for a file named 'aName' in the directory represented by the receiver." ^self at: aName ] at: aName [ "Answer a File or Directory object as appropriate for a file named 'aName' in the directory represented by the receiver." self subclassResponsibility ] includes: aName [ "Answer whether a file named `aName' exists in the directory represented by the receiver." ^(self at: aName) exists ] all [ "Return a decorator of the receiver that will provide recursive descent into directories for iteration methods. Furthermore, iteration on the returned wrapper will not include '.' or '..' directory entries, and will include the receiver (directly, not via '.')." ^Kernel.RecursiveFileWrapper on: self ] allFilesMatching: aPattern do: aBlock [ "Evaluate aBlock on the File objects that match aPattern (according to String>>#match:) in the directory named by the receiver. Recursively descend into directories." self all filesMatching: aPattern do: aBlock ] createDirectory [ "Create the receiver as a directory, together with all its parents." self subclassResponsibility ] createDirectories [ "Create the receiver as a directory, together with all its parents." | parent | parent := self parent. parent exists ifTrue: [ self exists ifTrue: [ self isDirectory ifFalse: [ self createDirectory ]. ^self ] ] ifFalse: [ parent createDirectories ]. self createDirectory ] files [ "Answer an Array with File objects for the contents of the directory represented by the receiver." ^self reject: [ :each | each isDirectory ] ] directories [ "Answer an Array with Directory objects for the subdirectories of the directory represented by the receiver." ^self select: [ :each | each isDirectory ] ] entries [ "Answer an Array with File or Directory objects for the contents of the directory represented by the receiver." | ws | ws := WriteStream on: (Array new: 50). self do: [:each | ws nextPut: each]. ^ws contents ] entryNames [ "Answer an Array with the names of the files in the directory represented by the receiver." | ws | ws := WriteStream on: (Array new: 50). self namesDo: [:each | ws nextPut: each]. ^ws contents ] do: aBlock [ "Evaluate aBlock once for each file in the directory represented by the receiver, passing a FilePath object (or a subclass) to it. It depends on the subclass whether iteration will include the '.' and '..' directory entries." self namesDo: [ :name | aBlock value: (self at: name) ] ] namesDo: aBlock [ "Evaluate aBlock once for each file in the directory represented by the receiver, passing its name. It depends on the subclass whether iteration will include the '.' and '..' directory entries." self subclassResponsibility ] filesMatching: aPattern [ "Evaluate aBlock once for each file in the directory represented by the receiver, passing a File or Directory object to aBlock. Returns the *names* of the files for which aBlock returns true." | ws | ws := WriteStream on: (Array new: 50). self namesDo: [ :name | (aPattern match: name) ifTrue: [ ws nextPut: (self at: name) ] ]. ^ws contents ] reject: aBlock [ "Evaluate aBlock once for each file in the directory represented by the receiver, passing a File or Directory object to aBlock. Returns the *names* of the files for which aBlock returns true." | ws | ws := WriteStream on: (Array new: 50). self do: [ :each | (aBlock value: each) ifFalse: [ ws nextPut: each ] ]. ^ws contents ] select: aBlock [ "Evaluate aBlock once for each file in the directory represented by the receiver, passing a File or Directory object to aBlock. Returns the *names* of the files for which aBlock returns true." | ws | ws := WriteStream on: (Array new: 50). self do: [ :each | (aBlock value: each) ifTrue: [ ws nextPut: each ] ]. ^ws contents ] filesMatching: aPattern do: block [ "Evaluate block on the File objects that match aPattern (according to String>>#match:) in the directory named by the receiver." self namesDo: [:name | (aPattern match: name) ifTrue: [block value: (self at: name)]] ] nameAt: aName [ "Answer a FilePath for a file named `aName' residing in the directory represented by the receiver." ^File append: aName to: self asString ] namesMatching: aPattern do: block [ "Evaluate block on the file names that match aPattern (according to String>>#match:) in the directory named by the receiver." self namesDo: [:name | (aPattern match: name) ifTrue: [block value: name]] ] ] smalltalk-3.2.5/kernel/Transcript.st0000644000175000017500000001301612123404352014404 00000000000000"====================================================================== | | Smalltalk Transcript object (TextCollector class) | | ======================================================================" "====================================================================== | | Copyright 1988,92,94,95,99,2000,2001,2008,2009 | Free Software Foundation, Inc. | Written by Paolo Bonzini. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" Stream subclass: TextCollector [ | semaphore receiver selector | TextCollector class >> new [ self shouldNotImplement ] TextCollector class >> message: receiverToSelectorAssociation [ "Answer a new instance of the receiver, that uses the message identified by anAssociation to perform write operations. anAssociation's key is the receiver, while its value is the selector." ^(self basicNew) initialize; message: receiverToSelectorAssociation ] message [ "Answer an association representing the message to be sent to perform write operations. The key is the receiver, the value is the selector" ^receiver -> selector ] message: receiverToSelectorAssociation [ "Set the message to be sent to perform write operations to the one represented by anAssociation. anAssociation's key is the receiver, while its value is the selector" receiver := receiverToSelectorAssociation key. selector := receiverToSelectorAssociation value ] cr [ "Emit a new-line (carriage return) to the Transcript" self nl ] endEntry [ "Emit two new-lines. This method is present for compatibility with VisualWorks." self nl; nl ] nextPut: aCharacter [ "Emit aCharacter to the Transcript" self nextPutAll: (String with: aCharacter) ] next: anInteger put: anObject [ "Write anInteger copies of anObject to the Transcript" self nextPutAll: (String new: anInteger withAll: anObject) ] critical: aBlock [ "Evaluate aBlock while holding the Transcript lock" semaphore critical: aBlock ] next: n putAll: aString startingAt: pos [ "Write aString to the Transcript" semaphore critical: [self primNextPutAll: (aString copyFrom: pos to: pos + n - 1). Processor idle] ] show: aString [ "Write aString to the Transcript" semaphore critical: [self primNextPutAll: aString. Processor idle] ] showCr: aString [ "Write aString to the Transcript, followed by a new-line character" semaphore critical: [self primNextPutAll: aString. self primNextPutAll: Character nl asString. Processor idle] ] showOnNewLine: aString [ "Write aString to the Transcript, preceded by a new-line character" semaphore critical: [self primNextPutAll: Character nl asString. self primNextPutAll: aString. Processor idle] ] print: anObject [ "Print anObject's representation to the Transcript" semaphore critical: [self primNextPutAll: anObject printString. Processor idle] ] printOn: aStream [ "Print a representation of the receiver onto aStream" self == Transcript ifTrue: [aStream nextPutAll: 'Transcript'] ifFalse: [super printOn: aStream] ] store: anObject [ "Print Smalltalk code which evaluates to anObject on the Transcript" semaphore critical: [self primNextPutAll: anObject storeString. Processor idle] ] storeOn: aStream [ "Print Smalltalk code which evaluates to the receiver onto aStream" self == Transcript ifTrue: [aStream nextPutAll: 'Transcript'] ifFalse: [super storeOn: aStream] ] primNextPutAll: aString [ "Private - Forward the writing request to the actual object" [receiver perform: selector with: aString] on: Error do: [:ex | stderr nextPutAll: aString; flush. ex return] ] initialize [ "Private - Initialize the receiver's instance variables" semaphore := RecursionLock new ] ] Eval [ Smalltalk at: #Transcript put: (TextCollector message: stdout -> #nextPutAllFlush:) ] smalltalk-3.2.5/kernel/RecursionLock.st0000644000175000017500000000565112123404352015043 00000000000000"====================================================================== | | RecursionLock Method Definitions | | ======================================================================" "====================================================================== | | Copyright 2002 Free Software Foundation, Inc. | Written by Paolo Bonzini. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" Object subclass: RecursionLock [ | owner sema | RecursionLock class >> new [ "Answer a new semaphore" ^self basicNew initialize ] printOn: aStream [ "Print a human-readable represention of the receiver on aStream." aStream nextPutAll: self class name; nextPut: $(; print: self name; nextPut: $:; nextPutAll: (sema signals = 1 ifTrue: ['free'] ifFalse: ['held']); nextPut: $) ] isOwnerProcess [ "Answer whether the receiver is the owner of the lock." ^owner == Processor activeProcess ] name [ "Answer a user-defined name for the lock." ^sema name ] name: aString [ "Set to aString the user-defined name for the lock." sema name: aString ] waitingProcesses [ "Answer the set of processes that are waiting on the semaphore." ^sema asArray ] wouldBlock [ "Answer whether sending #wait to the receiver would suspend the active process." ^sema wouldBlock and: [owner ~~ Processor activeProcess] ] critical: aBlock [ "Wait for the receiver to be free, execute aBlock and signal the receiver again. Return the result of evaluating aBlock." self isOwnerProcess ifTrue: [^aBlock value]. "Look out for race conditions!" sema critical: [ [owner := Processor activeProcess. aBlock value] ensure: [owner := nil]]. ] initialize [ sema := Semaphore forMutualExclusion ] ] smalltalk-3.2.5/kernel/Point.st0000644000175000017500000001712612123404352013352 00000000000000"===================================================================== | | Point Class Definitions | | =====================================================================" "====================================================================== | | Copyright 1992,94,95,99,2000,2001,2002,2006 | Free Software Foundation, Inc. | Written by Doug McCallum. | Additions by Steve Byrne and Paolo Bonzini | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" Object subclass: Point [ | x y | Point class >> new [ "Create a new point with both coordinates set to 0" ^self basicNew x: 0 y: 0 ] Point class >> x: xInteger y: yInteger [ "Create a new point with the given coordinates" ^self basicNew x: xInteger y: yInteger ] printOn: aStream [ "Print a representation for the receiver on aStream" aStream print: x; nextPut: $@; print: y ] storeOn: aStream [ "Print Smalltalk code compiling to the receiver on aStream" aStream nextPut: $(; store: x; nextPutAll: ' @ '; store: y; nextPut: $) ] x [ "Answer the x coordinate" ^x ] y [ "Answer the y coordinate" ^y ] x: aNumber [ "Set the x coordinate to aNumber" x := aNumber ] y: aNumber [ "Set the y coordinate to aNumber" y := aNumber ] x: anXNumber y: aYNumber [ "Set the x and y coordinate to anXNumber and aYNumber, respectively" x := anXNumber. y := aYNumber ] asPoint [ ^self "But I already AM a point!" ] hash [ "Answer an hash value for the receiver" ^self x hash bitXor: self y hash ] + delta [ "Sum the receiver and delta, which can be a Number or a Point" | deltaPoint | deltaPoint := delta asPoint. ^Point x: self x + deltaPoint x y: self y + deltaPoint y ] - delta [ "Subtract delta, which can be a Number or a Point, from the receiver" | deltaPoint | deltaPoint := delta asPoint. ^Point x: self x - deltaPoint x y: self y - deltaPoint y ] * scale [ "Multiply the receiver by scale, which can be a Number or a Point" | scalePoint | scalePoint := scale asPoint. ^Point x: self x * scalePoint x y: self y * scalePoint y ] / scale [ "Divide the receiver by scale, which can be a Number or a Point, with no loss of precision" | scalePoint | scalePoint := scale asPoint. ^Point x: self x / scalePoint x y: self y / scalePoint y ] // scale [ "Divide the receiver by scale, which can be a Number or a Point, with truncation towards -infinity" | scalePoint | scalePoint := scale asPoint. ^Point x: self x // scalePoint x y: self y // scalePoint y ] abs [ "Answer a new point whose coordinates are the absolute values of the receiver's" ^Point x: self x abs y: self y abs ] rounded [ "Answer a new point whose coordinates are rounded to the nearest integer" ^Point x: self x rounded y: self y rounded ] truncateTo: grid [ "Answer a new point whose coordinates are rounded towards -infinity, to a multiple of grid (which must be a Number)" ^Point x: (self x truncateTo: grid) y: (self y truncateTo: grid) ] = aPoint [ "Answer whether the receiver is equal to aPoint" ^aPoint class == Point and: [self x = aPoint x & (self y = aPoint y)] ] < aPoint [ "Answer whether the receiver is higher and to the left of aPoint" ^self x < aPoint x and: [self y < aPoint y] ] > aPoint [ "Answer whether the receiver is lower and to the right of aPoint" ^self x > aPoint x and: [self y > aPoint y] ] <= aPoint [ "Answer whether aPoint is equal to the receiver, or the receiver is higher and to the left of aPoint" ^self x <= aPoint x and: [self y <= aPoint y] ] >= aPoint [ "Answer whether aPoint is equal to the receiver, or the receiver is lower and to the right of aPoint" ^self x >= aPoint x and: [self y >= aPoint y] ] max: aPoint [ "Answer self if it is lower and to the right of aPoint, aPoint otherwise" ^(self x max: aPoint x) @ (self y max: aPoint y) ] min: aPoint [ "Answer self if it is higher and to the left of aPoint, aPoint otherwise" ^(self x min: aPoint x) @ (self y min: aPoint y) ] arcTan [ "Answer the angle (measured counterclockwise) between the receiver and a ray starting in (0, 0) and moving towards (1, 0) - i.e. 3 o'clock" ^self y arcTan: self x ] dist: aPoint [ "Answer the distance between the receiver and aPoint" | a b | a := self x - aPoint x. b := self y - aPoint y. ^(a squared + b squared) sqrt ] dotProduct: aPoint [ "Answer the dot product between the receiver and aPoint" ^self x * aPoint x + (self y * aPoint y) ] grid: aPoint [ "Answer a new point whose coordinates are rounded towards the nearest multiple of aPoint" ^Point x: (self x roundTo: aPoint x) y: (self y roundTo: aPoint y) ] normal [ "Rotate the Point 90degrees clockwise and get the unit vector" | len | len := (self x squared + self y squared) sqrt. ^Point x: self y negated / len y: x / len ] transpose [ "Answer a new point whose coordinates are the receiver's coordinates exchanged (x becomes y, y becomes x)" ^Point x: y y: x ] truncatedGrid: aPoint [ "Answer a new point whose coordinates are rounded towards -infinity, to a multiple of grid (which must be a Point)" ^Point x: (self x truncateTo: aPoint x) y: (self y truncateTo: aPoint y) ] ] Number extend [ @ y [ "Answer a new point whose x is the receiver and whose y is y" ^Point x: self y: y ] asPoint [ "Answer a new point, self @ self" ^Point x: self y: self ] ] smalltalk-3.2.5/kernel/Collection.st0000644000175000017500000004106312130343734014355 00000000000000"====================================================================== | | Collection Method Definitions | | ======================================================================" "====================================================================== | | Copyright 1988,92,94,95,99,2000,2001,2002,2003,2006,2007,2008,2009 | Free Software Foundation, Inc. | Written by Steve Byrne. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" Iterable subclass: Collection [ Collection class >> from: anArray [ "Convert anArray to an instance of the receiver. anArray is structured such that the instance can be conveniently and fully specified using brace-syntax, possibly by imposing some additional structure on anArray." ^self withAll: anArray ] Collection class >> withAll: aCollection [ "Answer a collection whose elements are all those in aCollection" ^(self new) addAll: aCollection; yourself ] Collection class >> with: anObject [ "Answer a collection whose only element is anObject" ^(self new) add: anObject; yourself ] Collection class >> with: firstObject with: secondObject [ "Answer a collection whose only elements are the parameters in the order they were passed" ^(self new) add: firstObject; add: secondObject; yourself ] Collection class >> with: firstObject with: secondObject with: thirdObject [ "Answer a collection whose only elements are the parameters in the order they were passed" ^(self new) add: firstObject; add: secondObject; add: thirdObject; yourself ] Collection class >> with: firstObject with: secondObject with: thirdObject with: fourthObject [ "Answer a collection whose only elements are the parameters in the order they were passed" ^(self new) add: firstObject; add: secondObject; add: thirdObject; add: fourthObject; yourself ] Collection class >> with: firstObject with: secondObject with: thirdObject with: fourthObject with: fifthObject [ "Answer a collection whose only elements are the parameters in the order they were passed" ^(self new) add: firstObject; add: secondObject; add: thirdObject; add: fourthObject; add: fifthObject; yourself ] Collection class >> join: aCollection [ "Answer a collection formed by treating each element in aCollection as a `withAll:' argument collection to be added to a new instance." | newInst | newInst := self new: (aCollection inject: 0 into: [:size :each | size + each size]). aCollection do: [:each | newInst addAll: each]. ^newInst ] Collection class >> isUnicode [ "Answer true; the receiver is able to store arbitrary Unicode characters." ^true ] , anIterable [ "Append anIterable at the end of a copy of the receiver (using #add:), and answer a new collection" ^(self copyEmpty: self size + anIterable size) addAll: self; addAll: anIterable; yourself ] add: newObject [ "Add newObject to the receiver, answer it" self subclassResponsibility ] addAll: aCollection [ "Adds all the elements of 'aCollection' to the receiver, answer aCollection" aCollection do: [:element | self add: element]. ^aCollection ] empty [ "Remove everything from the receiver." ^self become: self copyEmpty ] removeAllSuchThat: aBlock [ "Remove from the receiver all objects for which aBlock returns true." self removeAll: (self select: aBlock) ifAbsent: [] ] remove: oldObject ifAbsent: anExceptionBlock [ "Remove oldObject from the receiver. If absent, evaluate anExceptionBlock and answer the result, else answer oldObject." self subclassResponsibility ] remove: oldObject [ "Remove oldObject from the receiver. If absent, fail, else answer oldObject." ^self remove: oldObject ifAbsent: [SystemExceptions.NotFound signalOn: oldObject what: 'object'] ] removeAll: aCollection [ "Remove each object in aCollection, answer aCollection, fail if some of them is absent. Warning: this could leave the collection in a semi-updated state." aCollection do: [:element | self remove: element]. ^aCollection ] removeAll: aCollection ifAbsent: aBlock [ "Remove each object in aCollection, answer aCollection; if some element is absent, pass it to aBlock." aCollection do: [:element | self remove: element ifAbsent: [aBlock cull: element]]. ^aCollection ] isSequenceable [ "Answer whether the receiver can be accessed by a numeric index with #at:/#at:put:." ^false ] capacity [ "Answer how many elements the receiver can hold before having to grow." ^self basicSize ] includesAllOf: aCollection [ "Answer whether we include all of the objects in aCollection" ^self allSatisfy: [:element | aCollection includes: element ] ] includesAnyOf: aCollection [ "Answer whether we include any of the objects in aCollection" ^self anySatisfy: [:element | aCollection includes: element ] ] includes: anObject [ "Answer whether we include anObject" self do: [:element | anObject = element ifTrue: [^true]]. ^false ] identityIncludes: anObject [ "Answer whether we include the anObject object" self do: [:element | anObject == element ifTrue: [^true]]. ^false ] isEmpty [ "Answer whether we are (still) empty" ^self size == 0 ] notEmpty [ "Answer whether we include at least one object" ^self size > 0 ] occurrencesOf: anObject [ "Answer how many occurrences of anObject we include" | count | count := 0. self do: [:element | anObject == element ifTrue: [count := count + 1]]. ^count ] size [ "Answer how many objects we include" | count | count := 0. self do: [:element | count := count + 1]. ^count ] anyOne [ "Answer an unspecified element of the collection." self do: [:each | ^each]. ^SystemExceptions.EmptyCollection signalOn: self ] join [ "Answer a new collection like my first element, with all the elements (in order) of all my elements, which should be collections. I use my first element instead of myself as a prototype because my elements are more likely to share the desired properties than I am, such as in: #('hello, ' 'world') join => 'hello, world'" ^self isEmpty ifTrue: [#()] ifFalse: [self anyOne species join: self] ] beConsistent [ "This method is private, but it is quite interesting so it is documented. It ensures that a collection is in a consistent state before attempting to iterate on it; its presence reduces the number of overrides needed by collections who try to amortize their execution times. The default implementation does nothing, so it is optimized out by the virtual machine and so it loses very little on the performance side. Note that descendants of Collection have to call it explicitly since #do: is abstract in Collection." ] readStream [ "Answer a stream that gives elements of the receiver" ^Generator on: self do: [ :gen :each | gen yield: each ] ] select: aBlock [ "Answer a new instance of a Collection containing all the elements in the receiver which, when passed to aBlock, answer true" | newCollection | newCollection := self copyEmpty. self do: [:element | (aBlock value: element) ifTrue: [newCollection add: element]]. ^newCollection ] reject: aBlock [ "Answer a new instance of a Collection containing all the elements in the receiver which, when passed to aBlock, don't answer true" | newCollection | newCollection := self copyEmpty. self do: [:element | (aBlock value: element) ifFalse: [newCollection add: element]]. ^newCollection ] collect: aBlock [ "Answer a new instance of a Collection containing all the results of evaluating aBlock passing each of the receiver's elements" | newCollection | newCollection := self copyEmptyForCollect. self do: [:element | newCollection add: (aBlock value: element)]. ^newCollection ] gather: aBlock [ "Answer a new instance of a Collection containing all the results of evaluating aBlock, joined together. aBlock should return collections. The result is the same kind as the first collection, returned by aBlock (as for #join)." ^(self collect: aBlock) join ] asArray [ "Answer an Array containing all the elements in the receiver" ^(Array new: self size) replaceFrom: 1 to: self size with: self; yourself ] asByteArray [ "Answer a ByteArray containing all the elements in the receiver" ^(ByteArray new: self size) replaceFrom: 1 to: self size with: self; yourself ] asBag [ "Answer a Bag containing all the elements in the receiver" ^(Bag new: self size) addAll: self; yourself ] asSet [ "Answer a Set containing all the elements in the receiver with no duplicates" ^(Set new: self size * 2) addAll: self; yourself ] asString [ "Answer a String containing all the elements in the receiver" ^(String new: self size) replaceFrom: 1 to: self size with: self; yourself ] asUnicodeString [ "Answer a UnicodeString containing all the elements in the receiver" ^(UnicodeString new: self size) replaceFrom: 1 to: self size with: self; yourself ] asOrderedCollection [ "Answer an OrderedCollection containing all the elements in the receiver" ^(OrderedCollection new: self size * 2) addAll: self; yourself ] sorted [ "Return a sequenceable collection with the contents of the receiver sorted according to the default sort block, which uses #<= to compare items." ^(Array new: self size) replaceFrom: 1 to: self size with: self asSortedCollection startingAt: 1 ] sorted: sortBlock [ "Return a sequenceable collection with the contents of the receiver sorted according to the given sort block, which accepts pair of items and returns true if the first item is less than the second one." ^(Array new: self size) replaceFrom: 1 to: self size with: (self asSortedCollection: sortBlock) startingAt: 1 ] asSortedCollection [ "Answer a SortedCollection containing all the elements in the receiver with the default sort block - [ :a :b | a <= b ]" ^(SortedCollection new: self size + 10) addAll: self; yourself ] asSortedCollection: aBlock [ "Answer a SortedCollection whose elements are the elements of the receiver, sorted according to the sort block aBlock" ^(self asSortedCollection) sortBlock: aBlock; yourself ] copyReplacing: targetObject withObject: newObject [ "Copy replacing each object which is = to targetObject with newObject" ^self collect: [:each | each = targetObject ifFalse: [each] ifTrue: [newObject]] ] copyWith: newElement [ "Answer a copy of the receiver to which newElement is added" ^(self copy) add: newElement; yourself ] copyWithout: oldElement [ "Answer a copy of the receiver to which all occurrences of oldElement are removed" ^self reject: [:element | element = oldElement] ] copyEmpty [ "Answer an empty copy of the receiver" ^self copyEmpty: self basicSize ] copyEmpty: newSize [ "Answer an empty copy of the receiver whose size is newSize" ^self species new: newSize ] copyEmptyForCollect: size [ "Answer an empty copy of the receiver, with the class answered by the collect: method." ^self copyEmpty: size ] copyEmptyForCollect [ "Answer an empty copy of the receiver, with the class answered by the collect: method." ^self copyEmpty ] rehash [ "Private - Do nothing, present for consistency in protocol" ] examineOn: aStream [ "Print all the instance variables and objects in the receiver on aStream" | instVars output object | self beConsistent. aStream nextPutAll: 'An instance of '; print: self class; nl. instVars := self class allInstVarNames. 1 to: instVars size do: [:i | object := self instVarAt: i. output := [object printString] on: Error do: [:ex | ex return: '%1 %2' % {object class article. object class name asString}]. aStream nextPutAll: ' '; nextPutAll: (instVars at: i); nextPutAll: ': '; nextPutAll: output; nl]. aStream nextPutAll: ' contents: ['; nl. self do: [:obj | | output | output := [obj printString] on: Error do: [:ex | ex return: '%1 %2' % {obj class article. obj class name asString}]. aStream nextPutAll: ' '; nextPutAll: output; nl]. aStream nextPutAll: ' ]'; nl ] printOn: aStream [ "Print a representation of the receiver on aStream" aStream nextPutAll: self class storeString. aStream nextPutAll: ' ('. self do: [:element | element printOn: aStream. aStream space]. aStream nextPut: $) ] displayLines [ "Print each element of the receiver to a line on standard output." self do: [:each | Transcript display: each; nl] ] storeOn: aStream [ "Store Smalltalk code compiling to the receiver on aStream" | noElements | aStream nextPut: $(. aStream nextPutAll: self class storeString. aStream nextPutAll: ' new'. noElements := true. self do: [:element | aStream nextPutAll: ' add: '. element storeOn: aStream. aStream nextPut: $;. noElements := false]. noElements ifFalse: [aStream nextPutAll: ' yourself']. aStream nextPut: $) ] mourn: anObject [ "Private - anObject has been found to have a weak key, remove it and possibly finalize the key." self remove: anObject ifAbsent: []. self == Object finalizableObjects ifTrue: [anObject key finalize] ] ] smalltalk-3.2.5/kernel/Process.st0000644000175000017500000003470712130343734013707 00000000000000"====================================================================== | | Process Method Definitions | | ======================================================================" "====================================================================== | | Copyright 1988,92,94,95,99,2000,2001,2002,2003,2007,2008,2009 | Free Software Foundation, Inc. | Written by Steve Byrne. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" Link subclass: Process [ | suspendedContext priority myList name environment interruptLock interrupts | Process class >> on: aBlockClosure at: aPriority suspend: aBoolean [ "Private - Create a process running aBlockClosure at the given priority. The process is suspended immediately after initialization if aBoolean is true" ^self new onBlock: aBlockClosure at: aPriority suspend: aBoolean ] debugger [ "Return the object in charge of debugging the receiver. This always returns nil unless the DebugTools package is loaded." ^self context debugger ] context [ "Return the execution context of the receiver." ^self == Processor activeProcess ifTrue: [thisContext parentContext] ifFalse: [suspendedContext] ] makeUntrusted: aBoolean [ "Set whether the receiver is trusted or not." | ctx | ctx := self context. [ctx isNil] whileFalse: [ctx makeUntrusted: aBoolean. ctx := ctx parentContext] ] lowerPriority [ "Lower a bit the priority of the receiver. A #lowerPriority will cancel a previous #raisePriority, and vice versa." self priority: self priority - 1 ] raisePriority [ "Raise a bit the priority of the receiver. A #lowerPriority will cancel a previous #raisePriority, and vice versa." self priority: self priority + 1 ] singleStep [ "Execute a limited amount of code (usually a bytecode, or up to the next backward jump, or up to the next message send) of the receiver, which must in a ready-to-run state (neither executing nor terminating nor suspended), then restart running the current process. The current process should have higher priority than the receiver. For better performance, use the underlying primitive, Process>>#singleStepWaitingOn:." ^self singleStepWaitingOn: Semaphore new ] suspend [ "Do nothing if we're already suspended. Note that the blue book made suspend a primitive - but the real primitive is yielding control to another process. Suspending is nothing more than taking ourselves out of every scheduling list and THEN yielding control to another process" ] finalize [ "Terminate processes that are GCed while waiting on a dead semaphore." ^self terminate ] terminate [ "Terminate the receiver after having evaluated all the #ensure: and #ifCurtailed: blocks that are active in it. This is done by signalling a ProcessBeingTerminated notification." | semaphore | [self isTerminated ifTrue: [^self]. Processor activeProcess == self ifFalse: [semaphore := self isWaiting ifTrue: [myList]. self queueInterrupt: [SystemExceptions.ProcessBeingTerminated new semaphore: semaphore; signal]. ^self]] valueWithoutPreemption. SystemExceptions.ProcessBeingTerminated signal ] update: aSymbol [ "Private - Terminate the process when ObjectMemory class>>#quit: is sent. This is invoked only after #terminateOnQuit." aSymbol == #aboutToQuit ifTrue: [ self terminate ] ] terminateOnQuit [ "Mark the receiver so that it is terminated when ObjectMemory class>>#quit: is sent." ObjectMemory addDependent: self ] primTerminate [ "Terminate the receiver - This is nothing more than prohibiting to resume the process, then suspending it." self removeToBeFinalized. suspendedContext := nil. self suspend ] printOn: aStream [ "Print a representation of the receiver on aStream" aStream print: self class; nextPut: $(; print: name; nextPutAll: ' at '; nextPutAll: (Processor priorityName: self priority); nextPut: $,. "The order here is important!" self isActive ifTrue: [aStream nextPutAll: ' active)'. ^self]. self isTerminated ifTrue: [aStream nextPutAll: ' terminated)'. ^self]. self isWaiting ifTrue: [aStream nextPutAll: ' waiting on a semaphore)'. ^self]. self isSuspended ifTrue: [aStream nextPutAll: ' suspended)'. ^self]. self isReady ifTrue: [aStream nextPutAll: ' ready to run)'. ^self]. aStream nextPutAll: ' undefined state)' ] externalInterruptsEnabled [ "Answer whether the receiver is executed with interrupts enabled" ^interrupts isNil or: [interrupts <= 0] ] suspendedContext [ "Answer the context that the process was executing at the time it was suspended." ^suspendedContext ] suspendedContext: aContext [ "Modify the context that the process was executing at the time it was suspended." suspendedContext := aContext ] name [ "Answer the user-friendly name of the process." ^name ] name: aString [ "Give the name aString to the process" name := aString ] priority [ "Answer the receiver's priority" ^priority ] priority: anInteger [ "Change the receiver's priority to anInteger" (anInteger between: Processor lowestPriority and: Processor highestPriority) ifFalse: [SystemExceptions.ArgumentOutOfRange signalOn: anInteger mustBeBetween: Processor lowestPriority and: Processor highestPriority]. [ | activePriority waiting | activePriority := Processor activePriority. waiting := self isActive not and: [ self isReady not ]. priority := anInteger. waiting ifFalse: [ "Atomically move the process to the right list." self resume. anInteger > activePriority ifTrue: [ Processor yield ] ]. ] valueWithoutPreemption ] valueWithoutInterrupts: aBlock [ "Evaluate aBlock and delay all interrupts that are requested during its execution to after aBlock returns." ^self interruptLock critical: aBlock ] signalInterrupt: anException [ "Force the receiver to be interrupted and anException to be raised as soon as it becomes the active process (this could mean NOW if the receiver is active). If the process is suspended or waiting on a semaphore, it is woken up so that the interrupt is processed as soon as the process priority allows to do. The exception should not be resumable to avoid that execution is continued without the process actually having gotten a signal on the semaphore (this restriction may be lifted in the future)." self interruptLock critical: [| block | self isActive ifTrue: [anException signal. ^self]. self isTerminated ifFalse: [ block := [self evaluate: [anException signal] ifNotTerminated: [self resume]]. suspendedContext := block asContext: suspendedContext. self resume]] ] queueInterrupt: aBlock [ "Force the receiver to be interrupted and to evaluate aBlock as soon as it becomes the active process (this could mean NOW if the receiver is active). If the process is temporarily suspended or waiting on a semaphore, it is temporarily woken up so that the interrupt is processed as soon as the process priority allows to do. Answer the receiver." self interruptLock critical: [| block suspended semaphore | self isActive ifTrue: [aBlock value. ^self]. self isTerminated ifTrue: [^SystemExceptions.ProcessTerminated signalOn: self]. semaphore := myList. suspended := self isReady not. block := suspended ifFalse: [self suspend. aBlock] ifTrue: [semaphore isNil ifTrue: [[self evaluate: aBlock ifNotTerminated: [self suspend]]] ifFalse: [[self evaluate: aBlock ifNotTerminated: [semaphore wait]]]]. suspendedContext := block asContext: suspendedContext. self resume] ] evaluate: aBlock ifNotTerminated: unwindBlock [ | terminated | terminated := false. [aBlock on: ProcessBeingTerminated do: [:sig | terminated := true. sig pass]] ensure: [terminated ifFalse: [unwindBlock value]] ] environment [ "This is private because it is not thread-safe. Access via ProcessorScheduler>>#environment only touches the environment of the current process, so expensive semaphores are unnecessary. We may want to revisit this in the future, but it won't be backwards-incompatible." environment isNil ifTrue: [environment := IdentityDictionary new]. ^environment ] interruptLock [ "Answer the RecursionLock object used to prevent nested interrupts." "Fast path for interruptLock ~~ nil." interruptLock isNil ifFalse: [^interruptLock]. "Slow path for when initialization is needed." ^ ["Look out for race conditions!" interruptLock isNil ifTrue: [interruptLock := RecursionLock new]. interruptLock] valueWithoutPreemption ] startExecution: aDirectedMessage [ "It is important to retrieve this before we start the process, because we want to choose whether to continue running the new process based on the *old* activePriority, not the one of the new process which is the maximum one." [aDirectedMessage send] on: SystemExceptions.ProcessBeingTerminated do: [:sig | sig return] ] onBlock: aBlockClosure at: aPriority suspend: aBoolean [ "It is important to retrieve this before we start the process, because we want to choose whether to continue running the new process based on the *old* activePriority, not the one of the new process which is the maximum one." | closure activePriority | activePriority := Processor activePriority. closure := [[[ "#priority: is inlined for two reasons. First, to be able to suspend the process, and second because we need to invert the test on activePriority! This because here we may want to yield to the creator, while in #priority: we may want to yield to the process whose priority was changed." priority := aPriority. aBoolean ifTrue: [self suspend] ifFalse: [ self resume. aPriority < activePriority ifTrue: [ Processor yield ] ]. aBlockClosure value] on: SystemExceptions.ProcessBeingTerminated do: [:sig | "If we terminate in the handler, the 'ensure' blocks are not evaluated. Instead, if the handler returns, the unwinding is done properly." sig return]] ensure: [self primTerminate]]. "Start the Process immediately so that we get into the #on:do: handler. Otherwise, we will not be able to terminate the process with #terminate." suspendedContext := closure asContext: nil. priority := Processor unpreemptedPriority. self addToBeFinalized; resume. aPriority > Processor activePriority ifTrue: [ Processor yield ]. ] isActive [ "Answer whether the receiver is running" ^self == Processor activeProcess ] isReady [ "Answer whether the receiver is not suspended nor waiting on a semaphore (maybe it is active, maybe it is not, though)" ^myList == (Processor processesAt: priority) ] isSuspended [ "Answer whether the receiver is suspended through #suspend" ^myList isNil ] isTerminated [ "Answer whether the receiver has already terminated" ^suspendedContext isNil ] isWaiting [ "Answer whether the receiver is wating on a semaphore" ^self isReady not & self isSuspended not ] singleStepWaitingOn: aSemaphore [ "Execute a limited amount of code (usually a bytecode, or up to the next backward jump, or up to the next message send) of the receiver, which must in a ready-to-run state (neither executing nor terminating nor suspended), then restart running the current process. aSemaphore is used as a means to synchronize the execution of the current process and the receiver and should have no signals on it. The current process should have higher priority than the receiver." SystemExceptions.InvalidProcessState signalOn: self ] resume [ "Resume the receiver's execution" SystemExceptions.ProcessTerminated signalOn: self ] yield [ "Yield control from the receiver to other processes" ] detach [ "Do nothing, instances of Process are already detached." ] ] smalltalk-3.2.5/kernel/MethodDict.st0000644000175000017500000001075012130343734014305 00000000000000"====================================================================== | | MethodDictionary Method Definitions | | ======================================================================" "====================================================================== | | Copyright 1999, 2000, 2001, 2002 Free Software Foundation, Inc. | Written by Paolo Bonzini. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" IdentityDictionary subclass: MethodDictionary [ at: key put: value [ "Store value as associated to the given key" | index | index := self findIndex: key. (self primAt: index) isNil ifTrue: [self incrementTally ifTrue: [index := self findIndex: key]. self primAt: index put: key] ifFalse: [(self valueAt: index) discardTranslation]. self valueAt: index put: value. Behavior flushCache. ^value ] remove: anAssociation [ "Remove anAssociation's key from the dictionary" "The interpreter might be using this MethodDictionary while this method is running!! Therefore we perform the removal in a copy, and then atomically become that copy" | copy result | (self includesKey: anAssociation key) ifFalse: [SystemExceptions.NotFound signalOn: anAssociation key what: 'key']. copy := self copy. result := copy dangerouslyRemove: anAssociation. self become: copy. Behavior flushCache. ^result ] removeKey: anElement ifAbsent: aBlock [ "Remove the passed key from the dictionary, answer the result of evaluating aBlock if it is not found" "The interpreter might be using this MethodDictionary while this method is running!! Therefore we perform the removal in a copy, and then atomically become that copy" | copy result | (self includesKey: anElement) ifFalse: [^aBlock value]. copy := self copy. result := copy dangerouslyRemoveKey: anElement. self become: copy. Behavior flushCache. ^result ] rehash [ "Rehash the receiver" "The interpreter might be using this MethodDictionary while this method is running!! Therefore we create a copy that has correct hashing (it is built on the fly), then atomically become that copy" self growBy: 0 ] dangerouslyRemove: anAssociation [ "This is not really dangerous. But if normal removal were done WHILE a MethodDictionary were being used, the system might crash. So instead we make a copy, then do this operation (which is NOT dangerous in a copy that is not being used), and then use the copy after the removal." | association | association := super remove: anAssociation. association value discardTranslation. ^association ] dangerouslyRemoveKey: anElement [ "This is not really dangerous. But if normal removal were done WHILE a MethodDictionary were being used, the system might crash. So instead we make a copy, then do this operation (which is NOT dangerous in a copy that is not being used), and then use the copy after the removal." | value | value := super removeKey: anElement ifAbsent: [self error: 'synchronization problem?']. value discardTranslation. ^value ] keysClass [ "Answer the class answered by #keys. Return Set in 3.2.x for backwards compatibility. This method will be removed in 3.3, and #keys will return IdentitySet." ^Set ] ] smalltalk-3.2.5/kernel/Namespace.st0000644000175000017500000001766612123404352014166 00000000000000"====================================================================== | | Namespace Method Definitions | | ======================================================================" "====================================================================== | | Copyright 1999, 2000, 2001, 2002, 2003 Free Software Foundation, Inc. | Written by Paolo Bonzini. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" AbstractNamespace subclass: Namespace [ Current := nil. Namespace class >> initialize [ "This actually is not needed, the job could be done in dict.c (function namespace_new). But I'm lazy and I prefer to rely on the Smalltalk implementation of IdentitySet." self allInstancesDo: [:each | each superspace isNil ifTrue: [each setSuperspace: Smalltalk]. each superspace subspaces add: each] ] Namespace class >> new [ "Disabled - use #addSubspace: to create instances" SystemExceptions.WrongMessageSent signalOn: #new useInstead: #addSubspace: ] Namespace class >> new: size [ "Disabled - use #addSubspace: to create instances" SystemExceptions.WrongMessageSent signalOn: #new: useInstead: #addSubspace: ] Namespace class >> current [ "Answer the current namespace" Current isNil ifTrue: [Current := Smalltalk]. ^Current ] Namespace class >> current: aNamespaceOrClass [ "Set the current namespace to be aNamespace or, if it is a class, its class pool (the Dictionary that holds class variables)." "The primitive call is needed to inform the compiler" | namespace | namespace := aNamespaceOrClass isClass ifTrue: [aNamespaceOrClass classPool] ifFalse: [aNamespaceOrClass]. (namespace isKindOf: Dictionary) ifTrue: [Current := namespace] ifFalse: [SystemExceptions.WrongClass signalOn: aNamespaceOrClass mustBe: {Dictionary. Class}] ] inheritedKeys [ "Answer a Set of all the keys in the receiver and its superspaces" ^(self keys) removeAll: self definedKeys ifAbsent: [:each | self error: 'synchronization problem?']; yourself ] associationsDo: aBlock [ "Pass each association in the namespace to aBlock" self allAssociations associationsDo: aBlock ] at: key ifPresent: aBlock [ "If aKey is absent from the receiver and all its superspaces, answer nil. Else, evaluate aBlock passing the associated value and answer the result of the invocation" | index space | space := self. [index := space findIndexOrNil: key. index isNil] whileTrue: [space := space superspace. space isNil ifTrue: [^nil]]. ^aBlock value: (space primAt: index) value ] associationAt: key ifAbsent: aBlock [ "Return the key/value pair associated to the variable named as specified by `key'. If the key is not found search will be brought on in superspaces, finally evaluating aBlock if the variable cannot be found in any of the superspaces." | index space | space := self. [index := space findIndexOrNil: key. index isNil] whileTrue: [space := space superspace. space isNil ifTrue: [^aBlock value]]. ^space primAt: index ] at: key ifAbsent: aBlock [ "Return the value associated to the variable named as specified by `key'. If the key is not found search will be brought on in superspaces, finally evaluating aBlock if the variable cannot be found in any of the superspaces." | index space | space := self. [index := space findIndexOrNil: key. index isNil] whileTrue: [space := space superspace. space isNil ifTrue: [^aBlock value]]. ^(space primAt: index) value ] do: aBlock [ "Pass each value in the namespace to aBlock" self allAssociations do: aBlock ] includesKey: key [ "Answer whether the receiver or any of its superspaces contain the given key" | index space | space := self. [index := space findIndexOrNil: key. index isNil] whileTrue: [space := space superspace. space isNil ifTrue: [^false]]. ^true ] keysAndValuesDo: aBlock [ "Pass to aBlock each of the receiver's keys and values, in two separate parameters" self allAssociations keysAndValuesDo: aBlock ] keysDo: aBlock [ "Pass to aBlock each of the receiver's keys" self keys do: aBlock ] set: key to: newValue ifAbsent: aBlock [ "Assign newValue to the variable named as specified by `key'. This method won't define a new variable; instead if the key is not found it will search in superspaces and evaluate aBlock if it is not found. Answer newValue." | index space | space := self. [index := space findIndexOrNil: key. index isNil] whileTrue: [space := space superspace. space isNil ifTrue: [^aBlock value]]. (space primAt: index) value: newValue. ^newValue ] size [ "Answer the number of keys in the receiver and each of its superspaces" ^super size + self superspace size ] siblings [ "Answer all the other namespaces that inherit from the receiver's superspace." ^(self superspace subspaces copy) remove: self; yourself ] siblingsDo: aBlock [ "Evaluate aBlock once for each of the other namespaces that inherit from the receiver's superspace, passing the namespace as a parameter." self superspace subspaces do: [:space | space == self ifFalse: [aBlock value: space]] ] nameIn: aNamespace [ "Answer Smalltalk code compiling to the receiver when the current namespace is aNamespace" | reference | reference := aNamespace at: self name asGlobalKey ifAbsent: [nil]. reference == self ifTrue: [^self name asString]. ^(self superspace nameIn: aNamespace) , '.' , self name ] printOn: aStream in: aNamespace [ "Print on aStream some Smalltalk code compiling to the receiver when the current namespace is aNamespace" | reference | reference := aNamespace at: self name asGlobalKey ifAbsent: [nil]. reference == self ifFalse: [self superspace printOn: aStream in: aNamespace. aStream nextPut: $.]. aStream nextPutAll: self name ] storeOn: aStream [ "Store Smalltalk code compiling to the receiver" | result name | name := self name. name isNil ifTrue: [self error: 'cannot print unnamed namespace']. self superspace storeOn: aStream. aStream nextPut: $.; nextPutAll: name ] ] smalltalk-3.2.5/kernel/SymLink.st0000644000175000017500000000475512123404352013653 00000000000000"====================================================================== | | SymLink Method Definitions | | ======================================================================" "====================================================================== | | Copyright 1988,92,94,95,99,2000,2001 | Free Software Foundation, Inc. | Written by Steve Byrne. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" Link subclass: SymLink [ | symbol | SymLink class >> symbol: aSymbol nextLink: aSymLink [ "Answer a new SymLink, which refers to aSymbol and points to aSymLink as the next SymLink in the chain." ^(self nextLink: aSymLink) symbol: aSymbol; yourself ] do: aBlock [ "Evaluate aBlock for each symbol in the list" | item | item := self. [aBlock value: item symbol. (item := item nextLink) isNil] whileFalse ] symbol [ "Answer the Symbol that the receiver refers to in the symbol table." ^symbol ] symbol: aSymbol [ "Set the Symbol that the receiver refers to in the symbol table." symbol := aSymbol ] printOn: aStream [ "Print a representation of the receiver on aStream." aStream nextPut: $[. self do: [:elt | elt printOn: aStream. aStream nextPut: Character space]. aStream nextPut: $] ] ] smalltalk-3.2.5/kernel/SysDict.st0000644000175000017500000001446712123404352013650 00000000000000"====================================================================== | | SystemDictionary Method Definitions | | ======================================================================" "====================================================================== | | Copyright 1988,89,90,91,92,94,95,99,2000,2001,2002,2006,2008,2009 | Free Software Foundation, Inc. | Written by Steve Byrne. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" RootNamespace subclass: SystemDictionary [ SystemDictionary class >> initialize [ "Create the kernel's private namespace." Smalltalk addSubspace: #Kernel. Smalltalk addFeature: #Kernel. KernelInitialized := true ] basicBacktrace [ "Prints the method invocation stack backtrace, as an aid to debugging" self primitiveFailed ] backtrace [ "Print a backtrace on the Transcript." "This replaces the primitive in builtins.st" thisContext parentContext backtrace ] getTraceFlag: anIndex [ "Private - Returns a boolean value which is one of the interpreter's tracing flags" self primitiveFailed ] setTraceFlag: anIndex to: aBoolean [ "Private - Sets the value of one of the interpreter's tracing flags (indicated by 'anIndex') to the value aBoolean." self primitiveFailed ] byteCodeCounter [ "Answer the number of bytecodes executed by the VM" ] debug [ "This methods provides a way to break in the VM code. Set a breakpoint in _gst_debug and call this method near the point where you think the bug happens." ] executionTrace [ "Answer whether executed bytecodes are printed on stdout" ^self getTraceFlag: 1 ] executionTrace: aBoolean [ "Set whether executed bytecodes are printed on stdout" ^self setTraceFlag: 1 to: aBoolean ] declarationTrace [ "Answer whether compiled bytecodes are printed on stdout" ^self getTraceFlag: 0 ] declarationTrace: aBoolean [ "Set whether compiled bytecodes are printed on stdout" ^self setTraceFlag: 0 to: aBoolean ] verboseTrace [ "Answer whether execution tracing prints the object on the stack top" ^self getTraceFlag: 2 ] verboseTrace: aBoolean [ "Set whether execution tracing prints the object on the stack top" ^self setTraceFlag: 2 to: aBoolean ] hash [ "Smalltalk usually contains a reference to itself, avoid infinite loops" ^self identityHash ] halt [ "Interrupt interpreter" thisContext environment continue: nil ] printOn: aStream in: aNamespace [ "Store Smalltalk code compiling to the receiver" aStream nextPutAll: 'Smalltalk' ] nameIn: aNamespace [ ^'Smalltalk' ] storeOn: aStream [ "Store Smalltalk code compiling to the receiver" aStream nextPutAll: 'Smalltalk' ] arguments [ "Return the command line arguments after the -a switch" self getArgc > 0 ifFalse: [^#()]. ^(1 to: self getArgc) collect: [:i | self getArgv: i] ] hostSystem [ "Answer the triplet corresponding to the system for which GNU Smalltalk was built." ^CSymbols.HostSystem ] hasFeatures: features [ "Returns true if the feature or features in 'features' is one of the implementation dependent features present" (features isKindOf: String) ifTrue: [^Features includes: features asSymbol] ifFalse: [features do: [:feature | (Features includes: feature asSymbol) ifTrue: [^true]]. ^false] ] addFeature: aFeature [ "Add the aFeature feature to the Features set" Features class == Set ifFalse: [Features := Features asSet]. Features add: aFeature asSymbol ] removeFeature: aFeature [ "Remove the aFeature feature to the Features set" Features class == Set ifFalse: [Features := Features asSet]. Features remove: aFeature ifAbsent: [] ] version [ "Answer the current version of the GNU Smalltalk environment" ^Version ] imageLocal [ "Answer whether the kernel directory is a subdirectory of the image directory (non-local image) or not." ^Directory kernel parent ~= Directory image ] isSmalltalk [ ^true ] rawProfile: anIdentityDictionary [ "Set the raw profile to be anIdentityDictionary and return the old one." ] ] smalltalk-3.2.5/kernel/Stream.st0000644000175000017500000004334512123404352013516 00000000000000"====================================================================== | | Stream Method Definitions | | ======================================================================" "====================================================================== | | Copyright 1988,92,94,95,99,2000,2001,2002,2005,2006,2007,2008,2009 | Free Software Foundation, Inc. | Written by Steve Byrne. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" Iterable subclass: Stream [ file [ "Return nil by default; not all streams have a file." ^nil ] name [ "Return nil by default; not all streams have a name." ^nil ] next [ "Return the next object in the receiver" self subclassResponsibility ] next: anInteger [ "Return the next anInteger objects in the receiver" | answer | self next: anInteger into: (answer := self species new: anInteger) startingAt: 1. ^answer ] next: anInteger putAllOn: aStream [ "Read up to anInteger bytes from the stream and store them into aStream. Return the number of bytes that were read, raising an exception if we could not read the full amount of data." | read | read := 0. [ read = anInteger ] whileFalse: [ self atEnd ifTrue: [ ^SystemExceptions.NotEnoughElements signalOn: anInteger - read]. read := read + (self nextAvailable: anInteger - read putAllOn: aStream) ]. ^read ] next: anInteger into: answer startingAt: pos [ "Read up to anInteger bytes from the stream and store them into answer. Return the number of bytes that were read, raising an exception if we could not read the full amount of data." | read | read := 0. [ read = anInteger ] whileFalse: [ self atEnd ifTrue: [ ^SystemExceptions.NotEnoughElements signalOn: anInteger - read]. read := read + (self nextAvailable: anInteger - read into: answer startingAt: read + pos) ]. ^answer ] nextAvailable: anInteger putAllOn: aStream [ "Copy up to anInteger objects in the receiver to aStream. Besides stopping if the end of the stream is reached, this may return less than this number of bytes for various reasons. For example, on files and sockets this operation could be non-blocking, or could do at most one I/O operation." | n coll | n := anInteger min: 1024. n := self nextAvailable: n into: (coll := self species new: n) startingAt: 1. aStream next: n putAll: coll startingAt: 1. ^n ] nextAvailable: anInteger [ "Return up to anInteger objects in the receiver. Besides stopping if the end of the stream is reached, this may return less than this number of bytes for various reasons. For example, on files and sockets this operation could be non-blocking, or could do at most one I/O operation." | n answer | n := self nextAvailable: anInteger into: (answer := self species new: anInteger) startingAt: 1. n < anInteger ifTrue: [ answer := answer copyFrom: 1 to: n ]. ^answer ] nextAvailable: anInteger into: aCollection startingAt: pos [ "Place the next anInteger objects from the receiver into aCollection, starting at position pos. Return the number of items stored. Besides stopping if the end of the stream is reached, this may return less than this number of bytes for various reasons. For example, on files and sockets this operation could be non-blocking, or could do at most one I/O operation." | i | i := -1. [(i := i + 1) = anInteger] whileFalse: [ self atEnd ifTrue: [^i]. aCollection at: i + pos put: self next]. ^anInteger ] nextMatchFor: anObject [ "Answer whether the next object is equal to anObject. Even if it does not, anObject is lost" ^anObject = self next ] splitAt: anObject [ "Answer an OrderedCollection of parts of the receiver. A new (possibly empty) part starts at the start of the receiver, or after every occurrence of an object which is equal to anObject (as compared by #=)." | result | result := OrderedCollection new: 10. [self atEnd] whileFalse: [result addLast: (self upTo: anObject)]. ^result ] contents [ "Answer the whole contents of the receiver, from the next object to the last" ^self upToEnd ] upToEnd [ "Answer every item in the collection on which the receiver is streaming, from the next one to the last" | ws | ws := WriteStream on: (self species new: 8). self nextPutAllOn: ws. ^ws contents ] nextLine [ "Returns a collection of the same type that the stream accesses, containing the next line up to the next new-line character. Returns the entire rest of the stream's contents if no new-line character is found." | next ws | ws := WriteStream on: (self species new: 40). [self atEnd or: [(next := self next) == ##(Character cr) or: [next == ##(Character nl) or: [next isNil]]]] whileFalse: [ws nextPut: next]. next == ##(Character cr) ifTrue: [self peekFor: ##(Character nl)]. ^ws contents ] upTo: anObject [ "Returns a collection of the same type that the stream accesses, up to but not including the object anObject. Returns the entire rest of the stream's contents if anObject is not present." | next ws | ws := WriteStream on: (self species new: 8). [self atEnd or: [(next := self next) = anObject]] whileFalse: [ws nextPut: next]. ^ws contents ] upToAll: aCollection [ "If there is a sequence of objects remaining in the stream that is equal to the sequence in aCollection, set the stream position just past that sequence and answer the elements up to, but not including, the sequence. Else, set the stream position to its end and answer all the remaining elements." | result prefix ch j | self atEnd ifTrue: [^self species new]. aCollection isEmpty ifTrue: [^self species new]. result := WriteStream on: (self species new: 20). "Use the Knuth-Morris-Pratt algorithm." prefix := self prefixTableFor: aCollection. ch := self next. j := 1. result nextPut: ch. [(ch = (aCollection at: j) or: [(j := prefix at: j) = 0]) ifTrue: [j := j + 1. j > prefix size ifTrue: [result skip: aCollection size negated. ^result contents]. self atEnd ifTrue: [^result contents]. ch := self next. result nextPut: ch]] repeat ] nextPut: anObject [ "Write anObject to the receiver" self subclassResponsibility ] next: n putAll: aCollection startingAt: start [ "Write n objects to the stream, reading them from aCollection and starting at the start-th item." aCollection from: start to: start + n - 1 do: [:element | self nextPut: element]. ^aCollection ] nextPutAllFlush: aCollection [ "Put all the elements of aCollection in the stream, then flush the buffers if supported by the stream." self nextPutAll: aCollection; flush ] nextPutAll: aCollection [ "Write all the objects in aCollection to the receiver" aCollection nextPutAllOn: self. ^aCollection ] nextPutAllOn: aStream [ "Write all the objects in the receiver to aStream" [self atEnd] whileFalse: [self nextAvailablePutAllOn: aStream]. ] next: anInteger put: anObject [ "Write anInteger copies of anObject to the receiver" anInteger timesRepeat: [self nextPut: anObject]. ^anObject ] atEnd [ "Answer whether the stream has got to an end" self subclassResponsibility ] readStream [ "As a wild guess, return the receiver. WriteStreams should override this method." ^self ] isSequenceable [ "Answer whether the receiver can be accessed by a numeric index with #at:/#at:put:." ^false ] isExternalStream [ "Answer whether the receiver streams on a file or socket. By default, answer false." ^false ] linesDo: aBlock [ "Evaluate aBlock once for every line in the receiver (assuming the receiver is streaming on Characters)." "FIXME: this is not very safe if the block uses the stream too. But maybe we can assume it doesn't?" [[self atEnd] whileFalse: [aBlock value: self nextLine]] on: SystemExceptions.EndOfStream do: [:ex | ex stream == self ifFalse: [ex resume]] ] do: aBlock [ "Evaluate aBlock once for every object in the receiver" "FIXME: this is not very safe if the block uses the stream too. But maybe we can assume it doesn't?" [[self atEnd] whileFalse: [aBlock value: self next]] on: SystemExceptions.EndOfStream do: [:ex | ex stream == self ifFalse: [ex resume]] ] species [ ^Array ] isUnicode [ "Answer whether the receiver is able to store Unicode characters. Note that if this method returns true, the stream may or may not be able to store Characters (as opposed to UnicodeCharacters) whose value is above 127." ^self species isUnicode ] encoding [ "Answer the encoding to be used when storing Unicode characters." self species isUnicode ifTrue: [ ^'Unicode' ]. ^self species defaultEncoding ] cr [ "Store a cr on the receiver" self nextPut: Character cr ] nl [ "Store a new line on the receiver" self nextPut: Character nl ] crTab [ "Store a cr and a tab on the receiver" self cr. self tab ] nlTab [ "Store a new line and a tab on the receiver" self nl. self tab ] space: n [ "Store n spaces on the receiver" self next: n put: Character space ] tab: n [ "Store n tabs on the receiver" self next: n put: Character tab ] space [ "Store a space on the receiver" self nextPut: Character space ] tab [ "Store a tab on the receiver" self nextPut: Character tab ] close [ "Do nothing. This is provided for consistency with file streams" ] pastEnd [ "The end of the stream has been reached. Signal a Notification." SystemExceptions.EndOfStream signalOn: self. ^nil ] flush [ "Do nothing. This is provided for consistency with file streams" ] << anObject [ "This method is a short-cut for #display:; it prints anObject on the receiver by sending displayOn: to anObject. This method is provided so that you can use cascading and obtain better-looking code" anObject displayOn: self ] display: anObject [ "Print anObject on the receiver by sending displayOn: to anObject. This method is provided so that you can use cascading and obtain better-looking code" anObject displayOn: self ] print: anObject [ "Print anObject on the receiver by sending printOn: to anObject. This method is provided so that you can use cascading and obtain better-looking code" anObject printOn: self ] store: anObject [ "Print Smalltalk code compiling to anObject on the receiver, by sending storeOn: to anObject. This method is provided so that you can use cascading and obtain better-looking code" anObject storeOn: self ] fileOut: aClass [ "File out aClass on the receiver. If aClass is not a metaclass, file out class and instance methods; if aClass is a metaclass, file out only the class methods" aClass fileOutOn: self ] isPositionable [ "Answer true if the stream supports moving backwards with #skip:." ^false ] skip: anInteger [ "Move the position forwards by anInteger places" anInteger < 0 ifTrue: [SystemExceptions.InvalidArgument signalOn: anInteger reason: 'must be positive']. anInteger timesRepeat: [self atEnd ifTrue: [^false]. self next]. ^true ] skipTo: anObject [ "Move the current position to after the next occurrence of anObject and return true if anObject was found. If anObject doesn't exist, the pointer is atEnd, and false is returned." [self atEnd] whileFalse: [self next = anObject ifTrue: [^true]]. ^false ] skipToAll: aCollection [ "If there is a sequence of objects remaining in the stream that is equal to the sequence in aCollection, set the stream position just past that sequence and answer true. Else, set the stream position to its end and answer false." | prefix ch j | self atEnd ifTrue: [^false]. aCollection isEmpty ifTrue: [^true]. "Use the Knuth-Morris-Pratt algorithm." prefix := self prefixTableFor: aCollection. ch := self next. j := 1. [(ch = (aCollection at: j) or: [(j := prefix at: j) = 0]) ifTrue: [j := j + 1. j > prefix size ifTrue: [^true]. self atEnd ifTrue: [^false]. ch := self next]] repeat ] nextAvailablePutAllOn: aStream [ "Copy to aStream a more-or-less arbitrary amount of data. When used on files, this does at most one I/O operation. For other kinds of stream, the definition may vary. This method is used to do stream-to-stream copies." self nextAvailable: 16rFFFFFFF putAllOn: aStream. ] prefixTableFor: aCollection [ "Private - Answer the prefix table for the Knuth-Morris-Pratt algorithm. After a failure, the table is looked up to see how the longest prefix that still matches. For example, when searching 'aabab' in 'aabaabab', when the fourth `a' is reached the table tells that we can proceed with the match as long as we restart from the second `a' in the searched string." | prefix j | prefix := aCollection size < 256 ifTrue: [ByteArray new: aCollection size] ifFalse: [Array new: aCollection size]. prefix at: 1 put: 0; at: 2 put: 1. aCollection from: 2 to: aCollection size - 1 keysAndValuesDo: [:i :ch | j := prefix at: i. [j <= 1 or: [ch = (aCollection at: j)]] whileFalse: [j := prefix at: j]. prefix at: i + 1 put: j]. ^prefix ] fileIn [ "File in the contents of the receiver. During a file in operation, global variables (starting with an uppercase letter) that are not declared don't yield an `unknown variable' error. Instead, they are defined as nil in the `Undeclared' dictionary (a global variable residing in Smalltalk). As soon as you add the variable to a namespace (for example by creating a class) the Association will be removed from Undeclared and reused in the namespace, so that the old references will automagically point to the new value." | pos | pos := [self position] on: MessageNotUnderstood do: [:ex | ex return: 0]. ^self fileInLine: 1 file: self file at: pos ] fileInLine: lineNum file: aFile at: charPosInt [ "Private - Much like a preprocessor #line directive; it is used internally by #fileIn, and explicitly by the Emacs Smalltalk mode." ^self fileInLine: 1 file: (aFile ifNotNil: [aFile full]) fileName: (aFile ifNotNil: [aFile displayString]) at: charPosInt ] fileInLine: lineNum file: aFile fileName: aString at: charPosInt [ "Private - Much like a preprocessor #line directive; it is used internally by #fileIn, and explicitly by the Emacs Smalltalk mode." self primitiveFailed ] fileInLine: lineNum fileName: aString at: charPosInt [ "Private - Much like a preprocessor #line directive; it is used internally by #fileIn, and explicitly by the Emacs Smalltalk mode." self primitiveFailed ] ] smalltalk-3.2.5/kernel/UniChar.st0000644000175000017500000000466212123404352013613 00000000000000"====================================================================== | | UnicodeCharacter Method Definitions | | ======================================================================" "====================================================================== | | Copyright 2006, 2008 Free Software Foundation, Inc. | Written by Paolo Bonzini. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" Character subclass: UnicodeCharacter [ >#codePoint:.'> UnicodeCharacter class >> value: anInteger [ "Returns the character object, possibly a Character, corresponding to anInteger. Error if anInteger is not an integer, or not in 0..16r10FFFF. This is only a primitive for speed. UnicodeCharacter's #value: method is equivalent to #codePoint: (which is the same for Character and UnicodeCharacter)." anInteger isInteger ifFalse: [SystemExceptions.WrongClass signalOn: anInteger mustBe: SmallInteger] ifTrue: [SystemExceptions.ArgumentOutOfRange signalOn: anInteger mustBeBetween: 0 and: 1114111] ] * aNumber [ "Returns a String with aNumber occurrences of the receiver." ^UnicodeString new: aNumber withAll: self ] ] smalltalk-3.2.5/kernel/Continuation.st0000644000175000017500000001173712123404352014735 00000000000000"====================================================================== | | Continuation Method Definitions | | ======================================================================" "====================================================================== | | Copyright (C) 2007 University of Manchester | Originally by Ian Piumarta, rewritten by Paolo Bonzini. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" Object subclass: Continuation [ | stack | Continuation class >> escapeDo: aBlock [ "Pass a continuation to the one-argument block, knowing that aBlock does not fall off (either because it includes a method return, or because it yields control to another continuation). If it does, an exception will be signalled and the current process terminated." aBlock value: (self new stack: thisContext parentContext). SystemExceptions.BadReturn signal. Processor activeProcess terminate ] Continuation class >> current [ "Return a continuation." ^self new stack: thisContext parentContext copyStack ] Continuation class >> currentDo: aBlock [ "Pass a continuation to the one-argument block, aBlock and return the result of evaluating it." ^aBlock value: (self new stack: thisContext parentContext copyStack) ] oneShotValue [ "Return nil to the original continuation, which becomes unusable. Attempting to reactivate it will cause an exception. This is an optimization over #value." ^self resume: nil nextContinuation: nil ] oneShotValue: v [ "Return anObject to the original continuation, which becomes unusable. Attempting to reactivate it will cause an exception. This is an optimization over #value:." ^self resume: v nextContinuation: nil ] callCC [ "Activate the original continuation, passing back in turn a continuation for the caller. The called continuation becomes unusable, and any attempt to reactivate it will cause an exception. This is not a limitation, in general, because this method is used to replace a continuation with another (see the implementation of the Generator class)." | cont | cont := Continuation new stack: thisContext parentContext. ^self resume: cont nextContinuation: nil ] value [ "Return nil to the original continuation, copying the stack to allow another activation." ^self resume: nil nextContinuation: stack copyStack ] value: anObject [ "Return anObject to the original continuation, copying the stack to allow another activation." ^self resume: anObject nextContinuation: stack copyStack ] valueWithArguments: aCollection [ "Return the sole element of aCollection to the original continuation (or nil if aCollection is empty), copying the stack to allow another activation" aCollection size == 0 ifTrue: [^self value: nil]. aCollection size == 1 ifFalse: [^self value: (aCollection at: 1)]. SystemExceptions.InvalidArgument signalOn: aCollection reason: 'continuations can only be resumed with zero or one argument' ] resume: returnValue nextContinuation: aContext [ SystemExceptions.BadReturn signal. Processor activeProcess terminate. ^returnValue "The primitive is equivalent to this code: | continuation | stack isNil ifTrue: [ ^self primitiveFailed ]. continuation := stack. stack := aContext. thisContext parentContext: continuation. ^returnValue" ] stack [ ^stack ] stack: s [ stack := s ] ] smalltalk-3.2.5/kernel/IdentDict.st0000644000175000017500000000575512130343734014141 00000000000000"====================================================================== | | IdentityDictionary Method Definitions | | ======================================================================" "====================================================================== | | Copyright 1988,89,90,91,92,94,95,99,2000,2001,2002 | Free Software Foundation, Inc. | Written by Steve Byrne and Paolo Bonzini. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" LookupTable subclass: IdentityDictionary [ keysClass [ "Answer the class answered by #keys" ^IdentitySet ] hashFor: anObject [ "Return an hash value for the item, anObject" ^anObject identityHash ] findElementIndex: anObject [ "Tries to see where anObject can be placed as an indexed variable. As soon as nil is found, the index of that slot is answered. anObject also comes from an indexed variable." | index size element | self beConsistent. "Sorry for the lack of readability, but I want speed... :-)" index := (anObject identityHash scramble bitAnd: (size := self primSize) - 1) + 1. [(element := self primAt: index) isNil ifTrue: [^index]. index == size ifTrue: [index := 1] ifFalse: [index := index + 1]] repeat ] findIndex: anObject [ "Tries to see if anObject exists as an indexed variable. As soon as nil or anObject is found, the index of that slot is answered" | index size element | self beConsistent. "Sorry for the lack of readability, but I want speed... :-)" index := (anObject identityHash scramble bitAnd: (size := self primSize) - 1) + 1. [((element := self primAt: index) isNil or: [element == anObject]) ifTrue: [^index]. index == size ifTrue: [index := 1] ifFalse: [index := index + 1]] repeat ] ] smalltalk-3.2.5/kernel/VFSZip.st0000644000175000017500000002151612123404352013400 00000000000000"====================================================================== | | Virtual File System (new classes) | | ======================================================================" "====================================================================== | | Copyright 2007, 2008 Free Software Foundation, Inc. | Written by Paolo Bonzini. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" Namespace current: VFS [ ArchiveFile subclass: ZipFile [ createDirectory: dirName [ "Create a subdirectory of the receiver, naming it dirName." self notYetImplemented ] member: anArchiveMember mode: bits [ "Set the permission bits for the file in anArchiveMember." self notYetImplemented ] extractMember: anArchiveMember into: temp [ "Extract the contents of anArchiveMember into a file that resides on disk, and answer the name of the file." Smalltalk system: 'unzip -p %1 %2 > %3' withArguments: {self file name. anArchiveMember name. temp name} ] removeMember: anArchiveMember [ "Remove the member represented by anArchiveMember." Smalltalk system: 'zip -d %1 %2' withArguments: {self file name. anArchiveMember name} ] updateMember: anArchiveMember [ "Update the member represented by anArchiveMember by copying the file into which it was extracted back to the archive." self notYetImplemented ] centralDirectoryRangeIn: f [ | r beginCD size comLen buf ofsCD | size := f size. r := 21. "Great idea, that of putting a variable-length item at the end. Luckily, we can make a sanity check of the data and find the correct spot of the central directory's final record." size - 22 to: size - 65535 - 22 by: -257 do: [:pos | buf := (f copyFrom: pos to: pos + r) asByteArray. beginCD := buf indexOfSubCollection: #[80 75 5 6] ifAbsent: [0]. beginCD = 0 ifFalse: [comLen := (buf at: beginCD + 21) * 256 + (buf at: beginCD + 20). pos + beginCD + 21 + comLen = size ifTrue: [ofsCD := (buf at: beginCD + 19) * 16777216 + ((buf at: beginCD + 18) * 65536) + ((buf at: beginCD + 17) * 256) + (buf at: beginCD + 16). ^ofsCD to: pos + beginCD - 2]]. r := 278]. self error: 'invalid data in ZIP file' ] fileData [ "Extract the directory listing from the archive" ^Generator on: [:gen | | f cd cdEnd data path date method dataSize fileSize fnsize extra comment attr ofs | f := self readStream. cd := self centralDirectoryRangeIn: f. f position: cd first. cdEnd := cd last. date := DateTime now. [f position <= cdEnd ] whileTrue: [f skip: 10. method := f nextUshort. data := method = 0 ifTrue: [Array new: 5] ifFalse: [Array new: 4]. data at: 3 put: date. f skip: 12. data at: 2 put: f nextUlong. fnsize := f nextUshort. extra := f nextUshort. comment := f nextUshort. f skip: 4. attr := f nextUlong. ofs := f nextUlong. data at: 1 put: (f next: fnsize). f skip: extra + comment. data at: 4 put: (attr bitAnd: 16) = 16. method = 0 ifTrue: [data at: 5 put: ((StoredZipMember new) name: (data at: 1); archive: self; offset: ofs; yourself)]. gen yield: data]. f close] ] ] ] Namespace current: VFS [ TmpFileArchiveMember subclass: StoredZipMember [ | offset | offset [ ^offset ] offset: anInteger [ offset := anInteger ] open: class mode: mode ifFail: aBlock [ | fileStream | (mode = FileStream read or: [ self extracted ]) ifFalse: [^super open: class mode: mode ifFail: aBlock]. fileStream := self archive open: class mode: mode ifFail: [^aBlock value]. fileStream skip: self offset + 26. fileStream skip: fileStream nextUshort + fileStream nextUshort. fileStream setFile: self. ^LimitedStream on: fileStream from: fileStream position to: fileStream position + self size - 1 ] ] ] Namespace current: Kernel [ Stream subclass: LimitedStream [ | stream offset limit | LimitedStream class >> on: aStream from: start to: end [ ^(self new) stream: aStream; offset: start; limit: end + 1; yourself ] atEnd [ ^stream position >= limit or: [stream atEnd] ] copyFrom: start to: end [ (start between: 0 and: limit - offset) ifFalse: [SystemExceptions.IndexOutOfRange signalOn: self withIndex: start]. (end between: 0 and: limit - offset) ifFalse: [SystemExceptions.IndexOutOfRange signalOn: self withIndex: end]. ^stream copyFrom: offset + start to: offset + end ] isPositionable [ ^true ] nextAvailable: n into: aCollection startingAt: pos [ ^stream nextAvailable: (n min: limit - stream position) into: aCollection startingAt: pos ] next [ self atEnd ifTrue: [^self pastEnd]. ^stream next ] peek [ self atEnd ifTrue: [^nil]. ^stream peek ] peekFor: aCharacter [ self atEnd ifTrue: [^false]. ^stream peek ] position [ ^stream position - offset ] position: anInteger [ (anInteger between: 0 and: limit - offset) ifTrue: [stream position: offset + anInteger] ifFalse: [SystemExceptions.IndexOutOfRange signalOn: self withIndex: anInteger] ] setToEnd [ stream position: limit ] size [ ^limit - offset ] skip: anInteger [ self position: anInteger + self position ] printOn: aStream [ aStream print: stream; nextPut: $[; print: offset; nextPut: $:; print: limit; nextPut: $] ] file [ ^stream file ] name [ ^stream name ] species [ ^stream species ] stream: aStream [ stream := aStream ] limit: anInteger [ limit := anInteger ] offset: anInteger [ offset := anInteger ] fileIn [ "File in the contents of the receiver. During a file in operation, global variables (starting with an uppercase letter) that are not declared don't yield an `unknown variable' error. Instead, they are defined as nil in the `Undeclared' dictionary (a global variable residing in Smalltalk). As soon as you add the variable to a namespace (for example by creating a class) the Association will be removed from Undeclared and reused in the namespace, so that the old references will automagically point to the new value." | pos | stream isPipe ifTrue: [ ^super fileIn ]. ^self fileInLine: 1 file: stream file full fileName: stream name at: self position ] flush [ stream flush ] close [ stream close ] ] ] FilePath extend [ zip [ ^VFS.ZipFile on: self ] ] smalltalk-3.2.5/kernel/Behavior.st0000644000175000017500000014370312130343734014025 00000000000000"====================================================================== | | Behavior Method Definitions | | ======================================================================" "====================================================================== | | Copyright 1988,89,90,91,92,94,95,99,2000,2001,2002,2003, | 2005,2006,2007,2008,2009 Free Software Foundation, Inc. | Written by Steve Byrne. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" Object subclass: Behavior [ | superClass methodDictionary instanceSpec subClasses instanceVariables | addInstVarName: aString [ "Add the given instance variable to instance of the receiver" | newInstanceVariables duplicated symbol | self validateIdentifier: aString. symbol := aString asSymbol. newInstanceVariables := instanceVariables isNil ifTrue: [{symbol}] ifFalse: [instanceVariables copyWith: symbol]. duplicated := self superclass allInstVarNames includes: symbol. self updateInstanceVars: newInstanceVariables shape: self shape. duplicated ifTrue: [self compileAll]. self compileAllSubclasses ] removeInstVarName: aString [ "Remove the given instance variable from the receiver and recompile all of the receiver's subclasses" | newInstanceVariables symbol index | symbol := aString asSymbol. index := instanceVariables findLast: [:each | each = symbol]. index = 0 ifTrue: [SystemExceptions.NotFound signalOn: symbol what: 'instance variable']. newInstanceVariables := instanceVariables copyReplaceFrom: index to: index with: #(). self updateInstanceVars: newInstanceVariables shape: self shape; compileAll; compileAllSubclasses ] instanceVariableNames: instVarNames [ "Set the instance variables for the receiver to be those in instVarNames" | variableArray oldInstVarNames oldSize removed changed added | variableArray := self parseInstanceVariableString: instVarNames. variableArray := self subclassInstVarNames, variableArray. oldInstVarNames := self allInstVarNames. "If instance variables change, update instance variables and instance spec of the class and all its subclasses" variableArray = oldInstVarNames ifTrue: [^self]. self updateInstanceVars: variableArray shape: self shape. "If this class or the subclasses' variables changed, need to recompile." oldSize := oldInstVarNames size. changed := variableArray size < oldSize or: [ (variableArray first: oldSize) ~= (oldInstVarNames first: oldSize)]. removed := oldInstVarNames anySatisfy: [:each | (variableArray includes: each) not]. added := variableArray anySatisfy: [:each | (oldInstVarNames includes: each) not]. changed | removed | added ifFalse: [^self]. changed | removed ifTrue: [self compileAll]. self compileAllSubclasses ] parseInstanceVariableString: variableString [ "As with #parseVariableString:, but answer symbols that name the variables instead of strings." | variableArray | variableArray := self parseVariableString: variableString. ^variableArray collect: [:each | each asSymbol] ] parseVariableString: aString [ "Answer an array of instance variable names. aString should specify these in traditional file-in `instanceVariableNames' format. Signal an error if aString contains something other than valid Smalltalk variables." | tokens | tokens := aString subStrings asArray. tokens do: [:token | self validateIdentifier: token]. ^tokens ] createGetMethod: what default: value [ "Create a method accessing the variable `what', with a default value of `value', using lazy initialization" ^self compile: '%1 [ "Answer the receiver''s %1. Its default value is %2" %1 isNil ifTrue: [ %1 := %2 ]. ^%1 ]' % {what. value} ] createGetMethod: what [ "Create a method accessing the variable `what'." ^self compile: '%1 [ "Answer the receiver''s %1" ^%1 ]' % {what} ] createSetMethod: what [ "Create a method which sets the variable `what'." | parameter | parameter := what = 'value' ifTrue: ['theValue'] ifFalse: ['value']. ^self compile: '%1: %2 [ "Set the receiver''s %1 to %2" %1 := %2 ]' % {what. parameter} ] defineAsyncCFunc: cFuncNameString withSelectorArgs: selectorAndArgs args: argsArray [ "Please lookup the part on the C interface in the manual. This method is deprecated, you should use the asyncCCall:args: attribute." | code | code := '%1 [ ]' % {selectorAndArgs. cFuncNameString. argsArray printString}. ^self compile: code ifError: [:file :line :error | code error: error] ] defineCFunc: cFuncNameString withSelectorArgs: selectorAndArgs returning: returnTypeSymbol args: argsArray [ "Please lookup the part on the C interface in the manual. This method is deprecated, you should use the cCall:returning:args: attribute." | code | code := '%1 [ ]' % {selectorAndArgs. cFuncNameString. returnTypeSymbol storeString. argsArray printString}. ^self compile: code ifError: [:file :line :error | code error: error] ] methodDictionary [ "Answer the receiver's method dictionary. Don't modify the method dictionary unless you exactly know what you're doing" ^methodDictionary ] selectorsAndMethodsDo: aBlock [ "Evaluate aBlock, passing for each evaluation a selector that's defined in the receiver and the corresponding method." self methodDictionary isNil ifFalse: [self methodDictionary keysAndValuesDo: aBlock] ] methodDictionary: aDictionary [ "Set the receiver's method dictionary to aDictionary" | newDictionary | aDictionary isNil ifFalse: [ newDictionary := aDictionary collect: [:each | each withNewMethodClass: self]. aDictionary become: newDictionary ]. Behavior flushCache. methodDictionary := aDictionary ] addSelector: selector withMethod: compiledMethod [ "Add the given compiledMethod to the method dictionary, giving it the passed selector. Answer compiledMethod" self methodDictionary isNil ifTrue: [methodDictionary := MethodDictionary new]. ^self methodDictionary at: selector put: (compiledMethod withNewMethodClass: self selector: selector) ] removeSelector: selector [ "Remove the given selector from the method dictionary, answer the CompiledMethod attached to that selector" ^self removeSelector: selector ifAbsent: [SystemExceptions.NotFound signalOn: selector what: 'method'] ] removeSelector: selector ifAbsent: aBlock [ "Remove the given selector from the method dictionary, answer the CompiledMethod attached to that selector. If the selector cannot be found, answer the result of evaluating aBlock." self methodDictionary isNil ifTrue: [^aBlock value]. (self methodDictionary includesKey: selector) ifFalse: [^aBlock value]. ^self methodDictionary removeKey: selector ifAbsent: [self error: 'huh?!?'] ] formattedSourceStringAt: aSelector ifAbsent: aBlock [ "Answer the method source code as a formatted string. Requires package Parser." self notYetImplemented ] formattedSourceStringAt: selector [ "Answer the method source code as a formatted string (if available) for the given selector. Requires package Parser." ^self formattedSourceStringAt: selector ifAbsent: [ '" *** SOURCE CODE NOT AVAILABLE *** "'] ] compile: code [ "Compile method source. If there are parsing errors, answer nil. Else, return a CompiledMethod result of compilation" (code isKindOf: WriteStream) ifTrue: [^self primCompile: code readStream]. (code isKindOf: Stream) ifTrue: [^self primCompile: code]. ^self primCompile: code asString ] compile: code ifError: block [ "Compile method source. If there are parsing errors, invoke exception block, 'block' passing file name, line number and error. Return a CompiledMethod result of compilation" (code isKindOf: WriteStream) ifTrue: [^self primCompile: code readStream ifError: block]. (code isKindOf: Stream) ifTrue: [^self primCompile: code ifError: block]. ^self primCompile: code asString ifError: block ] compile: code notifying: requestor [ "Compile method source. If there are parsing errors, send #error: to the requestor object, else return a CompiledMethod result of compilation" | method | method := self compile: code. method isNil ifTrue: [requestor error: 'Compilation failed']. ^method ] compileAllSubclasses: aNotifier [ "Recompile all selector of all subclasses. Notify aNotifier by sending #error: messages if something goes wrong." self allSubclassesDo: [:subclass | subclass compileAll: aNotifier] ] compileAllSubclasses [ "Recompile all selector of all subclasses. Notify aNotifier by sending #error: messages if something goes wrong." self allSubclassesDo: [:subclass | subclass compileAll] ] recompile: selector [ "Recompile the given selector, answer nil if something goes wrong or the new CompiledMethod if everything's ok." (self >> selector) recompile. ] recompile: selector notifying: aNotifier [ "Recompile the given selector. If there are parsing errors, send #error: to the aNotifier object, else return a CompiledMethod result of compilation" (self >> selector) recompileNotifying: aNotifier. ] decompile: selector [ "Decompile the bytecodes for the given selector." | method source | method := self >> selector. source := method methodSourceString. ^source isNil & self decompilerClass notNil ifTrue: [self decompilerClass decompile: selector in: self] ifFalse: [source] ] edit: selector [ "Open Emacs to edit the method with the passed selector, then compile it" | method sourceFile sourcePos | method := self >> selector. sourceFile := method methodSourceFile. sourceFile isNil ifTrue: [^self error: 'decompiler can''t edit methods without source']. sourcePos := method methodSourcePos. Smalltalk system: 'emacs -l st -smalltalk ' , sourceFile , ' ' , sourcePos printString "Possible Windows code follows:" " method := self >> selector. sourceFile := method methodSourceCode asString. sourcePos := sourceFile size. (sourceFile at: sourcePos) = $! ifTrue: [ sourcePos := sourcePos - 1 ]. (FileStream open: 'st.tmp' mode: FileStream write) nextPutAll: (sourceFile copyFrom: 1 to: sourcePos); close. Smalltalk system: 'notepad st.tmp'. sourceFile := FileStream open: 'st.tmp' mode: FileStream read. self compile: sourceFile contents. sourceFile close. (self >> selector) methodCategory: method methodCategory. Smalltalk system: 'del st.tmp'" ] compileAll [ "Recompile all selectors in the receiver. Ignore errors." self methodDictionary notNil ifTrue: [self methodDictionary do: [:method | method recompile]] ] compileAll: aNotifier [ "Recompile all selectors in the receiver. Notify aNotifier by sending #error: messages if something goes wrong." self methodDictionary notNil ifTrue: [self methodDictionary do: [:method | method recompileNotifying: aNotifier]] ] evalString: aString to: anObject [ "Answer the stack top at the end of the evaluation of the code in aString. The code is executed as part of anObject" | s result next method | s := ReadStream on: aString. [next := self extractEvalChunk: s. method := anObject class compile: 'Doit [ ^ [ ' , next , ' ] value ]' ifError: [:fname :line :error | nil]. method isNil | (next allSatisfy: [:each | each = Character space]) ifFalse: [[result := anObject perform: method] valueWithUnwind]. s atEnd] whileFalse. anObject class removeSelector: #Doit ifAbsent: []. ^result ] evalString: aString to: anObject ifError: aBlock [ "Answer the stack top at the end of the evaluation of the code in aString. If aString cannot be parsed, evaluate aBlock (see compile:ifError:). The code is executed as part of anObject" | s result next method | s := ReadStream on: aString. [next := self extractEvalChunk: s. method := anObject class compile: 'Doit [ ^ [ ' , next , ' ] value ] ' ifError: [:fname :lineNo :errorString | aBlock value: fname value: lineNo - 1 value: errorString. nil]. method isNil | (next allSatisfy: [:each | each = Character space]) ifFalse: [[result := anObject perform: method] valueWithUnwind]. s atEnd] whileFalse. anObject class removeSelector: #Doit ifAbsent: []. ^result ] evaluate: code [ "Evaluate Smalltalk expression in 'code' and return result." ^self evaluate: code to: nil ] evaluate: code ifError: block [ "Evaluate 'code'. If a parsing error is detected, invoke 'block'" ^self evaluate: code to: nil ifError: block ] evaluate: code to: anObject ifError: block [ "Evaluate Smalltalk expression as part of anObject's method definition. This method is used to support Inspector expression evaluation. If a parsing error is encountered, invoke error block, 'block'" (code isKindOf: Stream) ifTrue: [^self evalString: code contents to: anObject ifError: block]. ^self evalString: code to: anObject ifError: block ] evaluate: code to: anObject [ "Evaluate Smalltalk expression as part of anObject's method definition" (code isKindOf: Stream) ifTrue: [^self evalString: code contents to: anObject]. ^self evalString: code to: anObject ] evaluate: code notifying: requestor [ "Evaluate Smalltalk expression in 'code'. If a parsing error is encountered, send #error: to requestor" | method aStream | ^self evaluate: code ifError: [:fname :lineNo :errorString | requestor error: 'line ' , lineNo printString , ': ' , errorString] ] superclass: aClass [ "Set the receiver's superclass." superClass := aClass. instanceSpec isNil ifTrue: [instanceSpec := aClass isNil ifTrue: [0] ifFalse: [aClass instanceSpec]] ] addSubclass: aClass [ "Add aClass asone of the receiver's subclasses." subClasses isNil ifTrue: [subClasses := Array new] ifFalse: ["remove old class if any" subClasses := subClasses copyWithout: aClass]. subClasses := subClasses copyWith: aClass ] removeSubclass: aClass [ "Remove aClass from the list of the receiver's subclasses" subClasses := subClasses copyWithout: aClass ] selectors [ "Answer a Set of the receiver's selectors" self methodDictionary isNil ifTrue: [^Set new] ifFalse: [^self methodDictionary keys] ] allSelectors [ "Answer a Set of all the selectors understood by the receiver" | aSet | aSet := self selectors. self allSuperclassesDo: [:superclass | aSet addAll: superclass selectors]. ^aSet ] lookupSelector: aSelector [ "Return the compiled method associated with selector, from the local method dictionary or one of a superclass; return nil if not found." | class method | class := self. [method := class compiledMethodAt: aSelector ifAbsent: [nil]. method isNil ifFalse: [^method]. class := class superclass. class isNil ifTrue: [^nil]] repeat ] lookupAllSelectors: aSelector [ "Answer a Set of all the compiled method associated with selector. from the local method dictionary and all of the superclasses." | implementors | implementors := Set new. self withAllSuperclassesDo: [:c | | m | m := c compiledMethodAt: aSelector ifAbsent: [nil]. m ifNotNil: [implementors add: m]]. ^implementors ] compiledMethodAt: selector ifAbsent: aBlock [ "Return the compiled method associated with selector, from the local method dictionary. Evaluate aBlock if not found." self methodDictionary isNil ifTrue: [^aBlock value]. ^self methodDictionary at: selector ifAbsent: aBlock ] compiledMethodAt: selector [ "Return the compiled method associated with selector, from the local method dictionary. Error if not found." self methodDictionary isNil ifTrue: [SystemExceptions.NotFound signalOn: selector what: 'key']. ^self methodDictionary at: selector ifAbsent: [SystemExceptions.NotFound signalOn: selector what: 'key'] ] >> selector [ "Return the compiled method associated with selector, from the local method dictionary. Error if not found." self methodDictionary isNil ifTrue: [SystemExceptions.NotFound signalOn: selector what: 'key']. ^self methodDictionary at: selector ifAbsent: [SystemExceptions.NotFound signalOn: selector what: 'key'] ] selectorAt: method [ "Return selector for the given CompiledMethod" self methodDictionary isNil ifTrue: [SystemExceptions.NotFound signalOn: method what: 'method']. ^self methodDictionary keyAtValue: method ifAbsent: [SystemExceptions.NotFound signalOn: method what: 'method'] ] parseTreeFor: selector [ "Answer the parse tree for the given selector, or nil if there was an error. Requires the Parser package to be loaded." ^(self >> selector) methodParseNode ] sourceCodeAt: selector ifAbsent: aBlock [ "Answer source code (if available) for the given selector." | source | source := (self >> selector) methodSourceCode. source isNil ifTrue: [^aBlock value copy]. ^source asString ] sourceCodeAt: selector [ "Answer source code (if available) for the given selector." ^self sourceCodeAt: selector ifAbsent: [ '" *** SOURCE CODE NOT AVAILABLE *** "'] ] sourceMethodAt: selector [ "This is too dependent on the original implementation" self shouldNotImplement ] allInstances [ "Returns a set of all instances of the receiver" | result weakResult anInstance | result := WriteStream on: (Array new: 100). anInstance := self someInstance. [anInstance notNil] whileTrue: [result nextPut: anInstance. anInstance := anInstance nextInstance]. result := result contents. weakResult := WeakArray new: result size. 1 to: result size do: [:i | weakResult at: i put: (result at: i)]. ^weakResult ] instanceCount [ "Return a count of all the instances of the receiver" | count anInstance | count := 0. anInstance := self someInstance. [anInstance notNil] whileTrue: [count := count + 1. anInstance := anInstance nextInstance]. ^count ] indexOfInstVar: aString [ "Answer the index of aString in the fixed instance variables of the instances of the receiver, or 0 if the variable is missing." ^self allInstVarNames indexOfLast: aString asSymbol ifAbsent: [0] ] indexOfInstVar: aString ifAbsent: aBlock [ "Answer the index of aString in the fixed instance variables of the instances of the receiver, or 0 if the variable is missing." ^self allInstVarNames indexOfLast: aString asSymbol ifAbsent: aBlock ] instVarNames [ "Answer an Array containing the instance variables defined by the receiver" | superVars | instanceVariables isNil ifTrue: [^#()]. superClass isNil ifTrue: [^instanceVariables copy] ifFalse: [superVars := superClass allInstVarNames. ^instanceVariables copyFrom: superVars size + 1 to: instanceVariables size] ] subclassInstVarNames [ "Answer the names of the instance variables the receiver inherited from its superclass" | superVars | instanceVariables isNil ifTrue: [^#()]. superClass isNil ifTrue: [^#()]. ^superClass allInstVarNames ] allInstVarNames [ "Answer the names of every instance variables the receiver contained in the receiver's instances" ^instanceVariables isNil ifTrue: [#()] ifFalse: [instanceVariables] ] classVarNames [ "Answer all the class variables for instances of the receiver" ^self superclass isNil ifTrue: [#()] ifFalse: [self superclass classVarNames] ] allClassVarNames [ "Return all the class variables understood by the receiver" | result | result := WriteStream with: self classVarNames asArray. self allSuperclassesDo: [:each | result nextPutAll: each classVarNames]. ^result contents ] classPool [ "Answer the class pool dictionary. Since Behavior does not support classes with class variables, we answer an empty one; adding variables to it results in an error." ^(Dictionary new) makeReadOnly: true; yourself ] sharedPools [ "Return the names of the shared pools defined by the class" ^self superclass isNil ifTrue: [#()] ifFalse: [self superclass sharedPools] ] allSharedPoolDictionariesDo: aBlock [ "Answer the shared pools visible from methods in the metaclass, in the correct search order." self superclass allSharedPoolDictionariesDo: aBlock ] allSharedPoolDictionaries [ "Return the shared pools defined by the class and any of its superclasses, in the correct search order." | result | result := OrderedCollection new. self allSharedPoolDictionariesDo: [:each | result add: each]. ^result ] allSharedPools [ "Return the names of the shared pools defined by the class and any of its superclasses, in the correct search order." | result | result := OrderedCollection new. self allSharedPoolDictionariesDo: [:each | result add: (each nameIn: self environment)]. ^result ] subclasses [ "Answer the direct subclasses of the receiver in a Set" subClasses isNil ifTrue: [^Set new] ifFalse: [^subClasses asSet] ] allSubclasses [ "Answer the direct and indirect subclasses of the receiver in a Set" | aSet | aSet := Set new. self allSubclassesDo: [:subclass | aSet add: subclass]. ^aSet ] withAllSubclasses [ "Answer a Set containing the receiver together with its direct and indirect subclasses" | aSet | aSet := Set with: self. aSet addAll: self allSubclasses. ^aSet ] superclass [ "Answer the receiver's superclass (if any, otherwise answer nil)" ^superClass ] withAllSuperclasses [ "Answer the receiver and all of its superclasses in a collection" | supers | supers := OrderedCollection with: self. self allSuperclassesDo: [:superclass | supers addLast: superclass]. ^supers ] allSuperclasses [ "Answer all the receiver's superclasses in a collection" | supers | supers := OrderedCollection new. self allSuperclassesDo: [:superclass | supers addLast: superclass]. ^supers ] whichSelectorsReferToByteCode: aByteCode [ "Return the collection of selectors in the class which reference the byte code, aByteCode" | s method specialSelector | s := Set new. self methodDictionary isNil ifTrue: [^s]. self methodDictionary keysAndValuesDo: [:sel :method | ((1 to: method numBytecodes) detect: [:i | aByteCode = (method bytecodeAt: i)] ifNone: [0]) > 0 ifTrue: [s add: sel]]. ^s ] hasMethods [ "Return whether the receiver has any methods defined" ^self methodDictionary notNil and: [self methodDictionary notEmpty] ] includesSelector: selector [ "Returns true if the local method dictionary contains the given selector" self methodDictionary isNil ifTrue: [^false]. ^self methodDictionary includesKey: selector ] canUnderstand: selector [ "Returns true if the instances of the receiver understand the given selector" ^(self lookupSelector: selector) notNil ] whichClassIncludesSelector: selector [ "Answer which class in the receiver's hierarchy contains the implementation of selector used by instances of the class (nil if none does)" self withAllSuperclassesDo: [:superclass | (superclass includesSelector: selector) ifTrue: [^superclass]]. ^nil ] whichSelectorsRead: instVarName [ "Answer a Set of selectors which read the given instance variable" | md index | index := self allInstVarNames indexOf: instVarName asSymbol ifAbsent: [^Set new]. "### should it raise an error?" md := self methodDictionary. md isNil ifTrue: [^Set new]. ^(md select: [:each | each reads: index - 1]) keys ] whichSelectorsAssign: instVarName [ "Answer a Set of selectors which read the given instance variable" | md index | index := self allInstVarNames indexOf: instVarName asSymbol ifAbsent: [^Set new]. "### should it raise an error?" md := self methodDictionary. md isNil ifTrue: [^Set new]. ^(md select: [:each | each assigns: index - 1]) keys ] whichSelectorsAccess: instVarName [ "Answer a Set of selectors which access the given instance variable" | md index | index := self allInstVarNames indexOf: instVarName asSymbol ifAbsent: [^Set new]. "### should it raise an error?" md := self methodDictionary. md isNil ifTrue: [^Set new]. ^(md select: [:each | each accesses: index - 1]) keys ] whichSelectorsReferTo: anObject [ "Returns a Set of selectors that refer to anObject" | md | md := self methodDictionary. md isNil ifTrue: [^Set new]. ^(md select: [:each | each refersTo: anObject]) keys ] scopeHas: name ifTrue: aBlock [ "If methods understood by the receiver's instances have access to a symbol named 'name', evaluate aBlock" | nameSym | nameSym := name asSymbol. (self allInstVarNames includes: nameSym) ifTrue: [^aBlock value]. (self allClassVarNames includes: nameSym) ifTrue: [^aBlock value]. (self environment includesKey: nameSym) ifTrue: [^aBlock value]. self allSharedPools do: [:dictName | ((self environment at: dictName asGlobalKey) includesKey: nameSym) ifTrue: [^aBlock value]] ] isBits [ "Answer whether my instances' variables are immediate, non-OOP values." ^self shape notNil and: [self isPointers not] ] isPointers [ "Answer whether the instance variables of the receiver's instances are objects" ^(self instanceSpec bitAnd: 31) = 31 ] isIdentity [ "Answer whether x = y implies x == y for instances of the receiver" ^false ] isImmediate [ "Answer whether, if x is an instance of the receiver, x copy == x" ^false ] isFixed [ "Answer whether the receiver's instances have no indexed instance variables" ^self isVariable not ] isVariable [ "Answer whether the receiver's instances have indexed instance variables" ^(self instanceSpec bitAt: 5) ~= 0 ] instSize [ "Answer how many fixed instance variables are reserved to each of the receiver's instances" ^self instanceSpec bitShift: -12 ] includesBehavior: aClass [ "Returns true if aClass is the receiver or a superclass of the receiver." ^self == aClass or: [self inheritsFrom: aClass] ] inheritsFrom: aClass [ "Returns true if aClass is a superclass of the receiver" | sc | aClass isNil ifTrue: [^true]. sc := self. [sc := sc superclass. sc isNil] whileFalse: [sc == aClass ifTrue: [^true]]. ^false ] kindOfSubclass [ "Return a string indicating the type of class the receiver is" self isVariable ifFalse: [^'subclass:']. self isPointers ifTrue: [^'variableSubclass:']. ^'variable: ' , self shape storeString , 'subclass:' ] shapes [ "Used by #shape to map a bitfield to symbolic shapes." ^#(#int8 #byte #character #short #ushort #int #uint #float #int64 #uint64 #double #utf32 nil nil nil #pointer) ] shape: shape [ "Give the provided shape to the receiver's instances. The shape can be nil, or one of #byte #int8 #character #short #word #ushort #int #uint #int64 #uint64 #utf32 #float #double or #pointer. In addition, the special value #inherit means to use the shape of the superclass; note however that this is a static setting, and subclasses that used #inherit are not mutated when the superclass adopts a different shape." | realShape | realShape := shape. shape = #word ifTrue: [realShape := CSymbols.CLongSize = 4 ifTrue: [#uint] ifFalse: [#uint64]]. shape = #inherit ifTrue: [realShape := self superclass isNil ifTrue: [nil] ifFalse: [self superclass shape]]. self shape == realShape ifTrue: [^false]. realShape isNil ifTrue: [ self updateInstanceVars: self allInstVarNames shape: nil ]. self isVariable ifTrue: [SystemExceptions.MutationError signal: 'Cannot change shape of variable class']. "Changing from fixed to variable. No need to mutate the instances." self setInstanceSpec: realShape instVars: self allInstVarNames size ] shape [ "Answer the symbolic shape of my instances." self isVariable ifFalse: [^nil]. ^self shapes at: (instanceSpec bitAnd: 15) + 1 ] allSubclassesDo: aBlock [ "Invokes aBlock for all subclasses, both direct and indirect." subClasses isNil ifTrue: [^self]. subClasses do: [:class | aBlock value: class. class allSubclassesDo: aBlock] ] allSuperclassesDo: aBlock [ "Invokes aBlock for all superclasses, both direct and indirect." | class superclass | class := self. [superclass := class superclass. class := superclass. superclass notNil] whileTrue: [aBlock value: superclass] ] withAllSubclassesDo: aBlock [ "Invokes aBlock for the receiver and all subclasses, both direct and indirect." aBlock value: self. self allSubclassesDo: aBlock ] withAllSuperclassesDo: aBlock [ "Invokes aBlock for the receiver and all superclasses, both direct and indirect." | class | class := self. [aBlock value: class. class := class superclass. class notNil] whileTrue ] allInstancesDo: aBlock [ "Invokes aBlock for all instances of the receiver" | anInstance | anInstance := self someInstance. [anInstance notNil] whileTrue: [aBlock value: anInstance. anInstance := anInstance nextInstance] ] allSubinstancesDo: aBlock [ "Invokes aBlock for all instances of each of the receiver's subclasses." | oopIndex object classes last ok | classes := IdentitySet withAll: self allSubclasses. "Break-even point found by trial and error" classes size < 17 ifTrue: [classes do: [:each | each allInstancesDo: aBlock]. ^self]. "Use a more complicated walk when there are many subclasses." classes := (IdentitySet new: classes size * 3) addAll: classes; yourself. "Get the first OOP. Implementation dependent!" oopIndex := 0 asCharacter asOop. [object := oopIndex asObject. "Simple-minded caching" object class == last ifFalse: [ok := classes includes: (last := object class)]. ok ifTrue: [aBlock value: object]. (oopIndex := oopIndex nextValidOop) isNil] whileFalse ] selectSubclasses: aBlock [ "Return a Set of subclasses of the receiver satisfying aBlock." | aSet | aSet := Set new. self allSubclassesDo: [:subclass | (aBlock value: subclass) ifTrue: [aSet add: subclass]]. ^aSet ] selectSuperclasses: aBlock [ "Return a Set of superclasses of the receiver satisfying aBlock." | aSet | aSet := Set new. self allSuperclassesDo: [:superclass | (aBlock value: superclass) ifTrue: [aSet add: superclass]]. ^aSet ] subclassesDo: aBlock [ "Invokes aBlock for all direct subclasses." subClasses isNil ifTrue: [^self]. subClasses do: aBlock ] methods [ "Don't use this, it's only present to file in from Smalltalk/V" ^self methodsFor: 'no category' ] methodsFor [ "Don't use this, it's only present to file in from Dolphin Smalltalk" ^self methodsFor: 'no category' ] methodsFor: category ifFeatures: features [ "Start compiling methods in the receiver if this implementation of Smalltalk has the given features, else skip the section" ^self methodsFor: category ifTrue: (Smalltalk hasFeatures: features) ] methodsFor: category stamp: notUsed [ "Don't use this, it's only present to file in from Squeak" ^self methodsFor: category ] privateMethods [ "Don't use this, it's only present to file in from IBM Smalltalk" ^self methodsFor: 'private' ] publicMethods [ "Don't use this, it's only present to file in from IBM Smalltalk" ^self methodsFor: 'public' ] article [ "Answer an article (`a' or `an') which is ok for the receiver's name" ^self superclass article ] asClass [ "Answer the first superclass that is a full-fledged Class object" ^self superclass asClass ] environment [ "Answer the namespace that this class belongs to - the same as the superclass, since Behavior does not support namespaces yet." ^self superclass environment ] nameIn: aNamespace [ "Answer the class name when the class is referenced from aNamespace - a dummy one, since Behavior does not support names." ^'' ] securityPolicy [ ^self asClass securityPolicy ] securityPolicy: aSecurityPolicy [ self shouldNotImplement ] printOn: aStream in: aNamespace [ "Answer the class name when the class is referenced from aNamespace - a dummy one, since Behavior does not support names." aStream nextPutAll: (self nameIn: aNamespace) ] name [ "Answer the class name; this prints to the name of the superclass enclosed in braces. This class name is used, for example, to print the receiver." ^'{%1}' % {self asClass} ] newInFixedSpace: numInstanceVariables [ "Create a new instance of a class with indexed instance variables. The instance has numInstanceVariables indexed instance variables. The instance is guaranteed not to move across garbage collections. If a subclass overrides #new:, the changes will apply to this method too." ^(self new: numInstanceVariables) makeFixed ] newInFixedSpace [ "Create a new instance of a class without indexed instance variables. The instance is guaranteed not to move across garbage collections. If a subclass overrides #new, the changes will apply to this method too." ^self new makeFixed ] extractEvalChunk: aStream [ "Private - Extract the code in the next evaluation chunk (i.e. the code until the next bang which is outside string literals or comments)" | code ch | code := WriteStream on: (String new: 100). [aStream atEnd] whileFalse: [ch := aStream next. ch = $! ifTrue: [^code contents]. code nextPut: ch. ch = $" ifTrue: [code nextPutAll: (aStream upTo: ch); nextPut: ch]. ch = $' ifTrue: [ [code nextPutAll: (aStream upTo: ch); nextPut: $'. aStream atEnd not and: [aStream peekFor: ch]] whileTrue: [code nextPut: ch]]]. ^code contents ] instanceSpec [ ^instanceSpec ] setInstanceSpec: shape instVars: anIntegerSize [ | realShape | instanceSpec := anIntegerSize bitShift: 12. shape isNil ifFalse: [realShape := shape = #inherit ifTrue: [self superclass isNil ifTrue: [nil] ifFalse: [self superclass shape]] ifFalse: [shape]. instanceSpec := instanceSpec bitOr: 15 + (self shapes indexOf: realShape ifAbsent: [self error: 'invalid shape value'])] ] sharedPoolDictionaries [ "Return the shared pools (not the names!) defined by the class" ^self superclass sharedPoolDictionaries ] setInstanceVariables: instVariableArray [ instanceVariables := instVariableArray ] validateIdentifier: token [ "Token is a string or string-oid" | firstTime | firstTime := true. token do: [:ch | ch isLetter | (firstTime not and: [ch = $_ | ch isDigit]) ifFalse: [SystemExceptions.InvalidValue signalOn: token reason: 'invalid Smalltalk identifier']. firstTime := false]. ^true ] updateInstanceVars: variableArray shape: shape [ "Update instance variables and instance spec of the class and all its subclasses. variableArray lists the new variables, including inherited ones." ^self updateInstanceVars: variableArray superclass: self superclass shape: shape ] updateInstanceVars: variableArray superclass: newSuper shape: shape [ "Update instance variables and instance spec of the class and all its subclasses. variableArray lists the new variables, including those inherited from newSuper." | instVarMap newInstVars oldInstVars oldClass instances oldSuper | "Find a common superclass." oldSuper := self superclass. newSuper == oldSuper ifFalse: [ [ newSuper includesBehavior: oldSuper ] whileFalse: [ oldSuper := oldSuper superclass ] ]. "Make map for inherited instance variables." oldInstVars := self allInstVarNames. instVarMap := Array new: oldInstVars size. 1 to: oldSuper instSize do: [ :i | instVarMap at: i put: i ]. "Make map for this class's instance variables." newInstVars := variableArray copyFrom: newSuper instSize + 1. oldInstVars from: oldSuper instSize + 1 to: oldInstVars size keysAndValuesDo: [ :index :var | | map | map := newInstVars findLast: [:each | each = var]. map > 0 ifTrue: [instVarMap at: index put: map + newSuper instSize]]. "Fix up all subclasses." self allSubclassesDo: [:sc | | iv | oldClass := Behavior new. oldClass superclass: sc. instances := sc allInstances. instances do: [:each | each changeClassTo: oldClass]. iv := variableArray, (sc allInstVarNames copyFrom: oldInstVars size + 1 to: sc allInstVarNames size). sc setInstanceVariables: iv. sc setInstanceSpec: sc shape instVars: sc allInstVarNames size. "Mutate all instances of the class to conform to new memory model of the class." instances do: [:each | sc mutate: each via: instVarMap]]. "Now update this class' instance vars" oldClass := Behavior new. oldClass superclass: self. instances := self allInstances. instances do: [:each | each changeClassTo: oldClass]. self setInstanceVariables: variableArray. self setInstanceSpec: shape instVars: variableArray size. instances do: [:each | self mutate: each via: instVarMap] ] mutate: object via: instVarMap [ "Private - Mutate object to a new class representation. instVarMap maps from old instVarAt: indices to new instVarAt:put: indices. start is the first instance variable to change." | aCopy mappedValue end adjustment | aCopy := object class isVariable ifTrue: [self basicNew: object basicSize] ifFalse: [self basicNew]. "Copy old instance variables to their new positions using instVarMap." 1 to: instVarMap size do: [:i | mappedValue := instVarMap at: i. mappedValue notNil ifTrue: [aCopy instVarAt: mappedValue put: (object instVarAt: i)]]. "If mutating a subclass, instVarMap is smaller than `object class instSize'; in this case, everything after it must be copied." adjustment := self instSize - object class instSize. instVarMap size + 1 to: object class instSize do: [:i | aCopy instVarAt: i + adjustment put: (object instVarAt: i)]. "Copy the indexed variables, if any." 1 to: object basicSize do: [:i | aCopy basicAt: i put: (object basicAt: i)]. ^object become: aCopy ] isBehavior [ ^true ] debuggerClass [ "Answer which class is to be used to debug a chain of contexts which includes the receiver. nil means 'do not debug'; other classes are sent #debuggingPriority and the one with the highest priority is picked." ^nil ] decompilerClass [ "Answer the class that can be used to decompile methods, or nil if there is none (as is the case now)." ^nil ] evaluatorClass [ "Answer the class that can be used to evaluate doits, or nil if there is none (as is the case now)." ^nil ] parserClass [ "Answer the class that can be used to parse methods, or nil if there is none (as is the case now)." ^nil ] compilerClass [ "Answer the class that can be used to compile parse trees, or nil if there is none (as is the case now). Not used for methods if parserClass answers nil, and for doits if evaluatorClass answers nil." ^nil ] printHierarchy [ "Print my entire subclass hierarchy on the terminal." self printSubclasses: 0 ] printFullHierarchy [ "Print my full hierarchy (i.e. all my superclasses and subclasses) on the terminal." self printSuperclasses: 0; printSubclasses: self allSuperclasses size ] printSuperclasses: level [ "I print all my superclasses, each indented according to its position in the hierarchy. I pass aBlock a class name and a level." | mySuperclass currentLevel | currentLevel := level. self allSuperclasses reverseDo: [:superclass | Transcript space: currentLevel * self hierarchyIndent; nextPutAll: (superclass nameIn: Namespace current); nl. currentLevel := currentLevel + 1] ] printSubclasses: level [ "I print my name, and then all my subclasses, each indented according to its position in the hierarchy. I pass aBlock a class name and a level" | mySubclasses | Transcript space: level * self hierarchyIndent; nextPutAll: (self nameIn: Namespace current); nl. mySubclasses := self subclasses reject: [ :a | a isMetaclass ]. (mySubclasses asSortedCollection: [:a :b | a name <= b name]) do: [:subclass | subclass printSubclasses: level + 1] ] hierarchyIndent [ "Answer the indent to be used by #printHierarchy - 4 by default" ^4 ] flushCache [ "Invalidate the method cache kept by the virtual machine. This message should not need to be called by user programs." ^self primitiveFailed ] basicNewInFixedSpace: numInstanceVariables [ "Create a new instance of a class with indexed instance variables. The instance has numInstanceVariables indexed instance variables. The instance is guaranteed not to move across garbage collections. Like #basicNew:, this method should not be overridden." self isFixed ifTrue: [SystemExceptions.WrongMessageSent signalOn: #basicNewInFixedSpace: useInstead: #basicNewInFixedSpace]. numInstanceVariables isSmallInteger ifTrue: [^self primitiveFailed]. ^SystemExceptions.WrongClass signalOn: numInstanceVariables mustBe: SmallInteger ] basicNewInFixedSpace [ "Create a new instance of a class with no indexed instance variables. The instance is guaranteed not to move across garbage collections. Like #basicNew, this method should not be overridden." self isFixed ifTrue: [^self primitiveFailed]. SystemExceptions.WrongMessageSent signalOn: #basicNewInFixedSpace useInstead: #basicNewInFixedSpace: ] someInstance [ "Private - Answer the first instance of the receiver in the object table" ^nil "return nil on failure" ] methodsFor: category ifTrue: condition [ "Compile the following code inside the receiver, with the given category, if condition is true; else ignore it" ^self primitiveFailed ] primCompile: code [ "Compile the code, a string or readable stream, with no category. Fail if the code does not obey Smalltalk syntax. Answer the generated CompiledMethod if it does. Do not send this in user code; use #compile: or related methods instead." ^self primitiveFailed ] primCompile: code ifError: aBlock [ "As with #primCompile:, but evaluate aBlock (passing the file name, line number and description of the error) if the code does not obey Smalltalk syntax. Do not send this in user code; use #compile:ifError: or related methods instead." ^self primitiveFailed ] scopeDictionary [ "Answer the dictionary that is used when the receiver is before a period in Smalltalk source code." ^self classPool ] ] smalltalk-3.2.5/kernel/BlkClosure.st0000644000175000017500000004260412123404352014325 00000000000000"====================================================================== | | BlockClosure Method Definitions | | ======================================================================" "====================================================================== | | Copyright 1999, 2000, 2001, 2002, 2003, 2007, 2008, 2009 | Free Software Foundation, Inc. | Written by Steve Byrne. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" Object subclass: BlockClosure [ | outerContext block receiver | BlockClosure class >> exceptionHandlerResetBlock [ ^[:context | context at: context numArgs + 1 put: 0] ] BlockClosure class >> exceptionHandlerSearchBlock [ ^ [:context :signal | | best bestGoodness goodness activeHandlers nested | bestGoodness := -1. activeHandlers := context at: context numArgs + 1. context at: context numArgs + 1 put: -1. nested := activeHandlers = -1. nested ifFalse: [1 to: context numArgs - 1 by: 2 do: [:i | goodness := (context at: i) goodness: signal class. goodness > -1 ifTrue: [(activeHandlers bitAt: i) = 1 ifTrue: ["Sorry, this handler is already active..." nested := true. goodness := -1]]. goodness > bestGoodness ifTrue: [best := i. bestGoodness := goodness]]]. "Now instantiate the best handler we found" best isNil ifFalse: [context at: context numArgs + 1 put: (activeHandlers setBit: best). signal onDoBlock: context receiver handlerBlock: (context at: best + 1) onDoContext: context previousState: activeHandlers. #found] ifTrue: [context at: context numArgs + 1 put: activeHandlers. nested ifTrue: [#skip] ifFalse: [nil]]] ] BlockClosure class >> numArgs: args numTemps: temps bytecodes: bytecodes depth: depth literals: literalArray [ "Answer a BlockClosure for a new CompiledBlock that is created using the passed parameters. To make it work, you must put the BlockClosure into a CompiledMethod's literals." ^self block: (CompiledBlock numArgs: args numTemps: temps bytecodes: bytecodes depth: depth literals: literalArray) ] BlockClosure class >> block: aCompiledBlock receiver: anObject outerContext: aContext [ "Answer a BlockClosure that activates the passed CompiledBlock with the given receiver." ^(self new) block: aCompiledBlock; receiver: anObject; outerContext: aContext; yourself ] BlockClosure class >> block: aCompiledBlock receiver: anObject [ "Answer a BlockClosure that activates the passed CompiledBlock with the given receiver." ^(self new) block: aCompiledBlock; receiver: anObject; yourself ] BlockClosure class >> block: aCompiledBlock [ "Answer a BlockClosure that activates the passed CompiledBlock." ^(self new) block: aCompiledBlock; yourself ] BlockClosure class >> isImmediate [ "Answer whether, if x is an instance of the receiver, x copy == x" ^true ] copy [ ^self "We only have one instance" ] deepCopy [ "Answer a shallow copy." ^self shallowCopy "it's about as deep as we need to get" ] asContext: parent [ "Answer a context which will evaluate the receiver without effects on the given context's stack (the return value won't be pushed), as soon as it becomes the VM's thisContext. parent can be nil - in which case reaching the end of the block will probably crash Smalltalk. Note that the block has no home, so it cannot contain returns." ^BlockContext fromClosure: [ | top | top := parent isNil ifTrue: [nil] ifFalse: [ parent sp == 0 ifTrue: [parent receiver] ifFalse: [parent at: parent sp]]. self value. top] parent: parent. ] on: anException do: aBlock [ "Evaluate the receiver; when anException is signaled, evaluate aBlock passing a Signal describing the exception. Answer either the result of evaluating the receiver or the parameter of a Signal>>#return:" | active | active := 0. ^self valueAndResumeOnUnwind ] on: e1 do: b1 on: e2 do: b2 [ "Evaluate the receiver; when e1 or e2 are signaled, evaluate respectively b1 or b2, passing a Signal describing the exception. Answer either the result of evaluating the receiver or the argument of a Signal>>#return:" | active | active := 0. ^self valueAndResumeOnUnwind ] on: e1 do: b1 on: e2 do: b2 on: e3 do: b3 [ "Evaluate the receiver; when e1, e2 or e3 are signaled, evaluate respectively b1, b2 or b3, passing a Signal describing the exception. Answer either the result of evaluating the receiver or the parameter of a Signal>>#return:" | active | active := 0. ^self valueAndResumeOnUnwind ] on: e1 do: b1 on: e2 do: b2 on: e3 do: b3 on: e4 do: b4 [ "Evaluate the receiver; when e1, e2, e3 or e4 are signaled, evaluate respectively b1, b2, b3 or b4, passing a Signal describing the exception. Answer either the result of evaluating the receiver or the parameter of a Signal>>#return:" | active | active := 0. ^self valueAndResumeOnUnwind ] on: e1 do: b1 on: e2 do: b2 on: e3 do: b3 on: e4 do: b4 on: e5 do: b5 [ "Evaluate the receiver; when e1, e2, e3, e4 or e5 are signaled, evaluate respectively b1, b2, b3, b4 or b5, passing a Signal describing the exception. Answer either the result of evaluating the receiver or the parameter of a Signal>>#return:" | active | active := 0. ^self valueAndResumeOnUnwind ] ifError: aBlock [ "Evaluate the receiver; when #error: is called, pass to aBlock the receiver and the parameter, and answer the result of evaluating aBlock. If another exception is raised, it is passed to an outer handler; if no exception is raised, the result of evaluating the receiver is returned." ^self on: Error do: [:sig | sig return: (aBlock cull: sig messageText)] ] ensure: aBlock [ "Evaluate the receiver; when any exception is signaled exit returning the result of evaluating aBlock; if no exception is raised, return the result of evaluating aBlock when the receiver has ended" | result | result := self valueAndResumeOnUnwind. aBlock value. ^result ] ifCurtailed: aBlock [ "Evaluate the receiver; if its execution triggers an unwind which truncates the execution of the block (`curtails' the block), evaluate aBlock. The three cases which can curtail the execution of the receiver are: a non-local return in the receiver, a non-local return in a block evaluated by the receiver which returns past the receiver itself, and an exception raised and not resumed during the execution of the receiver." | curtailed | ^ [| result | curtailed := true. result := self value. curtailed := false. result] ensure: [curtailed ifTrue: [aBlock value]] ] valueWithUnwind [ "Evaluate the receiver. Any errors caused by the block will cause a backtrace, but execution will continue in the method that sent #valueWithUnwind, after that call. Example: [ 1 / 0 ] valueWithUnwind. 'unwind works!' printNl. Important: this method is public, but it is intended to be used in very special cases (as a rule of thumb, use it only when the corresponding C code uses the _gst_prepare_execution_environment and _gst_finish_execution_environment functions). You should usually rely on #ensure: and #on:do:." thisContext mark. ^self value ] repeat [ "Evaluate the receiver 'forever' (actually until a return is executed or the process is terminated)." "When the receiver is a block expression, repeat is optimized by the compiler" [self value] repeat ] whileTrue: aBlock [ "Evaluate the receiver. If it returns true, evaluate aBlock and restart" "When the receiver is a block expression, whileTrue: is optimized by the compiler" [self value] whileTrue: [aBlock value]. ^nil ] whileFalse: aBlock [ "Evaluate the receiver. If it returns false, evaluate aBlock and restart" "When the receiver is a block expression, whileFalse: is optimized by the compiler" [self value] whileFalse: [aBlock value]. ^nil ] whileTrue [ "Evaluate the receiver until it returns false" "When the receiver is a block expression, whileTrue is optimized by the compiler" ^[self value] whileTrue ] whileFalse [ "Evaluate the receiver until it returns true" "When the receiver is a block expression, whileFalse is optimized by the compiler" ^[self value] whileFalse ] fork [ "Create a new process executing the receiver and start it" ^Process on: self at: Processor activePriority suspend: false ] forkAt: priority [ "Create a new process executing the receiver with given priority and start it" ^Process on: self at: priority suspend: false ] newProcess [ "Create a new process executing the receiver in suspended state. The priority is the same as for the calling process. The receiver must not contain returns" ^Process on: self at: Processor activePriority suspend: true ] newProcessWith: anArray [ "Create a new process executing the receiver with the passed arguments, and leave it in suspended state. The priority is the same as for the calling process. The receiver must not contain returns" ^Process on: [self valueWithArguments: anArray] at: Processor activePriority suspend: true ] forkWithoutPreemption [ "Evaluate the receiver in a process that cannot be preempted. If the receiver expect a parameter, pass the current process." | creator | creator := Processor activeProcess. ^Process on: [self cull: creator] at: Processor unpreemptedPriority suspend: false ] valueWithoutInterrupts [ "Evaluate aBlock and delay all interrupts that are requested to the active process during its execution to after aBlock returns." ^Processor activeProcess valueWithoutInterrupts: self ] valueWithoutPreemption [ "Evaluate the receiver with external interrupts disabled. This effectively disables preemption as long as the block does not explicitly yield control, wait on semaphores, and the like." ^ [Processor disableInterrupts. self value] ensure: [Processor enableInterrupts] ] hasMethodReturn [ "Answer whether the block contains a method return" ^self method hasBytecode: 124 between: self initialIP and: self finalIP ] fixTemps [ "This should fix the values of the temporary variables used in the block that are ordinarily shared with the method in which the block is defined. Not defined yet, but it is not harmful that it isn't. Answer the receiver." ^self ] block [ "Answer the CompiledBlock which contains the receiver's bytecodes" ^block ] block: aCompiledBlock [ "Set the CompiledBlock which contains the receiver's bytecodes" block := aCompiledBlock ] finalIP [ "Answer the last instruction that can be executed by the receiver" ^self block size ] initialIP [ "Answer the initial instruction pointer into the receiver." ^1 ] argumentCount [ "Answer the number of arguments passed to the receiver" ^block numArgs ] numArgs [ "Answer the number of arguments passed to the receiver" ^block numArgs ] numTemps [ "Answer the number of temporary variables used by the receiver" ^block numTemps ] stackDepth [ "Answer the number of stack slots needed for the receiver" ^block stackDepth ] method [ "Answer the CompiledMethod in which the receiver lies" ^block method ] receiver [ "Answer the object that is used as `self' when executing the receiver (if nil, it might mean that the receiver is not valid though...)" ^receiver ] receiver: anObject [ "Set the object that is used as `self' when executing the receiver" receiver := anObject ] outerContext [ "Answer the method/block context which is the immediate outer of the receiver" ^outerContext ] outerContext: containingContext [ "Set the method/block context which is the immediate outer of the receiver" outerContext := containingContext ] value [ "Evaluate the receiver passing no parameters" SystemExceptions.WrongArgumentCount signal ] value: arg1 [ "Evaluate the receiver passing arg1 as the only parameter" SystemExceptions.WrongArgumentCount signal ] value: arg1 value: arg2 [ "Evaluate the receiver passing arg1 and arg2 as the parameters" SystemExceptions.WrongArgumentCount signal ] value: arg1 value: arg2 value: arg3 [ "Evaluate the receiver passing arg1, arg2 and arg3 as the parameters" SystemExceptions.WrongArgumentCount signal ] cull: arg1 [ "Evaluate the receiver, passing arg1 as the only parameter if the receiver has parameters." SystemExceptions.WrongArgumentCount signal ] cull: arg1 cull: arg2 [ "Evaluate the receiver, passing arg1 and arg2 as parameters if the receiver accepts them." SystemExceptions.WrongArgumentCount signal ] cull: arg1 cull: arg2 cull: arg3 [ "Evaluate the receiver, passing arg1, arg2 and arg3 as parameters if the receiver accepts them." SystemExceptions.WrongArgumentCount signal ] valueWithArguments: argumentsArray [ "Evaluate the receiver passing argArray's elements as the parameters" argumentsArray isArray ifFalse: [SystemExceptions.WrongClass signalOn: argumentsArray mustBe: Array]. SystemExceptions.WrongArgumentCount signal ] valueAndResumeOnUnwind [ "Private - For use by #ensure:" SystemExceptions.WrongArgumentCount signal ] ] smalltalk-3.2.5/kernel/CFuncs.st0000644000175000017500000001034112123404352013432 00000000000000"====================================================================== | | CFunctionDescriptor Method Definitions | | ======================================================================" "====================================================================== | | Copyright 1988,92,94,95,99,2000,2001,2002,2003,2005,2008 | Free Software Foundation, Inc. | Written by Steve Byrne. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" CCallable subclass: CFunctionDescriptor [ | cFunctionName | CFunctionDescriptor class >> for: funcName returning: returnTypeSymbol withArgs: argsArray [ "Answer a CFunctionDescriptor with the given function name, return type and arguments. funcName must be a String." ^(super for: nil returning: returnTypeSymbol withArgs: argsArray) name: funcName; yourself ] CFunctionDescriptor class >> addressOf: function [ "Answer the address (CObject) of the function which is registered (on the C side) with the given name, or zero if no such a function is registered." ^CObject new ] CFunctionDescriptor class >> isFunction: function [ "Answer whether a function is registered (on the C side) with the given name." ^(self addressOf: function) address ~= 0 ] name [ "Answer the name of the function (on the C side) represented by the receiver" ^cFunctionName ] name: aString [ "Set the name of the function (on the C side) represented by the receiver" cFunctionName := aString ] link [ "Make the address of the function point to the registered address." self address: (CFunctionDescriptor addressOf: self name) address. ] printOn: aStream [ "Print a representation of the receiver onto aStream" aStream print: self class; nextPut: $(. self name isNil ifFalse: [ aStream nextPutAll: self name ]. self address = 0 ifFalse: [ self name isNil ifFalse: [ aStream nextPutAll: ' @ ' ]. aStream nextPutAll: (self address printStringRadix: 16) ]. aStream nextPut: $) ] ] SystemDictionary extend [ system: aString withArguments: args [ ^self system: aString % (args collect: [ :string | string withShellEscapes ]) ] system: aString [ ] getenv: aString [ ] environ [ ] putenv: aString [ ] getArgc [ ] getArgv: index [ ] ] smalltalk-3.2.5/kernel/CallinProcess.st0000644000175000017500000000550112123404352015014 00000000000000"====================================================================== | | CallinProcess Method Definitions | | ======================================================================" "====================================================================== | | Copyright 2002 Free Software Foundation, Inc. | Written by Paolo Bonzini. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" Process subclass: CallinProcess [ | returnedValue | returnContext [ "Return the base context in the process, i.e. the one that is responsible for passing the return value to C." | context | context := self context. [ context parentContext isNil ] whileFalse: [ context := context parentContext ]. ^context ] detach [ "Continue running the receiver as a normal Process, and return nil from the callin." | p | self isActive ifFalse: [ ^SystemExceptions.InvalidState signalOn: self reason: 'process not active' ]. p := Process basicNew. "Skip suspendedContext, priority, myList" Link instSize + 4 to: Process instSize do: [ :i | p instVarAt: i put: (self instVarAt: i) ]. "Start executing the detached process from here." p instVarNamed: #priority put: priority. p suspendedContext: thisContext copy. Processor activeProcess == self ifTrue: [ "This only runs in the CallinProcess." thisContext parentContext: self returnContext. p resume. ^nil ] ] ] smalltalk-3.2.5/kernel/Association.st0000644000175000017500000000713212123404352014531 00000000000000"====================================================================== | | Association Method Definitions | | ======================================================================" "====================================================================== | | Copyright 1988,92,94,95,99,2000,2001,2002 | Free Software Foundation, Inc. | Written by Steve Byrne. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" LookupKey subclass: Association [ | value | Association class >> key: aKey value: aValue [ "Answer a new association with the given key and value" ^self new key: aKey value: aValue ] environment [ "Answer nil. This is present to achieve polymorphism with instances of VariableBinding." ^nil ] environment: aNamespace [ "Do nothing. This is present to achieve polymorphism with instances of VariableBinding." ] value: aValue [ "Set the association's value to aValue" value := aValue ] key: aKey value: aValue [ "Set the association's key to aKey, and its value to aValue" key := aKey. value := aValue ] value [ "Answer the association's value" ^value ] = anAssociation [ "Answer whether the association's key and value are the same as anAssociation's, or false if anAssociation is not an Association. As a special case, identical values are considered equal even if #= returns false (as is the case for NaN floating-point values)." self class == anAssociation class ifFalse: [^false]. self key = anAssociation key ifFalse: [^false]. self value == anAssociation value ifTrue: [^true]. ^self value = anAssociation value ] hash [ "Answer an hash value for the receiver" ^key hash bitXor: value hash ] printOn: aStream [ "Put on aStream a representation of the receiver" self key printOn: aStream. aStream nextPutAll: '->'. self value printOn: aStream ] storeOn: aStream [ "Put on aStream some Smalltalk code compiling to the receiver" aStream nextPut: $(. aStream store: self class. aStream nextPutAll: ' key: '. self key storeOn: aStream. aStream nextPutAll: ' value: '. self value storeOn: aStream. aStream nextPut: $) ] mourn [ "Finalize the receiver" self key: nil value: nil ] ] smalltalk-3.2.5/kernel/Array.st0000644000175000017500000000746212123404352013341 00000000000000"====================================================================== | | Array Method Definitions | | ======================================================================" "====================================================================== | | Copyright 1988,92,94,95,99,2000,2001,2008,2009 | Free Software Foundation, Inc. | Written by Steve Byrne. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" ArrayedCollection subclass: Array [ Array class >> from: anArray [ "Answer anArray, which is expected to be an array specified with a brace-syntax expression per my inherited protocol." ^anArray ] at: anIndex ifAbsent: aBlock [ "Answer the index-th indexed instance variable of the receiver" ^self checkIndexableBounds: anIndex ifAbsent: aBlock ] printOn: aStream [ "Print a representation for the receiver on aStream" aStream nextPut: $(. self do: [:elt | elt printOn: aStream. aStream space]. aStream nextPut: $) ] isLiteralObject [ "Answer whether the receiver is expressible as a Smalltalk literal." ^self isReadOnly not ] replaceFrom: start to: stop with: byteArray startingAt: replaceStart [ "Replace the characters from start to stop with new characters whose ASCII codes are contained in byteArray, starting at the replaceStart location of byteArray" ^super replaceFrom: start to: stop with: byteArray startingAt: replaceStart ] storeLiteralOn: aStream [ "Store a Smalltalk literal compiling to the receiver on aStream" self class == Array ifFalse: [ ^super storeLiteralOn: aStream ]. aStream nextPut: $#. aStream nextPut: $(. self do: [:elt | elt storeLiteralOn: aStream. aStream space]. aStream nextPut: $) ] storeOn: aStream [ "Store Smalltalk code compiling to the receiver on aStream" self class == Array ifFalse: [ ^super storeOn: aStream ]. self storeLiteralOn: aStream. self isReadOnly ifFalse: [aStream nextPutAll: ' copy'] ] multiBecome: anArray [ "Transform every object in the receiver in each corresponding object in anArray. anArray and the receiver must have the same size" | index | index := 0. ^self collect: [:object | index := index + 1. object become: (anArray at: index)] ] isArray [ ^true ] ] smalltalk-3.2.5/kernel/Memory.st0000644000175000017500000002147512123404352013533 00000000000000"====================================================================== | | Memory definitions | | ======================================================================" "====================================================================== | | Copyright 1988,92,94,95,99,2000,2001,2003 | Free Software Foundation, Inc. | Written by Steve Byrne. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" Object subclass: Memory [ Memory class >> at: anAddress [ "Access the Smalltalk object (OOP) at the given address." ^self type: 9 at: anAddress ] Memory class >> bigEndian [ "Answer whether we're running on a big- or little-endian system." ^Bigendian ] Memory class >> charAt: anAddress [ "Access the C char at the given address. The value is returned as a Smalltalk Character." ^self type: 0 at: anAddress ] Memory class >> unsignedCharAt: anAddress [ "Access the C unsigned char at the given address. The value is returned as a Smalltalk Character." ^self type: 1 at: anAddress ] Memory class >> shortAt: anAddress [ "Access the C short int at the given address." ^self type: 2 at: anAddress ] Memory class >> unsignedShortAt: anAddress [ "Access the C unsigned short int at the given address." ^self type: 3 at: anAddress ] Memory class >> longAt: anAddress [ "Access the C long int at the given address." ^self type: 4 at: anAddress ] Memory class >> unsignedLongAt: anAddress [ "Access the C unsigned long int at the given address." ^self type: 5 at: anAddress ] Memory class >> intAt: anAddress [ "Access the C int at the given address." ^self type: 10 at: anAddress ] Memory class >> unsignedIntAt: anAddress [ "Access the C unsigned int at the given address." ^self type: 11 at: anAddress ] Memory class >> floatAt: anAddress [ "Access the C float at the given address." ^self type: 6 at: anAddress ] Memory class >> doubleAt: anAddress [ "Access the C double at the given address." ^self type: 7 at: anAddress ] Memory class >> longDoubleAt: anAddress [ "Access the C long double at the given address." ^self type: 12 at: anAddress ] Memory class >> stringAt: anAddress [ "Access the string pointed by the C `char *' at the given given address." ^self type: 8 at: anAddress ] Memory class >> deref: anAddress [ "Access the C int pointed by the given address" ^self intAt: anAddress ] Memory class >> at: anAddress put: aValue [ "Store a pointer (OOP) to the Smalltalk object identified by `value' at the given address." ^self type: 9 at: anAddress put: aValue ] Memory class >> intAt: anAddress put: aValue [ "Store the Smalltalk Integer object identified by `value', at the given address, using sizeof(int) bytes." ^self type: 10 at: anAddress put: aValue ] Memory class >> unsignedIntAt: anAddress put: aValue [ "Store the Smalltalk Integer object identified by `value', at the given address, using sizeof(int) bytes." ^self type: 11 at: anAddress put: aValue ] Memory class >> uintAt: anAddress put: aValue [ "Store the Smalltalk Integer object identified by `value', at the given address, using sizeof(int) bytes." ^self type: 11 at: anAddress put: aValue ] Memory class >> charAt: anAddress put: aValue [ "Store as a C char the Smalltalk Character or Integer object identified by `value', at the given address, using sizeof(char) bytes - i.e. 1 byte." ^self type: 0 at: anAddress put: aValue ] Memory class >> unsignedCharAt: anAddress put: aValue [ "Store as a C char the Smalltalk Character or Integer object identified by `value', at the given address, using sizeof(char) bytes - i.e. 1 byte." ^self type: 1 at: anAddress put: aValue ] Memory class >> ucharAt: anAddress put: aValue [ "Store as a C char the Smalltalk Character or Integer object identified by `value', at the given address, using sizeof(char) bytes - i.e. 1 byte." ^self type: 1 at: anAddress put: aValue ] Memory class >> shortAt: anAddress put: aValue [ "Store the Smalltalk Integer object identified by `value', at the given address, using sizeof(short) bytes." ^self type: 2 at: anAddress put: aValue ] Memory class >> unsignedShortAt: anAddress put: aValue [ "Store the Smalltalk Integer object identified by `value', at the given address, using sizeof(short) bytes." ^self type: 3 at: anAddress put: aValue ] Memory class >> ushortAt: anAddress put: aValue [ "Store the Smalltalk Integer object identified by `value', at the given address, using sizeof(short) bytes." ^self type: 3 at: anAddress put: aValue ] Memory class >> longAt: anAddress put: aValue [ "Store the Smalltalk Integer object identified by `value', at the given address, using sizeof(long) bytes." ^self type: 4 at: anAddress put: aValue ] Memory class >> unsignedLongAt: anAddress put: aValue [ "Store the Smalltalk Integer object identified by `value', at the given address, using sizeof(long) bytes." ^self type: 5 at: anAddress put: aValue ] Memory class >> ulongAt: anAddress put: aValue [ "Store the Smalltalk Integer object identified by `value', at the given address, using sizeof(long) bytes." ^self type: 5 at: anAddress put: aValue ] Memory class >> floatAt: anAddress put: aValue [ "Store the Smalltalk Float object identified by `value', at the given address, writing it like a C float." ^self type: 6 at: anAddress put: aValue ] Memory class >> doubleAt: anAddress put: aValue [ "Store the Smalltalk Float object identified by `value', at the given address, writing it like a C double." ^self type: 7 at: anAddress put: aValue ] Memory class >> longDoubleAt: anAddress put: aValue [ "Store the Smalltalk Float object identified by `value', at the given address, writing it like a C long double." ^self type: 12 at: anAddress put: aValue ] Memory class >> stringAt: anAddress put: aValue [ "Store the Smalltalk String object identified by `value', at the given address in memory, writing it like a *FRESHLY ALLOCATED* C string. It is the caller's responsibility to free it if necessary." ^self type: 8 at: anAddress put: aValue ] Memory class >> type: aType at: anAddress [ "Returns a particular type object from memory at anAddress" ^self primitiveFailed ] Memory class >> type: aType at: anAddress put: aValue [ "Sets the memory location anAddress to aValue" ^self primitiveFailed ] ] smalltalk-3.2.5/kernel/MthContext.st0000644000175000017500000001213212123404352014346 00000000000000"====================================================================== | | MethodContext Method Definitions | | ======================================================================" "====================================================================== | | Copyright 1988,92,94,95,99,2000,2001,2002,2007,2008 | Free Software Foundation, Inc. | Written by Steve Byrne. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" ContextPart subclass: MethodContext [ | flags | printOn: aStream [ "Print a representation for the receiver on aStream" self printOn: aStream line: self currentLineInFile ] printOn: aStream line: line [ "Print a representation for the receiver on aStream, using the given line number and printing aString before the method name." self receiver class printOn: aStream in: Namespace current. self receiver class == self methodClass ifFalse: [aStream nextPut: $(. self methodClass printOn: aStream in: Namespace current. aStream nextPut: $)]. aStream nextPutAll: '>>'; nextPutAll: self selector. self selector = #doesNotUnderstand: ifTrue: [aStream space; print: (self at: 1) selector]. aStream nextPutAll: ' ('; display: self currentFileName; nextPut: $:; display: line; nextPut: $). self isDisabled ifTrue: [aStream nextPutAll: ' '] ] isInternalExceptionHandlingContext [ "Answer whether the receiver is a context that should be hidden to the user when presenting a backtrace. Such contexts are identified through the #exceptionHandlingInternal: attribute: if there is such a context in the backtrace, all those above it are marked as internal. That is, the attribute being set to true means that the context and all those above it are to be hidden, while the attribute being set to false means that the contexts above it must be hidden, but not the context itself." | attr | attr := self method attributeAt: #exceptionHandlingInternal: ifAbsent: [nil]. attr isNil ifFalse: [^attr arguments at: 1]. self scanBacktraceForAttribute: #exceptionHandlingInternal: do: [:ctx :attr | ^true]. ^false ] isDisabled [ "Answers whether the receiver has actually ended execution and will be skipped when doing a return. BlockContexts are removed from the chain whenever a non-local return is done, but MethodContexts need to stay there in case there is a non-local return from the #ensure: block." flags isInteger ifFalse: [^false]. ^flags == 1 ] isUnwind [ "Answers whether the context must continue execution even after a non-local return (a return from the enclosing method of a block, or a call to the #continue: method of ContextPart). Such contexts are created only by #ensure:." flags isInteger ifFalse: [^false]. ^(flags bitAnd: 2) == 2 ] isEnvironment [ "To create a valid execution environment for the interpreter even before it starts, GST creates a fake context which invokes a special ``termination'' method. Such a context can be used as a marker for the current execution environment. Answer whether the receiver is that kind of context." flags isInteger ifFalse: [^false]. ^(flags bitAnd: 4) == 4 ] mark [ "To create a valid execution environment for the interpreter even before it starts, GST creates a fake context which invokes a special ``termination'' method. A similar context is created by #valueWithUnwind, by using this method." flags := flags bitOr: 4 ] sender [ "Return the context from which the receiver was sent" ^self parentContext ] home [ "Answer the MethodContext to which the receiver refers (i.e. the receiver itself)" ^self ] isBlock [ "Answer whether the receiver is a block context" ^false ] ] smalltalk-3.2.5/kernel/Number.st0000644000175000017500000007117012123404352013510 00000000000000"====================================================================== | | Number Method Definitions | | ======================================================================" "====================================================================== | | Copyright 1988,92,94,95,99,2000,2001,2002,2007,2008,2009 | Free Software Foundation, Inc. | Written by Steve Byrne. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" Magnitude subclass: Number [ Number class >> coerce: aNumber [ "Answer aNumber - whatever class it belongs to, it is good" aNumber class == Fraction ifTrue: [ ^aNumber asFloatD ]. ^aNumber ] Number class >> readFrom: aStream radix: anInteger [ "Answer the number read from the rest of aStream, converted to an instance of the receiver. If the receiver is number, the class of the result is undefined -- but the result is good. The exponent (for example 1.2e-1) is only parsed if anInteger is 10." | c sgn int intexp frac exp isfloat | isfloat := false. sgn := 1. int := 0. intexp := 1. c := aStream peek. c isNil ifTrue: [ ^0 ]. c = $- ifTrue: [ sgn := -1. aStream next. ]. c := aStream peek. c isNil ifTrue: [ ^0 ]. c := c asUppercase. ((c isDigit: anInteger) or: [ c = $. ]) ifFalse: [ ^0 ]. [ c notNil and: [ c := c asUppercase. c isDigit: anInteger ] ] whileTrue: [ aStream next. int := sgn * c digitValue + (int * anInteger). c := aStream peek ]. c isNil ifTrue: [ ^int ]. c = $. ifTrue: [ aStream next. isfloat := true. [ c := aStream peek. c notNil and: [ c := c asUppercase. c isDigit: anInteger ] ] whileTrue: [ sgn := sgn / anInteger. int := sgn * c digitValue + int. aStream next ] ]. exp := 0. (anInteger = 10 and: [c = $E]) ifFalse: [ ^isfloat ifTrue: [ int asFloat ] ifFalse: [ int ] ]. aStream next. c := aStream peek. c isNil ifTrue: [ ^int ]. sgn := 1. c = $+ ifTrue: [ sgn := 1. aStream next ]. c = $- ifTrue: [ sgn := -1. aStream next ]. [ c := aStream peek. c notNil and: [ c isDigit ] ] whileTrue: [ exp := c digitValue + (exp * 10). aStream next ]. int := int * (10 raisedToInteger: exp * sgn). ^int asFloat ] Number class >> readFrom: aStream [ "Answer the number read from the rest of aStream, converted to an instance of the receiver. If the receiver is number, the class of the result is undefined -- but the result is good." ^self readFrom: aStream radix: 10 ] Number class >> isImmediate [ "Answer whether, if x is an instance of the receiver, x copy == x" ^true ] shallowCopy [ "Return the receiver - it's an immediate (immutable) object" ^self ] deepCopy [ "Return the receiver - it's an immediate (immutable) object" ^self ] asNumber [ "Answer the receiver, since it is already a number" ^self ] asString [ "Answer the receiver's #displayString, which should be a good enough conversion to String for a number." ^self displayString ] degreesToRadians [ "Convert the receiver to radians" ^self asFloatD / 57.29577951308232 ] radiansToDegrees [ "Convert the receiver from radians to degrees" ^self asFloatD * 57.29577951308232 ] coerce: aNumber [ "Answer aNumber, converted to an integer or floating-point number." aNumber class == Fraction ifTrue: [ ^aNumber asFloatD ]. ^aNumber ] zero [ "Coerce 0 to the receiver's class. The default implementation works, but is inefficient" ^self coerce: 0 ] unity [ "Coerce 1 to the receiver's class. The default implementation works, but is inefficient" ^self coerce: 1 ] generality [ "Answer the receiver's generality" self subclassResponsibility ] asScaledDecimal: n [ "Answer the receiver, converted to a ScaledDecimal object." ^ScaledDecimal newFromNumber: self asFraction scale: n ] asScaledDecimal: denDigits radix: base scale: n [ "Answer the receiver, divided by base^denDigits and converted to a ScaledDecimal object." ^ScaledDecimal newFromNumber: self asFraction * (base raisedToInteger: denDigits) scale: n ] asCNumber [ "Convert the receiver to a kind of number that is understood by the C call-out mechanism." self subclassResponsibility ] asFloat [ "Convert the receiver to an arbitrary subclass of Float" ^self asFloatD ] asFloatD [ self subclassResponsibility ] asFloatE [ self subclassResponsibility ] asFloatQ [ self subclassResponsibility ] asFraction [ self subclassResponsibility ] asExactFraction [ "Return the receiver, converted to a Fraction retaining the exact value of the receiver." ^self asFraction ] retryError [ "Raise an error---a retrying method was called with two arguments having the same generality." ^self error: 'retry:coercing: called with arguments of the same generality' ] retry: aSymbol coercing: aNumber [ "Coerce to the other number's class the one number between the receiver and aNumber which has the lowest, and retry calling aSymbol. aSymbol is supposed not to be #= or #~= (since those don't fail if aNumber is not a Number)." | selfGen aNumGen | selfGen := self generality. aNumGen := aNumber generality. selfGen > aNumGen ifTrue: [^self perform: aSymbol with: (self coerce: aNumber)]. selfGen < aNumGen ifTrue: [^(aNumber coerce: self) perform: aSymbol with: aNumber]. self retryError ] retryRelationalOp: aSymbol coercing: aNumber [ "Coerce to the other number's class the one number between the receiver and aNumber which has the lowest, and retry calling aSymbol (<, <=, >, >=)." | delta | delta := self retryDifferenceCoercing: aNumber. "Avoids a #perform: which is usually more expensive -- all the comparisons below are inlined by both the compiler and the interpreter" aSymbol == #< ifTrue: [^delta < delta zero]. aSymbol == #<= ifTrue: [^delta <= delta zero]. aSymbol == #>= ifTrue: [^delta >= delta zero]. aSymbol == #> ifTrue: [^delta > delta zero]. self error: 'bad relational operator' ] retryEqualityCoercing: aNumber [ "Coerce to the other number's class the one number between the receiver and aNumber which has the lowest, and retry calling #=." | selfGen aNumGen | (aNumber isKindOf: Number) ifFalse: [^false]. selfGen := self generality. aNumGen := aNumber generality. aNumGen isNil ifTrue: [^false]. selfGen > aNumGen ifTrue: [^self = (self coerce: aNumber)]. selfGen < aNumGen ifTrue: [^(aNumber coerce: self) = aNumber]. self retryError ] retryInequalityCoercing: aNumber [ "Coerce to the other number's class the one number between the receiver and aNumber which has the lowest, and retry calling #~=." | selfGen aNumGen | (aNumber isKindOf: Number) ifFalse: [^true]. selfGen := self generality. aNumGen := aNumber generality. aNumGen isNil ifTrue: [^true]. selfGen > aNumGen ifTrue: [^false == (self = (self coerce: aNumber))]. selfGen < aNumGen ifTrue: [^false == ((aNumber coerce: self) = aNumber)]. self retryError ] retrySumCoercing: aNumber [ "Coerce to the other number's class the one number between the receiver and aNumber which has the lowest, and retry calling #+." | selfGen aNumGen | selfGen := self generality. aNumGen := aNumber generality. aNumGen isNil ifTrue: [^aNumber sumFromNumber: self]. selfGen > aNumGen ifTrue: [^self + (self coerce: aNumber)]. selfGen < aNumGen ifTrue: [^(aNumber coerce: self) + aNumber]. self retryError ] retryDifferenceCoercing: aNumber [ "Coerce to the other number's class the one number between the receiver and aNumber which has the lowest, and retry calling #-." | selfGen aNumGen | selfGen := self generality. aNumGen := aNumber generality. aNumGen isNil ifTrue: [^aNumber differenceFromNumber: self]. selfGen > aNumGen ifTrue: [^self - (self coerce: aNumber)]. selfGen < aNumGen ifTrue: [^(aNumber coerce: self) - aNumber]. self retryError ] retryMultiplicationCoercing: aNumber [ "Coerce to the other number's class the one number between the receiver and aNumber which has the lowest, and retry calling #*." | selfGen aNumGen | selfGen := self generality. aNumGen := aNumber generality. aNumGen isNil ifTrue: [^aNumber productFromNumber: self]. selfGen > aNumGen ifTrue: [^self * (self coerce: aNumber)]. selfGen < aNumGen ifTrue: [^(aNumber coerce: self) * aNumber]. self retryError ] retryDivisionCoercing: aNumber [ "Coerce to the other number's class the one number between the receiver and aNumber which has the lowest, and retry calling #/." | selfGen aNumGen | selfGen := self generality. aNumGen := aNumber generality. selfGen > aNumGen ifTrue: [^self / (self coerce: aNumber)]. selfGen < aNumGen ifTrue: [^(aNumber coerce: self) / aNumber]. self retryError ] + aNumber [ "Sum the receiver and aNumber, answer the result" self subclassResponsibility ] - aNumber [ "Subtract aNumber from the receiver, answer the result" self subclassResponsibility ] * aNumber [ "Subtract the receiver and aNumber, answer the result" self subclassResponsibility ] / aNumber [ "Divide the receiver by aNumber, answer the result (no loss of precision). Raise a ZeroDivide exception or return a valid (possibly infinite) continuation value if aNumber is zero." self subclassResponsibility ] // aNumber [ "Return the integer quotient of dividing the receiver by aNumber with truncation towards negative infinity. Raise a ZeroDivide exception if aNumber is zero" aNumber = 0 ifTrue: [self zeroDivide]. ^(self / aNumber) floor ] \\ aNumber [ "Return the remainder of dividing the receiver by aNumber with truncation towards negative infinity. Raise a ZeroDivide exception if aNumber is zero" aNumber = 0 ifTrue: [self zeroDivide]. ^self - (self // aNumber * aNumber) ] quo: aNumber [ "Return the integer quotient of dividing the receiver by aNumber with truncation towards zero. Raise a ZeroDivide exception if aNumber is zero" aNumber = 0 ifTrue: [self zeroDivide]. ^(self / aNumber) truncated ] rem: aNumber [ "Return the remainder of dividing the receiver by aNumber with truncation towards zero. Raise a ZeroDivide exception if aNumber is zero" ^self - ((self quo: aNumber) * aNumber) ] integerPart [ "Answer the receiver, truncated towards zero" ^self truncated ] fractionPart [ "Answer a number which, summed to the #integerPart of the receiver, gives the receiver itself." ^self - self integerPart ] asInteger [ "Answer the receiver, rounded to the nearest integer" ^self rounded ] truncated [ "Answer the receiver, truncated towards zero" ^self subclassResponsibility ] truncateTo: aNumber [ "Answer the receiver, truncated towards zero to a multiple of aNumber" ^(self coerce: (self quo: aNumber)) * aNumber ] rounded [ "Returns the integer nearest the receiver" ^self negative ifTrue: [(self - (self unity / 2)) ceiling] ifFalse: [(self + (self unity / 2)) floor] ] roundTo: aNumber [ "Answer the receiver, truncated to the nearest multiple of aNumber" ^(self coerce: (self / aNumber) rounded) * aNumber ] closeTo: num [ "Answer whether the receiver can be considered sufficiently close to num (this is done by checking equality if num is not a number, and by checking with 0.01% tolerance if num is a number)." "Shortcut common cases. But the first one is also needed so that FloatD infinity closeTo: FloatD infinity!" self = num ifTrue: [^true]. num isNumber ifFalse: [^false]. self = self zero ifTrue: [^num abs < 0.0001]. num = num zero ifTrue: [^self abs < 0.0001]. ^(self - num) abs / (self abs max: num abs) <= 0.0001 ] isExact [ "Answer whether the receiver performs exact arithmetic. Most numeric classes do (in fact the only exceptions is Float and its descendants), so the default is to answer true rather than calling #subclassResponsibility." ^true ] isNaN [ "Answer whether the receiver is a Not-A-Number. Most numeric classes don't handle nans, so the default is to answer false rather than calling #subclassResponsibility." ^false ] isFinite [ "Answer whether the receiver represents a finite quantity. Most numeric classes are for finite quantities, so the default is to answer true rather than calling #subclassResponsibility." ^true ] isInfinite [ "Answer whether the receiver represents an infinite quantity. Most numeric classes are for finite quantities, so the default is to answer false rather than calling #subclassResponsibility." ^false ] isRational [ "Answer whether the receiver is rational - false by default" ^false ] isNumber [ ^true ] negative [ "Answer whether the receiver is < 0" ^self < self zero ] positive [ "Answer whether the receiver is >= 0" ^self >= self zero ] strictlyPositive [ "Answer whether the receiver is > 0" ^self > self zero ] sign [ "Returns the sign of the receiver." self < self zero ifTrue: [^-1]. self > self zero ifTrue: [^1]. ^0 ] even [ "Returns true if self is divisible by 2" ^self truncated even ] odd [ "Returns true if self is not divisible by 2" ^self truncated odd ] min: aNumber [ "Answer the minimum between the receiver and aNumber. Redefine in subclasses if necessary to ensure that if either self or aNumber is a NaN, it is always answered." "If both self and aNumber are zero, return aNumber in case it has a negative sign, because we assume our zero is positive. If the test is false, always answer aNumber in case it is a NaN, because we assume that self is not a NaN." ^aNumber > self ifTrue: [self] ifFalse: [aNumber] ] max: aNumber [ "Answer the maximum between the receiver and aNumber. Redefine in subclasses if necessary to ensure that if either self or aNumber is a NaN, it is always answered." "If both self and aNumber are zero, return self in case aNumber has a negative sign, because we assume our zero is positive. If the test is false, always answer aNumber in case it is a NaN, because we assume that self is not a NaN." ^aNumber <= self ifTrue: [self] ifFalse: [aNumber] ] positiveDifference: aNumber [ "Answer the positive difference of the receiver and aNumber, that is self - aNumber if it is positive, 0 otherwise." | diff | diff := self - aNumber. diff isNaN ifTrue: [^diff]. ^diff negative ifTrue: [diff zero] ifFalse: [diff] ] squared [ "Answer the square of the receiver" ^self * self ] abs [ "Answer the absolute value of the receiver" ^self > self zero ifTrue: [self] ifFalse: [self negated] ] negated [ "Answer the negated of the receiver" ^self zero - self ] sin [ "Answer the sine of the receiver" ^self asFloatD sin ] cos [ "Answer the cosine of the receiver" ^self asFloatD cos ] tan [ "Answer the tangent of the receiver" ^self asFloatD tan ] arcSin [ "Answer the arc sine of the receiver" ^self asFloatD arcSin ] arcCos [ "Answer the arc cosine of the receiver" ^self asFloatD arcCos ] arcTan [ "Answer the arc tangent of the receiver" ^self asFloatD arcTan ] arcTan: x [ "Answer the angle (measured counterclockwise) between (x, self) and a ray starting in (0, 0) and moving towards (1, 0) - i.e. 3 o'clock" | result | x = 0 ifTrue: ["Always adopt the most general number representation of pi. If none of the number is a floating point number, go with a FloatD." ^self generality < x generality ifTrue: [x generality < 0.0e generality ifTrue: [FloatD pi * self sign / 2] ifFalse: [x class pi * self sign / 2]] ifFalse: [self generality < 0.0e generality ifTrue: [FloatD pi * self sign / 2] ifFalse: [self class pi * self sign / 2]]]. result := (self / x) arcTan. ^x < 0 ifFalse: [result] ifTrue: [result > result zero ifFalse: [result + result class pi] ifTrue: [result - result class pi]] ] cosh [ "Answer the hyperbolic cosine of the receiver." ^(self exp + self negated exp) / 2 ] sinh [ "Answer the hyperbolic sine of the receiver." ^(self exp - self negated exp) / 2 ] tanh [ "Answer the hyperbolic tangent of the receiver." | ep en | ep := self exp. en := self negated exp. ^(ep - en) / (ep + en) ] arcCosh [ "Answer the hyperbolic arc-cosine of the receiver." ^(self + (self squared - 1) sqrt) ln ] arcSinh [ "Answer the hyperbolic arc-sine of the receiver." ^(self + (self squared + 1) sqrt) ln ] arcTanh [ "Answer the hyperbolic arc-tangent of the receiver." ^((1 + self) / (1 - self)) ln / 2 ] sqrt [ "Answer the square root of the receiver" ^self asFloatD sqrt ] exp [ "Answer e raised to the receiver" ^self asFloatD exp ] ln [ "Answer log base e of the receiver" ^self asFloatD ln ] estimatedLog [ "Answer an estimate of (self abs floorLog: 10). This method should be overridden by subclasses, but Number's implementation does not raise errors - simply, it gives a correct result, so it is slow." ^self abs floorLog: 10 ] log [ "Answer log base 10 of the receiver" ^self asFloatD ln / FloatD ln10 ] log: aNumber [ "Answer log base aNumber of the receiver" ^self asFloatD ln / aNumber asFloatD ln ] floorLog: radix [ "Answer (self log: radix) floor. Optimized to answer an integer." | me that answer | self < self zero ifTrue: [^self arithmeticError: 'cannot extract logarithm of a negative number']. radix <= radix unity ifTrue: [radix <= radix zero ifTrue: [^self arithmeticError: 'bad radix']. radix = radix unity ifTrue: [^self arithmeticError: 'bad radix']. ^(self ceilingLog: radix reciprocal) negated]. answer := -1. self < self unity ifTrue: [me := self. [me := me * radix. me < me unity] whileTrue: [answer := answer - 1]] ifFalse: [that := 1. [that <= self] whileTrue: [that := that * radix. answer := answer + 1]]. ^answer ] ceilingLog: radix [ "Answer (self log: radix) ceiling. Optimized to answer an integer." | me that answer | self < self zero ifTrue: [^self arithmeticError: 'cannot extract logarithm of a negative number']. radix <= radix unity ifTrue: [radix <= radix zero ifTrue: [^self arithmeticError: 'bad radix']. radix = radix unity ifTrue: [^self arithmeticError: 'bad radix']. ^(self floorLog: radix reciprocal) negated]. answer := 0. self < self unity ifTrue: [me := self. [me := me * radix. me <= me unity] whileTrue: [answer := answer - 1]] ifFalse: [that := 1. [that < self] whileTrue: [that := that * radix. answer := answer + 1]]. ^answer ] raisedTo: aNumber [ "Return self raised to aNumber power" aNumber isInteger ifTrue: [^self raisedToInteger: aNumber]. ^aNumber generality > 1.0d generality ifTrue: [(aNumber coerce: self) raisedTo: aNumber] ifFalse: [self asFloatD raisedTo: aNumber asFloatD] ] raisedToInteger: anInteger [ "Return self raised to the anInteger-th power" "Some special cases first" anInteger isInteger ifFalse: [SystemExceptions.WrongClass signalOn: anInteger mustBe: Integer]. anInteger < 0 ifTrue: [^self reciprocal raisedToInteger: 0 - anInteger]. anInteger = 0 ifTrue: [ self = self zero ifTrue: [self arithmeticError: 'invalid operands']. ^self unity]. anInteger = 1 ifTrue: [^self]. "Fire the big loop." ^self raisedToInteger: anInteger withCache: ((Array new: (255 min: anInteger)) at: 1 put: self; yourself) ] withSignOf: aNumber [ "Answer the receiver, with its sign possibly changed to match that of aNumber." ^aNumber positive == self positive ifTrue: [self] ifFalse: [self negated] ] floor [ "Return the integer nearest the receiver toward negative infinity." | selfTruncated | selfTruncated := self truncated. "If positive, truncation to zero is what we want." self >= self zero ifTrue: [^selfTruncated]. "Must be negative." self = (self coerce: selfTruncated) ifTrue: [^selfTruncated] ifFalse: [^selfTruncated - 1] ] reciprocal [ "Return the reciprocal of the receiver" self = self zero ifTrue: [self zeroDivide] ifFalse: [^self unity / self] ] to: stop [ "Return an interval going from the receiver to stop by 1" ^Interval from: self to: stop ] to: stop by: step [ "Return an interval going from the receiver to stop with the given step" ^Interval from: self to: stop by: step ] to: stop by: step do: aBlock [ "Evaluate aBlock for each value in the interval going from the receiver to stop with the given step. Compiled in-line for integer literal steps, and for one-argument aBlocks without temporaries, and therefore not overridable." | i | i := self. step > step zero ifTrue: [[i <= stop] whileTrue: [aBlock value: i. i := i + step]] ifFalse: [[i >= stop] whileTrue: [aBlock value: i. i := i + step]]. ^stop ] to: stop do: aBlock [ "Evaluate aBlock for each value in the interval going from the receiver to stop by 1. Compiled in-line for one-argument aBlocks without temporaries, and therefore not overridable." | i | i := self. [i <= stop] whileTrue: [aBlock value: i. i := i + self unity] ] to: stop collect: aBlock [ "Evaluate aBlock for each value in the interval going from the receiver to stop by 1. The results are collected in an Array and returned." | size result i j | size := (stop - self) truncated + 1 max: 0. result := Array new: size. i := self. j := 1. [j <= size] whileTrue: [result at: j put: (aBlock value: i). i := i + self unity. j := j + 1]. ^result ] to: stop by: step collect: aBlock [ "Evaluate aBlock for each value in the interval going from the receiver to stop with the given step. The results are collected in an Array and returned." | size result i j | size := step > 0 ifTrue: [stop >= self ifTrue: [(stop - self) // step + 1] ifFalse: [0]] ifFalse: [self >= stop ifTrue: [(stop - self) // step + 1] ifFalse: [0]]. result := Array new: size. i := self. j := 1. [j <= size] whileTrue: [result at: j put: (aBlock value: i). i := i + step. j := j + 1]. ^result ] arithmeticError: message [ self error: message ] zeroDivide [ self error: 'cannot divide by zero' ] raisedToInteger: n withCache: cache [ "Internal implementation of #raisedToInteger:." "For very big numbers, remove the rightmost bit." | result index | n > 255 ifTrue: [result := self raisedToInteger: n // 2 withCache: cache. ^(n bitAnd: 1) = 0 ifTrue: [result squared] ifFalse: [result * (result * self)]]. "Else, use a table with the optimal choice of k so that self^k * self^(n - k) does as few multiplications as possible." result := cache at: n. result isNil ifTrue: [index := self powerTable at: n. result := (self raisedToInteger: n - index withCache: cache) * (self raisedToInteger: index withCache: cache). cache at: n put: result]. ^result ] powerTable [ "Internal table for #raisedToInteger:withCache:. Example: (powerTable at: 9) == 6 means that n^9 is best computed as n^3 * n^6. From Knuth's Seminumerical Algorithms." ^#[0 1 2 2 3 3 4 4 6 5 6 6 10 7 9 8 16 9 16 10 12 11 13 12 17 13 18 14 24 15 26 16 17 17 19 18 33 19 26 20 25 21 40 22 27 23 44 24 32 25 34 26 29 27 44 28 31 29 34 30 60 31 36 32 64 33 34 34 46 35 37 36 65 37 50 38 48 39 69 40 49 41 43 42 51 43 58 44 64 45 47 46 59 47 76 48 65 49 66 50 67 51 66 52 70 53 74 54 104 55 74 56 64 57 69 58 78 59 68 60 61 61 80 62 75 63 68 64 65 65 128 66 129 67 90 68 73 69 131 70 94 71 88 72 128 73 98 74 132 75 121 76 102 77 124 78 132 79 106 80 97 81 160 82 99 83 134 84 86 85 95 86 160 87 100 88 113 89 98 90 107 91 122 92 111 93 102 94 126 95 150 96 128 97 130 98 133 99 195 100 128 101 123 102 164 103 138 104 145 105 146 106 109 107 149 108 200 109 146 110 170 111 157 112 128 113 130 114 182 115 132 116 200 117 132 118 158 119 206 120 240 121 162 122 147 123 152 124 166 125 214 126 138 127 153] "1 - 7" "8 - 15" "16 - 23" "24 - 31" "32 - 39" "40 - 47" "48 - 55" "56 - 63" "64 - 71" "72 - 79" "80 - 87" "88 - 95" "96 - 103" "104 - 111" "112 - 119" "120 - 127" "128 - 135" "136 - 143" "144 - 151" "152 - 159" "160 - 167" "168 - 175" "176 - 183" "184 - 191" "192 - 199" "200 - 207" "208 - 215" "216 - 223" "224 - 231" "232 - 239" "240 - 247" "248 - 255" ] ] smalltalk-3.2.5/kernel/DirMessage.st0000644000175000017500000001143512130343734014305 00000000000000"====================================================================== | | DirectedMessage Method Definitions | | ======================================================================" "====================================================================== | | Copyright 1999, 2000, 2001, 2002, 2008 Free Software Foundation, Inc. | Written by Paolo Bonzini. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" Message subclass: DirectedMessage [ | receiver | DirectedMessage class >> selector: aSymbol arguments: anArray [ self shouldNotImplement ] DirectedMessage class >> receiver: anObject selector: aSymbol [ "Create a new instance of the receiver" ^(super selector: aSymbol arguments: #()) receiver: anObject ] DirectedMessage class >> receiver: receiverObject selector: aSymbol argument: argumentObject [ "Create a new instance of the receiver" ^(super selector: aSymbol argument: argumentObject) receiver: receiverObject ] DirectedMessage class >> receiver: anObject selector: aSymbol arguments: anArray [ "Create a new instance of the receiver" ^(super selector: aSymbol arguments: anArray) receiver: anObject ] DirectedMessage class >> selector: aSymbol arguments: anArray receiver: anObject [ "Create a new instance of the receiver" ^(super selector: aSymbol arguments: anArray) receiver: anObject ] printOn: aStream [ "Print a representation of the receiver on aStream" aStream print: receiver; space. super printOn: aStream ] send [ "Send the message" ^self sendTo: receiver ] value [ "Send the message (this message provides interoperability between DirectedMessages and blocks)" ^self sendTo: receiver ] value: anObject [ "Send the message with the sole argument anObject (this message provides interoperability between DirectedMessages and blocks)" ^receiver perform: self selector with: anObject ] value: obj1 value: obj2 [ "Send the message with the arguments obj1 and obj2 (this message provides interoperability between DirectedMessages and blocks)" ^receiver perform: self selector with: obj1 with: obj2 ] valueWithArguments: anArray [ "Send the message with the arguments replaced by anArray (this message provides interoperability between DirectedMessages and blocks)" ^receiver perform: self selector withArguments: anArray ] receiver: anObject [ "Change the receiver" receiver := anObject ] receiver [ "Answer the receiver" ^receiver ] fork [ "Create a new process executing the receiver and start it" ^Process on: self at: Processor activePriority suspend: false ] forkAt: priority [ "Create a new process executing the receiver with given priority and start it" ^Process on: self at: priority suspend: false ] newProcess [ "Create a new process executing the receiver in suspended state. The priority is the same as for the calling process. The receiver must not contain returns" ^Process on: self at: Processor activePriority suspend: true ] reconstructOriginalObject [ "This method is used when DirectedMessages are used together with PluggableProxies (see ObjectDumper). It sends the receiver to reconstruct the object that was originally stored." ^self send ] ] smalltalk-3.2.5/kernel/DLD.st0000644000175000017500000002221112123404352012653 00000000000000"====================================================================== | | Dynamic Loader Method Definitions | | ======================================================================" "====================================================================== | | Copyright 1992,94,95,99,2000,2001,2002,2003,2005,2008,2009 | Free Software Foundation, Inc. | Written by Steve Byrne. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" Namespace current: Kernel [ Stream subclass: RoundRobinStream [ | stream first last | RoundRobinStream class >> test: s get: n [ n timesRepeat: [s next print]. Transcript nl ] RoundRobinStream class >> test: s leaveAfter: n [ | i | i := 0. s do: [:each | each print. (i := i + 1) = n ifTrue: [Transcript nl. ^nil]]. Transcript nl ] RoundRobinStream class >> testOn: anArray [ "RoundRobinStream testOn: #(1 2 3 4 5 6)" | s | s := RoundRobinStream on: anArray readStream. self test: s get: anArray size + 1. self test: s get: anArray size + 1. self test: s get: (anArray size + 1) * 2. self test: s get: 2. self test: s leaveAfter: anArray size + 1. self test: s leaveAfter: anArray size + 1. self test: s leaveAfter: 1. self test: s leaveAfter: 1. self test: s leaveAfter: 2. self test: s leaveAfter: 2. self test: s leaveAfter: anArray size + 1. self test: s leaveAfter: anArray size + 1. Transcript nl ] RoundRobinStream class >> on: aStream [ ^self new stream: aStream ] stream [ ^stream ] stream: aStream [ stream := aStream ] atEnd [ stream atEnd ifTrue: [stream reset. "If there is no established first, we started iterating from the first element in the stream." first isNil ifTrue: [^true]]. ^(last := stream peek) == first ] next [ ^self atEnd ifTrue: [SystemExceptions.EndOfStream signalOn: self] ifFalse: [stream next] ] do: aBlock [ "Iterate on all the items in the Stream. If it is not the first iteration, and the last item was retrieved with #next or passed to a #do: block *that did a global return*, return from there." stream atEnd ifTrue: [stream reset. stream atEnd ifTrue: [^self]]. "Establish the item at which we'll stop iterating. Start from that one." last isNil ifTrue: [last := stream next]. first := last. aBlock value: last. super do: aBlock. "Make sure we will not restart from the last item we passed to aBlock, because aBlock did not return." last := nil ] ] ] Object subclass: DLD [ DLD class [ | libraryList libraryStream moduleList | ] DLD class >> linkFile: aFileName [ "Private-used by addLibrary: and addModule:." ] DLD class >> library: libHandle getFunc: aFuncString [ "Private-used for library searches." ] DLD class >> defineCFunc: aName as: aFuncAddr [ "Register aFuncAddr as the target for cCalls to aName." ] DLD class >> defineExternFunc: aFuncName [ "This method calls #primDefineExternFunc: to try to link to a function with the given name, and answers whether the linkage was successful. You can redefine this method to restrict the ability to do dynamic linking." ^self primDefineExternFunc: aFuncName ] DLD class >> primDefineExternFunc: aFuncName [ "This method tries to link to a function with the given name, and answers whether the linkage was successful. It should not be overridden." | couldNotLink | libraryStream do: [:lib | | funcAddr | lib value notNil ifTrue: [funcAddr := self library: lib value getFunc: aFuncName. funcAddr notNil ifTrue: [self defineCFunc: aFuncName as: funcAddr. ^true]]]. ^false ] DLD class >> initialize [ "Private - Initialize the receiver's class variables" libraryList := OrderedCollection new. libraryStream := Kernel.RoundRobinStream on: libraryList readStream. moduleList := OrderedCollection new. ] DLD class >> update: aspect [ "Called on startup - Make DLD re-link and reset the addresses of all the externally defined functions" | notLoaded | aspect == #returnFromSnapshot ifFalse: [^self]. libraryList := libraryList reject: [:lib | lib key isNil]. libraryList do: [:lib | lib value: (self linkFile: lib key)]. notLoaded := WriteStream on: Array new. moduleList do: [:each | (self linkFile: each) isNil ifTrue: [notLoaded nextPut: each]]. notLoaded := notLoaded contents. notLoaded isEmpty ifFalse: [SystemExceptions.CInterfaceError signal: 'modules ' , notLoaded printString , ' could not be loaded.'] ] DLD class >> libraryList [ "Answer a copy of the search path of libraries to be used by DLD" ^(libraryList select: [:each | each key notNil]) collect: [:each | each key] ] DLD class >> moduleList [ "Answer a copy of the modules reloaded when the image is started" ^moduleList copy ] DLD class >> addLibrary: library [ "Add library to the search path of libraries to be used by DLD." (libraryList anySatisfy: [:anAssociation | anAssociation key = library]) ifFalse: [libraryList add: library -> (self linkFile: library). libraryStream := Kernel.RoundRobinStream on: libraryList readStream] ] DLD class >> addLibraryHandle: libraryHandle [ "This is called internally by gst_dlopen. The library will be open and put in the search path." libraryList add: nil -> libraryHandle. libraryStream := Kernel.RoundRobinStream on: libraryList readStream ] DLD class >> addModule: library [ "Add library to the list of modules to be loaded when the image is started. The gst_initModule function in the library is called, but the library will not be put in the search path used whenever a C function is requested but not registered." (moduleList includes: library) ifFalse: [(self linkFile: library) isNil ifTrue: [SystemExceptions.CInterfaceError signal: 'requested module ' , library , ' was not found'] ifFalse: [moduleList add: library]] ] ] CFunctionDescriptor class extend [ addressOf: function [ "Answer whether a function is registered (on the C side) with the given name or is dynamically loadable." ^(DLD defineExternFunc: function) ifTrue: [self addressOf: function] "Try again." ifFalse: [CObject new] ] ] Eval [ DLD initialize ] smalltalk-3.2.5/kernel/Fraction.st0000644000175000017500000003375612123404352014035 00000000000000"====================================================================== | | Class Fraction Definitions | | ======================================================================" "====================================================================== | | Copyright 1992,94,95,99,2000,2001,2002,2008,2009 | Free Software Foundation, Inc. | Written by David Duke. | Slightly modified by Steve Byrne and Paolo Bonzini. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" Number subclass: Fraction [ | numerator denominator | Zero := nil. One := nil. Fraction class >> coerce: aNumber [ "Answer aNumber converted to a Fraction" ^aNumber asExactFraction ] Fraction class >> initialize [ "Initialize the receiver's class variables" Zero := self numerator: 0 denominator: 1. One := self numerator: 1 denominator: 1 ] Fraction class >> numerator: nInteger denominator: dInteger [ "Answer a new instance of fraction (nInteger/dInteger)" ^self new setNumerator: nInteger setDenominator: dInteger ] denominator [ "Answer the receiver's denominator" ^denominator ] numerator [ "Answer the receiver's numerator" ^numerator ] * aNumber [ "Multiply two numbers and answer the result." | num den gcd | aNumber generality = self generality ifFalse: [^self retryMultiplicationCoercing: aNumber]. aNumber numerator = 0 ifTrue: [^aNumber]. self numerator = 0 ifTrue: [^self]. num := numerator * aNumber numerator. den := denominator * aNumber denominator. aNumber == self ifFalse: [gcd := (numerator gcd: aNumber denominator) * (denominator gcd: aNumber numerator). num := num divExact: gcd. den := den divExact: gcd]. den = 1 ifTrue: [^num]. ^Fraction numerator: num denominator: den ] + aNumber [ "Sum two numbers and answer the result." | gcd num den | aNumber generality = self generality ifFalse: [^self retrySumCoercing: aNumber]. gcd := denominator gcd: aNumber denominator. gcd == 1 ifTrue: [^Fraction numerator: numerator * aNumber denominator + (aNumber numerator * denominator) denominator: denominator * aNumber denominator]. num := numerator * (aNumber denominator divExact: gcd) + (aNumber numerator * (denominator divExact: gcd)). den := denominator * aNumber denominator divExact: gcd. "Compute a GCD on smaller operands" gcd := num gcd: den. num := num divExact: gcd. den := den divExact: gcd. den = 1 ifTrue: [^num]. ^Fraction numerator: num denominator: den ] - aNumber [ "Subtract aNumber from the receiver and answer the result." | gcd num den | aNumber generality = self generality ifFalse: [^self retryDifferenceCoercing: aNumber]. gcd := denominator gcd: aNumber denominator. gcd == 1 ifTrue: [^Fraction numerator: numerator * aNumber denominator - (aNumber numerator * denominator) denominator: denominator * aNumber denominator]. num := numerator * (aNumber denominator divExact: gcd) - (aNumber numerator * (denominator divExact: gcd)). den := denominator * aNumber denominator divExact: gcd. "Compute a GCD on smaller operands" gcd := num gcd: den. num := num divExact: gcd. den := den divExact: gcd. den = 1 ifTrue: [^num]. ^Fraction numerator: num denominator: den ] / aNumber [ "Divide the receiver by aNumber and answer the result." | num den gcd | aNumber generality = self generality ifFalse: [^self retryDivisionCoercing: aNumber]. aNumber numerator = 0 ifTrue: [^self zeroDivide]. self numerator = 0 ifTrue: [^self]. num := numerator * aNumber denominator. den := denominator * aNumber numerator. gcd := (numerator gcd: aNumber numerator) * (denominator gcd: aNumber denominator). num := num divExact: gcd. den := den divExact: gcd. den = 1 ifTrue: [^num]. ^Fraction numerator: num denominator: den ] // aNumber [ "Return the integer quotient of dividing the receiver by aNumber with truncation towards negative infinity." ^(self / aNumber) floor ] \\ aNumber [ "Return the remainder from dividing the receiver by aNumber, (using //)." ^self - (self // aNumber * aNumber) ] estimatedLog [ "Answer an estimate of (self abs floorLog: 10)" ^numerator estimatedLog - denominator estimatedLog ] zero [ "Coerce 0 to the receiver's class" ^Zero ] unity [ "Coerce 1 to the receiver's class" ^One ] coerce: aNumber [ "Coerce aNumber to the receiver's class" ^aNumber asExactFraction ] generality [ "Return the receiver's generality" ^300 ] floor [ "Truncate the receiver towards negative infinity and return the truncated result" ^numerator // denominator ] ceiling [ "Truncate the receiver towards positive infinity and return the truncated result" ^(numerator + denominator - 1) // denominator ] truncated [ "Truncate the receiver and return the truncated result" ^numerator quo: denominator ] < arg [ "Test if the receiver is less than arg." arg generality = self generality ifFalse: [^self retryRelationalOp: #< coercing: arg]. ^(self compare: arg) < 0 ] <= arg [ "Test if the receiver is less than or equal to arg." arg generality = self generality ifFalse: [^self retryRelationalOp: #<= coercing: arg]. ^(self compare: arg) <= 0 ] > arg [ "Test if the receiver is more than arg." arg generality = self generality ifFalse: [^self retryRelationalOp: #> coercing: arg]. ^(self compare: arg) > 0 ] >= arg [ "Test if the receiver is greater than or equal to arg." arg generality = self generality ifFalse: [^self retryRelationalOp: #>= coercing: arg]. ^(self compare: arg) >= 0 ] = arg [ "Test if the receiver equals arg." (arg isKindOf: Number) ifFalse: [^false]. arg generality = self generality ifFalse: [^self retryEqualityCoercing: arg]. ^self numerator = arg numerator and: [self denominator = arg denominator] ] hash [ "Answer an hash value for the receiver" denominator = 1 ifTrue: [^numerator hash]. ^self asFloatD hash ] compare: arg [ "Answer an integer <, >, = 0 depending on the ordering between the receiver and arg." "Comparing numbers with different signs, we just care about that; canonical form further restricts the check to the numerator." | n1 n2 delta | self numerator sign = arg numerator sign ifFalse: [^numerator sign - arg numerator sign]. n1 := numerator abs. n2 := arg numerator abs. "The first line is (n1 * d2) highBit +/- 1, and similarly for the second." delta := numerator abs highBit + arg denominator highBit - arg numerator abs highBit - denominator highBit. delta < -1 ifTrue: [^delta * numerator sign]. delta > 1 ifTrue: [^delta * numerator sign]. "Cross multiply and compare. Sending #* to the denominators is faster because they cannot be LargeNegativeIntegers." ^(arg denominator * numerator - (denominator * arg numerator)) sign ] isRational [ "Answer whether the receiver is rational - true" ^true ] integerPart [ "Answer the integer part of the receiver, expressed as a Fraction" ^Fraction numerator: self truncated denominator: 1 ] asCNumber [ "Convert the receiver to a kind of number that is understood by the C call-out mechanism." ^self asFloat: FloatD ] asFloatD [ "Answer the receiver converted to a FloatD" ^self asFloat: FloatD ] asFloatE [ "Answer the receiver converted to a FloatD" ^self asFloat: FloatE ] asFloatQ [ "Answer the receiver converted to a FloatD" ^self asFloat: FloatQ ] asExactFraction [ "Answer the receiver, it is already a Fraction" ^self ] asFraction [ "Answer the receiver, it is already a Fraction" ^self ] printOn: aStream [ "Print a representation of the receiver on aStream" aStream print: numerator; nextPut: $/; print: denominator ] storeOn: aStream [ "Store Smalltalk code compiling to the receiver on aStream" aStream nextPutAll: '(Fraction numerator: '; store: numerator; nextPutAll: ' denominator: '; store: denominator; nextPut: $) ] asFloat: characterization [ "Answer the receiver converted to a Float" "Answer the receiver converted to a Float" | n d sign hn hd hq nBits q q1 r exponent floatExponent | sign := numerator sign * denominator sign. n := numerator abs. d := denominator abs. hn := n highBit. hd := d highBit. "If both numerator and denominator are represented exactly in floating point number, then fastest thing to do is to use hardwired float division" nBits := characterization precision + 1. (hn < nBits and: [hd < nBits]) ifTrue: [^(characterization coerce: numerator) / (characterization coerce: denominator)]. "Try and obtain a mantissa with characterization precision + 1 bits by integer division. Additional bit is a helper for rounding mode. First guess is rough, we might get one more bit or one less" exponent := hn - hd - nBits. exponent > 0 ifTrue: [d := d bitShift: exponent] ifFalse: [n := n bitShift: exponent negated]. q := n quo: d. r := n - (q * d). hq := q highBit. "check for gradual underflow, in which case we should use less bits" floatExponent := exponent + hq. floatExponent >= (characterization emin - 1) ifFalse: [nBits := nBits + floatExponent - characterization emin + 1]. "Use exactly nBits" hq > nBits ifTrue: [exponent := exponent + hq - nBits. r := (q bitAnd: (1 bitShift: hq - nBits) - 1) * d + r. q := q bitShift: nBits - hq]. hq < nBits ifTrue: [exponent := exponent + hq - nBits. q1 := (r bitShift: nBits - hq) quo: d. q := (q bitShift: nBits - hq) bitAnd: q1. r := (r bitShift: nBits - hq) - (q1 * d)]. "check if we should round upward. The case of exact half (q bitAnd: 1) = 1 & (r = 0) will be handled by Integer>>asFloat:" ((q bitAnd: 1) = 0 or: [r = 0]) ifFalse: [q := q + 1]. "build the Float" ^(sign > 0 ifTrue: [characterization coerce: q] ifFalse: [(characterization coerce: q) negated]) timesTwoPower: exponent ] reduce [ "Reduce the fraction." | gcd | numerator = 1 ifTrue: [^self]. denominator = 1 ifTrue: [^numerator]. numerator = 0 ifTrue: [^0]. numerator = denominator ifTrue: [^1]. gcd := numerator gcd: denominator. gcd = 1 ifTrue: [^self]. denominator = gcd ifTrue: [^numerator divExact: gcd]. numerator := numerator divExact: gcd. denominator := denominator divExact: gcd. ^self ] setNumerator: numInteger setDenominator: denInteger [ "Set the fraction's numerator and denominator" denInteger = 0 ifTrue: [^numInteger zeroDivide]. denInteger < 0 ifTrue: [numerator := numInteger negated. denominator := denInteger negated] ifFalse: [numerator := numInteger. denominator := denInteger] ] negated [ "Return the receiver, with its sign changed." ^Fraction numerator: 0 - numerator denominator: denominator ] raisedToInteger: anInteger [ "Return self raised to the anInteger-th power." "No need to reduce" anInteger < 0 ifTrue: [^self reciprocal raisedToInteger: 0 - anInteger]. ^Fraction numerator: (numerator raisedToInteger: anInteger) denominator: (denominator raisedToInteger: anInteger) ] reciprocal [ "Return the reciprocal of the receiver" denominator < 0 ifTrue: [^Fraction numerator: denominator negated denominator: numerator negated] ifFalse: [^Fraction numerator: denominator denominator: numerator] ] sqrt [ "Return the square root of the receiver." | n d | n := numerator sqrt. d := denominator sqrt. "If both are integers the gcd is known to be 1, don't use n/d straight." (n isInteger and: [ d isInteger ]) ifFalse: [ ^n / d ]. ^Fraction numerator: n denominator: d ] squared [ "Return the square of the receiver." ^Fraction numerator: numerator squared denominator: denominator squared ] ] smalltalk-3.2.5/kernel/ScaledDec.st0000644000175000017500000002260612123404352014067 00000000000000"====================================================================== | | ScaledDecimal Method Definitions | | ======================================================================" "====================================================================== | | Copyright 2000, 2001, 2002, 2003, 2008 Free Software Foundation, Inc. | Written by Paolo Bonzini. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" Number subclass: ScaledDecimal [ | fraction scale | ScaledDecimal class >> newFromNumber: aNumber scale: scale [ "Answer a new instance of ScaledDecimal, representing a decimal fraction with a decimal representation considered valid up to the scale-th digit." ^(self basicNew) setFraction: aNumber asFraction scale: scale; yourself ] one [ "Answer the receiver's representation of one." ^self class newFromNumber: 1 scale: scale ] zero [ "Answer the receiver's representation of zero." ^self class newFromNumber: 0 scale: scale ] fractionPart [ "Answer the fractional part of the receiver." ^ScaledDecimal newFromNumber: fraction fractionPart scale: scale ] integerPart [ "Answer the fractional part of the receiver." ^ScaledDecimal newFromNumber: fraction integerPart scale: scale ] truncated [ "Answer the receiver, converted to an Integer and truncated towards -infinity." ^fraction truncated ] ceiling [ "Answer the receiver, converted to an Integer and truncated towards +infinity." ^fraction ceiling ] asCNumber [ "Convert the receiver to a kind of number that is understood by the C call-out mechanism." ^self asFloatD ] asFloatD [ "Answer the receiver, converted to a FloatD" ^fraction asFloatD ] asFloatE [ "Answer the receiver, converted to a FloatE" ^fraction asFloatE ] asFloatQ [ "Answer the receiver, converted to a FloatQ" ^fraction asFloatQ ] asFraction [ "Answer the receiver, converted to a Fraction" | num denom gcd | denom := 10 raisedToInteger: scale. num := fraction numerator * denom quo: fraction denominator. gcd := num gcd: denom. ^Fraction numerator: (num divExact: gcd) denominator: (denom divExact: gcd) ] coerce: aNumber [ "Answer aNumber, converted to a ScaledDecimal with the same scale as the receiver." ^ScaledDecimal newFromNumber: aNumber asFraction scale: scale ] generality [ "Return the receiver's generality" ^250 ] + aNumber [ "Sum two numbers and answer the result." aNumber generality = self generality ifTrue: [^ScaledDecimal newFromNumber: fraction + aNumber fraction scale: (scale max: aNumber scale)] ifFalse: [^self retrySumCoercing: aNumber] ] - aNumber [ "Subtract aNumber from the receiver and answer the result." aNumber generality = self generality ifTrue: [^ScaledDecimal newFromNumber: fraction - aNumber fraction scale: (scale max: aNumber scale)] ifFalse: [^self retryDifferenceCoercing: aNumber] ] * aNumber [ "Multiply two numbers and answer the result." aNumber generality = self generality ifTrue: [^ScaledDecimal newFromNumber: fraction * aNumber fraction scale: (scale max: aNumber scale)] ifFalse: [^self retryMultiplicationCoercing: aNumber] ] / aNumber [ "Divide two numbers and answer the result." aNumber generality = self generality ifTrue: [^ScaledDecimal newFromNumber: fraction / aNumber fraction scale: (scale max: aNumber scale)] ifFalse: [^self retryDivisionCoercing: aNumber] ] \\ aNumber [ "Answer the remainder after integer division the receiver by aNumber with truncation towards negative infinity." aNumber generality = self generality ifTrue: [^ScaledDecimal newFromNumber: fraction \\ aNumber fraction scale: (scale max: aNumber scale)] ifFalse: [^self retry: #\\ coercing: aNumber] ] // aNumber [ "Answer the integer quotient after dividing the receiver by aNumber with truncation towards negative infinity." ^fraction // aNumber ] < aNumber [ "Answer whether the receiver is less than arg." aNumber generality = self generality ifTrue: [^(self compare: aNumber) < 0] ifFalse: [^self retryRelationalOp: #< coercing: aNumber] ] <= aNumber [ "Answer whether the receiver is less than or equal to arg." aNumber generality = self generality ifTrue: [^(self compare: aNumber) <= 0] ifFalse: [^self retryRelationalOp: #<= coercing: aNumber] ] > aNumber [ "Answer whether the receiver is greater than arg." aNumber generality = self generality ifTrue: [^(self compare: aNumber) > 0] ifFalse: [^self retryRelationalOp: #> coercing: aNumber] ] >= aNumber [ "Answer whether the receiver is greater than or equal to arg." aNumber generality = self generality ifTrue: [^(self compare: aNumber) >= 0] ifFalse: [^self retryRelationalOp: #>= coercing: aNumber] ] = arg [ "Answer whether the receiver is equal to arg." (arg isKindOf: Number) ifFalse: [^false]. arg generality = self generality ifTrue: [^(self compare: arg) = 0] ifFalse: [^self retryEqualityCoercing: arg] ] ~= arg [ "Answer whether the receiver is not equal arg." (arg isKindOf: Number) ifFalse: [^true]. arg generality = self generality ifTrue: [^(self compare: arg) ~= 0] ifFalse: [^self retryInequalityCoercing: arg] ] hash [ "Answer an hash value for the receiver." ^fraction hash ] displayOn: aStream [ "Print a representation of the receiver on aStream, intended to be directed to a user. In this particular case, the `scale' part of the #printString is not emitted." | aFraction fracDigits | self < 0 ifTrue: [aStream nextPut: $-]. aFraction := fraction abs. aStream nextPutAll: aFraction truncated printString. scale = 0 ifTrue: [^self]. aStream nextPut: $.. fracDigits := aFraction fractionPart. scale timesRepeat: [fracDigits := fracDigits * 10. aStream nextPut: (Character digitValue: fracDigits truncated). fracDigits := fracDigits fractionPart] ] printOn: aStream [ "Print a representation of the receiver on aStream." self displayOn: aStream. aStream nextPut: $s. scale printOn: aStream ] isLiteralObject [ "Answer whether the receiver is expressible as a Smalltalk literal." ^true ] storeLiteralOn: aStream [ "Store on aStream some Smalltalk code which compiles to the receiver" self storeOn: aStream ] storeOn: aStream [ "Print Smalltalk code that compiles to the receiver on aStream." self printOn: aStream ] fraction [ "Private - Answer to full precision the fraction that the receiver represents." ^fraction ] compare: arg [ "Private - Answer a Number that is the receiver - arg, truncated to a number of digits equal to the minimum of our scale and aScaledDecimal's." ^((fraction - arg fraction) * (10 raisedToInteger: (self scale min: arg scale))) rounded ] scale [ "Private - Answer a integer which represents the total number of digits used to represent the fraction part of the receiver, including trailing zeroes." ^scale ] setFraction: theFraction scale: theScale [ "Private - Set the fraction to theFraction and the total number of digits used to represent the fraction part of the receiver, including trailing zeroes, to the Integer theScale." fraction := theFraction. scale := theScale ] ] smalltalk-3.2.5/kernel/CompildMeth.st0000644000175000017500000005107312123404352014465 00000000000000"====================================================================== | | CompiledMethod Method Definitions | | ======================================================================" "====================================================================== | | Copyright 1988,92,94,95,99,2000,2001,2002,2003,2005,2008,2009 | Free Software Foundation, Inc. | Written by Steve Byrne. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" CompiledCode subclass: CompiledMethod [ | descriptor | CompiledMethod class >> literals: lits numArgs: numArg numTemps: numTemp attributes: attrArray bytecodes: bytecodes depth: depth [ "Answer a full fledged CompiledMethod. Construct the method header from the parameters, and set the literals and bytecodes to the provided ones. Also, the bytecodes are optimized and any embedded CompiledBlocks modified to refer to these literals and to the newly created CompiledMethod." attrArray inject: false into: [:found :each | each arguments size ~= each selector numArgs ifTrue: [SystemExceptions.VerificationError signal: 'invalid number of arguments']. each selector == #primitive: ifFalse: [found] ifTrue: [found ifTrue: [SystemExceptions.VerificationError signal: 'duplicate primitive declaration']. (each arguments first class == SmallInteger and: [each arguments first strictlyPositive]) ifFalse: [SystemExceptions.VerificationError signal: 'invalid primitive declaration']. true]] ] CompiledMethod class >> numArgs: args [ "Create a user-defined method (one that is sent #valueWithReceiver:withArguments: when it is invoked) with numArgs arguments. This only makes sense when called for a subclass of CompiledMethod." args isInteger ifFalse: [SystemExceptions.WrongClass signalOn: args mustBe: Integer]. (args between: 0 and: 31) ifFalse: [SystemExceptions.ArgumentOutOfRange signalOn: args mustBeBetween: 0 and: 31]. ^(self new) initialize; header: (6 bitShift: 27) + args literals: #() ] CompiledMethod class >> cCall: descr numArgs: numArgs attributes: attributesArray [ "Return a CompiledMethod corresponding to a #cCall:returning:args: pragma with the given arguments." | literals bytecodes | "One of these: descr callInto: nil. ^self ^(descr callInto: ValueHolder now) value ^(descr callInto: ValueHolder now) value narrow" descr returnType == #void ifTrue: [literals := {descr}. bytecodes := #[179 1 45 0 30 34 66 0]] ifFalse: [literals := {descr. #{ValueHolder}}. bytecodes := (descr returnType isKindOf: CType) ifTrue: [#[179 1 34 1 30 84 30 34 22 0 30 35 51 0]] ifFalse: [#[179 1 34 1 30 84 30 34 22 0 51 0]]]. ^self literals: literals numArgs: numArgs numTemps: 0 attributes: attributesArray bytecodes: bytecodes depth: numArgs + 4 ] CompiledMethod class >> asyncCCall: descr numArgs: numArgs attributes: attributesArray [ "Return a CompiledMethod corresponding to a #asyncCCall:args: pragma with the given arguments." | literals bytecodes | "descr asyncCall. ^self" literals := {descr. #asyncCall}. bytecodes := #[179 1 65 1 66 0]. ^self literals: literals numArgs: numArgs numTemps: 0 attributes: attributesArray bytecodes: bytecodes depth: numArgs + 3. ] CompiledMethod class >> stripSourceCode [ "Remove all the references to method source code from the system" self allInstancesDo: [:each | each stripSourceCode] ] sourceCodeLinesDelta [ "Answer the delta from the numbers in LINE_NUMBER bytecodes to source code line numbers." | line | self allByteCodeIndicesDo: [:each :byte :operand | (self class bytecodeInfoTable at: byte * 4 + 4) >= 128 ifTrue: [^operand - 1]]. ^0 ] methodCategory [ "Answer the method category" ^descriptor category ] methodCategory: aCategory [ "Set the method category to the given string" descriptor category: aCategory ] methodSourceCode [ "Answer the method source code (a FileSegment or String or nil)" ^(descriptor sourceCode isNil or: [descriptor sourceFile = 'stdin']) ifTrue: [nil] ifFalse: [descriptor sourceCode] ] methodParseNode [ "Answer the parse tree for the receiver, or nil if there is an error. Requires the Parser package to be loaded." self notYetImplemented ] methodFormattedSourceString [ "Answer the pretty-printed method source code as a string. Requires the Parser package to be loaded." self notYetImplemented ] methodRecompilationSourceString [ "Answer the method source code as a string, ensuring that it is in new syntax (it has brackets)." ^self isOldSyntax ifTrue: [ self methodFormattedSourceString ] ifFalse: [ self methodSourceString trimSeparators ]. ] methodSourceString [ "Answer the method source code as a string" ^(descriptor sourceCode isNil or: [descriptor sourceFile = 'stdin']) ifTrue: [nil] ifFalse: [descriptor sourceString] ] methodSourceFile [ "Answer the file where the method source code is stored" ^(descriptor sourceCode isNil or: [descriptor sourceFile = 'stdin']) ifTrue: [nil] ifFalse: [descriptor sourceFile] ] methodSourcePos [ "Answer the location where the method source code is stored in the methodSourceFile" ^(descriptor sourceCode isNil or: [descriptor sourceFile = 'stdin']) ifTrue: [nil] ifFalse: [descriptor sourcePos] ] = aMethod [ "Answer whether the receiver and aMethod are equal" self == aMethod ifTrue: [^true]. ^super = aMethod and: [descriptor = aMethod descriptor] ] hash [ "Answer an hash value for the receiver" ^super hash bitXor: descriptor hash ] method [ "Answer the receiver, since it is already a method." ^self ] methodClass [ "Answer the class in which the receiver is installed." ^descriptor methodClass ] methodClass: methodClass [ "Set the receiver's class instance variable" descriptor methodClass: methodClass ] allBlocksDo: aBlock [ "Evaluate aBlock, passing to it all the CompiledBlocks it holds" self allLiterals do: [:each | each class == CompiledBlock ifTrue: [aBlock value: each]. each class == BlockClosure ifTrue: [aBlock value: each block]] ] withAllBlocksDo: aBlock [ "Evaluate aBlock, passing the receiver and all the CompiledBlocks it holds" aBlock value: self. self allBlocksDo: aBlock ] withNewMethodClass: class [ "Answer either the receiver or a copy of it, with the method class set to class" ^self methodClass isNil ifTrue: [self methodClass: class; yourself] ifFalse: [(self deepCopy) methodClass: class; yourself] ] withNewMethodClass: class selector: selector [ "Answer either the receiver or a copy of it, with the method class set to class" ^(self withNewMethodClass: class) selector: selector; yourself ] selector: aSymbol [ "Set the selector through which the method is called" descriptor selector: aSymbol ] selector [ "Answer the selector through which the method is called" ^descriptor selector ] flags [ "Private - Answer the optimization flags for the receiver" ^(header bitShift: -27) bitAnd: 7 ] primitive [ "Answer the primitive called by the receiver" ^(header bitShift: -17) bitAnd: 511 ] isOldSyntax [ "Answer whether the method was written with the old (chunk-format) syntax" ^((header bitShift: -26) bitAnd: 1) == 1 ] noteOldSyntax [ "Remember that the method is written with the old (chunk-format) syntax" header := header bitOr: (1 bitShift: 26) ] allLiterals [ "Answer the literals referred to by the receiver and all the blocks in it" ^literals isNil ifTrue: [#()] ifFalse: [literals] ] numArgs [ "Answer the number of arguments for the receiver" ^header bitAnd: 31 ] numTemps [ "Answer the number of temporaries for the receiver" ^(header bitShift: -11) bitAnd: 63 ] stackDepth [ "Answer the number of stack slots needed for the receiver" ^((header bitShift: -5) bitAnd: 63) * 4 ] valueWithReceiver: anObject withArguments: args [ "Execute the method within anObject, passing the elements of the args Array as parameters. The method need not reside on the hierarchy from the receiver's class to Object -- it need not reside at all in a MethodDictionary, in fact -- but doing bad things will compromise stability of the Smalltalk virtual machine (and don't blame anybody but yourself). If the flags field of the method header is 6, this method instead provides a hook from which the virtual machine can call back whenever execution of the method is requested. In this case, invoking the method would cause an infinite loop (the VM asks the method to run, the method asks the VM to invoke it, and so on), so this method fails with a #subclassResponsibility error." ^self flags = 6 ifTrue: [self subclassResponsibility] ifFalse: [anObject perform: self withArguments: args] ] recompile [ "Recompile the method in the scope of the class where it leaves." | source category ok | ok := [source := self methodRecompilationSourceString. category := self methodCategory. true] on: Error do: [:ex | ex return: false]. ok ifFalse: [^nil]. ^self methodClass compile: source classified: category ] recompileNotifying: aNotifier [ "Recompile the method in the scope of the class where it leaves, notifying errors to aNotifier by sending it #error:." | source category ok | ok := [source := self methodRecompilationSourceString. category := self methodCategory. true] on: Error do: [:ex | ex return: false]. ok ifFalse: [^nil]. ^self methodClass compile: source classified: category notifying: aNotifier ] isAnnotated [ "If the receiver has any attributes, answer true." | flags | flags := self flags. ^flags == 4 or: [flags == 5] ] primitiveAttribute [ "If the receiver defines a primitive, return a Message resembling the attribute that was used to define it." | primitive | primitive = 0 ifTrue: [^nil]. ^Message selector: #primitive: arguments: {primitive} ] attributes [ "Return an Array of Messages, one for each attribute defined by the receiver." | attributes numAttr | self isAnnotated ifFalse: [^#()]. numAttr := descriptor size. self primitive = 0 ifFalse: [numAttr := numAttr + 1]. attributes := Array new: numAttr. self primitive = 0 ifFalse: [attributes at: numAttr put: self primitiveAttribute]. 1 to: descriptor size do: [:i | attributes at: i put: (descriptor at: i)]. ^attributes ] attributeAt: aSymbol [ "Return a Message for the first attribute named aSymbol defined by the receiver, or answer an error if none was found." ^self attributeAt: aSymbol ifAbsent: [SystemExceptions.NotFound signalOn: aSymbol what: 'attribute'] ] attributeAt: aSymbol ifAbsent: aBlock [ "Return a Message for the first attribute named aSymbol defined by the receiver, or evaluate aBlock is none was found." | primitive attr | self isAnnotated ifFalse: [^aBlock value]. aSymbol == #primitive: ifTrue: [primitive := self primitiveAttribute. ^primitive isNil ifTrue: [aBlock value] ifFalse: [primitive]]. 1 to: descriptor size do: [:i | attr := descriptor at: i. attr selector = aSymbol ifTrue: [^attr]]. ^aBlock value ] attributesDo: aBlock [ "Evaluate aBlock once for each attribute defined by the receiver, passing a Message each time." | attr | self isAnnotated ifFalse: [^self]. self primitive = 0 ifFalse: [aBlock value: self primitiveAttribute]. 1 to: descriptor size do: [:i | | attr | attr := descriptor at: i. aBlock value: attr] ] storeOn: aStream [ "Print code to create the receiver on aStream" aStream nextPutAll: '(('; print: self class; nextPutAll: ' literals: '; store: ((1 to: self numLiterals) collect: [:i | self literalAt: i]); nextPutAll: ' numArgs: '; store: self numArgs; nextPutAll: ' numTemps: '; store: self numTemps; nextPutAll: ' primitive: '; store: self primitive; nextPutAll: ' bytecodes: '; store: self asByteArray; nextPutAll: ' source: '; store: self methodSourceCode; nextPutAll: ') makeLiteralsReadOnly; setDescriptor: '; store: self descriptor; nextPutAll: '; yourself)' ] printHeaderOn: aStream [ "Private - Disassemble the method header to aStream" aStream nextPutAll: ' Header Flags: '; nl; nextPutAll: ' flags: '; print: self flags; nl; nextPutAll: ' primitive index: '; print: self primitive. self flags = 4 ifTrue: [aStream nextPutAll: ' ('; nextPutAll: (VMPrimitives keyAtValue: self primitive ifAbsent: ['unknown']); nextPut: $)]. aStream nl; nextPutAll: ' number of arguments: '; print: self numArgs; nl; nextPutAll: ' number of temporaries: '; print: self numTemps; nl; nextPutAll: ' number of literals: '; print: self numLiterals; nl; nextPutAll: ' needed stack slots: '; print: self stackDepth; nl ] printOn: aStream [ "Print the receiver's class and selector on aStream" descriptor isNil ifTrue: [^super printOn: aStream]. self methodClass printOn: aStream in: Namespace current. aStream nextPutAll: '>>'; nextPutAll: self selector ] postCopy [ "Private - Make a deep copy of the descriptor and literals. Don't need to replace the method header and bytecodes, since they are integers." super postCopy. descriptor := descriptor copy "literals := literals deepCopy. self makeLiteralsReadOnly" ] makeLiteralsReadOnly [ literals isNil ifTrue: [^self]. self makeLiteralsReadOnly: literals ] makeLiteralsReadOnly: array [ array do: [:each | each class == Array ifTrue: [self makeLiteralsReadOnly: each]. (each class isKindOf: LookupKey) ifFalse: [each makeReadOnly: true]]. ] initialize [ descriptor := MethodInfo new ] descriptor [ ^descriptor ] descriptor: aMethodInfo [ descriptor := aMethodInfo ] stripSourceCode [ descriptor stripSourceCode ] isAbstract [ "Answer whether the receiver is abstract." ^self refersTo: #subclassResponsibility ] sendsToSuper [ "Answer whether the receiver or the blocks it contains have sends to super" self allBlocksDo: [:ccode | ccode sendsToSuper ifTrue: [^true]]. ^super sendsToSuper ] reads: instVarIndex [ "Answer whether the receiver or the blocks it contains reads to the instance variable with the given index" self allBlocksDo: [:ccode | (ccode reads: instVarIndex) ifTrue: [^true]]. ^super reads: instVarIndex ] assigns: instVarIndex [ "Answer whether the receiver or the blocks it contains writes to the instance variable with the given index" self allBlocksDo: [:ccode | (ccode assigns: instVarIndex) ifTrue: [^true]]. ^super assigns: instVarIndex ] accesses: instVarIndex [ "Answer whether the receiver or the blocks it contains accesses the instance variable with the given index" self allBlocksDo: [:ccode | (ccode accesses: instVarIndex) ifTrue: [^true]]. ^super accesses: instVarIndex ] binaryRepresentationObject [ "This method is implemented to allow for a PluggableProxy to be used with CompiledMethods. Answer a DirectedMessage which sends #>> to the class object containing the receiver." ^DirectedMessage selector: #>> arguments: (Array with: self selector) receiver: self methodClass ] isValidCCall [ "Answer whether I appear to have the valid flags, information, and ops to invoke a C function and answer its result." ^(self bytecodeAt: 1) == 66 and: [(self bytecodeAt: 2) == 0 and: [self numLiterals == 0 and: [self numTemps == 0 and: [self flags == 5]]]] ] rewriteAsCCall: funcOrDescr for: aClass [ | args newMethod | funcOrDescr isString ifFalse: [ self isValidCCall ifFalse: [^'C call-out not empty']. newMethod := CompiledMethod cCall: funcOrDescr numArgs: self numArgs attributes: self attributes. newMethod descriptor: self descriptor. self isOldSyntax ifTrue: [ newMethod noteOldSyntax ]. self become: newMethod. ^nil]. args := aClass isMetaclass ifFalse: [(Array new: self numArgs + 1 withAll: #smalltalk) at: 1 put: #selfSmalltalk; yourself] ifTrue: [Array new: self numArgs withAll: #smalltalk]. ^self rewriteAsCCall: funcOrDescr returning: #smalltalk args: args ] rewriteAsCCall: func returning: returnType args: argsArray [ | newMethod descr | self isValidCCall ifFalse: [^'C call-out not empty']. newMethod := CompiledMethod cCall: (CFunctionDescriptor for: func returning: returnType withArgs: argsArray) numArgs: self numArgs attributes: self attributes. newMethod isNil ifTrue: [^'C function not defined']. newMethod descriptor: self descriptor. self isOldSyntax ifTrue: [ newMethod noteOldSyntax ]. self become: newMethod. ^nil ] rewriteAsAsyncCCall: func args: argsArray [ | newMethod | self isValidCCall ifFalse: [^'C call-out not empty']. newMethod := CompiledMethod asyncCCall: (CFunctionDescriptor for: func returning: #void withArgs: argsArray) numArgs: self numArgs attributes: self attributes. newMethod isNil ifTrue: [^'C function not defined']. newMethod descriptor: self descriptor. self isOldSyntax ifTrue: [ newMethod noteOldSyntax ]. self become: newMethod. ^nil ] ] smalltalk-3.2.5/kernel/Object.st0000644000175000017500000011515412130343734013473 00000000000000"====================================================================== | | Object Method Definitions | | ======================================================================" "====================================================================== | | Copyright 1990,1991,1992,94,95,99,2000,2001,2002,2003,2007,2008,2009 | Free Software Foundation, Inc. | Written by Steve Byrne. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" nil subclass: Object [ Dependencies := nil. FinalizableObjects := nil. Object class >> update: aspect [ "Do any global tasks for the ObjectMemory events." aspect == #returnFromSnapshot ifFalse: [^self]. ContextPart checkPresenceOfJIT. FinalizableObjects := nil ] Object class >> dependencies [ "Answer a dictionary that associates an object with its dependents." ^Dependencies ] Object class >> dependencies: anObject [ "Use anObject as the dictionary that associates an object with its dependents." Dependencies := anObject ] Object class >> finalizableObjects [ "Answer a set of finalizable objects." FinalizableObjects isNil ifTrue: [FinalizableObjects := Set new]. ^FinalizableObjects ] Object class >> initialize [ "Initialize the Dependencies dictionary to be a WeakKeyIdentityDictionary." self == Object ifFalse: [^self]. self dependencies: WeakKeyIdentityDictionary new. ObjectMemory addDependent: self ] ~= anObject [ "Answer whether the receiver and anObject are not equal" ^self = anObject == false ] ~~ anObject [ "Answer whether the receiver and anObject are not the same object" ^self == anObject == false ] isKindOf: aClass [ "Answer whether the receiver's class is aClass or a subclass of aClass" ^self class == aClass or: [self class inheritsFrom: aClass] ] isMemberOf: aClass [ "Returns true if the receiver is an instance of the class 'aClass'" ^self class == aClass ] respondsTo: aSymbol [ "Returns true if the receiver understands the given selector" ^self class canUnderstand: aSymbol ] isNil [ "Answer whether the receiver is nil" ^false ] notNil [ "Answer whether the receiver is not nil" ^true ] ifNil: nilBlock [ "Evaluate nilBlock if the receiver is nil, else answer self" ^self ] ifNil: nilBlock ifNotNil: notNilBlock [ "Evaluate nilBlock if the receiver is nil, else evaluate notNilBlock, passing the receiver." ^notNilBlock cull: self ] ifNotNil: notNilBlock [ "Evaluate notNilBlock if the receiver is not nil, passing the receiver. Else answer nil." ^notNilBlock cull: self ] ifNotNil: notNilBlock ifNil: nilBlock [ "Evaluate nilBlock if the receiver is nil, else evaluate notNilBlock, passing the receiver." ^notNilBlock cull: self ] isCObject [ ^false ] isString [ ^false ] isCharacterArray [ ^false ] isSymbol [ ^false ] isCharacter [ ^false ] isNumber [ ^false ] isFloat [ ^false ] isInteger [ ^false ] isSmallInteger [ ^false ] isNamespace [ ^false ] isClass [ ^false ] isArray [ ^false ] isBehavior [ ^false ] isMeta [ "Same as isMetaclass" ^self isMetaclass ] isMetaClass [ "Same as isMetaclass" ^self isMetaclass ] isMetaclass [ ^false ] copy [ "Returns a shallow copy of the receiver (the instance variables are not copied). The shallow copy receives the message postCopy and the result of postCopy is passed back." ^self shallowCopy postCopy ] postCopy [ "Performs any changes required to do on a copied object. This is the place where one could, for example, put code to replace objects with copies of the objects" ^self ] deepCopy [ "Returns a deep copy of the receiver (the instance variables are copies of the receiver's instance variables)" | class aCopy num | class := self class. aCopy := self shallowCopy. class isPointers ifTrue: [num := class instSize + self basicSize] ifFalse: [num := class instSize]. "copy the instance variables (if any)" 1 to: num do: [:i | aCopy instVarAt: i put: (self instVarAt: i) copy]. ^aCopy ] species [ "This method has no unique definition. Generally speaking, methods which always return the same type usually don't use #class, but #species. For example, a PositionableStream's species is the class of the collection on which it is streaming (used by upTo:, upToAll:, upToEnd). Stream uses species for obtaining the class of next:'s return value, Collection uses it in its #copyEmpty: message, which in turn is used by all collection-returning methods. An Interval's species is Array (used by collect:, select:, reject:, etc.)." ^self class ] yourself [ "Answer the receiver" ^self ] addDependent: anObject [ "Add anObject to the set of the receiver's dependents. Important: if an object has dependents, it won't be garbage collected." ^(Dependencies at: self ifAbsentPut: [OrderedCollection new]) add: anObject ] removeDependent: anObject [ "Remove anObject to the set of the receiver's dependents. No problem if anObject is not in the set of the receiver's dependents." | dependencies | dependencies := Dependencies at: self ifAbsent: [^anObject]. dependencies remove: anObject ifAbsent: []. dependencies size < 1 ifTrue: [ Dependencies removeKey: self ifAbsent: []]. ^anObject ] dependents [ "Answer a collection of the receiver's dependents." | dependencies | dependencies := Dependencies at: self ifAbsent: [^OrderedCollection new]. ^dependencies asOrderedCollection ] release [ "Remove all of the receiver's dependents from the set and allow the receiver to be garbage collected." Dependencies removeKey: self ifAbsent: [] ] addToBeFinalized [ "Arrange things so that #finalize is sent to the object when the garbage collector finds out there are only weak references to it." self class finalizableObjects add: ((HomedAssociation key: self value: nil environment: FinalizableObjects) makeEphemeron; yourself) ] removeToBeFinalized [ "Unregister the object, so that #finalize is no longer sent to the object when the garbage collector finds out there are only weak references to it." self class finalizableObjects remove: (HomedAssociation key: self value: nil environment: self class finalizableObjects) ifAbsent: [] ] mourn [ "This method is sent by the VM to weak and ephemeron objects when one of their fields is found out to be garbage collectable (this means, for weak objects, that there are no references to it from non-weak objects, and for ephemeron objects, that the only paths to the first instance variable pass through other instance variables of the same ephemeron). The default behavior is to do nothing." ] finalize [ "Do nothing by default" ] changed [ "Send update: for each of the receiver's dependents, passing them the receiver" self changed: self ] changed: aParameter [ "Send update: for each of the receiver's dependents, passing them aParameter" | dependencies | dependencies := Object dependencies at: self ifAbsent: [nil]. dependencies notNil ifTrue: [dependencies do: [:dependent | dependent update: aParameter]] ] update: aParameter [ "Default behavior is to do nothing. Called by #changed and #changed:" ] broadcast: aSymbol [ "Send the unary message aSymbol to each of the receiver's dependents" | dependencies | dependencies := Object dependencies at: self ifAbsent: [nil]. dependencies notNil ifTrue: [dependencies do: [:dependent | dependent perform: aSymbol]] ] broadcast: aSymbol with: anObject [ "Send the message aSymbol to each of the receiver's dependents, passing anObject" | dependencies | dependencies := Object dependencies at: self ifAbsent: [nil]. dependencies notNil ifTrue: [dependencies do: [:dependent | dependent perform: aSymbol with: anObject]] ] broadcast: aSymbol with: arg1 with: arg2 [ "Send the message aSymbol to each of the receiver's dependents, passing arg1 and arg2 as parameters" | dependencies | dependencies := Object dependencies at: self ifAbsent: [nil]. dependencies notNil ifTrue: [dependencies do: [:dependent | dependent perform: aSymbol with: arg1 with: arg2]] ] broadcast: aSymbol withBlock: aBlock [ "Send the message aSymbol to each of the receiver's dependents, passing the result of evaluating aBlock with each dependent as the parameter" | dependencies | dependencies := Object dependencies at: self ifAbsent: [nil]. dependencies notNil ifTrue: [dependencies do: [:dependent | dependent perform: aSymbol with: (aBlock value: dependent)]] ] broadcast: aSymbol withArguments: anArray [ "Send the message aSymbol to each of the receiver's dependents, passing the parameters in anArray" | dependencies | dependencies := Object dependencies at: self ifAbsent: [nil]. dependencies notNil ifTrue: [dependencies do: [:dependent | dependent perform: aSymbol withArguments: anArray]] ] -> anObject [ "Creates a new instance of Association with the receiver being the key and the argument becoming the value" ^Association key: self value: anObject ] displayString [ "Answer a String representing the receiver. For most objects this is simply its #printString, but for strings and characters, superfluous dollars or extra pair of quotes are stripped." | stream | stream := WriteStream on: String new. self displayOn: stream. ^stream contents ] displayOn: aStream [ "Print a represention of the receiver on aStream. For most objects this is simply its #printOn: representation, but for strings and characters, superfluous dollars or extra pair of quotes are stripped." self printOn: aStream ] display [ "Print a represention of the receiver on the Transcript (stdout the GUI is not active). For most objects this is simply its #print representation, but for strings and characters, superfluous dollars or extra pair of quotes are stripped." Transcript show: self displayString ] displayNl [ "Print a represention of the receiver, then put a new line on the Transcript (stdout the GUI is not active). For most objects this is simply its #printNl representation, but for strings and characters, superfluous dollars or extra pair of quotes are stripped." Transcript showCr: self displayString ] printString [ "Answer a String representing the receiver" | stream | stream := WriteStream on: String new. self printOn: stream. ^stream contents ] printOn: aStream [ "Print a represention of the receiver on aStream" aStream nextPutAll: self class article; space; nextPutAll: self class name ] basicPrintOn: aStream [ "Print a represention of the receiver on aStream" aStream nextPutAll: self class article; space; nextPutAll: self class name ] print [ "Print a represention of the receiver on the Transcript (stdout the GUI is not active)" Transcript show: self printString ] printNl [ "Print a represention of the receiver on stdout, put a new line the Transcript (stdout the GUI is not active)" Transcript showCr: self printString ] basicPrintNl [ "Print a basic representation of the receiver, followed by a new line." stdout flush. self basicPrint. stdout nextPut: Character nl; flush ] storeString [ "Answer a String of Smalltalk code compiling to the receiver" | stream | stream := WriteStream on: String new. self storeOn: stream. ^stream contents ] storeLiteralOn: aStream [ "Put a Smalltalk literal compiling to the receiver on aStream" aStream nextPutAll: '##('. self storeOn: aStream. aStream nextPut: $) ] storeOn: aStream [ "Put Smalltalk code compiling to the receiver on aStream" | class hasSemi | class := self class. aStream nextPut: $(. aStream nextPutAll: self class storeString. hasSemi := false. class isVariable ifTrue: [aStream nextPutAll: ' basicNew: '. self basicSize printOn: aStream] ifFalse: [aStream nextPutAll: ' basicNew']. 1 to: class instSize do: [:i | aStream nextPutAll: ' instVarAt: '. i printOn: aStream. aStream nextPutAll: ' put: '. (self instVarAt: i) storeOn: aStream. aStream nextPut: $;. hasSemi := true]. class isVariable ifTrue: [1 to: self validSize do: [:i | aStream nextPutAll: ' basicAt: '. i printOn: aStream. aStream nextPutAll: ' put: '. (self basicAt: i) storeOn: aStream. aStream nextPut: $;. hasSemi := true]]. hasSemi ifTrue: [aStream nextPutAll: ' yourself']. aStream nextPut: $) ] store [ "Put a String of Smalltalk code compiling to the receiver on the Transcript (stdout the GUI is not active)" Transcript show: self storeString ] storeNl [ "Put a String of Smalltalk code compiling to the receiver, followed by a new line, on the Transcript (stdout the GUI is not active)" Transcript showCr: self storeString ] binaryRepresentationObject [ "This method must be implemented if PluggableProxies are used with the receiver's class. The default implementation raises an exception." (ObjectDumper proxyClassFor: self) == PluggableProxy ifTrue: [self subclassResponsibility] ifFalse: [self shouldNotImplement] ] postLoad [ "Called after loading an object; must restore it to the state before `preStore' was called. Do nothing by default" ] postStore [ "Called after an object is dumped; must restore it to the state before `preStore' was called. Call #postLoad by default" self postLoad ] preStore [ "Called before dumping an object; it must *change* it (it must not answer a new object) if necessary. Do nothing by default" ] reconstructOriginalObject [ "Used if an instance of the receiver's class is returned as the #binaryRepresentationObject of another object. The default implementation raises an exception." self subclassResponsibility ] examine [ "Print all the instance variables of the receiver on the Transcript" self examineOn: Transcript ] inspect [ "In a GUI environment, this opens a tool to examine and modify the receiver. In the default image, it just calls #examine." self examineOn: Transcript ] examineOn: aStream [ "Print all the instance variables of the receiver on aStream" | instVars output object | aStream nextPutAll: 'An instance of '; print: self class; nl. instVars := self class allInstVarNames. 1 to: instVars size + self validSize do: [:i | object := self instVarAt: i. output := [object printString] on: Error do: [:ex | ex return: '%1 %2' % {object class article. object class name asString}]. i <= instVars size ifTrue: [aStream nextPutAll: ' '; nextPutAll: (instVars at: i); nextPutAll: ': '] ifFalse: [aStream nextPutAll: ' ['; print: i - instVars size; nextPutAll: ']: ']. aStream nextPutAll: output; nl] ] validSize [ "Answer how many elements in the receiver should be inspected" ^self basicSize ] allOwners [ "Return an Array of Objects that point to the receiver." ] changeClassTo: aBehavior [ "Mutate the class of the receiver to be aBehavior. Note: Tacitly assumes that the structure is the same for the original and new class!!" ] checkIndexableBounds: index ifAbsent: aBlock [ "Private - Check the reason why an access to the given indexed instance variable failed. Evaluate aBlock for an invalid index." self class isFixed ifTrue: [^SystemExceptions.NotIndexable signalOn: self]. index isInteger ifFalse: [^SystemExceptions.WrongClass signalOn: index mustBe: SmallInteger]. ^aBlock value ] checkIndexableBounds: index [ "Private - Check the reason why an access to the given indexed instance variable failed" self class isFixed ifTrue: [^SystemExceptions.NotIndexable signalOn: self]. index isInteger ifFalse: [^SystemExceptions.WrongClass signalOn: index mustBe: SmallInteger]. index < 1 ifTrue: [^SystemExceptions.IndexOutOfRange signalOn: self withIndex: index]. index > self basicSize ifTrue: [^SystemExceptions.IndexOutOfRange signalOn: self withIndex: index] ] checkIndexableBounds: index put: object [ "Private - Check the reason why a store to the given indexed instance variable failed" | shape size | self class isFixed ifTrue: [^SystemExceptions.NotIndexable signalOn: self]. self isReadOnly ifTrue: [^SystemExceptions.ReadOnlyObject signal]. index isInteger ifFalse: [^SystemExceptions.WrongClass signalOn: index mustBe: SmallInteger]. index < 1 ifTrue: [^SystemExceptions.IndexOutOfRange signalOn: self withIndex: index]. index > self basicSize ifTrue: [^SystemExceptions.IndexOutOfRange signalOn: self withIndex: index]. shape := self class shape. (shape == #float or: [shape == #double]) ifTrue: [SystemExceptions.WrongClass signalOn: object mustBe: {Float. SmallInteger}]. (object isKindOf: Character) ifFalse: [(shape == #character or: [shape == #utf32]) ifTrue: [SystemExceptions.WrongClass signalOn: object mustBe: Character]]. shape == #character ifTrue: [^SystemExceptions.ArgumentOutOfRange signalOn: object mustBeBetween: (Character value: 0) and: (Character value: 255)]. shape == #utf32 ifTrue: [^SystemExceptions.ArgumentOutOfRange signalOn: object mustBeBetween: 0 asCharacter and: 1114111 asCharacter]. shape == #byte ifTrue: [size := 8]. shape == #int8 ifTrue: [size := 7]. shape == #ushort ifTrue: [size := 16]. shape == #short ifTrue: [size := 15]. shape == #uint ifTrue: [size := 32]. shape == #int ifTrue: [size := 31]. shape == #uint64 ifTrue: [size := 64]. shape == #int64 ifTrue: [size := 63]. size isNil ifTrue: [^self primtiveFailed]. ^SystemExceptions.ArgumentOutOfRange signalOn: object mustBeBetween: (size odd ifTrue: [-1 bitShift: size] ifFalse: [0]) and: (1 bitShift: size) - 1 ] at: anIndex [ "Answer the index-th indexed instance variable of the receiver" self checkIndexableBounds: anIndex ] basicAt: anIndex [ "Answer the index-th indexed instance variable of the receiver. This method must not be overridden, override at: instead" self checkIndexableBounds: anIndex ] at: anIndex put: value [ "Store value in the index-th indexed instance variable of the receiver" self checkIndexableBounds: anIndex put: value ] basicAt: anIndex put: value [ "Store value in the index-th indexed instance variable of the receiver This method must not be overridden, override at:put: instead" self checkIndexableBounds: anIndex put: value ] size [ "Answer the number of indexed instance variable in the receiver" ] basicSize [ "Answer the number of indexed instance variable in the receiver" ] becomeForward: otherObject [ "Change all references to the receiver into references to otherObject. References to otherObject are not transformed into the receiver. Answer the receiver so that it is not lost." ^SystemExceptions.ReadOnlyObject signal ] become: otherObject [ "Change all references to the receiver into references to otherObject. Depending on the implementation, references to otherObject might or might not be transformed into the receiver (respectively, 'two-way become' and 'one-way become'). Implementations doing one-way become answer the receiver (so that it is not lost). Most implementations doing two-way become answer otherObject, but this is not assured - so do answer the receiver for consistency. GNU Smalltalk does two-way become and answers otherObject, but this might change in future versions: programs should not rely on the behavior and results of #become: ." ^SystemExceptions.ReadOnlyObject signal ] shallowCopy [ "Returns a shallow copy of the receiver (the instance variables are not copied)" "This is a primitive for speed. An alternative implementation is found below." | class aCopy | class := self class. class isVariable ifTrue: [aCopy := class basicNew: self basicSize] ifFalse: [aCopy := class basicNew]. "copy the instance variables (if any)" 1 to: class instSize + self basicSize do: [:i | aCopy instVarAt: i put: (self instVarAt: i)]. ^aCopy ] makeFixed [ "Avoid that the receiver moves in memory across garbage collections." "We are an integer - fail" SystemExceptions.InvalidValue signalOn: self reason: 'Instances of Integer cannot be tenured!' ] tenure [ "Move the object to oldspace." "We are an integer - they won't notice the difference so don't fail." ] instVarNamed: aString [ "Answer the instance variable named aString in the receiver." ^self instVarAt: (self class indexOfInstVar: aString) ] instVarNamed: aString put: anObject [ "Answer the instance variable named aString in the receiver." ^self instVarAt: (self class indexOfInstVar: aString) put: anObject ] instVarAt: index [ "Answer the index-th instance variable of the receiver. This method must not be overridden." index < 1 ifTrue: [^SystemExceptions.IndexOutOfRange signalOn: self withIndex: index]. index isInteger ifFalse: [^SystemExceptions.WrongClass signalOn: index mustBe: SmallInteger]. index > (self basicSize + self class instSize) ifTrue: [^SystemExceptions.IndexOutOfRange signalOn: self withIndex: index]. ^self basicAt: index - self class instSize ] instVarAt: index put: value [ "Store value in the index-th instance variable of the receiver. This method must not be overridden." self isReadOnly ifTrue: [^SystemExceptions.ReadOnlyObject signal]. index < 1 ifTrue: [^SystemExceptions.IndexOutOfRange signalOn: self withIndex: index]. index isInteger ifFalse: [^SystemExceptions.WrongClass signalOn: index mustBe: SmallInteger]. index > (self basicSize + self class instSize) ifTrue: [^SystemExceptions.IndexOutOfRange signalOn: self withIndex: index]. ^self basicAt: index - self class instSize put: value ] isReadOnly [ "Answer whether the object's indexed instance variables can be written" ] isUntrusted [ "Answer whether the object is to be considered untrusted." ] makeReadOnly: aBoolean [ "Set whether the object's indexed instance variables can be written" SystemExceptions.WrongClass signalOn: aBoolean mustBe: Boolean ] makeUntrusted: aBoolean [ "Set whether the object is to be considered untrusted." SystemExceptions.WrongClass signalOn: aBoolean mustBe: Boolean ] makeWeak [ "Make the object a 'weak' one. When an object is only referenced by weak objects, it is collected and the slots in the weak objects are changed to nils by the VM; the weak object is then sent the #mourn message." ] makeEphemeron [ "Make the object an 'ephemeron'. An ephemeron is marked after all other objects, and if no references are found to the key except from the object itself, it is sent the #mourn message." SystemExceptions.InvalidValue signalOn: self reason: 'ephemerons should have at least one instance variables' ] asOop [ "Answer the object index associated to the receiver. The object index doesn't change when garbage collection is performed." "We are an integer - fail" SystemExceptions.InvalidValue signalOn: self reason: 'Instances of Integer have no associated OOP!' ] identityHash [ "Answer an hash value for the receiver. This method must not be overridden" "We are an integer - answer the receiver" ^self ] hash [ "Answer an hash value for the receiver. This hash value is ok for objects that do not redefine ==." "We are an integer - answer the receiver" ^self ] nextInstance [ "Private - answer another instance of the receiver's class, or nil if the entire object table has been walked" ^nil ] perform: selectorOrMessageOrMethod [ "Send the unary message named selectorOrMessageOrMethod (if a Symbol) to the receiver, or the message and arguments it identifies (if a Message or DirectedMessage), or finally execute the method within the receiver (if a CompiledMethod). In the last case, the method need not reside on the hierarchy from the receiver's class to Object -- it need not reside at all in a MethodDictionary, in fact -- but doing bad things will compromise stability of the Smalltalk virtual machine (and don't blame anybody but yourself). This method should not be overridden" selectorOrMessageOrMethod isSymbol ifTrue: [(self respondsTo: selectorOrMessageOrMethod) ifTrue: [^SystemExceptions.WrongArgumentCount signal] ifFalse: [self doesNotUnderstand: (Message selector: selectorOrMessageOrMethod arguments: #())]]. (selectorOrMessageOrMethod isKindOf: CompiledMethod) ifTrue: [SystemExceptions.WrongArgumentCount signal]. ^selectorOrMessageOrMethod sendTo: self ] perform: selectorOrMethod with: arg1 [ "Send the message named selectorOrMethod (if a Symbol) to the receiver, passing arg1 to it, or execute the method within the receiver (if a CompiledMethod). In the latter case, the method need not reside on the hierarchy from the receiver's class to Object -- it need not reside at all in a MethodDictionary, in fact -- but doing bad things will compromise stability of the Smalltalk virtual machine (and don't blame anybody but yourself). This method should not be overridden" (selectorOrMethod isKindOf: CompiledMethod) ifTrue: [SystemExceptions.WrongArgumentCount signal]. selectorOrMethod isSymbol ifFalse: [SystemExceptions.WrongClass signalOn: selectorOrMethod mustBe: Symbol]. (self respondsTo: selectorOrMethod) ifTrue: [SystemExceptions.WrongArgumentCount signal] ifFalse: [self doesNotUnderstand: (Message selector: selectorOrMethod arguments: {arg1})] ] perform: selectorOrMethod with: arg1 with: arg2 [ "Send the message named selectorOrMethod (if a Symbol) to the receiver, passing arg1 and arg2 to it, or execute the method within the receiver (if a CompiledMethod). In the latter case, the method need not reside on the hierarchy from the receiver's class to Object -- it need not reside at all in a MethodDictionary, in fact -- but doing bad things will compromise stability of the Smalltalk virtual machine (and don't blame anybody but yourself). This method should not be overridden" (selectorOrMethod isKindOf: CompiledMethod) ifTrue: [SystemExceptions.WrongArgumentCount signal]. selectorOrMethod isSymbol ifFalse: [SystemExceptions.WrongClass signalOn: selectorOrMethod mustBe: Symbol]. (self respondsTo: selectorOrMethod) ifTrue: [SystemExceptions.WrongArgumentCount signal] ifFalse: [self doesNotUnderstand: (Message selector: selectorOrMethod arguments: {arg1. arg2})] ] perform: selectorOrMethod with: arg1 with: arg2 with: arg3 [ "Send the message named selectorOrMethod (if a Symbol) to the receiver, passing the other arguments to it, or execute the method within the receiver (if a CompiledMethod). In the latter case, the method need not reside on the hierarchy from the receiver's class to Object -- it need not reside at all in a MethodDictionary, in fact -- but doing bad things will compromise stability of the Smalltalk virtual machine (and don't blame anybody but yourself). This method should not be overridden" (selectorOrMethod isKindOf: CompiledMethod) ifTrue: [SystemExceptions.WrongArgumentCount signal]. selectorOrMethod isSymbol ifFalse: [SystemExceptions.WrongClass signalOn: selectorOrMethod mustBe: Symbol]. (self respondsTo: selectorOrMethod) ifTrue: [SystemExceptions.WrongArgumentCount signal] ifFalse: [self doesNotUnderstand: (Message selector: selectorOrMethod arguments: {arg1. arg2. arg3})] ] perform: selectorOrMethod with: arg1 with: arg2 with: arg3 with: arg4 [ "Send the message named selectorOrMethod (if a Symbol) to the receiver, passing the other arguments to it, or execute the method within the receiver (if a CompiledMethod). In the latter case, the method need not reside on the hierarchy from the receiver's class to Object -- it need not reside at all in a MethodDictionary, in fact -- but doing bad things will compromise stability of the Smalltalk virtual machine (and don't blame anybody but yourself). This method should not be overridden" (selectorOrMethod isKindOf: CompiledMethod) ifTrue: [SystemExceptions.WrongArgumentCount signal]. selectorOrMethod isSymbol ifFalse: [SystemExceptions.WrongClass signalOn: selectorOrMethod mustBe: Symbol]. (self respondsTo: selectorOrMethod) ifTrue: [SystemExceptions.WrongArgumentCount signal] ifFalse: [self doesNotUnderstand: (Message selector: selectorOrMethod arguments: {arg1. arg2. arg3. arg4})] ] perform: selectorOrMethod withArguments: argumentsArray [ "Send the message named selectorOrMethod (if a Symbol) to the receiver, passing the elements of argumentsArray as parameters, or execute the method within the receiver (if a CompiledMethod). In the latter case, the method need not reside on the hierarchy from the receiver's class to Object -- it need not reside at all in a MethodDictionary, in fact -- but doing bad things will compromise stability of the Smalltalk virtual machine (and don't blame anybody but yourself). This method should not be overridden" argumentsArray isArray ifFalse: [SystemExceptions.WrongClass signalOn: argumentsArray mustBe: Array]. (selectorOrMethod isKindOf: CompiledMethod) ifTrue: [SystemExceptions.WrongArgumentCount signal]. selectorOrMethod isSymbol ifFalse: [SystemExceptions.WrongClass signalOn: selectorOrMethod mustBe: Symbol]. (self respondsTo: selectorOrMethod) ifTrue: [SystemExceptions.WrongArgumentCount signal] ifFalse: [self doesNotUnderstand: (Message selector: selectorOrMethod arguments: argumentsArray)] ] == arg [ "Answer whether the receiver is the same object as arg. This is a very fast test and is called 'object identity'." ] = arg [ "Answer whether the receiver is equal to arg. The equality test is by default the same as that for identical objects. = must not fail; answer false if the receiver cannot be compared to arg" ] class [ "Answer the class to which the receiver belongs" self primitiveFailed ] error: message [ "Stop the execution and/or bring up a debugger. message is an error message to be shown" ] basicPrint [ "Print a basic representation of the receiver" ] halt [ "Called to enter the debugger" ^self halt: 'halt encountered' ] halt: aString [ "Called to enter the debugger" ^self error: aString ] mark: aSymbol [ "Private - use this method to mark code which needs to be reworked, removed, etc. You can then find all senders of #mark: to find all marked methods or you can look for all senders of the symbol that you sent to #mark: to find a category of marked methods." ] primitiveFailed [ "Called when a VM primitive fails" SystemExceptions.PrimitiveFailed signal ] shouldNotImplement [ "Called when objects belonging to a class should not answer a selector defined by a superclass" SystemExceptions.ShouldNotImplement signal ] subclassResponsibility [ "Called when a method defined by a class should be overridden in a subclass" SystemExceptions.SubclassResponsibility signal ] notYetImplemented [ "Called when a method defined by a class is not yet implemented, but is going to be" SystemExceptions.NotYetImplemented signal ] doesNotUnderstand: message [ "Called by the system when a selector was not found. message is a Message containing information on the receiver" ] badReturnError [ "Called back when a block performs a bad return." SystemExceptions.BadReturn signal ] mustBeBoolean [ "Called by the system when ifTrue:*, ifFalse:*, and: or or: are sent to anything but a boolean" | result | result := SystemExceptions.MustBeBoolean signalOn: self. result == false ifFalse: [result := true]. ^result ] noRunnableProcess [ "Called back when all processes are suspended" SystemExceptions.NoRunnableProcess signal ] userInterrupt [ "Called back when the user presses Ctrl-Break" SystemExceptions.UserInterrupt signal ] ] smalltalk-3.2.5/kernel/Generator.st0000644000175000017500000001464712123404352014214 00000000000000"====================================================================== | | Generator Method Definitions | | ======================================================================" "====================================================================== | | Copyright 2003, 2007, 2009 Free Software Foundation, Inc. | Written by Paolo Bonzini. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" Stream subclass: Generator [ | next genCC consCC atEnd | Generator class >> on: aBlock [ "Return a generator and pass it to aBlock. When #next is sent to the generator, the block will start execution, and will be suspended again as soon as #yield: is sent from the block to the generator." ^(self new) forkOn: aBlock; yourself ] Generator class >> on: aCollection do: aBlock [ "Return a generator; for each item of aCollection, evaluate aBlock passing the generator and the item." ^self on: [:gen | aCollection do: [:each | aBlock value: gen value: each]] ] Generator class >> inject: aValue into: aBlock [ "Return an infinite generator; the first item is aValue, the following items are obtained by passing the previous value to aBlock." ^self on: [:gen | | last | last := aValue. [gen yield: last. last := aBlock value: last] repeat] ] atEnd [ "Answer whether more data can be generated." atEnd isNil ifTrue: [genCC := genCC callCC]. ^atEnd ] next [ "Evaluate the generator until it generates the next value or decides that nothing else can be generated." | result | self atEnd ifTrue: [^self pastEnd]. result := next. next := nil. atEnd := nil. ^result ] peek [ "Evaluate the generator until it generates the next value or decides that nothing else can be generated, and save the value so that #peek or #next will return it again." self atEnd ifTrue: [^nil]. ^next ] peekFor: anObject [ "Evaluate the generator until it generates the next value or decides that nothing else can be generated, and if it is not equal to anObject, save the value so that #peek or #next will return it again." self atEnd ifTrue: [self pastEnd. ^false]. ^next = anObject ifTrue: [next := nil. atEnd := nil. true] ifFalse: [false] ] yield: anObject [ "When entering from the generator the code in the block is executed and control flow goes back to the consumer. When entering from the consumer, the code after the continuation is executed, which resumes execution of the generator block." atEnd := false. next := anObject. consCC := consCC callCC. "Make sure that an exception (or any other event that causes #yield: not to be invoked again) terminates the generator. Also, generators should not reenter." genCC := nil. atEnd := true ] forkOn: aBlock [ "When initializing, we just store the current continuation and exit; the ^self is where the control flow is actually split. When #next is called first, the code after the continuation is executed, which executes the generator block and finally resumes execution of the consumer when the block leaves. This is the only time we create a continuation with a block; after this, we just replace a continuation with another through Continuation>>#callCC." consCC := Continuation currentDo: [:cc | genCC := cc. atEnd := nil. ^self]. atEnd := true. genCC := nil. aBlock value: self. consCC oneShotValue ] ] smalltalk-3.2.5/kernel/VarBinding.st0000644000175000017500000000574412123404352014307 00000000000000"====================================================================== | | VariableBinding Method Definitions | | ======================================================================" "====================================================================== | | Copyright 2002 Free Software Foundation, Inc. | Written by Paolo Bonzini. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" HomedAssociation subclass: VariableBinding [ isDefined [ "Answer true if this VariableBinding lives outside the Undeclared dictionary" ^self environment ~~ Undeclared ] path [ "Print a dotted path that compiles to the receiver's value" ^self environment storeString , '.' , self key ] printOn: aStream [ "Put on aStream a representation of the receiver" aStream nextPut: ${; nextPutAll: self environment name; nextPut: $.; nextPutAll: self key; nextPut: $} ] isLiteralObject [ "Answer whether the receiver is expressible as a Smalltalk literal." ^true ] storeLiteralOn: aStream [ "Store on aStream some Smalltalk code which compiles to the receiver" self storeOn: aStream ] storeOn: aStream [ "Put on aStream some Smalltalk code compiling to the receiver" aStream nextPutAll: '#{'; nextPutAll: (self environment nameIn: Smalltalk); nextPut: $.; nextPutAll: self key; nextPut: $} ] binaryRepresentationObject [ "This method is implemented to allow for a PluggableProxy to be used with VariableBindings. Answer a DirectedMessage which sends #at: to the environment that holds the receiver." ^DirectedMessage selector: #at: arguments: (Array with: self key) receiver: self environment ] ] smalltalk-3.2.5/kernel/URL.st0000644000175000017500000005726012123404352012726 00000000000000"====================================================================== | | URL class and basic support for resolving URLs | | ======================================================================" "====================================================================== | | Based on code copyright (c) Kazuki Yasumatsu, in the public domain | Copyright (c) 2002, 2003, 2008, 2008, 2009 Free Software Foundation, Inc. | Adapted by Paolo Bonzini. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" Namespace current: NetClients [ Object subclass: URL [ | scheme username password host port path query hasPostData fragment hash | NoPercentEncoding := nil. URL class >> decode: aString [ "Decode a text/x-www-form-urlencoded String into a text/plain String." | result in ch | result := WriteStream on: (String new: aString size). in := ReadStream on: aString. [in atEnd] whileFalse: [(ch := in next) = $+ ifTrue: [result nextPut: $ ] ifFalse: [ch = $% ifFalse: [result nextPut: ch] ifTrue: [ch := in next digitValue * 16 + in next digitValue. result nextPut: ch asCharacter]]]. ^result contents ] URL class >> encode: anURL [ "Encode a text/plain into a text/x-www-form-urlencoded String (those things with lots of % in them)." | result value | result := WriteStream on: (String new: anURL size + 10). anURL do: [:each | each = $ ifTrue: [result nextPut: $+] ifFalse: [value := each value. (NoPercentEncoding at: value + 1) = 1 ifTrue: [result nextPut: each] ifFalse: [result nextPut: $%; nextPut: ('0123456789ABCDEF' at: value // 16 + 1); nextPut: ('0123456789ABCDEF' at: value \\ 16 + 1)]]]. ^result contents ] URL class >> initialize [ "Initialize the receiver's class variables." NoPercentEncoding := ByteArray new: 256. 'abcdefghijklmnopqrstuvwxyzABCDEFGHIJKLMNOPQRSTUVWXYZ -_.*0123456789' do: [:each | NoPercentEncoding at: each value + 1 put: 1] ] URL class >> fromString: aString [ "Parse the given URL and answer an URL object based on it." "URL fromString: 'http://www/dir/file.html'." "URL fromString: 'http://www:10080/dir/file.html'." "URL fromString: 'http://www:10080/dir/file.html?x=100'." "URL fromString: 'http://www:10080/dir/file.html#section'." "URL fromString: 'ftp://ftp/pub/smalltalk'." "URL fromString: 'ftp://ftp:21/pub/smalltalk'." "URL fromString: 'ftp://user@ftp:21/pub/smalltalk'." "URL fromString: 'ftp://user@ftp/pub/smalltalk'." "URL fromString: 'ftp://user:passwd@ftp:21/pub/smalltalk'." "URL fromString: 'news:fj.lang.smalltalk'." "URL fromString: '/dir/file.html'." "URL fromString: 'file.html'." "check fragment and query parts" | fragmentIndex queryIndex limit fragmentLimit queryLimit urlString url | urlString := aString asString. urlString == aString ifFalse: [ ^self fromString: urlString ]. limit := aString size + 1. (queryIndex := aString indexOf: $?) ~= 0 ifTrue: [limit := queryIndex. queryLimit := aString indexOf: $# startingAt: queryIndex + 1 ifAbsent: [aString size + 1]]. (fragmentIndex := aString indexOf: $#) ~= 0 ifTrue: [limit := limit min: fragmentIndex. fragmentLimit := aString indexOf: $? startingAt: fragmentIndex + 1 ifAbsent: [aString size + 1]]. urlString := aString copyFrom: 1 to: limit - 1. url := self fromURLString: urlString. queryIndex > 0 ifTrue: [url query: (aString copyFrom: queryIndex + 1 to: queryLimit - 1)]. fragmentIndex > 0 ifTrue: [url fragment: (aString copyFrom: fragmentIndex + 1 to: fragmentLimit - 1)]. ^url ] URL class >> new [ "Answer a 'blank' URL." ^self basicNew initialize ] URL class >> scheme: schemeString username: userString password: passwordString host: hostString port: portNumber path: pathString [ "Answer an URL object made from all the parts passed as arguments." ^(self new) scheme: schemeString; username: userString; password: passwordString; host: hostString; port: portNumber; path: pathString; yourself ] URL class >> scheme: schemeString host: hostString port: portNumber path: pathString [ "Answer an URL object made from all the parts passed as arguments." ^(self new) scheme: schemeString; host: hostString; port: portNumber; path: pathString; yourself ] URL class >> scheme: schemeString host: hostString path: pathString [ "Answer an URL object made from all the parts passed as arguments." ^(self new) scheme: schemeString; host: hostString; port: 0; path: pathString; yourself ] URL class >> scheme: schemeString path: pathString [ "Answer an URL object made from all the parts passed as arguments." ^(self new) scheme: schemeString; host: nil; port: 0; path: pathString; yourself ] URL class >> fromURLString: aString [ "URL fromString: 'http://www/dir/file.html'." "URL fromString: 'http://www:10080/dir/file.html'." "URL fromString: 'ftp://ftp/pub/smalltalk'." "URL fromString: 'ftp://ftp:21/pub/smalltalk'." "URL fromString: 'ftp://user@ftp:21/pub/smalltalk'." "URL fromString: 'ftp://user@ftp/pub/smalltalk'." "URL fromString: 'ftp://user:passwd@ftp:21/pub/smalltalk'." "URL fromString: 'news:fj.lang.smalltalk'." "URL fromString: '/dir/file.html'." "URL fromString: '//host/dir/file.html'." "URL fromString: 'file.html'." "defPath := String with: $/." | defPath read write ch scheme username password host port path pos try | defPath := nil. read := aString readStream. write := WriteStream on: (String new: aString size). "parse scheme" [read atEnd or: [ (ch := read next) isAlphaNumeric not and: [ch ~= $+]]] whileFalse: [write nextPut: ch]. (write isEmpty or: [ch ~= $:]) ifTrue: ["no scheme" read reset. scheme := nil "aString isEmpty ifTrue: [path := defPath] ifFalse: [path := aString]." "It's may be a file name." "^self scheme: nil path: path"] ifFalse: [scheme := write contents]. write reset. pos := read position. (read nextAvailable: 2) = '//' ifFalse: ["no host and port" read position: pos. path := read upToEnd. path isEmpty ifTrue: [path := defPath]. ^self scheme: scheme path: path]. "parse host and port (and user and password)." try := true. [try] whileTrue: [[read atEnd or: [(ch := read next) = $/ or: [ch = $: or: [ch = $@]]]] whileFalse: [write nextPut: ch]. write isEmpty ifFalse: [host := write contents]. write reset. ch = $: ifTrue: ["parse port or passwd" [read atEnd or: [(ch := read next) = $/ or: [ch = $@]]] whileFalse: [write nextPut: ch]. write isEmpty ifFalse: [port := write contents]. write reset]. ch = $@ ifFalse: [try := false] ifTrue: ["re-parse host" host notNil ifTrue: [username := host. host := nil]. port notNil ifTrue: [password := port. port := nil]]]. port := port isNil ifTrue: [0] ifFalse: [port asInteger]. read atEnd ifTrue: [path := defPath] ifFalse: [write nextPut: ch; nextPutAll: read. path := write contents]. ^self scheme: scheme username: username password: password host: host port: port path: path ] = anURL [ "Answer whether the two URLs are equal. The file and anchor are converted to full 8-bit ASCII (contrast with urlencoded) and the comparison is case-sensitive; on the other hand, the protocol and host are compared without regard to case." self class == anURL class ifFalse: [^false]. self hash = anURL hash ifFalse: [^false]. self scheme == anURL scheme ifFalse: [(self scheme sameAs: anURL scheme) ifFalse: [^false]]. self host == anURL host ifFalse: [(self host sameAs: anURL host) ifFalse: [^false]]. ^self port = anURL port and: [self decodedFile = anURL decodedFile and: [self decodedFragment = anURL decodedFragment]] ] hash [ "Answer an hash value for the receiver" hash isNil ifTrue: [hash := (URL decode: self printString) hash]. ^hash ] canCache [ "Answer whether the URL is cacheable. The current implementation considers file URLs not to be cacheable, and everything else to be." ^self isFileScheme not ] hasFragment [ "Answer whether the URL points to a particular fragment (anchor) of the resource." ^fragment notNil ] hasQuery [ "Answer whether the URL includes query arguments to be submitted when retrieving the resource." ^query notNil ] isFileScheme [ "Answer whether the URL is a file URL." ^scheme isNil or: [scheme = 'file'] ] isFragmentOnly [ "Answer whether the URL only includes the name of a particular fragment (anchor) of the resource to which it refers." ^fragment notNil and: [scheme isNil and: [host isNil and: [port = 0 and: [path isNil]]]] ] add: key to: dict value: value [ "Add the key->value pair to dict; if the key is specified multiple times, make an OrderedCollection with all the values" | values | values := dict at: key ifAbsent: [^dict at: key put: value]. values isString ifFalse: [^values add: value]. "Make the OrderedCollection" dict at: key put: (OrderedCollection with: values with: value). ^value ] clearAuxiliaryParts [ hasPostData := false. fragment := query := nil ] clearFragment [ fragment := nil ] constructPath: path1 with: path2 [ | sep dirStack read p write | sep := $/. dirStack := OrderedCollection new. (path2 isEmpty not and: [path2 first = sep]) ifFalse: [read := path1 readStream. [read atEnd] whileFalse: [p := read upTo: sep. (p isEmpty or: [p = '.']) ifFalse: [p = '..' ifTrue: [dirStack isEmpty ifFalse: [dirStack removeLast]] ifFalse: [dirStack addLast: p]]]. (path1 isEmpty not and: [path1 last = sep]) ifFalse: ["trim path tail (file name)." dirStack isEmpty ifFalse: [dirStack removeLast]]]. read := path2 readStream. [read atEnd] whileFalse: [p := read upTo: sep. (p isEmpty or: [p = '.']) ifFalse: [p = '..' ifTrue: [dirStack isEmpty ifFalse: [dirStack removeLast]] ifFalse: [dirStack addLast: p]]]. dirStack isEmpty ifTrue: [^String with: sep]. write := WriteStream on: (String new: path1 size + path2 size). [dirStack isEmpty] whileFalse: [write nextPut: sep; nextPutAll: dirStack removeFirst]. (path2 isEmpty not and: [path2 last = sep]) ifTrue: [write nextPut: sep]. ^write contents ] construct: anURL [ "Construct an absolute URL based on the relative URL anURL and the base path represented by the receiver" "(URL fromString: 'http://www/dir/file.html') construct: (URL fromString: 'subdir/image.gif')." "(URL fromString: 'http://www/dir1/file.html') construct: (URL fromString: '/dir2/image.gif')." "(URL fromString: 'http://www/dir1/file.html') construct: (URL fromString: '~kyasu/')." "(URL fromString: 'http://www/dir/file.html') construct: (URL fromString: '#introduction')." "(URL fromString: 'http://www/dir/file.html') construct: (URL fromString: '/cgi-bin/perl.pl?dest=/other')." "(URL fromString: 'http://www/dir/file.html') construct: (URL fromString: 'http:/cgi-bin/perl.pl?dest=/other')." "(URL fromString: 'http://www-s2.rsl.crl.fujixerox.co.jp/~kyasu/') construct: (URL fromString: 'http://arrow')." "(URL fromString: 'gopher://www.com') construct: (URL fromString: '//www.com:70/ParcBenchMain')." "(URL fromString: 'http://www/some.html') construct: (URL fromString: 'http://www/')." "(URL fromString: '../tmp/table.html') construct: (URL fromString: 'kyasu.gif')." | newURL | anURL scheme notNil ifTrue: [scheme ~= anURL scheme ifTrue: [^anURL]. anURL host notNil ifTrue: [^anURL] "(anURL host notNil and: [host ~= anURL host]) ifTrue: [^anURL]. (anURL port notNil and: [port ~= anURL port]) ifTrue: [^anURL]"]. newURL := self copyWithoutAuxiliaryParts. anURL path notNil ifTrue: [self isFileScheme ifTrue: [(path isNil or: [anURL path isEmpty not and: [anURL path first = $/]]) ifTrue: [newURL path: anURL path] ifFalse: [(path isEmpty not and: [path first = $/]) ifTrue: [newURL path: (self constructPath: path with: anURL path)] ifFalse: [newURL path: (path asFilename directory constructString: anURL path)]]] ifFalse: [path isNil ifTrue: [newURL path: (self constructPath: '/' with: anURL path)] ifFalse: [newURL path: (self constructPath: path with: anURL path)]]]. newURL query: anURL query; hasPostData: anURL hasPostData; fragment: anURL fragment. ^newURL ] copyWithoutAuxiliaryParts [ "Answer a copy of the receiver where the fragment and query parts of the URL have been cleared." ^self shallowCopy clearAuxiliaryParts postCopy ] copyWithoutFragment [ "Answer a copy of the receiver where the fragment parts of the URL has been cleared." ^self shallowCopy clearFragment postCopy ] postCopy [ "All the variables are copied when an URL object is copied." super postCopy. scheme := scheme copy. username := username copy. password := password copy. host := host copy. port := port copy. path := path copy. fragment := fragment copy. query := query copy ] decodedFields [ "Convert the form fields to a Dictionary, answer nil if no question mark is found in the URL." | query dict | query := self query. query isNil ifTrue: [^nil]. dict := LookupTable new. (query substrings: $&) do: [:keyValue | | i key value | i := keyValue indexOf: $= ifAbsent: [value := nil. keyValue size + 1]. key := keyValue copyFrom: 1 to: i - 1. i < keyValue size ifTrue: [value := keyValue copyFrom: i + 1 to: value size. value := URL decode: value]. self add: key to: dict value: value]. ^dict ] decodedFragment [ "Answer the fragment part of the URL, decoding it from x-www-form-urlencoded format." ^URL decode: self fragment ] decodedFile [ "Answer the file part of the URL, decoding it from x-www-form-urlencoded format." ^URL decode: self file ] fragment [ "Answer the fragment part of the URL, leaving it in x-www-form-urlencoded format." ^fragment ] fragment: aString [ "Set the fragment part of the URL, which should be in x-www-form-urlencoded format." fragment := aString ] asString [ "Answer the full request string corresponding to the URL. This is how the URL would be printed in the address bar of a web browser, except that the query data is printed even if it is to be sent through a POST request." ^self printString ] fullRequestString [ "Answer the full request string corresponding to the URL. This is how the URL would be printed in the address bar of a web browser, except that the query data is printed even if it is to be sent through a POST request." ^self printString ] hasPostData [ "Answer whether the URL has a query part but is actually for an HTTP POST request and not really part of the URL (as it would be for the HTTP GET request)." ^hasPostData and: [query notNil] ] hasPostData: aBoolean [ "Set whether the query part of the URL is actually the data for an HTTP POST request and not really part of the URL (as it would be for the HTTP GET request)." hasPostData := aBoolean ] host [ "Answer the host part of the URL." ^host ] host: aString [ "Set the host part of the URL to aString." host := aString ] newsGroup [ "If the receiver is an nntp url, return the news group." ((scheme = 'nntp' | scheme) = 'news' and: [path notNil]) ifTrue: [^path copyFrom: 2 to: (path indexOf: $/ startingAt: 2 ifAbsent: [path size + 1]) - 1]. ^nil ] password [ "Answer the password part of the URL." ^password ] password: aString [ "Set the password part of the URL to aString." password := aString ] path [ "Answer the path part of the URL." ^path ] path: aString [ "Set the path part of the URL to aString." path := aString ] port [ "Answer the port number part of the URL." ^port ] port: anInteger [ "Set the port number part of the URL to anInteger." port := anInteger ] postData [ "Answer whether the URL has a query part and it is meant for an HTTP POST request, answer it. Else answer nil." self hasPostData ifTrue: [^query]. ^nil ] postData: aString [ "Associate to the URL some data that is meant to be sent through an HTTP POST request, answer it." query := aString. hasPostData := true ] requestString [ "Answer the URL as it would be sent in an HTTP stream (that is, the path and the query data, the latter only if it is to be sent with an HTTP POST request)." | stream | stream := WriteStream on: (String new: 128). path isNil ifTrue: [stream nextPut: $/] ifFalse: [stream nextPutAll: path]. (self hasQuery and: [self hasPostData not]) ifTrue: [stream nextPut: $?; nextPutAll: query]. ^stream contents ] scheme [ "Answer the URL's scheme." ^scheme ] scheme: aString [ "Set the URL's scheme to be aString." scheme := aString ] username [ "Answer the username part of the URL." ^username ] username: aString [ "Set the username part of the URL to aString." username := aString ] query [ "Answer the query data associated to the URL." ^query ] query: aString [ "Set the query data associated to the URL to aString." query := aString ] initialize [ "Initialize the object to a consistent state." self clearAuxiliaryParts ] printOn: stream [ "Print a representation of the URL on the given stream." scheme notNil ifTrue: [stream nextPutAll: scheme; nextPut: $:]. host notNil ifTrue: [scheme notNil ifTrue: [stream nextPutAll: '//']. username notNil ifTrue: [stream nextPutAll: username. password notNil ifTrue: [stream nextPut: $:; nextPutAll: password]. stream nextPut: $@]. stream nextPutAll: host. port > 0 ifTrue: [stream nextPut: $:; print: port]]. path isNil ifTrue: [stream nextPut: $/] ifFalse: [stream nextPutAll: path]. self hasQuery ifTrue: [stream nextPut: $?; nextPutAll: query]. self hasFragment ifTrue: [stream nextPut: $#; nextPutAll: fragment] ] contents [ | s | ^[ (s := self readStream) contents ] ensure: [ s ifNotNil: [ s close ] ] ] entity [ ^NetClients.URIResolver openOn: self ifFail: [ SystemExceptions.FileError signal: 'could not open %1' % {self} ] ] readStream [ ^NetClients.URIResolver openStreamOn: self ifFail: [ SystemExceptions.FileError signal: 'could not open %1' % {self} ] ] resolvePath: newName [ ^NetClients.URIResolver resolve: newName from: self ] ] ] Namespace current: NetClients [ Object subclass: URIResolver [ URIResolver class >> on: anURL [ "Answer a new URIResolver that will do its best to fetch the data for anURL from the Internet." ^self new on: anURL ] URIResolver class >> openStreamOn: aURI ifFail: aBlock [ "Check if aURI can be fetched from the Internet or from the local system, and if so return a Stream with its contents. If this is not possible, instead, evaluate the zero-argument block aBlock and answer the result of the evaluation." | url name body | url := aURI. (url respondsTo: #key) ifTrue: [url := url key , ':/' , url value]. url isString ifTrue: [url := URL fromString: url]. url scheme = 'file' ifFalse: [^aBlock value]. name := url path copy. name replaceAll: $/ with: Directory pathSeparator. ^FileStream fopen: name mode: FileStream read ifFail: aBlock ] URIResolver class >> openOn: aURI ifFail: aBlock [ "Always evaluate aBlock and answer the result if the additional NetClients package is not loaded. If it is, instead, return a WebEntity with the contents of the resource specified by anURI, and only evaluate the block if loading the resource fails." ^aBlock value ] URIResolver class >> openStreamOn: aURI [ "Check if aURI can be fetched from the Internet or from the local system, and if so return a Stream with its contents. If this is not possible, raise an exception." ^self openStreamOn: aURI ifFail: [SystemExceptions.FileError signal: 'could not open ' , aURI printString] ] URIResolver class >> openOn: aURI [ "Always raise an error, as this method is not supported without loading the additional NetClients package." ^self openOn: aURI ifFail: [SystemExceptions.FileError signal: 'could not open ' , aURI printString] ] URIResolver class >> resolve: newName from: oldURI [ | url newURI | url := oldURI. (url respondsTo: #key) ifTrue: [url := url key , ':/' , url value]. url isString ifTrue: [url := URL fromString: url]. url := url construct: (URL fromString: newName). newURI := url printString. ^url ] ] ] Namespace current: NetClients [ URL initialize ] smalltalk-3.2.5/kernel/ProcEnv.st0000644000175000017500000001712112123404352013630 00000000000000"====================================================================== | | ProcessEnvironment Method Definitions | | ======================================================================" "====================================================================== | | Copyright 2008, 2009 Free Software Foundation, Inc. | Written by Paolo Bonzini. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" LookupKey subclass: ProcessVariable [ ProcessVariable class >> key: anObject [ "Return a new ProcessVariable with the given key. Not that the key need not be a symbol or string, for example you could use an array #(#{class name} 'name'). Setting the variable's value will automatically create it in the current process, while removal must be done by hand through the ProcessEnvironment singleton object." ^self basicNew key: anObject ] ProcessVariable class >> new [ "Return a new ProcessVariable with a new anonymous but unique key. It is suggested to use a descriptive name instead to ease debugging. Setting the variable's value will automatically create it in the current process, while removal must be done by hand through the ProcessEnvironment singleton object." ^self basicNew key: Object new ] environment [ "Return the environment in which this ProcessVariable lives. This is the singleton instance of ProcessEnvironment for all variables." ^ProcessEnvironment uniqueInstance ] use: anObject during: aBlock [ "Set the value of this variable to anObject during the execution of aBlock, then restore it." | oldValue | oldValue := self value. self value: anObject. ^aBlock ensure: [self value: oldValue] ] valueIfAbsent: aBlock [ "Return the value of this variable in the current process." ^Processor activeProcess environment at: self key ifAbsent: [ nil ] ] value [ "Return the value of this variable in the current process." ^Processor activeProcess environment at: self key ifAbsent: [ nil ] ] value: anObject [ "Set the value of the current process's copy of the variable to be anObject." Processor activeProcess environment at: self key put: anObject ] ] Object subclass: ProcessEnvironment [ ProcessEnvironment class [ | uniqueInstance | uniqueInstance [ "Return the singleton instance of ProcessEnvironment." uniqueInstance isNil ifTrue: [ uniqueInstance := self basicNew ]. ^uniqueInstance ] new [ self shouldNotImplement ] ] add: newObject [ "Add the newObject association to the receiver" ^Processor activeProcess environment add: newObject ] at: key put: value [ "Store value as associated to the given key" ^Processor activeProcess environment at: key put: value ] at: key [ "Answer the value associated to the given key. Return nil if the key is not found" ^Processor activeProcess environment at: key ifAbsent: [nil] ] at: key ifAbsent: aBlock [ "Answer the value associated to the given key, or the result of evaluating aBlock if the key is not found" ^Processor activeProcess environment at: key ifAbsent: aBlock ] at: key ifAbsentPut: aBlock [ "Answer the value associated to the given key, setting it to the result of evaluating aBlock if the key is not found." ^Processor activeProcess environment at: key ifAbsentPut: aBlock ] at: key ifPresent: aBlock [ "Answer the value associated to the given key, or the result of evaluating aBlock if the key is not found" ^Processor activeProcess environment at: key ifPresent: aBlock ] associationAt: key ifAbsent: aBlock [ "Answer the value associated to the given key, or the result of evaluating aBlock if the key is not found" ^ProcessVariable key: key ] associationAt: key [ "Answer the value associated to the given key, or the result of evaluating aBlock if the key is not found" ^ProcessVariable key: key ] keys [ "Answer a kind of Set containing the keys of the receiver" ^Processor activeProcess environment keys ] includesKey: key [ "Answer whether the receiver contains the given key" ^Processor activeProcess environment includesKey: key ] removeAllKeys: keys [ "Remove all the keys in keys, without raising any errors" keys do: [:key | self removeKey: key ifAbsent: []] ] removeAllKeys: keys ifAbsent: aBlock [ "Remove all the keys in keys, passing the missing keys as parameters to aBlock as they're encountered" keys do: [:key | self removeKey: key ifAbsent: [aBlock value: key]] ] remove: anAssociation [ "Remove anAssociation's key from the dictionary" ^Processor activeProcess environment removeKey: anAssociation key ifAbsent: [] ] remove: anAssociation ifAbsent: aBlock [ "Remove anAssociation's key from the dictionary" ^Processor activeProcess environment removeKey: anAssociation key ifAbsent: aBlock ] removeKey: aSymbol [ "Remove the aSymbol key from the dictionary" ^Processor activeProcess environment removeKey: aSymbol ifAbsent: [] ] removeKey: aSymbol ifAbsent: aBlock [ "Remove the aSymbol key from the dictionary" ^Processor activeProcess environment removeKey: aSymbol ifAbsent: aBlock ] ] smalltalk-3.2.5/kernel/ByteArray.st0000644000175000017500000004145012123404352014160 00000000000000"====================================================================== | | ByteArray Method Definitions | | ======================================================================" "====================================================================== | | Copyright 1988,92,94,95,99,2000,2001,2002,2006,2008,2009 | Free Software Foundation, Inc. | Written by Steve Byrne. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" ArrayedCollection subclass: ByteArray [ ByteArray class >> fromCData: aCObject size: anInteger [ "Answer a ByteArray containing anInteger bytes starting at the location pointed to by aCObject" ^SystemExceptions.WrongClass signalOn: anInteger mustBe: SmallInteger ] asString [ "Answer a String whose character's ASCII codes are the receiver's contents" | string size | size := self size. string := String new: size. string replaceFrom: 1 to: size withByteArray: self startingAt: 1. ^string ] asUnicodeString [ "Answer a UnicodeString whose character's codes are the receiver's contents. This is not implemented unless you load the I18N package." self shouldNotImplement ] isLiteralObject [ "Answer whether the receiver is expressible as a Smalltalk literal." ^self isReadOnly not ] storeLiteralOn: aStream [ "Put a Smalltalk literal evaluating to the receiver on aStream." self class == ByteArray ifFalse: [ ^super storeLiteralOn: aStream ]. aStream nextPut: $#. aStream nextPut: $[. self do: [:elt | aStream print: elt; space]. aStream nextPut: $] ] storeOn: aStream [ "Put Smalltalk code evaluating to the receiver on aStream." self class == ByteArray ifFalse: [ ^super storeOn: aStream ]. self storeLiteralOn: aStream. self isReadOnly ifFalse: [aStream nextPutAll: ' copy'] ] at: anIndex ifAbsent: aBlock [ "Answer the index-th indexed instance variable of the receiver" ^self checkIndexableBounds: anIndex ifAbsent: aBlock ] objectAt: index [ "Access the Smalltalk object (OOP) at the given index in the receiver. Indices are 1-based just like for other Smalltalk access." ^self type: 9 at: index ] charAt: index [ "Access the C char at the given index in the receiver. The value is returned as a Smalltalk Character. Indices are 1-based just like for other Smalltalk access." ^self type: 0 at: index ] unsignedCharAt: index [ "Access the C unsigned char at the given index in the receiver. The value is returned as a Smalltalk Character. Indices are 1-based just like for other Smalltalk access." ^self type: 1 at: index ] ucharAt: index [ "Access the C unsigned char at the given index in the receiver. The value is returned as a Smalltalk Character. Indices are 1-based just like for other Smalltalk access." ^self type: 1 at: index ] shortAt: index [ "Access the C short int at the given index in the receiver. Indices are 1-based just like for other Smalltalk access." ^self type: 2 at: index ] unsignedShortAt: index [ "Access the C unsigned short int at the given index in the receiver. Indices are 1-based just like for other Smalltalk access." ^self type: 3 at: index ] ushortAt: index [ "Access the C unsigned short int at the given index in the receiver. Indices are 1-based just like for other Smalltalk access." ^self type: 3 at: index ] longAt: index [ "Access the C long int at the given index in the receiver. Indices are 1-based just like for other Smalltalk access." ^self type: 4 at: index ] unsignedLongAt: index [ "Access the C unsigned long int at the given index in the receiver. Indices are 1-based just like for other Smalltalk access." ^self type: 5 at: index ] ulongAt: index [ "Access the C unsigned long int at the given index in the receiver. Indices are 1-based just like for other Smalltalk access." ^self type: 5 at: index ] intAt: index [ "Access the C int at the given index in the receiver. Indices are 1-based just like for other Smalltalk access." ^self type: 10 at: index ] unsignedIntAt: index [ "Access the C unsigned int at the given index in the receiver. Indices are 1-based just like for other Smalltalk access." ^self type: 11 at: index ] uintAt: index [ "Access the C unsigned int at the given index in the receiver. Indices are 1-based just like for other Smalltalk access." ^self type: 11 at: index ] floatAt: index [ "Access the C float at the given index in the receiver. Indices are 1-based just like for other Smalltalk access." ^self type: 6 at: index ] doubleAt: index [ "Access the C double at the given index in the receiver. Indices are 1-based just like for other Smalltalk access." ^self type: 7 at: index ] longDoubleAt: index [ "Access the C long double at the given index in the receiver. Indices are 1-based just like for other Smalltalk access." ^self type: 12 at: index ] stringAt: index [ "Access the string pointed by the C `char *' at the given index in the receiver. Indices are 1-based just like for other Smalltalk access." ^self type: 8 at: index ] objectAt: index put: value [ "Store a pointer (OOP) to the Smalltalk object identified by `value', at the given index in the receiver. Indices are 1-based just like for other Smalltalk access." ^self type: 9 at: index put: value ] charAt: index put: value [ "Store as a C char the Smalltalk Character or Integer object identified by `value', at the given index in the receiver, using sizeof(char) bytes - i.e. 1 byte. Indices are 1-based just like for other Smalltalk access." ^self type: 0 at: index put: value ] unsignedCharAt: index put: value [ "Store as a C char the Smalltalk Character or Integer object identified by `value', at the given index in the receiver, using sizeof(char) bytes - i.e. 1 byte. Indices are 1-based just like for other Smalltalk access." ^self type: 1 at: index put: value ] ucharAt: index put: value [ "Store as a C char the Smalltalk Character or Integer object identified by `value', at the given index in the receiver, using sizeof(char) bytes - i.e. 1 byte. Indices are 1-based just like for other Smalltalk access." ^self type: 1 at: index put: value ] shortAt: index put: value [ "Store the Smalltalk Integer object identified by `value', at the given index in the receiver, using sizeof(short) bytes. Indices are 1-based just like for other Smalltalk access." ^self type: 2 at: index put: value ] unsignedShortAt: index put: value [ "Store the Smalltalk Integer object identified by `value', at the given index in the receiver, using sizeof(short) bytes. Indices are 1-based just like for other Smalltalk access." ^self type: 3 at: index put: value ] ushortAt: index put: value [ "Store the Smalltalk Integer object identified by `value', at the given index in the receiver, using sizeof(short) bytes. Indices are 1-based just like for other Smalltalk access." ^self type: 3 at: index put: value ] longAt: index put: value [ "Store the Smalltalk Integer object identified by `value', at the given index in the receiver, using sizeof(long) bytes. Indices are 1-based just like for other Smalltalk access." ^self type: 4 at: index put: value ] unsignedLongAt: index put: value [ "Store the Smalltalk Integer object identified by `value', at the given index in the receiver, using sizeof(long) bytes. Indices are 1-based just like for other Smalltalk access." ^self type: 5 at: index put: value ] ulongAt: index put: value [ "Store the Smalltalk Integer object identified by `value', at the given index in the receiver, using sizeof(long) bytes. Indices are 1-based just like for other Smalltalk access." ^self type: 5 at: index put: value ] intAt: index put: value [ "Store the Smalltalk Integer object identified by `value', at the given index in the receiver, using sizeof(int) bytes. Indices are 1-based just like for other Smalltalk access." ^self type: 10 at: index put: value ] unsignedIntAt: index put: value [ "Store the Smalltalk Integer object identified by `value', at the given index in the receiver, using sizeof(int) bytes. Indices are 1-based just like for other Smalltalk access." ^self type: 11 at: index put: value ] uintAt: index put: value [ "Store the Smalltalk Integer object identified by `value', at the given index in the receiver, using sizeof(int) bytes. Indices are 1-based just like for other Smalltalk access." ^self type: 11 at: index put: value ] floatAt: index put: value [ "Store the Smalltalk Float object identified by `value', at the given index in the receiver, writing it like a C float. Indices are 1-based just like for other Smalltalk access." ^self type: 6 at: index put: value ] doubleAt: index put: value [ "Store the Smalltalk Float object identified by `value', at the given index in the receiver, writing it like a C double. Indices are 1-based just like for other Smalltalk access." ^self type: 7 at: index put: value ] longDoubleAt: index put: value [ "Store the Smalltalk Float object identified by `value', at the given index in the receiver, writing it like a C double. Indices are 1-based just like for other Smalltalk access." ^self type: 12 at: index put: value ] stringAt: index put: value [ "Store the Smalltalk String object identified by `value', at the given index in the receiver, writing it like a *FRESHLY ALLOCATED* C string. It is the caller's responsibility to free it if necessary. Indices are 1-based just like for other Smalltalk access." ^self type: 8 at: index put: value ] growSize [ "Answer the amount by which a ByteArray will grow if necessary. Note - explicit growing of a Collection is a private thing you should not employ" ^self size ] castTo: type [ "Give access to the receiver as a value with the given CType." ^(CObject new storage: self) castTo: type ] type: type at: index [ "Private - Access in the receiver a value with the given type at the given 1-based index." ^(CObject new storage: self) at: index - 1 type: type ] type: type at: index put: value [ "Private - Write to the receiver a value with the given type at the given 1-based index." self isReadOnly ifTrue: [^SystemExceptions.ReadOnlyObject signal]. ^(CObject new storage: self) at: index - 1 put: value type: type ] byteAt: index [ "Answer the index-th indexed instance variable of the receiver" self checkIndexableBounds: index ] byteAt: index put: value [ "Store the `value' byte in the index-th indexed instance variable of the receiver" self checkIndexableBounds: index put: value ] = aCollection [ "Answer whether the receiver's items match those in aCollection" ^false ] hash [ "Answer an hash value for the receiver" ^0 ] indexOf: anElement startingAt: anIndex ifAbsent: exceptionBlock [ "Answer the first index > anIndex which contains anElement. Invoke exceptionBlock and answer its result if no item is found" "If anIndex is just past the end of the collection, don't raise an error (this is the most generic solution that avoids that #indexOf: fails when the collection is empty." ^(anIndex < 1 or: [anIndex > (self size + 1)]) ifTrue: [self checkIndexableBounds: anIndex] ifFalse: [exceptionBlock value] ] indexOf: anElement startingAt: anIndex [ "Answer the first index > anIndex which contains anElement. Invoke exceptionBlock and answer its result if no item is found" "If anIndex is just past the end of the collection, don't raise an error (this is the most generic solution that avoids that #indexOf: fails when the collection is empty." ^(anIndex < 1 or: [anIndex > (self size + 1)]) ifTrue: [self checkIndexableBounds: anIndex] ifFalse: [0] ] replaceFrom: start to: stop withString: aString startingAt: replaceStart [ "Replace the characters from start to stop with the ASCII codes contained in aString (which, actually, can be any variable byte class), starting at the replaceStart location of aString" ^super replaceFrom: start to: stop with: aString startingAt: replaceStart ] replaceFrom: start to: stop with: aByteArray startingAt: replaceStart [ "Replace the characters from start to stop with the bytes contained in aByteArray (which, actually, can be any variable byte class), starting at the replaceStart location of aByteArray" ^super replaceFrom: start to: stop with: aByteArray startingAt: replaceStart ] asCData [ "Allocate memory with malloc for a copy of the receiver, and return a pointer to it as a CByte." ^self asCData: CByteType ] asCData: aCType [ "Allocate memory with malloc for a copy of the receiver, and return it converted to a CObject with the given type" ^self primitiveFailed ] ] smalltalk-3.2.5/kernel/LinkedList.st0000644000175000017500000001231212123404352014313 00000000000000"====================================================================== | | LinkedList Method Definitions | | ======================================================================" "====================================================================== | | Copyright 1988,92,94,95,99,2000,2001,2002 | Free Software Foundation, Inc. | Written by Steve Byrne. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" SequenceableCollection subclass: LinkedList [ | firstLink lastLink | at: index [ "Return the element that is index into the linked list." self isEmpty ifTrue: [ ^SystemExceptions.IndexOutOfRange signalOn: self withIndex: index ]. ^firstLink at: index ] at: index put: object [ self shouldNotImplement ] add: aLink [ "Add aLink at the end of the list; return aLink." self addLast: aLink. ^aLink ] addFirst: aLink [ "Add aLink at the head of the list; return aLink." lastLink isNil ifTrue: [lastLink := aLink]. aLink nextLink: firstLink. ^firstLink := aLink ] addLast: aLink [ "Add aLink at then end of the list; return aLink." firstLink isNil ifTrue: [firstLink := aLink]. lastLink notNil ifTrue: [lastLink nextLink: aLink]. ^lastLink := aLink ] first [ "Retrieve the first element of the list and return it, or error if the list is empty." self isEmpty ifTrue: [ ^SystemExceptions.IndexOutOfRange signalOn: self withIndex: 1 ]. ^firstLink ] last [ "Retrieve the last element of the list and return it, or error if the list is empty." self isEmpty ifTrue: [ ^SystemExceptions.IndexOutOfRange signalOn: self withIndex: 0 ]. ^lastLink ] removeFirst [ "Remove the first element from the list and return it, or error if the list is empty." ^self remove: firstLink ifAbsent: [SystemExceptions.EmptyCollection signalOn: self] ] removeLast [ "Remove the final element from the list and return it, or error if the list is empty." ^self remove: lastLink ifAbsent: [SystemExceptions.EmptyCollection signalOn: self] ] remove: aLink ifAbsent: aBlock [ "Remove aLink from the list and return it, or invoke aBlock if it's not found in the list." | prev | aLink == firstLink ifTrue: [firstLink isNil ifTrue: [^aBlock value]. firstLink := firstLink nextLink. firstLink isNil ifTrue: [lastLink := nil]. aLink nextLink: nil. ^aLink]. prev := firstLink. [prev isNil ifTrue: [^aBlock value]. prev nextLink == aLink] whileFalse: [prev := prev nextLink]. prev nextLink: aLink nextLink. aLink == lastLink ifTrue: [lastLink := prev]. aLink nextLink: nil. ^aLink ] do: aBlock [ "Enumerate each object in the list, passing it to aBlock (actual behavior might depend on the subclass of Link that is being used)." self isEmpty ifFalse: [firstLink do: aBlock] ] includes: anObject [ "Answer whether we include anObject" "Blah, this is roughly the same implementation as in Collection." self isEmpty ifTrue: [^false]. firstLink do: [:element | anObject = element ifTrue: [^true]]. ^false ] identityIncludes: anObject [ "Answer whether we include the anObject object" "Blah, this is roughly the same implementation as in Collection." self isEmpty ifTrue: [^false]. firstLink do: [:element | anObject == element ifTrue: [^true]]. ^false ] isEmpty [ "Returns true if the list contains no members" ^firstLink isNil ] notEmpty [ "Returns true if the list contains at least a member" ^firstLink notNil ] size [ "Answer the number of elements in the list. Warning: this is O(n)" ^self isEmpty ifTrue: [0] ifFalse: [firstLink size] ] ] smalltalk-3.2.5/kernel/AbstNamespc.st0000644000175000017500000003303112123404352014452 00000000000000"====================================================================== | | AbstractNamespace Method Definitions | | ======================================================================" "====================================================================== | | Copyright 1999, 2000, 2001, 2002, 2007, 2008 | Free Software Foundation, Inc. | Written by Paolo Bonzini. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" BindingDictionary subclass: AbstractNamespace [ | name subspaces sharedPools | AbstractNamespace class >> new [ "Disabled - use #new to create instances" SystemExceptions.WrongMessageSent signalOn: #new useInstead: #new: ] AbstractNamespace class >> primNew: parent name: spaceName [ "Private - Create a new namespace with the given name and parent, and add to the parent a key that references it." (parent at: spaceName ifAbsent: [nil]) isNamespace ifTrue: [^parent at: spaceName asGlobalKey]. ^parent at: spaceName asGlobalKey put: ((super new: 24) setSuperspace: parent; name: spaceName asSymbol; yourself) ] whileCurrentDo: aBlock [ "Evaluate aBlock with the current namespace set to the receiver. Answer the result of the evaluation." | oldCurrent | oldCurrent := Namespace current. Namespace current: self. ^aBlock ensure: [Namespace current: oldCurrent] ] copyEmpty: newSize [ "Answer an empty copy of the receiver whose size is newSize" ^(super copyEmpty: newSize) name: self name; setSubspaces: self subspaces; yourself ] allAssociations [ "Answer a Dictionary with all of the associations in the receiver and each of its superspaces (duplicate keys are associated to the associations that are deeper in the namespace hierarchy)" | allAssociations value | allAssociations := Dictionary new. self withAllSuperspaces reverseDo: [:each | 1 to: each primSize do: [:index | value := each primAt: index. value isNil ifFalse: [allAssociations add: value copy]]]. ^allAssociations ] allBehaviorsDo: aBlock [ "Evaluate aBlock once for each class and metaclass in the namespace." Behavior withAllSubclassesDo: [:subclass | subclass isClass | subclass isMetaclass ifFalse: [subclass allInstancesDo: [:each | each environment == self ifTrue: [aBlock value: each]]]]. "Special case classes and metaclasses because #allInstancesDo: is very slow - the less we use it, the better it is." Class allSubclassesDo: [:eachMeta | eachMeta environment == self ifTrue: [aBlock value: eachMeta; value: eachMeta instanceClass]] ] allClassesDo: aBlock [ "Evaluate aBlock once for each class in the namespace." Class allSubclassesDo: [:eachMeta | eachMeta environment == self ifTrue: [aBlock value: eachMeta instanceClass]] ] allClassObjectsDo: aBlock [ "Evaluate aBlock once for each class and metaclass in the namespace." Class allSubclassesDo: [:eachMeta | eachMeta environment == self ifTrue: [aBlock value: eachMeta; value: eachMeta instanceClass]] ] allMetaclassesDo: aBlock [ "Evaluate aBlock once for each metaclass in the namespace." Class allSubclassesDo: [:eachMeta | eachMeta environment == self ifTrue: [aBlock value: eachMeta]] ] classAt: aKey [ "Answer the value corrisponding to aKey if it is a class. Fail if either aKey is not found or it is associated to something different from a class." ^self classAt: aKey ifAbsent: [SystemExceptions.NotFound signalOn: aKey what: 'class'] ] classAt: aKey ifAbsent: aBlock [ "Answer the value corrisponding to aKey if it is a class. Evaluate aBlock and answer its result if either aKey is not found or it is associated to something different from a class." | class | class := self at: aKey asGlobalKey ifAbsent: [^aBlock value]. class isClass ifFalse: [^aBlock value]. ^class ] addSharedPool: aDictionary [ "Import the given bindings for classes compiled with me as environment." sharedPools isNil ifTrue: [^sharedPools := {aDictionary}]. (sharedPools includes: aDictionary) ifFalse: [sharedPools := sharedPools copyWith: aDictionary]. ] import: aDictionary [ "Import the given bindings for classes compiled with me as environment." self addSharedPool: aDictionary ] removeSharedPool: aDictionary [ "Remove aDictionary from my list of direct pools." sharedPools isNil ifFalse: [sharedPools := sharedPools copyWithout: aDictionary] ] sharedPoolDictionaries [ "Answer the shared pools (not names) imported for my classes." ^sharedPools ifNil: [#()] ] inheritedKeys [ "Answer a Set of all the keys in the receiver and its superspaces" self subclassResponsibility ] set: key to: newValue [ "Assign newValue to the variable named as specified by `key'. This method won't define a new variable; instead if the key is not found it will search in superspaces and raising an error if the variable cannot be found in any of the superspaces. Answer newValue." ^self set: key to: newValue ifAbsent: [SystemExceptions.NotFound signalOn: key what: 'key'] ] set: key to: newValue ifAbsent: aBlock [ "Assign newValue to the variable named as specified by `key'. This method won't define a new variable; instead if the key is not found it will search in superspaces and evaluate aBlock if it is not found. Answer newValue." self subclassResponsibility ] values [ "Answer a Bag containing the values of the receiver" | aBag value | aBag := Bag new: tally. 1 to: self primSize do: [:index | value := self primAt: index. value isNil ifFalse: [aBag add: value value]]. ^aBag ] addSubspace: aSymbol [ "Create a namespace named aSymbol, add it to the receiver's subspaces, and answer it." ^Namespace primNew: self name: aSymbol ] allSubassociationsDo: aBlock [ "Invokes aBlock once for every association in each of the receiver's subspaces." self allSubspacesDo: [:subspace | subspace associationsDo: aBlock] ] allSubspacesDo: aBlock [ "Invokes aBlock for all subspaces, both direct and indirect." self subspaces notNil ifTrue: [self subspaces do: [:space | aBlock value: space. space allSubspacesDo: aBlock]] ] allSubspaces [ "Answer the direct and indirect subspaces of the receiver in a Set" | aSet | aSet := Set new. self allSubspacesDo: [:subspace | aSet add: subspace]. ^aSet ] allSuperspacesDo: aBlock [ "Evaluate aBlock once for each of the receiver's superspaces" | space | space := self. [space := space superspace. space notNil] whileTrue: [aBlock value: space] ] includesClassNamed: aString [ "Answer whether the receiver or any of its superspaces include the given class -- note that this method (unlike #includesKey:) does not require aString to be interned and (unlike #includesGlobalNamed:) only returns true if the global is a class object." | possibleClass | possibleClass := Symbol hasInterned: aString ifTrue: [:aSymbol | self at: aSymbol ifAbsent: [nil]]. ^possibleClass isClass ] includesGlobalNamed: aString [ "Answer whether the receiver or any of its superspaces include the given key -- note that this method (unlike #includesKey:) does not require aString to be interned but (unlike #includesClassNamed:) returns true even if the global is not a class object." Symbol hasInterned: aString ifTrue: [:aSymbol | self at: aSymbol ifPresent: [:value | ^true]]. ^false ] removeSubspace: aSymbol [ "Remove my subspace named aSymbol from the hierarchy." | spaceName | spaceName := aSymbol asGlobalKey. "as with primNew:name:" self subspaces remove: (self hereAt: spaceName) ifAbsent: [SystemExceptions.InvalidValue signalOn: aSymbol reason: 'aSymbol must name a subspace']. ^self removeKey: spaceName ] selectSubspaces: aBlock [ "Return a Set of subspaces of the receiver satisfying aBlock." | aSet | aSet := Set new. self allSubspacesDo: [:subspace | (aBlock value: subspace) ifTrue: [aSet add: subspace]]. ^aSet ] selectSuperspaces: aBlock [ "Return a Set of superspaces of the receiver satisfying aBlock." | aSet | aSet := Set new. self allSuperspacesDo: [:superspace | (aBlock value: superspace) ifTrue: [aSet add: superspace]]. ^aSet ] siblings [ "Answer all the other children of the same namespace as the receiver." self subclassResponsibility ] siblingsDo: aBlock [ "Evaluate aBlock once for each of the other root namespaces, passing the namespace as a parameter." self subclassResponsibility ] superspace [ "Answer the receiver's superspace." ^environment ] superspace: aNamespace [ "Set the superspace of the receiver to be 'aNamespace'. Also adds the receiver as a subspace of it." | oldSuperspace newSuperspace root | oldSuperspace := self superspace. newSuperspace := aNamespace. oldSuperspace == newSuperspace ifTrue: [^self]. "don't need to change anything" oldSuperspace isNil ifTrue: [oldSuperspace := Smalltalk. self become: ((Namespace basicNew: self primSize) copyAllFrom: self)] ifFalse: [oldSuperspace subspaces remove: self]. newSuperspace isNil ifTrue: [newSuperspace := Smalltalk. self become: ((AbstractNamespace basicNew: self primSize) copyAllFrom: self)] ifFalse: [aNamespace subspaces add: self]. environment := aNamespace. newSuperspace add: (oldSuperspace remove: self name asGlobalKey -> nil). self do: [:each | each isClass ifTrue: [each compileAll. each class compileAll]]. self allSubassociationsDo: [:assoc | assoc value isClass ifTrue: [assoc value compileAll. assoc value class compileAll]] ] subspaces [ "Answer the receiver's direct subspaces" subspaces isNil ifTrue: [subspaces := IdentitySet new]. ^subspaces ] subspacesDo: aBlock [ "Invokes aBlock for all direct subspaces." self subspaces do: aBlock ] withAllSubspaces [ "Answer a Set containing the receiver together with its direct and indirect subspaces" | aSet | aSet := Set with: self. aSet addAll: self allSubspaces. ^aSet ] withAllSubspacesDo: aBlock [ "Invokes aBlock for the receiver and all subclasses, both direct and indirect." aBlock value: self. self subspaces do: [:subspace | aBlock value: subspace. subspace allSubspacesDo: aBlock] ] nameIn: aNamespace [ "Answer Smalltalk code compiling to the receiver when the current namespace is aNamespace" self subclassResponsibility ] name [ "Answer the receiver's name" ^name ] name: aSymbol [ "Change the receiver's name to aSymbol" name := aSymbol ] printOn: aStream [ "Print a representation of the receiver" aStream nextPutAll: self name ] storeOn: aStream [ "Store Smalltalk code compiling to the receiver" self subclassResponsibility ] setSuperspace: newSuperspace [ self environment: newSuperspace. self environment subspaces add: self ] setSubspaces: newSubspaces [ subspaces := newSubspaces ] isNamespace [ ^true ] isSmalltalk [ ^false ] ] smalltalk-3.2.5/kernel/Character.st0000644000175000017500000003264512123404352014160 00000000000000"====================================================================== | | Character Method Definitions | | ======================================================================" "====================================================================== | | Copyright 1988,92,94,95,99,2000,2001,2002,2005,2006,2007,2008 | Free Software Foundation, Inc. | Written by Steve Byrne. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" Magnitude subclass: Character [ | codePoint | Table := nil. UpperTable := nil. LowerTable := nil. Character class >> isImmediate [ "Answer whether, if x is an instance of the receiver, x copy == x" ^true ] Character class >> initialize [ "Initialize the lookup table which is used to make case and digit-to-char conversions faster. Indices in Table are ASCII values incremented by one. Indices 1-256 classify chars (0 = nothing special, 2 = separator, 48 = digit, 55 = uppercase, 3 = lowercase), indices 257-512 map to lowercase chars, indices 513-768 map to uppercase chars." Table := ByteArray new: 768. UpperTable := ByteArray new: 256. LowerTable := ByteArray new: 256. 1 to: 256 do: [:value | UpperTable at: value put: value - 1. LowerTable at: value put: value - 1. (value between: 49 and: 58) ifTrue: [Table at: value put: 48]. (value between: 66 and: 91) ifTrue: [Table at: value put: 55. LowerTable at: value put: value + 31]. (value between: 98 and: 123) ifTrue: [Table at: value put: 3. UpperTable at: value put: value - 33]]. Table at: Character space value + 1 put: 2; at: Character cr value + 1 put: 2; at: Character tab value + 1 put: 2; at: Character nl value + 1 put: 2; at: Character newPage value + 1 put: 2; at: $. value + 1 put: 4; at: $, value + 1 put: 4; at: $: value + 1 put: 4; at: $; value + 1 put: 4; at: $! value + 1 put: 4; at: $? value + 1 put: 4 ] Character class >> codePoint: anInteger [ "Returns the character object, possibly an UnicodeCharacter, corresponding to anInteger. Error if anInteger is not an integer, or not in 0..16r10FFFF." anInteger isInteger ifFalse: [SystemExceptions.WrongClass signalOn: anInteger mustBe: SmallInteger] ifTrue: [SystemExceptions.ArgumentOutOfRange signalOn: anInteger mustBeBetween: 0 and: 1114111] ] Character class >> asciiValue: anInteger [ "Returns the character object corresponding to anInteger. Error if anInteger is not an integer, or not in 0..127." anInteger isInteger ifFalse: [SystemExceptions.WrongClass signalOn: anInteger mustBe: SmallInteger]. ^(anInteger between: 0 and: 127) ifTrue: [self value: anInteger] ifFalse: [SystemExceptions.ArgumentOutOfRange signalOn: anInteger mustBeBetween: 0 and: 127] ] Character class >> value: anInteger [ "Returns the character object corresponding to anInteger. Error if anInteger is not an integer, or not in 0..255." anInteger isInteger ifFalse: [SystemExceptions.WrongClass signalOn: anInteger mustBe: SmallInteger] ifTrue: [SystemExceptions.ArgumentOutOfRange signalOn: anInteger mustBeBetween: 0 and: 255] ] Character class >> backspace [ "Returns the character 'backspace'" ^##(Character value: 8) ] Character class >> cr [ "Returns the character 'cr'" ^##(Character value: 13) ] Character class >> bell [ "Returns the character 'bel'" ^##(Character value: 7) ] Character class >> eof [ "Returns the character 'eof', also known as 'sub'" ^##(Character value: 26) ] Character class >> eot [ "Returns the character 'eot', also known as 'Ctrl-D'" ^##(Character value: 4) ] Character class >> esc [ "Returns the character 'esc'" ^##(Character value: 27) ] Character class >> nul [ "Returns the character 'nul'" ^##(Character value: 0) ] Character class >> tab [ "Returns the character 'tab'" ^##(Character value: 9) ] Character class >> nl [ "Returns the character 'nl', also known as 'lf'" ^##(Character value: 10) ] Character class >> lf [ "Returns the character 'lf', also known as 'nl'" ^##(Character value: 10) ] Character class >> newPage [ "Returns the character 'newPage', also known as 'ff'" ^##(Character value: 12) ] Character class >> ff [ "Returns the character 'ff', also known as 'newPage'" ^##(Character value: 12) ] Character class >> space [ "Returns the character 'space'" ^$ ] Character class >> digitValue: anInteger [ "Returns a character that corresponds to anInteger. 0-9 map to $0-$9, 10-35 map to $A-$Z" ^'0123456789ABCDEFGHIJKLMNOPQRSTUVWXYZ' at: anInteger + 1 ] asCharacter [ "Return the receiver, since it is already a character." ^self ] digitValue [ "Returns the value of self interpreted as a digit. Here, 'digit' means either 0-9, or A-Z, which maps to 10-35." | result | result := Table at: 1 + codePoint ifAbsent: [-1]. ^result > 32 ifTrue: [codePoint - result] ifFalse: [SystemExceptions.InvalidValue signalOn: self reason: 'Not a digit character'] ] < aCharacter [ "Compare the character's ASCII value. Answer whether the receiver's is the least." ^codePoint < aCharacter codePoint ] <= aCharacter [ "Compare the character's ASCII value. Answer whether the receiver's is the least or their equal." ^codePoint <= aCharacter codePoint ] > aCharacter [ "Compare the character's ASCII value. Answer whether the receiver's is the greatest." ^codePoint > aCharacter codePoint ] >= aCharacter [ "Compare the character's ASCII value. Answer whether the receiver's is the greatest or their equal." ^codePoint >= aCharacter codePoint ] isDigit [ "True if self is a 0-9 digit" ^(Table at: 1 + codePoint ifAbsent: [0]) = 48 ] isLetter [ "True if self is an upper- or lowercase letter" ^((Table at: 1 + codePoint ifAbsent: [0]) bitAnd: 1) = 1 ] isAlphaNumeric [ "True if self is a letter or a digit" ^((Table at: 1 + self codePoint ifAbsent: [0]) bitAnd: 17) > 0 ] isLowercase [ "True if self is a lowercase letter" ^(Table at: 1 + codePoint ifAbsent: [0]) = 3 ] isUppercase [ "True if self is uppercase" ^(Table at: 1 + codePoint ifAbsent: [0]) = 55 ] isSeparator [ "Returns true if self is a space, cr, tab, nl, or newPage" ^(Table at: 1 + codePoint ifAbsent: [0]) = 2 ] isPunctuation [ "Returns true if self is one of '.,:;!?'" ^(Table at: 1 + codePoint ifAbsent: [0]) = 4 ] isPathSeparator [ "Returns true if self is a path separator ($/ or $\ under Windows, $/ only under Unix systems including Mac OS X)." ^self == $/ or: [self == Directory pathSeparator] ] isVowel [ "Returns true if self is a, e, i, o, or u; case insensitive" "So rare it isn't worth optimization" | char | char := self asLowercase. char = $a ifTrue: [^true]. char = $e ifTrue: [^true]. char = $i ifTrue: [^true]. char = $o ifTrue: [^true]. char = $u ifTrue: [^true]. ^false ] isDigit: radix [ "Answer whether the receiver is a valid character in the given radix." | result | (radix between: 2 and: 36) ifFalse: [SystemExceptions.ArgumentOutOfRange signalOn: radix mustBeBetween: 2 and: 36]. result := Table at: 1 + codePoint ifAbsent: [0]. ^result > 32 and: [codePoint - result between: 0 and: radix - 1] ] asLowercase [ "Returns self as a lowercase character if it's an uppercase letter, otherwise returns the character unchanged." ^Character value: (LowerTable at: 1 + codePoint ifAbsent: [codePoint]) ] asUppercase [ "Returns self as a uppercase character if it's an lowercase letter, otherwise returns the character unchanged." ^Character value: (UpperTable at: 1 + codePoint ifAbsent: [codePoint]) ] * aNumber [ "Returns a String with aNumber occurrences of the receiver." ^String new: aNumber withAll: self ] asString [ "Returns the character self as a string. Only valid if the character is between 0 and 255." ^String with: self ] asUnicodeString [ "Returns the character self as a Unicode string." ^UnicodeString with: self ] asSymbol [ "Returns the character self as a symbol." ^Symbol internCharacter: self ] displayOn: aStream [ "Print a representation of the receiver on aStream. Unlike #printOn:, this method strips the leading dollar." (codePoint between: 0 and: 127) ifTrue: [aStream nextPut: self] ifFalse: [aStream nextPut: $<. self printCodePointOn: aStream. aStream nextPut: $>] ] storeLiteralOn: aStream [ "Store on aStream some Smalltalk code which compiles to the receiver" self storeOn: aStream ] printOn: aStream [ "Print a representation of the receiver on aStream" self storeOn: aStream ] isLiteralObject [ "Answer whether the receiver is expressible as a Smalltalk literal." ^true ] storeOn: aStream [ "Store Smalltalk code compiling to the receiver on aStream" aStream nextPut: $$. (codePoint between: 32 and: 126) ifTrue: [aStream nextPut: self. ^self]. aStream nextPut: $<. self printCodePointOn: aStream. aStream nextPut: $> ] printCodePointOn: aStream [ codePoint < 32 ifTrue: [aStream print: codePoint. ^self]. aStream nextPutAll: '16r'. codePoint <= 255 ifTrue: [aStream nextPut: $0]. codePoint <= 4095 ifTrue: [aStream nextPut: $0]. aStream nextPutAll: (codePoint printString: 16) ] asLowercaseValue [ "Returns the ASCII value of the receiver converted to a lowercase character if it's an uppercase letter, otherwise returns the ASCII value unchanged." ^LowerTable at: 1 + codePoint ifAbsent: [codePoint] ] isCharacter [ "Answer True. We're definitely characters" ^true ] = char [ "Boolean return value; true if the characters are equal" ] asciiValue [ "Returns the integer value corresponding to self. #codePoint, #asciiValue, #value, and #asInteger are synonyms." ^codePoint ] asInteger [ "Returns the integer value corresponding to self. #codePoint, #asciiValue, #value, and #asInteger are synonyms." ^codePoint ] codePoint [ "Returns the integer value corresponding to self. #codePoint, #asciiValue, #value, and #asInteger are synonyms." ^codePoint ] value [ "Returns the integer value corresponding to self. #codePoint, #asciiValue, #value, and #asInteger are synonyms." ^codePoint ] ] Eval [ Character initialize ] smalltalk-3.2.5/kernel/Set.st0000644000175000017500000000760712130343734013023 00000000000000"====================================================================== | | Set Method Definitions | | ======================================================================" "====================================================================== | | Copyright 1988,92,94,95,99,2000,2001 | Free Software Foundation, Inc. | Written by Steve Byrne and Paolo Bonzini. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" HashedCollection subclass: Set [ & aSet [ "Compute the set intersection of the receiver and aSet." | intersectionSet | intersectionSet := self copyEmpty: self size. self size < aSet size ifTrue: [self do: [:elem | (aSet includes: elem) ifTrue: [intersectionSet add: elem]]] ifFalse: [aSet do: [:elem | (self includes: elem) ifTrue: [intersectionSet add: elem]]]. ^intersectionSet ] + aSet [ "Compute the set union of the receiver and aSet." | unionSet | unionSet := self copy. unionSet addAll: aSet. ^unionSet ] - aSet [ "Compute the set difference of the receiver and aSet." | differenceSet | differenceSet := self copyEmpty: self size. self do: [:elem | (aSet includes: elem) ifFalse: [differenceSet add: elem]]. ^differenceSet ] < aSet [ "Answer whether the receiver is a strict subset of aSet" self size < aSet size ifFalse: [^false] ifTrue: [self do: [:elem | (aSet includes: elem) ifFalse: [^false]]]. ^true ] <= aSet [ "Answer whether the receiver is a subset of aSet" self size <= aSet size ifFalse: [^false] ifTrue: [self do: [:elem | (aSet includes: elem) ifFalse: [^false]]]. ^true ] > aSet [ "Answer whether the receiver is a strict superset of aSet" ^aSet < self ] >= aSet [ "Answer whether the receiver is a superset of aSet" ^aSet <= self ] hashFor: anObject [ "Return an hash value for the item, anObject" ^anObject hash ] findIndex: anObject [ "Tries to see if anObject exists as an indexed variable. As soon as nil or anObject is found, the index of that slot is answered" | index size element | self beConsistent. "Sorry for the lack of readability, but I want speed... :-)" index := (anObject hash scramble bitAnd: (size := self primSize) - 1) + 1. [((element := self primAt: index) isNil or: [element = anObject]) ifTrue: [^index]. index == size ifTrue: [index := 1] ifFalse: [index := index + 1]] repeat ] findObjectIndex: object [ "Tries to see if anObject exists as an indexed variable. As soon as nil or anObject is found, the index of that slot is answered" ^self findIndex: object ] ] smalltalk-3.2.5/kernel/RunArray.st0000644000175000017500000003056412123404352014025 00000000000000"====================================================================== | | RunArray Method Definitions | | ======================================================================" "====================================================================== | | Copyright 1999, 2000, 2001, 2002, 2009 Free Software Foundation, Inc. | Written by Paolo Bonzini. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" "Some of the methods I define (first, last, indexOf:startingAt:ifAbsent:, shallowCopy, deepCopy, =, hash) are here only for performance purposes (their inherited implementation works, but it is slow)" OrderedCollection subclass: RunArray [ | map mapIndex firstInRun lastInRun size | RunArray class >> new [ "Answer an empty RunArray" ^(self basicNew) map: OrderedCollection new; initialize ] RunArray class >> new: aSize [ "Answer a RunArray with space for aSize runs" ^(self basicNew) map: (OrderedCollection new: aSize); initialize ] at: anIndex [ "Answer the element at index anIndex" self updateMapIndexFor: anIndex. ^(map at: mapIndex) key ] at: anIndex put: anObject [ "Replace the element at index anIndex with anObject and answer anObject" ^self at: anIndex splitAndPut: anObject decrementBy: 1 ] first [ "Answer the first element in the receiver" ^(map at: 1) key ] last [ "Answer the last element of the receiver" ^(map at: map size) key ] size [ "Answer the number of elements in the receiver" ^size ] addAll: aCollection afterIndex: anIndex [ "Add all the elements of aCollection after the one at index anIndex. If aCollection is unordered, its elements could be added in an order which is not the #do: order" | newMap | aCollection isEmpty ifTrue: [^self]. newMap := aCollection asRunArrayMap. self updateMapIndexFor: anIndex. self splitAt: anIndex decrementBy: 0. map addAll: newMap afterIndex: mapIndex. self packTwoRuns: mapIndex + newMap size - 1; packTwoRuns: mapIndex. size := size + aCollection size ] addAllFirst: aCollection [ "Add all the elements of aCollection at the beginning of the receiver. If aCollection is unordered, its elements could be added in an order which is not the #do: order" ^self addAll: aCollection afterIndex: 0 ] addAllLast: aCollection [ "Add all the elements of aCollection at the end of the receiver. If aCollection is unordered, its elements could be added in an order which is not the #do: order" ^self addAll: aCollection afterIndex: self size ] addFirst: anObject [ "Add anObject at the beginning of the receiver. Watch out: this operation can cause serious performance pitfalls" ^self add: anObject afterIndex: 0 ] addLast: anObject [ "Add anObject at the end of the receiver" ^self add: anObject afterIndex: self size ] add: anObject afterIndex: anIndex [ "Add anObject after the element at index anIndex" size := size + 1. ^self at: anIndex splitAndPut: anObject decrementBy: 0 ] shallowCopy [ "Answer a copy of the receiver. The elements are not copied" ^(self species basicNew) map: (map collect: [:assoc | assoc shallowCopy]); initialize ] deepCopy [ "Answer a copy of the receiver containing copies of the receiver's elements (#copy is used to obtain them)" ^(self species basicNew) map: (map collect: [:assoc | assoc deepCopy]); initialize ] objectsAndRunLengthsDo: aBlock [ "Enumerate all the runs in the receiver, passing to aBlock two parameters for every run: the first is the repeated object, the second is the number of copies" map do: [:each | aBlock value: each key value: each value] ] do: aBlock [ "Enumerate all the objects in the receiver, passing each one to aBlock" map do: [:each | each value timesRepeat: [aBlock value: each key]] ] afterMapIndexAdd: n copiesOf: anObject [ "Private - Add a run of n copies of anObject after the mapIndex-th run. Answer anObject" map add: (Association key: anObject value: n) afterIndex: mapIndex. ^anObject ] at: anIndex splitAndPut: anObject decrementBy: i [ "Private - Split the run at index anIndex (say it's made of n elements) into two runs for a total of n-i elements; between them, put a one element run for anObject. Answer anObject" | run | (self at: (1 max: anIndex)) = anObject ifTrue: ["No need to split, simply update the current run" run := map at: mapIndex. run value: run value + (1 - i)] ifFalse: [self splitAt: anIndex decrementBy: i; afterMapIndexAdd: 1 copiesOf: anObject]. ^anObject ] initialize [ "Private - Initialize mapIndex, firstInRun, lastInRun" map isEmpty ifTrue: [mapIndex := firstInRun := lastInRun := 0] ifFalse: [mapIndex := firstInRun := 1. lastInRun := (map at: 1) value] ] map [ "Private - Answer the receiver's map" ^map ] map: anOrderedCollection [ "Private - Initialize size and set the map to anOrderedCollection" map := anOrderedCollection. size := map inject: 0 into: [:sz :assoc | sz + assoc value] ] packTwoRuns: indexInMap [ "Private - Check if the two runs at indexes indexInMap and indexInMap + 1 are runs for equal elements. If so, pack them in a single run" | run nextRun | indexInMap < 1 ifTrue: [^self]. indexInMap > self size ifTrue: [^self]. run := map at: indexInMap. nextRun := map at: indexInMap + 1. run key = nextRun key ifTrue: [run value: run value + nextRun value. map removeAtIndex: indexInMap + 1] ] splitAt: anIndex decrementBy: i [ "Private - Split the run at index anIndex (say it's made of n elements) into two runs for a total of n-i elements. You must have already called #at: or #updateMapIndexFor: passing them anIndex" | run | anIndex < 1 ifTrue: [^self]. anIndex > self size ifTrue: [^self]. run := map at: mapIndex. anIndex = firstInRun ifTrue: [run value: run value - i. "Decrement mapIndex, update firstInRun and lastInRun" self updateMapIndexFor: anIndex - 1]. anIndex = lastInRun ifTrue: [run value: run value - i]. run value: anIndex - firstInRun + (1 - i). self afterMapIndexAdd: lastInRun - anIndex copiesOf: run key ] updateMapIndexFor: anIndex [ "Private - Update mapIndex so that it points to the run containing the object at index anIndex. To set mapIndex to 0, set anIndex to 0" (anIndex >= firstInRun and: [anIndex <= lastInRun]) ifTrue: [^self]. "anIndex = 0 is used internally by RunArray" anIndex = 0 ifTrue: [mapIndex := firstInRun := lastInRun := 0. ^self]. anIndex < 0 ifTrue: [SystemExceptions.IndexOutOfRange signalOn: self withIndex: anIndex]. anIndex > self size ifTrue: [SystemExceptions.IndexOutOfRange signalOn: self withIndex: anIndex]. anIndex < firstInRun ifTrue: [ [mapIndex := mapIndex - 1. lastInRun := firstInRun - 1. firstInRun := firstInRun - (map at: mapIndex) value. anIndex < firstInRun] whileTrue] ifFalse: [ [mapIndex := mapIndex + 1. firstInRun := lastInRun + 1. lastInRun := lastInRun + (map at: mapIndex) value. lastInRun < anIndex] whileTrue] ] indexOf: anObject startingAt: anIndex ifAbsent: aBlock [ "Answer the index of the first copy of anObject in the receiver, starting the search at the element at index anIndex. If no equal object is found, answer the result of evaluating aBlock" | first last | last := 0. map do: [:each | first := last + 1. last := last + each value. (first >= anIndex and: [each key = anIndex]) ifTrue: [^first]]. ^aBlock value ] removeAtIndex: anIndex [ "Remove the object at index anIndex from the receiver and answer the removed object" | run | self updateMapIndexFor: anIndex. run := map at: mapIndex. size := size - 1. run value = 1 ifFalse: [run value: run value - 1. lastInRun := lastInRun - 1. ^run key]. map removeAtIndex: mapIndex. mapIndex > map size ifTrue: [mapIndex := map size. lastInRun := self size. firstInRun := lastInRun - (map at: map size) value + 1] ifFalse: [lastInRun := firstInRun + (map at: mapIndex) value - 1]. ^run key ] removeFirst [ "Remove the first object from the receiver and answer the removed object" ^self removeAtIndex: 1 ] removeLast [ "Remove the last object from the receiver and answer the removed object" ^self removeAtIndex: self size ] = anObject [ "Answer true if the receiver is equal to anObject" ^anObject class == self class and: [anObject map = self map] ] hash [ "Answer an hash value for the receiver" ^map hash ] ] Collection extend [ asRunArray [ "Answer the receiver converted to a RunArray. If the receiver is not ordered the order of the elements in the RunArray might not be the #do: order." ^(RunArray basicNew) map: self asRunArrayMap; initialize ] asRunArrayMap [ "Private - Answer the receiver converted to an OrderedCollection of Associations whose keys are the actual objects and whose values are the number of consecutive copies of them" "Bags can be easily packed, because they are made of runs of unordered elements like RunArrays. As the #do: order of non-sequenceable collections is undefined, we choose the ordering which yields the best map." ^self asBag asRunArrayMap ] ] Bag extend [ asRunArrayMap [ "Private - Answer the receiver converted to an OrderedCollection of Associations whose keys are the actual objects and whose values are the number of consecutive copies of them" | map | map := OrderedCollection new: contents size. contents associationsDo: [:assoc | map addLast: assoc]. ^map ] ] SequenceableCollection extend [ asRunArrayMap [ "Private - Answer the receiver converted to an OrderedCollection of Associations whose keys are the actual objects and whose values are the number of consecutive copies of them" | map prev startIndex | map := OrderedCollection new. prev := self at: 1. startIndex := 1. self from: 2 to: self size keysAndValuesDo: [:currIndex :each | each = prev ifFalse: [map addLast: (Association key: prev value: currIndex - startIndex). prev := each. startIndex := currIndex]]. map addLast: (Association key: prev value: self size + 1 - startIndex). ^map ] ] smalltalk-3.2.5/kernel/OrderColl.st0000644000175000017500000003655012130343734014154 00000000000000"====================================================================== | | OrderedCollection Method Definitions | | ======================================================================" "====================================================================== | | Copyright 1988,92,94,95,99,2000,2001,2002,2008 | Free Software Foundation, Inc. | Written by Steve Byrne. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" SequenceableCollection subclass: OrderedCollection [ | firstIndex lastIndex | OrderedCollection class >> new: anInteger [ "Answer an OrderedCollection of size anInteger" ^(self basicNew: anInteger) initIndices ] OrderedCollection class >> new [ "Answer an OrderedCollection of default size" ^self new: 16 ] do: aBlock [ "Evaluate aBlock for all the elements in the collection" | index | self beConsistent. index := firstIndex. [ index <= lastIndex ] whileTrue: [ aBlock value: (self basicAt: index). index := index + 1 ] ] first [ "Answer the first item of the receiver" self beConsistent. ^lastIndex >= firstIndex ifTrue: [self basicAt: firstIndex] ifFalse: [SystemExceptions.IndexOutOfRange signalOn: self withIndex: 1] ] last [ "Answer the last item of the receiver" self beConsistent. ^lastIndex >= firstIndex ifTrue: [self basicAt: lastIndex] ifFalse: [SystemExceptions.IndexOutOfRange signalOn: self withIndex: 0] ] at: anIndex [ "Answer the anIndex-th item of the receiver" | index | self beConsistent. index := anIndex + firstIndex - 1. ^(index >= firstIndex and: [index <= lastIndex]) ifTrue: [self basicAt: index] ifFalse: [SystemExceptions.IndexOutOfRange signalOn: self withIndex: anIndex] ] at: anIndex put: anObject [ "Store anObject at the anIndex-th item of the receiver, answer anObject" | index | self beConsistent. index := anIndex + firstIndex - 1. (index >= firstIndex and: [index <= lastIndex]) ifTrue: [^self basicAt: index put: anObject] ifFalse: [^SystemExceptions.IndexOutOfRange signalOn: self withIndex: anIndex] ] size [ "Return the number of objects in the receiver" ^lastIndex - firstIndex + 1 ] add: anObject [ "Add anObject in the receiver, answer it" lastIndex == self basicSize ifTrue: [self growBy: self growSize shiftBy: 0]. lastIndex := lastIndex + 1. ^self basicAt: lastIndex put: anObject ] add: newObject after: oldObject [ "Add newObject in the receiver just after oldObject, answer it. Fail if oldObject can't be found" ^self add: newObject afterIndex: (self indexOf: oldObject ifAbsent: [^SystemExceptions.NotFound signalOn: oldObject what: 'object']) ] add: newObject before: oldObject [ "Add newObject in the receiver just before oldObject, answer it. Fail if oldObject can't be found" ^self add: newObject beforeIndex: (self indexOf: oldObject ifAbsent: [^SystemExceptions.NotFound signalOn: oldObject what: 'object']) ] add: newObject afterIndex: i [ "Add newObject in the receiver just after the i-th, answer it. Fail if i < 0 or i > self size" | index | (i between: 0 and: self size) ifFalse: [^SystemExceptions.IndexOutOfRange signalOn: self withIndex: i]. index := i + firstIndex. lastIndex == self basicSize ifTrue: [self growBy: self growSize shiftBy: 0]. lastIndex to: index by: -1 do: [:i | self basicAt: i + 1 put: (self basicAt: i)]. lastIndex := lastIndex + 1. ^self basicAt: index put: newObject ] add: newObject beforeIndex: i [ "Add newObject in the receiver just before the i-th, answer it. Fail if i < 1 or i > self size + 1" ^self add: newObject afterIndex: i - 1 ] addAll: aCollection [ "Add every item of aCollection to the receiver, answer it" | index | self makeRoomLastFor: aCollection size. index := lastIndex + 1. lastIndex := lastIndex + aCollection size. aCollection do: [:element | self basicAt: index put: element. index := index + 1]. ^aCollection ] addAll: newCollection after: oldObject [ "Add every item of newCollection to the receiver just after oldObject, answer it. Fail if oldObject is not found" ^self addAll: newCollection afterIndex: (self indexOf: oldObject ifAbsent: [^SystemExceptions.NotFound signalOn: oldObject what: 'object']) ] addAll: newCollection afterIndex: i [ "Add every item of newCollection to the receiver just after the i-th, answer it. Fail if i < 0 or i > self size" | index | (i between: 0 and: self size) ifFalse: [^SystemExceptions.IndexOutOfRange signalOn: self withIndex: i]. index := i + firstIndex. self makeRoomLastFor: newCollection size. lastIndex to: index by: -1 do: [:i | self basicAt: i + newCollection size put: (self basicAt: i)]. lastIndex := lastIndex + newCollection size. (1 to: newCollection size) with: newCollection do: [:i :each | self basicAt: index + i - 1 put: each]. ^newCollection ] addAll: newCollection before: oldObject [ "Add every item of newCollection to the receiver just before oldObject, answer it. Fail if oldObject is not found" ^self addAll: newCollection beforeIndex: (self indexOf: oldObject ifAbsent: [^SystemExceptions.NotFound signalOn: oldObject what: 'object']) ] addAll: newCollection beforeIndex: i [ "Add every item of newCollection to the receiver just before the i-th, answer it. Fail if i < 1 or i > self size + 1" ^self addAll: newCollection afterIndex: i - 1 ] addAllFirst: aCollection [ "Add every item of newCollection to the receiver right at the start of the receiver. Answer aCollection" | index | self makeRoomFirstFor: aCollection size. index := firstIndex := firstIndex - aCollection size. aCollection do: [:element | self basicAt: index put: element. index := index + 1]. ^aCollection ] addAllLast: aCollection [ "Add every item of newCollection to the receiver right at the end of the receiver. Answer aCollection" | index | self makeRoomLastFor: aCollection size. index := lastIndex + 1. lastIndex := lastIndex + aCollection size. aCollection do: [:element | self basicAt: index put: element. index := index + 1]. ^aCollection ] addFirst: newObject [ "Add newObject to the receiver right at the start of the receiver. Answer newObject" firstIndex <= 1 ifTrue: [self growBy: self growSize shiftBy: self growSize]. firstIndex := firstIndex - 1. ^self basicAt: firstIndex put: newObject ] addLast: newObject [ "Add newObject to the receiver right at the end of the receiver. Answer newObject" lastIndex == self basicSize ifTrue: [self growBy: self growSize shiftBy: 0]. lastIndex := lastIndex + 1. ^self basicAt: lastIndex put: newObject ] removeFirst [ "Remove an object from the start of the receiver. Fail if the receiver is empty" | answer | self beConsistent. lastIndex < firstIndex ifTrue: [^SystemExceptions.EmptyCollection signalOn: self]. answer := self basicAt: firstIndex. "Get the element" self basicAt: firstIndex put: nil. "Allow it to be garbage collected" lastIndex = firstIndex ifTrue: [self initIndices] ifFalse: [firstIndex := firstIndex + 1]. self size < self shrinkSize ifTrue: [self shrink]. ^answer ] removeLast [ "Remove an object from the end of the receiver. Fail if the receiver is empty" | answer | self beConsistent. lastIndex < firstIndex ifTrue: [^SystemExceptions.EmptyCollection signalOn: self]. answer := self basicAt: lastIndex. "Get the element" self basicAt: lastIndex put: nil. "Allow it to be garbage collected" lastIndex = firstIndex ifTrue: [self initIndices] ifFalse: [lastIndex := lastIndex - 1]. self size < self shrinkSize ifTrue: [self shrink]. ^answer ] identityRemove: oldObject [ "Remove oldObject from the receiver. If absent, fail, else answer oldObject." ^self identityRemove: oldObject ifAbsent: [SystemExceptions.NotFound signalOn: oldObject what: 'object'] ] identityRemove: anObject ifAbsent: aBlock [ "Remove anObject from the receiver. If it can't be found, answer the result of evaluating aBlock" ^self removeAtIndex: (self identityIndexOf: anObject startingAt: 1 ifAbsent: [^aBlock value]) ] remove: anObject ifAbsent: aBlock [ "Remove anObject from the receiver. If it can't be found, answer the result of evaluating aBlock" ^self removeAtIndex: (self indexOf: anObject startingAt: 1 ifAbsent: [^aBlock value]) ] removeAtIndex: anIndex [ "Remove the object at index anIndex from the receiver. Fail if the index is out of bounds." | answer | answer := self basicRemoveAtIndex: anIndex. self size < self shrinkSize ifTrue: [self shrink]. ^answer ] basicRemoveAtIndex: anIndex [ "Remove the object at index anIndex from the receiver. Fail if the index is out of bounds." | answer | self beConsistent. lastIndex < firstIndex ifTrue: [^SystemExceptions.EmptyCollection signalOn: self]. (anIndex < 1 or: [anIndex > self size]) ifTrue: [^SystemExceptions.IndexOutOfRange signalOn: self withIndex: anIndex]. answer := self basicAt: anIndex + firstIndex - 1. self primReplaceFrom: anIndex + firstIndex - 1 to: lastIndex - 1 with: self startingAt: anIndex + firstIndex. self basicAt: lastIndex put: nil. lastIndex = firstIndex ifTrue: [self initIndices] ifFalse: [lastIndex := lastIndex - 1]. ^answer ] basicAddLast: newObject [ "Private - Add to the end of the receiver newObject, answer newObject. Don't override this method!" lastIndex == self basicSize ifTrue: [self growBy: self growSize shiftBy: 0]. lastIndex := lastIndex + 1. ^self basicAt: lastIndex put: newObject ] basicAddAllLast: aCollection [ "Private - Add to the end of the receiver all the items in aCollection, answer newObject. Don't override this method!" | index | self makeRoomLastFor: aCollection size. index := lastIndex + 1. lastIndex := lastIndex + aCollection size. aCollection do: [:element | self basicAt: index put: element. index := index + 1]. ^aCollection ] basicRemoveFirst [ "Remove an object from the start of the receiver. Fail if the receiver is empty" | answer | lastIndex < firstIndex ifTrue: [^SystemExceptions.EmptyCollection signalOn: self]. answer := self basicAt: firstIndex. "Get the element" self basicAt: firstIndex put: nil. "Allow it to be garbage collected" lastIndex = firstIndex ifTrue: [self initIndices] ifFalse: [firstIndex := firstIndex + 1]. self size < self shrinkSize ifTrue: [self shrink]. ^answer ] basicRemoveLast [ "Remove an object from the end of the receiver. Fail if the receiver is empty" | answer | lastIndex < firstIndex ifTrue: [^SystemExceptions.EmptyCollection signalOn: self]. answer := self basicAt: lastIndex. "Get the element" self basicAt: lastIndex put: nil. "Allow it to be garbage collected" lastIndex = firstIndex ifTrue: [self initIndices] ifFalse: [lastIndex := lastIndex - 1]. self size < self shrinkSize ifTrue: [self shrink]. ^answer ] initIndices [ firstIndex := self basicSize // 2 max: 1. lastIndex := firstIndex - 1 ] firstIndex: first lastIndex: last [ firstIndex := first. lastIndex := last ] makeRoomFirstFor: n [ "Private - Make room for n elements at the start of the collection" firstIndex <= n ifTrue: [self growBy: (n max: self growSize) shiftBy: (n max: self growSize)] ] makeRoomLastFor: n [ "Private - Make room for n elements at the end of the collection" lastIndex + n > self basicSize ifTrue: [self growBy: (n max: self growSize) shiftBy: 0] ] shrinkSize [ ^self basicSize // 3 ] shrink [ "Decrease the room in the collection by shrinkSize" | shift shrink | shrink := self shrinkSize. "Check that the new firstIndex is >= 1." shift := firstIndex - 1 min: shrink // 2. "Check that the new lastIndex is <= basicSize." shrink := shrink min: self basicSize - (lastIndex - shift). self growBy: shrink negated shiftBy: shift negated ] grow [ "Make growSize room in the collection, putting the old contents in the middle." self growBy: self growSize shiftBy: firstIndex // 2 ] growBy: delta shiftBy: shiftCount [ "Make room for delta more places in the collection, shifting the old contents by shiftCount places" | newOrderedCollection | newOrderedCollection := self copyEmpty: self basicSize + delta. newOrderedCollection primReplaceFrom: firstIndex + shiftCount to: lastIndex + shiftCount with: self startingAt: firstIndex. newOrderedCollection firstIndex: firstIndex + shiftCount lastIndex: lastIndex + shiftCount. self become: newOrderedCollection ] primReplaceFrom: start to: stop with: byteArray startingAt: replaceStart [ "Replace the characters from start to stop with new characters whose ASCII codes are contained in byteArray, starting at the replaceStart location of byteArray" self primitiveFailed ] ] smalltalk-3.2.5/kernel/FileStream.st0000644000175000017500000004411312123404352014310 00000000000000"====================================================================== | | FileStream Method Definitions | | ======================================================================" "====================================================================== | | Copyright 1988,92,94,95,99,2000,2001,2002,2003,2006,2008 | Free Software Foundation, Inc. | Written by Paolo Bonzini. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" FileDescriptor subclass: FileStream [ | collection ptr endPtr writePtr writeEnd | Verbose := nil. Record := nil. Includes := nil. FileStream class >> stderr [ "Answer a FileStream that is attached the Smalltalk program's standard error file handle, which can be used for error messages and diagnostics issued by the program." ^stderr ] FileStream class >> stdin [ "Answer a FileStream that is attached the Smalltalk program's standard input file handle, which is the normal source of input for the program." ^stdin ] FileStream class >> stdout [ "Answer a FileStream that is attached the Smalltalk program's standard output file handle; this is used for normal output from the program." ^stdout ] FileStream class >> initialize [ "Private - Initialize the receiver's class variables" Record := Verbose := false ] FileStream class >> fileIn: aFileName [ "File in the aFileName file. During a file in operation, global variables (starting with an uppercase letter) that are not declared yet don't yield an `unknown variable' error. Instead, they are defined as nil in the `Undeclared' dictionary (a global variable residing in Smalltalk). As soon as you add the variable to a namespace (for example by creating a class) the Association will be removed from Undeclared and reused in the namespace, so that the old references will automagically point to the new value." | oldIncludes newCollection file stream | Verbose ifTrue: [Transcript nextPutAll: 'Loading ' , aFileName; nl]. Record ifTrue: [newCollection := OrderedCollection new. Includes add: aFileName -> newCollection. oldIncludes := Includes. Includes := newCollection]. stream := self open: aFileName mode: FileStream read. [ stream fileIn ] ensure: [ stream close. Record ifTrue: [Includes := oldIncludes] ] ] FileStream class >> fileIn: aFileName line: lineInteger from: realFileName at: aCharPos [ "File in the aFileName file giving errors such as if it was loaded from the given line, file name and starting position (instead of 1)." (self open: aFileName mode: FileStream read) fileInLine: lineInteger fileName: realFileName at: aCharPos; close ] FileStream class >> fileIn: aFileName ifMissing: aSymbol [ "Conditionally do a file in, only if the key (often a class) specified by 'aSymbol' is not present in the Smalltalk system dictionary already. During a file in operation, global variables (starting with an uppercase letter) that are not declared don't yield an `unknown variable' error. Instead, they are defined as nil in the `Undeclared' dictionary (a global variable residing in Smalltalk). As soon as you add the variable to a namespace (for example by creating a class) the Association will be removed from Undeclared and reused in the namespace, so that the old references will automagically point to the new value." Smalltalk at: aSymbol ifAbsent: [self fileIn: aFileName] ] FileStream class >> fileIn: aFileName ifTrue: aBoolean [ "Conditionally do a file in, only if the supplied boolean is true. During a file in operation, global variables (starting with an uppercase letter) that are not declared don't yield an `unknown variable' error. Instead, they are defined as nil in the `Undeclared' dictionary (a global variable residing in Smalltalk). As soon as you add the variable to a namespace (for example by creating a class) the Association will be removed from Undeclared and reused in the namespace, so that the old references will automagically point to the new value." aBoolean ifTrue: [self fileIn: aFileName] ] FileStream class >> require: assoc [ "Conditionally do a file in from the value of assoc, only if the key of assoc is not present in the Smalltalk system dictionary already. During a file in operation, global variables (starting with an uppercase letter) that are not declared don't yield an `unknown variable' error. Instead, they are defined as nil in the `Undeclared' dictionary (a global variable residing in Smalltalk). As soon as you add the variable to a namespace (for example by creating a class) the Association will be removed from Undeclared and reused in the namespace, so that the old references will automagically point to the new value." Smalltalk at: assoc key ifAbsent: [self fileIn: assoc value] ] FileStream class >> verbose: verboseFlag [ "Set whether Smalltalk should output debugging messages when filing in" | oldVerbose | oldVerbose := Verbose. Verbose := verboseFlag. ^oldVerbose ] FileStream class >> record: recordFlag [ "Set whether Smalltalk should record information about nested file-ins. When recording is enabled, use #generateMakefileOnto: to automatically generate a valid makefile for the intervening file-ins." | oldRecord | oldRecord := Record. Record := recordFlag. Includes := Record ifTrue: [OrderedCollection new] ifFalse: [nil]. ^oldRecord ] FileStream class >> generateMakefileOnto: aStream [ "Generate a make file for the file-ins since record was last set to true. Store it on aStream" aStream nextPutAll: ' # # Automatically generated Smalltalk dependencies # '. self recursiveGenerateOnto: aStream with: Includes. aStream nextPutAll: '# # End automatically generated Smalltalk dependencies # ' ] FileStream class >> recursiveGenerateOnto: aStream with: includeCollection [ "Private - Generate a make file for the file in information in includeCollection. Store it on aStream" includeCollection isNil ifTrue: [^self]. includeCollection do: [:include | include value size > 0 ifTrue: [aStream nextPutAll: include key; nextPutAll: ': '. include value do: [:subinclude | aStream nextPutAll: subinclude key; space]. aStream nl; nl. self recursiveGenerateOnto: aStream with: include value]] ] peek [ "Return the next character in the file, or nil at eof. Don't advance the file pointer." writePtr notNil ifTrue: [self flush]. ptr > endPtr ifTrue: [self fill. self atEnd ifTrue: [^self pastEnd]]. ^collection at: ptr ] next [ "Return the next character in the file, or nil at eof" | element | writePtr notNil ifTrue: [self flush]. ptr > endPtr ifTrue: [self fill. self atEnd ifTrue: [^self pastEnd]]. element := collection at: ptr. ptr := ptr + 1. ^element ] nextPut: aCharacter [ "Store aCharacter on the file" ptr > collection size ifTrue: [self flush]. writePtr isNil ifTrue: [(access bitAnd: 2) = 0 ifTrue: [^self shouldNotImplement]. writePtr := ptr. writeEnd := ptr - 1]. collection at: ptr put: aCharacter. ptr := ptr + 1. writeEnd := ptr - 1 ] bufferStart [ "Private - Answer the offset from the start of the file corresponding to the beginning of the read buffer." ^super position - endPtr ] position [ "Answer the zero-based position from the start of the file" ^self bufferStart + ptr - 1 ] position: n [ "Set the file pointer to the zero-based position n" "There is a lot of duplicate code between here and #flush." | pos bufferStart | writePtr notNil ifTrue: [bufferStart := self bufferStart. pos := bufferStart + endPtr. self fileOp: 18 with: collection with: writePtr with: writeEnd with: bufferStart + writePtr - 1]. "If we didn't write, pos is nil and we always do the lseek. It makes no sense to do an lseek (to get the current file pointer in #bufferStart) only to possibly skip this other lseek." pos = n ifFalse: [super position: n]. ptr := 1. endPtr := 0. writePtr := nil ] size [ "Return the current size of the file, in bytes" writePtr notNil ifTrue: [self flush]. ^super size ] truncate [ "Truncate the file at the current position" writePtr notNil ifTrue: [self flush]. super truncate ] copyFrom: from to: to [ "Answer the contents of the file between the two given positions" | offset fromPos toPos result | from > to ifTrue: [to + 1 = from ifTrue: [^self species new]. ^SystemExceptions.ArgumentOutOfRange signalOn: from mustBeBetween: 1 and: to + 1]. self checkIfPipe. endPtr = 0 ifFalse: [offset := self bufferStart - 1. fromPos := from - offset. toPos := to - offset. (fromPos >= 1 and: [toPos <= endPtr]) ifTrue: [^collection copyFrom: fromPos to: toPos]]. writePtr notNil ifTrue: [self flush]. result := self species new: to - from + 1. self fileOp: 17 with: result with: 1 with: result size with: from. ^result ] next: n putAll: aCollection startingAt: pos [ "Write n values from aCollection, the first being at pos." | written | written := collection size - ptr + 1 min: n. self next: written bufferAll: aCollection startingAt: pos. written = n ifTrue: [^self]. self flush. n - written < collection size ifTrue: [self next: n - written bufferAll: aCollection startingAt: pos + written] ifFalse: [super next: n - written putAll: aCollection asString startingAt: pos + written] ] upTo: aCharacter [ "Returns a collection of the same type that the stream accesses, containing data up to aCharacter. Returns the entire rest of the stream's contents if no such character is found." | n resultStream result ch | writePtr notNil ifTrue: [self flush]. ptr > endPtr ifTrue: [self fill. self atEnd ifTrue: [^self pastEnd]]. "First, examine the buffer's contents." [ptr to: endPtr do: [:i | (ch := collection at: i) == aCharacter ifTrue: [result := collection copyFrom: ptr to: i - 1. ptr := i + 1. "If we went through the loop only once, we're done." resultStream isNil ifTrue: [^result]. "Else finish the stream and return its contents." ^resultStream nextPutAll: result; contents]]. resultStream isNil ifTrue: [resultStream := WriteStream on: (self species new: endPtr - ptr + 20)]. resultStream next: endPtr - ptr + 1 putAll: collection startingAt: ptr. ptr := endPtr + 1. self fill. self atEnd] whileFalse. ^resultStream contents ] nextLine [ "Returns a collection of the same type that the stream accesses, containing the next line up to the next new-line character. Returns the entire rest of the stream's contents if no new-line character is found." | n resultStream result ch | writePtr notNil ifTrue: [self flush]. ptr > endPtr ifTrue: [self fill. self atEnd ifTrue: [^self pastEnd]]. "First, examine the buffer's contents." [ptr to: endPtr do: [:i | ((ch := collection at: i) == ##(Character cr) or: [ch == ##(Character nl)]) ifTrue: [result := collection copyFrom: ptr to: i - 1. ptr := i + 1. ch == ##(Character cr) ifTrue: [self peekFor: ##(Character nl)]. "If we went through the loop only once, we're done." resultStream isNil ifTrue: [^result]. "Else finish the stream and return its contents." ^resultStream nextPutAll: result; contents]]. resultStream isNil ifTrue: [resultStream := WriteStream on: (self species new: endPtr - ptr + 20)]. resultStream next: endPtr - ptr + 1 putAll: collection startingAt: ptr. ptr := endPtr + 1. self fill. self atEnd] whileFalse. ^resultStream contents ] nextAvailable: anInteger putAllOn: aStream [ "Copy up to anInteger bytes from the stream into aStream. Return the number of bytes read." | last n | writePtr notNil ifTrue: [self flush]. ptr > endPtr ifTrue: [self fill]. "Fetch data from the buffer, without doing more than one I/O operation." last := endPtr min: ptr + anInteger - 1. n := last - ptr + 1. aStream next: n putAll: collection startingAt: ptr. ptr := ptr + n. ^n ] nextAvailable: anInteger into: aCollection startingAt: pos [ "Read up to anInteger bytes from the stream and store them into aCollection. Return the number of bytes read." | last n | writePtr notNil ifTrue: [self flush]. ptr > endPtr ifTrue: [self fill]. "Fetch data from the buffer, without doing more than one I/O operation." last := endPtr min: ptr + anInteger - 1. n := last - ptr + 1. aCollection replaceFrom: pos to: pos + n - 1 with: collection startingAt: ptr. ptr := ptr + n. ^n ] nextPutAllOn: aStream [ "Put all the characters of the receiver in aStream." | buf bufSize | writePtr notNil ifTrue: [self flush]. ptr > endPtr ifTrue: [self fill]. [ self atEnd ] whileFalse: [ aStream next: endPtr - ptr + 1 putAll: collection startingAt: ptr. ptr := endPtr + 1. self resetBuffer; fill. ] ] atEnd [ "Answer whether data has come to an end" ^ptr > endPtr and: [super atEnd] ] bufferSize [ "Answer the file's current buffer" ^collection size ] bufferSize: bufSize [ "Flush the file and set the buffer's size to bufSize" self flush. collection := self species new: bufSize ] initialize [ "Initialize the receiver's instance variables" super initialize. collection := self newBuffer. ptr := 1. endPtr := 0. ] newBuffer [ "Private - Answer a String to be used as the receiver's buffer" ^self species new: 1024 ] flush [ "Flush the output buffer." "Decide whether to use a pwrite or a write. In many cases, a regular write can be better than a pwrite+lseek. We are now at (self bufferStart + endPtr). The position we will set is (self bufferStart + ptr - 1). If we perform a write, we will do a single seek from (self bufferStart + endPtr) to (self bufferStart + writePtr - 1), and then issue the write which will set the file pointer to (self bufferStart + writeEnd): That's why if writeEnd = ptr - 1, we use write. Otherwise we use pwrite and possibly an lseek after it." (self isPipe or: [writePtr notNil and: [ptr - 1 = writeEnd]]) ifTrue: [writePtr notNil ifTrue: [(self isPipe or: [writePtr - 1 = endPtr]) ifFalse: [super skip: writePtr - 1 - endPtr]. super next: writeEnd - writePtr + 1 putAll: collection startingAt: writePtr]] ifFalse: [writePtr notNil ifTrue: [self fileOp: 18 with: collection with: writePtr with: writeEnd with: self bufferStart + writePtr - 1]. ptr - 1 = endPtr ifFalse: [super skip: ptr - 1 - endPtr]]. ptr := 1. endPtr := 0. writePtr := nil ] resetBuffer [ "Reset the buffer. Only valid if no write is pending." ptr := 1. endPtr := 0. writePtr := nil ] pendingWrite [ "Answer whether the output buffer is full." ^writePtr notNil ] clean [ "Synchronize the file descriptor's state with the object's state." self flush ] next: n bufferAll: aCollection startingAt: pos [ "Private - Assuming that the buffer has space for n characters, store n characters of aCollection in the buffer, starting from the pos-th." writePtr isNil ifTrue: [(access bitAnd: 2) = 0 ifTrue: [^self shouldNotImplement]. writePtr := ptr. writeEnd := ptr - 1]. n = 0 ifTrue: [^self]. collection replaceFrom: ptr to: ptr + n - 1 with: aCollection startingAt: pos. ptr := ptr + n. writeEnd := ptr - 1 ] fill [ "Private - Fill the input buffer" (access bitAnd: 1) = 0 ifTrue: [^self shouldNotImplement]. ptr > endPtr ifTrue: [self flush]. endPtr := endPtr + (super nextAvailable: collection size - endPtr into: collection startingAt: endPtr + 1) ] ] Eval [ FileStream initialize ] smalltalk-3.2.5/kernel/UndefObject.st0000644000175000017500000003545612130343734014463 00000000000000"====================================================================== | | UndefinedObject (nil) Method Definitions | | ======================================================================" "====================================================================== | | Copyright 1988,92,94,95,99,2000,2001,2002,2003,2006,2008 | Free Software Foundation, Inc. | Written by Steve Byrne. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" Object subclass: UndefinedObject [ copy [ ^self ] shallowCopy [ ^self ] deepCopy [ ^self ] isNull [ "Answer whether the receiver represents a NULL C pointer. Always answer true." ^true ] isNil [ "Answer whether the receiver is the undefined object nil. Always answer true." ^true ] notNil [ "Answer whether the receiver is not the undefined object nil. Always answer false." ^false ] ifNil: nilBlock [ "Evaluate nilBlock if the receiver is nil, else answer nil" ^nilBlock value ] ifNil: nilBlock ifNotNil: notNilBlock [ "Evaluate nilBlock if the receiver is nil, else evaluate notNilBlock, passing the receiver." ^nilBlock value ] ifNotNil: notNilBlock [ "Evaluate notNilBlock if the receiver is not nil, passing the receiver. Else answer nil" ^nil ] ifNotNil: notNilBlock ifNil: nilBlock [ "Evaluate nilBlock if the receiver is nil, else evaluate notNilBlock, passing the receiver." ^nilBlock value ] ifNil: nilBlock ifNotNilDo: iterableBlock [ "Evaluate nilBlock if the receiver is nil, else evaluate iterableBlock with each element of the receiver (which should be an Iterable)." ^nilBlock value ] ifNotNilDo: iterableBlock [ "Evaluate iterableBlock with each element of the receiver (which should be an Iterable) if not nil. Else answer nil" ^nil ] ifNotNilDo: iterableBlock ifNil: nilBlock [ "Evaluate nilBlock if the receiver is nil, else evaluate iterableBlock, passing each element of the receiver (which should be an Iterable)." ^nilBlock value ] addDependent: ignored [ "Fail, nil does not support dependents." self shouldNotImplement ] release [ "Ignore this call, nil does not support dependents." ] printOn: aStream in: aNamespace [ "Print on aStream a representation of the receiver as it would be accessed from aNamespace: nil is the same everywhere, so print the same as #printOn:" aStream nextPutAll: 'nil' ] printOn: aStream [ "Print a representation of the receiver on aStream." aStream nextPutAll: 'nil' ] isLiteralObject [ "Answer whether the receiver is expressible as a Smalltalk literal." ^true ] storeLiteralOn: aStream [ "Store on aStream some Smalltalk code which compiles to the receiver" self storeOn: aStream ] storeOn: aStream [ "Store Smalltalk code compiling to the receiver on aStream." self printOn: aStream ] subclass: classNameString instanceVariableNames: stringInstVarNames classVariableNames: stringOfClassVarNames poolDictionaries: stringOfPoolNames [ "Don't use this, it is only present to file in from IBM Smalltalk" ^self subclass: classNameString instanceVariableNames: stringInstVarNames classVariableNames: stringOfClassVarNames poolDictionaries: stringOfPoolNames category: 'no category' ] subclass: classNameString classInstanceVariableNames: stringClassInstVarNames instanceVariableNames: stringInstVarNames classVariableNames: stringOfClassVarNames poolDictionaries: stringOfPoolNames [ "Don't use this, it is only present to file in from IBM Smalltalk" ^(self subclass: classNameString instanceVariableNames: stringInstVarNames classVariableNames: stringOfClassVarNames poolDictionaries: stringOfPoolNames category: 'no category') classInstanceVariableNames: stringClassInstVarNames; yourself ] variableSubclass: classNameString instanceVariableNames: stringInstVarNames classVariableNames: stringOfClassVarNames poolDictionaries: stringOfPoolNames [ "Don't use this, it is only present to file in from IBM Smalltalk" ^self variableSubclass: classNameString instanceVariableNames: stringInstVarNames classVariableNames: stringOfClassVarNames poolDictionaries: stringOfPoolNames category: 'no category' ] variableSubclass: classNameString classInstanceVariableNames: stringClassInstVarNames instanceVariableNames: stringInstVarNames classVariableNames: stringOfClassVarNames poolDictionaries: stringOfPoolNames [ "Don't use this, it is only present to file in from IBM Smalltalk" ^(self variableSubclass: classNameString instanceVariableNames: stringInstVarNames classVariableNames: stringOfClassVarNames poolDictionaries: stringOfPoolNames category: 'no category') classInstanceVariableNames: stringClassInstVarNames; yourself ] variableByteSubclass: classNameString instanceVariableNames: stringInstVarNames classVariableNames: stringOfClassVarNames poolDictionaries: stringOfPoolNames [ "Don't use this, it is only present to file in from IBM Smalltalk" ^self variableByteSubclass: classNameString instanceVariableNames: stringInstVarNames classVariableNames: stringOfClassVarNames poolDictionaries: stringOfPoolNames category: 'no category' ] variableByteSubclass: classNameString classInstanceVariableNames: stringClassInstVarNames instanceVariableNames: stringInstVarNames classVariableNames: stringOfClassVarNames poolDictionaries: stringOfPoolNames [ "Don't use this, it is only present to file in from IBM Smalltalk" ^(self variableByteSubclass: classNameString instanceVariableNames: stringInstVarNames classVariableNames: stringOfClassVarNames poolDictionaries: stringOfPoolNames category: 'no category') classInstanceVariableNames: stringClassInstVarNames; yourself ] variableLongSubclass: classNameString instanceVariableNames: stringInstVarNames classVariableNames: stringOfClassVarNames poolDictionaries: stringOfPoolNames [ "Don't use this, it is only present to file in from IBM Smalltalk" ^self variable: #uint subclass: classNameString instanceVariableNames: stringInstVarNames classVariableNames: stringOfClassVarNames poolDictionaries: stringOfPoolNames category: 'no category' ] variableLongSubclass: classNameString classInstanceVariableNames: stringClassInstVarNames instanceVariableNames: stringInstVarNames classVariableNames: stringOfClassVarNames poolDictionaries: stringOfPoolNames [ "Don't use this, it is only present to file in from IBM Smalltalk" ^(self variable: #uint subclass: classNameString instanceVariableNames: stringInstVarNames classVariableNames: stringOfClassVarNames poolDictionaries: stringOfPoolNames category: 'no category') classInstanceVariableNames: stringClassInstVarNames; yourself ] instSize [ ^0 ] methodDictionary [ ^nil ] removeSubclass: aClass [ "Ignored -- necessary to support disjoint class hierarchies" ] subclass: classNameString instanceVariableNames: stringInstVarNames classVariableNames: stringOfClassVarNames poolDictionaries: stringOfPoolNames category: categoryNameString [ "Define a fixed subclass of the receiver with the given name, instance variables, class variables, pool dictionaries and category. If the class is already defined, if necessary, recompile everything needed." | meta | KernelInitialized ifFalse: [^(Smalltalk at: classNameString) category: categoryNameString]. meta := self metaclassFor: classNameString. ^meta name: classNameString environment: Namespace current subclassOf: self instanceVariableNames: stringInstVarNames shape: nil classVariableNames: stringOfClassVarNames poolDictionaries: stringOfPoolNames category: categoryNameString ] variable: shape subclass: classNameString instanceVariableNames: stringInstVarNames classVariableNames: stringOfClassVarNames poolDictionaries: stringOfPoolNames category: categoryNameString [ "Define a variable subclass of the receiver with the given name, shape, instance variables, class variables, pool dictionaries and category. If the class is already defined, if necessary, recompile everything needed. The shape can be one of #byte #int8 #character #short #ushort #int #uint #int64 #uint64 #utf32 #float #double or #pointer." | meta | KernelInitialized ifFalse: [^(Smalltalk at: classNameString) category: categoryNameString]. meta := self metaclassFor: classNameString. ^meta name: classNameString environment: Namespace current subclassOf: self instanceVariableNames: stringInstVarNames shape: shape classVariableNames: stringOfClassVarNames poolDictionaries: stringOfPoolNames category: categoryNameString ] subclass: classNameString [ "Define a subclass of the receiver with the given name. If the class is already defined, don't modify its instance or class variables but still, if necessary, recompile everything needed." | meta | KernelInitialized ifFalse: [^Smalltalk at: classNameString]. meta := self metaclassFor: classNameString. ^meta name: classNameString environment: Namespace current subclassOf: self ] variableSubclass: classNameString instanceVariableNames: stringInstVarNames classVariableNames: stringOfClassVarNames poolDictionaries: stringOfPoolNames category: categoryNameString [ "Define a variable pointer subclass of the receiver with the given name, instance variables, class variables, pool dictionaries and category. If the class is already defined, if necessary, recompile everything needed." | meta | KernelInitialized ifFalse: [^(Smalltalk at: classNameString) category: categoryNameString]. meta := self metaclassFor: classNameString. ^meta name: classNameString environment: Namespace current subclassOf: self instanceVariableNames: stringInstVarNames shape: #pointer classVariableNames: stringOfClassVarNames poolDictionaries: stringOfPoolNames category: categoryNameString ] variableWordSubclass: classNameString instanceVariableNames: stringInstVarNames classVariableNames: stringOfClassVarNames poolDictionaries: stringOfPoolNames category: categoryNameString [ "Define a word variable subclass of the receiver with the given name, instance variables, class variables, pool dictionaries and category. If the class is already defined, if necessary, recompile everything needed." | meta | KernelInitialized ifFalse: [^(Smalltalk at: classNameString) category: categoryNameString]. meta := self metaclassFor: classNameString. ^meta name: classNameString environment: Namespace current subclassOf: self instanceVariableNames: stringInstVarNames shape: #word classVariableNames: stringOfClassVarNames poolDictionaries: stringOfPoolNames category: categoryNameString ] variableByteSubclass: classNameString instanceVariableNames: stringInstVarNames classVariableNames: stringOfClassVarNames poolDictionaries: stringOfPoolNames category: categoryNameString [ "Define a byte variable subclass of the receiver with the given name, instance variables, class variables, pool dictionaries and category. If the class is already defined, if necessary, recompile everything needed." | meta | KernelInitialized ifFalse: [^(Smalltalk at: classNameString) category: categoryNameString]. meta := self metaclassFor: classNameString. ^meta name: classNameString environment: Namespace current subclassOf: self instanceVariableNames: stringInstVarNames shape: #byte classVariableNames: stringOfClassVarNames poolDictionaries: stringOfPoolNames category: categoryNameString ] metaclassFor: classNameString [ "Create a Metaclass object for the given class name. The metaclass is a subclass of Class" | className class | className := classNameString asSymbol. class := Namespace current hereAt: className ifAbsent: [nil]. ^(class isNil or: [class isClass not]) ifTrue: [Metaclass subclassOf: Class] ifFalse: [class class] ] allSubclasses [ "Return all the classes in the system." ^Class allSubclasses collect: [:each | each instanceClass] ] mutate: instVarMap startAt: start newClass: class [ "Private - Do nothing, this is here in case the WeakArray garbage collects an object that is to be mutated." ] inheritsFrom: aClass [ "Always return false, as nil inherits from nothing." ^false ] ] smalltalk-3.2.5/kernel/ValueAdapt.st0000644000175000017500000002321412123404352014302 00000000000000"====================================================================== | | ValueAdaptor hierarchy Method Definitions | | ======================================================================" "====================================================================== | | Copyright 1999, 2000, 2001, 2002, 2008, 2009 Free Software Foundation, Inc. | Written by Paolo Bonzini. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" Object subclass: ValueAdaptor [ ValueAdaptor class >> new [ "We don't know enough of subclasses to have a shared implementation of new" self shouldNotImplement ] printOn: aStream [ "Print a representation of the receiver" aStream print: self class; nextPut: $(; print: self value; nextPut: $) ] value: anObject [ "Set the value of the receiver. Must be implemented by ValueAdaptor's subclasses" self subclassResponsibility ] value [ "Retrive the value of the receiver. Must be implemented by ValueAdaptor's subclasses" self subclassResponsibility ] ] ValueAdaptor subclass: NullValueHolder [ NullValueHolder class [ | uniqueInstance | ] NullValueHolder class >> new [ "Not used -- use `ValueHolder null' instead" ^self shouldNotImplement ] NullValueHolder class >> uniqueInstance [ "Answer the sole instance of NullValueHolder" ^uniqueInstance isNil ifTrue: [uniqueInstance := self basicNew] ifFalse: [uniqueInstance] ] value: anObject [ "Set the value of the receiver. Do nothing, discard the value" ] value [ "Retrive the value of the receiver. Always answer nil" ^nil ] ] ValueAdaptor subclass: ValueHolder [ | value | ValueHolder class >> new [ "Create a ValueHolder whose starting value is nil" ^self basicNew initialize ] ValueHolder class >> null [ "Answer the sole instance of NullValueHolder" ^NullValueHolder uniqueInstance ] ValueHolder class >> with: anObject [ "Create a ValueHolder whose starting value is anObject" ^self new value: anObject ] value: anObject [ "Set the value of the receiver." value := anObject ] value [ "Get the value of the receiver." ^value ] initialize [ "Private - set the initial value of the receiver" value := nil ] ] Object extend [ asValue [ "Answer a ValueHolder whose initial value is the receiver." ^ValueHolder with: self ] ] ValueHolder subclass: Promise [ | sema error | Promise class >> for: aBlock [ "Invoke aBlock at an indeterminate time in an indeterminate process before answering its value from #value sent to my result." | p | p := Promise new. [[ p value: aBlock value ] on: Error do: [ :ex | p errorValue: ex. ex return ]] fork. ^p ] Promise class >> null [ self shouldNotImplement ] hasError [ "Answer whether calling #value will raise an exception." ^error notNil ] hasValue [ "Answer whether we already have a value (or calling #value will raise an error)." ^sema isNil ] value: anObject [ "Set the value of the receiver." super value: anObject. [sema notifyAll. sema := nil] valueWithoutPreemption ] errorValue: anException [ "Private - Raise anException whenever #value is called." error := anException. [sema notifyAll. sema := nil] valueWithoutPreemption ] value [ "Get the value of the receiver." "This is guaranteed to execute atomically by the VM!" sema == nil ifFalse: [sema wait]. ^error isNil ifTrue: [ super value ] ifFalse: [ error copy signal ] ] printOn: aStream [ "Print a representation of the receiver" aStream print: self class. self hasValue ifFalse: [ aStream nextPutAll: '(???)' ]. self hasError ifTrue: [ aStream nextPutAll: '(Error!)' ]. aStream nextPut: $(; print: self value; nextPut: $) ] initialize [ "Private - set the initial state of the receiver" super initialize. sema := Semaphore new ] ] ValueAdaptor subclass: PluggableAdaptor [ | getBlock putBlock | PluggableAdaptor class >> getBlock: getBlock putBlock: putBlock [ "Answer a PluggableAdaptor using the given blocks to implement #value and #value:" ^self basicNew getBlock: getBlock putBlock: putBlock ] PluggableAdaptor class >> on: anObject getSelector: getSelector putSelector: putSelector [ "Answer a PluggableAdaptor using anObject's getSelector message to implement #value, and anObject's putSelector message to implement #value:" ^self basicNew getBlock: [anObject perform: getSelector] putBlock: [:value | anObject perform: putSelector with: value] ] PluggableAdaptor class >> on: anObject aspect: aSymbol [ "Answer a PluggableAdaptor using anObject's aSymbol message to implement #value, and anObject's aSymbol: message (aSymbol followed by a colon) to implement #value:" ^self on: anObject getSelector: aSymbol putSelector: (aSymbol , ':') asSymbol ] PluggableAdaptor class >> on: anObject index: anIndex [ "Answer a PluggableAdaptor using anObject's #at: and #at:put: message to implement #value and #value:; the first parameter of #at: and #at:put: is anIndex" ^self getBlock: [anObject at: anIndex] putBlock: [:value | anObject at: anIndex put: value] ] PluggableAdaptor class >> on: aDictionary key: aKey [ "Same as #on:index:. Provided for clarity and completeness." ^self on: aDictionary index: aKey ] value: anObject [ "Set the value of the receiver." putBlock value: anObject ] value [ "Get the value of the receiver." ^getBlock value ] getBlock: get putBlock: put [ getBlock := get. putBlock := put. ^self ] ] PluggableAdaptor subclass: DelayedAdaptor [ | value delayed | trigger [ "Really set the value of the receiver." delayed ifTrue: [delayed := false. super value: value] ] value: anObject [ "Set the value of the receiver - actually, the value is cached and is not set until the #trigger method is sent." value := anObject. delayed := true ] value [ "Get the value of the receiver." ^delayed ifTrue: [value] ifFalse: [getBlock value] ] getBlock: get putBlock: put [ delayed := false. ^super getBlock: get putBlock: put ] ] smalltalk-3.2.5/kernel/False.st0000644000175000017500000000574012123404352013312 00000000000000"====================================================================== | | False Method Definitions | | ======================================================================" "====================================================================== | | Copyright 1988,92,94,95,99,2000,2001 | Free Software Foundation, Inc. | Written by Steve Byrne. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" Boolean subclass: False [ | truthValue | asCBooleanValue [ ^0 ] ifTrue: trueBlock ifFalse: falseBlock [ "We are false -- evaluate the falseBlock" ^falseBlock value ] ifFalse: falseBlock ifTrue: trueBlock [ "We are false -- evaluate the falseBlock" ^falseBlock value ] ifTrue: trueBlock [ "We are false -- answer nil" ^nil ] ifFalse: falseBlock [ "We are false -- evaluate the falseBlock" ^falseBlock value ] not [ "We are false -- answer true" ^true ] & aBoolean [ "We are false -- anded with anything, we always answer false" ^false ] | aBoolean [ "We are false -- ored with anything, we always answer the other operand" ^aBoolean ] eqv: aBoolean [ "Answer whether the receiver and aBoolean represent the same boolean value" ^aBoolean not ] xor: aBoolean [ "Answer whether the receiver and aBoolean represent different boolean values" ^aBoolean ] and: aBlock [ "We are false -- anded with anything, we always answer false" ^false ] or: aBlock [ "We are false -- ored with anything, we always answer the other operand, so evaluate aBlock" ^aBlock value ] printOn: aStream [ "Print a representation of the receiver on aStream" aStream nextPutAll: 'false' ] ] smalltalk-3.2.5/kernel/CCallable.st0000644000175000017500000001454312123404352014063 00000000000000"====================================================================== | | CFunctionDescriptor Method Definitions | | ======================================================================" "====================================================================== | | Copyright 1988,92,94,95,99,2000,2001,2002,2003,2005,2008 | Free Software Foundation, Inc. | Written by Steve Byrne. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" CObject subclass: CCallable [ | returnType argTypes | CCallable class >> typeMap [ "Private - Return the map from Smalltalk symbols representing a C type, to an integer." ^##(| reverse dict | reverse := #(#char #uChar #short #uShort #long #uLong #float #double #string #smalltalk #int #uInt #longDouble #unknown #stringOut #symbol #byteArray #byteArrayOut #boolean #void #variadic #variadicSmalltalk #cObject #cObjectPtr #self #selfSmalltalk #wchar #wstring #wstringOut #symbolOut #longLong #uLongLong). dict := LookupTable new. reverse keysAndValuesDo: [ :k :v | dict at: v put: k - 1; at: v asLowercase asSymbol put: k - 1 ]. dict) ] CCallable class >> mapType: aSymbolOrType [ "Private - Map a Smalltalk symbols representing a C type to an integer." ^self typeMap at: aSymbolOrType ifAbsent: [ (aSymbolOrType isKindOf: CType) ifTrue: [ ^aSymbolOrType ]. aSymbolOrType isSymbol ifFalse: [ ^CType from: aSymbolOrType]. ^self error: 'invalid C argument type ', aSymbolOrType storeString ] ] CCallable class >> for: aCObject returning: returnTypeSymbol withArgs: argsArray [ "Answer a CFunctionDescriptor with the given address, return type and arguments. The address will be reset to NULL upon image save (and it's the user's task to figure out a way to reinitialize it!)" | result | result := aCObject isNil ifTrue: [ self new ] ifFalse: [ aCObject castTo: self type ]. result returnType: returnTypeSymbol. result argTypes: argsArray. ^result ] argTypes: anArray [ argTypes := anArray asArray collect: [ :arg | self class mapType: arg ] ] returnType [ returnType isInteger ifFalse: [ ^returnType ]. ^self class typeMap at: returnType + 1 ifAbsent: [ returnType ] ] returnType: aSymbol [ returnType := self class mapType: aSymbol ] link [ "Rebuild the object after the image is restarted." self subclassResponsibility ] isValid [ "Answer whether the object represents a valid function." self address = 0 ifFalse: [^true]. self link. ^self address ~= 0 ] asyncCall [ "Perform the call-out for the function represented by the receiver. The arguments (and the receiver if one of the arguments has type #self or #selfSmalltalk) are taken from the parent context. Asynchronous call-outs don't return a value, but if the function calls back into Smalltalk the process that started the call-out is not suspended." ^self isValid ifFalse: [SystemExceptions.CInterfaceError signal: 'Invalid C call-out ' , self name] ifTrue: [self asyncCallNoRetryFrom: thisContext parentContext] ] asyncCallNoRetryFrom: aContext [ "Perform the call-out for the function represented by the receiver. The arguments (and the receiver if one of the arguments has type #self or #selfSmalltalk) are taken from the base of the stack of aContext. Asynchronous call-outs don't return a value, but if the function calls back into Smalltalk the process that started the call-out is not suspended. Unlike #asyncCallFrom:, this method does not attempt to find functions in shared objects." self primitiveFailed ] callInto: aValueHolder [ "Perform the call-out for the function represented by the receiver. The arguments (and the receiver if one of the arguments has type #self or #selfSmalltalk) are taken from the parent context, and the the result is stored into aValueHolder. aValueHolder is also returned." ^self isValid ifFalse: [SystemExceptions.CInterfaceError signal: 'Invalid C call-out ' , self name] ifTrue: [self callNoRetryFrom: thisContext parentContext into: aValueHolder] ] callNoRetryFrom: aContext into: aValueHolder [ "Perform the call-out for the function represented by the receiver. The arguments (and the receiver if one of the arguments has type #self or #selfSmalltalk) are taken from the base of the stack of aContext, and the result is stored into aValueHolder. aValueHolder is also returned. Unlike #callFrom:into:, this method does not attempt to find functions in shared objects." self primitiveFailed ] ] smalltalk-3.2.5/kernel/OtherArrays.st0000644000175000017500000003460612123404352014526 00000000000000"===================================================================== | | Variations on the Array class | | ======================================================================" "====================================================================== | | Copyright 2001, 2002, 2009 Free Software Foundation, Inc. | Written by Paolo Bonzini. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" ArrayedCollection subclass: WordArray [ at: anIndex ifAbsent: aBlock [ "Answer the index-th indexed instance variable of the receiver" ^self checkIndexableBounds: anIndex ifAbsent: aBlock ] ] Namespace current: Kernel [ Magnitude subclass: LargeArraySubpart [ | first last index | LargeArraySubpart class >> first: first last: last index: index [ "Answer a LargeArraySubpart which answers first, last, and index when it is sent (respectively) #first, #last and #firstIndex." ^self new first: first last: last index: index ] < anObject [ "Answer whether the receiver points to a part of the array that is before anObject (this makes sense only if the receiver and anObject are two LargeArraySubparts referring to the same LargeArrayedCollection)." ^self first < anObject first ] <= anObject [ "Answer whether the receiver points to a part of the array that is before anObject or starts at the same point (this makes sense only if the receiver and anObject are two LargeArraySubparts referring to the same LargeArrayedCollection)." ^self first <= anObject first ] = anObject [ "Answer whether the receiver and anObject are equal (assuming that the receiver and anObject are two LargeArraySubparts referring to the same LargeArrayedCollection, which the receiver cannot check for)." ^self first = anObject first ] hash [ "Answer an hash value for the receiver" ^self first hash ] first: firstIndex last: lastIndex index: storagePosition [ "Set up the receiver so that it answers first, last, and index when it is sent (respectively) #first, #last and #firstIndex." first := firstIndex. last := lastIndex. index := storagePosition ] first [ "Answer the index of the first item of the LargeArrayedCollection that the receiver refers to." ^first ] last [ "Answer the index of the last item of the LargeArrayedCollection that the receiver refers to." ^last ] firstIndex [ "Answer the index in the collection's storage object of the first item of the LargeArrayedCollection that the receiver refers to." ^index ] lastIndex [ "Answer the index in the collection's storage object of the last item of the LargeArrayedCollection that the receiver refers to." ^index + last - first ] cutAt: position [ "Answer a new LargeArraySubpart whose lastIndex is position - 1, and apply a #removeFirst: to the receiver so that the firstIndex becomes position" | newPart newFirst | newFirst := first + (position - index). newPart := self class first: first last: newFirst - 1 index: index. first := newFirst. index := position. ^newPart ] grow [ "Add one to last and lastIndex" last := last + 1 ] growBy: numberOfElements [ "Add numberOfElements to last and lastIndex" last := last + numberOfElements ] relocateTo: position [ "Move the firstIndex to position, and the lastIndex accordingly." index := position ] removeFirst: n [ "Sum n to first and firstIndex, but leave last/lastIndex untouched" first := first + n. index := index + n ] removeLast: n [ "Subtract n from last and lastIndex, but leave first/firstIndex untouched" last := last - n ] ] ] ArrayedCollection subclass: LargeArrayedCollection [ | storage indices position size | LargeArrayedCollection class >> new: anInteger [ "Answer a new instance of the receiver, with room for anInteger elements." ^self basicNew initialize: anInteger ] at: anIndex [ "Answer the anIndex-th item of the receiver." | subpart | self checkIndex: anIndex. subpart := self atSubpart: anIndex. subpart isNil ifTrue: [^self defaultElement]. ^storage at: anIndex - subpart first + subpart firstIndex ] at: anIndex put: anObject [ "Replace the anIndex-th item of the receiver with anObject." | subpart | self checkIndex: anIndex. "Reset compression flag" position < 0 ifTrue: [position := position negated]. subpart := self atPutSubpart: anIndex. subpart isNil ifTrue: [self addToStorage: anObject. indices add: (Kernel.LargeArraySubpart first: anIndex last: anIndex index: position - 1). ^anObject]. "The item was not a nil one" subpart last >= anIndex ifTrue: [^storage at: anIndex - subpart first + subpart firstIndex put: anObject]. self addToStorage: anObject. subpart lastIndex = (position - 2) ifTrue: ["Extend the last subpart we created" subpart grow] ifFalse: ["Create a new subpart." indices add: (Kernel.LargeArraySubpart first: anIndex last: anIndex index: position - 1)]. ^anObject ] compress [ "Arrange the representation of the array for maximum memory saving." | newStorage newIndices last startOfNils trailingNils | position < 0 ifTrue: [^self]. newStorage := WriteStream on: (self newCollection: self size // 100 + 10). newIndices := WriteStream on: (Array new: self size // 1000 + 10). "This algorithm is complicated to code but intuitive. Read it slowly and follow its rhythm..." indices do: [:each | "First, do a pass on the indices, searching for spans of nils that can be removed from the array." | oldPosition i element | startOfNils := i := each firstIndex. [i <= each lastIndex] whileTrue: [element := storage at: i. i := i + 1. element == self defaultElement ifFalse: [startOfNils := i]. i - startOfNils >= self costOfNewIndex ifTrue: ["Find the end of this run of nil elements, and remove the nils from the start of the subpart" [i <= each lastIndex and: [(storage at: i) == self defaultElement]] whileTrue: [i := i + 1]. "Create a new part that spans until the start of the nils" self from: each firstIndex to: startOfNils - 1 putOn: newStorage. last := each cutAt: startOfNils. newIndices nextPut: last. each removeFirst: i - each firstIndex. startOfNils := i]]. startOfNils <= each lastIndex ifTrue: [each removeLast: each lastIndex - startOfNils + 1]. "Now check whether we can merge the last LargeArraySubpart and this one" last isNil ifFalse: [each first - last last <= self costOfNewIndex ifTrue: [newStorage next: each first - last last - 1 put: self defaultElement. last growBy: each last - last last] ifFalse: [last := nil]]. "Anyway, add the items to the newStorage" oldPosition := newStorage position + 1. self from: each firstIndex to: each lastIndex putOn: newStorage. "Then add a new LargeArraySubpart if necessary" (last isNil and: [each lastIndex >= each firstIndex]) ifTrue: [each relocateTo: oldPosition. newIndices nextPut: each. last := each]]. indices := newIndices contents asSortedCollection. storage := newStorage contents. position := newStorage size negated ] = aLargeArray [ "Answer whether the receiver and aLargeArray have the same contents" self class == aLargeArray class ifFalse: [^false]. self == aLargeArray ifTrue: [^true]. self compress. aLargeArray compress. ^indices = aLargeArray indices and: [storage = aLargeArray storage] ] hash [ "Answer an hash value for the receiver" self compress. ^storage hash ] size [ "Answer the maximum valid index for the receiver" ^size ] addToStorage: anObject [ "Add anObject to the storage, possibly growing it if necessary." position > storage size ifTrue: [storage := (self newCollection: storage size * 2) replaceFrom: 1 to: storage size with: storage startingAt: 1; yourself]. storage at: position put: anObject. position := position + 1. ^anObject ] atSubpart: index [ "Private - Perform a binary search on the indices, searching for a LargeArraySubpart referring to index." | i j last mid element | i := 1. j := last := indices size. [i > j] whileFalse: [mid := (i + j + 1) // 2. element := indices at: mid. index > element last ifTrue: [i := mid + 1] ifFalse: [index < element first ifTrue: [j := mid - 1] ifFalse: [^element]]]. ^nil ] atPutSubpart: index [ "Private - Perform a binary search on the indices, searching for a LargeArraySubpart referring to index or (if it cannot be found) to index - 1." | i j last mid element | i := 1. j := last := indices size. [i > j] whileFalse: [mid := (i + j + 1) // 2. element := indices at: mid. index > element last ifTrue: ["Answer a LargeArraySubpart to be extended" index = (element last + 1) ifTrue: [(j = last or: [(indices at: mid + 1) first > index]) ifTrue: [^element] ifFalse: [^indices at: mid + 1]]. "Discard up to this element" i := mid + 1] ifFalse: [index < element first ifTrue: [j := mid - 1] ifFalse: [^element]]]. ^nil ] checkIndex: index [ "Check if the given index is valid" index isInteger ifFalse: [^SystemExceptions.WrongClass signalOn: index mustBe: Integer]. index < 1 ifTrue: [^SystemExceptions.IndexOutOfRange signalOn: self withIndex: index]. index > self size ifTrue: [^SystemExceptions.IndexOutOfRange signalOn: self withIndex: index] ] from: first to: last putOn: newStorage [ "Store on newStorage every item of the current storage from the first-th to the last-th" storage from: first to: last do: [:element | newStorage nextPut: element] ] indices [ ^indices ] storage [ ^storage ] costOfNewIndex [ "Answer the maximum number of consecutive items set to the defaultElement that can be present in a compressed array." ^5 ] defaultElement [ "Answer the value which is hoped to be the most common in the array" ^nil ] newCollection: size [ self subclassResponsibility ] initialize: mySize [ "Initialize the receiver's state" indices := SortedCollection new: mySize // 1000 + 10. storage := self newCollection: mySize // 100 + 10. size := mySize. position := -1 ] ] LargeArrayedCollection subclass: LargeArray [ newCollection: size [ "Create an Array of the given size" ^Array new: size ] ] LargeArrayedCollection subclass: LargeByteArray [ costOfNewIndex [ "Answer the maximum number of consecutive items set to the defaultElement that can be present in a compressed array." "### Should be 40 on 64-bit machines (super costOfNewIndex * CLong sizeof)" ^20 ] defaultElement [ "Answer the value which is hoped to be the most common in the array" ^0 ] newCollection: size [ "Create a ByteArray of the given size" ^ByteArray new: size ] ] LargeArrayedCollection subclass: LargeWordArray [ defaultElement [ "Answer the value which is hoped to be the most common in the array" ^0 ] newCollection: size [ "Create a WordArray of the given size" ^WordArray new: size ] ] smalltalk-3.2.5/kernel/Delay.st0000644000175000017500000003115412123404352013314 00000000000000"====================================================================== | | Delay Method Definitions | | ======================================================================" "====================================================================== | | Copyright 1988,92,94,95,99,2000,2001,2002,2007,2008,2009 | Free Software Foundation, Inc. | Written by Steve Byrne. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" Object subclass: Delay [ | resumptionTime delayDuration delaySemaphore waitingProcess | MutexSem := nil. DelayRequestor := nil. Queue := nil. DelayProcess := nil. IdleProcess := nil. TimeoutSem := nil. Delay class >> forNanoseconds: nanosecondCount [ "Answer a Delay waiting for nanosecondCount nanoseconds" ^self new initForNanoseconds: nanosecondCount ] Delay class >> forMilliseconds: millisecondCount [ "Answer a Delay waiting for millisecondCount milliseconds" ^self forNanoseconds: millisecondCount * 1000000 ] Delay class >> forSeconds: secondCount [ "Answer a Delay waiting for secondCount seconds" ^self forNanoseconds: secondCount * 1000000000 ] Delay class >> untilNanoseconds: nanosecondCount [ "Answer a Delay waiting until nanosecondCount nanoseconds after startup" ^self new initUntilNanoseconds: nanosecondCount ] Delay class >> untilMilliseconds: millisecondCount [ "Answer a Delay waiting until millisecondCount milliseconds after startup" ^self untilMilliseconds: millisecondCount * 1000000 ] Delay class >> activeDelay [ "Return the delay at the head of the queue." Queue isEmpty ifTrue: [^nil]. ^Queue last ] Delay class >> handleDelayRequestor [ "Handle a timer event; which can be either: - a schedule or unschedule request (DelayRequestor notNil) - a timer signal (not explicitly specified) We check for timer expiry every time we get a signal." | nextTick activeDelay | "Wait until there is work to do." TimeoutSem wait. "Process any schedule/unschedule requests" DelayRequestor isNil ifFalse: ["Schedule the given delay" DelayRequestor isActive ifTrue: [ self scheduleDelay: DelayRequestor ] ifFalse: [ self unscheduleDelay: DelayRequestor ]. DelayRequestor := nil]. "Signal any expired delays" [activeDelay := self activeDelay. activeDelay notNil and: [Time nanosecondClockValue >= activeDelay resumptionTime]] whileTrue: [activeDelay signal. self unscheduleDelay: activeDelay]. "Since we have processed all outstanding requests, reset the timing semaphore so that only new work will wake us up again. Do this RIGHT BEFORE setting the next wakeup call from the VM because it is only signaled once so we mustn't miss it." TimeoutSem initialize. "And signal when the next request is due." activeDelay isNil ifFalse: [ nextTick := activeDelay resumptionTime + Time.ClockOnStartup. Processor signal: TimeoutSem atNanosecondClockValue: nextTick]. ] Delay class >> runDelayProcess [ "Run the timer event loop." [[self handleDelayRequestor] repeat] ifCurtailed: [DelayProcess := nil. Delay startDelayLoop] ] Delay class >> scheduleDelay: aDelay [ "Private - Schedule this Delay. Run in the timer process, which is the only one that manipulates Queue." Queue add: aDelay ] Delay class >> unscheduleDelay: aDelay [ "Private - Unschedule this Delay. Run in the timer process, which is the only one that manipulates Queue." | activeDelay | activeDelay := self activeDelay. activeDelay isNil ifTrue: [^self]. activeDelay == aDelay ifTrue: [Queue removeLast] ifFalse: [Queue identityRemove: aDelay ifAbsent: []]. aDelay reset. ] Delay class >> startDelayLoop [ "Start the timer event loop." "Delay startDelayLoop" DelayProcess isNil ifFalse: [ DelayProcess terminate ]. "This semaphore does not protect Queue (which is only manipulated within one process for thread-safety, but rather DelayRequestor)." MutexSem := Semaphore forMutualExclusion. DelayRequestor := nil. "A sorted collection of delay->semaphore associations." Queue := SortedCollection sortBlock: [:d1 :d2 | d1 resumptionTime >= d2 resumptionTime]. TimeoutSem := Semaphore new. DelayProcess := [self runDelayProcess] forkAt: Processor timingPriority. DelayProcess name: 'delay process'. ObjectMemory addDependent: self. self update: #returnFromSnapshot ] Delay class >> update: aspect [ "Prime the timer event loop when the image starts running." aspect == #returnFromSnapshot ifTrue: [TimeoutSem signal] ] Delay class >> initialize [ IdleProcess := [[Processor pause: Processor idle] repeat] forkAt: Processor idlePriority. IdleProcess name: 'idle'. self startDelayLoop ] = aDelay [ "Answer whether the receiver and aDelay denote the same delay" self class == aDelay class ifFalse: [^false]. ^delayDuration isNil ifFalse: [delayDuration = aDelay basicDelayDuration] ifTrue: [resumptionTime = aDelay resumptionTime] ] hash [ "Answer an hash value for the receiver" ^resumptionTime hash bitXor: delayDuration hash ] notifyChange [ "Private - Notify the Delay process of a change in the active/inactive state of this Delay. Return immediately." MutexSem critical: [DelayRequestor := self. TimeoutSem signal]. ] signal [ "Wake the process that is waiting on this delay." | sema process | waitingProcess isNil ifTrue: [ sema := delaySemaphore. delaySemaphore := nil. sema isNil ifFalse: [sema signal]] ifFalse: [ process := waitingProcess. waitingProcess := nil. process isNil ifFalse: [process suspend; resume]]. ] isActive [ "Answer whether this Delay is being waited on." ^delaySemaphore notNil or: [waitingProcess notNil] ] timedWaitOn: aSemaphore [ "Schedule this Delay and wait on it. The current process will be suspended for the amount of time specified when this Delay was created, or until aSemaphore is signaled." | expired | self isActive ifTrue: [self error: 'delay already in use']. [self start. waitingProcess := Processor activeProcess. self notifyChange. "This can already signal the semaphore!" waitingProcess == nil ifFalse: [expired := aSemaphore wait]] ensure: [ waitingProcess == nil ifFalse: [waitingProcess := nil. self notifyChange]]. "#reset will have been called by #unscheduleDelay:, either through the second call to #notifyChange, or because the timeout fired. If the suspend/resume pair in #signal was executed, expired will be nil, otherwise it will be the semaphore. This is guaranteed by the VM. Use this fact to return the correct value." ^expired == nil ] wait [ "Schedule this Delay and wait on it. The current process will be suspended for the amount of time specified when this Delay was created." self isActive ifTrue: [self error: 'delay already in use']. [self start. delaySemaphore := Semaphore new. self notifyChange. "This can already signal the semaphore!" delaySemaphore == nil ifFalse: [delaySemaphore wait]] ensure: [ delaySemaphore == nil ifFalse: [delaySemaphore := nil. self notifyChange]]. "#reset will have been called by #unscheduleDelay:, either through the second call to #notifyChange, or because the timeout fired." ] value: aBlock onTimeoutDo: aTimeoutBlock [ "Execute aBlock for up to the time of my own delay; in case the code did not finish abort the execution, unwind the block and then evaluate aTimeoutBlock." | value timeout | timeout := false. value := [ | sem proc | "Use the semaphore to signal that we executed everything" sem := Semaphore new. "Remember the current process" proc := Processor activeProcess. "Start a process to wait in and then signal" [ Processor activeProcess name: 'Delay>>#value:onTimeoutDo:'. "Wait and see if it is timed out. If so send a signal." (self timedWaitOn: sem) ifTrue: [ proc signalInterrupt: (Kernel.TimeoutNotification on: self). ]. ] fork. aBlock ensure: [sem signal]. ] on: Kernel.TimeoutNotification do: [:e | e delay = self ifTrue: [timeout := true] ifFalse: [e pass]. ]. "Make sure we call the #ensure:/#ifCurtailed: blocks first." ^ timeout ifTrue: [aTimeoutBlock value] ifFalse: [value]. ] start [ "Prepare to wait on the delay." resumptionTime isNil ifTrue: [ resumptionTime := Time nanosecondClockValue + delayDuration ]. ] reset [ "Prepare to wait again on the delay." delayDuration isNil ifFalse: [resumptionTime := nil]. ] resumptionTime [ ^resumptionTime ] isAbsolute [ "Answer whether the receiver waits until an absolute time on the millisecond clock." ^delayDuration isNil ] asAbsolute [ "Answer a delay that waits until the current delay's resumptionTime, or delayDuration milliseconds from now if that would be nil. May answer the receiver if it is already waiting until an absolute time." self isAbsolute ifTrue: [ ^self ]. ^Delay untilNanoseconds: Time nanosecondClockValue + delayDuration. ] postCopy [ "Adjust the current delay so that it behaves as if it had just been created." self isAbsolute ifFalse: [ resumptionTime := nil ]. delaySemaphore := nil. waitingProcess := nil ] delayDuration [ "Answer the time I have left to wait, in milliseconds." ^resumptionTime isNil ifTrue: [ delayDuration ] ifFalse: [ (resumptionTime - Time nanosecondClockValue) max: 0 ] ] basicDelayDuration [ ^delayDuration ] initForNanoseconds: value [ "Initialize a Delay waiting for millisecondCount milliseconds" delayDuration := value ] initUntilNanoseconds: value [ "Initialize a Delay waiting for millisecondCount milliseconds after startup" resumptionTime := value. ] ] Eval [ Delay initialize ] smalltalk-3.2.5/kernel/Directory.st0000644000175000017500000001573012123404352014224 00000000000000"====================================================================== | | Directory Method Definitions | | ======================================================================" "====================================================================== | | Copyright 1988,92,94,95,99,2000,2001,2002,2005,2007,2008,2009 | Free Software Foundation, Inc. | Written by Paolo Bonzini. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" Object subclass: Directory [ Directory class >> primCreateTemporary: dirName [ ] Directory class >> primWorking: dirName [ ] Directory class >> home [ "Answer the path to the user's home directory" ^(Smalltalk getenv: 'HOME') ifNotNil: [ :path | File name: path ] ] Directory class >> image [ "Answer the path to GNU Smalltalk's image file" ^File name: ImageFilePath ] Directory class >> module [ "Answer the path to GNU Smalltalk's dynamically loaded modules" ModulePath isNil ifTrue:[ ^nil ]. ^File name: ModulePath ] Directory class >> prefix [ "Answer the path to GNU Smalltalk's installation prefix" Prefix isNil ifTrue:[ ^'/' ]. ^File name: Prefix ] Directory class >> execPrefix [ "Answer the path to GNU Smalltalk's executable installation prefix" ExecPrefix isNil ifTrue:[ ^'/' ]. ^File name: ExecPrefix ] Directory class >> libexec [ "Answer the path to GNU Smalltalk's auxiliary executables" LibexecPath isNil ifTrue:[ ^nil ]. ^File name: LibexecPath ] Directory class >> systemKernel [ "Answer the path to the installed Smalltalk kernel source files." SystemKernelPath isNil ifTrue:[ ^nil ]. ^File name: SystemKernelPath ] Directory class >> localKernel [ "Answer the path to the GNU Smalltalk kernel's Smalltalk source files. Same as `Directory kernel' since GNU Smalltalk 3.0." ^self kernel ] Directory class >> userBase [ "Answer the base path under which file for user customization of GNU Smalltalk are stored." ^File name: UserFileBasePath ] Directory class >> temporary [ "Answer the path in which temporary files can be created. This is read from the environment, and guessed if that fails." | d | (d := Smalltalk getenv: 'TMPDIR') isNil ifFalse: [^File name: d]. (d := Smalltalk getenv: 'TEMP') isNil ifFalse: [^File name: d]. (d := self home) isNil ifFalse: [d := d / 'tmp'. d isDirectory ifTrue: [^d]]. ^File name: '/tmp' ] Directory class >> kernel [ "Answer the path in which a local version of the GNU Smalltalk kernel's Smalltalk source files were searched when the image was created." ^KernelFilePath isNil ifTrue: [ File name: SystemKernelPath ] ifFalse: [ File name: KernelFilePath ] ] Directory class >> append: fileName to: directory [ "Answer the name of a file named `fileName' which resides in a directory named `directory'." directory isEmpty ifTrue: [^fileName]. fileName isEmpty ifTrue: [^directory]. self pathSeparator == $\ ifFalse: [(fileName at: 1) isPathSeparator ifTrue: [^fileName]] ifTrue: [(fileName at: 1) isPathSeparator ifTrue: [^(directory size >= 2 and: [(directory at: 2) = $:]) ifTrue: ['%1:%2' % {directory first. fileName}] ifFalse: [fileName]]. (fileName size >= 2 and: [(fileName at: 2) = $:]) ifTrue: [^fileName]]. ^(directory at: directory size) isPathSeparator ifTrue: [directory , fileName] ifFalse: [directory , self pathSeparatorString , fileName] ] Directory class >> pathSeparator [ "Answer (as a Character) the character used to separate directory names" ^CSymbols.PathSeparator ] Directory class >> pathSeparatorString [ "Answer (in a String) the character used to separate directory names" ^String with: self pathSeparator ] Directory class >> working [ "Answer the current working directory, not following symlinks." ^File name: Directory workingName ] Directory class >> workingName [ "Answer the current working directory, not following symlinks." ] Directory class >> working: dirName [ "Change the current working directory to dirName." (self primWorking: dirName asString) < 0 ifTrue: [File checkError]. ] Directory class >> createTemporary: prefix [ "Create an empty directory whose name starts with prefix and answer it." | name | name := prefix asString , 'XXXXXX'. (self primCreateTemporary: name) isNil ifTrue: [File checkError]. ^File name: name ] Directory class >> allFilesMatching: aPattern do: aBlock [ "Invoke #allFilesMatching:do: on the current working directory." self working allFilesMatching: aPattern do: aBlock ] Directory class >> create: dirName [ "Create a directory named dirName and answer it." ^(File name: dirName) createDirectory ] ] smalltalk-3.2.5/kernel/VFS.st0000644000175000017500000006766012123404352012727 00000000000000"====================================================================== | | Virtual File System layer definitions | | ======================================================================" "====================================================================== | | Copyright 2002, 2005, 2007, 2008, 2009 Free Software Foundation, Inc. | Written by Paolo Bonzini. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" Namespace current: VFS [ FilePath subclass: FileWrapper [ | file | FileWrapper class >> initialize [ "Register the receiver with ObjectMemory" ObjectMemory addDependent: self. ] FileWrapper class >> update: aspect [ "Private - Remove the files before quitting, and register the virtual filesystems specified by the subclasses upon image load." aspect == #aboutToQuit ifTrue: [self broadcast: #release] ] FileWrapper class >> on: file [ "Create an instance of this class representing the contents of the given file, under the virtual filesystem fsName." ^self new file: file ] = aFile [ "Answer whether the receiver represents the same file as the receiver." ^self class == aFile class and: [ self file = aFile file ] ] hash [ "Answer a hash value for the receiver." ^self file hash ] asString [ "Answer the string representation of the receiver's path." ^self file asString ] name [ "Answer the full path to the receiver." ^self file name ] isAbsolute [ "Answer whether the receiver identifies an absolute path." ^self file isAbsolute ] full [ "Answer the size of the file identified by the receiver" self isAbsolute ifTrue: [ ^self ]. ^self class on: self file full ] mode [ "Answer the permission bits for the file identified by the receiver" ^self file mode ] mode: anInteger [ "Answer the permission bits for the file identified by the receiver" self file mode: anInteger ] size [ "Answer the size of the file identified by the receiver" ^self file size ] lastAccessTime [ "Answer the last access time of the file identified by the receiver" ^self file lastAccessTime ] exists [ "Answer whether a file with the name contained in the receiver does exist." ^self file exists ] isAbsolute [ "Answer whether the receiver identifies an absolute path." ^self file isAbsolute ] isReadable [ "Answer whether a file with the name contained in the receiver does exist and is readable" ^self file isReadable ] isWriteable [ "Answer whether a file with the name contained in the receiver does exist and is writeable" ^self file isWriteable ] isExecutable [ "Answer whether a file with the name contained in the receiver does exist and is executable" ^self file isExecutable ] isAccessible [ "Answer whether a directory with the name contained in the receiver does exist and can be accessed" ^self file isAccessible ] isDirectory [ "Answer whether a file with the name contained in the receiver does exist identifies a directory." ^self file isDirectory ] isSymbolicLink [ "Answer whether a file with the name contained in the receiver does exist and identifies a symbolic link." ^self file isSymbolicLink ] owner: ownerString group: groupString [ "Set the receiver's owner and group to be ownerString and groupString." self file owner: ownerString group: groupString ] lastAccessTime: accessDateTime lastModifyTime: modifyDateTime [ "Update the timestamps of the file corresponding to the receiver, to be accessDateTime and modifyDateTime." self file lastAccessTime: accessDateTime lastModifyTime: modifyDateTime ] lastChangeTime [ "Answer the last change time of the file identified by the receiver (the `last change time' has to do with permissions, ownership and the like). On some operating systems, this could actually be the file creation time." ^self file lastChangeTime ] creationTime [ "Answer the creation time of the file identified by the receiver. On some operating systems, this could actually be the last change time (the `last change time' has to do with permissions, ownership and the like)." ^self file creationTime ] lastModifyTime [ "Answer the last modify time of the file identified by the receiver (the `last modify time' has to do with the actual file contents)." ^self file lastModifyTime ] isReadable [ "Answer whether a file with the name contained in the receiver does exist and is readable" ^self file isReadable ] isWriteable [ "Answer whether a file with the name contained in the receiver does exist and is writeable" ^self file isWritable ] isExecutable [ "Answer whether a file with the name contained in the receiver does exist and is executable" ^self file isExecutable ] open: class mode: mode ifFail: aBlock [ "Open the receiver in the given mode (as answered by FileStream's class constant methods)" ^self file open: class mode: mode ifFail: aBlock ] remove [ "Remove the file with the given path name" self file remove ] symlinkAs: destName [ "Create destName as a symbolic link of the receiver. The appropriate relative path is computed automatically." ^self file symlinkAs: destName ] pathFrom: dirName [ "Compute the relative path from the directory dirName to the receiver" ^self file pathFrom: dirName ] symlinkFrom: srcName [ "Create the receiver as a symbolic link from srcName (relative to the path of the receiver)." ^self file symlinkFrom: srcName ] renameTo: newName [ "Rename the file identified by the receiver to newName" ^self file renameTo: newName ] pathTo: destName [ "Compute the relative path from the receiver to destName." ^self file pathTo: destName ] at: aName [ "Answer a File or Directory object as appropriate for a file named 'aName' in the directory represented by the receiver." ^self class on: (self file at: aName) ] namesDo: aBlock [ "Evaluate aBlock once for each file in the directory represented by the receiver, passing its name." self file namesDo: aBlock ] file [ ^file ] file: aFilePath [ file := aFilePath. ] ] ] Namespace current: Kernel [ VFS.FileWrapper subclass: RecursiveFileWrapper [ do: aBlock [ "Same as the wrapped #do:, but reuses the file object for efficiency." aBlock value: self file. self file namesDo: [:name | | f | (#('.' '..') includes: name) ifFalse: [ f := self at: name. aBlock value: f file. (f isDirectory and: [f isSymbolicLink not]) ifTrue: [f do: aBlock]]] ] namesDo: aBlock prefixLength: anInteger [ "Same as the wrapped #namesDo:, but navigates the entire directory tree recursively. Since the objects created by #at: also contain the path to the receiver, anInteger is used to trim it." self file namesDo: [:name | | f | (#('.' '..') includes: name) ifFalse: [ f := self at: name. aBlock value: (f asString copyFrom: anInteger). (f isDirectory and: [f isSymbolicLink not]) ifTrue: [f namesDo: aBlock prefixLength: anInteger ]]] ] namesDo: aBlock [ "Same as the wrapped #namesDo:, but navigates the entire directory tree recursively." | n base | aBlock value: '.'. base := self asString. n := base last = Directory pathSeparator ifTrue: [ base size + 1 ] ifFalse: [ base size + 2 ]. self namesDo: aBlock prefixLength: n ] remove [ "Removes the entire directory tree recursively." self isDirectory ifTrue: [ self file namesDo: [:name | | f | f := self at: name. f isDirectory ifTrue: [((#('.' '..') includes: name) or: [f isSymbolicLink]) ifFalse: [f all remove]] ifFalse: [f remove]]]. super remove ] isFileSystemPath [ "Answer whether the receiver corresponds to a real filesystem path." ^self file isFileSystemPath ] lastAccessTime: accessDateTime lastModifyTime: modifyDateTime [ "Update the timestamps of all files in the tree to be accessDateTime and modifyDateTime." self isDirectory ifFalse: [ ^super lastAccessTime: accessDateTime lastModifyTime: modifyDateTime ]. self do: [ :each | each lastAccessTime: accessDateTime lastModifyTime: modifyDateTime ] ] owner: ownerString group: groupString [ "Set the owner and group for all files and directories in the tree." self isDirectory ifFalse: [ ^super owner: ownerString group: groupString ]. "These special calls cache the uid and gid to avoid repeated lookups." [ File setOwnerFor: nil owner: ownerString group: groupString. self do: [ :each | each owner: ownerString group: groupString ] ] ensure: [ File setOwnerFor: nil owner: nil group: nil ] ] mode: anInteger [ "Set the mode to be anInteger for all files in the tree. Directory modes are left unchanged." self isDirectory ifFalse: [ ^super mode: anInteger ]. self do: [ :each | each isDirectory ifFalse: [ each mode: anInteger ] ] ] fileMode: fMode directoryMode: dMode [ "Set the mode to be fMode for all files in the tree, and dMode for all directories in the tree." self isDirectory ifFalse: [ ^super mode: fMode ]. super mode: dMode. self isDirectory ifTrue: [ self do: [ :each | each mode: (each isDirectory ifTrue: [ dMode ] ifFalse: [ fMode ]) ] ] ] ] ] Namespace current: VFS [ FileWrapper subclass: ArchiveFile [ | tmpFiles topLevelFiles allFiles extractedFiles | displayOn: aStream [ "Print a representation of the file identified by the receiver." super displayOn: aStream. aStream nextPut: $#. self class printOn: aStream ] isDirectory [ "Answer true. The archive can always be considered as a directory." ^true ] isAccessible [ "Answer whether a directory with the name contained in the receiver does exist and can be accessed" ^self isReadable ] at: aName [ "Answer a FilePath for a file named `aName' residing in the directory represented by the receiver." | handler data | allFiles isNil ifTrue: [self refresh]. data := allFiles at: aName ifAbsent: [^nil]. handler := data at: 5 ifAbsent: [nil]. handler isNil ifFalse: [^handler]. tmpFiles isNil ifTrue: [tmpFiles := LookupTable new. FileWrapper addDependent: self. self addToBeFinalized]. ^tmpFiles at: aName ifAbsentPut: [(TmpFileArchiveMember new) name: aName; archive: self] ] nameAt: aString [ "Answer a FilePath for a file named `aName' residing in the directory represented by the receiver." ^aString ] namesDo: aBlock [ "Evaluate aBlock once for each file in the directory represented by the receiver, passing its name." topLevelFiles isNil ifTrue: [self refresh]. topLevelFiles do: aBlock ] release [ "Release the resources used by the receiver that don't survive when reloading a snapshot." tmpFiles isNil ifFalse: [tmpFiles do: [:each | each release]. tmpFiles := nil]. extractedFiles isNil ifFalse: [extractedFiles do: [:each | self primUnlink: each]. extractedFiles := nil]. super release ] fillMember: anArchiveMember [ "Extract the information on anArchiveMember. Answer false if it actually does not exist in the archive; otherwise, answer true after having told anArchiveMember about them by sending #size:stCtime:stMtime:stAtime:isDirectory: to it." | data | allFiles isNil ifTrue: [self refresh]. data := allFiles at: anArchiveMember name ifAbsent: [nil]. data isNil ifTrue: [^false]. anArchiveMember fillFrom: data. ^true ] member: anArchiveMember do: aBlock [ "Evaluate aBlock once for each file in the directory represented by anArchiveMember, passing its name." | data | allFiles isNil ifTrue: [self refresh]. data := allFiles at: anArchiveMember name ifAbsent: [nil]. data isNil ifTrue: [^SystemExceptions.FileError signal: 'File not found']. (data at: 1) isNil ifTrue: [^SystemExceptions.FileError signal: 'Not a directory']. (data at: 1) do: aBlock ] refresh [ "Extract the directory listing from the archive" | pipe line parentPath name current currentPath directoryTree directory | super refresh. current := currentPath := nil. allFiles := LookupTable new. directoryTree := LookupTable new. self fileData do: [:data | | path size date mode member | mode := self convertMode: (data at: 4). data at: 4 put: mode. path := data at: 1. path last = $/ ifTrue: [path := path copyFrom: 1 to: path size - 1]. "Look up the tree for the directory in which the file resides. We keep a simple 1-element cache." parentPath := File pathFor: path. name := File stripPathFrom: path. parentPath = currentPath ifFalse: [currentPath := parentPath. current := self findDirectory: path into: directoryTree]. "Create an item in the tree for directories, and add an association to the allFiles SortedCollection" directory := (mode bitAnd: 8r170000) = 8r40000 ifTrue: [current at: name put: LookupTable new] ifFalse: [current at: name put: nil]. data at: 1 put: directory. allFiles at: path put: data. member := data at: 5 ifAbsent: [nil]. member notNil ifTrue: [member fillFrom: data]]. "Leave the LookupTables to be garbage collected, we are now interested in the file names only." topLevelFiles := directoryTree keys asArray. allFiles do: [:data | (data at: 1) isNil ifFalse: [data at: 1 put: (data at: 1) keys asArray]] ] member: anArchiveMember mode: bits [ "Set the permission bits for the file in anArchiveMember." self subclassResponsibility ] removeMember: anArchiveMember [ "Remove the member represented by anArchiveMember." self subclassResponsibility ] updateMember: anArchiveMember [ "Update the member represented by anArchiveMember by copying the file into which it was extracted back to the archive." self subclassResponsibility ] extractMember: anArchiveMember [ "Extract the contents of anArchiveMember into a file that resides on disk, and answer the name of the file." extractedFiles isNil ifTrue: [extractedFiles := IdentityDictionary new]. ^extractedFiles at: anArchiveMember ifAbsentPut: [| temp | temp := FileStream openTemporaryFile: Directory temporary , '/vfs'. self extractMember: anArchiveMember into: temp. File name: temp name] ] extractMember: anArchiveMember into: file [ "Extract the contents of anArchiveMember into a file that resides on disk, and answer the name of the file." self subclassResponsibility ] convertMode: mode [ "Convert the mode from a string, character or boolean to an octal number." mode isNumber ifTrue: [^mode]. mode isString ifTrue: [^self convertModeString: mode]. mode isCharacter ifTrue: [^self convertMode: mode == $d]. ^mode ifTrue: [8r40755] ifFalse: [8r644] ] convertModeString: modeString [ "Convert the mode from a string to an octal number." | mode | mode := 0. (modeString at: 1) = $l ifTrue: [mode := 8r120000]. (modeString at: 1) = $d ifTrue: [mode := 8r40000]. (modeString at: 4) asLowercase = $s ifTrue: [mode := mode + 8r4000]. (modeString at: 7) asLowercase = $s ifTrue: [mode := mode + 8r2000]. (modeString at: 10) asLowercase = $t ifTrue: [mode := mode + 8r1000]. modeString from: 2 to: 10 keysAndValuesDo: [:i :ch | ch isLowercase ifTrue: [mode := mode setBit: 11 - i]]. ^mode ] findDirectory: path into: tree [ "Look up into tree (which is a tree of Dictionaries) the directory that is the parent of the file named `path'." | current last | current := tree. last := 1. path keysAndValuesDo: [:i :each | | element | each = $/ ifTrue: [last = i ifFalse: [element := path copyFrom: last to: i - 1. current := current at: element ifAbsentPut: ["The list command might output files but not directories. No problem, we create them along the way." | directory | directory := LookupTable new. allFiles at: (path copyFrom: 1 to: i - 1) put: {directory. 0. self creationTime. self mode bitOr: 8r40111}. directory]]. last := i + 1]]. ^current ] ] ] Namespace current: VFS [ FilePath subclass: ArchiveMember [ | archive name mode size stCtime stMtime stAtime | = aFile [ "Answer whether the receiver represents the same file as the receiver." ^self class == aFile class and: [ self archive = aFile archive and: [ self name = aFile name ] ] ] hash [ "Answer a hash value for the receiver." ^self archive hash bitXor: self name hash ] archive: anArchiveFile [ "Set the archive of which the receiver is a member." archive := anArchiveFile ] full [ "Answer the size of the file identified by the receiver" ^self archive full at: self name ] fillFrom: data [ "Called back by the receiver's archive when the ArchiveMember asks for file information." self size: (data at: 2) stMtime: (data at: 3) mode: (data at: 4) ] size: bytes stMtime: mtime mode: modeBits [ "Set the file information for the receiver." size := bytes. stCtime := self archive lastModifyTime. stMtime := mtime. stAtime := self archive lastAccessTime. mode := modeBits ] size: bytes stCtime: ctime stMtime: mtime stAtime: atime mode: modeBits [ "Set the file information for the receiver." size := bytes. stCtime := ctime. stMtime := mtime. stAtime := atime. mode := modeBits ] asString [ "Answer the name of the file identified by the receiver as answered by File>>#name." ^self name ] displayOn: aStream [ "Print a representation of the file identified by the receiver." self archive displayOn: aStream. aStream nextPut: $/. super displayOn: aStream ] isAbsolute [ "Answer whether the receiver identifies an absolute path." ^self archive isAbsolute ] name [ "Answer the receiver's file name." ^name ] name: aName [ "Set the receiver's file name to aName." name := aName ] archive [ "Answer the archive of which the receiver is a member." ^archive ] size [ "Answer the size of the file identified by the receiver" size isNil ifTrue: [self refresh]. ^size ] lastAccessTime [ "Answer the last access time of the file identified by the receiver" stAtime isNil ifTrue: [self refresh]. ^stAtime ] lastChangeTime [ "Answer the last change time of the file identified by the receiver (the `last change time' has to do with permissions, ownership and the like). On some operating systems, this could actually be the file creation time." stCtime isNil ifTrue: [self refresh]. ^stCtime ] creationTime [ "Answer the creation time of the file identified by the receiver. On some operating systems, this could actually be the last change time (the `last change time' has to do with permissions, ownership and the like)." stCtime isNil ifTrue: [self refresh]. ^stCtime ] lastModifyTime [ "Answer the last modify time of the file identified by the receiver (the `last modify time' has to do with the actual file contents)." stMtime isNil ifTrue: [self refresh]. ^stMtime ] refresh [ "Refresh the statistics for the receiver" self archive fillMember: self ] exists [ "Answer whether a file with the name contained in the receiver does exist." ^self archive fillMember: self ] mode [ "Answer the octal permissions for the file." size isNil ifTrue: [self refresh]. ^mode bitAnd: 4095 ] mode: mode [ "Set the octal permissions for the file to be `mode'." self archive member: self mode: (mode bitAnd: 4095) ] isSymbolicLink [ "Answer whether a file with the name contained in the receiver does exist and identifies a symbolic link." size isNil ifTrue: [self refresh]. ^(mode bitAnd: 8r170000) = 8r120000 ] isDirectory [ "Answer whether a file with the name contained in the receiver does exist and identifies a directory." size isNil ifTrue: [self refresh]. ^(mode bitAnd: 8r170000) = 8r40000 ] isReadable [ "Answer whether a file with the name contained in the receiver does exist and is readable" ^true ] isWriteable [ "Answer whether a file with the name contained in the receiver does exist and is writeable" ^true ] isExecutable [ "Answer whether a file with the name contained in the receiver does exist and is executable" ^false ] isAccessible [ "Answer whether a directory with the name contained in the receiver does exist and is accessible" ^true ] open: class mode: mode ifFail: aBlock [ "Open the receiver in the given mode (as answered by FileStream's class constant methods)" self subclassResponsibility ] update: aspect [ "Private - Update the in-archive version of the file before closing." aspect == #beforeClosing ifTrue: [self archive updateMember: self] aspect == #afterClosing ifTrue: [self archive refresh. self refresh] ] remove [ "Remove the file with the given path name" self archive removeMember: self. File checkError ] renameTo: newFileName [ "Rename the file with the given path name oldFileName to newFileName" self notYetImplemented ] at: aName [ "Answer a FilePath for a file named `aName' residing in the directory represented by the receiver." ^self archive at: (File append: aName to: self name) ] , aName [ "Answer an object of the same kind as the receiver, whose name is suffixed with aName." ^self archive at: (self name, aName) ] createDirectory: dirName [ "Create a subdirectory of the receiver, naming it dirName." self archive createDirectory: (File append: dirName to: self name) ] namesDo: aBlock [ "Evaluate aBlock once for each file in the directory represented by the receiver, passing its name." self archive member: self do: aBlock ] ] ] Namespace current: VFS [ ArchiveMember subclass: TmpFileArchiveMember [ | file | release [ "Release the resources used by the receiver that don't survive when reloading a snapshot." "Remove the file that was temporarily holding the file contents" self extracted ifTrue: [ file remove. file := nil ]. super release ] open: class mode: mode ifFail: aBlock [ "Open the receiver in the given mode (as answered by FileStream's class constant methods)" | fileStream | self file isNil ifTrue: [^aBlock value]. fileStream := file open: class mode: mode ifFail: [^aBlock value]. mode == FileStream read ifFalse: [fileStream addDependent: self]. fileStream setFile: self. ^fileStream ] extracted [ "Answer whether the file has already been extracted to disk." ^file notNil ] file [ "Answer the real file name which holds the file contents, or nil if it does not apply." file isNil ifFalse: [^file]. self exists ifFalse: [^nil]. file := self archive extractMember: self. ^file ] ] ] smalltalk-3.2.5/kernel/FloatE.st0000644000175000017500000002022512123404352013425 00000000000000"====================================================================== | | FloatE Method Definitions | | ======================================================================" "====================================================================== | | Copyright 2002, 2009 Free Software Foundation, Inc. | Written by Paolo Bonzini. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" Float subclass: FloatE [ FloatE class >> coerce: aNumber [ "Answer aNumber converted to a FloatE" ^aNumber asFloatE ] FloatE class >> signByte [ "Answer the byte of the receiver that contains the sign bit" ^##(| n k | n := -2.0e. 1 to: n size do: [:i | (n at: i) >= 128 ifTrue: [k := i]]. k) ] FloatE class >> fromBytes: aByteArray [ "Answer a float with the bytes in aByteArray, which are in big-endian format." | b permutation | permutation := ##(| signByte perm | signByte := FloatE signByte. signByte = 1 ifTrue: [ perm := #[1 2 3 4] ]. signByte = 4 ifTrue: [ perm := #[4 3 2 1] ]. perm). b := FloatE new: 4. 1 to: 4 do: [ :i | b at: i put: (aByteArray at: (permutation at: i)) ]. b makeReadOnly: true. ^b ] FloatE class >> e [ "Returns the value of e. Hope is that it is precise enough" ^16r2.B7E151628AED2A6ABF71588e ] FloatE class >> precision [ "Answer the number of bits in the mantissa. 1 + (2^-precision) = 1" ^CFloatBinaryDigits ] FloatE class >> fminNormalized [ "Return the smallest normalized FloatE that is > 0" ^CFloatMin ] FloatE class >> fmax [ "Return the largest normalized FloatE that is not infinite." ^CFloatMax ] FloatE class >> emax [ "Return the maximum allowable exponent for a FloatE that is finite." ^CFloatMaxExp ] FloatE class >> emin [ "Return the maximum allowable exponent for a FloatE that is finite." ^CFloatMinExp ] FloatE class >> decimalDigits [ "Return the number of decimal digits of precision for a FloatE. Technically, if P is the precision for the representation, then the decimal precision Q is the maximum number of decimal digits such that any floating point number with Q base 10 digits can be rounded to a floating point number with P base 2 digits and back again, without change to the Q decimal digits." ^CFloatDigits ] FloatE class >> log10Base2 [ "Returns the value of log2 10. Hope is that it is precise enough" ^16r3.5269E12F346E2BF924AFDBFDe ] FloatE class >> ln10 [ "Returns the value of ln 10. Hope is that it is precise enough" ^16r2.4D763776AAA2B05BA95B58AEe ] FloatE class >> infinity [ "Return a FloatE that represents positive infinity." ^CFloatPInf ] FloatE class >> negativeInfinity [ "Return a FloatE that represents negative infinity." ^CFloatNInf ] FloatE class >> nan [ "Return a FloatE that represents a mathematically indeterminate value (e.g. Inf - Inf, Inf / Inf)." ^CFloatNaN ] FloatE class >> pi [ "Returns the value of pi. Hope is that it is precise enough" ^16r3.243F6A8885A308D313198A2Ee ] zero [ "Coerce 0 to the receiver's class" ^0.0e ] half [ "Coerce 0.5 to the receiver's class" ^0.5e ] unity [ "Coerce 1 to the receiver's class" ^1.0e ] coerce: aNumber [ "Coerce aNumber to the receiver's class" ^aNumber asFloatE ] generality [ "Answer the receiver's generality" ^400 ] asFloatE [ "Just defined for completeness. Return the receiver." ^self ] ten [ "Private - Return 10, converted to the receiver's class." ^10.0e ] exponentLetter [ "Private - Return the letter to be printed just before the exponent" ^$e ] + arg [ "Sum the receiver and arg and answer another Number" ^self retrySumCoercing: arg ] - arg [ "Subtract arg from the receiver and answer another Number" ^self retryDifferenceCoercing: arg ] < arg [ "Answer whether the receiver is less than arg" ^self retryRelationalOp: #< coercing: arg ] > arg [ "Answer whether the receiver is greater than arg" ^self retryRelationalOp: #> coercing: arg ] <= arg [ "Answer whether the receiver is less than or equal to arg" ^self retryRelationalOp: #<= coercing: arg ] >= arg [ "Answer whether the receiver is greater than or equal to arg" ^self retryRelationalOp: #>= coercing: arg ] = arg [ "Answer whether the receiver is equal to arg" ^self retryEqualityCoercing: arg ] ~= arg [ "Answer whether the receiver is not equal to arg" ^self retryInequalityCoercing: arg ] * arg [ "Multiply the receiver and arg and answer another Number" ^self retryMultiplicationCoercing: arg ] / arg [ "Divide the receiver by arg and answer another FloatE" ^self generality = arg generality ifTrue: [self zeroDivide] ifFalse: [self retryDivisionCoercing: arg] ] asFloatD [ "Answer the receiver converted to a FloatD" self primitiveFailed ] asFloatQ [ "Answer the receiver converted to a FloatQ" self primitiveFailed ] truncated [ "Truncate the receiver towards zero and answer the result" ^super truncated ] fractionPart [ "Answer the fractional part of the receiver" self checkCoercion. ^self primitiveFailed ] exponent [ "Answer the exponent of the receiver in mantissa*2^exponent representation ( |mantissa|<=1 )" ] timesTwoPower: arg [ "Answer the receiver multiplied by 2^arg" ] ] smalltalk-3.2.5/kernel/DynVariable.st0000644000175000017500000000452512123404352014460 00000000000000"====================================================================== | | DynamicVariable Method Definitions | | ======================================================================" "====================================================================== | | Copyright 2010 Free Software Foundation, Inc. | Written by Paolo Bonzini. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" Object subclass: DynamicVariable [ DynamicVariable class [ | processVariable | processVariable [ processVariable isNil ifTrue: [ processVariable := ProcessEnvironment uniqueInstance associationAt: self ]. ^processVariable ] use: anObject during: aBlock [ ^self processVariable use: anObject during: aBlock ] valueIfAbsent: aBlock [ ^self processVariable valueIfAbsent: aBlock ] value [ ^self processVariable value ] ] ] smalltalk-3.2.5/kernel/HomedAssoc.st0000644000175000017500000000543112123404352014302 00000000000000"====================================================================== | | HomedAssociation Method Definitions | | ======================================================================" "====================================================================== | | Copyright 2002 Free Software Foundation, Inc. | Written by Paolo Bonzini. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" Association subclass: HomedAssociation [ | environment | HomedAssociation class >> key: aKey value: aValue environment: aNamespace [ "Answer a new association with the given key and value" ^(self key: aKey value: aValue) environment: aNamespace ] environment [ "Answer the namespace in which I live." ^environment ] environment: aNamespace [ "Set the namespace in which I live to be aNamespace." environment := aNamespace ] storeOn: aStream [ "Put on aStream some Smalltalk code compiling to the receiver" aStream nextPut: $(. aStream store: self class. aStream nextPutAll: ' key: '. self key storeOn: aStream. aStream nextPutAll: ' value: '. self value storeOn: aStream. aStream nextPutAll: ' environment: '. self environment storeOn: aStream. aStream nextPut: $) ] mourn [ "This message is sent to the receiver when the object is made ephemeron (which is common when HomedAssociations are used by a WeakKeyDictionary or a WeakSet). The mourning of the object's key is first of all demanded to the environment (which will likely remove the object from itself), and then performed as usual by clearing the key and value fields." self environment mourn: self. super mourn ] ] smalltalk-3.2.5/kernel/UniString.st0000644000175000017500000000764612123404352014211 00000000000000"====================================================================== | | UnicodeString Method Definitions | | ======================================================================" "====================================================================== | | Copyright 2006, 2009 Free Software Foundation, Inc. | Written by Paolo Bonzini. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" CharacterArray subclass: UnicodeString [ UnicodeString class >> fromString: aString [ "Return the String, aString, converted to its Unicode representation. Unless the I18N package is loaded, this is not implemented." ^aString asUnicodeString ] UnicodeString class >> defaultEncoding [ "Answer the encoding used by the receiver. Conventionally, we answer 'Unicode' to ensure that two UnicodeStrings always have the same encoding." ^'Unicode' ] UnicodeString class >> isUnicode [ "Answer true; the receiver stores characters." ^true ] asString [ "Returns the string corresponding to the receiver. Without the Iconv package, unrecognized Unicode characters become $? characters. When it is loaded, an appropriate single- or multi-byte encoding could be used." | s each | s := String new: self size. 1 to: self size do: [:i | each := self basicAt: i. s at: i put: ((each value between: 0 and: 127) ifTrue: [each asCharacter] ifFalse: [$?])]. ^s ] asSymbol [ "Returns the symbol corresponding to the receiver" ^self asString asSymbol ] asUnicodeString [ "But I already am a UnicodeString! Really!" ^self ] displayOn: aStream [ "Print a representation of the receiver on aStream" self do: [:char | char displayOn: aStream] ] printOn: aStream [ "Print a representation of the receiver on aStream" aStream nextPut: $'. self do: [:char | char == $' ifTrue: [aStream nextPut: char]. char displayOn: aStream]. aStream nextPut: $' ] at: anIndex ifAbsent: aBlock [ "Answer the index-th indexed instance variable of the receiver" ^self checkIndexableBounds: anIndex ifAbsent: aBlock ] encoding [ "Answer the encoding used by the receiver. Conventionally, we answer 'Unicode' to ensure that two UnicodeStrings always have the same encoding." ^'Unicode' ] numberOfCharacters [ "Answer the number of Unicode characters in the receiver. This is the same as #size for UnicodeString." ^self size ] hash [ "Answer an hash value for the receiver" ^0 ] ] smalltalk-3.2.5/kernel/Integer.st0000644000175000017500000004153112123404352013653 00000000000000"====================================================================== | | Integer Method Definitions | | ======================================================================" "====================================================================== | | Copyright 1988,92,94,95,99,2000,2001,2002,2003,2005,2006,2008,2009,2010 | Free Software Foundation, Inc. | Written by Steve Byrne. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" Number subclass: Integer [ Integer class >> coerce: aNumber [ "Answer aNumber converted to a kind of Integer" ^aNumber truncated ] hash [ "Answer an hash value for the receiver" ^self ] timesRepeat: aBlock [ "Evaluate aBlock a number of times equal to the receiver's value. Compiled in-line for no argument aBlocks without temporaries, and therefore not overridable." 1 to: self do: [:each | aBlock value] ] digitAt: index [ "Answer the index-th base-256 digit of the receiver (byte), expressed in two's complement" ^(self bitShift: 8 - (8 * index)) bitAnd: 255 ] bitAt: index [ "Answer the index-th bit of the receiver (the LSB has an index of 1)" ^(self bitShift: (index - 1) negated) bitAnd: 1 ] bitAt: index put: value [ "Answer an integer which is identical to the receiver, possibly with the exception of the index-th bit of the receiver (the LSB having an index of 1), which assumes a value equal to the low-order bit of the second parameter." | bit | bit := (value bitAnd: 1) bitXor: (self bitAt: index). bit := bit bitShift: index - 1. ^self bitXor: bit ] bitInvert [ "Return the 1's complement of the bits of the receiver" ^self bitXor: -1 ] bitClear: aMask [ "Answer an Integer equal to the receiver, except that all the bits that are set in aMask are cleared." ^(self bitOr: aMask) bitXor: aMask ] allMask: anInteger [ "True if all 1 bits in anInteger are 1 in the receiver" ^(self bitAnd: anInteger) = anInteger ] anyMask: anInteger [ "True if any 1 bits in anInteger are 1 in the receiver" ^(self bitAnd: anInteger) ~= 0 ] clearBit: index [ "Clear the index-th bit of the receiver and answer a new Integer" | bit | bit := 1 bitShift: index - 1. ^(self bitOr: bit) bitXor: bit ] noMask: anInteger [ "Answer true if no 1 bits in anInteger are 1 in the receiver." ^(self bitAnd: anInteger) = 0 ] lowBit [ "Return the index of the lowest order 1 bit of the receiver." self subclassResponsibility ] highBit [ "Return the index of the highest order 1 bit of the receiver." self subclassResponsibility ] isBitSet: index [ "Answer whether the index-th bit of the receiver is set" ^((self bitShift: (index - 1) negated) bitAnd: 1) == 1 ] setBit: index [ "Set the index-th bit of the receiver and answer a new Integer" ^self bitOr: (1 bitShift: index - 1) ] binomial: anInteger [ "Compute the number of combinations of anInteger objects among a number of objects given by the receiver." | n k mask gcd maxNum step num den stepNum stepDen | (self < 0 or: [anInteger < 0 or: [anInteger > self]]) ifTrue: [^self arithmeticError: 'binomial coefficient with invalid arguments']. "The easy one." k := anInteger + anInteger > self ifTrue: [self - anInteger] ifFalse: [anInteger]. k = 0 ifTrue: [^1]. "The number of SmallInteger factors we computed so far" step := 1. "Two stacks holding intermediate factors." num := OrderedCollection new. den := OrderedCollection new. "The next factors to be multiplied are k and n." n := self. [stepNum := stepDen := 1. [maxNum := SmallInteger largest // n. [stepNum <= maxNum] whileTrue: [stepNum := stepNum * n. stepDen := stepDen * k. k = 1 ifTrue: ["We're finishing, empty the stack and then simplify the remaining common factors." gcd := stepNum gcd: stepDen. stepNum := stepNum divExact: gcd. stepDen := stepDen divExact: gcd. num size timesRepeat: [stepNum := stepNum * num removeLast. stepDen := stepDen * den removeLast]. ^stepNum // stepDen]. n := n - 1. k := k - 1]. (gcd := stepNum gcd: stepDen) > 1 and: [stepNum := stepNum divExact: gcd. stepDen := stepDen divExact: gcd. "The numerators and denominators have been simplified, try to add some more factors." stepNum <= maxNum]] whileTrue. "Pop factors from the stack and combine them. The number of factors we pop is equal to the order of the lowest bit set. That is, on the first iteration we push a size 1 LargeInteger; on the second iteration we pop it and make a size 2 LargeInteger; on the third iteration we push another size 1 LargeInteger; on the fourth iteration we pop it and make a size 2 LargeInteger; we then combine it with the other similarly sized integer and make a size 4 LargeInteger; and so on. For the denominator the balancing is probably worse, since we decide when to stop multiplying based on the numerator's magnitude, but it is not a serious problem." mask := step bitXor: step - 1. [mask = 1] whileFalse: [stepNum := stepNum * num removeLast. stepDen := stepDen * den removeLast. mask := mask bitShift: -1]. gcd := stepNum gcd: stepDen. num addLast: (stepNum divExact: gcd). den addLast: (stepDen divExact: gcd). step := step + 1] repeat ] factorial [ "Return the receiver's factorial." | mask k n a b max stack | self < 0 ifTrue: [^self arithmeticError: 'factorial of a negative number']. self < 2 ifTrue: [^1]. "The number of SmallInteger factors we computed so far" k := 1. "The next factor to be multiplied." n := self. "The stack holding intermediate factors." stack := OrderedCollection new. [a := n - 1. b := n. max := SmallInteger largest // n. [n := n - 2. n < 2 ifTrue: ["Done, empty the stack and combine all the factors." a := a * b. stack size timesRepeat: [a := a * stack removeLast]. ^a]. b < max] whileTrue: [a := a * (n - 1). b := b * n]. "Compose the two SmallInteger factors" a := a * b. "Pop factors from the stack and combine them. The number of factors we pop is equal to the order of the lowest bit set. That is, on the first iteration we push a size 1 LargeInteger; on the second iteration we pop it and make a size 2 LargeInteger; on the third iteration we push another size 1 LargeInteger; on the fourth iteration we pop it and make a size 2 LargeInteger; we then combine it with the other similarly sized integer and make a size 4 LargeInteger; and so on." mask := k bitXor: k - 1. [mask = 1] whileFalse: [a := a * stack removeLast. mask := mask bitShift: -1]. stack addLast: a. k := k + 1] repeat ] estimatedLog [ "Answer an estimate of (self abs floorLog: 10)" ^(self highBit asFloatD / FloatD log10Base2) ceiling ] floorLog: radix [ "Answer (self log: radix) floor. Optimized to answer an integer." | me answer | self < self zero ifTrue: [^self arithmeticError: 'cannot extract logarithm of a negative number']. radix <= radix unity ifTrue: [radix <= radix zero ifTrue: [^self arithmeticError: 'base of a logarithm cannot be negative']. radix = radix unity ifTrue: [^self arithmeticError: 'base of a logarithm cannot be 1']. ^(self ceilingLog: radix reciprocal) negated]. radix isInteger ifFalse: [^(radix coerce: self) floorLog: radix]. me := self. answer := 0. [me >= radix] whileTrue: [me := me // radix. answer := answer + 1]. ^answer ] ceilingLog: radix [ "Answer (self log: radix) ceiling. Optimized to answer an integer." | me answer | self < self zero ifTrue: [^self arithmeticError: 'cannot extract logarithm of a negative number']. radix <= radix unity ifTrue: [radix <= radix zero ifTrue: [^self arithmeticError: 'base of a logarithm cannot be negative']. radix = radix unity ifTrue: [^self arithmeticError: 'base of a logarithm cannot be 1']. ^(self floorLog: radix reciprocal) negated]. radix isInteger ifFalse: [^(radix coerce: self) ceilingLog: radix]. me := self. answer := 1. [me > radix] whileTrue: [me := me // radix. answer := answer + 1]. ^answer ] gcd: anInteger [ "Return the greatest common divisor (Euclid's algorithm) between the receiver and anInteger" | a b remainder | self negative | anInteger negative ifTrue: [^self abs gcd: anInteger abs]. self < anInteger ifTrue: [a := anInteger. b := self] ifFalse: [a := self. b := anInteger]. [b = 0] whileFalse: [remainder := a \\ b. a := b. b := remainder]. ^a ] lcm: anInteger [ "Return the least common multiple between the receiver and anInteger" ^((self divExact: (self gcd: anInteger)) * anInteger) abs ] even [ "Return whether the receiver is even" ^(self bitAnd: 1) = 0 ] odd [ "Return whether the receiver is odd" ^(self bitAnd: 1) ~= 0 ] asCharacter [ "Return self as a Character or UnicodeCharacter object." ^Character codePoint: self ] coerce: aNumber [ "Coerce aNumber to the receiver's class." ^aNumber truncated ] ceiling [ "Return the receiver - it's already truncated" ^self ] floor [ "Return the receiver - it's already truncated" ^self ] truncated [ "Return the receiver - it's already truncated" ^self ] rounded [ "Return the receiver - it's already truncated" ^self ] asScaledDecimal: n [ "Answer the receiver, converted to a ScaledDecimal object. The scale is forced to be 0." ^ScaledDecimal newFromNumber: self asFraction scale: 0 ] asFraction [ "Return the receiver converted to a fraction" ^Fraction numerator: self denominator: 1 ] isLiteralObject [ "Answer whether the receiver is expressible as a Smalltalk literal." ^true ] storeLiteralOn: aStream [ "Store on aStream some Smalltalk code which compiles to the receiver" self storeOn: aStream ] printOn: aStream base: b [ "Print on aStream the base b representation of the receiver" aStream nextPutAll: (self printString: b) ] storeOn: aStream base: b [ "Print on aStream Smalltalk code compiling to the receiver, represented in base b" aStream nextPutAll: (self printStringRadix: b) ] radix: baseInteger [ "Return the base baseInteger representation of the receiver, with BBr in front of it. This method is deprecated, use #printStringRadix: instead." ^self printStringRadix: baseInteger ] printStringRadix: baseInteger [ "Return the base baseInteger representation of the receiver, with BBr in front of it" | sign num string size radixSize | sign := self < self zero. num := sign ifFalse: [self] ifTrue: [self negated]. radixSize := (baseInteger floorLog: 10) + 1. size := (num floorLog: baseInteger) + radixSize + 2. sign ifTrue: [size := size + 1]. string := String new: size. num replace: string withStringBase: baseInteger. string replaceFrom: 1 to: radixSize with: (baseInteger printString: 10) startingAt: 1. string at: radixSize + 1 put: $r. sign ifTrue: [string at: radixSize + 2 put: $-]. ^string ] printOn: aStream paddedWith: padding to: size [ "Print on aStream the base 10 representation of the receiver, padded if necessary to size characters with copies of padding." self printOn: aStream paddedWith: padding to: size base: 10 ] printPaddedWith: padding to: size [ "Return the base baseInteger representation of the receiver, padded if necessary to size characters with copies of padding." ^self printPaddedWith: padding to: size base: 10 ] printOn: aStream paddedWith: padding to: size base: baseInteger [ "Print on aStream the base b representation of the receiver, padded if necessary to size characters with copies of padding." | num string extra reqSize | self < self zero ifFalse: [num := self. extra := 0] ifTrue: [num := self negated. extra := 1. aStream nextPut: $-]. reqSize := (num floorLog: baseInteger) + 1. aStream next: (size - reqSize - extra max: 0) put: padding. string := String new: reqSize. num replace: string withStringBase: baseInteger. aStream nextPutAll: string ] printPaddedWith: padding to: size base: baseInteger [ "Return the base baseInteger representation of the receiver, padded if necessary to size characters with copies of padding." | num string padFirst reqSize | self < self zero ifFalse: [num := self. padFirst := 1] ifTrue: [num := self negated. padFirst := 2]. reqSize := (num floorLog: baseInteger) + padFirst. string := String new: (reqSize max: size). padFirst = 2 ifTrue: [string at: 1 put: $-]. string replaceFrom: padFirst to: string size - reqSize + padFirst - 1 withObject: padding. num replace: string withStringBase: baseInteger. ^string ] printString: baseInteger [ "Return the base baseInteger representation of the receiver" | num string | ^self < self zero ifFalse: [string := String new: (self floorLog: baseInteger) + 1. self replace: string withStringBase: baseInteger] ifTrue: [num := self negated. string := String new: (num floorLog: baseInteger) + 2. string at: 1 put: $-. num replace: string withStringBase: baseInteger] ] displayString [ "Return the base 10 representation of the receiver" ^self printString: 10 ] printString [ "Return the base 10 representation of the receiver" ^self printString: 10 ] displayOn: aStream [ "Print on aStream the base 10 representation of the receiver" aStream nextPutAll: (self printString: 10) ] printOn: aStream [ "Print on aStream the base 10 representation of the receiver" aStream nextPutAll: (self printString: 10) ] storeString [ "Return the base 10 representation of the receiver" ^self printString: 10 ] storeOn: aStream [ "Print on aStream the base 10 representation of the receiver" aStream nextPutAll: (self printString: 10) ] replace: string withStringBase: b [ "Put in str the reversed base b representation of the receiver (which is > 0)" | num where | num := self. where := string size. [string at: where put: (Character digitValue: num \\ b). where := where - 1. (num := num // b) > 0] whileTrue. ^string ] isRational [ "Answer whether the receiver is rational - true" ^true ] isInteger [ ^true ] numerator [ ^self ] denominator [ ^1 ] ] smalltalk-3.2.5/kernel/WeakObjects.st0000644000175000017500000004104412130343734014462 00000000000000"===================================================================== | | Weak collections | | ======================================================================" "====================================================================== | | Copyright 1999,2000,2001,2002,2007,2008,2009 Free Software Foundation, Inc. | Written by Paolo Bonzini. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" Array subclass: WeakArray [ | values nilValues | WeakArray class >> new [ "Create a new WeakArray of size 0." ^self new: 0 ] WeakArray class >> new: size [ "Create a new WeakArray of the given size." ^self basicNew initialize: size ] postLoad [ "Called after loading an object; must restore it to the state before `preStore' was called. Make it weak again" values makeWeak ] initialize: size [ "Private - Initialize the values array; plus, make it weak and create the ByteArray used to track garbage collected values" values := Array new: size. values makeWeak. nilValues := ByteArray new: size withAll: 1 ] values: anArray whichAreNil: nilArray [ "Private - Initialize the values array to anArray and make it weak; plus, set to a copy of nilArray the ByteArray used to track garbage collected values" values := anArray. values makeWeak. nilValues := ByteArray new: anArray size. nilValues replaceFrom: 1 to: anArray size with: nilArray startingAt: 1 ] at: index [ "Answer the index-th item of the receiver, or nil if it has been garbage collected." ^values at: index ] atAll: indices put: object [ "Put object at every index contained in the indices collection" nilValues atAll: indices put: (object isNil ifTrue: [1] ifFalse: [0]). ^values atAll: indices put: object ] atAllPut: object [ "Put object at every index in the receiver" nilValues atAllPut: (object isNil ifTrue: [1] ifFalse: [0]). ^values atAllPut: object ] at: index put: object [ "Store the value associated to the given index; plus, store in nilValues whether the object is nil. nil objects whose associated item of nilValues is 1 were touched by the garbage collector." nilValues at: index put: (object isNil ifTrue: [1] ifFalse: [0]). ^values at: index put: object ] clearGCFlag: index [ "Clear the `object has been garbage collected' flag for the item at the given index" | object | object := values at: index. nilValues at: index put: (object isNil ifTrue: [1] ifFalse: [0]) ] do: aBlock [ "Evaluate aBlock for all the elements in the array, including the garbage collected ones (pass nil for those)." values do: aBlock ] aliveObjectsDo: aBlock [ "Evaluate aBlock for all the elements in the array, excluding the garbage collected ones. Note: a finalized object stays alive until the next collection (the collector has no means to see whether it was resuscitated by the finalizer), so an object being alive does not mean that it is usable." | value | 1 to: self size do: [:i | (value := values at: i) isNil ifFalse: [aBlock value: value] ifTrue: [(nilValues at: i) = 0 ifFalse: [aBlock value: value]]] ] isAlive: index [ "Answer whether the item at the given index is still alive or has been garbage collected. Note: a finalized object stays alive until the next collection (the collector has no means to see whether it was resuscitated by the finalizer), so an object being alive does not mean that it is usable." ^(values at: index) notNil or: [(nilValues at: index) = 1] ] size [ "Answer the number of items in the receiver" ^values size ] asArray [ "Answer a non-weak version of the receiver" ^values copy ] deepCopy [ "Returns a deep copy of the receiver (the instance variables are copies of the receiver's instance variables)" ^self class basicNew values: values deepCopy whichAreNil: nilValues ] shallowCopy [ "Returns a shallow copy of the receiver (the instance variables are not copied)" ^self class basicNew values: values shallowCopy whichAreNil: nilValues ] species [ "Answer Array; this method is used in the #copyEmpty: message, which in turn is used by all collection-returning methods (collect:, select:, reject:, etc.)." ^Array ] ] Set subclass: WeakSet [ add: newObject [ "Add newObject to the set, if and only if the set doesn't already contain an occurrence of it. Don't fail if a duplicate is found. Answer newObject" | index | index := self findIndex: newObject. (self primAt: index) isNil ifTrue: [ self incrementTally ifTrue: [index := self findIndex: newObject]. self primAt: index put: (self newAssociation: newObject)]. ^newObject ] do: aBlock [ "Enumerate all the non-nil members of the set" 1 to: self primSize do: [:i | (self primAt: i) notNil ifTrue: [aBlock value: (self primAt: i) key]] ] postLoad [ "Called after loading an object; must restore it to the state before `preStore' was called. Make it weak again" 1 to: self primSize do: [:i | (self primAt: i) notNil ifTrue: [(self primAt: i) makeEphemeron]] ] shallowCopy [ "Returns a shallow copy of the receiver (the instance variables are not copied)" | copy | copy := self copyEmpty: self capacity. self do: [:each | copy addWhileGrowing: (copy newAssociation: each)]. ^copy ] deepCopy [ "Returns a deep copy of the receiver (the instance variables are copies of the receiver's instance variables)" | copy | copy := self copyEmpty: self capacity. self do: [:each | copy addWhileGrowing: (copy newAssociation: each copy)]. ^copy ] newAssociation: key [ ^(HomedAssociation key: key value: nil environment: self) makeEphemeron; yourself ] mourn: anObject [ "Private - anObject has been found to have a weak key, remove it." "What has to be passed to #remove: is the key, not the whole object." super mourn: anObject key ] findElementIndex: anObject [ "Tries to see if anObject exists as an indexed variable. As soon as nil is found, the index of that slot is answered" | index size element | self beConsistent. "Sorry for the lack of readability, but I want speed... :-)" index := (anObject key hash scramble bitAnd: (size := self primSize) - 1) + 1. [(element := self primAt: index) isNil ifTrue: [^index]. index == size ifTrue: [index := 1] ifFalse: [index := index + 1]] repeat ] findIndex: anObject [ "Tries to see if anObject exists as an indexed variable. As soon as nil or anObject is found, the index of that slot is answered" | index size element | self beConsistent. "Sorry for the lack of readability, but I want speed... :-)" index := (anObject identityHash scramble bitAnd: (size := self primSize) - 1) + 1. [((element := self primAt: index) isNil or: [element key = anObject]) ifTrue: [^index]. index == size ifTrue: [index := 1] ifFalse: [index := index + 1]] repeat ] ] Dictionary subclass: WeakKeyDictionary [ | keys | WeakKeyDictionary class >> postLoad [ "Called after loading an object; must restore it to the state before `preStore' was called. Make it weak again" 1 to: self primSize do: [:i | (self primAt: i) notNil ifTrue: [(self primAt: i) makeEphemeron]] ] add: anAssociation [ "Store value as associated to the given key." | assoc | assoc := anAssociation. ((assoc isKindOf: HomedAssociation) and: [assoc environment == self]) ifFalse: [assoc := HomedAssociation key: assoc key value: assoc value environment: self]. assoc makeEphemeron. ^super add: assoc ] at: key put: value [ "Store value as associated to the given key." | assoc | assoc := HomedAssociation key: key value: value environment: self. assoc makeEphemeron. self add: assoc. ^value ] ] LookupTable subclass: WeakValueLookupTable [ | values | WeakValueLookupTable class >> primNew: realSize [ "Answer a new, uninitialized instance of the receiver with the given size" ^self basicNew: realSize ] at: key ifAbsent: aBlock [ "Answer the value associated to the given key, or the result of evaluating aBlock if the key is not found" | result | result := super at: key ifAbsent: [^aBlock value]. result isNil ifFalse: [^result]. self beConsistent. ^super at: key ifAbsent: aBlock ] at: key ifPresent: aBlock [ "If aKey is absent, answer nil. Else, evaluate aBlock passing the associated value and answer the result of the invocation" ^aBlock value: (self at: key ifAbsent: [^nil]) ] includesKey: key [ "Answer whether the receiver contains the given key." self at: key ifAbsent: [^false]. ^true ] beConsistent [ "Private - Clean the dictionary of key->(finalized value) pairs" | keys key | keys := WriteStream on: (Array new: self size // 3 + 1). 1 to: self primSize do: [:index | "Find values that are nil and should not be" (values isAlive: index) ifFalse: [keys nextPut: (self primAt: index). values clearGCFlag: index]]. self removeAllKeys: keys contents ifAbsent: [:key | ] ] initialize: anInteger [ "Private - Initialize the values array; plus, make it weak and create the ByteArray used to track garbage collected values" super initialize: anInteger. values := WeakArray new: self primSize ] primSize [ ^self basicSize ] primAt: index [ ^self basicAt: index ] primAt: index put: object [ ^self basicAt: index put: object ] valueAt: index [ ^values at: index ] valueAt: index put: object [ ^values at: index put: object ] rehash [ "Rehash the receiver" | key val | key := Array new: self primSize. val := Array new: values size. self resetTally. 1 to: self primSize do: [:i | "Find values that are nil and should not be" (key := self primAt: i) notNil ifTrue: [(values isAlive: i) ifTrue: [key at: i put: (self primAt: i). val at: i put: (self valueAt: i)]]. self primAt: i put: nil. self valueAt: i put: nil]. 1 to: self primSize do: [:i | (key at: i) isNil ifFalse: [self whileGrowingAt: (key at: i) put: (val at: i)]] ] ] WeakSet subclass: WeakIdentitySet [ identityIncludes: anObject [ "Answer whether I include anObject exactly. As I am an identity-set, this is the same as #includes:." ^self includes: anObject ] findIndex: anObject [ "Tries to see if anObject exists as an indexed variable. As soon as nil or anObject is found, the index of that slot is answered" | index size element | self beConsistent. "Sorry for the lack of readability, but I want speed... :-)" index := (anObject identityHash scramble bitAnd: (size := self primSize) - 1) + 1. [((element := self primAt: index) isNil or: [element key == anObject]) ifTrue: [^index]. index == size ifTrue: [index := 1] ifFalse: [index := index + 1]] repeat ] ] WeakKeyDictionary subclass: WeakKeyIdentityDictionary [ keysClass [ "Answer the class answered by #keys" ^IdentitySet ] hashFor: anObject [ "Return an hash value for the item, anObject" ^anObject identityHash ] findIndex: anObject [ "Tries to see if anObject exists as an indexed variable. As soon as nil or anObject is found, the index of that slot is answered" | index size element | self beConsistent. "Sorry for the lack of readability, but I want speed... :-)" index := (anObject identityHash scramble bitAnd: (size := self primSize) - 1) + 1. [((element := self primAt: index) isNil or: [element key == anObject]) ifTrue: [^index]. index == size ifTrue: [index := 1] ifFalse: [index := index + 1]] repeat ] ] WeakValueLookupTable subclass: WeakValueIdentityDictionary [ keysClass [ "Answer the class answered by #keys" ^IdentitySet ] hashFor: anObject [ "Return an hash value for the item, anObject" ^anObject identityHash ] findIndex: anObject [ "Tries to see if anObject exists as an indexed variable. As soon as nil or anObject is found, the index of that slot is answered" | index size element | self beConsistent. "Sorry for the lack of readability, but I want speed... :-)" index := (anObject identityHash scramble bitAnd: (size := self primSize) - 1) + 1. [((element := self primAt: index) isNil or: [element == anObject]) ifTrue: [^index]. index == size ifTrue: [index := 1] ifFalse: [index := index + 1]] repeat ] ] smalltalk-3.2.5/kernel/LookupKey.st0000644000175000017500000000533012123404352014175 00000000000000"====================================================================== | | LookupKey Method Definitions | | ======================================================================" "====================================================================== | | Copyright 1999, 2000, 2001, 2002 Free Software Foundation, Inc. | Written by Paolo Bonzini. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" Magnitude subclass: LookupKey [ | key | LookupKey class >> key: aKey [ "Answer a new instance of the receiver with the given key and value" ^self new key: aKey ] key: aKey [ "Set the receiver's key to aKey" key := aKey ] key [ "Answer the receiver's key" ^key ] < aLookupKey [ "Answer whether the receiver's key is less than aLookupKey's" ^self key < aLookupKey key ] = aLookupKey [ "Answer whether the receiver's key and value are the same as aLookupKey's, or false if aLookupKey is not an instance of the receiver" ^self class == aLookupKey class and: [self key = aLookupKey key] ] hash [ "Answer an hash value for the receiver" ^key hash ] printOn: aStream [ "Put on aStream a representation of the receiver" aStream nextPut: $[. self key printOn: aStream. aStream nextPut: $] ] storeOn: aStream [ "Put on aStream some Smalltalk code compiling to the receiver" aStream nextPut: $(. aStream store: self class. aStream nextPutAll: ' key: '. self key storeOn: aStream. aStream nextPut: $) ] ] smalltalk-3.2.5/kernel/CType.st0000644000175000017500000003163012123404352013301 00000000000000"====================================================================== | | Base class definition for C data type description objects. | | ======================================================================" "====================================================================== | | Copyright 1990,91,92,94,95,99,2000,2001,2007,2008 | Free Software Foundation, Inc. | Written by Steve Byrne. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" Object subclass: CType [ | cObjectType | TypeMap := nil. CType class >> initialize [ "Initialize the receiver's TypeMap" Smalltalk at: #CObjectType put: (CType cObjectType: CObject). Smalltalk at: #CCharType put: (CScalarCType cObjectType: CChar). Smalltalk at: #CUCharType put: (CScalarCType cObjectType: CUChar). Smalltalk at: #CShortType put: (CScalarCType cObjectType: CShort). Smalltalk at: #CUShortType put: (CScalarCType cObjectType: CUShort). Smalltalk at: #CLongType put: (CScalarCType cObjectType: CLong). Smalltalk at: #CULongType put: (CScalarCType cObjectType: CULong). Smalltalk at: #CLongLongType put: (CScalarCType cObjectType: CLongLong). Smalltalk at: #CULongLongType put: (CScalarCType cObjectType: CULongLong). Smalltalk at: #CIntType put: (CScalarCType cObjectType: CInt). Smalltalk at: #CUIntType put: (CScalarCType cObjectType: CUInt). Smalltalk at: #CSmalltalkType put: (CScalarCType cObjectType: CSmalltalk). Smalltalk at: #CFloatType put: (CScalarCType cObjectType: CFloat). Smalltalk at: #CDoubleType put: (CScalarCType cObjectType: CDouble). Smalltalk at: #CLongDoubleType put: (CScalarCType cObjectType: CLongDouble). Smalltalk at: #CStringType put: (CStringCType cObjectType: CString). Smalltalk at: #CByteType put: (CScalarCType cObjectType: CByte). Smalltalk at: #CBooleanType put: (CScalarCType cObjectType: CBoolean). TypeMap := (IdentityDictionary new) at: #long put: CLongType; at: #uLong put: CULongType; at: #longLong put: CLongLongType; at: #uLongLong put: CULongLongType; at: #byte put: CByteType; at: #char put: CCharType; at: #uChar put: CUCharType; at: #uchar put: CUCharType; at: #short put: CShortType; at: #uShort put: CUShortType; at: #ushort put: CUShortType; at: #int put: CIntType; at: #uInt put: CUIntType; at: #uint put: CUIntType; at: #float put: CFloatType; at: #double put: CDoubleType; at: #longDouble put: CLongDoubleType; at: #string put: CStringType; at: #smalltalk put: CSmalltalkType; yourself ] CType class >> cObjectBinding: aCObjectSubclassBinding [ "Create a new CType for the given subclass of CObject" ^self basicNew init: aCObjectSubclassBinding ] CType class >> cObjectType: aCObjectSubclass [ "Create a new CType for the given subclass of CObject" ^self cObjectBinding: aCObjectSubclass binding ] CType class >> from: type [ "Private - Pass the size, alignment, and description of CType for aBlock, given the field description in `type' (the second element of each pair)." | typeInfo typeString | type class == Array ifTrue: [^self computeAggregateType: type]. "must be a type name, either built in or struct, either a Symbol or an Association" type isSymbol ifFalse: [^self cObjectBinding: type]. ^TypeMap at: type ifAbsent: [(Namespace current at: type) type] ] CType class >> computeAggregateType: type [ "Private - Called by from: for pointers/arrays. Format of type: (#array #int 3) or (#ptr #{FooStruct}) " | structureType | structureType := type at: 1. structureType == #array ifTrue: [^CArrayCType from: type]. structureType == #ptr ifTrue: [^CPtrCType from: type] ] = anObject [ "Return whether the receiver and anObject are equal." ^self class == anObject class and: [ self cObjectType = anObject cObjectType ] ] hash [ "Return a hash code for the receiver." ^self class hash bitXor: self cObjectType hash ] gcNew [ "Allocate a new CObject with the type (class) identified by the receiver. The object is movable in memory, but on the other hand it is garbage-collected automatically." ^CObject gcAlloc: self sizeof type: self ] gcNew: anInteger [ "Allocate a new CObject with room for anInteger C object of the type (class) identified by the receiver. The object is movable in memory, but on the other hand it is garbage-collected automatically." ^CObject gcAlloc: self sizeof * anInteger type: self ] new [ "Allocate a new CObject with the type (class) identified by the receiver. It is the caller's responsibility to free the memory allocated for it." ^CObject alloc: self sizeof type: self ] new: anInteger [ "Allocate a new CObject with room for anInteger C objects of the type (class) identified by the receiver. It is the caller's responsibility to free the memory allocated for it." ^CObject alloc: self sizeof * anInteger type: self ] address: cObjOrInt [ "Create a new CObject with the type (class) identified by the receiver, pointing to the given address (identified by an Integer or CObject)." ^(self cObjectType basicNew: 1) type: self; address: (cObjOrInt isInteger ifTrue: [cObjOrInt] ifFalse: [cObjOrInt address]); yourself ] arrayType: size [ "Answer a CArrayCType which represents an array with the given size of CObjects whose type is in turn represented by the receiver" ^CArrayCType elementType: self numberOfElements: size ] ptrType [ "Answer a CPtrCType which represents a pointer to CObjects whose type is in turn represented by the receiver" ^CPtrCType elementType: self ] cObjectType [ "Answer the CObject subclass whose instance is created when new is sent to the receiver" ^cObjectType value ] sizeof [ "Answer the size of the receiver's instances" ^self cObjectType sizeof ] alignof [ "Answer the size of the receiver's instances" ^self cObjectType alignof ] valueType [ "valueType is used as a means to communicate to the interpreter the underlying type of the data. For anything but scalars, it's just 'self'" ^self ] storeOn: aStream [ "Store Smalltalk code that compiles to the receiver" aStream nextPut: $(; print: self class; nextPutAll: ' cObjectType: '; print: self cObjectType; nextPut: $) ] init: aCObjectClass [ "Initialize the receiver's instance variablers" cObjectType := aCObjectClass ] ] CType subclass: CScalarCType [ storeOn: aStream [ "Store Smalltalk code that compiles to the receiver" aStream print: self cObjectType; nextPutAll: 'Type' ] valueType [ "valueType is used as a means to communicate to the interpreter the underlying type of the data. For scalars, it is supplied by the CObject subclass." ^self cObjectType cObjStoredType ] ] CScalarCType subclass: CStringCType [ elementType [ "Answer the type of the elements in the receiver's instances" ^CCharType ] ] CType subclass: CPtrCType [ | elementType | CPtrCType class >> from: type [ "Private - Called by computeAggregateType: for pointers" | subType typeInfo | subType := type at: 2. typeInfo := CType from: subType. ^self elementType: typeInfo ] CPtrCType class >> elementType: aCType [ "Answer a new instance of CPtrCType that maps pointers to the given CType" ^(self cObjectType: CPtr) elementType: aCType; yourself ] = anObject [ "Return whether the receiver and anObject are equal." ^super = anObject and: [self elementType = anObject elementType] ] hash [ "Return a hash code for the receiver." ^super hash bitXor: self elementType hash ] elementType [ "Answer the type of the elements in the receiver's instances" ^elementType ] storeOn: aStream [ aStream nextPutAll: '(CPtrCType elementType: '; store: self elementType; nextPut: $) ] elementType: aCType [ "Initialize the receiver's instance variables" elementType := aCType ] ] CPtrCType subclass: CArrayCType [ | numElements | CArrayCType class >> from: type [ "Private - Called by CType>>from: for arrays" | numElts elementType typeInfo | elementType := type at: 2. numElts := type at: 3. typeInfo := CType from: elementType. ^self elementType: typeInfo numberOfElements: numElts ] CArrayCType class >> elementType: aCType [ self shouldNotImplement ] CArrayCType class >> elementType: aCType numberOfElements: anInteger [ "Answer a new instance of CPtrCType that maps an array whose elements are of the given CType, and whose size is exactly anInteger elements (of course, anInteger only matters for allocation, not for access, since no out-of-bounds protection is provided for C objects)." ^(self cObjectType: CArray) elementType: aCType; numberOfElements: anInteger; yourself ] = anObject [ "Return whether the receiver and anObject are equal." ^super = anObject and: [ self numberOfElements = anObject numberOfElements] ] hash [ "Return a hash code for the receiver." ^super hash bitXor: self numberOfElements hash ] storeOn: aStream [ "As with super." aStream nextPutAll: '(CArrayCType elementType: '; store: self elementType; nextPutAll: ' numberOfElements: '; store: numElements asInteger; nextPut: $) ] sizeof [ "Answer the size of the receiver's instances" ^elementType sizeof * numElements ] alignof [ "Answer the alignment of the receiver's instances" ^elementType alignof ] numberOfElements [ "Answer the number of elements in the receiver's instances" ^numElements ] numberOfElements: anInteger [ "Initialize the receiver's instance variables" numElements := anInteger ] ] Eval [ CType initialize ] smalltalk-3.2.5/kernel/SharedQueue.st0000644000175000017500000000561512123404352014474 00000000000000"====================================================================== | | SharedQueue Method Definitions | | ======================================================================" "====================================================================== | | Copyright 1988,92,94,95,99,2000,2001,2002 | Free Software Foundation, Inc. | Written by Steve Byrne. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" Object subclass: SharedQueue [ | queueSem valueReady queue | SharedQueue class >> new [ "Create a new instance of the receiver" ^self basicNew init: (OrderedCollection new: 10) ] SharedQueue class >> sortBlock: sortBlock [ "Create a new instance of the receiver which implements a priority queue with the given sort block" ^self basicNew init: (SortedCollection sortBlock: sortBlock) ] isEmpty [ "Answer whether there is an object on the queue" ^queue isEmpty ] next [ "Wait for an object to be on the queue, then remove it and answer it" | result | valueReady wait. queueSem critical: [result := queue removeFirst]. ^result ] nextPut: value [ "Put value on the queue and answer it" queueSem critical: [queue add: value]. valueReady signal. ^value ] peek [ "Wait for an object to be on the queue if necessary, then answer the same object that #next would answer without removing it." | result | valueReady wait. queueSem critical: [result := queue first]. valueReady signal. ^result ] init: aCollection [ queue := aCollection. valueReady := Semaphore new. queueSem := Semaphore forMutualExclusion ] ] smalltalk-3.2.5/kernel/ObjMemory.st0000644000175000017500000004426112123404352014164 00000000000000"===================================================================== | | ObjectMemory method definitions | | ======================================================================" "====================================================================== | | Copyright 2001, 2002, 2003, 2005, 2006, 2008, 2009 | Free Software Foundation, Inc. | Written by Paolo Bonzini. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" Object subclass: ObjectMemory [ | bytesPerOOP bytesPerOTE edenSize survSpaceSize oldSpaceSize fixedSpaceSize edenUsedBytes survSpaceUsedBytes oldSpaceUsedBytes fixedSpaceUsedBytes rememberedTableEntries numScavenges numGlobalGCs numCompactions numGrowths numOldOOPs numFixedOOPs numWeakOOPs numOTEs numFreeOTEs timeBetweenScavenges timeBetweenGlobalGCs timeBetweenGrowths timeToScavenge timeToCollect timeToCompact reclaimedBytesPerScavenge tenuredBytesPerScavenge reclaimedBytesPerGlobalGC reclaimedPercentPerScavenge allocFailures allocMatches allocSplits allocProbes | ObjectMemory class >> changed: aSymbol [ | sema prio | prio := aSymbol == #returnFromSnapshot ifTrue: [Processor highIOPriority] ifFalse: [Processor userSchedulingPriority]. Processor activePriority < prio ifTrue: [ sema := Semaphore new. "Ensure that modules and libraries are initialized before anything else happens." [DLD update: aSymbol. super changed: aSymbol. sema signal] forkAt: prio. sema wait] ifFalse: [ DLD update: aSymbol. super changed: aSymbol]. "Before quitting, wait until all processes are done." aSymbol == #aboutToQuit ifTrue: [ Processor activeProcess priority: Processor idlePriority. Processor yield]. ] ObjectMemory class >> initialize [ "Initialize the globals" "This method is called after all the kernel Smalltalk classes have been loaded. It generally performs any initializations that might depend on the full Smalltalk class hierarchy being defined. After this is file is loaded, some 'advanced' class definitions are loaded (CFuncs, Autoload, exception handling, ...) and then the binary image is saved." Object initialize. Class initialize. Fraction initialize. LargeInteger initialize. Date initialize. Time initialize. FileDescriptor initialize. Namespace initialize. Processor initialize. SystemDictionary initialize. self changed: #returnFromSnapshot ] ObjectMemory class >> current [ "Return a snapshot of the VM's memory management statistics." ^self new update ] ObjectMemory class >> addressOfOOP: anObject [ "Returns the address of the OOP (object table slot) for anObject. The address is an Integer and will not change over time (i.e. is immune from garbage collector action) except if the virtual machine is stopped and restarted." SystemExceptions InvalidArgument signalOn: anObject reason: 'Cannot extract address of an immediate OOP' ] ObjectMemory class >> addressOf: anObject [ "Returns the address of the actual object that anObject references. Note that, with the exception of fixed objects this address is only valid until the next garbage collection; thus it's pretty risky to count on the address returned by this method for very long." SystemExceptions InvalidArgument signalOn: anObject reason: 'Cannot extract address of an immediate OOP' ] ObjectMemory class >> scavenge [ "Force a minor garbage collection" ^self primitiveFailed ] ObjectMemory class >> globalGarbageCollect [ "Force a full garbage collection" ^self primitiveFailed ] ObjectMemory class >> compact [ "Force a full garbage collection, including compaction of oldspace" ^self primitiveFailed ] ObjectMemory class >> incrementalGCStep [ "Do a step in the incremental garbage collection." ^self primitiveFailed ] ObjectMemory class >> finishIncrementalGC [ "Do a step in the incremental garbage collection." ^self primitiveFailed ] ObjectMemory class >> abort [ "Quit the Smalltalk environment, dumping core." ] ObjectMemory class >> quit [ "Quit the Smalltalk environment. Whether files are closed and other similar cleanup occurs depends on the platform" self quit: 0 ] ObjectMemory class >> quit: exitStatus [ "Quit the Smalltalk environment, passing the exitStatus integer to the OS. Files are closed and other similar cleanups occur." SystemExceptions.WrongClass signalOn: exitStatus mustBe: SmallInteger ] ObjectMemory class >> smoothingFactor [ "Answer the factor (between 0 and 1) used to smooth the statistics provided by the virtual machine about memory handling. 0 disables updating the averages, 1 disables the smoothing (the statistics return the last value)." ^self primitiveFailed ] ObjectMemory class >> smoothingFactor: rate [ "Set the factor (between 0 and 1) used to smooth the statistics provided by the virtual machine about memory handling. 0 disables updating the averages, 1 disables the smoothing (the statistics return the last value)." rate class == FloatD ifTrue: [SystemExceptions.ArgumentOutOfRange signalOn: rate mustBeBetween: 0 and: 1] ifFalse: [^self spaceGrowRate: rate asFloatD] ] ObjectMemory class >> spaceGrowRate [ "Answer the rate with which the amount of memory used by the system grows" ^self primitiveFailed ] ObjectMemory class >> spaceGrowRate: rate [ "Set the rate with which the amount of memory used by the system grows" rate class == FloatD ifTrue: [SystemExceptions.ArgumentOutOfRange signalOn: rate mustBeBetween: 0.01 and: 500.0] ifFalse: [^self spaceGrowRate: rate asFloatD] ] ObjectMemory class >> bigObjectThreshold [ "Answer the smallest size for objects that are allocated outside the main heap in the hope of providing more locality of reference between small objects." ^self primitiveFailed ] ObjectMemory class >> bigObjectThreshold: bytes [ "Set the smallest size for objects that are allocated outside the main heap in the hope of providing more locality of reference between small objects. bytes must be a positive SmallInteger." bytes isSmallInteger ifTrue: [SystemExceptions.ArgumentOutOfRange signalOn: bytes mustBeBetween: 0 and: SmallInteger largest] ifFalse: [SystemExceptions.WrongClass signalOn: bytes mustBe: SmallInteger] ] ObjectMemory class >> growThresholdPercent [ "Answer the percentage of the amount of memory used by the system grows which has to be full for the system to allocate more memory" ^self primitiveFailed ] ObjectMemory class >> growThresholdPercent: growPercent [ "Set the percentage of the amount of memory used by the system grows which has to be full for the system to allocate more memory" growPercent class == FloatD ifTrue: [SystemExceptions.ArgumentOutOfRange signalOn: growPercent mustBeBetween: 0.01 and: 100.0] ifFalse: [^self growThresholdPercent: growPercent asFloatD] ] ObjectMemory class >> growTo: numBytes [ "Grow the amount of memory used by the system grows to numBytes." ^self primitiveFailed ] ObjectMemory class >> primSnapshot: aString [ "Save an image on the aString file" ^aString isString ifFalse: [SystemExceptions.WrongClass signalOn: aString mustBe: String] ifTrue: [File checkError] ] ObjectMemory class >> snapshot [ "Save a snapshot on the image file that was loaded on startup." ^self primSnapshot: File image asString ] ObjectMemory class >> snapshot: aString [ "Save an image on the aString file" ^self primSnapshot: aString asString ] ObjectMemory class >> gcMessage [ "Answer whether messages indicating that garbage collection is taking place are printed on stdout" ^Smalltalk getTraceFlag: 3 ] ObjectMemory class >> gcMessage: aBoolean [ "Set whether messages indicating that garbage collection is taking place are printed on stdout" ^Smalltalk setTraceFlag: 3 to: aBoolean ] bytesPerOOP [ "Answer the number of bytes that is taken by an ordinary object pointer (in practice, a field such as a named instance variable)." ^bytesPerOOP ] bytesPerOTE [ "Answer the number of bytes that is taken by an object table entry (in practice, the overhead incurred by every object in the system, with the sole exception of SmallIntegers)." ^bytesPerOTE ] edenSize [ "Answer the number of bytes in the `eden' area of the young generation (in practice, the number of allocated bytes between two scavenges)." ^edenSize ] survSpaceSize [ "Answer the number of bytes in the `survivor' area of the young generation (the area to which young objects are relocated during scavenges)." ^survSpaceSize ] fixedSpaceSize [ "Answer the number of bytes in the special heap devoted to objects that the garbage collector cannot move around in memory." ^fixedSpaceSize ] oldSpaceSize [ "Answer the number of bytes in the old generation." ^oldSpaceSize ] edenUsedBytes [ "Answer the number of bytes that are currently filled in the `eden' area of the young generation." ^edenUsedBytes ] survSpaceUsedBytes [ "Answer the number of bytes that are currently filled in the `survivor' area of the young generation." ^survSpaceUsedBytes ] oldSpaceUsedBytes [ "Answer the number of bytes that are currently filled in the old generation." ^oldSpaceUsedBytes ] fixedSpaceUsedBytes [ "Answer the number of bytes that are currently filled in the special heap devoted to objects that the garbage collector cannot move around in memory." ^oldSpaceUsedBytes ] numScavenges [ "Answer the number of scavenges (fast collections of the young generation) that happened since the VM was started." ^numScavenges ] numGlobalGCs [ "Answer the number of global garbage collections (collection of the entire heap) that happened since the VM was started." ^numGlobalGCs ] numCompactions [ "Answer the number of oldspace compactions that happened since the VM was started." ^numCompactions ] numGrowths [ "Answer the number of times that oldspace was grown since the VM was started." ^numGrowths ] numOldOOPs [ "Answer the number of objects that reside in the old generation." ^numOldOOPs ] numFixedOOPs [ "Answer the number of objects that the garbage collector cannot move around in memory." ^numFixedOOPs ] numWeakOOPs [ "Answer the number of weak objects that the garbage collector is currently tracking." ^numWeakOOPs ] numOTEs [ "Answer the number of entries that are currently allocated for the object table." ^numOTEs ] numFreeOTEs [ "Answer the number of entries that are currently free in the object table." ^numFreeOTEs ] timeBetweenScavenges [ "Answer the average number of milliseconds between two scavenges (fast collections of the young generation)." ^timeBetweenScavenges ] timeBetweenGlobalGCs [ "Answer the average number of milliseconds between two global garbage collections." ^timeBetweenGlobalGCs ] timeBetweenGrowths [ "Answer the average number of milliseconds between decisions to grow the heap." ^timeBetweenGrowths ] timeToScavenge [ "Answer the average number of milliseconds that a scavenge takes (fast collections of the young generation)." ^timeToScavenge ] timeToCollect [ "Answer the average number of milliseconds that a global garbage collection takes." ^timeToCollect ] timeToCompact [ "Answer the average number of milliseconds that compacting the heap takes. This the same time that is taken by growing the heap." ^timeToCompact ] reclaimedBytesPerScavenge [ "Answer the average number of bytes that are found to be garbage during a scavenge." ^reclaimedBytesPerScavenge ] tenuredBytesPerScavenge [ "Answer the average number of bytes that are promoted to oldspace during a scavenge." ^tenuredBytesPerScavenge ] reclaimedBytesPerGlobalGC [ "Answer the average number of bytes that are found to be garbage during a global garbage collections." ^reclaimedBytesPerGlobalGC ] reclaimedPercentPerScavenge [ "Answer the average percentage of allocated bytes that are found to be garbage during a scavenge. If this number falls below 60-70 you should definitely increment the size of the eden, because you risk that scavenging is eating a considerable fraction of your execution time; do the measurement on a restarted image, so that the extra tenuring incurred when creating long-lived objects such as classes or methods is not considered." ^reclaimedPercentPerScavenge ] allocFailures [ "Answer the number of times that the old-space allocator found no block that was at least as big as requested, and had to ask the operating system for more memory." ^allocFailures ] allocMatches [ "Answer the number of times that the old-space allocator found a block that was exactly as big as requested." ^allocMatches ] allocSplits [ "Answer the number of times that the old-space allocator could not find a block that was exactly as big as requested, and had to split a larger free block in two parts." ^allocSplits ] allocProbes [ "Answer the number of free blocks that the old-space allocator had to examine so far to allocate all the objects that are in old-space" ^allocProbes ] scavengesBeforeTenuring [ "Answer the number of scavenges that an object must on average survive before being promoted to oldspace; this is however only an estimate because objects that are reachable from oldspace have a higher probability to be tenured soon, while objects that are only reachable from thisContext have a lower probability to be tenured. Anyway, if this number falls below 2-3 you should definitely increment the size of eden and/or of survivor space, because you are tenuring too often and relying too much on global garbage collection to keep your heap clean; do the measurement on a restarted image, so that the extra tenuring incurred when creating long-lived objects such as classes or methods is not considered." ^self survSpaceSize / self tenuredBytesPerScavenge ] update [ "Update the values in the object to the current state of the VM." self primitiveFailed ] ] Eval [ ObjectMemory initialize ] smalltalk-3.2.5/kernel/Metaclass.st0000644000175000017500000003457412130343734014207 00000000000000"====================================================================== | | Metaclass Method Definitions | | ======================================================================" "====================================================================== | | Copyright 1988,92,94,95,99,2000,2001,2002,2005,2007,2008,2009 | Free Software Foundation, Inc. | Written by Steve Byrne, Brad Diller and Paolo Bonzini. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" ClassDescription subclass: Metaclass [ | instanceClass | Metaclass class >> subclassOf: superMeta [ "Answer a new metaclass representing a subclass of superMeta" | newMeta | newMeta := self new. newMeta superclass: superMeta. superMeta addSubclass: newMeta. newMeta initMetaclass: superMeta. ^newMeta ] addClassVarName: aString [ "Add a class variable with the given name to the class pool dictionary" ^self instanceClass addClassVarName: aString ] removeClassVarName: aString [ "Removes the class variable from the class, error if not present, or still in use." ^self instanceClass removeClassVarName: aString ] name [ "Answer the class name - it has none, actually" ^nil ] allSharedPoolDictionariesDo: aBlock [ "Answer the shared pools visible from methods in the metaclass, in the correct search order." self asClass allSharedPoolDictionariesDo: aBlock ] category [ "Answer the class category" ^self asClass category ] comment [ "Answer the class comment" ^self asClass comment ] environment [ "Answer the namespace in which the receiver is implemented" ^self asClass environment ] classPool [ "Answer the class pool dictionary" ^self instanceClass classPool ] classVarNames [ "Answer the names of the variables in the class pool dictionary" ^self instanceClass classVarNames ] debuggerClass [ "Answer the debugger class that was set in the instance class" ^self instanceClass debuggerClass ] allClassVarNames [ "Answer the names of the variables in the receiver's class pool dictionary and in each of the superclasses' class pool dictionaries" ^self instanceClass allClassVarNames ] addSharedPool: aDictionary [ "Add the given shared pool to the list of the class' pool dictionaries" ^self instanceClass addSharedPool: aDictionary ] removeSharedPool: aDictionary [ "Remove the given dictionary to the list of the class' pool dictionaries" ^self instanceClass removeSharedPool: aDictionary ] sharedPools [ "Return the names of the shared pools defined by the class" ^self instanceClass sharedPools ] allSharedPools [ "Return the names of the shared pools defined by the class and any of its superclasses" ^self instanceClass allSharedPools ] pragmaHandlerFor: aSymbol [ "Answer the (possibly inherited) registered handler for pragma aSymbol, or nil if not found." ^self instanceClass pragmaHandlerFor: aSymbol ] name: className environment: aNamespace subclassOf: theSuperclass [ "Private - create a full featured class and install it, or change the superclass or shape of an existing one; instance variable names, class variable names and pool dictionaries are left untouched." | aClass variableArray inheritedShape | variableArray := theSuperclass notNil ifTrue: [theSuperclass allInstVarNames] ifFalse: [#()]. "Look for an existing metaclass" aClass := aNamespace hereAt: className ifAbsent: [nil]. aClass isNil ifTrue: [^self newMeta: className environment: aNamespace subclassOf: theSuperclass instanceVariableArray: variableArray shape: (theSuperclass isNil ifTrue: [ nil ] ifFalse: [ theSuperclass inheritShape ifTrue: [ #inherit ] ]) classPool: BindingDictionary new poolDictionaries: #() category: nil]. variableArray := variableArray , aClass instVarNames. ^self name: className environment: aNamespace subclassOf: theSuperclass instanceVariableArray: variableArray shape: aClass shape classPool: aClass classPool poolDictionaries: aClass sharedPoolDictionaries category: aClass category ] name: newName environment: aNamespace subclassOf: theSuperclass instanceVariableNames: stringOfInstVarNames shape: shape classVariableNames: stringOfClassVarNames poolDictionaries: stringOfPoolNames category: categoryName [ "Private - parse the instance and class variables, and the pool dictionaries, then create the class." "Inherit instance variables from parent" | variableArray classVarDict sharedPoolNames | variableArray := self parseInstanceVariableString: stringOfInstVarNames. variableArray := theSuperclass notNil ifTrue: [theSuperclass allInstVarNames , variableArray] ifFalse: [variableArray]. classVarDict := self parse: stringOfClassVarNames toDictionary: BindingDictionary new. sharedPoolNames := self parsePools: stringOfPoolNames in: aNamespace. ^self name: newName asSymbol environment: aNamespace subclassOf: theSuperclass instanceVariableArray: variableArray shape: shape classPool: classVarDict poolDictionaries: sharedPoolNames category: categoryName ] name: className environment: aNamespace subclassOf: newSuperclass instanceVariableArray: variableArray shape: shape classPool: classVarDict poolDictionaries: sharedPoolNames category: categoryName [ "Private - create a full featured class and install it, or change an existing one" | aClass realShape needToRecompileMetaclasses needToRecompileClasses | realShape := shape == #word ifTrue: [CSymbols.CLongSize = 4 ifTrue: [#uint] ifFalse: [#uint64]] ifFalse: [shape]. "Look for an existing metaclass" aClass := aNamespace hereAt: className ifAbsent: [nil]. aClass isNil ifTrue: [^self newMeta: className environment: aNamespace subclassOf: newSuperclass instanceVariableArray: variableArray shape: realShape classPool: classVarDict poolDictionaries: sharedPoolNames category: categoryName]. aClass isVariable & realShape notNil ifTrue: [aClass shape == realShape ifFalse: [SystemExceptions.MutationError signal: 'Cannot change shape of variable class']]. newSuperclass isUntrusted & self class isUntrusted not ifTrue: [SystemExceptions.MutationError signal: 'Cannot move trusted class below untrusted superclass']. needToRecompileMetaclasses := false. aClass classPool isNil ifTrue: [aClass setClassVariables: classVarDict] ifFalse: [classVarDict keysDo: [:key | (aClass classPool includesKey: key) ifFalse: [aClass addClassVarName: key]]. aClass classPool keys do: [:aKey | (classVarDict includesKey: aKey) ifFalse: [aClass removeClassVarName: aKey. needToRecompileMetaclasses := true]]]. "If instance or indexed variables change, update instance variables and instance spec of the class and all its subclasses" (needToRecompileClasses := variableArray ~= aClass allInstVarNames | needToRecompileMetaclasses) | (aClass shape ~~ realShape) ifTrue: [aClass instanceCount > 0 ifTrue: [ObjectMemory globalGarbageCollect]. aClass updateInstanceVars: variableArray superclass: newSuperclass shape: realShape]. "Now add/remove pool dictionaries. FIXME: They may affect name binding, so we should probably recompile everything if they change." aClass sharedPoolDictionaries isEmpty ifTrue: [aClass setSharedPools: sharedPoolNames] ifFalse: [sharedPoolNames do: [:dict | (aClass sharedPoolDictionaries includes: dict) ifFalse: [aClass addSharedPool: dict]]. aClass sharedPoolDictionaries copy do: [:dict | (sharedPoolNames includes: dict) ifFalse: [aClass removeSharedPool: dict. needToRecompileMetaclasses := true]]]. aClass superclass ~~ newSuperclass ifTrue: ["Mutate the class if the set of class-instance variables changes." self superclass allInstVarNames ~= newSuperclass class allInstVarNames ifTrue: [aClass class updateInstanceVars: newSuperclass class allInstVarNames, aClass class instVarNames superclass: newSuperclass class shape: aClass class shape]. "Fix references between classes..." aClass superclass removeSubclass: aClass. newSuperclass addSubclass: aClass. aClass superclass: newSuperclass. needToRecompileClasses := true. "...and between metaclasses..." self superclass removeSubclass: self. newSuperclass class addSubclass: self. self superclass: newSuperclass class. needToRecompileMetaclasses := true]. aClass category: categoryName. "Please note that I need to recompile the classes in this sequence; otherwise, the same error is propagated to each selector which is compiled after an error is detected even though there are no further compilation errors. Apparently, there is a bug in the primitive #primCompile:. This can be cleaned up later" needToRecompileClasses | needToRecompileMetaclasses ifTrue: [aClass compileAll. needToRecompileMetaclasses ifTrue: [aClass class compileAll]. aClass compileAllSubclasses. needToRecompileMetaclasses ifTrue: [aClass class compileAllSubclasses]]. Behavior flushCache. ^aClass ] newMeta: className environment: aNamespace subclassOf: theSuperclass instanceVariableArray: arrayOfInstVarNames shape: shape classPool: classVarDict poolDictionaries: sharedPoolNames category: categoryName [ "Private - create a full featured class and install it" | aClass | aClass := self new. classVarDict environment: aClass. instanceClass := aClass. aNamespace at: className put: aClass. theSuperclass isNil ifFalse: [theSuperclass addSubclass: aClass]. Behavior flushCache. ^aClass superclass: theSuperclass; setName: className; setEnvironment: aNamespace; setInstanceVariables: arrayOfInstVarNames; setInstanceSpec: shape instVars: arrayOfInstVarNames size; setClassVariables: classVarDict; setSharedPools: sharedPoolNames; makeUntrusted: theSuperclass isUntrusted; category: categoryName; yourself ] primaryInstance [ "Answer the only instance of the metaclass - present for compatibility" ^instanceClass ] soleInstance [ "Answer the only instance of the metaclass - present for compatibility" ^instanceClass ] instanceClass [ "Answer the only instance of the metaclass" ^instanceClass ] nameIn: aNamespace [ "Answer the class name when the class is referenced from aNamespace." ^self instanceClass nameIn: aNamespace ] printOn: aStream in: aNamespace [ "Print on aStream the class name when the class is referenced from aNamespace." instanceClass printOn: aStream in: aNamespace. aStream nextPutAll: ' class' ] printOn: aStream [ "Print a represention of the receiver on aStream" instanceClass printOn: aStream. aStream nextPutAll: ' class' ] storeOn: aStream [ "Store Smalltalk code compiling to the receiver on aStream" instanceClass storeOn: aStream. aStream nextPutAll: ' class' ] initMetaclass: theSuperclass [ instanceVariables := theSuperclass allInstVarNames. instanceSpec := theSuperclass instanceSpec ] parsePools: aString in: aNamespace [ | tokens | tokens := aString subStrings asArray. ^tokens collect: [:poolName | (poolName substrings: $.) inject: aNamespace into: [:namespace :key | self validateIdentifier: key. namespace at: key asGlobalKey ifAbsent: [SystemExceptions.NotFound signalOn: poolName what: 'pool']]] ] parse: aString toDictionary: dict [ | tokenArray | tokenArray := self parseVariableString: aString. tokenArray do: [:element | dict at: element asSymbol put: nil]. ^dict ] growClassInstance [ | newClass numInstVars | newClass := self new. numInstVars := self instSize. 1 to: numInstVars - 1 do: [:i | newClass instVarAt: i put: (instanceClass instVarAt: i)]. instanceClass become: newClass ] asClass [ ^instanceClass ] isMetaclass [ ^true ] fileOutOn: aFileStream [ "File out complete class description: class definition, class and instance methods" instanceClass fileOutOn: aFileStream ] ] smalltalk-3.2.5/kernel/Bag.st0000644000175000017500000001404512123404352012747 00000000000000"====================================================================== | | Bag Method Definitions | | ======================================================================" "====================================================================== | | Copyright 1988,92,94,95,99,2000,2001,2002,2008 | Free Software Foundation, Inc. | Written by Steve Byrne. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" Collection subclass: Bag [ | contents | Bag class >> new [ "Answer a new instance of the receiver" ^self basicNew initContents: 31 ] Bag class >> new: size [ "Answer a new instance of the receiver, with space for size distinct objects" ^self basicNew initContents: (7 max: size) ] add: newObject withOccurrences: anInteger [ "If anInteger > 0, add anInteger occurrences of newObject to the receiver. If anInteger < 0, remove them. Answer newObject. Fail if newObject is nil." | newOccurrences | newObject isNil ifTrue: [SystemExceptions.InvalidArgument signalOn: newObject reason: 'bag elements cannot be nil']. newOccurrences := contents at: newObject put: (self occurrencesOf: newObject) + anInteger. newOccurrences <= 0 ifTrue: [contents removeKey: newObject]. ^newObject ] add: newObject [ "Add an occurrence of newObject to the receiver. Answer newObject. Fail if newObject is nil." self add: newObject withOccurrences: 1. ^newObject ] remove: oldObject ifAbsent: anExceptionBlock [ "Remove oldObject from the collection and return it. If can't be found, answer instead the result of evaluationg anExceptionBlock" "Since we're using a dictionary, we need decrement the value until it's zero, in which case we can then remove the object from the dictionary" | count | count := self occurrencesOf: oldObject. count = 0 ifTrue: [^anExceptionBlock value]. count = 1 ifTrue: [contents removeKey: oldObject] ifFalse: [contents at: oldObject put: count - 1]. ^oldObject ] sortedByCount [ "Answer a collection of counts with elements, sorted by decreasing count." | counts | counts := SortedCollection sortBlock: [:x :y | x >= y]. contents keysAndValuesDo: [:key :count | counts add: count -> key]. ^counts asArray ] occurrencesOf: anObject [ "Answer the number of occurrences of anObject found in the receiver" ^contents at: anObject ifAbsent: [0] ] includes: anObject [ "Answer whether we include anObject" ^contents includesKey: anObject ] size [ "Answer the total number of objects found in the receiver" | count | count := 0. contents do: [:element | count := count + element]. ^count ] hash [ "Answer an hash value for the receiver" ^contents hash ] = aBag [ "Answer whether the receiver and aBag contain the same objects" self class == aBag class ifFalse: [^false]. ^contents = aBag contents ] asSet [ "Answer a set with the elements of the receiver" ^contents keys ] do: aBlock [ "Evaluate the block for all members in the collection." "For Bags, we need to go through the contents dictionary, and perform the block for as many occurrences of the objects as there are." contents keysAndValuesDo: [:key :count | count timesRepeat: [aBlock value: key]] ] storeOn: aStream [ "Put on aStream some Smalltalk code compiling to the receiver" | noElements | aStream nextPut: $(; nextPutAll: self class storeString; nextPutAll: ' new'. noElements := true. contents keysAndValuesDo: [:key :count | aStream nextPutAll: ' add: '; store: key; nextPutAll: ' withOccurrences: '; store: count; nextPut: $;. noElements := false]. noElements ifFalse: [aStream nextPutAll: '; yourself']. aStream nextPut: $) ] printOn: aStream [ "Put on aStream a representation of the receiver" aStream nextPutAll: self class storeString; nextPut: $(. contents keysAndValuesDo: [:key :count | aStream print: key; nextPut: $:; print: count; space]. aStream nextPut: $) ] dictionaryClass [ ^LookupTable ] initContents: size [ contents := self dictionaryClass new: size ] valuesAndCounts [ "Answer a dictionary whose keys are distinct elements of the receiver and whose values are the number of occurrences of each element." ^contents copy ] contents [ ^contents ] ] smalltalk-3.2.5/kernel/SysExcept.st0000644000175000017500000007377512130343734014230 00000000000000"====================================================================== | | ANSI exception handling classes | | ======================================================================" "====================================================================== | | Copyright 2000, 2001, 2002, 2007, 2008, 2009 Free Software Foundation, Inc. | Written by Paolo Bonzini. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" Exception subclass: Error [ description [ "Answer a textual description of the exception." ^'An exceptional condition has occurred, and has prevented normal continuation of processing.' ] isResumable [ "Answer false. Error exceptions are by default unresumable; subclasses can override this method if desired." ^false ] ] Exception subclass: Notification [ description [ "Answer a textual description of the exception." ^'An exceptional condition has occurred, but it is not to be considered an error.' ] isResumable [ "Answer true. Notification exceptions are by default resumable." ^true ] defaultAction [ "Do the default action for notifications, which is to resume execution of the context which signaled the exception." self resume: nil ] ] Notification subclass: Warning [ description [ "Answer a textual description of the exception." ^'An exceptional condition has occurred. It is reported to the user even though it is not to be considered an error.' ] ] Exception subclass: Halt [ description [ "Answer a textual description of the exception." ^'#halt was sent.' ] isResumable [ "Answer true. #halt exceptions are by default resumable." ^true ] ] Error subclass: ArithmeticError [ description [ "Answer a textual description of the exception." ^'The program attempted to do an impossible arithmetic operation' ] isResumable [ "Answer true. Arithmetic exceptions are by default resumable." ^true ] ] Error subclass: MessageNotUnderstood [ | message receiver | message [ "Answer the message that wasn't understood" ^message ] receiver [ "Answer the object to whom the message send was directed" ^receiver ] message: aMessage receiver: anObject [ message := aMessage. receiver := anObject. self messageText: 'did not understand ' , message selector printString ] description [ "Answer a textual description of the exception." ^'The program sent a message which was not understood by the receiver.' ] isResumable [ "Answer true. #doesNotUnderstand: exceptions are by default resumable." ^true ] ] ArithmeticError subclass: ZeroDivide [ | dividend | ZeroDivide class >> dividend: aNumber [ "Create a new ZeroDivide object remembering that the dividend was aNumber." ^super new dividend: aNumber ] ZeroDivide class >> new [ "Create a new ZeroDivide object; the dividend is conventionally set to zero." ^super new dividend: 0 ] dividend [ "Answer the number that was being divided by zero" ^dividend ] dividend: aNumber [ dividend := aNumber ] description [ "Answer a textual description of the exception." ^'The program attempted to divide a number by zero' ] ] Namespace current: SystemExceptions [ Notification subclass: ProcessBeingTerminated [ | semaphore | ProcessBeingTerminated class >> initialize [ (UndefinedObject>>#'__terminate') makeReadOnly: false; descriptor: ((MethodInfo new: 1) methodClass: UndefinedObject; selector: #'__terminate'; at: 1 put: (Message selector: #exceptionHandlerSearch:reset: arguments: { [ :context :signal | (self handles: signal) ifTrue: [ signal onDoBlock: nil handlerBlock: [ :sig | thisContext environment continue: nil ] onDoContext: nil previousState: nil. #found ] ifFalse: [nil] ]. [ :context | ] }); yourself); makeReadOnly: true ] description [ "Answer a textual description of the exception." ^'the current process is being terminated' ] semaphore [ "If the process was waiting on a semaphore, answer it." ^semaphore ] semaphore: aSemaphore [ "If the process was waiting on a semaphore, answer it." semaphore := aSemaphore ] ] ] Namespace current: SystemExceptions [ Notification subclass: EndOfStream [ | stream | EndOfStream class >> signalOn: stream [ "Answer an exception reporting the parameter has reached its end." ^(self new) stream: stream; signal ] description [ "Answer a textual description of the exception." ^'end of stream reached' ] stream [ "Answer the stream whose end was reached." ^stream ] stream: anObject [ "Set the stream whose end was reached." stream := anObject ] ] ] Namespace current: SystemExceptions [ Error subclass: NotEnoughElements [ | remainingCount | NotEnoughElements class >> signalOn: remainingCount [ "Answer an exception reporting the parameter as invalid." ^(self new) remainingCount: remainingCount; signal ] description [ "Answer a textual description of the exception." ^'premature end of stream' ] messageText [ "Answer an exception's message text." ^'%1: %2 element(s) missing' % {self basicMessageText. self remainingCount} ] remainingCount [ "Answer the number of items that were to be read." ^remainingCount ] remainingCount: anObject [ "Set the number of items that were to be read." remainingCount := anObject ] ] ] Namespace current: SystemExceptions [ Error subclass: InvalidValue [ | value | InvalidValue class >> signalOn: value [ "Answer an exception reporting the parameter as invalid." ^(self new) value: value; signal ] InvalidValue class >> signalOn: value reason: reason [ "Answer an exception reporting `value' as invalid, for the given reason." ^(self new) value: value; signal: reason ] description [ "Answer a textual description of the exception." ^'unknown error' ] messageText [ "Answer an exception's message text." ^'Invalid value %1: %2' % {self value. self basicMessageText} ] value [ "Answer the object that was found to be invalid." ^value ] value: anObject [ "Set the object that was found to be invalid." value := anObject ] ] ] Namespace current: SystemExceptions [ InvalidValue subclass: InvalidState [ messageText [ "Answer an exception's message text." ^'%1 is in an invalid state: %2' % {self value. self basicMessageText} ] ] ] Namespace current: SystemExceptions [ InvalidValue subclass: NotIndexable [ description [ "Answer a textual description of the exception." ^'object not indexable' ] ] ] Namespace current: SystemExceptions [ InvalidValue subclass: ReadOnlyObject [ description [ "Answer a textual description of the exception." ^'object is read-only' ] ] ] Namespace current: SystemExceptions [ InvalidValue subclass: EmptyCollection [ description [ "Answer a textual description of the exception." ^'the collection is empty' ] ] ] Namespace current: SystemExceptions [ InvalidValue subclass: InvalidArgument [ messageText [ "Answer an exception's message text." ^'Invalid argument %1: %2' % {self value. self basicMessageText} ] ] ] Namespace current: SystemExceptions [ InvalidArgument subclass: AlreadyDefined [ description [ "Answer a description for the error" ^'symbol already defined' ] ] ] Namespace current: SystemExceptions [ InvalidArgument subclass: ArgumentOutOfRange [ | low high | ArgumentOutOfRange class >> signalOn: value mustBeBetween: low and: high [ "Raise the exception. The given value was not between low and high." | errorString | errorString := RegressionTesting ifTrue: ['argument out of range'] ifFalse: ['argument must be between ' , low printString , ' and ' , high printString]. ^(self new) value: value; low: low; high: high; signal: errorString ] description [ "Answer a textual description of the exception." ^'argument out of range' ] low [ "Answer the lowest value that was permitted." ^low ] low: aMagnitude [ "Set the lowest value that was permitted." low := aMagnitude ] high [ "Answer the highest value that was permitted." ^high ] high: aMagnitude [ "Set the highest value that was permitted." high := aMagnitude ] ] ] Namespace current: SystemExceptions [ ArgumentOutOfRange subclass: IndexOutOfRange [ | collection | IndexOutOfRange class >> signalOn: aCollection withIndex: value [ "The given index was out of range in aCollection." ^(self new) collection: aCollection; value: value; signal ] description [ "Answer a textual description of the exception." ^'index out of range' ] messageText [ "Answer an exception's message text." ^'Invalid index %1: %2' % {self value. self basicMessageText} ] collection [ "Answer the collection that triggered the error" ^collection ] collection: anObject [ "Set the collection that triggered the error" collection := anObject ] ] ] Namespace current: SystemExceptions [ InvalidArgument subclass: InvalidSize [ description [ "Answer a textual description of the exception." ^'invalid size' ] ] ] Namespace current: SystemExceptions [ InvalidArgument subclass: NotFound [ NotFound class >> signalOn: value what: aString [ "Raise an exception; aString specifies what was not found (a key, an object, a class, and so on)." ^(self new) value: value; signal: aString , ' not found' ] NotFound class >> signalOn: value reason: aString [ "Raise an exception: reason specifies the reason of the exception." ^(self new) value: value; signal: aString ] description [ "Answer a textual description of the exception." ^'not found' ] ] ] Namespace current: SystemExceptions [ InvalidValue subclass: WrongClass [ | validClasses | WrongClass class >> signalOn: anObject mustBe: aClassOrArray [ "Raise an exception. The given object should have been an instance of one of the classes indicated by aClassOrArray (which should be a single class or an array of classes). Whether instances of subclasses are allowed should be clear from the context, though in general (i.e. with the exception of a few system messages) they should be." (aClassOrArray isKindOf: Collection) ifFalse: [^self signalOn: anObject mustBe: {aClassOrArray binding}]. ^(self new) validClasses: aClassOrArray; value: anObject; signal ] description [ "Answer a textual description of the exception." ^'wrong argument type' ] messageText [ "Answer an exception's message text." self validClasses isNil ifTrue: [^'Invalid argument ' , self value printString]. ^'Invalid argument %1: must be %2' % {self value. self validClassesString} ] validClasses [ "Answer the list of classes whose instances would have been valid." ^validClasses ] validClassesString [ "Answer the list of classes whose instances would have been valid, formatted as a string." ^String streamContents: [:str | validClasses keysAndValuesDo: [:idx :classOrBinding | | name class | idx > 1 ifTrue: [idx = validClasses size ifFalse: [str nextPutAll: ', '] ifTrue: [str nextPutAll: ' or ']]. class := classOrBinding isClass ifTrue: [classOrBinding] ifFalse: [classOrBinding value]. name := class nameIn: Namespace current. name first isVowel ifTrue: [str nextPutAll: 'an '] ifFalse: [str nextPutAll: 'a ']. str nextPutAll: name]] ] validClasses: aCollection [ "Set the list of classes whose instances would have been valid." validClasses := aCollection ] ] ] Namespace current: SystemExceptions [ WrongClass subclass: MustBeBoolean [ MustBeBoolean class >> signalOn: anObject [ "Signal a new exception, with the bad value in question being anObject." ^self signalOn: anObject mustBe: #(#{Boolean}) ] ] ] Namespace current: SystemExceptions [ InvalidValue subclass: ProcessTerminated [ description [ "Answer a textual description of the exception." ^'process has/was already terminated' ] ] ] Namespace current: SystemExceptions [ InvalidValue subclass: InvalidProcessState [ description [ "Answer a textual description of the exception." ^'invalid operation for this process' ] ] ] Namespace current: SystemExceptions [ Error subclass: MutationError [ MutationError class >> new [ "Create an instance of the receiver, which you will be able to signal later." ^self basicNew initialize: nil ] description [ "Answer a textual description of the exception." ^'cannot mutate the class this way' ] ] ] Namespace current: SystemExceptions [ Error subclass: VMError [ description [ "Answer a textual description of the exception." ^'virtual machine error' ] ] ] Namespace current: SystemExceptions [ VMError subclass: SecurityError [ | failedPermission | SecurityError class >> signal: aPermission [ "Raise the exception, setting to aPermission the permission that was tested and failed." ^(self new) failedPermission: aPermission; signal ] description [ "Answer a textual description of the exception." ^'insecure operation in an untrusted context' ] failedPermission [ "Answer the permission that was tested and that failed." ^failedPermission ] failedPermission: anObject [ "Set which permission was tested and failed." failedPermission := anObject ] ] ] Namespace current: SystemExceptions [ VMError subclass: VerificationError [ description [ "Answer a textual description of the exception." ^'a method did not pass the bytecode verification process' ] ] ] Namespace current: SystemExceptions [ VMError subclass: BadReturn [ description [ "Answer a textual description of the exception." ^'return from a dead method context' ] ] ] Namespace current: SystemExceptions [ VMError subclass: UserInterrupt [ description [ "Answer a textual description of the exception." ^'interrupted!!!' ] ] ] Namespace current: SystemExceptions [ VMError subclass: NoRunnableProcess [ description [ "Answer a textual description of the exception." ^'no runnable process' ] ] ] Namespace current: SystemExceptions [ VMError subclass: PrimitiveFailed [ description [ "Answer a textual description of the exception." ^'primitive operation failed' ] ] ] Namespace current: SystemExceptions [ PrimitiveFailed subclass: WrongArgumentCount [ description [ "Answer a textual description of the exception." ^'wrong number of arguments' ] ] ] Namespace current: SystemExceptions [ PrimitiveFailed subclass: CInterfaceError [ description [ "Answer a textual description of the exception." ^'error in the C-language interface' ] ] ] Namespace current: SystemExceptions [ PrimitiveFailed subclass: FileError [ description [ "Answer a textual description of the exception." ^'file system error' ] ] ] Namespace current: SystemExceptions [ Error subclass: NotImplemented [ description [ "Answer a textual description of the exception." ^'method is not implemented' ] ] ] Namespace current: SystemExceptions [ NotImplemented subclass: NotYetImplemented [ description [ "Answer a textual description of the exception." ^'not yet implemented' ] ] ] Namespace current: SystemExceptions [ NotImplemented subclass: ShouldNotImplement [ description [ "Answer a textual description of the exception." ^'should not be implemented in this class' ] ] ] Namespace current: SystemExceptions [ ShouldNotImplement subclass: WrongMessageSent [ | selector suggestedSelector | WrongMessageSent class >> signalOn: selector useInstead: aSymbol [ "Raise an exception, signaling which selector was sent and suggesting a valid alternative." ^(self new) selector: selector; suggestedSelector: aSymbol; signal ] messageText [ "Answer an exception's message text." ^'%1, use %2 instead' % {self basicMessageText. self suggestedSelector storeString} ] selector [ "Answer which selector was sent." ^selector ] selector: aSymbol [ "Set which selector was sent." selector := aSymbol ] suggestedSelector [ "Answer a valid alternative to the selector that was used." ^suggestedSelector ] suggestedSelector: aSymbol [ "Set a valid alternative to the selector that was used." suggestedSelector := aSymbol ] ] ] Namespace current: SystemExceptions [ ShouldNotImplement subclass: SubclassResponsibility [ description [ "Answer a textual description of the exception." ^'method is responsibility of a subclass' ] ] ] Namespace current: SystemExceptions [ Exception subclass: UnhandledException [ | originalException | description [ "Answer a textual description of the exception." ^'an unhandled exception occurred in the current process' ] defaultAction [ "Terminate the current process." | debugger debuggerClass context | Transcript flush. debugger := Processor activeDebugger. debugger isNil ifFalse: [^debugger stopInferior: self messageText ]. debuggerClass := thisContext debuggerClass. debuggerClass isNil ifFalse: [^debuggerClass open: self originalException creator printString , ' error: ' , self messageText ]. "Default behavior - print backtrace" RegressionTesting ifFalse: [self originalException creator basicPrint]. Transcript nextPutAll: ' error: '; display: self messageText; nl. RegressionTesting ifFalse: [context := thisContext. [context isInternalExceptionHandlingContext] whileTrue: [context := context parentContext]. context backtraceOn: Transcript]. thisContext environment continue: nil ] instantiateDefaultHandler [ "Private - Fill the receiver with information on its default handler." | signalingContext resumeContext | "This exception is kind of special, as we forcedly have to find a place to resume---even if the exception was not resumable! This typically will happens when the user steps out of the exception handling gobbledegook in the debugger." signalingContext := thisContext. [resumeContext := signalingContext parentContext. resumeContext isEnvironment not and: [resumeContext isInternalExceptionHandlingContext]] whileTrue: [signalingContext := resumeContext]. self onDoBlock: nil handlerBlock: [ :ex | ex defaultAction ] onDoContext: signalingContext previousState: nil ] originalException [ "Answer the uncaught exception." ^originalException ] originalException: anObject [ "Set the uncaught exception to anObject." originalException := anObject ] ] ] Namespace current: Kernel [ Notification subclass: TimeoutNotification [ | delay | TimeoutNotification class >> on: aDelay [ ^ self new delay: aDelay; yourself ] delay: aDelay [ delay := aDelay ] delay [ ^ delay ] isResumable [ ^ false ] defaultAction [ "We are not resumable, so do nothing. This should really never happen." ] ] ] Number extend [ arithmeticError: msg [ "Raise an ArithmeticError exception having msg as its message text." ^ArithmeticError new signal: msg ] zeroDivide [ "Raise a division-by-zero (ZeroDivide) exception whose dividend is the receiver." ^(ZeroDivide dividend: self) signal ] ] Object extend [ doesNotUnderstand: aMessage [ "Called by the system when a selector was not found. message is a Message containing information on the receiver" "aMessage inspect." "thisContext parentContext method inspect." "ObjectMemory abort." ^(MessageNotUnderstood new) message: aMessage receiver: self; signal ] error: message [ "Display a walkback for the receiver, with the given error message. Signal an `Error' exception." ^Error new signal: message ] halt: message [ "Display a walkback for the receiver, with the given error message. Signal an `Halt' exception." ^Halt new signal: message ] ] Eval [ SystemExceptions.ProcessBeingTerminated initialize ] smalltalk-3.2.5/kernel/Magnitude.st0000644000175000017500000000523612123404352014175 00000000000000"====================================================================== | | Magnitude Method Definitions | | ======================================================================" "====================================================================== | | Copyright 1988,92,94,95,99,2000,2001 | Free Software Foundation, Inc. | Written by Steve Byrne. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" Object subclass: Magnitude [ .'> = aMagnitude [ "Answer whether the receiver is equal to aMagnitude" self subclassResponsibility ] < aMagnitude [ "Answer whether the receiver is less than aMagnitude" self subclassResponsibility ] > aMagnitude [ "Answer whether the receiver is greater than aMagnitude" ^aMagnitude < self ] <= aMagnitude [ "Answer whether the receiver is less than or equal to aMagnitude" ^(aMagnitude < self) not ] >= aMagnitude [ "Answer whether the receiver is greater than or equal to aMagnitude" ^(self < aMagnitude) not ] between: min and: max [ "Returns true if object is inclusively between min and max." ^self >= min and: [self <= max] ] min: aMagnitude [ "Returns the least object between the receiver and aMagnitude" ^self < aMagnitude ifTrue: [self] ifFalse: [aMagnitude] ] max: aMagnitude [ "Returns the greatest object between the receiver and aMagnitude" ^self > aMagnitude ifTrue: [self] ifFalse: [aMagnitude] ] ] smalltalk-3.2.5/kernel/Symbol.st0000644000175000017500000002420312123404352013520 00000000000000"====================================================================== | | Symbol Method Definitions | | ======================================================================" "====================================================================== | | Copyright 1988,92,94,95,99,2000,2001,2002,2006,2007,2008,2009 | Free Software Foundation, Inc. | Written by Steve Byrne. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" String subclass: Symbol [ Symbol class >> rebuildTable [ "Rebuild the SymbolTable, thereby garbage-collecting unreferenced Symbols. While this process is done, preemption is disabled because it is not acceptable to leave the SymbolTable in a partially updated state. Note that this works because String>>#hash calculates the same hash value used by the VM when interning strings into the SymbolTable. Changing one of the hashing methods without changing the other will break this method." [| oldSymbols hashTableMask | oldSymbols := Symbol allInstances. hashTableMask := SymbolTable size - 1. "We have to use #become: so that any reference from the VM to the SymbolTable (via the _gst_symbol_table variable) is still valid." SymbolTable become: SymbolTable copyEmpty. ObjectMemory compact. oldSymbols aliveObjectsDo: [:each | | bucket | bucket := (each asString hash scramble bitAnd: hashTableMask) + 1. SymbolTable at: bucket put: (SymLink symbol: each nextLink: (SymbolTable at: bucket))]] valueWithoutPreemption ] Symbol class >> hasInterned: aString ifTrue: aBlock [ "If aString has not been interned yet, answer false. Else, pass the interned version to aBlock and answer true. Note that this works because String>>#hash calculates the same hash value used by the VM when interning strings into the SymbolTable. Changing one of the hashing methods without changing the other will break this method." | link hash | hash := aString asString hash scramble bitAnd: SymbolTable size - 1. link := SymbolTable at: hash + 1. link do: [:each | | ok | each size = aString size ifTrue: [ok := true. each with: aString do: [:a :b | a = b ifFalse: [ok := false]]. ok ifTrue: [aBlock value: each. ^true]]]. ^false ] Symbol class >> isSymbolString: aString [ "Answer whether aString has already been interned. Note that this works because String>>#hash calculates the same hash value used by the VM when interning strings into the SymbolTable. Changing one of the hashing methods without changing the other will break this method." | link hash | hash := aString asString hash scramble bitAnd: SymbolTable size - 1. link := SymbolTable at: hash + 1. link do: [:each | | ok | each size = aString size ifTrue: [ok := true. each with: aString do: [:a :b | a = b ifFalse: [ok := false]]. ok ifTrue: [^true]]]. ^false ] Symbol class >> internCharacter: aCharacter [ "Answer the one-character symbol associated to the given character." | s | s := String new: 1. s at: 1 put: aCharacter. ^self intern: s ] Symbol class >> new [ self shouldNotImplement ] Symbol class >> new: size [ self shouldNotImplement ] Symbol class >> with: element1 [ "Answer a collection whose only element is element1" | s | s := String new: 1. s at: 1 put: element1. ^self intern: s ] Symbol class >> with: element1 with: element2 [ "Answer a collection whose only elements are the parameters in the order they were passed" | s | s := String new: 2. s at: 1 put: element1. s at: 2 put: element2. ^self intern: s ] Symbol class >> with: element1 with: element2 with: element3 [ "Answer a collection whose only elements are the parameters in the order they were passed" | s | s := String new: 3. s at: 1 put: element1. s at: 2 put: element2. s at: 3 put: element3. ^self intern: s ] Symbol class >> with: element1 with: element2 with: element3 with: element4 [ "Answer a collection whose only elements are the parameters in the order they were passed" | s | s := String new: 4. s at: 1 put: element1. s at: 2 put: element2. s at: 3 put: element3. s at: 4 put: element4. ^self intern: s ] Symbol class >> with: element1 with: element2 with: element3 with: element4 with: element5 [ "Answer a collection whose only elements are the parameters in the order they were passed" | s | s := String new: 5. s at: 1 put: element1. s at: 2 put: element2. s at: 3 put: element3. s at: 4 put: element4. s at: 5 put: element5. ^self intern: s ] Symbol class >> intern: aString [ "Private - Same as 'aString asSymbol'" SystemExceptions.WrongClass signalOn: aString mustBe: String ] asString [ "Answer a String with the same characters as the receiver" ^self copyFrom: 1 to: self size ] asSymbol [ "But we are already a Symbol, and furthermore, Symbols are identity objects! So answer the receiver." ^self ] numArgs [ "Answer the number of arguments supported by the receiver, which is supposed to be a valid message name (#+, #not, #printOn:, #ifTrue:ifFalse:, etc.)" (self at: self size) = $: ifTrue: [^self occurrencesOf: $:]. (self anySatisfy: [ :ch | ch isLetter or: [ ch = $_ ]]) ifTrue: [^0]. ^1 ] keywords [ "Answer an array of keywords that compose the receiver, which is supposed to be a valid message name (#+, #not, #printOn:, #ifTrue:ifFalse:, etc.)" (self at: 1) isLetter ifFalse: [^{self}]. ^(self at: self size) = $: ifTrue: [(self substrings: $:) collect: [:each | (each , ':') asSymbol]] ifFalse: [{self}] ] implementors [ "Answer a Set of all the compiled method associated with selector named by the receiver, which is supposed to be a valid message name." | implementors | implementors := Set new. Class withAllSubclassesDo: [:c | | m | m := c compiledMethodAt: self ifAbsent: [nil]. m isNil ifFalse: [implementors add: m]. m := c asClass compiledMethodAt: self ifAbsent: [nil]. m isNil ifFalse: [implementors add: m]]. ^implementors ] shallowCopy [ "Returns a deep copy of the receiver. As Symbols are identity objects, we actually return the receiver itself." ^self ] deepCopy [ "Returns a deep copy of the receiver. As Symbols are identity objects, we actually return the receiver itself." ^self ] species [ ^String ] displayString [ "Answer a String representing the receiver. For most objects this is simply its #printString, but for strings and characters, superfluous dollars or extra pair of quotes are stripped." | stream | stream := WriteStream on: String new. self displayOn: stream. ^stream contents ] displayOn: aStream [ "Print a represention of the receiver on aStream. For most objects this is simply its #printOn: representation, but for strings and characters, superfluous dollars or extra pairs of quotes are stripped." self printOn: aStream ] storeLiteralOn: aStream [ "Print Smalltalk code on aStream that compiles to the same symbol as the receiver." self storeOn: aStream ] storeOn: aStream [ "Print Smalltalk code on aStream that compiles to the same symbol as the receiver." self printOn: aStream ] printOn: aStream [ "Print a represention of the receiver on aStream." aStream nextPut: $#. self isSimpleSymbol ifTrue: [aStream nextPutAll: self] ifFalse: [super printOn: aStream] ] isSimpleSymbol [ "Answer whether the receiver must be represented in quoted-string (e.g. #'abc-def') form." | first | first := self at: 1. first isLetter ifFalse: ["Binary symbol" self size > 2 ifTrue: [^false]. ^self allSatisfy: [:each | '+-*/\<>=~,%@?&|' includes: each]]. "Selector or kind-of-selector" ^self allSatisfy: [:each | each isAlphaNumeric or: [each = $:]] ] isString [ ^false ] isSymbol [ ^true ] = aSymbol [ "Answer whether the receiver and aSymbol are the same object" ^false ] hash [ "Answer an hash value for the receiver. Symbols are optimized for speed" ] ] smalltalk-3.2.5/kernel/Random.st0000644000175000017500000001004612130343734013477 00000000000000"====================================================================== | | Random number Method Definitions | | ======================================================================" "====================================================================== | | Copyright 1988,92,94,95,99,2000,2001,2002 | Free Software Foundation, Inc. | Written by Steve Byrne. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" Stream subclass: Random [ | seed | Random class [ | source | ] Random class >> seed: aFloat [ "Create a new random number generator whose seed is aFloat" ^(self basicNew) seed: aFloat; yourself ] Random class >> new [ "Create a new random number generator whose seed is given by the current time on the millisecond clock" ^self basicNew setSeed ] Random class >> source [ "Return a standard source of random numbers." ^source isNil ifTrue: [source := self new] ifFalse: [source] ] Random class >> next [ "Return a random number between 0 and 1 (excluded)" ^self source next ] Random class >> between: low and: high [ "Return a random integer between the given extrema" ^self source between: low and: high ] chiSquare [ "Compute the chi-square of the random that this class generates." "the previous algorithm's chi-square was 93.4" ^self chiSquare: 1000 range: 100 ] chiSquare: n range: r [ "Return the chi-square deduced from calculating n random numbers in the 0..r range." | f t seed | seed := 0.1234567. f := Array new: r + 1. 1 to: r + 1 do: [:i | f at: i put: 0]. n timesRepeat: [seed := (seed + Float pi) squared squared fractionPart. t := (seed * r) truncated. f at: t + 1 put: (f at: t + 1) + 1]. t := 0. 1 to: r do: [:i | t := t + (f at: i) squared]. ^r asFloat * t / n - n ] atEnd [ "This stream never ends. Always answer false." ^false ] between: low and: high [ "Return a random integer between low and high." | i range | range := high - low + 1. i := (self next * range) truncated. ^i + low ] next [ "Return the next random number in the sequence." "Found on an obscure Japanese manual. Turns out to be good!" ^seed := (seed + Float pi) squared squared fractionPart ] nextPut: value [ self shouldNotImplement ] seed: aFloat [ "Private - Set the random number seed to aFloat. Ensure decent results even when integers are passed" seed := (aFloat / 100000.0 + aFloat) fractionPart. self next. self next ] setSeed [ "Private - Set a random number seed." seed := Time primSecondClock bitXor: Time millisecondClock. seed := seed + (Time primNanosecondClock \\ 1000000). seed := (seed / 4194303.0) fractionPart. self next. self next ] ] smalltalk-3.2.5/kernel/RootNamespc.st0000644000175000017500000000733012123404352014507 00000000000000"====================================================================== | | RootNamespace Method Definitions | | ======================================================================" "====================================================================== | | Copyright 1999, 2000, 2001, 2002, 2007 | Free Software Foundation, Inc. | Written by Paolo Bonzini. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" AbstractNamespace subclass: RootNamespace [ RootNamespace class >> new: spaceName [ "Create a new root namespace with the given name, and add to Smalltalk a key that references it." ^Smalltalk at: spaceName asGlobalKey put: ((super new: 24) name: spaceName asSymbol; yourself) ] inheritedKeys [ "Answer a Set of all the keys in the receiver and its superspaces" ^Set new ] set: key to: newValue ifAbsent: aBlock [ "Assign newValue to the variable named as specified by `key'. This method won't define a new variable; instead if the key is not found it will search in superspaces and evaluate aBlock if it is not found. Answer newValue." | index | index := self findIndexOrNil: key. index isNil ifTrue: [^aBlock value]. (self primAt: index) value: newValue. ^newValue ] siblings [ "Answer all the other root namespaces" ^(RootNamespace allInstances asSet) remove: self; yourself ] siblingsDo: aBlock [ "Evaluate aBlock once for each of the other root namespaces, passing the namespace as a parameter." RootNamespace allInstances asSet do: [:space | space == self ifFalse: [aBlock value: space]] ] printOn: aStream in: aNamespace [ "Print on aStream some Smalltalk code compiling to the receiver when the current namespace is aNamespace" | reference | reference := aNamespace at: self name asGlobalKey ifAbsent: [nil]. reference == self ifFalse: [aStream nextPutAll: 'Smalltalk.']. aStream nextPutAll: self name ] nameIn: aNamespace [ "Answer Smalltalk code compiling to the receiver when the current namespace is aNamespace" | reference | reference := aNamespace at: self name asGlobalKey ifAbsent: [nil]. ^reference == self ifTrue: [self name asString] ifFalse: ['Smalltalk.' , self name] ] storeOn: aStream [ "Store Smalltalk code compiling to the receiver" self name isNil ifTrue: [self error: 'cannot print unnamed namespace']. aStream nextPutAll: 'Smalltalk.'; nextPutAll: self name ] ] smalltalk-3.2.5/kernel/String.st0000644000175000017500000002345112123404352013525 00000000000000"====================================================================== | | String Method Definitions | | ======================================================================" "====================================================================== | | Copyright 1988,92,94,95,99,2000,2001,2006,2008,2009 | Free Software Foundation, Inc. | Written by Steve Byrne. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" CharacterArray subclass: String [ String class >> fromCData: aCObject [ "Answer a String containing the bytes starting at the location pointed to by aCObject, up to the first NUL character." ^self primitiveFailed ] String class >> fromCData: aCObject size: anInteger [ "Answer a String containing anInteger bytes starting at the location pointed to by aCObject" ^SystemExceptions.WrongClass signalOn: anInteger mustBe: SmallInteger ] String class >> isUnicode [ "Answer false; the receiver stores bytes (i.e. an encoded form), not characters." ^false ] = aCollection [ "Answer whether the receiver's items match those in aCollection" ^super = aCollection ] , aString [ "Answer a new instance of an ArrayedCollection containing all the elements in the receiver, followed by all the elements in aSequenceableCollection" | newString mySize | aString class == String ifFalse: [^super , aString]. newString := self copyEmpty: (mySize := self size) + aString size. newString replaceFrom: 1 to: mySize with: self startingAt: 1. newString replaceFrom: mySize + 1 to: newString size with: aString startingAt: 1. ^newString ] encoding [ "Answer the encoding of the receiver. This is not implemented unless you load the Iconv package." self notYetImplemented ] asByteArray [ "Return the receiver, converted to a ByteArray of ASCII values" | byteArray size | size := self size. byteArray := ByteArray new: size. byteArray replaceFrom: 1 to: size withString: self startingAt: 1. ^byteArray ] asSymbol [ "Returns the symbol corresponding to the receiver" ^Symbol intern: self ] asString [ "But I already am a String! Really!" ^self ] isString [ ^true ] displayString [ "Answer a String representing the receiver. For most objects this is simply its #printString, but for CharacterArrays and characters, superfluous dollars or extra pair of quotes are stripped." ^self ] displayOn: aStream [ "Print a representation of the receiver on aStream. Unlike #printOn:, this method strips extra quotes." aStream nextPutAll: self ] isLiteralObject [ "Answer whether the receiver is expressible as a Smalltalk literal." ^self isReadOnly not ] storeLiteralOn: aStream [ "Store a Smalltalk literal compiling to the receiver on aStream" aStream nextPut: $'. self do: [:char | char == $' ifTrue: [aStream nextPut: char]. aStream nextPut: char]. aStream nextPut: $' ] storeOn: aStream [ "Store Smalltalk code compiling to the receiver on aStream" self storeLiteralOn: aStream. self isReadOnly ifFalse: [aStream nextPutAll: ' copy'] ] printOn: aStream [ "Print a representation of the receiver on aStream" aStream nextPut: $'. self do: [:char | char == $' ifTrue: [aStream nextPut: char]. aStream nextPut: char]. aStream nextPut: $' ] byteAt: index [ "Answer the ascii value of index-th character variable of the receiver" ^self valueAt: index ] byteAt: index put: value [ "Store (Character value: value) in the index-th indexed instance variable of the receiver" ^self valueAt: index put: value ] hash [ "Answer an hash value for the receiver" ^0 ] similarityTo: aString [ "Answer a number that denotes the similarity between aString and the receiver. 0 indicates equality, negative numbers indicate some difference. Implemented as a primitive for speed." ^SystemExceptions.WrongClass signalOn: aString mustBe: String ] size [ "Answer the size of the receiver" ^self primitiveFailed ] indexOf: anElement startingAt: anIndex ifAbsent: exceptionBlock [ "Answer the first index > anIndex which contains anElement. Invoke exceptionBlock and answer its result if no item is found" "If anIndex is just past the end of the collection, don't raise an error (this is the most generic solution that avoids that #indexOf: fails when the collection is empty." ^(anIndex < 1 or: [anIndex > (self size + 1)]) ifTrue: [self checkIndexableBounds: anIndex] ifFalse: [exceptionBlock value] ] indexOf: anElement startingAt: anIndex [ "Answer the first index > anIndex which contains anElement. Invoke exceptionBlock and answer its result if no item is found" "If anIndex is just past the end of the collection, don't raise an error (this is the most generic solution that avoids that #indexOf: fails when the collection is empty." ^(anIndex < 1 or: [anIndex > (self size + 1)]) ifTrue: [self checkIndexableBounds: anIndex] ifFalse: [0] ] replaceFrom: start to: stop withByteArray: byteArray startingAt: replaceStart [ "Replace the characters from start to stop with new characters whose ASCII codes are contained in byteArray, starting at the replaceStart location of byteArray" ^super replaceFrom: start to: stop with: byteArray asString startingAt: replaceStart ] replaceFrom: start to: stop with: aString startingAt: replaceStart [ "Replace the characters from start to stop with new characters whose ASCII codes are contained in aString, starting at the replaceStart location of aString" ^super replaceFrom: start to: stop with: aString startingAt: replaceStart ] at: anIndex ifAbsent: aBlock [ "Answer the index-th indexed instance variable of the receiver" ^self checkIndexableBounds: anIndex ifAbsent: aBlock ] at: anIndex [ "Answer the index-th indexed instance variable of the receiver" self checkIndexableBounds: anIndex ] basicAt: anIndex [ "Answer the index-th indexed instance variable of the receiver. This method must not be overridden, override at: instead" self checkIndexableBounds: anIndex ] at: anIndex put: value [ "Store value in the index-th indexed instance variable of the receiver" self checkIndexableBounds: anIndex put: value ] basicAt: anIndex put: value [ "Store value in the index-th indexed instance variable of the receiver This method must not be overridden, override at:put: instead" self checkIndexableBounds: anIndex put: value ] asCData [ "Allocate memory with malloc for a NULL-terminated copy of the receiver, and return a pointer to it as a CChar." ^self asCData: CCharType ] asCData: aCType [ "Allocate memory with malloc for a NULL-terminated copy of the receiver, and return a pointer to it as a CObject of the given type." ^self primitiveFailed ] ] smalltalk-3.2.5/kernel/LargeInt.st0000644000175000017500000012652412123404352013771 00000000000000"====================================================================== | | LargeInteger hierarchy Method Definitions | | ======================================================================" "====================================================================== | | Copyright 1999, 2000, 2001, 2002, 2008, 2009 Free Software Foundation, Inc. | Written by Paolo Bonzini. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" Integer subclass: LargeInteger [ Zero := nil. One := nil. ZeroBytes := nil. OneBytes := nil. LeadingZeros := nil. TrailingZeros := nil. LargeInteger class >> new [ self shouldNotImplement ] LargeInteger class >> initialize [ "Private - Initialize the receiver's class variables" ZeroBytes := #[0]. OneBytes := #[1]. Zero := LargeZeroInteger basicNew: 1. One := (LargePositiveInteger basicNew: 1) setBytes: OneBytes. "The leading zeros table is used in division and to compute #highBit. It is obtained by: LeadingZeros := ByteArray new: 255. 127 to: 1 by: -1 do: [ :i | LeadingZeros at: i put: 1 + (LeadingZeros at: i + i). ]." LeadingZeros := #[7 6 6 5 5 5 5 4 4 4 4 4 4 4 4 3 3 3 3 3 3 3 3 3 3 3 3 3 3 3 3 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 2 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0]. "The trailing zeros table is used in the GCD algorithm. It is obtained by: TrailingZeros := ByteArray new: 255. 2 to: 254 by: 2 do: [ :i | TrailingZeros at: i put: 1 + (TrailingZeros at: i // 2). ]." TrailingZeros := #[0 1 0 2 0 1 0 3 0 1 0 2 0 1 0 4 0 1 0 2 0 1 0 3 0 1 0 2 0 1 0 5 0 1 0 2 0 1 0 3 0 1 0 2 0 1 0 4 0 1 0 2 0 1 0 3 0 1 0 2 0 1 0 6 0 1 0 2 0 1 0 3 0 1 0 2 0 1 0 4 0 1 0 2 0 1 0 3 0 1 0 2 0 1 0 5 0 1 0 2 0 1 0 3 0 1 0 2 0 1 0 4 0 1 0 2 0 1 0 3 0 1 0 2 0 1 0 7 0 1 0 2 0 1 0 3 0 1 0 2 0 1 0 4 0 1 0 2 0 1 0 3 0 1 0 2 0 1 0 5 0 1 0 2 0 1 0 3 0 1 0 2 0 1 0 4 0 1 0 2 0 1 0 3 0 1 0 2 0 1 0 6 0 1 0 2 0 1 0 3 0 1 0 2 0 1 0 4 0 1 0 2 0 1 0 3 0 1 0 2 0 1 0 5 0 1 0 2 0 1 0 3 0 1 0 2 0 1 0 4 0 1 0 2 0 1 0 3 0 1 0 2 0 1 0] ] LargeInteger class >> test: selector with: a with: b [ | result | result := a perform: selector with: b. a printNl. b printNl. result printNl ] LargeInteger class >> from: byteArray [ "Private - Answer an instance of a descendant of LargeInteger representing the number whose base-256 representation is in byteArray (least significant byte first). The answered LargeInteger has the smallest possible representation (i.e. there are no spurious leading bytes set to all zeros or all ones) and already belongs to the correct class, either LargePositiveInteger, LargeNegativeInteger or LargeZeroInteger" | class lastSignificant byte | lastSignificant := byteArray size. [byte := byteArray at: lastSignificant. lastSignificant = 1 ifTrue: [byte = 0 ifTrue: [^Zero]. false "Leave the while loop"] ifFalse: ["Check if the current byte is spurious AND has the same sign as the previous" (byte = 0 or: [byte = 255]) and: [(byte bitXor: (byteArray at: lastSignificant - 1)) < 128]]] whileTrue: [lastSignificant := lastSignificant - 1]. class := (byteArray at: lastSignificant) < 128 ifTrue: [LargePositiveInteger] ifFalse: [LargeNegativeInteger]. ^(class basicNew: lastSignificant) setBytes: byteArray ] LargeInteger class >> fromInteger: anInteger [ "Private - Answer an instance of a descendant of LargeInteger representing the (small) Integer contained in anInteger. The answered LargeInteger has the smallest possible representation (i.e. there are no spurious leading bytes set to all zeros or all ones) and already belongs to the correct class, either LargePositiveInteger, LargeNegativeInteger or LargeZeroInteger" | bytes int | anInteger isInteger ifFalse: [^anInteger]. bytes := ByteArray new: CLongSize. int := anInteger. 1 to: CLongSize do: [:i | bytes at: i put: (int bitAnd: 255). int := int bitShift: -8]. ^self from: bytes ] LargeInteger class >> resultFrom: byteArray [ "Private - Answer an instance of a descendant of Integer representing the number whose base-256 representation is in byteArray (least significant byte first). If a kind of LargeInteger is answered, it has the smallest possible representation (i.e. there are no spurious leading bytes set to all zeros or all ones); however it is possible that this method answers an Integer." | result accum size | result := self from: byteArray. size := result size. size > CLongSize ifTrue: [^result]. size = CLongSize ifTrue: [((result at: size) between: 64 and: 191) ifTrue: [^result]]. accum := result negative ifTrue: [-1] ifFalse: [0]. result size to: 1 by: -1 do: [:i | accum := (accum bitShift: 8) bitOr: (result at: i)]. ^accum ] hash [ "Answer an hash value for the receiver" ^0 ] size [ "Answer the number of indexed instance variable in the receiver" ] digitLength [ "Answer the number of base-256 digits in the receiver" ] at: anIndex [ "Answer the anIndex-th byte in the receiver's representation" ^self mostSignificantByte ] at: anIndex put: aNumber [ "Set the anIndex-th byte in the receiver's representation" self checkIndexableBounds: anIndex put: aNumber ] primReplaceFrom: start to: stop with: replacementString startingAt: replaceStart [ "Private - Replace the characters from start to stop with new characters contained in replacementString (which, actually, can be any variable byte class), starting at the replaceStart location of replacementString" ^self primitiveFailed ] digitAt: anIndex [ "Answer the index-th base-256 digit of the receiver (byte), expressed in two's complement" ^self mostSignificantByte ] digitAt: anIndex put: aNumber [ "Set the anIndex-th base-256 digit in the receiver's representation" self checkIndexableBounds: anIndex put: aNumber ] asCNumber [ "Convert the receiver to a kind of number that is understood by the C call-out mechanism." ^self ] asObject [ "This method always fails. The number of OOPs is far less than the minimum number represented with a LargeInteger." self primitiveFailed ] asObjectNoFail [ ^nil ] = aNumber [ "Answer whether the receiver and aNumber identify the same number." (aNumber isKindOf: Number) ifFalse: [^false]. aNumber generality = self generality ifFalse: [^self retryEqualityCoercing: aNumber]. self sign = aNumber sign ifFalse: [^false]. self size = aNumber size ifFalse: [^false]. self size to: 1 by: -1 do: [:index | (self at: index) = (aNumber at: index) ifFalse: [^false]]. ^true ] ~= aNumber [ "Answer whether the receiver and aNumber identify different numbers." (aNumber isKindOf: Number) ifFalse: [^true]. aNumber generality = self generality ifFalse: [^self retryInequalityCoercing: aNumber]. self sign = aNumber sign ifFalse: [^true]. self size = aNumber size ifFalse: [^true]. self size to: 1 by: -1 do: [:index | (self at: index) = (aNumber at: index) ifFalse: [^true]]. ^false ] < aNumber [ "Answer whether the receiver is smaller than aNumber" aNumber generality = self generality ifFalse: [^self retryRelationalOp: #< coercing: aNumber]. self sign < aNumber sign ifTrue: [^true]. self sign > aNumber sign ifTrue: [^false]. self size > aNumber size ifTrue: [^self sign = -1]. aNumber size to: 1 by: -1 do: [:index | (self at: index) < (aNumber at: index) ifTrue: [^true]. (self at: index) > (aNumber at: index) ifTrue: [^false]]. ^false ] <= aNumber [ "Answer whether the receiver is smaller than aNumber or equal to it" aNumber generality = self generality ifFalse: [^self retryRelationalOp: #<= coercing: aNumber]. self sign < aNumber sign ifTrue: [^true]. self sign > aNumber sign ifTrue: [^false]. self size > aNumber size ifTrue: [^self sign = -1]. aNumber size to: 1 by: -1 do: [:index | (self at: index) < (aNumber at: index) ifTrue: [^true]. (self at: index) > (aNumber at: index) ifTrue: [^false]]. ^true ] > aNumber [ "Answer whether the receiver is greater than aNumber" aNumber generality = self generality ifFalse: [^self retryRelationalOp: #> coercing: aNumber]. aNumber sign < self sign ifTrue: [^true]. aNumber sign > self sign ifTrue: [^false]. aNumber size > self size ifTrue: [^self sign = -1]. self size to: 1 by: -1 do: [:index | (aNumber at: index) < (self at: index) ifTrue: [^true]. (aNumber at: index) > (self at: index) ifTrue: [^false]]. ^false ] >= aNumber [ "Answer whether the receiver is greater than aNumber or equal to it" aNumber generality = self generality ifFalse: [^self retryRelationalOp: #>= coercing: aNumber]. aNumber sign < self sign ifTrue: [^true]. aNumber sign > self sign ifTrue: [^false]. aNumber size > self size ifTrue: [^self sign = -1]. self size to: 1 by: -1 do: [:index | (aNumber at: index) < (self at: index) ifTrue: [^true]. (aNumber at: index) > (self at: index) ifTrue: [^false]]. ^true ] + aNumber [ "Sum the receiver and aNumber, answer the result" self subclassResponsibility ] - aNumber [ "Subtract aNumber from the receiver, answer the result" self subclassResponsibility ] * aNumber [ "Multiply aNumber and the receiver, answer the result" | result | aNumber sign = 0 ifTrue: [^0]. aNumber generality = self generality ifFalse: [^self retryMultiplicationCoercing: aNumber]. result := self abs multiply: aNumber abs. ^self sign = aNumber sign ifTrue: [result] ifFalse: [result negated] ] / aNumber [ "Divide aNumber and the receiver, answer the result (an Integer or Fraction)" | gcd | aNumber sign = 0 ifTrue: [^self zeroDivide]. self sign = 0 ifTrue: [^self]. aNumber generality = self generality ifFalse: [^self retryDivisionCoercing: aNumber]. gcd := self gcd: aNumber. gcd = self ifTrue: [^Fraction numerator: 1 denominator: (aNumber divExact: gcd)]. gcd = aNumber ifTrue: [^self divExact: gcd]. ^Fraction numerator: (self divExact: gcd) denominator: (aNumber divExact: gcd) ] // aNumber [ "Divide aNumber and the receiver, answer the result truncated towards -infinity" aNumber sign = 0 ifTrue: [^self zeroDivide]. self sign = 0 ifTrue: [^self]. aNumber generality = self generality ifFalse: [^self retry: #// coercing: aNumber]. self sign = aNumber sign ifFalse: [^self - aNumber + aNumber sign quo: aNumber]. ^self abs divide: aNumber abs using: [:quo :rem :remNotZero | self species resultFrom: quo] ] rem: aNumber [ "Divide aNumber and the receiver, answer the remainder truncated towards 0" | result | aNumber sign = 0 ifTrue: [^self zeroDivide]. self sign = 0 ifTrue: [^self]. aNumber generality = self generality ifFalse: [^self retry: #rem: coercing: aNumber]. ^self abs divide: aNumber abs using: [:quo :rem :remNotZero | self species resultFrom: rem] ] quo: aNumber [ "Divide aNumber and the receiver, answer the result truncated towards 0" | result | aNumber sign = 0 ifTrue: [^self zeroDivide]. self sign = 0 ifTrue: [^self]. aNumber generality = self generality ifFalse: [^self retry: #quo: coercing: aNumber]. result := self abs divide: aNumber abs using: [:quo :rem :remNotZero | self species resultFrom: quo]. ^self sign = aNumber sign ifTrue: [result] ifFalse: [result negated] ] divExact: aNumber [ "Dividing receiver by arg assuming that the remainder is zero, and answer the result" | result | aNumber sign = 0 ifTrue: ["Same as quo:, not worthwhile to implement it in Smalltalk." ^self zeroDivide]. self sign = 0 ifTrue: [^self]. aNumber generality = self generality ifFalse: [^self retry: #divExact: coercing: aNumber]. result := self abs divide: aNumber abs using: [:quo :rem :remNotZero | self species resultFrom: quo]. ^self sign = aNumber sign ifTrue: [result] ifFalse: [result negated] ] \\ aNumber [ "Divide aNumber and the receiver, answer the remainder truncated towards -infinity" aNumber sign = 0 ifTrue: [^self zeroDivide]. self sign = 0 ifTrue: [^self]. aNumber generality = self generality ifFalse: [^self retry: #\\ coercing: aNumber]. aNumber sign < 0 ifTrue: [^(self negated \\ aNumber negated) negated]. ^self abs divide: aNumber using: [:quo :rem :remNotZero | "must be positive" | remInteger | remInteger := self species resultFrom: rem. (remNotZero and: [self negative]) ifTrue: [aNumber - remInteger] ifFalse: [remInteger]] ] estimatedLog [ "Answer an estimate of (self abs floorLog: 10)" ^(self size asFloatD * 8.0 / FloatD log10Base2) ceiling ] negated [ "Answer the receiver's negated" | newBytes carry a | newBytes := ByteArray new: self size + 1. carry := 256. 1 to: self size do: [:index | a := carry - (self at: index). a < 256 ifTrue: [carry := 255] ifFalse: [carry := 256. a := a - 256]. newBytes at: index put: a]. newBytes at: newBytes size put: (self mostSignificantByte bitXor: 255). ^self species resultFrom: newBytes ] lowBit [ "Return the index of the lowest order 1 bit of the receiver." | each | 1 to: self size do: [:index | (each := self digitAt: index) = 0 ifFalse: [^index * 8 - 7 + (TrailingZeros at: each)]]. ^self highBit ] bitAnd: aNumber [ "Answer the receiver ANDed with aNumber" | newBytes | aNumber isInteger ifFalse: [^SystemExceptions.WrongClass signalOn: aNumber mustBe: Integer]. aNumber generality = self generality ifFalse: [^self retry: #bitAnd: coercing: aNumber]. newBytes := ByteArray new: (self size max: aNumber size). 1 to: newBytes size do: [:index | newBytes at: index put: ((self at: index) bitAnd: (aNumber at: index))]. ^self species resultFrom: newBytes ] bitAt: aNumber [ "Answer the aNumber-th bit in the receiver, where the LSB is 1" | bit | bit := aNumber - 1. ^(self at: bit // 8 + 1) bitAt: bit \\ 8 + 1 ] bitInvert [ "Answer the receiver's 1's complement" | bytes | bytes := ByteArray new: self size + 1. bytes at: bytes size put: (self mostSignificantByte bitXor: 255). 1 to: self size do: [:index | bytes at: index put: ((self at: index) bitXor: 255)]. ^self species resultFrom: bytes ] bitOr: aNumber [ "Answer the receiver ORed with aNumber" | newBytes | aNumber isInteger ifFalse: [^SystemExceptions.WrongClass signalOn: aNumber mustBe: Integer]. aNumber generality = self generality ifFalse: [^self retry: #bitOr: coercing: aNumber]. newBytes := ByteArray new: (self size max: aNumber size). 1 to: newBytes size do: [:index | newBytes at: index put: ((self at: index) bitOr: (aNumber at: index))]. ^self species resultFrom: newBytes ] bitXor: aNumber [ "Answer the receiver XORed with aNumber" | newBytes | aNumber isInteger ifFalse: [^SystemExceptions.WrongClass signalOn: aNumber mustBe: Integer]. aNumber generality = self generality ifFalse: [^self retry: #bitXor: coercing: aNumber]. newBytes := ByteArray new: (self size max: aNumber size). 1 to: newBytes size do: [:index | newBytes at: index put: ((self at: index) bitXor: (aNumber at: index))]. ^self species resultFrom: newBytes ] bitShift: aNumber [ "Answer the receiver shifted by aNumber places" aNumber isInteger ifFalse: [^SystemExceptions.WrongClass signalOn: aNumber mustBe: Integer]. ^aNumber > 0 ifTrue: [self basicLeftShift: aNumber] ifFalse: [self basicRightShift: aNumber negated] ] raisedToInteger: n [ "Return self raised to the anInteger-th power" "For LargeIntegers only, it pays off to strip the rightmost 0 bits and put them back later with a left shift..." | nbit | nbit := 1. [(self bitAt: nbit) = 0] whileTrue: [nbit := nbit + 1]. nbit = 1 ifTrue: [^super raisedToInteger: n]. nbit := nbit - 1. ^((self bitShift: nbit negated) raisedToInteger: n) bitShift: nbit * n ] basicLeftShift: totalShift [ "Private - Left shift the receiver by aNumber places" | newBytes byteShift carry shift a | byteShift := totalShift // 8. shift := totalShift bitAnd: 7. newBytes := ByteArray new: (totalShift + 7) // 8 + self size. "That `+ 1' in the #to:do: performs an extra iteration that stores the last carry in the extra byte reserved in the previous statement" carry := 0. 1 to: newBytes size - byteShift do: [:index | a := ((self at: index) bitShift: shift) + carry. carry := a bitShift: -8. a := a bitAnd: 255. newBytes at: index + byteShift put: a]. ^self species resultFrom: newBytes ] basicRightShift: totalShift [ "Private - Right shift the receiver by 'shift' places" | shift newBytes byteShift carryShift x a | byteShift := totalShift // 8. shift := (totalShift bitAnd: 7) negated. carryShift := 8 + shift. self size <= (byteShift - 1) ifTrue: [^0]. newBytes := ByteArray new: self size - byteShift + 1. x := (self at: byteShift + 1) bitShift: shift. byteShift + 1 to: self size do: [:j | a := self at: j + 1. newBytes at: j - byteShift put: ((a bitShift: carryShift) bitAnd: 255) + x. x := a bitShift: shift]. newBytes at: newBytes size put: self mostSignificantByte. ^self species resultFrom: newBytes ] largeNegated [ "Private - Same as negated, but always answer a LargeInteger" | newBytes carry a | newBytes := ByteArray new: self size + 1. carry := 256. 1 to: self size do: [:index | a := carry - (self at: index). a < 256 ifTrue: [carry := 255] ifFalse: [carry := 256. a := a - 256]. newBytes at: index put: a]. newBytes at: newBytes size put: (self mostSignificantByte bitXor: 255). ^self species from: newBytes ] zero [ "Coerce 0 to the receiver's class" ^Zero ] unity [ "Coerce 1 to the receiver's class" ^One ] coerce: aNumber [ "Truncate the number; if needed, convert it to LargeInteger representation." aNumber = 0 ifTrue: [^Zero]. ^aNumber isInteger ifTrue: [self species fromInteger: aNumber] ifFalse: [self species fromInteger: aNumber truncated] ] generality [ "Answer the receiver's generality" ^200 ] mostSignificantByte [ "Private - Answer the value of the most significant byte" self subclassResponsibility ] species [ ^LargeInteger ] bytes [ | bytes | bytes := ByteArray new: self size + 1. bytes replaceFrom: 1 to: self size with: self startingAt: 1. bytes at: bytes size put: self mostSignificantByte. ^bytes ] setBytes: aByteArray [ self primReplaceFrom: 1 to: self size with: aByteArray startingAt: 1 ] ] LargeInteger subclass: LargeNegativeInteger [ + aNumber [ "Sum the receiver and aNumber, answer the result" "All we have to do is convert the two numbers to two positive numbers and make LargePositiveInteger do the calculation. Use #largeNegated to save some coercions." aNumber sign = 0 ifTrue: [^self]. aNumber generality = self generality ifFalse: [^self retrySumCoercing: aNumber]. ^aNumber sign = -1 ifTrue: [(self largeNegated + aNumber largeNegated) negated] ifFalse: [(self largeNegated - aNumber) negated] ] - aNumber [ "Subtract aNumber from the receiver, answer the result" "All we have to do is convert the two numbers to two positive numbers and make LargePositiveInteger do the calculation. Use #largeNegated to save some coercions." aNumber sign = 0 ifTrue: [^self]. aNumber generality = self generality ifFalse: [^self retryDifferenceCoercing: aNumber]. ^aNumber sign = -1 ifTrue: [(self largeNegated - aNumber largeNegated) negated] ifFalse: [(self largeNegated + aNumber) negated] ] highBit [ "Answer the receiver's highest bit's index" ^(self at: self size) = 255 ifTrue: [^8 * self size - 16 + ((self at: self size - 1) - 256) highBit] ifFalse: [^8 * self size - 8 + ((self at: self size) - 256) highBit] ] gcd: anInteger [ "Return the greatest common divisor between the receiver and anInteger" ^self negated gcd: anInteger abs ] positive [ "Answer whether the receiver is >= 0" ^false ] strictlyPositive [ "Answer whether the receiver is > 0" ^false ] negative [ "Answer whether the receiver is < 0" ^true ] abs [ "Answer the receiver's absolute value." "This is surely a large integer (while `aLargePositiveInteger negated' might be the smallest small integer)." ^self largeNegated ] sign [ "Answer the receiver's sign" ^-1 ] asFloatD [ "Answer the receiver converted to a FloatD" ^self negated asFloatD negated ] asFloatE [ "Answer the receiver converted to a FloatE" ^self negated asFloatE negated ] asFloatQ [ "Answer the receiver converted to a FloatQ" ^self negated asFloatQ negated ] mostSignificantByte [ "Private - Answer the value of the most significant byte" ^255 ] ] LargeInteger subclass: LargePositiveInteger [ + aNumber [ "Sum the receiver and aNumber, answer the result" | newBytes carry a b result | aNumber sign = 0 ifTrue: [^self]. aNumber sign = -1 ifTrue: [^self - aNumber negated]. aNumber generality = self generality ifFalse: [^self retrySumCoercing: aNumber]. newBytes := ByteArray new: (self size max: aNumber size) + 1. carry := 0. 1 to: newBytes size - 1 do: [:index | result := (self at: index) + (aNumber at: index) + carry. result > 255 ifTrue: [carry := 1. result := result - 256] ifFalse: [carry := 0]. newBytes at: index put: result]. newBytes at: newBytes size put: carry. ^LargeInteger resultFrom: newBytes ] - aNumber [ "Subtract aNumber from the receiver, answer the result" | newBytes carry a b result | aNumber sign = 0 ifTrue: [^self]. aNumber sign = -1 ifTrue: [^self + aNumber negated]. aNumber generality = self generality ifFalse: [^self retryDifferenceCoercing: aNumber]. newBytes := ByteArray new: (self size max: aNumber size) + 1. carry := 0. 1 to: newBytes size - 1 do: [:index | result := (self at: index) - (aNumber at: index) + carry. result < 0 ifTrue: [carry := -1. result := result + 256] ifFalse: [carry := 0]. newBytes at: index put: result]. newBytes at: newBytes size put: (carry bitAnd: 255). ^LargeInteger resultFrom: newBytes ] gcd: anInteger [ "Calculate the GCD between the receiver and anInteger" "Binary GCD - See Knuth `Seminumerical algorithms', Vol 2, 4.5.2 It was adapted to remove the variable `r' and to only work with unsigned numbers" | adjust t tmp u v | (self sign bitAnd: anInteger sign) = 0 ifTrue: [^self + anInteger]. u := self bytes. v := anInteger abs. v generality = self generality ifFalse: [v := self coerce: v]. v := v bytes. "Divide u and v by 2 as long as they are both even" adjust := t := self bytesTrailingZeros: u. self bytesRightShift: u big: t. adjust := adjust min: (t := self bytesTrailingZeros: v). self bytesRightShift: v big: t. u size = v size ifFalse: [u size < v size ifTrue: [u := u copyGrowTo: v size] ifFalse: [v := v copyGrowTo: u size]]. "Well, this is it -- the stuff up to this point was just set up" [t := self bytes: u from: 1 compare: v. t = 0] whileFalse: [t < 0 ifTrue: [t := v. v := u. u := t]. self bytes: u from: 1 subtract: v. ((u at: 1) bitAnd: 1) = 0 ifTrue: [t := self bytesTrailingZeros: u. self bytesRightShift: u big: t]]. self bytesLeftShift: u big: adjust. ^self species resultFrom: u ] highBit [ "Answer the receiver's highest bit's index" ^(self at: self size) = 0 ifTrue: [^8 * self size - 8 - (LeadingZeros at: (self at: self size - 1))] ifFalse: [^8 * self size - (LeadingZeros at: (self at: self size))] ] positive [ "Answer whether the receiver is >= 0" ^true ] strictlyPositive [ "Answer whether the receiver is > 0" ^true ] negative [ "Answer whether the receiver is < 0" ^false ] abs [ "Answer the receiver's absolute value" ^self ] sign [ "Answer the receiver's sign" ^1 ] asFloat: characterization [ "Answer the receiver converted to a Float" "Check for number bigger than maximum mantissa" | nTruncatedBits mantissa exponent mask trailingBits inexact carry | nTruncatedBits := self highBit - characterization precision. nTruncatedBits <= 0 ifTrue: [^self fastAsFloat: characterization]. mantissa := self bitShift: nTruncatedBits negated. exponent := nTruncatedBits. "Apply IEEE 754 round to nearest even default rounding mode" carry := self bitAt: nTruncatedBits. (carry = 1 and: [mantissa odd or: [self lowBit < nTruncatedBits]]) ifTrue: [mantissa := mantissa + 1]. ^(characterization coerce: mantissa) timesTwoPower: exponent ] fastAsFloat: characterization [ "Conversion can be exact, construct Float by successive mul add operations" | result byte | byte := characterization coerce: 256. result := characterization coerce: 0. self size to: 1 by: -1 do: [:index | result := result * byte + (self at: index)]. ^result ] mostSignificantByte [ "Private - Answer the value of the most significant byte" ^0 ] asFloatD [ "Answer the receiver converted to a FloatD" ^self asFloat: FloatD ] asFloatE [ "Answer the receiver converted to a FloatE" ^self asFloat: FloatE ] asFloatQ [ "Answer the receiver converted to a FloatQ" ^self asFloat: FloatQ ] replace: str withStringBase: radix [ "Return in a String str the base radix representation of the receiver." | digits source quo t rem where | source := self. quo := ByteArray new: self size. where := str size. self size to: 1 by: -1 do: [:i | [rem := 0. i to: 1 by: -1 do: [:j | t := (rem bitShift: 8) + (source at: j). quo at: j put: t // radix. rem := t \\ radix]. str at: where put: (Character digitValue: rem). where := where - 1. source := quo. (source at: i) = 0] whileFalse]. ^str ] isSmall [ "Private - Answer whether the receiver is small enough to employ simple scalar algorithms for division and multiplication" ^self size <= 2 and: [(self at: 2) = 0] ] divide: aNumber using: aBlock [ "Private - Divide the receiver by aNumber (unsigned division). Evaluate aBlock passing the result ByteArray, the remainder ByteArray, and whether the division had a remainder" | result a b | aNumber isSmall ifTrue: [result := ByteArray new: self size. b := 0. self size to: 1 by: -1 do: [:j | a := (b bitShift: 8) + (self at: j). result at: j put: a // (aNumber at: 1). b := a \\ (aNumber at: 1)]. ^aBlock value: result value: (ByteArray with: b with: 0) value: b ~= 0]. "special case: numerator < denominator" self size < aNumber size ifTrue: [^aBlock value: ZeroBytes value: self value: true]. self size > aNumber size ifTrue: [result := self primDivide: aNumber. ^aBlock value: result key value: result value value: (result value anySatisfy: [:each | each ~= 0])]. self size to: 1 by: -1 do: [:index | a := self at: index. b := aNumber at: index. b > a ifTrue: [^aBlock value: ZeroBytes value: self value: true]. a > b ifTrue: [result := self primDivide: aNumber. ^aBlock value: result key value: result value value: (result value anySatisfy: [:each | each ~= 0])]]. "Special case: numerator = denominator" ^aBlock value: OneBytes value: ZeroBytes value: false ] multiply: aNumber [ "Private - Multiply the receiver by aNumber (unsigned multiply)" "Special case - other factor < 255" | newBytes byte carry index digit start | aNumber isSmall ifTrue: [^self species from: (self bytes: self bytes multiply: (aNumber at: 1))]. start := 1. [(aNumber at: start) = 0] whileTrue: [start := start + 1]. newBytes := ByteArray new: self size + aNumber size + 2. 1 to: self size do: [:indexA | digit := self at: indexA. digit = 0 ifFalse: [carry := 0. index := indexA + start - 1. start to: aNumber size do: [:indexB | byte := digit * (aNumber at: indexB) + carry + (newBytes at: index). carry := byte bitShift: -8. newBytes at: index put: (byte bitAnd: 255). index := index + 1]. newBytes at: indexA + aNumber size put: carry]]. "If I multiply two large integers, the result is large, so use #from:..." ^self species from: newBytes ] bytes: bytes multiply: anInteger [ "Private - Multiply the bytes in bytes by anInteger, which must be < 255. Put the result back in bytes." | byte carry | carry := 0. 1 to: bytes size do: [:index | byte := (bytes at: index) * anInteger + carry. carry := byte bitShift: -8. bytes at: index put: (byte bitAnd: 255)]. carry > 0 ifTrue: [bytes at: bytes size - 1 put: carry]. ^bytes ] bytes: byteArray1 from: j compare: byteArray2 [ "Private - Answer the sign of byteArray2 - byteArray1; the j-th byte of byteArray1 is compared with the first of byteArray2, the j+1-th with the second, and so on." | a b i | i := byteArray2 size. j + byteArray2 size - 1 to: j by: -1 do: [:index | b := byteArray2 at: i. a := byteArray1 at: index. a < b ifTrue: [^-1]. a > b ifTrue: [^1]. i := i - 1]. ^0 ] bytes: byteArray1 from: j subtract: byteArray2 [ "Private - Sutract the bytes in byteArray2 from those in byteArray1" | carry a i | carry := 256. i := 1. j to: j + byteArray2 size - 1 do: [:index | a := (byteArray1 at: index) - (byteArray2 at: i) + carry. a < 256 ifTrue: [carry := 255] ifFalse: [carry := 256. a := a - 256]. byteArray1 at: index put: a. i := i + 1] ] bytesLeftShift: aByteArray [ "Private - Left shift by 1 place the bytes in aByteArray" | carry a | carry := 0. 1 to: aByteArray size do: [:index | a := aByteArray at: index. a := a + a + carry. carry := a bitShift: -8. a := a bitAnd: 255. aByteArray at: index put: a] ] bytesLeftShift: aByteArray n: shift [ "Private - Left shift by shift places the bytes in aByteArray (shift <= 7)" | carry a | carry := 0. 1 to: aByteArray size do: [:index | a := aByteArray at: index. a := (a bitShift: shift) + carry. carry := a bitShift: -8. aByteArray at: index put: (a bitAnd: 255)] ] bytesLeftShift: aByteArray big: totalShift [ "Private - Left shift the bytes in aByteArray by totalShift places" | newBytes byteShift shift a last | totalShift = 0 ifTrue: [^self]. byteShift := totalShift // 8. shift := totalShift bitAnd: 7. last := 0. aByteArray size - 1 to: byteShift + 1 by: -1 do: [:index | a := aByteArray at: index - byteShift. a := a bitShift: shift. aByteArray at: index + 1 put: last + (a bitShift: -8). last := a bitAnd: 255]. aByteArray at: byteShift + 1 put: last. 1 to: byteShift do: [:i | aByteArray at: i put: 0] ] bytesRightShift: aByteArray big: totalShift [ "Private - Right shift the bytes in aByteArray by totalShift places" | shift byteShift carryShift x a | totalShift = 0 ifTrue: [^self]. byteShift := totalShift // 8. shift := (totalShift bitAnd: 7) negated. carryShift := 8 + shift. x := (aByteArray at: byteShift + 1) bitShift: shift. byteShift + 2 to: aByteArray size do: [:j | a := aByteArray at: j. aByteArray at: j - byteShift - 1 put: ((a bitShift: carryShift) bitAnd: 255) + x. x := a bitShift: shift]. aByteArray at: aByteArray size - byteShift put: x. aByteArray size - byteShift + 1 to: aByteArray size do: [:i | aByteArray at: i put: 0] ] bytesRightShift: bytes n: aNumber [ "Private - Right shift the bytes in `bytes' by 'aNumber' places (shift <= 7)" | shift carryShift x a | aNumber = 0 ifTrue: [^self]. shift := aNumber negated. carryShift := 8 + shift. x := (bytes at: 1) bitShift: shift. 2 to: bytes size do: [:j | a := bytes at: j. bytes at: j - 1 put: ((a bitShift: carryShift) bitAnd: 255) + x. x := a bitShift: shift]. bytes at: bytes size put: x ] bytesTrailingZeros: bytes [ "Private - Answer the number of trailing zero bits in the receiver" | each | 1 to: bytes size do: [:index | (each := bytes at: index) = 0 ifFalse: [^index * 8 - 8 + (TrailingZeros at: each)]]. ^bytes size * 8 ] primDivide: rhs [ "Private - Implements Knuth's divide and correct algorithm from `Seminumerical Algorithms' 3rd Edition, section 4.3.1 (which is basically an enhanced version of the divide `algorithm' for two-digit divisors which is taught in primary school!!!)" "Leading zeros in `v'" "Cached v at: n, v at: n - 1, j + n, j + n - 1" "Cached `u size - v size' and `v size'" "High 2 bytes of `u'" "guess times the divisor (v)" "Quotient" "guess at the quotient byte and remainder" "The operands" "0. Initialize everything" | d vn vn1 jn jn1 m n high sub q guess rem u v | u := self bytes. v := rhs bytes. n := v size. sub := ByteArray new: n. m := u size - n. q := ByteArray new: m + 2. "1. Normalize the divisor Knuth's algorithm is based on an initial guess for the quotient. The guess is guaranteed to be no more than 2 in error, if v[n] >= 128. If we multiply both vectors by the same value, the result of division remains the same, so we can always guarantee that v[n] is sufficiently large. While the algorithm calls for d to be 255 / v[n], we will set d to a simple left shift count because this is fast and nicely approximates that" [(v at: n) = 0] whileTrue: [n := n - 1]. (v at: n) < 128 ifFalse: [d := 0] ifTrue: ["Multiply each value by the normalizing value" d := LeadingZeros at: (v at: n). self bytesLeftShift: u n: d. self bytesLeftShift: v n: d]. vn := v at: n. "Cache common values" vn1 := v at: n - 1. m + 1 to: 1 by: -1 do: [:j | jn := j + n. jn1 := jn - 1. "2. Calculate the quotient `guess'. Remember that our guess will be generated such that guess - 2 <= quotient <= guess. Thus, we generate our first guess at quotient, and keep decrementing by one until we have found the real quotient." high := (u at: jn) * 256 + (u at: jn1). guess := high // vn. rem := high \\ vn. "(Array with: u with: high with: guess with: rem) printNl." "4. We know now that the quotient guess is most likely ok, but possibly the real quotient is guess - 1 or guess - 2. Multiply the divisor by the guess and compare the result with the dividend." sub replaceFrom: 1 to: sub size with: v startingAt: 1. self bytes: sub multiply: guess. [(self bytes: u from: j compare: sub) >= 0] whileFalse: ["Our guess was one off, so we need to readjust it by one and subtract back the divisor (since we multiplied by one in excess)." guess := guess - 1. self bytes: sub from: 1 subtract: v]. "(Array with: u with: sub with: guess with: rem) printNl." "Got another byte of the quotient" self bytes: u from: j subtract: sub. q at: j put: guess]. "Readjust the remainder" self bytesRightShift: u n: d. ^q -> u ] ] LargePositiveInteger subclass: LargeZeroInteger [ size [ ^0 ] hash [ ^0 ] at: anIndex [ ^0 ] strictlyPositive [ "Answer whether the receiver is > 0" ^false ] sign [ "Answer the receiver's sign" ^0 ] + aNumber [ "Sum the receiver and aNumber, answer the result" ^aNumber ] - aNumber [ "Subtract aNumber from the receiver, answer the result" ^aNumber negated ] * aNumber [ "Multiply aNumber and the receiver, answer the result" ^0 ] / aNumber [ "Divide aNumber and the receiver, answer the result (an Integer or Fraction)" ^0 ] // aNumber [ "Divide aNumber and the receiver, answer the result truncated towards -infinity" ^0 ] rem: aNumber [ "Divide aNumber and the receiver, answer the remainder truncated towards 0" ^0 ] quo: aNumber [ "Divide aNumber and the receiver, answer the result truncated towards 0" ^0 ] \\ aNumber [ "Divide aNumber and the receiver, answer the remainder truncated towards -infinity" ^0 ] replace: str withStringBase: radix [ "Return in a string the base radix representation of the receiver." str at: str size put: $0. ^str ] ] smalltalk-3.2.5/kernel/Link.st0000644000175000017500000000544712123404352013161 00000000000000"====================================================================== | | Link Method Definitions | | ======================================================================" "====================================================================== | | Copyright 1988,92,94,95,99,2000,2001,2002 | Free Software Foundation, Inc. | Written by Steve Byrne. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" Object subclass: Link [ | nextLink | Link class >> nextLink: aLink [ "Create an instance with the given next link" ^self new nextLink: aLink ] at: index [ "Retrieve a node (instance of Link) that is at a distance of `index' after the receiver." | i element | index >= 1 ifTrue: [ i := 1. element := self. [i = index ifTrue: [^element]. i := i + 1. (element := element nextLink) isNil] whileFalse]. SystemExceptions.IndexOutOfRange signalOn: self withIndex: index ] at: index put: object [ self shouldNotImplement ] do: aBlock [ "Evaluate aBlock for each element in the list" | item | item := self. [aBlock value: item. (item := item nextLink) isNil] whileFalse ] size [ "Answer the number of elements in the list. Warning: this is O(n)" | item count | item := self. count := 1. [(item := item nextLink) isNil] whileFalse: [count := count + 1]. ^count ] nextLink [ "Answer the next item in the list" ^nextLink ] nextLink: aLink [ "Set the next item in the list" nextLink := aLink ] ] smalltalk-3.2.5/kernel/Time.st0000644000175000017500000002622412123404352013156 00000000000000"====================================================================== | | Time Method Definitions | | ======================================================================" "====================================================================== | | Copyright 1988,92,94,95,99,2000,2001,2002,2008,2009 | Free Software Foundation, Inc. | Written by Steve Byrne. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" Magnitude subclass: Time [ | seconds | SecondClockAdjustment := nil. ClockOnStartup := nil. ClockOnImageSave := nil. Time class >> utcSecondClock [ "Answer the number of seconds since the midnight of 1/1/1901 (unlike #secondClock, the reference time is here expressed as UTC, that is as Coordinated Universal Time)." ^self secondClock - self timezoneBias ] Time class >> utcNow [ "Answer a time representing the current time of day in Coordinated Universal Time (UTC)" ^self new setSeconds: self utcSecondClock ] Time class >> midnight [ "Answer a time representing midnight in Coordinated Universal Time (UTC)" ^self new setSeconds: 0 ] Time class >> timezoneBias [ "Specifies the current bias, in seconds, for local time translation for the current time. The bias is the difference, in seconds, between Coordinated Universal Time (UTC) and local time; a positive bias indicates that the local timezone is to the east of Greenwich (e.g. Europe, Asia), while a negative bias indicates that it is to the west (e.g. America)" ^self primitiveFailed ] Time class >> timezoneBias: seconds [ "Specifies the bias, in seconds, for local time translation for the given second clock value (0 being midnight of 1/1/1901). The bias is the difference, in seconds, between Coordinated Universal Time (UTC) and local time; a positive bias indicates that the local timezone is to the east of Greenwich (e.g. Europe, Asia), while a negative bias indicates that it is to the west (e.g. America)" ^self primitiveFailed ] Time class >> timezone [ "Answer a String associated with the current timezone (either standard or daylight-saving) on this operating system. For example, the answer could be `EST' to indicate Eastern Standard Time; the answer can be empty and can't be assumed to be a three-character code such as `EST'." ^self primitiveFailed ] Time class >> secondClock [ "Answer the number of seconds since the midnight of 1/1/1901" ^self primSecondClock + SecondClockAdjustment ] Time class >> primSecondClock [ "Returns the number of seconds to/from 1/1/2000." ^self primitiveFailed ] Time class >> nanosecondClock [ "Answer the number of nanoseconds since startup." ^self primNanosecondClock - ClockOnStartup ] Time class >> millisecondClock [ "Answer the number of milliseconds since startup." ^self nanosecondClock // 1000000 ] Time class >> primNanosecondClock [ "Returns the number of milliseconds since midnight." ^self primitiveFailed ] Time class >> initialize [ "Initialize the Time class after the image has been bootstrapped" "(99 * 365 + 25) * 86400 secs/day." SecondClockAdjustment := 86400 * 36159. ClockOnImageSave := 0. ObjectMemory addDependent: self ] Time class >> update: aspect [ "Private - Initialize the receiver's instance variables" | time | aspect == #returnFromSnapshot ifTrue: [ ClockOnStartup := Time primNanosecondClock - ClockOnImageSave]. aspect == #aboutToSnapshot ifTrue: [ ClockOnImageSave := Time nanosecondClock]. ] Time class >> now [ "Answer a time representing the current time of day" "\\ rounds towards -infinity, so it is good for negative numbers too" ^self new setSeconds: self primSecondClock ] Time class >> new [ "Answer a Time representing midnight" ^self basicNew setSeconds: 0 ] Time class >> fromSeconds: secondCount [ "Answer a Time representing secondCount seconds past midnight" ^self new setSeconds: secondCount ] Time class >> hour: h [ "Answer a Time that is the given number of hours past midnight" ^self fromSeconds: h * 3600 ] Time class >> hour: h minute: m second: s [ "Answer a Time that is the given number of hours, minutes and seconds past midnight" ^self fromSeconds: (h * 60 + m) * 60 + s ] Time class >> minute: m [ "Answer a Time that is the given number of minutes past midnight" ^self fromSeconds: m * 60 ] Time class >> second: s [ "Answer a Time that is the given number of seconds past midnight" ^self fromSeconds: s ] Time class >> hours: h [ "Answer a Time that is the given number of hours past midnight" ^self fromSeconds: h * 3600 ] Time class >> hours: h minutes: m seconds: s [ "Answer a Time that is the given number of hours, minutes and seconds past midnight" ^self fromSeconds: (h * 60 + m) * 60 + s ] Time class >> minutes: m [ "Answer a Time that is the given number of minutes past midnight" ^self fromSeconds: m * 60 ] Time class >> seconds: s [ "Answer a Time that is the given number of seconds past midnight" ^self fromSeconds: s ] Time class >> readFrom: aStream [ "Parse an instance of the receiver (hours/minutes/seconds) from aStream" | hms i ch ws | hms := {0. 0. 0}. i := 1. ch := $:. [i <= 3 and: [aStream atEnd not and: [ch isSeparator not]]] whileTrue: [ ws := WriteStream on: (String new: 10). [aStream atEnd not and: [(ch := aStream next) isDigit]] whileTrue: [ws nextPut: ch]. hms at: i put: ws contents asNumber. i := i + 1]. ^self fromSeconds: (hms at: 1) * 3600 + ((hms at: 2) * 60) + (hms at: 3) ] Time class >> nanosecondClockValue [ "Answer the number of milliseconds since startup" ^self primNanosecondClock - ClockOnStartup ] Time class >> millisecondClockValue [ "Answer the number of milliseconds since startup" ^self nanosecondClockValue // 1000000 ] Time class >> millisecondsPerDay [ "Answer the number of milliseconds in a day" ^86400000 ] Time class >> millisecondsToRun: timedBlock [ "Answer the number of milliseconds which timedBlock took to run" | startTime | startTime := self millisecondClock. timedBlock value. ^self millisecondClock - startTime ] asNanoseconds [ ^seconds * 1000000000 ] asMilliseconds [ ^seconds * 1000 ] asSeconds [ ^seconds ] hours [ "Answer the number of hours in the receiver" ^(seconds quo: 3600) rem: 24 ] minutes [ "Answer the number of minutes in the receiver" ^(seconds quo: 60) rem: 60 ] seconds [ "Answer the number of seconds in the receiver" ^seconds rem: 60 ] hour [ "Answer the number of hours in the receiver" ^seconds // 3600 \\ 24 ] hour12 [ "Answer the hour in a 12-hour clock" | h | h := self hour \\ 12. ^h = 0 ifTrue: [12] ifFalse: [h] ] hour24 [ "Answer the hour in a 24-hour clock" ^self hour ] minute [ "Answer the number of minutes in the receiver" ^seconds // 60 \\ 60 ] second [ "Answer the number of seconds in the receiver" ^seconds \\ 60 ] = aTime [ "Answer whether the receiver is equal to aTime" ^self class == aTime class and: [seconds = aTime asSeconds] ] < aTime [ "Answer whether the receiver is less than aTime" ^seconds < aTime asSeconds ] hash [ "Answer an hash value for the receiver" ^seconds ] addSeconds: timeAmount [ "Answer a new Time that is timeAmount seconds after the receiver" ^Time new setSeconds: seconds + timeAmount ] addTime: timeAmount [ "Answer a new Time that is timeAmount seconds after the receiver; timeAmount is a Time." ^Time new setSeconds: seconds + timeAmount asSeconds ] subtractTime: timeAmount [ "Answer a new Time that is timeAmount seconds before the receiver; timeAmount is a Time." ^Time new setSeconds: seconds - timeAmount asSeconds ] printOn: aStream [ "Print a representation of the receiver on aStream" self hours printOn: aStream. aStream nextPut: $:. self minutes < 10 ifTrue: [aStream nextPut: $0]. self minutes printOn: aStream. aStream nextPut: $:. self seconds < 10 ifTrue: [aStream nextPut: $0]. self seconds printOn: aStream ] setSeconds: secs [ seconds := secs \\ 86400 ] ] smalltalk-3.2.5/kernel/CCallback.st0000644000175000017500000000443312123404352014055 00000000000000"====================================================================== | | CCallbackDescriptor Method Definitions | | ======================================================================" "====================================================================== | | Copyright 2008, 2009 Free Software Foundation, Inc. | Written by Paolo Bonzini. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" CCallable subclass: CCallbackDescriptor [ | block | CCallbackDescriptor class >> for: aBlock returning: returnTypeSymbol withArgs: argsArray [ "Answer a CCallbackDescriptor with the given block, return type and arguments." ^(super for: nil returning: returnTypeSymbol withArgs: argsArray) block: aBlock; link; yourself ] block [ "Answer the block of the function represented by the receiver." ^block ] block: aBlock [ "Set the block of the function represented by the receiver." block := aBlock ] link [ "Make the address of the function point to the registered address." "Always executed." self addToBeFinalized ] ] smalltalk-3.2.5/kernel/FileSegment.st0000644000175000017500000001324712123404352014463 00000000000000"====================================================================== | | FileSegment Method Definitions | | ======================================================================" "====================================================================== | | Copyright 1988,92,94,95,99,2000,2001,2002,2006,2007,2008 | Free Software Foundation, Inc. | Written by Steve Byrne. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" Object subclass: FileSegment [ | file startPos size | FileSegment class >> relocate [ "Remove the kernel path from all paths that start with it. Needed to support $(DESTDIR) and relocatable installation." | map startPath startPathString | map := IdentityDictionary new. startPath := Directory kernel asString. self allInstancesDo: [:each | each relocateFrom: startPath map: map]. Directory kernel = Directory systemKernel ifTrue: [KernelFilePath := nil]. ] FileSegment class >> on: aFile startingAt: startPos for: sizeInteger [ "Create a new FileSegment referring to the contents of the given file, from the startPos-th byte and for sizeInteger bytes. Note that FileSegments should always be created with full paths because relative paths are interpreted to be relative to the kernel directory." ^self new setFile: aFile start: startPos size: sizeInteger ] copyFrom: from to: to [ "Answer a String containing the given subsegment of the file. As for streams, from and to are 0-based." (to between: 0 and: size - 1) ifFalse: [^SystemExceptions.ArgumentOutOfRange signalOn: to mustBeBetween: 0 and: size - 1]. (from between: 0 and: to) ifFalse: [(from = to) + 1 ifTrue: [^self species new]. ^SystemExceptions.ArgumentOutOfRange signalOn: from mustBeBetween: 0 and: to + 1]. ^self withFileDo: [:fileStream | fileStream copyFrom: startPos + from to: startPos + to] ] asString [ "Answer a String containing the required segment of the file" ^self withFileDo: [:fileStream | fileStream copyFrom: startPos to: startPos + size - 1] ] relocateFrom: startPath map: map [ "If the path starts with startPath, remove that part of the path. map is a Dictionary that is used so that equal filenames stay equal, without increasing the amount of memory that the image uses." file := map at: self fileName ifAbsent: [(self fileName startsWith: startPath) ifTrue: [map at: self fileName put: (file copyFrom: startPath size + 2)] ifFalse: [file]] ] withFileDo: aBlock [ "Evaluate aBlock passing it the FileStream in which the segment identified by the receiver is stored" ^self file withReadStreamDo: aBlock ] file [ "Answer the File object for the file containing the segment" | f | f := file asFile. f isRelative ifTrue: [ f := Directory kernel / file ]. ^f ] printedFileName [ "Answer a printed representation of the file containing the segment. While introducing some ambiguity, this representation is compact eliminates the path for kernel files, and produces a relative path from the current working directory for other files." | f | f := file asFile. f isRelative ifTrue: [ ^f stripPath asString ]. f isFileSystemPath ifFalse: [ ^'%1/%2' % { f archive displayString copyAfterLast: $/. f name } ]. ^(f pathFrom: Directory working) asString ] fileName [ "Answer the name of the file containing the segment" ^file asString ] filePos [ "Answer the position in the file where the segment starts" ^startPos ] size [ "Answer the length of the segment" ^size ] = aFileSegment [ "Answer whether the receiver and aFileSegment are equal." (aFileSegment isKindOf: FileSegment) ifFalse: [^false]. self == aFileSegment ifTrue: [^true]. ^self fileName = aFileSegment fileName and: [startPos = aFileSegment filePos and: [size = aFileSegment size]] ] hash [ "Answer an hash value for the receiver." ^self fileName hash bitXor: startPos + size ] species [ ^String ] getFile [ ^file ] setFile: aFileName start: startingPos size: sizeInteger [ file := aFileName. startPos := startingPos. size := sizeInteger ] ] smalltalk-3.2.5/kernel/Message.st0000644000175000017500000000763612123404352013652 00000000000000"====================================================================== | | Message Method Definitions | | ======================================================================" "====================================================================== | | Copyright 1988,92,94,95,99,2000,2001,2008 | Free Software Foundation, Inc. | Written by Steve Byrne. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" Object subclass: Message [ | selector args | since their syntax is isomorphic to that of a message send.'> Message class >> selector: aSymbol argument: anObject [ "Create a new Message with the given selector and argument" ^(self new) selector: aSymbol; arguments: { anObject } ] Message class >> selector: aSymbol arguments: anArray [ "Create a new Message with the given selector and arguments" ^(self new) selector: aSymbol; arguments: anArray ] printAsAttributeOn: aStream [ "Print a representation of the receiver on aStream, modeling it after the source code for a attribute." aStream nextPut: $<. (self selector includes: $:) ifFalse: [aStream nextPutAll: self selector. self arguments do: [:arg | aStream store: arg]] ifTrue: [(self selector substrings: $:) with: self arguments do: [:sel :arg | aStream nextPutAll: sel; nextPutAll: ': '; store: arg; nextPut: $ ]]. aStream nextPut: $> ] printOn: aStream [ "Print a representation of the receiver on aStream" (self selector includes: $:) ifFalse: [aStream nextPutAll: self selector. self arguments do: [:arg | aStream nextPutAll: ' <'; print: arg; nextPutAll: '> ']] ifTrue: [(self selector substrings: $:) with: self arguments do: [:sel :arg | aStream nextPutAll: sel; nextPutAll: ': <'; print: arg; nextPutAll: '> ']] ] sendTo: aReceiver [ "Resend to aReceiver" ^aReceiver perform: selector withArguments: args ] reinvokeFor: aReceiver [ "Resend to aReceiver - present for compatibility" ^aReceiver perform: selector withArguments: args ] selector: aSymbol [ "Set the receiver's selector" selector := aSymbol ] arguments: anArray [ "Set the receiver's arguments" args := anArray ] selector [ "Answer the receiver's selector" ^selector ] argument [ "Answer the first of the receiver's arguments" ^args at: 1 ] arguments [ "Answer the receiver's arguments" ^args ] ] smalltalk-3.2.5/kernel/WriteStream.st0000644000175000017500000001203412123404352014520 00000000000000"====================================================================== | | WriteStream Method Definitions | | ======================================================================" "====================================================================== | | Copyright 1988,92,94,95,99,2000,2001,2002,2006,2007,2009 | Free Software Foundation, Inc. | Written by Steve Byrne. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" PositionableStream subclass: WriteStream [ WriteStream class >> on: aCollection [ "Answer a new instance of the receiver which streams on aCollection. Every item of aCollection is discarded." ^(self basicNew initCollection: aCollection) beWriteOnly; truncate; yourself ] WriteStream class >> with: aCollection [ "Answer a new instance of the receiver which streams from the end of aCollection." ^(self basicNew initCollection: aCollection) beWriteOnly; moveToEnd; yourself ] WriteStream class >> with: aCollection from: firstIndex to: lastIndex [ "Answer a new instance of the receiver which streams from the firstIndex-th item of aCollection to the lastIndex-th. The pointer is moved to the last item in that range." ^self with: (aCollection copyFrom: firstIndex to: lastIndex) ] contents [ "Returns a collection of the same type that the stream accesses, up to and including the final element." ^collection copyFrom: 1 to: ptr - 1 ] nextPut: anObject [ "Store anObject as the next item in the receiver. Grow the collection if necessary" "(access bitAnd: 2) = 0 ifTrue: [ ^self shouldNotImplement ]." ptr > endPtr ifTrue: [ptr > collection size ifTrue: [self growCollection]. endPtr := ptr]. collection at: ptr put: anObject. ptr := ptr + 1. ^anObject ] next: n putAll: aCollection startingAt: pos [ "Put n characters or bytes of aCollection, starting at the pos-th, in the collection buffer." | end | end := ptr + n. end > collection size ifTrue: [ self growCollectionTo: end - 1]. collection replaceFrom: ptr to: end - 1 with: aCollection startingAt: pos. ptr := end. ptr > endPtr ifTrue: [endPtr := ptr - 1] ] readStream [ "Answer a ReadStream on the same contents as the receiver" ^ReadStream on: collection from: 1 to: ptr - 1 ] reverseContents [ "Returns a collection of the same type that the stream accesses, up to and including the final element, but in reverse order." | newCollection | newCollection := self species new: ptr - 1. 1 to: endPtr do: [:i | newCollection at: i put: (collection at: ptr - i)]. ^newCollection ] emptyStream [ "Extension - Reset the stream" ptr := 1. endPtr := 0 ] initCollection: aCollection [ collection := aCollection. ptr := 1. endPtr := 0 ] moveToEnd [ endPtr := collection size. ptr := endPtr + 1 ] growCollection [ "Private - Double the size of the collection or, if its size < 8, grow it to 8 places" | size | size := collection size. "Guess which collection is which :-)" collection := (collection copyEmpty: (size * 2 max: 8)) replaceFrom: 1 to: collection size with: collection startingAt: 1; yourself ] growCollectionTo: n [ "Private - Double the size of the collection or, if its size < 8, grow it to 8 places" | size | n <= (size := collection size) ifTrue: [ ^self ]. size * 2 > n ifTrue: [ ^self growCollection ]. "Guess which collection is which :-)" collection := (collection copyEmpty: n) replaceFrom: 1 to: collection size with: collection startingAt: 1; yourself ] ] smalltalk-3.2.5/kernel/ReadStream.st0000644000175000017500000000456612123404352014314 00000000000000"====================================================================== | | ReadStream Method Definitions | | ======================================================================" "====================================================================== | | Copyright 1988,92,94,95,99,2000,2001,2006 | Free Software Foundation, Inc. | Written by Steve Byrne. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" PositionableStream subclass: ReadStream [ ReadStream class >> on: aCollection [ "Answer a new stream working on aCollection from its start." ^(self basicNew initCollection: aCollection limit: aCollection size) beReadOnly ] ReadStream class >> on: aCollection from: firstIndex to: lastIndex [ "Answer an instance of the receiver streaming from the firstIndex-th item of aCollection to the lastIndex-th" firstIndex = 1 ifFalse: [^super on: aCollection from: firstIndex to: lastIndex]. lastIndex > aCollection size ifTrue: [^SystemExceptions.IndexOutOfRange signalOn: self withIndex: lastIndex]. ^(self basicNew initCollection: aCollection limit: lastIndex) beReadOnly ] initCollection: aCollection limit: anInteger [ collection := aCollection. ptr := 1. endPtr := anInteger ] ] smalltalk-3.2.5/kernel/Rectangle.st0000644000175000017500000003774412123404352014175 00000000000000"======================================================================== | | Rectangle Class | | ========================================================================" "====================================================================== | | Copyright 1988,92,94,95,99,2000,2001,2002,2006,2008 | Free Software Foundation, Inc. | Written by Doug McCallum. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" Object subclass: Rectangle [ | origin corner | Rectangle class >> new [ "Answer the (0 @ 0 corner: 0 @ 0) rectangle" ^self origin: 0 @ 0 corner: 0 @ 0 ] Rectangle class >> origin: originPoint corner: cornerPoint [ "Answer a rectangle with the given corners" ^self basicNew origin: originPoint corner: cornerPoint ] Rectangle class >> origin: originPoint extent: extentPoint [ "Answer a rectangle with the given origin and size" ^self basicNew origin: originPoint corner: originPoint + extentPoint ] Rectangle class >> left: leftNumber right: rightNumber top: topNumber bottom: bottomNumber [ "Answer a rectangle with the given coordinates" ^self basicNew origin: (Point x: leftNumber y: topNumber) corner: (Point x: rightNumber y: bottomNumber) ] Rectangle class >> left: leftNumber top: topNumber right: rightNumber bottom: bottomNumber [ "Answer a rectangle with the given coordinates" ^self basicNew origin: (Point x: leftNumber y: topNumber) corner: (Point x: rightNumber y: bottomNumber) ] bottom [ "Answer the corner's y of the receiver" ^corner y ] bottom: aNumber [ "Set the corner's y of the receiver" corner y: aNumber ] bottomCenter [ "Answer the center of the receiver's bottom side" ^self xCenter @ corner y ] bottomLeft [ "Answer the bottom-left corner of the receiver" ^origin x @ corner y ] bottomLeft: aPoint [ "Answer the receiver with the bottom-left changed to aPoint" origin x: aPoint x. corner y: aPoint y ] bottomRight [ "Answer the bottom-right corner of the receiver" ^corner copy ] bottomRight: aPoint [ "Change the bottom-right corner of the receiver" corner := aPoint copy ] center [ "Answer the center of the receiver" ^self xCenter @ self yCenter ] corner [ "Answer the corner of the receiver" ^corner ] corner: aPoint [ "Set the corner of the receiver" corner := aPoint ] extent [ "Answer the extent of the receiver" ^corner - origin ] extent: aPoint [ "Change the size of the receiver, keeping the origin the same" corner := origin + aPoint ] height [ "Answer the height of the receiver" ^self bottom - self top ] height: aNumber [ "Set the height of the receiver" corner y: self origin y + aNumber ] left [ "Answer the x of the left edge of the receiver" ^origin x ] left: aValue [ "Set the x of the left edge of the receiver" origin x: aValue ] left: l top: t right: r bottom: b [ "Change all four the coordinates of the receiver's corners" origin := l @ t. corner := r @ b ] leftCenter [ "Answer the center of the receiver's left side" ^origin x @ self yCenter ] origin [ "Answer the top-left corner of the receiver" ^origin ] origin: aPoint [ "Change the top-left corner of the receiver to aPoint" origin := aPoint copy ] origin: pnt1 corner: pnt2 [ "Change both the origin (top-left corner) and the corner (bottom-right corner) of the receiver" origin := pnt1 copy. corner := pnt2 copy ] origin: pnt1 extent: pnt2 [ "Change the top-left corner and the size of the receiver" origin := pnt1 copy. corner := pnt1 + pnt2 ] right [ "Answer the x of the bottom-right corner of the receiver" ^corner x ] right: aNumber [ "Change the x of the bottom-right corner of the receiver" corner x: aNumber ] rightCenter [ "Answer the center of the receiver's right side" ^corner x @ self yCenter ] top [ "Answer the y of the receiver's top-left corner" ^origin y ] top: aValue [ "Change the y of the receiver's top-left corner" origin y: aValue ] topCenter [ "Answer the center of the receiver's top side" ^self xCenter @ origin y ] topLeft [ "Answer the receiver's top-left corner" ^origin copy ] topLeft: aPoint [ "Change the receiver's top-left corner's coordinates to aPoint" origin := aPoint copy ] topRight [ "Answer the receiver's top-right corner" ^corner x @ origin y ] topRight: aPoint [ "Change the receiver's top-right corner to aPoint" corner x: aPoint x. origin y: aPoint y ] width [ "Answer the receiver's width" ^self right - self left ] width: aNumber [ "Change the receiver's width to aNumber" corner x: origin x + aNumber ] containsPoint: aPoint [ "Answer true if aPoint is equal to, or below and to the right of, the receiver's origin; and aPoint is above and to the left of the receiver's corner" ^aPoint >= origin and: [aPoint < corner] ] contains: aRectangle [ "Answer true if the receiver contains (see containsPoint:) both aRectangle's origin and aRectangle's corner" ^(self containsPoint: aRectangle origin) and: [self containsPoint: aRectangle corner] ] intersects: aRectangle [ "Answer true if the receiver intersect aRectangle, i.e. if it contains (see containsPoint:) any of aRectangle corners or if aRectangle contains the receiver" | selfNorm rectNorm left top right bottom | selfNorm := self normalized. rectNorm := aRectangle normalized. right := selfNorm right min: rectNorm right. left := selfNorm left max: rectNorm left. right <= left ifTrue: [^false]. bottom := selfNorm bottom min: rectNorm bottom. top := selfNorm top max: rectNorm top. ^bottom > top ] = aRectangle [ "Answer whether the receiver is equal to aRectangle" ^self class == aRectangle class and: [origin = aRectangle origin and: [corner = aRectangle corner]] ] hash [ "Answer an hash value for the receiver" ^origin hash bitXor: corner hash ] amountToTranslateWithin: aRectangle [ "Answer a Point so that if aRectangle is translated by that point, its origin lies within the receiver's." (aRectangle contains: self) ifTrue: [^0 @ 0]. ^aRectangle origin - origin ] translatedToBeWithin: aRectangle [ "Answer a copy of the receiver that does not extend beyond aRectangle." ^self translateBy: (self amountToTranslateWithin: aRectangle) ] area [ "Answer the receiver's area. The area is the width times the height, so it is possible for it to be negative if the rectangle is not normalized." ^self width * self height ] areasOutside: aRectangle [ "Answer a collection of rectangles containing the parts of the receiver outside of aRectangle. For all points in the receiver, but outside aRectangle, exactly one rectangle in the collection will contain that point." "The basic algorithm is to first determine that there is an intersection by finding the overlapping rectangle. From the overlapping rectangle, determine which edges it runs along. For each edge, if it doesn't run along that edge, add a new rectangle to the collection. Most times 2 or 3 rectangles get formed, some times 0, 1 or 4." | ansSet l t r b xsect | xsect := self intersect: aRectangle. xsect area = 0 ifTrue: [^{self copy}]. ansSet := Set new: 8. l := self left min: self right. r := self left max: self right. t := self top min: self bottom. b := self top max: self bottom. l = xsect left ifFalse: [ansSet add: (l @ t corner: xsect left @ b)]. t = xsect top ifFalse: [ansSet add: (xsect left @ t corner: xsect topRight)]. b = xsect bottom ifFalse: [ansSet add: (xsect bottomLeft corner: xsect right @ b)]. r = xsect right ifFalse: [ansSet add: (xsect right @ t corner: r @ b)]. ^ansSet asArray ] expandBy: delta [ "Answer a new rectangle that is the receiver expanded by aValue: if aValue is a rectangle, calculate origin=origin-aValue origin, corner=corner+aValue corner; else calculate origin=origin-aValue, corner=corner+aValue." (delta isMemberOf: Point) ifTrue: [^Rectangle origin: origin - delta corner: corner + delta]. (delta isMemberOf: Rectangle) ifTrue: [^Rectangle origin: origin - delta origin corner: corner + delta corner]. (delta isKindOf: Number) ifTrue: [^Rectangle left: origin x - delta right: corner x + delta top: origin y - delta bottom: corner y + delta]. SystemExceptions.WrongClass signalOn: delta mustBe: #(#{Point} #{Rectangle} #{Number}) ] insetBy: delta [ "Answer a new rectangle that is the receiver inset by aValue: if aValue is a rectangle, calculate origin=origin+aValue origin, corner=corner-aValue corner; else calculate origin=origin+aValue, corner=corner-aValue." (delta isMemberOf: Point) ifTrue: [^Rectangle origin: origin + delta corner: corner - delta]. (delta isMemberOf: Rectangle) ifTrue: [^Rectangle origin: origin + delta origin corner: corner - delta corner]. (delta isKindOf: Number) ifTrue: [^Rectangle left: origin x + delta right: corner x - delta top: origin y + delta bottom: corner y - delta]. SystemExceptions.WrongClass signalOn: delta mustBe: #(#{Point} #{Rectangle} #{Number}) ] insetOriginBy: originDelta corner: cornerDelta [ "Answer a new rectangle that is the receiver inset so that origin=origin+originDelta, corner=corner-cornerDelta. The deltas can be points or numbers" ^Rectangle origin: origin + originDelta corner: corner - cornerDelta ] merge: aRectangle [ "Answer a new rectangle which is the smallest rectangle containing both the receiver and aRectangle." ^Rectangle origin: (origin min: aRectangle origin) corner: (corner max: aRectangle corner) ] intersect: aRectangle [ "Answers the rectangle (if any) created by the overlap of rectangles A and B. Answers nil if the rectangles do not overlap" | selfNorm rectNorm left top right bottom | selfNorm := self normalized. rectNorm := aRectangle normalized. right := selfNorm right min: rectNorm right. left := selfNorm left max: rectNorm left. right <= left ifTrue: [^nil]. bottom := selfNorm bottom min: rectNorm bottom. top := selfNorm top max: rectNorm top. bottom <= top ifTrue: [^nil]. ^Rectangle origin: left @ top corner: right @ bottom ] copy [ "Return a deep copy of the receiver for safety." ^self deepCopy ] printOn: aStream [ "Print a representation of the receiver on aStream" aStream print: origin; nextPutAll: ' corner: '; print: corner ] storeOn: aStream [ "Store Smalltalk code compiling to the receiver on aStream" aStream nextPutAll: '(Rectangle origin: '; store: origin; nextPutAll: ' corner: '; store: corner; nextPut: $) ] normalize [ "Normalize the receiver (make origin < corner)" | temp | self right > self left ifTrue: [temp := self left. origin x: corner x. corner x: temp]. self bottom > self top ifTrue: [temp := self top. origin y: corner y. corner y: temp] ] normalized [ "Answer the receiver if it is normalized, otherwise create and return a copy which is normalized (has origin < corner)" (self right > self left and: [self bottom > self top]) ifTrue: [^self]. ^Rectangle origin: (origin min: corner) corner: (origin max: corner) ] xCenter [ "Answer the x of the receiver's center" ^(origin x + corner x) / 2 ] yCenter [ "Answer the y of the receiver's center" ^(origin y + corner y) / 2 ] rounded [ "Answer a copy of the receiver with the coordinates rounded to the nearest integers" ^Rectangle origin: origin rounded corner: corner rounded ] moveBy: aPoint [ "Change the receiver so that the origin and corner are shifted by aPoint" origin := origin + aPoint. corner := corner + aPoint ] moveTo: aPoint [ "Change the receiver so that the origin moves to aPoint and the size remains unchanged" | diff | diff := aPoint - origin. origin := aPoint copy. corner := corner + diff ] scaleBy: scale [ "Answer a copy of the receiver in which the origin and corner are multiplied by scale" ^Rectangle origin: origin * scale corner: corner * scale ] translateBy: factor [ "Answer a copy of the receiver in which the origin and corner are shifted by aPoint" ^Rectangle origin: origin + factor corner: corner + factor ] ] Number extend [ asRectangle [ "Answer an empty rectangle whose origin is (self asPoint)" ^Rectangle left: self top: self right: self bottom: self ] ] Point extend [ asRectangle [ "Answer an empty rectangle whose origin is self" ^Rectangle origin: self corner: self copy ] corner: aPoint [ "Answer a Rectangle whose origin is the receiver and whose corner is aPoint" ^Rectangle origin: self corner: aPoint ] extent: aPoint [ "Answer a Rectangle whose origin is the receiver and whose extent is aPoint" ^Rectangle origin: self extent: aPoint ] ] smalltalk-3.2.5/kernel/Autoload.st0000644000175000017500000001471612123404352014033 00000000000000"====================================================================== | | File autoloading mechanism | | ======================================================================" "====================================================================== | | Copyright 1991,1992,94,95,99,2000,2001,2002,2008 | Free Software Foundation, Inc. | Written by Steve Byrne. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" Kernel.PackageInfo extend [ autoload [ self fileIn ] ] FilePath extend [ autoload [ self withReadStreamDo: [:rs | rs fileIn ] ] ] Namespace current: Kernel [ nil subclass: AutoloadClass [ "Warning: instance variable indices appear below in #class:in:from:" | superClass methodDictionary instanceSpec subClasses instanceVariables environment name loader | AutoloadClass class >> class: nameSymbol in: aNamespace loader: anObject [ | autoload behavior newClass | "Create the metaclass and its sole instance" behavior := Behavior new superclass: Autoload. "Turn the metaclass into an instance of AutoloadClass. To do this we create a `prototype' in the form of an array..." newClass := Array new: Kernel.AutoloadClass allInstVarNames size. 1 to: behavior class instSize do: [:i | newClass at: i put: (behavior instVarAt: i)]. newClass at: 6 put: aNamespace; at: 7 put: nameSymbol; at: 8 put: anObject. "... and change its class magically after it is initialized." newClass changeClassTo: Kernel.AutoloadClass. "Now create the instance. We go through some hops because of the very limited set of messages that these classes know about." autoload := behavior new. behavior become: newClass. ^autoload ] name [ "Answer the name of the class to be autoloaded" ^name ] environment [ "Answer the namespace in which the class will be autoloaded" ^environment ] doesNotUnderstand: aMessage [ "Load the class and resend the message to its metaclass." ^aMessage reinvokeFor: self loadedMetaclass_ ] loadedMetaclass_ [ "File-in the file and answer the metaclass for the new value of the association which held the receiver" ^self loadedClass_ class ] loadedClass_ [ "File-in the file and answer the new value of the association which held the receiver" | class saveLoader | loader isNil ifFalse: [saveLoader := loader. loader := nil. environment at: name put: nil. saveLoader autoload]. class := environment at: name ifAbsent: [nil]. class isNil ifTrue: [ ^Autoload error: '%1 should have defined class %2.%3 but didn''t' % {saveLoader. environment. name asString}]. ^class ] ] ] nil subclass: Autoload [ Autoload class >> class: nameSymbol from: fileNameString [ "Make Smalltalk automatically load the class named nameSymbol from fileNameString when needed" ^self class: nameSymbol in: Namespace current from: fileNameString ] Autoload class >> class: nameSymbol loader: anObject [ "Make Smalltalk automatically load the class named nameSymbol. When the class is needed, anObject will be sent #autoload. By default, instances of FilePath and Package can be used." ^self class: nameSymbol in: Namespace current loader: anObject ] Autoload class >> class: nameSymbol in: aNamespace from: fileNameString [ "Make Smalltalk automatically load the class named nameSymbol and residing in aNamespace from fileNameString when needed" | file | "Check if the file exists." file := fileNameString asFile. file withReadStreamDo: [ :rs | ]. "Turn the metaclass into an instance of AutoloadClass. To do this we create a `prototype' in the form of an array and then..." ^self class: nameSymbol in: aNamespace loader: file ] Autoload class >> class: nameSymbol in: aNamespace loader: anObject [ "Make Smalltalk automatically load the class named nameSymbol and residing in aNamespace. When the class is needed, anObject will be sent #autoload. By default, instances of FilePath and Package can be used." | autoload | autoload := Kernel.AutoloadClass class: nameSymbol in: aNamespace loader: anObject. ^aNamespace at: nameSymbol put: autoload ] class [ "We need it to access the metaclass instance, because that's what will load the file." ] doesNotUnderstand: aMessage [ "Load the class and resend the message to it" ^aMessage reinvokeFor: self class loadedClass_ ] ] smalltalk-3.2.5/kernel/MethodInfo.st0000644000175000017500000000675012123404352014316 00000000000000"====================================================================== | | MethodInfo Method Definitions | | ======================================================================" "====================================================================== | | Copyright 1988,92,94,95,99,2000,2001,2002,2003 | Free Software Foundation, Inc. | Written by Steve Byrne. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" Object subclass: MethodInfo [ | sourceCode category class selector | category [ "Answer the method category" category isNil ifTrue: [category := 'still unclassified']. ^category ] category: aCategory [ "Set the method category" category := aCategory ] methodClass [ "Answer the class in which the method is defined" ^class ] methodClass: aClass [ "Set the class in which the method is defined" class := aClass ] selector [ "Answer the selector through which the method is called" ^selector ] selector: aSymbol [ "Set the selector through which the method is called" selector := aSymbol ] stripSourceCode [ "Remove the reference to the source code for the method" sourceCode := nil ] sourceCode [ "Answer a FileSegment or String or nil containing the method source code" ^sourceCode ] sourceString [ "Answer a String containing the method source code" ^sourceCode asString ] sourceFile [ "Answer the name of the file where the method source code is" ^sourceCode fileName ] sourcePos [ "Answer the starting position of the method source code in the sourceFile" ^sourceCode filePos ] = aMethodInfo [ "Compare the receiver and aMethodInfo, answer whether they're equal" self class == aMethodInfo class ifFalse: [^false]. self == aMethodInfo ifTrue: [^true]. self sourceString = aMethodInfo sourceString ifFalse: [^false]. ^category = aMethodInfo category ] hash [ "Answer an hash value for the receiver" ^sourceCode hash bitXor: category hash ] setSourceCode: source [ sourceCode := source ] ] smalltalk-3.2.5/kernel/SortCollect.st0000644000175000017500000005065412130343734014525 00000000000000"====================================================================== | | SortedCollection Method Definitions | | ======================================================================" "====================================================================== | | Copyright 1988,89,90,91,92,94,95,99,2000,2001,2002,2006,2008 | Free Software Foundation, Inc. | Written by Steve Byrne and Paolo Bonzini. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" OrderedCollection subclass: SortedCollection [ | lastOrdered sorted sortBlock | DefaultSortBlock := nil. Marker := nil. SortedCollection class >> defaultSortBlock [ "Answer a default sort block for the receiver." "This is a clean block, so a single BlockClosure is used all the time." ^[:a :b | a <= b] ] SortedCollection class >> new [ "Answer a new collection with a default size and sort block" ^self sortBlock: self defaultSortBlock ] SortedCollection class >> new: aSize [ "Answer a new collection with a default sort block and the given size" ^(super new: aSize) setSortBlock: self defaultSortBlock ] SortedCollection class >> sortBlock: aSortBlock [ "Answer a new collection with a default size and the given sort block" ^super new setSortBlock: aSortBlock ] addFirst: anObject [ self shouldNotImplement ] addLast: anObject [ self shouldNotImplement ] at: index put: anObject [ self shouldNotImplement ] add: anObject afterIndex: i [ self shouldNotImplement ] addAll: aCollection afterIndex: i [ self shouldNotImplement ] addAllFirst: aCollection [ self shouldNotImplement ] addAllLast: aCollection [ self shouldNotImplement ] last [ "Answer the last item of the receiver" lastOrdered = lastIndex ifFalse: [sorted ifTrue: [self merge] ifFalse: [self makeHeap]]. ^sorted ifTrue: [self basicAt: lastIndex] ifFalse: [self basicAt: firstIndex] ] removeLast [ "Remove an object from the end of the receiver. Fail if the receiver is empty" lastOrdered = lastIndex ifFalse: [sorted ifTrue: [self merge] ifFalse: [self makeHeap]]. sorted ifFalse: [self percolateDown]. ^self basicRemoveLast ] sort [ "Sort the contents of the receiver according to the given sort block, which accepts pair of items and returns true if the first item is less than the second one. Fails if the collections's sort block is not the same as the default sort block." self sortBlock == self class defaultSortBlock ifTrue: [^self]. self shouldNotImplement ] sort: sortBlock [ "Sort the contents of the receiver according to the given sort block, which accepts pair of items and returns true if the first item is less than the second one. Fails if the sort block is not the same as the collection's sort block." self sortBlock == sortBlock ifTrue: [^self]. self shouldNotImplement ] sortBlock [ "Answer the receiver's sort criteria" ^sortBlock ] sortBlock: aSortBlock [ "Change the sort criteria for a sorted collection, resort the elements of the collection, and return it." sortBlock := aSortBlock fixTemps. self sortFrom: firstIndex to: lastIndex. sorted := true. lastOrdered := lastIndex. ^self ] postLoad [ "Restore the default sortBlock if it is nil" sortBlock isNil ifTrue: [sortBlock := self class defaultSortBlock] ] preStore [ "Store the default sortBlock as nil" sortBlock == self class defaultSortBlock ifTrue: [sortBlock := nil] ] beConsistent [ "Prepare the receiver to be walked through with #do: or another enumeration method." lastOrdered < firstIndex ifTrue: [self sortFrom: firstIndex to: lastIndex. sorted := true. lastOrdered := lastIndex. ^self]. lastOrdered = lastIndex ifFalse: [sorted ifTrue: [self merge] ifFalse: [self makeHeap]]. sorted ifFalse: [self sortHeap] ] indexOf: anObject startingAt: index ifAbsent: aBlock [ "Answer the first index > anIndex which contains anElement. Invoke exceptionBlock and answer its result if no item is found" | i j | index < 1 | (index > self size) ifTrue: ["If index is just past the end of the collection, don't raise an error (this is the most generic solution that avoids that #indexOf: fails when the collection is empty." index = (self size + 1) ifTrue: [^aBlock value] ifFalse: [^self checkIndexableBounds: index]]. self beConsistent. i := self binarySearch: anObject low: index + firstIndex - 1 high: lastIndex. i isNil ifTrue: [^aBlock value]. j := i - firstIndex + 1. [j ~= index and: [(self basicAt: i - 1) = anObject]] whileTrue: [i := i - 1. j := j - 1]. ^j ] includes: anObject [ "Private - Answer whether the receiver includes an item which is equal to anObject" self beConsistent. ^(self binarySearch: anObject low: firstIndex high: lastIndex) notNil ] occurrencesOf: anObject [ "Answer how many occurrences of anObject can be found in the receiver" "Find first the index of 'anObject' and then look at the both sides to count repetitions of 'anObject', if there are." | upper lower max count | self beConsistent. upper := self binarySearch: anObject low: firstIndex high: lastIndex. upper isNil ifTrue: [^0]. lower := upper - 1. max := self size. [lower > 1 and: [(self at: lower) = anObject]] whileTrue: [lower := lower - 1]. [upper < max and: [(self at: upper) = anObject]] whileTrue: [upper := upper + 1]. ^upper - lower - 1 ] copyEmpty: newSize [ "Answer an empty copy of the receiver, with the same sort block as the receiver" ^(super copyEmpty: newSize) setSortBlock: sortBlock ] basicRemoveAtIndex: anIndex [ "Remove the object at index anIndex from the receiver. Fail if the index is out of bounds." | answer | answer := super basicRemoveAtIndex: anIndex. "Ensure the invariant that lastOrdered <= lastIndex, otherwise remove+add would leave lastIndex = lastOrdered even if the add was done out of order. Unlike lastOrdered := lastOrdered - 1, this works even if there was an exception and execution resumed here." lastOrdered := lastIndex. ^answer ] copyEmptyForCollect: size [ "Answer an empty copy of the receiver, with the class answered by the collect: method." ^OrderedCollection new: size ] copyEmptyForCollect [ "Answer an empty copy of the receiver, with the class answered by the collect: method." ^OrderedCollection new: self basicSize ] initIndices [ firstIndex := 1. lastIndex := 0. sorted := false. lastOrdered := 0 ] makeRoomLastFor: n [ "Private - Make room for n elements at the end of the collection" lastIndex + n > self basicSize ifTrue: [self growBy: (n max: self growSize) shiftBy: 1 - firstIndex] ] setSortBlock: aSortBlock [ sortBlock := aSortBlock fixTemps ] buildHeap [ "Construct a heap from scratch out of the elements in the collection" | parentIndex childIndex heapSize parent child childB delta | delta := firstIndex - 1. heapSize := lastIndex - delta. (self size + 1) // 2 to: 1 by: -1 do: [:start | "Reorder the heap" parentIndex := start. childIndex := parentIndex + parentIndex. parent := self basicAt: delta + parentIndex. [childIndex > heapSize or: ["Pick the greatest of the two children" child := self basicAt: delta + childIndex. childIndex = heapSize ifFalse: [childB := self basicAt: delta + childIndex + 1. (self sortBlock value: child value: childB) ifTrue: [child := childB. childIndex := childIndex + 1]]. self sortBlock value: child value: parent]] whileFalse: ["The parent is less than the child -- so the child is actually meant to be the parent." self basicAt: delta + childIndex put: parent. self basicAt: delta + parentIndex put: child. parentIndex := childIndex. childIndex := childIndex + childIndex]] ] makeHeap [ "Construct a heap out of the elements in the collection" "If k elements are to be added to a n-k elements heap, rebuilding the heap from scratch is O(n) and adding the items is O(k log n)." | added size | added := lastIndex - lastOrdered. size := self size. added asFloatD * size asFloatD ln < size ifTrue: [added timesRepeat: [self percolateUp]] ifFalse: [self buildHeap]. lastOrdered := lastIndex. sorted := false. ^self ] sortHeap [ "Make a sorted collection out of the elements in the heap." self size - 1 timesRepeat: [self percolateDown]. lastOrdered := lastIndex. sorted := true ] percolateUp [ "Increment lastOrdered; put the item at the new lastOrdered index into the heap." | holeIndex parentIndex parent item | lastOrdered := lastOrdered + 1. holeIndex := lastOrdered - firstIndex. item := self basicAt: lastOrdered. [holeIndex > 0 and: [parentIndex := (holeIndex - 1) // 2. sortBlock value: (parent := self basicAt: firstIndex + parentIndex) value: item]] whileTrue: [self basicAt: firstIndex + holeIndex put: parent. holeIndex := parentIndex]. self basicAt: firstIndex + holeIndex put: item ] percolateDown [ "Remove the least item in the ordered part of the collection from the heap; decrement lastOrdered and store the item in the previous value of lastOrdered." "Put the highest item in lastOrdered and decrement the size of the heap" | parentIndex childIndex heapSize child childB parent delta | self basicSwap: lastOrdered with: firstIndex. lastOrdered := lastOrdered - 1. "Reorder the heap" parentIndex := 1. childIndex := 2. delta := firstIndex - 1. heapSize := lastOrdered - delta. parent := self basicAt: delta + parentIndex. [childIndex > heapSize ifTrue: [^self]. "Pick the greatest of the two children" child := self basicAt: delta + childIndex. childIndex = heapSize ifFalse: [childB := self basicAt: delta + childIndex + 1. (self sortBlock value: child value: childB) ifTrue: [child := childB. childIndex := childIndex + 1]]. self sortBlock value: child value: parent] whileFalse: ["The parent is less than the child -- so the child is actually meant to be the parent." self basicAt: delta + childIndex put: parent. self basicAt: delta + parentIndex put: child. parentIndex := childIndex. childIndex := childIndex + childIndex] ] compare: elementA with: elementB [ "Compare the two objects according to the sortBlock, answering -1, 0 or 1 depending on whether elementA sorts before, equally, or after elementB. Looking for equality is important for a correct implementation of #includes:; for example try | a sc | a := #('aa' 'ac' 'ab' 'bc' 'bb' 'ba' 'cc' 'ca' 'cb'). sc := a asSortedCollection: [ :x :y | x first <= y first ]. ^a allSatisfy: [ :each | sc includes: each ] On old versions of GNU Smalltalk (up to 1.96) which used a naive binary search, this failed because the sort-block introduced a partial ordering: object can be sort-block-equal even if their are not equal according to #~=." | less greater | less := sortBlock value: elementA value: elementB. greater := sortBlock value: elementB value: elementA. ^less == greater ifTrue: [0] ifFalse: [less ifTrue: [-1] ifFalse: [1]] ] basicSwap: indexA ifBefore: indexB [ | a b | (sortBlock value: (a := self basicAt: indexA) value: (b := self basicAt: indexB)) ifTrue: [self basicAt: indexA put: b. self basicAt: indexB put: a] ] basicSwap: indexA ifAfter: indexB [ | a b | (sortBlock value: (a := self basicAt: indexA) value: (b := self basicAt: indexB)) ifFalse: [self basicAt: indexA put: b. self basicAt: indexB put: a] ] basicSwap: anIndex with: anotherIndex [ "Private - Swap the item at index anIndex with the item at index another index" | saved | saved := self basicAt: anIndex. self basicAt: anIndex put: (self basicAt: anotherIndex). self basicAt: anotherIndex put: saved ] merge [ "Add all the elements in aCollection to the receiver in their proper places" | i add aCollection delta | self sortFrom: lastOrdered + 1 to: lastIndex. aCollection := (lastOrdered + 1 to: lastIndex) collect: [:each | self basicAt: each]. "Merge elements into the collection. We do binary searches on the not yet sorted part of the collection to find where to add the element. This economizes on expensive sort block evaluations." add := aCollection size. i := lastIndex - add. (aCollection asSortedCollection: self sortBlock) reverseDo: [:element | | newIndex | newIndex := self insertionIndexFor: element upTo: i. self primReplaceFrom: newIndex + add to: i + add with: self startingAt: newIndex. add := add - 1. self basicAt: newIndex + add put: element. i := newIndex - 1]. lastOrdered := lastIndex. sorted := true. ^self ] median: ia median: ib median: ic [ "Private - Calculate the middle of a, b and c. Needed for selecting the quicksort's pivot item" | a b c | a := self basicAt: ia. b := self basicAt: ib. c := self basicAt: ic. (sortBlock value: a value: b) ifTrue: [(sortBlock value: b value: c) ifTrue: [^ib]. (sortBlock value: a value: c) ifTrue: [^ic] ifFalse: [^ia]] ifFalse: [(sortBlock value: a value: c) ifTrue: [^ia]. (sortBlock value: b value: c) ifTrue: [^ic] ifFalse: [^ib]] ] sortFrom: first to: last [ "Private - Perform a quicksort on the indexed variables from the first-th to the last-th (using basicAt: indices!). Recursive." | pivot mid smaller larger | last - first < 2 ifTrue: [last > first ifTrue: [self basicSwap: first ifAfter: last]. ^self]. "First we pick a partititioning element. We must find one that is approximately the median of the values, but we must do that fast; we use the median of the first, last and middle one, which would require a very weirdly arranged array for worst case performance. We also have to to put it in the middle." mid := (first + last) // 2. self basicSwap: first ifAfter: mid. self basicSwap: mid ifAfter: last. self basicSwap: first ifAfter: last. pivot := self basicAt: mid. smaller := first. larger := last. [ [smaller <= last and: ["self[smaller] <= pivot" sortBlock value: (self basicAt: smaller) value: pivot]] whileTrue: [smaller := smaller + 1]. [larger >= first and: ["self[larger] >= pivot" sortBlock value: pivot value: (self basicAt: larger)]] whileTrue: [larger := larger - 1]. smaller < larger] whileTrue: [self basicSwap: smaller with: larger. smaller := smaller + 1. larger := larger - 1]. smaller > larger ifFalse: [smaller := smaller + 1. larger := larger - 1]. first < larger ifTrue: [self sortFrom: first to: larger]. smaller < last ifTrue: [self sortFrom: smaller to: last] ] binarySearch: anObject low: low high: high [ "Private - Perform a binary search on the receiver, searching between indexes i and j (indexes are referenced with #basicAt:). If anObject is not found, answer nil, else answer one of the indices containing anObject." "I hate this use of exception handling. Alas, according to the ANSI standard, the methods that use binarySearch must not fail even if the sort block does not support the class of their arguments. In other words, binarySearch must answer nil if there is an error in the sort block." ^ [self doBinarySearch: anObject low: low high: high] on: Error do: [:sig | sig return: nil] ] doBinarySearch: anObject low: low high: high [ "Private - This is the worker method for #binarySearch:low:high:. The algorithm is complex enough that I preferred to split it in two when exception handling added yet another level of indentation. Besides it also helps speed not having to access arguments in outer contexts." | i j mid element compare | i := low. j := high. [i > j ifTrue: [^nil]. mid := (i + j + 1) // 2. element := self basicAt: mid. compare := self compare: anObject with: element. compare = 0] whileFalse: [compare < 0 ifTrue: [j := mid - 1] ifFalse: [i := mid + 1]]. "We've found an element that is `sort-block-equal' to the one to be searched. Search in the two directions that is really equal to it" mid to: low by: -1 do: [:goDown | element := self basicAt: goDown. (self compare: anObject with: element) = 0 ifFalse: ["Exhausted the sort-block-equal elements in this direction, now look in the other!" mid to: high do: [:goUp | element := self basicAt: goUp. (self compare: anObject with: element) = 0 ifFalse: [^nil]. "Another sort-block equal element to test against." anObject = element ifTrue: [^goUp]]. ^nil]. "Another sort-block equal element to test against." anObject = element ifTrue: [^goDown]]. "All the elements in this direction were only sort-block-equal, now look in the other!" mid to: high do: [:goUp | element := self basicAt: goUp. (self compare: anObject with: element) = 0 ifFalse: [^nil]. "Another sort-block equal element to test against." anObject = element ifTrue: [^goUp]]. ^nil ] insertionIndexFor: anObject upTo: highestIndex [ "Private - Perform a binary search on the receiver, searching between indexes firstIndex and highestIndex for an element which comes just after anObject (according to the sort block of course)." | low high mid | low := firstIndex. high := highestIndex. [mid := (high + low) // 2. low > high] whileFalse: [(sortBlock value: (self basicAt: mid) value: anObject) ifTrue: [low := mid + 1] ifFalse: [high := mid - 1]]. ^low ] ] smalltalk-3.2.5/kernel/DeferBinding.st0000644000175000017500000001155612123404352014602 00000000000000"====================================================================== | | DeferredVariableBinding Method Definitions | | ======================================================================" "====================================================================== | | Copyright 2007, 2008 Free Software Foundation, Inc. | Written by Paolo Bonzini. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" LookupKey subclass: DeferredVariableBinding [ | class defaultDictionary association path | DeferredVariableBinding class >> path: anArray class: aClass defaultDictionary: aDictionary [ "As with #key:class:defaultDictionary:, but accepting an array of symbols, representing a namespace path, instead." ^(self key: anArray first) class: aClass; defaultDictionary: aDictionary; path: anArray allButFirst; yourself ] DeferredVariableBinding class >> key: aSymbol class: aClass defaultDictionary: aDictionary [ "Answer a binding that will look up aSymbol as a variable in aClass's environment at first access. See #resolveBinding's comment for aDictionary's meaning." ^(self key: aSymbol) class: aClass; defaultDictionary: aDictionary; yourself ] value [ "Answer a new instance of the receiver with the given key and value" association isNil ifTrue: [association := self resolvePathFrom: self resolveBinding]. ^association value ] value: anObject [ "Answer a new instance of the receiver with the given key and value" association isNil ifTrue: [association := self resolvePathFrom: self resolveBinding]. association value: anObject ] path [ "Answer the path followed after resolving the first key." ^path ] class: aClass [ class := aClass ] defaultDictionary: aDictionary [ defaultDictionary := aDictionary ] path: anArray [ path := anArray isEmpty ifTrue: [nil] ifFalse: [anArray] ] resolvePathFrom: assoc [ "Given the resolution of the first key, resolve the rest of the path. The final element might be put in Undeclared, the ones in the middle instead must exist." | pathAssoc | path isNil ifTrue: [^assoc]. pathAssoc := assoc. 1 to: path size - 1 do: [:each | pathAssoc := pathAssoc value associationAt: (path at: each)]. ^pathAssoc value associationAt: path last ifAbsent: [Undeclared at: path last put: nil; associationAt: path last] ] resolveBinding [ "Look for a pool dictionary of class that includes the key. If not found, add the variable to the defaultDictionary. If already bound, reuse the bound that was found on the previous lookup." "See if a previous access has created the binding." | assoc | assoc := defaultDictionary associationAt: self key ifAbsent: [nil]. assoc isNil ifFalse: [^assoc]. "Look for the binding in the class environment." class allSharedPoolDictionariesDo: [:env | assoc := env hereAssociationAt: self key ifAbsent: [nil]. assoc isNil ifFalse: [^assoc]]. "Create it as a temporary." defaultDictionary at: self key ifAbsentPut: [nil]. ^defaultDictionary associationAt: self key ] printOn: aStream [ "Put on aStream some Smalltalk code compiling to the receiver" aStream nextPut: ${. aStream nextPutAll: self key. self path isNil ifFalse: [self path do: [:each | aStream nextPut: $.; nextPutAll: each]]. aStream nextPut: $} ] storeOn: aStream [ "Put on aStream some Smalltalk code compiling to the receiver" aStream nextPut: $#. self printOn: aStream ] ] smalltalk-3.2.5/kernel/CStruct.st0000644000175000017500000001725712123404352013655 00000000000000"====================================================================== | | C struct definition support classes. | | ======================================================================" "====================================================================== | | Copyright 1992,94,95,99,2000,2001,2002,2008,2009 | Free Software Foundation, Inc. | Written by Steve Byrne. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" CObject subclass: CCompound [ CCompound class [ | declaration | ] CCompound class >> gcNew [ "Allocate a new instance of the receiver, backed by garbage-collected storage." ^self gcAlloc: self sizeof ] CCompound class >> new [ "Allocate a new instance of the receiver. To free the memory after GC, remember to call #addToBeFinalized." ^self alloc: self sizeof ] CCompound class >> sizeof [ "Answer 0, the size of an empty struct" ^0 ] CCompound class >> alignof [ "Answer 1, the alignment of an empty struct" ^1 ] CCompound class >> classPragmas [ "Return the pragmas that are written in the file-out of this class." ^super classPragmas copyWith: #declaration ] CCompound class >> newStruct: structName declaration: array [ "The old way to create a CStruct. Superseded by #subclass:declaration:..." ^self subclass: structName declaration: array classVariableNames: '' poolDictionaries: '' category: 'Synthetic Class' ] CCompound class >> subclass: structName declaration: array classVariableNames: cvn poolDictionaries: pd category: category [ "Create a new class with the given name that contains code to implement the given C struct. All the parameters except `array' are the same as for a standard class creation message; see documentation for more information" | newClass | newClass := self variableWordSubclass: structName asSymbol instanceVariableNames: '' classVariableNames: cvn poolDictionaries: pd category: category. newClass declaration: array. ^newClass ] CCompound class >> declaration [ "Return the description of the fields in the receiver class." declaration isNil ifTrue: [declaration := #()]. ^declaration ] CCompound class >> declaration: array [ self subclassResponsibility ] CCompound class >> declaration: array inject: startOffset into: aBlock [ "Compile methods that implement the declaration in array. To compute the offset after each field, the value of the old offset plus the new field's size is passed to aBlock, together with the new field's alignment requirements." | offset maxAlignment inspStr | (self declaration notEmpty and: [self declaration ~= array]) ifTrue: [self error: 'cannot redefine CStruct/CUnion']. declaration := array. offset := startOffset. maxAlignment := self superclass alignof. inspStr := WriteStream on: (String new: 8). inspStr nextPutAll: 'fieldSelectorList ['; nl; nextPutAll: ' ^#('. "Iterate through each member, doing alignment, size calculations, and creating accessor methods" array do: [:dcl | | typeDecl name str type | name := dcl at: 1. typeDecl := dcl at: 2. self emitFieldNameTo: inspStr for: name. type := CType from: typeDecl. offset := aBlock value: offset value: type alignof. maxAlignment := type alignof max: maxAlignment. str := WriteStream on: (String new: 20). str nextPutAll: name; nextPutAll: ' ['; nl; nextPutAll: ' ^self at: '; print: offset; nextPutAll: ' type: '; store: type; nl; nextPut: $]. self compile: str classified: 'accessing'. offset := offset + type sizeof]. inspStr nextPut: $); nl; nextPut: $]. self compile: inspStr contents classified: 'debugging'. self compileSize: offset align: maxAlignment ] CCompound class >> compileSize: size align: alignment [ "Private - Compile sizeof and alignof methods" | sizeofMethod alignofMethod | sizeofMethod := 'sizeof [ ^' , (size alignTo: alignment) printString, ' ]'. alignofMethod := 'alignof [ ^' , alignment printString, ' ]'. self compile: sizeofMethod classified: 'accessing'. self class compile: sizeofMethod classified: 'accessing'. self compile: alignofMethod classified: 'accessing'. self class compile: alignofMethod classified: 'accessing' ] CCompound class >> emitFieldNameTo: str for: name [ "Private - Emit onto the given stream the code for adding the given selector to the CCompound's #examineOn: method." str nl; next: 8 put: Character space; nextPut: $#; nextPutAll: name ] fieldSelectorList [ "Answer a list of selectors whose return values should be printed by #examineOn:." "We can't call subclassResponsibility because #inspect should never fail. So answer an empty array. For subclasses, it will answer an Array of the selectors whose values are to be shown in #examineOn: or a GUI inspector." ^#() ] examineOn: aStream [ "Print the contents of the receiver's fields on aStream" "This method applies to every instance of the receiver and their subclasses, which only override #fieldSelectorList." aStream print: self; nl. self fieldSelectorList do: [:each | Transcript nextPutAll: ' '; nextPutAll: each; nextPutAll: ': '; print: (self perform: each) value; nl] ] ] CCompound subclass: CStruct [ CStruct class >> declaration: array [ "Compile methods that implement the declaration in array." self declaration: array inject: self superclass sizeof into: [:oldOffset :alignment | oldOffset alignTo: alignment] ] ] CCompound subclass: CUnion [ CUnion class >> declaration: array [ "Compile methods that implement the declaration in array." self declaration: array inject: 0 into: [:oldOffset :alignment | 0] ] ] Integer extend [ alignTo: anInteger [ "Answer the receiver, truncated to the first higher or equal multiple of anInteger (which must be a power of two)" ^self + anInteger - 1 bitClear: anInteger - 1 ] ] Eval [ CCompound initialize ] smalltalk-3.2.5/kernel/Boolean.st0000644000175000017500000000704212123404352013634 00000000000000"====================================================================== | | Boolean Method Definitions | | ======================================================================" "====================================================================== | | Copyright 1988,92,94,95,99,2000,2001 | Free Software Foundation, Inc. | Written by Steve Byrne. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" Object subclass: Boolean [ Boolean class >> isIdentity [ "Answer whether x = y implies x == y for instances of the receiver" ^true ] Boolean class >> isImmediate [ "Answer whether, if x is an instance of the receiver, x copy == x" ^true ] shallowCopy [ ^self "We only have one instance" ] deepCopy [ ^self "it's about as deep as we need to get" ] isLiteralObject [ "Answer whether the receiver is expressible as a Smalltalk literal." ^true ] storeLiteralOn: aStream [ "Store on aStream some Smalltalk code which compiles to the receiver" self storeOn: aStream ] storeOn: aStream [ "Store on aStream some Smalltalk code which compiles to the receiver" self printOn: aStream "representation is the same" ] asCBooleanValue [ self subclassResponsibility ] ifTrue: trueBlock ifFalse: falseBlock [ self subclassResponsibility ] ifFalse: falseBlock ifTrue: trueBlock [ self subclassResponsibility ] ifTrue: trueBlock [ self subclassResponsibility ] ifFalse: falseBlock [ self subclassResponsibility ] not [ self subclassResponsibility ] & aBoolean [ self subclassResponsibility ] | aBoolean [ self subclassResponsibility ] eqv: aBoolean [ self subclassResponsibility ] xor: aBoolean [ self subclassResponsibility ] and: aBlock [ self subclassResponsibility ] or: aBlock [ self subclassResponsibility ] ] smalltalk-3.2.5/kernel/LookupTable.st0000644000175000017500000002322412130343734014502 00000000000000"====================================================================== | | LookupTable Method Definitions | | ======================================================================" "====================================================================== | | Copyright 1999, 2000, 2001, 2002, 2007, 2008 | Free Software Foundation, Inc. | Written by Steve Byrne and Paolo Bonzini. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" Dictionary subclass: LookupTable [ LookupTable class >> primNew: realSize [ ^self basicNew: realSize * 2 ] LookupTable class >> new [ "Create a new LookupTable with a default size" ^self new: 5 ] add: anAssociation [ "Add the anAssociation key to the receiver" self at: anAssociation key put: anAssociation value. ^anAssociation ] at: key put: value [ "Store value as associated to the given key" | index | index := self findIndex: key. (self primAt: index) isNil ifTrue: [self incrementTally ifTrue: [index := self findIndex: key]. self primAt: index put: key]. self valueAt: index put: value. ^value ] at: key ifAbsent: aBlock [ "Answer the value associated to the given key, or the result of evaluating aBlock if the key is not found" | index | index := self findIndexOrNil: key. ^index isNil ifTrue: [aBlock value] ifFalse: [self valueAt: index] ] at: aKey ifPresent: aBlock [ "If aKey is absent, answer nil. Else, evaluate aBlock passing the associated value and answer the result of the invocation" | index | index := self findIndexOrNil: aKey. ^index isNil ifTrue: [nil] ifFalse: [aBlock value: (self valueAt: index)] ] associationAt: key ifAbsent: aBlock [ "Answer the key/value Association for the given key. Evaluate aBlock (answering the result) if the key is not found" | index | index := self findIndexOrNil: key. ^index isNil ifTrue: [aBlock value] ifFalse: [Association key: key value: (self valueAt: index)] ] remove: anAssociation [ "Remove anAssociation's key from the dictionary" ^anAssociation key -> (self removeKey: anAssociation key) ] remove: anAssociation ifAbsent: aBlock [ "Remove anAssociation's key from the dictionary" "Inefficient (has a full block) but it is rarely used." ^anAssociation key -> (self removeKey: anAssociation key ifAbsent: [^aBlock value]) ] removeKey: key ifAbsent: aBlock [ "Remove the passed key from the LookupTable, answer the result of evaluating aBlock if it is not found" | index value | index := self findIndexOrNil: key. index isNil ifTrue: [^aBlock value]. value := self valueAt: index. self primAt: index put: nil. self valueAt: index put: nil. self decrementTally. self rehashObjectsAfter: index. ^value ] associationsDo: aBlock [ "Pass each association in the LookupTable to aBlock." self keysAndValuesDo: [:key :val | aBlock value: (Association key: key value: val)] ] keysDo: aBlock [ "Pass each key in the LookupTable to aBlock." self beConsistent. 1 to: self primSize do: [:i | (self primAt: i) notNil ifTrue: [aBlock value: (self primAt: i)]] ] do: aBlock [ "Pass each value in the LookupTable to aBlock." self beConsistent. 1 to: self primSize do: [:i | (self primAt: i) notNil ifTrue: [aBlock value: (self valueAt: i)]] ] keysAndValuesDo: aBlock [ "Pass each key/value pair in the LookupTable as two distinct parameters to aBlock." 1 to: self primSize do: [:i | (self primAt: i) notNil ifTrue: [aBlock value: (self primAt: i) value: (self valueAt: i)]] ] rehash [ "Rehash the receiver" | keys values n key | keys := Array new: self size. values := Array new: self size. self resetTally. n := 0. 1 to: self primSize do: [:i | (key := self primAt: i) isNil ifFalse: [keys at: (n := n + 1) put: key. values at: n put: (self valueAt: i). self primAt: i put: nil. self valueAt: i put: nil]]. keys keysAndValuesDo: [:i :key | self whileGrowingAt: key put: (values at: i)] ] hash [ "Answer the hash value for the receiver" | hashValue | hashValue := tally. self keysAndValuesDo: [:key :val | hashValue := hashValue bitXor: (self hashFor: key) scramble. "hack needed because the Smalltalk dictionary contains itself" val == self ifFalse: [hashValue := hashValue bitXor: val hash scramble]]. ^hashValue ] storeOn: aStream [ "Print Smalltalk code compiling to the receiver on aStream" | hasElements | aStream nextPutAll: '(' , self class name , ' new'. hasElements := false. self keysAndValuesDo: [:key :value | aStream nextPutAll: ' at: '; store: key; nextPutAll: ' put: '; store: value; nextPut: $;. hasElements := true]. hasElements ifTrue: [aStream nextPutAll: ' yourself']. aStream nextPut: $) ] rehashObjectsAfter: index [ "Rehashes all the objects in the collection after index to see if any of them hash to index. If so, that object is copied to index, and the process repeats with that object's index, until a nil is encountered." | i j size count key | i := index. size := self primSize. [i = size ifTrue: [i := 1] ifFalse: [i := i + 1]. key := self primAt: i. key notNil] whileTrue: [self primAt: i put: nil. j := self findElementIndex: key. self primAt: j put: key. j = i ifFalse: [ self valueAt: j put: (self valueAt: i). self valueAt: i put: nil]] ] copyAllFrom: aDictionary [ | key | 1 to: aDictionary primSize do: [:index | key := aDictionary primAt: index. key isNil ifFalse: [self whileGrowingAt: key put: (aDictionary valueAt: index)]]. ^self ] addWhileGrowing: association [ self whileGrowingAt: association key put: association value ] whileGrowingAt: key put: value [ "Private - Add the given key/value pair to the receiver. Don't check for the LookupTable to be full nor for the key's presence - we want SPEED!" | index | self primAt: (index := self findElementIndex: key) put: key. self valueAt: index put: value. tally := tally + 1. ^value ] primSize [ ^self basicSize // 2 ] primAt: index [ ^self basicAt: index + index - 1 ] primAt: index put: object [ ^self basicAt: index + index - 1 put: object ] valueAt: index [ ^self basicAt: index + index ] valueAt: index put: object [ ^self basicAt: index + index put: object ] hashFor: anObject [ "Return an hash value for the item, anObject" ^anObject hash ] findElementIndex: anObject [ "Tries to see where anObject can be placed as an indexed variable. As soon as nil is found, the index of that slot is answered. anObject also comes from an indexed variable." | index size element | self beConsistent. "Sorry for the lack of readability, but I want speed... :-)" index := (anObject hash scramble bitAnd: (size := self primSize) - 1) + 1. [(element := self primAt: index) isNil ifTrue: [^index]. index == size ifTrue: [index := 1] ifFalse: [index := index + 1]] repeat ] findIndex: anObject [ "Tries to see if anObject exists as an indexed variable. As soon as nil or anObject is found, the index of that slot is answered" | index size element | self beConsistent. "Sorry for the lack of readability, but I want speed... :-)" index := (anObject hash scramble bitAnd: (size := self primSize) - 1) + 1. [((element := self primAt: index) isNil or: [element = anObject]) ifTrue: [^index]. index == size ifTrue: [index := 1] ifFalse: [index := index + 1]] repeat ] ] smalltalk-3.2.5/kernel/Date.st0000644000175000017500000004341612123404352013137 00000000000000"====================================================================== | | Date Method Definitions | | ======================================================================" "====================================================================== | | Copyright 1988,92,94,95,99,2000,2001,2002,2008 | Free Software Foundation, Inc. | Written by Steve Byrne, Paolo Bonzini and Jeff Rosenwald. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" Magnitude subclass: Date [ | days day month year | DayNameDict := nil. MonthNameDict := nil. Date class >> initialize [ "Initialize the receiver" "28 = 7 days*2 keys each day, multiplied by 2 to make hashing effective. 48 = 12 months*2 keys each month, multiplied by 2 for the same reason." DayNameDict := IdentityDictionary new: 28. MonthNameDict := IdentityDictionary new: 48. self initDayNameDict. self initMonthNameDict ] Date class >> initDayNameDict [ "Initialize the DayNameDict to the names of the days" | dayNames | dayNames := #(#(#monday #mon) #(#tuesday #tue) #(#wednesday #wed) #(#thursday #thu) #(#friday #fri) #(#saturday #sat) #(#sunday #sun)). "1" "2" "3" "4" "5" "6" "7" dayNames keysAndValuesDo: [:dayIndex :names | names do: [:name | DayNameDict at: name put: dayIndex]] ] Date class >> initMonthNameDict [ "Initialize the MonthNameDict to the names of the months" | monthNames | monthNames := #(#(#january #jan) #(#february #feb) #(#march #mar) #(#april #apr) #(#may) #(#june #jun) #(#july #jul) #(#august #aug) #(#september #sep) #(#october #oct) #(#november #nov) #(#december #dec)). "1" "2" "3" "4" "5" "6" "7" "8" "9" "10" "11" "12" monthNames doWithIndex: [:names :dayIndex | names do: [:name | MonthNameDict at: name put: dayIndex]] ] Date class >> dayOfWeek: dayName [ "Answer the index of the day of week corresponding to the given name" ^DayNameDict at: dayName asLowercase asSymbol ] Date class >> nameOfDay: dayIndex [ "Answer the name of the day of week corresponding to the given index" ^#(#Monday #Tuesday #Wednesday #Thursday #Friday #Saturday #Sunday) at: dayIndex ] Date class >> abbreviationOfDay: dayIndex [ "Answer the abbreviated name of the day of week corresponding to the given index" ^#(#Mon #Tue #Wed #Thu #Fri #Sat #Sun) at: dayIndex ] Date class >> indexOfMonth: monthName [ "Answer the index of the month corresponding to the given name" ^MonthNameDict at: monthName asLowercase asSymbol ] Date class >> shortNameOfMonth: monthIndex [ "Answer the name of the month corresponding to the given index" ^#(#Jan #Feb #Mar #Apr #May #Jun #Jul #Aug #Sep #Oct #Nov #Dec) at: monthIndex ] Date class >> nameOfMonth: monthIndex [ "Answer the name of the month corresponding to the given index" ^#(#January #February #March #April #May #June #July #August #September #October #November #December) at: monthIndex ] Date class >> daysInMonth: monthName forYear: yearInteger [ "Answer the number of days in the given (named) month for the given year" | monthIndex | monthIndex := self indexOfMonth: monthName. ^self daysInMonthIndex: monthIndex forYear: yearInteger ] Date class >> daysInYear: i [ "Answer the number of days in the given year" ^(i + 4800) * 1461 // 4 - ((i + 4900) // 100 * 3 // 4) - ((i + 4799) * 1461 // 4) + ((i + 4899) // 100 * 3 // 4) ] Date class >> dateAndTimeNow [ "Answer an array containing the current date and time" | secondClock utcSecondClock | secondClock := Time secondClock. utcSecondClock := Time utcSecondClock. ^DateTime fromDays: secondClock // 86400 seconds: secondClock \\ 86400 offset: (Duration fromSeconds: secondClock - utcSecondClock) ] Date class >> utcDateAndTimeNow [ "Answer an array containing the current date and time in Coordinated Universal Time (UTC)" | utcSecondClock | utcSecondClock := Time utcSecondClock. ^DateTime fromDays: utcSecondClock // 86400 seconds: utcSecondClock \\ 86400 offset: Duration zero ] Date class >> today [ "Answer a Date denoting the current date in local time" ^self fromSeconds: Time secondClock ] Date class >> utcToday [ "Answer a Date denoting the current date in Coordinated Universal Time (UTC)" ^self fromSeconds: Time utcSecondClock ] Date class >> fromSeconds: time [ "Answer a Date denoting the date time seconds past Jan 1st, 1901" | days | days := time // (24 * 60 * 60). ^self new setDays: days ] Date class >> fromJulian: jd [ "Answer a Date denoting the jd-th day in the astronomical Julian calendar." ^self new setDays: jd - 2415386 ] Date class >> fromDays: dayCount [ "Answer a Date denoting dayCount days past 1/1/1901" ^self new setDays: dayCount ] Date class >> newDay: dayCount year: yearInteger [ "Answer a Date denoting the dayCount day of the yearInteger year" ^self new setDays: dayCount + (self yearAsDays: yearInteger) ] Date class >> newDay: day monthIndex: monthIndex year: yearInteger [ "Answer a Date denoting the dayCount day of the given (as a number) month and year" ^self new setDay: day monthIndex: monthIndex year: yearInteger ] Date class >> newDay: day month: monthName year: yearInteger [ "Answer a Date denoting the dayCount day of the given (named) month and year" ^self new setDay: day monthIndex: (self indexOfMonth: monthName) year: yearInteger ] Date class >> readFrom: aStream [ "Parse an instance of the receiver from aStream" | t1 t2 t3 ch month ws | 1 to: 3 do: [:i | ws := WriteStream on: (String new: 10). [aStream atEnd not and: [(ch := aStream peek) isAlphaNumeric not and: [ch ~= $-]]] whileTrue: [aStream next]. aStream atEnd ifFalse: [ aStream next. ch isLetter ifTrue: [[ws nextPut: ch. aStream atEnd not and: [(ch := aStream next) isLetter]] whileTrue] ifFalse: [[ws nextPut: ch. aStream atEnd not and: [(ch := aStream next) isDigit]] whileTrue]]. t1 := t2. t2 := t3. t3 := ws contents. (t3 at: 1) isLetter ifFalse: [t3 := t3 asNumber] ifTrue: [month := i. t3 := self indexOfMonth: t3 asSymbol]. (i = 2 and: [month = 1 and: [t3 > 31]]) ifTrue: ["January 2000" ^self newDay: 1 monthIndex: t2 year: t3]]. month isNil ifTrue: [(t1 between: 1 and: 31) ifFalse: [^self newDay: t3 monthIndex: t2 year: t1]. "YMD" ^t1 <= 12 ifTrue: [^self newDay: t2 monthIndex: t1 year: t3 "MDY"] ifFalse: [^self newDay: t1 monthIndex: t2 year: t3 "DMY"]]. ^month = 1 ifTrue: [self newDay: t2 monthIndex: t1 year: t3 "MDY"] ifFalse: [self newDay: t1 monthIndex: t2 year: t3 "DMY"] ] Date class >> year: y month: m day: d hour: h minute: min second: s [ "Answer a Date denoting the d-th day of the given (as a number) month and year" ^self new setDay: d monthIndex: m year: y ] Date class >> year: y day: d hour: h minute: min second: s [ "Answer a Date denoting the d-th day of the given year" ^self new setDays: (self yearAsDays: y) + d ] Date class >> yearAsDays: i [ "Private - Returns the number of days between Jan 1, 1901 and Jan 0th of the given year yearInteger" "Calculate Julian day via Fliegal & Van Flandern method -- ACM Algorithm 289. I have to subtract 2415387 to correct for Smalltalk epoch, and I merged that constant in the one (32074) in their formula." ^(i + 4799) * 1461 // 4 - ((i + 4899) // 100 * 3 // 4) - 2447125 ] Date class >> daysUntilMonth: monthIndex year: yearInteger [ "Private - Answer the number of days between Jan 1, 1901, and the hypotetical 0th day in the given month, for the given year" | i j | j := monthIndex - 14 quo: 12. i := j + yearInteger. "Calculate Julian day via Fliegal & Van Flandern method -- ACM Algorithm 289. I have to subtract 2415386 to correct for Smalltalk epoch, and I merged that constant in the one (32074) in their formula." ^(i + 4800) * 1461 // 4 + ((monthIndex - 2 - (j * 12)) * 367 // 12) - ((i + 4900) // 100 * 3 // 4) - 2447461 ] Date class >> daysInMonthIndex: monthIndex forYear: yearInteger [ "Private - Answer the number of days in the given (indexed) month, for the given year" monthIndex = 2 ifTrue: [^(self daysInYear: yearInteger) - 337]. ^#[31 0 31 30 31 30 31 31 30 31 30 31] at: monthIndex "Jan Feb Mar" "Apr May Jun" "Jul Aug Sep" "Oct Nov Dec" ] < aDate [ "Answer whether the receiver indicates a date preceding aDate" ^self days < aDate days ] = aDate [ "Answer whether the receiver indicates the same date as aDate" ^aDate class == self class and: [aDate days = self days] ] hash [ "Answer an hash value for the receievr" ^self days ] - aDate [ "Answer a new Duration counting the number of days between the receiver and aDate." ^Duration days: self days - aDate days ] + aDuration [ "Answer a new Date or DateTime pointing aDuration time past the receiver." aDuration seconds = 0 ifTrue: [ ^Date fromDays: self days + aDuration days ]. ^DateTime fromDays: self days + aDuration days seconds: aDuration seconds offset: Duration zero ] addDays: dayCount [ "Answer a new Date pointing dayCount past the receiver" ^Date fromDays: self days + dayCount ] subtractDays: dayCount [ "Answer a new Date pointing dayCount before the receiver" ^Date fromDays: self days - dayCount ] subtractDate: aDate [ "Answer the number of days between aDate and the receiver (negative if the receiver is before aDate)" ^self days - aDate days ] day [ "Answer the day represented by the receiver" ^day ] dayName [ "Answer the day of week of the receiver as a Symbol" ^Date nameOfDay: (self days + 1) \\ 7 + 1 ] shortMonthName [ "Answer the abbreviated name of the month represented by the receiver" ^Date shortNameOfMonth: self month ] asSeconds [ "Answer the date as the number of seconds from 1/1/1901." ^self days * 86400 ] dayOfWeek [ "Answer the day of week of the receiver. 1 = Monday, 7 = Sunday" ^(self days + 1) \\ 7 + 1 ] dayOfWeekName [ "Answer the day of week of the receiver as a Symbol" ^Date nameOfDay: (self days + 1) \\ 7 + 1 ] dayOfWeekAbbreviation [ "Answer the day of week of the receiver as a Symbol" ^Date abbreviationOfDay: (self days + 1) \\ 7 + 1 ] dayOfMonth [ "Answer the day represented by the receiver (same as #day)" ^day ] dayOfYear [ "Answer the days passed since 31/12 of last year; e.g. New Year's Day is 1" ^self days - (Date yearAsDays: self year) ] daysFromBaseDay [ "Answer the days passed since 1/1/1901" ^days ] daysInMonth [ "Answer the days in the month represented by the receiver" ^Date daysInMonthIndex: month forYear: year ] daysInYear [ "Answer the days in the year represented by the receiver" ^Date daysInYear: self year ] daysLeftInMonth [ "Answer the days to the end of the month represented by the receiver" ^(Date daysInMonthIndex: month forYear: year) - day ] daysLeftInYear [ "Answer the days to the end of the year represented by the receiver" ^(Date yearAsDays: self year + 1) - self days ] firstDayOfMonth [ "Answer a Date representing the first day of the month represented by the receiver" ^self subtractDays: self dayOfMonth - 1 ] isLeapYear [ "Answer whether the receiver refers to a date in a leap year." ^self daysInYear == 366 ] lastDayOfMonth [ "Answer a Date representing the last day of the month represented by the receiver" ^self addDays: self daysLeftInMonth ] month [ "Answer the index of the month represented by the receiver" ^month ] monthIndex [ "Answer the index of the month represented by the receiver" ^month ] monthName [ "Answer the name of the month represented by the receiver" ^Date nameOfMonth: self month ] monthAbbreviation [ "Answer the abbreviated name of the month represented by the receiver" ^Date shortNameOfMonth: self month ] year [ "Answer the year represented by the receiver" ^year ] printOn: aStream [ "Print a representation for the receiver on aStream" aStream print: self day; nextPut: $-; nextPutAll: (Date shortNameOfMonth: self month); nextPut: $-; print: self year ] storeOn: aStream [ "Store on aStream Smalltalk code compiling to the receiver" aStream nextPut: $(; nextPutAll: self class storeString; nextPutAll: ' newDay: '; store: self day; nextPutAll: ' monthIndex: '; store: self month; nextPutAll: ' year: '; store: self year; nextPut: $) ] days [ "Private - Same as daysFromBaseDay" ^days ] setDay: dayOfMonth monthIndex: monthIndex year: yearInteger [ "Private - Set the receiver to the given date parts" days := dayOfMonth + (Date daysUntilMonth: monthIndex year: yearInteger). dayOfMonth < 1 ifTrue: [^self setDays: days]. dayOfMonth > (Date daysInMonthIndex: monthIndex forYear: yearInteger) ifTrue: [^self setDays: days]. day := dayOfMonth. month := monthIndex. year := yearInteger ] setDays: dayCount [ "Private - Compute the date parts from the given dayCount and initialize the receiver" "Fliegal and Van Flandern's methods for computing y/m/d from Julian. The original algorithm starts by summing 68569 to the Julian day -- I sum 2483955 to adjust for smalltalk epoch." | julian n | days := dayCount. julian := days + 2483955. n := 4 * julian // 146097. julian := julian - ((146097 * n + 3) // 4). year := 4000 * (julian + 1) // 1461001. julian := julian - (1461 * year // 4) + 31. month := 80 * julian // 2447. day := julian - (2447 * month // 80). julian := month // 11. month := month + 2 - (12 * julian). year := 100 * (n - 49) + year + julian ] ] smalltalk-3.2.5/kernel/FileDescr.st0000644000175000017500000006762712123404352014134 00000000000000"====================================================================== | | FileDescriptor Method Definitions | | ======================================================================" "====================================================================== | | Copyright 2001, 2002, 2005, 2006, 2007, 2008, 2009 | Free Software Foundation, Inc. | Written by Paolo Bonzini. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" Stream subclass: FileDescriptor [ | access fd file isPipe atEnd peek | AllOpenFiles := nil. FileDescriptor class >> append [ "Open for writing. The file is created if it does not exist. The stream is positioned at the end of the file." ^'a' ] FileDescriptor class >> create [ "Open for reading and writing. The file is created if it does not exist, otherwise it is truncated. The stream is positioned at the beginning of the file." ^'w+' ] FileDescriptor class >> readWrite [ "Open for reading and writing. The stream is positioned at the beginning of the file." ^'r+' ] FileDescriptor class >> on: fd [ "Open a FileDescriptor on the given file descriptor. Read-write access is assumed." ^(self basicNew) setFD: fd; initialize ] FileDescriptor class >> open: fileName [ "Open fileName in read-write mode - fail if the file cannot be opened. Else answer a new FileStream. The file will be automatically closed upon GC if the object is not referenced anymore, but you should close it with #close anyway. To keep a file open, send it #removeToBeFinalized" ^self open: fileName mode: FileStream readWrite ] FileDescriptor class >> open: fileName mode: fileMode [ "Open fileName in the required mode - answered by #append, #create, #readWrite, #read or #write - and fail if the file cannot be opened. Else answer a new FileStream. For mode anyway you can use any standard C non-binary fopen mode. fileName can be a `virtual filesystem' path, including URLs and '#' suffixes that are inspected by the virtual filesystem layers and replaced with tasks such as un-gzipping a file or extracting a file from an archive. The file will be automatically closed upon GC if the object is not referenced anymore, but it is better to close it as soon as you're finished with it anyway, using #close. To keep a file open even when no references exist anymore, send it #removeToBeFinalized" ^self open: fileName mode: fileMode ifFail: [SystemExceptions.FileError signal: 'could not open ' , fileName] ] FileDescriptor class >> open: fileName mode: fileMode ifFail: aBlock [ "Open fileName in the required mode - answered by #append, #create, #readWrite, #read or #write - and evaluate aBlock if the file cannot be opened. Else answer a new instance of the receiver. For mode anyway you can use any standard C non-binary fopen mode. fileName can be a `virtual filesystem' path, including URLs and '#' suffixes that are inspected by the virtual filesystem layers and replaced with tasks such as un-gzipping a file or extracting a file from an archive. The file will be automatically closed upon GC if the object is not referenced anymore, but it is better to close it as soon as you're finished with it anyway, using #close. To keep a file open even when no references exist anymore, send it #removeToBeFinalized" ((fileName indexOfSubCollection: '://') > 0 and: [fileMode = FileStream read]) ifTrue: [^NetClients.URIResolver openStreamOn: fileName ifFail: aBlock ]. ^self fopen: fileName mode: fileMode ifFail: aBlock ] FileDescriptor class >> openTemporaryFile: baseName [ "Open for writing a file whose name starts with baseName, followed by six random alphanumeric characters. The file is created with mode read/write and permissions 0666 or 0600 on most recent operating systems (beware, the former behavior might constitute a security problem). The file is opened with the O_EXCL flag, guaranteeing that when the method returns successfully we are the only user." ^(self basicNew) fileOp: 16 with: baseName asString ifFail: [SystemExceptions.FileError signal: 'could not open temporary file']; initialize; yourself ] FileDescriptor class >> fopen: fileName mode: fileMode [ "Open fileName in the required mode - answered by #append, #create, #readWrite, #read or #write - and fail if the file cannot be opened. Else answer a new FileStream. For mode anyway you can use any standard C non-binary fopen mode. The file will be automatically closed upon GC if the object is not referenced anymore, but it is better to close it as soon as you're finished with it anyway, using #close. To keep a file open even when no references exist anymore, send it #removeToBeFinalized" ^(self basicNew) fileOp: 0 with: fileName asString with: fileMode ifFail: [SystemExceptions.FileError signal: 'could not open ' , fileName]; setFile: (File name: fileName); initialize; yourself ] FileDescriptor class >> fopen: fileName mode: fileMode ifFail: aBlock [ "Open fileName in the required mode - answered by #append, #create, #readWrite, #read or #write - and evaluate aBlock if the file cannot be opened. Else answer a new FileStream. For mode anyway you can use any The file will be automatically closed upon GC if the object is not referenced anymore, but it is better to close it as soon as you're finished with it anyway, using #close. To keep a file open even when no references exist anymore, send it #removeToBeFinalized" ^(self basicNew) fileOp: 0 with: fileName asString with: fileMode ifFail: [^aBlock value]; setFile: (File name: fileName); initialize; yourself ] FileDescriptor class >> popen: commandName dir: direction [ "Open a pipe on the given command and fail if the file cannot be opened. Else answer a new FileStream. The pipe will not be automatically closed upon GC, even if the object is not referenced anymore, because when you close a pipe you have to wait for the associated process to terminate. direction is returned by #read or #write ('r' or 'w') and is interpreted from the point of view of Smalltalk: reading means Smalltalk reads the standard output of the command, writing means Smalltalk writes the standard input of the command. The other channel (stdin when reading, stdout when writing) is the same as GST's, unless commandName alters it." ^(self basicNew) fileOp: 7 with: commandName with: direction ifFail: [SystemExceptions.FileError signal: 'could not open pipe on' , commandName]; initialize; yourself ] FileDescriptor class >> popen: commandName dir: direction ifFail: aBlock [ "Open a pipe on the given command and evaluate aBlock file cannot be opened. Else answer a new FileStream. The pipe will not be automatically closed upon GC, even if the object is not referenced anymore, because when you close a pipe you have to wait for the associated process to terminate. direction is interpreted from the point of view of Smalltalk: reading means that Smalltalk reads the standard output of the command, writing means that Smalltalk writes the standard input of the command" ^(self basicNew) fileOp: 7 with: commandName with: direction ifFail: [^aBlock value]; initialize; yourself ] FileDescriptor class >> read [ "Open text file for reading. The stream is positioned at the beginning of the file." ^'r' ] FileDescriptor class >> write [ "Truncate file to zero length or create text file for writing. The stream is positioned at the beginning of the file." ^'w' ] FileDescriptor class >> initialize [ "Initialize the receiver's class variables" ObjectMemory addDependent: self. AllOpenFiles := WeakIdentitySet new. ] FileDescriptor class >> update: aspect [ "Close open files before quitting" aspect == #afterEvaluation ifTrue: [stdin flush. stdout flush. stderr flush]. aspect == #aboutToQuit ifTrue: [stdin flush. stdout flush. stderr flush. AllOpenFiles asArray do: [:each | each close]] ] checkError [ "Perform error checking. By default, we call File class>>#checkError." self isOpen ifFalse: [SystemExceptions.FileError signal: 'file closed']. File checkError. self pastEnd. ^0 ] invalidate [ "Invalidate a file descriptor" fd := nil ] shutdown [ "Close the transmission side of a full-duplex connection. This is useful on read-write pipes." self isOpen ifFalse: [^self]. self flush. self fileOp: 19. access := 1 ] close [ "Close the file" self isOpen ifFalse: [^self]. self flush. self changed: #beforeClosing. self fileOp: 1. self removeToBeFinalized. self invalidate. self changed: #afterClosing ] finalize [ "Close the file if it is still open by the time the object becomes garbage." AllOpenFiles remove: self ifAbsent: []. self isOpen ifTrue: [self close] ] next [ "Return the next character in the file, or nil at eof" | result data | peek isNil ifFalse: [data := peek. peek := nil. result := 1] ifTrue: [data := self species new: 1. result := self nextAvailable: 1 into: data startingAt: 1. data := data at: 1]. ^result > 0 ifTrue: [data] ifFalse: [self pastEnd] ] peekFor: anObject [ "Returns whether the next element of the stream is equal to anObject, without moving the pointer if it is not." | result | ^self peek = anObject ifTrue: [ self next ]; yourself ] peek [ "Returns the next element of the stream without moving the pointer. Returns nil when at end of stream." | result data | peek isNil ifFalse: [^peek]. data := self species new: 1. result := self nextAvailable: 1 into: data startingAt: 1. ^result > 0 ifTrue: [peek := data at: 1] ifFalse: [self pastEnd] ] nextByte [ "Return the next byte in the file, or nil at eof" | a | a := self next. ^a isNil ifTrue: [a] ifFalse: [a asInteger] ] nextPut: aCharacter [ "Store aCharacter on the file" self next: 1 putAll: (String with: aCharacter) startingAt: 1 ] nextPutByte: anInteger [ "Store the byte, anInteger, on the file" self nextPut: (Character value: (anInteger bitAnd: 255)) ] nextPutByteArray: aByteArray [ "Store aByteArray on the file" ^self nextPutAll: aByteArray asString ] reset [ "Reset the stream to its beginning" self checkIfPipe; position: 0 ] position [ "Answer the zero-based position from the start of the file" self checkIfPipe. peek isNil ifFalse: [self skip: -1. peek := nil]. ^self fileOp: 5 ] position: n [ "Set the file pointer to the zero-based position n" self checkIfPipe. peek := nil. ^self fileOp: 4 with: n ] size [ "Return the current size of the file, in bytes" ^self checkIfPipe; fileOp: 9 ] truncate [ "Truncate the file at the current position" self checkIfPipe; fileOp: 10 ] contents [ "Answer the whole contents of the file" | stream | ^self isPipe ifTrue: [stream := WriteStream on: (self species new: 10). self nextPutAllOn: stream. stream contents] ifFalse: [^self next: self size - self position] ] copyFrom: from to: to [ "Answer the contents of the file between the two given positions" | savePos | from > to ifTrue: [(from = to) + 1 ifTrue: [^self species new]. ^SystemExceptions.ArgumentOutOfRange signalOn: from mustBeBetween: 0 and: to + 1]. savePos := self fileOp: 5. ^ [self position: from. self next: to - from + 1] ensure: [self position: savePos] ] exceptionalCondition [ "Answer whether the file is open and an exceptional condition (such as presence of out of band data) has occurred on it" | result | self isOpen ifFalse: [^false]. result := self fileOp: 13 with: 2 ifFail: [self close. 0]. ^result == 1 ] canWrite [ "Answer whether the file is open and we can write from it" | result | self isOpen ifFalse: [^false]. result := self fileOp: 13 with: 1 ifFail: [self close. 0]. ^result == 1 ] canRead [ "Answer whether the file is open and we can read from it" | result | self isOpen ifFalse: [^false]. result := self fileOp: 13 with: 0 ifFail: [self close. 0]. ^result == 1 ] ensureReadable [ "If the file is open, wait until data can be read from it. The wait allows other Processes to run." self isPipe ifFalse: [^self]. self isOpen ifFalse: [^self]. self fileOp: 14 with: 0 with: Semaphore new. self isOpen ifFalse: [^self]. self fileOp: 13 with: 0 ifFail: [self close] ] ensureWriteable [ "If the file is open, wait until we can write to it. The wait allows other Processes to run." self isOpen ifFalse: [^self]. self fileOp: 13 with: 1 ifFail: [self close] ] waitForException [ "If the file is open, wait until an exceptional condition (such as presence of out of band data) has occurred on it. The wait allows other Processes to run." self isPipe ifFalse: [^self]. self isOpen ifFalse: [^self]. self fileOp: 14 with: 2 with: Semaphore new. self isOpen ifFalse: [^self]. self fileOp: 13 with: 2 ifFail: [self close] ] isPeerAlive [ "Present for compatibility with sockets. For files, it answers whether the file is still open" ^self isOpen ] isOpen [ "Answer whether the file is still open" ^fd isInteger and: [fd positive] ] isPipe [ "Answer whether the file is a pipe or an actual disk file" isPipe isNil ifTrue: [isPipe := self fileOp: 15]. ^isPipe ] fd [ "Return the OS file descriptor of the file" ^fd ] file [ "Return the name of the file" ^file asFile ] name [ "Return the name of the file" file isNil ifTrue: [^'descriptor #', fd printString ]. ^file displayString ] printOn: aStream [ "Print a representation of the receiver on aStream" aStream nextPut: $<; nextPutAll: (self isPipe ifTrue: ['Pipe'] ifFalse: [self class name]); nextPutAll: ' on '; nextPutAll: self name; nextPut: $> ] setToEnd [ "Reset the file pointer to the end of the file" self position: self size ] skip: anInteger [ "Skip anInteger bytes in the file" | pos | pos := (self position + anInteger max: 0) min: self size - 1. self position: pos ] reverseContents [ "Return the contents of the file from the last byte to the first" ^self contents reverse ] isEmpty [ "Answer whether the receiver is empty" ^self size == 0 ] nextPutAllOn: aStream [ "Put all the characters of the receiver in aStream." | buf bufSize n | bufSize := self isPipe ifTrue: [ self atEnd ifTrue: [ 0 ] ifFalse: [ 1024 ] ] ifFalse: [ self size - self position min: 1024 ]. bufSize = 0 ifTrue: [ ^self ]. buf := String new: bufSize. [ n := self nextAvailable: bufSize into: buf startingAt: 1. aStream next: n putAll: buf startingAt: 1. n = 1024 ] whileTrue ] nextByteArray: anInteger [ "Return the next 'anInteger' bytes from the stream, as a ByteArray." ^self next: anInteger into: (ByteArray new: anInteger) startingAt: 1 ] atEnd [ "Answer whether data has come to an end" self isOpen ifFalse: [^true]. self isPipe ifFalse: [^self fileOp: 6]. atEnd isNil ifTrue: [peek isNil ifTrue: [self ensureReadable. self peek]. atEnd isNil ifTrue: [^false]]. ^atEnd ] checkIfPipe [ self isPipe ifTrue: [SystemExceptions.FileError signal: 'cannot do that to a pipe or socket.'] ] setFile: aString [ file := aString ] setFD: anInteger [ access := 3. fd := anInteger. isPipe := nil ] addToBeFinalized [ "Add me to the list of open files." AllOpenFiles add: self. super addToBeFinalized ] removeToBeFinalized [ "Remove me from the list of open files." AllOpenFiles remove: self ifAbsent: []. super removeToBeFinalized ] initialize [ "Initialize the receiver's instance variables" self addToBeFinalized. access isNil ifTrue: [access := 3]. atEnd := nil ] readStream [ "Answer myself, or an alternate stream coerced for reading." ^(access bitAnd: 1) = 0 ifTrue: [self file readStream] ifFalse: [self] ] isExternalStream [ "We stream on an external entity (a file), so answer true" ^true ] isBinary [ "We answer characters, so answer false" ^false ] isText [ "We answer characters, so answer true" ^true ] pastEnd [ "The end of the stream has been reached. Signal a Notification." atEnd := true. ^super pastEnd ] nextAvailable: n into: aCollection startingAt: position [ "Ignoring any buffering, try to fill the given range of aCollection with the contents of the file" | count available | n = 0 ifTrue: [ ^self ]. self ensureReadable. available := peek isNil ifTrue: [0] ifFalse: [1]. peek isNil ifFalse: [aCollection byteAt: position put: peek value. peek := nil]. self isOpen ifFalse: [^available]. count := self fileOp: 3 with: aCollection with: position + available with: (position + n - 1 min: aCollection size) ifFail: [self checkError]. count := count + available. count = 0 ifTrue: [atEnd := true]. ^count ] next: n putAll: aCollection startingAt: position [ "Put the characters in the supplied range of aCollection in the file" | cur last soFar result | cur := position. last := position + n - 1 min: aCollection size. [cur <= last] whileTrue: [self ensureWriteable. self isOpen ifFalse: [^cur - position]. result := self fileOp: 2 with: aCollection with: cur with: last ifFail: [self checkError]. result = 0 ifTrue: [^cur - position]. cur := cur + result]. ^cur - position ] fileIn [ "File in the contents of the receiver. During a file in operation, global variables (starting with an uppercase letter) that are not declared don't yield an `unknown variable' error. Instead, they are defined as nil in the `Undeclared' dictionary (a global variable residing in Smalltalk). As soon as you add the variable to a namespace (for example by creating a class) the Association will be removed from Undeclared and reused in the namespace, so that the old references will automagically point to the new value." | pos | self isPipe ifTrue: [ ^super fileIn ]. ^self fileInLine: 1 file: self file full fileName: self name at: self position ] fileOp: ioFuncIndex [ "Private - Used to limit the number of primitives used by FileStreams" self checkError. ^nil ] fileOp: ioFuncIndex ifFail: aBlock [ "Private - Used to limit the number of primitives used by FileStreams." ^aBlock value ] fileOp: ioFuncIndex with: arg1 [ "Private - Used to limit the number of primitives used by FileStreams" self checkError. ^nil ] fileOp: ioFuncIndex with: arg1 ifFail: aBlock [ "Private - Used to limit the number of primitives used by FileStreams." ^aBlock value ] fileOp: ioFuncIndex with: arg1 with: arg2 [ "Private - Used to limit the number of primitives used by FileStreams" self checkError. ^nil ] fileOp: ioFuncIndex with: arg1 with: arg2 ifFail: aBlock [ "Private - Used to limit the number of primitives used by FileStreams." ^aBlock value ] fileOp: ioFuncIndex with: arg1 with: arg2 with: arg3 [ "Private - Used to limit the number of primitives used by FileStreams" self checkError. ^nil ] fileOp: ioFuncIndex with: arg1 with: arg2 with: arg3 ifFail: aBlock [ "Private - Used to limit the number of primitives used by FileStreams." ^aBlock value ] fileOp: ioFuncIndex with: arg1 with: arg2 with: arg3 with: arg4 [ "Private - Used to limit the number of primitives used by FileStreams" self checkError. ^nil ] fileOp: ioFuncIndex with: arg1 with: arg2 with: arg3 with: arg4 ifFail: aBlock [ "Private - Used to limit the number of primitives used by FileStreams." ^aBlock value ] nextByteArray: numBytes [ "Return the next numBytes bytes in the byte array" ^(self next: numBytes) asByteArray ] nextSignedByte [ "Return the next byte in the byte array, interpreted as a 8 bit signed number" ^self nextBytes: 1 signed: true ] nextDouble [ "Return the next 64-bit float in the byte array" ^(FloatD new: 8) at: 1 put: self nextByte; at: 2 put: self nextByte; at: 3 put: self nextByte; at: 4 put: self nextByte; at: 5 put: self nextByte; at: 6 put: self nextByte; at: 7 put: self nextByte; at: 8 put: self nextByte ] nextFloat [ "Return the next 32-bit float in the byte array" ^(FloatE new: 4) at: 1 put: self nextByte; at: 2 put: self nextByte; at: 3 put: self nextByte; at: 4 put: self nextByte ] nextUint64 [ "Return the next 8 bytes in the byte array, interpreted as a 64 bit unsigned int" ^self nextBytes: 8 signed: false ] nextLongLong [ "Return the next 8 bytes in the byte array, interpreted as a 64 bit signed int" ^self nextBytes: 8 signed: true ] nextUlong [ "Return the next 4 bytes in the byte array, interpreted as a 32 bit unsigned int" ^self nextBytes: 4 signed: false ] nextLong [ "Return the next 4 bytes in the byte array, interpreted as a 32 bit signed int" ^self nextBytes: 4 signed: true ] nextUshort [ "Return the next 2 bytes in the byte array, interpreted as a 16 bit unsigned int" ^self nextBytes: 2 signed: false ] nextShort [ "Return the next 2 bytes in the byte array, interpreted as a 16 bit signed int" ^self nextBytes: 2 signed: true ] nextPutDouble: aDouble [ "Store aDouble as a 64-bit float in the byte array" | d | d := aDouble asFloatD. self nextPutByte: (d at: 1). self nextPutByte: (d at: 2). self nextPutByte: (d at: 3). self nextPutByte: (d at: 4). self nextPutByte: (d at: 5). self nextPutByte: (d at: 6). self nextPutByte: (d at: 7). self nextPutByte: (d at: 8) ] nextPutFloat: aFloat [ "Return the next 32-bit float in the byte array" | f | f := aFloat asFloatE. self nextPutByte: (f at: 1). self nextPutByte: (f at: 2). self nextPutByte: (f at: 3). self nextPutByte: (f at: 4) ] nextPutInt64: anInteger [ "Store anInteger (range: -2^63..2^64-1) on the byte array as 8 bytes" self nextPutBytes: 8 of: anInteger ] nextPutLong: anInteger [ "Store anInteger (range: -2^31..2^32-1) on the byte array as 4 bytes" self nextPutBytes: 4 of: anInteger ] nextPutShort: anInteger [ "Store anInteger (range: -32768..65535) on the byte array as 2 bytes" self nextPutBytes: 2 of: anInteger ] nextBytes: n signed: signed [ "Private - Get an integer out of the next anInteger bytes in the stream" | int msb | int := 0. 0 to: n * 8 - 16 by: 8 do: [:i | int := int + (self nextByte bitShift: i)]. msb := self nextByte. (signed and: [msb > 127]) ifTrue: [msb := msb - 256]. ^int + (msb bitShift: n * 8 - 8) ] nextPutBytes: n of: anInteger [ "Private - Store the n least significant bytes of int in little-endian format" | int | int := anInteger. n timesRepeat: [self nextPutByte: (int bitAnd: 255). int := int bitShift: -8. (int = 0 and: [anInteger < 0]) ifTrue: [int := 255]] ] species [ ^String ] isPositionable [ "Answer true if the stream supports moving backwards with #skip:." ^true ] ] smalltalk-3.2.5/kernel/CharArray.st0000644000175000017500000005627112123404352014141 00000000000000"====================================================================== | | CharacterArray Method Definitions | | ======================================================================" "====================================================================== | | Copyright 1999, 2000, 2001, 2002, 2006, 2007, 2008, 2009 | Free Software Foundation, Inc. | Written by Steve Byrne and Paolo Bonzini. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" ArrayedCollection subclass: CharacterArray [ CharacterArray class >> fromString: aCharacterArray [ "Make up an instance of the receiver containing the same characters as aCharacterArray, and answer it." ^(self new: aCharacterArray size) replaceFrom: 1 to: aCharacterArray size with: aCharacterArray startingAt: 1; yourself ] CharacterArray class >> lineDelimiter [ "Answer a CharacterArray which one can use as a line delimiter. This is meant to be used on subclasses of CharacterArray." ^self with: Character nl ] CharacterArray class >> isUnicode [ "Answer whether the receiver stores bytes (i.e. an encoded form) or characters (if true is returned)." self subclassResponsibility ] = aString [ "Answer whether the receiver's items match those in aCollection" aString isSymbol ifTrue: [^self == aString]. aString isCharacterArray ifFalse: [^false]. self encoding == aString encoding ifFalse: [^self asUnicodeString = aString asUnicodeString]. "Encoding matches, check the characters." self size = aString size ifFalse: [^false]. self hash == aString hash ifFalse: [^false]. 1 to: self size do: [:i | (self at: i) = (aString at: i) ifFalse: [^false]]. ^true ] < aCharacterArray [ "Return true if the receiver is less than aCharacterArray, ignoring case differences." ^(self caseInsensitiveCompareTo: aCharacterArray) < 0 ] > aCharacterArray [ "Return true if the receiver is greater than aCharacterArray, ignoring case differences." ^(self caseInsensitiveCompareTo: aCharacterArray) > 0 ] <= aCharacterArray [ "Returns true if the receiver is less than or equal to aCharacterArray, ignoring case differences. If is receiver is an initial substring of aCharacterArray, it is considered to be less than aCharacterArray." ^(self caseInsensitiveCompareTo: aCharacterArray) <= 0 ] >= aCharacterArray [ "Returns true if the receiver is greater than or equal to aCharacterArray, ignoring case differences. If is aCharacterArray is an initial substring of the receiver, it is considered to be less than the receiver." ^(self caseInsensitiveCompareTo: aCharacterArray) >= 0 ] sameAs: aCharacterArray [ "Returns true if the receiver is the same CharacterArray as aCharacterArray, ignoring case differences." self size ~= aCharacterArray size ifTrue: [^false]. ^(self caseInsensitiveCompareTo: aCharacterArray) = 0 ] match: aCharacterArray [ "Answer whether aCharacterArray matches the pattern contained in the receiver. # in the receiver means 'match any character', * in receiver means 'match any sequence of characters'." | result | result := self asLowercase matchSubstring: 1 in: aCharacterArray asLowercase at: 1. ^result = aCharacterArray size ] match: aCharacterArray ignoreCase: aBoolean [ "Answer whether aCharacterArray matches the pattern contained in the receiver. # in the receiver means 'match any character', * in receiver means 'match any sequence of characters'. The case of alphabetic characters is ignored if aBoolean is true." | result | aBoolean ifTrue: [^self asLowercase match: aCharacterArray asLowercase ignoreCase: false]. result := self matchSubstring: 1 in: aCharacterArray at: 1. ^result = aCharacterArray size ] indexOf: aCharacterArray matchCase: aBoolean startingAt: anIndex [ "Answer an Interval of indices in the receiver which match the aCharacterArray pattern. # in aCharacterArray means 'match any character', * in aCharacterArray means 'match any sequence of characters'. The first item of the returned interval is >= anIndex. If aBoolean is false, the search is case-insensitive, else it is case-sensitive. If no Interval matches the pattern, answer nil." | result | aBoolean ifFalse: [^self asLowercase indexOf: aCharacterArray asLowercase matchCase: true startingAt: anIndex]. anIndex to: self size do: [:i | result := aCharacterArray matchSubstring: 1 in: self at: i. result notNil ifTrue: [^i to: result]]. ^nil ] isUnicode [ "Answer whether the receiver stores bytes (i.e. an encoded form) or characters (if true is returned)." ^self class isUnicode ] encoding [ "Answer the encoding used by the receiver." self subclassResponsibility ] numberOfCharacters [ "Answer the number of Unicode characters in the receiver. This is not implemented unless you load the I18N package." self notYetImplemented ] contractTo: smallSize [ "Either return myself, or a copy shortened to smallSize characters by inserting an ellipsis (three dots: ...)" | leftSize | self size <= smallSize ifTrue: [^self]. smallSize < 5 ifTrue: [^self copyFrom: 1 to: smallSize]. leftSize := (smallSize - 2) // 2. ^self copyReplaceFrom: leftSize + 1 to: self size - (smallSize - leftSize - 3) with: '...' "First N/2 ... last N/2" ] linesDo: aBlock [ "Evaluate aBlock once for every newline delimited line in the receiver, passing the line to the block." self readStream linesDo: aBlock ] lines [ "Answer an Array of Strings each representing one line in the receiver." ^self readStream lines contents ] substrings [ "Answer an OrderedCollection of substrings of the receiver. A new substring start at the start of the receiver, or after every sequence of white space characters. This message is preserved for backwards compatibility; the ANSI standard mandates `subStrings', with an uppercase s." | oc last | last := 1. oc := OrderedCollection new. 1 to: self size do: [:i | (self at: i) isSeparator ifTrue: [last = i ifFalse: [oc addLast: (self copyFrom: last to: i - 1)]. last := i + 1]]. last <= self size ifTrue: [oc addLast: (self copyFrom: last to: self size)]. ^oc ] subStrings [ "Answer an OrderedCollection of substrings of the receiver. A new substring start at the start of the receiver, or after every sequence of white space characters" | oc last | last := 1. oc := OrderedCollection new. 1 to: self size do: [:i | (self at: i) isSeparator ifTrue: [last = i ifFalse: [oc addLast: (self copyFrom: last to: i - 1)]. last := i + 1]]. last <= self size ifTrue: [oc addLast: (self copyFrom: last to: self size)]. ^oc ] substrings: sep [ "Answer an OrderedCollection of substrings of the receiver. A new substring start at the start of the receiver, or after every occurrence of one of the characters in sep. This message is preserved for backwards compatibility; the ANSI standard mandates `subStrings:', with an uppercase s." | oc last | sep isCharacter ifTrue: [ ^self subStringsChar: sep ]. sep size = 1 ifTrue: [ ^self subStringsChar: sep first ]. last := 1. oc := OrderedCollection new. 1 to: self size do: [:i | (sep includes: (self at: i)) ifTrue: [last = i ifFalse: [oc addLast: (self copyFrom: last to: i - 1)]. last := i + 1]]. last <= self size ifTrue: [oc addLast: (self copyFrom: last to: self size)]. ^oc ] subStrings: sep [ "Answer an OrderedCollection of substrings of the receiver. A new substring start at the start of the receiver, or after every occurrence of one of the characters in sep" | oc last | sep isCharacter ifTrue: [ ^self subStringsChar: sep ]. sep size = 1 ifTrue: [ ^self subStringsChar: sep first ]. last := 1. oc := OrderedCollection new. 1 to: self size do: [:i | (sep includes: (self at: i)) ifTrue: [last = i ifFalse: [oc addLast: (self copyFrom: last to: i - 1)]. last := i + 1]]. last <= self size ifTrue: [oc addLast: (self copyFrom: last to: self size)]. ^oc ] subStringsChar: sepChar [ "Private - Answer an OrderedCollection of substrings of the receiver. A new substring start at the start of the receiver, or after every occurrence of the character sepChar." | oc last | last := 1. oc := OrderedCollection new. 1 to: self size do: [:i | (self at: i) = sepChar ifTrue: [last = i ifFalse: [oc addLast: (self copyFrom: last to: i - 1)]. last := i + 1]]. last <= self size ifTrue: [oc addLast: (self copyFrom: last to: self size)]. ^oc ] bindWith: s1 [ "Answer the receiver with every %1 replaced by the displayString of s1" ^self % {s1} ] bindWith: s1 with: s2 [ "Answer the receiver with every %1 or %2 replaced by s1 or s2, respectively. s1 and s2 are `displayed' (i.e. their displayString is used) upon replacement." ^self % {s1. s2} ] bindWith: s1 with: s2 with: s3 [ "Answer the receiver with every %1, %2 or %3 replaced by s1, s2 or s3, respectively. s1, s2 and s3 are `displayed' (i.e. their displayString is used) upon replacement." ^self % {s1. s2. s3} ] bindWith: s1 with: s2 with: s3 with: s4 [ "Answer the receiver with every %1, %2, %3 or %4 replaced by s1, s2, s3 or s4, respectively. s1, s2, s3 and s4 are `displayed' (i.e. their displayString is used) upon replacement." ^self % {s1. s2. s3. s4} ] bindWithArguments: aCollection [ "Answer the receiver with special escape sequences replaced by elements of aCollection. %n (1<=n<=9, A<=n<=Z) are replaced by the n-th element of aCollection (A being the 10-th element and so on until the 35th). %(string) sequences are accessed as strings, which makes sense only if aCollection is a Dictionary or LookupTable. In addition, the special pattern %n or %(string) is replaced with one of the two strings depending on the element of aCollection being true or false. The replaced elements are `displayed' (i.e. their displayString is used)." ^self % aCollection ] % aCollection [ "Answer the receiver with special escape sequences replaced by elements of aCollection. %n (1<=n<=9, A<=n<=Z) are replaced by the n-th element of aCollection (A being the 10-th element and so on until the 35th). %(string) sequences are accessed as strings, which makes sense only if aCollection is a Dictionary or LookupTable. In addition, the special pattern %n or %(string) is replaced with one of the two strings depending on the element of aCollection being true or false. The replaced elements are `displayed' (i.e. their displayString is used)." | result wasPercent pattern char trueString falseString key value | result := WriteStream on: (self copyEmpty: self size + 20). wasPercent := false. pattern := ReadStream on: self. [pattern atEnd] whileFalse: [char := pattern next. char = $% ifFalse: [result nextPut: char] ifTrue: [ char := pattern next. char = $% ifTrue: [result nextPut: char] ifFalse: [ char = $< ifTrue: [trueString := pattern upTo: $|. falseString := pattern upTo: $>. char := pattern next]. key := char = $( ifTrue: [pattern upTo: $)] ifFalse: [char digitValue]. value := trueString isNil ifTrue: [aCollection at: key] ifFalse: [(aCollection at: key) ifTrue: [trueString] ifFalse: [falseString]]. trueString := falseString := nil. result display: value]]]. ^result contents ] withShellEscapes [ "Answer the receiver with special shell characters converted to a backslash sequence." ^Directory pathSeparator == $\ ifTrue: [ self withWindowsShellEscapes ] ifFalse: [ self withUnixShellEscapes ] ] withWindowsShellEscapes [ "Answer the receiver with Windows shell characters escaped properly." | num result table slashes | table := ##( | t | t := ByteArray new: 256. #($% $" $< $> $| $& $^ $ ) do: [ :each | t at: each codePoint put: 1 ]. t). num := 0. 1 to: self size do: [ :i | num := num + (table at: (self valueAt: i) ifAbsent: [0])]. num = 0 ifTrue: [^self]. result := self copyEmpty writeStream. result nextPut: $". slashes := 0. self do: [:each| (each = $" or: [each = $%]) ifFalse: [ "Backslash is not special per se, but must be treated specially inside quotes." slashes := each = $\ ifTrue: [slashes+1] ifFalse: [0]. result nextPut: each] ifTrue: [ slashes > 0 ifTrue: [result next: slashes put: $\]. slashes := 0. result nextPut: $". each = $% ifTrue: [ result nextPut: $% ]. result nextPut: $"]]. result next: slashes put: $\. result nextPut: $". ^result contents ] withUnixShellEscapes [ "Answer the receiver with special shell characters converted to a backslash sequence." | num result table i j ch | table := ##( | t | t := ByteArray new: 256. #($ $' $" $` $| $^ $> $[ $= $< $; $( $) $* $& $$ $" $! $# $~ ${ $} $? $\) do: [ :each | t at: each codePoint put: 1 ]. t). num := 0. 1 to: self size do: [ :i | num := num + (table at: (self valueAt: i) ifAbsent: [0])]. num = 0 ifTrue: [^self]. result := self copyEmpty: self size + num. i := 1. j := 0. [j < num] whileTrue: [ ch := self valueAt: i. (table at: ch ifAbsent: [0]) = 0 ifFalse: [ result at: j + i put: $\. j := j + 1]. result valueAt: j + i put: ch. i := i + 1]. result replaceFrom: j+i to: self size + num with: self startingAt: i. ^result ] asNumber [ "Parse a Number from the receiver until the input character is invalid and answer the result at this point" ^Number readFrom: (ReadStream on: self) ] asUnicodeString [ "Answer a UnicodeString whose character's codes are the receiver's contents This is not implemented unless you load the I18N package." self subclassResponsibility ] asUppercase [ "Returns a copy of self as an uppercase CharacterArray" | newStr | newStr := self copyEmpty: self size. 1 to: self size do: [:i | newStr at: i put: (self at: i) asUppercase]. ^newStr ] asLowercase [ "Returns a copy of self as a lowercase CharacterArray" | newStr | newStr := self copyEmpty: self size. 1 to: self size do: [:i | newStr at: i put: (self at: i) asLowercase]. ^newStr ] asString [ "But I already am a String! Really!" self subclassResponsibility ] asGlobalKey [ "Return the receiver, ready to be put in the Smalltalk dictionary" ^self asSymbol ] asPoolKey [ "Return the receiver, ready to be put in a pool dictionary" ^self asSymbol ] asClassPoolKey [ "Return the receiver, ready to be put in a class pool dictionary" ^self asSymbol ] asByteArray [ "Return the receiver, converted to a ByteArray of ASCII values" ^self asString asByteArray ] asInteger [ "Parse an Integer number from the receiver until the input character is invalid and answer the result at this point" | result i sign ch value | self isEmpty ifTrue: [^0]. ch := self at: 1. result := ch codePoint - ##($0 codePoint). (result < 0 or: [result > 9]) ifTrue: [result := 0. ch = $- ifTrue: [2 to: self size do: [:i | ch := self at: i. value := ch codePoint - ##($0 codePoint). (value < 0 or: [value > 9]) ifTrue: [^result]. result := result * 10 - value]]] ifFalse: [2 to: self size do: [:i | ch := self at: i. value := ch codePoint - ##($0 codePoint). (value < 0 or: [value > 9]) ifTrue: [^result]. result := result * 10 + value]]. ^result ] fileName [ "But I don't HAVE a file name!" ^nil ] filePos [ "But I don't HAVE a file position!" ^nil ] isNumeric [ "Answer whether the receiver denotes a number" | stream ch | stream := ReadStream on: self. [stream atEnd ifTrue: [^true]. (ch := stream next) isDigit] whileTrue: []. ch = $. ifFalse: [^false]. [ch := stream next. ch isDigit ifFalse: [^false]. stream atEnd] whileFalse. ^true ] asSymbol [ "Returns the symbol corresponding to the CharacterArray" self subclassResponsibility ] trimSeparators [ "Return a copy of the reciever without any spaces on front or back. The implementation is protected against the `all blanks' case." "This is not implemented as two while loops, but as two nested #to:do:'s, for speed" 1 to: self size do: [:start | (self at: start) isSeparator ifFalse: [self size to: start by: -1 do: [:stop | (self at: stop) isSeparator ifFalse: [^self copyFrom: start to: stop]] "to:by:do:"]]. "to:do:" ^'' ] caseInsensitiveCompareTo: aCharacterArray [ "Answer a number < 0 if the receiver is less than aCharacterArray, a number > 0 if it is greater, or 0 if they are equal." "Scan self and aCharacterArray until a character is clearly greater or lesser (All preceding characters must have been equal). If the end is reached, one of the CharacterArrays is a possibly improper initial substring of the other, and for the receiver to be less than aCharacterArray, it must be the initial substring." | c1 c2 | 1 to: (self size min: aCharacterArray size) do: [:i | c1 := (self at: i) asLowercaseValue. c2 := (aCharacterArray at: i) asLowercaseValue. c1 = c2 ifFalse: [^c1 - c2]]. ^self size - aCharacterArray size ] matchSubstring: pp in: aCharacterArray at: i [ "Private - Match the pattern from the pp-th character of the receiver to the characters from the i-th in aCharacterArray. Answer nil if they don't match, else answer the last character making up the pattern" | result s | s := i. self from: pp to: self size keysAndValuesDo: [:p :pc | pc = $* ifTrue: [aCharacterArray size + 1 to: s by: -1 do: [:ss | result := self matchSubstring: p + 1 in: aCharacterArray at: ss. result notNil ifTrue: [^result]]. ^nil]. s > aCharacterArray size ifTrue: [^nil]. pc = $# ifFalse: [pc = (aCharacterArray at: s) ifFalse: [^nil]]. s := s + 1]. ^s - 1 ] isCharacterArray [ ^true ] valueAt: index [ "Answer the ascii value of index-th character variable of the receiver" | shape size | shape := self class shape. (shape == #character or: [shape == #utf32]) ifFalse: [^self subclassResponsibility]. self class isFixed ifTrue: [^self subclassResponsibility]. index isInteger ifFalse: [^SystemExceptions.WrongClass signalOn: index mustBe: SmallInteger]. ^SystemExceptions.IndexOutOfRange signalOn: self withIndex: index ] valueAt: anIndex ifAbsent: aBlock [ "Answer the ascii value of the anIndex-th character of the receiver, or evaluate aBlock and answer the result if the index is out of range." (anIndex between: 1 and: self size) ifFalse: [^aBlock value]. ^self valueAt: anIndex ] valueAt: index put: value [ "Store (Character value: value) in the index-th indexed instance variable of the receiver" | shape size | shape := self class shape. (shape == #character or: [shape == #utf32]) ifFalse: [^self subclassResponsibility]. self class isFixed ifTrue: [^self subclassResponsibility]. self isReadOnly ifTrue: [^SystemExceptions.ReadOnlyObject signal]. index isInteger ifFalse: [^SystemExceptions.WrongClass signalOn: index mustBe: SmallInteger]. index < 1 ifTrue: [^SystemExceptions.IndexOutOfRange signalOn: self withIndex: index]. index > self basicSize ifTrue: [^SystemExceptions.IndexOutOfRange signalOn: self withIndex: index]. value isInteger ifFalse: [SystemExceptions.WrongClass signalOn: value mustBe: SmallInteger]. shape == #character ifTrue: [^SystemExceptions.ArgumentOutOfRange signalOn: value mustBeBetween: 0 and: 255]. ^SystemExceptions.ArgumentOutOfRange signalOn: value mustBeBetween: 0 and: 1114111 ] ] smalltalk-3.2.5/kernel/ContextPart.st0000644000175000017500000003776012130343734014546 00000000000000"====================================================================== | | ContextPart Method Definitions | | ======================================================================" "====================================================================== | | Copyright 1999, 2000, 2001, 2002, 2003, 2007, 2008 | Free Software Foundation, Inc. | Written by Paolo Bonzini. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" Object subclass: ContextPart [ | parent nativeIP ip sp receiver method | ContextPart class >> spIndex [ ^4 ] ContextPart class >> checkPresenceOfJIT [ thisContext isJIT ifTrue: [Smalltalk addFeature: #JIT] ifFalse: [Smalltalk removeFeature: #JIT] ] ContextPart class >> backtrace [ "Print a backtrace from the caller to the bottom of the stack on the Transcript" thisContext parentContext backtraceOn: Transcript ] ContextPart class >> backtraceOn: aStream [ "Print a backtrace from the caller to the bottom of the stack on aStream" thisContext parentContext backtraceOn: aStream ] ContextPart class >> thisContext [ "Return the value of the thisContext variable. Called internally when the variable is accessed." ] backtrace [ "Print a backtrace from the receiver to the bottom of the stack on the Transcript." self backtraceOn: Transcript ] backtraceOn: aStream [ "Print a backtrace from the caller to the bottom of the stack on aStream." | ctx | ctx := self. [ctx isNil or: [ctx isEnvironment]] whileFalse: [ctx isDisabled ifFalse: [ctx printOn: aStream. aStream nl]. ctx := ctx parentContext] ] currentLineInFile [ "Answer the 1-based number of the line that is pointed to by the receiver's instruction pointer, relative to the method's file. The implementation is slow unless the DebugTools package is loaded." ^self currentLine + self method sourceCodeLinesDelta ] currentFileName [ "Answer the name of the file where the method source code is" | sourceCode | sourceCode := self method methodSourceCode. sourceCode isString ifTrue: [ ^'a String' ]. sourceCode isNil ifTrue: [ ^'source not available' ]. ^sourceCode printedFileName ] currentLine [ "Answer the 1-based number of the line that is pointed to by the receiver's instruction pointer. The DebugTools package caches information, thus making the implementation faster." ^self method sourceCodeMap at: (self ip - 1 max: 1) ifAbsent: [1] ] debugger [ "Answer the debugger that is attached to the given context. It is always nil unless the DebugTools package is loaded." ^nil ] debuggerClass [ "Answer which debugger should be used to debug the current context chain. The class with the highest debugging priority is picked among those mentioned in the chain." | ctx debuggerClass currentClass last | ctx := self. [currentClass := ctx receiver class debuggerClass. currentClass isNil ifTrue: [^nil]. (debuggerClass isNil or: [currentClass debuggingPriority > debuggerClass debuggingPriority]) ifTrue: [debuggerClass := currentClass]. ctx parentContext isNil or: [ctx isEnvironment]] whileFalse: [ctx := ctx parentContext]. ^debuggerClass ] isInternalExceptionHandlingContext [ "Answer whether the receiver is a context that should be hidden to the user when presenting a backtrace." self subclassResponsibility ] client [ "Answer the client of this context, that is, the object that sent the message that created this context. Fail if the receiver has no parent" ^self parentContext receiver ] environment [ "To create a valid execution environment for the interpreter even before it starts, GST creates a fake context whose selector is nil and which can be used as a marker for the current execution environment. This method answers that context. For processes, it answers the process block itself" | ctx next | ctx := self. [next := ctx parentContext. ctx isEnvironment | next isNil] whileFalse: [ctx := next]. ^ctx ] initialIP [ "Answer the value of the instruction pointer when execution starts in the current context" ^0 ] isDisabled [ "Answers whether the context is skipped when doing a return. Contexts are marked as disabled whenever a non-local return is done (either by returning from the enclosing method of a block, or with the #continue: method of ContextPart) and there are unwind contexts such as those created by #ensure:. All non-unwind contexts are then marked as disabled." self subclassResponsibility ] isUnwind [ "Answers whether the context must continue execution even after a non-local return (a return from the enclosing method of a block, or a call to the #continue: method of ContextPart). Such contexts are created by #ensure:." self subclassResponsibility ] isEnvironment [ "To create a valid execution environment for the interpreter even before it starts, GST creates a fake context which invokes a special ``termination'' method. Such a context can be used as a marker for the current execution environment. Answer whether the receiver is that kind of context." self subclassResponsibility ] isProcess [ "Answer whether the receiver represents a process context, i.e. a context created by BlockClosure>>#newProcess. Such a context can be recognized because it has no parent but its flags are different from those of the contexts created by the VM's prepareExecutionEnvironment function." ^self parentContext isNil & self isEnvironment not ] parentContext [ "Answer the context that called the receiver" ^parent ] parentContext: aContext [ "Set the context to which the receiver will return" "Fixed typing isn't usually good, but this is too important" aContext class superclass == ContextPart | aContext isNil ifFalse: [^SystemExceptions.WrongClass signalOn: aContext mustBe: ContextPart]. parent := aContext ] ip [ "Answer the current instruction pointer into the receiver" "This funny implementation thwarts the interpreter's optimizing effort" ^ip yourself ] ip: newIP [ "Set the instruction pointer for the receiver" "Fixed typing isn't usually good, but this is too important" newIP isSmallInteger ifFalse: [^SystemExceptions.WrongClass signalOn: newIP mustBe: SmallInteger]. ip := newIP ] size [ "Answer the number of valid fields for the receiver. Any read access from (self size + 1) to (self basicSize) will give nil." ^self sp + 1 ] at: index [ "Answer the index-th slot in the receiver. Any read access from (self size + 1) to (self basicSize) will give nil." (index > self size and: [ index <= self basicSize ]) ifTrue: [^nil]. ^super at: index ] at: index put: anObject [ "Answer the index-th slot in the receiver. Any write access from (self size + 1) to (self basicSize) will give an error unless nil is being written. This is because doing such an access first, and then updating sp, is racy: the garbage collector may trigger in the middle and move anObject, but the slot in the context won't be adjusted." (index > self size and: [ index <= self basicSize ]) ifTrue: [ anObject isNil ifFalse: [ ^SystemExceptions.InvalidArgument signalOn: self ] ]. ^super at: index put: anObject ] sp [ "Answer the current stack pointer into the receiver" "This funny implementation thwarts the interpreter's optimizing effort" ^sp yourself ] validSize [ "Answer how many elements in the receiver should be inspected" ^self size ] numArgs [ "Answer the number of arguments passed to the receiver" ^self method numArgs ] numTemps [ "Answer the number of temporaries used by the receiver" ^self method numTemps ] push: anObject [ "Push an object on the receiver's stack." "Since the newly accessible slots may have contained garbage, this method makes them valid *before* they become accessible." self at: sp + 1 put: nil. sp := sp + 1. self at: sp put: anObject. ] sp: newSP [ "Set the stack pointer for the receiver." "Storing into the stack pointer is a potentially dangerous thing, so this code tests that sp is effectively a number. Also, since the newly accessible slots may have contained garbage, this method stores nil into any cells that become accessible." newSP isSmallInteger ifFalse: [^SystemExceptions.WrongClass signalOn: newSP mustBe: SmallInteger]. newSP > sp ifTrue: [sp + 1 to: newSP do: [:i | self at: i put: nil]]. sp := newSP ] method [ "Return the CompiledMethod being executed" ^method ] methodClass [ "Return the class in which the CompiledMethod being executed is defined" ^self method methodClass ] isBlock [ "Answer whether the receiver is a block context" self subclassResponsibility ] receiver [ "Return the receiver (self) for the method being executed" "This funny implementation thwarts the interpreter's optimizing effort" ^receiver yourself ] selector [ "Return the selector for the method being executed" ^self method selector ] home [ "Answer the MethodContext to which the receiver refers" self subclassResponsibility ] isJIT [ ^nativeIP ~~ 0 ] deepCopy [ "Answer a copy of the entire stack, but don't copy any of the other instance variables of the context." ^self copyStack ] copyStack [ "Answer a copy of the entire stack." | ret ctx | ret := ctx := self copy. [ctx parentContext isNil] whileFalse: [ctx parentContext: (ctx := ctx parentContext copy)]. ^ret ] scanBacktraceForAttribute: selector do: aBlock [ "Scan the backtrace for contexts which have the attribute selector listed in selectors; if one is found, invoke aBlock passing the context and the attribute." | ctx attr | ctx := self. [(ctx isBlock not and: [attr := ctx method attributeAt: selector ifAbsent: [nil]. attr notNil]) ifTrue: [aBlock value: ctx value: attr]. ctx isEnvironment or: [(ctx := ctx parentContext) isNil]] whileFalse ] scanBacktraceFor: selectors do: aBlock [ "Scan the backtrace for contexts whose selector is among those listed in selectors; if one is found, invoke aBlock passing the context." | ctx | ctx := self. [ctx isNil or: [ctx isEnvironment]] whileFalse: [(ctx isBlock not and: [selectors includes: ctx selector]) ifTrue: [aBlock value: ctx]. ctx := ctx parentContext] ] securityCheckForName: name [ self isUntrusted ifFalse: [^self]. ^self doSecurityCheckForName: name actions: #() target: nil ] securityCheckForName: name action: action [ self isUntrusted ifFalse: [^self]. ^self doSecurityCheckForName: name actions: {action} target: nil ] securityCheckForName: name target: target [ self isUntrusted ifFalse: [^self]. ^self doSecurityCheckForName: name actions: #() target: target ] securityCheckForName: name actions: actions target: target [ self isUntrusted ifFalse: [^self]. ^self doSecurityCheckForName: name actions: actions target: target ] doSecurityCheckForName: name actions: actions target: target [ | perm ctx | perm := (Permission new) name: name actions: actions; target: target. (self checkSecurityFor: perm) ifFalse: [(SecurityError for: perm) signal] ] checkSecurityFor: perm [ "First of all, check against the static permissions for this context." | state foundAnnotation | (self receiver class check: perm) ifFalse: [^false]. "Then, check the dynamic permissions. So: 1) check if a method was specifically denying access, 2) look for a deeper context whose static permissions denies access, but stop if a method is specifically granting access." self method isAnnotated ifTrue: [foundAnnotation := false. self method attributesDo: [:each | | newPerm | each selector = #permission: ifTrue: [newPerm := each arguments at: 1. (newPerm implies: perm) ifTrue: ["Should we check if the granted permission is statically available? Of course, you can only grant permissions if you own them statically, so the real question is, should we check perm or newPerm? The answer is perm (which has already been found to be available), hence we can skip an expensive static permission check. Suppose we have a method that grants access to all files: it makes more sense if it means ``grant access to all files allowed by the class security policy'', rather than ``grant access to all files if the security policy allows it, else do not grant access to any file''." foundAnnotation := true. state := newPerm isAllowing]]]. foundAnnotation ifTrue: [^state]]. "Nope, no special regulations were found in this method. Look in the parent context, and grant permission if the bottom is reached." ^self parentContext isNil or: [self parentContext checkSecurityFor: perm] ] continue: anObject [ "Resume execution from the receiver, faking that the context on top of it in the execution chain has returned anObject. The receiver must belong to the same process as the executing context, otherwise the results are not predictable. All #ensure: (and possibly #ifCurtailed:) blocks between the currently executing context and the receiver are evaluated (which is not what would happen if you directly bashed at the parent context of thisContext)." self badReturnError ] ] smalltalk-3.2.5/kernel/HashedColl.st0000644000175000017500000002620012130343734014264 00000000000000"====================================================================== | | HashedCollection Method Definitions | | ======================================================================" "====================================================================== | | Copyright 2001, 2002, 2003, 2008, 2009 Free Software Foundation, Inc. | Written by Paolo Bonzini. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" Collection subclass: HashedCollection [ | tally | HashedCollection class >> primNew: realSize [ ^self basicNew: realSize ] HashedCollection class >> new [ "Answer a new instance of the receiver with a default size" ^self new: 0 ] HashedCollection class >> new: anInteger [ "Answer a new instance of the receiver with the given capacity" | realSize | realSize := 8 max: (anInteger * 4 + 2) // 3. (realSize bitAnd: realSize - 1) = 0 ifFalse: [realSize := 1 bitShift: realSize highBit]. ^(self primNew: realSize) initialize: realSize ] HashedCollection class >> withAll: aCollection [ "Answer a collection whose elements are all those in aCollection" ^(self new: aCollection size * 2) addAll: aCollection; yourself ] at: index [ self shouldNotImplement ] at: index put: value [ self shouldNotImplement ] add: newObject [ "Add newObject to the set, if and only if the set doesn't already contain an occurrence of it. Don't fail if a duplicate is found. Answer anObject" | index | newObject isNil ifTrue: [^newObject]. index := self findIndex: newObject. (self primAt: index) isNil ifTrue: [ self incrementTally ifTrue: [index := self findIndex: newObject]. self primAt: index put: newObject]. ^newObject ] remove: oldObject ifAbsent: anExceptionBlock [ "Remove oldObject from the set. If it is found, answer oldObject. Otherwise, evaluate anExceptionBlock and answer its value." | index | index := self findIndexOrNil: oldObject. index isNil ifTrue: [^anExceptionBlock value]. self primAt: index put: nil. self decrementTally. self rehashObjectsAfter: index. ^oldObject ] shallowCopy [ "Returns a shallow copy of the receiver (the instance variables are not copied)" ^(self copyEmpty: self capacity) copyAllFrom: self; yourself ] deepCopy [ "Returns a deep copy of the receiver (the instance variables are copies of the receiver's instance variables)" | newHashedCollection | newHashedCollection := self copyEmpty: self capacity. self do: [:each | newHashedCollection addWhileGrowing: each copy]. ^newHashedCollection ] includes: anObject [ "Answer whether the receiver contains an instance of anObject." ^(self findIndexOrNil: anObject) notNil ] isEmpty [ "Answer whether the receiver is empty." ^tally == 0 ] occurrencesOf: anObject [ "Return the number of occurrences of anObject. Since we're a set, this is either 0 or 1. Nil is never directly in the set, so we special case it (the result is always 1)." anObject isNil ifTrue: [^1]. ^(self includes: anObject) ifTrue: [1] ifFalse: [0] ] capacity [ "Answer how many elements the receiver can hold before having to grow." ^self primSize * 3 // 4 ] size [ "Answer the receiver's size" ^tally ] hash [ "Return the hash code for the members of the set. Since order is unimportant, we use a commutative operator to compute the hash value." | hashValue | hashValue := tally. self do: [:member | hashValue := hashValue bitXor: (self hashFor: member) scramble]. ^hashValue ] = aHashedCollection [ "Returns true if the two sets have the same membership, false if not" self class == aHashedCollection class ifFalse: [^false]. self == aHashedCollection ifTrue: [^true]. tally = aHashedCollection size ifFalse: [^false]. self do: [:element | (aHashedCollection includes: element) ifFalse: [^false]]. ^true ] do: aBlock [ "Enumerate all the non-nil members of the set" self beConsistent. 1 to: self primSize do: [:i | (self primAt: i) notNil ifTrue: [aBlock value: (self primAt: i)]] ] storeOn: aStream [ "Store on aStream some Smalltalk code which compiles to the receiver" | hasElements | aStream nextPut: $(; nextPutAll: self class storeString; nextPutAll: ' new'. hasElements := false. self do: [:element | aStream nextPutAll: ' add: '. element storeOn: aStream. aStream nextPut: $;. hasElements := true]. hasElements ifTrue: [aStream nextPutAll: ' yourself']. aStream nextPut: $) ] rehash [ "Rehash the receiver" | copy n obj | copy := Array new: self size. self resetTally. n := 0. 1 to: self primSize do: [:i | (obj := self primAt: i) isNil ifFalse: [copy at: (n := n + 1) put: obj. self primAt: i put: nil]]. copy do: [:each | self addWhileGrowing: each] ] initialize: anInteger [ "Private - Instance variable initialization." self resetTally ] resetTally [ "Private - Reset the tally of elements in the receiver." tally := 0 ] incrementTally [ "Answer whether the collection's size varied" | grown | (grown := tally >= (self primSize * 3 // 4)) ifTrue: [self growBy: self capacity]. tally := tally + 1. ^grown ] decrementTally [ "Answer whether the collection's size varied" tally := tally - 1. ^false ] addWhileGrowing: value [ "Private - Add the newObject association to the receiver. Don't check for the set to be full - we want SPEED!." self primAt: (self findElementIndex: value) put: value. tally := tally + 1. ^value ] copyEmpty [ "Answer an empty copy of the receiver" ^self copyEmpty: self capacity ] copyAllFrom: aHashedCollection [ | value | 1 to: aHashedCollection primSize do: [:index | value := aHashedCollection primAt: index. value isNil ifFalse: [self addWhileGrowing: value]]. ^self ] rehashObjectsAfter: index [ "Private - Rehashes all the objects in the collection after index to see if any of them hash to index. If so, that object is copied to index, and the process repeats with that object's index, until a nil is encountered." | i j size element | i := index. size := self primSize. [i = size ifTrue: [i := 1] ifFalse: [i := i + 1]. element := self primAt: i. element notNil] whileTrue: [self primAt: i put: nil. j := self findElementIndex: element. self primAt: j put: element] ] hashFor: anObject [ "Return an hash value for the item, anObject" self subclassResponsibility ] findElementIndex: anObject [ "Tries to see where anObject can be placed as an indexed variable. As soon as nil is found, the index of that slot is answered. anObject also comes from an indexed variable." | index size element | self beConsistent. "Sorry for the lack of readability, but I want speed... :-)" index := (anObject hash scramble bitAnd: (size := self primSize) - 1) + 1. [(element := self primAt: index) isNil ifTrue: [^index]. index == size ifTrue: [index := 1] ifFalse: [index := index + 1]] repeat ] findIndex: anObject [ "Tries to see if anObject exists as an indexed variable. As soon as nil or anObject is found, the index of that slot is answered" self subclassResponsibility ] findIndexOrNil: anObject [ "Finds the given object in the set and returns its index. If the set doesn't contain the object, answer nil." | index | index := self findIndex: anObject. (self primAt: index) isNil ifTrue: [^nil]. ^index ] grow [ ^self growBy: self capacity ] growBy: delta [ "Private - Grow by the receiver by delta places" | newSize newHashedCollection | newSize := self primSize + delta. newHashedCollection := self copyEmpty: self capacity + delta. newHashedCollection copyAllFrom: self. ^self become: newHashedCollection ] postLoad [ "Called after loading an object; rehash the collection because identity objects will most likely mutate their hashes." self rehash ] postStore [ "Called after an object is dumped. Do nothing -- necessary because by default this calls #postLoad by default" ] primAt: anIndex [ "Private - Answer the anIndex-th item of the hash table for the receiver. Using this instead of basicAt: allows for easier changes in the representation" self checkIndexableBounds: anIndex ] primAt: anIndex put: value [ "Private - Store value in the anIndex-th item of the hash table for the receiver. Using this instead of basicAt:put: allows for easier changes in the representation" self checkIndexableBounds: anIndex put: value ] primSize [ "Private - Answer the size of the hash table for the receiver. Using this instead of basicSize allows for easier changes in the representation" ] ] smalltalk-3.2.5/kernel/File.st0000644000175000017500000004145212123404352013137 00000000000000"====================================================================== | | File Method Definitions | | ======================================================================" "====================================================================== | | Copyright 1988,92,94,95,99,2000,2001,2002,2005,2006,2007,2008,2009 | Free Software Foundation, Inc. | Written by Paolo Bonzini. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" FilePath subclass: File [ | path stat isSymbolicLink | Epoch := nil. File class >> initialize [ "Initialize the receiver's class variables" Epoch := DateTime year: 2000 day: 1 hour: 0 minute: 0 second: 0 ] File class >> stringError: errno [ "Answer C strerror's result for errno." ] File class >> errno [ "Answer the current value of C errno." ] File class >> checkError [ "Return whether an error had been reported or not. If there had been one, raise an exception too" ^self checkError: self errno ] File class >> checkError: errno [ "The error with the C code `errno' has been reported. If errno >= 1, raise an exception" errno < 1 ifTrue: [^false]. SystemExceptions.FileError signal: (self stringError: errno). ^true ] File class >> setTimeFor: fileName atime: atimeSec mtime: mtimeSec [ ] File class >> setOwnerFor: fileName owner: ownerString group: groupString [ ] File class >> path: aString [ "Answer a new file with the given path. The path is not validated until some of the fields of the newly created objects are accessed" ^self basicNew init: aString ] File class >> name: aName [ "Answer a new file with the given path. The path is turned into an absolute path." ^self path: (self fullNameFor: aName) ] File class >> touch: fileName [ "Update the timestamp of the file with the given path name." (self path: fileName) touch ] File class >> symlink: srcName as: destName [ "Create a symlink for the srcName file with the given path name" (self path: srcName) symlinkAs: destName ] File class >> symlink: destName from: srcName [ "Create a symlink named destName file from the given path (relative to destName)" (self path: destName) symlinkFrom: srcName ] File class >> remove: fileName [ "Remove the file with the given path name" (self path: fileName) remove ] File class >> rename: oldFileName to: newFileName [ "Rename the file with the given path name oldFileName to newFileName" (self path: oldFileName) renameTo: newFileName ] File class >> exists: fileName [ "Answer whether a file with the given name exists" ^(self path: fileName) exists ] File class >> isReadable: fileName [ "Answer whether a file with the given name exists and is readable" ^(self path: fileName) isReadable ] File class >> isWriteable: fileName [ "Answer whether a file with the given name exists and is writeable" ^(self path: fileName) isWriteable ] File class >> isExecutable: fileName [ "Answer whether a file with the given name exists and can be executed" ^(self path: fileName) isExecutable ] File class >> isAccessible: fileName [ "Answer whether a directory with the given name exists and can be accessed" ^(self path: fileName) isAccessible ] File class >> executable [ "Answer the full path to the executable being run." ^self path: ExecutableFileName ] File class >> image [ "Answer the full path to the image being used." ^self path: ImageFileName ] = aFile [ "Answer whether the receiver represents the same file as the receiver." ^self class == aFile class and: [ self asString = aFile asString ] ] hash [ "Answer a hash value for the receiver." ^self asString hash ] lstatOn: fileName into: statStruct [ ] statOn: fileName into: statStruct [ ] openDir: dirName [ ] closeDir: dirObject [ ] primChmod: name mode: mode [ ] primIsReadable: name [ ] primIsWriteable: name [ ] primIsExecutable: name [ ] primSymlink: srcName as: destName [ ] primUnlink: fileName [ ] primRename: oldFileName to: newFileName [ ] primRemoveDir: fileName [ ] primCreateDir: dirName mode: mode [ ] extractDirentName: dirent [ ] readDir: dirObject [ ] rewindDir: dirObject [ ] , aName [ "Answer an object of the same kind as the receiver, whose name is suffixed with aName." ^self class path: self name, aName ] asString [ "Answer the name of the file identified by the receiver" ^path ] name [ "Answer the name of the file identified by the receiver" ^File fullNameFor: self asString ] size [ "Answer the size of the file identified by the receiver" ^self stat stSize ] mode [ "Answer the permission bits for the file identified by the receiver" ^self stat stMode bitAnd: 4095 ] mode: anInteger [ "Set the permission bits for the file identified by the receiver to be anInteger." (self primChmod: self asString mode: (anInteger bitAnd: 4095)) < 0 ifTrue: [ File checkError ] ] isFileSystemPath [ "Answer whether the receiver corresponds to a real filesystem path." ^true ] isSocket [ "Answer whether the file is an AF_UNIX socket." self exists ifFalse: [ ^false ]. ^(self stat stMode bitAnd: 8r170000) = 8r140000 ] isDirectory [ "Answer whether the file is a directory." self exists ifFalse: [ ^false ]. ^(self stat stMode bitAnd: 8r170000) = 8r40000 ] isSymbolicLink [ "Answer whether the file is a symbolic link." isSymbolicLink isNil ifTrue: [self refresh]. ^isSymbolicLink ] lastAccessTime [ "Answer the last access time of the file identified by the receiver" ^self getDateAndTime: self stat stAtime ] lastChangeTime [ "Answer the last change time of the file identified by the receiver (the `last change time' has to do with permissions, ownership and the like). On some operating systems, this could actually be the file creation time." ^self getDateAndTime: self stat stCtime ] creationTime [ "Answer the creation time of the file identified by the receiver. On some operating systems, this could actually be the last change time (the `last change time' has to do with permissions, ownership and the like)." ^self getDateAndTime: self stat stCtime ] lastModifyTime [ "Answer the last modify time of the file identified by the receiver (the `last modify time' has to do with the actual file contents)." ^self getDateAndTime: self stat stMtime ] refresh [ "Refresh the statistics for the receiver" stat isNil ifTrue: [stat := Kernel.Stat new]. (self lstatOn: self asString into: stat) < 0 ifTrue: [File checkError]. isSymbolicLink := (stat stMode bitAnd: 61440) = 40960. "S_IFLNK" isSymbolicLink ifTrue: [self statOn: self asString into: stat. File errno] ] exists [ "Answer whether a file with the name contained in the receiver does exist." stat isNil ifTrue: [stat := Kernel.Stat new]. (self lstatOn: self asString into: stat) < 0 ifTrue: [^false]. isSymbolicLink := (stat stMode bitAnd: 61440) = 40960. "S_IFLNK" isSymbolicLink ifTrue: [self statOn: self asString into: stat]. ^true ] isReadable [ "Answer whether a file with the name contained in the receiver does exist and is readable" ^self primIsReadable: self asString ] isWriteable [ "Answer whether a file with the name contained in the receiver does exist and is writeable" ^self primIsWriteable: self asString ] isAccessible [ "Answer whether a directory with the name contained in the receiver does exist and is accessible" ^self isDirectory and: [self primIsExecutable: self asString] ] isExecutable [ "Answer whether a file with the name contained in the receiver does exist and is executable" ^self isFile and: [self primIsExecutable: self asString] ] isAbsolute [ "Answer whether the receiver identifies an absolute path." ^File isAbsolute: self asString ] owner: ownerString group: groupString [ "Set the receiver's owner and group to be ownerString and groupString." (self class setOwnerFor: self asString owner: ownerString group: groupString) < 0 ifTrue: [ File checkError ] ] lastAccessTime: accessDateTime lastModifyTime: modifyDateTime [ "Set the receiver's timestamps to be accessDateTime and modifyDateTime." (self class setTimeFor: self asString atime: (self secondsFromDateTime: accessDateTime) mtime: (self secondsFromDateTime: modifyDateTime)) < 0 ifTrue: [ File checkError ] ] open: class mode: mode ifFail: aBlock [ "Open the receiver in the given mode (as answered by FileStream's class constant methods)" ^class fopen: self asString mode: mode ifFail: aBlock ] remove [ "Remove the file with the given path name" | result | result := self isDirectory ifTrue: [self primRemoveDir: self asString] ifFalse: [self primUnlink: self asString]. result < 0 ifTrue: [ File checkError ] ] symlinkFrom: srcName [ "Create the receiver as a symlink from path destName" (self primSymlink: srcName as: self asString) < 0 ifTrue: [ File checkError ] ] renameTo: newFileName [ "Rename the file with the given path name to newFileName" (self primRename: self asString to: newFileName) < 0 ifTrue: [ File checkError ] ] secondsFromDateTime: aDateTime [ "Private - Convert a time expressed in seconds from 1/1/2000 to an array of two Smalltalk Date and Time objects" ^aDateTime asSeconds - Epoch asSeconds - (aDateTime offset asSeconds - Epoch offset asSeconds) ] getDateAndTime: time [ "Private - Convert a time expressed in seconds from 1/1/2000 to a Smalltalk DateTime object." ^Epoch + (Duration seconds: time) offset: (Duration seconds: Time timezoneBias) ] stat [ "Private - Answer the receiver's statistics' C struct" stat isNil ifTrue: [self refresh]. ^stat ] createDirectory [ "Create the receiver as a directory." (self primCreateDir: self asString mode: 8r777) < 0 ifTrue: [ File checkError ] ] namesDo: aBlock [ "Evaluate aBlock once for each file in the directory represented by the receiver, passing its name. aBlock should not return." | dir entry | dir := self openDir: self asString. dir isNil ifTrue: [^File checkError]. [[(entry := self readDir: dir) notNil] whileTrue: [aBlock value: (self extractDirentName: entry)]] ensure: [self closeDir: dir]. File checkError. ] symlinkAs: destName [ "Create destName as a symbolic link of the receiver. The appropriate relative path is computed automatically." | relPath | relPath := File pathFrom: destName to: self asString. (self class path: destName) symlinkFrom: relPath ] pathFrom: dir [ "Compute the relative path from the directory dirName to the receiver" ^File pathFrom: (dir / 'somefile') asString to: self asString. ] pathTo: destName [ "Compute the relative path from the receiver to destName." ^File pathFrom: (self / 'somefile') asString to: destName asString. ] full [ "Answer the full name of the receiver, resolving the `.' and `..' directory entries, and answer the result. Answer nil if the name is invalid (such as '/usr/../../badname')" self isAbsolute ifTrue: [ ^self ]. ^self class path: (File fullNameFor: self name) ] at: aString [ "Answer a File or Directory object as appropriate for a file named 'aName' in the directory represented by the receiver." ^self class path: (self nameAt: aString asString) ] init: aString [ "Private - Initialize the receiver's instance variables" path := aString ] ] Namespace current: Kernel [ Object subclass: Stat [ | stMode stSize stAtime stMtime stCtime | stMode [ ^stMode ] stSize [ ^stSize ] stAtime [ ^stAtime ] stMtime [ ^stMtime ] stCtime [ ^stCtime ] ] ] String extend [ / aName [ "Answer a File object as appropriate for a file named 'aName' in the directory represented by the receiver." ^(File path: self) at: aName ] asFile [ "Answer a File object for the file whose name is in the receiver." ^(File path: self) ] ] Eval [ File initialize ] smalltalk-3.2.5/kernel/Iterable.st0000644000175000017500000001617012123404352014006 00000000000000"====================================================================== | | Iterable Method Definitions | | ======================================================================" "====================================================================== | | Copyright 2008, 2009 Free Software Foundation, Inc. | Written by Paolo Bonzini. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" Object subclass: Iterable [ Iterable class >> isUnicode [ "Answer true; the receiver is able to store arbitrary Unicode characters." self subclassResponsibility ] , anIterable [ "Answer an iterable that enumerates first the elements of the receiver and then the elements of anIterable." self subclassResponsibility ] ifNil: nilBlock ifNotNilDo: iterableBlock [ "Evaluate nilBlock if the receiver is nil, else evaluate iterableBlock with each element of the receiver (which should be an Iterable)." self do: iterableBlock ] ifNotNilDo: iterableBlock [ "Evaluate iterableBlock with each element of the receiver (which should be an Iterable) if not nil. Else answer nil" self do: iterableBlock ] ifNotNilDo: iterableBlock ifNil: nilBlock [ "Evaluate nilBlock if the receiver is nil, else evaluate iterableBlock, passing each element of the receiver (which should be an Iterable)." self do: iterableBlock ] do: aBlock [ "Enumerate each object of the receiver, passing them to aBlock" self subclassResponsibility ] do: aBlock separatedBy: separatorBlock [ "Enumerate each object of the receiver, passing them to aBlock. Between every two invocations of aBlock, invoke separatorBlock" | first | first := true. self do: [:each | first ifTrue: [first := false] ifFalse: [separatorBlock value]. aBlock value: each] ] select: aBlock [ "Answer a new instance of a Collection containing all the elements in the receiver which, when passed to aBlock, answer true" self subclassResponsibility ] reject: aBlock [ "Answer a new instance of a Collection containing all the elements in the receiver which, when passed to aBlock, don't answer true" self subclassResponsibility ] collect: aBlock [ "Answer a new instance of a Collection containing all the results of evaluating aBlock passing each of the receiver's elements" self subclassResponsibility ] detect: aBlock ifNone: exceptionBlock [ "Search the receiver for an element for which aBlock returns true. If some does, answer it. If none does, answer the result of evaluating aBlock" self do: [:element | (aBlock value: element) ifTrue: [^element]]. ^exceptionBlock value ] count: aBlock [ "Count the elements of the receiver for which aBlock returns true, and return their number." | count | count := 0. self do: [:element | (aBlock value: element) ifTrue: [count := count + 1]]. ^count ] allSatisfy: aBlock [ "Search the receiver for an element for which aBlock returns false. Answer true if none does, false otherwise." self do: [:element | (aBlock value: element) ifFalse: [^false]]. ^true ] noneSatisfy: aBlock [ "Search the receiver for an element for which aBlock returns true. Answer true if none does, false otherwise." self do: [:element | (aBlock value: element) ifTrue: [^false]]. ^true ] anySatisfy: aBlock [ "Search the receiver for an element for which aBlock returns true. Answer true if some does, false otherwise." self do: [:element | (aBlock value: element) ifTrue: [^true]]. ^false ] conform: aBlock [ "Search the receiver for an element for which aBlock returns false. Answer true if none does, false otherwise." self do: [:element | (aBlock value: element) ifFalse: [^false]]. ^true ] contains: aBlock [ "Search the receiver for an element for which aBlock returns true. Answer true if some does, false otherwise." self do: [:element | (aBlock value: element) ifTrue: [^true]]. ^false ] detect: aBlock [ "Search the receiver for an element for which aBlock returns true. If some does, answer it. If none does, fail" ^self detect: aBlock ifNone: [SystemExceptions.NotFound signal: 'object not found'] ] fold: binaryBlock [ "First, pass to binaryBlock the first and second elements of the receiver; for each subsequent element, pass the result of the previous evaluation and an element. Answer the result of the last invocation, or the first element if the collection has size 1. Fail if the collection is empty." | result marker | result := marker := Object new. self do: [:element | result := result == marker ifTrue: [element] ifFalse: [binaryBlock value: result value: element]]. result == marker ifTrue: [^SystemExceptions.EmptyCollection signalOn: self]. ^result ] inject: thisValue into: binaryBlock [ "First, pass to binaryBlock thisValue and the first element of the receiver; for each subsequent element, pass the result of the previous evaluation and an element. Answer the result of the last invocation." | result | result := thisValue. self do: [:element | result := binaryBlock value: result value: element]. ^result ] nextPutAllOn: aStream [ "Write all the objects in the receiver to aStream" self do: [ :each | aStream nextPut: each ] ] readStream [ "Return a stream with the same contents as the receiver." self subclassResponsibility ] ] smalltalk-3.2.5/kernel/CompildCode.st0000644000175000017500000007701012123404352014441 00000000000000"====================================================================== | | CompiledCode Method Definitions | | ======================================================================" "====================================================================== | | Copyright 2000,2001,2002,2003,2004,2005,2007,2008,2009 | Free Software Foundation, Inc. | Written by Paolo Bonzini. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" ArrayedCollection subclass: CompiledCode [ | literals header | CompiledCode class >> specialSelectors [ "Answer an array of message names that don't need to be in literals to be sent in a method. Their position here reflects their integer code in bytecode." ^#(#+ #- #< #> #<= #>= #= #~= #* #/ #\\ #bitXor: #bitShift: #// #bitAnd: #bitOr: #at: #at:put: #size #class #isNil #notNil #value #value: #== #javaAsInt #javaAsLong nil nil nil nil nil #new: #thisContext #callInto: #narrow #nextPutAll: #yourself #, #on: #subclassResponsibility #add: #nl #printString #contents #name #isEmpty #properties #container #error: #first #tclEval: #collect: #tclResult #key #asTkString #abs #basicNew #negated #not #close #includes: #at:ifAbsent: #asSymbol #with: #copy #copyFrom:to: #print: #last #initialize #tclEval:with:with: #assert: #primitiveFailed #initialize: #asString #cr #should: #arguments #x #readStream #y #tclEval:with:with:with: #asInteger #space #new #shouldNotImplement #-> #numArgs #with:with: #species #blox #step #signal #parent #selector #at:ifPresent: #to: #addLast: #squared #generality #signalOn:mustBe: #ensure: #body #max: #keysAndValuesDo: #printOn: #isKindOf: #visitNode: #addAll: #isInteger #name: #hash #sqrt #beep #primAt: #environment #position #at:ifAbsentPut: #signal: #postCopy #readFrom: #coefficients: #clientPI #flush #value:value: #asFloatD #on:do: #basicAt:put: #primSize #evaluate #connected #reset #copyEmpty: #start #signalOn: #basicAt: #asClass #ln #implementation #checkResponse #average #upTo: #receiver #peek #basicSize #x:y: #foregroundColor: #rows: #text #exp #statements #body: #| #sizeof #includesKey: #pi #completedSuccessfully #writeStream #superclass #arguments: #state #truncated #inject:into: #replaceFrom:to:with:startingAt: #current #between:and: #retryRelationalOp:coercing: #connectIfClosed #detect:ifNone: #checkError #executeAndWait:arguments: #min: #width #parentContext #removeLast #zero #bindWith:with: #temporaries #asOop #width:height: #methodDictionary #accumulate: #count #asLowercase #asArray #exists #signalOn:what: #select: #parent: #selector: #signalOn:withIndex: #bind:to:of:parameters: #return: #~~ #changeState: #sign #variance #asVector #getResponse #wait #instanceClass #asOrderedCollection #keys #asFloat #random #origin #superspace #stop #perform: #backgroundColor: #login #data: #nextToken #primAt:put: #method #allSatisfy: #position: #default #atAllPut: #asSortedCollection #invalidArgsError: #nameIn: #allSubclassesDo: #signalError #height #source #asNumber #primitive #store: #updateViews #errorContents: #displayString #skipSeparators #origin:corner: #activeProcess #bindWith: #beConsistent #at:type: #skip: #days #tclEval:with: #fromSeconds: #& #upToEnd #variable #become: #with:do: #findIndexOrNil: #asSeconds #copyWith: #background #status #selectors:receiver:argument: #create: #coerce: #bytecodeAt:) ] CompiledCode class >> specialSelectorsNumArgs [ "Answer a harmoniously-indexed array of arities for the messages answered by #specialSelectors." ^#[1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 1 2 0 0 0 0 0 1 1 0 0 255 255 255 255 255 1 0 1 0 1 0 1 1 0 1 0 0 0 0 0 0 0 1 0 1 1 0 0 0 0 0 0 0 0 1 2 0 1 0 2 1 0 0 3 1 0 1 0 0 1 0 0 0 0 4 0 0 0 0 1 0 2 0 0 0 0 0 0 2 1 1 0 0 2 1 0 1 1 1 1 1 1 0 1 0 0 0 1 0 0 2 1 0 1 1 0 0 2 0 2 2 0 0 0 0 1 0 1 1 0 0 0 0 0 1 0 0 0 2 1 1 0 0 0 1 1 0 1 0 0 0 0 1 0 0 2 4 0 2 2 0 2 0 2 1 0 0 0 0 2 0 0 2 0 1 0 0 0 0 2 1 1 1 2 4 1 1 1 0 0 0 0 0 0 0 0 0 0 0 0 0 1 1 0 1 0 2 0 1 1 0 1 0 1 1 1 0 0 0 0 0 1 0 1 0 0 2 0 1 0 2 1 0 2 1 1 0 0 1 2 1 0 1 0 0 3 1 1 1] ] CompiledCode class >> bytecodeInfoTable [ "Return a ByteArray which defines some properties of the bytecodes. For each bytecode, 4 bytes are reserved. The fourth byte is a flag byte: bit 7 means that the argument is a line number to be used in creating the bytecode->line number map. The first three have a meaning only for those bytecodes that represent a combination of operations: the combination can be BC1 ARG BC2 OPERAND if the fourth byte's bit 0 = 0 or BC1 OPERAND BC2 ARG if the fourth byte's bit 0 = 1 where BC1 is the first byte, BC2 is the second, ARG is the third and OPERAND is the bytecode argument as it appears in the bytecode stream." "Automatically generated by superops. Do not modify this definition!" ^#[0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 128 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 55 28 1 1 55 28 0 1 56 51 0 0 54 56 0 129 54 48 0 129 54 32 0 129 46 49 0 1 55 28 2 1 48 52 0 0 32 30 0 0 56 65 0 0 45 51 0 1 56 30 0 0 55 33 1 1 36 48 0 1 56 32 0 0 39 66 0 1 44 0 0 1 54 34 0 129 32 32 0 0 32 28 0 0 54 32 1 129 20 43 0 0 44 6 0 1 55 28 3 1 32 64 0 0 67 28 0 129 32 51 0 1 46 30 36 1 24 43 0 0 46 64 1 1 68 56 0 129 72 54 0 128 32 65 0 0 32 30 1 0 46 6 0 1 44 1 0 1 52 43 0 0 48 54 0 128 44 30 32 1 32 18 0 1 56 28 0 0 54 32 2 129 48 30 0 0 32 81 1 1 54 35 0 129 46 30 38 1 44 16 0 1 54 35 1 129 32 46 0 0 52 42 0 0 32 16 0 1 32 30 2 0 46 30 49 1 36 68 1 128 32 64 1 0 39 48 0 1 55 37 1 1 44 30 96 1 48 32 0 0 35 51 0 1 68 32 1 129 68 32 0 129 67 46 0 129 46 51 0 1 56 18 0 0 20 42 0 0 32 17 0 1 54 34 1 129 32 0 0 1 48 40 0 0 48 34 0 0 44 36 1 0 46 64 2 1 54 32 3 129 54 33 1 129 35 28 0 1 44 3 0 1 32 22 0 1 32 1 0 1 46 64 3 1 45 93 0 0 36 68 2 128 24 42 0 0 44 8 0 1 54 35 2 129 44 2 0 1 46 17 0 1 55 33 2 1 67 84 1 129 79 64 0 0 67 30 40 129 32 32 3 1 36 54 1 128 69 28 0 129 44 14 0 1 32 65 2 0 83 28 1 0 67 32 0 129 54 35 3 129 32 64 2 0 21 43 0 0 36 54 2 128 36 68 3 128 46 30 1 0 32 6 0 1 72 108 0 0 56 64 0 0 36 68 0 128 52 54 0 128 56 117 0 0 48 35 0 0 67 30 84 129 54 34 2 129 70 64 3 1 54 46 0 129 52 92 0 0 54 77 1 129 44 13 0 1 70 30 1 0 32 30 3 0 54 75 0 129 54 35 5 129 70 64 2 1 32 23 0 1 44 51 0 1 32 71 0 0 32 100 1 1 56 46 0 0 54 35 4 129 33 30 1 0 67 65 1 129 33 64 1 0 32 30 4 0 44 30 41 1 55 28 4 1 32 32 2 1 56 19 0 0 32 28 1 0 79 64 1 0 46 64 4 1 44 28 1 1 35 18 0 1 32 71 1 0 83 71 1 0 32 47 0 1 70 64 5 1 55 29 1 1 70 64 4 1 35 30 1 0 121 51 0 1 102 30 37 129 67 19 0 129 32 65 1 0 67 30 130 129 35 30 0 0 32 34 0 0 36 54 0 128 35 30 2 0 67 65 2 129 68 32 2 129 70 64 6 1 45 50 0 1 44 5 0 1 68 35 1 129 54 34 3 129 46 30 2 0 55 29 0 1 45 39 0 0 79 28 1 1 68 91 0 129 46 24 0 1 70 64 1 1 68 32 3 129 72 30 0 0 46 131 0 1 52 108 0 0 54 32 4 129 102 34 1 129 52 94 0 0 47 64 1 0 68 91 1 129 36 54 3 128 52 65 0 0 39 51 0 1 67 65 3 129 21 101 0 0 52 46 0 0 69 51 0 129 44 17 0 1 32 19 0 1 54 77 2 129] ] CompiledCode class >> new: numBytecodes header: anInteger numLiterals: numLiterals [ "Answer a new instance of the receiver with room for the given number of bytecodes and the given header" ^self new: numBytecodes header: anInteger literals: (Array new: numLiterals) ] CompiledCode class >> new: numBytecodes header: anInteger literals: literals [ "Answer a new instance of the receiver with room for the given number of bytecodes and the given header" anInteger isInteger ifFalse: [SystemExceptions.WrongClass signalOn: anInteger mustBe: Integer]. ^(self new: numBytecodes) initialize; header: anInteger literals: literals ] CompiledCode class >> flushTranslatorCache [ "Answer any kind of cache mantained by a just-in-time code translator in the virtual machine (if any). Do nothing for now." ] methodCategory [ "Answer the method category" self subclassResponsibility ] methodCategory: aCategory [ "Set the method category to the given string" self subclassResponsibility ] methodSourceCode [ "Answer the method source code (a FileSegment or String or nil)" self subclassResponsibility ] methodSourceString [ "Answer the method source code as a string" self subclassResponsibility ] methodSourceFile [ "Answer the file where the method source code is stored" self subclassResponsibility ] methodSourcePos [ "Answer the location where the method source code is stored in the methodSourceFile" self subclassResponsibility ] = aMethod [ "Answer whether the receiver is the same object as arg. Testing for equality could break the browser, since it's possible to put arbitrary objects via ##(...), so this is safer." ] hash [ "Answer an hash value for the receiver" | hashValue | hashValue := header hash bitAnd: 536870911 + (literals size hash bitAnd: 536870911). 1 to: self basicSize do: [:i | hashValue := ((hashValue bitShift: 1) bitAnd: 536870911) + (self basicAt: i)]. ^hashValue ] allLiteralSymbolsDo: aBlock [ "As with #allLiteralsDo:, but only call aBlock with found Symbols." literals isNil ifTrue: [^self]. self traverseLiteral: literals with: [:each | each isSymbol ifTrue: [aBlock value: each]] ] allLiteralsDo: aBlock [ "Walk my literals, descending into Arrays and Messages, invoking aBlock with each touched object." literals isNil ifTrue: [^self]. self traverseLiteral: literals with: aBlock ] traverseLiteral: anArray with: aBlock [ anArray do: [:each | aBlock value: each. each class == Array ifTrue: [self traverseLiteral: each with: aBlock]. each class == Message ifTrue: [aBlock value: each selector. self traverseLiteral: each arguments with: aBlock]] ] literalsDo: aBlock [ "Invoke aBlock with each object immediately in my list of literals." literals isNil ifTrue: [^self]. literals do: aBlock ] at: anIndex put: aBytecode [ "Store aBytecode as the anIndex-th bytecode" self basicAt: anIndex put: aBytecode. CompiledMethod flushTranslatorCache. ^aBytecode ] blockAt: anIndex [ "Answer the CompiledBlock attached to the anIndex-th literal, assuming that the literal is a CompiledBlock or a BlockClosure." | lit | lit := literals at: anIndex. lit class == BlockClosure ifTrue: [lit := lit block]. ^lit ] methodClass [ "Answer the class in which the receiver is installed." self subclassResponsibility ] methodClass: methodClass [ "Set the receiver's class instance variable" self subclassResponsibility ] selector: aSymbol [ "Set the selector through which the method is called" self subclassResponsibility ] selector [ "Answer the selector through which the method is called" self subclassResponsibility ] isAnnotated [ ^false ] literals [ "Answer the literals referenced by my code or any CompiledCode instances I own." ^literals isNil ifTrue: [#()] ifFalse: [literals] ] literalAt: anIndex [ "Answer the anIndex-th literal" ^literals at: anIndex ] literalAt: anInteger put: aValue [ "Store aValue as the anIndex-th literal" ^literals at: anInteger put: aValue ] bytecodeAt: anIndex [ "Answer the anIndex-th bytecode" ^self basicAt: anIndex + self bytecodeStart ] bytecodeAt: anIndex put: aBytecode [ "Store aBytecode as the anIndex-th bytecode" self basicAt: anIndex + self bytecodeStart put: aBytecode. CompiledMethod flushTranslatorCache. ^aBytecode ] flags [ "Private - Answer the optimization flags for the receiver" ^0 ] primitive [ "Answer the primitive called by the receiver" ^0 ] numArgs [ "Answer the number of arguments for the receiver" self subclassResponsibility ] numTemps [ "Answer the number of temporaries for the receiver" self subclassResponsibility ] stackDepth [ "Answer the number of stack slots needed for the receiver" self subclassResponsibility ] method [ "Answer the parent method for the receiver, or self if it is a method." ^self ] numLiterals [ "Answer the number of literals for the receiver" ^literals size ] deepCopy [ "Answer a deep copy of the receiver" ^self shallowCopy postCopy ] examineOn: aStream [ "Print the contents of the receiver in a verbose way." | instVars lit object output | instVars := self class allInstVarNames. aStream nextPutAll: 'An instance of '; print: self class; nl. 2 to: instVars size do: [:i | object := self instVarAt: i. output := [object printString] on: Error do: [:ex | ex return: '%1 %2' % {object class article. object class name asString}]. aStream nextPutAll: ' '; nextPutAll: (instVars at: i); nextPutAll: ': '; nextPutAll: output; nl. i = 2 ifTrue: [self printHeaderOn: aStream]]. self numLiterals > 0 ifTrue: [aStream nextPutAll: ' literals: ['; nl. 1 to: self numLiterals do: [:i | self bytecodeIndex: i with: aStream. aStream tab. lit := self literalAt: i. aStream print: lit; nl]. aStream nextPutAll: ' ]'; nl]. self numBytecodes > 0 ifTrue: [aStream nextPutAll: ' byte codes: ['; nl. self printByteCodesOn: aStream. aStream nextPutAll: ' ]'; nl] ] containsLiteral: anObject [ "Answer if the receiver contains a literal which is equal to anObject." self allLiteralsDo: [:lit | lit = anObject ifTrue: [^true]]. ^false ] refersTo: anObject [ "Answer whether the receiver refers to the given object" | byte | (self containsLiteral: anObject) ifTrue: [^true]. anObject isSymbol ifFalse: [^false]. "Look for symbols referenced to by special message sends" byte := self class specialSelectors indexOf: anObject. byte = 0 ifTrue: [^false]. byte := byte - 1. self allByteCodeIndicesDo: [:i :bytecode :operand | (byte <= 26 and: [byte = bytecode]) ifTrue: [^true]. ((byte bitAnd: 254) = 30 and: [byte = operand]) ifTrue: [^true]]. ^false ] hasBytecode: byte between: firstIndex and: lastIndex [ "Answer whether the receiver includes the `byte' bytecode in any of the indices between firstIndex and lastIndex." self allByteCodeIndicesDo: [:i :bytecode :operand | i > lastIndex ifTrue: [^false]. (i >= firstIndex and: [byte = bytecode]) ifTrue: [^true]]. ^false ] sourceCodeLinesDelta [ "Answer the delta from the numbers in LINE_NUMBER bytecodes to source code line numbers." self subclassResponsibility ] sourceCodeMap [ "Answer an array which maps bytecode indices to source code line numbers. 0 values represent invalid instruction pointer indices." | map line first | map := ByteArray new: self size. line := 1. first := true. self allByteCodeIndicesDo: [:each :byte :operand | (self class bytecodeInfoTable at: byte * 4 + 4) >= 128 ifTrue: [first ifFalse: [line := operand]. first := false. operand > 255 ifTrue: [map := map asArray]]. map at: each put: line]. ^map ] jumpDestinationAt: anIndex forward: aBoolean [ "Answer where the jump at bytecode index `anIndex' lands" | result ofs byte | ofs := anIndex. [anIndex > 2 and: [(self bytecodeAt: ofs - 2) = 55]] whileTrue: [ofs := ofs - 2]. result := 0. [result := result * 256 + (self bytecodeAt: ofs + 1). byte := self bytecodeAt: ofs. ofs := ofs + 2. byte = 55] whileTrue. ^aBoolean ifFalse: [ofs - result] ifTrue: [ofs + result] ] sendsToSuper [ "Answer whether the receiver includes a send to super." self allByteCodeIndicesDo: [:i :byte :operand | (byte = 29 or: [ byte = 31 ]) ifTrue: [^true]]. ^false ] reads: instVarIndex [ "Answer whether the receiver reads the instance variable with the given index" self flags = 2 ifTrue: [^((header bitShift: -6) bitAnd: 31) = instVarIndex]. self allByteCodeIndicesDo: [:i :byte :operand | (byte = 35 and: [operand = instVarIndex]) ifTrue: [^true]]. ^false ] assigns: instVarIndex [ "Answer whether the receiver writes to the instance variable with the given index" self allByteCodeIndicesDo: [:i :byte :operand | (byte = 39 and: [operand = instVarIndex]) ifTrue: [^true]]. ^false ] accesses: instVarIndex [ "Answer whether the receiver accesses the instance variable with the given index" | byte nextByte | self flags = 2 ifTrue: [^((header bitShift: -6) bitAnd: 31) = instVarIndex]. self allByteCodeIndicesDo: [:i :byte :operand | ((byte = 35 or: [byte = 39]) and: [operand = instVarIndex]) ifTrue: [^true]]. ^false ] dispatchTo: anObject with: param [ "Disassemble the bytecodes and tell anObject about them in the form of message sends. param is given as an argument to every message send." | lastOfs | self allByteCodeIndicesDo: [:i :byte :arg | lastOfs = i ifFalse: [anObject bytecodeIndex: i with: param. lastOfs := i]. self dispatchByte: byte with: arg at: i to: anObject with: param] ] dispatchByte: byte with: operand at: anIndex to: anObject with: param [ "Private - Print the byte bytecode (starting at anIndex) on param" byte <= 26 ifTrue: [^self dispatchSend: 30 with: byte to: anObject with: param]. byte < 32 ifTrue: [^self dispatchSend: byte with: operand to: anObject with: param]. byte < 40 ifTrue: [^self dispatchVariableOp: byte with: operand to: anObject with: param]. byte < 44 ifTrue: [^self dispatchJump: byte at: anIndex to: anObject with: param]. byte < 48 ifTrue: [^self dispatchOtherStack: byte with: operand to: anObject with: param]. byte < 54 ifTrue: [^self dispatchOneByte: byte to: anObject with: param]. byte = 54 ifTrue: [^anObject lineNo: operand with: param]. byte = 56 ifTrue: [^anObject pushSelf: param]. ^anObject invalidOpcode: param ] dispatchSuperoperator: byte with: operand at: ofs to: aBlock [ "Private - Split the superoperator and call back to aBlock for the two components (recursive calls are possible to several levels)." | index bc1 bc2 arg1 arg2 arg kind | index := byte * 4. bc1 := self class bytecodeInfoTable at: index + 1. bc2 := self class bytecodeInfoTable at: index + 2. arg := self class bytecodeInfoTable at: index + 3. kind := self class bytecodeInfoTable at: index + 4. kind \\ 2 = 0 ifTrue: [arg1 := arg. arg2 := operand] ifFalse: [arg1 := operand. arg2 := arg]. bc1 = 55 ifTrue: [arg2 := arg1 * 256 + arg2] ifFalse: [bc1 < 64 ifTrue: [aBlock value: ofs value: bc1 value: arg1] ifFalse: [self dispatchSuperoperator: bc1 with: arg1 at: ofs to: aBlock]]. bc2 < 64 ifTrue: [aBlock value: ofs value: bc2 value: arg2] ifFalse: [self dispatchSuperoperator: bc2 with: arg2 at: ofs to: aBlock] ] dispatchSend: byte with: operand to: anObject with: param [ byte = 28 ifTrue: [^anObject send: (self literalAt: operand // 256 + 1) numArgs: operand \\ 256 with: param]. byte = 29 ifTrue: [^anObject superSend: (self literalAt: operand // 256 + 1) numArgs: operand \\ 256 with: param]. byte = 30 ifTrue: [^anObject send: (self class specialSelectors at: operand + 1) numArgs: (self class specialSelectorsNumArgs at: operand + 1) with: param]. byte = 31 ifTrue: [^anObject superSend: (self class specialSelectors at: operand + 1) numArgs: (self class specialSelectorsNumArgs at: operand + 1) with: param]. ^anObject invalidOpcode: param ] dispatchVariableOp: byte with: operand to: anObject with: param [ byte = 32 ifTrue: [^anObject pushTemporary: operand with: param]. byte = 33 ifTrue: [^anObject pushTemporary: operand // 256 outer: operand \\ 256 with: param]. byte = 34 ifTrue: [^anObject pushGlobal: (self literalAt: operand + 1) with: param]. byte = 35 ifTrue: [^anObject pushInstVar: operand with: param]. byte = 36 ifTrue: [^anObject storeTemporary: operand with: param]. byte = 37 ifTrue: [^anObject storeTemporary: operand // 256 outer: operand \\ 256 with: param]. byte = 38 ifTrue: [^anObject storeGlobal: (self literalAt: operand + 1) with: param]. byte = 39 ifTrue: [^anObject storeInstVar: operand with: param] ] dispatchOneByte: byte to: anObject with: param [ byte == 48 ifTrue: [^anObject popStackTop: param]. byte == 49 ifTrue: [^anObject makeDirtyBlock: param]. byte == 50 ifTrue: [^anObject returnFromMethod: param]. byte == 51 ifTrue: [^anObject returnFromContext: param]. byte == 52 ifTrue: [^anObject dupStackTop: param]. byte == 53 ifTrue: [^anObject exitInterpreter: param] ] dispatchOtherStack: byte with: operand to: anObject with: param [ byte = 44 ifTrue: [^anObject pushLiteral: operand with: param]. byte = 46 ifTrue: [^anObject pushLiteral: (self literalAt: operand + 1) with: param]. byte = 47 ifTrue: [^anObject popIntoArray: operand with: param]. operand = 0 ifTrue: [^anObject pushLiteral: nil with: param]. operand = 1 ifTrue: [^anObject pushLiteral: true with: param]. operand = 2 ifTrue: [^anObject pushLiteral: false with: param]. ^anObject invalidOpcode: param ] dispatchJump: byte at: anIndex to: anObject with: param [ | destination | destination := self jumpDestinationAt: anIndex forward: byte > 40. byte < 42 ifTrue: [^anObject jumpTo: destination with: param]. byte = 42 ifTrue: [^anObject popJumpIfTrueTo: destination with: param]. byte = 43 ifTrue: [^anObject popJumpIfFalseTo: destination with: param] ] printHeaderOn: aStream [ "Private - Disassemble the method header to aStream" self subclassResponsibility ] printByteCodesOn: aStream [ "Private - Disassemble the bytecode instructions to aStream" self dispatchTo: self with: aStream ] invalidOpcode: aStream [ aStream tab; nextPutAll: 'invalid opcode'; nl ] pushInstVar: anIndex with: aStream [ aStream tab; nextPutAll: 'push Instance Variable[%1]' % {anIndex}; nl ] storeInstVar: anIndex with: aStream [ aStream tab; nextPutAll: 'store into Instance Variable[%1]' % {anIndex}; nl ] popIntoArray: anIndex with: aStream [ aStream tab; nextPutAll: 'pop and store into array element[%1]' % {anIndex}; nl ] pushTemporary: anIndex outer: scopes with: aStream [ aStream tab; nextPutAll: 'push Temporary[%1] from outer context #%2' % {anIndex. scopes}; nl ] storeTemporary: anIndex outer: scopes with: aStream [ aStream tab; nextPutAll: 'store into Temporary[%1] from outer context #%2' % {anIndex. scopes}; nl ] pushTemporary: anIndex with: aStream [ aStream tab; nextPutAll: 'push Temporary[%1]' % {anIndex}; nl ] storeTemporary: anIndex with: aStream [ aStream tab; nextPutAll: 'store into Temporary[%1]' % {anIndex}; nl ] pushLiteral: anObject with: aStream [ | printString | printString := anObject printString. (anObject isClass not and: [printString size > 30]) ifTrue: [printString := '%1 %2' % {anObject class article. anObject class name asString}]. aStream tab; nextPutAll: 'push '; nextPutAll: printString; nl ] pushGlobal: anObject with: aStream [ aStream tab; nextPutAll: 'push Global Variable '; print: anObject; nl ] storeGlobal: anObject with: aStream [ aStream tab; nextPutAll: 'store into Global Variable '; print: anObject; nl ] pushSelf: aStream [ aStream tab; nextPutAll: 'push self'; nl ] popStackTop: aStream [ aStream tab; nextPutAll: 'pop stack top'; nl ] makeDirtyBlock: aStream [ aStream tab; nextPutAll: 'make dirty block'; nl ] lineNo: n with: aStream [ aStream tab; nextPutAll: 'source code line number '; print: n; nl ] dupStackTop: aStream [ aStream tab; nextPutAll: 'dup stack top'; nl ] exitInterpreter: aStream [ aStream tab; nextPutAll: 'exit interpreter'; nl ] returnFromContext: aStream [ aStream tab; nextPutAll: 'return stack top'; nl ] returnFromMethod: aStream [ aStream tab; nextPutAll: 'return from method'; nl ] popJumpIfFalseTo: destination with: aStream [ aStream tab; nextPutAll: 'pop and if false jump to '; print: destination; nl ] popJumpIfTrueTo: destination with: aStream [ aStream tab; nextPutAll: 'pop and if true jump to '; print: destination; nl ] jumpTo: destination with: aStream [ aStream tab; nextPutAll: 'jump to '; print: destination; nl ] superSend: aSymbol numArgs: anInteger with: aStream [ aStream tab; nextPutAll: 'send %2 args message %1 to super' % {aSymbol. anInteger}; nl ] send: aSymbol numArgs: anInteger with: aStream [ aStream tab; nextPutAll: 'send %2 args message %1' % {aSymbol. anInteger}; nl ] bytecodeIndex: byte with: aStream [ "Private - Print the bytecode index for byte" | s | s := byte printString. aStream space: 5 - s size; nextPut: $[; nextPutAll: s; nextPut: $] ] nextBytecodeIndex: anIndex [ "Private - Answer the index of the bytecode after the one at index `anIndex'" | byte ofs | ofs := anIndex. [byte := self bytecodeAt: ofs. ofs := ofs + 2. byte = 55] whileTrue. ^ofs ] allByteCodeIndicesDo: aBlock [ "Private - Evaluate aBlock passing each of the index where a new bytecode instruction starts" | numBytes i byte operand ofs | i := 1. numBytes := self numBytecodes. [i <= numBytes] whileTrue: [ofs := i. operand := 0. [byte := self bytecodeAt: i. operand := operand * 256 + (self bytecodeAt: i + 1). i := i + 2. byte = 55] whileTrue. byte >= 64 ifTrue: [self dispatchSuperoperator: byte with: operand at: ofs to: aBlock] ifFalse: [aBlock value: ofs value: byte value: operand]] ] bytecodeSizeAt: anIndex [ "Private - Answer the size of the bytecode instruction starting at anIndex" ^(self nextBytecodeIndex: anIndex) - anIndex ] header: hdr literals: lits [ | oldHeader | oldHeader := header. header := hdr. literals := lits. oldHeader isNil ifFalse: [Behavior flushCache] ] initialize [ "Do nothing" ] getHeader [ ^header ] numBytecodes [ "Answer the number of bytecodes in the receiver" ^self basicSize - self bytecodeStart ] bytecodeStart [ "Answer the index where the bytecodes start - 1" ^0 ] discardTranslation [ "Flush the just-in-time translated code for the receiver (if any)." ] verificationResult [ "Answer the result of verifying the bytecodes for the receiver." ] verify [ "Verify the bytecodes for the receiver, and raise an exception if the verification process failed." | result | result := self verificationResult. result isNil ifFalse: [SystemExceptions.VerificationError signal: result] ] ] smalltalk-3.2.5/kernel/Builtins.st0000644000175000017500000001646112130343734014057 00000000000000"===================================================================== | | Smalltalk built in methods. These are read in by the system | initially, to prepare the execution environment. | | ======================================================================" "====================================================================== | | Copyright 1988,89,90,91,92,94,95,99,2000,2001,2002,2006,2007 | Free Software Foundation, Inc. | Written by Steve Byrne. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" Object extend [ class [ "Answer the class to which the receiver belongs" self primitiveFailed ] ] Behavior extend [ new [ "Create a new instance of a class with no indexed instance variables" self isFixed ifFalse: [ ^self new: 0 ]. ^self primitiveFailed ] basicNew [ "Create a new instance of a class with no indexed instance variables; this method must not be overridden." self isFixed ifFalse: [ ^self basicNew: 0 ]. ^self primitiveFailed ] new: numInstanceVariables [ "Create a new instance of a class with indexed instance variables. The instance has numInstanceVariables indexed instance variables." self isFixed ifTrue: [ SystemExceptions.WrongMessageSent signalOn: #new: useInstead: #new ]. numInstanceVariables isSmallInteger ifTrue: [ ^self primitiveFailed ]. ^SystemExceptions.WrongClass signalOn: numInstanceVariables mustBe: SmallInteger ] basicNew: numInstanceVariables [ "Create a new instance of a class with indexed instance variables. The instance has numInstanceVariables indexed instance variables; this method must not be overridden." self isFixed ifTrue: [ SystemExceptions.WrongMessageSent signalOn: #basicNew: useInstead: #basicNew ]. numInstanceVariables isSmallInteger ifTrue: [ ^self primitiveFailed ]. ^SystemExceptions.WrongClass signalOn: numInstanceVariables mustBe: SmallInteger ] ] Dictionary extend [ Dictionary class >> new [ "Answer a new Dictionary. This method, actually, won't last long - until LookupTbl.st is loaded" ^self primitiveFailed ] at: key [ "Answer the value associated with the given key in the receiver. This method, actually, won't last long - until LookupTbl.st is loaded" ^self primitiveFailed ] ] Class extend [ subclass: classNameString [ ^(Smalltalk at: classNameString) ] subclass: classNameString instanceVariableNames: stringInstVarNames classVariableNames: stringOfClassVarNames poolDictionaries: stringOfPoolNames category: categoryNameString [ ^(Smalltalk at: classNameString) category: categoryNameString ] variable: shape subclass: classNameString instanceVariableNames: stringInstVarNames classVariableNames: stringOfClassVarNames poolDictionaries: stringOfPoolNames category: categoryNameString [ ^(Smalltalk at: classNameString) category: categoryNameString ] variableSubclass: classNameString instanceVariableNames: stringInstVarNames classVariableNames: stringOfClassVarNames poolDictionaries: stringOfPoolNames category: categoryNameString [ ^(Smalltalk at: classNameString) category: categoryNameString ] variableWordSubclass: classNameString instanceVariableNames: stringInstVarNames classVariableNames: stringOfClassVarNames poolDictionaries: stringOfPoolNames category: categoryNameString [ ^(Smalltalk at: classNameString) category: categoryNameString ] variableByteSubclass: classNameString instanceVariableNames: stringInstVarNames classVariableNames: stringOfClassVarNames poolDictionaries: stringOfPoolNames category: categoryNameString [ ^(Smalltalk at: classNameString) category: categoryNameString ] category: aString [ "Define a category for the receiver" category := aString ] comment: aString [ "Define a comment for the receiver" comment := aString ] ] ClassDescription extend [ import: aString [ ] ] Behavior extend [ instanceVariableNames: ivn [ ] shape: aSymbol [ ] ] UndefinedObject extend [ subclass: classNameString [ ^(Smalltalk at: classNameString) ] subclass: classNameString instanceVariableNames: stringInstVarNames classVariableNames: stringOfClassVarNames poolDictionaries: stringOfPoolNames category: categoryNameString [ ^(Smalltalk at: classNameString) category: categoryNameString ] variable: shape subclass: classNameString instanceVariableNames: stringInstVarNames classVariableNames: stringOfClassVarNames poolDictionaries: stringOfPoolNames category: categoryNameString [ ^(Smalltalk at: classNameString) category: categoryNameString ] variableSubclass: classNameString instanceVariableNames: stringInstVarNames classVariableNames: stringOfClassVarNames poolDictionaries: stringOfPoolNames category: categoryNameString [ ^(Smalltalk at: classNameString) category: categoryNameString ] variableWordSubclass: classNameString instanceVariableNames: stringInstVarNames classVariableNames: stringOfClassVarNames poolDictionaries: stringOfPoolNames category: categoryNameString [ ^(Smalltalk at: classNameString) category: categoryNameString ] variableByteSubclass: classNameString instanceVariableNames: stringInstVarNames classVariableNames: stringOfClassVarNames poolDictionaries: stringOfPoolNames category: categoryNameString [ ^(Smalltalk at: classNameString) category: categoryNameString ] ] smalltalk-3.2.5/kernel/ClassDesc.st0000644000175000017500000002624012123404352014122 00000000000000"====================================================================== | | ClassDescription Method Definitions | | ======================================================================" "====================================================================== | | Copyright 1988,92,94,95,99,2000,2001,2002,2003,2005,2008 | Free Software Foundation, Inc. | Written by Steve Byrne. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" Behavior subclass: ClassDescription [ createGetMethod: what default: value [ "Create a method accessing the variable `what', with a default value of `value', using lazy initialization" ^(super createGetMethod: what default: value) methodCategory: 'accessing' ] createGetMethod: what [ "Create a method accessing the variable `what'." ^(super createGetMethod: what) methodCategory: 'accessing' ] createSetMethod: what [ "Create a method which sets the variable `what'." ^(super createSetMethod: what) methodCategory: 'accessing' ] defineAsyncCFunc: cFuncNameString withSelectorArgs: selectorAndArgs args: argsArray [ "See documentation. This function is deprecated, you should use the special syntax instead." ^(super defineAsyncCFunc: cFuncNameString withSelectorArgs: selectorAndArgs args: argsArray) methodCategory: 'C call-outs' ] defineCFunc: cFuncNameString withSelectorArgs: selectorAndArgs returning: returnTypeSymbol args: argsArray [ "See documentation. This function is deprecated, you should use the special syntax instead." ^(super defineCFunc: cFuncNameString withSelectorArgs: selectorAndArgs returning: returnTypeSymbol args: argsArray) methodCategory: 'C call-outs' ] classify: aSelector under: aString [ "Put the method identified by the selector aSelector under the category given by aString." ^self >> aSelector methodCategory: aString ] removeCategory: aString [ "Remove from the receiver every method belonging to the given category" | selector method category | methodDictionary isNil ifTrue: [^self]. methodDictionary copy associationsDo: [:assoc | method := assoc value. method methodCategory = category ifTrue: [methodDictionary remove: assoc]] ] whichCategoryIncludesSelector: selector [ "Answer the category for the given selector, or nil if the selector is not found" | method | methodDictionary isNil ifTrue: [^nil]. method := methodDictionary at: selector ifAbsent: [^nil]. ^method methodCategory ] copy: selector from: aClass [ "Copy the given selector from aClass, assigning it the same category" | method | method := aClass compiledMethodAt: selector. self addSelector: selector withMethod: (method withNewMethodClass: self) ] copy: selector from: aClass classified: categoryName [ "Copy the given selector from aClass, assigning it the given category" | method | method := (aClass compiledMethodAt: selector) withNewMethodClass: self. method methodCategory: categoryName. self addSelector: selector withMethod: method ] copyAll: arrayOfSelectors from: class [ "Copy all the selectors in arrayOfSelectors from class, assigning them the same category they have in class" arrayOfSelectors do: [:selector | self copy: selector from: class] ] copyAll: arrayOfSelectors from: class classified: categoryName [ "Copy all the selectors in arrayOfSelectors from aClass, assigning them the given category" arrayOfSelectors do: [:selector | self copy: selector from: class classified: categoryName] ] copyAllCategoriesFrom: aClass [ "Copy all the selectors in aClass, assigning them the original category" | method | aClass selectors do: [:selector | self copy: selector from: aClass] ] copyCategory: categoryName from: aClass [ "Copy all the selectors in from aClass that belong to the given category" | method | aClass selectors do: [:selector | method := aClass compiledMethodAt: selector. method methodCategory = categoryName ifTrue: [self copy: selector from: aClass]] ] copyCategory: categoryName from: aClass classified: newCategoryName [ "Copy all the selectors in from aClass that belong to the given category, reclassifying them as belonging to the given category" | method | aClass selectors do: [:selector | method := aClass compiledMethodAt: selector. method methodCategory = categoryName ifTrue: [self copy: selector from: aClass classified: newCategoryName]] ] compile: code classified: categoryName [ "Compile code in the receiver, assigning the method to the given category. Answer the newly created CompiledMethod, or nil if an error was found." | method | method := self compile: code. method notNil ifTrue: [method methodCategory: categoryName]. ^method ] compile: code classified: categoryName ifError: block [ "Compile method source and install in method category, categoryName. If there are parsing errors, invoke exception block, 'block' (see compile:ifError:). Return the method" | method | method := self compile: code ifError: [:f :l :e | ^block value: f value: l value: e]. method methodCategory: categoryName. ^method ] compile: code classified: categoryName notifying: requestor [ "Compile method source and install in method category, categoryName. If there are parsing errors, send an error message to requestor" | method | method := self compile: code notifying: requestor. method notNil ifTrue: [method methodCategory: categoryName]. ^method ] nameIn: aNamespace [ "Answer the class name when the class is referenced from aNamespace" ^self environment == aNamespace ifTrue: [self name asString] ifFalse: [(self environment nameIn: aNamespace) , '.' , self name] ] printOn: aStream in: aNamespace [ "Print on aStream the class name when the class is referenced from aNamespace" self environment == aNamespace ifFalse: [self environment printOn: aStream in: aNamespace. aStream nextPut: $.]. aStream nextPutAll: self name ] classVariableString [ self subclassResponsibility ] instanceVariableString [ "Answer a string containing the name of the receiver's instance variables." | stream | instanceVariables isNil ifTrue: [^'']. stream := WriteStream on: String new. instanceVariables do: [:instVarName | stream nextPutAll: instVarName; nextPut: $ ]. ^stream contents ] sharedVariableString [ self subclassResponsibility ] fileOutOn: aFileStream [ "File out complete class description: class definition, class and instance methods. Requires package Parser." self subclassResponsibility ] fileOut: fileName [ "Open the given file and to file out a complete class description to it. Requires package Parser." | aFileStream | aFileStream := FileStream open: fileName mode: FileStream write. Transcript nextPutAll: 'Filing out class to: '; nextPutAll: fileName. self fileOutOn: aFileStream. aFileStream close ] fileOutCategory: categoryName to: fileName [ "File out all the methods belonging to the method category, categoryName, to the fileName file. Requires package Parser." | aFileStream | aFileStream := FileStream open: fileName mode: FileStream write. Transcript nextPutAll: 'Filing out a category to: '; nextPutAll: fileName. self fileOutCategory: categoryName toStream: aFileStream. aFileStream close ] fileOutCategory: categoryName toStream: aFileStream [ "File out the given selector to a FileStream. Requires package Parser." self notYetImplemented ] fileOutSelector: selector to: fileName [ "File out the given selector to fileName. Requires package Parser." | aFileStream | aFileStream := FileStream open: fileName mode: FileStream write. Transcript nextPutAll: 'Filing out a selector to: '; nextPutAll: fileName. self fileOutSelector: selector toStream: aFileStream. aFileStream close ] fileOutSelector: selector toStream: aFileStream [ "File out the given selector to a FileStream. Requires package Parser." self notYetImplemented ] collectCategories [ "Answer all the method categories, sorted by name" | categories | methodDictionary isNil ifTrue: [^#()]. categories := Set new. methodDictionary do: [:method | categories add: method methodCategory]. ^categories asSortedCollection ] binding [ "Answer a VariableBinding object whose value is the receiver" ^self environment associationAt: self asClass name ] asClass [ self subclassResponsibility ] asMetaclass [ "Answer the metaclass associated to the receiver" ^self asClass class ] addSharedPool: aDictionary [ "Add the given shared pool to the list of the class' pool dictionaries" self subclassResponsibility ] import: aDictionary [ "Add the given shared pool to the list of the class' pool dictionaries" "If you promote this method, you must also promote the version in Builtins.st." self addSharedPool: aDictionary ] ] smalltalk-3.2.5/kernel/Interval.st0000644000175000017500000001666512123404352014054 00000000000000"====================================================================== | | Interval Method Definitions | | ======================================================================" "====================================================================== | | Copyright 1988,92,94,95,99,2000,2001,2002,2005,2008,2009 | Free Software Foundation, Inc. | Written by Steve Byrne. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" ArrayedCollection subclass: Interval [ | start stop step | Interval class >> from: startInteger to: stopInteger by: stepInteger [ "Answer an Interval going from startInteger to the stopInteger, with a step of stepInteger" ^self basicNew initializeFrom: startInteger to: stopInteger by: stepInteger ] Interval class >> from: startInteger to: stopInteger [ "Answer an Interval going from startInteger to the stopInteger, with a step of 1" ^self from: startInteger to: stopInteger by: 1 ] Interval class >> withAll: aCollection [ "Answer an Interval containing the same elements as aCollection. Fail if it is not possible to create one." | newInterval last delta | aCollection keysAndValuesDo: [:index :each | index > 2 ifTrue: [last - each = delta ifFalse: [SystemExceptions.InvalidArgument signalOn: aCollection reason: 'argument not an arithmetic progression']] ifFalse: [last isNil ifFalse: [delta := last - each]]. last := each]. ^self from: aCollection first to: aCollection last by: (aCollection last - aCollection first) // (aCollection size - 1) ] do: aBlock [ "Evaluate the receiver for each element in aBlock" | i | i := start. step > 0 ifTrue: [[i <= stop] whileTrue: [aBlock value: i. i := i + step]] ifFalse: [[i >= stop] whileTrue: [aBlock value: i. i := i + step]] ] collect: aBlock [ "Evaluate the receiver for each element in aBlock, collect in an array the result of the evaluations." | i result j | result := self copyEmpty: self size. i := 1. j := start. step > 0 ifTrue: [[j <= stop] whileTrue: [result at: i put: (aBlock value: j). j := j + step. i := i + 1]] ifFalse: [[j >= stop] whileTrue: [result at: i put: (aBlock value: j). j := j + step. i := i + 1]]. ^result ] isExact [ "Answer whether elements of the receiver are computed using exact arithmetic. This is true as long as the start and step value are exact (i.e. not floating-point)." ^start isExact and: [step isExact] ] isEmpty [ "Answer whether the receiver is empty." ^(step > 0) == (stop < start) ] size [ "Answer the number of elements in the receiver." step > 0 ifTrue: [stop >= start ifTrue: [^(stop - start) // step + 1] ifFalse: [^0]] ifFalse: [start >= stop ifTrue: [^(stop - start) // step + 1] ifFalse: [^0]] ] reverse [ "Answer a copy of the receiver with all of its items reversed" ^Interval from: (self at: self size) to: (self at: 1) by: step negated ] species [ ^Array ] at: index [ "Answer the index-th element of the receiver." (index >= 1 and: [index <= self size]) ifTrue: [^start + (step * (index - 1))] ifFalse: [SystemExceptions.IndexOutOfRange signalOn: self withIndex: index] ] at: index put: anObject [ self shouldNotImplement ] = anInterval [ "Answer whether anInterval is the same interval as the receiver" self class == anInterval class ifFalse: [^false]. self isEmpty ifTrue: [ ^anInterval isEmpty ]. anInterval isEmpty ifTrue: [ ^false ]. ^self first = anInterval first and: [self last = anInterval last and: [self increment = anInterval increment]] ] hash [ "Answer an hash value for the receiver" ^(start + stop + stop) * step bitAnd: 1073741823 ] copyFrom: startIndex to: stopIndex [ | last | stopIndex < startIndex ifTrue: [stopIndex = (startIndex - 1) ifTrue: [^Interval from: start to: start - step by: step]. ^SystemExceptions.ArgumentOutOfRange signalOn: stopIndex mustBeBetween: startIndex - 1 and: self size]. last := self at: stopIndex. self isExact ifFalse: [ last := last + (step / 2) ]. ^Interval from: (self at: startIndex) to: last by: step ] printOn: aStream [ "Print a representation for the receiver on aStream" | size | aStream nextPutAll: self class storeString; nextPut: $(. size := self size. size > 0 ifTrue: [aStream print: start]. size > 1 ifTrue: [aStream space; print: start + step]. size > 2 ifTrue: [(self at: 3) = stop ifFalse: [aStream nextPutAll: ' ...']. aStream space; print: stop]. aStream nextPut: $) ] first [ ^self isEmpty ifTrue: [SystemExceptions.IndexOutOfRange signalOn: self withIndex: 1] ifFalse: [start] ] last [ "Answer the last value." ^self isEmpty ifTrue: [SystemExceptions.IndexOutOfRange signalOn: self withIndex: 0] ifFalse: [stop - ((stop - start) \\ step)] ] increment [ ^step ] storeOn: aStream [ "Store Smalltalk code compiling to the receiver on aStream" aStream nextPut: $(. aStream nextPutAll: self class storeString. aStream nextPutAll: ' from: '. start storeOn: aStream. aStream nextPutAll: ' to: '. stop storeOn: aStream. aStream nextPutAll: ' by: '. step storeOn: aStream. aStream nextPut: $) ] copyEmpty [ "Answer an empty copy of the receiver, with the class answered by the collect: method." ^self species new: self size ] initializeFrom: startInteger to: stopInteger by: stepInteger [ start := startInteger. stop := stopInteger. step := stepInteger ] ] smalltalk-3.2.5/kernel/Security.st0000644000175000017500000001617412130343734014076 00000000000000"====================================================================== | | Security-related Class Definitions | | ======================================================================" "====================================================================== | | Copyright 2003 | Free Software Foundation, Inc. | Written by Paolo Bonzini. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" Object subclass: Permission [ | name actions target positive | Permission class >> name: aSymbol target: aTarget actions: actionsArray [ ^(self new) name: aSymbol; target: aTarget; actions: actionsArray; yourself ] Permission class >> name: aSymbol target: aTarget action: action [ ^self name: aSymbol target: aTarget actions: {action} ] Permission class >> allowing: aSymbol target: aTarget actions: actionsArray [ ^(self name: aSymbol target: aTarget actions: actionsArray) allow ] Permission class >> allowing: aSymbol target: aTarget action: action [ ^(self name: aSymbol target: aTarget actions: {action}) allow ] Permission class >> denying: aSymbol target: aTarget actions: actionsArray [ ^(self name: aSymbol target: aTarget actions: actionsArray) deny ] Permission class >> denying: aSymbol target: aTarget action: action [ ^(self name: aSymbol target: aTarget actions: {action}) deny ] Permission class >> granting: aSymbol target: aTarget actions: actionsArray [ ^(self name: aSymbol target: aTarget actions: actionsArray) allow ] Permission class >> granting: aSymbol target: aTarget action: action [ ^(self name: aSymbol target: aTarget actions: {action}) allow ] check: aPermission for: anObject [ ^(self implies: aPermission) ifTrue: [self isAllowing] ifFalse: [anObject isUntrusted not] ] implies: aPermission [ aPermission name = name ifFalse: [^false]. (self target notNil and: [aPermission target notNil]) ifTrue: [(self target isString and: [aPermission target isString]) ifTrue: [(self target match: aPermission target) ifFalse: [^false]] ifFalse: [self target == aPermission target ifFalse: [^false]]]. (self actions notNil and: [aPermission actions notNil]) ifTrue: [aPermission actions size = 1 ifTrue: [^self actions includes: (aPermission at: 1)]. ^aPermission actions allSatisfy: [:each | self actions includes: each]]. ^true ] action: anObject [ self actions: {anObject} ] actions [ ^actions ] actions: anObject [ actions isNil ifFalse: [self error: 'can set permission actions only once']. (actions allSatisfy: [:each | each isSymbol]) ifFalse: [self error: 'actions must be symbols']. actions := anObject copy asArray ] allow [ positive isNil ifFalse: [self error: 'can set allow/deny only once']. positive := true ] allowing [ | savePositive result | savePositive := positive. positive := true. result := self copy. positive := savePositive. ^result ] deny [ positive isNil ifFalse: [self error: 'can set allow/deny only once']. positive := false ] denying [ | savePositive result | savePositive := positive. positive := false. result := self copy. positive := savePositive. ^result ] isAllowing [ ^positive ] name [ ^name ] name: anObject [ name isNil ifFalse: [self error: 'can set permission name only once']. anObject isSymbol ifFalse: [self error: 'permission name must be a symbol']. name := anObject copy ] target [ ^target ] target: anObject [ target isNil ifFalse: [self error: 'can set permission target only once']. (target allSatisfy: [:each | each isSymbol]) ifFalse: [self error: 'target must be symbols']. target := anObject copy ] ] Object subclass: SecurityPolicy [ | dictionary owner | addPermission: aPermission [ owner isNil ifFalse: [thisContext securityCheckFor: #securityManagement target: owner]. dictionary isNil ifTrue: [dictionary := IdentityDictionary new]. (dictionary at: aPermission name ifAbsentPut: [OrderedCollection new]) add: aPermission allowing ] removePermission: aPermission [ owner isNil ifFalse: [thisContext securityCheckFor: #securityManagement target: owner]. dictionary isNil ifTrue: [dictionary := IdentityDictionary new]. (dictionary at: aPermission name ifAbsentPut: [OrderedCollection new]) add: aPermission denying ] withOwner: aClass [ ^(self copy) owner: aClass; yourself ] owner: aClass [ thisContext securityCheckFor: #securityManagement target: aClass. dictionary := dictionary deepCopy. owner := aClass. ^self ] check: aPermission [ ^(dictionary at: aPermission name ifAbsent: [#()]) inject: owner isUntrusted not into: [:old :perm | (perm implies: aPermission) ifTrue: [perm isAllowing] ifFalse: [old]] ] implies: aPermission [ ^(dictionary at: aPermission name ifAbsent: [#()]) inject: false into: [:old :perm | (perm implies: aPermission) ifTrue: [perm isAllowing] ifFalse: [old]] ] ] smalltalk-3.2.5/kernel/ExcHandling.st0000644000175000017500000003736612123404352014455 00000000000000"====================================================================== | | Core (instance-based) exception handling classes | | ======================================================================" "====================================================================== | | Copyright 1999, 2000, 2001, 2002, 2003, 2008, 2009 | Free Software Foundation, Inc. | Written by Paolo Bonzini. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" "Create these symbols. AnsiExcept.st will assign values to them; Also create some classes" Object subclass: ExceptionSet [ | collection | ExceptionSet class >> new [ "Private - Answer a new, empty ExceptionSet" ^self basicNew collection: Set new ] , aTrappableEvent [ "Answer an ExceptionSet containing all the exceptions in the receiver and all the exceptions in aTrappableEvent" ^(ExceptionSet new) add: self; add: aTrappableEvent; yourself ] allExceptionsDo: aBlock [ "Private - Evaluate aBlock for every exception in the receiver. Answer the receiver" collection do: aBlock ] goodness: exception [ "Answer how good the receiver is at handling the given exception. A negative value indicates that the receiver is not able to handle the exception." ^collection inject: -1 into: [:old :each | old max: (each goodness: exception)] ] handles: exception [ "Answer whether the receiver handles `exception'." ^collection anySatisfy: [:someItem | someItem handles: exception] ] add: aTrappableEvent [ "Private - Add aTrappableEvent to the receiver and answer aTrappableEvent" aTrappableEvent allExceptionsDo: [:exc | collection add: exc]. ^aTrappableEvent ] collection: aSet [ "Private - Set the collection of exception included in the receiver to aSet" collection := aSet. ^self ] ] Object subclass: Exception [ | creator tag messageText resumeBlock onDoBlock handlerBlock context isNested previousState | NoTag := nil. Exception class >> resetAllHandlers [ "Private, class - Reset the handlers for all the exceptions; that is, the next handlers used will be the first to be declared" thisContext scanBacktraceForAttribute: #exceptionHandlerSearch:reset: do: [:context :attr | (attr arguments at: 2) value: context] ] Exception class >> new [ "Create an instance of the receiver, which you will be able to signal later." | ctx creator | ctx := thisContext parentContext. [(creator := ctx receiver) == self] whileTrue: [ctx := ctx parentContext]. ^self basicNew initialize: creator ] Exception class >> signal [ "Create an instance of the receiver, give it default attributes, and signal it immediately." ^self new signal ] Exception class >> signal: messageText [ "Create an instance of the receiver, set its message text, and signal it immediately." ^(self new) messageText: messageText; signal ] Exception class >> , aTrappableEvent [ "Answer an ExceptionCollection containing all the exceptions in the receiver and all the exceptions in aTrappableEvent" ^(ExceptionSet new) add: self; add: aTrappableEvent; yourself ] Exception class >> allExceptionsDo: aBlock [ "Private - Pass ourselves to aBlock" aBlock value: self ] Exception class >> goodness: anExceptionClass [ "Answer how good the receiver is at handling the given exception. A negative value indicates that the receiver is not able to handle the exception." | depth found c target | depth := -100000. target := self. c := anExceptionClass. [c == target ifTrue: [ depth := 0 ]. c == Exception] whileFalse: [c := c superclass. depth := depth + 1]. "In general, the deeper is the exception, the more fine-grained the control is and the higher is the goodness (as long as the receiver can handle the exception)." ^depth ] Exception class >> handles: anException [ "Answer whether the receiver handles `anException'." | target | target := anException class asClass. self == target ifTrue: [^true]. ^target inheritsFrom: self ] = anObject [ "Answer whether the receiver is equal to anObject. This is true if either the receiver or its class are the same object as anObject." ^self == anObject ] initialize: anObject [ "Initialize the receiver's instance variables." creator := anObject. tag := self noTag. self messageText: self description ] description [ "Answer a textual description of the exception." ^'An exception has occurred' ] isResumable [ "Answer true. Exceptions are by default resumable." ^true ] defaultAction [ "Execute the default action that is attached to the receiver." self resignalAsUnhandled: self messageText ] signal [ "Raise the exceptional event represented by the receiver" self instantiateNextHandlerFrom: thisContext. ^self activateHandler: (onDoBlock isNil and: [ self isResumable ]) ] signal: messageText [ "Raise the exceptional event represented by the receiver, setting its message text to messageText." ^self messageText: messageText; signal ] creator [ ^creator ] basicMessageText [ "Answer an exception's message text. Do not override this method." ^messageText ] messageText [ "Answer an exception's message text." ^messageText ] messageText: aString [ "Set an exception's message text." messageText := aString ] tag [ "Answer an exception's tag value. If not specified, it is the same as the message text." ^tag == self noTag ifTrue: [self messageText] ifFalse: [tag] ] tag: anObject [ "Set an exception's tag value. If nil, the tag value will be the same as the message text." tag := anObject ] postCopy [ "Modify the receiver so that it does not refer to any instantiated exception handler." onDoBlock := nil. handlerBlock := nil. context := nil. isNested := nil. previousState := nil ] isNested [ "Answer whether the current exception handler is within the scope of another handler for the same exception." isNested isNil ifTrue: [isNested := false]. ^isNested ] instantiateNextHandlerFrom: aContext [ "Private - Fill the receiver with information on the next handler for it, possibly a handler for a parent or the default handler." aContext parentContext scanBacktraceForAttribute: #exceptionHandlerSearch:reset: do: [:context :attr | | status | status := (attr arguments at: 1) value: context value: self. status == #found ifTrue: [^self]]. self instantiateDefaultHandler. ] instantiateDefaultHandler [ "Private - Fill the receiver with information on its default handler." self onDoBlock: nil handlerBlock: [ :ex | ex defaultAction ] onDoContext: nil previousState: nil ] outer [ "Raise the exception that instantiated the receiver, passing the same parameters. If the receiver is resumable and the evaluated exception action resumes then the result returned from #outer will be the resumption value of the evaluated exception action. If the receiver is not resumable or if the exception action does not resume then this message will not return, and #outer will be equivalent to #pass." | signal | signal := self copy. signal isNested: true. signal instantiateNextHandlerFrom: self context. ^signal activateHandler: true ] pass [ "Yield control to the enclosing exception action for the receiver. Similar to #outer, but control does not return to the currently active exception handler." | signal | signal := self copy. signal isNested: true. signal instantiateNextHandlerFrom: self context. ^self return: (signal activateHandler: true) ] resignalAsUnhandled: message [ "This might start the debugger... Note that we use #basicPrint 'cause #printOn: might invoke an error." | exc | exc := SystemExceptions.UnhandledException new originalException: self; messageText: message; yourself. thisContext parentContext scanBacktraceFor: #(#resignalAsUnhandled:) do: [ :ctx | ^exc defaultAction ]. self resignalAs: exc ] resume [ "If the exception is resumable, resume the execution of the block that raised the exception; the method that was used to signal the exception will answer the receiver. Use this method IF AND ONLY IF you know who caused the exception and if it is possible to resume it in that particular case" self isResumable ifFalse: [self resignalAsUnhandled: 'Exception not resumable - #resume failed']. self resetHandler. resumeBlock value: self ] resume: anObject [ "If the exception is resumable, resume the execution of the block that raised the exception; the method that was used to signal the exception will answer anObject. Use this method IF AND ONLY IF you know who caused the exception and if it is possible to resume it in that particular case" self isResumable ifFalse: [self resignalAsUnhandled: 'Exception not resumable - #resume: failed']. self resetHandler. resumeBlock value: anObject ] resignalAs: replacementException [ "Reinstate all handlers and execute the handler for `replacementException'; control does not return to the currently active exception handler. The new Signal object that is created has the same contents as the receiver (this might or not be correct -- if it isn't you can use an idiom such as `sig retryUsing: [ replacementException signal ])" self class resetAllHandlers. replacementException instantiateNextHandlerFrom: thisContext. ^replacementException return: (replacementException activateHandler: true) ] retry [ "Re-execute the receiver of the #on:do: message. All handlers are reinstated: watch out, this can easily cause an infinite loop." onDoBlock isNil ifTrue: [self resignalAsUnhandled: 'No exception handler effective - #retry failed']. self class resetAllHandlers. self return: onDoBlock value ] retryUsing: aBlock [ "Execute aBlock reinstating all handlers, and return its result from the #signal method." self class resetAllHandlers. self return: aBlock value ] signalingContext [ "Return the execution context for the place that signaled the exception, or nil if it is not available anymore (for example if the exception handler has returned." | context | context := resumeBlock outerContext home. [context notNil and: [context isInternalExceptionHandlingContext]] whileTrue: [context := context parentContext]. ^context ] context [ "Return the execution context for the #on:do: snippet" ^context ] return [ "Exit the #on:do: snippet, answering nil to its caller." context isNil ifTrue: [self resignalAsUnhandled: 'No exception handler effective - #return failed']. self class resetAllHandlers. context parentContext continue: nil ] return: anObject [ "Exit the #on:do: snippet, answering anObject to its caller." context isNil ifTrue: [self resignalAsUnhandled: 'No exception handler effective - #return: failed']. self class resetAllHandlers. context parentContext continue: anObject ] activateHandler: resumeBoolean [ "Run the handler, passing to it aSignal, an instance of Signal. aBoolean indicates the action (either resuming the receiver of #on:do:... or exiting it) to be taken upon leaving from the handler block." | result | resumeBlock := [:object | self resetHandler. ^object]. result := handlerBlock cull: self. resumeBoolean ifTrue: [self resetHandler. ^result]. context parentContext continue: result ] isNested: aBoolean [ "Set the receiver's isNested instance variable." isNested := aBoolean ] onDoBlock: wdBlock handlerBlock: hBlock onDoContext: ctx previousState: anInteger [ "Initialize the receiver's instance variables." previousState := anInteger. context := ctx. onDoBlock := wdBlock. handlerBlock := hBlock. ^self ] resetHandler [ "Mark the handler that the receiver is using as not active." onDoBlock isNil ifFalse: [context at: context numArgs + 1 put: previousState] ] noTag [ NoTag isNil ifTrue: [NoTag := Object new]. ^NoTag ] ] smalltalk-3.2.5/kernel/Dictionary.st0000644000175000017500000005053712130343734014375 00000000000000"====================================================================== | | Dictionary Method Definitions | | ======================================================================" "====================================================================== | | Copyright 1988,92,94,95,99,2000,2001,2002,2003,2007,2008,2009 | Free Software Foundation, Inc. | Written by Steve Byrne and Paolo Bonzini. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" HashedCollection subclass: Dictionary [ Dictionary class >> from: anArray [ "Answer a new dictionary created from the keys and values of Associations in anArray, such as {1 -> 2. 3 -> 4}. anArray should be specified using brace-syntax." | inst | inst := self new: anArray size. anArray do: [:assoc | inst at: assoc key put: assoc value]. ^inst ] Dictionary class >> new [ "Create a new dictionary with a default size" "Builtins defines a #new method, so that during bootstrap there is a way to create dictionaries. Unfortunately, this #new method only creates dictionaries, so subclasses when trying to use this method, lose big. This fixes the problem." ^self new: 24 ] add: newObject [ "Add the newObject association to the receiver" | index assoc | index := self findIndex: newObject key. (assoc := self primAt: index) isNil ifTrue: [self incrementTally ifTrue: [index := self findIndex: newObject key]. self primAt: index put: newObject] ifFalse: [assoc value: newObject value]. ^newObject ] addAll: aCollection [ "Adds all the elements of 'aCollection' to the receiver, answer aCollection" aCollection keysAndValuesDo: [:key :value | self at: key put: value]. ^aCollection ] associations [ "Returns the content of a Dictionary as a Set of Associations." | array i | array := Array new: self size. i := 0. self associationsDo: [ :each | array at: (i := i + 1) put: each ]. ^array ] at: key put: value [ "Store value as associated to the given key" | index assoc | index := self findIndex: key. (assoc := self primAt: index) isNil ifTrue: [self incrementTally ifTrue: [index := self findIndex: key]. self primAt: index put: (Association key: key value: value)] ifFalse: [assoc value: value]. ^value ] atAll: keyCollection [ "Answer a Dictionary that only includes the given keys. Fail if any of them is not found" | result | result := self class new: keyCollection size. keyCollection do: [:key | result at: key put: (self at: key)]. ^result ] at: key [ "Answer the value associated to the given key. Fail if the key is not found" ^self at: key ifAbsent: [SystemExceptions.NotFound signalOn: key what: 'key'] ] at: key ifAbsent: aBlock [ "Answer the value associated to the given key, or the result of evaluating aBlock if the key is not found" | index | index := self findIndexOrNil: key. ^index isNil ifTrue: [aBlock value] ifFalse: [(self primAt: index) value] ] at: aKey ifAbsentPut: aBlock [ "Answer the value associated to the given key. If the key is not found, evaluate aBlock and associate the result to aKey before returning." ^self at: aKey ifAbsent: [self at: aKey put: aBlock value] ] at: aKey ifPresent: aBlock [ "If aKey is absent, answer nil. Else, evaluate aBlock passing the associated value and answer the result of the invocation" | index | index := self findIndexOrNil: aKey. ^index isNil ifTrue: [nil] ifFalse: [aBlock value: (self primAt: index) value] ] associationAt: key [ "Answer the key/value Association for the given key. Fail if the key is not found" ^self associationAt: key ifAbsent: [SystemExceptions.NotFound signalOn: key what: 'key'] ] associationAt: key ifAbsent: aBlock [ "Answer the key/value Association for the given key. Evaluate aBlock (answering the result) if the key is not found" | index | index := self findIndexOrNil: key. ^index isNil ifTrue: [aBlock value] ifFalse: [self primAt: index] ] keyAtValue: value ifAbsent: exceptionBlock [ "Answer the key associated to the given value. Evaluate exceptionBlock (answering the result) if the value is not found. IMPORTANT: == is used to compare values" self keysAndValuesDo: [:key :val | value == val ifTrue: [^key]]. ^exceptionBlock value ] keyAtValue: value [ "Answer the key associated to the given value, or nil if the value is not found" ^self keyAtValue: value ifAbsent: [nil] ] keys [ "Answer a kind of Set containing the keys of the receiver" | aSet | aSet := self keysClass new: self size * 4 // 3. self keysAndValuesDo: [:key :value | aSet add: key]. ^aSet ] values [ "Answer an Array containing the values of the receiver" | result i | result := Array new: self size. i := 0. self keysAndValuesDo: [:key :value | result at: (i := i + 1) put: value]. ^result ] includesAssociation: anAssociation [ "Answer whether the receiver contains the key which is anAssociation's key and its value is anAssociation's value" ^true == (self at: anAssociation key ifPresent: [:value | value = anAssociation value]) ] includesKey: key [ "Answer whether the receiver contains the given key" ^super includes: key ] includes: anObject [ "Answer whether the receiver contains anObject as one of its values" self do: [:element | element = anObject ifTrue: [^true]]. ^false ] occurrencesOf: aValue [ "Answer whether the number of occurrences of aValue as one of the receiver's values" | count | count := 0. self do: [:element | element = aValue ifTrue: [count := count + 1]]. ^count ] removeAllKeysSuchThat: aBlock [ "Remove from the receiver all keys for which aBlock returns true." self removeAllKeys: (self keys select: aBlock) ifAbsent: [] ] removeAllKeys: keys [ "Remove all the keys in keys, without raising any errors" keys do: [:key | self removeKey: key ifAbsent: []] ] removeAllKeys: keys ifAbsent: aBlock [ "Remove all the keys in keys, passing the missing keys as parameters to aBlock as they're encountered" keys do: [:key | self removeKey: key ifAbsent: [aBlock cull: key]] ] remove: anAssociation [ "Remove anAssociation's key from the dictionary" | index assoc | index := self findIndexOrNil: anAssociation key. index isNil ifTrue: [^SystemExceptions.NotFound signalOn: anAssociation key what: 'key']. assoc := self primAt: index. self primAt: index put: nil. self decrementTally. self rehashObjectsAfter: index. ^assoc ] remove: anAssociation ifAbsent: aBlock [ "Remove anAssociation's key from the dictionary" | index assoc | index := self findIndexOrNil: anAssociation key. index isNil ifTrue: [^aBlock value]. assoc := self primAt: index. self primAt: index put: nil. self decrementTally. self rehashObjectsAfter: index. ^assoc ] removeKey: key [ "Remove the passed key from the dictionary, fail if it is not found" ^self removeKey: key ifAbsent: [SystemExceptions.NotFound signalOn: key what: 'key'] ] removeKey: key ifAbsent: aBlock [ "Remove the passed key from the dictionary, answer the result of evaluating aBlock if it is not found" | index assoc | index := self findIndexOrNil: key. index isNil ifTrue: [^aBlock value]. assoc := self primAt: index. self primAt: index put: nil. self decrementTally. self rehashObjectsAfter: index. ^assoc value ] associationsDo: aBlock [ "Pass each association in the dictionary to aBlock" super do: aBlock ] keysDo: aBlock [ "Pass each key in the dictionary to aBlock" super do: [:assoc | aBlock value: assoc key] ] do: aBlock [ "Pass each value in the dictionary to aBlock" super do: [:assoc | aBlock value: assoc value] ] keysAndValuesDo: aBlock [ "Pass each key/value pair in the dictionary as two distinct parameters to aBlock" super do: [:assoc | aBlock value: assoc key value: assoc value] ] collect: aBlock [ "Answer a new dictionary where the keys are the same and the values are obtained by passing each value to aBlock and collecting the return values" | aDictionary | aDictionary := self copyEmpty: self capacity. self keysAndValuesDo: [:key :value | aDictionary whileGrowingAt: key put: (aBlock value: value)]. ^aDictionary ] select: aBlock [ "Answer a new dictionary containing the key/value pairs for which aBlock returns true. aBlock only receives the value part of the pairs." | newDict | newDict := self copyEmpty: self capacity. self associationsDo: [:assoc | (aBlock value: assoc value) ifTrue: [newDict add: assoc]]. ^newDict ] reject: aBlock [ "Answer a new dictionary containing the key/value pairs for which aBlock returns false. aBlock only receives the value part of the pairs." | newDict | newDict := self copyEmpty: self capacity. self associationsDo: [:assoc | (aBlock value: assoc value) ifFalse: [newDict add: assoc]]. ^newDict ] = aDictionary [ "Answer whether the receiver and aDictionary are equal" self class == aDictionary class ifFalse: [^false]. self == aDictionary ifTrue: [^true]. self size = aDictionary size ifFalse: [^false]. self keysAndValuesDo: [:key :val | val = (aDictionary at: key ifAbsent: [^false]) ifFalse: [^false]]. ^true ] hash [ "Answer the hash value for the receiver" | hashValue | hashValue := tally. self associationsDo: [:assoc | hashValue := hashValue bitXor: (self hashFor: assoc) scramble. "hack needed because the Smalltalk dictionary contains itself" assoc value == self ifFalse: [hashValue := hashValue bitXor: assoc value hash scramble]]. ^hashValue ] examineOn: aStream [ "Print all the instance variables and objects in the receiver on aStream" | class instVars i | self beConsistent. class := self class. instVars := class allInstVarNames. aStream nextPutAll: 'An instance of '. aStream print: class; nl. 1 to: instVars size do: [:i | aStream nextPutAll: ' '; nextPutAll: (instVars at: i); nextPutAll: ': '; print: (self instVarAt: i); nl]. aStream nextPutAll: ' contents: ['; nl. self associationsDo: [:obj | aStream nextPutAll: ' '; print: obj; nl]. aStream nextPutAll: ' ]'; nl ] printOn: aStream [ "Print a representation of the receiver on aStream" aStream nextPutAll: self class storeString , ' ('; nl. self keysAndValuesDo: [:key :value | aStream tab; print: key; nextPutAll: '->'; print: value; nl]. aStream nextPut: $) ] storeOn: aStream [ "Print Smalltalk code compiling to the receiver on aStream" | hasElements | aStream nextPutAll: '((' , self class storeString , ' new: '; print: self size; nextPut: $). hasElements := false. self associationsDo: [:assoc | aStream nextPutAll: ' at: '; store: assoc key; nextPutAll: ' put: '; store: assoc value; nextPut: $;. hasElements := true]. hasElements ifTrue: [aStream nextPutAll: ' yourself']. aStream nextPut: $) ] rehash [ "Rehash the receiver" | copy | copy := self copy. self resetTally. 1 to: self primSize do: [:i | self primAt: i put: nil]. copy associationsDo: [:each | self addWhileGrowing: each] ] copyAllFrom: aHashedCollection [ | assoc | 1 to: aHashedCollection primSize do: [:index | assoc := aHashedCollection primAt: index. assoc isNil ifFalse: [self addWhileGrowing: assoc key -> assoc value]]. ^self ] whileGrowingAt: key put: value [ "Private - Add the given key/value association to the receiver. Don't check for the set to be full - we want SPEED!." self addWhileGrowing: key -> value ] deepCopy [ "Returns a deep copy of the receiver (the keys and values are copies of the receiver's instance variables)" | newDictionary | newDictionary := self copyEmpty: self capacity. self keysAndValuesDo: [:k :v | newDictionary whileGrowingAt: k put: v copy]. ^newDictionary ] keysClass [ "Private - Answer the class answered by #keys" ^Set ] hashFor: anObject [ "Return an hash value for the item, anObject" ^anObject key hash ] findElementIndex: anObject [ "Tries to see where anObject can be placed as an indexed variable. As soon as nil is found, the index of that slot is answered. anObject also comes from an indexed variable." | index size element | self beConsistent. "Sorry for the lack of readability, but I want speed... :-)" index := (anObject key hash scramble bitAnd: (size := self primSize) - 1) + 1. [(element := self primAt: index) isNil ifTrue: [^index]. index == size ifTrue: [index := 1] ifFalse: [index := index + 1]] repeat ] findIndex: anObject [ "Tries to see if anObject exists as an indexed variable. As soon as nil or anObject is found, the index of that slot is answered" | index size element | self beConsistent. "Sorry for the lack of readability, but I want speed... :-)" index := (anObject hash scramble bitAnd: (size := self primSize) - 1) + 1. [((element := self primAt: index) isNil or: [element key = anObject]) ifTrue: [^index]. index == size ifTrue: [index := 1] ifFalse: [index := index + 1]] repeat ] findKeyIndex: key [ "Tries to see if key exists as a the key of an indexed variable. As soon as nil or an association with the correct key is found, the index of that slot is answered" ^self findIndex: key ] allSuperspaces [ "Answer all the receiver's superspaces in a collection" | supers | supers := OrderedCollection new. self allSuperspacesDo: [:superspace | supers addLast: superspace]. ^supers ] allSuperspacesDo: aBlock [ "Evaluate aBlock once for each of the receiver's superspaces (which is none for BindingDictionary)." ] definedKeys [ "Answer a kind of Set containing the keys of the receiver" | aSet value | aSet := self keysClass new: tally * 4 // 3. 1 to: self primSize do: [:index | value := self primAt: index. value isNil ifFalse: [aSet add: value key]]. ^aSet ] inheritsFrom: aNamespace [ "Answer whether aNamespace is one of the receiver's direct and indirect superspaces" | space | space := self. [space := space superspace. space == aNamespace ifTrue: [^true]. space notNil] whileTrue ] superspace [ "Answer the receiver's superspace, which is nil for BindingDictionary." ^nil ] withAllSuperspaces [ "Answer the receiver and all of its superspaces in a collection, which is none for BindingDictionary" | supers | supers := OrderedCollection with: self. self allSuperspacesDo: [:superspace | supers addLast: superspace]. ^supers ] withAllSuperspacesDo: aBlock [ "Invokes aBlock for the receiver and all superspaces, both direct and indirect (though a BindingDictionary does not have any)." aBlock value: self. self allSuperspacesDo: aBlock ] definesKey: key [ "Answer whether the receiver defines the given key. `Defines' means that the receiver's superspaces, if any, are not considered." ^super includes: key ] hereAssociationAt: key ifAbsent: aBlock [ "Return the association for the variable named as specified by `key' *in this namespace*. If the key is not found search will *not* be carried on in superspaces and aBlock will be immediately evaluated." | index | index := self findIndexOrNil: key. ^index isNil ifTrue: [aBlock value] ifFalse: [self primAt: index] ] hereAssociationAt: key [ "Return the association for the variable named as specified by `key' *in this namespace*. If the key is not found search will *not* be carried on in superspaces and the method will fail." ^self hereAssociationAt: key ifAbsent: [SystemExceptions.NotFound signalOn: key what: 'key'] ] hereAt: key ifAbsent: aBlock [ "Return the value associated to the variable named as specified by `key' *in this namespace*. If the key is not found search will *not* be carried on in superspaces and aBlock will be immediately evaluated." | index | index := self findIndexOrNil: key. ^index isNil ifTrue: [aBlock value] ifFalse: [(self primAt: index) value] ] hereAt: key [ "Return the value associated to the variable named as specified by `key' *in this namespace*. If the key is not found search will *not* be carried on in superspaces and the method will fail." ^self hereAt: key ifAbsent: [SystemExceptions.NotFound signalOn: key what: 'key'] ] scopeDictionary [ "Answer the dictionary that is used when the receiver is before a period in Smalltalk source code." ^self ] ] smalltalk-3.2.5/kernel/Class.st0000644000175000017500000006212112130343734013325 00000000000000"====================================================================== | | Class Method Definitions | | ======================================================================" "====================================================================== | | Copyright 1988,92,94,95,99,2000,2001,2002,2003,2005,2006,2007,2008,2009 | Free Software Foundation, Inc. | Written by Steve Byrne. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" ClassDescription subclass: Class [ | name comment category environment classVariables sharedPools securityPolicy pragmaHandlers | Class class >> allPoolDictionaries: list except: inWhite do: aBlock [ "Invoke aBlock with each of the result of combining the list of pools using a topological sort, preferring dependent to prerequisite, and then left to right. Any pool that is already in inWhite will not be answered." | white grey order descend | list isEmpty ifTrue: [ ^self ]. white := inWhite copy. grey := IdentitySet new: list size. order := OrderedCollection new: list size. descend := [:pool | (white includes: pool) ifFalse: [(grey includes: pool) ifTrue: [^SystemExceptions.InvalidValue signalOn: list reason: 'includes circular dependency']. "#allSuperspaces is not available on all pools" grey add: pool. pool allSuperspaces reverseDo: descend. order addFirst: pool. white add: pool]]. list reverseDo: descend. order do: aBlock ] Class class >> initialize [ "Perform the special initialization of root classes." self subclassesDo: [:each | each instanceClass initializeAsRootClass] ] name [ "Answer the class name" ^name ] comment [ "Answer the class comment" ^comment ] comment: aString [ "Change the class name" comment := aString ] environment [ ^environment ] environment: aNamespace [ "Set the receiver's environment to aNamespace and recompile everything" environment := aNamespace. (self asClass) compileAll; compileAllSubclasses. (self asMetaclass) compileAll; compileAllSubclasses ] category [ "Answer the class category" ^category ] category: aString [ "Change the class category to aString" category := aString ] superclass: aClass [ "Set the receiver's superclass." (aClass isNil and: [self superclass notNil]) ifTrue: [self initializeAsRootClass]. super superclass: aClass ] addClassVarName: aString [ "Add a class variable with the given name to the class pool dictionary." | sym | sym := aString asClassPoolKey. (self classPool includesKey: sym) ifFalse: [self classPool at: sym put: nil]. ^self classPool associationAt: sym ] addClassVarName: aString value: valueBlock [ "Add a class variable with the given name to the class pool dictionary, and evaluate valueBlock as its initializer." ^(self addClassVarName: aString) value: valueBlock value; yourself ] bindingFor: aString [ "Answer the variable binding for the class variable with the given name" | sym | sym := aString asClassPoolKey. ^self classPool associationAt: sym ] removeClassVarName: aString [ "Removes the class variable from the class, error if not present, or still in use." | sym | sym := aString asClassPoolKey. (classVariables notNil and: [classVariables includesKey: sym]) ifFalse: [SystemExceptions.NotFound signalOn: aString what: 'class variable']. classVariables removeKey: sym. (self asClass) compileAll; compileAllSubclasses. (self asMetaclass) compileAll; compileAllSubclasses ] classPool [ "Answer the class pool dictionary" classVariables isNil ifTrue: [classVariables := BindingDictionary new environment: self]. ^classVariables ] classVarNames [ "Answer the names of the variables in the class pool dictionary" ^classVariables notNil ifTrue: [classVariables keys] ifFalse: [Set new] ] allClassVarNames [ "Answer the names of the variables in the receiver's class pool dictionary and in each of the superclasses' class pool dictionaries" | superVarNames | superVarNames := self classVarNames. self allSuperclasses do: [:each | superVarNames addAll: each classVarNames]. ^superVarNames ] addSharedPool: aDictionary [ "Add the given shared pool to the list of the class' pool dictionaries" sharedPools ifNil: [sharedPools := #()]. (sharedPools includes: aDictionary) ifFalse: [sharedPools := sharedPools copyWith: aDictionary] ] removeSharedPool: aDictionary [ "Remove the given dictionary to the list of the class' pool dictionaries" sharedPools ifNil: [sharedPools := #()]. sharedPools := sharedPools copyWithout: aDictionary ] sharedPools [ "Return the names of the shared pools defined by the class" | s | s := Set new. (sharedPools notNil and: [sharedPools notEmpty]) ifTrue: [self environment associationsDo: [:each | (sharedPools identityIncludes: each value) ifTrue: [s add: each key]]]. ^s ] classPragmas [ "Return the pragmas that are written in the file-out of this class." ^#(#category #comment) ] initializeAsRootClass [ "Perform special initialization reserved to root classes." self registerHandler: [:method :ann | method rewriteAsCCall: (ann arguments at: 1) for: self] forPragma: #cCall:. self registerHandler: [:method :ann | method rewriteAsCCall: (ann arguments at: 1) returning: (ann arguments at: 2) args: (ann arguments at: 3)] forPragma: #cCall:returning:args:. self registerHandler: [:method :ann | method rewriteAsAsyncCCall: (ann arguments at: 1) args: (ann arguments at: 2)] forPragma: #asyncCCall:args: ] initialize [ "redefined in children (?)" ^self ] = aClass [ "Returns true if the two class objects are to be considered equal." "^(aClass isKindOf: Class) and: [name = aClass name]" ^self == aClass ] categoriesFor: method are: categories [ "Don't use this, it is only present to file in from IBM Smalltalk" self >> method methodCategory: (categories at: 1) ] subclass: classNameString instanceVariableNames: stringInstVarNames classVariableNames: stringOfClassVarNames poolDictionaries: stringOfPoolNames [ "Don't use this, it is only present to file in from IBM Smalltalk" ^self subclass: classNameString instanceVariableNames: stringInstVarNames classVariableNames: stringOfClassVarNames poolDictionaries: stringOfPoolNames category: 'no category' ] subclass: classNameString classInstanceVariableNames: stringClassInstVarNames instanceVariableNames: stringInstVarNames classVariableNames: stringOfClassVarNames poolDictionaries: stringOfPoolNames [ "Don't use this, it is only present to file in from IBM Smalltalk" ^(self subclass: classNameString instanceVariableNames: stringInstVarNames classVariableNames: stringOfClassVarNames poolDictionaries: stringOfPoolNames category: 'no category') classInstanceVariableNames: stringClassInstVarNames; yourself ] variableSubclass: classNameString instanceVariableNames: stringInstVarNames classVariableNames: stringOfClassVarNames poolDictionaries: stringOfPoolNames [ "Don't use this, it is only present to file in from IBM Smalltalk" ^self variableSubclass: classNameString instanceVariableNames: stringInstVarNames classVariableNames: stringOfClassVarNames poolDictionaries: stringOfPoolNames category: 'no category' ] variableSubclass: classNameString classInstanceVariableNames: stringClassInstVarNames instanceVariableNames: stringInstVarNames classVariableNames: stringOfClassVarNames poolDictionaries: stringOfPoolNames [ "Don't use this, it is only present to file in from IBM Smalltalk" ^(self variableSubclass: classNameString instanceVariableNames: stringInstVarNames classVariableNames: stringOfClassVarNames poolDictionaries: stringOfPoolNames category: 'no category') classInstanceVariableNames: stringClassInstVarNames; yourself ] variableByteSubclass: classNameString classVariableNames: stringOfClassVarNames poolDictionaries: stringOfPoolNames [ "Don't use this, it is only present to file in from IBM Smalltalk" ^self variableByteSubclass: classNameString instanceVariableNames: '' classVariableNames: stringOfClassVarNames poolDictionaries: stringOfPoolNames category: 'no category' ] variableByteSubclass: classNameString classInstanceVariableNames: stringClassInstVarNames classVariableNames: stringOfClassVarNames poolDictionaries: stringOfPoolNames [ "Don't use this, it is only present to file in from IBM Smalltalk" ^(self variableByteSubclass: classNameString instanceVariableNames: '' classVariableNames: stringOfClassVarNames poolDictionaries: stringOfPoolNames category: 'no category') classInstanceVariableNames: stringClassInstVarNames; yourself ] variableLongSubclass: classNameString classVariableNames: stringOfClassVarNames poolDictionaries: stringOfPoolNames [ "Don't use this, it is only present to file in from IBM Smalltalk" ^self variable: #uint subclass: classNameString instanceVariableNames: '' classVariableNames: stringOfClassVarNames poolDictionaries: stringOfPoolNames category: 'no category' ] variableLongSubclass: classNameString classInstanceVariableNames: stringClassInstVarNames classVariableNames: stringOfClassVarNames poolDictionaries: stringOfPoolNames [ "Don't use this, it is only present to file in from IBM Smalltalk" ^(self variable: #uint subclass: classNameString instanceVariableNames: '' classVariableNames: stringOfClassVarNames poolDictionaries: stringOfPoolNames category: 'no category') classInstanceVariableNames: stringClassInstVarNames; yourself ] extend [ "Redefine a version of the receiver in the current namespace. Note: this method can bite you in various ways when sent to system classes; read the section on namespaces in the manual for some examples of the problems you can encounter." | method | method := self kindOfSubclass , 'instanceVariableNames:classVariableNames:poolDictionaries:category:'. ^self perform: method asSymbol withArguments: {self name asSymbol. ''. ''. ''. 'Extensions'} ] inheritShape [ "Answer whether subclasses will have by default the same shape as this class. The default is false." ^false ] subclass: classNameString [ "Define a subclass of the receiver with the given name. If the class is already defined, don't modify its instance or class variables but still, if necessary, recompile everything needed." | meta | KernelInitialized ifFalse: [^Smalltalk at: classNameString]. meta := self metaclassFor: classNameString. ^meta name: classNameString environment: Namespace current subclassOf: self ] subclass: classNameString instanceVariableNames: stringInstVarNames classVariableNames: stringOfClassVarNames poolDictionaries: stringOfPoolNames category: categoryNameString [ "Define a fixed subclass of the receiver with the given name, instance variables, class variables, pool dictionaries and category. If the class is already defined, if necessary, recompile everything needed." | meta | KernelInitialized ifFalse: [^(Smalltalk at: classNameString) category: categoryNameString]. meta := self metaclassFor: classNameString. ^meta name: classNameString environment: Namespace current subclassOf: self instanceVariableNames: stringInstVarNames shape: (self inheritShape ifTrue: [ #inherit ]) classVariableNames: stringOfClassVarNames poolDictionaries: stringOfPoolNames category: categoryNameString ] variableSubclass: classNameString instanceVariableNames: stringInstVarNames classVariableNames: stringOfClassVarNames poolDictionaries: stringOfPoolNames category: categoryNameString [ "Define a variable pointer subclass of the receiver with the given name, instance variables, class variables, pool dictionaries and category. If the class is already defined, if necessary, recompile everything needed." | meta | KernelInitialized ifFalse: [^(Smalltalk at: classNameString) category: categoryNameString]. meta := self metaclassFor: classNameString. ^meta name: classNameString environment: Namespace current subclassOf: self instanceVariableNames: stringInstVarNames shape: #pointer classVariableNames: stringOfClassVarNames poolDictionaries: stringOfPoolNames category: categoryNameString ] variable: shape subclass: classNameString instanceVariableNames: stringInstVarNames classVariableNames: stringOfClassVarNames poolDictionaries: stringOfPoolNames category: categoryNameString [ "Define a variable subclass of the receiver with the given name, shape, instance variables, class variables, pool dictionaries and category. If the class is already defined, if necessary, recompile everything needed. The shape can be one of #byte #int8 #character #short #ushort #int #uint #int64 #uint64 #utf32 #float #double or #pointer." | meta | KernelInitialized ifFalse: [^(Smalltalk at: classNameString) category: categoryNameString]. meta := self metaclassFor: classNameString. ^meta name: classNameString environment: Namespace current subclassOf: self instanceVariableNames: stringInstVarNames shape: shape classVariableNames: stringOfClassVarNames poolDictionaries: stringOfPoolNames category: categoryNameString ] variableWordSubclass: classNameString instanceVariableNames: stringInstVarNames classVariableNames: stringOfClassVarNames poolDictionaries: stringOfPoolNames category: categoryNameString [ "Define a word variable subclass of the receiver with the given name, instance variables (must be ''), class variables, pool dictionaries and category. If the class is already defined, if necessary, recompile everything needed." | meta | KernelInitialized ifFalse: [^(Smalltalk at: classNameString) category: categoryNameString]. meta := self metaclassFor: classNameString. ^meta name: classNameString environment: Namespace current subclassOf: self instanceVariableNames: stringInstVarNames shape: #word classVariableNames: stringOfClassVarNames poolDictionaries: stringOfPoolNames category: categoryNameString ] variableByteSubclass: classNameString instanceVariableNames: stringInstVarNames classVariableNames: stringOfClassVarNames poolDictionaries: stringOfPoolNames category: categoryNameString [ "Define a byte variable subclass of the receiver with the given name, instance variables (must be ''), class variables, pool dictionaries and category. If the class is already defined, if necessary, recompile everything needed." | meta | KernelInitialized ifFalse: [^(Smalltalk at: classNameString) category: categoryNameString]. meta := self metaclassFor: classNameString. ^meta name: classNameString environment: Namespace current subclassOf: self instanceVariableNames: stringInstVarNames shape: #byte classVariableNames: stringOfClassVarNames poolDictionaries: stringOfPoolNames category: categoryNameString ] article [ "Answer an article (`a' or `an') which is ok for the receiver's name" | name | name := self name. ^(name at: 1) isVowel ifTrue: ['an'] ifFalse: ['a'] ] printOn: aStream [ "Print a representation of the receiver on aStream" aStream nextPutAll: (self nameIn: Smalltalk) ] storeOn: aStream [ "Store Smalltalk code compiling to the receiver on aStream" aStream nextPutAll: (self nameIn: Smalltalk) ] securityPolicy [ ^securityPolicy ] securityPolicy: aSecurityPolicy [ securityPolicy := aSecurityPolicy withOwner: self ] check: aPermission [ self securityPolicy isNil ifTrue: [^self isUntrusted not]. ^self securityPolicy check: aPermission ] registerHandler: aBlock forPragma: pragma [ "While compiling methods, on every encounter of the pragma with the given name, call aBlock with the CompiledMethod and an array of pragma argument values." pragmaHandlers isNil ifTrue: [pragmaHandlers := IdentityDictionary new]. pragmaHandlers at: pragma put: aBlock ] pragmaHandlerFor: aSymbol [ "Answer the (possibly inherited) registered handler for pragma aSymbol, or nil if not found." | handler | pragmaHandlers isNil ifFalse: [handler := pragmaHandlers at: aSymbol ifAbsent: [nil]. handler isNil ifFalse: [^handler]]. self superclass isNil ifFalse: [^self superclass pragmaHandlerFor: aSymbol]. ^nil ] classInstanceVariableNames: stringClassInstVarNames [ self class instanceVariableNames: stringClassInstVarNames ] setClassVariables: aDictionary [ classVariables := aDictionary ] setName: aString [ name := aString ] setEnvironment: aNamespace [ environment := aNamespace ] setSharedPools: anArray [ "Private - Set the receiver's shared pools to be those in anArray" sharedPools := anArray ifNil: [#()] ] sharedPoolDictionaries [ "Return the shared pools (not the names!) defined by the class" ^sharedPools ifNil: [#()] ] allSharedPoolDictionariesDo: aBlock [ "Answer the shared pools visible from methods in the metaclass, in the correct search order." | superclassSpaces | self withAllSuperclassesDo: [:behavior || classSpaces | aBlock value: behavior classPool. "Extract the spaces of this class from superclassSpaces into classSpaces..." superclassSpaces isNil ifTrue: [classSpaces := IdentitySet new. behavior environment withAllSuperspacesDo: [ :each | classSpaces add: each]] ifFalse: [classSpaces := superclassSpaces]. "... and visit them." behavior allLocalSharedPoolDictionariesExcept: classSpaces do: aBlock. "Collect those spaces that have to be skipped in the search." superclassSpaces := IdentitySet new. behavior superclass ifNotNil: [:superclass | superclass environment withAllSuperspacesDo: [ :each | superclassSpaces add: each ]]. "Now proceed with the `natural' (non-imported spaces)." behavior environment withAllSuperspacesDo: [:each | (superclassSpaces includes: each) ifFalse: [aBlock value: each. "also visit the namespace shared pools" Class allPoolDictionaries: each sharedPoolDictionaries except: classSpaces do: aBlock]]] ] allLocalSharedPoolDictionariesExcept: inWhite do: aBlock [ "Answer the result of combining the list of pools imported into the receiver using a topological sort, preferring dependent to prerequisite, and then left to right. Any pool that is already in inWhite will not be answered." Class allPoolDictionaries: self sharedPoolDictionaries except: inWhite do: aBlock ] metaclassFor: classNameString [ "Create a Metaclass object for the given class name. The metaclass is a subclass of the receiver's metaclass" | className class | className := classNameString asGlobalKey. class := Namespace current hereAt: className ifAbsent: [nil]. class isNamespace ifTrue: [ self error: 'Class name %1 conflicts with the name of its namespace' % {classNameString asString} ]. ^(class isNil or: [class isClass not]) ifTrue: [Metaclass subclassOf: self class] ifFalse: [class class] ] asClass [ ^self ] isClass [ ^true ] fileOutDeclarationOn: aFileStream [ "File out class definition to aFileStream. Requires package Parser." self notYetImplemented ] fileOutOn: aFileStream [ "File out complete class description: class definition, class and instance methods. Requires package Parser." self notYetImplemented ] binaryRepresentationVersion [ "Answer a number >= 0 which represents the current version of the object's representation. The default implementation answers zero." ^0 ] nonVersionedInstSize [ "Answer the number of instance variables that the class used to have when objects were stored without using a VersionableObjectProxy. The default implementation answers the current instSize." ^self instSize ] convertFromVersion: version withFixedVariables: fixed indexedVariables: indexed for: anObjectDumper [ "This method is called if a VersionableObjectProxy is attached to a class. It receives the version number that was stored for the object (or nil if the object did not use a VersionableObjectProxy), the fixed instance variables, the indexed instance variables, and the ObjectDumper that has read the object. The default implementation ignores the version and simply fills in an instance of the receiver with the given fixed and indexed instance variables (nil if the class instances are of fixed size). If instance variables were removed from the class, extras are ignored; if the class is now fixed and used to be indexed, indexed is not used." | object | object := self isFixed ifTrue: [self basicNew] ifFalse: [self basicNew: indexed size]. fixed from: 1 to: (fixed size min: self instSize) keysAndValuesDo: [:i :obj | object instVarAt: i put: obj]. (self isFixed or: [indexed isNil]) ifTrue: [^object]. indexed keysAndValuesDo: [:i :obj | object basicAt: i put: obj]. ^object ] ] smalltalk-3.2.5/kernel/Float.st0000644000175000017500000005007512130343734013332 00000000000000"====================================================================== | | Float Method Definitions | | ======================================================================" "====================================================================== | | Copyright 1988,92,94,95,99,2000,2001,2002,2003,2007,2008,2009 | Free Software Foundation, Inc. | Written by Steve Byrne. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" Number subclass: Float [ Float class >> signByte [ "Answer the byte of the receiver that contains the sign bit" self subclassResponsibility ] Float class >> e [ "Returns the value of e. Hope is that it is precise enough" ^16r2.B7E151628AED2A6ABF71588d ] Float class >> log10Base2 [ "Returns the value of log2 10. Hope is that it is precise enough" ^16r3.5269E12F346E2BF924AFDBFDd ] Float class >> ln10 [ "Returns the value of ln 10. Hope is that it is precise enough" ^16r2.4D763776AAA2B05BA95B58AEd ] Float class >> pi [ "Returns the value of pi. Hope is that it is precise enough" ^16r3.243F6A8885A308D313198A2Ed ] Float class >> radix [ "Answer the base in which computations between instances of the receiver are made. This should be 2 on about every known computer, so GNU Smalltalk always answers 2." ^2 ] Float class >> denormalized [ "Answer whether instances of the receiver can be in denormalized form." ^self fminDenormalized > 0 ] Float class >> fminDenormalized [ "Return the smallest Float that is > 0 if denormalized values are supported, else return 0." ^self fminNormalized timesTwoPower: 1 - self precision ] Float class >> fmin [ "Return the smallest Float that is > 0." | fminDen fmin | fmin := self fminNormalized. fminDen := fmin timesTwoPower: 1 - self precision. ^fminDen = 0 ifTrue: [fmin] ifFalse: [fminDen] ] Float class >> epsilon [ "Return the smallest Float x for which is 1 + x ~= 1" ^(self coerce: 2) timesTwoPower: self precision negated ] hash [ "Answer an hash value for the receiver. Not-a-number values do not have a hash code and cannot be put in a hashed collection." "Hack so that 2 hash = 2.0 hash" self = self ifFalse: [ SystemExceptions.InvalidValue signalOn: self reason: 'cannot put NaN in a hashed collection' ]. ^self fractionPart = 0.0 ifTrue: [self asInteger hash] ifFalse: [self primHash] ] negated [ "Return the negation of the receiver. Unlike 0-self, this converts correctly signed zeros." ^self * -1 ] integerPart [ "Return the receiver's integer part" ^self - self fractionPart ] raisedToInteger: anInteger [ "Return self raised to the anInteger-th power" "Some special cases first" | exp adjustExp val mant | anInteger isInteger ifFalse: [SystemExceptions.WrongClass signalOn: anInteger mustBe: Integer]. anInteger = 0 ifTrue: [^self unity]. anInteger = 1 ifTrue: [^self]. "Avoid overflow when the result is denormal and we would have an unrepresentable intermediate result for its reciprocal." adjustExp := self exponent. exp := anInteger abs. (anInteger > 0 or: [(adjustExp + 1) * exp < self class emax]) ifTrue: [mant := self. adjustExp := 0] ifFalse: [mant := self timesTwoPower: 0 - adjustExp. adjustExp := adjustExp * anInteger]. "Fire the big loop." val := mant raisedToInteger: exp withCache: ((Array new: (255 min: exp)) at: 1 put: mant; yourself). anInteger < 0 ifTrue: [val := val reciprocal]. adjustExp = 0 ifFalse: [val := val timesTwoPower: adjustExp]. ^val ] isNaN [ "Answer whether the receiver represents a NaN" ^self ~= self ] isFinite [ "Answer whether the receiver does not represent infinity, nor a NaN" ^self - self = self zero ] isInfinite [ "Answer whether the receiver represents positive or negative infinity" ^self = self class infinity or: [self = self class negativeInfinity] ] negative [ "Answer whether the receiver is negative" ^self <= self zero and: [self unity / self <= self zero] ] strictlyPositive [ "Answer whether the receiver is > 0" ^self > self zero ] positive [ "Answer whether the receiver is positive. Negative zero is not positive, so the definition is not simply >= 0." ^self >= self zero and: [self unity / self >= self zero] ] sign [ "Answer 1 if the receiver is greater than 0, -1 if less than 0, else 0. Negative zero is the same as positive zero." self = self zero ifTrue: [^0]. ^self < 0 ifTrue: [-1] ifFalse: [1] ] truncated [ "Convert the receiver to an Integer. Only used for LargeIntegers, there are primitives for the other cases." | exponent bytes positive float | self isFinite ifFalse: [^self]. (positive := self > 0) ifTrue: [float := self] ifFalse: [float := self negated]. exponent := float exponent. bytes := LargePositiveInteger new: (self class precision + 7) // 8 + 1. float := float timesTwoPower: float class precision - exponent - 8. 1 to: bytes size do: [:i | bytes digitAt: i put: (float fractionPart timesTwoPower: 8) truncated. float := float integerPart timesTwoPower: -8]. bytes := bytes bitShift: exponent - float class precision. positive ifFalse: [bytes := bytes negated]. ^bytes ] asCNumber [ "Convert the receiver to a kind of number that is understood by the C call-out mechanism." ^self ] asExactFraction [ "Convert the receiver into a fraction with optimal approximation, but with usually huge terms." | shift mantissa | self checkCoercion. shift := self exponent negated + self class precision. mantissa := (self timesTwoPower: shift) truncated. ^shift negative ifTrue: [(mantissa * (1 bitShift: shift negated)) asFraction] ifFalse: [(mantissa / (1 bitShift: shift)) asFraction] ] asFraction [ "Convert the receiver into a fraction with a good (but undefined) approximation" | a x n2 d2 n1 d1 n0 d0 eps abs gcd | self checkCoercion. "This uses an algorithm based on continued fractions. n2/d2 = numerator and denominator of the fraction two steps ago n1/d1 = numerator and denominator of the fraction a steps ago n0/d0 = numerator and denominator of the fraction at the current step" n1 := d0 := 0. n0 := d1 := 1. abs := self abs timesTwoPower: self exponent negated. eps := self class epsilon. x := abs. [a := x truncated. n2 := n1. d2 := d1. n1 := n0. d1 := d0. n0 := n1 * a + n2. d0 := d1 * a + d2. (x := self unity / x fractionPart) isInfinite or: [((self coerce: n0) / (self coerce: d0) - abs) abs < eps]] whileFalse. self exponent < 0 ifTrue: [d0 := d0 * (2 raisedToInteger: self exponent negated)] ifFalse: [n0 := n0 * (2 raisedToInteger: self exponent)]. gcd := n0 gcd: d0. n0 := n0 divExact: gcd. d0 := d0 divExact: gcd. ^Fraction numerator: (self < 0 ifTrue: [n0 negated] ifFalse: [n0]) denominator: d0 ] log [ "Answer log base 10 of the receiver." ^self ln / self class ln10 ] log: aNumber [ "Answer log base aNumber of the receiver" ^self ln / (self coerce: aNumber) ln ] ceilingLog: radix [ "Answer (self log: radix) ceiling. Use exact arithmetic if radix is not a floating point value." radix isFloat ifFalse: [ ^self asExactFraction ceilingLog: radix ]. self < self zero ifTrue: [^self arithmeticError: 'cannot extract logarithm of a negative number']. radix <= radix unity ifTrue: [radix <= radix zero ifTrue: [^self arithmeticError: 'bad radix']. radix = radix unity ifTrue: [^self arithmeticError: 'bad radix']]. ^(self log: radix) ceiling ] floorLog: radix [ "Answer (self log: radix) floor. Use exact arithmetic if radix is not a floating point value." radix isFloat ifFalse: [ ^self asExactFraction floorLog: radix ]. self < self zero ifTrue: [^self arithmeticError: 'cannot extract logarithm of a negative number']. radix <= radix unity ifTrue: [radix <= radix zero ifTrue: [^self arithmeticError: 'bad radix']. radix = radix unity ifTrue: [^self arithmeticError: 'bad radix']]. ^(self log: radix) floor ] estimatedLog [ "Answer an estimate of (self abs floorLog: 10)" ^(self exponent + 1) asFloatD / FloatD log10Base2 ] asFloat [ "Just defined for completeness. Return the receiver." ^self ] min: aNumber [ "Answer the minimum between the receiver and aNumber. Redefine in subclasses if necessary to ensure that if either self or aNumber is a NaN, it is always answered." "If both self and aNumber are zero, return aNumber in case it has a negative sign, because we assume our zero is positive. If the test is false, always answer aNumber in case it is a NaN, because we assume that self is not a NaN." ^aNumber < self ifTrue: [aNumber] ifFalse: [self = aNumber ifFalse: [aNumber = aNumber ifFalse: [aNumber] ifTrue: [self]] ifTrue: ["Remember than -0.0 - +0.0 = -0.0, but the other pairs are +0.0." self = self zero ifTrue: [(self * -1 - aNumber) * -1] ifFalse: [self]]] ] max: aNumber [ "Answer the maximum between the receiver and aNumber. Redefine in subclasses if necessary to ensure that if either self or aNumber is a NaN, it is always answered." ^aNumber > self ifTrue: [aNumber] ifFalse: [self = aNumber ifFalse: [aNumber = aNumber ifFalse: [aNumber] ifTrue: [self]] ifTrue: ["Remember than -0.0 + -0.0 = -0.0, but the other pairs are +0.0." self = self zero ifTrue: [self + aNumber] ifFalse: [self]]] ] withSignOf: aNumber [ "Answer the receiver, with its sign possibly changed to match that of aNumber." ^aNumber positive == self positive ifTrue: [self] ifFalse: [self negated] ] printOn: aStream [ "Print a representation of the receiver on aStream" self printOn: aStream special: #('Inf' '-Inf' 'NaN') ] isExact [ "Answer whether the receiver performs exact arithmetic. Floats do not." ^false ] isLiteralObject [ "Answer whether the receiver is expressible as a Smalltalk literal." ^true ] storeLiteralOn: aStream [ "Store on aStream some Smalltalk code which compiles to the receiver" self storeOn: aStream ] storeOn: aStream [ "Print a representation of the receiver on aStream" | printString | (self isInfinite or: [self isNaN]) ifTrue: [^self printOn: aStream special: #('%1 infinity' '%1 negativeInfinity' '%1 nan')]. printString := self printString. aStream nextPutAll: printString. "For FloatE/FloatQ, force printing the exponent at the end." self exponentLetter == $d ifTrue: [^self]. (printString includes: self exponentLetter) ifFalse: [aStream nextPut: self exponentLetter] ] checkCoercion [ "Private - Fail if the receiver is only representable as a Float" self isInfinite ifTrue: [self arithmeticError: 'Infinity can only be a Float']. self isNaN ifTrue: [self arithmeticError: 'Not-a-Number can only be a Float'] ] printOn: aStream special: whatToPrintArray [ "Private - Print a decimal representation of the receiver on aStream, printing one of the three elements of whatToPrintArray if it is infinity, negative infinity, or a NaN" "First, take care of the easy cases." | me exponential small num sameUp sameDown weight prevWeight digit eps precision digits digitStream exponent dotPrinted allNines adjust | self isNaN ifTrue: [^aStream nextPutAll: (whatToPrintArray at: 3) % {self class}]. self = self class infinity ifTrue: [^aStream nextPutAll: (whatToPrintArray at: 1) % {self class}]. self = self class negativeInfinity ifTrue: [^aStream nextPutAll: (whatToPrintArray at: 2) % {self class}]. "We deal only with positive values." me := self abs. self negative ifTrue: [aStream nextPut: $-]. self = self zero ifTrue: [aStream nextPutAll: '0.0'. ^self]. "Figure out some quantities and the way we'll print the number." exponential := me exponent abs > me class precision. small := me < me unity. "Compute the digits one by one." num := me asExactFraction. exponent := (num floorLog: 10) + 1. digits := 0. weight := 10 raisedToInteger: exponent - 1. "Smallest number such that me + eps ~= eps" eps := 2 raisedToInteger: me exponent - me class precision + 1. allNines := true. sameDown := true. sameUp := true. [digit := num // weight. allNines := allNines and: [digit = 9]. sameDown := sameDown and: [(num - eps) // weight = digit]. sameUp := sameUp and: [(num + eps) // weight = digit]. digits := digits * 10 + digit. num := num - (digit * weight). prevWeight := weight. weight := weight / 10. sameDown or: [sameUp]] whileTrue. "For large numbers, don't let round-to-even bite us." eps isInteger ifTrue: [eps := eps / 2]. adjust := 0. "Round the last digit if it allows to save trailing digits while not changing the meaning." (digit <= 5 and: [num + (digit * prevWeight) < (eps / 2)]) ifTrue: [adjust := digit negated]. (digit > 5 and: [num + ((digit - 10) * prevWeight) > (eps / -2)]) ifTrue: [adjust := 10 - digit]. "... otherwise, try rounding it up if it is a better approximation." (adjust = 0 and: [digit > 0]) ifTrue: [ (num - prevWeight) abs < num ifTrue: [adjust := 1]]. digits := digits + adjust. (adjust > 0 and: [allNines]) ifTrue: [allNines := false. exponent := exponent + 1]. digits := digits printString. "Print the non-significant zeros." dotPrinted := false. (small and: [exponential not]) ifTrue: [1 - exponent timesRepeat: [aStream nextPut: $0. dotPrinted ifFalse: [dotPrinted := true. aStream nextPut: $.]. exponent := exponent + 1]]. "Make a stream with the significant digits." precision := digits findLast: [:ch | ch ~= $0]. digitStream := ReadStream on: digits from: 1 to: precision. "Print the integer part (only one digit if using exponential notation)." [digitStream atEnd ifTrue: [aStream nextPut: $0] ifFalse: [aStream nextPut: digitStream next]. exponent := exponent - 1. exponent > 0 and: [exponential not]] whileTrue. "Print the fractional part." digitStream atEnd ifTrue: [dotPrinted ifFalse: [aStream nextPutAll: '.0']] ifFalse: [dotPrinted ifFalse: [aStream nextPut: $.]. digitStream do: [:each | aStream nextPut: each]]. "Finally, print the exponent if necessary." exponential ifTrue: [aStream nextPut: me exponentLetter; print: exponent] ] isFloat [ ^true ] exp [ "Answer 'e' (2.718281828459...) raised to the receiver" self primitiveFailed ] ln [ "Answer the logarithm of the receiver in base 'e' (2.718281828459...)" self primitiveFailed ] raisedTo: aNumber [ "Answer the receiver raised to its aNumber power" aNumber isFloat ifTrue: [self arithmeticError: 'invalid operands']. ^self raisedTo: (self coerce: aNumber) ] sqrt [ "Answer the square root of the receiver" self primitiveFailed ] ceiling [ "Answer the integer part of the receiver, truncated towards +infinity" self checkCoercion. ^self > 0 ifTrue: [self truncated + self fractionPart sign] ifFalse: [self truncated] ] rounded [ "Answer the receiver, rounded to the nearest integer" self fractionPart abs < self half ifTrue: [^self truncated] ifFalse: [^self truncated + self sign rounded] ] half [ "Answer 0.5 in the representation of the receiver" ^self unity / 2 ] primHash [ "Private - Answer an hash value for the receiver" ^0 ] floor [ "Answer the integer part of the receiver, truncated towards -infinity" self checkCoercion. ^self < 0 ifTrue: [self truncated + self fractionPart sign] ifFalse: [self truncated] ] sin [ "Answer the sine of the receiver" self primitiveFailed ] cos [ "Answer the cosine of the receiver" self primitiveFailed ] tan [ "Answer the tangent of the receiver" ] arcSin [ "Answer the arc-sine of the receiver" ^self arithmeticError: 'argument out of range' ] arcCos [ "Answer the arc-cosine of the receiver" ^self arithmeticError: 'argument out of range' ] arcTan [ "Answer the arc-tangent of the receiver" ] successor [ | exponent | self isFinite ifFalse: [ (self isNaN or: [self positive]) ifTrue: [^self]. ^self class fmax negated]. self = 0.0 ifTrue: [^self class fmin]. exponent := self exponent. ^exponent < self class emin ifTrue: [self + self class fminDenormalized] ifFalse: [self + (self class epsilon timesTwoPower: exponent)] ] predecessor [ | exponent | self isFinite ifFalse: [ (self isNaN or: [self negative]) ifTrue: [^self]. ^self class fmax]. self = 0.0 ifTrue: [^self class fmin negated]. exponent := self exponent. ^exponent < self class emin ifTrue: [self - self class fminDenormalized] ifFalse: [self - (self class epsilon timesTwoPower: exponent)] ] ] smalltalk-3.2.5/kernel/ProcSched.st0000644000175000017500000002222312130343734014131 00000000000000"====================================================================== | | ProcessorScheduler Method Definitions | | ======================================================================" "====================================================================== | | Copyright 1988,89,90,91,92,94,95,99,2000,2001,2002,2003,2008,2009 | Free Software Foundation, Inc. | Written by Steve Byrne. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" Object subclass: ProcessorScheduler [ | processLists activeProcess idleTasks processTimeslice gcSemaphore gcArray | ProcessorScheduler class >> new [ "Error---new instances of ProcessorScheduler should not be created." self shouldNotImplement ] processEnvironment [ "Answer another singleton object hosting thread-local variables for the Smalltalk processes. This acts like a normal Dictionary with a couple of differences: a) using #associationAt: will return special associations that retrieve a thread-local value; b) requesting missing keys will return nil, and removing them will be a nop." ^ProcessEnvironment uniqueInstance ] activeProcess [ "Answer the active process" ^activeProcess ] activeDebugger [ "Answer the active process' debugger" ^self activeProcess debugger ] activePriority [ "Answer the active process' priority" ^self activeProcess priority ] processesAt: aPriority [ "Answer a linked list of processes at the given priority" ^processLists at: aPriority ] terminateActive [ "Terminate the active process" self activeProcess terminate ] timeSlice: milliSeconds [ "Set the timeslice that is assigned to each Process before it is automatically preempted by the system. Setting this to zero disables preemptive multitasking. Note that the system by default is compiled with preemptive multitasking disabled, and that even if it is enabled it will surely work only under BSD derivatives (or, in general, systems that support ITIMER_VIRTUAL)." processTimeslice := milliSeconds ] timeSlice [ "Answer the timeslice that is assigned to each Process before it is automatically preempted by the system (in milliseconds). An answer of zero means that preemptive multitasking is disabled. Note that the system by default is compiled without preemptive multitasking, and that even if it is enabled it will work only under BSD derivatives (or, in general, systems that support ITIMER_VIRTUAL)." ^processTimeslice ] yield [ "Let the active process yield control to other processes" self activeProcess yield ] priorityName: priority [ "Private - Answer a name for the given process priority" ^#('idlePriority' 'systemBackgroundPriority' 'userBackgroundPriority' 'userSchedulingPriority' 'userInterruptPriority' 'lowIOPriority' 'highIOPriority' 'timingPriority' 'unpreemptedPriority') at: priority ] highestPriority [ "Answer the highest valid priority" ^processLists size ] unpreemptedPriority [ "Answer the highest priority avilable in the system; never create a process with this priority, instead use BlockClosure>>#valueWithoutPreemption." ^9 ] timingPriority [ "Answer the priority for system real-time processes." ^8 ] highIOPriority [ "Answer the priority for system high-priority I/O processes, such as a process handling input from a network." ^7 ] lowIOPriority [ "Answer the priority for system low-priority I/O processes. Examples are the process handling input from the user (keyboard, pointing device, etc.) and the process distributing input from a network." ^6 ] userInterruptPriority [ "Answer the priority for user interrupt-priority processes. Processes run at this level will preempt the window scheduler and should, therefore, not consume the processor forever." ^5 ] userSchedulingPriority [ "Answer the priority for user standard-priority processes" ^4 ] userBackgroundPriority [ "Answer the priority for user background-priority processes" ^3 ] systemBackgroundPriority [ "Answer the priority for system background-priority processes. An incremental garbage collector could run at this level but now it runs at idlePriority instead." ^2 ] idlePriority [ "Answer the priority of idle processes." ^1 ] lowestPriority [ "Answer the lowest valid priority" ^1 ] pause: aBoolean [ "Private - Pause for some time if aBoolean is false, or until a signal if it is true." ] idle [ "Private - Call the next idle task. Return whether GNU Smalltalk should pause until the next OS signal." | gcDone index | gcDone := ObjectMemory incrementalGCStep. idleTasks size <= 1 ifTrue: [ ^gcDone ]. index := idleTasks at: 1. (idleTasks at: index + 2) value. idleTasks at: 1 put: (index + 1) \\ (idleTasks size - 1). ^false ] idleAdd: aBlock [ "Register aBlock to be executed when things are idle" idleTasks add: aBlock ] startFinalizers [ "Private - Fire a low-priority process to finalize the objects" | local localFinalizerProcess | local := gcArray. gcArray := nil. localFinalizerProcess := [:array | array do: [:each | each mourn]] newProcessWith: {local}. localFinalizerProcess priority: Processor userSchedulingPriority. localFinalizerProcess name: 'finalization worker'. localFinalizerProcess resume ] initialize [ "Private - Start the finalization process." | finalizerProcess | idleTasks := OrderedCollection with: 0. gcSemaphore := Semaphore new. ObjectMemory addDependent: self. finalizerProcess := [[gcSemaphore wait. self startFinalizers] repeat] forkAt: Processor timingPriority. finalizerProcess name: 'finalization listener' ] update: aSymbol [ "If we left some work behind when the image was saved, do it now." aSymbol == #returnFromSnapshot ifFalse: [^self]. gcArray isNil ifFalse: [self startFinalizers] ] printOn: aStream [ "Store onto aStream a printed representation of the receiver" aStream nextPutAll: 'Processor' ] storeOn: aStream [ "Store onto aStream a Smalltalk expression which evaluates to the receiver" aStream nextPutAll: 'Processor' ] disableInterrupts [ "Disable interrupts caused by external events while the current process is executing. Note that interrupts are disabled on a per-process basis, and that calling #disableInterrupts twice requires calling #enableInterrupts twice as well to re-enable interrupts." ] enableInterrupts [ "Re-enable interrupts caused by external events while the current process is executing. By default, interrupts are enabled." ] isTimeoutProgrammed [ "Private - Answer whether there is a pending call to #signal:atMilliseconds:" ] signal: aSemaphore atNanosecondClockValue: ns [ "Private - signal 'aSemaphore' when the nanosecond clock reaches 'ns' nanoseconds." ^self primitiveFailed ] signal: aSemaphore onInterrupt: anIntegerSignalNumber [ "Signal 'aSemaphore' when the given C signal occurs." ^self primitiveFailed ] ] smalltalk-3.2.5/kernel/Semaphore.st0000644000175000017500000001403512123404352014200 00000000000000"====================================================================== | | Semaphore Method Definitions | | ======================================================================" "====================================================================== | | Copyright 1988,92,94,95,99,2000,2001,2002,2008,2009 | Free Software Foundation, Inc. | Written by Steve Byrne. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" LinkedList subclass: Semaphore [ | signals name | Semaphore class >> new [ "Answer a new semaphore" ^self basicNew initialize ] Semaphore class >> forMutualExclusion [ "Answer a new semaphore with a signal on it. These semaphores are a useful shortcut when you use semaphores as critical sections." ^(self new) signal; yourself ] critical: aBlock [ "Wait for the receiver to be free, execute aBlock and signal the receiver again. Return the result of evaluating aBlock." "Look out for race conditions!" | ownedSem c | ^[ "With a little help from the VM we can easily ascertain whether we did get a signal. It is still necessary to trap process termination however, because if we did simply `ownedSem := self wait' we might be terminated after the wait has ended, and yet before the variable is assigned. Pushing self and sending #wait is atomic thanks to superoperators." c := #(nil). ownedSem := [c := thisContext. self wait] on: ProcessBeingTerminated do: [:ex | ownedSem := c at: 1. ex pass]. ownedSem == self ifTrue: [aBlock value]] ensure: [ownedSem == self ifTrue: [self signal]] ] name [ "Answer a user-friendly name for the receiver" ^name ] name: aString [ "Answer a user-friendly name for the receiver" name := aString ] waitingProcesses [ "Answer an Array of processes currently waiting on the receiver." ^self asArray ] wouldBlock [ "Answer whether waiting on the receiver would suspend the current process." ^signals <= 0 ] printOn: aStream [ "Print a human-readable represention of the receiver on aStream." aStream nextPutAll: self class name; nextPutAll: '(%1: %2, %3 %2)' % {self name printString. self signals > 0. self signals abs} ] initialize [ signals := 0 ] signals [ "Answer the number of processes that can be accomodated or (if negative the number of waiting processes." "If <= 0 the value of signals does not have a relationship to the number of waiting processes (currently it never goes at all below zero). So - if 0 and 0 processes are waiting, the signal count is 0 - if 0 and k processes are waiting, the signal count is -k - if >0, no processes must be waiting and the signal count is signals" ^(signals max: 0) - self size ] notify [ "Resume one of the processes that were waiting on the semaphore if there were any. Do not leave a signal on the semaphore if no process is waiting." ^self primitiveFailed ] notifyAll [ "Resume all the processes that were waiting on the semaphore if there were any. Do not leave a signal on the semaphore if no process is waiting." ^self primitiveFailed ] signal [ "Signal the receiver, resuming a waiting process' if there is one" ^self primitiveFailed ] wait [ "Wait for the receiver to be signalled, suspending the executing process if it is not yet. Return nil if the wait was interrupted, the receiver otherwise." ^self primitiveFailed ] waitAfterSignalling: aSemaphore [ "Signal aSemaphore then, atomically, wait for the receiver to be signalled, suspending the executing process if it is not yet. This is needed to avoid race conditions when the #notify and #notifyAll are used before waiting on receiver: otherwise, if a process sends any of the two between the time aSemaphore is signaled and the time the process starts waiting on the receiver, the notification is lost." ^self primitiveFailed ] lock [ "Without putting the receiver to sleep, force processes that try to wait on the semaphore to block. Answer whether this was the case even before." ^self primitiveFailed ] ] smalltalk-3.2.5/kernel/StreamOps.st0000644000175000017500000003514012123404352014172 00000000000000"====================================================================== | | Adds collection-like operations to GNU Smalltalk streams | | ======================================================================" "====================================================================== | | Copyright 2001, 2002, 2007, 2008, 2009, 2013 Free Software Foundation, Inc. | Written by Paolo Bonzini. | | This file is part of GNU Smalltalk. | | GNU Smalltalk is free software; you can redistribute it and/or modify it | under the terms of the GNU General Public License as published by the Free | Software Foundation; either version 2, or (at your option) any later version. | | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS | FOR A PARTICULAR PURPOSE. See the GNU General Public License for more | details. | | You should have received a copy of the GNU General Public License along with | GNU Smalltalk; see the file COPYING. If not, write to the Free Software | Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. | ======================================================================" Namespace current: Kernel [ Stream subclass: ConcatenatedStream [ | streams startPos curPos last lastStart | ConcatenatedStream class >> new [ ^#() readStream ] ConcatenatedStream class >> with: stream1 [ ^(self basicNew) streams: {stream1}; yourself ] ConcatenatedStream class >> with: stream1 with: stream2 [ ^(self basicNew) streams: {stream1. stream2}; yourself ] ConcatenatedStream class >> withAll: array [ ^(self basicNew) streams: array; yourself ] , aStream [ ^(self copy) addStream: aStream; yourself ] postCopy [ streams := streams copy ] stream [ | s | "This is somewhat performance-sensitive, so avoid testing for an empty collection." [(s := streams at: 1) atEnd] whileTrue: [curPos > 0 ifTrue: [ lastStart := startPos. startPos := startPos + curPos. curPos := 0]. streams size = 1 ifTrue: [last := streams first. ^nil]. last := streams removeFirst]. ^s ] atEnd [ ^self stream isNil ] file [ self atEnd ifTrue: [^nil]. ^streams first file ] name [ self atEnd ifTrue: [^nil]. ^streams first name ] next [ | s | ^(s := self stream) isNil ifTrue: [self pastEnd] ifFalse: [curPos := curPos + 1. s next] ] pastEnd [ ^streams last pastEnd ] peekFor: aCharacter [ | s result | (s := self stream) isNil ifTrue: [self pastEnd. ^false]. result := s peekFor: aCharacter. result ifTrue: [curPos := curPos + 1]. ^result ] peek [ | s | (s := self stream) isNil ifTrue: [^self pastEnd]. ^s peek ] position [ self stream. ^startPos + curPos ] position: anInteger [ | s | (s := self stream) isNil ifTrue: [self pastEnd. ^self]. s position: anInteger - startPos. curPos := anInteger - startPos ] copyFrom: start to: end [ "needed to do the documentation" | adjust stream | stream := self stream. end + 1 = start ifTrue: [^'']. adjust := end <= startPos ifTrue: [stream := last. lastStart] ifFalse: [startPos]. ^stream copyFrom: (start - adjust max: 0) to: end - adjust ] species [ ^ self stream species. ] addStream: stream [ streams addLast: stream ] streams: arrayOfStreams [ streams := arrayOfStreams asOrderedCollection. startPos := curPos := 0 ] ] ] Namespace current: Kernel [ Stream subclass: FilteringStream [ | stream block result next atEnd | FilteringStream class >> on: aStream select: selectBlock [ ^self new initStream: aStream block: selectBlock result: true ] FilteringStream class >> on: aStream reject: selectBlock [ ^self new initStream: aStream block: selectBlock result: false ] initStream: aStream block: selectBlock result: aBoolean [ stream := aStream. block := selectBlock. result := aBoolean. atEnd := false. self lookahead ] atEnd [ ^atEnd ] next [ | result | atEnd ifTrue: [self pastEnd. ^nil]. result := next. self lookahead. ^result ] pastEnd [ ^stream pastEnd ] peek [ atEnd ifTrue: [^nil]. ^next ] peekFor: aCharacter [ atEnd ifTrue: [self pastEnd. ^false]. next == aCharacter ifTrue: [self lookahead. ^true]. ^false ] species [ ^stream species ] lookahead [ [stream atEnd ifTrue: [atEnd := true. ^self]. next := stream next. (block value: next) == result] whileFalse ] ] ] Namespace current: Kernel [ Stream subclass: CollectingStream [ | stream block | CollectingStream class >> on: aStream collect: collectBlock [ ^self new initStream: aStream block: collectBlock ] initStream: aStream block: collectBlock [ stream := aStream. block := collectBlock ] atEnd [ ^stream atEnd ] next [ stream atEnd ifTrue: [^stream pastEnd]. ^block value: stream next ] pastEnd [ ^stream pastEnd ] peek [ stream atEnd ifTrue: [^nil]. ^block value: stream peek ] peekFor: anObject [ | result | stream atEnd ifTrue: [stream pastEnd. ^false]. result := (block value: stream peek) = anObject result ifTrue: [stream next]. ^result ] position [ ^stream position ] position: anInteger [ stream position: anInteger ] species [ ^stream species ] ] ] Namespace current: Kernel [ Stream subclass: PeekableStream [ | stream haveLookahead lookahead | PeekableStream class >> on: aStream [ ^self new initStream: aStream ] species [ ^stream species ] file [ ^stream file ] name [ ^stream name ] next [ | char | ^haveLookahead ifTrue: [haveLookahead := false. char := lookahead. lookahead := nil. char] ifFalse: [stream next] ] atEnd [ "Answer whether the input stream has no more tokens." ^haveLookahead not and: [stream atEnd] ] pastEnd [ ^stream pastEnd ] peek [ "Returns the next element of the stream without moving the pointer. Returns nil when at end of stream." haveLookahead ifFalse: [stream atEnd ifTrue: [^nil]. haveLookahead := true. lookahead := stream next]. ^lookahead ] peekFor: anObject [ "Answer a new whitespace-separated token from the input stream" | result | haveLookahead ifFalse: [stream atEnd ifTrue: [self pastEnd. ^false]. lookahead := stream next]. result := lookahead = anObject. result ifTrue: [lookahead := nil]. haveLookahead := result not. ^result ] initStream: aStream [ stream := aStream. haveLookahead := false ] ] ] Namespace current: Kernel [ Stream subclass: LineStream [ | charStream | LineStream class >> on: aStream [ "Answer a LineStream working on aStream" ^self new initStream: aStream ] file [ ^charStream file ] name [ ^charStream name ] next [ ^charStream nextLine ] atEnd [ ^charStream atEnd ] pastEnd [ ^charStream pastEnd ] initStream: aStream [ charStream := aStream ] ] ] Namespace current: Kernel [ Stream subclass: OneOfEachStream [ | streams delta | OneOfEachStream class >> new [ ^#() readStream ] OneOfEachStream class >> with: stream1 [ ^(self basicNew) streams: {stream1} ] OneOfEachStream class >> with: stream1 with: stream2 [ ^(self basicNew) streams: {stream1. stream2} ] OneOfEachStream class >> with: stream1 with: stream2 with: stream3 [ ^(self basicNew) streams: {stream1. stream2. stream3} ] OneOfEachStream class >> with: stream1 with: stream2 with: stream3 with: stream4 [ ^(self basicNew) streams: {stream1. stream2. stream3. stream4} ] OneOfEachStream class >> withAll: array [ ^(self basicNew) streams: array ] atEnd [ ^streams anySatisfy: [ :each | each atEnd] ] do: aBlock [ [ aBlock value: (streams collect: [:each | each atEnd ifTrue: [ ^self ]. each next ]) ] repeat ] next [ ^streams collect: [:each | each atEnd ifTrue: [ ^self pastEnd ] ifFalse: [ each next ]] ] pastEnd [ ^streams first pastEnd ] peekFor: anObject [ ^self peek = anObject ifTrue: [ streams do: [ :each | streams next ] ]; yourself ] peek [ ^streams collect: [:each | each atEnd ifTrue: [ ^self pastEnd ] ifFalse: [ each peek ]] ] position [ ^streams first position - delta ] position: anInteger [ ^self skip: anInteger - self position ] reset [ self position: 0 ] skip: anInteger [ streams do: [ :each | each skip: anInteger ] ] streams: arrayOfStreams [ streams := arrayOfStreams. delta := arrayOfStreams first position. ] ] ] Stream extend [ , anIterable [ "Answer a new stream that concatenates the data in the receiver with the data in aStream. Both the receiver and aStream should be readable." ^Kernel.ConcatenatedStream with: self with: anIterable readStream ] lines [ "Answer a new stream that answers lines from the receiver." ^Kernel.LineStream on: self ] peek [ "Returns the next element of the stream without moving the pointer. Returns nil when at end of stream. Lookahead is implemented automatically for streams that are not positionable but can be copied." | copy | copy := self copy. copy == self ifTrue: [^self shouldNotImplement]. self become: (Kernel.PeekableStream on: copy). ^self peek ] skipSeparators [ "Advance the receiver until we find a character that is not a separator. Answer false if we reach the end of the stream, else answer true; in this case, sending #next will return the first non-separator character (possibly the same to which the stream pointed before #skipSeparators was sent)." | ch | [(ch := self peek) isNil ifTrue: [^false]. ch isSeparator] whileTrue: [self next]. ^true ] peekFor: aCharacter [ "Returns true and gobbles the next element from the stream of it is equal to anObject, returns false and doesn't gobble the next element if the next element is not equal to anObject. Lookahead is implemented automatically for streams that are not positionable but can be copied." | copy | copy := self copy. copy == self ifTrue: [^self shouldNotImplement]. self become: (Kernel.PeekableStream on: copy). ^self peekFor: aCharacter ] select: aBlock [ "Answer a new stream that only returns those objects for which aBlock returns true. Note that the returned stream will not be positionable." "Example: Sieve of Erathostenes. GNU Smalltalk does not detect that i escapes, so we need to avoid optimizations of #to:do:. s := (2 to: 100) readStream. (2 to: 10) do: [ :i | s := s reject: [ :n | n > i and: [ n \\ i = 0 ] ] ]. s contents printNl" ^Kernel.FilteringStream on: self select: aBlock ] reject: aBlock [ "Answer a new stream that only returns those objects for which aBlock returns false. Note that the returned stream will not be positionable." ^Kernel.FilteringStream on: self reject: aBlock ] collect: aBlock [ "Answer a new stream that will pass the returned objects through aBlock, and return whatever object is returned by aBlock instead. Note that when peeking in the returned stream, the block will be invoked multiple times, with possibly surprising results." ^Kernel.CollectingStream on: self collect: aBlock ] with: aStream [ "Return a new Stream whose elements are 2-element Arrays, including one element from the receiver and one from aStream." ^Kernel.OneOfEachStream with: self with: aStream ] with: stream1 with: stream2 [ "Return a new Stream whose elements are 3-element Arrays, including one element from the receiver and one from each argument." ^Kernel.OneOfEachStream with: self with: stream1 with: stream2 ] with: stream1 with: stream2 with: stream3 [ "Return a new Stream whose elements are 3-element Arrays, including one element from the receiver and one from each argument." ^Kernel.OneOfEachStream with: self with: stream1 with: stream2 with: stream3 ] ] smalltalk-3.2.5/kernel/stamp-classes0000644000175000017500000000000012123404352014372 00000000000000smalltalk-3.2.5/kernel/BindingDict.st0000644000175000017500000002047212130343734014441 00000000000000"====================================================================== | | BindingDictionary Method Definitions | | ======================================================================" "====================================================================== | | Copyright 1999, 2000, 2001, 2002, 2003, 2008 Free Software Foundation, Inc. | Written by Paolo Bonzini. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" Dictionary subclass: BindingDictionary [ | environment | = arg [ "Answer whether the receiver is equal to arg. The equality test is by default the same as that for equal objects. = must not fail; answer false if the receiver cannot be compared to arg" ] hash [ "Answer an hash value for the receiver. This is the same as the object's #identityHash." ] copy [ ^self ] copyEmpty: newSize [ "Answer an empty copy of the receiver whose size is newSize" | realSize | realSize := 8 max: (newSize * 4 + 2) // 3. (realSize bitAnd: realSize - 1) = 0 ifFalse: [realSize := 1 bitShift: realSize highBit]. ^(self class primNew: realSize) initialize: realSize; environment: self environment; yourself ] copyEmptyForCollect [ "Answer an empty copy of the receiver which is filled in to compute the result of #collect:" ^self species new: self capacity ] copyEmptyForCollect: size [ "Answer an empty copy of the receiver which is filled in to compute the result of #collect:" ^self species new: size ] shallowCopy [ ^self ] deepCopy [ ^self ] environment [ "Answer the environment to which the receiver is connected. This can be the class for a dictionary that holds class variables, or the super-namespace. In general it is used to compute the receiver's name." ^environment ] environment: anObject [ "Set the environment to which the receiver is connected. This can be the class for a dictionary that holds class variables, or the super-namespace. In general it is used to compute the receiver's name." environment := anObject ] name [ "Answer the receiver's name, which by default is the same as the name of the receiver's environment." ^self environment name ] nameIn: aNamespace [ "Answer the receiver's name when referred to from aNamespace; by default the computation is deferred to the receiver's environment." ^self environment nameIn: aNamespace ] define: aSymbol [ "Define aSymbol as equal to nil inside the receiver. Fail if such a variable already exists (use #at:put: if you don't want to fail)" super at: aSymbol ifAbsent: [self at: aSymbol put: nil. ^self]. SystemExceptions.AlreadyDefined signalOn: aSymbol ] import: aSymbol from: aNamespace [ "Add to the receiver the symbol aSymbol, associated to the same value as in aNamespace. Fail if aNamespace does not contain the given key." self add: (aNamespace associationAt: aSymbol) copy ] doesNotUnderstand: aMessage [ "Try to map unary selectors to read accesses to the Namespace, and one-argument keyword selectors to write accesses. Note that: a) this works only if the selector has an uppercase first letter; and b) `aNamespace Variable: value' is the same as `aNamespace set: #Variable to: value', not the same as `aNamespace at: #Variable put: value' --- the latter always refers to the current namespace, while the former won't define a new variable, instead searching in superspaces (and raising an error if the variable cannot be found)." | key | (aMessage selector at: 1) isUppercase ifFalse: [^super doesNotUnderstand: aMessage]. aMessage arguments size = 0 ifTrue: [^self at: aMessage selector ifAbsent: [super doesNotUnderstand: aMessage]]. aMessage arguments size > 1 ifTrue: [^super doesNotUnderstand: aMessage]. key := (aMessage selector copyWithout: $:) asSymbol. ^self set: key to: aMessage argument ifAbsent: [super doesNotUnderstand: aMessage] ] printOn: aStream in: aNamespace [ "Print the receiver's name when referred to from aNamespace; by default the computation is deferred to the receiver's environment." self environment printOn: aStream in: aNamespace ] at: key put: value [ "Store value as associated to the given key. If any, recycle Associations temporarily stored by the compiler inside the `Undeclared' dictionary." | index assoc newAssoc | index := self findIndex: key. assoc := self primAt: index. assoc isNil ifFalse: [assoc value: value. ^value]. newAssoc := VariableBinding key: key value: value environment: self. self incrementTally ifTrue: [index := self findIndex: key]. assoc := Undeclared associationAt: key ifAbsent: [nil]. assoc isNil ifTrue: [assoc := newAssoc] ifFalse: [Undeclared remove: assoc ifAbsent: []. assoc become: newAssoc]. self primAt: index put: assoc. ^value ] hashFor: anObject [ "Return an hash value for the item, anObject" ^anObject key identityHash ] findIndex: anObject [ "Tries to see if anObject exists as an indexed variable. As soon as nil or anObject is found, the index of that slot is answered" | index size element | self beConsistent. "Sorry for the lack of readability, but I want speed... :-)" index := (anObject identityHash scramble bitAnd: (size := self primSize) - 1) + 1. [((element := self primAt: index) isNil or: [element key == anObject]) ifTrue: [^index]. index == size ifTrue: [index := 1] ifFalse: [index := index + 1]] repeat ] primAt: index put: anObject [ "Store anObject in the dictionary. If any, recycle Associations temporarily stored by the compiler inside the `Undeclared' dictionary." | assoc | assoc := anObject. assoc isNil ifFalse: ["Need static typing to avoid crashes..." ((assoc isKindOf: VariableBinding) and: [assoc environment == self]) ifFalse: [assoc := VariableBinding key: assoc key value: assoc value environment: self]. assoc makeUntrusted: environment isUntrusted]. ^super primAt: index put: assoc ] addWhileGrowing: anAssociation [ | save | save := anAssociation environment. anAssociation environment: self. super addWhileGrowing: anAssociation. anAssociation environment: save. ^anAssociation ] keysClass [ ^IdentitySet ] species [ ^IdentityDictionary ] ] smalltalk-3.2.5/kernel/FloatQ.st0000644000175000017500000001723212123404352013445 00000000000000"====================================================================== | | FloatQ Method Definitions | | ======================================================================" "====================================================================== | | Copyright 2002, 2009 Free Software Foundation, Inc. | Written by Paolo Bonzini. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" Float subclass: FloatQ [ FloatQ class >> coerce: aNumber [ "Answer aNumber converted to a FloatQ" ^aNumber asFloatQ ] FloatQ class >> signByte [ "Answer the byte of the receiver that contains the sign bit" ^##(| n k | n := -2.0q. 1 to: n size do: [:i | (n at: i) >= 128 ifTrue: [k := i]]. k) ] FloatQ class >> e [ "Returns the value of e. Hope is that it is precise enough" ^16r2.B7E151628AED2A6ABF7158809CF4F3C75Eq ] FloatQ class >> precision [ "Answer the number of bits in the mantissa. 1 + (2^-precision) = 1" ^CLongDoubleBinaryDigits ] FloatQ class >> fminNormalized [ "Return the smallest normalized FloatQ that is > 0" ^CLongDoubleMin ] FloatQ class >> fmax [ "Return the largest normalized FloatQ that is not infinite." ^CLongDoubleMax ] FloatQ class >> emax [ "Return the maximum allowable exponent for a FloatQ that is finite." ^CLongDoubleMaxExp ] FloatQ class >> emin [ "Return the maximum allowable exponent for a FloatQ that is finite." ^CLongDoubleMinExp ] FloatQ class >> decimalDigits [ "Return the number of decimal digits of precision for a FloatQ. Technically, if P is the precision for the representation, then the decimal precision Q is the maximum number of decimal digits such that any floating point number with Q base 10 digits can be rounded to a floating point number with P base 2 digits and back again, without change to the Q decimal digits." ^CLongDoubleDigits ] FloatQ class >> log10Base2 [ "Returns the value of log2 10. Hope is that it is precise enough" ^16r3.5269E12F346E2BF924AFDBFD36BF6D3362q ] FloatQ class >> ln10 [ "Returns the value of ln 10. Hope is that it is precise enough" ^16r2.4D763776AAA2B05BA95B58AE0B4C28A38Aq ] FloatQ class >> infinity [ "Return a FloatQ that represents positive infinity." ^CLongDoublePInf ] FloatQ class >> negativeInfinity [ "Return a FloatQ that represents negative infinity." ^CLongDoubleNInf ] FloatQ class >> nan [ "Return a FloatQ that represents a mathematically indeterminate value (e.g. Inf - Inf, Inf / Inf)." ^CLongDoubleNaN ] FloatQ class >> pi [ "Returns the value of pi. Hope is that it is precise enough" ^16r3.243F6A8885A308D313198A2E0370734483q ] zero [ "Coerce 0 to the receiver's class" ^0.0q ] half [ "Coerce 0.5 to the receiver's class" ^0.5q ] unity [ "Coerce 1 to the receiver's class" ^1.0q ] coerce: aNumber [ "Coerce aNumber to the receiver's class" ^aNumber asFloatQ ] generality [ "Answer the receiver's generality" ^420 ] asFloatQ [ "Just defined for completeness. Return the receiver." ^self ] ten [ "Private - Return 10, converted to the receiver's class." ^10.0q ] exponentLetter [ "Private - Return the letter to be printed just before the exponent" ^$q ] + arg [ "Sum the receiver and arg and answer another Number" ^self retrySumCoercing: arg ] - arg [ "Subtract arg from the receiver and answer another Number" ^self retryDifferenceCoercing: arg ] < arg [ "Answer whether the receiver is less than arg" ^self retryRelationalOp: #< coercing: arg ] > arg [ "Answer whether the receiver is greater than arg" ^self retryRelationalOp: #> coercing: arg ] <= arg [ "Answer whether the receiver is less than or equal to arg" ^self retryRelationalOp: #<= coercing: arg ] >= arg [ "Answer whether the receiver is greater than or equal to arg" ^self retryRelationalOp: #>= coercing: arg ] = arg [ "Answer whether the receiver is equal to arg" ^self retryEqualityCoercing: arg ] ~= arg [ "Answer whether the receiver is not equal to arg" ^self retryInequalityCoercing: arg ] * arg [ "Multiply the receiver and arg and answer another Number" ^self retryMultiplicationCoercing: arg ] / arg [ "Divide the receiver by arg and answer another FloatQ" ^self generality = arg generality ifTrue: [self zeroDivide] ifFalse: [self retryDivisionCoercing: arg] ] asFloatD [ "Answer the receiver converted to a FloatD" self primitiveFailed ] asFloatE [ "Answer the receiver converted to a FloatE" self primitiveFailed ] truncated [ "Truncate the receiver towards zero and answer the result" ^super truncated ] fractionPart [ "Answer the fractional part of the receiver" self checkCoercion. ^self primitiveFailed ] exponent [ "Answer the exponent of the receiver in mantissa*2^exponent representation ( |mantissa|<=1 )" ] timesTwoPower: arg [ "Answer the receiver multiplied by 2^arg" ] ] smalltalk-3.2.5/kernel/ObjDumper.st0000644000175000017500000010327712130343734014157 00000000000000"====================================================================== | | ObjectDumper Method Definitions | | ======================================================================" "====================================================================== | | Copyright 1999, 2000, 2001, 2002, 2003, 2006, 2008, 2009 | Free Software Foundation, Inc. | Written by Paolo Bonzini. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" Stream subclass: ObjectDumper [ | toObjects fromObjects stream | SpecialCaseDump := nil. SpecialCaseLoad := nil. Proxies := nil. ObjectDumper class >> example [ "This is a real torture test: it outputs recursive objects, identical objects multiple times, classes, metaclasses, integers, characters and proxies (which is also a test of more complex objects)!" | file test dumper method | Transcript nextPutAll: 'Must print true without errors.'; nl. file := FileStream open: 'dumptest' mode: FileStream write. test := Array new: 1. test at: 1 put: test. method := thisContext method. (ObjectDumper on: file) dump: 'asdf'; dump: #('asdf' 1 2 $a); dump: Array; dump: 'asdf'; dump: Array class; dump: test; dump: Processor; dump: Processor; dump: method; dump: method. "String" "Array" "Class" "String (must be identical to the first)" "Metaclass" "Circular reference" "SingletonProxy" "SingletonProxy" "PluggableProxy" "PluggableProxy" file close. file := FileStream open: 'dumptest' mode: FileStream read. dumper := ObjectDumper on: file. ((test := dumper load) = 'asdf') printNl. (dumper load = #('asdf' 1 2 $a)) printNl. (dumper load == Array) printNl. (dumper load == test) printNl. (dumper load == Array class) printNl. test := dumper load. (test == (test at: 1)) printNl. (dumper load == Processor) printNl. (dumper load == Processor) printNl. (dumper load == method) printNl. (dumper load == method) printNl. file close ] ObjectDumper class >> hasProxyFor: aClass [ "Answer whether a proxy class has been registered for instances of aClass." Proxies keysDo: [:any | (aClass inheritsFrom: any) ifTrue: [^true]. aClass == any ifTrue: [^true]]. ^false ] ObjectDumper class >> disableProxyFor: aClass [ "Disable proxies for instances of aClass and its descendants" self registerProxyClass: NullProxy for: aClass ] ObjectDumper class >> registerProxyClass: aProxyClass for: aClass [ "Register the proxy class aProxyClass - descendent of DumperProxy - to be used for instances of aClass and its descendants" (aProxyClass acceptUsageForClass: aClass) ifFalse: [self error: 'registration request denied']. Proxies at: aClass put: aProxyClass ] ObjectDumper class >> proxyFor: anObject [ "Answer a valid proxy for an object, or the object itself if none could be found" Proxies keysAndValuesDo: [:key :value | (anObject isKindOf: key) ifTrue: [^value on: anObject]]. ^anObject ] ObjectDumper class >> proxyClassFor: anObject [ "Answer the class of a valid proxy for an object, or nil if none could be found" Proxies keysAndValuesDo: [:key :value | (anObject isKindOf: key) ifTrue: [^value]]. ^nil ] ObjectDumper class >> specialCaseIf: aBlock dump: dumpBlock load: loadBlock [ "Private - This method establishes a condition on which a particular method must be used to save an object. An application should not use this method, since it might cause failure to load file that set the special-case blocks differently; instead, you should use ObjectDumper's higher level proxy feature, i.e. its #registerProxyClass:for: method - which builds on the low-level feature enabled by this method but without its inherent problems." SpecialCaseDump addLast: aBlock -> dumpBlock. SpecialCaseLoad addLast: loadBlock ] ObjectDumper class >> initialize [ "Initialize the ObjectDumper class" Proxies := IdentityDictionary new. SpecialCaseDump := OrderedCollection new. SpecialCaseLoad := OrderedCollection new. "We can only use #isNil, #==, #class here" self specialCaseIf: [:object | object == nil] dump: [:client :object | ] load: [:client | nil]; specialCaseIf: [:object | object == true] dump: [:client :object | ] load: [:client | true]; specialCaseIf: [:object | object == false] dump: [:client :object | ] load: [:client | false]; specialCaseIf: [:object | object class == SmallInteger] dump: [:client :object | client nextPutLong: object] load: [:client | client nextLong]; specialCaseIf: [:object | object class == Character] dump: [:client :object | client stream nextPut: object] load: [:client | client stream next]; specialCaseIf: [:object | object class class == Metaclass] dump: [:client :object | client storeGlobal: object] load: [:client | client loadGlobal]; specialCaseIf: [:object | object class == Metaclass] dump: [:client :object | client storeGlobal: object asClass] load: [:client | client loadGlobal class]; specialCaseIf: [:object | object == Smalltalk] dump: [:client :object | ] load: [:client | Smalltalk]; specialCaseIf: [:object | object class == Namespace] dump: [:client :object | client storeGlobal: object] load: [:client | client loadGlobal]; specialCaseIf: [:object | object class == RootNamespace] dump: [:client :object | client storeGlobal: object] load: [:client | client loadGlobal]; specialCaseIf: [:object | object class == Symbol] dump: [:client :object | client stream nextPutAll: object. client nextPutByte: 0] load: [:client | client nextAsciiz asSymbol]; specialCaseIf: [:object | self hasProxyFor: object class] dump: [:client :object | | class | (client lookup: object) ifFalse: [client storeGlobal: (class := self proxyClassFor: object). (class on: object) dumpTo: client. client register: object]] load: [:client | "Special-case metaclasses and other objects" | index | index := client nextLong. index = 0 ifTrue: [client register: (client loadGlobal loadFrom: client)] ifFalse: [client lookupIndex: index]]; specialCaseIf: [:object | object class == UnicodeCharacter] dump: [:client :object | client nextPutLong: object codePoint] load: [:client | client nextLong asCharacter] ] ObjectDumper class >> on: aFileStream [ "Answer an ObjectDumper working on aFileStream." ^self basicNew initializeStream: aFileStream ] ObjectDumper class >> new [ self shouldNotImplement ] ObjectDumper class >> dump: anObject to: aFileStream [ "Dump anObject to aFileStream. Answer anObject" ^(self on: aFileStream) dump: anObject ] ObjectDumper class >> loadFrom: aFileStream [ "Load an object from aFileStream and answer it" ^(self on: aFileStream) load ] atEnd [ "Answer whether the underlying stream is at EOF" ^stream atEnd ] next [ "Load an object from the underlying stream" ^self load ] nextPut: anObject [ "Store an object on the underlying stream" self dump: anObject ] dump: anObject [ "Dump anObject on the stream associated with the receiver. Answer anObject" (self lookup: anObject) ifTrue: [^anObject]. (self specialCaseDump: anObject) ifFalse: [anObject preStore. [self primDump: anObject] ensure: [anObject postStore]] ] load [ "Load an object from the stream associated with the receiver and answer it" "Special-case metaclasses and other objects" | index class | stream atEnd ifTrue: [^self pastEnd]. index := self nextLong. index < 0 ifTrue: [^self specialCaseLoad: index]. index > 0 ifTrue: [^self lookupIndex: index]. class := self loadClass. ^self primLoad: class ] flush [ "`Forget' any information on previously stored objects." toObjects := OrderedCollection new. fromObjects := IdentityDictionary new ] stream [ "Answer the ByteStream to which the ObjectDumper will write and from which it will read." ^stream ] stream: aByteStream [ "Set the ByteStream to which the ObjectDumper will write and from which it will read." stream := aByteStream ] lookup: anObject [ | index | index := fromObjects at: anObject ifAbsent: [0]. self nextPutLong: index. ^index > 0 ] lookupIndex: index [ "Private - If index is a valid index into the toObjects map, evaluate return the object associated to it. Else, fail." ^toObjects at: index ] register: anObject [ "Private - Register the anObject in the fromObjects and toObjects maps. Assumes that anObject is absent in these maps. Answer anObject" "(fromObject includesKey: anObject) ifTrue: [ ^self error: 'Huh?!? Assertion failed' ]." toObjects addLast: anObject. fromObjects at: anObject put: toObjects size. ^anObject ] dumpContentsOf: anObject [ "Dump anObject on the stream associated with the receiver. Answer anObject" | index | (self lookup: anObject) ifTrue: [^anObject]. anObject preStore. [self primDump: anObject] ensure: [anObject postStore]. ^self register: anObject ] initializeStream: aStream [ "Private - Initialize the receiver's instance variables" stream := aStream. self flush. ^self ] isClass: loadedClass [ "Private - Answer whether loadedClass is really a class; only use optimized selectors to avoid mess with objects that do not inherit from Object." ^loadedClass class class == Metaclass ] loadClass [ "Private - Load the next object's class from stream" | isMeta loadedClass | isMeta := self nextByte = 0. loadedClass := self loadGlobal. (self isClass: loadedClass) ifFalse: [^self error: 'Bad class']. ^isMeta ifTrue: [loadedClass class] ifFalse: [loadedClass] ] loadGlobal [ "Private - Load a global object from the stream" | object space index | index := self nextLong. index > 0 ifTrue: [^self lookupIndex: index]. space := self load. space isNil ifTrue: [space := Smalltalk]. object := space at: self nextAsciiz asGlobalKey ifAbsent: [^self error: 'Unknown global referenced']. ^self register: object ] load: anObject through: aBlock [ "Private - Fill anObject's indexed instance variables from the stream. To get a variable, evaluate aBlock. Answer anObject" 1 to: anObject basicSize do: [:i | anObject basicAt: i put: aBlock value]. ^anObject postLoad; yourself ] loadFixedPart: class [ "Private - Load the fixed instance variables of a new instance of class" | object | object := class isVariable ifTrue: [class basicNew: self nextLong] ifFalse: [class basicNew]. self register: object. 1 to: class instSize do: [:i | object instVarAt: i put: self load]. ^object ] nextAsciiz [ "Private - Get a Null-terminated string from stream and answer it" | ch answer | answer := WriteStream on: (String new: 30). "Hopefully large enough" [ch := stream next. ch asciiValue = 0] whileFalse: [answer nextPut: ch]. ^answer contents ] primDump: anObject [ "Private - Basic code to dump anObject on the stream associated with the receiver, without using proxies and the like." | class shape | self storeClass: (class := anObject class). self register: anObject. class isVariable ifTrue: [self nextPutLong: anObject basicSize]. 1 to: class instSize do: [:i | self dump: (anObject instVarAt: i)]. class isVariable ifFalse: [^self]. class isPointers ifTrue: [^self store: anObject through: [:obj | self dump: obj]]. shape := class shape. shape == #character ifTrue: [^self store: anObject through: [:char | stream nextPut: char]]. (shape == #byte or: [shape == #int8]) ifTrue: [^self store: anObject through: [:byte | self nextPutByte: byte]]. (shape == #short or: [shape == #ushort]) ifTrue: [^self store: anObject through: [:short | self nextPutShort: short]]. (shape == #int or: [shape == #int]) ifTrue: [^self store: anObject through: [:int | self nextPutLong: int]]. (shape == #int64 or: [shape == #uint64]) ifTrue: [^self store: anObject through: [:int64 | self nextPutInt64: int64]]. shape == #utf32 ifTrue: [^self store: anObject through: [:char | self nextPutLong: char codePoint]]. shape == #float ifTrue: [^self store: anObject through: [:float | self nextPutFloat: float]]. shape == #double ifTrue: [^self store: anObject through: [:double | self nextPutFloat: double]]. self notYetImplemented ] loadFromVersion: version fixedSize: instSize index: index [ "Private - Basic code to load an object from a stream associated with the receiver, calling the class' #convertFromVersion:withFixedVariables:instanceVariables:for: method. version will be the first parameter to that method, while instSize will be the size of the second parameter. The object returned by that method is registered and returned." | object class realSize size fixed indexed placeholder shape | index > 0 ifTrue: [^self lookupIndex: index]. class := self loadClass. version == class binaryRepresentationVersion ifTrue: [ ^ self primLoad: class ]. self register: (placeholder := Object new). class isVariable ifTrue: [size := self nextUlong]. realSize := instSize isNil ifTrue: [class nonVersionedInstSize] ifFalse: [instSize]. fixed := (1 to: realSize) collect: [:i | self load]. class isVariable ifTrue: [class isPointers ifTrue: [indexed := (1 to: size) collect: [:i | self load]]. shape := class shape. shape == #character ifTrue: [indexed := (1 to: size) collect: [:i | Character value: self nextByte]]. (shape == #byte and: [indexed isNil]) ifTrue: [indexed := (1 to: size) collect: [:i | self nextByte]]. shape == #int8 ifTrue: [indexed := (1 to: size) collect: [:i | self nextSignByte]]. shape == #short ifTrue: [indexed := (1 to: size) collect: [:i | self nextShort]]. shape == #ushort ifTrue: [indexed := (1 to: size) collect: [:i | self nextUshort]]. shape == #int ifTrue: [indexed := (1 to: size) collect: [:i | self nextLong]]. shape == #uint ifTrue: [indexed := (1 to: size) collect: [:i | self nextUlong]]. shape == #int64 ifTrue: [indexed := (1 to: size) collect: [:i | self nextInt64]]. shape == #uint64 ifTrue: [indexed := (1 to: size) collect: [:i | self nextUint64]]. shape == #utf32 ifTrue: [indexed := (1 to: size) collect: [:i | self nextLong asCharacter]]. shape == #float ifTrue: [indexed := (1 to: size) collect: [:i | self nextFloat]]. shape == #double ifTrue: [indexed := (1 to: size) collect: [:i | self nextDouble]]. indexed isNil ifTrue: [self shouldNotImplement]]. placeholder become: (class convertFromVersion: version withFixedVariables: fixed indexedVariables: indexed for: self). ^placeholder ] primLoad: class [ "Private - Basic code to load an object from the stream associated with the receiver, assuming it doesn't use proxies and the like. The class of the loaded object is in index" | object shape | class isMetaclass ifTrue: [^class instanceClass]. object := self loadFixedPart: class. class isVariable ifFalse: [^object postLoad; yourself]. class isPointers ifTrue: [^self load: object through: [self load]]. shape := class shape. shape == #character ifTrue: [^self load: object through: [Character value: self nextByte]]. shape == #byte ifTrue: [^self load: object through: [self nextByte]]. shape == #int8 ifTrue: [^self load: object through: [self nextSignByte]]. shape == #short ifTrue: [^self load: object through: [self nextShort]]. shape == #ushort ifTrue: [^self load: object through: [self nextUshort]]. shape == #int ifTrue: [^self load: object through: [self nextLong]]. shape == #uint ifTrue: [^self load: object through: [self nextUlong]]. shape == #int64 ifTrue: [^self load: object through: [self nextInt64]]. shape == #uint64 ifTrue: [^self load: object through: [self nextUint64]]. shape == #utf32 ifTrue: [^self load: object through: [self nextLong asCharacter]]. shape == #float ifTrue: [^self load: object through: [self nextFloat]]. shape == #double ifTrue: [^self load: object through: [self nextDouble]]. self shouldNotImplement ] specialCaseDump: anObject [ "Private - Store special-cased objects. These include booleans, integers, nils, characters, classes and Processor. Answer true if object belongs to one of these categories, else do nothing and answer false" SpecialCaseDump keysAndValuesDo: [:index :each | (each key value: anObject) ifTrue: [stream skip: -4. self nextPutLong: index negated. each value value: self value: anObject. self register: anObject. ^true]]. ^false ] specialCaseLoad: index [ "Private - The first 4 bytes in the file were less than 0. Load the remaining info about the object and answer it." | object | index > SpecialCaseLoad size ifTrue: [^self error: 'error in file']. object := (SpecialCaseLoad at: index negated) value: self. ^self register: object ] storeClass: aClass [ "Private - Store the aClass class in stream. The format is: - for a metaclass, a 0 followed by the asciiz name of its instance - for a class, a 1 followed by its asciiz name" "We don't register metaclasses; instead we register their instance (the class) and use a byte to distinguish between the two cases." aClass isMetaclass ifTrue: [self nextPutByte: 0] ifFalse: [self nextPutByte: 1]. self storeGlobal: aClass asClass ] storeGlobal: anObject [ | namespace | (self lookup: anObject) ifTrue: [^anObject]. (anObject respondsTo: #environment) ifTrue: [namespace := anObject environment] ifFalse: [(anObject respondsTo: #superspace) ifTrue: [namespace := anObject superspace] ifFalse: [namespace := nil "read as `Smalltalk' upon load."]]. self dump: namespace; register: anObject. stream nextPutAll: anObject name. self nextPutByte: 0 ] store: anObject through: aBlock [ "Private - Store anObject's indexed instance variables into the stream. To store a variable, pass its value to aBlock." 1 to: anObject basicSize do: [:i | aBlock value: (anObject basicAt: i)]. ^anObject ] nextByte [ "Return the next byte in the byte array" ^stream next asInteger ] nextByteArray: numBytes [ "Return the next numBytes bytes in the byte array" ^(stream next: numBytes) asByteArray ] nextSignedByte [ "Return the next byte in the byte array, interpreted as a 8 bit signed number" ^self nextBytes: 1 signed: true ] nextDouble [ "Return the next 64-bit float in the byte array" ^(FloatD new: 8) at: 1 put: self nextByte; at: 2 put: self nextByte; at: 3 put: self nextByte; at: 4 put: self nextByte; at: 5 put: self nextByte; at: 6 put: self nextByte; at: 7 put: self nextByte; at: 8 put: self nextByte ] nextFloat [ "Return the next 32-bit float in the byte array" ^(FloatE new: 4) at: 1 put: self nextByte; at: 2 put: self nextByte; at: 3 put: self nextByte; at: 4 put: self nextByte ] nextUint64 [ "Return the next 8 bytes in the byte array, interpreted as a 64 bit unsigned int" ^self nextBytes: 8 signed: false ] nextLongLong [ "Return the next 8 bytes in the byte array, interpreted as a 64 bit signed int" ^self nextBytes: 8 signed: true ] nextUlong [ "Return the next 4 bytes in the byte array, interpreted as a 32 bit unsigned int" ^self nextBytes: 4 signed: false ] nextLong [ "Return the next 4 bytes in the byte array, interpreted as a 32 bit signed int" ^self nextBytes: 4 signed: true ] nextUshort [ "Return the next 2 bytes in the byte array, interpreted as a 16 bit unsigned int" ^self nextBytes: 2 signed: false ] nextShort [ "Return the next 2 bytes in the byte array, interpreted as a 16 bit signed int" ^self nextBytes: 2 signed: true ] nextPutDouble: aDouble [ "Store aDouble as a 64-bit float in the byte array" | d | d := aDouble asFloatD. self nextPutByte: (d at: 1). self nextPutByte: (d at: 2). self nextPutByte: (d at: 3). self nextPutByte: (d at: 4). self nextPutByte: (d at: 5). self nextPutByte: (d at: 6). self nextPutByte: (d at: 7). self nextPutByte: (d at: 8) ] nextPutFloat: aFloat [ "Return the next 32-bit float in the byte array" | f | f := aFloat asFloatE. self nextPutByte: (f at: 1). self nextPutByte: (f at: 2). self nextPutByte: (f at: 3). self nextPutByte: (f at: 4) ] nextPutByte: anInteger [ "Store anInteger (range: -128..255) on the byte array" | int | int := anInteger < 0 ifTrue: [256 + anInteger] ifFalse: [anInteger]. ^stream nextPut: (Character value: int) ] nextPutByteArray: aByteArray [ "Store aByteArray on the byte array" ^self nextPutAll: aByteArray ] nextPutInt64: anInteger [ "Store anInteger (range: -2^63..2^64-1) on the byte array as 4 bytes" self nextPutBytes: 8 of: anInteger ] nextPutLong: anInteger [ "Store anInteger (range: -2^31..2^32-1) on the byte array as 4 bytes" self nextPutBytes: 4 of: anInteger ] nextPutShort: anInteger [ "Store anInteger (range: -32768..65535) on the byte array as 2 bytes" self nextPutBytes: 2 of: anInteger ] nextBytes: n signed: signed [ "Private - Get an integer out of the next anInteger bytes in the stream" | int msb | int := 0. 0 to: n * 8 - 16 by: 8 do: [:i | int := int + (self nextByte bitShift: i)]. msb := self nextByte. (signed and: [msb > 127]) ifTrue: [msb := msb - 256]. ^int + (msb bitShift: n * 8 - 8) ] nextPutBytes: n of: anInteger [ "Private - Store the n least significant bytes of int in little-endian format" | int | int := anInteger. n timesRepeat: [self nextPutByte: (int bitAnd: 255). int := int bitShift: -8. (int = 0 and: [anInteger < 0]) ifTrue: [int := 255]] ] ] Object subclass: DumperProxy [ DumperProxy class >> loadFrom: anObjectDumper [ "Reload a proxy stored in anObjectDumper and reconstruct the object" ^anObjectDumper load object ] DumperProxy class >> acceptUsageForClass: aClass [ "The receiver was asked to be used as a proxy for the class aClass. Answer whether the registration is fine. By default, answer true" ^true ] DumperProxy class >> on: anObject [ "Answer a proxy to be used to save anObject. This method MUST be overridden and anObject must NOT be stored in the object's instance variables unless you override #dumpTo:, because that would result in an infinite loop!" self subclassResponsibility ] dumpTo: anObjectDumper [ "Dump the proxy to anObjectDumper -- the #loadFrom: class method will reconstruct the original object." anObjectDumper dump: self ] object [ "Reconstruct the object stored in the proxy and answer it" self subclassResponsibility ] ] DumperProxy subclass: AlternativeObjectProxy [ | object | AlternativeObjectProxy class >> acceptUsageForClass: aClass [ "The receiver was asked to be used as a proxy for the class aClass. Answer whether the registration is fine. By default, answer true except if AlternativeObjectProxy itself is being used." ^self ~~ AlternativeObjectProxy ] AlternativeObjectProxy class >> on: anObject [ "Answer a proxy to be used to save anObject. IMPORTANT: this method MUST be overridden so that the overridden version sends #on: to super passing an object that is NOT the same as anObject (alternatively, you can override #dumpTo:, which is what NullProxy does), because that would result in an infinite loop! This also means that AlternativeObjectProxy must never be used directly -- only as a superclass." ^self new object: anObject ] object [ "Reconstruct the object stored in the proxy and answer it. A subclass will usually override this" ^object ] primObject [ "Reconstruct the object stored in the proxy and answer it. This method must not be overridden" ^object ] object: theObject [ "Set the object to be dumped to theObject. This should not be overridden." object := theObject ] ] AlternativeObjectProxy subclass: NullProxy [ NullProxy class >> loadFrom: anObjectDumper [ "Reload the object stored in anObjectDumper" ^anObjectDumper load ] dumpTo: anObjectDumper [ "Dump the object stored in the proxy to anObjectDumper" anObjectDumper dumpContentsOf: self object ] ] AlternativeObjectProxy subclass: PluggableProxy [ PluggableProxy class >> on: anObject [ "Answer a proxy to be used to save anObject. The proxy stores a different object obtained by sending to anObject the #binaryRepresentationObject message (embedded between #preStore and #postStore as usual)." anObject preStore. ^[super on: anObject binaryRepresentationObject] ensure: [anObject postStore] ] object [ "Reconstruct the object stored in the proxy and answer it; the binaryRepresentationObject is sent the #reconstructOriginalObject message, and the resulting object is sent the #postLoad message." ^(super object reconstructOriginalObject) postLoad; yourself ] ] NullProxy subclass: VersionableObjectProxy [ VersionableObjectProxy class >> loadFrom: anObjectDumper [ "Retrieve the object. If the version number doesn't match the #binaryRepresentationVersion answered by the class, call the class' #convertFromVersion:withFixedVariables:instanceVariables:for: method. The stored version number will be the first parameter to that method (or nil if the stored object did not employ a VersionableObjectProxy), the remaining parameters will be respectively the fixed instance variables, the indexed instance variables (or nil if the class is fixed), and the ObjectDumper itself. If no VersionableObjectProxy, the class is sent #nonVersionedInstSize to retrieve the number of fixed instance variables stored for the non-versioned object." | version object instSize index | version := anObjectDumper nextLong. version := version >= 0 ifTrue: ["The version was actually an object index." instSize := nil. index := version. nil] ifFalse: [instSize := anObjectDumper nextUlong. index := anObjectDumper nextLong. -1 - version]. ^anObjectDumper loadFromVersion: version fixedSize: instSize index: index ] dumpTo: anObjectDumper [ "Save the object with extra versioning information." anObjectDumper nextPutLong: -1 - self object class binaryRepresentationVersion; nextPutLong: self object class instSize. super dumpTo: anObjectDumper ] ] AlternativeObjectProxy subclass: SingletonProxy [ SingletonProxy class [ | singletons | ] SingletonProxy class >> singletons [ ^singletons isNil ifTrue: [singletons := IdentityDictionary new] ifFalse: [singletons] ] SingletonProxy class >> acceptUsageForClass: aClass [ "The receiver was asked to be used as a proxy for the class aClass. The registration is fine if the class is actually a singleton." | singleton | singleton := aClass someInstance. singleton nextInstance isNil ifFalse: [^false]. self singletons at: aClass put: singleton. ^true ] SingletonProxy class >> on: anObject [ "Answer a proxy to be used to save anObject. The proxy stores the class and restores the object by looking into a dictionary of class -> singleton objects." (self singletons includesKey: anObject class) ifTrue: [^super on: anObject class]. self error: 'class not registered within SingletonProxy' ] object [ "Reconstruct the object stored in the proxy and answer it; the binaryRepresentationObject is sent the #reconstructOriginalObject message, and the resulting object is sent the #postLoad message." ^self class singletons at: super object ifAbsent: [self error: 'class not registered within SingletonProxy'] ] ] Eval [ ObjectDumper initialize; registerProxyClass: PluggableProxy for: CompiledMethod; registerProxyClass: PluggableProxy for: CompiledBlock; registerProxyClass: SingletonProxy for: Processor class ] smalltalk-3.2.5/smalltalk-mode-init.el.in0000644000175000017500000000127012123404352015220 00000000000000;; Autoload file for smalltalk-mode ;; duplicate zip files' setup for star files or fall back on ;; archive-mode, which scans file contents to determine type so is ;; safe to use (push (cons "\\.star\\'" (catch 'archive-mode (dolist (mode-assoc auto-mode-alist 'archive-mode) (and (string-match (car mode-assoc) "Starfile.zip") (functionp (cdr mode-assoc)) (throw 'archive-mode (cdr mode-assoc)))))) auto-mode-alist) (push '("\\.st\\'" . smalltalk-mode) auto-mode-alist) (push "\\.star\\'" inhibit-first-line-modes-regexps) (autoload 'smalltalk-mode "@lispdir@/smalltalk-mode.elc" "" t) @WITH_EMACS_COMINT_TRUE@(autoload 'gst "@lispdir@/gst-mode.elc" "" t) smalltalk-3.2.5/gsticon.ico0000644000175000017500000002043612123404352012571 00000000000000(Vh~ èæ ¨Î 00¨v( À€€€€€€€€€ÀÀÀ€€€ÿÿÿÿÿÿÿÿÿÿÿÿ``‡hGd€€GFv`f@Àÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿþÿÿœ?ÿÿÌÿÿàÏÿÿàãÿÿññÿÿÿùÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿ( @€€€€€€€€€ÀÀÀÀÜÀðʦÔðÿ±âÿŽÔÿkÆÿH¸ÿ%ªÿªÿ’Üz¹b–Js2PÔãÿ±ÇÿŽ«ÿkÿHsÿ%WÿUÿIÜ=¹1–%sPÔÔÿ±±ÿŽŽÿkkÿHHÿ%%ÿþܹ–sPãÔÿDZÿ«ŽÿkÿsHÿW%ÿUÿIÜ=¹1–%sPðÔÿâ±ÿÔŽÿÆkÿ¸Hÿª%ÿªÿ’Üz¹b–Js2PÿÔÿÿ±ÿÿŽÿÿkÿÿHÿÿ%ÿþþÜܹ¹––ssPPÿÔðÿ±âÿŽÔÿkÆÿH¸ÿ%ªÿªÜ’¹z–bsJP2ÿÔãÿ±ÇÿŽ«ÿkÿHsÿ%WÿUÜI¹=–1s%PÿÔÔÿ±±ÿŽŽÿkkÿHHÿ%%þܹ–sPÿãÔÿDZÿ«ŽÿkÿsHÿW%ÿUÜI¹=–1s%PÿðÔÿâ±ÿÔŽÿÆkÿ¸Hÿª%ÿªÜ’¹z–bsJP2ÿÿÔÿÿ±ÿÿŽÿÿkÿÿHÿÿ%þþÜܹ¹––ssPPðÿÔâÿ±ÔÿŽÆÿk¸ÿHªÿ%ªÿ’Üz¹b–Js2PãÿÔÇÿ±«ÿŽÿksÿHWÿ%UÿIÜ=¹1–%sPÔÿÔ±ÿ±ŽÿŽkÿkHÿH%ÿ%þܹ–sPÔÿã±ÿÇŽÿ«kÿHÿs%ÿWÿUÜI¹=–1s%PÔÿð±ÿâŽÿÔkÿÆHÿ¸%ÿªÿªÜ’¹z–bsJP2Ôÿÿ±ÿÿŽÿÿkÿÿHÿÿ%ÿÿþþÜܹ¹––ssPPòòòæææÚÚÚÎÎζ¶¶ªªªžžž’’’†††zzznnnbbbVVVJJJ>>>222&&&ðûÿ¤  €€€ÿÿÿÿÿÿÿÿÿÿÿÿ€~u‹Šuy„zzuâ{ÿ€‚y‚yzvŠ€‹ ‹}x‹Šuy}‚ÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿž?ÿÿÌÿÿÀ‡ÿÿàÃÿÿðñÿÿÿøÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿ( @€€€€€€€€€€ÀÀÀ€€€ÿÿÿÿÿÿÿÿÿÿÿÿwpwpwpwÌÀ Œ||ÇÌ À||ÀÌ Œp| |Ç ÀÇ|À| €Ç |Ç ÀÇÀ| ÀŒÀ ÌÇ€|ÀÌÀ| Çwpp|ÀÀ p| ÌÇÌ ÀÆÌ €xp€ Ç À| ÌÀ Ç pÀ €Ì pÇ À À À À |w ÀÀ À| À|Ì ÀÌ|ÀÇwpˆp@`ndd``Dvˆ`@h††xh@pf`„`†„Gd@h@h@€hggvhDp††FG†„f„fGf`pvffpvfpvgfd@l`¤ºJHJ"ÐIŠ2ÒI$ÒJ8dÖJü“ËŸü›Ûÿÿÿÿÿ‰#ÿÿk%ÿþI-ÿþzíÿþx-ÿÿi-ÿÿ ÿÿÿÿÿÿÿÿÿÿñÿÿÇàÿÿÃÀ?ÿÁÀÿàÀÿðáÿøaÁÿøÀüð?þøÿüÿÃÿÿÿÿ‡ÿÿÿï( @€€€€€€€€€€ÀÀÀÀÜÀðʦÔðÿ±âÿŽÔÿkÆÿH¸ÿ%ªÿªÿ’Üz¹b–Js2PÔãÿ±ÇÿŽ«ÿkÿHsÿ%WÿUÿIÜ=¹1–%sPÔÔÿ±±ÿŽŽÿkkÿHHÿ%%ÿþܹ–sPãÔÿDZÿ«ŽÿkÿsHÿW%ÿUÿIÜ=¹1–%sPðÔÿâ±ÿÔŽÿÆkÿ¸Hÿª%ÿªÿ’Üz¹b–Js2PÿÔÿÿ±ÿÿŽÿÿkÿÿHÿÿ%ÿþþÜܹ¹––ssPPÿÔðÿ±âÿŽÔÿkÆÿH¸ÿ%ªÿªÜ’¹z–bsJP2ÿÔãÿ±ÇÿŽ«ÿkÿHsÿ%WÿUÜI¹=–1s%PÿÔÔÿ±±ÿŽŽÿkkÿHHÿ%%þܹ–sPÿãÔÿDZÿ«ŽÿkÿsHÿW%ÿUÜI¹=–1s%PÿðÔÿâ±ÿÔŽÿÆkÿ¸Hÿª%ÿªÜ’¹z–bsJP2ÿÿÔÿÿ±ÿÿŽÿÿkÿÿHÿÿ%þþÜܹ¹––ssPPðÿÔâÿ±ÔÿŽÆÿk¸ÿHªÿ%ªÿ’Üz¹b–Js2PãÿÔÇÿ±«ÿŽÿksÿHWÿ%UÿIÜ=¹1–%sPÔÿÔ±ÿ±ŽÿŽkÿkHÿH%ÿ%þܹ–sPÔÿã±ÿÇŽÿ«kÿHÿs%ÿWÿUÜI¹=–1s%PÔÿð±ÿâŽÿÔkÿÆHÿ¸%ÿªÿªÜ’¹z–bsJP2Ôÿÿ±ÿÿŽÿÿkÿÿHÿÿ%ÿÿþþÜܹ¹––ssPPòòòæææÚÚÚÎÎζ¶¶ªªªžžž’’’†††zzznnnbbbVVVJJJ>>>222&&&ðûÿ¤  €€€ÿÿÿÿÿÿÿÿÿÿÿÿkkw^kkk^k^kk^kkwk^^k^kk^kk^k^knk{j^nxykmkmmklzwn^kmkmyjmmwlxmxkkn†kkwlmkw|nkkkyyvkkƒxxjlnkn†kkwmkw|nkkkyvkkwxzyzzv^nxymkvxlww|nymwlyjkkw|wl{kww^kkkk‚www|nymwwkkw|wmkmk |wnwxmkw|^kk‚jkwwƒk^ãkvznwllwwxnnqwÿn‚‚mknwzlxnol wwqknzyy vnwjnnz…ƒkmkknnm^novkknzwnnlln‚ynwolvowvææv ÷xâvz‹jŠŒŒìâëŒzzŠŒŒìjyŠŠŒy‚Š‹yŠzy‹Œ‹jvyzzŒyyŠy‹yzzy‹Œ âŠz‹Œ jŠz‹ì yŠy‹î jŠz‹‹ ÿxŠz‹j zy‹ŒêjxŠyŒŒx zyŠx zyyŒ‹x‚xŠy‹Œ‹ŒŠŠ jyyy‹ŒøâxŠzzŒ‹zŠjâ Šz‹Œxâ yzzzz ‚ yyzŒ‹xâ yy vzzz‹zvâyzzyv‚jxv€€JЊ ÒÐ$ÒBü“Ãü›Ãÿÿÿÿÿ #ÿÿ %ÿþ@-ÿþx-ÿþx-ÿÿ,-ÿÿÿÿÿÿÿÿÿÿÿÿàÿÿÃÀÿÁÀÿÀÀÿÀÀÿà@ÿð€ÿøÀ?üà?üðÿüÿƒþÿÿÿÿÿÿ‡(0`€ €€€€€€€€€ÀÀÀÀÜÀðʦÔðÿ±âÿŽÔÿkÆÿH¸ÿ%ªÿªÿ’Üz¹b–Js2PÔãÿ±ÇÿŽ«ÿkÿHsÿ%WÿUÿIÜ=¹1–%sPÔÔÿ±±ÿŽŽÿkkÿHHÿ%%ÿþܹ–sPãÔÿDZÿ«ŽÿkÿsHÿW%ÿUÿIÜ=¹1–%sPðÔÿâ±ÿÔŽÿÆkÿ¸Hÿª%ÿªÿ’Üz¹b–Js2PÿÔÿÿ±ÿÿŽÿÿkÿÿHÿÿ%ÿþþÜܹ¹––ssPPÿÔðÿ±âÿŽÔÿkÆÿH¸ÿ%ªÿªÜ’¹z–bsJP2ÿÔãÿ±ÇÿŽ«ÿkÿHsÿ%WÿUÜI¹=–1s%PÿÔÔÿ±±ÿŽŽÿkkÿHHÿ%%þܹ–sPÿãÔÿDZÿ«ŽÿkÿsHÿW%ÿUÜI¹=–1s%PÿðÔÿâ±ÿÔŽÿÆkÿ¸Hÿª%ÿªÜ’¹z–bsJP2ÿÿÔÿÿ±ÿÿŽÿÿkÿÿHÿÿ%þþÜܹ¹––ssPPðÿÔâÿ±ÔÿŽÆÿk¸ÿHªÿ%ªÿ’Üz¹b–Js2PãÿÔÇÿ±«ÿŽÿksÿHWÿ%UÿIÜ=¹1–%sPÔÿÔ±ÿ±ŽÿŽkÿkHÿH%ÿ%þܹ–sPÔÿã±ÿÇŽÿ«kÿHÿs%ÿWÿUÜI¹=–1s%PÔÿð±ÿâŽÿÔkÿÆHÿ¸%ÿªÿªÜ’¹z–bsJP2Ôÿÿ±ÿÿŽÿÿkÿÿHÿÿ%ÿÿþþÜܹ¹––ssPPòòòæææÚÚÚÎÎζ¶¶ªªªžžž’’’†††zzznnnbbbVVVJJJ>>>222&&&ðûÿ¤  €€€ÿÿÿÿÿÿÿÿÿÿÿÿ|||||†|‡|||z||z|‡||‡z||||‡‡|z||||||yy|zz|‡|zz|||zzz|zzw‡z||zz|||zzz||z|zzz|zzzzy||zz||‡zzzz||zz|‡z|†z‡||z‡|zz|z|zzz||zzz|zzzy|x‡x|zz|z x|zzz|||wz|zxx||z||z|‡‡|zz|zzz|z…||||zxxz}|‡zzz|||zxx|zwz||w|zwxy||yz|y||x z|†x|yx|||||zx||||||zz|x‡x|||zz|zz|yzzz|‡zzzx†‡z|zxxzx‡zzz|zxx†x‡|yz|zzz x|zz|z|zz|zzz|z||zyy|yx|||||z|z|‡zz|zzzzzzzzzzŒŒŠzzŠ‹zzŠŒó‹zzŒ‹zzŒŒzy~ŒŒŠzz‹~Œ‹yzŒ‹wzzyy‹ŒŠzz‹Šy‹‹yzŒzx‹ŠŠŠyy‹ŒŠzŠŠx‹Œ‹zy‹zyŒz ŠŠzyzŒŒ‹zy‹ŠxŒŒŠŠŠxŒŒz yŠŠyxŒŒ‹y‹ŠyŒŒyz‹ŠyŒŒx yŠzyŒ‹zz‹yŠŒŒyz‹yzŒzyŠzzŒŒyz‹Šy‹ŒyzŠŠyŠŠy‹zy‹ŒŒ‹yyŠŠx‹ŒzzƒyŠ zŠzyŠzzy‹ŒŒŠzz‹ŠyŠŒz‹ŒzŠŠyzzyzŠ‹zyŠŠyyŒŒzŠŠyzŠyzŒŠzŠŠzzzŒ‹xzŠyzŠ‹zyŒ‹zzzŠŠyyzŠŠzz z‹zxŒŒzzzŠŠŠŠyyŠzy‹zzyyzyŠŠyzŒzzŠŠy{zzzzzÿÿÿÿÿÿÿÿÉ'ÿÿÙ¥lÛ ÿÿÝ¥lš ÿÿý¥Œ™ ÿÿñ¤ì™Éÿÿá¤,›I/ÿÿÇœ‘™'ÿÿÝÿü›ù?ÿÿÝÿüÙù?ÿÿáÿø™ð?ÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿøs¸ÿÿÿÿ󳱿ÿÿÿÿ÷³3¿ÿÿÿÿæ3¿ÿÿÿÿçò3¿ÿÿÿÿçð³¿ÿÿÿÿçñ³¿ÿÿÿÿ÷±³¿ÿÿÿÿû¹»¿ÿÿÿÿøsÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÿÁÿÿÿÿÿñÿ€ÿÿÿÿÿàÿÿÿÿÿà~ÿÿÿÿà>ÿÿÿÿàÿÿÿÿðÿÿÿÿøÿÿÿÿüÿÿÿþÀ?ÿÿÿþàÿÿÿÿðÿÿÿÿ€øÿÿÿÿÀþÿÿÿÿàÿÿÿÿðÿ€?ÿÿÿüÿàÿÿÿÿÿðÿÿÿÿÿÿøÿÿÿÿÿÿü?ÿÿÿÿÿÿÿÿÿÿsmalltalk-3.2.5/INSTALL0000644000175000017500000003660012130455426011466 00000000000000Installation Instructions ************************* Copyright (C) 1994-1996, 1999-2002, 2004-2011 Free Software Foundation, Inc. Copying and distribution of this file, with or without modification, are permitted in any medium without royalty provided the copyright notice and this notice are preserved. This file is offered as-is, without warranty of any kind. Basic Installation ================== Briefly, the shell commands `./configure; make; make install' should configure, build, and install this package. The following more-detailed instructions are generic; see the `README' file for instructions specific to this package. Some packages provide this `INSTALL' file but do not implement all of the features documented below. The lack of an optional feature in a given package is not necessarily a bug. More recommendations for GNU packages can be found in *note Makefile Conventions: (standards)Makefile Conventions. The `configure' shell script attempts to guess correct values for various system-dependent variables used during compilation. It uses those values to create a `Makefile' in each directory of the package. It may also create one or more `.h' files containing system-dependent definitions. Finally, it creates a shell script `config.status' that you can run in the future to recreate the current configuration, and a file `config.log' containing compiler output (useful mainly for debugging `configure'). It can also use an optional file (typically called `config.cache' and enabled with `--cache-file=config.cache' or simply `-C') that saves the results of its tests to speed up reconfiguring. Caching is disabled by default to prevent problems with accidental use of stale cache files. If you need to do unusual things to compile the package, please try to figure out how `configure' could check whether to do them, and mail diffs or instructions to the address given in the `README' so they can be considered for the next release. If you are using the cache, and at some point `config.cache' contains results you don't want to keep, you may remove or edit it. The file `configure.ac' (or `configure.in') is used to create `configure' by a program called `autoconf'. You need `configure.ac' if you want to change it or regenerate `configure' using a newer version of `autoconf'. The simplest way to compile this package is: 1. `cd' to the directory containing the package's source code and type `./configure' to configure the package for your system. Running `configure' might take a while. While running, it prints some messages telling which features it is checking for. 2. Type `make' to compile the package. 3. Optionally, type `make check' to run any self-tests that come with the package, generally using the just-built uninstalled binaries. 4. Type `make install' to install the programs and any data files and documentation. When installing into a prefix owned by root, it is recommended that the package be configured and built as a regular user, and only the `make install' phase executed with root privileges. 5. Optionally, type `make installcheck' to repeat any self-tests, but this time using the binaries in their final installed location. This target does not install anything. Running this target as a regular user, particularly if the prior `make install' required root privileges, verifies that the installation completed correctly. 6. You can remove the program binaries and object files from the source code directory by typing `make clean'. To also remove the files that `configure' created (so you can compile the package for a different kind of computer), type `make distclean'. There is also a `make maintainer-clean' target, but that is intended mainly for the package's developers. If you use it, you may have to get all sorts of other programs in order to regenerate files that came with the distribution. 7. Often, you can also type `make uninstall' to remove the installed files again. In practice, not all packages have tested that uninstallation works correctly, even though it is required by the GNU Coding Standards. 8. Some packages, particularly those that use Automake, provide `make distcheck', which can by used by developers to test that all other targets like `make install' and `make uninstall' work correctly. This target is generally not run by end users. Compilers and Options ===================== Some systems require unusual options for compilation or linking that the `configure' script does not know about. Run `./configure --help' for details on some of the pertinent environment variables. You can give `configure' initial values for configuration parameters by setting variables in the command line or in the environment. Here is an example: ./configure CC=c99 CFLAGS=-g LIBS=-lposix *Note Defining Variables::, for more details. Compiling For Multiple Architectures ==================================== You can compile the package for more than one kind of computer at the same time, by placing the object files for each architecture in their own directory. To do this, you can use GNU `make'. `cd' to the directory where you want the object files and executables to go and run the `configure' script. `configure' automatically checks for the source code in the directory that `configure' is in and in `..'. This is known as a "VPATH" build. With a non-GNU `make', it is safer to compile the package for one architecture at a time in the source code directory. After you have installed the package for one architecture, use `make distclean' before reconfiguring for another architecture. On MacOS X 10.5 and later systems, you can create libraries and executables that work on multiple system types--known as "fat" or "universal" binaries--by specifying multiple `-arch' options to the compiler but only a single `-arch' option to the preprocessor. Like this: ./configure CC="gcc -arch i386 -arch x86_64 -arch ppc -arch ppc64" \ CXX="g++ -arch i386 -arch x86_64 -arch ppc -arch ppc64" \ CPP="gcc -E" CXXCPP="g++ -E" This is not guaranteed to produce working output in all cases, you may have to build one architecture at a time and combine the results using the `lipo' tool if you have problems. Installation Names ================== By default, `make install' installs the package's commands under `/usr/local/bin', include files under `/usr/local/include', etc. You can specify an installation prefix other than `/usr/local' by giving `configure' the option `--prefix=PREFIX', where PREFIX must be an absolute file name. You can specify separate installation prefixes for architecture-specific files and architecture-independent files. If you pass the option `--exec-prefix=PREFIX' to `configure', the package uses PREFIX as the prefix for installing programs and libraries. Documentation and other data files still use the regular prefix. In addition, if you use an unusual directory layout you can give options like `--bindir=DIR' to specify different values for particular kinds of files. Run `configure --help' for a list of the directories you can set and what kinds of files go in them. In general, the default for these options is expressed in terms of `${prefix}', so that specifying just `--prefix' will affect all of the other directory specifications that were not explicitly provided. The most portable way to affect installation locations is to pass the correct locations to `configure'; however, many packages provide one or both of the following shortcuts of passing variable assignments to the `make install' command line to change installation locations without having to reconfigure or recompile. The first method involves providing an override variable for each affected directory. For example, `make install prefix=/alternate/directory' will choose an alternate location for all directory configuration variables that were expressed in terms of `${prefix}'. Any directories that were specified during `configure', but not in terms of `${prefix}', must each be overridden at install time for the entire installation to be relocated. The approach of makefile variable overrides for each directory variable is required by the GNU Coding Standards, and ideally causes no recompilation. However, some platforms have known limitations with the semantics of shared libraries that end up requiring recompilation when using this method, particularly noticeable in packages that use GNU Libtool. The second method involves providing the `DESTDIR' variable. For example, `make install DESTDIR=/alternate/directory' will prepend `/alternate/directory' before all installation names. The approach of `DESTDIR' overrides is not required by the GNU Coding Standards, and does not work on platforms that have drive letters. On the other hand, it does better at avoiding recompilation issues, and works well even when some directory options were not specified in terms of `${prefix}' at `configure' time. Optional Features ================= If the package supports it, you can cause programs to be installed with an extra prefix or suffix on their names by giving `configure' the option `--program-prefix=PREFIX' or `--program-suffix=SUFFIX'. Some packages pay attention to `--enable-FEATURE' options to `configure', where FEATURE indicates an optional part of the package. They may also pay attention to `--with-PACKAGE' options, where PACKAGE is something like `gnu-as' or `x' (for the X Window System). The `README' should mention any `--enable-' and `--with-' options that the package recognizes. For packages that use the X Window System, `configure' can usually find the X include and library files automatically, but if it doesn't, you can use the `configure' options `--x-includes=DIR' and `--x-libraries=DIR' to specify their locations. Some packages offer the ability to configure how verbose the execution of `make' will be. For these packages, running `./configure --enable-silent-rules' sets the default to minimal output, which can be overridden with `make V=1'; while running `./configure --disable-silent-rules' sets the default to verbose, which can be overridden with `make V=0'. Particular systems ================== On HP-UX, the default C compiler is not ANSI C compatible. If GNU CC is not installed, it is recommended to use the following options in order to use an ANSI C compiler: ./configure CC="cc -Ae -D_XOPEN_SOURCE=500" and if that doesn't work, install pre-built binaries of GCC for HP-UX. HP-UX `make' updates targets which have the same time stamps as their prerequisites, which makes it generally unusable when shipped generated files such as `configure' are involved. Use GNU `make' instead. On OSF/1 a.k.a. Tru64, some versions of the default C compiler cannot parse its `' header file. The option `-nodtk' can be used as a workaround. If GNU CC is not installed, it is therefore recommended to try ./configure CC="cc" and if that doesn't work, try ./configure CC="cc -nodtk" On Solaris, don't put `/usr/ucb' early in your `PATH'. This directory contains several dysfunctional programs; working variants of these programs are available in `/usr/bin'. So, if you need `/usr/ucb' in your `PATH', put it _after_ `/usr/bin'. On Haiku, software installed for all users goes in `/boot/common', not `/usr/local'. It is recommended to use the following options: ./configure --prefix=/boot/common Specifying the System Type ========================== There may be some features `configure' cannot figure out automatically, but needs to determine by the type of machine the package will run on. Usually, assuming the package is built to be run on the _same_ architectures, `configure' can figure that out, but if it prints a message saying it cannot guess the machine type, give it the `--build=TYPE' option. TYPE can either be a short name for the system type, such as `sun4', or a canonical name which has the form: CPU-COMPANY-SYSTEM where SYSTEM can have one of these forms: OS KERNEL-OS See the file `config.sub' for the possible values of each field. If `config.sub' isn't included in this package, then this package doesn't need to know the machine type. If you are _building_ compiler tools for cross-compiling, you should use the option `--target=TYPE' to select the type of system they will produce code for. If you want to _use_ a cross compiler, that generates code for a platform different from the build platform, you should specify the "host" platform (i.e., that on which the generated programs will eventually be run) with `--host=TYPE'. Sharing Defaults ================ If you want to set default values for `configure' scripts to share, you can create a site shell script called `config.site' that gives default values for variables like `CC', `cache_file', and `prefix'. `configure' looks for `PREFIX/share/config.site' if it exists, then `PREFIX/etc/config.site' if it exists. Or, you can set the `CONFIG_SITE' environment variable to the location of the site script. A warning: not all `configure' scripts look for a site script. Defining Variables ================== Variables not defined in a site shell script can be set in the environment passed to `configure'. However, some packages may run configure again during the build, and the customized values of these variables may be lost. In order to avoid this problem, you should set them in the `configure' command line, using `VAR=value'. For example: ./configure CC=/usr/local2/bin/gcc causes the specified `gcc' to be used as the C compiler (unless it is overridden in the site shell script). Unfortunately, this technique does not work for `CONFIG_SHELL' due to an Autoconf bug. Until the bug is fixed you can use this workaround: CONFIG_SHELL=/bin/bash /bin/bash ./configure CONFIG_SHELL=/bin/bash `configure' Invocation ====================== `configure' recognizes the following options to control how it operates. `--help' `-h' Print a summary of all of the options to `configure', and exit. `--help=short' `--help=recursive' Print a summary of the options unique to this package's `configure', and exit. The `short' variant lists options used only in the top level, while the `recursive' variant lists options also present in any nested packages. `--version' `-V' Print the version of Autoconf used to generate the `configure' script, and exit. `--cache-file=FILE' Enable the cache: use and save the results of the tests in FILE, traditionally `config.cache'. FILE defaults to `/dev/null' to disable caching. `--config-cache' `-C' Alias for `--cache-file=config.cache'. `--quiet' `--silent' `-q' Do not print messages saying which checks are being made. To suppress all normal output, redirect it to `/dev/null' (any error messages will still be shown). `--srcdir=DIR' Look for the package's source code in directory DIR. Usually `configure' can determine that directory automatically. `--prefix=DIR' Use DIR as the installation prefix. *note Installation Names:: for more details, including other options available for fine-tuning the installation locations. `--no-create' `-n' Run the configure checks, but stop before creating any output files. `configure' also accepts some other, not widely useful, options. Run `configure --help' for more details. smalltalk-3.2.5/aclocal.m40000644000175000017500000011330612130455422012270 00000000000000# generated automatically by aclocal 1.11.6 -*- Autoconf -*- # Copyright (C) 1996, 1997, 1998, 1999, 2000, 2001, 2002, 2003, 2004, # 2005, 2006, 2007, 2008, 2009, 2010, 2011 Free Software Foundation, # Inc. # This file is free software; the Free Software Foundation # gives unlimited permission to copy and/or distribute it, # with or without modifications, as long as this notice is preserved. # This program is distributed in the hope that it will be useful, # but WITHOUT ANY WARRANTY, to the extent permitted by law; without # even the implied warranty of MERCHANTABILITY or FITNESS FOR A # PARTICULAR PURPOSE. m4_ifndef([AC_AUTOCONF_VERSION], [m4_copy([m4_PACKAGE_VERSION], [AC_AUTOCONF_VERSION])])dnl m4_if(m4_defn([AC_AUTOCONF_VERSION]), [2.69],, [m4_warning([this file was generated for autoconf 2.69. You have another version of autoconf. It may work, but is not guaranteed to. If you have problems, you may need to regenerate the build system entirely. To do so, use the procedure documented by the package, typically `autoreconf'.])]) # Copyright (C) 2002, 2003, 2005, 2006, 2007, 2008, 2011 Free Software # Foundation, Inc. # # This file is free software; the Free Software Foundation # gives unlimited permission to copy and/or distribute it, # with or without modifications, as long as this notice is preserved. # serial 1 # AM_AUTOMAKE_VERSION(VERSION) # ---------------------------- # Automake X.Y traces this macro to ensure aclocal.m4 has been # generated from the m4 files accompanying Automake X.Y. # (This private macro should not be called outside this file.) AC_DEFUN([AM_AUTOMAKE_VERSION], [am__api_version='1.11' dnl Some users find AM_AUTOMAKE_VERSION and mistake it for a way to dnl require some minimum version. Point them to the right macro. m4_if([$1], [1.11.6], [], [AC_FATAL([Do not call $0, use AM_INIT_AUTOMAKE([$1]).])])dnl ]) # _AM_AUTOCONF_VERSION(VERSION) # ----------------------------- # aclocal traces this macro to find the Autoconf version. # This is a private macro too. Using m4_define simplifies # the logic in aclocal, which can simply ignore this definition. m4_define([_AM_AUTOCONF_VERSION], []) # AM_SET_CURRENT_AUTOMAKE_VERSION # ------------------------------- # Call AM_AUTOMAKE_VERSION and AM_AUTOMAKE_VERSION so they can be traced. # This function is AC_REQUIREd by AM_INIT_AUTOMAKE. AC_DEFUN([AM_SET_CURRENT_AUTOMAKE_VERSION], [AM_AUTOMAKE_VERSION([1.11.6])dnl m4_ifndef([AC_AUTOCONF_VERSION], [m4_copy([m4_PACKAGE_VERSION], [AC_AUTOCONF_VERSION])])dnl _AM_AUTOCONF_VERSION(m4_defn([AC_AUTOCONF_VERSION]))]) # AM_AUX_DIR_EXPAND -*- Autoconf -*- # Copyright (C) 2001, 2003, 2005, 2011 Free Software Foundation, Inc. # # This file is free software; the Free Software Foundation # gives unlimited permission to copy and/or distribute it, # with or without modifications, as long as this notice is preserved. # serial 1 # For projects using AC_CONFIG_AUX_DIR([foo]), Autoconf sets # $ac_aux_dir to `$srcdir/foo'. In other projects, it is set to # `$srcdir', `$srcdir/..', or `$srcdir/../..'. # # Of course, Automake must honor this variable whenever it calls a # tool from the auxiliary directory. The problem is that $srcdir (and # therefore $ac_aux_dir as well) can be either absolute or relative, # depending on how configure is run. This is pretty annoying, since # it makes $ac_aux_dir quite unusable in subdirectories: in the top # source directory, any form will work fine, but in subdirectories a # relative path needs to be adjusted first. # # $ac_aux_dir/missing # fails when called from a subdirectory if $ac_aux_dir is relative # $top_srcdir/$ac_aux_dir/missing # fails if $ac_aux_dir is absolute, # fails when called from a subdirectory in a VPATH build with # a relative $ac_aux_dir # # The reason of the latter failure is that $top_srcdir and $ac_aux_dir # are both prefixed by $srcdir. In an in-source build this is usually # harmless because $srcdir is `.', but things will broke when you # start a VPATH build or use an absolute $srcdir. # # So we could use something similar to $top_srcdir/$ac_aux_dir/missing, # iff we strip the leading $srcdir from $ac_aux_dir. That would be: # am_aux_dir='\$(top_srcdir)/'`expr "$ac_aux_dir" : "$srcdir//*\(.*\)"` # and then we would define $MISSING as # MISSING="\${SHELL} $am_aux_dir/missing" # This will work as long as MISSING is not called from configure, because # unfortunately $(top_srcdir) has no meaning in configure. # However there are other variables, like CC, which are often used in # configure, and could therefore not use this "fixed" $ac_aux_dir. # # Another solution, used here, is to always expand $ac_aux_dir to an # absolute PATH. The drawback is that using absolute paths prevent a # configured tree to be moved without reconfiguration. AC_DEFUN([AM_AUX_DIR_EXPAND], [dnl Rely on autoconf to set up CDPATH properly. AC_PREREQ([2.50])dnl # expand $ac_aux_dir to an absolute path am_aux_dir=`cd $ac_aux_dir && pwd` ]) # AM_CONDITIONAL -*- Autoconf -*- # Copyright (C) 1997, 2000, 2001, 2003, 2004, 2005, 2006, 2008 # Free Software Foundation, Inc. # # This file is free software; the Free Software Foundation # gives unlimited permission to copy and/or distribute it, # with or without modifications, as long as this notice is preserved. # serial 9 # AM_CONDITIONAL(NAME, SHELL-CONDITION) # ------------------------------------- # Define a conditional. AC_DEFUN([AM_CONDITIONAL], [AC_PREREQ(2.52)dnl ifelse([$1], [TRUE], [AC_FATAL([$0: invalid condition: $1])], [$1], [FALSE], [AC_FATAL([$0: invalid condition: $1])])dnl AC_SUBST([$1_TRUE])dnl AC_SUBST([$1_FALSE])dnl _AM_SUBST_NOTMAKE([$1_TRUE])dnl _AM_SUBST_NOTMAKE([$1_FALSE])dnl m4_define([_AM_COND_VALUE_$1], [$2])dnl if $2; then $1_TRUE= $1_FALSE='#' else $1_TRUE='#' $1_FALSE= fi AC_CONFIG_COMMANDS_PRE( [if test -z "${$1_TRUE}" && test -z "${$1_FALSE}"; then AC_MSG_ERROR([[conditional "$1" was never defined. Usually this means the macro was only invoked conditionally.]]) fi])]) # Copyright (C) 1999, 2000, 2001, 2002, 2003, 2004, 2005, 2006, 2009, # 2010, 2011 Free Software Foundation, Inc. # # This file is free software; the Free Software Foundation # gives unlimited permission to copy and/or distribute it, # with or without modifications, as long as this notice is preserved. # serial 12 # There are a few dirty hacks below to avoid letting `AC_PROG_CC' be # written in clear, in which case automake, when reading aclocal.m4, # will think it sees a *use*, and therefore will trigger all it's # C support machinery. Also note that it means that autoscan, seeing # CC etc. in the Makefile, will ask for an AC_PROG_CC use... # _AM_DEPENDENCIES(NAME) # ---------------------- # See how the compiler implements dependency checking. # NAME is "CC", "CXX", "GCJ", or "OBJC". # We try a few techniques and use that to set a single cache variable. # # We don't AC_REQUIRE the corresponding AC_PROG_CC since the latter was # modified to invoke _AM_DEPENDENCIES(CC); we would have a circular # dependency, and given that the user is not expected to run this macro, # just rely on AC_PROG_CC. AC_DEFUN([_AM_DEPENDENCIES], [AC_REQUIRE([AM_SET_DEPDIR])dnl AC_REQUIRE([AM_OUTPUT_DEPENDENCY_COMMANDS])dnl AC_REQUIRE([AM_MAKE_INCLUDE])dnl AC_REQUIRE([AM_DEP_TRACK])dnl ifelse([$1], CC, [depcc="$CC" am_compiler_list=], [$1], CXX, [depcc="$CXX" am_compiler_list=], [$1], OBJC, [depcc="$OBJC" am_compiler_list='gcc3 gcc'], [$1], UPC, [depcc="$UPC" am_compiler_list=], [$1], GCJ, [depcc="$GCJ" am_compiler_list='gcc3 gcc'], [depcc="$$1" am_compiler_list=]) AC_CACHE_CHECK([dependency style of $depcc], [am_cv_$1_dependencies_compiler_type], [if test -z "$AMDEP_TRUE" && test -f "$am_depcomp"; then # We make a subdir and do the tests there. Otherwise we can end up # making bogus files that we don't know about and never remove. For # instance it was reported that on HP-UX the gcc test will end up # making a dummy file named `D' -- because `-MD' means `put the output # in D'. rm -rf conftest.dir mkdir conftest.dir # Copy depcomp to subdir because otherwise we won't find it if we're # using a relative directory. cp "$am_depcomp" conftest.dir cd conftest.dir # We will build objects and dependencies in a subdirectory because # it helps to detect inapplicable dependency modes. For instance # both Tru64's cc and ICC support -MD to output dependencies as a # side effect of compilation, but ICC will put the dependencies in # the current directory while Tru64 will put them in the object # directory. mkdir sub am_cv_$1_dependencies_compiler_type=none if test "$am_compiler_list" = ""; then am_compiler_list=`sed -n ['s/^#*\([a-zA-Z0-9]*\))$/\1/p'] < ./depcomp` fi am__universal=false m4_case([$1], [CC], [case " $depcc " in #( *\ -arch\ *\ -arch\ *) am__universal=true ;; esac], [CXX], [case " $depcc " in #( *\ -arch\ *\ -arch\ *) am__universal=true ;; esac]) for depmode in $am_compiler_list; do # Setup a source with many dependencies, because some compilers # like to wrap large dependency lists on column 80 (with \), and # we should not choose a depcomp mode which is confused by this. # # We need to recreate these files for each test, as the compiler may # overwrite some of them when testing with obscure command lines. # This happens at least with the AIX C compiler. : > sub/conftest.c for i in 1 2 3 4 5 6; do echo '#include "conftst'$i'.h"' >> sub/conftest.c # Using `: > sub/conftst$i.h' creates only sub/conftst1.h with # Solaris 8's {/usr,}/bin/sh. touch sub/conftst$i.h done echo "${am__include} ${am__quote}sub/conftest.Po${am__quote}" > confmf # We check with `-c' and `-o' for the sake of the "dashmstdout" # mode. It turns out that the SunPro C++ compiler does not properly # handle `-M -o', and we need to detect this. Also, some Intel # versions had trouble with output in subdirs am__obj=sub/conftest.${OBJEXT-o} am__minus_obj="-o $am__obj" case $depmode in gcc) # This depmode causes a compiler race in universal mode. test "$am__universal" = false || continue ;; nosideeffect) # after this tag, mechanisms are not by side-effect, so they'll # only be used when explicitly requested if test "x$enable_dependency_tracking" = xyes; then continue else break fi ;; msvc7 | msvc7msys | msvisualcpp | msvcmsys) # This compiler won't grok `-c -o', but also, the minuso test has # not run yet. These depmodes are late enough in the game, and # so weak that their functioning should not be impacted. am__obj=conftest.${OBJEXT-o} am__minus_obj= ;; none) break ;; esac if depmode=$depmode \ source=sub/conftest.c object=$am__obj \ depfile=sub/conftest.Po tmpdepfile=sub/conftest.TPo \ $SHELL ./depcomp $depcc -c $am__minus_obj sub/conftest.c \ >/dev/null 2>conftest.err && grep sub/conftst1.h sub/conftest.Po > /dev/null 2>&1 && grep sub/conftst6.h sub/conftest.Po > /dev/null 2>&1 && grep $am__obj sub/conftest.Po > /dev/null 2>&1 && ${MAKE-make} -s -f confmf > /dev/null 2>&1; then # icc doesn't choke on unknown options, it will just issue warnings # or remarks (even with -Werror). So we grep stderr for any message # that says an option was ignored or not supported. # When given -MP, icc 7.0 and 7.1 complain thusly: # icc: Command line warning: ignoring option '-M'; no argument required # The diagnosis changed in icc 8.0: # icc: Command line remark: option '-MP' not supported if (grep 'ignoring option' conftest.err || grep 'not supported' conftest.err) >/dev/null 2>&1; then :; else am_cv_$1_dependencies_compiler_type=$depmode break fi fi done cd .. rm -rf conftest.dir else am_cv_$1_dependencies_compiler_type=none fi ]) AC_SUBST([$1DEPMODE], [depmode=$am_cv_$1_dependencies_compiler_type]) AM_CONDITIONAL([am__fastdep$1], [ test "x$enable_dependency_tracking" != xno \ && test "$am_cv_$1_dependencies_compiler_type" = gcc3]) ]) # AM_SET_DEPDIR # ------------- # Choose a directory name for dependency files. # This macro is AC_REQUIREd in _AM_DEPENDENCIES AC_DEFUN([AM_SET_DEPDIR], [AC_REQUIRE([AM_SET_LEADING_DOT])dnl AC_SUBST([DEPDIR], ["${am__leading_dot}deps"])dnl ]) # AM_DEP_TRACK # ------------ AC_DEFUN([AM_DEP_TRACK], [AC_ARG_ENABLE(dependency-tracking, [ --disable-dependency-tracking speeds up one-time build --enable-dependency-tracking do not reject slow dependency extractors]) if test "x$enable_dependency_tracking" != xno; then am_depcomp="$ac_aux_dir/depcomp" AMDEPBACKSLASH='\' am__nodep='_no' fi AM_CONDITIONAL([AMDEP], [test "x$enable_dependency_tracking" != xno]) AC_SUBST([AMDEPBACKSLASH])dnl _AM_SUBST_NOTMAKE([AMDEPBACKSLASH])dnl AC_SUBST([am__nodep])dnl _AM_SUBST_NOTMAKE([am__nodep])dnl ]) # Generate code to set up dependency tracking. -*- Autoconf -*- # Copyright (C) 1999, 2000, 2001, 2002, 2003, 2004, 2005, 2008 # Free Software Foundation, Inc. # # This file is free software; the Free Software Foundation # gives unlimited permission to copy and/or distribute it, # with or without modifications, as long as this notice is preserved. #serial 5 # _AM_OUTPUT_DEPENDENCY_COMMANDS # ------------------------------ AC_DEFUN([_AM_OUTPUT_DEPENDENCY_COMMANDS], [{ # Autoconf 2.62 quotes --file arguments for eval, but not when files # are listed without --file. Let's play safe and only enable the eval # if we detect the quoting. case $CONFIG_FILES in *\'*) eval set x "$CONFIG_FILES" ;; *) set x $CONFIG_FILES ;; esac shift for mf do # Strip MF so we end up with the name of the file. mf=`echo "$mf" | sed -e 's/:.*$//'` # Check whether this is an Automake generated Makefile or not. # We used to match only the files named `Makefile.in', but # some people rename them; so instead we look at the file content. # Grep'ing the first line is not enough: some people post-process # each Makefile.in and add a new line on top of each file to say so. # Grep'ing the whole file is not good either: AIX grep has a line # limit of 2048, but all sed's we know have understand at least 4000. if sed -n 's,^#.*generated by automake.*,X,p' "$mf" | grep X >/dev/null 2>&1; then dirpart=`AS_DIRNAME("$mf")` else continue fi # Extract the definition of DEPDIR, am__include, and am__quote # from the Makefile without running `make'. DEPDIR=`sed -n 's/^DEPDIR = //p' < "$mf"` test -z "$DEPDIR" && continue am__include=`sed -n 's/^am__include = //p' < "$mf"` test -z "am__include" && continue am__quote=`sed -n 's/^am__quote = //p' < "$mf"` # When using ansi2knr, U may be empty or an underscore; expand it U=`sed -n 's/^U = //p' < "$mf"` # Find all dependency output files, they are included files with # $(DEPDIR) in their names. We invoke sed twice because it is the # simplest approach to changing $(DEPDIR) to its actual value in the # expansion. for file in `sed -n " s/^$am__include $am__quote\(.*(DEPDIR).*\)$am__quote"'$/\1/p' <"$mf" | \ sed -e 's/\$(DEPDIR)/'"$DEPDIR"'/g' -e 's/\$U/'"$U"'/g'`; do # Make sure the directory exists. test -f "$dirpart/$file" && continue fdir=`AS_DIRNAME(["$file"])` AS_MKDIR_P([$dirpart/$fdir]) # echo "creating $dirpart/$file" echo '# dummy' > "$dirpart/$file" done done } ])# _AM_OUTPUT_DEPENDENCY_COMMANDS # AM_OUTPUT_DEPENDENCY_COMMANDS # ----------------------------- # This macro should only be invoked once -- use via AC_REQUIRE. # # This code is only required when automatic dependency tracking # is enabled. FIXME. This creates each `.P' file that we will # need in order to bootstrap the dependency handling code. AC_DEFUN([AM_OUTPUT_DEPENDENCY_COMMANDS], [AC_CONFIG_COMMANDS([depfiles], [test x"$AMDEP_TRUE" != x"" || _AM_OUTPUT_DEPENDENCY_COMMANDS], [AMDEP_TRUE="$AMDEP_TRUE" ac_aux_dir="$ac_aux_dir"]) ]) # Do all the work for Automake. -*- Autoconf -*- # Copyright (C) 1996, 1997, 1998, 1999, 2000, 2001, 2002, 2003, 2004, # 2005, 2006, 2008, 2009 Free Software Foundation, Inc. # # This file is free software; the Free Software Foundation # gives unlimited permission to copy and/or distribute it, # with or without modifications, as long as this notice is preserved. # serial 16 # This macro actually does too much. Some checks are only needed if # your package does certain things. But this isn't really a big deal. # AM_INIT_AUTOMAKE(PACKAGE, VERSION, [NO-DEFINE]) # AM_INIT_AUTOMAKE([OPTIONS]) # ----------------------------------------------- # The call with PACKAGE and VERSION arguments is the old style # call (pre autoconf-2.50), which is being phased out. PACKAGE # and VERSION should now be passed to AC_INIT and removed from # the call to AM_INIT_AUTOMAKE. # We support both call styles for the transition. After # the next Automake release, Autoconf can make the AC_INIT # arguments mandatory, and then we can depend on a new Autoconf # release and drop the old call support. AC_DEFUN([AM_INIT_AUTOMAKE], [AC_PREREQ([2.62])dnl dnl Autoconf wants to disallow AM_ names. We explicitly allow dnl the ones we care about. m4_pattern_allow([^AM_[A-Z]+FLAGS$])dnl AC_REQUIRE([AM_SET_CURRENT_AUTOMAKE_VERSION])dnl AC_REQUIRE([AC_PROG_INSTALL])dnl if test "`cd $srcdir && pwd`" != "`pwd`"; then # Use -I$(srcdir) only when $(srcdir) != ., so that make's output # is not polluted with repeated "-I." AC_SUBST([am__isrc], [' -I$(srcdir)'])_AM_SUBST_NOTMAKE([am__isrc])dnl # test to see if srcdir already configured if test -f $srcdir/config.status; then AC_MSG_ERROR([source directory already configured; run "make distclean" there first]) fi fi # test whether we have cygpath if test -z "$CYGPATH_W"; then if (cygpath --version) >/dev/null 2>/dev/null; then CYGPATH_W='cygpath -w' else CYGPATH_W=echo fi fi AC_SUBST([CYGPATH_W]) # Define the identity of the package. dnl Distinguish between old-style and new-style calls. m4_ifval([$2], [m4_ifval([$3], [_AM_SET_OPTION([no-define])])dnl AC_SUBST([PACKAGE], [$1])dnl AC_SUBST([VERSION], [$2])], [_AM_SET_OPTIONS([$1])dnl dnl Diagnose old-style AC_INIT with new-style AM_AUTOMAKE_INIT. m4_if(m4_ifdef([AC_PACKAGE_NAME], 1)m4_ifdef([AC_PACKAGE_VERSION], 1), 11,, [m4_fatal([AC_INIT should be called with package and version arguments])])dnl AC_SUBST([PACKAGE], ['AC_PACKAGE_TARNAME'])dnl AC_SUBST([VERSION], ['AC_PACKAGE_VERSION'])])dnl _AM_IF_OPTION([no-define],, [AC_DEFINE_UNQUOTED(PACKAGE, "$PACKAGE", [Name of package]) AC_DEFINE_UNQUOTED(VERSION, "$VERSION", [Version number of package])])dnl # Some tools Automake needs. AC_REQUIRE([AM_SANITY_CHECK])dnl AC_REQUIRE([AC_ARG_PROGRAM])dnl AM_MISSING_PROG(ACLOCAL, aclocal-${am__api_version}) AM_MISSING_PROG(AUTOCONF, autoconf) AM_MISSING_PROG(AUTOMAKE, automake-${am__api_version}) AM_MISSING_PROG(AUTOHEADER, autoheader) AM_MISSING_PROG(MAKEINFO, makeinfo) AC_REQUIRE([AM_PROG_INSTALL_SH])dnl AC_REQUIRE([AM_PROG_INSTALL_STRIP])dnl AC_REQUIRE([AM_PROG_MKDIR_P])dnl # We need awk for the "check" target. The system "awk" is bad on # some platforms. AC_REQUIRE([AC_PROG_AWK])dnl AC_REQUIRE([AC_PROG_MAKE_SET])dnl AC_REQUIRE([AM_SET_LEADING_DOT])dnl _AM_IF_OPTION([tar-ustar], [_AM_PROG_TAR([ustar])], [_AM_IF_OPTION([tar-pax], [_AM_PROG_TAR([pax])], [_AM_PROG_TAR([v7])])]) _AM_IF_OPTION([no-dependencies],, [AC_PROVIDE_IFELSE([AC_PROG_CC], [_AM_DEPENDENCIES(CC)], [define([AC_PROG_CC], defn([AC_PROG_CC])[_AM_DEPENDENCIES(CC)])])dnl AC_PROVIDE_IFELSE([AC_PROG_CXX], [_AM_DEPENDENCIES(CXX)], [define([AC_PROG_CXX], defn([AC_PROG_CXX])[_AM_DEPENDENCIES(CXX)])])dnl AC_PROVIDE_IFELSE([AC_PROG_OBJC], [_AM_DEPENDENCIES(OBJC)], [define([AC_PROG_OBJC], defn([AC_PROG_OBJC])[_AM_DEPENDENCIES(OBJC)])])dnl ]) _AM_IF_OPTION([silent-rules], [AC_REQUIRE([AM_SILENT_RULES])])dnl dnl The `parallel-tests' driver may need to know about EXEEXT, so add the dnl `am__EXEEXT' conditional if _AM_COMPILER_EXEEXT was seen. This macro dnl is hooked onto _AC_COMPILER_EXEEXT early, see below. AC_CONFIG_COMMANDS_PRE(dnl [m4_provide_if([_AM_COMPILER_EXEEXT], [AM_CONDITIONAL([am__EXEEXT], [test -n "$EXEEXT"])])])dnl ]) dnl Hook into `_AC_COMPILER_EXEEXT' early to learn its expansion. Do not dnl add the conditional right here, as _AC_COMPILER_EXEEXT may be further dnl mangled by Autoconf and run in a shell conditional statement. m4_define([_AC_COMPILER_EXEEXT], m4_defn([_AC_COMPILER_EXEEXT])[m4_provide([_AM_COMPILER_EXEEXT])]) # When config.status generates a header, we must update the stamp-h file. # This file resides in the same directory as the config header # that is generated. The stamp files are numbered to have different names. # Autoconf calls _AC_AM_CONFIG_HEADER_HOOK (when defined) in the # loop where config.status creates the headers, so we can generate # our stamp files there. AC_DEFUN([_AC_AM_CONFIG_HEADER_HOOK], [# Compute $1's index in $config_headers. _am_arg=$1 _am_stamp_count=1 for _am_header in $config_headers :; do case $_am_header in $_am_arg | $_am_arg:* ) break ;; * ) _am_stamp_count=`expr $_am_stamp_count + 1` ;; esac done echo "timestamp for $_am_arg" >`AS_DIRNAME(["$_am_arg"])`/stamp-h[]$_am_stamp_count]) # Copyright (C) 2001, 2003, 2005, 2008, 2011 Free Software Foundation, # Inc. # # This file is free software; the Free Software Foundation # gives unlimited permission to copy and/or distribute it, # with or without modifications, as long as this notice is preserved. # serial 1 # AM_PROG_INSTALL_SH # ------------------ # Define $install_sh. AC_DEFUN([AM_PROG_INSTALL_SH], [AC_REQUIRE([AM_AUX_DIR_EXPAND])dnl if test x"${install_sh}" != xset; then case $am_aux_dir in *\ * | *\ *) install_sh="\${SHELL} '$am_aux_dir/install-sh'" ;; *) install_sh="\${SHELL} $am_aux_dir/install-sh" esac fi AC_SUBST(install_sh)]) # Copyright (C) 2003, 2005 Free Software Foundation, Inc. # # This file is free software; the Free Software Foundation # gives unlimited permission to copy and/or distribute it, # with or without modifications, as long as this notice is preserved. # serial 2 # Check whether the underlying file-system supports filenames # with a leading dot. For instance MS-DOS doesn't. AC_DEFUN([AM_SET_LEADING_DOT], [rm -rf .tst 2>/dev/null mkdir .tst 2>/dev/null if test -d .tst; then am__leading_dot=. else am__leading_dot=_ fi rmdir .tst 2>/dev/null AC_SUBST([am__leading_dot])]) # Copyright (C) 1996, 1997, 1998, 1999, 2000, 2001, 2002, 2003, 2004, 2005, # 2006 Free Software Foundation, Inc. # # This file is free software; the Free Software Foundation # gives unlimited permission to copy and/or distribute it, # with or without modifications, as long as this notice is preserved. # serial 10 # AM_PATH_LISPDIR # --------------- AC_DEFUN([AM_PATH_LISPDIR], [AC_PREREQ([2.60])dnl # If set to t, that means we are running in a shell under Emacs. # If you have an Emacs named "t", then use the full path. test x"$EMACS" = xt && EMACS= AC_CHECK_PROGS([EMACS], [emacs xemacs], [no]) AC_ARG_VAR([EMACS], [the Emacs editor command]) AC_ARG_VAR([EMACSLOADPATH], [the Emacs library search path]) AC_ARG_WITH([lispdir], [ --with-lispdir override the default lisp directory], [ lispdir="$withval" AC_MSG_CHECKING([where .elc files should go]) AC_MSG_RESULT([$lispdir])], [ AC_CACHE_CHECK([where .elc files should go], [am_cv_lispdir], [ if test $EMACS != "no"; then if test x${lispdir+set} != xset; then # If $EMACS isn't GNU Emacs or XEmacs, this can blow up pretty badly # Some emacsen will start up in interactive mode, requiring C-x C-c to exit, # which is non-obvious for non-emacs users. # Redirecting /dev/null should help a bit; pity we can't detect "broken" # emacsen earlier and avoid running this altogether. AC_RUN_LOG([$EMACS -batch -q -eval '(while load-path (princ (concat (car load-path) "\n")) (setq load-path (cdr load-path)))' conftest.out]) am_cv_lispdir=`sed -n \ -e 's,/$,,' \ -e '/.*\/lib\/x*emacs\/site-lisp$/{s,.*/lib/\(x*emacs/site-lisp\)$,${libdir}/\1,;p;q;}' \ -e '/.*\/share\/x*emacs\/site-lisp$/{s,.*/share/\(x*emacs/site-lisp\),${datarootdir}/\1,;p;q;}' \ conftest.out` rm conftest.out fi fi test -z "$am_cv_lispdir" && am_cv_lispdir='${datadir}/emacs/site-lisp' ]) lispdir="$am_cv_lispdir" ]) AC_SUBST([lispdir]) ])# AM_PATH_LISPDIR AU_DEFUN([ud_PATH_LISPDIR], [AM_PATH_LISPDIR]) # Check to see how 'make' treats includes. -*- Autoconf -*- # Copyright (C) 2001, 2002, 2003, 2005, 2009 Free Software Foundation, Inc. # # This file is free software; the Free Software Foundation # gives unlimited permission to copy and/or distribute it, # with or without modifications, as long as this notice is preserved. # serial 4 # AM_MAKE_INCLUDE() # ----------------- # Check to see how make treats includes. AC_DEFUN([AM_MAKE_INCLUDE], [am_make=${MAKE-make} cat > confinc << 'END' am__doit: @echo this is the am__doit target .PHONY: am__doit END # If we don't find an include directive, just comment out the code. AC_MSG_CHECKING([for style of include used by $am_make]) am__include="#" am__quote= _am_result=none # First try GNU make style include. echo "include confinc" > confmf # Ignore all kinds of additional output from `make'. case `$am_make -s -f confmf 2> /dev/null` in #( *the\ am__doit\ target*) am__include=include am__quote= _am_result=GNU ;; esac # Now try BSD make style include. if test "$am__include" = "#"; then echo '.include "confinc"' > confmf case `$am_make -s -f confmf 2> /dev/null` in #( *the\ am__doit\ target*) am__include=.include am__quote="\"" _am_result=BSD ;; esac fi AC_SUBST([am__include]) AC_SUBST([am__quote]) AC_MSG_RESULT([$_am_result]) rm -f confinc confmf ]) # Fake the existence of programs that GNU maintainers use. -*- Autoconf -*- # Copyright (C) 1997, 1999, 2000, 2001, 2003, 2004, 2005, 2008 # Free Software Foundation, Inc. # # This file is free software; the Free Software Foundation # gives unlimited permission to copy and/or distribute it, # with or without modifications, as long as this notice is preserved. # serial 6 # AM_MISSING_PROG(NAME, PROGRAM) # ------------------------------ AC_DEFUN([AM_MISSING_PROG], [AC_REQUIRE([AM_MISSING_HAS_RUN]) $1=${$1-"${am_missing_run}$2"} AC_SUBST($1)]) # AM_MISSING_HAS_RUN # ------------------ # Define MISSING if not defined so far and test if it supports --run. # If it does, set am_missing_run to use it, otherwise, to nothing. AC_DEFUN([AM_MISSING_HAS_RUN], [AC_REQUIRE([AM_AUX_DIR_EXPAND])dnl AC_REQUIRE_AUX_FILE([missing])dnl if test x"${MISSING+set}" != xset; then case $am_aux_dir in *\ * | *\ *) MISSING="\${SHELL} \"$am_aux_dir/missing\"" ;; *) MISSING="\${SHELL} $am_aux_dir/missing" ;; esac fi # Use eval to expand $SHELL if eval "$MISSING --run true"; then am_missing_run="$MISSING --run " else am_missing_run= AC_MSG_WARN([`missing' script is too old or missing]) fi ]) # Copyright (C) 2003, 2004, 2005, 2006, 2011 Free Software Foundation, # Inc. # # This file is free software; the Free Software Foundation # gives unlimited permission to copy and/or distribute it, # with or without modifications, as long as this notice is preserved. # serial 1 # AM_PROG_MKDIR_P # --------------- # Check for `mkdir -p'. AC_DEFUN([AM_PROG_MKDIR_P], [AC_PREREQ([2.60])dnl AC_REQUIRE([AC_PROG_MKDIR_P])dnl dnl Automake 1.8 to 1.9.6 used to define mkdir_p. We now use MKDIR_P, dnl while keeping a definition of mkdir_p for backward compatibility. dnl @MKDIR_P@ is magic: AC_OUTPUT adjusts its value for each Makefile. dnl However we cannot define mkdir_p as $(MKDIR_P) for the sake of dnl Makefile.ins that do not define MKDIR_P, so we do our own dnl adjustment using top_builddir (which is defined more often than dnl MKDIR_P). AC_SUBST([mkdir_p], ["$MKDIR_P"])dnl case $mkdir_p in [[\\/$]]* | ?:[[\\/]]*) ;; */*) mkdir_p="\$(top_builddir)/$mkdir_p" ;; esac ]) # Helper functions for option handling. -*- Autoconf -*- # Copyright (C) 2001, 2002, 2003, 2005, 2008, 2010 Free Software # Foundation, Inc. # # This file is free software; the Free Software Foundation # gives unlimited permission to copy and/or distribute it, # with or without modifications, as long as this notice is preserved. # serial 5 # _AM_MANGLE_OPTION(NAME) # ----------------------- AC_DEFUN([_AM_MANGLE_OPTION], [[_AM_OPTION_]m4_bpatsubst($1, [[^a-zA-Z0-9_]], [_])]) # _AM_SET_OPTION(NAME) # -------------------- # Set option NAME. Presently that only means defining a flag for this option. AC_DEFUN([_AM_SET_OPTION], [m4_define(_AM_MANGLE_OPTION([$1]), 1)]) # _AM_SET_OPTIONS(OPTIONS) # ------------------------ # OPTIONS is a space-separated list of Automake options. AC_DEFUN([_AM_SET_OPTIONS], [m4_foreach_w([_AM_Option], [$1], [_AM_SET_OPTION(_AM_Option)])]) # _AM_IF_OPTION(OPTION, IF-SET, [IF-NOT-SET]) # ------------------------------------------- # Execute IF-SET if OPTION is set, IF-NOT-SET otherwise. AC_DEFUN([_AM_IF_OPTION], [m4_ifset(_AM_MANGLE_OPTION([$1]), [$2], [$3])]) # Check to make sure that the build environment is sane. -*- Autoconf -*- # Copyright (C) 1996, 1997, 2000, 2001, 2003, 2005, 2008 # Free Software Foundation, Inc. # # This file is free software; the Free Software Foundation # gives unlimited permission to copy and/or distribute it, # with or without modifications, as long as this notice is preserved. # serial 5 # AM_SANITY_CHECK # --------------- AC_DEFUN([AM_SANITY_CHECK], [AC_MSG_CHECKING([whether build environment is sane]) # Just in case sleep 1 echo timestamp > conftest.file # Reject unsafe characters in $srcdir or the absolute working directory # name. Accept space and tab only in the latter. am_lf=' ' case `pwd` in *[[\\\"\#\$\&\'\`$am_lf]]*) AC_MSG_ERROR([unsafe absolute working directory name]);; esac case $srcdir in *[[\\\"\#\$\&\'\`$am_lf\ \ ]]*) AC_MSG_ERROR([unsafe srcdir value: `$srcdir']);; esac # Do `set' in a subshell so we don't clobber the current shell's # arguments. Must try -L first in case configure is actually a # symlink; some systems play weird games with the mod time of symlinks # (eg FreeBSD returns the mod time of the symlink's containing # directory). if ( set X `ls -Lt "$srcdir/configure" conftest.file 2> /dev/null` if test "$[*]" = "X"; then # -L didn't work. set X `ls -t "$srcdir/configure" conftest.file` fi rm -f conftest.file if test "$[*]" != "X $srcdir/configure conftest.file" \ && test "$[*]" != "X conftest.file $srcdir/configure"; then # If neither matched, then we have a broken ls. This can happen # if, for instance, CONFIG_SHELL is bash and it inherits a # broken ls alias from the environment. This has actually # happened. Such a system could not be considered "sane". AC_MSG_ERROR([ls -t appears to fail. Make sure there is not a broken alias in your environment]) fi test "$[2]" = conftest.file ) then # Ok. : else AC_MSG_ERROR([newly created file is older than distributed files! Check your system clock]) fi AC_MSG_RESULT(yes)]) # Copyright (C) 2001, 2003, 2005, 2011 Free Software Foundation, Inc. # # This file is free software; the Free Software Foundation # gives unlimited permission to copy and/or distribute it, # with or without modifications, as long as this notice is preserved. # serial 1 # AM_PROG_INSTALL_STRIP # --------------------- # One issue with vendor `install' (even GNU) is that you can't # specify the program used to strip binaries. This is especially # annoying in cross-compiling environments, where the build's strip # is unlikely to handle the host's binaries. # Fortunately install-sh will honor a STRIPPROG variable, so we # always use install-sh in `make install-strip', and initialize # STRIPPROG with the value of the STRIP variable (set by the user). AC_DEFUN([AM_PROG_INSTALL_STRIP], [AC_REQUIRE([AM_PROG_INSTALL_SH])dnl # Installed binaries are usually stripped using `strip' when the user # run `make install-strip'. However `strip' might not be the right # tool to use in cross-compilation environments, therefore Automake # will honor the `STRIP' environment variable to overrule this program. dnl Don't test for $cross_compiling = yes, because it might be `maybe'. if test "$cross_compiling" != no; then AC_CHECK_TOOL([STRIP], [strip], :) fi INSTALL_STRIP_PROGRAM="\$(install_sh) -c -s" AC_SUBST([INSTALL_STRIP_PROGRAM])]) # Copyright (C) 2006, 2008, 2010 Free Software Foundation, Inc. # # This file is free software; the Free Software Foundation # gives unlimited permission to copy and/or distribute it, # with or without modifications, as long as this notice is preserved. # serial 3 # _AM_SUBST_NOTMAKE(VARIABLE) # --------------------------- # Prevent Automake from outputting VARIABLE = @VARIABLE@ in Makefile.in. # This macro is traced by Automake. AC_DEFUN([_AM_SUBST_NOTMAKE]) # AM_SUBST_NOTMAKE(VARIABLE) # -------------------------- # Public sister of _AM_SUBST_NOTMAKE. AC_DEFUN([AM_SUBST_NOTMAKE], [_AM_SUBST_NOTMAKE($@)]) # Check how to create a tarball. -*- Autoconf -*- # Copyright (C) 2004, 2005, 2012 Free Software Foundation, Inc. # # This file is free software; the Free Software Foundation # gives unlimited permission to copy and/or distribute it, # with or without modifications, as long as this notice is preserved. # serial 2 # _AM_PROG_TAR(FORMAT) # -------------------- # Check how to create a tarball in format FORMAT. # FORMAT should be one of `v7', `ustar', or `pax'. # # Substitute a variable $(am__tar) that is a command # writing to stdout a FORMAT-tarball containing the directory # $tardir. # tardir=directory && $(am__tar) > result.tar # # Substitute a variable $(am__untar) that extract such # a tarball read from stdin. # $(am__untar) < result.tar AC_DEFUN([_AM_PROG_TAR], [# Always define AMTAR for backward compatibility. Yes, it's still used # in the wild :-( We should find a proper way to deprecate it ... AC_SUBST([AMTAR], ['$${TAR-tar}']) m4_if([$1], [v7], [am__tar='$${TAR-tar} chof - "$$tardir"' am__untar='$${TAR-tar} xf -'], [m4_case([$1], [ustar],, [pax],, [m4_fatal([Unknown tar format])]) AC_MSG_CHECKING([how to create a $1 tar archive]) # Loop over all known methods to create a tar archive until one works. _am_tools='gnutar m4_if([$1], [ustar], [plaintar]) pax cpio none' _am_tools=${am_cv_prog_tar_$1-$_am_tools} # Do not fold the above two line into one, because Tru64 sh and # Solaris sh will not grok spaces in the rhs of `-'. for _am_tool in $_am_tools do case $_am_tool in gnutar) for _am_tar in tar gnutar gtar; do AM_RUN_LOG([$_am_tar --version]) && break done am__tar="$_am_tar --format=m4_if([$1], [pax], [posix], [$1]) -chf - "'"$$tardir"' am__tar_="$_am_tar --format=m4_if([$1], [pax], [posix], [$1]) -chf - "'"$tardir"' am__untar="$_am_tar -xf -" ;; plaintar) # Must skip GNU tar: if it does not support --format= it doesn't create # ustar tarball either. (tar --version) >/dev/null 2>&1 && continue am__tar='tar chf - "$$tardir"' am__tar_='tar chf - "$tardir"' am__untar='tar xf -' ;; pax) am__tar='pax -L -x $1 -w "$$tardir"' am__tar_='pax -L -x $1 -w "$tardir"' am__untar='pax -r' ;; cpio) am__tar='find "$$tardir" -print | cpio -o -H $1 -L' am__tar_='find "$tardir" -print | cpio -o -H $1 -L' am__untar='cpio -i -H $1 -d' ;; none) am__tar=false am__tar_=false am__untar=false ;; esac # If the value was cached, stop now. We just wanted to have am__tar # and am__untar set. test -n "${am_cv_prog_tar_$1}" && break # tar/untar a dummy directory, and stop if the command works rm -rf conftest.dir mkdir conftest.dir echo GrepMe > conftest.dir/file AM_RUN_LOG([tardir=conftest.dir && eval $am__tar_ >conftest.tar]) rm -rf conftest.dir if test -s conftest.tar; then AM_RUN_LOG([$am__untar /dev/null 2>&1 && break fi done rm -rf conftest.dir AC_CACHE_VAL([am_cv_prog_tar_$1], [am_cv_prog_tar_$1=$_am_tool]) AC_MSG_RESULT([$am_cv_prog_tar_$1])]) AC_SUBST([am__tar]) AC_SUBST([am__untar]) ]) # _AM_PROG_TAR m4_include([build-aux/bold.m4]) m4_include([build-aux/codeset.m4]) m4_include([build-aux/emacs-pkg.m4]) m4_include([build-aux/emacs-site-start.m4]) m4_include([build-aux/ext_goto.m4]) m4_include([build-aux/gawk.m4]) m4_include([build-aux/gcc.m4]) m4_include([build-aux/gl.m4]) m4_include([build-aux/glib-2.0.m4]) m4_include([build-aux/glut.m4]) m4_include([build-aux/gmp.m4]) m4_include([build-aux/gst-package.m4]) m4_include([build-aux/gtk-2.0.m4]) m4_include([build-aux/iconv.m4]) m4_include([build-aux/lib-ld.m4]) m4_include([build-aux/lib-link.m4]) m4_include([build-aux/lib-prefix.m4]) m4_include([build-aux/lib.m4]) m4_include([build-aux/libc-so-name.m4]) m4_include([build-aux/libtool.m4]) m4_include([build-aux/lightning.m4]) m4_include([build-aux/ln.m4]) m4_include([build-aux/localtime.m4]) m4_include([build-aux/lock.m4]) m4_include([build-aux/long-double.m4]) m4_include([build-aux/lrint.m4]) m4_include([build-aux/ltdl-gst.m4]) m4_include([build-aux/ltoptions.m4]) m4_include([build-aux/ltsugar.m4]) m4_include([build-aux/ltversion.m4]) m4_include([build-aux/lt~obsolete.m4]) m4_include([build-aux/modules.m4]) m4_include([build-aux/pkg.m4]) m4_include([build-aux/poll.m4]) m4_include([build-aux/readline.m4]) m4_include([build-aux/relocatable.m4]) m4_include([build-aux/setenv.m4]) m4_include([build-aux/snprintfv.m4]) m4_include([build-aux/sockets.m4]) m4_include([build-aux/sockpfaf.m4]) m4_include([build-aux/strtoul.m4]) m4_include([build-aux/sync-builtins.m4]) m4_include([build-aux/tcltk.m4]) m4_include([build-aux/version.m4]) m4_include([build-aux/vis-hidden.m4]) m4_include([build-aux/wine.m4]) smalltalk-3.2.5/gst-tool.c0000644000175000017500000003217012123404352012341 00000000000000/*********************************************************************** * * Option handling and dispatching to installed .st scripts * * ***********************************************************************/ /*********************************************************************** * * Copyright 2007, 2008, 2009, 2010 Free Software Foundation, Inc. * Written by Paolo Bonzini. * * This file is part of GNU Smalltalk. * * GNU Smalltalk is free software; you can redistribute it and/or modify it * under the terms of the GNU General Public License as published by the Free * Software Foundation; either version 2, or (at your option) any later * version. * * Linking GNU Smalltalk statically or dynamically with other modules is * making a combined work based on GNU Smalltalk. Thus, the terms and * conditions of the GNU General Public License cover the whole * combination. * * In addition, as a special exception, the Free Software Foundation * give you permission to combine GNU Smalltalk with free software * programs or libraries that are released under the GNU LGPL and with * independent programs running under the GNU Smalltalk virtual machine. * * You may copy and distribute such a system following the terms of the * GNU GPL for GNU Smalltalk and the licenses of the other code * concerned, provided that you include the source code of that other * code when and as the GNU GPL requires distribution of source code. * * Note that people who make modified versions of GNU Smalltalk are not * obligated to grant this special exception for their modified * versions; it is their choice whether to do so. The GNU General * Public License gives permission to release a modified version without * this exception; this exception also makes it possible to release a * modified version which carries forward this exception. * * GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or * FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for * more details. * * You should have received a copy of the GNU General Public License along with * GNU Smalltalk; see the file COPYING. If not, write to the Free Software * Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * ***********************************************************************/ #ifdef HAVE_CONFIG_H #include "config.h" #endif #include "gstpub.h" #include #include #include #include #include #include #ifdef HAVE_UNISTD_H #include #endif char *program_name; const char *kernel_dir; const char *image_file; int flags = GST_NO_TTY; int run_as_daemon; int usage; struct tool { const char *name; const char *script; const char *options; const char *force_opt; mst_Boolean allow_other_arguments; }; const struct tool tools[] = { { "gst-convert", "scripts/Convert.st", "-h|--help --version -q|--quiet -v|-V|--verbose -C|--class: -r|--rule: \ -c|--category: -f|--format: -o|--output: -I|--image-file: \ -F|--output-format: --kernel-directory:", NULL, true }, { "gst-load", "scripts/Load.st", "-h|--help --version -q|--quiet -v|-V|--verbose -n|--dry-run -f|--force \ --start:: -t|--test -I|--image-file: --kernel-directory: \ -i|--rebuild-image", NULL, true }, { "gst-reload", "scripts/Load.st", "-h|--help --version -q|--quiet -v|-V|--verbose -n|--dry-run -f|--force \ --start:: -t|--test -I|--image-file: --kernel-directory: \ -i|--rebuild-image", "--force\0", true }, { "gst-package", "scripts/Package.st", "-h|--help --version -v|-V|--verbose --load --no-load --no-install --uninstall --dist \ --prepare --test -t|--target-directory: --list-files: --list-packages \ --srcdir: --distdir|--destdir: --copy --all-files --vpath -n|--dry-run \ -I|--image-file: --kernel-directory: --update|--download ", NULL, true }, { "gst-sunit", "scripts/Test.st", "-h|--help --version -q|--quiet -v|-V|--verbose -f|--file: -p|--package: \ -I|--image-file: --kernel-directory:", NULL, true }, { "gst-browser", "scripts/Load.st", "-i|--rebuild-image -I|--image-file: --kernel-directory: -v|-V|--verbose", "--dry-run\0--start\0Browser\0", false }, { "gst-blox", "scripts/Load.st", "-i|--rebuild-image -I|--image-file: --kernel-directory: -v|-V|--verbose", "--dry-run\0--start\0BLOXBrowser\0", false }, { "gst-doc", "scripts/GenDoc.st", "-h|--help --version -p|--package: -f|--file: -I|--image-file: \ -n|--namespace: -o|--output: --kernel-directory: -F|--output-format: -v|-V|--verbose", NULL, true }, { "gst-remote", "scripts/Remote.st", "-h|--help --version --daemon --server -p|--port: -f|--file: -e|--eval: \ -l|--login: --package: --start: --stop: --pid --kill --snapshot:: \ -I|--image-file: --kernel-directory: -v|-V|--verbose", NULL, true }, { "gst-profile", "scripts/Profile.st", "-f|--file: -e|--eval: -o|--output: -h|--help --version \ --no-separate-blocks -v|-V|--verbose", NULL, true }, { NULL, NULL, NULL, NULL, false } }; /* An option parser compatible with the one in the Getopt class. Does not support canonical option names, otherwise it is pretty complete. */ struct long_option { char arg; const char *name; struct long_option *next; }; #define OPT_NONE 0 #define OPT_MANDATORY 1 #define OPT_OPTIONAL 2 char short_opts[1 << (sizeof (char) * 8)]; struct long_option *long_opts; const struct tool *tool; void option_error (const char *s, ...) { va_list ap; va_start (ap, s); fprintf (stderr, "%s: ", program_name); vfprintf (stderr, s, ap); fprintf (stderr, "\n"); va_end (ap); exit (1); } void setup_option (char *p, char *end) { int arg = 0; if (*p != '-') abort (); while (*end == ':') { *end-- = '\0'; arg++; } if (arg > 2) abort (); while (p) { unsigned char short_opt = 0; const char *long_opt = NULL; if (*p++ != '-') abort (); if (*p == '-') { ++p; long_opt = strsep (&p, "|"); } else { short_opt = *p++; if (!*p) p = NULL; else if (*p++ != '|') abort (); } if (long_opt) { struct long_option *opt = malloc (sizeof (struct long_option)); opt->name = strdup (long_opt); opt->arg = arg; opt->next = long_opts; long_opts = opt; } else short_opts[(unsigned char) short_opt] = arg; } } void setup_options (const char *str) { char *copy = strdup (str); char *p = copy; memset (short_opts, -1, sizeof (short_opts)); do { while (isspace (*p)) p++; if (*p) { char *begin, *end; begin = strsep (&p, " \t\n"); end = begin + strlen (begin) - 1; setup_option (begin, end); } } while (p && *p); free (copy); } void parse_option (int short_opt, const char *long_opt, const char *arg) { if (!short_opt && !long_opt && !tool->allow_other_arguments) { option_error ("invalid argument '%s'", arg); return; } if (short_opt == 'I' || (long_opt && !strcmp (long_opt, "image-file"))) { if (image_file) option_error ("duplicate --image-file option"); image_file = arg; } if (long_opt && !strcmp (long_opt, "kernel-directory")) { if (kernel_dir) option_error ("duplicate --kernel-directory option"); kernel_dir = arg; } if (short_opt == 'i' || (long_opt && !strcmp (long_opt, "rebuild-image"))) flags |= GST_REBUILD_IMAGE; if (long_opt && !strcmp (long_opt, "daemon")) { #ifdef HAVE_FORK run_as_daemon = 1; #else fprintf (stderr, "Daemon operation not supported."); exit (77); #endif } if (long_opt && !strcmp (long_opt, "version")) usage = 1; if (short_opt == 'h' || (long_opt && !strcmp (long_opt, "help"))) usage = 1; } #ifdef HAVE_FORK static void fork_daemon (void) { int child_pid; #ifdef SIGHUP signal (SIGHUP, SIG_IGN); #endif child_pid = fork(); if (child_pid < 0) { perror("Failed to fork daemon"); exit(1); } /* Stop parent. */ if (child_pid != 0) exit (0); /* Detach and spawn server. Create a new SID for the child process */ #ifdef HAVE_SETSID if (setsid() < 0) { perror("setsid failed"); exit(1); } #endif #ifdef SIGHUP signal (SIGHUP, SIG_DFL); #endif } #endif int parse_short_options (const char *name, const char *arg) { while (*name) { unsigned char short_opt = (unsigned char) *name++; int have_arg = short_opts[short_opt]; if (have_arg == -1) option_error ("invalid option -%c", short_opt); if (have_arg == OPT_NONE || (have_arg == OPT_OPTIONAL && !*name)) parse_option (short_opt, NULL, NULL); else if (*name || arg) { parse_option (short_opt, NULL, *name ? name : arg); return *name ? 1 : 2; } else /* if (have_arg == OPT_MANDATORY) */ option_error ("expected argument for option -%c", short_opt); } return 1; } int parse_long_option (const char *name, const char *arg) { struct long_option *all_opts, *opt = NULL; int num_matches = 0; int len; const char *p = strchr (name, '='); if (!p) len = strlen (name); else len = p++ - name; for (all_opts = long_opts; all_opts; all_opts = all_opts->next) if (!memcmp (name, all_opts->name, len)) { opt = all_opts; if (opt->name[len] == '\0') { /* Exact match! */ num_matches = 1; break; } else num_matches++; } if (!opt) option_error ("invalid option --%.*s", len, name); if (num_matches > 1) option_error ("ambiguous option --%.*s", len, name); if (opt->arg == OPT_NONE && p) option_error ("unexpected argument for option --%s", opt->name); else if (p || opt->arg != OPT_MANDATORY) { parse_option (0, opt->name, p); return 1; } else if (!arg) option_error ("expected argument for option --%s", opt->name); else { parse_option (0, opt->name, arg); return 2; } return 1; } void parse_options (const char **argv) { int at_end = 0; while (*argv) { if (at_end || argv[0][0] != '-' || argv[0][1] == '\0') { parse_option (0, NULL, argv[0]); argv++; } else if (argv[0][1] != '-') argv += parse_short_options (&argv[0][1], argv[1]); else if (argv[0][2] == '\0') { at_end = true; argv++; } else argv += parse_long_option (&argv[0][2], argv[1]); } } int main(int argc, const char **argv) { int smalltalk_argc; const char **smalltalk_argv; const char *executable_name; int i; int result; #ifdef _WIN32 executable_name = strrchr (argv[0], '\\'); if (!executable_name || strchr (executable_name, '/')) executable_name = strrchr (argv[0], '/'); #else executable_name = strrchr (argv[0], '/'); #endif /* _WIN32 */ if (executable_name) executable_name++; else executable_name = argv[0]; /* Check if used in the build tree. */ if (!strcasecmp (executable_name, "gst-tool" EXEEXT) || !strcasecmp (executable_name, "gst-tool" ARGV_EXEEXT) || !strcasecmp (executable_name, "lt-gst-tool" EXEEXT) || !strcasecmp (executable_name, "lt-gst-tool" ARGV_EXEEXT)) { program_name = strdup (argv[1]); flags |= GST_IGNORE_USER_FILES; argv++, argc--; } else { int n = strlen (executable_name); program_name = strdup (executable_name); /* Strip the executable extension if needed. */ if (EXEEXT[0] && n > strlen (EXEEXT) && !strcasecmp (program_name + n - strlen (EXEEXT), EXEEXT)) program_name[n - strlen (EXEEXT)] = 0; } for (i = 0; ; i++) if (!tools[i].name) exit (127); else if (!strcmp (tools[i].name, program_name)) break; tool = &tools[i]; setup_options (tool->options); parse_options (&argv[1]); #ifdef HAVE_FORK if (run_as_daemon && !usage) fork_daemon (); #endif if (tool->force_opt) { const char *p; int n; for (p = tool->force_opt, n = 0; *p; p += strlen (p) + 1) n++; smalltalk_argc = argc + n - 1; smalltalk_argv = alloca (sizeof (char *) * smalltalk_argc); for (p = tool->force_opt, n = 0; *p; p += strlen (p) + 1) smalltalk_argv[n++] = p; memcpy (&smalltalk_argv[n], &argv[1], argc * sizeof (char *)); } else { smalltalk_argc = argc - 1; smalltalk_argv = argv + 1; } #ifdef CMD_LN_S if (!getenv ("LN_S")) setenv ("LN_S", CMD_LN_S, 0); #endif #ifdef CMD_INSTALL if (!getenv ("INSTALL")) setenv ("INSTALL", CMD_INSTALL, 0); #endif #ifdef CMD_ZIP if (!getenv ("XZIP")) setenv ("XZIP", CMD_XZIP, 0); #endif gst_set_var (GST_VERBOSITY, 0); gst_smalltalk_args (smalltalk_argc, smalltalk_argv); gst_set_executable_path (argv[0]); result = gst_initialize (kernel_dir, image_file, flags); if (result != 0) exit (result < 0 ? 1 : result); if (!gst_process_file (tool->script, GST_DIR_KERNEL_SYSTEM)) fprintf (stderr, "%s: Couldn't open kernel file `%s': %s\n", executable_name, tool->script, strerror (errno)); gst_invoke_hook (GST_ABOUT_TO_QUIT); exit (0); } smalltalk-3.2.5/ChangeLog0000644000175000017500000101641412130343734012207 000000000000002013-02-14 Holger Hans Peter Freyther * kernel/StreamOps.st: Override the >>#species selector. * tests/streams.st: Add testcase. * tests/streams.ok: Update the result. 2013-01-29 Holger Hans Peter Freyther * tests/stcompiler.st: Add parsing test. * tests/stcompiler.ok: Update the test result. 2013-01-17 Holger Freyther * kernel/Delay.st: Name the process created. 2013-01-17 Holger Freyther * tests/dates.ok: Fix the testcase to read from the right ReadStream. * tests/dates.st: Update the test result. 2012-10-09 Paolo Bonzini Holger Freyther * kernel/StreamOps.st: Fix previous changeset. * tests/streams.st: New. * tests/streams.ok: New. 2012-10-08 Paolo Bonzini * kernel/StreamOps.st: Ensure "last" is up to date when a stream has reached its end. Reported by Holger Freyther. 2012-10-02 Holger Freyther * tests/stcompiler.st: Add testcase for pragma parsing. * tests/stcompiler.ok: Update the test result. 2012-09-29 Holger Freyther * scripts/Convert.st: Collect all rewrite expressions and parse them with the selected parser. 2012-09-29 Holger Freyther * tests/stcompiler.st: Add testcase for parsing 16rff. * tests/stcompiler.ok: Update the test result. 2012-09-14 Thomas Girard * tests/cobjects.st: Add CBoolean test case for issue#659. * tests/cobjects.ok: Regenerate. * kernel/CObject.st: Add missing CBoolean class>>#type. 2012-09-09 Holger Freyther * tests/stcompiler.st: Add testcase for article. * tests/stcompiler.ok: Update the test result. 2012-09-09 Holger Freyther * kernel/Delay.st: Name the delay process. 2012-09-09 Holger Freyther * kernel/CallinProcess.st: Copy the priority directly. 2012-10-08 Roman * kernel/Iterable.st: Fix #fold: for objects that do not implement #isEmpty. 2012-10-08 Roman * kernel/Link.st: Fail fast on zero or negative indices. 2012-02-22 Paolo Bonzini * kernel/CallinProcess.st: Fix creation of cloned process, reported by Holger Freyther. 2012-02-22 Gwenael Casaccio Paolo Bonzini * kernel/PkgLoader.st: Add support for tag. 2012-07-15 Paolo Bonzini * scripts/Package.st: Disable again backtraces. 2012-06-04 Thomas Girard * tests/cobjects.st: Adapt longLong test case, showing the issue#646. * tests/cobjects.ok: Regenerate. 2012-05-19 Paolo Bonzini * kernel/Delay.st: Switch to nanosecond-precision. * kernel/ProcSched.st: Rename #signal:atMillisecondClockValue: to #signal:atNanosecondClockValue:. 2012-05-19 Paolo Bonzini * libgst/sysdep.h: Rename _gst_init_sysdep_win32 to _gst_init_sysdep_timer. * libgst/sysdep/common/files.c: Likewise. * libgst/sysdep/cygwin/timer.c: Likewise. * libgst/sysdep/win32/timer.c: Likewise. * libgst/sysdep/posix/timer.c: Support POSIX real-time timers. 2012-05-19 Paolo Bonzini * kernel/Delay.st: Use #signal:atMillisecondClockValue:. * kernel/ProcSched.st: Define #signal:atMillisecondClockValue:. 2012-05-19 Paolo Bonzini * kernel/Random.st: Do not use #primMillisecondClock. * kernel/Time.st: Base time on nanoseconds. 2012-05-13 Stefano Lattarini (tiny change) build: don't use obsolescent AM_PROG_CC_STDC and AM_CONFIG_HEADER The Automake-provided macros 'AM_PROG_CC_STDC' and 'AM_CONFIG_HEADER' have been superseded respectively by the Autoconf-provided ones 'AC_PROG_CC' (since October 2002) and 'AC_CONFIG_HEADERS' (since July 2002). Moreover, those obsolescent macros will be removed in the next major Automake version (1.13). Stop using them. * configure.ac (AM_CONFIG_HEADER): Don't use this, ... (AC_CONFIG_HEADERS): ... use this instead. While we are at it, properly quote the argument. * snprintfv/configure.ac (AM_PROG_CC_STDC): Drop this, the invocation to AC_PROG_CC is enough. 2012-03-29 Paolo Bonzini * tests/compiler.st: Add testcase. * tests/compiler.ok: Regenerate. 2012-02-02 Holger Hans Peter Freyther * scripts/Package.st: Scan for new *.star files. 2011-09-25 Holger Hans Peter Freyther * kernel/File.st: Add a to the class. * kernel/PkgLoader.st: Ditto. * kernel/VFS.st: Ditto. 2012-03-01 Paolo Bonzini * kernel/CompildMeth.st: Return self from #makeLiteralsReadOnly. Do not make globals read-only. Reported by Gwenael Casaccio. 2012-02-22 Paolo Bonzini * kernel/LinkedList: Add #first, #last, and improve error on #at:. 2012-02-22 Paolo Bonzini Gwenael Casaccio * tests/processes.st: Add testcase. * tests/processes.ok: Regenerate. 2012-02-02 Paolo Bonzini Gwenael Casaccio * tests/delays.st: Add testcase. * tests/delays.ok: Regenerate. 2012-02-02 Paolo Bonzini * kernel/Process.st: Do not interrupt a terminated process. 2012-01-30 Paolo Bonzini * kernel/Delay.st: Fix previous commit. * tests/delays.st: Add testcase. * tests/delays.ok: Regenerate. 2012-01-21 Gwenael Casaccio * kernel/Delay.st: Reset delay before removing. 2011-12-27 Paolo Bonzini * kernel/CFuncs.st: Add #system:withArguments:. * kernel/VFSZip.st: Use it instead of #%. Reported by Maarten van Beek. * scripts/Package.st: Use it instead of #%. 2011-12-27 Paolo Bonzini * kernel/FilePath.st: Add #withShellEscapes and use it for printing. 2011-12-27 Paolo Bonzini * kernel/CharArray.st: Add #withShellEscapes (and OS-specific workers). 2011-11-28 Paolo Bonzini * scripts/Package.st: Use #symlinkFrom: to create absolute-path symlinks. 2011-11-23 Paolo Bonzini * kernel/AnsiDates.st: Improve #readFrom: to not read ahead too much and parse more formats. Reported by Maarten van Beek. * kernel/Date.st: Improve #readFrom: to not read ahead too much and parse negative years. * kernel/Time.st: Improve #readFrom: to not read ahead too much. * tests/dates.st: Add testcases. * tests/dates.ok: Regenerate. 2011-11-23 Paolo Bonzini * kernel/AnsiDates.st: Fix printing DateTimes with negative fractional offsets. 2011-11-14 Mehul Sanghvi * kernel/CFuncs.st: Add #environ. 2011-11-10 Gwenael Casaccio Paolo Bonzini * kernel/Behavior.st: Add #scopeDictionary. * kernel/Dictionary.st: Add #scopeDictionary. 2011-11-04 Gwenael Casaccio * kernel/RootNamespc.st: Fix #new:. 2011-09-22 Paolo Bonzini * kernel/Delay.st: Restart pending delays when the image restarts. * kernel/Time.st: Make the millisecondClockValue monotonic across image save. 2011-08-24 Gwenael Casaccio * kernel/ObjDumper.st: Fix VersionableObjectProxy. 2011-08-13 Paolo Bonzini * scripts/Remote.st: Move server logic to RemoteServer class. 2011-08-13 Gwenael Casaccio * scripts/Remote.st: Suspend/resume server process across snapshots. 2011-08-13 Paolo Bonzini * scripts/Remote.st: Fix typo in 2fc74b9. 2011-08-13 Paolo Bonzini * kernel/FileDescr.st: Recheck file descriptor state between async and sync polling. 2011-08-13 Paolo Bonzini Mathieu Suen * kernel/FilePath.st: Fix Windows "File fullNameFor: 'C:'". 2011-08-05 Paolo Bonzini * gst-tool.c: Add -i option. 2011-08-03 Paolo Bonzini * kernel/ObjDumper.st: Fix VersionableObjectProxy. Reported by Gwenael Casaccio. 2011-08-01 Mathieu Suen * kernel/CCallable.st: Add #longLong/#uLongLong. * kernel/CObject.st: Add CLongLong and CULongLong. * kernel/CType.st: Add CLongLongType and CULongLongType. * tests/cobjects.ok: Add long long test cases. * tests/cobjects.st: Regenerate. 2011-07-29 Gwenael Casaccio * kernel/AbstNamespc.st: Fix name of #compileAll. 2011-07-27 Paolo Bonzini * kernel/ContextPart.st: Improve 2011-07-15 change. * tests/compiler.ok: Regenerate. 2011-07-15 Paolo Bonzini * kernel/ContextPart.st: Fix off-by-one in accessing ip for currentLine. 2011-07-13 Paolo Bonzini * libgst/sysdep/posix/signals.c: Use pthread_sigmask, not sigprocmask. Suggested by Gwenael Casaccio. 2011-07-04 Paolo Bonzini Gwenael Casaccio * kernel/OrderColl.st: Replace loops with replaceFromToWithStartingAt primitives. * kernel/SortedColl.st: Likewise. 2011-07-04 Gwenael Casaccio * kernel/OrderColl.st: Fix previous commit. 2011-07-04 Paolo Bonzini * kernel/OrderColl.st: Inline #makeRoomFirstFor: and #makeRoomLastFor: when the argument is one. 2011-07-04 Paolo Bonzini * kernel/Float.st: Test against both num - eps and num + eps. * tests/floatmath.st: Add regression test. * tests/floatmath.ok: Regenerate. 2011-06-10 Mathieu Suen * kernel/CType.st: Add methods for equality and hashing. 2011-06-06 Paolo Bonzini * kernel/VFS.st: Fix previous commit. 2011-06-06 Paolo Bonzini * kernel/Collection.st: Add #includesAllOf:. 2011-06-02 Paolo Bonzini * kernel/ObjDumper.st: Call #postLoad on fixed objects. 2011-05-30 Holger Hans Peter Freyther * scripts/Remote.st: Resolve the hostname to an address to be used by Sockets.ServerSocket>>#port:bindTo:. 2011-05-26 Paolo Bonzini * kernel/VFS.st: Fix off-by-one in RecursiveFileWrapper>>#namesDo:. Reported by Gwenael Casaccio. 2011-05-26 Paolo Bonzini * kernel/CharArray.st: Support string keys in #%. * tests/strings.st: Add testcases. * tests/strings.ok: Regenerate. 2011-05-26 Paolo Bonzini * kernel/AnsiDates.st: Fix printing of negative offsets. Reported by Holger Hans Peter Freyther. 2011-05-26 Gwenael Casaccio * kernel/MethodDict.st: Temporarily return Set from MethodDictionary>>#keys. 2011-05-19 Paolo Bonzini * kernel/SysExcept.st: Wrap modifications to #'__terminate' with #makeReadOnly:. 2011-05-19 Paolo Bonzini * kernel/AnsiDates.st: Implement #today sensibly. Reported by Holger Hans Peter Freyther. 2011-05-19 Paolo Bonzini * kernel/AnsiDates.st: Implement #asLocal correctly. * kernel/Time.st: Implement #timezoneBias: helper primitive. 2011-05-18 Paolo Bonzini * tests/compiler.st: Add testcases. * tests/compiler.ok: Regenerate. 2011-04-29 Paolo Bonzini * kernel/Integer.st: Add #printPaddedWith:to:. 2011-04-29 Paolo Bonzini * kernel/FileDescr.st: Fix finalizer. Reported by Holger Hans Peter Freyther. 2011-04-21 Gwenael Casaccio * kernel/CompildMeth.st: Move oldsyntax flag over from the old CompiledMethod in the cCall pragma handlers. 2011-04-12 Holger Hans Peter Freyther * kernel/Delay.st: Add #value:onTimeoutDo:. * kernel/Process.st: Add #signalInterrupt:. * kernel/SysExcept.st: Add TimeoutNotification. * tests/delays.st: Add testcases. * tests/delays.ok: Regenerate. 2011-04-06 Paolo Bonzini * kernel/CType.st: Add #new: and #gcNew:. 2011-04-06 Paolo Bonzini * kernel/SeqCollect.st: Add #size. 2011-03-28 Paolo Bonzini * kernel/FileDescr.st: Report end-of-stream when read/write return 0. 2011-03-24 Paolo Bonzini * tests/intmath.st: Add testcases. * tests/intmath.ok: Regenerate. 2011-03-07 Paolo Bonzini * tests/pools.st: Add broken testcases. 2011-03-07 Paolo Bonzini * kernel/CType.st: Fix #storeOn: for array types. 2011-03-07 Paolo Bonzini * kernel/Autoload.st: Fix declaration of #class for Autoload. 2011-02-28 Paolo Bonzini * kernel/FloatQ.st: Improve precision of FloatQ constants for 113-bit floats. 2011-02-11 Paolo Bonzini * tests/cobjects.ok: Regenerate. * tests/cobjects.st: Add test case for variadic. 2011-02-06 Holger Hans Peter Freyther * tests/stcompiler.ok: Regenerate. * tests/stcompiler.st: Add test case. 2011-02-04 Holger Hans Peter Freyther * tests/testsuite.at: Add the Sockets test. 2011-02-02 Holger Hans Peter Freyther * tests/Makefile.am: Add shape.ok and shape.st to the noinst data 2011-02-02 Holger Hans Peter Freyther * tests/stcompiler.ok: New. * tests/stcompiler.st: New. * tests/testsuite.at: Add STInST compiler tests. * tests/Makefile.am: Add STInST compiler tests. 2011-02-03 Paolo Bonzini * tests/shape.st: Fix for 32-bit compilation. * tests/shape.ok: Regenerate. 2011-01-25 Paolo Bonzini * scripts/Package.st: Fix String<->File confusion with --prepare. 2011-01-15 Paolo Bonzini * kernel/DLD.st: Fix case when the same library is loaded multiple times. 2011-01-14 Gwenael Casaccio * kernel/Class.st: Detect class name conflicting with its namespace. 2011-01-10 Paolo Bonzini * kernel/Autoload.st: Add the ability to plug arbitrary loaders. Suggested by Denis Washington. 2011-01-10 Mathieu Suen * tests/shape.ok: New. * tests/shape.st: New. * tests/testsuite.at: Add it. 2010-12-20 Paolo Bonzini * kernel/Transcript.st: Add #critical:. 2010-12-18 Paolo Bonzini * kernel/OrderColl.st: Add #identityRemove:ifAbsent: and #identityRemove:. * kernel/Delay.st: Use it. Reset the delay after removal. 2010-12-13 Paolo Bonzini * kernel/OrderColl.st: Speed up iteration 2x. 2010-12-13 Paolo Bonzini * kernel/FilePath.st: Remove unused instance variable. Reported by Gwenael Casaccio. 2010-12-09 Paolo Bonzini * kernel/PkgLoader.st: Do not modify "self files". 2010-12-05 Paolo Bonzini * kernel/FileDescr.st: Fix deadlock when reading last byte from a two-way pipe. 2010-12-04 Paolo Bonzini * kernel/PkgLoader.st: Add tags that do not have a matching tag to #files. Do not print tags for files that are already printed with . 2010-12-04 Paolo Bonzini * tests/strings.st: Add testcase. * tests/strings.ok: Regenerate. 2010-11-13 Paolo Bonzini * kernel/Semaphore.st: Fix race. 2010-11-10 Paolo Bonzini * kernel/Delay.st: Remove ActiveDelay, simplify code. 2010-11-10 Paolo Bonzini * kernel/ContextPart.st: Make accesses to out of bounds stack slots safe. 2010-11-10 Paolo Bonzini * kernel/Delay.st: Add #asAbsolute, #isAbsolute. Add #postCopy to make copied delays reusable. 2010-11-10 Paolo Bonzini * kernel/Semaphore.st: Document return value of #wait. Use it to simplify #critical:. * kernel/Delay.st: Add return value from #timedWaitOn:. * testsuite/delays.st: Test return values of #timedWaitOn:. * testsuite/delays.ok: Regenerate. 2010-11-10 Paolo Bonzini * kernel/Delay.st: Add #timedWaitOn:. * testsuite/delays.st: Add testcases. * testsuite/delays.ok: Regenerate. 2010-11-10 Paolo Bonzini * kernel/Delay.st: Fix race. 2010-11-10 Paolo Bonzini * kernel/Delay.st: Add delaySemaphore to detect reentrant usage of a Delay. Change DelayEvent to DelayRequestor throughout, changing it and ActiveDelay to not be an Association anymore. Use #isActive to distinguish between schedule and unschedule requests. 2010-11-10 Paolo Bonzini * kernel/Delay.st: Slight simplification of #wait. 2010-11-08 Paolo Bonzini * kernel/SeqCollect.st: Optimize #atAllPut:. * examples/Bench.st: Use #atAllPut: for array initialization. 2010-11-02 Paolo Bonzini * examples/Bench.st: Increase runtime to keep up with newer computers. 2010-10-24 Paolo Bonzini * kernel/Iterable.st: Add #ifNil:ifNotNilDo: and friends. * kernel/UndefObject.st: Likewise. 2010-10-23 Paolo Bonzini * examples/MiniDebugger.st: Fix and improve process commands. 2010-10-19 Paolo Bonzini * examples/Methods.st: Fix bitrot. 2010-10-17 Holger Hans Peter Freyther * tests/cobject.st: Add client code for ByteArray>>#asCData and String>>#asCData. * tests/cobject.ok: Update the result. 2010-10-17 Paolo Bonzini * kernel/String.st: Document NULL-termination of output of #asCData and #asCData:. 2010-10-17 Paolo Bonzini * kernel/UndefObject.st: Add #inheritsFrom: * scripts/Test.st: Automatically load SUnit. 2010-10-16 Paolo Bonzini * kernel/ByteArray.st: Add #asCData. * kernel/String.st: Add #asCData. 2010-10-16 Paolo Bonzini * scripts/GenDoc.st: Handle warnings from STClassLoader, document all loaded classes rather than only the fully defined ones. 2010-10-15 Paolo Bonzini * kernel/ByteArray.st: Add #castTo:. 2010-10-07 Paolo Bonzini * tests/testsuite.at: Mark packages depending on Iconv as optional. * tests/testsuite: Regenerate. 2010-09-28 Holger Hans Peter Freyther * kernel/FileDescr.st: Fix a typo. 2010-09-28 Holger Hans Peter Freyther * tests/classes.ok: Remove "Recompiling" messages. * tests/mutate.ok: Remove "Recompiling" messages. 2010-09-28 Paolo Bonzini * kernel/Behavior.st: Recompile this class is "removed" is true. Remove #subclassesNeedRecompilation since it's useless now with no "Recompiling" messages. 2010-09-27 Paolo Bonzini * kernel/Behavior.st: Remove "Recompiling" messages. * kernel/CompildMeth.st: Remove "Recompiling" messages. * kernel/Metaclass.st: Remove "Recompiling" messages. 2010-09-25 Paolo Bonzini * kernel/SysExcept.st: Fix duplicate instance variable declaration. 2010-09-25 Paolo Bonzini * kernel/Behavior.st: Fix #instanceVariableNames: to always recompile when needed. Reported by Mathieu Suen. * tests/classes.st: Add testcase. * tests/classes.ok: Regenerate. 2010-09-13 Holger Hand Peter Freyther * tests/strings.st: Tests for String>>asNumber. * tests/strings.ok: Regenerate. 2010-09-13 Paolo Bonzini * tests/cobjects.st: Add CPtr testcase. * tests/cobjects.ok: Regenerate. 2010-08-31 Paolo Bonzini * kernel/Float.st: Correctly print numbers that require extra digits to be distinguished. Also try rounding down to eliminate long sequence of zeros. Reported by Nicolas Petton. * tests/floatmath.st: Add testcases. * tests/floatmath.ok: Regenerate. 2010-08-31 Paolo Bonzini * kernel/Number.st: Read base-10 exponents. 2010-08-05 Paolo Bonzini * kernel/URL.st: Add #scheme:host:path:, fix #scheme:path:. 2010-07-26 Paolo Bonzini * scripts/Remote.st: Fix typo. 2010-06-16 Holger Hans Peter Freyther * kernel/File.st: Remove unused local variable. 2010-06-06 Paolo Bonzini * kernel/CompildCode.st: Implement #= using identity. Reported by Gwenael Casaccio. 2010-06-03 Paolo Bonzini * kernel/PkgLoader.st: Add /usr/share/smalltalk/site-packages. 2010-05-31 Paolo Bonzini * scripts/Package.st: Remove debugging output. Change "git fetch" to "git pull". 2010-05-27 Gwenael Casaccio * kernel/LookupKey.st: Remove value instance variable. 2010-05-25 Paolo Bonzini * kernel/Object.st: Fix error message for storing UnicodeCharacters into Strings. 2010-05-21 Paolo Bonzini * kernel/FileDescr.st: Fix #atEnd for pipes. 2010-05-21 Paolo Bonzini * kernel/DynVariable.st: Reimplement DynamicVariable here. * kernel/ProcEnv.st: Add methods used by DynamicVariable. * kernel/SysExcept.st: Remove old implementation from here. 2010-05-19 Paolo Bonzini * scripts/Remote.st: Gracefully handle #atEnd on the remote socket. 2010-05-03 Holger Hans Peter Freyther * gst-tool.c: Add -v|-V|--verbose to all tools. * scripts/Package.st: Handle the verbose option. * scripts/GenDoc.st: Likewise. * scripts/Profile.st: Likewise. * scripts/Remote.st: Likewise. 2010-04-15 Paolo Bonzini * kernel/Regex.st: Fix printing a MatchingRegexResults. 2010-04-11 Paolo Bonzini * winewrapper.c: Work around spawnl(P_WAIT, "...") and system() not waiting when a Unix program is invoked (see http://bugs.winehq.org/show_bug.cgi?id=22338). 2010-04-11 Paolo Bonzini * scripts/Test.st: Fix help message. 2010-04-11 Paolo Bonzini * kernel/Directory.st: Fix running with no home directory. 2010-04-10 Paolo Bonzini * winewrapper.c: Support Unix to DOS path conversion. Always convert argv[1] to a DOS path. 2010-04-10 Paolo Bonzini * scripts/Package.st: Use File>>#isAbsolute. 2010-04-06 Paolo Bonzini * kernel/Interval.st: Add #copyFrom:to:. 2010-04-06 Paolo Bonzini * kernel/Interval.st: Fix operations on empty interval, improve printing. 2010-04-06 Paolo Bonzini * kernel/DirMessage.st: Add #value:value:. 2010-04-06 Paolo Bonzini * kernel/Number.st: Add #isExact. * kernel/Float.st: Add #isExact. * kernel/Interval.st: Add #isExact. 2010-03-27 Paolo Bonzini * kernel/File.st: Do not check errno unless a system call fails. * kernel/Directory.st: Likewise. * kernel/FileDescr.st: Likewise. Remove useless #...ifFail: keywords. 2010-03-25 Holger Hans Peter Freyther * kernel/Integer.st: Refer to the right parameter of the selectors. 2010-03-25 Paolo Bonzini * kernel/SeqCollect.st: Make #indexOfSubCollection: return true for an empty needle. Against ANSI, but consistent with #startsWith:/#endsWith:. 2010-03-03 Gwenael Casaccio * kernel/ContextPart.st: Fix thinko in #debuggerClass. 2010-03-03 Gwenael Casaccio Paolo Bonzini * kernel/Process.st: Add #detach. * kernel/CallinProcess.st: Add class categories. 2010-02-20 Paolo Bonzini * kernel/AnsiExcept.st: Rename to SysExcept.st, leave only subclasses of Exceptions, move everything else to... * kernel/ExcHandling.st: ... here, dropping instance-based exceptions. * kernel/BlkClosure.st: Adjust for above changes. * packages.xml: Adjust for AnsiExcept.st rename. 2010-02-19 Paolo Bonzini * tests/exceptions.st: Do not use instance-based exceptions. * tests/sets.st: Do not use instance-based exceptions. * tests/exceptions.ok: Regenerate. 2010-02-19 Paolo Bonzini * kernel/CallinProcess.st: Add #detach. * kernel/Process.st: Add #suspendedContext:. 2010-02-19 Paolo Bonzini * kernel/Continuation.st: Remove failed experiment. Causes too many problems with exception handlers and block closures. Since I need this only for the GtkDebugger, and not really need all of it, I'll special case what is really needed. * kernel/Process.st: Likewise. * tests/processes.st: Likewise. * tests/processes.ok: Likewise. 2010-02-18 Paolo Bonzini * kernel/CallinProcess.st: Add a convenience method. 2010-02-18 Paolo Bonzini * kernel/ExcHandling.st: Extract #instantiateDefaultHandler. * kernel/AnsiExcept.st: Override it for UnhandledException. 2010-02-18 Paolo Bonzini * kernel/AnsiExcept.st: Use #instantiateNextHandlerFrom:. * kernel/ExcHandling.st: Likewise. Move #instantiateNextHandler:from: to Signal and rename it. 2010-02-18 Paolo Bonzini * kernel/ExcHandling.st: Small refactoring of Signal part 1, just make the next part more obvious. 2010-02-18 Paolo Bonzini * kernel/AnsiExcept.st: Add InvalidState. * kernel/Continuation.st: Add forking of continuations. * kernel/Process.st: Add forking of processes. * tests/processes.st: Add testcase. * tests/processes.ok: Regenerate. 2010-01-30 Paolo Bonzini * kernel/Collection.st: Add #sorted and #sorted:. * kernel/SeqCollect.st: Add #sorted and #sorted:. * kernel/ArrayColl.st: Add #sorted and #sorted:. * kernel/SortCollect.st: Add #sorted and #sorted:, disable #sort and #sort:. 2010-01-22 Paolo Bonzini * kernel/Collection.st: Error on #anyOne for empty collections. 2010-01-10 Paolo Bonzini * scripts/Package.st: Fix previous patch to Package.st. 2010-01-02 Paolo Bonzini * kernel/SeqCollect.st: Rename #sortBy: to #sort: for Grease compatibility. 2010-01-01 Paolo Bonzini * Update copyright years. 2010-01-01 Gwenael Casaccio * scripts/Package.st: Give an error if no arguments are given. 2010-01-01 Paolo Bonzini * kernel/AnsiDates.st: Add some methods for Grease. * kernel/Bag.st: Likewise. * kernel/Collection.st: Likewise. * kernel/Date.st: Likewise. * kernel/Time.st: Likewise. * kernel/Iterable.st: Add abstract #,. * kernel/SeqCollect.st: Remove #, pushed up to Collection. * kernel/StreamOps.st: Make #, accept a Collection argument. 2009-12-30 Gwenael Casaccio * kernel/PkgLoader.st: Add , use indirect dispatch. 2009-12-30 Paolo Bonzini * kernel/CharArray.st: Fix #subStrings: for Unicode strings. 2009-12-30 Paolo Bonzini * kernel/CharArray.st: Fix ANSItude of #subStrings:. 2009-12-13 Paolo Bonzini * kernel/PkgLoader.st: Push #isDisabled up to PackageInfo. 2009-12-02 Paolo Bonzini * kernel/CompildMeth.st: Add #method. 2009-11-26 Paolo Bonzini * kernel/DateTime.st: Add more creation methods. 2009-11-14 Nicolas Petton (tiny change) * kernel/VFS.st: ArchiveFile>>at: answer nil if fo file found 2009-11-13 Paolo Bonzini * gst-tool.c: Uh-oh. * scripts/Package.st: Uh-oh. 2009-11-13 Paolo Bonzini * gst-tool.c: Add --update/--download. * scripts/Package.st: Add --update. 2009-11-13 Paolo Bonzini * scripts/Package.st: Fix --list-files=Foo --list-files=Bar. 2009-11-13 Paolo Bonzini * kernel/PkgLoader.st: Adjust for downloadable packages. * scripts/Package.st: Refactoring and downloadable packages. 2009-11-13 Paolo Bonzini * kernel/URL.st: Allow + in URL schemes. 2009-11-12 Paolo Bonzini * kernel/AnsiExcept.st: Add DynamicVariable. 2009-11-12 Paolo Bonzini * kernel/Directory.st: Add #prefix and #execPrefix. 2009-11-09 Paolo Bonzini * scripts/Package.st: Fix gst-package when -t is not passed. 2009-11-09 Paolo Bonzini * kernel/PkgLoader.st: Add #packageAt:ifAbsent:. 2009-11-09 Paolo Bonzini * kernel/URL.st: Add #entity. 2009-11-06 Paolo Bonzini * kernel/PkgLoader.st: Add missing bracket. 2009-11-06 Nicolas Petton * example/PackageBuilder.st: Make url optional. 2009-11-05 Paolo Bonzini * kernel/PkgLoader.st: Add #url/#url: accessors. * examples/PackageBuilder.st: Here too. 2009-11-04 Paolo Bonzini * kernel/Number.st: Add abstract #asFraction and (concrete) #asExactFraction. * kernel/Float.st: Return a Fraction from #asExactFraction. * kernel/Fraction.st: Use #asExactFraction for coercion. 2009-11-02 Paolo Bonzini * kernel/Number.st: Fail on "x raisedToInteger: 0". 2009-11-02 Paolo Bonzini * kernel/FloatQ.st: Remove useless override of #raisedTo:. 2009-11-02 Paolo Bonzini * kernel/Float.st: Refuse to hash NaNs. 2009-11-01 Paolo Bonzini * kernel/Float.st: Fix printing floats when an all-nines mantissa is rounded up to 10^n. * tests/floatmath.st: Add regression test. * tests/floatmath.st: Regenerate. 2009-11-01 Paolo Bonzini * tests/compiler.st: Add regression test. 2009-10-28 Lee Duhem Paolo Bonzini * kernel/Behavior.st: Clean up hierarchy printing methods. 2009-10-27 Lee Duhem Paolo Bonzini * kernel/Behavior.st: Adjust method categories, add #formattedSourceStringAt: and #formattedSourceStringAt:ifAbsent:, #lookupAllSelectors:, #printFullHierarchy. * kernel/Collection.st: Add #displayLines. * kernel/Symbol.st: Add #implementors. 2009-10-22 Lee Duhem * kernel/AnsiExcept.st: Add NotFound>>#signal:reason:. * kernel/PkgLoader.st: Specify the reason why the package is not found. 2009-10-22 Lee Duhem * kernel/CCallback.st: Fix comments. * kernel/Object.st: Fix comments. 2009-10-19 Lee Duhem * kernel/Interval.st: Fix wrong send of #step. 2009-10-18 Paolo Bonzini * kernel/FloatQ.st: Fix infinite loop. * tests/floatmath.st: Add testcases. * tests/floatmath.ok: Regenerate. 2009-10-13 Paolo Bonzini * gst-tool.c: Do not save image when starting browsers, let the user do that within the GUI. 2009-10-06 Paolo Bonzini * tests/objects.st: Add #becomeForward: testcase for bug triggered by PetitParser. * tests/objects.ok: Regenerate. 2009-10-05 Paolo Bonzini * kernel/Number.st: Add #asString. 2009-10-05 Paolo Bonzini * kernel/FileDescr.st: Fix #nextPutByte:, reported by Nicolas Petton. 2009-10-04 Paolo Bonzini * kernel/Array.st: Use a primitive for #at:ifAbsent:. * kernel/ByteArray.st: Use a primitive for #at:ifAbsent:. * kernel/OtherArrays.st: Use a primitive for #at:ifAbsent:. * kernel/String.st: Use a primitive for #at:ifAbsent:. * kernel/UniString.st: Use a primitive for #at:ifAbsent:. * kernel/Object.st: Implement helper method for #at:ifAbsent:. 2009-10-04 Paolo Bonzini * kernel/PosStream.st: Implement #upTo: using #indexOf:. 2009-10-04 Paolo Bonzini * kernel/String.st: Use memchr primitive. * kernel/ByteArray.st: Use memchr primitive. 2009-10-03 Paolo Bonzini * kernel/WriteStream.st: Optimize #next:putAll:startingAt:. 2009-10-03 Paolo Bonzini * kernel/Stream.st: Use #nextPutAllOn: for Stream>>#upToEnd, implement Stream>>#contents using #upToEnd. 2009-10-03 Paolo Bonzini * kernel/PosStream.st: Fix #nextPutAllOn:. 2009-09-19 Paolo Bonzini Nicolas Cellier * kernel/Float.st: Add #predecessor and #successor. * tests/floatmath.st: New tests. * tests/floatmath.ok: Regenerate. 2009-09-19 Paolo Bonzini * kernel/URL.st: Add #asString and #resolvePath:. 2009-09-15 Paolo Bonzini * kernel/Generator.st: Use a non-escaping continuation. 2009-09-13 Paolo Bonzini * kernel/Regex.st: Fix. 2009-09-13 Paolo Bonzini * scripts/Convert.st: Add bang at end of squeak evals. 2009-09-11 Paolo Bonzini * kernel/Regex.st: Add #escapeRegex. 2009-09-08 Paolo Bonzini * scripts/Load.st: Fix "gst-load --start A B". 2009-09-07 Paolo Bonzini * scripts/Convert.st: Remove #fileOutHeader override. 2009-09-07 Paolo Bonzini * kernel/Behavior.st: Add shape == #inherit support in nil subclasses and in #setInstanceSpec:instVars:. * kernel/CObject.st: Define #inheritShape instead of #subclass:. Omit irrelevant pragmas. * kernel/Class.st: Add #inheritShape. * kernel/Metaclass.st: Handle inheritShape. 2009-09-04 Paolo Bonzini * gst-tool.c: Add gst-browser, support passing multiple implicit arguments. * scripts/Browser: Delete. 2009-09-03 Paolo Bonzini * scripts/Load.st: Save image before starting packages. 2009-09-03 Paolo Bonzini * tests/compiler.st: Add regression test. * tests/compiler.ok: Regenerate 2009-09-02 Lee Duhem * kernel/ArrayColl.st: Remove unnecessary manual hyphenations. * kernel/Behavior.st: Ditto. * kernel/BlkClosure.st: Ditto. * kernel/CharArray.st: Ditto. * kernel/Object.st: Ditto. * kernel/RunArray.st: Ditto. * kernel/SeqCollect.st: Ditto. * kernel/ValueAdapt.st: Ditto. 2009-09-01 Lee Duhem * scripts/Remote.st: Fix typo in help message 2009-08-25 Paolo Bonzini * scripts/Remote.st: Fix inadvertent commit. 2009-08-24 Paolo Bonzini Nicolas Petton * kernel/Object.st: Add #becomeForward:. * tests/objects.st: Add #becomeForward: tests. * tests/objects.ok: Regenerate. 2009-08-22 Paolo Bonzini * kernel/Dictionary.st: Override #copyAllFrom: to copy associations. Reported by Nicolas Petton. 2009-08-21 Paolo Bonzini * kernel/Delay.st: Use #pause: in IdleProcess. * kernel/ProcSched.st: Return whether to pause for a signal in #idle. 2009-08-21 Paolo Bonzini * kernel/Delay.st: Rename rockBottomPriority to idlePriority. * kernel/ObjMemory.st: Rename rockBottomPriority to idlePriority. * kernel/ProcSched.st: Rename rockBottomPriority to idlePriority. 2009-08-18 Paolo Bonzini * kernel/DLD.st: Add #addLibraryHandle:. 2009-08-04 Paolo Bonzini * kernel/Semaphore.st: Minor change, planning for future changes. 2009-08-01 Stefan Schmiedl * kernel/FilePath.st: Improve commentary. 2009-08-01 Paolo Bonzini * kernel/ProcSched.st: Improve handling of finalizers upon restart. 2009-08-01 Paolo Bonzini * kernel/Delay.st: Initialize here. * kernel/ObjMemory.st: Not here. 2009-07-28 Paolo Bonzini * kernel/AnsiDates.st: Add Duration>>#storeOn: and DateTime>>#storeOn:. 2009-07-28 Paolo Bonzini * main.c: Add git revision number to --version output. 2009-07-27 Paolo Bonzini * scripts/Convert.st: Add Squeak format. Unbreak case when -F is not passed at all. 2009-07-27 Paolo Bonzini * scripts/Convert.st: Support multiple output formats. * gst-tool.c: Add new option. 2009-07-27 Paolo Bonzini * scripts/Convert.st: Refactor emitting of eval. 2009-07-26 Paolo Bonzini * gst-tool.c: Accept overrides from the environment for ZIP etc. * winewrapper.c: New. 2009-07-26 Paolo Bonzini * kernel/FilePath.st: Fix Windows path cases. 2009-07-25 Paolo Bonzini * kernel/AnsiDates.st: Add Duration>>#wait. 2009-07-25 Paolo Bonzini * kernel/Time.st: Simplify millisecond clock since GNU Smalltalk has had LargeIntegers for, ehm, quite some time. 2009-07-25 Paolo Bonzini * kernel/PkgLoader.st: Automatically wrap start and stop scripts with Eval. 2009-07-25 Paolo Bonzini * scripts/Load.st: Fix --start. 2009-07-23 Paolo Bonzini * kernel/Integer.st: Add base-10 methods too. 2009-07-23 Paolo Bonzini * kernel/Integer.st: Implement print-with-padding methods. 2009-07-16 Paolo Bonzini * kernel/Number.st: Don't say +Inf is close to -Inf. 2009-07-16 Paolo Bonzini * kernel/Iterable.st: Remove duplicate method. 2009-07-15 Paolo Bonzini * kernel/ObjDumper.st: Check #atEnd in #load. * tests/objdump.st: Add test. * tests/objdump.ok: Regenerate. 2009-07-15 Stefan Schmiedl * kernel/FileDescr.st: Add forgotten return in #pastEnd. 2009-07-11 Paolo Bonzini * kernel/ExcHandling.st: Make #signalingContext more robust. * tests/exceptions.st: Add regression test. * tests/exceptions.ok: Regenerate. 2009-07-11 Paolo Bonzini * tests/floatmath.st: Stress-test reading pi. * tests/floatmath.ok: Regenerate. 2009-07-11 Paolo Bonzini * tests/compiler.st: Test reading 16r-33.0. * tests/compiler.ok: Regenerate. 2009-07-07 Stefan Schmiedl * scripts/Convert.st: Typo fix. 2009-07-07 Paolo Bonzini Stefan Schmiedl * scripts/Remote.st: Fix order of #evaluate:ifError: block argument. 2009-07-01 Paolo Bonzini * kernel/ProcSched.st: Do lower the priority of the finalization worker. 2009-06-29 Paolo Bonzini * kernel/Integer.st: Add #digitAt:. * kernel/LargeInteger.st: Fix comment. 2009-06-28 Paolo Bonzini Stefan Schmiedl * kernel/CStruct.st: Change #inspect to #examineOn:. * kernel/Collection.st: Change #inspect to #examineOn:. * kernel/CompildCode.st: Change #inspect to #examineOn:. * kernel/Dictionary.st: Change #inspect to #examineOn:. * kernel/Object.st: Change #inspect to #examineOn:, use it for #inspect. * kernel/SeqCollect.st: Change #inspect to #examineOn:. 2009-06-28 Paolo Bonzini * kernel/ExcHandling.st: Add #signalingContext to Signal. 2009-06-22 Paolo Bonzini * kernel/Directory.st: Fix #allFilesMatching:do:. 2009-06-19 Paolo Bonzini * tests/floatmath.st: Eliminate inexact regression test. 2009-06-15 Paolo Bonzini * kernel/Float.st: Eliminate hack for #floorLog: and #ceilingLog: that was inexact for numbers very close to 1. Compute exponent in exact arithmetic while printing. * tests/floatmath.st: Add regression test. * tests/floatmath.ok: Regenerate. 2009-06-15 Paolo Bonzini * kernel/Float.st: Write well-known constants in binary. * kernel/FloatE.st: Likewise. * kernel/FloatQ.st: Likewise. 2009-06-12 Gwanael Casaccio * kernel/CompildCode.st: Fix #= to compare number of literals and of bytecodes. 2009-06-12 Paolo Bonzini * kernel/Float.st: Implement #log:. 2009-06-08 Paolo Bonzini * kernel/LargeInt.st: Fix #asFloat: as reported by Nicolas Cellier. * tests/floatmath.st: Add regression test. * tests/floatmath.ok: Regenerate. 2009-06-08 Paolo Bonzini Nicolas Cellier * kernel/Float.st: Implement #rounded. * kernel/FloatD.st: Implement #half. * kernel/FloatE.st: Implement #half. * kernel/FloatQ.st: Implement #half. * tests/floatmath.st: Add regression test. * tests/floatmath.ok: Regenerate. 2009-06-07 Paolo Bonzini * kernel/StreamOps.st: Remove #segmentFrom:to:. 2009-04-27 Paolo Bonzini * main.c: Fix for real. 2009-04-25 Paolo Bonzini * main.c: Fix newlines at end of --help messages. * scripts/Convert.st: Fix newlines at end of --help messages. * scripts/GenDoc.st: Fix newlines at end of --help messages. * scripts/Load.st: Fix newlines at end of --help messages. * scripts/Package.st: Fix newlines at end of --help messages. * scripts/Profile.st: Fix newlines at end of --help messages. * scripts/Remote.st: Fix newlines at end of --help messages. * scripts/Test.st: Fix newlines at end of --help messages. 2009-03-30 Derek Zhou Paolo Bonzini * scripts/Profile.st: New. * gst-tool.c: Add its options. * kernel/CompildCode.st: Add #method. * kernel/SysDict.st: Add profiling primitive. 2009-03-08 Nicolas Petton * scripts/GenDoc.st: Use FilePath>>#readStream where appropriate. 2009-03-04 Paolo Bonzini * kernel/Transcript.st: Use a RecursionLock, not a Semaphore. 2009-02-02 Paolo Bonzini * kernel/HashedColl.st: Inline and eliminate #findIndex:ifAbsent:. * kernel/WeakObjects.st: Likewise. Suggested by Derek Zhou. 2009-01-29 Paolo Bonzini * main.c: Link help message to home page. 2009-01-25 Paolo Bonzini * kernel/FilePath.st: Always canonicalize / path separators to \ if needed. 2009-01-19 Paolo Bonzini * kernel/ProcEnv.st: Fix ProcessVariable>>#key:. 2009-01-17 Paolo Bonzini * kernel/ProcEnv.st: Add comments for ProcessVariable and make it public. * kernel/Process.st: Make the environment an IdentityDictionary. 2009-01-12 Paolo Bonzini * kernel/Fraction.st: Add #sqrt. 2009-01-12 Paolo Bonzini * kernel/ExcHandling.st: Remove empty "Object extend". 2009-01-09 Paolo Bonzini * kernel/FilePath.st: Clarify semantics of #all, #do:, #namesDo: with respect to . and .. entries. * kernel/VFS.st: Do not pass . and .. in the RecursiveFileWrapper. Pass an entry for the directory itself in #do: and #namesDo:. Unwrap the passed object in #do:. Adjust #mode:, #owner:group:, #lastAccessTime:lastModifyTime:. 2009-01-09 Paolo Bonzini * kernel/Directory.st: Update class comment. 2009-01-08 Paolo Bonzini * kernel/FilePath.st: Add back #fullName. 2009-01-07 Paolo Bonzini * kernel/FilePath.st: Add group/owner setting methods. * kernel/File.st: Add concrete implementation. * kernel/VFS.st: Add recursive group/owner setting method 2009-01-07 Paolo Bonzini * kernel/VFS.st: Add recursive mode and access time setters. 2009-01-07 Paolo Bonzini * kernel/FilePath.st: Add missing #setTimeFor:mtime:atime: method. 2008-12-12 Paolo Bonzini * kernel/SortCollect.st: Fix #percolateUp bug. * tests/arrays.st: Add regression test. * tests/arrays.ok: Regenerate. 2008-11-24 Paolo Bonzini * kernel/IdentDict.st: Override #findIndex:. 2008-11-18 Paolo Bonzini * scripts/Package.st: Fix explanation of the operation of "gst-package -t ~/.st TestPack.star". 2008-10-28 Paolo Bonzini * tests/intmath.st: Run the pi test with only 7 iterations. Suggested by Stephen Woolerton. * tests/intmath.ok: Regenerate. 2008-10-23 Paolo Bonzini * tests/compiler.st: Add regression test. * tests/compiler.ok: Regenerate. 2008-10-22 David M. Cooke (tiny change) * gst-tool.c: Fix for "gst-remote -I". 2008-10-18 Paolo Bonzini * kernel/Rectangle.st: Add both keyword orders. 2008-10-04 Paolo Bonzini * kernel/Rectangle.st: Fix keyword order in #left:top:right:bottom:. 2008-10-03 Paolo Bonzini * kernel/Float.st: Fix possible rounding errors in floorLog/ceilingLog. * tests/floatmath.st: Add regression test. * tests/floatmath.ok: Regenerate. 2008-09-22 Paolo Bonzini * kernel/Stream.st: Add Stream>>#file, use it. * kernel/StreamOps.st: Implement #file when relevant. * kernel/VFSZip.st: Add LimitedStream>>#file. 2008-09-20 Paolo Bonzini * kernel/CObject.st: Snafu. 2008-09-18 Paolo Bonzini * kernel/CObject.st: Add #isNull. * kernel/UndefObject.st: Add #isNull. 2008-09-18 Paolo Bonzini * kernel/Regex.st: Call #cull: for #ifMatched:ifNotMatched: and friends. 2008-09-16 Paolo Bonzini * kernel/Collection.st: Call #cull: for #removeAll:ifAbsent:. * kernel/Dictionary.st: Call #cull: for #removeAllKeys:ifAbsent:, add #removeAllKeysSuchThat:. * kernel/DirMessage: Add #value:. 2008-09-18 Paolo Bonzini * tests/compiler.st: Test that filed-in streams are correctly associated to FileSegments or Strings. * tests/compiler.ok: Regenerate. 2008-09-18 Paolo Bonzini * kernel/Behavior.st: Fix for methodDictionary being nil. * kernel/ClassDesc.st: Fix for methodDictionary being nil. 2008-09-16 Paolo Bonzini * kernel/Behavior.st: Add #sourceCodeAt:ifAbsent:. * kernel/CompildCode.st: Add #sendsToSuper. * kernel/CompildMeth.st: Add #isAbstract and #sendsToSuper. 2008-09-15 Paolo Bonzini * kernel/Number.st: Do not use #skip:. 2008-08-27 Masatake YAMATO * kernel/Character.st: Add `ff'. 2008-08-27 Paolo Bonzini * kernel/PkgLoader.st: Add #/ as a synonym of #fullPathOf:. 2008-08-18 Paolo Bonzini * kernel/AnsiExcept.st: Register an exception handler within UndefinedObject>>#'__terminate'. * kernel/ContextPart.st: Scan the environment context too for #scanBacktraceForAttribute:do:. * tests/processes.st: Add testcase. * tests/processes.ok: Regenerate. 2008-08-17 Paolo Bonzini * scripts/GenDoc.st: Oops. 2008-08-17 Paolo Bonzini * kernel/WeakObjects.st: Implement WeakArray>>#new. 2008-08-16 Thomas Girard * gst-tool.c: Add `-F' argument to gst-doc. * scripts/GenDoc.st: Implement it. Use #publishAll:toLocation:. 2008-08-14 Paolo Bonzini * kernel/Number.st: Add #readFrom:radix:. * kernel/Integer.st: Remove it from here. 2008-08-14 Paolo Bonzini * kernel/DirMessage.st: Add #valueWithArguments:. 2008-08-13 Paolo Bonzini * kernel/AnsiExcept.st: Change superclass of ArithmeticError and MessageNotUnderstood to Error, make them resumable. 2008-08-13 Paolo Bonzini * kernel/AnsiExcept.st: Change #primError: to #resignalAsUnhandled:. Change superclass of Halt to Exception. Move old implementation of #primError: to UnhandledException>>#defaultAction. Add originalException field to UnhandledException. * kernel/ContextPart.st: Remove #unwind and #unwind:. * kernel/ExcHandling.st: Add #resignalAsUnhandled:, remove #primError:. Change #primError: to #resignalAsUnhandled:. * kernel/SysDict.st: Don't use ContextPart class>>#unwind. 2008-08-13 Paolo Bonzini * kernel/Duration.st: Add #readFrom:. 2008-08-13 Paolo Bonzini * kernel/File.st: Move #createDirectories... * kernel/FilePath.st: ... here. Make it succeed if the path exists and is a directory. Add abstract #createDirectory. 2008-08-13 Paolo Bonzini * kernel/Array.st: Fix #storeOn: for subclasses. * kernel/ByteArray.st: Fix #storeOn: for subclasses. 2008-08-13 Paolo Bonzini * kernel/Collection.st: Add #includesAnyOf:. * kernel/SeqCollect.st: Add #copyWithFirst: and #swap:with:. * kernel/SortCollect.st: Prepend `basic' prefix to old methods #swap:with:, #swap:ifBefore:, #swap:ifAfter:. 2008-08-13 Paolo Bonzini * kernel/Time.st: Add constructor methods compatible with Duration. 2008-08-13 Paolo Bonzini * kernel/Behavior.st: Add #indexOfInstVar: and #indexOfInstVar:ifAbsent:. * kernel/Object.st: add #instVarNamed: and #instVarNamed:put:. 2008-08-13 Paolo Bonzini * kernel/ArrayColl.st: Replace #classNameString with #storeString. * kernel/Bag.st: Replace #classNameString with #storeString. * kernel/Collection.st: Replace #classNameString with #storeString. * kernel/Date.st: Replace #classNameString with #storeString. * kernel/Dictionary.st: Replace #classNameString with #storeString. * kernel/HashedColl.st: Replace #classNameString with #storeString. * kernel/Interval.st: Replace #classNameString with #storeString. * kernel/Object.st: Replace #classNameString with #storeString. 2008-08-13 Paolo Bonzini * scripts/Convert.st: Fix class-name filters, which would fail if class-side extensions were present in the input. 2008-08-11 Paolo Bonzini * kernel/BlkContext.st: Make printing more resilient to "bad" contexts. 2008-08-08 Paolo Bonzini * scripts/Package.st: Another empty filename. 2008-08-07 Paolo Bonzini * kernel/ProcSched.st: Document #signal:onInterrupt:. 2008-08-06 Paolo Bonzini * kernel/FilePath.st: Prohibit accessing files with a '' filename. * scripts/Package.st: ... which we were doing here. 2008-08-06 Paolo Bonzini * kernel/PosStream.st: Add #nextAvailable:putAllOn:. * kernel/FileStream.st: Add #nextAvailable:putAllOn:, and remove #nextHunkPutAllOn: and #nextHunk. * kernel/Stream.st: Add #nextAvailable:putAllOn: and #next:putAllOn:, remove #nextHunk, rename #nextHunkPutAllOn: to #nextAvailablePutAllOn: and rewrite it. * kernel/VFSZip.st: Remove #nextHunk. * example/PipeStream.st: Switch to new block stream protocol. 2008-08-05 Paolo Bonzini * kernel/FileDescr.st: Remove #read:... methods, except #read:from:to: which becomes #nextAvailable:into:startingAt:. Remove #write:... methods except #write:from:to: which becomes #next:putAll:startingAt:. Remove #next:, #nextAvailable:, #nextHunk, #nextHunkPutAllOn: to use the superclass version, change #next:into: to #next:into:startingAt:. * kernel/FileStream.st: Change calls to #read:form:to: and #write:from:to: to super sends. Change #nextAvailable: to #nextAvailable:into:startingAt:, #next:into: to #next:into:startingAt:. * kernel/PosStream.st: Add #nextAvailable:into:startingAt:. * kernel/Stream.st: Add #next:into:startingAt: and #nextAvailable:into:startingAt:, use them in #next:, #nextAvailable:, #nextHunk. 2008-08-05 Paolo Bonzini * kernel/Stream.st: Do not use Streams in the default implementation of #nextAvailable:. 2008-08-05 Paolo Bonzini * kernel/FileDescr.st: Move setting atEnd to true into #pastEnd. Add #nextHunkPutAllOn:. Remove duplicate #copyFrom:to: in #nextHunk. * kernel/FileStream.st: Add #nextHunkPutAllOn:. * kernel/Stream.st: Extract pieces of #nextPutAllOn: into #nextHunkPutAllOn:. 2008-08-05 Paolo Bonzini * kernel/FileDescr.st: Implement #nextPutAllOn: and #next:into:. Move #next: and #nextByteArray: here... * kernel/FileStream.st: ... from here. Remove #nextByte, implement #nextPutAllOn: here too. Add #resetBuffer. 2008-08-05 Paolo Bonzini * kernel/FileDescr.st: Make a subclass of Stream. * kernel/FileStream.st: Add here the creation of the buffer. * kernel/PosStream.st: Implement #nextPutAllOn:. Move #skipSeparators... * kernel/StreamOps.st: ... here. 2008-08-05 Paolo Bonzini * kernel/ByteStream.st: Delete. Copy implementation... * kernel/FileDescr.st: ... here ... * kernel/ObjDumper.st: ... and here. * kernel/VFSZip.st: Do not use ByteStream. * tests/objdump.st: Adapt. * tests/objdump.ok: Regenerate. 2008-08-05 Paolo Bonzini * kernel/Stream.st: Implement #nextPutAll: polymorphically. Implement #nextPutAllOn:. * kernel/Iterable.st: Implement #nextPutAllOn:. * kernel/SeqCollect.st: Implement #nextPutAllOn:. * kernel/FileDescr.st: Use #nextPutAllOn: to implement #contents. 2008-08-05 Paolo Bonzini * kernel/Collection.st: Move enumeration methods... * kernel/Iterable.st: ... here. * kernel/StreamOps.st: Change superclass. * kernel/Stream.st: Remove duplicate code. 2008-08-05 Paolo Bonzini * kernel/VFS.st: Change #files to #fileData to avoid clash. * kernel/VFSZip.st: Likewise. 2008-08-04 Paolo Bonzini * kernel/Semaphore.st: Initialize the caught variable in #critical:. 2008-08-04 Paolo Bonzini * kernel/FileDescr.st: Reimplement #next:, move previous implementation to #nextAvailable:. * kernel/FileStream.st: Modify #next:into: to fail if the given number of bytes cannot be read, implement #nextAvailable:. * kernel/Stream.st: Document #nextAvailable: better. 2008-08-01 Paolo Bonzini * kernel/Stream.st: Fix #do: and #linesDo: to check for the right stream before bailing out. * tests/strings.st: Add regression test. * tests/strings.ok: Regenerate. 2008-07-28 Paolo Bonzini * tests/compiler.st: Add tests for parsing unary minus. * tests/compiler.ok: Regenerate. 2008-07-28 Paolo Bonzini * kernel/BlkContext.st: Oops, fix printing of optimized blocks. 2008-07-24 Paolo Bonzini * kernel/BlkContext.st: Include filename in the representation. * kernel/ContextPart.st: Add #currentFileName. * kernel/FileSegment.st: Add #printedFileName. * kernel/MthContext.st: Include filename in the representation. 2008-07-24 Paolo Bonzini * kernel/File.st: Add #isFileSystemPath. * kernel/FilePath.st: Likewise. * kernel/VFS.st: Likewise. 2008-07-24 Paolo Bonzini * kernel/BlkContext.st: Use #currentLineInFile to print contexts. * kernel/CompildCode.st: Add abstract #sourceCodeLinesDelta, discard the first line number bytecode in #sourceCodeMap. * kernel/CompildMeth.st: Add #sourceCodeLinesDelta. * kernel/CompiledBlk.st: Add #sourceCodeLinesDelta and #sourceCodeMap. * kernel/ContextPart.st: Add #currentLineInFile. * kernel/MthContext.st: Use #currentLineInFile to print contexts. 2008-07-23 Paolo Bonzini * kernel/ContextPart.st: Implement #currentLine in an inefficient but correct way. * kernel/BlkContext.st: Include line numbers in the representation. * kernel/MthContext.st: Add #printOn:line:. Use it to print contexts. 2008-07-20 Paolo Bonzini * kernel/CObject.st: Avoid returning a LargeInteger for the hash value. 2008-07-15 Paolo Bonzini * kernel/File.st: Add #isSocket. 2008-07-14 Tony Garnock-Jones * kernel/LargeInt.st: Fix a bootstrapping bug by correcting a send of primReplaceFrom:to:with:startingAt: to replaceFrom:to:with:startingAt: on LargeInteger's use of ByteArrays. 2008-07-14 Paolo Bonzini * kernel/CompildCode.st: Fix printing of superoperators including JUMP_BACK. 2008-07-14 Paolo Bonzini * tests/compiler.st: Add testcase. * tests/compiler.ok: Regenerate. 2008-07-10 Paolo Bonzini * kernel/MappedColl.st: Forward #keysDo: to the map, don't change it to #do:. 2008-07-10 Paolo Bonzini * kernel/Autoload.st: Fix order of metaclass instance variables. 2008-06-05 Paolo Bonzini * examples/CairoDemo.st: Minor changes. 2008-06-01 Paolo Bonzini * tests/Ansi.st: Remove one testcase. 2008-06-01 Paolo Bonzini * kernel/AnsiExcept.st: Adjust call to #instantiateNextHandler:. * kernel/ExcHandling.st: Scan for outer exception handlers from the handler's context. * tests/exceptions.st: Add test case. * tests/exceptions.ok: Regenerate. 2008-06-01 Paolo Bonzini * kernel/FileDescr.st: Make #file call #asFile. * kernel/URL.st: Fix bugs introduced in File rewrite. 2008-06-01 Paolo Bonzini * kernel/URL.st: Fix redirects including a GET query. Add #contents and #readStream. 2008-05-31 Daniele Sciascia * scripts/Convert.st: --quiet was verbose. 2008-05-30 Paolo Bonzini * scripts/Remote.st: Do not crash if getpid not present. 2008-05-30 Paolo Bonzini * gst-tool.c: Remove executable extension if present. 2008-05-30 Paolo Bonzini * examples/CairoBlit.st: Hack together OpenGL support here. 2008-05-30 Paolo Bonzini * kernel/CObject.st: Fix CByte. 2008-05-30 Paolo Bonzini * kernel/CCallable.st: Support both #uint and #uInt spelling (and similarly for #ushort, #uchar, #ulong). 2008-05-28 Paolo Bonzini * kernel/FileStream.st: Use #ensure: in #fileIn:. 2008-05-27 Paolo Bonzini * kernel/SeqCollect.st: Move #join... * kernel/Collection.st: ... here. Use #anyOne. 2008-05-27 Paolo Bonzini * kernel/ByteArray.st: Use VMpr_ArrayedCollection_equal. * kernel/String.st: Use VMpr_ArrayedCollection_equal. 2008-05-27 Paolo Bonzini * kernel/ArrayColl.st: Avoid useless checks. * kernel/SeqCollect.st: Allow replacing zero elements with #replaceFrom:to:withObject:. * tests/Ansi.st: Adjust testsuite. 2008-05-24 Paolo Bonzini * kernel/VFSZip.st: Avoid leaking file descriptors for LimitedStreams. 2008-05-22 Paolo Bonzini * kernel/ArrayColl.st: Remove implementation of #gather:. * kernel/Collection.st: Implement #gather: in terms of #join. 2008-05-22 Paolo Bonzini * kernel/VFS.st: Fix #all on archives. 2008-05-22 Paolo Bonzini * kernel/Array.st: Add #replaceFrom:to:with:startingAt: primitive, simplify #storeOn:. * kernel/ByteArray.st: Rename the primitive. * kernel/LargeInt.st: Rename the primitive. * kernel/String.st: Rename the primitive. 2008-05-22 Paolo Bonzini * kernel/OrderColl.st: Override #first and #last for speed. * kernel/StreamOps.st: Avoid repeatedly colling #first. * kernel/SeqCollect.st: Use #replaceFrom:to:with:startingAt: when doing #replaceFrom:to:with: with a sequenceable collection argument. 2008-05-21 Paolo Bonzini * kernel/CCallback.st: New. * tests/cobject.st: Test closures. 2008-05-21 Paolo Bonzini * kernel/CCallable.st: Split from part of... * kernel/CFuncs.st: ... this. Change superclass to CCallable. * kernel/CompildMeth.st: Accept a descriptor in the class methods that create C call-out method. 2008-05-20 Paolo Bonzini * kernel/CFuncs.st: Always execute #for:returning:withArgs: as Smalltalk code, make #addressOf: a primitive. Add #name:. * kernel/DLD.st: Make overridden #addressOf: a primitive. 2008-05-20 Paolo Bonzini * kernel/CFuncs.st: Make a subclass of CObject. Reorganize creation, avoid overriding #address, remove #tag/#tag:. * kernel/DLD.st: Adjust for above changes. 2008-05-20 Paolo Bonzini * kernel/VFS.st: Add "rm -rf" functionality to RecursiveFileWrapper. * scripts/Package.st: Use it. 2008-05-19 Paolo Bonzini * kernel/Directory.st: Fix when TMPDIR and TEMP are not set. 2008-05-18 Paolo Bonzini * kernel/Integer.st: Fix off-by-one in #binomial:. 2008-05-18 Stephen Compall * tests/pools.st: Test that namespace pragmas work, at least for imports. 2008-05-17 Stephen Compall * kernel/AbstNamespc.st: Add `sharedPools' instvar and methods for it similar to Class's. * kernel/Class.st: Refactor allLocalSharedPoolDictionariesExcept:do: to a list-independent class method. Use it to import shared pools from namespaces as they are visited. * tests/pools.st: Test for namespace shared pools. 2008-05-15 Paolo Bonzini * kernel/FilePath.st: Deal correctly with UNC paths. 2008-05-12 Paolo Bonzini * kernel/BlkClosure.st: Add #cull:, #cull:cull:, #cull:cull:cull:. * kernel/ExcHandling.st: Use it for the exception handlers. * kernel/Object.st: Use it for #ifNotNil:. * tests/blocks.st: New tests. * tests/blocks.ok: Regenerate. 2008-05-11 Paolo Bonzini * examples/xml.sed: Fix for VW7. * scripts/Convert.st: Fix for 2008-02-25 change to exception handling. Apply rewrites to doits too. 2008-05-06 Paolo Bonzini * kernel/CObject.st: Fix typo. 2008-05-06 Paolo Bonzini * kernel/ByteArray.st: Rewrite memory access methods in terms of CObject. * kernel/CObject.st: Add support for ByteArrays as CObject storage. Add #= and #hash. * kernel/CStruct.st: Add #gcNew. * kernel/CType.st: Add #gcNew. * kernel/Object.st: Add #isCObject. * tests/cobjects.st: Add more tests. * tests/cobjects.ok: Update. 2008-05-05 Paolo Bonzini * kernel/CObject.st: Remove odd cases of #at:put:type: and #derefAt:put:type:. 2008-05-05 Paolo Bonzini * examples/CairoBlit.st: New. * examples/CairoDemo.st: New. 2008-04-30 Paolo Bonzini * kernel/Object.st: Inline call to #release. 2008-04-25 Paolo Bonzini Stephen Compall * tests/pools.st: New. * tests/pools.ok: New. * kernel/Class.st: Eliminate only the direct superclass's namespaces from the namespace walk while searching pools, and walk every superclass's pools as well as my own. 2008-04-24 Paolo Bonzini * kernel/ProcEnv.st: Fix thinko in ProcessVariable>>#environment. 2008-04-21 Paolo Bonzini * kernel/Float.st: Define #asCNumber. * kernel/Fraction.st: Define #asCNumber. * kernel/LargeInt.st: Define #asCNumber. * kernel/Number.st: Define #asCNumber. * kernel/ScaledDec.st: Define #asCNumber. * kernel/SmallInt.st: Define #asCNumber. 2008-04-17 Paolo Bonzini * kernel/DLD.st: Don't register DLD with ObjectMemory. * kernel/ObjMemory.st: Execute #returnFromSnapshot callback at high priority, and pass it to DLD before anything else. 2008-04-15 Paolo Bonzini * kernel/CompildMeth.st: Fix error message for undefined C functions. 2008-04-15 Paolo Bonzini * kernel/FilePath.st: Don't prepend a \ if an absolute path is created by #computePathFrom:to: and the destination path has a disk letter in it. 2008-04-10 Paolo Bonzini * kernel/Behavior.st: Put fundamental instance variables at the beginning. 2008-04-08 Stephen Compall * kernel/Class.st: Never answer nil from #sharedPoolDictionaries. * kernel/DeferBinding.st: Remove symmetric nil check. * kernel/Metaclass.st: Likewise. 2008-04-08 Paolo Bonzini * kernel/FilePath.st: Add more abstract methods. Implement #lastAccessTime: and #lastModifyTime:. Add #all. Do not create full paths in #namesMatching:do: for similarity with #namesDo:. * kernel/VFS.st: Add more delegation methods. Implement RecursiveFileWrapper. 2008-04-07 Paolo Bonzini * kernel/Directory.st: Inherit from Object. Remove methods now in File or FilePath. Return File objects from methods that return system parameters. * kernel/File.st: Inherit from FilePath. Remove methods now in FilePath. Do not delegate to a VFSHandler. * kernel/FileDescr.st: Rename instance variable "name" to "file" and adjust. Remove VFS indirection for #open:mode:. Use new 4-argument filein primitive. * kernel/FilePath.st: New. * kernel/FileSegment.st: Support storing a File object in the FileSegment. * kernel/ObjMemory.st: Add indirection for #snapshot: to support passing a File. * kernel/PkgLoader.st: Store files and directories as File objects. Adjust for VFS changes. * kernel/Stream.st: Support 4-argument filein primitive. * kernel/SysDict.st: Use Files more extensively. * kernel/URL.st: Support converting Files to URLs. * kernel/VFS.st: Rewrite. * kernel/VFSZip.st: Rewrite. * scripts/Load.st: Use new File methods. * scripts/Package.st: Adjust for PackageLoader changes. * scripts/Remote.st: Use new File methods. * tests/AnsiLoad.st: Adjust for Directory class>>#working returning a File. 2008-04-07 Paolo Bonzini * kernel/FileDescr.st: Rename fd instance variable to file. 2008-04-01 Paolo Bonzini * kernel/CFuncs.st: Accept Associations too. 2008-04-01 Paolo Bonzini * kernel/CFuncs.st: Change numFixedArgs to tag. Add Smalltalk counterpart of classify_type_symbol. Add setters. Improve #printOn:. * kernel/CompildMeth.st: Extract creation of C call-out methods to new constructor methods on the class side. 2008-04-01 Paolo Bonzini * kernel/Process.st: Rename unwindPoints variable to environment. * kernel/ProcSched.st: Add #processEnvironment. * kernel/ProcEnv.st: New. * tests/processes.st: Test ProcessEnvironment. * tests/processes.ok: New. 2008-04-01 Paolo Bonzini * kernel/AnsiExcept.st: Add UnhandledException. * kernel/ContextPart.st: Rewrite #unwind: to raise UnhandledException. Use #isEnvironment to delimit stack scanning. * kernel/BlkClosure.st: Rewrite #valueWithUnwind to trap UnhandledException. * kernel/MthContext.st: Rewrite #mark. 2008-04-01 Paolo Bonzini * kernel/Regex.st: Sob. 2008-03-31 Paolo Bonzini * kernel/Character.st: Add #*. * kernel/UniChar.st: Add #*. * kernel/Regex.st: Add #asArray for results, accept blocks for substitutions. 2008-03-26 Paolo Bonzini * kernel/VFS.st: Use new variants of stat/lstat that fill in a Smalltalk object. 2008-03-25 Paolo Bonzini * kernel/FileDescr.st: Move #isOpen checks after #ensureReadable and #ensureWritable. 2008-03-25 Paolo Bonzini * kernel/FileDescr.st: Move open checks to #checkError, use #isOpen. 2008-03-24 Paolo Bonzini * kernel/FileDescr.st: Open URLs from #open:mode:ifFail:. 2008-03-19 Paolo Bonzini * kernel/File.st: Return result of evaluating block from File>>#withReadStreamDo: and File>>#withWriteStreamDo:. 2008-03-19 Paolo Bonzini * kernel/File.st: Add #fileIn. 2008-03-19 Paolo Bonzini * kernel/Regex.st: Add #allOccurrencesOfRegex:do:. 2008-03-19 Paolo Bonzini * kernel/FileStream.st: Implement #upTo: like #nextLine. 2008-03-18 Paolo Bonzini * scripts/Remote.st: Implement ssh connections. * gst-tool.c: Add --login to gst-remote. 2008-03-18 Paolo Bonzini * scripts/Remote.st: Use #canRead instead of #available. 2008-03-18 Paolo Bonzini * kernel/FileDescr.st: Add a couple of methods for polymorphism with sockets. 2008-03-18 Paolo Bonzini * kernel/Class.st: Rename #policy/#policy: to #securityPolicy/#securityPolicy:. 2008-03-15 Paolo Bonzini * kernel/Directory.st: Readd Directory class>>#systemKernel. Default Directory class>>#kernel to it. * kernel/FileSegment.st: Change #relocateFrom:to: to #relocate:, and #relocateFrom:to:map: to #relocateFrom:map:. * scripts/Finish.st: Do not call #relocate, strip source code from the last evaluated method to remove its FileSegment from the image. 2008-03-15 Paolo Bonzini * kernel/FileSegment.st: Add a warning that relative FileSegments are always interpreted from the kernel directory, and apply this rule in #fileName. 2008-03-15 Paolo Bonzini * main.c: Fix -S. 2008-03-15 Paolo Bonzini * gst-tool.c: Support relocatable installation. * main.c: Support relocatable installation. 2008-03-11 Paolo Bonzini * scripts/Load.st: Add -i. * gst-tool.c: Likewise. 2008-03-10 Paolo Bonzini * kernel/CharArray.st: Move #startsWith: and #endsWith:... * kernel/SeqCollect.st: ... here. 2008-03-07 Paolo Bonzini * scripts/Remote.st: Exit when the server socket is closed. 2008-03-04 Paolo Bonzini * main.c: Set GST_NO_TTY in Emacs mode. * smalltalk-mode.el.in: Fix smalltalk-bang for old syntax. * gst-mode.el.in: Wrap send-to-smalltalk with save-window-excursion. 2008-02-28 Paolo Bonzini * kernel/ExcHandling.st: Backtrace on the Transcript. * kernel/Transcript.st: Handle errors while printing on the Transcript. 2008-02-27 Paolo Bonzini * gst-tool.c: Fix pasto. * scripts/Remote.st: Change default port to 12345. 2008-02-25 Paolo Bonzini * kernel/PkgLoader.st: Add start/stop script support. * scripts/Load.st: Add start/stop script support. * scripts/Remote.st: Add start/stop script support. * gst-tool.c: Keep options synchronized. 2008-02-25 Paolo Bonzini * kernel/Float.st: The final word on floating-point printing. * tests/floatmath.st: Adjust test vectors. 2008-02-25 Paolo Bonzini * kernel/ScaledDec.st: Make #zero and #one return a number with the same scale as the receiver. 2008-02-25 Paolo Bonzini * kernel/DirMessage.st: Add #receiver:selector:argument:. * kernel/Message.st: Add #selector:argument:. 2008-02-25 Paolo Bonzini * kernel/AnsiExcept.st: Upon executing off the end of an exception handler, always return from the associated #on:do:. 2008-02-22 Paolo Bonzini * kernel/AnsiDates.st: Add #date:time:offset:, #date:time:. * kernel/Date.st: Add #-. * kernel/Dictionary.st: Add #associations. * kernel/Time.st: Add #midnight, #addSeconds:. 2008-02-22 Paolo Bonzini * kernel/Collection.st: Add #gather:. * kernel/ArrayColl.st: Likewise. 2008-02-14 Paolo Bonzini * kernel/AnsiDates.st: Return the date itself in #asUTC if already UTC. 2008-02-13 Paolo Bonzini * kernel/Regex.st: Make Regex a subclass of Object. 2008-02-13 Paolo Bonzini * kernel/File.st: Canonicalize names before finding directory components. 2008-02-12 Paolo Bonzini * gst-tool.c: Rename "struct option". 2008-02-12 Paolo Bonzini * kernel/Collection.st: Add #noneSatisfy:. 2008-02-12 Paolo Bonzini * kernel/SeqCollect.st: Add more methods for Seaside. 2008-02-12 Paolo Bonzini * kernel/Collection.st: Add #count:. * kernel/DirMessage.st: Implement more creation messages. * kernel/Number.st: Modify #coerce: so as to not return Fractions if #readFrom: is called on Number. 2008-02-08 Paolo Bonzini * tests/processes.st: Test that processes with the same priority are scheduled fairly. 2008-02-08 Paolo Bonzini * scripts/Remote.st: Close transcript before quitting, send file contents instead of filing in remotely. 2008-02-08 Paolo Bonzini * scripts/Remote.st: Ignore errors on the server side, to allow a computation to be interrupted by ^C-ing the client-side. 2008-02-08 Paolo Bonzini * scripts/Remote.st: Fix flushing of stdout. 2008-02-08 Paolo Bonzini Mike Anderson * scripts/Remote.st: New. * gst-tool.c: Handle --daemon option. 2008-02-08 Paolo Bonzini * kernel/ExcHandling.st: Print error messages on the Transcript. 2008-02-06 Paolo Bonzini * kernel/SeqCollect.st: Don't fail in #copyUpTo: if the character is not there, return the whole collection instead. 2008-02-05 Paolo Bonzini * kernel/CharArray.st: Add #endsWith:. * kernel/SeqCollect.st: Add #sort and #sortBy:. 2008-02-05 Paolo Bonzini * scripts/Convert.st: Return method from #compile:. 2008-02-01 Paolo Bonzini * kernel/Number.st: Add #to:collect: and #to:by:collect:. * kernel/SeqCollect.st: Add instance side #with:... * kernel/StreamOps.st: Add #with:... and a class implementing it. 2008-01-27 Stephen Compall * kernel/AnsiExcept.st: Comment or private-ize uncommented methods. * kernel/Behavior.st: Likewise. * kernel/BlkClosure.st: Likewise. * kernel/CType.st: Likewise. * kernel/Class.st: Likewise. * kernel/CompildCode.st: Likewise. * kernel/CompildMeth.st: Likewise. * kernel/DLD.st: Likewise. * kernel/DeferBinding.st: Likewise. * kernel/Delay.st: Likewise. * kernel/Directory.st: Likewise. * kernel/File.st: Likewise. * kernel/FileDescr.st: Likewise. * kernel/FileStream.st: Likewise. * kernel/Float.st: Likewise. * kernel/HashedColl.st: Likewise. * kernel/Interval.st: Likewise. * kernel/LookupTable.st: Likewise. * kernel/MappedColl.st: Likewise. * kernel/Metaclass.st: Likewise. * kernel/Number.st: Likewise. * kernel/ObjMemory.st: Likewise. * kernel/PkgLoader.st: Likewise. * kernel/Regex.st: Likewise. * kernel/SysDict.st: Likewise. * kernel/VFS.st: Likewise. * kernel/ValueAdapt.st: Likewise. 2008-01-27 Paolo Bonzini * kernel/SeqCollect.st: Add category to #atRandom. 2008-01-27 Paolo Bonzini * kernel/OrderColl.st: Avoid grow-shrink pingpong. 2008-01-25 Paolo Bonzini * tests/intmath.st: Add LargeInteger testcase from SICP. * tests/intmath.ok: Regenerate. 2008-01-24 Paolo Bonzini * kernel/Regex.st: Do same fix for #allOccurrencesOfRegex:. * tests/strings.st: Add testcases. * tests/strings.ok: Regenerate. 2008-01-24 Paolo Bonzini * kernel/Regex.st: Fix global substitution and tokenization for regexes that can match the empty string. * tests/strings.st: Add testcases. * tests/strings.ok: Regenerate. 2008-01-24 Paolo Bonzini * kernel/Symbol.st: Fix #numArgs for underscores in the symbol, reported by Sam Phillips. 2008-01-23 Paolo Bonzini * kernel/SeqCollect.st: Add #atRandom. 2008-01-23 Paolo Bonzini * kernel/Regex.st: Add #allOccurrencesOfRegex:, remove dead code. 2008-01-22 Paolo Bonzini * kernel/CompildCode.st: Eliminate possible infinite loop in #hash. 2008-01-22 Paolo Bonzini * kernel/Dictionary.st: Rewrite #findElementIndex:. * kernel/WeakObjects.st: Ditto. * kernel/HashedColl.st: Ditto, and store nil before calling it from #rehashObjectsAfter:. * kernel/LookupTable.st: Ditto, and also use it in #whileGrowingAt:put:. 2008-01-18 Paolo Bonzini * scripts/Package.st: Change default -t value for --list-files, reject --destdir and -t for --list-files. 2008-01-18 Paolo Bonzini * scripts/GenDoc.st: Add --namespace, use #fullyDefinedLoadedClasses. 2008-01-18 Paolo Bonzini * scripts/Package.st: Support multiple --list-files options, add --load and --test suboptions to --list-files. 2008-01-18 Paolo Bonzini * kernel/ObjMemory.st: Make #snapshot return the same as #snapshot:. 2008-01-10 Paolo Bonzini * kernel/PkgLoader.st: Fix wrong reference to PackageNotAvailable. 2008-01-07 Paolo Bonzini * kernel/Object.st: Fix #basicPrintNl. 2008-01-07 Paolo Bonzini * kernel/SmallInt.st: Don't coerce for 0 divExact: x. 2008-01-06 Paolo Bonzini * kernel/FileDescr.st: Don't close stdin/stdout/stderr before quitting, but flush them explicitly. * kernel/Process.st: Add #terminateOnQuit to mark the receiver so that it is terminated when ObjectMemory class>>#quit: is sent. 2008-01-03 Tony Garnock-Jones * kernel/CType.st: Fix printing CTypes for CObject subclasses. * tests/cobjects.st: Add testcase. 2007-12-27 Paolo Bonzini * kernel/PkgLoader.st: Move PackageNotAvailable to SystemExceptions namespace. Raise it instead of Error when appropriate. 2007-12-20 Paolo Bonzini * kernel/Collection.st: Add #readStream. 2007-12-10 Paolo Bonzini * kernel/Process.st: Call ProcessorScheduler>>#yield if needed after changing the priority. * tests/exceptions.st: Wait for the process to exit, just to be sure. 2007-12-10 Paolo Bonzini * kernel/Number.st: Fix thinko in #retryInequalityCoercing:, fixing (3 perform: #~= with: 3.0). 2007-12-06 Paolo Bonzini * kernel/BlkClosure.st: Don't modify the stack top in #asContext:. * kernel/ProcSched.st: Remove #changePriorityListOf:to:suspend:. * kernel/Process.st: Implement #suspend with a primitive. Use #resume to restart the process in the right priority list when the priority is changed and the process was not/is not to be suspended. Remove #setPriorityFrom:to:suspend:. * tests/processes.st: Be more robust in running processes to a sync point. Avoid busy waiting which may or may not work depending on the execution order of the process. 2007-11-29 Paolo Bonzini * kernel/FloatD.st: Fix #signByte, add #fromBytes:. * kernel/FloatE.st: Fix #signByte, add #fromBytes:. * kernel/FloatQ.st: Fix #signByte. * tests/floatmath.st: Use #fromBytes:. 2007-11-20 Paolo Bonzini * kernel/Behavior.st: Partially undo change from #updateInstanceVars:shape: to #updateInstanceVars:numInherited:shape:. Add back #updateInstanceVars:shape: and add new #updateInstanceVars:superclass:shape:. Return true from #inheritsFrom: if passed nil. Use new keyword argument to include superclass variables in instVarMap. Reverse direction of instVarMap. Simplify creation of subclasses' instance variable array. Add here #mutate:via: (taken from kernel/Object.st) and use it instead of #mutate:startingAt:newClass:. * kernel/Object.st: Remove #mutate:startingAt:newClass:. * kernel/Metaclass.st: Rename "superclass" argument to "theSuperclass" or "newSuperclass". Call #updateInstanceVars:superclass:shape:. * tests/mutate.st: Add minimal testcase for GTK+ loading failure. Test that class-instance variables are copied around correctly. Test that moving up the hierarchy preserves instance variables. 2007-11-18 Freddie Akeroyd * kernel/VFS.st: Support backslashes as directory separators 2007-11-13 Paolo Bonzini * kernel/Number.st: Coerce #raisedTo: to aNumber's precision if necessary. * kernel/FloatQ.st: Coerce #raisedTo: to FloatQ. 2007-11-08 Paolo Bonzini * tests/ackermann.st: Add "iterative" implementation. 2007-11-07 Paolo Bonzini * examples/Methods.st: Add brackets around compiled methods. * kernel/Behavior.st: Likewise. * tests/compiler.st: Likewise. * tests/objects.st: Likewise. * tests/untrusted.st: Likewise. * unsupported/cint/CToken.st: Likewise. * unsupported/t.st: Likewise. * tests/Ansi.st: Use exception handling. 2007-11-05 Paolo Bonzini * kernel/SeqCollect.st: Move #streamContents:... * kernel/ArrayColl.st: ... here. 2007-11-05 Stephen Compall * examples/JSON.st: Make it return UnicodeStrings if no output encoding is given. 2007-10-23 Paolo Bonzini Robin Redeker * examples/JSON.st: Make it work on Unicode. 2007-10-23 Paolo Bonzini * kernel/CompildMeth.st: Fix return value of #valueWithReceiver:withArguments:, reported by Sam Phillips. 2007-10-22 Paolo Bonzini * kernel/Collection.st: Add #isUnicode. * kernel/CharArray.st: Add an abstract #isUnicode method to class side. * kernel/String.st: Add class-side #isUnicode. * kernel/UniString.st: Add class-side #isUnicode. * kernel/Stream.st: Add #encoding. Forward #isUnicode to the species class. 2007-10-21 Paolo Bonzini * kernel/Behavior.st: Move recompilation methods to CompiledMethod. Move #instanceVariableNames: and related methods from ClassDescription. Change #updateInstanceVars:shape: to #updateInstanceVars:numInherited:shape:. * kernel/Builtins.st: Promote #instanceVariableNames: to Behavior. * kernel/CStruct.st: Compile methods as new syntax. * kernel/ClassDesc.st: Remove #instanceVariableNames: and related methods. * kernel/CompildMeth.st: Add #methodFormattedSourceString, #methodRecompilationSourceString, #isOldSyntax, #noteOldSyntax, #recompile, #recompileNotifying:. Support recompiling methods from both syntaxes. * kernel/Metaclass.st: Change #updateInstanceVars:shape: to #updateInstanceVars:numInherited:shape:. * kernel/UndefObject.st: Add #instSize for polymorphism. * tests/mutate.st: Add new tests on class extension. * tests/mutate.ok: Update test results. 2007-10-18 Paolo Bonzini * kernel/SeqCollect.st: Avoid overlapping array problems in #replaceFrom:to:with:startingAt:. * tests/arrays.st: Add corresponding test. * tests/arrays.ok: Adjust output. 2007-10-16 Paolo Bonzini * kernel/Semaphore.st: Pass the ProcessBeingTerminated exception. * tests/processes.st: Test for bug fixed by the above change. 2007-10-14 Stephen Compall * kernel/Builtins.st: Promote #import: to ClassDescription. * kernel/ClassDesc.st: Document promotion requirement. 2007-10-09 Paolo Bonzini * kernel/CompildMeth.st: Omit sharp sign when printing. 2007-10-08 Paolo Bonzini * kernel/ExcHandling.st: In #pass/#outer, call #activateHandler: on the newly created Signal. Add Signal>>#postCopy. 2007-10-08 Paolo Bonzini * kernel/Delay.st: Rewrite to manipulate Queue entirely in the timing process. 2007-10-06 Robin Redeker * example/JSON.st: Parse strings with whitespace correctly. 2007-10-06 Paolo Bonzini * kernel/ExcHandling.st: Copy exception in #pass/#outer. 2007-10-06 Paolo Bonzini * kernel/AnsiExcept.st: Add semaphore field to ProcessBeingTerminated. Remove #copyFrom:. * kernel/ExcHandling.st: remove #activateOuterHandlerFor:, inline it in the callers. Remove #copyFrom:. * kernel/Process.st: In #terminate, pass semaphore if waiting on one. * kernel/RecursionLock.st: Remove #enter/#exit, inline them since we have to use Semaphore>>#critical:. * kernel/Semaphore.st: Rewrite #critical: to avoid races. * tests/processes.st: Add race condition testcases. 2007-10-06 Paolo Bonzini * kernel/Dictionary.st: Implement #deepCopy and #whileGrowingAt:put:. Use the latter in #collect:. * kernel/LookupTable.st: Remove #deepCopy. 2007-10-05 Paolo Bonzini * scripts/GenDoc.st: Use GSTFileInParser. 2007-10-01 Paolo Bonzini * kernel/RecursionLock.st: Signal waiting semaphore if a process is terminated inside its critical section. * kernel/Semaphore.st: Likewise. 2007-09-27 Paolo Bonzini * examples/Behavior.st: Add #inherit shape. 2007-09-20 Paolo Bonzini * examples/JSON.st: New, by Robin Redeker. 2007-09-19 Paolo Bonzini * kernel/Generator.st: Added #inject:into: on the class side. 2007-09-19 Paolo Bonzini * kernel/LargeInt.st: Avoid #|. 2007-09-17 Paolo Bonzini * kernel/CStruct.st: Use lazy initialization for declaration. Allow replacing an empty declaration. * kernel/Metaclass.st: Mutate the class object if the list of class- instance variables changes. 2007-09-10 Paolo Bonzini * kernel/Association.st: Treat identical values as equal. * kernel/ArrayColl.st: Range-check arguments to #copyFrom:to:. * kernel/SeqCollect.st: Range-check arguments to #copyFrom:to: and #copyFrom:. 2007-09-09 Paolo Bonzini * kernel/Process.st: Don't fail if terminating a terminated process. 2007-09-08 Paolo Bonzini * kernel/PkgLoader.st: Avoid refreshing the list if filing in no package. * scripts/Finish.st: Clear ExecutableFileName before saving. 2007-09-05 Paolo Bonzini * kernel/ArrayColl.st: Guard #join:separatedBy: for empty separator. * kernel/SeqCollect.st: Guard #join:separatedBy: for empty separator. 2007-09-05 Paolo Bonzini * kernel/ArrayColl.st: Add #join:separatedBy:. * kernel/SeqCollect.st: Add #join:separatedBy: and #join:. 2007-09-02 Paolo Bonzini * kernel/UndefObject.st: Add #allSubclasses. * kernel/ExcHandling.st: Add #context. 2007-08-28 Paolo Bonzini * kernel/SeqCollect.st: Properly forward #identityIndexOf: methods. * examples/Methods.st: Add MethodWrapper. 2007-08-28 Paolo Bonzini * kernel/Getopt.st: Fix regex to use \A instead of ^. 2007-08-28 Paolo Bonzini * kernel/Generator.st: Add #on:do:. * kernel/StreamOps.st: Always delegate species, fix PeekableStream>>#peek. 2007-08-24 Paolo Bonzini * kernel/MthContext.st: Print what was not understood. 2007-08-24 Paolo Bonzini * kernel/DeferBinding.st: Add path variable and #resolvePathFrom: method. 2007-08-23 Paolo Bonzini * kernel/ByteStream.st: Remove #nextPutAll:. * kernel/FileDescr.st: Remove #nextPutAll: and #nextPutAllFlush:. * kernel/FileStream.st: Remove #nextPutAll: and #nextPutAllFlush:. * kernel/Stream.st: Use #nextHunk in #nextPutAll:, add #nextPutAllFlush:. * kernel/Transcript.st: Implement #next:putAll:startingAt:. * kernel/WriteStream.st: Likewise. 2007-08-22 Paolo Bonzini * examples/PipeStream.st: New. 2007-08-20 Paolo Bonzini * kernel/CompildCode.st: Regenerate bytecodeInfoTable. * kernel/CompildMeth.st: Fix for new bytecode set. 2007-08-20 Paolo Bonzini * kernel/DeferBinding.st: Fix infinite recursion. 2007-08-20 Paolo Bonzini * kernel/CompildMeth.st: Temporarily disable #isValidCCall. * kernel/DeferBinding.st: New. 2007-08-14 Paolo Bonzini * kernel/SeqCollect.st: Move #writeStream... * kernel/ArrayColl.st: ... here. 2007-08-14 Paolo Bonzini * kernel/Behavior.st: Add back #isBits. 2007-08-13 Paolo Bonzini * kernel/Float.st: Override #floorLog: and #ceilingLog:. 2007-08-13 Paolo Bonzini * kernel/CType.st: Store a VariableBinding inside a CType. 2007-08-13 Paolo Bonzini * kernel/CStruct.st: Remove TypeMap, #computeType:block: and its callees. Use CType>>#from: to make a CType from an array or VariableBinding, and #storeOn: instead of the former second argument of the block. * kernel/CType.st: Add TypeMap and CType>>#from:. Override #storeOn: in CArray and CPtr. * kernel/CompildMeth.st: Use CType>>#from:. 2007-08-13 Paolo Bonzini * kernel/CObject.st: Make #alloc:/#new: not a primitive. Add a defaultType class-instance variable and make the class-side #type default to it; the instance-side #type defaults to the class-side #type. Always return aValue from #at:put:. Remove the instance-side #scalarIndex and rename the class-side method to cObjStoredType. Add missing CString class>>#cObjStoredType. * kernel/CStruct.st: Remove #type override. * kernel/CType.st: Adapt so that the binding is stored in the class variable. Use the #cObjectType accessor consistently. 2007-08-13 Paolo Bonzini * kernel/BindingDict.st: Use a different association than the one in Undeclared, using #become: on it. * kernel/WeakObjects.st: Fix wrong method comments. 2007-08-13 Paolo Bonzini * kernel/WriteStream.st: Fix ANSI testcases. * kernel/RWStream.st: Eliminate useless overrides. 2007-08-12 Paolo Bonzini * kernel/Array.st: Add #storeLiteralOn:. * kernel/Boolean.st: Add #storeLiteralOn:. * kernel/ByteArray.st: Add #storeLiteralOn:. * kernel/Character.st: Add #storeLiteralOn:. * kernel/Float.st: Add #storeLiteralOn:. * kernel/Integer.st: Add #storeLiteralOn:. * kernel/Object.st: Add #storeLiteralOn:. * kernel/ScaledDec.st: Add #storeLiteralOn:. * kernel/String.st: Add #storeLiteralOn:. * kernel/Symbol.st: Add #storeLiteralOn:. * kernel/UndefObject.st: Add #storeLiteralOn:. * kernel/VarBinding.st: Add #storeLiteralOn:. * kernel/Class.st: Add #classPragmas. * kernel/CObject.st: Set shape on subclasses. * kernel/CStruct.st: Add #classPragmas, #declaration, #declaration:. 2007-08-10 Paolo Bonzini * kernel/Number.st: Fix #= vs. #~= blunder. 2007-08-08 Paolo Bonzini Daniele Sciascia * kernel/Class.st: Add #addClassVarName:value:. * scripts/Convert.st: Add GSTParser support. Remove error block. 2007-08-08 Paolo Bonzini * kernel/WriteStream.st: Reimplement #moveToEnd. 2007-08-07 Paolo Bonzini * kernel/VFS.st: Eliminate wrong redefinition of #release. 2007-08-06 Paolo Bonzini * kernel/Behavior.st: Add a (notYetImplemented) parseTreeFor: method. * kernel/PkgLoader.st: Move #fullPathsOf: (new name of #findPathsFor:) and #createNamespace up to PackageInfo, implement #fullPathOf: (new name of #findPathFor:) in StarPackage. * kernel/Namespace.st: Return a string in #nameIn:. * kernel/RootNamespc.st: Return a string in #nameIn:. * kernel/SeqCollect.st: Add #first: and #last:. * kernel/VFSZip.st: Add #copyFrom:to: to LimitedStream. * scripts/GenDoc.st: New. * scripts/Package.st: Fix for renaming of #findPathFor:. * scripts/GenBaseDoc.st: Removed. * scripts/GenLibDoc.st: Removed. 2007-07-23 Paolo Bonzini * kernel/VFSZip.st: Refuse to open for writing. 2007-07-23 Paolo Bonzini * kernel/MthContext.st: Make flags accessors foolproof. * kernel/VFS.st: Don't redirect from %1 for DecodedFileHandler. 2007-07-23 Paolo Bonzini * kernel/VFS.st: Move ZipFileHandler... * kernel/VFSZip.st: ... here. Add StoredZipMember and LimitedStream to provide faster access to uncompressed files. * scripts/Package.st: Do not compress .st and .xml files. 2007-07-23 Paolo Bonzini * kernel/PosStream.st: Use #size in #position: or #basicPosition:. * kernel/RWStream.st: Use PositionableStream definition of #size. 2007-07-23 Paolo Bonzini * kernel/VFS.st: Avoid referring to realFileName, refactoring hierarchy to use a parent VFSHandler instead. Allow creating a special ArchiveMemberHandler in ArchiveFileMember>>#files. Read the ZIP file directory directly from the file. 2007-07-20 Paolo Bonzini * scripts/Package.st: prepare will only be in 2.95c. Honor --dry-run there too. 2007-07-19 Paolo Bonzini * kernel/StreamOps.st: Oops. 2007-07-19 Paolo Bonzini * examples/Publish.st: Fix new syntax support. 2007-07-19 Paolo Bonzini * kernel/CharArray.st: Add #linesDo:. * examples/Publish.st: Remove #linesDo:. 2007-07-19 Paolo Bonzini * kernel/Stream.st: Add #name, implement #fileIn in Smalltalk. * kernel/StreamOps.st: Add #name. 2007-07-18 Paolo Bonzini * scripts/Package.st: add --prepare option. 2007-07-18 Paolo Bonzini * kernel/Directory.st: Return '.' from #pathTo: if appropriate. * kernel/SeqCollect.st: Fix #allButLast and #allButLast:. 2007-07-18 Stephen Compall * kernel/Behavior.st: Rename #compileString: to #primCompile: and document; similarly with #compileString:ifError:. In evaluation methods, remove vacuous "code isMemberOf: String" cases in evaluation methods, remove some inlining, and fix the WriteStream cases. (#compile:, #compile:ifError:): Use #primCompile:. (#evalString:to:, #evalString:to:ifError:): Use #compile: and #compile:ifError:. * kernel/Metaclass.st: Mention #primCompile:. 2007-07-18 Paolo Bonzini * tests/classes.st: Test bad instance variable names. * tests/strings.st: Add nice example from unsupported/Extensn.st. * unsupported/Extensn.st: Delete. * unsupported/IfError.st: Delete. * unsupported/ParseErr.st: Delete. * unsupported/Process1.st: Delete. * unsupported/Process2.st: Rename to Process.st. * unsupported/a.st: Delete. * unsupported/ba.st: Delete. * unsupported/bug.st: Delete. * unsupported/bug2.st: Delete. * unsupported/bug4.st: Delete. * unsupported/er2.st: Delete. * unsupported/self.st: Delete. 2007-07-17 Stephen Compall * kernel/Behavior.st: Use #compileString:ifError: instead of #compileString: in #compile:ifError:. Remove vacuous "code class == String" case in compile methods. 2007-07-17 Paolo Bonzini * kernel/Number.st: Add hyperbolic functions. 2007-07-16 Paolo Bonzini * examples/MiniDebugger.st: Use DebugTools. * kernel/ContextPart.st: Add stub methods for #currentLine and #debugger. * kernel/ExcHandling.st: Use #stopInferior: if the process is already being debugged. * kernel/ProcSched.st: Add #activeDebugger. * kernel/Process.st: Add #debugger. 2007-07-16 Paolo Bonzini * kernel/VFS.st: Set a FileStream's name to the full path. 2007-07-13 Paolo Bonzini * scripts/Convert.st: Add rewriting rules. 2007-07-13 Paolo Bonzini * scripts/Convert.st: Print line number. * kernel/CharArray.st: Add #lines. 2007-07-13 Paolo Bonzini * scripts/Convert.st: Handle command-line options. 2007-07-13 Paolo Bonzini * kernel/Getopt.st: Parse a lone "-" correctly. 2007-07-13 Stephen Compall * kernel/Dictionary.st: Explain that LookupTable is usually a better choice. * kernel/LookupTable.st: Expand the explanation of differences with Dictionary. 2007-07-13 Paolo Bonzini * scripts/Load.st: Add --version. * scripts/Package.st: Add --version. * scripts/Test.st: Add --version. 2007-07-12 Paolo Bonzini * scripts/Convert.st: Give error or warning on undefined classes. 2007-07-12 Paolo Bonzini * kernel/Collection.st: Add a few messages from Squeak. * kernel/SeqCollect.st: Add a few messages from Squeak. 2007-07-12 Paolo Bonzini * tests/compiler.st: Add new testcase. 2007-07-12 Paolo Bonzini * kernel/StreamOps.st: Fix access to PeekableStream. 2007-07-11 Paolo Bonzini * examples/MiniDebugger.st: Fix bitrot. * kernel/CompildCode.st: Fix generation of source code line map. 2007-07-05 Paolo Bonzini * scripts/Load.st: Add --kernel-directory. * scripts/Test.st: Add --kernel-directory. * scripts/Package.st: Add --kernel-directory, --load, --test. * scripts/Browser.st: Move gst-blox.in here, remove shebang. * kernel/File.st: Add #executable and #directory. Quote with " on Windows. 2007-07-05 Paolo Bonzini * kernel/File.st: Fix typo. 2007-07-04 Paolo Bonzini * scripts/Package.st: Stricter option checking. 2007-07-04 Paolo Bonzini * scripts/Package.st: Handle testing within the script. 2007-07-04 Paolo Bonzini * scripts/Package.st: Execute commands within the script. 2007-07-04 Paolo Bonzini * kernel/Directory.st: Add binding for mkdtemp. * kernel/File.st: Add #mode/#mode: * kernel/VFS.st: Add #mode/#mode: and replace isDir variables with it. * packages/vfs/VFS.st: Add support for #mode. 2007-07-03 Paolo Bonzini * kernel/File.st: Create absolute symlink if first component of path differs. * kernel/VFS.st: Don't fail if a symlink's destination does not exist. 2007-07-03 Paolo Bonzini * kernel/VFS.st: Move most of the code in ExternalArchiveFileHandler up to ArchiveFileHandler, modify ExternalArchiveFileHandler to be ZipFileHandler and adjusting it for the new ArchiveFileHandler protocol, add priorities to each class. * kernel/Directory.st: Add #libexec. 2007-07-01 Paolo Bonzini * kernel/File.st: Use VFSHandler>>#fullName. * kernel/FileDescr.st: Add #setName:. * kernel/VFS.st: Add fsName field to ArchiveFileHandler, replacing command in ExternalArchiveFileHandler and making #vfsFor:name: concrete in ArchiveFileHandler. Add #fullName, implement it in ArchiveMemberHandler. Use #setName: when opening files. 2007-07-01 Paolo Bonzini * kernel/Regex.st: add #replaceRegex:with: and #replacingAllRegex:with:. 2007-06-29 Paolo Bonzini * kernel/PkgLoader.st: Turn baseDirectories into a block. Replace #shouldReload: with #refresh:. Support as root tag for PackageDirectory>>#parse:. Include test package files in #allFiles and #allDistFiles. Move #loaded up to PackageInfo. Prepend the owner relativeDirectory to the test package's in #baseDirectories. Add PackageLoader class>>#flush:. * scripts/Finish.st: Flush PackageLoader. * scripts/Package.st: Revamping, including full .star support, --copy and --all-files options to --dist, proper handling of srcdir paths, --vpath option to --list-files. 2007-06-29 Paolo Bonzini * kernel/File.st: Move #pathTo:... * kernel/Directory.st: ... here, and mimic what File>>#pathFrom: does. 2007-06-28 Paolo Bonzini * kernel/VFS.st: Free stat into the RealFileHandler's finalizer. Move responsibility of registering an object with VFS's ObjectMemory handler to the object, rather than doing this in #addToBeFinalized. Fixes race where stat was finalized before an object that was later resurrected. 2007-06-27 Paolo Bonzini * scripts/Convert.st: Emit Namespace creation when needed. Emit form feeds here. 2007-06-26 Paolo Bonzini * scripts/Package.st: Emit shell function prolog here. 2007-06-25 Paolo Bonzini * kernel/AnsiExcept.st: Use #%. * kernel/Behavior.st: Likewise. * kernel/CStruct.st: Likewise. * kernel/Collection.st: Likewise. * kernel/CompildCode.st: Likewise. * kernel/Directory.st: Likewise. * kernel/Float.st: Likewise. * kernel/Object.st: Likewise. * kernel/Semaphore.st: Likewise. * kernel/SeqCollect.st: Likewise. * kernel/VFS.st: Likewise. * tests/AnsiRun.st: Likewise. * tests/ackermann.st: Likewise. * tests/ary3.st: Likewise. * tests/except.st: Likewise. * tests/hash2.st: Likewise. * tests/lists1.st: Likewise. * tests/matrix.st: Likewise. * tests/prodcons.st: Likewise. * tests/sieve.st: Likewise. 2007-06-25 Paolo Bonzini * kernel/CharArray.st: Add #%. 2007-06-25 Paolo Bonzini * kernel/PkgLoader.st: Refactor using Command pattern. 2007-06-24 Paolo Bonzini * kernel/FileDescr.st: Add #readStream. * kernel/PkgLoader.st: Don't load packages that are already loaded. * scripts/Load.st: Merge testing into here. * sunit/SUnitScript.st: Put code for outputting test results here. * scripts/Test.st: Use it. 2007-06-23 Stephen Compall * kernel/PkgLoader.st: Add class TestPackage, reifying its relationship with its owner package, and use it for all tags. 2007-06-22 Paolo Bonzini * kernel/PkgLoader.st: Store info in objects as it is in packages.xml, resolving filenames at load time. Add DisabledPackage. * scripts/Package.st: New. 2007-06-22 Paolo Bonzini * kernel/File.st: Fix fullNameFor: returning root, add printing methods and #with{Read,Write}StreamDo:. * kernel/Directory.st: Support appending empty filename, return newly created directory in #create:. 2007-06-21 Paolo Bonzini * kernel/PkgLoader.st: Add #test to StarPackage. 2007-06-21 Paolo Bonzini * kernel/PkgLoader.st: Set test package after loading the rest. * compiler/STLoader.st: A proxy of a proxy is the proxy itself. 2007-06-21 Paolo Bonzini * kernel/PkgLoader.st: Set namespace for test package. * scripts/Test.st: Check if SUnit is loaded. 2007-06-21 Paolo Bonzini * kernel/PkgLoader.st: Support test packages. * scripts/Test.st: Load the test package if available. 2007-06-21 Paolo Bonzini * kernel/Collection.st: Fix #do:separatedBy:. 2007-06-21 Paolo Bonzini * kernel/File.st: Concatenate starting from an empty string. * kernel/PkgLoader.st: Implement beginning of STAR format. 2007-06-21 Paolo Bonzini * kernel/PkgLoader.st: Extract parsing of a single package in XML format. 2007-06-21 Paolo Bonzini * kernel/PkgLoader.st: Implement composite pattern. 2007-06-19 Freddie Akeroyd Paolo Bonzini * kernel/File.st: Support mixed \ and / in a Windows path. Support a file named "C:" in the middle of a Windows path (?). 2007-06-18 Paolo Bonzini * tests/fileext.st: Run tests using Unix file separator. 2007-06-15 Freddie Akeroyd Paolo Bonzini * kernel/Character.st: Add #isPathSeparator. * kernel/Directory.st: Use it; add special cases for Win32 systems. * kernel/File.st: Use it; add special cases for Win32 systems. * kernel/FileDescr.st: Look for :// instead of :/ to distinguish URIs. 2007-06-13 Paolo Bonzini * kernel/Dictionary.st: Add #findElementIndex:, remove subsumed methods. * kernel/HashedColl.st: Add #findElementIndex:, use it. * kernel/LookupTable.st: Add #findElementIndex:. * kernel/WeakObjects.st: Add #findElementIndex:, remove subsumed methods. 2007-06-11 Stephen Compall * kernel/WeakObjects.st: Reimplement some private and public methods from HashedCollection for WeakSet, removing unneeded HomedAssociations. * kernel/HashedColl.st: Tweak #remove:ifAbsent:'s comment. 2007-06-10 Stephen Compall * examples/Publish.st: Add Basic>>#skipWhiteExceptNewlines:, and use it in Basic>>#reformatComment:, thereby preserving multiple newlines as they appear in comments. * kernel/AbstNamespc.st: Reduce default size. * kernel/RootNamespc.st: Same. 2007-06-10 Stephen Compall * kernel/AbstNamespc.st: Document that #addSubspace: answers the new namespace, also referring to the argument. * kernel/SeqCollect.st: Fix doc example for #join usage. 2007-06-10 Stephen Compall * kernel/WeakObjects.st: Add #includes: to WeakSet, as the inherited method doesn't work with this class. Add #identityIncludes: to WeakIdentitySet. 2007-06-11 Paolo Bonzini * kernel/File.st: Add #pathFrom:to: and symlink creation. * kernel/VFS.st: Add symlink creation. 2007-06-09 Paolo Bonzini * kernel/MappedColl.st: Add back #domain and #map. * scripts/Convert.st: Add example method to convert from Squeak. 2007-06-08 Paolo Bonzini * kernel/Process.st: Terminate GCed processes. 2007-06-08 Paolo Bonzini * scripts/Convert.st: Adjust for new STParsingDriver hierarchy. * scripts/GenLibDoc.st: Likewise. 2007-06-08 Daniele Sciascia * scripts/Convert.st: Track current Namespace for Evals. 2007-06-07 Paolo Bonzini * kernel/AnsiExcept.st: Move TrappableEvent and CoreException to the Kernel namespace. * kernel/ExcHandling.st: Likewise. * kernel/Autoload.st: Likewise for AutoloadClass. * kernel/OtherArrays.st: Likewise for LargeArraySubpart. 2007-06-07 Paolo Bonzini * kernel/AnsiExcept.st: Remove two archaeological mysteries. 2007-06-07 Paolo Bonzini * kernel/StreamOps.st: Add ConcatenatedStream>>#copyFrom:to:. * scripts/Convert.st: Handle comments properly, using #formatAll: and handling toplevel comments independently. 2007-06-07 Paolo Bonzini * kernel/ArrayColl.st: Add #atAll:. * kernel/Dictionary.st: Add #atAll:. * kernel/SeqCollect.st: Add #atAll:. * kernel/MappedColl.st: Add #atAll:, remove #domain/#map accessors, rewrite #select:/#collect:/#reject:. 2007-06-06 Stephen Compall * kernel/Collection.st: Add #join: class method. * kernel/ArrayColl.st: Specialize. * kernel/SeqCollect.st: Add #join method. 2007-06-06 Paolo Bonzini * kernel/Continuation.st: Moved Continuation class from examples, practically rewriting it in the meanwhile. * kernel/Generator.st: Moved from examples. 2007-06-05 Paolo Bonzini * kernel/FileDescr.st: Add #shutdown. * kernel/Stream.st: Wrap #linesDo: and #do: in an exception handler. * kernel/VFS.st: Use #linesDo:. 2007-06-04 Paolo Bonzini * examples/Continuations.st: Adopt definitive API. * examples/Gen3.st: Use Continuation>>#callCC, much faster. Rename to Generator.st. * examples/Generator.st: Rename to Gen3.st. * kernel/ContextPart.st: Move the continuations example's #copyStack method here, as #deepCopy. 2007-06-01 Paolo Bonzini * scripts/GenLibDoc.st: Don't load examples/StreamFilter.st. * examples/StreamFilter.st: Move... * kernel/StreamOps.st: ... here. Clean up, add PeekableStream. Move the Stream subclasses into the Kernel namespace. * examples/Generator.st: Fix #peekFor: to return false at end of stream. * examples/Gen2.st: Fix #peekFor: to return false at end of stream. * examples/Gen3.st: Fix #peekFor: to return false at end of stream. * kernel/DLD.st: Move RoundRobinStream into the Kernel namespace. 2007-06-01 Paolo Bonzini * scripts/Getopt.st: New. * scripts/Load.st: Add (and ignore) --test and --image-file. * scripts/Test.st: Add (and ignore) --image-file. 2007-05-31 Paolo Bonzini * kernel/Object.st: Remove stale method. 2007-05-31 Paolo Bonzini * examples/Generator.st: Fix bug. * examples/Gen2.st: Fix bug. * examples/Gen3.st: Another variation on Generators, this time continuation based (as funny as the context-based one, as fast as the process-based one). * examples/StreamFilter.st: Add cute Sieve of Erathostenes example. * examples/Continuations.st: Add more tests, add #escape/#escapeDo:. 2007-05-31 Paolo Bonzini * examples/Continuations.st: Add more funny stuff. 2007-05-31 Paolo Bonzini * kernel/BindingDict.st: Check for capacity in #copyEmpty:, add #copyEmptyForCollect: * kernel/Collection.st: Add #copyEmptyForCollect:. * kernel/SortCollect.st: Add #copyEmptyForCollect:. * examples/LazyCollection.st: Add #readStream to the ArrayedCollection proxy, don't use a stream when transforming the result of #collect: into a collection. 2007-05-30 Paolo Bonzini * examples/Generator.st: Use same example as Gen2.st. * examples/Gen2.st: Provide same API as Generator.st. 2007-05-29 Paolo Bonzini * examples/gdbm-c.st: Fix 64-bit cleanliness. 2007-05-29 Paolo Bonzini * tests/geometry.st: Improve numerical stability. 2007-05-28 Paolo Bonzini * kernel/LargeInt.st: Fix division when GMP is absent. 2007-05-26 Paolo Bonzini * kernel/Number.st: Change #asScaledDecimal:scale: to #asScaledDecimal:radix:scale:. 2007-05-25 Paolo Bonzini * kernel/Behavior.st: Support nil superclass more thoroughly. * kernel/Builtins.st: Move #instanceVariableNames: to ClassDescription. * kernel/Float.st: Print exponent for 1.0e/1.0q. The zillionth printing bug. * kernel/ScaledDec.st: Remove initial space. 2007-05-25 Daniele Sciascia * scripts/Convert.st: New. 2007-05-25 Paolo Bonzini * kernel/Class.st: Require Parser to file out. * kernel/ClassDesc.st: Require Parser to file out. 2007-05-25 Paolo Bonzini * kernel/UndefObject.st: Fix bug in #subclass: * kernel/Metaclass.st: Fix bug in sending #subclass: to nil 2007-05-24 Paolo Bonzini * tests/floatmath.st: Test printing on hexadecimal patterns. 2007-05-24 Paolo Bonzini * examples/gdbmtests.st: Remove created files. 2007-05-24 Paolo Bonzini * kernel/Behavior.st: Add #shape:. Support #word shape. * kernel/Builtins.st: Add #shape: and instanceVariableNames: for Behavior. * kernel/Class.st: Remove #shape:. Use #word shape. * kernel/Metaclass.st: Support #word shape. * kernel/UndefObject.st: Use #word shape. 2007-05-24 Paolo Bonzini * kernel/Collection.st: Don't use #basicSize in #copyWith:. * kernel/Dictionary.st: Replace #primSize with #capacity. * kernel/HashedColl.st: Replace #primSize with #capacity. * kernel/LookupTable.st: Replace #primSize with #capacity. 2007-05-24 Paolo Bonzini * scripts/Test.st: Fix error output. 2007-05-24 Paolo Bonzini * kernel/Float.st: Use rational arithmetic to print Floats. 2007-05-23 Paolo Bonzini * kernel/Class.st: Don't use TokenStream. * kernel/Metaclass.st: Don't use TokenStream. * kernel/TokenStream.st: Move it... * examples/TokenStream.st: ... here. 2007-05-22 Paolo Bonzini * kernel/Fraction.st: Fix multiplication/division by zero. * numerics/Basic.st: Fix rounding. 2007-05-22 Paolo Bonzini * numerics/NumericsAdds.st: Make all tests pass. * numerics/NumericsTests.st: Update usage of SUnit logging API. 2007-05-21 Paolo Bonzini * examples/Continuations.st: Add the Amb class from seaside and related SUnit tests. 2007-05-21 Paolo Bonzini * examples/gdbm-c.st: Fix finalization bug. Move tests from here... * examples/gdbm.st: ... and here... * examples/gdbmtests.st: ... to here. 2007-05-21 Paolo Bonzini * kernel/PkgLoader.st: Add public #fileIn method to Package. 2007-05-21 Paolo Bonzini * examples/md5tests.st: New. 2007-05-18 Stephen Compall * examples/zlibtests.st: New file split from examples/zlib.st. Convert to an SUnit test. 2007-05-18 Paolo Bonzini * scripts/Load.st: Rewrite. * scripts/Test.st: Rewrite. * scripts/Reload.st: Replace with... * scripts/gst-reload.sh: ... this script. 2007-05-18 Paolo Bonzini * kernel/PipeStream.st: New. * kernel/zlib.st: Use it. 2007-05-18 Paolo Bonzini * kernel/ByteStream.st: Support #nextPutAll: of Streams into Streams. * kernel/Collection.st: Add #isSequenceable. * kernel/FileDescr.st: Add #next:putAll:startingAt:. Support #nextPutAll: of Streams into Streams. Fix #next: * kernel/FileStream.st: Support #nextPutAll: of Streams into Streams. * kernel/SeqCollect.st: Add #isSequenceable. * kernel/Stream.st: Add #isSequenceable. Support #nextPutAll: of Streams into Streams. 2007-05-17 Paolo Bonzini * kernel/PosStream.st: Fix comment of #species. * kernel/Stream.st: Fix #nextHunk. * examples/zlib.c: New. * examples/zlib.st: New. 2007-05-14 Paolo Bonzini * kernel/Behavior.st: Fix #kindOfSubclass. 2007-04-17 Paolo Bonzini * kernel/Behavior.st: Move Class methods... * kernel/Class.st: ... here. 2007-04-17 Paolo Bonzini * examples/Publish.st: Accept new syntax. 2007-04-17 Paolo Bonzini * kernel/Builtins.st: Convert to new syntax. 2007-04-17 Paolo Bonzini * kernel/Builtins.st: Move most builtins... * kernel/AbstNamespc.st: ...here. * kernel/ArrayColl.st: ... and here, * kernel/Behavior.st: ... and here, * kernel/BlkClosure.st: ... and here, * kernel/ByteArray.st: ... and here, * kernel/CFuncs.st: ... and here, * kernel/CObject.st: ... and here, * kernel/CharArray.st: ... and here, * kernel/Character.st: ... and here, * kernel/CompildCode.st: ... and here, * kernel/CompildMeth.st: ... and here, * kernel/CompiledBlk.st: ... and here, * kernel/ContextPart.st: ... and here, * kernel/FileDescr.st: ... and here, * kernel/Float.st: ... and here, * kernel/FloatD.st: ... and here, * kernel/FloatE.st: ... and here, * kernel/FloatQ.st: ... and here, * kernel/HashedColl.st: ... and here, * kernel/LargeInt.st: ... and here, * kernel/Memory.st: ... and here, * kernel/Namespace.st: ... and here, * kernel/ObjMemory.st: ... and here, * kernel/Object.st: ... and here, * kernel/ProcSched.st: ... and here, * kernel/Process.st: ... and here, * kernel/Semaphore.st: ... and here, * kernel/SmallInt.st: ... and here, * kernel/Stream.st: ... and here, * kernel/String.st: ... and here, * kernel/Symbol.st: ... and here, * kernel/SysDict.st: ... and here, * kernel/Time.st: ... and here, * kernel/UniChar.st: ... and here, * kernel/UniString.st: ... and here, 2007-04-17 Paolo Bonzini * tests/mutate.st: Finish converting to new syntax. 2007-04-11 Paolo Bonzini Thomas Girard * libgst/vm.def: Fix pipelining typo. * libgst/interp-bc.inl: Fix pipelining typo. 2007-04-11 Paolo Bonzini * tests/heapsort.st: Use class variables. * tests/random-bench.st: Use class variables. 2007-04-11 Paolo Bonzini * kernel/ClassDesc.st: Add #import:. * tests/blocks.st: Convert to new syntax. * tests/chars.st: Convert to new syntax. * tests/classes.st: Convert to new syntax. * tests/cobjects.st: Convert to new syntax. * tests/compiler.st: Convert to new syntax. * tests/dates.st: Convert to new syntax. * tests/delays.st: Convert to new syntax. * tests/except.st: Convert to new syntax. * tests/exceptions.st: Convert to new syntax. * tests/fibo.st: Convert to new syntax. * tests/fileext.st: Convert to new syntax. * tests/floatmath.st: Convert to new syntax. * tests/geometry.st: Convert to new syntax. * tests/getopt.st: Convert to new syntax. * tests/hash.st: Convert to new syntax. * tests/hash2.st: Convert to new syntax. * tests/heapsort.st: Convert to new syntax. * tests/intmath.st: Convert to new syntax. * tests/lists.st: Convert to new syntax. * tests/lists1.st: Convert to new syntax. * tests/lists2.st: Convert to new syntax. * tests/matrix.st: Convert to new syntax. * tests/methcall.st: Convert to new syntax. * tests/mutate.st: Convert to new syntax. * tests/nestedloop.st: Convert to new syntax. * tests/objdump.st: Convert to new syntax. * tests/objects.st: Convert to new syntax. * tests/objinst.st: Convert to new syntax. * tests/processes.st: Convert to new syntax. * tests/prodcons.st: Convert to new syntax. * tests/random-bench.st: Convert to new syntax. * tests/untrusted.st: Convert to new syntax. * tests/sets.st: Convert to new syntax. * tests/sieve.st: Convert to new syntax. * tests/strcat.st: Convert to new syntax. * tests/strings.st: Convert to new syntax. 2007-04-11 Paolo Bonzini * tests/compiler.st: Check that compiling a method does not capture the temporaries dictionary. * tests/exceptions.st: Wrap into block when evaluating multiple statements together is important. * tests/objects.st: Likewise. * tests/untrusted.st: Likewise. 2007-04-02 Paolo Bonzini * kernel/ClassDesc.st: Fix bugs in previous checkin to this file. * kernel/Metaclass.st: Remove overrides where bugs were fixed directly in the superclass. 2007-03-29 Stephen Compall * kernel/Collection.st: Add and describe class from: protocol. * kernel/Array.st: Specialize from:. * kernel/Dictionary.st: Same. 2007-03-29 Stephen Compall * kernel/Dictionary.st: Use a smaller default size in new. * kernel/HashedColl.st: Treat new:'s argument as a requested capacity. 2007-03-28 Palo Bonzini * kernel/AnsiExcept.st: Force MutationError's creator to be nil. * kernel/Builtins.st: Add #subclass:, always return class from class creation stubs. * kernel/Class.st: Add #shape: and #subclass:. * kernel/ClassDesc.st: Add #instanceVariableNames:. * kernel/Metaclass.st: Remove #instanceVariableNames:, add #name:environment:subclassOf: (used by Class>>#subclass:). * kernel/UndefObject.st: Add #subclass:. * tests/mutate.st: Add tests for #subclass:. 2007-03-26 Paolo Bonzini * kernel/Float.st: Add exclamation mark. 2007-03-26 Paolo Bonzini * kernel/HashedColl.st: Add #withAll:. 2007-03-20 Paolo Bonzini * kernel/Integer.st: Fix infinite loop in #binomial: when anInteger is 0 or self. 2007-03-20 Paolo Bonzini * kernel/CharArray.st: Point out that #lineDelimiter is not usable on this class. * kernel/Dictionary.st: Fix #addAll:, suggested by Janis Rucis. 2007-03-20 Paolo Bonzini * tests/compiler.st: Test pragma. 2007-03-20 Paolo Bonzini * kernel/ObjDumper: Fix typo. 2007-03-19 Paolo Bonzini * examples/Application.st: Delete. * examples/Debugger.st: Delete. * examples/RandomInt.st: Delete. * examples/DeltaBlue.st: Convert class variables to class-instance. * kernel/Regex.st: Likewise. * kernel/DLD.st: Likewise. * kernel/ObjDumper.st: Likewise. * kernel/PkgLoader.st: Likewise. * kernel/Random.st: Likewise. * kernel/ValueAdapt.st: Likewise. * kernel/VFS.st: Likewise. * examples/RegExp.st: Remove useless debugging code. * kernel/ContextPart.st: Remove unused class variable. 2007-03-16 Paolo Bonzini * kernel/Regex.st: Fix calls to #interval. 2007-03-09 Paolo Bonzini * scripts/Finish.st: Fix DESTDIR installation. 2007-03-06 Paolo Bonzini * examples/Continuations.st: Make more compatible with Seaside's implementation. 2007-02-10 Stephen Compall * kernel/AbstNamespc.st: Make removeSubspace: public, change its argument to be a symbol rather than a namespace, and don't make it a subspace of Smalltalk. 2007-02-10 Paolo Bonzini * kernel/Directory.st: Add #kernel and #userKernel, deprecate #systemKernel and #localKernel. * kernel/VFS.st: Adjust. * kernel/PkgLoader.st: Adjust. * kernel/SysDict.st: Add #imageLocal. * scripts/Finish.st: Get `old' file path from ImageFilePath. 2007-02-06 Paolo Bonzini * kernel/FileDescr.st: Use #remove:ifAbsent:. 2007-02-05 Paolo Bonzini * kernel/FileDescr.st: Remove #allSubinstancesDo: on quit, instead register open files in a WeakIdentitySet. * kernel/Object.st: Store dependencies in a WeakKeyIdentityDictionary. * kernel/WeakObjects.st: Don't transform dependencies into a WeakKeyIdentityDictionary here. 2007-02-04 Paolo Bonzini * kernel/Float.st: Remove debugging statement. 2007-02-01 Paolo Bonzini * kernel/CharArray.st: Speed up #asInteger by 2x. 2007-01-29 Paolo Bonzini * kernel/Float.st: Really fix bug in printing floating point numbers. 2007-01-29 Paolo Bonzini * kernel/LargeInt.st: Rename #trailingZeros to #lowBit. * kernel/SmallInt.st: Rename #trailingZeros to #lowBit. * kernel/Integer.st: Rename #trailingZeros to #lowBit. * kernel/Float.st: Fix bug in printing exact floating-point numbers. Support gradual underflow in #raisedToInteger:. * tests/floatmath.st: Add accuracy tests. * tests/floatmath.ok: Adjust. 2007-01-28 Paolo Bonzini Nicolas Cellier * kernel/Float.st: Rewrite #truncated and #asExactFraction. * kernel/Fraction.st: Use #asFloatD in #hash. Rewrite #asFloat:. * kernel/LargeInt.st: Rewrite #asFloat:. Add #trailingZeros. * kernel/SmallInt.st: Add #trailingZeros. * kernel/Integer.st: Add #trailingZeros. * kernel/MappedColl.st: Use map size as collection size. * tests/floatmath.st: Add accuracy tests. * tests/floatmath.ok: Adjust. 2007-01-27 Paolo Bonzini * tests/intmath.st: Add one regression test. * tests/intmath.ok: Adjust. 2007-01-26 Stephen Compall * kernel/Dictionary.st: Use aBlock directly in associationsDo:. * kernel/AbstNamespc.st: Likewise with subspacesDo:. 2007-01-26 Paolo Bonzini * kernel/BlkClosure.st: Override #copy rather than #shallowCopy. 2007-01-22 Stephen Compall * kernel/Fraction.st: Print denominator for storeOn: as denominator, not numerator as denominator. Reported by J Pfersich. 2007-01-14 Stephen Compall * kernel/HashedColl.st: Add copyEmpty, using primSize instead of basicSize. Fixes size-doubling for LookupTable. 2007-01-09 Stephen Compall * kernel/Directory.st: Pass Directory entries to #allFilesMatching:do:'s block argument if they match aPattern. 2007-01-02 Paolo Bonzini Stephen Compall * kernel/FileSegment.st: Add #copyFrom:to:. * kernel/Class.st: Fix bugs in pragma handlers. 2007-01-02 Mike Anderson * kernel/Builtins.st: Fix Character>>#asciiValue: pasto. 2006-12-31 Paolo Bonzini Stephen Compall * kernel/FileDescr.st: Fix #copyFrom:to:. * kernel/PosStream.st: Make the same method 0-based. 2006-12-19 Paolo Bonzini * kernel/VFS.st: Initialize file system registry lazily. 2006-12-18 Paolo Bonzini * kernel/VFS.st: Use dependency to invoke #release instead of #allSubinstancesDo: 2006-12-18 Paolo Bonzini * kernel/FileDescr.st: Fix #nextPutByte:. * kernel/FileStream.st: Remove it and #nextPutByteArray:. 2006-12-14 Paolo Bonzini * kernel/CFuncs.st: Accept that the address is nil. 2006-12-07 Paolo Bonzini * kernel/Builtins.st: Add #divExact: primitive. * kernel/Float.st: Use it when dividing by a GCD. * kernel/Fraction.st: Use it when dividing by a GCD. * kernel/Integer.st: Use it when dividing by a GCD. * kernel/LargeInt.st: Use it when dividing by a GCD. * kernel/ScaledDec.st: Use it when dividing by a GCD. 2006-12-05 Paolo Bonzini *** Version 2.3 released. 2006-12-05 Paolo Bonzini * kernel/Number.st: Fix coercion in previous checkin. 2006-12-02 Paolo Bonzini * kernel/Number.st: Don't use Floats in #rounded and use #rounded in #roundTo:. 2006-12-01 Paolo Bonzini * kernel/CompildMeth.st: Fix typo in asynchronous call-outs. * tests/cobjects.st: Test it. 2006-11-30 Paolo Bonzini * kernel/VFS.st: Execute hooks before/after snapshots too. Add release method to get rid of DESTDIRs. 2006-11-27 Paolo Bonzini * scripts/Finish.st: Get rid of all DESTDIRs. 2006-11-21 Paolo Bonzini * kernel/Regex.st: Move creation of MatchingRegexResults object to C. 2006-11-21 Paolo Bonzini * examples/gdbm.c: Add GPL exception. * examples/md5.c: Add GPL exception. 2006-11-19 Paolo Bonzini * tests/quit.st: New. 2006-11-15 Brad Watson * examples/ncurses.st: New. 2006-11-15 Paolo Bonzini * kernel/CFuncs.st: Rename #asyncCallFrom: and #callFrom:into: into #asyncCall: and #callInto:. * kernel/Class.st: Provide pragmas. * kernel/CompildCode.st: Change special selector #callFrom:into: into #callInto:. * kernel/CompildMeth.st: Do not materialize context in the call-outs. Add support for the pragma. * kernel/ScaledDec.st: Fix bug in previous check-in. 2006-11-13 Paolo Bonzini * kernel/Float.st: Fix typo. * kernel/ScaledDec.st: Compute GCD here for #asFraction. 2006-11-08 Paolo Bonzini * kernel/Float.st: Rewrite printing to round correctly and never divide a floating-point number. * kernel/Number.st: Fix problems in #floorLog:, add #ceilingLog:. Never divide. * kernel/Integer.st: Likewise. * tests/floatmath.st: Test rounding when printing. * tests/geometry.st: Fix test vector to test the correct rounding. 2006-11-04 Paolo Bonzini * kernel/CObject.st: Use #numberOfElements rather than #numElements. 2006-11-04 Paolo Bonzini * kernel/Builtins.st: Fix primitive number for ByteArray class>>#fromCData:size:. 2006-11-03 Paolo Bonzini * kernel/LargeInt.st: Fix method comments. 2006-11-03 Paolo Bonzini * kernel/BlkClosure.st: Mark #on:do: contexts as unwinding * kernel/ProcSched.st: Remove debug code. * kernel/Process.st: Fix parameter names in #on:at:suspend:. Add #context and use it in #makeUntrusted:. Wrap process not only in an #on:do:, but also in an #ensure: block. * tests/exceptions.st: Test exception raising within a process. 2006-11-02 Paolo Bonzini * kernel/BlkClosure.st: Do not fail if #on:do: has something else than an exception passed to it. 2006-10-31 Paolo Bonzini * kernel/Stream.st: Put pastEnd here... * kernel/PosStream.st: ... from here. 2006-10-31 Paolo Bonzini * kernel/AnsiExcept.st: Support raising WrongClass without setting validClasses first. 2006-10-28 Paolo Bonzini * kernel/CharArray.st: Add missing period in #isNumeric. Patch by J Pfersich. 2006-10-27 Paolo Bonzini * kernel/VFS.st: Implement isDirectory by accessing struct stat. 2006-10-27 Paolo Bonzini * kernel/Float.st: Run #asFraction loop after stripping the exponent. * kernel/FloatD.st: Fix comment. Reported by J Pfersich. * kernel/FloatE.st: Likewise. * kernel/FloatQ.st: Likewise. 2006-10-25 Paolo Bonzini * examples/MiniInspector.st: Test #atEnd before reading next line. 2006-10-25 Paolo Bonzini * examples/Prolog.st: Enjoy the wonders of polymorphism. 2006-10-23 Paolo Bonzini * kernel/CharArray.st: Make #numberOfCharacters notYetImplemented and #asUnicodeString subclassResponsibility. * kernel/String.st: Remove #numberOfCharacters. 2006-10-16 Paolo Bonzini * examples/Methods.st: New. 2006-10-16 Paolo Bonzini * kernel/String.st: Fix storeString of read-only literals. 2006-10-15 Paolo Bonzini * kernel/Regex.st: Fix Regex>>#asString, reported by J Pfersich. 2006-10-05 Paolo Bonzini * kernel/ObjMemory.st: Wait for the completion of other processes before quitting. 2006-09-29 Paolo Bonzini * examples/LazyCollect.st: Fix reference to deleted class. 2006-09-22 Paolo Bonzini * examples/regex.st: Move ... * kernel/Regex.st: ... here. Move private classes into Kernel namespace. Add documentation. 2006-09-22 Paolo Bonzini * kernel/Builtins.st: Add UnicodeString>>#hash. * kernel/UniString.st: Add #fromString: and #encoding methods. * kernel/CharArray.st: Add #=, #encoding, #asUnicodeString. * kernel/String.st: Add fast version of #=, remove #asUnicodeString. 2006-09-15 Paolo Bonzini * examples/LazyCollect.st: Refactor. 2006-09-13 Paolo Bonzini * kernel/Behavior.st: Use #readStream to convert a WriteStream into a ReadStream. * kernel/PosStream.st: Add #readStream. * kernel/RWStream.st: Replace #useWholeStream with new method #limit:. Define #on:from:to:. * kernel/ReadStream.st: Optimize #on:from:to: with new method #initCollection:limit:. Remove useless #reverseContents. * kernel/WriteStream.st: Add #readStream. * kernel/File.st: Create new file in #touch if not existing. 2006-09-08 Paolo Bonzini * kernel/LinkedList.st: Fix quadraticness of #includes:. 2006-09-08 Paolo Bonzini * kernel/File.st: Add methods to wrap utime and use them in #touch. * kernel/VFS.st: Add methods to wrap utime. * kernel/FileStream.st: Fix typo. 2006-09-08 Paolo Bonzini * kernel/ExcHandling.st: Reinstate skipping internal contexts. 2006-09-08 Paolo Bonzini * kernel/Builtins.st: Add checks to "Namespace current:" * kernel/AnsiExcept.st: Accept classes in addition to VariableBindings. 2006-09-07 Paolo Bonzini * scripts/Finish.st: Accept the full $(DESTDIR)$(pkgdatadir) and $(pkgdatadir). 2006-09-06 Paolo Bonzini * kernel/File.st: Add #pathFor:ifNone:. * kernel/Directory.st: Use it in #create:. 2006-07-28 Paolo Bonzini * kernel/SeqCollect.st: Add #keys. * kernel/MappedColl.st: Likewise. 2006-07-26 Paolo Bonzini * kernel/MappedColl.st: Don't use #species. * kernel/SeqCollect.st: Don't use #species. * kernel/ArrayColl.st: Don't use #species. 2006-07-20 Paolo Bonzini * kernel/Getopt.st: New. * tests/getopt.st: New. 2006-07-20 Paolo Bonzini * kernel/Builtins.st: Define Stream>>#fileIn and #fileInLine:fileName:at:. * kernel/FileDescr.st: Redefine #nextHunk. * kernel/FileStream.st: Fix bug in #nextHunk. Remove file-in methods. * kernel/Stream.st: Define #nextHunk. 2006-07-20 Paolo Bonzini * kernel/Builtins.st: Add four-argument #fileOp: primitive. * kernel/FileDescr.st: Look ahead one character in #atEnd for pipes. * kernel/FileSegment.st: Use FileStream>>#copyFrom:to:. * kernel/FileStream.st: Rewrite buffer flushing and collection read/write. Do not use any fileOp: directly except for pread/pwrite (which are not used for pipes -- see kernel/FileDescr.st) and fileIn (which will disappear before the release). 2006-07-18 Paolo Bonzini * kernel/Behavior.st: Add #utf32 shape. * kernel/Builtins.st: Recognize ranges correctly for #character and #utf32 shapes. Implement CharacterArray>>#valueAt: and #valueAt:put: as primitives. Add UnicodeCharacter methods and distinguish Character class>>#codePoint: from #value:. Adjust instance variable name for character. Use specific primitive for Character equality. * kernel/ByteArray.st: Do not implement #asUnicodeString. * kernel/CharArray.st: Remove #basicAt:/#basicAt:put:. Add (abstract) #numberOfCharacters and #printOn:/#displayOn:/#storeOn:. * kernel/Character.st: Use separate tables for classification and case mapping. Answer false for #isIdentity. Change name of instance variable. Add #asUnicodeString. Adjust printing to support Unicode characters. * kernel/Class.st: Document #utf32 shape. * kernel/Collection.st: Add #asString and #asUnicodeString. * kernel/Integer.st: Use #codePoint: in #asCharacter. * kernel/ObjDumper.st: Add UnicodeCharacter storing. Add support for #utf32 shape. * kernel/PosStream.st: Add #isPositionable. * kernel/Stream.st: Add #isPositionable and #isUnicode. * kernel/String.st: Do not implement #asUnicodeString. Add printing methods removed from CharacterArray. Add #byteAt:/#byteAt:put:. * kernel/UndefObject.st: Document #utf32 shape. * kernel/UniChar.st: New. * kernel/UniString.st: New. * tests/Ansi.st: Raise the codePoint needed to get an Error. * tests/chars.st: Only test ASCII characters for #asCharacter. 2006-07-10 Paolo Bonzini * examples/regex.st: Define with correct shape. 2006-07-08 Paolo Bonzini * kernel/Rectangle.st: Fix incorrect checkin. 2006-07-07 Paolo Bonzini * examples/LazyCollection.st: New. 2006-07-07 Paolo Bonzini * kernel/Point.st: Fix #min: and #max:. * kernel/Rectangle.st: Deal more gracefully with non-normalized rectangles. 2006-04-27 Paolo Bonzini * kernel/OrderColl.st: Split part of #removeAtIndex: into #basicRemoveAtIndex:. * kernel/SortCollect.st: Rename #removeAtIndex: to #basicRemoveAtIndex:. 2006-04-19 Paolo Bonzini * kernel/SortCollect.st: Provide #removeAtIndex:. 2006-01-02 Paolo Bonzini * examples/regex.st: Fix methods expecting nil rather than FailedMatchRegexResults. 2005-11-29 Paolo Bonzini * kernel/Behavior.st: Add #character shape. * kernel/Builtins.st: Copy implementation of #at: and friends from Object to String. Add here a stub implementation of #variable:subclass:instanceVariableNames:classVariableNames: poolDictionaries:category:. * kernel/Class.st: Fix comment to add #character shape. * kernel/ObjDumper.st: Look for #character shape instead of String. * kernel/String.st: Use #character shape. * kernel/Symbol.st: Use #character shape. * kernel/UndefObject.st: Fix comment to add #character shape. 2005-11-23 Paolo Bonzini * kernel/CharArray.st: Optimize #asInteger. 2005-11-22 Paolo Bonzini * examples/shell: Change the invocation method once more. 2005-11-21 Paolo Bonzini * kernel/PkgLoader.st: Add `features' instance variables and accessors to the Package class. Use it in #fileInPackage: and when computing the dependencies. Fix the printXmlOn: method. Parse the tag when reading the packages file. 2005-11-21 Paolo Bonzini * kernel/VFS.st: Give the current timezone to the file timestamps. 2005-10-04 Paolo Bonzini * examples/regex.c: Constify bm_search. 2005-09-05 Paolo Bonzini * examples/StreamFilter.st: Reimplement #peek and add #peekFor: to ConcatenedStream. * kernel/Character.st: new method #isDigit:. * kernel/Integer.st: new method #readFrom:radix:. 2005-08-30 Paolo Bonzini * tests/geometry.st: Make more resilient to #basicHash vagaries. * tests/geometry.ok: Adapt. 2005-08-28 Paolo Bonzini * examples/Continuations.st: New. 2005-08-28 Paolo Bonzini * kernel/Interval.st: Fix #= after 2005-05-27 changes. 2005-08-23 Mike Anderson * kernel/FileDescr.st: Fix thinkos. 2005-08-14 Paolo Bonzini * kernel/VFS.st: Add #isSymbolicLink and lstat. * kernel/File.st: Add #isSymbolicLink. * kernel/Directory.st: Add #allFilesMatching:do: and #fileAt:, return File or Directory from #at:. * kernel/Stream.st: Add #linesDo:. 2005-08-07 Paolo Bonzini * kernel/VFS.st: Do my math correctly. 2005-08-07 Paolo Bonzini * kernel/Float.st: Use x - x == 0 to implement #isFinite. 2005-07-28 Paolo Bonzini * kernel/ClassDesc.st: Add #fileOutHeaderOn: * kernel/Class.st: Remove it. 2005-06-16 Paolo Bonzini * kernel/ArrayColl.st: remove #...stream methods. * kernel/SeqCollect.st: move them here. 2005-06-16 Paolo Bonzini * kernel/DLD.st: Restart search from the last library where we found a function. 2005-06-12 Paolo Bonzini * kernel/Interval.st: Fix pasto. 2005-06-01 Paolo Bonzini * examples/regex.st: Always return a RegexResults object from =~. Create a small hierarchy rooted at RegexResults. 2005-05-27 Paolo Bonzini Mike Anderson * kernel/Interval.st: Add #first, #last, #increment. * kernel/SeqCollect.st: Fix exceptional case in #replaceFrom:to:with:. * examples/re.c (): Return a struct pre_registers * from reh_search. New reh_free_registers function, register it. * examples/regex.st: New class CRegexRegisters, modify all the methods to use it. Name the C call-out method #searchRegexInternal:from:to:. New class RegexResults, return it from #searchRegex:from:to:, #searchRegex:startingAt:, #searchRegex:. 2005-04-07 Mike Anderson * kernel/PosStream.st: Fix bug in #peekFor:. 2005-03-25 Paolo Bonzini * kernel/Class.st: Implement "active" method annotations and C-call method annotations. * kernel/CompildMeth.st: Implement C-call method annotations. * kernel/ObjMemory.st: Call "Class initialize". * examples/gdbm-c.st: Switch to new C-call description. * examples/md5.st: Likewise. * examples/regex.st: Likewise. * kernel/Behavior.st: Likewise. * kernel/CFuncs.st: Likewise. * kernel/ClassDesc.st: Likewise. * kernel/DLD.st: Likewise. * kernel/Directory.st: Likewise. * kernel/File.st: Likewise. * kernel/VFS.st: Likewise. 2005-03-25 Paolo Bonzini * kernel/FileDescr.st: add #nextPutAllFlush: 2005-02-02 Paolo Bonzini * kernel/PkgLoader.st: Add comments to undocumented methods. 2005-02-02 Paolo Bonzini * examples/gdbm.c: Do not include malloc.h. 2005-02-02 Paolo Bonzini * scripts/GenLibDoc.st: Remove debugging statement. 2004-11-13 Paolo Bonzini * kernel/Directory.st: support passing an absolute path as the file name in Directory>>#append:to:. * kernel/PkgLoader.st: support source files in multiple directories. 2004-09-07 Paolo Bonzini * kernel/PkgLoader.st: add #fileIn method to Package, and support namespaces. 2004-09-06 Paolo Bonzini * kernel/CObject.st: implement #narrow for UndefinedObject. 2004-01-29 Paolo Bonzini * kernel/Number.st: redefine #min: and #max: to handle NaNs and negative zeros. * kernel/Float.st: likewise. * kernel/Number.st: add #arcTan: * kernel/Point.st: use it 2004-01-08 Paolo Bonzini * examples/DeltaBlue.st: New file. 2003-12-10 Paolo Bonzini * kernel/PkgLoader.st: Be quiet if OutputVerbosity == 0. 2003-11-28 Paolo Bonzini * examples/Sync.st: Monitor replaced with simpler and much faster code. 2003-11-27 Paolo Bonzini * kernel/CompildCode.st: New bytecodes 25 and 26 (#javaAsInt, #javaAsLong). 2003-11-21 Paolo Bonzini * kernel/Behavior.st: Support multiple shapes. * kernel/Builtins.st: Support multiple shapes. * kernel/Class.st: Support multiple shapes. * kernel/Metaclass.st: Support multiple shapes. * kernel/ObjDumper.st: Support multiple shapes. * kernel/UndefObj.st: Support multiple shapes. * kernel/ByteStream.st: Support 64-bit I/O. 2003-11-18 Paolo Bonzini * kernel/Builtins.st: Use FileDescriptor>>#checkError. * kernel/FileDescr.st: Add a #checkError method. * kernel/FileStream.st: Use FileDescriptor>>#checkError. 2003-11-10 Paolo Bonzini * kernel/Character.st: Add a dummy #asCharacter method. 2003-11-07 Paolo Bonzini * kernel/CompildCode.st: Don't abridge classes (printing "a XXX class" instead of "XXX" does not abridge much...) 2003-11-03 Paolo Bonzini * kernel/AnsiExcept.st: New exception NotEnoughElements * kernel/Stream.st: Raise it from #next: * kernel/SeqCollect.st: Move stream creation methods... * kernel/ArrayColl.st: ...here. 2003-11-02 Paolo Bonzini * kernel/HashedColl.st: Add more calls to #beConsistent. * kernel/LookupTable.st: Likewise. * kernel/WeakObjects.st: Rename #cleanup to #beConsistent. 2003-10-24 Paolo Bonzini * kernel/SysDict.st: New method #hostSystem. 2003-10-21 Paolo Bonzini * kernel/ExcHandling.st: Correctly reinstate exception handlers on #return and #return:. * kernel/PkgLoader.st: Fix bug in recognizing already loaded packages. * kernel/SysDict.st: Accept a String in #hasFeatures: 2003-10-17 Paolo Bonzini * kernel/ContextPart.st: Correctly find exception handlers when unwinding, as in [ [^self] ensure: [ self halt ] ] on: Halt do: [ :ex | ] 2003-09-28 Paolo Bonzini * kernel/Metaclass.st: Refactor parsing of variable names out of the class creation methods. 2003-09-24 Paolo Bonzini * kernel/UndefObject.st: Add #printOn:in: 2003-09-20 Paolo Bonzini * kernel/ArrayColl.st: Fix bug in #copyReplaceFrom:to:with: 2003-09-13 Paolo Bonzini * kernel/CompildCode.st: Remove unused callbacks for disassembling bytecodes. Dispatch superoperators. Right align bytecode indices. 2003-09-07 Paolo Bonzini * kernel/CompildMeth.st: Print correctly if descriptor is nil. 2003-09-05 Paolo Bonzini * compiler/STLoaderObjs.st: Create link from namespace to itself. * kernel/CompildCode.st: Adapt instruction decoder to new bytecode set. 2003-08-25 Paolo Bonzini * examples/Sync.st: Fix #forSeconds: --> #forMilliseconds: in Watchdog. * kernel/Autoload.st: Add a method to get the class of the autoloaded class, because #class is not optimized by the virtual machine anymore. 2003-08-16 Paolo Bonzini * examples/Generators.st: New file 2003-08-09 Paolo Bonzini * kernel/Security.st: New file * kernel/Class.st: Implement securityPolicy accessors * kernel/Behavior.st: Likewise * kernel/ContextPart.st: Implement security checks 2003-07-22 Paolo Bonzini * kernel/Behavior.st: Call #narrow in C call-outs * kernel/CObject.st: Implement #narrow. 2003-07-13 Paolo Bonzini * kernel/LookupTable.st: Implement #hash. * kernel/Character.st: Make it not indexed, reimplement asciiValue & co. * kernel/Stream.st: Replace #| with #or: * kernel/FileStream.st: Signal EndOfStream appropriately, reimplement #nextLine more efficiently, inline some tests. * kernel/FileDescr.st: Signal EndOfStream appropriately 2003-07-10 Paolo Bonzini * tests/compiler.st: Add test case 2003-07-09 Paolo Bonzini * kernel/SeqCollect.st: Do some optimization * kernel/BindingDict.st: Inline hash lookup into #findIndex: * kernel/Dictionary.st: Inline hash lookup into #findIndex: * kernel/HashedColl.st: make #findIndex: an abstract method * kernel/IdentDict.st: Inline hash lookup into #findIndex: * kernel/IdentitySet.st: Inline hash lookup into #findIndex: * kernel/LookupTable.st: Inline hash lookup into #findIndex: * kernel/Set.st: Inline hash lookup into #findIndex: * kernel/WeakObjects.st: Inline hash lookup into #findIndex: 2003-07-08 Paolo Bonzini * kernel/ObjMemory.st: Initialize Processor. * kernel/Processor.st: Fire GC process. * unsupported/profile.st: Show how to write a profiler in 30 lines of code. 2003-07-06 Paolo Bonzini * kernel/Integer.st: Make printing code faster * kernel/LargeInt.st: Make printing code faster 2003-07-03 Paolo Bonzini * kernel/CompildCode.st: Try to avoid invalidating the method cache when a new method is created. * kernel/CompildMeth.st: Support creation of user-defined methods, and #valueWithReceiver:withArguments: 2003-06-30 Paolo Bonzini * compiler/STLoader.st: Fix fallout of change to variable lookup 2003-06-29 Paolo Bonzini * kernel/File.st: Add #touch 2003-06-25 Paolo Bonzini * kernel/LookupTable.st: Remove values instance variable, store key/value pairs in adjacent slots. * kernel/WeakObjects.st: Put values instance variable here * kernel/CompildMeth.st: Make attribute-accessing methods use MethodInfo * kernel/MethodInfo.st: Make MethodInfo indexable 2003-06-23 Paolo Bonzini * kernel/Metaclass.st: Properly handle untrustedness upon class creation. 2003-06-22 Paolo Bonzini * kernel/AnsiExcept.st: Create SecurityError class. * kernel/BindingDict.st: Move part of the extra work to do into #primAt:put:. Make bindings untrusted if the environment is untrusted too. 2003-06-21 Paolo Bonzini * kernel/Number.st: Implement extra-cool #raisedToInteger: * kernel/LargeInt.st: Fixed bug in #bitAt: 2003-06-11 Paolo Bonzini * kernel/Builtins.st: Implement trustedness primitives. 2003-06-10 Paolo Bonzini * kernel/Memory.st: Made a #subclass: (used to be a variableWordSubclass:???) 2003-06-09 Paolo Bonzini * kernel/AnsiExcept.st: Accept variable bindings for the WrongClass exception, when passing an array. * kernel/Rectangle.st: Adapt. * kernel/SeqCollect.st: implement #fold: for efficiency; added #second, #third, #fourth. 2003-06-08 Paolo Bonzini * kernel/Builtins.st: death to #blockCopy: in every sauce, add ContextPart class>>#thisContext * kernel/Collection.st: Fix typo in the comment for Collection>>#inject:into:, add #fold: * kernel/CompildCode.st: Death to the "push this context" bytecode and to #blockCopy: in every sauce * compiler/STDecompiler.st: Adapt to the above 2003-06-05 Paolo Bonzini * kernel/Builtins.st: #blockCopy: moved to CompiledBlock. * kernel/CompildMeth.st: Adapted #allBlocksDo: to the possibility of having CompiledBlocks in the literal frame. * kernel/CompildCode.st: Ditto for #blockAt: * kernel/CompildBlk.st: Ditto for #binaryRepresentationProxy * kernel/CompildCode.st: No need to special case Associations in the method printing code, because methods don't own Association anymore (they have VariableBindings, but they print differently also to avoid this kind of special casing). * kernel/BlkClosure.st: Move some code from ExcHandling.st and refer to it from exception handling attributes * kernel/ContextPart.st: Add #scanBacktraceForAttribute: and use it to determine which contexts to hide from backtraces. * kernel/ExcHandling.st: Use exception handling attributes 2003-06-04 Paolo Bonzini * kernel/ExcHandling.st: Death to CoreException class>> #unwindTo: 2003-05-30 Paolo Bonzini * kernel/CompildMeth.st: Add accessors for attributes. 2003-05-27 Paolo Bonzini * kernel/Builtins.st: Add Object>>#allOwners * kernel/CallinProcess.st: Point out that CallinProcesses do not survive across image saves. 2003-05-16 Paolo Bonzini * kernel/Builtins.st: Add more C->String primitives * kernel/CObject.st: Add a few conversion methods to CChar * kernel/Bag.st: Don't leave items with zero occurrences in the dictionary. * kernel/CObject.st: Support long doubles * kernel/CStruct.st: Support long doubles * kernel/CType.st: Support long doubles * kernel/Memory.st: Support long double access * kernel/ByteArray.st: Support long double access 2003-05-09 Paolo Bonzini *** Version 2.1.2 released. * kernel/Stream.st: Define #isExternalStream. * kernel/FileDescr.st: Ditto. 2003-05-06 Paolo Bonzini * kernel/CompildCode.st: Omit # when outputting a literal in short form (a ClassName). * kernel/Builtins.st: Possibly raise a FileError exception in ObjectMemory class>>#snapshot: 2003-04-29 Paolo Bonzini * kernel/Behavior.st: Make recompiles more silent in regression testing mode. * kernel/Behavior.st: Don't update instanceSpec in #addInstVarName: and #removeInstVarName:. Possibly recompile subclasses when adding variables. Move #validateIdentifier: here from Metaclass.st, and use it. * kernel/Class.st: Possibly recompile subclasses when removing class variables. * kernel/Metaclass.st: moved #validateIdentifier: to Behavior. * kernel/Object.st: Fix thinko in class mutation. 2003-04-27 Paolo Bonzini * kernel/File.st: #extensionFor: should include the leading dot. Reported by nicolas.pelletier3@wanadoo.fr. 2003-04-17 Paolo Bonzini *** Version 2.1.1 (stable) released. 2003-04-12 Paolo Bonzini *** Version 2.1 (stable) released. 2003-03-22 Paolo Bonzini * sunit/SUnitPreload.st: Upgrade to SUnit 3.1RC2. * sunit/SUnitTests.st: Upgrade to SUnit 3.1RC2. * sunit/SUnitLog.st: Included into SUnit.st. * sunit/SUnit.st: Upgrade to SUnit 3.1RC2, include SUnitLog.st 2003-03-20 Paolo Bonzini * kernel/FileDescr.st: Ensure that the whole data is written on the file (for #write:... methods) -- previously done in the VM. 2003-03-04 Paolo Bonzini * kernel/VFS.st: Wrap loading of filesystems with exception handlers. 2003-03-02 Paolo Bonzini * kernel/Behavior.st: Implement #printOn:in: * kernel/BindingDict.st: Implement #printOn:in: * kernel/ClassDesc.st: Implement #printOn:in: * kernel/Metaclass.st: Implement #printOn:in: * kernel/Namespace.st: Implement #printOn:in: * kernel/RootNamespc.st: Implement #printOn:in: * kernel/SysDict.st: Implement #printOn:in: * kernel/CompildMeth.st: use #printOn:in: when printing 2003-02-08 Paolo Bonzini * kernel/DLD.st: Do not relink DLD functions at startup * kernel/CFuncs.st: Do that here on demand * kernel/CFuncs.st: use #printStringRadix: instead of #radix: * kernel/CObject.st: Ditto 2003-02-07 Paolo Bonzini * tests/processes.st: Add process names and a few other simplifications. * kernel/URL.st: Add comments. 2003-01-17 Paolo Bonzini * kernel/ExcHandling.st: Fix off-by-one error in #resetHandler * kernel/CompildCode.st: Also send #postCopy to super * kernel/ExcHandling.st: Override #postCopy rather than #copy 2003-01-16 Paolo Bonzini * kernel/Process.st: Don't suspend an interrupted process if the interruption has caused it to terminate (!) 2003-01-15 Paolo Bonzini * kernel/PkgLoader.st: Support dynamically loaded libraries. 2003-01-02 Paolo Bonzini * kernel/BlkClosure.st: Remove workaround for JIT bug. 2002-12-31 Paolo Bonzini * tests/processes.st: Fix for expected change in behavior. * examples/RandomInt.st: Add 2002 copyright year * examples/StreamFilter.st: Likewise * examples/shell: Likewise * kernel/Autoload.st: Likewise * kernel/ByteStream.st: Likewise * kernel/Character.st: Likewise * kernel/Class.st: Likewise * kernel/ClassDesc.st: Likewise * kernel/CStruct.st: Likewise * kernel/Date.st: Likewise * kernel/DLD.st: Likewise * kernel/Delay.st: Likewise * kernel/DirMessage.st: Likewise * kernel/FileSegment.st: Likewise * kernel/Interval.st: Likewise * kernel/LookupKey.st: Likewise * kernel/MappedColl.st: Likewise * kernel/Metaclass.st: Likewise * kernel/MethodInfo.st: Likewise * kernel/MthContext.st: Likewise * kernel/Point.st: Likewise * kernel/OtherArrays.st: Likewise * kernel/Rectangle.st: Likewise * kernel/ScaledDec.st: Likewise * kernel/Semaphore.st: Likewise * kernel/SharedQueue.st: Likewise * kernel/Symbol.st: Likewise * kernel/Time.st: Likewise * kernel/Stream.st: Remove duplicate implementation of #upToAll: * kernel/LargeInt.st: Fix bugs in Smalltalk implementation of LargeIntegers. 2002-12-27 Paolo Bonzini * kernel/ContextPart.st: Implement #isInternalExceptionHandlingContext * kernel/ExcHandling.st: Hide internal aspects of exception handling from backtraces * examples/MiniDebugger.st: Terminate internal exception handling contexts when entering the debugger. 2002-12-24 Paolo Bonzini * kernel/Builtins.st: Raise an error when the #addressOf: and #addressOfOOP: primitives fail. * kernel/ByteArray.st: send #addressOf: to ObjectMemory 2002-12-20 Paolo Bonzini * examples/Debugger.st: Removed 2002-12-19 Paolo Bonzini * kernel/Builtins.st: Implement ObjectMemory>>#abort * kernel/CompildCode.st: If a method does not have source code line information, don't fail in #sourceCodeMap * kernel/Behavior.st: Implement #debuggerClass * kernel/Metaclass.st: Implement #debuggerClass * kernel/ContextPart.st: Implement #debuggerClass * kernel/Process.st: Implement #suspendedContext * kernel/ExcHandling.st: Added support for starting a debugger. * examples/MiniDebugger.st: New file 2002-12-12 Paolo Bonzini * kernel/ArrayColl.st: Implement #copyEmpty using #size for the size of the new collection (instead of #basicSize). 2002-11-25 Paolo Bonzini * kernel/Behavior.st: Implement asyncronous call-outs * kernel/CFuncs.st: Implement asyncronous call-out primitive 2002-11-20 Paolo Bonzini * kernel/Class.st: Look in the current namespace for a class to redefine (#metaclassFor:) instead of looking in Smalltalk * kernel/UndefObject.st: Likewise 2002-11-15 Paolo Bonzini * kernel/Behavior.st: Use compile-time constant to define call-outs * kernel/DLD.st: Get rid of CFunctionDescs * kernel/Class.st: Use identity to look for shared pools. Avoids autoloading classes when there are any in the same environment as the shared pools'. 2002-11-14 Paolo Bonzini * kernel/CFuncs.st: Define new call-out primitive * kernel/Behavior.st: Use it 2002-11-12 Paolo Bonzini * kernel/Builtins.st: Added Semaphore>>#lock 2002-11-09 Paolo Bonzini * kernel/Delay.st: Ensure that the idle process is started and placed on the process lists. * kernel/DirMessage.st: Add process creation methods * kernel/Process.st: Add method to add an handler for ProcessTerminated into every call-in from C. 2002-10-21 Paolo Bonzini * kernel/ObjMemory.st: Adjusted for new memory manager 2002-10-18 Paolo Bonzini * kernel/FileDescr.st: Don't call #initialize * kernel/Object.st: Don't do anything if self ~~ Object in #initialize. 2002-10-17 Paolo Bonzini * kernel/Builtins.st: Adjusted for new memory manager 2002-10-13 Paolo Bonzini * kernel/Stream.st: Use Knuth-Morris-Pratt algorithm to implement #skipToAll: and #upToAll:. 2002-10-08 Paolo Bonzini * kernel/Autoload.st: Rewritten * kernel/ArrayColl.st: Don't implement #new: * kernel/Behavior.st: "new: 0" -> "new" * kernel/ClassDesc.st: Likewise * kernel/Object.st: Likewise * kernel/Symbol.st: Likewise * kernel/Builtins.st: send #new: or #basicNew: if #new or #basicNew fail because the class is fixed. 2002-10-07 Paolo Bonzini * kernel/Bag.st: Replace Dictionary with LookupTable, #associationsDo: with #keysAndValuesDo: * kernel/CStruct.st: Replace Dictionary with IdentityDictionary * kernel/Date.st: Replace Dictionary with IdentityDictionary * kernel/PkgLoader.st: Replace Dictionary with LookupTable * kernel/URL.st: Replace Dictionary with LookupTable 2002-10-06 Paolo Bonzini * kernel/Namespace.st: Inherit from AbstractNamespace * kernel/RootNamespc.st: Moved parts to AbstractNamespace and BindingDictionary * kernel/AbstNamespc.st: Create from RootNamespc.st * kernel/BindingDict.st: Create from RootNamespc.st * kernel/Class.st: Create BindingDictionaries for class pools. * kernel/CompildCode.st: Show line number bytecodes; added #sourceCodeMap. 2002-10-05 Paolo Bonzini * kernel/PkgLoader.st: Check the availability of call-outs after modules have been loaded. 2002-10-02 Paolo Bonzini * kernel/PkgLoader.st: Adopted XML input format 2002-09-29 Paolo Bonzini * kernel/OrderColl.st: Shrink 2002-09-28 Paolo Bonzini * kernel/Association.st: Don't hardcode the class in #storeOn: * kernel/LookupKey.st: Add brackets around the key in #printOn:, and don't hardcode the class * kernel/Behavior.st: Don't print a sharp in front of the name of a lightweight class. * kernel/Builtins.st: Replace finalization primitives with ephemeron primitive * kernel/Collection.st: Add #mourn: * kernel/HomedAssoc.st: New file from part of VarBinding.st * kernel/ObjMemory.st: Call Object class>>#initialize * kernel/Object.st: Add class variable and their accessors, and finalization methods * kernel/VarBinding.st: Change superclass to be HomedAssociation * kernel/WeakObjects.st: Reimplement parts to use ephemerons * kernel/RecursionLock.st: Doc fixes * kernel/Semaphore.st: Doc fixes * kernel/VFS.st: Doc fixes 2002-09-26 Paolo Bonzini * kernel/Builtins.st: Revert to #basicAt:/#basicAt:put: to access indexed instance variables in #instVarAt: and #instVarAt:put: 2002-09-22 Paolo Bonzini * kernel/BlkContext.st: Changed printing of block contexts 2002-09-19 Paolo Bonzini * kernel/CompildCode.st: Rewritten printing to adopt parameterized dispatch. * kernel/Process.st: Added interruptLock and revamped #queueInterrupt: so that it interrupts suspended processes as well. 2002-09-18 Paolo Bonzini * kernel/SharedQueue.st: Added #isEmpty * kernel/Delay.st: Solved a race condition * kernel/BlkClosure.st: Move process termination upon falling off the #fork-ed block from here... * kernel/Process.st: ...to here, where I also rewrote some parts so that #terminate uses the ProcessBeingTerminated notification... * kernel/AnsiExcept.st: ...that's defined here * kernel/ExcHandling.st: move declaration of #on:do: from here... * kernel/BlkClosure.st: ...to here, as it is needed to start the delay and idle processes. 2002-09-16 Paolo Bonzini * kernel/CharArray.st: Add support for %n. * kernel/Semaphore.st: Demonstrate %n. 2002-09-13 Paolo Bonzini *** Versions 2.0c (development) and 2.0.6 (stable) released * kernel/SeqCollect.st: Added #copyUpTo: * kernel/Stream.st: Added #next:putAll:startingAt: * kernel/Builtins.st: Allow specifying a class as the current namespace 2002-09-12 Paolo Bonzini * kernel/ClassDesc.st: Answer dot-separated names in #nameIn: * kernel/RootNamespc.st: Likewise * kernel/VarBinding.st: Don't replace spaces with periods 2002-09-11 Paolo Bonzini * kernel/Builtins.st: Add interrupt handling methods * kernel/BlkClosure.st: Implement #valueWithoutPreemption, possible now to do it with correct semantics * kernel/Process.st: Added `interrupts' variable * kernel/ValueAdapt.st: Use #valueWithoutPreemption * kernel/Semaphore.st: Fix comment, give 'em a name and a nice #printOn: method. * kernel/RecursionLock.st: New file 2002-09-10 Paolo Bonzini * numerics/Approximation.st: New file * numerics/Basic.st: New file * numerics/Distributions.st: New file * numerics/Functions.st: New file * numerics/Integration.st: New file * numerics/Load.st: New file * numerics/Matrixes.st: New file * numerics/NumericsAdds.st: New file * numerics/NumericsTests.st: New file * numerics/Optimization.st: New file * numerics/RNG.st: New file * numerics/Statistics.st: New file 2002-09-09 Paolo Bonzini * sunit/SUnitLog.st: New file * kernel/Class.st: Various additions to support RBEnvironments * kernel/CompildCode.st: Various additions to support RBEnvironments * kernel/Association.st: Achieve polymorphism with VariableBindings * kernel/RootNamespc.st: Add VariableBindings, not Associations * kernel/VarBinding.st: New file 2002-09-08 Paolo Bonzini * sunit/SUnit.st: Made logging less verbose * kernel/RootNamespc.st: Remove duplicates in #allBehaviorsDo: * kernel/Class.st: Store classes as how they are found in the current namespace. 2002-09-06 Paolo Bonzini * kernel/CompildCode.st: Remove references to the Debugger symbol * kernel/Behavior.st: Add missing return in #sourceCodeAt: and #selectorsAndMethodsDo:. Added pluggable behavior (as a provision only) through #...Class methods. * kernel/ClassDict.st: use #remove: instead of #removeAssociation: * kernel/Dictionary.st: implement #remove: and #remove:ifAbsent: * kernel/IdentDict.st: Implement #remove: * kernel/MethodDict.st: Implement #remove: * kernel/Namespace.st: use #remove: instead of #removeAssociation: 2002-09-05 Paolo Bonzini * kernel/CompildCode.st: Print 8-bit push bytecodes. * kernel/Builtins.st: Support single-step mode * kernel/Process.st: Ditto * sunit/SUnit.st: Upgraded to 3.1 * sunit/SUnitTests.st: Ditto * sunit/SUnitPreload.st: Ditto 2002-08-22 Paolo Bonzini * kernel/Behavior.st: Reimplement #allSubinstancesDo: to scan the OOP table just once. * kernel/SeqCollect.st: Reimplement #includes: and #identityIncludes: to avoid creating a full block. 2002-08-21 Paolo Bonzini * kernel/FileDescr.st: Raise events through #changed: before and after closing * kernel/VFS.st: Use this mechanism 2002-08-20 Paolo Bonzini * kernel/Association.st: Make sure that hash values are SmallIntegers. * kernel/CompildMeth.st: Likewise * kernel/FileSegment.st: Likewise * kernel/MethodInfo.st: Likewise * kernel/Point.st: Likewise * kernel/Rectangle.st: Likewise * kernel/FileDescr.st: Don't do unnecessary polls before invoking the asynchronous file polling service. * kernel/Stream.st: Check for end-of-stream condition in #nextLine. * kernel/Time.st: Delimit the parsed time by a space in #readFrom: 2002-08-19 Paolo Bonzini * kernel/Directory.st: Accessor methods rely on VFSHandler>>#at: * kernel/File.st: Added #on: * kernel/VFS.st: Implemented ExternalArchiveFileHandler. Created ArchiveMemberHandler and added abstract methods to VFSHandler. 2002-08-17 Paolo Bonzini * kernel/ValueAdapt.st: Add Object>>#asValue. * kernel/PosStream.st: Add the #pastEnd hook. * kernel/AnsiExcept.st: Make EndOfStream a subclass of Notification. 2002-08-14 Paolo Bonzini *** Version 2.0.5 (stable) released * kernel/Builtins.st: Implement ByteArray>> #replaceFrom:to:with:startingAt: as a primitive 2002-08-12 Paolo Bonzini *** Version 2.0b (development) released 2002-08-07 Paolo Bonzini *** Versions 2.0a (development) and 2.0.4 (stable) released * kernel/CharArray.st: 'abc' startsWith: 'abc' is now true. * kernel/VFS.st: Added method to open a file with specified class * kernel/FileDescr.st: Use it; added #peek. * kernel/FileStream.st: Added #peek. 2002-07-24 Paolo Bonzini * kernel/Builtins.st: Use the correct type when storing a CObject into another CObject * kernel/CObject.st: Rework things * examples/modules/gdbm-c.st: Fix memory leak 2002-07-22 Paolo Bonzini * kernel/Browser.st: Removed 2002-07-17 Paolo Bonzini *** Version 2.0.3 released 2002-07-15 Paolo Bonzini * examples/StreamFilter.st: Implement ConcatenatedStream>>#peek * kernel/URL.st: Moved here from net/URL.st * kernel/FileStream.st: Support opening URLs 2002-07-11 Paolo Bonzini *** Version 2.0.2 released 2002-07-10 Paolo Bonzini * kernel/ExcHandling.st: Moved definition of #ifCurtailed: * kernel/BlkClosure.st: Here (and fixed the method comment) 2002-07-06 Paolo Bonzini * kernel/ContextPart.st: Skip disabled contexts on backtraces. * kernel/BlkContext.st: Provide informational methods * kernel/MthContext.st: Likewise * kernel/Behavior.st: Use free methods to do evaluations 2002-07-05 Paolo Bonzini * kernel/Class.st: File out declaration of classes derived from nil correctly. * kernel/ExcHandling.st: Moved definition of #ensure: * kernel/BlkClosure.st: Here. * kernel/Object.st: Moved definition of #shallowCopy * kernel/Builtins.st: Here. * kernel/ByteArray.st: Remove redefinition of #shallowCopy, not needed with a primitive * kernel/CharArray.st: Likewise * kernel/ContextPart.st: Likewise 2002-07-04 Paolo Bonzini * kernel/Builtins.st: Define ContextPart>>#continue: and BlockClosure>>#valueAndResumeOnUnwind * kernel/ExcHandling.st: Simplify the unwinding logic through the new primitives. * kernel/ContextPart.st: Likewise 2002-07-03 Paolo Bonzini * kernel/PkgLoader.st: Store absolute paths 2002-07-02 Paolo Bonzini * kernel/ScaledDec.st: Define #ceiling, compare only to the lowest scale in equality and inequality * kernel/Number.st: Use #integerPart to round and truncate, so that Floats still answer Floats. * kernel/Float.st: Modified #hash to return the correct value when compared to LargeIntegers. * kernel/Fraction.st: Fix comparisons of negative fractions, print without parentheses, return Integers if possible; modified #hash to return the correct value when compared to Floats. * kernel/Integer.st: force #asScaledDecimal: to generate decimals with scale 0. * kernel/LargeInt.st: Fix <= and >= comparisons with zero, divisions by zero on #/, and corrected the order of computations and generality comparisons on most division methods 2002-06-28 Paolo Bonzini * kernel/Builtins.st: Float -> FloatD * kernel/Float.st: Moved some parts into * kernel/FloatD.st: This new file * kernel/FloatE.st: Created from FloatD.st * kernel/FloatQ.st: Created from FloatD.st * kernel/Number.st: Provide conversions to various flavors of Floats * kernel/Fraction.st: Likewise * kernel/LargeInt.st: Likewise * kernel/ScaledDec.st: Likewise * kernel/Integer.st: Use #asFloatD * kernel/SortCollect.st: Use #asFloatD 2002-06-29 Paolo Bonzini *** Version 2.0.1 released 2002-06-25 Paolo Bonzini *** Version 2.0 released 2002-06-21 Paolo Bonzini * kernel/PkgLoader.st: Fixes for vpath builds. Always compute directories relative to the package file they are found in. 2002-06-19 Paolo Bonzini * kernel/AnsiExcept.st: added the #goodness: method * kernel/ExcHandling.st: Use best-fit rather than first-fit to pick an exception handler when more than one is specified. Work decently (i.e. without performing correct unwinding of #ensure:/#ifCurtailed: blocks, but without incorrect data structure contents) if there are returns in exception handlers. * kernel/Process.st: Removed the exceptionHandlers variable 2002-06-14 Paolo Bonzini * kernel/ValueAdapt.st: Fixed race condition * kernel/CharArray.st: Added #match:ignoreCase: * kernel/CObject.st: Initialize the new object's type in #address:, new method #new to provide an instance initialized to NULL. 2002-06-05 Paolo Bonzini * kernel/UndefObject.st: Removed references to CFunctionDescs * kernel/Behavior.st: Use full path to refer to CFunctionsDescs * kernel/AnsiExcept.st: Don't show ArgumentOutOfRange limits in regression testing mode 2002-05-30 Paolo Bonzini * kernel/Fraction.st: Small bug fix, sometimes subtraction actually summed... 2002-05-28 Paolo Bonzini * kernel/Class.st: File out the superclass' name *in the context of the filed out class*. * kernel/Date.st: Return DateTimes with a Duration as an offset, not a number * kernel/Dictionary.st: Add inspect method 2002-05-26 Paolo Bonzini * kernel/FileSegment.st: use #ensure: in #withFileDo:, add a map of original file names to modified file names in the relocation code. 2002-05-23 Paolo Bonzini * kernel/Builtins.st: Declare a primitive to scramble the bits of a SmallInteger * kernel/Dictionary.st: Scramble the hash values * kernel/WeakObjects.st: Ditto * kernel/HashedColl.st: Ditto, and keep the size a power of two 2002-05-12 Paolo Bonzini * kernel/FileDescr.st: Trap #afterEvaluation and flush the standard handles 2002-05-11 Paolo Bonzini *** Version 1.96.6 released 2002-05-11 Paolo Bonzini * kernel/Integer.st: Add binomial coefficient computation * kernel/RunArray.st: Fix category to be "Collections-Sequenceable" * kernel/WriteStream.st: Fix category to be "Streams-Collections" * kernel/ScaledDec.st: Fix category to be "Language-Data types" * kernel/ByteArray.st: Fix category to be "Collections-Sequenceable" 2002-05-10 Paolo Bonzini * kernel/SeqCollect.st: Don't raise an error if replacing with an empty collection 2002-05-05 Paolo Bonzini * kernel/HashedColl.st: Don't use #copy when rehashing, since namespaces are identity objects * kernel/LookupTable.st: Don't do that here as well, just in case 2002-05-05 Paolo Bonzini * examples/MemUsage.st: Removed stale reference to WordMemory (eliminated in Sep 2000...) * kernel/ObjDumper.st: Call #postLoad only the first time an object is found in the stream; once the object got its definitive shape it makes no sense to lose time (or do harm) with post-load fixups. 2002-05-02 Paolo Bonzini * kernel/Builtins.st: Add primitives to tune allocation of big objects outside the main heap. 2002-05-01 Paolo Bonzini * kernel/ByteArray.st: Add CSymbols pool dictionary * kernel/CObject.st: Add CSymbols pool dictionary * kernel/Float.st: Add CSymbols pool dictionary, modified printing code to use them. Changed name of "characterization" methods to comply to the ANSI standard. Defined Float[DEQ] as synonyms of Float (for now). * kernel/Integer.st: Add CSymbols pool dictionary, added #bitAt:put:, the private method #signedStringBase:radix:on: now is called #printOn:base:showRadix: and is public * kernel/Fraction.st: Use the new characterization methods in Float. 2002-04-19 Paolo Bonzini * kernel/VFS.st: Added #openDescriptor:ifFail: * kernel/File.st: Added #openDescriptor:ifFail:, #open:ifFail:, #openDescriptor: * kernel/FileDescr.st: Open files with #openDescriptor:ifFail: * kernel/FileStream.st: Open files with #open:ifFail: 2002-04-18 Paolo Bonzini * kernel/VFS.st: Fix bug in mkdir * examples/shell: Replace with nice script by Alexander Lazarevic. 2002-04-16 Paolo Bonzini * kernel/ArrayColl.st: Move implementation of copying methods from SequenceableCollection to here. * kernel/Bag.st: Fail when adding nil * kernel/Dictionary.st: correct #keyAtValue: to return nil if the value is not found. Added #rehash. * kernel/AnsiDates.st: Removed call to missing #isDuration method. * kernel/Float.st: Strip trailing zeros from the #printString * kernel/HashedColl.st: WhileGrowingAdd: -> addWhileGrowing: * kernel/LargeInteger.st: Removed primitive in LargeInteger>>#/ * kernel/OrderColl.st: Raise errors for indices out of bounds in #add:afterIndex: & co. * kernel/PosStream.st: Make #position answer ptr - 1 and adjust callers. #next returns nil at end of stream. * kernel/SeqCollect.st: Use #copyEmptyForCollect in #reverse; implement copying methods in terms of #add: * kernel/SortCollect.st: #occurrencesOf: result was off by one * kernel/WriteStream.st: Allow extending the stream to previous values of the collection, truncate when answering the #contents instead. 2002-04-14 Paolo Bonzini *** Version 1.96.5 released 2002-04-13 Paolo Bonzini * sunit/SUnit.st: Show assertion results * kernel/SeqCollect.st: correct #replaceFrom:to:with: to accept only collections of the exact specified size, added #at:ifAbsent: * kernel/CharArray.st: Added #startsWith: * kernel/ExcHandling.st: Bug fixes 2002-04-10 Paolo Bonzini * kernel/Float.st: Implemented #negated to behave correctly with respect to negative zeros. Print minus sign in front of negative zero. Rewritten printing logic. * kernel/Number.st: Added tests for NaNs and infinities; added #withSignOf: Implemented #min: and #max: to behave correctly with respect to NaNs. Added remarks on negative zeros 2002-04-06 Paolo Bonzini * kernel/Fraction.st: Skip GCDs when computing squared fractions, do them on lower numbers when adding and subtracting; try to avoid multiplications on comparisons. * kernel/SmallInt.st: Implemented #highBit with a binary search, fixed result for negative powers of two (-4, -8, etc) * kernel/LargeInt.st: Implemented #highBit separately for LargeNegativeIntegers and LargePositiveIntegers, fixed result for negative powers of two * kernel/Integer.st: Removed generic implementation of #highBit 2002-04-01 Paolo Bonzini * kernel/LargeInt.st: Define / in terms of GCD * kernel/Fraction.st: Fix typo in #estimatedLog; compute cross GCDs for multiplication and exact division; implement #floor and #ceiling in terms of operations on the numerator and denominator. 2002-03-27 Paolo Bonzini * kernel/LargeInt.st: Added support for primitives 2002-03-23 Paolo Bonzini * kernel/Integer.st: Implemented better factorial algorithm * examples/Publish.st: Add `writing documentation for' in front of class names 2002-03-21 Paolo Bonzini * compiler/STTok.st: Skip _ inside numeric literals 2002-03-17 Paolo Bonzini * kernel/VFS.st: Created from File.st and Directory.st * kernel/FileStream.st: Put in some VFS hooks * kernel/File.st: Demand operations to a vfsHandler * kernel/Directory.st: Demand operations to a vfsHandler * kernel/MethodDict.st: Added class comment * kernel/SmallInt.st: Added class comment * kernel/File.st: Added class comment * kernel/Directory.st: Added class comment * kernel/Browser.st: Added class comment * kernel/AnsiDates.st: Added missing class comments * kernel/AnsiExcept.st: Added missing class comments * kernel/ValueAdapt.st: Added missing class comments * kernel/ObjDumper.st: Added missing class comments 2002-03-15 Paolo Bonzini * kernel/PkgLoader.st: Support a system-wide package file 2002-03-12 Paolo Bonzini *** Version 1.96.4 released * kernel/File.st: Fix some misbehavior (not bugs, simply it was not very predictable) in the filename-manipulation methods. 2002-02-26 Paolo Bonzini * kernel/Object.st: Removed calls to #debug * kernel/CObject.st: Removed calls to #debug * kernel/Behavior.st: Switch to primitive names * kernel/Builtins.st: Switch to primitive name * kernel/CFuncs.st: Switch to primitive names * kernel/CObject.st: Switch to primitive names * kernel/CompildMeth.st: Print the primitive name in #inspect * compiler/STParser.st: Parse primitive names * compiler/STParseNodes.st: Include primitive names in STMethodBodyNodes * kernel/Behavior.st: Instead of the progressive number CFunctionGensym, use the OOP to build keys for the CFunctionDescs dictionary. Also use #{...} syntax to avoid namespace clashes * kernel/Builtins.st: Removed CFunctionGensym * kernel/Object.st: Removed CFunctionDescs from the pool dictionary list 2002-02-07 Paolo Bonzini * kernel/FileDescr.st: Was not assigning to `count' in #read:numBytes: * kernel/FileDescr.st: Commented out the code in #ensureWriteable because not all devices support sending SIGIO's when they become writeable -- notably, tty's under Linux :-( 2002-02-05 Paolo Bonzini * kernel/PkgLoader.st: Fix imprecise error message 2002-01-29 Paolo Bonzini *** Version 1.96.3 released. 2002-01-22 Paolo Bonzini * kernel/Behavior.st: Added a missing period * kernel/ExcHandling.st: Added a missing period * kernel/RootNamespc.st: Added a missing period 2002-01-18 Paolo Bonzini * kernel/Builtins.st: Removed duplicated methods in ObjectMemory and SystemDictionary. * kernel/SysDict.st: Removed initialization blocks * tests/low-level/objects.st: Adapt 2002-01-17 Nigel Williams * kernel/FileDescr.st: Use exact rather than conservative implementations of #isPipe and of end-of-file detection for pipes. * kernel/ProcSched.st: Added timeSlice instance variable 2002-01-09 Paolo Bonzini * kernel/SortCollect.st: To #beConsistent, use quicksort if nothing in the collection is sorted. 2002-01-04 Paolo Bonzini *** Version 1.96.2 released 2002-01-03 Paolo Bonzini * kernel/Namespace.st: #associationAt: was returning the value. * kernel/Collection.st: Use #copyEmptyForCollect to create the result collection 2002-01-02 Paolo Bonzini * examples/RandomInt.st: Removed * kernel/Random.st: Merged examples/RandomInt.st's features. 2001-12-11 Paolo Bonzini * examples/Publish.st: Process correctly methods whose source code starts with whitespace (the compiler does not generate them, but STLoader does). * examples/StreamFilter.st: New file * kernel/HashedColl.st: use #copyEmpty: while growing 2001-11-29 Paolo Bonzini * examples/Publish.st: Use #asMetaclass to retrieve class methods since #class is inlined by the VM and cannot be overriden by proxies. * kernel/Metaclass.st: Accept dot notation to indicate nested namespaces in the pool dictionaries string 2001-11-20 Paolo Bonzini *** Version 1.96.1 released * kernel/SysDict.st: Smalltalk usually contains a reference to itself, avoid infinite loops in #hash 2001-11-19 Paolo Bonzini * kernel/Behavior.st: wrap #recompile: in an exception handler 2001-11-19 Nigel Williams * kernel/WriteStream.st: don't do #become: when growing a collection. 2001-11-13 Paolo Bonzini * examples/Debugger.st: Prefixed # to symbols in arrays * examples/Lisp.st: Prefixed # to symbols in arrays * examples/blox/Man.st: Prefixed # to symbols in arrays * examples/blox/Tetris.st: Prefixed # to symbols in arrays * examples/modules/gdbm-c.st: Prefixed # to symbols in arrays * examples/modules/md5.st: Prefixed # to symbols in arrays * examples/modules/regex.st: Prefixed # to symbols in arrays * kernel/CFuncs.st: Prefixed # to symbols in arrays * kernel/CStruct.st: Prefixed # to symbols in arrays * kernel/CompildCode.st: Prefixed # to symbols in arrays * kernel/DLD.st: Prefixed # to symbols in arrays * kernel/Date.st: Prefixed # to symbols in arrays * kernel/Directory.st: Prefixed # to symbols in arrays * kernel/ExcHandling.st: Prefixed # to symbols in arrays * kernel/File.st: Prefixed # to symbols in arrays 2001-11-04 Paolo Bonzini * kernel/FileStream.st: Adjust position after #next: 2001-10-31 Paolo Bonzini * kernel/ValueAdapt.st: Implemented Promise * kernel/BlkClosure.st: Added #forkWithoutPreemption and deprecated #valueWithoutPreemption. * kernel/Date.st: Implemented #readFrom: * kernel/Time.st: Likewise * kernel/AnsiDates.st: Likewise * kernel/Stream.st: Implemented #skip:... * kernel/SeqCollect.st: Implemented #identityIndexOf:... * kernel/Collection.st: Implemented #identityIncludes: * kernel/IdentitySet.st: Implemented #identityIncludes: as a synonym of #includes: 2001-10-26 Paolo Bonzini * kernel/AnsiExcept.st: Implemented EndOfStream. 2001-10-16 Paolo Bonzini * kernel/RootNamespc.st: Added #nameIn: * kernel/Namespace.st: Added #nameIn: * kernel/SysDict.st: Added #nameIn: * kernel/ClassDesc.st: use the environment's #nameIn: method in ClassDescription>>#nameIn: * examples/Publish.st: Support publication of entire namespaces 2001-09-15 Paolo Bonzini * kernel/AnsiExcept.st: Implement system exceptions 2001-08-28 Paolo Bonzini * kernel/CharArray.st: Allow one to specify numbers or other objects as parameters to #bindWith: 2001-06-20 Paolo Bonzini * examples/Bench.st: Modified results to those obtained with GCC 3.0's new back end (+15%!!!). 2001-06-12 Paolo Bonzini * kernel/MappedColl.st: Doc fixes. 2001-06-07 Paolo Bonzini * kernel/AnsiDates.st: Use exception handling instead of #error: * kernel/AnsiExcept.st: Likewise * kernel/ArrayColl.st: Likewise * kernel/Behavior.st: Likewise * kernel/Builtins.st: Likewise * kernel/ByteArray.st: Likewise * kernel/ByteStream.st: Likewise * kernel/CObject.st: Likewise * kernel/Character.st: Likewise * kernel/Class.st: Likewise * kernel/ClassDesc.st: Likewise * kernel/Collection.st: Likewise * kernel/ContextPart.st: Likewise * kernel/DLD.st: Likewise * kernel/Dictionary.st: Likewise * kernel/File.st: Likewise * kernel/FileDescr.st: Likewise * kernel/FileStream.st: Likewise * kernel/Float.st: Likewise * kernel/Integer.st: Likewise * kernel/Interval.st: Likewise * kernel/LargeInt.st: Likewise * kernel/Link.st: Likewise * kernel/LinkedList.st: Likewise * kernel/MappedColl.st: Likewise * kernel/Metaclass.st: Likewise * kernel/MethodDict.st: Likewise * kernel/Namespace.st: Likewise * kernel/Number.st: Likewise * kernel/OrderColl.st: Likewise * kernel/OtherArrays.st: Likewise * kernel/PkgLoader.st: Likewise * kernel/PosStream.st: Likewise * kernel/ProcSched.st: Likewise * kernel/Process.st: Likewise * kernel/Rectangle.st: Likewise * kernel/RootNamespc.st: Likewise * kernel/RunArray.st: Likewise * kernel/SeqCollect.st: Likewise * kernel/SortCollect.st: Likewise * kernel/UndefObject.st: Likewise * kernel/WriteStream.st: Likewise 2001-06-05 Paolo Bonzini * kernel/SortCollect.st: Fix methods whose parameters need not be sortable so that they do not fail. Fix #binarySearchFor:low:high: to handle sort-block that do not establish a total sort (a sorts before b, and vice versa, does not imply a = b). 2001-05-22 Paolo Bonzini * examples/Bench.st: Adjusted for the new great performance improvements (inlined primitives). 2001-05-20 Paolo Bonzini * kernel/DLD.st: Show failed linkages without duplicates. 2001-05-17 Paolo Bonzini * kernel/Number.st: Fixed bug in inequality (2 ~= 1.0). * kernel/FileStream.st: Fixed bug in positioning the file pointer before flushing the write buffer. * kernel/Delay.st: Removed a couple of debug printNls. 2001-05-17 Pahi Andras * kernel/Builtins.st: Return correct value for #perform:... if #doesNotUnderstand: is called. 2001-05-15 Paolo Bonzini *** Version 1.96 (alpha) released 2001-05-04 Paolo Bonzini * examples/modules/regex.st: Added a Regex class and declared reh_make_cacheable 2001-05-02 Dragomir Milivojevic * examples/modules/regex.st: Added more juice... 2001-04-28 Simon Britnell * kernel/DLD.st: Ensure that each library and module is included in the DLD lists only once. 2001-04-24 Paolo Bonzini * kernel/SharedQueue.st: Add support for priority queues and #peek. * kernel/Delay.st: Use SharedQueues. * kernel/BlkClosure.st: Implement #ensure: (it does not ensure anything, but has correct semantics if no exception occurs) * kernel/Semaphore.st: use #ensure: in #critical: 2001-04-16 Paolo Bonzini * kernel/FileDescr.st: Created from part of FileStream.st * kernel/FileStream.st: Partially moved to FileDescr.st 2001-04-15 Paolo Bonzini * examples/modules/md5.st: Created * kernel/ObjMemory.st: Removed the call to enableGC:. * kernel/Builtins.st: Removed the definition of ObjectMemory>>#enableGC:. 2001-04-02 Paolo Bonzini * kernel/Builtins.st: Copied a few builtins to ObjectMemory, marked them as deprecated for SystemDictionary. * kernel/initialize.st: Removed * kernel/ObjMemory.st: New file, created from initialize.st * kernel/SysDict.st: Marked a few methods as deprecated * kernel/Browser.st: send #gcMessage: to ObjectMemory instead of Smalltalk * kernel/Time.st: Use ObjectMemory instead of init blocks * kernel/FileStream.st: Use ObjectMemory to close files * Load.st: Use ObjectMemory class>>#snapshot * Reload.st: Use ObjectMemory class>>#snapshot 2001-03-28 Paolo Bonzini * tests/ansi/AnsiProtos.st: Removed * tests/ansi/AnsiSUnit.st: Removed * tests/ansi/AnsiTests.st: Upgraded * tests/ansi/load-tests.st: Updated for new structure * examples/pepe.sed: Added * examples/xml.sed: Added 2001-03-20 Paolo Bonzini * kernel/Builtins.st: Removed the file-in primitives, added three-argument #fileOp: variants. * kernel/FileStream.st: Rewritten for new buffering scheme, use #fileOp:... to file-in too. 2001-03-14 Paolo Bonzini * kernel/CStruct.st: Factored most of CStruct into CCompound. Added CUnion. 2001-02-23 Paolo Bonzini *** Released version 1.95.3 2001-02-19 Paolo Bonzini * kernel/Builtins.st: Documented the ability of #perform: & friends to receive a CompiledMethod as their first parameter. * kernel/CStruct.st: Made CStruct accept #{...} literals in the declaration. 2001-02-15 Paolo Bonzini * kernel/Behavior.st: Raise an error on invalid C call-outs 2001-02-14 Paolo Bonzini * gdbm/gdbm-c.st: New file (old gdbm.st) * gdbm/gdbm.st: New file * kernel/CStruct.st: Allow subclasses of CStruct to be generated. * kernel/File.st: Use new syntax for generating CStructs 2001-02-13 Paolo Bonzini * sunit/SUnitTests.st: Upgraded to version 3.0 * sunit/SUnitPreload.st: Ditto * sunit/SUnit.st: Ditto * sunit/SUnitScript.st: Restored from SUnit 2.7 (it is not in 3.0) * kernel/SortCollect.st: Fixed bug in #indexOf:startingAt:ifAbsent: which raised an error if the collection was empty. * kernel/SeqCollect.st: Raise an error if the starting index in #indexOf:startingAt:ifAbsent: is out of range. 2001-02-09 Paolo Bonzini * kernel/PosStream.st: Added #isExternalStream * kernel/FileStream.st: Added #isExternalStream * kernel/MthContext.st: Print namespaces in backtraces * kernel/AnsiExcept.st: Exception's coreException is now a child of ExAll, rather than ExAll * kernel/ContextPart.st: Use Process-wide unwindPoints. * kernel/ExcHandling.st: Rewritten to use marked contexts instead of separate Dictionaries (faster, neater & less buggy). * kernel/Process.st: Defined unwindPoints and its accessors. 2001-02-08 Paolo Bonzini * kernel/HashedColl.st: Keep the size of the collection a prime number (stolen from GLib). 2001-02-06 Paolo Bonzini * kernel/SeqCollect.st: correct #copyReplaceAll:with: which created wrong-sized collections. 2001-02-05 Paolo Bonzini * examples/Publish.st: Avoid overfull hboxes due to missing hyphenation. Also emit indexes. * kernel/AnsiDates.st: Added missing comments. * kernel/AnsiExcept.st: Added missing comments. * kernel/CObject.st: Added missing comments. * kernel/Date.st: Added missing comments. * kernel/DirMessage.st: Added missing comments. * kernel/ExcHandling.st: Added missing comments. * kernel/Number.st: Added missing comments. * kernel/ObjDumper.st: Added missing comments. * kernel/OtherArrays.st: Added missing comments. * kernel/PosStream.st: Added missing comments. * kernel/ProcSched.st: Added missing comments. * kernel/ScaledDec.st: Added missing comments * kernel/SortCollect.st: Added missing comments. * kernel/SymLink.st: Added missing comments. * kernel/Symbol.st: Added missing comments. * kernel/Time.st: Added missing comments. 2001-02-01 Paolo Bonzini * kernel/DLD.st: Added support for dynamically-loaded modules, removed the need for the ExternalFunctions variable. * kernel/PkgLoader.st: Added support for dynamically-loaded modules * kernel/Directory.st: Added class method #module 2001-01-31 Paolo Bonzini * kernel/Builtins.st: Moved Set builtins to HashedCollection * kernel/File.st: Added #isExecutable/#isAccessible * kernel/HashedColl.st: New file * kernel/OtherArrays.st: New file * kernel/Set.st: Moved lots of it to HashedColl.st; added methods to do arithmetic. 2001-01-30 Paolo Bonzini * kernel/Directory.st: Added #systemKernel * kernel/Time.st: Fixed one-second skews in the millisecond clock 2001-01-30 Paolo Bonzini *** Released version 1.95.1 2001-01-14 Paolo Bonzini * kernel/LargeInt.st: Fixed bugs in GCD computation which caused it to be underestimated (bugs were in #bytesLeftShift:big: and #bytesRightShift:big:) * kernel/Set.st: Recompute index when adding causes a Set to grow. * kernel/Dictionary.st: Likewise. * kernel/LookupTable.st: Likewise. 2001-01-11 Paolo Bonzini * kernel/FileStream.st: Removed declaration of #species * kernel/ByteStream.st: Declared #species to return String 2000-11-11 Jens Bjerrehuus (j.bjerrehuus@acm.org) * examples/Timer.st: Fixed missing bang * kernel/Class.st: #addClassVarName: works even if no class variables were defined. * kernel/Object.st: #ifNotNil:ifNotNil: --> #ifNotNil:ifNil: * kernel/UndefObject.st: #ifNotNil:ifNotNil: --> #ifNotNil:ifNil: 2000-11-01 Paolo Bonzini * examples/Quine.st: New file -- sorry for lack of updates (the longest since I picked up maintenance), but I really had no free time anymore! * kernel/BlkClosure.st: Define #valueWithoutPreemption * kernel/ProcSched.st: Define (and print correctly) the names for the two extreme priorities, #rockBottomPriority and #unpreemptedPriority. * kernel/Symbol.st: Define #rebuildTable, to rebuild and garbage collect the symbol table. * kernel/SymLink.st: Define a creation method, #symbol:nextLink: -- this is probably the least modified file in GNU Smalltalk!!! 2000-09-11 Paolo Bonzini * kernel/Dictionary.st: Tried to lessen usage of dirty blocks * kernel/LookupTable.st: Same as above * kernel/MethodDict.st: Same as above * kernel/Set.st: Same as above; plus, added #postLoad/#postStore * kernel/WeakObjects.st: Same as above 2000-09-09 Paolo Bonzini * kernel/Builtins.st: New meaning of primitive 90, so the name of the method that invokes it has changed to discardTranslation * kernel/MethodDict.st: Use CompiledCode>>#discardTranslation * kernel/Point.st: Fixed bug in #= 2000-09-09 Paolo Bonzini * kernel/CharArray.st: Use {} syntax. * kernel/Class.st: Use {} syntax. * kernel/Date.st: Use {} syntax. * kernel/Dictionary.st: Use {} syntax. * kernel/ExcHandling.st: Use {} syntax. * kernel/Symbol.st: Use {} syntax. * kernel/Rectangle.st: Use {} syntax. * kernel/PkgLoader.st: Use {} syntax. 2000-09-07 Paolo Bonzini *** Version 1.8.3 released * kernel/ByteArray.st: Added various shortcut methods (#uintAt: for #unsignedIntAt: etc.) * kernel/Builtins.st: Removed ByteMemory methods. * kernel/ByteMemory.st: Removed * kernel/Memory.st: Added #bigEndian and various shortcut methods (#uintAt: for #unsignedIntAt: etc.) * kernel/WordMemory.st: Removed 2000-09-01 Nigel Williams * kernel/DLD.st: Fixed typo 2000-08-13 Paolo Bonzini * kernel/ArrayColl.st: Moved here old SequenceableCollection>>#copyFrom:to: * kernel/Collection.st: Added #beConsistent * kernel/SeqCollect.st: reimplemented #copyFrom:to: to use #add: * kernel/OrderColl.st: Added support for #beConsistent, added #basicRemoveFirst and #basicRemoveLast. * kernel/SortCollect.st: Modified to use #beConsistent, fixed several buglets. 2000-08-06 Paolo Bonzini * kernel/Builtins.st: Added #basicNewInFixedSpace, #basicNewInFixedSpace: and #makeFixed. Also added error handling to #become: * kernel/Behavior.st: Added #newInFixedSpace and #newInFixedSpace:. 2000-07-18 Nigel Williams * kernel/CFuncs.st: Added #address: * kernel/DLD.st: Re-link and reset the addresses of all the externally defined functions. 2000-07-10 Paolo Bonzini * kernel/Builtins.st: Since usage of Undeclared in the kernel's source is now allowed, I removed the forward declarations. * kernel/Class.st: Added support for versionable schemas. * kernel/CompildBlk.st: Support usage of PluggableProxy. * kernel/CompildCode.st: Implemented #blockAt:. * kernel/CompildMeth.st: Support usage of PluggableProxy. * kernel/ObjDumper.st: Implemented SingletonProxy and VersionableObjectProxy. Declare usage of proxies for CompiledMethods, CompiledBlocks and Processor. Rewritten parts to avoid non-local returns. * kernel/Processor.st: implemented #printOn: and #storeOn: 2000-07-09 Paolo Bonzini * kernel/DirMessage.st: Added methods for PluggableProxy support. * kernel/ObjDumper.st: Implemented AlternativeObjectProxy, PluggableProxy. Added support for #postStore and used exception handling to ensure that it is always called. Don't use #perform: which is slow with the JIT compiler and less flexible than blocks. * kernel/Object.st: Added #postStore and methods for PluggableProxy support. 2000-07-04 Paolo Bonzini * kernel/File.st: Use the new DateTime and Duration classes * kernel/PkgLoader.st: Use the new DateTime class * test/ansi/SUnitANSI.st: Fixed a few false negatives * kernel/SeqCollect.st: Implemented #keysAndValuesDo: * kernel/RunArray.st: use #keysAndValuesDo: instead of #doWithIndex: * kernel/CharArray.st: use #keysAndValuesDo: instead of #doWithIndex: * kernel/ObjDumper.st: use #keysAndValuesDo: instead of #doWithIndex: * kernel/Date.st: use #keysAndValuesDo: instead of #doWithIndex: * kernel/OrderColl.st: Allow one to pass non-sequenceable collections to #addAll: 2000-07-03 Paolo Bonzini * kernel/AnsiExcept.st: New file * kernel/Bag.st: Added #new: (incredible that it was not here) * kernel/ExcHandling.st: added BlockClosure>>#ifError: and more changes for ANSI conformance * kernel/Builtins.st: Use Number>>#zeroDivide and #arithmeticError: to raise numeric exceptions. * kernel/Fraction.st: Likewise * kernel/LargeInt.st: Likewise * kernel/Number.st: Added #zeroDivide and #arithmeticError: * test/ansi/Protos.st: New file * test/ansi/ProtosDB.st: New file * test/ansi/ProtosInit.st: New file * test/ansi/SUnit.st: New file * test/ansi/SUnitANSI.st: New file * test/ansi/SUnitCamp.st: New file * test/ansi/SUnitPreload.st: New file * test/ansi/SUnitTests.st: New file * test/ansi/run-tests.st: New file 2000-07-02 Paolo Bonzini * kernel/Number.st: Implemented additional #retry... methods because the JIT does not like #perform:, which is used in #retry:coercing: * kernel/Builtins.st: Use the new retrying-coercion methods * kernel/Fraction.st: Use the new retrying-coercion methods * kernel/LargeInt.st: Use the new retrying-coercion methods * kernel/Number.st: #asInteger now uses #rounded for ANSI compatibility; #integerPart and #fractionPart added. * kernel/Date.st: Some changes for ANSI compliance * kernel/PosStream.st: #close is not a stub anymore. * kernel/Time.st: Some changes for ANSI compliance * kernel/AnsiDates.st: New file * kernel/ScaledDec.st: New file 2000-06-21 Paolo Bonzini * kernel/BlkClosure.st: adjust #asContext: because of the change below. * kernel/BlkContext.st: Removed the BlockContext>>#initBlock: method, replaced with a more JIT-friendly (and involute) class method called #fromClosure:parent: * test/intmath.st: Fixed a couple of "must return..." comments which were actually wrong. 2000-06-19 Paolo Bonzini * kernel/Collection.st: Rewritten #as... methods to use cascading and to use the change to #replaceFrom:to:with: below. * kernel/SeqCollect.st: allow usage of #replaceFrom:to:with: with unordered collections * kernel/SortCollect.st: To leave no holes at the front of the collection, set firstIndex to 1 in #initIndices and #makeRoomLastFor: (new method). Implemented heap algorithms. 2000-06-18 Paolo Bonzini * kernel/Collection.st: No need to call #firstIndex:lastIndex: in #asSortedCollection: because of the change in SortCollect.st (see below) * kernel/Delay.st: Reversed the ordering of the Queue's sortBlock because #removeLast is faster then #removeFirst (it saves memory because slots freed by #removeLast are reused by #add:, unlike slots freed by #removeFirst). * kernel/OrderColl.st: When removing the last item, call #initIndices 2000-06-17 Paolo Bonzini *** Released versions 1.95 (development) and 1.7.5 (stable) 2000-06-03 Paolo Bonzini * examples/Bench.st: Do one more iteration (9 instead of 8) if the JIT compiler is detected (eh eh eh...) * kernel/ContextPart.st: Added methods to detect the presence of the JIT compiler 2000-06-03 Paolo Bonzini * kernel/Array.st: #isArray returned false instead of true * kernel/BlkContext.st: Initialize returnIP in #initBlock:, using the new CompiledCode>>#compileToNativeCodeFor: method * kernel/Builtins.st: Declare CompiledCode>>#compileToNativeCodeFor: (primitive 90) 2000-05-28 Paolo Bonzini (bonzini@gnu.org) * examples/Publish.st: Output to docs/classes.texi instead of docs/classes.txi 2000-05-12 Paolo Bonzini (bonzini@gnu.org) * kernel/ByteStream.st: Avoid creating LargeIntegers to retrieve negative 32-bit numbers. This sped up the loading of collation data by 10 times! 2000-05-09 Paolo Bonzini (bonzini@gnu.org) * kernel/RootNamespc.st: #addSubspace: is now a no-op if a subspace with the given name already exists. 2000-05-04 Paolo Bonzini (bonzini@gnu.org) *** Version 1.94.90 released 2000-04-27 Paolo Bonzini (bonzini@gnu.org) * kernel/LargeInt.st: Fixed bug in #~= 2000-04-23 Paolo Bonzini (bonzini@gnu.org) * kernel/FileSegment.st: Changed length variable to size, added #withFileDo: * kernel/SortCollect.st: Removed a few non-local returns 2000-04-12 Paolo Bonzini (bonzini@gnu.org) *** Version 1.7.4 released * kernel/Behavior.st: Added private method #sharedPoolDictionaries * kernel/Class.st: Added private method #sharedPoolDictionaries * kernel/Metaclass.st: Added private method #sharedPoolDictionaries, used it to fix bug with redefinition of classes with pool dictionaries 2000-04-10 Paolo Bonzini (bonzini@gnu.org) * examples/CStream.st: Moved to compiler/STFormatter.st * examples/IndStream.st: Moved to compiler/STFormatter.st * kernel/Symbol.st: Perfected #printOn: (to be perused by formatter...) 2000-03-23 Paolo Bonzini (bonzini@gnu.org) *** Version 1.7.3 released 2000-03-11 Paolo Bonzini (bonzini@gnu.org) *** Version 1.7.2 released 2000-02-24 Paolo Bonzini (bonzini@gnu.org) * kernel/Delay.st: Fixed race condition when garbage collection suspended the interpreter and Delay class>>#timeout: was called when the process should have been already resumed. 2000-02-22 Paolo Bonzini (bonzini@gnu.org) *** Version 1.7.1 released 2000-02-22 Paolo Bonzini (bonzini@gnu.org) * kernel/File.st: Added methods to test file accessing modes. 2000-02-21 Paolo Bonzini (bonzini@gnu.org) * kernel/Builtins.st: Added a few time-zone related methods. * kernel/Time.st: Added a few time-zone related methods. 2000-02-15 Paolo Bonzini (bonzini@gnu.org) *** Version 1.7 released 2000-02-01 Paolo Bonzini (bonzini@gnu.org) * kernel/CompildCode.st: Print bytecode 132 according to the new coding 2000-01-31 Paolo Bonzini (bonzini@gnu.org) *** Sixth beta of 1.7 (labeled 1.6.85) released 1999-12-31 Paolo Bonzini * kernel/Builtins.st: Use identity for RootNamespaces' equality and the #identityHash for hashing * kernel/Symbol.st: Sending #copy, #shallowCopy or #deepCopy to a symbol was actually answering a String!! 2000-01-28 Paolo Bonzini (bonzini@gnu.org) * kernel/BlkContext.st: fixed #initBlock: for CompiledBlocks * kernel/Builtins.st: removed declarations of #adjPtrBy: and #ptrDiff:... as primitives * kernel/CObject.st: implemented #adjPtrBy: and #ptrDiff:... in Smalltalk 2000-01-24 Paolo Bonzini * kernel/BlkClosure.st: Access lots of things through CompiledBlocks. * kernel/CompiledBlk.st: Created. * kernel/CompildCode.st: Created from CompildMeth.st. * kernel/CompildMeth.st: Removed `class' and `selector' variables, which are now accessed indirectly through the descriptor (`MethodInfo') object. Moved lots of code to kernel/CompildCode.st * kernel/MethodInfo.st: Added `class' and `selector' variables 2000-01-20 Paolo Bonzini * kernel/Builtins.st: Integer primitives now defined in SmallInteger. * kernel/Integer.st: Moved part to SmallInt.st * kernel/LargeInt.st: Removed #isIdentity and #isSmallInteger (now they are not defined anymore in Integer, but rather in SmallInteger which is not a superclass of LargeInteger). * kernel/Number.st: Added abstract #asFloat method. * kernel/SmallInt.st: Created from Integer.st * test/intmath.st: `Integer largest' --> `SmallInteger largest'; `Integer smallest' --> `SmallInteger smallest'; 2000-01-15 Paolo Bonzini * kernel/ByteArray.st: C-like accessors (e.g. #intAt:) had sizeof(long) hardcoded as 4. Fixed. * kernel/Behavior.st: Fixed problem with #allInstances, when instances of the class are created during its execution. * kernel/CompildMeth.st: Use ByteArray literal in #accesses: just to show that it is possible. * kernel/Date.st: Use ByteArray literal in #daysInMonthIndex:forYear: just to show that it is possible. 2000-01-08 Paolo Bonzini * kernel/BlkContext.st: Added #isEnvironment * kernel/ContextPart.st: Use #isEnvironment in #environment, added #isEnvironment as an abstract method * kernel/MthContext.st: Added #isEnvironment * kernel/CompildMeth.st: Print new bytecode 143 1999-12-29 Paolo Bonzini * kernel/ContextPart.st: Set to nil the stack slots that become accessible because of sending #sp: to a context. * kernel/FileStream.st: Added #stdin/#stdout/#stderr accessors for global variables. * kernel/Transcript.st: Class name changed to TextCollector for consistency with other environments 1999-12-28 Paolo Bonzini *** Fifth beta of 1.7 (labeled 1.6.84) released 1999-12-27 Paolo Bonzini * examples/Debugger.st: New implementation of #blockCopy: (bytecode 200). * kernel/Builtins.st: Primitive 80 (blockCopy:) is now used by BlockClosure. 1999-12-27 Paolo Bonzini * kernel/BlkClosure.st: New `method' instance variable * kernel/ContextPart.st: Removed methodClass variable, replaced implementation of the accessor to retrieve the class from the method. * kernel/MthContext.st: New implementation of #selector. 1999-12-26 Paolo Bonzini * kernel/Behavior.st: Support for the new `class' and `selector' variables in CompiledMethods. * kernel/ClassDesc.st: Support for the new `class' and `selector' variables in CompiledMethods. * kernel/CompildMeth.st: New `class' and `selector' variables in CompiledMethods. * kernel/MethodDict.st: encapsulated #removeAssociation: which can be dangerous just like #removeKey:ifAbsent:. 1999-12-19 Paolo Bonzini * kernel/BlkContext.st: Removed home, moved receiver to ContextPart. * kernel/ContextPart.st: Removed hasBlock, made the structure of contexts more uniform (only two variables lie in the subclasses) * kernel/MthContext.st: Moved method, methodClass, receiver to ContextPart. 1999-12-06 Paolo Bonzini * kernel/Builtins.st: Hacked Float>>#hash so that '2 hash = 2.0 hash' * kernel/CompildMeth.st: Bit 30 is now part of the method flags. 1999-12-10 Paolo Bonzini * kernel/WordMemory.st: Added accessor for the `Bigendian' global variable. 1999-12-05 Paolo Bonzini * kernel/Behavior.st: ANSI asks for 65535 instance variables, so I shifted the instance specification's `number of instance vars' field right by three bits (now 262143 variables are possible). * kernel/Directory.st: Added methods to manage file names. * kernel/ExcHandling.st: Neater implementation of #pass and #signalWithArguments:, more encapsulation in the ExceptionHandler class. * kernel/File.st: Added methods to manage file names; plus, use the strerror C function. 1999-11-26 Paolo Bonzini *** Fourth beta of 1.7 (labeled 1.6.83) released 1999-11-23 Paolo Bonzini * examples/Publish.st: Fixes for Texinfo 4.0 (which produces HTML too, not just TeX and Info). * kernel/Class.st: GNU Smalltalk's #variableWordSubclasses: are actually IBM Smalltalk's #variableLongSubclasses: (fix to the compatibility methods). 1999-11-21 Paolo Bonzini * examples/bench.st: Fixes to make measurements more constant. See `e)' in the discussion of the results at the top of the file. * kernel/ClassDesc.st: #fileOutCategory:toStream: was ending a category with `!!' instead of `! !' * kernel/FileStream.st: Added #nextPutAllFlush: * kernel/Transcript.st: use #nextPutAllFlush: when stdout is the transcript. 1999-11-19 Paolo Bonzini * examples/Prolog.st: Added 1999-11-18 Paolo Bonzini * kernel/Behavior.st: Better handling of mutation -- create a lightweight class with the old representation, change the object to it and forget #specialBasicAt:. * kernel/Object.st: Better handling of mutation -- see above. 1999-11-17 Paolo Bonzini * examples/Lisp.st: Added * kernel/CharArray.st: Moved implementation of #asNumber to Number>>#readFrom: * kernel/Number.st: #readFrom: reads a Number from the current stream position, not from its start (correct semantics) 1999-11-14 Paolo Bonzini * examples/Bench.st: More comparisons added * kernel/CompildMeth.h: Move flag bits to high end, so that there is place for two additional bits if needed * kernel/BlkContext.c: BlockContexts now hold the receiver and the BlockClosure instead of the number of arguments and temporaries. 1999-11-06 Paolo Bonzini * examples/Publish.st: Support for namespaces 1999-11-01 Paolo Bonzini * kernel/ClassDesc.st: moved #nameIn: from Class. * kernel/Class.st: moved #nameIn: to ClassDescription. 1999-10-31 Paolo Bonzini *** Third beta of 1.7 (labeled 1.6.82) released 1999-10-25 Paolo Bonzini * kernel/SeqCollect.st: Added optimized version of #anyOne 1999-10-22 Paolo Bonzini * kernel/Float.st: Use the last decimal digit as a guard digit when printing * kernel/SeqCollect.st: Added #do:separatedBy: 1999-10-21 Paolo Bonzini * kernel/Builtins.st: Moved a few String primitives to CharacterArray * kernel/Object.st: Added #isCharacterArray * kernel/String.st: Moved most code to CharArray.st * kernel/CharArray.st: Created by refactoring of String. 1999-10-20 Paolo Bonzini * kernel/Object.st: Added #display* methods. * kernel/String.st: added #displayOn: and #displayString methods. * kernel/Symbol.st: added #displayOn: and #displayString methods. * kernel/Character.st: added #displayOn: methods. 1999-10-13 Paolo Bonzini * examples/Buffers.st: Created from tcp/ReadBuffer.st and tcp/WriteBuffer.st * kernel/Builtins.st: Set's #primXXX methods moved here * kernel/Float.st: #hash was not always returning integers * kernel/Set.st: Removed #primXXX 1999-10-11 Paolo Bonzini * kernel/Float.st: Added missing #integerPart (`num := self integerPart' was `num := self') in code to print the Float's integer part -- the solution to the printing bug that I had tried on Oct 2nd was wrong. * kernel/WeakObjects.st: Added #postLoad to WeakArray to make the array weak again. 1999-10-10 Paolo Bonzini * kernel/Association.st: Parts moved to kernel/LookupKey.st. * kernel/Builtins.st: Added comment for the new behavior of file-ins regarding undeclared globals (usage of the `Undeclared' dictionary). * kernel/FileStream.st: Same as above. * kernel/LookupKey.st: Recreated from parts of kernel/Association.st. * kernel/PkgLoader.st: Added ability to ignore undeclared call-outs (useful for producing documentation without recompiling the VM). 1999-10-09 Paolo Bonzini *** Second beta of 1.7 (labeled 1.6.81) released * kernel/Builtins.st: Added primitive to flush the dynamic translator's code cache. Fail on `anInteger asOop'. * kernel/CompildMeth.st: Use the primitive above. 1999-10-07 Paolo Bonzini * kernel/Behavior.st: Use MethodDictionaries; removed calls to #flushCache since they are in MethodDict.st * kernel/Builtins.st: Removed definition of primitives in Array that were there to minimize the possibility that removals inside the MethodDictionary of a class crashed the system. * kernel/MethodDict.st: Created 1999-10-05 Paolo Bonzini * kernel/ExcHandling.st: Added helper class ActiveHandlersList to avoid messy usage of ReadStreams and #copy. * kernel/Float.st: Added #ln10 class method to answer 2.302... * kernel/Number.st: Added #log. * kernel/ObjDumper.st: Fixed bugs in namespace handling. 1999-10-04 Paolo Bonzini * examples/Publish.st: Remove subclasses of CStruct from the manual. * kernel/CompildMeth.st: #literals was erroneously going into an infinite loop (^self literals). 1999-10-02 Paolo Bonzini * kernel/Float.st: Fixed \\ (was returning the floor of the result) and printing (the last integer digit of numbers with a large decimal part, such as 4.999, was misprinted -- 5.999 in this case) * kernel/Number.st: Fixed rounded (was using `truncated' instead of `floor') * test/intmath.st: Added more // and \\ tests. * test/floatmath.st: Added // and \\ tests. 1999-09-30 Paolo Bonzini * kernel/BlkClosure.st: Added #repeat * kernel/Date.st: Added #shortNameOfMonth * kernel/Stream.st: Moved methods that traditionally were in PositionableStream, but which I implemented without using PositionableStream protocol, here; added #splitAt: * kernel/PosStream.st: Opposite of above 1999-09-25 Paolo Bonzini *** First beta of 1.7 (labeled 1.6.80) released 1999-09-23 Paolo Bonzini * kernel/Set.st: Initialize in new method #initialize: * kernel/LookupTbl.st: Initialize in #initialize: * kernel/WeakObjs.st: Initialize hashed collections in #initialize: * kernel/RootNamespc.st: Initialize #Super key in #setSuperspace: 1999-09-19 Paolo Bonzini * kernel/Behavior.st: Use a WeakArray in #allInstances * kernel/Builtins.st: moved all `Smalltalk at: #... put: nil' declarations here. Fixed missing dot in Behavior>>#basicNew: * kernel/CType.st: CArrayCType subclass of CPtrCType * kernel/LookupTbl.st: Created from IdentDict.st * kernel/IdentDict.st: Mostly moved to LookupTbl.st * kernel/SeqCollect.st: moved #swap:with: to SortedCollection -- it was used just there, and meant to be used just there. * kernel/SortCollect.st: #swap:with: moved here. * kernel/WeakObjects.st: Created 1999-09-18 Paolo Bonzini * kernel/Bag.st: Added #sortedByCount. * kernel/BlockClosure.st: Don't make copies (answer the original object) * kernel/Character.st: Added #isPunctuation * kernel/UndefObj.st: Nil should not have dependents 1999-09-15 Paolo Bonzini * kernel/Directory.st: Added #create: * kernel/Object.st: Added #broadcast:with:with: * oodb/*: Added * test/chars.st: Made more comprehensive * test/exceptions.st: Added * test/sets.st: Added * test/*.base: Renamed to *.ok for easier life on 14-char systems. 1999-09-14 Paolo Bonzini * examples/Case.st: Added #ifEqualTo:do: * examples/SortCriter.st: Added * kernel/ObjDumper.st: Uses preStore and postLoad. * kernel/Object.st: Definition of preStore and postLoad. * kernel/SortCollect.st: Added DefaultSortBlock to SortedCollection; uses preStore and postLoad. 1999-09-12 Paolo Bonzini * kernel/Behavior.st: Variable instanceVariables came here from ClassDescription. * kernel/Class.st: Variables name/comment/category/environment moved to Class (they make no sense in Metaclass, so why were they in ClassDescription?) * kernel/ClassDesc.st: Combination of the two above. 1999-09-11 Paolo Bonzini * kernel/ClassDesc.st: Implementation of namespaces * kernel/Class.st: Implementation of namespaces * kernel/Namespace.st: Created from Behavior.st and SysDict.st * kernel/Object.st: Smalltalk is no longer a pool dictionary. * kernel/RootNamespc.st: Created from Behavior.st and SysDict.st * kernel/SysDict.st: Moved something to Namespace.st and RootNamespc.st * kernel/UndefObject.st: Implementation of namespaces 1999-09-10 Paolo Bonzini * examples/Queens.st: added #do: to NullQueen. * kernel/BlkClosure.st: BlockClosures are now variableWordSubclasses since the previous encoding was incompatible with the code to switch the endianness in a saved image. * kernel/PosStream.st: Added support for Cr/Lf terminators in #nextLine. 1999-09-06 Paolo Bonzini * kernel/Delay.st: #idle method now lies in ProcessorScheduler. * kernel/ProcSched.st: Added support for idle block registration. 1999-08-31 Paolo Bonzini * kernel/Collection.st: Added #with:collect: * kernel/ArrayColl.st: Added #with:collect:, removed duplicate definition of #copyWith: 1999-08-29 Paolo Bonzini *** Version 1.6.2 released. 1999-08-26 Paolo Bonzini * examples/Publish.st: Finally got hierarchy tree formatting to work. * kernel/DLD.st: Don't define the `DLD' feature since DLD.st is always loaded now. The feature is defined in lib/dict.c if the DLD functions are not stubs. * kernel/Float.st: Use CDoubleMin and CDoubleMax. * kernel/PkgLoader.st: More meaningful error messages (`package not available' instead of `key not found'). 1999-08-08 Paolo Bonzini * kernel/Builtins.st: `Smalltalk snapshot' primitive (250) removed -- the new ImageFileName global makes it redundant. * kernel/File.st: Added polite accessor to the ImageFileName global (File class>>#image). * kernel/SysDict.st: `Smalltalk snapshot' primitive (250) is now implemented in terms of the new ImageFileName global. 1999-08-07 Paolo Bonzini * kernel/File.st: Declare `unlink' (valid only for files) instead of `remove' (which works for directories too) to be used to implement File class>>#primRemove: 1999-08-07 Paolo Bonzini * examples/Case.st: Provided by Ulf Dambacher. * examples/EditStream.st: Provided by Ulf Dambacher. * examples/Watchdog.st: Provided by Ulf Dambacher. * kernel/Date.st: Handle dates like 0-Feb-1989. * kernel/MappedColl.st: Added `domain' and `map' accessors. * kernel/Transcript.st: In #next:put:, #new:withAllPut: (which does not exist) was sent to String instead of #new:withAll: * kernel/ValueAdapt.st: Added NullValueHolder. 1999-07-14 Paolo Bonzini * kernel/Float.st: Removed conditional code so that images produced by computers with different endianness can be used. * test/delays.st: Created from test/processes.st since it is the only part that fails under some architectures (e.g. SunOS) 1999-06-25 Paolo Bonzini *** Bug-fixing version 1.6.1 released. 1999-06-17 Paolo Bonzini *** Version 1.6 released. 1999-06-09 Pahi Andras * kernel/DLD.st: Fixed lots of stupid bugs (misspelled method names and more) * test/arrays.st: Renamed (used to be array.st) so that it works in case-insensitive filesystems. * test/classes.st: Renamed (used to be class.st) for same reason. * test/processes.st: Renamed (used to be process.st) for same reason. 1999-06-03 Paolo Bonzini * kernel/Builtins.st: #at:put: for C strings and aggregates (arrays/ptrs) can take both a smalltalk object and a CObject. * kernel/CObject.st: Moved some primitives to Builtins.st * kernel/CompildMeth.st: #storeOn: stored bytecodes as an Array (not a ByteArray). * kernel/Object.st: #storeOn: now uses the Object's validSize. 1999-05-31 Paolo Bonzini * kernel/CompildMeth.st: Added #stripSourceCode. * kernel/Date.st: Some bug fixes. * kernel/MethodInfo.st: Added #stripSourceCode. 1999-05-24 Paolo Bonzini * kernel/Date.st: Removed iterative algorithms, replaced with numerical ones proposed by Jeff Rosenwald (JeffRose@acm.org). 1999-05-23 Paolo Bonzini * examples/Debugger.st: Added new bytecodes 1999-05-13 Paolo Bonzini * kernel/Float.st: Finished revamped Floats -- added #hash 1999-05-08 Paolo Bonzini * kernel/Transcript.st: Moved here from blox. Modified to initially set up a Transcript on stdout. * kernel/Object.st: Changed #print and #store to work with the Transcript object. 1999-05-06 Paolo Bonzini * kernel/ExcHandling.st: Exception handlers are now per process. * kernel/Fraction.st: Added code to test for NaNs in #asFloat. Also, now I use #quo: in #reduced. * kernel/LargeInt.st: Misc bug fixes. * kernel/Process.st: Added exceptionHandlers variable. * kernel/Object.st: added #ifNil:, #ifNotNil: and companions. * kernel/UndefObject.st: added #ifNil:, #ifNotNil: and companions. 1999-05-05 Paolo Bonzini * kernel/Float.st: Added stuff to print/store infinite values and NaNs * kernel/LargeInt.st: changed divide:using: and reverseStringBase:on: to special case divisions by small (< 256) divisors. * kernel/WriteStream.st: Fixed #size -- was returning 1 more than the correct value. For example, "String new writeStream size" returned 1. 1999-05-03 Paolo Bonzini * kernel/Builtins.st: Changed the system message #booleanRequired to #mustBeBoolean for coherence with the Blue Book (I had not noted that passage). 1999-05-02 Luciano Esteban Notarfrancesco * kernel/SortCollect.st: new algorithm for #includes: and #occurrencesOf: * kernel/Number.st: new algorithm for #raisedToInteger: and #raisedTo:. Added #isRational. * kernel/Fraction.st: Added #isRational. Generality multiplied by 100. * kernel/Integer.st: #gcd: and #lcm: always return positive numbers. Added #isRational. Generality multiplied by 100. * kernel/Float.st: Generality multiplied by 100. * kernel/LargeInt.st: Generality multiplied by 100. 1999-04-29 Paolo Bonzini * kernel/CompildMeth.st: Added code to handle the 142 (replace stack top) bytecode in the #accesses: method. 1999-04-27 Paolo Bonzini *** Version 1.5.beta3 released. 1999-04-22 Paolo Bonzini * kernel/ArrayColl.st: Added #new:withAll: . * kernel/Builtins.st: added #at:/#at:put:/#basicAt:/#basicAt:put: to Array. They are needed so that, when updating method dictionaries, GST doesn't look for methods inherited by Array and defined in method dictionaries that are still in a semi-updated state (e.g. this happens when removing Collection's #inspect method, during Blox's load). Thanks to Christopher Painter-Wakefield for signaling this. 1999-04-20 Paolo Bonzini * kernel/CompildMeth.st: Added code to print the nop bytecode (139) 1999-04-16 Paolo Bonzini * kernel/ContextPart.st: Added hasBlock instance variable, moved its accessor here (used to be in the subclasses) * kernel/MthContext.st: Removed hasBlock instance variable and its accessor * kernel/BlkContext.st: Same as above * kernel/Builtins.st: Moved in (as methods in SystemDictionary) the two primitives that were in examples/PerfMonitor.st * examples/PerfMonitor.st: Nuked; its contents are now part of Builtins.st * cxtnsn/DLD.st: Modified so that if you use defineCFunc:... and DLD is used, unresolved functions are searched in dynamically linked libraries. One day I'll make it use dlopen and dlsym. 1999-04-10 Paolo Bonzini *** Version 1.5.beta2 released. * kernel/Time.st: Remove GMT from printOn: (see changes in sysdep.c). 1999-04-08 Paolo Bonzini * examples/Publish.st: Added some comment guessing. * kernel/CObject.st: Merged CPtr and CArray into CAggregate at last. * kernel/SortCollect.st: Fixed implementation of pivot selection. * kernel/File.st: Fixed file times to be returned relative to 1/1/2000 to avoid possible overflows (which would have happened around 2004 on 32-bit machine, and around 8.000.000.000 AD on 64-bit ones...). 1999-03-15 Paolo Bonzini *** Version 1.5.beta1 released. * examples/Publish.st: Some bug fixes now that we use it to generate GST's manual. 1999-03-13 Paolo Bonzini * examples/Publish.st: Added DocumentationClassPublisher (refactored from HTMLClassPublisher) and TexinfoClassPublisher. 1999-02-27 Paolo Bonzini * kernel/Builtins.st: Added ProcessorScheduler>>#isTimeoutProgrammed as part of the changes below for Delay. * kernel/Delay.st: Added backgroundProcess in Delay's #startDelayLoop class method, and added #idle class method. Fixed so that delays across two evaluations (i.e. an evalua- tion starts, a delay is pending when it ends, and then another evaluation starts which must discard that delay and accept new ones) works. * examples/Dinner.st: Ditto 1999-02-26 Paolo Bonzini * kernel/Class.st: #removeClassVarName: referred to non- existent method #classVariables (instead of #classPool) 1999-02-23 Paolo Bonzini * kernel/Symbol.st: Changed storeOn: to properly handle #'ab cd' symbols and printOn: to use the version inherited from String 1999-02-22 Paolo Bonzini * kernel/Bag.st: printOn: sent `print: ($ )' instead of `space' * examples/Dinner.st: Created. * kernel/Process.st: Added various accessors for the regression tests, changed many things because of changes in the VM, new experimental interrupt mechanism. * kernel/ProcSched.st: Added various accessors to account for the changes in Process. * kernel/Builtins.st: Moved #blockCopy:... to ContextPart 1999-02-19 Paolo Bonzini * examples/Queens.st: Created. 1999-02-17 Paolo Bonzini * kernel/SysDict.st: Added class accessors (eg allBehaviorsDo:) 1999-02-16 Paolo Bonzini * kernel/CompildMeth.st: Changed for new representation of literals 1999-02-15 Paolo Bonzini * kernel/PosStream.st: Fixed #reset to use #position: * kernel/FileStream.st: Added selectors for new style opening modes (FileStream open: 'foo' mode: FileStream read) 1999-02-14 Paolo Bonzini * kernel/ContextPart.st: Finally got the unwinding system to work. 1999-02-13 Paolo Bonzini * kernel/Symbol.st: Added isSymbolString: * kernel/CType.st: Great! Factored out everything in CScalarCType! C*Type are now instances of CScalarCType. So we save a source of confusion (is it CByteCType or CByteType?!?) and ten classes which were carbon copies. 1999-02-12 Paolo Bonzini * examples/Publish.st: Added HTML output 1999-02-09 Paolo Bonzini * examples/Tokenizer.st: Removed recording, which was way too slow and in fact not even needed by the compiler. * kernel/Behavior.st: Fixed bug in #extractEvalChunk: not handling unterminated string literals. * kernel/Collection.st: Added #removeAll:ifAbsent: 1999-02-08 Paolo Bonzini * kernel/ExcHandling.st: fixed bug with unwind mechanism: in code like [ [ 1/0 ] valueWithUnwind ] on: ExAll do: [ :sig | ... ] the exception handler must NOT be used - in other words, if we are inside a #valueWithUnwind, outer exception handlers are momentarily disabled. * kernel/PkgLoader.st: Created. * Load.st: Created. * Reload.st: Created. 1999-02-05 Paolo Bonzini * kernel/ExcHandling.st: Added ExUserBreak. * kernel/LinkedList.st: Fixed missing dot problem - probably I had introduced it earlier. 1999-02-04 Paolo Bonzini * kernel/ContextPart.st: Fixed bug in the unwinding system (using SystemDictionary>>#halt did not work properly) 1999-02-01 Paolo Bonzini * kernel/Builtins.st: 'self perform: ' now acts like ' sendTo: self' - stole from Dolphin Smalltalk: not particularly useful, but makes GST more `universal' * kernel/Symbol.st: Added with:... * kernel/ObjDumper.st: Changed superclass to Stream. Added proxy feature. * kernel/IdentDict.st: Created a separate version of growBy: which does not involve Associations (which are not used by IdentityDictionaries). This halved the execution time for Andreas Klimas' little torture test (examples/mixed/torture.st), performing half the GCs. * kernel/FileStream.st: Fixed open and popen to use basicNew instead of new. new is now disabled. 1999-01-31 Steve Byrne * kernel/Builtins.st: Switched FileStream to returning nil on failure only if errno = 0. If not, it is probably better to check the errno. Things like search paths, etc, can be still implemented (from the highest level to the lowest) a) by using methods like open:mode:ifFail: b) by using new exception handling mechanisms c) by using methods like fileOp:ifFail: - see open:mode:ifFail: 1999-01-29 Paolo Bonzini * kernel/CObject.st: Added CBoolean. * kernel/CType.st: Added CBooleanCType * kernel/Boolean.st: Added `self subclassResponsibility' methods * kernel/True.st: Added asCBooleanValue * kernel/Browser.st: Changed the BrowserClassesValid global (brrr!!!!) to a more sedate-sounding class variable. 1999-01-28 Paolo Bonzini * kernel/FileStream.st: #close now sets the `file' instance variable to nil, to prevent multiple closes of the same file. At least under Win32 this does not usually cause SIGSEGV or similar: however you might end up closing the file descriptor for some other open file, resulting in difficult to catch bugs * kernel/Behavior.st: Added a few goodies needed to make lightweight classes work a little better (#new class method, #name instance method) * kernel/LargeInt.st: Added ~= 1999-01-27 Paolo Bonzini * kernel/Date.st: Changed now that assignment to argument is invalid. Fixed asSeconds to answer seconds from 1/1/1901 - with LargeIntegers, there's no reason to answer seconds from 1/1/1970. 1999-01-26 Paolo Bonzini * kernel/File.st: Changed now that assignment to argument is invalid * kernel/CompildMeth.st: Also * kernel/Integer.st: Also * kernel/ObjDumper.st: Also * kernel/OrderColl.st: Also * kernel/Point.st: Also * kernel/Rectangle.st: Also * kernel/SeqCollect.st: Also * kernel/Set.st: Also * kernel/String.st: Also * kernel/LargeInt.st: Also * kernel/Collection.st: Changed now that assignment to argument is invalid. Switched to quicksort for implementing #asSortedCollection:. * kernel/SortCollect.st: Changed now that assignment to argument is invalid. Switched to quicksort for implementing #asSortedCollection:. 1999-01-18 Paolo Bonzini * kernel/Float.st: Fixed up floating point printing to round correctly. It should work now... * kernel/LargeInt.st: Implemented a faster way to print LargeIntegers: I split them into small parts which stay into a small integer: this usually results in executing a lot fewer bytecodes (650,000 instead of 5,500,000 to print 1e36)!! * kernel/Integer.st: Added special floorLog: implementation. Added largest/smallest. 1999-01-16 Paolo Bonzini * examples/Tokenizer.st: Added line counting * kernel/ByteStream.st: Created. * kernel/ByteArray.st: Added Memory-style accessors. Very interesting!! 1999-01-15 Paolo Bonzini * kernel/WriteStream.st: Removed maxSize instance variable 1999-01-13 Paolo Bonzini * kernel/SysDict.st: Added access to the command line arguments. * kernel/CFuncs.st: Added getArgc and getArgv 1998-12-15 Paolo Bonzini * examples/Publish.st: Added class hierarchy (previously methods laid in ClassDescription). 1998-12-10 Paolo Bonzini * kernel/ObjDumper.st: Added support for byte objects with fixed instance variables. 1998-12-09 Paolo Bonzini * kernel/File.st: Changed struct Stat format for portability. * kernel/LargeInt.st: Fixed bug in basicRightShift: 1998-12-01 Paolo Bonzini * kernel/Object.st: Added postCopy 1998-11-29 Paolo Bonzini * kernel/Metaclass.st: Finished integration of class-instance variables 1998-11-27 Paolo Bonzini * kernel/Character.st: Added lookup table for speed 1998-11-25 Paolo Bonzini * kernel/Rectangle.st: Changed #intersect to make it work ;-) * kernel/Builtins.st: Added String>>hash and ByteArray>>hash 1998-11-24 Paolo Bonzini * kernel/ExcHandling.st: Now uses ContextPart class>>#unwind mechanism * examples/PushBack.st: Added #position and #position: * kernel/Metaclass.st: Added methods for class pool/shared pools, which delegate their work to Class 1998-11-23 Paolo Bonzini * kernel/BlkContext.st: Switched superclass to ContextPart. * kernel/MthContext.st: Switched superclass to ContextPart. * kernel/ContextPart.st: Created. 1998-11-18 Paolo Bonzini * examples/Debugger.st: Added experimental bytecode simulator. 1998-11-14 Paolo Bonzini * kernel/CStruct.st: Changed to subclass of CObject and changed implementation of inspection for easier port to Blox. 1998-11-10 Paolo Bonzini * kernel/UndefObject.st: Added class creation methods. * kernel/Object.st: Added class declaration now that nil defines class creation statements * kernel/Autoload.st: Class directly created as subclass of nil. 1998-11-05 Paolo Bonzini * kernel/Metaclass.st: Added instanceVariableNames: for class-instance variables. Modified mutation policy to be a bit more restrictive but logical. 1998-10-21 Paolo Bonzini * examples/CompFileSeg.st: Created. 1998-10-15 Paolo Bonzini * kernel/CObject.st: Added CSmalltalk. Turned to a variable word subclass to make access to the address simpler and not cause SIGSEGVs on trying to access the address instance variable as an object * kernel/CType.st: Added various storeOn: methods, and classes CScalarCType and CSmalltalkCType 1998-10-13 Paolo Bonzini * kernel/Float.st: Changed to a variable byte subclass. * kernel/Number.st: Added #zero and #unity 1998-10-12 Paolo Bonzini * kernel/BlkClosure.st: Created from BlkContext.st. * kernel/SeqCollect.st: Switched to copyEmpty: about a week ago. Now tried to change to:do: to whileTrue: in a desperate attempt at gaining more speed ;-) * kernel/BlkContext.st: Changed to support blocks as closures 1998-10-11 Paolo Bonzini * kernel/Collection.st: Added copyEmpty:, copyEmpty now uses it. * kernel/Dictionary.st: Changed growing mechanism and other methods to use #copyEmpty: Also, now #keyAtValue:ifAbsent: uses identity to compare objects. This was marked as a 'questionable' change in Brad Diller's extras.st file, but it turns out that most Smalltalks implement this method this way. * kernel/OrderColl.st: Switched to using copyEmpty: when growing. * kernel/Set.st: Switched to using copyEmpty: when growing. 1998-10-10 Paolo Bonzini * kernel/LargeInt.st: Removed 'self sign = 0' tests, replaced with overridden methods in LargeZeroInteger. 1998-10-08 Paolo Bonzini * kernel/ArrayColl.st: Moved here the growing methods that used to be in SequenceableCollection. Why weren't they here? OrderedCollection has a different growing system... 1998-10-04 Paolo Bonzini * kernel/Behavior.st: Fixed symbol that was being printed instead of nextPutAll:'d in definition of C functions. 1998-09-30 Paolo Bonzini * kernel/Rectangle.st: Made #origin, #corner, #bottomRight and #topLeft return copies of the origin and corner. This is for consistency with #bottomLeft, #topCenter, etc. * kernel/TokenStream.st: Removed a few methods whose implementation was the same as Stream's. 1998-09-29 Paolo Bonzini * kernel/Object.st: Switched dependancy mechanism to use IdentitySets. Also declared Dependencies as part of Smalltalk. 1998-09-28 Paolo Bonzini * kernel/Set.st: Changed storeOn: to avoid hard coding Set as the class name. * kernel/CStruct.st: Changed to a fixed subclass. Added 'put' methods. * kernel/IdentitySet.st: Created. * kernel/Directory.st: Promoted to kernel from cxtnsn. * kernel/File.st: Promoted to kernel from cxtnsn. 1998-09-25 Paolo Bonzini * kernel/ValueAdapt.st: Created. 1998-09-18 Paolo Bonzini * kernel/Time.st: Fixed possible secondClock overflow. Added #asSeconds * kernel/Date.st: Fixed possible secondClock overflow. Now it will overflow somewhen in 2038. Hope 64-bit machines are widespread enough by that time... I'll be 58. 1998-09-15 Paolo Bonzini * kernel/Builtins.st: Added CObject>>free, String>>valueAt:, String>>valueAt:put: * kernel/Random.st: Changed algorithm. Needed because, with new LargeInteger support, the old algorithm created a lot of temporary objects and caused a lot of GCs. This algorithm uses Floats; it has approximately the same chisquare as the old one. The performance is not as good as when it used small Integers, but better than LargeIntegers. There are algorithms which use small Integers without overflowing; I know about one of them, but it only works with 32 bit words and ours only have 30 bits. Tell me if you can find one! 1998-09-14 Paolo Bonzini * kernel/BlkContext.st: Added accessr functions; there didn't seem to be a good reason why they weren't there in the first place. * kernel/MthContext.st: Oops... methodClass instance variable was missing! * kernel/BlkContext.st: Added printOn: and backtrace methods * kernel/PosStream.st: Modified so that upTo:, upToAll:, skipTo:, upToEnd, skipToAll: operate unidirectionally on the receiver. This is needed to make them work with special streams such as stdin. * kernel/MthContext.st: Added printOn:, home and backtrace methods 1998-09-10 Paolo Bonzini * kernel/Builtins.st: Added support for LargeIntegers. This included adding a 'fail' section to Integer>>asFloat. Also changed asObjectNoFail to return nil if bad OOP index. * kernel/WordMemory.st: Added LargeInteger support (well, actually just removed 'sorry, no LargeIntegers yet' errors); shifted to to bitShift: instead of * and // (which are slow with LargeIntegers). Also now #at:put: returns the stored value (which is what it was always supposed to do, like any other #at:put:). Finally, the size of a word is now CLongSize instead of always 4 bytes. * kernel/Time.st: Fixed secondClock to use LargeIntegers. 1998-09-09 Paolo Bonzini * kernel/initialize.st: Modified to initialize LargeInteger. 1998-09-08 Paolo Bonzini * kernel/Builtins.st: Added Behavior>>#flushCache. * examples/Tokenizer.st: Created from Tok * examples/PushBack.st: Removed recording capability, which was too expensive in terms of performance, and moved it to Tokenizer. * kernel/LargeInt.st: Created. 1998-09-07 Paolo Bonzini * kernel/WriteStream.st: Changed the growing policy so that WriteStreams are more efficient at concatenating data. 1998-09-06 Paolo Bonzini * kernel/MethodInfo.st: Added setSourceCode: to support compiler. 1998-09-03 Paolo Bonzini * kernel/Set.st: Merged changes by Brad Diller to solve rehash bug. Added primAt:/primAt:put: to support subclasses that for example store data on disk or on a separate instance variable. * kernel/Float.st: Added #asFraction using a continued fractions algorithm (ugh!) * kernel/Date.st: Extended to make it more flexible. * kernel/Interval.st: Fixed bug in #size, returning negative sizes if step < 0. Changed superclass to ArrayedCollection. * kernel/Fraction.st: Integrated changes.st. * kernel/Behavior.st: Merged changes by Brad Diller. * kernel/Builtins.st: Merged changes by Brad Diller. * kernel/ClassDesc.st: Merged changes by Brad Diller. * kernel/Metaclass.st: Merged changes by Brad Diller. * kernel/Object.st: Merged changes by Brad Diller. * kernel/IdentDict.st: Merged changes by Brad Diller to solve rehash bug. * kernel/Dictionary.st: Merged changes by Brad Diller to solve rehash bug. Also modified add: to resuse the existing Association if there is one, rather than always using the parameter. Changed hashing so that hashing a dictionary that contains itself is not a problem. * kernel/Class.st: Merged corrections by Brad Diller. * kernel/Association.st: Switched superclass to be Magnitude. Added class equality test to Association>>#= * kernel/DirMessage.st: Created. * kernel/RunArray.st: Created around January 1997. * kernel/ObjDumper.st: Created around March 1997. * kernel/ExcHandling.st: Now uses SystemDictionary>>#halt. Thanks Brad Diller. 1998-09-02 Paolo Bonzini *** Began development of version 1.6 1997-07-23 Paolo Bonzini * kernel/ExcHandling.st: Created. 1996-04-15 Paolo Bonzini * kernel/Set.st: Refactored to reduce duplicated code in Dictionary and IdentityDictionary. 1995-09-30 Steve Byrne *** Version 1.1.5 released. 1995-09-16 Steve Byrne * kernel/CType.st: Removed separate valueType defintion for pointers and arrays (returning eltCType); using the inherited version instead. * kernel/Fraction.st: Added storeOn:, cleaned up formatting a bit. * kernel/Class.st: Fixed a bug in subClass:... was saying 'words: true', which means that the object consists of non-gc'ed words. subClass is pointers which are GC'ed, and saying word: true was just plain 100% wrong. 1995-09-09 Steve Byrne * kernel/CType.st: Adjusted sizes of scalar types to use actual values for the platform instead of constant values that Smalltalk made up. 1995-09-04 Steve Byrne * kernel/Class.st: Incorporated (finally) Jim Fulton's fix to the = operator. * kernel/Object.st: Incorporated (finally) Jim Fulton's fixes to removeDependent: 1995-08-26 Steve Byrne * kernel/Builtins.st: Modified Behavior #new & friends (primitives 70 & 71) to issue errors when they are used inappropriately (such as sending #new to an indexable class). 1995-07-23 Steve Byrne * kernel/CStruct.st: Added struct datatypes int and uInt. 1995-07-16 Steve Byrne * kernel/Behavior.st: Fixed instsize to correctly shift by 4, now that bit 0 (st) is reserved for the hasFinalize flag. 1995-07-14 Steve Byrne * kernel/Metaclass.st: Fixed so that invalid variable names cannot be declared. 1995-05-29 Steve Byrne * kernel/Boolean.st: Fixed to have a simple deep copy and shallow copy. 1995-05-07 Steve Byrne * kernel/CObject.st: Added usage of more machine size constants (float,long, ptr, double). 1995-05-06 Steve Byrne * kernel/CStruct.st: Updated for new C type system. 1995-05-01 Steve Byrne * kernel/CType.st: Changed CType>>cObjectType to return CObject instead of subclass responsibility. 1995-04-29 Steve Byrne * kernel/CType.st: Added cObjectType -- may be replacing what the baseType method was, but this is more descriptive. Also added a new operation on CType instances to create a new CObject subclass from the CType instance. * kernel/CObject.st: Moved the creation of CType instances into CType. Removed forward declaring of CType instances from this file and changed the load order to load CObject first since it now has no dependencies on the CType symbols. * kernel/CType.st: Moved the creation of the instances of CType subclasses into this file -- makes more sense here. * kernel/CType.st: Removed baseType -- it appears to have no function now. 1995-01-08 Steve Byrne * kernel/CObject.st: Converted to new types. * kernel/CObject.st: Fixed some bugs with pointer subtraction. 1995-01-02 Steve Byrne * kernel/CType.st: Hacked for new type architecture. 1994-10-08 Steve Byrne * kernel/Builtins.st: Added SystemDictionary>>growTo: 1994-09-15 Steve Byrne *** Version 1.2.alpha1 released. 1994-08-30 Steve Byrne * examples/MemUsage.st: Added header stuff * examples/PrtHier.st: Added header stuff. 1994-08-21 Steve Byrne * kernel/Behavior.st: Adjusted tests for low bit int marking. * kernel/CompildMeth.st: Fixed for low bit int marking 1994-08-14 Steve Byrne * kernel/Builtins.st: Fixed ~~ on integers to return true (the objects did not match) if the primitve failed. 1994-07-24 Steve Byrne * kernel/FileStream.st: Added class>>require: 1994-07-10 Steve Byrne * kernel/ClassDesc.st: Fixed instVarNames to deal properly with classes which have no instance variables. * kernel/MthContext.st: Added accessr functions; there didn't seem to be a good reason why they weren't there in the first place. * kernel/Class.st: Fixed allClassVarNames and allSharedPools to properly deal with nil collections of class variables or pool dictionaries. 1994-07-02 Steve Byrne * kernel/SysDict.st: Fixed dependenciesAt: to return nil if there was no dependency already present. 1994-06-12 Steve Byrne * kernel/CObject.st: Added adjPtrBy:, derefAt:, etc. (finally). 1994-04-30 Steve Byrne * kernel/Builtins.st: Added incrBy: 1994-04-09 Steve Byrne * kernel/CObject.st: Added CScalar, value: methods on scalar instances as a shorthand notation for instance creation, started folding in the effects of the CType new method. * kernel/CType.st: Added alloc:type: 1994-04-05 Steve Byrne * kernel/Builtins.st: Added CObject>>alloc:type: 1994-03-26 Steve Byrne * kernel/WordMemory.st: Added little endian support. 1994-02-06 Steve Byrne * kernel/ProcSched.st: Fixed the 'symbolic constants' for priority to actually return their values, instead of returning self (duh!). 1993-10-17 Steve Byrne * kernel/Message.st: Added accessors for the components. 1993-10-16 Steve Byrne * kernel/ProcSched.st: Fixed yield to operate correctly in the presence of repeated higher priority interrupts. * kernel/ClassDesc.st: Fixed addInstVarName: specially treat meta classes and grow their single class instances when new instance variables are added to the class. 1993-10-03 Steve Byrne * kernel/ArrayColl.st: Put in #copy, to use replace from to get the nice efficient copy that we can have if we are an array. 1993-10-01 Steve Byrne * kernel/Dictionary.st: Fixed removeKey:ifAbsent: to evaluate the ifAbsent block if the key actually was absent. Previously, this was being evaludated only if the entire dictionary was full and the key was not found. 1993-09-26 Steve Byrne * kernel/Collection.st: Made exceptionBlock's value in detect:ifNone: be returned, so the exception handler could just yield a value if it wanted. * kernel/String.st: Fixed some methods to check its second operand's type before calling into primitives which don't check type. 1992-11-27 Steve Byrne * kernel/Class.st: Fixed variableSubclass:... to correctly mark new subclasses as being pointers and indexable, but not words (words implies unscanned raw data). * cxtnsn/DLD.st: Added support to DLD for searching through a list of libraries to resolve references, with the default being libc. 1992-05-25 Steve Byrne * kernel/Browser.st: Added support for Emacs caching class names 1992-02-23 Steve Byrne * kernel/String.st: Added asInteger and asByteArray. 1992-02-16 Steve Byrne * kernel/Autoload.st: Created in the 1.1 timeframe * kernel/Fraction.st: Created in the 1.1 timeframe * examples/Publish.st: Created 02 92. * kernel/Browser.st: Created a while ago * kernel/CType.st: Created summer 90 * kernel/CObject.st: Created summer 90. * kernel/CStruct.st: Created summer 90. 1992-02-15 Steve Byrne * kernel/Collection.st: Switched the collection creating enumerators to use the copyEmpty message, so it can be overridden by subclasses (like SortedCollection) when copying empty involves more than just doing a new. 1991-12-14 Steve Byrne * kernel/ByteArray.st: Added asString -- generally useful functionality, but especially for STIX. 1991-11-28 Steve Byrne * kernel/Builtins.st: Added SystemDictionary byteCodeCounter. * kernel/ByteArray.st: Added growSize method -- 10 wasn't right, and we should probably base the grow size on the size of the object in question. * kernel/ByteArray.st: Switched shallowCopy to use faster primitives. 1991-11-02 Steve Byrne * kernel/Builtins.st: Fixed == and ~~ definitions for Integer to fail if the integers aren't = (including the case where they aren't both integers). Used to retry:coercing: which lost badly. 1991-10-20 Steve Byrne * kernel/Builtins.st: Added support for user level control of GC growth rate flags. 1991-09-22 Steve Byrne * kernel/FileStream.st: Added #popen:dir:ifFail: and #open:mode:ifFail: so that open failures can be explicitly handled. Thanks to Michael Richardson for the brilliant idea! * kernel/Builtins.st: Switched FileStream to returning nil on failure, so that higher level methods can chose to deal with failure. This was due to a brilliant observation by Michael Richardson. Now that higher level functions can handle failure, things like search paths, etc, can be trivially implemented. 1991-09-15 Steve Byrne * kernel/CompildMeth.st: Adjusted to account for larger numbers of primitives, literals, and temporaries. 1991-07-28 Steve Byrne * kernel/Dictionary.st: Fixed #= to check argument class. Also fixed printing and storing to use cascaded messages. * kernel/Set.st: Checks argument type better. * kernel/Bag.st: Now checks args better. * kernel/IdentDict.st: Fixed #= to check argument class. Converted to use cascaded printing. 1991-07-19 Steve Byrne * cxtnsn/DLD.st: Created 1991-07-12 Steve Byrne * kernel/Date.st: Added methods for comparing, and for hashing dates. Also fixed storing to use cascaded messages. * kernel/Time.st: Added methods for comparing, including #= and #hash. 1991-07-10 Steve Byrne * kernel/Rectangle.st: Added #= and #hash methods. * kernel/Point.st: Added = for Points (= from Object isn't right) * kernel/Stream.st: Added store: for streams (can't imagine why it wasn't here before). * kernel/Rectangle.st: Altered the printing and storing to use cascaded messages. 1991-07-05 Steve Byrne * kernel/FileStream.st: Added fileIn:line:from:at: so that when Emacs sends out an expression or a method definition to Smalltalk the error messages accurately report the line number. * kernel/Builtins.st: Added fileInLine:fileName:at: to improve error reporting and recording of file position information for later browsing. 1991-06-26 Steve Byrne * kernel/False.st: Fixed ifFalse: to send value to falseBlock 1991-06-06 Steve Byrne * kernel/FileStream.st: Fixed open and popen to use self new instead of FileStream explicitly. * kernel/Builtins.st: Switched declare and execution tracing from being direct primitives to a more general primitive mechanism. 1991-05-18 Steve Byrne * kernel/Delay.st: Actually implemented the thing. 1991-04-20 Steve Byrne * kernel/SysDict.st: Added some methods for testing and modifying implementation specific features. * kernel/Behavior.st: Added methodsFor:ifFeatures: 1991-03-25 Steve Byrne * kernel/Object.st: Added -> operator. 1991-03-24 Steve Byrne * kernel/Float.st: Fixed up floating point printing to take account of the number of digits printed in the integer part when printing the fractional part. 1991-03-23 Steve Byrne * kernel/Builtins.st: Added Integer primitives == and ~~ for more efficient operation. 1991-03-16 Steve Byrne * kernel/Array.st: Fixed class creation to be separate statement from class commenting. * kernel/ArrayColl.st: Class creation now separate statement. * kernel/Association.st: Class creation now separate statement. * kernel/Bag.st: Class creation now separate statement. * kernel/Behavior.st: Class creation now separate statement. * kernel/BlkContext.st: Class creation now separate statement. * kernel/Boolean.st: Class creation now separate statement. * kernel/ByteArray.st: Class creation now separate statement. * kernel/ByteMemory.st: Class creation now separate statement. * kernel/Character.st: Class creation now separate statement. * kernel/Class.st: Class creation now separate statement. * kernel/ClassDesc.st: Class creation now separate statement. * kernel/Collection.st: Class creation now separate statement. * kernel/CompildMeth.st: Class creation now separate statement. * kernel/Date.st: Class creation now separate statement. * kernel/Dictionary.st: Class creation now separate statement. * kernel/False.st: Class creation now separate statement. * kernel/FileSegment.st: Class creation now separate statement. * kernel/Float.st: Class creation now separate statement. * kernel/IdentDict.st: Class creation now separate statement. * kernel/Integer.st: Class creation now separate statement. * kernel/Interval.st: Class creation now separate statement. * kernel/Link.st: Class creation now separate statement. * kernel/LinkedList.st: Class creation now separate statement. * kernel/Magnitude.st: Class creation now separate statement. * kernel/MappedColl.st: Class creation now separate statement. * kernel/Memory.st: Class creation now separate statement. * kernel/Message.st: Class creation now separate statement. * kernel/MethodInfo.st: Class creation now separate statement. * kernel/MthContext.st: Class creation now separate statement. * kernel/Number.st: Class creation now separate statement. * kernel/PosStream.st: Class creation now separate statement. * kernel/ProcSched.st: Class creation now separate statement. * kernel/Process.st: Class creation now separate statement. * kernel/RWStream.st: Class creation now separate statement. * kernel/Random.st: Class creation now separate statement. * kernel/ReadStream.st: Class creation now separate statement. * kernel/Semaphore.st: Class creation now separate statement. * kernel/SeqCollect.st: Class creation now separate statement. * kernel/Set.st: Class creation now separate statement. * kernel/SortCollect.st: Class creation now separate statement. * kernel/Stream.st: Class creation now separate statement. * kernel/String.st: Class creation now separate statement. * kernel/SymLink.st: Class creation now separate statement. * kernel/Symbol.st: Class creation now separate statement. * kernel/SysDict.st: Class creation now separate statement. * kernel/Time.st: Class creation now separate statement. * kernel/TokenStream.st: Class creation now separate statement. * kernel/True.st: Class creation now separate statement. * kernel/UndefObject.st: Class creation now separate statement. * kernel/WordMemory.st: Class creation now separate statement. * kernel/WriteStream.st: Class creation now separate statement. 1991-03-04 Steve Byrne * kernel/FileStream.st: Added verbose flag. 1991-02-16 Steve Byrne * kernel/Dictionary.st: Override the #new method from builtins when this file is loaded so that subclasses of Dictionary have a proper #new method instead of the built-in one that only creates Dictionary instances. 1991-02-07 Steve Byrne * kernel/Collection.st: Fixed detect: to return the value that detect:ifNone: returns. 1991-02-04 Steve Byrne * kernel/String.st: Fixed duplicate fileName definition to be filePos 1991-01-22 Steve Byrne * kernel/CFuncs.st: Added putenv. 1991-01-01 Steve Byrne * kernel/WriteStream.st: Added print: and store: so that printing and storing can be cascaded. 1990-12-29 Steve Byrne * kernel/SeqCollect.st: Added = test to check sub elements for equality. * kernel/SeqCollect.st: Added hash function. * kernel/ArrayColl.st: Removed = and hash (put them into SequenceableCollection). 1990-11-10 Steve Byrne * kernel/ClassDesc.st: Implemented compile:classified: and compile:classified:notifying:. * kernel/Behavior.st: Implemented compile:notifying: 1990-11-09 Steve Byrne * kernel/Integer.st: Converted to use fractions. * kernel/Number.st: Put in changes for fractions. 1990-11-05 Steve Byrne * kernel/Object.st: Fixed bug with addDependent: -- syntax error. 1990-11-01 Steve Byrne * kernel/Behavior.st: Fixed isBytes to return true only if the object is not pointers and not words. 1990-09-22 Steve Byrne * kernel/False.st: Changed printOn: to reflect changes in String>>#printOn:. * kernel/True.st: Changed printOn: to reflect new String printOn: (so we can't use it any more). * kernel/Date.st: Changed to reflect the changes required by String>>#printOn:. * kernel/Character.st: Changed character to always print with a leading $. * kernel/CompildMeth.st: Fixed printOn method to account for change to String printOn:. * kernel/Class.st: Implemented classVarNames and allClassVarNames. Implemented sharedPools and allSharedPools. 1990-09-21 Steve Byrne * kernel/Bag.st: Removed printOn: method; the one from Collection does the right thing. * kernel/Set.st: Removed printOn: method; the one from Collection is fine. * kernel/LinkedList.st: Removed printOn: method; the one from Collection should be ok. Also, the storeOn: method from Collection should be ok. * kernel/ArrayColl.st: Removed storeOn: method; doesn't seem to be the right thing. * kernel/Integer.st: Fixed printOn: to reflect the fact that String printOn: no longer "does the right thing". * kernel/Collection.st: Fixed store: to be storeOn: * kernel/ClassDesc.st: Fixed the implementation of instVarNames to just return the variables defined by the current class, and added implementatinos of allInstVarNames and subclassInstVarNames. * kernel/Array.st: Added printOn: and storeOn: methods. * kernel/Symbol.st: Added printOn: to print the un-sharped version of the symbol, since string printOn: changed. * kernel/Behavior.st: Changed allSubclassesDo: to use ALL subclasses, both direct and indirect. * kernel/Dictionary.st: Changed printOn: to print the associations directly. * kernel/String.st: Changed printOn: to print with quote marks. On re-reading the documentation it appears as if this is the proper behavior (sigh). * kernel/UndefObject.st: Fixed due to String printOn: change. 1990-09-20 Steve Byrne * kernel/SeqCollect.st: Fixed indexOfSubCollection (it was off by one and did too much computation. * kernel/Float.st: Fixed storeOn: to not be recursive. 1990-09-16 Steve Byrne * kernel/Behavior.st: Implemented whichSelectorsReferTo: and scopeHas:ifTrue:. 1990-08-03 Steve Byrne * kernel/Builtins.st: Added definition of CObject class alloc:. 1990-05-22 Steve Byrne *** Version 1.1.1 released (I think. I added this on 05 10th, 1999... --- pb) 1990-05-20 Steve Byrne * kernel/WriteStream.st: Fixed semantics of write streams so that they return only the characters that have been written to them. * kernel/RWStream.st: Fixed to accomodate changes in WriteStream. 1990-05-19 Steve Byrne * kernel/FileStream.st: Rewrite contents to take advantage of the new FileStream>>size method. * kernel/Stream.st: Added print: for streams. 1990-05-16 Steve Byrne * kernel/Character.st: Changed from being variableSubclass to variableWordSubclass. * kernel/Metaclass.st: Changed the implementation of name:... to try to preserve an existing class (if possible). The original code exists in newMeta:... * kernel/Class.st: Improved error checking: you now cannot create a subclass of a class whose type is not compatible (i.e. non-variable subclass of a variable byte class). * kernel/Class.st: Minor changes to support preserving class definitions as long as possible (i.e. if you re-invoke the class definition method, it tries to re-use the existing class if possible). 1990-05-14 Steve Byrne * kernel/TokenStream.st: Removed isWhiteSpace:;replaced uses with Character isSeparator. 1990-04-07 Steve Byrne * kernel/Dictionary.st: Modified at:put: to resuse the existing Association if there is one, rather than create a new one all the time. This was causing lossage when setting global variables in Smalltalk that previous usages weren't being changed. 1990-05-06 Steve Byrne * kernel/Dictionary.st: Fixed grow method to preserve associations in use in the dictionary instead of making new ones. This should be faster, and doesn't break compiled methods that reference global variables when Smalltalk grows. 1990-04-26 Steve Byrne * kernel/Object.st: Fixed shallowCopy to send new messages to the object's class instead of the object itself. 1990-04-25 Steve Byrne * kernel/Integer.st: Fixed (oh...happy birthday, Integer.st!) bitInvert. After fixing the lexer to be pickier about integer literals that were too large to be represented as Smalltalk literals, the previous code (which xored with 7fffffff) broke, so we xor -1. 1990-04-24 Steve Byrne * kernel/Dictionary.st: Fix at:ifAbsent: to deal with failure better (and be a tad more efficient). Kudos (or BarNone's, depending on preference) to Andy Valencia. 1990-04-22 Steve Byrne * kernel/SysDict.st: Fixed Dependencies to be an IdentityDictionary instead of a regular Dictionary. This has better semantics and is faster. 1990-04-19 dougm * kernel/Rectangle.st: Initial definitions for Rectangle class (needs Point) 1990-04-16 dougm * kernel/Point.st: Created basic Point class. 1990-04-15 Steve Byrne * kernel/Builtins.st: Added sqrt primitive (I'm sure this was here before) must have got lost during breaking out from builtins. 1990-04-07 Steve Byrne * kernel/Builtins.st: Added declare tracing primitive. 1990-04-15 Steve Byrne * kernel/Float.st: Added asFloat...I could have sworn this was already here...must have been lost in an edit. 1990-04-20 Steve Byrne * kernel/Builtins.st: Added SystemDictionary debug to help out with DBX level debugging. 1990-02-11 Steve Byrne * kernel/Boolean.st: Converted to printOn: representation. 1990-01-13 Steve Byrne * kernel/Class.st: Began experimental addition of actual class definitions. * kernel/Builtins.st: Experimental Class self-definition. 1989-12-27 Steve Byrne * kernel/CompildMeth.st: Added real print method for compiled methods. 1989-12-25 Steve Byrne * examples/Debugger.st: Created. 1989-12-22 Steve Byrne * kernel/SymLink.st: Created. 1989-12-19 Steve Byrne * kernel/Builtins.st: Added filein primitive. * kernel/FileStream.st: added fileIn: and primitive file in. 1989-09-23 Steve Byrne * kernel/ClassDesc.st: fileOutCategory: is dangerous, so I make it write to a subdirectory called './categories'. 1989-09-19 Steve Byrne * kernel/SortCollect.st: Changed to use real method categories. * kernel/Stream.st: Changed to use real method categories. * kernel/Symbol.st: Changed to use real method categories. * kernel/Time.st: Changed to use real method categories. * kernel/TokenStream.st: Changed to use real method categories. * kernel/True.st: Changed to use real method categories. * kernel/UndefObject.st: Changed to use real method categories. * kernel/WriteStream.st: Changed to use real method categories. * kernel/Number.st: Converted to use real category strings. * kernel/PosStream.st: Converted to use real method categories * kernel/Process.st: Converted to use real method categories * kernel/Object.st: Converted to use real method categories. * kernel/OrderColl.st: Converted to use real method categories. * kernel/Random.st: Converted to use real method categories. * kernel/ReadStream.st: Converted to use real method categories. * kernel/Semaphore.st: Converted to use real method categories. * kernel/SeqCollect.st: Converted to use real method categories. * kernel/Set.st: Converted to use real method categories. 1989-09-06 Steve Byrne * kernel/CompildMeth.st: Added lots of methods: inspect, =, hash, methodCategory, methodSourceCode, methodSourceString, and some private accessors such as bytecodeAt:. 1989-09-03 Steve Byrne * kernel/String.st: Added asString for method source package * kernel/FileSegment.st: Created. * kernel/MethodInfo.st: Created. 1989-08-12 Steve Byrne * kernel/Builtins.st: Added process and semaphore builtins. * kernel/Time.st: Implemented many methods. The book is exceptionally vague here, so please feel free to change the behavior to something which is more correct. 1989-07-12 Steve Byrne * kernel/TokenStream.st: Created. 1989-07-08 Steve Byrne * kernel/CFuncs.st: Created. 1989-07-04 Steve Byrne * kernel/Object.st: Added support for dependence relationships. (-: how appropriate: on INdependence day :-) * kernel/SysDict.st: Added initBlocks methods. 1989-07-03 Steve Byrne * kernel/Random.st: Created. 1989-06-04 Steve Byrne * kernel/Stream.st: Made more of the methods defined here, but the class itself stays abstract; no implementations are given for next, nextPut:, etc. 1989-05-29 Steve Byrne * kernel/ByteMemory.st: Created. * kernel/Memory.st: Created. * kernel/WordMemory.st: Created. 1989-05-24 Steve Byrne * kernel/initialize.st: Created. 1989-05-21 Steve Byrne * kernel/FileStream.st: Created. 1989-04-25 Steve Byrne * kernel/Array.st: Created. * kernel/ArrayColl.st: Created. * kernel/Association.st: Created. * kernel/Bag.st: Created. * kernel/Behavior.st: Created. * kernel/BlkContext.st: Created. * kernel/Boolean.st: Created. * kernel/ByteArray.st: Created. * kernel/Character.st: Created. * kernel/Class.st: Created. * kernel/ClassDesc.st: Created. * kernel/Collection.st: Created. * kernel/CompildMeth.st: Created. * kernel/Date.st: Created. * kernel/Delay.st: Created. * kernel/Dictionary.st: Created. * kernel/False.st: Created. * kernel/Float.st: Created. * kernel/IdentDict.st: Created. * kernel/Integer.st: Created. * kernel/Interval.st: Created. * kernel/Link.st: Created. * kernel/LinkedList.st: Created. * kernel/Magnitude.st: Created. * kernel/MappedColl.st: Created. * kernel/Message.st: Created. * kernel/Metaclass.st: Created. * kernel/MthContext.st: Created. * kernel/Number.st: Created. * kernel/Object.st: Created. * kernel/OrderColl.st: Created. * kernel/PosStream.st: Created. * kernel/ProcSched.st: Created. * kernel/Process.st: Created. * kernel/RWStream.st: Created. * kernel/ReadStream.st: Created. * kernel/Semaphore.st: Created. * kernel/SeqCollect.st: Created. * kernel/Set.st: Created. * kernel/SharedQueue.st: Created. * kernel/SortCollect.st: Created. * kernel/Stream.st: Created. * kernel/String.st: Created. * kernel/Symbol.st: Created. * kernel/SysDict.st: Created. * kernel/Time.st: Created. * kernel/True.st: Created. * kernel/UndefObject.st: Created. * kernel/WriteStream.st: Created. 1989-02-06 Steve Byrne * kernel/Builtins.st: Created. smalltalk-3.2.5/lightning/0000755000175000017500000000000012130456003012463 500000000000000smalltalk-3.2.5/lightning/ppc/0000755000175000017500000000000012130456003013245 500000000000000smalltalk-3.2.5/lightning/ppc/asm.h0000644000175000017500000006424112123404352014127 00000000000000/******************************** -*- C -*- **************************** * * Run-time assembler for the PowerPC * ***********************************************************************/ /*********************************************************************** * * Copyright 1999, 2000, 2001, 2002 Ian Piumarta * * This file is part of GNU lightning. * * GNU lightning is free software; you can redistribute it and/or modify it * under the terms of the GNU Lesser General Public License as published * by the Free Software Foundation; either version 2.1, or (at your option) * any later version. * * GNU lightning is distributed in the hope that it will be useful, but * WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY * or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser General Public * License for more details. * * You should have received a copy of the GNU Lesser General Public License * along with GNU lightning; see the file COPYING.LESSER; if not, write to the * Free Software Foundation, 51 Franklin Street, Fifth Floor, Boston, * MA 02110-1301, USA. * ***********************************************************************/ #ifndef __lightning_asm_h #define __lightning_asm_h /* = [0-9]+ | (.+) -> add i, one parameter (imm) * = r -> add r, one parameter (imm) * = () -> add m, two parameters (imm,reg) * = () -> add x, two parameters (reg,reg) * * `x' operands have two forms. For example `stwu source, rega(regb)' * could be written as either * STWUrx(source, rega, regb) * or * STWUXrrr(source, rega, regb) */ /*** a brief NOTE about halfwords and "shifted" operands * * LOGICAL insns require UNSIGNED args in 0..65535, whether or not shifted * * ARITHMETIC insns require SIGNED args in -32768..32767, even when shifted * * as a special case: "lis/addis" also accepts UNSIGNED arguments in * 0..65535 since it is often used immediately before "ori" to load a 32-bit * constant (this is consistent with the GNU rs/6000 and PowerPC assemblers) * * thus: lis rD, expression@hi * ori rD, rD, expression@lo ; load 32-bit constant */ typedef unsigned int jit_insn; #ifndef LIGHTNING_DEBUG #define _cr0 0 #define _cr1 1 #define _cr2 2 #define _cr3 3 #define _cr4 4 #define _cr5 5 #define _cr6 6 #define _cr7 7 #define _lt 0 #define _gt 1 #define _eq 2 #define _so 3 #define _un 3 #define _d16(D) (_ck_d(16,(_jit_UL(D)-_jit_UL(_jit.x.pc))) & ~3) #define _d26(D) (_ck_d(26,(_jit_UL(D)-_jit_UL(_jit.x.pc))) & ~3) /* primitive instruction forms [1, Section A.4] */ #define _FB( OP, BD,AA,LK ) (_jit_I_noinc((_u6(OP)<<26)| _d26(BD)| (_u1(AA)<<1)|_u1(LK)), _jit.x.pc++, 0) #define _FBA( OP, BD,AA,LK ) _jit_I((_u6(OP)<<26)| (_u26(BD)&~3)| (_u1(AA)<<1)|_u1(LK)) #define _BB( OP,BO,BI, BD,AA,LK ) (_jit_I_noinc((_u6(OP)<<26)|(_u5(BO)<<21)|(_u5(BI)<<16)| _d16(BD)| (_u1(AA)<<1)|_u1(LK)), _jit.x.pc++, 0) #define _D( OP,RD,RA, DD ) _jit_I((_u6(OP)<<26)|(_u5(RD)<<21)|(_u5(RA)<<16)| _s16(DD) ) #define _Du( OP,RD,RA, DD ) _jit_I((_u6(OP)<<26)|(_u5(RD)<<21)|(_u5(RA)<<16)| _u16(DD) ) #define _Ds( OP,RD,RA, DD ) _jit_I((_u6(OP)<<26)|(_u5(RD)<<21)|(_u5(RA)<<16)| _su16(DD) ) #define _X( OP,RD,RA,RB, XO,RC ) _jit_I((_u6(OP)<<26)|(_u5(RD)<<21)|(_u5(RA)<<16)|( _u5(RB)<<11)| (_u10(XO)<<1)|_u1(RC)) #define _XL( OP,BO,BI, XO,LK ) _jit_I((_u6(OP)<<26)|(_u5(BO)<<21)|(_u5(BI)<<16)|( _u5(00)<<11)| (_u10(XO)<<1)|_u1(LK)) #define _XFX( OP,RD, SR,XO ) _jit_I((_u6(OP)<<26)|(_u5(RD)<<21)| (_u10(SR)<<11)| (_u10(XO)<<1)|_u1(00)) #define _XO( OP,RD,RA,RB,OE,XO,RC ) _jit_I((_u6(OP)<<26)|(_u5(RD)<<21)|(_u5(RA)<<16)|( _u5(RB)<<11)|(_u1(OE)<<10)|( _u9(XO)<<1)|_u1(RC)) #define _M( OP,RS,RA,SH,MB,ME,RC ) _jit_I((_u6(OP)<<26)|(_u5(RS)<<21)|(_u5(RA)<<16)|( _u5(SH)<<11)|(_u5(MB)<< 6)|( _u5(ME)<<1)|_u1(RC)) /* special purpose registers (form XFX) [1, Section 8.2, page 8-138] */ #define SPR_LR ((8<<5)|(0)) /* +++ intrinsic instructions */ #define ADDrrr(RD, RA, RB) _XO (31, RD, RA, RB, 0, 266, 0) #define ADD_rrr(RD, RA, RB) _XO (31, RD, RA, RB, 0, 266, 1) #define ADDCrrr(RD, RA, RB) _XO (31, RD, RA, RB, 0, 10, 0) #define ADDC_rrr(RD, RA, RB) _XO (31, RD, RA, RB, 0, 10, 1) #define ADDErrr(RD, RA, RB) _XO (31, RD, RA, RB, 0, 138, 0) #define ADDE_rrr(RD, RA, RB) _XO (31, RD, RA, RB, 0, 138, 1) #define ADDOrrr(RD, RA, RB) _XO (31, RD, RA, RB, 1, 266, 0) #define ADDO_rrr(RD, RA, RB) _XO (31, RD, RA, RB, 1, 266, 1) #define ADDIrri(RD, RA, IMM) _D (14, RD, RA, IMM) #define ADDICrri(RD, RA, IMM) _D (12, RD, RA, IMM) #define ADDIC_rri(RD, RA, IMM) _D (13, RD, RA, IMM) #define ADDISrri(RD, RA, IMM) _Ds (15, RD, RA, IMM) #define ANDrrr(RA, RS, RB) _X (31, RS, RA, RB, 28, 0) #define AND_rrr(RA, RS, RB) _X (31, RS, RA, RB, 28, 1) #define ANDCrrr(RA, RS, RB) _X (31, RS, RA, RB, 60, 0) #define ANDC_rrr(RA, RS, RB) _X (31, RS, RA, RB, 60, 1) #define ANDI_rri(RA, RS, IMM) _Du (28, RS, RA, IMM) #define ANDIS_rri(RA, RS, IMM) _Du (29, RS, RA, IMM) #define Bi(BD) _FB (18, BD, 0, 0) #define BAi(BD) _FBA (18, BD, 1, 0) #define BLi(BD) _FB (18, BD, 0, 1) #define BLAi(BD) _FBA (18, BD, 1, 1) #define BCiii(BO,BI,BD) _BB (16, BO, BI, BD, 0, 0) #define BCAiii(BO,BI,BD) _BB (16, BO, BI, BD, 1, 0) #define BCLiii(BO,BI,BD) _BB (16, BO, BI, BD, 0, 1) #define BCLAiii(BO,BI,BD) _BB (16, BO, BI, BD, 1, 1) #define BCCTRii(BO,BI) _XL (19, BO, BI, 528, 0) #define BCCTRLii(BO,BI) _XL (19, BO, BI, 528, 1) #define BCLRii(BO,BI) _XL (19, BO, BI, 16, 0) #define BCLRLii(BO,BI) _XL (19, BO, BI, 16, 1) #define CMPiirr(CR, LL, RA, RB) _X (31, ((CR)<<2)|(LL), RA, RB, 0, 0) #define CMPIiiri(CR, LL, RA, IMM) _D (11, ((CR)<<2)|(LL), RA, IMM) #define CMPLiirr(CR, LL, RA, RB) _X (31, ((CR)<<2)|(LL), RA, RB, 32, 0) #define CMPLIiiri(CR, LL, RA, IMM) _D (10, ((CR)<<2)|(LL), RA, IMM) #define CRANDiii(CRD,CRA,CRB) _X (19, CRD, CRA, CRB, 257, 0) #define CRANDCiii(CRD,CRA,CRB) _X (19, CRD, CRA, CRB, 129, 0) #define CREQViii(CRD,CRA,CRB) _X (19, CRD, CRA, CRB, 289, 0) #define CRNANDiii(CRD,CRA,CRB) _X (19, CRD, CRA, CRB, 225, 0) #define CRNORiii(CRD,CRA,CRB) _X (19, CRD, CRA, CRB, 33, 0) #define CRORiii(CRD,CRA,CRB) _X (19, CRD, CRA, CRB, 449, 0) #define CRORCiii(CRD,CRA,CRB) _X (19, CRD, CRA, CRB, 417, 0) #define CRXORiii(CRD,CRA,CRB) _X (19, CRD, CRA, CRB, 193, 0) #define DCBSTrr(RA,RB) _X (31, 00, RA, RB, 54, 0) #define DIVWrrr(RD, RA, RB) _XO (31, RD, RA, RB, 0, 491, 0) #define DIVW_rrr(RD, RA, RB) _XO (31, RD, RA, RB, 0, 491, 1) #define DIVWOrrr(RD, RA, RB) _XO (31, RD, RA, RB, 1, 491, 0) #define DIVWO_rrr(RD, RA, RB) _XO (31, RD, RA, RB, 1, 491, 1) #define DIVWUrrr(RD, RA, RB) _XO (31, RD, RA, RB, 0, 459, 0) #define DIVWU_rrr(RD, RA, RB) _XO (31, RD, RA, RB, 0, 459, 1) #define DIVWUOrrr(RD, RA, RB) _XO (31, RD, RA, RB, 1, 459, 0) #define DIVWUO_rrr(RD, RA, RB) _XO (31, RD, RA, RB, 1, 459, 1) #define EQVrrr(Ra,RS,RB) _X (31, RS, RA, RB, 284, 0) #define EQV_rrr(Ra,RS,RB) _X (31, RS, RA, RB, 284, 1) #define EXTSBrr(RA,RS) _X (31, RS, RA, 0, 954, 0) #define EXTSB_rr(RA,RS) _X (31, RS, RA, 0, 954, 1) #define EXTSHrr(RA,RS) _X (31, RS, RA, 0, 922, 0) #define EXTSH_rr(RA,RS) _X (31, RS, RA, 0, 922, 1) #define ICBIrr(RA,RB) _X (31, 00, RA, RB, 982, 0) #define ISYNC() _X (19, 00, 00, 00, 150, 0) #define LBZrm(RD,ID,RA) _D (34, RD, RA, ID) #define LBZUrm(RD,ID,RA) _D (35, RD, RA, ID) #define LBZUXrrr(RD,RA,RB) _X (31, RD, RA, RB, 119, 0) #define LBZXrrr(RD,RA,RB) _X (31, RD, RA, RB, 87, 0) #define LHArm(RD,ID,RA) _D (42, RD, RA, ID) #define LHAUrm(RD,ID,RA) _D (43, RD, RA, ID) #define LHAUXrrr(RD,RA,RB) _X (31, RD, RA, RB, 375, 0) #define LHAXrrr(RD,RA,RB) _X (31, RD, RA, RB, 343, 0) #define LHBRXrrr(RD,RA,RB) _X (31, RD, RA, RB, 790, 0) #define LHZrm(RD,ID,RA) _D (40, RD, RA, ID) #define LHZUrm(RD,ID,RA) _D (41, RD, RA, ID) #define LHZUXrrr(RD,RA,RB) _X (31, RD, RA, RB, 311, 0) #define LHZXrrr(RD,RA,RB) _X (31, RD, RA, RB, 279, 0) #define LMWrm(RD,ID,RA) _D (46, RD, RA, ID) #define LWBRXrrr(RD,RA,RB) _X (31, RD, RA, RB, 534, 0) #define LWZrm(RD, DISP, RA) _D (32, RD, RA, DISP) #define LWZUrm(RD, DISP, RA) _D (33, RD, RA, DISP) #define LWZUXrrr(RD, RA, RB) _X (31, RD, RA, RB, 56, 0) #define LWZXrrr(RD, RA, RB) _X (31, RD, RA, RB, 23, 0) #define MCRFii(CD,CS) _X (19, ((CD)<<2), ((CS)<<2), 0, 0, 0) #define MFCRr(RD) _X (31, RD, 0, 0, 19, 0) #define MCRXRi(RD) _XFX (31, (RD)<<2, 0, 512) #define MFSPRri(RD, SPR) _XFX (31, RD, (SPR)<<5, 339) #define MTSPRir(SPR, RS) _XFX (31, RS, (SPR)<<5, 467) #define MULHWrrr(RD,RA,RB) _XO (31, RD, RA, RB, 0, 75, 0) #define MULHW_rrr(RD,RA,RB) _XO (31, RD, RA, RB, 0, 75, 1) #define MULHWUrrr(RD,RA,RB) _XO (31, RD, RA, RB, 0, 11, 0) #define MULHWU_rrr(RD,RA,RB) _XO (31, RD, RA, RB, 0, 11, 1) #define MULLIrri(RD,RA,IM) _D (07, RD, RA, IM) #define MULLWrrr(RD,RA,RB) _XO (31, RD, RA, RB, 0, 235, 0) #define MULLW_rrr(RD,RA,RB) _XO (31, RD, RA, RB, 0, 235, 1) #define MULLWOrrr(RD,RA,RB) _XO (31, RD, RA, RB, 1, 235, 0) #define MULLWO_rrr(RD,RA,RB) _XO (31, RD, RA, RB, 1, 235, 1) #define NANDrrr(RA,RS,RB) _X (31, RS, RA, RB, 476, 0) #define NAND_rrr(RA,RS,RB) _X (31, RS, RA, RB, 476, 1) #define NEGrr(RD,RA) _XO (31, RD, RA, 0, 0, 104, 0) #define NEG_rr(RD,RA) _XO (31, RD, RA, 0, 0, 104, 1) #define NEGOrr(RD,RA) _XO (31, RD, RA, 0, 1, 104, 0) #define NEGO_rr(RD,RA) _XO (31, RD, RA, 0, 1, 104, 1) #define NORrrr(RA,RS,RB) _X (31, RS, RA, RB, 124, 0) #define NOR_rrr(RA,RS,RB) _X (31, RS, RA, RB, 124, 1) #define ORrrr(RA,RS,RB) _X (31, RS, RA, RB, 444, 0) #define OR_rrr(RA,RS,RB) _X (31, RS, RA, RB, 444, 1) #define ORCrrr(RA,RS,RB) _X (31, RS, RA, RB, 412, 0) #define ORC_rrr(RA,RS,RB) _X (31, RS, RA, RB, 412, 1) #define ORIrri(RA,RS,IM) _Du (24, RS, RA, IM) #define ORISrri(RA,RS,IM) _Du (25, RS, RA, IM) #define RLWIMIrriii(RA,RS,SH,MB,ME) _M (20, RS, RA, SH, MB, ME, 0) #define RLWIMI_rriii(RA,RS,SH,MB,ME) _M (20, RS, RA, SH, MB, ME, 1) #define RLWINMrriii(RA,RS,SH,MB,ME) _M (21, RS, RA, SH, MB, ME, 0) #define RLWINM_rriii(RA,RS,SH,MB,ME) _M (21, RS, RA, SH, MB, ME, 1) #define RLWNMrrrii(RA,RS,RB,MB,ME) _M (23, RS, RA, RB, MB, ME, 0) #define RLWNM_rrrii(RA,RS,RB,MB,ME) _M (23, RS, RA, RB, MB, ME, 1) #define SLWrrr(RA,RS,RB) _X (31, RS, RA, RB, 24, 0) #define SLW_rrr(RA,RS,RB) _X (31, RS, RA, RB, 24, 1) #define SRAWrrr(RA,RS,RB) _X (31, RS, RA, RB, 792, 0) #define SRAW_rrr(RA,RS,RB) _X (31, RS, RA, RB, 792, 1) #define SRAWIrri(RD, RS, SH) _X (31, RS, RD, SH, 824, 0) #define SRAWI_rri(RD, RS, SH) _X (31, RS, RD, SH, 824, 1) #define SRWrrr(RA,RS,RB) _X (31, RS, RA, RB, 536, 0) #define SRW_rrr(RA,RS,RB) _X (31, RS, RA, RB, 536, 1) #define STBrm(RS,ID,RA) _D (38, RS, RA, ID) #define STBUrm(RS,ID,RA) _D (39, RS, RA, ID) #define STBUXrrr(RS,RA,RB) _X (31, RS, RA, RB, 247, 0) #define STBXrrr(RS,RA,RB) _X (31, RS, RA, RB, 215, 0) #define STHrm(RS,ID,RA) _D (44, RS, RA, ID) #define STHUrm(RS,ID,RA) _D (45, RS, RA, ID) #define STHBRXrrr(RS,RA,RB) _X (31, RS, RA, RB, 918, 0) #define STHUXrrr(RS,RA,RB) _X (31, RS, RA, RB, 439, 0) #define STHXrrr(RS,RA,RB) _X (31, RS, RA, RB, 407, 0) #define STMWrm(RS,ID,RA) _D (47, RS, RA, ID) #define STWrm(RS,ID,RA) _D (36, RS, RA, ID) #define STWBRXrrr(RS,RA,RB) _X (31, RS, RA, RB, 662, 0) #define STWCXrrr(RS,RA,RB) _X (31, RS, RA, RB, 150, 0) #define STWCX_rrr(RS,RA,RB) _X (31, RS, RA, RB, 150, 1) #define STWUrm(RS,ID,RA) _D (37, RS, RA, ID) #define STWUXrrr(RS,RA,RB) _X (31, RS, RA, RB, 183, 0) #define STWXrrr(RS,RA,RB) _X (31, RS, RA, RB, 151, 0) #define SUBFrrr(RD, RA, RB) _XO (31, RD, RA, RB, 0, 40, 0) #define SUBF_rrr(RD, RA, RB) _XO (31, RD, RA, RB, 0, 40, 1) #define SUBFrrr(RD, RA, RB) _XO (31, RD, RA, RB, 0, 40, 0) #define SUBF_rrr(RD, RA, RB) _XO (31, RD, RA, RB, 0, 40, 1) #define SUBFErrr(RD, RA, RB) _XO (31, RD, RA, RB, 1, 136, 0) #define SUBFE_rrr(RD, RA, RB) _XO (31, RD, RA, RB, 1, 136, 1) #define SUBFCrrr(RD, RA, RB) _XO (31, RD, RA, RB, 0, 8, 0) #define SUBFC_rrr(RD, RA, RB) _XO (31, RD, RA, RB, 0, 8, 1) #define SUBFCOrrr(RD, RA, RB) _XO (31, RD, RA, RB, 1, 8, 0) #define SUBFCO_rrr(RD, RA, RB) _XO (31, RD, RA, RB, 1, 8, 1) #define SUBFICrri(RD, RA, IMM) _D (8, RD, RA, IMM) #define ADDrrr(RD, RA, RB) _XO (31, RD, RA, RB, 0, 266, 0) #define ADDOrrr(RD, RA, RB) _XO (31, RD, RA, RB, 1, 266, 0) #define ADDIrri(RD, RA, IMM) _D (14, RD, RA, IMM) #define ADDISrri(RD, RA, IMM) _Ds (15, RD, RA, IMM) #define SYNC() _X (31, 00, 00, 00, 598, 0) #define TWirr(TO,RA,RB) _X (31, TO, RA, RB, 4, 0) #define TWIiri(TO,RA,IM) _D (03, TO, RA, IM) #define XORrrr(RA,RS,RB) _X (31, RS, RA, RB, 316, 0) #define XOR_rrr(RA,RS,RB) _X (31, RS, RA, RB, 316, 1) #define XORIrri(RA,RS,IM) _Du (26, RS, RA, IM) #define XORISrri(RA,RS,IM) _Du (27, RS, RA, IM) /* simplified mnemonics [1, Appendix F] */ #define MOVEIri2(R,H,L) (LISri(R,H), (L ? ORIrri(R,R,L) : 0)) #define MOVEIri(R,I) (_siP(16,I) ? LIri(R,I) : \ MOVEIri2(R, _HI(I), _LO(I)) ) #define SUBIrri(RD,RA,IM) ADDIrri(RD,RA,-_LO((IM))) /* [1, Section F.2.1] */ #define SUBISrri(RD,RA,IM) ADDISrri(RD,RA,-_LO((IM))) #define SUBICrri(RD,RA,IM) ADDICrri(RD,RA,-_LO((IM))) #define SUBIC_rri(RD,RA,IM) ADDIC_rri(RD,RA,-_LO((IM))) #define SUBrrr(RD,RA,RB) SUBFrrr(RD,RB,RA) /* [1, Section F.2.2] */ #define SUBOrrr(RD,RA,RB) SUBFOrrr(RD,RB,RA) #define SUB_rrr(RD,RA,RB) SUBF_rrr(RD,RB,RA) #define SUBCrrr(RD,RA,RB) SUBFCrrr(RD,RB,RA) #define SUBCOrrr(RD,RA,RB) SUBFCOrrr(RD,RB,RA) #define SUBC_rrr(RD,RA,RB) SUBFC_rrr(RD,RB,RA) #define SUBErrr(RD,RA,RB) SUBFErrr(RD,RB,RA) #define SUBE_rrr(RD,RA,RB) SUBFE_rrr(RD,RB,RA) #define CMPWIiri(C,RA,IM) CMPIiiri(C,0,RA,IM) /* [1, Table F-2] */ #define CMPWirr(C,RA,RB) CMPiirr(C,0,RA,RB) #define CMPLWIiri(C,RA,IM) CMPLIiiri(C,0,RA,IM) #define CMPLWirr(C,RA,RB) CMPLiirr(C,0,RA,RB) #define CMPWIri(RA,IM) CMPWIiri(0,RA,IM) /* with implicit _cr0 */ #define CMPWrr(RA,RB) CMPWirr(0,RA,RB) #define CMPLWIri(RA,IM) CMPLWIiri(0,RA,IM) #define CMPLWrr(RA,RB) CMPLWirr(0,RA,RB) #define EXTLWIrrii(RA,RS,N,B) RLWINMrriii(RA, RS, B, 0, (N)-1) /* [1, Table F-3] */ #define EXTRWIrrii(RA,RS,N,B) RLWINMrriii(RA, RS, (B)+(N), 32-(N), 31) #define INSLWIrrii(RA,RS,N,B) RLWIMIrriii(RA, RS, 32-(B), B, (B)+(N)-1) #define INSRWIrrii(RA,RS,N,B) RLWIMIrriii(RA, RS, 32-((B)+(N)), B, (B)+(N)-1) #define ROTLWIrri(RA,RS,N) RLWINMrriii(RA, RS, N, 0, 31) #define ROTRWIrri(RA,RS,N) RLWINMrriii(RA, RS, 32-(N), 0, 31) #define ROTLWrrr(RA,RS,RB) RLWNMrrrii( RA, RS, RB, 0, 31) #define SLWIrri(RA,RS,N) RLWINMrriii(RA, RS, N, 0, 31-(N)) #define SRWIrri(RA,RS,N) RLWINMrriii(RA, RS, 32-(N), N, 31) #define CLRLWIrri(RA,RS,N) RLWINMrriii(RA, RS, 0, N, 31) #define CLRRWIrri(RA,RS,N) RLWINMrriii(RA, RS, 0, 0, 31-(N)) #define CLRLSLWIrrii(RA,RS,B,N) RLWINMrriii(RA, RS, N, (B)-(N), 31-(N)) /* 9 below inverts the branch condition and the branch prediction. * This has an incestuous knowledge of JIT_AUX */ #define BC_EXT(A, C, D) (_siP(16, _jit_UL(D)-_jit_UL(_jit.x.pc)) \ ? BCiii((A), (C), (D)) \ : (BCiii((A)^9, (C), _jit.x.pc+5), \ LISri(JIT_AUX,_HI(D)), \ ORIrri(JIT_AUX,JIT_AUX,_LO(D)), \ MTLRr(JIT_AUX), BLR() )) #define B_EXT(D) (_siP(16, _jit_UL(D)-_jit_UL(_jit.x.pc)) \ ? Bi((D)) \ : (LISri(JIT_AUX,_HI(D)), \ ORIrri(JIT_AUX,JIT_AUX,_LO(D)), \ MTLRr(JIT_AUX), BLR()) ) #define BTii(C,D) BC_EXT(12, C, D) /* [1, Table F-5] */ #define BFii(C,D) BC_EXT( 4, C, D) #define BDNZi(D) BCiii(16, 0, D) #define BDNZTii(C,D) BC_EXT( 8, C, D) #define BDNZFii(C,D) BC_EXT( 0, C, D) #define BDZi(D) BCiii(18, 0, D) #define BDZTii(C,D) BC_EXT(10, C, D) #define BDZFii(C,D) BC_EXT( 2, C, D) #define BCTR() BCCTRii(20, 0) /* [1, Table F-6] */ #define BCTRL() BCCTRLii(20, 0) #define BLR() BCLRii(20, 0) /* [1, Table F-6] */ #define BLRL() BCLRLii(20, 0) #define BLTLRi(CR) BCLRii(12, ((CR)<<2)+0) /* [1, Table F-10] */ #define BLELRi(CR) BCLRii( 4, ((CR)<<2)+1) #define BEQLRi(CR) BCLRii(12, ((CR)<<2)+2) #define BGELRi(CR) BCLRii( 4, ((CR)<<2)+0) #define BGTLRi(CR) BCLRii(12, ((CR)<<2)+1) #define BNLLRi(CR) BCLRii( 4, ((CR)<<2)+0) #define BNELRi(CR) BCLRii( 4, ((CR)<<2)+2) #define BNGLRi(CR) BCLRii( 4, ((CR)<<2)+1) #define BSOLRi(CR) BCLRii(12, ((CR)<<2)+3) #define BNSLRi(CR) BCLRii( 4, ((CR)<<2)+3) #define BUNLRi(CR) BCLRii(12, ((CR)<<2)+3) #define BNULRi(CR) BCLRii( 4, ((CR)<<2)+3) #define BLTLRLi(CR) BCLRLii(12, ((CR)<<2)+0) /* [1, Table F-10] */ #define BLELRLi(CR) BCLRLii( 4, ((CR)<<2)+1) #define BEQLRLi(CR) BCLRLii(12, ((CR)<<2)+2) #define BGELRLi(CR) BCLRLii( 4, ((CR)<<2)+0) #define BGTLRLi(CR) BCLRLii(12, ((CR)<<2)+1) #define BNLLRLi(CR) BCLRLii( 4, ((CR)<<2)+0) #define BNELRLi(CR) BCLRLii( 4, ((CR)<<2)+2) #define BNGLRLi(CR) BCLRLii( 4, ((CR)<<2)+1) #define BSOLRLi(CR) BCLRLii(12, ((CR)<<2)+3) #define BNSLRLi(CR) BCLRLii( 4, ((CR)<<2)+3) #define BUNLRLi(CR) BCLRLii(12, ((CR)<<2)+3) #define BNULRLi(CR) BCLRLii( 4, ((CR)<<2)+3) #define BLTCTRi(CR) BCCTRii(12, ((CR)<<2)+0) /* [1, Table F-10] */ #define BLECTRi(CR) BCCTRii( 4, ((CR)<<2)+1) #define BEQCTRi(CR) BCCTRii(12, ((CR)<<2)+2) #define BGECTRi(CR) BCCTRii( 4, ((CR)<<2)+0) #define BGTCTRi(CR) BCCTRii(12, ((CR)<<2)+1) #define BNLCTRi(CR) BCCTRii( 4, ((CR)<<2)+0) #define BNECTRi(CR) BCCTRii( 4, ((CR)<<2)+2) #define BNGCTRi(CR) BCCTRii( 4, ((CR)<<2)+1) #define BSOCTRi(CR) BCCTRii(12, ((CR)<<2)+3) #define BNSCTRi(CR) BCCTRii( 4, ((CR)<<2)+3) #define BUNCTRi(CR) BCCTRii(12, ((CR)<<2)+3) #define BNUCTRi(CR) BCCTRii( 4, ((CR)<<2)+3) #define BLTCTRLi(CR) BCCTRLii(12, ((CR)<<2)+0) /* [1, Table F-10] */ #define BLECTRLi(CR) BCCTRLii( 4, ((CR)<<2)+1) #define BEQCTRLi(CR) BCCTRLii(12, ((CR)<<2)+2) #define BGECTRLi(CR) BCCTRLii( 4, ((CR)<<2)+0) #define BGTCTRLi(CR) BCCTRLii(12, ((CR)<<2)+1) #define BNLCTRLi(CR) BCCTRLii( 4, ((CR)<<2)+0) #define BNECTRLi(CR) BCCTRLii( 4, ((CR)<<2)+2) #define BNGCTRLi(CR) BCCTRLii( 4, ((CR)<<2)+1) #define BSOCTRLi(CR) BCCTRLii(12, ((CR)<<2)+3) #define BNSCTRLi(CR) BCCTRLii( 4, ((CR)<<2)+3) #define BUNCTRLi(CR) BCCTRLii(12, ((CR)<<2)+3) #define BNUCTRLi(CR) BCCTRLii( 4, ((CR)<<2)+3) #define BLTLR() BLTLRi(0) /* with implicit _cr0 */ #define BLELR() BLELRi(0) #define BEQLR() BEQLRi(0) #define BGELR() BGELRi(0) #define BGTLR() BGTLRi(0) #define BNLLR() BNLLRi(0) #define BNELR() BNELRi(0) #define BNGLR() BNGLRi(0) #define BSOLR() BSOLRi(0) #define BNSLR() BNSLRi(0) #define BUNLR() BUNLRi(0) #define BNULR() BNULRi(0) #define BLTLRL() BLTLRLi(0) #define BLELRL() BLELRLi(0) #define BEQLRL() BEQLRLi(0) #define BGELRL() BGELRLi(0) #define BGTLRL() BGTLRLi(0) #define BNLLRL() BNLLRLi(0) #define BNELRL() BNELRLi(0) #define BNGLRL() BNGLRLi(0) #define BSOLRL() BSOLRLi(0) #define BNSLRL() BNSLRLi(0) #define BUNLRL() BUNLRLi(0) #define BNULRL() BNULRLi(0) #define BLTCTR() BLTCTRi(0) #define BLECTR() BLECTRi(0) #define BEQCTR() BEQCTRi(0) #define BGECTR() BGECTRi(0) #define BGTCTR() BGTCTRi(0) #define BNLCTR() BNLCTRi(0) #define BNECTR() BNECTRi(0) #define BNGCTR() BNGCTRi(0) #define BSOCTR() BSOCTRi(0) #define BNSCTR() BNSCTRi(0) #define BUNCTR() BUNCTRi(0) #define BNUCTR() BNUCTRi(0) #define BLTCTRL() BLTCTRLi(0) #define BLECTRL() BLECTRLi(0) #define BEQCTRL() BEQCTRLi(0) #define BGECTRL() BGECTRLi(0) #define BGTCTRL() BGTCTRLi(0) #define BNLCTRL() BNLCTRLi(0) #define BNECTRL() BNECTRLi(0) #define BNGCTRL() BNGCTRLi(0) #define BSOCTRL() BSOCTRLi(0) #define BNSCTRL() BNSCTRLi(0) #define BUNCTRL() BUNCTRLi(0) #define BNUCTRL() BNUCTRLi(0) #define BLTii(C,D) BC_EXT(12, ((C)<<2)+0, D) /* [1, Table F-11] */ #define BNLii(C,D) BC_EXT( 4, ((C)<<2)+0, D) #define BGEii(C,D) BC_EXT( 4, ((C)<<2)+0, D) #define BGTii(C,D) BC_EXT(12, ((C)<<2)+1, D) #define BNGii(C,D) BC_EXT( 4, ((C)<<2)+1, D) #define BLEii(C,D) BC_EXT( 4, ((C)<<2)+1, D) #define BEQii(C,D) BC_EXT(12, ((C)<<2)+2, D) #define BNEii(C,D) BC_EXT( 4, ((C)<<2)+2, D) #define BSOii(C,D) BC_EXT(12, ((C)<<2)+3, D) #define BNSii(C,D) BC_EXT( 4, ((C)<<2)+3, D) #define BUNii(C,D) BC_EXT(12, ((C)<<2)+3, D) #define BNUii(C,D) BC_EXT( 4, ((C)<<2)+3, D) #define BLTi(D) BLTii(0,D) /* with implicit _cr0 */ #define BLEi(D) BLEii(0,D) #define BEQi(D) BEQii(0,D) #define BGEi(D) BGEii(0,D) #define BGTi(D) BGTii(0,D) #define BNLi(D) BNLii(0,D) #define BNEi(D) BNEii(0,D) #define BNGi(D) BNGii(0,D) #define BSOi(D) BSOii(0,D) #define BNSi(D) BNSii(0,D) #define BUNi(D) BUNii(0,D) #define BNUi(D) BNUii(0,D) #define BLTLii(C,D) BCLiii(12, ((C)<<2)+0, D) /* [1, Table F-??] */ #define BLELii(C,D) BCLiii( 4, ((C)<<2)+1, D) #define BEQLii(C,D) BCLiii(12, ((C)<<2)+2, D) #define BGELii(C,D) BCLiii( 4, ((C)<<2)+0, D) #define BGTLii(C,D) BCLiii(12, ((C)<<2)+1, D) #define BNLLii(C,D) BCLiii( 4, ((C)<<2)+0, D) #define BNELii(C,D) BCLiii( 4, ((C)<<2)+2, D) #define BNGLii(C,D) BCLiii( 4, ((C)<<2)+1, D) #define BSOLii(C,D) BCLiii(12, ((C)<<2)+3, D) #define BNSLii(C,D) BCLiii( 4, ((C)<<2)+3, D) #define BUNLii(C,D) BCLiii(12, ((C)<<2)+3, D) #define BNULii(C,D) BCLiii( 4, ((C)<<2)+3, D) #define BLTLi(D) BLTLii(0,D) /* with implicit _cr0 */ #define BLELi(D) BLELii(0,D) #define BEQLi(D) BEQLii(0,D) #define BGELi(D) BGELii(0,D) #define BGTLi(D) BGTLii(0,D) #define BNLLi(D) BNLLii(0,D) #define BNELi(D) BNELii(0,D) #define BNGLi(D) BNGLii(0,D) #define BSOLi(D) BSOLii(0,D) #define BNSLi(D) BNSLii(0,D) #define BUNLi(D) BUNLii(0,D) #define BNULi(D) BNULii(0,D) /* Note: there are many tens of other simplified branches that are not (yet?) defined here */ #define CRSETi(BX) CREQViii(BX, BX, BX) /* [1, Table F-15] */ #define CRCLRi(BX) CRXORiii(BX, BX, BX) #define CRMOVEii(BX,BY) CRORiii(BX, BY, BY) #define CRNOTii(BX,BY) CRNORiii(BX, BY, BY) #define MTLRr(RS) MTSPRir(8, RS) /* [1, Table F-20] */ #define MFLRr(RD) MFSPRri(RD, 8) #define MTCTRr(RS) MTSPRir(9, RS) #define MFCTRr(RD) MFSPRri(RD, 9) #define MTXERr(RS) MTSPRir(1, RS) #define MFXERr(RD) MFSPRri(RD, 1) #define NOP() ORIrri(0, 0, 0) /* [1, Section F.9] */ #define LIri(RD,IM) ADDIrri(RD, 0, IM) #define LISri(RD,IM) ADDISrri(RD, 0, IM) #define LArm(RD,D,RA) ADDIrri(RD, RA, D) #define LArrr(RD,RB,RA) ADDIrrr(RD, RA, RB) #define MRrr(RA,RS) ORrrr(RA, RS, RS) #define NOTrr(RA,RS) NORrrr(RA, RS, RS) /* alternative parenthesised forms of extended indexed load/store insns */ #define LBZUrx(RD,RA,RB) LBZUXrrr(RD,RA,RB) #define LBZrx(RD,RA,RB) LBZXrrr(RD,RA,RB) #define LHAUrx(RD,RA,RB) LHAUXrrr(RD,RA,RB) #define LHArx(RD,RA,RB) LHAXrrr(RD,RA,RB) #define LHBRrx(RD,RA,RB) LHBRXrrr(RD,RA,RB) #define LHZUrx(RD,RA,RB) LHZUXrrr(RD,RA,RB) #define LHZrx(RD,RA,RB) LHZXrrr(RD,RA,RB) #define LWBRrx(RD,RA,RB) LWBRXrrr(RD,RA,RB) #define LWZUrx(RD, RA, RB) LWZUXrrr(RD, RA, RB) #define LWZrx(RD, RA, RB) LWZXrrr(RD, RA, RB) #define STBUrx(RD,RA,RB) STBUXrrr(RD,RA,RB) #define STBrx(RD,RA,RB) STBXrrr(RD,RA,RB) #define STHBRrx(RS,RA,RB) STHBRXrrr(RS,RA,RB) #define STHUrx(RS,RA,RB) STHUXrrr(RS,RA,RB) #define STHrx(RS,RA,RB) STHXrrr(RS,RA,RB) #define STWBRrx(RS,RA,RB) STWBRXrrr(RS,RA,RB) #define STWCrx(RS,RA,RB) STWCXrrr(RS,RA,RB) #define STWCX_rx(RS,RA,RB) STWCX_rrr(RS,RA,RB) #define STWUrx(RS,RA,RB) STWUXrrr(RS,RA,RB) #define STWrx(RS,RA,RB) STWXrrr(RS,RA,RB) #define LArx(RD,RB,RA) LArrr(RD,RB,RA) #define _LO(I) (_jit_UL(I) & _MASK(16)) #define _HI(I) (_jit_UL(I) >> (16)) #define _A(OP,RD,RA,RB,RC,XO,RCx) _jit_I((_u6(OP)<<26)|(_u5(RD)<<21)|(_u5(RA)<<16)|( _u5(RB)<<11)|_u5(RC)<<6|(_u5(XO)<<1)|_u1(RCx)) #define LFDrri(RD,RA,imm) _D(50,RD,RA,imm) #define LFDUrri(RD,RA,imm) _D(51,RD,RA,imm) #define LFDUxrrr(RD,RA,RB) _X(31,RD,RA,RB,631,0) #define LFDxrrr(RD,RA,RB) _X(31,RD,RA,RB,599,0) #define LFSrri(RD,RA,imm) _D(48,RD,RA,imm) #define LFSUrri(RD,RA,imm) _D(49,RD,RA,imm) #define LFSUxrrr(RD,RA,RB) _X(31,RD,RA,RB,567,0) #define LFSxrrr(RD,RA,RB) _X(31,RD,RA,RB,535,0) #define STFDrri(RS,RA,imm) _D(54,RS,RA,imm) #define STFDUrri(RS,RA,imm) _D(55,RS,RA,imm) #define STFDUxrrr(RS,RA,RB) _X(31,RS,RA,RB,759,0) #define STFDxrrr(RS,RA,RB) _X(31,RS,RA,RB,727,0) #define STFSrri(RS,RA,imm) _D(52,RS,RA,imm) #define STFSUrri(RS,RA,imm) _D(53,RS,RA,imm) #define STFSUxrrr(RS,RA,RB) _X(31,RS,RA,RB,695,0) #define STFSxrrr(RS,RA,RB) _X(31,RS,RA,RB,663,0) #define STFIWXrrr(RS,RA,RB) _X(31,RS,RA,RB,983,0) #define FADDDrrr(RD,RA,RB) _A(63,RD,RA,RB,0,21,0) #define FADDSrrr(RD,RA,RB) _A(59,RD,RA,RB,0,21,0) #define FSUBDrrr(RD,RA,RB) _A(63,RD,RA,RB,0,20,0) #define FSUBSrrr(RD,RA,RB) _A(59,RD,RA,RB,0,20,0) #define FMULDrrr(RD,RA,RC) _A(63,RD,RA,0,RC,25,0) #define FMULSrrr(RD,RA,RC) _A(59,RD,RA,0,RC,25,0) #define FDIVDrrr(RD,RA,RB) _A(63,RD,RA,RB,0,18,0) #define FDIVSrrr(RD,RA,RB) _A(59,RD,RA,RB,0,25,0) #define FSQRTDrr(RD,RB) _A(63,RD,0,RB,0,22,0) #define FSQRTSrr(RD,RB) _A(59,RD,0,RB,0,22,0) #define FSELrrrr(RD,RA,RB,RC) _A(63,RD,RA,RB,RC,23,0) #define FCTIWrr(RD,RB) _X(63,RD,0,RB,14,0) #define FCTIWZrr(RD,RB) _X(63,RD,0,RB,15,0) #define FRSPrr(RD,RB) _X(63,RD,0,RB,12,0) #define FABSrr(RD,RB) _X(63,RD,0,RB,264,0) #define FNABSrr(RD,RB) _X(63,RD,0,RB,136,0) #define FNEGrr(RD,RB) _X(63,RD,0,RB,40,0) #define FMOVErr(RD,RB) _X(63,RD,0,RB,72,0) #define FCMPOrrr(CR,RA,RB) _X(63,_u3((CR)<<2),RA,RB,32,0) #define FCMPUrrr(CR,RA,RB) _X(63,_u3((CR)<<2),RA,RB,0,0) #define MTFSFIri(CR,IMM) _X(63,_u5((CR)<<2),0,_u5((IMM)<<1),134,0) /*** References: * * [1] "PowerPC Microprocessor Family: The Programming Environments For 32-Bit Microprocessors", Motorola, 1997. */ #endif #endif /* __ccg_asm_ppc_h */ smalltalk-3.2.5/lightning/ppc/core.h0000644000175000017500000004503312123404352014275 00000000000000/******************************** -*- C -*- **************************** * * Platform-independent layer (PowerPC version) * ***********************************************************************/ /*********************************************************************** * * Copyright 2000, 2001, 2002, 2006 Free Software Foundation, Inc. * Written by Paolo Bonzini. * * This file is part of GNU lightning. * * GNU lightning is free software; you can redistribute it and/or modify it * under the terms of the GNU Lesser General Public License as published * by the Free Software Foundation; either version 2.1, or (at your option) * any later version. * * GNU lightning is distributed in the hope that it will be useful, but * WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY * or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser General Public * License for more details. * * You should have received a copy of the GNU Lesser General Public License * along with GNU lightning; see the file COPYING.LESSER; if not, write to the * Free Software Foundation, 51 Franklin Street, Fifth Floor, Boston, * MA 02110-1301, USA. * ***********************************************************************/ #ifndef __lightning_core_h #define __lightning_core_h struct jit_local_state { int nextarg_puti; /* number of integer args */ int nextarg_putf; /* number of float args */ int nextarg_putd; /* number of double args */ int nextarg_geti; /* Next r20-r25 reg. to be read */ int nextarg_getd; /* The FP args are picked up from FPR1 -> FPR10 */ int nbArgs; /* Number of arguments for the prolog */ }; #define JIT_SP 1 #define JIT_RET 3 #define JIT_R_NUM 3 #define JIT_V_NUM 7 #define JIT_R(i) (9+(i)) #define JIT_V(i) (31-(i)) #define JIT_AUX JIT_V(JIT_V_NUM) /* for 32-bit operands & shift counts */ #define jit_pfx_start() (_jit.jitl.trampolines) #define jit_pfx_end() (_jit.jitl.free) /* If possible, use the `small' instruction (rd, rs, imm) * else load imm into r26 and use the `big' instruction (rd, rs, r26) */ #define jit_chk_ims(imm, small, big) (_siP(16,(imm)) ? (small) : (MOVEIri(JIT_AUX, imm), (big)) ) #define jit_chk_imu(imm, small, big) (_uiP(16,(imm)) ? (small) : (MOVEIri(JIT_AUX, imm), (big)) ) #define jit_chk_imu15(imm, small, big) (_uiP(15,(imm)) ? (small) : (MOVEIri(JIT_AUX, imm), (big)) ) #define jit_big_ims(imm, big) (MOVEIri(JIT_AUX, imm), (big)) #define jit_big_imu(imm, big) (MOVEIri(JIT_AUX, imm), (big)) /* Helper macros for branches */ #define jit_s_brai(rs, is, jmp) (jit_chk_ims (is, CMPWIri(rs, is), CMPWrr(rs, JIT_AUX)), jmp, _jit.x.pc) #define jit_s_brar(s1, s2, jmp) ( CMPWrr(s1, s2), jmp, _jit.x.pc) #define jit_u_brai(rs, is, jmp) (jit_chk_imu (is, CMPLWIri(rs, is), CMPLWrr(rs, JIT_AUX)), jmp, _jit.x.pc) #define jit_u_brar(s1, s2, jmp) ( CMPLWrr(s1, s2), jmp, _jit.x.pc) /* Helper macros for boolean tests. */ #define jit_sbooli(d, rs, is, jmp) (jit_chk_ims (is, CMPWIri (rs, is), CMPWrr(rs, JIT_AUX)), MFCRr((d)), EXTRWIrrii((d), (d), 1, (jmp))) #define jit_sboolr(d, s1, s2, jmp) ( CMPWrr (s1, s2), MFCRr((d)), EXTRWIrrii((d), (d), 1, (jmp))) #define jit_sbooli2(d, rs, is, jmp) (jit_chk_ims (is, CMPWIri (rs, is), CMPWrr(rs, JIT_AUX)), MFCRr((d)), EXTRWIrrii((d), (d), 1, (jmp)), XORIrri((d), (d), 1)) #define jit_sboolr2(d, s1, s2, jmp) ( CMPWrr (s1, s2), MFCRr((d)), EXTRWIrrii((d), (d), 1, (jmp)), XORIrri((d), (d), 1)) #define jit_ubooli(d, rs, is, jmp) (jit_chk_imu (is, CMPLWIri(rs, is), CMPLWrr(rs, JIT_AUX)), MFCRr((d)), EXTRWIrrii((d), (d), 1, (jmp))) #define jit_uboolr(d, s1, s2, jmp) ( CMPLWrr (s1, s2), MFCRr((d)), EXTRWIrrii((d), (d), 1, (jmp))) #define jit_ubooli2(d, rs, is, jmp) (jit_chk_imu (is, CMPLWIri(rs, is), CMPLWrr(rs, JIT_AUX)), MFCRr((d)), EXTRWIrrii((d), (d), 1, (jmp)), XORIrri((d), (d), 1)) #define jit_uboolr2(d, s1, s2, jmp) ( CMPLWrr (s1, s2), MFCRr((d)), EXTRWIrrii((d), (d), 1, (jmp)), XORIrri((d), (d), 1)) /* modulus with big immediate with small immediate * movei r24, imm movei r24, imm * mtlr r31 * divw r31, rs, r24 (or divwu) divw r24, rs, r24 * mullw r31, r31, r24 mulli r24, r24, imm * sub d, rs, r31 sub d, rs, r24 * mflr r31 * * * jit_mod_big expects immediate in JIT_AUX. */ #define _jit_mod_big(div, d, rs) (MTLRr(31), div(31, (rs), JIT_AUX), \ MULLWrrr(31, 31, JIT_AUX), SUBrrr((d), (rs), 31), \ MFLRr(31)) #define _jit_mod_small(div, d, rs, imm) (MOVEIri(JIT_AUX, (imm)), div(JIT_AUX, (rs), JIT_AUX), \ MULLIrri(JIT_AUX, JIT_AUX, (imm)), SUBrrr((d), (rs), JIT_AUX)) /* Patch a movei instruction made of a LIS at lis_pc and an ORI at ori_pc. */ #define jit_patch_movei(lis_pc, ori_pc, dest) \ (*(lis_pc) &= ~_MASK(16), *(lis_pc) |= _HI(dest), \ *(ori_pc) &= ~_MASK(16), *(ori_pc) |= _LO(dest)) \ /* Patch a branch instruction */ #define jit_patch_branch(jump_pc,pv) \ (*(jump_pc) &= ~_MASK(16) | 3, \ *(jump_pc) |= (_jit_UL(pv) - _jit_UL(jump_pc)) & _MASK(16)) #define jit_patch_ucbranch(jump_pc,pv) \ (*(jump_pc) &= ~_MASK(26) | 3, \ (*(jump_pc) |= (_jit_UL((pv)) - _jit_UL(jump_pc)) & _MASK(26))) #define _jit_b_encoding (18 << 26) #define _jit_blr_encoding ((19 << 26) | (20 << 21) | (00 << 16) | (00 << 11) | (16 << 1)) #define _jit_is_ucbranch(a) (((*(a) & (63<<26)) == _jit_b_encoding)) #define jit_patch_at(jump_pc, value) ( \ ((*(jump_pc - 1) & ~1) == _jit_blr_encoding) \ ? jit_patch_movei(((jump_pc) - 4), ((jump_pc) - 3), (value)) \ : ( _jit_is_ucbranch((jump_pc) - 1) \ ? jit_patch_ucbranch((jump_pc) - 1, (value)) \ : jit_patch_branch((jump_pc) - 1, (value)))) #define jit_patch_movi(movi_pc, val) \ jit_patch_movei((movi_pc) - 2, (movi_pc) - 1, (val)) #define jit_arg_c() (_jitl.nextarg_geti--) #define jit_arg_i() (_jitl.nextarg_geti--) #define jit_arg_l() (_jitl.nextarg_geti--) #define jit_arg_p() (_jitl.nextarg_geti--) #define jit_arg_s() (_jitl.nextarg_geti--) #define jit_arg_uc() (_jitl.nextarg_geti--) #define jit_arg_ui() (_jitl.nextarg_geti--) #define jit_arg_ul() (_jitl.nextarg_geti--) #define jit_arg_us() (_jitl.nextarg_geti--) /* Check Mach-O-Runtime documentation: Must skip GPR(s) whenever "corresponding" FPR is used */ #define jit_arg_f() (_jitl.nextarg_geti-- ,_jitl.nextarg_getd++) #define jit_arg_d() (_jitl.nextarg_geti-=2,_jitl.nextarg_getd++) #define jit_addi_i(d, rs, is) jit_chk_ims((is), ADDICrri((d), (rs), (is)), ADDrrr((d), (rs), JIT_AUX)) #define jit_addr_i(d, s1, s2) ADDrrr((d), (s1), (s2)) #define jit_addci_i(d, rs, is) jit_chk_ims((is), ADDICrri((d), (rs), (is)), ADDCrrr((d), (rs), JIT_AUX)) #define jit_addcr_i(d, s1, s2) ADDCrrr((d), (s1), (s2)) #define jit_addxi_i(d, rs, is) (MOVEIri(JIT_AUX, (is)), ADDErrr((d), (rs), JIT_AUX)) #define jit_addxr_i(d, s1, s2) ADDErrr((d), (s1), (s2)) #define jit_andi_i(d, rs, is) jit_chk_imu((is), ANDI_rri((d), (rs), (is)), ANDrrr((d), (rs), JIT_AUX)) #define jit_andr_i(d, s1, s2) ANDrrr((d), (s1), (s2)) #define jit_bmsi_i(label, rs, is) (jit_chk_imu((is), ANDI_rri(JIT_AUX, (rs), (is)), AND_rrr(JIT_AUX, (rs), JIT_AUX)), BNEi((label)), _jit.x.pc) #define jit_bmci_i(label, rs, is) (jit_chk_imu((is), ANDI_rri(JIT_AUX, (rs), (is)), AND_rrr(JIT_AUX, (rs), JIT_AUX)), BEQi((label)), _jit.x.pc) #define jit_bmsr_i(label, s1, s2) ( AND_rrr(JIT_AUX, (s1), (s2)), BNEi((label)), _jit.x.pc) #define jit_bmcr_i(label, s1, s2) ( AND_rrr(JIT_AUX, (s1), (s2)), BEQi((label)), _jit.x.pc) #define jit_beqi_i(label, rs, is) jit_s_brai((rs), (is), BEQi((label)) ) #define jit_beqr_i(label, s1, s2) jit_s_brar((s1), (s2), BEQi((label)) ) #define jit_bgei_i(label, rs, is) jit_s_brai((rs), (is), BGEi((label)) ) #define jit_bgei_ui(label, rs, is) jit_u_brai((rs), (is), BGEi((label)) ) #define jit_bger_i(label, s1, s2) jit_s_brar((s1), (s2), BGEi((label)) ) #define jit_bger_ui(label, s1, s2) jit_u_brar((s1), (s2), BGEi((label)) ) #define jit_bgti_i(label, rs, is) jit_s_brai((rs), (is), BGTi((label)) ) #define jit_bgti_ui(label, rs, is) jit_u_brai((rs), (is), BGTi((label)) ) #define jit_bgtr_i(label, s1, s2) jit_s_brar((s1), (s2), BGTi((label)) ) #define jit_bgtr_ui(label, s1, s2) jit_u_brar((s1), (s2), BGTi((label)) ) #define jit_blei_i(label, rs, is) jit_s_brai((rs), (is), BLEi((label)) ) #define jit_blei_ui(label, rs, is) jit_u_brai((rs), (is), BLEi((label)) ) #define jit_bler_i(label, s1, s2) jit_s_brar((s1), (s2), BLEi((label)) ) #define jit_bler_ui(label, s1, s2) jit_u_brar((s1), (s2), BLEi((label)) ) #define jit_blti_i(label, rs, is) jit_s_brai((rs), (is), BLTi((label)) ) #define jit_blti_ui(label, rs, is) jit_u_brai((rs), (is), BLTi((label)) ) #define jit_bltr_i(label, s1, s2) jit_s_brar((s1), (s2), BLTi((label)) ) #define jit_bltr_ui(label, s1, s2) jit_u_brar((s1), (s2), BLTi((label)) ) #define jit_bnei_i(label, rs, is) jit_s_brai((rs), (is), BNEi((label)) ) #define jit_bner_i(label, s1, s2) jit_s_brar((s1), (s2), BNEi((label)) ) #define jit_boaddi_i(label, rs, is) (MOVEIri(JIT_AUX, (is)), ADDOrrr((rs), (rs), JIT_AUX), MCRXRi(0), BGTi((label)), _jit.x.pc) /* GT = bit 1 of XER = OV */ #define jit_bosubi_i(label, rs, is) (MOVEIri(JIT_AUX, (is)), SUBCOrrr((rs), (rs), JIT_AUX), MCRXRi(0), BGTi((label)), _jit.x.pc) #define jit_boaddr_i(label, s1, s2) ( ADDOrrr((s1), (s1), (s2)), MCRXRi(0), BGTi((label)), _jit.x.pc) #define jit_bosubr_i(label, s1, s2) ( SUBCOrrr((s1), (s1), (s2)), MCRXRi(0), BGTi((label)), _jit.x.pc) #define jit_boaddi_ui(label, rs, is) (jit_chk_ims ((is), ADDICri((rs), (rs), is), ADDCrr((rs), JIT_AUX)), MCRXRi(0), BEQi((label)), _jit.x.pc) /* EQ = bit 2 of XER = CA */ #define jit_bosubi_ui(label, rs, is) (jit_chk_ims ((is), SUBICri((rs), (rs), is), SUBCrr((rs), JIT_AUX)), MCRXRi(0), BEQi((label)), _jit.x.pc) #define jit_boaddr_ui(label, s1, s2) ( ADDCrr((s1), (s1), (s2)), MCRXRi(0), BEQi((label)), _jit.x.pc) #define jit_bosubr_ui(label, s1, s2) ( SUBCrr((s1), (s1), (s2)), MCRXRi(0), BEQi((label)), _jit.x.pc) #define jit_calli(label) (jit_movi_p(JIT_AUX, (label)), MTCTRr(JIT_AUX), BCTRL(), _jitl.nextarg_puti = _jitl.nextarg_putf = _jitl.nextarg_putd = 0, _jit.x.pc) #define jit_callr(reg) (MTCTRr(reg), BCTRL()) #define jit_divi_i(d, rs, is) jit_big_ims((is), DIVWrrr ((d), (rs), JIT_AUX)) #define jit_divi_ui(d, rs, is) jit_big_imu((is), DIVWUrrr((d), (rs), JIT_AUX)) #define jit_divr_i(d, s1, s2) DIVWrrr ((d), (s1), (s2)) #define jit_divr_ui(d, s1, s2) DIVWUrrr((d), (s1), (s2)) #define jit_eqi_i(d, rs, is) (jit_chk_ims((is), SUBIrri(JIT_AUX, (rs), (is)), SUBrrr(JIT_AUX, (rs), JIT_AUX)), SUBFICrri((d), JIT_AUX, 0), ADDErrr((d), (d), JIT_AUX)) #define jit_eqr_i(d, s1, s2) (SUBrrr(JIT_AUX, (s1), (s2)), SUBFICrri((d), JIT_AUX, 0), ADDErrr((d), (d), JIT_AUX)) #define jit_extr_c_i(d, rs) EXTSBrr((d), (rs)) #define jit_extr_s_i(d, rs) EXTSHrr((d), (rs)) #define jit_gei_i(d, rs, is) jit_sbooli2((d), (rs), (is), _lt) #define jit_gei_ui(d, rs, is) jit_ubooli2((d), (rs), (is), _lt) #define jit_ger_i(d, s1, s2) jit_sboolr2((d), (s1), (s2), _lt) #define jit_ger_ui(d, s1, s2) jit_uboolr2((d), (s1), (s2), _lt) #define jit_gti_i(d, rs, is) jit_sbooli ((d), (rs), (is), _gt) #define jit_gti_ui(d, rs, is) jit_ubooli ((d), (rs), (is), _gt) #define jit_gtr_i(d, s1, s2) jit_sboolr ((d), (s1), (s2), _gt) #define jit_gtr_ui(d, s1, s2) jit_uboolr ((d), (s1), (s2), _gt) #define jit_hmuli_i(d, rs, is) jit_big_ims((is), MULHWrrr ((d), (rs), JIT_AUX)) #define jit_hmuli_ui(d, rs, is) jit_big_imu((is), MULHWUrrr((d), (rs), JIT_AUX)) #define jit_hmulr_i(d, s1, s2) MULHWrrr ((d), (s1), (s2)) #define jit_hmulr_ui(d, s1, s2) MULHWUrrr((d), (s1), (s2)) #define jit_jmpi(label) (B_EXT((label)), _jit.x.pc) #define jit_jmpr(reg) (MTLRr(reg), BLR()) #define jit_ldxi_c(d, rs, is) (jit_ldxi_uc((d), (rs), (is)), jit_extr_c_i((d), (d))) #define jit_ldxr_c(d, s1, s2) (jit_ldxr_uc((d), (s1), (s2)), jit_extr_c_i((d), (d))) #define jit_ldxi_i(d, rs, is) jit_chk_ims((is), LWZrm((d), (is), (rs)), LWZrx((d), JIT_AUX, (rs))) #define jit_ldxi_s(d, rs, is) jit_chk_ims((is), LHArm((d), (is), (rs)), LHArx((d), JIT_AUX, (rs))) #define jit_ldxi_uc(d, rs, is) jit_chk_ims((is), LBZrm((d), (is), (rs)), LBZrx((d), JIT_AUX, (rs))) #define jit_ldxi_us(d, rs, is) jit_chk_ims((is), LHZrm((d), (is), (rs)), LHZrx((d), JIT_AUX, (rs))) #define jit_ldxr_i(d, s1, s2) LWZrx((d), (s1), (s2)) #define jit_ldxr_s(d, s1, s2) LHArx((d), (s1), (s2)) #define jit_ldxr_uc(d, s1, s2) LBZrx((d), (s1), (s2)) #define jit_ldxr_us(d, s1, s2) LHZrx((d), (s1), (s2)) #define jit_lei_i(d, rs, is) jit_sbooli2((d), (rs), (is), _gt ) #define jit_lei_ui(d, rs, is) jit_ubooli2((d), (rs), (is), _gt ) #define jit_ler_i(d, s1, s2) jit_sboolr2((d), (s1), (s2), _gt ) #define jit_ler_ui(d, s1, s2) jit_uboolr2((d), (s1), (s2), _gt ) #define jit_lshi_i(d, rs, is) SLWIrri((d), (rs), (is)) #define jit_lshr_i(d, s1, s2) (ANDI_rri(JIT_AUX, (s2), 31), SLWrrr ((d), (s1), JIT_AUX)) #define jit_lti_i(d, rs, is) jit_sbooli ((d), (rs), (is), _lt ) #define jit_lti_ui(d, rs, is) jit_ubooli ((d), (rs), (is), _lt ) #define jit_ltr_i(d, s1, s2) jit_sboolr ((d), (s1), (s2), _lt ) #define jit_ltr_ui(d, s1, s2) jit_uboolr ((d), (s1), (s2), _lt ) #define jit_modi_i(d, rs, is) jit_chk_ims ((is), _jit_mod_small(jit_divr_i , (d), (rs), (is)), _jit_mod_big(jit_divr_i , (d), (rs))) #define jit_modi_ui(d, rs, is) jit_chk_imu15((is), _jit_mod_small(jit_divr_ui, (d), (rs), (is)), _jit_mod_big(jit_divr_ui, (d), (rs))) #define jit_modr_i(d, s1, s2) (DIVWrrr(JIT_AUX, (s1), (s2)), MULLWrrr(JIT_AUX, JIT_AUX, (s2)), SUBrrr((d), (s1), JIT_AUX)) #define jit_modr_ui(d, s1, s2) (DIVWUrrr(JIT_AUX, (s1), (s2)), MULLWrrr(JIT_AUX, JIT_AUX, (s2)), SUBrrr((d), (s1), JIT_AUX)) #define jit_movi_i(d, is) MOVEIri((d), (is)) #define jit_movi_p(d, is) (LISri((d), _HI((is))),ORIrri((d),(d),_LO((is))),_jit.x.pc) #define jit_movr_i(d, rs) MRrr((d), (rs)) #define jit_muli_i(d, rs, is) jit_chk_ims ((is), MULLIrri((d), (rs), (is)), MULLWrrr((d), (rs), JIT_AUX)) #define jit_muli_ui(d, rs, is) jit_chk_imu15((is), MULLIrri((d), (rs), (is)), MULLWrrr((d), (rs), JIT_AUX)) #define jit_mulr_i(d, s1, s2) MULLWrrr((d), (s1), (s2)) #define jit_mulr_ui(d, s1, s2) MULLWrrr((d), (s1), (s2)) #define jit_nei_i(d, rs, is) (jit_chk_ims((is), SUBIrri(JIT_AUX, (rs), (is)), SUBrrr(JIT_AUX, (rs), JIT_AUX)), ADDICrri((d), JIT_AUX, -1), SUBFErrr((d), (d), JIT_AUX)) #define jit_ner_i(d, s1, s2) (SUBrrr(JIT_AUX, (s1), (s2)), ADDICrri((d), JIT_AUX, -1), SUBFErrr((d), (d), JIT_AUX)) #define jit_nop() NOP() #define jit_ori_i(d, rs, is) jit_chk_imu((is), ORIrri((d), (rs), (is)), ORrrr((d), (rs), JIT_AUX)) #define jit_orr_i(d, s1, s2) ORrrr((d), (s1), (s2)) #define jit_popr_i(rs) (LWZrm((rs), 0, 1), ADDIrri(1, 1, 4)) #define jit_prepare_i(numi) (_jitl.nextarg_puti = numi) #define jit_prepare_f(numf) (_jitl.nextarg_putf = numf) #define jit_prepare_d(numd) (_jitl.nextarg_putd = numd) #define jit_prolog(n) _jit_prolog(&_jit, (n)) #define jit_pushr_i(rs) STWUrm((rs), -4, 1) #define jit_pusharg_i(rs) (--_jitl.nextarg_puti, MRrr((3 + _jitl.nextarg_putd * 2 + _jitl.nextarg_putf + _jitl.nextarg_puti), (rs))) #define jit_ret() _jit_epilog(&_jit) #define jit_retval_i(rd) MRrr((rd), 3) #define jit_rsbi_i(d, rs, is) jit_chk_ims((is), SUBFICrri((d), (rs), (is)), SUBFCrrr((d), (rs), JIT_AUX)) #define jit_rshi_i(d, rs, is) SRAWIrri((d), (rs), (is)) #define jit_rshi_ui(d, rs, is) SRWIrri ((d), (rs), (is)) #define jit_rshr_i(d, s1, s2) (ANDI_rri(JIT_AUX, (s2), 31), SRAWrrr ((d), (s1), JIT_AUX)) #define jit_rshr_ui(d, s1, s2) (ANDI_rri(JIT_AUX, (s2), 31), SRWrrr ((d), (s1), JIT_AUX)) #define jit_stxi_c(id, rd, rs) jit_chk_ims((id), STBrm((rs), (id), (rd)), STBrx((rs), (rd), JIT_AUX)) #define jit_stxi_i(id, rd, rs) jit_chk_ims((id), STWrm((rs), (id), (rd)), STWrx((rs), (rd), JIT_AUX)) #define jit_stxi_s(id, rd, rs) jit_chk_ims((id), STHrm((rs), (id), (rd)), STHrx((rs), (rd), JIT_AUX)) #define jit_stxr_c(d1, d2, rs) STBrx((rs), (d1), (d2)) #define jit_stxr_i(d1, d2, rs) STWrx((rs), (d1), (d2)) #define jit_stxr_s(d1, d2, rs) STHrx((rs), (d1), (d2)) #define jit_subr_i(d, s1, s2) SUBrrr((d), (s1), (s2)) #define jit_subcr_i(d, s1, s2) SUBCrrr((d), (s1), (s2)) #define jit_subxi_i(d, rs, is) jit_big_ims((is), SUBErrr((d), (rs), JIT_AUX)) #define jit_subxr_i(d, s1, s2) SUBErrr((d), (s1), (s2)) #define jit_xori_i(d, rs, is) jit_chk_imu((is), XORIrri((d), (rs), (is)), XORrrr((d), (rs), JIT_AUX)) #define jit_xorr_i(d, s1, s2) XORrrr((d), (s1), (s2)) /* Cannot use JIT_RZERO because having 0 in a register field on the PowerPC * does not mean `a register whose value is 0', but rather `no register at * all' */ #define jit_negr_i(d, rs) jit_rsbi_i((d), (rs), 0) #define jit_negr_l(d, rs) jit_rsbi_l((d), (rs), 0) #define jit_ldr_c(rd, rs) jit_ldxr_c((rd), 0, (rs)) #define jit_str_c(rd, rs) jit_stxr_c(0, (rd), (rs)) #define jit_ldr_s(rd, rs) jit_ldxr_s((rd), 0, (rs)) #define jit_str_s(rd, rs) jit_stxr_s(0, (rd), (rs)) #define jit_ldr_i(rd, rs) jit_ldxr_i((rd), 0, (rs)) #define jit_str_i(rd, rs) jit_stxr_i(0, (rd), (rs)) #define jit_ldr_uc(rd, rs) jit_ldxr_uc((rd), 0, (rs)) #define jit_ldr_us(rd, rs) jit_ldxr_us((rd), 0, (rs)) /* e.g. * 0x01234567 _HA << 16 = 0x01230000 _LA = 0x00004567 _HA << 16 + LA = 0x01234567 * 0x89abcdef _HA << 16 = 0x89ac0000 _LA = 0xffffcdef _HA << 16 + LA = 0x89abcdef */ #define _HA(addr) ((_jit_UL(addr) >> 16) + (_jit_US(_jit_UL(addr)) >> 15)) #define _LA(addr) (_jit_UL(addr) - (_HA(addr) << 16)) #define jit_ldi_c(rd, is) (LISri(JIT_AUX, _HA(is)), jit_ldxi_c((rd), JIT_AUX, _LA(is))) #define jit_sti_c(id, rs) (LISri(JIT_AUX, _HA(id)), jit_stxi_c(_LA(id), JIT_AUX, (rs))) #define jit_ldi_s(rd, is) (LISri(JIT_AUX, _HA(is)), jit_ldxi_s((rd), JIT_AUX, _LA(is))) #define jit_sti_s(id, rs) (LISri(JIT_AUX, _HA(id)), jit_stxi_s(_LA(id), JIT_AUX, (rs))) #define jit_ldi_i(rd, is) (LISri(JIT_AUX, _HA(is)), jit_ldxi_i((rd), JIT_AUX, _LA(is))) #define jit_sti_i(id, rs) (LISri(JIT_AUX, _HA(id)), jit_stxi_i(_LA(id), JIT_AUX, (rs))) #define jit_ldi_uc(rd, is) (LISri(JIT_AUX, _HA(is)), jit_ldxi_uc((rd), JIT_AUX, _LA(is))) #define jit_ldi_us(rd, is) (LISri(JIT_AUX, _HA(is)), jit_ldxi_us((rd), JIT_AUX, _LA(is))) #endif /* __lightning_core_h */ smalltalk-3.2.5/lightning/ppc/funcs.h0000644000175000017500000001250312123404352014457 00000000000000/******************************** -*- C -*- **************************** * * Platform-independent layer inline functions (PowerPC) * ***********************************************************************/ /*********************************************************************** * * Copyright 2000, 2001, 2002, 2003, 2004 Free Software Foundation, Inc. * Written by Paolo Bonzini. * * This file is part of GNU lightning. * * GNU lightning is free software; you can redistribute it and/or modify it * under the terms of the GNU Lesser General Public License as published * by the Free Software Foundation; either version 2.1, or (at your option) * any later version. * * GNU lightning is distributed in the hope that it will be useful, but * WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY * or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser General Public * License for more details. * * You should have received a copy of the GNU Lesser General Public License * along with GNU lightning; see the file COPYING.LESSER; if not, write to the * Free Software Foundation, 51 Franklin Street, Fifth Floor, Boston, * MA 02110-1301, USA. * ***********************************************************************/ #ifndef __lightning_funcs_h #define __lightning_funcs_h #include #if !defined(__GNUC__) && !defined(__GNUG__) #error Go get GNU C, I do not know how to flush the cache #error with this compiler. #else static void jit_flush_code(void *start, void *end) { #ifndef LIGHTNING_CROSS register char *ddest, *idest; static int cache_line_size; if (cache_line_size == 0) { char buffer[8192]; int i, probe; /* Find out the size of a cache line by zeroing one */ memset(buffer, 0xFF, 8192); __asm__ __volatile__ ("dcbz 0,%0" : : "r"(buffer + 4096)); /* Probe for the beginning of the cache line. */ for(i = 0, probe = 4096; probe; probe >>= 1) if (buffer[i | probe] != 0x00) i |= probe; /* i is now just before the start of the cache line */ i++; for(cache_line_size = 1; i + cache_line_size < 8192; cache_line_size <<= 1) if (buffer[i + cache_line_size] != 0x00) break; } start -= ((long) start) & (cache_line_size - 1); end -= ((long) end) & (cache_line_size - 1); /* Force data cache write-backs */ for (ddest = (char *) start; ddest <= (char *) end; ddest += cache_line_size) { __asm__ __volatile__ ("dcbst 0,%0" : : "r"(ddest)); } __asm__ __volatile__ ("sync" : : ); /* Now invalidate the instruction cache */ for (idest = (char *) start; idest <= (char *) end; idest += cache_line_size) { __asm__ __volatile__ ("icbi 0,%0" : : "r"(idest)); } __asm__ __volatile__ ("isync" : : ); #endif /* !LIGHTNING_CROSS */ } #endif /* __GNUC__ || __GNUG__ */ #define _jit (*jit) static void _jit_epilog(jit_state *jit) { int n = _jitl.nbArgs; int frame_size, ofs; int first_saved_reg = JIT_AUX - n; int num_saved_regs = 32 - first_saved_reg; frame_size = 24 + 32 + num_saved_regs * 4; /* r24..r31 + args */ frame_size += 15; /* the stack must be quad-word */ frame_size &= ~15; /* aligned */ #ifdef __APPLE__ LWZrm(0, frame_size + 8, 1); /* lwz r0, x+8(r1) (ret.addr.) */ #else LWZrm(0, frame_size + 4, 1); /* lwz r0, x+4(r1) (ret.addr.) */ #endif MTLRr(0); /* mtspr LR, r0 */ ofs = frame_size - num_saved_regs * 4; LMWrm(first_saved_reg, ofs, 1); /* lmw rI, ofs(r1) */ ADDIrri(1, 1, frame_size); /* addi r1, r1, x */ BLR(); /* blr */ } /* Emit a prolog for a function. Upon entrance to the trampoline: - LR = address where the real code for the function lies - R3-R8 = parameters Upon finishing the trampoline: - R0 = return address for the function - R25-R20 = parameters (order is reversed, 1st argument is R25) The +32 in frame_size computation is to accound for the parameter area of a function frame. On PPC the frame must have space to host the arguments of any callee. However, as it currently stands, the argument to jit_trampoline (n) is the number of arguments of the caller we generate. Therefore, the callee can overwrite a part of the stack (saved register area when it flushes its own parameter on the stack. The addition of a constant offset = 32 is enough to hold eight 4 bytes arguments. This is less than perfect but is a reasonable work around for now. Better solution must be investigated. */ static void _jit_prolog(jit_state *jit, int n) { int frame_size; int ofs, i; int first_saved_reg = JIT_AUX - n; int num_saved_regs = 32 - first_saved_reg; _jitl.nextarg_geti = JIT_AUX - 1; _jitl.nextarg_getd = 1; _jitl.nbArgs = n; frame_size = 24 + 32 + num_saved_regs * 4; /* r27..r31 + args */ frame_size += 15; /* the stack must be quad-word */ frame_size &= ~15; /* aligned */ MFLRr(0); STWUrm(1, -frame_size, 1); /* stwu r1, -x(r1) */ ofs = frame_size - num_saved_regs * 4; STMWrm(first_saved_reg, ofs, 1); /* stmw rI, ofs(r1) */ #ifdef __APPLE__ STWrm(0, frame_size + 8, 1); /* stw r0, x+8(r1) */ #else STWrm(0, frame_size + 4, 1); /* stw r0, x+4(r1) */ #endif for (i = 0; i < n; i++) MRrr(JIT_AUX-1-i, 3+i); /* save parameters below r24 */ } #undef _jit #endif /* __lightning_funcs_h */ smalltalk-3.2.5/lightning/ppc/fp.h0000644000175000017500000002225512123404352013753 00000000000000/******************************** -*- C -*- **************************** * * Run-time assembler & support macros for the PowerPC math unit * ***********************************************************************/ /*********************************************************************** * * Copyright 2000, 2001, 2002 Free Software Foundation, Inc. * Written by Paolo Bonzini. * * This file is part of GNU lightning. * * GNU lightning is free software; you can redistribute it and/or modify it * under the terms of the GNU Lesser General Public License as published * by the Free Software Foundation; either version 2.1, or (at your option) * any later version. * * GNU lightning is distributed in the hope that it will be useful, but * WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY * or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser General Public * License for more details. * * You should have received a copy of the GNU Lesser General Public License * along with GNU lightning; see the file COPYING.LESSER; if not, write to the * Free Software Foundation, 51 Franklin Street, Fifth Floor, Boston, * MA 02110-1301, USA. * ***********************************************************************/ #ifndef __lightning_asm_fp_h #define __lightning_asm_fp_h #define JIT_FPR_NUM 6 #define JIT_FPR(i) (8+(i)) #define JIT_FPFR 0 /* Make space for 1 or 2 words, store address in REG */ #define jit_data(REG, D1) (_FBA (18, 8, 0, 1), _jit_L(D1), MFLRr(REG)) #define jit_addr_d(rd,s1,s2) FADDDrrr((rd),(s1),(s2)) #define jit_subr_d(rd,s1,s2) FSUBDrrr((rd),(s1),(s2)) #define jit_mulr_d(rd,s1,s2) FMULDrrr((rd),(s1),(s2)) #define jit_divr_d(rd,s1,s2) FDIVDrrr((rd),(s1),(s2)) #define jit_addr_f(rd,s1,s2) FADDSrrr((rd),(s1),(s2)) #define jit_subr_f(rd,s1,s2) FSUBSrrr((rd),(s1),(s2)) #define jit_mulr_f(rd,s1,s2) FMULSrrr((rd),(s1),(s2)) #define jit_divr_f(rd,s1,s2) FDIVSrrr((rd),(s1),(s2)) #define jit_movr_d(rd,rs) ( (rd) == (rs) ? 0 : FMOVErr((rd),(rs))) #define jit_movi_d(reg0,d) do { \ double _v = (d); \ _FBA (18, 12, 0, 1); \ memcpy(_jit.x.uc_pc, &_v, sizeof (double)); \ _jit.x.uc_pc += sizeof (double); \ MFLRr (JIT_AUX); \ jit_ldxi_d((reg0), JIT_AUX, 0); \ } while(0) #define jit_movr_f(rd,rs) ( (rd) == (rs) ? 0 : FMOVErr((rd),(rs))) #define jit_movi_f(reg0,f) do { \ float _v = (f); \ _FBA (18, 8, 0, 1); \ memcpy(_jit.x.uc_pc, &_v, sizeof (float)); \ _jit.x.uc_pc += sizeof (float); \ MFLRr (JIT_AUX); \ jit_ldxi_f((reg0), JIT_AUX, 0); \ } while(0) #define jit_abs_d(rd,rs) FABSrr((rd),(rs)) #define jit_negr_d(rd,rs) FNEGrr((rd),(rs)) #define jit_sqrt_d(rd,rs) FSQRTDrr((rd),(rs)) #define jit_ldxi_f(reg0, rs, is) (_siP(16,(is)) ? LFSrri((reg0),(rs),(is)) : (MOVEIri(JIT_AUX,(is)),LFSxrrr((reg0),(rs),JIT_AUX))) #define jit_ldxi_d(reg0, rs, is) (_siP(16,(is)) ? LFDrri((reg0),(rs),(is)) : (MOVEIri(JIT_AUX,(is)),LFDxrrr((reg0),(rs),JIT_AUX))) #define jit_ldxr_f(reg0, s1, s2) LFSxrrr((reg0),(s1),(s2)) #define jit_ldxr_d(reg0, s1, s2) LFDxrrr((reg0),(s1),(s2)) #define jit_ldi_f(reg0, is) (_siP(16,(is)) ? LFSrri((reg0),0,(is)) : (MOVEIri(JIT_AUX,(is)),LFSrri((reg0),JIT_AUX,0))) #define jit_ldi_d(reg0, is) (_siP(16,(is)) ? LFDrri((reg0),0,(is)) : (MOVEIri(JIT_AUX,(is)),LFDrri((reg0),JIT_AUX,0))) #define jit_ldr_f(reg0, rs) LFSrri((reg0),(rs),0) #define jit_ldr_d(reg0, rs) LFDrri((reg0),(rs),0) #define jit_stxi_f(id, rd, reg0) (_siP(16,(id)) ? STFSrri((reg0),(rd),(id)) : (MOVEIri(JIT_AUX,(id)),STFSrri((reg0),(rd),JIT_AUX))) #define jit_stxi_d(id, rd, reg0) (_siP(16,(id)) ? STFDrri((reg0),(rd),(id)) : (MOVEIri(JIT_AUX,(id)),STFDrri((reg0),(rd),JIT_AUX))) #define jit_stxr_f(d1, d2, reg0) STFSxrrr((reg0),(d1),(d2)) #define jit_stxr_d(d1, d2, reg0) STFDxrrr((reg0),(d1),(d2)) #define jit_sti_f(id, reg0) (_siP(16,(id)) ? STFSrri((reg0),0,(id)) : (MOVEIri(JIT_AUX,(id)),STFSrri((reg0),JIT_AUX,0))) #define jit_sti_d(id, reg0) (_siP(16,(id)) ? STFDrri((reg0),0,(id)) : (MOVEIri(JIT_AUX,(id)),STFDrri((reg0),JIT_AUX,0))) #define jit_str_f(rd, reg0) STFSrri((reg0),(rd),0) #define jit_str_d(rd, reg0) STFDrri((reg0),(rd),0) #define jit_fpboolr(d, s1, s2, rcbit) ( \ FCMPOrrr(_cr0,(s1),(s2)), \ MFCRr((d)), \ EXTRWIrrii((d), (d), 1, (rcbit))) #define jit_fpboolr_neg(d, s1, s2,rcbit) ( \ FCMPOrrr(_cr0,(s1),(s2)), \ MFCRr((d)), \ EXTRWIrrii((d), (d), 1, (rcbit)), \ XORIrri((d), (d), 1)) #define jit_fpboolur(d, s1, s2, rcbit) ( \ FCMPUrrr(_cr0,(s1),(s2)), \ MFCRr((d)), \ EXTRWIrrii((d), (d), 1, (rcbit))) #define jit_fpboolur_neg(d, s1, s2,rcbit) ( \ FCMPUrrr(_cr0,(s1),(s2)), \ MFCRr((d)), \ EXTRWIrrii((d), (d), 1, (rcbit)), \ XORIrri((d), (d), 1)) #define jit_fpboolur_or(d, s1, s2, bit1, bit2) (\ FCMPUrrr(_cr0,(s1),(s2)), \ CRORiii((bit1), (bit1), (bit2)), \ MFCRr((d)), \ EXTRWIrrii((d), (d), 1, (bit1))) #define jit_gtr_d(d, s1, s2) jit_fpboolr ((d),(s1),(s2),_gt) #define jit_ger_d(d, s1, s2) jit_fpboolr_neg((d),(s1),(s2),_lt) #define jit_ltr_d(d, s1, s2) jit_fpboolr ((d),(s1),(s2),_lt) #define jit_ler_d(d, s1, s2) jit_fpboolr_neg((d),(s1),(s2),_gt) #define jit_eqr_d(d, s1, s2) jit_fpboolr ((d),(s1),(s2),_eq) #define jit_ner_d(d, s1, s2) jit_fpboolr_neg((d),(s1),(s2),_eq) #define jit_unordr_d(d, s1, s2) jit_fpboolur ((d),(s1),(s2),_un) #define jit_ordr_d(d, s1, s2) jit_fpboolur_neg((d),(s1),(s2),_un) #define jit_unler_d(d, s1, s2) jit_fpboolur_neg ((d), (s1), (s2), _gt) #define jit_unltr_d(d, s1, s2) jit_fpboolur_or ((d), (s1), (s2), _un, _lt) #define jit_unger_d(d, s1, s2) jit_fpboolur_neg ((d), (s1), (s2), _lt) #define jit_ungtr_d(d, s1, s2) jit_fpboolur_or ((d), (s1), (s2), _un, _gt) #define jit_ltgtr_d(d, s1, s2) jit_fpboolur_or ((d), (s1), (s2), _gt, _lt) #define jit_uneqr_d(d, s1, s2) jit_fpboolur_or ((d), (s1), (s2), _un, _eq) #define jit_fpbr(d, s1, s2, rcbit) ( \ FCMPOrrr(_cr0,(s1),(s2)), \ BTii ((rcbit), (d))) #define jit_fpbr_neg(d, s1, s2,rcbit) ( \ FCMPOrrr(_cr0,(s1),(s2)), \ BFii ((rcbit), (d))) #define jit_fpbur(d, s1, s2, rcbit) ( \ FCMPUrrr(_cr0,(s1),(s2)), \ BTii ((rcbit), (d))) #define jit_fpbur_neg(d, s1, s2,rcbit) ( \ FCMPUrrr(_cr0,(s1),(s2)), \ BFii ((rcbit), (d))) #define jit_fpbur_or(d, s1, s2, bit1, bit2) ( \ FCMPUrrr(_cr0,(s1),(s2)), \ CRORiii((bit1), (bit1), (bit2)), \ BTii ((bit1), (d))) #define jit_bgtr_d(d, s1, s2) jit_fpbr ((d),(s1),(s2),_gt) #define jit_bger_d(d, s1, s2) jit_fpbr_neg((d),(s1),(s2),_lt) #define jit_bltr_d(d, s1, s2) jit_fpbr ((d),(s1),(s2),_lt) #define jit_bler_d(d, s1, s2) jit_fpbr_neg((d),(s1),(s2),_gt) #define jit_beqr_d(d, s1, s2) jit_fpbr ((d),(s1),(s2),_eq) #define jit_bner_d(d, s1, s2) jit_fpbr_neg((d),(s1),(s2),_eq) #define jit_bunordr_d(d, s1, s2) jit_fpbur ((d),(s1),(s2),_un) #define jit_bordr_d(d, s1, s2) jit_fpbur_neg((d),(s1),(s2),_un) #define jit_bunler_d(d, s1, s2) jit_fpbur_neg ((d), (s1), (s2), _gt) #define jit_bunltr_d(d, s1, s2) jit_fpbur_or ((d), (s1), (s2), _un, _lt) #define jit_bunger_d(d, s1, s2) jit_fpbur_neg ((d), (s1), (s2), _lt) #define jit_bungtr_d(d, s1, s2) jit_fpbur_or ((d), (s1), (s2), _un, _gt) #define jit_bltgtr_d(d, s1, s2) jit_fpbur_or ((d), (s1), (s2), _gt, _lt) #define jit_buneqr_d(d, s1, s2) jit_fpbur_or ((d), (s1), (s2), _un, _eq) #define jit_getarg_f(rd, ofs) jit_movr_f((rd),(ofs)) #define jit_getarg_d(rd, ofs) jit_movr_d((rd),(ofs)) #define jit_pusharg_d(rs) (_jitl.nextarg_putd--,jit_movr_d((_jitl.nextarg_putf+_jitl.nextarg_putd+1), (rs))) #define jit_pusharg_f(rs) (_jitl.nextarg_putf--,jit_movr_f((_jitl.nextarg_putf+_jitl.nextarg_putd+1), (rs))) #define jit_retval_d(op1) jit_movr_d(1, (op1)) #define jit_retval_f(op1) jit_movr_f(1, (op1)) #define jit_floorr_d_i(rd,rs) (MTFSFIri(7,3), \ FCTIWrr(7,(rs)), \ MOVEIri(JIT_AUX,-4), \ STFIWXrrr(7,JIT_SP,JIT_AUX), \ LWZrm((rd),-4,JIT_SP)) #define jit_ceilr_d_i(rd,rs) (MTFSFIri(7,2), \ FCTIWrr(7,(rs)), \ MOVEIri(JIT_AUX,-4), \ STFIWXrrr(7,JIT_SP,JIT_AUX), \ LWZrm((rd),-4,JIT_SP)) #define jit_roundr_d_i(rd,rs) (MTFSFIri(7,0), \ FCTIWrr(7,(rs)), \ MOVEIri(JIT_AUX,-4), \ STFIWXrrr(7,JIT_SP,JIT_AUX), \ LWZrm((rd),-4,JIT_SP)) #define jit_truncr_d_i(rd,rs) (FCTIWZrr(7,(rs)), \ MOVEIri(JIT_AUX,-4), \ STFIWXrrr(7,JIT_SP,JIT_AUX), \ LWZrm((rd),-4,JIT_SP)) #endif /* __lightning_asm_h */ smalltalk-3.2.5/lightning/fp-common.h0000644000175000017500000000705712123404352014462 00000000000000/******************************** -*- C -*- **************************** * * Platform-independent layer floating-point interface * ***********************************************************************/ /*********************************************************************** * * Copyright 2000, 2001, 2002 Free Software Foundation, Inc. * Written by Paolo Bonzini. * * This file is part of GNU lightning. * * GNU lightning is free software; you can redistribute it and/or modify it * under the terms of the GNU Lesser General Public License as published * by the Free Software Foundation; either version 2.1, or (at your option) * any later version. * * GNU lightning is distributed in the hope that it will be useful, but * WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY * or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser General Public * License for more details. * * You should have received a copy of the GNU Lesser General Public License * along with GNU lightning; see the file COPYING.LESSER; if not, write to the * Free Software Foundation, 51 Franklin Street, Fifth Floor, Boston, * MA 02110-1301, USA. * ***********************************************************************/ #define JIT_FPR0 JIT_FPR(0) #define JIT_FPR1 JIT_FPR(1) #define JIT_FPR2 JIT_FPR(2) #define JIT_FPR3 JIT_FPR(3) #define JIT_FPR4 JIT_FPR(4) #define JIT_FPR5 JIT_FPR(5) #ifdef JIT_RZERO #ifndef jit_ldi_f #define jit_ldi_f(rd, is) jit_ldxi_f((rd), JIT_RZERO, (is)) #define jit_sti_f(id, rs) jit_stxi_f((id), JIT_RZERO, (rs)) #define jit_ldi_d(rd, is) jit_ldxi_d((rd), JIT_RZERO, (is)) #define jit_sti_d(id, rs) jit_stxi_d((id), JIT_RZERO, (rs)) #endif #ifndef jit_ldr_f #define jit_ldr_f(rd, rs) jit_ldxr_f((rd), JIT_RZERO, (rs)) #define jit_str_f(rd, rs) jit_stxr_f((rd), JIT_RZERO, (rs)) #define jit_ldr_d(rd, rs) jit_ldxr_d((rd), JIT_RZERO, (rs)) #define jit_str_d(rd, rs) jit_stxr_d((rd), JIT_RZERO, (rs)) #endif #endif #ifndef jit_addr_f #define jit_addr_f(rd,s1,s2) jit_addr_d(rd,s1,s2) #define jit_subr_f(rd,s1,s2) jit_subr_d(rd,s1,s2) #define jit_mulr_f(rd,s1,s2) jit_mulr_d(rd,s1,s2) #define jit_divr_f(rd,s1,s2) jit_divr_d(rd,s1,s2) #define jit_movr_f(rd,rs) jit_movr_d(rd,rs) #define jit_abs_f(rd,rs) jit_abs_d(rd,rs) #define jit_negr_f(rd,rs) jit_negr_d(rd,rs) #define jit_sqrt_f(rd,rs) jit_sqrt_d(rd,rs) #define jit_extr_f_d(rs, rd) #define jit_extr_d_f(rs, rd) #define jit_extr_i_f(rd, rs) jit_extr_i_d(rd, rs) #define jit_roundr_f_i(rd, rs) jit_roundr_d_i(rd, rs) #define jit_floorr_f_i(rd, rs) jit_floorr_d_i(rd, rs) #define jit_ceilr_f_i(rd, rs) jit_ceilr_d_i(rd, rs) #define jit_truncr_f_i(rd, rs) jit_truncr_d_i(rd, rs) #define jit_ltr_f(d, s1, s2) jit_ltr_d(d, s1, s2) #define jit_ler_f(d, s1, s2) jit_ler_d(d, s1, s2) #define jit_eqr_f(d, s1, s2) jit_eqr_d(d, s1, s2) #define jit_ner_f(d, s1, s2) jit_ner_d(d, s1, s2) #define jit_ger_f(d, s1, s2) jit_ger_d(d, s1, s2) #define jit_gtr_f(d, s1, s2) jit_gtr_d(d, s1, s2) #define jit_unltr_f(d, s1, s2) jit_unltr_d(d, s1, s2) #define jit_unler_f(d, s1, s2) jit_unler_d(d, s1, s2) #define jit_uneqr_f(d, s1, s2) jit_uneqr_d(d, s1, s2) #define jit_ltgtr_f(d, s1, s2) jit_ltgtr_d(d, s1, s2) #define jit_unger_f(d, s1, s2) jit_unger_d(d, s1, s2) #define jit_ungtr_f(d, s1, s2) jit_ungtr_d(d, s1, s2) #define jit_ordr_f(d, s1, s2) jit_ordr_d(d, s1, s2) #define jit_unordr_f(d, s1, s2) jit_unordr_d(d, s1, s2) #define jit_retval_f(rs) jit_retval_d(rs) #endif smalltalk-3.2.5/lightning/i386/0000755000175000017500000000000012130456003013154 500000000000000smalltalk-3.2.5/lightning/i386/asm-i386.h0000644000175000017500000014337612123404352014534 00000000000000/******************************** -*- C -*- **************************** * * Run-time assembler for the i386 * ***********************************************************************/ /*********************************************************************** * * Copyright 1999, 2000, 2001, 2002 Ian Piumarta * * This file is part of GNU lightning. * * GNU lightning is free software; you can redistribute it and/or modify it * under the terms of the GNU Lesser General Public License as published * by the Free Software Foundation; either version 2.1, or (at your option) * any later version. * * GNU lightning is distributed in the hope that it will be useful, but * WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY * or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser General Public * License for more details. * * You should have received a copy of the GNU Lesser General Public License * along with GNU lightning; see the file COPYING.LESSER; if not, write to the * Free Software Foundation, 51 Franklin Street, Fifth Floor, Boston, * MA 02110-1301, USA. * ***********************************************************************/ #ifndef __lightning_asm_i386_h #define __lightning_asm_i386_h /* OPCODE + i = immediate operand * + r = register operand * + m = memory operand (disp,base,index,scale) * + sr/sm = a star preceding a register or memory */ typedef _uc jit_insn; #ifndef LIGHTNING_DEBUG #define _b00 0 #define _b01 1 #define _b10 2 #define _b11 3 #define _b000 0 #define _b001 1 #define _b010 2 #define _b011 3 #define _b100 4 #define _b101 5 #define _b110 6 #define _b111 7 /*** REGISTERS ***/ /* [size,,number] */ #define _AL 0x10 #define _CL 0x11 #define _DL 0x12 #define _BL 0x13 #define _AH 0x14 #define _CH 0x15 #define _DH 0x16 #define _BH 0x17 #define _AX 0x20 #define _CX 0x21 #define _DX 0x22 #define _BX 0x23 #define _SP 0x24 #define _BP 0x25 #define _SI 0x26 #define _DI 0x27 #define _EAX 0x40 #define _ECX 0x41 #define _EDX 0x42 #define _EBX 0x43 #define _ESP 0x44 #define _EBP 0x45 #define _ESI 0x46 #define _EDI 0x47 #define _ST0 0 #define _ST1 1 #define _ST2 2 #define _ST3 3 #define _ST4 4 #define _ST5 5 #define _ST6 6 #define _ST7 7 #define _rS(R) ((R)>>4) #define _rN(R) ((R)&0x7) #define _r0P(R) ((R)==0) #ifndef _ASM_SAFETY #define _r1(R) _rN(R) #define _r2(R) _rN(R) #define _r4(R) _rN(R) #else #define _r1(R) ((_rS(R)==1) ? _rN(R) : JITFAIL( "8-bit register required")) #define _r2(R) ((_rS(R)==2) ? _rN(R) : JITFAIL("16-bit register required")) #define _r4(R) ((_rS(R)==4) ? _rN(R) : JITFAIL("32-bit register required")) #endif /*** ASSEMBLER ***/ #define _OFF4(D) (_jit_UL(D) - _jit_UL(_jit.x.pc)) #define _CKD8(D) _ck_d(8, ((_uc) _OFF4(D)) ) #define _D8(D) (_jit_B(0), ((*(_PUC(_jit.x.pc)-1))= _CKD8(D))) #define _D32(D) (_jit_L(0), ((*(_PUL(_jit.x.pc)-1))= _OFF4(D))) #ifndef _ASM_SAFETY # define _M(M) (M) # define _r(R) (R) # define _m(M) (M) # define _s(S) (S) # define _i(I) (I) # define _b(B) (B) # define _noESP(I,OK) (OK) #else # define _M(M) (((M)>3) ? JITFAIL("internal error: mod = " #M) : (M)) # define _r(R) (((R)>7) ? JITFAIL("internal error: reg = " #R) : (R)) # define _m(M) (((M)>7) ? JITFAIL("internal error: r/m = " #M) : (M)) # define _s(S) (((S)>3) ? JITFAIL("internal error: memory scale = " #S) : (S)) # define _i(I) (((I)>7) ? JITFAIL("internal error: memory index = " #I) : (I)) # define _b(B) (((B)>7) ? JITFAIL("internal error: memory base = " #B) : (B)) # define _noESP(I,OK) (((I)==_ESP) ? JITFAIL("illegal index register: %esp") : (OK)) #endif #define _Mrm(Md,R,M) _jit_B((_M(Md)<<6)|(_r(R)<<3)|_m(M)) #define _SIB(Sc,I, B) _jit_B((_s(Sc)<<6)|(_i(I)<<3)|_b(B)) #define _SCL(S) ((((S)==1) ? _b00 : \ (((S)==2) ? _b01 : \ (((S)==4) ? _b10 : \ (((S)==8) ? _b11 : JITFAIL("illegal scale: " #S)))))) /* memory subformats - urgh! */ #define _r_0B( R, B ) (_Mrm(_b00,_rN(R),_r4(B)) ) #define _r_0BIS(R, B,I,S) (_Mrm(_b00,_rN(R),_b100 ),_SIB(_SCL(S),_r4(I),_r4(B)) ) #define _r_1B( R, D,B ) (_Mrm(_b01,_rN(R),_r4(B)) ,_jit_B((long)(D))) #define _r_1BIS(R, D,B,I,S) (_Mrm(_b01,_rN(R),_b100 ),_SIB(_SCL(S),_r4(I),_r4(B)),_jit_B((long)(D))) #define _r_4B( R, D,B ) (_Mrm(_b10,_rN(R),_r4(B)) ,_jit_L((long)(D))) #define _r_4IS( R, D,I,S) (_Mrm(_b00,_rN(R),_b100 ),_SIB(_SCL(S),_r4(I),_b101 ),_jit_L((long)(D))) #define _r_4BIS(R, D,B,I,S) (_Mrm(_b10,_rN(R),_b100 ),_SIB(_SCL(S),_r4(I),_r4(B)),_jit_L((long)(D))) #define _r_DB( R, D,B ) ((_s0P(D) && (B != _EBP) ? _r_0B (R, B ) : (_s8P(D) ? _r_1B( R,D,B ) : _r_4B( R,D,B )))) #define _r_DBIS(R, D,B,I,S) ((_s0P(D) ? _r_0BIS(R, B,I,S) : (_s8P(D) ? _r_1BIS(R,D,B,I,S) : _r_4BIS(R,D,B,I,S)))) #define _r_X( R, D,B,I,S) (_r0P(I) ? (_r0P(B) ? _r_D (R,D ) : \ (_ESP==(B) ? _r_DBIS(R,D,_ESP,_ESP,1) : \ _r_DB (R,D, B ))) : \ (_r0P(B) ? _r_4IS (R,D, I,S) : \ (((I)!=_ESP) ? _r_DBIS(R,D, B, I,S) : \ JITFAIL("illegal index register: %esp")))) /* instruction formats */ /* _format Opcd ModR/M dN(rB,rI,Sc) imm... */ #define _d16() ( _jit_B(0x66 ) ) #define _O( OP ) ( _jit_B( OP ) ) #define _Or( OP,R ) ( _jit_B( (OP)|_r(R)) ) #define _OO( OP ) ( _jit_B((OP)>>8), _jit_B( (OP) ) ) #define _OOr( OP,R ) ( _jit_B((OP)>>8), _jit_B( (OP)|_r(R)) ) #define _Os( OP,B ) ( _s8P(B) ? _jit_B(((OP)|_b10)) : _jit_B(OP) ) #define _sW( W ) ( _s8P(W) ? _jit_B(W):_jit_W(W) ) #define _sL( L ) ( _s8P(L) ? _jit_B(L):_jit_L(L) ) #define _O_W( OP ,W ) ( _O ( OP ) ,_jit_W(W) ) #define _O_D8( OP ,D ) ( _O ( OP ) ,_D8(D) ) #define _O_D32( OP ,D ) ( _O ( OP ) ,_D32(D) ) #define _OO_D32( OP ,D ) ( _OO ( OP ) ,_D32(D) ) #define _Os_sW( OP ,W ) ( _Os ( OP,W) ,_sW(W) ) #define _Os_sL( OP ,L ) ( _Os ( OP,L) ,_sL(L) ) #define _O_W_B( OP ,W,B) ( _O ( OP ) ,_jit_W(W),_jit_B(B)) #define _Or_B( OP,R ,B ) ( _Or ( OP,R) ,_jit_B(B) ) #define _Or_W( OP,R ,W ) ( _Or ( OP,R) ,_jit_W(W) ) #define _Or_L( OP,R ,L ) ( _Or ( OP,R) ,_jit_L(L) ) #define _O_Mrm( OP ,MO,R,M ) ( _O ( OP ),_Mrm(MO,R,M ) ) #define _OO_Mrm( OP ,MO,R,M ) ( _OO ( OP ),_Mrm(MO,R,M ) ) #define _O_Mrm_B( OP ,MO,R,M ,B ) ( _O ( OP ),_Mrm(MO,R,M ) ,_jit_B(B) ) #define _O_Mrm_W( OP ,MO,R,M ,W ) ( _O ( OP ),_Mrm(MO,R,M ) ,_jit_W(W) ) #define _O_Mrm_L( OP ,MO,R,M ,L ) ( _O ( OP ),_Mrm(MO,R,M ) ,_jit_L(L) ) #define _OO_Mrm_B( OP ,MO,R,M ,B ) ( _OO ( OP ),_Mrm(MO,R,M ) ,_jit_B(B) ) #define _Os_Mrm_sW(OP ,MO,R,M ,W ) ( _Os ( OP,W),_Mrm(MO,R,M ),_sW(W) ) #define _Os_Mrm_sL(OP ,MO,R,M ,L ) ( _Os ( OP,L),_Mrm(MO,R,M ),_sL(L) ) #define _O_r_X( OP ,R ,MD,MB,MI,MS ) ( _O ( OP ),_r_X( R ,MD,MB,MI,MS) ) #define _OO_r_X( OP ,R ,MD,MB,MI,MS ) ( _OO ( OP ),_r_X( R ,MD,MB,MI,MS) ) #define _O_r_X_B( OP ,R ,MD,MB,MI,MS,B ) ( _O ( OP ),_r_X( R ,MD,MB,MI,MS) ,_jit_B(B) ) #define _O_r_X_W( OP ,R ,MD,MB,MI,MS,W ) ( _O ( OP ),_r_X( R ,MD,MB,MI,MS) ,_jit_W(W) ) #define _O_r_X_L( OP ,R ,MD,MB,MI,MS,L ) ( _O ( OP ),_r_X( R ,MD,MB,MI,MS) ,_jit_L(L) ) #define _OO_r_X_B( OP ,R ,MD,MB,MI,MS,B ) ( _OO ( OP ),_r_X( R ,MD,MB,MI,MS) ,_jit_B(B) ) #define _Os_r_X_sW(OP ,R ,MD,MB,MI,MS,W ) ( _Os ( OP,W),_r_X( R ,MD,MB,MI,MS),_sW(W) ) #define _Os_r_X_sL(OP ,R ,MD,MB,MI,MS,L ) ( _Os ( OP,L),_r_X( R ,MD,MB,MI,MS),_sL(L) ) #define _O_X_B( OP ,MD,MB,MI,MS,B ) ( _O_r_X_B( OP ,0 ,MD,MB,MI,MS ,B) ) #define _O_X_W( OP ,MD,MB,MI,MS,W ) ( _O_r_X_W( OP ,0 ,MD,MB,MI,MS ,W) ) #define _O_X_L( OP ,MD,MB,MI,MS,L ) ( _O_r_X_L( OP ,0 ,MD,MB,MI,MS ,L) ) #define _wO( OP ) (_d16(), _O( OP ) ) #define _wOr( OP,R ) (_d16(), _Or( OP,R ) ) #define _wOr_W( OP,R ,W ) (_d16(), _Or_W( OP,R ,W) ) #define _wOs_sW( OP ,W ) (_d16(), _Os_sW( OP ,W) ) #define _wO_Mrm( OP ,MO,R,M ) (_d16(), _O_Mrm( OP ,MO,R,M ) ) #define _wOO_Mrm( OP ,MO,R,M ) (_d16(),_OO_Mrm( OP ,MO,R,M ) ) #define _wO_Mrm_B( OP ,MO,R,M ,B ) (_d16(), _O_Mrm_B( OP ,MO,R,M ,B) ) #define _wOO_Mrm_B( OP ,MO,R,M ,B ) (_d16(),_OO_Mrm_B( OP ,MO,R,M ,B) ) #define _wO_Mrm_W( OP ,MO,R,M ,W ) (_d16(), _O_Mrm_W( OP ,MO,R,M ,W) ) #define _wOs_Mrm_sW(OP ,MO,R,M ,W ) (_d16(), _Os_Mrm_sW(OP ,MO,R,M ,W) ) #define _wO_X_W( OP ,MD,MB,MI,MS,W ) (_d16(), _O_X_W( OP ,MD,MB,MI,MS ,W) ) #define _wO_r_X( OP ,R ,MD,MB,MI,MS ) (_d16(), _O_r_X( OP ,R ,MD,MB,MI,MS ) ) #define _wOO_r_X( OP ,R ,MD,MB,MI,MS ) (_d16(),_OO_r_X( OP ,R ,MD,MB,MI,MS ) ) #define _wO_r_X_B( OP ,R ,MD,MB,MI,MS,B ) (_d16(), _O_r_X_B( OP ,R ,MD,MB,MI,MS ,B) ) #define _wOO_r_X_B( OP ,R ,MD,MB,MI,MS,B ) (_d16(),_OO_r_X_B( OP ,R ,MD,MB,MI,MS ,B) ) #define _wO_r_X_W( OP ,R ,MD,MB,MI,MS,W ) (_d16(), _O_r_X_W( OP ,R ,MD,MB,MI,MS ,W) ) #define _wOs_r_X_sW(OP ,R ,MD,MB,MI,MS,W ) (_d16(), _Os_r_X_sW(OP ,R ,MD,MB,MI,MS ,W) ) /* +++ fully-qualified intrinsic instructions */ /* _format Opcd ,Mod ,r ,m ,mem=dsp+sib ,imm... */ #define ADCBrr(RS, RD) _O_Mrm (0x10 ,_b11,_r1(RS),_r1(RD) ) #define ADCBmr(MD, MB, MI, MS, RD) _O_r_X (0x12 ,_r1(RD) ,MD,MB,MI,MS ) #define ADCBrm(RS, MD, MB, MI, MS) _O_r_X (0x10 ,_r1(RS) ,MD,MB,MI,MS ) #define ADCBir(IM, RD) _O_Mrm_B (0x80 ,_b11,_b010 ,_r1(RD) ,_su8(IM)) #define ADCBim(IM, MD, MB, MI, MS) _O_r_X_B (0x80 ,_b010 ,MD,MB,MI,MS ,_su8(IM)) #define ADCWrr(RS, RD) _wO_Mrm (0x11 ,_b11,_r2(RS),_r2(RD) ) #define ADCWmr(MD, MB, MI, MS, RD) _wO_r_X (0x13 ,_r2(RD) ,MD,MB,MI,MS ) #define ADCWrm(RS, MD, MB, MI, MS) _wO_r_X (0x11 ,_r2(RS) ,MD,MB,MI,MS ) #define ADCWir(IM, RD) _wOs_Mrm_sW (0x81 ,_b11,_b010 ,_r2(RD) ,_su16(IM)) #define ADCWim(IM, MD, MB, MI, MS) _wOs_r_X_sW (0x81 ,_b010 ,MD,MB,MI,MS ,_su16(IM)) #define ADCLrr(RS, RD) _O_Mrm (0x11 ,_b11,_r4(RS),_r4(RD) ) #define ADCLmr(MD, MB, MI, MS, RD) _O_r_X (0x13 ,_r4(RD) ,MD,MB,MI,MS ) #define ADCLrm(RS, MD, MB, MI, MS) _O_r_X (0x11 ,_r4(RS) ,MD,MB,MI,MS ) #define ADCLir(IM, RD) _Os_Mrm_sL (0x81 ,_b11,_b010 ,_r4(RD) ,IM ) #define ADCLim(IM, MD, MB, MI, MS) _Os_r_X_sL (0x81 ,_b010 ,MD,MB,MI,MS ,IM ) #define ADDBrr(RS, RD) _O_Mrm (0x00 ,_b11,_r1(RS),_r1(RD) ) #define ADDBmr(MD, MB, MI, MS, RD) _O_r_X (0x02 ,_r1(RD) ,MD,MB,MI,MS ) #define ADDBrm(RS, MD, MB, MI, MS) _O_r_X (0x00 ,_r1(RS) ,MD,MB,MI,MS ) #define ADDBir(IM, RD) _O_Mrm_B (0x80 ,_b11,_b000 ,_r1(RD) ,_su8(IM)) #define ADDBim(IM, MD, MB, MI, MS) _O_r_X_B (0x80 ,_b000 ,MD,MB,MI,MS ,_su8(IM)) #define ADDWrr(RS, RD) _wO_Mrm (0x01 ,_b11,_r2(RS),_r2(RD) ) #define ADDWmr(MD, MB, MI, MS, RD) _wO_r_X (0x03 ,_r2(RD) ,MD,MB,MI,MS ) #define ADDWrm(RS, MD, MB, MI, MS) _wO_r_X (0x01 ,_r2(RS) ,MD,MB,MI,MS ) #define ADDWir(IM, RD) _wOs_Mrm_sW (0x81 ,_b11,_b000 ,_r2(RD) ,_su16(IM)) #define ADDWim(IM, MD, MB, MI, MS) _wOs_r_X_sW (0x81 ,_b000 ,MD,MB,MI,MS ,_su16(IM)) #define ADDLrr(RS, RD) _O_Mrm (0x01 ,_b11,_r4(RS),_r4(RD) ) #define ADDLmr(MD, MB, MI, MS, RD) _O_r_X (0x03 ,_r4(RD) ,MD,MB,MI,MS ) #define ADDLrm(RS, MD, MB, MI, MS) _O_r_X (0x01 ,_r4(RS) ,MD,MB,MI,MS ) #define ADDLir(IM, RD) _Os_Mrm_sL (0x81 ,_b11,_b000 ,_r4(RD) ,IM ) #define ADDLim(IM, MD, MB, MI, MS) _Os_r_X_sL (0x81 ,_b000 ,MD,MB,MI,MS ,IM ) #define ANDBrr(RS, RD) _O_Mrm (0x20 ,_b11,_r1(RS),_r1(RD) ) #define ANDBmr(MD, MB, MI, MS, RD) _O_r_X (0x22 ,_r1(RD) ,MD,MB,MI,MS ) #define ANDBrm(RS, MD, MB, MI, MS) _O_r_X (0x20 ,_r1(RS) ,MD,MB,MI,MS ) #define ANDBir(IM, RD) _O_Mrm_B (0x80 ,_b11,_b100 ,_r1(RD) ,_su8(IM)) #define ANDBim(IM, MD, MB, MI, MS) _O_r_X_B (0x80 ,_b100 ,MD,MB,MI,MS ,_su8(IM)) #define ANDWrr(RS, RD) _wO_Mrm (0x21 ,_b11,_r2(RS),_r2(RD) ) #define ANDWmr(MD, MB, MI, MS, RD) _wO_r_X (0x23 ,_r2(RD) ,MD,MB,MI,MS ) #define ANDWrm(RS, MD, MB, MI, MS) _wO_r_X (0x21 ,_r2(RS) ,MD,MB,MI,MS ) #define ANDWir(IM, RD) _wOs_Mrm_sW (0x81 ,_b11,_b100 ,_r2(RD) ,_su16(IM)) #define ANDWim(IM, MD, MB, MI, MS) _wOs_r_X_sW (0x81 ,_b100 ,MD,MB,MI,MS ,_su16(IM)) #define ANDLrr(RS, RD) _O_Mrm (0x21 ,_b11,_r4(RS),_r4(RD) ) #define ANDLmr(MD, MB, MI, MS, RD) _O_r_X (0x23 ,_r4(RD) ,MD,MB,MI,MS ) #define ANDLrm(RS, MD, MB, MI, MS) _O_r_X (0x21 ,_r4(RS) ,MD,MB,MI,MS ) #define ANDLir(IM, RD) _Os_Mrm_sL (0x81 ,_b11,_b100 ,_r4(RD) ,IM ) #define ANDLim(IM, MD, MB, MI, MS) _Os_r_X_sL (0x81 ,_b100 ,MD,MB,MI,MS ,IM ) #define BSWAPLr(R) _OOr (0x0fc8,_r4(R) ) #define BTWir(IM,RD) _wOO_Mrm_B (0x0fba ,_b11,_b100 ,_r2(RD) ,_u8(IM)) #define BTWim(IM,MD,MB,MI,MS) _wOO_r_X_B (0x0fba ,_b100 ,MD,MB,MI,MS ,_u8(IM)) #define BTWrr(RS,RD) _wOO_Mrm (0x0fa3 ,_b11,_r2(RS),_r2(RD) ) #define BTWrm(RS,MD,MB,MI,MS) _wOO_r_X (0x0fa3 ,_r2(RS) ,MD,MB,MI,MS ) #define BTLir(IM,RD) _OO_Mrm_B (0x0fba ,_b11,_b100 ,_r4(RD) ,_u8(IM)) #define BTLim(IM,MD,MB,MI,MS) _OO_r_X_B (0x0fba ,_b100 ,MD,MB,MI,MS ,_u8(IM)) #define BTLrr(RS,RD) _OO_Mrm (0x0fa3 ,_b11,_r4(RS),_r4(RD) ) #define BTLrm(RS,MD,MB,MI,MS) _OO_r_X (0x0fa3 ,_r4(RS) ,MD,MB,MI,MS ) #define BTCWir(IM,RD) _wOO_Mrm_B (0x0fba ,_b11,_b111 ,_r2(RD) ,_u8(IM)) #define BTCWim(IM,MD,MB,MI,MS) _wOO_r_X_B (0x0fba ,_b111 ,MD,MB,MI,MS ,_u8(IM)) #define BTCWrr(RS,RD) _wOO_Mrm (0x0fbb ,_b11,_r2(RS),_r2(RD) ) #define BTCWrm(RS,MD,MB,MI,MS) _wOO_r_X (0x0fbb ,_r2(RS) ,MD,MB,MI,MS ) #define BTCLir(IM,RD) _OO_Mrm_B (0x0fba ,_b11,_b111 ,_r4(RD) ,_u8(IM)) #define BTCLim(IM,MD,MB,MI,MS) _OO_r_X_B (0x0fba ,_b111 ,MD,MB,MI,MS ,_u8(IM)) #define BTCLrr(RS,RD) _OO_Mrm (0x0fbb ,_b11,_r4(RS),_r4(RD) ) #define BTCLrm(RS,MD,MB,MI,MS) _OO_r_X (0x0fbb ,_r4(RS) ,MD,MB,MI,MS ) #define BTRWir(IM,RD) _wOO_Mrm_B (0x0fba ,_b11,_b110 ,_r2(RD) ,_u8(IM)) #define BTRWim(IM,MD,MB,MI,MS) _wOO_r_X_B (0x0fba ,_b110 ,MD,MB,MI,MS ,_u8(IM)) #define BTRWrr(RS,RD) _wOO_Mrm (0x0fb3 ,_b11,_r2(RS),_r2(RD) ) #define BTRWrm(RS,MD,MB,MI,MS) _wOO_r_X (0x0fb3 ,_r2(RS) ,MD,MB,MI,MS ) #define BTRLir(IM,RD) _OO_Mrm_B (0x0fba ,_b11,_b110 ,_r4(RD) ,_u8(IM)) #define BTRLim(IM,MD,MB,MI,MS) _OO_r_X_B (0x0fba ,_b110 ,MD,MB,MI,MS ,_u8(IM)) #define BTRLrr(RS,RD) _OO_Mrm (0x0fb3 ,_b11,_r4(RS),_r4(RD) ) #define BTRLrm(RS,MD,MB,MI,MS) _OO_r_X (0x0fb3 ,_r4(RS) ,MD,MB,MI,MS ) #define BTSWir(IM,RD) _wOO_Mrm_B (0x0fba ,_b11,_b101 ,_r2(RD) ,_u8(IM)) #define BTSWim(IM,MD,MB,MI,MS) _wOO_r_X_B (0x0fba ,_b101 ,MD,MB,MI,MS ,_u8(IM)) #define BTSWrr(RS,RD) _wOO_Mrm (0x0fab ,_b11,_r2(RS),_r2(RD) ) #define BTSWrm(RS,MD,MB,MI,MS) _wOO_r_X (0x0fab ,_r2(RS) ,MD,MB,MI,MS ) #define BTSLir(IM,RD) _OO_Mrm_B (0x0fba ,_b11,_b101 ,_r4(RD) ,_u8(IM)) #define BTSLim(IM,MD,MB,MI,MS) _OO_r_X_B (0x0fba ,_b101 ,MD,MB,MI,MS ,_u8(IM)) #define BTSLrr(RS,RD) _OO_Mrm (0x0fab ,_b11,_r4(RS),_r4(RD) ) #define BTSLrm(RS,MD,MB,MI,MS) _OO_r_X (0x0fab ,_r4(RS) ,MD,MB,MI,MS ) #define CALLsr(R) _O_Mrm (0xff ,_b11,_b010,_r4(R) ) #define CALLsm(D,B,I,S) _O_r_X (0xff ,_b010 ,(int)(D),B,I,S ) #define CBW_() _O (0x98 ) #define CLC_() _O (0xf8 ) #define CLTD_() _O (0x99 ) #define CMC_() _O (0xf5 ) #define CMPBrr(RS, RD) _O_Mrm (0x38 ,_b11,_r1(RS),_r1(RD) ) #define CMPBmr(MD, MB, MI, MS, RD) _O_r_X (0x3a ,_r1(RD) ,MD,MB,MI,MS ) #define CMPBrm(RS, MD, MB, MI, MS) _O_r_X (0x38 ,_r1(RS) ,MD,MB,MI,MS ) #define CMPBir(IM, RD) _O_Mrm_B (0x80 ,_b11,_b111 ,_r1(RD) ,_su8(IM)) #define CMPBim(IM, MD, MB, MI, MS) _O_r_X_B (0x80 ,_b111 ,MD,MB,MI,MS ,_su8(IM)) #define CMPWrr(RS, RD) _wO_Mrm (0x39 ,_b11,_r2(RS),_r2(RD) ) #define CMPWmr(MD, MB, MI, MS, RD) _wO_r_X (0x3b ,_r2(RD) ,MD,MB,MI,MS ) #define CMPWrm(RS, MD, MB, MI, MS) _wO_r_X (0x39 ,_r2(RS) ,MD,MB,MI,MS ) #define CMPWir(IM, RD) _wOs_Mrm_sW (0x81 ,_b11,_b111 ,_r2(RD) ,_su16(IM)) #define CMPWim(IM, MD, MB, MI, MS) _wOs_r_X_sW (0x81 ,_b111 ,MD,MB,MI,MS ,_su16(IM)) #define CMPLrr(RS, RD) _O_Mrm (0x39 ,_b11,_r4(RS),_r4(RD) ) #define CMPLmr(MD, MB, MI, MS, RD) _O_r_X (0x3b ,_r4(RD) ,MD,MB,MI,MS ) #define CMPLrm(RS, MD, MB, MI, MS) _O_r_X (0x39 ,_r4(RS) ,MD,MB,MI,MS ) #define CMPLir(IM, RD) _O_Mrm_L (0x81 ,_b11,_b111 ,_r4(RD) ,IM ) #define CMPLim(IM, MD, MB, MI, MS) _O_r_X_L (0x81 ,_b111 ,MD,MB,MI,MS ,IM ) #define CWD_() _O (0x99 ) #define CMPXCHGBrr(RS,RD) _OO_Mrm (0x0fb0 ,_b11,_r1(RS),_r1(RD) ) #define CMPXCHGBrm(RS,MD,MB,MI,MS) _OO_r_X (0x0fb0 ,_r1(RS) ,MD,MB,MI,MS ) #define CMPXCHGWrr(RS,RD) _wOO_Mrm (0x0fb1 ,_b11,_r2(RS),_r2(RD) ) #define CMPXCHGWrm(RS,MD,MB,MI,MS) _wOO_r_X (0x0fb1 ,_r2(RS) ,MD,MB,MI,MS ) #define CMPXCHGLrr(RS,RD) _OO_Mrm (0x0fb1 ,_b11,_r4(RS),_r4(RD) ) #define CMPXCHGLrm(RS,MD,MB,MI,MS) _OO_r_X (0x0fb1 ,_r4(RS) ,MD,MB,MI,MS ) #define DECBr(RD) _O_Mrm (0xfe ,_b11,_b001 ,_r1(RD) ) #define DECBm(MD,MB,MI,MS) _O_r_X (0xfe ,_b001 ,MD,MB,MI,MS ) #define DECWr(RD) _wOr (0x48,_r2(RD) ) #define DECWm(MD,MB,MI,MS) _wO_r_X (0xff ,_b001 ,MD,MB,MI,MS ) #define DECLr(RD) _Or (0x48,_r4(RD) ) #define DECLm(MD,MB,MI,MS) _O_r_X (0xff ,_b001 ,MD,MB,MI,MS ) #define DIVBr(RS) _O_Mrm (0xf6 ,_b11,_b110 ,_r1(RS) ) #define DIVBm(MD,MB,MI,MS) _O_r_X (0xf6 ,_b110 ,MD,MB,MI,MS ) #define DIVWr(RS) _wO_Mrm (0xf7 ,_b11,_b110 ,_r2(RS) ) #define DIVWm(MD,MB,MI,MS) _wO_r_X (0xf7 ,_b110 ,MD,MB,MI,MS ) #define DIVLr(RS) _O_Mrm (0xf7 ,_b11,_b110 ,_r4(RS) ) #define DIVLm(MD,MB,MI,MS) _O_r_X (0xf7 ,_b110 ,MD,MB,MI,MS ) #define ENTERii(W, B) _O_W_B (0xc8 ,_su16(W),_su8(B)) #define HLT_() _O (0xf4 ) #define IDIVBr(RS) _O_Mrm (0xf6 ,_b11,_b111 ,_r1(RS) ) #define IDIVBm(MD,MB,MI,MS) _O_r_X (0xf6 ,_b111 ,MD,MB,MI,MS ) #define IDIVWr(RS) _wO_Mrm (0xf7 ,_b11,_b111 ,_r2(RS) ) #define IDIVWm(MD,MB,MI,MS) _wO_r_X (0xf7 ,_b111 ,MD,MB,MI,MS ) #define IDIVLr(RS) _O_Mrm (0xf7 ,_b11,_b111 ,_r4(RS) ) #define IDIVLm(MD,MB,MI,MS) _O_r_X (0xf7 ,_b111 ,MD,MB,MI,MS ) #define IMULBr(RS) _O_Mrm (0xf6 ,_b11,_b101 ,_r1(RS) ) #define IMULBm(MD,MB,MI,MS) _O_r_X (0xf6 ,_b101 ,MD,MB,MI,MS ) #define IMULWr(RS) _wO_Mrm (0xf7 ,_b11,_b101 ,_r2(RS) ) #define IMULWm(MD,MB,MI,MS) _wO_r_X (0xf7 ,_b101 ,MD,MB,MI,MS ) #define IMULLr(RS) _O_Mrm (0xf7 ,_b11,_b101 ,_r4(RS) ) #define IMULLm(MD,MB,MI,MS) _O_r_X (0xf7 ,_b101 ,MD,MB,MI,MS ) #define IMULWrr(RS,RD) _wOO_Mrm (0x0faf ,_b11,_r2(RS),_r2(RD) ) #define IMULWmr(MD,MB,MI,MS,RD) _wOO_r_X (0x0faf ,_r2(RD) ,MD,MB,MI,MS ) #define IMULWirr(IM,RS,RD) _wOs_Mrm_sW (0x69 ,_b11,_r2(RS),_r2(RD) ,_su16(IM) ) #define IMULWimr(IM,MD,MB,MI,MS,RD) _wOs_r_X_sW (0x69 ,_r2(RD) ,MD,MB,MI,MS ,_su16(IM) ) #define IMULLir(IM,RD) _Os_Mrm_sL (0x69 ,_b11,_r4(RD),_r4(RD) ,IM ) #define IMULLrr(RS,RD) _OO_Mrm (0x0faf ,_b11,_r4(RD),_r4(RS) ) #define IMULLmr(MD,MB,MI,MS,RD) _OO_r_X (0x0faf ,_r4(RD) ,MD,MB,MI,MS ) #define IMULLirr(IM,RS,RD) _Os_Mrm_sL (0x69 ,_b11,_r4(RS),_r4(RD) ,IM ) #define IMULLimr(IM,MD,MB,MI,MS,RD) _Os_r_X_sL (0x69 ,_r4(RD) ,MD,MB,MI,MS ,IM ) #define INCBr(RD) _O_Mrm (0xfe ,_b11,_b000 ,_r1(RD) ) #define INCBm(MD,MB,MI,MS) _O_r_X (0xfe ,_b000 ,MD,MB,MI,MS ) #define INCWr(RD) _wOr (0x40,_r2(RD) ) #define INCWm(MD,MB,MI,MS) _wO_r_X (0xff ,_b000 ,MD,MB,MI,MS ) #define INCLr(RD) _Or (0x40,_r4(RD) ) #define INCLm(MD,MB,MI,MS) _O_r_X (0xff ,_b000 ,MD,MB,MI,MS ) #define INVD_() _OO (0x0f08 ) #define INVLPGm(MD, MB, MI, MS) _OO_r_X (0x0f01 ,_b111 ,MD,MB,MI,MS ) #define JCCSim(CC,D,B,I,S) ((_r0P(B) && _r0P(I)) ? _O_D8 (0x70|(CC) ,(int)(D) ) : \ JITFAIL("illegal mode in conditional jump")) #define JOSm(D,B,I,S) JCCSim(0x0,D,B,I,S) #define JNOSm(D,B,I,S) JCCSim(0x1,D,B,I,S) #define JCSm(D,B,I,S) JCCSim(0x2,D,B,I,S) #define JBSm(D,B,I,S) JCCSim(0x2,D,B,I,S) #define JNAESm(D,B,I,S) JCCSim(0x2,D,B,I,S) #define JNCSm(D,B,I,S) JCCSim(0x3,D,B,I,S) #define JNBSm(D,B,I,S) JCCSim(0x3,D,B,I,S) #define JAESm(D,B,I,S) JCCSim(0x3,D,B,I,S) #define JESm(D,B,I,S) JCCSim(0x4,D,B,I,S) #define JZSm(D,B,I,S) JCCSim(0x4,D,B,I,S) #define JNESm(D,B,I,S) JCCSim(0x5,D,B,I,S) #define JNZSm(D,B,I,S) JCCSim(0x5,D,B,I,S) #define JBESm(D,B,I,S) JCCSim(0x6,D,B,I,S) #define JNASm(D,B,I,S) JCCSim(0x6,D,B,I,S) #define JNBESm(D,B,I,S) JCCSim(0x7,D,B,I,S) #define JASm(D,B,I,S) JCCSim(0x7,D,B,I,S) #define JSSm(D,B,I,S) JCCSim(0x8,D,B,I,S) #define JNSSm(D,B,I,S) JCCSim(0x9,D,B,I,S) #define JPSm(D,B,I,S) JCCSim(0xa,D,B,I,S) #define JPESm(D,B,I,S) JCCSim(0xa,D,B,I,S) #define JNPSm(D,B,I,S) JCCSim(0xb,D,B,I,S) #define JPOSm(D,B,I,S) JCCSim(0xb,D,B,I,S) #define JLSm(D,B,I,S) JCCSim(0xc,D,B,I,S) #define JNGESm(D,B,I,S) JCCSim(0xc,D,B,I,S) #define JNLSm(D,B,I,S) JCCSim(0xd,D,B,I,S) #define JGESm(D,B,I,S) JCCSim(0xd,D,B,I,S) #define JLESm(D,B,I,S) JCCSim(0xe,D,B,I,S) #define JNGSm(D,B,I,S) JCCSim(0xe,D,B,I,S) #define JNLESm(D,B,I,S) JCCSim(0xf,D,B,I,S) #define JGSm(D,B,I,S) JCCSim(0xf,D,B,I,S) #define JOm(D,B,I,S) JCCim(0x0,D,B,I,S) #define JNOm(D,B,I,S) JCCim(0x1,D,B,I,S) #define JCm(D,B,I,S) JCCim(0x2,D,B,I,S) #define JBm(D,B,I,S) JCCim(0x2,D,B,I,S) #define JNAEm(D,B,I,S) JCCim(0x2,D,B,I,S) #define JNCm(D,B,I,S) JCCim(0x3,D,B,I,S) #define JNBm(D,B,I,S) JCCim(0x3,D,B,I,S) #define JAEm(D,B,I,S) JCCim(0x3,D,B,I,S) #define JEm(D,B,I,S) JCCim(0x4,D,B,I,S) #define JZm(D,B,I,S) JCCim(0x4,D,B,I,S) #define JNEm(D,B,I,S) JCCim(0x5,D,B,I,S) #define JNZm(D,B,I,S) JCCim(0x5,D,B,I,S) #define JBEm(D,B,I,S) JCCim(0x6,D,B,I,S) #define JNAm(D,B,I,S) JCCim(0x6,D,B,I,S) #define JNBEm(D,B,I,S) JCCim(0x7,D,B,I,S) #define JAm(D,B,I,S) JCCim(0x7,D,B,I,S) #define JSm(D,B,I,S) JCCim(0x8,D,B,I,S) #define JNSm(D,B,I,S) JCCim(0x9,D,B,I,S) #define JPm(D,B,I,S) JCCim(0xa,D,B,I,S) #define JPEm(D,B,I,S) JCCim(0xa,D,B,I,S) #define JNPm(D,B,I,S) JCCim(0xb,D,B,I,S) #define JPOm(D,B,I,S) JCCim(0xb,D,B,I,S) #define JLm(D,B,I,S) JCCim(0xc,D,B,I,S) #define JNGEm(D,B,I,S) JCCim(0xc,D,B,I,S) #define JNLm(D,B,I,S) JCCim(0xd,D,B,I,S) #define JGEm(D,B,I,S) JCCim(0xd,D,B,I,S) #define JLEm(D,B,I,S) JCCim(0xe,D,B,I,S) #define JNGm(D,B,I,S) JCCim(0xe,D,B,I,S) #define JNLEm(D,B,I,S) JCCim(0xf,D,B,I,S) #define JGm(D,B,I,S) JCCim(0xf,D,B,I,S) #define JMPSm(D,B,I,S) ((_r0P(B) && _r0P(I)) ? _O_D8 (0xeb ,(int)(D) ) : \ JITFAIL("illegal mode in short jump")) #define JMPsr(R) _O_Mrm (0xff ,_b11,_b100,_r4(R) ) #define JMPsm(D,B,I,S) _O_r_X (0xff ,_b100 ,(int)(D),B,I,S ) #define LAHF_() _O (0x9f ) #define LEALmr(MD, MB, MI, MS, RD) _O_r_X (0x8d ,_r4(RD) ,MD,MB,MI,MS ) #define LEAVE_() _O (0xc9 ) #define LMSWr(RS) _OO_Mrm (0x0f01 ,_b11,_b110,_r4(RS) ) #define LMSWm(MD,MB,MI,MS) _OO_r_X (0x0f01 ,_b110 ,MD,MB,MI,MS ) #define LOOPm(MD,MB,MI,MS) ((_r0P(MB) && _r0P(MI)) ? _O_D8 (0xe2 ,MD ) : \ JITFAIL("illegal mode in loop")) #define LOOPEm(MD,MB,MI,MS) ((_r0P(MB) && _r0P(MI)) ? _O_D8 (0xe1 ,MD ) : \ JITFAIL("illegal mode in loope")) #define LOOPZm(MD,MB,MI,MS) ((_r0P(MB) && _r0P(MI)) ? _O_D8 (0xe1 ,MD ) : \ JITFAIL("illegal mode in loopz")) #define LOOPNEm(MD,MB,MI,MS) ((_r0P(MB) && _r0P(MI)) ? _O_D8 (0xe0 ,MD ) : \ JITFAIL("illegal mode in loopne")) #define LOOPNZm(MD,MB,MI,MS) ((_r0P(MB) && _r0P(MI)) ? _O_D8 (0xe0 ,MD ) : \ JITFAIL("illegal mode in loopnz")) #define MOVBrr(RS, RD) _O_Mrm (0x80 ,_b11,_r1(RS),_r1(RD) ) #define MOVBmr(MD, MB, MI, MS, RD) _O_r_X (0x8a ,_r1(RD) ,MD,MB,MI,MS ) #define MOVBrm(RS, MD, MB, MI, MS) _O_r_X (0x88 ,_r1(RS) ,MD,MB,MI,MS ) #define MOVBir(IM, R) _Or_B (0xb0,_r1(R) ,_su8(IM)) #define MOVBim(IM, MD, MB, MI, MS) _O_X_B (0xc6 ,MD,MB,MI,MS ,_su8(IM)) #define MOVWrr(RS, RD) _wO_Mrm (0x89 ,_b11,_r2(RS),_r2(RD) ) #define MOVWmr(MD, MB, MI, MS, RD) _wO_r_X (0x8b ,_r2(RD) ,MD,MB,MI,MS ) #define MOVWrm(RS, MD, MB, MI, MS) _wO_r_X (0x89 ,_r2(RS) ,MD,MB,MI,MS ) #define MOVWir(IM, R) _wOr_W (0xb8,_r2(R) ,_su16(IM)) #define MOVWim(IM, MD, MB, MI, MS) _wO_X_W (0xc7 ,MD,MB,MI,MS ,_su16(IM)) #define MOVLrr(RS, RD) _O_Mrm (0x89 ,_b11,_r4(RS),_r4(RD) ) #define MOVLmr(MD, MB, MI, MS, RD) _O_r_X (0x8b ,_r4(RD) ,MD,MB,MI,MS ) #define MOVLrm(RS, MD, MB, MI, MS) _O_r_X (0x89 ,_r4(RS) ,MD,MB,MI,MS ) #define MOVLir(IM, R) _Or_L (0xb8,_r4(R) ,IM ) #define MOVLim(IM, MD, MB, MI, MS) _O_X_L (0xc7 ,MD,MB,MI,MS ,IM ) #define MOVZBLrr(RS, RD) _OO_Mrm (0x0fb6 ,_b11,_r1(RD),_r1(RS) ) #define MOVZBLmr(MD, MB, MI, MS, RD) _OO_r_X (0x0fb6 ,_r1(RD) ,MD,MB,MI,MS ) #define MOVZBWrr(RS, RD) _wOO_Mrm (0x0fb6 ,_b11,_r2(RD),_r2(RS) ) #define MOVZBWmr(MD, MB, MI, MS, RD) _wOO_r_X (0x0fb6 ,_r2(RD) ,MD,MB,MI,MS ) #define MOVZWLrr(RS, RD) _OO_Mrm (0x0fb7 ,_b11,_r1(RD),_r1(RS) ) #define MOVZWLmr(MD, MB, MI, MS, RD) _OO_r_X (0x0fb7 ,_r1(RD) ,MD,MB,MI,MS ) #define MOVSBLrr(RS, RD) _OO_Mrm (0x0fbe ,_b11,_r1(RD),_r1(RS) ) #define MOVSBLmr(MD, MB, MI, MS, RD) _OO_r_X (0x0fbe ,_r1(RD) ,MD,MB,MI,MS ) #define MOVSBWrr(RS, RD) _wOO_Mrm (0x0fbe ,_b11,_r2(RD),_r2(RS) ) #define MOVSBWmr(MD, MB, MI, MS, RD) _wOO_r_X (0x0fbe ,_r2(RD) ,MD,MB,MI,MS ) #define MOVSWLrr(RS, RD) _OO_Mrm (0x0fbf ,_b11,_r1(RD),_r1(RS) ) #define MOVSWLmr(MD, MB, MI, MS, RD) _OO_r_X (0x0fbf ,_r1(RD) ,MD,MB,MI,MS ) #define MULBr(RS) _O_Mrm (0xf6 ,_b11,_b100 ,_r1(RS) ) #define MULBm(MD,MB,MI,MS) _O_r_X (0xf6 ,_b100 ,MD,MB,MI,MS ) #define MULWr(RS) _wO_Mrm (0xf7 ,_b11,_b100 ,_r2(RS) ) #define MULWm(MD,MB,MI,MS) _wO_r_X (0xf7 ,_b100 ,MD,MB,MI,MS ) #define MULLr(RS) _O_Mrm (0xf7 ,_b11,_b100 ,_r4(RS) ) #define MULLm(MD,MB,MI,MS) _O_r_X (0xf7 ,_b100 ,MD,MB,MI,MS ) #define NEGBr(RD) _O_Mrm (0xf6 ,_b11,_b011 ,_r1(RD) ) #define NEGBm(MD,MB,MI,MS) _O_r_X (0xf6 ,_b011 ,MD,MB,MI,MS ) #define NEGWr(RD) _wO_Mrm (0xf7 ,_b11,_b011 ,_r2(RD) ) #define NEGWm(MD,MB,MI,MS) _wO_r_X (0xf7 ,_b011 ,MD,MB,MI,MS ) #define NEGLr(RD) _O_Mrm (0xf7 ,_b11,_b011 ,_r4(RD) ) #define NEGLm(MD,MB,MI,MS) _O_r_X (0xf7 ,_b011 ,MD,MB,MI,MS ) #define NOP_() _O (0x90 ) #define NOTBr(RD) _O_Mrm (0xf6 ,_b11,_b010 ,_r1(RD) ) #define NOTBm(MD,MB,MI,MS) _O_r_X (0xf6 ,_b010 ,MD,MB,MI,MS ) #define NOTWr(RD) _wO_Mrm (0xf7 ,_b11,_b010 ,_r2(RD) ) #define NOTWm(MD,MB,MI,MS) _wO_r_X (0xf7 ,_b010 ,MD,MB,MI,MS ) #define NOTLr(RD) _O_Mrm (0xf7 ,_b11,_b010 ,_r4(RD) ) #define NOTLm(MD,MB,MI,MS) _O_r_X (0xf7 ,_b010 ,MD,MB,MI,MS ) #define ORBrr(RS, RD) _O_Mrm (0x08 ,_b11,_r1(RS),_r1(RD) ) #define ORBmr(MD, MB, MI, MS, RD) _O_r_X (0x0a ,_r1(RD) ,MD,MB,MI,MS ) #define ORBrm(RS, MD, MB, MI, MS) _O_r_X (0x08 ,_r1(RS) ,MD,MB,MI,MS ) #define ORBir(IM, RD) _O_Mrm_B (0x80 ,_b11,_b001 ,_r1(RD) ,_su8(IM)) #define ORBim(IM, MD, MB, MI, MS) _O_r_X_B (0x80 ,_b001 ,MD,MB,MI,MS ,_su8(IM)) #define ORWrr(RS, RD) _wO_Mrm (0x09 ,_b11,_r2(RS),_r2(RD) ) #define ORWmr(MD, MB, MI, MS, RD) _wO_r_X (0x0b ,_r2(RD) ,MD,MB,MI,MS ) #define ORWrm(RS, MD, MB, MI, MS) _wO_r_X (0x09 ,_r2(RS) ,MD,MB,MI,MS ) #define ORWir(IM, RD) _wOs_Mrm_sW (0x81 ,_b11,_b001 ,_r2(RD) ,_su16(IM)) #define ORWim(IM, MD, MB, MI, MS) _wOs_r_X_sW (0x81 ,_b001 ,MD,MB,MI,MS ,_su16(IM)) #define ORLrr(RS, RD) _O_Mrm (0x09 ,_b11,_r4(RS),_r4(RD) ) #define ORLmr(MD, MB, MI, MS, RD) _O_r_X (0x0b ,_r4(RD) ,MD,MB,MI,MS ) #define ORLrm(RS, MD, MB, MI, MS) _O_r_X (0x09 ,_r4(RS) ,MD,MB,MI,MS ) #define ORLir(IM, RD) _Os_Mrm_sL (0x81 ,_b11,_b001 ,_r4(RD) ,IM ) #define ORLim(IM, MD, MB, MI, MS) _Os_r_X_sL (0x81 ,_b001 ,MD,MB,MI,MS ,IM ) #define POPWr(RD) _wOr (0x58,_r2(RD) ) #define POPWm(MD,MB,MI,MS) _wO_r_X (0x8f ,_b000 ,MD,MB,MI,MS ) #define POPLr(RD) _Or (0x58,_r4(RD) ) #define POPLm(MD,MB,MI,MS) _O_r_X (0x8f ,_b000 ,MD,MB,MI,MS ) #define POPA_() _wO (0x61 ) #define POPAD_() _O (0x61 ) #define POPF_() _wO (0x9d ) #define POPFD_() _O (0x9d ) #define PUSHWr(R) _wOr (0x50,_r2(R) ) #define PUSHWm(MD,MB,MI,MS) _wO_r_X (0xff, ,_b110 ,MD,MB,MI,MS ) #define PUSHWi(IM) _wOs_sW (0x68 ,IM ) #define PUSHLr(R) _Or (0x50,_r4(R) ) #define PUSHLm(MD,MB,MI,MS) _O_r_X (0xff ,_b110 ,MD,MB,MI,MS ) #define PUSHLi(IM) _Os_sL (0x68 ,IM ) #define PUSHA_() _wO (0x60 ) #define PUSHAD_() _O (0x60 ) #define PUSHF_() _O (0x9c ) #define PUSHFD_() _wO (0x9c ) #define RET_() _O (0xc3 ) #define RETi(IM) _O_W (0xc2 ,_su16(IM)) #define ROLBir(IM,RD) (((IM)==1) ? _O_Mrm (0xd0 ,_b11,_b000,_r1(RD) ) : \ _O_Mrm_B (0xc0 ,_b11,_b000,_r1(RD) ,_u8(IM) ) ) #define ROLBim(IM,MD,MB,MS,MI) (((IM)==1) ? _O_r_X (0xd0 ,_b000 ,MD,MB,MI,MS ) : \ _O_r_X_B (0xc0 ,_b000 ,MD,MB,MI,MS ,_u8(IM) ) ) #define ROLBrr(RS,RD) (((RS)==_CL) ? _O_Mrm (0xd2 ,_b11,_b000,_r1(RD) ) : \ JITFAIL ("source register must be CL" ) ) #define ROLBrm(RS,MD,MB,MS,MI) (((RS)==_CL) ? _O_r_X (0xd2 ,_b000 ,MD,MB,MI,MS ) : \ JITFAIL ("source register must be CL" ) ) #define ROLWir(IM,RD) (((IM)==1) ? _wO_Mrm (0xd1 ,_b11,_b000,_r2(RD) ) : \ _wO_Mrm_B (0xc1 ,_b11,_b000,_r2(RD) ,_u8(IM) ) ) #define ROLWim(IM,MD,MB,MS,MI) (((IM)==1) ? _wO_r_X (0xd1 ,_b000 ,MD,MB,MI,MS ) : \ _wO_r_X_B (0xc1 ,_b000 ,MD,MB,MI,MS ,_u8(IM) ) ) #define ROLWrr(RS,RD) (((RS)==_CL) ? _wO_Mrm (0xd3 ,_b11,_b000,_r2(RD) ) : \ JITFAIL ("source register must be CL" ) ) #define ROLWrm(RS,MD,MB,MS,MI) (((RS)==_CL) ? _wO_r_X (0xd3 ,_b000 ,MD,MB,MI,MS ) : \ JITFAIL ("source register must be CL" ) ) #define ROLLir(IM,RD) (((IM)==1) ? _O_Mrm (0xd1 ,_b11,_b000,_r4(RD) ) : \ _O_Mrm_B (0xc1 ,_b11,_b000,_r4(RD) ,_u8(IM) ) ) #define ROLLim(IM,MD,MB,MS,MI) (((IM)==1) ? _O_r_X (0xd1 ,_b000 ,MD,MB,MI,MS ) : \ _O_r_X_B (0xc1 ,_b000 ,MD,MB,MI,MS ,_u8(IM) ) ) #define ROLLrr(RS,RD) (((RS)==_CL) ? _O_Mrm (0xd3 ,_b11,_b000,_r4(RD) ) : \ JITFAIL ("source register must be CL" ) ) #define ROLLrm(RS,MD,MB,MS,MI) (((RS)==_CL) ? _O_r_X (0xd3 ,_b000 ,MD,MB,MI,MS ) : \ JITFAIL ("source register must be CL" ) ) #define RORBir(IM,RD) (((IM)==1) ? _O_Mrm (0xd0 ,_b11,_b001,_r1(RD) ) : \ _O_Mrm_B (0xc0 ,_b11,_b001,_r1(RD) ,_u8(IM) ) ) #define RORBim(IM,MD,MB,MS,MI) (((IM)==1) ? _O_r_X (0xd0 ,_b001 ,MD,MB,MI,MS ) : \ _O_r_X_B (0xc0 ,_b001 ,MD,MB,MI,MS ,_u8(IM) ) ) #define RORBrr(RS,RD) (((RS)==_CL) ? _O_Mrm (0xd2 ,_b11,_b001,_r1(RD) ) : \ JITFAIL ("source register must be CL" ) ) #define RORBrm(RS,MD,MB,MS,MI) (((RS)==_CL) ? _O_r_X (0xd2 ,_b001 ,MD,MB,MI,MS ) : \ JITFAIL ("source register must be CL" ) ) #define RORWir(IM,RD) (((IM)==1) ? _wO_Mrm (0xd1 ,_b11,_b001,_r2(RD) ) : \ _wO_Mrm_B (0xc1 ,_b11,_b001,_r2(RD) ,_u8(IM) ) ) #define RORWim(IM,MD,MB,MS,MI) (((IM)==1) ? _wO_r_X (0xd1 ,_b001 ,MD,MB,MI,MS ) : \ _wO_r_X_B (0xc1 ,_b001 ,MD,MB,MI,MS ,_u8(IM) ) ) #define RORWrr(RS,RD) (((RS)==_CL) ? _wO_Mrm (0xd3 ,_b11,_b001,_r2(RD) ) : \ JITFAIL ("source register must be CL" ) ) #define RORWrm(RS,MD,MB,MS,MI) (((RS)==_CL) ? _wO_r_X (0xd3 ,_b001 ,MD,MB,MI,MS ) : \ JITFAIL ("source register must be CL" ) ) #define RORLir(IM,RD) (((IM)==1) ? _O_Mrm (0xd1 ,_b11,_b001,_r4(RD) ) : \ _O_Mrm_B (0xc1 ,_b11,_b001,_r4(RD) ,_u8(IM) ) ) #define RORLim(IM,MD,MB,MS,MI) (((IM)==1) ? _O_r_X (0xd1 ,_b001 ,MD,MB,MI,MS ) : \ _O_r_X_B (0xc1 ,_b001 ,MD,MB,MI,MS ,_u8(IM) ) ) #define RORLrr(RS,RD) (((RS)==_CL) ? _O_Mrm (0xd3 ,_b11,_b001,_r4(RD) ) : \ JITFAIL ("source register must be CL" ) ) #define RORLrm(RS,MD,MB,MS,MI) (((RS)==_CL) ? _O_r_X (0xd3 ,_b001 ,MD,MB,MI,MS ) : \ JITFAIL ("source register must be CL" ) ) #define SAHF_() _O (0x9e ) #define SALBir SHLBir #define SALBim SHLBim #define SALBrr SHLBrr #define SALBrm SHLBrm #define SALWir SHLWir #define SALWim SHLWim #define SALWrr SHLWrr #define SALWrm SHLWrm #define SALLir SHLLir #define SALLim SHLLim #define SALLrr SHLLrr #define SALLrm SHLLrm #define SARBir(IM,RD) (((IM)==1) ? _O_Mrm (0xd0 ,_b11,_b111,_r1(RD) ) : \ _O_Mrm_B (0xc0 ,_b11,_b111,_r1(RD) ,_u8(IM) ) ) #define SARBim(IM,MD,MB,MS,MI) (((IM)==1) ? _O_r_X (0xd0 ,_b111 ,MD,MB,MI,MS ) : \ _O_r_X_B (0xc0 ,_b111 ,MD,MB,MI,MS ,_u8(IM) ) ) #define SARBrr(RS,RD) (((RS)==_CL) ? _O_Mrm (0xd2 ,_b11,_b111,_r1(RD) ) : \ JITFAIL ("source register must be CL" ) ) #define SARBrm(RS,MD,MB,MS,MI) (((RS)==_CL) ? _O_r_X (0xd2 ,_b111 ,MD,MB,MI,MS ) : \ JITFAIL ("source register must be CL" ) ) #define SARWir(IM,RD) (((IM)==1) ? _wO_Mrm (0xd1 ,_b11,_b111,_r2(RD) ) : \ _wO_Mrm_B (0xc1 ,_b11,_b111,_r2(RD) ,_u8(IM) ) ) #define SARWim(IM,MD,MB,MS,MI) (((IM)==1) ? _wO_r_X (0xd1 ,_b111 ,MD,MB,MI,MS ) : \ _wO_r_X_B (0xc1 ,_b111 ,MD,MB,MI,MS ,_u8(IM) ) ) #define SARWrr(RS,RD) (((RS)==_CL) ? _wO_Mrm (0xd3 ,_b11,_b111,_r2(RD) ) : \ JITFAIL ("source register must be CL" ) ) #define SARWrm(RS,MD,MB,MS,MI) (((RS)==_CL) ? _wO_r_X (0xd3 ,_b111 ,MD,MB,MI,MS ) : \ JITFAIL ("source register must be CL" ) ) #define SARLir(IM,RD) (((IM)==1) ? _O_Mrm (0xd1 ,_b11,_b111,_r4(RD) ) : \ _O_Mrm_B (0xc1 ,_b11,_b111,_r4(RD) ,_u8(IM) ) ) #define SARLim(IM,MD,MB,MS,MI) (((IM)==1) ? _O_r_X (0xd1 ,_b111 ,MD,MB,MI,MS ) : \ _O_r_X_B (0xc1 ,_b111 ,MD,MB,MI,MS ,_u8(IM) ) ) #define SARLrr(RS,RD) (((RS)==_CL) ? _O_Mrm (0xd3 ,_b11,_b111,_r4(RD) ) : \ JITFAIL ("source register must be CL" ) ) #define SARLrm(RS,MD,MB,MS,MI) (((RS)==_CL) ? _O_r_X (0xd3 ,_b111 ,MD,MB,MI,MS ) : \ JITFAIL ("source register must be CL" ) ) #define SBBBrr(RS, RD) _O_Mrm (0x18 ,_b11,_r1(RS),_r1(RD) ) #define SBBBmr(MD, MB, MI, MS, RD) _O_r_X (0x1a ,_r1(RD) ,MD,MB,MI,MS ) #define SBBBrm(RS, MD, MB, MI, MS) _O_r_X (0x18 ,_r1(RS) ,MD,MB,MI,MS ) #define SBBBir(IM, RD) _O_Mrm_B (0x80 ,_b11,_b011 ,_r1(RD) ,_su8(IM)) #define SBBBim(IM, MD, MB, MI, MS) _O_r_X_B (0x80 ,_b011 ,MD,MB,MI,MS ,_su8(IM)) #define SBBWrr(RS, RD) _wO_Mrm (0x19 ,_b11,_r2(RS),_r2(RD) ) #define SBBWmr(MD, MB, MI, MS, RD) _wO_r_X (0x1b ,_r2(RD) ,MD,MB,MI,MS ) #define SBBWrm(RS, MD, MB, MI, MS) _wO_r_X (0x19 ,_r2(RS) ,MD,MB,MI,MS ) #define SBBWir(IM, RD) _wOs_Mrm_sW (0x81 ,_b11,_b011 ,_r2(RD) ,_su16(IM)) #define SBBWim(IM, MD, MB, MI, MS) _wOs_r_X_sW (0x81 ,_b011 ,MD,MB,MI,MS ,_su16(IM)) #define SBBLrr(RS, RD) _O_Mrm (0x19 ,_b11,_r4(RS),_r4(RD) ) #define SBBLmr(MD, MB, MI, MS, RD) _O_r_X (0x1b ,_r4(RD) ,MD,MB,MI,MS ) #define SBBLrm(RS, MD, MB, MI, MS) _O_r_X (0x19 ,_r4(RS) ,MD,MB,MI,MS ) #define SBBLir(IM, RD) _Os_Mrm_sL (0x81 ,_b11,_b011 ,_r4(RD) ,IM ) #define SBBLim(IM, MD, MB, MI, MS) _Os_r_X_sL (0x81 ,_b011 ,MD,MB,MI,MS ,IM ) #define SETCCir(CC,RD) _OO_Mrm (0x0f90|(CC) ,_b11,_b000,_r1(RD) ) #define SETOr(RD) SETCCir(0x0,RD) #define SETNOr(RD) SETCCir(0x1,RD) #define SETBr(RD) SETCCir(0x2,RD) #define SETNAEr(RD) SETCCir(0x2,RD) #define SETNBr(RD) SETCCir(0x3,RD) #define SETAEr(RD) SETCCir(0x3,RD) #define SETEr(RD) SETCCir(0x4,RD) #define SETZr(RD) SETCCir(0x4,RD) #define SETNEr(RD) SETCCir(0x5,RD) #define SETNZr(RD) SETCCir(0x5,RD) #define SETBEr(RD) SETCCir(0x6,RD) #define SETNAr(RD) SETCCir(0x6,RD) #define SETNBEr(RD) SETCCir(0x7,RD) #define SETAr(RD) SETCCir(0x7,RD) #define SETSr(RD) SETCCir(0x8,RD) #define SETNSr(RD) SETCCir(0x9,RD) #define SETPr(RD) SETCCir(0xa,RD) #define SETPEr(RD) SETCCir(0xa,RD) #define SETNPr(RD) SETCCir(0xb,RD) #define SETPOr(RD) SETCCir(0xb,RD) #define SETLr(RD) SETCCir(0xc,RD) #define SETNGEr(RD) SETCCir(0xc,RD) #define SETNLr(RD) SETCCir(0xd,RD) #define SETGEr(RD) SETCCir(0xd,RD) #define SETLEr(RD) SETCCir(0xe,RD) #define SETNGr(RD) SETCCir(0xe,RD) #define SETNLEr(RD) SETCCir(0xf,RD) #define SETGr(RD) SETCCir(0xf,RD) #define SETCCim(CC,MD,MB,MI,MS) _OO_r_X (0x0f90|(CC) ,_b000 ,MD,MB,MI,MS ) #define SETOm(D,B,I,S) SETCCim(0x0,D,B,I,S) #define SETNOm(D,B,I,S) SETCCim(0x1,D,B,I,S) #define SETBm(D,B,I,S) SETCCim(0x2,D,B,I,S) #define SETNAEm(D,B,I,S) SETCCim(0x2,D,B,I,S) #define SETNBm(D,B,I,S) SETCCim(0x3,D,B,I,S) #define SETAEm(D,B,I,S) SETCCim(0x3,D,B,I,S) #define SETEm(D,B,I,S) SETCCim(0x4,D,B,I,S) #define SETZm(D,B,I,S) SETCCim(0x4,D,B,I,S) #define SETNEm(D,B,I,S) SETCCim(0x5,D,B,I,S) #define SETNZm(D,B,I,S) SETCCim(0x5,D,B,I,S) #define SETBEm(D,B,I,S) SETCCim(0x6,D,B,I,S) #define SETNAm(D,B,I,S) SETCCim(0x6,D,B,I,S) #define SETNBEm(D,B,I,S) SETCCim(0x7,D,B,I,S) #define SETAm(D,B,I,S) SETCCim(0x7,D,B,I,S) #define SETSm(D,B,I,S) SETCCim(0x8,D,B,I,S) #define SETNSm(D,B,I,S) SETCCim(0x9,D,B,I,S) #define SETPm(D,B,I,S) SETCCim(0xa,D,B,I,S) #define SETPEm(D,B,I,S) SETCCim(0xa,D,B,I,S) #define SETNPm(D,B,I,S) SETCCim(0xb,D,B,I,S) #define SETPOm(D,B,I,S) SETCCim(0xb,D,B,I,S) #define SETLm(D,B,I,S) SETCCim(0xc,D,B,I,S) #define SETNGEm(D,B,I,S) SETCCim(0xc,D,B,I,S) #define SETNLm(D,B,I,S) SETCCim(0xd,D,B,I,S) #define SETGEm(D,B,I,S) SETCCim(0xd,D,B,I,S) #define SETLEm(D,B,I,S) SETCCim(0xe,D,B,I,S) #define SETNGm(D,B,I,S) SETCCim(0xe,D,B,I,S) #define SETNLEm(D,B,I,S) SETCCim(0xf,D,B,I,S) #define SETGm(D,B,I,S) SETCCim(0xf,D,B,I,S) #define SHLBir(IM,RD) (((IM)==1) ? _O_Mrm (0xd0 ,_b11,_b100,_r1(RD) ) : \ _O_Mrm_B (0xc0 ,_b11,_b100,_r1(RD) ,_u8(IM) ) ) #define SHLBim(IM,MD,MB,MS,MI) (((IM)==1) ? _O_r_X (0xd0 ,_b100 ,MD,MB,MI,MS ) : \ _O_r_X_B (0xc0 ,_b100 ,MD,MB,MI,MS ,_u8(IM) ) ) #define SHLBrr(RS,RD) (((RS)==_CL) ? _O_Mrm (0xd2 ,_b11,_b100,_r1(RD) ) : \ JITFAIL ("source register must be CL" ) ) #define SHLBrm(RS,MD,MB,MS,MI) (((RS)==_CL) ? _O_r_X (0xd2 ,_b100 ,MD,MB,MI,MS ) : \ JITFAIL ("source register must be CL" ) ) #define SHLWir(IM,RD) (((IM)==1) ? _wO_Mrm (0xd1 ,_b11,_b100,_r2(RD) ) : \ _wO_Mrm_B (0xc1 ,_b11,_b100,_r2(RD) ,_u8(IM) ) ) #define SHLWim(IM,MD,MB,MS,MI) (((IM)==1) ? _wO_r_X (0xd1 ,_b100 ,MD,MB,MI,MS ) : \ _wO_r_X_B (0xc1 ,_b100 ,MD,MB,MI,MS ,_u8(IM) ) ) #define SHLWrr(RS,RD) (((RS)==_CL) ? _wO_Mrm (0xd3 ,_b11,_b100,_r2(RD) ) : \ JITFAIL ("source register must be CL" ) ) #define SHLWrm(RS,MD,MB,MS,MI) (((RS)==_CL) ? _wO_r_X (0xd3 ,_b100 ,MD,MB,MI,MS ) : \ JITFAIL ("source register must be CL" ) ) #define SHLLir(IM,RD) (((IM)==1) ? _O_Mrm (0xd1 ,_b11,_b100,_r4(RD) ) : \ _O_Mrm_B (0xc1 ,_b11,_b100,_r4(RD) ,_u8(IM) ) ) #define SHLLim(IM,MD,MB,MS,MI) (((IM)==1) ? _O_r_X (0xd1 ,_b100 ,MD,MB,MI,MS ) : \ _O_r_X_B (0xc1 ,_b100 ,MD,MB,MI,MS ,_u8(IM) ) ) #define SHLLrr(RS,RD) (((RS)==_CL) ? _O_Mrm (0xd3 ,_b11,_b100,_r4(RD) ) : \ JITFAIL ("source register must be CL" ) ) #define SHLLrm(RS,MD,MB,MS,MI) (((RS)==_CL) ? _O_r_X (0xd3 ,_b100 ,MD,MB,MI,MS ) : \ JITFAIL ("source register must be CL" ) ) #define SHRBir(IM,RD) (((IM)==1) ? _O_Mrm (0xd0 ,_b11,_b101,_r1(RD) ) : \ _O_Mrm_B (0xc0 ,_b11,_b101,_r1(RD) ,_u8(IM) ) ) #define SHRBim(IM,MD,MB,MS,MI) (((IM)==1) ? _O_r_X (0xd0 ,_b101 ,MD,MB,MI,MS ) : \ _O_r_X_B (0xc0 ,_b101 ,MD,MB,MI,MS ,_u8(IM) ) ) #define SHRBrr(RS,RD) (((RS)==_CL) ? _O_Mrm (0xd2 ,_b11,_b101,_r1(RD) ) : \ JITFAIL ("source register must be CL" ) ) #define SHRBrm(RS,MD,MB,MS,MI) (((RS)==_CL) ? _O_r_X (0xd2 ,_b101 ,MD,MB,MI,MS ) : \ JITFAIL ("source register must be CL" ) ) #define SHRWir(IM,RD) (((IM)==1) ? _wO_Mrm (0xd1 ,_b11,_b101,_r2(RD) ) : \ _wO_Mrm_B (0xc1 ,_b11,_b101,_r2(RD) ,_u8(IM) ) ) #define SHRWim(IM,MD,MB,MS,MI) (((IM)==1) ? _wO_r_X (0xd1 ,_b101 ,MD,MB,MI,MS ) : \ _wO_r_X_B (0xc1 ,_b101 ,MD,MB,MI,MS ,_u8(IM) ) ) #define SHRWrr(RS,RD) (((RS)==_CL) ? _wO_Mrm (0xd3 ,_b11,_b101,_r2(RD) ) : \ JITFAIL ("source register must be CL" ) ) #define SHRWrm(RS,MD,MB,MS,MI) (((RS)==_CL) ? _wO_r_X (0xd3 ,_b101 ,MD,MB,MI,MS ) : \ JITFAIL ("source register must be CL" ) ) #define SHRLir(IM,RD) (((IM)==1) ? _O_Mrm (0xd1 ,_b11,_b101,_r4(RD) ) : \ _O_Mrm_B (0xc1 ,_b11,_b101,_r4(RD) ,_u8(IM) ) ) #define SHRLim(IM,MD,MB,MS,MI) (((IM)==1) ? _O_r_X (0xd1 ,_b101 ,MD,MB,MI,MS ) : \ _O_r_X_B (0xc1 ,_b101 ,MD,MB,MI,MS ,_u8(IM) ) ) #define SHRLrr(RS,RD) (((RS)==_CL) ? _O_Mrm (0xd3 ,_b11,_b101,_r4(RD) ) : \ JITFAIL ("source register must be CL" ) ) #define SHRLrm(RS,MD,MB,MS,MI) (((RS)==_CL) ? _O_r_X (0xd3 ,_b101 ,MD,MB,MI,MS ) : \ JITFAIL ("source register must be CL" ) ) #define STC_() _O (0xf9 ) #define SUBBrr(RS, RD) _O_Mrm (0x28 ,_b11,_r1(RS),_r1(RD) ) #define SUBBmr(MD, MB, MI, MS, RD) _O_r_X (0x2a ,_r1(RD) ,MD,MB,MI,MS ) #define SUBBrm(RS, MD, MB, MI, MS) _O_r_X (0x28 ,_r1(RS) ,MD,MB,MI,MS ) #define SUBBir(IM, RD) _O_Mrm_B (0x80 ,_b11,_b101 ,_r1(RD) ,_su8(IM)) #define SUBBim(IM, MD, MB, MI, MS) _O_r_X_B (0x80 ,_b101 ,MD,MB,MI,MS ,_su8(IM)) #define SUBWrr(RS, RD) _wO_Mrm (0x29 ,_b11,_r2(RS),_r2(RD) ) #define SUBWmr(MD, MB, MI, MS, RD) _wO_r_X (0x2b ,_r2(RD) ,MD,MB,MI,MS ) #define SUBWrm(RS, MD, MB, MI, MS) _wO_r_X (0x29 ,_r2(RS) ,MD,MB,MI,MS ) #define SUBWir(IM, RD) _wOs_Mrm_sW (0x81 ,_b11,_b101 ,_r2(RD) ,_su16(IM)) #define SUBWim(IM, MD, MB, MI, MS) _wOs_r_X_sW (0x81 ,_b101 ,MD,MB,MI,MS ,_su16(IM)) #define SUBLrr(RS, RD) _O_Mrm (0x29 ,_b11,_r4(RS),_r4(RD) ) #define SUBLmr(MD, MB, MI, MS, RD) _O_r_X (0x2b ,_r4(RD) ,MD,MB,MI,MS ) #define SUBLrm(RS, MD, MB, MI, MS) _O_r_X (0x29 ,_r4(RS) ,MD,MB,MI,MS ) #define SUBLir(IM, RD) _Os_Mrm_sL (0x81 ,_b11,_b101 ,_r4(RD) ,IM ) #define SUBLim(IM, MD, MB, MI, MS) _Os_r_X_sL (0x81 ,_b101 ,MD,MB,MI,MS ,IM ) #define TESTBrr(RS, RD) _O_Mrm (0x84 ,_b11,_r1(RS),_r1(RD) ) #define TESTBrm(RS, MD, MB, MI, MS) _O_r_X (0x84 ,_r1(RS) ,MD,MB,MI,MS ) #define TESTBir(IM, RD) _O_Mrm_B (0xf6 ,_b11,_b000 ,_r1(RD) ,_u8(IM)) #define TESTBim(IM, MD, MB, MI, MS) _O_r_X_B (0xf6 ,_b000 ,MD,MB,MI,MS ,_u8(IM)) #define TESTWrr(RS, RD) _wO_Mrm (0x85 ,_b11,_r2(RS),_r2(RD) ) #define TESTWrm(RS, MD, MB, MI, MS) _wO_r_X (0x85 ,_r2(RS) ,MD,MB,MI,MS ) #define TESTWir(IM, RD) _wO_Mrm_W (0xf7 ,_b11,_b000 ,_r2(RD) ,_u16(IM)) #define TESTWim(IM, MD, MB, MI, MS) _wO_r_X_W (0xf7 ,_b000 ,MD,MB,MI,MS ,_u16(IM)) #define TESTLrr(RS, RD) _O_Mrm (0x85 ,_b11,_r4(RS),_r4(RD) ) #define TESTLrm(RS, MD, MB, MI, MS) _O_r_X (0x85 ,_r4(RS) ,MD,MB,MI,MS ) #define TESTLir(IM, RD) _O_Mrm_L (0xf7 ,_b11,_b000 ,_r4(RD) ,IM ) #define TESTLim(IM, MD, MB, MI, MS) _O_r_X_L (0xf7 ,_b000 ,MD,MB,MI,MS ,IM ) #define XADDBrr(RS,RD) _OO_Mrm (0x0fc0 ,_b11,_r1(RS),_r1(RD) ) #define XADDBrm(RS,MD,MB,MI,MS) _OO_r_X (0x0fc0 ,_r1(RS) ,MD,MB,MI,MS ) #define XADDWrr(RS,RD) _wOO_Mrm (0x0fc1 ,_b11,_r2(RS),_r2(RD) ) #define XADDWrm(RS,MD,MB,MI,MS) _wOO_r_X (0x0fc1 ,_r2(RS) ,MD,MB,MI,MS ) #define XADDLrr(RS,RD) _OO_Mrm (0x0fc1 ,_b11,_r4(RS),_r4(RD) ) #define XADDLrm(RS,MD,MB,MI,MS) _OO_r_X (0x0fc1 ,_r4(RS) ,MD,MB,MI,MS ) #define XCHGBrr(RS,RD) _O_Mrm (0x86 ,_b11,_r1(RS),_r1(RD) ) #define XCHGBrm(RS,MD,MB,MI,MS) _O_r_X (0x86 ,_r1(RS) ,MD,MB,MI,MS ) #define XCHGWrr(RS,RD) _wO_Mrm (0x87 ,_b11,_r2(RS),_r2(RD) ) #define XCHGWrm(RS,MD,MB,MI,MS) _wO_r_X (0x87 ,_r2(RS) ,MD,MB,MI,MS ) #define XCHGLrr(RS,RD) _O_Mrm (0x87 ,_b11,_r4(RS),_r4(RD) ) #define XCHGLrm(RS,MD,MB,MI,MS) _O_r_X (0x87 ,_r4(RS) ,MD,MB,MI,MS ) #define XORBrr(RS, RD) _O_Mrm (0x30 ,_b11,_r1(RS),_r1(RD) ) #define XORBmr(MD, MB, MI, MS, RD) _O_r_X (0x32 ,_r1(RD) ,MD,MB,MI,MS ) #define XORBrm(RS, MD, MB, MI, MS) _O_r_X (0x30 ,_r1(RS) ,MD,MB,MI,MS ) #define XORBir(IM, RD) _O_Mrm_B (0x80 ,_b11,_b110 ,_r1(RD) ,_su8(IM)) #define XORBim(IM, MD, MB, MI, MS) _O_r_X_B (0x80 ,_b110 ,MD,MB,MI,MS ,_su8(IM)) #define XORWrr(RS, RD) _wO_Mrm (0x31 ,_b11,_r2(RS),_r2(RD) ) #define XORWmr(MD, MB, MI, MS, RD) _wO_r_X (0x33 ,_r2(RD) ,MD,MB,MI,MS ) #define XORWrm(RS, MD, MB, MI, MS) _wO_r_X (0x31 ,_r2(RS) ,MD,MB,MI,MS ) #define XORWir(IM, RD) _wOs_Mrm_sW (0x81 ,_b11,_b110 ,_r2(RD) ,_su16(IM)) #define XORWim(IM, MD, MB, MI, MS) _wOs_r_X_sW (0x81 ,_b110 ,MD,MB,MI,MS ,_su16(IM)) #define XORLrr(RS, RD) _O_Mrm (0x31 ,_b11,_r4(RS),_r4(RD) ) #define XORLmr(MD, MB, MI, MS, RD) _O_r_X (0x33 ,_r4(RD) ,MD,MB,MI,MS ) #define XORLrm(RS, MD, MB, MI, MS) _O_r_X (0x31 ,_r4(RS) ,MD,MB,MI,MS ) #define XORLir(IM, RD) _Os_Mrm_sL (0x81 ,_b11,_b110 ,_r4(RD) ,IM ) #define XORLim(IM, MD, MB, MI, MS) _Os_r_X_sL (0x81 ,_b110 ,MD,MB,MI,MS ,IM ) /* x87 instructions -- yay, we found a use for octal constants :-) */ #define ESCmi(D,B,I,S,OP) _O_r_X(0xd8|(OP >> 3), (OP & 7), D,B,I,S) #define ESCri(RD,OP) _O_Mrm(0xd8|(OP >> 3), _b11, (OP & 7), RD) #define ESCrri(RS,RD,OP) ((RS) == _ST0 ? ESCri(RD,(OP|040)) \ : (RD) == _ST0 ? ESCri(RS,OP) \ : JITFAIL ("coprocessor instruction without st0")) #define FLDSm(D,B,I,S) ESCmi(D,B,I,S,010) /* fld m32real */ #define FILDLm(D,B,I,S) ESCmi(D,B,I,S,030) /* fild m32int */ #define FLDLm(D,B,I,S) ESCmi(D,B,I,S,050) /* fld m64real */ #define FILDWm(D,B,I,S) ESCmi(D,B,I,S,070) /* fild m16int */ #define FSTSm(D,B,I,S) ESCmi(D,B,I,S,012) /* fst m32real */ #define FISTLm(D,B,I,S) ESCmi(D,B,I,S,032) /* fist m32int */ #define FSTLm(D,B,I,S) ESCmi(D,B,I,S,052) /* fst m64real */ #define FISTWm(D,B,I,S) ESCmi(D,B,I,S,072) /* fist m16int */ #define FSTPSm(D,B,I,S) ESCmi(D,B,I,S,013) /* fstp m32real */ #define FISTPLm(D,B,I,S) ESCmi(D,B,I,S,033) /* fistp m32int */ #define FSTPLm(D,B,I,S) ESCmi(D,B,I,S,053) /* fstp m64real */ #define FISTPWm(D,B,I,S) ESCmi(D,B,I,S,073) /* fistp m16int */ #define FLDTm(D,B,I,S) ESCmi(D,B,I,S,035) /* fld m80real */ #define FILDQm(D,B,I,S) ESCmi(D,B,I,S,075) /* fild m64int */ #define FSTPTm(D,B,I,S) ESCmi(D,B,I,S,037) /* fstp m80real */ #define FISTPQm(D,B,I,S) ESCmi(D,B,I,S,077) /* fistp m64int */ #define FADDrr(RS,RD) ESCrri(RS,RD,000) #define FMULrr(RS,RD) ESCrri(RS,RD,001) #define FSUBrr(RS,RD) ESCrri(RS,RD,004) #define FSUBRrr(RS,RD) ESCrri(RS,RD,005) #define FDIVrr(RS,RD) ESCrri(RS,RD,006) #define FDIVRrr(RS,RD) ESCrri(RS,RD,007) #define FLDr(RD) ESCri(RD,010) #define FXCHr(RD) ESCri(RD,011) #define FFREEr(RD) ESCri(RD,050) #define FSTr(RD) ESCri(RD,052) #define FSTPr(RD) ESCri(RD,053) #define FCOMr(RD) ESCri(RD,002) #define FCOMPr(RD) ESCri(RD,003) #define FCOMIr(RD) ESCri(RD,036) #define FCOMIPr(RD) ESCri(RD,076) #define FUCOMr(RD) ESCri(RD,054) #define FUCOMPr(RD) ESCri(RD,055) #define FUCOMIr(RD) ESCri(RD,035) #define FUCOMIPr(RD) ESCri(RD,075) #define FADDPr(RD) ESCri(RD,060) #define FMULPr(RD) ESCri(RD,061) #define FSUBPr(RD) ESCri(RD,064) #define FSUBRPr(RD) ESCri(RD,065) #define FDIVPr(RD) ESCri(RD,066) #define FDIVRPr(RD) ESCri(RD,067) #define FNSTSWr(RD) ((RD == _AX || RD == _EAX) ? _OO (0xdfe0) \ : JITFAIL ("AX or EAX expected")) /* N byte NOPs */ #define NOPi(N) ((( (N) >= 8) ? (_jit_B(0x8d),_jit_B(0xb4),_jit_B(0x26),_jit_L(0x00),_jit_B(0x90)) : (void) 0), \ (( ((N)&7) == 7) ? (_jit_B(0x8d),_jit_B(0xb4),_jit_B(0x26),_jit_L(0x00)) : \ ( ((N)&7) == 6) ? (_jit_B(0x8d),_jit_B(0xb6),_jit_L(0x00)) : \ ( ((N)&7) == 5) ? (_jit_B(0x90),_jit_B(0x8d),_jit_B(0x74),_jit_B(0x26),_jit_B(0x00)) : \ /* leal 0(,%esi), %esi */ ( ((N)&7) == 4) ? (_jit_B(0x8d),_jit_B(0x74),_jit_B(0x26),_jit_B(0x00)) : \ /* leal (,%esi), %esi */ ( ((N)&7) == 3) ? (_jit_B(0x8d),_jit_B(0x76),_jit_B(0x00)) : \ /* movl %esi, %esi */ ( ((N)&7) == 2) ? (_jit_B(0x89),_jit_B(0xf6)) : \ ( ((N)&7) == 1) ? (_jit_B(0x90)) : \ ( ((N)&7) == 0) ? 0 : \ JITFAIL(".align argument too large"))) /*** References: */ /* */ /* [1] "Intel Architecture Software Developer's Manual Volume 1: Basic Architecture", */ /* Intel Corporation 1997. */ /* */ /* [2] "Intel Architecture Software Developer's Manual Volume 2: Instruction Set Reference", */ /* Intel Corporation 1997. */ #endif #endif /* __lightning_asm_i386_h */ smalltalk-3.2.5/lightning/i386/Makefile.frag0000644000175000017500000000007312123404352015454 00000000000000LIGHTNING_TARGET_FILES += i386/asm-i386.h i386/core-i386.h smalltalk-3.2.5/lightning/i386/core-64.h0000644000175000017500000002427112123404352014434 00000000000000/******************************** -*- C -*- **************************** * * Platform-independent layer (i386 version) * ***********************************************************************/ /*********************************************************************** * * Copyright 2000, 2001, 2002, 2003 Free Software Foundation, Inc. * Written by Paolo Bonzini. * * This file is part of GNU lightning. * * GNU lightning is free software; you can redistribute it and/or modify it * under the terms of the GNU Lesser General Public License as published * by the Free Software Foundation; either version 2.1, or (at your option) * any later version. * * GNU lightning is distributed in the hope that it will be useful, but * WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY * or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser General Public * License for more details. * * You should have received a copy of the GNU Lesser General Public License * along with GNU lightning; see the file COPYING.LESSER; if not, write to the * Free Software Foundation, 59 Temple Place - Suite 330, Boston, * MA 02111-1307, USA. * ***********************************************************************/ #ifndef __lightning_core_h #define __lightning_core_h #include "core-i386.h" struct jit_local_state { int long_jumps; int nextarg_geti; int argssize; }; /* 3-parameter operation */ #define jit_qopr_(d, s1, s2, op1d, op2d) \ ( (s2 == d) ? op1d : \ ( ((s1 == d) ? (void)0 : (void)MOVQrr(s1, d)), op2d ) \ ) /* 3-parameter operation, with immediate */ #define jit_qop_(d, s1, op2d) \ #define jit_bra_qr(s1, s2, op) (CMPQrr(s2, s1), op, _jit.x.pc) #define _jit_bra_l(rs, is, op) (CMPQir(is, rs), op, _jit.x.pc) #define jit_bra_l(rs, is, op) (_s32P((long)(is)) \ ? _jit_bra_l(rs, is, op) \ : (jit_movi_l(JIT_REXTMP, is), jit_bra_qr(JIT_REXTMP, rs, op))) /* When CMP with 0 can be replaced with TEST */ #define jit_bra_l0(rs, is, op, op0) \ ( (is) == 0 ? (TESTQrr(rs, rs), op0, _jit.x.pc) : jit_bra_l(rs, is, op)) /* Used to implement ldc, stc, ... */ #define JIT_CAN_16 0 #define jit_reduceQ(op, is, rs) \ (_u8P(is) && jit_check8(rs) ? jit_reduce_(op##Bir(is, jit_reg8(rs))) : \ jit_reduce_(op##Qir(is, rs)) ) #define jit_addi_l(d, rs, is) jit_opi_((d), (rs), ADDQir((is), (d)), LEAQmr((is), (rs), 0, 0, (d)) ) #define jit_addr_l(d, s1, s2) jit_opo_((d), (s1), (s2), ADDQrr((s2), (d)), ADDQrr((s1), (d)), LEAQmr(0, (s1), (s2), 1, (d)) ) #define jit_andi_l(d, rs, is) jit_qop_ ((d), (rs), ANDQir((is), (d)) ) #define jit_andr_l(d, s1, s2) jit_qopr_((d), (s1), (s2), ANDQrr((s1), (d)), ANDQrr((s2), (d)) ) #define jit_orr_l(d, s1, s2) jit_qopr_((d), (s1), (s2), ORQrr((s1), (d)), ORQrr((s2), (d)) ) #define jit_subr_l(d, s1, s2) jit_qopr_((d), (s1), (s2), (SUBQrr((s1), (d)), NEGQr(d)), SUBQrr((s2), (d)) ) #define jit_xorr_l(d, s1, s2) jit_qopr_((d), (s1), (s2), XORQrr((s1), (d)), XORQrr((s2), (d)) ) /* These can sometimes use byte or word versions! */ #define jit_ori_i(d, rs, is) jit_op_ ((d), (rs), jit_reduce(OR, (is), (d)) ) #define jit_xori_i(d, rs, is) jit_op_ ((d), (rs), jit_reduce(XOR, (is), (d)) ) #define jit_ori_l(d, rs, is) jit_qop_ ((d), (rs), jit_reduceQ(OR, (is), (d)) ) #define jit_xori_l(d, rs, is) jit_qop_ ((d), (rs), jit_reduceQ(XOR, (is), (d)) ) #define jit_lshi_l(d, rs, is) ((is) <= 3 ? LEAQmr(0, 0, (rs), 1 << (is), (d)) : jit_qop_ ((d), (rs), SHLQir((is), (d)) )) #define jit_rshi_l(d, rs, is) jit_qop_ ((d), (rs), SARQir((is), (d)) ) #define jit_rshi_ul(d, rs, is) jit_qop_ ((d), (rs), SHRQir((is), (d)) ) #define jit_lshr_l(d, r1, r2) jit_replace((r1), (r2), _ECX, jit_qop_ ((d), (r1), SHLQrr(_CL, (d)) )) #define jit_rshr_l(d, r1, r2) jit_replace((r1), (r2), _ECX, jit_qop_ ((d), (r1), SARQrr(_CL, (d)) )) #define jit_rshr_ul(d, r1, r2) jit_replace((r1), (r2), _ECX, jit_qop_ ((d), (r1), SHRQrr(_CL, (d)) )) /* Stack */ #define jit_pushr_l(rs) PUSHQr(rs) #define jit_popr_l(rs) POPQr(rs) #define jit_base_prolog() (PUSHQr(_EBP), MOVQrr(_ESP, _EBP), PUSHQr(_EBX), PUSHQr(_R12), PUSHQr(_R13)) #define jit_prolog(n) (_jitl.nextarg_geti = 0, jit_base_prolog()) /* Stack isn't used for arguments: */ #define jit_prepare_i(ni) (_jitl.argssize = 0) #define jit_pusharg_i(rs) (_jitl.argssize++, MOVQrr(rs, JIT_CALLTMPSTART + _jitl.argssize - 1)) #define jit_finish(sub) (jit_shift_args(), (void)jit_calli((sub)), jit_restore_locals()) #define jit_reg_is_arg(reg) ((reg == _EDI) || (reg ==_ESI) || (reg == _EDX)) #define jit_finishr(reg) ((jit_reg_is_arg((reg)) ? MOVQrr(reg, JIT_REXTMP) : (void)0), \ jit_shift_args(), \ jit_reg_is_arg((reg)) ? CALQsr((JIT_REXTMP)) : jit_callr((reg)), \ jit_restore_locals()) /* R12 and R13 are callee-save, instead of EDI and ESI. Can be improved. */ #define jit_shift_args() \ (MOVQrr(_ESI, _R12), MOVQrr(_EDI, _R13), \ (_jitl.argssize-- \ ? (MOVQrr(JIT_CALLTMPSTART + _jitl.argssize, jit_arg_reg_order[0]), \ (_jitl.argssize-- \ ? (MOVQrr(JIT_CALLTMPSTART + _jitl.argssize, jit_arg_reg_order[1]), \ (_jitl.argssize-- \ ? MOVQrr(JIT_CALLTMPSTART, jit_arg_reg_order[2]) \ : (void)0)) \ : (void)0)) \ : (void)0)) #define jit_restore_locals() \ (MOVQrr(_R12, _ESI), MOVQrr(_R13, _EDI)) #define jit_retval_l(rd) ((void)jit_movr_l ((rd), _EAX)) #define jit_arg_i() (_jitl.nextarg_geti++) #define jit_arg_l() (_jitl.nextarg_geti++) #define jit_arg_p() (_jitl.nextarg_geti++) #define jit_arg_reg(p) (jit_arg_reg_order[p]) static int jit_arg_reg_order[] = { _EDI, _ESI, _EDX, _ECX }; #define jit_negr_l(d, rs) jit_opi_((d), (rs), NEGQr(d), (XORQrr((d), (d)), SUBQrr((rs), (d))) ) #define jit_movr_l(d, rs) ((void)((rs) == (d) ? 0 : MOVQrr((rs), (d)))) #define jit_movi_l(d, is) ((is) \ ? (_u32P((long)(is)) \ ? MOVLir((is), (d)) \ : MOVQir((is), (d))) \ : XORLrr ((d), (d)) ) #define jit_bmsr_l(label, s1, s2) (TESTQrr((s1), (s2)), JNZm(label,0,0,0), _jit.x.pc) #define jit_bmcr_l(label, s1, s2) (TESTQrr((s1), (s2)), JZm(label,0,0,0), _jit.x.pc) #define jit_boaddr_l(label, s1, s2) (ADDQrr((s2), (s1)), JOm(label,0,0,0), _jit.x.pc) #define jit_bosubr_l(label, s1, s2) (SUBQrr((s2), (s1)), JOm(label,0,0,0), _jit.x.pc) #define jit_boaddr_ul(label, s1, s2) (ADDQrr((s2), (s1)), JCm(label,0,0,0), _jit.x.pc) #define jit_bosubr_ul(label, s1, s2) (SUBQrr((s2), (s1)), JCm(label,0,0,0), _jit.x.pc) #define jit_boaddi_l(label, rs, is) (ADDQir((is), (rs)), JOm(label,0,0,0), _jit.x.pc) #define jit_bosubi_l(label, rs, is) (SUBQir((is), (rs)), JOm(label,0,0,0), _jit.x.pc) #define jit_boaddi_ul(label, rs, is) (ADDQir((is), (rs)), JCm(label,0,0,0), _jit.x.pc) #define jit_bosubi_ul(label, rs, is) (SUBQir((is), (rs)), JCm(label,0,0,0), _jit.x.pc) #define jit_patch_long_at(jump_pc,v) (*_PSL((jump_pc) - sizeof(long)) = _jit_SL((jit_insn *)(v))) #define jit_patch_short_at(jump_pc,v) (*_PSI((jump_pc) - sizeof(int)) = _jit_SI((jit_insn *)(v) - (jump_pc))) #define jit_patch_at(jump_pc,v) (_jitl.long_jumps ? jit_patch_long_at((jump_pc)-3, v) : jit_patch_short_at(jump_pc, v)) #define jit_ret() (POPQr(_R13), POPQr(_R12), POPQr(_EBX), POPQr(_EBP), RET_()) #define _jit_ldi_l(d, is) MOVQmr((is), 0, 0, 0, (d)) #define jit_ldr_l(d, rs) MOVQmr(0, (rs), 0, 0, (d)) #define jit_ldxr_l(d, s1, s2) MOVQmr(0, (s1), (s2), 1, (d)) #define jit_ldxi_l(d, rs, is) MOVQmr((is), (rs), 0, 0, (d)) #define _jit_sti_l(id, rs) MOVQrm((rs), (id), 0, 0, 0) #define jit_str_l(rd, rs) MOVQrm((rs), 0, (rd), 0, 0) #define jit_stxr_l(d1, d2, rs) MOVQrm((rs), 0, (d1), (d2), 1) #define jit_stxi_l(id, rd, rs) MOVQrm((rs), (id), (rd), 0, 0) #define jit_ldi_l(d, is) (_u32P((long)(is)) ? _jit_ldi_l(d, is) : (jit_movi_l(d, is), jit_ldr_l(d, d))) #define jit_sti_l(id, rs) (_u32P((long)(id)) ? _jit_sti_l(id, rs) : (jit_movi_l(JIT_REXTMP, id), MOVQrQm(rs, 0, JIT_REXTMP, 0, 0))) #define jit_blti_l(label, rs, is) jit_bra_l0((rs), (is), JLm(label, 0,0,0), JSm(label, 0,0,0) ) #define jit_blei_l(label, rs, is) jit_bra_l ((rs), (is), JLEm(label,0,0,0) ) #define jit_bgti_l(label, rs, is) jit_bra_l ((rs), (is), JGm(label, 0,0,0) ) #define jit_bgei_l(label, rs, is) jit_bra_l0((rs), (is), JGEm(label,0,0,0), JNSm(label,0,0,0) ) #define jit_beqi_l(label, rs, is) jit_bra_l0((rs), (is), JEm(label, 0,0,0), JEm(label, 0,0,0) ) #define jit_bnei_l(label, rs, is) jit_bra_l0((rs), (is), JNEm(label,0,0,0), JNEm(label,0,0,0) ) #define jit_blti_ul(label, rs, is) jit_bra_l ((rs), (is), JBm(label, 0,0,0) ) #define jit_blei_ul(label, rs, is) jit_bra_l0((rs), (is), JBEm(label,0,0,0), JEm(label, 0,0,0) ) #define jit_bgti_ul(label, rs, is) jit_bra_l0((rs), (is), JAm(label, 0,0,0), JNEm(label,0,0,0) ) #define jit_bgei_ul(label, rs, is) jit_bra_l ((rs), (is), JAEm(label,0,0,0) ) #define jit_bmsi_l(label, rs, is) jit_bmsi_i(label, rs, is) #define jit_bmci_l(label, rs, is) jit_bmci_i(label, rs, is) #define jit_pushr_l(rs) jit_pushr_i(rs) #define jit_popr_l(rs) jit_popr_i(rs) #define jit_pusharg_l(rs) jit_pusharg_i(rs) #define jit_retval_l(rd) ((void)jit_movr_l ((rd), _EAX)) #define jit_bltr_l(label, s1, s2) jit_bra_qr((s1), (s2), JLm(label, 0,0,0) ) #define jit_bler_l(label, s1, s2) jit_bra_qr((s1), (s2), JLEm(label,0,0,0) ) #define jit_bgtr_l(label, s1, s2) jit_bra_qr((s1), (s2), JGm(label, 0,0,0) ) #define jit_bger_l(label, s1, s2) jit_bra_qr((s1), (s2), JGEm(label,0,0,0) ) #define jit_beqr_l(label, s1, s2) jit_bra_qr((s1), (s2), JEm(label, 0,0,0) ) #define jit_bner_l(label, s1, s2) jit_bra_qr((s1), (s2), JNEm(label,0,0,0) ) #define jit_bltr_ul(label, s1, s2) jit_bra_qr((s1), (s2), JBm(label, 0,0,0) ) #define jit_bler_ul(label, s1, s2) jit_bra_qr((s1), (s2), JBEm(label,0,0,0) ) #define jit_bgtr_ul(label, s1, s2) jit_bra_qr((s1), (s2), JAm(label, 0,0,0) ) #define jit_bger_ul(label, s1, s2) jit_bra_qr((s1), (s2), JAEm(label,0,0,0) ) #endif /* __lightning_core_h */ smalltalk-3.2.5/lightning/i386/asm-64.h0000644000175000017500000001235212123404352014261 00000000000000/******************************** -*- C -*- **************************** * * Run-time assembler for the x86-64 * ***********************************************************************/ /*********************************************************************** * * Copyright 2006 Matthew Flatt * * This file is part of GNU lightning. * * GNU lightning is free software; you can redistribute it and/or modify it * under the terms of the GNU Lesser General Public License as published * by the Free Software Foundation; either version 2.1, or (at your option) * any later version. * * GNU lightning is distributed in the hope that it will be useful, but * WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY * or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser General Public * License for more details. * * You should have received a copy of the GNU Lesser General Public License * along with GNU lightning; see the file COPYING.LESSER; if not, write to the * Free Software Foundation, 59 Temple Place - Suite 330, Boston, * MA 02111-1307, USA. * ***********************************************************************/ #ifndef __lightning_asm_h #define __lightning_asm_h #include "asm-i386.h" /* OPCODE + i = immediate operand * + r = register operand * + m = memory operand (disp,base,index,scale) * + sr/sm = a star preceding a register or memory */ #ifndef LIGHTNING_DEBUG #define _R12 0x4C #define _R13 0x4D #define JIT_CALLTMPSTART 0x48 #define JIT_REXTMP 0x4B #define _qMrm(Md,R,M) _jit_B((_M(Md)<<6)|(_r((R & 0x7))<<3)|_m((M & 0x7))) #define _r_D( R, D ) (_Mrm(_b00,_rN(R),_b100 ),_SIB(0,_b100,_b101) ,_jit_I((long)(D))) #define _r_Q( R, D ) (_qMrm(_b00,_rN(R),_b100 ),_SIB(0,_b100,_b101) ,_jit_I((long)(D))) #define _REX(R,X,B) ( _jit_B(0x48|((R&0x8)>>1)|((X&0x8)>>2)|((B&0x8)>>3)) ) #define _qO( OP, R,X,B ) ( _REX(R,X,B), _jit_B( OP ) ) #define _qOr( OP,R ) ( _REX(0,0,R), _jit_B( (OP)|_r(R&0x7)) ) #define _qOs( OP, B, R, M ) ( _REX(0, M, R), _Os(OP, B) ) #define ADDQrr(RS, RD) _qO_Mrm (0x01 ,_b11,_r8(RS),_r8(RD) ) #define ADDQir(IM, RD) _qOs_Mrm_sL (0x81 ,_b11,_b000 ,_r8(RD) ,IM ) #define ANDQrr(RS, RD) _qO_Mrm (0x21 ,_b11,_r8(RS),_r8(RD) ) #define ANDQir(IM, RD) _qOs_Mrm_sL (0x81 ,_b11,_b100 ,_r8(RD) ,IM ) #define CALLm(D,B,I,S) (MOVQir((D), JIT_REXTMP), CALLQsr(JIT_REXTMP)) #define CALLsr(R) _O_Mrm (0xff ,_b11,_b010,_r4(R) ) #define CALLQsr(R) _qO_Mrm (0xff ,_b11,_b010,_r8(R)) #define CMPQrr(RS, RD) _qO_Mrm (0x39 ,_b11,_r8(RS),_r8(RD) ) #define CMPQir(IM, RD) _qO_Mrm_L (0x81 ,_b11,_b111 ,_r8(RD) ,IM ) #define JCCim(CC,D,B,I,S) (!_jitl.long_jumps \ ? _OO_D32(0x0f80|(CC), (long)(D) ) \ : (_O_D8(0x71^(CC), _jit_UL(_jit.x.pc) + 13), JMPm((long)D, 0, 0, 0))) #define JMPm(D,B,I,S) (!_jitl.long_jumps \ ? _O_D32(0xe9, (long)(D)) \ : (MOVQir((D), JIT_REXTMP), _qO_Mrm(0xff,_b11,_b100,_r8(JIT_REXTMP)))) #define LEAQmr(MD, MB, MI, MS, RD) _qO_r_X (0x8d ,_r8(RD) ,MD,MB,MI,MS ) #define MOVQmr(MD, MB, MI, MS, RD) _qO_r_X (0x8b ,_r8(RD) ,MD,MB,MI,MS ) #define MOVQrm(RS, MD, MB, MI, MS) _qO_r_X (0x89 ,_r8(RS) ,MD,MB,MI,MS ) #define MOVQrQm(RS, MD, MB, MI, MS) _qO_r_XB (0x89 ,_r8(RS) ,MD,MB,MI,MS ) #define MOVQir(IM, R) _qOr_Q (0xb8,_r8(R) ,IM ) #define MOVQrr(RS, RD) _qO_Mrm (0x89 ,_b11,_r8(RS),_r8(RD) ) #define NEGQr(RD) _qO_Mrm (0xf7 ,_b11,_b011 ,_r8(RD) ) #define ORQrr(RS, RD) _qO_Mrm (0x09 ,_b11,_r8(RS),_r8(RD) ) #define ORQir(IM, RD) _qOs_Mrm_sL (0x81 ,_b11,_b001 ,_r8(RD) ,IM ) #define POPQr(RD) _qOr (0x58,_r8(RD) ) #define PUSHQr(R) _qOr (0x50,_r8(R) ) #define SALQir SHLQir #define SALQim SHLQim #define SALQrr SHLQrr #define SALQrm SHLQrm #define SARQir(IM,RD) (((IM)==1) ? _qO_Mrm (0xd1 ,_b11,_b111,_r8(RD) ) : \ _qO_Mrm_B (0xc1 ,_b11,_b111,_r4(RD) ,_u8(IM) ) ) #define SARQrr(RS,RD) (((RS)==_CL) ? _qO_Mrm (0xd3 ,_b11,_b111,_r8(RD) ) : \ JITFAIL ("source register must be CL" ) ) #define SHLQir(IM,RD) (((IM)==1) ? _qO_Mrm (0xd1 ,_b11,_b100,_r8(RD) ) : \ _qO_Mrm_B (0xc1 ,_b11,_b100,_r8(RD) ,_u8(IM) ) ) #define SHLQrr(RS,RD) (((RS)==_CL) ? _qO_Mrm (0xd3 ,_b11,_b100,_r8(RD) ) : \ JITFAIL ("source register must be CL" ) ) #define SHRQir(IM,RD) (((IM)==1) ? _qO_Mrm (0xd1 ,_b11,_b101,_r8(RD) ) : \ _qO_Mrm_B (0xc1 ,_b11,_b101,_r8(RD) ,_u8(IM) ) ) #define SHRQrr(RS,RD) (((RS)==_CL) ? _qO_Mrm (0xd3 ,_b11,_b101,_r8(RD) ) : \ JITFAIL ("source register must be CL" ) ) #define SUBQrr(RS, RD) _qO_Mrm (0x29 ,_b11,_r8(RS),_r8(RD) ) #define SUBQir(IM, RD) _qOs_Mrm_sL (0x81 ,_b11,_b101 ,_r8(RD) ,IM ) #define TESTQrr(RS, RD) _qO_Mrm (0x85 ,_b11,_r8(RS),_r8(RD) ) #define TESTQir(IM, RD) _qO_Mrm_L (0xf7 ,_b11,_b000 ,_r8(RD) ,IM ) #define XORQrr(RS, RD) _qO_Mrm (0x31 ,_b11,_r8(RS),_r8(RD) ) #define XORQir(IM, RD) _qOs_Mrm_sL (0x81 ,_b11,_b110 ,_r8(RD) ,IM ) #endif #endif /* __lightning_asm_h */ smalltalk-3.2.5/lightning/i386/funcs.h0000644000175000017500000000626212123404352014373 00000000000000/******************************** -*- C -*- **************************** * * Platform-independent layer inline functions (i386) * ***********************************************************************/ /*********************************************************************** * * Copyright 2000, 2001, 2002 Free Software Foundation, Inc. * Written by Paolo Bonzini. * * This file is part of GNU lightning. * * GNU lightning is free software; you can redistribute it and/or modify it * under the terms of the GNU Lesser General Public License as published * by the Free Software Foundation; either version 2.1, or (at your option) * any later version. * * GNU lightning is distributed in the hope that it will be useful, but * WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY * or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser General Public * License for more details. * * You should have received a copy of the GNU Lesser General Public License * along with GNU lightning; see the file COPYING.LESSER; if not, write to the * Free Software Foundation, 51 Franklin Street, Fifth Floor, Boston, * MA 02110-1301, USA. * ***********************************************************************/ #ifndef __lightning_funcs_h #define __lightning_funcs_h #ifdef __linux__ #include #include #endif static void jit_flush_code(void *dest, void *end) { /* On the x86, the PROT_EXEC bits are not handled by the MMU. However, the kernel can emulate this by setting the code segment's limit to the end address of the highest page whose PROT_EXEC bit is set. Linux kernels that do so and that disable by default the execution of the data and stack segment are becoming more and more common (Fedora, for example), so we implement our jit_flush_code as an mprotect. */ #ifdef __linux__ static unsigned long prev_page = 0, prev_length = 0; int page, length; #ifdef PAGESIZE const int page_size = PAGESIZE; #else static int page_size = -1; if (page_size == -1) page_size = sysconf (_SC_PAGESIZE); #endif page = (long) dest & ~(page_size - 1); length = ((char *) end - (char *) page + page_size - 1) & ~(page_size - 1); /* Simple-minded attempt at optimizing the common case where a single chunk of memory is used to compile multiple functions. */ if (page >= prev_page && page + length <= prev_page + prev_length) return; mprotect ((void *) page, length, PROT_READ | PROT_WRITE | PROT_EXEC); /* See if we can extend the previously mprotect'ed memory area towards higher addresses: the starting address remains the same as before. */ if (page >= prev_page && page <= prev_page + prev_length) prev_length = page + length - prev_page; /* See if we can extend the previously mprotect'ed memory area towards lower addresses: the highest address remains the same as before. */ else if (page < prev_page && page + length >= prev_page && page + length <= prev_page + prev_length) prev_length += prev_page - page, prev_page = page; /* Nothing to do, replace the area. */ else prev_page = page, prev_length = length; #endif } #endif /* __lightning_funcs_h */ smalltalk-3.2.5/lightning/i386/asm-32.h0000644000175000017500000000371312123404352014255 00000000000000/******************************** -*- C -*- **************************** * * Run-time assembler for the i386 * ***********************************************************************/ /*********************************************************************** * * Copyright 2006 Free Software Foundation, Inc. * * This file is part of GNU lightning. * * GNU lightning is free software; you can redistribute it and/or modify it * under the terms of the GNU Lesser General Public License as published * by the Free Software Foundation; either version 2.1, or (at your option) * any later version. * * GNU lightning is distributed in the hope that it will be useful, but * WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY * or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser General Public * License for more details. * * You should have received a copy of the GNU Lesser General Public License * along with GNU lightning; see the file COPYING.LESSER; if not, write to the * Free Software Foundation, 59 Temple Place - Suite 330, Boston, * MA 02111-1307, USA. * ***********************************************************************/ #ifndef __lightning_asm_h #define __lightning_asm_h /* OPCODE + i = immediate operand * + r = register operand * + m = memory operand (disp,base,index,scale) * + sr/sm = a star preceding a register or memory */ #include "asm-i386.h" #ifndef LIGHTNING_DEBUG #define _r_D( R, D ) (_Mrm(_b00,_rN(R),_b101 ) ,_jit_I((long)(D))) #define CALLm(D,B,I,S) ((_r0P(B) && _r0P(I)) ? _O_D32 (0xe8 ,(long)(D) ) : \ JITFAIL("illegal mode in direct jump")) #define JCCim(CC,D,B,I,S) ((_r0P(B) && _r0P(I)) ? _OO_D32 (0x0f80|(CC) ,(long)(D) ) : \ JITFAIL("illegal mode in conditional jump")) #define JMPm(D,B,I,S) ((_r0P(B) && _r0P(I)) ? _O_D32 (0xe9 ,(long)(D) ) : \ JITFAIL("illegal mode in direct jump")) #endif #endif /* __lightning_asm_h */ smalltalk-3.2.5/lightning/i386/core-i386.h0000644000175000017500000004507012123404352014674 00000000000000/******************************** -*- C -*- **************************** * * Platform-independent layer (i386 version) * ***********************************************************************/ /*********************************************************************** * * Copyright 2000, 2001, 2002, 2003 Free Software Foundation, Inc. * Written by Paolo Bonzini. * * This file is part of GNU lightning. * * GNU lightning is free software; you can redistribute it and/or modify it * under the terms of the GNU Lesser General Public License as published * by the Free Software Foundation; either version 2.1, or (at your option) * any later version. * * GNU lightning is distributed in the hope that it will be useful, but * WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY * or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser General Public * License for more details. * * You should have received a copy of the GNU Lesser General Public License * along with GNU lightning; see the file COPYING.LESSER; if not, write to the * Free Software Foundation, 59 Temple Place - Suite 330, Boston, * MA 02111-1307, USA. * ***********************************************************************/ #ifndef __lightning_core_i386_h #define __lightning_core_i386_h #define JIT_FP _EBP #define JIT_SP _ESP #define JIT_RET _EAX #define JIT_R_NUM 3 #define JIT_V_NUM 3 #define JIT_R(i) (_EAX + (i)) #define JIT_V(i) ((i) == 0 ? _EBX : _ESI + (i) - 1) /* 3-parameter operation */ #define jit_opr_(d, s1, s2, op1d, op2d) \ ( (s2 == d) ? op1d : \ ( ((s1 == d) ? (void)0 : (void)MOVLrr(s1, d)), op2d ) \ ) /* 3-parameter operation, with immediate */ #define jit_op_(d, s1, op2d) \ ((s1 == d) ? op2d : (MOVLrr(s1, d), op2d)) /* 3-parameter operation, optimizable */ #define jit_opo_(d, s1, s2, op1d, op2d, op12d) \ ((s2 == d) ? op2d : \ ((s1 == d) ? op1d : op12d)) /* 3-parameter operation, optimizable, with immediate */ #define jit_opi_(d, rs, opdi, opdri) \ ((rs == d) ? opdi : opdri) /* An operand is forced into a register */ #define jit_replace(rd, rs, forced, op) \ ((rd == forced) ? JITSORRY("Register conflict for " # op) : \ (rs == forced) ? op : (PUSHLr(forced), MOVLrr(rs, forced), op, POPLr(forced))) /* For LT, LE, ... */ #define jit_replace8(d, op) \ (jit_check8(d) \ ? (MOVLir(0, d), op(d)) \ : (PUSHLr(_EAX), MOVLir(0, _EAX), op(_EAX), MOVLrr(_EAX, (d)), POPLr(_EAX))) #define jit_bool_r(d, s1, s2, op) \ (CMPLrr(s2, s1), jit_replace8(d, op)) #define jit_bool_i(d, rs, is, op) \ (CMPLir(is, rs), jit_replace8(d, op)) /* When CMP with 0 can be replaced with TEST */ #define jit_bool_i0(d, rs, is, op, op0) \ ((is) != 0 \ ? (CMPLir(is, rs), jit_replace8(d, op)) \ : (TESTLrr(rs, rs), jit_replace8(d, op0))) /* For BLT, BLE, ... */ #define jit_bra_r(s1, s2, op) (CMPLrr(s2, s1), op, _jit.x.pc) #define jit_bra_i(rs, is, op) (CMPLir(is, rs), op, _jit.x.pc) /* When CMP with 0 can be replaced with TEST */ #define jit_bra_i0(rs, is, op, op0) \ ( (is) == 0 ? (TESTLrr(rs, rs), op0, _jit.x.pc) : (CMPLir(is, rs), op, _jit.x.pc)) /* Used to implement ldc, stc, ... */ #define jit_check8(rs) ( (rs) <= _EBX ) #define jit_reg8(rs) ( ((rs) == _SI || (rs) == _DI) ? _AL : ((rs) & _BH) | _AL ) #define jit_reg16(rs) ( ((rs) & _BH) | _AX ) /* In jit_replace below, _EBX is dummy */ #define jit_movbrm(rs, dd, db, di, ds) \ (jit_check8(rs) \ ? MOVBrm(jit_reg8(rs), dd, db, di, ds) \ : jit_replace(_EBX, rs, _EAX, MOVBrm(_AL, dd, db, di, ds))) /* Reduce arguments of XOR/OR/TEST */ #ifdef JIT_X86_64 # define JIT_CAN_16 0 #else # define JIT_CAN_16 1 #endif #define jit_reduce_(op) op #define jit_reduce(op, is, rs) \ (_u8P(is) && jit_check8(rs) ? jit_reduce_(op##Bir(is, jit_reg8(rs))) : \ (_u16P(is) && JIT_CAN_16 ? jit_reduce_(op##Wir(is, jit_reg16(rs))) : \ jit_reduce_(op##Lir(is, rs)) )) /* Helper macros for MUL/DIV/IDIV */ #define jit_might(d, s1, op) \ ((s1 == d) ? 0 : op) #define jit_mulr_ui_(s1, s2) jit_opr_(_EAX, s1, s2, MULLr(s1), MULLr(s2)) #define jit_mulr_i_(s1, s2) jit_opr_(_EAX, s1, s2, IMULLr(s1), IMULLr(s2)) #define jit_muli_i_(is, rs) \ (MOVLir(is, rs == _EAX ? _EDX : _EAX), \ IMULLr(rs == _EAX ? _EDX : rs)) #define jit_muli_ui_(is, rs) \ (MOVLir(is, rs == _EAX ? _EDX : _EAX), \ IMULLr(rs == _EAX ? _EDX : rs)) #define jit_divi_i_(result, d, rs, is) \ (jit_might (d, _EAX, PUSHLr(_EAX)), \ jit_might (d, _ECX, PUSHLr(_ECX)), \ jit_might (d, _EDX, PUSHLr(_EDX)), \ jit_might (rs, _EAX, MOVLrr(rs, _EAX)), \ jit_might (rs, _EDX, MOVLrr(rs, _EDX)), \ MOVLir(is, _ECX), \ SARLir(31, _EDX), \ IDIVLr(_ECX), \ jit_might(d, result, MOVLrr(result, d)), \ jit_might(d, _EDX, POPLr(_EDX)), \ jit_might(d, _ECX, POPLr(_ECX)), \ jit_might(d, _EAX, POPLr(_EAX))) #define jit_divr_i_(result, d, s1, s2) \ (jit_might (d, _EAX, PUSHLr(_EAX)), \ jit_might (d, _ECX, PUSHLr(_ECX)), \ jit_might (d, _EDX, PUSHLr(_EDX)), \ ((s1 == _ECX) ? PUSHLr(_ECX) : 0), \ jit_might (s2, _ECX, MOVLrr(s2, _ECX)), \ ((s1 == _ECX) ? POPLr(_EDX) : \ jit_might (s1, _EDX, MOVLrr(s1, _EDX))), \ MOVLrr(_EDX, _EAX), \ SARLir(31, _EDX), \ IDIVLr(_ECX), \ jit_might(d, result, MOVLrr(result, d)), \ jit_might(d, _EDX, POPLr(_EDX)), \ jit_might(d, _ECX, POPLr(_ECX)), \ jit_might(d, _EAX, POPLr(_EAX))) #define jit_divi_ui_(result, d, rs, is) \ (jit_might (d, _EAX, PUSHLr(_EAX)), \ jit_might (d, _ECX, PUSHLr(_ECX)), \ jit_might (d, _EDX, PUSHLr(_EDX)), \ jit_might (rs, _EAX, MOVLrr(rs, _EAX)), \ MOVLir(is, _ECX), \ XORLrr(_EDX, _EDX), \ DIVLr(_ECX), \ jit_might(d, result, MOVLrr(result, d)), \ jit_might(d, _EDX, POPLr(_EDX)), \ jit_might(d, _ECX, POPLr(_ECX)), \ jit_might(d, _EAX, POPLr(_EAX))) #define jit_divr_ui_(result, d, s1, s2) \ (jit_might (d, _EAX, PUSHLr(_EAX)), \ jit_might (d, _ECX, PUSHLr(_ECX)), \ jit_might (d, _EDX, PUSHLr(_EDX)), \ ((s1 == _ECX) ? PUSHLr(_ECX) : 0), \ jit_might (s2, _ECX, MOVLrr(s2, _ECX)), \ ((s1 == _ECX) ? POPLr(_EAX) : \ jit_might (s1, _EAX, MOVLrr(s1, _EAX))), \ XORLrr(_EDX, _EDX), \ DIVLr(_ECX), \ jit_might(d, result, MOVLrr(result, d)), \ jit_might(d, _EDX, POPLr(_EDX)), \ jit_might(d, _ECX, POPLr(_ECX)), \ jit_might(d, _EAX, POPLr(_EAX))) /* ALU */ #define jit_addi_i(d, rs, is) jit_opi_((d), (rs), ADDLir((is), (d)), LEALmr((is), (rs), 0, 0, (d)) ) #define jit_addr_i(d, s1, s2) jit_opo_((d), (s1), (s2), ADDLrr((s2), (d)), ADDLrr((s1), (d)), LEALmr(0, (s1), (s2), 1, (d)) ) #define jit_addci_i(d, rs, is) jit_op_ ((d), (rs), ADDLir((is), (d)) ) #define jit_addcr_i(d, s1, s2) jit_opr_((d), (s1), (s2), ADDLrr((s1), (d)), ADDLrr((s2), (d)) ) #define jit_addxi_i(d, rs, is) jit_op_ ((d), (rs), ADCLir((is), (d)) ) #define jit_addxr_i(d, s1, s2) jit_opr_((d), (s1), (s2), ADCLrr((s1), (d)), ADCLrr((s2), (d)) ) #define jit_andi_i(d, rs, is) jit_op_ ((d), (rs), ANDLir((is), (d)) ) #define jit_andr_i(d, s1, s2) jit_opr_((d), (s1), (s2), ANDLrr((s1), (d)), ANDLrr((s2), (d)) ) #define jit_orr_i(d, s1, s2) jit_opr_((d), (s1), (s2), ORLrr((s1), (d)), ORLrr((s2), (d)) ) #define jit_subr_i(d, s1, s2) jit_opr_((d), (s1), (s2), (SUBLrr((s1), (d)), NEGLr(d)), SUBLrr((s2), (d)) ) #define jit_subcr_i(d, s1, s2) jit_subr_i((d), (s1), (s2)) #define jit_subxr_i(d, s1, s2) jit_opr_((d), (s1), (s2), SBBLrr((s1), (d)), SBBLrr((s2), (d)) ) #define jit_subxi_i(d, rs, is) jit_op_ ((d), (rs), SBBLir((is), (d)) ) #define jit_xorr_i(d, s1, s2) jit_opr_((d), (s1), (s2), XORLrr((s1), (d)), XORLrr((s2), (d)) ) /* These can sometimes use byte or word versions! */ #define jit_ori_i(d, rs, is) jit_op_ ((d), (rs), jit_reduce(OR, (is), (d)) ) #define jit_xori_i(d, rs, is) jit_op_ ((d), (rs), jit_reduce(XOR, (is), (d)) ) #define jit_muli_i(d, rs, is) jit_op_ ((d), (rs), IMULLir((is), (d)) ) #define jit_mulr_i(d, s1, s2) jit_opr_((d), (s1), (s2), IMULLrr((s1), (d)), IMULLrr((s2), (d)) ) /* As far as low bits are concerned, signed and unsigned multiplies are exactly the same. */ #define jit_muli_ui(d, rs, is) jit_op_ ((d), (rs), IMULLir((is), (d)) ) #define jit_mulr_ui(d, s1, s2) jit_opr_((d), (s1), (s2), IMULLrr((s1), (d)), IMULLrr((s2), (d)) ) #define jit_hmuli_i(d, rs, is) \ ((d) == _EDX ? ( PUSHLr(_EAX), jit_muli_i_((is), (rs)), POPLr(_EAX) ) : \ ((d) == _EAX ? (PUSHLr(_EDX), jit_muli_i_((is), (rs)), MOVLrr(_EDX, _EAX), POPLr(_EDX) ) : \ (PUSHLr(_EDX), PUSHLr(_EAX), jit_muli_i_((is), (rs)), MOVLrr(_EDX, (d)), POPLr(_EAX), POPLr(_EDX) ))) #define jit_hmulr_i(d, s1, s2) \ ((d) == _EDX ? ( PUSHLr(_EAX), jit_mulr_i_((s1), (s2)), POPLr(_EAX) ) : \ ((d) == _EAX ? (PUSHLr(_EDX), jit_mulr_i_((s1), (s2)), MOVLrr(_EDX, _EAX), POPLr(_EDX) ) : \ (PUSHLr(_EDX), PUSHLr(_EAX), jit_mulr_i_((s1), (s2)), MOVLrr(_EDX, (d)), POPLr(_EAX), POPLr(_EDX) ))) #define jit_hmuli_ui(d, rs, is) \ ((d) == _EDX ? ( PUSHLr(_EAX), jit_muli_ui_((is), (rs)), POPLr(_EAX) ) : \ ((d) == _EAX ? (PUSHLr(_EDX), jit_muli_ui_((is), (rs)), MOVLrr(_EDX, _EAX), POPLr(_EDX) ) : \ (PUSHLr(_EDX), PUSHLr(_EAX), jit_muli_ui_((is), (rs)), MOVLrr(_EDX, (d)), POPLr(_EAX), POPLr(_EDX) ))) #define jit_hmulr_ui(d, s1, s2) \ ((d) == _EDX ? ( PUSHLr(_EAX), jit_mulr_ui_((s1), (s2)), POPLr(_EAX) ) : \ ((d) == _EAX ? (PUSHLr(_EDX), jit_mulr_ui_((s1), (s2)), MOVLrr(_EDX, _EAX), POPLr(_EDX) ) : \ (PUSHLr(_EDX), PUSHLr(_EAX), jit_mulr_ui_((s1), (s2)), MOVLrr(_EDX, (d)), POPLr(_EAX), POPLr(_EDX) ))) #define jit_divi_i(d, rs, is) jit_divi_i_(_EAX, (d), (rs), (is)) #define jit_divi_ui(d, rs, is) jit_divi_ui_(_EAX, (d), (rs), (is)) #define jit_modi_i(d, rs, is) jit_divi_i_(_EDX, (d), (rs), (is)) #define jit_modi_ui(d, rs, is) jit_divi_ui_(_EDX, (d), (rs), (is)) #define jit_divr_i(d, s1, s2) jit_divr_i_(_EAX, (d), (s1), (s2)) #define jit_divr_ui(d, s1, s2) jit_divr_ui_(_EAX, (d), (s1), (s2)) #define jit_modr_i(d, s1, s2) jit_divr_i_(_EDX, (d), (s1), (s2)) #define jit_modr_ui(d, s1, s2) jit_divr_ui_(_EDX, (d), (s1), (s2)) /* Shifts */ #define jit_lshi_i(d, rs, is) ((is) <= 3 ? LEALmr(0, 0, (rs), 1 << (is), (d)) : jit_op_ ((d), (rs), SHLLir((is), (d)) )) #define jit_rshi_i(d, rs, is) jit_op_ ((d), (rs), SARLir((is), (d)) ) #define jit_rshi_ui(d, rs, is) jit_op_ ((d), (rs), SHRLir((is), (d)) ) #define jit_lshr_i(d, r1, r2) jit_replace((r1), (r2), _ECX, jit_op_ ((d), (r1), SHLLrr(_CL, (d)) )) #define jit_rshr_i(d, r1, r2) jit_replace((r1), (r2), _ECX, jit_op_ ((d), (r1), SARLrr(_CL, (d)) )) #define jit_rshr_ui(d, r1, r2) jit_replace((r1), (r2), _ECX, jit_op_ ((d), (r1), SHRLrr(_CL, (d)) )) /* Stack */ #define jit_pushr_i(rs) PUSHLr(rs) #define jit_popr_i(rs) POPLr(rs) #define jit_prepare_f(nf) (_jitl.argssize += (nf)) #define jit_prepare_d(nd) (_jitl.argssize += 2 * (nd)) #define jit_retval_i(rd) ((void)jit_movr_i ((rd), _EAX)) #define jit_arg_f() ((_jitl.framesize += sizeof(float)) - sizeof(float)) #define jit_arg_d() ((_jitl.framesize += sizeof(double)) - sizeof(double)) /* Unary */ #define jit_negr_i(d, rs) jit_opi_((d), (rs), NEGLr(d), (XORLrr((d), (d)), SUBLrr((rs), (d))) ) #define jit_movr_i(d, rs) ((void)((rs) == (d) ? 0 : MOVLrr((rs), (d)))) #define jit_movi_i(d, is) ((is) ? MOVLir((is), (d)) : XORLrr ((d), (d)) ) #define jit_movi_p(d, is) (jit_movi_l(d, ((long)(is))), _jit.x.pc) #define jit_patch_movi(pa,pv) (*_PSL((pa) - sizeof(long)) = _jit_SL((pv))) #define jit_ntoh_ui(d, rs) jit_op_((d), (rs), BSWAPLr(d)) #define jit_ntoh_us(d, rs) jit_op_((d), (rs), RORWir(8, d)) /* Boolean */ #define jit_ltr_i(d, s1, s2) jit_bool_r((d), (s1), (s2), SETLr ) #define jit_ler_i(d, s1, s2) jit_bool_r((d), (s1), (s2), SETLEr ) #define jit_gtr_i(d, s1, s2) jit_bool_r((d), (s1), (s2), SETGr ) #define jit_ger_i(d, s1, s2) jit_bool_r((d), (s1), (s2), SETGEr ) #define jit_eqr_i(d, s1, s2) jit_bool_r((d), (s1), (s2), SETEr ) #define jit_ner_i(d, s1, s2) jit_bool_r((d), (s1), (s2), SETNEr ) #define jit_ltr_ui(d, s1, s2) jit_bool_r((d), (s1), (s2), SETBr ) #define jit_ler_ui(d, s1, s2) jit_bool_r((d), (s1), (s2), SETBEr ) #define jit_gtr_ui(d, s1, s2) jit_bool_r((d), (s1), (s2), SETAr ) #define jit_ger_ui(d, s1, s2) jit_bool_r((d), (s1), (s2), SETAEr ) #define jit_lti_i(d, rs, is) jit_bool_i0((d), (rs), (is), SETLr, SETSr ) #define jit_lei_i(d, rs, is) jit_bool_i ((d), (rs), (is), SETLEr ) #define jit_gti_i(d, rs, is) jit_bool_i ((d), (rs), (is), SETGr ) #define jit_gei_i(d, rs, is) jit_bool_i0((d), (rs), (is), SETGEr, SETNSr ) #define jit_eqi_i(d, rs, is) jit_bool_i0((d), (rs), (is), SETEr, SETEr ) #define jit_nei_i(d, rs, is) jit_bool_i0((d), (rs), (is), SETNEr, SETNEr ) #define jit_lti_ui(d, rs, is) jit_bool_i ((d), (rs), (is), SETBr ) #define jit_lei_ui(d, rs, is) jit_bool_i0((d), (rs), (is), SETBEr, SETEr ) #define jit_gti_ui(d, rs, is) jit_bool_i0((d), (rs), (is), SETAr, SETNEr ) #define jit_gei_ui(d, rs, is) jit_bool_i0((d), (rs), (is), SETAEr, INCLr ) /* Jump */ #define jit_bltr_i(label, s1, s2) jit_bra_r((s1), (s2), JLm(label, 0,0,0) ) #define jit_bler_i(label, s1, s2) jit_bra_r((s1), (s2), JLEm(label,0,0,0) ) #define jit_bgtr_i(label, s1, s2) jit_bra_r((s1), (s2), JGm(label, 0,0,0) ) #define jit_bger_i(label, s1, s2) jit_bra_r((s1), (s2), JGEm(label,0,0,0) ) #define jit_beqr_i(label, s1, s2) jit_bra_r((s1), (s2), JEm(label, 0,0,0) ) #define jit_bner_i(label, s1, s2) jit_bra_r((s1), (s2), JNEm(label,0,0,0) ) #define jit_bltr_ui(label, s1, s2) jit_bra_r((s1), (s2), JBm(label, 0,0,0) ) #define jit_bler_ui(label, s1, s2) jit_bra_r((s1), (s2), JBEm(label,0,0,0) ) #define jit_bgtr_ui(label, s1, s2) jit_bra_r((s1), (s2), JAm(label, 0,0,0) ) #define jit_bger_ui(label, s1, s2) jit_bra_r((s1), (s2), JAEm(label,0,0,0) ) #define jit_bmsr_i(label, s1, s2) (TESTLrr((s1), (s2)), JNZm(label,0,0,0), _jit.x.pc) #define jit_bmcr_i(label, s1, s2) (TESTLrr((s1), (s2)), JZm(label,0,0,0), _jit.x.pc) #define jit_boaddr_i(label, s1, s2) (ADDLrr((s2), (s1)), JOm(label,0,0,0), _jit.x.pc) #define jit_bosubr_i(label, s1, s2) (SUBLrr((s2), (s1)), JOm(label,0,0,0), _jit.x.pc) #define jit_boaddr_ui(label, s1, s2) (ADDLrr((s2), (s1)), JCm(label,0,0,0), _jit.x.pc) #define jit_bosubr_ui(label, s1, s2) (SUBLrr((s2), (s1)), JCm(label,0,0,0), _jit.x.pc) #define jit_blti_i(label, rs, is) jit_bra_i0((rs), (is), JLm(label, 0,0,0), JSm(label, 0,0,0) ) #define jit_blei_i(label, rs, is) jit_bra_i ((rs), (is), JLEm(label,0,0,0) ) #define jit_bgti_i(label, rs, is) jit_bra_i ((rs), (is), JGm(label, 0,0,0) ) #define jit_bgei_i(label, rs, is) jit_bra_i0((rs), (is), JGEm(label,0,0,0), JNSm(label,0,0,0) ) #define jit_beqi_i(label, rs, is) jit_bra_i0((rs), (is), JEm(label, 0,0,0), JEm(label, 0,0,0) ) #define jit_bnei_i(label, rs, is) jit_bra_i0((rs), (is), JNEm(label,0,0,0), JNEm(label,0,0,0) ) #define jit_blti_ui(label, rs, is) jit_bra_i ((rs), (is), JBm(label, 0,0,0) ) #define jit_blei_ui(label, rs, is) jit_bra_i0((rs), (is), JBEm(label,0,0,0), JEm(label, 0,0,0) ) #define jit_bgti_ui(label, rs, is) jit_bra_i0((rs), (is), JAm(label, 0,0,0), JNEm(label,0,0,0) ) #define jit_bgei_ui(label, rs, is) jit_bra_i ((rs), (is), JAEm(label,0,0,0) ) #define jit_boaddi_i(label, rs, is) (ADDLir((is), (rs)), JOm(label,0,0,0), _jit.x.pc) #define jit_bosubi_i(label, rs, is) (SUBLir((is), (rs)), JOm(label,0,0,0), _jit.x.pc) #define jit_boaddi_ui(label, rs, is) (ADDLir((is), (rs)), JCm(label,0,0,0), _jit.x.pc) #define jit_bosubi_ui(label, rs, is) (SUBLir((is), (rs)), JCm(label,0,0,0), _jit.x.pc) #define jit_bmsi_i(label, rs, is) (jit_reduce(TEST, (is), (rs)), JNZm(label,0,0,0), _jit.x.pc) #define jit_bmci_i(label, rs, is) (jit_reduce(TEST, (is), (rs)), JZm(label,0,0,0), _jit.x.pc) #define jit_jmpi(label) (JMPm( ((unsigned long) (label)), 0, 0, 0), _jit.x.pc) #define jit_calli(label) (CALLm( ((unsigned long) (label)), 0, 0, 0), _jit.x.pc) #define jit_callr(reg) (CALLsr(reg)) #define jit_jmpr(reg) JMPsr(reg) /* Memory */ #define jit_ldi_c(d, is) MOVSBLmr((is), 0, 0, 0, (d)) #define jit_ldr_c(d, rs) MOVSBLmr(0, (rs), 0, 0, (d)) #define jit_ldxr_c(d, s1, s2) MOVSBLmr(0, (s1), (s2), 1, (d)) #define jit_ldxi_c(d, rs, is) MOVSBLmr((is), (rs), 0, 0, (d)) #define jit_ldi_uc(d, is) MOVZBLmr((is), 0, 0, 0, (d)) #define jit_ldr_uc(d, rs) MOVZBLmr(0, (rs), 0, 0, (d)) #define jit_ldxr_uc(d, s1, s2) MOVZBLmr(0, (s1), (s2), 1, (d)) #define jit_ldxi_uc(d, rs, is) MOVZBLmr((is), (rs), 0, 0, (d)) #define jit_sti_c(id, rs) jit_movbrm((rs), (id), 0, 0, 0) #define jit_str_c(rd, rs) jit_movbrm((rs), 0, (rd), 0, 0) #define jit_stxr_c(d1, d2, rs) jit_movbrm((rs), 0, (d1), (d2), 1) #define jit_stxi_c(id, rd, rs) jit_movbrm((rs), (id), (rd), 0, 0) #define jit_ldi_s(d, is) MOVSWLmr((is), 0, 0, 0, (d)) #define jit_ldr_s(d, rs) MOVSWLmr(0, (rs), 0, 0, (d)) #define jit_ldxr_s(d, s1, s2) MOVSWLmr(0, (s1), (s2), 1, (d)) #define jit_ldxi_s(d, rs, is) MOVSWLmr((is), (rs), 0, 0, (d)) #define jit_ldi_us(d, is) MOVZWLmr((is), 0, 0, 0, (d)) #define jit_ldr_us(d, rs) MOVZWLmr(0, (rs), 0, 0, (d)) #define jit_ldxr_us(d, s1, s2) MOVZWLmr(0, (s1), (s2), 1, (d)) #define jit_ldxi_us(d, rs, is) MOVZWLmr((is), (rs), 0, 0, (d)) #define jit_sti_s(id, rs) MOVWrm(jit_reg16(rs), (id), 0, 0, 0) #define jit_str_s(rd, rs) MOVWrm(jit_reg16(rs), 0, (rd), 0, 0) #define jit_stxr_s(d1, d2, rs) MOVWrm(jit_reg16(rs), 0, (d1), (d2), 1) #define jit_stxi_s(id, rd, rs) MOVWrm(jit_reg16(rs), (id), (rd), 0, 0) #define jit_ldi_i(d, is) MOVLmr((is), 0, 0, 0, (d)) #define jit_ldr_i(d, rs) MOVLmr(0, (rs), 0, 0, (d)) #define jit_ldxr_i(d, s1, s2) MOVLmr(0, (s1), (s2), 1, (d)) #define jit_ldxi_i(d, rs, is) MOVLmr((is), (rs), 0, 0, (d)) #define jit_sti_i(id, rs) MOVLrm((rs), (id), 0, 0, 0) #define jit_str_i(rd, rs) MOVLrm((rs), 0, (rd), 0, 0) #define jit_stxr_i(d1, d2, rs) MOVLrm((rs), 0, (d1), (d2), 1) #define jit_stxi_i(id, rd, rs) MOVLrm((rs), (id), (rd), 0, 0) /* Extra */ #define jit_nop() NOP_() #define _jit_alignment(pc, n) (((pc ^ _MASK(4)) + 1) & _MASK(n)) #define jit_align(n) NOPi(_jit_alignment(_jit_UL(_jit.x.pc), (n))) #endif /* __lightning_core_i386_h */ smalltalk-3.2.5/lightning/i386/core-32.h0000644000175000017500000000617512123404352014432 00000000000000/******************************** -*- C -*- **************************** * * Platform-independent layer (i386 version) * ***********************************************************************/ /*********************************************************************** * * Copyright 2000, 2001, 2002, 2003 Free Software Foundation, Inc. * Written by Paolo Bonzini. * * This file is part of GNU lightning. * * GNU lightning is free software; you can redistribute it and/or modify it * under the terms of the GNU Lesser General Public License as published * by the Free Software Foundation; either version 2.1, or (at your option) * any later version. * * GNU lightning is distributed in the hope that it will be useful, but * WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY * or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser General Public * License for more details. * * You should have received a copy of the GNU Lesser General Public License * along with GNU lightning; see the file COPYING.LESSER; if not, write to the * Free Software Foundation, 59 Temple Place - Suite 330, Boston, * MA 02111-1307, USA. * ***********************************************************************/ #ifndef __lightning_core_h #define __lightning_core_h #include "core-i386.h" #define JIT_CAN_16 1 struct jit_local_state { int framesize; int argssize; }; #define jit_base_prolog() (PUSHLr(_EBP), MOVLrr(_ESP, _EBP), PUSHLr(_EBX), PUSHLr(_ESI), PUSHLr(_EDI)) #define jit_prolog(n) (_jitl.framesize = 8, jit_base_prolog()) /* The += allows for stack pollution */ #ifdef __APPLE__ /* Stack must stay 16-byte aligned: */ # define jit_prepare_i(ni) (((ni & 0x3) \ ? SUBLir(4 * ((((ni) + 3) & ~(0x3)) - (ni)), JIT_SP) \ : (void)0), \ _jitl.argssize += (((ni) + 3) & ~(0x3))) #else # define jit_prepare_i(ni) (_jitl.argssize += (ni)) #endif #define jit_pusharg_i(rs) PUSHLr(rs) #define jit_finish(sub) ((void)jit_calli((sub)), ADDLir(sizeof(long) * _jitl.argssize, JIT_SP), _jitl.argssize = 0) #define jit_finishr(reg) (jit_callr((reg)), ADDLir(sizeof(long) * _jitl.argssize, JIT_SP), _jitl.argssize = 0) #define jit_arg_c() ((_jitl.framesize += sizeof(int)) - sizeof(int)) #define jit_arg_uc() ((_jitl.framesize += sizeof(int)) - sizeof(int)) #define jit_arg_s() ((_jitl.framesize += sizeof(int)) - sizeof(int)) #define jit_arg_us() ((_jitl.framesize += sizeof(int)) - sizeof(int)) #define jit_arg_i() ((_jitl.framesize += sizeof(int)) - sizeof(int)) #define jit_arg_ui() ((_jitl.framesize += sizeof(int)) - sizeof(int)) #define jit_arg_l() ((_jitl.framesize += sizeof(long)) - sizeof(long)) #define jit_arg_ul() ((_jitl.framesize += sizeof(long)) - sizeof(long)) #define jit_arg_p() ((_jitl.framesize += sizeof(long)) - sizeof(long)) #define jit_patch_long_at(jump_pc,v) (*_PSL((jump_pc) - sizeof(long)) = _jit_SL((jit_insn *)(v) - (jump_pc))) #define jit_patch_at(jump_pc,v) jit_patch_long_at(jump_pc, v) #define jit_ret() (POPLr(_EDI), POPLr(_ESI), POPLr(_EBX), POPLr(_EBP), RET_()) #endif /* __lightning_core_h */ smalltalk-3.2.5/lightning/i386/fp-64.h0000644000175000017500000000256512123404352014113 00000000000000/******************************** -*- C -*- **************************** * * Run-time assembler & support macros for the i386 math coprocessor * ***********************************************************************/ /*********************************************************************** * * Copyright 2000, 2001, 2002, 2004 Free Software Foundation, Inc. * Written by Paolo Bonzini. * * This file is part of GNU lightning. * * GNU lightning is free software; you can redistribute it and/or modify it * under the terms of the GNU Lesser General Public License as published * by the Free Software Foundation; either version 2.1, or (at your option) * any later version. * * GNU lightning is distributed in the hope that it will be useful, but * WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY * or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser General Public * License for more details. * * You should have received a copy of the GNU Lesser General Public License * along with GNU lightning; see the file COPYING.LESSER; if not, write to the * Free Software Foundation, 51 Franklin Street, Fifth Floor, Boston, * MA 02110-1301, USA. * ***********************************************************************/ #ifndef __lightning_fp_h #define __lightning_fp_h #warning SSE math not yet supported #endif /* __lightning_fp_h */ smalltalk-3.2.5/lightning/i386/fp-32.h0000644000175000017500000003506612123404352014110 00000000000000/******************************** -*- C -*- **************************** * * Run-time assembler & support macros for the i386 math coprocessor * ***********************************************************************/ /*********************************************************************** * * Copyright 2000, 2001, 2002, 2004 Free Software Foundation, Inc. * Written by Paolo Bonzini. * * This file is part of GNU lightning. * * GNU lightning is free software; you can redistribute it and/or modify it * under the terms of the GNU Lesser General Public License as published * by the Free Software Foundation; either version 2.1, or (at your option) * any later version. * * GNU lightning is distributed in the hope that it will be useful, but * WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY * or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser General Public * License for more details. * * You should have received a copy of the GNU Lesser General Public License * along with GNU lightning; see the file COPYING.LESSER; if not, write to the * Free Software Foundation, 51 Franklin Street, Fifth Floor, Boston, * MA 02110-1301, USA. * ***********************************************************************/ #ifndef __lightning_asm_fp_h #define __lightning_asm_fp_h /* We really must map the x87 stack onto a flat register file. In practice, we can provide something sensible and make it work on the x86 using the stack like a file of eight registers. We use six or seven registers so as to have some freedom for floor, ceil, round, (and log, tan, atn and exp). Not hard at all, basically play with FXCH. FXCH is mostly free, so the generated code is not bad. Of course we special case when one of the operands turns out to be ST0. Here are the macros that actually do the trick. */ #define JIT_FPR_NUM 6 #define JIT_FPR(i) (i) #define jit_fxch(rs, op) (((rs) != 0 ? FXCHr(rs) : 0), \ op, ((rs) != 0 ? FXCHr(rs) : 0)) #define jit_fp_unary(rd, s1, op) \ ((rd) == (s1) ? jit_fxch ((rd), op) \ : (rd) == 0 ? (FSTPr (0), FLDr ((s1)-1), op) \ : (FLDr ((s1)), op, FSTPr ((rd)))) #define jit_fp_binary(rd, s1, s2, op, opr) \ ((rd) == (s1) ? \ ((s2) == 0 ? opr(0, (rd)) \ : (s2) == (s1) ? jit_fxch((rd), op(0, 0)) \ : jit_fxch((rd), op((s2), 0))) \ : (rd) == (s2) ? jit_fxch((s1), opr(0, (rd) == 0 ? (s1) : (rd))) \ : (FLDr (s1), op(0, (s2)+1), FSTPr((rd)+1))) #define jit_addr_d(rd,s1,s2) jit_fp_binary((rd),(s1),(s2),FADDrr,FADDrr) #define jit_subr_d(rd,s1,s2) jit_fp_binary((rd),(s1),(s2),FSUBrr,FSUBRrr) #define jit_mulr_d(rd,s1,s2) jit_fp_binary((rd),(s1),(s2),FMULrr,FMULrr) #define jit_divr_d(rd,s1,s2) jit_fp_binary((rd),(s1),(s2),FDIVrr,FDIVRrr) #define jit_abs_d(rd,rs) jit_fp_unary ((rd), (rs), _OO (0xd9e1)) #define jit_negr_d(rd,rs) jit_fp_unary ((rd), (rs), _OO (0xd9e0)) #define jit_sqrt_d(rd,rs) jit_fp_unary ((rd), (rs), _OO (0xd9fa)) /* - moves: move FPR0 to FPR3 FST ST3 move FPR3 to FPR0 FXCH ST3 FST ST3 move FPR3 to FPR1 FLD ST3 FST ST2 Stack is rotated, so FPRn becomes STn+1 */ #define jit_movr_d(rd,s1) \ ((s1) == (rd) ? 0 \ : (s1) == 0 ? FSTr ((rd)) \ : (rd) == 0 ? (FXCHr ((s1)), FSTr ((s1))) \ : (FLDr ((s1)), FSTr ((rd)+1))) /* - loads: load into FPR0 FSTP ST0 FLD [FUBAR] load into FPR3 FSTP ST3 Save old st0 into destination register FLD [FUBAR] FXCH ST3 Get back old st0 (and similarly for immediates, using the stack) */ #define jit_movi_f(rd,immf) \ (_O (0x68), \ *((float *) _jit.x.pc) = (float) immf, \ _jit.x.uc_pc += sizeof (float), \ jit_ldr_f((rd), _ESP), \ ADDLir(4, _ESP)) union jit_double_imm { double d; int i[2]; }; #define jit_movi_d(rd,immd) \ (_O (0x68), \ _jit.x.uc_pc[4] = 0x68, \ ((union jit_double_imm *) (_jit.x.uc_pc + 5))->d = (double) immd, \ *((int *) _jit.x.uc_pc) = ((union jit_double_imm *) (_jit.x.uc_pc + 5))->i[1], \ _jit.x.uc_pc += 9, \ jit_ldr_d((rd), _ESP), \ ADDLir(8, _ESP)) #define jit_ldi_f(rd, is) \ ((rd) == 0 ? (FSTPr (0), FLDSm((is), 0, 0, 0)) \ : (FLDSm((is), 0, 0, 0), FSTPr ((rd) + 1))) #define jit_ldi_d(rd, is) \ ((rd) == 0 ? (FSTPr (0), FLDLm((is), 0, 0, 0)) \ : (FLDLm((is), 0, 0, 0), FSTPr ((rd) + 1))) #define jit_ldr_f(rd, rs) \ ((rd) == 0 ? (FSTPr (0), FLDSm(0, (rs), 0, 0)) \ : (FLDSm(0, (rs), 0, 0), FSTPr ((rd) + 1))) #define jit_ldr_d(rd, rs) \ ((rd) == 0 ? (FSTPr (0), FLDLm(0, (rs), 0, 0)) \ : (FLDLm(0, (rs), 0, 0), FSTPr ((rd) + 1))) #define jit_ldxi_f(rd, rs, is) \ ((rd) == 0 ? (FSTPr (0), FLDSm((is), (rs), 0, 0)) \ : (FLDSm((is), (rs), 0, 0), FSTPr ((rd) + 1))) #define jit_ldxi_d(rd, rs, is) \ ((rd) == 0 ? (FSTPr (0), FLDLm((is), (rs), 0, 0)) \ : (FLDLm((is), (rs), 0, 0), FSTPr ((rd) + 1))) #define jit_ldxr_f(rd, s1, s2) \ ((rd) == 0 ? (FSTPr (0), FLDSm(0, (s1), (s2), 1)) \ : (FLDSm(0, (s1), (s2), 1), FSTPr ((rd) + 1))) #define jit_ldxr_d(rd, s1, s2) \ ((rd) == 0 ? (FSTPr (0), FLDLm(0, (s1), (s2), 1)) \ : (FLDLm(0, (s1), (s2), 1), FSTPr ((rd) + 1))) #define jit_extr_i_d(rd, rs) (PUSHLr((rs)), \ ((rd) == 0 ? (FSTPr (0), FILDLm(0, _ESP, 0, 0)) \ : (FILDLm(0, _ESP, 0, 0), FSTPr ((rd) + 1))), \ POPLr((rs))) #define jit_stxi_f(id, rd, rs) jit_fxch ((rs), FSTSm((id), (rd), 0, 0)) #define jit_stxr_f(d1, d2, rs) jit_fxch ((rs), FSTSm(0, (d1), (d2), 1)) #define jit_stxi_d(id, rd, rs) jit_fxch ((rs), FSTLm((id), (rd), 0, 0)) #define jit_stxr_d(d1, d2, rs) jit_fxch ((rs), FSTLm(0, (d1), (d2), 1)) #define jit_sti_f(id, rs) jit_fxch ((rs), FSTSm((id), 0, 0, 0)) #define jit_str_f(rd, rs) jit_fxch ((rs), FSTSm(0, (rd), 0, 0)) #define jit_sti_d(id, rs) jit_fxch ((rs), FSTLm((id), 0, 0, 0)) #define jit_str_d(rd, rs) jit_fxch ((rs), FSTLm(0, (rd), 0, 0)) /* Assume round to near mode */ #define jit_floorr_d_i(rd, rs) \ (FLDr (rs), jit_floor2((rd), ((rd) == _EDX ? _EAX : _EDX))) #define jit_ceilr_d_i(rd, rs) \ (FLDr (rs), jit_ceil2((rd), ((rd) == _EDX ? _EAX : _EDX))) #define jit_truncr_d_i(rd, rs) \ (FLDr (rs), jit_trunc2((rd), ((rd) == _EDX ? _EAX : _EDX))) #define jit_calc_diff(ofs) \ FISTLm(ofs, _ESP, 0, 0), \ FILDLm(ofs, _ESP, 0, 0), \ FSUBRPr(1), \ FSTPSm(4+ofs, _ESP, 0, 0) \ /* The real meat */ #define jit_floor2(rd, aux) \ (PUSHLr(aux), \ SUBLir(8, _ESP), \ jit_calc_diff(0), \ POPLr(rd), /* floor in rd */ \ POPLr(aux), /* x-round(x) in aux */ \ ADDLir(0x7FFFFFFF, aux), /* carry if x-round(x) < -0 */ \ SBBLir(0, rd), /* subtract 1 if carry */ \ POPLr(aux)) #define jit_ceil2(rd, aux) \ (PUSHLr(aux), \ SUBLir(8, _ESP), \ jit_calc_diff(0), \ POPLr(rd), /* floor in rd */ \ POPLr(aux), /* x-round(x) in aux */ \ TESTLrr(aux, aux), \ SETGr(jit_reg8(aux)), \ SHRLir(1, aux), \ ADCLir(0, rd), \ POPLr(aux)) /* a mingling of the two above */ #define jit_trunc2(rd, aux) \ (PUSHLr(aux), \ SUBLir(12, _ESP), \ FSTSm(0, _ESP, 0, 0), \ jit_calc_diff(4), \ POPLr(aux), \ POPLr(rd), \ TESTLrr(aux, aux), \ POPLr(aux), \ JSSm(_jit.x.pc + 11, 0, 0, 0), \ ADDLir(0x7FFFFFFF, aux), /* 6 */ \ SBBLir(0, rd), /* 3 */ \ JMPSm(_jit.x.pc + 10, 0, 0, 0), /* 2 */ \ TESTLrr(aux, aux), /* 2 */ \ SETGr(jit_reg8(aux)), /* 3 */ \ SHRLir(1, aux), /* 2 */ \ ADCLir(0, rd), /* 3 */ \ POPLr(aux)) /* the easy one */ #define jit_roundr_d_i(rd, rs) \ (PUSHLr(_EAX), \ jit_fxch ((rs), FISTPLm(0, _ESP, 0, 0)), \ POPLr((rd))) #define jit_fp_test(d, s1, s2, n, _and, res) \ (((s1) == 0 ? FUCOMr((s2)) : (FLDr((s1)), FUCOMPr((s2) + 1))), \ ((d) != _EAX ? MOVLrr(_EAX, (d)) : 0), \ FNSTSWr(_EAX), \ SHRLir(n, _EAX), \ ((_and) ? ANDLir((_and), _EAX) : MOVLir(0, _EAX)), \ res, \ ((d) != _EAX ? _O (0x90 + ((d) & 7)) : 0)) /* xchg */ #define jit_fp_btest(d, s1, s2, n, _and, cmp, res) \ (((s1) == 0 ? FUCOMr((s2)) : (FLDr((s1)), FUCOMPr((s2) + 1))), \ PUSHLr(_EAX), \ FNSTSWr(_EAX), \ SHRLir(n, _EAX), \ ((_and) ? ANDLir ((_and), _EAX) : 0), \ ((cmp) ? CMPLir ((cmp), _AL) : 0), \ POPLr(_EAX), \ res ((d), 0, 0, 0)) #define jit_nothing_needed(x) /* After FNSTSW we have 1 if <, 40 if =, 0 if >, 45 if unordered. Here is how to map the values of the status word's high byte to the conditions. < = > unord valid values condition gt no no yes no 0 STSW & 45 == 0 lt yes no no no 1 STSW & 45 == 1 eq no yes no no 40 STSW & 45 == 40 unord no no no yes 45 bit 2 == 1 ge no yes no no 0, 40 bit 0 == 0 unlt yes no no yes 1, 45 bit 0 == 1 ltgt yes no yes no 0, 1 bit 6 == 0 uneq no yes no yes 40, 45 bit 6 == 1 le yes yes no no 1, 40 odd parity for STSW & 41 ungt no no yes yes 0, 45 even parity for STSW & 41 unle yes yes no yes 1, 40, 45 STSW & 45 != 0 unge no yes yes yes 0, 40, 45 STSW & 45 != 1 ne yes no yes yes 0, 1, 45 STSW & 45 != 40 ord yes yes yes no 0, 1, 40 bit 2 == 0 lt, le, ungt, unge are actually computed as gt, ge, unlt, unle with the operands swapped; it is more efficient this way. */ #define jit_gtr_d(d, s1, s2) jit_fp_test((d), (s1), (s2), 8, 0x45, SETZr (_AL)) #define jit_ger_d(d, s1, s2) jit_fp_test((d), (s1), (s2), 9, 0, SBBBir (-1, _AL)) #define jit_unler_d(d, s1, s2) jit_fp_test((d), (s1), (s2), 8, 0x45, SETNZr (_AL)) #define jit_unltr_d(d, s1, s2) jit_fp_test((d), (s1), (s2), 9, 0, ADCBir (0, _AL)) #define jit_ltr_d(d, s1, s2) jit_fp_test((d), (s2), (s1), 8, 0x45, SETZr (_AL)) #define jit_ler_d(d, s1, s2) jit_fp_test((d), (s2), (s1), 9, 0, SBBBir (-1, _AL)) #define jit_unger_d(d, s1, s2) jit_fp_test((d), (s2), (s1), 8, 0x45, SETNZr (_AL)) #define jit_ungtr_d(d, s1, s2) jit_fp_test((d), (s2), (s1), 9, 0, ADCBir (0, _AL)) #define jit_eqr_d(d, s1, s2) jit_fp_test((d), (s1), (s2), 8, 0x45, (CMPBir (0x40, _AL), SETEr (_AL))) #define jit_ner_d(d, s1, s2) jit_fp_test((d), (s1), (s2), 8, 0x45, (CMPBir (0x40, _AL), SETNEr (_AL))) #define jit_ltgtr_d(d, s1, s2) jit_fp_test((d), (s1), (s2), 15, 0, SBBBir (-1, _AL)) #define jit_uneqr_d(d, s1, s2) jit_fp_test((d), (s1), (s2), 15, 0, ADCBir (0, _AL)) #define jit_ordr_d(d, s1, s2) jit_fp_test((d), (s1), (s2), 11, 0, SBBBir (-1, _AL)) #define jit_unordr_d(d, s1, s2) jit_fp_test((d), (s1), (s2), 11, 0, ADCBir (0, _AL)) #define jit_bgtr_d(d, s1, s2) jit_fp_btest((d), (s1), (s2), 8, 0x45, 0, JZm) #define jit_bger_d(d, s1, s2) jit_fp_btest((d), (s1), (s2), 9, 0, 0, JNCm) #define jit_bunler_d(d, s1, s2) jit_fp_btest((d), (s1), (s2), 8, 0x45, 0, JNZm) #define jit_bunltr_d(d, s1, s2) jit_fp_btest((d), (s1), (s2), 9, 0, 0, JCm) #define jit_bltr_d(d, s1, s2) jit_fp_btest((d), (s2), (s1), 8, 0x45, 0, JZm) #define jit_bler_d(d, s1, s2) jit_fp_btest((d), (s2), (s1), 9, 0, 0, JNCm) #define jit_bunger_d(d, s1, s2) jit_fp_btest((d), (s2), (s1), 8, 0x45, 0, JNZm) #define jit_bungtr_d(d, s1, s2) jit_fp_btest((d), (s2), (s1), 9, 0, 0, JCm) #define jit_beqr_d(d, s1, s2) jit_fp_btest((d), (s1), (s2), 8, 0x45, 0x40, JZm) #define jit_bner_d(d, s1, s2) jit_fp_btest((d), (s1), (s2), 8, 0x45, 0x40, JNZm) #define jit_bltgtr_d(d, s1, s2) jit_fp_btest((d), (s1), (s2), 15, 0, 0, JNCm) #define jit_buneqr_d(d, s1, s2) jit_fp_btest((d), (s1), (s2), 15, 0, 0, JCm) #define jit_bordr_d(d, s1, s2) jit_fp_btest((d), (s1), (s2), 11, 0, 0, JNCm) #define jit_bunordr_d(d, s1, s2) jit_fp_btest((d), (s1), (s2), 11, 0, 0, JCm) #define jit_getarg_f(rd, ofs) jit_ldxi_f((rd), JIT_FP,(ofs)) #define jit_getarg_d(rd, ofs) jit_ldxi_d((rd), JIT_FP,(ofs)) #define jit_pusharg_d(rs) (jit_subi_i(JIT_SP,JIT_SP,sizeof(double)), jit_str_d(JIT_SP,(rs))) #define jit_pusharg_f(rs) (jit_subi_i(JIT_SP,JIT_SP,sizeof(float)), jit_str_f(JIT_SP,(rs))) #define jit_retval_d(op1) jit_movr_d(0, (op1)) #if 0 #define jit_sin() _OO(0xd9fe) /* fsin */ #define jit_cos() _OO(0xd9ff) /* fcos */ #define jit_tan() (_OO(0xd9f2), /* fptan */ \ FSTPr(0)) /* fstp st */ #define jit_atn() (_OO(0xd9e8), /* fld1 */ \ _OO(0xd9f3)) /* fpatan */ #define jit_exp() (_OO(0xd9ea), /* fldl2e */ \ FMULPr(1), /* fmulp */ \ _OO(0xd9c0), /* fld st */ \ _OO(0xd9fc), /* frndint */ \ _OO(0xdce9), /* fsubr */ \ FXCHr(1), /* fxch st(1) */ \ _OO(0xd9f0), /* f2xm1 */ \ _OO(0xd9e8), /* fld1 */ \ _OO(0xdec1), /* faddp */ \ _OO(0xd9fd), /* fscale */ \ FSTPr(1)) /* fstp st(1) */ #define jit_log() (_OO(0xd9ed), /* fldln2 */ \ FXCHr(1), /* fxch st(1) */ \ _OO(0xd9f1)) /* fyl2x */ #endif #endif /* __lightning_asm_h */ smalltalk-3.2.5/lightning/lightning.h0000644000175000017500000000327712123404352014552 00000000000000/******************************** -*- C -*- **************************** * * lightning main include file * ***********************************************************************/ /*********************************************************************** * * Copyright 2000 Free Software Foundation, Inc. * Written by Paolo Bonzini. * * This file is part of GNU lightning. * * GNU lightning is free software; you can redistribute it and/or modify it * under the terms of the GNU Lesser General Public License as published * by the Free Software Foundation; either version 2.1, or (at your option) * any later version. * * GNU lightning is distributed in the hope that it will be useful, but * WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY * or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser General Public * License for more details. * * You should have received a copy of the GNU Lesser General Public License * along with GNU lightning; see the file COPYING.LESSER; if not, write to the * Free Software Foundation, 51 Franklin Street, Fifth Floor, Boston, * MA 02110-1301, USA. * ***********************************************************************/ #ifndef __lightning_h #define __lightning_h #ifdef __cplusplus extern "C" { #endif #include #ifndef LIGHTNING_DEBUG #include #endif #include #include #include #include #include #include #ifndef JIT_R0 #error GNU lightning does not support the current target #endif #ifdef __cplusplus } #endif #endif /* __lightning_h */ smalltalk-3.2.5/lightning/sparc/0000755000175000017500000000000012130456003013573 500000000000000smalltalk-3.2.5/lightning/sparc/asm.h0000644000175000017500000004122012123404352014445 00000000000000/******************************** -*- C -*- **************************** * * Run-time assembler for the SPARC * ***********************************************************************/ /*********************************************************************** * * Copyright 1999, 2000, 2001, 2002 Ian Piumarta * * This file is part of GNU lightning. * * GNU lightning is free software; you can redistribute it and/or modify it * under the terms of the GNU Lesser General Public License as published * by the Free Software Foundation; either version 2.1, or (at your option) * any later version. * * GNU lightning is distributed in the hope that it will be useful, but * WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY * or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser General Public * License for more details. * * You should have received a copy of the GNU Lesser General Public License * along with GNU lightning; see the file COPYING.LESSER; if not, write to the * Free Software Foundation, 51 Franklin Street, Fifth Floor, Boston, * MA 02110-1301, USA. * ***********************************************************************/ #ifndef __lightning_asm_h #define __lightning_asm_h /* = [0-9]+ -> add i, one parameter (imm) * = % -> add r, one parameter (imm or _Rr(imm) ) * %g -> add r, one parameter (imm or _Rg(imm) ) * %o -> add r, one parameter (imm+8 or _Ro(imm) ) * %l -> add r, one parameter (imm+16 or _Rl(imm) ) * %i -> add r, one parameter (imm+24 or _Ri(imm) ) * = () -> add m, two parameters (reg,imm) * = () -> add x, two parameters (reg,reg) */ typedef unsigned int jit_insn; #ifndef LIGHTNING_DEBUG #define _d30(BD) ((_jit_UL(BD) - _jit_UL(_jit.x.pc))>>2) #define _d22(BD) _ck_d(22, _d30(BD)) #define _HI(I) (_jit_UL(I) >> (10)) #define _LO(I) (_jit_UL(I) & _MASK(10)) /* register names */ #define _y 0 #define _psr 1 #define _Rr(N) ( 0+(N)) #define _Rg(N) ( 0+(N)) #define _Ro(N) ( 8+(N)) #define _Rl(N) (16+(N)) #define _Ri(N) (24+(N)) /* instruction formats -- Figure 5-1, page 44 in */ /* SPARC International, "The SPARC Architecture Manual, Version 8", Prentice-Hall, 1992. */ #define _0i(RD, OP2, IMM) _jit_I((0<<30)| (_u5(RD)<<25)|(_u3(OP2)<<22)| _u22(IMM)) #define _0( A, CC, OP2, DSP) _jit_I((0<<30)|(_u1(A)<<29)|(_u4(CC)<<25)|(_u3(OP2)<<22)| _d22(DSP)) #define _0d( A, CC, OP2, DSP) _jit_I((0<<30)|(_u1(A)<<29)|(_u4(CC)<<25)|(_u3(OP2)<<22)| _u22(DSP)) #define _1( DSP) _jit_I((1<<30)| _d30(DSP)) #define _2( RD, OP3, RS1, I, ASI, RS2) _jit_I((2<<30)| (_u5(RD)<<25)|(_u6(OP3)<<19)|(_u5(RS1)<<14)|(_u1(I)<<13)|(_u8(ASI)<<5)|_u5 (RS2)) #define _2i(RD, OP3, RS1, I, IMM) _jit_I((2<<30)| (_u5(RD)<<25)|(_u6(OP3)<<19)|(_u5(RS1)<<14)|(_u1(I)<<13)| _s13(IMM)) #define _2f(RD, OP3, RS1, OPF, RS2) _jit_I((2<<30)| (_u5(RD)<<25)|(_u6(OP3)<<19)|(_u5(RS1)<<14)| (_u9(OPF)<<5)|_u5 (RS2)) #define _3( RD, OP3, RS1, I, ASI, RS2) _jit_I((3<<30)| (_u5(RD)<<25)|(_u6(OP3)<<19)|(_u5(RS1)<<14)|(_u1(I)<<13)|(_u8(ASI)<<5)|_u5 (RS2)) #define _3i(RD, OP3, RS1, I, IMM) _jit_I((3<<30)| (_u5(RD)<<25)|(_u6(OP3)<<19)|(_u5(RS1)<<14)|(_u1(I)<<13)| _s13(IMM)) #define _FP1(RD, RS1, OPF, RS2) _2f((RD), 52, (RS1), (OPF), (RS2)) #define _FP2(RD, RS1, OPF, RS2) _2f((RD), 53, (RS1), (OPF), (RS2)) /* basic instructions [Section B, page 87] */ #define ADDrrr(RS1, RS2, RD) _2 ((RD), 0, (RS1), 0, 0, (RS2)) #define ADDrir(RS1, IMM, RD) _2i ((RD), 0, (RS1), 1, (IMM)) #define ADDCCrrr(RS1, RS2, RD) _2 ((RD), 16, (RS1), 0, 0, (RS2)) #define ADDCCrir(RS1, IMM, RD) _2i ((RD), 16, (RS1), 1, (IMM)) #define ADDXrrr(RS1, RS2, RD) _2 ((RD), 8, (RS1), 0, 0, (RS2)) #define ADDXrir(RS1, IMM, RD) _2i ((RD), 8, (RS1), 1, (IMM)) #define ADDXCCrrr(RS1, RS2, RD) _2 ((RD), 24, (RS1), 0, 0, (RS2)) #define ADDXCCrir(RS1, IMM, RD) _2i ((RD), 24, (RS1), 1, (IMM)) #define ANDrrr(RS1, RS2, RD) _2 ((RD), 1, (RS1), 0, 0, (RS2)) #define ANDrir(RS1, IMM, RD) _2i ((RD), 1, (RS1), 1, (IMM)) #define ANDCCrrr(RS1, RS2, RD) _2 ((RD), 17, (RS1), 0, 0, (RS2)) #define ANDCCrir(RS1, IMM, RD) _2i ((RD), 17, (RS1), 1, (IMM)) #define BNi(DISP) _0 (0, 0, 2, (DISP)) #define BN_Ai(DISP) _0 (1, 0, 2, (DISP)) #define BEi(DISP) _0 (0, 1, 2, (DISP)) #define BE_Ai(DISP) _0 (1, 1, 2, (DISP)) #define BLEi(DISP) _0 (0, 2, 2, (DISP)) #define BLE_Ai(DISP) _0 (1, 2, 2, (DISP)) #define BLi(DISP) _0 (0, 3, 2, (DISP)) #define BL_Ai(DISP) _0 (1, 3, 2, (DISP)) #define BLEUi(DISP) _0 (0, 4, 2, (DISP)) #define BLEU_Ai(DISP) _0 (1, 4, 2, (DISP)) #define BCSi(DISP) _0 (0, 5, 2, (DISP)) #define BCS_Ai(DISP) _0 (1, 5, 2, (DISP)) #define BNEGi(DISP) _0 (0, 6, 2, (DISP)) #define BNEG_Ai(DISP) _0 (1, 6, 2, (DISP)) #define BVSi(DISP) _0 (0, 7, 2, (DISP)) #define BVS_Ai(DISP) _0 (1, 7, 2, (DISP)) #define BAi(DISP) _0 (0, 8, 2, (DISP)) #define BA_Ai(DISP) _0 (1, 8, 2, (DISP)) #define BNEi(DISP) _0 (0, 9, 2, (DISP)) #define BNE_Ai(DISP) _0 (1, 9, 2, (DISP)) #define BGi(DISP) _0 (0, 10, 2, (DISP)) #define BG_Ai(DISP) _0 (1, 10, 2, (DISP)) #define BGEi(DISP) _0 (0, 11, 2, (DISP)) #define BGE_Ai(DISP) _0 (1, 11, 2, (DISP)) #define BGUi(DISP) _0 (0, 12, 2, (DISP)) #define BGU_Ai(DISP) _0 (1, 12, 2, (DISP)) #define BCCi(DISP) _0 (0, 13, 2, (DISP)) #define BCC_Ai(DISP) _0 (1, 13, 2, (DISP)) #define BPOSi(DISP) _0 (0, 14, 2, (DISP)) #define BPOS_Ai(DISP) _0 (1, 14, 2, (DISP)) #define BVCi(DISP) _0 (0, 15, 2, (DISP)) #define BVC_Ai(DISP) _0 (1, 15, 2, (DISP)) #define CALLi(DISP) _1 ((DISP)) #define FLUSHrr(RS1, RS2) _2 (0, 0x3b, (RS1), 0, 0, (RS2)) #define FLUSHir(IMM, RS1) _2i (0, 0x3b, (RS1), 1, (IMM)) #define JMPLxr(RS1, RS2, RD) _2 ((RD), 56, (RS1), 0, 0, (RS2)) #define JMPLmr(RS1, IMM, RD) _2i ((RD), 56, (RS1), 1, (IMM)) #define LDxr(RS1, RS2, RD) _3 ((RD), 0, (RS1), 0, 0, (RS2)) #define LDmr(RS1, IMM, RD) _3i ((RD), 0, (RS1), 1, (IMM)) #define LDUBxr(RS1, RS2, RD) _3 ((RD), 1, (RS1), 0, 0, (RS2)) #define LDUBmr(RS1, IMM, RD) _3i ((RD), 1, (RS1), 1, (IMM)) #define LDUHxr(RS1, RS2, RD) _3 ((RD), 2, (RS1), 0, 0, (RS2)) #define LDUHmr(RS1, IMM, RD) _3i ((RD), 2, (RS1), 1, (IMM)) #define LDDxr(RS1, RS2, RD) _3 ((RD), 3, (RS1), 0, 0, (RS2)) #define LDDmr(RS1, IMM, RD) _3i ((RD), 3, (RS1), 1, (IMM)) #define LDSBxr(RS1, RS2, RD) _3 ((RD), 9, (RS1), 0, 0, (RS2)) #define LDSBmr(RS1, IMM, RD) _3i ((RD), 9, (RS1), 1, (IMM)) #define LDSHxr(RS1, RS2, RD) _3 ((RD), 10, (RS1), 0, 0, (RS2)) #define LDSHmr(RS1, IMM, RD) _3i ((RD), 10, (RS1), 1, (IMM)) #define ORrrr(RS1, RS2, RD) _2 ((RD), 2, (RS1), 0, 0, (RS2)) #define ORrir(RS1, IMM, RD) _2i ((RD), 2, (RS1), 1, (IMM)) #define ORCCrrr(RS1, RS2, RD) _2 ((RD), 18, (RS1), 0, 0, (RS2)) #define ORCCrir(RS1, IMM, RD) _2i ((RD), 18, (RS1), 1, (IMM)) #define RDir(RS, RD) _2 ((RD), (RS)|0x28, 0, 0, 0,0) #define RESTORErrr(RS1, RS2, RD) _2 ((RD), 61, (RS1), 0, 0, (RS2)) #define RESTORErir(RS1, IMM, RD) _2i ((RD), 61, (RS1), 1, (IMM)) #define SAVErrr(RS1, RS2, RD) _2 ((RD), 60, (RS1), 0, 0, (RS2)) #define SAVErir(RS1, IMM, RD) _2i ((RD), 60, (RS1), 1, (IMM)) #define SDIVrrr(RS1, RS2, RD) _2 ((RD), 15, (RS1), 0, 0, (RS2)) #define SDIVrir(RS1, IMM, RD) _2i ((RD), 15, (RS1), 1, (IMM)) #define SDIVCCrrr(RS1, RS2, RD) _2 ((RD), 31, (RS1), 0, 0, (RS2)) #define SDIVCCrir(RS1, IMM, RD) _2i ((RD), 31, (RS1), 1, (IMM)) #define SETHIir(IMM, RD) _0i ((RD), 4, (IMM)) #define SLLrrr(RS1, RS2, RD) _2 ((RD), 37, (RS1), 0, 0, (RS2)) #define SLLrir(RS1, IMM, RD) _2i ((RD), 37, (RS1), 1, (IMM)) #define SMULrrr(RS1, RS2, RD) _2 ((RD), 11, (RS1), 0, 0, (RS2)) #define SMULrir(RS1, IMM, RD) _2i ((RD), 11, (RS1), 1, (IMM)) #define SMULCCrrr(RS1, RS2, RD) _2 ((RD), 27, (RS1), 0, 0, (RS2)) #define SMULCCrir(RS1, IMM, RD) _2i ((RD), 27, (RS1), 1, (IMM)) #define SRArrr(RS1, RS2, RD) _2 ((RD), 39, (RS1), 0, 0, (RS2)) #define SRArir(RS1, IMM, RD) _2i ((RD), 39, (RS1), 1, (IMM)) #define SRLrrr(RS1, RS2, RD) _2 ((RD), 38, (RS1), 0, 0, (RS2)) #define SRLrir(RS1, IMM, RD) _2i ((RD), 38, (RS1), 1, (IMM)) #define STrx(RS, RD1, RD2) _3 ((RS), 4, (RD1), 0, 0, (RD2)) #define STrm(RS, RD, IMM) _3i ((RS), 4, (RD), 1, (IMM)) #define STBrx(RS, RD1, RD2) _3 ((RS), 5, (RD1), 0, 0, (RD2)) #define STBrm(RS, RD, IMM) _3i ((RS), 5, (RD), 1, (IMM)) #define STBAR() _0i (0, 0x28, 15, 0, 0) #define STHrx(RS, RD1, RD2) _3 ((RS), 6, (RD1), 0, 0, (RD2)) #define STHrm(RS, RD, IMM) _3i ((RS), 6, (RD), 1, (IMM)) #define STDrx(RS, RD1, RD2) _3 ((RS), 7, (RD1), 0, 0, (RD2)) #define STDrm(RS, RD, IMM) _3i ((RS), 7, (RD), 1, (IMM)) #define SUBrrr(RS1, RS2, RD) _2 ((RD), 4, (RS1), 0, 0, (RS2)) #define SUBrir(RS1, IMM, RD) _2i ((RD), 4, (RS1), 1, (IMM)) #define SUBCCrrr(RS1, RS2, RD) _2 ((RD), 20, (RS1), 0, 0, (RS2)) #define SUBCCrir(RS1, IMM, RD) _2i ((RD), 20, (RS1), 1, (IMM)) #define SUBXrrr(RS1, RS2, RD) _2 ((RD), 12, (RS1), 0, 0, (RS2)) #define SUBXrir(RS1, IMM, RD) _2i ((RD), 12, (RS1), 1, (IMM)) #define SUBXCCrrr(RS1, RS2, RD) _2 ((RD), 28, (RS1), 0, 0, (RS2)) #define SUBXCCrir(RS1, IMM, RD) _2i ((RD), 28, (RS1), 1, (IMM)) #define UDIVrrr(RS1, RS2, RD) _2 ((RD), 14, (RS1), 0, 0, (RS2)) #define UDIVrir(RS1, IMM, RD) _2i ((RD), 14, (RS1), 1, (IMM)) #define UDIVCCrrr(RS1, RS2, RD) _2 ((RD), 30, (RS1), 0, 0, (RS2)) #define UDIVCCrir(RS1, IMM, RD) _2i ((RD), 30, (RS1), 1, (IMM)) #define UMULrrr(RS1, RS2, RD) _2 ((RD), 10, (RS1), 0, 0, (RS2)) #define UMULrir(RS1, IMM, RD) _2i ((RD), 10, (RS1), 1, (IMM)) #define UMULCCrrr(RS1, RS2, RD) _2 ((RD), 26, (RS1), 0, 0, (RS2)) #define UMULCCrir(RS1, IMM, RD) _2i ((RD), 26, (RS1), 1, (IMM)) #define WRrri(RS1, RS2, RD) _2 (0, (RD)|0x30, RS1, 0, 0, (RS2)) #define WRrii(RS1, IMM, RD) _2i (0, (RD)|0x30, RS1, 1, (IMM)) #define XORrrr(RS1, RS2, RD) _2 ((RD), 3, (RS1), 0, 0, (RS2)) #define XORrir(RS1, IMM, RD) _2i ((RD), 3, (RS1), 1, (IMM)) #define XORCCrrr(RS1, RS2, RD) _2 ((RD), 19, (RS1), 0, 0, (RS2)) #define XORCCrir(RS1, IMM, RD) _2i ((RD), 19, (RS1), 1, (IMM)) /* synonyms */ #define Bi(DISP) BAi((DISP)) #define B_Ai(DISP) BA_Ai((DISP)) #define BNZi(DISP) BNEi((DISP)) #define BNZ_Ai(DISP) BNE_Ai((DISP)) #define BZi(DISP) BEi((DISP)) #define BZ_Ai(DISP) BE_Ai((DISP)) #define BGEUi(DISP) BCCi((DISP)) #define BGEU_Ai(DISP) BCC_Ai((DISP)) #define BLUi(DISP) BCSi((DISP)) #define BLU_Ai(DISP) BCS_Ai((DISP)) #define LDUWxr(RS1, RS2, RD) LDxr((RS1), (RS2), (RD)) #define LDUWmr(RS1, IMM, RD) LDmr((RS1), (IMM), (RD)) #define LDSWxr(RS1, RS2, RD) LDxr((RS1), (RS2), (RD)) #define LDSWmr(RS1, IMM, RD) LDmr((RS1), (IMM), (RD)) #define STWrx(RS, RD1, RD2) STrx((RS), (RD1), (RD2)) #define STWrm(RS, RD, IMM) STrm((RS), (RD), (IMM)) /* synthetic instructions [Table A-1, page 85] */ #define BCLRrr(R,S) ANDNrrr((R), (S), (S)) #define BCLRir(I,R) ANDNrir((R), (I), (R)) #define BSETrr(R,S) ORrrr((R), (S), (S)) #define BSETir(I,R) ORrir((R), (I), (R)) #define BTOGrr(R,S) XORrrr((R), (S), (S)) #define BTOGir(I,R) XORrir((R), (I), (R)) #define BTSTrr(R,S) ANDCCrrr((R), (S), 0) #define BTSTir(I,R) ANDCCrir((R), (I), 0) #define CALLm(R,I) JMPLmr((R), (I), _Ro(7)) #define CALLx(R,S) JMPLxr((R), (S), _Ro(7)) #define CLRr(R) ORrrr(0, 0, (R)) #define CLRBm(R,I) STBrm(0, (R), (I)) #define CLRBx(R,S) STBrm(0, (R), (S)) #define CLRHm(R,I) STHrm(0, (R), (I)) #define CLRHx(R,S) STHrm(0, (R), (S)) #define CLRm(R,I) STrm(0, (R), (I)) #define CLRx(R,S) STrm(0, (R), (S)) #define CMPrr(RS1, RS2) SUBCCrrr((RS1), (RS2), 0) #define CMPri(RS1, IMM) SUBCCrir((RS1), (IMM), 0) #define DECr(R) SUBrir((R), 1, (R)) #define DECir(I,R) SUBrir((R), (I), (R)) #define DECCCr(R) SUBCCrir((R), 1, (R)) #define DECCCir(I,R) SUBCCrir((R), (I), (R)) #define INCr(R) ADDrir((R), 1, (R)) #define INCir(I,R) ADDrir((R), (I), (R)) #define INCCCr(R) ADDCCrir((R), 1, (R)) #define INCCCir(I,R) ADDCCrir((R), (I), (R)) #define JMPm(R,I) JMPLmr((R), (I), 0) #define JMPx(R,S) JMPLxr((R), (S), 0) #define MOVrr(R,S) ORrrr(0, (R), (S)) #define MOVir(I, R) ORrir(0, (I), (R)) #define NEGrr(R,S) SUBrrr(0, (R), (S)) #define NEGr(R) SUBrrr(0, (R), (R)) #define NOP() SETHIir(0, 0) #define NOTrr(R,S) XNORrrr((R), 0, (S)) #define NOTr(R) XNORrrr((R), 0, (R)) #define RESTORE() RESTORErrr(0, 0, 0) #define RET() JMPLmr(_Ri(7),8 ,0) #define RETL() JMPLmr(_Ro(7),8 ,0) #define SAVE() SAVErrr(0, 0, 0) #define SETir(I,R) (_siP(13,(I)) ? MOVir((I),(R)) : SETir2(_HI(I), _LO(I), (R))) #define SETir2(H,L,R) (SETHIir(H,R), (L ? ORrir(R,L,R) : 0)) /* BNZ,a executes the delay instruction if NZ (so skips if Z) * BZ,a executes the delay instruction if Z (so skips if NZ). */ #define SKIPZ() _0d (1, 9, 2, 2) /* BNZ,a .+8 */ #define SKIPNZ() _0d (1, 1, 2, 2) /* BZ,a .+8 */ #define SKIP() _0d (1, 0, 2, 0) /* BN,a . */ #define TSTr(R) ORCCrrr(0, (R), 0) #define WRii(IMM, RD) WRrii(0, (IMM), (RD)) #define WRri(RS2, RD) WRrri(0, (RS2), (RD)) #define LDFSRx(RS1, RS2) _3 (0, 33, (RS1), 0, 0, (RS2)) #define LDFSRm(RS1, IMM) _3i (0, 33, (RS1), 1, (IMM)) #define STFSRx(RD1, RD2) _3 (0, 37, (RD1), 0, 0, (RD2)) #define STFSRm(RD, IMM) _3i (0, 37, (RD), 1, (IMM)) #define FITODrr(FRS, FRD) _FP1((FRD), 0, 200, (FRS)) #define FITOSrr(FRS, FRD) _FP1((FRD), 0, 196, (FRS)) #define FDTOIrr(FRS, FRD) _FP1((FRD), 0, 210, (FRS)) #define FSTOIrr(FRS, FRD) _FP1((FRD), 0, 209, (FRS)) #define FSTODrr(FRS, FRD) _FP1((FRD), 0, 201, (FRS)) #define FDTOSrr(FRS, FRD) _FP1((FRD), 0, 198, (FRS)) #define FMOVSrr(FRS, FRD) _FP1((FRD), 0, 1, (FRS)) #define FNEGSrr(FRS, FRD) _FP1((FRD), 0, 5, (FRS)) #define FABSSrr(FRS, FRD) _FP1((FRD), 0, 9, (FRS)) #define FMOVDrr(FRS, FRD) _FP1((FRD), 0, 2, (FRS)) #define FNEGDrr(FRS, FRD) _FP1((FRD), 0, 6, (FRS)) #define FABSDrr(FRS, FRD) _FP1((FRD), 0, 10, (FRS)) #define FSQRTDrr(FRS, FRD) _FP1((FRD), 0, 42, (FRS)) #define FSQRTSrr(FRS, FRD) _FP1((FRD), 0, 41, (FRS)) #define FADDSrrr(FRS1, FRS2, FRD) _FP1((FRD), (FRS1), 65, (FRS2)) #define FSUBSrrr(FRS1, FRS2, FRD) _FP1((FRD), (FRS1), 69, (FRS2)) #define FMULSrrr(FRS1, FRS2, FRD) _FP1((FRD), (FRS1), 73, (FRS2)) #define FDIVSrrr(FRS1, FRS2, FRD) _FP1((FRD), (FRS1), 77, (FRS2)) #define FADDDrrr(FRS1, FRS2, FRD) _FP1((FRD), (FRS1), 66, (FRS2)) #define FSUBDrrr(FRS1, FRS2, FRD) _FP1((FRD), (FRS1), 70, (FRS2)) #define FMULDrrr(FRS1, FRS2, FRD) _FP1((FRD), (FRS1), 74, (FRS2)) #define FDIVDrrr(FRS1, FRS2, FRD) _FP1((FRD), (FRS1), 78, (FRS2)) #define FCMPSrr(FRS1, FRS2) _FP2(0, (FRS1), 81, (FRS2)) #define FCMPDrr(FRS1, FRS2) _FP2(0, (FRS1), 82, (FRS2)) #define LDFxr(RS1, RS2, RD) _3 ((RD), 32, (RS1), 0, 0, (RS2)) #define LDFmr(RS1, IMM, RD) _3i ((RD), 32, (RS1), 1, (IMM)) #define LDDFxr(RS1, RS2, RD) _3 ((RD), 35, (RS1), 0, 0, (RS2)) #define LDDFmr(RS1, IMM, RD) _3i ((RD), 35, (RS1), 1, (IMM)) #define STFrx(RS, RD1, RD2) _3 ((RS), 36, (RD1), 0, 0, (RD2)) #define STFrm(RS, RD1, IMM) _3i ((RS), 36, (RD1), 1, (IMM)) #define STDFrx(RS, RD1, RD2) _3 ((RS), 39, (RD1), 0, 0, (RD2)) #define STDFrm(RS, RD1, IMM) _3i ((RS), 39, (RD1), 1, (IMM)) #define FBNi(DISP) _0 (0, 0, 6, (DISP)) #define FBN_Ai(DISP) _0 (1, 0, 6, (DISP)) #define FBNEi(DISP) _0 (0, 1, 6, (DISP)) #define FBNE_Ai(DISP) _0 (1, 1, 6, (DISP)) #define FBLGi(DISP) _0 (0, 2, 6, (DISP)) #define FBLG_Ai(DISP) _0 (1, 2, 6, (DISP)) #define FBULi(DISP) _0 (0, 3, 6, (DISP)) #define FBUL_Ai(DISP) _0 (1, 3, 6, (DISP)) #define FBLi(DISP) _0 (0, 4, 6, (DISP)) #define FBL_Ai(DISP) _0 (1, 4, 6, (DISP)) #define FBUGi(DISP) _0 (0, 5, 6, (DISP)) #define FBUG_Ai(DISP) _0 (1, 5, 6, (DISP)) #define FBGi(DISP) _0 (0, 6, 6, (DISP)) #define FBG_Ai(DISP) _0 (1, 6, 6, (DISP)) #define FBUi(DISP) _0 (0, 7, 6, (DISP)) #define FBU_Ai(DISP) _0 (1, 7, 6, (DISP)) #define FBAi(DISP) _0 (0, 8, 6, (DISP)) #define FBA_Ai(DISP) _0 (1, 8, 6, (DISP)) #define FBEi(DISP) _0 (0, 9, 6, (DISP)) #define FBE_Ai(DISP) _0 (1, 9, 6, (DISP)) #define FBUEi(DISP) _0 (0, 10, 6, (DISP)) #define FBUE_Ai(DISP) _0 (1, 10, 6, (DISP)) #define FBGEi(DISP) _0 (0, 11, 6, (DISP)) #define FBGE_Ai(DISP) _0 (1, 11, 6, (DISP)) #define FBUGEi(DISP) _0 (0, 12, 6, (DISP)) #define FBUGE_Ai(DISP) _0 (1, 12, 6, (DISP)) #define FBLEi(DISP) _0 (0, 13, 6, (DISP)) #define FBLE_Ai(DISP) _0 (1, 13, 6, (DISP)) #define FBULEi(DISP) _0 (0, 14, 6, (DISP)) #define FBULE_Ai(DISP) _0 (1, 14, 6, (DISP)) #define FBOi(DISP) _0 (0, 15, 6, (DISP)) #define FBO_Ai(DISP) _0 (1, 15, 6, (DISP)) #endif #endif /* __ccg_asm_sparc_h */ smalltalk-3.2.5/lightning/sparc/core.h0000644000175000017500000003770212123404352014627 00000000000000/******************************** -*- C -*- **************************** * * Platform-independent layer (Sparc version) * ***********************************************************************/ /*********************************************************************** * * Copyright 2000, 2001, 2002 Free Software Foundation, Inc. * Written by Paolo Bonzini. * * This file is part of GNU lightning. * * GNU lightning is free software; you can redistribute it and/or modify it * under the terms of the GNU Lesser General Public License as published * by the Free Software Foundation; either version 2.1, or (at your option) * any later version. * * GNU lightning is distributed in the hope that it will be useful, but * WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY * or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser General Public * License for more details. * * You should have received a copy of the GNU Lesser General Public License * along with GNU lightning; see the file COPYING.LESSER; if not, write to the * Free Software Foundation, 51 Franklin Street, Fifth Floor, Boston, * MA 02110-1301, USA. * ***********************************************************************/ #ifndef __lightning_core_h #define __lightning_core_h #define JIT_R_NUM 3 #define JIT_V_NUM 6 #define JIT_R(i) ((i) ? _Rl((i) - 1) : _Rg(2)) #define JIT_V(i) _Rl((i)+2) #define JIT_BIG _Rg(1) /* %g1 used to make 32-bit operands */ #define JIT_BIG2 _Ro(7) /* %o7 used to make 32-bit compare operands */ #define JIT_SP _Ro(6) #define JIT_RZERO _Rg(0) #define JIT_RET _Ri(0) /* Delay slot scheduling: jmp generates branches with annulled delay * slots; we toggle the annul bit if we can fill the slot. CALLs and * cond. branches have a different meaning for the annul bit, so we * automatically generate a NOP and eventually copy the delay insn onto * it. Delay slots in RET are already used for RESTORE, so we don't * schedule them. * * ,--- _jit.x.pc * insn X X before * cmp branch insn X X after (branch) * `--- _jit.x.pc * call insn insn X after (call) * `--- _jit.x.pc */ struct jit_local_state { int nextarg_put; /* Next %o reg. to be written */ int nextarg_get; /* Next %i reg. to be read */ jit_insn delay; }; #define jit_fill_delay_after(branch) (_jitl.delay = *--_jit.x.pc, \ ((branch) == _jit.x.pc /* check if NOP was inserted */ \ ? (_jit.x.pc[-1] ^= 1<<29) /* no if branch, toggle annul bit */ \ : (_jit.x.pc[-1] = _jitl.delay)), /* yes if call, replace NOP with delay insn */ \ *_jit.x.pc = _jitl.delay, _jit.x.pc - 1) /* return addr of delay insn */ /* If possible, use the `small' instruction (rs, imm, rd) * else load imm into %l6 and use the `big' instruction (rs, %l6, rd) * jit_chk_imm2 uses %l7 instead of %l6 to avoid conflicts when using delay slots */ #define jit_chk_imm(imm, small, big) (_siP(13,(imm)) ? (small) : (SETir((imm), JIT_BIG), (big)) ) #define jit_chk_imm2(imm, small, big) (_siP(13,(imm)) ? (small) : (SETir((imm), JIT_BIG2), (big)) ) /* Helper macros for branches */ #define jit_branchi(rs, is, jmp, nop) (jit_chk_imm2(is, CMPri(rs, is), CMPrr(rs, JIT_BIG2)), jmp, nop, _jit.x.pc - 1) #define jit_branchr(s1, s2, jmp, nop) ( CMPrr(s1, s2), jmp, nop, _jit.x.pc - 1) /* Helper macros for boolean tests -- delay slot sets d to 1; * taken branch leaves it to 1, not-taken branch resets it to 0 */ #define jit_booli(d, rs, is, jmp) (jit_chk_imm (is, CMPri(rs, is), CMPrr(rs, JIT_BIG)), jmp, MOVir(1, (d)), MOVir(0, (d))) #define jit_boolr(d, s1, s2, jmp) ( CMPrr(s1, s2), jmp, MOVir(1, (d)), MOVir(0, (d))) /* Helper macros for division * The architecture specifies that there must be 3 instructions between * * a y register write and a use of it for correct results. */ #define jit_prepare_y(rs, is) (SRArir(rs, 31, JIT_BIG), WRri(JIT_BIG, _y), NOP(), NOP(), NOP(), _jit.x.pc -= jit_immsize(is)) #define jit_clr_y(rs, is) ( WRri(0, _y), NOP(), NOP(), NOP(), _jit.x.pc -= jit_immsize(is)) #define jit_modr(jit_div, jit_mul, d, s1, s2) \ (jit_div (JIT_BIG, s1, s2), \ jit_mul (JIT_BIG, JIT_BIG, s2), \ jit_subr_i (d, s1, JIT_BIG)) #define jit_modi(jit_divi, jit_muli, jit_divr, jit_mulr, d, rs, is) \ (_siP(13,(imm)) \ ? (jit_divi (JIT_BIG, rs, is), \ jit_muli (JIT_BIG, JIT_BIG, is), \ jit_subr_i (d, rs, JIT_BIG)) \ : (SETir ((is), JIT_BIG2), \ jit_modr (jit_divr, jit_mulr, d, rs, JIT_BIG2))) /* How many instruction are needed to put imm in a register. */ #define jit_immsize(imm) (!(imm) ? 0 : \ (!_siP((imm), 13) && ((imm) & 0x3ff) ? 2 : 1)) /* branch instructions return the address of the *delay* instruction -- this * is just a helper macro that makes jit_patch more readable. */ #define jit_patch_(jump_pc,pv) \ (*jump_pc &= ~_MASK(22), \ *jump_pc |= ((_jit_UL((pv)) - _jit_UL(jump_pc)) >> 2) & _MASK(22)) #define jit_patch_set(sethi_pc, or_pc, dest) \ (*(sethi_pc) &= ~_MASK(22), *(sethi_pc) |= _HI(dest), \ *(or_pc) &= ~_MASK(13), *(or_pc) |= _LO(dest)) \ #define jit_patch_movi(movi_pc, val) \ jit_patch_set((movi_pc) - 2, (movi_pc) - 1, (val)) #define jit_arg_c() (_jitl.nextarg_get++) #define jit_arg_i() (_jitl.nextarg_get++) #define jit_arg_l() (_jitl.nextarg_get++) #define jit_arg_p() (_jitl.nextarg_get++) #define jit_arg_s() (_jitl.nextarg_get++) #define jit_arg_uc() (_jitl.nextarg_get++) #define jit_arg_ui() (_jitl.nextarg_get++) #define jit_arg_ul() (_jitl.nextarg_get++) #define jit_arg_us() (_jitl.nextarg_get++) #define jit_addi_i(d, rs, is) jit_chk_imm((is), ADDrir((rs), (is), (d)), ADDrrr((rs), JIT_BIG, (d))) #define jit_addr_i(d, s1, s2) ADDrrr((s1), (s2), (d)) #define jit_addci_i(d, rs, is) jit_chk_imm((is), ADDCCrir((rs), (is), (d)), ADDCCrrr((rs), JIT_BIG, (d))) #define jit_addcr_i(d, s1, s2) ADDCCrrr((s1), (s2), (d)) #define jit_addxi_i(d, rs, is) jit_chk_imm((is), ADDXCCrir((rs), (is), (d)), ADDXCCrrr((rs), JIT_BIG, (d))) #define jit_addxr_i(d, s1, s2) ADDXCCrrr((s1), (s2), (d)) #define jit_andi_i(d, rs, is) jit_chk_imm((is), ANDrir((rs), (is), (d)), ANDrrr((rs), JIT_BIG, (d))) #define jit_andr_i(d, s1, s2) ANDrrr((s1), (s2), (d)) #define jit_beqi_i(label, rs, is) jit_branchi((rs), (is), BEi((label)), NOP() ) #define jit_beqr_i(label, s1, s2) jit_branchr((s1), (s2), BEi((label)), NOP() ) #define jit_bgei_i(label, rs, is) jit_branchi((rs), (is), BGEi((label)), NOP() ) #define jit_bgei_ui(label, rs, is) jit_branchi((rs), (is), BGEUi((label)), NOP() ) #define jit_bger_i(label, s1, s2) jit_branchr((s1), (s2), BGEi((label)), NOP() ) #define jit_bger_ui(label, s1, s2) jit_branchr((s1), (s2), BGEUi((label)), NOP() ) #define jit_bgti_i(label, rs, is) jit_branchi((rs), (is), BGi((label)), NOP() ) #define jit_bgti_ui(label, rs, is) jit_branchi((rs), (is), BGUi((label)), NOP() ) #define jit_bgtr_i(label, s1, s2) jit_branchr((s1), (s2), BGi((label)), NOP() ) #define jit_bgtr_ui(label, s1, s2) jit_branchr((s1), (s2), BGUi((label)), NOP() ) #define jit_blei_i(label, rs, is) jit_branchi((rs), (is), BLEi((label)), NOP() ) #define jit_blei_ui(label, rs, is) jit_branchi((rs), (is), BLEUi((label)), NOP() ) #define jit_bler_i(label, s1, s2) jit_branchr((s1), (s2), BLEi((label)), NOP() ) #define jit_bler_ui(label, s1, s2) jit_branchr((s1), (s2), BLEUi((label)), NOP() ) #define jit_blti_i(label, rs, is) jit_branchi((rs), (is), BLi((label)), NOP() ) #define jit_blti_ui(label, rs, is) jit_branchi((rs), (is), BLUi((label)), NOP() ) #define jit_bltr_i(label, s1, s2) jit_branchr((s1), (s2), BLi((label)), NOP() ) #define jit_bltr_ui(label, s1, s2) jit_branchr((s1), (s2), BLUi((label)), NOP() ) #define jit_bnei_i(label, rs, is) jit_branchi((rs), (is), BNEi((label)), NOP() ) #define jit_bner_i(label, s1, s2) jit_branchr((s1), (s2), BNEi((label)), NOP() ) #define jit_bmsi_i(label, rs, is) (jit_chk_imm((is), BTSTir((is), (rs)), BTSTrr((rs), JIT_BIG)), BNEi((label)), NOP(), _jit.x.pc - 1) #define jit_bmci_i(label, rs, is) (jit_chk_imm((is), BTSTir((is), (rs)), BTSTrr((rs), JIT_BIG)), BEi((label)), NOP(), _jit.x.pc - 1) #define jit_bmsr_i(label, s1, s2) ( BTSTrr((s1), (s2)), BNEi((label)), NOP(), _jit.x.pc - 1) #define jit_bmcr_i(label, s1, s2) ( BTSTrr((s1), (s2)), BEi((label)), NOP(), _jit.x.pc - 1) #define jit_boaddi_i(label, rs, is) (jit_chk_imm((is), ADDCCrir((rs), (is), (rs)), ADDCCrrr((rs), JIT_BIG, (rs))), BVSi((label)), NOP(), _jit.x.pc - 1) #define jit_bosubi_i(label, rs, is) (jit_chk_imm((is), SUBCCrir((rs), (is), (rs)), SUBCCrrr((rs), JIT_BIG, (rs))), BVSi((label)), NOP(), _jit.x.pc - 1) #define jit_boaddr_i(label, s1, s2) ( ADDCCrrr((s1), (s2), (s1)), BVSi((label)), NOP(), _jit.x.pc - 1) #define jit_bosubr_i(label, s1, s2) ( SUBCCrrr((s1), (s2), (s1)), BVSi((label)), NOP(), _jit.x.pc - 1) #define jit_boaddi_ui(label, rs, is) (jit_chk_imm((is), ADDCCrir((rs), (is), (rs)), ADDCCrrr((rs), JIT_BIG, (rs))), BCSi((label)), NOP(), _jit.x.pc - 1) #define jit_bosubi_ui(label, rs, is) (jit_chk_imm((is), SUBCCrir((rs), (is), (rs)), SUBCCrrr((rs), JIT_BIG, (rs))), BCSi((label)), NOP(), _jit.x.pc - 1) #define jit_boaddr_ui(label, s1, s2) ( ADDCCrrr((s1), (s2), (s1)), BCSi((label)), NOP(), _jit.x.pc - 1) #define jit_bosubr_ui(label, s1, s2) ( SUBCCrrr((s1), (s2), (s1)), BCSi((label)), NOP(), _jit.x.pc - 1) #define jit_calli(label) (CALLi(label), NOP(), _jit.x.pc - 1) #define jit_callr(reg) (CALLx((reg), 0), NOP()) #define jit_divi_i(d, rs, is) (jit_prepare_y((rs), 0x12345678), SETir((is), JIT_BIG), SDIVrrr((rs), JIT_BIG, (d)) ) #define jit_divi_ui(d, rs, is) (jit_clr_y((rs), 0x12345678), SETir((is), JIT_BIG), UDIVrrr((rs), JIT_BIG, (d)) ) #define jit_divr_i(d, s1, s2) (jit_prepare_y((s1), 0), SDIVrrr((s1), (s2), (d))) #define jit_divr_ui(d, s1, s2) (jit_clr_y((s1), 0), UDIVrrr((s1), (s2), (d))) #define jit_eqi_i(d, rs, is) jit_chk_imm((is), \ (SUBCCrir((rs), (is), (d)), ADDXCCrir((d), -1, JIT_BIG), SUBXrir(0,-1,(d))),\ jit_eqr_i(d, rs, JIT_BIG)) #define jit_eqr_i(d, s1, s2) (SUBCCrrr((s1), (s2), (d)), ADDXCCrir((d), -1, JIT_BIG), SUBXrir(0,-1,(d))) #define jit_nei_i(d, rs, is) jit_chk_imm((is), \ (SUBCCrir((rs), (is), (d)), ADDXCCrir((d), -1, JIT_BIG), ADDXrrr(0,0,(d))),\ jit_ner_i(d, rs, JIT_BIG)) #define jit_ner_i(d, s1, s2) (SUBCCrrr((s1), (s2), (d)), ADDXCCrir((d), -1, JIT_BIG), ADDXrrr(0,0,(d))) #define jit_gei_i(d, rs, is) jit_booli ((d), (rs), (is), BGEi(_jit.x.pc + 3) ) #define jit_gei_ui(d, rs, is) jit_booli ((d), (rs), (is), BGEUi(_jit.x.pc + 3)) #define jit_ger_i(d, s1, s2) jit_boolr ((d), (s1), (s2), BGEi(_jit.x.pc + 3) ) #define jit_ger_ui(d, s1, s2) jit_boolr ((d), (s1), (s2), BGEUi(_jit.x.pc + 3)) #define jit_gti_i(d, rs, is) jit_booli ((d), (rs), (is), BGi(_jit.x.pc + 3) ) #define jit_gti_ui(d, rs, is) jit_booli ((d), (rs), (is), BGUi(_jit.x.pc + 3) ) #define jit_gtr_i(d, s1, s2) jit_boolr ((d), (s1), (s2), BGi(_jit.x.pc + 3) ) #define jit_gtr_ui(d, s1, s2) jit_boolr ((d), (s1), (s2), BGUi(_jit.x.pc + 3) ) #define jit_hmuli_i(d, rs, is) (jit_muli_i (JIT_BIG, (rs), (is)), RDir (_y, (d))) #define jit_hmuli_ui(d, rs, is) (jit_muli_ui(JIT_BIG, (rs), (is)), RDir (_y, (d))) #define jit_hmulr_i(d, s1, s2) (jit_mulr_i (JIT_BIG, (s1), (s2)), RDir (_y, (d))) #define jit_hmulr_ui(d, s1, s2) (jit_mulr_ui(JIT_BIG, (s1), (s2)), RDir (_y, (d))) #define jit_jmpi(label) (BA_Ai((label)), _jit.x.pc) #define jit_jmpr(reg) (JMPx(JIT_RZERO, (reg)), NOP(), _jit.x.pc - 1) #define jit_ldxi_c(d, rs, is) jit_chk_imm((is), LDSBmr((rs), (is), (d)), LDSBxr((rs), JIT_BIG, (d))) #define jit_ldxi_i(d, rs, is) jit_chk_imm((is), LDSWmr((rs), (is), (d)), LDSWxr((rs), JIT_BIG, (d))) #define jit_ldxi_s(d, rs, is) jit_chk_imm((is), LDSHmr((rs), (is), (d)), LDSHxr((rs), JIT_BIG, (d))) #define jit_ldxi_uc(d, rs, is) jit_chk_imm((is), LDUBmr((rs), (is), (d)), LDUBxr((rs), JIT_BIG, (d))) #define jit_ldxi_us(d, rs, is) jit_chk_imm((is), LDUHmr((rs), (is), (d)), LDUHxr((rs), JIT_BIG, (d))) #define jit_ldxr_c(d, s1, s2) LDSBxr((s1), (s2), (d)) #define jit_ldxr_i(d, s1, s2) LDSWxr((s1), (s2), (d)) #define jit_ldxr_s(d, s1, s2) LDSHxr((s1), (s2), (d)) #define jit_ldxr_uc(d, s1, s2) LDUBxr((s1), (s2), (d)) #define jit_ldxr_us(d, s1, s2) LDUHxr((s1), (s2), (d)) #define jit_lei_i(d, rs, is) jit_booli ((d), (rs), (is), BLEi(_jit.x.pc + 3) ) #define jit_lei_ui(d, rs, is) jit_booli ((d), (rs), (is), BLEUi(_jit.x.pc + 3)) #define jit_ler_i(d, s1, s2) jit_boolr ((d), (s1), (s2), BLEi(_jit.x.pc + 3) ) #define jit_ler_ui(d, s1, s2) jit_boolr ((d), (s1), (s2), BLEUi(_jit.x.pc + 3)) #define jit_lshi_i(d, rs, is) SLLrir((rs), (is), (d)) #define jit_lshr_i(d, r1, r2) SLLrrr((r1), (r2), (d)) #define jit_lti_i(d, rs, is) jit_booli ((d), (rs), (is), BLi(_jit.x.pc + 3) ) #define jit_lti_ui(d, rs, is) jit_booli ((d), (rs), (is), BLUi(_jit.x.pc + 3) ) #define jit_ltr_i(d, s1, s2) jit_boolr ((d), (s1), (s2), BLi(_jit.x.pc + 3) ) #define jit_ltr_ui(d, s1, s2) jit_boolr ((d), (s1), (s2), BLUi(_jit.x.pc + 3) ) #define jit_modi_i(d, rs, is) jit_modi(jit_divi_i, jit_muli_i, jit_divr_i, jit_mulr_i, (d), (rs), (is)) #define jit_modi_ui(d, rs, is) jit_modi(jit_divi_ui, jit_muli_ui, jit_divr_ui, jit_mulr_ui, (d), (rs), (is)) #define jit_modr_i(d, s1, s2) jit_modr(jit_divr_i, jit_mulr_i, (d), (s1), (s2)) #define jit_modr_ui(d, s1, s2) jit_modr(jit_divr_ui, jit_mulr_ui, (d), (s1), (s2)) #define jit_movi_i(d, is) SETir((is), (d)) #define jit_movi_p(d, is) (SETir2(_HI((is)), _LO((is)), (d)), _jit.x.pc) #define jit_movr_i(d, rs) MOVrr((rs), (d)) #define jit_muli_i(d, rs, is) jit_chk_imm((is), SMULrir((rs), (is), (d)), SMULrrr((rs), JIT_BIG, (d))) #define jit_muli_ui(d, rs, is) jit_chk_imm((is), UMULrir((rs), (is), (d)), UMULrrr((rs), JIT_BIG, (d))) #define jit_mulr_i(d, s1, s2) SMULrrr((s1), (s2), (d)) #define jit_mulr_ui(d, s1, s2) UMULrrr((s1), (s2), (d)) #define jit_nop() NOP() #define jit_ori_i(d, rs, is) jit_chk_imm((is), ORrir((rs), (is), (d)), ORrrr((rs), JIT_BIG, (d))) #define jit_orr_i(d, s1, s2) ORrrr((s1), (s2), (d)) #define jit_patch_at(delay_pc, pv) jit_patch_ (((delay_pc) - 1) , (pv)) #define jit_popr_i(rs) (LDmr(JIT_SP, 0, (rs)), ADDrir(JIT_SP, 8, JIT_SP)) #define jit_prepare_i(num) (_jitl.nextarg_put += (num)) #define jit_prolog(numargs) (SAVErir(JIT_SP, -120, JIT_SP), _jitl.nextarg_get = _Ri(0)) #define jit_pushr_i(rs) (STrm((rs), JIT_SP, -8), SUBrir(JIT_SP, 8, JIT_SP)) #define jit_pusharg_i(rs) (--_jitl.nextarg_put, MOVrr((rs), _Ro(_jitl.nextarg_put))) #define jit_ret() (RET(), RESTORE()) #define jit_retval_i(rd) MOVrr(_Ro(0), (rd)) #define jit_rshi_i(d, rs, is) SRArir((rs), (is), (d)) #define jit_rshi_ui(d, rs, is) SRLrir((rs), (is), (d)) #define jit_rshr_i(d, r1, r2) SRArrr((r1), (r2), (d)) #define jit_rshr_ui(d, r1, r2) SRLrrr((r1), (r2), (d)) #define jit_stxi_c(id, rd, rs) jit_chk_imm((id), STBrm((rs), (rd), (id)), STBrx((rs), (rd), JIT_BIG)) #define jit_stxi_i(id, rd, rs) jit_chk_imm((id), STWrm((rs), (rd), (id)), STWrx((rs), (rd), JIT_BIG)) #define jit_stxi_s(id, rd, rs) jit_chk_imm((id), STHrm((rs), (rd), (id)), STHrx((rs), (rd), JIT_BIG)) #define jit_stxr_c(d1, d2, rs) STBrx((rs), (d1), (d2)) #define jit_stxr_i(d1, d2, rs) STWrx((rs), (d1), (d2)) #define jit_stxr_s(d1, d2, rs) STHrx((rs), (d1), (d2)) #define jit_subr_i(d, s1, s2) SUBrrr((s1), (s2), (d)) #define jit_subcr_i(d, s1, s2) SUBCCrrr((s1), (s2), (d)) #define jit_subxi_i(d, rs, is) jit_chk_imm((is), SUBXCCrir((rs), (is), (d)), SUBXCCrrr((rs), JIT_BIG, (d))) #define jit_subxr_i(d, s1, s2) SUBXCCrrr((s1), (s2), (d)) #define jit_xori_i(d, rs, is) jit_chk_imm((is), XORrir((rs), (is), (d)), XORrrr((rs), JIT_BIG, (d))) #define jit_xorr_i(d, s1, s2) XORrrr((s1), (s2), (d)) #endif /* __lightning_core_h */ smalltalk-3.2.5/lightning/sparc/funcs.h0000644000175000017500000000372212123404352015010 00000000000000/******************************** -*- C -*- **************************** * * Platform-independent layer inline functions (Sparc) * ***********************************************************************/ /*********************************************************************** * * Copyright 2000, 2001, 2002 Free Software Foundation, Inc. * Written by Paolo Bonzini. * * This file is part of GNU lightning. * * GNU lightning is free software; you can redistribute it and/or modify it * under the terms of the GNU Lesser General Public License as published * by the Free Software Foundation; either version 2.1, or (at your option) * any later version. * * GNU lightning is distributed in the hope that it will be useful, but * WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY * or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser General Public * License for more details. * * You should have received a copy of the GNU Lesser General Public License * along with GNU lightning; see the file COPYING.LESSER; if not, write to the * Free Software Foundation, 51 Franklin Street, Fifth Floor, Boston, * MA 02110-1301, USA. * ***********************************************************************/ #ifndef __lightning_funcs_h #define __lightning_funcs_h #if !defined(__GNUC__) && !defined(__GNUG__) #error Go get GNU C, I do not know how to flush the cache #error with this compiler. #else /* Why doesn't this compile?!? * static void * jit_flush_code(start, end) * void *start; * void *end; */ static void jit_flush_code(void* start, void* end) { #ifndef LIGHTNING_CROSS register char *dest; __asm__ __volatile__ ("stbar"); for (dest = (char *)start; dest <= (char *)end; dest += 4) { __asm__ __volatile__ ("flush %0"::"r"(dest)); } /* [SPARC Architecture Manual v8, page 139, implementation note #5] */ __asm__ __volatile__ ("nop; nop; nop; nop; nop"); #endif } #endif #endif /* __lightning_core_h */ smalltalk-3.2.5/lightning/sparc/fp.h0000644000175000017500000002572012123404352014301 00000000000000/******************************** -*- C -*- **************************** * * Run-time assembler & support macros for the SPARC math unit * ***********************************************************************/ /*********************************************************************** * * Copyright 2000, 2001, 2002, 2004 Free Software Foundation, Inc. * Written by Paolo Bonzini. * * This file is part of GNU lightning. * * GNU lightning is free software; you can redistribute it and/or modify it * under the terms of the GNU Lesser General Public License as published * by the Free Software Foundation; either version 2.1, or (at your option) * any later version. * * GNU lightning is distributed in the hope that it will be useful, but * WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY * or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser General Public * License for more details. * * You should have received a copy of the GNU Lesser General Public License * along with GNU lightning; see the file COPYING.LESSER; if not, write to the * Free Software Foundation, 51 Franklin Street, Fifth Floor, Boston, * MA 02110-1301, USA. * ***********************************************************************/ #ifndef __lightning_asm_fp_h #define __lightning_asm_fp_h #include #define JIT_FPR_NUM 6 #define JIT_FPR(i) (30-(i)*2) #define JIT_FPTMP 18 #define jit_addr_f(rd,s1,s2) FADDSrrr((s1), (s2), (rd)) #define jit_subr_f(rd,s1,s2) FSUBSrrr((s1), (s2), (rd)) #define jit_mulr_f(rd,s1,s2) FMULSrrr((s1), (s2), (rd)) #define jit_divr_f(rd,s1,s2) FDIVSrrr((s1), (s2), (rd)) #define jit_addr_d(rd,s1,s2) FADDDrrr((s1), (s2), (rd)) #define jit_subr_d(rd,s1,s2) FSUBDrrr((s1), (s2), (rd)) #define jit_mulr_d(rd,s1,s2) FMULDrrr((s1), (s2), (rd)) #define jit_divr_d(rd,s1,s2) FDIVDrrr((s1), (s2), (rd)) #define jit_movr_f(rd,rs) FMOVSrr((rs), (rd)) #define jit_abs_d(rd,rs) FABSSrr((rs), (rd)) #define jit_negr_d(rd,rs) FNEGSrr((rs), (rd)) #define jit_sqrt_d(rd,rs) FSQRTSrr((rs), (rd)) #define jit_movr_d(rd,rs) FMOVDrr((rs), (rd)) #define jit_abs_f(rd,rs) FABSDrr((rs), (rd)) #define jit_negr_f(rd,rs) FNEGDrr((rs), (rd)) #define jit_sqrt_f(rd,rs) FSQRTDrr((rs), (rd)) #define jit_extr_f_d(rs, rd) FSTODrr((rs), (rd)) #define jit_extr_d_f(rs, rd) FDTOSrr((rs), (rd)) #define jit_movi_f(rd,immf) \ do { \ float _v = (immf); \ _1(_jit.x.pc + 3), LDFmr(_Ro(7), 8, (rd)); \ memcpy(_jit.x.uc_pc, &_v, sizeof (float)); \ _jit.x.uc_pc += sizeof (float); \ } while(0) #define jit_movi_d(rd,immd) \ do { \ double _v = (immd); \ if ((long)_jit.x.pc & 4) NOP(); \ _1(_jit.x.pc + 4); \ LDDFmr(_Ro(7), 8, (rd)); \ memcpy(_jit.x.uc_pc, &_v, sizeof (double)); \ _jit.x.uc_pc += sizeof (double); \ } while(0) #define jit_ldxi_f(rd, rs, is) jit_chk_imm((is), LDFmr((rs), (is), (rd)), LDFxr((rs), JIT_BIG, (rd))) #define jit_ldxi_d(rd, rs, is) jit_chk_imm((is), LDDFmr((rs), (is), (rd)), LDDFxr((rs), JIT_BIG, (rd))) #define jit_ldxr_f(rd, s1, s2) LDFxr((s1), (s2), (rd)) #define jit_ldxr_d(rd, s1, s2) LDDFxr((s1), (s2), (rd)) #define jit_stxi_f(id, rd, rs) jit_chk_imm((id), STFrm((rs), (rd), (id)), STFrx((rs), (rd), JIT_BIG)) #define jit_stxi_d(id, rd, rs) jit_chk_imm((id), STDFrm((rs), (rd), (id)), STDFrx((rs), (rd), JIT_BIG)) #define jit_stxr_f(d1, d2, rs) STFrx((rs), (d1), (d2)) #define jit_stxr_d(d1, d2, rs) STDFrx((rs), (d1), (d2)) #define jit_truncr_f_i(rd, rs) ( \ _1(_jit.x.pc + 3), \ FSTOIrr((rs), JIT_FPTMP), \ NOP(), \ STFrm(JIT_FPTMP, _Ro(7), 8), \ LDmr(_Ro(7), 8, (rd))) #define jit_truncr_d_i(rd, rs) ( \ _1(_jit.x.pc + 3), \ FDTOIrr((rs), JIT_FPTMP), \ NOP(), \ STFrm(JIT_FPTMP, _Ro(7), 8), \ LDmr(_Ro(7), 8, (rd))) #define jit_extr_i_d(rd, rs) (_1 (_jit.x.pc + 3), NOP(), NOP(), STrm((rs), _Ro(7), 8), LDFmr(_Ro(7), 8, (rd)), FITODrr((rd), (rd))) #define jit_extr_i_f(rd, rs) (_1 (_jit.x.pc + 3), NOP(), NOP(), STrm((rs), _Ro(7), 8), LDFmr(_Ro(7), 8, (rd)), FITOSrr((rd), (rd))) #define jit_do_round_f(rd, rs, fixup, mode) do { \ jit_movi_f (JIT_FPTMP, fixup); \ _1(_jit.x.pc + 4); \ SETHIir(_HI(mode << 29), JIT_BIG); \ NOP(); \ NOP(); \ STFSRm(_Ro(7), 8); /* store fsr */ \ LDmr(_Ro(7), 8, rd); \ XORrrr(rd, JIT_BIG, JIT_BIG); /* adjust mode */ \ STrm(JIT_BIG, _Ro(7), 12); \ LDFSRm(_Ro(7), 12); /* load fsr */ \ FADDSrrr ((rs), JIT_FPTMP, JIT_FPTMP); \ LDFSRm(_Ro(7), 8); \ FSTOIrr(JIT_FPTMP, JIT_FPTMP); \ STFrm(JIT_FPTMP, _Ro(7), 8); \ LDmr(_Ro(7), 8, (rd)); \ ADDCCrrr ((rd), (rd), 0); \ SUBXrrr ((rd), 0, (rd)); \ } while (0); #define jit_do_round_d(rd, rs, fixup, mode) do { \ jit_movi_d (JIT_FPTMP, fixup); \ _1(_jit.x.pc + 4); \ SETHIir(_HI(mode << 29), JIT_BIG); \ NOP(); \ NOP(); \ STFSRm(_Ro(7), 8); /* store fsr */ \ LDmr(_Ro(7), 8, rd); \ XORrrr(rd, JIT_BIG, JIT_BIG); /* adjust mode */ \ STrm(JIT_BIG, _Ro(7), 12); \ LDFSRm(_Ro(7), 12); /* load fsr */ \ FADDDrrr ((rs), JIT_FPTMP, JIT_FPTMP); \ LDFSRm(_Ro(7), 8); \ FDTOIrr(JIT_FPTMP, JIT_FPTMP); \ STFrm(JIT_FPTMP, _Ro(7), 8); \ LDmr(_Ro(7), 8, (rd)); \ ADDCCrrr ((rd), (rd), 0); \ SUBXrrr ((rd), 0, (rd)); \ } while (0); #define jit_roundr_f_i(rd, rs) do { \ jit_movi_f (JIT_FPTMP, 0.5); \ FADDSrrr ((rs), JIT_FPTMP, JIT_FPTMP); \ jit_truncr_f_i ((rd), JIT_FPTMP); \ ADDCCrrr ((rd), (rd), 0); \ SUBXrrr ((rd), 0, (rd)); \ } while (0) #define jit_roundr_d_i(rd, rs) do { \ jit_movi_d (JIT_FPTMP, 0.5); \ FADDDrrr ((rs), JIT_FPTMP, JIT_FPTMP); \ jit_truncr_d_i ((rd), JIT_FPTMP); \ ADDCCrrr ((rd), (rd), 0); \ SUBXrrr ((rd), 0, (rd)); \ } while (0) #define jit_ceilr_f_i(rd, rs) \ jit_do_round_f ((rd), (rs), 1.0f - FLT_EPSILON, 3) #define jit_ceilr_d_i(rd, rs) \ jit_do_round_d ((rd), (rs), 1.0 - DBL_EPSILON, 3) #define jit_floorr_f_i(rd, rs) \ jit_do_round_f ((rd), (rs), FLT_EPSILON, 2) #define jit_floorr_d_i(rd, rs) \ jit_do_round_d ((rd), (rs), DBL_EPSILON, 2) #define jit_ltr_d(d, s1, s2) (FCMPDrr ((s1), (s2)), FBLi(_jit.x.pc + 3), MOVir (1, (d)), MOVir (0, (d))) #define jit_ltr_f(d, s1, s2) (FCMPSrr ((s1), (s2)), FBLi(_jit.x.pc + 3), MOVir (1, (d)), MOVir (0, (d))) #define jit_ler_d(d, s1, s2) (FCMPDrr ((s1), (s2)), FBLEi(_jit.x.pc + 3), MOVir (1, (d)), MOVir (0, (d))) #define jit_ler_f(d, s1, s2) (FCMPSrr ((s1), (s2)), FBLEi(_jit.x.pc + 3), MOVir (1, (d)), MOVir (0, (d))) #define jit_eqr_d(d, s1, s2) (FCMPDrr ((s1), (s2)), FBEi(_jit.x.pc + 3), MOVir (1, (d)), MOVir (0, (d))) #define jit_eqr_f(d, s1, s2) (FCMPSrr ((s1), (s2)), FBEi(_jit.x.pc + 3), MOVir (1, (d)), MOVir (0, (d))) #define jit_ner_d(d, s1, s2) (FCMPDrr ((s1), (s2)), FBNEi(_jit.x.pc + 3), MOVir (1, (d)), MOVir (0, (d))) #define jit_ner_f(d, s1, s2) (FCMPSrr ((s1), (s2)), FBNEi(_jit.x.pc + 3), MOVir (1, (d)), MOVir (0, (d))) #define jit_ger_d(d, s1, s2) (FCMPDrr ((s1), (s2)), FBGEi(_jit.x.pc + 3), MOVir (1, (d)), MOVir (0, (d))) #define jit_ger_f(d, s1, s2) (FCMPSrr ((s1), (s2)), FBGEi(_jit.x.pc + 3), MOVir (1, (d)), MOVir (0, (d))) #define jit_gtr_d(d, s1, s2) (FCMPDrr ((s1), (s2)), FBGi(_jit.x.pc + 3), MOVir (1, (d)), MOVir (0, (d))) #define jit_gtr_f(d, s1, s2) (FCMPSrr ((s1), (s2)), FBGi(_jit.x.pc + 3), MOVir (1, (d)), MOVir (0, (d))) #define jit_unltr_d(d, s1, s2) (FCMPDrr ((s1), (s2)), FBULi(_jit.x.pc + 3), MOVir (1, (d)), MOVir (0, (d))) #define jit_unltr_f(d, s1, s2) (FCMPSrr ((s1), (s2)), FBULi(_jit.x.pc + 3), MOVir (1, (d), MOVir (0, (d))) #define jit_unler_d(d, s1, s2) (FCMPDrr ((s1), (s2)), FBULEi(_jit.x.pc + 3), MOVir (1, (d)), MOVir (0, (d))) #define jit_unler_f(d, s1, s2) (FCMPSrr ((s1), (s2)), FBULEi(_jit.x.pc + 3), MOVir (1, (d)), MOVir (0, (d))) #define jit_uneqr_d(d, s1, s2) (FCMPDrr ((s1), (s2)), FBUEi(_jit.x.pc + 3), MOVir (1, (d)), MOVir (0, (d))) #define jit_uneqr_f(d, s1, s2) (FCMPSrr ((s1), (s2)), FBUEi(_jit.x.pc + 3), MOVir (1, (d)), MOVir (0, (d))) #define jit_ltgtr_d(d, s1, s2) (FCMPDrr ((s1), (s2)), FBLGi(_jit.x.pc + 3), MOVir (1, (d)), MOVir (0, (d))) #define jit_ltgtr_f(d, s1, s2) (FCMPSrr ((s1), (s2)), FBLGi(_jit.x.pc + 3), MOVir (1, (d)), MOVir (0, (d))) #define jit_unger_d(d, s1, s2) (FCMPDrr ((s1), (s2)), FBUGEi(_jit.x.pc + 3), MOVir (1, (d)), MOVir (0, (d))) #define jit_unger_f(d, s1, s2) (FCMPSrr ((s1), (s2)), FBUGEi(_jit.x.pc + 3), MOVir (1, (d)), MOVir (0, (d))) #define jit_ungtr_d(d, s1, s2) (FCMPDrr ((s1), (s2)), FBUGi(_jit.x.pc + 3), MOVir (1, (d)), MOVir (0, (d))) #define jit_ungtr_f(d, s1, s2) (FCMPSrr ((s1), (s2)), FBUGi(_jit.x.pc + 3), MOVir (1, (d)), MOVir (0, (d))) #define jit_ordr_d(d, s1, s2) (FCMPDrr ((s1), (s2)), FBOi(_jit.x.pc + 3), MOVir (1, (d)), MOVir (0, (d))) #define jit_ordr_f(d, s1, s2) (FCMPSrr ((s1), (s2)), FBOi(_jit.x.pc + 3), MOVir (1, (d)), MOVir (0, (d))) #define jit_unordr_d(d, s1, s2) (FCMPDrr ((s1), (s2)), FBUi(_jit.x.pc + 3), MOVir (1, (d)), MOVir (0, (d))) #define jit_unordr_f(d, s1, s2) (FCMPSrr ((s1), (s2)), FBUi(_jit.x.pc + 3), MOVir (1, (d)), MOVir (0, (d))) #define jit_prepare_f(num) (_jitl.nextarg_put += (num)) #define jit_prepare_d(num) (_jitl.nextarg_put += 2 * (num)) #define jit_arg_f() (_jitl.nextarg_get++) #define jit_arg_d() (_jitl.nextarg_get += _jitl.nextarg_get & 1, _jitl.nextarg_get += 2, _jitl.nextarg_get - 2) #define jit_getarg_f(rd, ofs) (STrm(ofs, _Ri(6), -24), LDFmr (_Ri(6), -24, (rd))) #define jit_getarg_d(rd, ofs) (STDrm(ofs, _Ri(6), -24), LDDFmr (_Ri(6), -24, (rd))) #define jit_pusharg_f(rs) (STFrm((rs), _Ri(6), -24), --_jitl.nextarg_put, LDmr (_Ri(6), -24, _Ro(_jitl.nextarg_put))) #define jit_pusharg_d(rs) (STDFrm((rs), _Ri(6), -24), _jitl.nextarg_put -= 2, LDmr (_Ri(6), -24, _Ro(_jitl.nextarg_put))) #define jit_retval_f(rs) jit_movr_f(0, rs) #define jit_retval_d(rs) jit_movr_d(0, rs) #endif /* __lightning_asm_fp_h */ smalltalk-3.2.5/lightning/Makefile.am0000644000175000017500000000204112123404352014436 00000000000000DISTCLEANFILES = asm.h core.h funcs.h fp.h EXTRA_DIST = i386/Makefile.frag \ i386/asm-32.h i386/asm-64.h i386/asm-i386.h \ i386/core-32.h i386/core-64.h i386/core-i386.h \ i386/fp-32.h i386/fp-64.h \ i386/funcs.h \ sparc/asm.h sparc/core.h sparc/funcs.h sparc/fp.h \ ppc/asm.h ppc/core.h ppc/funcs.h ppc/fp.h @lightning_frag@ LIGHTNING_COMMON_FILES = funcs-common.h core-common.h fp-common.h asm-common.h if LIGHTNING_MAIN lightningdir = $(includedir)/lightning dist_pkgdata_DATA = Makefile.am dist_lightning_HEADERS = $(LIGHTNING_COMMON_FILES) nodist_lightning_HEADERS = asm.h core.h funcs.h fp.h $(LIGHTNING_TARGET_FILES) else all-am: @set frob $(LIGHTNING_TARGET_FILES); shift; \ for i; \ do \ echo $(LN_S) -f $(srcdir)/$$i `basename $$i`; \ $(LN_S) -f $(srcdir)/$$i `basename $$i`; \ done clean-local: @set frob $(LIGHTNING_TARGET_FILES); shift; \ for i; \ do \ echo rm -f `basename $$i`; \ rm -f `basename $$i`; \ done dist-hook: cp -p $(srcdir)/lightning.h $(distdir) endif smalltalk-3.2.5/lightning/asm-common.h0000644000175000017500000001576712123404352014644 00000000000000/******************************** -*- C -*- **************************** * * Dynamic assembler support * ***********************************************************************/ /*********************************************************************** * * Copyright 2000, 2001, 2002 Free Software Foundation, Inc. * Written by Paolo Bonzini. * * This file is part of GNU lightning. * * GNU lightning is free software; you can redistribute it and/or modify it * under the terms of the GNU Lesser General Public License as published * by the Free Software Foundation; either version 2.1, or (at your option) * any later version. * * GNU lightning is distributed in the hope that it will be useful, but * WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY * or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser General Public * License for more details. * * You should have received a copy of the GNU Lesser General Public License * along with GNU lightning; see the file COPYING.LESSER; if not, write to the * Free Software Foundation, 51 Franklin Street, Fifth Floor, Boston, * MA 02110-1301, USA. * ***********************************************************************/ #ifndef __lightning_asm_common_h #define __lightning_asm_common_h_ #ifndef _ASM_SAFETY #define JITFAIL(MSG) 0 #else #if (defined __STDC_VERSION__ && __STDC_VERSION__ >= 199901L) || (defined __GNUC__ && (__GNUC__ == 3 ? __GNUC_MINOR__ >= 2 : __GNUC__ > 3)) #define JITFAIL(MSG) jit_fail(MSG, __FILE__, __LINE__, __func__) #elif defined __GNUC__ #define JITFAIL(MSG) jit_fail(MSG, __FILE__, __LINE__, __FUNCTION__) #else #define JITFAIL(MSG) jit_fail(MSG, __FILE__, __LINE__, "(unknown)") #endif #endif #if (defined __STDC_VERSION__ && __STDC_VERSION__ >= 199901L) || (defined __GNUC__ && (__GNUC__ == 3 ? __GNUC_MINOR__ >= 2 : __GNUC__ > 3)) #define JITSORRY(MSG) jit_fail("sorry, unimplemented: " MSG, __FILE__, __LINE__, __func__) #elif defined __GNUC__ #define JITSORRY(MSG) jit_fail("sorry, unimplemented: " MSG, __FILE__, __LINE__, __FUNCTION__) #else #define JITSORRY(MSG) jit_fail("sorry, unimplemented: " MSG, __FILE__, __LINE__, "(unknown)") #endif #ifdef __GNUC__ #define JIT_UNUSED __attribute__((unused)) #else #define JIT_UNUSED #endif /* NextStep 2.0 cc is really gcc 1.93 but it defines __GNUC__ = 2 and does not implement __extension__. But that compiler doesn't define __GNUC_MINOR__. */ #ifdef __GNUC__ #if __GNUC__ < 2 || (defined(__NeXT__) && !__GNUC_MINOR__) #define __extension__ #endif #define _TEMPD(type, var) #define _TEMP(type, var, val, body) __extension__ ({ \ register struct { type var } _jitl; _jitl.var = val; \ body; \ }) #else /* Between loading a global and calling a subroutine, we choose the lesser * evil. */ #define _TEMPD(type, var) static type var; #define _TEMP(type, var, val, body) ((var = val), body) #endif typedef char _sc; typedef unsigned char _uc; typedef unsigned short _us; typedef unsigned int _ui; typedef long _sl; typedef unsigned long _ul; #define _jit_UC(X) ((_uc )(X)) #define _jit_US(X) ((_us )(X)) #define _jit_UI(X) ((_ui )(X)) #define _jit_SL(X) ((_sl )(X)) #define _jit_UL(X) ((_ul )(X)) # define _PUC(X) ((_uc *)(X)) # define _PUS(X) ((_us *)(X)) # define _PUI(X) ((_ui *)(X)) # define _PSL(X) ((_sl *)(X)) # define _PUL(X) ((_ul *)(X)) #define _jit_B(B) _jit_UL(((*_jit.x.uc_pc++)= _jit_UC((B)& 0xff))) #define _jit_W(W) _jit_UL(((*_jit.x.us_pc++)= _jit_US((W)&0xffff))) #define _jit_I(I) _jit_UL(((*_jit.x.ui_pc++)= _jit_UI((I) ))) #define _jit_L(L) _jit_UL(((*_jit.x.ul_pc++)= _jit_UL((L) ))) #define _jit_I_noinc(I) _jit_UL(((*_jit.x.ui_pc)= _jit_UI((I) ))) #define _MASK(N) ((unsigned)((1<<(N)))-1) #define _siP(N,I) (!((((unsigned)(I))^(((unsigned)(I))<<1))&~_MASK(N))) #define _uiP(N,I) (!(((unsigned)(I))&~_MASK(N))) #define _suiP(N,I) (_siP(N,I) | _uiP(N,I)) #ifndef _ASM_SAFETY #define _ck_s(W,I) (_jit_UL(I) & _MASK(W)) #define _ck_u(W,I) (_jit_UL(I) & _MASK(W)) #define _ck_su(W,I) (_jit_UL(I) & _MASK(W)) #define _ck_d(W,I) (_jit_UL(I) & _MASK(W)) #else #define _ck_s(W,I) (_siP(W,I) ? (_jit_UL(I) & _MASK(W)) : JITFAIL( "signed integer `"#I"' too large for "#W"-bit field")) #define _ck_u(W,I) (_uiP(W,I) ? (_jit_UL(I) & _MASK(W)) : JITFAIL("unsigned integer `"#I"' too large for "#W"-bit field")) #define _ck_su(W,I) (_suiP(W,I) ? (_jit_UL(I) & _MASK(W)) : JITFAIL( "integer `"#I"' too large for "#W"-bit field")) #define _ck_d(W,I) (_siP(W,I) ? (_jit_UL(I) & _MASK(W)) : JITFAIL( "displacement `"#I"' too large for "#W"-bit field")) #endif #define _s0P(I) ((I)==0) #define _s8P(I) _siP(8,I) #define _s16P(I) _siP(16,I) #define _u8P(I) _uiP(8,I) #define _u16P(I) _uiP(16,I) #define _su8(I) _ck_su(8,I) #define _su16(I) _ck_su(16,I) #define _s1(I) _ck_s( 1,I) #define _s2(I) _ck_s( 2,I) #define _s3(I) _ck_s( 3,I) #define _s4(I) _ck_s( 4,I) #define _s5(I) _ck_s( 5,I) #define _s6(I) _ck_s( 6,I) #define _s7(I) _ck_s( 7,I) #define _s8(I) _ck_s( 8,I) #define _s9(I) _ck_s( 9,I) #define _s10(I) _ck_s(10,I) #define _s11(I) _ck_s(11,I) #define _s12(I) _ck_s(12,I) #define _s13(I) _ck_s(13,I) #define _s14(I) _ck_s(14,I) #define _s15(I) _ck_s(15,I) #define _s16(I) _ck_s(16,I) #define _s17(I) _ck_s(17,I) #define _s18(I) _ck_s(18,I) #define _s19(I) _ck_s(19,I) #define _s20(I) _ck_s(20,I) #define _s21(I) _ck_s(21,I) #define _s22(I) _ck_s(22,I) #define _s23(I) _ck_s(23,I) #define _s24(I) _ck_s(24,I) #define _s25(I) _ck_s(25,I) #define _s26(I) _ck_s(26,I) #define _s27(I) _ck_s(27,I) #define _s28(I) _ck_s(28,I) #define _s29(I) _ck_s(29,I) #define _s30(I) _ck_s(30,I) #define _s31(I) _ck_s(31,I) #define _u1(I) _ck_u( 1,I) #define _u2(I) _ck_u( 2,I) #define _u3(I) _ck_u( 3,I) #define _u4(I) _ck_u( 4,I) #define _u5(I) _ck_u( 5,I) #define _u6(I) _ck_u( 6,I) #define _u7(I) _ck_u( 7,I) #define _u8(I) _ck_u( 8,I) #define _u9(I) _ck_u( 9,I) #define _u10(I) _ck_u(10,I) #define _u11(I) _ck_u(11,I) #define _u12(I) _ck_u(12,I) #define _u13(I) _ck_u(13,I) #define _u14(I) _ck_u(14,I) #define _u15(I) _ck_u(15,I) #define _u16(I) _ck_u(16,I) #define _u17(I) _ck_u(17,I) #define _u18(I) _ck_u(18,I) #define _u19(I) _ck_u(19,I) #define _u20(I) _ck_u(20,I) #define _u21(I) _ck_u(21,I) #define _u22(I) _ck_u(22,I) #define _u23(I) _ck_u(23,I) #define _u24(I) _ck_u(24,I) #define _u25(I) _ck_u(25,I) #define _u26(I) _ck_u(26,I) #define _u27(I) _ck_u(27,I) #define _u28(I) _ck_u(28,I) #define _u29(I) _ck_u(29,I) #define _u30(I) _ck_u(30,I) #define _u31(I) _ck_u(31,I) #endif /* __lightning_asm_common_h */ smalltalk-3.2.5/lightning/Makefile.in0000644000175000017500000005353212130455425014467 00000000000000# Makefile.in generated by automake 1.11.6 from Makefile.am. # @configure_input@ # Copyright (C) 1994, 1995, 1996, 1997, 1998, 1999, 2000, 2001, 2002, # 2003, 2004, 2005, 2006, 2007, 2008, 2009, 2010, 2011 Free Software # Foundation, Inc. # This Makefile.in is free software; the Free Software Foundation # gives unlimited permission to copy and/or distribute it, # with or without modifications, as long as this notice is preserved. # This program is distributed in the hope that it will be useful, # but WITHOUT ANY WARRANTY, to the extent permitted by law; without # even the implied warranty of MERCHANTABILITY or FITNESS FOR A # PARTICULAR PURPOSE. @SET_MAKE@ VPATH = @srcdir@ am__make_dryrun = \ { \ am__dry=no; \ case $$MAKEFLAGS in \ *\\[\ \ ]*) \ echo 'am--echo: ; @echo "AM" OK' | $(MAKE) -f - 2>/dev/null \ | grep '^AM OK$$' >/dev/null || am__dry=yes;; \ *) \ for am__flg in $$MAKEFLAGS; do \ case $$am__flg in \ *=*|--*) ;; \ *n*) am__dry=yes; break;; \ esac; \ done;; \ esac; \ test $$am__dry = yes; \ } pkgdatadir = $(datadir)/@PACKAGE@ pkgincludedir = $(includedir)/@PACKAGE@ pkglibdir = $(libdir)/@PACKAGE@ pkglibexecdir = $(libexecdir)/@PACKAGE@ am__cd = CDPATH="$${ZSH_VERSION+.}$(PATH_SEPARATOR)" && cd install_sh_DATA = $(install_sh) -c -m 644 install_sh_PROGRAM = $(install_sh) -c install_sh_SCRIPT = $(install_sh) -c INSTALL_HEADER = $(INSTALL_DATA) transform = $(program_transform_name) NORMAL_INSTALL = : PRE_INSTALL = : POST_INSTALL = : NORMAL_UNINSTALL = : PRE_UNINSTALL = : POST_UNINSTALL = : build_triplet = @build@ host_triplet = @host@ subdir = lightning DIST_COMMON = $(am__dist_lightning_HEADERS_DIST) \ $(am__dist_pkgdata_DATA_DIST) $(srcdir)/Makefile.am \ $(srcdir)/Makefile.in ACLOCAL_M4 = $(top_srcdir)/aclocal.m4 am__aclocal_m4_deps = $(top_srcdir)/build-aux/bold.m4 \ $(top_srcdir)/build-aux/codeset.m4 \ $(top_srcdir)/build-aux/emacs-pkg.m4 \ $(top_srcdir)/build-aux/emacs-site-start.m4 \ $(top_srcdir)/build-aux/ext_goto.m4 \ $(top_srcdir)/build-aux/gawk.m4 $(top_srcdir)/build-aux/gcc.m4 \ $(top_srcdir)/build-aux/gl.m4 \ $(top_srcdir)/build-aux/glib-2.0.m4 \ $(top_srcdir)/build-aux/glut.m4 $(top_srcdir)/build-aux/gmp.m4 \ $(top_srcdir)/build-aux/gst-package.m4 \ $(top_srcdir)/build-aux/gtk-2.0.m4 \ $(top_srcdir)/build-aux/iconv.m4 \ $(top_srcdir)/build-aux/lib-ld.m4 \ $(top_srcdir)/build-aux/lib-link.m4 \ $(top_srcdir)/build-aux/lib-prefix.m4 \ $(top_srcdir)/build-aux/lib.m4 \ $(top_srcdir)/build-aux/libc-so-name.m4 \ $(top_srcdir)/build-aux/libtool.m4 \ $(top_srcdir)/build-aux/lightning.m4 \ $(top_srcdir)/build-aux/ln.m4 \ $(top_srcdir)/build-aux/localtime.m4 \ $(top_srcdir)/build-aux/lock.m4 \ $(top_srcdir)/build-aux/long-double.m4 \ $(top_srcdir)/build-aux/lrint.m4 \ $(top_srcdir)/build-aux/ltdl-gst.m4 \ $(top_srcdir)/build-aux/ltoptions.m4 \ $(top_srcdir)/build-aux/ltsugar.m4 \ $(top_srcdir)/build-aux/ltversion.m4 \ $(top_srcdir)/build-aux/lt~obsolete.m4 \ $(top_srcdir)/build-aux/modules.m4 \ $(top_srcdir)/build-aux/pkg.m4 $(top_srcdir)/build-aux/poll.m4 \ $(top_srcdir)/build-aux/readline.m4 \ $(top_srcdir)/build-aux/relocatable.m4 \ $(top_srcdir)/build-aux/setenv.m4 \ $(top_srcdir)/build-aux/snprintfv.m4 \ $(top_srcdir)/build-aux/sockets.m4 \ $(top_srcdir)/build-aux/sockpfaf.m4 \ $(top_srcdir)/build-aux/strtoul.m4 \ $(top_srcdir)/build-aux/sync-builtins.m4 \ $(top_srcdir)/build-aux/tcltk.m4 \ $(top_srcdir)/build-aux/version.m4 \ $(top_srcdir)/build-aux/vis-hidden.m4 \ $(top_srcdir)/build-aux/wine.m4 $(top_srcdir)/configure.ac am__configure_deps = $(am__aclocal_m4_deps) $(CONFIGURE_DEPENDENCIES) \ $(ACLOCAL_M4) mkinstalldirs = $(install_sh) -d CONFIG_HEADER = $(top_builddir)/config.h CONFIG_CLEAN_FILES = asm.h fp.h core.h funcs.h CONFIG_CLEAN_VPATH_FILES = SOURCES = DIST_SOURCES = am__can_run_installinfo = \ case $$AM_UPDATE_INFO_DIR in \ n|no|NO) false;; \ *) (install-info --version) >/dev/null 2>&1;; \ esac am__dist_pkgdata_DATA_DIST = Makefile.am am__vpath_adj_setup = srcdirstrip=`echo "$(srcdir)" | sed 's|.|.|g'`; am__vpath_adj = case $$p in \ $(srcdir)/*) f=`echo "$$p" | sed "s|^$$srcdirstrip/||"`;; \ *) f=$$p;; \ esac; am__strip_dir = f=`echo $$p | sed -e 's|^.*/||'`; am__install_max = 40 am__nobase_strip_setup = \ srcdirstrip=`echo "$(srcdir)" | sed 's/[].[^$$\\*|]/\\\\&/g'` am__nobase_strip = \ for p in $$list; do echo "$$p"; done | sed -e "s|$$srcdirstrip/||" am__nobase_list = $(am__nobase_strip_setup); \ for p in $$list; do echo "$$p $$p"; done | \ sed "s| $$srcdirstrip/| |;"' / .*\//!s/ .*/ ./; s,\( .*\)/[^/]*$$,\1,' | \ $(AWK) 'BEGIN { files["."] = "" } { files[$$2] = files[$$2] " " $$1; \ if (++n[$$2] == $(am__install_max)) \ { print $$2, files[$$2]; n[$$2] = 0; files[$$2] = "" } } \ END { for (dir in files) print dir, files[dir] }' am__base_list = \ sed '$$!N;$$!N;$$!N;$$!N;$$!N;$$!N;$$!N;s/\n/ /g' | \ sed '$$!N;$$!N;$$!N;$$!N;s/\n/ /g' am__uninstall_files_from_dir = { \ test -z "$$files" \ || { test ! -d "$$dir" && test ! -f "$$dir" && test ! -r "$$dir"; } \ || { echo " ( cd '$$dir' && rm -f" $$files ")"; \ $(am__cd) "$$dir" && rm -f $$files; }; \ } am__installdirs = "$(DESTDIR)$(pkgdatadir)" \ "$(DESTDIR)$(lightningdir)" "$(DESTDIR)$(lightningdir)" DATA = $(dist_pkgdata_DATA) am__dist_lightning_HEADERS_DIST = funcs-common.h core-common.h \ fp-common.h asm-common.h HEADERS = $(dist_lightning_HEADERS) $(nodist_lightning_HEADERS) ETAGS = etags CTAGS = ctags DISTFILES = $(DIST_COMMON) $(DIST_SOURCES) $(TEXINFOS) $(EXTRA_DIST) ACLOCAL = @ACLOCAL@ ALLOCA = @ALLOCA@ ALL_PACKAGES = @ALL_PACKAGES@ AMTAR = @AMTAR@ AR = @AR@ AS = @AS@ ATK_CFLAGS = @ATK_CFLAGS@ ATK_LIBS = @ATK_LIBS@ AUTOCONF = @AUTOCONF@ AUTOHEADER = @AUTOHEADER@ AUTOM4TE = @AUTOM4TE@ AUTOMAKE = @AUTOMAKE@ AWK = @AWK@ BLOX_IMPLEMENTATION = @BLOX_IMPLEMENTATION@ BUILT_PACKAGES = @BUILT_PACKAGES@ CAIRO_CFLAGS = @CAIRO_CFLAGS@ CAIRO_LIBS = @CAIRO_LIBS@ CC = @CC@ CCDEPMODE = @CCDEPMODE@ CFLAGS = @CFLAGS@ CPP = @CPP@ CPPFLAGS = @CPPFLAGS@ CYGPATH_W = @CYGPATH_W@ DEFS = @DEFS@ DEPDIR = @DEPDIR@ DLLTOOL = @DLLTOOL@ DSYMUTIL = @DSYMUTIL@ DUMPBIN = @DUMPBIN@ ECHO_C = @ECHO_C@ ECHO_N = @ECHO_N@ ECHO_T = @ECHO_T@ EGREP = @EGREP@ EMACS = @EMACS@ EMACSLOADPATH = @EMACSLOADPATH@ EXEEXT = @EXEEXT@ FGREP = @FGREP@ GLIB_CFLAGS = @GLIB_CFLAGS@ GLIB_GENMARSHAL = @GLIB_GENMARSHAL@ GLIB_LIBS = @GLIB_LIBS@ GLIB_MKENUMS = @GLIB_MKENUMS@ GNUTLS_CFLAGS = @GNUTLS_CFLAGS@ GNUTLS_LIBS = @GNUTLS_LIBS@ GOBJECT_QUERY = @GOBJECT_QUERY@ GPERF = @GPERF@ GREP = @GREP@ GST_RUN = @GST_RUN@ GTHREAD_CFLAGS = @GTHREAD_CFLAGS@ GTHREAD_LIBS = @GTHREAD_LIBS@ GTK_CFLAGS = @GTK_CFLAGS@ GTK_LIBS = @GTK_LIBS@ ICON = @ICON@ INCFFI = @INCFFI@ INCLTDL = @INCLTDL@ INCSIGSEGV = @INCSIGSEGV@ INCSNPRINTFV = @INCSNPRINTFV@ INCTCLTK = @INCTCLTK@ INSTALL = @INSTALL@ INSTALL_DATA = @INSTALL_DATA@ INSTALL_INFO = @INSTALL_INFO@ INSTALL_PROGRAM = @INSTALL_PROGRAM@ INSTALL_SCRIPT = @INSTALL_SCRIPT@ INSTALL_STRIP_PROGRAM = @INSTALL_STRIP_PROGRAM@ LD = @LD@ LDFLAGS = @LDFLAGS@ LEX = @LEX@ LIBADD_DL = @LIBADD_DL@ LIBC_SO_DIR = @LIBC_SO_DIR@ LIBC_SO_NAME = @LIBC_SO_NAME@ LIBFFI = @LIBFFI@ LIBFFI_CFLAGS = @LIBFFI_CFLAGS@ LIBFFI_EXECUTABLE_LDFLAGS = @LIBFFI_EXECUTABLE_LDFLAGS@ LIBFFI_LIBS = @LIBFFI_LIBS@ LIBGLUT = @LIBGLUT@ LIBGMP = @LIBGMP@ LIBGST_CFLAGS = @LIBGST_CFLAGS@ LIBICONV = @LIBICONV@ LIBLTDL = @LIBLTDL@ LIBOBJS = @LIBOBJS@ LIBOPENGL = @LIBOPENGL@ LIBREADLINE = @LIBREADLINE@ LIBS = @LIBS@ LIBSIGSEGV = @LIBSIGSEGV@ LIBSNPRINTFV = @LIBSNPRINTFV@ LIBTCLTK = @LIBTCLTK@ LIBTHREAD = @LIBTHREAD@ LIBTOOL = @LIBTOOL@ LIPO = @LIPO@ LN = @LN@ LN_S = @LN_S@ LTALLOCA = @LTALLOCA@ LTLIBICONV = @LTLIBICONV@ LTLIBOBJS = @LTLIBOBJS@ MAINTAINER = @MAINTAINER@ MAKEINFO = @MAKEINFO@ MANIFEST_TOOL = @MANIFEST_TOOL@ MKDIR_P = @MKDIR_P@ MODULES = @MODULES@ NM = @NM@ NMEDIT = @NMEDIT@ OBJC = @OBJC@ OBJCDEPMODE = @OBJCDEPMODE@ OBJCFLAGS = @OBJCFLAGS@ OBJDUMP = @OBJDUMP@ OBJEXT = @OBJEXT@ OTOOL = @OTOOL@ OTOOL64 = @OTOOL64@ PACKAGE = @PACKAGE@ PACKAGE_BUGREPORT = @PACKAGE_BUGREPORT@ PACKAGE_DLOPEN_FLAGS = @PACKAGE_DLOPEN_FLAGS@ PACKAGE_NAME = @PACKAGE_NAME@ PACKAGE_STRING = @PACKAGE_STRING@ PACKAGE_TARNAME = @PACKAGE_TARNAME@ PACKAGE_URL = @PACKAGE_URL@ PACKAGE_VERSION = @PACKAGE_VERSION@ PANGO_CFLAGS = @PANGO_CFLAGS@ PANGO_LIBS = @PANGO_LIBS@ PATH_SEPARATOR = @PATH_SEPARATOR@ PKG_CONFIG = @PKG_CONFIG@ RANLIB = @RANLIB@ RELOCATABLE = @RELOCATABLE@ RELOC_CPPFLAGS = @RELOC_CPPFLAGS@ RELOC_LDFLAGS = @RELOC_LDFLAGS@ SDL_CFLAGS = @SDL_CFLAGS@ SDL_LIBS = @SDL_LIBS@ SED = @SED@ SET_MAKE = @SET_MAKE@ SHELL = @SHELL@ SOCKET_LIBS = @SOCKET_LIBS@ STRIP = @STRIP@ SYNC_CFLAGS = @SYNC_CFLAGS@ TCLSH = @TCLSH@ TIMEOUT = @TIMEOUT@ VERSION = @VERSION@ VERSION_INFO = @VERSION_INFO@ WINDRES = @WINDRES@ WINEWRAPPER = @WINEWRAPPER@ WINEWRAPPERDEP = @WINEWRAPPERDEP@ XMKMF = @XMKMF@ XZIP = @XZIP@ X_CFLAGS = @X_CFLAGS@ X_EXTRA_LIBS = @X_EXTRA_LIBS@ X_LIBS = @X_LIBS@ X_PRE_LIBS = @X_PRE_LIBS@ YACC = @YACC@ ZIP = @ZIP@ abs_builddir = @abs_builddir@ abs_srcdir = @abs_srcdir@ abs_top_builddir = @abs_top_builddir@ abs_top_srcdir = @abs_top_srcdir@ ac_ct_AR = @ac_ct_AR@ ac_ct_CC = @ac_ct_CC@ ac_ct_DUMPBIN = @ac_ct_DUMPBIN@ am__include = @am__include@ am__leading_dot = @am__leading_dot@ am__quote = @am__quote@ am__tar = @am__tar@ am__untar = @am__untar@ bindir = @bindir@ build = @build@ build_alias = @build_alias@ build_cpu = @build_cpu@ build_os = @build_os@ build_vendor = @build_vendor@ builddir = @builddir@ datadir = @datadir@ datarootdir = @datarootdir@ docdir = @docdir@ dvidir = @dvidir@ enable_mysql_tests = @enable_mysql_tests@ exec_prefix = @exec_prefix@ host = @host@ host_alias = @host_alias@ host_cpu = @host_cpu@ host_os = @host_os@ host_vendor = @host_vendor@ htmldir = @htmldir@ imagedir = @imagedir@ includedir = @includedir@ infodir = @infodir@ install_sh = @install_sh@ libdir = @libdir@ libexecdir = @libexecdir@ lispdir = @lispdir@ lispstartdir = @lispstartdir@ localedir = @localedir@ localstatedir = @localstatedir@ mandir = @mandir@ mkdir_p = @mkdir_p@ moduledir = @moduledir@ moduleexecdir = @moduleexecdir@ oldincludedir = @oldincludedir@ pdfdir = @pdfdir@ prefix = @prefix@ program_transform_name = @program_transform_name@ psdir = @psdir@ sbindir = @sbindir@ sharedstatedir = @sharedstatedir@ srcdir = @srcdir@ subdirs = @subdirs@ sysconfdir = @sysconfdir@ target_alias = @target_alias@ top_build_prefix = @top_build_prefix@ top_builddir = @top_builddir@ top_srcdir = @top_srcdir@ DISTCLEANFILES = asm.h core.h funcs.h fp.h EXTRA_DIST = i386/Makefile.frag \ i386/asm-32.h i386/asm-64.h i386/asm-i386.h \ i386/core-32.h i386/core-64.h i386/core-i386.h \ i386/fp-32.h i386/fp-64.h \ i386/funcs.h \ sparc/asm.h sparc/core.h sparc/funcs.h sparc/fp.h \ ppc/asm.h ppc/core.h ppc/funcs.h ppc/fp.h LIGHTNING_COMMON_FILES = funcs-common.h core-common.h fp-common.h asm-common.h @LIGHTNING_MAIN_TRUE@lightningdir = $(includedir)/lightning @LIGHTNING_MAIN_TRUE@dist_pkgdata_DATA = Makefile.am @LIGHTNING_MAIN_TRUE@dist_lightning_HEADERS = $(LIGHTNING_COMMON_FILES) @LIGHTNING_MAIN_TRUE@nodist_lightning_HEADERS = asm.h core.h funcs.h fp.h $(LIGHTNING_TARGET_FILES) all: all-am .SUFFIXES: $(srcdir)/Makefile.in: $(srcdir)/Makefile.am $(am__configure_deps) @for dep in $?; do \ case '$(am__configure_deps)' in \ *$$dep*) \ ( cd $(top_builddir) && $(MAKE) $(AM_MAKEFLAGS) am--refresh ) \ && { if test -f $@; then exit 0; else break; fi; }; \ exit 1;; \ esac; \ done; \ echo ' cd $(top_srcdir) && $(AUTOMAKE) --gnu lightning/Makefile'; \ $(am__cd) $(top_srcdir) && \ $(AUTOMAKE) --gnu lightning/Makefile .PRECIOUS: Makefile Makefile: $(srcdir)/Makefile.in $(top_builddir)/config.status @case '$?' in \ *config.status*) \ cd $(top_builddir) && $(MAKE) $(AM_MAKEFLAGS) am--refresh;; \ *) \ echo ' cd $(top_builddir) && $(SHELL) ./config.status $(subdir)/$@ $(am__depfiles_maybe)'; \ cd $(top_builddir) && $(SHELL) ./config.status $(subdir)/$@ $(am__depfiles_maybe);; \ esac; $(top_builddir)/config.status: $(top_srcdir)/configure $(CONFIG_STATUS_DEPENDENCIES) cd $(top_builddir) && $(MAKE) $(AM_MAKEFLAGS) am--refresh $(top_srcdir)/configure: $(am__configure_deps) cd $(top_builddir) && $(MAKE) $(AM_MAKEFLAGS) am--refresh $(ACLOCAL_M4): $(am__aclocal_m4_deps) cd $(top_builddir) && $(MAKE) $(AM_MAKEFLAGS) am--refresh $(am__aclocal_m4_deps): mostlyclean-libtool: -rm -f *.lo clean-libtool: -rm -rf .libs _libs install-dist_pkgdataDATA: $(dist_pkgdata_DATA) @$(NORMAL_INSTALL) @list='$(dist_pkgdata_DATA)'; test -n "$(pkgdatadir)" || list=; \ if test -n "$$list"; then \ echo " $(MKDIR_P) '$(DESTDIR)$(pkgdatadir)'"; \ $(MKDIR_P) "$(DESTDIR)$(pkgdatadir)" || exit 1; \ fi; \ for p in $$list; do \ if test -f "$$p"; then d=; else d="$(srcdir)/"; fi; \ echo "$$d$$p"; \ done | $(am__base_list) | \ while read files; do \ echo " $(INSTALL_DATA) $$files '$(DESTDIR)$(pkgdatadir)'"; \ $(INSTALL_DATA) $$files "$(DESTDIR)$(pkgdatadir)" || exit $$?; \ done uninstall-dist_pkgdataDATA: @$(NORMAL_UNINSTALL) @list='$(dist_pkgdata_DATA)'; test -n "$(pkgdatadir)" || list=; \ files=`for p in $$list; do echo $$p; done | sed -e 's|^.*/||'`; \ dir='$(DESTDIR)$(pkgdatadir)'; $(am__uninstall_files_from_dir) install-dist_lightningHEADERS: $(dist_lightning_HEADERS) @$(NORMAL_INSTALL) @list='$(dist_lightning_HEADERS)'; test -n "$(lightningdir)" || list=; \ if test -n "$$list"; then \ echo " $(MKDIR_P) '$(DESTDIR)$(lightningdir)'"; \ $(MKDIR_P) "$(DESTDIR)$(lightningdir)" || exit 1; \ fi; \ for p in $$list; do \ if test -f "$$p"; then d=; else d="$(srcdir)/"; fi; \ echo "$$d$$p"; \ done | $(am__base_list) | \ while read files; do \ echo " $(INSTALL_HEADER) $$files '$(DESTDIR)$(lightningdir)'"; \ $(INSTALL_HEADER) $$files "$(DESTDIR)$(lightningdir)" || exit $$?; \ done uninstall-dist_lightningHEADERS: @$(NORMAL_UNINSTALL) @list='$(dist_lightning_HEADERS)'; test -n "$(lightningdir)" || list=; \ files=`for p in $$list; do echo $$p; done | sed -e 's|^.*/||'`; \ dir='$(DESTDIR)$(lightningdir)'; $(am__uninstall_files_from_dir) install-nodist_lightningHEADERS: $(nodist_lightning_HEADERS) @$(NORMAL_INSTALL) @list='$(nodist_lightning_HEADERS)'; test -n "$(lightningdir)" || list=; \ if test -n "$$list"; then \ echo " $(MKDIR_P) '$(DESTDIR)$(lightningdir)'"; \ $(MKDIR_P) "$(DESTDIR)$(lightningdir)" || exit 1; \ fi; \ for p in $$list; do \ if test -f "$$p"; then d=; else d="$(srcdir)/"; fi; \ echo "$$d$$p"; \ done | $(am__base_list) | \ while read files; do \ echo " $(INSTALL_HEADER) $$files '$(DESTDIR)$(lightningdir)'"; \ $(INSTALL_HEADER) $$files "$(DESTDIR)$(lightningdir)" || exit $$?; \ done uninstall-nodist_lightningHEADERS: @$(NORMAL_UNINSTALL) @list='$(nodist_lightning_HEADERS)'; test -n "$(lightningdir)" || list=; \ files=`for p in $$list; do echo $$p; done | sed -e 's|^.*/||'`; \ dir='$(DESTDIR)$(lightningdir)'; $(am__uninstall_files_from_dir) ID: $(HEADERS) $(SOURCES) $(LISP) $(TAGS_FILES) list='$(SOURCES) $(HEADERS) $(LISP) $(TAGS_FILES)'; \ unique=`for i in $$list; do \ if test -f "$$i"; then echo $$i; else echo $(srcdir)/$$i; fi; \ done | \ $(AWK) '{ files[$$0] = 1; nonempty = 1; } \ END { if (nonempty) { for (i in files) print i; }; }'`; \ mkid -fID $$unique tags: TAGS TAGS: $(HEADERS) $(SOURCES) $(TAGS_DEPENDENCIES) \ $(TAGS_FILES) $(LISP) set x; \ here=`pwd`; \ list='$(SOURCES) $(HEADERS) $(LISP) $(TAGS_FILES)'; \ unique=`for i in $$list; do \ if test -f "$$i"; then echo $$i; else echo $(srcdir)/$$i; fi; \ done | \ $(AWK) '{ files[$$0] = 1; nonempty = 1; } \ END { if (nonempty) { for (i in files) print i; }; }'`; \ shift; \ if test -z "$(ETAGS_ARGS)$$*$$unique"; then :; else \ test -n "$$unique" || unique=$$empty_fix; \ if test $$# -gt 0; then \ $(ETAGS) $(ETAGSFLAGS) $(AM_ETAGSFLAGS) $(ETAGS_ARGS) \ "$$@" $$unique; \ else \ $(ETAGS) $(ETAGSFLAGS) $(AM_ETAGSFLAGS) $(ETAGS_ARGS) \ $$unique; \ fi; \ fi ctags: CTAGS CTAGS: $(HEADERS) $(SOURCES) $(TAGS_DEPENDENCIES) \ $(TAGS_FILES) $(LISP) list='$(SOURCES) $(HEADERS) $(LISP) $(TAGS_FILES)'; \ unique=`for i in $$list; do \ if test -f "$$i"; then echo $$i; else echo $(srcdir)/$$i; fi; \ done | \ $(AWK) '{ files[$$0] = 1; nonempty = 1; } \ END { if (nonempty) { for (i in files) print i; }; }'`; \ test -z "$(CTAGS_ARGS)$$unique" \ || $(CTAGS) $(CTAGSFLAGS) $(AM_CTAGSFLAGS) $(CTAGS_ARGS) \ $$unique GTAGS: here=`$(am__cd) $(top_builddir) && pwd` \ && $(am__cd) $(top_srcdir) \ && gtags -i $(GTAGS_ARGS) "$$here" distclean-tags: -rm -f TAGS ID GTAGS GRTAGS GSYMS GPATH tags @LIGHTNING_MAIN_TRUE@dist-hook: distdir: $(DISTFILES) @srcdirstrip=`echo "$(srcdir)" | sed 's/[].[^$$\\*]/\\\\&/g'`; \ topsrcdirstrip=`echo "$(top_srcdir)" | sed 's/[].[^$$\\*]/\\\\&/g'`; \ list='$(DISTFILES)'; \ dist_files=`for file in $$list; do echo $$file; done | \ sed -e "s|^$$srcdirstrip/||;t" \ -e "s|^$$topsrcdirstrip/|$(top_builddir)/|;t"`; \ case $$dist_files in \ */*) $(MKDIR_P) `echo "$$dist_files" | \ sed '/\//!d;s|^|$(distdir)/|;s,/[^/]*$$,,' | \ sort -u` ;; \ esac; \ for file in $$dist_files; do \ if test -f $$file || test -d $$file; then d=.; else d=$(srcdir); fi; \ if test -d $$d/$$file; then \ dir=`echo "/$$file" | sed -e 's,/[^/]*$$,,'`; \ if test -d "$(distdir)/$$file"; then \ find "$(distdir)/$$file" -type d ! -perm -700 -exec chmod u+rwx {} \;; \ fi; \ if test -d $(srcdir)/$$file && test $$d != $(srcdir); then \ cp -fpR $(srcdir)/$$file "$(distdir)$$dir" || exit 1; \ find "$(distdir)/$$file" -type d ! -perm -700 -exec chmod u+rwx {} \;; \ fi; \ cp -fpR $$d/$$file "$(distdir)$$dir" || exit 1; \ else \ test -f "$(distdir)/$$file" \ || cp -p $$d/$$file "$(distdir)/$$file" \ || exit 1; \ fi; \ done $(MAKE) $(AM_MAKEFLAGS) \ top_distdir="$(top_distdir)" distdir="$(distdir)" \ dist-hook check-am: all-am check: check-am all-am: Makefile $(DATA) $(HEADERS) installdirs: for dir in "$(DESTDIR)$(pkgdatadir)" "$(DESTDIR)$(lightningdir)" "$(DESTDIR)$(lightningdir)"; do \ test -z "$$dir" || $(MKDIR_P) "$$dir"; \ done install: install-am install-exec: install-exec-am install-data: install-data-am uninstall: uninstall-am install-am: all-am @$(MAKE) $(AM_MAKEFLAGS) install-exec-am install-data-am installcheck: installcheck-am install-strip: if test -z '$(STRIP)'; then \ $(MAKE) $(AM_MAKEFLAGS) INSTALL_PROGRAM="$(INSTALL_STRIP_PROGRAM)" \ install_sh_PROGRAM="$(INSTALL_STRIP_PROGRAM)" INSTALL_STRIP_FLAG=-s \ install; \ else \ $(MAKE) $(AM_MAKEFLAGS) INSTALL_PROGRAM="$(INSTALL_STRIP_PROGRAM)" \ install_sh_PROGRAM="$(INSTALL_STRIP_PROGRAM)" INSTALL_STRIP_FLAG=-s \ "INSTALL_PROGRAM_ENV=STRIPPROG='$(STRIP)'" install; \ fi mostlyclean-generic: clean-generic: distclean-generic: -test -z "$(CONFIG_CLEAN_FILES)" || rm -f $(CONFIG_CLEAN_FILES) -test . = "$(srcdir)" || test -z "$(CONFIG_CLEAN_VPATH_FILES)" || rm -f $(CONFIG_CLEAN_VPATH_FILES) -test -z "$(DISTCLEANFILES)" || rm -f $(DISTCLEANFILES) maintainer-clean-generic: @echo "This command is intended for maintainers to use" @echo "it deletes files that may require special tools to rebuild." @LIGHTNING_MAIN_TRUE@clean-local: clean: clean-am clean-am: clean-generic clean-libtool clean-local mostlyclean-am distclean: distclean-am -rm -f Makefile distclean-am: clean-am distclean-generic distclean-tags dvi: dvi-am dvi-am: html: html-am html-am: info: info-am info-am: install-data-am: install-dist_lightningHEADERS \ install-dist_pkgdataDATA install-nodist_lightningHEADERS install-dvi: install-dvi-am install-dvi-am: install-exec-am: install-html: install-html-am install-html-am: install-info: install-info-am install-info-am: install-man: install-pdf: install-pdf-am install-pdf-am: install-ps: install-ps-am install-ps-am: installcheck-am: maintainer-clean: maintainer-clean-am -rm -f Makefile maintainer-clean-am: distclean-am maintainer-clean-generic mostlyclean: mostlyclean-am mostlyclean-am: mostlyclean-generic mostlyclean-libtool pdf: pdf-am pdf-am: ps: ps-am ps-am: uninstall-am: uninstall-dist_lightningHEADERS \ uninstall-dist_pkgdataDATA uninstall-nodist_lightningHEADERS .MAKE: install-am install-strip .PHONY: CTAGS GTAGS all all-am check check-am clean clean-generic \ clean-libtool clean-local ctags dist-hook distclean \ distclean-generic distclean-libtool distclean-tags distdir dvi \ dvi-am html html-am info info-am install install-am \ install-data install-data-am install-dist_lightningHEADERS \ install-dist_pkgdataDATA install-dvi install-dvi-am \ install-exec install-exec-am install-html install-html-am \ install-info install-info-am install-man \ install-nodist_lightningHEADERS install-pdf install-pdf-am \ install-ps install-ps-am install-strip installcheck \ installcheck-am installdirs maintainer-clean \ maintainer-clean-generic mostlyclean mostlyclean-generic \ mostlyclean-libtool pdf pdf-am ps ps-am tags uninstall \ uninstall-am uninstall-dist_lightningHEADERS \ uninstall-dist_pkgdataDATA uninstall-nodist_lightningHEADERS @lightning_frag@ @LIGHTNING_MAIN_FALSE@all-am: @LIGHTNING_MAIN_FALSE@ @set frob $(LIGHTNING_TARGET_FILES); shift; \ @LIGHTNING_MAIN_FALSE@ for i; \ @LIGHTNING_MAIN_FALSE@ do \ @LIGHTNING_MAIN_FALSE@ echo $(LN_S) -f $(srcdir)/$$i `basename $$i`; \ @LIGHTNING_MAIN_FALSE@ $(LN_S) -f $(srcdir)/$$i `basename $$i`; \ @LIGHTNING_MAIN_FALSE@ done @LIGHTNING_MAIN_FALSE@clean-local: @LIGHTNING_MAIN_FALSE@ @set frob $(LIGHTNING_TARGET_FILES); shift; \ @LIGHTNING_MAIN_FALSE@ for i; \ @LIGHTNING_MAIN_FALSE@ do \ @LIGHTNING_MAIN_FALSE@ echo rm -f `basename $$i`; \ @LIGHTNING_MAIN_FALSE@ rm -f `basename $$i`; \ @LIGHTNING_MAIN_FALSE@ done @LIGHTNING_MAIN_FALSE@dist-hook: @LIGHTNING_MAIN_FALSE@ cp -p $(srcdir)/lightning.h $(distdir) # Tell versions [3.59,3.63) of GNU make to not export all variables. # Otherwise a system limit (for SysV at least) may be exceeded. .NOEXPORT: smalltalk-3.2.5/lightning/core-common.h0000644000175000017500000006510612123404352015004 00000000000000/******************************** -*- C -*- **************************** * * Platform-independent layer support * ***********************************************************************/ /*********************************************************************** * * Copyright 2000, 2001, 2002, 2003 Free Software Foundation, Inc. * Written by Paolo Bonzini. * * This file is part of GNU lightning. * * GNU lightning is free software; you can redistribute it and/or modify it * under the terms of the GNU Lesser General Public License as published * by the Free Software Foundation; either version 2.1, or (at your option) * any later version. * * GNU lightning is distributed in the hope that it will be useful, but * WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY * or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser General Public * License for more details. * * You should have received a copy of the GNU Lesser General Public License * along with GNU lightning; see the file COPYING.LESSER; if not, write to the * Free Software Foundation, 51 Franklin Street, Fifth Floor, Boston, * MA 02110-1301, USA. * ***********************************************************************/ #ifndef __lightning_core_common_h #define __lightning_core_common_h_ typedef struct { union { jit_insn *pc; _uc *uc_pc; _us *us_pc; _ui *ui_pc; _ul *ul_pc; } x; struct jit_fp *fp; struct jit_local_state jitl; } jit_state; #ifdef jit_init static jit_state _jit = jit_init (); #else static jit_state _jit; #endif #define JIT_NOREG (-1) #define JIT_R0 JIT_R(0) #define JIT_R1 JIT_R(1) #define JIT_R2 JIT_R(2) #define JIT_V0 JIT_V(0) #define JIT_V1 JIT_V(1) #define JIT_V2 JIT_V(2) #define _jitl _jit.jitl #define jit_get_ip() (*(jit_code *) &_jit.x.pc) #define jit_set_ip(ptr) (_jit.x.pc = (ptr), jit_get_ip ()) #define jit_get_label() (_jit.x.pc) #define jit_forward() (_jit.x.pc) #define jit_field(struc, f) ( ((long) (&((struc *) 8)->f) ) - 8) #define jit_ptr_field(struc_p, f) ( ((long) (&((struc_p) 8)->f) ) - 8) /* realignment via N-byte no-ops */ #ifndef jit_align #define jit_align(n) #endif /* jit_code: union of many possible function pointer types. Returned * by jit_get_ip(). */ typedef union jit_code { char *ptr; void (*vptr)(void); char (*cptr)(void); unsigned char (*ucptr)(void); short (*sptr)(void); unsigned short (*usptr)(void); int (*iptr)(void); unsigned int (*uiptr)(void); long (*lptr)(void); unsigned long (*ulptr)(void); void * (*pptr)(void); float (*fptr)(void); double (*dptr)(void); } jit_code; #ifndef jit_fill_delay_after #define jit_fill_delay_after(branch) (branch) #endif #define jit_delay(insn, branch) ((insn), jit_fill_delay_after(branch)) /* ALU synonyms */ #define jit_addi_ui(d, rs, is) jit_addi_i((d), (rs), (is)) #define jit_addr_ui(d, s1, s2) jit_addr_i((d), (s1), (s2)) #define jit_addci_ui(d, rs, is) jit_addci_i((d), (rs), (is)) #define jit_addcr_ui(d, s1, s2) jit_addcr_i((d), (s1), (s2)) #define jit_addxi_ui(d, rs, is) jit_addxi_i((d), (rs), (is)) #define jit_addxr_ui(d, s1, s2) jit_addxr_i((d), (s1), (s2)) #define jit_andi_ui(d, rs, is) jit_andi_i((d), (rs), (is)) #define jit_andr_ui(d, s1, s2) jit_andr_i((d), (s1), (s2)) #define jit_lshi_ui(d, rs, is) jit_lshi_i((d), (rs), (is)) #define jit_lshr_ui(d, s1, s2) jit_lshr_i((d), (s1), (s2)) #define jit_movi_ui(d, rs) jit_movi_i((d), (rs)) #define jit_movr_ui(d, rs) jit_movr_i((d), (rs)) #define jit_ori_ui(d, rs, is) jit_ori_i((d), (rs), (is)) #define jit_orr_ui(d, s1, s2) jit_orr_i((d), (s1), (s2)) #define jit_rsbi_ui(d, rs, is) jit_rsbi_i((d), (rs), (is)) #define jit_rsbr_ui(d, s1, s2) jit_rsbr_i((d), (s1), (s2)) #define jit_subi_ui(d, rs, is) jit_subi_i((d), (rs), (is)) #define jit_subr_ui(d, s1, s2) jit_subr_i((d), (s1), (s2)) #define jit_subci_ui(d, rs, is) jit_subci_i((d), (rs), (is)) #define jit_subcr_ui(d, s1, s2) jit_subcr_i((d), (s1), (s2)) #define jit_subxi_ui(d, rs, is) jit_subxi_i((d), (rs), (is)) #define jit_subxr_ui(d, s1, s2) jit_subxr_i((d), (s1), (s2)) #define jit_xori_ui(d, rs, is) jit_xori_i((d), (rs), (is)) #define jit_xorr_ui(d, s1, s2) jit_xorr_i((d), (s1), (s2)) #define jit_addi_ul(d, rs, is) jit_addi_l((d), (rs), (is)) #define jit_addr_ul(d, s1, s2) jit_addr_l((d), (s1), (s2)) #define jit_addci_ul(d, rs, is) jit_addci_l((d), (rs), (is)) #define jit_addcr_ul(d, s1, s2) jit_addcr_l((d), (s1), (s2)) #define jit_addxi_ul(d, rs, is) jit_addxi_l((d), (rs), (is)) #define jit_addxr_ul(d, s1, s2) jit_addxr_l((d), (s1), (s2)) #define jit_andi_ul(d, rs, is) jit_andi_l((d), (rs), (is)) #define jit_andr_ul(d, s1, s2) jit_andr_l((d), (s1), (s2)) #define jit_lshi_ul(d, rs, is) jit_lshi_l((d), (rs), (is)) #define jit_lshr_ul(d, s1, s2) jit_lshr_l((d), (s1), (s2)) #define jit_movi_ul(d, rs) jit_movi_l((d), (rs)) #define jit_movr_ul(d, rs) jit_movr_l((d), (rs)) #define jit_ori_ul(d, rs, is) jit_ori_l((d), (rs), (is)) #define jit_orr_ul(d, s1, s2) jit_orr_l((d), (s1), (s2)) #define jit_rsbi_ul(d, rs, is) jit_rsbi_l((d), (rs), (is)) #define jit_rsbr_ul(d, s1, s2) jit_rsbr_l((d), (s1), (s2)) #define jit_subi_ul(d, rs, is) jit_subi_l((d), (rs), (is)) #define jit_subr_ul(d, s1, s2) jit_subr_l((d), (s1), (s2)) #define jit_subci_ul(d, rs, is) jit_subci_l((d), (rs), (is)) #define jit_subcr_ul(d, s1, s2) jit_subcr_l((d), (s1), (s2)) #define jit_subxi_ui(d, rs, is) jit_subxi_i((d), (rs), (is)) #define jit_subxi_ul(d, rs, is) jit_subxi_l((d), (rs), (is)) #define jit_subxr_ui(d, s1, s2) jit_subxr_i((d), (s1), (s2)) #define jit_subxr_ul(d, s1, s2) jit_subxr_i((d), (s1), (s2)) #define jit_xori_ul(d, rs, is) jit_xori_l((d), (rs), (is)) #define jit_xorr_ul(d, s1, s2) jit_xorr_l((d), (s1), (s2)) #define jit_addr_p(d, s1, s2) jit_addr_ul((d), (s1), (s2)) #define jit_addi_p(d, rs, is) jit_addi_ul((d), (rs), (long) (is)) #define jit_movr_p(d, rs) jit_movr_ul((d), (rs)) #define jit_subr_p(d, s1, s2) jit_subr_ul((d), (s1), (s2)) #define jit_subi_p(d, rs, is) jit_subi_ul((d), (rs), (long) (is)) #define jit_rsbi_p(d, rs, is) jit_rsbi_ul((d), (rs), (long) (is)) #ifndef jit_movi_p #define jit_movi_p(d, is) (jit_movi_ul((d), (long) (is)), _jit.x.pc) #endif #define jit_patch(pv) jit_patch_at ((pv), (_jit.x.pc)) #ifndef jit_addci_i #define jit_addci_i(d, rs, is) jit_addi_i((d), (rs), (is)) #define jit_addcr_i(d, s1, s2) jit_addr_i((d), (s1), (s2)) #define jit_addci_l(d, rs, is) jit_addi_l((d), (rs), (is)) #define jit_addcr_l(d, s1, s2) jit_addr_l((d), (s1), (s2)) #endif #ifndef jit_subcr_i #define jit_subcr_i(d, s1, s2) jit_subr_i((d), (s1), (s2)) #endif /* NEG is not mandatory -- pick an appropriate implementation */ #ifndef jit_negr_i # ifdef JIT_RZERO # define jit_negr_i(d, rs) jit_subr_i((d), JIT_RZERO, (rs)) # define jit_negr_l(d, rs) jit_subr_l((d), JIT_RZERO, (rs)) # else /* !JIT_RZERO */ # ifndef jit_rsbi_i # define jit_negr_i(d, rs) (jit_xori_i((d), (rs), -1), jit_addi_l((d), (d), 1)) # define jit_negr_l(d, rs) (jit_xori_l((d), (rs), -1), jit_addi_l((d), (d), 1)) # else /* jit_rsbi_i */ # define jit_negr_i(d, rs) jit_rsbi_i((d), (rs), 0) # define jit_negr_l(d, rs) jit_rsbi_l((d), (rs), 0) # endif /* jit_rsbi_i */ # endif /* !JIT_RZERO */ #endif /* !jit_negr_i */ /* RSB is not mandatory */ #ifndef jit_rsbi_i # define jit_rsbi_i(d, rs, is) (jit_subi_i((d), (rs), (is)), jit_negr_i((d), (d))) # ifndef jit_rsbi_l # define jit_rsbi_l(d, rs, is) (jit_subi_l((d), (rs), (is)), jit_negr_l((d), (d))) # endif #endif /* Common 'shortcut' implementations */ #define jit_subi_i(d, rs, is) jit_addi_i((d), (rs), -(is)) #define jit_subi_l(d, rs, is) jit_addi_l((d), (rs), -(is)) #define jit_subci_i(d, rs, is) jit_addci_i((d), (rs), -(is)) #define jit_subci_l(d, rs, is) jit_addci_l((d), (rs), -(is)) #define jit_rsbr_f(d, s1, s2) jit_subr_f((d), (s2), (s1)) #define jit_rsbr_d(d, s1, s2) jit_subr_d((d), (s2), (s1)) #define jit_rsbr_i(d, s1, s2) jit_subr_i((d), (s2), (s1)) #define jit_rsbr_l(d, s1, s2) jit_subr_l((d), (s2), (s1)) #define jit_rsbr_p(d, s1, s2) jit_subr_p((d), (s2), (s1)) /* Unary */ #define jit_notr_c(d, rs) jit_xori_c((d), (rs), 255) #define jit_notr_uc(d, rs) jit_xori_c((d), (rs), 255) #define jit_notr_s(d, rs) jit_xori_s((d), (rs), 65535) #define jit_notr_us(d, rs) jit_xori_s((d), (rs), 65535) #define jit_notr_i(d, rs) jit_xori_i((d), (rs), ~0) #define jit_notr_ui(d, rs) jit_xori_i((d), (rs), ~0) #define jit_notr_l(d, rs) jit_xori_l((d), (rs), ~0L) #define jit_notr_ul(d, rs) jit_xori_l((d), (rs), ~0L) #ifndef jit_extr_c_ui #define jit_extr_c_ui(d, rs) jit_andi_ui((d), (rs), 0xFF) #endif #ifndef jit_extr_s_ui #define jit_extr_s_ui(d, rs) jit_andi_ui((d), (rs), 0xFFFF) #endif #ifndef jit_extr_c_i #define jit_extr_c_i(d, rs) (jit_lshi_i((d), (rs), 24), jit_rshi_i((d), (d), 24)) #endif #ifndef jit_extr_s_i #define jit_extr_s_i(d, rs) (jit_lshi_i((d), (rs), 16), jit_rshi_i((d), (d), 16)) #endif #ifdef jit_addi_l /* sizeof(long) != sizeof(int) */ #ifndef jit_extr_c_l #define jit_extr_c_l(d, rs) (jit_lshi_l((d), (rs), 56), jit_rshi_l((d), (d), 56)) #endif #ifndef jit_extr_s_l #define jit_extr_s_l(d, rs) (jit_lshi_l((d), (rs), 48), jit_rshi_l((d), (d), 48)) #endif #ifndef jit_extr_i_l #define jit_extr_i_l(d, rs) (jit_lshi_l((d), (rs), 32), jit_rshi_l((d), (d), 32)) #endif #ifndef jit_extr_c_ul #define jit_extr_c_ul(d, rs) jit_andi_l((d), (rs), 0xFF) #endif #ifndef jit_extr_s_ul #define jit_extr_s_ul(d, rs) jit_andi_l((d), (rs), 0xFFFF) #endif #ifndef jit_extr_i_ul #define jit_extr_i_ul(d, rs) jit_andi_l((d), (rs), 0xFFFFFFFFUL) #endif #endif #define jit_extr_c_s(d, rs) jit_extr_c_i((d), (rs)) #define jit_extr_c_us(d, rs) jit_extr_c_ui((d), (rs)) #define jit_extr_uc_s(d, rs) jit_extr_uc_i((d), (rs)) #define jit_extr_uc_us(d, rs) jit_extr_uc_ui((d), (rs)) #define jit_extr_uc_i(d, rs) jit_extr_c_ui((d), (rs)) #define jit_extr_uc_ui(d, rs) jit_extr_c_ui((d), (rs)) #define jit_extr_us_i(d, rs) jit_extr_s_ui((d), (rs)) #define jit_extr_us_ui(d, rs) jit_extr_s_ui((d), (rs)) #define jit_extr_uc_l(d, rs) jit_extr_c_ul((d), (rs)) #define jit_extr_uc_ul(d, rs) jit_extr_c_ul((d), (rs)) #define jit_extr_us_l(d, rs) jit_extr_s_ul((d), (rs)) #define jit_extr_us_ul(d, rs) jit_extr_s_ul((d), (rs)) #define jit_extr_ui_l(d, rs) jit_extr_i_ul((d), (rs)) #define jit_extr_ui_ul(d, rs) jit_extr_i_ul((d), (rs)) /* NTOH/HTON is not mandatory for big endian architectures */ #ifndef jit_ntoh_ui /* big endian */ #define jit_ntoh_ui(d, rs) ((d) == (rs) ? (void)0 : jit_movr_i((d), (rs))) #define jit_ntoh_us(d, rs) ((d) == (rs) ? (void)0 : jit_movr_i((d), (rs))) #endif /* big endian */ /* hton is a synonym for ntoh */ #define jit_hton_ui(d, rs) jit_ntoh_ui((d), (rs)) #define jit_hton_us(d, rs) jit_ntoh_us((d), (rs)) /* Stack synonyms */ #define jit_pushr_ui(rs) jit_pushr_i(rs) #define jit_popr_ui(rs) jit_popr_i(rs) #define jit_pushr_ul(rs) jit_pushr_l(rs) #define jit_popr_ul(rs) jit_popr_l(rs) #define jit_pushr_p(rs) jit_pushr_ul(rs) #define jit_popr_p(rs) jit_popr_ul(rs) #define jit_prepare(nint) jit_prepare_i((nint)) #define jit_pusharg_c(rs) jit_pusharg_i(rs) #define jit_pusharg_s(rs) jit_pusharg_i(rs) #define jit_pusharg_uc(rs) jit_pusharg_i(rs) #define jit_pusharg_us(rs) jit_pusharg_i(rs) #define jit_pusharg_ui(rs) jit_pusharg_i(rs) #define jit_pusharg_ul(rs) jit_pusharg_l(rs) #define jit_pusharg_p(rs) jit_pusharg_ul(rs) /* Memory synonyms */ #ifdef JIT_RZERO #ifndef jit_ldi_c #define jit_ldi_c(rd, is) jit_ldxi_c((rd), JIT_RZERO, (is)) #define jit_sti_c(id, rs) jit_stxi_c((id), JIT_RZERO, (rs)) #define jit_ldi_s(rd, is) jit_ldxi_s((rd), JIT_RZERO, (is)) #define jit_sti_s(id, rs) jit_stxi_s((id), JIT_RZERO, (rs)) #define jit_ldi_i(rd, is) jit_ldxi_i((rd), JIT_RZERO, (is)) #define jit_sti_i(id, rs) jit_stxi_i((id), JIT_RZERO, (rs)) #define jit_ldi_l(rd, is) jit_ldxi_l((rd), JIT_RZERO, (is)) #define jit_sti_l(id, rs) jit_stxi_l((id), JIT_RZERO, (rs)) #define jit_ldi_uc(rd, is) jit_ldxi_uc((rd), JIT_RZERO, (is)) #define jit_ldi_us(rd, is) jit_ldxi_us((rd), JIT_RZERO, (is)) #define jit_ldi_ui(rd, is) jit_ldxi_ui((rd), JIT_RZERO, (is)) #define jit_ldi_ul(rd, is) jit_ldxi_ul((rd), JIT_RZERO, (is)) #endif #ifndef jit_ldr_c #define jit_ldr_c(rd, rs) jit_ldxr_c((rd), JIT_RZERO, (rs)) #define jit_str_c(rd, rs) jit_stxr_c(JIT_RZERO, (rd), (rs)) #define jit_ldr_s(rd, rs) jit_ldxr_s((rd), JIT_RZERO, (rs)) #define jit_str_s(rd, rs) jit_stxr_s(JIT_RZERO, (rd), (rs)) #define jit_ldr_i(rd, rs) jit_ldxr_i((rd), JIT_RZERO, (rs)) #define jit_str_i(rd, rs) jit_stxr_i(JIT_RZERO, (rd), (rs)) #define jit_ldr_l(rd, rs) jit_ldxr_l((rd), JIT_RZERO, (rs)) #define jit_str_l(rd, rs) jit_stxr_l(JIT_RZERO, (rd), (rs)) #define jit_ldr_uc(rd, rs) jit_ldxr_uc((rd), JIT_RZERO, (rs)) #define jit_ldr_us(rd, rs) jit_ldxr_us((rd), JIT_RZERO, (rs)) #define jit_ldr_ui(rd, rs) jit_ldxr_ui((rd), JIT_RZERO, (rs)) #define jit_ldr_ul(rd, rs) jit_ldxr_ul((rd), JIT_RZERO, (rs)) #endif #endif #define jit_str_uc(rd, rs) jit_str_c((rd), (rs)) #define jit_sti_uc(id, rs) jit_sti_c((id), (rs)) #define jit_stxr_uc(d1, d2, rs) jit_stxr_c((d1), (d2), (rs)) #define jit_stxi_uc(id, rd, is) jit_stxi_c((id), (rd), (is)) #define jit_str_us(rd, rs) jit_str_s((rd), (rs)) #define jit_sti_us(id, rs) jit_sti_s((id), (rs)) #define jit_stxr_us(d1, d2, rs) jit_stxr_s((d1), (d2), (rs)) #define jit_stxi_us(id, rd, is) jit_stxi_s((id), (rd), (is)) #define jit_str_ui(rd, rs) jit_str_i((rd), (rs)) #define jit_sti_ui(id, rs) jit_sti_i((id), (rs)) #define jit_stxr_ui(d1, d2, rs) jit_stxr_i((d1), (d2), (rs)) #define jit_stxi_ui(id, rd, is) jit_stxi_i((id), (rd), (is)) #define jit_str_ul(rd, rs) jit_str_l((rd), (rs)) #define jit_sti_ul(id, rs) jit_sti_l((id), (rs)) #define jit_stxr_ul(d1, d2, rs) jit_stxr_l((d1), (d2), (rs)) #define jit_stxi_ul(id, rd, is) jit_stxi_l((id), (rd), (is)) #define jit_str_p(rd, rs) jit_str_l((rd), (rs)) #define jit_sti_p(id, rs) jit_sti_l((id), (rs)) #define jit_stxr_p(d1, d2, rs) jit_stxr_l((d1), (d2), (rs)) #define jit_stxi_p(id, rd, is) jit_stxi_l((id), (rd), (is)) #define jit_ldr_p(rd, rs) jit_ldr_l((rd), (rs)) #define jit_ldi_p(rd, is) jit_ldi_l((rd), (is)) #define jit_ldxr_p(rd, s1, s2) jit_ldxr_l((rd), (s1), (s2)) #define jit_ldxi_p(rd, rs, is) jit_ldxi_l((rd), (rs), (is)) /* Boolean & branch synonyms */ #define jit_eqr_ui(d, s1, s2) jit_eqr_i((d), (s1), (s2)) #define jit_eqi_ui(d, rs, is) jit_eqi_i((d), (rs), (is)) #define jit_ner_ui(d, s1, s2) jit_ner_i((d), (s1), (s2)) #define jit_nei_ui(d, rs, is) jit_nei_i((d), (rs), (is)) #define jit_eqr_ul(d, s1, s2) jit_eqr_l((d), (s1), (s2)) #define jit_eqi_ul(d, rs, is) jit_eqi_l((d), (rs), (is)) #define jit_ner_ul(d, s1, s2) jit_ner_l((d), (s1), (s2)) #define jit_nei_ul(d, rs, is) jit_nei_l((d), (rs), (is)) #define jit_beqr_ui(label, s1, s2) jit_beqr_i((label), (s1), (s2)) #define jit_beqi_ui(label, rs, is) jit_beqi_i((label), (rs), (is)) #define jit_bner_ui(label, s1, s2) jit_bner_i((label), (s1), (s2)) #define jit_bnei_ui(label, rs, is) jit_bnei_i((label), (rs), (is)) #define jit_bmcr_ui(label, s1, s2) jit_bmcr_i((label), (s1), (s2)) #define jit_bmci_ui(label, rs, is) jit_bmci_i((label), (rs), (is)) #define jit_bmsr_ui(label, s1, s2) jit_bmsr_i((label), (s1), (s2)) #define jit_bmsi_ui(label, rs, is) jit_bmsi_i((label), (rs), (is)) #define jit_beqr_ul(label, s1, s2) jit_beqr_l((label), (s1), (s2)) #define jit_beqi_ul(label, rs, is) jit_beqi_l((label), (rs), (is)) #define jit_bner_ul(label, s1, s2) jit_bner_l((label), (s1), (s2)) #define jit_bnei_ul(label, rs, is) jit_bnei_l((label), (rs), (is)) #define jit_bmcr_ul(label, s1, s2) jit_bmcr_l((label), (s1), (s2)) #define jit_bmci_ul(label, rs, is) jit_bmci_l((label), (rs), (is)) #define jit_bmsr_ul(label, s1, s2) jit_bmsr_l((label), (s1), (s2)) #define jit_bmsi_ul(label, rs, is) jit_bmsi_l((label), (rs), (is)) #define jit_ltr_p(d, s1, s2) jit_ltr_ul((d), (s1), (s2)) #define jit_lti_p(d, rs, is) jit_lti_ul((d), (rs), (is)) #define jit_ler_p(d, s1, s2) jit_ler_ul((d), (s1), (s2)) #define jit_lei_p(d, rs, is) jit_lei_ul((d), (rs), (is)) #define jit_gtr_p(d, s1, s2) jit_gtr_ul((d), (s1), (s2)) #define jit_gti_p(d, rs, is) jit_gti_ul((d), (rs), (is)) #define jit_ger_p(d, s1, s2) jit_ger_ul((d), (s1), (s2)) #define jit_gei_p(d, rs, is) jit_gei_ul((d), (rs), (is)) #define jit_eqr_p(d, s1, s2) jit_eqr_ul((d), (s1), (s2)) #define jit_eqi_p(d, rs, is) jit_eqi_ul((d), (rs), (is)) #define jit_ner_p(d, s1, s2) jit_ner_ul((d), (s1), (s2)) #define jit_nei_p(d, rs, is) jit_nei_ul((d), (rs), (is)) #define jit_bltr_p(label, s1, s2) jit_bltr_ul((label), (s1), (s2)) #define jit_blti_p(label, rs, is) jit_blti_ul((label), (rs), (is)) #define jit_bler_p(label, s1, s2) jit_bler_ul((label), (s1), (s2)) #define jit_blei_p(label, rs, is) jit_blei_ul((label), (rs), (is)) #define jit_bgtr_p(label, s1, s2) jit_bgtr_ul((label), (s1), (s2)) #define jit_bgti_p(label, rs, is) jit_bgti_ul((label), (rs), (is)) #define jit_bger_p(label, s1, s2) jit_bger_ul((label), (s1), (s2)) #define jit_bgei_p(label, rs, is) jit_bgei_ul((label), (rs), (is)) #define jit_beqr_p(label, s1, s2) jit_beqr_ul((label), (s1), (s2)) #define jit_beqi_p(label, rs, is) jit_beqi_ul((label), (rs), (is)) #define jit_bner_p(label, s1, s2) jit_bner_ul((label), (s1), (s2)) #define jit_bnei_p(label, rs, is) jit_bnei_ul((label), (rs), (is)) #define jit_retval_ui(rd) jit_retval_i((rd)) #define jit_retval_uc(rd) jit_retval_i((rd)) #define jit_retval_us(rd) jit_retval_i((rd)) #define jit_retval_ul(rd) jit_retval_l((rd)) #define jit_retval_p(rd) jit_retval_ul((rd)) #define jit_retval_c(rd) jit_retval_i((rd)) #define jit_retval_s(rd) jit_retval_i((rd)) /* This was a bug, but we keep it. */ #define jit_retval(rd) jit_retval_i ((rd)) #ifndef jit_finish #define jit_finish(sub) jit_calli(sub) #endif #ifndef jit_finishr #define jit_finishr(reg) jit_callr(reg) #endif #ifndef jit_prolog #define jit_prolog(numargs) #endif #ifndef jit_leaf #define jit_leaf(numargs) jit_prolog(numargs) #endif #ifndef jit_getarg_c #ifndef JIT_FP #define jit_getarg_c(reg, ofs) jit_extr_c_i ((reg), (ofs)) #define jit_getarg_i(reg, ofs) jit_movr_i ((reg), (ofs)) #define jit_getarg_l(reg, ofs) jit_movr_l ((reg), (ofs)) #define jit_getarg_p(reg, ofs) jit_movr_p ((reg), (ofs)) #define jit_getarg_s(reg, ofs) jit_extr_s_i ((reg), (ofs)) #define jit_getarg_uc(reg, ofs) jit_extr_uc_ui((reg), (ofs)) #define jit_getarg_ui(reg, ofs) jit_movr_ui ((reg), (ofs)) #define jit_getarg_ul(reg, ofs) jit_extr_uc_ul((reg), (ofs)) #define jit_getarg_us(reg, ofs) jit_extr_us_ul((reg), (ofs)) #else #define jit_getarg_c(reg, ofs) jit_ldxi_c((reg), JIT_FP, (ofs)); #define jit_getarg_uc(reg, ofs) jit_ldxi_uc((reg), JIT_FP, (ofs)); #define jit_getarg_s(reg, ofs) jit_ldxi_s((reg), JIT_FP, (ofs)); #define jit_getarg_us(reg, ofs) jit_ldxi_us((reg), JIT_FP, (ofs)); #define jit_getarg_i(reg, ofs) jit_ldxi_i((reg), JIT_FP, (ofs)); #define jit_getarg_ui(reg, ofs) jit_ldxi_ui((reg), JIT_FP, (ofs)); #define jit_getarg_l(reg, ofs) jit_ldxi_l((reg), JIT_FP, (ofs)); #define jit_getarg_ul(reg, ofs) jit_ldxi_ul((reg), JIT_FP, (ofs)); #define jit_getarg_p(reg, ofs) jit_ldxi_p((reg), JIT_FP, (ofs)); #endif #endif /* Common definitions when sizeof(long) = sizeof(int) */ #ifndef jit_addi_l #define JIT_LONG_IS_INT /* ALU */ #define jit_addi_l(d, rs, is) jit_addi_i((d), (rs), (is)) #define jit_addr_l(d, s1, s2) jit_addr_i((d), (s1), (s2)) #ifndef jit_addci_l #define jit_addci_l(d, rs, is) jit_addci_i((d), (rs), (is)) #endif #ifndef jit_addcr_l #define jit_addcr_l(d, s1, s2) jit_addcr_i((d), (s1), (s2)) #endif #define jit_addxi_l(d, rs, is) jit_addxi_i((d), (rs), (is)) #define jit_addxr_l(d, s1, s2) jit_addxr_i((d), (s1), (s2)) #define jit_andi_l(d, rs, is) jit_andi_i((d), (rs), (is)) #define jit_andr_l(d, s1, s2) jit_andr_i((d), (s1), (s2)) #define jit_divi_l(d, rs, is) jit_divi_i((d), (rs), (is)) #define jit_divr_l(d, s1, s2) jit_divr_i((d), (s1), (s2)) #define jit_hmuli_l(d, rs, is) jit_hmuli_i((d), (rs), (is)) #define jit_hmulr_l(d, s1, s2) jit_hmulr_i((d), (s1), (s2)) #define jit_lshi_l(d, rs, is) jit_lshi_i((d), (rs), (is)) #define jit_lshr_l(d, s1, s2) jit_lshr_i((d), (s1), (s2)) #define jit_modi_l(d, rs, is) jit_modi_i((d), (rs), (is)) #define jit_modr_l(d, s1, s2) jit_modr_i((d), (s1), (s2)) #define jit_muli_l(d, rs, is) jit_muli_i((d), (rs), (is)) #define jit_mulr_l(d, s1, s2) jit_mulr_i((d), (s1), (s2)) #define jit_negr_l(d, s1) jit_negr_i((d), (s1)) #define jit_ori_l(d, rs, is) jit_ori_i((d), (rs), (is)) #define jit_orr_l(d, s1, s2) jit_orr_i((d), (s1), (s2)) #define jit_rshi_l(d, rs, is) jit_rshi_i((d), (rs), (is)) #define jit_rshr_l(d, s1, s2) jit_rshr_i((d), (s1), (s2)) #define jit_subr_l(d, s1, s2) jit_subr_i((d), (s1), (s2)) #define jit_subcr_l(d, s1, s2) jit_subcr_i((d), (s1), (s2)) #define jit_subxi_l(d, rs, is) jit_subxi_i((d), (rs), (is)) #define jit_subxr_l(d, s1, s2) jit_subxr_i((d), (s1), (s2)) #define jit_xori_l(d, rs, is) jit_xori_i((d), (rs), (is)) #define jit_xorr_l(d, s1, s2) jit_xorr_i((d), (s1), (s2)) #ifndef jit_rsbi_l #define jit_rsbi_l(d, rs, is) jit_rsbi_i((d), (rs), (is)) #endif #define jit_divi_ul(d, rs, is) jit_divi_ui((d), (rs), (is)) #define jit_divr_ul(d, s1, s2) jit_divr_ui((d), (s1), (s2)) #define jit_hmuli_ul(d, rs, is) jit_hmuli_ui((d), (rs), (is)) #define jit_hmulr_ul(d, s1, s2) jit_hmulr_ui((d), (s1), (s2)) #define jit_modi_ul(d, rs, is) jit_modi_ui((d), (rs), (is)) #define jit_modr_ul(d, s1, s2) jit_modr_ui((d), (s1), (s2)) #define jit_muli_ul(d, rs, is) jit_muli_ui((d), (rs), (is)) #define jit_mulr_ul(d, s1, s2) jit_mulr_ui((d), (s1), (s2)) #define jit_rshi_ul(d, rs, is) jit_rshi_ui((d), (rs), (is)) #define jit_rshr_ul(d, s1, s2) jit_rshr_ui((d), (s1), (s2)) /* Sign/Zero extension */ #define jit_extr_c_l(d, rs) jit_extr_c_i(d, rs) #define jit_extr_c_ul(d, rs) jit_extr_c_ui(d, rs) #define jit_extr_s_l(d, rs) jit_extr_s_i(d, rs) #define jit_extr_s_ul(d, rs) jit_extr_s_ui(d, rs) #define jit_extr_i_l(d, rs) jit_movr_i(d, rs) #define jit_extr_i_ul(d, rs) jit_movr_i(d, rs) /* Unary */ #define jit_movi_l(d, rs) jit_movi_i((d), (rs)) #define jit_movr_l(d, rs) jit_movr_i((d), (rs)) /* Stack */ #define jit_pushr_l(rs) jit_pushr_i(rs) #define jit_popr_l(rs) jit_popr_i(rs) #define jit_pusharg_l(rs) jit_pusharg_i(rs) /* Memory */ #ifndef JIT_RZERO #define jit_ldr_l(d, rs) jit_ldr_i((d), (rs)) #define jit_ldi_l(d, is) jit_ldi_i((d), (is)) #define jit_str_l(d, rs) jit_str_i((d), (rs)) #define jit_sti_l(d, is) jit_sti_i((d), (is)) #define jit_ldr_ui(d, rs) jit_ldr_i((d), (rs)) #define jit_ldi_ui(d, is) jit_ldi_i((d), (is)) #define jit_ldr_ul(d, rs) jit_ldr_ui((d), (rs)) #define jit_ldi_ul(d, is) jit_ldi_ui((d), (is)) #endif #define jit_ldxr_l(d, s1, s2) jit_ldxr_i((d), (s1), (s2)) #define jit_ldxi_l(d, rs, is) jit_ldxi_i((d), (rs), (is)) #define jit_stxr_l(d, s1, s2) jit_stxr_i((d), (s1), (s2)) #define jit_stxi_l(d, rs, is) jit_stxi_i((d), (rs), (is)) #define jit_ldxr_ui(d, s1, s2) jit_ldxr_i((d), (s1), (s2)) #define jit_ldxi_ui(d, rs, is) jit_ldxi_i((d), (rs), (is)) #define jit_ldxr_ul(d, s1, s2) jit_ldxr_ui((d), (s1), (s2)) #define jit_ldxi_ul(d, rs, is) jit_ldxi_ui((d), (rs), (is)) /* Boolean */ #define jit_ltr_l(d, s1, s2) jit_ltr_i((d), (s1), (s2)) #define jit_lti_l(d, rs, is) jit_lti_i((d), (rs), (is)) #define jit_ler_l(d, s1, s2) jit_ler_i((d), (s1), (s2)) #define jit_lei_l(d, rs, is) jit_lei_i((d), (rs), (is)) #define jit_gtr_l(d, s1, s2) jit_gtr_i((d), (s1), (s2)) #define jit_gti_l(d, rs, is) jit_gti_i((d), (rs), (is)) #define jit_ger_l(d, s1, s2) jit_ger_i((d), (s1), (s2)) #define jit_gei_l(d, rs, is) jit_gei_i((d), (rs), (is)) #define jit_eqr_l(d, s1, s2) jit_eqr_i((d), (s1), (s2)) #define jit_eqi_l(d, rs, is) jit_eqi_i((d), (rs), (is)) #define jit_ner_l(d, s1, s2) jit_ner_i((d), (s1), (s2)) #define jit_nei_l(d, rs, is) jit_nei_i((d), (rs), (is)) #define jit_ltr_ul(d, s1, s2) jit_ltr_ui((d), (s1), (s2)) #define jit_lti_ul(d, rs, is) jit_lti_ui((d), (rs), (is)) #define jit_ler_ul(d, s1, s2) jit_ler_ui((d), (s1), (s2)) #define jit_lei_ul(d, rs, is) jit_lei_ui((d), (rs), (is)) #define jit_gtr_ul(d, s1, s2) jit_gtr_ui((d), (s1), (s2)) #define jit_gti_ul(d, rs, is) jit_gti_ui((d), (rs), (is)) #define jit_ger_ul(d, s1, s2) jit_ger_ui((d), (s1), (s2)) #define jit_gei_ul(d, rs, is) jit_gei_ui((d), (rs), (is)) /* Branches */ #define jit_bltr_l(label, s1, s2) jit_bltr_i((label), (s1), (s2)) #define jit_blti_l(label, rs, is) jit_blti_i((label), (rs), (is)) #define jit_bler_l(label, s1, s2) jit_bler_i((label), (s1), (s2)) #define jit_blei_l(label, rs, is) jit_blei_i((label), (rs), (is)) #define jit_bgtr_l(label, s1, s2) jit_bgtr_i((label), (s1), (s2)) #define jit_bgti_l(label, rs, is) jit_bgti_i((label), (rs), (is)) #define jit_bger_l(label, s1, s2) jit_bger_i((label), (s1), (s2)) #define jit_bgei_l(label, rs, is) jit_bgei_i((label), (rs), (is)) #define jit_beqr_l(label, s1, s2) jit_beqr_i((label), (s1), (s2)) #define jit_beqi_l(label, rs, is) jit_beqi_i((label), (rs), (is)) #define jit_bner_l(label, s1, s2) jit_bner_i((label), (s1), (s2)) #define jit_bnei_l(label, rs, is) jit_bnei_i((label), (rs), (is)) #define jit_bmcr_l(label, s1, s2) jit_bmcr_i((label), (s1), (s2)) #define jit_bmci_l(label, rs, is) jit_bmci_i((label), (rs), (is)) #define jit_bmsr_l(label, s1, s2) jit_bmsr_i((label), (s1), (s2)) #define jit_bmsi_l(label, rs, is) jit_bmsi_i((label), (rs), (is)) #define jit_boaddr_l(label, s1, s2) jit_boaddr_i((label), (s1), (s2)) #define jit_boaddi_l(label, rs, is) jit_boaddi_i((label), (rs), (is)) #define jit_bosubr_l(label, s1, s2) jit_bosubr_i((label), (s1), (s2)) #define jit_bosubi_l(label, rs, is) jit_bosubi_i((label), (rs), (is)) #define jit_bltr_ul(label, s1, s2) jit_bltr_ui((label), (s1), (s2)) #define jit_blti_ul(label, rs, is) jit_blti_ui((label), (rs), (is)) #define jit_bler_ul(label, s1, s2) jit_bler_ui((label), (s1), (s2)) #define jit_blei_ul(label, rs, is) jit_blei_ui((label), (rs), (is)) #define jit_bgtr_ul(label, s1, s2) jit_bgtr_ui((label), (s1), (s2)) #define jit_bgti_ul(label, rs, is) jit_bgti_ui((label), (rs), (is)) #define jit_bger_ul(label, s1, s2) jit_bger_ui((label), (s1), (s2)) #define jit_bgei_ul(label, rs, is) jit_bgei_ui((label), (rs), (is)) #define jit_boaddr_ul(label, s1, s2) jit_boaddr_ui((label), (s1), (s2)) #define jit_boaddi_ul(label, rs, is) jit_boaddi_ui((label), (rs), (is)) #define jit_bosubr_ul(label, s1, s2) jit_bosubr_ui((label), (s1), (s2)) #define jit_bosubi_ul(label, rs, is) jit_bosubi_ui((label), (rs), (is)) #define jit_retval_l(rd) jit_retval_i((rd)) #endif #endif /* __lightning_core_common_h_ */ smalltalk-3.2.5/lightning/funcs-common.h0000644000175000017500000000347212123404352015170 00000000000000/******************************** -*- C -*- **************************** * * Platform-independent layer inline functions (common part) * ***********************************************************************/ /*********************************************************************** * * Copyright 2000, 2001, 2002 Free Software Foundation, Inc. * Written by Paolo Bonzini. * * This file is part of GNU lightning. * * GNU lightning is free software; you can redistribute it and/or modify it * under the terms of the GNU Lesser General Public License as published * by the Free Software Foundation; either version 2.1, or (at your option) * any later version. * * GNU lightning is distributed in the hope that it will be useful, but * WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY * or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser General Public * License for more details. * * You should have received a copy of the GNU Lesser General Public License * along with GNU lightning; see the file COPYING.LESSER; if not, write to the * Free Software Foundation, 51 Franklin Street, Fifth Floor, Boston, * MA 02110-1301, USA. * ***********************************************************************/ #ifndef __lightning_funcs_common_h #define __lightning_funcs_common_h #include #include static int jit_fail(const char *, const char*, int, const char *) JIT_UNUSED; int jit_fail(const char *msg, const char *file, int line, const char *function) { fprintf(stderr, "%s: In function `%s':\n", file, function); fprintf(stderr, "%s:%d: %s\n", file, line, msg); abort(); } #ifndef jit_start_pfx #define jit_start_pfx() ( (jit_insn*)0x4) #define jit_end_pfx() ( (jit_insn*)0x0) #endif #endif /* __lightning_funcs_common_h */ smalltalk-3.2.5/snprintfv/0000755000175000017500000000000012130456002012530 500000000000000smalltalk-3.2.5/snprintfv/NEWS0000644000175000017500000000165212123404352013156 00000000000000This is a list of user-visible changes between releases of libsnprintfv. New in 1.1: 2003-??-?? * Support *n$ and .*n$ specifications for width and precision * libltdl is not configured separately. * The convenience library may omit floating point printing routines if desired. * The floating point algorithms in libio v.2.95 were adopted which are correct for long doubles (1.0 sometimes got the last digit wrong). * Uses unlocked I/O for improved speed. New in 1.0: 2003-04-11 * First stable release of snprintfv * POSIX formatted printing API * GNU dprintf and asprintf API * snprintfv API accepts argv arrays of argument lists * User definable % format specifier handlers * User definable output streams * Load custom % format specifier handlers from shared libraries * Can be built as a libtool convenience library or installed from the distribution as a shared and static libtool archive * functions for 8-bit clean string smalltalk-3.2.5/snprintfv/configure0000755000175000017500000162136312130455536014406 00000000000000#! /bin/sh # Guess values for system-dependent variables and create Makefiles. # Generated by GNU Autoconf 2.69 for snprintfv 1.1. # # Report bugs to . # # # Copyright (C) 1992-1996, 1998-2012 Free Software Foundation, Inc. # # # This configure script is free software; the Free Software Foundation # gives unlimited permission to copy, distribute and modify it. ## -------------------- ## ## M4sh Initialization. ## ## -------------------- ## # Be more Bourne compatible DUALCASE=1; export DUALCASE # for MKS sh if test -n "${ZSH_VERSION+set}" && (emulate sh) >/dev/null 2>&1; then : emulate sh NULLCMD=: # Pre-4.2 versions of Zsh do word splitting on ${1+"$@"}, which # is contrary to our usage. Disable this feature. alias -g '${1+"$@"}'='"$@"' setopt NO_GLOB_SUBST else case `(set -o) 2>/dev/null` in #( *posix*) : set -o posix ;; #( *) : ;; esac fi as_nl=' ' export as_nl # Printing a long string crashes Solaris 7 /usr/bin/printf. as_echo='\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\' as_echo=$as_echo$as_echo$as_echo$as_echo$as_echo as_echo=$as_echo$as_echo$as_echo$as_echo$as_echo$as_echo # Prefer a ksh shell builtin over an external printf program on Solaris, # but without wasting forks for bash or zsh. if test -z "$BASH_VERSION$ZSH_VERSION" \ && (test "X`print -r -- $as_echo`" = "X$as_echo") 2>/dev/null; then as_echo='print -r --' as_echo_n='print -rn --' elif (test "X`printf %s $as_echo`" = "X$as_echo") 2>/dev/null; then as_echo='printf %s\n' as_echo_n='printf %s' else if test "X`(/usr/ucb/echo -n -n $as_echo) 2>/dev/null`" = "X-n $as_echo"; then as_echo_body='eval /usr/ucb/echo -n "$1$as_nl"' as_echo_n='/usr/ucb/echo -n' else as_echo_body='eval expr "X$1" : "X\\(.*\\)"' as_echo_n_body='eval arg=$1; case $arg in #( *"$as_nl"*) expr "X$arg" : "X\\(.*\\)$as_nl"; arg=`expr "X$arg" : ".*$as_nl\\(.*\\)"`;; esac; expr "X$arg" : "X\\(.*\\)" | tr -d "$as_nl" ' export as_echo_n_body as_echo_n='sh -c $as_echo_n_body as_echo' fi export as_echo_body as_echo='sh -c $as_echo_body as_echo' fi # The user is always right. if test "${PATH_SEPARATOR+set}" != set; then PATH_SEPARATOR=: (PATH='/bin;/bin'; FPATH=$PATH; sh -c :) >/dev/null 2>&1 && { (PATH='/bin:/bin'; FPATH=$PATH; sh -c :) >/dev/null 2>&1 || PATH_SEPARATOR=';' } fi # IFS # We need space, tab and new line, in precisely that order. Quoting is # there to prevent editors from complaining about space-tab. # (If _AS_PATH_WALK were called with IFS unset, it would disable word # splitting by setting IFS to empty value.) IFS=" "" $as_nl" # Find who we are. Look in the path if we contain no directory separator. as_myself= case $0 in #(( *[\\/]* ) as_myself=$0 ;; *) as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. test -r "$as_dir/$0" && as_myself=$as_dir/$0 && break done IFS=$as_save_IFS ;; esac # We did not find ourselves, most probably we were run as `sh COMMAND' # in which case we are not to be found in the path. if test "x$as_myself" = x; then as_myself=$0 fi if test ! -f "$as_myself"; then $as_echo "$as_myself: error: cannot find myself; rerun with an absolute file name" >&2 exit 1 fi # Unset variables that we do not need and which cause bugs (e.g. in # pre-3.0 UWIN ksh). But do not cause bugs in bash 2.01; the "|| exit 1" # suppresses any "Segmentation fault" message there. '((' could # trigger a bug in pdksh 5.2.14. for as_var in BASH_ENV ENV MAIL MAILPATH do eval test x\${$as_var+set} = xset \ && ( (unset $as_var) || exit 1) >/dev/null 2>&1 && unset $as_var || : done PS1='$ ' PS2='> ' PS4='+ ' # NLS nuisances. LC_ALL=C export LC_ALL LANGUAGE=C export LANGUAGE # CDPATH. (unset CDPATH) >/dev/null 2>&1 && unset CDPATH # Use a proper internal environment variable to ensure we don't fall # into an infinite loop, continuously re-executing ourselves. if test x"${_as_can_reexec}" != xno && test "x$CONFIG_SHELL" != x; then _as_can_reexec=no; export _as_can_reexec; # We cannot yet assume a decent shell, so we have to provide a # neutralization value for shells without unset; and this also # works around shells that cannot unset nonexistent variables. # Preserve -v and -x to the replacement shell. BASH_ENV=/dev/null ENV=/dev/null (unset BASH_ENV) >/dev/null 2>&1 && unset BASH_ENV ENV case $- in # (((( *v*x* | *x*v* ) as_opts=-vx ;; *v* ) as_opts=-v ;; *x* ) as_opts=-x ;; * ) as_opts= ;; esac exec $CONFIG_SHELL $as_opts "$as_myself" ${1+"$@"} # Admittedly, this is quite paranoid, since all the known shells bail # out after a failed `exec'. $as_echo "$0: could not re-execute with $CONFIG_SHELL" >&2 as_fn_exit 255 fi # We don't want this to propagate to other subprocesses. { _as_can_reexec=; unset _as_can_reexec;} if test "x$CONFIG_SHELL" = x; then as_bourne_compatible="if test -n \"\${ZSH_VERSION+set}\" && (emulate sh) >/dev/null 2>&1; then : emulate sh NULLCMD=: # Pre-4.2 versions of Zsh do word splitting on \${1+\"\$@\"}, which # is contrary to our usage. Disable this feature. alias -g '\${1+\"\$@\"}'='\"\$@\"' setopt NO_GLOB_SUBST else case \`(set -o) 2>/dev/null\` in #( *posix*) : set -o posix ;; #( *) : ;; esac fi " as_required="as_fn_return () { (exit \$1); } as_fn_success () { as_fn_return 0; } as_fn_failure () { as_fn_return 1; } as_fn_ret_success () { return 0; } as_fn_ret_failure () { return 1; } exitcode=0 as_fn_success || { exitcode=1; echo as_fn_success failed.; } as_fn_failure && { exitcode=1; echo as_fn_failure succeeded.; } as_fn_ret_success || { exitcode=1; echo as_fn_ret_success failed.; } as_fn_ret_failure && { exitcode=1; echo as_fn_ret_failure succeeded.; } if ( set x; as_fn_ret_success y && test x = \"\$1\" ); then : else exitcode=1; echo positional parameters were not saved. fi test x\$exitcode = x0 || exit 1 test -x / || exit 1" as_suggested=" as_lineno_1=";as_suggested=$as_suggested$LINENO;as_suggested=$as_suggested" as_lineno_1a=\$LINENO as_lineno_2=";as_suggested=$as_suggested$LINENO;as_suggested=$as_suggested" as_lineno_2a=\$LINENO eval 'test \"x\$as_lineno_1'\$as_run'\" != \"x\$as_lineno_2'\$as_run'\" && test \"x\`expr \$as_lineno_1'\$as_run' + 1\`\" = \"x\$as_lineno_2'\$as_run'\"' || exit 1 test -n \"\${ZSH_VERSION+set}\${BASH_VERSION+set}\" || ( ECHO='\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\' ECHO=\$ECHO\$ECHO\$ECHO\$ECHO\$ECHO ECHO=\$ECHO\$ECHO\$ECHO\$ECHO\$ECHO\$ECHO PATH=/empty FPATH=/empty; export PATH FPATH test \"X\`printf %s \$ECHO\`\" = \"X\$ECHO\" \\ || test \"X\`print -r -- \$ECHO\`\" = \"X\$ECHO\" ) || exit 1 test \$(( 1 + 1 )) = 2 || exit 1" if (eval "$as_required") 2>/dev/null; then : as_have_required=yes else as_have_required=no fi if test x$as_have_required = xyes && (eval "$as_suggested") 2>/dev/null; then : else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR as_found=false for as_dir in /bin$PATH_SEPARATOR/usr/bin$PATH_SEPARATOR$PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. as_found=: case $as_dir in #( /*) for as_base in sh bash ksh sh5; do # Try only shells that exist, to save several forks. as_shell=$as_dir/$as_base if { test -f "$as_shell" || test -f "$as_shell.exe"; } && { $as_echo "$as_bourne_compatible""$as_required" | as_run=a "$as_shell"; } 2>/dev/null; then : CONFIG_SHELL=$as_shell as_have_required=yes if { $as_echo "$as_bourne_compatible""$as_suggested" | as_run=a "$as_shell"; } 2>/dev/null; then : break 2 fi fi done;; esac as_found=false done $as_found || { if { test -f "$SHELL" || test -f "$SHELL.exe"; } && { $as_echo "$as_bourne_compatible""$as_required" | as_run=a "$SHELL"; } 2>/dev/null; then : CONFIG_SHELL=$SHELL as_have_required=yes fi; } IFS=$as_save_IFS if test "x$CONFIG_SHELL" != x; then : export CONFIG_SHELL # We cannot yet assume a decent shell, so we have to provide a # neutralization value for shells without unset; and this also # works around shells that cannot unset nonexistent variables. # Preserve -v and -x to the replacement shell. BASH_ENV=/dev/null ENV=/dev/null (unset BASH_ENV) >/dev/null 2>&1 && unset BASH_ENV ENV case $- in # (((( *v*x* | *x*v* ) as_opts=-vx ;; *v* ) as_opts=-v ;; *x* ) as_opts=-x ;; * ) as_opts= ;; esac exec $CONFIG_SHELL $as_opts "$as_myself" ${1+"$@"} # Admittedly, this is quite paranoid, since all the known shells bail # out after a failed `exec'. $as_echo "$0: could not re-execute with $CONFIG_SHELL" >&2 exit 255 fi if test x$as_have_required = xno; then : $as_echo "$0: This script requires a shell more modern than all" $as_echo "$0: the shells that I found on your system." if test x${ZSH_VERSION+set} = xset ; then $as_echo "$0: In particular, zsh $ZSH_VERSION has bugs and should" $as_echo "$0: be upgraded to zsh 4.3.4 or later." else $as_echo "$0: Please tell bug-autoconf@gnu.org and bonzini@gnu.org $0: about your system, including any error possibly output $0: before this message. Then install a modern shell, or $0: manually run the script under such a shell if you do $0: have one." fi exit 1 fi fi fi SHELL=${CONFIG_SHELL-/bin/sh} export SHELL # Unset more variables known to interfere with behavior of common tools. CLICOLOR_FORCE= GREP_OPTIONS= unset CLICOLOR_FORCE GREP_OPTIONS ## --------------------- ## ## M4sh Shell Functions. ## ## --------------------- ## # as_fn_unset VAR # --------------- # Portably unset VAR. as_fn_unset () { { eval $1=; unset $1;} } as_unset=as_fn_unset # as_fn_set_status STATUS # ----------------------- # Set $? to STATUS, without forking. as_fn_set_status () { return $1 } # as_fn_set_status # as_fn_exit STATUS # ----------------- # Exit the shell with STATUS, even in a "trap 0" or "set -e" context. as_fn_exit () { set +e as_fn_set_status $1 exit $1 } # as_fn_exit # as_fn_mkdir_p # ------------- # Create "$as_dir" as a directory, including parents if necessary. as_fn_mkdir_p () { case $as_dir in #( -*) as_dir=./$as_dir;; esac test -d "$as_dir" || eval $as_mkdir_p || { as_dirs= while :; do case $as_dir in #( *\'*) as_qdir=`$as_echo "$as_dir" | sed "s/'/'\\\\\\\\''/g"`;; #'( *) as_qdir=$as_dir;; esac as_dirs="'$as_qdir' $as_dirs" as_dir=`$as_dirname -- "$as_dir" || $as_expr X"$as_dir" : 'X\(.*[^/]\)//*[^/][^/]*/*$' \| \ X"$as_dir" : 'X\(//\)[^/]' \| \ X"$as_dir" : 'X\(//\)$' \| \ X"$as_dir" : 'X\(/\)' \| . 2>/dev/null || $as_echo X"$as_dir" | sed '/^X\(.*[^/]\)\/\/*[^/][^/]*\/*$/{ s//\1/ q } /^X\(\/\/\)[^/].*/{ s//\1/ q } /^X\(\/\/\)$/{ s//\1/ q } /^X\(\/\).*/{ s//\1/ q } s/.*/./; q'` test -d "$as_dir" && break done test -z "$as_dirs" || eval "mkdir $as_dirs" } || test -d "$as_dir" || as_fn_error $? "cannot create directory $as_dir" } # as_fn_mkdir_p # as_fn_executable_p FILE # ----------------------- # Test if FILE is an executable regular file. as_fn_executable_p () { test -f "$1" && test -x "$1" } # as_fn_executable_p # as_fn_append VAR VALUE # ---------------------- # Append the text in VALUE to the end of the definition contained in VAR. Take # advantage of any shell optimizations that allow amortized linear growth over # repeated appends, instead of the typical quadratic growth present in naive # implementations. if (eval "as_var=1; as_var+=2; test x\$as_var = x12") 2>/dev/null; then : eval 'as_fn_append () { eval $1+=\$2 }' else as_fn_append () { eval $1=\$$1\$2 } fi # as_fn_append # as_fn_arith ARG... # ------------------ # Perform arithmetic evaluation on the ARGs, and store the result in the # global $as_val. Take advantage of shells that can avoid forks. The arguments # must be portable across $(()) and expr. if (eval "test \$(( 1 + 1 )) = 2") 2>/dev/null; then : eval 'as_fn_arith () { as_val=$(( $* )) }' else as_fn_arith () { as_val=`expr "$@" || test $? -eq 1` } fi # as_fn_arith # as_fn_error STATUS ERROR [LINENO LOG_FD] # ---------------------------------------- # Output "`basename $0`: error: ERROR" to stderr. If LINENO and LOG_FD are # provided, also output the error to LOG_FD, referencing LINENO. Then exit the # script with STATUS, using 1 if that was 0. as_fn_error () { as_status=$1; test $as_status -eq 0 && as_status=1 if test "$4"; then as_lineno=${as_lineno-"$3"} as_lineno_stack=as_lineno_stack=$as_lineno_stack $as_echo "$as_me:${as_lineno-$LINENO}: error: $2" >&$4 fi $as_echo "$as_me: error: $2" >&2 as_fn_exit $as_status } # as_fn_error if expr a : '\(a\)' >/dev/null 2>&1 && test "X`expr 00001 : '.*\(...\)'`" = X001; then as_expr=expr else as_expr=false fi if (basename -- /) >/dev/null 2>&1 && test "X`basename -- / 2>&1`" = "X/"; then as_basename=basename else as_basename=false fi if (as_dir=`dirname -- /` && test "X$as_dir" = X/) >/dev/null 2>&1; then as_dirname=dirname else as_dirname=false fi as_me=`$as_basename -- "$0" || $as_expr X/"$0" : '.*/\([^/][^/]*\)/*$' \| \ X"$0" : 'X\(//\)$' \| \ X"$0" : 'X\(/\)' \| . 2>/dev/null || $as_echo X/"$0" | sed '/^.*\/\([^/][^/]*\)\/*$/{ s//\1/ q } /^X\/\(\/\/\)$/{ s//\1/ q } /^X\/\(\/\).*/{ s//\1/ q } s/.*/./; q'` # Avoid depending upon Character Ranges. as_cr_letters='abcdefghijklmnopqrstuvwxyz' as_cr_LETTERS='ABCDEFGHIJKLMNOPQRSTUVWXYZ' as_cr_Letters=$as_cr_letters$as_cr_LETTERS as_cr_digits='0123456789' as_cr_alnum=$as_cr_Letters$as_cr_digits as_lineno_1=$LINENO as_lineno_1a=$LINENO as_lineno_2=$LINENO as_lineno_2a=$LINENO eval 'test "x$as_lineno_1'$as_run'" != "x$as_lineno_2'$as_run'" && test "x`expr $as_lineno_1'$as_run' + 1`" = "x$as_lineno_2'$as_run'"' || { # Blame Lee E. McMahon (1931-1989) for sed's syntax. :-) sed -n ' p /[$]LINENO/= ' <$as_myself | sed ' s/[$]LINENO.*/&-/ t lineno b :lineno N :loop s/[$]LINENO\([^'$as_cr_alnum'_].*\n\)\(.*\)/\2\1\2/ t loop s/-\n.*// ' >$as_me.lineno && chmod +x "$as_me.lineno" || { $as_echo "$as_me: error: cannot create $as_me.lineno; rerun with a POSIX shell" >&2; as_fn_exit 1; } # If we had to re-execute with $CONFIG_SHELL, we're ensured to have # already done that, so ensure we don't try to do so again and fall # in an infinite loop. This has already happened in practice. _as_can_reexec=no; export _as_can_reexec # Don't try to exec as it changes $[0], causing all sort of problems # (the dirname of $[0] is not the place where we might find the # original and so on. Autoconf is especially sensitive to this). . "./$as_me.lineno" # Exit status is that of the last command. exit } ECHO_C= ECHO_N= ECHO_T= case `echo -n x` in #((((( -n*) case `echo 'xy\c'` in *c*) ECHO_T=' ';; # ECHO_T is single tab character. xy) ECHO_C='\c';; *) echo `echo ksh88 bug on AIX 6.1` > /dev/null ECHO_T=' ';; esac;; *) ECHO_N='-n';; esac rm -f conf$$ conf$$.exe conf$$.file if test -d conf$$.dir; then rm -f conf$$.dir/conf$$.file else rm -f conf$$.dir mkdir conf$$.dir 2>/dev/null fi if (echo >conf$$.file) 2>/dev/null; then if ln -s conf$$.file conf$$ 2>/dev/null; then as_ln_s='ln -s' # ... but there are two gotchas: # 1) On MSYS, both `ln -s file dir' and `ln file dir' fail. # 2) DJGPP < 2.04 has no symlinks; `ln -s' creates a wrapper executable. # In both cases, we have to default to `cp -pR'. ln -s conf$$.file conf$$.dir 2>/dev/null && test ! -f conf$$.exe || as_ln_s='cp -pR' elif ln conf$$.file conf$$ 2>/dev/null; then as_ln_s=ln else as_ln_s='cp -pR' fi else as_ln_s='cp -pR' fi rm -f conf$$ conf$$.exe conf$$.dir/conf$$.file conf$$.file rmdir conf$$.dir 2>/dev/null if mkdir -p . 2>/dev/null; then as_mkdir_p='mkdir -p "$as_dir"' else test -d ./-p && rmdir ./-p as_mkdir_p=false fi as_test_x='test -x' as_executable_p=as_fn_executable_p # Sed expression to map a string onto a valid CPP name. as_tr_cpp="eval sed 'y%*$as_cr_letters%P$as_cr_LETTERS%;s%[^_$as_cr_alnum]%_%g'" # Sed expression to map a string onto a valid variable name. as_tr_sh="eval sed 'y%*+%pp%;s%[^_$as_cr_alnum]%_%g'" SHELL=${CONFIG_SHELL-/bin/sh} test -n "$DJDIR" || exec 7<&0 &1 # Name of the host. # hostname on some systems (SVR3.2, old GNU/Linux) returns a bogus exit status, # so uname gets run too. ac_hostname=`(hostname || uname -n) 2>/dev/null | sed 1q` # # Initializations. # ac_default_prefix=/usr/local ac_clean_files= ac_config_libobj_dir=. LIBOBJS= cross_compiling=no subdirs= MFLAGS= MAKEFLAGS= # Identity of this package. PACKAGE_NAME='snprintfv' PACKAGE_TARNAME='snprintfv' PACKAGE_VERSION='1.1' PACKAGE_STRING='snprintfv 1.1' PACKAGE_BUGREPORT='bonzini@gnu.org' PACKAGE_URL='' ac_unique_file="snprintfv/printf.h" # Factoring default headers for most tests. ac_includes_default="\ #include #ifdef HAVE_SYS_TYPES_H # include #endif #ifdef HAVE_SYS_STAT_H # include #endif #ifdef STDC_HEADERS # include # include #else # ifdef HAVE_STDLIB_H # include # endif #endif #ifdef HAVE_STRING_H # if !defined STDC_HEADERS && defined HAVE_MEMORY_H # include # endif # include #endif #ifdef HAVE_STRINGS_H # include #endif #ifdef HAVE_INTTYPES_H # include #endif #ifdef HAVE_STDINT_H # include #endif #ifdef HAVE_UNISTD_H # include #endif" ac_subst_vars='am__EXEEXT_FALSE am__EXEEXT_TRUE LIBOBJS ac_aux_dir INCLUDES LTLIBOBJS LIBSNPRINTFVC_PRINT_FLOATS convenience_libsnprintfv CONVENIENCE_SNPRINTFV_FALSE CONVENIENCE_SNPRINTFV_TRUE installed_libsnprintfv INSTALL_SNPRINTFV_FALSE INSTALL_SNPRINTFV_TRUE SUBDIR_SNPRINTFV_FALSE SUBDIR_SNPRINTFV_TRUE CPP OTOOL64 OTOOL LIPO NMEDIT DSYMUTIL MANIFEST_TOOL RANLIB ac_ct_AR AR LN_S NM ac_ct_DUMPBIN DUMPBIN LD FGREP EGREP GREP SED am__fastdepCC_FALSE am__fastdepCC_TRUE CCDEPMODE am__nodep AMDEPBACKSLASH AMDEP_FALSE AMDEP_TRUE am__quote am__include DEPDIR OBJEXT EXEEXT ac_ct_CC CPPFLAGS LDFLAGS CFLAGS CC LIBTOOL OBJDUMP DLLTOOL AS host_os host_vendor host_cpu host build_os build_vendor build_cpu build SNV_AGE SNV_REVISION SNV_CURRENT am__untar am__tar AMTAR am__leading_dot SET_MAKE AWK mkdir_p MKDIR_P INSTALL_STRIP_PROGRAM STRIP install_sh MAKEINFO AUTOHEADER AUTOMAKE AUTOCONF ACLOCAL VERSION PACKAGE CYGPATH_W am__isrc INSTALL_DATA INSTALL_SCRIPT INSTALL_PROGRAM target_alias host_alias build_alias LIBS ECHO_T ECHO_N ECHO_C DEFS mandir localedir libdir psdir pdfdir dvidir htmldir infodir docdir oldincludedir includedir localstatedir sharedstatedir sysconfdir datadir datarootdir libexecdir sbindir bindir program_transform_name prefix exec_prefix PACKAGE_URL PACKAGE_BUGREPORT PACKAGE_STRING PACKAGE_VERSION PACKAGE_TARNAME PACKAGE_NAME PATH_SEPARATOR SHELL' ac_subst_files='' ac_user_opts=' enable_option_checking enable_subdir enable_shared enable_static with_pic enable_fast_install enable_dependency_tracking with_gnu_ld with_sysroot enable_libtool_lock enable_convenience_float_printing with_dmalloc ' ac_precious_vars='build_alias host_alias target_alias CC CFLAGS LDFLAGS LIBS CPPFLAGS CPP' # Initialize some variables set by options. ac_init_help= ac_init_version=false ac_unrecognized_opts= ac_unrecognized_sep= # The variables have the same names as the options, with # dashes changed to underlines. cache_file=/dev/null exec_prefix=NONE no_create= no_recursion= prefix=NONE program_prefix=NONE program_suffix=NONE program_transform_name=s,x,x, silent= site= srcdir= verbose= x_includes=NONE x_libraries=NONE # Installation directory options. # These are left unexpanded so users can "make install exec_prefix=/foo" # and all the variables that are supposed to be based on exec_prefix # by default will actually change. # Use braces instead of parens because sh, perl, etc. also accept them. # (The list follows the same order as the GNU Coding Standards.) bindir='${exec_prefix}/bin' sbindir='${exec_prefix}/sbin' libexecdir='${exec_prefix}/libexec' datarootdir='${prefix}/share' datadir='${datarootdir}' sysconfdir='${prefix}/etc' sharedstatedir='${prefix}/com' localstatedir='${prefix}/var' includedir='${prefix}/include' oldincludedir='/usr/include' docdir='${datarootdir}/doc/${PACKAGE_TARNAME}' infodir='${datarootdir}/info' htmldir='${docdir}' dvidir='${docdir}' pdfdir='${docdir}' psdir='${docdir}' libdir='${exec_prefix}/lib' localedir='${datarootdir}/locale' mandir='${datarootdir}/man' ac_prev= ac_dashdash= for ac_option do # If the previous option needs an argument, assign it. if test -n "$ac_prev"; then eval $ac_prev=\$ac_option ac_prev= continue fi case $ac_option in *=?*) ac_optarg=`expr "X$ac_option" : '[^=]*=\(.*\)'` ;; *=) ac_optarg= ;; *) ac_optarg=yes ;; esac # Accept the important Cygnus configure options, so we can diagnose typos. case $ac_dashdash$ac_option in --) ac_dashdash=yes ;; -bindir | --bindir | --bindi | --bind | --bin | --bi) ac_prev=bindir ;; -bindir=* | --bindir=* | --bindi=* | --bind=* | --bin=* | --bi=*) bindir=$ac_optarg ;; -build | --build | --buil | --bui | --bu) ac_prev=build_alias ;; -build=* | --build=* | --buil=* | --bui=* | --bu=*) build_alias=$ac_optarg ;; -cache-file | --cache-file | --cache-fil | --cache-fi \ | --cache-f | --cache- | --cache | --cach | --cac | --ca | --c) ac_prev=cache_file ;; -cache-file=* | --cache-file=* | --cache-fil=* | --cache-fi=* \ | --cache-f=* | --cache-=* | --cache=* | --cach=* | --cac=* | --ca=* | --c=*) cache_file=$ac_optarg ;; --config-cache | -C) cache_file=config.cache ;; -datadir | --datadir | --datadi | --datad) ac_prev=datadir ;; -datadir=* | --datadir=* | --datadi=* | --datad=*) datadir=$ac_optarg ;; -datarootdir | --datarootdir | --datarootdi | --datarootd | --dataroot \ | --dataroo | --dataro | --datar) ac_prev=datarootdir ;; -datarootdir=* | --datarootdir=* | --datarootdi=* | --datarootd=* \ | --dataroot=* | --dataroo=* | --dataro=* | --datar=*) datarootdir=$ac_optarg ;; -disable-* | --disable-*) ac_useropt=`expr "x$ac_option" : 'x-*disable-\(.*\)'` # Reject names that are not valid shell variable names. expr "x$ac_useropt" : ".*[^-+._$as_cr_alnum]" >/dev/null && as_fn_error $? "invalid feature name: $ac_useropt" ac_useropt_orig=$ac_useropt ac_useropt=`$as_echo "$ac_useropt" | sed 's/[-+.]/_/g'` case $ac_user_opts in *" "enable_$ac_useropt" "*) ;; *) ac_unrecognized_opts="$ac_unrecognized_opts$ac_unrecognized_sep--disable-$ac_useropt_orig" ac_unrecognized_sep=', ';; esac eval enable_$ac_useropt=no ;; -docdir | --docdir | --docdi | --doc | --do) ac_prev=docdir ;; -docdir=* | --docdir=* | --docdi=* | --doc=* | --do=*) docdir=$ac_optarg ;; -dvidir | --dvidir | --dvidi | --dvid | --dvi | --dv) ac_prev=dvidir ;; -dvidir=* | --dvidir=* | --dvidi=* | --dvid=* | --dvi=* | --dv=*) dvidir=$ac_optarg ;; -enable-* | --enable-*) ac_useropt=`expr "x$ac_option" : 'x-*enable-\([^=]*\)'` # Reject names that are not valid shell variable names. expr "x$ac_useropt" : ".*[^-+._$as_cr_alnum]" >/dev/null && as_fn_error $? "invalid feature name: $ac_useropt" ac_useropt_orig=$ac_useropt ac_useropt=`$as_echo "$ac_useropt" | sed 's/[-+.]/_/g'` case $ac_user_opts in *" "enable_$ac_useropt" "*) ;; *) ac_unrecognized_opts="$ac_unrecognized_opts$ac_unrecognized_sep--enable-$ac_useropt_orig" ac_unrecognized_sep=', ';; esac eval enable_$ac_useropt=\$ac_optarg ;; -exec-prefix | --exec_prefix | --exec-prefix | --exec-prefi \ | --exec-pref | --exec-pre | --exec-pr | --exec-p | --exec- \ | --exec | --exe | --ex) ac_prev=exec_prefix ;; -exec-prefix=* | --exec_prefix=* | --exec-prefix=* | --exec-prefi=* \ | --exec-pref=* | --exec-pre=* | --exec-pr=* | --exec-p=* | --exec-=* \ | --exec=* | --exe=* | --ex=*) exec_prefix=$ac_optarg ;; -gas | --gas | --ga | --g) # Obsolete; use --with-gas. with_gas=yes ;; -help | --help | --hel | --he | -h) ac_init_help=long ;; -help=r* | --help=r* | --hel=r* | --he=r* | -hr*) ac_init_help=recursive ;; -help=s* | --help=s* | --hel=s* | --he=s* | -hs*) ac_init_help=short ;; -host | --host | --hos | --ho) ac_prev=host_alias ;; -host=* | --host=* | --hos=* | --ho=*) host_alias=$ac_optarg ;; -htmldir | --htmldir | --htmldi | --htmld | --html | --htm | --ht) ac_prev=htmldir ;; -htmldir=* | --htmldir=* | --htmldi=* | --htmld=* | --html=* | --htm=* \ | --ht=*) htmldir=$ac_optarg ;; -includedir | --includedir | --includedi | --included | --include \ | --includ | --inclu | --incl | --inc) ac_prev=includedir ;; -includedir=* | --includedir=* | --includedi=* | --included=* | --include=* \ | --includ=* | --inclu=* | --incl=* | --inc=*) includedir=$ac_optarg ;; -infodir | --infodir | --infodi | --infod | --info | --inf) ac_prev=infodir ;; -infodir=* | --infodir=* | --infodi=* | --infod=* | --info=* | --inf=*) infodir=$ac_optarg ;; -libdir | --libdir | --libdi | --libd) ac_prev=libdir ;; -libdir=* | --libdir=* | --libdi=* | --libd=*) libdir=$ac_optarg ;; -libexecdir | --libexecdir | --libexecdi | --libexecd | --libexec \ | --libexe | --libex | --libe) ac_prev=libexecdir ;; -libexecdir=* | --libexecdir=* | --libexecdi=* | --libexecd=* | --libexec=* \ | --libexe=* | --libex=* | --libe=*) libexecdir=$ac_optarg ;; -localedir | --localedir | --localedi | --localed | --locale) ac_prev=localedir ;; -localedir=* | --localedir=* | --localedi=* | --localed=* | --locale=*) localedir=$ac_optarg ;; -localstatedir | --localstatedir | --localstatedi | --localstated \ | --localstate | --localstat | --localsta | --localst | --locals) ac_prev=localstatedir ;; -localstatedir=* | --localstatedir=* | --localstatedi=* | --localstated=* \ | --localstate=* | --localstat=* | --localsta=* | --localst=* | --locals=*) localstatedir=$ac_optarg ;; -mandir | --mandir | --mandi | --mand | --man | --ma | --m) ac_prev=mandir ;; -mandir=* | --mandir=* | --mandi=* | --mand=* | --man=* | --ma=* | --m=*) mandir=$ac_optarg ;; -nfp | --nfp | --nf) # Obsolete; use --without-fp. with_fp=no ;; -no-create | --no-create | --no-creat | --no-crea | --no-cre \ | --no-cr | --no-c | -n) no_create=yes ;; -no-recursion | --no-recursion | --no-recursio | --no-recursi \ | --no-recurs | --no-recur | --no-recu | --no-rec | --no-re | --no-r) no_recursion=yes ;; -oldincludedir | --oldincludedir | --oldincludedi | --oldincluded \ | --oldinclude | --oldinclud | --oldinclu | --oldincl | --oldinc \ | --oldin | --oldi | --old | --ol | --o) ac_prev=oldincludedir ;; -oldincludedir=* | --oldincludedir=* | --oldincludedi=* | --oldincluded=* \ | --oldinclude=* | --oldinclud=* | --oldinclu=* | --oldincl=* | --oldinc=* \ | --oldin=* | --oldi=* | --old=* | --ol=* | --o=*) oldincludedir=$ac_optarg ;; -prefix | --prefix | --prefi | --pref | --pre | --pr | --p) ac_prev=prefix ;; -prefix=* | --prefix=* | --prefi=* | --pref=* | --pre=* | --pr=* | --p=*) prefix=$ac_optarg ;; -program-prefix | --program-prefix | --program-prefi | --program-pref \ | --program-pre | --program-pr | --program-p) ac_prev=program_prefix ;; -program-prefix=* | --program-prefix=* | --program-prefi=* \ | --program-pref=* | --program-pre=* | --program-pr=* | --program-p=*) program_prefix=$ac_optarg ;; -program-suffix | --program-suffix | --program-suffi | --program-suff \ | --program-suf | --program-su | --program-s) ac_prev=program_suffix ;; -program-suffix=* | --program-suffix=* | --program-suffi=* \ | --program-suff=* | --program-suf=* | --program-su=* | --program-s=*) program_suffix=$ac_optarg ;; -program-transform-name | --program-transform-name \ | --program-transform-nam | --program-transform-na \ | --program-transform-n | --program-transform- \ | --program-transform | --program-transfor \ | --program-transfo | --program-transf \ | --program-trans | --program-tran \ | --progr-tra | --program-tr | --program-t) ac_prev=program_transform_name ;; -program-transform-name=* | --program-transform-name=* \ | --program-transform-nam=* | --program-transform-na=* \ | --program-transform-n=* | --program-transform-=* \ | --program-transform=* | --program-transfor=* \ | --program-transfo=* | --program-transf=* \ | --program-trans=* | --program-tran=* \ | --progr-tra=* | --program-tr=* | --program-t=*) program_transform_name=$ac_optarg ;; -pdfdir | --pdfdir | --pdfdi | --pdfd | --pdf | --pd) ac_prev=pdfdir ;; -pdfdir=* | --pdfdir=* | --pdfdi=* | --pdfd=* | --pdf=* | --pd=*) pdfdir=$ac_optarg ;; -psdir | --psdir | --psdi | --psd | --ps) ac_prev=psdir ;; -psdir=* | --psdir=* | --psdi=* | --psd=* | --ps=*) psdir=$ac_optarg ;; -q | -quiet | --quiet | --quie | --qui | --qu | --q \ | -silent | --silent | --silen | --sile | --sil) silent=yes ;; -sbindir | --sbindir | --sbindi | --sbind | --sbin | --sbi | --sb) ac_prev=sbindir ;; -sbindir=* | --sbindir=* | --sbindi=* | --sbind=* | --sbin=* \ | --sbi=* | --sb=*) sbindir=$ac_optarg ;; -sharedstatedir | --sharedstatedir | --sharedstatedi \ | --sharedstated | --sharedstate | --sharedstat | --sharedsta \ | --sharedst | --shareds | --shared | --share | --shar \ | --sha | --sh) ac_prev=sharedstatedir ;; -sharedstatedir=* | --sharedstatedir=* | --sharedstatedi=* \ | --sharedstated=* | --sharedstate=* | --sharedstat=* | --sharedsta=* \ | --sharedst=* | --shareds=* | --shared=* | --share=* | --shar=* \ | --sha=* | --sh=*) sharedstatedir=$ac_optarg ;; -site | --site | --sit) ac_prev=site ;; -site=* | --site=* | --sit=*) site=$ac_optarg ;; -srcdir | --srcdir | --srcdi | --srcd | --src | --sr) ac_prev=srcdir ;; -srcdir=* | --srcdir=* | --srcdi=* | --srcd=* | --src=* | --sr=*) srcdir=$ac_optarg ;; -sysconfdir | --sysconfdir | --sysconfdi | --sysconfd | --sysconf \ | --syscon | --sysco | --sysc | --sys | --sy) ac_prev=sysconfdir ;; -sysconfdir=* | --sysconfdir=* | --sysconfdi=* | --sysconfd=* | --sysconf=* \ | --syscon=* | --sysco=* | --sysc=* | --sys=* | --sy=*) sysconfdir=$ac_optarg ;; -target | --target | --targe | --targ | --tar | --ta | --t) ac_prev=target_alias ;; -target=* | --target=* | --targe=* | --targ=* | --tar=* | --ta=* | --t=*) target_alias=$ac_optarg ;; -v | -verbose | --verbose | --verbos | --verbo | --verb) verbose=yes ;; -version | --version | --versio | --versi | --vers | -V) ac_init_version=: ;; -with-* | --with-*) ac_useropt=`expr "x$ac_option" : 'x-*with-\([^=]*\)'` # Reject names that are not valid shell variable names. expr "x$ac_useropt" : ".*[^-+._$as_cr_alnum]" >/dev/null && as_fn_error $? "invalid package name: $ac_useropt" ac_useropt_orig=$ac_useropt ac_useropt=`$as_echo "$ac_useropt" | sed 's/[-+.]/_/g'` case $ac_user_opts in *" "with_$ac_useropt" "*) ;; *) ac_unrecognized_opts="$ac_unrecognized_opts$ac_unrecognized_sep--with-$ac_useropt_orig" ac_unrecognized_sep=', ';; esac eval with_$ac_useropt=\$ac_optarg ;; -without-* | --without-*) ac_useropt=`expr "x$ac_option" : 'x-*without-\(.*\)'` # Reject names that are not valid shell variable names. expr "x$ac_useropt" : ".*[^-+._$as_cr_alnum]" >/dev/null && as_fn_error $? "invalid package name: $ac_useropt" ac_useropt_orig=$ac_useropt ac_useropt=`$as_echo "$ac_useropt" | sed 's/[-+.]/_/g'` case $ac_user_opts in *" "with_$ac_useropt" "*) ;; *) ac_unrecognized_opts="$ac_unrecognized_opts$ac_unrecognized_sep--without-$ac_useropt_orig" ac_unrecognized_sep=', ';; esac eval with_$ac_useropt=no ;; --x) # Obsolete; use --with-x. with_x=yes ;; -x-includes | --x-includes | --x-include | --x-includ | --x-inclu \ | --x-incl | --x-inc | --x-in | --x-i) ac_prev=x_includes ;; -x-includes=* | --x-includes=* | --x-include=* | --x-includ=* | --x-inclu=* \ | --x-incl=* | --x-inc=* | --x-in=* | --x-i=*) x_includes=$ac_optarg ;; -x-libraries | --x-libraries | --x-librarie | --x-librari \ | --x-librar | --x-libra | --x-libr | --x-lib | --x-li | --x-l) ac_prev=x_libraries ;; -x-libraries=* | --x-libraries=* | --x-librarie=* | --x-librari=* \ | --x-librar=* | --x-libra=* | --x-libr=* | --x-lib=* | --x-li=* | --x-l=*) x_libraries=$ac_optarg ;; -*) as_fn_error $? "unrecognized option: \`$ac_option' Try \`$0 --help' for more information" ;; *=*) ac_envvar=`expr "x$ac_option" : 'x\([^=]*\)='` # Reject names that are not valid shell variable names. case $ac_envvar in #( '' | [0-9]* | *[!_$as_cr_alnum]* ) as_fn_error $? "invalid variable name: \`$ac_envvar'" ;; esac eval $ac_envvar=\$ac_optarg export $ac_envvar ;; *) # FIXME: should be removed in autoconf 3.0. $as_echo "$as_me: WARNING: you should use --build, --host, --target" >&2 expr "x$ac_option" : ".*[^-._$as_cr_alnum]" >/dev/null && $as_echo "$as_me: WARNING: invalid host type: $ac_option" >&2 : "${build_alias=$ac_option} ${host_alias=$ac_option} ${target_alias=$ac_option}" ;; esac done if test -n "$ac_prev"; then ac_option=--`echo $ac_prev | sed 's/_/-/g'` as_fn_error $? "missing argument to $ac_option" fi if test -n "$ac_unrecognized_opts"; then case $enable_option_checking in no) ;; fatal) as_fn_error $? "unrecognized options: $ac_unrecognized_opts" ;; *) $as_echo "$as_me: WARNING: unrecognized options: $ac_unrecognized_opts" >&2 ;; esac fi # Check all directory arguments for consistency. for ac_var in exec_prefix prefix bindir sbindir libexecdir datarootdir \ datadir sysconfdir sharedstatedir localstatedir includedir \ oldincludedir docdir infodir htmldir dvidir pdfdir psdir \ libdir localedir mandir do eval ac_val=\$$ac_var # Remove trailing slashes. case $ac_val in */ ) ac_val=`expr "X$ac_val" : 'X\(.*[^/]\)' \| "X$ac_val" : 'X\(.*\)'` eval $ac_var=\$ac_val;; esac # Be sure to have absolute directory names. case $ac_val in [\\/$]* | ?:[\\/]* ) continue;; NONE | '' ) case $ac_var in *prefix ) continue;; esac;; esac as_fn_error $? "expected an absolute directory name for --$ac_var: $ac_val" done # There might be people who depend on the old broken behavior: `$host' # used to hold the argument of --host etc. # FIXME: To remove some day. build=$build_alias host=$host_alias target=$target_alias # FIXME: To remove some day. if test "x$host_alias" != x; then if test "x$build_alias" = x; then cross_compiling=maybe elif test "x$build_alias" != "x$host_alias"; then cross_compiling=yes fi fi ac_tool_prefix= test -n "$host_alias" && ac_tool_prefix=$host_alias- test "$silent" = yes && exec 6>/dev/null ac_pwd=`pwd` && test -n "$ac_pwd" && ac_ls_di=`ls -di .` && ac_pwd_ls_di=`cd "$ac_pwd" && ls -di .` || as_fn_error $? "working directory cannot be determined" test "X$ac_ls_di" = "X$ac_pwd_ls_di" || as_fn_error $? "pwd does not report name of working directory" # Find the source files, if location was not specified. if test -z "$srcdir"; then ac_srcdir_defaulted=yes # Try the directory containing this script, then the parent directory. ac_confdir=`$as_dirname -- "$as_myself" || $as_expr X"$as_myself" : 'X\(.*[^/]\)//*[^/][^/]*/*$' \| \ X"$as_myself" : 'X\(//\)[^/]' \| \ X"$as_myself" : 'X\(//\)$' \| \ X"$as_myself" : 'X\(/\)' \| . 2>/dev/null || $as_echo X"$as_myself" | sed '/^X\(.*[^/]\)\/\/*[^/][^/]*\/*$/{ s//\1/ q } /^X\(\/\/\)[^/].*/{ s//\1/ q } /^X\(\/\/\)$/{ s//\1/ q } /^X\(\/\).*/{ s//\1/ q } s/.*/./; q'` srcdir=$ac_confdir if test ! -r "$srcdir/$ac_unique_file"; then srcdir=.. fi else ac_srcdir_defaulted=no fi if test ! -r "$srcdir/$ac_unique_file"; then test "$ac_srcdir_defaulted" = yes && srcdir="$ac_confdir or .." as_fn_error $? "cannot find sources ($ac_unique_file) in $srcdir" fi ac_msg="sources are in $srcdir, but \`cd $srcdir' does not work" ac_abs_confdir=`( cd "$srcdir" && test -r "./$ac_unique_file" || as_fn_error $? "$ac_msg" pwd)` # When building in place, set srcdir=. if test "$ac_abs_confdir" = "$ac_pwd"; then srcdir=. fi # Remove unnecessary trailing slashes from srcdir. # Double slashes in file names in object file debugging info # mess up M-x gdb in Emacs. case $srcdir in */) srcdir=`expr "X$srcdir" : 'X\(.*[^/]\)' \| "X$srcdir" : 'X\(.*\)'`;; esac for ac_var in $ac_precious_vars; do eval ac_env_${ac_var}_set=\${${ac_var}+set} eval ac_env_${ac_var}_value=\$${ac_var} eval ac_cv_env_${ac_var}_set=\${${ac_var}+set} eval ac_cv_env_${ac_var}_value=\$${ac_var} done # # Report the --help message. # if test "$ac_init_help" = "long"; then # Omit some internal or obsolete options to make the list less imposing. # This message is too long to be a string in the A/UX 3.1 sh. cat <<_ACEOF \`configure' configures snprintfv 1.1 to adapt to many kinds of systems. Usage: $0 [OPTION]... [VAR=VALUE]... To assign environment variables (e.g., CC, CFLAGS...), specify them as VAR=VALUE. See below for descriptions of some of the useful variables. Defaults for the options are specified in brackets. Configuration: -h, --help display this help and exit --help=short display options specific to this package --help=recursive display the short help of all the included packages -V, --version display version information and exit -q, --quiet, --silent do not print \`checking ...' messages --cache-file=FILE cache test results in FILE [disabled] -C, --config-cache alias for \`--cache-file=config.cache' -n, --no-create do not create output files --srcdir=DIR find the sources in DIR [configure dir or \`..'] Installation directories: --prefix=PREFIX install architecture-independent files in PREFIX [$ac_default_prefix] --exec-prefix=EPREFIX install architecture-dependent files in EPREFIX [PREFIX] By default, \`make install' will install all the files in \`$ac_default_prefix/bin', \`$ac_default_prefix/lib' etc. You can specify an installation prefix other than \`$ac_default_prefix' using \`--prefix', for instance \`--prefix=\$HOME'. For better control, use the options below. Fine tuning of the installation directories: --bindir=DIR user executables [EPREFIX/bin] --sbindir=DIR system admin executables [EPREFIX/sbin] --libexecdir=DIR program executables [EPREFIX/libexec] --sysconfdir=DIR read-only single-machine data [PREFIX/etc] --sharedstatedir=DIR modifiable architecture-independent data [PREFIX/com] --localstatedir=DIR modifiable single-machine data [PREFIX/var] --libdir=DIR object code libraries [EPREFIX/lib] --includedir=DIR C header files [PREFIX/include] --oldincludedir=DIR C header files for non-gcc [/usr/include] --datarootdir=DIR read-only arch.-independent data root [PREFIX/share] --datadir=DIR read-only architecture-independent data [DATAROOTDIR] --infodir=DIR info documentation [DATAROOTDIR/info] --localedir=DIR locale-dependent data [DATAROOTDIR/locale] --mandir=DIR man documentation [DATAROOTDIR/man] --docdir=DIR documentation root [DATAROOTDIR/doc/snprintfv] --htmldir=DIR html documentation [DOCDIR] --dvidir=DIR dvi documentation [DOCDIR] --pdfdir=DIR pdf documentation [DOCDIR] --psdir=DIR ps documentation [DOCDIR] _ACEOF cat <<\_ACEOF Program names: --program-prefix=PREFIX prepend PREFIX to installed program names --program-suffix=SUFFIX append SUFFIX to installed program names --program-transform-name=PROGRAM run sed PROGRAM on installed program names System types: --build=BUILD configure for building on BUILD [guessed] --host=HOST cross-compile to build programs to run on HOST [BUILD] _ACEOF fi if test -n "$ac_init_help"; then case $ac_init_help in short | recursive ) echo "Configuration of snprintfv 1.1:";; esac cat <<\_ACEOF Optional Features: --disable-option-checking ignore unrecognized --enable/--with options --disable-FEATURE do not include FEATURE (same as --enable-FEATURE=no) --enable-FEATURE[=ARG] include FEATURE [ARG=yes] --enable-subdir used in a package, texinfo+testsuite stripped --enable-shared[=PKGS] build shared libraries [default=yes] --enable-static[=PKGS] build static libraries [default=yes] --enable-fast-install[=PKGS] optimize for fast installation [default=yes] --disable-dependency-tracking speeds up one-time build --enable-dependency-tracking do not reject slow dependency extractors --disable-libtool-lock avoid locking (might break parallel builds) --enable-convenience-float-printing enable/disable printing floats in convenience snprintfv yes Optional Packages: --with-PACKAGE[=ARG] use PACKAGE [ARG=yes] --without-PACKAGE do not use PACKAGE (same as --with-PACKAGE=no) --with-pic[=PKGS] try to use only PIC/non-PIC objects [default=use both] --with-gnu-ld assume the C compiler uses GNU ld [default=no] --with-sysroot=DIR Search for dependent libraries within DIR (or the compiler's sysroot if not specified). --with-dmalloc use dmalloc, as in http://www.dmalloc.com Some influential environment variables: CC C compiler command CFLAGS C compiler flags LDFLAGS linker flags, e.g. -L if you have libraries in a nonstandard directory LIBS libraries to pass to the linker, e.g. -l CPPFLAGS (Objective) C/C++ preprocessor flags, e.g. -I if you have headers in a nonstandard directory CPP C preprocessor Use these variables to override the choices made by `configure' or to help it to find libraries and programs with nonstandard names/locations. Report bugs to . _ACEOF ac_status=$? fi if test "$ac_init_help" = "recursive"; then # If there are subdirs, report their specific --help. for ac_dir in : $ac_subdirs_all; do test "x$ac_dir" = x: && continue test -d "$ac_dir" || { cd "$srcdir" && ac_pwd=`pwd` && srcdir=. && test -d "$ac_dir"; } || continue ac_builddir=. case "$ac_dir" in .) ac_dir_suffix= ac_top_builddir_sub=. ac_top_build_prefix= ;; *) ac_dir_suffix=/`$as_echo "$ac_dir" | sed 's|^\.[\\/]||'` # A ".." for each directory in $ac_dir_suffix. ac_top_builddir_sub=`$as_echo "$ac_dir_suffix" | sed 's|/[^\\/]*|/..|g;s|/||'` case $ac_top_builddir_sub in "") ac_top_builddir_sub=. ac_top_build_prefix= ;; *) ac_top_build_prefix=$ac_top_builddir_sub/ ;; esac ;; esac ac_abs_top_builddir=$ac_pwd ac_abs_builddir=$ac_pwd$ac_dir_suffix # for backward compatibility: ac_top_builddir=$ac_top_build_prefix case $srcdir in .) # We are building in place. ac_srcdir=. ac_top_srcdir=$ac_top_builddir_sub ac_abs_top_srcdir=$ac_pwd ;; [\\/]* | ?:[\\/]* ) # Absolute name. ac_srcdir=$srcdir$ac_dir_suffix; ac_top_srcdir=$srcdir ac_abs_top_srcdir=$srcdir ;; *) # Relative name. ac_srcdir=$ac_top_build_prefix$srcdir$ac_dir_suffix ac_top_srcdir=$ac_top_build_prefix$srcdir ac_abs_top_srcdir=$ac_pwd/$srcdir ;; esac ac_abs_srcdir=$ac_abs_top_srcdir$ac_dir_suffix cd "$ac_dir" || { ac_status=$?; continue; } # Check for guested configure. if test -f "$ac_srcdir/configure.gnu"; then echo && $SHELL "$ac_srcdir/configure.gnu" --help=recursive elif test -f "$ac_srcdir/configure"; then echo && $SHELL "$ac_srcdir/configure" --help=recursive else $as_echo "$as_me: WARNING: no configuration information is in $ac_dir" >&2 fi || ac_status=$? cd "$ac_pwd" || { ac_status=$?; break; } done fi test -n "$ac_init_help" && exit $ac_status if $ac_init_version; then cat <<\_ACEOF snprintfv configure 1.1 generated by GNU Autoconf 2.69 Copyright (C) 2012 Free Software Foundation, Inc. This configure script is free software; the Free Software Foundation gives unlimited permission to copy, distribute and modify it. _ACEOF exit fi ## ------------------------ ## ## Autoconf initialization. ## ## ------------------------ ## # ac_fn_c_try_compile LINENO # -------------------------- # Try to compile conftest.$ac_ext, and return whether this succeeded. ac_fn_c_try_compile () { as_lineno=${as_lineno-"$1"} as_lineno_stack=as_lineno_stack=$as_lineno_stack rm -f conftest.$ac_objext if { { ac_try="$ac_compile" case "(($ac_try" in *\"* | *\`* | *\\*) ac_try_echo=\$ac_try;; *) ac_try_echo=$ac_try;; esac eval ac_try_echo="\"\$as_me:${as_lineno-$LINENO}: $ac_try_echo\"" $as_echo "$ac_try_echo"; } >&5 (eval "$ac_compile") 2>conftest.err ac_status=$? if test -s conftest.err; then grep -v '^ *+' conftest.err >conftest.er1 cat conftest.er1 >&5 mv -f conftest.er1 conftest.err fi $as_echo "$as_me:${as_lineno-$LINENO}: \$? = $ac_status" >&5 test $ac_status = 0; } && { test -z "$ac_c_werror_flag" || test ! -s conftest.err } && test -s conftest.$ac_objext; then : ac_retval=0 else $as_echo "$as_me: failed program was:" >&5 sed 's/^/| /' conftest.$ac_ext >&5 ac_retval=1 fi eval $as_lineno_stack; ${as_lineno_stack:+:} unset as_lineno as_fn_set_status $ac_retval } # ac_fn_c_try_compile # ac_fn_c_try_link LINENO # ----------------------- # Try to link conftest.$ac_ext, and return whether this succeeded. ac_fn_c_try_link () { as_lineno=${as_lineno-"$1"} as_lineno_stack=as_lineno_stack=$as_lineno_stack rm -f conftest.$ac_objext conftest$ac_exeext if { { ac_try="$ac_link" case "(($ac_try" in *\"* | *\`* | *\\*) ac_try_echo=\$ac_try;; *) ac_try_echo=$ac_try;; esac eval ac_try_echo="\"\$as_me:${as_lineno-$LINENO}: $ac_try_echo\"" $as_echo "$ac_try_echo"; } >&5 (eval "$ac_link") 2>conftest.err ac_status=$? if test -s conftest.err; then grep -v '^ *+' conftest.err >conftest.er1 cat conftest.er1 >&5 mv -f conftest.er1 conftest.err fi $as_echo "$as_me:${as_lineno-$LINENO}: \$? = $ac_status" >&5 test $ac_status = 0; } && { test -z "$ac_c_werror_flag" || test ! -s conftest.err } && test -s conftest$ac_exeext && { test "$cross_compiling" = yes || test -x conftest$ac_exeext }; then : ac_retval=0 else $as_echo "$as_me: failed program was:" >&5 sed 's/^/| /' conftest.$ac_ext >&5 ac_retval=1 fi # Delete the IPA/IPO (Inter Procedural Analysis/Optimization) information # created by the PGI compiler (conftest_ipa8_conftest.oo), as it would # interfere with the next link command; also delete a directory that is # left behind by Apple's compiler. We do this before executing the actions. rm -rf conftest.dSYM conftest_ipa8_conftest.oo eval $as_lineno_stack; ${as_lineno_stack:+:} unset as_lineno as_fn_set_status $ac_retval } # ac_fn_c_try_link # ac_fn_c_check_header_compile LINENO HEADER VAR INCLUDES # ------------------------------------------------------- # Tests whether HEADER exists and can be compiled using the include files in # INCLUDES, setting the cache variable VAR accordingly. ac_fn_c_check_header_compile () { as_lineno=${as_lineno-"$1"} as_lineno_stack=as_lineno_stack=$as_lineno_stack { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $2" >&5 $as_echo_n "checking for $2... " >&6; } if eval \${$3+:} false; then : $as_echo_n "(cached) " >&6 else cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ $4 #include <$2> _ACEOF if ac_fn_c_try_compile "$LINENO"; then : eval "$3=yes" else eval "$3=no" fi rm -f core conftest.err conftest.$ac_objext conftest.$ac_ext fi eval ac_res=\$$3 { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_res" >&5 $as_echo "$ac_res" >&6; } eval $as_lineno_stack; ${as_lineno_stack:+:} unset as_lineno } # ac_fn_c_check_header_compile # ac_fn_c_try_cpp LINENO # ---------------------- # Try to preprocess conftest.$ac_ext, and return whether this succeeded. ac_fn_c_try_cpp () { as_lineno=${as_lineno-"$1"} as_lineno_stack=as_lineno_stack=$as_lineno_stack if { { ac_try="$ac_cpp conftest.$ac_ext" case "(($ac_try" in *\"* | *\`* | *\\*) ac_try_echo=\$ac_try;; *) ac_try_echo=$ac_try;; esac eval ac_try_echo="\"\$as_me:${as_lineno-$LINENO}: $ac_try_echo\"" $as_echo "$ac_try_echo"; } >&5 (eval "$ac_cpp conftest.$ac_ext") 2>conftest.err ac_status=$? if test -s conftest.err; then grep -v '^ *+' conftest.err >conftest.er1 cat conftest.er1 >&5 mv -f conftest.er1 conftest.err fi $as_echo "$as_me:${as_lineno-$LINENO}: \$? = $ac_status" >&5 test $ac_status = 0; } > conftest.i && { test -z "$ac_c_preproc_warn_flag$ac_c_werror_flag" || test ! -s conftest.err }; then : ac_retval=0 else $as_echo "$as_me: failed program was:" >&5 sed 's/^/| /' conftest.$ac_ext >&5 ac_retval=1 fi eval $as_lineno_stack; ${as_lineno_stack:+:} unset as_lineno as_fn_set_status $ac_retval } # ac_fn_c_try_cpp # ac_fn_c_try_run LINENO # ---------------------- # Try to link conftest.$ac_ext, and return whether this succeeded. Assumes # that executables *can* be run. ac_fn_c_try_run () { as_lineno=${as_lineno-"$1"} as_lineno_stack=as_lineno_stack=$as_lineno_stack if { { ac_try="$ac_link" case "(($ac_try" in *\"* | *\`* | *\\*) ac_try_echo=\$ac_try;; *) ac_try_echo=$ac_try;; esac eval ac_try_echo="\"\$as_me:${as_lineno-$LINENO}: $ac_try_echo\"" $as_echo "$ac_try_echo"; } >&5 (eval "$ac_link") 2>&5 ac_status=$? $as_echo "$as_me:${as_lineno-$LINENO}: \$? = $ac_status" >&5 test $ac_status = 0; } && { ac_try='./conftest$ac_exeext' { { case "(($ac_try" in *\"* | *\`* | *\\*) ac_try_echo=\$ac_try;; *) ac_try_echo=$ac_try;; esac eval ac_try_echo="\"\$as_me:${as_lineno-$LINENO}: $ac_try_echo\"" $as_echo "$ac_try_echo"; } >&5 (eval "$ac_try") 2>&5 ac_status=$? $as_echo "$as_me:${as_lineno-$LINENO}: \$? = $ac_status" >&5 test $ac_status = 0; }; }; then : ac_retval=0 else $as_echo "$as_me: program exited with status $ac_status" >&5 $as_echo "$as_me: failed program was:" >&5 sed 's/^/| /' conftest.$ac_ext >&5 ac_retval=$ac_status fi rm -rf conftest.dSYM conftest_ipa8_conftest.oo eval $as_lineno_stack; ${as_lineno_stack:+:} unset as_lineno as_fn_set_status $ac_retval } # ac_fn_c_try_run # ac_fn_c_check_func LINENO FUNC VAR # ---------------------------------- # Tests whether FUNC exists, setting the cache variable VAR accordingly ac_fn_c_check_func () { as_lineno=${as_lineno-"$1"} as_lineno_stack=as_lineno_stack=$as_lineno_stack { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $2" >&5 $as_echo_n "checking for $2... " >&6; } if eval \${$3+:} false; then : $as_echo_n "(cached) " >&6 else cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ /* Define $2 to an innocuous variant, in case declares $2. For example, HP-UX 11i declares gettimeofday. */ #define $2 innocuous_$2 /* System header to define __stub macros and hopefully few prototypes, which can conflict with char $2 (); below. Prefer to if __STDC__ is defined, since exists even on freestanding compilers. */ #ifdef __STDC__ # include #else # include #endif #undef $2 /* Override any GCC internal prototype to avoid an error. Use char because int might match the return type of a GCC builtin and then its argument prototype would still apply. */ #ifdef __cplusplus extern "C" #endif char $2 (); /* The GNU C library defines this for functions which it implements to always fail with ENOSYS. Some functions are actually named something starting with __ and the normal name is an alias. */ #if defined __stub_$2 || defined __stub___$2 choke me #endif int main () { return $2 (); ; return 0; } _ACEOF if ac_fn_c_try_link "$LINENO"; then : eval "$3=yes" else eval "$3=no" fi rm -f core conftest.err conftest.$ac_objext \ conftest$ac_exeext conftest.$ac_ext fi eval ac_res=\$$3 { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_res" >&5 $as_echo "$ac_res" >&6; } eval $as_lineno_stack; ${as_lineno_stack:+:} unset as_lineno } # ac_fn_c_check_func # ac_fn_c_check_header_mongrel LINENO HEADER VAR INCLUDES # ------------------------------------------------------- # Tests whether HEADER exists, giving a warning if it cannot be compiled using # the include files in INCLUDES and setting the cache variable VAR # accordingly. ac_fn_c_check_header_mongrel () { as_lineno=${as_lineno-"$1"} as_lineno_stack=as_lineno_stack=$as_lineno_stack if eval \${$3+:} false; then : { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $2" >&5 $as_echo_n "checking for $2... " >&6; } if eval \${$3+:} false; then : $as_echo_n "(cached) " >&6 fi eval ac_res=\$$3 { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_res" >&5 $as_echo "$ac_res" >&6; } else # Is the header compilable? { $as_echo "$as_me:${as_lineno-$LINENO}: checking $2 usability" >&5 $as_echo_n "checking $2 usability... " >&6; } cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ $4 #include <$2> _ACEOF if ac_fn_c_try_compile "$LINENO"; then : ac_header_compiler=yes else ac_header_compiler=no fi rm -f core conftest.err conftest.$ac_objext conftest.$ac_ext { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_header_compiler" >&5 $as_echo "$ac_header_compiler" >&6; } # Is the header present? { $as_echo "$as_me:${as_lineno-$LINENO}: checking $2 presence" >&5 $as_echo_n "checking $2 presence... " >&6; } cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ #include <$2> _ACEOF if ac_fn_c_try_cpp "$LINENO"; then : ac_header_preproc=yes else ac_header_preproc=no fi rm -f conftest.err conftest.i conftest.$ac_ext { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_header_preproc" >&5 $as_echo "$ac_header_preproc" >&6; } # So? What about this header? case $ac_header_compiler:$ac_header_preproc:$ac_c_preproc_warn_flag in #(( yes:no: ) { $as_echo "$as_me:${as_lineno-$LINENO}: WARNING: $2: accepted by the compiler, rejected by the preprocessor!" >&5 $as_echo "$as_me: WARNING: $2: accepted by the compiler, rejected by the preprocessor!" >&2;} { $as_echo "$as_me:${as_lineno-$LINENO}: WARNING: $2: proceeding with the compiler's result" >&5 $as_echo "$as_me: WARNING: $2: proceeding with the compiler's result" >&2;} ;; no:yes:* ) { $as_echo "$as_me:${as_lineno-$LINENO}: WARNING: $2: present but cannot be compiled" >&5 $as_echo "$as_me: WARNING: $2: present but cannot be compiled" >&2;} { $as_echo "$as_me:${as_lineno-$LINENO}: WARNING: $2: check for missing prerequisite headers?" >&5 $as_echo "$as_me: WARNING: $2: check for missing prerequisite headers?" >&2;} { $as_echo "$as_me:${as_lineno-$LINENO}: WARNING: $2: see the Autoconf documentation" >&5 $as_echo "$as_me: WARNING: $2: see the Autoconf documentation" >&2;} { $as_echo "$as_me:${as_lineno-$LINENO}: WARNING: $2: section \"Present But Cannot Be Compiled\"" >&5 $as_echo "$as_me: WARNING: $2: section \"Present But Cannot Be Compiled\"" >&2;} { $as_echo "$as_me:${as_lineno-$LINENO}: WARNING: $2: proceeding with the compiler's result" >&5 $as_echo "$as_me: WARNING: $2: proceeding with the compiler's result" >&2;} ( $as_echo "## ------------------------------ ## ## Report this to bonzini@gnu.org ## ## ------------------------------ ##" ) | sed "s/^/$as_me: WARNING: /" >&2 ;; esac { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $2" >&5 $as_echo_n "checking for $2... " >&6; } if eval \${$3+:} false; then : $as_echo_n "(cached) " >&6 else eval "$3=\$ac_header_compiler" fi eval ac_res=\$$3 { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_res" >&5 $as_echo "$ac_res" >&6; } fi eval $as_lineno_stack; ${as_lineno_stack:+:} unset as_lineno } # ac_fn_c_check_header_mongrel # ac_fn_c_check_type LINENO TYPE VAR INCLUDES # ------------------------------------------- # Tests whether TYPE exists after having included INCLUDES, setting cache # variable VAR accordingly. ac_fn_c_check_type () { as_lineno=${as_lineno-"$1"} as_lineno_stack=as_lineno_stack=$as_lineno_stack { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $2" >&5 $as_echo_n "checking for $2... " >&6; } if eval \${$3+:} false; then : $as_echo_n "(cached) " >&6 else eval "$3=no" cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ $4 int main () { if (sizeof ($2)) return 0; ; return 0; } _ACEOF if ac_fn_c_try_compile "$LINENO"; then : cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ $4 int main () { if (sizeof (($2))) return 0; ; return 0; } _ACEOF if ac_fn_c_try_compile "$LINENO"; then : else eval "$3=yes" fi rm -f core conftest.err conftest.$ac_objext conftest.$ac_ext fi rm -f core conftest.err conftest.$ac_objext conftest.$ac_ext fi eval ac_res=\$$3 { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_res" >&5 $as_echo "$ac_res" >&6; } eval $as_lineno_stack; ${as_lineno_stack:+:} unset as_lineno } # ac_fn_c_check_type # ac_fn_c_compute_int LINENO EXPR VAR INCLUDES # -------------------------------------------- # Tries to find the compile-time value of EXPR in a program that includes # INCLUDES, setting VAR accordingly. Returns whether the value could be # computed ac_fn_c_compute_int () { as_lineno=${as_lineno-"$1"} as_lineno_stack=as_lineno_stack=$as_lineno_stack if test "$cross_compiling" = yes; then # Depending upon the size, compute the lo and hi bounds. cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ $4 int main () { static int test_array [1 - 2 * !(($2) >= 0)]; test_array [0] = 0; return test_array [0]; ; return 0; } _ACEOF if ac_fn_c_try_compile "$LINENO"; then : ac_lo=0 ac_mid=0 while :; do cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ $4 int main () { static int test_array [1 - 2 * !(($2) <= $ac_mid)]; test_array [0] = 0; return test_array [0]; ; return 0; } _ACEOF if ac_fn_c_try_compile "$LINENO"; then : ac_hi=$ac_mid; break else as_fn_arith $ac_mid + 1 && ac_lo=$as_val if test $ac_lo -le $ac_mid; then ac_lo= ac_hi= break fi as_fn_arith 2 '*' $ac_mid + 1 && ac_mid=$as_val fi rm -f core conftest.err conftest.$ac_objext conftest.$ac_ext done else cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ $4 int main () { static int test_array [1 - 2 * !(($2) < 0)]; test_array [0] = 0; return test_array [0]; ; return 0; } _ACEOF if ac_fn_c_try_compile "$LINENO"; then : ac_hi=-1 ac_mid=-1 while :; do cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ $4 int main () { static int test_array [1 - 2 * !(($2) >= $ac_mid)]; test_array [0] = 0; return test_array [0]; ; return 0; } _ACEOF if ac_fn_c_try_compile "$LINENO"; then : ac_lo=$ac_mid; break else as_fn_arith '(' $ac_mid ')' - 1 && ac_hi=$as_val if test $ac_mid -le $ac_hi; then ac_lo= ac_hi= break fi as_fn_arith 2 '*' $ac_mid && ac_mid=$as_val fi rm -f core conftest.err conftest.$ac_objext conftest.$ac_ext done else ac_lo= ac_hi= fi rm -f core conftest.err conftest.$ac_objext conftest.$ac_ext fi rm -f core conftest.err conftest.$ac_objext conftest.$ac_ext # Binary search between lo and hi bounds. while test "x$ac_lo" != "x$ac_hi"; do as_fn_arith '(' $ac_hi - $ac_lo ')' / 2 + $ac_lo && ac_mid=$as_val cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ $4 int main () { static int test_array [1 - 2 * !(($2) <= $ac_mid)]; test_array [0] = 0; return test_array [0]; ; return 0; } _ACEOF if ac_fn_c_try_compile "$LINENO"; then : ac_hi=$ac_mid else as_fn_arith '(' $ac_mid ')' + 1 && ac_lo=$as_val fi rm -f core conftest.err conftest.$ac_objext conftest.$ac_ext done case $ac_lo in #(( ?*) eval "$3=\$ac_lo"; ac_retval=0 ;; '') ac_retval=1 ;; esac else cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ $4 static long int longval () { return $2; } static unsigned long int ulongval () { return $2; } #include #include int main () { FILE *f = fopen ("conftest.val", "w"); if (! f) return 1; if (($2) < 0) { long int i = longval (); if (i != ($2)) return 1; fprintf (f, "%ld", i); } else { unsigned long int i = ulongval (); if (i != ($2)) return 1; fprintf (f, "%lu", i); } /* Do not output a trailing newline, as this causes \r\n confusion on some platforms. */ return ferror (f) || fclose (f) != 0; ; return 0; } _ACEOF if ac_fn_c_try_run "$LINENO"; then : echo >>conftest.val; read $3 config.log <<_ACEOF This file contains any messages produced by compilers while running configure, to aid debugging if configure makes a mistake. It was created by snprintfv $as_me 1.1, which was generated by GNU Autoconf 2.69. Invocation command line was $ $0 $@ _ACEOF exec 5>>config.log { cat <<_ASUNAME ## --------- ## ## Platform. ## ## --------- ## hostname = `(hostname || uname -n) 2>/dev/null | sed 1q` uname -m = `(uname -m) 2>/dev/null || echo unknown` uname -r = `(uname -r) 2>/dev/null || echo unknown` uname -s = `(uname -s) 2>/dev/null || echo unknown` uname -v = `(uname -v) 2>/dev/null || echo unknown` /usr/bin/uname -p = `(/usr/bin/uname -p) 2>/dev/null || echo unknown` /bin/uname -X = `(/bin/uname -X) 2>/dev/null || echo unknown` /bin/arch = `(/bin/arch) 2>/dev/null || echo unknown` /usr/bin/arch -k = `(/usr/bin/arch -k) 2>/dev/null || echo unknown` /usr/convex/getsysinfo = `(/usr/convex/getsysinfo) 2>/dev/null || echo unknown` /usr/bin/hostinfo = `(/usr/bin/hostinfo) 2>/dev/null || echo unknown` /bin/machine = `(/bin/machine) 2>/dev/null || echo unknown` /usr/bin/oslevel = `(/usr/bin/oslevel) 2>/dev/null || echo unknown` /bin/universe = `(/bin/universe) 2>/dev/null || echo unknown` _ASUNAME as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. $as_echo "PATH: $as_dir" done IFS=$as_save_IFS } >&5 cat >&5 <<_ACEOF ## ----------- ## ## Core tests. ## ## ----------- ## _ACEOF # Keep a trace of the command line. # Strip out --no-create and --no-recursion so they do not pile up. # Strip out --silent because we don't want to record it for future runs. # Also quote any args containing shell meta-characters. # Make two passes to allow for proper duplicate-argument suppression. ac_configure_args= ac_configure_args0= ac_configure_args1= ac_must_keep_next=false for ac_pass in 1 2 do for ac_arg do case $ac_arg in -no-create | --no-c* | -n | -no-recursion | --no-r*) continue ;; -q | -quiet | --quiet | --quie | --qui | --qu | --q \ | -silent | --silent | --silen | --sile | --sil) continue ;; *\'*) ac_arg=`$as_echo "$ac_arg" | sed "s/'/'\\\\\\\\''/g"` ;; esac case $ac_pass in 1) as_fn_append ac_configure_args0 " '$ac_arg'" ;; 2) as_fn_append ac_configure_args1 " '$ac_arg'" if test $ac_must_keep_next = true; then ac_must_keep_next=false # Got value, back to normal. else case $ac_arg in *=* | --config-cache | -C | -disable-* | --disable-* \ | -enable-* | --enable-* | -gas | --g* | -nfp | --nf* \ | -q | -quiet | --q* | -silent | --sil* | -v | -verb* \ | -with-* | --with-* | -without-* | --without-* | --x) case "$ac_configure_args0 " in "$ac_configure_args1"*" '$ac_arg' "* ) continue ;; esac ;; -* ) ac_must_keep_next=true ;; esac fi as_fn_append ac_configure_args " '$ac_arg'" ;; esac done done { ac_configure_args0=; unset ac_configure_args0;} { ac_configure_args1=; unset ac_configure_args1;} # When interrupted or exit'd, cleanup temporary files, and complete # config.log. We remove comments because anyway the quotes in there # would cause problems or look ugly. # WARNING: Use '\'' to represent an apostrophe within the trap. # WARNING: Do not start the trap code with a newline, due to a FreeBSD 4.0 bug. trap 'exit_status=$? # Save into config.log some information that might help in debugging. { echo $as_echo "## ---------------- ## ## Cache variables. ## ## ---------------- ##" echo # The following way of writing the cache mishandles newlines in values, ( for ac_var in `(set) 2>&1 | sed -n '\''s/^\([a-zA-Z_][a-zA-Z0-9_]*\)=.*/\1/p'\''`; do eval ac_val=\$$ac_var case $ac_val in #( *${as_nl}*) case $ac_var in #( *_cv_*) { $as_echo "$as_me:${as_lineno-$LINENO}: WARNING: cache variable $ac_var contains a newline" >&5 $as_echo "$as_me: WARNING: cache variable $ac_var contains a newline" >&2;} ;; esac case $ac_var in #( _ | IFS | as_nl) ;; #( BASH_ARGV | BASH_SOURCE) eval $ac_var= ;; #( *) { eval $ac_var=; unset $ac_var;} ;; esac ;; esac done (set) 2>&1 | case $as_nl`(ac_space='\'' '\''; set) 2>&1` in #( *${as_nl}ac_space=\ *) sed -n \ "s/'\''/'\''\\\\'\'''\''/g; s/^\\([_$as_cr_alnum]*_cv_[_$as_cr_alnum]*\\)=\\(.*\\)/\\1='\''\\2'\''/p" ;; #( *) sed -n "/^[_$as_cr_alnum]*_cv_[_$as_cr_alnum]*=/p" ;; esac | sort ) echo $as_echo "## ----------------- ## ## Output variables. ## ## ----------------- ##" echo for ac_var in $ac_subst_vars do eval ac_val=\$$ac_var case $ac_val in *\'\''*) ac_val=`$as_echo "$ac_val" | sed "s/'\''/'\''\\\\\\\\'\'''\''/g"`;; esac $as_echo "$ac_var='\''$ac_val'\''" done | sort echo if test -n "$ac_subst_files"; then $as_echo "## ------------------- ## ## File substitutions. ## ## ------------------- ##" echo for ac_var in $ac_subst_files do eval ac_val=\$$ac_var case $ac_val in *\'\''*) ac_val=`$as_echo "$ac_val" | sed "s/'\''/'\''\\\\\\\\'\'''\''/g"`;; esac $as_echo "$ac_var='\''$ac_val'\''" done | sort echo fi if test -s confdefs.h; then $as_echo "## ----------- ## ## confdefs.h. ## ## ----------- ##" echo cat confdefs.h echo fi test "$ac_signal" != 0 && $as_echo "$as_me: caught signal $ac_signal" $as_echo "$as_me: exit $exit_status" } >&5 rm -f core *.core core.conftest.* && rm -f -r conftest* confdefs* conf$$* $ac_clean_files && exit $exit_status ' 0 for ac_signal in 1 2 13 15; do trap 'ac_signal='$ac_signal'; as_fn_exit 1' $ac_signal done ac_signal=0 # confdefs.h avoids OS command line length limits that DEFS can exceed. rm -f -r conftest* confdefs.h $as_echo "/* confdefs.h */" > confdefs.h # Predefined preprocessor variables. cat >>confdefs.h <<_ACEOF #define PACKAGE_NAME "$PACKAGE_NAME" _ACEOF cat >>confdefs.h <<_ACEOF #define PACKAGE_TARNAME "$PACKAGE_TARNAME" _ACEOF cat >>confdefs.h <<_ACEOF #define PACKAGE_VERSION "$PACKAGE_VERSION" _ACEOF cat >>confdefs.h <<_ACEOF #define PACKAGE_STRING "$PACKAGE_STRING" _ACEOF cat >>confdefs.h <<_ACEOF #define PACKAGE_BUGREPORT "$PACKAGE_BUGREPORT" _ACEOF cat >>confdefs.h <<_ACEOF #define PACKAGE_URL "$PACKAGE_URL" _ACEOF # Let the site file select an alternate cache file if it wants to. # Prefer an explicitly selected file to automatically selected ones. ac_site_file1=NONE ac_site_file2=NONE if test -n "$CONFIG_SITE"; then # We do not want a PATH search for config.site. case $CONFIG_SITE in #(( -*) ac_site_file1=./$CONFIG_SITE;; */*) ac_site_file1=$CONFIG_SITE;; *) ac_site_file1=./$CONFIG_SITE;; esac elif test "x$prefix" != xNONE; then ac_site_file1=$prefix/share/config.site ac_site_file2=$prefix/etc/config.site else ac_site_file1=$ac_default_prefix/share/config.site ac_site_file2=$ac_default_prefix/etc/config.site fi for ac_site_file in "$ac_site_file1" "$ac_site_file2" do test "x$ac_site_file" = xNONE && continue if test /dev/null != "$ac_site_file" && test -r "$ac_site_file"; then { $as_echo "$as_me:${as_lineno-$LINENO}: loading site script $ac_site_file" >&5 $as_echo "$as_me: loading site script $ac_site_file" >&6;} sed 's/^/| /' "$ac_site_file" >&5 . "$ac_site_file" \ || { { $as_echo "$as_me:${as_lineno-$LINENO}: error: in \`$ac_pwd':" >&5 $as_echo "$as_me: error: in \`$ac_pwd':" >&2;} as_fn_error $? "failed to load site script $ac_site_file See \`config.log' for more details" "$LINENO" 5; } fi done if test -r "$cache_file"; then # Some versions of bash will fail to source /dev/null (special files # actually), so we avoid doing that. DJGPP emulates it as a regular file. if test /dev/null != "$cache_file" && test -f "$cache_file"; then { $as_echo "$as_me:${as_lineno-$LINENO}: loading cache $cache_file" >&5 $as_echo "$as_me: loading cache $cache_file" >&6;} case $cache_file in [\\/]* | ?:[\\/]* ) . "$cache_file";; *) . "./$cache_file";; esac fi else { $as_echo "$as_me:${as_lineno-$LINENO}: creating cache $cache_file" >&5 $as_echo "$as_me: creating cache $cache_file" >&6;} >$cache_file fi # Check that the precious variables saved in the cache have kept the same # value. ac_cache_corrupted=false for ac_var in $ac_precious_vars; do eval ac_old_set=\$ac_cv_env_${ac_var}_set eval ac_new_set=\$ac_env_${ac_var}_set eval ac_old_val=\$ac_cv_env_${ac_var}_value eval ac_new_val=\$ac_env_${ac_var}_value case $ac_old_set,$ac_new_set in set,) { $as_echo "$as_me:${as_lineno-$LINENO}: error: \`$ac_var' was set to \`$ac_old_val' in the previous run" >&5 $as_echo "$as_me: error: \`$ac_var' was set to \`$ac_old_val' in the previous run" >&2;} ac_cache_corrupted=: ;; ,set) { $as_echo "$as_me:${as_lineno-$LINENO}: error: \`$ac_var' was not set in the previous run" >&5 $as_echo "$as_me: error: \`$ac_var' was not set in the previous run" >&2;} ac_cache_corrupted=: ;; ,);; *) if test "x$ac_old_val" != "x$ac_new_val"; then # differences in whitespace do not lead to failure. ac_old_val_w=`echo x $ac_old_val` ac_new_val_w=`echo x $ac_new_val` if test "$ac_old_val_w" != "$ac_new_val_w"; then { $as_echo "$as_me:${as_lineno-$LINENO}: error: \`$ac_var' has changed since the previous run:" >&5 $as_echo "$as_me: error: \`$ac_var' has changed since the previous run:" >&2;} ac_cache_corrupted=: else { $as_echo "$as_me:${as_lineno-$LINENO}: warning: ignoring whitespace changes in \`$ac_var' since the previous run:" >&5 $as_echo "$as_me: warning: ignoring whitespace changes in \`$ac_var' since the previous run:" >&2;} eval $ac_var=\$ac_old_val fi { $as_echo "$as_me:${as_lineno-$LINENO}: former value: \`$ac_old_val'" >&5 $as_echo "$as_me: former value: \`$ac_old_val'" >&2;} { $as_echo "$as_me:${as_lineno-$LINENO}: current value: \`$ac_new_val'" >&5 $as_echo "$as_me: current value: \`$ac_new_val'" >&2;} fi;; esac # Pass precious variables to config.status. if test "$ac_new_set" = set; then case $ac_new_val in *\'*) ac_arg=$ac_var=`$as_echo "$ac_new_val" | sed "s/'/'\\\\\\\\''/g"` ;; *) ac_arg=$ac_var=$ac_new_val ;; esac case " $ac_configure_args " in *" '$ac_arg' "*) ;; # Avoid dups. Use of quotes ensures accuracy. *) as_fn_append ac_configure_args " '$ac_arg'" ;; esac fi done if $ac_cache_corrupted; then { $as_echo "$as_me:${as_lineno-$LINENO}: error: in \`$ac_pwd':" >&5 $as_echo "$as_me: error: in \`$ac_pwd':" >&2;} { $as_echo "$as_me:${as_lineno-$LINENO}: error: changes in the environment can compromise the build" >&5 $as_echo "$as_me: error: changes in the environment can compromise the build" >&2;} as_fn_error $? "run \`make distclean' and/or \`rm $cache_file' and start over" "$LINENO" 5 fi ## -------------------- ## ## Main body of script. ## ## -------------------- ## ac_ext=c ac_cpp='$CPP $CPPFLAGS' ac_compile='$CC -c $CFLAGS $CPPFLAGS conftest.$ac_ext >&5' ac_link='$CC -o conftest$ac_exeext $CFLAGS $CPPFLAGS $LDFLAGS conftest.$ac_ext $LIBS >&5' ac_compiler_gnu=$ac_cv_c_compiler_gnu ac_config_headers="$ac_config_headers config.h" ac_aux_dir= for ac_dir in ../build-aux "$srcdir"/../build-aux; do if test -f "$ac_dir/install-sh"; then ac_aux_dir=$ac_dir ac_install_sh="$ac_aux_dir/install-sh -c" break elif test -f "$ac_dir/install.sh"; then ac_aux_dir=$ac_dir ac_install_sh="$ac_aux_dir/install.sh -c" break elif test -f "$ac_dir/shtool"; then ac_aux_dir=$ac_dir ac_install_sh="$ac_aux_dir/shtool install -c" break fi done if test -z "$ac_aux_dir"; then as_fn_error $? "cannot find install-sh, install.sh, or shtool in ../build-aux \"$srcdir\"/../build-aux" "$LINENO" 5 fi # These three variables are undocumented and unsupported, # and are intended to be withdrawn in a future Autoconf release. # They can cause serious problems if a builder's source tree is in a directory # whose full name contains unusual characters. ac_config_guess="$SHELL $ac_aux_dir/config.guess" # Please don't use this var. ac_config_sub="$SHELL $ac_aux_dir/config.sub" # Please don't use this var. ac_configure="$SHELL $ac_aux_dir/configure" # Please don't use this var. # Check whether --enable-subdir was given. if test "${enable_subdir+set}" = set; then : enableval=$enable_subdir; else enable_subdir=no fi am__api_version='1.11' # Find a good install program. We prefer a C program (faster), # so one script is as good as another. But avoid the broken or # incompatible versions: # SysV /etc/install, /usr/sbin/install # SunOS /usr/etc/install # IRIX /sbin/install # AIX /bin/install # AmigaOS /C/install, which installs bootblocks on floppy discs # AIX 4 /usr/bin/installbsd, which doesn't work without a -g flag # AFS /usr/afsws/bin/install, which mishandles nonexistent args # SVR4 /usr/ucb/install, which tries to use the nonexistent group "staff" # OS/2's system install, which has a completely different semantic # ./install, which can be erroneously created by make from ./install.sh. # Reject install programs that cannot install multiple files. { $as_echo "$as_me:${as_lineno-$LINENO}: checking for a BSD-compatible install" >&5 $as_echo_n "checking for a BSD-compatible install... " >&6; } if test -z "$INSTALL"; then if ${ac_cv_path_install+:} false; then : $as_echo_n "(cached) " >&6 else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. # Account for people who put trailing slashes in PATH elements. case $as_dir/ in #(( ./ | .// | /[cC]/* | \ /etc/* | /usr/sbin/* | /usr/etc/* | /sbin/* | /usr/afsws/bin/* | \ ?:[\\/]os2[\\/]install[\\/]* | ?:[\\/]OS2[\\/]INSTALL[\\/]* | \ /usr/ucb/* ) ;; *) # OSF1 and SCO ODT 3.0 have their own names for install. # Don't use installbsd from OSF since it installs stuff as root # by default. for ac_prog in ginstall scoinst install; do for ac_exec_ext in '' $ac_executable_extensions; do if as_fn_executable_p "$as_dir/$ac_prog$ac_exec_ext"; then if test $ac_prog = install && grep dspmsg "$as_dir/$ac_prog$ac_exec_ext" >/dev/null 2>&1; then # AIX install. It has an incompatible calling convention. : elif test $ac_prog = install && grep pwplus "$as_dir/$ac_prog$ac_exec_ext" >/dev/null 2>&1; then # program-specific install script used by HP pwplus--don't use. : else rm -rf conftest.one conftest.two conftest.dir echo one > conftest.one echo two > conftest.two mkdir conftest.dir if "$as_dir/$ac_prog$ac_exec_ext" -c conftest.one conftest.two "`pwd`/conftest.dir" && test -s conftest.one && test -s conftest.two && test -s conftest.dir/conftest.one && test -s conftest.dir/conftest.two then ac_cv_path_install="$as_dir/$ac_prog$ac_exec_ext -c" break 3 fi fi fi done done ;; esac done IFS=$as_save_IFS rm -rf conftest.one conftest.two conftest.dir fi if test "${ac_cv_path_install+set}" = set; then INSTALL=$ac_cv_path_install else # As a last resort, use the slow shell script. Don't cache a # value for INSTALL within a source directory, because that will # break other packages using the cache if that directory is # removed, or if the value is a relative name. INSTALL=$ac_install_sh fi fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $INSTALL" >&5 $as_echo "$INSTALL" >&6; } # Use test -z because SunOS4 sh mishandles braces in ${var-val}. # It thinks the first close brace ends the variable substitution. test -z "$INSTALL_PROGRAM" && INSTALL_PROGRAM='${INSTALL}' test -z "$INSTALL_SCRIPT" && INSTALL_SCRIPT='${INSTALL}' test -z "$INSTALL_DATA" && INSTALL_DATA='${INSTALL} -m 644' { $as_echo "$as_me:${as_lineno-$LINENO}: checking whether build environment is sane" >&5 $as_echo_n "checking whether build environment is sane... " >&6; } # Just in case sleep 1 echo timestamp > conftest.file # Reject unsafe characters in $srcdir or the absolute working directory # name. Accept space and tab only in the latter. am_lf=' ' case `pwd` in *[\\\"\#\$\&\'\`$am_lf]*) as_fn_error $? "unsafe absolute working directory name" "$LINENO" 5;; esac case $srcdir in *[\\\"\#\$\&\'\`$am_lf\ \ ]*) as_fn_error $? "unsafe srcdir value: \`$srcdir'" "$LINENO" 5;; esac # Do `set' in a subshell so we don't clobber the current shell's # arguments. Must try -L first in case configure is actually a # symlink; some systems play weird games with the mod time of symlinks # (eg FreeBSD returns the mod time of the symlink's containing # directory). if ( set X `ls -Lt "$srcdir/configure" conftest.file 2> /dev/null` if test "$*" = "X"; then # -L didn't work. set X `ls -t "$srcdir/configure" conftest.file` fi rm -f conftest.file if test "$*" != "X $srcdir/configure conftest.file" \ && test "$*" != "X conftest.file $srcdir/configure"; then # If neither matched, then we have a broken ls. This can happen # if, for instance, CONFIG_SHELL is bash and it inherits a # broken ls alias from the environment. This has actually # happened. Such a system could not be considered "sane". as_fn_error $? "ls -t appears to fail. Make sure there is not a broken alias in your environment" "$LINENO" 5 fi test "$2" = conftest.file ) then # Ok. : else as_fn_error $? "newly created file is older than distributed files! Check your system clock" "$LINENO" 5 fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: yes" >&5 $as_echo "yes" >&6; } test "$program_prefix" != NONE && program_transform_name="s&^&$program_prefix&;$program_transform_name" # Use a double $ so make ignores it. test "$program_suffix" != NONE && program_transform_name="s&\$&$program_suffix&;$program_transform_name" # Double any \ or $. # By default was `s,x,x', remove it if useless. ac_script='s/[\\$]/&&/g;s/;s,x,x,$//' program_transform_name=`$as_echo "$program_transform_name" | sed "$ac_script"` # expand $ac_aux_dir to an absolute path am_aux_dir=`cd $ac_aux_dir && pwd` if test x"${MISSING+set}" != xset; then case $am_aux_dir in *\ * | *\ *) MISSING="\${SHELL} \"$am_aux_dir/missing\"" ;; *) MISSING="\${SHELL} $am_aux_dir/missing" ;; esac fi # Use eval to expand $SHELL if eval "$MISSING --run true"; then am_missing_run="$MISSING --run " else am_missing_run= { $as_echo "$as_me:${as_lineno-$LINENO}: WARNING: \`missing' script is too old or missing" >&5 $as_echo "$as_me: WARNING: \`missing' script is too old or missing" >&2;} fi if test x"${install_sh}" != xset; then case $am_aux_dir in *\ * | *\ *) install_sh="\${SHELL} '$am_aux_dir/install-sh'" ;; *) install_sh="\${SHELL} $am_aux_dir/install-sh" esac fi # Installed binaries are usually stripped using `strip' when the user # run `make install-strip'. However `strip' might not be the right # tool to use in cross-compilation environments, therefore Automake # will honor the `STRIP' environment variable to overrule this program. if test "$cross_compiling" != no; then if test -n "$ac_tool_prefix"; then # Extract the first word of "${ac_tool_prefix}strip", so it can be a program name with args. set dummy ${ac_tool_prefix}strip; ac_word=$2 { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $ac_word" >&5 $as_echo_n "checking for $ac_word... " >&6; } if ${ac_cv_prog_STRIP+:} false; then : $as_echo_n "(cached) " >&6 else if test -n "$STRIP"; then ac_cv_prog_STRIP="$STRIP" # Let the user override the test. else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_exec_ext in '' $ac_executable_extensions; do if as_fn_executable_p "$as_dir/$ac_word$ac_exec_ext"; then ac_cv_prog_STRIP="${ac_tool_prefix}strip" $as_echo "$as_me:${as_lineno-$LINENO}: found $as_dir/$ac_word$ac_exec_ext" >&5 break 2 fi done done IFS=$as_save_IFS fi fi STRIP=$ac_cv_prog_STRIP if test -n "$STRIP"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $STRIP" >&5 $as_echo "$STRIP" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi fi if test -z "$ac_cv_prog_STRIP"; then ac_ct_STRIP=$STRIP # Extract the first word of "strip", so it can be a program name with args. set dummy strip; ac_word=$2 { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $ac_word" >&5 $as_echo_n "checking for $ac_word... " >&6; } if ${ac_cv_prog_ac_ct_STRIP+:} false; then : $as_echo_n "(cached) " >&6 else if test -n "$ac_ct_STRIP"; then ac_cv_prog_ac_ct_STRIP="$ac_ct_STRIP" # Let the user override the test. else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_exec_ext in '' $ac_executable_extensions; do if as_fn_executable_p "$as_dir/$ac_word$ac_exec_ext"; then ac_cv_prog_ac_ct_STRIP="strip" $as_echo "$as_me:${as_lineno-$LINENO}: found $as_dir/$ac_word$ac_exec_ext" >&5 break 2 fi done done IFS=$as_save_IFS fi fi ac_ct_STRIP=$ac_cv_prog_ac_ct_STRIP if test -n "$ac_ct_STRIP"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_ct_STRIP" >&5 $as_echo "$ac_ct_STRIP" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi if test "x$ac_ct_STRIP" = x; then STRIP=":" else case $cross_compiling:$ac_tool_warned in yes:) { $as_echo "$as_me:${as_lineno-$LINENO}: WARNING: using cross tools not prefixed with host triplet" >&5 $as_echo "$as_me: WARNING: using cross tools not prefixed with host triplet" >&2;} ac_tool_warned=yes ;; esac STRIP=$ac_ct_STRIP fi else STRIP="$ac_cv_prog_STRIP" fi fi INSTALL_STRIP_PROGRAM="\$(install_sh) -c -s" { $as_echo "$as_me:${as_lineno-$LINENO}: checking for a thread-safe mkdir -p" >&5 $as_echo_n "checking for a thread-safe mkdir -p... " >&6; } if test -z "$MKDIR_P"; then if ${ac_cv_path_mkdir+:} false; then : $as_echo_n "(cached) " >&6 else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH$PATH_SEPARATOR/opt/sfw/bin do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_prog in mkdir gmkdir; do for ac_exec_ext in '' $ac_executable_extensions; do as_fn_executable_p "$as_dir/$ac_prog$ac_exec_ext" || continue case `"$as_dir/$ac_prog$ac_exec_ext" --version 2>&1` in #( 'mkdir (GNU coreutils) '* | \ 'mkdir (coreutils) '* | \ 'mkdir (fileutils) '4.1*) ac_cv_path_mkdir=$as_dir/$ac_prog$ac_exec_ext break 3;; esac done done done IFS=$as_save_IFS fi test -d ./--version && rmdir ./--version if test "${ac_cv_path_mkdir+set}" = set; then MKDIR_P="$ac_cv_path_mkdir -p" else # As a last resort, use the slow shell script. Don't cache a # value for MKDIR_P within a source directory, because that will # break other packages using the cache if that directory is # removed, or if the value is a relative name. MKDIR_P="$ac_install_sh -d" fi fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $MKDIR_P" >&5 $as_echo "$MKDIR_P" >&6; } mkdir_p="$MKDIR_P" case $mkdir_p in [\\/$]* | ?:[\\/]*) ;; */*) mkdir_p="\$(top_builddir)/$mkdir_p" ;; esac for ac_prog in gawk mawk nawk awk do # Extract the first word of "$ac_prog", so it can be a program name with args. set dummy $ac_prog; ac_word=$2 { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $ac_word" >&5 $as_echo_n "checking for $ac_word... " >&6; } if ${ac_cv_prog_AWK+:} false; then : $as_echo_n "(cached) " >&6 else if test -n "$AWK"; then ac_cv_prog_AWK="$AWK" # Let the user override the test. else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_exec_ext in '' $ac_executable_extensions; do if as_fn_executable_p "$as_dir/$ac_word$ac_exec_ext"; then ac_cv_prog_AWK="$ac_prog" $as_echo "$as_me:${as_lineno-$LINENO}: found $as_dir/$ac_word$ac_exec_ext" >&5 break 2 fi done done IFS=$as_save_IFS fi fi AWK=$ac_cv_prog_AWK if test -n "$AWK"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $AWK" >&5 $as_echo "$AWK" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi test -n "$AWK" && break done { $as_echo "$as_me:${as_lineno-$LINENO}: checking whether ${MAKE-make} sets \$(MAKE)" >&5 $as_echo_n "checking whether ${MAKE-make} sets \$(MAKE)... " >&6; } set x ${MAKE-make} ac_make=`$as_echo "$2" | sed 's/+/p/g; s/[^a-zA-Z0-9_]/_/g'` if eval \${ac_cv_prog_make_${ac_make}_set+:} false; then : $as_echo_n "(cached) " >&6 else cat >conftest.make <<\_ACEOF SHELL = /bin/sh all: @echo '@@@%%%=$(MAKE)=@@@%%%' _ACEOF # GNU make sometimes prints "make[1]: Entering ...", which would confuse us. case `${MAKE-make} -f conftest.make 2>/dev/null` in *@@@%%%=?*=@@@%%%*) eval ac_cv_prog_make_${ac_make}_set=yes;; *) eval ac_cv_prog_make_${ac_make}_set=no;; esac rm -f conftest.make fi if eval test \$ac_cv_prog_make_${ac_make}_set = yes; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: yes" >&5 $as_echo "yes" >&6; } SET_MAKE= else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } SET_MAKE="MAKE=${MAKE-make}" fi rm -rf .tst 2>/dev/null mkdir .tst 2>/dev/null if test -d .tst; then am__leading_dot=. else am__leading_dot=_ fi rmdir .tst 2>/dev/null if test "`cd $srcdir && pwd`" != "`pwd`"; then # Use -I$(srcdir) only when $(srcdir) != ., so that make's output # is not polluted with repeated "-I." am__isrc=' -I$(srcdir)' # test to see if srcdir already configured if test -f $srcdir/config.status; then as_fn_error $? "source directory already configured; run \"make distclean\" there first" "$LINENO" 5 fi fi # test whether we have cygpath if test -z "$CYGPATH_W"; then if (cygpath --version) >/dev/null 2>/dev/null; then CYGPATH_W='cygpath -w' else CYGPATH_W=echo fi fi # Define the identity of the package. PACKAGE='snprintfv' VERSION='1.1' cat >>confdefs.h <<_ACEOF #define PACKAGE "$PACKAGE" _ACEOF cat >>confdefs.h <<_ACEOF #define VERSION "$VERSION" _ACEOF # Some tools Automake needs. ACLOCAL=${ACLOCAL-"${am_missing_run}aclocal-${am__api_version}"} AUTOCONF=${AUTOCONF-"${am_missing_run}autoconf"} AUTOMAKE=${AUTOMAKE-"${am_missing_run}automake-${am__api_version}"} AUTOHEADER=${AUTOHEADER-"${am_missing_run}autoheader"} MAKEINFO=${MAKEINFO-"${am_missing_run}makeinfo"} # We need awk for the "check" target. The system "awk" is bad on # some platforms. # Always define AMTAR for backward compatibility. Yes, it's still used # in the wild :-( We should find a proper way to deprecate it ... AMTAR='$${TAR-tar}' am__tar='$${TAR-tar} chof - "$$tardir"' am__untar='$${TAR-tar} xf -' SNV_CURRENT=3; SNV_REVISION=0; SNV_AGE=0; # Make sure we can run config.sub. $SHELL "$ac_aux_dir/config.sub" sun4 >/dev/null 2>&1 || as_fn_error $? "cannot run $SHELL $ac_aux_dir/config.sub" "$LINENO" 5 { $as_echo "$as_me:${as_lineno-$LINENO}: checking build system type" >&5 $as_echo_n "checking build system type... " >&6; } if ${ac_cv_build+:} false; then : $as_echo_n "(cached) " >&6 else ac_build_alias=$build_alias test "x$ac_build_alias" = x && ac_build_alias=`$SHELL "$ac_aux_dir/config.guess"` test "x$ac_build_alias" = x && as_fn_error $? "cannot guess build type; you must specify one" "$LINENO" 5 ac_cv_build=`$SHELL "$ac_aux_dir/config.sub" $ac_build_alias` || as_fn_error $? "$SHELL $ac_aux_dir/config.sub $ac_build_alias failed" "$LINENO" 5 fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_cv_build" >&5 $as_echo "$ac_cv_build" >&6; } case $ac_cv_build in *-*-*) ;; *) as_fn_error $? "invalid value of canonical build" "$LINENO" 5;; esac build=$ac_cv_build ac_save_IFS=$IFS; IFS='-' set x $ac_cv_build shift build_cpu=$1 build_vendor=$2 shift; shift # Remember, the first character of IFS is used to create $*, # except with old shells: build_os=$* IFS=$ac_save_IFS case $build_os in *\ *) build_os=`echo "$build_os" | sed 's/ /-/g'`;; esac { $as_echo "$as_me:${as_lineno-$LINENO}: checking host system type" >&5 $as_echo_n "checking host system type... " >&6; } if ${ac_cv_host+:} false; then : $as_echo_n "(cached) " >&6 else if test "x$host_alias" = x; then ac_cv_host=$ac_cv_build else ac_cv_host=`$SHELL "$ac_aux_dir/config.sub" $host_alias` || as_fn_error $? "$SHELL $ac_aux_dir/config.sub $host_alias failed" "$LINENO" 5 fi fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_cv_host" >&5 $as_echo "$ac_cv_host" >&6; } case $ac_cv_host in *-*-*) ;; *) as_fn_error $? "invalid value of canonical host" "$LINENO" 5;; esac host=$ac_cv_host ac_save_IFS=$IFS; IFS='-' set x $ac_cv_host shift host_cpu=$1 host_vendor=$2 shift; shift # Remember, the first character of IFS is used to create $*, # except with old shells: host_os=$* IFS=$ac_save_IFS case $host_os in *\ *) host_os=`echo "$host_os" | sed 's/ /-/g'`;; esac enable_win32_dll=yes case $host in *-*-cygwin* | *-*-mingw* | *-*-pw32* | *-*-cegcc*) if test -n "$ac_tool_prefix"; then # Extract the first word of "${ac_tool_prefix}as", so it can be a program name with args. set dummy ${ac_tool_prefix}as; ac_word=$2 { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $ac_word" >&5 $as_echo_n "checking for $ac_word... " >&6; } if ${ac_cv_prog_AS+:} false; then : $as_echo_n "(cached) " >&6 else if test -n "$AS"; then ac_cv_prog_AS="$AS" # Let the user override the test. else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_exec_ext in '' $ac_executable_extensions; do if as_fn_executable_p "$as_dir/$ac_word$ac_exec_ext"; then ac_cv_prog_AS="${ac_tool_prefix}as" $as_echo "$as_me:${as_lineno-$LINENO}: found $as_dir/$ac_word$ac_exec_ext" >&5 break 2 fi done done IFS=$as_save_IFS fi fi AS=$ac_cv_prog_AS if test -n "$AS"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $AS" >&5 $as_echo "$AS" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi fi if test -z "$ac_cv_prog_AS"; then ac_ct_AS=$AS # Extract the first word of "as", so it can be a program name with args. set dummy as; ac_word=$2 { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $ac_word" >&5 $as_echo_n "checking for $ac_word... " >&6; } if ${ac_cv_prog_ac_ct_AS+:} false; then : $as_echo_n "(cached) " >&6 else if test -n "$ac_ct_AS"; then ac_cv_prog_ac_ct_AS="$ac_ct_AS" # Let the user override the test. else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_exec_ext in '' $ac_executable_extensions; do if as_fn_executable_p "$as_dir/$ac_word$ac_exec_ext"; then ac_cv_prog_ac_ct_AS="as" $as_echo "$as_me:${as_lineno-$LINENO}: found $as_dir/$ac_word$ac_exec_ext" >&5 break 2 fi done done IFS=$as_save_IFS fi fi ac_ct_AS=$ac_cv_prog_ac_ct_AS if test -n "$ac_ct_AS"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_ct_AS" >&5 $as_echo "$ac_ct_AS" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi if test "x$ac_ct_AS" = x; then AS="false" else case $cross_compiling:$ac_tool_warned in yes:) { $as_echo "$as_me:${as_lineno-$LINENO}: WARNING: using cross tools not prefixed with host triplet" >&5 $as_echo "$as_me: WARNING: using cross tools not prefixed with host triplet" >&2;} ac_tool_warned=yes ;; esac AS=$ac_ct_AS fi else AS="$ac_cv_prog_AS" fi if test -n "$ac_tool_prefix"; then # Extract the first word of "${ac_tool_prefix}dlltool", so it can be a program name with args. set dummy ${ac_tool_prefix}dlltool; ac_word=$2 { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $ac_word" >&5 $as_echo_n "checking for $ac_word... " >&6; } if ${ac_cv_prog_DLLTOOL+:} false; then : $as_echo_n "(cached) " >&6 else if test -n "$DLLTOOL"; then ac_cv_prog_DLLTOOL="$DLLTOOL" # Let the user override the test. else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_exec_ext in '' $ac_executable_extensions; do if as_fn_executable_p "$as_dir/$ac_word$ac_exec_ext"; then ac_cv_prog_DLLTOOL="${ac_tool_prefix}dlltool" $as_echo "$as_me:${as_lineno-$LINENO}: found $as_dir/$ac_word$ac_exec_ext" >&5 break 2 fi done done IFS=$as_save_IFS fi fi DLLTOOL=$ac_cv_prog_DLLTOOL if test -n "$DLLTOOL"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $DLLTOOL" >&5 $as_echo "$DLLTOOL" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi fi if test -z "$ac_cv_prog_DLLTOOL"; then ac_ct_DLLTOOL=$DLLTOOL # Extract the first word of "dlltool", so it can be a program name with args. set dummy dlltool; ac_word=$2 { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $ac_word" >&5 $as_echo_n "checking for $ac_word... " >&6; } if ${ac_cv_prog_ac_ct_DLLTOOL+:} false; then : $as_echo_n "(cached) " >&6 else if test -n "$ac_ct_DLLTOOL"; then ac_cv_prog_ac_ct_DLLTOOL="$ac_ct_DLLTOOL" # Let the user override the test. else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_exec_ext in '' $ac_executable_extensions; do if as_fn_executable_p "$as_dir/$ac_word$ac_exec_ext"; then ac_cv_prog_ac_ct_DLLTOOL="dlltool" $as_echo "$as_me:${as_lineno-$LINENO}: found $as_dir/$ac_word$ac_exec_ext" >&5 break 2 fi done done IFS=$as_save_IFS fi fi ac_ct_DLLTOOL=$ac_cv_prog_ac_ct_DLLTOOL if test -n "$ac_ct_DLLTOOL"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_ct_DLLTOOL" >&5 $as_echo "$ac_ct_DLLTOOL" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi if test "x$ac_ct_DLLTOOL" = x; then DLLTOOL="false" else case $cross_compiling:$ac_tool_warned in yes:) { $as_echo "$as_me:${as_lineno-$LINENO}: WARNING: using cross tools not prefixed with host triplet" >&5 $as_echo "$as_me: WARNING: using cross tools not prefixed with host triplet" >&2;} ac_tool_warned=yes ;; esac DLLTOOL=$ac_ct_DLLTOOL fi else DLLTOOL="$ac_cv_prog_DLLTOOL" fi if test -n "$ac_tool_prefix"; then # Extract the first word of "${ac_tool_prefix}objdump", so it can be a program name with args. set dummy ${ac_tool_prefix}objdump; ac_word=$2 { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $ac_word" >&5 $as_echo_n "checking for $ac_word... " >&6; } if ${ac_cv_prog_OBJDUMP+:} false; then : $as_echo_n "(cached) " >&6 else if test -n "$OBJDUMP"; then ac_cv_prog_OBJDUMP="$OBJDUMP" # Let the user override the test. else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_exec_ext in '' $ac_executable_extensions; do if as_fn_executable_p "$as_dir/$ac_word$ac_exec_ext"; then ac_cv_prog_OBJDUMP="${ac_tool_prefix}objdump" $as_echo "$as_me:${as_lineno-$LINENO}: found $as_dir/$ac_word$ac_exec_ext" >&5 break 2 fi done done IFS=$as_save_IFS fi fi OBJDUMP=$ac_cv_prog_OBJDUMP if test -n "$OBJDUMP"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $OBJDUMP" >&5 $as_echo "$OBJDUMP" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi fi if test -z "$ac_cv_prog_OBJDUMP"; then ac_ct_OBJDUMP=$OBJDUMP # Extract the first word of "objdump", so it can be a program name with args. set dummy objdump; ac_word=$2 { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $ac_word" >&5 $as_echo_n "checking for $ac_word... " >&6; } if ${ac_cv_prog_ac_ct_OBJDUMP+:} false; then : $as_echo_n "(cached) " >&6 else if test -n "$ac_ct_OBJDUMP"; then ac_cv_prog_ac_ct_OBJDUMP="$ac_ct_OBJDUMP" # Let the user override the test. else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_exec_ext in '' $ac_executable_extensions; do if as_fn_executable_p "$as_dir/$ac_word$ac_exec_ext"; then ac_cv_prog_ac_ct_OBJDUMP="objdump" $as_echo "$as_me:${as_lineno-$LINENO}: found $as_dir/$ac_word$ac_exec_ext" >&5 break 2 fi done done IFS=$as_save_IFS fi fi ac_ct_OBJDUMP=$ac_cv_prog_ac_ct_OBJDUMP if test -n "$ac_ct_OBJDUMP"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_ct_OBJDUMP" >&5 $as_echo "$ac_ct_OBJDUMP" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi if test "x$ac_ct_OBJDUMP" = x; then OBJDUMP="false" else case $cross_compiling:$ac_tool_warned in yes:) { $as_echo "$as_me:${as_lineno-$LINENO}: WARNING: using cross tools not prefixed with host triplet" >&5 $as_echo "$as_me: WARNING: using cross tools not prefixed with host triplet" >&2;} ac_tool_warned=yes ;; esac OBJDUMP=$ac_ct_OBJDUMP fi else OBJDUMP="$ac_cv_prog_OBJDUMP" fi ;; esac test -z "$AS" && AS=as test -z "$DLLTOOL" && DLLTOOL=dlltool test -z "$OBJDUMP" && OBJDUMP=objdump case `pwd` in *\ * | *\ *) { $as_echo "$as_me:${as_lineno-$LINENO}: WARNING: Libtool does not cope well with whitespace in \`pwd\`" >&5 $as_echo "$as_me: WARNING: Libtool does not cope well with whitespace in \`pwd\`" >&2;} ;; esac macro_version='2.4.2' macro_revision='1.3337' ltmain="$ac_aux_dir/ltmain.sh" # Backslashify metacharacters that are still active within # double-quoted strings. sed_quote_subst='s/\(["`$\\]\)/\\\1/g' # Same as above, but do not quote variable references. double_quote_subst='s/\(["`\\]\)/\\\1/g' # Sed substitution to delay expansion of an escaped shell variable in a # double_quote_subst'ed string. delay_variable_subst='s/\\\\\\\\\\\$/\\\\\\$/g' # Sed substitution to delay expansion of an escaped single quote. delay_single_quote_subst='s/'\''/'\'\\\\\\\'\''/g' # Sed substitution to avoid accidental globbing in evaled expressions no_glob_subst='s/\*/\\\*/g' ECHO='\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\' ECHO=$ECHO$ECHO$ECHO$ECHO$ECHO ECHO=$ECHO$ECHO$ECHO$ECHO$ECHO$ECHO { $as_echo "$as_me:${as_lineno-$LINENO}: checking how to print strings" >&5 $as_echo_n "checking how to print strings... " >&6; } # Test print first, because it will be a builtin if present. if test "X`( print -r -- -n ) 2>/dev/null`" = X-n && \ test "X`print -r -- $ECHO 2>/dev/null`" = "X$ECHO"; then ECHO='print -r --' elif test "X`printf %s $ECHO 2>/dev/null`" = "X$ECHO"; then ECHO='printf %s\n' else # Use this function as a fallback that always works. func_fallback_echo () { eval 'cat <<_LTECHO_EOF $1 _LTECHO_EOF' } ECHO='func_fallback_echo' fi # func_echo_all arg... # Invoke $ECHO with all args, space-separated. func_echo_all () { $ECHO "" } case "$ECHO" in printf*) { $as_echo "$as_me:${as_lineno-$LINENO}: result: printf" >&5 $as_echo "printf" >&6; } ;; print*) { $as_echo "$as_me:${as_lineno-$LINENO}: result: print -r" >&5 $as_echo "print -r" >&6; } ;; *) { $as_echo "$as_me:${as_lineno-$LINENO}: result: cat" >&5 $as_echo "cat" >&6; } ;; esac DEPDIR="${am__leading_dot}deps" ac_config_commands="$ac_config_commands depfiles" am_make=${MAKE-make} cat > confinc << 'END' am__doit: @echo this is the am__doit target .PHONY: am__doit END # If we don't find an include directive, just comment out the code. { $as_echo "$as_me:${as_lineno-$LINENO}: checking for style of include used by $am_make" >&5 $as_echo_n "checking for style of include used by $am_make... " >&6; } am__include="#" am__quote= _am_result=none # First try GNU make style include. echo "include confinc" > confmf # Ignore all kinds of additional output from `make'. case `$am_make -s -f confmf 2> /dev/null` in #( *the\ am__doit\ target*) am__include=include am__quote= _am_result=GNU ;; esac # Now try BSD make style include. if test "$am__include" = "#"; then echo '.include "confinc"' > confmf case `$am_make -s -f confmf 2> /dev/null` in #( *the\ am__doit\ target*) am__include=.include am__quote="\"" _am_result=BSD ;; esac fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $_am_result" >&5 $as_echo "$_am_result" >&6; } rm -f confinc confmf # Check whether --enable-dependency-tracking was given. if test "${enable_dependency_tracking+set}" = set; then : enableval=$enable_dependency_tracking; fi if test "x$enable_dependency_tracking" != xno; then am_depcomp="$ac_aux_dir/depcomp" AMDEPBACKSLASH='\' am__nodep='_no' fi if test "x$enable_dependency_tracking" != xno; then AMDEP_TRUE= AMDEP_FALSE='#' else AMDEP_TRUE='#' AMDEP_FALSE= fi ac_ext=c ac_cpp='$CPP $CPPFLAGS' ac_compile='$CC -c $CFLAGS $CPPFLAGS conftest.$ac_ext >&5' ac_link='$CC -o conftest$ac_exeext $CFLAGS $CPPFLAGS $LDFLAGS conftest.$ac_ext $LIBS >&5' ac_compiler_gnu=$ac_cv_c_compiler_gnu if test -n "$ac_tool_prefix"; then # Extract the first word of "${ac_tool_prefix}gcc", so it can be a program name with args. set dummy ${ac_tool_prefix}gcc; ac_word=$2 { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $ac_word" >&5 $as_echo_n "checking for $ac_word... " >&6; } if ${ac_cv_prog_CC+:} false; then : $as_echo_n "(cached) " >&6 else if test -n "$CC"; then ac_cv_prog_CC="$CC" # Let the user override the test. else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_exec_ext in '' $ac_executable_extensions; do if as_fn_executable_p "$as_dir/$ac_word$ac_exec_ext"; then ac_cv_prog_CC="${ac_tool_prefix}gcc" $as_echo "$as_me:${as_lineno-$LINENO}: found $as_dir/$ac_word$ac_exec_ext" >&5 break 2 fi done done IFS=$as_save_IFS fi fi CC=$ac_cv_prog_CC if test -n "$CC"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $CC" >&5 $as_echo "$CC" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi fi if test -z "$ac_cv_prog_CC"; then ac_ct_CC=$CC # Extract the first word of "gcc", so it can be a program name with args. set dummy gcc; ac_word=$2 { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $ac_word" >&5 $as_echo_n "checking for $ac_word... " >&6; } if ${ac_cv_prog_ac_ct_CC+:} false; then : $as_echo_n "(cached) " >&6 else if test -n "$ac_ct_CC"; then ac_cv_prog_ac_ct_CC="$ac_ct_CC" # Let the user override the test. else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_exec_ext in '' $ac_executable_extensions; do if as_fn_executable_p "$as_dir/$ac_word$ac_exec_ext"; then ac_cv_prog_ac_ct_CC="gcc" $as_echo "$as_me:${as_lineno-$LINENO}: found $as_dir/$ac_word$ac_exec_ext" >&5 break 2 fi done done IFS=$as_save_IFS fi fi ac_ct_CC=$ac_cv_prog_ac_ct_CC if test -n "$ac_ct_CC"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_ct_CC" >&5 $as_echo "$ac_ct_CC" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi if test "x$ac_ct_CC" = x; then CC="" else case $cross_compiling:$ac_tool_warned in yes:) { $as_echo "$as_me:${as_lineno-$LINENO}: WARNING: using cross tools not prefixed with host triplet" >&5 $as_echo "$as_me: WARNING: using cross tools not prefixed with host triplet" >&2;} ac_tool_warned=yes ;; esac CC=$ac_ct_CC fi else CC="$ac_cv_prog_CC" fi if test -z "$CC"; then if test -n "$ac_tool_prefix"; then # Extract the first word of "${ac_tool_prefix}cc", so it can be a program name with args. set dummy ${ac_tool_prefix}cc; ac_word=$2 { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $ac_word" >&5 $as_echo_n "checking for $ac_word... " >&6; } if ${ac_cv_prog_CC+:} false; then : $as_echo_n "(cached) " >&6 else if test -n "$CC"; then ac_cv_prog_CC="$CC" # Let the user override the test. else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_exec_ext in '' $ac_executable_extensions; do if as_fn_executable_p "$as_dir/$ac_word$ac_exec_ext"; then ac_cv_prog_CC="${ac_tool_prefix}cc" $as_echo "$as_me:${as_lineno-$LINENO}: found $as_dir/$ac_word$ac_exec_ext" >&5 break 2 fi done done IFS=$as_save_IFS fi fi CC=$ac_cv_prog_CC if test -n "$CC"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $CC" >&5 $as_echo "$CC" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi fi fi if test -z "$CC"; then # Extract the first word of "cc", so it can be a program name with args. set dummy cc; ac_word=$2 { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $ac_word" >&5 $as_echo_n "checking for $ac_word... " >&6; } if ${ac_cv_prog_CC+:} false; then : $as_echo_n "(cached) " >&6 else if test -n "$CC"; then ac_cv_prog_CC="$CC" # Let the user override the test. else ac_prog_rejected=no as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_exec_ext in '' $ac_executable_extensions; do if as_fn_executable_p "$as_dir/$ac_word$ac_exec_ext"; then if test "$as_dir/$ac_word$ac_exec_ext" = "/usr/ucb/cc"; then ac_prog_rejected=yes continue fi ac_cv_prog_CC="cc" $as_echo "$as_me:${as_lineno-$LINENO}: found $as_dir/$ac_word$ac_exec_ext" >&5 break 2 fi done done IFS=$as_save_IFS if test $ac_prog_rejected = yes; then # We found a bogon in the path, so make sure we never use it. set dummy $ac_cv_prog_CC shift if test $# != 0; then # We chose a different compiler from the bogus one. # However, it has the same basename, so the bogon will be chosen # first if we set CC to just the basename; use the full file name. shift ac_cv_prog_CC="$as_dir/$ac_word${1+' '}$@" fi fi fi fi CC=$ac_cv_prog_CC if test -n "$CC"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $CC" >&5 $as_echo "$CC" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi fi if test -z "$CC"; then if test -n "$ac_tool_prefix"; then for ac_prog in cl.exe do # Extract the first word of "$ac_tool_prefix$ac_prog", so it can be a program name with args. set dummy $ac_tool_prefix$ac_prog; ac_word=$2 { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $ac_word" >&5 $as_echo_n "checking for $ac_word... " >&6; } if ${ac_cv_prog_CC+:} false; then : $as_echo_n "(cached) " >&6 else if test -n "$CC"; then ac_cv_prog_CC="$CC" # Let the user override the test. else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_exec_ext in '' $ac_executable_extensions; do if as_fn_executable_p "$as_dir/$ac_word$ac_exec_ext"; then ac_cv_prog_CC="$ac_tool_prefix$ac_prog" $as_echo "$as_me:${as_lineno-$LINENO}: found $as_dir/$ac_word$ac_exec_ext" >&5 break 2 fi done done IFS=$as_save_IFS fi fi CC=$ac_cv_prog_CC if test -n "$CC"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $CC" >&5 $as_echo "$CC" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi test -n "$CC" && break done fi if test -z "$CC"; then ac_ct_CC=$CC for ac_prog in cl.exe do # Extract the first word of "$ac_prog", so it can be a program name with args. set dummy $ac_prog; ac_word=$2 { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $ac_word" >&5 $as_echo_n "checking for $ac_word... " >&6; } if ${ac_cv_prog_ac_ct_CC+:} false; then : $as_echo_n "(cached) " >&6 else if test -n "$ac_ct_CC"; then ac_cv_prog_ac_ct_CC="$ac_ct_CC" # Let the user override the test. else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_exec_ext in '' $ac_executable_extensions; do if as_fn_executable_p "$as_dir/$ac_word$ac_exec_ext"; then ac_cv_prog_ac_ct_CC="$ac_prog" $as_echo "$as_me:${as_lineno-$LINENO}: found $as_dir/$ac_word$ac_exec_ext" >&5 break 2 fi done done IFS=$as_save_IFS fi fi ac_ct_CC=$ac_cv_prog_ac_ct_CC if test -n "$ac_ct_CC"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_ct_CC" >&5 $as_echo "$ac_ct_CC" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi test -n "$ac_ct_CC" && break done if test "x$ac_ct_CC" = x; then CC="" else case $cross_compiling:$ac_tool_warned in yes:) { $as_echo "$as_me:${as_lineno-$LINENO}: WARNING: using cross tools not prefixed with host triplet" >&5 $as_echo "$as_me: WARNING: using cross tools not prefixed with host triplet" >&2;} ac_tool_warned=yes ;; esac CC=$ac_ct_CC fi fi fi test -z "$CC" && { { $as_echo "$as_me:${as_lineno-$LINENO}: error: in \`$ac_pwd':" >&5 $as_echo "$as_me: error: in \`$ac_pwd':" >&2;} as_fn_error $? "no acceptable C compiler found in \$PATH See \`config.log' for more details" "$LINENO" 5; } # Provide some information about the compiler. $as_echo "$as_me:${as_lineno-$LINENO}: checking for C compiler version" >&5 set X $ac_compile ac_compiler=$2 for ac_option in --version -v -V -qversion; do { { ac_try="$ac_compiler $ac_option >&5" case "(($ac_try" in *\"* | *\`* | *\\*) ac_try_echo=\$ac_try;; *) ac_try_echo=$ac_try;; esac eval ac_try_echo="\"\$as_me:${as_lineno-$LINENO}: $ac_try_echo\"" $as_echo "$ac_try_echo"; } >&5 (eval "$ac_compiler $ac_option >&5") 2>conftest.err ac_status=$? if test -s conftest.err; then sed '10a\ ... rest of stderr output deleted ... 10q' conftest.err >conftest.er1 cat conftest.er1 >&5 fi rm -f conftest.er1 conftest.err $as_echo "$as_me:${as_lineno-$LINENO}: \$? = $ac_status" >&5 test $ac_status = 0; } done cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ int main () { ; return 0; } _ACEOF ac_clean_files_save=$ac_clean_files ac_clean_files="$ac_clean_files a.out a.out.dSYM a.exe b.out" # Try to create an executable without -o first, disregard a.out. # It will help us diagnose broken compilers, and finding out an intuition # of exeext. { $as_echo "$as_me:${as_lineno-$LINENO}: checking whether the C compiler works" >&5 $as_echo_n "checking whether the C compiler works... " >&6; } ac_link_default=`$as_echo "$ac_link" | sed 's/ -o *conftest[^ ]*//'` # The possible output files: ac_files="a.out conftest.exe conftest a.exe a_out.exe b.out conftest.*" ac_rmfiles= for ac_file in $ac_files do case $ac_file in *.$ac_ext | *.xcoff | *.tds | *.d | *.pdb | *.xSYM | *.bb | *.bbg | *.map | *.inf | *.dSYM | *.o | *.obj ) ;; * ) ac_rmfiles="$ac_rmfiles $ac_file";; esac done rm -f $ac_rmfiles if { { ac_try="$ac_link_default" case "(($ac_try" in *\"* | *\`* | *\\*) ac_try_echo=\$ac_try;; *) ac_try_echo=$ac_try;; esac eval ac_try_echo="\"\$as_me:${as_lineno-$LINENO}: $ac_try_echo\"" $as_echo "$ac_try_echo"; } >&5 (eval "$ac_link_default") 2>&5 ac_status=$? $as_echo "$as_me:${as_lineno-$LINENO}: \$? = $ac_status" >&5 test $ac_status = 0; }; then : # Autoconf-2.13 could set the ac_cv_exeext variable to `no'. # So ignore a value of `no', otherwise this would lead to `EXEEXT = no' # in a Makefile. We should not override ac_cv_exeext if it was cached, # so that the user can short-circuit this test for compilers unknown to # Autoconf. for ac_file in $ac_files '' do test -f "$ac_file" || continue case $ac_file in *.$ac_ext | *.xcoff | *.tds | *.d | *.pdb | *.xSYM | *.bb | *.bbg | *.map | *.inf | *.dSYM | *.o | *.obj ) ;; [ab].out ) # We found the default executable, but exeext='' is most # certainly right. break;; *.* ) if test "${ac_cv_exeext+set}" = set && test "$ac_cv_exeext" != no; then :; else ac_cv_exeext=`expr "$ac_file" : '[^.]*\(\..*\)'` fi # We set ac_cv_exeext here because the later test for it is not # safe: cross compilers may not add the suffix if given an `-o' # argument, so we may need to know it at that point already. # Even if this section looks crufty: it has the advantage of # actually working. break;; * ) break;; esac done test "$ac_cv_exeext" = no && ac_cv_exeext= else ac_file='' fi if test -z "$ac_file"; then : { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } $as_echo "$as_me: failed program was:" >&5 sed 's/^/| /' conftest.$ac_ext >&5 { { $as_echo "$as_me:${as_lineno-$LINENO}: error: in \`$ac_pwd':" >&5 $as_echo "$as_me: error: in \`$ac_pwd':" >&2;} as_fn_error 77 "C compiler cannot create executables See \`config.log' for more details" "$LINENO" 5; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: yes" >&5 $as_echo "yes" >&6; } fi { $as_echo "$as_me:${as_lineno-$LINENO}: checking for C compiler default output file name" >&5 $as_echo_n "checking for C compiler default output file name... " >&6; } { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_file" >&5 $as_echo "$ac_file" >&6; } ac_exeext=$ac_cv_exeext rm -f -r a.out a.out.dSYM a.exe conftest$ac_cv_exeext b.out ac_clean_files=$ac_clean_files_save { $as_echo "$as_me:${as_lineno-$LINENO}: checking for suffix of executables" >&5 $as_echo_n "checking for suffix of executables... " >&6; } if { { ac_try="$ac_link" case "(($ac_try" in *\"* | *\`* | *\\*) ac_try_echo=\$ac_try;; *) ac_try_echo=$ac_try;; esac eval ac_try_echo="\"\$as_me:${as_lineno-$LINENO}: $ac_try_echo\"" $as_echo "$ac_try_echo"; } >&5 (eval "$ac_link") 2>&5 ac_status=$? $as_echo "$as_me:${as_lineno-$LINENO}: \$? = $ac_status" >&5 test $ac_status = 0; }; then : # If both `conftest.exe' and `conftest' are `present' (well, observable) # catch `conftest.exe'. For instance with Cygwin, `ls conftest' will # work properly (i.e., refer to `conftest.exe'), while it won't with # `rm'. for ac_file in conftest.exe conftest conftest.*; do test -f "$ac_file" || continue case $ac_file in *.$ac_ext | *.xcoff | *.tds | *.d | *.pdb | *.xSYM | *.bb | *.bbg | *.map | *.inf | *.dSYM | *.o | *.obj ) ;; *.* ) ac_cv_exeext=`expr "$ac_file" : '[^.]*\(\..*\)'` break;; * ) break;; esac done else { { $as_echo "$as_me:${as_lineno-$LINENO}: error: in \`$ac_pwd':" >&5 $as_echo "$as_me: error: in \`$ac_pwd':" >&2;} as_fn_error $? "cannot compute suffix of executables: cannot compile and link See \`config.log' for more details" "$LINENO" 5; } fi rm -f conftest conftest$ac_cv_exeext { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_cv_exeext" >&5 $as_echo "$ac_cv_exeext" >&6; } rm -f conftest.$ac_ext EXEEXT=$ac_cv_exeext ac_exeext=$EXEEXT cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ #include int main () { FILE *f = fopen ("conftest.out", "w"); return ferror (f) || fclose (f) != 0; ; return 0; } _ACEOF ac_clean_files="$ac_clean_files conftest.out" # Check that the compiler produces executables we can run. If not, either # the compiler is broken, or we cross compile. { $as_echo "$as_me:${as_lineno-$LINENO}: checking whether we are cross compiling" >&5 $as_echo_n "checking whether we are cross compiling... " >&6; } if test "$cross_compiling" != yes; then { { ac_try="$ac_link" case "(($ac_try" in *\"* | *\`* | *\\*) ac_try_echo=\$ac_try;; *) ac_try_echo=$ac_try;; esac eval ac_try_echo="\"\$as_me:${as_lineno-$LINENO}: $ac_try_echo\"" $as_echo "$ac_try_echo"; } >&5 (eval "$ac_link") 2>&5 ac_status=$? $as_echo "$as_me:${as_lineno-$LINENO}: \$? = $ac_status" >&5 test $ac_status = 0; } if { ac_try='./conftest$ac_cv_exeext' { { case "(($ac_try" in *\"* | *\`* | *\\*) ac_try_echo=\$ac_try;; *) ac_try_echo=$ac_try;; esac eval ac_try_echo="\"\$as_me:${as_lineno-$LINENO}: $ac_try_echo\"" $as_echo "$ac_try_echo"; } >&5 (eval "$ac_try") 2>&5 ac_status=$? $as_echo "$as_me:${as_lineno-$LINENO}: \$? = $ac_status" >&5 test $ac_status = 0; }; }; then cross_compiling=no else if test "$cross_compiling" = maybe; then cross_compiling=yes else { { $as_echo "$as_me:${as_lineno-$LINENO}: error: in \`$ac_pwd':" >&5 $as_echo "$as_me: error: in \`$ac_pwd':" >&2;} as_fn_error $? "cannot run C compiled programs. If you meant to cross compile, use \`--host'. See \`config.log' for more details" "$LINENO" 5; } fi fi fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $cross_compiling" >&5 $as_echo "$cross_compiling" >&6; } rm -f conftest.$ac_ext conftest$ac_cv_exeext conftest.out ac_clean_files=$ac_clean_files_save { $as_echo "$as_me:${as_lineno-$LINENO}: checking for suffix of object files" >&5 $as_echo_n "checking for suffix of object files... " >&6; } if ${ac_cv_objext+:} false; then : $as_echo_n "(cached) " >&6 else cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ int main () { ; return 0; } _ACEOF rm -f conftest.o conftest.obj if { { ac_try="$ac_compile" case "(($ac_try" in *\"* | *\`* | *\\*) ac_try_echo=\$ac_try;; *) ac_try_echo=$ac_try;; esac eval ac_try_echo="\"\$as_me:${as_lineno-$LINENO}: $ac_try_echo\"" $as_echo "$ac_try_echo"; } >&5 (eval "$ac_compile") 2>&5 ac_status=$? $as_echo "$as_me:${as_lineno-$LINENO}: \$? = $ac_status" >&5 test $ac_status = 0; }; then : for ac_file in conftest.o conftest.obj conftest.*; do test -f "$ac_file" || continue; case $ac_file in *.$ac_ext | *.xcoff | *.tds | *.d | *.pdb | *.xSYM | *.bb | *.bbg | *.map | *.inf | *.dSYM ) ;; *) ac_cv_objext=`expr "$ac_file" : '.*\.\(.*\)'` break;; esac done else $as_echo "$as_me: failed program was:" >&5 sed 's/^/| /' conftest.$ac_ext >&5 { { $as_echo "$as_me:${as_lineno-$LINENO}: error: in \`$ac_pwd':" >&5 $as_echo "$as_me: error: in \`$ac_pwd':" >&2;} as_fn_error $? "cannot compute suffix of object files: cannot compile See \`config.log' for more details" "$LINENO" 5; } fi rm -f conftest.$ac_cv_objext conftest.$ac_ext fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_cv_objext" >&5 $as_echo "$ac_cv_objext" >&6; } OBJEXT=$ac_cv_objext ac_objext=$OBJEXT { $as_echo "$as_me:${as_lineno-$LINENO}: checking whether we are using the GNU C compiler" >&5 $as_echo_n "checking whether we are using the GNU C compiler... " >&6; } if ${ac_cv_c_compiler_gnu+:} false; then : $as_echo_n "(cached) " >&6 else cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ int main () { #ifndef __GNUC__ choke me #endif ; return 0; } _ACEOF if ac_fn_c_try_compile "$LINENO"; then : ac_compiler_gnu=yes else ac_compiler_gnu=no fi rm -f core conftest.err conftest.$ac_objext conftest.$ac_ext ac_cv_c_compiler_gnu=$ac_compiler_gnu fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_cv_c_compiler_gnu" >&5 $as_echo "$ac_cv_c_compiler_gnu" >&6; } if test $ac_compiler_gnu = yes; then GCC=yes else GCC= fi ac_test_CFLAGS=${CFLAGS+set} ac_save_CFLAGS=$CFLAGS { $as_echo "$as_me:${as_lineno-$LINENO}: checking whether $CC accepts -g" >&5 $as_echo_n "checking whether $CC accepts -g... " >&6; } if ${ac_cv_prog_cc_g+:} false; then : $as_echo_n "(cached) " >&6 else ac_save_c_werror_flag=$ac_c_werror_flag ac_c_werror_flag=yes ac_cv_prog_cc_g=no CFLAGS="-g" cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ int main () { ; return 0; } _ACEOF if ac_fn_c_try_compile "$LINENO"; then : ac_cv_prog_cc_g=yes else CFLAGS="" cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ int main () { ; return 0; } _ACEOF if ac_fn_c_try_compile "$LINENO"; then : else ac_c_werror_flag=$ac_save_c_werror_flag CFLAGS="-g" cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ int main () { ; return 0; } _ACEOF if ac_fn_c_try_compile "$LINENO"; then : ac_cv_prog_cc_g=yes fi rm -f core conftest.err conftest.$ac_objext conftest.$ac_ext fi rm -f core conftest.err conftest.$ac_objext conftest.$ac_ext fi rm -f core conftest.err conftest.$ac_objext conftest.$ac_ext ac_c_werror_flag=$ac_save_c_werror_flag fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_cv_prog_cc_g" >&5 $as_echo "$ac_cv_prog_cc_g" >&6; } if test "$ac_test_CFLAGS" = set; then CFLAGS=$ac_save_CFLAGS elif test $ac_cv_prog_cc_g = yes; then if test "$GCC" = yes; then CFLAGS="-g -O2" else CFLAGS="-g" fi else if test "$GCC" = yes; then CFLAGS="-O2" else CFLAGS= fi fi { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $CC option to accept ISO C89" >&5 $as_echo_n "checking for $CC option to accept ISO C89... " >&6; } if ${ac_cv_prog_cc_c89+:} false; then : $as_echo_n "(cached) " >&6 else ac_cv_prog_cc_c89=no ac_save_CC=$CC cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ #include #include struct stat; /* Most of the following tests are stolen from RCS 5.7's src/conf.sh. */ struct buf { int x; }; FILE * (*rcsopen) (struct buf *, struct stat *, int); static char *e (p, i) char **p; int i; { return p[i]; } static char *f (char * (*g) (char **, int), char **p, ...) { char *s; va_list v; va_start (v,p); s = g (p, va_arg (v,int)); va_end (v); return s; } /* OSF 4.0 Compaq cc is some sort of almost-ANSI by default. It has function prototypes and stuff, but not '\xHH' hex character constants. These don't provoke an error unfortunately, instead are silently treated as 'x'. The following induces an error, until -std is added to get proper ANSI mode. Curiously '\x00'!='x' always comes out true, for an array size at least. It's necessary to write '\x00'==0 to get something that's true only with -std. */ int osf4_cc_array ['\x00' == 0 ? 1 : -1]; /* IBM C 6 for AIX is almost-ANSI by default, but it replaces macro parameters inside strings and character constants. */ #define FOO(x) 'x' int xlc6_cc_array[FOO(a) == 'x' ? 1 : -1]; int test (int i, double x); struct s1 {int (*f) (int a);}; struct s2 {int (*f) (double a);}; int pairnames (int, char **, FILE *(*)(struct buf *, struct stat *, int), int, int); int argc; char **argv; int main () { return f (e, argv, 0) != argv[0] || f (e, argv, 1) != argv[1]; ; return 0; } _ACEOF for ac_arg in '' -qlanglvl=extc89 -qlanglvl=ansi -std \ -Ae "-Aa -D_HPUX_SOURCE" "-Xc -D__EXTENSIONS__" do CC="$ac_save_CC $ac_arg" if ac_fn_c_try_compile "$LINENO"; then : ac_cv_prog_cc_c89=$ac_arg fi rm -f core conftest.err conftest.$ac_objext test "x$ac_cv_prog_cc_c89" != "xno" && break done rm -f conftest.$ac_ext CC=$ac_save_CC fi # AC_CACHE_VAL case "x$ac_cv_prog_cc_c89" in x) { $as_echo "$as_me:${as_lineno-$LINENO}: result: none needed" >&5 $as_echo "none needed" >&6; } ;; xno) { $as_echo "$as_me:${as_lineno-$LINENO}: result: unsupported" >&5 $as_echo "unsupported" >&6; } ;; *) CC="$CC $ac_cv_prog_cc_c89" { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_cv_prog_cc_c89" >&5 $as_echo "$ac_cv_prog_cc_c89" >&6; } ;; esac if test "x$ac_cv_prog_cc_c89" != xno; then : fi ac_ext=c ac_cpp='$CPP $CPPFLAGS' ac_compile='$CC -c $CFLAGS $CPPFLAGS conftest.$ac_ext >&5' ac_link='$CC -o conftest$ac_exeext $CFLAGS $CPPFLAGS $LDFLAGS conftest.$ac_ext $LIBS >&5' ac_compiler_gnu=$ac_cv_c_compiler_gnu depcc="$CC" am_compiler_list= { $as_echo "$as_me:${as_lineno-$LINENO}: checking dependency style of $depcc" >&5 $as_echo_n "checking dependency style of $depcc... " >&6; } if ${am_cv_CC_dependencies_compiler_type+:} false; then : $as_echo_n "(cached) " >&6 else if test -z "$AMDEP_TRUE" && test -f "$am_depcomp"; then # We make a subdir and do the tests there. Otherwise we can end up # making bogus files that we don't know about and never remove. For # instance it was reported that on HP-UX the gcc test will end up # making a dummy file named `D' -- because `-MD' means `put the output # in D'. rm -rf conftest.dir mkdir conftest.dir # Copy depcomp to subdir because otherwise we won't find it if we're # using a relative directory. cp "$am_depcomp" conftest.dir cd conftest.dir # We will build objects and dependencies in a subdirectory because # it helps to detect inapplicable dependency modes. For instance # both Tru64's cc and ICC support -MD to output dependencies as a # side effect of compilation, but ICC will put the dependencies in # the current directory while Tru64 will put them in the object # directory. mkdir sub am_cv_CC_dependencies_compiler_type=none if test "$am_compiler_list" = ""; then am_compiler_list=`sed -n 's/^#*\([a-zA-Z0-9]*\))$/\1/p' < ./depcomp` fi am__universal=false case " $depcc " in #( *\ -arch\ *\ -arch\ *) am__universal=true ;; esac for depmode in $am_compiler_list; do # Setup a source with many dependencies, because some compilers # like to wrap large dependency lists on column 80 (with \), and # we should not choose a depcomp mode which is confused by this. # # We need to recreate these files for each test, as the compiler may # overwrite some of them when testing with obscure command lines. # This happens at least with the AIX C compiler. : > sub/conftest.c for i in 1 2 3 4 5 6; do echo '#include "conftst'$i'.h"' >> sub/conftest.c # Using `: > sub/conftst$i.h' creates only sub/conftst1.h with # Solaris 8's {/usr,}/bin/sh. touch sub/conftst$i.h done echo "${am__include} ${am__quote}sub/conftest.Po${am__quote}" > confmf # We check with `-c' and `-o' for the sake of the "dashmstdout" # mode. It turns out that the SunPro C++ compiler does not properly # handle `-M -o', and we need to detect this. Also, some Intel # versions had trouble with output in subdirs am__obj=sub/conftest.${OBJEXT-o} am__minus_obj="-o $am__obj" case $depmode in gcc) # This depmode causes a compiler race in universal mode. test "$am__universal" = false || continue ;; nosideeffect) # after this tag, mechanisms are not by side-effect, so they'll # only be used when explicitly requested if test "x$enable_dependency_tracking" = xyes; then continue else break fi ;; msvc7 | msvc7msys | msvisualcpp | msvcmsys) # This compiler won't grok `-c -o', but also, the minuso test has # not run yet. These depmodes are late enough in the game, and # so weak that their functioning should not be impacted. am__obj=conftest.${OBJEXT-o} am__minus_obj= ;; none) break ;; esac if depmode=$depmode \ source=sub/conftest.c object=$am__obj \ depfile=sub/conftest.Po tmpdepfile=sub/conftest.TPo \ $SHELL ./depcomp $depcc -c $am__minus_obj sub/conftest.c \ >/dev/null 2>conftest.err && grep sub/conftst1.h sub/conftest.Po > /dev/null 2>&1 && grep sub/conftst6.h sub/conftest.Po > /dev/null 2>&1 && grep $am__obj sub/conftest.Po > /dev/null 2>&1 && ${MAKE-make} -s -f confmf > /dev/null 2>&1; then # icc doesn't choke on unknown options, it will just issue warnings # or remarks (even with -Werror). So we grep stderr for any message # that says an option was ignored or not supported. # When given -MP, icc 7.0 and 7.1 complain thusly: # icc: Command line warning: ignoring option '-M'; no argument required # The diagnosis changed in icc 8.0: # icc: Command line remark: option '-MP' not supported if (grep 'ignoring option' conftest.err || grep 'not supported' conftest.err) >/dev/null 2>&1; then :; else am_cv_CC_dependencies_compiler_type=$depmode break fi fi done cd .. rm -rf conftest.dir else am_cv_CC_dependencies_compiler_type=none fi fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $am_cv_CC_dependencies_compiler_type" >&5 $as_echo "$am_cv_CC_dependencies_compiler_type" >&6; } CCDEPMODE=depmode=$am_cv_CC_dependencies_compiler_type if test "x$enable_dependency_tracking" != xno \ && test "$am_cv_CC_dependencies_compiler_type" = gcc3; then am__fastdepCC_TRUE= am__fastdepCC_FALSE='#' else am__fastdepCC_TRUE='#' am__fastdepCC_FALSE= fi { $as_echo "$as_me:${as_lineno-$LINENO}: checking for a sed that does not truncate output" >&5 $as_echo_n "checking for a sed that does not truncate output... " >&6; } if ${ac_cv_path_SED+:} false; then : $as_echo_n "(cached) " >&6 else ac_script=s/aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa/bbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbb/ for ac_i in 1 2 3 4 5 6 7; do ac_script="$ac_script$as_nl$ac_script" done echo "$ac_script" 2>/dev/null | sed 99q >conftest.sed { ac_script=; unset ac_script;} if test -z "$SED"; then ac_path_SED_found=false # Loop through the user's path and test for each of PROGNAME-LIST as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_prog in sed gsed; do for ac_exec_ext in '' $ac_executable_extensions; do ac_path_SED="$as_dir/$ac_prog$ac_exec_ext" as_fn_executable_p "$ac_path_SED" || continue # Check for GNU ac_path_SED and select it if it is found. # Check for GNU $ac_path_SED case `"$ac_path_SED" --version 2>&1` in *GNU*) ac_cv_path_SED="$ac_path_SED" ac_path_SED_found=:;; *) ac_count=0 $as_echo_n 0123456789 >"conftest.in" while : do cat "conftest.in" "conftest.in" >"conftest.tmp" mv "conftest.tmp" "conftest.in" cp "conftest.in" "conftest.nl" $as_echo '' >> "conftest.nl" "$ac_path_SED" -f conftest.sed < "conftest.nl" >"conftest.out" 2>/dev/null || break diff "conftest.out" "conftest.nl" >/dev/null 2>&1 || break as_fn_arith $ac_count + 1 && ac_count=$as_val if test $ac_count -gt ${ac_path_SED_max-0}; then # Best one so far, save it but keep looking for a better one ac_cv_path_SED="$ac_path_SED" ac_path_SED_max=$ac_count fi # 10*(2^10) chars as input seems more than enough test $ac_count -gt 10 && break done rm -f conftest.in conftest.tmp conftest.nl conftest.out;; esac $ac_path_SED_found && break 3 done done done IFS=$as_save_IFS if test -z "$ac_cv_path_SED"; then as_fn_error $? "no acceptable sed could be found in \$PATH" "$LINENO" 5 fi else ac_cv_path_SED=$SED fi fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_cv_path_SED" >&5 $as_echo "$ac_cv_path_SED" >&6; } SED="$ac_cv_path_SED" rm -f conftest.sed test -z "$SED" && SED=sed Xsed="$SED -e 1s/^X//" { $as_echo "$as_me:${as_lineno-$LINENO}: checking for grep that handles long lines and -e" >&5 $as_echo_n "checking for grep that handles long lines and -e... " >&6; } if ${ac_cv_path_GREP+:} false; then : $as_echo_n "(cached) " >&6 else if test -z "$GREP"; then ac_path_GREP_found=false # Loop through the user's path and test for each of PROGNAME-LIST as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH$PATH_SEPARATOR/usr/xpg4/bin do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_prog in grep ggrep; do for ac_exec_ext in '' $ac_executable_extensions; do ac_path_GREP="$as_dir/$ac_prog$ac_exec_ext" as_fn_executable_p "$ac_path_GREP" || continue # Check for GNU ac_path_GREP and select it if it is found. # Check for GNU $ac_path_GREP case `"$ac_path_GREP" --version 2>&1` in *GNU*) ac_cv_path_GREP="$ac_path_GREP" ac_path_GREP_found=:;; *) ac_count=0 $as_echo_n 0123456789 >"conftest.in" while : do cat "conftest.in" "conftest.in" >"conftest.tmp" mv "conftest.tmp" "conftest.in" cp "conftest.in" "conftest.nl" $as_echo 'GREP' >> "conftest.nl" "$ac_path_GREP" -e 'GREP$' -e '-(cannot match)-' < "conftest.nl" >"conftest.out" 2>/dev/null || break diff "conftest.out" "conftest.nl" >/dev/null 2>&1 || break as_fn_arith $ac_count + 1 && ac_count=$as_val if test $ac_count -gt ${ac_path_GREP_max-0}; then # Best one so far, save it but keep looking for a better one ac_cv_path_GREP="$ac_path_GREP" ac_path_GREP_max=$ac_count fi # 10*(2^10) chars as input seems more than enough test $ac_count -gt 10 && break done rm -f conftest.in conftest.tmp conftest.nl conftest.out;; esac $ac_path_GREP_found && break 3 done done done IFS=$as_save_IFS if test -z "$ac_cv_path_GREP"; then as_fn_error $? "no acceptable grep could be found in $PATH$PATH_SEPARATOR/usr/xpg4/bin" "$LINENO" 5 fi else ac_cv_path_GREP=$GREP fi fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_cv_path_GREP" >&5 $as_echo "$ac_cv_path_GREP" >&6; } GREP="$ac_cv_path_GREP" { $as_echo "$as_me:${as_lineno-$LINENO}: checking for egrep" >&5 $as_echo_n "checking for egrep... " >&6; } if ${ac_cv_path_EGREP+:} false; then : $as_echo_n "(cached) " >&6 else if echo a | $GREP -E '(a|b)' >/dev/null 2>&1 then ac_cv_path_EGREP="$GREP -E" else if test -z "$EGREP"; then ac_path_EGREP_found=false # Loop through the user's path and test for each of PROGNAME-LIST as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH$PATH_SEPARATOR/usr/xpg4/bin do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_prog in egrep; do for ac_exec_ext in '' $ac_executable_extensions; do ac_path_EGREP="$as_dir/$ac_prog$ac_exec_ext" as_fn_executable_p "$ac_path_EGREP" || continue # Check for GNU ac_path_EGREP and select it if it is found. # Check for GNU $ac_path_EGREP case `"$ac_path_EGREP" --version 2>&1` in *GNU*) ac_cv_path_EGREP="$ac_path_EGREP" ac_path_EGREP_found=:;; *) ac_count=0 $as_echo_n 0123456789 >"conftest.in" while : do cat "conftest.in" "conftest.in" >"conftest.tmp" mv "conftest.tmp" "conftest.in" cp "conftest.in" "conftest.nl" $as_echo 'EGREP' >> "conftest.nl" "$ac_path_EGREP" 'EGREP$' < "conftest.nl" >"conftest.out" 2>/dev/null || break diff "conftest.out" "conftest.nl" >/dev/null 2>&1 || break as_fn_arith $ac_count + 1 && ac_count=$as_val if test $ac_count -gt ${ac_path_EGREP_max-0}; then # Best one so far, save it but keep looking for a better one ac_cv_path_EGREP="$ac_path_EGREP" ac_path_EGREP_max=$ac_count fi # 10*(2^10) chars as input seems more than enough test $ac_count -gt 10 && break done rm -f conftest.in conftest.tmp conftest.nl conftest.out;; esac $ac_path_EGREP_found && break 3 done done done IFS=$as_save_IFS if test -z "$ac_cv_path_EGREP"; then as_fn_error $? "no acceptable egrep could be found in $PATH$PATH_SEPARATOR/usr/xpg4/bin" "$LINENO" 5 fi else ac_cv_path_EGREP=$EGREP fi fi fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_cv_path_EGREP" >&5 $as_echo "$ac_cv_path_EGREP" >&6; } EGREP="$ac_cv_path_EGREP" { $as_echo "$as_me:${as_lineno-$LINENO}: checking for fgrep" >&5 $as_echo_n "checking for fgrep... " >&6; } if ${ac_cv_path_FGREP+:} false; then : $as_echo_n "(cached) " >&6 else if echo 'ab*c' | $GREP -F 'ab*c' >/dev/null 2>&1 then ac_cv_path_FGREP="$GREP -F" else if test -z "$FGREP"; then ac_path_FGREP_found=false # Loop through the user's path and test for each of PROGNAME-LIST as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH$PATH_SEPARATOR/usr/xpg4/bin do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_prog in fgrep; do for ac_exec_ext in '' $ac_executable_extensions; do ac_path_FGREP="$as_dir/$ac_prog$ac_exec_ext" as_fn_executable_p "$ac_path_FGREP" || continue # Check for GNU ac_path_FGREP and select it if it is found. # Check for GNU $ac_path_FGREP case `"$ac_path_FGREP" --version 2>&1` in *GNU*) ac_cv_path_FGREP="$ac_path_FGREP" ac_path_FGREP_found=:;; *) ac_count=0 $as_echo_n 0123456789 >"conftest.in" while : do cat "conftest.in" "conftest.in" >"conftest.tmp" mv "conftest.tmp" "conftest.in" cp "conftest.in" "conftest.nl" $as_echo 'FGREP' >> "conftest.nl" "$ac_path_FGREP" FGREP < "conftest.nl" >"conftest.out" 2>/dev/null || break diff "conftest.out" "conftest.nl" >/dev/null 2>&1 || break as_fn_arith $ac_count + 1 && ac_count=$as_val if test $ac_count -gt ${ac_path_FGREP_max-0}; then # Best one so far, save it but keep looking for a better one ac_cv_path_FGREP="$ac_path_FGREP" ac_path_FGREP_max=$ac_count fi # 10*(2^10) chars as input seems more than enough test $ac_count -gt 10 && break done rm -f conftest.in conftest.tmp conftest.nl conftest.out;; esac $ac_path_FGREP_found && break 3 done done done IFS=$as_save_IFS if test -z "$ac_cv_path_FGREP"; then as_fn_error $? "no acceptable fgrep could be found in $PATH$PATH_SEPARATOR/usr/xpg4/bin" "$LINENO" 5 fi else ac_cv_path_FGREP=$FGREP fi fi fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_cv_path_FGREP" >&5 $as_echo "$ac_cv_path_FGREP" >&6; } FGREP="$ac_cv_path_FGREP" test -z "$GREP" && GREP=grep # Check whether --with-gnu-ld was given. if test "${with_gnu_ld+set}" = set; then : withval=$with_gnu_ld; test "$withval" = no || with_gnu_ld=yes else with_gnu_ld=no fi ac_prog=ld if test "$GCC" = yes; then # Check if gcc -print-prog-name=ld gives a path. { $as_echo "$as_me:${as_lineno-$LINENO}: checking for ld used by $CC" >&5 $as_echo_n "checking for ld used by $CC... " >&6; } case $host in *-*-mingw*) # gcc leaves a trailing carriage return which upsets mingw ac_prog=`($CC -print-prog-name=ld) 2>&5 | tr -d '\015'` ;; *) ac_prog=`($CC -print-prog-name=ld) 2>&5` ;; esac case $ac_prog in # Accept absolute paths. [\\/]* | ?:[\\/]*) re_direlt='/[^/][^/]*/\.\./' # Canonicalize the pathname of ld ac_prog=`$ECHO "$ac_prog"| $SED 's%\\\\%/%g'` while $ECHO "$ac_prog" | $GREP "$re_direlt" > /dev/null 2>&1; do ac_prog=`$ECHO $ac_prog| $SED "s%$re_direlt%/%"` done test -z "$LD" && LD="$ac_prog" ;; "") # If it fails, then pretend we aren't using GCC. ac_prog=ld ;; *) # If it is relative, then search for the first ld in PATH. with_gnu_ld=unknown ;; esac elif test "$with_gnu_ld" = yes; then { $as_echo "$as_me:${as_lineno-$LINENO}: checking for GNU ld" >&5 $as_echo_n "checking for GNU ld... " >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: checking for non-GNU ld" >&5 $as_echo_n "checking for non-GNU ld... " >&6; } fi if ${lt_cv_path_LD+:} false; then : $as_echo_n "(cached) " >&6 else if test -z "$LD"; then lt_save_ifs="$IFS"; IFS=$PATH_SEPARATOR for ac_dir in $PATH; do IFS="$lt_save_ifs" test -z "$ac_dir" && ac_dir=. if test -f "$ac_dir/$ac_prog" || test -f "$ac_dir/$ac_prog$ac_exeext"; then lt_cv_path_LD="$ac_dir/$ac_prog" # Check to see if the program is GNU ld. I'd rather use --version, # but apparently some variants of GNU ld only accept -v. # Break only if it was the GNU/non-GNU ld that we prefer. case `"$lt_cv_path_LD" -v 2>&1 &5 $as_echo "$LD" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi test -z "$LD" && as_fn_error $? "no acceptable ld found in \$PATH" "$LINENO" 5 { $as_echo "$as_me:${as_lineno-$LINENO}: checking if the linker ($LD) is GNU ld" >&5 $as_echo_n "checking if the linker ($LD) is GNU ld... " >&6; } if ${lt_cv_prog_gnu_ld+:} false; then : $as_echo_n "(cached) " >&6 else # I'd rather use --version here, but apparently some GNU lds only accept -v. case `$LD -v 2>&1 &5 $as_echo "$lt_cv_prog_gnu_ld" >&6; } with_gnu_ld=$lt_cv_prog_gnu_ld { $as_echo "$as_me:${as_lineno-$LINENO}: checking for BSD- or MS-compatible name lister (nm)" >&5 $as_echo_n "checking for BSD- or MS-compatible name lister (nm)... " >&6; } if ${lt_cv_path_NM+:} false; then : $as_echo_n "(cached) " >&6 else if test -n "$NM"; then # Let the user override the test. lt_cv_path_NM="$NM" else lt_nm_to_check="${ac_tool_prefix}nm" if test -n "$ac_tool_prefix" && test "$build" = "$host"; then lt_nm_to_check="$lt_nm_to_check nm" fi for lt_tmp_nm in $lt_nm_to_check; do lt_save_ifs="$IFS"; IFS=$PATH_SEPARATOR for ac_dir in $PATH /usr/ccs/bin/elf /usr/ccs/bin /usr/ucb /bin; do IFS="$lt_save_ifs" test -z "$ac_dir" && ac_dir=. tmp_nm="$ac_dir/$lt_tmp_nm" if test -f "$tmp_nm" || test -f "$tmp_nm$ac_exeext" ; then # Check to see if the nm accepts a BSD-compat flag. # Adding the `sed 1q' prevents false positives on HP-UX, which says: # nm: unknown option "B" ignored # Tru64's nm complains that /dev/null is an invalid object file case `"$tmp_nm" -B /dev/null 2>&1 | sed '1q'` in */dev/null* | *'Invalid file or object type'*) lt_cv_path_NM="$tmp_nm -B" break ;; *) case `"$tmp_nm" -p /dev/null 2>&1 | sed '1q'` in */dev/null*) lt_cv_path_NM="$tmp_nm -p" break ;; *) lt_cv_path_NM=${lt_cv_path_NM="$tmp_nm"} # keep the first match, but continue # so that we can try to find one that supports BSD flags ;; esac ;; esac fi done IFS="$lt_save_ifs" done : ${lt_cv_path_NM=no} fi fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $lt_cv_path_NM" >&5 $as_echo "$lt_cv_path_NM" >&6; } if test "$lt_cv_path_NM" != "no"; then NM="$lt_cv_path_NM" else # Didn't find any BSD compatible name lister, look for dumpbin. if test -n "$DUMPBIN"; then : # Let the user override the test. else if test -n "$ac_tool_prefix"; then for ac_prog in dumpbin "link -dump" do # Extract the first word of "$ac_tool_prefix$ac_prog", so it can be a program name with args. set dummy $ac_tool_prefix$ac_prog; ac_word=$2 { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $ac_word" >&5 $as_echo_n "checking for $ac_word... " >&6; } if ${ac_cv_prog_DUMPBIN+:} false; then : $as_echo_n "(cached) " >&6 else if test -n "$DUMPBIN"; then ac_cv_prog_DUMPBIN="$DUMPBIN" # Let the user override the test. else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_exec_ext in '' $ac_executable_extensions; do if as_fn_executable_p "$as_dir/$ac_word$ac_exec_ext"; then ac_cv_prog_DUMPBIN="$ac_tool_prefix$ac_prog" $as_echo "$as_me:${as_lineno-$LINENO}: found $as_dir/$ac_word$ac_exec_ext" >&5 break 2 fi done done IFS=$as_save_IFS fi fi DUMPBIN=$ac_cv_prog_DUMPBIN if test -n "$DUMPBIN"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $DUMPBIN" >&5 $as_echo "$DUMPBIN" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi test -n "$DUMPBIN" && break done fi if test -z "$DUMPBIN"; then ac_ct_DUMPBIN=$DUMPBIN for ac_prog in dumpbin "link -dump" do # Extract the first word of "$ac_prog", so it can be a program name with args. set dummy $ac_prog; ac_word=$2 { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $ac_word" >&5 $as_echo_n "checking for $ac_word... " >&6; } if ${ac_cv_prog_ac_ct_DUMPBIN+:} false; then : $as_echo_n "(cached) " >&6 else if test -n "$ac_ct_DUMPBIN"; then ac_cv_prog_ac_ct_DUMPBIN="$ac_ct_DUMPBIN" # Let the user override the test. else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_exec_ext in '' $ac_executable_extensions; do if as_fn_executable_p "$as_dir/$ac_word$ac_exec_ext"; then ac_cv_prog_ac_ct_DUMPBIN="$ac_prog" $as_echo "$as_me:${as_lineno-$LINENO}: found $as_dir/$ac_word$ac_exec_ext" >&5 break 2 fi done done IFS=$as_save_IFS fi fi ac_ct_DUMPBIN=$ac_cv_prog_ac_ct_DUMPBIN if test -n "$ac_ct_DUMPBIN"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_ct_DUMPBIN" >&5 $as_echo "$ac_ct_DUMPBIN" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi test -n "$ac_ct_DUMPBIN" && break done if test "x$ac_ct_DUMPBIN" = x; then DUMPBIN=":" else case $cross_compiling:$ac_tool_warned in yes:) { $as_echo "$as_me:${as_lineno-$LINENO}: WARNING: using cross tools not prefixed with host triplet" >&5 $as_echo "$as_me: WARNING: using cross tools not prefixed with host triplet" >&2;} ac_tool_warned=yes ;; esac DUMPBIN=$ac_ct_DUMPBIN fi fi case `$DUMPBIN -symbols /dev/null 2>&1 | sed '1q'` in *COFF*) DUMPBIN="$DUMPBIN -symbols" ;; *) DUMPBIN=: ;; esac fi if test "$DUMPBIN" != ":"; then NM="$DUMPBIN" fi fi test -z "$NM" && NM=nm { $as_echo "$as_me:${as_lineno-$LINENO}: checking the name lister ($NM) interface" >&5 $as_echo_n "checking the name lister ($NM) interface... " >&6; } if ${lt_cv_nm_interface+:} false; then : $as_echo_n "(cached) " >&6 else lt_cv_nm_interface="BSD nm" echo "int some_variable = 0;" > conftest.$ac_ext (eval echo "\"\$as_me:$LINENO: $ac_compile\"" >&5) (eval "$ac_compile" 2>conftest.err) cat conftest.err >&5 (eval echo "\"\$as_me:$LINENO: $NM \\\"conftest.$ac_objext\\\"\"" >&5) (eval "$NM \"conftest.$ac_objext\"" 2>conftest.err > conftest.out) cat conftest.err >&5 (eval echo "\"\$as_me:$LINENO: output\"" >&5) cat conftest.out >&5 if $GREP 'External.*some_variable' conftest.out > /dev/null; then lt_cv_nm_interface="MS dumpbin" fi rm -f conftest* fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $lt_cv_nm_interface" >&5 $as_echo "$lt_cv_nm_interface" >&6; } { $as_echo "$as_me:${as_lineno-$LINENO}: checking whether ln -s works" >&5 $as_echo_n "checking whether ln -s works... " >&6; } LN_S=$as_ln_s if test "$LN_S" = "ln -s"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: yes" >&5 $as_echo "yes" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no, using $LN_S" >&5 $as_echo "no, using $LN_S" >&6; } fi # find the maximum length of command line arguments { $as_echo "$as_me:${as_lineno-$LINENO}: checking the maximum length of command line arguments" >&5 $as_echo_n "checking the maximum length of command line arguments... " >&6; } if ${lt_cv_sys_max_cmd_len+:} false; then : $as_echo_n "(cached) " >&6 else i=0 teststring="ABCD" case $build_os in msdosdjgpp*) # On DJGPP, this test can blow up pretty badly due to problems in libc # (any single argument exceeding 2000 bytes causes a buffer overrun # during glob expansion). Even if it were fixed, the result of this # check would be larger than it should be. lt_cv_sys_max_cmd_len=12288; # 12K is about right ;; gnu*) # Under GNU Hurd, this test is not required because there is # no limit to the length of command line arguments. # Libtool will interpret -1 as no limit whatsoever lt_cv_sys_max_cmd_len=-1; ;; cygwin* | mingw* | cegcc*) # On Win9x/ME, this test blows up -- it succeeds, but takes # about 5 minutes as the teststring grows exponentially. # Worse, since 9x/ME are not pre-emptively multitasking, # you end up with a "frozen" computer, even though with patience # the test eventually succeeds (with a max line length of 256k). # Instead, let's just punt: use the minimum linelength reported by # all of the supported platforms: 8192 (on NT/2K/XP). lt_cv_sys_max_cmd_len=8192; ;; mint*) # On MiNT this can take a long time and run out of memory. lt_cv_sys_max_cmd_len=8192; ;; amigaos*) # On AmigaOS with pdksh, this test takes hours, literally. # So we just punt and use a minimum line length of 8192. lt_cv_sys_max_cmd_len=8192; ;; netbsd* | freebsd* | openbsd* | darwin* | dragonfly*) # This has been around since 386BSD, at least. Likely further. if test -x /sbin/sysctl; then lt_cv_sys_max_cmd_len=`/sbin/sysctl -n kern.argmax` elif test -x /usr/sbin/sysctl; then lt_cv_sys_max_cmd_len=`/usr/sbin/sysctl -n kern.argmax` else lt_cv_sys_max_cmd_len=65536 # usable default for all BSDs fi # And add a safety zone lt_cv_sys_max_cmd_len=`expr $lt_cv_sys_max_cmd_len \/ 4` lt_cv_sys_max_cmd_len=`expr $lt_cv_sys_max_cmd_len \* 3` ;; interix*) # We know the value 262144 and hardcode it with a safety zone (like BSD) lt_cv_sys_max_cmd_len=196608 ;; os2*) # The test takes a long time on OS/2. lt_cv_sys_max_cmd_len=8192 ;; osf*) # Dr. Hans Ekkehard Plesser reports seeing a kernel panic running configure # due to this test when exec_disable_arg_limit is 1 on Tru64. It is not # nice to cause kernel panics so lets avoid the loop below. # First set a reasonable default. lt_cv_sys_max_cmd_len=16384 # if test -x /sbin/sysconfig; then case `/sbin/sysconfig -q proc exec_disable_arg_limit` in *1*) lt_cv_sys_max_cmd_len=-1 ;; esac fi ;; sco3.2v5*) lt_cv_sys_max_cmd_len=102400 ;; sysv5* | sco5v6* | sysv4.2uw2*) kargmax=`grep ARG_MAX /etc/conf/cf.d/stune 2>/dev/null` if test -n "$kargmax"; then lt_cv_sys_max_cmd_len=`echo $kargmax | sed 's/.*[ ]//'` else lt_cv_sys_max_cmd_len=32768 fi ;; *) lt_cv_sys_max_cmd_len=`(getconf ARG_MAX) 2> /dev/null` if test -n "$lt_cv_sys_max_cmd_len" && \ test undefined != "$lt_cv_sys_max_cmd_len"; then lt_cv_sys_max_cmd_len=`expr $lt_cv_sys_max_cmd_len \/ 4` lt_cv_sys_max_cmd_len=`expr $lt_cv_sys_max_cmd_len \* 3` else # Make teststring a little bigger before we do anything with it. # a 1K string should be a reasonable start. for i in 1 2 3 4 5 6 7 8 ; do teststring=$teststring$teststring done SHELL=${SHELL-${CONFIG_SHELL-/bin/sh}} # If test is not a shell built-in, we'll probably end up computing a # maximum length that is only half of the actual maximum length, but # we can't tell. while { test "X"`env echo "$teststring$teststring" 2>/dev/null` \ = "X$teststring$teststring"; } >/dev/null 2>&1 && test $i != 17 # 1/2 MB should be enough do i=`expr $i + 1` teststring=$teststring$teststring done # Only check the string length outside the loop. lt_cv_sys_max_cmd_len=`expr "X$teststring" : ".*" 2>&1` teststring= # Add a significant safety factor because C++ compilers can tack on # massive amounts of additional arguments before passing them to the # linker. It appears as though 1/2 is a usable value. lt_cv_sys_max_cmd_len=`expr $lt_cv_sys_max_cmd_len \/ 2` fi ;; esac fi if test -n $lt_cv_sys_max_cmd_len ; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $lt_cv_sys_max_cmd_len" >&5 $as_echo "$lt_cv_sys_max_cmd_len" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: none" >&5 $as_echo "none" >&6; } fi max_cmd_len=$lt_cv_sys_max_cmd_len : ${CP="cp -f"} : ${MV="mv -f"} : ${RM="rm -f"} { $as_echo "$as_me:${as_lineno-$LINENO}: checking whether the shell understands some XSI constructs" >&5 $as_echo_n "checking whether the shell understands some XSI constructs... " >&6; } # Try some XSI features xsi_shell=no ( _lt_dummy="a/b/c" test "${_lt_dummy##*/},${_lt_dummy%/*},${_lt_dummy#??}"${_lt_dummy%"$_lt_dummy"}, \ = c,a/b,b/c, \ && eval 'test $(( 1 + 1 )) -eq 2 \ && test "${#_lt_dummy}" -eq 5' ) >/dev/null 2>&1 \ && xsi_shell=yes { $as_echo "$as_me:${as_lineno-$LINENO}: result: $xsi_shell" >&5 $as_echo "$xsi_shell" >&6; } { $as_echo "$as_me:${as_lineno-$LINENO}: checking whether the shell understands \"+=\"" >&5 $as_echo_n "checking whether the shell understands \"+=\"... " >&6; } lt_shell_append=no ( foo=bar; set foo baz; eval "$1+=\$2" && test "$foo" = barbaz ) \ >/dev/null 2>&1 \ && lt_shell_append=yes { $as_echo "$as_me:${as_lineno-$LINENO}: result: $lt_shell_append" >&5 $as_echo "$lt_shell_append" >&6; } if ( (MAIL=60; unset MAIL) || exit) >/dev/null 2>&1; then lt_unset=unset else lt_unset=false fi # test EBCDIC or ASCII case `echo X|tr X '\101'` in A) # ASCII based system # \n is not interpreted correctly by Solaris 8 /usr/ucb/tr lt_SP2NL='tr \040 \012' lt_NL2SP='tr \015\012 \040\040' ;; *) # EBCDIC based system lt_SP2NL='tr \100 \n' lt_NL2SP='tr \r\n \100\100' ;; esac { $as_echo "$as_me:${as_lineno-$LINENO}: checking how to convert $build file names to $host format" >&5 $as_echo_n "checking how to convert $build file names to $host format... " >&6; } if ${lt_cv_to_host_file_cmd+:} false; then : $as_echo_n "(cached) " >&6 else case $host in *-*-mingw* ) case $build in *-*-mingw* ) # actually msys lt_cv_to_host_file_cmd=func_convert_file_msys_to_w32 ;; *-*-cygwin* ) lt_cv_to_host_file_cmd=func_convert_file_cygwin_to_w32 ;; * ) # otherwise, assume *nix lt_cv_to_host_file_cmd=func_convert_file_nix_to_w32 ;; esac ;; *-*-cygwin* ) case $build in *-*-mingw* ) # actually msys lt_cv_to_host_file_cmd=func_convert_file_msys_to_cygwin ;; *-*-cygwin* ) lt_cv_to_host_file_cmd=func_convert_file_noop ;; * ) # otherwise, assume *nix lt_cv_to_host_file_cmd=func_convert_file_nix_to_cygwin ;; esac ;; * ) # unhandled hosts (and "normal" native builds) lt_cv_to_host_file_cmd=func_convert_file_noop ;; esac fi to_host_file_cmd=$lt_cv_to_host_file_cmd { $as_echo "$as_me:${as_lineno-$LINENO}: result: $lt_cv_to_host_file_cmd" >&5 $as_echo "$lt_cv_to_host_file_cmd" >&6; } { $as_echo "$as_me:${as_lineno-$LINENO}: checking how to convert $build file names to toolchain format" >&5 $as_echo_n "checking how to convert $build file names to toolchain format... " >&6; } if ${lt_cv_to_tool_file_cmd+:} false; then : $as_echo_n "(cached) " >&6 else #assume ordinary cross tools, or native build. lt_cv_to_tool_file_cmd=func_convert_file_noop case $host in *-*-mingw* ) case $build in *-*-mingw* ) # actually msys lt_cv_to_tool_file_cmd=func_convert_file_msys_to_w32 ;; esac ;; esac fi to_tool_file_cmd=$lt_cv_to_tool_file_cmd { $as_echo "$as_me:${as_lineno-$LINENO}: result: $lt_cv_to_tool_file_cmd" >&5 $as_echo "$lt_cv_to_tool_file_cmd" >&6; } { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $LD option to reload object files" >&5 $as_echo_n "checking for $LD option to reload object files... " >&6; } if ${lt_cv_ld_reload_flag+:} false; then : $as_echo_n "(cached) " >&6 else lt_cv_ld_reload_flag='-r' fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $lt_cv_ld_reload_flag" >&5 $as_echo "$lt_cv_ld_reload_flag" >&6; } reload_flag=$lt_cv_ld_reload_flag case $reload_flag in "" | " "*) ;; *) reload_flag=" $reload_flag" ;; esac reload_cmds='$LD$reload_flag -o $output$reload_objs' case $host_os in cygwin* | mingw* | pw32* | cegcc*) if test "$GCC" != yes; then reload_cmds=false fi ;; darwin*) if test "$GCC" = yes; then reload_cmds='$LTCC $LTCFLAGS -nostdlib ${wl}-r -o $output$reload_objs' else reload_cmds='$LD$reload_flag -o $output$reload_objs' fi ;; esac if test -n "$ac_tool_prefix"; then # Extract the first word of "${ac_tool_prefix}objdump", so it can be a program name with args. set dummy ${ac_tool_prefix}objdump; ac_word=$2 { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $ac_word" >&5 $as_echo_n "checking for $ac_word... " >&6; } if ${ac_cv_prog_OBJDUMP+:} false; then : $as_echo_n "(cached) " >&6 else if test -n "$OBJDUMP"; then ac_cv_prog_OBJDUMP="$OBJDUMP" # Let the user override the test. else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_exec_ext in '' $ac_executable_extensions; do if as_fn_executable_p "$as_dir/$ac_word$ac_exec_ext"; then ac_cv_prog_OBJDUMP="${ac_tool_prefix}objdump" $as_echo "$as_me:${as_lineno-$LINENO}: found $as_dir/$ac_word$ac_exec_ext" >&5 break 2 fi done done IFS=$as_save_IFS fi fi OBJDUMP=$ac_cv_prog_OBJDUMP if test -n "$OBJDUMP"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $OBJDUMP" >&5 $as_echo "$OBJDUMP" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi fi if test -z "$ac_cv_prog_OBJDUMP"; then ac_ct_OBJDUMP=$OBJDUMP # Extract the first word of "objdump", so it can be a program name with args. set dummy objdump; ac_word=$2 { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $ac_word" >&5 $as_echo_n "checking for $ac_word... " >&6; } if ${ac_cv_prog_ac_ct_OBJDUMP+:} false; then : $as_echo_n "(cached) " >&6 else if test -n "$ac_ct_OBJDUMP"; then ac_cv_prog_ac_ct_OBJDUMP="$ac_ct_OBJDUMP" # Let the user override the test. else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_exec_ext in '' $ac_executable_extensions; do if as_fn_executable_p "$as_dir/$ac_word$ac_exec_ext"; then ac_cv_prog_ac_ct_OBJDUMP="objdump" $as_echo "$as_me:${as_lineno-$LINENO}: found $as_dir/$ac_word$ac_exec_ext" >&5 break 2 fi done done IFS=$as_save_IFS fi fi ac_ct_OBJDUMP=$ac_cv_prog_ac_ct_OBJDUMP if test -n "$ac_ct_OBJDUMP"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_ct_OBJDUMP" >&5 $as_echo "$ac_ct_OBJDUMP" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi if test "x$ac_ct_OBJDUMP" = x; then OBJDUMP="false" else case $cross_compiling:$ac_tool_warned in yes:) { $as_echo "$as_me:${as_lineno-$LINENO}: WARNING: using cross tools not prefixed with host triplet" >&5 $as_echo "$as_me: WARNING: using cross tools not prefixed with host triplet" >&2;} ac_tool_warned=yes ;; esac OBJDUMP=$ac_ct_OBJDUMP fi else OBJDUMP="$ac_cv_prog_OBJDUMP" fi test -z "$OBJDUMP" && OBJDUMP=objdump { $as_echo "$as_me:${as_lineno-$LINENO}: checking how to recognize dependent libraries" >&5 $as_echo_n "checking how to recognize dependent libraries... " >&6; } if ${lt_cv_deplibs_check_method+:} false; then : $as_echo_n "(cached) " >&6 else lt_cv_file_magic_cmd='$MAGIC_CMD' lt_cv_file_magic_test_file= lt_cv_deplibs_check_method='unknown' # Need to set the preceding variable on all platforms that support # interlibrary dependencies. # 'none' -- dependencies not supported. # `unknown' -- same as none, but documents that we really don't know. # 'pass_all' -- all dependencies passed with no checks. # 'test_compile' -- check by making test program. # 'file_magic [[regex]]' -- check by looking for files in library path # which responds to the $file_magic_cmd with a given extended regex. # If you have `file' or equivalent on your system and you're not sure # whether `pass_all' will *always* work, you probably want this one. case $host_os in aix[4-9]*) lt_cv_deplibs_check_method=pass_all ;; beos*) lt_cv_deplibs_check_method=pass_all ;; bsdi[45]*) lt_cv_deplibs_check_method='file_magic ELF [0-9][0-9]*-bit [ML]SB (shared object|dynamic lib)' lt_cv_file_magic_cmd='/usr/bin/file -L' lt_cv_file_magic_test_file=/shlib/libc.so ;; cygwin*) # func_win32_libid is a shell function defined in ltmain.sh lt_cv_deplibs_check_method='file_magic ^x86 archive import|^x86 DLL' lt_cv_file_magic_cmd='func_win32_libid' ;; mingw* | pw32*) # Base MSYS/MinGW do not provide the 'file' command needed by # func_win32_libid shell function, so use a weaker test based on 'objdump', # unless we find 'file', for example because we are cross-compiling. # func_win32_libid assumes BSD nm, so disallow it if using MS dumpbin. if ( test "$lt_cv_nm_interface" = "BSD nm" && file / ) >/dev/null 2>&1; then lt_cv_deplibs_check_method='file_magic ^x86 archive import|^x86 DLL' lt_cv_file_magic_cmd='func_win32_libid' else # Keep this pattern in sync with the one in func_win32_libid. lt_cv_deplibs_check_method='file_magic file format (pei*-i386(.*architecture: i386)?|pe-arm-wince|pe-x86-64)' lt_cv_file_magic_cmd='$OBJDUMP -f' fi ;; cegcc*) # use the weaker test based on 'objdump'. See mingw*. lt_cv_deplibs_check_method='file_magic file format pe-arm-.*little(.*architecture: arm)?' lt_cv_file_magic_cmd='$OBJDUMP -f' ;; darwin* | rhapsody*) lt_cv_deplibs_check_method=pass_all ;; freebsd* | dragonfly*) if echo __ELF__ | $CC -E - | $GREP __ELF__ > /dev/null; then case $host_cpu in i*86 ) # Not sure whether the presence of OpenBSD here was a mistake. # Let's accept both of them until this is cleared up. lt_cv_deplibs_check_method='file_magic (FreeBSD|OpenBSD|DragonFly)/i[3-9]86 (compact )?demand paged shared library' lt_cv_file_magic_cmd=/usr/bin/file lt_cv_file_magic_test_file=`echo /usr/lib/libc.so.*` ;; esac else lt_cv_deplibs_check_method=pass_all fi ;; haiku*) lt_cv_deplibs_check_method=pass_all ;; hpux10.20* | hpux11*) lt_cv_file_magic_cmd=/usr/bin/file case $host_cpu in ia64*) lt_cv_deplibs_check_method='file_magic (s[0-9][0-9][0-9]|ELF-[0-9][0-9]) shared object file - IA64' lt_cv_file_magic_test_file=/usr/lib/hpux32/libc.so ;; hppa*64*) lt_cv_deplibs_check_method='file_magic (s[0-9][0-9][0-9]|ELF[ -][0-9][0-9])(-bit)?( [LM]SB)? shared object( file)?[, -]* PA-RISC [0-9]\.[0-9]' lt_cv_file_magic_test_file=/usr/lib/pa20_64/libc.sl ;; *) lt_cv_deplibs_check_method='file_magic (s[0-9][0-9][0-9]|PA-RISC[0-9]\.[0-9]) shared library' lt_cv_file_magic_test_file=/usr/lib/libc.sl ;; esac ;; interix[3-9]*) # PIC code is broken on Interix 3.x, that's why |\.a not |_pic\.a here lt_cv_deplibs_check_method='match_pattern /lib[^/]+(\.so|\.a)$' ;; irix5* | irix6* | nonstopux*) case $LD in *-32|*"-32 ") libmagic=32-bit;; *-n32|*"-n32 ") libmagic=N32;; *-64|*"-64 ") libmagic=64-bit;; *) libmagic=never-match;; esac lt_cv_deplibs_check_method=pass_all ;; # This must be glibc/ELF. linux* | k*bsd*-gnu | kopensolaris*-gnu | gnu*) lt_cv_deplibs_check_method=pass_all ;; netbsd* | netbsdelf*-gnu) if echo __ELF__ | $CC -E - | $GREP __ELF__ > /dev/null; then lt_cv_deplibs_check_method='match_pattern /lib[^/]+(\.so\.[0-9]+\.[0-9]+|_pic\.a)$' else lt_cv_deplibs_check_method='match_pattern /lib[^/]+(\.so|_pic\.a)$' fi ;; newos6*) lt_cv_deplibs_check_method='file_magic ELF [0-9][0-9]*-bit [ML]SB (executable|dynamic lib)' lt_cv_file_magic_cmd=/usr/bin/file lt_cv_file_magic_test_file=/usr/lib/libnls.so ;; *nto* | *qnx*) lt_cv_deplibs_check_method=pass_all ;; openbsd*) if test -z "`echo __ELF__ | $CC -E - | $GREP __ELF__`" || test "$host_os-$host_cpu" = "openbsd2.8-powerpc"; then lt_cv_deplibs_check_method='match_pattern /lib[^/]+(\.so\.[0-9]+\.[0-9]+|\.so|_pic\.a)$' else lt_cv_deplibs_check_method='match_pattern /lib[^/]+(\.so\.[0-9]+\.[0-9]+|_pic\.a)$' fi ;; osf3* | osf4* | osf5*) lt_cv_deplibs_check_method=pass_all ;; rdos*) lt_cv_deplibs_check_method=pass_all ;; solaris*) lt_cv_deplibs_check_method=pass_all ;; sysv5* | sco3.2v5* | sco5v6* | unixware* | OpenUNIX* | sysv4*uw2*) lt_cv_deplibs_check_method=pass_all ;; sysv4 | sysv4.3*) case $host_vendor in motorola) lt_cv_deplibs_check_method='file_magic ELF [0-9][0-9]*-bit [ML]SB (shared object|dynamic lib) M[0-9][0-9]* Version [0-9]' lt_cv_file_magic_test_file=`echo /usr/lib/libc.so*` ;; ncr) lt_cv_deplibs_check_method=pass_all ;; sequent) lt_cv_file_magic_cmd='/bin/file' lt_cv_deplibs_check_method='file_magic ELF [0-9][0-9]*-bit [LM]SB (shared object|dynamic lib )' ;; sni) lt_cv_file_magic_cmd='/bin/file' lt_cv_deplibs_check_method="file_magic ELF [0-9][0-9]*-bit [LM]SB dynamic lib" lt_cv_file_magic_test_file=/lib/libc.so ;; siemens) lt_cv_deplibs_check_method=pass_all ;; pc) lt_cv_deplibs_check_method=pass_all ;; esac ;; tpf*) lt_cv_deplibs_check_method=pass_all ;; esac fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $lt_cv_deplibs_check_method" >&5 $as_echo "$lt_cv_deplibs_check_method" >&6; } file_magic_glob= want_nocaseglob=no if test "$build" = "$host"; then case $host_os in mingw* | pw32*) if ( shopt | grep nocaseglob ) >/dev/null 2>&1; then want_nocaseglob=yes else file_magic_glob=`echo aAbBcCdDeEfFgGhHiIjJkKlLmMnNoOpPqQrRsStTuUvVwWxXyYzZ | $SED -e "s/\(..\)/s\/[\1]\/[\1]\/g;/g"` fi ;; esac fi file_magic_cmd=$lt_cv_file_magic_cmd deplibs_check_method=$lt_cv_deplibs_check_method test -z "$deplibs_check_method" && deplibs_check_method=unknown if test -n "$ac_tool_prefix"; then # Extract the first word of "${ac_tool_prefix}dlltool", so it can be a program name with args. set dummy ${ac_tool_prefix}dlltool; ac_word=$2 { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $ac_word" >&5 $as_echo_n "checking for $ac_word... " >&6; } if ${ac_cv_prog_DLLTOOL+:} false; then : $as_echo_n "(cached) " >&6 else if test -n "$DLLTOOL"; then ac_cv_prog_DLLTOOL="$DLLTOOL" # Let the user override the test. else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_exec_ext in '' $ac_executable_extensions; do if as_fn_executable_p "$as_dir/$ac_word$ac_exec_ext"; then ac_cv_prog_DLLTOOL="${ac_tool_prefix}dlltool" $as_echo "$as_me:${as_lineno-$LINENO}: found $as_dir/$ac_word$ac_exec_ext" >&5 break 2 fi done done IFS=$as_save_IFS fi fi DLLTOOL=$ac_cv_prog_DLLTOOL if test -n "$DLLTOOL"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $DLLTOOL" >&5 $as_echo "$DLLTOOL" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi fi if test -z "$ac_cv_prog_DLLTOOL"; then ac_ct_DLLTOOL=$DLLTOOL # Extract the first word of "dlltool", so it can be a program name with args. set dummy dlltool; ac_word=$2 { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $ac_word" >&5 $as_echo_n "checking for $ac_word... " >&6; } if ${ac_cv_prog_ac_ct_DLLTOOL+:} false; then : $as_echo_n "(cached) " >&6 else if test -n "$ac_ct_DLLTOOL"; then ac_cv_prog_ac_ct_DLLTOOL="$ac_ct_DLLTOOL" # Let the user override the test. else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_exec_ext in '' $ac_executable_extensions; do if as_fn_executable_p "$as_dir/$ac_word$ac_exec_ext"; then ac_cv_prog_ac_ct_DLLTOOL="dlltool" $as_echo "$as_me:${as_lineno-$LINENO}: found $as_dir/$ac_word$ac_exec_ext" >&5 break 2 fi done done IFS=$as_save_IFS fi fi ac_ct_DLLTOOL=$ac_cv_prog_ac_ct_DLLTOOL if test -n "$ac_ct_DLLTOOL"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_ct_DLLTOOL" >&5 $as_echo "$ac_ct_DLLTOOL" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi if test "x$ac_ct_DLLTOOL" = x; then DLLTOOL="false" else case $cross_compiling:$ac_tool_warned in yes:) { $as_echo "$as_me:${as_lineno-$LINENO}: WARNING: using cross tools not prefixed with host triplet" >&5 $as_echo "$as_me: WARNING: using cross tools not prefixed with host triplet" >&2;} ac_tool_warned=yes ;; esac DLLTOOL=$ac_ct_DLLTOOL fi else DLLTOOL="$ac_cv_prog_DLLTOOL" fi test -z "$DLLTOOL" && DLLTOOL=dlltool { $as_echo "$as_me:${as_lineno-$LINENO}: checking how to associate runtime and link libraries" >&5 $as_echo_n "checking how to associate runtime and link libraries... " >&6; } if ${lt_cv_sharedlib_from_linklib_cmd+:} false; then : $as_echo_n "(cached) " >&6 else lt_cv_sharedlib_from_linklib_cmd='unknown' case $host_os in cygwin* | mingw* | pw32* | cegcc*) # two different shell functions defined in ltmain.sh # decide which to use based on capabilities of $DLLTOOL case `$DLLTOOL --help 2>&1` in *--identify-strict*) lt_cv_sharedlib_from_linklib_cmd=func_cygming_dll_for_implib ;; *) lt_cv_sharedlib_from_linklib_cmd=func_cygming_dll_for_implib_fallback ;; esac ;; *) # fallback: assume linklib IS sharedlib lt_cv_sharedlib_from_linklib_cmd="$ECHO" ;; esac fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $lt_cv_sharedlib_from_linklib_cmd" >&5 $as_echo "$lt_cv_sharedlib_from_linklib_cmd" >&6; } sharedlib_from_linklib_cmd=$lt_cv_sharedlib_from_linklib_cmd test -z "$sharedlib_from_linklib_cmd" && sharedlib_from_linklib_cmd=$ECHO if test -n "$ac_tool_prefix"; then for ac_prog in ar do # Extract the first word of "$ac_tool_prefix$ac_prog", so it can be a program name with args. set dummy $ac_tool_prefix$ac_prog; ac_word=$2 { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $ac_word" >&5 $as_echo_n "checking for $ac_word... " >&6; } if ${ac_cv_prog_AR+:} false; then : $as_echo_n "(cached) " >&6 else if test -n "$AR"; then ac_cv_prog_AR="$AR" # Let the user override the test. else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_exec_ext in '' $ac_executable_extensions; do if as_fn_executable_p "$as_dir/$ac_word$ac_exec_ext"; then ac_cv_prog_AR="$ac_tool_prefix$ac_prog" $as_echo "$as_me:${as_lineno-$LINENO}: found $as_dir/$ac_word$ac_exec_ext" >&5 break 2 fi done done IFS=$as_save_IFS fi fi AR=$ac_cv_prog_AR if test -n "$AR"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $AR" >&5 $as_echo "$AR" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi test -n "$AR" && break done fi if test -z "$AR"; then ac_ct_AR=$AR for ac_prog in ar do # Extract the first word of "$ac_prog", so it can be a program name with args. set dummy $ac_prog; ac_word=$2 { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $ac_word" >&5 $as_echo_n "checking for $ac_word... " >&6; } if ${ac_cv_prog_ac_ct_AR+:} false; then : $as_echo_n "(cached) " >&6 else if test -n "$ac_ct_AR"; then ac_cv_prog_ac_ct_AR="$ac_ct_AR" # Let the user override the test. else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_exec_ext in '' $ac_executable_extensions; do if as_fn_executable_p "$as_dir/$ac_word$ac_exec_ext"; then ac_cv_prog_ac_ct_AR="$ac_prog" $as_echo "$as_me:${as_lineno-$LINENO}: found $as_dir/$ac_word$ac_exec_ext" >&5 break 2 fi done done IFS=$as_save_IFS fi fi ac_ct_AR=$ac_cv_prog_ac_ct_AR if test -n "$ac_ct_AR"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_ct_AR" >&5 $as_echo "$ac_ct_AR" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi test -n "$ac_ct_AR" && break done if test "x$ac_ct_AR" = x; then AR="false" else case $cross_compiling:$ac_tool_warned in yes:) { $as_echo "$as_me:${as_lineno-$LINENO}: WARNING: using cross tools not prefixed with host triplet" >&5 $as_echo "$as_me: WARNING: using cross tools not prefixed with host triplet" >&2;} ac_tool_warned=yes ;; esac AR=$ac_ct_AR fi fi : ${AR=ar} : ${AR_FLAGS=cru} { $as_echo "$as_me:${as_lineno-$LINENO}: checking for archiver @FILE support" >&5 $as_echo_n "checking for archiver @FILE support... " >&6; } if ${lt_cv_ar_at_file+:} false; then : $as_echo_n "(cached) " >&6 else lt_cv_ar_at_file=no cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ int main () { ; return 0; } _ACEOF if ac_fn_c_try_compile "$LINENO"; then : echo conftest.$ac_objext > conftest.lst lt_ar_try='$AR $AR_FLAGS libconftest.a @conftest.lst >&5' { { eval echo "\"\$as_me\":${as_lineno-$LINENO}: \"$lt_ar_try\""; } >&5 (eval $lt_ar_try) 2>&5 ac_status=$? $as_echo "$as_me:${as_lineno-$LINENO}: \$? = $ac_status" >&5 test $ac_status = 0; } if test "$ac_status" -eq 0; then # Ensure the archiver fails upon bogus file names. rm -f conftest.$ac_objext libconftest.a { { eval echo "\"\$as_me\":${as_lineno-$LINENO}: \"$lt_ar_try\""; } >&5 (eval $lt_ar_try) 2>&5 ac_status=$? $as_echo "$as_me:${as_lineno-$LINENO}: \$? = $ac_status" >&5 test $ac_status = 0; } if test "$ac_status" -ne 0; then lt_cv_ar_at_file=@ fi fi rm -f conftest.* libconftest.a fi rm -f core conftest.err conftest.$ac_objext conftest.$ac_ext fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $lt_cv_ar_at_file" >&5 $as_echo "$lt_cv_ar_at_file" >&6; } if test "x$lt_cv_ar_at_file" = xno; then archiver_list_spec= else archiver_list_spec=$lt_cv_ar_at_file fi if test -n "$ac_tool_prefix"; then # Extract the first word of "${ac_tool_prefix}strip", so it can be a program name with args. set dummy ${ac_tool_prefix}strip; ac_word=$2 { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $ac_word" >&5 $as_echo_n "checking for $ac_word... " >&6; } if ${ac_cv_prog_STRIP+:} false; then : $as_echo_n "(cached) " >&6 else if test -n "$STRIP"; then ac_cv_prog_STRIP="$STRIP" # Let the user override the test. else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_exec_ext in '' $ac_executable_extensions; do if as_fn_executable_p "$as_dir/$ac_word$ac_exec_ext"; then ac_cv_prog_STRIP="${ac_tool_prefix}strip" $as_echo "$as_me:${as_lineno-$LINENO}: found $as_dir/$ac_word$ac_exec_ext" >&5 break 2 fi done done IFS=$as_save_IFS fi fi STRIP=$ac_cv_prog_STRIP if test -n "$STRIP"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $STRIP" >&5 $as_echo "$STRIP" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi fi if test -z "$ac_cv_prog_STRIP"; then ac_ct_STRIP=$STRIP # Extract the first word of "strip", so it can be a program name with args. set dummy strip; ac_word=$2 { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $ac_word" >&5 $as_echo_n "checking for $ac_word... " >&6; } if ${ac_cv_prog_ac_ct_STRIP+:} false; then : $as_echo_n "(cached) " >&6 else if test -n "$ac_ct_STRIP"; then ac_cv_prog_ac_ct_STRIP="$ac_ct_STRIP" # Let the user override the test. else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_exec_ext in '' $ac_executable_extensions; do if as_fn_executable_p "$as_dir/$ac_word$ac_exec_ext"; then ac_cv_prog_ac_ct_STRIP="strip" $as_echo "$as_me:${as_lineno-$LINENO}: found $as_dir/$ac_word$ac_exec_ext" >&5 break 2 fi done done IFS=$as_save_IFS fi fi ac_ct_STRIP=$ac_cv_prog_ac_ct_STRIP if test -n "$ac_ct_STRIP"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_ct_STRIP" >&5 $as_echo "$ac_ct_STRIP" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi if test "x$ac_ct_STRIP" = x; then STRIP=":" else case $cross_compiling:$ac_tool_warned in yes:) { $as_echo "$as_me:${as_lineno-$LINENO}: WARNING: using cross tools not prefixed with host triplet" >&5 $as_echo "$as_me: WARNING: using cross tools not prefixed with host triplet" >&2;} ac_tool_warned=yes ;; esac STRIP=$ac_ct_STRIP fi else STRIP="$ac_cv_prog_STRIP" fi test -z "$STRIP" && STRIP=: if test -n "$ac_tool_prefix"; then # Extract the first word of "${ac_tool_prefix}ranlib", so it can be a program name with args. set dummy ${ac_tool_prefix}ranlib; ac_word=$2 { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $ac_word" >&5 $as_echo_n "checking for $ac_word... " >&6; } if ${ac_cv_prog_RANLIB+:} false; then : $as_echo_n "(cached) " >&6 else if test -n "$RANLIB"; then ac_cv_prog_RANLIB="$RANLIB" # Let the user override the test. else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_exec_ext in '' $ac_executable_extensions; do if as_fn_executable_p "$as_dir/$ac_word$ac_exec_ext"; then ac_cv_prog_RANLIB="${ac_tool_prefix}ranlib" $as_echo "$as_me:${as_lineno-$LINENO}: found $as_dir/$ac_word$ac_exec_ext" >&5 break 2 fi done done IFS=$as_save_IFS fi fi RANLIB=$ac_cv_prog_RANLIB if test -n "$RANLIB"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $RANLIB" >&5 $as_echo "$RANLIB" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi fi if test -z "$ac_cv_prog_RANLIB"; then ac_ct_RANLIB=$RANLIB # Extract the first word of "ranlib", so it can be a program name with args. set dummy ranlib; ac_word=$2 { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $ac_word" >&5 $as_echo_n "checking for $ac_word... " >&6; } if ${ac_cv_prog_ac_ct_RANLIB+:} false; then : $as_echo_n "(cached) " >&6 else if test -n "$ac_ct_RANLIB"; then ac_cv_prog_ac_ct_RANLIB="$ac_ct_RANLIB" # Let the user override the test. else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_exec_ext in '' $ac_executable_extensions; do if as_fn_executable_p "$as_dir/$ac_word$ac_exec_ext"; then ac_cv_prog_ac_ct_RANLIB="ranlib" $as_echo "$as_me:${as_lineno-$LINENO}: found $as_dir/$ac_word$ac_exec_ext" >&5 break 2 fi done done IFS=$as_save_IFS fi fi ac_ct_RANLIB=$ac_cv_prog_ac_ct_RANLIB if test -n "$ac_ct_RANLIB"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_ct_RANLIB" >&5 $as_echo "$ac_ct_RANLIB" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi if test "x$ac_ct_RANLIB" = x; then RANLIB=":" else case $cross_compiling:$ac_tool_warned in yes:) { $as_echo "$as_me:${as_lineno-$LINENO}: WARNING: using cross tools not prefixed with host triplet" >&5 $as_echo "$as_me: WARNING: using cross tools not prefixed with host triplet" >&2;} ac_tool_warned=yes ;; esac RANLIB=$ac_ct_RANLIB fi else RANLIB="$ac_cv_prog_RANLIB" fi test -z "$RANLIB" && RANLIB=: # Determine commands to create old-style static archives. old_archive_cmds='$AR $AR_FLAGS $oldlib$oldobjs' old_postinstall_cmds='chmod 644 $oldlib' old_postuninstall_cmds= if test -n "$RANLIB"; then case $host_os in openbsd*) old_postinstall_cmds="$old_postinstall_cmds~\$RANLIB -t \$tool_oldlib" ;; *) old_postinstall_cmds="$old_postinstall_cmds~\$RANLIB \$tool_oldlib" ;; esac old_archive_cmds="$old_archive_cmds~\$RANLIB \$tool_oldlib" fi case $host_os in darwin*) lock_old_archive_extraction=yes ;; *) lock_old_archive_extraction=no ;; esac # If no C compiler was specified, use CC. LTCC=${LTCC-"$CC"} # If no C compiler flags were specified, use CFLAGS. LTCFLAGS=${LTCFLAGS-"$CFLAGS"} # Allow CC to be a program name with arguments. compiler=$CC # Check for command to grab the raw symbol name followed by C symbol from nm. { $as_echo "$as_me:${as_lineno-$LINENO}: checking command to parse $NM output from $compiler object" >&5 $as_echo_n "checking command to parse $NM output from $compiler object... " >&6; } if ${lt_cv_sys_global_symbol_pipe+:} false; then : $as_echo_n "(cached) " >&6 else # These are sane defaults that work on at least a few old systems. # [They come from Ultrix. What could be older than Ultrix?!! ;)] # Character class describing NM global symbol codes. symcode='[BCDEGRST]' # Regexp to match symbols that can be accessed directly from C. sympat='\([_A-Za-z][_A-Za-z0-9]*\)' # Define system-specific variables. case $host_os in aix*) symcode='[BCDT]' ;; cygwin* | mingw* | pw32* | cegcc*) symcode='[ABCDGISTW]' ;; hpux*) if test "$host_cpu" = ia64; then symcode='[ABCDEGRST]' fi ;; irix* | nonstopux*) symcode='[BCDEGRST]' ;; osf*) symcode='[BCDEGQRST]' ;; solaris*) symcode='[BDRT]' ;; sco3.2v5*) symcode='[DT]' ;; sysv4.2uw2*) symcode='[DT]' ;; sysv5* | sco5v6* | unixware* | OpenUNIX*) symcode='[ABDT]' ;; sysv4) symcode='[DFNSTU]' ;; esac # If we're using GNU nm, then use its standard symbol codes. case `$NM -V 2>&1` in *GNU* | *'with BFD'*) symcode='[ABCDGIRSTW]' ;; esac # Transform an extracted symbol line into a proper C declaration. # Some systems (esp. on ia64) link data and code symbols differently, # so use this general approach. lt_cv_sys_global_symbol_to_cdecl="sed -n -e 's/^T .* \(.*\)$/extern int \1();/p' -e 's/^$symcode* .* \(.*\)$/extern char \1;/p'" # Transform an extracted symbol line into symbol name and symbol address lt_cv_sys_global_symbol_to_c_name_address="sed -n -e 's/^: \([^ ]*\)[ ]*$/ {\\\"\1\\\", (void *) 0},/p' -e 's/^$symcode* \([^ ]*\) \([^ ]*\)$/ {\"\2\", (void *) \&\2},/p'" lt_cv_sys_global_symbol_to_c_name_address_lib_prefix="sed -n -e 's/^: \([^ ]*\)[ ]*$/ {\\\"\1\\\", (void *) 0},/p' -e 's/^$symcode* \([^ ]*\) \(lib[^ ]*\)$/ {\"\2\", (void *) \&\2},/p' -e 's/^$symcode* \([^ ]*\) \([^ ]*\)$/ {\"lib\2\", (void *) \&\2},/p'" # Handle CRLF in mingw tool chain opt_cr= case $build_os in mingw*) opt_cr=`$ECHO 'x\{0,1\}' | tr x '\015'` # option cr in regexp ;; esac # Try without a prefix underscore, then with it. for ac_symprfx in "" "_"; do # Transform symcode, sympat, and symprfx into a raw symbol and a C symbol. symxfrm="\\1 $ac_symprfx\\2 \\2" # Write the raw and C identifiers. if test "$lt_cv_nm_interface" = "MS dumpbin"; then # Fake it for dumpbin and say T for any non-static function # and D for any global variable. # Also find C++ and __fastcall symbols from MSVC++, # which start with @ or ?. lt_cv_sys_global_symbol_pipe="$AWK '"\ " {last_section=section; section=\$ 3};"\ " /^COFF SYMBOL TABLE/{for(i in hide) delete hide[i]};"\ " /Section length .*#relocs.*(pick any)/{hide[last_section]=1};"\ " \$ 0!~/External *\|/{next};"\ " / 0+ UNDEF /{next}; / UNDEF \([^|]\)*()/{next};"\ " {if(hide[section]) next};"\ " {f=0}; \$ 0~/\(\).*\|/{f=1}; {printf f ? \"T \" : \"D \"};"\ " {split(\$ 0, a, /\||\r/); split(a[2], s)};"\ " s[1]~/^[@?]/{print s[1], s[1]; next};"\ " s[1]~prfx {split(s[1],t,\"@\"); print t[1], substr(t[1],length(prfx))}"\ " ' prfx=^$ac_symprfx" else lt_cv_sys_global_symbol_pipe="sed -n -e 's/^.*[ ]\($symcode$symcode*\)[ ][ ]*$ac_symprfx$sympat$opt_cr$/$symxfrm/p'" fi lt_cv_sys_global_symbol_pipe="$lt_cv_sys_global_symbol_pipe | sed '/ __gnu_lto/d'" # Check to see that the pipe works correctly. pipe_works=no rm -f conftest* cat > conftest.$ac_ext <<_LT_EOF #ifdef __cplusplus extern "C" { #endif char nm_test_var; void nm_test_func(void); void nm_test_func(void){} #ifdef __cplusplus } #endif int main(){nm_test_var='a';nm_test_func();return(0);} _LT_EOF if { { eval echo "\"\$as_me\":${as_lineno-$LINENO}: \"$ac_compile\""; } >&5 (eval $ac_compile) 2>&5 ac_status=$? $as_echo "$as_me:${as_lineno-$LINENO}: \$? = $ac_status" >&5 test $ac_status = 0; }; then # Now try to grab the symbols. nlist=conftest.nm if { { eval echo "\"\$as_me\":${as_lineno-$LINENO}: \"$NM conftest.$ac_objext \| "$lt_cv_sys_global_symbol_pipe" \> $nlist\""; } >&5 (eval $NM conftest.$ac_objext \| "$lt_cv_sys_global_symbol_pipe" \> $nlist) 2>&5 ac_status=$? $as_echo "$as_me:${as_lineno-$LINENO}: \$? = $ac_status" >&5 test $ac_status = 0; } && test -s "$nlist"; then # Try sorting and uniquifying the output. if sort "$nlist" | uniq > "$nlist"T; then mv -f "$nlist"T "$nlist" else rm -f "$nlist"T fi # Make sure that we snagged all the symbols we need. if $GREP ' nm_test_var$' "$nlist" >/dev/null; then if $GREP ' nm_test_func$' "$nlist" >/dev/null; then cat <<_LT_EOF > conftest.$ac_ext /* Keep this code in sync between libtool.m4, ltmain, lt_system.h, and tests. */ #if defined(_WIN32) || defined(__CYGWIN__) || defined(_WIN32_WCE) /* DATA imports from DLLs on WIN32 con't be const, because runtime relocations are performed -- see ld's documentation on pseudo-relocs. */ # define LT_DLSYM_CONST #elif defined(__osf__) /* This system does not cope well with relocations in const data. */ # define LT_DLSYM_CONST #else # define LT_DLSYM_CONST const #endif #ifdef __cplusplus extern "C" { #endif _LT_EOF # Now generate the symbol file. eval "$lt_cv_sys_global_symbol_to_cdecl"' < "$nlist" | $GREP -v main >> conftest.$ac_ext' cat <<_LT_EOF >> conftest.$ac_ext /* The mapping between symbol names and symbols. */ LT_DLSYM_CONST struct { const char *name; void *address; } lt__PROGRAM__LTX_preloaded_symbols[] = { { "@PROGRAM@", (void *) 0 }, _LT_EOF $SED "s/^$symcode$symcode* \(.*\) \(.*\)$/ {\"\2\", (void *) \&\2},/" < "$nlist" | $GREP -v main >> conftest.$ac_ext cat <<\_LT_EOF >> conftest.$ac_ext {0, (void *) 0} }; /* This works around a problem in FreeBSD linker */ #ifdef FREEBSD_WORKAROUND static const void *lt_preloaded_setup() { return lt__PROGRAM__LTX_preloaded_symbols; } #endif #ifdef __cplusplus } #endif _LT_EOF # Now try linking the two files. mv conftest.$ac_objext conftstm.$ac_objext lt_globsym_save_LIBS=$LIBS lt_globsym_save_CFLAGS=$CFLAGS LIBS="conftstm.$ac_objext" CFLAGS="$CFLAGS$lt_prog_compiler_no_builtin_flag" if { { eval echo "\"\$as_me\":${as_lineno-$LINENO}: \"$ac_link\""; } >&5 (eval $ac_link) 2>&5 ac_status=$? $as_echo "$as_me:${as_lineno-$LINENO}: \$? = $ac_status" >&5 test $ac_status = 0; } && test -s conftest${ac_exeext}; then pipe_works=yes fi LIBS=$lt_globsym_save_LIBS CFLAGS=$lt_globsym_save_CFLAGS else echo "cannot find nm_test_func in $nlist" >&5 fi else echo "cannot find nm_test_var in $nlist" >&5 fi else echo "cannot run $lt_cv_sys_global_symbol_pipe" >&5 fi else echo "$progname: failed program was:" >&5 cat conftest.$ac_ext >&5 fi rm -rf conftest* conftst* # Do not use the global_symbol_pipe unless it works. if test "$pipe_works" = yes; then break else lt_cv_sys_global_symbol_pipe= fi done fi if test -z "$lt_cv_sys_global_symbol_pipe"; then lt_cv_sys_global_symbol_to_cdecl= fi if test -z "$lt_cv_sys_global_symbol_pipe$lt_cv_sys_global_symbol_to_cdecl"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: failed" >&5 $as_echo "failed" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: ok" >&5 $as_echo "ok" >&6; } fi # Response file support. if test "$lt_cv_nm_interface" = "MS dumpbin"; then nm_file_list_spec='@' elif $NM --help 2>/dev/null | grep '[@]FILE' >/dev/null; then nm_file_list_spec='@' fi { $as_echo "$as_me:${as_lineno-$LINENO}: checking for sysroot" >&5 $as_echo_n "checking for sysroot... " >&6; } # Check whether --with-sysroot was given. if test "${with_sysroot+set}" = set; then : withval=$with_sysroot; else with_sysroot=no fi lt_sysroot= case ${with_sysroot} in #( yes) if test "$GCC" = yes; then lt_sysroot=`$CC --print-sysroot 2>/dev/null` fi ;; #( /*) lt_sysroot=`echo "$with_sysroot" | sed -e "$sed_quote_subst"` ;; #( no|'') ;; #( *) { $as_echo "$as_me:${as_lineno-$LINENO}: result: ${with_sysroot}" >&5 $as_echo "${with_sysroot}" >&6; } as_fn_error $? "The sysroot must be an absolute path." "$LINENO" 5 ;; esac { $as_echo "$as_me:${as_lineno-$LINENO}: result: ${lt_sysroot:-no}" >&5 $as_echo "${lt_sysroot:-no}" >&6; } # Check whether --enable-libtool-lock was given. if test "${enable_libtool_lock+set}" = set; then : enableval=$enable_libtool_lock; fi test "x$enable_libtool_lock" != xno && enable_libtool_lock=yes # Some flags need to be propagated to the compiler or linker for good # libtool support. case $host in ia64-*-hpux*) # Find out which ABI we are using. echo 'int i;' > conftest.$ac_ext if { { eval echo "\"\$as_me\":${as_lineno-$LINENO}: \"$ac_compile\""; } >&5 (eval $ac_compile) 2>&5 ac_status=$? $as_echo "$as_me:${as_lineno-$LINENO}: \$? = $ac_status" >&5 test $ac_status = 0; }; then case `/usr/bin/file conftest.$ac_objext` in *ELF-32*) HPUX_IA64_MODE="32" ;; *ELF-64*) HPUX_IA64_MODE="64" ;; esac fi rm -rf conftest* ;; *-*-irix6*) # Find out which ABI we are using. echo '#line '$LINENO' "configure"' > conftest.$ac_ext if { { eval echo "\"\$as_me\":${as_lineno-$LINENO}: \"$ac_compile\""; } >&5 (eval $ac_compile) 2>&5 ac_status=$? $as_echo "$as_me:${as_lineno-$LINENO}: \$? = $ac_status" >&5 test $ac_status = 0; }; then if test "$lt_cv_prog_gnu_ld" = yes; then case `/usr/bin/file conftest.$ac_objext` in *32-bit*) LD="${LD-ld} -melf32bsmip" ;; *N32*) LD="${LD-ld} -melf32bmipn32" ;; *64-bit*) LD="${LD-ld} -melf64bmip" ;; esac else case `/usr/bin/file conftest.$ac_objext` in *32-bit*) LD="${LD-ld} -32" ;; *N32*) LD="${LD-ld} -n32" ;; *64-bit*) LD="${LD-ld} -64" ;; esac fi fi rm -rf conftest* ;; x86_64-*kfreebsd*-gnu|x86_64-*linux*|ppc*-*linux*|powerpc*-*linux*| \ s390*-*linux*|s390*-*tpf*|sparc*-*linux*) # Find out which ABI we are using. echo 'int i;' > conftest.$ac_ext if { { eval echo "\"\$as_me\":${as_lineno-$LINENO}: \"$ac_compile\""; } >&5 (eval $ac_compile) 2>&5 ac_status=$? $as_echo "$as_me:${as_lineno-$LINENO}: \$? = $ac_status" >&5 test $ac_status = 0; }; then case `/usr/bin/file conftest.o` in *32-bit*) case $host in x86_64-*kfreebsd*-gnu) LD="${LD-ld} -m elf_i386_fbsd" ;; x86_64-*linux*) case `/usr/bin/file conftest.o` in *x86-64*) LD="${LD-ld} -m elf32_x86_64" ;; *) LD="${LD-ld} -m elf_i386" ;; esac ;; ppc64-*linux*|powerpc64-*linux*) LD="${LD-ld} -m elf32ppclinux" ;; s390x-*linux*) LD="${LD-ld} -m elf_s390" ;; sparc64-*linux*) LD="${LD-ld} -m elf32_sparc" ;; esac ;; *64-bit*) case $host in x86_64-*kfreebsd*-gnu) LD="${LD-ld} -m elf_x86_64_fbsd" ;; x86_64-*linux*) LD="${LD-ld} -m elf_x86_64" ;; ppc*-*linux*|powerpc*-*linux*) LD="${LD-ld} -m elf64ppc" ;; s390*-*linux*|s390*-*tpf*) LD="${LD-ld} -m elf64_s390" ;; sparc*-*linux*) LD="${LD-ld} -m elf64_sparc" ;; esac ;; esac fi rm -rf conftest* ;; *-*-sco3.2v5*) # On SCO OpenServer 5, we need -belf to get full-featured binaries. SAVE_CFLAGS="$CFLAGS" CFLAGS="$CFLAGS -belf" { $as_echo "$as_me:${as_lineno-$LINENO}: checking whether the C compiler needs -belf" >&5 $as_echo_n "checking whether the C compiler needs -belf... " >&6; } if ${lt_cv_cc_needs_belf+:} false; then : $as_echo_n "(cached) " >&6 else ac_ext=c ac_cpp='$CPP $CPPFLAGS' ac_compile='$CC -c $CFLAGS $CPPFLAGS conftest.$ac_ext >&5' ac_link='$CC -o conftest$ac_exeext $CFLAGS $CPPFLAGS $LDFLAGS conftest.$ac_ext $LIBS >&5' ac_compiler_gnu=$ac_cv_c_compiler_gnu cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ int main () { ; return 0; } _ACEOF if ac_fn_c_try_link "$LINENO"; then : lt_cv_cc_needs_belf=yes else lt_cv_cc_needs_belf=no fi rm -f core conftest.err conftest.$ac_objext \ conftest$ac_exeext conftest.$ac_ext ac_ext=c ac_cpp='$CPP $CPPFLAGS' ac_compile='$CC -c $CFLAGS $CPPFLAGS conftest.$ac_ext >&5' ac_link='$CC -o conftest$ac_exeext $CFLAGS $CPPFLAGS $LDFLAGS conftest.$ac_ext $LIBS >&5' ac_compiler_gnu=$ac_cv_c_compiler_gnu fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $lt_cv_cc_needs_belf" >&5 $as_echo "$lt_cv_cc_needs_belf" >&6; } if test x"$lt_cv_cc_needs_belf" != x"yes"; then # this is probably gcc 2.8.0, egcs 1.0 or newer; no need for -belf CFLAGS="$SAVE_CFLAGS" fi ;; *-*solaris*) # Find out which ABI we are using. echo 'int i;' > conftest.$ac_ext if { { eval echo "\"\$as_me\":${as_lineno-$LINENO}: \"$ac_compile\""; } >&5 (eval $ac_compile) 2>&5 ac_status=$? $as_echo "$as_me:${as_lineno-$LINENO}: \$? = $ac_status" >&5 test $ac_status = 0; }; then case `/usr/bin/file conftest.o` in *64-bit*) case $lt_cv_prog_gnu_ld in yes*) case $host in i?86-*-solaris*) LD="${LD-ld} -m elf_x86_64" ;; sparc*-*-solaris*) LD="${LD-ld} -m elf64_sparc" ;; esac # GNU ld 2.21 introduced _sol2 emulations. Use them if available. if ${LD-ld} -V | grep _sol2 >/dev/null 2>&1; then LD="${LD-ld}_sol2" fi ;; *) if ${LD-ld} -64 -r -o conftest2.o conftest.o >/dev/null 2>&1; then LD="${LD-ld} -64" fi ;; esac ;; esac fi rm -rf conftest* ;; esac need_locks="$enable_libtool_lock" if test -n "$ac_tool_prefix"; then # Extract the first word of "${ac_tool_prefix}mt", so it can be a program name with args. set dummy ${ac_tool_prefix}mt; ac_word=$2 { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $ac_word" >&5 $as_echo_n "checking for $ac_word... " >&6; } if ${ac_cv_prog_MANIFEST_TOOL+:} false; then : $as_echo_n "(cached) " >&6 else if test -n "$MANIFEST_TOOL"; then ac_cv_prog_MANIFEST_TOOL="$MANIFEST_TOOL" # Let the user override the test. else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_exec_ext in '' $ac_executable_extensions; do if as_fn_executable_p "$as_dir/$ac_word$ac_exec_ext"; then ac_cv_prog_MANIFEST_TOOL="${ac_tool_prefix}mt" $as_echo "$as_me:${as_lineno-$LINENO}: found $as_dir/$ac_word$ac_exec_ext" >&5 break 2 fi done done IFS=$as_save_IFS fi fi MANIFEST_TOOL=$ac_cv_prog_MANIFEST_TOOL if test -n "$MANIFEST_TOOL"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $MANIFEST_TOOL" >&5 $as_echo "$MANIFEST_TOOL" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi fi if test -z "$ac_cv_prog_MANIFEST_TOOL"; then ac_ct_MANIFEST_TOOL=$MANIFEST_TOOL # Extract the first word of "mt", so it can be a program name with args. set dummy mt; ac_word=$2 { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $ac_word" >&5 $as_echo_n "checking for $ac_word... " >&6; } if ${ac_cv_prog_ac_ct_MANIFEST_TOOL+:} false; then : $as_echo_n "(cached) " >&6 else if test -n "$ac_ct_MANIFEST_TOOL"; then ac_cv_prog_ac_ct_MANIFEST_TOOL="$ac_ct_MANIFEST_TOOL" # Let the user override the test. else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_exec_ext in '' $ac_executable_extensions; do if as_fn_executable_p "$as_dir/$ac_word$ac_exec_ext"; then ac_cv_prog_ac_ct_MANIFEST_TOOL="mt" $as_echo "$as_me:${as_lineno-$LINENO}: found $as_dir/$ac_word$ac_exec_ext" >&5 break 2 fi done done IFS=$as_save_IFS fi fi ac_ct_MANIFEST_TOOL=$ac_cv_prog_ac_ct_MANIFEST_TOOL if test -n "$ac_ct_MANIFEST_TOOL"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_ct_MANIFEST_TOOL" >&5 $as_echo "$ac_ct_MANIFEST_TOOL" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi if test "x$ac_ct_MANIFEST_TOOL" = x; then MANIFEST_TOOL=":" else case $cross_compiling:$ac_tool_warned in yes:) { $as_echo "$as_me:${as_lineno-$LINENO}: WARNING: using cross tools not prefixed with host triplet" >&5 $as_echo "$as_me: WARNING: using cross tools not prefixed with host triplet" >&2;} ac_tool_warned=yes ;; esac MANIFEST_TOOL=$ac_ct_MANIFEST_TOOL fi else MANIFEST_TOOL="$ac_cv_prog_MANIFEST_TOOL" fi test -z "$MANIFEST_TOOL" && MANIFEST_TOOL=mt { $as_echo "$as_me:${as_lineno-$LINENO}: checking if $MANIFEST_TOOL is a manifest tool" >&5 $as_echo_n "checking if $MANIFEST_TOOL is a manifest tool... " >&6; } if ${lt_cv_path_mainfest_tool+:} false; then : $as_echo_n "(cached) " >&6 else lt_cv_path_mainfest_tool=no echo "$as_me:$LINENO: $MANIFEST_TOOL '-?'" >&5 $MANIFEST_TOOL '-?' 2>conftest.err > conftest.out cat conftest.err >&5 if $GREP 'Manifest Tool' conftest.out > /dev/null; then lt_cv_path_mainfest_tool=yes fi rm -f conftest* fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $lt_cv_path_mainfest_tool" >&5 $as_echo "$lt_cv_path_mainfest_tool" >&6; } if test "x$lt_cv_path_mainfest_tool" != xyes; then MANIFEST_TOOL=: fi case $host_os in rhapsody* | darwin*) if test -n "$ac_tool_prefix"; then # Extract the first word of "${ac_tool_prefix}dsymutil", so it can be a program name with args. set dummy ${ac_tool_prefix}dsymutil; ac_word=$2 { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $ac_word" >&5 $as_echo_n "checking for $ac_word... " >&6; } if ${ac_cv_prog_DSYMUTIL+:} false; then : $as_echo_n "(cached) " >&6 else if test -n "$DSYMUTIL"; then ac_cv_prog_DSYMUTIL="$DSYMUTIL" # Let the user override the test. else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_exec_ext in '' $ac_executable_extensions; do if as_fn_executable_p "$as_dir/$ac_word$ac_exec_ext"; then ac_cv_prog_DSYMUTIL="${ac_tool_prefix}dsymutil" $as_echo "$as_me:${as_lineno-$LINENO}: found $as_dir/$ac_word$ac_exec_ext" >&5 break 2 fi done done IFS=$as_save_IFS fi fi DSYMUTIL=$ac_cv_prog_DSYMUTIL if test -n "$DSYMUTIL"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $DSYMUTIL" >&5 $as_echo "$DSYMUTIL" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi fi if test -z "$ac_cv_prog_DSYMUTIL"; then ac_ct_DSYMUTIL=$DSYMUTIL # Extract the first word of "dsymutil", so it can be a program name with args. set dummy dsymutil; ac_word=$2 { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $ac_word" >&5 $as_echo_n "checking for $ac_word... " >&6; } if ${ac_cv_prog_ac_ct_DSYMUTIL+:} false; then : $as_echo_n "(cached) " >&6 else if test -n "$ac_ct_DSYMUTIL"; then ac_cv_prog_ac_ct_DSYMUTIL="$ac_ct_DSYMUTIL" # Let the user override the test. else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_exec_ext in '' $ac_executable_extensions; do if as_fn_executable_p "$as_dir/$ac_word$ac_exec_ext"; then ac_cv_prog_ac_ct_DSYMUTIL="dsymutil" $as_echo "$as_me:${as_lineno-$LINENO}: found $as_dir/$ac_word$ac_exec_ext" >&5 break 2 fi done done IFS=$as_save_IFS fi fi ac_ct_DSYMUTIL=$ac_cv_prog_ac_ct_DSYMUTIL if test -n "$ac_ct_DSYMUTIL"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_ct_DSYMUTIL" >&5 $as_echo "$ac_ct_DSYMUTIL" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi if test "x$ac_ct_DSYMUTIL" = x; then DSYMUTIL=":" else case $cross_compiling:$ac_tool_warned in yes:) { $as_echo "$as_me:${as_lineno-$LINENO}: WARNING: using cross tools not prefixed with host triplet" >&5 $as_echo "$as_me: WARNING: using cross tools not prefixed with host triplet" >&2;} ac_tool_warned=yes ;; esac DSYMUTIL=$ac_ct_DSYMUTIL fi else DSYMUTIL="$ac_cv_prog_DSYMUTIL" fi if test -n "$ac_tool_prefix"; then # Extract the first word of "${ac_tool_prefix}nmedit", so it can be a program name with args. set dummy ${ac_tool_prefix}nmedit; ac_word=$2 { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $ac_word" >&5 $as_echo_n "checking for $ac_word... " >&6; } if ${ac_cv_prog_NMEDIT+:} false; then : $as_echo_n "(cached) " >&6 else if test -n "$NMEDIT"; then ac_cv_prog_NMEDIT="$NMEDIT" # Let the user override the test. else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_exec_ext in '' $ac_executable_extensions; do if as_fn_executable_p "$as_dir/$ac_word$ac_exec_ext"; then ac_cv_prog_NMEDIT="${ac_tool_prefix}nmedit" $as_echo "$as_me:${as_lineno-$LINENO}: found $as_dir/$ac_word$ac_exec_ext" >&5 break 2 fi done done IFS=$as_save_IFS fi fi NMEDIT=$ac_cv_prog_NMEDIT if test -n "$NMEDIT"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $NMEDIT" >&5 $as_echo "$NMEDIT" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi fi if test -z "$ac_cv_prog_NMEDIT"; then ac_ct_NMEDIT=$NMEDIT # Extract the first word of "nmedit", so it can be a program name with args. set dummy nmedit; ac_word=$2 { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $ac_word" >&5 $as_echo_n "checking for $ac_word... " >&6; } if ${ac_cv_prog_ac_ct_NMEDIT+:} false; then : $as_echo_n "(cached) " >&6 else if test -n "$ac_ct_NMEDIT"; then ac_cv_prog_ac_ct_NMEDIT="$ac_ct_NMEDIT" # Let the user override the test. else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_exec_ext in '' $ac_executable_extensions; do if as_fn_executable_p "$as_dir/$ac_word$ac_exec_ext"; then ac_cv_prog_ac_ct_NMEDIT="nmedit" $as_echo "$as_me:${as_lineno-$LINENO}: found $as_dir/$ac_word$ac_exec_ext" >&5 break 2 fi done done IFS=$as_save_IFS fi fi ac_ct_NMEDIT=$ac_cv_prog_ac_ct_NMEDIT if test -n "$ac_ct_NMEDIT"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_ct_NMEDIT" >&5 $as_echo "$ac_ct_NMEDIT" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi if test "x$ac_ct_NMEDIT" = x; then NMEDIT=":" else case $cross_compiling:$ac_tool_warned in yes:) { $as_echo "$as_me:${as_lineno-$LINENO}: WARNING: using cross tools not prefixed with host triplet" >&5 $as_echo "$as_me: WARNING: using cross tools not prefixed with host triplet" >&2;} ac_tool_warned=yes ;; esac NMEDIT=$ac_ct_NMEDIT fi else NMEDIT="$ac_cv_prog_NMEDIT" fi if test -n "$ac_tool_prefix"; then # Extract the first word of "${ac_tool_prefix}lipo", so it can be a program name with args. set dummy ${ac_tool_prefix}lipo; ac_word=$2 { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $ac_word" >&5 $as_echo_n "checking for $ac_word... " >&6; } if ${ac_cv_prog_LIPO+:} false; then : $as_echo_n "(cached) " >&6 else if test -n "$LIPO"; then ac_cv_prog_LIPO="$LIPO" # Let the user override the test. else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_exec_ext in '' $ac_executable_extensions; do if as_fn_executable_p "$as_dir/$ac_word$ac_exec_ext"; then ac_cv_prog_LIPO="${ac_tool_prefix}lipo" $as_echo "$as_me:${as_lineno-$LINENO}: found $as_dir/$ac_word$ac_exec_ext" >&5 break 2 fi done done IFS=$as_save_IFS fi fi LIPO=$ac_cv_prog_LIPO if test -n "$LIPO"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $LIPO" >&5 $as_echo "$LIPO" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi fi if test -z "$ac_cv_prog_LIPO"; then ac_ct_LIPO=$LIPO # Extract the first word of "lipo", so it can be a program name with args. set dummy lipo; ac_word=$2 { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $ac_word" >&5 $as_echo_n "checking for $ac_word... " >&6; } if ${ac_cv_prog_ac_ct_LIPO+:} false; then : $as_echo_n "(cached) " >&6 else if test -n "$ac_ct_LIPO"; then ac_cv_prog_ac_ct_LIPO="$ac_ct_LIPO" # Let the user override the test. else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_exec_ext in '' $ac_executable_extensions; do if as_fn_executable_p "$as_dir/$ac_word$ac_exec_ext"; then ac_cv_prog_ac_ct_LIPO="lipo" $as_echo "$as_me:${as_lineno-$LINENO}: found $as_dir/$ac_word$ac_exec_ext" >&5 break 2 fi done done IFS=$as_save_IFS fi fi ac_ct_LIPO=$ac_cv_prog_ac_ct_LIPO if test -n "$ac_ct_LIPO"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_ct_LIPO" >&5 $as_echo "$ac_ct_LIPO" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi if test "x$ac_ct_LIPO" = x; then LIPO=":" else case $cross_compiling:$ac_tool_warned in yes:) { $as_echo "$as_me:${as_lineno-$LINENO}: WARNING: using cross tools not prefixed with host triplet" >&5 $as_echo "$as_me: WARNING: using cross tools not prefixed with host triplet" >&2;} ac_tool_warned=yes ;; esac LIPO=$ac_ct_LIPO fi else LIPO="$ac_cv_prog_LIPO" fi if test -n "$ac_tool_prefix"; then # Extract the first word of "${ac_tool_prefix}otool", so it can be a program name with args. set dummy ${ac_tool_prefix}otool; ac_word=$2 { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $ac_word" >&5 $as_echo_n "checking for $ac_word... " >&6; } if ${ac_cv_prog_OTOOL+:} false; then : $as_echo_n "(cached) " >&6 else if test -n "$OTOOL"; then ac_cv_prog_OTOOL="$OTOOL" # Let the user override the test. else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_exec_ext in '' $ac_executable_extensions; do if as_fn_executable_p "$as_dir/$ac_word$ac_exec_ext"; then ac_cv_prog_OTOOL="${ac_tool_prefix}otool" $as_echo "$as_me:${as_lineno-$LINENO}: found $as_dir/$ac_word$ac_exec_ext" >&5 break 2 fi done done IFS=$as_save_IFS fi fi OTOOL=$ac_cv_prog_OTOOL if test -n "$OTOOL"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $OTOOL" >&5 $as_echo "$OTOOL" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi fi if test -z "$ac_cv_prog_OTOOL"; then ac_ct_OTOOL=$OTOOL # Extract the first word of "otool", so it can be a program name with args. set dummy otool; ac_word=$2 { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $ac_word" >&5 $as_echo_n "checking for $ac_word... " >&6; } if ${ac_cv_prog_ac_ct_OTOOL+:} false; then : $as_echo_n "(cached) " >&6 else if test -n "$ac_ct_OTOOL"; then ac_cv_prog_ac_ct_OTOOL="$ac_ct_OTOOL" # Let the user override the test. else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_exec_ext in '' $ac_executable_extensions; do if as_fn_executable_p "$as_dir/$ac_word$ac_exec_ext"; then ac_cv_prog_ac_ct_OTOOL="otool" $as_echo "$as_me:${as_lineno-$LINENO}: found $as_dir/$ac_word$ac_exec_ext" >&5 break 2 fi done done IFS=$as_save_IFS fi fi ac_ct_OTOOL=$ac_cv_prog_ac_ct_OTOOL if test -n "$ac_ct_OTOOL"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_ct_OTOOL" >&5 $as_echo "$ac_ct_OTOOL" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi if test "x$ac_ct_OTOOL" = x; then OTOOL=":" else case $cross_compiling:$ac_tool_warned in yes:) { $as_echo "$as_me:${as_lineno-$LINENO}: WARNING: using cross tools not prefixed with host triplet" >&5 $as_echo "$as_me: WARNING: using cross tools not prefixed with host triplet" >&2;} ac_tool_warned=yes ;; esac OTOOL=$ac_ct_OTOOL fi else OTOOL="$ac_cv_prog_OTOOL" fi if test -n "$ac_tool_prefix"; then # Extract the first word of "${ac_tool_prefix}otool64", so it can be a program name with args. set dummy ${ac_tool_prefix}otool64; ac_word=$2 { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $ac_word" >&5 $as_echo_n "checking for $ac_word... " >&6; } if ${ac_cv_prog_OTOOL64+:} false; then : $as_echo_n "(cached) " >&6 else if test -n "$OTOOL64"; then ac_cv_prog_OTOOL64="$OTOOL64" # Let the user override the test. else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_exec_ext in '' $ac_executable_extensions; do if as_fn_executable_p "$as_dir/$ac_word$ac_exec_ext"; then ac_cv_prog_OTOOL64="${ac_tool_prefix}otool64" $as_echo "$as_me:${as_lineno-$LINENO}: found $as_dir/$ac_word$ac_exec_ext" >&5 break 2 fi done done IFS=$as_save_IFS fi fi OTOOL64=$ac_cv_prog_OTOOL64 if test -n "$OTOOL64"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $OTOOL64" >&5 $as_echo "$OTOOL64" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi fi if test -z "$ac_cv_prog_OTOOL64"; then ac_ct_OTOOL64=$OTOOL64 # Extract the first word of "otool64", so it can be a program name with args. set dummy otool64; ac_word=$2 { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $ac_word" >&5 $as_echo_n "checking for $ac_word... " >&6; } if ${ac_cv_prog_ac_ct_OTOOL64+:} false; then : $as_echo_n "(cached) " >&6 else if test -n "$ac_ct_OTOOL64"; then ac_cv_prog_ac_ct_OTOOL64="$ac_ct_OTOOL64" # Let the user override the test. else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_exec_ext in '' $ac_executable_extensions; do if as_fn_executable_p "$as_dir/$ac_word$ac_exec_ext"; then ac_cv_prog_ac_ct_OTOOL64="otool64" $as_echo "$as_me:${as_lineno-$LINENO}: found $as_dir/$ac_word$ac_exec_ext" >&5 break 2 fi done done IFS=$as_save_IFS fi fi ac_ct_OTOOL64=$ac_cv_prog_ac_ct_OTOOL64 if test -n "$ac_ct_OTOOL64"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_ct_OTOOL64" >&5 $as_echo "$ac_ct_OTOOL64" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi if test "x$ac_ct_OTOOL64" = x; then OTOOL64=":" else case $cross_compiling:$ac_tool_warned in yes:) { $as_echo "$as_me:${as_lineno-$LINENO}: WARNING: using cross tools not prefixed with host triplet" >&5 $as_echo "$as_me: WARNING: using cross tools not prefixed with host triplet" >&2;} ac_tool_warned=yes ;; esac OTOOL64=$ac_ct_OTOOL64 fi else OTOOL64="$ac_cv_prog_OTOOL64" fi { $as_echo "$as_me:${as_lineno-$LINENO}: checking for -single_module linker flag" >&5 $as_echo_n "checking for -single_module linker flag... " >&6; } if ${lt_cv_apple_cc_single_mod+:} false; then : $as_echo_n "(cached) " >&6 else lt_cv_apple_cc_single_mod=no if test -z "${LT_MULTI_MODULE}"; then # By default we will add the -single_module flag. You can override # by either setting the environment variable LT_MULTI_MODULE # non-empty at configure time, or by adding -multi_module to the # link flags. rm -rf libconftest.dylib* echo "int foo(void){return 1;}" > conftest.c echo "$LTCC $LTCFLAGS $LDFLAGS -o libconftest.dylib \ -dynamiclib -Wl,-single_module conftest.c" >&5 $LTCC $LTCFLAGS $LDFLAGS -o libconftest.dylib \ -dynamiclib -Wl,-single_module conftest.c 2>conftest.err _lt_result=$? # If there is a non-empty error log, and "single_module" # appears in it, assume the flag caused a linker warning if test -s conftest.err && $GREP single_module conftest.err; then cat conftest.err >&5 # Otherwise, if the output was created with a 0 exit code from # the compiler, it worked. elif test -f libconftest.dylib && test $_lt_result -eq 0; then lt_cv_apple_cc_single_mod=yes else cat conftest.err >&5 fi rm -rf libconftest.dylib* rm -f conftest.* fi fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $lt_cv_apple_cc_single_mod" >&5 $as_echo "$lt_cv_apple_cc_single_mod" >&6; } { $as_echo "$as_me:${as_lineno-$LINENO}: checking for -exported_symbols_list linker flag" >&5 $as_echo_n "checking for -exported_symbols_list linker flag... " >&6; } if ${lt_cv_ld_exported_symbols_list+:} false; then : $as_echo_n "(cached) " >&6 else lt_cv_ld_exported_symbols_list=no save_LDFLAGS=$LDFLAGS echo "_main" > conftest.sym LDFLAGS="$LDFLAGS -Wl,-exported_symbols_list,conftest.sym" cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ int main () { ; return 0; } _ACEOF if ac_fn_c_try_link "$LINENO"; then : lt_cv_ld_exported_symbols_list=yes else lt_cv_ld_exported_symbols_list=no fi rm -f core conftest.err conftest.$ac_objext \ conftest$ac_exeext conftest.$ac_ext LDFLAGS="$save_LDFLAGS" fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $lt_cv_ld_exported_symbols_list" >&5 $as_echo "$lt_cv_ld_exported_symbols_list" >&6; } { $as_echo "$as_me:${as_lineno-$LINENO}: checking for -force_load linker flag" >&5 $as_echo_n "checking for -force_load linker flag... " >&6; } if ${lt_cv_ld_force_load+:} false; then : $as_echo_n "(cached) " >&6 else lt_cv_ld_force_load=no cat > conftest.c << _LT_EOF int forced_loaded() { return 2;} _LT_EOF echo "$LTCC $LTCFLAGS -c -o conftest.o conftest.c" >&5 $LTCC $LTCFLAGS -c -o conftest.o conftest.c 2>&5 echo "$AR cru libconftest.a conftest.o" >&5 $AR cru libconftest.a conftest.o 2>&5 echo "$RANLIB libconftest.a" >&5 $RANLIB libconftest.a 2>&5 cat > conftest.c << _LT_EOF int main() { return 0;} _LT_EOF echo "$LTCC $LTCFLAGS $LDFLAGS -o conftest conftest.c -Wl,-force_load,./libconftest.a" >&5 $LTCC $LTCFLAGS $LDFLAGS -o conftest conftest.c -Wl,-force_load,./libconftest.a 2>conftest.err _lt_result=$? if test -s conftest.err && $GREP force_load conftest.err; then cat conftest.err >&5 elif test -f conftest && test $_lt_result -eq 0 && $GREP forced_load conftest >/dev/null 2>&1 ; then lt_cv_ld_force_load=yes else cat conftest.err >&5 fi rm -f conftest.err libconftest.a conftest conftest.c rm -rf conftest.dSYM fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $lt_cv_ld_force_load" >&5 $as_echo "$lt_cv_ld_force_load" >&6; } case $host_os in rhapsody* | darwin1.[012]) _lt_dar_allow_undefined='${wl}-undefined ${wl}suppress' ;; darwin1.*) _lt_dar_allow_undefined='${wl}-flat_namespace ${wl}-undefined ${wl}suppress' ;; darwin*) # darwin 5.x on # if running on 10.5 or later, the deployment target defaults # to the OS version, if on x86, and 10.4, the deployment # target defaults to 10.4. Don't you love it? case ${MACOSX_DEPLOYMENT_TARGET-10.0},$host in 10.0,*86*-darwin8*|10.0,*-darwin[91]*) _lt_dar_allow_undefined='${wl}-undefined ${wl}dynamic_lookup' ;; 10.[012]*) _lt_dar_allow_undefined='${wl}-flat_namespace ${wl}-undefined ${wl}suppress' ;; 10.*) _lt_dar_allow_undefined='${wl}-undefined ${wl}dynamic_lookup' ;; esac ;; esac if test "$lt_cv_apple_cc_single_mod" = "yes"; then _lt_dar_single_mod='$single_module' fi if test "$lt_cv_ld_exported_symbols_list" = "yes"; then _lt_dar_export_syms=' ${wl}-exported_symbols_list,$output_objdir/${libname}-symbols.expsym' else _lt_dar_export_syms='~$NMEDIT -s $output_objdir/${libname}-symbols.expsym ${lib}' fi if test "$DSYMUTIL" != ":" && test "$lt_cv_ld_force_load" = "no"; then _lt_dsymutil='~$DSYMUTIL $lib || :' else _lt_dsymutil= fi ;; esac ac_ext=c ac_cpp='$CPP $CPPFLAGS' ac_compile='$CC -c $CFLAGS $CPPFLAGS conftest.$ac_ext >&5' ac_link='$CC -o conftest$ac_exeext $CFLAGS $CPPFLAGS $LDFLAGS conftest.$ac_ext $LIBS >&5' ac_compiler_gnu=$ac_cv_c_compiler_gnu { $as_echo "$as_me:${as_lineno-$LINENO}: checking how to run the C preprocessor" >&5 $as_echo_n "checking how to run the C preprocessor... " >&6; } # On Suns, sometimes $CPP names a directory. if test -n "$CPP" && test -d "$CPP"; then CPP= fi if test -z "$CPP"; then if ${ac_cv_prog_CPP+:} false; then : $as_echo_n "(cached) " >&6 else # Double quotes because CPP needs to be expanded for CPP in "$CC -E" "$CC -E -traditional-cpp" "/lib/cpp" do ac_preproc_ok=false for ac_c_preproc_warn_flag in '' yes do # Use a header file that comes with gcc, so configuring glibc # with a fresh cross-compiler works. # Prefer to if __STDC__ is defined, since # exists even on freestanding compilers. # On the NeXT, cc -E runs the code through the compiler's parser, # not just through cpp. "Syntax error" is here to catch this case. cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ #ifdef __STDC__ # include #else # include #endif Syntax error _ACEOF if ac_fn_c_try_cpp "$LINENO"; then : else # Broken: fails on valid input. continue fi rm -f conftest.err conftest.i conftest.$ac_ext # OK, works on sane cases. Now check whether nonexistent headers # can be detected and how. cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ #include _ACEOF if ac_fn_c_try_cpp "$LINENO"; then : # Broken: success on invalid input. continue else # Passes both tests. ac_preproc_ok=: break fi rm -f conftest.err conftest.i conftest.$ac_ext done # Because of `break', _AC_PREPROC_IFELSE's cleaning code was skipped. rm -f conftest.i conftest.err conftest.$ac_ext if $ac_preproc_ok; then : break fi done ac_cv_prog_CPP=$CPP fi CPP=$ac_cv_prog_CPP else ac_cv_prog_CPP=$CPP fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $CPP" >&5 $as_echo "$CPP" >&6; } ac_preproc_ok=false for ac_c_preproc_warn_flag in '' yes do # Use a header file that comes with gcc, so configuring glibc # with a fresh cross-compiler works. # Prefer to if __STDC__ is defined, since # exists even on freestanding compilers. # On the NeXT, cc -E runs the code through the compiler's parser, # not just through cpp. "Syntax error" is here to catch this case. cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ #ifdef __STDC__ # include #else # include #endif Syntax error _ACEOF if ac_fn_c_try_cpp "$LINENO"; then : else # Broken: fails on valid input. continue fi rm -f conftest.err conftest.i conftest.$ac_ext # OK, works on sane cases. Now check whether nonexistent headers # can be detected and how. cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ #include _ACEOF if ac_fn_c_try_cpp "$LINENO"; then : # Broken: success on invalid input. continue else # Passes both tests. ac_preproc_ok=: break fi rm -f conftest.err conftest.i conftest.$ac_ext done # Because of `break', _AC_PREPROC_IFELSE's cleaning code was skipped. rm -f conftest.i conftest.err conftest.$ac_ext if $ac_preproc_ok; then : else { { $as_echo "$as_me:${as_lineno-$LINENO}: error: in \`$ac_pwd':" >&5 $as_echo "$as_me: error: in \`$ac_pwd':" >&2;} as_fn_error $? "C preprocessor \"$CPP\" fails sanity check See \`config.log' for more details" "$LINENO" 5; } fi ac_ext=c ac_cpp='$CPP $CPPFLAGS' ac_compile='$CC -c $CFLAGS $CPPFLAGS conftest.$ac_ext >&5' ac_link='$CC -o conftest$ac_exeext $CFLAGS $CPPFLAGS $LDFLAGS conftest.$ac_ext $LIBS >&5' ac_compiler_gnu=$ac_cv_c_compiler_gnu { $as_echo "$as_me:${as_lineno-$LINENO}: checking for ANSI C header files" >&5 $as_echo_n "checking for ANSI C header files... " >&6; } if ${ac_cv_header_stdc+:} false; then : $as_echo_n "(cached) " >&6 else cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ #include #include #include #include int main () { ; return 0; } _ACEOF if ac_fn_c_try_compile "$LINENO"; then : ac_cv_header_stdc=yes else ac_cv_header_stdc=no fi rm -f core conftest.err conftest.$ac_objext conftest.$ac_ext if test $ac_cv_header_stdc = yes; then # SunOS 4.x string.h does not declare mem*, contrary to ANSI. cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ #include _ACEOF if (eval "$ac_cpp conftest.$ac_ext") 2>&5 | $EGREP "memchr" >/dev/null 2>&1; then : else ac_cv_header_stdc=no fi rm -f conftest* fi if test $ac_cv_header_stdc = yes; then # ISC 2.0.2 stdlib.h does not declare free, contrary to ANSI. cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ #include _ACEOF if (eval "$ac_cpp conftest.$ac_ext") 2>&5 | $EGREP "free" >/dev/null 2>&1; then : else ac_cv_header_stdc=no fi rm -f conftest* fi if test $ac_cv_header_stdc = yes; then # /bin/cc in Irix-4.0.5 gets non-ANSI ctype macros unless using -ansi. if test "$cross_compiling" = yes; then : : else cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ #include #include #if ((' ' & 0x0FF) == 0x020) # define ISLOWER(c) ('a' <= (c) && (c) <= 'z') # define TOUPPER(c) (ISLOWER(c) ? 'A' + ((c) - 'a') : (c)) #else # define ISLOWER(c) \ (('a' <= (c) && (c) <= 'i') \ || ('j' <= (c) && (c) <= 'r') \ || ('s' <= (c) && (c) <= 'z')) # define TOUPPER(c) (ISLOWER(c) ? ((c) | 0x40) : (c)) #endif #define XOR(e, f) (((e) && !(f)) || (!(e) && (f))) int main () { int i; for (i = 0; i < 256; i++) if (XOR (islower (i), ISLOWER (i)) || toupper (i) != TOUPPER (i)) return 2; return 0; } _ACEOF if ac_fn_c_try_run "$LINENO"; then : else ac_cv_header_stdc=no fi rm -f core *.core core.conftest.* gmon.out bb.out conftest$ac_exeext \ conftest.$ac_objext conftest.beam conftest.$ac_ext fi fi fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_cv_header_stdc" >&5 $as_echo "$ac_cv_header_stdc" >&6; } if test $ac_cv_header_stdc = yes; then $as_echo "#define STDC_HEADERS 1" >>confdefs.h fi # On IRIX 5.3, sys/types and inttypes.h are conflicting. for ac_header in sys/types.h sys/stat.h stdlib.h string.h memory.h strings.h \ inttypes.h stdint.h unistd.h do : as_ac_Header=`$as_echo "ac_cv_header_$ac_header" | $as_tr_sh` ac_fn_c_check_header_compile "$LINENO" "$ac_header" "$as_ac_Header" "$ac_includes_default " if eval test \"x\$"$as_ac_Header"\" = x"yes"; then : cat >>confdefs.h <<_ACEOF #define `$as_echo "HAVE_$ac_header" | $as_tr_cpp` 1 _ACEOF fi done for ac_header in dlfcn.h do : ac_fn_c_check_header_compile "$LINENO" "dlfcn.h" "ac_cv_header_dlfcn_h" "$ac_includes_default " if test "x$ac_cv_header_dlfcn_h" = xyes; then : cat >>confdefs.h <<_ACEOF #define HAVE_DLFCN_H 1 _ACEOF fi done # Set options enable_dlopen=no # Check whether --enable-shared was given. if test "${enable_shared+set}" = set; then : enableval=$enable_shared; p=${PACKAGE-default} case $enableval in yes) enable_shared=yes ;; no) enable_shared=no ;; *) enable_shared=no # Look at the argument we got. We use all the common list separators. lt_save_ifs="$IFS"; IFS="${IFS}$PATH_SEPARATOR," for pkg in $enableval; do IFS="$lt_save_ifs" if test "X$pkg" = "X$p"; then enable_shared=yes fi done IFS="$lt_save_ifs" ;; esac else enable_shared=yes fi # Check whether --enable-static was given. if test "${enable_static+set}" = set; then : enableval=$enable_static; p=${PACKAGE-default} case $enableval in yes) enable_static=yes ;; no) enable_static=no ;; *) enable_static=no # Look at the argument we got. We use all the common list separators. lt_save_ifs="$IFS"; IFS="${IFS}$PATH_SEPARATOR," for pkg in $enableval; do IFS="$lt_save_ifs" if test "X$pkg" = "X$p"; then enable_static=yes fi done IFS="$lt_save_ifs" ;; esac else enable_static=yes fi # Check whether --with-pic was given. if test "${with_pic+set}" = set; then : withval=$with_pic; lt_p=${PACKAGE-default} case $withval in yes|no) pic_mode=$withval ;; *) pic_mode=default # Look at the argument we got. We use all the common list separators. lt_save_ifs="$IFS"; IFS="${IFS}$PATH_SEPARATOR," for lt_pkg in $withval; do IFS="$lt_save_ifs" if test "X$lt_pkg" = "X$lt_p"; then pic_mode=yes fi done IFS="$lt_save_ifs" ;; esac else pic_mode=default fi test -z "$pic_mode" && pic_mode=default # Check whether --enable-fast-install was given. if test "${enable_fast_install+set}" = set; then : enableval=$enable_fast_install; p=${PACKAGE-default} case $enableval in yes) enable_fast_install=yes ;; no) enable_fast_install=no ;; *) enable_fast_install=no # Look at the argument we got. We use all the common list separators. lt_save_ifs="$IFS"; IFS="${IFS}$PATH_SEPARATOR," for pkg in $enableval; do IFS="$lt_save_ifs" if test "X$pkg" = "X$p"; then enable_fast_install=yes fi done IFS="$lt_save_ifs" ;; esac else enable_fast_install=yes fi # This can be used to rebuild libtool when needed LIBTOOL_DEPS="$ltmain" # Always use our own libtool. LIBTOOL='$(SHELL) $(top_builddir)/libtool' test -z "$LN_S" && LN_S="ln -s" if test -n "${ZSH_VERSION+set}" ; then setopt NO_GLOB_SUBST fi { $as_echo "$as_me:${as_lineno-$LINENO}: checking for objdir" >&5 $as_echo_n "checking for objdir... " >&6; } if ${lt_cv_objdir+:} false; then : $as_echo_n "(cached) " >&6 else rm -f .libs 2>/dev/null mkdir .libs 2>/dev/null if test -d .libs; then lt_cv_objdir=.libs else # MS-DOS does not allow filenames that begin with a dot. lt_cv_objdir=_libs fi rmdir .libs 2>/dev/null fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $lt_cv_objdir" >&5 $as_echo "$lt_cv_objdir" >&6; } objdir=$lt_cv_objdir cat >>confdefs.h <<_ACEOF #define LT_OBJDIR "$lt_cv_objdir/" _ACEOF case $host_os in aix3*) # AIX sometimes has problems with the GCC collect2 program. For some # reason, if we set the COLLECT_NAMES environment variable, the problems # vanish in a puff of smoke. if test "X${COLLECT_NAMES+set}" != Xset; then COLLECT_NAMES= export COLLECT_NAMES fi ;; esac # Global variables: ofile=libtool can_build_shared=yes # All known linkers require a `.a' archive for static linking (except MSVC, # which needs '.lib'). libext=a with_gnu_ld="$lt_cv_prog_gnu_ld" old_CC="$CC" old_CFLAGS="$CFLAGS" # Set sane defaults for various variables test -z "$CC" && CC=cc test -z "$LTCC" && LTCC=$CC test -z "$LTCFLAGS" && LTCFLAGS=$CFLAGS test -z "$LD" && LD=ld test -z "$ac_objext" && ac_objext=o for cc_temp in $compiler""; do case $cc_temp in compile | *[\\/]compile | ccache | *[\\/]ccache ) ;; distcc | *[\\/]distcc | purify | *[\\/]purify ) ;; \-*) ;; *) break;; esac done cc_basename=`$ECHO "$cc_temp" | $SED "s%.*/%%; s%^$host_alias-%%"` # Only perform the check for file, if the check method requires it test -z "$MAGIC_CMD" && MAGIC_CMD=file case $deplibs_check_method in file_magic*) if test "$file_magic_cmd" = '$MAGIC_CMD'; then { $as_echo "$as_me:${as_lineno-$LINENO}: checking for ${ac_tool_prefix}file" >&5 $as_echo_n "checking for ${ac_tool_prefix}file... " >&6; } if ${lt_cv_path_MAGIC_CMD+:} false; then : $as_echo_n "(cached) " >&6 else case $MAGIC_CMD in [\\/*] | ?:[\\/]*) lt_cv_path_MAGIC_CMD="$MAGIC_CMD" # Let the user override the test with a path. ;; *) lt_save_MAGIC_CMD="$MAGIC_CMD" lt_save_ifs="$IFS"; IFS=$PATH_SEPARATOR ac_dummy="/usr/bin$PATH_SEPARATOR$PATH" for ac_dir in $ac_dummy; do IFS="$lt_save_ifs" test -z "$ac_dir" && ac_dir=. if test -f $ac_dir/${ac_tool_prefix}file; then lt_cv_path_MAGIC_CMD="$ac_dir/${ac_tool_prefix}file" if test -n "$file_magic_test_file"; then case $deplibs_check_method in "file_magic "*) file_magic_regex=`expr "$deplibs_check_method" : "file_magic \(.*\)"` MAGIC_CMD="$lt_cv_path_MAGIC_CMD" if eval $file_magic_cmd \$file_magic_test_file 2> /dev/null | $EGREP "$file_magic_regex" > /dev/null; then : else cat <<_LT_EOF 1>&2 *** Warning: the command libtool uses to detect shared libraries, *** $file_magic_cmd, produces output that libtool cannot recognize. *** The result is that libtool may fail to recognize shared libraries *** as such. This will affect the creation of libtool libraries that *** depend on shared libraries, but programs linked with such libtool *** libraries will work regardless of this problem. Nevertheless, you *** may want to report the problem to your system manager and/or to *** bug-libtool@gnu.org _LT_EOF fi ;; esac fi break fi done IFS="$lt_save_ifs" MAGIC_CMD="$lt_save_MAGIC_CMD" ;; esac fi MAGIC_CMD="$lt_cv_path_MAGIC_CMD" if test -n "$MAGIC_CMD"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $MAGIC_CMD" >&5 $as_echo "$MAGIC_CMD" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi if test -z "$lt_cv_path_MAGIC_CMD"; then if test -n "$ac_tool_prefix"; then { $as_echo "$as_me:${as_lineno-$LINENO}: checking for file" >&5 $as_echo_n "checking for file... " >&6; } if ${lt_cv_path_MAGIC_CMD+:} false; then : $as_echo_n "(cached) " >&6 else case $MAGIC_CMD in [\\/*] | ?:[\\/]*) lt_cv_path_MAGIC_CMD="$MAGIC_CMD" # Let the user override the test with a path. ;; *) lt_save_MAGIC_CMD="$MAGIC_CMD" lt_save_ifs="$IFS"; IFS=$PATH_SEPARATOR ac_dummy="/usr/bin$PATH_SEPARATOR$PATH" for ac_dir in $ac_dummy; do IFS="$lt_save_ifs" test -z "$ac_dir" && ac_dir=. if test -f $ac_dir/file; then lt_cv_path_MAGIC_CMD="$ac_dir/file" if test -n "$file_magic_test_file"; then case $deplibs_check_method in "file_magic "*) file_magic_regex=`expr "$deplibs_check_method" : "file_magic \(.*\)"` MAGIC_CMD="$lt_cv_path_MAGIC_CMD" if eval $file_magic_cmd \$file_magic_test_file 2> /dev/null | $EGREP "$file_magic_regex" > /dev/null; then : else cat <<_LT_EOF 1>&2 *** Warning: the command libtool uses to detect shared libraries, *** $file_magic_cmd, produces output that libtool cannot recognize. *** The result is that libtool may fail to recognize shared libraries *** as such. This will affect the creation of libtool libraries that *** depend on shared libraries, but programs linked with such libtool *** libraries will work regardless of this problem. Nevertheless, you *** may want to report the problem to your system manager and/or to *** bug-libtool@gnu.org _LT_EOF fi ;; esac fi break fi done IFS="$lt_save_ifs" MAGIC_CMD="$lt_save_MAGIC_CMD" ;; esac fi MAGIC_CMD="$lt_cv_path_MAGIC_CMD" if test -n "$MAGIC_CMD"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $MAGIC_CMD" >&5 $as_echo "$MAGIC_CMD" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi else MAGIC_CMD=: fi fi fi ;; esac # Use C for the default configuration in the libtool script lt_save_CC="$CC" ac_ext=c ac_cpp='$CPP $CPPFLAGS' ac_compile='$CC -c $CFLAGS $CPPFLAGS conftest.$ac_ext >&5' ac_link='$CC -o conftest$ac_exeext $CFLAGS $CPPFLAGS $LDFLAGS conftest.$ac_ext $LIBS >&5' ac_compiler_gnu=$ac_cv_c_compiler_gnu # Source file extension for C test sources. ac_ext=c # Object file extension for compiled C test sources. objext=o objext=$objext # Code to be used in simple compile tests lt_simple_compile_test_code="int some_variable = 0;" # Code to be used in simple link tests lt_simple_link_test_code='int main(){return(0);}' # If no C compiler was specified, use CC. LTCC=${LTCC-"$CC"} # If no C compiler flags were specified, use CFLAGS. LTCFLAGS=${LTCFLAGS-"$CFLAGS"} # Allow CC to be a program name with arguments. compiler=$CC # Save the default compiler, since it gets overwritten when the other # tags are being tested, and _LT_TAGVAR(compiler, []) is a NOP. compiler_DEFAULT=$CC # save warnings/boilerplate of simple test code ac_outfile=conftest.$ac_objext echo "$lt_simple_compile_test_code" >conftest.$ac_ext eval "$ac_compile" 2>&1 >/dev/null | $SED '/^$/d; /^ *+/d' >conftest.err _lt_compiler_boilerplate=`cat conftest.err` $RM conftest* ac_outfile=conftest.$ac_objext echo "$lt_simple_link_test_code" >conftest.$ac_ext eval "$ac_link" 2>&1 >/dev/null | $SED '/^$/d; /^ *+/d' >conftest.err _lt_linker_boilerplate=`cat conftest.err` $RM -r conftest* ## CAVEAT EMPTOR: ## There is no encapsulation within the following macros, do not change ## the running order or otherwise move them around unless you know exactly ## what you are doing... if test -n "$compiler"; then lt_prog_compiler_no_builtin_flag= if test "$GCC" = yes; then case $cc_basename in nvcc*) lt_prog_compiler_no_builtin_flag=' -Xcompiler -fno-builtin' ;; *) lt_prog_compiler_no_builtin_flag=' -fno-builtin' ;; esac { $as_echo "$as_me:${as_lineno-$LINENO}: checking if $compiler supports -fno-rtti -fno-exceptions" >&5 $as_echo_n "checking if $compiler supports -fno-rtti -fno-exceptions... " >&6; } if ${lt_cv_prog_compiler_rtti_exceptions+:} false; then : $as_echo_n "(cached) " >&6 else lt_cv_prog_compiler_rtti_exceptions=no ac_outfile=conftest.$ac_objext echo "$lt_simple_compile_test_code" > conftest.$ac_ext lt_compiler_flag="-fno-rtti -fno-exceptions" # Insert the option either (1) after the last *FLAGS variable, or # (2) before a word containing "conftest.", or (3) at the end. # Note that $ac_compile itself does not contain backslashes and begins # with a dollar sign (not a hyphen), so the echo should work correctly. # The option is referenced via a variable to avoid confusing sed. lt_compile=`echo "$ac_compile" | $SED \ -e 's:.*FLAGS}\{0,1\} :&$lt_compiler_flag :; t' \ -e 's: [^ ]*conftest\.: $lt_compiler_flag&:; t' \ -e 's:$: $lt_compiler_flag:'` (eval echo "\"\$as_me:$LINENO: $lt_compile\"" >&5) (eval "$lt_compile" 2>conftest.err) ac_status=$? cat conftest.err >&5 echo "$as_me:$LINENO: \$? = $ac_status" >&5 if (exit $ac_status) && test -s "$ac_outfile"; then # The compiler can only warn and ignore the option if not recognized # So say no if there are warnings other than the usual output. $ECHO "$_lt_compiler_boilerplate" | $SED '/^$/d' >conftest.exp $SED '/^$/d; /^ *+/d' conftest.err >conftest.er2 if test ! -s conftest.er2 || diff conftest.exp conftest.er2 >/dev/null; then lt_cv_prog_compiler_rtti_exceptions=yes fi fi $RM conftest* fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $lt_cv_prog_compiler_rtti_exceptions" >&5 $as_echo "$lt_cv_prog_compiler_rtti_exceptions" >&6; } if test x"$lt_cv_prog_compiler_rtti_exceptions" = xyes; then lt_prog_compiler_no_builtin_flag="$lt_prog_compiler_no_builtin_flag -fno-rtti -fno-exceptions" else : fi fi lt_prog_compiler_wl= lt_prog_compiler_pic= lt_prog_compiler_static= if test "$GCC" = yes; then lt_prog_compiler_wl='-Wl,' lt_prog_compiler_static='-static' case $host_os in aix*) # All AIX code is PIC. if test "$host_cpu" = ia64; then # AIX 5 now supports IA64 processor lt_prog_compiler_static='-Bstatic' fi ;; amigaos*) case $host_cpu in powerpc) # see comment about AmigaOS4 .so support lt_prog_compiler_pic='-fPIC' ;; m68k) # FIXME: we need at least 68020 code to build shared libraries, but # adding the `-m68020' flag to GCC prevents building anything better, # like `-m68040'. lt_prog_compiler_pic='-m68020 -resident32 -malways-restore-a4' ;; esac ;; beos* | irix5* | irix6* | nonstopux* | osf3* | osf4* | osf5*) # PIC is the default for these OSes. ;; mingw* | cygwin* | pw32* | os2* | cegcc*) # This hack is so that the source file can tell whether it is being # built for inclusion in a dll (and should export symbols for example). # Although the cygwin gcc ignores -fPIC, still need this for old-style # (--disable-auto-import) libraries lt_prog_compiler_pic='-DDLL_EXPORT' ;; darwin* | rhapsody*) # PIC is the default on this platform # Common symbols not allowed in MH_DYLIB files lt_prog_compiler_pic='-fno-common' ;; haiku*) # PIC is the default for Haiku. # The "-static" flag exists, but is broken. lt_prog_compiler_static= ;; hpux*) # PIC is the default for 64-bit PA HP-UX, but not for 32-bit # PA HP-UX. On IA64 HP-UX, PIC is the default but the pic flag # sets the default TLS model and affects inlining. case $host_cpu in hppa*64*) # +Z the default ;; *) lt_prog_compiler_pic='-fPIC' ;; esac ;; interix[3-9]*) # Interix 3.x gcc -fpic/-fPIC options generate broken code. # Instead, we relocate shared libraries at runtime. ;; msdosdjgpp*) # Just because we use GCC doesn't mean we suddenly get shared libraries # on systems that don't support them. lt_prog_compiler_can_build_shared=no enable_shared=no ;; *nto* | *qnx*) # QNX uses GNU C++, but need to define -shared option too, otherwise # it will coredump. lt_prog_compiler_pic='-fPIC -shared' ;; sysv4*MP*) if test -d /usr/nec; then lt_prog_compiler_pic=-Kconform_pic fi ;; *) lt_prog_compiler_pic='-fPIC' ;; esac case $cc_basename in nvcc*) # Cuda Compiler Driver 2.2 lt_prog_compiler_wl='-Xlinker ' if test -n "$lt_prog_compiler_pic"; then lt_prog_compiler_pic="-Xcompiler $lt_prog_compiler_pic" fi ;; esac else # PORTME Check for flag to pass linker flags through the system compiler. case $host_os in aix*) lt_prog_compiler_wl='-Wl,' if test "$host_cpu" = ia64; then # AIX 5 now supports IA64 processor lt_prog_compiler_static='-Bstatic' else lt_prog_compiler_static='-bnso -bI:/lib/syscalls.exp' fi ;; mingw* | cygwin* | pw32* | os2* | cegcc*) # This hack is so that the source file can tell whether it is being # built for inclusion in a dll (and should export symbols for example). lt_prog_compiler_pic='-DDLL_EXPORT' ;; hpux9* | hpux10* | hpux11*) lt_prog_compiler_wl='-Wl,' # PIC is the default for IA64 HP-UX and 64-bit HP-UX, but # not for PA HP-UX. case $host_cpu in hppa*64*|ia64*) # +Z the default ;; *) lt_prog_compiler_pic='+Z' ;; esac # Is there a better lt_prog_compiler_static that works with the bundled CC? lt_prog_compiler_static='${wl}-a ${wl}archive' ;; irix5* | irix6* | nonstopux*) lt_prog_compiler_wl='-Wl,' # PIC (with -KPIC) is the default. lt_prog_compiler_static='-non_shared' ;; linux* | k*bsd*-gnu | kopensolaris*-gnu | gnu*) case $cc_basename in # old Intel for x86_64 which still supported -KPIC. ecc*) lt_prog_compiler_wl='-Wl,' lt_prog_compiler_pic='-KPIC' lt_prog_compiler_static='-static' ;; # icc used to be incompatible with GCC. # ICC 10 doesn't accept -KPIC any more. icc* | ifort*) lt_prog_compiler_wl='-Wl,' lt_prog_compiler_pic='-fPIC' lt_prog_compiler_static='-static' ;; # Lahey Fortran 8.1. lf95*) lt_prog_compiler_wl='-Wl,' lt_prog_compiler_pic='--shared' lt_prog_compiler_static='--static' ;; nagfor*) # NAG Fortran compiler lt_prog_compiler_wl='-Wl,-Wl,,' lt_prog_compiler_pic='-PIC' lt_prog_compiler_static='-Bstatic' ;; pgcc* | pgf77* | pgf90* | pgf95* | pgfortran*) # Portland Group compilers (*not* the Pentium gcc compiler, # which looks to be a dead project) lt_prog_compiler_wl='-Wl,' lt_prog_compiler_pic='-fpic' lt_prog_compiler_static='-Bstatic' ;; ccc*) lt_prog_compiler_wl='-Wl,' # All Alpha code is PIC. lt_prog_compiler_static='-non_shared' ;; xl* | bgxl* | bgf* | mpixl*) # IBM XL C 8.0/Fortran 10.1, 11.1 on PPC and BlueGene lt_prog_compiler_wl='-Wl,' lt_prog_compiler_pic='-qpic' lt_prog_compiler_static='-qstaticlink' ;; *) case `$CC -V 2>&1 | sed 5q` in *Sun\ Ceres\ Fortran* | *Sun*Fortran*\ [1-7].* | *Sun*Fortran*\ 8.[0-3]*) # Sun Fortran 8.3 passes all unrecognized flags to the linker lt_prog_compiler_pic='-KPIC' lt_prog_compiler_static='-Bstatic' lt_prog_compiler_wl='' ;; *Sun\ F* | *Sun*Fortran*) lt_prog_compiler_pic='-KPIC' lt_prog_compiler_static='-Bstatic' lt_prog_compiler_wl='-Qoption ld ' ;; *Sun\ C*) # Sun C 5.9 lt_prog_compiler_pic='-KPIC' lt_prog_compiler_static='-Bstatic' lt_prog_compiler_wl='-Wl,' ;; *Intel*\ [CF]*Compiler*) lt_prog_compiler_wl='-Wl,' lt_prog_compiler_pic='-fPIC' lt_prog_compiler_static='-static' ;; *Portland\ Group*) lt_prog_compiler_wl='-Wl,' lt_prog_compiler_pic='-fpic' lt_prog_compiler_static='-Bstatic' ;; esac ;; esac ;; newsos6) lt_prog_compiler_pic='-KPIC' lt_prog_compiler_static='-Bstatic' ;; *nto* | *qnx*) # QNX uses GNU C++, but need to define -shared option too, otherwise # it will coredump. lt_prog_compiler_pic='-fPIC -shared' ;; osf3* | osf4* | osf5*) lt_prog_compiler_wl='-Wl,' # All OSF/1 code is PIC. lt_prog_compiler_static='-non_shared' ;; rdos*) lt_prog_compiler_static='-non_shared' ;; solaris*) lt_prog_compiler_pic='-KPIC' lt_prog_compiler_static='-Bstatic' case $cc_basename in f77* | f90* | f95* | sunf77* | sunf90* | sunf95*) lt_prog_compiler_wl='-Qoption ld ';; *) lt_prog_compiler_wl='-Wl,';; esac ;; sunos4*) lt_prog_compiler_wl='-Qoption ld ' lt_prog_compiler_pic='-PIC' lt_prog_compiler_static='-Bstatic' ;; sysv4 | sysv4.2uw2* | sysv4.3*) lt_prog_compiler_wl='-Wl,' lt_prog_compiler_pic='-KPIC' lt_prog_compiler_static='-Bstatic' ;; sysv4*MP*) if test -d /usr/nec ;then lt_prog_compiler_pic='-Kconform_pic' lt_prog_compiler_static='-Bstatic' fi ;; sysv5* | unixware* | sco3.2v5* | sco5v6* | OpenUNIX*) lt_prog_compiler_wl='-Wl,' lt_prog_compiler_pic='-KPIC' lt_prog_compiler_static='-Bstatic' ;; unicos*) lt_prog_compiler_wl='-Wl,' lt_prog_compiler_can_build_shared=no ;; uts4*) lt_prog_compiler_pic='-pic' lt_prog_compiler_static='-Bstatic' ;; *) lt_prog_compiler_can_build_shared=no ;; esac fi case $host_os in # For platforms which do not support PIC, -DPIC is meaningless: *djgpp*) lt_prog_compiler_pic= ;; *) lt_prog_compiler_pic="$lt_prog_compiler_pic -DPIC" ;; esac { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $compiler option to produce PIC" >&5 $as_echo_n "checking for $compiler option to produce PIC... " >&6; } if ${lt_cv_prog_compiler_pic+:} false; then : $as_echo_n "(cached) " >&6 else lt_cv_prog_compiler_pic=$lt_prog_compiler_pic fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $lt_cv_prog_compiler_pic" >&5 $as_echo "$lt_cv_prog_compiler_pic" >&6; } lt_prog_compiler_pic=$lt_cv_prog_compiler_pic # # Check to make sure the PIC flag actually works. # if test -n "$lt_prog_compiler_pic"; then { $as_echo "$as_me:${as_lineno-$LINENO}: checking if $compiler PIC flag $lt_prog_compiler_pic works" >&5 $as_echo_n "checking if $compiler PIC flag $lt_prog_compiler_pic works... " >&6; } if ${lt_cv_prog_compiler_pic_works+:} false; then : $as_echo_n "(cached) " >&6 else lt_cv_prog_compiler_pic_works=no ac_outfile=conftest.$ac_objext echo "$lt_simple_compile_test_code" > conftest.$ac_ext lt_compiler_flag="$lt_prog_compiler_pic -DPIC" # Insert the option either (1) after the last *FLAGS variable, or # (2) before a word containing "conftest.", or (3) at the end. # Note that $ac_compile itself does not contain backslashes and begins # with a dollar sign (not a hyphen), so the echo should work correctly. # The option is referenced via a variable to avoid confusing sed. lt_compile=`echo "$ac_compile" | $SED \ -e 's:.*FLAGS}\{0,1\} :&$lt_compiler_flag :; t' \ -e 's: [^ ]*conftest\.: $lt_compiler_flag&:; t' \ -e 's:$: $lt_compiler_flag:'` (eval echo "\"\$as_me:$LINENO: $lt_compile\"" >&5) (eval "$lt_compile" 2>conftest.err) ac_status=$? cat conftest.err >&5 echo "$as_me:$LINENO: \$? = $ac_status" >&5 if (exit $ac_status) && test -s "$ac_outfile"; then # The compiler can only warn and ignore the option if not recognized # So say no if there are warnings other than the usual output. $ECHO "$_lt_compiler_boilerplate" | $SED '/^$/d' >conftest.exp $SED '/^$/d; /^ *+/d' conftest.err >conftest.er2 if test ! -s conftest.er2 || diff conftest.exp conftest.er2 >/dev/null; then lt_cv_prog_compiler_pic_works=yes fi fi $RM conftest* fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $lt_cv_prog_compiler_pic_works" >&5 $as_echo "$lt_cv_prog_compiler_pic_works" >&6; } if test x"$lt_cv_prog_compiler_pic_works" = xyes; then case $lt_prog_compiler_pic in "" | " "*) ;; *) lt_prog_compiler_pic=" $lt_prog_compiler_pic" ;; esac else lt_prog_compiler_pic= lt_prog_compiler_can_build_shared=no fi fi # # Check to make sure the static flag actually works. # wl=$lt_prog_compiler_wl eval lt_tmp_static_flag=\"$lt_prog_compiler_static\" { $as_echo "$as_me:${as_lineno-$LINENO}: checking if $compiler static flag $lt_tmp_static_flag works" >&5 $as_echo_n "checking if $compiler static flag $lt_tmp_static_flag works... " >&6; } if ${lt_cv_prog_compiler_static_works+:} false; then : $as_echo_n "(cached) " >&6 else lt_cv_prog_compiler_static_works=no save_LDFLAGS="$LDFLAGS" LDFLAGS="$LDFLAGS $lt_tmp_static_flag" echo "$lt_simple_link_test_code" > conftest.$ac_ext if (eval $ac_link 2>conftest.err) && test -s conftest$ac_exeext; then # The linker can only warn and ignore the option if not recognized # So say no if there are warnings if test -s conftest.err; then # Append any errors to the config.log. cat conftest.err 1>&5 $ECHO "$_lt_linker_boilerplate" | $SED '/^$/d' > conftest.exp $SED '/^$/d; /^ *+/d' conftest.err >conftest.er2 if diff conftest.exp conftest.er2 >/dev/null; then lt_cv_prog_compiler_static_works=yes fi else lt_cv_prog_compiler_static_works=yes fi fi $RM -r conftest* LDFLAGS="$save_LDFLAGS" fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $lt_cv_prog_compiler_static_works" >&5 $as_echo "$lt_cv_prog_compiler_static_works" >&6; } if test x"$lt_cv_prog_compiler_static_works" = xyes; then : else lt_prog_compiler_static= fi { $as_echo "$as_me:${as_lineno-$LINENO}: checking if $compiler supports -c -o file.$ac_objext" >&5 $as_echo_n "checking if $compiler supports -c -o file.$ac_objext... " >&6; } if ${lt_cv_prog_compiler_c_o+:} false; then : $as_echo_n "(cached) " >&6 else lt_cv_prog_compiler_c_o=no $RM -r conftest 2>/dev/null mkdir conftest cd conftest mkdir out echo "$lt_simple_compile_test_code" > conftest.$ac_ext lt_compiler_flag="-o out/conftest2.$ac_objext" # Insert the option either (1) after the last *FLAGS variable, or # (2) before a word containing "conftest.", or (3) at the end. # Note that $ac_compile itself does not contain backslashes and begins # with a dollar sign (not a hyphen), so the echo should work correctly. lt_compile=`echo "$ac_compile" | $SED \ -e 's:.*FLAGS}\{0,1\} :&$lt_compiler_flag :; t' \ -e 's: [^ ]*conftest\.: $lt_compiler_flag&:; t' \ -e 's:$: $lt_compiler_flag:'` (eval echo "\"\$as_me:$LINENO: $lt_compile\"" >&5) (eval "$lt_compile" 2>out/conftest.err) ac_status=$? cat out/conftest.err >&5 echo "$as_me:$LINENO: \$? = $ac_status" >&5 if (exit $ac_status) && test -s out/conftest2.$ac_objext then # The compiler can only warn and ignore the option if not recognized # So say no if there are warnings $ECHO "$_lt_compiler_boilerplate" | $SED '/^$/d' > out/conftest.exp $SED '/^$/d; /^ *+/d' out/conftest.err >out/conftest.er2 if test ! -s out/conftest.er2 || diff out/conftest.exp out/conftest.er2 >/dev/null; then lt_cv_prog_compiler_c_o=yes fi fi chmod u+w . 2>&5 $RM conftest* # SGI C++ compiler will create directory out/ii_files/ for # template instantiation test -d out/ii_files && $RM out/ii_files/* && rmdir out/ii_files $RM out/* && rmdir out cd .. $RM -r conftest $RM conftest* fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $lt_cv_prog_compiler_c_o" >&5 $as_echo "$lt_cv_prog_compiler_c_o" >&6; } { $as_echo "$as_me:${as_lineno-$LINENO}: checking if $compiler supports -c -o file.$ac_objext" >&5 $as_echo_n "checking if $compiler supports -c -o file.$ac_objext... " >&6; } if ${lt_cv_prog_compiler_c_o+:} false; then : $as_echo_n "(cached) " >&6 else lt_cv_prog_compiler_c_o=no $RM -r conftest 2>/dev/null mkdir conftest cd conftest mkdir out echo "$lt_simple_compile_test_code" > conftest.$ac_ext lt_compiler_flag="-o out/conftest2.$ac_objext" # Insert the option either (1) after the last *FLAGS variable, or # (2) before a word containing "conftest.", or (3) at the end. # Note that $ac_compile itself does not contain backslashes and begins # with a dollar sign (not a hyphen), so the echo should work correctly. lt_compile=`echo "$ac_compile" | $SED \ -e 's:.*FLAGS}\{0,1\} :&$lt_compiler_flag :; t' \ -e 's: [^ ]*conftest\.: $lt_compiler_flag&:; t' \ -e 's:$: $lt_compiler_flag:'` (eval echo "\"\$as_me:$LINENO: $lt_compile\"" >&5) (eval "$lt_compile" 2>out/conftest.err) ac_status=$? cat out/conftest.err >&5 echo "$as_me:$LINENO: \$? = $ac_status" >&5 if (exit $ac_status) && test -s out/conftest2.$ac_objext then # The compiler can only warn and ignore the option if not recognized # So say no if there are warnings $ECHO "$_lt_compiler_boilerplate" | $SED '/^$/d' > out/conftest.exp $SED '/^$/d; /^ *+/d' out/conftest.err >out/conftest.er2 if test ! -s out/conftest.er2 || diff out/conftest.exp out/conftest.er2 >/dev/null; then lt_cv_prog_compiler_c_o=yes fi fi chmod u+w . 2>&5 $RM conftest* # SGI C++ compiler will create directory out/ii_files/ for # template instantiation test -d out/ii_files && $RM out/ii_files/* && rmdir out/ii_files $RM out/* && rmdir out cd .. $RM -r conftest $RM conftest* fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $lt_cv_prog_compiler_c_o" >&5 $as_echo "$lt_cv_prog_compiler_c_o" >&6; } hard_links="nottested" if test "$lt_cv_prog_compiler_c_o" = no && test "$need_locks" != no; then # do not overwrite the value of need_locks provided by the user { $as_echo "$as_me:${as_lineno-$LINENO}: checking if we can lock with hard links" >&5 $as_echo_n "checking if we can lock with hard links... " >&6; } hard_links=yes $RM conftest* ln conftest.a conftest.b 2>/dev/null && hard_links=no touch conftest.a ln conftest.a conftest.b 2>&5 || hard_links=no ln conftest.a conftest.b 2>/dev/null && hard_links=no { $as_echo "$as_me:${as_lineno-$LINENO}: result: $hard_links" >&5 $as_echo "$hard_links" >&6; } if test "$hard_links" = no; then { $as_echo "$as_me:${as_lineno-$LINENO}: WARNING: \`$CC' does not support \`-c -o', so \`make -j' may be unsafe" >&5 $as_echo "$as_me: WARNING: \`$CC' does not support \`-c -o', so \`make -j' may be unsafe" >&2;} need_locks=warn fi else need_locks=no fi { $as_echo "$as_me:${as_lineno-$LINENO}: checking whether the $compiler linker ($LD) supports shared libraries" >&5 $as_echo_n "checking whether the $compiler linker ($LD) supports shared libraries... " >&6; } runpath_var= allow_undefined_flag= always_export_symbols=no archive_cmds= archive_expsym_cmds= compiler_needs_object=no enable_shared_with_static_runtimes=no export_dynamic_flag_spec= export_symbols_cmds='$NM $libobjs $convenience | $global_symbol_pipe | $SED '\''s/.* //'\'' | sort | uniq > $export_symbols' hardcode_automatic=no hardcode_direct=no hardcode_direct_absolute=no hardcode_libdir_flag_spec= hardcode_libdir_separator= hardcode_minus_L=no hardcode_shlibpath_var=unsupported inherit_rpath=no link_all_deplibs=unknown module_cmds= module_expsym_cmds= old_archive_from_new_cmds= old_archive_from_expsyms_cmds= thread_safe_flag_spec= whole_archive_flag_spec= # include_expsyms should be a list of space-separated symbols to be *always* # included in the symbol list include_expsyms= # exclude_expsyms can be an extended regexp of symbols to exclude # it will be wrapped by ` (' and `)$', so one must not match beginning or # end of line. Example: `a|bc|.*d.*' will exclude the symbols `a' and `bc', # as well as any symbol that contains `d'. exclude_expsyms='_GLOBAL_OFFSET_TABLE_|_GLOBAL__F[ID]_.*' # Although _GLOBAL_OFFSET_TABLE_ is a valid symbol C name, most a.out # platforms (ab)use it in PIC code, but their linkers get confused if # the symbol is explicitly referenced. Since portable code cannot # rely on this symbol name, it's probably fine to never include it in # preloaded symbol tables. # Exclude shared library initialization/finalization symbols. extract_expsyms_cmds= case $host_os in cygwin* | mingw* | pw32* | cegcc*) # FIXME: the MSVC++ port hasn't been tested in a loooong time # When not using gcc, we currently assume that we are using # Microsoft Visual C++. if test "$GCC" != yes; then with_gnu_ld=no fi ;; interix*) # we just hope/assume this is gcc and not c89 (= MSVC++) with_gnu_ld=yes ;; openbsd*) with_gnu_ld=no ;; linux* | k*bsd*-gnu | gnu*) link_all_deplibs=no ;; esac ld_shlibs=yes # On some targets, GNU ld is compatible enough with the native linker # that we're better off using the native interface for both. lt_use_gnu_ld_interface=no if test "$with_gnu_ld" = yes; then case $host_os in aix*) # The AIX port of GNU ld has always aspired to compatibility # with the native linker. However, as the warning in the GNU ld # block says, versions before 2.19.5* couldn't really create working # shared libraries, regardless of the interface used. case `$LD -v 2>&1` in *\ \(GNU\ Binutils\)\ 2.19.5*) ;; *\ \(GNU\ Binutils\)\ 2.[2-9]*) ;; *\ \(GNU\ Binutils\)\ [3-9]*) ;; *) lt_use_gnu_ld_interface=yes ;; esac ;; *) lt_use_gnu_ld_interface=yes ;; esac fi if test "$lt_use_gnu_ld_interface" = yes; then # If archive_cmds runs LD, not CC, wlarc should be empty wlarc='${wl}' # Set some defaults for GNU ld with shared library support. These # are reset later if shared libraries are not supported. Putting them # here allows them to be overridden if necessary. runpath_var=LD_RUN_PATH hardcode_libdir_flag_spec='${wl}-rpath ${wl}$libdir' export_dynamic_flag_spec='${wl}--export-dynamic' # ancient GNU ld didn't support --whole-archive et. al. if $LD --help 2>&1 | $GREP 'no-whole-archive' > /dev/null; then whole_archive_flag_spec="$wlarc"'--whole-archive$convenience '"$wlarc"'--no-whole-archive' else whole_archive_flag_spec= fi supports_anon_versioning=no case `$LD -v 2>&1` in *GNU\ gold*) supports_anon_versioning=yes ;; *\ [01].* | *\ 2.[0-9].* | *\ 2.10.*) ;; # catch versions < 2.11 *\ 2.11.93.0.2\ *) supports_anon_versioning=yes ;; # RH7.3 ... *\ 2.11.92.0.12\ *) supports_anon_versioning=yes ;; # Mandrake 8.2 ... *\ 2.11.*) ;; # other 2.11 versions *) supports_anon_versioning=yes ;; esac # See if GNU ld supports shared libraries. case $host_os in aix[3-9]*) # On AIX/PPC, the GNU linker is very broken if test "$host_cpu" != ia64; then ld_shlibs=no cat <<_LT_EOF 1>&2 *** Warning: the GNU linker, at least up to release 2.19, is reported *** to be unable to reliably create shared libraries on AIX. *** Therefore, libtool is disabling shared libraries support. If you *** really care for shared libraries, you may want to install binutils *** 2.20 or above, or modify your PATH so that a non-GNU linker is found. *** You will then need to restart the configuration process. _LT_EOF fi ;; amigaos*) case $host_cpu in powerpc) # see comment about AmigaOS4 .so support archive_cmds='$CC -shared $libobjs $deplibs $compiler_flags ${wl}-soname $wl$soname -o $lib' archive_expsym_cmds='' ;; m68k) archive_cmds='$RM $output_objdir/a2ixlibrary.data~$ECHO "#define NAME $libname" > $output_objdir/a2ixlibrary.data~$ECHO "#define LIBRARY_ID 1" >> $output_objdir/a2ixlibrary.data~$ECHO "#define VERSION $major" >> $output_objdir/a2ixlibrary.data~$ECHO "#define REVISION $revision" >> $output_objdir/a2ixlibrary.data~$AR $AR_FLAGS $lib $libobjs~$RANLIB $lib~(cd $output_objdir && a2ixlibrary -32)' hardcode_libdir_flag_spec='-L$libdir' hardcode_minus_L=yes ;; esac ;; beos*) if $LD --help 2>&1 | $GREP ': supported targets:.* elf' > /dev/null; then allow_undefined_flag=unsupported # Joseph Beckenbach says some releases of gcc # support --undefined. This deserves some investigation. FIXME archive_cmds='$CC -nostart $libobjs $deplibs $compiler_flags ${wl}-soname $wl$soname -o $lib' else ld_shlibs=no fi ;; cygwin* | mingw* | pw32* | cegcc*) # _LT_TAGVAR(hardcode_libdir_flag_spec, ) is actually meaningless, # as there is no search path for DLLs. hardcode_libdir_flag_spec='-L$libdir' export_dynamic_flag_spec='${wl}--export-all-symbols' allow_undefined_flag=unsupported always_export_symbols=no enable_shared_with_static_runtimes=yes export_symbols_cmds='$NM $libobjs $convenience | $global_symbol_pipe | $SED -e '\''/^[BCDGRS][ ]/s/.*[ ]\([^ ]*\)/\1 DATA/;s/^.*[ ]__nm__\([^ ]*\)[ ][^ ]*/\1 DATA/;/^I[ ]/d;/^[AITW][ ]/s/.* //'\'' | sort | uniq > $export_symbols' exclude_expsyms='[_]+GLOBAL_OFFSET_TABLE_|[_]+GLOBAL__[FID]_.*|[_]+head_[A-Za-z0-9_]+_dll|[A-Za-z0-9_]+_dll_iname' if $LD --help 2>&1 | $GREP 'auto-import' > /dev/null; then archive_cmds='$CC -shared $libobjs $deplibs $compiler_flags -o $output_objdir/$soname ${wl}--enable-auto-image-base -Xlinker --out-implib -Xlinker $lib' # If the export-symbols file already is a .def file (1st line # is EXPORTS), use it as is; otherwise, prepend... archive_expsym_cmds='if test "x`$SED 1q $export_symbols`" = xEXPORTS; then cp $export_symbols $output_objdir/$soname.def; else echo EXPORTS > $output_objdir/$soname.def; cat $export_symbols >> $output_objdir/$soname.def; fi~ $CC -shared $output_objdir/$soname.def $libobjs $deplibs $compiler_flags -o $output_objdir/$soname ${wl}--enable-auto-image-base -Xlinker --out-implib -Xlinker $lib' else ld_shlibs=no fi ;; haiku*) archive_cmds='$CC -shared $libobjs $deplibs $compiler_flags ${wl}-soname $wl$soname -o $lib' link_all_deplibs=yes ;; interix[3-9]*) hardcode_direct=no hardcode_shlibpath_var=no hardcode_libdir_flag_spec='${wl}-rpath,$libdir' export_dynamic_flag_spec='${wl}-E' # Hack: On Interix 3.x, we cannot compile PIC because of a broken gcc. # Instead, shared libraries are loaded at an image base (0x10000000 by # default) and relocated if they conflict, which is a slow very memory # consuming and fragmenting process. To avoid this, we pick a random, # 256 KiB-aligned image base between 0x50000000 and 0x6FFC0000 at link # time. Moving up from 0x10000000 also allows more sbrk(2) space. archive_cmds='$CC -shared $pic_flag $libobjs $deplibs $compiler_flags ${wl}-h,$soname ${wl}--image-base,`expr ${RANDOM-$$} % 4096 / 2 \* 262144 + 1342177280` -o $lib' archive_expsym_cmds='sed "s,^,_," $export_symbols >$output_objdir/$soname.expsym~$CC -shared $pic_flag $libobjs $deplibs $compiler_flags ${wl}-h,$soname ${wl}--retain-symbols-file,$output_objdir/$soname.expsym ${wl}--image-base,`expr ${RANDOM-$$} % 4096 / 2 \* 262144 + 1342177280` -o $lib' ;; gnu* | linux* | tpf* | k*bsd*-gnu | kopensolaris*-gnu) tmp_diet=no if test "$host_os" = linux-dietlibc; then case $cc_basename in diet\ *) tmp_diet=yes;; # linux-dietlibc with static linking (!diet-dyn) esac fi if $LD --help 2>&1 | $EGREP ': supported targets:.* elf' > /dev/null \ && test "$tmp_diet" = no then tmp_addflag=' $pic_flag' tmp_sharedflag='-shared' case $cc_basename,$host_cpu in pgcc*) # Portland Group C compiler whole_archive_flag_spec='${wl}--whole-archive`for conv in $convenience\"\"; do test -n \"$conv\" && new_convenience=\"$new_convenience,$conv\"; done; func_echo_all \"$new_convenience\"` ${wl}--no-whole-archive' tmp_addflag=' $pic_flag' ;; pgf77* | pgf90* | pgf95* | pgfortran*) # Portland Group f77 and f90 compilers whole_archive_flag_spec='${wl}--whole-archive`for conv in $convenience\"\"; do test -n \"$conv\" && new_convenience=\"$new_convenience,$conv\"; done; func_echo_all \"$new_convenience\"` ${wl}--no-whole-archive' tmp_addflag=' $pic_flag -Mnomain' ;; ecc*,ia64* | icc*,ia64*) # Intel C compiler on ia64 tmp_addflag=' -i_dynamic' ;; efc*,ia64* | ifort*,ia64*) # Intel Fortran compiler on ia64 tmp_addflag=' -i_dynamic -nofor_main' ;; ifc* | ifort*) # Intel Fortran compiler tmp_addflag=' -nofor_main' ;; lf95*) # Lahey Fortran 8.1 whole_archive_flag_spec= tmp_sharedflag='--shared' ;; xl[cC]* | bgxl[cC]* | mpixl[cC]*) # IBM XL C 8.0 on PPC (deal with xlf below) tmp_sharedflag='-qmkshrobj' tmp_addflag= ;; nvcc*) # Cuda Compiler Driver 2.2 whole_archive_flag_spec='${wl}--whole-archive`for conv in $convenience\"\"; do test -n \"$conv\" && new_convenience=\"$new_convenience,$conv\"; done; func_echo_all \"$new_convenience\"` ${wl}--no-whole-archive' compiler_needs_object=yes ;; esac case `$CC -V 2>&1 | sed 5q` in *Sun\ C*) # Sun C 5.9 whole_archive_flag_spec='${wl}--whole-archive`new_convenience=; for conv in $convenience\"\"; do test -z \"$conv\" || new_convenience=\"$new_convenience,$conv\"; done; func_echo_all \"$new_convenience\"` ${wl}--no-whole-archive' compiler_needs_object=yes tmp_sharedflag='-G' ;; *Sun\ F*) # Sun Fortran 8.3 tmp_sharedflag='-G' ;; esac archive_cmds='$CC '"$tmp_sharedflag""$tmp_addflag"' $libobjs $deplibs $compiler_flags ${wl}-soname $wl$soname -o $lib' if test "x$supports_anon_versioning" = xyes; then archive_expsym_cmds='echo "{ global:" > $output_objdir/$libname.ver~ cat $export_symbols | sed -e "s/\(.*\)/\1;/" >> $output_objdir/$libname.ver~ echo "local: *; };" >> $output_objdir/$libname.ver~ $CC '"$tmp_sharedflag""$tmp_addflag"' $libobjs $deplibs $compiler_flags ${wl}-soname $wl$soname ${wl}-version-script ${wl}$output_objdir/$libname.ver -o $lib' fi case $cc_basename in xlf* | bgf* | bgxlf* | mpixlf*) # IBM XL Fortran 10.1 on PPC cannot create shared libs itself whole_archive_flag_spec='--whole-archive$convenience --no-whole-archive' hardcode_libdir_flag_spec='${wl}-rpath ${wl}$libdir' archive_cmds='$LD -shared $libobjs $deplibs $linker_flags -soname $soname -o $lib' if test "x$supports_anon_versioning" = xyes; then archive_expsym_cmds='echo "{ global:" > $output_objdir/$libname.ver~ cat $export_symbols | sed -e "s/\(.*\)/\1;/" >> $output_objdir/$libname.ver~ echo "local: *; };" >> $output_objdir/$libname.ver~ $LD -shared $libobjs $deplibs $linker_flags -soname $soname -version-script $output_objdir/$libname.ver -o $lib' fi ;; esac else ld_shlibs=no fi ;; netbsd* | netbsdelf*-gnu) if echo __ELF__ | $CC -E - | $GREP __ELF__ >/dev/null; then archive_cmds='$LD -Bshareable $libobjs $deplibs $linker_flags -o $lib' wlarc= else archive_cmds='$CC -shared $pic_flag $libobjs $deplibs $compiler_flags ${wl}-soname $wl$soname -o $lib' archive_expsym_cmds='$CC -shared $pic_flag $libobjs $deplibs $compiler_flags ${wl}-soname $wl$soname ${wl}-retain-symbols-file $wl$export_symbols -o $lib' fi ;; solaris*) if $LD -v 2>&1 | $GREP 'BFD 2\.8' > /dev/null; then ld_shlibs=no cat <<_LT_EOF 1>&2 *** Warning: The releases 2.8.* of the GNU linker cannot reliably *** create shared libraries on Solaris systems. Therefore, libtool *** is disabling shared libraries support. We urge you to upgrade GNU *** binutils to release 2.9.1 or newer. Another option is to modify *** your PATH or compiler configuration so that the native linker is *** used, and then restart. _LT_EOF elif $LD --help 2>&1 | $GREP ': supported targets:.* elf' > /dev/null; then archive_cmds='$CC -shared $pic_flag $libobjs $deplibs $compiler_flags ${wl}-soname $wl$soname -o $lib' archive_expsym_cmds='$CC -shared $pic_flag $libobjs $deplibs $compiler_flags ${wl}-soname $wl$soname ${wl}-retain-symbols-file $wl$export_symbols -o $lib' else ld_shlibs=no fi ;; sysv5* | sco3.2v5* | sco5v6* | unixware* | OpenUNIX*) case `$LD -v 2>&1` in *\ [01].* | *\ 2.[0-9].* | *\ 2.1[0-5].*) ld_shlibs=no cat <<_LT_EOF 1>&2 *** Warning: Releases of the GNU linker prior to 2.16.91.0.3 can not *** reliably create shared libraries on SCO systems. Therefore, libtool *** is disabling shared libraries support. We urge you to upgrade GNU *** binutils to release 2.16.91.0.3 or newer. Another option is to modify *** your PATH or compiler configuration so that the native linker is *** used, and then restart. _LT_EOF ;; *) # For security reasons, it is highly recommended that you always # use absolute paths for naming shared libraries, and exclude the # DT_RUNPATH tag from executables and libraries. But doing so # requires that you compile everything twice, which is a pain. if $LD --help 2>&1 | $GREP ': supported targets:.* elf' > /dev/null; then hardcode_libdir_flag_spec='${wl}-rpath ${wl}$libdir' archive_cmds='$CC -shared $libobjs $deplibs $compiler_flags ${wl}-soname $wl$soname -o $lib' archive_expsym_cmds='$CC -shared $libobjs $deplibs $compiler_flags ${wl}-soname $wl$soname ${wl}-retain-symbols-file $wl$export_symbols -o $lib' else ld_shlibs=no fi ;; esac ;; sunos4*) archive_cmds='$LD -assert pure-text -Bshareable -o $lib $libobjs $deplibs $linker_flags' wlarc= hardcode_direct=yes hardcode_shlibpath_var=no ;; *) if $LD --help 2>&1 | $GREP ': supported targets:.* elf' > /dev/null; then archive_cmds='$CC -shared $pic_flag $libobjs $deplibs $compiler_flags ${wl}-soname $wl$soname -o $lib' archive_expsym_cmds='$CC -shared $pic_flag $libobjs $deplibs $compiler_flags ${wl}-soname $wl$soname ${wl}-retain-symbols-file $wl$export_symbols -o $lib' else ld_shlibs=no fi ;; esac if test "$ld_shlibs" = no; then runpath_var= hardcode_libdir_flag_spec= export_dynamic_flag_spec= whole_archive_flag_spec= fi else # PORTME fill in a description of your system's linker (not GNU ld) case $host_os in aix3*) allow_undefined_flag=unsupported always_export_symbols=yes archive_expsym_cmds='$LD -o $output_objdir/$soname $libobjs $deplibs $linker_flags -bE:$export_symbols -T512 -H512 -bM:SRE~$AR $AR_FLAGS $lib $output_objdir/$soname' # Note: this linker hardcodes the directories in LIBPATH if there # are no directories specified by -L. hardcode_minus_L=yes if test "$GCC" = yes && test -z "$lt_prog_compiler_static"; then # Neither direct hardcoding nor static linking is supported with a # broken collect2. hardcode_direct=unsupported fi ;; aix[4-9]*) if test "$host_cpu" = ia64; then # On IA64, the linker does run time linking by default, so we don't # have to do anything special. aix_use_runtimelinking=no exp_sym_flag='-Bexport' no_entry_flag="" else # If we're using GNU nm, then we don't want the "-C" option. # -C means demangle to AIX nm, but means don't demangle with GNU nm # Also, AIX nm treats weak defined symbols like other global # defined symbols, whereas GNU nm marks them as "W". if $NM -V 2>&1 | $GREP 'GNU' > /dev/null; then export_symbols_cmds='$NM -Bpg $libobjs $convenience | awk '\''{ if (((\$ 2 == "T") || (\$ 2 == "D") || (\$ 2 == "B") || (\$ 2 == "W")) && (substr(\$ 3,1,1) != ".")) { print \$ 3 } }'\'' | sort -u > $export_symbols' else export_symbols_cmds='$NM -BCpg $libobjs $convenience | awk '\''{ if (((\$ 2 == "T") || (\$ 2 == "D") || (\$ 2 == "B")) && (substr(\$ 3,1,1) != ".")) { print \$ 3 } }'\'' | sort -u > $export_symbols' fi aix_use_runtimelinking=no # Test if we are trying to use run time linking or normal # AIX style linking. If -brtl is somewhere in LDFLAGS, we # need to do runtime linking. case $host_os in aix4.[23]|aix4.[23].*|aix[5-9]*) for ld_flag in $LDFLAGS; do if (test $ld_flag = "-brtl" || test $ld_flag = "-Wl,-brtl"); then aix_use_runtimelinking=yes break fi done ;; esac exp_sym_flag='-bexport' no_entry_flag='-bnoentry' fi # When large executables or shared objects are built, AIX ld can # have problems creating the table of contents. If linking a library # or program results in "error TOC overflow" add -mminimal-toc to # CXXFLAGS/CFLAGS for g++/gcc. In the cases where that is not # enough to fix the problem, add -Wl,-bbigtoc to LDFLAGS. archive_cmds='' hardcode_direct=yes hardcode_direct_absolute=yes hardcode_libdir_separator=':' link_all_deplibs=yes file_list_spec='${wl}-f,' if test "$GCC" = yes; then case $host_os in aix4.[012]|aix4.[012].*) # We only want to do this on AIX 4.2 and lower, the check # below for broken collect2 doesn't work under 4.3+ collect2name=`${CC} -print-prog-name=collect2` if test -f "$collect2name" && strings "$collect2name" | $GREP resolve_lib_name >/dev/null then # We have reworked collect2 : else # We have old collect2 hardcode_direct=unsupported # It fails to find uninstalled libraries when the uninstalled # path is not listed in the libpath. Setting hardcode_minus_L # to unsupported forces relinking hardcode_minus_L=yes hardcode_libdir_flag_spec='-L$libdir' hardcode_libdir_separator= fi ;; esac shared_flag='-shared' if test "$aix_use_runtimelinking" = yes; then shared_flag="$shared_flag "'${wl}-G' fi link_all_deplibs=no else # not using gcc if test "$host_cpu" = ia64; then # VisualAge C++, Version 5.5 for AIX 5L for IA-64, Beta 3 Release # chokes on -Wl,-G. The following line is correct: shared_flag='-G' else if test "$aix_use_runtimelinking" = yes; then shared_flag='${wl}-G' else shared_flag='${wl}-bM:SRE' fi fi fi export_dynamic_flag_spec='${wl}-bexpall' # It seems that -bexpall does not export symbols beginning with # underscore (_), so it is better to generate a list of symbols to export. always_export_symbols=yes if test "$aix_use_runtimelinking" = yes; then # Warning - without using the other runtime loading flags (-brtl), # -berok will link without error, but may produce a broken library. allow_undefined_flag='-berok' # Determine the default libpath from the value encoded in an # empty executable. if test "${lt_cv_aix_libpath+set}" = set; then aix_libpath=$lt_cv_aix_libpath else if ${lt_cv_aix_libpath_+:} false; then : $as_echo_n "(cached) " >&6 else cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ int main () { ; return 0; } _ACEOF if ac_fn_c_try_link "$LINENO"; then : lt_aix_libpath_sed=' /Import File Strings/,/^$/ { /^0/ { s/^0 *\([^ ]*\) *$/\1/ p } }' lt_cv_aix_libpath_=`dump -H conftest$ac_exeext 2>/dev/null | $SED -n -e "$lt_aix_libpath_sed"` # Check for a 64-bit object if we didn't find anything. if test -z "$lt_cv_aix_libpath_"; then lt_cv_aix_libpath_=`dump -HX64 conftest$ac_exeext 2>/dev/null | $SED -n -e "$lt_aix_libpath_sed"` fi fi rm -f core conftest.err conftest.$ac_objext \ conftest$ac_exeext conftest.$ac_ext if test -z "$lt_cv_aix_libpath_"; then lt_cv_aix_libpath_="/usr/lib:/lib" fi fi aix_libpath=$lt_cv_aix_libpath_ fi hardcode_libdir_flag_spec='${wl}-blibpath:$libdir:'"$aix_libpath" archive_expsym_cmds='$CC -o $output_objdir/$soname $libobjs $deplibs '"\${wl}$no_entry_flag"' $compiler_flags `if test "x${allow_undefined_flag}" != "x"; then func_echo_all "${wl}${allow_undefined_flag}"; else :; fi` '"\${wl}$exp_sym_flag:\$export_symbols $shared_flag" else if test "$host_cpu" = ia64; then hardcode_libdir_flag_spec='${wl}-R $libdir:/usr/lib:/lib' allow_undefined_flag="-z nodefs" archive_expsym_cmds="\$CC $shared_flag"' -o $output_objdir/$soname $libobjs $deplibs '"\${wl}$no_entry_flag"' $compiler_flags ${wl}${allow_undefined_flag} '"\${wl}$exp_sym_flag:\$export_symbols" else # Determine the default libpath from the value encoded in an # empty executable. if test "${lt_cv_aix_libpath+set}" = set; then aix_libpath=$lt_cv_aix_libpath else if ${lt_cv_aix_libpath_+:} false; then : $as_echo_n "(cached) " >&6 else cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ int main () { ; return 0; } _ACEOF if ac_fn_c_try_link "$LINENO"; then : lt_aix_libpath_sed=' /Import File Strings/,/^$/ { /^0/ { s/^0 *\([^ ]*\) *$/\1/ p } }' lt_cv_aix_libpath_=`dump -H conftest$ac_exeext 2>/dev/null | $SED -n -e "$lt_aix_libpath_sed"` # Check for a 64-bit object if we didn't find anything. if test -z "$lt_cv_aix_libpath_"; then lt_cv_aix_libpath_=`dump -HX64 conftest$ac_exeext 2>/dev/null | $SED -n -e "$lt_aix_libpath_sed"` fi fi rm -f core conftest.err conftest.$ac_objext \ conftest$ac_exeext conftest.$ac_ext if test -z "$lt_cv_aix_libpath_"; then lt_cv_aix_libpath_="/usr/lib:/lib" fi fi aix_libpath=$lt_cv_aix_libpath_ fi hardcode_libdir_flag_spec='${wl}-blibpath:$libdir:'"$aix_libpath" # Warning - without using the other run time loading flags, # -berok will link without error, but may produce a broken library. no_undefined_flag=' ${wl}-bernotok' allow_undefined_flag=' ${wl}-berok' if test "$with_gnu_ld" = yes; then # We only use this code for GNU lds that support --whole-archive. whole_archive_flag_spec='${wl}--whole-archive$convenience ${wl}--no-whole-archive' else # Exported symbols can be pulled into shared objects from archives whole_archive_flag_spec='$convenience' fi archive_cmds_need_lc=yes # This is similar to how AIX traditionally builds its shared libraries. archive_expsym_cmds="\$CC $shared_flag"' -o $output_objdir/$soname $libobjs $deplibs ${wl}-bnoentry $compiler_flags ${wl}-bE:$export_symbols${allow_undefined_flag}~$AR $AR_FLAGS $output_objdir/$libname$release.a $output_objdir/$soname' fi fi ;; amigaos*) case $host_cpu in powerpc) # see comment about AmigaOS4 .so support archive_cmds='$CC -shared $libobjs $deplibs $compiler_flags ${wl}-soname $wl$soname -o $lib' archive_expsym_cmds='' ;; m68k) archive_cmds='$RM $output_objdir/a2ixlibrary.data~$ECHO "#define NAME $libname" > $output_objdir/a2ixlibrary.data~$ECHO "#define LIBRARY_ID 1" >> $output_objdir/a2ixlibrary.data~$ECHO "#define VERSION $major" >> $output_objdir/a2ixlibrary.data~$ECHO "#define REVISION $revision" >> $output_objdir/a2ixlibrary.data~$AR $AR_FLAGS $lib $libobjs~$RANLIB $lib~(cd $output_objdir && a2ixlibrary -32)' hardcode_libdir_flag_spec='-L$libdir' hardcode_minus_L=yes ;; esac ;; bsdi[45]*) export_dynamic_flag_spec=-rdynamic ;; cygwin* | mingw* | pw32* | cegcc*) # When not using gcc, we currently assume that we are using # Microsoft Visual C++. # hardcode_libdir_flag_spec is actually meaningless, as there is # no search path for DLLs. case $cc_basename in cl*) # Native MSVC hardcode_libdir_flag_spec=' ' allow_undefined_flag=unsupported always_export_symbols=yes file_list_spec='@' # Tell ltmain to make .lib files, not .a files. libext=lib # Tell ltmain to make .dll files, not .so files. shrext_cmds=".dll" # FIXME: Setting linknames here is a bad hack. archive_cmds='$CC -o $output_objdir/$soname $libobjs $compiler_flags $deplibs -Wl,-dll~linknames=' archive_expsym_cmds='if test "x`$SED 1q $export_symbols`" = xEXPORTS; then sed -n -e 's/\\\\\\\(.*\\\\\\\)/-link\\\ -EXPORT:\\\\\\\1/' -e '1\\\!p' < $export_symbols > $output_objdir/$soname.exp; else sed -e 's/\\\\\\\(.*\\\\\\\)/-link\\\ -EXPORT:\\\\\\\1/' < $export_symbols > $output_objdir/$soname.exp; fi~ $CC -o $tool_output_objdir$soname $libobjs $compiler_flags $deplibs "@$tool_output_objdir$soname.exp" -Wl,-DLL,-IMPLIB:"$tool_output_objdir$libname.dll.lib"~ linknames=' # The linker will not automatically build a static lib if we build a DLL. # _LT_TAGVAR(old_archive_from_new_cmds, )='true' enable_shared_with_static_runtimes=yes exclude_expsyms='_NULL_IMPORT_DESCRIPTOR|_IMPORT_DESCRIPTOR_.*' export_symbols_cmds='$NM $libobjs $convenience | $global_symbol_pipe | $SED -e '\''/^[BCDGRS][ ]/s/.*[ ]\([^ ]*\)/\1,DATA/'\'' | $SED -e '\''/^[AITW][ ]/s/.*[ ]//'\'' | sort | uniq > $export_symbols' # Don't use ranlib old_postinstall_cmds='chmod 644 $oldlib' postlink_cmds='lt_outputfile="@OUTPUT@"~ lt_tool_outputfile="@TOOL_OUTPUT@"~ case $lt_outputfile in *.exe|*.EXE) ;; *) lt_outputfile="$lt_outputfile.exe" lt_tool_outputfile="$lt_tool_outputfile.exe" ;; esac~ if test "$MANIFEST_TOOL" != ":" && test -f "$lt_outputfile.manifest"; then $MANIFEST_TOOL -manifest "$lt_tool_outputfile.manifest" -outputresource:"$lt_tool_outputfile" || exit 1; $RM "$lt_outputfile.manifest"; fi' ;; *) # Assume MSVC wrapper hardcode_libdir_flag_spec=' ' allow_undefined_flag=unsupported # Tell ltmain to make .lib files, not .a files. libext=lib # Tell ltmain to make .dll files, not .so files. shrext_cmds=".dll" # FIXME: Setting linknames here is a bad hack. archive_cmds='$CC -o $lib $libobjs $compiler_flags `func_echo_all "$deplibs" | $SED '\''s/ -lc$//'\''` -link -dll~linknames=' # The linker will automatically build a .lib file if we build a DLL. old_archive_from_new_cmds='true' # FIXME: Should let the user specify the lib program. old_archive_cmds='lib -OUT:$oldlib$oldobjs$old_deplibs' enable_shared_with_static_runtimes=yes ;; esac ;; darwin* | rhapsody*) archive_cmds_need_lc=no hardcode_direct=no hardcode_automatic=yes hardcode_shlibpath_var=unsupported if test "$lt_cv_ld_force_load" = "yes"; then whole_archive_flag_spec='`for conv in $convenience\"\"; do test -n \"$conv\" && new_convenience=\"$new_convenience ${wl}-force_load,$conv\"; done; func_echo_all \"$new_convenience\"`' else whole_archive_flag_spec='' fi link_all_deplibs=yes allow_undefined_flag="$_lt_dar_allow_undefined" case $cc_basename in ifort*) _lt_dar_can_shared=yes ;; *) _lt_dar_can_shared=$GCC ;; esac if test "$_lt_dar_can_shared" = "yes"; then output_verbose_link_cmd=func_echo_all archive_cmds="\$CC -dynamiclib \$allow_undefined_flag -o \$lib \$libobjs \$deplibs \$compiler_flags -install_name \$rpath/\$soname \$verstring $_lt_dar_single_mod${_lt_dsymutil}" module_cmds="\$CC \$allow_undefined_flag -o \$lib -bundle \$libobjs \$deplibs \$compiler_flags${_lt_dsymutil}" archive_expsym_cmds="sed 's,^,_,' < \$export_symbols > \$output_objdir/\${libname}-symbols.expsym~\$CC -dynamiclib \$allow_undefined_flag -o \$lib \$libobjs \$deplibs \$compiler_flags -install_name \$rpath/\$soname \$verstring ${_lt_dar_single_mod}${_lt_dar_export_syms}${_lt_dsymutil}" module_expsym_cmds="sed -e 's,^,_,' < \$export_symbols > \$output_objdir/\${libname}-symbols.expsym~\$CC \$allow_undefined_flag -o \$lib -bundle \$libobjs \$deplibs \$compiler_flags${_lt_dar_export_syms}${_lt_dsymutil}" else ld_shlibs=no fi ;; dgux*) archive_cmds='$LD -G -h $soname -o $lib $libobjs $deplibs $linker_flags' hardcode_libdir_flag_spec='-L$libdir' hardcode_shlibpath_var=no ;; # FreeBSD 2.2.[012] allows us to include c++rt0.o to get C++ constructor # support. Future versions do this automatically, but an explicit c++rt0.o # does not break anything, and helps significantly (at the cost of a little # extra space). freebsd2.2*) archive_cmds='$LD -Bshareable -o $lib $libobjs $deplibs $linker_flags /usr/lib/c++rt0.o' hardcode_libdir_flag_spec='-R$libdir' hardcode_direct=yes hardcode_shlibpath_var=no ;; # Unfortunately, older versions of FreeBSD 2 do not have this feature. freebsd2.*) archive_cmds='$LD -Bshareable -o $lib $libobjs $deplibs $linker_flags' hardcode_direct=yes hardcode_minus_L=yes hardcode_shlibpath_var=no ;; # FreeBSD 3 and greater uses gcc -shared to do shared libraries. freebsd* | dragonfly*) archive_cmds='$CC -shared $pic_flag -o $lib $libobjs $deplibs $compiler_flags' hardcode_libdir_flag_spec='-R$libdir' hardcode_direct=yes hardcode_shlibpath_var=no ;; hpux9*) if test "$GCC" = yes; then archive_cmds='$RM $output_objdir/$soname~$CC -shared $pic_flag ${wl}+b ${wl}$install_libdir -o $output_objdir/$soname $libobjs $deplibs $compiler_flags~test $output_objdir/$soname = $lib || mv $output_objdir/$soname $lib' else archive_cmds='$RM $output_objdir/$soname~$LD -b +b $install_libdir -o $output_objdir/$soname $libobjs $deplibs $linker_flags~test $output_objdir/$soname = $lib || mv $output_objdir/$soname $lib' fi hardcode_libdir_flag_spec='${wl}+b ${wl}$libdir' hardcode_libdir_separator=: hardcode_direct=yes # hardcode_minus_L: Not really in the search PATH, # but as the default location of the library. hardcode_minus_L=yes export_dynamic_flag_spec='${wl}-E' ;; hpux10*) if test "$GCC" = yes && test "$with_gnu_ld" = no; then archive_cmds='$CC -shared $pic_flag ${wl}+h ${wl}$soname ${wl}+b ${wl}$install_libdir -o $lib $libobjs $deplibs $compiler_flags' else archive_cmds='$LD -b +h $soname +b $install_libdir -o $lib $libobjs $deplibs $linker_flags' fi if test "$with_gnu_ld" = no; then hardcode_libdir_flag_spec='${wl}+b ${wl}$libdir' hardcode_libdir_separator=: hardcode_direct=yes hardcode_direct_absolute=yes export_dynamic_flag_spec='${wl}-E' # hardcode_minus_L: Not really in the search PATH, # but as the default location of the library. hardcode_minus_L=yes fi ;; hpux11*) if test "$GCC" = yes && test "$with_gnu_ld" = no; then case $host_cpu in hppa*64*) archive_cmds='$CC -shared ${wl}+h ${wl}$soname -o $lib $libobjs $deplibs $compiler_flags' ;; ia64*) archive_cmds='$CC -shared $pic_flag ${wl}+h ${wl}$soname ${wl}+nodefaultrpath -o $lib $libobjs $deplibs $compiler_flags' ;; *) archive_cmds='$CC -shared $pic_flag ${wl}+h ${wl}$soname ${wl}+b ${wl}$install_libdir -o $lib $libobjs $deplibs $compiler_flags' ;; esac else case $host_cpu in hppa*64*) archive_cmds='$CC -b ${wl}+h ${wl}$soname -o $lib $libobjs $deplibs $compiler_flags' ;; ia64*) archive_cmds='$CC -b ${wl}+h ${wl}$soname ${wl}+nodefaultrpath -o $lib $libobjs $deplibs $compiler_flags' ;; *) # Older versions of the 11.00 compiler do not understand -b yet # (HP92453-01 A.11.01.20 doesn't, HP92453-01 B.11.X.35175-35176.GP does) { $as_echo "$as_me:${as_lineno-$LINENO}: checking if $CC understands -b" >&5 $as_echo_n "checking if $CC understands -b... " >&6; } if ${lt_cv_prog_compiler__b+:} false; then : $as_echo_n "(cached) " >&6 else lt_cv_prog_compiler__b=no save_LDFLAGS="$LDFLAGS" LDFLAGS="$LDFLAGS -b" echo "$lt_simple_link_test_code" > conftest.$ac_ext if (eval $ac_link 2>conftest.err) && test -s conftest$ac_exeext; then # The linker can only warn and ignore the option if not recognized # So say no if there are warnings if test -s conftest.err; then # Append any errors to the config.log. cat conftest.err 1>&5 $ECHO "$_lt_linker_boilerplate" | $SED '/^$/d' > conftest.exp $SED '/^$/d; /^ *+/d' conftest.err >conftest.er2 if diff conftest.exp conftest.er2 >/dev/null; then lt_cv_prog_compiler__b=yes fi else lt_cv_prog_compiler__b=yes fi fi $RM -r conftest* LDFLAGS="$save_LDFLAGS" fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $lt_cv_prog_compiler__b" >&5 $as_echo "$lt_cv_prog_compiler__b" >&6; } if test x"$lt_cv_prog_compiler__b" = xyes; then archive_cmds='$CC -b ${wl}+h ${wl}$soname ${wl}+b ${wl}$install_libdir -o $lib $libobjs $deplibs $compiler_flags' else archive_cmds='$LD -b +h $soname +b $install_libdir -o $lib $libobjs $deplibs $linker_flags' fi ;; esac fi if test "$with_gnu_ld" = no; then hardcode_libdir_flag_spec='${wl}+b ${wl}$libdir' hardcode_libdir_separator=: case $host_cpu in hppa*64*|ia64*) hardcode_direct=no hardcode_shlibpath_var=no ;; *) hardcode_direct=yes hardcode_direct_absolute=yes export_dynamic_flag_spec='${wl}-E' # hardcode_minus_L: Not really in the search PATH, # but as the default location of the library. hardcode_minus_L=yes ;; esac fi ;; irix5* | irix6* | nonstopux*) if test "$GCC" = yes; then archive_cmds='$CC -shared $pic_flag $libobjs $deplibs $compiler_flags ${wl}-soname ${wl}$soname `test -n "$verstring" && func_echo_all "${wl}-set_version ${wl}$verstring"` ${wl}-update_registry ${wl}${output_objdir}/so_locations -o $lib' # Try to use the -exported_symbol ld option, if it does not # work, assume that -exports_file does not work either and # implicitly export all symbols. # This should be the same for all languages, so no per-tag cache variable. { $as_echo "$as_me:${as_lineno-$LINENO}: checking whether the $host_os linker accepts -exported_symbol" >&5 $as_echo_n "checking whether the $host_os linker accepts -exported_symbol... " >&6; } if ${lt_cv_irix_exported_symbol+:} false; then : $as_echo_n "(cached) " >&6 else save_LDFLAGS="$LDFLAGS" LDFLAGS="$LDFLAGS -shared ${wl}-exported_symbol ${wl}foo ${wl}-update_registry ${wl}/dev/null" cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ int foo (void) { return 0; } _ACEOF if ac_fn_c_try_link "$LINENO"; then : lt_cv_irix_exported_symbol=yes else lt_cv_irix_exported_symbol=no fi rm -f core conftest.err conftest.$ac_objext \ conftest$ac_exeext conftest.$ac_ext LDFLAGS="$save_LDFLAGS" fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $lt_cv_irix_exported_symbol" >&5 $as_echo "$lt_cv_irix_exported_symbol" >&6; } if test "$lt_cv_irix_exported_symbol" = yes; then archive_expsym_cmds='$CC -shared $pic_flag $libobjs $deplibs $compiler_flags ${wl}-soname ${wl}$soname `test -n "$verstring" && func_echo_all "${wl}-set_version ${wl}$verstring"` ${wl}-update_registry ${wl}${output_objdir}/so_locations ${wl}-exports_file ${wl}$export_symbols -o $lib' fi else archive_cmds='$CC -shared $libobjs $deplibs $compiler_flags -soname $soname `test -n "$verstring" && func_echo_all "-set_version $verstring"` -update_registry ${output_objdir}/so_locations -o $lib' archive_expsym_cmds='$CC -shared $libobjs $deplibs $compiler_flags -soname $soname `test -n "$verstring" && func_echo_all "-set_version $verstring"` -update_registry ${output_objdir}/so_locations -exports_file $export_symbols -o $lib' fi archive_cmds_need_lc='no' hardcode_libdir_flag_spec='${wl}-rpath ${wl}$libdir' hardcode_libdir_separator=: inherit_rpath=yes link_all_deplibs=yes ;; netbsd* | netbsdelf*-gnu) if echo __ELF__ | $CC -E - | $GREP __ELF__ >/dev/null; then archive_cmds='$LD -Bshareable -o $lib $libobjs $deplibs $linker_flags' # a.out else archive_cmds='$LD -shared -o $lib $libobjs $deplibs $linker_flags' # ELF fi hardcode_libdir_flag_spec='-R$libdir' hardcode_direct=yes hardcode_shlibpath_var=no ;; newsos6) archive_cmds='$LD -G -h $soname -o $lib $libobjs $deplibs $linker_flags' hardcode_direct=yes hardcode_libdir_flag_spec='${wl}-rpath ${wl}$libdir' hardcode_libdir_separator=: hardcode_shlibpath_var=no ;; *nto* | *qnx*) ;; openbsd*) if test -f /usr/libexec/ld.so; then hardcode_direct=yes hardcode_shlibpath_var=no hardcode_direct_absolute=yes if test -z "`echo __ELF__ | $CC -E - | $GREP __ELF__`" || test "$host_os-$host_cpu" = "openbsd2.8-powerpc"; then archive_cmds='$CC -shared $pic_flag -o $lib $libobjs $deplibs $compiler_flags' archive_expsym_cmds='$CC -shared $pic_flag -o $lib $libobjs $deplibs $compiler_flags ${wl}-retain-symbols-file,$export_symbols' hardcode_libdir_flag_spec='${wl}-rpath,$libdir' export_dynamic_flag_spec='${wl}-E' else case $host_os in openbsd[01].* | openbsd2.[0-7] | openbsd2.[0-7].*) archive_cmds='$LD -Bshareable -o $lib $libobjs $deplibs $linker_flags' hardcode_libdir_flag_spec='-R$libdir' ;; *) archive_cmds='$CC -shared $pic_flag -o $lib $libobjs $deplibs $compiler_flags' hardcode_libdir_flag_spec='${wl}-rpath,$libdir' ;; esac fi else ld_shlibs=no fi ;; os2*) hardcode_libdir_flag_spec='-L$libdir' hardcode_minus_L=yes allow_undefined_flag=unsupported archive_cmds='$ECHO "LIBRARY $libname INITINSTANCE" > $output_objdir/$libname.def~$ECHO "DESCRIPTION \"$libname\"" >> $output_objdir/$libname.def~echo DATA >> $output_objdir/$libname.def~echo " SINGLE NONSHARED" >> $output_objdir/$libname.def~echo EXPORTS >> $output_objdir/$libname.def~emxexp $libobjs >> $output_objdir/$libname.def~$CC -Zdll -Zcrtdll -o $lib $libobjs $deplibs $compiler_flags $output_objdir/$libname.def' old_archive_from_new_cmds='emximp -o $output_objdir/$libname.a $output_objdir/$libname.def' ;; osf3*) if test "$GCC" = yes; then allow_undefined_flag=' ${wl}-expect_unresolved ${wl}\*' archive_cmds='$CC -shared${allow_undefined_flag} $libobjs $deplibs $compiler_flags ${wl}-soname ${wl}$soname `test -n "$verstring" && func_echo_all "${wl}-set_version ${wl}$verstring"` ${wl}-update_registry ${wl}${output_objdir}/so_locations -o $lib' else allow_undefined_flag=' -expect_unresolved \*' archive_cmds='$CC -shared${allow_undefined_flag} $libobjs $deplibs $compiler_flags -soname $soname `test -n "$verstring" && func_echo_all "-set_version $verstring"` -update_registry ${output_objdir}/so_locations -o $lib' fi archive_cmds_need_lc='no' hardcode_libdir_flag_spec='${wl}-rpath ${wl}$libdir' hardcode_libdir_separator=: ;; osf4* | osf5*) # as osf3* with the addition of -msym flag if test "$GCC" = yes; then allow_undefined_flag=' ${wl}-expect_unresolved ${wl}\*' archive_cmds='$CC -shared${allow_undefined_flag} $pic_flag $libobjs $deplibs $compiler_flags ${wl}-msym ${wl}-soname ${wl}$soname `test -n "$verstring" && func_echo_all "${wl}-set_version ${wl}$verstring"` ${wl}-update_registry ${wl}${output_objdir}/so_locations -o $lib' hardcode_libdir_flag_spec='${wl}-rpath ${wl}$libdir' else allow_undefined_flag=' -expect_unresolved \*' archive_cmds='$CC -shared${allow_undefined_flag} $libobjs $deplibs $compiler_flags -msym -soname $soname `test -n "$verstring" && func_echo_all "-set_version $verstring"` -update_registry ${output_objdir}/so_locations -o $lib' archive_expsym_cmds='for i in `cat $export_symbols`; do printf "%s %s\\n" -exported_symbol "\$i" >> $lib.exp; done; printf "%s\\n" "-hidden">> $lib.exp~ $CC -shared${allow_undefined_flag} ${wl}-input ${wl}$lib.exp $compiler_flags $libobjs $deplibs -soname $soname `test -n "$verstring" && $ECHO "-set_version $verstring"` -update_registry ${output_objdir}/so_locations -o $lib~$RM $lib.exp' # Both c and cxx compiler support -rpath directly hardcode_libdir_flag_spec='-rpath $libdir' fi archive_cmds_need_lc='no' hardcode_libdir_separator=: ;; solaris*) no_undefined_flag=' -z defs' if test "$GCC" = yes; then wlarc='${wl}' archive_cmds='$CC -shared $pic_flag ${wl}-z ${wl}text ${wl}-h ${wl}$soname -o $lib $libobjs $deplibs $compiler_flags' archive_expsym_cmds='echo "{ global:" > $lib.exp~cat $export_symbols | $SED -e "s/\(.*\)/\1;/" >> $lib.exp~echo "local: *; };" >> $lib.exp~ $CC -shared $pic_flag ${wl}-z ${wl}text ${wl}-M ${wl}$lib.exp ${wl}-h ${wl}$soname -o $lib $libobjs $deplibs $compiler_flags~$RM $lib.exp' else case `$CC -V 2>&1` in *"Compilers 5.0"*) wlarc='' archive_cmds='$LD -G${allow_undefined_flag} -h $soname -o $lib $libobjs $deplibs $linker_flags' archive_expsym_cmds='echo "{ global:" > $lib.exp~cat $export_symbols | $SED -e "s/\(.*\)/\1;/" >> $lib.exp~echo "local: *; };" >> $lib.exp~ $LD -G${allow_undefined_flag} -M $lib.exp -h $soname -o $lib $libobjs $deplibs $linker_flags~$RM $lib.exp' ;; *) wlarc='${wl}' archive_cmds='$CC -G${allow_undefined_flag} -h $soname -o $lib $libobjs $deplibs $compiler_flags' archive_expsym_cmds='echo "{ global:" > $lib.exp~cat $export_symbols | $SED -e "s/\(.*\)/\1;/" >> $lib.exp~echo "local: *; };" >> $lib.exp~ $CC -G${allow_undefined_flag} -M $lib.exp -h $soname -o $lib $libobjs $deplibs $compiler_flags~$RM $lib.exp' ;; esac fi hardcode_libdir_flag_spec='-R$libdir' hardcode_shlibpath_var=no case $host_os in solaris2.[0-5] | solaris2.[0-5].*) ;; *) # The compiler driver will combine and reorder linker options, # but understands `-z linker_flag'. GCC discards it without `$wl', # but is careful enough not to reorder. # Supported since Solaris 2.6 (maybe 2.5.1?) if test "$GCC" = yes; then whole_archive_flag_spec='${wl}-z ${wl}allextract$convenience ${wl}-z ${wl}defaultextract' else whole_archive_flag_spec='-z allextract$convenience -z defaultextract' fi ;; esac link_all_deplibs=yes ;; sunos4*) if test "x$host_vendor" = xsequent; then # Use $CC to link under sequent, because it throws in some extra .o # files that make .init and .fini sections work. archive_cmds='$CC -G ${wl}-h $soname -o $lib $libobjs $deplibs $compiler_flags' else archive_cmds='$LD -assert pure-text -Bstatic -o $lib $libobjs $deplibs $linker_flags' fi hardcode_libdir_flag_spec='-L$libdir' hardcode_direct=yes hardcode_minus_L=yes hardcode_shlibpath_var=no ;; sysv4) case $host_vendor in sni) archive_cmds='$LD -G -h $soname -o $lib $libobjs $deplibs $linker_flags' hardcode_direct=yes # is this really true??? ;; siemens) ## LD is ld it makes a PLAMLIB ## CC just makes a GrossModule. archive_cmds='$LD -G -o $lib $libobjs $deplibs $linker_flags' reload_cmds='$CC -r -o $output$reload_objs' hardcode_direct=no ;; motorola) archive_cmds='$LD -G -h $soname -o $lib $libobjs $deplibs $linker_flags' hardcode_direct=no #Motorola manual says yes, but my tests say they lie ;; esac runpath_var='LD_RUN_PATH' hardcode_shlibpath_var=no ;; sysv4.3*) archive_cmds='$LD -G -h $soname -o $lib $libobjs $deplibs $linker_flags' hardcode_shlibpath_var=no export_dynamic_flag_spec='-Bexport' ;; sysv4*MP*) if test -d /usr/nec; then archive_cmds='$LD -G -h $soname -o $lib $libobjs $deplibs $linker_flags' hardcode_shlibpath_var=no runpath_var=LD_RUN_PATH hardcode_runpath_var=yes ld_shlibs=yes fi ;; sysv4*uw2* | sysv5OpenUNIX* | sysv5UnixWare7.[01].[10]* | unixware7* | sco3.2v5.0.[024]*) no_undefined_flag='${wl}-z,text' archive_cmds_need_lc=no hardcode_shlibpath_var=no runpath_var='LD_RUN_PATH' if test "$GCC" = yes; then archive_cmds='$CC -shared ${wl}-h,$soname -o $lib $libobjs $deplibs $compiler_flags' archive_expsym_cmds='$CC -shared ${wl}-Bexport:$export_symbols ${wl}-h,$soname -o $lib $libobjs $deplibs $compiler_flags' else archive_cmds='$CC -G ${wl}-h,$soname -o $lib $libobjs $deplibs $compiler_flags' archive_expsym_cmds='$CC -G ${wl}-Bexport:$export_symbols ${wl}-h,$soname -o $lib $libobjs $deplibs $compiler_flags' fi ;; sysv5* | sco3.2v5* | sco5v6*) # Note: We can NOT use -z defs as we might desire, because we do not # link with -lc, and that would cause any symbols used from libc to # always be unresolved, which means just about no library would # ever link correctly. If we're not using GNU ld we use -z text # though, which does catch some bad symbols but isn't as heavy-handed # as -z defs. no_undefined_flag='${wl}-z,text' allow_undefined_flag='${wl}-z,nodefs' archive_cmds_need_lc=no hardcode_shlibpath_var=no hardcode_libdir_flag_spec='${wl}-R,$libdir' hardcode_libdir_separator=':' link_all_deplibs=yes export_dynamic_flag_spec='${wl}-Bexport' runpath_var='LD_RUN_PATH' if test "$GCC" = yes; then archive_cmds='$CC -shared ${wl}-h,$soname -o $lib $libobjs $deplibs $compiler_flags' archive_expsym_cmds='$CC -shared ${wl}-Bexport:$export_symbols ${wl}-h,$soname -o $lib $libobjs $deplibs $compiler_flags' else archive_cmds='$CC -G ${wl}-h,$soname -o $lib $libobjs $deplibs $compiler_flags' archive_expsym_cmds='$CC -G ${wl}-Bexport:$export_symbols ${wl}-h,$soname -o $lib $libobjs $deplibs $compiler_flags' fi ;; uts4*) archive_cmds='$LD -G -h $soname -o $lib $libobjs $deplibs $linker_flags' hardcode_libdir_flag_spec='-L$libdir' hardcode_shlibpath_var=no ;; *) ld_shlibs=no ;; esac if test x$host_vendor = xsni; then case $host in sysv4 | sysv4.2uw2* | sysv4.3* | sysv5*) export_dynamic_flag_spec='${wl}-Blargedynsym' ;; esac fi fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ld_shlibs" >&5 $as_echo "$ld_shlibs" >&6; } test "$ld_shlibs" = no && can_build_shared=no with_gnu_ld=$with_gnu_ld # # Do we need to explicitly link libc? # case "x$archive_cmds_need_lc" in x|xyes) # Assume -lc should be added archive_cmds_need_lc=yes if test "$enable_shared" = yes && test "$GCC" = yes; then case $archive_cmds in *'~'*) # FIXME: we may have to deal with multi-command sequences. ;; '$CC '*) # Test whether the compiler implicitly links with -lc since on some # systems, -lgcc has to come before -lc. If gcc already passes -lc # to ld, don't add -lc before -lgcc. { $as_echo "$as_me:${as_lineno-$LINENO}: checking whether -lc should be explicitly linked in" >&5 $as_echo_n "checking whether -lc should be explicitly linked in... " >&6; } if ${lt_cv_archive_cmds_need_lc+:} false; then : $as_echo_n "(cached) " >&6 else $RM conftest* echo "$lt_simple_compile_test_code" > conftest.$ac_ext if { { eval echo "\"\$as_me\":${as_lineno-$LINENO}: \"$ac_compile\""; } >&5 (eval $ac_compile) 2>&5 ac_status=$? $as_echo "$as_me:${as_lineno-$LINENO}: \$? = $ac_status" >&5 test $ac_status = 0; } 2>conftest.err; then soname=conftest lib=conftest libobjs=conftest.$ac_objext deplibs= wl=$lt_prog_compiler_wl pic_flag=$lt_prog_compiler_pic compiler_flags=-v linker_flags=-v verstring= output_objdir=. libname=conftest lt_save_allow_undefined_flag=$allow_undefined_flag allow_undefined_flag= if { { eval echo "\"\$as_me\":${as_lineno-$LINENO}: \"$archive_cmds 2\>\&1 \| $GREP \" -lc \" \>/dev/null 2\>\&1\""; } >&5 (eval $archive_cmds 2\>\&1 \| $GREP \" -lc \" \>/dev/null 2\>\&1) 2>&5 ac_status=$? $as_echo "$as_me:${as_lineno-$LINENO}: \$? = $ac_status" >&5 test $ac_status = 0; } then lt_cv_archive_cmds_need_lc=no else lt_cv_archive_cmds_need_lc=yes fi allow_undefined_flag=$lt_save_allow_undefined_flag else cat conftest.err 1>&5 fi $RM conftest* fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $lt_cv_archive_cmds_need_lc" >&5 $as_echo "$lt_cv_archive_cmds_need_lc" >&6; } archive_cmds_need_lc=$lt_cv_archive_cmds_need_lc ;; esac fi ;; esac { $as_echo "$as_me:${as_lineno-$LINENO}: checking dynamic linker characteristics" >&5 $as_echo_n "checking dynamic linker characteristics... " >&6; } if test "$GCC" = yes; then case $host_os in darwin*) lt_awk_arg="/^libraries:/,/LR/" ;; *) lt_awk_arg="/^libraries:/" ;; esac case $host_os in mingw* | cegcc*) lt_sed_strip_eq="s,=\([A-Za-z]:\),\1,g" ;; *) lt_sed_strip_eq="s,=/,/,g" ;; esac lt_search_path_spec=`$CC -print-search-dirs | awk $lt_awk_arg | $SED -e "s/^libraries://" -e $lt_sed_strip_eq` case $lt_search_path_spec in *\;*) # if the path contains ";" then we assume it to be the separator # otherwise default to the standard path separator (i.e. ":") - it is # assumed that no part of a normal pathname contains ";" but that should # okay in the real world where ";" in dirpaths is itself problematic. lt_search_path_spec=`$ECHO "$lt_search_path_spec" | $SED 's/;/ /g'` ;; *) lt_search_path_spec=`$ECHO "$lt_search_path_spec" | $SED "s/$PATH_SEPARATOR/ /g"` ;; esac # Ok, now we have the path, separated by spaces, we can step through it # and add multilib dir if necessary. lt_tmp_lt_search_path_spec= lt_multi_os_dir=`$CC $CPPFLAGS $CFLAGS $LDFLAGS -print-multi-os-directory 2>/dev/null` for lt_sys_path in $lt_search_path_spec; do if test -d "$lt_sys_path/$lt_multi_os_dir"; then lt_tmp_lt_search_path_spec="$lt_tmp_lt_search_path_spec $lt_sys_path/$lt_multi_os_dir" else test -d "$lt_sys_path" && \ lt_tmp_lt_search_path_spec="$lt_tmp_lt_search_path_spec $lt_sys_path" fi done lt_search_path_spec=`$ECHO "$lt_tmp_lt_search_path_spec" | awk ' BEGIN {RS=" "; FS="/|\n";} { lt_foo=""; lt_count=0; for (lt_i = NF; lt_i > 0; lt_i--) { if ($lt_i != "" && $lt_i != ".") { if ($lt_i == "..") { lt_count++; } else { if (lt_count == 0) { lt_foo="/" $lt_i lt_foo; } else { lt_count--; } } } } if (lt_foo != "") { lt_freq[lt_foo]++; } if (lt_freq[lt_foo] == 1) { print lt_foo; } }'` # AWK program above erroneously prepends '/' to C:/dos/paths # for these hosts. case $host_os in mingw* | cegcc*) lt_search_path_spec=`$ECHO "$lt_search_path_spec" |\ $SED 's,/\([A-Za-z]:\),\1,g'` ;; esac sys_lib_search_path_spec=`$ECHO "$lt_search_path_spec" | $lt_NL2SP` else sys_lib_search_path_spec="/lib /usr/lib /usr/local/lib" fi library_names_spec= libname_spec='lib$name' soname_spec= shrext_cmds=".so" postinstall_cmds= postuninstall_cmds= finish_cmds= finish_eval= shlibpath_var= shlibpath_overrides_runpath=unknown version_type=none dynamic_linker="$host_os ld.so" sys_lib_dlsearch_path_spec="/lib /usr/lib" need_lib_prefix=unknown hardcode_into_libs=no # when you set need_version to no, make sure it does not cause -set_version # flags to be left without arguments need_version=unknown case $host_os in aix3*) version_type=linux # correct to gnu/linux during the next big refactor library_names_spec='${libname}${release}${shared_ext}$versuffix $libname.a' shlibpath_var=LIBPATH # AIX 3 has no versioning support, so we append a major version to the name. soname_spec='${libname}${release}${shared_ext}$major' ;; aix[4-9]*) version_type=linux # correct to gnu/linux during the next big refactor need_lib_prefix=no need_version=no hardcode_into_libs=yes if test "$host_cpu" = ia64; then # AIX 5 supports IA64 library_names_spec='${libname}${release}${shared_ext}$major ${libname}${release}${shared_ext}$versuffix $libname${shared_ext}' shlibpath_var=LD_LIBRARY_PATH else # With GCC up to 2.95.x, collect2 would create an import file # for dependence libraries. The import file would start with # the line `#! .'. This would cause the generated library to # depend on `.', always an invalid library. This was fixed in # development snapshots of GCC prior to 3.0. case $host_os in aix4 | aix4.[01] | aix4.[01].*) if { echo '#if __GNUC__ > 2 || (__GNUC__ == 2 && __GNUC_MINOR__ >= 97)' echo ' yes ' echo '#endif'; } | ${CC} -E - | $GREP yes > /dev/null; then : else can_build_shared=no fi ;; esac # AIX (on Power*) has no versioning support, so currently we can not hardcode correct # soname into executable. Probably we can add versioning support to # collect2, so additional links can be useful in future. if test "$aix_use_runtimelinking" = yes; then # If using run time linking (on AIX 4.2 or later) use lib.so # instead of lib.a to let people know that these are not # typical AIX shared libraries. library_names_spec='${libname}${release}${shared_ext}$versuffix ${libname}${release}${shared_ext}$major $libname${shared_ext}' else # We preserve .a as extension for shared libraries through AIX4.2 # and later when we are not doing run time linking. library_names_spec='${libname}${release}.a $libname.a' soname_spec='${libname}${release}${shared_ext}$major' fi shlibpath_var=LIBPATH fi ;; amigaos*) case $host_cpu in powerpc) # Since July 2007 AmigaOS4 officially supports .so libraries. # When compiling the executable, add -use-dynld -Lsobjs: to the compileline. library_names_spec='${libname}${release}${shared_ext}$versuffix ${libname}${release}${shared_ext}$major $libname${shared_ext}' ;; m68k) library_names_spec='$libname.ixlibrary $libname.a' # Create ${libname}_ixlibrary.a entries in /sys/libs. finish_eval='for lib in `ls $libdir/*.ixlibrary 2>/dev/null`; do libname=`func_echo_all "$lib" | $SED '\''s%^.*/\([^/]*\)\.ixlibrary$%\1%'\''`; test $RM /sys/libs/${libname}_ixlibrary.a; $show "cd /sys/libs && $LN_S $lib ${libname}_ixlibrary.a"; cd /sys/libs && $LN_S $lib ${libname}_ixlibrary.a || exit 1; done' ;; esac ;; beos*) library_names_spec='${libname}${shared_ext}' dynamic_linker="$host_os ld.so" shlibpath_var=LIBRARY_PATH ;; bsdi[45]*) version_type=linux # correct to gnu/linux during the next big refactor need_version=no library_names_spec='${libname}${release}${shared_ext}$versuffix ${libname}${release}${shared_ext}$major $libname${shared_ext}' soname_spec='${libname}${release}${shared_ext}$major' finish_cmds='PATH="\$PATH:/sbin" ldconfig $libdir' shlibpath_var=LD_LIBRARY_PATH sys_lib_search_path_spec="/shlib /usr/lib /usr/X11/lib /usr/contrib/lib /lib /usr/local/lib" sys_lib_dlsearch_path_spec="/shlib /usr/lib /usr/local/lib" # the default ld.so.conf also contains /usr/contrib/lib and # /usr/X11R6/lib (/usr/X11 is a link to /usr/X11R6), but let us allow # libtool to hard-code these into programs ;; cygwin* | mingw* | pw32* | cegcc*) version_type=windows shrext_cmds=".dll" need_version=no need_lib_prefix=no case $GCC,$cc_basename in yes,*) # gcc library_names_spec='$libname.dll.a' # DLL is installed to $(libdir)/../bin by postinstall_cmds postinstall_cmds='base_file=`basename \${file}`~ dlpath=`$SHELL 2>&1 -c '\''. $dir/'\''\${base_file}'\''i; echo \$dlname'\''`~ dldir=$destdir/`dirname \$dlpath`~ test -d \$dldir || mkdir -p \$dldir~ $install_prog $dir/$dlname \$dldir/$dlname~ chmod a+x \$dldir/$dlname~ if test -n '\''$stripme'\'' && test -n '\''$striplib'\''; then eval '\''$striplib \$dldir/$dlname'\'' || exit \$?; fi' postuninstall_cmds='dldll=`$SHELL 2>&1 -c '\''. $file; echo \$dlname'\''`~ dlpath=$dir/\$dldll~ $RM \$dlpath' shlibpath_overrides_runpath=yes case $host_os in cygwin*) # Cygwin DLLs use 'cyg' prefix rather than 'lib' soname_spec='`echo ${libname} | sed -e 's/^lib/cyg/'``echo ${release} | $SED -e 's/[.]/-/g'`${versuffix}${shared_ext}' sys_lib_search_path_spec="$sys_lib_search_path_spec /usr/lib/w32api" ;; mingw* | cegcc*) # MinGW DLLs use traditional 'lib' prefix soname_spec='${libname}`echo ${release} | $SED -e 's/[.]/-/g'`${versuffix}${shared_ext}' ;; pw32*) # pw32 DLLs use 'pw' prefix rather than 'lib' library_names_spec='`echo ${libname} | sed -e 's/^lib/pw/'``echo ${release} | $SED -e 's/[.]/-/g'`${versuffix}${shared_ext}' ;; esac dynamic_linker='Win32 ld.exe' ;; *,cl*) # Native MSVC libname_spec='$name' soname_spec='${libname}`echo ${release} | $SED -e 's/[.]/-/g'`${versuffix}${shared_ext}' library_names_spec='${libname}.dll.lib' case $build_os in mingw*) sys_lib_search_path_spec= lt_save_ifs=$IFS IFS=';' for lt_path in $LIB do IFS=$lt_save_ifs # Let DOS variable expansion print the short 8.3 style file name. lt_path=`cd "$lt_path" 2>/dev/null && cmd //C "for %i in (".") do @echo %~si"` sys_lib_search_path_spec="$sys_lib_search_path_spec $lt_path" done IFS=$lt_save_ifs # Convert to MSYS style. sys_lib_search_path_spec=`$ECHO "$sys_lib_search_path_spec" | sed -e 's|\\\\|/|g' -e 's| \\([a-zA-Z]\\):| /\\1|g' -e 's|^ ||'` ;; cygwin*) # Convert to unix form, then to dos form, then back to unix form # but this time dos style (no spaces!) so that the unix form looks # like /cygdrive/c/PROGRA~1:/cygdr... sys_lib_search_path_spec=`cygpath --path --unix "$LIB"` sys_lib_search_path_spec=`cygpath --path --dos "$sys_lib_search_path_spec" 2>/dev/null` sys_lib_search_path_spec=`cygpath --path --unix "$sys_lib_search_path_spec" | $SED -e "s/$PATH_SEPARATOR/ /g"` ;; *) sys_lib_search_path_spec="$LIB" if $ECHO "$sys_lib_search_path_spec" | $GREP ';[c-zC-Z]:/' >/dev/null; then # It is most probably a Windows format PATH. sys_lib_search_path_spec=`$ECHO "$sys_lib_search_path_spec" | $SED -e 's/;/ /g'` else sys_lib_search_path_spec=`$ECHO "$sys_lib_search_path_spec" | $SED -e "s/$PATH_SEPARATOR/ /g"` fi # FIXME: find the short name or the path components, as spaces are # common. (e.g. "Program Files" -> "PROGRA~1") ;; esac # DLL is installed to $(libdir)/../bin by postinstall_cmds postinstall_cmds='base_file=`basename \${file}`~ dlpath=`$SHELL 2>&1 -c '\''. $dir/'\''\${base_file}'\''i; echo \$dlname'\''`~ dldir=$destdir/`dirname \$dlpath`~ test -d \$dldir || mkdir -p \$dldir~ $install_prog $dir/$dlname \$dldir/$dlname' postuninstall_cmds='dldll=`$SHELL 2>&1 -c '\''. $file; echo \$dlname'\''`~ dlpath=$dir/\$dldll~ $RM \$dlpath' shlibpath_overrides_runpath=yes dynamic_linker='Win32 link.exe' ;; *) # Assume MSVC wrapper library_names_spec='${libname}`echo ${release} | $SED -e 's/[.]/-/g'`${versuffix}${shared_ext} $libname.lib' dynamic_linker='Win32 ld.exe' ;; esac # FIXME: first we should search . and the directory the executable is in shlibpath_var=PATH ;; darwin* | rhapsody*) dynamic_linker="$host_os dyld" version_type=darwin need_lib_prefix=no need_version=no library_names_spec='${libname}${release}${major}$shared_ext ${libname}$shared_ext' soname_spec='${libname}${release}${major}$shared_ext' shlibpath_overrides_runpath=yes shlibpath_var=DYLD_LIBRARY_PATH shrext_cmds='`test .$module = .yes && echo .so || echo .dylib`' sys_lib_search_path_spec="$sys_lib_search_path_spec /usr/local/lib" sys_lib_dlsearch_path_spec='/usr/local/lib /lib /usr/lib' ;; dgux*) version_type=linux # correct to gnu/linux during the next big refactor need_lib_prefix=no need_version=no library_names_spec='${libname}${release}${shared_ext}$versuffix ${libname}${release}${shared_ext}$major $libname$shared_ext' soname_spec='${libname}${release}${shared_ext}$major' shlibpath_var=LD_LIBRARY_PATH ;; freebsd* | dragonfly*) # DragonFly does not have aout. When/if they implement a new # versioning mechanism, adjust this. if test -x /usr/bin/objformat; then objformat=`/usr/bin/objformat` else case $host_os in freebsd[23].*) objformat=aout ;; *) objformat=elf ;; esac fi version_type=freebsd-$objformat case $version_type in freebsd-elf*) library_names_spec='${libname}${release}${shared_ext}$versuffix ${libname}${release}${shared_ext} $libname${shared_ext}' need_version=no need_lib_prefix=no ;; freebsd-*) library_names_spec='${libname}${release}${shared_ext}$versuffix $libname${shared_ext}$versuffix' need_version=yes ;; esac shlibpath_var=LD_LIBRARY_PATH case $host_os in freebsd2.*) shlibpath_overrides_runpath=yes ;; freebsd3.[01]* | freebsdelf3.[01]*) shlibpath_overrides_runpath=yes hardcode_into_libs=yes ;; freebsd3.[2-9]* | freebsdelf3.[2-9]* | \ freebsd4.[0-5] | freebsdelf4.[0-5] | freebsd4.1.1 | freebsdelf4.1.1) shlibpath_overrides_runpath=no hardcode_into_libs=yes ;; *) # from 4.6 on, and DragonFly shlibpath_overrides_runpath=yes hardcode_into_libs=yes ;; esac ;; haiku*) version_type=linux # correct to gnu/linux during the next big refactor need_lib_prefix=no need_version=no dynamic_linker="$host_os runtime_loader" library_names_spec='${libname}${release}${shared_ext}$versuffix ${libname}${release}${shared_ext}${major} ${libname}${shared_ext}' soname_spec='${libname}${release}${shared_ext}$major' shlibpath_var=LIBRARY_PATH shlibpath_overrides_runpath=yes sys_lib_dlsearch_path_spec='/boot/home/config/lib /boot/common/lib /boot/system/lib' hardcode_into_libs=yes ;; hpux9* | hpux10* | hpux11*) # Give a soname corresponding to the major version so that dld.sl refuses to # link against other versions. version_type=sunos need_lib_prefix=no need_version=no case $host_cpu in ia64*) shrext_cmds='.so' hardcode_into_libs=yes dynamic_linker="$host_os dld.so" shlibpath_var=LD_LIBRARY_PATH shlibpath_overrides_runpath=yes # Unless +noenvvar is specified. library_names_spec='${libname}${release}${shared_ext}$versuffix ${libname}${release}${shared_ext}$major $libname${shared_ext}' soname_spec='${libname}${release}${shared_ext}$major' if test "X$HPUX_IA64_MODE" = X32; then sys_lib_search_path_spec="/usr/lib/hpux32 /usr/local/lib/hpux32 /usr/local/lib" else sys_lib_search_path_spec="/usr/lib/hpux64 /usr/local/lib/hpux64" fi sys_lib_dlsearch_path_spec=$sys_lib_search_path_spec ;; hppa*64*) shrext_cmds='.sl' hardcode_into_libs=yes dynamic_linker="$host_os dld.sl" shlibpath_var=LD_LIBRARY_PATH # How should we handle SHLIB_PATH shlibpath_overrides_runpath=yes # Unless +noenvvar is specified. library_names_spec='${libname}${release}${shared_ext}$versuffix ${libname}${release}${shared_ext}$major $libname${shared_ext}' soname_spec='${libname}${release}${shared_ext}$major' sys_lib_search_path_spec="/usr/lib/pa20_64 /usr/ccs/lib/pa20_64" sys_lib_dlsearch_path_spec=$sys_lib_search_path_spec ;; *) shrext_cmds='.sl' dynamic_linker="$host_os dld.sl" shlibpath_var=SHLIB_PATH shlibpath_overrides_runpath=no # +s is required to enable SHLIB_PATH library_names_spec='${libname}${release}${shared_ext}$versuffix ${libname}${release}${shared_ext}$major $libname${shared_ext}' soname_spec='${libname}${release}${shared_ext}$major' ;; esac # HP-UX runs *really* slowly unless shared libraries are mode 555, ... postinstall_cmds='chmod 555 $lib' # or fails outright, so override atomically: install_override_mode=555 ;; interix[3-9]*) version_type=linux # correct to gnu/linux during the next big refactor need_lib_prefix=no need_version=no library_names_spec='${libname}${release}${shared_ext}$versuffix ${libname}${release}${shared_ext}$major ${libname}${shared_ext}' soname_spec='${libname}${release}${shared_ext}$major' dynamic_linker='Interix 3.x ld.so.1 (PE, like ELF)' shlibpath_var=LD_LIBRARY_PATH shlibpath_overrides_runpath=no hardcode_into_libs=yes ;; irix5* | irix6* | nonstopux*) case $host_os in nonstopux*) version_type=nonstopux ;; *) if test "$lt_cv_prog_gnu_ld" = yes; then version_type=linux # correct to gnu/linux during the next big refactor else version_type=irix fi ;; esac need_lib_prefix=no need_version=no soname_spec='${libname}${release}${shared_ext}$major' library_names_spec='${libname}${release}${shared_ext}$versuffix ${libname}${release}${shared_ext}$major ${libname}${release}${shared_ext} $libname${shared_ext}' case $host_os in irix5* | nonstopux*) libsuff= shlibsuff= ;; *) case $LD in # libtool.m4 will add one of these switches to LD *-32|*"-32 "|*-melf32bsmip|*"-melf32bsmip ") libsuff= shlibsuff= libmagic=32-bit;; *-n32|*"-n32 "|*-melf32bmipn32|*"-melf32bmipn32 ") libsuff=32 shlibsuff=N32 libmagic=N32;; *-64|*"-64 "|*-melf64bmip|*"-melf64bmip ") libsuff=64 shlibsuff=64 libmagic=64-bit;; *) libsuff= shlibsuff= libmagic=never-match;; esac ;; esac shlibpath_var=LD_LIBRARY${shlibsuff}_PATH shlibpath_overrides_runpath=no sys_lib_search_path_spec="/usr/lib${libsuff} /lib${libsuff} /usr/local/lib${libsuff}" sys_lib_dlsearch_path_spec="/usr/lib${libsuff} /lib${libsuff}" hardcode_into_libs=yes ;; # No shared lib support for Linux oldld, aout, or coff. linux*oldld* | linux*aout* | linux*coff*) dynamic_linker=no ;; # This must be glibc/ELF. linux* | k*bsd*-gnu | kopensolaris*-gnu | gnu*) version_type=linux # correct to gnu/linux during the next big refactor need_lib_prefix=no need_version=no library_names_spec='${libname}${release}${shared_ext}$versuffix ${libname}${release}${shared_ext}$major $libname${shared_ext}' soname_spec='${libname}${release}${shared_ext}$major' finish_cmds='PATH="\$PATH:/sbin" ldconfig -n $libdir' shlibpath_var=LD_LIBRARY_PATH shlibpath_overrides_runpath=no # Some binutils ld are patched to set DT_RUNPATH if ${lt_cv_shlibpath_overrides_runpath+:} false; then : $as_echo_n "(cached) " >&6 else lt_cv_shlibpath_overrides_runpath=no save_LDFLAGS=$LDFLAGS save_libdir=$libdir eval "libdir=/foo; wl=\"$lt_prog_compiler_wl\"; \ LDFLAGS=\"\$LDFLAGS $hardcode_libdir_flag_spec\"" cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ int main () { ; return 0; } _ACEOF if ac_fn_c_try_link "$LINENO"; then : if ($OBJDUMP -p conftest$ac_exeext) 2>/dev/null | grep "RUNPATH.*$libdir" >/dev/null; then : lt_cv_shlibpath_overrides_runpath=yes fi fi rm -f core conftest.err conftest.$ac_objext \ conftest$ac_exeext conftest.$ac_ext LDFLAGS=$save_LDFLAGS libdir=$save_libdir fi shlibpath_overrides_runpath=$lt_cv_shlibpath_overrides_runpath # This implies no fast_install, which is unacceptable. # Some rework will be needed to allow for fast_install # before this can be enabled. hardcode_into_libs=yes # Append ld.so.conf contents to the search path if test -f /etc/ld.so.conf; then lt_ld_extra=`awk '/^include / { system(sprintf("cd /etc; cat %s 2>/dev/null", \$2)); skip = 1; } { if (!skip) print \$0; skip = 0; }' < /etc/ld.so.conf | $SED -e 's/#.*//;/^[ ]*hwcap[ ]/d;s/[:, ]/ /g;s/=[^=]*$//;s/=[^= ]* / /g;s/"//g;/^$/d' | tr '\n' ' '` sys_lib_dlsearch_path_spec="/lib /usr/lib $lt_ld_extra" fi # We used to test for /lib/ld.so.1 and disable shared libraries on # powerpc, because MkLinux only supported shared libraries with the # GNU dynamic linker. Since this was broken with cross compilers, # most powerpc-linux boxes support dynamic linking these days and # people can always --disable-shared, the test was removed, and we # assume the GNU/Linux dynamic linker is in use. dynamic_linker='GNU/Linux ld.so' ;; netbsdelf*-gnu) version_type=linux need_lib_prefix=no need_version=no library_names_spec='${libname}${release}${shared_ext}$versuffix ${libname}${release}${shared_ext}$major ${libname}${shared_ext}' soname_spec='${libname}${release}${shared_ext}$major' shlibpath_var=LD_LIBRARY_PATH shlibpath_overrides_runpath=no hardcode_into_libs=yes dynamic_linker='NetBSD ld.elf_so' ;; netbsd*) version_type=sunos need_lib_prefix=no need_version=no if echo __ELF__ | $CC -E - | $GREP __ELF__ >/dev/null; then library_names_spec='${libname}${release}${shared_ext}$versuffix ${libname}${shared_ext}$versuffix' finish_cmds='PATH="\$PATH:/sbin" ldconfig -m $libdir' dynamic_linker='NetBSD (a.out) ld.so' else library_names_spec='${libname}${release}${shared_ext}$versuffix ${libname}${release}${shared_ext}$major ${libname}${shared_ext}' soname_spec='${libname}${release}${shared_ext}$major' dynamic_linker='NetBSD ld.elf_so' fi shlibpath_var=LD_LIBRARY_PATH shlibpath_overrides_runpath=yes hardcode_into_libs=yes ;; newsos6) version_type=linux # correct to gnu/linux during the next big refactor library_names_spec='${libname}${release}${shared_ext}$versuffix ${libname}${release}${shared_ext}$major $libname${shared_ext}' shlibpath_var=LD_LIBRARY_PATH shlibpath_overrides_runpath=yes ;; *nto* | *qnx*) version_type=qnx need_lib_prefix=no need_version=no library_names_spec='${libname}${release}${shared_ext}$versuffix ${libname}${release}${shared_ext}$major $libname${shared_ext}' soname_spec='${libname}${release}${shared_ext}$major' shlibpath_var=LD_LIBRARY_PATH shlibpath_overrides_runpath=no hardcode_into_libs=yes dynamic_linker='ldqnx.so' ;; openbsd*) version_type=sunos sys_lib_dlsearch_path_spec="/usr/lib" need_lib_prefix=no # Some older versions of OpenBSD (3.3 at least) *do* need versioned libs. case $host_os in openbsd3.3 | openbsd3.3.*) need_version=yes ;; *) need_version=no ;; esac library_names_spec='${libname}${release}${shared_ext}$versuffix ${libname}${shared_ext}$versuffix' finish_cmds='PATH="\$PATH:/sbin" ldconfig -m $libdir' shlibpath_var=LD_LIBRARY_PATH if test -z "`echo __ELF__ | $CC -E - | $GREP __ELF__`" || test "$host_os-$host_cpu" = "openbsd2.8-powerpc"; then case $host_os in openbsd2.[89] | openbsd2.[89].*) shlibpath_overrides_runpath=no ;; *) shlibpath_overrides_runpath=yes ;; esac else shlibpath_overrides_runpath=yes fi ;; os2*) libname_spec='$name' shrext_cmds=".dll" need_lib_prefix=no library_names_spec='$libname${shared_ext} $libname.a' dynamic_linker='OS/2 ld.exe' shlibpath_var=LIBPATH ;; osf3* | osf4* | osf5*) version_type=osf need_lib_prefix=no need_version=no soname_spec='${libname}${release}${shared_ext}$major' library_names_spec='${libname}${release}${shared_ext}$versuffix ${libname}${release}${shared_ext}$major $libname${shared_ext}' shlibpath_var=LD_LIBRARY_PATH sys_lib_search_path_spec="/usr/shlib /usr/ccs/lib /usr/lib/cmplrs/cc /usr/lib /usr/local/lib /var/shlib" sys_lib_dlsearch_path_spec="$sys_lib_search_path_spec" ;; rdos*) dynamic_linker=no ;; solaris*) version_type=linux # correct to gnu/linux during the next big refactor need_lib_prefix=no need_version=no library_names_spec='${libname}${release}${shared_ext}$versuffix ${libname}${release}${shared_ext}$major $libname${shared_ext}' soname_spec='${libname}${release}${shared_ext}$major' shlibpath_var=LD_LIBRARY_PATH shlibpath_overrides_runpath=yes hardcode_into_libs=yes # ldd complains unless libraries are executable postinstall_cmds='chmod +x $lib' ;; sunos4*) version_type=sunos library_names_spec='${libname}${release}${shared_ext}$versuffix ${libname}${shared_ext}$versuffix' finish_cmds='PATH="\$PATH:/usr/etc" ldconfig $libdir' shlibpath_var=LD_LIBRARY_PATH shlibpath_overrides_runpath=yes if test "$with_gnu_ld" = yes; then need_lib_prefix=no fi need_version=yes ;; sysv4 | sysv4.3*) version_type=linux # correct to gnu/linux during the next big refactor library_names_spec='${libname}${release}${shared_ext}$versuffix ${libname}${release}${shared_ext}$major $libname${shared_ext}' soname_spec='${libname}${release}${shared_ext}$major' shlibpath_var=LD_LIBRARY_PATH case $host_vendor in sni) shlibpath_overrides_runpath=no need_lib_prefix=no runpath_var=LD_RUN_PATH ;; siemens) need_lib_prefix=no ;; motorola) need_lib_prefix=no need_version=no shlibpath_overrides_runpath=no sys_lib_search_path_spec='/lib /usr/lib /usr/ccs/lib' ;; esac ;; sysv4*MP*) if test -d /usr/nec ;then version_type=linux # correct to gnu/linux during the next big refactor library_names_spec='$libname${shared_ext}.$versuffix $libname${shared_ext}.$major $libname${shared_ext}' soname_spec='$libname${shared_ext}.$major' shlibpath_var=LD_LIBRARY_PATH fi ;; sysv5* | sco3.2v5* | sco5v6* | unixware* | OpenUNIX* | sysv4*uw2*) version_type=freebsd-elf need_lib_prefix=no need_version=no library_names_spec='${libname}${release}${shared_ext}$versuffix ${libname}${release}${shared_ext} $libname${shared_ext}' soname_spec='${libname}${release}${shared_ext}$major' shlibpath_var=LD_LIBRARY_PATH shlibpath_overrides_runpath=yes hardcode_into_libs=yes if test "$with_gnu_ld" = yes; then sys_lib_search_path_spec='/usr/local/lib /usr/gnu/lib /usr/ccs/lib /usr/lib /lib' else sys_lib_search_path_spec='/usr/ccs/lib /usr/lib' case $host_os in sco3.2v5*) sys_lib_search_path_spec="$sys_lib_search_path_spec /lib" ;; esac fi sys_lib_dlsearch_path_spec='/usr/lib' ;; tpf*) # TPF is a cross-target only. Preferred cross-host = GNU/Linux. version_type=linux # correct to gnu/linux during the next big refactor need_lib_prefix=no need_version=no library_names_spec='${libname}${release}${shared_ext}$versuffix ${libname}${release}${shared_ext}$major $libname${shared_ext}' shlibpath_var=LD_LIBRARY_PATH shlibpath_overrides_runpath=no hardcode_into_libs=yes ;; uts4*) version_type=linux # correct to gnu/linux during the next big refactor library_names_spec='${libname}${release}${shared_ext}$versuffix ${libname}${release}${shared_ext}$major $libname${shared_ext}' soname_spec='${libname}${release}${shared_ext}$major' shlibpath_var=LD_LIBRARY_PATH ;; *) dynamic_linker=no ;; esac { $as_echo "$as_me:${as_lineno-$LINENO}: result: $dynamic_linker" >&5 $as_echo "$dynamic_linker" >&6; } test "$dynamic_linker" = no && can_build_shared=no variables_saved_for_relink="PATH $shlibpath_var $runpath_var" if test "$GCC" = yes; then variables_saved_for_relink="$variables_saved_for_relink GCC_EXEC_PREFIX COMPILER_PATH LIBRARY_PATH" fi if test "${lt_cv_sys_lib_search_path_spec+set}" = set; then sys_lib_search_path_spec="$lt_cv_sys_lib_search_path_spec" fi if test "${lt_cv_sys_lib_dlsearch_path_spec+set}" = set; then sys_lib_dlsearch_path_spec="$lt_cv_sys_lib_dlsearch_path_spec" fi { $as_echo "$as_me:${as_lineno-$LINENO}: checking how to hardcode library paths into programs" >&5 $as_echo_n "checking how to hardcode library paths into programs... " >&6; } hardcode_action= if test -n "$hardcode_libdir_flag_spec" || test -n "$runpath_var" || test "X$hardcode_automatic" = "Xyes" ; then # We can hardcode non-existent directories. if test "$hardcode_direct" != no && # If the only mechanism to avoid hardcoding is shlibpath_var, we # have to relink, otherwise we might link with an installed library # when we should be linking with a yet-to-be-installed one ## test "$_LT_TAGVAR(hardcode_shlibpath_var, )" != no && test "$hardcode_minus_L" != no; then # Linking always hardcodes the temporary library directory. hardcode_action=relink else # We can link without hardcoding, and we can hardcode nonexisting dirs. hardcode_action=immediate fi else # We cannot hardcode anything, or else we can only hardcode existing # directories. hardcode_action=unsupported fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $hardcode_action" >&5 $as_echo "$hardcode_action" >&6; } if test "$hardcode_action" = relink || test "$inherit_rpath" = yes; then # Fast installation is not supported enable_fast_install=no elif test "$shlibpath_overrides_runpath" = yes || test "$enable_shared" = no; then # Fast installation is not necessary enable_fast_install=needless fi if test "x$enable_dlopen" != xyes; then enable_dlopen=unknown enable_dlopen_self=unknown enable_dlopen_self_static=unknown else lt_cv_dlopen=no lt_cv_dlopen_libs= case $host_os in beos*) lt_cv_dlopen="load_add_on" lt_cv_dlopen_libs= lt_cv_dlopen_self=yes ;; mingw* | pw32* | cegcc*) lt_cv_dlopen="LoadLibrary" lt_cv_dlopen_libs= ;; cygwin*) lt_cv_dlopen="dlopen" lt_cv_dlopen_libs= ;; darwin*) # if libdl is installed we need to link against it { $as_echo "$as_me:${as_lineno-$LINENO}: checking for dlopen in -ldl" >&5 $as_echo_n "checking for dlopen in -ldl... " >&6; } if ${ac_cv_lib_dl_dlopen+:} false; then : $as_echo_n "(cached) " >&6 else ac_check_lib_save_LIBS=$LIBS LIBS="-ldl $LIBS" cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ /* Override any GCC internal prototype to avoid an error. Use char because int might match the return type of a GCC builtin and then its argument prototype would still apply. */ #ifdef __cplusplus extern "C" #endif char dlopen (); int main () { return dlopen (); ; return 0; } _ACEOF if ac_fn_c_try_link "$LINENO"; then : ac_cv_lib_dl_dlopen=yes else ac_cv_lib_dl_dlopen=no fi rm -f core conftest.err conftest.$ac_objext \ conftest$ac_exeext conftest.$ac_ext LIBS=$ac_check_lib_save_LIBS fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_cv_lib_dl_dlopen" >&5 $as_echo "$ac_cv_lib_dl_dlopen" >&6; } if test "x$ac_cv_lib_dl_dlopen" = xyes; then : lt_cv_dlopen="dlopen" lt_cv_dlopen_libs="-ldl" else lt_cv_dlopen="dyld" lt_cv_dlopen_libs= lt_cv_dlopen_self=yes fi ;; *) ac_fn_c_check_func "$LINENO" "shl_load" "ac_cv_func_shl_load" if test "x$ac_cv_func_shl_load" = xyes; then : lt_cv_dlopen="shl_load" else { $as_echo "$as_me:${as_lineno-$LINENO}: checking for shl_load in -ldld" >&5 $as_echo_n "checking for shl_load in -ldld... " >&6; } if ${ac_cv_lib_dld_shl_load+:} false; then : $as_echo_n "(cached) " >&6 else ac_check_lib_save_LIBS=$LIBS LIBS="-ldld $LIBS" cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ /* Override any GCC internal prototype to avoid an error. Use char because int might match the return type of a GCC builtin and then its argument prototype would still apply. */ #ifdef __cplusplus extern "C" #endif char shl_load (); int main () { return shl_load (); ; return 0; } _ACEOF if ac_fn_c_try_link "$LINENO"; then : ac_cv_lib_dld_shl_load=yes else ac_cv_lib_dld_shl_load=no fi rm -f core conftest.err conftest.$ac_objext \ conftest$ac_exeext conftest.$ac_ext LIBS=$ac_check_lib_save_LIBS fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_cv_lib_dld_shl_load" >&5 $as_echo "$ac_cv_lib_dld_shl_load" >&6; } if test "x$ac_cv_lib_dld_shl_load" = xyes; then : lt_cv_dlopen="shl_load" lt_cv_dlopen_libs="-ldld" else ac_fn_c_check_func "$LINENO" "dlopen" "ac_cv_func_dlopen" if test "x$ac_cv_func_dlopen" = xyes; then : lt_cv_dlopen="dlopen" else { $as_echo "$as_me:${as_lineno-$LINENO}: checking for dlopen in -ldl" >&5 $as_echo_n "checking for dlopen in -ldl... " >&6; } if ${ac_cv_lib_dl_dlopen+:} false; then : $as_echo_n "(cached) " >&6 else ac_check_lib_save_LIBS=$LIBS LIBS="-ldl $LIBS" cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ /* Override any GCC internal prototype to avoid an error. Use char because int might match the return type of a GCC builtin and then its argument prototype would still apply. */ #ifdef __cplusplus extern "C" #endif char dlopen (); int main () { return dlopen (); ; return 0; } _ACEOF if ac_fn_c_try_link "$LINENO"; then : ac_cv_lib_dl_dlopen=yes else ac_cv_lib_dl_dlopen=no fi rm -f core conftest.err conftest.$ac_objext \ conftest$ac_exeext conftest.$ac_ext LIBS=$ac_check_lib_save_LIBS fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_cv_lib_dl_dlopen" >&5 $as_echo "$ac_cv_lib_dl_dlopen" >&6; } if test "x$ac_cv_lib_dl_dlopen" = xyes; then : lt_cv_dlopen="dlopen" lt_cv_dlopen_libs="-ldl" else { $as_echo "$as_me:${as_lineno-$LINENO}: checking for dlopen in -lsvld" >&5 $as_echo_n "checking for dlopen in -lsvld... " >&6; } if ${ac_cv_lib_svld_dlopen+:} false; then : $as_echo_n "(cached) " >&6 else ac_check_lib_save_LIBS=$LIBS LIBS="-lsvld $LIBS" cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ /* Override any GCC internal prototype to avoid an error. Use char because int might match the return type of a GCC builtin and then its argument prototype would still apply. */ #ifdef __cplusplus extern "C" #endif char dlopen (); int main () { return dlopen (); ; return 0; } _ACEOF if ac_fn_c_try_link "$LINENO"; then : ac_cv_lib_svld_dlopen=yes else ac_cv_lib_svld_dlopen=no fi rm -f core conftest.err conftest.$ac_objext \ conftest$ac_exeext conftest.$ac_ext LIBS=$ac_check_lib_save_LIBS fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_cv_lib_svld_dlopen" >&5 $as_echo "$ac_cv_lib_svld_dlopen" >&6; } if test "x$ac_cv_lib_svld_dlopen" = xyes; then : lt_cv_dlopen="dlopen" lt_cv_dlopen_libs="-lsvld" else { $as_echo "$as_me:${as_lineno-$LINENO}: checking for dld_link in -ldld" >&5 $as_echo_n "checking for dld_link in -ldld... " >&6; } if ${ac_cv_lib_dld_dld_link+:} false; then : $as_echo_n "(cached) " >&6 else ac_check_lib_save_LIBS=$LIBS LIBS="-ldld $LIBS" cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ /* Override any GCC internal prototype to avoid an error. Use char because int might match the return type of a GCC builtin and then its argument prototype would still apply. */ #ifdef __cplusplus extern "C" #endif char dld_link (); int main () { return dld_link (); ; return 0; } _ACEOF if ac_fn_c_try_link "$LINENO"; then : ac_cv_lib_dld_dld_link=yes else ac_cv_lib_dld_dld_link=no fi rm -f core conftest.err conftest.$ac_objext \ conftest$ac_exeext conftest.$ac_ext LIBS=$ac_check_lib_save_LIBS fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_cv_lib_dld_dld_link" >&5 $as_echo "$ac_cv_lib_dld_dld_link" >&6; } if test "x$ac_cv_lib_dld_dld_link" = xyes; then : lt_cv_dlopen="dld_link" lt_cv_dlopen_libs="-ldld" fi fi fi fi fi fi ;; esac if test "x$lt_cv_dlopen" != xno; then enable_dlopen=yes else enable_dlopen=no fi case $lt_cv_dlopen in dlopen) save_CPPFLAGS="$CPPFLAGS" test "x$ac_cv_header_dlfcn_h" = xyes && CPPFLAGS="$CPPFLAGS -DHAVE_DLFCN_H" save_LDFLAGS="$LDFLAGS" wl=$lt_prog_compiler_wl eval LDFLAGS=\"\$LDFLAGS $export_dynamic_flag_spec\" save_LIBS="$LIBS" LIBS="$lt_cv_dlopen_libs $LIBS" { $as_echo "$as_me:${as_lineno-$LINENO}: checking whether a program can dlopen itself" >&5 $as_echo_n "checking whether a program can dlopen itself... " >&6; } if ${lt_cv_dlopen_self+:} false; then : $as_echo_n "(cached) " >&6 else if test "$cross_compiling" = yes; then : lt_cv_dlopen_self=cross else lt_dlunknown=0; lt_dlno_uscore=1; lt_dlneed_uscore=2 lt_status=$lt_dlunknown cat > conftest.$ac_ext <<_LT_EOF #line $LINENO "configure" #include "confdefs.h" #if HAVE_DLFCN_H #include #endif #include #ifdef RTLD_GLOBAL # define LT_DLGLOBAL RTLD_GLOBAL #else # ifdef DL_GLOBAL # define LT_DLGLOBAL DL_GLOBAL # else # define LT_DLGLOBAL 0 # endif #endif /* We may have to define LT_DLLAZY_OR_NOW in the command line if we find out it does not work in some platform. */ #ifndef LT_DLLAZY_OR_NOW # ifdef RTLD_LAZY # define LT_DLLAZY_OR_NOW RTLD_LAZY # else # ifdef DL_LAZY # define LT_DLLAZY_OR_NOW DL_LAZY # else # ifdef RTLD_NOW # define LT_DLLAZY_OR_NOW RTLD_NOW # else # ifdef DL_NOW # define LT_DLLAZY_OR_NOW DL_NOW # else # define LT_DLLAZY_OR_NOW 0 # endif # endif # endif # endif #endif /* When -fvisbility=hidden is used, assume the code has been annotated correspondingly for the symbols needed. */ #if defined(__GNUC__) && (((__GNUC__ == 3) && (__GNUC_MINOR__ >= 3)) || (__GNUC__ > 3)) int fnord () __attribute__((visibility("default"))); #endif int fnord () { return 42; } int main () { void *self = dlopen (0, LT_DLGLOBAL|LT_DLLAZY_OR_NOW); int status = $lt_dlunknown; if (self) { if (dlsym (self,"fnord")) status = $lt_dlno_uscore; else { if (dlsym( self,"_fnord")) status = $lt_dlneed_uscore; else puts (dlerror ()); } /* dlclose (self); */ } else puts (dlerror ()); return status; } _LT_EOF if { { eval echo "\"\$as_me\":${as_lineno-$LINENO}: \"$ac_link\""; } >&5 (eval $ac_link) 2>&5 ac_status=$? $as_echo "$as_me:${as_lineno-$LINENO}: \$? = $ac_status" >&5 test $ac_status = 0; } && test -s conftest${ac_exeext} 2>/dev/null; then (./conftest; exit; ) >&5 2>/dev/null lt_status=$? case x$lt_status in x$lt_dlno_uscore) lt_cv_dlopen_self=yes ;; x$lt_dlneed_uscore) lt_cv_dlopen_self=yes ;; x$lt_dlunknown|x*) lt_cv_dlopen_self=no ;; esac else : # compilation failed lt_cv_dlopen_self=no fi fi rm -fr conftest* fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $lt_cv_dlopen_self" >&5 $as_echo "$lt_cv_dlopen_self" >&6; } if test "x$lt_cv_dlopen_self" = xyes; then wl=$lt_prog_compiler_wl eval LDFLAGS=\"\$LDFLAGS $lt_prog_compiler_static\" { $as_echo "$as_me:${as_lineno-$LINENO}: checking whether a statically linked program can dlopen itself" >&5 $as_echo_n "checking whether a statically linked program can dlopen itself... " >&6; } if ${lt_cv_dlopen_self_static+:} false; then : $as_echo_n "(cached) " >&6 else if test "$cross_compiling" = yes; then : lt_cv_dlopen_self_static=cross else lt_dlunknown=0; lt_dlno_uscore=1; lt_dlneed_uscore=2 lt_status=$lt_dlunknown cat > conftest.$ac_ext <<_LT_EOF #line $LINENO "configure" #include "confdefs.h" #if HAVE_DLFCN_H #include #endif #include #ifdef RTLD_GLOBAL # define LT_DLGLOBAL RTLD_GLOBAL #else # ifdef DL_GLOBAL # define LT_DLGLOBAL DL_GLOBAL # else # define LT_DLGLOBAL 0 # endif #endif /* We may have to define LT_DLLAZY_OR_NOW in the command line if we find out it does not work in some platform. */ #ifndef LT_DLLAZY_OR_NOW # ifdef RTLD_LAZY # define LT_DLLAZY_OR_NOW RTLD_LAZY # else # ifdef DL_LAZY # define LT_DLLAZY_OR_NOW DL_LAZY # else # ifdef RTLD_NOW # define LT_DLLAZY_OR_NOW RTLD_NOW # else # ifdef DL_NOW # define LT_DLLAZY_OR_NOW DL_NOW # else # define LT_DLLAZY_OR_NOW 0 # endif # endif # endif # endif #endif /* When -fvisbility=hidden is used, assume the code has been annotated correspondingly for the symbols needed. */ #if defined(__GNUC__) && (((__GNUC__ == 3) && (__GNUC_MINOR__ >= 3)) || (__GNUC__ > 3)) int fnord () __attribute__((visibility("default"))); #endif int fnord () { return 42; } int main () { void *self = dlopen (0, LT_DLGLOBAL|LT_DLLAZY_OR_NOW); int status = $lt_dlunknown; if (self) { if (dlsym (self,"fnord")) status = $lt_dlno_uscore; else { if (dlsym( self,"_fnord")) status = $lt_dlneed_uscore; else puts (dlerror ()); } /* dlclose (self); */ } else puts (dlerror ()); return status; } _LT_EOF if { { eval echo "\"\$as_me\":${as_lineno-$LINENO}: \"$ac_link\""; } >&5 (eval $ac_link) 2>&5 ac_status=$? $as_echo "$as_me:${as_lineno-$LINENO}: \$? = $ac_status" >&5 test $ac_status = 0; } && test -s conftest${ac_exeext} 2>/dev/null; then (./conftest; exit; ) >&5 2>/dev/null lt_status=$? case x$lt_status in x$lt_dlno_uscore) lt_cv_dlopen_self_static=yes ;; x$lt_dlneed_uscore) lt_cv_dlopen_self_static=yes ;; x$lt_dlunknown|x*) lt_cv_dlopen_self_static=no ;; esac else : # compilation failed lt_cv_dlopen_self_static=no fi fi rm -fr conftest* fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $lt_cv_dlopen_self_static" >&5 $as_echo "$lt_cv_dlopen_self_static" >&6; } fi CPPFLAGS="$save_CPPFLAGS" LDFLAGS="$save_LDFLAGS" LIBS="$save_LIBS" ;; esac case $lt_cv_dlopen_self in yes|no) enable_dlopen_self=$lt_cv_dlopen_self ;; *) enable_dlopen_self=unknown ;; esac case $lt_cv_dlopen_self_static in yes|no) enable_dlopen_self_static=$lt_cv_dlopen_self_static ;; *) enable_dlopen_self_static=unknown ;; esac fi striplib= old_striplib= { $as_echo "$as_me:${as_lineno-$LINENO}: checking whether stripping libraries is possible" >&5 $as_echo_n "checking whether stripping libraries is possible... " >&6; } if test -n "$STRIP" && $STRIP -V 2>&1 | $GREP "GNU strip" >/dev/null; then test -z "$old_striplib" && old_striplib="$STRIP --strip-debug" test -z "$striplib" && striplib="$STRIP --strip-unneeded" { $as_echo "$as_me:${as_lineno-$LINENO}: result: yes" >&5 $as_echo "yes" >&6; } else # FIXME - insert some real tests, host_os isn't really good enough case $host_os in darwin*) if test -n "$STRIP" ; then striplib="$STRIP -x" old_striplib="$STRIP -S" { $as_echo "$as_me:${as_lineno-$LINENO}: result: yes" >&5 $as_echo "yes" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi ;; *) { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } ;; esac fi # Report which library types will actually be built { $as_echo "$as_me:${as_lineno-$LINENO}: checking if libtool supports shared libraries" >&5 $as_echo_n "checking if libtool supports shared libraries... " >&6; } { $as_echo "$as_me:${as_lineno-$LINENO}: result: $can_build_shared" >&5 $as_echo "$can_build_shared" >&6; } { $as_echo "$as_me:${as_lineno-$LINENO}: checking whether to build shared libraries" >&5 $as_echo_n "checking whether to build shared libraries... " >&6; } test "$can_build_shared" = "no" && enable_shared=no # On AIX, shared libraries and static libraries use the same namespace, and # are all built from PIC. case $host_os in aix3*) test "$enable_shared" = yes && enable_static=no if test -n "$RANLIB"; then archive_cmds="$archive_cmds~\$RANLIB \$lib" postinstall_cmds='$RANLIB $lib' fi ;; aix[4-9]*) if test "$host_cpu" != ia64 && test "$aix_use_runtimelinking" = no ; then test "$enable_shared" = yes && enable_static=no fi ;; esac { $as_echo "$as_me:${as_lineno-$LINENO}: result: $enable_shared" >&5 $as_echo "$enable_shared" >&6; } { $as_echo "$as_me:${as_lineno-$LINENO}: checking whether to build static libraries" >&5 $as_echo_n "checking whether to build static libraries... " >&6; } # Make sure either enable_shared or enable_static is yes. test "$enable_shared" = yes || enable_static=yes { $as_echo "$as_me:${as_lineno-$LINENO}: result: $enable_static" >&5 $as_echo "$enable_static" >&6; } fi ac_ext=c ac_cpp='$CPP $CPPFLAGS' ac_compile='$CC -c $CFLAGS $CPPFLAGS conftest.$ac_ext >&5' ac_link='$CC -o conftest$ac_exeext $CFLAGS $CPPFLAGS $LDFLAGS conftest.$ac_ext $LIBS >&5' ac_compiler_gnu=$ac_cv_c_compiler_gnu CC="$lt_save_CC" ac_config_commands="$ac_config_commands libtool" # Only expand once: { $as_echo "$as_me:${as_lineno-$LINENO}: checking for a sed that does not truncate output" >&5 $as_echo_n "checking for a sed that does not truncate output... " >&6; } if ${ac_cv_path_SED+:} false; then : $as_echo_n "(cached) " >&6 else ac_script=s/aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa/bbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbb/ for ac_i in 1 2 3 4 5 6 7; do ac_script="$ac_script$as_nl$ac_script" done echo "$ac_script" 2>/dev/null | sed 99q >conftest.sed { ac_script=; unset ac_script;} if test -z "$SED"; then ac_path_SED_found=false # Loop through the user's path and test for each of PROGNAME-LIST as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_prog in sed gsed; do for ac_exec_ext in '' $ac_executable_extensions; do ac_path_SED="$as_dir/$ac_prog$ac_exec_ext" as_fn_executable_p "$ac_path_SED" || continue # Check for GNU ac_path_SED and select it if it is found. # Check for GNU $ac_path_SED case `"$ac_path_SED" --version 2>&1` in *GNU*) ac_cv_path_SED="$ac_path_SED" ac_path_SED_found=:;; *) ac_count=0 $as_echo_n 0123456789 >"conftest.in" while : do cat "conftest.in" "conftest.in" >"conftest.tmp" mv "conftest.tmp" "conftest.in" cp "conftest.in" "conftest.nl" $as_echo '' >> "conftest.nl" "$ac_path_SED" -f conftest.sed < "conftest.nl" >"conftest.out" 2>/dev/null || break diff "conftest.out" "conftest.nl" >/dev/null 2>&1 || break as_fn_arith $ac_count + 1 && ac_count=$as_val if test $ac_count -gt ${ac_path_SED_max-0}; then # Best one so far, save it but keep looking for a better one ac_cv_path_SED="$ac_path_SED" ac_path_SED_max=$ac_count fi # 10*(2^10) chars as input seems more than enough test $ac_count -gt 10 && break done rm -f conftest.in conftest.tmp conftest.nl conftest.out;; esac $ac_path_SED_found && break 3 done done done IFS=$as_save_IFS if test -z "$ac_cv_path_SED"; then as_fn_error $? "no acceptable sed could be found in \$PATH" "$LINENO" 5 fi else ac_cv_path_SED=$SED fi fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_cv_path_SED" >&5 $as_echo "$ac_cv_path_SED" >&6; } SED="$ac_cv_path_SED" rm -f conftest.sed # ---------------------------------------------------------------------- # If `configure' is invoked (in)directly via `make', ensure that it # encounters no `make' conflicts. Ignore error if shell does not have # unset, but at least set these to empty values. # ---------------------------------------------------------------------- MFLAGS= MAKEFLAGS= MAKELEVEL= unset MFLAGS MAKEFLAGS MAKELEVEL 2>/dev/null # ---------------------------------------------------------------------- # Set up and process configure options # ---------------------------------------------------------------------- if test x"${enable_subdir-no}" != xno; then SUBDIR_SNPRINTFV_TRUE= SUBDIR_SNPRINTFV_FALSE='#' else SUBDIR_SNPRINTFV_TRUE='#' SUBDIR_SNPRINTFV_FALSE= fi if test x"${enable_subdir-no}" = xno; then enable_snprintfv_install=yes enable_snprintfv_convenience=no else if test x"$enable_snprintfv_convenience$enable_snprintfv_install" = x; then { $as_echo "$as_me:${as_lineno-$LINENO}: WARNING: *** The top-level configure should select either" >&5 $as_echo "$as_me: WARNING: *** The top-level configure should select either" >&2;} { $as_echo "$as_me:${as_lineno-$LINENO}: WARNING: *** AC_SNPRINTFV_INSTALL or AC_SNPRINTFV_CONVENIENCE," >&5 $as_echo "$as_me: WARNING: *** AC_SNPRINTFV_INSTALL or AC_SNPRINTFV_CONVENIENCE," >&2;} enable_snprintfv_convenience=yes enable_snprintfv_install=no fi fi if test x"${enable_snprintfv_install-no}" != xno; then INSTALL_SNPRINTFV_TRUE= INSTALL_SNPRINTFV_FALSE='#' else INSTALL_SNPRINTFV_TRUE='#' INSTALL_SNPRINTFV_FALSE= fi if test x"${enable_snprintfv_install-no}" != xno; then installed_libsnprintfv=libsnprintfv.la fi if test x"${enable_snprintfv_convenience-no}" != xno; then CONVENIENCE_SNPRINTFV_TRUE= CONVENIENCE_SNPRINTFV_FALSE='#' else CONVENIENCE_SNPRINTFV_TRUE='#' CONVENIENCE_SNPRINTFV_FALSE= fi if test x"${enable_snprintfv_convenience-no}" != xno; then convenience_libsnprintfv=libsnprintfvc.la fi # Check whether --enable-convenience-float-printing was given. if test "${enable_convenience_float_printing+set}" = set; then : enableval=$enable_convenience_float_printing; else enable_convenience_float_printing=yes fi if test x"$enable_convenience_float_printing" = yes; then enable_convenience_float_printing=$enable_snprintfv_convenience fi { $as_echo "$as_me:${as_lineno-$LINENO}: checking whether the convenience libsnprintfv needs printing floats" >&5 $as_echo_n "checking whether the convenience libsnprintfv needs printing floats... " >&6; } { $as_echo "$as_me:${as_lineno-$LINENO}: result: $enable_convenience_float_printing" >&5 $as_echo "$enable_convenience_float_printing" >&6; } if test x$enable_convenience_float_printing = xyes; then LIBSNPRINTFVC_PRINT_FLOATS= else LIBSNPRINTFVC_PRINT_FLOATS='-DNO_FLOAT_PRINTING' fi { $as_echo "$as_me:${as_lineno-$LINENO}: checking if malloc debugging is wanted" >&5 $as_echo_n "checking if malloc debugging is wanted... " >&6; } # Check whether --with-dmalloc was given. if test "${with_dmalloc+set}" = set; then : withval=$with_dmalloc; if test "$withval" = yes; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: yes" >&5 $as_echo "yes" >&6; } $as_echo "#define WITH_DMALLOC 1" >>confdefs.h LIBS="$LIBS -ldmalloc" LDFLAGS="$LDFLAGS -g" else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi # ---------------------------------------------------------------------- # check for various programs used during the build. # ---------------------------------------------------------------------- ac_ext=c ac_cpp='$CPP $CPPFLAGS' ac_compile='$CC -c $CFLAGS $CPPFLAGS conftest.$ac_ext >&5' ac_link='$CC -o conftest$ac_exeext $CFLAGS $CPPFLAGS $LDFLAGS conftest.$ac_ext $LIBS >&5' ac_compiler_gnu=$ac_cv_c_compiler_gnu if test -n "$ac_tool_prefix"; then # Extract the first word of "${ac_tool_prefix}gcc", so it can be a program name with args. set dummy ${ac_tool_prefix}gcc; ac_word=$2 { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $ac_word" >&5 $as_echo_n "checking for $ac_word... " >&6; } if ${ac_cv_prog_CC+:} false; then : $as_echo_n "(cached) " >&6 else if test -n "$CC"; then ac_cv_prog_CC="$CC" # Let the user override the test. else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_exec_ext in '' $ac_executable_extensions; do if as_fn_executable_p "$as_dir/$ac_word$ac_exec_ext"; then ac_cv_prog_CC="${ac_tool_prefix}gcc" $as_echo "$as_me:${as_lineno-$LINENO}: found $as_dir/$ac_word$ac_exec_ext" >&5 break 2 fi done done IFS=$as_save_IFS fi fi CC=$ac_cv_prog_CC if test -n "$CC"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $CC" >&5 $as_echo "$CC" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi fi if test -z "$ac_cv_prog_CC"; then ac_ct_CC=$CC # Extract the first word of "gcc", so it can be a program name with args. set dummy gcc; ac_word=$2 { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $ac_word" >&5 $as_echo_n "checking for $ac_word... " >&6; } if ${ac_cv_prog_ac_ct_CC+:} false; then : $as_echo_n "(cached) " >&6 else if test -n "$ac_ct_CC"; then ac_cv_prog_ac_ct_CC="$ac_ct_CC" # Let the user override the test. else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_exec_ext in '' $ac_executable_extensions; do if as_fn_executable_p "$as_dir/$ac_word$ac_exec_ext"; then ac_cv_prog_ac_ct_CC="gcc" $as_echo "$as_me:${as_lineno-$LINENO}: found $as_dir/$ac_word$ac_exec_ext" >&5 break 2 fi done done IFS=$as_save_IFS fi fi ac_ct_CC=$ac_cv_prog_ac_ct_CC if test -n "$ac_ct_CC"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_ct_CC" >&5 $as_echo "$ac_ct_CC" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi if test "x$ac_ct_CC" = x; then CC="" else case $cross_compiling:$ac_tool_warned in yes:) { $as_echo "$as_me:${as_lineno-$LINENO}: WARNING: using cross tools not prefixed with host triplet" >&5 $as_echo "$as_me: WARNING: using cross tools not prefixed with host triplet" >&2;} ac_tool_warned=yes ;; esac CC=$ac_ct_CC fi else CC="$ac_cv_prog_CC" fi if test -z "$CC"; then if test -n "$ac_tool_prefix"; then # Extract the first word of "${ac_tool_prefix}cc", so it can be a program name with args. set dummy ${ac_tool_prefix}cc; ac_word=$2 { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $ac_word" >&5 $as_echo_n "checking for $ac_word... " >&6; } if ${ac_cv_prog_CC+:} false; then : $as_echo_n "(cached) " >&6 else if test -n "$CC"; then ac_cv_prog_CC="$CC" # Let the user override the test. else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_exec_ext in '' $ac_executable_extensions; do if as_fn_executable_p "$as_dir/$ac_word$ac_exec_ext"; then ac_cv_prog_CC="${ac_tool_prefix}cc" $as_echo "$as_me:${as_lineno-$LINENO}: found $as_dir/$ac_word$ac_exec_ext" >&5 break 2 fi done done IFS=$as_save_IFS fi fi CC=$ac_cv_prog_CC if test -n "$CC"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $CC" >&5 $as_echo "$CC" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi fi fi if test -z "$CC"; then # Extract the first word of "cc", so it can be a program name with args. set dummy cc; ac_word=$2 { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $ac_word" >&5 $as_echo_n "checking for $ac_word... " >&6; } if ${ac_cv_prog_CC+:} false; then : $as_echo_n "(cached) " >&6 else if test -n "$CC"; then ac_cv_prog_CC="$CC" # Let the user override the test. else ac_prog_rejected=no as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_exec_ext in '' $ac_executable_extensions; do if as_fn_executable_p "$as_dir/$ac_word$ac_exec_ext"; then if test "$as_dir/$ac_word$ac_exec_ext" = "/usr/ucb/cc"; then ac_prog_rejected=yes continue fi ac_cv_prog_CC="cc" $as_echo "$as_me:${as_lineno-$LINENO}: found $as_dir/$ac_word$ac_exec_ext" >&5 break 2 fi done done IFS=$as_save_IFS if test $ac_prog_rejected = yes; then # We found a bogon in the path, so make sure we never use it. set dummy $ac_cv_prog_CC shift if test $# != 0; then # We chose a different compiler from the bogus one. # However, it has the same basename, so the bogon will be chosen # first if we set CC to just the basename; use the full file name. shift ac_cv_prog_CC="$as_dir/$ac_word${1+' '}$@" fi fi fi fi CC=$ac_cv_prog_CC if test -n "$CC"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $CC" >&5 $as_echo "$CC" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi fi if test -z "$CC"; then if test -n "$ac_tool_prefix"; then for ac_prog in cl.exe do # Extract the first word of "$ac_tool_prefix$ac_prog", so it can be a program name with args. set dummy $ac_tool_prefix$ac_prog; ac_word=$2 { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $ac_word" >&5 $as_echo_n "checking for $ac_word... " >&6; } if ${ac_cv_prog_CC+:} false; then : $as_echo_n "(cached) " >&6 else if test -n "$CC"; then ac_cv_prog_CC="$CC" # Let the user override the test. else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_exec_ext in '' $ac_executable_extensions; do if as_fn_executable_p "$as_dir/$ac_word$ac_exec_ext"; then ac_cv_prog_CC="$ac_tool_prefix$ac_prog" $as_echo "$as_me:${as_lineno-$LINENO}: found $as_dir/$ac_word$ac_exec_ext" >&5 break 2 fi done done IFS=$as_save_IFS fi fi CC=$ac_cv_prog_CC if test -n "$CC"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $CC" >&5 $as_echo "$CC" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi test -n "$CC" && break done fi if test -z "$CC"; then ac_ct_CC=$CC for ac_prog in cl.exe do # Extract the first word of "$ac_prog", so it can be a program name with args. set dummy $ac_prog; ac_word=$2 { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $ac_word" >&5 $as_echo_n "checking for $ac_word... " >&6; } if ${ac_cv_prog_ac_ct_CC+:} false; then : $as_echo_n "(cached) " >&6 else if test -n "$ac_ct_CC"; then ac_cv_prog_ac_ct_CC="$ac_ct_CC" # Let the user override the test. else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_exec_ext in '' $ac_executable_extensions; do if as_fn_executable_p "$as_dir/$ac_word$ac_exec_ext"; then ac_cv_prog_ac_ct_CC="$ac_prog" $as_echo "$as_me:${as_lineno-$LINENO}: found $as_dir/$ac_word$ac_exec_ext" >&5 break 2 fi done done IFS=$as_save_IFS fi fi ac_ct_CC=$ac_cv_prog_ac_ct_CC if test -n "$ac_ct_CC"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_ct_CC" >&5 $as_echo "$ac_ct_CC" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi test -n "$ac_ct_CC" && break done if test "x$ac_ct_CC" = x; then CC="" else case $cross_compiling:$ac_tool_warned in yes:) { $as_echo "$as_me:${as_lineno-$LINENO}: WARNING: using cross tools not prefixed with host triplet" >&5 $as_echo "$as_me: WARNING: using cross tools not prefixed with host triplet" >&2;} ac_tool_warned=yes ;; esac CC=$ac_ct_CC fi fi fi test -z "$CC" && { { $as_echo "$as_me:${as_lineno-$LINENO}: error: in \`$ac_pwd':" >&5 $as_echo "$as_me: error: in \`$ac_pwd':" >&2;} as_fn_error $? "no acceptable C compiler found in \$PATH See \`config.log' for more details" "$LINENO" 5; } # Provide some information about the compiler. $as_echo "$as_me:${as_lineno-$LINENO}: checking for C compiler version" >&5 set X $ac_compile ac_compiler=$2 for ac_option in --version -v -V -qversion; do { { ac_try="$ac_compiler $ac_option >&5" case "(($ac_try" in *\"* | *\`* | *\\*) ac_try_echo=\$ac_try;; *) ac_try_echo=$ac_try;; esac eval ac_try_echo="\"\$as_me:${as_lineno-$LINENO}: $ac_try_echo\"" $as_echo "$ac_try_echo"; } >&5 (eval "$ac_compiler $ac_option >&5") 2>conftest.err ac_status=$? if test -s conftest.err; then sed '10a\ ... rest of stderr output deleted ... 10q' conftest.err >conftest.er1 cat conftest.er1 >&5 fi rm -f conftest.er1 conftest.err $as_echo "$as_me:${as_lineno-$LINENO}: \$? = $ac_status" >&5 test $ac_status = 0; } done { $as_echo "$as_me:${as_lineno-$LINENO}: checking whether we are using the GNU C compiler" >&5 $as_echo_n "checking whether we are using the GNU C compiler... " >&6; } if ${ac_cv_c_compiler_gnu+:} false; then : $as_echo_n "(cached) " >&6 else cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ int main () { #ifndef __GNUC__ choke me #endif ; return 0; } _ACEOF if ac_fn_c_try_compile "$LINENO"; then : ac_compiler_gnu=yes else ac_compiler_gnu=no fi rm -f core conftest.err conftest.$ac_objext conftest.$ac_ext ac_cv_c_compiler_gnu=$ac_compiler_gnu fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_cv_c_compiler_gnu" >&5 $as_echo "$ac_cv_c_compiler_gnu" >&6; } if test $ac_compiler_gnu = yes; then GCC=yes else GCC= fi ac_test_CFLAGS=${CFLAGS+set} ac_save_CFLAGS=$CFLAGS { $as_echo "$as_me:${as_lineno-$LINENO}: checking whether $CC accepts -g" >&5 $as_echo_n "checking whether $CC accepts -g... " >&6; } if ${ac_cv_prog_cc_g+:} false; then : $as_echo_n "(cached) " >&6 else ac_save_c_werror_flag=$ac_c_werror_flag ac_c_werror_flag=yes ac_cv_prog_cc_g=no CFLAGS="-g" cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ int main () { ; return 0; } _ACEOF if ac_fn_c_try_compile "$LINENO"; then : ac_cv_prog_cc_g=yes else CFLAGS="" cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ int main () { ; return 0; } _ACEOF if ac_fn_c_try_compile "$LINENO"; then : else ac_c_werror_flag=$ac_save_c_werror_flag CFLAGS="-g" cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ int main () { ; return 0; } _ACEOF if ac_fn_c_try_compile "$LINENO"; then : ac_cv_prog_cc_g=yes fi rm -f core conftest.err conftest.$ac_objext conftest.$ac_ext fi rm -f core conftest.err conftest.$ac_objext conftest.$ac_ext fi rm -f core conftest.err conftest.$ac_objext conftest.$ac_ext ac_c_werror_flag=$ac_save_c_werror_flag fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_cv_prog_cc_g" >&5 $as_echo "$ac_cv_prog_cc_g" >&6; } if test "$ac_test_CFLAGS" = set; then CFLAGS=$ac_save_CFLAGS elif test $ac_cv_prog_cc_g = yes; then if test "$GCC" = yes; then CFLAGS="-g -O2" else CFLAGS="-g" fi else if test "$GCC" = yes; then CFLAGS="-O2" else CFLAGS= fi fi { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $CC option to accept ISO C89" >&5 $as_echo_n "checking for $CC option to accept ISO C89... " >&6; } if ${ac_cv_prog_cc_c89+:} false; then : $as_echo_n "(cached) " >&6 else ac_cv_prog_cc_c89=no ac_save_CC=$CC cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ #include #include struct stat; /* Most of the following tests are stolen from RCS 5.7's src/conf.sh. */ struct buf { int x; }; FILE * (*rcsopen) (struct buf *, struct stat *, int); static char *e (p, i) char **p; int i; { return p[i]; } static char *f (char * (*g) (char **, int), char **p, ...) { char *s; va_list v; va_start (v,p); s = g (p, va_arg (v,int)); va_end (v); return s; } /* OSF 4.0 Compaq cc is some sort of almost-ANSI by default. It has function prototypes and stuff, but not '\xHH' hex character constants. These don't provoke an error unfortunately, instead are silently treated as 'x'. The following induces an error, until -std is added to get proper ANSI mode. Curiously '\x00'!='x' always comes out true, for an array size at least. It's necessary to write '\x00'==0 to get something that's true only with -std. */ int osf4_cc_array ['\x00' == 0 ? 1 : -1]; /* IBM C 6 for AIX is almost-ANSI by default, but it replaces macro parameters inside strings and character constants. */ #define FOO(x) 'x' int xlc6_cc_array[FOO(a) == 'x' ? 1 : -1]; int test (int i, double x); struct s1 {int (*f) (int a);}; struct s2 {int (*f) (double a);}; int pairnames (int, char **, FILE *(*)(struct buf *, struct stat *, int), int, int); int argc; char **argv; int main () { return f (e, argv, 0) != argv[0] || f (e, argv, 1) != argv[1]; ; return 0; } _ACEOF for ac_arg in '' -qlanglvl=extc89 -qlanglvl=ansi -std \ -Ae "-Aa -D_HPUX_SOURCE" "-Xc -D__EXTENSIONS__" do CC="$ac_save_CC $ac_arg" if ac_fn_c_try_compile "$LINENO"; then : ac_cv_prog_cc_c89=$ac_arg fi rm -f core conftest.err conftest.$ac_objext test "x$ac_cv_prog_cc_c89" != "xno" && break done rm -f conftest.$ac_ext CC=$ac_save_CC fi # AC_CACHE_VAL case "x$ac_cv_prog_cc_c89" in x) { $as_echo "$as_me:${as_lineno-$LINENO}: result: none needed" >&5 $as_echo "none needed" >&6; } ;; xno) { $as_echo "$as_me:${as_lineno-$LINENO}: result: unsupported" >&5 $as_echo "unsupported" >&6; } ;; *) CC="$CC $ac_cv_prog_cc_c89" { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_cv_prog_cc_c89" >&5 $as_echo "$ac_cv_prog_cc_c89" >&6; } ;; esac if test "x$ac_cv_prog_cc_c89" != xno; then : fi ac_ext=c ac_cpp='$CPP $CPPFLAGS' ac_compile='$CC -c $CFLAGS $CPPFLAGS conftest.$ac_ext >&5' ac_link='$CC -o conftest$ac_exeext $CFLAGS $CPPFLAGS $LDFLAGS conftest.$ac_ext $LIBS >&5' ac_compiler_gnu=$ac_cv_c_compiler_gnu depcc="$CC" am_compiler_list= { $as_echo "$as_me:${as_lineno-$LINENO}: checking dependency style of $depcc" >&5 $as_echo_n "checking dependency style of $depcc... " >&6; } if ${am_cv_CC_dependencies_compiler_type+:} false; then : $as_echo_n "(cached) " >&6 else if test -z "$AMDEP_TRUE" && test -f "$am_depcomp"; then # We make a subdir and do the tests there. Otherwise we can end up # making bogus files that we don't know about and never remove. For # instance it was reported that on HP-UX the gcc test will end up # making a dummy file named `D' -- because `-MD' means `put the output # in D'. rm -rf conftest.dir mkdir conftest.dir # Copy depcomp to subdir because otherwise we won't find it if we're # using a relative directory. cp "$am_depcomp" conftest.dir cd conftest.dir # We will build objects and dependencies in a subdirectory because # it helps to detect inapplicable dependency modes. For instance # both Tru64's cc and ICC support -MD to output dependencies as a # side effect of compilation, but ICC will put the dependencies in # the current directory while Tru64 will put them in the object # directory. mkdir sub am_cv_CC_dependencies_compiler_type=none if test "$am_compiler_list" = ""; then am_compiler_list=`sed -n 's/^#*\([a-zA-Z0-9]*\))$/\1/p' < ./depcomp` fi am__universal=false case " $depcc " in #( *\ -arch\ *\ -arch\ *) am__universal=true ;; esac for depmode in $am_compiler_list; do # Setup a source with many dependencies, because some compilers # like to wrap large dependency lists on column 80 (with \), and # we should not choose a depcomp mode which is confused by this. # # We need to recreate these files for each test, as the compiler may # overwrite some of them when testing with obscure command lines. # This happens at least with the AIX C compiler. : > sub/conftest.c for i in 1 2 3 4 5 6; do echo '#include "conftst'$i'.h"' >> sub/conftest.c # Using `: > sub/conftst$i.h' creates only sub/conftst1.h with # Solaris 8's {/usr,}/bin/sh. touch sub/conftst$i.h done echo "${am__include} ${am__quote}sub/conftest.Po${am__quote}" > confmf # We check with `-c' and `-o' for the sake of the "dashmstdout" # mode. It turns out that the SunPro C++ compiler does not properly # handle `-M -o', and we need to detect this. Also, some Intel # versions had trouble with output in subdirs am__obj=sub/conftest.${OBJEXT-o} am__minus_obj="-o $am__obj" case $depmode in gcc) # This depmode causes a compiler race in universal mode. test "$am__universal" = false || continue ;; nosideeffect) # after this tag, mechanisms are not by side-effect, so they'll # only be used when explicitly requested if test "x$enable_dependency_tracking" = xyes; then continue else break fi ;; msvc7 | msvc7msys | msvisualcpp | msvcmsys) # This compiler won't grok `-c -o', but also, the minuso test has # not run yet. These depmodes are late enough in the game, and # so weak that their functioning should not be impacted. am__obj=conftest.${OBJEXT-o} am__minus_obj= ;; none) break ;; esac if depmode=$depmode \ source=sub/conftest.c object=$am__obj \ depfile=sub/conftest.Po tmpdepfile=sub/conftest.TPo \ $SHELL ./depcomp $depcc -c $am__minus_obj sub/conftest.c \ >/dev/null 2>conftest.err && grep sub/conftst1.h sub/conftest.Po > /dev/null 2>&1 && grep sub/conftst6.h sub/conftest.Po > /dev/null 2>&1 && grep $am__obj sub/conftest.Po > /dev/null 2>&1 && ${MAKE-make} -s -f confmf > /dev/null 2>&1; then # icc doesn't choke on unknown options, it will just issue warnings # or remarks (even with -Werror). So we grep stderr for any message # that says an option was ignored or not supported. # When given -MP, icc 7.0 and 7.1 complain thusly: # icc: Command line warning: ignoring option '-M'; no argument required # The diagnosis changed in icc 8.0: # icc: Command line remark: option '-MP' not supported if (grep 'ignoring option' conftest.err || grep 'not supported' conftest.err) >/dev/null 2>&1; then :; else am_cv_CC_dependencies_compiler_type=$depmode break fi fi done cd .. rm -rf conftest.dir else am_cv_CC_dependencies_compiler_type=none fi fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $am_cv_CC_dependencies_compiler_type" >&5 $as_echo "$am_cv_CC_dependencies_compiler_type" >&6; } CCDEPMODE=depmode=$am_cv_CC_dependencies_compiler_type if test "x$enable_dependency_tracking" != xno \ && test "$am_cv_CC_dependencies_compiler_type" = gcc3; then am__fastdepCC_TRUE= am__fastdepCC_FALSE='#' else am__fastdepCC_TRUE='#' am__fastdepCC_FALSE= fi { $as_echo "$as_me:${as_lineno-$LINENO}: checking for an ANSI C-conforming const" >&5 $as_echo_n "checking for an ANSI C-conforming const... " >&6; } if ${ac_cv_c_const+:} false; then : $as_echo_n "(cached) " >&6 else cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ int main () { #ifndef __cplusplus /* Ultrix mips cc rejects this sort of thing. */ typedef int charset[2]; const charset cs = { 0, 0 }; /* SunOS 4.1.1 cc rejects this. */ char const *const *pcpcc; char **ppc; /* NEC SVR4.0.2 mips cc rejects this. */ struct point {int x, y;}; static struct point const zero = {0,0}; /* AIX XL C 1.02.0.0 rejects this. It does not let you subtract one const X* pointer from another in an arm of an if-expression whose if-part is not a constant expression */ const char *g = "string"; pcpcc = &g + (g ? g-g : 0); /* HPUX 7.0 cc rejects these. */ ++pcpcc; ppc = (char**) pcpcc; pcpcc = (char const *const *) ppc; { /* SCO 3.2v4 cc rejects this sort of thing. */ char tx; char *t = &tx; char const *s = 0 ? (char *) 0 : (char const *) 0; *t++ = 0; if (s) return 0; } { /* Someone thinks the Sun supposedly-ANSI compiler will reject this. */ int x[] = {25, 17}; const int *foo = &x[0]; ++foo; } { /* Sun SC1.0 ANSI compiler rejects this -- but not the above. */ typedef const int *iptr; iptr p = 0; ++p; } { /* AIX XL C 1.02.0.0 rejects this sort of thing, saying "k.c", line 2.27: 1506-025 (S) Operand must be a modifiable lvalue. */ struct s { int j; const int *ap[3]; } bx; struct s *b = &bx; b->j = 5; } { /* ULTRIX-32 V3.1 (Rev 9) vcc rejects this */ const int foo = 10; if (!foo) return 0; } return !cs[0] && !zero.x; #endif ; return 0; } _ACEOF if ac_fn_c_try_compile "$LINENO"; then : ac_cv_c_const=yes else ac_cv_c_const=no fi rm -f core conftest.err conftest.$ac_objext conftest.$ac_ext fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_cv_c_const" >&5 $as_echo "$ac_cv_c_const" >&6; } if test $ac_cv_c_const = no; then $as_echo "#define const /**/" >>confdefs.h fi { $as_echo "$as_me:${as_lineno-$LINENO}: checking for inline" >&5 $as_echo_n "checking for inline... " >&6; } if ${ac_cv_c_inline+:} false; then : $as_echo_n "(cached) " >&6 else ac_cv_c_inline=no for ac_kw in inline __inline__ __inline; do cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ #ifndef __cplusplus typedef int foo_t; static $ac_kw foo_t static_foo () {return 0; } $ac_kw foo_t foo () {return 0; } #endif _ACEOF if ac_fn_c_try_compile "$LINENO"; then : ac_cv_c_inline=$ac_kw fi rm -f core conftest.err conftest.$ac_objext conftest.$ac_ext test "$ac_cv_c_inline" != no && break done fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_cv_c_inline" >&5 $as_echo "$ac_cv_c_inline" >&6; } case $ac_cv_c_inline in inline | yes) ;; *) case $ac_cv_c_inline in no) ac_val=;; *) ac_val=$ac_cv_c_inline;; esac cat >>confdefs.h <<_ACEOF #ifndef __cplusplus #define inline $ac_val #endif _ACEOF ;; esac for ac_prog in gawk mawk nawk awk do # Extract the first word of "$ac_prog", so it can be a program name with args. set dummy $ac_prog; ac_word=$2 { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $ac_word" >&5 $as_echo_n "checking for $ac_word... " >&6; } if ${ac_cv_prog_AWK+:} false; then : $as_echo_n "(cached) " >&6 else if test -n "$AWK"; then ac_cv_prog_AWK="$AWK" # Let the user override the test. else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_exec_ext in '' $ac_executable_extensions; do if as_fn_executable_p "$as_dir/$ac_word$ac_exec_ext"; then ac_cv_prog_AWK="$ac_prog" $as_echo "$as_me:${as_lineno-$LINENO}: found $as_dir/$ac_word$ac_exec_ext" >&5 break 2 fi done done IFS=$as_save_IFS fi fi AWK=$ac_cv_prog_AWK if test -n "$AWK"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $AWK" >&5 $as_echo "$AWK" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi test -n "$AWK" && break done # ---------------------------------------------------------------------- # check for standard headers. # ---------------------------------------------------------------------- { $as_echo "$as_me:${as_lineno-$LINENO}: checking for ANSI C header files" >&5 $as_echo_n "checking for ANSI C header files... " >&6; } if ${ac_cv_header_stdc+:} false; then : $as_echo_n "(cached) " >&6 else cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ #include #include #include #include int main () { ; return 0; } _ACEOF if ac_fn_c_try_compile "$LINENO"; then : ac_cv_header_stdc=yes else ac_cv_header_stdc=no fi rm -f core conftest.err conftest.$ac_objext conftest.$ac_ext if test $ac_cv_header_stdc = yes; then # SunOS 4.x string.h does not declare mem*, contrary to ANSI. cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ #include _ACEOF if (eval "$ac_cpp conftest.$ac_ext") 2>&5 | $EGREP "memchr" >/dev/null 2>&1; then : else ac_cv_header_stdc=no fi rm -f conftest* fi if test $ac_cv_header_stdc = yes; then # ISC 2.0.2 stdlib.h does not declare free, contrary to ANSI. cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ #include _ACEOF if (eval "$ac_cpp conftest.$ac_ext") 2>&5 | $EGREP "free" >/dev/null 2>&1; then : else ac_cv_header_stdc=no fi rm -f conftest* fi if test $ac_cv_header_stdc = yes; then # /bin/cc in Irix-4.0.5 gets non-ANSI ctype macros unless using -ansi. if test "$cross_compiling" = yes; then : : else cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ #include #include #if ((' ' & 0x0FF) == 0x020) # define ISLOWER(c) ('a' <= (c) && (c) <= 'z') # define TOUPPER(c) (ISLOWER(c) ? 'A' + ((c) - 'a') : (c)) #else # define ISLOWER(c) \ (('a' <= (c) && (c) <= 'i') \ || ('j' <= (c) && (c) <= 'r') \ || ('s' <= (c) && (c) <= 'z')) # define TOUPPER(c) (ISLOWER(c) ? ((c) | 0x40) : (c)) #endif #define XOR(e, f) (((e) && !(f)) || (!(e) && (f))) int main () { int i; for (i = 0; i < 256; i++) if (XOR (islower (i), ISLOWER (i)) || toupper (i) != TOUPPER (i)) return 2; return 0; } _ACEOF if ac_fn_c_try_run "$LINENO"; then : else ac_cv_header_stdc=no fi rm -f core *.core core.conftest.* gmon.out bb.out conftest$ac_exeext \ conftest.$ac_objext conftest.beam conftest.$ac_ext fi fi fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_cv_header_stdc" >&5 $as_echo "$ac_cv_header_stdc" >&6; } if test $ac_cv_header_stdc = yes; then $as_echo "#define STDC_HEADERS 1" >>confdefs.h fi for ac_header in sys/types.h do : ac_fn_c_check_header_mongrel "$LINENO" "sys/types.h" "ac_cv_header_sys_types_h" "$ac_includes_default" if test "x$ac_cv_header_sys_types_h" = xyes; then : cat >>confdefs.h <<_ACEOF #define HAVE_SYS_TYPES_H 1 _ACEOF fi done { $as_echo "$as_me:${as_lineno-$LINENO}: checking for static inline" >&5 $as_echo_n "checking for static inline... " >&6; } if ${snv_cv_static_inline+:} false; then : $as_echo_n "(cached) " >&6 else cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ static inline foo(bar) int bar; { return bar; } int main () { return foo(0); ; return 0; } _ACEOF if ac_fn_c_try_compile "$LINENO"; then : snv_cv_static_inline=yes else snv_cv_static_inline=no fi rm -f core conftest.err conftest.$ac_objext conftest.$ac_ext fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $snv_cv_static_inline" >&5 $as_echo "$snv_cv_static_inline" >&6; } # If string.h is present define HAVE_STRING_H, otherwise if strings.h # is present define HAVE_STRINGS_H. for ac_header in string.h strings.h do : as_ac_Header=`$as_echo "ac_cv_header_$ac_header" | $as_tr_sh` ac_fn_c_check_header_mongrel "$LINENO" "$ac_header" "$as_ac_Header" "$ac_includes_default" if eval test \"x\$"$as_ac_Header"\" = x"yes"; then : cat >>confdefs.h <<_ACEOF #define `$as_echo "HAVE_$ac_header" | $as_tr_cpp` 1 _ACEOF break fi done for ac_func in flockfile fputc_unlocked do : as_ac_var=`$as_echo "ac_cv_func_$ac_func" | $as_tr_sh` ac_fn_c_check_func "$LINENO" "$ac_func" "$as_ac_var" if eval test \"x\$"$as_ac_var"\" = x"yes"; then : cat >>confdefs.h <<_ACEOF #define `$as_echo "HAVE_$ac_func" | $as_tr_cpp` 1 _ACEOF fi done # ---------------------------------------------------------------------- # Checks for typedefs # ---------------------------------------------------------------------- ac_fn_c_check_header_mongrel "$LINENO" "wchar.h" "ac_cv_header_wchar_h" "$ac_includes_default" if test "x$ac_cv_header_wchar_h" = xyes; then : fi ac_fn_c_check_type "$LINENO" "wchar_t" "ac_cv_type_wchar_t" "$ac_includes_default" if test "x$ac_cv_type_wchar_t" = xyes; then : fi ac_fn_c_check_type "$LINENO" "wint_t" "ac_cv_type_wint_t" "$ac_includes_default" if test "x$ac_cv_type_wint_t" = xyes; then : fi ac_fn_c_check_type "$LINENO" "intmax_t" "ac_cv_type_intmax_t" "$ac_includes_default" if test "x$ac_cv_type_intmax_t" = xyes; then : fi ac_fn_c_check_type "$LINENO" "size_t" "ac_cv_type_size_t" "$ac_includes_default" if test "x$ac_cv_type_size_t" = xyes; then : else cat >>confdefs.h <<_ACEOF #define size_t unsigned int _ACEOF fi # The cast to long int works around a bug in the HP C Compiler # version HP92453-01 B.11.11.23709.GP, which incorrectly rejects # declarations like `int a3[[(sizeof (unsigned char)) >= 0]];'. # This bug is HP SR number 8606223364. { $as_echo "$as_me:${as_lineno-$LINENO}: checking size of int" >&5 $as_echo_n "checking size of int... " >&6; } if ${ac_cv_sizeof_int+:} false; then : $as_echo_n "(cached) " >&6 else if ac_fn_c_compute_int "$LINENO" "(long int) (sizeof (int))" "ac_cv_sizeof_int" "$ac_includes_default"; then : else if test "$ac_cv_type_int" = yes; then { { $as_echo "$as_me:${as_lineno-$LINENO}: error: in \`$ac_pwd':" >&5 $as_echo "$as_me: error: in \`$ac_pwd':" >&2;} as_fn_error 77 "cannot compute sizeof (int) See \`config.log' for more details" "$LINENO" 5; } else ac_cv_sizeof_int=0 fi fi fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_cv_sizeof_int" >&5 $as_echo "$ac_cv_sizeof_int" >&6; } cat >>confdefs.h <<_ACEOF #define SIZEOF_INT $ac_cv_sizeof_int _ACEOF # The cast to long int works around a bug in the HP C Compiler # version HP92453-01 B.11.11.23709.GP, which incorrectly rejects # declarations like `int a3[[(sizeof (unsigned char)) >= 0]];'. # This bug is HP SR number 8606223364. { $as_echo "$as_me:${as_lineno-$LINENO}: checking size of wint_t" >&5 $as_echo_n "checking size of wint_t... " >&6; } if ${ac_cv_sizeof_wint_t+:} false; then : $as_echo_n "(cached) " >&6 else if ac_fn_c_compute_int "$LINENO" "(long int) (sizeof (wint_t))" "ac_cv_sizeof_wint_t" "$ac_includes_default"; then : else if test "$ac_cv_type_wint_t" = yes; then { { $as_echo "$as_me:${as_lineno-$LINENO}: error: in \`$ac_pwd':" >&5 $as_echo "$as_me: error: in \`$ac_pwd':" >&2;} as_fn_error 77 "cannot compute sizeof (wint_t) See \`config.log' for more details" "$LINENO" 5; } else ac_cv_sizeof_wint_t=0 fi fi fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_cv_sizeof_wint_t" >&5 $as_echo "$ac_cv_sizeof_wint_t" >&6; } cat >>confdefs.h <<_ACEOF #define SIZEOF_WINT_T $ac_cv_sizeof_wint_t _ACEOF # ---------------------------------------------------------------------- # Checks for floating-point features # ---------------------------------------------------------------------- { $as_echo "$as_me:${as_lineno-$LINENO}: checking for long double with more range or precision than double" >&5 $as_echo_n "checking for long double with more range or precision than double... " >&6; } if ${ac_cv_type_long_double_wider+:} false; then : $as_echo_n "(cached) " >&6 else cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ #include long double const a[] = { 0.0L, DBL_MIN, DBL_MAX, DBL_EPSILON, LDBL_MIN, LDBL_MAX, LDBL_EPSILON }; long double f (long double x) { return ((x + (unsigned long int) 10) * (-1 / x) + a[0] + (x ? f (x) : 'c')); } int main () { static int test_array [1 - 2 * !((0 < ((DBL_MAX_EXP < LDBL_MAX_EXP) + (DBL_MANT_DIG < LDBL_MANT_DIG) - (LDBL_MAX_EXP < DBL_MAX_EXP) - (LDBL_MANT_DIG < DBL_MANT_DIG))) && (int) LDBL_EPSILON == 0 )]; test_array [0] = 0; return test_array [0]; ; return 0; } _ACEOF if ac_fn_c_try_compile "$LINENO"; then : ac_cv_type_long_double_wider=yes else ac_cv_type_long_double_wider=no fi rm -f core conftest.err conftest.$ac_objext conftest.$ac_ext fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_cv_type_long_double_wider" >&5 $as_echo "$ac_cv_type_long_double_wider" >&6; } if test $ac_cv_type_long_double_wider = yes; then $as_echo "#define HAVE_LONG_DOUBLE_WIDER 1" >>confdefs.h fi ac_cv_c_long_double=$ac_cv_type_long_double_wider if test $ac_cv_c_long_double = yes; then $as_echo "#define HAVE_LONG_DOUBLE 1" >>confdefs.h fi { $as_echo "$as_me:${as_lineno-$LINENO}: checking for log in -lm" >&5 $as_echo_n "checking for log in -lm... " >&6; } if ${ac_cv_lib_m_log+:} false; then : $as_echo_n "(cached) " >&6 else ac_check_lib_save_LIBS=$LIBS LIBS="-lm $LIBS" cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ /* Override any GCC internal prototype to avoid an error. Use char because int might match the return type of a GCC builtin and then its argument prototype would still apply. */ #ifdef __cplusplus extern "C" #endif char log (); int main () { return log (); ; return 0; } _ACEOF if ac_fn_c_try_link "$LINENO"; then : ac_cv_lib_m_log=yes else ac_cv_lib_m_log=no fi rm -f core conftest.err conftest.$ac_objext \ conftest$ac_exeext conftest.$ac_ext LIBS=$ac_check_lib_save_LIBS fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_cv_lib_m_log" >&5 $as_echo "$ac_cv_lib_m_log" >&6; } if test "x$ac_cv_lib_m_log" = xyes; then : cat >>confdefs.h <<_ACEOF #define HAVE_LIBM 1 _ACEOF LIBS="-lm $LIBS" fi for ac_func in copysign copysignl isinf isinfl isnan isnanl modfl do : as_ac_var=`$as_echo "ac_cv_func_$ac_func" | $as_tr_sh` ac_fn_c_check_func "$LINENO" "$ac_func" "$as_ac_var" if eval test \"x\$"$as_ac_var"\" = x"yes"; then : cat >>confdefs.h <<_ACEOF #define `$as_echo "HAVE_$ac_func" | $as_tr_cpp` 1 _ACEOF fi done # ---------------------------------------------------------------------- # Add code to config.status to create an installable host dependent # configuration file. # ---------------------------------------------------------------------- ac_config_commands="$ac_config_commands snprintfv/compat.h" # ---------------------------------------------------------------------- # Generate the make files. # ---------------------------------------------------------------------- LTLIBOBJS=`echo "$LIBOBJS"|sed 's,\.o ,.lo,g;s,\.o$,.lo,'` ac_config_files="$ac_config_files Makefile snprintfv/Makefile" cat >confcache <<\_ACEOF # This file is a shell script that caches the results of configure # tests run on this system so they can be shared between configure # scripts and configure runs, see configure's option --config-cache. # It is not useful on other systems. If it contains results you don't # want to keep, you may remove or edit it. # # config.status only pays attention to the cache file if you give it # the --recheck option to rerun configure. # # `ac_cv_env_foo' variables (set or unset) will be overridden when # loading this file, other *unset* `ac_cv_foo' will be assigned the # following values. _ACEOF # The following way of writing the cache mishandles newlines in values, # but we know of no workaround that is simple, portable, and efficient. # So, we kill variables containing newlines. # Ultrix sh set writes to stderr and can't be redirected directly, # and sets the high bit in the cache file unless we assign to the vars. ( for ac_var in `(set) 2>&1 | sed -n 's/^\([a-zA-Z_][a-zA-Z0-9_]*\)=.*/\1/p'`; do eval ac_val=\$$ac_var case $ac_val in #( *${as_nl}*) case $ac_var in #( *_cv_*) { $as_echo "$as_me:${as_lineno-$LINENO}: WARNING: cache variable $ac_var contains a newline" >&5 $as_echo "$as_me: WARNING: cache variable $ac_var contains a newline" >&2;} ;; esac case $ac_var in #( _ | IFS | as_nl) ;; #( BASH_ARGV | BASH_SOURCE) eval $ac_var= ;; #( *) { eval $ac_var=; unset $ac_var;} ;; esac ;; esac done (set) 2>&1 | case $as_nl`(ac_space=' '; set) 2>&1` in #( *${as_nl}ac_space=\ *) # `set' does not quote correctly, so add quotes: double-quote # substitution turns \\\\ into \\, and sed turns \\ into \. sed -n \ "s/'/'\\\\''/g; s/^\\([_$as_cr_alnum]*_cv_[_$as_cr_alnum]*\\)=\\(.*\\)/\\1='\\2'/p" ;; #( *) # `set' quotes correctly as required by POSIX, so do not add quotes. sed -n "/^[_$as_cr_alnum]*_cv_[_$as_cr_alnum]*=/p" ;; esac | sort ) | sed ' /^ac_cv_env_/b end t clear :clear s/^\([^=]*\)=\(.*[{}].*\)$/test "${\1+set}" = set || &/ t end s/^\([^=]*\)=\(.*\)$/\1=${\1=\2}/ :end' >>confcache if diff "$cache_file" confcache >/dev/null 2>&1; then :; else if test -w "$cache_file"; then if test "x$cache_file" != "x/dev/null"; then { $as_echo "$as_me:${as_lineno-$LINENO}: updating cache $cache_file" >&5 $as_echo "$as_me: updating cache $cache_file" >&6;} if test ! -f "$cache_file" || test -h "$cache_file"; then cat confcache >"$cache_file" else case $cache_file in #( */* | ?:*) mv -f confcache "$cache_file"$$ && mv -f "$cache_file"$$ "$cache_file" ;; #( *) mv -f confcache "$cache_file" ;; esac fi fi else { $as_echo "$as_me:${as_lineno-$LINENO}: not updating unwritable cache $cache_file" >&5 $as_echo "$as_me: not updating unwritable cache $cache_file" >&6;} fi fi rm -f confcache test "x$prefix" = xNONE && prefix=$ac_default_prefix # Let make expand exec_prefix. test "x$exec_prefix" = xNONE && exec_prefix='${prefix}' DEFS=-DHAVE_CONFIG_H ac_libobjs= ac_ltlibobjs= U= for ac_i in : $LIBOBJS; do test "x$ac_i" = x: && continue # 1. Remove the extension, and $U if already installed. ac_script='s/\$U\././;s/\.o$//;s/\.obj$//' ac_i=`$as_echo "$ac_i" | sed "$ac_script"` # 2. Prepend LIBOBJDIR. When used with automake>=1.10 LIBOBJDIR # will be set to the directory where LIBOBJS objects are built. as_fn_append ac_libobjs " \${LIBOBJDIR}$ac_i\$U.$ac_objext" as_fn_append ac_ltlibobjs " \${LIBOBJDIR}$ac_i"'$U.lo' done LIBOBJS=$ac_libobjs LTLIBOBJS=$ac_ltlibobjs if test -n "$EXEEXT"; then am__EXEEXT_TRUE= am__EXEEXT_FALSE='#' else am__EXEEXT_TRUE='#' am__EXEEXT_FALSE= fi if test -z "${AMDEP_TRUE}" && test -z "${AMDEP_FALSE}"; then as_fn_error $? "conditional \"AMDEP\" was never defined. Usually this means the macro was only invoked conditionally." "$LINENO" 5 fi if test -z "${am__fastdepCC_TRUE}" && test -z "${am__fastdepCC_FALSE}"; then as_fn_error $? "conditional \"am__fastdepCC\" was never defined. Usually this means the macro was only invoked conditionally." "$LINENO" 5 fi if test -z "${SUBDIR_SNPRINTFV_TRUE}" && test -z "${SUBDIR_SNPRINTFV_FALSE}"; then as_fn_error $? "conditional \"SUBDIR_SNPRINTFV\" was never defined. Usually this means the macro was only invoked conditionally." "$LINENO" 5 fi if test -z "${INSTALL_SNPRINTFV_TRUE}" && test -z "${INSTALL_SNPRINTFV_FALSE}"; then as_fn_error $? "conditional \"INSTALL_SNPRINTFV\" was never defined. Usually this means the macro was only invoked conditionally." "$LINENO" 5 fi if test -z "${CONVENIENCE_SNPRINTFV_TRUE}" && test -z "${CONVENIENCE_SNPRINTFV_FALSE}"; then as_fn_error $? "conditional \"CONVENIENCE_SNPRINTFV\" was never defined. Usually this means the macro was only invoked conditionally." "$LINENO" 5 fi if test -z "${am__fastdepCC_TRUE}" && test -z "${am__fastdepCC_FALSE}"; then as_fn_error $? "conditional \"am__fastdepCC\" was never defined. Usually this means the macro was only invoked conditionally." "$LINENO" 5 fi : "${CONFIG_STATUS=./config.status}" ac_write_fail=0 ac_clean_files_save=$ac_clean_files ac_clean_files="$ac_clean_files $CONFIG_STATUS" { $as_echo "$as_me:${as_lineno-$LINENO}: creating $CONFIG_STATUS" >&5 $as_echo "$as_me: creating $CONFIG_STATUS" >&6;} as_write_fail=0 cat >$CONFIG_STATUS <<_ASEOF || as_write_fail=1 #! $SHELL # Generated by $as_me. # Run this file to recreate the current configuration. # Compiler output produced by configure, useful for debugging # configure, is in config.log if it exists. debug=false ac_cs_recheck=false ac_cs_silent=false SHELL=\${CONFIG_SHELL-$SHELL} export SHELL _ASEOF cat >>$CONFIG_STATUS <<\_ASEOF || as_write_fail=1 ## -------------------- ## ## M4sh Initialization. ## ## -------------------- ## # Be more Bourne compatible DUALCASE=1; export DUALCASE # for MKS sh if test -n "${ZSH_VERSION+set}" && (emulate sh) >/dev/null 2>&1; then : emulate sh NULLCMD=: # Pre-4.2 versions of Zsh do word splitting on ${1+"$@"}, which # is contrary to our usage. Disable this feature. alias -g '${1+"$@"}'='"$@"' setopt NO_GLOB_SUBST else case `(set -o) 2>/dev/null` in #( *posix*) : set -o posix ;; #( *) : ;; esac fi as_nl=' ' export as_nl # Printing a long string crashes Solaris 7 /usr/bin/printf. as_echo='\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\' as_echo=$as_echo$as_echo$as_echo$as_echo$as_echo as_echo=$as_echo$as_echo$as_echo$as_echo$as_echo$as_echo # Prefer a ksh shell builtin over an external printf program on Solaris, # but without wasting forks for bash or zsh. if test -z "$BASH_VERSION$ZSH_VERSION" \ && (test "X`print -r -- $as_echo`" = "X$as_echo") 2>/dev/null; then as_echo='print -r --' as_echo_n='print -rn --' elif (test "X`printf %s $as_echo`" = "X$as_echo") 2>/dev/null; then as_echo='printf %s\n' as_echo_n='printf %s' else if test "X`(/usr/ucb/echo -n -n $as_echo) 2>/dev/null`" = "X-n $as_echo"; then as_echo_body='eval /usr/ucb/echo -n "$1$as_nl"' as_echo_n='/usr/ucb/echo -n' else as_echo_body='eval expr "X$1" : "X\\(.*\\)"' as_echo_n_body='eval arg=$1; case $arg in #( *"$as_nl"*) expr "X$arg" : "X\\(.*\\)$as_nl"; arg=`expr "X$arg" : ".*$as_nl\\(.*\\)"`;; esac; expr "X$arg" : "X\\(.*\\)" | tr -d "$as_nl" ' export as_echo_n_body as_echo_n='sh -c $as_echo_n_body as_echo' fi export as_echo_body as_echo='sh -c $as_echo_body as_echo' fi # The user is always right. if test "${PATH_SEPARATOR+set}" != set; then PATH_SEPARATOR=: (PATH='/bin;/bin'; FPATH=$PATH; sh -c :) >/dev/null 2>&1 && { (PATH='/bin:/bin'; FPATH=$PATH; sh -c :) >/dev/null 2>&1 || PATH_SEPARATOR=';' } fi # IFS # We need space, tab and new line, in precisely that order. Quoting is # there to prevent editors from complaining about space-tab. # (If _AS_PATH_WALK were called with IFS unset, it would disable word # splitting by setting IFS to empty value.) IFS=" "" $as_nl" # Find who we are. Look in the path if we contain no directory separator. as_myself= case $0 in #(( *[\\/]* ) as_myself=$0 ;; *) as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. test -r "$as_dir/$0" && as_myself=$as_dir/$0 && break done IFS=$as_save_IFS ;; esac # We did not find ourselves, most probably we were run as `sh COMMAND' # in which case we are not to be found in the path. if test "x$as_myself" = x; then as_myself=$0 fi if test ! -f "$as_myself"; then $as_echo "$as_myself: error: cannot find myself; rerun with an absolute file name" >&2 exit 1 fi # Unset variables that we do not need and which cause bugs (e.g. in # pre-3.0 UWIN ksh). But do not cause bugs in bash 2.01; the "|| exit 1" # suppresses any "Segmentation fault" message there. '((' could # trigger a bug in pdksh 5.2.14. for as_var in BASH_ENV ENV MAIL MAILPATH do eval test x\${$as_var+set} = xset \ && ( (unset $as_var) || exit 1) >/dev/null 2>&1 && unset $as_var || : done PS1='$ ' PS2='> ' PS4='+ ' # NLS nuisances. LC_ALL=C export LC_ALL LANGUAGE=C export LANGUAGE # CDPATH. (unset CDPATH) >/dev/null 2>&1 && unset CDPATH # as_fn_error STATUS ERROR [LINENO LOG_FD] # ---------------------------------------- # Output "`basename $0`: error: ERROR" to stderr. If LINENO and LOG_FD are # provided, also output the error to LOG_FD, referencing LINENO. Then exit the # script with STATUS, using 1 if that was 0. as_fn_error () { as_status=$1; test $as_status -eq 0 && as_status=1 if test "$4"; then as_lineno=${as_lineno-"$3"} as_lineno_stack=as_lineno_stack=$as_lineno_stack $as_echo "$as_me:${as_lineno-$LINENO}: error: $2" >&$4 fi $as_echo "$as_me: error: $2" >&2 as_fn_exit $as_status } # as_fn_error # as_fn_set_status STATUS # ----------------------- # Set $? to STATUS, without forking. as_fn_set_status () { return $1 } # as_fn_set_status # as_fn_exit STATUS # ----------------- # Exit the shell with STATUS, even in a "trap 0" or "set -e" context. as_fn_exit () { set +e as_fn_set_status $1 exit $1 } # as_fn_exit # as_fn_unset VAR # --------------- # Portably unset VAR. as_fn_unset () { { eval $1=; unset $1;} } as_unset=as_fn_unset # as_fn_append VAR VALUE # ---------------------- # Append the text in VALUE to the end of the definition contained in VAR. Take # advantage of any shell optimizations that allow amortized linear growth over # repeated appends, instead of the typical quadratic growth present in naive # implementations. if (eval "as_var=1; as_var+=2; test x\$as_var = x12") 2>/dev/null; then : eval 'as_fn_append () { eval $1+=\$2 }' else as_fn_append () { eval $1=\$$1\$2 } fi # as_fn_append # as_fn_arith ARG... # ------------------ # Perform arithmetic evaluation on the ARGs, and store the result in the # global $as_val. Take advantage of shells that can avoid forks. The arguments # must be portable across $(()) and expr. if (eval "test \$(( 1 + 1 )) = 2") 2>/dev/null; then : eval 'as_fn_arith () { as_val=$(( $* )) }' else as_fn_arith () { as_val=`expr "$@" || test $? -eq 1` } fi # as_fn_arith if expr a : '\(a\)' >/dev/null 2>&1 && test "X`expr 00001 : '.*\(...\)'`" = X001; then as_expr=expr else as_expr=false fi if (basename -- /) >/dev/null 2>&1 && test "X`basename -- / 2>&1`" = "X/"; then as_basename=basename else as_basename=false fi if (as_dir=`dirname -- /` && test "X$as_dir" = X/) >/dev/null 2>&1; then as_dirname=dirname else as_dirname=false fi as_me=`$as_basename -- "$0" || $as_expr X/"$0" : '.*/\([^/][^/]*\)/*$' \| \ X"$0" : 'X\(//\)$' \| \ X"$0" : 'X\(/\)' \| . 2>/dev/null || $as_echo X/"$0" | sed '/^.*\/\([^/][^/]*\)\/*$/{ s//\1/ q } /^X\/\(\/\/\)$/{ s//\1/ q } /^X\/\(\/\).*/{ s//\1/ q } s/.*/./; q'` # Avoid depending upon Character Ranges. as_cr_letters='abcdefghijklmnopqrstuvwxyz' as_cr_LETTERS='ABCDEFGHIJKLMNOPQRSTUVWXYZ' as_cr_Letters=$as_cr_letters$as_cr_LETTERS as_cr_digits='0123456789' as_cr_alnum=$as_cr_Letters$as_cr_digits ECHO_C= ECHO_N= ECHO_T= case `echo -n x` in #((((( -n*) case `echo 'xy\c'` in *c*) ECHO_T=' ';; # ECHO_T is single tab character. xy) ECHO_C='\c';; *) echo `echo ksh88 bug on AIX 6.1` > /dev/null ECHO_T=' ';; esac;; *) ECHO_N='-n';; esac rm -f conf$$ conf$$.exe conf$$.file if test -d conf$$.dir; then rm -f conf$$.dir/conf$$.file else rm -f conf$$.dir mkdir conf$$.dir 2>/dev/null fi if (echo >conf$$.file) 2>/dev/null; then if ln -s conf$$.file conf$$ 2>/dev/null; then as_ln_s='ln -s' # ... but there are two gotchas: # 1) On MSYS, both `ln -s file dir' and `ln file dir' fail. # 2) DJGPP < 2.04 has no symlinks; `ln -s' creates a wrapper executable. # In both cases, we have to default to `cp -pR'. ln -s conf$$.file conf$$.dir 2>/dev/null && test ! -f conf$$.exe || as_ln_s='cp -pR' elif ln conf$$.file conf$$ 2>/dev/null; then as_ln_s=ln else as_ln_s='cp -pR' fi else as_ln_s='cp -pR' fi rm -f conf$$ conf$$.exe conf$$.dir/conf$$.file conf$$.file rmdir conf$$.dir 2>/dev/null # as_fn_mkdir_p # ------------- # Create "$as_dir" as a directory, including parents if necessary. as_fn_mkdir_p () { case $as_dir in #( -*) as_dir=./$as_dir;; esac test -d "$as_dir" || eval $as_mkdir_p || { as_dirs= while :; do case $as_dir in #( *\'*) as_qdir=`$as_echo "$as_dir" | sed "s/'/'\\\\\\\\''/g"`;; #'( *) as_qdir=$as_dir;; esac as_dirs="'$as_qdir' $as_dirs" as_dir=`$as_dirname -- "$as_dir" || $as_expr X"$as_dir" : 'X\(.*[^/]\)//*[^/][^/]*/*$' \| \ X"$as_dir" : 'X\(//\)[^/]' \| \ X"$as_dir" : 'X\(//\)$' \| \ X"$as_dir" : 'X\(/\)' \| . 2>/dev/null || $as_echo X"$as_dir" | sed '/^X\(.*[^/]\)\/\/*[^/][^/]*\/*$/{ s//\1/ q } /^X\(\/\/\)[^/].*/{ s//\1/ q } /^X\(\/\/\)$/{ s//\1/ q } /^X\(\/\).*/{ s//\1/ q } s/.*/./; q'` test -d "$as_dir" && break done test -z "$as_dirs" || eval "mkdir $as_dirs" } || test -d "$as_dir" || as_fn_error $? "cannot create directory $as_dir" } # as_fn_mkdir_p if mkdir -p . 2>/dev/null; then as_mkdir_p='mkdir -p "$as_dir"' else test -d ./-p && rmdir ./-p as_mkdir_p=false fi # as_fn_executable_p FILE # ----------------------- # Test if FILE is an executable regular file. as_fn_executable_p () { test -f "$1" && test -x "$1" } # as_fn_executable_p as_test_x='test -x' as_executable_p=as_fn_executable_p # Sed expression to map a string onto a valid CPP name. as_tr_cpp="eval sed 'y%*$as_cr_letters%P$as_cr_LETTERS%;s%[^_$as_cr_alnum]%_%g'" # Sed expression to map a string onto a valid variable name. as_tr_sh="eval sed 'y%*+%pp%;s%[^_$as_cr_alnum]%_%g'" exec 6>&1 ## ----------------------------------- ## ## Main body of $CONFIG_STATUS script. ## ## ----------------------------------- ## _ASEOF test $as_write_fail = 0 && chmod +x $CONFIG_STATUS || ac_write_fail=1 cat >>$CONFIG_STATUS <<\_ACEOF || ac_write_fail=1 # Save the log message, to keep $0 and so on meaningful, and to # report actual input values of CONFIG_FILES etc. instead of their # values after options handling. ac_log=" This file was extended by snprintfv $as_me 1.1, which was generated by GNU Autoconf 2.69. Invocation command line was CONFIG_FILES = $CONFIG_FILES CONFIG_HEADERS = $CONFIG_HEADERS CONFIG_LINKS = $CONFIG_LINKS CONFIG_COMMANDS = $CONFIG_COMMANDS $ $0 $@ on `(hostname || uname -n) 2>/dev/null | sed 1q` " _ACEOF case $ac_config_files in *" "*) set x $ac_config_files; shift; ac_config_files=$*;; esac case $ac_config_headers in *" "*) set x $ac_config_headers; shift; ac_config_headers=$*;; esac cat >>$CONFIG_STATUS <<_ACEOF || ac_write_fail=1 # Files that config.status was made for. config_files="$ac_config_files" config_headers="$ac_config_headers" config_commands="$ac_config_commands" _ACEOF cat >>$CONFIG_STATUS <<\_ACEOF || ac_write_fail=1 ac_cs_usage="\ \`$as_me' instantiates files and other configuration actions from templates according to the current configuration. Unless the files and actions are specified as TAGs, all are instantiated by default. Usage: $0 [OPTION]... [TAG]... -h, --help print this help, then exit -V, --version print version number and configuration settings, then exit --config print configuration, then exit -q, --quiet, --silent do not print progress messages -d, --debug don't remove temporary files --recheck update $as_me by reconfiguring in the same conditions --file=FILE[:TEMPLATE] instantiate the configuration file FILE --header=FILE[:TEMPLATE] instantiate the configuration header FILE Configuration files: $config_files Configuration headers: $config_headers Configuration commands: $config_commands Report bugs to ." _ACEOF cat >>$CONFIG_STATUS <<_ACEOF || ac_write_fail=1 ac_cs_config="`$as_echo "$ac_configure_args" | sed 's/^ //; s/[\\""\`\$]/\\\\&/g'`" ac_cs_version="\\ snprintfv config.status 1.1 configured by $0, generated by GNU Autoconf 2.69, with options \\"\$ac_cs_config\\" Copyright (C) 2012 Free Software Foundation, Inc. This config.status script is free software; the Free Software Foundation gives unlimited permission to copy, distribute and modify it." ac_pwd='$ac_pwd' srcdir='$srcdir' INSTALL='$INSTALL' MKDIR_P='$MKDIR_P' AWK='$AWK' test -n "\$AWK" || AWK=awk _ACEOF cat >>$CONFIG_STATUS <<\_ACEOF || ac_write_fail=1 # The default lists apply if the user does not specify any file. ac_need_defaults=: while test $# != 0 do case $1 in --*=?*) ac_option=`expr "X$1" : 'X\([^=]*\)='` ac_optarg=`expr "X$1" : 'X[^=]*=\(.*\)'` ac_shift=: ;; --*=) ac_option=`expr "X$1" : 'X\([^=]*\)='` ac_optarg= ac_shift=: ;; *) ac_option=$1 ac_optarg=$2 ac_shift=shift ;; esac case $ac_option in # Handling of the options. -recheck | --recheck | --rechec | --reche | --rech | --rec | --re | --r) ac_cs_recheck=: ;; --version | --versio | --versi | --vers | --ver | --ve | --v | -V ) $as_echo "$ac_cs_version"; exit ;; --config | --confi | --conf | --con | --co | --c ) $as_echo "$ac_cs_config"; exit ;; --debug | --debu | --deb | --de | --d | -d ) debug=: ;; --file | --fil | --fi | --f ) $ac_shift case $ac_optarg in *\'*) ac_optarg=`$as_echo "$ac_optarg" | sed "s/'/'\\\\\\\\''/g"` ;; '') as_fn_error $? "missing file argument" ;; esac as_fn_append CONFIG_FILES " '$ac_optarg'" ac_need_defaults=false;; --header | --heade | --head | --hea ) $ac_shift case $ac_optarg in *\'*) ac_optarg=`$as_echo "$ac_optarg" | sed "s/'/'\\\\\\\\''/g"` ;; esac as_fn_append CONFIG_HEADERS " '$ac_optarg'" ac_need_defaults=false;; --he | --h) # Conflict between --help and --header as_fn_error $? "ambiguous option: \`$1' Try \`$0 --help' for more information.";; --help | --hel | -h ) $as_echo "$ac_cs_usage"; exit ;; -q | -quiet | --quiet | --quie | --qui | --qu | --q \ | -silent | --silent | --silen | --sile | --sil | --si | --s) ac_cs_silent=: ;; # This is an error. -*) as_fn_error $? "unrecognized option: \`$1' Try \`$0 --help' for more information." ;; *) as_fn_append ac_config_targets " $1" ac_need_defaults=false ;; esac shift done ac_configure_extra_args= if $ac_cs_silent; then exec 6>/dev/null ac_configure_extra_args="$ac_configure_extra_args --silent" fi _ACEOF cat >>$CONFIG_STATUS <<_ACEOF || ac_write_fail=1 if \$ac_cs_recheck; then set X $SHELL '$0' $ac_configure_args \$ac_configure_extra_args --no-create --no-recursion shift \$as_echo "running CONFIG_SHELL=$SHELL \$*" >&6 CONFIG_SHELL='$SHELL' export CONFIG_SHELL exec "\$@" fi _ACEOF cat >>$CONFIG_STATUS <<\_ACEOF || ac_write_fail=1 exec 5>>config.log { echo sed 'h;s/./-/g;s/^.../## /;s/...$/ ##/;p;x;p;x' <<_ASBOX ## Running $as_me. ## _ASBOX $as_echo "$ac_log" } >&5 _ACEOF cat >>$CONFIG_STATUS <<_ACEOF || ac_write_fail=1 # # INIT-COMMANDS # AMDEP_TRUE="$AMDEP_TRUE" ac_aux_dir="$ac_aux_dir" # The HP-UX ksh and POSIX shell print the target directory to stdout # if CDPATH is set. (unset CDPATH) >/dev/null 2>&1 && unset CDPATH sed_quote_subst='$sed_quote_subst' double_quote_subst='$double_quote_subst' delay_variable_subst='$delay_variable_subst' AS='`$ECHO "$AS" | $SED "$delay_single_quote_subst"`' DLLTOOL='`$ECHO "$DLLTOOL" | $SED "$delay_single_quote_subst"`' OBJDUMP='`$ECHO "$OBJDUMP" | $SED "$delay_single_quote_subst"`' macro_version='`$ECHO "$macro_version" | $SED "$delay_single_quote_subst"`' macro_revision='`$ECHO "$macro_revision" | $SED "$delay_single_quote_subst"`' enable_shared='`$ECHO "$enable_shared" | $SED "$delay_single_quote_subst"`' enable_static='`$ECHO "$enable_static" | $SED "$delay_single_quote_subst"`' pic_mode='`$ECHO "$pic_mode" | $SED "$delay_single_quote_subst"`' enable_fast_install='`$ECHO "$enable_fast_install" | $SED "$delay_single_quote_subst"`' SHELL='`$ECHO "$SHELL" | $SED "$delay_single_quote_subst"`' ECHO='`$ECHO "$ECHO" | $SED "$delay_single_quote_subst"`' PATH_SEPARATOR='`$ECHO "$PATH_SEPARATOR" | $SED "$delay_single_quote_subst"`' host_alias='`$ECHO "$host_alias" | $SED "$delay_single_quote_subst"`' host='`$ECHO "$host" | $SED "$delay_single_quote_subst"`' host_os='`$ECHO "$host_os" | $SED "$delay_single_quote_subst"`' build_alias='`$ECHO "$build_alias" | $SED "$delay_single_quote_subst"`' build='`$ECHO "$build" | $SED "$delay_single_quote_subst"`' build_os='`$ECHO "$build_os" | $SED "$delay_single_quote_subst"`' SED='`$ECHO "$SED" | $SED "$delay_single_quote_subst"`' Xsed='`$ECHO "$Xsed" | $SED "$delay_single_quote_subst"`' GREP='`$ECHO "$GREP" | $SED "$delay_single_quote_subst"`' EGREP='`$ECHO "$EGREP" | $SED "$delay_single_quote_subst"`' FGREP='`$ECHO "$FGREP" | $SED "$delay_single_quote_subst"`' LD='`$ECHO "$LD" | $SED "$delay_single_quote_subst"`' NM='`$ECHO "$NM" | $SED "$delay_single_quote_subst"`' LN_S='`$ECHO "$LN_S" | $SED "$delay_single_quote_subst"`' max_cmd_len='`$ECHO "$max_cmd_len" | $SED "$delay_single_quote_subst"`' ac_objext='`$ECHO "$ac_objext" | $SED "$delay_single_quote_subst"`' exeext='`$ECHO "$exeext" | $SED "$delay_single_quote_subst"`' lt_unset='`$ECHO "$lt_unset" | $SED "$delay_single_quote_subst"`' lt_SP2NL='`$ECHO "$lt_SP2NL" | $SED "$delay_single_quote_subst"`' lt_NL2SP='`$ECHO "$lt_NL2SP" | $SED "$delay_single_quote_subst"`' lt_cv_to_host_file_cmd='`$ECHO "$lt_cv_to_host_file_cmd" | $SED "$delay_single_quote_subst"`' lt_cv_to_tool_file_cmd='`$ECHO "$lt_cv_to_tool_file_cmd" | $SED "$delay_single_quote_subst"`' reload_flag='`$ECHO "$reload_flag" | $SED "$delay_single_quote_subst"`' reload_cmds='`$ECHO "$reload_cmds" | $SED "$delay_single_quote_subst"`' deplibs_check_method='`$ECHO "$deplibs_check_method" | $SED "$delay_single_quote_subst"`' file_magic_cmd='`$ECHO "$file_magic_cmd" | $SED "$delay_single_quote_subst"`' file_magic_glob='`$ECHO "$file_magic_glob" | $SED "$delay_single_quote_subst"`' want_nocaseglob='`$ECHO "$want_nocaseglob" | $SED "$delay_single_quote_subst"`' sharedlib_from_linklib_cmd='`$ECHO "$sharedlib_from_linklib_cmd" | $SED "$delay_single_quote_subst"`' AR='`$ECHO "$AR" | $SED "$delay_single_quote_subst"`' AR_FLAGS='`$ECHO "$AR_FLAGS" | $SED "$delay_single_quote_subst"`' archiver_list_spec='`$ECHO "$archiver_list_spec" | $SED "$delay_single_quote_subst"`' STRIP='`$ECHO "$STRIP" | $SED "$delay_single_quote_subst"`' RANLIB='`$ECHO "$RANLIB" | $SED "$delay_single_quote_subst"`' old_postinstall_cmds='`$ECHO "$old_postinstall_cmds" | $SED "$delay_single_quote_subst"`' old_postuninstall_cmds='`$ECHO "$old_postuninstall_cmds" | $SED "$delay_single_quote_subst"`' old_archive_cmds='`$ECHO "$old_archive_cmds" | $SED "$delay_single_quote_subst"`' lock_old_archive_extraction='`$ECHO "$lock_old_archive_extraction" | $SED "$delay_single_quote_subst"`' CC='`$ECHO "$CC" | $SED "$delay_single_quote_subst"`' CFLAGS='`$ECHO "$CFLAGS" | $SED "$delay_single_quote_subst"`' compiler='`$ECHO "$compiler" | $SED "$delay_single_quote_subst"`' GCC='`$ECHO "$GCC" | $SED "$delay_single_quote_subst"`' lt_cv_sys_global_symbol_pipe='`$ECHO "$lt_cv_sys_global_symbol_pipe" | $SED "$delay_single_quote_subst"`' lt_cv_sys_global_symbol_to_cdecl='`$ECHO "$lt_cv_sys_global_symbol_to_cdecl" | $SED "$delay_single_quote_subst"`' lt_cv_sys_global_symbol_to_c_name_address='`$ECHO "$lt_cv_sys_global_symbol_to_c_name_address" | $SED "$delay_single_quote_subst"`' lt_cv_sys_global_symbol_to_c_name_address_lib_prefix='`$ECHO "$lt_cv_sys_global_symbol_to_c_name_address_lib_prefix" | $SED "$delay_single_quote_subst"`' nm_file_list_spec='`$ECHO "$nm_file_list_spec" | $SED "$delay_single_quote_subst"`' lt_sysroot='`$ECHO "$lt_sysroot" | $SED "$delay_single_quote_subst"`' objdir='`$ECHO "$objdir" | $SED "$delay_single_quote_subst"`' MAGIC_CMD='`$ECHO "$MAGIC_CMD" | $SED "$delay_single_quote_subst"`' lt_prog_compiler_no_builtin_flag='`$ECHO "$lt_prog_compiler_no_builtin_flag" | $SED "$delay_single_quote_subst"`' lt_prog_compiler_pic='`$ECHO "$lt_prog_compiler_pic" | $SED "$delay_single_quote_subst"`' lt_prog_compiler_wl='`$ECHO "$lt_prog_compiler_wl" | $SED "$delay_single_quote_subst"`' lt_prog_compiler_static='`$ECHO "$lt_prog_compiler_static" | $SED "$delay_single_quote_subst"`' lt_cv_prog_compiler_c_o='`$ECHO "$lt_cv_prog_compiler_c_o" | $SED "$delay_single_quote_subst"`' need_locks='`$ECHO "$need_locks" | $SED "$delay_single_quote_subst"`' MANIFEST_TOOL='`$ECHO "$MANIFEST_TOOL" | $SED "$delay_single_quote_subst"`' DSYMUTIL='`$ECHO "$DSYMUTIL" | $SED "$delay_single_quote_subst"`' NMEDIT='`$ECHO "$NMEDIT" | $SED "$delay_single_quote_subst"`' LIPO='`$ECHO "$LIPO" | $SED "$delay_single_quote_subst"`' OTOOL='`$ECHO "$OTOOL" | $SED "$delay_single_quote_subst"`' OTOOL64='`$ECHO "$OTOOL64" | $SED "$delay_single_quote_subst"`' libext='`$ECHO "$libext" | $SED "$delay_single_quote_subst"`' shrext_cmds='`$ECHO "$shrext_cmds" | $SED "$delay_single_quote_subst"`' extract_expsyms_cmds='`$ECHO "$extract_expsyms_cmds" | $SED "$delay_single_quote_subst"`' archive_cmds_need_lc='`$ECHO "$archive_cmds_need_lc" | $SED "$delay_single_quote_subst"`' enable_shared_with_static_runtimes='`$ECHO "$enable_shared_with_static_runtimes" | $SED "$delay_single_quote_subst"`' export_dynamic_flag_spec='`$ECHO "$export_dynamic_flag_spec" | $SED "$delay_single_quote_subst"`' whole_archive_flag_spec='`$ECHO "$whole_archive_flag_spec" | $SED "$delay_single_quote_subst"`' compiler_needs_object='`$ECHO "$compiler_needs_object" | $SED "$delay_single_quote_subst"`' old_archive_from_new_cmds='`$ECHO "$old_archive_from_new_cmds" | $SED "$delay_single_quote_subst"`' old_archive_from_expsyms_cmds='`$ECHO "$old_archive_from_expsyms_cmds" | $SED "$delay_single_quote_subst"`' archive_cmds='`$ECHO "$archive_cmds" | $SED "$delay_single_quote_subst"`' archive_expsym_cmds='`$ECHO "$archive_expsym_cmds" | $SED "$delay_single_quote_subst"`' module_cmds='`$ECHO "$module_cmds" | $SED "$delay_single_quote_subst"`' module_expsym_cmds='`$ECHO "$module_expsym_cmds" | $SED "$delay_single_quote_subst"`' with_gnu_ld='`$ECHO "$with_gnu_ld" | $SED "$delay_single_quote_subst"`' allow_undefined_flag='`$ECHO "$allow_undefined_flag" | $SED "$delay_single_quote_subst"`' no_undefined_flag='`$ECHO "$no_undefined_flag" | $SED "$delay_single_quote_subst"`' hardcode_libdir_flag_spec='`$ECHO "$hardcode_libdir_flag_spec" | $SED "$delay_single_quote_subst"`' hardcode_libdir_separator='`$ECHO "$hardcode_libdir_separator" | $SED "$delay_single_quote_subst"`' hardcode_direct='`$ECHO "$hardcode_direct" | $SED "$delay_single_quote_subst"`' hardcode_direct_absolute='`$ECHO "$hardcode_direct_absolute" | $SED "$delay_single_quote_subst"`' hardcode_minus_L='`$ECHO "$hardcode_minus_L" | $SED "$delay_single_quote_subst"`' hardcode_shlibpath_var='`$ECHO "$hardcode_shlibpath_var" | $SED "$delay_single_quote_subst"`' hardcode_automatic='`$ECHO "$hardcode_automatic" | $SED "$delay_single_quote_subst"`' inherit_rpath='`$ECHO "$inherit_rpath" | $SED "$delay_single_quote_subst"`' link_all_deplibs='`$ECHO "$link_all_deplibs" | $SED "$delay_single_quote_subst"`' always_export_symbols='`$ECHO "$always_export_symbols" | $SED "$delay_single_quote_subst"`' export_symbols_cmds='`$ECHO "$export_symbols_cmds" | $SED "$delay_single_quote_subst"`' exclude_expsyms='`$ECHO "$exclude_expsyms" | $SED "$delay_single_quote_subst"`' include_expsyms='`$ECHO "$include_expsyms" | $SED "$delay_single_quote_subst"`' prelink_cmds='`$ECHO "$prelink_cmds" | $SED "$delay_single_quote_subst"`' postlink_cmds='`$ECHO "$postlink_cmds" | $SED "$delay_single_quote_subst"`' file_list_spec='`$ECHO "$file_list_spec" | $SED "$delay_single_quote_subst"`' variables_saved_for_relink='`$ECHO "$variables_saved_for_relink" | $SED "$delay_single_quote_subst"`' need_lib_prefix='`$ECHO "$need_lib_prefix" | $SED "$delay_single_quote_subst"`' need_version='`$ECHO "$need_version" | $SED "$delay_single_quote_subst"`' version_type='`$ECHO "$version_type" | $SED "$delay_single_quote_subst"`' runpath_var='`$ECHO "$runpath_var" | $SED "$delay_single_quote_subst"`' shlibpath_var='`$ECHO "$shlibpath_var" | $SED "$delay_single_quote_subst"`' shlibpath_overrides_runpath='`$ECHO "$shlibpath_overrides_runpath" | $SED "$delay_single_quote_subst"`' libname_spec='`$ECHO "$libname_spec" | $SED "$delay_single_quote_subst"`' library_names_spec='`$ECHO "$library_names_spec" | $SED "$delay_single_quote_subst"`' soname_spec='`$ECHO "$soname_spec" | $SED "$delay_single_quote_subst"`' install_override_mode='`$ECHO "$install_override_mode" | $SED "$delay_single_quote_subst"`' postinstall_cmds='`$ECHO "$postinstall_cmds" | $SED "$delay_single_quote_subst"`' postuninstall_cmds='`$ECHO "$postuninstall_cmds" | $SED "$delay_single_quote_subst"`' finish_cmds='`$ECHO "$finish_cmds" | $SED "$delay_single_quote_subst"`' finish_eval='`$ECHO "$finish_eval" | $SED "$delay_single_quote_subst"`' hardcode_into_libs='`$ECHO "$hardcode_into_libs" | $SED "$delay_single_quote_subst"`' sys_lib_search_path_spec='`$ECHO "$sys_lib_search_path_spec" | $SED "$delay_single_quote_subst"`' sys_lib_dlsearch_path_spec='`$ECHO "$sys_lib_dlsearch_path_spec" | $SED "$delay_single_quote_subst"`' hardcode_action='`$ECHO "$hardcode_action" | $SED "$delay_single_quote_subst"`' enable_dlopen='`$ECHO "$enable_dlopen" | $SED "$delay_single_quote_subst"`' enable_dlopen_self='`$ECHO "$enable_dlopen_self" | $SED "$delay_single_quote_subst"`' enable_dlopen_self_static='`$ECHO "$enable_dlopen_self_static" | $SED "$delay_single_quote_subst"`' old_striplib='`$ECHO "$old_striplib" | $SED "$delay_single_quote_subst"`' striplib='`$ECHO "$striplib" | $SED "$delay_single_quote_subst"`' LTCC='$LTCC' LTCFLAGS='$LTCFLAGS' compiler='$compiler_DEFAULT' # A function that is used when there is no print builtin or printf. func_fallback_echo () { eval 'cat <<_LTECHO_EOF \$1 _LTECHO_EOF' } # Quote evaled strings. for var in AS \ DLLTOOL \ OBJDUMP \ SHELL \ ECHO \ PATH_SEPARATOR \ SED \ GREP \ EGREP \ FGREP \ LD \ NM \ LN_S \ lt_SP2NL \ lt_NL2SP \ reload_flag \ deplibs_check_method \ file_magic_cmd \ file_magic_glob \ want_nocaseglob \ sharedlib_from_linklib_cmd \ AR \ AR_FLAGS \ archiver_list_spec \ STRIP \ RANLIB \ CC \ CFLAGS \ compiler \ lt_cv_sys_global_symbol_pipe \ lt_cv_sys_global_symbol_to_cdecl \ lt_cv_sys_global_symbol_to_c_name_address \ lt_cv_sys_global_symbol_to_c_name_address_lib_prefix \ nm_file_list_spec \ lt_prog_compiler_no_builtin_flag \ lt_prog_compiler_pic \ lt_prog_compiler_wl \ lt_prog_compiler_static \ lt_cv_prog_compiler_c_o \ need_locks \ MANIFEST_TOOL \ DSYMUTIL \ NMEDIT \ LIPO \ OTOOL \ OTOOL64 \ shrext_cmds \ export_dynamic_flag_spec \ whole_archive_flag_spec \ compiler_needs_object \ with_gnu_ld \ allow_undefined_flag \ no_undefined_flag \ hardcode_libdir_flag_spec \ hardcode_libdir_separator \ exclude_expsyms \ include_expsyms \ file_list_spec \ variables_saved_for_relink \ libname_spec \ library_names_spec \ soname_spec \ install_override_mode \ finish_eval \ old_striplib \ striplib; do case \`eval \\\\\$ECHO \\\\""\\\\\$\$var"\\\\"\` in *[\\\\\\\`\\"\\\$]*) eval "lt_\$var=\\\\\\"\\\`\\\$ECHO \\"\\\$\$var\\" | \\\$SED \\"\\\$sed_quote_subst\\"\\\`\\\\\\"" ;; *) eval "lt_\$var=\\\\\\"\\\$\$var\\\\\\"" ;; esac done # Double-quote double-evaled strings. for var in reload_cmds \ old_postinstall_cmds \ old_postuninstall_cmds \ old_archive_cmds \ extract_expsyms_cmds \ old_archive_from_new_cmds \ old_archive_from_expsyms_cmds \ archive_cmds \ archive_expsym_cmds \ module_cmds \ module_expsym_cmds \ export_symbols_cmds \ prelink_cmds \ postlink_cmds \ postinstall_cmds \ postuninstall_cmds \ finish_cmds \ sys_lib_search_path_spec \ sys_lib_dlsearch_path_spec; do case \`eval \\\\\$ECHO \\\\""\\\\\$\$var"\\\\"\` in *[\\\\\\\`\\"\\\$]*) eval "lt_\$var=\\\\\\"\\\`\\\$ECHO \\"\\\$\$var\\" | \\\$SED -e \\"\\\$double_quote_subst\\" -e \\"\\\$sed_quote_subst\\" -e \\"\\\$delay_variable_subst\\"\\\`\\\\\\"" ;; *) eval "lt_\$var=\\\\\\"\\\$\$var\\\\\\"" ;; esac done ac_aux_dir='$ac_aux_dir' xsi_shell='$xsi_shell' lt_shell_append='$lt_shell_append' # See if we are running on zsh, and set the options which allow our # commands through without removal of \ escapes INIT. if test -n "\${ZSH_VERSION+set}" ; then setopt NO_GLOB_SUBST fi PACKAGE='$PACKAGE' VERSION='$VERSION' TIMESTAMP='$TIMESTAMP' RM='$RM' ofile='$ofile' ac_cv_header_inttypes_h=$ac_cv_header_inttypes_h ac_cv_header_stdint_h=$ac_cv_header_stdint_h ac_cv_header_stdlib_h=$ac_cv_header_stdlib_h ac_cv_header_sys_types_h=$ac_cv_header_sys_types_h ac_cv_header_wchar_h=$ac_cv_header_wchar_h ac_cv_header_memory_h=$ac_cv_header_memory_h ac_cv_header_stdarg_h=$ac_cv_header_stdarg_h ac_cv_header_varargs_h=$ac_cv_header_varargs_h ac_cv_header_string_h=$ac_cv_header_string_h ac_cv_header_strings_h=$ac_cv_header_strings_h ac_cv_header_limits_h=$ac_cv_header_limits_h ac_cv_header_values_h=$ac_cv_header_values_h ac_cv_header_errno_h=$ac_cv_header_errno_h ac_cv_func_fputc_unlocked=$ac_cv_func_fputc_unlocked ac_cv_func_flockfile=$ac_cv_func_flockfile ac_cv_type_intmax_t=$ac_cv_type_intmax_t ac_cv_c_long_double=$ac_cv_c_long_double ac_cv_type_size_t=$ac_cv_type_size_t ac_cv_type_wchar_t=$ac_cv_type_wchar_t ac_cv_type_wint_t=$ac_cv_type_wint_t ac_cv_sizeof_wint_t=$ac_cv_sizeof_wint_t ac_cv_sizeof_int=$ac_cv_sizeof_int snv_cv_static_inline=$snv_cv_static_inline srcdir=$srcdir _ACEOF cat >>$CONFIG_STATUS <<\_ACEOF || ac_write_fail=1 # Handling of arguments. for ac_config_target in $ac_config_targets do case $ac_config_target in "config.h") CONFIG_HEADERS="$CONFIG_HEADERS config.h" ;; "depfiles") CONFIG_COMMANDS="$CONFIG_COMMANDS depfiles" ;; "libtool") CONFIG_COMMANDS="$CONFIG_COMMANDS libtool" ;; "snprintfv/compat.h") CONFIG_COMMANDS="$CONFIG_COMMANDS snprintfv/compat.h" ;; "Makefile") CONFIG_FILES="$CONFIG_FILES Makefile" ;; "snprintfv/Makefile") CONFIG_FILES="$CONFIG_FILES snprintfv/Makefile" ;; *) as_fn_error $? "invalid argument: \`$ac_config_target'" "$LINENO" 5;; esac done # If the user did not use the arguments to specify the items to instantiate, # then the envvar interface is used. Set only those that are not. # We use the long form for the default assignment because of an extremely # bizarre bug on SunOS 4.1.3. if $ac_need_defaults; then test "${CONFIG_FILES+set}" = set || CONFIG_FILES=$config_files test "${CONFIG_HEADERS+set}" = set || CONFIG_HEADERS=$config_headers test "${CONFIG_COMMANDS+set}" = set || CONFIG_COMMANDS=$config_commands fi # Have a temporary directory for convenience. Make it in the build tree # simply because there is no reason against having it here, and in addition, # creating and moving files from /tmp can sometimes cause problems. # Hook for its removal unless debugging. # Note that there is a small window in which the directory will not be cleaned: # after its creation but before its name has been assigned to `$tmp'. $debug || { tmp= ac_tmp= trap 'exit_status=$? : "${ac_tmp:=$tmp}" { test ! -d "$ac_tmp" || rm -fr "$ac_tmp"; } && exit $exit_status ' 0 trap 'as_fn_exit 1' 1 2 13 15 } # Create a (secure) tmp directory for tmp files. { tmp=`(umask 077 && mktemp -d "./confXXXXXX") 2>/dev/null` && test -d "$tmp" } || { tmp=./conf$$-$RANDOM (umask 077 && mkdir "$tmp") } || as_fn_error $? "cannot create a temporary directory in ." "$LINENO" 5 ac_tmp=$tmp # Set up the scripts for CONFIG_FILES section. # No need to generate them if there are no CONFIG_FILES. # This happens for instance with `./config.status config.h'. if test -n "$CONFIG_FILES"; then ac_cr=`echo X | tr X '\015'` # On cygwin, bash can eat \r inside `` if the user requested igncr. # But we know of no other shell where ac_cr would be empty at this # point, so we can use a bashism as a fallback. if test "x$ac_cr" = x; then eval ac_cr=\$\'\\r\' fi ac_cs_awk_cr=`$AWK 'BEGIN { print "a\rb" }' /dev/null` if test "$ac_cs_awk_cr" = "a${ac_cr}b"; then ac_cs_awk_cr='\\r' else ac_cs_awk_cr=$ac_cr fi echo 'BEGIN {' >"$ac_tmp/subs1.awk" && _ACEOF { echo "cat >conf$$subs.awk <<_ACEOF" && echo "$ac_subst_vars" | sed 's/.*/&!$&$ac_delim/' && echo "_ACEOF" } >conf$$subs.sh || as_fn_error $? "could not make $CONFIG_STATUS" "$LINENO" 5 ac_delim_num=`echo "$ac_subst_vars" | grep -c '^'` ac_delim='%!_!# ' for ac_last_try in false false false false false :; do . ./conf$$subs.sh || as_fn_error $? "could not make $CONFIG_STATUS" "$LINENO" 5 ac_delim_n=`sed -n "s/.*$ac_delim\$/X/p" conf$$subs.awk | grep -c X` if test $ac_delim_n = $ac_delim_num; then break elif $ac_last_try; then as_fn_error $? "could not make $CONFIG_STATUS" "$LINENO" 5 else ac_delim="$ac_delim!$ac_delim _$ac_delim!! " fi done rm -f conf$$subs.sh cat >>$CONFIG_STATUS <<_ACEOF || ac_write_fail=1 cat >>"\$ac_tmp/subs1.awk" <<\\_ACAWK && _ACEOF sed -n ' h s/^/S["/; s/!.*/"]=/ p g s/^[^!]*!// :repl t repl s/'"$ac_delim"'$// t delim :nl h s/\(.\{148\}\)..*/\1/ t more1 s/["\\]/\\&/g; s/^/"/; s/$/\\n"\\/ p n b repl :more1 s/["\\]/\\&/g; s/^/"/; s/$/"\\/ p g s/.\{148\}// t nl :delim h s/\(.\{148\}\)..*/\1/ t more2 s/["\\]/\\&/g; s/^/"/; s/$/"/ p b :more2 s/["\\]/\\&/g; s/^/"/; s/$/"\\/ p g s/.\{148\}// t delim ' >$CONFIG_STATUS || ac_write_fail=1 rm -f conf$$subs.awk cat >>$CONFIG_STATUS <<_ACEOF || ac_write_fail=1 _ACAWK cat >>"\$ac_tmp/subs1.awk" <<_ACAWK && for (key in S) S_is_set[key] = 1 FS = "" } { line = $ 0 nfields = split(line, field, "@") substed = 0 len = length(field[1]) for (i = 2; i < nfields; i++) { key = field[i] keylen = length(key) if (S_is_set[key]) { value = S[key] line = substr(line, 1, len) "" value "" substr(line, len + keylen + 3) len += length(value) + length(field[++i]) substed = 1 } else len += 1 + keylen } print line } _ACAWK _ACEOF cat >>$CONFIG_STATUS <<\_ACEOF || ac_write_fail=1 if sed "s/$ac_cr//" < /dev/null > /dev/null 2>&1; then sed "s/$ac_cr\$//; s/$ac_cr/$ac_cs_awk_cr/g" else cat fi < "$ac_tmp/subs1.awk" > "$ac_tmp/subs.awk" \ || as_fn_error $? "could not setup config files machinery" "$LINENO" 5 _ACEOF # VPATH may cause trouble with some makes, so we remove sole $(srcdir), # ${srcdir} and @srcdir@ entries from VPATH if srcdir is ".", strip leading and # trailing colons and then remove the whole line if VPATH becomes empty # (actually we leave an empty line to preserve line numbers). if test "x$srcdir" = x.; then ac_vpsub='/^[ ]*VPATH[ ]*=[ ]*/{ h s/// s/^/:/ s/[ ]*$/:/ s/:\$(srcdir):/:/g s/:\${srcdir}:/:/g s/:@srcdir@:/:/g s/^:*// s/:*$// x s/\(=[ ]*\).*/\1/ G s/\n// s/^[^=]*=[ ]*$// }' fi cat >>$CONFIG_STATUS <<\_ACEOF || ac_write_fail=1 fi # test -n "$CONFIG_FILES" # Set up the scripts for CONFIG_HEADERS section. # No need to generate them if there are no CONFIG_HEADERS. # This happens for instance with `./config.status Makefile'. if test -n "$CONFIG_HEADERS"; then cat >"$ac_tmp/defines.awk" <<\_ACAWK || BEGIN { _ACEOF # Transform confdefs.h into an awk script `defines.awk', embedded as # here-document in config.status, that substitutes the proper values into # config.h.in to produce config.h. # Create a delimiter string that does not exist in confdefs.h, to ease # handling of long lines. ac_delim='%!_!# ' for ac_last_try in false false :; do ac_tt=`sed -n "/$ac_delim/p" confdefs.h` if test -z "$ac_tt"; then break elif $ac_last_try; then as_fn_error $? "could not make $CONFIG_HEADERS" "$LINENO" 5 else ac_delim="$ac_delim!$ac_delim _$ac_delim!! " fi done # For the awk script, D is an array of macro values keyed by name, # likewise P contains macro parameters if any. Preserve backslash # newline sequences. ac_word_re=[_$as_cr_Letters][_$as_cr_alnum]* sed -n ' s/.\{148\}/&'"$ac_delim"'/g t rset :rset s/^[ ]*#[ ]*define[ ][ ]*/ / t def d :def s/\\$// t bsnl s/["\\]/\\&/g s/^ \('"$ac_word_re"'\)\(([^()]*)\)[ ]*\(.*\)/P["\1"]="\2"\ D["\1"]=" \3"/p s/^ \('"$ac_word_re"'\)[ ]*\(.*\)/D["\1"]=" \2"/p d :bsnl s/["\\]/\\&/g s/^ \('"$ac_word_re"'\)\(([^()]*)\)[ ]*\(.*\)/P["\1"]="\2"\ D["\1"]=" \3\\\\\\n"\\/p t cont s/^ \('"$ac_word_re"'\)[ ]*\(.*\)/D["\1"]=" \2\\\\\\n"\\/p t cont d :cont n s/.\{148\}/&'"$ac_delim"'/g t clear :clear s/\\$// t bsnlc s/["\\]/\\&/g; s/^/"/; s/$/"/p d :bsnlc s/["\\]/\\&/g; s/^/"/; s/$/\\\\\\n"\\/p b cont ' >$CONFIG_STATUS || ac_write_fail=1 cat >>$CONFIG_STATUS <<_ACEOF || ac_write_fail=1 for (key in D) D_is_set[key] = 1 FS = "" } /^[\t ]*#[\t ]*(define|undef)[\t ]+$ac_word_re([\t (]|\$)/ { line = \$ 0 split(line, arg, " ") if (arg[1] == "#") { defundef = arg[2] mac1 = arg[3] } else { defundef = substr(arg[1], 2) mac1 = arg[2] } split(mac1, mac2, "(") #) macro = mac2[1] prefix = substr(line, 1, index(line, defundef) - 1) if (D_is_set[macro]) { # Preserve the white space surrounding the "#". print prefix "define", macro P[macro] D[macro] next } else { # Replace #undef with comments. This is necessary, for example, # in the case of _POSIX_SOURCE, which is predefined and required # on some systems where configure will not decide to define it. if (defundef == "undef") { print "/*", prefix defundef, macro, "*/" next } } } { print } _ACAWK _ACEOF cat >>$CONFIG_STATUS <<\_ACEOF || ac_write_fail=1 as_fn_error $? "could not setup config headers machinery" "$LINENO" 5 fi # test -n "$CONFIG_HEADERS" eval set X " :F $CONFIG_FILES :H $CONFIG_HEADERS :C $CONFIG_COMMANDS" shift for ac_tag do case $ac_tag in :[FHLC]) ac_mode=$ac_tag; continue;; esac case $ac_mode$ac_tag in :[FHL]*:*);; :L* | :C*:*) as_fn_error $? "invalid tag \`$ac_tag'" "$LINENO" 5;; :[FH]-) ac_tag=-:-;; :[FH]*) ac_tag=$ac_tag:$ac_tag.in;; esac ac_save_IFS=$IFS IFS=: set x $ac_tag IFS=$ac_save_IFS shift ac_file=$1 shift case $ac_mode in :L) ac_source=$1;; :[FH]) ac_file_inputs= for ac_f do case $ac_f in -) ac_f="$ac_tmp/stdin";; *) # Look for the file first in the build tree, then in the source tree # (if the path is not absolute). The absolute path cannot be DOS-style, # because $ac_f cannot contain `:'. test -f "$ac_f" || case $ac_f in [\\/$]*) false;; *) test -f "$srcdir/$ac_f" && ac_f="$srcdir/$ac_f";; esac || as_fn_error 1 "cannot find input file: \`$ac_f'" "$LINENO" 5;; esac case $ac_f in *\'*) ac_f=`$as_echo "$ac_f" | sed "s/'/'\\\\\\\\''/g"`;; esac as_fn_append ac_file_inputs " '$ac_f'" done # Let's still pretend it is `configure' which instantiates (i.e., don't # use $as_me), people would be surprised to read: # /* config.h. Generated by config.status. */ configure_input='Generated from '` $as_echo "$*" | sed 's|^[^:]*/||;s|:[^:]*/|, |g' `' by configure.' if test x"$ac_file" != x-; then configure_input="$ac_file. $configure_input" { $as_echo "$as_me:${as_lineno-$LINENO}: creating $ac_file" >&5 $as_echo "$as_me: creating $ac_file" >&6;} fi # Neutralize special characters interpreted by sed in replacement strings. case $configure_input in #( *\&* | *\|* | *\\* ) ac_sed_conf_input=`$as_echo "$configure_input" | sed 's/[\\\\&|]/\\\\&/g'`;; #( *) ac_sed_conf_input=$configure_input;; esac case $ac_tag in *:-:* | *:-) cat >"$ac_tmp/stdin" \ || as_fn_error $? "could not create $ac_file" "$LINENO" 5 ;; esac ;; esac ac_dir=`$as_dirname -- "$ac_file" || $as_expr X"$ac_file" : 'X\(.*[^/]\)//*[^/][^/]*/*$' \| \ X"$ac_file" : 'X\(//\)[^/]' \| \ X"$ac_file" : 'X\(//\)$' \| \ X"$ac_file" : 'X\(/\)' \| . 2>/dev/null || $as_echo X"$ac_file" | sed '/^X\(.*[^/]\)\/\/*[^/][^/]*\/*$/{ s//\1/ q } /^X\(\/\/\)[^/].*/{ s//\1/ q } /^X\(\/\/\)$/{ s//\1/ q } /^X\(\/\).*/{ s//\1/ q } s/.*/./; q'` as_dir="$ac_dir"; as_fn_mkdir_p ac_builddir=. case "$ac_dir" in .) ac_dir_suffix= ac_top_builddir_sub=. ac_top_build_prefix= ;; *) ac_dir_suffix=/`$as_echo "$ac_dir" | sed 's|^\.[\\/]||'` # A ".." for each directory in $ac_dir_suffix. ac_top_builddir_sub=`$as_echo "$ac_dir_suffix" | sed 's|/[^\\/]*|/..|g;s|/||'` case $ac_top_builddir_sub in "") ac_top_builddir_sub=. ac_top_build_prefix= ;; *) ac_top_build_prefix=$ac_top_builddir_sub/ ;; esac ;; esac ac_abs_top_builddir=$ac_pwd ac_abs_builddir=$ac_pwd$ac_dir_suffix # for backward compatibility: ac_top_builddir=$ac_top_build_prefix case $srcdir in .) # We are building in place. ac_srcdir=. ac_top_srcdir=$ac_top_builddir_sub ac_abs_top_srcdir=$ac_pwd ;; [\\/]* | ?:[\\/]* ) # Absolute name. ac_srcdir=$srcdir$ac_dir_suffix; ac_top_srcdir=$srcdir ac_abs_top_srcdir=$srcdir ;; *) # Relative name. ac_srcdir=$ac_top_build_prefix$srcdir$ac_dir_suffix ac_top_srcdir=$ac_top_build_prefix$srcdir ac_abs_top_srcdir=$ac_pwd/$srcdir ;; esac ac_abs_srcdir=$ac_abs_top_srcdir$ac_dir_suffix case $ac_mode in :F) # # CONFIG_FILE # case $INSTALL in [\\/$]* | ?:[\\/]* ) ac_INSTALL=$INSTALL ;; *) ac_INSTALL=$ac_top_build_prefix$INSTALL ;; esac ac_MKDIR_P=$MKDIR_P case $MKDIR_P in [\\/$]* | ?:[\\/]* ) ;; */*) ac_MKDIR_P=$ac_top_build_prefix$MKDIR_P ;; esac _ACEOF cat >>$CONFIG_STATUS <<\_ACEOF || ac_write_fail=1 # If the template does not know about datarootdir, expand it. # FIXME: This hack should be removed a few years after 2.60. ac_datarootdir_hack=; ac_datarootdir_seen= ac_sed_dataroot=' /datarootdir/ { p q } /@datadir@/p /@docdir@/p /@infodir@/p /@localedir@/p /@mandir@/p' case `eval "sed -n \"\$ac_sed_dataroot\" $ac_file_inputs"` in *datarootdir*) ac_datarootdir_seen=yes;; *@datadir@*|*@docdir@*|*@infodir@*|*@localedir@*|*@mandir@*) { $as_echo "$as_me:${as_lineno-$LINENO}: WARNING: $ac_file_inputs seems to ignore the --datarootdir setting" >&5 $as_echo "$as_me: WARNING: $ac_file_inputs seems to ignore the --datarootdir setting" >&2;} _ACEOF cat >>$CONFIG_STATUS <<_ACEOF || ac_write_fail=1 ac_datarootdir_hack=' s&@datadir@&$datadir&g s&@docdir@&$docdir&g s&@infodir@&$infodir&g s&@localedir@&$localedir&g s&@mandir@&$mandir&g s&\\\${datarootdir}&$datarootdir&g' ;; esac _ACEOF # Neutralize VPATH when `$srcdir' = `.'. # Shell code in configure.ac might set extrasub. # FIXME: do we really want to maintain this feature? cat >>$CONFIG_STATUS <<_ACEOF || ac_write_fail=1 ac_sed_extra="$ac_vpsub $extrasub _ACEOF cat >>$CONFIG_STATUS <<\_ACEOF || ac_write_fail=1 :t /@[a-zA-Z_][a-zA-Z_0-9]*@/!b s|@configure_input@|$ac_sed_conf_input|;t t s&@top_builddir@&$ac_top_builddir_sub&;t t s&@top_build_prefix@&$ac_top_build_prefix&;t t s&@srcdir@&$ac_srcdir&;t t s&@abs_srcdir@&$ac_abs_srcdir&;t t s&@top_srcdir@&$ac_top_srcdir&;t t s&@abs_top_srcdir@&$ac_abs_top_srcdir&;t t s&@builddir@&$ac_builddir&;t t s&@abs_builddir@&$ac_abs_builddir&;t t s&@abs_top_builddir@&$ac_abs_top_builddir&;t t s&@INSTALL@&$ac_INSTALL&;t t s&@MKDIR_P@&$ac_MKDIR_P&;t t $ac_datarootdir_hack " eval sed \"\$ac_sed_extra\" "$ac_file_inputs" | $AWK -f "$ac_tmp/subs.awk" \ >$ac_tmp/out || as_fn_error $? "could not create $ac_file" "$LINENO" 5 test -z "$ac_datarootdir_hack$ac_datarootdir_seen" && { ac_out=`sed -n '/\${datarootdir}/p' "$ac_tmp/out"`; test -n "$ac_out"; } && { ac_out=`sed -n '/^[ ]*datarootdir[ ]*:*=/p' \ "$ac_tmp/out"`; test -z "$ac_out"; } && { $as_echo "$as_me:${as_lineno-$LINENO}: WARNING: $ac_file contains a reference to the variable \`datarootdir' which seems to be undefined. Please make sure it is defined" >&5 $as_echo "$as_me: WARNING: $ac_file contains a reference to the variable \`datarootdir' which seems to be undefined. Please make sure it is defined" >&2;} rm -f "$ac_tmp/stdin" case $ac_file in -) cat "$ac_tmp/out" && rm -f "$ac_tmp/out";; *) rm -f "$ac_file" && mv "$ac_tmp/out" "$ac_file";; esac \ || as_fn_error $? "could not create $ac_file" "$LINENO" 5 ;; :H) # # CONFIG_HEADER # if test x"$ac_file" != x-; then { $as_echo "/* $configure_input */" \ && eval '$AWK -f "$ac_tmp/defines.awk"' "$ac_file_inputs" } >"$ac_tmp/config.h" \ || as_fn_error $? "could not create $ac_file" "$LINENO" 5 if diff "$ac_file" "$ac_tmp/config.h" >/dev/null 2>&1; then { $as_echo "$as_me:${as_lineno-$LINENO}: $ac_file is unchanged" >&5 $as_echo "$as_me: $ac_file is unchanged" >&6;} else rm -f "$ac_file" mv "$ac_tmp/config.h" "$ac_file" \ || as_fn_error $? "could not create $ac_file" "$LINENO" 5 fi else $as_echo "/* $configure_input */" \ && eval '$AWK -f "$ac_tmp/defines.awk"' "$ac_file_inputs" \ || as_fn_error $? "could not create -" "$LINENO" 5 fi # Compute "$ac_file"'s index in $config_headers. _am_arg="$ac_file" _am_stamp_count=1 for _am_header in $config_headers :; do case $_am_header in $_am_arg | $_am_arg:* ) break ;; * ) _am_stamp_count=`expr $_am_stamp_count + 1` ;; esac done echo "timestamp for $_am_arg" >`$as_dirname -- "$_am_arg" || $as_expr X"$_am_arg" : 'X\(.*[^/]\)//*[^/][^/]*/*$' \| \ X"$_am_arg" : 'X\(//\)[^/]' \| \ X"$_am_arg" : 'X\(//\)$' \| \ X"$_am_arg" : 'X\(/\)' \| . 2>/dev/null || $as_echo X"$_am_arg" | sed '/^X\(.*[^/]\)\/\/*[^/][^/]*\/*$/{ s//\1/ q } /^X\(\/\/\)[^/].*/{ s//\1/ q } /^X\(\/\/\)$/{ s//\1/ q } /^X\(\/\).*/{ s//\1/ q } s/.*/./; q'`/stamp-h$_am_stamp_count ;; :C) { $as_echo "$as_me:${as_lineno-$LINENO}: executing $ac_file commands" >&5 $as_echo "$as_me: executing $ac_file commands" >&6;} ;; esac case $ac_file$ac_mode in "depfiles":C) test x"$AMDEP_TRUE" != x"" || { # Autoconf 2.62 quotes --file arguments for eval, but not when files # are listed without --file. Let's play safe and only enable the eval # if we detect the quoting. case $CONFIG_FILES in *\'*) eval set x "$CONFIG_FILES" ;; *) set x $CONFIG_FILES ;; esac shift for mf do # Strip MF so we end up with the name of the file. mf=`echo "$mf" | sed -e 's/:.*$//'` # Check whether this is an Automake generated Makefile or not. # We used to match only the files named `Makefile.in', but # some people rename them; so instead we look at the file content. # Grep'ing the first line is not enough: some people post-process # each Makefile.in and add a new line on top of each file to say so. # Grep'ing the whole file is not good either: AIX grep has a line # limit of 2048, but all sed's we know have understand at least 4000. if sed -n 's,^#.*generated by automake.*,X,p' "$mf" | grep X >/dev/null 2>&1; then dirpart=`$as_dirname -- "$mf" || $as_expr X"$mf" : 'X\(.*[^/]\)//*[^/][^/]*/*$' \| \ X"$mf" : 'X\(//\)[^/]' \| \ X"$mf" : 'X\(//\)$' \| \ X"$mf" : 'X\(/\)' \| . 2>/dev/null || $as_echo X"$mf" | sed '/^X\(.*[^/]\)\/\/*[^/][^/]*\/*$/{ s//\1/ q } /^X\(\/\/\)[^/].*/{ s//\1/ q } /^X\(\/\/\)$/{ s//\1/ q } /^X\(\/\).*/{ s//\1/ q } s/.*/./; q'` else continue fi # Extract the definition of DEPDIR, am__include, and am__quote # from the Makefile without running `make'. DEPDIR=`sed -n 's/^DEPDIR = //p' < "$mf"` test -z "$DEPDIR" && continue am__include=`sed -n 's/^am__include = //p' < "$mf"` test -z "am__include" && continue am__quote=`sed -n 's/^am__quote = //p' < "$mf"` # When using ansi2knr, U may be empty or an underscore; expand it U=`sed -n 's/^U = //p' < "$mf"` # Find all dependency output files, they are included files with # $(DEPDIR) in their names. We invoke sed twice because it is the # simplest approach to changing $(DEPDIR) to its actual value in the # expansion. for file in `sed -n " s/^$am__include $am__quote\(.*(DEPDIR).*\)$am__quote"'$/\1/p' <"$mf" | \ sed -e 's/\$(DEPDIR)/'"$DEPDIR"'/g' -e 's/\$U/'"$U"'/g'`; do # Make sure the directory exists. test -f "$dirpart/$file" && continue fdir=`$as_dirname -- "$file" || $as_expr X"$file" : 'X\(.*[^/]\)//*[^/][^/]*/*$' \| \ X"$file" : 'X\(//\)[^/]' \| \ X"$file" : 'X\(//\)$' \| \ X"$file" : 'X\(/\)' \| . 2>/dev/null || $as_echo X"$file" | sed '/^X\(.*[^/]\)\/\/*[^/][^/]*\/*$/{ s//\1/ q } /^X\(\/\/\)[^/].*/{ s//\1/ q } /^X\(\/\/\)$/{ s//\1/ q } /^X\(\/\).*/{ s//\1/ q } s/.*/./; q'` as_dir=$dirpart/$fdir; as_fn_mkdir_p # echo "creating $dirpart/$file" echo '# dummy' > "$dirpart/$file" done done } ;; "libtool":C) # See if we are running on zsh, and set the options which allow our # commands through without removal of \ escapes. if test -n "${ZSH_VERSION+set}" ; then setopt NO_GLOB_SUBST fi cfgfile="${ofile}T" trap "$RM \"$cfgfile\"; exit 1" 1 2 15 $RM "$cfgfile" cat <<_LT_EOF >> "$cfgfile" #! $SHELL # `$ECHO "$ofile" | sed 's%^.*/%%'` - Provide generalized library-building support services. # Generated automatically by $as_me ($PACKAGE$TIMESTAMP) $VERSION # Libtool was configured on host `(hostname || uname -n) 2>/dev/null | sed 1q`: # NOTE: Changes made to this file will be lost: look at ltmain.sh. # # Copyright (C) 1996, 1997, 1998, 1999, 2000, 2001, 2003, 2004, 2005, # 2006, 2007, 2008, 2009, 2010, 2011 Free Software # Foundation, Inc. # Written by Gordon Matzigkeit, 1996 # # This file is part of GNU Libtool. # # GNU Libtool is free software; you can redistribute it and/or # modify it under the terms of the GNU General Public License as # published by the Free Software Foundation; either version 2 of # the License, or (at your option) any later version. # # As a special exception to the GNU General Public License, # if you distribute this file as part of a program or library that # is built using GNU Libtool, you may include this file under the # same distribution terms that you use for the rest of that program. # # GNU Libtool is distributed in the hope that it will be useful, # but WITHOUT ANY WARRANTY; without even the implied warranty of # MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the # GNU General Public License for more details. # # You should have received a copy of the GNU General Public License # along with GNU Libtool; see the file COPYING. If not, a copy # can be downloaded from http://www.gnu.org/licenses/gpl.html, or # obtained by writing to the Free Software Foundation, Inc., # 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. # The names of the tagged configurations supported by this script. available_tags="" # ### BEGIN LIBTOOL CONFIG # Assembler program. AS=$lt_AS # DLL creation program. DLLTOOL=$lt_DLLTOOL # Object dumper program. OBJDUMP=$lt_OBJDUMP # Which release of libtool.m4 was used? macro_version=$macro_version macro_revision=$macro_revision # Whether or not to build shared libraries. build_libtool_libs=$enable_shared # Whether or not to build static libraries. build_old_libs=$enable_static # What type of objects to build. pic_mode=$pic_mode # Whether or not to optimize for fast installation. fast_install=$enable_fast_install # Shell to use when invoking shell scripts. SHELL=$lt_SHELL # An echo program that protects backslashes. ECHO=$lt_ECHO # The PATH separator for the build system. PATH_SEPARATOR=$lt_PATH_SEPARATOR # The host system. host_alias=$host_alias host=$host host_os=$host_os # The build system. build_alias=$build_alias build=$build build_os=$build_os # A sed program that does not truncate output. SED=$lt_SED # Sed that helps us avoid accidentally triggering echo(1) options like -n. Xsed="\$SED -e 1s/^X//" # A grep program that handles long lines. GREP=$lt_GREP # An ERE matcher. EGREP=$lt_EGREP # A literal string matcher. FGREP=$lt_FGREP # A BSD- or MS-compatible name lister. NM=$lt_NM # Whether we need soft or hard links. LN_S=$lt_LN_S # What is the maximum length of a command? max_cmd_len=$max_cmd_len # Object file suffix (normally "o"). objext=$ac_objext # Executable file suffix (normally ""). exeext=$exeext # whether the shell understands "unset". lt_unset=$lt_unset # turn spaces into newlines. SP2NL=$lt_lt_SP2NL # turn newlines into spaces. NL2SP=$lt_lt_NL2SP # convert \$build file names to \$host format. to_host_file_cmd=$lt_cv_to_host_file_cmd # convert \$build files to toolchain format. to_tool_file_cmd=$lt_cv_to_tool_file_cmd # Method to check whether dependent libraries are shared objects. deplibs_check_method=$lt_deplibs_check_method # Command to use when deplibs_check_method = "file_magic". file_magic_cmd=$lt_file_magic_cmd # How to find potential files when deplibs_check_method = "file_magic". file_magic_glob=$lt_file_magic_glob # Find potential files using nocaseglob when deplibs_check_method = "file_magic". want_nocaseglob=$lt_want_nocaseglob # Command to associate shared and link libraries. sharedlib_from_linklib_cmd=$lt_sharedlib_from_linklib_cmd # The archiver. AR=$lt_AR # Flags to create an archive. AR_FLAGS=$lt_AR_FLAGS # How to feed a file listing to the archiver. archiver_list_spec=$lt_archiver_list_spec # A symbol stripping program. STRIP=$lt_STRIP # Commands used to install an old-style archive. RANLIB=$lt_RANLIB old_postinstall_cmds=$lt_old_postinstall_cmds old_postuninstall_cmds=$lt_old_postuninstall_cmds # Whether to use a lock for old archive extraction. lock_old_archive_extraction=$lock_old_archive_extraction # A C compiler. LTCC=$lt_CC # LTCC compiler flags. LTCFLAGS=$lt_CFLAGS # Take the output of nm and produce a listing of raw symbols and C names. global_symbol_pipe=$lt_lt_cv_sys_global_symbol_pipe # Transform the output of nm in a proper C declaration. global_symbol_to_cdecl=$lt_lt_cv_sys_global_symbol_to_cdecl # Transform the output of nm in a C name address pair. global_symbol_to_c_name_address=$lt_lt_cv_sys_global_symbol_to_c_name_address # Transform the output of nm in a C name address pair when lib prefix is needed. global_symbol_to_c_name_address_lib_prefix=$lt_lt_cv_sys_global_symbol_to_c_name_address_lib_prefix # Specify filename containing input files for \$NM. nm_file_list_spec=$lt_nm_file_list_spec # The root where to search for dependent libraries,and in which our libraries should be installed. lt_sysroot=$lt_sysroot # The name of the directory that contains temporary libtool files. objdir=$objdir # Used to examine libraries when file_magic_cmd begins with "file". MAGIC_CMD=$MAGIC_CMD # Must we lock files when doing compilation? need_locks=$lt_need_locks # Manifest tool. MANIFEST_TOOL=$lt_MANIFEST_TOOL # Tool to manipulate archived DWARF debug symbol files on Mac OS X. DSYMUTIL=$lt_DSYMUTIL # Tool to change global to local symbols on Mac OS X. NMEDIT=$lt_NMEDIT # Tool to manipulate fat objects and archives on Mac OS X. LIPO=$lt_LIPO # ldd/readelf like tool for Mach-O binaries on Mac OS X. OTOOL=$lt_OTOOL # ldd/readelf like tool for 64 bit Mach-O binaries on Mac OS X 10.4. OTOOL64=$lt_OTOOL64 # Old archive suffix (normally "a"). libext=$libext # Shared library suffix (normally ".so"). shrext_cmds=$lt_shrext_cmds # The commands to extract the exported symbol list from a shared archive. extract_expsyms_cmds=$lt_extract_expsyms_cmds # Variables whose values should be saved in libtool wrapper scripts and # restored at link time. variables_saved_for_relink=$lt_variables_saved_for_relink # Do we need the "lib" prefix for modules? need_lib_prefix=$need_lib_prefix # Do we need a version for libraries? need_version=$need_version # Library versioning type. version_type=$version_type # Shared library runtime path variable. runpath_var=$runpath_var # Shared library path variable. shlibpath_var=$shlibpath_var # Is shlibpath searched before the hard-coded library search path? shlibpath_overrides_runpath=$shlibpath_overrides_runpath # Format of library name prefix. libname_spec=$lt_libname_spec # List of archive names. First name is the real one, the rest are links. # The last name is the one that the linker finds with -lNAME library_names_spec=$lt_library_names_spec # The coded name of the library, if different from the real name. soname_spec=$lt_soname_spec # Permission mode override for installation of shared libraries. install_override_mode=$lt_install_override_mode # Command to use after installation of a shared archive. postinstall_cmds=$lt_postinstall_cmds # Command to use after uninstallation of a shared archive. postuninstall_cmds=$lt_postuninstall_cmds # Commands used to finish a libtool library installation in a directory. finish_cmds=$lt_finish_cmds # As "finish_cmds", except a single script fragment to be evaled but # not shown. finish_eval=$lt_finish_eval # Whether we should hardcode library paths into libraries. hardcode_into_libs=$hardcode_into_libs # Compile-time system search path for libraries. sys_lib_search_path_spec=$lt_sys_lib_search_path_spec # Run-time system search path for libraries. sys_lib_dlsearch_path_spec=$lt_sys_lib_dlsearch_path_spec # Whether dlopen is supported. dlopen_support=$enable_dlopen # Whether dlopen of programs is supported. dlopen_self=$enable_dlopen_self # Whether dlopen of statically linked programs is supported. dlopen_self_static=$enable_dlopen_self_static # Commands to strip libraries. old_striplib=$lt_old_striplib striplib=$lt_striplib # The linker used to build libraries. LD=$lt_LD # How to create reloadable object files. reload_flag=$lt_reload_flag reload_cmds=$lt_reload_cmds # Commands used to build an old-style archive. old_archive_cmds=$lt_old_archive_cmds # A language specific compiler. CC=$lt_compiler # Is the compiler the GNU compiler? with_gcc=$GCC # Compiler flag to turn off builtin functions. no_builtin_flag=$lt_lt_prog_compiler_no_builtin_flag # Additional compiler flags for building library objects. pic_flag=$lt_lt_prog_compiler_pic # How to pass a linker flag through the compiler. wl=$lt_lt_prog_compiler_wl # Compiler flag to prevent dynamic linking. link_static_flag=$lt_lt_prog_compiler_static # Does compiler simultaneously support -c and -o options? compiler_c_o=$lt_lt_cv_prog_compiler_c_o # Whether or not to add -lc for building shared libraries. build_libtool_need_lc=$archive_cmds_need_lc # Whether or not to disallow shared libs when runtime libs are static. allow_libtool_libs_with_static_runtimes=$enable_shared_with_static_runtimes # Compiler flag to allow reflexive dlopens. export_dynamic_flag_spec=$lt_export_dynamic_flag_spec # Compiler flag to generate shared objects directly from archives. whole_archive_flag_spec=$lt_whole_archive_flag_spec # Whether the compiler copes with passing no objects directly. compiler_needs_object=$lt_compiler_needs_object # Create an old-style archive from a shared archive. old_archive_from_new_cmds=$lt_old_archive_from_new_cmds # Create a temporary old-style archive to link instead of a shared archive. old_archive_from_expsyms_cmds=$lt_old_archive_from_expsyms_cmds # Commands used to build a shared archive. archive_cmds=$lt_archive_cmds archive_expsym_cmds=$lt_archive_expsym_cmds # Commands used to build a loadable module if different from building # a shared archive. module_cmds=$lt_module_cmds module_expsym_cmds=$lt_module_expsym_cmds # Whether we are building with GNU ld or not. with_gnu_ld=$lt_with_gnu_ld # Flag that allows shared libraries with undefined symbols to be built. allow_undefined_flag=$lt_allow_undefined_flag # Flag that enforces no undefined symbols. no_undefined_flag=$lt_no_undefined_flag # Flag to hardcode \$libdir into a binary during linking. # This must work even if \$libdir does not exist hardcode_libdir_flag_spec=$lt_hardcode_libdir_flag_spec # Whether we need a single "-rpath" flag with a separated argument. hardcode_libdir_separator=$lt_hardcode_libdir_separator # Set to "yes" if using DIR/libNAME\${shared_ext} during linking hardcodes # DIR into the resulting binary. hardcode_direct=$hardcode_direct # Set to "yes" if using DIR/libNAME\${shared_ext} during linking hardcodes # DIR into the resulting binary and the resulting library dependency is # "absolute",i.e impossible to change by setting \${shlibpath_var} if the # library is relocated. hardcode_direct_absolute=$hardcode_direct_absolute # Set to "yes" if using the -LDIR flag during linking hardcodes DIR # into the resulting binary. hardcode_minus_L=$hardcode_minus_L # Set to "yes" if using SHLIBPATH_VAR=DIR during linking hardcodes DIR # into the resulting binary. hardcode_shlibpath_var=$hardcode_shlibpath_var # Set to "yes" if building a shared library automatically hardcodes DIR # into the library and all subsequent libraries and executables linked # against it. hardcode_automatic=$hardcode_automatic # Set to yes if linker adds runtime paths of dependent libraries # to runtime path list. inherit_rpath=$inherit_rpath # Whether libtool must link a program against all its dependency libraries. link_all_deplibs=$link_all_deplibs # Set to "yes" if exported symbols are required. always_export_symbols=$always_export_symbols # The commands to list exported symbols. export_symbols_cmds=$lt_export_symbols_cmds # Symbols that should not be listed in the preloaded symbols. exclude_expsyms=$lt_exclude_expsyms # Symbols that must always be exported. include_expsyms=$lt_include_expsyms # Commands necessary for linking programs (against libraries) with templates. prelink_cmds=$lt_prelink_cmds # Commands necessary for finishing linking programs. postlink_cmds=$lt_postlink_cmds # Specify filename containing input files. file_list_spec=$lt_file_list_spec # How to hardcode a shared library path into an executable. hardcode_action=$hardcode_action # ### END LIBTOOL CONFIG _LT_EOF case $host_os in aix3*) cat <<\_LT_EOF >> "$cfgfile" # AIX sometimes has problems with the GCC collect2 program. For some # reason, if we set the COLLECT_NAMES environment variable, the problems # vanish in a puff of smoke. if test "X${COLLECT_NAMES+set}" != Xset; then COLLECT_NAMES= export COLLECT_NAMES fi _LT_EOF ;; esac ltmain="$ac_aux_dir/ltmain.sh" # We use sed instead of cat because bash on DJGPP gets confused if # if finds mixed CR/LF and LF-only lines. Since sed operates in # text mode, it properly converts lines to CR/LF. This bash problem # is reportedly fixed, but why not run on old versions too? sed '$q' "$ltmain" >> "$cfgfile" \ || (rm -f "$cfgfile"; exit 1) if test x"$xsi_shell" = xyes; then sed -e '/^func_dirname ()$/,/^} # func_dirname /c\ func_dirname ()\ {\ \ case ${1} in\ \ */*) func_dirname_result="${1%/*}${2}" ;;\ \ * ) func_dirname_result="${3}" ;;\ \ esac\ } # Extended-shell func_dirname implementation' "$cfgfile" > $cfgfile.tmp \ && mv -f "$cfgfile.tmp" "$cfgfile" \ || (rm -f "$cfgfile" && cp "$cfgfile.tmp" "$cfgfile" && rm -f "$cfgfile.tmp") test 0 -eq $? || _lt_function_replace_fail=: sed -e '/^func_basename ()$/,/^} # func_basename /c\ func_basename ()\ {\ \ func_basename_result="${1##*/}"\ } # Extended-shell func_basename implementation' "$cfgfile" > $cfgfile.tmp \ && mv -f "$cfgfile.tmp" "$cfgfile" \ || (rm -f "$cfgfile" && cp "$cfgfile.tmp" "$cfgfile" && rm -f "$cfgfile.tmp") test 0 -eq $? || _lt_function_replace_fail=: sed -e '/^func_dirname_and_basename ()$/,/^} # func_dirname_and_basename /c\ func_dirname_and_basename ()\ {\ \ case ${1} in\ \ */*) func_dirname_result="${1%/*}${2}" ;;\ \ * ) func_dirname_result="${3}" ;;\ \ esac\ \ func_basename_result="${1##*/}"\ } # Extended-shell func_dirname_and_basename implementation' "$cfgfile" > $cfgfile.tmp \ && mv -f "$cfgfile.tmp" "$cfgfile" \ || (rm -f "$cfgfile" && cp "$cfgfile.tmp" "$cfgfile" && rm -f "$cfgfile.tmp") test 0 -eq $? || _lt_function_replace_fail=: sed -e '/^func_stripname ()$/,/^} # func_stripname /c\ func_stripname ()\ {\ \ # pdksh 5.2.14 does not do ${X%$Y} correctly if both X and Y are\ \ # positional parameters, so assign one to ordinary parameter first.\ \ func_stripname_result=${3}\ \ func_stripname_result=${func_stripname_result#"${1}"}\ \ func_stripname_result=${func_stripname_result%"${2}"}\ } # Extended-shell func_stripname implementation' "$cfgfile" > $cfgfile.tmp \ && mv -f "$cfgfile.tmp" "$cfgfile" \ || (rm -f "$cfgfile" && cp "$cfgfile.tmp" "$cfgfile" && rm -f "$cfgfile.tmp") test 0 -eq $? || _lt_function_replace_fail=: sed -e '/^func_split_long_opt ()$/,/^} # func_split_long_opt /c\ func_split_long_opt ()\ {\ \ func_split_long_opt_name=${1%%=*}\ \ func_split_long_opt_arg=${1#*=}\ } # Extended-shell func_split_long_opt implementation' "$cfgfile" > $cfgfile.tmp \ && mv -f "$cfgfile.tmp" "$cfgfile" \ || (rm -f "$cfgfile" && cp "$cfgfile.tmp" "$cfgfile" && rm -f "$cfgfile.tmp") test 0 -eq $? || _lt_function_replace_fail=: sed -e '/^func_split_short_opt ()$/,/^} # func_split_short_opt /c\ func_split_short_opt ()\ {\ \ func_split_short_opt_arg=${1#??}\ \ func_split_short_opt_name=${1%"$func_split_short_opt_arg"}\ } # Extended-shell func_split_short_opt implementation' "$cfgfile" > $cfgfile.tmp \ && mv -f "$cfgfile.tmp" "$cfgfile" \ || (rm -f "$cfgfile" && cp "$cfgfile.tmp" "$cfgfile" && rm -f "$cfgfile.tmp") test 0 -eq $? || _lt_function_replace_fail=: sed -e '/^func_lo2o ()$/,/^} # func_lo2o /c\ func_lo2o ()\ {\ \ case ${1} in\ \ *.lo) func_lo2o_result=${1%.lo}.${objext} ;;\ \ *) func_lo2o_result=${1} ;;\ \ esac\ } # Extended-shell func_lo2o implementation' "$cfgfile" > $cfgfile.tmp \ && mv -f "$cfgfile.tmp" "$cfgfile" \ || (rm -f "$cfgfile" && cp "$cfgfile.tmp" "$cfgfile" && rm -f "$cfgfile.tmp") test 0 -eq $? || _lt_function_replace_fail=: sed -e '/^func_xform ()$/,/^} # func_xform /c\ func_xform ()\ {\ func_xform_result=${1%.*}.lo\ } # Extended-shell func_xform implementation' "$cfgfile" > $cfgfile.tmp \ && mv -f "$cfgfile.tmp" "$cfgfile" \ || (rm -f "$cfgfile" && cp "$cfgfile.tmp" "$cfgfile" && rm -f "$cfgfile.tmp") test 0 -eq $? || _lt_function_replace_fail=: sed -e '/^func_arith ()$/,/^} # func_arith /c\ func_arith ()\ {\ func_arith_result=$(( $* ))\ } # Extended-shell func_arith implementation' "$cfgfile" > $cfgfile.tmp \ && mv -f "$cfgfile.tmp" "$cfgfile" \ || (rm -f "$cfgfile" && cp "$cfgfile.tmp" "$cfgfile" && rm -f "$cfgfile.tmp") test 0 -eq $? || _lt_function_replace_fail=: sed -e '/^func_len ()$/,/^} # func_len /c\ func_len ()\ {\ func_len_result=${#1}\ } # Extended-shell func_len implementation' "$cfgfile" > $cfgfile.tmp \ && mv -f "$cfgfile.tmp" "$cfgfile" \ || (rm -f "$cfgfile" && cp "$cfgfile.tmp" "$cfgfile" && rm -f "$cfgfile.tmp") test 0 -eq $? || _lt_function_replace_fail=: fi if test x"$lt_shell_append" = xyes; then sed -e '/^func_append ()$/,/^} # func_append /c\ func_append ()\ {\ eval "${1}+=\\${2}"\ } # Extended-shell func_append implementation' "$cfgfile" > $cfgfile.tmp \ && mv -f "$cfgfile.tmp" "$cfgfile" \ || (rm -f "$cfgfile" && cp "$cfgfile.tmp" "$cfgfile" && rm -f "$cfgfile.tmp") test 0 -eq $? || _lt_function_replace_fail=: sed -e '/^func_append_quoted ()$/,/^} # func_append_quoted /c\ func_append_quoted ()\ {\ \ func_quote_for_eval "${2}"\ \ eval "${1}+=\\\\ \\$func_quote_for_eval_result"\ } # Extended-shell func_append_quoted implementation' "$cfgfile" > $cfgfile.tmp \ && mv -f "$cfgfile.tmp" "$cfgfile" \ || (rm -f "$cfgfile" && cp "$cfgfile.tmp" "$cfgfile" && rm -f "$cfgfile.tmp") test 0 -eq $? || _lt_function_replace_fail=: # Save a `func_append' function call where possible by direct use of '+=' sed -e 's%func_append \([a-zA-Z_]\{1,\}\) "%\1+="%g' $cfgfile > $cfgfile.tmp \ && mv -f "$cfgfile.tmp" "$cfgfile" \ || (rm -f "$cfgfile" && cp "$cfgfile.tmp" "$cfgfile" && rm -f "$cfgfile.tmp") test 0 -eq $? || _lt_function_replace_fail=: else # Save a `func_append' function call even when '+=' is not available sed -e 's%func_append \([a-zA-Z_]\{1,\}\) "%\1="$\1%g' $cfgfile > $cfgfile.tmp \ && mv -f "$cfgfile.tmp" "$cfgfile" \ || (rm -f "$cfgfile" && cp "$cfgfile.tmp" "$cfgfile" && rm -f "$cfgfile.tmp") test 0 -eq $? || _lt_function_replace_fail=: fi if test x"$_lt_function_replace_fail" = x":"; then { $as_echo "$as_me:${as_lineno-$LINENO}: WARNING: Unable to substitute extended shell functions in $ofile" >&5 $as_echo "$as_me: WARNING: Unable to substitute extended shell functions in $ofile" >&2;} fi mv -f "$cfgfile" "$ofile" || (rm -f "$ofile" && cp "$cfgfile" "$ofile" && rm -f "$cfgfile") chmod +x "$ofile" ;; "snprintfv/compat.h":C) outfile=snprintfv/compat.h tmpfile=${outfile}T dirname="sed s,^.*/,,g" echo creating $outfile cat > $tmpfile << _EOF_ /* -*- Mode: C -*- * -------------------------------------------------------------------- * DO NOT EDIT THIS FILE! It has been automatically generated * from: configure.in and `echo $outfile|$dirname`.in * on host: `(hostname || uname -n) 2>/dev/null | sed 1q` * -------------------------------------------------------------------- * `echo $outfile|$dirname` --- portability code generated for snprintfv by configure.in */ #ifndef SNPRINTFV_COMPAT_H #define SNPRINTFV_COMPAT_H 1 #ifdef __cplusplus extern "C" { #if 0 /* This brace is so that emacs can still indent properly: */ } #endif #endif /* __cplusplus */ #include #include #include #include #include _EOF_ # Add the code to include these headers only if autoconf has # shown them to be present. if test x$ac_cv_header_sys_types_h = xyes; then echo '#include ' >> $tmpfile fi if test x$ac_cv_header_string_h = xyes; then echo '#include ' >> $tmpfile elif test x$ac_cv_header_strings_h = xyes; then echo '#include ' >> $tmpfile fi if test x$ac_cv_header_inttypes_h = xyes; then echo '#include ' >> $tmpfile elif test x$ac_cv_header_stdint_h = xyes; then echo '#include ' >> $tmpfile fi if test x$ac_cv_header_wchar_h = xyes; then echo '#include ' >> $tmpfile fi if test x$snv_cv_static_inline = xyes; then echo '#define SNV_INLINE static inline' >> $tmpfile else echo '#define SNV_INLINE static' >> $tmpfile fi if test x$ac_cv_type_wchar_t = xno; then echo 'typedef unsigned int snv_wchar_t;' >> $tmpfile else echo 'typedef wchar_t snv_wchar_t;' >> $tmpfile fi if test x$ac_cv_type_wint_t = xno || test $ac_cv_sizeof_wint_t -lt $ac_cv_sizeof_int; then echo 'typedef unsigned int snv_wint_t;' >> $tmpfile else echo 'typedef wint_t snv_wint_t;' >> $tmpfile fi if test x$ac_cv_c_long_double = xno; then echo 'typedef double snv_long_double;' >> $tmpfile else echo 'typedef long double snv_long_double;' >> $tmpfile fi if test x$ac_cv_type_intmax_t = xno; then cat >> $tmpfile << '_EOF_' #if __GNUC__ >= 2 typedef long long intmax_t; typedef unsigned long long uintmax_t; #else typedef long intmax_t; typedef unsigned long uintmax_t; #endif _EOF_ fi if test x$ac_cv_type_size_t != xyes; then cat >> $tmpfile << \_EOF_ typedef unsigned long size_t; _EOF_ fi if test $ac_cv_func_fputc_unlocked = no || test $ac_cv_func_flockfile = no; then cat >> $tmpfile << \_EOF_ #define SNV_FPUTC_UNLOCKED fputc #define SNV_PUTC_UNLOCKED putc #define SNV_WITH_LOCKED_FP(fp, tmp_var) \ for (tmp_var = 1; tmp_var--; ) _EOF_ else cat >> $tmpfile << \_EOF_ #define SNV_FPUTC_UNLOCKED fputc_unlocked #define SNV_PUTC_UNLOCKED putc_unlocked #define SNV_WITH_LOCKED_FP(fp, tmp_var) \ for (flockfile (fp), tmp_var = 1; \ tmp_var--; funlockfile (fp)) _EOF_ fi cat >> $tmpfile << \_EOF_ /* Define macros for storing integers inside pointers. * Be aware that it is only safe to use these macros to store `int' * values in `char*' (or `void*') words, and then extract them later. * Although it will work the other way round on many common * architectures, it is not portable to assume a `char*' can be * stored in an `int' and extracted later without loss of the msb's */ #define SNV_POINTER_TO_INT(p) ((long)(p)) #define SNV_POINTER_TO_UINT(p) ((unsigned long)(p)) #define SNV_INT_TO_POINTER(i) ((snv_pointer)(long)(i)) #define SNV_UINT_TO_POINTER(u) ((snv_pointer)(unsigned long)(u)) _EOF_ # The ugly but portable cpp stuff comes from here infile=$srcdir/snprintfv/`echo $outfile | sed 's,.*/,,g;s,\..*$,,g'`.in sed '/^##.*$/d' $infile >> $tmpfile cat >> $tmpfile << \_EOF_ #ifdef __cplusplus #if 0 /* This brace is so that emacs can still indent properly: */ { #endif } #endif /* __cplusplus */ #endif /* COMPAT_H */ _EOF_ if cmp -s $tmpfile $outfile; then echo $outfile is unchanged rm -f $tmpfile else mv $tmpfile $outfile fi ;; esac done # for ac_tag as_fn_exit 0 _ACEOF ac_clean_files=$ac_clean_files_save test $ac_write_fail = 0 || as_fn_error $? "write failure creating $CONFIG_STATUS" "$LINENO" 5 # configure is writing to config.log, and then calls config.status. # config.status does its own redirection, appending to config.log. # Unfortunately, on DOS this fails, as config.log is still kept open # by configure, so config.status won't be able to write to it; its # output is simply discarded. So we exec the FD to /dev/null, # effectively closing config.log, so it can be properly (re)opened and # appended to by config.status. When coming back to configure, we # need to make the FD available again. if test "$no_create" != yes; then ac_cs_success=: ac_config_status_args= test "$silent" = yes && ac_config_status_args="$ac_config_status_args --quiet" exec 5>/dev/null $SHELL $CONFIG_STATUS $ac_config_status_args || ac_cs_success=false exec 5>>config.log # Use ||, not &&, to avoid exiting from the if with $? = 1, which # would make configure fail if this is the last instruction. $ac_cs_success || as_fn_exit 1 fi if test -n "$ac_unrecognized_opts" && test "$enable_option_checking" != no; then { $as_echo "$as_me:${as_lineno-$LINENO}: WARNING: unrecognized options: $ac_unrecognized_opts" >&5 $as_echo "$as_me: WARNING: unrecognized options: $ac_unrecognized_opts" >&2;} fi smalltalk-3.2.5/snprintfv/THANKS0000644000175000017500000000074212123404352013371 00000000000000libsnprintfv would not be what it is without the invaluable help of these people: Everybody who was kind enough to spend time testing libsnprintfv, use it in their packages and report bugs. The following people made especially gracious contributions of their time and energy in helping to track down bugs, port to new systems, and generally assist in the maintainership process: Bruce Korb Kaveh R. Ghazi Robert Lipe smalltalk-3.2.5/snprintfv/config.h.in0000644000175000017500000000616612130455546014520 00000000000000/* config.h.in. Generated from configure.ac by autoheader. */ /* Define to 1 if you have the `copysign' function. */ #undef HAVE_COPYSIGN /* Define to 1 if you have the `copysignl' function. */ #undef HAVE_COPYSIGNL /* Define to 1 if you have the header file. */ #undef HAVE_DLFCN_H /* Define to 1 if you have the `flockfile' function. */ #undef HAVE_FLOCKFILE /* Define to 1 if you have the `fputc_unlocked' function. */ #undef HAVE_FPUTC_UNLOCKED /* Define to 1 if you have the header file. */ #undef HAVE_INTTYPES_H /* Define to 1 if you have the `isinf' function. */ #undef HAVE_ISINF /* Define to 1 if you have the `isinfl' function. */ #undef HAVE_ISINFL /* Define to 1 if you have the `isnan' function. */ #undef HAVE_ISNAN /* Define to 1 if you have the `isnanl' function. */ #undef HAVE_ISNANL /* Define to 1 if you have the `m' library (-lm). */ #undef HAVE_LIBM /* Define to 1 if the type `long double' works and has more range or precision than `double'. */ #undef HAVE_LONG_DOUBLE /* Define to 1 if the type `long double' works and has more range or precision than `double'. */ #undef HAVE_LONG_DOUBLE_WIDER /* Define to 1 if you have the header file. */ #undef HAVE_MEMORY_H /* Define to 1 if you have the `modfl' function. */ #undef HAVE_MODFL /* Define to 1 if you have the header file. */ #undef HAVE_STDINT_H /* Define to 1 if you have the header file. */ #undef HAVE_STDLIB_H /* Define to 1 if you have the header file. */ #undef HAVE_STRINGS_H /* Define to 1 if you have the header file. */ #undef HAVE_STRING_H /* Define to 1 if you have the header file. */ #undef HAVE_SYS_STAT_H /* Define to 1 if you have the header file. */ #undef HAVE_SYS_TYPES_H /* Define to 1 if you have the header file. */ #undef HAVE_UNISTD_H /* Define to the sub-directory in which libtool stores uninstalled libraries. */ #undef LT_OBJDIR /* Name of package */ #undef PACKAGE /* Define to the address where bug reports for this package should be sent. */ #undef PACKAGE_BUGREPORT /* Define to the full name of this package. */ #undef PACKAGE_NAME /* Define to the full name and version of this package. */ #undef PACKAGE_STRING /* Define to the one symbol short name of this package. */ #undef PACKAGE_TARNAME /* Define to the home page for this package. */ #undef PACKAGE_URL /* Define to the version of this package. */ #undef PACKAGE_VERSION /* The size of `int', as computed by sizeof. */ #undef SIZEOF_INT /* The size of `wint_t', as computed by sizeof. */ #undef SIZEOF_WINT_T /* Define to 1 if you have the ANSI C header files. */ #undef STDC_HEADERS /* Version number of package */ #undef VERSION /* Define if using the dmalloc debugging malloc package */ #undef WITH_DMALLOC /* Define to empty if `const' does not conform to ANSI C. */ #undef const /* Define to `__inline__' or `__inline' if that's what the C compiler calls it, or to nothing if 'inline' is not supported under any name. */ #ifndef __cplusplus #undef inline #endif /* Define to `unsigned int' if does not define. */ #undef size_t smalltalk-3.2.5/snprintfv/genproto0000755000175000017500000000565212123404352014246 00000000000000#! /bin/sh # -*- Mode: Shell-script -*- # genproto.sh --- extract exported functions from sources # Copyright (C) 1999 Gary V. Vaughan # Originally by Gary V. Vaughan , 1998 # This file is part of Snprintfv. # # Snprintfv is free software; you can redistribute it and/or # modify it under the terms of the GNU General Public License as # published by the Free Software Foundation; either version 2 of the # License, or (at your option) any later version. # # Snprintfv is distributed in the hope that it will be useful, # but WITHOUT ANY WARRANTY; without even the implied warranty of # MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU # General Public License for more details. # # You should have received a copy of the GNU General Public License # along with this program; see the file COPYING. If not, write to # the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, # Boston, MA 02110-1301, USA. # # As a special exception to the GNU General Public License, if you # distribute this file as part of a program that also links with and # uses the libopts library from AutoGen, you may include it under # the same distribution terms used by the libopts library. # # Copyright (C) 1999 Gary V. Vaughan # As a special exception to the GNU General Public License, if you # distribute this file as part of a program that also links with and # uses the libopts library from AutoGen, you may include it under # the same distribution terms used by the libopts library. # Commentary: # # USAGE: genproto [debug] source.h-in > source.h # # This program scans a C source file for special comments preceding # K&R function declarations, and generates commented function # declarations suitable for use in a header file. # # See the accompanying README for details of how to format function headers # for extraction by this script. # Code: debug= #debug="-v debug=1" if test "X$1" = Xdebug; then debug="-v debug=1" shift else # cleanup temporary files on exit, hangup, interrupt, quit or terminate trap 'rm -f genproto.*.$$' 0 1 2 3 15 fi if test $# -lt 2; then echo "USAGE: genproto source.h.in > source.h" >&2 exit 1 fi case $2 in */*) file=$2 ;; *) file=./$2 ;; esac dir=`echo $file | sed 's,/[^/]*$,,'` mode=`echo $file | sed 's,^.*/,,g;s,\.in$,.h,'` format=${FORMAT-GNUC_PRINTF} global=${GLOBAL-GLOBAL_DATA} scope=${SCOPE-SCOPE} filter="${AWK-awk} $debug -v mode=$mode -v format=$format -v global=$global -v scope=$scope -f $1" # Read in the source file expanding @protos foo.c lines using the # gendoc.awk script # ${AWK-awk} ' NR == 1 { printf "#line 1 \"%s\"\n", FILENAME do { if (tolower($1) != "@protos") { print; continue; } source = "'"$dir"'/" $2; while ((getline < source) > 0) { print | "'"$filter"'"; } close("'"$filter"'"); printf "#line %d \"%s\"\n", NR + 1, FILENAME } while (getline > 0) }' $file exit 0 # genproto.sh ends here smalltalk-3.2.5/snprintfv/INSTALL0000644000175000017500000003660012130455406013515 00000000000000Installation Instructions ************************* Copyright (C) 1994-1996, 1999-2002, 2004-2011 Free Software Foundation, Inc. Copying and distribution of this file, with or without modification, are permitted in any medium without royalty provided the copyright notice and this notice are preserved. This file is offered as-is, without warranty of any kind. Basic Installation ================== Briefly, the shell commands `./configure; make; make install' should configure, build, and install this package. The following more-detailed instructions are generic; see the `README' file for instructions specific to this package. Some packages provide this `INSTALL' file but do not implement all of the features documented below. The lack of an optional feature in a given package is not necessarily a bug. More recommendations for GNU packages can be found in *note Makefile Conventions: (standards)Makefile Conventions. The `configure' shell script attempts to guess correct values for various system-dependent variables used during compilation. It uses those values to create a `Makefile' in each directory of the package. It may also create one or more `.h' files containing system-dependent definitions. Finally, it creates a shell script `config.status' that you can run in the future to recreate the current configuration, and a file `config.log' containing compiler output (useful mainly for debugging `configure'). It can also use an optional file (typically called `config.cache' and enabled with `--cache-file=config.cache' or simply `-C') that saves the results of its tests to speed up reconfiguring. Caching is disabled by default to prevent problems with accidental use of stale cache files. If you need to do unusual things to compile the package, please try to figure out how `configure' could check whether to do them, and mail diffs or instructions to the address given in the `README' so they can be considered for the next release. If you are using the cache, and at some point `config.cache' contains results you don't want to keep, you may remove or edit it. The file `configure.ac' (or `configure.in') is used to create `configure' by a program called `autoconf'. You need `configure.ac' if you want to change it or regenerate `configure' using a newer version of `autoconf'. The simplest way to compile this package is: 1. `cd' to the directory containing the package's source code and type `./configure' to configure the package for your system. Running `configure' might take a while. While running, it prints some messages telling which features it is checking for. 2. Type `make' to compile the package. 3. Optionally, type `make check' to run any self-tests that come with the package, generally using the just-built uninstalled binaries. 4. Type `make install' to install the programs and any data files and documentation. When installing into a prefix owned by root, it is recommended that the package be configured and built as a regular user, and only the `make install' phase executed with root privileges. 5. Optionally, type `make installcheck' to repeat any self-tests, but this time using the binaries in their final installed location. This target does not install anything. Running this target as a regular user, particularly if the prior `make install' required root privileges, verifies that the installation completed correctly. 6. You can remove the program binaries and object files from the source code directory by typing `make clean'. To also remove the files that `configure' created (so you can compile the package for a different kind of computer), type `make distclean'. There is also a `make maintainer-clean' target, but that is intended mainly for the package's developers. If you use it, you may have to get all sorts of other programs in order to regenerate files that came with the distribution. 7. Often, you can also type `make uninstall' to remove the installed files again. In practice, not all packages have tested that uninstallation works correctly, even though it is required by the GNU Coding Standards. 8. Some packages, particularly those that use Automake, provide `make distcheck', which can by used by developers to test that all other targets like `make install' and `make uninstall' work correctly. This target is generally not run by end users. Compilers and Options ===================== Some systems require unusual options for compilation or linking that the `configure' script does not know about. Run `./configure --help' for details on some of the pertinent environment variables. You can give `configure' initial values for configuration parameters by setting variables in the command line or in the environment. Here is an example: ./configure CC=c99 CFLAGS=-g LIBS=-lposix *Note Defining Variables::, for more details. Compiling For Multiple Architectures ==================================== You can compile the package for more than one kind of computer at the same time, by placing the object files for each architecture in their own directory. To do this, you can use GNU `make'. `cd' to the directory where you want the object files and executables to go and run the `configure' script. `configure' automatically checks for the source code in the directory that `configure' is in and in `..'. This is known as a "VPATH" build. With a non-GNU `make', it is safer to compile the package for one architecture at a time in the source code directory. After you have installed the package for one architecture, use `make distclean' before reconfiguring for another architecture. On MacOS X 10.5 and later systems, you can create libraries and executables that work on multiple system types--known as "fat" or "universal" binaries--by specifying multiple `-arch' options to the compiler but only a single `-arch' option to the preprocessor. Like this: ./configure CC="gcc -arch i386 -arch x86_64 -arch ppc -arch ppc64" \ CXX="g++ -arch i386 -arch x86_64 -arch ppc -arch ppc64" \ CPP="gcc -E" CXXCPP="g++ -E" This is not guaranteed to produce working output in all cases, you may have to build one architecture at a time and combine the results using the `lipo' tool if you have problems. Installation Names ================== By default, `make install' installs the package's commands under `/usr/local/bin', include files under `/usr/local/include', etc. You can specify an installation prefix other than `/usr/local' by giving `configure' the option `--prefix=PREFIX', where PREFIX must be an absolute file name. You can specify separate installation prefixes for architecture-specific files and architecture-independent files. If you pass the option `--exec-prefix=PREFIX' to `configure', the package uses PREFIX as the prefix for installing programs and libraries. Documentation and other data files still use the regular prefix. In addition, if you use an unusual directory layout you can give options like `--bindir=DIR' to specify different values for particular kinds of files. Run `configure --help' for a list of the directories you can set and what kinds of files go in them. In general, the default for these options is expressed in terms of `${prefix}', so that specifying just `--prefix' will affect all of the other directory specifications that were not explicitly provided. The most portable way to affect installation locations is to pass the correct locations to `configure'; however, many packages provide one or both of the following shortcuts of passing variable assignments to the `make install' command line to change installation locations without having to reconfigure or recompile. The first method involves providing an override variable for each affected directory. For example, `make install prefix=/alternate/directory' will choose an alternate location for all directory configuration variables that were expressed in terms of `${prefix}'. Any directories that were specified during `configure', but not in terms of `${prefix}', must each be overridden at install time for the entire installation to be relocated. The approach of makefile variable overrides for each directory variable is required by the GNU Coding Standards, and ideally causes no recompilation. However, some platforms have known limitations with the semantics of shared libraries that end up requiring recompilation when using this method, particularly noticeable in packages that use GNU Libtool. The second method involves providing the `DESTDIR' variable. For example, `make install DESTDIR=/alternate/directory' will prepend `/alternate/directory' before all installation names. The approach of `DESTDIR' overrides is not required by the GNU Coding Standards, and does not work on platforms that have drive letters. On the other hand, it does better at avoiding recompilation issues, and works well even when some directory options were not specified in terms of `${prefix}' at `configure' time. Optional Features ================= If the package supports it, you can cause programs to be installed with an extra prefix or suffix on their names by giving `configure' the option `--program-prefix=PREFIX' or `--program-suffix=SUFFIX'. Some packages pay attention to `--enable-FEATURE' options to `configure', where FEATURE indicates an optional part of the package. They may also pay attention to `--with-PACKAGE' options, where PACKAGE is something like `gnu-as' or `x' (for the X Window System). The `README' should mention any `--enable-' and `--with-' options that the package recognizes. For packages that use the X Window System, `configure' can usually find the X include and library files automatically, but if it doesn't, you can use the `configure' options `--x-includes=DIR' and `--x-libraries=DIR' to specify their locations. Some packages offer the ability to configure how verbose the execution of `make' will be. For these packages, running `./configure --enable-silent-rules' sets the default to minimal output, which can be overridden with `make V=1'; while running `./configure --disable-silent-rules' sets the default to verbose, which can be overridden with `make V=0'. Particular systems ================== On HP-UX, the default C compiler is not ANSI C compatible. If GNU CC is not installed, it is recommended to use the following options in order to use an ANSI C compiler: ./configure CC="cc -Ae -D_XOPEN_SOURCE=500" and if that doesn't work, install pre-built binaries of GCC for HP-UX. HP-UX `make' updates targets which have the same time stamps as their prerequisites, which makes it generally unusable when shipped generated files such as `configure' are involved. Use GNU `make' instead. On OSF/1 a.k.a. Tru64, some versions of the default C compiler cannot parse its `' header file. The option `-nodtk' can be used as a workaround. If GNU CC is not installed, it is therefore recommended to try ./configure CC="cc" and if that doesn't work, try ./configure CC="cc -nodtk" On Solaris, don't put `/usr/ucb' early in your `PATH'. This directory contains several dysfunctional programs; working variants of these programs are available in `/usr/bin'. So, if you need `/usr/ucb' in your `PATH', put it _after_ `/usr/bin'. On Haiku, software installed for all users goes in `/boot/common', not `/usr/local'. It is recommended to use the following options: ./configure --prefix=/boot/common Specifying the System Type ========================== There may be some features `configure' cannot figure out automatically, but needs to determine by the type of machine the package will run on. Usually, assuming the package is built to be run on the _same_ architectures, `configure' can figure that out, but if it prints a message saying it cannot guess the machine type, give it the `--build=TYPE' option. TYPE can either be a short name for the system type, such as `sun4', or a canonical name which has the form: CPU-COMPANY-SYSTEM where SYSTEM can have one of these forms: OS KERNEL-OS See the file `config.sub' for the possible values of each field. If `config.sub' isn't included in this package, then this package doesn't need to know the machine type. If you are _building_ compiler tools for cross-compiling, you should use the option `--target=TYPE' to select the type of system they will produce code for. If you want to _use_ a cross compiler, that generates code for a platform different from the build platform, you should specify the "host" platform (i.e., that on which the generated programs will eventually be run) with `--host=TYPE'. Sharing Defaults ================ If you want to set default values for `configure' scripts to share, you can create a site shell script called `config.site' that gives default values for variables like `CC', `cache_file', and `prefix'. `configure' looks for `PREFIX/share/config.site' if it exists, then `PREFIX/etc/config.site' if it exists. Or, you can set the `CONFIG_SITE' environment variable to the location of the site script. A warning: not all `configure' scripts look for a site script. Defining Variables ================== Variables not defined in a site shell script can be set in the environment passed to `configure'. However, some packages may run configure again during the build, and the customized values of these variables may be lost. In order to avoid this problem, you should set them in the `configure' command line, using `VAR=value'. For example: ./configure CC=/usr/local2/bin/gcc causes the specified `gcc' to be used as the C compiler (unless it is overridden in the site shell script). Unfortunately, this technique does not work for `CONFIG_SHELL' due to an Autoconf bug. Until the bug is fixed you can use this workaround: CONFIG_SHELL=/bin/bash /bin/bash ./configure CONFIG_SHELL=/bin/bash `configure' Invocation ====================== `configure' recognizes the following options to control how it operates. `--help' `-h' Print a summary of all of the options to `configure', and exit. `--help=short' `--help=recursive' Print a summary of the options unique to this package's `configure', and exit. The `short' variant lists options used only in the top level, while the `recursive' variant lists options also present in any nested packages. `--version' `-V' Print the version of Autoconf used to generate the `configure' script, and exit. `--cache-file=FILE' Enable the cache: use and save the results of the tests in FILE, traditionally `config.cache'. FILE defaults to `/dev/null' to disable caching. `--config-cache' `-C' Alias for `--cache-file=config.cache'. `--quiet' `--silent' `-q' Do not print messages saying which checks are being made. To suppress all normal output, redirect it to `/dev/null' (any error messages will still be shown). `--srcdir=DIR' Look for the package's source code in directory DIR. Usually `configure' can determine that directory automatically. `--prefix=DIR' Use DIR as the installation prefix. *note Installation Names:: for more details, including other options available for fine-tuning the installation locations. `--no-create' `-n' Run the configure checks, but stop before creating any output files. `configure' also accepts some other, not widely useful, options. Run `configure --help' for more details. smalltalk-3.2.5/snprintfv/commit0000755000175000017500000001507212123404352013676 00000000000000#! /bin/sh # commit version 0.9.2 # Copyright (C) 1999, Free Software Foundation # This script is Free Software, and it can be copied, distributed and # modified as defined in the GNU General Public License. A copy of # its license can be downloaded from http://www.gnu.org/copyleft/gpl.html # Originally by Gary V. Vaughan # Heavily modified by Alexandre Oliva # This scripts eases checking in changes to CVS-maintained projects # with ChangeLog files. It will check that there have been no # conflicting commits in the CVS repository and print which files it # is going to commit to stderr. A list of files to compare and to # check in can be given in the command line. If it is not given, all # files in the current directory (and below, unless `-l' is given) are # considered for check in. # The commit message will be extracted from the differences between # the local ChangeLog and the one in the repository (unless a message # was specified with `-m' or `-F'). An empty message is not accepted # (but a blank line is). If the message is acceptable, it will be # presented for verification (and possible edition) using the $PAGER # environment variable (or `more', if it is not set, or `cat', if the # `-f' switch is given). If $PAGER exits successfully, the modified # files (at that moment) are checked in, unless `-n' was specified, in # which case nothing is checked in. # usage: commit [-v] [-h] [-f] [-l] [-n] [-q] [-z N] # [-m msg|-F msg_file] [--] [file|dir ...] # -f --fast don't check (unless *followed* by -n), and just # --force display commit message instead of running $PAGER # -l --local don't descend into subdirectories # -m msg --message=msg set commit message # --msg=msg same as -m # -F file --file=file read commit message from file # -n --dry-run don't commit anything # -q --quiet run cvs in quiet mode # -zN --compress=N set compression level (0-9, 0=none, 9=max) # -v --version print version information # -h,-? --help print short or long help message name=commit cvsopt= updateopt= commitopt= dry_run=false commit=: update=: log_file="${TMPDIR-/tmp}/commitlog.$$" rm -f "$log_file" trap 'rm -f "$log_file"; exit 1' 1 2 15 # this just eases exit handling main_repeat=":" while $main_repeat; do repeat="test $# -gt 0" while $repeat; do case "$1" in -f|--force|--fast) update=false PAGER=cat shift ;; -l|--local) updateopt="$updateopt -l" commitopt="$commitopt -l" shift ;; -m|--message|--msg) if test $# = 1; then echo "$name: missing argument for $1" >&2 break fi if test -f "$log_file"; then echo "$name: you can have at most one of -m and -F" >&2 break fi shift echo "$1" > "$log_file" shift ;; -F|--file) if test -f "$log_file"; then echo "$name: you can have at most one of -m and -F" >&2 break fi if test $# = 1; then echo "$name: missing argument for $1" >&2 break fi shift if cat < "$1" > "$log_file"; then :; else break fi shift ;; -n|--dry-run) commit=false update=true shift ;; -q|--quiet) cvsopt="$cvsopt -q" shift ;; -z|--compress) if test $# = 1; then echo "$name: missing argument for $1" >&2 break fi case "$2" in [0-9]) :;; *) echo "$name: invalid argument for $1" >&2 break ;; esac cvsopt="$cvsopt -z$2" shift shift ;; -m*|-F*|-z*) opt=`echo "$1" | sed '1s/^\(..\).*$/\1/;q'` arg=`echo "$1" | sed '1s/^-[a-zA-Z0-9]//'` shift set -- "$opt" "$arg" ${1+"$@"} ;; --message=*|--msg=*|--file=*|--compress=*) opt=`echo "$1" | sed '1s/^\(--[^=]*\)=.*/\1/;q'` arg=`echo "$1" | sed '1s/^--[^=]*=//'` shift set -- "$opt" "$arg" ${1+"$@"} ;; -v|--version) sed '/^# '$name' version /,/^# Heavily modified by/ { s/^# //; p; }; d' < $0 exit 0 ;; -\?|-h) sed '/^# usage:/,/# -h/ { s/^# //; p; }; d' < $0 && echo echo "run \`$name --help | more' for full usage" exit 0 ;; --help) sed '/^# '$name' version /,/^[^#]/ { /^[^#]/ d; s/^# //; p; }; d' < $0 exit 0 ;; --) shift repeat=false ;; -*) echo "$name: invalid flag $1" >&2 break ;; *) repeat=false ;; esac done # might have used break 2 within the previous loop, but so what $repeat && break $update && \ if echo "$name: checking for conflicts..." >&2 (cvs $cvsopt -q -n update $updateopt ${1+"$@"} 2>/dev/null \ | while read line; do echo "$line" echo "$line" >&3 done | grep '^C') 3>&1 >/dev/null; then echo "$name: some conflicts were found, aborting..." >&2 break fi if test ! -f "$log_file"; then echo "$name: checking commit message..." >&2 cvs $cvsopt diff -u ChangeLog \ | while read line; do case "$line" in "--- ChangeLog"*) :;; "-"*) echo "$name: *** Warning: the following line in ChangeLog diff is suspicious:" >&2 echo "$line" | sed 's/^.//' >&2;; "+ "*) echo "$name: *** Warning: lines should start with tabs, not spaces; ignoring line:" >&2 echo "$line" | sed 's/^.//' >&2;; "+") echo;; "+ "*) echo "$line";; esac done \ | sed -e 's,\+ ,,' -e '/./p' -e '/./d' -e '1d' -e '$d' > "$log_file" \ || break # The sed script above removes "+TAB" from the beginning of a line, then # deletes the first and/or the last line, when they happen to be empty fi if grep '[^ ]' < "$log_file" > /dev/null; then :; else echo "$name: empty commit message, aborting" >&2 break fi if grep '^$' < "$log_file" > /dev/null; then echo "$name: *** Warning: blank lines should not appear within a commit messages." >&2 echo "$name: *** They should be used to separate distinct commits." >&2 fi ${PAGER-more} "$log_file" || break sleep 1 # give the user some time for a ^C # Do not check for empty $log_file again, even though the user might have # zeroed it out. If s/he did, it was probably intentional. if $commit; then cvs $cvsopt commit $commitopt -F $log_file ${1+"$@"} || break fi main_repeat=false done rm -f "$log_file" # if main_repeat was not set to `false', we failed $main_repeat && exit 1 exit 0 smalltalk-3.2.5/snprintfv/aclocal.m40000644000175000017500000010610312130455535014323 00000000000000# generated automatically by aclocal 1.11.6 -*- Autoconf -*- # Copyright (C) 1996, 1997, 1998, 1999, 2000, 2001, 2002, 2003, 2004, # 2005, 2006, 2007, 2008, 2009, 2010, 2011 Free Software Foundation, # Inc. # This file is free software; the Free Software Foundation # gives unlimited permission to copy and/or distribute it, # with or without modifications, as long as this notice is preserved. # This program is distributed in the hope that it will be useful, # but WITHOUT ANY WARRANTY, to the extent permitted by law; without # even the implied warranty of MERCHANTABILITY or FITNESS FOR A # PARTICULAR PURPOSE. m4_ifndef([AC_AUTOCONF_VERSION], [m4_copy([m4_PACKAGE_VERSION], [AC_AUTOCONF_VERSION])])dnl m4_if(m4_defn([AC_AUTOCONF_VERSION]), [2.69],, [m4_warning([this file was generated for autoconf 2.69. You have another version of autoconf. It may work, but is not guaranteed to. If you have problems, you may need to regenerate the build system entirely. To do so, use the procedure documented by the package, typically `autoreconf'.])]) # Copyright (C) 2002, 2003, 2005, 2006, 2007, 2008, 2011 Free Software # Foundation, Inc. # # This file is free software; the Free Software Foundation # gives unlimited permission to copy and/or distribute it, # with or without modifications, as long as this notice is preserved. # serial 1 # AM_AUTOMAKE_VERSION(VERSION) # ---------------------------- # Automake X.Y traces this macro to ensure aclocal.m4 has been # generated from the m4 files accompanying Automake X.Y. # (This private macro should not be called outside this file.) AC_DEFUN([AM_AUTOMAKE_VERSION], [am__api_version='1.11' dnl Some users find AM_AUTOMAKE_VERSION and mistake it for a way to dnl require some minimum version. Point them to the right macro. m4_if([$1], [1.11.6], [], [AC_FATAL([Do not call $0, use AM_INIT_AUTOMAKE([$1]).])])dnl ]) # _AM_AUTOCONF_VERSION(VERSION) # ----------------------------- # aclocal traces this macro to find the Autoconf version. # This is a private macro too. Using m4_define simplifies # the logic in aclocal, which can simply ignore this definition. m4_define([_AM_AUTOCONF_VERSION], []) # AM_SET_CURRENT_AUTOMAKE_VERSION # ------------------------------- # Call AM_AUTOMAKE_VERSION and AM_AUTOMAKE_VERSION so they can be traced. # This function is AC_REQUIREd by AM_INIT_AUTOMAKE. AC_DEFUN([AM_SET_CURRENT_AUTOMAKE_VERSION], [AM_AUTOMAKE_VERSION([1.11.6])dnl m4_ifndef([AC_AUTOCONF_VERSION], [m4_copy([m4_PACKAGE_VERSION], [AC_AUTOCONF_VERSION])])dnl _AM_AUTOCONF_VERSION(m4_defn([AC_AUTOCONF_VERSION]))]) # AM_AUX_DIR_EXPAND -*- Autoconf -*- # Copyright (C) 2001, 2003, 2005, 2011 Free Software Foundation, Inc. # # This file is free software; the Free Software Foundation # gives unlimited permission to copy and/or distribute it, # with or without modifications, as long as this notice is preserved. # serial 1 # For projects using AC_CONFIG_AUX_DIR([foo]), Autoconf sets # $ac_aux_dir to `$srcdir/foo'. In other projects, it is set to # `$srcdir', `$srcdir/..', or `$srcdir/../..'. # # Of course, Automake must honor this variable whenever it calls a # tool from the auxiliary directory. The problem is that $srcdir (and # therefore $ac_aux_dir as well) can be either absolute or relative, # depending on how configure is run. This is pretty annoying, since # it makes $ac_aux_dir quite unusable in subdirectories: in the top # source directory, any form will work fine, but in subdirectories a # relative path needs to be adjusted first. # # $ac_aux_dir/missing # fails when called from a subdirectory if $ac_aux_dir is relative # $top_srcdir/$ac_aux_dir/missing # fails if $ac_aux_dir is absolute, # fails when called from a subdirectory in a VPATH build with # a relative $ac_aux_dir # # The reason of the latter failure is that $top_srcdir and $ac_aux_dir # are both prefixed by $srcdir. In an in-source build this is usually # harmless because $srcdir is `.', but things will broke when you # start a VPATH build or use an absolute $srcdir. # # So we could use something similar to $top_srcdir/$ac_aux_dir/missing, # iff we strip the leading $srcdir from $ac_aux_dir. That would be: # am_aux_dir='\$(top_srcdir)/'`expr "$ac_aux_dir" : "$srcdir//*\(.*\)"` # and then we would define $MISSING as # MISSING="\${SHELL} $am_aux_dir/missing" # This will work as long as MISSING is not called from configure, because # unfortunately $(top_srcdir) has no meaning in configure. # However there are other variables, like CC, which are often used in # configure, and could therefore not use this "fixed" $ac_aux_dir. # # Another solution, used here, is to always expand $ac_aux_dir to an # absolute PATH. The drawback is that using absolute paths prevent a # configured tree to be moved without reconfiguration. AC_DEFUN([AM_AUX_DIR_EXPAND], [dnl Rely on autoconf to set up CDPATH properly. AC_PREREQ([2.50])dnl # expand $ac_aux_dir to an absolute path am_aux_dir=`cd $ac_aux_dir && pwd` ]) # AM_CONDITIONAL -*- Autoconf -*- # Copyright (C) 1997, 2000, 2001, 2003, 2004, 2005, 2006, 2008 # Free Software Foundation, Inc. # # This file is free software; the Free Software Foundation # gives unlimited permission to copy and/or distribute it, # with or without modifications, as long as this notice is preserved. # serial 9 # AM_CONDITIONAL(NAME, SHELL-CONDITION) # ------------------------------------- # Define a conditional. AC_DEFUN([AM_CONDITIONAL], [AC_PREREQ(2.52)dnl ifelse([$1], [TRUE], [AC_FATAL([$0: invalid condition: $1])], [$1], [FALSE], [AC_FATAL([$0: invalid condition: $1])])dnl AC_SUBST([$1_TRUE])dnl AC_SUBST([$1_FALSE])dnl _AM_SUBST_NOTMAKE([$1_TRUE])dnl _AM_SUBST_NOTMAKE([$1_FALSE])dnl m4_define([_AM_COND_VALUE_$1], [$2])dnl if $2; then $1_TRUE= $1_FALSE='#' else $1_TRUE='#' $1_FALSE= fi AC_CONFIG_COMMANDS_PRE( [if test -z "${$1_TRUE}" && test -z "${$1_FALSE}"; then AC_MSG_ERROR([[conditional "$1" was never defined. Usually this means the macro was only invoked conditionally.]]) fi])]) # Copyright (C) 1999, 2000, 2001, 2002, 2003, 2004, 2005, 2006, 2009, # 2010, 2011 Free Software Foundation, Inc. # # This file is free software; the Free Software Foundation # gives unlimited permission to copy and/or distribute it, # with or without modifications, as long as this notice is preserved. # serial 12 # There are a few dirty hacks below to avoid letting `AC_PROG_CC' be # written in clear, in which case automake, when reading aclocal.m4, # will think it sees a *use*, and therefore will trigger all it's # C support machinery. Also note that it means that autoscan, seeing # CC etc. in the Makefile, will ask for an AC_PROG_CC use... # _AM_DEPENDENCIES(NAME) # ---------------------- # See how the compiler implements dependency checking. # NAME is "CC", "CXX", "GCJ", or "OBJC". # We try a few techniques and use that to set a single cache variable. # # We don't AC_REQUIRE the corresponding AC_PROG_CC since the latter was # modified to invoke _AM_DEPENDENCIES(CC); we would have a circular # dependency, and given that the user is not expected to run this macro, # just rely on AC_PROG_CC. AC_DEFUN([_AM_DEPENDENCIES], [AC_REQUIRE([AM_SET_DEPDIR])dnl AC_REQUIRE([AM_OUTPUT_DEPENDENCY_COMMANDS])dnl AC_REQUIRE([AM_MAKE_INCLUDE])dnl AC_REQUIRE([AM_DEP_TRACK])dnl ifelse([$1], CC, [depcc="$CC" am_compiler_list=], [$1], CXX, [depcc="$CXX" am_compiler_list=], [$1], OBJC, [depcc="$OBJC" am_compiler_list='gcc3 gcc'], [$1], UPC, [depcc="$UPC" am_compiler_list=], [$1], GCJ, [depcc="$GCJ" am_compiler_list='gcc3 gcc'], [depcc="$$1" am_compiler_list=]) AC_CACHE_CHECK([dependency style of $depcc], [am_cv_$1_dependencies_compiler_type], [if test -z "$AMDEP_TRUE" && test -f "$am_depcomp"; then # We make a subdir and do the tests there. Otherwise we can end up # making bogus files that we don't know about and never remove. For # instance it was reported that on HP-UX the gcc test will end up # making a dummy file named `D' -- because `-MD' means `put the output # in D'. rm -rf conftest.dir mkdir conftest.dir # Copy depcomp to subdir because otherwise we won't find it if we're # using a relative directory. cp "$am_depcomp" conftest.dir cd conftest.dir # We will build objects and dependencies in a subdirectory because # it helps to detect inapplicable dependency modes. For instance # both Tru64's cc and ICC support -MD to output dependencies as a # side effect of compilation, but ICC will put the dependencies in # the current directory while Tru64 will put them in the object # directory. mkdir sub am_cv_$1_dependencies_compiler_type=none if test "$am_compiler_list" = ""; then am_compiler_list=`sed -n ['s/^#*\([a-zA-Z0-9]*\))$/\1/p'] < ./depcomp` fi am__universal=false m4_case([$1], [CC], [case " $depcc " in #( *\ -arch\ *\ -arch\ *) am__universal=true ;; esac], [CXX], [case " $depcc " in #( *\ -arch\ *\ -arch\ *) am__universal=true ;; esac]) for depmode in $am_compiler_list; do # Setup a source with many dependencies, because some compilers # like to wrap large dependency lists on column 80 (with \), and # we should not choose a depcomp mode which is confused by this. # # We need to recreate these files for each test, as the compiler may # overwrite some of them when testing with obscure command lines. # This happens at least with the AIX C compiler. : > sub/conftest.c for i in 1 2 3 4 5 6; do echo '#include "conftst'$i'.h"' >> sub/conftest.c # Using `: > sub/conftst$i.h' creates only sub/conftst1.h with # Solaris 8's {/usr,}/bin/sh. touch sub/conftst$i.h done echo "${am__include} ${am__quote}sub/conftest.Po${am__quote}" > confmf # We check with `-c' and `-o' for the sake of the "dashmstdout" # mode. It turns out that the SunPro C++ compiler does not properly # handle `-M -o', and we need to detect this. Also, some Intel # versions had trouble with output in subdirs am__obj=sub/conftest.${OBJEXT-o} am__minus_obj="-o $am__obj" case $depmode in gcc) # This depmode causes a compiler race in universal mode. test "$am__universal" = false || continue ;; nosideeffect) # after this tag, mechanisms are not by side-effect, so they'll # only be used when explicitly requested if test "x$enable_dependency_tracking" = xyes; then continue else break fi ;; msvc7 | msvc7msys | msvisualcpp | msvcmsys) # This compiler won't grok `-c -o', but also, the minuso test has # not run yet. These depmodes are late enough in the game, and # so weak that their functioning should not be impacted. am__obj=conftest.${OBJEXT-o} am__minus_obj= ;; none) break ;; esac if depmode=$depmode \ source=sub/conftest.c object=$am__obj \ depfile=sub/conftest.Po tmpdepfile=sub/conftest.TPo \ $SHELL ./depcomp $depcc -c $am__minus_obj sub/conftest.c \ >/dev/null 2>conftest.err && grep sub/conftst1.h sub/conftest.Po > /dev/null 2>&1 && grep sub/conftst6.h sub/conftest.Po > /dev/null 2>&1 && grep $am__obj sub/conftest.Po > /dev/null 2>&1 && ${MAKE-make} -s -f confmf > /dev/null 2>&1; then # icc doesn't choke on unknown options, it will just issue warnings # or remarks (even with -Werror). So we grep stderr for any message # that says an option was ignored or not supported. # When given -MP, icc 7.0 and 7.1 complain thusly: # icc: Command line warning: ignoring option '-M'; no argument required # The diagnosis changed in icc 8.0: # icc: Command line remark: option '-MP' not supported if (grep 'ignoring option' conftest.err || grep 'not supported' conftest.err) >/dev/null 2>&1; then :; else am_cv_$1_dependencies_compiler_type=$depmode break fi fi done cd .. rm -rf conftest.dir else am_cv_$1_dependencies_compiler_type=none fi ]) AC_SUBST([$1DEPMODE], [depmode=$am_cv_$1_dependencies_compiler_type]) AM_CONDITIONAL([am__fastdep$1], [ test "x$enable_dependency_tracking" != xno \ && test "$am_cv_$1_dependencies_compiler_type" = gcc3]) ]) # AM_SET_DEPDIR # ------------- # Choose a directory name for dependency files. # This macro is AC_REQUIREd in _AM_DEPENDENCIES AC_DEFUN([AM_SET_DEPDIR], [AC_REQUIRE([AM_SET_LEADING_DOT])dnl AC_SUBST([DEPDIR], ["${am__leading_dot}deps"])dnl ]) # AM_DEP_TRACK # ------------ AC_DEFUN([AM_DEP_TRACK], [AC_ARG_ENABLE(dependency-tracking, [ --disable-dependency-tracking speeds up one-time build --enable-dependency-tracking do not reject slow dependency extractors]) if test "x$enable_dependency_tracking" != xno; then am_depcomp="$ac_aux_dir/depcomp" AMDEPBACKSLASH='\' am__nodep='_no' fi AM_CONDITIONAL([AMDEP], [test "x$enable_dependency_tracking" != xno]) AC_SUBST([AMDEPBACKSLASH])dnl _AM_SUBST_NOTMAKE([AMDEPBACKSLASH])dnl AC_SUBST([am__nodep])dnl _AM_SUBST_NOTMAKE([am__nodep])dnl ]) # Generate code to set up dependency tracking. -*- Autoconf -*- # Copyright (C) 1999, 2000, 2001, 2002, 2003, 2004, 2005, 2008 # Free Software Foundation, Inc. # # This file is free software; the Free Software Foundation # gives unlimited permission to copy and/or distribute it, # with or without modifications, as long as this notice is preserved. #serial 5 # _AM_OUTPUT_DEPENDENCY_COMMANDS # ------------------------------ AC_DEFUN([_AM_OUTPUT_DEPENDENCY_COMMANDS], [{ # Autoconf 2.62 quotes --file arguments for eval, but not when files # are listed without --file. Let's play safe and only enable the eval # if we detect the quoting. case $CONFIG_FILES in *\'*) eval set x "$CONFIG_FILES" ;; *) set x $CONFIG_FILES ;; esac shift for mf do # Strip MF so we end up with the name of the file. mf=`echo "$mf" | sed -e 's/:.*$//'` # Check whether this is an Automake generated Makefile or not. # We used to match only the files named `Makefile.in', but # some people rename them; so instead we look at the file content. # Grep'ing the first line is not enough: some people post-process # each Makefile.in and add a new line on top of each file to say so. # Grep'ing the whole file is not good either: AIX grep has a line # limit of 2048, but all sed's we know have understand at least 4000. if sed -n 's,^#.*generated by automake.*,X,p' "$mf" | grep X >/dev/null 2>&1; then dirpart=`AS_DIRNAME("$mf")` else continue fi # Extract the definition of DEPDIR, am__include, and am__quote # from the Makefile without running `make'. DEPDIR=`sed -n 's/^DEPDIR = //p' < "$mf"` test -z "$DEPDIR" && continue am__include=`sed -n 's/^am__include = //p' < "$mf"` test -z "am__include" && continue am__quote=`sed -n 's/^am__quote = //p' < "$mf"` # When using ansi2knr, U may be empty or an underscore; expand it U=`sed -n 's/^U = //p' < "$mf"` # Find all dependency output files, they are included files with # $(DEPDIR) in their names. We invoke sed twice because it is the # simplest approach to changing $(DEPDIR) to its actual value in the # expansion. for file in `sed -n " s/^$am__include $am__quote\(.*(DEPDIR).*\)$am__quote"'$/\1/p' <"$mf" | \ sed -e 's/\$(DEPDIR)/'"$DEPDIR"'/g' -e 's/\$U/'"$U"'/g'`; do # Make sure the directory exists. test -f "$dirpart/$file" && continue fdir=`AS_DIRNAME(["$file"])` AS_MKDIR_P([$dirpart/$fdir]) # echo "creating $dirpart/$file" echo '# dummy' > "$dirpart/$file" done done } ])# _AM_OUTPUT_DEPENDENCY_COMMANDS # AM_OUTPUT_DEPENDENCY_COMMANDS # ----------------------------- # This macro should only be invoked once -- use via AC_REQUIRE. # # This code is only required when automatic dependency tracking # is enabled. FIXME. This creates each `.P' file that we will # need in order to bootstrap the dependency handling code. AC_DEFUN([AM_OUTPUT_DEPENDENCY_COMMANDS], [AC_CONFIG_COMMANDS([depfiles], [test x"$AMDEP_TRUE" != x"" || _AM_OUTPUT_DEPENDENCY_COMMANDS], [AMDEP_TRUE="$AMDEP_TRUE" ac_aux_dir="$ac_aux_dir"]) ]) # Copyright (C) 1996, 1998, 1999, 2000, 2001, 2002, 2003, 2005, 2010 # Free Software Foundation, Inc. # # This file is free software; the Free Software Foundation # gives unlimited permission to copy and/or distribute it, # with or without modifications, as long as this notice is preserved. # serial 4 AC_DEFUN([AM_WITH_DMALLOC], [AC_MSG_CHECKING([if malloc debugging is wanted]) AC_ARG_WITH(dmalloc, [ --with-dmalloc use dmalloc, as in http://www.dmalloc.com], [if test "$withval" = yes; then AC_MSG_RESULT(yes) AC_DEFINE(WITH_DMALLOC,1, [Define if using the dmalloc debugging malloc package]) LIBS="$LIBS -ldmalloc" LDFLAGS="$LDFLAGS -g" else AC_MSG_RESULT(no) fi], [AC_MSG_RESULT(no)]) ]) AU_DEFUN([fp_WITH_DMALLOC], [AM_WITH_DMALLOC]) # Do all the work for Automake. -*- Autoconf -*- # Copyright (C) 1996, 1997, 1998, 1999, 2000, 2001, 2002, 2003, 2004, # 2005, 2006, 2008, 2009 Free Software Foundation, Inc. # # This file is free software; the Free Software Foundation # gives unlimited permission to copy and/or distribute it, # with or without modifications, as long as this notice is preserved. # serial 16 # This macro actually does too much. Some checks are only needed if # your package does certain things. But this isn't really a big deal. # AM_INIT_AUTOMAKE(PACKAGE, VERSION, [NO-DEFINE]) # AM_INIT_AUTOMAKE([OPTIONS]) # ----------------------------------------------- # The call with PACKAGE and VERSION arguments is the old style # call (pre autoconf-2.50), which is being phased out. PACKAGE # and VERSION should now be passed to AC_INIT and removed from # the call to AM_INIT_AUTOMAKE. # We support both call styles for the transition. After # the next Automake release, Autoconf can make the AC_INIT # arguments mandatory, and then we can depend on a new Autoconf # release and drop the old call support. AC_DEFUN([AM_INIT_AUTOMAKE], [AC_PREREQ([2.62])dnl dnl Autoconf wants to disallow AM_ names. We explicitly allow dnl the ones we care about. m4_pattern_allow([^AM_[A-Z]+FLAGS$])dnl AC_REQUIRE([AM_SET_CURRENT_AUTOMAKE_VERSION])dnl AC_REQUIRE([AC_PROG_INSTALL])dnl if test "`cd $srcdir && pwd`" != "`pwd`"; then # Use -I$(srcdir) only when $(srcdir) != ., so that make's output # is not polluted with repeated "-I." AC_SUBST([am__isrc], [' -I$(srcdir)'])_AM_SUBST_NOTMAKE([am__isrc])dnl # test to see if srcdir already configured if test -f $srcdir/config.status; then AC_MSG_ERROR([source directory already configured; run "make distclean" there first]) fi fi # test whether we have cygpath if test -z "$CYGPATH_W"; then if (cygpath --version) >/dev/null 2>/dev/null; then CYGPATH_W='cygpath -w' else CYGPATH_W=echo fi fi AC_SUBST([CYGPATH_W]) # Define the identity of the package. dnl Distinguish between old-style and new-style calls. m4_ifval([$2], [m4_ifval([$3], [_AM_SET_OPTION([no-define])])dnl AC_SUBST([PACKAGE], [$1])dnl AC_SUBST([VERSION], [$2])], [_AM_SET_OPTIONS([$1])dnl dnl Diagnose old-style AC_INIT with new-style AM_AUTOMAKE_INIT. m4_if(m4_ifdef([AC_PACKAGE_NAME], 1)m4_ifdef([AC_PACKAGE_VERSION], 1), 11,, [m4_fatal([AC_INIT should be called with package and version arguments])])dnl AC_SUBST([PACKAGE], ['AC_PACKAGE_TARNAME'])dnl AC_SUBST([VERSION], ['AC_PACKAGE_VERSION'])])dnl _AM_IF_OPTION([no-define],, [AC_DEFINE_UNQUOTED(PACKAGE, "$PACKAGE", [Name of package]) AC_DEFINE_UNQUOTED(VERSION, "$VERSION", [Version number of package])])dnl # Some tools Automake needs. AC_REQUIRE([AM_SANITY_CHECK])dnl AC_REQUIRE([AC_ARG_PROGRAM])dnl AM_MISSING_PROG(ACLOCAL, aclocal-${am__api_version}) AM_MISSING_PROG(AUTOCONF, autoconf) AM_MISSING_PROG(AUTOMAKE, automake-${am__api_version}) AM_MISSING_PROG(AUTOHEADER, autoheader) AM_MISSING_PROG(MAKEINFO, makeinfo) AC_REQUIRE([AM_PROG_INSTALL_SH])dnl AC_REQUIRE([AM_PROG_INSTALL_STRIP])dnl AC_REQUIRE([AM_PROG_MKDIR_P])dnl # We need awk for the "check" target. The system "awk" is bad on # some platforms. AC_REQUIRE([AC_PROG_AWK])dnl AC_REQUIRE([AC_PROG_MAKE_SET])dnl AC_REQUIRE([AM_SET_LEADING_DOT])dnl _AM_IF_OPTION([tar-ustar], [_AM_PROG_TAR([ustar])], [_AM_IF_OPTION([tar-pax], [_AM_PROG_TAR([pax])], [_AM_PROG_TAR([v7])])]) _AM_IF_OPTION([no-dependencies],, [AC_PROVIDE_IFELSE([AC_PROG_CC], [_AM_DEPENDENCIES(CC)], [define([AC_PROG_CC], defn([AC_PROG_CC])[_AM_DEPENDENCIES(CC)])])dnl AC_PROVIDE_IFELSE([AC_PROG_CXX], [_AM_DEPENDENCIES(CXX)], [define([AC_PROG_CXX], defn([AC_PROG_CXX])[_AM_DEPENDENCIES(CXX)])])dnl AC_PROVIDE_IFELSE([AC_PROG_OBJC], [_AM_DEPENDENCIES(OBJC)], [define([AC_PROG_OBJC], defn([AC_PROG_OBJC])[_AM_DEPENDENCIES(OBJC)])])dnl ]) _AM_IF_OPTION([silent-rules], [AC_REQUIRE([AM_SILENT_RULES])])dnl dnl The `parallel-tests' driver may need to know about EXEEXT, so add the dnl `am__EXEEXT' conditional if _AM_COMPILER_EXEEXT was seen. This macro dnl is hooked onto _AC_COMPILER_EXEEXT early, see below. AC_CONFIG_COMMANDS_PRE(dnl [m4_provide_if([_AM_COMPILER_EXEEXT], [AM_CONDITIONAL([am__EXEEXT], [test -n "$EXEEXT"])])])dnl ]) dnl Hook into `_AC_COMPILER_EXEEXT' early to learn its expansion. Do not dnl add the conditional right here, as _AC_COMPILER_EXEEXT may be further dnl mangled by Autoconf and run in a shell conditional statement. m4_define([_AC_COMPILER_EXEEXT], m4_defn([_AC_COMPILER_EXEEXT])[m4_provide([_AM_COMPILER_EXEEXT])]) # When config.status generates a header, we must update the stamp-h file. # This file resides in the same directory as the config header # that is generated. The stamp files are numbered to have different names. # Autoconf calls _AC_AM_CONFIG_HEADER_HOOK (when defined) in the # loop where config.status creates the headers, so we can generate # our stamp files there. AC_DEFUN([_AC_AM_CONFIG_HEADER_HOOK], [# Compute $1's index in $config_headers. _am_arg=$1 _am_stamp_count=1 for _am_header in $config_headers :; do case $_am_header in $_am_arg | $_am_arg:* ) break ;; * ) _am_stamp_count=`expr $_am_stamp_count + 1` ;; esac done echo "timestamp for $_am_arg" >`AS_DIRNAME(["$_am_arg"])`/stamp-h[]$_am_stamp_count]) # Copyright (C) 2001, 2003, 2005, 2008, 2011 Free Software Foundation, # Inc. # # This file is free software; the Free Software Foundation # gives unlimited permission to copy and/or distribute it, # with or without modifications, as long as this notice is preserved. # serial 1 # AM_PROG_INSTALL_SH # ------------------ # Define $install_sh. AC_DEFUN([AM_PROG_INSTALL_SH], [AC_REQUIRE([AM_AUX_DIR_EXPAND])dnl if test x"${install_sh}" != xset; then case $am_aux_dir in *\ * | *\ *) install_sh="\${SHELL} '$am_aux_dir/install-sh'" ;; *) install_sh="\${SHELL} $am_aux_dir/install-sh" esac fi AC_SUBST(install_sh)]) # Copyright (C) 2003, 2005 Free Software Foundation, Inc. # # This file is free software; the Free Software Foundation # gives unlimited permission to copy and/or distribute it, # with or without modifications, as long as this notice is preserved. # serial 2 # Check whether the underlying file-system supports filenames # with a leading dot. For instance MS-DOS doesn't. AC_DEFUN([AM_SET_LEADING_DOT], [rm -rf .tst 2>/dev/null mkdir .tst 2>/dev/null if test -d .tst; then am__leading_dot=. else am__leading_dot=_ fi rmdir .tst 2>/dev/null AC_SUBST([am__leading_dot])]) # Check to see how 'make' treats includes. -*- Autoconf -*- # Copyright (C) 2001, 2002, 2003, 2005, 2009 Free Software Foundation, Inc. # # This file is free software; the Free Software Foundation # gives unlimited permission to copy and/or distribute it, # with or without modifications, as long as this notice is preserved. # serial 4 # AM_MAKE_INCLUDE() # ----------------- # Check to see how make treats includes. AC_DEFUN([AM_MAKE_INCLUDE], [am_make=${MAKE-make} cat > confinc << 'END' am__doit: @echo this is the am__doit target .PHONY: am__doit END # If we don't find an include directive, just comment out the code. AC_MSG_CHECKING([for style of include used by $am_make]) am__include="#" am__quote= _am_result=none # First try GNU make style include. echo "include confinc" > confmf # Ignore all kinds of additional output from `make'. case `$am_make -s -f confmf 2> /dev/null` in #( *the\ am__doit\ target*) am__include=include am__quote= _am_result=GNU ;; esac # Now try BSD make style include. if test "$am__include" = "#"; then echo '.include "confinc"' > confmf case `$am_make -s -f confmf 2> /dev/null` in #( *the\ am__doit\ target*) am__include=.include am__quote="\"" _am_result=BSD ;; esac fi AC_SUBST([am__include]) AC_SUBST([am__quote]) AC_MSG_RESULT([$_am_result]) rm -f confinc confmf ]) # Fake the existence of programs that GNU maintainers use. -*- Autoconf -*- # Copyright (C) 1997, 1999, 2000, 2001, 2003, 2004, 2005, 2008 # Free Software Foundation, Inc. # # This file is free software; the Free Software Foundation # gives unlimited permission to copy and/or distribute it, # with or without modifications, as long as this notice is preserved. # serial 6 # AM_MISSING_PROG(NAME, PROGRAM) # ------------------------------ AC_DEFUN([AM_MISSING_PROG], [AC_REQUIRE([AM_MISSING_HAS_RUN]) $1=${$1-"${am_missing_run}$2"} AC_SUBST($1)]) # AM_MISSING_HAS_RUN # ------------------ # Define MISSING if not defined so far and test if it supports --run. # If it does, set am_missing_run to use it, otherwise, to nothing. AC_DEFUN([AM_MISSING_HAS_RUN], [AC_REQUIRE([AM_AUX_DIR_EXPAND])dnl AC_REQUIRE_AUX_FILE([missing])dnl if test x"${MISSING+set}" != xset; then case $am_aux_dir in *\ * | *\ *) MISSING="\${SHELL} \"$am_aux_dir/missing\"" ;; *) MISSING="\${SHELL} $am_aux_dir/missing" ;; esac fi # Use eval to expand $SHELL if eval "$MISSING --run true"; then am_missing_run="$MISSING --run " else am_missing_run= AC_MSG_WARN([`missing' script is too old or missing]) fi ]) # Copyright (C) 2003, 2004, 2005, 2006, 2011 Free Software Foundation, # Inc. # # This file is free software; the Free Software Foundation # gives unlimited permission to copy and/or distribute it, # with or without modifications, as long as this notice is preserved. # serial 1 # AM_PROG_MKDIR_P # --------------- # Check for `mkdir -p'. AC_DEFUN([AM_PROG_MKDIR_P], [AC_PREREQ([2.60])dnl AC_REQUIRE([AC_PROG_MKDIR_P])dnl dnl Automake 1.8 to 1.9.6 used to define mkdir_p. We now use MKDIR_P, dnl while keeping a definition of mkdir_p for backward compatibility. dnl @MKDIR_P@ is magic: AC_OUTPUT adjusts its value for each Makefile. dnl However we cannot define mkdir_p as $(MKDIR_P) for the sake of dnl Makefile.ins that do not define MKDIR_P, so we do our own dnl adjustment using top_builddir (which is defined more often than dnl MKDIR_P). AC_SUBST([mkdir_p], ["$MKDIR_P"])dnl case $mkdir_p in [[\\/$]]* | ?:[[\\/]]*) ;; */*) mkdir_p="\$(top_builddir)/$mkdir_p" ;; esac ]) # Helper functions for option handling. -*- Autoconf -*- # Copyright (C) 2001, 2002, 2003, 2005, 2008, 2010 Free Software # Foundation, Inc. # # This file is free software; the Free Software Foundation # gives unlimited permission to copy and/or distribute it, # with or without modifications, as long as this notice is preserved. # serial 5 # _AM_MANGLE_OPTION(NAME) # ----------------------- AC_DEFUN([_AM_MANGLE_OPTION], [[_AM_OPTION_]m4_bpatsubst($1, [[^a-zA-Z0-9_]], [_])]) # _AM_SET_OPTION(NAME) # -------------------- # Set option NAME. Presently that only means defining a flag for this option. AC_DEFUN([_AM_SET_OPTION], [m4_define(_AM_MANGLE_OPTION([$1]), 1)]) # _AM_SET_OPTIONS(OPTIONS) # ------------------------ # OPTIONS is a space-separated list of Automake options. AC_DEFUN([_AM_SET_OPTIONS], [m4_foreach_w([_AM_Option], [$1], [_AM_SET_OPTION(_AM_Option)])]) # _AM_IF_OPTION(OPTION, IF-SET, [IF-NOT-SET]) # ------------------------------------------- # Execute IF-SET if OPTION is set, IF-NOT-SET otherwise. AC_DEFUN([_AM_IF_OPTION], [m4_ifset(_AM_MANGLE_OPTION([$1]), [$2], [$3])]) # Check to make sure that the build environment is sane. -*- Autoconf -*- # Copyright (C) 1996, 1997, 2000, 2001, 2003, 2005, 2008 # Free Software Foundation, Inc. # # This file is free software; the Free Software Foundation # gives unlimited permission to copy and/or distribute it, # with or without modifications, as long as this notice is preserved. # serial 5 # AM_SANITY_CHECK # --------------- AC_DEFUN([AM_SANITY_CHECK], [AC_MSG_CHECKING([whether build environment is sane]) # Just in case sleep 1 echo timestamp > conftest.file # Reject unsafe characters in $srcdir or the absolute working directory # name. Accept space and tab only in the latter. am_lf=' ' case `pwd` in *[[\\\"\#\$\&\'\`$am_lf]]*) AC_MSG_ERROR([unsafe absolute working directory name]);; esac case $srcdir in *[[\\\"\#\$\&\'\`$am_lf\ \ ]]*) AC_MSG_ERROR([unsafe srcdir value: `$srcdir']);; esac # Do `set' in a subshell so we don't clobber the current shell's # arguments. Must try -L first in case configure is actually a # symlink; some systems play weird games with the mod time of symlinks # (eg FreeBSD returns the mod time of the symlink's containing # directory). if ( set X `ls -Lt "$srcdir/configure" conftest.file 2> /dev/null` if test "$[*]" = "X"; then # -L didn't work. set X `ls -t "$srcdir/configure" conftest.file` fi rm -f conftest.file if test "$[*]" != "X $srcdir/configure conftest.file" \ && test "$[*]" != "X conftest.file $srcdir/configure"; then # If neither matched, then we have a broken ls. This can happen # if, for instance, CONFIG_SHELL is bash and it inherits a # broken ls alias from the environment. This has actually # happened. Such a system could not be considered "sane". AC_MSG_ERROR([ls -t appears to fail. Make sure there is not a broken alias in your environment]) fi test "$[2]" = conftest.file ) then # Ok. : else AC_MSG_ERROR([newly created file is older than distributed files! Check your system clock]) fi AC_MSG_RESULT(yes)]) # Copyright (C) 2001, 2003, 2005, 2011 Free Software Foundation, Inc. # # This file is free software; the Free Software Foundation # gives unlimited permission to copy and/or distribute it, # with or without modifications, as long as this notice is preserved. # serial 1 # AM_PROG_INSTALL_STRIP # --------------------- # One issue with vendor `install' (even GNU) is that you can't # specify the program used to strip binaries. This is especially # annoying in cross-compiling environments, where the build's strip # is unlikely to handle the host's binaries. # Fortunately install-sh will honor a STRIPPROG variable, so we # always use install-sh in `make install-strip', and initialize # STRIPPROG with the value of the STRIP variable (set by the user). AC_DEFUN([AM_PROG_INSTALL_STRIP], [AC_REQUIRE([AM_PROG_INSTALL_SH])dnl # Installed binaries are usually stripped using `strip' when the user # run `make install-strip'. However `strip' might not be the right # tool to use in cross-compilation environments, therefore Automake # will honor the `STRIP' environment variable to overrule this program. dnl Don't test for $cross_compiling = yes, because it might be `maybe'. if test "$cross_compiling" != no; then AC_CHECK_TOOL([STRIP], [strip], :) fi INSTALL_STRIP_PROGRAM="\$(install_sh) -c -s" AC_SUBST([INSTALL_STRIP_PROGRAM])]) # Copyright (C) 2006, 2008, 2010 Free Software Foundation, Inc. # # This file is free software; the Free Software Foundation # gives unlimited permission to copy and/or distribute it, # with or without modifications, as long as this notice is preserved. # serial 3 # _AM_SUBST_NOTMAKE(VARIABLE) # --------------------------- # Prevent Automake from outputting VARIABLE = @VARIABLE@ in Makefile.in. # This macro is traced by Automake. AC_DEFUN([_AM_SUBST_NOTMAKE]) # AM_SUBST_NOTMAKE(VARIABLE) # -------------------------- # Public sister of _AM_SUBST_NOTMAKE. AC_DEFUN([AM_SUBST_NOTMAKE], [_AM_SUBST_NOTMAKE($@)]) # Check how to create a tarball. -*- Autoconf -*- # Copyright (C) 2004, 2005, 2012 Free Software Foundation, Inc. # # This file is free software; the Free Software Foundation # gives unlimited permission to copy and/or distribute it, # with or without modifications, as long as this notice is preserved. # serial 2 # _AM_PROG_TAR(FORMAT) # -------------------- # Check how to create a tarball in format FORMAT. # FORMAT should be one of `v7', `ustar', or `pax'. # # Substitute a variable $(am__tar) that is a command # writing to stdout a FORMAT-tarball containing the directory # $tardir. # tardir=directory && $(am__tar) > result.tar # # Substitute a variable $(am__untar) that extract such # a tarball read from stdin. # $(am__untar) < result.tar AC_DEFUN([_AM_PROG_TAR], [# Always define AMTAR for backward compatibility. Yes, it's still used # in the wild :-( We should find a proper way to deprecate it ... AC_SUBST([AMTAR], ['$${TAR-tar}']) m4_if([$1], [v7], [am__tar='$${TAR-tar} chof - "$$tardir"' am__untar='$${TAR-tar} xf -'], [m4_case([$1], [ustar],, [pax],, [m4_fatal([Unknown tar format])]) AC_MSG_CHECKING([how to create a $1 tar archive]) # Loop over all known methods to create a tar archive until one works. _am_tools='gnutar m4_if([$1], [ustar], [plaintar]) pax cpio none' _am_tools=${am_cv_prog_tar_$1-$_am_tools} # Do not fold the above two line into one, because Tru64 sh and # Solaris sh will not grok spaces in the rhs of `-'. for _am_tool in $_am_tools do case $_am_tool in gnutar) for _am_tar in tar gnutar gtar; do AM_RUN_LOG([$_am_tar --version]) && break done am__tar="$_am_tar --format=m4_if([$1], [pax], [posix], [$1]) -chf - "'"$$tardir"' am__tar_="$_am_tar --format=m4_if([$1], [pax], [posix], [$1]) -chf - "'"$tardir"' am__untar="$_am_tar -xf -" ;; plaintar) # Must skip GNU tar: if it does not support --format= it doesn't create # ustar tarball either. (tar --version) >/dev/null 2>&1 && continue am__tar='tar chf - "$$tardir"' am__tar_='tar chf - "$tardir"' am__untar='tar xf -' ;; pax) am__tar='pax -L -x $1 -w "$$tardir"' am__tar_='pax -L -x $1 -w "$tardir"' am__untar='pax -r' ;; cpio) am__tar='find "$$tardir" -print | cpio -o -H $1 -L' am__tar_='find "$tardir" -print | cpio -o -H $1 -L' am__untar='cpio -i -H $1 -d' ;; none) am__tar=false am__tar_=false am__untar=false ;; esac # If the value was cached, stop now. We just wanted to have am__tar # and am__untar set. test -n "${am_cv_prog_tar_$1}" && break # tar/untar a dummy directory, and stop if the command works rm -rf conftest.dir mkdir conftest.dir echo GrepMe > conftest.dir/file AM_RUN_LOG([tardir=conftest.dir && eval $am__tar_ >conftest.tar]) rm -rf conftest.dir if test -s conftest.tar; then AM_RUN_LOG([$am__untar /dev/null 2>&1 && break fi done rm -rf conftest.dir AC_CACHE_VAL([am_cv_prog_tar_$1], [am_cv_prog_tar_$1=$_am_tool]) AC_MSG_RESULT([$am_cv_prog_tar_$1])]) AC_SUBST([am__tar]) AC_SUBST([am__untar]) ]) # _AM_PROG_TAR m4_include([../build-aux/libtool.m4]) m4_include([../build-aux/ltoptions.m4]) m4_include([../build-aux/ltsugar.m4]) m4_include([../build-aux/ltversion.m4]) m4_include([../build-aux/lt~obsolete.m4]) smalltalk-3.2.5/snprintfv/ChangeLog0000644000175000017500000002440712123404352014234 000000000000002010-09-13 Paolo Bonzini * configure.ac: Fix cut-and-paste mistake. 2010-09-13 Paolo Bonzini * configure.ac: Remove --enable-debug support. 2010-07-27 Paolo Bonzini * configure.ac: Do not use wint_t under Windows, it is useless as it causes a warning when passed to va_arg. 2009-07-12 Paolo Bonzini * snprintfv/dl-yes.c: Delete. * snprintfv/dl-no.c: Delete. * snprintfv/dl.h: Delete. * snprintfv/dl.in: Delete. * snprintfv/dl.stamp: Delete. * snprintfv/ltdl.c: Delete. * snprintfv/ltdl.h: Delete. * snprintfv/printf.c: Delete references to dl.h. 2008-05-16 Paolo Bonzini * snprintf/format.c: Fix bad comment termination, spotted by Bruno Haible. 2006-11-26 Bruce Korb * snprintfv/printf.c (call_argtype_function, parse_printf_format, do_printfv, snv_fdputc): 64-bit cleanliness. 2006-10-23 Paolo Bonzini * snprintf/stream.c (stream_put, stream_puts): Cast printed char to unsigned char. 2006-03-27 Bruce Korb * snprintfv/printf.c: Fix problems with uninitialized memory. 2005-08-30 Paolo Bonzini * snprintfv/Makefile.am: Make more portable. 2003-12-03 Paolo Bonzini * libltdl: die die die * configure.ac: always do the libltdl tests. * snprintfv/ltdl.c: moved from libltdl. * snprintfv/ltdl.h: moved from libltdl. * snprintfv/Makefile.am: put ltdl.c in the library, and ltdl.h in noinst_HEADERS. Death to INCLTDL and LIBLTDL. 2003-07-25 Paolo Bonzini * configure.ac: generate unlocked I/O macros * snprintfv/printf.c: use them 2003-07-24 Paolo Bonzini * snprintfv/format.c: support *n$ notation, merge printf_flag and printf_flag_info, printf_numeric_param and printf_numeric_param_info * snprintfv/printf.c: don't call the formatting function for modifiers because it is now NULL, check this to distinguish modifiers and non-modifiers, save argindex in call_argtype_function, save pointer to the arguments (for printf_numeric_param_info's perusal) into the parser's state. * snprintfv/printf.in: add pointer to the arguments to the parser's state. * tests/Makefile.am: enable width-test 2003-06-19 Paolo Bonzini * snprintfv/format.c: fix %hhd to work on a signed char. 2003-04-18 Paolo Bonzini * snprintfv/format.c: extracted *_generic_* * snprintfv/custom.c: to here * snprintfv/filament.in: change argument of filelt to ssize_t. 2003-04-12 Paolo Bonzini *** Version 1.0 released 2003-03-30 Bruce Korb * snprintfv/filament.in: more ANSIfication * snprintfv/format.c: make all functions explicitly static. 2003-03-25 Paolo Bonzini *** Version 1.0-pre2 released. * snprintfv/filament.c: remove functions * snprintfv/filament.in: turn them into inlines * snprintfv/printf.c: drop support for varargs, ANSIfy * snprintfv/filament.c: ANSIfy * snprintfv/stream.c: ANSIfy * tests/filament-test.c: ANSIfy * tests/piglatin.c: ANSIfy * tests/regress-test.c: ANSIfy * tests/snprintfv-test.c: ANSIfy * tests/stream-test.c: ANSIfy 2003-03-20 Paolo Bonzini *** Version 1.0-pre released. * snprintfv/format.c: clarify error message for things like %2$*s (where the second argument should give the width). 2003-03-19 Paolo Bonzini * snprintfv/format.c: make replacement frexpl/ldexpl static in case some other convenience library defines them, and get rid of strtoul. 2003-03-04 Paolo Bonzini * tests/regress-test.c: added test, suggested by bkorb, for the bug below. 2003-03-02 Bruce Korb * snprintfv/printf.c: fix bug for 64-bit hosts, i.e. where sizeof (int) != sizeof (char *). 2002-12-15 Paolo Bonzini * snprintfv/printf.in: more protection against namespace pollution (*printfv functions) * snprintfv/printf.c: more protection against namespace pollution (*putc functions) * snprintfv/format.c, tests/stream-test.c, tests/snprintfv-test.c: adapt callers 2002-12-14 Paolo Bonzini * snprintfv/stream.c (stream_new): always set get_func and put_func (stream_get, stream_put): don't check for get_func != NULL (stream_not_readable, stream_not_writeable): stub implementation 2002-12-13 Paolo Bonzini * snprintfv/filament.in: define macros equivalent to each filament function. * snprintfv/filament.c: likewise, plus doc fixes. 2002-12-12 Paolo Bonzini *** Version 0.99f released. 2002-12-11 Paolo Bonzini * snprintfv/filament.c: various bug fixes from me or Bruce Korb. * snprintfv/dl-yes.c: new file * snprintfv/dl-no.c: new file * snprintfv/printf.c: call hook in dl-*.c * tests/snprintfv-test.c: remove pig latin modifier * tests/piglatin.c: put it here, in a shared library 2002-12-05 Paolo Bonzini *** Version 0.99d released. 2002-11-25 Paolo Bonzini * snprintfv/format.c: improve handling of boundary floating-point values. * tests/regress-test.c: add floating-point stress tests. 2002-11-20 Paolo Bonzini * configure.ac: detect wint_t * snprintfv/compat.in: don't concatenate literal strings with __PRETTY_FUNCTION__; ERROR_FUNCTION changed SNV_ASSERT_FMT * snprintfv/printf.in: adapt for change to compat.in: printf_error receives all the arguments and builds the error string * snprintfv/printf.c: implement printf_error as above * snprintfv/printf.in (snprintfv, printfv, asprintfv, fprintfv, stream_printfv): accept a snv_constpointer * as the last parameter, not a union printf_arg *. * snprintfv/printf.c (snprintfv, printfv, asprintfv, fprintfv): likewise (do_printfv): new name of the old stream_printfv (stream_printfv): rewritten * snprintfv/snprintfv-test.c (vector_canonicalize): return a snv_constpointer *. Caller adjusted * tests/regress-test.c: add another test. * tests/char-test, tests/count-test, tests/hex-test, tests/octal-test, tests/unsigned-test, tests/width-test: fix incorrect last line 2002-11-19 Paolo Bonzini *** Version 0.99b released. * snprintfv/format.c (call_argtype_function): fix bug, test on spec->modifier_char was inverted * snprintfv/format.c: change overridable to modifier_char * snprintfv/printf.c: likewise * snprintfv/printf.in: likewise * tests/regress-test.c: new test based on bug reported by Bruce Korb. 2002-11-15 Bruce Korb * snprintfv/printf.c (call_argtype_function): initialize the new elements when reallocating the vector 2002-10-25 Paolo Bonzini * snprintfv/format.c: add prototypes for frexpl and ldexpl * snprintfv/compat.in: protect against multiple definitions of "_STR" and "_CONC". 2002-10-17 Paolo Bonzini *** Version 0.99 released. 2002-07-12 Paolo Bonzini * tests/snprintfv-test.c: convert the vector based on the results of parse_printf_format * tests/width-test, tests/exponent-test, tests/float-test, tests/gfloat-test, tests/char-test, tests/octal-test, tests/hex-test: more tests from Gary V. Vaughan 2002-07-11 Paolo Bonzini * snprintfv/format.c: added %n 2002-07-09 Paolo Bonzini * snprintfv/format.c: second round of glibc compatibility, split formatting function and argument-parsing functions * snprintfv/list.c: removed * snprintfv/list.in: removed * snprintfv/snprintfv.c: renamed to printf.c * snprintfv/snprintfv.in: renamed to printf.in * snprintfv/stream.c: return 1 if the stream is full * tests/snprintfv-test.c: don't print past buflen characters. * tests/limit-test: adjusted * tests/stream-test.c: adjusted 2002-07-03 Paolo Bonzini * snprintfv/format.c: added %p; showsign flag reserves a place for the sign at the expense of the width. 2002-06-27 Paolo Bonzini * snprintfv/format.c: don't try to format the arguments when all we are interested in is their types. Add more state to printf_info instead of passing it through handler parameters * snprintfv/snprintfv.c: document passing a NULL stream to stream_*. * snprintfv/snprintfv.in: don't declare DEFINE/DECLARE macros anymore, we only have three parameters now. * tests/hex-test: test %x and %X. 2002-06-27 Paolo Bonzini * snprintfv/register.in: adopt the fields in glibc's struct printf_info and PA_ instead of SNV_, moved to snprintfv.in * snprintfv/format.c: use the new fields instead of parser data and PA_ instead of SNV_. * snprintfv/snprintfv.c: initialize some of the new fields and use PA_ instead of SNV_. Added parse_printf_format and related helper functions. parser_argtype_renew now called argtype_renew and made static. * tests/snprintfv-test.c: use PA_ instead of SNV_. 2002-06-26 Paolo Bonzini * snprintfv/format.c: a lot of changes including support for %[eEfFgG], snv_generic_specifier_modifier and long longs. * snprintfv/compat.in: define intmax_t and uintmax_t. * snprintfv/snprintfv.c: asprintf compatible with GNU libc; support long longs; support user data in custom handlers * tests/extend-test: new test case * tests/snprintfv-test.c: test extensibility via the pig-latin modifier %P. 2001-08-11 Bruce Korb * snprintfv/format.c: fix unimportant uninitialized variable * snprintfv/snprintfv.c: Do not allocate longs in value array * test/Makefile.am: add hex-test and cleanup scripts * test/test-cleanup: clean up the dinkleberries when done 2001-08-08 Gary V. Vaughan * snprintfv/format.c (fetch_argv_long): Don't let my knowledge that void* is not guaranteed to be large enough to hold an integral type larger than an int leak out into the interface. (fetch_argv_ulong): Ditto. * tests/snprintfv-test.c (vector_canonicalize): Now that the library no longer expects long ints to be stored indirectly, force them into a void* and hope for the best! * README: Confessional. 2001-08-04 Bruce Korb * snprintfv/format.c: broken ptr dereference and unsigned format types are treated as signed. 1998-11-13 Gary V. Vaughan * For hysterical reasons, this is when I first started to write smalltalk-3.2.5/snprintfv/snprintfv/0000755000175000017500000000000012130456003014562 500000000000000smalltalk-3.2.5/snprintfv/snprintfv/printf.c0000644000175000017500000012005012123404352016150 00000000000000/* -*- Mode: C -*- */ /* printf.c --- printf clone for argv arrays * Copyright (C) 1998, 1999, 2000, 2002, 2009 Gary V. Vaughan * Originally by Gary V. Vaughan, 1998 * This file is part of Snprintfv * * Snprintfv is free software; you can redistribute it and/or * modify it under the terms of the GNU General Public License as * published by the Free Software Foundation; either version 2 of the * License, or (at your option) any later version. * * Snprintfv program is distributed in the hope that it will be useful, * but WITHOUT ANY WARRANTY; without even the implied warranty of * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU * General Public License for more details. * * You should have received a copy of the GNU General Public License * along with this program. If not, write to the Free Software * Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * * As a special exception to the GNU General Public License, if you * distribute this file as part of a program that also links with and * uses the libopts library from AutoGen, you may include it under * the same distribution terms used by the libopts library. */ /* Code: */ #ifdef HAVE_CONFIG_H # include #endif #include /* for the write(2) call */ #define COMPILING_PRINTF_C #include "printf.h" #ifdef WITH_DMALLOC #include #endif #include "filament.h" #include "stream.h" #include "mem.h" #define EOS '\0' #define SNV_CHAR_SPEC '%' #define SNV_ESC_SPEC '\\' /* Functions to manage mapping of spec chars to handlers. */ SNV_INLINE unsigned spec_hash (unsigned spec); SNV_INLINE void spec_init (void); SNV_INLINE spec_entry *spec_lookup (unsigned spec); static void spec_insert (spec_entry * pentry); static int do_printfv (STREAM *stream, const char *format, union printf_arg const args[]); /* FIXME: We are assuming an ASCII character set where all the printable characters are between SPACE and DEL. */ #define ASCII_DEL (int)'\177' #define ASCII_SPACE (int)' ' #define IS_MODIFIER(spec) (!((spec)->fmt)) /* TODO: This is not thread-safe. Change the API to pass the spec_table in as the first parameter to the functions which use it? */ static spec_entry *spec_table[ASCII_DEL - ASCII_SPACE]; /* TODO: This is not thread-safe as well. */ static char *printf_last_error; SNV_INLINE unsigned spec_hash (unsigned spec) { return (spec & ASCII_DEL) - ASCII_SPACE; } /* Register all of the functions in INIT_SPEC_TABLE. */ static void spec_init (void) { static boolean is_init = FALSE; if (!is_init) { extern spec_entry snv_default_spec_table[]; unsigned index = 0; memset (spec_table, 0, sizeof (spec_table)); while (snv_default_spec_table[index].spec != EOS) { unsigned hash = spec_hash (snv_default_spec_table[index].spec); spec_table[hash] = snv_default_spec_table + index; index++; } is_init = TRUE; } } /* Insert PENTRY, a new handler, into SPEC_TABLE. */ SNV_INLINE void spec_insert (spec_entry *pentry) { unsigned hash = spec_hash (pentry->spec); spec_init (); spec_table[hash] = pentry; } /* Lookup and return the SPEC_TABLE entry for SPEC. */ SNV_INLINE spec_entry * spec_lookup (unsigned spec) { unsigned hash = spec_hash (spec); spec_init (); return spec_table[hash]; } /** * register_printf_function: printf.h * @spec: the character which will trigger @func, cast to an unsigned int. * @fmt: the handler function to actually print the arguments to the specifier * @arg: the handler function to tell %printf about the types of the arguments to the specifier * * Register the pair made of @fmt and @arg, so that it is called * when @spec is encountered in a format string. * * Return value: * Returns %NULL if @func was not successfully registered, a * %spec_entry with the information on the function if it was. **/ spec_entry * register_printf_function (unsigned spec, printf_function *fmt, printf_arginfo_function *arg) { spec_entry *new, *old; old = spec_lookup (spec); if (old && IS_MODIFIER (old)) return NULL; if (!fmt || !spec) return NULL; new = snv_new (spec_entry, 1); new->spec = spec; new->fmt = fmt; new->arg = arg; new->user = NULL; spec_insert (new); return new; } static int call_argtype_function (struct printf_info *const pinfo, int **argtypes, spec_entry *spec) { int n; int argindex = (pinfo->dollar && !IS_MODIFIER (spec)) ? pinfo->dollar - 1 : pinfo->argindex; int save_argindex = pinfo->argindex; int save_state = pinfo->state; char const *save_format = pinfo->format; if (!spec->arg) { n = 1; if (pinfo->argc <= argindex) { /* * "argtypes" points to a pointer of an array of int values. * Here, we ensure that there are "argindex + 1" entries in * that array. */ *argtypes = snv_renew (int, *argtypes, argindex + 1); /* * IF there are more entries that follow the current argument * index, then we will clobber all the entries that follow. * The size of these entries is the size of the array elements, * not the size of the pointer to the array elements. */ if (pinfo->argc < argindex) memset(*argtypes + pinfo->argc, PA_UNKNOWN, (argindex - pinfo->argc) * sizeof(**argtypes)); pinfo->argc = argindex + 1; } (*argtypes) [argindex] = spec->type; } else { pinfo->spec = *pinfo->format; pinfo->extra = spec->user; pinfo->type = spec->type; if (pinfo->argc > argindex) n = spec->arg(pinfo, (size_t) (pinfo->argc - argindex), *argtypes + argindex); else n = spec->arg(pinfo, (size_t) 0, NULL); if (n < 0) return n; if (argindex + n > pinfo->argc) { int new_ct = argindex + n; *argtypes = snv_renew (int, *argtypes, new_ct); memset(*argtypes + pinfo->argc, PA_UNKNOWN, (new_ct - pinfo->argc) * sizeof(**argtypes)); pinfo->argc = argindex + n; /* Call again... */ pinfo->argindex = save_argindex; pinfo->format = save_format; pinfo->state = save_state; pinfo->spec = *pinfo->format; pinfo->extra = spec->user; pinfo->type = spec->type; n = spec->arg(pinfo, (size_t)n, *argtypes + argindex); } } if (!pinfo->dollar && !IS_MODIFIER (spec)) pinfo->argindex += n; return n; } /** * printf_strerror: printf.h * * Communicate information on the last error in a printf * format string. * * Return value: * A string describing the last error which occurred during the * parsing of a printf format string. It is the responsibility * of the caller to free the string. */ char * printf_strerror (void) { return snv_strdup(printf_last_error); } /* (re)initialise the memory used by PPARSER. */ static inline void parser_init (struct printf_info *pinfo, const char *format, const union printf_arg *args) { memset (pinfo, 0, sizeof (struct printf_info)); pinfo->format = format; pinfo->args = args; } static inline struct printf_info * parser_reset (struct printf_info *pinfo) { pinfo->is_long_double = pinfo->is_char = pinfo->is_short = pinfo->is_long = pinfo->alt = pinfo->space = pinfo->left = pinfo->showsign = pinfo->group = pinfo->wide = pinfo->width = pinfo->spec = 0; pinfo->state = SNV_STATE_BEGIN; pinfo->prec = -1; pinfo->dollar = 0; pinfo->pad = ' '; return pinfo; } /** * printf_error: printf.h * @pinfo: pointer to the current parser state. * @file: file where error was detected. * @line: line where error was detected. * @func1: " (" if function is supplied by compiler. * @func2: function where error was detected, if supplied by compiler. * @func3: ")" if function is supplied by compiler. * @error_message: new error message to append to @pinfo. * * The contents of @error_message are appended to the @pinfo internal * error string, so it is safe to pass static strings or recycle the * original when this function returns. * * Return value: * The address of the full accumulated error message in @pinfo is * returned. **/ char * printf_error (struct printf_info *pinfo, const char *file, int line, const char *func1, const char *func2, const char *func3, const char *error_message) { int i; char *result; if (pinfo->error == NULL) pinfo->error = filnew (NULL, 0); else filccat (pinfo->error, '\n'); /* Cannot use printf because a bug in it might trigger another printf_error! */ result = filcat (pinfo->error, "file "); filcat (pinfo->error, file); filcat (pinfo->error, ": line "); for (i = 10; i <= line; i *= 10); for (i /= 10; i >= 1; i /= 10) filccat (pinfo->error, '0' + (line / i) % 10); filcat (pinfo->error, func1); filcat (pinfo->error, func2); filcat (pinfo->error, func3); filcat (pinfo->error, ": "); filcat (pinfo->error, error_message); return result; } /** * parse_printf_format: printf.h * @format: a % delimited format string. * @n: the size of the @argtypes vector * @argtypes: a vector of ints, to be filled with the argument types from @format * * Returns information about the number and types of * arguments expected by the template string @format. * The argument @n specifies the number of elements in the array * @argtypes. This is the maximum number of elements that * the function will try to write. * * Return value: * The total number of arguments required by @format. If this * number is greater than @n, then the information returned * describes only the first @n arguments. If you want information * about additional arguments, allocate a bigger array and call * this function again. If there is an error, then %SNV_ERROR * is returned instead. **/ size_t parse_printf_format (const char *format, int n, int *argtypes) { struct printf_info info; return_val_if_fail (format != NULL, -1); parser_init (&info, format, NULL); while (*info.format != EOS) { int ch = (int) *info.format++; switch (ch) { case SNV_CHAR_SPEC: if (*info.format != SNV_CHAR_SPEC) { /* We found the start of a format specifier! */ spec_entry *spec; int status; int argindex; parser_reset (&info); do { /* Until we fill the stream (or get some other exception) or one of the handlers tells us we have reached the end of the specifier... */ /* ...lookup the handler associated with the char we are looking at in the format string... */ spec = spec_lookup (*info.format); if (spec == NULL) { PRINTF_ERROR (&info, "unregistered specifier"); goto error; } if (!IS_MODIFIER (spec) && !(info.state & (SNV_STATE_BEGIN | SNV_STATE_SPECIFIER))) { PRINTF_ERROR (&info, "invalid combination of flags"); goto error; } argindex = info.dollar && !IS_MODIFIER (spec) ? info.dollar - 1 : info.argindex; /* ...and call the relevant handler. */ if (spec->arg) { info.spec = *info.format; info.extra = spec->user; info.type = spec->type; status = (*spec->arg) (&info, (size_t) (n - argindex), argtypes + argindex); } else { status = 1; if (n > argindex) argtypes[argindex] = spec->type; } if (status < 0) goto error; info.argc = MAX (info.argc, argindex + status); if (!info.dollar && !IS_MODIFIER (spec)) info.argindex += status; info.format++; } while (IS_MODIFIER (spec)); continue; } /* An escaped CHAR_SPEC: ignore it (by falling through). */ ++info.format; /*NOBREAK*/ default: /* Just a character: ignore it. */ continue; } error: /* Get here on error */ info.argc = -1; break; } if (printf_last_error) snv_delete (printf_last_error); if (info.error) printf_last_error = fildelete (info.error); else printf_last_error = NULL; return info.argc; } int do_printfv (STREAM *stream, const char *format, union printf_arg const args[]) { struct printf_info info; /* This is the parser driver. Here we scan through the format string and move bytes into the stream and call handlers based on the parser state. */ parser_init (&info, format, args); /* Keep going until the format string runs out! */ while (*info.format != EOS) { int ch = (int) *info.format++; switch (ch) { case SNV_CHAR_SPEC: if (*info.format != SNV_CHAR_SPEC) { /* We found the start of a format specifier! */ spec_entry *spec; int status, argindex; parser_reset (&info); do { /* Until we fill the stream (or get some other exception) or one of the handlers tells us we have reached the end of the specifier... */ /* ...lookup the handler associated with the char we are looking at in the format string... */ spec = spec_lookup (*info.format); if (spec == NULL) { PRINTF_ERROR (&info, "unregistered specifier"); goto error; } if (!IS_MODIFIER (spec) && !(info.state & (SNV_STATE_BEGIN | SNV_STATE_SPECIFIER))) { PRINTF_ERROR (&info, "invalid combination of flags"); goto error; } /* ...and call the relevant handler. */ info.spec = *info.format; info.extra = spec->user; info.type = spec->type; status = spec->arg ? (*spec->arg) (&info, (size_t)0, NULL) : 1; if (status < 0) goto error; argindex = info.dollar && !IS_MODIFIER (spec) ? info.dollar - 1 : info.argindex; info.format++; info.argc = MAX (info.argc, argindex + status); if (!info.dollar && !IS_MODIFIER (spec)) info.argindex += status; } while (info.count >= 0 && IS_MODIFIER (spec)); status = (*spec->fmt) (stream, &info, args + argindex); if (status < 0) goto error; info.count += status; continue; } /* An escaped CHAR_SPEC: ignore it (by falling through). */ ++info.format; /*NOBREAK*/ default: /* Just a character: ignore it. */ /* Just a character: copy it. */ SNV_EMIT (ch, stream, info.count); continue; } error: /* Get here on error */ info.count = -1; break; } if (printf_last_error) snv_delete (printf_last_error); if (info.error) printf_last_error = fildelete (info.error); else printf_last_error = NULL; return info.count; } /** * stream_printfv: printf.h * @stream: an initialised stream structure. * @format: a % delimited format string. * @args: a vector of argument addresses to match @format. * * Format the elements of @args according to @format, and write * the results to @stream. If @stream is %NULL, only count the * number of characters needed to output the format. * * Return value: * The number of characters written is returned, unless there is * an error, when %SNV_ERROR is returned. **/ int stream_printfv (STREAM *stream, const char *format, snv_constpointer const *ap) { union printf_arg *args; struct printf_info info; int count_or_errorcode; int *argtypes = NULL; return_val_if_fail (format != NULL, SNV_ERROR); parser_init (&info, format, NULL); while (*info.format != EOS) { int ch = (int) *info.format++; switch (ch) { case SNV_CHAR_SPEC: if (*info.format != SNV_CHAR_SPEC) { /* We found the start of a format specifier! */ spec_entry *spec; parser_reset (&info); do { /* Until we fill the stream (or get some other exception) or one of the handlers tells us we have reached the end of the specifier... */ /* ...lookup the handler associated with the char we are looking at in the format string... */ spec = spec_lookup (*info.format); if (spec == NULL) { PRINTF_ERROR (&info, "unregistered specifier"); goto error; } if (!IS_MODIFIER (spec) && !(info.state & (SNV_STATE_BEGIN | SNV_STATE_SPECIFIER))) { PRINTF_ERROR (&info, "invalid combination of flags"); goto error; } /* ...and call the relevant handler. */ if (call_argtype_function (&info, &argtypes, spec) < 0) goto error; info.format++; } while (info.count >= 0 && IS_MODIFIER (spec)); continue; } /* An escaped CHAR_SPEC: ignore it (by falling through). */ ++info.format; /*NOBREAK*/ default: /* Just a character: ignore it. */ continue; } error: /* Get here on error */ info.argc = -1; break; } if (info.argc > 0) { int index; args = snv_new (union printf_arg, info.argc); /* We scanned the format string to find the type of the arguments, so we can now cast it and store it correctly. */ for (index = 0; index < info.argc; index++) { int tp = argtypes[index]; if ((tp & PA_TYPE_MASK) == PA_TYPE_MASK) { if (index + 1 == info.argc) info.argc--; else continue; } switch (tp & ~PA_FLAG_UNSIGNED) { case PA_CHAR: args[index].pa_char = (char) *(const long int *)(ap + index); break; case PA_WCHAR: args[index].pa_wchar = (snv_wchar_t) *(const long int *)(ap + index); break; case PA_INT|PA_FLAG_SHORT: args[index].pa_short_int = (short int) *(const long int *)(ap + index); break; case PA_INT: args[index].pa_int = (int) *(const long int *)(ap + index); break; case PA_INT|PA_FLAG_LONG: args[index].pa_long_int = *(const long int *)(ap + index); break; case PA_INT|PA_FLAG_LONG_LONG: args[index].pa_long_long_int = **(const intmax_t **)(ap + index); break; case PA_FLOAT: args[index].pa_float = **(const float **)(ap + index); break; case PA_DOUBLE|PA_FLAG_LONG_DOUBLE: #ifdef HAVE_LONG_DOUBLE args[index].pa_long_double = **(const long double **)(ap + index); break; #endif /* else fall through */ case PA_DOUBLE: args[index].pa_double = **(const double **)(ap + index); break; /* Note that pointer types are dereferenced just once! */ case PA_STRING: args[index].pa_string = *(const char **)(ap + index); break; case PA_WSTRING: args[index].pa_wstring = *(const snv_wchar_t **)(ap + index); break; case PA_POINTER: args[index].pa_pointer = *(snv_constpointer *)(ap + index); break; default: if (argtypes[index] & PA_FLAG_PTR) args[index].pa_pointer = *(snv_constpointer *)(ap + index); else args[index].pa_long_double = 0.0; break; } } } if (printf_last_error) snv_delete (printf_last_error); if (info.error) printf_last_error = fildelete (info.error); else printf_last_error = NULL; count_or_errorcode = do_printfv (stream, format, args); snv_delete (argtypes); if (info.argc > 0) snv_delete (args); return count_or_errorcode; } /** * stream_vprintf: printf.h * @stream: an initialised stream structure. * @format: a % delimited format string. * @ap: a varargs/stdargs va_list. * * Format the elements of @ap according to @format, and write * the results to @stream. If @stream is %NULL, only count the * number of characters needed to output the format. * * Return value: * The number of characters written is returned, unless there is * an error, when %SNV_ERROR is returned. **/ int stream_vprintf (STREAM *stream, const char *format, va_list ap) { union printf_arg *args = NULL; struct printf_info info; int count_or_errorcode; int *argtypes = NULL; return_val_if_fail (format != NULL, SNV_ERROR); parser_init (&info, format, NULL); while (*info.format != EOS) { int ch = (int) *info.format++; switch (ch) { case SNV_CHAR_SPEC: if (*info.format != SNV_CHAR_SPEC) { /* We found the start of a format specifier! */ spec_entry *spec; parser_reset (&info); do { /* Until we fill the stream (or get some other exception) or one of the handlers tells us we have reached the end of the specifier... */ /* ...lookup the handler associated with the char we are looking at in the format string... */ spec = spec_lookup (*info.format); if (spec == NULL) { PRINTF_ERROR (&info, "unregistered specifier"); goto error; } if (!IS_MODIFIER (spec) && !(info.state & (SNV_STATE_BEGIN | SNV_STATE_SPECIFIER))) { PRINTF_ERROR (&info, "invalid combination of flags"); goto error; } /* ...and call the relevant handler. */ if (call_argtype_function (&info, &argtypes, spec) < 0) goto error; info.format++; } while (info.count >= 0 && IS_MODIFIER (spec)); continue; } /* An escaped CHAR_SPEC: ignore it (by falling through). */ ++info.format; /*NOBREAK*/ default: /* Just a character: ignore it. */ continue; } error: /* Get here on error */ info.argc = -1; break; } if (info.argc > 0) { int index; args = snv_new (union printf_arg, info.argc); /* Scan the format string to find the type of the argument so we can cast it and store it correctly. Note that according to the ISO C standards, standard type promotion takes place on any variadic arguments as they are aligned on the call stack, and so it is these promoted types that we must extract with the va_arg() macro, or the alignment gets all messed up. Thanks to Robert Lipe for explaining all this to me. */ for (index = 0; index < info.argc; index++) switch (argtypes[index] & ~PA_FLAG_UNSIGNED) { case PA_CHAR: args[index].pa_char = va_arg (ap, int); /* Promoted. */ break; case PA_WCHAR: args[index].pa_wchar = va_arg (ap, snv_wint_t); /* Promoted. */ break; case PA_INT|PA_FLAG_SHORT: args[index].pa_short_int = va_arg (ap, int); /* Promoted. */ break; case PA_INT: args[index].pa_int = va_arg (ap, int); break; case PA_INT|PA_FLAG_LONG: args[index].pa_long_int = va_arg (ap, long int); break; case PA_INT|PA_FLAG_LONG_LONG: args[index].pa_long_long_int = va_arg (ap, intmax_t); break; case PA_FLOAT: args[index].pa_float = va_arg (ap, double); /* Promoted. */ break; case PA_DOUBLE|PA_FLAG_LONG_DOUBLE: args[index].pa_long_double = va_arg (ap, long double); break; case PA_DOUBLE: args[index].pa_double = va_arg (ap, double); break; case PA_STRING: args[index].pa_string = va_arg (ap, const char *); break; case PA_WSTRING: args[index].pa_wstring = va_arg (ap, const snv_wchar_t *); break; case PA_POINTER: args[index].pa_pointer = va_arg (ap, void *); break; default: if (argtypes[index] & PA_FLAG_PTR) args[index].pa_pointer = va_arg (ap, void *); else args[index].pa_long_double = 0.0; break; } } if (printf_last_error) snv_delete (printf_last_error); if (info.error) printf_last_error = fildelete (info.error); else printf_last_error = NULL; count_or_errorcode = do_printfv (stream, format, args); snv_delete (argtypes); snv_delete (args); return count_or_errorcode; } /** * stream_printf: printf.h * @stream: an initialised stream structure. * @format: a % delimited format string. * @va_alist: a varargs/stdargs va_list. * * Format the elements of @va_alist according to @format, and write * the results to @stream. If @stream is %NULL, only count the * number of characters needed to output the format. * * Return value: * The number of characters written is returned, unless there is * an error, when %SNV_ERROR is returned. **/ int stream_printf (STREAM * stream, const char *format, ...) { int count_or_errorcode; va_list ap; va_start (ap, format); count_or_errorcode = stream_vprintf (stream, format, ap); va_end (ap); return count_or_errorcode; } /* Finally... the main API implementation: */ /** * snv_fdputc: printf.h * @ch: A single character to be added to @stream. * @stream: The stream in which to write @ch. * * A StreamPut function for use in putting characters * into STREAMs holding a file descriptor. * * Return value: * The value of @ch that has been put in @stream, or -1 in case of * an error (errno will be set to indicate the type of error). **/ int snv_fdputc (int ch, STREAM *stream) { static char buf[1] = { 0 }; buf[0] = (char) ch; return write ((int) SNV_POINTER_TO_INT (stream_details (stream)), buf, 1) ? ch : -1; } /** * snv_dprintf: printf.h * @fd: an open file descriptor. * @format: a % delimited format string. * @va_alist: a varargs/stdargs va_list. * * Format the elements of @va_alist according to @format, and write * the results to the file descriptor @fd. * * Return value: * The number of characters written is returned, unless there is * an error, when %SNV_ERROR is returned. **/ int snv_dprintf (int fd, const char *format, ...) { int count_or_errorcode; va_list ap; va_start (ap, format); count_or_errorcode = snv_vdprintf (fd, format, ap); va_end (ap); return count_or_errorcode; } /** * snv_vdprintf: printf.h * @fd: an open file descriptor. * @format: a % delimited format string. * @ap: a varargs/stdargs va_list. * * Format the elements of @ap according to @format, and write * the results to the file descriptor @fd. * * Return value: * The number of characters written is returned, unless there is * an error, when %SNV_ERROR is returned. **/ int snv_vdprintf (int fd, const char *format, va_list ap) { int result; STREAM *out = stream_new (SNV_INT_TO_POINTER (fd), SNV_UNLIMITED, NULL, snv_fdputc); result = stream_vprintf (out, format, ap); stream_delete (out); return result; } /** * snv_dprintfv: printf.h * @fd: an open file descriptor. * @format: a % delimited format string. * @args: a vector of argument addresses to match @format. * * Format the elements of @args according to @format, and write * the results to file descriptor @fd. * * Return value: * The number of characters written is returned, unless there is * an error, when %SNV_ERROR is returned. **/ int snv_dprintfv (int fd, const char *format, snv_constpointer const args[]) { int result; STREAM *out = stream_new (SNV_INT_TO_POINTER (fd), SNV_UNLIMITED, NULL, snv_fdputc); result = stream_printfv (out, format, args); stream_delete (out); return result; } /** * snv_fileputc: printf.h * @ch: A single character to be added to @stream. * @stream: The stream in which to write @ch. * * A StreamPut function for use in putting characters * into STREAMs holding a FILE*. * * Return value: * The value of @ch that has been put in @stream. **/ int snv_fileputc (int ch, STREAM *stream) { FILE *fp = (FILE *) stream_details (stream); return putc (ch, fp); } static int snv_fileputc_unlocked (int ch, STREAM *stream) { FILE *fp = (FILE *) stream_details (stream); return SNV_PUTC_UNLOCKED (ch, fp); } /** * snv_printf: printf.h * @format: a % delimited format string. * @va_alist: a varargs/stdargs va_list. * * Format the elements of @va_alist according to @format, and write * the results to the standard output stream. * * Return value: * The number of characters written is returned, unless there is * an error, when %SNV_ERROR is returned. **/ int snv_printf (const char *format, ...) { int count_or_errorcode; va_list ap; va_start (ap, format); count_or_errorcode = snv_vprintf (format, ap); va_end (ap); return count_or_errorcode; } /** * snv_vprintf: printf.h * @format: a % delimited format string. * @ap: a varargs/stdargs va_list. * * Format the elements of @ap according to @format, and write * the results to the standard output stream. * * Return value: * The number of characters written is returned, unless there is * an error, when %SNV_ERROR is returned. **/ int snv_vprintf (const char *format, va_list ap) { int result; STREAM *out = stream_new (stdout, SNV_UNLIMITED, NULL, snv_fileputc_unlocked); int tmp; SNV_WITH_LOCKED_FP (stdout, tmp) result = stream_vprintf (out, format, ap); stream_delete (out); return result; } /** * snv_printfv: printf.h * @format: a % delimited format string. * @args: a vector of argument addresses to match @format. * * Format the elements of @args according to the string @format, * and write the result to the standard output stream. * * Return value: * The number of characters written is returned, unless there is * an error, when %SNV_ERROR is returned. **/ int snv_printfv (const char *format, snv_constpointer const args[]) { int result; STREAM *out = stream_new (stdout, SNV_UNLIMITED, NULL, snv_fileputc_unlocked); int tmp; SNV_WITH_LOCKED_FP (stdout, tmp) result = stream_printfv (out, format, args); stream_delete (out); return result; } /** * snv_fprintf: printf.h * @file: a stdio.h FILE* stream. * @format: a % delimited format string. * @va_alist: a varargs/stdargs va_list. * * Format the elements of @va_alist according to @format, and write * the results to the @file stream. * * Return value: * The number of characters written is returned, unless there is * an error, when %SNV_ERROR is returned. **/ int snv_fprintf (FILE * file, const char *format, ...) { int count_or_errorcode; va_list ap; va_start (ap, format); count_or_errorcode = snv_vfprintf (file, format, ap); va_end (ap); return count_or_errorcode; } /** * snv_vfprintf: printf.h * @file: a stdio.h FILE* stream. * @format: a % delimited format string. * @ap: a varargs/stdargs va_list. * * Format the elements of @ap according to @format, and write * the results to the @file stream. * * Return value: * The number of characters written is returned, unless there is * an error, when %SNV_ERROR is returned. **/ int snv_vfprintf (FILE *file, const char *format, va_list ap) { int result; STREAM *out = stream_new (file, SNV_UNLIMITED, NULL, snv_fileputc_unlocked); int tmp; SNV_WITH_LOCKED_FP (file, tmp) result = stream_vprintf (out, format, ap); stream_delete (out); return result; } /** * snv_fprintfv: printf.h * @file: a stdio.h FILE* stream. * @format: a % delimited format string. * @args: a vector of argument addresses to match @format. * * Format the elements of @args according to @format, and write * the results to @file. * * Return value: * The number of characters written is returned, unless there is * an error, when %SNV_ERROR is returned. **/ int snv_fprintfv (FILE *file, const char *format, snv_constpointer const args[]) { int result; STREAM *out = stream_new (file, SNV_UNLIMITED, NULL, snv_fileputc_unlocked); int tmp; SNV_WITH_LOCKED_FP (file, tmp) result = stream_printfv (out, format, args); stream_delete (out); return result; } /** * snv_bufputc: printf.h * @ch: A single character to be added to @stream. * @stream: The stream in which to write @ch. * * A StreamPut function for use in putting characters * into STREAMs holding a char buffer. * * Return value: * The value of @ch that has been put in @stream. **/ int snv_bufputc (ch, stream) int ch; STREAM *stream; { char **ppbuffer = (char **) stream_details (stream); **ppbuffer = (char) ch; (*ppbuffer)++; return ch; } /** * snv_sprintf: printf.h * @buffer: a preallocated char* buffer. * @format: a % delimited format string. * @va_alist: a varargs/stdargs va_list. * * Format the elements of @va_alist according to @format, and write * the results to the string @buffer. * * Return value: * The number of characters written is returned, unless there is * an error, when %SNV_ERROR is returned. **/ int snv_sprintf (char buffer[], const char *format, ...) { int count_or_errorcode; va_list ap; va_start (ap, format); count_or_errorcode = snv_vsprintf (buffer, format, ap); va_end (ap); return count_or_errorcode; } /** * snv_vsprintf: printf.h * @buffer: a preallocated char* buffer. * @format: a % delimited format string. * @ap: a varargs/stdargs va_list. * * Format the elements of @ap according to @format, and write * the results to the string @buffer. * * Return value: * The number of characters written is returned, unless there is * an error, when %SNV_ERROR is returned. **/ int snv_vsprintf (char buffer[], const char *format, va_list ap) { int count_or_errorcode; STREAM *out = stream_new (&buffer, SNV_UNLIMITED, NULL, snv_bufputc); count_or_errorcode = stream_vprintf (out, format, ap); /* Terminate with an EOS without incrementing the counter. */ stream_put (EOS, out); stream_delete (out); return count_or_errorcode; } /** * snv_sprintfv: printf.h * @buffer: a preallocated char* buffer. * @format: a % delimited format string. * @args: a vector of argument addresses to match @format. * * Format the elements of @args according to @format, and write * the results to the string @buffer. * * Return value: * The number of characters written is returned, unless there is * an error, when %SNV_ERROR is returned. **/ int snv_sprintfv (char buffer[], const char *format, snv_constpointer const args[]) { int count_or_errorcode; STREAM *out = stream_new (&buffer, SNV_UNLIMITED, NULL, snv_bufputc); count_or_errorcode = stream_printfv (out, format, args); /* Terminate with an EOS without incrementing the counter. */ stream_put (EOS, out); stream_delete (out); return count_or_errorcode; } /** * snv_snprintf: printf.h * @buffer: a preallocated char* buffer. * @limit: the maximum number of characters to write into @buffer. * @format: a % delimited format string. * @va_alist: a varargs/stdargs va_list. * * Format the elements of @va_alist according to @format, and write * the results to the string @buffer, truncating the formatted string * if it reaches @limit characters in length. * * Return value: * The number of characters written is returned, unless there is * an error, when %SNV_ERROR is returned. **/ int snv_snprintf (char buffer[], unsigned long limit, const char *format, ...) { int count_or_errorcode; va_list ap; va_start (ap, format); count_or_errorcode = snv_vsnprintf (buffer, limit, format, ap); va_end (ap); return count_or_errorcode; } /** * snv_vsnprintf: printf.h * @buffer: a preallocated char* buffer. * @limit: the maximum number of characters to write into @buffer. * @format: a % delimited format string. * @ap: a varargs/stdargs va_list. * * Format the elements of @ap according to @format, and write * the results to the string @buffer, truncating the formatted string * if it reaches @limit characters in length. * * Return value: * The number of characters written is returned, unless there is * an error, when %SNV_ERROR is returned. **/ int snv_vsnprintf (char buffer[], unsigned long limit, const char *format, va_list ap) { int count_or_errorcode; STREAM *out = stream_new (&buffer, limit - 1, NULL, snv_bufputc); count_or_errorcode = stream_vprintf (out, format, ap); *buffer = EOS; stream_delete (out); return count_or_errorcode; } /** * snv_snprintfv: printf.h * @buffer: a preallocated char* buffer. * @limit: the maximum number of characters to write into @buffer. * @format: a % delimited format string. * @args: a vector of argument addresses to match @format. * * Format the elements of @args according to @format, and write * the results to the string @buffer, truncating the formatted string * if it reaches @limit characters in length. * * Return value: * The number of characters written is returned, unless there is * an error, when %SNV_ERROR is returned. **/ int snv_snprintfv (char buffer[], unsigned long limit, const char *format, snv_constpointer const args[]) { int count_or_errorcode; STREAM *out = stream_new (&buffer, limit - 1, NULL, snv_bufputc); count_or_errorcode = stream_printfv (out, format, args); *buffer = EOS; stream_delete (out); return count_or_errorcode; } /** * snv_filputc: printf.h * @ch: A single character to be added to @stream. * @stream: The stream in which to write @ch. * * A StreamPut function for use in putting characters * into STREAMs holding a Filament*. * * Return value: * The value of @ch that has been put in @stream. **/ int snv_filputc (ch, stream) int ch; STREAM *stream; { return filccat ((Filament *) stream_details (stream), ch), ch; } /** * snv_asprintf: printf.h * @result: the address of a char * variable. * @format: a % delimited format string. * @va_alist: a varargs/stdargs va_list. * * Format the elements of @va_alist according to @format, and write * the results to an internally allocated buffer whose address is * stored in @result (and should be freed by the caller) unless * there is an error. * * Yes, this interface is cumbersome and totally useless. It would * have been better to simply return the allocated address, but * it turns out that somebody wasn't thinking much when adding * asprintf to libiberty a few years ago. * * Return value: * The number of characters written is returned, unless there is * an error, when %SNV_ERROR is returned. **/ int snv_asprintf (char **result, const char *format, ...) { int count; va_list ap; va_start (ap, format); count = snv_vasprintf (result, format, ap); va_end (ap); return count; } /** * snv_vasprintf: printf.h * @result: the address of a char * variable. * @format: a % delimited format string. * @ap: a varargs/stdargs va_list. * * Format the elements of @ap according to @format, and write * the results to an internally allocated buffer whose address is * stored in @result (and should be freed by the caller) unless * there is an error. * * Above moaning for asprintf applies here too. * * Return value: * The number of characters written is returned, unless there is * an error, when %SNV_ERROR is returned. **/ int snv_vasprintf (char **result, const char *format, va_list ap) { int count_or_errorcode; char *base; Filament *fil = filnew (NULL, 0); STREAM *out = stream_new (fil, SNV_UNLIMITED, NULL, snv_filputc); count_or_errorcode = stream_vprintf (out, format, ap); base = fildelete (fil); stream_delete (out); *result = (count_or_errorcode < 0) ? NULL : base; return count_or_errorcode; } /** * snv_asprintfv: printf.h * @result: the address of a char * variable. * @format: a % delimited format string. * @args: a vector of argument addresses to match @format. * * Format the elements of @args according to @format, and write * the results to an internally allocated buffer whose address is * stored in @result (and should be freed by the caller) unless * there is an error. * * Above moaning for asprintf applies here too. * * Return value: * The number of characters written is returned, unless there is * an error, when %SNV_ERROR is returned. **/ int snv_asprintfv (char **result, const char *format, snv_constpointer const args[]) { int count_or_errorcode; char *base; Filament *fil = filnew (NULL, 0); STREAM *out = stream_new (fil, SNV_UNLIMITED, NULL, snv_filputc); count_or_errorcode = stream_printfv (out, format, args); base = fildelete (fil); stream_delete (out); *result = (count_or_errorcode < 0) ? NULL : base; return count_or_errorcode; } /* snprintfv.c ends here */ smalltalk-3.2.5/snprintfv/snprintfv/printf.h0000644000175000017500000006340612123404352016170 00000000000000#line 1 "../../../snprintfv/snprintfv/printf.in" /* -*- Mode: C -*- */ /* printf.in --- printf clone for argv arrays * Copyright (C) 1998, 1999, 2000, 2002 Gary V. Vaughan * Originally by Gary V. Vaughan, 1998 * This file is part of Snprintfv * * Snprintfv is free software; you can redistribute it and/or * modify it under the terms of the GNU General Public License as * published by the Free Software Foundation; either version 2 of the * License, or (at your option) any later version. * * Snprintfv program is distributed in the hope that it will be useful, * but WITHOUT ANY WARRANTY; without even the implied warranty of * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU * General Public License for more details. * * You should have received a copy of the GNU General Public License * along with this program. If not, write to the Free Software * Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * * As a special exception to the GNU General Public License, if you * distribute this file as part of a program that also links with and * uses the libopts library from AutoGen, you may include it under * the same distribution terms used by the libopts library. */ /* Code: */ #ifndef SNPRINTFV_SNPRINTFV_H #define SNPRINTFV_SNPRINTFV_H 1 #include #include #include #include #ifdef HAVE_WCHAR_H # include #endif #ifdef __cplusplus extern "C" { #endif /* The type of each element in the table of printf specifiers. */ struct spec_entry; typedef enum { SNV_ERROR = -1, SNV_OK } snv_status; /* Basic states required by the parser. On initialisation the parser will be in SNV_STATE_BEGIN, and tokens will be parsed by the registered functions until the parser reached SNV_STATE_END. */ #define SNV_STATE_BEGIN 1 #define SNV_STATE_END 0 /* States needed to support: %[$][|\*][.|\*] */ #define SNV_STATE_FLAG (1 << 1) #define SNV_STATE_WIDTH (1 << 2) #define SNV_STATE_PRECISION (1 << 3) #define SNV_STATE_MODIFIER (1 << 4) #define SNV_STATE_SPECIFIER (1 << 5) /* First state available to the user */ #define SNV_STATE_USER_FIRST (1 << 8) /* Mask for states available to the user */ #define SNV_STATE_USER_MASK ~(SNV_STATE_USER_FIRST - 1) typedef struct printf_info { int count; /* accumulated count, or SNV_ERROR */ int state; /* one of the defines above */ Filament *error; /* accumulated error details */ const char *format; /* pointer to format string */ int argc; /* number of arguments used by format */ int argindex; /* number of non-dollar arguments used so far */ int dollar; /* standard parser state, as in glibc */ int prec; /* from this field on, as in glibc */ int width; snv_pointer extra; int type; char spec; char pad; unsigned is_long_double:1; unsigned is_char:1; unsigned is_short:1; unsigned is_long:1; unsigned alt:1; unsigned space:1; unsigned left:1; unsigned showsign:1; unsigned group:1; unsigned wide:1; const union printf_arg *args; } printf_info; /** * printf_arg: * @pa_char: an unsigned %char * @pa_wchar: a %wchar_t * @pa_short_int: a %short integer * @pa_int: an %int * @pa_long_int: a %long integer * @pa_long_long_int: the widest signed integer type in use on the host * @pa_u_short_int: an unsigned %short integer * @pa_u_int: an unsigned %int * @pa_u_long_int: an unsigned %long integer * @pa_u_long_long_int: the widest unsigned integer type in use on the host * @pa_float: a %float * @pa_double: a %double * @pa_long_double: a long %double, or a simple %double if it is the widest floating-point type in use on the host * @pa_string: a %const pointer to %char * @pa_wstring: a %const pointer to %wchar_t * @pa_pointer: a generic pointer * * The various kinds of arguments that can be passed to printf. */ typedef union printf_arg { unsigned char pa_char; snv_wchar_t pa_wchar; short int pa_short_int; int pa_int; long int pa_long_int; intmax_t pa_long_long_int; unsigned short int pa_u_short_int; unsigned int pa_u_int; unsigned long int pa_u_long_int; uintmax_t pa_u_long_long_int; float pa_float; double pa_double; long double pa_long_double; const char *pa_string; const snv_wchar_t *pa_wstring; snv_constpointer pa_pointer; } printf_arg; /** * PRINTF_ERROR: * @pi: A pointer to the current state for the parser * @str: The error message * * Append an error that will be returned by printf_strerror. */ #define PRINTF_ERROR(pi, str) \ printf_error(pi, __FILE__, __LINE__, SNV_ASSERT_FMT, str); typedef int printf_function (STREAM *stream, struct printf_info *pparser, union printf_arg const * args); typedef int printf_arginfo_function (struct printf_info *pparser, size_t n, int *argtypes); /** * spec_entry: * @spec: the specifier character that was matched * @type: when @arg is NULL, the type of the only argument to the specifier * @fmt: the handler function to actually print the arguments to the specifier * @arg: the handler function to tell %printf about the types of the arguments to the specifier * @user: the user data for the specifier, accessible to the handler function * * This is returned by register_printf_function. */ typedef struct spec_entry { int spec; int unused; /* for binary compatibility */ int type; printf_function *fmt; printf_arginfo_function *arg; snv_pointer user; } spec_entry; /** * register_callback_function: printf.h * @spec: the character which will trigger the functions, cast to an unsigned int. * @fmt: the handler function to actually print the arguments to the specifier * @arg: the handler function to tell %printf about the types of the arguments to the specifier * * Register the pair made of @fmt and @arg, so that it is called * when @spec is encountered in a format string. If you create * a shared library with an entry point named * %snv_register_printf_funcs, and put the library in the * search path given by the environment library %LTDL_LIBRARY_PATH, * that entry point will be called when %libsnprintfv is initialized, * passing a pointer to this kind of function (actually, a pointer * to %register_printf_function) to it. This functionality is only * present when the library is installed, not when it is built as * a convenience library. * * Return value: * Returns %NULL if @func was not successfully registered, a * %spec_entry with the information on the function if it was. **/ typedef spec_entry *register_callback_function (unsigned spec, printf_function *func, printf_arginfo_function *arginfo); /* Codes to determine basic types. These values cover all the standard format specifications. Users can add new values after PA_LAST for their own types. */ enum { PA_INT, /* int */ PA_CHAR, /* int, cast to char */ PA_WCHAR, /* wide char */ PA_STRING, /* const char *, a '\0'-terminated string */ PA_WSTRING, /* const snv_wchar_t *, wide character string */ PA_POINTER, /* void * */ PA_FLOAT, /* float */ PA_DOUBLE, /* double */ PA_LAST, PA_UNKNOWN = -1 }; /* Flag bits that can be set in a type. */ #define PA_TYPE_MASK 0x00ff #define PA_FLAG_MASK ~SNV_TYPE_MASK #define PA_FLAG_LONG_LONG (1 << 8) #define PA_FLAG_LONG_DOUBLE PA_FLAG_LONG_LONG #define PA_FLAG_LONG (1 << 9) #define PA_FLAG_SHORT (1 << 10) #define PA_FLAG_UNSIGNED (1 << 11) #define PA_FLAG_CHAR (1 << 12) #define PA_FLAG_PTR (1 << 13) /** * SNV_EMIT: * @ch: the character to be printed * @stream: the stream on which to print * @count: a variable to be updated with the count of printed * characters * * Maintain the count while putting @ch in @stream, also be careful about * handling %NULL stream if the handler is being called purely to count * output size. **/ #define SNV_EMIT(ch, stream, count) \ SNV_STMT_START { \ if (stream) \ { \ if (count >= 0) \ { \ int m_status = stream_put((ch), stream); \ count = m_status < 0 ? m_status : count + m_status; \ } \ } \ else \ { \ (void)(ch); \ count++; \ } \ } SNV_STMT_END #line 269 "../../../snprintfv/snprintfv/printf.in" /** * printf_generic_info: * @pinfo: the current state information for the format * string parser. * @n: the number of available slots in the @argtypes array * @argtypes: the pointer to the first slot to be filled by the * function * * An example implementation of a %printf_arginfo_function, which * takes the basic type from the type given in the %spec_entry * and adds flags depending on what was parsed (e.g. %PA_FLAG_SHORT * is %pparser->is_short and so on). * * Return value: * Always 1. */ extern int printf_generic_info (struct printf_info *const pinfo, size_t n, int *argtypes); /** * printf_generic: * @stream: the stream (possibly a struct printfv_stream appropriately * cast) on which to write output. * @pinfo: the current state information for the format string parser. * @args: the pointer to the first argument to be read by the handler * * An example implementation of a %printf_function, used to provide easy * access to justification, width and precision options. * * Return value: * The number of characters output. **/ extern int printf_generic (STREAM *stream, struct printf_info *const pinfo, union printf_arg const *args); #line 270 "../../../snprintfv/snprintfv/printf.in" /** * register_printf_function: * @spec: the character which will trigger @func, cast to an unsigned int. * @fmt: the handler function to actually print the arguments to the specifier * @arg: the handler function to tell %printf about the types of the arguments to the specifier * * Register the pair made of @fmt and @arg, so that it is called * when @spec is encountered in a format string. * * Return value: * Returns %NULL if @func was not successfully registered, a * %spec_entry with the information on the function if it was. **/ extern spec_entry * register_printf_function (unsigned spec, printf_function *fmt, printf_arginfo_function *arg); /** * printf_strerror: * * Communicate information on the last error in a printf * format string. * * Return value: * A string describing the last error which occurred during the * parsing of a printf format string. It is the responsibility * of the caller to free the string. */ extern char * printf_strerror (void); /** * printf_error: * @pinfo: pointer to the current parser state. * @file: file where error was detected. * @line: line where error was detected. * @func1: " (" if function is supplied by compiler. * @func2: function where error was detected, if supplied by compiler. * @func3: ")" if function is supplied by compiler. * @error_message: new error message to append to @pinfo. * * The contents of @error_message are appended to the @pinfo internal * error string, so it is safe to pass static strings or recycle the * original when this function returns. * * Return value: * The address of the full accumulated error message in @pinfo is * returned. **/ extern char * printf_error (struct printf_info *pinfo, const char *file, int line, const char *func1, const char *func2, const char *func3, const char *error_message); /** * parse_printf_format: * @format: a % delimited format string. * @n: the size of the @argtypes vector * @argtypes: a vector of ints, to be filled with the argument types from @format * * Returns information about the number and types of * arguments expected by the template string @format. * The argument @n specifies the number of elements in the array * @argtypes. This is the maximum number of elements that * the function will try to write. * * Return value: * The total number of arguments required by @format. If this * number is greater than @n, then the information returned * describes only the first @n arguments. If you want information * about additional arguments, allocate a bigger array and call * this function again. If there is an error, then %SNV_ERROR * is returned instead. **/ extern size_t parse_printf_format (const char *format, int n, int *argtypes); /** * stream_printfv: * @stream: an initialised stream structure. * @format: a % delimited format string. * @args: a vector of argument addresses to match @format. * * Format the elements of @args according to @format, and write * the results to @stream. If @stream is %NULL, only count the * number of characters needed to output the format. * * Return value: * The number of characters written is returned, unless there is * an error, when %SNV_ERROR is returned. **/ extern int stream_printfv (STREAM *stream, const char *format, snv_constpointer const *ap); /** * stream_vprintf: * @stream: an initialised stream structure. * @format: a % delimited format string. * @ap: a varargs/stdargs va_list. * * Format the elements of @ap according to @format, and write * the results to @stream. If @stream is %NULL, only count the * number of characters needed to output the format. * * Return value: * The number of characters written is returned, unless there is * an error, when %SNV_ERROR is returned. **/ extern int stream_vprintf (STREAM *stream, const char *format, va_list ap); /** * stream_printf: * @stream: an initialised stream structure. * @format: a % delimited format string. * @va_alist: a varargs/stdargs va_list. * * Format the elements of @va_alist according to @format, and write * the results to @stream. If @stream is %NULL, only count the * number of characters needed to output the format. * * Return value: * The number of characters written is returned, unless there is * an error, when %SNV_ERROR is returned. **/ extern int stream_printf SNV_GNUC_PRINTF((STREAM * stream, const char *format, ...), 2, 3); /** * snv_fdputc: * @ch: A single character to be added to @stream. * @stream: The stream in which to write @ch. * * A StreamPut function for use in putting characters * into STREAMs holding a file descriptor. * * Return value: * The value of @ch that has been put in @stream, or -1 in case of * an error (errno will be set to indicate the type of error). **/ extern int snv_fdputc (int ch, STREAM *stream); /** * snv_dprintf: * @fd: an open file descriptor. * @format: a % delimited format string. * @va_alist: a varargs/stdargs va_list. * * Format the elements of @va_alist according to @format, and write * the results to the file descriptor @fd. * * Return value: * The number of characters written is returned, unless there is * an error, when %SNV_ERROR is returned. **/ extern int snv_dprintf SNV_GNUC_PRINTF((int fd, const char *format, ...), 2, 3); /** * snv_vdprintf: * @fd: an open file descriptor. * @format: a % delimited format string. * @ap: a varargs/stdargs va_list. * * Format the elements of @ap according to @format, and write * the results to the file descriptor @fd. * * Return value: * The number of characters written is returned, unless there is * an error, when %SNV_ERROR is returned. **/ extern int snv_vdprintf (int fd, const char *format, va_list ap); /** * snv_dprintfv: * @fd: an open file descriptor. * @format: a % delimited format string. * @args: a vector of argument addresses to match @format. * * Format the elements of @args according to @format, and write * the results to file descriptor @fd. * * Return value: * The number of characters written is returned, unless there is * an error, when %SNV_ERROR is returned. **/ extern int snv_dprintfv (int fd, const char *format, snv_constpointer const args[]); /** * snv_fileputc: * @ch: A single character to be added to @stream. * @stream: The stream in which to write @ch. * * A StreamPut function for use in putting characters * into STREAMs holding a FILE*. * * Return value: * The value of @ch that has been put in @stream. **/ extern int snv_fileputc (int ch, STREAM *stream); /** * snv_printf: * @format: a % delimited format string. * @va_alist: a varargs/stdargs va_list. * * Format the elements of @va_alist according to @format, and write * the results to the standard output stream. * * Return value: * The number of characters written is returned, unless there is * an error, when %SNV_ERROR is returned. **/ extern int snv_printf SNV_GNUC_PRINTF((const char *format, ...), 1, 2); /** * snv_vprintf: * @format: a % delimited format string. * @ap: a varargs/stdargs va_list. * * Format the elements of @ap according to @format, and write * the results to the standard output stream. * * Return value: * The number of characters written is returned, unless there is * an error, when %SNV_ERROR is returned. **/ extern int snv_vprintf (const char *format, va_list ap); /** * snv_printfv: * @format: a % delimited format string. * @args: a vector of argument addresses to match @format. * * Format the elements of @args according to the string @format, * and write the result to the standard output stream. * * Return value: * The number of characters written is returned, unless there is * an error, when %SNV_ERROR is returned. **/ extern int snv_printfv (const char *format, snv_constpointer const args[]); /** * snv_fprintf: * @file: a stdio.h FILE* stream. * @format: a % delimited format string. * @va_alist: a varargs/stdargs va_list. * * Format the elements of @va_alist according to @format, and write * the results to the @file stream. * * Return value: * The number of characters written is returned, unless there is * an error, when %SNV_ERROR is returned. **/ extern int snv_fprintf SNV_GNUC_PRINTF((FILE * file, const char *format, ...), 2, 3); /** * snv_vfprintf: * @file: a stdio.h FILE* stream. * @format: a % delimited format string. * @ap: a varargs/stdargs va_list. * * Format the elements of @ap according to @format, and write * the results to the @file stream. * * Return value: * The number of characters written is returned, unless there is * an error, when %SNV_ERROR is returned. **/ extern int snv_vfprintf (FILE *file, const char *format, va_list ap); /** * snv_fprintfv: * @file: a stdio.h FILE* stream. * @format: a % delimited format string. * @args: a vector of argument addresses to match @format. * * Format the elements of @args according to @format, and write * the results to @file. * * Return value: * The number of characters written is returned, unless there is * an error, when %SNV_ERROR is returned. **/ extern int snv_fprintfv (FILE *file, const char *format, snv_constpointer const args[]); /** * snv_bufputc: * @ch: A single character to be added to @stream. * @stream: The stream in which to write @ch. * * A StreamPut function for use in putting characters * into STREAMs holding a char buffer. * * Return value: * The value of @ch that has been put in @stream. **/ extern int snv_bufputc (int ch, STREAM *stream); /** * snv_sprintf: * @buffer: a preallocated char* buffer. * @format: a % delimited format string. * @va_alist: a varargs/stdargs va_list. * * Format the elements of @va_alist according to @format, and write * the results to the string @buffer. * * Return value: * The number of characters written is returned, unless there is * an error, when %SNV_ERROR is returned. **/ extern int snv_sprintf SNV_GNUC_PRINTF((char buffer[], const char *format, ...), 2, 3); /** * snv_vsprintf: * @buffer: a preallocated char* buffer. * @format: a % delimited format string. * @ap: a varargs/stdargs va_list. * * Format the elements of @ap according to @format, and write * the results to the string @buffer. * * Return value: * The number of characters written is returned, unless there is * an error, when %SNV_ERROR is returned. **/ extern int snv_vsprintf (char buffer[], const char *format, va_list ap); /** * snv_sprintfv: * @buffer: a preallocated char* buffer. * @format: a % delimited format string. * @args: a vector of argument addresses to match @format. * * Format the elements of @args according to @format, and write * the results to the string @buffer. * * Return value: * The number of characters written is returned, unless there is * an error, when %SNV_ERROR is returned. **/ extern int snv_sprintfv (char buffer[], const char *format, snv_constpointer const args[]); /** * snv_snprintf: * @buffer: a preallocated char* buffer. * @limit: the maximum number of characters to write into @buffer. * @format: a % delimited format string. * @va_alist: a varargs/stdargs va_list. * * Format the elements of @va_alist according to @format, and write * the results to the string @buffer, truncating the formatted string * if it reaches @limit characters in length. * * Return value: * The number of characters written is returned, unless there is * an error, when %SNV_ERROR is returned. **/ extern int snv_snprintf SNV_GNUC_PRINTF((char buffer[], unsigned long limit, const char *format, ...), 3, 4); /** * snv_vsnprintf: * @buffer: a preallocated char* buffer. * @limit: the maximum number of characters to write into @buffer. * @format: a % delimited format string. * @ap: a varargs/stdargs va_list. * * Format the elements of @ap according to @format, and write * the results to the string @buffer, truncating the formatted string * if it reaches @limit characters in length. * * Return value: * The number of characters written is returned, unless there is * an error, when %SNV_ERROR is returned. **/ extern int snv_vsnprintf (char buffer[], unsigned long limit, const char *format, va_list ap); /** * snv_snprintfv: * @buffer: a preallocated char* buffer. * @limit: the maximum number of characters to write into @buffer. * @format: a % delimited format string. * @args: a vector of argument addresses to match @format. * * Format the elements of @args according to @format, and write * the results to the string @buffer, truncating the formatted string * if it reaches @limit characters in length. * * Return value: * The number of characters written is returned, unless there is * an error, when %SNV_ERROR is returned. **/ extern int snv_snprintfv (char buffer[], unsigned long limit, const char *format, snv_constpointer const args[]); /** * snv_filputc: * @ch: A single character to be added to @stream. * @stream: The stream in which to write @ch. * * A StreamPut function for use in putting characters * into STREAMs holding a Filament*. * * Return value: * The value of @ch that has been put in @stream. **/ extern int snv_filputc (int ch, STREAM *stream); /** * snv_asprintf: * @result: the address of a char * variable. * @format: a % delimited format string. * @va_alist: a varargs/stdargs va_list. * * Format the elements of @va_alist according to @format, and write * the results to an internally allocated buffer whose address is * stored in @result (and should be freed by the caller) unless * there is an error. * * Yes, this interface is cumbersome and totally useless. It would * have been better to simply return the allocated address, but * it turns out that somebody wasn't thinking much when adding * asprintf to libiberty a few years ago. * * Return value: * The number of characters written is returned, unless there is * an error, when %SNV_ERROR is returned. **/ extern int snv_asprintf SNV_GNUC_PRINTF((char **result, const char *format, ...), 2, 3); /** * snv_vasprintf: * @result: the address of a char * variable. * @format: a % delimited format string. * @ap: a varargs/stdargs va_list. * * Format the elements of @ap according to @format, and write * the results to an internally allocated buffer whose address is * stored in @result (and should be freed by the caller) unless * there is an error. * * Above moaning for asprintf applies here too. * * Return value: * The number of characters written is returned, unless there is * an error, when %SNV_ERROR is returned. **/ extern int snv_vasprintf (char **result, const char *format, va_list ap); /** * snv_asprintfv: * @result: the address of a char * variable. * @format: a % delimited format string. * @args: a vector of argument addresses to match @format. * * Format the elements of @args according to @format, and write * the results to an internally allocated buffer whose address is * stored in @result (and should be freed by the caller) unless * there is an error. * * Above moaning for asprintf applies here too. * * Return value: * The number of characters written is returned, unless there is * an error, when %SNV_ERROR is returned. **/ extern int snv_asprintfv (char **result, const char *format, snv_constpointer const args[]); #line 271 "../../../snprintfv/snprintfv/printf.in" /* If you don't want to use snprintfv functions for *all* of your string formatting API, then define COMPILING_SNPRINTFV_C and use the snv_ prefix for the entry points below. */ #ifndef COMPILING_PRINTF_C #undef printf #undef vprintf #undef dprintf #undef vdprintf #undef fprintf #undef vfprintf #undef sprintf #undef vsprintf #undef snprintf #undef vsnprintf #undef asprintf #undef vasprintf #undef asprintfv #undef dprintfv #undef fprintfv #undef sprintfv #undef printfv #undef snprintfv #define printf snv_printf #define vprintf snv_vprintf #define dprintf snv_dprintf #define vdprintf snv_vdprintf #define fprintf snv_fprintf #define vfprintf snv_vfprintf #define sprintf snv_sprintf #define vsprintf snv_vsprintf #define snprintf snv_snprintf #define vsnprintf snv_vsnprintf #define asprintf snv_asprintf #define vasprintf snv_vasprintf #define asprintfv snv_asprintfv #define dprintfv snv_dprintfv #define fprintfv snv_fprintfv #define sprintfv snv_sprintfv #define printfv snv_printfv #define snprintfv snv_snprintfv #endif /* !COMPILING_SNPRINTFV_C */ #ifdef __cplusplus } #endif #endif /* SNPRINTFV_SNPRINTFV_H */ /* snprintfv.h ends here */ smalltalk-3.2.5/snprintfv/snprintfv/format.c0000644000175000017500000007625412123404352016156 00000000000000/* -*- Mode: C -*- */ /* format.c --- printf clone for argv arrays * Copyright (C) 1998, 1999, 2000, 2002 Gary V. Vaughan * Copyright (C) 2003, 2008 Paolo Bonzini * Originally by Gary V. Vaughan, 1998 * This file is part of Snprintfv * * Snprintfv is free software; you can redistribute it and/or * modify it under the terms of the GNU General Public License as * published by the Free Software Foundation; either version 2 of the * License, or (at your option) any later version. * * Snprintfv program is distributed in the hope that it will be useful, * but WITHOUT ANY WARRANTY; without even the implied warranty of * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU * General Public License for more details. * * You should have received a copy of the GNU General Public License * along with this program. If not, write to the Free Software * Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * * As a special exception to the GNU General Public License, if you * distribute this file as part of a program that also links with and * uses the libopts library from AutoGen, you may include it under * the same distribution terms used by the libopts library. */ /* Code: */ #ifdef HAVE_CONFIG_H # include #endif #ifdef WITH_DMALLOC # include #endif #include #include #include #ifdef HAVE_WCHAR_H # include #endif #include "printf.h" #ifndef NO_FLOAT_PRINTING # ifdef HAVE_LONG_DOUBLE # ifndef HAVE_ISNANL # define isnanl(x) ((x) != (x)) # endif # ifndef HAVE_ISINFL # define isinfl(x) isnanl ((x) - (x)) # endif # ifndef HAVE_MODFL static snv_long_double modfl (long double x, long double *exp); # endif # ifndef HAVE_COPYSIGNL static snv_long_double copysignl (long double x, long double y); # endif # else # ifdef HAVE_ISNAN # define isnanl isnan # else # define isnanl(x) ((x) != (x)) # endif # ifdef HAVE_ISINF # define isinfl isinf # else # define isinfl(x) isnanl ((x) - (x)) # endif # ifdef HAVE_COPYSIGN # define copysignl copysign # else # define copysign(x, y) (((x) < 0.0 ^ (y) < 0.0) ? (x) * -1.0 : (x)); # endif # define modfl modf # endif #endif static uintmax_t fetch_uintmax (struct printf_info *pinfo, union printf_arg const *arg) { if (pinfo->is_long_double) return (uintmax_t) arg->pa_u_long_long_int; if (pinfo->is_long) return (uintmax_t) arg->pa_u_long_int; if (pinfo->is_short) return (uintmax_t) arg->pa_u_short_int; if (pinfo->is_char) return (uintmax_t) arg->pa_char; return (uintmax_t) arg->pa_u_int; } static intmax_t fetch_intmax (struct printf_info *pinfo, union printf_arg const *arg) { if (pinfo->is_long_double) return (intmax_t) (signed long long) arg->pa_long_long_int; if (pinfo->is_long) return (intmax_t) (signed long) arg->pa_long_int; if (pinfo->is_short) return (intmax_t) (signed short) arg->pa_short_int; if (pinfo->is_char) return (intmax_t) (signed char) arg->pa_char; return (intmax_t) (signed int) arg->pa_int; } #ifndef NO_FLOAT_PRINTING static snv_long_double fetch_double (struct printf_info *pinfo, union printf_arg const *arg) { if (pinfo->is_long_double) return (snv_long_double) arg->pa_long_double; else return (snv_long_double) (arg->pa_double); } #endif #ifndef NO_FLOAT_PRINTING /* These two routines are cleaned up version of the code in libio 2.95.3 (actually I got it from the Attic, not from the released tarball). The changes were mainly to share code between %f and %g (libio did share some code between %e and %g), and to share code between the %e and %f when invoked by %g. Support from infinities and NaNs comes from the old snprintfv code. */ static char * print_float_round (snv_long_double fract, int *exp, char *start, char *end, char ch, int *signp) { snv_long_double tmp; if (fract) (void) modfl (fract * 10, &tmp); else tmp = ch - '0'; if (tmp > 4) for (;; --end) { if (*end == '.') --end; if (end == start) { if (exp) /* e/E; increment exponent */ ++end, ++*exp; *end = '1'; break; } if (++*end <= '9') break; *end = '0'; } /* ``"%.3f", (double)-0.0004'' gives you a negative 0. */ else if (*signp == '-') for (;; --end) { if (*end == '.') --end; if (*end != '0') break; if (end == start) *signp = 0; } return (start); } static int print_float (struct printf_info *pinfo, char *startp, char *endp, int *signp, snv_long_double n) { int prec, fmtch; char *p, *t; snv_long_double fract; int expcnt, gformat = 0; snv_long_double integer, tmp; char expbuf[10]; prec = pinfo->prec; fmtch = pinfo->spec; t = startp; *signp = 0; /* Do the special cases: nans, infinities, zero, and negative numbers. */ if (isnanl (n)) { /* Not-a-numbers are printed as a simple string. */ *t++ = fmtch < 'a' ? 'N' : 'n'; *t++ = fmtch < 'a' ? 'A' : 'a'; *t++ = fmtch < 'a' ? 'N' : 'n'; return t - startp; } /* Zero and infinity also can have a sign in front of them. */ if (copysignl (1.0, n) < 0.0) { n = -1.0 * n; *signp = '-'; } if (isinfl (n)) { /* Infinities are printed as a simple string. */ *t++ = fmtch < 'a' ? 'I' : 'i'; *t++ = fmtch < 'a' ? 'N' : 'n'; *t++ = fmtch < 'a' ? 'F' : 'f'; goto set_signp; } expcnt = 0; fract = modfl (n, &integer); /* get an extra slot for rounding. */ *t++ = '0'; /* get integer portion of number; put into the end of the buffer; the .01 is added for modfl (356.0 / 10, &integer) returning .59999999... */ for (p = endp - 1; p >= startp && integer; ++expcnt) { tmp = modfl (integer / 10, &integer); *p-- = '0' + ((int) ((tmp + .01L) * 10)); } switch (fmtch) { case 'g': case 'G': gformat = 1; /* a precision of 0 is treated as a precision of 1. */ if (!prec) pinfo->prec = ++prec; /* ``The style used depends on the value converted; style e will be used only if the exponent resulting from the conversion is less than -4 or greater than the precision.'' -- ANSI X3J11 */ if (expcnt > prec || (!expcnt && fract && fract < .0001L)) { /* g/G format counts "significant digits, not digits of precision; for the e/E format, this just causes an off-by-one problem, i.e. g/G considers the digit before the decimal point significant and e/E doesn't count it as precision. */ --prec; fmtch -= 2; /* G->E, g->e */ goto eformat; } else { /* Decrement precision */ if (n != 0.0L) prec -= (endp - p) - 1; else prec--; goto fformat; } case 'f': case 'F': fformat: /* reverse integer into beginning of buffer */ if (expcnt) for (; ++p < endp; *t++ = *p); else *t++ = '0'; /* If precision required or alternate flag set, add in a decimal point. */ if (pinfo->prec || pinfo->alt) *t++ = '.'; /* if requires more precision and some fraction left */ if (fract) { if (prec) { /* For %g, if no integer part, don't count initial zeros as significant digits. */ do { fract = modfl (fract * 10, &tmp); *t++ = '0' + ((int) tmp); } while (!tmp && !expcnt && gformat); while (--prec && fract) { fract = modfl (fract * 10, &tmp); *t++ = '0' + ((int) tmp); } } if (fract) startp = print_float_round (fract, (int *) NULL, startp, t - 1, (char) 0, signp); } break; case 'e': case 'E': eformat: if (expcnt) { *t++ = *++p; if (pinfo->prec || pinfo->alt) *t++ = '.'; /* if requires more precision and some integer left */ for (; prec && ++p < endp; --prec) *t++ = *p; /* if done precision and more of the integer component, round using it; adjust fract so we don't re-round later. */ if (!prec && ++p < endp) { fract = 0; startp = print_float_round ((snv_long_double) 0, &expcnt, startp, t - 1, *p, signp); } /* adjust expcnt for digit in front of decimal */ --expcnt; } /* until first fractional digit, decrement exponent */ else if (fract) { /* adjust expcnt for digit in front of decimal */ for (expcnt = -1;; --expcnt) { fract = modfl (fract * 10, &tmp); if (tmp) break; } *t++ = '0' + ((int) tmp); if (pinfo->prec || pinfo->alt) *t++ = '.'; } else { *t++ = '0'; if (pinfo->prec || pinfo->alt) *t++ = '.'; } /* if requires more precision and some fraction left */ if (fract) { if (prec) do { fract = modfl (fract * 10, &tmp); *t++ = '0' + ((int) tmp); } while (--prec && fract); if (fract) startp = print_float_round (fract, &expcnt, startp, t - 1, (char) 0, signp); } break; default: abort (); } /* %e/%f/%#g add 0's for precision, others trim 0's */ if (gformat && !pinfo->alt) { while (t > startp && *--t == '0'); if (*t != '.') ++t; } else for (; prec--; *t++ = '0'); if (fmtch == 'e' || fmtch == 'E') { *t++ = fmtch; if (expcnt < 0) { expcnt = -expcnt; *t++ = '-'; } else *t++ = '+'; p = expbuf; do *p++ = '0' + (expcnt % 10); while ((expcnt /= 10) > 9); *p++ = '0' + expcnt; while (p > expbuf) *t++ = *--p; } set_signp: if (!*signp) { if (pinfo->showsign) *signp = '+'; else if (pinfo->space) *signp = ' '; } return (t - startp); } #endif static int printf_flag_info (struct printf_info *const pinfo, size_t n, int *argtypes) { return_val_if_fail (pinfo != NULL, SNV_ERROR); if (!(pinfo->state & (SNV_STATE_BEGIN | SNV_STATE_FLAG))) { PRINTF_ERROR (pinfo, "invalid specifier"); return -1; } pinfo->state = SNV_STATE_FLAG; while (pinfo->state & SNV_STATE_FLAG) { switch (*pinfo->format) { case '#': pinfo->alt = TRUE; pinfo->format++; break; case '0': if (!pinfo->left) pinfo->pad = '0'; pinfo->format++; break; case '-': pinfo->pad = ' '; pinfo->left = TRUE; pinfo->format++; break; case ' ': pinfo->space = TRUE; pinfo->format++; break; case '+': pinfo->showsign = TRUE; pinfo->format++; break; case '\'': pinfo->group = TRUE; pinfo->format++; break; default: pinfo->state = ~(SNV_STATE_BEGIN | SNV_STATE_FLAG); break; } } pinfo->format--; /* Return the number of characters emitted. */ return 0; } /* This function has considerably more freedom than the others in playing with pinfo; in particular, it modifies argindex and can return completely bogus values whose only purpose is to extend the argtypes vector so that it has enough items for the positional parameter of the width (in the *n$ case). It also expects that argtypes = (base of argtypes vector) + pinfo->argindex. This is messy, suggestion for simplifying it are gladly accepted. */ static int printf_numeric_param_info (struct printf_info *const pinfo, size_t n, int *argtypes) { const char *pEnd = NULL; int found = 0, allowed_states, new_state; int position = 0, skipped_args = 0; long value; return_val_if_fail (pinfo != NULL, SNV_ERROR); /* If we are looking at a ``.'', then this is a precision parameter. */ if (*pinfo->format == '.') { pinfo->format++; found |= 1; } /* First we might have a ``*''. */ if (*pinfo->format == '*') { pinfo->format++; found |= 2; } /* Parse the number. */ for (pEnd = pinfo->format, value = 0; *pEnd >= '0' && *pEnd <= '9'; pEnd++) value = value * 10 + (*pEnd - '0'); if (pEnd > pinfo->format) { pinfo->format = pEnd; found |= 4; } if (value > INT_MAX) { PRINTF_ERROR (pinfo, "out of range"); return -1; } /* And finally a dollar sign. */ if (*pinfo->format == '$') { if (value == 0) { PRINTF_ERROR (pinfo, "invalid position specifier"); return -1; } position = value; pinfo->format++; found |= 8; } switch (found & 14) { /* We found a * specification */ case 2: if (pinfo->args) value = pinfo->args[pinfo->argindex].pa_int; if (n) argtypes[0] = PA_INT; pinfo->argindex++; skipped_args = 1; found ^= 6; break; /* We found a *n$ specification */ case 14: if (n + pinfo->argindex > position - 1) argtypes[position - 1 - pinfo->argindex] = PA_INT; /* Else there is not enough space, reallocate and retry please... ... but we must say how much to skip. */ if (position >= pinfo->argindex) skipped_args = position - pinfo->argindex; if (pinfo->args) value = pinfo->args[position - 1].pa_int; found ^= 10; break; } switch (found) { /* We must have read a width specification. */ case 4: allowed_states = SNV_STATE_BEGIN | SNV_STATE_WIDTH; new_state = ~(SNV_STATE_BEGIN | SNV_STATE_FLAG | SNV_STATE_WIDTH); /* How awful... */ if (value < 0) { pinfo->pad = ' '; pinfo->left = TRUE; value = -value; } pinfo->width = value; break; /* We must have read a precision specification. */ case 5: allowed_states = SNV_STATE_PRECISION | SNV_STATE_BEGIN; new_state = SNV_STATE_MODIFIER | SNV_STATE_SPECIFIER; pinfo->prec = value; break; /* We must have read a position specification. */ case 12: allowed_states = SNV_STATE_BEGIN; new_state = ~SNV_STATE_BEGIN; pinfo->dollar = position; break; /* We must have read something bogus. */ default: PRINTF_ERROR (pinfo, "invalid specifier"); return -1; } if (!(pinfo->state & allowed_states)) { PRINTF_ERROR (pinfo, "invalid specifier"); return -1; } pinfo->state = new_state; pinfo->format--; return skipped_args; } static int printf_modifier_info (struct printf_info *const pinfo, size_t n, int *argtypes) { return_val_if_fail (pinfo != NULL, SNV_ERROR); /* Check for valid pre-state. */ if (!(pinfo->state & (SNV_STATE_BEGIN | SNV_STATE_MODIFIER))) { PRINTF_ERROR (pinfo, "out of range"); return -1; } while (pinfo->state != SNV_STATE_SPECIFIER) { switch (*pinfo->format) { case 'h': if (*++pinfo->format != 'h') { pinfo->is_short = TRUE; break; } pinfo->is_char = TRUE; pinfo->format++; break; case 'z': if (sizeof (size_t) > sizeof (char *)) pinfo->is_long_double = TRUE; else pinfo->is_long = TRUE; pinfo->format++; break; case 't': if (sizeof (ptrdiff_t) > sizeof (char *)) pinfo->is_long_double = TRUE; else pinfo->is_long = TRUE; pinfo->format++; break; case 'l': if (*++pinfo->format != 'l') { pinfo->is_long = TRUE; break; } /*NOBREAK*/ case 'j': case 'q': case 'L': pinfo->is_long_double = TRUE; pinfo->format++; break; default: pinfo->state = SNV_STATE_SPECIFIER; pinfo->format--; break; } } /* Return the number of characters emitted. */ return 0; } static int printf_char (STREAM *stream, struct printf_info *const pinfo, union printf_arg const *args) { int count_or_errorcode = SNV_OK; char ch = '\0'; return_val_if_fail (pinfo != NULL, SNV_ERROR); /* Check for valid pre-state. */ if (pinfo->prec != -1 || pinfo->is_char || pinfo->is_short || pinfo->is_long || pinfo->is_long_double || pinfo->pad == '0' || pinfo->alt || pinfo->space || pinfo->showsign) { PRINTF_ERROR (pinfo, "invalid flags"); return -1; } /* Extract the correct argument from the arg vector. */ ch = args->pa_char; /* Left pad to the width if the supplied argument is less than the width specifier. */ if ((pinfo->width > 1) && !pinfo->left) { int padwidth = pinfo->width - 1; while ((count_or_errorcode >= 0) && (count_or_errorcode < padwidth)) SNV_EMIT (pinfo->pad, stream, count_or_errorcode); } /* Emit the character argument. */ SNV_EMIT (ch, stream, count_or_errorcode); /* Right pad to the width if we still didn't reach the specified width and the left justify flag was set. */ if ((count_or_errorcode < pinfo->width) && pinfo->left) while ((count_or_errorcode >= 0) && (count_or_errorcode < pinfo->width)) SNV_EMIT (pinfo->pad, stream, count_or_errorcode); /* Return the number of characters emitted. */ return count_or_errorcode; } #ifndef NO_FLOAT_PRINTING static int printf_float (STREAM *stream, struct printf_info *const pinfo, union printf_arg const *args) { snv_long_double value = 0.0; int sign, len, count_or_errorcode = SNV_OK; #ifdef HAVE_LONG_DOUBLE char buffer[LDBL_MAX_10_EXP * 2 + 20], *p = buffer; #else char buffer[DBL_MAX_10_EXP * 2 + 20], *p = buffer; #endif return_val_if_fail (pinfo != NULL, SNV_ERROR); /* Check for valid pre-state */ if (pinfo->prec == -1) pinfo->prec = SNV_POINTER_TO_INT (pinfo->extra); /* Check for valid pre-state. */ if (pinfo->prec <= -1 || pinfo->is_char || pinfo->is_short || pinfo->is_long) { PRINTF_ERROR (pinfo, "invalid flags"); return -1; } /* Extract the correct argument from the arg vector. */ value = fetch_double (pinfo, args); /* Convert the number into a string. */ len = print_float (pinfo, buffer, buffer + sizeof (buffer), &sign, value); if (*buffer == '0') p++, len--; /* Compute the size of the padding. */ pinfo->width -= len; if (sign) pinfo->width--; /* Left pad to the remaining width if the supplied argument is less than the width specifier, and the padding character is ' '. */ if (pinfo->pad == ' ' && !pinfo->left) while ((count_or_errorcode >= 0) && (pinfo->width-- > 0)) SNV_EMIT (pinfo->pad, stream, count_or_errorcode); /* Display any sign character. */ if (count_or_errorcode >= 0 && sign) SNV_EMIT (sign, stream, count_or_errorcode); /* Left pad to the remaining width if the supplied argument is less than the width specifier, and the padding character is not ' '. */ if (pinfo->pad != ' ' && !pinfo->left) while ((count_or_errorcode >= 0) && (pinfo->width-- > 0)) SNV_EMIT (pinfo->pad, stream, count_or_errorcode); /* Fill the stream buffer with as many characters from the number buffer as possible without overflowing. */ while ((count_or_errorcode >= 0) && (len-- > 0)) SNV_EMIT (*p++, stream, count_or_errorcode); /* Right pad to the width if we still didn't reach the specified width and the left justify flag was set. */ if (pinfo->left) while ((count_or_errorcode >= 0) && (pinfo->width-- > 0)) SNV_EMIT (pinfo->pad, stream, count_or_errorcode); /* Return the number of characters emitted. */ return count_or_errorcode; } #endif static int printf_count (STREAM *stream, struct printf_info *const pinfo, union printf_arg const *args) { if (pinfo->is_char) *(char *) (args->pa_pointer) = pinfo->count; else if (pinfo->is_short) *(short *) (args->pa_pointer) = pinfo->count; else if (pinfo->is_long) *(long *) (args->pa_pointer) = pinfo->count; else if (pinfo->is_long_double) *(intmax_t *) (args->pa_pointer) = pinfo->count; else *(int *) (args->pa_pointer) = pinfo->count; return 0; } static int printf_integer (STREAM *stream, struct printf_info *const pinfo, union printf_arg const *args) { static const char digits_lower[] = "0123456789abcdefghijklmnopqrstuvwxyz"; static const char digits_upper[] = "0123456789ABCDEFGHIJKLMNOPQRSTUVWXYZ"; const char *digits; unsigned base = SNV_POINTER_TO_UINT (pinfo->extra); uintmax_t value = 0L; int type, count_or_errorcode = SNV_OK; char buffer[256], *p, *end; boolean is_negative = FALSE; return_val_if_fail (pinfo != NULL, SNV_ERROR); /* Check for valid pre-state. */ if (!(pinfo->state & (SNV_STATE_BEGIN | SNV_STATE_SPECIFIER))) { PRINTF_ERROR (pinfo, "out of range"); return -1; } /* Upper or lower-case hex conversion? */ digits = ((pinfo->spec >= 'a') && (pinfo->spec <= 'z')) ? digits_lower : digits_upper; if (pinfo->prec == -1) pinfo->prec = 0; /* Check for valid pre-state. */ if (pinfo->prec < 0) { PRINTF_ERROR (pinfo, "invalid precision"); return -1; } type = pinfo->type; /* Extract the correct argument from the arg vector. */ if (type & PA_FLAG_UNSIGNED) { value = fetch_uintmax (pinfo, args); is_negative = FALSE; pinfo->showsign = pinfo->space = FALSE; } else { intmax_t svalue = 0L; svalue = fetch_intmax (pinfo, args); is_negative = (svalue < 0); value = (uintmax_t) ABS (svalue); } /* Convert the number into a string. */ p = end = &buffer[sizeof (buffer) - 1]; if (value == 0) *p-- = '0'; else while (value > 0) { *p-- = digits[value % base]; value /= base; } pinfo->width -= end - p; pinfo->prec -= end - p; /* Octal numbers have a leading zero in alterate form. */ if (pinfo->alt && base == 8) { *p-- = '0'; --pinfo->width; } /* Left pad with zeros to make up the precision. */ if (pinfo->prec > 0) { pinfo->width -= pinfo->prec; while (pinfo->prec-- > 0) *p-- = '0'; } /* Reserve room for leading `0x' for hexadecimal. */ if (pinfo->alt && base == 16) pinfo->width -= 2; /* Reserve room for a sign character. */ if (is_negative || pinfo->showsign || pinfo->space) --pinfo->width; /* Left pad to the remaining width if the supplied argument is less * than the width specifier, and the padding character is ' '. */ if (pinfo->pad == ' ' && !pinfo->left) while ((count_or_errorcode >= 0) && (pinfo->width-- > 0)) SNV_EMIT (pinfo->pad, stream, count_or_errorcode); /* Display any sign character. */ if (count_or_errorcode >= 0) { if (is_negative) SNV_EMIT ('-', stream, count_or_errorcode); else if (pinfo->showsign) SNV_EMIT ('+', stream, count_or_errorcode); else if (pinfo->space) SNV_EMIT (' ', stream, count_or_errorcode); } /* Display `0x' for alternate hexadecimal specifier. */ if ((count_or_errorcode >= 0) && (base == 16) && pinfo->alt) { SNV_EMIT ('0', stream, count_or_errorcode); SNV_EMIT (digits['X' - 'A' + 10], stream, count_or_errorcode); } /* Left pad to the remaining width if the supplied argument is less * than the width specifier, and the padding character is not ' '. */ if (pinfo->pad != ' ' && !pinfo->left) while ((count_or_errorcode >= 0) && (pinfo->width-- > 0)) SNV_EMIT (pinfo->pad, stream, count_or_errorcode); /* Fill the stream buffer with as many characters from the number * buffer as possible without overflowing. */ while ((count_or_errorcode >= 0) && (++p < &buffer[sizeof (buffer)])) SNV_EMIT (*p, stream, count_or_errorcode); /* Right pad to the width if we still didn't reach the specified * width and the left justify flag was set. */ if (pinfo->left) while ((count_or_errorcode >= 0) && (pinfo->width-- > 0)) SNV_EMIT (pinfo->pad, stream, count_or_errorcode); /* Return the number of characters emitted. */ return count_or_errorcode; } static int printf_pointer (STREAM *stream, struct printf_info *const pinfo, union printf_arg const *args) { int count_or_errorcode = SNV_OK; return_val_if_fail (pinfo != NULL, SNV_ERROR); /* Read these now to advance the argument pointer appropriately */ if (pinfo->prec == -1) pinfo->prec = 0; /* Check for valid pre-state. */ if (pinfo->prec <= -1 || pinfo->is_char || pinfo->is_short || pinfo->is_long || pinfo->is_long_double) { PRINTF_ERROR (pinfo, "invalid flags"); return -1; } /* Always print 0x. */ pinfo->alt = 1; pinfo->is_long = sizeof(long) == sizeof (char *); pinfo->is_long_double = sizeof(intmax_t) == sizeof (char *); /* Use the standard routine for numbers for the printing call, if the pointer is not NULL. */ if (args->pa_pointer != NULL) return printf_integer (stream, pinfo, args); /* Print a NULL pointer as (nil), appropriately padded. */ if ((pinfo->width > 5) && !pinfo->left) { int padwidth = pinfo->width - 5; while ((count_or_errorcode >= 0) && (count_or_errorcode < padwidth)) SNV_EMIT (pinfo->pad, stream, count_or_errorcode); } SNV_EMIT ('(', stream, count_or_errorcode); SNV_EMIT ('n', stream, count_or_errorcode); SNV_EMIT ('i', stream, count_or_errorcode); SNV_EMIT ('l', stream, count_or_errorcode); SNV_EMIT (')', stream, count_or_errorcode); if ((pinfo->width > 5) && pinfo->left) while ((count_or_errorcode >= 0) && (count_or_errorcode < pinfo->width)) SNV_EMIT (pinfo->pad, stream, count_or_errorcode); return count_or_errorcode; } static int printf_string (STREAM *stream, struct printf_info *const pinfo, union printf_arg const *args) { int len = 0, count_or_errorcode = SNV_OK; const char *p = NULL; return_val_if_fail (pinfo != NULL, SNV_ERROR); /* Read these now to advance the argument pointer appropriately */ if (pinfo->prec == -1) pinfo->prec = 0; /* Check for valid pre-state. */ if (pinfo->prec <= -1 || pinfo->is_char || pinfo->is_short || pinfo->is_long || pinfo->is_long_double) { PRINTF_ERROR (pinfo, "invalid flags"); return -1; } /* Extract the correct argument from the arg vector. */ p = args->pa_string; /* Left pad to the width if the supplied argument is less than the width specifier. */ if (p != NULL) { len = strlen (p); if (pinfo->prec && pinfo->prec < len) len = pinfo->prec; } if ((len < pinfo->width) && !pinfo->left) { int padwidth = pinfo->width - len; while ((count_or_errorcode >= 0) && (count_or_errorcode < padwidth)) SNV_EMIT (pinfo->pad, stream, count_or_errorcode); } /* Fill the buffer with as many characters from the format argument as possible without overflowing or exceeding the precision. */ if ((count_or_errorcode >= 0) && (p != NULL)) { int mark = count_or_errorcode; while ((count_or_errorcode >= 0) && *p != '\0' && ((pinfo->prec == 0) || (count_or_errorcode - mark < len))) SNV_EMIT (*p++, stream, count_or_errorcode); } /* Right pad to the width if we still didn't reach the specified width and the left justify flag was set. */ if ((count_or_errorcode < pinfo->width) && pinfo->left) while ((count_or_errorcode >= 0) && (count_or_errorcode < pinfo->width)) SNV_EMIT (pinfo->pad, stream, count_or_errorcode); /* Return the number of characters emitted. */ return count_or_errorcode; } /* replacements for modfl and copysignl follow. */ #if !defined NO_FLOAT_PRINTING && defined HAVE_LONG_DOUBLE # ifndef HAVE_MODFL static long double modfl (long double x, long double *exp) { /* To compute the integer part of a positive integer (in this case abs(X)), sum a big enough integer to the absolute value, so that the precision of the floating point number is exactly 1. Then we round towards zero. The code in the two branches is the same but it considers -x if x is negative. */ long double z; if (x < 0.0L) { z = 1.0L / LDBL_EPSILON - x - 1.0 / LDBL_EPSILON; if (z + x > 0.0L) z = z - 1.0L; return (*exp = -z) + x; } else { z = 1.0L / LDBL_EPSILON + x - 1.0 / LDBL_EPSILON; if (z > x) z = z - 1.0L; return x - (*exp = z); } } # endif /* !HAVE_MODFL */ # ifndef HAVE_COPYSIGNL long double copysignl (long double x, long double y) { # ifdef HAVE_COPYSIGN return x * (long double) copysign (1.0, x * y); # else /* !HAVE_COPYSIGN */ /* If we do not have copysign, assume zero is unsigned (too risky to assume we have infinities, which would allow to test with (x < 0.0 && 1.0 / x < 0.0). */ return (x < 0.0 ^ y < 0.0) ? x * -1.0 : x; # endif /* !HAVE_COPYSIGN */ } # endif /* !HAVE_COPYSIGNL */ #endif /* !NO_FLOAT_PRINTING && HAVE_LONG_DOUBLE */ /* This is where the parsing of FORMAT strings is handled: Each of these functions should inspect PPARSER for parser state information; update PPARSER as necessary based on the state discovered; possibly put some characters in STREAM, in which case that number of characters must be returned. If the handler detects that parsing (of the current specifier) is complete, then it must set pinfo->state to SNV_STATE_END. The library will then copy characters from the format string to STREAM until another unescaped SNV_CHAR_SPEC is detected when the handlers will be called again. */ spec_entry snv_default_spec_table[] = { /* ch type function */ {' ', 0, 0, NULL, printf_flag_info, NULL}, {'#', 0, 0, NULL, printf_flag_info, NULL}, {'+', 0, 0, NULL, printf_flag_info, NULL}, {'-', 0, 0, NULL, printf_flag_info, NULL}, {'\'', 0, 0, NULL, printf_flag_info, NULL}, {'*', 0, PA_INT, NULL, printf_numeric_param_info, NULL}, {'$', 0, 0, NULL, printf_numeric_param_info, NULL}, {'.', 0, 0, NULL, printf_numeric_param_info, NULL}, {'0', 0, 0, NULL, printf_flag_info, NULL}, {'1', 0, 0, NULL, printf_numeric_param_info, NULL}, {'2', 0, 0, NULL, printf_numeric_param_info, NULL}, {'3', 0, 0, NULL, printf_numeric_param_info, NULL}, {'4', 0, 0, NULL, printf_numeric_param_info, NULL}, {'5', 0, 0, NULL, printf_numeric_param_info, NULL}, {'6', 0, 0, NULL, printf_numeric_param_info, NULL}, {'7', 0, 0, NULL, printf_numeric_param_info, NULL}, {'8', 0, 0, NULL, printf_numeric_param_info, NULL}, {'9', 0, 0, NULL, printf_numeric_param_info, NULL}, {'c', 0, PA_CHAR, printf_char, NULL, NULL}, {'d', 0, PA_INT, printf_integer, printf_generic_info, (snv_pointer) 10}, #ifndef NO_FLOAT_PRINTING {'e', 0, PA_DOUBLE, printf_float, printf_generic_info, (snv_pointer) 6}, {'E', 0, PA_DOUBLE, printf_float, printf_generic_info, (snv_pointer) 6}, {'f', 0, PA_DOUBLE, printf_float, printf_generic_info, (snv_pointer) 6}, {'F', 0, PA_DOUBLE, printf_float, printf_generic_info, (snv_pointer) 6}, {'g', 0, PA_DOUBLE, printf_float, printf_generic_info, (snv_pointer) 6}, {'G', 0, PA_DOUBLE, printf_float, printf_generic_info, (snv_pointer) 6}, #endif {'h', 0, 0, NULL, printf_modifier_info, NULL}, {'i', 0, PA_INT, printf_integer, printf_generic_info, (snv_pointer) 10}, {'j', 0, 0, NULL, printf_modifier_info, NULL}, {'l', 0, 0, NULL, printf_modifier_info, NULL}, {'L', 0, 0, NULL, printf_modifier_info, NULL}, {'n', 0, PA_INT | PA_FLAG_PTR, printf_count, printf_generic_info, NULL}, {'o', 0, PA_INT | PA_FLAG_UNSIGNED, printf_integer, printf_generic_info, (snv_pointer) 8}, {'p', 0, PA_POINTER, printf_pointer, NULL, (snv_pointer) 16}, {'q', 0, 0, NULL, printf_modifier_info, NULL}, {'s', 0, PA_STRING, printf_string, NULL, NULL}, {'t', 0, 0, NULL, printf_modifier_info, NULL}, {'u', 0, PA_INT | PA_FLAG_UNSIGNED, printf_integer, printf_generic_info, (snv_pointer) 10}, {'x', 0, PA_INT | PA_FLAG_UNSIGNED, printf_integer, printf_generic_info, (snv_pointer) 16}, {'X', 0, PA_INT | PA_FLAG_UNSIGNED, printf_integer, printf_generic_info, (snv_pointer) 16}, {'z', 0, 0, NULL, printf_modifier_info, NULL}, {'\0', 0, PA_LAST, NULL, NULL, NULL} }; /* format.c ends here */ smalltalk-3.2.5/snprintfv/snprintfv/filament.in0000644000175000017500000001303412123404352016634 00000000000000/* -*- Mode: C -*- */ /* filament.h --- a bit like a string but different =)O| * Copyright (C) 1998, 1999, 2000, 2002 Gary V. Vaughan * Originally by Gary V. Vaughan, 1998 * This file is part of Snprintfv * * Snprintfv is free software; you can redistribute it and/or * modify it under the terms of the GNU General Public License as * published by the Free Software Foundation; either version 2 of the * License, or (at your option) any later version. * * Snprintfv program is distributed in the hope that it will be useful, * but WITHOUT ANY WARRANTY; without even the implied warranty of * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU * General Public License for more details. * * You should have received a copy of the GNU General Public License * along with this program. If not, write to the Free Software * Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * * As a special exception to the GNU General Public License, if you * distribute this file as part of a program that also links with and * uses the libopts library from AutoGen, you may include it under * the same distribution terms used by the libopts library. */ /* Code: */ #ifndef FILAMENT_H #define FILAMENT_H 1 #include #ifdef __cplusplus extern "C" { #if 0 /* This brace is so that emacs can still indent properly: */ } #endif #endif /* __cplusplus */ #define FILAMENT_BUFSIZ 512 /** * Filament: * Opaque data type used to hold 8-bit clean dynamic strings which know * their own length and resize themselves to avoid buffer overruns. **/ typedef struct filament Filament; struct filament { char *value; /* pointer to the start of the string */ size_t length; /* length of the string */ size_t size; /* total memory allocated */ char buffer[FILAMENT_BUFSIZ]; /* usually string == &buffer[0] */ }; @protos filament.c /* Save the overhead of a function call in the great majority of cases. */ #define fil_maybe_extend(fil, len, copy) \ (((len)>=(fil)->size) ? _fil_extend((fil), (len), (copy)) : (void)0) /** * filval: * @fil: The Filament object being queried. * * Return value: * A pointer to the null terminated string held by the Filament * object is returned. Since the @fil may contain embedded nulls, it * is not entirely safe to use the strfoo() API to examine the contents * of the return value. **/ SNV_INLINE char * filval (Filament *fil) { /* Because we have been careful to ensure there is always at least one spare byte of allocated memory, it is safe to set it here. */ fil->value[fil->length] = '\0'; return (char *) (fil->value); } /** * fillen: * @fil: The Filament object being queried. * * Return value: * The length of @fil, including any embedded nulls, but excluding the * terminating null, is returned. **/ SNV_INLINE size_t fillen (Filament *fil) { return fil->length; } /** * filelt: * @fil: The Filament being queried. * @n: A zero based index into @fil. * * This function looks for the @n'th element of @fil. * * Return value: * If @n is an index inside the Filament @fil, then the character stored * at that index cast to an int is returned, otherwise @n is outside * this range and -1 is returned. **/ SNV_INLINE int filelt (Filament *fil, ssize_t n) { if ((n >= 0) && (n < fil->length)) return (int) fil->value[n]; else return -1; } /** * filncat: * @fil: The destination Filament of the concatenation. * @str: The address of the source bytes for concatenation. * @n: The number of bytes to be copied from @str. * * @n bytes starting with the byte at address @str are destructively * concatenated to @fil. If necessary, @fil is dynamically reallocated * to make room for this operation. * * Return value: * A pointer to the (not null terminated) string which is the result * of this concatenation is returned. **/ SNV_INLINE char * filncat (Filament *fil, const char *str, size_t n) { fil_maybe_extend (fil, n + fil->length, TRUE); memcpy (fil->value + fil->length, str, n); fil->length += n; return fil->value; } /** * filcat: * @fil: The destination Filament of the concatenation. * @str: The address of the source bytes for concatenation. * * The bytes starting at address @str upto and including the first null * byte encountered are destructively concatenated to @fil. If * necessary @fil is dynamically reallocated to make room for this * operation. * * Return value: * A pointer to the (not null terminated) string which is the result * of this concatenation is returned. **/ SNV_INLINE char * filcat (Filament *fil, const char *str) { size_t length = strlen (str); return filncat (fil, str, length); } /** * filccat: * @fil: The destination Filament of the concatenation. * @c: The character to append to @fil. * * @c is destructively concatenated to @fil. If necessary, @fil is * dynamically reallocated to make room for this operation. When used * repeatedly this function is less efficient than %filncat, * since it must check whether to extend the filament before each * character is appended. * * Return value: * A pointer to the (not null terminated) string which is the result * of this concatenation is returned. **/ SNV_INLINE char * filccat (Filament *fil, int c) { fil_maybe_extend (fil, 1 + fil->length, TRUE); fil->value[fil->length++] = c; return fil->value; } #ifdef __cplusplus #if 0 /* This brace is so that emacs can still indent properly: */ { #endif } #endif /* __cplusplus */ #endif /* FILAMENT_H */ /* filament.h ends here */ smalltalk-3.2.5/snprintfv/snprintfv/printf.in0000644000175000017500000002257212123404352016346 00000000000000/* -*- Mode: C -*- */ /* printf.in --- printf clone for argv arrays * Copyright (C) 1998, 1999, 2000, 2002 Gary V. Vaughan * Originally by Gary V. Vaughan, 1998 * This file is part of Snprintfv * * Snprintfv is free software; you can redistribute it and/or * modify it under the terms of the GNU General Public License as * published by the Free Software Foundation; either version 2 of the * License, or (at your option) any later version. * * Snprintfv program is distributed in the hope that it will be useful, * but WITHOUT ANY WARRANTY; without even the implied warranty of * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU * General Public License for more details. * * You should have received a copy of the GNU General Public License * along with this program. If not, write to the Free Software * Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * * As a special exception to the GNU General Public License, if you * distribute this file as part of a program that also links with and * uses the libopts library from AutoGen, you may include it under * the same distribution terms used by the libopts library. */ /* Code: */ #ifndef SNPRINTFV_SNPRINTFV_H #define SNPRINTFV_SNPRINTFV_H 1 #include #include #include #include #ifdef HAVE_WCHAR_H # include #endif #ifdef __cplusplus extern "C" { #endif /* The type of each element in the table of printf specifiers. */ struct spec_entry; typedef enum { SNV_ERROR = -1, SNV_OK } snv_status; /* Basic states required by the parser. On initialisation the parser will be in SNV_STATE_BEGIN, and tokens will be parsed by the registered functions until the parser reached SNV_STATE_END. */ #define SNV_STATE_BEGIN 1 #define SNV_STATE_END 0 /* States needed to support: %[$][|\*][.|\*] */ #define SNV_STATE_FLAG (1 << 1) #define SNV_STATE_WIDTH (1 << 2) #define SNV_STATE_PRECISION (1 << 3) #define SNV_STATE_MODIFIER (1 << 4) #define SNV_STATE_SPECIFIER (1 << 5) /* First state available to the user */ #define SNV_STATE_USER_FIRST (1 << 8) /* Mask for states available to the user */ #define SNV_STATE_USER_MASK ~(SNV_STATE_USER_FIRST - 1) typedef struct printf_info { int count; /* accumulated count, or SNV_ERROR */ int state; /* one of the defines above */ Filament *error; /* accumulated error details */ const char *format; /* pointer to format string */ int argc; /* number of arguments used by format */ int argindex; /* number of non-dollar arguments used so far */ int dollar; /* standard parser state, as in glibc */ int prec; /* from this field on, as in glibc */ int width; snv_pointer extra; int type; char spec; char pad; unsigned is_long_double:1; unsigned is_char:1; unsigned is_short:1; unsigned is_long:1; unsigned alt:1; unsigned space:1; unsigned left:1; unsigned showsign:1; unsigned group:1; unsigned wide:1; const union printf_arg *args; } printf_info; /** * printf_arg: * @pa_char: an unsigned %char * @pa_wchar: a %wchar_t * @pa_short_int: a %short integer * @pa_int: an %int * @pa_long_int: a %long integer * @pa_long_long_int: the widest signed integer type in use on the host * @pa_u_short_int: an unsigned %short integer * @pa_u_int: an unsigned %int * @pa_u_long_int: an unsigned %long integer * @pa_u_long_long_int: the widest unsigned integer type in use on the host * @pa_float: a %float * @pa_double: a %double * @pa_long_double: a long %double, or a simple %double if it is the widest floating-point type in use on the host * @pa_string: a %const pointer to %char * @pa_wstring: a %const pointer to %wchar_t * @pa_pointer: a generic pointer * * The various kinds of arguments that can be passed to printf. */ typedef union printf_arg { unsigned char pa_char; snv_wchar_t pa_wchar; short int pa_short_int; int pa_int; long int pa_long_int; intmax_t pa_long_long_int; unsigned short int pa_u_short_int; unsigned int pa_u_int; unsigned long int pa_u_long_int; uintmax_t pa_u_long_long_int; float pa_float; double pa_double; long double pa_long_double; const char *pa_string; const snv_wchar_t *pa_wstring; snv_constpointer pa_pointer; } printf_arg; /** * PRINTF_ERROR: * @pi: A pointer to the current state for the parser * @str: The error message * * Append an error that will be returned by printf_strerror. */ #define PRINTF_ERROR(pi, str) \ printf_error(pi, __FILE__, __LINE__, SNV_ASSERT_FMT, str); typedef int printf_function (STREAM *stream, struct printf_info *pparser, union printf_arg const * args); typedef int printf_arginfo_function (struct printf_info *pparser, size_t n, int *argtypes); /** * spec_entry: * @spec: the specifier character that was matched * @type: when @arg is NULL, the type of the only argument to the specifier * @fmt: the handler function to actually print the arguments to the specifier * @arg: the handler function to tell %printf about the types of the arguments to the specifier * @user: the user data for the specifier, accessible to the handler function * * This is returned by register_printf_function. */ typedef struct spec_entry { int spec; int unused; /* for binary compatibility */ int type; printf_function *fmt; printf_arginfo_function *arg; snv_pointer user; } spec_entry; /** * register_callback_function: printf.h * @spec: the character which will trigger the functions, cast to an unsigned int. * @fmt: the handler function to actually print the arguments to the specifier * @arg: the handler function to tell %printf about the types of the arguments to the specifier * * Register the pair made of @fmt and @arg, so that it is called * when @spec is encountered in a format string. If you create * a shared library with an entry point named * %snv_register_printf_funcs, and put the library in the * search path given by the environment library %LTDL_LIBRARY_PATH, * that entry point will be called when %libsnprintfv is initialized, * passing a pointer to this kind of function (actually, a pointer * to %register_printf_function) to it. This functionality is only * present when the library is installed, not when it is built as * a convenience library. * * Return value: * Returns %NULL if @func was not successfully registered, a * %spec_entry with the information on the function if it was. **/ typedef spec_entry *register_callback_function (unsigned spec, printf_function *func, printf_arginfo_function *arginfo); /* Codes to determine basic types. These values cover all the standard format specifications. Users can add new values after PA_LAST for their own types. */ enum { PA_INT, /* int */ PA_CHAR, /* int, cast to char */ PA_WCHAR, /* wide char */ PA_STRING, /* const char *, a '\0'-terminated string */ PA_WSTRING, /* const snv_wchar_t *, wide character string */ PA_POINTER, /* void * */ PA_FLOAT, /* float */ PA_DOUBLE, /* double */ PA_LAST, PA_UNKNOWN = -1 }; /* Flag bits that can be set in a type. */ #define PA_TYPE_MASK 0x00ff #define PA_FLAG_MASK ~SNV_TYPE_MASK #define PA_FLAG_LONG_LONG (1 << 8) #define PA_FLAG_LONG_DOUBLE PA_FLAG_LONG_LONG #define PA_FLAG_LONG (1 << 9) #define PA_FLAG_SHORT (1 << 10) #define PA_FLAG_UNSIGNED (1 << 11) #define PA_FLAG_CHAR (1 << 12) #define PA_FLAG_PTR (1 << 13) /** * SNV_EMIT: * @ch: the character to be printed * @stream: the stream on which to print * @count: a variable to be updated with the count of printed * characters * * Maintain the count while putting @ch in @stream, also be careful about * handling %NULL stream if the handler is being called purely to count * output size. **/ #define SNV_EMIT(ch, stream, count) \ SNV_STMT_START { \ if (stream) \ { \ if (count >= 0) \ { \ int m_status = stream_put((ch), stream); \ count = m_status < 0 ? m_status : count + m_status; \ } \ } \ else \ { \ (void)(ch); \ count++; \ } \ } SNV_STMT_END @protos format.c @protos custom.c @protos printf.c /* If you don't want to use snprintfv functions for *all* of your string formatting API, then define COMPILING_SNPRINTFV_C and use the snv_ prefix for the entry points below. */ #ifndef COMPILING_PRINTF_C #undef printf #undef vprintf #undef dprintf #undef vdprintf #undef fprintf #undef vfprintf #undef sprintf #undef vsprintf #undef snprintf #undef vsnprintf #undef asprintf #undef vasprintf #undef asprintfv #undef dprintfv #undef fprintfv #undef sprintfv #undef printfv #undef snprintfv #define printf snv_printf #define vprintf snv_vprintf #define dprintf snv_dprintf #define vdprintf snv_vdprintf #define fprintf snv_fprintf #define vfprintf snv_vfprintf #define sprintf snv_sprintf #define vsprintf snv_vsprintf #define snprintf snv_snprintf #define vsnprintf snv_vsnprintf #define asprintf snv_asprintf #define vasprintf snv_vasprintf #define asprintfv snv_asprintfv #define dprintfv snv_dprintfv #define fprintfv snv_fprintfv #define sprintfv snv_sprintfv #define printfv snv_printfv #define snprintfv snv_snprintfv #endif /* !COMPILING_SNPRINTFV_C */ #ifdef __cplusplus } #endif #endif /* SNPRINTFV_SNPRINTFV_H */ /* snprintfv.h ends here */ smalltalk-3.2.5/snprintfv/snprintfv/mem.c0000644000175000017500000000454412123404352015435 00000000000000/* -*- Mode: C -*- */ /* mem.c --- memory management routines * Copyright (C) 2002 Gary V. Vaughan * Originally by Paolo Bonzini, 2002 * This file is part of Snprintfv * * Snprintfv is free software; you can redistribute it and/or * modify it under the terms of the GNU General Public License as * published by the Free Software Foundation; either version 2 of the * License, or (at your option) any later version. * * Snprintfv program is distributed in the hope that it will be useful, * but WITHOUT ANY WARRANTY; without even the implied warranty of * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU * General Public License for more details. * * You should have received a copy of the GNU General Public License * along with this program. If not, write to the Free Software * Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * * As a special exception to the GNU General Public License, if you * distribute this file as part of a program that also links with and * uses the libopts library from AutoGen, you may include it under * the same distribution terms used by the libopts library. */ /* Code: */ #ifdef HAVE_CONFIG_H # include #endif #ifdef HAVE_DMALLOC # include #endif #include "mem.h" /* We deliberately don't prototype the malloc functions; they are cast to match the function pointers we expose to avoid compiler warnings from mismatched prototypes (if we find a host implementation. Not also that if this file is compiled -DWITH_DMALLOC, the inclusion in mem.h will cause the malloc references below to be redirected correctly. */ snv_pointer (*snv_malloc) (size_t count) = (snv_pointer (*) (size_t)) malloc; snv_pointer (*snv_realloc) (snv_pointer old, size_t count) = (snv_pointer (*) (snv_pointer old, size_t count)) realloc; void (*snv_free) (snv_pointer old) = (void (*) (snv_pointer old)) free; /* Unportable memory management functions are reimplemented tout court. */ snv_pointer snv_xrealloc (snv_pointer old, size_t count) { if (count < 1) { snv_free (old); return NULL; } if (!old) return snv_malloc (count); else return snv_realloc (old, count); } char *snv_strdup (const char *str) { size_t len = strlen (str); char *result = snv_malloc (len + 1); memcpy (result, str, len + 1); return result; } smalltalk-3.2.5/snprintfv/snprintfv/Makefile.am0000644000175000017500000000771212123404352016547 00000000000000## -*- Mode: Makefile -*- ## --------------------------------------------------------------------- ## Makefile.am -- process this file with automake to produce Makefile.in ## Copyright (C) 1998, 1999, 2000, 2002, 2009 Gary V. Vaughan ## Originally by Gary V. Vaughan, 1998 ## This file is part of Snprintfv ## ## Snprintfv is free software; you can redistribute it and/or ## modify it under the terms of the GNU General Public License as ## published by the Free Software Foundation; either version 2 of the ## License, or (at your option) any later version. ## ## Snprintfv program is distributed in the hope that it will be useful, ## but WITHOUT ANY WARRANTY; without even the implied warranty of ## MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU ## General Public License for more details. ## ## You should have received a copy of the GNU General Public License ## along with this program. If not, write to the Free Software ## Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. ## ## As a special exception to the GNU General Public License, if you ## distribute this file as part of a program that also links with and ## uses the libopts library from AutoGen, you may include it under ## the same distribution terms used by the libopts library. ## Code: AUTOMAKE_OPTIONS = gnits DISTCLEANFILES = compat.h compat.stamp GENPROTO = $(top_srcdir)/genproto GENPROTO_FLAGS = $(top_srcdir)/gendoc.awk GENPROTO_ENVIRONMENT = FORMAT=SNV_GNUC_PRINTF AM_CPPFLAGS = -I$(top_srcdir) if INSTALL_SNPRINTFV include_HEADERS = printf.h pkginclude_HEADERS = mem.h filament.h stream.h nodist_pkginclude_HEADERS = compat.h else noinst_HEADERS = mem.h filament.h stream.h printf.h nodist_noinst_HEADERS = compat.h endif dist_noinst_DATA = filament.stamp stream.stamp printf.stamp CLEANFILES = $(dist_noinst_DATA) EXTRA_LTLIBRARIES = libsnprintfv.la libsnprintfvc.la noinst_LTLIBRARIES = $(convenience_libsnprintfv) lib_LTLIBRARIES = $(installed_libsnprintfv) libsnprintfv_la_LDFLAGS = -no-undefined -rpath $(libdir) -version-info \ @SNV_CURRENT@:@SNV_REVISION@:@SNV_AGE@ libsnprintfv_la_LIBADD = @LTLIBOBJS@ $(LIBADD_DL) libsnprintfv_la_SOURCES = \ filament.c \ format.c \ printf.c \ mem.c \ stream.c \ custom.c libsnprintfvc_la_CPPFLAGS = $(AM_CPPFLAGS) @LIBSNPRINTFVC_PRINT_FLOATS@ libsnprintfvc_la_LIBADD = @LTLIBOBJS@ libsnprintfvc_la_SOURCES= \ filament.c \ format.c \ printf.c \ mem.c \ stream.c \ custom.c # These files are the raw sources used to generate similarly named # header files after extracting the prototypes from the sources # EXTRA_DIST = \ compat.in \ filament.in \ printf.in \ stream.in BUILT_SOURCES = \ compat.h \ filament.h \ printf.h \ stream.h gen: $(BUILT_SOURCES) # # Make sure the prototypes are reextracted if the sources change # SUFFIXES = .stamp .in .h .c # Create these in the source directory because that is where # they are when the distribution tarball is unpacked. $(srcdir)/%.h: %.stamp @: %.stamp: %.in @file=`echo $@ | $(SED) 's,\.stamp$$,.h,'`; \ $(GENPROTO_ENVIRONMENT) $(GENPROTO) $(GENPROTO_FLAGS) $^ > \ $${file}T; \ if cmp -s $(srcdir)/$$file $${file}T; then \ echo $$file is unchanged; rm -f $${file}T; \ else \ echo creating $(srcdir)/$$file; mv -f $${file}T $(srcdir)/$$file; \ fi @echo timestamp > $@ printf.h: printf.stamp filament.h: filament.stamp stream.h: stream.stamp printf.stamp: printf.in printf.c format.c custom.c filament.stamp: filament.in filament.c stream.stamp: stream.in stream.c # # compat.h is generated differently, so we can't use the pattern rule # above: # compat.h: compat.stamp compat.stamp: $(srcdir)/compat.in $(top_builddir)/config.status cd $(top_builddir) \ && $(SHELL) ./config.status snprintfv/compat.h echo timestamp > $@ # Makefile.am ends here smalltalk-3.2.5/snprintfv/snprintfv/filament.c0000644000175000017500000001614612123404352016457 00000000000000/* -*- Mode: C -*- */ /* filament.c --- a bit like a string, but different =)O| * Copyright (C) 1999 Gary V. Vaughan * Originally by Gary V. Vaughan, 1999 * This file is part of Snprintfv * * Snprintfv is free software; you can redistribute it and/or * modify it under the terms of the GNU General Public License as * published by the Free Software Foundation; either version 2 of the * License, or (at your option) any later version. * * Snprintfv program is distributed in the hope that it will be useful, * but WITHOUT ANY WARRANTY; without even the implied warranty of * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU * General Public License for more details. * * You should have received a copy of the GNU General Public License * along with this program. If not, write to the Free Software * Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * * As a special exception to the GNU General Public License, if you * distribute this file as part of a program that also links with and * uses the libopts library from AutoGen, you may include it under * the same distribution terms used by the libopts library. */ /* Commentary: * * Try to exploit usage patterns to optimise string handling, and * as a happy consequence handle NUL's embedded in strings properly. * * o Since finding the length of a (long) string is time consuming and * requires careful coding to cache the result in local scope: We * keep count of the length of a Filament all the time, so finding the * length is O(1) at the expense of a little bookkeeping while * manipulating the Filament contents. * * o Constantly resizing a block of memory to hold a string is memory * efficient, but slow: Filaments are only ever expanded in size, * doubling at each step to minimise the number of times the block * needs to be reallocated and the contents copied (this problem is * especially poignant for very large strings). * * o Most strings tend to be either relatively small and short-lived, * or else long-lived but growing in asymptotically in size: To * care for the former case, Filaments start off with a modest static * buffer for the string contents to avoid any mallocations (except * the initial one to get the structure!); the latter case is handled * gracefully by the resizing algorithm in the previous point. * * o Extracting a C-style NUL terminated string from the Filament is * an extremely common operation: We ensure there is always a * terminating NUL character after the last character in the string * so that the conversion can be performed quickly. * * In summary, Filaments are good where you need to do a lot of length * calculations with your strings and/or gradually append more text * onto existing strings. Filaments are also an easy way to get 8-bit * clean strings is a more lightweight approach isn't required. * * They probably don't buy much if you need to do insertions and partial * deletions, but optimising for that is a whole other problem! */ /* Code: */ #ifdef HAVE_CONFIG_H # include #endif #ifdef WITH_DMALLOC # include #endif #include "mem.h" #include "filament.h" /** * filnew: constructor * @init: address of the first byte to copy into the new object. * @len: the number of bytes to copy into the new object. * * Create a new Filament object, initialised to hold a copy of the * first @len bytes starting at address @init. If @init is NULL, or * @len is 0 (or less), then the initialised Filament will return the * empty string, "", if its value is queried. * * Return value: * A newly created Filament object is returned. **/ Filament * filnew (const char *const init, size_t len) { Filament *new; new = snv_new (Filament, 1); new->value = new->buffer; new->length = 0; new->size = FILAMENT_BUFSIZ; return (init || len) ? filinit (new, init, len) : new; } /** * filinit: * @fil: The Filament object to initialise. * @init: address of the first byte to copy into the new object. * @len: the number of bytes to copy into the new object. * * Initialise a Filament object to hold a copy of the first @len bytes * starting at address @init. If @init is NULL, or @len is 0 (or less), * then the Filament will be reset to hold the empty string, "". * * Return value: * The initialised Filament object is returned. **/ Filament * filinit (Filament *fil, const char *const init, size_t len) { if (init == NULL || len < 1) { /* Recycle any dynamic memory assigned to the previous contents of @fil, and point back into the static buffer. */ if (fil->value != fil->buffer) snv_delete (fil->value); fil->value = fil->buffer; fil->length = 0; fil->size = FILAMENT_BUFSIZ; } else { if (len < FILAMENT_BUFSIZ) { /* We have initialisation data which will easily fit into the static buffer: recycle any memory already assigned and initialise in the static buffer. */ if (fil->value != fil->buffer) { snv_delete (fil->value); fil->value = fil->buffer; fil->size = FILAMENT_BUFSIZ; } } else { /* If we get to here then we never try to shrink the already allocated dynamic buffer (if any), we just leave it in place all ready to expand into later... */ fil_maybe_extend (fil, len, FALSE); } snv_assert (len < fil->size); fil->length = len; memcpy (fil->value, init, len); } return fil; } /** * fildelete: destructor * @fil: The Filament object for recycling. * * The memory being used by @fil is recycled. * * Return value: * The original contents of @fil are converted to a null terminated * string which is returned, either to be freed itself or else used * as a normal C string. The entire Filament contents are copied into * this string including any embedded nulls. **/ char * fildelete (Filament *fil) { char *value; if (fil->value == fil->buffer) { value = memcpy (snv_new (char, 1 + fil->length), fil->buffer, 1 + fil->length); value[fil->length] = '\0'; } else value = filval (fil); snv_delete (fil); return value; } /** * _fil_extend: * @fil: The Filament object which may need more string space. * @len: The length of the data to be stored in @fil. * @copy: whether to copy data from the static buffer on reallocation. * * This function will will assign a bigger block of memory to @fil * considering the space left in @fil and @len, the length required * for the prospective contents. */ void _fil_extend (Filament *fil, size_t len, boolean copy) { /* Usually we will simply double the amount of space previously allocated, but if the extra data is larger than the current size it *still* won't fit, so in that case we allocate enough room plus some we leave the current free space to expand into. */ fil->size += MAX (len, fil->size); if (fil->value == fil->buffer) { fil->value = snv_new (char, fil->size); if (copy) memcpy (fil->value, fil->buffer, fil->length); } else fil->value = snv_renew (char, fil->value, fil->size); } /* Filament.c ends here */ smalltalk-3.2.5/snprintfv/snprintfv/stream.in0000644000175000017500000000537212123404352016336 00000000000000/* -*- Mode: C -*- */ /* stream.h --- customizable stream routines * Copyright (C) 1998, 1999, 2000, 2002 Gary V. Vaughan * Originally by Gary V. Vaughan, 1998 * This file is part of Snprintfv * * Snprintfv is free software; you can redistribute it and/or * modify it under the terms of the GNU General Public License as * published by the Free Software Foundation; either version 2 of the * License, or (at your option) any later version. * * Snprintfv program is distributed in the hope that it will be useful, * but WITHOUT ANY WARRANTY; without even the implied warranty of * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU * General Public License for more details. * * You should have received a copy of the GNU General Public License * along with this program. If not, write to the Free Software * Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * * As a special exception to the GNU General Public License, if you * distribute this file as part of a program that also links with and * uses the libopts library from AutoGen, you may include it under * the same distribution terms used by the libopts library. */ /* Code: */ #ifndef STREAM_H #define STREAM_H 1 #define STREAM_READABLE (1 << 0) #define STREAM_WRITABLE (1 << 1) /** * SNV_UNLIMITED: * Used to denote that there is no upper limit to the number of characters * that can safely be written to a stream. **/ #define SNV_UNLIMITED ~(0L) #ifdef __cplusplus extern "C" { #if 0 /* This brace is so that emacs can still indent properly: */ } #endif #endif /* __cplusplus */ /** * STREAM: * Data type used to pass details of streams between functions, * much like stdio's %FILE, but more flexible. A %STREAM can be uni- or * bi-directional depending on how it is initialised. **/ typedef struct stream STREAM; /** * StreamPut: * @ch: The character to write to @stream cast to an int. * @stream: The stream being written to. * * Type of the function to put a character in a writeable stream. * * Return value: * The function should return the character written to the * stream, cast to an int if it was written successfully, or * else %EOF, if the write failed. **/ typedef int (*StreamPut) (int ch, STREAM * stream); /** * StreamGet: * @stream: The stream being read from. * * Type of the function to get a character from a readable stream. * * Return value: * The function should return the character read from the * stream, cast to an int if it was read successfully, or * else %EOF, if the read failed. **/ typedef int (*StreamGet) (STREAM * stream); @protos stream.c #ifdef __cplusplus #if 0 /* This brace is so that emacs can still indent properly: */ { #endif } #endif /* __cplusplus */ #endif /* STREAM_H */ smalltalk-3.2.5/snprintfv/snprintfv/mem.h0000644000175000017500000000561112123404352015436 00000000000000/* -*- Mode: C -*- */ /* mem.h --- memory handling macros * Copyright (C) 1999 Gary V. Vaughan * Originally by Gary V. Vaughan, 1999 * This file is part of Snprintfv * * Snprintfv is free software; you can redistribute it and/or * modify it under the terms of the GNU General Public License as * published by the Free Software Foundation; either version 2 of the * License, or (at your option) any later version. * * Snprintfv program is distributed in the hope that it will be useful, * but WITHOUT ANY WARRANTY; without even the implied warranty of * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU * General Public License for more details. * * You should have received a copy of the GNU General Public License * along with this program. If not, write to the Free Software * Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * * As a special exception to the GNU General Public License, if you * distribute this file as part of a program that also links with and * uses the libopts library from AutoGen, you may include it under * the same distribution terms used by the libopts library. */ /* Code: */ #ifndef SNPRINTFV_MEM_H #define SNPRINTFV_MEM_H 1 #include #ifdef WITH_DMALLOC # include #endif /* This is the API we use throughout libsnprintfv. */ #define snv_new(type, count) \ ((type*)snv_malloc((size_t)sizeof(type) * (count))) #define snv_renew(type, ptr, count) \ ((type*)snv_xrealloc((ptr), (size_t)sizeof(type) * (count))) #define snv_delete(old) snv_free(old) #ifdef __cplusplus extern "C" { #endif /* __cplusplus */ /* These function pointers are exposed through the API incase a user of this library needs to map our memory management routines to their own (e.g. xmalloc). */ /** * snv_malloc: * @count: The number of bytes to allocate. * * Allocates a fresh block of memory whose size is @count bytes. * * Return value: * The pointer to the newly-allocated memory area. */ SNV_SCOPE snv_pointer (*snv_malloc) (size_t count); /** * snv_realloc: * @old: The pointer to the block whose size must be changed. * @count: The number of bytes to allocate. * * Reallocates a fresh block of memory pointed to by @old * so that its size becomes @count bytes. * * Return value: * The pointer to the newly-allocated memory area, possibly * the same as @old. */ SNV_SCOPE snv_pointer (*snv_realloc) (snv_pointer old, size_t count); /** * snv_free: * @old: The pointer to the block that must freed. * * Frees a block of memory pointed to by @old. */ SNV_SCOPE void (*snv_free) (snv_pointer old); /* And these are reimplemented tout court because they are not fully portable. */ extern snv_pointer snv_xrealloc (snv_pointer old, size_t count); extern char* snv_strdup (const char *str); #ifdef __cplusplus } #endif /* __cplusplus */ #endif /* SNPRINTFV_MEM_H */ /* mem.h ends here */ smalltalk-3.2.5/snprintfv/snprintfv/Makefile.in0000644000175000017500000007701312130455536016571 00000000000000# Makefile.in generated by automake 1.11.6 from Makefile.am. # @configure_input@ # Copyright (C) 1994, 1995, 1996, 1997, 1998, 1999, 2000, 2001, 2002, # 2003, 2004, 2005, 2006, 2007, 2008, 2009, 2010, 2011 Free Software # Foundation, Inc. # This Makefile.in is free software; the Free Software Foundation # gives unlimited permission to copy and/or distribute it, # with or without modifications, as long as this notice is preserved. # This program is distributed in the hope that it will be useful, # but WITHOUT ANY WARRANTY, to the extent permitted by law; without # even the implied warranty of MERCHANTABILITY or FITNESS FOR A # PARTICULAR PURPOSE. @SET_MAKE@ VPATH = @srcdir@ am__make_dryrun = \ { \ am__dry=no; \ case $$MAKEFLAGS in \ *\\[\ \ ]*) \ echo 'am--echo: ; @echo "AM" OK' | $(MAKE) -f - 2>/dev/null \ | grep '^AM OK$$' >/dev/null || am__dry=yes;; \ *) \ for am__flg in $$MAKEFLAGS; do \ case $$am__flg in \ *=*|--*) ;; \ *n*) am__dry=yes; break;; \ esac; \ done;; \ esac; \ test $$am__dry = yes; \ } pkgdatadir = $(datadir)/@PACKAGE@ pkgincludedir = $(includedir)/@PACKAGE@ pkglibdir = $(libdir)/@PACKAGE@ pkglibexecdir = $(libexecdir)/@PACKAGE@ am__cd = CDPATH="$${ZSH_VERSION+.}$(PATH_SEPARATOR)" && cd install_sh_DATA = $(install_sh) -c -m 644 install_sh_PROGRAM = $(install_sh) -c install_sh_SCRIPT = $(install_sh) -c INSTALL_HEADER = $(INSTALL_DATA) transform = $(program_transform_name) NORMAL_INSTALL = : PRE_INSTALL = : POST_INSTALL = : NORMAL_UNINSTALL = : PRE_UNINSTALL = : POST_UNINSTALL = : build_triplet = @build@ host_triplet = @host@ subdir = snprintfv DIST_COMMON = $(am__include_HEADERS_DIST) $(am__noinst_HEADERS_DIST) \ $(am__pkginclude_HEADERS_DIST) $(dist_noinst_DATA) \ $(srcdir)/Makefile.am $(srcdir)/Makefile.in ACLOCAL_M4 = $(top_srcdir)/aclocal.m4 am__aclocal_m4_deps = $(top_srcdir)/../build-aux/libtool.m4 \ $(top_srcdir)/../build-aux/ltoptions.m4 \ $(top_srcdir)/../build-aux/ltsugar.m4 \ $(top_srcdir)/../build-aux/ltversion.m4 \ $(top_srcdir)/../build-aux/lt~obsolete.m4 \ $(top_srcdir)/configure.ac am__configure_deps = $(am__aclocal_m4_deps) $(CONFIGURE_DEPENDENCIES) \ $(ACLOCAL_M4) mkinstalldirs = $(install_sh) -d CONFIG_HEADER = $(top_builddir)/config.h CONFIG_CLEAN_FILES = CONFIG_CLEAN_VPATH_FILES = am__vpath_adj_setup = srcdirstrip=`echo "$(srcdir)" | sed 's|.|.|g'`; am__vpath_adj = case $$p in \ $(srcdir)/*) f=`echo "$$p" | sed "s|^$$srcdirstrip/||"`;; \ *) f=$$p;; \ esac; am__strip_dir = f=`echo $$p | sed -e 's|^.*/||'`; am__install_max = 40 am__nobase_strip_setup = \ srcdirstrip=`echo "$(srcdir)" | sed 's/[].[^$$\\*|]/\\\\&/g'` am__nobase_strip = \ for p in $$list; do echo "$$p"; done | sed -e "s|$$srcdirstrip/||" am__nobase_list = $(am__nobase_strip_setup); \ for p in $$list; do echo "$$p $$p"; done | \ sed "s| $$srcdirstrip/| |;"' / .*\//!s/ .*/ ./; s,\( .*\)/[^/]*$$,\1,' | \ $(AWK) 'BEGIN { files["."] = "" } { files[$$2] = files[$$2] " " $$1; \ if (++n[$$2] == $(am__install_max)) \ { print $$2, files[$$2]; n[$$2] = 0; files[$$2] = "" } } \ END { for (dir in files) print dir, files[dir] }' am__base_list = \ sed '$$!N;$$!N;$$!N;$$!N;$$!N;$$!N;$$!N;s/\n/ /g' | \ sed '$$!N;$$!N;$$!N;$$!N;s/\n/ /g' am__uninstall_files_from_dir = { \ test -z "$$files" \ || { test ! -d "$$dir" && test ! -f "$$dir" && test ! -r "$$dir"; } \ || { echo " ( cd '$$dir' && rm -f" $$files ")"; \ $(am__cd) "$$dir" && rm -f $$files; }; \ } am__installdirs = "$(DESTDIR)$(libdir)" "$(DESTDIR)$(includedir)" \ "$(DESTDIR)$(pkgincludedir)" "$(DESTDIR)$(pkgincludedir)" LTLIBRARIES = $(lib_LTLIBRARIES) $(noinst_LTLIBRARIES) libsnprintfv_la_DEPENDENCIES = @LTLIBOBJS@ am_libsnprintfv_la_OBJECTS = filament.lo format.lo printf.lo mem.lo \ stream.lo custom.lo libsnprintfv_la_OBJECTS = $(am_libsnprintfv_la_OBJECTS) libsnprintfv_la_LINK = $(LIBTOOL) --tag=CC $(AM_LIBTOOLFLAGS) \ $(LIBTOOLFLAGS) --mode=link $(CCLD) $(AM_CFLAGS) $(CFLAGS) \ $(libsnprintfv_la_LDFLAGS) $(LDFLAGS) -o $@ libsnprintfvc_la_DEPENDENCIES = @LTLIBOBJS@ am_libsnprintfvc_la_OBJECTS = libsnprintfvc_la-filament.lo \ libsnprintfvc_la-format.lo libsnprintfvc_la-printf.lo \ libsnprintfvc_la-mem.lo libsnprintfvc_la-stream.lo \ libsnprintfvc_la-custom.lo libsnprintfvc_la_OBJECTS = $(am_libsnprintfvc_la_OBJECTS) DEFAULT_INCLUDES = -I.@am__isrc@ -I$(top_builddir) depcomp = $(SHELL) $(top_srcdir)/../build-aux/depcomp am__depfiles_maybe = depfiles am__mv = mv -f COMPILE = $(CC) $(DEFS) $(DEFAULT_INCLUDES) $(INCLUDES) $(AM_CPPFLAGS) \ $(CPPFLAGS) $(AM_CFLAGS) $(CFLAGS) LTCOMPILE = $(LIBTOOL) --tag=CC $(AM_LIBTOOLFLAGS) $(LIBTOOLFLAGS) \ --mode=compile $(CC) $(DEFS) $(DEFAULT_INCLUDES) $(INCLUDES) \ $(AM_CPPFLAGS) $(CPPFLAGS) $(AM_CFLAGS) $(CFLAGS) CCLD = $(CC) LINK = $(LIBTOOL) --tag=CC $(AM_LIBTOOLFLAGS) $(LIBTOOLFLAGS) \ --mode=link $(CCLD) $(AM_CFLAGS) $(CFLAGS) $(AM_LDFLAGS) \ $(LDFLAGS) -o $@ SOURCES = $(libsnprintfv_la_SOURCES) $(libsnprintfvc_la_SOURCES) DIST_SOURCES = $(libsnprintfv_la_SOURCES) $(libsnprintfvc_la_SOURCES) am__can_run_installinfo = \ case $$AM_UPDATE_INFO_DIR in \ n|no|NO) false;; \ *) (install-info --version) >/dev/null 2>&1;; \ esac DATA = $(dist_noinst_DATA) am__include_HEADERS_DIST = printf.h am__noinst_HEADERS_DIST = mem.h filament.h stream.h printf.h am__pkginclude_HEADERS_DIST = mem.h filament.h stream.h HEADERS = $(include_HEADERS) $(nodist_noinst_HEADERS) \ $(nodist_pkginclude_HEADERS) $(noinst_HEADERS) \ $(pkginclude_HEADERS) ETAGS = etags CTAGS = ctags DISTFILES = $(DIST_COMMON) $(DIST_SOURCES) $(TEXINFOS) $(EXTRA_DIST) ACLOCAL = @ACLOCAL@ AMTAR = @AMTAR@ AR = @AR@ AS = @AS@ AUTOCONF = @AUTOCONF@ AUTOHEADER = @AUTOHEADER@ AUTOMAKE = @AUTOMAKE@ AWK = @AWK@ CC = @CC@ CCDEPMODE = @CCDEPMODE@ CFLAGS = @CFLAGS@ CPP = @CPP@ CPPFLAGS = @CPPFLAGS@ CYGPATH_W = @CYGPATH_W@ DEFS = @DEFS@ DEPDIR = @DEPDIR@ DLLTOOL = @DLLTOOL@ DSYMUTIL = @DSYMUTIL@ DUMPBIN = @DUMPBIN@ ECHO_C = @ECHO_C@ ECHO_N = @ECHO_N@ ECHO_T = @ECHO_T@ EGREP = @EGREP@ EXEEXT = @EXEEXT@ FGREP = @FGREP@ GREP = @GREP@ INCLUDES = @INCLUDES@ INSTALL = @INSTALL@ INSTALL_DATA = @INSTALL_DATA@ INSTALL_PROGRAM = @INSTALL_PROGRAM@ INSTALL_SCRIPT = @INSTALL_SCRIPT@ INSTALL_STRIP_PROGRAM = @INSTALL_STRIP_PROGRAM@ LD = @LD@ LDFLAGS = @LDFLAGS@ LIBOBJS = @LIBOBJS@ LIBS = @LIBS@ LIBSNPRINTFVC_PRINT_FLOATS = @LIBSNPRINTFVC_PRINT_FLOATS@ LIBTOOL = @LIBTOOL@ LIPO = @LIPO@ LN_S = @LN_S@ LTLIBOBJS = @LTLIBOBJS@ MAKEINFO = @MAKEINFO@ MANIFEST_TOOL = @MANIFEST_TOOL@ MKDIR_P = @MKDIR_P@ NM = @NM@ NMEDIT = @NMEDIT@ OBJDUMP = @OBJDUMP@ OBJEXT = @OBJEXT@ OTOOL = @OTOOL@ OTOOL64 = @OTOOL64@ PACKAGE = @PACKAGE@ PACKAGE_BUGREPORT = @PACKAGE_BUGREPORT@ PACKAGE_NAME = @PACKAGE_NAME@ PACKAGE_STRING = @PACKAGE_STRING@ PACKAGE_TARNAME = @PACKAGE_TARNAME@ PACKAGE_URL = @PACKAGE_URL@ PACKAGE_VERSION = @PACKAGE_VERSION@ PATH_SEPARATOR = @PATH_SEPARATOR@ RANLIB = @RANLIB@ SED = @SED@ SET_MAKE = @SET_MAKE@ SHELL = @SHELL@ SNV_AGE = @SNV_AGE@ SNV_CURRENT = @SNV_CURRENT@ SNV_REVISION = @SNV_REVISION@ STRIP = @STRIP@ VERSION = @VERSION@ abs_builddir = @abs_builddir@ abs_srcdir = @abs_srcdir@ abs_top_builddir = @abs_top_builddir@ abs_top_srcdir = @abs_top_srcdir@ ac_aux_dir = @ac_aux_dir@ ac_ct_AR = @ac_ct_AR@ ac_ct_CC = @ac_ct_CC@ ac_ct_DUMPBIN = @ac_ct_DUMPBIN@ am__include = @am__include@ am__leading_dot = @am__leading_dot@ am__quote = @am__quote@ am__tar = @am__tar@ am__untar = @am__untar@ bindir = @bindir@ build = @build@ build_alias = @build_alias@ build_cpu = @build_cpu@ build_os = @build_os@ build_vendor = @build_vendor@ builddir = @builddir@ convenience_libsnprintfv = @convenience_libsnprintfv@ datadir = @datadir@ datarootdir = @datarootdir@ docdir = @docdir@ dvidir = @dvidir@ exec_prefix = @exec_prefix@ host = @host@ host_alias = @host_alias@ host_cpu = @host_cpu@ host_os = @host_os@ host_vendor = @host_vendor@ htmldir = @htmldir@ includedir = @includedir@ infodir = @infodir@ install_sh = @install_sh@ installed_libsnprintfv = @installed_libsnprintfv@ libdir = @libdir@ libexecdir = @libexecdir@ localedir = @localedir@ localstatedir = @localstatedir@ mandir = @mandir@ mkdir_p = @mkdir_p@ oldincludedir = @oldincludedir@ pdfdir = @pdfdir@ prefix = @prefix@ program_transform_name = @program_transform_name@ psdir = @psdir@ sbindir = @sbindir@ sharedstatedir = @sharedstatedir@ srcdir = @srcdir@ sysconfdir = @sysconfdir@ target_alias = @target_alias@ top_build_prefix = @top_build_prefix@ top_builddir = @top_builddir@ top_srcdir = @top_srcdir@ AUTOMAKE_OPTIONS = gnits DISTCLEANFILES = compat.h compat.stamp GENPROTO = $(top_srcdir)/genproto GENPROTO_FLAGS = $(top_srcdir)/gendoc.awk GENPROTO_ENVIRONMENT = FORMAT=SNV_GNUC_PRINTF AM_CPPFLAGS = -I$(top_srcdir) @INSTALL_SNPRINTFV_TRUE@include_HEADERS = printf.h @INSTALL_SNPRINTFV_TRUE@pkginclude_HEADERS = mem.h filament.h stream.h @INSTALL_SNPRINTFV_TRUE@nodist_pkginclude_HEADERS = compat.h @INSTALL_SNPRINTFV_FALSE@noinst_HEADERS = mem.h filament.h stream.h printf.h @INSTALL_SNPRINTFV_FALSE@nodist_noinst_HEADERS = compat.h dist_noinst_DATA = filament.stamp stream.stamp printf.stamp CLEANFILES = $(dist_noinst_DATA) EXTRA_LTLIBRARIES = libsnprintfv.la libsnprintfvc.la noinst_LTLIBRARIES = $(convenience_libsnprintfv) lib_LTLIBRARIES = $(installed_libsnprintfv) libsnprintfv_la_LDFLAGS = -no-undefined -rpath $(libdir) -version-info \ @SNV_CURRENT@:@SNV_REVISION@:@SNV_AGE@ libsnprintfv_la_LIBADD = @LTLIBOBJS@ $(LIBADD_DL) libsnprintfv_la_SOURCES = \ filament.c \ format.c \ printf.c \ mem.c \ stream.c \ custom.c libsnprintfvc_la_CPPFLAGS = $(AM_CPPFLAGS) @LIBSNPRINTFVC_PRINT_FLOATS@ libsnprintfvc_la_LIBADD = @LTLIBOBJS@ libsnprintfvc_la_SOURCES = \ filament.c \ format.c \ printf.c \ mem.c \ stream.c \ custom.c # These files are the raw sources used to generate similarly named # header files after extracting the prototypes from the sources # EXTRA_DIST = \ compat.in \ filament.in \ printf.in \ stream.in BUILT_SOURCES = \ compat.h \ filament.h \ printf.h \ stream.h # # Make sure the prototypes are reextracted if the sources change # SUFFIXES = .stamp .in .h .c all: $(BUILT_SOURCES) $(MAKE) $(AM_MAKEFLAGS) all-am .SUFFIXES: .SUFFIXES: .stamp .in .h .c .lo .o .obj $(srcdir)/Makefile.in: $(srcdir)/Makefile.am $(am__configure_deps) @for dep in $?; do \ case '$(am__configure_deps)' in \ *$$dep*) \ ( cd $(top_builddir) && $(MAKE) $(AM_MAKEFLAGS) am--refresh ) \ && { if test -f $@; then exit 0; else break; fi; }; \ exit 1;; \ esac; \ done; \ echo ' cd $(top_srcdir) && $(AUTOMAKE) --gnits snprintfv/Makefile'; \ $(am__cd) $(top_srcdir) && \ $(AUTOMAKE) --gnits snprintfv/Makefile .PRECIOUS: Makefile Makefile: $(srcdir)/Makefile.in $(top_builddir)/config.status @case '$?' in \ *config.status*) \ cd $(top_builddir) && $(MAKE) $(AM_MAKEFLAGS) am--refresh;; \ *) \ echo ' cd $(top_builddir) && $(SHELL) ./config.status $(subdir)/$@ $(am__depfiles_maybe)'; \ cd $(top_builddir) && $(SHELL) ./config.status $(subdir)/$@ $(am__depfiles_maybe);; \ esac; $(top_builddir)/config.status: $(top_srcdir)/configure $(CONFIG_STATUS_DEPENDENCIES) cd $(top_builddir) && $(MAKE) $(AM_MAKEFLAGS) am--refresh $(top_srcdir)/configure: $(am__configure_deps) cd $(top_builddir) && $(MAKE) $(AM_MAKEFLAGS) am--refresh $(ACLOCAL_M4): $(am__aclocal_m4_deps) cd $(top_builddir) && $(MAKE) $(AM_MAKEFLAGS) am--refresh $(am__aclocal_m4_deps): install-libLTLIBRARIES: $(lib_LTLIBRARIES) @$(NORMAL_INSTALL) @list='$(lib_LTLIBRARIES)'; test -n "$(libdir)" || list=; \ list2=; for p in $$list; do \ if test -f $$p; then \ list2="$$list2 $$p"; \ else :; fi; \ done; \ test -z "$$list2" || { \ echo " $(MKDIR_P) '$(DESTDIR)$(libdir)'"; \ $(MKDIR_P) "$(DESTDIR)$(libdir)" || exit 1; \ echo " $(LIBTOOL) $(AM_LIBTOOLFLAGS) $(LIBTOOLFLAGS) --mode=install $(INSTALL) $(INSTALL_STRIP_FLAG) $$list2 '$(DESTDIR)$(libdir)'"; \ $(LIBTOOL) $(AM_LIBTOOLFLAGS) $(LIBTOOLFLAGS) --mode=install $(INSTALL) $(INSTALL_STRIP_FLAG) $$list2 "$(DESTDIR)$(libdir)"; \ } uninstall-libLTLIBRARIES: @$(NORMAL_UNINSTALL) @list='$(lib_LTLIBRARIES)'; test -n "$(libdir)" || list=; \ for p in $$list; do \ $(am__strip_dir) \ echo " $(LIBTOOL) $(AM_LIBTOOLFLAGS) $(LIBTOOLFLAGS) --mode=uninstall rm -f '$(DESTDIR)$(libdir)/$$f'"; \ $(LIBTOOL) $(AM_LIBTOOLFLAGS) $(LIBTOOLFLAGS) --mode=uninstall rm -f "$(DESTDIR)$(libdir)/$$f"; \ done clean-libLTLIBRARIES: -test -z "$(lib_LTLIBRARIES)" || rm -f $(lib_LTLIBRARIES) @list='$(lib_LTLIBRARIES)'; for p in $$list; do \ dir="`echo $$p | sed -e 's|/[^/]*$$||'`"; \ test "$$dir" != "$$p" || dir=.; \ echo "rm -f \"$${dir}/so_locations\""; \ rm -f "$${dir}/so_locations"; \ done clean-noinstLTLIBRARIES: -test -z "$(noinst_LTLIBRARIES)" || rm -f $(noinst_LTLIBRARIES) @list='$(noinst_LTLIBRARIES)'; for p in $$list; do \ dir="`echo $$p | sed -e 's|/[^/]*$$||'`"; \ test "$$dir" != "$$p" || dir=.; \ echo "rm -f \"$${dir}/so_locations\""; \ rm -f "$${dir}/so_locations"; \ done libsnprintfv.la: $(libsnprintfv_la_OBJECTS) $(libsnprintfv_la_DEPENDENCIES) $(EXTRA_libsnprintfv_la_DEPENDENCIES) $(libsnprintfv_la_LINK) $(libsnprintfv_la_OBJECTS) $(libsnprintfv_la_LIBADD) $(LIBS) libsnprintfvc.la: $(libsnprintfvc_la_OBJECTS) $(libsnprintfvc_la_DEPENDENCIES) $(EXTRA_libsnprintfvc_la_DEPENDENCIES) $(LINK) $(libsnprintfvc_la_OBJECTS) $(libsnprintfvc_la_LIBADD) $(LIBS) mostlyclean-compile: -rm -f *.$(OBJEXT) distclean-compile: -rm -f *.tab.c @AMDEP_TRUE@@am__include@ @am__quote@./$(DEPDIR)/custom.Plo@am__quote@ @AMDEP_TRUE@@am__include@ @am__quote@./$(DEPDIR)/filament.Plo@am__quote@ @AMDEP_TRUE@@am__include@ @am__quote@./$(DEPDIR)/format.Plo@am__quote@ @AMDEP_TRUE@@am__include@ @am__quote@./$(DEPDIR)/libsnprintfvc_la-custom.Plo@am__quote@ @AMDEP_TRUE@@am__include@ @am__quote@./$(DEPDIR)/libsnprintfvc_la-filament.Plo@am__quote@ @AMDEP_TRUE@@am__include@ @am__quote@./$(DEPDIR)/libsnprintfvc_la-format.Plo@am__quote@ @AMDEP_TRUE@@am__include@ @am__quote@./$(DEPDIR)/libsnprintfvc_la-mem.Plo@am__quote@ @AMDEP_TRUE@@am__include@ @am__quote@./$(DEPDIR)/libsnprintfvc_la-printf.Plo@am__quote@ @AMDEP_TRUE@@am__include@ @am__quote@./$(DEPDIR)/libsnprintfvc_la-stream.Plo@am__quote@ @AMDEP_TRUE@@am__include@ @am__quote@./$(DEPDIR)/mem.Plo@am__quote@ @AMDEP_TRUE@@am__include@ @am__quote@./$(DEPDIR)/printf.Plo@am__quote@ @AMDEP_TRUE@@am__include@ @am__quote@./$(DEPDIR)/stream.Plo@am__quote@ .c.o: @am__fastdepCC_TRUE@ $(COMPILE) -MT $@ -MD -MP -MF $(DEPDIR)/$*.Tpo -c -o $@ $< @am__fastdepCC_TRUE@ $(am__mv) $(DEPDIR)/$*.Tpo $(DEPDIR)/$*.Po @AMDEP_TRUE@@am__fastdepCC_FALSE@ source='$<' object='$@' libtool=no @AMDEPBACKSLASH@ @AMDEP_TRUE@@am__fastdepCC_FALSE@ DEPDIR=$(DEPDIR) $(CCDEPMODE) $(depcomp) @AMDEPBACKSLASH@ @am__fastdepCC_FALSE@ $(COMPILE) -c $< .c.obj: @am__fastdepCC_TRUE@ $(COMPILE) -MT $@ -MD -MP -MF $(DEPDIR)/$*.Tpo -c -o $@ `$(CYGPATH_W) '$<'` @am__fastdepCC_TRUE@ $(am__mv) $(DEPDIR)/$*.Tpo $(DEPDIR)/$*.Po @AMDEP_TRUE@@am__fastdepCC_FALSE@ source='$<' object='$@' libtool=no @AMDEPBACKSLASH@ @AMDEP_TRUE@@am__fastdepCC_FALSE@ DEPDIR=$(DEPDIR) $(CCDEPMODE) $(depcomp) @AMDEPBACKSLASH@ @am__fastdepCC_FALSE@ $(COMPILE) -c `$(CYGPATH_W) '$<'` .c.lo: @am__fastdepCC_TRUE@ $(LTCOMPILE) -MT $@ -MD -MP -MF $(DEPDIR)/$*.Tpo -c -o $@ $< @am__fastdepCC_TRUE@ $(am__mv) $(DEPDIR)/$*.Tpo $(DEPDIR)/$*.Plo @AMDEP_TRUE@@am__fastdepCC_FALSE@ source='$<' object='$@' libtool=yes @AMDEPBACKSLASH@ @AMDEP_TRUE@@am__fastdepCC_FALSE@ DEPDIR=$(DEPDIR) $(CCDEPMODE) $(depcomp) @AMDEPBACKSLASH@ @am__fastdepCC_FALSE@ $(LTCOMPILE) -c -o $@ $< libsnprintfvc_la-filament.lo: filament.c @am__fastdepCC_TRUE@ $(LIBTOOL) --tag=CC $(AM_LIBTOOLFLAGS) $(LIBTOOLFLAGS) --mode=compile $(CC) $(DEFS) $(DEFAULT_INCLUDES) $(INCLUDES) $(libsnprintfvc_la_CPPFLAGS) $(CPPFLAGS) $(AM_CFLAGS) $(CFLAGS) -MT libsnprintfvc_la-filament.lo -MD -MP -MF $(DEPDIR)/libsnprintfvc_la-filament.Tpo -c -o libsnprintfvc_la-filament.lo `test -f 'filament.c' || echo '$(srcdir)/'`filament.c @am__fastdepCC_TRUE@ $(am__mv) $(DEPDIR)/libsnprintfvc_la-filament.Tpo $(DEPDIR)/libsnprintfvc_la-filament.Plo @AMDEP_TRUE@@am__fastdepCC_FALSE@ source='filament.c' object='libsnprintfvc_la-filament.lo' libtool=yes @AMDEPBACKSLASH@ @AMDEP_TRUE@@am__fastdepCC_FALSE@ DEPDIR=$(DEPDIR) $(CCDEPMODE) $(depcomp) @AMDEPBACKSLASH@ @am__fastdepCC_FALSE@ $(LIBTOOL) --tag=CC $(AM_LIBTOOLFLAGS) $(LIBTOOLFLAGS) --mode=compile $(CC) $(DEFS) $(DEFAULT_INCLUDES) $(INCLUDES) $(libsnprintfvc_la_CPPFLAGS) $(CPPFLAGS) $(AM_CFLAGS) $(CFLAGS) -c -o libsnprintfvc_la-filament.lo `test -f 'filament.c' || echo '$(srcdir)/'`filament.c libsnprintfvc_la-format.lo: format.c @am__fastdepCC_TRUE@ $(LIBTOOL) --tag=CC $(AM_LIBTOOLFLAGS) $(LIBTOOLFLAGS) --mode=compile $(CC) $(DEFS) $(DEFAULT_INCLUDES) $(INCLUDES) $(libsnprintfvc_la_CPPFLAGS) $(CPPFLAGS) $(AM_CFLAGS) $(CFLAGS) -MT libsnprintfvc_la-format.lo -MD -MP -MF $(DEPDIR)/libsnprintfvc_la-format.Tpo -c -o libsnprintfvc_la-format.lo `test -f 'format.c' || echo '$(srcdir)/'`format.c @am__fastdepCC_TRUE@ $(am__mv) $(DEPDIR)/libsnprintfvc_la-format.Tpo $(DEPDIR)/libsnprintfvc_la-format.Plo @AMDEP_TRUE@@am__fastdepCC_FALSE@ source='format.c' object='libsnprintfvc_la-format.lo' libtool=yes @AMDEPBACKSLASH@ @AMDEP_TRUE@@am__fastdepCC_FALSE@ DEPDIR=$(DEPDIR) $(CCDEPMODE) $(depcomp) @AMDEPBACKSLASH@ @am__fastdepCC_FALSE@ $(LIBTOOL) --tag=CC $(AM_LIBTOOLFLAGS) $(LIBTOOLFLAGS) --mode=compile $(CC) $(DEFS) $(DEFAULT_INCLUDES) $(INCLUDES) $(libsnprintfvc_la_CPPFLAGS) $(CPPFLAGS) $(AM_CFLAGS) $(CFLAGS) -c -o libsnprintfvc_la-format.lo `test -f 'format.c' || echo '$(srcdir)/'`format.c libsnprintfvc_la-printf.lo: printf.c @am__fastdepCC_TRUE@ $(LIBTOOL) --tag=CC $(AM_LIBTOOLFLAGS) $(LIBTOOLFLAGS) --mode=compile $(CC) $(DEFS) $(DEFAULT_INCLUDES) $(INCLUDES) $(libsnprintfvc_la_CPPFLAGS) $(CPPFLAGS) $(AM_CFLAGS) $(CFLAGS) -MT libsnprintfvc_la-printf.lo -MD -MP -MF $(DEPDIR)/libsnprintfvc_la-printf.Tpo -c -o libsnprintfvc_la-printf.lo `test -f 'printf.c' || echo '$(srcdir)/'`printf.c @am__fastdepCC_TRUE@ $(am__mv) $(DEPDIR)/libsnprintfvc_la-printf.Tpo $(DEPDIR)/libsnprintfvc_la-printf.Plo @AMDEP_TRUE@@am__fastdepCC_FALSE@ source='printf.c' object='libsnprintfvc_la-printf.lo' libtool=yes @AMDEPBACKSLASH@ @AMDEP_TRUE@@am__fastdepCC_FALSE@ DEPDIR=$(DEPDIR) $(CCDEPMODE) $(depcomp) @AMDEPBACKSLASH@ @am__fastdepCC_FALSE@ $(LIBTOOL) --tag=CC $(AM_LIBTOOLFLAGS) $(LIBTOOLFLAGS) --mode=compile $(CC) $(DEFS) $(DEFAULT_INCLUDES) $(INCLUDES) $(libsnprintfvc_la_CPPFLAGS) $(CPPFLAGS) $(AM_CFLAGS) $(CFLAGS) -c -o libsnprintfvc_la-printf.lo `test -f 'printf.c' || echo '$(srcdir)/'`printf.c libsnprintfvc_la-mem.lo: mem.c @am__fastdepCC_TRUE@ $(LIBTOOL) --tag=CC $(AM_LIBTOOLFLAGS) $(LIBTOOLFLAGS) --mode=compile $(CC) $(DEFS) $(DEFAULT_INCLUDES) $(INCLUDES) $(libsnprintfvc_la_CPPFLAGS) $(CPPFLAGS) $(AM_CFLAGS) $(CFLAGS) -MT libsnprintfvc_la-mem.lo -MD -MP -MF $(DEPDIR)/libsnprintfvc_la-mem.Tpo -c -o libsnprintfvc_la-mem.lo `test -f 'mem.c' || echo '$(srcdir)/'`mem.c @am__fastdepCC_TRUE@ $(am__mv) $(DEPDIR)/libsnprintfvc_la-mem.Tpo $(DEPDIR)/libsnprintfvc_la-mem.Plo @AMDEP_TRUE@@am__fastdepCC_FALSE@ source='mem.c' object='libsnprintfvc_la-mem.lo' libtool=yes @AMDEPBACKSLASH@ @AMDEP_TRUE@@am__fastdepCC_FALSE@ DEPDIR=$(DEPDIR) $(CCDEPMODE) $(depcomp) @AMDEPBACKSLASH@ @am__fastdepCC_FALSE@ $(LIBTOOL) --tag=CC $(AM_LIBTOOLFLAGS) $(LIBTOOLFLAGS) --mode=compile $(CC) $(DEFS) $(DEFAULT_INCLUDES) $(INCLUDES) $(libsnprintfvc_la_CPPFLAGS) $(CPPFLAGS) $(AM_CFLAGS) $(CFLAGS) -c -o libsnprintfvc_la-mem.lo `test -f 'mem.c' || echo '$(srcdir)/'`mem.c libsnprintfvc_la-stream.lo: stream.c @am__fastdepCC_TRUE@ $(LIBTOOL) --tag=CC $(AM_LIBTOOLFLAGS) $(LIBTOOLFLAGS) --mode=compile $(CC) $(DEFS) $(DEFAULT_INCLUDES) $(INCLUDES) $(libsnprintfvc_la_CPPFLAGS) $(CPPFLAGS) $(AM_CFLAGS) $(CFLAGS) -MT libsnprintfvc_la-stream.lo -MD -MP -MF $(DEPDIR)/libsnprintfvc_la-stream.Tpo -c -o libsnprintfvc_la-stream.lo `test -f 'stream.c' || echo '$(srcdir)/'`stream.c @am__fastdepCC_TRUE@ $(am__mv) $(DEPDIR)/libsnprintfvc_la-stream.Tpo $(DEPDIR)/libsnprintfvc_la-stream.Plo @AMDEP_TRUE@@am__fastdepCC_FALSE@ source='stream.c' object='libsnprintfvc_la-stream.lo' libtool=yes @AMDEPBACKSLASH@ @AMDEP_TRUE@@am__fastdepCC_FALSE@ DEPDIR=$(DEPDIR) $(CCDEPMODE) $(depcomp) @AMDEPBACKSLASH@ @am__fastdepCC_FALSE@ $(LIBTOOL) --tag=CC $(AM_LIBTOOLFLAGS) $(LIBTOOLFLAGS) --mode=compile $(CC) $(DEFS) $(DEFAULT_INCLUDES) $(INCLUDES) $(libsnprintfvc_la_CPPFLAGS) $(CPPFLAGS) $(AM_CFLAGS) $(CFLAGS) -c -o libsnprintfvc_la-stream.lo `test -f 'stream.c' || echo '$(srcdir)/'`stream.c libsnprintfvc_la-custom.lo: custom.c @am__fastdepCC_TRUE@ $(LIBTOOL) --tag=CC $(AM_LIBTOOLFLAGS) $(LIBTOOLFLAGS) --mode=compile $(CC) $(DEFS) $(DEFAULT_INCLUDES) $(INCLUDES) $(libsnprintfvc_la_CPPFLAGS) $(CPPFLAGS) $(AM_CFLAGS) $(CFLAGS) -MT libsnprintfvc_la-custom.lo -MD -MP -MF $(DEPDIR)/libsnprintfvc_la-custom.Tpo -c -o libsnprintfvc_la-custom.lo `test -f 'custom.c' || echo '$(srcdir)/'`custom.c @am__fastdepCC_TRUE@ $(am__mv) $(DEPDIR)/libsnprintfvc_la-custom.Tpo $(DEPDIR)/libsnprintfvc_la-custom.Plo @AMDEP_TRUE@@am__fastdepCC_FALSE@ source='custom.c' object='libsnprintfvc_la-custom.lo' libtool=yes @AMDEPBACKSLASH@ @AMDEP_TRUE@@am__fastdepCC_FALSE@ DEPDIR=$(DEPDIR) $(CCDEPMODE) $(depcomp) @AMDEPBACKSLASH@ @am__fastdepCC_FALSE@ $(LIBTOOL) --tag=CC $(AM_LIBTOOLFLAGS) $(LIBTOOLFLAGS) --mode=compile $(CC) $(DEFS) $(DEFAULT_INCLUDES) $(INCLUDES) $(libsnprintfvc_la_CPPFLAGS) $(CPPFLAGS) $(AM_CFLAGS) $(CFLAGS) -c -o libsnprintfvc_la-custom.lo `test -f 'custom.c' || echo '$(srcdir)/'`custom.c mostlyclean-libtool: -rm -f *.lo clean-libtool: -rm -rf .libs _libs install-includeHEADERS: $(include_HEADERS) @$(NORMAL_INSTALL) @list='$(include_HEADERS)'; test -n "$(includedir)" || list=; \ if test -n "$$list"; then \ echo " $(MKDIR_P) '$(DESTDIR)$(includedir)'"; \ $(MKDIR_P) "$(DESTDIR)$(includedir)" || exit 1; \ fi; \ for p in $$list; do \ if test -f "$$p"; then d=; else d="$(srcdir)/"; fi; \ echo "$$d$$p"; \ done | $(am__base_list) | \ while read files; do \ echo " $(INSTALL_HEADER) $$files '$(DESTDIR)$(includedir)'"; \ $(INSTALL_HEADER) $$files "$(DESTDIR)$(includedir)" || exit $$?; \ done uninstall-includeHEADERS: @$(NORMAL_UNINSTALL) @list='$(include_HEADERS)'; test -n "$(includedir)" || list=; \ files=`for p in $$list; do echo $$p; done | sed -e 's|^.*/||'`; \ dir='$(DESTDIR)$(includedir)'; $(am__uninstall_files_from_dir) install-nodist_pkgincludeHEADERS: $(nodist_pkginclude_HEADERS) @$(NORMAL_INSTALL) @list='$(nodist_pkginclude_HEADERS)'; test -n "$(pkgincludedir)" || list=; \ if test -n "$$list"; then \ echo " $(MKDIR_P) '$(DESTDIR)$(pkgincludedir)'"; \ $(MKDIR_P) "$(DESTDIR)$(pkgincludedir)" || exit 1; \ fi; \ for p in $$list; do \ if test -f "$$p"; then d=; else d="$(srcdir)/"; fi; \ echo "$$d$$p"; \ done | $(am__base_list) | \ while read files; do \ echo " $(INSTALL_HEADER) $$files '$(DESTDIR)$(pkgincludedir)'"; \ $(INSTALL_HEADER) $$files "$(DESTDIR)$(pkgincludedir)" || exit $$?; \ done uninstall-nodist_pkgincludeHEADERS: @$(NORMAL_UNINSTALL) @list='$(nodist_pkginclude_HEADERS)'; test -n "$(pkgincludedir)" || list=; \ files=`for p in $$list; do echo $$p; done | sed -e 's|^.*/||'`; \ dir='$(DESTDIR)$(pkgincludedir)'; $(am__uninstall_files_from_dir) install-pkgincludeHEADERS: $(pkginclude_HEADERS) @$(NORMAL_INSTALL) @list='$(pkginclude_HEADERS)'; test -n "$(pkgincludedir)" || list=; \ if test -n "$$list"; then \ echo " $(MKDIR_P) '$(DESTDIR)$(pkgincludedir)'"; \ $(MKDIR_P) "$(DESTDIR)$(pkgincludedir)" || exit 1; \ fi; \ for p in $$list; do \ if test -f "$$p"; then d=; else d="$(srcdir)/"; fi; \ echo "$$d$$p"; \ done | $(am__base_list) | \ while read files; do \ echo " $(INSTALL_HEADER) $$files '$(DESTDIR)$(pkgincludedir)'"; \ $(INSTALL_HEADER) $$files "$(DESTDIR)$(pkgincludedir)" || exit $$?; \ done uninstall-pkgincludeHEADERS: @$(NORMAL_UNINSTALL) @list='$(pkginclude_HEADERS)'; test -n "$(pkgincludedir)" || list=; \ files=`for p in $$list; do echo $$p; done | sed -e 's|^.*/||'`; \ dir='$(DESTDIR)$(pkgincludedir)'; $(am__uninstall_files_from_dir) ID: $(HEADERS) $(SOURCES) $(LISP) $(TAGS_FILES) list='$(SOURCES) $(HEADERS) $(LISP) $(TAGS_FILES)'; \ unique=`for i in $$list; do \ if test -f "$$i"; then echo $$i; else echo $(srcdir)/$$i; fi; \ done | \ $(AWK) '{ files[$$0] = 1; nonempty = 1; } \ END { if (nonempty) { for (i in files) print i; }; }'`; \ mkid -fID $$unique tags: TAGS TAGS: $(HEADERS) $(SOURCES) $(TAGS_DEPENDENCIES) \ $(TAGS_FILES) $(LISP) set x; \ here=`pwd`; \ list='$(SOURCES) $(HEADERS) $(LISP) $(TAGS_FILES)'; \ unique=`for i in $$list; do \ if test -f "$$i"; then echo $$i; else echo $(srcdir)/$$i; fi; \ done | \ $(AWK) '{ files[$$0] = 1; nonempty = 1; } \ END { if (nonempty) { for (i in files) print i; }; }'`; \ shift; \ if test -z "$(ETAGS_ARGS)$$*$$unique"; then :; else \ test -n "$$unique" || unique=$$empty_fix; \ if test $$# -gt 0; then \ $(ETAGS) $(ETAGSFLAGS) $(AM_ETAGSFLAGS) $(ETAGS_ARGS) \ "$$@" $$unique; \ else \ $(ETAGS) $(ETAGSFLAGS) $(AM_ETAGSFLAGS) $(ETAGS_ARGS) \ $$unique; \ fi; \ fi ctags: CTAGS CTAGS: $(HEADERS) $(SOURCES) $(TAGS_DEPENDENCIES) \ $(TAGS_FILES) $(LISP) list='$(SOURCES) $(HEADERS) $(LISP) $(TAGS_FILES)'; \ unique=`for i in $$list; do \ if test -f "$$i"; then echo $$i; else echo $(srcdir)/$$i; fi; \ done | \ $(AWK) '{ files[$$0] = 1; nonempty = 1; } \ END { if (nonempty) { for (i in files) print i; }; }'`; \ test -z "$(CTAGS_ARGS)$$unique" \ || $(CTAGS) $(CTAGSFLAGS) $(AM_CTAGSFLAGS) $(CTAGS_ARGS) \ $$unique GTAGS: here=`$(am__cd) $(top_builddir) && pwd` \ && $(am__cd) $(top_srcdir) \ && gtags -i $(GTAGS_ARGS) "$$here" distclean-tags: -rm -f TAGS ID GTAGS GRTAGS GSYMS GPATH tags distdir: $(DISTFILES) @srcdirstrip=`echo "$(srcdir)" | sed 's/[].[^$$\\*]/\\\\&/g'`; \ topsrcdirstrip=`echo "$(top_srcdir)" | sed 's/[].[^$$\\*]/\\\\&/g'`; \ list='$(DISTFILES)'; \ dist_files=`for file in $$list; do echo $$file; done | \ sed -e "s|^$$srcdirstrip/||;t" \ -e "s|^$$topsrcdirstrip/|$(top_builddir)/|;t"`; \ case $$dist_files in \ */*) $(MKDIR_P) `echo "$$dist_files" | \ sed '/\//!d;s|^|$(distdir)/|;s,/[^/]*$$,,' | \ sort -u` ;; \ esac; \ for file in $$dist_files; do \ if test -f $$file || test -d $$file; then d=.; else d=$(srcdir); fi; \ if test -d $$d/$$file; then \ dir=`echo "/$$file" | sed -e 's,/[^/]*$$,,'`; \ if test -d "$(distdir)/$$file"; then \ find "$(distdir)/$$file" -type d ! -perm -700 -exec chmod u+rwx {} \;; \ fi; \ if test -d $(srcdir)/$$file && test $$d != $(srcdir); then \ cp -fpR $(srcdir)/$$file "$(distdir)$$dir" || exit 1; \ find "$(distdir)/$$file" -type d ! -perm -700 -exec chmod u+rwx {} \;; \ fi; \ cp -fpR $$d/$$file "$(distdir)$$dir" || exit 1; \ else \ test -f "$(distdir)/$$file" \ || cp -p $$d/$$file "$(distdir)/$$file" \ || exit 1; \ fi; \ done check-am: all-am check: $(BUILT_SOURCES) $(MAKE) $(AM_MAKEFLAGS) check-am all-am: Makefile $(LTLIBRARIES) $(DATA) $(HEADERS) installdirs: for dir in "$(DESTDIR)$(libdir)" "$(DESTDIR)$(includedir)" "$(DESTDIR)$(pkgincludedir)" "$(DESTDIR)$(pkgincludedir)"; do \ test -z "$$dir" || $(MKDIR_P) "$$dir"; \ done install: $(BUILT_SOURCES) $(MAKE) $(AM_MAKEFLAGS) install-am install-exec: install-exec-am install-data: install-data-am uninstall: uninstall-am install-am: all-am @$(MAKE) $(AM_MAKEFLAGS) install-exec-am install-data-am installcheck: installcheck-am install-strip: if test -z '$(STRIP)'; then \ $(MAKE) $(AM_MAKEFLAGS) INSTALL_PROGRAM="$(INSTALL_STRIP_PROGRAM)" \ install_sh_PROGRAM="$(INSTALL_STRIP_PROGRAM)" INSTALL_STRIP_FLAG=-s \ install; \ else \ $(MAKE) $(AM_MAKEFLAGS) INSTALL_PROGRAM="$(INSTALL_STRIP_PROGRAM)" \ install_sh_PROGRAM="$(INSTALL_STRIP_PROGRAM)" INSTALL_STRIP_FLAG=-s \ "INSTALL_PROGRAM_ENV=STRIPPROG='$(STRIP)'" install; \ fi mostlyclean-generic: clean-generic: -test -z "$(CLEANFILES)" || rm -f $(CLEANFILES) distclean-generic: -test -z "$(CONFIG_CLEAN_FILES)" || rm -f $(CONFIG_CLEAN_FILES) -test . = "$(srcdir)" || test -z "$(CONFIG_CLEAN_VPATH_FILES)" || rm -f $(CONFIG_CLEAN_VPATH_FILES) -test -z "$(DISTCLEANFILES)" || rm -f $(DISTCLEANFILES) maintainer-clean-generic: @echo "This command is intended for maintainers to use" @echo "it deletes files that may require special tools to rebuild." -test -z "$(BUILT_SOURCES)" || rm -f $(BUILT_SOURCES) clean: clean-am clean-am: clean-generic clean-libLTLIBRARIES clean-libtool \ clean-noinstLTLIBRARIES mostlyclean-am distclean: distclean-am -rm -rf ./$(DEPDIR) -rm -f Makefile distclean-am: clean-am distclean-compile distclean-generic \ distclean-tags dvi: dvi-am dvi-am: html: html-am html-am: info: info-am info-am: install-data-am: install-includeHEADERS \ install-nodist_pkgincludeHEADERS install-pkgincludeHEADERS install-dvi: install-dvi-am install-dvi-am: install-exec-am: install-libLTLIBRARIES install-html: install-html-am install-html-am: install-info: install-info-am install-info-am: install-man: install-pdf: install-pdf-am install-pdf-am: install-ps: install-ps-am install-ps-am: installcheck-am: maintainer-clean: maintainer-clean-am -rm -rf ./$(DEPDIR) -rm -f Makefile maintainer-clean-am: distclean-am maintainer-clean-generic mostlyclean: mostlyclean-am mostlyclean-am: mostlyclean-compile mostlyclean-generic \ mostlyclean-libtool pdf: pdf-am pdf-am: ps: ps-am ps-am: uninstall-am: uninstall-includeHEADERS uninstall-libLTLIBRARIES \ uninstall-nodist_pkgincludeHEADERS uninstall-pkgincludeHEADERS .MAKE: all check install install-am install-strip .PHONY: CTAGS GTAGS all all-am check check-am clean clean-generic \ clean-libLTLIBRARIES clean-libtool clean-noinstLTLIBRARIES \ ctags distclean distclean-compile distclean-generic \ distclean-libtool distclean-tags distdir dvi dvi-am html \ html-am info info-am install install-am install-data \ install-data-am install-dvi install-dvi-am install-exec \ install-exec-am install-html install-html-am \ install-includeHEADERS install-info install-info-am \ install-libLTLIBRARIES install-man \ install-nodist_pkgincludeHEADERS install-pdf install-pdf-am \ install-pkgincludeHEADERS install-ps install-ps-am \ install-strip installcheck installcheck-am installdirs \ maintainer-clean maintainer-clean-generic mostlyclean \ mostlyclean-compile mostlyclean-generic mostlyclean-libtool \ pdf pdf-am ps ps-am tags uninstall uninstall-am \ uninstall-includeHEADERS uninstall-libLTLIBRARIES \ uninstall-nodist_pkgincludeHEADERS uninstall-pkgincludeHEADERS gen: $(BUILT_SOURCES) # Create these in the source directory because that is where # they are when the distribution tarball is unpacked. $(srcdir)/%.h: %.stamp @: %.stamp: %.in @file=`echo $@ | $(SED) 's,\.stamp$$,.h,'`; \ $(GENPROTO_ENVIRONMENT) $(GENPROTO) $(GENPROTO_FLAGS) $^ > \ $${file}T; \ if cmp -s $(srcdir)/$$file $${file}T; then \ echo $$file is unchanged; rm -f $${file}T; \ else \ echo creating $(srcdir)/$$file; mv -f $${file}T $(srcdir)/$$file; \ fi @echo timestamp > $@ printf.h: printf.stamp filament.h: filament.stamp stream.h: stream.stamp printf.stamp: printf.in printf.c format.c custom.c filament.stamp: filament.in filament.c stream.stamp: stream.in stream.c # # compat.h is generated differently, so we can't use the pattern rule # above: # compat.h: compat.stamp compat.stamp: $(srcdir)/compat.in $(top_builddir)/config.status cd $(top_builddir) \ && $(SHELL) ./config.status snprintfv/compat.h echo timestamp > $@ # Makefile.am ends here # Tell versions [3.59,3.63) of GNU make to not export all variables. # Otherwise a system limit (for SysV at least) may be exceeded. .NOEXPORT: smalltalk-3.2.5/snprintfv/snprintfv/stream.c0000644000175000017500000001313112123404352016142 00000000000000/* -*- Mode: C -*- */ /* stream.c --- customizable stream routines * Copyright (C) 1998, 1999, 2000, 2002, 2003 Gary V. Vaughan * Originally by Gary V. Vaughan, 1998 * This file is part of Snprintfv * * Snprintfv is free software; you can redistribute it and/or * modify it under the terms of the GNU General Public License as * published by the Free Software Foundation; either version 2 of the * License, or (at your option) any later version. * * Snprintfv program is distributed in the hope that it will be useful, * but WITHOUT ANY WARRANTY; without even the implied warranty of * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU * General Public License for more details. * * You should have received a copy of the GNU General Public License * along with this program. If not, write to the Free Software * Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * * As a special exception to the GNU General Public License, if you * distribute this file as part of a program that also links with and * uses the libopts library from AutoGen, you may include it under * the same distribution terms used by the libopts library. */ /* Code: */ #ifdef HAVE_CONFIG_H # include #endif #ifdef WITH_DMALLOC # include #endif #include "compat.h" #include "stream.h" #include "mem.h" struct stream { snv_pointer stream; unsigned long limit; StreamGet get_func; StreamPut put_func; }; static int stream_not_readable (STREAM *stream) { return -1; } static int stream_not_writable (int ch, STREAM *stream) { return -1; } /** * stream_new: constructor * @dets: user supplied stream details to be passed into the various funcs. * @limit: the maximum number of consecutive bytes to fit in @dets. * @get_func: function to get a character from @dets stream. * @put_func: function to put a character in @dets stream. * * Allocate and initialize a new %STREAM data type. The @get_func * and @put_func can be NULL if you intend to create a non-readable * or non-writable stream, respectively. * * Return value: * The address of the newly allocated and initialised stream is returned. **/ STREAM * stream_new (snv_pointer dets, unsigned long limit, StreamGet get_func, StreamPut put_func) { STREAM *new = snv_new (STREAM, 1); new->stream = dets; new->limit = limit; new->get_func = get_func ? get_func : stream_not_readable; new->put_func = put_func ? put_func : stream_not_writable; return new; } /** * stream_delete: destructor * @stream: The stream pending deletion * * The memory associated with @stream is recycled. * Return value: * The %dets supplied by the user when the stream was created are * returned for handling by the calling function. **/ snv_pointer stream_delete (STREAM *stream) { snv_pointer dets = stream->stream; snv_delete (stream); return dets; } /** * stream_details: * @stream: the stream being queried. * * The finalization function specified when @stream was created (if any) * is called, and then the memory associated with @stream is recycled. * It is the responsibility of the finalization function to recycle, or * otherwise manage, any memory associated with the user supplied %dets. * Return value: * This function returns the stream details associated with @stream * when it was originally created. **/ snv_pointer stream_details (STREAM *stream) { return stream ? stream->stream : NULL; } /** * stream_put: * @ch: A single character to be placed in @stream. * @stream: The stream to be written to. * * This function will @ch in @stream if that stream's output limit will * not be exceeded. * * Return value: * If @stream is full, return 1. Otherwise, if any other error occurs, * that error code is returned unchanged. This is of course dependant * on what the handler function uses to indicate an error. If the stream * is not full and the stream's writing function succeeds, 1 (the number of * characters emitted!) is returned. **/ int stream_put (int ch, STREAM *stream) { int ch_or_errorcode; if (!stream) return -1; if (stream->limit < 1) return 1; stream->limit -= 1; ch_or_errorcode = (*stream->put_func) ((unsigned char) ch, stream); return (ch_or_errorcode < 0) ? ch_or_errorcode : 1; } /** * stream_puts: * @s: A string to be placed in @stream. * @stream: The stream to be written to. * * This function will @ch in @stream if that stream's output limit will * not be exceeded. * * Return value: * If any other error occurs, that error code is returned unchanged. * This is of course dependant on what the handler function uses to * indicate an error. If the stream becomes full, the remaining * characters are not printed. If the stream's writing function * always succeeds, the number of characters emitted or skipped is * returned. **/ int stream_puts (char *s, STREAM *stream) { int ch_or_errorcode; int num; if (!stream) return -1; for (num = 0; *s; num++, s++) { if (stream->limit < 1) return num + strlen (s); stream->limit -= 1; ch_or_errorcode = (*stream->put_func) ((unsigned char) *s, stream); if (ch_or_errorcode < 0) return ch_or_errorcode; } return num; } /** * stream_get: * @stream: The stream to be read from. * * This function will try to read a single character from @stream. * * Return value: * If an error occurs or the end of @stream is reached, -1 is returned. * Under normal circumstances the value if the character read (cast to * an int) is returned. **/ int stream_get (STREAM *stream) { return (*stream->get_func) (stream); } /* stream.c ends here */ smalltalk-3.2.5/snprintfv/snprintfv/filament.stamp0000644000175000017500000000001212123404352017342 00000000000000timestamp smalltalk-3.2.5/snprintfv/snprintfv/printf.stamp0000644000175000017500000000001212123404352017045 00000000000000timestamp smalltalk-3.2.5/snprintfv/snprintfv/filament.h0000644000175000017500000001707612123404352016467 00000000000000#line 1 "../../../snprintfv/snprintfv/filament.in" /* -*- Mode: C -*- */ /* filament.h --- a bit like a string but different =)O| * Copyright (C) 1998, 1999, 2000, 2002 Gary V. Vaughan * Originally by Gary V. Vaughan, 1998 * This file is part of Snprintfv * * Snprintfv is free software; you can redistribute it and/or * modify it under the terms of the GNU General Public License as * published by the Free Software Foundation; either version 2 of the * License, or (at your option) any later version. * * Snprintfv program is distributed in the hope that it will be useful, * but WITHOUT ANY WARRANTY; without even the implied warranty of * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU * General Public License for more details. * * You should have received a copy of the GNU General Public License * along with this program. If not, write to the Free Software * Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * * As a special exception to the GNU General Public License, if you * distribute this file as part of a program that also links with and * uses the libopts library from AutoGen, you may include it under * the same distribution terms used by the libopts library. */ /* Code: */ #ifndef FILAMENT_H #define FILAMENT_H 1 #include #ifdef __cplusplus extern "C" { #if 0 /* This brace is so that emacs can still indent properly: */ } #endif #endif /* __cplusplus */ #define FILAMENT_BUFSIZ 512 /** * Filament: * Opaque data type used to hold 8-bit clean dynamic strings which know * their own length and resize themselves to avoid buffer overruns. **/ typedef struct filament Filament; struct filament { char *value; /* pointer to the start of the string */ size_t length; /* length of the string */ size_t size; /* total memory allocated */ char buffer[FILAMENT_BUFSIZ]; /* usually string == &buffer[0] */ }; /** * filnew: constructor * @init: address of the first byte to copy into the new object. * @len: the number of bytes to copy into the new object. * * Create a new Filament object, initialised to hold a copy of the * first @len bytes starting at address @init. If @init is NULL, or * @len is 0 (or less), then the initialised Filament will return the * empty string, "", if its value is queried. * * Return value: * A newly created Filament object is returned. **/ extern Filament * filnew (const char *const init, size_t len); /** * filinit: * @fil: The Filament object to initialise. * @init: address of the first byte to copy into the new object. * @len: the number of bytes to copy into the new object. * * Initialise a Filament object to hold a copy of the first @len bytes * starting at address @init. If @init is NULL, or @len is 0 (or less), * then the Filament will be reset to hold the empty string, "". * * Return value: * The initialised Filament object is returned. **/ extern Filament * filinit (Filament *fil, const char *const init, size_t len); /** * fildelete: destructor * @fil: The Filament object for recycling. * * The memory being used by @fil is recycled. * * Return value: * The original contents of @fil are converted to a null terminated * string which is returned, either to be freed itself or else used * as a normal C string. The entire Filament contents are copied into * this string including any embedded nulls. **/ extern char * fildelete (Filament *fil); /** * _fil_extend: * @fil: The Filament object which may need more string space. * @len: The length of the data to be stored in @fil. * @copy: whether to copy data from the static buffer on reallocation. * * This function will will assign a bigger block of memory to @fil * considering the space left in @fil and @len, the length required * for the prospective contents. */ extern void _fil_extend (Filament *fil, size_t len, boolean copy); #line 61 "../../../snprintfv/snprintfv/filament.in" /* Save the overhead of a function call in the great majority of cases. */ #define fil_maybe_extend(fil, len, copy) \ (((len)>=(fil)->size) ? _fil_extend((fil), (len), (copy)) : (void)0) /** * filval: * @fil: The Filament object being queried. * * Return value: * A pointer to the null terminated string held by the Filament * object is returned. Since the @fil may contain embedded nulls, it * is not entirely safe to use the strfoo() API to examine the contents * of the return value. **/ SNV_INLINE char * filval (Filament *fil) { /* Because we have been careful to ensure there is always at least one spare byte of allocated memory, it is safe to set it here. */ fil->value[fil->length] = '\0'; return (char *) (fil->value); } /** * fillen: * @fil: The Filament object being queried. * * Return value: * The length of @fil, including any embedded nulls, but excluding the * terminating null, is returned. **/ SNV_INLINE size_t fillen (Filament *fil) { return fil->length; } /** * filelt: * @fil: The Filament being queried. * @n: A zero based index into @fil. * * This function looks for the @n'th element of @fil. * * Return value: * If @n is an index inside the Filament @fil, then the character stored * at that index cast to an int is returned, otherwise @n is outside * this range and -1 is returned. **/ SNV_INLINE int filelt (Filament *fil, ssize_t n) { if ((n >= 0) && (n < fil->length)) return (int) fil->value[n]; else return -1; } /** * filncat: * @fil: The destination Filament of the concatenation. * @str: The address of the source bytes for concatenation. * @n: The number of bytes to be copied from @str. * * @n bytes starting with the byte at address @str are destructively * concatenated to @fil. If necessary, @fil is dynamically reallocated * to make room for this operation. * * Return value: * A pointer to the (not null terminated) string which is the result * of this concatenation is returned. **/ SNV_INLINE char * filncat (Filament *fil, const char *str, size_t n) { fil_maybe_extend (fil, n + fil->length, TRUE); memcpy (fil->value + fil->length, str, n); fil->length += n; return fil->value; } /** * filcat: * @fil: The destination Filament of the concatenation. * @str: The address of the source bytes for concatenation. * * The bytes starting at address @str upto and including the first null * byte encountered are destructively concatenated to @fil. If * necessary @fil is dynamically reallocated to make room for this * operation. * * Return value: * A pointer to the (not null terminated) string which is the result * of this concatenation is returned. **/ SNV_INLINE char * filcat (Filament *fil, const char *str) { size_t length = strlen (str); return filncat (fil, str, length); } /** * filccat: * @fil: The destination Filament of the concatenation. * @c: The character to append to @fil. * * @c is destructively concatenated to @fil. If necessary, @fil is * dynamically reallocated to make room for this operation. When used * repeatedly this function is less efficient than %filncat, * since it must check whether to extend the filament before each * character is appended. * * Return value: * A pointer to the (not null terminated) string which is the result * of this concatenation is returned. **/ SNV_INLINE char * filccat (Filament *fil, int c) { fil_maybe_extend (fil, 1 + fil->length, TRUE); fil->value[fil->length++] = c; return fil->value; } #ifdef __cplusplus #if 0 /* This brace is so that emacs can still indent properly: */ { #endif } #endif /* __cplusplus */ #endif /* FILAMENT_H */ /* filament.h ends here */ smalltalk-3.2.5/snprintfv/snprintfv/stream.h0000644000175000017500000001363412123404352016157 00000000000000#line 1 "../../../snprintfv/snprintfv/stream.in" /* -*- Mode: C -*- */ /* stream.h --- customizable stream routines * Copyright (C) 1998, 1999, 2000, 2002 Gary V. Vaughan * Originally by Gary V. Vaughan, 1998 * This file is part of Snprintfv * * Snprintfv is free software; you can redistribute it and/or * modify it under the terms of the GNU General Public License as * published by the Free Software Foundation; either version 2 of the * License, or (at your option) any later version. * * Snprintfv program is distributed in the hope that it will be useful, * but WITHOUT ANY WARRANTY; without even the implied warranty of * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU * General Public License for more details. * * You should have received a copy of the GNU General Public License * along with this program. If not, write to the Free Software * Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * * As a special exception to the GNU General Public License, if you * distribute this file as part of a program that also links with and * uses the libopts library from AutoGen, you may include it under * the same distribution terms used by the libopts library. */ /* Code: */ #ifndef STREAM_H #define STREAM_H 1 #define STREAM_READABLE (1 << 0) #define STREAM_WRITABLE (1 << 1) /** * SNV_UNLIMITED: * Used to denote that there is no upper limit to the number of characters * that can safely be written to a stream. **/ #define SNV_UNLIMITED ~(0L) #ifdef __cplusplus extern "C" { #if 0 /* This brace is so that emacs can still indent properly: */ } #endif #endif /* __cplusplus */ /** * STREAM: * Data type used to pass details of streams between functions, * much like stdio's %FILE, but more flexible. A %STREAM can be uni- or * bi-directional depending on how it is initialised. **/ typedef struct stream STREAM; /** * StreamPut: * @ch: The character to write to @stream cast to an int. * @stream: The stream being written to. * * Type of the function to put a character in a writeable stream. * * Return value: * The function should return the character written to the * stream, cast to an int if it was written successfully, or * else %EOF, if the write failed. **/ typedef int (*StreamPut) (int ch, STREAM * stream); /** * StreamGet: * @stream: The stream being read from. * * Type of the function to get a character from a readable stream. * * Return value: * The function should return the character read from the * stream, cast to an int if it was read successfully, or * else %EOF, if the read failed. **/ typedef int (*StreamGet) (STREAM * stream); /** * stream_new: constructor * @dets: user supplied stream details to be passed into the various funcs. * @limit: the maximum number of consecutive bytes to fit in @dets. * @get_func: function to get a character from @dets stream. * @put_func: function to put a character in @dets stream. * * Allocate and initialize a new %STREAM data type. The @get_func * and @put_func can be NULL if you intend to create a non-readable * or non-writable stream, respectively. * * Return value: * The address of the newly allocated and initialised stream is returned. **/ extern STREAM * stream_new (snv_pointer dets, unsigned long limit, StreamGet get_func, StreamPut put_func); /** * stream_delete: destructor * @stream: The stream pending deletion * * The memory associated with @stream is recycled. * Return value: * The %dets supplied by the user when the stream was created are * returned for handling by the calling function. **/ extern snv_pointer stream_delete (STREAM *stream); /** * stream_details: * @stream: the stream being queried. * * The finalization function specified when @stream was created (if any) * is called, and then the memory associated with @stream is recycled. * It is the responsibility of the finalization function to recycle, or * otherwise manage, any memory associated with the user supplied %dets. * Return value: * This function returns the stream details associated with @stream * when it was originally created. **/ extern snv_pointer stream_details (STREAM *stream); /** * stream_put: * @ch: A single character to be placed in @stream. * @stream: The stream to be written to. * * This function will @ch in @stream if that stream's output limit will * not be exceeded. * * Return value: * If @stream is full, return 1. Otherwise, if any other error occurs, * that error code is returned unchanged. This is of course dependant * on what the handler function uses to indicate an error. If the stream * is not full and the stream's writing function succeeds, 1 (the number of * characters emitted!) is returned. **/ extern int stream_put (int ch, STREAM *stream); /** * stream_puts: * @s: A string to be placed in @stream. * @stream: The stream to be written to. * * This function will @ch in @stream if that stream's output limit will * not be exceeded. * * Return value: * If any other error occurs, that error code is returned unchanged. * This is of course dependant on what the handler function uses to * indicate an error. If the stream becomes full, the remaining * characters are not printed. If the stream's writing function * always succeeds, the number of characters emitted or skipped is * returned. **/ extern int stream_puts (char *s, STREAM *stream); /** * stream_get: * @stream: The stream to be read from. * * This function will try to read a single character from @stream. * * Return value: * If an error occurs or the end of @stream is reached, -1 is returned. * Under normal circumstances the value if the character read (cast to * an int) is returned. **/ extern int stream_get (STREAM *stream); #line 88 "../../../snprintfv/snprintfv/stream.in" #ifdef __cplusplus #if 0 /* This brace is so that emacs can still indent properly: */ { #endif } #endif /* __cplusplus */ #endif /* STREAM_H */ smalltalk-3.2.5/snprintfv/snprintfv/compat.in0000644000175000017500000001206612123404352016324 00000000000000## -*- Mode: C -*- ## -------------------------------------------------------------------- ## compat.h.in --- verbose but portable cpp defines for snprintfv ## Copyright (C) 1999 Gary V. Vaughan ## Originally by Gary V. Vaughan, 1999 ## This file is part of Snprintfv ## ## Snprintfv is free software; you can redistribute it and/or ## modify it under the terms of the GNU General Public License as ## published by the Free Software Foundation; either version 2 of the ## License, or (at your option) any later version. ## ## Snprintfv program is distributed in the hope that it will be useful, ## but WITHOUT ANY WARRANTY; without even the implied warranty of ## MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU ## General Public License for more details. ## ## You should have received a copy of the GNU General Public License ## along with this program. If not, write to the Free Software ## Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. ## ## As a special exception to the GNU General Public License, if you ## distribute this file as part of a program that also links with and ## uses the libopts library from AutoGen, you may include it under ## the same distribution terms used by the libopts library. ## Code: /* inline and const keywords are (mostly) handled by config.h */ #ifdef __GNUC__ # ifndef const # define const __const # endif # ifndef signed # define signed __signed # endif # ifndef volatile # define volatile __volatile # endif #else # ifndef __STDC__ # undef signed # define signed # undef volatile # define volatile # endif #endif #ifdef __STDC__ # ifndef _STR # define _STR(x) #x # endif # ifndef _CONC # define _CONC(x, y) x##y # endif typedef void *snv_pointer; typedef const void *snv_constpointer; #else # ifndef _STR # define _STR(x) "x" # endif # ifndef _CONC # define _CONC(x, y) x/**/y # endif typedef char *snv_pointer; typedef char *snv_constpointer; #endif /* If FALSE is defined, we presume TRUE is defined too. In this case, merely typedef boolean as being int. Or else, define these all. */ #ifndef FALSE /* Do not use `enum boolean': this tag is used in SVR4 . */ typedef enum { FALSE = 0, TRUE = 1 } compatboolean; #else typedef int compatboolean; #endif #ifndef boolean # define boolean compatboolean #endif #if defined __CYGWIN32__ # ifndef __CYGWIN__ # define __CYGWIN__ # endif #endif #if defined __CYGWIN__ || defined __MSVCRT__ || defined WIN32 || defined __WIN32__ # ifndef _WIN32 # define _WIN32 # endif #endif #ifndef EXIT_SUCCESS # define EXIT_SUCCESS 0 # define EXIT_FAILURE 1 #endif #undef SNV_STMT_START #undef SNV_STMT_END #if defined (__GNUC__) && !defined (__STRICT_ANSI__) && !defined (__cplusplus) # define SNV_STMT_START (void)( # define SNV_STMT_END ) #else # if (defined (sun) || defined (__sun__)) # define SNV_STMT_START if (1) # define SNV_STMT_END else (void)0 # else # define SNV_STMT_START do # define SNV_STMT_END while (0) # endif #endif #ifdef _WIN32 # ifdef DLL_EXPORT # define SNV_SCOPE extern __declspec(dllexport) # else # ifdef LIBSNPRINTFV_DLL_IMPORT # define SNV_SCOPE extern __declspec(dllimport) # endif # endif #endif #ifndef SNV_SCOPE # define SNV_SCOPE extern #endif #undef SNV_GNUC_PRINTF #undef SNV_GNUC_NORETURN #if __GNUC__ > 2 || (__GNUC__ == 2 && __GNUC_MINOR__ > 4) # define SNV_GNUC_PRINTF( args, format_idx, arg_idx ) \ args __attribute__((format (printf, format_idx, arg_idx))) # define SNV_GNUC_NORETURN \ __attribute__((noreturn)) # define SNV_ASSERT_FMT " (", __PRETTY_FUNCTION__, ")" #else /* !__GNUC__ */ # define SNV_GNUC_PRINTF( args, format_idx, arg_idx ) args # define SNV_GNUC_NORETURN # define SNV_ASSERT_FMT "", "", "" #endif /* !__GNUC__ */ #ifndef STR # define STR(s) _STR(s) #endif #define snv_assert(expr) snv_fassert(stderr, expr) #define snv_fassert(stream, expr) SNV_STMT_START{ \ if (!(expr)) \ { \ fprintf (stream, "file %s: line %d%s%s%s: assertion \"%s\" failed.\n", \ __FILE__, __LINE__, SNV_ASSERT_FMT, _STR(expr)); \ exit(EXIT_FAILURE); \ }; }SNV_STMT_END #define return_if_fail(expr) freturn_if_fail(stderr, expr) #define freturn_if_fail(expr) SNV_STMT_START{ \ if (!(expr)) \ { \ fprintf (stream, "file %s: line %d%s%s%s: assertion \"%s\" failed.\n", \ __FILE__, __LINE__, SNV_ASSERT_FMT, _STR(expr)); \ return; \ }; }SNV_STMT_END #define return_val_if_fail(expr, val) freturn_val_if_fail(stderr, expr, val) #define freturn_val_if_fail(stream, expr, val) SNV_STMT_START{ \ if (!(expr)) \ { \ fprintf (stream, "file %s: line %d%s%s%s: assertion \"%s\" failed.\n", \ __FILE__, __LINE__, SNV_ASSERT_FMT, _STR(expr)); \ return val; \ }; }SNV_STMT_END #ifndef MAX #define MAX(a,b) ((a) > (b) ? (a) : (b)) #endif #ifndef MIN #define MIN(a,b) ((a) < (b) ? (a) : (b)) #endif #ifndef ABS #define ABS(a) ((a) < 0 ? -(a) : (a)) #endif ## compat.h.in ends here smalltalk-3.2.5/snprintfv/snprintfv/stream.stamp0000644000175000017500000000001212123404352017036 00000000000000timestamp smalltalk-3.2.5/snprintfv/snprintfv/custom.c0000644000175000017500000001141112123404352016160 00000000000000/* -*- Mode: C -*- */ /* custom.c --- printf clone for argv arrays * Copyright (C) 2003 Gary V. Vaughan * Originally by Paolo Bonzini, 2002 * This file is part of Snprintfv * * Snprintfv is free software; you can redistribute it and/or * modify it under the terms of the GNU General Public License as * published by the Free Software Foundation; either version 2 of the * License, or (at your option) any later version. * * Snprintfv program is distributed in the hope that it will be useful, * but WITHOUT ANY WARRANTY; without even the implied warranty of * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU * General Public License for more details. * * You should have received a copy of the GNU General Public License * along with this program. If not, write to the Free Software * Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * * As a special exception to the GNU General Public License, if you * distribute this file as part of a program that also links with and * uses the libopts library from AutoGen, you may include it under * the same distribution terms used by the libopts library. */ /* Code: */ #ifdef HAVE_CONFIG_H # include #endif #ifdef WITH_DMALLOC # include #endif #include #ifdef HAVE_WCHAR_H # include #endif #include "printf.h" /** * printf_generic_info: * @pinfo: the current state information for the format * string parser. * @n: the number of available slots in the @argtypes array * @argtypes: the pointer to the first slot to be filled by the * function * * An example implementation of a %printf_arginfo_function, which * takes the basic type from the type given in the %spec_entry * and adds flags depending on what was parsed (e.g. %PA_FLAG_SHORT * is %pparser->is_short and so on). * * Return value: * Always 1. */ int printf_generic_info (struct printf_info *const pinfo, size_t n, int *argtypes) { int type = pinfo->type; if (!n) return 1; if ((type & PA_TYPE_MASK) == PA_POINTER) type |= PA_FLAG_UNSIGNED; if (pinfo->is_char) type = PA_CHAR; if (pinfo->is_short) type |= PA_FLAG_SHORT; if (pinfo->is_long) type |= PA_FLAG_LONG; if (pinfo->is_long_double) type |= PA_FLAG_LONG_LONG; argtypes[0] = type; return 1; } /** * printf_generic: * @stream: the stream (possibly a struct printfv_stream appropriately * cast) on which to write output. * @pinfo: the current state information for the format string parser. * @args: the pointer to the first argument to be read by the handler * * An example implementation of a %printf_function, used to provide easy * access to justification, width and precision options. * * Return value: * The number of characters output. **/ int printf_generic (STREAM *stream, struct printf_info *const pinfo, union printf_arg const *args) { int len = 0, count_or_errorcode = SNV_OK; char *p = NULL; /* Used to interface to the custom function. */ STREAM *out; Filament *fil; printf_function *user_func = (printf_function *) pinfo->extra; return_val_if_fail (pinfo != NULL, SNV_ERROR); /* Read these now to advance the argument pointer appropriately */ if (pinfo->prec == -1) pinfo->prec = 0; /* Check for valid pre-state. */ if (pinfo->prec <= -1) { PRINTF_ERROR (pinfo, "invalid flags"); return -1; } /* Print to a stream using a user-supplied function. */ fil = filnew (NULL, 0); out = stream_new (fil, SNV_UNLIMITED, NULL, snv_filputc); user_func (out, pinfo, args); stream_delete (out); len = fillen (fil); p = fildelete (fil); /* Left pad to the width if the supplied argument is less than the width specifier. */ if (p != NULL && pinfo->prec && pinfo->prec < len) len = pinfo->prec; if ((len < pinfo->width) && !pinfo->left) { int padwidth = pinfo->width - len; while ((count_or_errorcode >= 0) && (count_or_errorcode < padwidth)) SNV_EMIT (pinfo->pad, stream, count_or_errorcode); } /* Fill the buffer with as many characters from the format argument * as possible without overflowing or exceeding the precision. */ if ((count_or_errorcode >= 0) && (p != NULL)) { int mark = count_or_errorcode; while ((count_or_errorcode >= 0) && *p != '\0' && ((pinfo->prec == 0) || (count_or_errorcode - mark < len))) SNV_EMIT (*p++, stream, count_or_errorcode); } /* Right pad to the width if we still didn't reach the specified * width and the left justify flag was set. */ if ((count_or_errorcode < pinfo->width) && pinfo->left) while ((count_or_errorcode >= 0) && (count_or_errorcode < pinfo->width)) SNV_EMIT (pinfo->pad, stream, count_or_errorcode); /* Return the number of characters emitted. */ return count_or_errorcode; } smalltalk-3.2.5/snprintfv/ltmain.sh0000644000175000017500000041724012123404352014303 00000000000000# ltmain.sh - Provide generalized library-building support services. # NOTE: Changing this file will not affect anything until you rerun configure. # # Copyright (C) 1996, 1997, 1998, 1999, 2000, 2001 # Free Software Foundation, Inc. # Originally by Gordon Matzigkeit , 1996 # # This program is free software; you can redistribute it and/or modify # it under the terms of the GNU General Public License as published by # the Free Software Foundation; either version 2 of the License, or # (at your option) any later version. # # This program is distributed in the hope that it will be useful, but # WITHOUT ANY WARRANTY; without even the implied warranty of # MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU # General Public License for more details. # # You should have received a copy of the GNU General Public License # along with this program; if not, write to the Free Software # Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. # # As a special exception to the GNU General Public License, if you # distribute this file as part of a program that contains a # configuration script generated by Autoconf, you may include it under # the same distribution terms that you use for the rest of that program. # Check that we have a working $echo. if test "X$1" = X--no-reexec; then # Discard the --no-reexec flag, and continue. shift elif test "X$1" = X--fallback-echo; then # Avoid inline document here, it may be left over : elif test "X`($echo '\t') 2>/dev/null`" = 'X\t'; then # Yippee, $echo works! : else # Restart under the correct shell, and then maybe $echo will work. exec $SHELL "$0" --no-reexec ${1+"$@"} fi if test "X$1" = X--fallback-echo; then # used as fallback echo shift cat <&2 echo "Fatal configuration error. See the $PACKAGE docs for more information." 1>&2 exit 1 fi # Global variables. mode=$default_mode nonopt= prev= prevopt= run= show="$echo" show_help= execute_dlfiles= lo2o="s/\\.lo\$/.${objext}/" o2lo="s/\\.${objext}\$/.lo/" # Parse our command line options once, thoroughly. while test $# -gt 0 do arg="$1" shift case $arg in -*=*) optarg=`$echo "X$arg" | $Xsed -e 's/[-_a-zA-Z0-9]*=//'` ;; *) optarg= ;; esac # If the previous option needs an argument, assign it. if test -n "$prev"; then case $prev in execute_dlfiles) execute_dlfiles="$execute_dlfiles $arg" ;; ### Changed by Paolo Bonzini (Apr 26 2001), this change ### is compatible with libtool 1.4's multi-language branch tag) test "x$arg" = xdisable-shared && build_libtool_libs=no build_old_libs=yes test "x$arg" = xdisable-static && build_old_libs=no build_libtool_libs=yes test "x$arg" = xenable-shared && build_libtool_libs=yes test "x$arg" = xenable-static && build_old_libs=yes ;; *) eval "$prev=\$arg" ;; esac prev= prevopt= continue fi # Have we seen a non-optional argument yet? case $arg in --help) show_help=yes ;; --version) echo "$PROGRAM (GNU $PACKAGE) $VERSION$TIMESTAMP" exit 0 ;; --config) sed -e '1,/^# ### BEGIN LIBTOOL CONFIG/d' -e '/^# ### END LIBTOOL CONFIG/,$d' $0 exit 0 ;; --debug) echo "$progname: enabling shell trace mode" set -x ;; --dry-run | -n) run=: ;; ### Changed by Paolo Bonzini (Apr 26 2001), this change ### is compatible with libtool 1.4's multi-language branch --tag) prevopt="--tag" prev=tag ;; --features) echo "host: $host" if test "$build_libtool_libs" = yes; then echo "enable shared libraries" else echo "disable shared libraries" fi if test "$build_old_libs" = yes; then echo "enable static libraries" else echo "disable static libraries" fi exit 0 ;; --finish) mode="finish" ;; --mode) prevopt="--mode" prev=mode ;; --mode=*) mode="$optarg" ;; --quiet | --silent) show=: ;; -dlopen) prevopt="-dlopen" prev=execute_dlfiles ;; -*) $echo "$modename: unrecognized option \`$arg'" 1>&2 $echo "$help" 1>&2 exit 1 ;; *) nonopt="$arg" break ;; esac done if test -n "$prevopt"; then $echo "$modename: option \`$prevopt' requires an argument" 1>&2 $echo "$help" 1>&2 exit 1 fi if test -z "$show_help"; then # Infer the operation mode. if test -z "$mode"; then case $nonopt in *cc | *++ | gcc* | *-gcc*) mode=link for arg do case $arg in -c) mode=compile break ;; esac done ;; *db | *dbx | *strace | *truss) mode=execute ;; *install*|cp|mv) mode=install ;; *rm) mode=uninstall ;; *) # If we have no mode, but dlfiles were specified, then do execute mode. test -n "$execute_dlfiles" && mode=execute # Just use the default operation mode. if test -z "$mode"; then if test -n "$nonopt"; then $echo "$modename: warning: cannot infer operation mode from \`$nonopt'" 1>&2 else $echo "$modename: warning: cannot infer operation mode without MODE-ARGS" 1>&2 fi fi ;; esac fi # Only execute mode is allowed to have -dlopen flags. if test -n "$execute_dlfiles" && test "$mode" != execute; then $echo "$modename: unrecognized option \`-dlopen'" 1>&2 $echo "$help" 1>&2 exit 1 fi # Change the help message to a mode-specific one. generic_help="$help" help="Try \`$modename --help --mode=$mode' for more information." # These modes are in order of execution frequency so that they run quickly. case $mode in # libtool compile mode compile) modename="$modename: compile" # Get the compilation command and the source file. base_compile= prev= lastarg= srcfile="$nonopt" suppress_output= user_target=no for arg do case $prev in "") ;; xcompiler) # Aesthetically quote the previous argument. prev= lastarg=`$echo "X$arg" | $Xsed -e "$sed_quote_subst"` case $arg in # Double-quote args containing other shell metacharacters. # Many Bourne shells cannot handle close brackets correctly # in scan sets, so we specify it separately. *[\[\~\#\^\&\*\(\)\{\}\|\;\<\>\?\'\ \ ]*|*]*|"") arg="\"$arg\"" ;; esac # Add the previous argument to base_compile. if test -z "$base_compile"; then base_compile="$lastarg" else base_compile="$base_compile $lastarg" fi continue ;; esac # Accept any command-line options. case $arg in -o) if test "$user_target" != "no"; then $echo "$modename: you cannot specify \`-o' more than once" 1>&2 exit 1 fi user_target=next ;; -static) build_old_libs=yes continue ;; -prefer-pic) pic_mode=yes continue ;; -prefer-non-pic) pic_mode=no continue ;; -Xcompiler) prev=xcompiler continue ;; -Wc,*) args=`$echo "X$arg" | $Xsed -e "s/^-Wc,//"` lastarg= IFS="${IFS= }"; save_ifs="$IFS"; IFS=',' for arg in $args; do IFS="$save_ifs" # Double-quote args containing other shell metacharacters. # Many Bourne shells cannot handle close brackets correctly # in scan sets, so we specify it separately. case $arg in *[\[\~\#\^\&\*\(\)\{\}\|\;\<\>\?\'\ \ ]*|*]*|"") arg="\"$arg\"" ;; esac lastarg="$lastarg $arg" done IFS="$save_ifs" lastarg=`$echo "X$lastarg" | $Xsed -e "s/^ //"` # Add the arguments to base_compile. if test -z "$base_compile"; then base_compile="$lastarg" else base_compile="$base_compile $lastarg" fi continue ;; esac case $user_target in next) # The next one is the -o target name user_target=yes continue ;; yes) # We got the output file user_target=set libobj="$arg" continue ;; esac # Accept the current argument as the source file. lastarg="$srcfile" srcfile="$arg" # Aesthetically quote the previous argument. # Backslashify any backslashes, double quotes, and dollar signs. # These are the only characters that are still specially # interpreted inside of double-quoted scrings. lastarg=`$echo "X$lastarg" | $Xsed -e "$sed_quote_subst"` # Double-quote args containing other shell metacharacters. # Many Bourne shells cannot handle close brackets correctly # in scan sets, so we specify it separately. case $lastarg in *[\[\~\#\^\&\*\(\)\{\}\|\;\<\>\?\'\ \ ]*|*]*|"") lastarg="\"$lastarg\"" ;; esac # Add the previous argument to base_compile. if test -z "$base_compile"; then base_compile="$lastarg" else base_compile="$base_compile $lastarg" fi done case $user_target in set) ;; no) # Get the name of the library object. libobj=`$echo "X$srcfile" | $Xsed -e 's%^.*/%%'` ;; *) $echo "$modename: you must specify a target with \`-o'" 1>&2 exit 1 ;; esac # Recognize several different file suffixes. # If the user specifies -o file.o, it is replaced with file.lo xform='[cCFSfmso]' case $libobj in *.ada) xform=ada ;; *.adb) xform=adb ;; *.ads) xform=ads ;; *.asm) xform=asm ;; *.c++) xform=c++ ;; *.cc) xform=cc ;; *.cpp) xform=cpp ;; *.cxx) xform=cxx ;; *.f90) xform=f90 ;; *.for) xform=for ;; esac libobj=`$echo "X$libobj" | $Xsed -e "s/\.$xform$/.lo/"` case $libobj in *.lo) obj=`$echo "X$libobj" | $Xsed -e "$lo2o"` ;; *) $echo "$modename: cannot determine name of library object from \`$libobj'" 1>&2 exit 1 ;; esac if test -z "$base_compile"; then $echo "$modename: you must specify a compilation command" 1>&2 $echo "$help" 1>&2 exit 1 fi # Delete any leftover library objects. if test "$build_old_libs" = yes; then removelist="$obj $libobj" else removelist="$libobj" fi $run $rm $removelist trap "$run $rm $removelist; exit 1" 1 2 15 # On Cygwin there's no "real" PIC flag so we must build both object types case $host_os in cygwin* | mingw* | pw32* | os2*) pic_mode=default ;; esac if test $pic_mode = no && test "$deplibs_check_method" != pass_all; then # non-PIC code in shared libraries is not supported pic_mode=default fi # Calculate the filename of the output object if compiler does # not support -o with -c if test "$compiler_c_o" = no; then output_obj=`$echo "X$srcfile" | $Xsed -e 's%^.*/%%' -e 's%\.[^.]*$%%'`.${objext} lockfile="$output_obj.lock" removelist="$removelist $output_obj $lockfile" trap "$run $rm $removelist; exit 1" 1 2 15 else need_locks=no lockfile= fi # Lock this critical section if it is needed # We use this script file to make the link, it avoids creating a new file if test "$need_locks" = yes; then until $run ln "$0" "$lockfile" 2>/dev/null; do $show "Waiting for $lockfile to be removed" sleep 2 done elif test "$need_locks" = warn; then if test -f "$lockfile"; then echo "\ *** ERROR, $lockfile exists and contains: `cat $lockfile 2>/dev/null` This indicates that another process is trying to use the same temporary object file, and libtool could not work around it because your compiler does not support \`-c' and \`-o' together. If you repeat this compilation, it may succeed, by chance, but you had better avoid parallel builds (make -j) in this platform, or get a better compiler." $run $rm $removelist exit 1 fi echo $srcfile > "$lockfile" fi if test -n "$fix_srcfile_path"; then eval srcfile=\"$fix_srcfile_path\" fi # Only build a PIC object if we are building libtool libraries. if test "$build_libtool_libs" = yes; then # Without this assignment, base_compile gets emptied. fbsd_hideous_sh_bug=$base_compile if test "$pic_mode" != no; then # All platforms use -DPIC, to notify preprocessed assembler code. command="$base_compile $srcfile $pic_flag -DPIC" else # Don't build PIC code command="$base_compile $srcfile" fi if test "$build_old_libs" = yes; then lo_libobj="$libobj" dir=`$echo "X$libobj" | $Xsed -e 's%/[^/]*$%%'` if test "X$dir" = "X$libobj"; then dir="$objdir" else dir="$dir/$objdir" fi libobj="$dir/"`$echo "X$libobj" | $Xsed -e 's%^.*/%%'` if test -d "$dir"; then $show "$rm $libobj" $run $rm $libobj else $show "$mkdir $dir" $run $mkdir $dir status=$? if test $status -ne 0 && test ! -d $dir; then exit $status fi fi fi if test "$compiler_o_lo" = yes; then output_obj="$libobj" command="$command -o $output_obj" elif test "$compiler_c_o" = yes; then output_obj="$obj" command="$command -o $output_obj" fi $run $rm "$output_obj" $show "$command" if $run eval "$command"; then : else test -n "$output_obj" && $run $rm $removelist exit 1 fi if test "$need_locks" = warn && test x"`cat $lockfile 2>/dev/null`" != x"$srcfile"; then echo "\ *** ERROR, $lockfile contains: `cat $lockfile 2>/dev/null` but it should contain: $srcfile This indicates that another process is trying to use the same temporary object file, and libtool could not work around it because your compiler does not support \`-c' and \`-o' together. If you repeat this compilation, it may succeed, by chance, but you had better avoid parallel builds (make -j) in this platform, or get a better compiler." $run $rm $removelist exit 1 fi # Just move the object if needed, then go on to compile the next one if test x"$output_obj" != x"$libobj"; then $show "$mv $output_obj $libobj" if $run $mv $output_obj $libobj; then : else error=$? $run $rm $removelist exit $error fi fi # If we have no pic_flag, then copy the object into place and finish. if (test -z "$pic_flag" || test "$pic_mode" != default) && test "$build_old_libs" = yes; then # Rename the .lo from within objdir to obj if test -f $obj; then $show $rm $obj $run $rm $obj fi $show "$mv $libobj $obj" if $run $mv $libobj $obj; then : else error=$? $run $rm $removelist exit $error fi xdir=`$echo "X$obj" | $Xsed -e 's%/[^/]*$%%'` if test "X$xdir" = "X$obj"; then xdir="." else xdir="$xdir" fi baseobj=`$echo "X$obj" | $Xsed -e "s%.*/%%"` libobj=`$echo "X$baseobj" | $Xsed -e "$o2lo"` # Now arrange that obj and lo_libobj become the same file $show "(cd $xdir && $LN_S $baseobj $libobj)" if $run eval '(cd $xdir && $LN_S $baseobj $libobj)'; then exit 0 else error=$? $run $rm $removelist exit $error fi fi # Allow error messages only from the first compilation. suppress_output=' >/dev/null 2>&1' fi # Only build a position-dependent object if we build old libraries. if test "$build_old_libs" = yes; then if test "$pic_mode" != yes; then # Don't build PIC code command="$base_compile $srcfile" else # All platforms use -DPIC, to notify preprocessed assembler code. command="$base_compile $srcfile $pic_flag -DPIC" fi if test "$compiler_c_o" = yes; then command="$command -o $obj" output_obj="$obj" fi # Suppress compiler output if we already did a PIC compilation. command="$command$suppress_output" $run $rm "$output_obj" $show "$command" if $run eval "$command"; then : else $run $rm $removelist exit 1 fi if test "$need_locks" = warn && test x"`cat $lockfile 2>/dev/null`" != x"$srcfile"; then echo "\ *** ERROR, $lockfile contains: `cat $lockfile 2>/dev/null` but it should contain: $srcfile This indicates that another process is trying to use the same temporary object file, and libtool could not work around it because your compiler does not support \`-c' and \`-o' together. If you repeat this compilation, it may succeed, by chance, but you had better avoid parallel builds (make -j) in this platform, or get a better compiler." $run $rm $removelist exit 1 fi # Just move the object if needed if test x"$output_obj" != x"$obj"; then $show "$mv $output_obj $obj" if $run $mv $output_obj $obj; then : else error=$? $run $rm $removelist exit $error fi fi # Create an invalid libtool object if no PIC, so that we do not # accidentally link it into a program. if test "$build_libtool_libs" != yes; then $show "echo timestamp > $libobj" $run eval "echo timestamp > \$libobj" || exit $? else # Move the .lo from within objdir $show "$mv $libobj $lo_libobj" if $run $mv $libobj $lo_libobj; then : else error=$? $run $rm $removelist exit $error fi fi fi # Unlock the critical section if it was locked if test "$need_locks" != no; then $run $rm "$lockfile" fi exit 0 ;; # libtool link mode link | relink) modename="$modename: link" case $host in *-*-cygwin* | *-*-mingw* | *-*-pw32* | *-*-os2*) # It is impossible to link a dll without this setting, and # we shouldn't force the makefile maintainer to figure out # which system we are compiling for in order to pass an extra # flag for every libtool invokation. # allow_undefined=no # FIXME: Unfortunately, there are problems with the above when trying # to make a dll which has undefined symbols, in which case not # even a static library is built. For now, we need to specify # -no-undefined on the libtool link line when we can be certain # that all symbols are satisfied, otherwise we get a static library. allow_undefined=yes ;; *) allow_undefined=yes ;; esac libtool_args="$nonopt" compile_command="$nonopt" finalize_command="$nonopt" compile_rpath= finalize_rpath= compile_shlibpath= finalize_shlibpath= convenience= old_convenience= deplibs= old_deplibs= compiler_flags= linker_flags= dllsearchpath= lib_search_path=`pwd` avoid_version=no dlfiles= dlprefiles= dlself=no export_dynamic=no export_symbols= export_symbols_regex= generated= libobjs= ltlibs= module=no no_install=no objs= prefer_static_libs=no preload=no prev= prevarg= release= rpath= xrpath= perm_rpath= temp_rpath= thread_safe=no vinfo= # We need to know -static, to get the right output filenames. for arg do case $arg in -all-static | -static) if test "X$arg" = "X-all-static"; then if test "$build_libtool_libs" = yes && test -z "$link_static_flag"; then $echo "$modename: warning: complete static linking is impossible in this configuration" 1>&2 fi if test -n "$link_static_flag"; then dlopen_self=$dlopen_self_static fi else if test -z "$pic_flag" && test -n "$link_static_flag"; then dlopen_self=$dlopen_self_static fi fi build_libtool_libs=no build_old_libs=yes prefer_static_libs=yes break ;; esac done # See if our shared archives depend on static archives. test -n "$old_archive_from_new_cmds" && build_old_libs=yes # Go through the arguments, transforming them on the way. while test $# -gt 0; do arg="$1" shift case $arg in *[\[\~\#\^\&\*\(\)\{\}\|\;\<\>\?\'\ \ ]*|*]*|"") qarg=\"`$echo "X$arg" | $Xsed -e "$sed_quote_subst"`\" ### testsuite: skip nested quoting test ;; *) qarg=$arg ;; esac libtool_args="$libtool_args $qarg" # If the previous option needs an argument, assign it. if test -n "$prev"; then case $prev in output) compile_command="$compile_command @OUTPUT@" finalize_command="$finalize_command @OUTPUT@" ;; esac case $prev in dlfiles|dlprefiles) if test "$preload" = no; then # Add the symbol object into the linking commands. compile_command="$compile_command @SYMFILE@" finalize_command="$finalize_command @SYMFILE@" preload=yes fi case $arg in *.la | *.lo) ;; # We handle these cases below. force) if test "$dlself" = no; then dlself=needless export_dynamic=yes fi prev= continue ;; self) if test "$prev" = dlprefiles; then dlself=yes elif test "$prev" = dlfiles && test "$dlopen_self" != yes; then dlself=yes else dlself=needless export_dynamic=yes fi prev= continue ;; *) if test "$prev" = dlfiles; then dlfiles="$dlfiles $arg" else dlprefiles="$dlprefiles $arg" fi prev= continue ;; esac ;; expsyms) export_symbols="$arg" if test ! -f "$arg"; then $echo "$modename: symbol file \`$arg' does not exist" exit 1 fi prev= continue ;; expsyms_regex) export_symbols_regex="$arg" prev= continue ;; release) release="-$arg" prev= continue ;; rpath | xrpath) # We need an absolute path. case $arg in [\\/]* | [A-Za-z]:[\\/]*) ;; *) $echo "$modename: only absolute run-paths are allowed" 1>&2 exit 1 ;; esac if test "$prev" = rpath; then case "$rpath " in *" $arg "*) ;; *) rpath="$rpath $arg" ;; esac else case "$xrpath " in *" $arg "*) ;; *) xrpath="$xrpath $arg" ;; esac fi prev= continue ;; xcompiler) compiler_flags="$compiler_flags $qarg" prev= compile_command="$compile_command $qarg" finalize_command="$finalize_command $qarg" continue ;; xlinker) linker_flags="$linker_flags $qarg" compiler_flags="$compiler_flags $wl$qarg" prev= compile_command="$compile_command $wl$qarg" finalize_command="$finalize_command $wl$qarg" continue ;; *) eval "$prev=\"\$arg\"" prev= continue ;; esac fi # test -n $prev prevarg="$arg" case $arg in -all-static) if test -n "$link_static_flag"; then compile_command="$compile_command $link_static_flag" finalize_command="$finalize_command $link_static_flag" fi continue ;; -allow-undefined) # FIXME: remove this flag sometime in the future. $echo "$modename: \`-allow-undefined' is deprecated because it is the default" 1>&2 continue ;; -avoid-version) avoid_version=yes continue ;; -dlopen) prev=dlfiles continue ;; -dlpreopen) prev=dlprefiles continue ;; -export-dynamic) export_dynamic=yes continue ;; -export-symbols | -export-symbols-regex) if test -n "$export_symbols" || test -n "$export_symbols_regex"; then $echo "$modename: more than one -exported-symbols argument is not allowed" exit 1 fi if test "X$arg" = "X-export-symbols"; then prev=expsyms else prev=expsyms_regex fi continue ;; # The native IRIX linker understands -LANG:*, -LIST:* and -LNO:* # so, if we see these flags be careful not to treat them like -L -L[A-Z][A-Z]*:*) case $with_gcc/$host in no/*-*-irix*) compile_command="$compile_command $arg" finalize_command="$finalize_command $arg" ;; esac continue ;; -L*) dir=`$echo "X$arg" | $Xsed -e 's/^-L//'` # We need an absolute path. case $dir in [\\/]* | [A-Za-z]:[\\/]*) ;; *) absdir=`cd "$dir" && pwd` if test -z "$absdir"; then $echo "$modename: cannot determine absolute directory name of \`$dir'" 1>&2 exit 1 fi dir="$absdir" ;; esac case "$deplibs " in *" -L$dir "*) ;; *) deplibs="$deplibs -L$dir" lib_search_path="$lib_search_path $dir" ;; esac case $host in *-*-cygwin* | *-*-mingw* | *-*-pw32* | *-*-os2*) case :$dllsearchpath: in *":$dir:"*) ;; *) dllsearchpath="$dllsearchpath:$dir";; esac ;; esac continue ;; -l*) if test "X$arg" = "X-lc" || test "X$arg" = "X-lm"; then case $host in *-*-cygwin* | *-*-pw32* | *-*-beos*) # These systems don't actually have a C or math library (as such) continue ;; *-*-mingw* | *-*-os2*) # These systems don't actually have a C library (as such) test "X$arg" = "X-lc" && continue ;; esac fi deplibs="$deplibs $arg" continue ;; -module) module=yes continue ;; -no-fast-install) fast_install=no continue ;; -no-install) case $host in *-*-cygwin* | *-*-mingw* | *-*-pw32* | *-*-os2*) # The PATH hackery in wrapper scripts is required on Windows # in order for the loader to find any dlls it needs. $echo "$modename: warning: \`-no-install' is ignored for $host" 1>&2 $echo "$modename: warning: assuming \`-no-fast-install' instead" 1>&2 fast_install=no ;; *) no_install=yes ;; esac continue ;; -no-undefined) allow_undefined=no continue ;; -o) prev=output ;; -release) prev=release continue ;; -rpath) prev=rpath continue ;; -R) prev=xrpath continue ;; -R*) dir=`$echo "X$arg" | $Xsed -e 's/^-R//'` # We need an absolute path. case $dir in [\\/]* | [A-Za-z]:[\\/]*) ;; *) $echo "$modename: only absolute run-paths are allowed" 1>&2 exit 1 ;; esac case "$xrpath " in *" $dir "*) ;; *) xrpath="$xrpath $dir" ;; esac continue ;; -static) # The effects of -static are defined in a previous loop. # We used to do the same as -all-static on platforms that # didn't have a PIC flag, but the assumption that the effects # would be equivalent was wrong. It would break on at least # Digital Unix and AIX. continue ;; -thread-safe) thread_safe=yes continue ;; -version-info) prev=vinfo continue ;; -Wc,*) args=`$echo "X$arg" | $Xsed -e "$sed_quote_subst" -e 's/^-Wc,//'` arg= IFS="${IFS= }"; save_ifs="$IFS"; IFS=',' for flag in $args; do IFS="$save_ifs" case $flag in *[\[\~\#\^\&\*\(\)\{\}\|\;\<\>\?\'\ \ ]*|*]*|"") flag="\"$flag\"" ;; esac arg="$arg $wl$flag" compiler_flags="$compiler_flags $flag" done IFS="$save_ifs" arg=`$echo "X$arg" | $Xsed -e "s/^ //"` ;; -Wl,*) args=`$echo "X$arg" | $Xsed -e "$sed_quote_subst" -e 's/^-Wl,//'` arg= IFS="${IFS= }"; save_ifs="$IFS"; IFS=',' for flag in $args; do IFS="$save_ifs" case $flag in *[\[\~\#\^\&\*\(\)\{\}\|\;\<\>\?\'\ \ ]*|*]*|"") flag="\"$flag\"" ;; esac arg="$arg $wl$flag" compiler_flags="$compiler_flags $wl$flag" linker_flags="$linker_flags $flag" done IFS="$save_ifs" arg=`$echo "X$arg" | $Xsed -e "s/^ //"` ;; -Xcompiler) prev=xcompiler continue ;; -Xlinker) prev=xlinker continue ;; # Some other compiler flag. -* | +*) # Unknown arguments in both finalize_command and compile_command need # to be aesthetically quoted because they are evaled later. arg=`$echo "X$arg" | $Xsed -e "$sed_quote_subst"` case $arg in *[\[\~\#\^\&\*\(\)\{\}\|\;\<\>\?\'\ \ ]*|*]*|"") arg="\"$arg\"" ;; esac ;; *.lo | *.$objext) # A library or standard object. if test "$prev" = dlfiles; then # This file was specified with -dlopen. if test "$build_libtool_libs" = yes && test "$dlopen_support" = yes; then dlfiles="$dlfiles $arg" prev= continue else # If libtool objects are unsupported, then we need to preload. prev=dlprefiles fi fi if test "$prev" = dlprefiles; then # Preload the old-style object. dlprefiles="$dlprefiles "`$echo "X$arg" | $Xsed -e "$lo2o"` prev= else case $arg in *.lo) libobjs="$libobjs $arg" ;; *) objs="$objs $arg" ;; esac fi ;; *.$libext) # An archive. deplibs="$deplibs $arg" old_deplibs="$old_deplibs $arg" continue ;; *.la) # A libtool-controlled library. if test "$prev" = dlfiles; then # This library was specified with -dlopen. dlfiles="$dlfiles $arg" prev= elif test "$prev" = dlprefiles; then # The library was specified with -dlpreopen. dlprefiles="$dlprefiles $arg" prev= else deplibs="$deplibs $arg" fi continue ;; # Some other compiler argument. *) # Unknown arguments in both finalize_command and compile_command need # to be aesthetically quoted because they are evaled later. arg=`$echo "X$arg" | $Xsed -e "$sed_quote_subst"` case $arg in *[\[\~\#\^\&\*\(\)\{\}\|\;\<\>\?\'\ \ ]*|*]*|"") arg="\"$arg\"" ;; esac ;; esac # arg # Now actually substitute the argument into the commands. if test -n "$arg"; then compile_command="$compile_command $arg" finalize_command="$finalize_command $arg" fi done # argument parsing loop if test -n "$prev"; then $echo "$modename: the \`$prevarg' option requires an argument" 1>&2 $echo "$help" 1>&2 exit 1 fi if test "$export_dynamic" = yes && test -n "$export_dynamic_flag_spec"; then eval arg=\"$export_dynamic_flag_spec\" compile_command="$compile_command $arg" finalize_command="$finalize_command $arg" fi # calculate the name of the file, without its directory outputname=`$echo "X$output" | $Xsed -e 's%^.*/%%'` libobjs_save="$libobjs" if test -n "$shlibpath_var"; then # get the directories listed in $shlibpath_var eval shlib_search_path=\`\$echo \"X\${$shlibpath_var}\" \| \$Xsed -e \'s/:/ /g\'\` else shlib_search_path= fi eval sys_lib_search_path=\"$sys_lib_search_path_spec\" eval sys_lib_dlsearch_path=\"$sys_lib_dlsearch_path_spec\" output_objdir=`$echo "X$output" | $Xsed -e 's%/[^/]*$%%'` if test "X$output_objdir" = "X$output"; then output_objdir="$objdir" else output_objdir="$output_objdir/$objdir" fi # Create the object directory. if test ! -d $output_objdir; then $show "$mkdir $output_objdir" $run $mkdir $output_objdir status=$? if test $status -ne 0 && test ! -d $output_objdir; then exit $status fi fi # Determine the type of output case $output in "") $echo "$modename: you must specify an output file" 1>&2 $echo "$help" 1>&2 exit 1 ;; *.$libext) linkmode=oldlib ;; *.lo | *.$objext) linkmode=obj ;; *.la) linkmode=lib ;; *) linkmode=prog ;; # Anything else should be a program. esac specialdeplibs= libs= # Find all interdependent deplibs by searching for libraries # that are linked more than once (e.g. -la -lb -la) for deplib in $deplibs; do case "$libs " in *" $deplib "*) specialdeplibs="$specialdeplibs $deplib" ;; esac libs="$libs $deplib" done deplibs= newdependency_libs= newlib_search_path= need_relink=no # whether we're linking any uninstalled libtool libraries notinst_deplibs= # not-installed libtool libraries notinst_path= # paths that contain not-installed libtool libraries case $linkmode in lib) passes="conv link" for file in $dlfiles $dlprefiles; do case $file in *.la) ;; *) $echo "$modename: libraries can \`-dlopen' only libtool libraries: $file" 1>&2 exit 1 ;; esac done ;; prog) compile_deplibs= finalize_deplibs= alldeplibs=no newdlfiles= newdlprefiles= passes="conv scan dlopen dlpreopen link" ;; *) passes="conv" ;; esac for pass in $passes; do if test $linkmode = prog; then # Determine which files to process case $pass in dlopen) libs="$dlfiles" save_deplibs="$deplibs" # Collect dlpreopened libraries deplibs= ;; dlpreopen) libs="$dlprefiles" ;; link) libs="$deplibs %DEPLIBS% $dependency_libs" ;; esac fi for deplib in $libs; do lib= found=no case $deplib in -l*) if test $linkmode = oldlib && test $linkmode = obj; then $echo "$modename: warning: \`-l' is ignored for archives/objects: $deplib" 1>&2 continue fi if test $pass = conv; then deplibs="$deplib $deplibs" continue fi name=`$echo "X$deplib" | $Xsed -e 's/^-l//'` for searchdir in $newlib_search_path $lib_search_path $sys_lib_search_path $shlib_search_path; do # Search the libtool library lib="$searchdir/lib${name}.la" if test -f "$lib"; then found=yes break fi done if test "$found" != yes; then # deplib doesn't seem to be a libtool library if test "$linkmode,$pass" = "prog,link"; then compile_deplibs="$deplib $compile_deplibs" finalize_deplibs="$deplib $finalize_deplibs" else deplibs="$deplib $deplibs" test $linkmode = lib && newdependency_libs="$deplib $newdependency_libs" fi continue fi ;; # -l -L*) case $linkmode in lib) deplibs="$deplib $deplibs" test $pass = conv && continue newdependency_libs="$deplib $newdependency_libs" newlib_search_path="$newlib_search_path "`$echo "X$deplib" | $Xsed -e 's/^-L//'` ;; prog) if test $pass = conv; then deplibs="$deplib $deplibs" continue fi if test $pass = scan; then deplibs="$deplib $deplibs" newlib_search_path="$newlib_search_path "`$echo "X$deplib" | $Xsed -e 's/^-L//'` else compile_deplibs="$deplib $compile_deplibs" finalize_deplibs="$deplib $finalize_deplibs" fi ;; *) $echo "$modename: warning: \`-L' is ignored for archives/objects: $deplib" 1>&2 ;; esac # linkmode continue ;; # -L -R*) if test $pass = link; then dir=`$echo "X$deplib" | $Xsed -e 's/^-R//'` # Make sure the xrpath contains only unique directories. case "$xrpath " in *" $dir "*) ;; *) xrpath="$xrpath $dir" ;; esac fi deplibs="$deplib $deplibs" continue ;; *.la) lib="$deplib" ;; *.$libext) if test $pass = conv; then deplibs="$deplib $deplibs" continue fi case $linkmode in lib) if test "$deplibs_check_method" != pass_all; then echo echo "*** Warning: This library needs some functionality provided by $deplib." echo "*** I have the capability to make that library automatically link in when" echo "*** you link to this library. But I can only do this if you have a" echo "*** shared version of the library, which you do not appear to have." else echo echo "*** Warning: Linking the shared library $output against the" echo "*** static library $deplib is not portable!" deplibs="$deplib $deplibs" fi continue ;; prog) if test $pass != link; then deplibs="$deplib $deplibs" else compile_deplibs="$deplib $compile_deplibs" finalize_deplibs="$deplib $finalize_deplibs" fi continue ;; esac # linkmode ;; # *.$libext *.lo | *.$objext) if test $pass = dlpreopen || test "$dlopen_support" != yes || test "$build_libtool_libs" = no; then # If there is no dlopen support or we're linking statically, # we need to preload. newdlprefiles="$newdlprefiles $deplib" compile_deplibs="$deplib $compile_deplibs" finalize_deplibs="$deplib $finalize_deplibs" else newdlfiles="$newdlfiles $deplib" fi continue ;; %DEPLIBS%) alldeplibs=yes continue ;; esac # case $deplib if test $found = yes || test -f "$lib"; then : else $echo "$modename: cannot find the library \`$lib'" 1>&2 exit 1 fi # Check to see that this really is a libtool archive. if (sed -e '2q' $lib | egrep "^# Generated by .*$PACKAGE") >/dev/null 2>&1; then : else $echo "$modename: \`$lib' is not a valid libtool archive" 1>&2 exit 1 fi ladir=`$echo "X$lib" | $Xsed -e 's%/[^/]*$%%'` test "X$ladir" = "X$lib" && ladir="." dlname= dlopen= dlpreopen= libdir= library_names= old_library= # If the library was installed with an old release of libtool, # it will not redefine variable installed. installed=yes # Read the .la file case $lib in */* | *\\*) . $lib ;; *) . ./$lib ;; esac if test "$linkmode,$pass" = "lib,link" || test "$linkmode,$pass" = "prog,scan" || { test $linkmode = oldlib && test $linkmode = obj; }; then # Add dl[pre]opened files of deplib test -n "$dlopen" && dlfiles="$dlfiles $dlopen" test -n "$dlpreopen" && dlprefiles="$dlprefiles $dlpreopen" fi if test $pass = conv; then # Only check for convenience libraries deplibs="$lib $deplibs" if test -z "$libdir"; then if test -z "$old_library"; then $echo "$modename: cannot find name of link library for \`$lib'" 1>&2 exit 1 fi # It is a libtool convenience library, so add in its objects. convenience="$convenience $ladir/$objdir/$old_library" old_convenience="$old_convenience $ladir/$objdir/$old_library" tmp_libs= for deplib in $dependency_libs; do deplibs="$deplib $deplibs" case "$tmp_libs " in *" $deplib "*) specialdeplibs="$specialdeplibs $deplib" ;; esac tmp_libs="$tmp_libs $deplib" done elif test $linkmode != prog && test $linkmode != lib; then $echo "$modename: \`$lib' is not a convenience library" 1>&2 exit 1 fi continue fi # $pass = conv # Get the name of the library we link against. linklib= for l in $old_library $library_names; do linklib="$l" done if test -z "$linklib"; then $echo "$modename: cannot find name of link library for \`$lib'" 1>&2 exit 1 fi # This library was specified with -dlopen. if test $pass = dlopen; then if test -z "$libdir"; then $echo "$modename: cannot -dlopen a convenience library: \`$lib'" 1>&2 exit 1 fi if test -z "$dlname" || test "$dlopen_support" != yes || test "$build_libtool_libs" = no; then # If there is no dlname, no dlopen support or we're linking # statically, we need to preload. dlprefiles="$dlprefiles $lib" else newdlfiles="$newdlfiles $lib" fi continue fi # $pass = dlopen # We need an absolute path. case $ladir in [\\/]* | [A-Za-z]:[\\/]*) abs_ladir="$ladir" ;; *) abs_ladir=`cd "$ladir" && pwd` if test -z "$abs_ladir"; then $echo "$modename: warning: cannot determine absolute directory name of \`$ladir'" 1>&2 $echo "$modename: passing it literally to the linker, although it might fail" 1>&2 abs_ladir="$ladir" fi ;; esac laname=`$echo "X$lib" | $Xsed -e 's%^.*/%%'` # Find the relevant object directory and library name. if test "X$installed" = Xyes; then if test ! -f "$libdir/$linklib" && test -f "$abs_ladir/$linklib"; then $echo "$modename: warning: library \`$lib' was moved." 1>&2 dir="$ladir" absdir="$abs_ladir" libdir="$abs_ladir" else dir="$libdir" absdir="$libdir" fi else dir="$ladir/$objdir" absdir="$abs_ladir/$objdir" # Remove this search path later notinst_path="$notinst_path $abs_ladir" fi # $installed = yes name=`$echo "X$laname" | $Xsed -e 's/\.la$//' -e 's/^lib//'` # This library was specified with -dlpreopen. if test $pass = dlpreopen; then if test -z "$libdir"; then $echo "$modename: cannot -dlpreopen a convenience library: \`$lib'" 1>&2 exit 1 fi # Prefer using a static library (so that no silly _DYNAMIC symbols # are required to link). if test -n "$old_library"; then newdlprefiles="$newdlprefiles $dir/$old_library" # Otherwise, use the dlname, so that lt_dlopen finds it. elif test -n "$dlname"; then newdlprefiles="$newdlprefiles $dir/$dlname" else newdlprefiles="$newdlprefiles $dir/$linklib" fi fi # $pass = dlpreopen if test -z "$libdir"; then # Link the convenience library if test $linkmode = lib; then deplibs="$dir/$old_library $deplibs" elif test "$linkmode,$pass" = "prog,link"; then compile_deplibs="$dir/$old_library $compile_deplibs" finalize_deplibs="$dir/$old_library $finalize_deplibs" else deplibs="$lib $deplibs" fi continue fi if test $linkmode = prog && test $pass != link; then newlib_search_path="$newlib_search_path $ladir" deplibs="$lib $deplibs" linkalldeplibs=no if test "$link_all_deplibs" != no || test -z "$library_names" || test "$build_libtool_libs" = no; then linkalldeplibs=yes fi tmp_libs= for deplib in $dependency_libs; do case $deplib in -L*) newlib_search_path="$newlib_search_path "`$echo "X$deplib" | $Xsed -e 's/^-L//'`;; ### testsuite: skip nested quoting test esac # Need to link against all dependency_libs? if test $linkalldeplibs = yes; then deplibs="$deplib $deplibs" else # Need to hardcode shared library paths # or/and link against static libraries newdependency_libs="$deplib $newdependency_libs" fi case "$tmp_libs " in *" $deplib "*) specialdeplibs="$specialdeplibs $deplib" ;; esac tmp_libs="$tmp_libs $deplib" done # for deplib continue fi # $linkmode = prog... link_static=no # Whether the deplib will be linked statically if test -n "$library_names" && { test "$prefer_static_libs" = no || test -z "$old_library"; }; then # Link against this shared library if test "$linkmode,$pass" = "prog,link" || { test $linkmode = lib && test $hardcode_into_libs = yes; }; then # Hardcode the library path. # Skip directories that are in the system default run-time # search path. case " $sys_lib_dlsearch_path " in *" $absdir "*) ;; *) case "$compile_rpath " in *" $absdir "*) ;; *) compile_rpath="$compile_rpath $absdir" esac ;; esac case " $sys_lib_dlsearch_path " in *" $libdir "*) ;; *) case "$finalize_rpath " in *" $libdir "*) ;; *) finalize_rpath="$finalize_rpath $libdir" esac ;; esac if test $linkmode = prog; then # We need to hardcode the library path if test -n "$shlibpath_var"; then # Make sure the rpath contains only unique directories. case "$temp_rpath " in *" $dir "*) ;; *" $absdir "*) ;; *) temp_rpath="$temp_rpath $dir" ;; esac fi fi fi # $linkmode,$pass = prog,link... if test "$alldeplibs" = yes && { test "$deplibs_check_method" = pass_all || { test "$build_libtool_libs" = yes && test -n "$library_names"; }; }; then # We only need to search for static libraries continue fi if test "$installed" = no; then notinst_deplibs="$notinst_deplibs $lib" need_relink=yes fi if test -n "$old_archive_from_expsyms_cmds"; then # figure out the soname set dummy $library_names realname="$2" shift; shift libname=`eval \\$echo \"$libname_spec\"` # use dlname if we got it. it's perfectly good, no? if test -n "$dlname"; then soname="$dlname" elif test -n "$soname_spec"; then # bleh windows case $host in *cygwin*) major=`expr $current - $age` versuffix="-$major" ;; esac eval soname=\"$soname_spec\" else soname="$realname" fi # Make a new name for the extract_expsyms_cmds to use soroot="$soname" soname=`echo $soroot | sed -e 's/^.*\///'` newlib="libimp-`echo $soname | sed 's/^lib//;s/\.dll$//'`.a" # If the library has no export list, then create one now if test -f "$output_objdir/$soname-def"; then : else $show "extracting exported symbol list from \`$soname'" IFS="${IFS= }"; save_ifs="$IFS"; IFS='~' eval cmds=\"$extract_expsyms_cmds\" for cmd in $cmds; do IFS="$save_ifs" $show "$cmd" $run eval "$cmd" || exit $? done IFS="$save_ifs" fi # Create $newlib if test -f "$output_objdir/$newlib"; then :; else $show "generating import library for \`$soname'" IFS="${IFS= }"; save_ifs="$IFS"; IFS='~' eval cmds=\"$old_archive_from_expsyms_cmds\" for cmd in $cmds; do IFS="$save_ifs" $show "$cmd" $run eval "$cmd" || exit $? done IFS="$save_ifs" fi # make sure the library variables are pointing to the new library dir=$output_objdir linklib=$newlib fi # test -n $old_archive_from_expsyms_cmds if test $linkmode = prog || test "$mode" != relink; then add_shlibpath= add_dir= add= lib_linked=yes case $hardcode_action in immediate | unsupported) if test "$hardcode_direct" = no; then add="$dir/$linklib" elif test "$hardcode_minus_L" = no; then case $host in *-*-sunos*) add_shlibpath="$dir" ;; esac add_dir="-L$dir" add="-l$name" elif test "$hardcode_shlibpath_var" = no; then add_shlibpath="$dir" add="-l$name" else lib_linked=no fi ;; relink) if test "$hardcode_direct" = yes; then add="$dir/$linklib" elif test "$hardcode_minus_L" = yes; then add_dir="-L$dir" add="-l$name" elif test "$hardcode_shlibpath_var" = yes; then add_shlibpath="$dir" add="-l$name" else lib_linked=no fi ;; *) lib_linked=no ;; esac if test "$lib_linked" != yes; then $echo "$modename: configuration error: unsupported hardcode properties" exit 1 fi if test -n "$add_shlibpath"; then case :$compile_shlibpath: in *":$add_shlibpath:"*) ;; *) compile_shlibpath="$compile_shlibpath$add_shlibpath:" ;; esac fi if test $linkmode = prog; then test -n "$add_dir" && compile_deplibs="$add_dir $compile_deplibs" test -n "$add" && compile_deplibs="$add $compile_deplibs" else test -n "$add_dir" && deplibs="$add_dir $deplibs" test -n "$add" && deplibs="$add $deplibs" if test "$hardcode_direct" != yes && \ test "$hardcode_minus_L" != yes && \ test "$hardcode_shlibpath_var" = yes; then case :$finalize_shlibpath: in *":$libdir:"*) ;; *) finalize_shlibpath="$finalize_shlibpath$libdir:" ;; esac fi fi fi if test $linkmode = prog || test "$mode" = relink; then add_shlibpath= add_dir= add= # Finalize command for both is simple: just hardcode it. if test "$hardcode_direct" = yes; then add="$libdir/$linklib" elif test "$hardcode_minus_L" = yes; then add_dir="-L$libdir" add="-l$name" elif test "$hardcode_shlibpath_var" = yes; then case :$finalize_shlibpath: in *":$libdir:"*) ;; *) finalize_shlibpath="$finalize_shlibpath$libdir:" ;; esac add="-l$name" else # We cannot seem to hardcode it, guess we'll fake it. add_dir="-L$libdir" add="-l$name" fi if test $linkmode = prog; then test -n "$add_dir" && finalize_deplibs="$add_dir $finalize_deplibs" test -n "$add" && finalize_deplibs="$add $finalize_deplibs" else test -n "$add_dir" && deplibs="$add_dir $deplibs" test -n "$add" && deplibs="$add $deplibs" fi fi elif test $linkmode = prog; then if test "$alldeplibs" = yes && { test "$deplibs_check_method" = pass_all || { test "$build_libtool_libs" = yes && test -n "$library_names"; }; }; then # We only need to search for static libraries continue fi # Try to link the static library # Here we assume that one of hardcode_direct or hardcode_minus_L # is not unsupported. This is valid on all known static and # shared platforms. if test "$hardcode_direct" != unsupported; then test -n "$old_library" && linklib="$old_library" compile_deplibs="$dir/$linklib $compile_deplibs" finalize_deplibs="$dir/$linklib $finalize_deplibs" else compile_deplibs="-l$name -L$dir $compile_deplibs" finalize_deplibs="-l$name -L$dir $finalize_deplibs" fi elif test "$build_libtool_libs" = yes; then # Not a shared library if test "$deplibs_check_method" != pass_all; then # We're trying link a shared library against a static one # but the system doesn't support it. # Just print a warning and add the library to dependency_libs so # that the program can be linked against the static library. echo echo "*** Warning: This library needs some functionality provided by $lib." echo "*** I have the capability to make that library automatically link in when" echo "*** you link to this library. But I can only do this if you have a" echo "*** shared version of the library, which you do not appear to have." if test "$module" = yes; then echo "*** Therefore, libtool will create a static module, that should work " echo "*** as long as the dlopening application is linked with the -dlopen flag." if test -z "$global_symbol_pipe"; then echo echo "*** However, this would only work if libtool was able to extract symbol" echo "*** lists from a program, using \`nm' or equivalent, but libtool could" echo "*** not find such a program. So, this module is probably useless." echo "*** \`nm' from GNU binutils and a full rebuild may help." fi if test "$build_old_libs" = no; then build_libtool_libs=module build_old_libs=yes else build_libtool_libs=no fi fi else convenience="$convenience $dir/$old_library" old_convenience="$old_convenience $dir/$old_library" deplibs="$dir/$old_library $deplibs" link_static=yes fi fi # link shared/static library? if test $linkmode = lib; then if test -n "$dependency_libs" && { test $hardcode_into_libs != yes || test $build_old_libs = yes || test $link_static = yes; }; then # Extract -R from dependency_libs temp_deplibs= for libdir in $dependency_libs; do case $libdir in -R*) temp_xrpath=`$echo "X$libdir" | $Xsed -e 's/^-R//'` case " $xrpath " in *" $temp_xrpath "*) ;; *) xrpath="$xrpath $temp_xrpath";; esac;; *) temp_deplibs="$temp_deplibs $libdir";; esac done dependency_libs="$temp_deplibs" fi newlib_search_path="$newlib_search_path $absdir" # Link against this library test "$link_static" = no && newdependency_libs="$abs_ladir/$laname $newdependency_libs" # ... and its dependency_libs tmp_libs= for deplib in $dependency_libs; do newdependency_libs="$deplib $newdependency_libs" case "$tmp_libs " in *" $deplib "*) specialdeplibs="$specialdeplibs $deplib" ;; esac tmp_libs="$tmp_libs $deplib" done if test $link_all_deplibs != no; then # Add the search paths of all dependency libraries for deplib in $dependency_libs; do case $deplib in -L*) path="$deplib" ;; *.la) dir=`$echo "X$deplib" | $Xsed -e 's%/[^/]*$%%'` test "X$dir" = "X$deplib" && dir="." # We need an absolute path. case $dir in [\\/]* | [A-Za-z]:[\\/]*) absdir="$dir" ;; *) absdir=`cd "$dir" && pwd` if test -z "$absdir"; then $echo "$modename: warning: cannot determine absolute directory name of \`$dir'" 1>&2 absdir="$dir" fi ;; esac if grep "^installed=no" $deplib > /dev/null; then path="-L$absdir/$objdir" else eval libdir=`sed -n -e 's/^libdir=\(.*\)$/\1/p' $deplib` if test -z "$libdir"; then $echo "$modename: \`$deplib' is not a valid libtool archive" 1>&2 exit 1 fi if test "$absdir" != "$libdir"; then $echo "$modename: warning: \`$deplib' seems to be moved" 1>&2 fi path="-L$absdir" fi ;; *) continue ;; esac case " $deplibs " in *" $path "*) ;; *) deplibs="$deplibs $path" ;; esac done fi # link_all_deplibs != no fi # linkmode = lib done # for deplib in $libs if test $pass = dlpreopen; then # Link the dlpreopened libraries before other libraries for deplib in $save_deplibs; do deplibs="$deplib $deplibs" done fi if test $pass != dlopen; then test $pass != scan && dependency_libs="$newdependency_libs" if test $pass != conv; then # Make sure lib_search_path contains only unique directories. lib_search_path= for dir in $newlib_search_path; do case "$lib_search_path " in *" $dir "*) ;; *) lib_search_path="$lib_search_path $dir" ;; esac done newlib_search_path= fi if test "$linkmode,$pass" != "prog,link"; then vars="deplibs" else vars="compile_deplibs finalize_deplibs" fi for var in $vars dependency_libs; do # Add libraries to $var in reverse order eval tmp_libs=\"\$$var\" new_libs= for deplib in $tmp_libs; do case $deplib in -L*) new_libs="$deplib $new_libs" ;; *) case " $specialdeplibs " in *" $deplib "*) new_libs="$deplib $new_libs" ;; *) case " $new_libs " in *" $deplib "*) ;; *) new_libs="$deplib $new_libs" ;; esac ;; esac ;; esac done tmp_libs= for deplib in $new_libs; do case $deplib in -L*) case " $tmp_libs " in *" $deplib "*) ;; *) tmp_libs="$tmp_libs $deplib" ;; esac ;; *) tmp_libs="$tmp_libs $deplib" ;; esac done eval $var=\"$tmp_libs\" done # for var fi if test "$pass" = "conv" && { test "$linkmode" = "lib" || test "$linkmode" = "prog"; }; then libs="$deplibs" # reset libs deplibs= fi done # for pass if test $linkmode = prog; then dlfiles="$newdlfiles" dlprefiles="$newdlprefiles" fi case $linkmode in oldlib) if test -n "$dlfiles$dlprefiles" || test "$dlself" != no; then $echo "$modename: warning: \`-dlopen' is ignored for archives" 1>&2 fi if test -n "$rpath"; then $echo "$modename: warning: \`-rpath' is ignored for archives" 1>&2 fi if test -n "$xrpath"; then $echo "$modename: warning: \`-R' is ignored for archives" 1>&2 fi if test -n "$vinfo"; then $echo "$modename: warning: \`-version-info' is ignored for archives" 1>&2 fi if test -n "$release"; then $echo "$modename: warning: \`-release' is ignored for archives" 1>&2 fi if test -n "$export_symbols" || test -n "$export_symbols_regex"; then $echo "$modename: warning: \`-export-symbols' is ignored for archives" 1>&2 fi # Now set the variables for building old libraries. build_libtool_libs=no oldlibs="$output" objs="$objs$old_deplibs" ;; lib) # Make sure we only generate libraries of the form `libNAME.la'. case $outputname in lib*) name=`$echo "X$outputname" | $Xsed -e 's/\.la$//' -e 's/^lib//'` eval libname=\"$libname_spec\" ;; *) if test "$module" = no; then $echo "$modename: libtool library \`$output' must begin with \`lib'" 1>&2 $echo "$help" 1>&2 exit 1 fi if test "$need_lib_prefix" != no; then # Add the "lib" prefix for modules if required name=`$echo "X$outputname" | $Xsed -e 's/\.la$//'` eval libname=\"$libname_spec\" else libname=`$echo "X$outputname" | $Xsed -e 's/\.la$//'` fi ;; esac if test -n "$objs"; then if test "$deplibs_check_method" != pass_all; then $echo "$modename: cannot build libtool library \`$output' from non-libtool objects on this host:$objs" 2>&1 exit 1 else echo echo "*** Warning: Linking the shared library $output against the non-libtool" echo "*** objects $objs is not portable!" libobjs="$libobjs $objs" fi fi if test "$dlself" != no; then $echo "$modename: warning: \`-dlopen self' is ignored for libtool libraries" 1>&2 fi set dummy $rpath if test $# -gt 2; then $echo "$modename: warning: ignoring multiple \`-rpath's for a libtool library" 1>&2 fi install_libdir="$2" oldlibs= if test -z "$rpath"; then if test "$build_libtool_libs" = yes; then # Building a libtool convenience library. libext=al oldlibs="$output_objdir/$libname.$libext $oldlibs" build_libtool_libs=convenience build_old_libs=yes fi if test -n "$vinfo"; then $echo "$modename: warning: \`-version-info' is ignored for convenience libraries" 1>&2 fi if test -n "$release"; then $echo "$modename: warning: \`-release' is ignored for convenience libraries" 1>&2 fi else # Parse the version information argument. IFS="${IFS= }"; save_ifs="$IFS"; IFS=':' set dummy $vinfo 0 0 0 IFS="$save_ifs" if test -n "$8"; then $echo "$modename: too many parameters to \`-version-info'" 1>&2 $echo "$help" 1>&2 exit 1 fi current="$2" revision="$3" age="$4" # Check that each of the things are valid numbers. case $current in 0 | [1-9] | [1-9][0-9] | [1-9][0-9][0-9]) ;; *) $echo "$modename: CURRENT \`$current' is not a nonnegative integer" 1>&2 $echo "$modename: \`$vinfo' is not valid version information" 1>&2 exit 1 ;; esac case $revision in 0 | [1-9] | [1-9][0-9] | [1-9][0-9][0-9]) ;; *) $echo "$modename: REVISION \`$revision' is not a nonnegative integer" 1>&2 $echo "$modename: \`$vinfo' is not valid version information" 1>&2 exit 1 ;; esac case $age in 0 | [1-9] | [1-9][0-9] | [1-9][0-9][0-9]) ;; *) $echo "$modename: AGE \`$age' is not a nonnegative integer" 1>&2 $echo "$modename: \`$vinfo' is not valid version information" 1>&2 exit 1 ;; esac if test $age -gt $current; then $echo "$modename: AGE \`$age' is greater than the current interface number \`$current'" 1>&2 $echo "$modename: \`$vinfo' is not valid version information" 1>&2 exit 1 fi # Calculate the version variables. major= versuffix= verstring= case $version_type in none) ;; darwin) # Like Linux, but with the current version available in # verstring for coding it into the library header major=.`expr $current - $age` versuffix="$major.$age.$revision" # Darwin ld doesn't like 0 for these options... minor_current=`expr $current + 1` verstring="-compatibility_version $minor_current -current_version $minor_current.$revision" ;; freebsd-aout) major=".$current" versuffix=".$current.$revision"; ;; freebsd-elf) major=".$current" versuffix=".$current"; ;; irix) major=`expr $current - $age + 1` verstring="sgi$major.$revision" # Add in all the interfaces that we are compatible with. loop=$revision while test $loop != 0; do iface=`expr $revision - $loop` loop=`expr $loop - 1` verstring="sgi$major.$iface:$verstring" done # Before this point, $major must not contain `.'. major=.$major versuffix="$major.$revision" ;; linux) major=.`expr $current - $age` versuffix="$major.$age.$revision" ;; osf) major=`expr $current - $age` versuffix=".$current.$age.$revision" verstring="$current.$age.$revision" # Add in all the interfaces that we are compatible with. loop=$age while test $loop != 0; do iface=`expr $current - $loop` loop=`expr $loop - 1` verstring="$verstring:${iface}.0" done # Make executables depend on our current version. verstring="$verstring:${current}.0" ;; sunos) major=".$current" versuffix=".$current.$revision" ;; windows) # Use '-' rather than '.', since we only want one # extension on DOS 8.3 filesystems. major=`expr $current - $age` versuffix="-$major" ;; *) $echo "$modename: unknown library version type \`$version_type'" 1>&2 echo "Fatal configuration error. See the $PACKAGE docs for more information." 1>&2 exit 1 ;; esac # Clear the version info if we defaulted, and they specified a release. if test -z "$vinfo" && test -n "$release"; then major= verstring="0.0" if test "$need_version" = no; then versuffix= else versuffix=".0.0" fi fi # Remove version info from name if versioning should be avoided if test "$avoid_version" = yes && test "$need_version" = no; then major= versuffix= verstring="" fi # Check to see if the archive will have undefined symbols. if test "$allow_undefined" = yes; then if test "$allow_undefined_flag" = unsupported; then $echo "$modename: warning: undefined symbols not allowed in $host shared libraries" 1>&2 build_libtool_libs=no build_old_libs=yes fi else # Don't allow undefined symbols. allow_undefined_flag="$no_undefined_flag" fi fi if test "$mode" != relink; then # Remove our outputs. $show "${rm}r $output_objdir/$outputname $output_objdir/$libname.* $output_objdir/${libname}${release}.*" $run ${rm}r $output_objdir/$outputname $output_objdir/$libname.* $output_objdir/${libname}${release}.* fi # Now set the variables for building old libraries. if test "$build_old_libs" = yes && test "$build_libtool_libs" != convenience ; then oldlibs="$oldlibs $output_objdir/$libname.$libext" # Transform .lo files to .o files. oldobjs="$objs "`$echo "X$libobjs" | $SP2NL | $Xsed -e '/\.'${libext}'$/d' -e "$lo2o" | $NL2SP` fi # Eliminate all temporary directories. for path in $notinst_path; do lib_search_path=`echo "$lib_search_path " | sed -e 's% $path % %g'` deplibs=`echo "$deplibs " | sed -e 's% -L$path % %g'` dependency_libs=`echo "$dependency_libs " | sed -e 's% -L$path % %g'` done if test -n "$xrpath"; then # If the user specified any rpath flags, then add them. temp_xrpath= for libdir in $xrpath; do temp_xrpath="$temp_xrpath -R$libdir" case "$finalize_rpath " in *" $libdir "*) ;; *) finalize_rpath="$finalize_rpath $libdir" ;; esac done if test $hardcode_into_libs != yes || test $build_old_libs = yes; then dependency_libs="$temp_xrpath $dependency_libs" fi fi # Make sure dlfiles contains only unique files that won't be dlpreopened old_dlfiles="$dlfiles" dlfiles= for lib in $old_dlfiles; do case " $dlprefiles $dlfiles " in *" $lib "*) ;; *) dlfiles="$dlfiles $lib" ;; esac done # Make sure dlprefiles contains only unique files old_dlprefiles="$dlprefiles" dlprefiles= for lib in $old_dlprefiles; do case "$dlprefiles " in *" $lib "*) ;; *) dlprefiles="$dlprefiles $lib" ;; esac done if test "$build_libtool_libs" = yes; then if test -n "$rpath"; then case $host in *-*-cygwin* | *-*-mingw* | *-*-pw32* | *-*-os2* | *-*-beos*) # these systems don't actually have a c library (as such)! ;; *-*-rhapsody* | *-*-darwin1.[012]) # Rhapsody C library is in the System framework deplibs="$deplibs -framework System" ;; *-*-netbsd*) # Don't link with libc until the a.out ld.so is fixed. ;; *) # Add libc to deplibs on all other systems if necessary. if test $build_libtool_need_lc = "yes"; then deplibs="$deplibs -lc" fi ;; esac fi # Transform deplibs into only deplibs that can be linked in shared. name_save=$name libname_save=$libname release_save=$release versuffix_save=$versuffix major_save=$major # I'm not sure if I'm treating the release correctly. I think # release should show up in the -l (ie -lgmp5) so we don't want to # add it in twice. Is that correct? release="" versuffix="" major="" newdeplibs= droppeddeps=no case $deplibs_check_method in pass_all) # Don't check for shared/static. Everything works. # This might be a little naive. We might want to check # whether the library exists or not. But this is on # osf3 & osf4 and I'm not really sure... Just # implementing what was already the behaviour. newdeplibs=$deplibs ;; test_compile) # This code stresses the "libraries are programs" paradigm to its # limits. Maybe even breaks it. We compile a program, linking it # against the deplibs as a proxy for the library. Then we can check # whether they linked in statically or dynamically with ldd. $rm conftest.c cat > conftest.c </dev/null` for potent_lib in $potential_libs; do # Follow soft links. if ls -lLd "$potent_lib" 2>/dev/null \ | grep " -> " >/dev/null; then continue fi # The statement above tries to avoid entering an # endless loop below, in case of cyclic links. # We might still enter an endless loop, since a link # loop can be closed while we follow links, # but so what? potlib="$potent_lib" while test -h "$potlib" 2>/dev/null; do potliblink=`ls -ld $potlib | sed 's/.* -> //'` case $potliblink in [\\/]* | [A-Za-z]:[\\/]*) potlib="$potliblink";; *) potlib=`$echo "X$potlib" | $Xsed -e 's,[^/]*$,,'`"$potliblink";; esac done if eval $file_magic_cmd \"\$potlib\" 2>/dev/null \ | sed 10q \ | egrep "$file_magic_regex" > /dev/null; then newdeplibs="$newdeplibs $a_deplib" a_deplib="" break 2 fi done done if test -n "$a_deplib" ; then droppeddeps=yes echo echo "*** Warning: This library needs some functionality provided by $a_deplib." echo "*** I have the capability to make that library automatically link in when" echo "*** you link to this library. But I can only do this if you have a" echo "*** shared version of the library, which you do not appear to have." fi else # Add a -L argument. newdeplibs="$newdeplibs $a_deplib" fi done # Gone through all deplibs. ;; match_pattern*) set dummy $deplibs_check_method match_pattern_regex=`expr "$deplibs_check_method" : "$2 \(.*\)"` for a_deplib in $deplibs; do name="`expr $a_deplib : '-l\(.*\)'`" # If $name is empty we are operating on a -L argument. if test -n "$name" && test "$name" != "0"; then libname=`eval \\$echo \"$libname_spec\"` for i in $lib_search_path $sys_lib_search_path $shlib_search_path; do potential_libs=`ls $i/$libname[.-]* 2>/dev/null` for potent_lib in $potential_libs; do if eval echo \"$potent_lib\" 2>/dev/null \ | sed 10q \ | egrep "$match_pattern_regex" > /dev/null; then newdeplibs="$newdeplibs $a_deplib" a_deplib="" break 2 fi done done if test -n "$a_deplib" ; then droppeddeps=yes echo echo "*** Warning: This library needs some functionality provided by $a_deplib." echo "*** I have the capability to make that library automatically link in when" echo "*** you link to this library. But I can only do this if you have a" echo "*** shared version of the library, which you do not appear to have." fi else # Add a -L argument. newdeplibs="$newdeplibs $a_deplib" fi done # Gone through all deplibs. ;; none | unknown | *) newdeplibs="" if $echo "X $deplibs" | $Xsed -e 's/ -lc$//' \ -e 's/ -[LR][^ ]*//g' -e 's/[ ]//g' | grep . >/dev/null; then echo if test "X$deplibs_check_method" = "Xnone"; then echo "*** Warning: inter-library dependencies are not supported in this platform." else echo "*** Warning: inter-library dependencies are not known to be supported." fi echo "*** All declared inter-library dependencies are being dropped." droppeddeps=yes fi ;; esac versuffix=$versuffix_save major=$major_save release=$release_save libname=$libname_save name=$name_save case $host in *-*-rhapsody* | *-*-darwin1.[012]) # On Rhapsody replace the C library is the System framework newdeplibs=`$echo "X $newdeplibs" | $Xsed -e 's/ -lc / -framework System /'` ;; esac if test "$droppeddeps" = yes; then if test "$module" = yes; then echo echo "*** Warning: libtool could not satisfy all declared inter-library" echo "*** dependencies of module $libname. Therefore, libtool will create" echo "*** a static module, that should work as long as the dlopening" echo "*** application is linked with the -dlopen flag." if test -z "$global_symbol_pipe"; then echo echo "*** However, this would only work if libtool was able to extract symbol" echo "*** lists from a program, using \`nm' or equivalent, but libtool could" echo "*** not find such a program. So, this module is probably useless." echo "*** \`nm' from GNU binutils and a full rebuild may help." fi if test "$build_old_libs" = no; then oldlibs="$output_objdir/$libname.$libext" build_libtool_libs=module build_old_libs=yes else build_libtool_libs=no fi else echo "*** The inter-library dependencies that have been dropped here will be" echo "*** automatically added whenever a program is linked with this library" echo "*** or is declared to -dlopen it." if test $allow_undefined = no; then echo echo "*** Since this library must not contain undefined symbols," echo "*** because either the platform does not support them or" echo "*** it was explicitly requested with -no-undefined," echo "*** libtool will only create a static version of it." if test "$build_old_libs" = no; then oldlibs="$output_objdir/$libname.$libext" build_libtool_libs=module build_old_libs=yes else build_libtool_libs=no fi fi fi fi # Done checking deplibs! deplibs=$newdeplibs fi # All the library-specific variables (install_libdir is set above). library_names= old_library= dlname= # Test again, we may have decided not to build it any more if test "$build_libtool_libs" = yes; then if test $hardcode_into_libs = yes; then # Hardcode the library paths hardcode_libdirs= dep_rpath= rpath="$finalize_rpath" test "$mode" != relink && rpath="$compile_rpath$rpath" for libdir in $rpath; do if test -n "$hardcode_libdir_flag_spec"; then if test -n "$hardcode_libdir_separator"; then if test -z "$hardcode_libdirs"; then hardcode_libdirs="$libdir" else # Just accumulate the unique libdirs. case $hardcode_libdir_separator$hardcode_libdirs$hardcode_libdir_separator in *"$hardcode_libdir_separator$libdir$hardcode_libdir_separator"*) ;; *) hardcode_libdirs="$hardcode_libdirs$hardcode_libdir_separator$libdir" ;; esac fi else eval flag=\"$hardcode_libdir_flag_spec\" dep_rpath="$dep_rpath $flag" fi elif test -n "$runpath_var"; then case "$perm_rpath " in *" $libdir "*) ;; *) perm_rpath="$perm_rpath $libdir" ;; esac fi done # Substitute the hardcoded libdirs into the rpath. if test -n "$hardcode_libdir_separator" && test -n "$hardcode_libdirs"; then libdir="$hardcode_libdirs" eval dep_rpath=\"$hardcode_libdir_flag_spec\" fi if test -n "$runpath_var" && test -n "$perm_rpath"; then # We should set the runpath_var. rpath= for dir in $perm_rpath; do rpath="$rpath$dir:" done eval "$runpath_var='$rpath\$$runpath_var'; export $runpath_var" fi test -n "$dep_rpath" && deplibs="$dep_rpath $deplibs" fi shlibpath="$finalize_shlibpath" test "$mode" != relink && shlibpath="$compile_shlibpath$shlibpath" if test -n "$shlibpath"; then eval "$shlibpath_var='$shlibpath\$$shlibpath_var'; export $shlibpath_var" fi # Get the real and link names of the library. eval library_names=\"$library_names_spec\" set dummy $library_names realname="$2" shift; shift if test -n "$soname_spec"; then eval soname=\"$soname_spec\" else soname="$realname" fi test -z "$dlname" && dlname=$soname lib="$output_objdir/$realname" for link do linknames="$linknames $link" done # Ensure that we have .o objects for linkers which dislike .lo # (e.g. aix) in case we are running --disable-static for obj in $libobjs; do xdir=`$echo "X$obj" | $Xsed -e 's%/[^/]*$%%'` if test "X$xdir" = "X$obj"; then xdir="." else xdir="$xdir" fi baseobj=`$echo "X$obj" | $Xsed -e 's%^.*/%%'` oldobj=`$echo "X$baseobj" | $Xsed -e "$lo2o"` if test ! -f $xdir/$oldobj; then $show "(cd $xdir && ${LN_S} $baseobj $oldobj)" $run eval '(cd $xdir && ${LN_S} $baseobj $oldobj)' || exit $? fi done # Use standard objects if they are pic test -z "$pic_flag" && libobjs=`$echo "X$libobjs" | $SP2NL | $Xsed -e "$lo2o" | $NL2SP` # Prepare the list of exported symbols if test -z "$export_symbols"; then if test "$always_export_symbols" = yes || test -n "$export_symbols_regex"; then $show "generating symbol list for \`$libname.la'" export_symbols="$output_objdir/$libname.exp" $run $rm $export_symbols eval cmds=\"$export_symbols_cmds\" IFS="${IFS= }"; save_ifs="$IFS"; IFS='~' for cmd in $cmds; do IFS="$save_ifs" $show "$cmd" $run eval "$cmd" || exit $? done IFS="$save_ifs" if test -n "$export_symbols_regex"; then $show "egrep -e \"$export_symbols_regex\" \"$export_symbols\" > \"${export_symbols}T\"" $run eval 'egrep -e "$export_symbols_regex" "$export_symbols" > "${export_symbols}T"' $show "$mv \"${export_symbols}T\" \"$export_symbols\"" $run eval '$mv "${export_symbols}T" "$export_symbols"' fi fi fi if test -n "$export_symbols" && test -n "$include_expsyms"; then $run eval '$echo "X$include_expsyms" | $SP2NL >> "$export_symbols"' fi if test -n "$convenience"; then if test -n "$whole_archive_flag_spec"; then eval libobjs=\"\$libobjs $whole_archive_flag_spec\" else gentop="$output_objdir/${outputname}x" $show "${rm}r $gentop" $run ${rm}r "$gentop" $show "mkdir $gentop" $run mkdir "$gentop" status=$? if test $status -ne 0 && test ! -d "$gentop"; then exit $status fi generated="$generated $gentop" for xlib in $convenience; do # Extract the objects. case $xlib in [\\/]* | [A-Za-z]:[\\/]*) xabs="$xlib" ;; *) xabs=`pwd`"/$xlib" ;; esac xlib=`$echo "X$xlib" | $Xsed -e 's%^.*/%%'` xdir="$gentop/$xlib" $show "${rm}r $xdir" $run ${rm}r "$xdir" $show "mkdir $xdir" $run mkdir "$xdir" status=$? if test $status -ne 0 && test ! -d "$xdir"; then exit $status fi $show "(cd $xdir && $AR x $xabs)" $run eval "(cd \$xdir && $AR x \$xabs)" || exit $? libobjs="$libobjs "`find $xdir -name \*.o -print -o -name \*.lo -print | $NL2SP` done fi fi if test "$thread_safe" = yes && test -n "$thread_safe_flag_spec"; then eval flag=\"$thread_safe_flag_spec\" linker_flags="$linker_flags $flag" fi # Make a backup of the uninstalled library when relinking if test "$mode" = relink; then $run eval '(cd $output_objdir && $rm ${realname}U && $mv $realname ${realname}U)' || exit $? fi # Do each of the archive commands. if test -n "$export_symbols" && test -n "$archive_expsym_cmds"; then eval cmds=\"$archive_expsym_cmds\" else eval cmds=\"$archive_cmds\" fi IFS="${IFS= }"; save_ifs="$IFS"; IFS='~' for cmd in $cmds; do IFS="$save_ifs" $show "$cmd" $run eval "$cmd" || exit $? done IFS="$save_ifs" # Restore the uninstalled library and exit if test "$mode" = relink; then $run eval '(cd $output_objdir && $rm ${realname}T && $mv $realname ${realname}T && $mv "$realname"U $realname)' || exit $? exit 0 fi # Create links to the real library. for linkname in $linknames; do if test "$realname" != "$linkname"; then $show "(cd $output_objdir && $rm $linkname && $LN_S $realname $linkname)" $run eval '(cd $output_objdir && $rm $linkname && $LN_S $realname $linkname)' || exit $? fi done # If -module or -export-dynamic was specified, set the dlname. if test "$module" = yes || test "$export_dynamic" = yes; then # On all known operating systems, these are identical. dlname="$soname" fi fi ;; obj) if test -n "$deplibs"; then $echo "$modename: warning: \`-l' and \`-L' are ignored for objects" 1>&2 fi if test -n "$dlfiles$dlprefiles" || test "$dlself" != no; then $echo "$modename: warning: \`-dlopen' is ignored for objects" 1>&2 fi if test -n "$rpath"; then $echo "$modename: warning: \`-rpath' is ignored for objects" 1>&2 fi if test -n "$xrpath"; then $echo "$modename: warning: \`-R' is ignored for objects" 1>&2 fi if test -n "$vinfo"; then $echo "$modename: warning: \`-version-info' is ignored for objects" 1>&2 fi if test -n "$release"; then $echo "$modename: warning: \`-release' is ignored for objects" 1>&2 fi case $output in *.lo) if test -n "$objs$old_deplibs"; then $echo "$modename: cannot build library object \`$output' from non-libtool objects" 1>&2 exit 1 fi libobj="$output" obj=`$echo "X$output" | $Xsed -e "$lo2o"` ;; *) libobj= obj="$output" ;; esac # Delete the old objects. $run $rm $obj $libobj # Objects from convenience libraries. This assumes # single-version convenience libraries. Whenever we create # different ones for PIC/non-PIC, this we'll have to duplicate # the extraction. reload_conv_objs= gentop= # reload_cmds runs $LD directly, so let us get rid of # -Wl from whole_archive_flag_spec wl= if test -n "$convenience"; then if test -n "$whole_archive_flag_spec"; then eval reload_conv_objs=\"\$reload_objs $whole_archive_flag_spec\" else gentop="$output_objdir/${obj}x" $show "${rm}r $gentop" $run ${rm}r "$gentop" $show "mkdir $gentop" $run mkdir "$gentop" status=$? if test $status -ne 0 && test ! -d "$gentop"; then exit $status fi generated="$generated $gentop" for xlib in $convenience; do # Extract the objects. case $xlib in [\\/]* | [A-Za-z]:[\\/]*) xabs="$xlib" ;; *) xabs=`pwd`"/$xlib" ;; esac xlib=`$echo "X$xlib" | $Xsed -e 's%^.*/%%'` xdir="$gentop/$xlib" $show "${rm}r $xdir" $run ${rm}r "$xdir" $show "mkdir $xdir" $run mkdir "$xdir" status=$? if test $status -ne 0 && test ! -d "$xdir"; then exit $status fi $show "(cd $xdir && $AR x $xabs)" $run eval "(cd \$xdir && $AR x \$xabs)" || exit $? reload_conv_objs="$reload_objs "`find $xdir -name \*.o -print -o -name \*.lo -print | $NL2SP` done fi fi # Create the old-style object. reload_objs="$objs$old_deplibs "`$echo "X$libobjs" | $SP2NL | $Xsed -e '/\.'${libext}$'/d' -e '/\.lib$/d' -e "$lo2o" | $NL2SP`" $reload_conv_objs" ### testsuite: skip nested quoting test output="$obj" eval cmds=\"$reload_cmds\" IFS="${IFS= }"; save_ifs="$IFS"; IFS='~' for cmd in $cmds; do IFS="$save_ifs" $show "$cmd" $run eval "$cmd" || exit $? done IFS="$save_ifs" # Exit if we aren't doing a library object file. if test -z "$libobj"; then if test -n "$gentop"; then $show "${rm}r $gentop" $run ${rm}r $gentop fi exit 0 fi if test "$build_libtool_libs" != yes; then if test -n "$gentop"; then $show "${rm}r $gentop" $run ${rm}r $gentop fi # Create an invalid libtool object if no PIC, so that we don't # accidentally link it into a program. $show "echo timestamp > $libobj" $run eval "echo timestamp > $libobj" || exit $? exit 0 fi if test -n "$pic_flag" || test "$pic_mode" != default; then # Only do commands if we really have different PIC objects. reload_objs="$libobjs $reload_conv_objs" output="$libobj" eval cmds=\"$reload_cmds\" IFS="${IFS= }"; save_ifs="$IFS"; IFS='~' for cmd in $cmds; do IFS="$save_ifs" $show "$cmd" $run eval "$cmd" || exit $? done IFS="$save_ifs" else # Just create a symlink. $show $rm $libobj $run $rm $libobj xdir=`$echo "X$libobj" | $Xsed -e 's%/[^/]*$%%'` if test "X$xdir" = "X$libobj"; then xdir="." else xdir="$xdir" fi baseobj=`$echo "X$libobj" | $Xsed -e 's%^.*/%%'` oldobj=`$echo "X$baseobj" | $Xsed -e "$lo2o"` $show "(cd $xdir && $LN_S $oldobj $baseobj)" $run eval '(cd $xdir && $LN_S $oldobj $baseobj)' || exit $? fi if test -n "$gentop"; then $show "${rm}r $gentop" $run ${rm}r $gentop fi exit 0 ;; prog) case $host in *cygwin*) output=`echo $output | sed -e 's,.exe$,,;s,$,.exe,'` ;; esac if test -n "$vinfo"; then $echo "$modename: warning: \`-version-info' is ignored for programs" 1>&2 fi if test -n "$release"; then $echo "$modename: warning: \`-release' is ignored for programs" 1>&2 fi if test "$preload" = yes; then if test "$dlopen_support" = unknown && test "$dlopen_self" = unknown && test "$dlopen_self_static" = unknown; then $echo "$modename: warning: \`AC_LIBTOOL_DLOPEN' not used. Assuming no dlopen support." fi fi case $host in *-*-rhapsody* | *-*-darwin1.[012]) # On Rhapsody replace the C library is the System framework compile_deplibs=`$echo "X $compile_deplibs" | $Xsed -e 's/ -lc / -framework System /'` finalize_deplibs=`$echo "X $finalize_deplibs" | $Xsed -e 's/ -lc / -framework System /'` ;; esac compile_command="$compile_command $compile_deplibs" finalize_command="$finalize_command $finalize_deplibs" if test -n "$rpath$xrpath"; then # If the user specified any rpath flags, then add them. for libdir in $rpath $xrpath; do # This is the magic to use -rpath. case "$finalize_rpath " in *" $libdir "*) ;; *) finalize_rpath="$finalize_rpath $libdir" ;; esac done fi # Now hardcode the library paths rpath= hardcode_libdirs= for libdir in $compile_rpath $finalize_rpath; do if test -n "$hardcode_libdir_flag_spec"; then if test -n "$hardcode_libdir_separator"; then if test -z "$hardcode_libdirs"; then hardcode_libdirs="$libdir" else # Just accumulate the unique libdirs. case $hardcode_libdir_separator$hardcode_libdirs$hardcode_libdir_separator in *"$hardcode_libdir_separator$libdir$hardcode_libdir_separator"*) ;; *) hardcode_libdirs="$hardcode_libdirs$hardcode_libdir_separator$libdir" ;; esac fi else eval flag=\"$hardcode_libdir_flag_spec\" rpath="$rpath $flag" fi elif test -n "$runpath_var"; then case "$perm_rpath " in *" $libdir "*) ;; *) perm_rpath="$perm_rpath $libdir" ;; esac fi case $host in *-*-cygwin* | *-*-mingw* | *-*-pw32* | *-*-os2*) case :$dllsearchpath: in *":$libdir:"*) ;; *) dllsearchpath="$dllsearchpath:$libdir";; esac ;; esac done # Substitute the hardcoded libdirs into the rpath. if test -n "$hardcode_libdir_separator" && test -n "$hardcode_libdirs"; then libdir="$hardcode_libdirs" eval rpath=\" $hardcode_libdir_flag_spec\" fi compile_rpath="$rpath" rpath= hardcode_libdirs= for libdir in $finalize_rpath; do if test -n "$hardcode_libdir_flag_spec"; then if test -n "$hardcode_libdir_separator"; then if test -z "$hardcode_libdirs"; then hardcode_libdirs="$libdir" else # Just accumulate the unique libdirs. case $hardcode_libdir_separator$hardcode_libdirs$hardcode_libdir_separator in *"$hardcode_libdir_separator$libdir$hardcode_libdir_separator"*) ;; *) hardcode_libdirs="$hardcode_libdirs$hardcode_libdir_separator$libdir" ;; esac fi else eval flag=\"$hardcode_libdir_flag_spec\" rpath="$rpath $flag" fi elif test -n "$runpath_var"; then case "$finalize_perm_rpath " in *" $libdir "*) ;; *) finalize_perm_rpath="$finalize_perm_rpath $libdir" ;; esac fi done # Substitute the hardcoded libdirs into the rpath. if test -n "$hardcode_libdir_separator" && test -n "$hardcode_libdirs"; then libdir="$hardcode_libdirs" eval rpath=\" $hardcode_libdir_flag_spec\" fi finalize_rpath="$rpath" if test -n "$libobjs" && test "$build_old_libs" = yes; then # Transform all the library objects into standard objects. compile_command=`$echo "X$compile_command" | $SP2NL | $Xsed -e "$lo2o" | $NL2SP` finalize_command=`$echo "X$finalize_command" | $SP2NL | $Xsed -e "$lo2o" | $NL2SP` fi dlsyms= if test -n "$dlfiles$dlprefiles" || test "$dlself" != no; then if test -n "$NM" && test -n "$global_symbol_pipe"; then dlsyms="${outputname}S.c" else $echo "$modename: not configured to extract global symbols from dlpreopened files" 1>&2 fi fi if test -n "$dlsyms"; then case $dlsyms in "") ;; *.c) # Discover the nlist of each of the dlfiles. nlist="$output_objdir/${outputname}.nm" $show "$rm $nlist ${nlist}S ${nlist}T" $run $rm "$nlist" "${nlist}S" "${nlist}T" # Parse the name list into a source file. $show "creating $output_objdir/$dlsyms" test -z "$run" && $echo > "$output_objdir/$dlsyms" "\ /* $dlsyms - symbol resolution table for \`$outputname' dlsym emulation. */ /* Generated by $PROGRAM - GNU $PACKAGE $VERSION$TIMESTAMP */ #ifdef __cplusplus extern \"C\" { #endif /* Prevent the only kind of declaration conflicts we can make. */ #define lt_preloaded_symbols some_other_symbol /* External symbol declarations for the compiler. */\ " if test "$dlself" = yes; then $show "generating symbol list for \`$output'" test -z "$run" && $echo ': @PROGRAM@ ' > "$nlist" # Add our own program objects to the symbol list. progfiles=`$echo "X$objs$old_deplibs" | $SP2NL | $Xsed -e "$lo2o" | $NL2SP` for arg in $progfiles; do $show "extracting global C symbols from \`$arg'" $run eval "$NM $arg | $global_symbol_pipe >> '$nlist'" done if test -n "$exclude_expsyms"; then $run eval 'egrep -v " ($exclude_expsyms)$" "$nlist" > "$nlist"T' $run eval '$mv "$nlist"T "$nlist"' fi if test -n "$export_symbols_regex"; then $run eval 'egrep -e "$export_symbols_regex" "$nlist" > "$nlist"T' $run eval '$mv "$nlist"T "$nlist"' fi # Prepare the list of exported symbols if test -z "$export_symbols"; then export_symbols="$output_objdir/$output.exp" $run $rm $export_symbols $run eval "sed -n -e '/^: @PROGRAM@$/d' -e 's/^.* \(.*\)$/\1/p' "'< "$nlist" > "$export_symbols"' else $run eval "sed -e 's/\([][.*^$]\)/\\\1/g' -e 's/^/ /' -e 's/$/$/'"' < "$export_symbols" > "$output_objdir/$output.exp"' $run eval 'grep -f "$output_objdir/$output.exp" < "$nlist" > "$nlist"T' $run eval 'mv "$nlist"T "$nlist"' fi fi for arg in $dlprefiles; do $show "extracting global C symbols from \`$arg'" name=`echo "$arg" | sed -e 's%^.*/%%'` $run eval 'echo ": $name " >> "$nlist"' $run eval "$NM $arg | $global_symbol_pipe >> '$nlist'" done if test -z "$run"; then # Make sure we have at least an empty file. test -f "$nlist" || : > "$nlist" if test -n "$exclude_expsyms"; then egrep -v " ($exclude_expsyms)$" "$nlist" > "$nlist"T $mv "$nlist"T "$nlist" fi # Try sorting and uniquifying the output. if grep -v "^: " < "$nlist" | sort +2 | uniq > "$nlist"S; then : else grep -v "^: " < "$nlist" > "$nlist"S fi if test -f "$nlist"S; then eval "$global_symbol_to_cdecl"' < "$nlist"S >> "$output_objdir/$dlsyms"' else echo '/* NONE */' >> "$output_objdir/$dlsyms" fi $echo >> "$output_objdir/$dlsyms" "\ #undef lt_preloaded_symbols #if defined (__STDC__) && __STDC__ # define lt_ptr_t void * #else # define lt_ptr_t char * # define const #endif /* The mapping between symbol names and symbols. */ const struct { const char *name; lt_ptr_t address; } lt_preloaded_symbols[] = {\ " sed -n -e 's/^: \([^ ]*\) $/ {\"\1\", (lt_ptr_t) 0},/p' \ -e 's/^. \([^ ]*\) \([^ ]*\)$/ {"\2", (lt_ptr_t) \&\2},/p' \ < "$nlist" >> "$output_objdir/$dlsyms" $echo >> "$output_objdir/$dlsyms" "\ {0, (lt_ptr_t) 0} }; /* This works around a problem in FreeBSD linker */ #ifdef FREEBSD_WORKAROUND static const void *lt_preloaded_setup() { return lt_preloaded_symbols; } #endif #ifdef __cplusplus } #endif\ " fi pic_flag_for_symtable= case $host in # compiling the symbol table file with pic_flag works around # a FreeBSD bug that causes programs to crash when -lm is # linked before any other PIC object. But we must not use # pic_flag when linking with -static. The problem exists in # FreeBSD 2.2.6 and is fixed in FreeBSD 3.1. *-*-freebsd2*|*-*-freebsd3.0*|*-*-freebsdelf3.0*) case "$compile_command " in *" -static "*) ;; *) pic_flag_for_symtable=" $pic_flag -DPIC -DFREEBSD_WORKAROUND";; esac;; *-*-hpux*) case "$compile_command " in *" -static "*) ;; *) pic_flag_for_symtable=" $pic_flag -DPIC";; esac esac # Now compile the dynamic symbol file. $show "(cd $output_objdir && $CC -c$no_builtin_flag$pic_flag_for_symtable \"$dlsyms\")" $run eval '(cd $output_objdir && $CC -c$no_builtin_flag$pic_flag_for_symtable "$dlsyms")' || exit $? # Clean up the generated files. $show "$rm $output_objdir/$dlsyms $nlist ${nlist}S ${nlist}T" $run $rm "$output_objdir/$dlsyms" "$nlist" "${nlist}S" "${nlist}T" # Transform the symbol file into the correct name. compile_command=`$echo "X$compile_command" | $Xsed -e "s%@SYMFILE@%$output_objdir/${outputname}S.${objext}%"` finalize_command=`$echo "X$finalize_command" | $Xsed -e "s%@SYMFILE@%$output_objdir/${outputname}S.${objext}%"` ;; *) $echo "$modename: unknown suffix for \`$dlsyms'" 1>&2 exit 1 ;; esac else # We keep going just in case the user didn't refer to # lt_preloaded_symbols. The linker will fail if global_symbol_pipe # really was required. # Nullify the symbol file. compile_command=`$echo "X$compile_command" | $Xsed -e "s% @SYMFILE@%%"` finalize_command=`$echo "X$finalize_command" | $Xsed -e "s% @SYMFILE@%%"` fi if test $need_relink = no || test "$build_libtool_libs" != yes; then # Replace the output file specification. compile_command=`$echo "X$compile_command" | $Xsed -e 's%@OUTPUT@%'"$output"'%g'` link_command="$compile_command$compile_rpath" # We have no uninstalled library dependencies, so finalize right now. $show "$link_command" $run eval "$link_command" status=$? # Delete the generated files. if test -n "$dlsyms"; then $show "$rm $output_objdir/${outputname}S.${objext}" $run $rm "$output_objdir/${outputname}S.${objext}" fi exit $status fi if test -n "$shlibpath_var"; then # We should set the shlibpath_var rpath= for dir in $temp_rpath; do case $dir in [\\/]* | [A-Za-z]:[\\/]*) # Absolute path. rpath="$rpath$dir:" ;; *) # Relative path: add a thisdir entry. rpath="$rpath\$thisdir/$dir:" ;; esac done temp_rpath="$rpath" fi if test -n "$compile_shlibpath$finalize_shlibpath"; then compile_command="$shlibpath_var=\"$compile_shlibpath$finalize_shlibpath\$$shlibpath_var\" $compile_command" fi if test -n "$finalize_shlibpath"; then finalize_command="$shlibpath_var=\"$finalize_shlibpath\$$shlibpath_var\" $finalize_command" fi compile_var= finalize_var= if test -n "$runpath_var"; then if test -n "$perm_rpath"; then # We should set the runpath_var. rpath= for dir in $perm_rpath; do rpath="$rpath$dir:" done compile_var="$runpath_var=\"$rpath\$$runpath_var\" " fi if test -n "$finalize_perm_rpath"; then # We should set the runpath_var. rpath= for dir in $finalize_perm_rpath; do rpath="$rpath$dir:" done finalize_var="$runpath_var=\"$rpath\$$runpath_var\" " fi fi if test "$no_install" = yes; then # We don't need to create a wrapper script. link_command="$compile_var$compile_command$compile_rpath" # Replace the output file specification. link_command=`$echo "X$link_command" | $Xsed -e 's%@OUTPUT@%'"$output"'%g'` # Delete the old output file. $run $rm $output # Link the executable and exit $show "$link_command" $run eval "$link_command" || exit $? exit 0 fi if test "$hardcode_action" = relink; then # Fast installation is not supported link_command="$compile_var$compile_command$compile_rpath" relink_command="$finalize_var$finalize_command$finalize_rpath" $echo "$modename: warning: this platform does not like uninstalled shared libraries" 1>&2 $echo "$modename: \`$output' will be relinked during installation" 1>&2 else if test "$fast_install" != no; then link_command="$finalize_var$compile_command$finalize_rpath" if test "$fast_install" = yes; then relink_command=`$echo "X$compile_var$compile_command$compile_rpath" | $Xsed -e 's%@OUTPUT@%\$progdir/\$file%g'` else # fast_install is set to needless relink_command= fi else link_command="$compile_var$compile_command$compile_rpath" relink_command="$finalize_var$finalize_command$finalize_rpath" fi fi # Replace the output file specification. link_command=`$echo "X$link_command" | $Xsed -e 's%@OUTPUT@%'"$output_objdir/$outputname"'%g'` # Delete the old output files. $run $rm $output $output_objdir/$outputname $output_objdir/lt-$outputname $show "$link_command" $run eval "$link_command" || exit $? # Now create the wrapper script. $show "creating $output" # Quote the relink command for shipping. if test -n "$relink_command"; then # Preserve any variables that may affect compiler behavior for var in $variables_saved_for_relink; do if eval test -z \"\${$var+set}\"; then relink_command="{ test -z \"\${$var+set}\" || unset $var || { $var=; export $var; }; }; $relink_command" elif eval var_value=\$$var; test -z "$var_value"; then relink_command="$var=; export $var; $relink_command" else var_value=`$echo "X$var_value" | $Xsed -e "$sed_quote_subst"` relink_command="$var=\"$var_value\"; export $var; $relink_command" fi done relink_command="cd `pwd`; $relink_command" relink_command=`$echo "X$relink_command" | $Xsed -e "$sed_quote_subst"` fi # Quote $echo for shipping. if test "X$echo" = "X$SHELL $0 --fallback-echo"; then case $0 in [\\/]* | [A-Za-z]:[\\/]*) qecho="$SHELL $0 --fallback-echo";; *) qecho="$SHELL `pwd`/$0 --fallback-echo";; esac qecho=`$echo "X$qecho" | $Xsed -e "$sed_quote_subst"` else qecho=`$echo "X$echo" | $Xsed -e "$sed_quote_subst"` fi # Only actually do things if our run command is non-null. if test -z "$run"; then # win32 will think the script is a binary if it has # a .exe suffix, so we strip it off here. case $output in *.exe) output=`echo $output|sed 's,.exe$,,'` ;; esac # test for cygwin because mv fails w/o .exe extensions case $host in *cygwin*) exeext=.exe ;; *) exeext= ;; esac $rm $output trap "$rm $output; exit 1" 1 2 15 $echo > $output "\ #! $SHELL # $output - temporary wrapper script for $objdir/$outputname # Generated by $PROGRAM - GNU $PACKAGE $VERSION$TIMESTAMP # # The $output program cannot be directly executed until all the libtool # libraries that it depends on are installed. # # This wrapper script should never be moved out of the build directory. # If it is, it will not operate correctly. # Sed substitution that helps us do robust quoting. It backslashifies # metacharacters that are still active within double-quoted strings. Xsed='sed -e 1s/^X//' sed_quote_subst='$sed_quote_subst' # The HP-UX ksh and POSIX shell print the target directory to stdout # if CDPATH is set. if test \"\${CDPATH+set}\" = set; then CDPATH=:; export CDPATH; fi relink_command=\"$relink_command\" # This environment variable determines our operation mode. if test \"\$libtool_install_magic\" = \"$magic\"; then # install mode needs the following variable: notinst_deplibs='$notinst_deplibs' else # When we are sourced in execute mode, \$file and \$echo are already set. if test \"\$libtool_execute_magic\" != \"$magic\"; then echo=\"$qecho\" file=\"\$0\" # Make sure echo works. if test \"X\$1\" = X--no-reexec; then # Discard the --no-reexec flag, and continue. shift elif test \"X\`(\$echo '\t') 2>/dev/null\`\" = 'X\t'; then # Yippee, \$echo works! : else # Restart under the correct shell, and then maybe \$echo will work. exec $SHELL \"\$0\" --no-reexec \${1+\"\$@\"} fi fi\ " $echo >> $output "\ # Find the directory that this script lives in. thisdir=\`\$echo \"X\$file\" | \$Xsed -e 's%/[^/]*$%%'\` test \"x\$thisdir\" = \"x\$file\" && thisdir=. # Follow symbolic links until we get to the real thisdir. file=\`ls -ld \"\$file\" | sed -n 's/.*-> //p'\` while test -n \"\$file\"; do destdir=\`\$echo \"X\$file\" | \$Xsed -e 's%/[^/]*\$%%'\` # If there was a directory component, then change thisdir. if test \"x\$destdir\" != \"x\$file\"; then case \"\$destdir\" in [\\\\/]* | [A-Za-z]:[\\\\/]*) thisdir=\"\$destdir\" ;; *) thisdir=\"\$thisdir/\$destdir\" ;; esac fi file=\`\$echo \"X\$file\" | \$Xsed -e 's%^.*/%%'\` file=\`ls -ld \"\$thisdir/\$file\" | sed -n 's/.*-> //p'\` done # Try to get the absolute directory name. absdir=\`cd \"\$thisdir\" && pwd\` test -n \"\$absdir\" && thisdir=\"\$absdir\" " if test "$fast_install" = yes; then echo >> $output "\ program=lt-'$outputname'$exeext progdir=\"\$thisdir/$objdir\" if test ! -f \"\$progdir/\$program\" || \\ { file=\`ls -1dt \"\$progdir/\$program\" \"\$progdir/../\$program\" 2>/dev/null | sed 1q\`; \\ test \"X\$file\" != \"X\$progdir/\$program\"; }; then file=\"\$\$-\$program\" if test ! -d \"\$progdir\"; then $mkdir \"\$progdir\" else $rm \"\$progdir/\$file\" fi" echo >> $output "\ # relink executable if necessary if test -n \"\$relink_command\"; then if (eval \$relink_command); then : else $rm \"\$progdir/\$file\" exit 1 fi fi $mv \"\$progdir/\$file\" \"\$progdir/\$program\" 2>/dev/null || { $rm \"\$progdir/\$program\"; $mv \"\$progdir/\$file\" \"\$progdir/\$program\"; } $rm \"\$progdir/\$file\" fi" else echo >> $output "\ program='$outputname' progdir=\"\$thisdir/$objdir\" " fi echo >> $output "\ if test -f \"\$progdir/\$program\"; then" # Export our shlibpath_var if we have one. if test "$shlibpath_overrides_runpath" = yes && test -n "$shlibpath_var" && test -n "$temp_rpath"; then $echo >> $output "\ # Add our own library path to $shlibpath_var $shlibpath_var=\"$temp_rpath\$$shlibpath_var\" # Some systems cannot cope with colon-terminated $shlibpath_var # The second colon is a workaround for a bug in BeOS R4 sed $shlibpath_var=\`\$echo \"X\$$shlibpath_var\" | \$Xsed -e 's/::*\$//'\` export $shlibpath_var " fi # fixup the dll searchpath if we need to. if test -n "$dllsearchpath"; then $echo >> $output "\ # Add the dll search path components to the executable PATH PATH=$dllsearchpath:\$PATH " fi $echo >> $output "\ if test \"\$libtool_execute_magic\" != \"$magic\"; then # Run the actual program with our arguments. " case $host in # win32 systems need to use the prog path for dll # lookup to work *-*-cygwin* | *-*-pw32*) $echo >> $output "\ exec \$progdir/\$program \${1+\"\$@\"} " ;; # Backslashes separate directories on plain windows *-*-mingw | *-*-os2*) $echo >> $output "\ exec \$progdir\\\\\$program \${1+\"\$@\"} " ;; *) $echo >> $output "\ # Export the path to the program. PATH=\"\$progdir:\$PATH\" export PATH exec \$program \${1+\"\$@\"} " ;; esac $echo >> $output "\ \$echo \"\$0: cannot exec \$program \${1+\"\$@\"}\" exit 1 fi else # The program doesn't exist. \$echo \"\$0: error: \$progdir/\$program does not exist\" 1>&2 \$echo \"This script is just a wrapper for \$program.\" 1>&2 echo \"See the $PACKAGE documentation for more information.\" 1>&2 exit 1 fi fi\ " chmod +x $output fi exit 0 ;; esac # See if we need to build an old-fashioned archive. for oldlib in $oldlibs; do if test "$build_libtool_libs" = convenience; then oldobjs="$libobjs_save" addlibs="$convenience" build_libtool_libs=no else if test "$build_libtool_libs" = module; then oldobjs="$libobjs_save" build_libtool_libs=no else oldobjs="$objs$old_deplibs "`$echo "X$libobjs_save" | $SP2NL | $Xsed -e '/\.'${libext}'$/d' -e '/\.lib$/d' -e "$lo2o" | $NL2SP` fi addlibs="$old_convenience" fi if test -n "$addlibs"; then gentop="$output_objdir/${outputname}x" $show "${rm}r $gentop" $run ${rm}r "$gentop" $show "mkdir $gentop" $run mkdir "$gentop" status=$? if test $status -ne 0 && test ! -d "$gentop"; then exit $status fi generated="$generated $gentop" # Add in members from convenience archives. for xlib in $addlibs; do # Extract the objects. case $xlib in [\\/]* | [A-Za-z]:[\\/]*) xabs="$xlib" ;; *) xabs=`pwd`"/$xlib" ;; esac xlib=`$echo "X$xlib" | $Xsed -e 's%^.*/%%'` xdir="$gentop/$xlib" $show "${rm}r $xdir" $run ${rm}r "$xdir" $show "mkdir $xdir" $run mkdir "$xdir" status=$? if test $status -ne 0 && test ! -d "$xdir"; then exit $status fi $show "(cd $xdir && $AR x $xabs)" $run eval "(cd \$xdir && $AR x \$xabs)" || exit $? oldobjs="$oldobjs "`find $xdir -name \*.${objext} -print -o -name \*.lo -print | $NL2SP` done fi # Do each command in the archive commands. if test -n "$old_archive_from_new_cmds" && test "$build_libtool_libs" = yes; then eval cmds=\"$old_archive_from_new_cmds\" else # Ensure that we have .o objects in place in case we decided # not to build a shared library, and have fallen back to building # static libs even though --disable-static was passed! for oldobj in $oldobjs; do if test ! -f $oldobj; then xdir=`$echo "X$oldobj" | $Xsed -e 's%/[^/]*$%%'` if test "X$xdir" = "X$oldobj"; then xdir="." else xdir="$xdir" fi baseobj=`$echo "X$oldobj" | $Xsed -e 's%^.*/%%'` obj=`$echo "X$baseobj" | $Xsed -e "$o2lo"` $show "(cd $xdir && ${LN_S} $obj $baseobj)" $run eval '(cd $xdir && ${LN_S} $obj $baseobj)' || exit $? fi done eval cmds=\"$old_archive_cmds\" fi IFS="${IFS= }"; save_ifs="$IFS"; IFS='~' for cmd in $cmds; do IFS="$save_ifs" $show "$cmd" $run eval "$cmd" || exit $? done IFS="$save_ifs" done if test -n "$generated"; then $show "${rm}r$generated" $run ${rm}r$generated fi # Now create the libtool archive. case $output in *.la) old_library= test "$build_old_libs" = yes && old_library="$libname.$libext" $show "creating $output" # Preserve any variables that may affect compiler behavior for var in $variables_saved_for_relink; do if eval test -z \"\${$var+set}\"; then relink_command="{ test -z \"\${$var+set}\" || unset $var || { $var=; export $var; }; }; $relink_command" elif eval var_value=\$$var; test -z "$var_value"; then relink_command="$var=; export $var; $relink_command" else var_value=`$echo "X$var_value" | $Xsed -e "$sed_quote_subst"` relink_command="$var=\"$var_value\"; export $var; $relink_command" fi done # Quote the link command for shipping. relink_command="cd `pwd`; $SHELL $0 --mode=relink $libtool_args" relink_command=`$echo "X$relink_command" | $Xsed -e "$sed_quote_subst"` # Only create the output if not a dry run. if test -z "$run"; then for installed in no yes; do if test "$installed" = yes; then if test -z "$install_libdir"; then break fi output="$output_objdir/$outputname"i # Replace all uninstalled libtool libraries with the installed ones newdependency_libs= for deplib in $dependency_libs; do case $deplib in *.la) name=`$echo "X$deplib" | $Xsed -e 's%^.*/%%'` eval libdir=`sed -n -e 's/^libdir=\(.*\)$/\1/p' $deplib` if test -z "$libdir"; then $echo "$modename: \`$deplib' is not a valid libtool archive" 1>&2 exit 1 fi newdependency_libs="$newdependency_libs $libdir/$name" ;; *) newdependency_libs="$newdependency_libs $deplib" ;; esac done dependency_libs="$newdependency_libs" newdlfiles= for lib in $dlfiles; do name=`$echo "X$lib" | $Xsed -e 's%^.*/%%'` eval libdir=`sed -n -e 's/^libdir=\(.*\)$/\1/p' $lib` if test -z "$libdir"; then $echo "$modename: \`$lib' is not a valid libtool archive" 1>&2 exit 1 fi newdlfiles="$newdlfiles $libdir/$name" done dlfiles="$newdlfiles" newdlprefiles= for lib in $dlprefiles; do name=`$echo "X$lib" | $Xsed -e 's%^.*/%%'` eval libdir=`sed -n -e 's/^libdir=\(.*\)$/\1/p' $lib` if test -z "$libdir"; then $echo "$modename: \`$lib' is not a valid libtool archive" 1>&2 exit 1 fi newdlprefiles="$newdlprefiles $libdir/$name" done dlprefiles="$newdlprefiles" fi $rm $output # place dlname in correct position for cygwin tdlname=$dlname case $host,$output,$installed,$module,$dlname in *cygwin*,*lai,yes,no,*.dll) tdlname=../bin/$dlname ;; esac $echo > $output "\ # $outputname - a libtool library file # Generated by $PROGRAM - GNU $PACKAGE $VERSION$TIMESTAMP # # Please DO NOT delete this file! # It is necessary for linking the library. # The name that we can dlopen(3). dlname='$tdlname' # Names of this library. library_names='$library_names' # The name of the static archive. old_library='$old_library' # Libraries that this one depends upon. dependency_libs='$dependency_libs' # Version information for $libname. current=$current age=$age revision=$revision # Is this an already installed library? installed=$installed # Files to dlopen/dlpreopen dlopen='$dlfiles' dlpreopen='$dlprefiles' # Directory that this library needs to be installed in: libdir='$install_libdir'" if test "$installed" = no && test $need_relink = yes; then $echo >> $output "\ relink_command=\"$relink_command\"" fi done fi # Do a symbolic link so that the libtool archive can be found in # LD_LIBRARY_PATH before the program is installed. $show "(cd $output_objdir && $rm $outputname && $LN_S ../$outputname $outputname)" $run eval '(cd $output_objdir && $rm $outputname && $LN_S ../$outputname $outputname)' || exit $? ;; esac exit 0 ;; # libtool install mode install) modename="$modename: install" # There may be an optional sh(1) argument at the beginning of # install_prog (especially on Windows NT). if test "$nonopt" = "$SHELL" || test "$nonopt" = /bin/sh || # Allow the use of GNU shtool's install command. $echo "X$nonopt" | $Xsed | grep shtool > /dev/null; then # Aesthetically quote it. arg=`$echo "X$nonopt" | $Xsed -e "$sed_quote_subst"` case $arg in *[\[\~\#\^\&\*\(\)\{\}\|\;\<\>\?\'\ \ ]*|*]*) arg="\"$arg\"" ;; esac install_prog="$arg " arg="$1" shift else install_prog= arg="$nonopt" fi # The real first argument should be the name of the installation program. # Aesthetically quote it. arg=`$echo "X$arg" | $Xsed -e "$sed_quote_subst"` case $arg in *[\[\~\#\^\&\*\(\)\{\}\|\;\<\>\?\'\ \ ]*|*]*) arg="\"$arg\"" ;; esac install_prog="$install_prog$arg" # We need to accept at least all the BSD install flags. dest= files= opts= prev= install_type= isdir=no stripme= for arg do if test -n "$dest"; then files="$files $dest" dest="$arg" continue fi case $arg in -d) isdir=yes ;; -f) prev="-f" ;; -g) prev="-g" ;; -m) prev="-m" ;; -o) prev="-o" ;; -s) stripme=" -s" continue ;; -*) ;; *) # If the previous option needed an argument, then skip it. if test -n "$prev"; then prev= else dest="$arg" continue fi ;; esac # Aesthetically quote the argument. arg=`$echo "X$arg" | $Xsed -e "$sed_quote_subst"` case $arg in *[\[\~\#\^\&\*\(\)\{\}\|\;\<\>\?\'\ \ ]*|*]*) arg="\"$arg\"" ;; esac install_prog="$install_prog $arg" done if test -z "$install_prog"; then $echo "$modename: you must specify an install program" 1>&2 $echo "$help" 1>&2 exit 1 fi if test -n "$prev"; then $echo "$modename: the \`$prev' option requires an argument" 1>&2 $echo "$help" 1>&2 exit 1 fi if test -z "$files"; then if test -z "$dest"; then $echo "$modename: no file or destination specified" 1>&2 else $echo "$modename: you must specify a destination" 1>&2 fi $echo "$help" 1>&2 exit 1 fi # Strip any trailing slash from the destination. dest=`$echo "X$dest" | $Xsed -e 's%/$%%'` # Check to see that the destination is a directory. test -d "$dest" && isdir=yes if test "$isdir" = yes; then destdir="$dest" destname= else destdir=`$echo "X$dest" | $Xsed -e 's%/[^/]*$%%'` test "X$destdir" = "X$dest" && destdir=. destname=`$echo "X$dest" | $Xsed -e 's%^.*/%%'` # Not a directory, so check to see that there is only one file specified. set dummy $files if test $# -gt 2; then $echo "$modename: \`$dest' is not a directory" 1>&2 $echo "$help" 1>&2 exit 1 fi fi case $destdir in [\\/]* | [A-Za-z]:[\\/]*) ;; *) for file in $files; do case $file in *.lo) ;; *) $echo "$modename: \`$destdir' must be an absolute directory name" 1>&2 $echo "$help" 1>&2 exit 1 ;; esac done ;; esac # This variable tells wrapper scripts just to set variables rather # than running their programs. libtool_install_magic="$magic" staticlibs= future_libdirs= current_libdirs= for file in $files; do # Do each installation. case $file in *.$libext) # Do the static libraries later. staticlibs="$staticlibs $file" ;; *.la) # Check to see that this really is a libtool archive. if (sed -e '2q' $file | egrep "^# Generated by .*$PACKAGE") >/dev/null 2>&1; then : else $echo "$modename: \`$file' is not a valid libtool archive" 1>&2 $echo "$help" 1>&2 exit 1 fi library_names= old_library= relink_command= # If there is no directory component, then add one. case $file in */* | *\\*) . $file ;; *) . ./$file ;; esac # Add the libdir to current_libdirs if it is the destination. if test "X$destdir" = "X$libdir"; then case "$current_libdirs " in *" $libdir "*) ;; *) current_libdirs="$current_libdirs $libdir" ;; esac else # Note the libdir as a future libdir. case "$future_libdirs " in *" $libdir "*) ;; *) future_libdirs="$future_libdirs $libdir" ;; esac fi dir=`$echo "X$file" | $Xsed -e 's%/[^/]*$%%'`/ test "X$dir" = "X$file/" && dir= dir="$dir$objdir" if test -n "$relink_command"; then $echo "$modename: warning: relinking \`$file'" 1>&2 $show "$relink_command" if $run eval "$relink_command"; then : else $echo "$modename: error: relink \`$file' with the above command before installing it" 1>&2 continue fi fi # See the names of the shared library. set dummy $library_names if test -n "$2"; then realname="$2" shift shift srcname="$realname" test -n "$relink_command" && srcname="$realname"T # Install the shared library and build the symlinks. $show "$install_prog $dir/$srcname $destdir/$realname" $run eval "$install_prog $dir/$srcname $destdir/$realname" || exit $? if test -n "$stripme" && test -n "$striplib"; then $show "$striplib $destdir/$realname" $run eval "$striplib $destdir/$realname" || exit $? fi if test $# -gt 0; then # Delete the old symlinks, and create new ones. for linkname do if test "$linkname" != "$realname"; then $show "(cd $destdir && $rm $linkname && $LN_S $realname $linkname)" $run eval "(cd $destdir && $rm $linkname && $LN_S $realname $linkname)" fi done fi # Do each command in the postinstall commands. lib="$destdir/$realname" eval cmds=\"$postinstall_cmds\" IFS="${IFS= }"; save_ifs="$IFS"; IFS='~' for cmd in $cmds; do IFS="$save_ifs" $show "$cmd" $run eval "$cmd" || exit $? done IFS="$save_ifs" fi # Install the pseudo-library for information purposes. name=`$echo "X$file" | $Xsed -e 's%^.*/%%'` instname="$dir/$name"i $show "$install_prog $instname $destdir/$name" $run eval "$install_prog $instname $destdir/$name" || exit $? # Maybe install the static library, too. test -n "$old_library" && staticlibs="$staticlibs $dir/$old_library" ;; *.lo) # Install (i.e. copy) a libtool object. # Figure out destination file name, if it wasn't already specified. if test -n "$destname"; then destfile="$destdir/$destname" else destfile=`$echo "X$file" | $Xsed -e 's%^.*/%%'` destfile="$destdir/$destfile" fi # Deduce the name of the destination old-style object file. case $destfile in *.lo) staticdest=`$echo "X$destfile" | $Xsed -e "$lo2o"` ;; *.$objext) staticdest="$destfile" destfile= ;; *) $echo "$modename: cannot copy a libtool object to \`$destfile'" 1>&2 $echo "$help" 1>&2 exit 1 ;; esac # Install the libtool object if requested. if test -n "$destfile"; then $show "$install_prog $file $destfile" $run eval "$install_prog $file $destfile" || exit $? fi # Install the old object if enabled. if test "$build_old_libs" = yes; then # Deduce the name of the old-style object file. staticobj=`$echo "X$file" | $Xsed -e "$lo2o"` $show "$install_prog $staticobj $staticdest" $run eval "$install_prog \$staticobj \$staticdest" || exit $? fi exit 0 ;; *) # Figure out destination file name, if it wasn't already specified. if test -n "$destname"; then destfile="$destdir/$destname" else destfile=`$echo "X$file" | $Xsed -e 's%^.*/%%'` destfile="$destdir/$destfile" fi # Do a test to see if this is really a libtool program. if (sed -e '4q' $file | egrep "^# Generated by .*$PACKAGE") >/dev/null 2>&1; then notinst_deplibs= relink_command= # If there is no directory component, then add one. case $file in */* | *\\*) . $file ;; *) . ./$file ;; esac # Check the variables that should have been set. if test -z "$notinst_deplibs"; then $echo "$modename: invalid libtool wrapper script \`$file'" 1>&2 exit 1 fi finalize=yes for lib in $notinst_deplibs; do # Check to see that each library is installed. libdir= if test -f "$lib"; then # If there is no directory component, then add one. case $lib in */* | *\\*) . $lib ;; *) . ./$lib ;; esac fi libfile="$libdir/"`$echo "X$lib" | $Xsed -e 's%^.*/%%g'` ### testsuite: skip nested quoting test if test -n "$libdir" && test ! -f "$libfile"; then $echo "$modename: warning: \`$lib' has not been installed in \`$libdir'" 1>&2 finalize=no fi done relink_command= # If there is no directory component, then add one. case $file in */* | *\\*) . $file ;; *) . ./$file ;; esac outputname= if test "$fast_install" = no && test -n "$relink_command"; then if test "$finalize" = yes && test -z "$run"; then tmpdir="/tmp" test -n "$TMPDIR" && tmpdir="$TMPDIR" tmpdir="$tmpdir/libtool-$$" if $mkdir -p "$tmpdir" && chmod 700 "$tmpdir"; then : else $echo "$modename: error: cannot create temporary directory \`$tmpdir'" 1>&2 continue fi file=`$echo "X$file" | $Xsed -e 's%^.*/%%'` outputname="$tmpdir/$file" # Replace the output file specification. relink_command=`$echo "X$relink_command" | $Xsed -e 's%@OUTPUT@%'"$outputname"'%g'` $show "$relink_command" if $run eval "$relink_command"; then : else $echo "$modename: error: relink \`$file' with the above command before installing it" 1>&2 ${rm}r "$tmpdir" continue fi file="$outputname" else $echo "$modename: warning: cannot relink \`$file'" 1>&2 fi else # Install the binary that we compiled earlier. file=`$echo "X$file" | $Xsed -e "s%\([^/]*\)$%$objdir/\1%"` fi fi # remove .exe since cygwin /usr/bin/install will append another # one anyways case $install_prog,$host in /usr/bin/install*,*cygwin*) case $file:$destfile in *.exe:*.exe) # this is ok ;; *.exe:*) destfile=$destfile.exe ;; *:*.exe) destfile=`echo $destfile | sed -e 's,.exe$,,'` ;; esac ;; esac $show "$install_prog$stripme $file $destfile" $run eval "$install_prog\$stripme \$file \$destfile" || exit $? test -n "$outputname" && ${rm}r "$tmpdir" ;; esac done for file in $staticlibs; do name=`$echo "X$file" | $Xsed -e 's%^.*/%%'` # Set up the ranlib parameters. oldlib="$destdir/$name" $show "$install_prog $file $oldlib" $run eval "$install_prog \$file \$oldlib" || exit $? if test -n "$stripme" && test -n "$striplib"; then $show "$old_striplib $oldlib" $run eval "$old_striplib $oldlib" || exit $? fi # Do each command in the postinstall commands. eval cmds=\"$old_postinstall_cmds\" IFS="${IFS= }"; save_ifs="$IFS"; IFS='~' for cmd in $cmds; do IFS="$save_ifs" $show "$cmd" $run eval "$cmd" || exit $? done IFS="$save_ifs" done if test -n "$future_libdirs"; then $echo "$modename: warning: remember to run \`$progname --finish$future_libdirs'" 1>&2 fi if test -n "$current_libdirs"; then # Maybe just do a dry run. test -n "$run" && current_libdirs=" -n$current_libdirs" exec $SHELL $0 --finish$current_libdirs exit 1 fi exit 0 ;; # libtool finish mode finish) modename="$modename: finish" libdirs="$nonopt" admincmds= if test -n "$finish_cmds$finish_eval" && test -n "$libdirs"; then for dir do libdirs="$libdirs $dir" done for libdir in $libdirs; do if test -n "$finish_cmds"; then # Do each command in the finish commands. eval cmds=\"$finish_cmds\" IFS="${IFS= }"; save_ifs="$IFS"; IFS='~' for cmd in $cmds; do IFS="$save_ifs" $show "$cmd" $run eval "$cmd" || admincmds="$admincmds $cmd" done IFS="$save_ifs" fi if test -n "$finish_eval"; then # Do the single finish_eval. eval cmds=\"$finish_eval\" $run eval "$cmds" || admincmds="$admincmds $cmds" fi done fi # Exit here if they wanted silent mode. test "$show" = ":" && exit 0 echo "----------------------------------------------------------------------" echo "Libraries have been installed in:" for libdir in $libdirs; do echo " $libdir" done echo echo "If you ever happen to want to link against installed libraries" echo "in a given directory, LIBDIR, you must either use libtool, and" echo "specify the full pathname of the library, or use the \`-LLIBDIR'" echo "flag during linking and do at least one of the following:" if test -n "$shlibpath_var"; then echo " - add LIBDIR to the \`$shlibpath_var' environment variable" echo " during execution" fi if test -n "$runpath_var"; then echo " - add LIBDIR to the \`$runpath_var' environment variable" echo " during linking" fi if test -n "$hardcode_libdir_flag_spec"; then libdir=LIBDIR eval flag=\"$hardcode_libdir_flag_spec\" echo " - use the \`$flag' linker flag" fi if test -n "$admincmds"; then echo " - have your system administrator run these commands:$admincmds" fi if test -f /etc/ld.so.conf; then echo " - have your system administrator add LIBDIR to \`/etc/ld.so.conf'" fi echo echo "See any operating system documentation about shared libraries for" echo "more information, such as the ld(1) and ld.so(8) manual pages." echo "----------------------------------------------------------------------" exit 0 ;; # libtool execute mode execute) modename="$modename: execute" # The first argument is the command name. cmd="$nonopt" if test -z "$cmd"; then $echo "$modename: you must specify a COMMAND" 1>&2 $echo "$help" exit 1 fi # Handle -dlopen flags immediately. for file in $execute_dlfiles; do if test ! -f "$file"; then $echo "$modename: \`$file' is not a file" 1>&2 $echo "$help" 1>&2 exit 1 fi dir= case $file in *.la) # Check to see that this really is a libtool archive. if (sed -e '2q' $file | egrep "^# Generated by .*$PACKAGE") >/dev/null 2>&1; then : else $echo "$modename: \`$lib' is not a valid libtool archive" 1>&2 $echo "$help" 1>&2 exit 1 fi # Read the libtool library. dlname= library_names= # If there is no directory component, then add one. case $file in */* | *\\*) . $file ;; *) . ./$file ;; esac # Skip this library if it cannot be dlopened. if test -z "$dlname"; then # Warn if it was a shared library. test -n "$library_names" && $echo "$modename: warning: \`$file' was not linked with \`-export-dynamic'" continue fi dir=`$echo "X$file" | $Xsed -e 's%/[^/]*$%%'` test "X$dir" = "X$file" && dir=. if test -f "$dir/$objdir/$dlname"; then dir="$dir/$objdir" else $echo "$modename: cannot find \`$dlname' in \`$dir' or \`$dir/$objdir'" 1>&2 exit 1 fi ;; *.lo) # Just add the directory containing the .lo file. dir=`$echo "X$file" | $Xsed -e 's%/[^/]*$%%'` test "X$dir" = "X$file" && dir=. ;; *) $echo "$modename: warning \`-dlopen' is ignored for non-libtool libraries and objects" 1>&2 continue ;; esac # Get the absolute pathname. absdir=`cd "$dir" && pwd` test -n "$absdir" && dir="$absdir" # Now add the directory to shlibpath_var. if eval "test -z \"\$$shlibpath_var\""; then eval "$shlibpath_var=\"\$dir\"" else eval "$shlibpath_var=\"\$dir:\$$shlibpath_var\"" fi done # This variable tells wrapper scripts just to set shlibpath_var # rather than running their programs. libtool_execute_magic="$magic" # Check if any of the arguments is a wrapper script. args= for file do case $file in -*) ;; *) # Do a test to see if this is really a libtool program. if (sed -e '4q' $file | egrep "^# Generated by .*$PACKAGE") >/dev/null 2>&1; then # If there is no directory component, then add one. case $file in */* | *\\*) . $file ;; *) . ./$file ;; esac # Transform arg to wrapped name. file="$progdir/$program" fi ;; esac # Quote arguments (to preserve shell metacharacters). file=`$echo "X$file" | $Xsed -e "$sed_quote_subst"` args="$args \"$file\"" done if test -z "$run"; then if test -n "$shlibpath_var"; then # Export the shlibpath_var. eval "export $shlibpath_var" fi # Restore saved enviroment variables if test "${save_LC_ALL+set}" = set; then LC_ALL="$save_LC_ALL"; export LC_ALL fi if test "${save_LANG+set}" = set; then LANG="$save_LANG"; export LANG fi # Now actually exec the command. eval "exec \$cmd$args" $echo "$modename: cannot exec \$cmd$args" exit 1 else # Display what would be done. if test -n "$shlibpath_var"; then eval "\$echo \"\$shlibpath_var=\$$shlibpath_var\"" $echo "export $shlibpath_var" fi $echo "$cmd$args" exit 0 fi ;; # libtool clean and uninstall mode clean | uninstall) modename="$modename: $mode" rm="$nonopt" files= rmforce= exit_status=0 # This variable tells wrapper scripts just to set variables rather # than running their programs. libtool_install_magic="$magic" for arg do case $arg in -f) rm="$rm $arg"; rmforce=yes ;; -*) rm="$rm $arg" ;; *) files="$files $arg" ;; esac done if test -z "$rm"; then $echo "$modename: you must specify an RM program" 1>&2 $echo "$help" 1>&2 exit 1 fi rmdirs= for file in $files; do dir=`$echo "X$file" | $Xsed -e 's%/[^/]*$%%'` if test "X$dir" = "X$file"; then dir=. objdir="$objdir" else objdir="$dir/$objdir" fi name=`$echo "X$file" | $Xsed -e 's%^.*/%%'` test $mode = uninstall && objdir="$dir" # Remember objdir for removal later, being careful to avoid duplicates if test $mode = clean; then case " $rmdirs " in *" $objdir "*) ;; *) rmdirs="$rmdirs $objdir" ;; esac fi # Don't error if the file doesn't exist and rm -f was used. if (test -L "$file") >/dev/null 2>&1 \ || (test -h "$file") >/dev/null 2>&1 \ || test -f "$file"; then : elif test -d "$file"; then exit_status=1 continue elif test "$rmforce" = yes; then continue fi rmfiles="$file" case $name in *.la) # Possibly a libtool archive, so verify it. if (sed -e '2q' $file | egrep "^# Generated by .*$PACKAGE") >/dev/null 2>&1; then . $dir/$name # Delete the libtool libraries and symlinks. for n in $library_names; do rmfiles="$rmfiles $objdir/$n" done test -n "$old_library" && rmfiles="$rmfiles $objdir/$old_library" test $mode = clean && rmfiles="$rmfiles $objdir/$name $objdir/${name}i" if test $mode = uninstall; then if test -n "$library_names"; then # Do each command in the postuninstall commands. eval cmds=\"$postuninstall_cmds\" IFS="${IFS= }"; save_ifs="$IFS"; IFS='~' for cmd in $cmds; do IFS="$save_ifs" $show "$cmd" $run eval "$cmd" if test $? != 0 && test "$rmforce" != yes; then exit_status=1 fi done IFS="$save_ifs" fi if test -n "$old_library"; then # Do each command in the old_postuninstall commands. eval cmds=\"$old_postuninstall_cmds\" IFS="${IFS= }"; save_ifs="$IFS"; IFS='~' for cmd in $cmds; do IFS="$save_ifs" $show "$cmd" $run eval "$cmd" if test $? != 0 && test "$rmforce" != yes; then exit_status=1 fi done IFS="$save_ifs" fi # FIXME: should reinstall the best remaining shared library. fi fi ;; *.lo) if test "$build_old_libs" = yes; then oldobj=`$echo "X$name" | $Xsed -e "$lo2o"` rmfiles="$rmfiles $dir/$oldobj" fi ;; *) # Do a test to see if this is a libtool program. if test $mode = clean && (sed -e '4q' $file | egrep "^# Generated by .*$PACKAGE") >/dev/null 2>&1; then relink_command= . $dir/$file rmfiles="$rmfiles $objdir/$name $objdir/${name}S.${objext}" if test "$fast_install" = yes && test -n "$relink_command"; then rmfiles="$rmfiles $objdir/lt-$name" fi fi ;; esac $show "$rm $rmfiles" $run $rm $rmfiles || exit_status=1 done # Try to remove the ${objdir}s in the directories where we deleted files for dir in $rmdirs; do if test -d "$dir"; then $show "rmdir $dir" $run rmdir $dir >/dev/null 2>&1 fi done exit $exit_status ;; "") $echo "$modename: you must specify a MODE" 1>&2 $echo "$generic_help" 1>&2 exit 1 ;; esac $echo "$modename: invalid operation mode \`$mode'" 1>&2 $echo "$generic_help" 1>&2 exit 1 fi # test -z "$show_help" # We need to display help for each of the modes. case $mode in "") $echo \ "Usage: $modename [OPTION]... [MODE-ARG]... Provide generalized library-building support services. --config show all configuration variables --debug enable verbose shell tracing -n, --dry-run display commands without modifying any files --features display basic configuration information and exit --finish same as \`--mode=finish' --help display this help message and exit --mode=MODE use operation mode MODE [default=inferred from MODE-ARGS] --quiet same as \`--silent' --silent don't print informational messages --version print version information MODE must be one of the following: clean remove files from the build directory compile compile a source file into a libtool object execute automatically set library path, then run a program finish complete the installation of libtool libraries install install libraries or executables link create a library or an executable uninstall remove libraries from an installed directory MODE-ARGS vary depending on the MODE. Try \`$modename --help --mode=MODE' for a more detailed description of MODE." exit 0 ;; clean) $echo \ "Usage: $modename [OPTION]... --mode=clean RM [RM-OPTION]... FILE... Remove files from the build directory. RM is the name of the program to use to delete files associated with each FILE (typically \`/bin/rm'). RM-OPTIONS are options (such as \`-f') to be passed to RM. If FILE is a libtool library, object or program, all the files associated with it are deleted. Otherwise, only FILE itself is deleted using RM." ;; compile) $echo \ "Usage: $modename [OPTION]... --mode=compile COMPILE-COMMAND... SOURCEFILE Compile a source file into a libtool library object. This mode accepts the following additional options: -o OUTPUT-FILE set the output file name to OUTPUT-FILE -prefer-pic try to building PIC objects only -prefer-non-pic try to building non-PIC objects only -static always build a \`.o' file suitable for static linking COMPILE-COMMAND is a command to be used in creating a \`standard' object file from the given SOURCEFILE. The output file name is determined by removing the directory component from SOURCEFILE, then substituting the C source code suffix \`.c' with the library object suffix, \`.lo'." ;; execute) $echo \ "Usage: $modename [OPTION]... --mode=execute COMMAND [ARGS]... Automatically set library path, then run a program. This mode accepts the following additional options: -dlopen FILE add the directory containing FILE to the library path This mode sets the library path environment variable according to \`-dlopen' flags. If any of the ARGS are libtool executable wrappers, then they are translated into their corresponding uninstalled binary, and any of their required library directories are added to the library path. Then, COMMAND is executed, with ARGS as arguments." ;; finish) $echo \ "Usage: $modename [OPTION]... --mode=finish [LIBDIR]... Complete the installation of libtool libraries. Each LIBDIR is a directory that contains libtool libraries. The commands that this mode executes may require superuser privileges. Use the \`--dry-run' option if you just want to see what would be executed." ;; install) $echo \ "Usage: $modename [OPTION]... --mode=install INSTALL-COMMAND... Install executables or libraries. INSTALL-COMMAND is the installation command. The first component should be either the \`install' or \`cp' program. The rest of the components are interpreted as arguments to that command (only BSD-compatible install options are recognized)." ;; link) $echo \ "Usage: $modename [OPTION]... --mode=link LINK-COMMAND... Link object files or libraries together to form another library, or to create an executable program. LINK-COMMAND is a command using the C compiler that you would use to create a program from several object files. The following components of LINK-COMMAND are treated specially: -all-static do not do any dynamic linking at all -avoid-version do not add a version suffix if possible -dlopen FILE \`-dlpreopen' FILE if it cannot be dlopened at runtime -dlpreopen FILE link in FILE and add its symbols to lt_preloaded_symbols -export-dynamic allow symbols from OUTPUT-FILE to be resolved with dlsym(3) -export-symbols SYMFILE try to export only the symbols listed in SYMFILE -export-symbols-regex REGEX try to export only the symbols matching REGEX -LLIBDIR search LIBDIR for required installed libraries -lNAME OUTPUT-FILE requires the installed library libNAME -module build a library that can dlopened -no-fast-install disable the fast-install mode -no-install link a not-installable executable -no-undefined declare that a library does not refer to external symbols -o OUTPUT-FILE create OUTPUT-FILE from the specified objects -release RELEASE specify package release information -rpath LIBDIR the created library will eventually be installed in LIBDIR -R[ ]LIBDIR add LIBDIR to the runtime path of programs and libraries -static do not do any dynamic linking of libtool libraries -version-info CURRENT[:REVISION[:AGE]] specify library version info [each variable defaults to 0] All other options (arguments beginning with \`-') are ignored. Every other argument is treated as a filename. Files ending in \`.la' are treated as uninstalled libtool libraries, other files are standard or library object files. If the OUTPUT-FILE ends in \`.la', then a libtool library is created, only library objects (\`.lo' files) may be specified, and \`-rpath' is required, except when creating a convenience library. If OUTPUT-FILE ends in \`.a' or \`.lib', then a standard library is created using \`ar' and \`ranlib', or on Windows using \`lib'. If OUTPUT-FILE ends in \`.lo' or \`.${objext}', then a reloadable object file is created, otherwise an executable program is created." ;; uninstall) $echo \ "Usage: $modename [OPTION]... --mode=uninstall RM [RM-OPTION]... FILE... Remove libraries from an installation directory. RM is the name of the program to use to delete files associated with each FILE (typically \`/bin/rm'). RM-OPTIONS are options (such as \`-f') to be passed to RM. If FILE is a libtool library, all the files associated with it are deleted. Otherwise, only FILE itself is deleted using RM." ;; *) $echo "$modename: invalid operation mode \`$mode'" 1>&2 $echo "$help" 1>&2 exit 1 ;; esac echo $echo "Try \`$modename --help' for more information about other modes." exit 0 # Local Variables: # mode:shell-script # sh-indentation:2 # End: smalltalk-3.2.5/snprintfv/COPYING0000644000175000017500000004312212123404352013510 00000000000000 GNU GENERAL PUBLIC LICENSE Version 2, June 1991 Copyright (C) 1989, 1991 Free Software Foundation, Inc. 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA Everyone is permitted to copy and distribute verbatim copies of this license document, but changing it is not allowed. Preamble The licenses for most software are designed to take away your freedom to share and change it. By contrast, the GNU General Public License is intended to guarantee your freedom to share and change free software--to make sure the software is free for all its users. This General Public License applies to most of the Free Software Foundation's software and to any other program whose authors commit to using it. (Some other Free Software Foundation software is covered by the GNU Library General Public License instead.) You can apply it to your programs, too. When we speak of free software, we are referring to freedom, not price. Our General Public Licenses are designed to make sure that you have the freedom to distribute copies of free software (and charge for this service if you wish), that you receive source code or can get it if you want it, that you can change the software or use pieces of it in new free programs; and that you know you can do these things. To protect your rights, we need to make restrictions that forbid anyone to deny you these rights or to ask you to surrender the rights. These restrictions translate to certain responsibilities for you if you distribute copies of the software, or if you modify it. For example, if you distribute copies of such a program, whether gratis or for a fee, you must give the recipients all the rights that you have. You must make sure that they, too, receive or can get the source code. And you must show them these terms so they know their rights. We protect your rights with two steps: (1) copyright the software, and (2) offer you this license which gives you legal permission to copy, distribute and/or modify the software. Also, for each author's protection and ours, we want to make certain that everyone understands that there is no warranty for this free software. If the software is modified by someone else and passed on, we want its recipients to know that what they have is not the original, so that any problems introduced by others will not reflect on the original authors' reputations. Finally, any free program is threatened constantly by software patents. We wish to avoid the danger that redistributors of a free program will individually obtain patent licenses, in effect making the program proprietary. To prevent this, we have made it clear that any patent must be licensed for everyone's free use or not licensed at all. The precise terms and conditions for copying, distribution and modification follow. GNU GENERAL PUBLIC LICENSE TERMS AND CONDITIONS FOR COPYING, DISTRIBUTION AND MODIFICATION 0. This License applies to any program or other work which contains a notice placed by the copyright holder saying it may be distributed under the terms of this General Public License. The "Program", below, refers to any such program or work, and a "work based on the Program" means either the Program or any derivative work under copyright law: that is to say, a work containing the Program or a portion of it, either verbatim or with modifications and/or translated into another language. (Hereinafter, translation is included without limitation in the term "modification".) Each licensee is addressed as "you". Activities other than copying, distribution and modification are not covered by this License; they are outside its scope. The act of running the Program is not restricted, and the output from the Program is covered only if its contents constitute a work based on the Program (independent of having been made by running the Program). Whether that is true depends on what the Program does. 1. You may copy and distribute verbatim copies of the Program's source code as you receive it, in any medium, provided that you conspicuously and appropriately publish on each copy an appropriate copyright notice and disclaimer of warranty; keep intact all the notices that refer to this License and to the absence of any warranty; and give any other recipients of the Program a copy of this License along with the Program. You may charge a fee for the physical act of transferring a copy, and you may at your option offer warranty protection in exchange for a fee. 2. You may modify your copy or copies of the Program or any portion of it, thus forming a work based on the Program, and copy and distribute such modifications or work under the terms of Section 1 above, provided that you also meet all of these conditions: a) You must cause the modified files to carry prominent notices stating that you changed the files and the date of any change. b) You must cause any work that you distribute or publish, that in whole or in part contains or is derived from the Program or any part thereof, to be licensed as a whole at no charge to all third parties under the terms of this License. c) If the modified program normally reads commands interactively when run, you must cause it, when started running for such interactive use in the most ordinary way, to print or display an announcement including an appropriate copyright notice and a notice that there is no warranty (or else, saying that you provide a warranty) and that users may redistribute the program under these conditions, and telling the user how to view a copy of this License. (Exception: if the Program itself is interactive but does not normally print such an announcement, your work based on the Program is not required to print an announcement.) These requirements apply to the modified work as a whole. If identifiable sections of that work are not derived from the Program, and can be reasonably considered independent and separate works in themselves, then this License, and its terms, do not apply to those sections when you distribute them as separate works. But when you distribute the same sections as part of a whole which is a work based on the Program, the distribution of the whole must be on the terms of this License, whose permissions for other licensees extend to the entire whole, and thus to each and every part regardless of who wrote it. Thus, it is not the intent of this section to claim rights or contest your rights to work written entirely by you; rather, the intent is to exercise the right to control the distribution of derivative or collective works based on the Program. In addition, mere aggregation of another work not based on the Program with the Program (or with a work based on the Program) on a volume of a storage or distribution medium does not bring the other work under the scope of this License. 3. You may copy and distribute the Program (or a work based on it, under Section 2) in object code or executable form under the terms of Sections 1 and 2 above provided that you also do one of the following: a) Accompany it with the complete corresponding machine-readable source code, which must be distributed under the terms of Sections 1 and 2 above on a medium customarily used for software interchange; or, b) Accompany it with a written offer, valid for at least three years, to give any third party, for a charge no more than your cost of physically performing source distribution, a complete machine-readable copy of the corresponding source code, to be distributed under the terms of Sections 1 and 2 above on a medium customarily used for software interchange; or, c) Accompany it with the information you received as to the offer to distribute corresponding source code. (This alternative is allowed only for noncommercial distribution and only if you received the program in object code or executable form with such an offer, in accord with Subsection b above.) The source code for a work means the preferred form of the work for making modifications to it. For an executable work, complete source code means all the source code for all modules it contains, plus any associated interface definition files, plus the scripts used to control compilation and installation of the executable. However, as a special exception, the source code distributed need not include anything that is normally distributed (in either source or binary form) with the major components (compiler, kernel, and so on) of the operating system on which the executable runs, unless that component itself accompanies the executable. If distribution of executable or object code is made by offering access to copy from a designated place, then offering equivalent access to copy the source code from the same place counts as distribution of the source code, even though third parties are not compelled to copy the source along with the object code. 4. You may not copy, modify, sublicense, or distribute the Program except as expressly provided under this License. Any attempt otherwise to copy, modify, sublicense or distribute the Program is void, and will automatically terminate your rights under this License. However, parties who have received copies, or rights, from you under this License will not have their licenses terminated so long as such parties remain in full compliance. 5. You are not required to accept this License, since you have not signed it. However, nothing else grants you permission to modify or distribute the Program or its derivative works. These actions are prohibited by law if you do not accept this License. Therefore, by modifying or distributing the Program (or any work based on the Program), you indicate your acceptance of this License to do so, and all its terms and conditions for copying, distributing or modifying the Program or works based on it. 6. Each time you redistribute the Program (or any work based on the Program), the recipient automatically receives a license from the original licensor to copy, distribute or modify the Program subject to these terms and conditions. You may not impose any further restrictions on the recipients' exercise of the rights granted herein. You are not responsible for enforcing compliance by third parties to this License. 7. If, as a consequence of a court judgment or allegation of patent infringement or for any other reason (not limited to patent issues), conditions are imposed on you (whether by court order, agreement or otherwise) that contradict the conditions of this License, they do not excuse you from the conditions of this License. If you cannot distribute so as to satisfy simultaneously your obligations under this License and any other pertinent obligations, then as a consequence you may not distribute the Program at all. For example, if a patent license would not permit royalty-free redistribution of the Program by all those who receive copies directly or indirectly through you, then the only way you could satisfy both it and this License would be to refrain entirely from distribution of the Program. If any portion of this section is held invalid or unenforceable under any particular circumstance, the balance of the section is intended to apply and the section as a whole is intended to apply in other circumstances. It is not the purpose of this section to induce you to infringe any patents or other property right claims or to contest validity of any such claims; this section has the sole purpose of protecting the integrity of the free software distribution system, which is implemented by public license practices. Many people have made generous contributions to the wide range of software distributed through that system in reliance on consistent application of that system; it is up to the author/donor to decide if he or she is willing to distribute software through any other system and a licensee cannot impose that choice. This section is intended to make thoroughly clear what is believed to be a consequence of the rest of this License. 8. If the distribution and/or use of the Program is restricted in certain countries either by patents or by copyrighted interfaces, the original copyright holder who places the Program under this License may add an explicit geographical distribution limitation excluding those countries, so that distribution is permitted only in or among countries not thus excluded. In such case, this License incorporates the limitation as if written in the body of this License. 9. The Free Software Foundation may publish revised and/or new versions of the General Public License from time to time. Such new versions will be similar in spirit to the present version, but may differ in detail to address new problems or concerns. Each version is given a distinguishing version number. If the Program specifies a version number of this License which applies to it and "any later version", you have the option of following the terms and conditions either of that version or of any later version published by the Free Software Foundation. If the Program does not specify a version number of this License, you may choose any version ever published by the Free Software Foundation. 10. If you wish to incorporate parts of the Program into other free programs whose distribution conditions are different, write to the author to ask for permission. For software which is copyrighted by the Free Software Foundation, write to the Free Software Foundation; we sometimes make exceptions for this. Our decision will be guided by the two goals of preserving the free status of all derivatives of our free software and of promoting the sharing and reuse of software generally. NO WARRANTY 11. BECAUSE THE PROGRAM IS LICENSED FREE OF CHARGE, THERE IS NO WARRANTY FOR THE PROGRAM, TO THE EXTENT PERMITTED BY APPLICABLE LAW. EXCEPT WHEN OTHERWISE STATED IN WRITING THE COPYRIGHT HOLDERS AND/OR OTHER PARTIES PROVIDE THE PROGRAM "AS IS" WITHOUT WARRANTY OF ANY KIND, EITHER EXPRESSED OR IMPLIED, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE. THE ENTIRE RISK AS TO THE QUALITY AND PERFORMANCE OF THE PROGRAM IS WITH YOU. SHOULD THE PROGRAM PROVE DEFECTIVE, YOU ASSUME THE COST OF ALL NECESSARY SERVICING, REPAIR OR CORRECTION. 12. IN NO EVENT UNLESS REQUIRED BY APPLICABLE LAW OR AGREED TO IN WRITING WILL ANY COPYRIGHT HOLDER, OR ANY OTHER PARTY WHO MAY MODIFY AND/OR REDISTRIBUTE THE PROGRAM AS PERMITTED ABOVE, BE LIABLE TO YOU FOR DAMAGES, INCLUDING ANY GENERAL, SPECIAL, INCIDENTAL OR CONSEQUENTIAL DAMAGES ARISING OUT OF THE USE OR INABILITY TO USE THE PROGRAM (INCLUDING BUT NOT LIMITED TO LOSS OF DATA OR DATA BEING RENDERED INACCURATE OR LOSSES SUSTAINED BY YOU OR THIRD PARTIES OR A FAILURE OF THE PROGRAM TO OPERATE WITH ANY OTHER PROGRAMS), EVEN IF SUCH HOLDER OR OTHER PARTY HAS BEEN ADVISED OF THE POSSIBILITY OF SUCH DAMAGES. END OF TERMS AND CONDITIONS How to Apply These Terms to Your New Programs If you develop a new program, and you want it to be of the greatest possible use to the public, the best way to achieve this is to make it free software which everyone can redistribute and change under these terms. To do so, attach the following notices to the program. It is safest to attach them to the start of each source file to most effectively convey the exclusion of warranty; and each file should have at least the "copyright" line and a pointer to where the full notice is found. Copyright (C) This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2 of the License, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA Also add information on how to contact you by electronic and paper mail. If the program is interactive, make it output a short notice like this when it starts in an interactive mode: Gnomovision version 69, Copyright (C) year name of author Gnomovision comes with ABSOLUTELY NO WARRANTY; for details type `show w'. This is free software, and you are welcome to redistribute it under certain conditions; type `show c' for details. The hypothetical commands `show w' and `show c' should show the appropriate parts of the General Public License. Of course, the commands you use may be called something other than `show w' and `show c'; they could even be mouse-clicks or menu items--whatever suits your program. You should also get your employer (if you work as a programmer) or your school, if any, to sign a "copyright disclaimer" for the program, if necessary. Here is a sample; alter the names: Yoyodyne, Inc., hereby disclaims all copyright interest in the program `Gnomovision' (which makes passes at compilers) written by James Hacker. , 1 April 1989 Ty Coon, President of Vice This General Public License does not permit incorporating your program into proprietary programs. If your program is a subroutine library, you may consider it more useful to permit linking proprietary applications with the library. If this is what you want to do, use the GNU Library General Public License instead of this License. smalltalk-3.2.5/snprintfv/COPYING.DOC0000644000175000017500000004330212123404352014114 00000000000000 GNU Free Documentation License Version 1.1, March 2000 Copyright (C) 2000 Free Software Foundation, Inc. 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA Everyone is permitted to copy and distribute verbatim copies of this license document, but changing it is not allowed. 0. PREAMBLE The purpose of this License is to make a manual, textbook, or other written document "free" in the sense of freedom: to assure everyone the effective freedom to copy and redistribute it, with or without modifying it, either commercially or noncommercially. Secondarily, this License preserves for the author and publisher a way to get credit for their work, while not being considered responsible for modifications made by others. This License is a kind of "copyleft", which means that derivative works of the document must themselves be free in the same sense. It complements the GNU General Public License, which is a copyleft license designed for free software. We have designed this License in order to use it for manuals for free software, because free software needs free documentation: a free program should come with manuals providing the same freedoms that the software does. But this License is not limited to software manuals; it can be used for any textual work, regardless of subject matter or whether it is published as a printed book. We recommend this License principally for works whose purpose is instruction or reference. 1. APPLICABILITY AND DEFINITIONS This License applies to any manual or other work that contains a notice placed by the copyright holder saying it can be distributed under the terms of this License. The "Document", below, refers to any such manual or work. Any member of the public is a licensee, and is addressed as "you". A "Modified Version" of the Document means any work containing the Document or a portion of it, either copied verbatim, or with modifications and/or translated into another language. A "Secondary Section" is a named appendix or a front-matter section of the Document that deals exclusively with the relationship of the publishers or authors of the Document to the Document's overall subject (or to related matters) and contains nothing that could fall directly within that overall subject. (For example, if the Document is in part a textbook of mathematics, a Secondary Section may not explain any mathematics.) The relationship could be a matter of historical connection with the subject or with related matters, or of legal, commercial, philosophical, ethical or political position regarding them. The "Invariant Sections" are certain Secondary Sections whose titles are designated, as being those of Invariant Sections, in the notice that says that the Document is released under this License. The "Cover Texts" are certain short passages of text that are listed, as Front-Cover Texts or Back-Cover Texts, in the notice that says that the Document is released under this License. A "Transparent" copy of the Document means a machine-readable copy, represented in a format whose specification is available to the general public, whose contents can be viewed and edited directly and straightforwardly with generic text editors or (for images composed of pixels) generic paint programs or (for drawings) some widely available drawing editor, and that is suitable for input to text formatters or for automatic translation to a variety of formats suitable for input to text formatters. A copy made in an otherwise Transparent file format whose markup has been designed to thwart or discourage subsequent modification by readers is not Transparent. A copy that is not "Transparent" is called "Opaque". Examples of suitable formats for Transparent copies include plain ASCII without markup, Texinfo input format, LaTeX input format, SGML or XML using a publicly available DTD, and standard-conforming simple HTML designed for human modification. Opaque formats include PostScript, PDF, proprietary formats that can be read and edited only by proprietary word processors, SGML or XML for which the DTD and/or processing tools are not generally available, and the machine-generated HTML produced by some word processors for output purposes only. The "Title Page" means, for a printed book, the title page itself, plus such following pages as are needed to hold, legibly, the material this License requires to appear in the title page. For works in formats which do not have any title page as such, "Title Page" means the text near the most prominent appearance of the work's title, preceding the beginning of the body of the text. 2. VERBATIM COPYING You may copy and distribute the Document in any medium, either commercially or noncommercially, provided that this License, the copyright notices, and the license notice saying this License applies to the Document are reproduced in all copies, and that you add no other conditions whatsoever to those of this License. You may not use technical measures to obstruct or control the reading or further copying of the copies you make or distribute. However, you may accept compensation in exchange for copies. If you distribute a large enough number of copies you must also follow the conditions in section 3. You may also lend copies, under the same conditions stated above, and you may publicly display copies. 3. COPYING IN QUANTITY If you publish printed copies of the Document numbering more than 100, and the Document's license notice requires Cover Texts, you must enclose the copies in covers that carry, clearly and legibly, all these Cover Texts: Front-Cover Texts on the front cover, and Back-Cover Texts on the back cover. Both covers must also clearly and legibly identify you as the publisher of these copies. The front cover must present the full title with all words of the title equally prominent and visible. You may add other material on the covers in addition. Copying with changes limited to the covers, as long as they preserve the title of the Document and satisfy these conditions, can be treated as verbatim copying in other respects. If the required texts for either cover are too voluminous to fit legibly, you should put the first ones listed (as many as fit reasonably) on the actual cover, and continue the rest onto adjacent pages. If you publish or distribute Opaque copies of the Document numbering more than 100, you must either include a machine-readable Transparent copy along with each Opaque copy, or state in or with each Opaque copy a publicly-accessible computer-network location containing a complete Transparent copy of the Document, free of added material, which the general network-using public has access to download anonymously at no charge using public-standard network protocols. If you use the latter option, you must take reasonably prudent steps, when you begin distribution of Opaque copies in quantity, to ensure that this Transparent copy will remain thus accessible at the stated location until at least one year after the last time you distribute an Opaque copy (directly or through your agents or retailers) of that edition to the public. It is requested, but not required, that you contact the authors of the Document well before redistributing any large number of copies, to give them a chance to provide you with an updated version of the Document. 4. MODIFICATIONS You may copy and distribute a Modified Version of the Document under the conditions of sections 2 and 3 above, provided that you release the Modified Version under precisely this License, with the Modified Version filling the role of the Document, thus licensing distribution and modification of the Modified Version to whoever possesses a copy of it. In addition, you must do these things in the Modified Version: A. Use in the Title Page (and on the covers, if any) a title distinct from that of the Document, and from those of previous versions (which should, if there were any, be listed in the History section of the Document). You may use the same title as a previous version if the original publisher of that version gives permission. B. List on the Title Page, as authors, one or more persons or entities responsible for authorship of the modifications in the Modified Version, together with at least five of the principal authors of the Document (all of its principal authors, if it has less than five). C. State on the Title page the name of the publisher of the Modified Version, as the publisher. D. Preserve all the copyright notices of the Document. E. Add an appropriate copyright notice for your modifications adjacent to the other copyright notices. F. Include, immediately after the copyright notices, a license notice giving the public permission to use the Modified Version under the terms of this License, in the form shown in the Addendum below. G. Preserve in that license notice the full lists of Invariant Sections and required Cover Texts given in the Document's license notice. H. Include an unaltered copy of this License. I. Preserve the section entitled "History", and its title, and add to it an item stating at least the title, year, new authors, and publisher of the Modified Version as given on the Title Page. If there is no section entitled "History" in the Document, create one stating the title, year, authors, and publisher of the Document as given on its Title Page, then add an item describing the Modified Version as stated in the previous sentence. J. Preserve the network location, if any, given in the Document for public access to a Transparent copy of the Document, and likewise the network locations given in the Document for previous versions it was based on. These may be placed in the "History" section. You may omit a network location for a work that was published at least four years before the Document itself, or if the original publisher of the version it refers to gives permission. K. In any section entitled "Acknowledgements" or "Dedications", preserve the section's title, and preserve in the section all the substance and tone of each of the contributor acknowledgements and/or dedications given therein. L. Preserve all the Invariant Sections of the Document, unaltered in their text and in their titles. Section numbers or the equivalent are not considered part of the section titles. M. Delete any section entitled "Endorsements". Such a section may not be included in the Modified Version. N. Do not retitle any existing section as "Endorsements" or to conflict in title with any Invariant Section. If the Modified Version includes new front-matter sections or appendices that qualify as Secondary Sections and contain no material copied from the Document, you may at your option designate some or all of these sections as invariant. To do this, add their titles to the list of Invariant Sections in the Modified Version's license notice. These titles must be distinct from any other section titles. You may add a section entitled "Endorsements", provided it contains nothing but endorsements of your Modified Version by various parties--for example, statements of peer review or that the text has been approved by an organization as the authoritative definition of a standard. You may add a passage of up to five words as a Front-Cover Text, and a passage of up to 25 words as a Back-Cover Text, to the end of the list of Cover Texts in the Modified Version. Only one passage of Front-Cover Text and one of Back-Cover Text may be added by (or through arrangements made by) any one entity. If the Document already includes a cover text for the same cover, previously added by you or by arrangement made by the same entity you are acting on behalf of, you may not add another; but you may replace the old one, on explicit permission from the previous publisher that added the old one. The author(s) and publisher(s) of the Document do not by this License give permission to use their names for publicity for or to assert or imply endorsement of any Modified Version. 5. COMBINING DOCUMENTS You may combine the Document with other documents released under this License, under the terms defined in section 4 above for modified versions, provided that you include in the combination all of the Invariant Sections of all of the original documents, unmodified, and list them all as Invariant Sections of your combined work in its license notice. The combined work need only contain one copy of this License, and multiple identical Invariant Sections may be replaced with a single copy. If there are multiple Invariant Sections with the same name but different contents, make the title of each such section unique by adding at the end of it, in parentheses, the name of the original author or publisher of that section if known, or else a unique number. Make the same adjustment to the section titles in the list of Invariant Sections in the license notice of the combined work. In the combination, you must combine any sections entitled "History" in the various original documents, forming one section entitled "History"; likewise combine any sections entitled "Acknowledgements", and any sections entitled "Dedications". You must delete all sections entitled "Endorsements." 6. COLLECTIONS OF DOCUMENTS You may make a collection consisting of the Document and other documents released under this License, and replace the individual copies of this License in the various documents with a single copy that is included in the collection, provided that you follow the rules of this License for verbatim copying of each of the documents in all other respects. You may extract a single document from such a collection, and distribute it individually under this License, provided you insert a copy of this License into the extracted document, and follow this License in all other respects regarding verbatim copying of that document. 7. AGGREGATION WITH INDEPENDENT WORKS A compilation of the Document or its derivatives with other separate and independent documents or works, in or on a volume of a storage or distribution medium, does not as a whole count as a Modified Version of the Document, provided no compilation copyright is claimed for the compilation. Such a compilation is called an "aggregate", and this License does not apply to the other self-contained works thus compiled with the Document, on account of their being thus compiled, if they are not themselves derivative works of the Document. If the Cover Text requirement of section 3 is applicable to these copies of the Document, then if the Document is less than one quarter of the entire aggregate, the Document's Cover Texts may be placed on covers that surround only the Document within the aggregate. Otherwise they must appear on covers around the whole aggregate. 8. TRANSLATION Translation is considered a kind of modification, so you may distribute translations of the Document under the terms of section 4. Replacing Invariant Sections with translations requires special permission from their copyright holders, but you may include translations of some or all Invariant Sections in addition to the original versions of these Invariant Sections. You may include a translation of this License provided that you also include the original English version of this License. In case of a disagreement between the translation and the original English version of this License, the original English version will prevail. 9. TERMINATION You may not copy, modify, sublicense, or distribute the Document except as expressly provided for under this License. Any other attempt to copy, modify, sublicense or distribute the Document is void, and will automatically terminate your rights under this License. However, parties who have received copies, or rights, from you under this License will not have their licenses terminated so long as such parties remain in full compliance. 10. FUTURE REVISIONS OF THIS LICENSE The Free Software Foundation may publish new, revised versions of the GNU Free Documentation License from time to time. Such new versions will be similar in spirit to the present version, but may differ in detail to address new problems or concerns. See http://www.gnu.org/copyleft/. Each version of the License is given a distinguishing version number. If the Document specifies that a particular numbered version of this License "or any later version" applies to it, you have the option of following the terms and conditions either of that specified version or of any later version that has been published (not as a draft) by the Free Software Foundation. If the Document does not specify a version number of this License, you may choose any version ever published (not as a draft) by the Free Software Foundation. ADDENDUM: How to use this License for your documents To use this License in a document you have written, include a copy of the License in the document and put the following copyright and license notices just after the title page: Copyright (c) YEAR YOUR NAME. Permission is granted to copy, distribute and/or modify this document under the terms of the GNU Free Documentation License, Version 1.1 or any later version published by the Free Software Foundation; with the Invariant Sections being LIST THEIR TITLES, with the Front-Cover Texts being LIST, and with the Back-Cover Texts being LIST. A copy of the license is included in the section entitled "GNU Free Documentation License". If you have no Invariant Sections, write "with no Invariant Sections" instead of saying which ones are invariant. If you have no Front-Cover Texts, write "no Front-Cover Texts" instead of "Front-Cover Texts being LIST"; likewise for Back-Cover Texts. If your document contains nontrivial examples of program code, we recommend releasing these examples in parallel under your choice of free software license, such as the GNU General Public License, to permit their use in free software. smalltalk-3.2.5/snprintfv/Makefile.am0000644000175000017500000000271412123404352014513 00000000000000## -*- Mode: Makefile -*- ## --------------------------------------------------------------------- ## Makefile.am -- process this file with automake to produce Makefile.in ## Copyright (C) 1998, 1999, 2000, 2002 Gary V. Vaughan ## Originally by Gary V. Vaughan, 1998 ## This file is part of Snprintfv ## ## Snprintfv is free software; you can redistribute it and/or ## modify it under the terms of the GNU General Public License as ## published by the Free Software Foundation; either version 2 of the ## License, or (at your option) any later version. ## ## Snprintfv program is distributed in the hope that it will be useful, ## but WITHOUT ANY WARRANTY; without even the implied warranty of ## MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU ## General Public License for more details. ## ## You should have received a copy of the GNU General Public License ## along with this program. If not, write to the Free Software ## Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. ## ## As a special exception to the GNU General Public License, if you ## distribute this file as part of a program that also links with and ## uses the libopts library from AutoGen, you may include it under ## the same distribution terms used by the libopts library. ACLOCAL_AMFLAGS = -I ../build-aux AUTOMAKE_OPTIONS = gnits dist-hook: rm -rf $(distdir)/doc $(distdir)/tests SUBDIRS = snprintfv dist_noinst_SCRIPTS = gendoc.awk genproto commit smalltalk-3.2.5/snprintfv/Makefile.in0000644000175000017500000006107312130455536014537 00000000000000# Makefile.in generated by automake 1.11.6 from Makefile.am. # @configure_input@ # Copyright (C) 1994, 1995, 1996, 1997, 1998, 1999, 2000, 2001, 2002, # 2003, 2004, 2005, 2006, 2007, 2008, 2009, 2010, 2011 Free Software # Foundation, Inc. # This Makefile.in is free software; the Free Software Foundation # gives unlimited permission to copy and/or distribute it, # with or without modifications, as long as this notice is preserved. # This program is distributed in the hope that it will be useful, # but WITHOUT ANY WARRANTY, to the extent permitted by law; without # even the implied warranty of MERCHANTABILITY or FITNESS FOR A # PARTICULAR PURPOSE. @SET_MAKE@ VPATH = @srcdir@ am__make_dryrun = \ { \ am__dry=no; \ case $$MAKEFLAGS in \ *\\[\ \ ]*) \ echo 'am--echo: ; @echo "AM" OK' | $(MAKE) -f - 2>/dev/null \ | grep '^AM OK$$' >/dev/null || am__dry=yes;; \ *) \ for am__flg in $$MAKEFLAGS; do \ case $$am__flg in \ *=*|--*) ;; \ *n*) am__dry=yes; break;; \ esac; \ done;; \ esac; \ test $$am__dry = yes; \ } pkgdatadir = $(datadir)/@PACKAGE@ pkgincludedir = $(includedir)/@PACKAGE@ pkglibdir = $(libdir)/@PACKAGE@ pkglibexecdir = $(libexecdir)/@PACKAGE@ am__cd = CDPATH="$${ZSH_VERSION+.}$(PATH_SEPARATOR)" && cd install_sh_DATA = $(install_sh) -c -m 644 install_sh_PROGRAM = $(install_sh) -c install_sh_SCRIPT = $(install_sh) -c INSTALL_HEADER = $(INSTALL_DATA) transform = $(program_transform_name) NORMAL_INSTALL = : PRE_INSTALL = : POST_INSTALL = : NORMAL_UNINSTALL = : PRE_UNINSTALL = : POST_UNINSTALL = : build_triplet = @build@ host_triplet = @host@ subdir = . DIST_COMMON = README $(am__configure_deps) $(dist_noinst_SCRIPTS) \ $(srcdir)/../build-aux/config.guess \ $(srcdir)/../build-aux/config.sub \ $(srcdir)/../build-aux/install-sh \ $(srcdir)/../build-aux/ltmain.sh \ $(srcdir)/../build-aux/missing $(srcdir)/Makefile.am \ $(srcdir)/Makefile.in $(srcdir)/config.h.in \ $(top_srcdir)/configure ../build-aux/compile \ ../build-aux/config.guess ../build-aux/config.rpath \ ../build-aux/config.sub ../build-aux/depcomp \ ../build-aux/elisp-comp ../build-aux/install-sh \ ../build-aux/ltmain.sh ../build-aux/mdate-sh \ ../build-aux/missing ../build-aux/texinfo.tex \ ../build-aux/ylwrap AUTHORS COPYING COPYING.DOC ChangeLog \ INSTALL NEWS THANKS TODO ltmain.sh ACLOCAL_M4 = $(top_srcdir)/aclocal.m4 am__aclocal_m4_deps = $(top_srcdir)/../build-aux/libtool.m4 \ $(top_srcdir)/../build-aux/ltoptions.m4 \ $(top_srcdir)/../build-aux/ltsugar.m4 \ $(top_srcdir)/../build-aux/ltversion.m4 \ $(top_srcdir)/../build-aux/lt~obsolete.m4 \ $(top_srcdir)/configure.ac am__configure_deps = $(am__aclocal_m4_deps) $(CONFIGURE_DEPENDENCIES) \ $(ACLOCAL_M4) am__CONFIG_DISTCLEAN_FILES = config.status config.cache config.log \ configure.lineno config.status.lineno mkinstalldirs = $(install_sh) -d CONFIG_HEADER = config.h CONFIG_CLEAN_FILES = CONFIG_CLEAN_VPATH_FILES = SCRIPTS = $(dist_noinst_SCRIPTS) SOURCES = DIST_SOURCES = RECURSIVE_TARGETS = all-recursive check-recursive dvi-recursive \ html-recursive info-recursive install-data-recursive \ install-dvi-recursive install-exec-recursive \ install-html-recursive install-info-recursive \ install-pdf-recursive install-ps-recursive install-recursive \ installcheck-recursive installdirs-recursive pdf-recursive \ ps-recursive uninstall-recursive am__can_run_installinfo = \ case $$AM_UPDATE_INFO_DIR in \ n|no|NO) false;; \ *) (install-info --version) >/dev/null 2>&1;; \ esac RECURSIVE_CLEAN_TARGETS = mostlyclean-recursive clean-recursive \ distclean-recursive maintainer-clean-recursive AM_RECURSIVE_TARGETS = $(RECURSIVE_TARGETS:-recursive=) \ $(RECURSIVE_CLEAN_TARGETS:-recursive=) tags TAGS ctags CTAGS \ distdir dist dist-all distcheck ETAGS = etags CTAGS = ctags DIST_SUBDIRS = $(SUBDIRS) DISTFILES = $(DIST_COMMON) $(DIST_SOURCES) $(TEXINFOS) $(EXTRA_DIST) distdir = $(PACKAGE)-$(VERSION) top_distdir = $(distdir) am__remove_distdir = \ if test -d "$(distdir)"; then \ find "$(distdir)" -type d ! -perm -200 -exec chmod u+w {} ';' \ && rm -rf "$(distdir)" \ || { sleep 5 && rm -rf "$(distdir)"; }; \ else :; fi am__relativize = \ dir0=`pwd`; \ sed_first='s,^\([^/]*\)/.*$$,\1,'; \ sed_rest='s,^[^/]*/*,,'; \ sed_last='s,^.*/\([^/]*\)$$,\1,'; \ sed_butlast='s,/*[^/]*$$,,'; \ while test -n "$$dir1"; do \ first=`echo "$$dir1" | sed -e "$$sed_first"`; \ if test "$$first" != "."; then \ if test "$$first" = ".."; then \ dir2=`echo "$$dir0" | sed -e "$$sed_last"`/"$$dir2"; \ dir0=`echo "$$dir0" | sed -e "$$sed_butlast"`; \ else \ first2=`echo "$$dir2" | sed -e "$$sed_first"`; \ if test "$$first2" = "$$first"; then \ dir2=`echo "$$dir2" | sed -e "$$sed_rest"`; \ else \ dir2="../$$dir2"; \ fi; \ dir0="$$dir0"/"$$first"; \ fi; \ fi; \ dir1=`echo "$$dir1" | sed -e "$$sed_rest"`; \ done; \ reldir="$$dir2" DIST_ARCHIVES = $(distdir).tar.gz GZIP_ENV = --best distuninstallcheck_listfiles = find . -type f -print am__distuninstallcheck_listfiles = $(distuninstallcheck_listfiles) \ | sed 's|^\./|$(prefix)/|' | grep -v '$(infodir)/dir$$' distcleancheck_listfiles = find . -type f -print ACLOCAL = @ACLOCAL@ AMTAR = @AMTAR@ AR = @AR@ AS = @AS@ AUTOCONF = @AUTOCONF@ AUTOHEADER = @AUTOHEADER@ AUTOMAKE = @AUTOMAKE@ AWK = @AWK@ CC = @CC@ CCDEPMODE = @CCDEPMODE@ CFLAGS = @CFLAGS@ CPP = @CPP@ CPPFLAGS = @CPPFLAGS@ CYGPATH_W = @CYGPATH_W@ DEFS = @DEFS@ DEPDIR = @DEPDIR@ DLLTOOL = @DLLTOOL@ DSYMUTIL = @DSYMUTIL@ DUMPBIN = @DUMPBIN@ ECHO_C = @ECHO_C@ ECHO_N = @ECHO_N@ ECHO_T = @ECHO_T@ EGREP = @EGREP@ EXEEXT = @EXEEXT@ FGREP = @FGREP@ GREP = @GREP@ INCLUDES = @INCLUDES@ INSTALL = @INSTALL@ INSTALL_DATA = @INSTALL_DATA@ INSTALL_PROGRAM = @INSTALL_PROGRAM@ INSTALL_SCRIPT = @INSTALL_SCRIPT@ INSTALL_STRIP_PROGRAM = @INSTALL_STRIP_PROGRAM@ LD = @LD@ LDFLAGS = @LDFLAGS@ LIBOBJS = @LIBOBJS@ LIBS = @LIBS@ LIBSNPRINTFVC_PRINT_FLOATS = @LIBSNPRINTFVC_PRINT_FLOATS@ LIBTOOL = @LIBTOOL@ LIPO = @LIPO@ LN_S = @LN_S@ LTLIBOBJS = @LTLIBOBJS@ MAKEINFO = @MAKEINFO@ MANIFEST_TOOL = @MANIFEST_TOOL@ MKDIR_P = @MKDIR_P@ NM = @NM@ NMEDIT = @NMEDIT@ OBJDUMP = @OBJDUMP@ OBJEXT = @OBJEXT@ OTOOL = @OTOOL@ OTOOL64 = @OTOOL64@ PACKAGE = @PACKAGE@ PACKAGE_BUGREPORT = @PACKAGE_BUGREPORT@ PACKAGE_NAME = @PACKAGE_NAME@ PACKAGE_STRING = @PACKAGE_STRING@ PACKAGE_TARNAME = @PACKAGE_TARNAME@ PACKAGE_URL = @PACKAGE_URL@ PACKAGE_VERSION = @PACKAGE_VERSION@ PATH_SEPARATOR = @PATH_SEPARATOR@ RANLIB = @RANLIB@ SED = @SED@ SET_MAKE = @SET_MAKE@ SHELL = @SHELL@ SNV_AGE = @SNV_AGE@ SNV_CURRENT = @SNV_CURRENT@ SNV_REVISION = @SNV_REVISION@ STRIP = @STRIP@ VERSION = @VERSION@ abs_builddir = @abs_builddir@ abs_srcdir = @abs_srcdir@ abs_top_builddir = @abs_top_builddir@ abs_top_srcdir = @abs_top_srcdir@ ac_aux_dir = @ac_aux_dir@ ac_ct_AR = @ac_ct_AR@ ac_ct_CC = @ac_ct_CC@ ac_ct_DUMPBIN = @ac_ct_DUMPBIN@ am__include = @am__include@ am__leading_dot = @am__leading_dot@ am__quote = @am__quote@ am__tar = @am__tar@ am__untar = @am__untar@ bindir = @bindir@ build = @build@ build_alias = @build_alias@ build_cpu = @build_cpu@ build_os = @build_os@ build_vendor = @build_vendor@ builddir = @builddir@ convenience_libsnprintfv = @convenience_libsnprintfv@ datadir = @datadir@ datarootdir = @datarootdir@ docdir = @docdir@ dvidir = @dvidir@ exec_prefix = @exec_prefix@ host = @host@ host_alias = @host_alias@ host_cpu = @host_cpu@ host_os = @host_os@ host_vendor = @host_vendor@ htmldir = @htmldir@ includedir = @includedir@ infodir = @infodir@ install_sh = @install_sh@ installed_libsnprintfv = @installed_libsnprintfv@ libdir = @libdir@ libexecdir = @libexecdir@ localedir = @localedir@ localstatedir = @localstatedir@ mandir = @mandir@ mkdir_p = @mkdir_p@ oldincludedir = @oldincludedir@ pdfdir = @pdfdir@ prefix = @prefix@ program_transform_name = @program_transform_name@ psdir = @psdir@ sbindir = @sbindir@ sharedstatedir = @sharedstatedir@ srcdir = @srcdir@ sysconfdir = @sysconfdir@ target_alias = @target_alias@ top_build_prefix = @top_build_prefix@ top_builddir = @top_builddir@ top_srcdir = @top_srcdir@ ACLOCAL_AMFLAGS = -I ../build-aux AUTOMAKE_OPTIONS = gnits SUBDIRS = snprintfv dist_noinst_SCRIPTS = gendoc.awk genproto commit all: config.h $(MAKE) $(AM_MAKEFLAGS) all-recursive .SUFFIXES: am--refresh: Makefile @: $(srcdir)/Makefile.in: $(srcdir)/Makefile.am $(am__configure_deps) @for dep in $?; do \ case '$(am__configure_deps)' in \ *$$dep*) \ echo ' cd $(srcdir) && $(AUTOMAKE) --gnits'; \ $(am__cd) $(srcdir) && $(AUTOMAKE) --gnits \ && exit 0; \ exit 1;; \ esac; \ done; \ echo ' cd $(top_srcdir) && $(AUTOMAKE) --gnits Makefile'; \ $(am__cd) $(top_srcdir) && \ $(AUTOMAKE) --gnits Makefile .PRECIOUS: Makefile Makefile: $(srcdir)/Makefile.in $(top_builddir)/config.status @case '$?' in \ *config.status*) \ echo ' $(SHELL) ./config.status'; \ $(SHELL) ./config.status;; \ *) \ echo ' cd $(top_builddir) && $(SHELL) ./config.status $@ $(am__depfiles_maybe)'; \ cd $(top_builddir) && $(SHELL) ./config.status $@ $(am__depfiles_maybe);; \ esac; $(top_builddir)/config.status: $(top_srcdir)/configure $(CONFIG_STATUS_DEPENDENCIES) $(SHELL) ./config.status --recheck $(top_srcdir)/configure: $(am__configure_deps) $(am__cd) $(srcdir) && $(AUTOCONF) $(ACLOCAL_M4): $(am__aclocal_m4_deps) $(am__cd) $(srcdir) && $(ACLOCAL) $(ACLOCAL_AMFLAGS) $(am__aclocal_m4_deps): config.h: stamp-h1 @if test ! -f $@; then rm -f stamp-h1; else :; fi @if test ! -f $@; then $(MAKE) $(AM_MAKEFLAGS) stamp-h1; else :; fi stamp-h1: $(srcdir)/config.h.in $(top_builddir)/config.status @rm -f stamp-h1 cd $(top_builddir) && $(SHELL) ./config.status config.h $(srcdir)/config.h.in: $(am__configure_deps) ($(am__cd) $(top_srcdir) && $(AUTOHEADER)) rm -f stamp-h1 touch $@ distclean-hdr: -rm -f config.h stamp-h1 mostlyclean-libtool: -rm -f *.lo clean-libtool: -rm -rf .libs _libs distclean-libtool: -rm -f libtool config.lt # This directory's subdirectories are mostly independent; you can cd # into them and run `make' without going through this Makefile. # To change the values of `make' variables: instead of editing Makefiles, # (1) if the variable is set in `config.status', edit `config.status' # (which will cause the Makefiles to be regenerated when you run `make'); # (2) otherwise, pass the desired values on the `make' command line. $(RECURSIVE_TARGETS): @fail= failcom='exit 1'; \ for f in x $$MAKEFLAGS; do \ case $$f in \ *=* | --[!k]*);; \ *k*) failcom='fail=yes';; \ esac; \ done; \ dot_seen=no; \ target=`echo $@ | sed s/-recursive//`; \ list='$(SUBDIRS)'; for subdir in $$list; do \ echo "Making $$target in $$subdir"; \ if test "$$subdir" = "."; then \ dot_seen=yes; \ local_target="$$target-am"; \ else \ local_target="$$target"; \ fi; \ ($(am__cd) $$subdir && $(MAKE) $(AM_MAKEFLAGS) $$local_target) \ || eval $$failcom; \ done; \ if test "$$dot_seen" = "no"; then \ $(MAKE) $(AM_MAKEFLAGS) "$$target-am" || exit 1; \ fi; test -z "$$fail" $(RECURSIVE_CLEAN_TARGETS): @fail= failcom='exit 1'; \ for f in x $$MAKEFLAGS; do \ case $$f in \ *=* | --[!k]*);; \ *k*) failcom='fail=yes';; \ esac; \ done; \ dot_seen=no; \ case "$@" in \ distclean-* | maintainer-clean-*) list='$(DIST_SUBDIRS)' ;; \ *) list='$(SUBDIRS)' ;; \ esac; \ rev=''; for subdir in $$list; do \ if test "$$subdir" = "."; then :; else \ rev="$$subdir $$rev"; \ fi; \ done; \ rev="$$rev ."; \ target=`echo $@ | sed s/-recursive//`; \ for subdir in $$rev; do \ echo "Making $$target in $$subdir"; \ if test "$$subdir" = "."; then \ local_target="$$target-am"; \ else \ local_target="$$target"; \ fi; \ ($(am__cd) $$subdir && $(MAKE) $(AM_MAKEFLAGS) $$local_target) \ || eval $$failcom; \ done && test -z "$$fail" tags-recursive: list='$(SUBDIRS)'; for subdir in $$list; do \ test "$$subdir" = . || ($(am__cd) $$subdir && $(MAKE) $(AM_MAKEFLAGS) tags); \ done ctags-recursive: list='$(SUBDIRS)'; for subdir in $$list; do \ test "$$subdir" = . || ($(am__cd) $$subdir && $(MAKE) $(AM_MAKEFLAGS) ctags); \ done ID: $(HEADERS) $(SOURCES) $(LISP) $(TAGS_FILES) list='$(SOURCES) $(HEADERS) $(LISP) $(TAGS_FILES)'; \ unique=`for i in $$list; do \ if test -f "$$i"; then echo $$i; else echo $(srcdir)/$$i; fi; \ done | \ $(AWK) '{ files[$$0] = 1; nonempty = 1; } \ END { if (nonempty) { for (i in files) print i; }; }'`; \ mkid -fID $$unique tags: TAGS TAGS: tags-recursive $(HEADERS) $(SOURCES) config.h.in $(TAGS_DEPENDENCIES) \ $(TAGS_FILES) $(LISP) set x; \ here=`pwd`; \ if ($(ETAGS) --etags-include --version) >/dev/null 2>&1; then \ include_option=--etags-include; \ empty_fix=.; \ else \ include_option=--include; \ empty_fix=; \ fi; \ list='$(SUBDIRS)'; for subdir in $$list; do \ if test "$$subdir" = .; then :; else \ test ! -f $$subdir/TAGS || \ set "$$@" "$$include_option=$$here/$$subdir/TAGS"; \ fi; \ done; \ list='$(SOURCES) $(HEADERS) config.h.in $(LISP) $(TAGS_FILES)'; \ unique=`for i in $$list; do \ if test -f "$$i"; then echo $$i; else echo $(srcdir)/$$i; fi; \ done | \ $(AWK) '{ files[$$0] = 1; nonempty = 1; } \ END { if (nonempty) { for (i in files) print i; }; }'`; \ shift; \ if test -z "$(ETAGS_ARGS)$$*$$unique"; then :; else \ test -n "$$unique" || unique=$$empty_fix; \ if test $$# -gt 0; then \ $(ETAGS) $(ETAGSFLAGS) $(AM_ETAGSFLAGS) $(ETAGS_ARGS) \ "$$@" $$unique; \ else \ $(ETAGS) $(ETAGSFLAGS) $(AM_ETAGSFLAGS) $(ETAGS_ARGS) \ $$unique; \ fi; \ fi ctags: CTAGS CTAGS: ctags-recursive $(HEADERS) $(SOURCES) config.h.in $(TAGS_DEPENDENCIES) \ $(TAGS_FILES) $(LISP) list='$(SOURCES) $(HEADERS) config.h.in $(LISP) $(TAGS_FILES)'; \ unique=`for i in $$list; do \ if test -f "$$i"; then echo $$i; else echo $(srcdir)/$$i; fi; \ done | \ $(AWK) '{ files[$$0] = 1; nonempty = 1; } \ END { if (nonempty) { for (i in files) print i; }; }'`; \ test -z "$(CTAGS_ARGS)$$unique" \ || $(CTAGS) $(CTAGSFLAGS) $(AM_CTAGSFLAGS) $(CTAGS_ARGS) \ $$unique GTAGS: here=`$(am__cd) $(top_builddir) && pwd` \ && $(am__cd) $(top_srcdir) \ && gtags -i $(GTAGS_ARGS) "$$here" distclean-tags: -rm -f TAGS ID GTAGS GRTAGS GSYMS GPATH tags distdir: $(DISTFILES) @case `sed 15q $(srcdir)/NEWS` in \ *"$(VERSION)"*) : ;; \ *) \ echo "NEWS not updated; not releasing" 1>&2; \ exit 1;; \ esac $(am__remove_distdir) test -d "$(distdir)" || mkdir "$(distdir)" @srcdirstrip=`echo "$(srcdir)" | sed 's/[].[^$$\\*]/\\\\&/g'`; \ topsrcdirstrip=`echo "$(top_srcdir)" | sed 's/[].[^$$\\*]/\\\\&/g'`; \ list='$(DISTFILES)'; \ dist_files=`for file in $$list; do echo $$file; done | \ sed -e "s|^$$srcdirstrip/||;t" \ -e "s|^$$topsrcdirstrip/|$(top_builddir)/|;t"`; \ case $$dist_files in \ */*) $(MKDIR_P) `echo "$$dist_files" | \ sed '/\//!d;s|^|$(distdir)/|;s,/[^/]*$$,,' | \ sort -u` ;; \ esac; \ for file in $$dist_files; do \ if test -f $$file || test -d $$file; then d=.; else d=$(srcdir); fi; \ if test -d $$d/$$file; then \ dir=`echo "/$$file" | sed -e 's,/[^/]*$$,,'`; \ if test -d "$(distdir)/$$file"; then \ find "$(distdir)/$$file" -type d ! -perm -700 -exec chmod u+rwx {} \;; \ fi; \ if test -d $(srcdir)/$$file && test $$d != $(srcdir); then \ cp -fpR $(srcdir)/$$file "$(distdir)$$dir" || exit 1; \ find "$(distdir)/$$file" -type d ! -perm -700 -exec chmod u+rwx {} \;; \ fi; \ cp -fpR $$d/$$file "$(distdir)$$dir" || exit 1; \ else \ test -f "$(distdir)/$$file" \ || cp -p $$d/$$file "$(distdir)/$$file" \ || exit 1; \ fi; \ done @list='$(DIST_SUBDIRS)'; for subdir in $$list; do \ if test "$$subdir" = .; then :; else \ $(am__make_dryrun) \ || test -d "$(distdir)/$$subdir" \ || $(MKDIR_P) "$(distdir)/$$subdir" \ || exit 1; \ dir1=$$subdir; dir2="$(distdir)/$$subdir"; \ $(am__relativize); \ new_distdir=$$reldir; \ dir1=$$subdir; dir2="$(top_distdir)"; \ $(am__relativize); \ new_top_distdir=$$reldir; \ echo " (cd $$subdir && $(MAKE) $(AM_MAKEFLAGS) top_distdir="$$new_top_distdir" distdir="$$new_distdir" \\"; \ echo " am__remove_distdir=: am__skip_length_check=: am__skip_mode_fix=: distdir)"; \ ($(am__cd) $$subdir && \ $(MAKE) $(AM_MAKEFLAGS) \ top_distdir="$$new_top_distdir" \ distdir="$$new_distdir" \ am__remove_distdir=: \ am__skip_length_check=: \ am__skip_mode_fix=: \ distdir) \ || exit 1; \ fi; \ done $(MAKE) $(AM_MAKEFLAGS) \ top_distdir="$(top_distdir)" distdir="$(distdir)" \ dist-hook -test -n "$(am__skip_mode_fix)" \ || find "$(distdir)" -type d ! -perm -755 \ -exec chmod u+rwx,go+rx {} \; -o \ ! -type d ! -perm -444 -links 1 -exec chmod a+r {} \; -o \ ! -type d ! -perm -400 -exec chmod a+r {} \; -o \ ! -type d ! -perm -444 -exec $(install_sh) -c -m a+r {} {} \; \ || chmod -R a+r "$(distdir)" dist-gzip: distdir tardir=$(distdir) && $(am__tar) | GZIP=$(GZIP_ENV) gzip -c >$(distdir).tar.gz $(am__remove_distdir) dist-bzip2: distdir tardir=$(distdir) && $(am__tar) | BZIP2=$${BZIP2--9} bzip2 -c >$(distdir).tar.bz2 $(am__remove_distdir) dist-lzip: distdir tardir=$(distdir) && $(am__tar) | lzip -c $${LZIP_OPT--9} >$(distdir).tar.lz $(am__remove_distdir) dist-lzma: distdir tardir=$(distdir) && $(am__tar) | lzma -9 -c >$(distdir).tar.lzma $(am__remove_distdir) dist-xz: distdir tardir=$(distdir) && $(am__tar) | XZ_OPT=$${XZ_OPT--e} xz -c >$(distdir).tar.xz $(am__remove_distdir) dist-tarZ: distdir tardir=$(distdir) && $(am__tar) | compress -c >$(distdir).tar.Z $(am__remove_distdir) dist-shar: distdir shar $(distdir) | GZIP=$(GZIP_ENV) gzip -c >$(distdir).shar.gz $(am__remove_distdir) dist-zip: distdir -rm -f $(distdir).zip zip -rq $(distdir).zip $(distdir) $(am__remove_distdir) dist dist-all: distdir tardir=$(distdir) && $(am__tar) | GZIP=$(GZIP_ENV) gzip -c >$(distdir).tar.gz $(am__remove_distdir) # This target untars the dist file and tries a VPATH configuration. Then # it guarantees that the distribution is self-contained by making another # tarfile. distcheck: dist case '$(DIST_ARCHIVES)' in \ *.tar.gz*) \ GZIP=$(GZIP_ENV) gzip -dc $(distdir).tar.gz | $(am__untar) ;;\ *.tar.bz2*) \ bzip2 -dc $(distdir).tar.bz2 | $(am__untar) ;;\ *.tar.lzma*) \ lzma -dc $(distdir).tar.lzma | $(am__untar) ;;\ *.tar.lz*) \ lzip -dc $(distdir).tar.lz | $(am__untar) ;;\ *.tar.xz*) \ xz -dc $(distdir).tar.xz | $(am__untar) ;;\ *.tar.Z*) \ uncompress -c $(distdir).tar.Z | $(am__untar) ;;\ *.shar.gz*) \ GZIP=$(GZIP_ENV) gzip -dc $(distdir).shar.gz | unshar ;;\ *.zip*) \ unzip $(distdir).zip ;;\ esac chmod -R a-w $(distdir); chmod u+w $(distdir) mkdir $(distdir)/_build mkdir $(distdir)/_inst chmod a-w $(distdir) test -d $(distdir)/_build || exit 0; \ dc_install_base=`$(am__cd) $(distdir)/_inst && pwd | sed -e 's,^[^:\\/]:[\\/],/,'` \ && dc_destdir="$${TMPDIR-/tmp}/am-dc-$$$$/" \ && am__cwd=`pwd` \ && $(am__cd) $(distdir)/_build \ && ../configure --srcdir=.. --prefix="$$dc_install_base" \ $(AM_DISTCHECK_CONFIGURE_FLAGS) \ $(DISTCHECK_CONFIGURE_FLAGS) \ && $(MAKE) $(AM_MAKEFLAGS) \ && $(MAKE) $(AM_MAKEFLAGS) dvi \ && $(MAKE) $(AM_MAKEFLAGS) check \ && $(MAKE) $(AM_MAKEFLAGS) install \ && $(MAKE) $(AM_MAKEFLAGS) installcheck \ && $(MAKE) $(AM_MAKEFLAGS) uninstall \ && $(MAKE) $(AM_MAKEFLAGS) distuninstallcheck_dir="$$dc_install_base" \ distuninstallcheck \ && chmod -R a-w "$$dc_install_base" \ && ({ \ (cd ../.. && umask 077 && mkdir "$$dc_destdir") \ && $(MAKE) $(AM_MAKEFLAGS) DESTDIR="$$dc_destdir" install \ && $(MAKE) $(AM_MAKEFLAGS) DESTDIR="$$dc_destdir" uninstall \ && $(MAKE) $(AM_MAKEFLAGS) DESTDIR="$$dc_destdir" \ distuninstallcheck_dir="$$dc_destdir" distuninstallcheck; \ } || { rm -rf "$$dc_destdir"; exit 1; }) \ && rm -rf "$$dc_destdir" \ && $(MAKE) $(AM_MAKEFLAGS) dist \ && rm -rf $(DIST_ARCHIVES) \ && $(MAKE) $(AM_MAKEFLAGS) distcleancheck \ && cd "$$am__cwd" \ || exit 1 $(am__remove_distdir) @(echo "$(distdir) archives ready for distribution: "; \ list='$(DIST_ARCHIVES)'; for i in $$list; do echo $$i; done) | \ sed -e 1h -e 1s/./=/g -e 1p -e 1x -e '$$p' -e '$$x' distuninstallcheck: @test -n '$(distuninstallcheck_dir)' || { \ echo 'ERROR: trying to run $@ with an empty' \ '$$(distuninstallcheck_dir)' >&2; \ exit 1; \ }; \ $(am__cd) '$(distuninstallcheck_dir)' || { \ echo 'ERROR: cannot chdir into $(distuninstallcheck_dir)' >&2; \ exit 1; \ }; \ test `$(am__distuninstallcheck_listfiles) | wc -l` -eq 0 \ || { echo "ERROR: files left after uninstall:" ; \ if test -n "$(DESTDIR)"; then \ echo " (check DESTDIR support)"; \ fi ; \ $(distuninstallcheck_listfiles) ; \ exit 1; } >&2 distcleancheck: distclean @if test '$(srcdir)' = . ; then \ echo "ERROR: distcleancheck can only run from a VPATH build" ; \ exit 1 ; \ fi @test `$(distcleancheck_listfiles) | wc -l` -eq 0 \ || { echo "ERROR: files left in build directory after distclean:" ; \ $(distcleancheck_listfiles) ; \ exit 1; } >&2 check-am: all-am check: check-recursive all-am: Makefile $(SCRIPTS) config.h installdirs: installdirs-recursive installdirs-am: install: install-recursive install-exec: install-exec-recursive install-data: install-data-recursive uninstall: uninstall-recursive install-am: all-am @$(MAKE) $(AM_MAKEFLAGS) install-exec-am install-data-am installcheck: installcheck-recursive install-strip: if test -z '$(STRIP)'; then \ $(MAKE) $(AM_MAKEFLAGS) INSTALL_PROGRAM="$(INSTALL_STRIP_PROGRAM)" \ install_sh_PROGRAM="$(INSTALL_STRIP_PROGRAM)" INSTALL_STRIP_FLAG=-s \ install; \ else \ $(MAKE) $(AM_MAKEFLAGS) INSTALL_PROGRAM="$(INSTALL_STRIP_PROGRAM)" \ install_sh_PROGRAM="$(INSTALL_STRIP_PROGRAM)" INSTALL_STRIP_FLAG=-s \ "INSTALL_PROGRAM_ENV=STRIPPROG='$(STRIP)'" install; \ fi mostlyclean-generic: clean-generic: distclean-generic: -test -z "$(CONFIG_CLEAN_FILES)" || rm -f $(CONFIG_CLEAN_FILES) -test . = "$(srcdir)" || test -z "$(CONFIG_CLEAN_VPATH_FILES)" || rm -f $(CONFIG_CLEAN_VPATH_FILES) maintainer-clean-generic: @echo "This command is intended for maintainers to use" @echo "it deletes files that may require special tools to rebuild." clean: clean-recursive clean-am: clean-generic clean-libtool mostlyclean-am distclean: distclean-recursive -rm -f $(am__CONFIG_DISTCLEAN_FILES) -rm -f Makefile distclean-am: clean-am distclean-generic distclean-hdr \ distclean-libtool distclean-tags dvi: dvi-recursive dvi-am: html: html-recursive html-am: info: info-recursive info-am: install-data-am: install-dvi: install-dvi-recursive install-dvi-am: install-exec-am: install-html: install-html-recursive install-html-am: install-info: install-info-recursive install-info-am: install-man: install-pdf: install-pdf-recursive install-pdf-am: install-ps: install-ps-recursive install-ps-am: installcheck-am: maintainer-clean: maintainer-clean-recursive -rm -f $(am__CONFIG_DISTCLEAN_FILES) -rm -rf $(top_srcdir)/autom4te.cache -rm -f Makefile maintainer-clean-am: distclean-am maintainer-clean-generic mostlyclean: mostlyclean-recursive mostlyclean-am: mostlyclean-generic mostlyclean-libtool pdf: pdf-recursive pdf-am: ps: ps-recursive ps-am: uninstall-am: .MAKE: $(RECURSIVE_CLEAN_TARGETS) $(RECURSIVE_TARGETS) all \ ctags-recursive install-am install-strip tags-recursive .PHONY: $(RECURSIVE_CLEAN_TARGETS) $(RECURSIVE_TARGETS) CTAGS GTAGS \ all all-am am--refresh check check-am clean clean-generic \ clean-libtool ctags ctags-recursive dist dist-all dist-bzip2 \ dist-gzip dist-hook dist-lzip dist-lzma dist-shar dist-tarZ \ dist-xz dist-zip distcheck distclean distclean-generic \ distclean-hdr distclean-libtool distclean-tags distcleancheck \ distdir distuninstallcheck dvi dvi-am html html-am info \ info-am install install-am install-data install-data-am \ install-dvi install-dvi-am install-exec install-exec-am \ install-html install-html-am install-info install-info-am \ install-man install-pdf install-pdf-am install-ps \ install-ps-am install-strip installcheck installcheck-am \ installdirs installdirs-am maintainer-clean \ maintainer-clean-generic mostlyclean mostlyclean-generic \ mostlyclean-libtool pdf pdf-am ps ps-am tags tags-recursive \ uninstall uninstall-am dist-hook: rm -rf $(distdir)/doc $(distdir)/tests # Tell versions [3.59,3.63) of GNU make to not export all variables. # Otherwise a system limit (for SysV at least) may be exceeded. .NOEXPORT: smalltalk-3.2.5/snprintfv/configure.ac0000644000175000017500000002666212130343734014761 00000000000000dnl -*- Mode: M4 -*- dnl configure.in --- GNU autoconf source for toplevel directory. dnl Copyright (C) 1998, 1999, 2000, 2009 Gary V. Vaughan dnl Originally by Gary V. Vaughan , 1998 dnl This file is part of Snprintfv. dnl dnl Snprintfv is free software; you can redistribute it and/or dnl modify it under the terms of the GNU General Public License as dnl published by the Free Software Foundation; either version 2 of the dnl License, or (at your option) any later version. dnl dnl Snprintfv is distributed in the hope that it will be useful, dnl but WITHOUT ANY WARRANTY; without even the implied warranty of dnl MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU dnl General Public License for more details. dnl dnl You should have received a copy of the GNU General Public License dnl along with this program; if not, write to the Free Software dnl Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. dnl dnl As a special exception to the GNU General Public License, if you dnl distribute this file as part of a program that also links with and dnl uses the libopts library from AutoGen, you may include it under dnl the same distribution terms used by the libopts library. dnl Code: AC_PREREQ(2.60) AC_INIT(snprintfv, 1.1, bonzini@gnu.org) AC_CONFIG_SRCDIR(snprintfv/printf.h) AC_CONFIG_HEADERS(config.h) AC_CONFIG_AUX_DIR(../build-aux) AC_CONFIG_MACRO_DIR(../build-aux) AC_ARG_ENABLE(subdir, [ --enable-subdir used in a package, texinfo+testsuite stripped], , [enable_subdir=no]) AM_INIT_AUTOMAKE SNV_CURRENT=3; AC_SUBST(SNV_CURRENT) SNV_REVISION=0; AC_SUBST(SNV_REVISION) SNV_AGE=0; AC_SUBST(SNV_AGE) AC_LIBTOOL_WIN32_DLL AC_PROG_LIBTOOL AC_PROG_SED # ---------------------------------------------------------------------- # If `configure' is invoked (in)directly via `make', ensure that it # encounters no `make' conflicts. Ignore error if shell does not have # unset, but at least set these to empty values. # ---------------------------------------------------------------------- MFLAGS= MAKEFLAGS= MAKELEVEL= unset MFLAGS MAKEFLAGS MAKELEVEL 2>/dev/null # ---------------------------------------------------------------------- # Set up and process configure options # ---------------------------------------------------------------------- AM_CONDITIONAL(SUBDIR_SNPRINTFV, test x"${enable_subdir-no}" != xno) if test x"${enable_subdir-no}" = xno; then enable_snprintfv_install=yes enable_snprintfv_convenience=no else if test x"$enable_snprintfv_convenience$enable_snprintfv_install" = x; then AC_MSG_WARN([*** The top-level configure should select either]) AC_MSG_WARN([*** [A@&t@C_SNPRINTFV_INSTALL] or [A@&t@C_SNPRINTFV_CONVENIENCE],]) enable_snprintfv_convenience=yes enable_snprintfv_install=no fi fi AM_CONDITIONAL(INSTALL_SNPRINTFV, test x"${enable_snprintfv_install-no}" != xno) if test x"${enable_snprintfv_install-no}" != xno; then installed_libsnprintfv=libsnprintfv.la fi AC_SUBST(installed_libsnprintfv) AM_CONDITIONAL(CONVENIENCE_SNPRINTFV, test x"${enable_snprintfv_convenience-no}" != xno) if test x"${enable_snprintfv_convenience-no}" != xno; then convenience_libsnprintfv=libsnprintfvc.la fi AC_SUBST(convenience_libsnprintfv) AC_ARG_ENABLE(convenience-float-printing, [ --enable-convenience-float-printing enable/disable printing floats in convenience snprintfv [yes]], , enable_convenience_float_printing=yes) if test x"$enable_convenience_float_printing" = yes; then enable_convenience_float_printing=$enable_snprintfv_convenience fi AC_MSG_CHECKING([whether the convenience libsnprintfv needs printing floats]) AC_MSG_RESULT([$enable_convenience_float_printing]) if test x$enable_convenience_float_printing = xyes; then LIBSNPRINTFVC_PRINT_FLOATS= else LIBSNPRINTFVC_PRINT_FLOATS='-DNO_FLOAT_PRINTING' fi AC_SUBST(LIBSNPRINTFVC_PRINT_FLOATS) AM_WITH_DMALLOC # ---------------------------------------------------------------------- # check for various programs used during the build. # ---------------------------------------------------------------------- AC_PROG_CC AC_C_CONST AC_C_INLINE AC_EXEEXT AC_PROG_INSTALL AC_PROG_AWK # ---------------------------------------------------------------------- # check for standard headers. # ---------------------------------------------------------------------- AC_HEADER_STDC AC_CHECK_HEADERS(sys/types.h) AC_CACHE_CHECK([for static inline], [snv_cv_static_inline], [ AC_TRY_COMPILE([static inline foo(bar) int bar; { return bar; }], [return foo(0);], [snv_cv_static_inline=yes], [snv_cv_static_inline=no]) ]) # If string.h is present define HAVE_STRING_H, otherwise if strings.h # is present define HAVE_STRINGS_H. AC_CHECK_HEADERS(string.h strings.h, break) AC_CHECK_FUNCS(flockfile fputc_unlocked) # ---------------------------------------------------------------------- # Checks for typedefs # ---------------------------------------------------------------------- AC_CHECK_HEADER(wchar.h) AC_CHECK_TYPE(wchar_t) AC_CHECK_TYPE(wint_t) AC_CHECK_TYPE(intmax_t) AC_TYPE_SIZE_T AC_CHECK_SIZEOF(int) AC_CHECK_SIZEOF(wint_t) # ---------------------------------------------------------------------- # Checks for floating-point features # ---------------------------------------------------------------------- AC_C_LONG_DOUBLE AC_CHECK_LIB(m, log) AC_CHECK_FUNCS(copysign copysignl isinf isinfl isnan isnanl modfl) # ---------------------------------------------------------------------- # Add code to config.status to create an installable host dependent # configuration file. # ---------------------------------------------------------------------- AC_CONFIG_COMMANDS([snprintfv/compat.h], [ outfile=snprintfv/compat.h tmpfile=${outfile}T dirname="sed s,^.*/,,g" echo creating $outfile cat > $tmpfile << _EOF_ /* -*- Mode: C -*- * -------------------------------------------------------------------- * DO NOT EDIT THIS FILE! It has been automatically generated * from: configure.in and `echo $outfile|$dirname`.in * on host: `(hostname || uname -n) 2>/dev/null | sed 1q` * -------------------------------------------------------------------- * `echo $outfile|$dirname` --- portability code generated for snprintfv by configure.in */ #ifndef SNPRINTFV_COMPAT_H #define SNPRINTFV_COMPAT_H 1 #ifdef __cplusplus extern "C" { #if 0 /* This brace is so that emacs can still indent properly: */ } #endif #endif /* __cplusplus */ #include #include #include #include #include _EOF_ # Add the code to include these headers only if autoconf has # shown them to be present. if test x$ac_cv_header_sys_types_h = xyes; then echo '#include ' >> $tmpfile fi if test x$ac_cv_header_string_h = xyes; then echo '#include ' >> $tmpfile elif test x$ac_cv_header_strings_h = xyes; then echo '#include ' >> $tmpfile fi if test x$ac_cv_header_inttypes_h = xyes; then echo '#include ' >> $tmpfile elif test x$ac_cv_header_stdint_h = xyes; then echo '#include ' >> $tmpfile fi if test x$ac_cv_header_wchar_h = xyes; then echo '#include ' >> $tmpfile fi if test x$snv_cv_static_inline = xyes; then echo '#define SNV_INLINE static inline' >> $tmpfile else echo '#define SNV_INLINE static' >> $tmpfile fi if test x$ac_cv_type_wchar_t = xno; then echo 'typedef unsigned int snv_wchar_t;' >> $tmpfile else echo 'typedef wchar_t snv_wchar_t;' >> $tmpfile fi if test x$ac_cv_type_wint_t = xno || test $ac_cv_sizeof_wint_t -lt $ac_cv_sizeof_int; then echo 'typedef unsigned int snv_wint_t;' >> $tmpfile else echo 'typedef wint_t snv_wint_t;' >> $tmpfile fi if test x$ac_cv_c_long_double = xno; then echo 'typedef double snv_long_double;' >> $tmpfile else echo 'typedef long double snv_long_double;' >> $tmpfile fi if test x$ac_cv_type_intmax_t = xno; then cat >> $tmpfile << '_EOF_' #if __GNUC__ >= 2 typedef long long intmax_t; typedef unsigned long long uintmax_t; #else typedef long intmax_t; typedef unsigned long uintmax_t; #endif _EOF_ fi if test x$ac_cv_type_size_t != xyes; then cat >> $tmpfile << \_EOF_ typedef unsigned long size_t; _EOF_ fi if test $ac_cv_func_fputc_unlocked = no || test $ac_cv_func_flockfile = no; then cat >> $tmpfile << \_EOF_ #define SNV_FPUTC_UNLOCKED fputc #define SNV_PUTC_UNLOCKED putc #define SNV_WITH_LOCKED_FP(fp, tmp_var) \ for (tmp_var = 1; tmp_var--; ) _EOF_ else cat >> $tmpfile << \_EOF_ #define SNV_FPUTC_UNLOCKED fputc_unlocked #define SNV_PUTC_UNLOCKED putc_unlocked #define SNV_WITH_LOCKED_FP(fp, tmp_var) \ for (flockfile (fp), tmp_var = 1; \ tmp_var--; funlockfile (fp)) _EOF_ fi cat >> $tmpfile << \_EOF_ /* Define macros for storing integers inside pointers. * Be aware that it is only safe to use these macros to store `int' * values in `char*' (or `void*') words, and then extract them later. * Although it will work the other way round on many common * architectures, it is not portable to assume a `char*' can be * stored in an `int' and extracted later without loss of the msb's */ #define SNV_POINTER_TO_INT(p) ((long)(p)) #define SNV_POINTER_TO_UINT(p) ((unsigned long)(p)) #define SNV_INT_TO_POINTER(i) ((snv_pointer)(long)(i)) #define SNV_UINT_TO_POINTER(u) ((snv_pointer)(unsigned long)(u)) _EOF_ # The ugly but portable cpp stuff comes from here infile=$srcdir/snprintfv/`echo $outfile | sed 's,.*/,,g;s,\..*$,,g'`.in sed '/^##.*$/d' $infile >> $tmpfile cat >> $tmpfile << \_EOF_ #ifdef __cplusplus #if 0 /* This brace is so that emacs can still indent properly: */ { #endif } #endif /* __cplusplus */ #endif /* COMPAT_H */ _EOF_ if cmp -s $tmpfile $outfile; then echo $outfile is unchanged rm -f $tmpfile else mv $tmpfile $outfile fi ],[ ac_cv_header_inttypes_h=$ac_cv_header_inttypes_h ac_cv_header_stdint_h=$ac_cv_header_stdint_h ac_cv_header_stdlib_h=$ac_cv_header_stdlib_h ac_cv_header_sys_types_h=$ac_cv_header_sys_types_h ac_cv_header_wchar_h=$ac_cv_header_wchar_h ac_cv_header_memory_h=$ac_cv_header_memory_h ac_cv_header_stdarg_h=$ac_cv_header_stdarg_h ac_cv_header_varargs_h=$ac_cv_header_varargs_h ac_cv_header_string_h=$ac_cv_header_string_h ac_cv_header_strings_h=$ac_cv_header_strings_h ac_cv_header_limits_h=$ac_cv_header_limits_h ac_cv_header_values_h=$ac_cv_header_values_h ac_cv_header_errno_h=$ac_cv_header_errno_h ac_cv_func_fputc_unlocked=$ac_cv_func_fputc_unlocked ac_cv_func_flockfile=$ac_cv_func_flockfile ac_cv_type_intmax_t=$ac_cv_type_intmax_t ac_cv_c_long_double=$ac_cv_c_long_double ac_cv_type_size_t=$ac_cv_type_size_t ac_cv_type_wchar_t=$ac_cv_type_wchar_t ac_cv_type_wint_t=$ac_cv_type_wint_t ac_cv_sizeof_wint_t=$ac_cv_sizeof_wint_t ac_cv_sizeof_int=$ac_cv_sizeof_int snv_cv_static_inline=$snv_cv_static_inline srcdir=$srcdir ]) # ---------------------------------------------------------------------- # Generate the make files. # ---------------------------------------------------------------------- LTLIBOBJS=`echo "$LIB@&t@OBJS"|sed 's,\.o ,.lo,g;s,\.o$,.lo,'` AC_SUBST(LTLIBOBJS) AC_SUBST(LIBS) AC_SUBST(INCLUDES) AC_SUBST(ac_aux_dir) AC_CONFIG_FILES(Makefile snprintfv/Makefile) dnl BEGIN GNU SMALLTALK LOCAL dnl if test "x${enable_subdir-no}" = xno; then dnl AC_CONFIG_FILES(doc/Makefile tests/Makefile) dnl fi dnl END GNU SMALLTALK LOCAL AC_OUTPUT dnl configure.ac ends here smalltalk-3.2.5/snprintfv/README0000644000175000017500000000245612123404352013342 00000000000000This is libsnprintfv, a portable, extensible reimplementation of the POSIX format printing API. libsnprintfv provides all the features which should be present in a POSIX format printing implementation, but which often are not, such as guaranteed return of number of characters printed and support for %n$ format specifiers. In addition the the POSIX features, libsnprintfv also provides some extensions to the API, and a GNU glibc-2 compatible printf custom format specifier, all of which you can use with impunity if you link with libsnprintfv, rather than worrying about whether the target C library provides the extensions. See the info manual for details of the API calls available, and an explanation of how to write custom specifier handlers. The latest version of libsnprintfv is available from the author's homepage: http://www.oranda.demon.co.uk. libsnprintfv is written in a very portable K&R compatible style, and should build anywhere that provides a reasonable C compiler and runtime. See the file INSTALL for instructions on how to build and install libsnprintfv. See the file NEWS for a description of user visible changes to libsnprintfv between releases. See the file TODO for a list of outstanding work. If you have any suggestions or bug reports, please send email to the author at . smalltalk-3.2.5/snprintfv/TODO0000644000175000017500000000155512123404352013151 00000000000000# -*- Mode: Outline -*- * namespace ** decide whether it is fine to override the printf functions in the C library instead of prefixing them with snv_ * performance ** move handling of limit (and possibly buffering?) to the single streams. This would give better performance and possibly turn stream_put into a macro that just dispatches to the put_func. * modules ** the printf_load_module_callback i/face is kludgy: there is no provision to load only dlpreloaded modules (perhaps the loader field in lt_dlhandle_struct should be moved into lt_dlinfo so that the validation callback can decide?) * documentation ** Write the non-generated docs with an examples of: *** custom streams *** dynamic loading * easy integration ** wrap up an autoconf macro so that snprintfv can be distributed without the overhead of a subconfigure (see how we use libltdl for an example). smalltalk-3.2.5/snprintfv/AUTHORS0000644000175000017500000000047012123404352013524 00000000000000Authors of libsnprintfv. See individual files for their licenses. Gary V. Vaughan : Designed, implemented and maintained libsnprintfv up to the 0.98h release. Paolo Bonzini and Bruce Korb : Are currently maintaining libsnprintfv (starting from Summer 2002). smalltalk-3.2.5/snprintfv/gendoc.awk0000755000175000017500000006653112123404352014434 00000000000000#! /usr/bin/awk -f # gendoc.awk --- extract and format API comments # Copyright (C) 1999 Gary V. Vaughan # Originally by Gary V. Vaughan , 1999 # This file is part of Snprintfv. # # Snprintfv is free software; you can redistribute it and/or # modify it under the terms of the GNU General Public License as # published by the Free Software Foundation; either version 2 of the # License, or (at your option) any later version. # # Snprintfv is distributed in the hope that it will be useful, # but WITHOUT ANY WARRANTY; without even the implied warranty of # MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU # General Public License for more details. # # You should have received a copy of the GNU General Public License # along with this program; if not, write to the Free Software # Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. # # As a special exception to the GNU General Public License, if you # distribute this file as part of a program that also links with and # uses the libopts library from AutoGen, you may include it under # the same distribution terms used by the libopts library. # Commentary: # # USAGE: awk -f gendoc.awk source.c > doc.texi # awk [-v OPTION] -f gendoc.awk source.c > output # # OPTIONS: # debug=1 execution trace on # debug= execution trace while parsing # mode=texinfo output texinfo documentation [default] # mode= output exported function prototypes with # in their keyword list (or all # exported functions if none cite header.h). # global=GLOBAL_DATA private global data scope macro name used in # .c file to be replaced by... # scope=SCOPE public global data scope macro name to be used # int generated .h file. # format=PRINTF gnu printf attribute macro name [default] # This macro needs to handle ANSI and GNU C. # e.g. int baz PRINTF((char *format, ...), 1, 2); # # See the accompanying README for details of how to format function headers # for extraction by this script. # Todo: # # Support %constant to @code{constant} transform in description # Allow non-API documentation to be embedded in source file # Code: BEGIN { program_name = "gendoc.awk"; status = 0; # return status start = 0; # waiting for function name in header retcomment = 0; # reading the description of return values funcdecl = 0; # reading the function declaration fname = ""; # name of function under consideration paramname = ""; # name of parameter under consideration funclist = ""; # list of functions discovered so far argc = 0; # parameter index delete comment[fname]; # full comment text for FNAME delete desc[fname]; # general description of FNAME delete keywords[fname]; # keywords associated with FUNC delete returnval[fname]; # description of return values from FNAME delete paramlist[fname]; # list of PARAMNAMES in FNAME delete type[fname]; # return type of FNAME delete param[fname,argc]; # declaration of FNAME parameter ARGC delete paramdesc[fname,paramname];# description of PARAMNAME in FNAME if (!length(mode)) mode = "texinfo"; if (!length(format)) format = "PRINTF"; if (!length(global)) global = "GLOBAL_DATA"; if (!length(scope)) scope = "SCOPE"; # work around a bug in mawk match ("abcdef", "abc"); workaround = length(substr ("abcdef", 0, RSTART)); } # # Extract details from docu-comments # /^\/\*\*$/, /\*\/$/ { # # ignore preprocessor directives # if ($0 ~ /^[ \t]*\#/) next; # # function name in comment header # if ($0 ~ /^\/\*\*$/) { start = 1; # wait for fname next; } if (start) { start = 0; # fname found fname = $2; # key for various arrays sub(/:$/, "", fname); # strip trailing colon if (index(" " funclist " ", " " fname " ") != 0) { # function has already been declared printf("%s: Error: %s comment header appears twice.\n", program_name, fname) | "cat >&2"; status = 1; } funclist = funclist " " fname; if (debug != 0) { printf("%s: DEBUG: Function header, \"%s\" found.\n", program_name, fname) | "cat >&2"; } # what remains is the keyword list sub(fname, ""); sub(/^[ \t]*\*+[ \t]*:?[ \t]*/, ""); keywords[fname] = keywords[fname] " " $0; # start a new comment entry comment[fname] = "/**\n * " fname ": " keywords[fname] " \n"; if (match(mode, /\.h$/) && index(comment[fname], " " mode " ")) { # strip the .h modenames from the comment sub(mode " ", "", comment[fname]); } next; } # # All C comment lines for this function are saved verbatim # if ($0 ~ /^[ \t]*\*/) { comment[fname] = comment[fname] $0 "\n"; } # # parameter description # if ($0 ~ /^[ \t]*\*[ \t]*@[_a-zA-Z][_a-zA-Z0-9]*[ \t]*:/) { sub(/^[ \t]*\*[ \t]*@/, ""); # strip leading garbage sub(/[ \t]*:/, ""); # strip trailing garbage paramname = $1; # extract parameter name sub(paramname, ""); # remove it from the description sub(/^[ \t]*/, ""); # strip leading whitespace if ((fname,paramname) in paramdesc) { # this parameter is described twice for this function printf("%s: Error: parameter \"%s\" in %s has two descriptions.\n", program_name, $1, fname) | "cat >&2"; status = 1; } # Save the description by function name and parameter name && # add this parameter name to the list of names for this function paramdesc[fname,paramname] = $0; paramlist[fname] = paramlist[fname] " " paramname; if (debug == 1 || index(debug, fname) != 0) { printf("%s: DEBUG(%s): Description for parameter \"%s\" found:\n" \ "\t>%s<\n", program_name, fname, paramname, paramdesc[fname, paramname]) | "cat >&2"; } next; } # # function declaration to follow comment end. # if ($0 ~ /^[ \t]*\*+\//) { if (debug == 1 || index(debug, fname) != 0) { printf("%s: DEBUG(%s): end of comment header reached.\n", program_name, fname) | "cat >&2"; } retcomment = 0; # no longer reading return values comment funcdecl = 1; # wait for function declaration next; } # # return value description # Note that we are careful to leave leading tab characters, which # indicate that what follows is formatted code. # if ($0 ~ /^[ \t]*\*[ \t]*[Re]eturn [Vv]alues?[ \t]*:/) { retcomment = 1; if (debug == 1 || index(debug, fname) != 0) { printf("%s: DEBUG(%s): start of returnval description reached\n", program_name, fname) | "cat >&2"; } } if (retcomment == 1) { sub(/^[ \t]*\* */, ""); sub(/^[ \t]*[Rr]eturn [Vv]alues?[ \t]*:[ \t]*/, ""); if (debug == 1 || index(debug, fname) != 0) { printf("%s: DEBUG(%s): return value description section found:\n" \ "\t>%s<\n", program_name, fname, $0) | "cat >&2"; } if (length() > 0 || length(returnval[fname]) > 0) { returnval[fname] = returnval[fname] $0 "\n"; if (debug == 1 || index(debug, fname) != 0) { printf("%s: DEBUG(%s): ...and added!\n", program_name, fname) | "cat >&2"; } } next; } # # Other commented lines must be part of the description # Note that we are careful to leave leading tab characters, which # indicate that what follows is formatted code. # if ($0 ~ /^[ \t]*\*([^\/]|$)/) { sub(/^[ \t]*\* */, ""); if (debug == 1 || index(debug, fname) != 0) { printf("%s: DEBUG(%s): function description found:\n\t>%s<\n", program_name, fname, $0) | "cat >&2"; } if (length() > 0 || length(desc[fname]) > 0) { desc[fname] = desc[fname] $0 "\n"; if (debug == 1 || index(debug, fname) != 0) { printf("%s: DEBUG(%s): ...and added!\n", program_name, fname) | "cat >&2"; } } next; } } # # Extract details from declaration/prototype # funcdecl>0 { if (debug == 1 || index(debug, fname) != 0) { printf("%s: DEBUG(%s): attempting declaration extraction:\n" \ "\t>%s<\n", program_name, fname, $0) | "cat >&2"; } # # first following line is return type in a c file, or a prototype # or a variable or macro in a generated header. # if (funcdecl == 1) { # strip private global data macro global_re = "[ \t]*(extern[ \t]+)?" global "[ \t]+"; if ($0 ~ global_re) { sub(global_re, ""); keywords[fname] = keywords[fname] " global"; if (debug == 1 || index(debug, fname) != 0) { printf("%s: DEBUG(%s): global data declaration found:\n" \ "\t>%s<\n", program_name, fname, $0) | "cat >&2"; } type[fname] = $0; sub(/[ \t]+[a-zA-Z_][a-zA-Z_0-9]*;$/, "", type[fname]); decl[fname] = $0; } # Function pointer typedef else if ($0 ~ /^[ \t]*typedef[ \t]+.*\);[ \t]*$/) { keywords[fname] = keywords[fname] " functionpointer typedef"; if (debug == 1 || index(debug, fname) != 0) { printf("%s: DEBUG(%s): function pointer typedef found:\n" \ "\t>%s<\n", program_name, fname, $0) | "cat >&2"; } # remove parentheses and asterisk for function pointer pointer = match($0, /\(\*[A-Za-z0-9_]*\)/) if (pointer) { $0 = substr($0, 1, RSTART - 1) \ substr($0, RSTART + 2, RLENGTH - 3) \ substr($0, RSTART + RLENGTH); } # Extract return type type[fname] = $0; sub(/^[ \t]*typedef[ \t]+/, "", type[fname]); # strip "typedef" sub(/[ \t]+[A-Z_]*P[A-Z]* *\(\(/, " (", type[fname]); # and __P/PARAMS macro sub(/[ \t]*[(].*$/, "", type[fname]); # strip arguments sub(/[ \t]*[_A-Za-z][_A-Za-z0-9]*[ \t]*$/, "", type[fname]); # Extract parameter declarations sub(/^[^(]*\(+/, ""); # strip leading garbage sub(/\).*$/, ""); # strip trailing garbage # populate the function's param array argc = split($0, params, /,[ \t]*/); if (pointer) { decl[fname] = type[fname] " (*" fname ") ("; } else { decl[fname] = type[fname] " " fname " ("; } for (i = 1; i <= argc; i++) { if (debug == 1 || index(debug, fname) != 0) { printf("\tparam%d: >%s<\n", i, params[i]) | "cat >&2"; } param[fname,i -1] = params[i]; decl[fname] = decl[fname] param[fname, i -1]; if (i < argc) { decl[fname] = decl[fname] ", "; } delete params[i]; } decl[fname] = decl[fname] ")"; param[fname, argc] = "NULL"; if (debug == 1 || index(debug, fname) != 0) { printf("\tparam%d: >%s<\n", argc +1, param[fname, argc]) | "cat >&2"; } } # Typedef declaration else if ($0 ~ /^[ \t]*typedef[ \t]+/) { keywords[fname] = keywords[fname] " typedef"; if (debug == 1 || index(debug, fname) != 0) { printf("%s: DEBUG(%s): type definition found:\n" \ "\t>%s<\n", program_name, fname, $0) | "cat >&2"; } decl[fname] = fname; } # Macro function else if ($0 ~ /^\#[ \t]*define[ \t]+[_A-Za-z0-9]+\(/) { keywords[fname] = keywords[fname] " macro"; if (debug == 1 || index(debug, fname) != 0) { printf("%s: DEBUG(%s): macro function definition found:\n" \ "\t>%s<\n", program_name, fname, $0) | "cat >&2"; } sub(/^[^(]*\(+/, ""); # strip leading garbage sub(/\).*$/, ""); # strip trailing garbage # populate the macro's param array argc = split($0, params, /,[ \t]*/); decl[fname] = fname "("; for (i = 1; i <= argc; i++) { if (debug == 1 || index(debug, fname) != 0) { printf("\tparam%d: >%s<\n", i, params[i]) | "cat >&2"; } param[fname,i -1] = params[i]; decl[fname] = decl[fname] param[fname, i -1]; if (i < argc) { decl[fname] = decl[fname] ", "; } delete params[i]; } decl[fname] = decl[fname] ")"; param[fname, argc] = "NULL"; if (debug == 1 || index(debug, fname) != 0) { printf("\tparam%d: >%s<\n", argc +1, param[fname, argc]) | "cat >&2"; } } # Macro alias else if ($0 ~ /^\#[ \t]*define[ \t]+[_A-Za-z0-9]+[ \t]+/) { keywords[fname] = keywords[fname] " alias"; if (debug == 1 || index(debug, fname) != 0) { printf("%s: DEBUG(%s): macro alias definition found:\n" \ "\t>%s<\n", program_name, fname, $0) | "cat >&2"; } decl[fname] = fname; } # Function prototype else if ($0 ~ /^[ \t]*(extern)?[ \t]*.*\);?[ \t]*$/) { sub(/^[ \t]*extern[ \t]*/, ""); # strip leading extern keyword sub(/[ \t]+[A-Z_]*P[A-Z]*\(\(/, " ("); # and __P/PARAMS macro sub(/[ \t]*\)\)[ \t]*;?[ \t]*$/, ")"); # and trailing garbage if (debug == 1 || index(debug, fname) != 0) { printf("%s: DEBUG(%s): ANSI prototype found:\n" \ "\t>%s<\n", program_name, fname, $0) | "cat >&2"; } type[fname] = $0; sub(/^[ \t]*inline[ \t]*/, "", type[fname]); type[fname] = substr(type[fname], 1, match(type[fname], /[ \t]*\(/) -1); sub(/[ \t][a-zA-Z0-9_]+$/, "", type[fname]); if (debug == 1 || index(debug, fname) != 0) { printf("\ttype: >%s<\n", type[fname]) | "cat >&2"; } decl[fname] = $0; sub(/^.*\(+/, ""); # strip leading garbage sub(/(\)[0-9, \t]*)?\);*[ \t]*$/, ""); # strip trailing garbage # populate the functions param array argc = split($0, params, /,[ \t]*/); for (i = 1; i <= argc; i++) { if (debug == 1 || index(debug, fname) != 0) { printf("\tparam%d: >%s<\n", i, params[i]) | "cat >&2"; } param[fname,i -1] = params[i]; delete params[i]; } param[fname, argc] = "NULL"; if (debug == 1 || index(debug, fname) != 0) { printf("\tparam%d: >%s<\n", argc +1, param[fname, argc]) | "cat >&2"; } } # ignore other preprocessor directives else if ($0 ~ /^[ \t]*\#/) { next; } # assume return type line from a function definition else { if (debug == 1 || index(debug, fname) != 0) { printf("%s: DEBUG(%s): return type declaration found:\n" \ "\t>%s<\n", program_name, fname, $0) | "cat >&2"; } funcdecl = 2; # wait for function prototype argc = 0; type[fname] = $0; decl[fname] = "extern " $0 " " fname; if (debug == 1 || index(debug, fname) != 0) { printf("%s: DEBUG(%s): ...and added, \"%s\"!\n", program_name, fname, $0) | "cat >&2"; } next; } if (debug == 1 || index(debug, fname) != 0) { printf("%s: DEBUG(%s): full declaration generated:\n" \ "\t>%s<\n", program_name, fname, decl[fname]) | "cat >&2"; } funcdecl = 0; next; } if ($0 ~ /^[ \t]*\#/) # skip any preprocessor when funcdecl > 1 { next; } if (funcdecl == 2) { # second line contains function name @ $1 if ($0 ~ /\(.*[A-Za-z_]+[* \t]+[_A-Za-z]+/ || $0 ~ /\([ \t]*void/) { # We have just seen two consecutive keywords or "void", both of # which mark an ANSI declaration, and need to reset for the next # header funcdecl = 0; # Is this a printf attributable prototype? Look for # ``format,'' in the penultimate argument: use_format=0; if ($0 ~ /[^a-zA-Z_]format,[ \t]*\.\.\.\)$/) { use_format=1; } sub(/^.*\(+/, ""); # strip leading garbage sub(/\)+[ \t]*$/, ""); # strip trailing garbage argc = split($0, params, /,[ \t]*/); if (index(debug, fname) != 0) { printf("%s: DEBUG(%s): checking param %d, \"%s\".\n", program_name, fname, argc, params[argc -1]) | "cat >&2"; } if (use_format == 1 && (debug == 1 || index(debug, fname) != 0)) { printf("%s: DEBUG(%s): printf function declaration found:\n" \ "\t>%s<\n", program_name, fname, $0) | "cat >&2"; } if (use_format == 0 && (debug == 1 || index(debug, fname) != 0)) { printf("%s: DEBUG(%s): ANSI function declaration found:\n" \ "\t>%s<\n", program_name, fname, $0) | "cat >&2"; } # populate the function's param array and decl entry if (use_format) { decl[fname] = decl[fname] " " format "(("; } else { decl[fname] = decl[fname] " ("; } for (i = 1; i <= argc; i++) { if (debug == 1 || index(debug, fname) != 0) { printf("\tparam%d: >%s<\n", i, params[i]) | "cat >&2"; } decl[fname] = decl[fname] params[i]; if (i < argc) { decl[fname] = decl[fname] ", "; } param[fname,i -1] = params[i]; delete params[i]; } param[fname, argc] = "NULL"; if (argc == 0) decl[fname] = decl[fname] "void"; if (use_format) { decl[fname] = decl[fname] "), " (argc -1) ", " argc ");\n"; } else { decl[fname] = decl[fname] ");\n"; } if (debug == 1 || index(debug, fname) != 0) { printf("\tparam%d: >%s<\n", argc +1, param[fname, argc]) | "cat >&2"; } funcdecl = 0; } else { if (debug == 1 || index(debug, fname) != 0) { printf("%s: DEBUG(%s): K&R function declaration found:\n" \ "\t>%s<\n", program_name, fname, $0) | "cat >&2"; } funcdecl = 3; argc = 0; } next; } if (funcdecl == 3) { # the rest are K&R parameter declarations if ($0 ~ /^[ \t]*[{]/) { # We have just seen the "{" which marks the start of the # function body, and need to reset for the next header funcdecl = 0; decl[fname] = decl[fname] " ("; for (i = 0; i < argc; i++) { decl[fname] = decl[fname] param[fname,i]; if (param[fname,i +1] != "NULL") { decl[fname] = decl[fname] ", "; } } if (argc == 0) decl[fname] = decl[fname] "void"; decl[fname] = decl[fname] ");"; if (debug == 1 || index(debug, fname) != 0) { printf("%s: DEBUG(%s): full declaration generated:\n" \ "\t>%s<\n", program_name, fname, decl[fname]) | "cat >&2"; } next; } # We did not see the "{" yet, so this must be another parameter # declaration. sub(/^[ \t]*/, ""); # strip leading garbage sub(/[ \t]*;.*$/,""); # strip trailing garbage param[fname,argc] = $0; argc++; param[fname,argc] = "NULL"; # used as an end marker if (debug == 1 || index(debug, fname) != 0) { printf("%s: DEBUG(%s): parameter declaration found:\n" \ "\t>%s<\n", program_name, fname, $0) | "cat >&2"; } next; } } END { # TODO: optionally output html or nroff instead of texi # # Print formatted C header code for each function described # if ((status == 0) && (match(mode, /\.h$/))) { # split out the function names we found during parsing func_count = split(funclist, funcs); # select the functions with the destination in their keywords # (or else all functions if none name the destination). newlist = ""; for (count = 1; count <= func_count; count++) { if (index(" " keywords[funcs[count]] " ", " " mode " ")) { newlist = newlist funcs[count] " "; } } if (length(newlist)) { funclist = newlist; func_count = split(funclist, funcs); } for (count = 1; count <= func_count; count++) { fname = funcs[count]; print comment[fname] decl[fname] "\n"; } } # # Print texinfo formatted blocks for each element described # if ((status == 0) && (mode == "texinfo")) { # split out the function names we found during parsing func_count = split(funclist, funcs); # reorder the funclist to put typedefs first, constructors next, # destructors after that and the rest following on funclist = ""; for (count = 1; count <= func_count; count++) { if (index(" " keywords[funcs[count]] " ", " typedef ")) { funclist = funclist funcs[count] " "; } } for (count = 1; count <= func_count; count++) { if ((index(" " keywords[funcs[count]] " ", " constructor ")) && (index(" " keywords[funcs[count]] " ", " typedef ") == 0)) { funclist = funclist funcs[count] " "; } } for (count = 1; count <= func_count; count++) { if ((index(" " keywords[funcs[count]] " ", " destructor ")) && (index(" " keywords[funcs[count]] " ", " typedef ") == 0)) { funclist = funclist funcs[count] " "; } } for (count = 1; count <= func_count; count++) { if ((index(" " keywords[funcs[count]] " ", " constructor ")== 0)&& (index(" " keywords[funcs[count]] " ", " destructor ") == 0)&& (index(" " keywords[funcs[count]] " ", " typedef ") == 0)) { funclist = funclist funcs[count] " "; } } func_count = split(funclist, funcs); for (count = 1; count <= func_count; count++) { fname = funcs[count]; # split out the parameter names for this function argc = split(paramlist[fname], funcparam); # replace {, } and @ with @{, @} and @@ repectively for (i = 1; i <= argc; i++) { paramname = funcparam[i]; gsub(/@/, "@@", paramdesc[fname, paramname]); gsub(/[{]/, "@{", paramdesc[fname, paramname]); gsub(/[}]/, "@}", paramdesc[fname, paramname]); gsub(/[a-zA-Z_][a-zA-Z0-9_]*\(\)/, "@code{&}", paramdesc[fname, paramname]); } gsub(/@/, "@@", desc[fname]); gsub(/[{]/, "@{", desc[fname]); gsub(/[}]/, "@}", desc[fname]); gsub(/[a-zA-Z_][a-zA-Z0-9_]*\(\)/, "@code{&}", desc[fname]); gsub(/@/, "@@", returnval[fname]); gsub(/[{]/, "@{", returnval[fname]); gsub(/[}]/, "@}", returnval[fname]); gsub(/[a-zA-Z_][a-zA-Z0-9_]*\(\)/, "@code{&}", returnval[fname]); # rewrite decl[fname] in a format suitable for texinfo if (index(" " keywords[funcs[count]] " ", " alias ") || (index(" " keywords[funcs[count]] " ", " typedef ") && index(" " keywords[funcs[count]] " ", " funcpointer ") == 0)) { # decl[fname] is already correct! } else { decl[fname] = type[fname] " " fname " ("; sub(/^[ \t]*inline[ \t]*/, "", decl[fname]); for (i = 0; i < argc; i++) { decl[fname] = decl[fname] param[fname,i]; if (param[fname,i +1] != "NULL") { decl[fname] = decl[fname] ", "; } } decl[fname] = decl[fname] ")"; } # replace all references to named params with @var{param} for (i = 1; i <= argc; i++) { paramname = funcparam[i]; # Oh god! gensub is a GNU extension =(O| # Here is a hacky reimplementation using match source = decl[fname]; dest = ""; while (match(source, paramname)) { prechar="<"; # dummy so that start of string will work postchar=">"; # dummy for end of string if (RSTART > 1) { prechar = substr(source, RSTART -1, 1); } if (RSTART + RLENGTH < length (source)) { postchar = substr(source, RSTART + RLENGTH, 1); } dest = dest substr(source, 0, RSTART - workaround); source = substr(source, RSTART + RLENGTH); if (match(prechar, /[^A-Za-z0-9_]/) \ && match(postchar, /[^A-Za-z0-9_]/)) { dest = dest "@var{" paramname "}"; } else { dest = dest paramname; } } decl[fname] = dest source; for (j = 1; j <= argc; j++) { descname = funcparam[j]; gsub("@@" paramname, "@var{" paramname "}", paramdesc[fname, descname]); } gsub("@@" paramname, "@var{" paramname "}", desc[fname]); gsub("@@" paramname, "@var{" paramname "}", returnval[fname]); } # @deftypefn Category if (index(" " keywords[funcs[count]] " ", " alias ") || index(" " keywords[funcs[count]] " ", " macro ")) { printf "@deffn Macro " decl[fname] "\n"; } else if (index(" " keywords[funcs[count]] " ", " functionpointer ")) { printf "@deftypefn Typedef " decl[fname] "\n"; } else if (index(" " keywords[funcs[count]] " ", " typedef ")) { printf "@deffn Typedef " decl[fname] "\n"; } else { printf "@deftypefn Function " decl[fname] "\n"; } print "@fnindex " fname "\n"; # param descriptions if (argc) { print index (decl[fname], "(") ? "Parameters:" : "Fields:"; print "@table @code"; for (i = 1; i <= argc; i++) { paramname = funcparam[i]; if ((fname, paramname) in paramdesc) { print "@item " paramname; print paramdesc[fname,paramname]; } else { # No description was given for this parameter printf("%s: Warning: No description for \"%s\" in %s.\n", program_name, paramname, fname) | "cat >&2"; } } print "@end table\n"; } # function description # lines starting with a tab represent preformatted code. argc = split(desc[fname], lines, "\n"); code = 0; # are we in a code section? blanks = 0; # how many blank lines (of undetermined type) for (i = 1; i <= argc; i++) { # %word becoming @code{} source = lines[i]; dest = ""; while (match(source, /%[-+*\/%<>!=()A-Za-z0-9_\\\'\"]+/)) { postchar="$"; # dummy for end of string if (RSTART + RLENGTH < length (source)) { postchar = substr(source, RSTART + RLENGTH, 1); } dest = dest substr(source, 0, RSTART - workaround); matched = substr(source, RSTART + 1, RLENGTH - 1); source = substr(source, RSTART + RLENGTH); if (match(postchar, /[^A-Za-z0-9_]/)) { dest = dest "@code{" matched "}"; } else { dest = dest "%" matched; } } dest = dest source; if (code == 0) { if (dest ~ /^\t[ \t]*[^ \t]/) { code = 1; print "@smallexample" sub(/^\t/, "", dest); } print dest; } else { if (dest ~ /^[^\t]/ && dest !~ /^[\t ]*$/) { code = 0; print "@end smallexample"; print dest; } else { sub(/^\t/, "", dest); if (dest ~ /^[ \t]*$/) { blanks++; } else { while (blanks > 0) { print; blanks--; } print dest; } } } } if (code == 1) { print "@end smallexample\n"; } # return value description if (!fname in returnval && type[fname] !~ /[ \t]*void[ \t]*/) { # No return value section was found for non-void function printf("%s: Warning: No return value for \"%s\".\n", program_name, fname) | "cat >&2"; } # lines starting with a tab represent preformatted code. argc = split(returnval[fname], lines, "\n"); code = 0; # are we in a code section? blanks = 0; # how many blank lines (of undetermined type) for (i = 1; i <= argc; i++) { # %word becoming @code{} source = lines[i]; dest = ""; while (match(source, /%[-+*\/%<>!=()A-Za-z0-9_\\\"\']+/)) { postchar="$"; # dummy for end of string if (RSTART + RLENGTH < length (source)) { postchar = substr(source, RSTART + RLENGTH, 1); } dest = dest substr(source, 0, RSTART - workaround); matched = substr(source, RSTART + 1, RLENGTH - 1); source = substr(source, RSTART + RLENGTH); if (match(postchar, /[^A-Za-z0-9_]/)) { dest = dest "@code{" matched "}"; } else { dest = dest "%" matched; } } dest = dest source; if (code == 0) { if (dest ~ /^\t[ \t]*[^ \t]/) { code = 1; print "@smallexample" sub(/^\t/, "", dest); } print dest; } else { if (dest ~ /^[^\t]/ && dest !~ /^[\t ]*$/) { code = 0; print "@end smallexample\n"; print dest; } else { sub(/^\t/, "", dest); if (dest ~ /^[ \t]*$/) { blanks++; } else { while (blanks > 0) { print; blanks--; } print dest; } } } } if (code == 1) { print "@end smallexample"; } if (index(" " keywords[funcs[count]] " ", " functionpointer ")) { print "@end deftypefn\n"; } else if (index(" " keywords[funcs[count]] " ", " alias ") || index(" " keywords[funcs[count]] " ", " macro ") || index(" " keywords[funcs[count]] " ", " typedef ")) { print "@end deffn\n"; } else { print "@end deftypefn\n"; } } } # Keep lint happy: close("cat >&2"); exit status; } # gendoc.awk ends here smalltalk-3.2.5/COPYING0000644000175000017500000004312212123404352011457 00000000000000 GNU GENERAL PUBLIC LICENSE Version 2, June 1991 Copyright (C) 1989, 1991 Free Software Foundation, Inc. 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA Everyone is permitted to copy and distribute verbatim copies of this license document, but changing it is not allowed. Preamble The licenses for most software are designed to take away your freedom to share and change it. By contrast, the GNU General Public License is intended to guarantee your freedom to share and change free software--to make sure the software is free for all its users. This General Public License applies to most of the Free Software Foundation's software and to any other program whose authors commit to using it. (Some other Free Software Foundation software is covered by the GNU Library General Public License instead.) You can apply it to your programs, too. When we speak of free software, we are referring to freedom, not price. Our General Public Licenses are designed to make sure that you have the freedom to distribute copies of free software (and charge for this service if you wish), that you receive source code or can get it if you want it, that you can change the software or use pieces of it in new free programs; and that you know you can do these things. To protect your rights, we need to make restrictions that forbid anyone to deny you these rights or to ask you to surrender the rights. These restrictions translate to certain responsibilities for you if you distribute copies of the software, or if you modify it. For example, if you distribute copies of such a program, whether gratis or for a fee, you must give the recipients all the rights that you have. You must make sure that they, too, receive or can get the source code. And you must show them these terms so they know their rights. We protect your rights with two steps: (1) copyright the software, and (2) offer you this license which gives you legal permission to copy, distribute and/or modify the software. Also, for each author's protection and ours, we want to make certain that everyone understands that there is no warranty for this free software. If the software is modified by someone else and passed on, we want its recipients to know that what they have is not the original, so that any problems introduced by others will not reflect on the original authors' reputations. Finally, any free program is threatened constantly by software patents. We wish to avoid the danger that redistributors of a free program will individually obtain patent licenses, in effect making the program proprietary. To prevent this, we have made it clear that any patent must be licensed for everyone's free use or not licensed at all. The precise terms and conditions for copying, distribution and modification follow. GNU GENERAL PUBLIC LICENSE TERMS AND CONDITIONS FOR COPYING, DISTRIBUTION AND MODIFICATION 0. This License applies to any program or other work which contains a notice placed by the copyright holder saying it may be distributed under the terms of this General Public License. The "Program", below, refers to any such program or work, and a "work based on the Program" means either the Program or any derivative work under copyright law: that is to say, a work containing the Program or a portion of it, either verbatim or with modifications and/or translated into another language. (Hereinafter, translation is included without limitation in the term "modification".) Each licensee is addressed as "you". Activities other than copying, distribution and modification are not covered by this License; they are outside its scope. The act of running the Program is not restricted, and the output from the Program is covered only if its contents constitute a work based on the Program (independent of having been made by running the Program). Whether that is true depends on what the Program does. 1. You may copy and distribute verbatim copies of the Program's source code as you receive it, in any medium, provided that you conspicuously and appropriately publish on each copy an appropriate copyright notice and disclaimer of warranty; keep intact all the notices that refer to this License and to the absence of any warranty; and give any other recipients of the Program a copy of this License along with the Program. You may charge a fee for the physical act of transferring a copy, and you may at your option offer warranty protection in exchange for a fee. 2. You may modify your copy or copies of the Program or any portion of it, thus forming a work based on the Program, and copy and distribute such modifications or work under the terms of Section 1 above, provided that you also meet all of these conditions: a) You must cause the modified files to carry prominent notices stating that you changed the files and the date of any change. b) You must cause any work that you distribute or publish, that in whole or in part contains or is derived from the Program or any part thereof, to be licensed as a whole at no charge to all third parties under the terms of this License. c) If the modified program normally reads commands interactively when run, you must cause it, when started running for such interactive use in the most ordinary way, to print or display an announcement including an appropriate copyright notice and a notice that there is no warranty (or else, saying that you provide a warranty) and that users may redistribute the program under these conditions, and telling the user how to view a copy of this License. (Exception: if the Program itself is interactive but does not normally print such an announcement, your work based on the Program is not required to print an announcement.) These requirements apply to the modified work as a whole. If identifiable sections of that work are not derived from the Program, and can be reasonably considered independent and separate works in themselves, then this License, and its terms, do not apply to those sections when you distribute them as separate works. But when you distribute the same sections as part of a whole which is a work based on the Program, the distribution of the whole must be on the terms of this License, whose permissions for other licensees extend to the entire whole, and thus to each and every part regardless of who wrote it. Thus, it is not the intent of this section to claim rights or contest your rights to work written entirely by you; rather, the intent is to exercise the right to control the distribution of derivative or collective works based on the Program. In addition, mere aggregation of another work not based on the Program with the Program (or with a work based on the Program) on a volume of a storage or distribution medium does not bring the other work under the scope of this License. 3. You may copy and distribute the Program (or a work based on it, under Section 2) in object code or executable form under the terms of Sections 1 and 2 above provided that you also do one of the following: a) Accompany it with the complete corresponding machine-readable source code, which must be distributed under the terms of Sections 1 and 2 above on a medium customarily used for software interchange; or, b) Accompany it with a written offer, valid for at least three years, to give any third party, for a charge no more than your cost of physically performing source distribution, a complete machine-readable copy of the corresponding source code, to be distributed under the terms of Sections 1 and 2 above on a medium customarily used for software interchange; or, c) Accompany it with the information you received as to the offer to distribute corresponding source code. (This alternative is allowed only for noncommercial distribution and only if you received the program in object code or executable form with such an offer, in accord with Subsection b above.) The source code for a work means the preferred form of the work for making modifications to it. For an executable work, complete source code means all the source code for all modules it contains, plus any associated interface definition files, plus the scripts used to control compilation and installation of the executable. However, as a special exception, the source code distributed need not include anything that is normally distributed (in either source or binary form) with the major components (compiler, kernel, and so on) of the operating system on which the executable runs, unless that component itself accompanies the executable. If distribution of executable or object code is made by offering access to copy from a designated place, then offering equivalent access to copy the source code from the same place counts as distribution of the source code, even though third parties are not compelled to copy the source along with the object code. 4. You may not copy, modify, sublicense, or distribute the Program except as expressly provided under this License. Any attempt otherwise to copy, modify, sublicense or distribute the Program is void, and will automatically terminate your rights under this License. However, parties who have received copies, or rights, from you under this License will not have their licenses terminated so long as such parties remain in full compliance. 5. You are not required to accept this License, since you have not signed it. However, nothing else grants you permission to modify or distribute the Program or its derivative works. These actions are prohibited by law if you do not accept this License. Therefore, by modifying or distributing the Program (or any work based on the Program), you indicate your acceptance of this License to do so, and all its terms and conditions for copying, distributing or modifying the Program or works based on it. 6. Each time you redistribute the Program (or any work based on the Program), the recipient automatically receives a license from the original licensor to copy, distribute or modify the Program subject to these terms and conditions. You may not impose any further restrictions on the recipients' exercise of the rights granted herein. You are not responsible for enforcing compliance by third parties to this License. 7. If, as a consequence of a court judgment or allegation of patent infringement or for any other reason (not limited to patent issues), conditions are imposed on you (whether by court order, agreement or otherwise) that contradict the conditions of this License, they do not excuse you from the conditions of this License. If you cannot distribute so as to satisfy simultaneously your obligations under this License and any other pertinent obligations, then as a consequence you may not distribute the Program at all. For example, if a patent license would not permit royalty-free redistribution of the Program by all those who receive copies directly or indirectly through you, then the only way you could satisfy both it and this License would be to refrain entirely from distribution of the Program. If any portion of this section is held invalid or unenforceable under any particular circumstance, the balance of the section is intended to apply and the section as a whole is intended to apply in other circumstances. It is not the purpose of this section to induce you to infringe any patents or other property right claims or to contest validity of any such claims; this section has the sole purpose of protecting the integrity of the free software distribution system, which is implemented by public license practices. Many people have made generous contributions to the wide range of software distributed through that system in reliance on consistent application of that system; it is up to the author/donor to decide if he or she is willing to distribute software through any other system and a licensee cannot impose that choice. This section is intended to make thoroughly clear what is believed to be a consequence of the rest of this License. 8. If the distribution and/or use of the Program is restricted in certain countries either by patents or by copyrighted interfaces, the original copyright holder who places the Program under this License may add an explicit geographical distribution limitation excluding those countries, so that distribution is permitted only in or among countries not thus excluded. In such case, this License incorporates the limitation as if written in the body of this License. 9. The Free Software Foundation may publish revised and/or new versions of the General Public License from time to time. Such new versions will be similar in spirit to the present version, but may differ in detail to address new problems or concerns. Each version is given a distinguishing version number. If the Program specifies a version number of this License which applies to it and "any later version", you have the option of following the terms and conditions either of that version or of any later version published by the Free Software Foundation. If the Program does not specify a version number of this License, you may choose any version ever published by the Free Software Foundation. 10. If you wish to incorporate parts of the Program into other free programs whose distribution conditions are different, write to the author to ask for permission. For software which is copyrighted by the Free Software Foundation, write to the Free Software Foundation; we sometimes make exceptions for this. Our decision will be guided by the two goals of preserving the free status of all derivatives of our free software and of promoting the sharing and reuse of software generally. NO WARRANTY 11. BECAUSE THE PROGRAM IS LICENSED FREE OF CHARGE, THERE IS NO WARRANTY FOR THE PROGRAM, TO THE EXTENT PERMITTED BY APPLICABLE LAW. EXCEPT WHEN OTHERWISE STATED IN WRITING THE COPYRIGHT HOLDERS AND/OR OTHER PARTIES PROVIDE THE PROGRAM "AS IS" WITHOUT WARRANTY OF ANY KIND, EITHER EXPRESSED OR IMPLIED, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE. THE ENTIRE RISK AS TO THE QUALITY AND PERFORMANCE OF THE PROGRAM IS WITH YOU. SHOULD THE PROGRAM PROVE DEFECTIVE, YOU ASSUME THE COST OF ALL NECESSARY SERVICING, REPAIR OR CORRECTION. 12. IN NO EVENT UNLESS REQUIRED BY APPLICABLE LAW OR AGREED TO IN WRITING WILL ANY COPYRIGHT HOLDER, OR ANY OTHER PARTY WHO MAY MODIFY AND/OR REDISTRIBUTE THE PROGRAM AS PERMITTED ABOVE, BE LIABLE TO YOU FOR DAMAGES, INCLUDING ANY GENERAL, SPECIAL, INCIDENTAL OR CONSEQUENTIAL DAMAGES ARISING OUT OF THE USE OR INABILITY TO USE THE PROGRAM (INCLUDING BUT NOT LIMITED TO LOSS OF DATA OR DATA BEING RENDERED INACCURATE OR LOSSES SUSTAINED BY YOU OR THIRD PARTIES OR A FAILURE OF THE PROGRAM TO OPERATE WITH ANY OTHER PROGRAMS), EVEN IF SUCH HOLDER OR OTHER PARTY HAS BEEN ADVISED OF THE POSSIBILITY OF SUCH DAMAGES. END OF TERMS AND CONDITIONS How to Apply These Terms to Your New Programs If you develop a new program, and you want it to be of the greatest possible use to the public, the best way to achieve this is to make it free software which everyone can redistribute and change under these terms. To do so, attach the following notices to the program. It is safest to attach them to the start of each source file to most effectively convey the exclusion of warranty; and each file should have at least the "copyright" line and a pointer to where the full notice is found. Copyright (C) This program is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2 of the License, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; if not, write to the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA Also add information on how to contact you by electronic and paper mail. If the program is interactive, make it output a short notice like this when it starts in an interactive mode: Gnomovision version 69, Copyright (C) year name of author Gnomovision comes with ABSOLUTELY NO WARRANTY; for details type `show w'. This is free software, and you are welcome to redistribute it under certain conditions; type `show c' for details. The hypothetical commands `show w' and `show c' should show the appropriate parts of the General Public License. Of course, the commands you use may be called something other than `show w' and `show c'; they could even be mouse-clicks or menu items--whatever suits your program. You should also get your employer (if you work as a programmer) or your school, if any, to sign a "copyright disclaimer" for the program, if necessary. Here is a sample; alter the names: Yoyodyne, Inc., hereby disclaims all copyright interest in the program `Gnomovision' (which makes passes at compilers) written by James Hacker. , 1 April 1989 Ty Coon, President of Vice This General Public License does not permit incorporating your program into proprietary programs. If your program is a subroutine library, you may consider it more useful to permit linking proprietary applications with the library. If this is what you want to do, use the GNU Library General Public License instead of this License. smalltalk-3.2.5/COPYING.DOC0000644000175000017500000005466212123404352012076 00000000000000 GNU Free Documentation License Version 1.3, 3 November 2008 Copyright (C) 2000, 2001, 2002, 2007, 2008 Free Software Foundation, Inc. Everyone is permitted to copy and distribute verbatim copies of this license document, but changing it is not allowed. 0. PREAMBLE The purpose of this License is to make a manual, textbook, or other functional and useful document "free" in the sense of freedom: to assure everyone the effective freedom to copy and redistribute it, with or without modifying it, either commercially or noncommercially. Secondarily, this License preserves for the author and publisher a way to get credit for their work, while not being considered responsible for modifications made by others. This License is a kind of "copyleft", which means that derivative works of the document must themselves be free in the same sense. It complements the GNU General Public License, which is a copyleft license designed for free software. We have designed this License in order to use it for manuals for free software, because free software needs free documentation: a free program should come with manuals providing the same freedoms that the software does. But this License is not limited to software manuals; it can be used for any textual work, regardless of subject matter or whether it is published as a printed book. We recommend this License principally for works whose purpose is instruction or reference. 1. APPLICABILITY AND DEFINITIONS This License applies to any manual or other work, in any medium, that contains a notice placed by the copyright holder saying it can be distributed under the terms of this License. Such a notice grants a world-wide, royalty-free license, unlimited in duration, to use that work under the conditions stated herein. The "Document", below, refers to any such manual or work. Any member of the public is a licensee, and is addressed as "you". You accept the license if you copy, modify or distribute the work in a way requiring permission under copyright law. A "Modified Version" of the Document means any work containing the Document or a portion of it, either copied verbatim, or with modifications and/or translated into another language. A "Secondary Section" is a named appendix or a front-matter section of the Document that deals exclusively with the relationship of the publishers or authors of the Document to the Document's overall subject (or to related matters) and contains nothing that could fall directly within that overall subject. (Thus, if the Document is in part a textbook of mathematics, a Secondary Section may not explain any mathematics.) The relationship could be a matter of historical connection with the subject or with related matters, or of legal, commercial, philosophical, ethical or political position regarding them. The "Invariant Sections" are certain Secondary Sections whose titles are designated, as being those of Invariant Sections, in the notice that says that the Document is released under this License. If a section does not fit the above definition of Secondary then it is not allowed to be designated as Invariant. The Document may contain zero Invariant Sections. If the Document does not identify any Invariant Sections then there are none. The "Cover Texts" are certain short passages of text that are listed, as Front-Cover Texts or Back-Cover Texts, in the notice that says that the Document is released under this License. A Front-Cover Text may be at most 5 words, and a Back-Cover Text may be at most 25 words. A "Transparent" copy of the Document means a machine-readable copy, represented in a format whose specification is available to the general public, that is suitable for revising the document straightforwardly with generic text editors or (for images composed of pixels) generic paint programs or (for drawings) some widely available drawing editor, and that is suitable for input to text formatters or for automatic translation to a variety of formats suitable for input to text formatters. A copy made in an otherwise Transparent file format whose markup, or absence of markup, has been arranged to thwart or discourage subsequent modification by readers is not Transparent. An image format is not Transparent if used for any substantial amount of text. A copy that is not "Transparent" is called "Opaque". Examples of suitable formats for Transparent copies include plain ASCII without markup, Texinfo input format, LaTeX input format, SGML or XML using a publicly available DTD, and standard-conforming simple HTML, PostScript or PDF designed for human modification. Examples of transparent image formats include PNG, XCF and JPG. Opaque formats include proprietary formats that can be read and edited only by proprietary word processors, SGML or XML for which the DTD and/or processing tools are not generally available, and the machine-generated HTML, PostScript or PDF produced by some word processors for output purposes only. The "Title Page" means, for a printed book, the title page itself, plus such following pages as are needed to hold, legibly, the material this License requires to appear in the title page. For works in formats which do not have any title page as such, "Title Page" means the text near the most prominent appearance of the work's title, preceding the beginning of the body of the text. The "publisher" means any person or entity that distributes copies of the Document to the public. A section "Entitled XYZ" means a named subunit of the Document whose title either is precisely XYZ or contains XYZ in parentheses following text that translates XYZ in another language. (Here XYZ stands for a specific section name mentioned below, such as "Acknowledgements", "Dedications", "Endorsements", or "History".) To "Preserve the Title" of such a section when you modify the Document means that it remains a section "Entitled XYZ" according to this definition. The Document may include Warranty Disclaimers next to the notice which states that this License applies to the Document. These Warranty Disclaimers are considered to be included by reference in this License, but only as regards disclaiming warranties: any other implication that these Warranty Disclaimers may have is void and has no effect on the meaning of this License. 2. VERBATIM COPYING You may copy and distribute the Document in any medium, either commercially or noncommercially, provided that this License, the copyright notices, and the license notice saying this License applies to the Document are reproduced in all copies, and that you add no other conditions whatsoever to those of this License. You may not use technical measures to obstruct or control the reading or further copying of the copies you make or distribute. However, you may accept compensation in exchange for copies. If you distribute a large enough number of copies you must also follow the conditions in section 3. You may also lend copies, under the same conditions stated above, and you may publicly display copies. 3. COPYING IN QUANTITY If you publish printed copies (or copies in media that commonly have printed covers) of the Document, numbering more than 100, and the Document's license notice requires Cover Texts, you must enclose the copies in covers that carry, clearly and legibly, all these Cover Texts: Front-Cover Texts on the front cover, and Back-Cover Texts on the back cover. Both covers must also clearly and legibly identify you as the publisher of these copies. The front cover must present the full title with all words of the title equally prominent and visible. You may add other material on the covers in addition. Copying with changes limited to the covers, as long as they preserve the title of the Document and satisfy these conditions, can be treated as verbatim copying in other respects. If the required texts for either cover are too voluminous to fit legibly, you should put the first ones listed (as many as fit reasonably) on the actual cover, and continue the rest onto adjacent pages. If you publish or distribute Opaque copies of the Document numbering more than 100, you must either include a machine-readable Transparent copy along with each Opaque copy, or state in or with each Opaque copy a computer-network location from which the general network-using public has access to download using public-standard network protocols a complete Transparent copy of the Document, free of added material. If you use the latter option, you must take reasonably prudent steps, when you begin distribution of Opaque copies in quantity, to ensure that this Transparent copy will remain thus accessible at the stated location until at least one year after the last time you distribute an Opaque copy (directly or through your agents or retailers) of that edition to the public. It is requested, but not required, that you contact the authors of the Document well before redistributing any large number of copies, to give them a chance to provide you with an updated version of the Document. 4. MODIFICATIONS You may copy and distribute a Modified Version of the Document under the conditions of sections 2 and 3 above, provided that you release the Modified Version under precisely this License, with the Modified Version filling the role of the Document, thus licensing distribution and modification of the Modified Version to whoever possesses a copy of it. In addition, you must do these things in the Modified Version: A. Use in the Title Page (and on the covers, if any) a title distinct from that of the Document, and from those of previous versions (which should, if there were any, be listed in the History section of the Document). You may use the same title as a previous version if the original publisher of that version gives permission. B. List on the Title Page, as authors, one or more persons or entities responsible for authorship of the modifications in the Modified Version, together with at least five of the principal authors of the Document (all of its principal authors, if it has fewer than five), unless they release you from this requirement. C. State on the Title page the name of the publisher of the Modified Version, as the publisher. D. Preserve all the copyright notices of the Document. E. Add an appropriate copyright notice for your modifications adjacent to the other copyright notices. F. Include, immediately after the copyright notices, a license notice giving the public permission to use the Modified Version under the terms of this License, in the form shown in the Addendum below. G. Preserve in that license notice the full lists of Invariant Sections and required Cover Texts given in the Document's license notice. H. Include an unaltered copy of this License. I. Preserve the section Entitled "History", Preserve its Title, and add to it an item stating at least the title, year, new authors, and publisher of the Modified Version as given on the Title Page. If there is no section Entitled "History" in the Document, create one stating the title, year, authors, and publisher of the Document as given on its Title Page, then add an item describing the Modified Version as stated in the previous sentence. J. Preserve the network location, if any, given in the Document for public access to a Transparent copy of the Document, and likewise the network locations given in the Document for previous versions it was based on. These may be placed in the "History" section. You may omit a network location for a work that was published at least four years before the Document itself, or if the original publisher of the version it refers to gives permission. K. For any section Entitled "Acknowledgements" or "Dedications", Preserve the Title of the section, and preserve in the section all the substance and tone of each of the contributor acknowledgements and/or dedications given therein. L. Preserve all the Invariant Sections of the Document, unaltered in their text and in their titles. Section numbers or the equivalent are not considered part of the section titles. M. Delete any section Entitled "Endorsements". Such a section may not be included in the Modified Version. N. Do not retitle any existing section to be Entitled "Endorsements" or to conflict in title with any Invariant Section. O. Preserve any Warranty Disclaimers. If the Modified Version includes new front-matter sections or appendices that qualify as Secondary Sections and contain no material copied from the Document, you may at your option designate some or all of these sections as invariant. To do this, add their titles to the list of Invariant Sections in the Modified Version's license notice. These titles must be distinct from any other section titles. You may add a section Entitled "Endorsements", provided it contains nothing but endorsements of your Modified Version by various parties--for example, statements of peer review or that the text has been approved by an organization as the authoritative definition of a standard. You may add a passage of up to five words as a Front-Cover Text, and a passage of up to 25 words as a Back-Cover Text, to the end of the list of Cover Texts in the Modified Version. Only one passage of Front-Cover Text and one of Back-Cover Text may be added by (or through arrangements made by) any one entity. If the Document already includes a cover text for the same cover, previously added by you or by arrangement made by the same entity you are acting on behalf of, you may not add another; but you may replace the old one, on explicit permission from the previous publisher that added the old one. The author(s) and publisher(s) of the Document do not by this License give permission to use their names for publicity for or to assert or imply endorsement of any Modified Version. 5. COMBINING DOCUMENTS You may combine the Document with other documents released under this License, under the terms defined in section 4 above for modified versions, provided that you include in the combination all of the Invariant Sections of all of the original documents, unmodified, and list them all as Invariant Sections of your combined work in its license notice, and that you preserve all their Warranty Disclaimers. The combined work need only contain one copy of this License, and multiple identical Invariant Sections may be replaced with a single copy. If there are multiple Invariant Sections with the same name but different contents, make the title of each such section unique by adding at the end of it, in parentheses, the name of the original author or publisher of that section if known, or else a unique number. Make the same adjustment to the section titles in the list of Invariant Sections in the license notice of the combined work. In the combination, you must combine any sections Entitled "History" in the various original documents, forming one section Entitled "History"; likewise combine any sections Entitled "Acknowledgements", and any sections Entitled "Dedications". You must delete all sections Entitled "Endorsements". 6. COLLECTIONS OF DOCUMENTS You may make a collection consisting of the Document and other documents released under this License, and replace the individual copies of this License in the various documents with a single copy that is included in the collection, provided that you follow the rules of this License for verbatim copying of each of the documents in all other respects. You may extract a single document from such a collection, and distribute it individually under this License, provided you insert a copy of this License into the extracted document, and follow this License in all other respects regarding verbatim copying of that document. 7. AGGREGATION WITH INDEPENDENT WORKS A compilation of the Document or its derivatives with other separate and independent documents or works, in or on a volume of a storage or distribution medium, is called an "aggregate" if the copyright resulting from the compilation is not used to limit the legal rights of the compilation's users beyond what the individual works permit. When the Document is included in an aggregate, this License does not apply to the other works in the aggregate which are not themselves derivative works of the Document. If the Cover Text requirement of section 3 is applicable to these copies of the Document, then if the Document is less than one half of the entire aggregate, the Document's Cover Texts may be placed on covers that bracket the Document within the aggregate, or the electronic equivalent of covers if the Document is in electronic form. Otherwise they must appear on printed covers that bracket the whole aggregate. 8. TRANSLATION Translation is considered a kind of modification, so you may distribute translations of the Document under the terms of section 4. Replacing Invariant Sections with translations requires special permission from their copyright holders, but you may include translations of some or all Invariant Sections in addition to the original versions of these Invariant Sections. You may include a translation of this License, and all the license notices in the Document, and any Warranty Disclaimers, provided that you also include the original English version of this License and the original versions of those notices and disclaimers. In case of a disagreement between the translation and the original version of this License or a notice or disclaimer, the original version will prevail. If a section in the Document is Entitled "Acknowledgements", "Dedications", or "History", the requirement (section 4) to Preserve its Title (section 1) will typically require changing the actual title. 9. TERMINATION You may not copy, modify, sublicense, or distribute the Document except as expressly provided under this License. Any attempt otherwise to copy, modify, sublicense, or distribute it is void, and will automatically terminate your rights under this License. However, if you cease all violation of this License, then your license from a particular copyright holder is reinstated (a) provisionally, unless and until the copyright holder explicitly and finally terminates your license, and (b) permanently, if the copyright holder fails to notify you of the violation by some reasonable means prior to 60 days after the cessation. Moreover, your license from a particular copyright holder is reinstated permanently if the copyright holder notifies you of the violation by some reasonable means, this is the first time you have received notice of violation of this License (for any work) from that copyright holder, and you cure the violation prior to 30 days after your receipt of the notice. Termination of your rights under this section does not terminate the licenses of parties who have received copies or rights from you under this License. If your rights have been terminated and not permanently reinstated, receipt of a copy of some or all of the same material does not give you any rights to use it. 10. FUTURE REVISIONS OF THIS LICENSE The Free Software Foundation may publish new, revised versions of the GNU Free Documentation License from time to time. Such new versions will be similar in spirit to the present version, but may differ in detail to address new problems or concerns. See http://www.gnu.org/copyleft/. Each version of the License is given a distinguishing version number. If the Document specifies that a particular numbered version of this License "or any later version" applies to it, you have the option of following the terms and conditions either of that specified version or of any later version that has been published (not as a draft) by the Free Software Foundation. If the Document does not specify a version number of this License, you may choose any version ever published (not as a draft) by the Free Software Foundation. If the Document specifies that a proxy can decide which future versions of this License can be used, that proxy's public statement of acceptance of a version permanently authorizes you to choose that version for the Document. 11. RELICENSING "Massive Multiauthor Collaboration Site" (or "MMC Site") means any World Wide Web server that publishes copyrightable works and also provides prominent facilities for anybody to edit those works. A public wiki that anybody can edit is an example of such a server. A "Massive Multiauthor Collaboration" (or "MMC") contained in the site means any set of copyrightable works thus published on the MMC site. "CC-BY-SA" means the Creative Commons Attribution-Share Alike 3.0 license published by Creative Commons Corporation, a not-for-profit corporation with a principal place of business in San Francisco, California, as well as future copyleft versions of that license published by that same organization. "Incorporate" means to publish or republish a Document, in whole or in part, as part of another Document. An MMC is "eligible for relicensing" if it is licensed under this License, and if all works that were first published under this License somewhere other than this MMC, and subsequently incorporated in whole or in part into the MMC, (1) had no cover texts or invariant sections, and (2) were thus incorporated prior to November 1, 2008. The operator of an MMC Site may republish an MMC contained in the site under CC-BY-SA on the same site at any time before August 1, 2009, provided the MMC is eligible for relicensing. ADDENDUM: How to use this License for your documents To use this License in a document you have written, include a copy of the License in the document and put the following copyright and license notices just after the title page: Copyright (c) YEAR YOUR NAME. Permission is granted to copy, distribute and/or modify this document under the terms of the GNU Free Documentation License, Version 1.3 or any later version published by the Free Software Foundation; with no Invariant Sections, no Front-Cover Texts, and no Back-Cover Texts. A copy of the license is included in the section entitled "GNU Free Documentation License". If you have Invariant Sections, Front-Cover Texts and Back-Cover Texts, replace the "with...Texts." line with this: with the Invariant Sections being LIST THEIR TITLES, with the Front-Cover Texts being LIST, and with the Back-Cover Texts being LIST. If you have Invariant Sections without Cover Texts, or some other combination of the three, merge those two alternatives to suit the situation. If your document contains nontrivial examples of program code, we recommend releasing these examples in parallel under your choice of free software license, such as the GNU General Public License, to permit their use in free software. smalltalk-3.2.5/build-aux/0000755000175000017500000000000012130456003012372 500000000000000smalltalk-3.2.5/build-aux/fault.m40000644000175000017500000000671012123404352013675 00000000000000# fault.m4 serial 5 (libsigsegv-2.2) dnl Copyright (C) 2002-2003 Bruno Haible dnl This file is free software, distributed under the terms of the GNU dnl General Public License. As a special exception to the GNU General dnl Public License, this file may be distributed as part of a program dnl that contains a configuration script generated by Autoconf, under dnl the same distribution terms as the rest of that program. dnl How to write a SIGSEGV handler with access to the fault address. dnl SV_TRY_FAULT(KIND, CACHESYMBOL, KNOWN-SYSTEMS, dnl INCLUDES, FAULT_HANDLER_ARGLIST, FAULT_ADDRESS, [INSTALLCODE]) AC_DEFUN([SV_TRY_FAULT], [ AC_REQUIRE([AC_PROG_CC]) AC_REQUIRE([AC_CANONICAL_HOST]) AC_CACHE_CHECK([whether a fault handler according to $1 works], [$2], [ AC_RUN_IFELSE([ AC_LANG_SOURCE([[ #include #include #if HAVE_SYS_SIGNAL_H # include #endif $4 #include #include #if HAVE_MMAP_DEVZERO # include # ifndef MAP_FILE # define MAP_FILE 0 # endif #endif #ifndef PROT_NONE # define PROT_NONE 0 #endif #if HAVE_MMAP_ANON # define zero_fd -1 # define map_flags MAP_ANON | MAP_PRIVATE #elif HAVE_MMAP_ANONYMOUS # define zero_fd -1 # define map_flags MAP_ANONYMOUS | MAP_PRIVATE #elif HAVE_MMAP_DEVZERO static int zero_fd; # define map_flags MAP_FILE | MAP_PRIVATE #endif unsigned long page; int handler_called = 0; void sigsegv_handler ($5) { void *fault_address = (void *) ($6); handler_called++; if (handler_called == 10) exit (4); if (fault_address != (void*)(page + 0x678)) exit (3); if (mprotect ((void *) page, 0x10000, PROT_READ | PROT_WRITE) < 0) exit (2); } void crasher (unsigned long p) { *(int *) (p + 0x678) = 42; } int main () { void *p; struct sigaction action; /* Preparations. */ #if !HAVE_MMAP_ANON && !HAVE_MMAP_ANONYMOUS && HAVE_MMAP_DEVZERO zero_fd = open ("/dev/zero", O_RDONLY, 0644); #endif /* Setup some mmaped memory. */ #ifdef __hpux /* HP-UX 10 mmap() often fails when given a hint. So give the OS complete freedom about the address range. */ p = mmap ((void *) 0, 0x10000, PROT_READ | PROT_WRITE, map_flags, zero_fd, 0); #else p = mmap ((void *) 0x12340000, 0x10000, PROT_READ | PROT_WRITE, map_flags, zero_fd, 0); #endif if (p == (void *)(-1)) exit (2); page = (unsigned long) p; /* Make it read-only. */ if (mprotect ((void *) page, 0x10000, PROT_READ) < 0) exit (2); /* Install the SIGSEGV handler. */ sigemptyset(&action.sa_mask); ]m4_if([$7], [], [ action.sa_handler = (void (*) (int)) &sigsegv_handler; action.sa_flags = 0; ], [$7])[ sigaction (SIGSEGV, &action, (struct sigaction *) NULL); sigaction (SIGBUS, &action, (struct sigaction *) NULL); /* The first write access should invoke the handler and then complete. */ crasher (page); /* The second write access should not invoke the handler. */ crasher (page); /* Check that the handler was called only once. */ if (handler_called != 1) exit (1); /* Test passed! */ return 0; }]])], [$2=yes], [$2=no], [case "$host" in m4_if([$3], [], [], [[$3]) $2=yes ;;]) *) AC_LINK_IFELSE([ AC_LANG_PROGRAM([[ #include $4 void sigsegv_handler ($5) { void *fault_address = (void *) ($6); } ]], [[struct sigaction action; $7]])], [$2="guessing no"], [$2=no]) ;; esac ]) ]) ]) smalltalk-3.2.5/build-aux/libtool.m40000644000175000017500000106000712130455416014233 00000000000000# libtool.m4 - Configure libtool for the host system. -*-Autoconf-*- # # Copyright (C) 1996, 1997, 1998, 1999, 2000, 2001, 2003, 2004, 2005, # 2006, 2007, 2008, 2009, 2010, 2011 Free Software # Foundation, Inc. # Written by Gordon Matzigkeit, 1996 # # This file is free software; the Free Software Foundation gives # unlimited permission to copy and/or distribute it, with or without # modifications, as long as this notice is preserved. m4_define([_LT_COPYING], [dnl # Copyright (C) 1996, 1997, 1998, 1999, 2000, 2001, 2003, 2004, 2005, # 2006, 2007, 2008, 2009, 2010, 2011 Free Software # Foundation, Inc. # Written by Gordon Matzigkeit, 1996 # # This file is part of GNU Libtool. # # GNU Libtool is free software; you can redistribute it and/or # modify it under the terms of the GNU General Public License as # published by the Free Software Foundation; either version 2 of # the License, or (at your option) any later version. # # As a special exception to the GNU General Public License, # if you distribute this file as part of a program or library that # is built using GNU Libtool, you may include this file under the # same distribution terms that you use for the rest of that program. # # GNU Libtool is distributed in the hope that it will be useful, # but WITHOUT ANY WARRANTY; without even the implied warranty of # MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the # GNU General Public License for more details. # # You should have received a copy of the GNU General Public License # along with GNU Libtool; see the file COPYING. If not, a copy # can be downloaded from http://www.gnu.org/licenses/gpl.html, or # obtained by writing to the Free Software Foundation, Inc., # 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. ]) # serial 57 LT_INIT # LT_PREREQ(VERSION) # ------------------ # Complain and exit if this libtool version is less that VERSION. m4_defun([LT_PREREQ], [m4_if(m4_version_compare(m4_defn([LT_PACKAGE_VERSION]), [$1]), -1, [m4_default([$3], [m4_fatal([Libtool version $1 or higher is required], 63)])], [$2])]) # _LT_CHECK_BUILDDIR # ------------------ # Complain if the absolute build directory name contains unusual characters m4_defun([_LT_CHECK_BUILDDIR], [case `pwd` in *\ * | *\ *) AC_MSG_WARN([Libtool does not cope well with whitespace in `pwd`]) ;; esac ]) # LT_INIT([OPTIONS]) # ------------------ AC_DEFUN([LT_INIT], [AC_PREREQ([2.58])dnl We use AC_INCLUDES_DEFAULT AC_REQUIRE([AC_CONFIG_AUX_DIR_DEFAULT])dnl AC_BEFORE([$0], [LT_LANG])dnl AC_BEFORE([$0], [LT_OUTPUT])dnl AC_BEFORE([$0], [LTDL_INIT])dnl m4_require([_LT_CHECK_BUILDDIR])dnl dnl Autoconf doesn't catch unexpanded LT_ macros by default: m4_pattern_forbid([^_?LT_[A-Z_]+$])dnl m4_pattern_allow([^(_LT_EOF|LT_DLGLOBAL|LT_DLLAZY_OR_NOW|LT_MULTI_MODULE)$])dnl dnl aclocal doesn't pull ltoptions.m4, ltsugar.m4, or ltversion.m4 dnl unless we require an AC_DEFUNed macro: AC_REQUIRE([LTOPTIONS_VERSION])dnl AC_REQUIRE([LTSUGAR_VERSION])dnl AC_REQUIRE([LTVERSION_VERSION])dnl AC_REQUIRE([LTOBSOLETE_VERSION])dnl m4_require([_LT_PROG_LTMAIN])dnl _LT_SHELL_INIT([SHELL=${CONFIG_SHELL-/bin/sh}]) dnl Parse OPTIONS _LT_SET_OPTIONS([$0], [$1]) # This can be used to rebuild libtool when needed LIBTOOL_DEPS="$ltmain" # Always use our own libtool. LIBTOOL='$(SHELL) $(top_builddir)/libtool' AC_SUBST(LIBTOOL)dnl _LT_SETUP # Only expand once: m4_define([LT_INIT]) ])# LT_INIT # Old names: AU_ALIAS([AC_PROG_LIBTOOL], [LT_INIT]) AU_ALIAS([AM_PROG_LIBTOOL], [LT_INIT]) dnl aclocal-1.4 backwards compatibility: dnl AC_DEFUN([AC_PROG_LIBTOOL], []) dnl AC_DEFUN([AM_PROG_LIBTOOL], []) # _LT_CC_BASENAME(CC) # ------------------- # Calculate cc_basename. Skip known compiler wrappers and cross-prefix. m4_defun([_LT_CC_BASENAME], [for cc_temp in $1""; do case $cc_temp in compile | *[[\\/]]compile | ccache | *[[\\/]]ccache ) ;; distcc | *[[\\/]]distcc | purify | *[[\\/]]purify ) ;; \-*) ;; *) break;; esac done cc_basename=`$ECHO "$cc_temp" | $SED "s%.*/%%; s%^$host_alias-%%"` ]) # _LT_FILEUTILS_DEFAULTS # ---------------------- # It is okay to use these file commands and assume they have been set # sensibly after `m4_require([_LT_FILEUTILS_DEFAULTS])'. m4_defun([_LT_FILEUTILS_DEFAULTS], [: ${CP="cp -f"} : ${MV="mv -f"} : ${RM="rm -f"} ])# _LT_FILEUTILS_DEFAULTS # _LT_SETUP # --------- m4_defun([_LT_SETUP], [AC_REQUIRE([AC_CANONICAL_HOST])dnl AC_REQUIRE([AC_CANONICAL_BUILD])dnl AC_REQUIRE([_LT_PREPARE_SED_QUOTE_VARS])dnl AC_REQUIRE([_LT_PROG_ECHO_BACKSLASH])dnl _LT_DECL([], [PATH_SEPARATOR], [1], [The PATH separator for the build system])dnl dnl _LT_DECL([], [host_alias], [0], [The host system])dnl _LT_DECL([], [host], [0])dnl _LT_DECL([], [host_os], [0])dnl dnl _LT_DECL([], [build_alias], [0], [The build system])dnl _LT_DECL([], [build], [0])dnl _LT_DECL([], [build_os], [0])dnl dnl AC_REQUIRE([AC_PROG_CC])dnl AC_REQUIRE([LT_PATH_LD])dnl AC_REQUIRE([LT_PATH_NM])dnl dnl AC_REQUIRE([AC_PROG_LN_S])dnl test -z "$LN_S" && LN_S="ln -s" _LT_DECL([], [LN_S], [1], [Whether we need soft or hard links])dnl dnl AC_REQUIRE([LT_CMD_MAX_LEN])dnl _LT_DECL([objext], [ac_objext], [0], [Object file suffix (normally "o")])dnl _LT_DECL([], [exeext], [0], [Executable file suffix (normally "")])dnl dnl m4_require([_LT_FILEUTILS_DEFAULTS])dnl m4_require([_LT_CHECK_SHELL_FEATURES])dnl m4_require([_LT_PATH_CONVERSION_FUNCTIONS])dnl m4_require([_LT_CMD_RELOAD])dnl m4_require([_LT_CHECK_MAGIC_METHOD])dnl m4_require([_LT_CHECK_SHAREDLIB_FROM_LINKLIB])dnl m4_require([_LT_CMD_OLD_ARCHIVE])dnl m4_require([_LT_CMD_GLOBAL_SYMBOLS])dnl m4_require([_LT_WITH_SYSROOT])dnl _LT_CONFIG_LIBTOOL_INIT([ # See if we are running on zsh, and set the options which allow our # commands through without removal of \ escapes INIT. if test -n "\${ZSH_VERSION+set}" ; then setopt NO_GLOB_SUBST fi ]) if test -n "${ZSH_VERSION+set}" ; then setopt NO_GLOB_SUBST fi _LT_CHECK_OBJDIR m4_require([_LT_TAG_COMPILER])dnl case $host_os in aix3*) # AIX sometimes has problems with the GCC collect2 program. For some # reason, if we set the COLLECT_NAMES environment variable, the problems # vanish in a puff of smoke. if test "X${COLLECT_NAMES+set}" != Xset; then COLLECT_NAMES= export COLLECT_NAMES fi ;; esac # Global variables: ofile=libtool can_build_shared=yes # All known linkers require a `.a' archive for static linking (except MSVC, # which needs '.lib'). libext=a with_gnu_ld="$lt_cv_prog_gnu_ld" old_CC="$CC" old_CFLAGS="$CFLAGS" # Set sane defaults for various variables test -z "$CC" && CC=cc test -z "$LTCC" && LTCC=$CC test -z "$LTCFLAGS" && LTCFLAGS=$CFLAGS test -z "$LD" && LD=ld test -z "$ac_objext" && ac_objext=o _LT_CC_BASENAME([$compiler]) # Only perform the check for file, if the check method requires it test -z "$MAGIC_CMD" && MAGIC_CMD=file case $deplibs_check_method in file_magic*) if test "$file_magic_cmd" = '$MAGIC_CMD'; then _LT_PATH_MAGIC fi ;; esac # Use C for the default configuration in the libtool script LT_SUPPORTED_TAG([CC]) _LT_LANG_C_CONFIG _LT_LANG_DEFAULT_CONFIG _LT_CONFIG_COMMANDS ])# _LT_SETUP # _LT_PREPARE_SED_QUOTE_VARS # -------------------------- # Define a few sed substitution that help us do robust quoting. m4_defun([_LT_PREPARE_SED_QUOTE_VARS], [# Backslashify metacharacters that are still active within # double-quoted strings. sed_quote_subst='s/\([["`$\\]]\)/\\\1/g' # Same as above, but do not quote variable references. double_quote_subst='s/\([["`\\]]\)/\\\1/g' # Sed substitution to delay expansion of an escaped shell variable in a # double_quote_subst'ed string. delay_variable_subst='s/\\\\\\\\\\\$/\\\\\\$/g' # Sed substitution to delay expansion of an escaped single quote. delay_single_quote_subst='s/'\''/'\'\\\\\\\'\''/g' # Sed substitution to avoid accidental globbing in evaled expressions no_glob_subst='s/\*/\\\*/g' ]) # _LT_PROG_LTMAIN # --------------- # Note that this code is called both from `configure', and `config.status' # now that we use AC_CONFIG_COMMANDS to generate libtool. Notably, # `config.status' has no value for ac_aux_dir unless we are using Automake, # so we pass a copy along to make sure it has a sensible value anyway. m4_defun([_LT_PROG_LTMAIN], [m4_ifdef([AC_REQUIRE_AUX_FILE], [AC_REQUIRE_AUX_FILE([ltmain.sh])])dnl _LT_CONFIG_LIBTOOL_INIT([ac_aux_dir='$ac_aux_dir']) ltmain="$ac_aux_dir/ltmain.sh" ])# _LT_PROG_LTMAIN ## ------------------------------------- ## ## Accumulate code for creating libtool. ## ## ------------------------------------- ## # So that we can recreate a full libtool script including additional # tags, we accumulate the chunks of code to send to AC_CONFIG_COMMANDS # in macros and then make a single call at the end using the `libtool' # label. # _LT_CONFIG_LIBTOOL_INIT([INIT-COMMANDS]) # ---------------------------------------- # Register INIT-COMMANDS to be passed to AC_CONFIG_COMMANDS later. m4_define([_LT_CONFIG_LIBTOOL_INIT], [m4_ifval([$1], [m4_append([_LT_OUTPUT_LIBTOOL_INIT], [$1 ])])]) # Initialize. m4_define([_LT_OUTPUT_LIBTOOL_INIT]) # _LT_CONFIG_LIBTOOL([COMMANDS]) # ------------------------------ # Register COMMANDS to be passed to AC_CONFIG_COMMANDS later. m4_define([_LT_CONFIG_LIBTOOL], [m4_ifval([$1], [m4_append([_LT_OUTPUT_LIBTOOL_COMMANDS], [$1 ])])]) # Initialize. m4_define([_LT_OUTPUT_LIBTOOL_COMMANDS]) # _LT_CONFIG_SAVE_COMMANDS([COMMANDS], [INIT_COMMANDS]) # ----------------------------------------------------- m4_defun([_LT_CONFIG_SAVE_COMMANDS], [_LT_CONFIG_LIBTOOL([$1]) _LT_CONFIG_LIBTOOL_INIT([$2]) ]) # _LT_FORMAT_COMMENT([COMMENT]) # ----------------------------- # Add leading comment marks to the start of each line, and a trailing # full-stop to the whole comment if one is not present already. m4_define([_LT_FORMAT_COMMENT], [m4_ifval([$1], [ m4_bpatsubst([m4_bpatsubst([$1], [^ *], [# ])], [['`$\]], [\\\&])]m4_bmatch([$1], [[!?.]$], [], [.]) )]) ## ------------------------ ## ## FIXME: Eliminate VARNAME ## ## ------------------------ ## # _LT_DECL([CONFIGNAME], VARNAME, VALUE, [DESCRIPTION], [IS-TAGGED?]) # ------------------------------------------------------------------- # CONFIGNAME is the name given to the value in the libtool script. # VARNAME is the (base) name used in the configure script. # VALUE may be 0, 1 or 2 for a computed quote escaped value based on # VARNAME. Any other value will be used directly. m4_define([_LT_DECL], [lt_if_append_uniq([lt_decl_varnames], [$2], [, ], [lt_dict_add_subkey([lt_decl_dict], [$2], [libtool_name], [m4_ifval([$1], [$1], [$2])]) lt_dict_add_subkey([lt_decl_dict], [$2], [value], [$3]) m4_ifval([$4], [lt_dict_add_subkey([lt_decl_dict], [$2], [description], [$4])]) lt_dict_add_subkey([lt_decl_dict], [$2], [tagged?], [m4_ifval([$5], [yes], [no])])]) ]) # _LT_TAGDECL([CONFIGNAME], VARNAME, VALUE, [DESCRIPTION]) # -------------------------------------------------------- m4_define([_LT_TAGDECL], [_LT_DECL([$1], [$2], [$3], [$4], [yes])]) # lt_decl_tag_varnames([SEPARATOR], [VARNAME1...]) # ------------------------------------------------ m4_define([lt_decl_tag_varnames], [_lt_decl_filter([tagged?], [yes], $@)]) # _lt_decl_filter(SUBKEY, VALUE, [SEPARATOR], [VARNAME1..]) # --------------------------------------------------------- m4_define([_lt_decl_filter], [m4_case([$#], [0], [m4_fatal([$0: too few arguments: $#])], [1], [m4_fatal([$0: too few arguments: $#: $1])], [2], [lt_dict_filter([lt_decl_dict], [$1], [$2], [], lt_decl_varnames)], [3], [lt_dict_filter([lt_decl_dict], [$1], [$2], [$3], lt_decl_varnames)], [lt_dict_filter([lt_decl_dict], $@)])[]dnl ]) # lt_decl_quote_varnames([SEPARATOR], [VARNAME1...]) # -------------------------------------------------- m4_define([lt_decl_quote_varnames], [_lt_decl_filter([value], [1], $@)]) # lt_decl_dquote_varnames([SEPARATOR], [VARNAME1...]) # --------------------------------------------------- m4_define([lt_decl_dquote_varnames], [_lt_decl_filter([value], [2], $@)]) # lt_decl_varnames_tagged([SEPARATOR], [VARNAME1...]) # --------------------------------------------------- m4_define([lt_decl_varnames_tagged], [m4_assert([$# <= 2])dnl _$0(m4_quote(m4_default([$1], [[, ]])), m4_ifval([$2], [[$2]], [m4_dquote(lt_decl_tag_varnames)]), m4_split(m4_normalize(m4_quote(_LT_TAGS)), [ ]))]) m4_define([_lt_decl_varnames_tagged], [m4_ifval([$3], [lt_combine([$1], [$2], [_], $3)])]) # lt_decl_all_varnames([SEPARATOR], [VARNAME1...]) # ------------------------------------------------ m4_define([lt_decl_all_varnames], [_$0(m4_quote(m4_default([$1], [[, ]])), m4_if([$2], [], m4_quote(lt_decl_varnames), m4_quote(m4_shift($@))))[]dnl ]) m4_define([_lt_decl_all_varnames], [lt_join($@, lt_decl_varnames_tagged([$1], lt_decl_tag_varnames([[, ]], m4_shift($@))))dnl ]) # _LT_CONFIG_STATUS_DECLARE([VARNAME]) # ------------------------------------ # Quote a variable value, and forward it to `config.status' so that its # declaration there will have the same value as in `configure'. VARNAME # must have a single quote delimited value for this to work. m4_define([_LT_CONFIG_STATUS_DECLARE], [$1='`$ECHO "$][$1" | $SED "$delay_single_quote_subst"`']) # _LT_CONFIG_STATUS_DECLARATIONS # ------------------------------ # We delimit libtool config variables with single quotes, so when # we write them to config.status, we have to be sure to quote all # embedded single quotes properly. In configure, this macro expands # each variable declared with _LT_DECL (and _LT_TAGDECL) into: # # ='`$ECHO "$" | $SED "$delay_single_quote_subst"`' m4_defun([_LT_CONFIG_STATUS_DECLARATIONS], [m4_foreach([_lt_var], m4_quote(lt_decl_all_varnames), [m4_n([_LT_CONFIG_STATUS_DECLARE(_lt_var)])])]) # _LT_LIBTOOL_TAGS # ---------------- # Output comment and list of tags supported by the script m4_defun([_LT_LIBTOOL_TAGS], [_LT_FORMAT_COMMENT([The names of the tagged configurations supported by this script])dnl available_tags="_LT_TAGS"dnl ]) # _LT_LIBTOOL_DECLARE(VARNAME, [TAG]) # ----------------------------------- # Extract the dictionary values for VARNAME (optionally with TAG) and # expand to a commented shell variable setting: # # # Some comment about what VAR is for. # visible_name=$lt_internal_name m4_define([_LT_LIBTOOL_DECLARE], [_LT_FORMAT_COMMENT(m4_quote(lt_dict_fetch([lt_decl_dict], [$1], [description])))[]dnl m4_pushdef([_libtool_name], m4_quote(lt_dict_fetch([lt_decl_dict], [$1], [libtool_name])))[]dnl m4_case(m4_quote(lt_dict_fetch([lt_decl_dict], [$1], [value])), [0], [_libtool_name=[$]$1], [1], [_libtool_name=$lt_[]$1], [2], [_libtool_name=$lt_[]$1], [_libtool_name=lt_dict_fetch([lt_decl_dict], [$1], [value])])[]dnl m4_ifval([$2], [_$2])[]m4_popdef([_libtool_name])[]dnl ]) # _LT_LIBTOOL_CONFIG_VARS # ----------------------- # Produce commented declarations of non-tagged libtool config variables # suitable for insertion in the LIBTOOL CONFIG section of the `libtool' # script. Tagged libtool config variables (even for the LIBTOOL CONFIG # section) are produced by _LT_LIBTOOL_TAG_VARS. m4_defun([_LT_LIBTOOL_CONFIG_VARS], [m4_foreach([_lt_var], m4_quote(_lt_decl_filter([tagged?], [no], [], lt_decl_varnames)), [m4_n([_LT_LIBTOOL_DECLARE(_lt_var)])])]) # _LT_LIBTOOL_TAG_VARS(TAG) # ------------------------- m4_define([_LT_LIBTOOL_TAG_VARS], [m4_foreach([_lt_var], m4_quote(lt_decl_tag_varnames), [m4_n([_LT_LIBTOOL_DECLARE(_lt_var, [$1])])])]) # _LT_TAGVAR(VARNAME, [TAGNAME]) # ------------------------------ m4_define([_LT_TAGVAR], [m4_ifval([$2], [$1_$2], [$1])]) # _LT_CONFIG_COMMANDS # ------------------- # Send accumulated output to $CONFIG_STATUS. Thanks to the lists of # variables for single and double quote escaping we saved from calls # to _LT_DECL, we can put quote escaped variables declarations # into `config.status', and then the shell code to quote escape them in # for loops in `config.status'. Finally, any additional code accumulated # from calls to _LT_CONFIG_LIBTOOL_INIT is expanded. m4_defun([_LT_CONFIG_COMMANDS], [AC_PROVIDE_IFELSE([LT_OUTPUT], dnl If the libtool generation code has been placed in $CONFIG_LT, dnl instead of duplicating it all over again into config.status, dnl then we will have config.status run $CONFIG_LT later, so it dnl needs to know what name is stored there: [AC_CONFIG_COMMANDS([libtool], [$SHELL $CONFIG_LT || AS_EXIT(1)], [CONFIG_LT='$CONFIG_LT'])], dnl If the libtool generation code is destined for config.status, dnl expand the accumulated commands and init code now: [AC_CONFIG_COMMANDS([libtool], [_LT_OUTPUT_LIBTOOL_COMMANDS], [_LT_OUTPUT_LIBTOOL_COMMANDS_INIT])]) ])#_LT_CONFIG_COMMANDS # Initialize. m4_define([_LT_OUTPUT_LIBTOOL_COMMANDS_INIT], [ # The HP-UX ksh and POSIX shell print the target directory to stdout # if CDPATH is set. (unset CDPATH) >/dev/null 2>&1 && unset CDPATH sed_quote_subst='$sed_quote_subst' double_quote_subst='$double_quote_subst' delay_variable_subst='$delay_variable_subst' _LT_CONFIG_STATUS_DECLARATIONS LTCC='$LTCC' LTCFLAGS='$LTCFLAGS' compiler='$compiler_DEFAULT' # A function that is used when there is no print builtin or printf. func_fallback_echo () { eval 'cat <<_LTECHO_EOF \$[]1 _LTECHO_EOF' } # Quote evaled strings. for var in lt_decl_all_varnames([[ \ ]], lt_decl_quote_varnames); do case \`eval \\\\\$ECHO \\\\""\\\\\$\$var"\\\\"\` in *[[\\\\\\\`\\"\\\$]]*) eval "lt_\$var=\\\\\\"\\\`\\\$ECHO \\"\\\$\$var\\" | \\\$SED \\"\\\$sed_quote_subst\\"\\\`\\\\\\"" ;; *) eval "lt_\$var=\\\\\\"\\\$\$var\\\\\\"" ;; esac done # Double-quote double-evaled strings. for var in lt_decl_all_varnames([[ \ ]], lt_decl_dquote_varnames); do case \`eval \\\\\$ECHO \\\\""\\\\\$\$var"\\\\"\` in *[[\\\\\\\`\\"\\\$]]*) eval "lt_\$var=\\\\\\"\\\`\\\$ECHO \\"\\\$\$var\\" | \\\$SED -e \\"\\\$double_quote_subst\\" -e \\"\\\$sed_quote_subst\\" -e \\"\\\$delay_variable_subst\\"\\\`\\\\\\"" ;; *) eval "lt_\$var=\\\\\\"\\\$\$var\\\\\\"" ;; esac done _LT_OUTPUT_LIBTOOL_INIT ]) # _LT_GENERATED_FILE_INIT(FILE, [COMMENT]) # ------------------------------------ # Generate a child script FILE with all initialization necessary to # reuse the environment learned by the parent script, and make the # file executable. If COMMENT is supplied, it is inserted after the # `#!' sequence but before initialization text begins. After this # macro, additional text can be appended to FILE to form the body of # the child script. The macro ends with non-zero status if the # file could not be fully written (such as if the disk is full). m4_ifdef([AS_INIT_GENERATED], [m4_defun([_LT_GENERATED_FILE_INIT],[AS_INIT_GENERATED($@)])], [m4_defun([_LT_GENERATED_FILE_INIT], [m4_require([AS_PREPARE])]dnl [m4_pushdef([AS_MESSAGE_LOG_FD])]dnl [lt_write_fail=0 cat >$1 <<_ASEOF || lt_write_fail=1 #! $SHELL # Generated by $as_me. $2 SHELL=\${CONFIG_SHELL-$SHELL} export SHELL _ASEOF cat >>$1 <<\_ASEOF || lt_write_fail=1 AS_SHELL_SANITIZE _AS_PREPARE exec AS_MESSAGE_FD>&1 _ASEOF test $lt_write_fail = 0 && chmod +x $1[]dnl m4_popdef([AS_MESSAGE_LOG_FD])])])# _LT_GENERATED_FILE_INIT # LT_OUTPUT # --------- # This macro allows early generation of the libtool script (before # AC_OUTPUT is called), incase it is used in configure for compilation # tests. AC_DEFUN([LT_OUTPUT], [: ${CONFIG_LT=./config.lt} AC_MSG_NOTICE([creating $CONFIG_LT]) _LT_GENERATED_FILE_INIT(["$CONFIG_LT"], [# Run this file to recreate a libtool stub with the current configuration.]) cat >>"$CONFIG_LT" <<\_LTEOF lt_cl_silent=false exec AS_MESSAGE_LOG_FD>>config.log { echo AS_BOX([Running $as_me.]) } >&AS_MESSAGE_LOG_FD lt_cl_help="\ \`$as_me' creates a local libtool stub from the current configuration, for use in further configure time tests before the real libtool is generated. Usage: $[0] [[OPTIONS]] -h, --help print this help, then exit -V, --version print version number, then exit -q, --quiet do not print progress messages -d, --debug don't remove temporary files Report bugs to ." lt_cl_version="\ m4_ifset([AC_PACKAGE_NAME], [AC_PACKAGE_NAME ])config.lt[]dnl m4_ifset([AC_PACKAGE_VERSION], [ AC_PACKAGE_VERSION]) configured by $[0], generated by m4_PACKAGE_STRING. Copyright (C) 2011 Free Software Foundation, Inc. This config.lt script is free software; the Free Software Foundation gives unlimited permision to copy, distribute and modify it." while test $[#] != 0 do case $[1] in --version | --v* | -V ) echo "$lt_cl_version"; exit 0 ;; --help | --h* | -h ) echo "$lt_cl_help"; exit 0 ;; --debug | --d* | -d ) debug=: ;; --quiet | --q* | --silent | --s* | -q ) lt_cl_silent=: ;; -*) AC_MSG_ERROR([unrecognized option: $[1] Try \`$[0] --help' for more information.]) ;; *) AC_MSG_ERROR([unrecognized argument: $[1] Try \`$[0] --help' for more information.]) ;; esac shift done if $lt_cl_silent; then exec AS_MESSAGE_FD>/dev/null fi _LTEOF cat >>"$CONFIG_LT" <<_LTEOF _LT_OUTPUT_LIBTOOL_COMMANDS_INIT _LTEOF cat >>"$CONFIG_LT" <<\_LTEOF AC_MSG_NOTICE([creating $ofile]) _LT_OUTPUT_LIBTOOL_COMMANDS AS_EXIT(0) _LTEOF chmod +x "$CONFIG_LT" # configure is writing to config.log, but config.lt does its own redirection, # appending to config.log, which fails on DOS, as config.log is still kept # open by configure. Here we exec the FD to /dev/null, effectively closing # config.log, so it can be properly (re)opened and appended to by config.lt. lt_cl_success=: test "$silent" = yes && lt_config_lt_args="$lt_config_lt_args --quiet" exec AS_MESSAGE_LOG_FD>/dev/null $SHELL "$CONFIG_LT" $lt_config_lt_args || lt_cl_success=false exec AS_MESSAGE_LOG_FD>>config.log $lt_cl_success || AS_EXIT(1) ])# LT_OUTPUT # _LT_CONFIG(TAG) # --------------- # If TAG is the built-in tag, create an initial libtool script with a # default configuration from the untagged config vars. Otherwise add code # to config.status for appending the configuration named by TAG from the # matching tagged config vars. m4_defun([_LT_CONFIG], [m4_require([_LT_FILEUTILS_DEFAULTS])dnl _LT_CONFIG_SAVE_COMMANDS([ m4_define([_LT_TAG], m4_if([$1], [], [C], [$1]))dnl m4_if(_LT_TAG, [C], [ # See if we are running on zsh, and set the options which allow our # commands through without removal of \ escapes. if test -n "${ZSH_VERSION+set}" ; then setopt NO_GLOB_SUBST fi cfgfile="${ofile}T" trap "$RM \"$cfgfile\"; exit 1" 1 2 15 $RM "$cfgfile" cat <<_LT_EOF >> "$cfgfile" #! $SHELL # `$ECHO "$ofile" | sed 's%^.*/%%'` - Provide generalized library-building support services. # Generated automatically by $as_me ($PACKAGE$TIMESTAMP) $VERSION # Libtool was configured on host `(hostname || uname -n) 2>/dev/null | sed 1q`: # NOTE: Changes made to this file will be lost: look at ltmain.sh. # _LT_COPYING _LT_LIBTOOL_TAGS # ### BEGIN LIBTOOL CONFIG _LT_LIBTOOL_CONFIG_VARS _LT_LIBTOOL_TAG_VARS # ### END LIBTOOL CONFIG _LT_EOF case $host_os in aix3*) cat <<\_LT_EOF >> "$cfgfile" # AIX sometimes has problems with the GCC collect2 program. For some # reason, if we set the COLLECT_NAMES environment variable, the problems # vanish in a puff of smoke. if test "X${COLLECT_NAMES+set}" != Xset; then COLLECT_NAMES= export COLLECT_NAMES fi _LT_EOF ;; esac _LT_PROG_LTMAIN # We use sed instead of cat because bash on DJGPP gets confused if # if finds mixed CR/LF and LF-only lines. Since sed operates in # text mode, it properly converts lines to CR/LF. This bash problem # is reportedly fixed, but why not run on old versions too? sed '$q' "$ltmain" >> "$cfgfile" \ || (rm -f "$cfgfile"; exit 1) _LT_PROG_REPLACE_SHELLFNS mv -f "$cfgfile" "$ofile" || (rm -f "$ofile" && cp "$cfgfile" "$ofile" && rm -f "$cfgfile") chmod +x "$ofile" ], [cat <<_LT_EOF >> "$ofile" dnl Unfortunately we have to use $1 here, since _LT_TAG is not expanded dnl in a comment (ie after a #). # ### BEGIN LIBTOOL TAG CONFIG: $1 _LT_LIBTOOL_TAG_VARS(_LT_TAG) # ### END LIBTOOL TAG CONFIG: $1 _LT_EOF ])dnl /m4_if ], [m4_if([$1], [], [ PACKAGE='$PACKAGE' VERSION='$VERSION' TIMESTAMP='$TIMESTAMP' RM='$RM' ofile='$ofile'], []) ])dnl /_LT_CONFIG_SAVE_COMMANDS ])# _LT_CONFIG # LT_SUPPORTED_TAG(TAG) # --------------------- # Trace this macro to discover what tags are supported by the libtool # --tag option, using: # autoconf --trace 'LT_SUPPORTED_TAG:$1' AC_DEFUN([LT_SUPPORTED_TAG], []) # C support is built-in for now m4_define([_LT_LANG_C_enabled], []) m4_define([_LT_TAGS], []) # LT_LANG(LANG) # ------------- # Enable libtool support for the given language if not already enabled. AC_DEFUN([LT_LANG], [AC_BEFORE([$0], [LT_OUTPUT])dnl m4_case([$1], [C], [_LT_LANG(C)], [C++], [_LT_LANG(CXX)], [Go], [_LT_LANG(GO)], [Java], [_LT_LANG(GCJ)], [Fortran 77], [_LT_LANG(F77)], [Fortran], [_LT_LANG(FC)], [Windows Resource], [_LT_LANG(RC)], [m4_ifdef([_LT_LANG_]$1[_CONFIG], [_LT_LANG($1)], [m4_fatal([$0: unsupported language: "$1"])])])dnl ])# LT_LANG # _LT_LANG(LANGNAME) # ------------------ m4_defun([_LT_LANG], [m4_ifdef([_LT_LANG_]$1[_enabled], [], [LT_SUPPORTED_TAG([$1])dnl m4_append([_LT_TAGS], [$1 ])dnl m4_define([_LT_LANG_]$1[_enabled], [])dnl _LT_LANG_$1_CONFIG($1)])dnl ])# _LT_LANG m4_ifndef([AC_PROG_GO], [ ############################################################ # NOTE: This macro has been submitted for inclusion into # # GNU Autoconf as AC_PROG_GO. When it is available in # # a released version of Autoconf we should remove this # # macro and use it instead. # ############################################################ m4_defun([AC_PROG_GO], [AC_LANG_PUSH(Go)dnl AC_ARG_VAR([GOC], [Go compiler command])dnl AC_ARG_VAR([GOFLAGS], [Go compiler flags])dnl _AC_ARG_VAR_LDFLAGS()dnl AC_CHECK_TOOL(GOC, gccgo) if test -z "$GOC"; then if test -n "$ac_tool_prefix"; then AC_CHECK_PROG(GOC, [${ac_tool_prefix}gccgo], [${ac_tool_prefix}gccgo]) fi fi if test -z "$GOC"; then AC_CHECK_PROG(GOC, gccgo, gccgo, false) fi ])#m4_defun ])#m4_ifndef # _LT_LANG_DEFAULT_CONFIG # ----------------------- m4_defun([_LT_LANG_DEFAULT_CONFIG], [AC_PROVIDE_IFELSE([AC_PROG_CXX], [LT_LANG(CXX)], [m4_define([AC_PROG_CXX], defn([AC_PROG_CXX])[LT_LANG(CXX)])]) AC_PROVIDE_IFELSE([AC_PROG_F77], [LT_LANG(F77)], [m4_define([AC_PROG_F77], defn([AC_PROG_F77])[LT_LANG(F77)])]) AC_PROVIDE_IFELSE([AC_PROG_FC], [LT_LANG(FC)], [m4_define([AC_PROG_FC], defn([AC_PROG_FC])[LT_LANG(FC)])]) dnl The call to [A][M_PROG_GCJ] is quoted like that to stop aclocal dnl pulling things in needlessly. AC_PROVIDE_IFELSE([AC_PROG_GCJ], [LT_LANG(GCJ)], [AC_PROVIDE_IFELSE([A][M_PROG_GCJ], [LT_LANG(GCJ)], [AC_PROVIDE_IFELSE([LT_PROG_GCJ], [LT_LANG(GCJ)], [m4_ifdef([AC_PROG_GCJ], [m4_define([AC_PROG_GCJ], defn([AC_PROG_GCJ])[LT_LANG(GCJ)])]) m4_ifdef([A][M_PROG_GCJ], [m4_define([A][M_PROG_GCJ], defn([A][M_PROG_GCJ])[LT_LANG(GCJ)])]) m4_ifdef([LT_PROG_GCJ], [m4_define([LT_PROG_GCJ], defn([LT_PROG_GCJ])[LT_LANG(GCJ)])])])])]) AC_PROVIDE_IFELSE([AC_PROG_GO], [LT_LANG(GO)], [m4_define([AC_PROG_GO], defn([AC_PROG_GO])[LT_LANG(GO)])]) AC_PROVIDE_IFELSE([LT_PROG_RC], [LT_LANG(RC)], [m4_define([LT_PROG_RC], defn([LT_PROG_RC])[LT_LANG(RC)])]) ])# _LT_LANG_DEFAULT_CONFIG # Obsolete macros: AU_DEFUN([AC_LIBTOOL_CXX], [LT_LANG(C++)]) AU_DEFUN([AC_LIBTOOL_F77], [LT_LANG(Fortran 77)]) AU_DEFUN([AC_LIBTOOL_FC], [LT_LANG(Fortran)]) AU_DEFUN([AC_LIBTOOL_GCJ], [LT_LANG(Java)]) AU_DEFUN([AC_LIBTOOL_RC], [LT_LANG(Windows Resource)]) dnl aclocal-1.4 backwards compatibility: dnl AC_DEFUN([AC_LIBTOOL_CXX], []) dnl AC_DEFUN([AC_LIBTOOL_F77], []) dnl AC_DEFUN([AC_LIBTOOL_FC], []) dnl AC_DEFUN([AC_LIBTOOL_GCJ], []) dnl AC_DEFUN([AC_LIBTOOL_RC], []) # _LT_TAG_COMPILER # ---------------- m4_defun([_LT_TAG_COMPILER], [AC_REQUIRE([AC_PROG_CC])dnl _LT_DECL([LTCC], [CC], [1], [A C compiler])dnl _LT_DECL([LTCFLAGS], [CFLAGS], [1], [LTCC compiler flags])dnl _LT_TAGDECL([CC], [compiler], [1], [A language specific compiler])dnl _LT_TAGDECL([with_gcc], [GCC], [0], [Is the compiler the GNU compiler?])dnl # If no C compiler was specified, use CC. LTCC=${LTCC-"$CC"} # If no C compiler flags were specified, use CFLAGS. LTCFLAGS=${LTCFLAGS-"$CFLAGS"} # Allow CC to be a program name with arguments. compiler=$CC ])# _LT_TAG_COMPILER # _LT_COMPILER_BOILERPLATE # ------------------------ # Check for compiler boilerplate output or warnings with # the simple compiler test code. m4_defun([_LT_COMPILER_BOILERPLATE], [m4_require([_LT_DECL_SED])dnl ac_outfile=conftest.$ac_objext echo "$lt_simple_compile_test_code" >conftest.$ac_ext eval "$ac_compile" 2>&1 >/dev/null | $SED '/^$/d; /^ *+/d' >conftest.err _lt_compiler_boilerplate=`cat conftest.err` $RM conftest* ])# _LT_COMPILER_BOILERPLATE # _LT_LINKER_BOILERPLATE # ---------------------- # Check for linker boilerplate output or warnings with # the simple link test code. m4_defun([_LT_LINKER_BOILERPLATE], [m4_require([_LT_DECL_SED])dnl ac_outfile=conftest.$ac_objext echo "$lt_simple_link_test_code" >conftest.$ac_ext eval "$ac_link" 2>&1 >/dev/null | $SED '/^$/d; /^ *+/d' >conftest.err _lt_linker_boilerplate=`cat conftest.err` $RM -r conftest* ])# _LT_LINKER_BOILERPLATE # _LT_REQUIRED_DARWIN_CHECKS # ------------------------- m4_defun_once([_LT_REQUIRED_DARWIN_CHECKS],[ case $host_os in rhapsody* | darwin*) AC_CHECK_TOOL([DSYMUTIL], [dsymutil], [:]) AC_CHECK_TOOL([NMEDIT], [nmedit], [:]) AC_CHECK_TOOL([LIPO], [lipo], [:]) AC_CHECK_TOOL([OTOOL], [otool], [:]) AC_CHECK_TOOL([OTOOL64], [otool64], [:]) _LT_DECL([], [DSYMUTIL], [1], [Tool to manipulate archived DWARF debug symbol files on Mac OS X]) _LT_DECL([], [NMEDIT], [1], [Tool to change global to local symbols on Mac OS X]) _LT_DECL([], [LIPO], [1], [Tool to manipulate fat objects and archives on Mac OS X]) _LT_DECL([], [OTOOL], [1], [ldd/readelf like tool for Mach-O binaries on Mac OS X]) _LT_DECL([], [OTOOL64], [1], [ldd/readelf like tool for 64 bit Mach-O binaries on Mac OS X 10.4]) AC_CACHE_CHECK([for -single_module linker flag],[lt_cv_apple_cc_single_mod], [lt_cv_apple_cc_single_mod=no if test -z "${LT_MULTI_MODULE}"; then # By default we will add the -single_module flag. You can override # by either setting the environment variable LT_MULTI_MODULE # non-empty at configure time, or by adding -multi_module to the # link flags. rm -rf libconftest.dylib* echo "int foo(void){return 1;}" > conftest.c echo "$LTCC $LTCFLAGS $LDFLAGS -o libconftest.dylib \ -dynamiclib -Wl,-single_module conftest.c" >&AS_MESSAGE_LOG_FD $LTCC $LTCFLAGS $LDFLAGS -o libconftest.dylib \ -dynamiclib -Wl,-single_module conftest.c 2>conftest.err _lt_result=$? # If there is a non-empty error log, and "single_module" # appears in it, assume the flag caused a linker warning if test -s conftest.err && $GREP single_module conftest.err; then cat conftest.err >&AS_MESSAGE_LOG_FD # Otherwise, if the output was created with a 0 exit code from # the compiler, it worked. elif test -f libconftest.dylib && test $_lt_result -eq 0; then lt_cv_apple_cc_single_mod=yes else cat conftest.err >&AS_MESSAGE_LOG_FD fi rm -rf libconftest.dylib* rm -f conftest.* fi]) AC_CACHE_CHECK([for -exported_symbols_list linker flag], [lt_cv_ld_exported_symbols_list], [lt_cv_ld_exported_symbols_list=no save_LDFLAGS=$LDFLAGS echo "_main" > conftest.sym LDFLAGS="$LDFLAGS -Wl,-exported_symbols_list,conftest.sym" AC_LINK_IFELSE([AC_LANG_PROGRAM([],[])], [lt_cv_ld_exported_symbols_list=yes], [lt_cv_ld_exported_symbols_list=no]) LDFLAGS="$save_LDFLAGS" ]) AC_CACHE_CHECK([for -force_load linker flag],[lt_cv_ld_force_load], [lt_cv_ld_force_load=no cat > conftest.c << _LT_EOF int forced_loaded() { return 2;} _LT_EOF echo "$LTCC $LTCFLAGS -c -o conftest.o conftest.c" >&AS_MESSAGE_LOG_FD $LTCC $LTCFLAGS -c -o conftest.o conftest.c 2>&AS_MESSAGE_LOG_FD echo "$AR cru libconftest.a conftest.o" >&AS_MESSAGE_LOG_FD $AR cru libconftest.a conftest.o 2>&AS_MESSAGE_LOG_FD echo "$RANLIB libconftest.a" >&AS_MESSAGE_LOG_FD $RANLIB libconftest.a 2>&AS_MESSAGE_LOG_FD cat > conftest.c << _LT_EOF int main() { return 0;} _LT_EOF echo "$LTCC $LTCFLAGS $LDFLAGS -o conftest conftest.c -Wl,-force_load,./libconftest.a" >&AS_MESSAGE_LOG_FD $LTCC $LTCFLAGS $LDFLAGS -o conftest conftest.c -Wl,-force_load,./libconftest.a 2>conftest.err _lt_result=$? if test -s conftest.err && $GREP force_load conftest.err; then cat conftest.err >&AS_MESSAGE_LOG_FD elif test -f conftest && test $_lt_result -eq 0 && $GREP forced_load conftest >/dev/null 2>&1 ; then lt_cv_ld_force_load=yes else cat conftest.err >&AS_MESSAGE_LOG_FD fi rm -f conftest.err libconftest.a conftest conftest.c rm -rf conftest.dSYM ]) case $host_os in rhapsody* | darwin1.[[012]]) _lt_dar_allow_undefined='${wl}-undefined ${wl}suppress' ;; darwin1.*) _lt_dar_allow_undefined='${wl}-flat_namespace ${wl}-undefined ${wl}suppress' ;; darwin*) # darwin 5.x on # if running on 10.5 or later, the deployment target defaults # to the OS version, if on x86, and 10.4, the deployment # target defaults to 10.4. Don't you love it? case ${MACOSX_DEPLOYMENT_TARGET-10.0},$host in 10.0,*86*-darwin8*|10.0,*-darwin[[91]]*) _lt_dar_allow_undefined='${wl}-undefined ${wl}dynamic_lookup' ;; 10.[[012]]*) _lt_dar_allow_undefined='${wl}-flat_namespace ${wl}-undefined ${wl}suppress' ;; 10.*) _lt_dar_allow_undefined='${wl}-undefined ${wl}dynamic_lookup' ;; esac ;; esac if test "$lt_cv_apple_cc_single_mod" = "yes"; then _lt_dar_single_mod='$single_module' fi if test "$lt_cv_ld_exported_symbols_list" = "yes"; then _lt_dar_export_syms=' ${wl}-exported_symbols_list,$output_objdir/${libname}-symbols.expsym' else _lt_dar_export_syms='~$NMEDIT -s $output_objdir/${libname}-symbols.expsym ${lib}' fi if test "$DSYMUTIL" != ":" && test "$lt_cv_ld_force_load" = "no"; then _lt_dsymutil='~$DSYMUTIL $lib || :' else _lt_dsymutil= fi ;; esac ]) # _LT_DARWIN_LINKER_FEATURES([TAG]) # --------------------------------- # Checks for linker and compiler features on darwin m4_defun([_LT_DARWIN_LINKER_FEATURES], [ m4_require([_LT_REQUIRED_DARWIN_CHECKS]) _LT_TAGVAR(archive_cmds_need_lc, $1)=no _LT_TAGVAR(hardcode_direct, $1)=no _LT_TAGVAR(hardcode_automatic, $1)=yes _LT_TAGVAR(hardcode_shlibpath_var, $1)=unsupported if test "$lt_cv_ld_force_load" = "yes"; then _LT_TAGVAR(whole_archive_flag_spec, $1)='`for conv in $convenience\"\"; do test -n \"$conv\" && new_convenience=\"$new_convenience ${wl}-force_load,$conv\"; done; func_echo_all \"$new_convenience\"`' m4_case([$1], [F77], [_LT_TAGVAR(compiler_needs_object, $1)=yes], [FC], [_LT_TAGVAR(compiler_needs_object, $1)=yes]) else _LT_TAGVAR(whole_archive_flag_spec, $1)='' fi _LT_TAGVAR(link_all_deplibs, $1)=yes _LT_TAGVAR(allow_undefined_flag, $1)="$_lt_dar_allow_undefined" case $cc_basename in ifort*) _lt_dar_can_shared=yes ;; *) _lt_dar_can_shared=$GCC ;; esac if test "$_lt_dar_can_shared" = "yes"; then output_verbose_link_cmd=func_echo_all _LT_TAGVAR(archive_cmds, $1)="\$CC -dynamiclib \$allow_undefined_flag -o \$lib \$libobjs \$deplibs \$compiler_flags -install_name \$rpath/\$soname \$verstring $_lt_dar_single_mod${_lt_dsymutil}" _LT_TAGVAR(module_cmds, $1)="\$CC \$allow_undefined_flag -o \$lib -bundle \$libobjs \$deplibs \$compiler_flags${_lt_dsymutil}" _LT_TAGVAR(archive_expsym_cmds, $1)="sed 's,^,_,' < \$export_symbols > \$output_objdir/\${libname}-symbols.expsym~\$CC -dynamiclib \$allow_undefined_flag -o \$lib \$libobjs \$deplibs \$compiler_flags -install_name \$rpath/\$soname \$verstring ${_lt_dar_single_mod}${_lt_dar_export_syms}${_lt_dsymutil}" _LT_TAGVAR(module_expsym_cmds, $1)="sed -e 's,^,_,' < \$export_symbols > \$output_objdir/\${libname}-symbols.expsym~\$CC \$allow_undefined_flag -o \$lib -bundle \$libobjs \$deplibs \$compiler_flags${_lt_dar_export_syms}${_lt_dsymutil}" m4_if([$1], [CXX], [ if test "$lt_cv_apple_cc_single_mod" != "yes"; then _LT_TAGVAR(archive_cmds, $1)="\$CC -r -keep_private_externs -nostdlib -o \${lib}-master.o \$libobjs~\$CC -dynamiclib \$allow_undefined_flag -o \$lib \${lib}-master.o \$deplibs \$compiler_flags -install_name \$rpath/\$soname \$verstring${_lt_dsymutil}" _LT_TAGVAR(archive_expsym_cmds, $1)="sed 's,^,_,' < \$export_symbols > \$output_objdir/\${libname}-symbols.expsym~\$CC -r -keep_private_externs -nostdlib -o \${lib}-master.o \$libobjs~\$CC -dynamiclib \$allow_undefined_flag -o \$lib \${lib}-master.o \$deplibs \$compiler_flags -install_name \$rpath/\$soname \$verstring${_lt_dar_export_syms}${_lt_dsymutil}" fi ],[]) else _LT_TAGVAR(ld_shlibs, $1)=no fi ]) # _LT_SYS_MODULE_PATH_AIX([TAGNAME]) # ---------------------------------- # Links a minimal program and checks the executable # for the system default hardcoded library path. In most cases, # this is /usr/lib:/lib, but when the MPI compilers are used # the location of the communication and MPI libs are included too. # If we don't find anything, use the default library path according # to the aix ld manual. # Store the results from the different compilers for each TAGNAME. # Allow to override them for all tags through lt_cv_aix_libpath. m4_defun([_LT_SYS_MODULE_PATH_AIX], [m4_require([_LT_DECL_SED])dnl if test "${lt_cv_aix_libpath+set}" = set; then aix_libpath=$lt_cv_aix_libpath else AC_CACHE_VAL([_LT_TAGVAR([lt_cv_aix_libpath_], [$1])], [AC_LINK_IFELSE([AC_LANG_PROGRAM],[ lt_aix_libpath_sed='[ /Import File Strings/,/^$/ { /^0/ { s/^0 *\([^ ]*\) *$/\1/ p } }]' _LT_TAGVAR([lt_cv_aix_libpath_], [$1])=`dump -H conftest$ac_exeext 2>/dev/null | $SED -n -e "$lt_aix_libpath_sed"` # Check for a 64-bit object if we didn't find anything. if test -z "$_LT_TAGVAR([lt_cv_aix_libpath_], [$1])"; then _LT_TAGVAR([lt_cv_aix_libpath_], [$1])=`dump -HX64 conftest$ac_exeext 2>/dev/null | $SED -n -e "$lt_aix_libpath_sed"` fi],[]) if test -z "$_LT_TAGVAR([lt_cv_aix_libpath_], [$1])"; then _LT_TAGVAR([lt_cv_aix_libpath_], [$1])="/usr/lib:/lib" fi ]) aix_libpath=$_LT_TAGVAR([lt_cv_aix_libpath_], [$1]) fi ])# _LT_SYS_MODULE_PATH_AIX # _LT_SHELL_INIT(ARG) # ------------------- m4_define([_LT_SHELL_INIT], [m4_divert_text([M4SH-INIT], [$1 ])])# _LT_SHELL_INIT # _LT_PROG_ECHO_BACKSLASH # ----------------------- # Find how we can fake an echo command that does not interpret backslash. # In particular, with Autoconf 2.60 or later we add some code to the start # of the generated configure script which will find a shell with a builtin # printf (which we can use as an echo command). m4_defun([_LT_PROG_ECHO_BACKSLASH], [ECHO='\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\' ECHO=$ECHO$ECHO$ECHO$ECHO$ECHO ECHO=$ECHO$ECHO$ECHO$ECHO$ECHO$ECHO AC_MSG_CHECKING([how to print strings]) # Test print first, because it will be a builtin if present. if test "X`( print -r -- -n ) 2>/dev/null`" = X-n && \ test "X`print -r -- $ECHO 2>/dev/null`" = "X$ECHO"; then ECHO='print -r --' elif test "X`printf %s $ECHO 2>/dev/null`" = "X$ECHO"; then ECHO='printf %s\n' else # Use this function as a fallback that always works. func_fallback_echo () { eval 'cat <<_LTECHO_EOF $[]1 _LTECHO_EOF' } ECHO='func_fallback_echo' fi # func_echo_all arg... # Invoke $ECHO with all args, space-separated. func_echo_all () { $ECHO "$*" } case "$ECHO" in printf*) AC_MSG_RESULT([printf]) ;; print*) AC_MSG_RESULT([print -r]) ;; *) AC_MSG_RESULT([cat]) ;; esac m4_ifdef([_AS_DETECT_SUGGESTED], [_AS_DETECT_SUGGESTED([ test -n "${ZSH_VERSION+set}${BASH_VERSION+set}" || ( ECHO='\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\' ECHO=$ECHO$ECHO$ECHO$ECHO$ECHO ECHO=$ECHO$ECHO$ECHO$ECHO$ECHO$ECHO PATH=/empty FPATH=/empty; export PATH FPATH test "X`printf %s $ECHO`" = "X$ECHO" \ || test "X`print -r -- $ECHO`" = "X$ECHO" )])]) _LT_DECL([], [SHELL], [1], [Shell to use when invoking shell scripts]) _LT_DECL([], [ECHO], [1], [An echo program that protects backslashes]) ])# _LT_PROG_ECHO_BACKSLASH # _LT_WITH_SYSROOT # ---------------- AC_DEFUN([_LT_WITH_SYSROOT], [AC_MSG_CHECKING([for sysroot]) AC_ARG_WITH([sysroot], [ --with-sysroot[=DIR] Search for dependent libraries within DIR (or the compiler's sysroot if not specified).], [], [with_sysroot=no]) dnl lt_sysroot will always be passed unquoted. We quote it here dnl in case the user passed a directory name. lt_sysroot= case ${with_sysroot} in #( yes) if test "$GCC" = yes; then lt_sysroot=`$CC --print-sysroot 2>/dev/null` fi ;; #( /*) lt_sysroot=`echo "$with_sysroot" | sed -e "$sed_quote_subst"` ;; #( no|'') ;; #( *) AC_MSG_RESULT([${with_sysroot}]) AC_MSG_ERROR([The sysroot must be an absolute path.]) ;; esac AC_MSG_RESULT([${lt_sysroot:-no}]) _LT_DECL([], [lt_sysroot], [0], [The root where to search for ]dnl [dependent libraries, and in which our libraries should be installed.])]) # _LT_ENABLE_LOCK # --------------- m4_defun([_LT_ENABLE_LOCK], [AC_ARG_ENABLE([libtool-lock], [AS_HELP_STRING([--disable-libtool-lock], [avoid locking (might break parallel builds)])]) test "x$enable_libtool_lock" != xno && enable_libtool_lock=yes # Some flags need to be propagated to the compiler or linker for good # libtool support. case $host in ia64-*-hpux*) # Find out which ABI we are using. echo 'int i;' > conftest.$ac_ext if AC_TRY_EVAL(ac_compile); then case `/usr/bin/file conftest.$ac_objext` in *ELF-32*) HPUX_IA64_MODE="32" ;; *ELF-64*) HPUX_IA64_MODE="64" ;; esac fi rm -rf conftest* ;; *-*-irix6*) # Find out which ABI we are using. echo '[#]line '$LINENO' "configure"' > conftest.$ac_ext if AC_TRY_EVAL(ac_compile); then if test "$lt_cv_prog_gnu_ld" = yes; then case `/usr/bin/file conftest.$ac_objext` in *32-bit*) LD="${LD-ld} -melf32bsmip" ;; *N32*) LD="${LD-ld} -melf32bmipn32" ;; *64-bit*) LD="${LD-ld} -melf64bmip" ;; esac else case `/usr/bin/file conftest.$ac_objext` in *32-bit*) LD="${LD-ld} -32" ;; *N32*) LD="${LD-ld} -n32" ;; *64-bit*) LD="${LD-ld} -64" ;; esac fi fi rm -rf conftest* ;; x86_64-*kfreebsd*-gnu|x86_64-*linux*|ppc*-*linux*|powerpc*-*linux*| \ s390*-*linux*|s390*-*tpf*|sparc*-*linux*) # Find out which ABI we are using. echo 'int i;' > conftest.$ac_ext if AC_TRY_EVAL(ac_compile); then case `/usr/bin/file conftest.o` in *32-bit*) case $host in x86_64-*kfreebsd*-gnu) LD="${LD-ld} -m elf_i386_fbsd" ;; x86_64-*linux*) case `/usr/bin/file conftest.o` in *x86-64*) LD="${LD-ld} -m elf32_x86_64" ;; *) LD="${LD-ld} -m elf_i386" ;; esac ;; ppc64-*linux*|powerpc64-*linux*) LD="${LD-ld} -m elf32ppclinux" ;; s390x-*linux*) LD="${LD-ld} -m elf_s390" ;; sparc64-*linux*) LD="${LD-ld} -m elf32_sparc" ;; esac ;; *64-bit*) case $host in x86_64-*kfreebsd*-gnu) LD="${LD-ld} -m elf_x86_64_fbsd" ;; x86_64-*linux*) LD="${LD-ld} -m elf_x86_64" ;; ppc*-*linux*|powerpc*-*linux*) LD="${LD-ld} -m elf64ppc" ;; s390*-*linux*|s390*-*tpf*) LD="${LD-ld} -m elf64_s390" ;; sparc*-*linux*) LD="${LD-ld} -m elf64_sparc" ;; esac ;; esac fi rm -rf conftest* ;; *-*-sco3.2v5*) # On SCO OpenServer 5, we need -belf to get full-featured binaries. SAVE_CFLAGS="$CFLAGS" CFLAGS="$CFLAGS -belf" AC_CACHE_CHECK([whether the C compiler needs -belf], lt_cv_cc_needs_belf, [AC_LANG_PUSH(C) AC_LINK_IFELSE([AC_LANG_PROGRAM([[]],[[]])],[lt_cv_cc_needs_belf=yes],[lt_cv_cc_needs_belf=no]) AC_LANG_POP]) if test x"$lt_cv_cc_needs_belf" != x"yes"; then # this is probably gcc 2.8.0, egcs 1.0 or newer; no need for -belf CFLAGS="$SAVE_CFLAGS" fi ;; *-*solaris*) # Find out which ABI we are using. echo 'int i;' > conftest.$ac_ext if AC_TRY_EVAL(ac_compile); then case `/usr/bin/file conftest.o` in *64-bit*) case $lt_cv_prog_gnu_ld in yes*) case $host in i?86-*-solaris*) LD="${LD-ld} -m elf_x86_64" ;; sparc*-*-solaris*) LD="${LD-ld} -m elf64_sparc" ;; esac # GNU ld 2.21 introduced _sol2 emulations. Use them if available. if ${LD-ld} -V | grep _sol2 >/dev/null 2>&1; then LD="${LD-ld}_sol2" fi ;; *) if ${LD-ld} -64 -r -o conftest2.o conftest.o >/dev/null 2>&1; then LD="${LD-ld} -64" fi ;; esac ;; esac fi rm -rf conftest* ;; esac need_locks="$enable_libtool_lock" ])# _LT_ENABLE_LOCK # _LT_PROG_AR # ----------- m4_defun([_LT_PROG_AR], [AC_CHECK_TOOLS(AR, [ar], false) : ${AR=ar} : ${AR_FLAGS=cru} _LT_DECL([], [AR], [1], [The archiver]) _LT_DECL([], [AR_FLAGS], [1], [Flags to create an archive]) AC_CACHE_CHECK([for archiver @FILE support], [lt_cv_ar_at_file], [lt_cv_ar_at_file=no AC_COMPILE_IFELSE([AC_LANG_PROGRAM], [echo conftest.$ac_objext > conftest.lst lt_ar_try='$AR $AR_FLAGS libconftest.a @conftest.lst >&AS_MESSAGE_LOG_FD' AC_TRY_EVAL([lt_ar_try]) if test "$ac_status" -eq 0; then # Ensure the archiver fails upon bogus file names. rm -f conftest.$ac_objext libconftest.a AC_TRY_EVAL([lt_ar_try]) if test "$ac_status" -ne 0; then lt_cv_ar_at_file=@ fi fi rm -f conftest.* libconftest.a ]) ]) if test "x$lt_cv_ar_at_file" = xno; then archiver_list_spec= else archiver_list_spec=$lt_cv_ar_at_file fi _LT_DECL([], [archiver_list_spec], [1], [How to feed a file listing to the archiver]) ])# _LT_PROG_AR # _LT_CMD_OLD_ARCHIVE # ------------------- m4_defun([_LT_CMD_OLD_ARCHIVE], [_LT_PROG_AR AC_CHECK_TOOL(STRIP, strip, :) test -z "$STRIP" && STRIP=: _LT_DECL([], [STRIP], [1], [A symbol stripping program]) AC_CHECK_TOOL(RANLIB, ranlib, :) test -z "$RANLIB" && RANLIB=: _LT_DECL([], [RANLIB], [1], [Commands used to install an old-style archive]) # Determine commands to create old-style static archives. old_archive_cmds='$AR $AR_FLAGS $oldlib$oldobjs' old_postinstall_cmds='chmod 644 $oldlib' old_postuninstall_cmds= if test -n "$RANLIB"; then case $host_os in openbsd*) old_postinstall_cmds="$old_postinstall_cmds~\$RANLIB -t \$tool_oldlib" ;; *) old_postinstall_cmds="$old_postinstall_cmds~\$RANLIB \$tool_oldlib" ;; esac old_archive_cmds="$old_archive_cmds~\$RANLIB \$tool_oldlib" fi case $host_os in darwin*) lock_old_archive_extraction=yes ;; *) lock_old_archive_extraction=no ;; esac _LT_DECL([], [old_postinstall_cmds], [2]) _LT_DECL([], [old_postuninstall_cmds], [2]) _LT_TAGDECL([], [old_archive_cmds], [2], [Commands used to build an old-style archive]) _LT_DECL([], [lock_old_archive_extraction], [0], [Whether to use a lock for old archive extraction]) ])# _LT_CMD_OLD_ARCHIVE # _LT_COMPILER_OPTION(MESSAGE, VARIABLE-NAME, FLAGS, # [OUTPUT-FILE], [ACTION-SUCCESS], [ACTION-FAILURE]) # ---------------------------------------------------------------- # Check whether the given compiler option works AC_DEFUN([_LT_COMPILER_OPTION], [m4_require([_LT_FILEUTILS_DEFAULTS])dnl m4_require([_LT_DECL_SED])dnl AC_CACHE_CHECK([$1], [$2], [$2=no m4_if([$4], , [ac_outfile=conftest.$ac_objext], [ac_outfile=$4]) echo "$lt_simple_compile_test_code" > conftest.$ac_ext lt_compiler_flag="$3" # Insert the option either (1) after the last *FLAGS variable, or # (2) before a word containing "conftest.", or (3) at the end. # Note that $ac_compile itself does not contain backslashes and begins # with a dollar sign (not a hyphen), so the echo should work correctly. # The option is referenced via a variable to avoid confusing sed. lt_compile=`echo "$ac_compile" | $SED \ -e 's:.*FLAGS}\{0,1\} :&$lt_compiler_flag :; t' \ -e 's: [[^ ]]*conftest\.: $lt_compiler_flag&:; t' \ -e 's:$: $lt_compiler_flag:'` (eval echo "\"\$as_me:$LINENO: $lt_compile\"" >&AS_MESSAGE_LOG_FD) (eval "$lt_compile" 2>conftest.err) ac_status=$? cat conftest.err >&AS_MESSAGE_LOG_FD echo "$as_me:$LINENO: \$? = $ac_status" >&AS_MESSAGE_LOG_FD if (exit $ac_status) && test -s "$ac_outfile"; then # The compiler can only warn and ignore the option if not recognized # So say no if there are warnings other than the usual output. $ECHO "$_lt_compiler_boilerplate" | $SED '/^$/d' >conftest.exp $SED '/^$/d; /^ *+/d' conftest.err >conftest.er2 if test ! -s conftest.er2 || diff conftest.exp conftest.er2 >/dev/null; then $2=yes fi fi $RM conftest* ]) if test x"[$]$2" = xyes; then m4_if([$5], , :, [$5]) else m4_if([$6], , :, [$6]) fi ])# _LT_COMPILER_OPTION # Old name: AU_ALIAS([AC_LIBTOOL_COMPILER_OPTION], [_LT_COMPILER_OPTION]) dnl aclocal-1.4 backwards compatibility: dnl AC_DEFUN([AC_LIBTOOL_COMPILER_OPTION], []) # _LT_LINKER_OPTION(MESSAGE, VARIABLE-NAME, FLAGS, # [ACTION-SUCCESS], [ACTION-FAILURE]) # ---------------------------------------------------- # Check whether the given linker option works AC_DEFUN([_LT_LINKER_OPTION], [m4_require([_LT_FILEUTILS_DEFAULTS])dnl m4_require([_LT_DECL_SED])dnl AC_CACHE_CHECK([$1], [$2], [$2=no save_LDFLAGS="$LDFLAGS" LDFLAGS="$LDFLAGS $3" echo "$lt_simple_link_test_code" > conftest.$ac_ext if (eval $ac_link 2>conftest.err) && test -s conftest$ac_exeext; then # The linker can only warn and ignore the option if not recognized # So say no if there are warnings if test -s conftest.err; then # Append any errors to the config.log. cat conftest.err 1>&AS_MESSAGE_LOG_FD $ECHO "$_lt_linker_boilerplate" | $SED '/^$/d' > conftest.exp $SED '/^$/d; /^ *+/d' conftest.err >conftest.er2 if diff conftest.exp conftest.er2 >/dev/null; then $2=yes fi else $2=yes fi fi $RM -r conftest* LDFLAGS="$save_LDFLAGS" ]) if test x"[$]$2" = xyes; then m4_if([$4], , :, [$4]) else m4_if([$5], , :, [$5]) fi ])# _LT_LINKER_OPTION # Old name: AU_ALIAS([AC_LIBTOOL_LINKER_OPTION], [_LT_LINKER_OPTION]) dnl aclocal-1.4 backwards compatibility: dnl AC_DEFUN([AC_LIBTOOL_LINKER_OPTION], []) # LT_CMD_MAX_LEN #--------------- AC_DEFUN([LT_CMD_MAX_LEN], [AC_REQUIRE([AC_CANONICAL_HOST])dnl # find the maximum length of command line arguments AC_MSG_CHECKING([the maximum length of command line arguments]) AC_CACHE_VAL([lt_cv_sys_max_cmd_len], [dnl i=0 teststring="ABCD" case $build_os in msdosdjgpp*) # On DJGPP, this test can blow up pretty badly due to problems in libc # (any single argument exceeding 2000 bytes causes a buffer overrun # during glob expansion). Even if it were fixed, the result of this # check would be larger than it should be. lt_cv_sys_max_cmd_len=12288; # 12K is about right ;; gnu*) # Under GNU Hurd, this test is not required because there is # no limit to the length of command line arguments. # Libtool will interpret -1 as no limit whatsoever lt_cv_sys_max_cmd_len=-1; ;; cygwin* | mingw* | cegcc*) # On Win9x/ME, this test blows up -- it succeeds, but takes # about 5 minutes as the teststring grows exponentially. # Worse, since 9x/ME are not pre-emptively multitasking, # you end up with a "frozen" computer, even though with patience # the test eventually succeeds (with a max line length of 256k). # Instead, let's just punt: use the minimum linelength reported by # all of the supported platforms: 8192 (on NT/2K/XP). lt_cv_sys_max_cmd_len=8192; ;; mint*) # On MiNT this can take a long time and run out of memory. lt_cv_sys_max_cmd_len=8192; ;; amigaos*) # On AmigaOS with pdksh, this test takes hours, literally. # So we just punt and use a minimum line length of 8192. lt_cv_sys_max_cmd_len=8192; ;; netbsd* | freebsd* | openbsd* | darwin* | dragonfly*) # This has been around since 386BSD, at least. Likely further. if test -x /sbin/sysctl; then lt_cv_sys_max_cmd_len=`/sbin/sysctl -n kern.argmax` elif test -x /usr/sbin/sysctl; then lt_cv_sys_max_cmd_len=`/usr/sbin/sysctl -n kern.argmax` else lt_cv_sys_max_cmd_len=65536 # usable default for all BSDs fi # And add a safety zone lt_cv_sys_max_cmd_len=`expr $lt_cv_sys_max_cmd_len \/ 4` lt_cv_sys_max_cmd_len=`expr $lt_cv_sys_max_cmd_len \* 3` ;; interix*) # We know the value 262144 and hardcode it with a safety zone (like BSD) lt_cv_sys_max_cmd_len=196608 ;; os2*) # The test takes a long time on OS/2. lt_cv_sys_max_cmd_len=8192 ;; osf*) # Dr. Hans Ekkehard Plesser reports seeing a kernel panic running configure # due to this test when exec_disable_arg_limit is 1 on Tru64. It is not # nice to cause kernel panics so lets avoid the loop below. # First set a reasonable default. lt_cv_sys_max_cmd_len=16384 # if test -x /sbin/sysconfig; then case `/sbin/sysconfig -q proc exec_disable_arg_limit` in *1*) lt_cv_sys_max_cmd_len=-1 ;; esac fi ;; sco3.2v5*) lt_cv_sys_max_cmd_len=102400 ;; sysv5* | sco5v6* | sysv4.2uw2*) kargmax=`grep ARG_MAX /etc/conf/cf.d/stune 2>/dev/null` if test -n "$kargmax"; then lt_cv_sys_max_cmd_len=`echo $kargmax | sed 's/.*[[ ]]//'` else lt_cv_sys_max_cmd_len=32768 fi ;; *) lt_cv_sys_max_cmd_len=`(getconf ARG_MAX) 2> /dev/null` if test -n "$lt_cv_sys_max_cmd_len" && \ test undefined != "$lt_cv_sys_max_cmd_len"; then lt_cv_sys_max_cmd_len=`expr $lt_cv_sys_max_cmd_len \/ 4` lt_cv_sys_max_cmd_len=`expr $lt_cv_sys_max_cmd_len \* 3` else # Make teststring a little bigger before we do anything with it. # a 1K string should be a reasonable start. for i in 1 2 3 4 5 6 7 8 ; do teststring=$teststring$teststring done SHELL=${SHELL-${CONFIG_SHELL-/bin/sh}} # If test is not a shell built-in, we'll probably end up computing a # maximum length that is only half of the actual maximum length, but # we can't tell. while { test "X"`env echo "$teststring$teststring" 2>/dev/null` \ = "X$teststring$teststring"; } >/dev/null 2>&1 && test $i != 17 # 1/2 MB should be enough do i=`expr $i + 1` teststring=$teststring$teststring done # Only check the string length outside the loop. lt_cv_sys_max_cmd_len=`expr "X$teststring" : ".*" 2>&1` teststring= # Add a significant safety factor because C++ compilers can tack on # massive amounts of additional arguments before passing them to the # linker. It appears as though 1/2 is a usable value. lt_cv_sys_max_cmd_len=`expr $lt_cv_sys_max_cmd_len \/ 2` fi ;; esac ]) if test -n $lt_cv_sys_max_cmd_len ; then AC_MSG_RESULT($lt_cv_sys_max_cmd_len) else AC_MSG_RESULT(none) fi max_cmd_len=$lt_cv_sys_max_cmd_len _LT_DECL([], [max_cmd_len], [0], [What is the maximum length of a command?]) ])# LT_CMD_MAX_LEN # Old name: AU_ALIAS([AC_LIBTOOL_SYS_MAX_CMD_LEN], [LT_CMD_MAX_LEN]) dnl aclocal-1.4 backwards compatibility: dnl AC_DEFUN([AC_LIBTOOL_SYS_MAX_CMD_LEN], []) # _LT_HEADER_DLFCN # ---------------- m4_defun([_LT_HEADER_DLFCN], [AC_CHECK_HEADERS([dlfcn.h], [], [], [AC_INCLUDES_DEFAULT])dnl ])# _LT_HEADER_DLFCN # _LT_TRY_DLOPEN_SELF (ACTION-IF-TRUE, ACTION-IF-TRUE-W-USCORE, # ACTION-IF-FALSE, ACTION-IF-CROSS-COMPILING) # ---------------------------------------------------------------- m4_defun([_LT_TRY_DLOPEN_SELF], [m4_require([_LT_HEADER_DLFCN])dnl if test "$cross_compiling" = yes; then : [$4] else lt_dlunknown=0; lt_dlno_uscore=1; lt_dlneed_uscore=2 lt_status=$lt_dlunknown cat > conftest.$ac_ext <<_LT_EOF [#line $LINENO "configure" #include "confdefs.h" #if HAVE_DLFCN_H #include #endif #include #ifdef RTLD_GLOBAL # define LT_DLGLOBAL RTLD_GLOBAL #else # ifdef DL_GLOBAL # define LT_DLGLOBAL DL_GLOBAL # else # define LT_DLGLOBAL 0 # endif #endif /* We may have to define LT_DLLAZY_OR_NOW in the command line if we find out it does not work in some platform. */ #ifndef LT_DLLAZY_OR_NOW # ifdef RTLD_LAZY # define LT_DLLAZY_OR_NOW RTLD_LAZY # else # ifdef DL_LAZY # define LT_DLLAZY_OR_NOW DL_LAZY # else # ifdef RTLD_NOW # define LT_DLLAZY_OR_NOW RTLD_NOW # else # ifdef DL_NOW # define LT_DLLAZY_OR_NOW DL_NOW # else # define LT_DLLAZY_OR_NOW 0 # endif # endif # endif # endif #endif /* When -fvisbility=hidden is used, assume the code has been annotated correspondingly for the symbols needed. */ #if defined(__GNUC__) && (((__GNUC__ == 3) && (__GNUC_MINOR__ >= 3)) || (__GNUC__ > 3)) int fnord () __attribute__((visibility("default"))); #endif int fnord () { return 42; } int main () { void *self = dlopen (0, LT_DLGLOBAL|LT_DLLAZY_OR_NOW); int status = $lt_dlunknown; if (self) { if (dlsym (self,"fnord")) status = $lt_dlno_uscore; else { if (dlsym( self,"_fnord")) status = $lt_dlneed_uscore; else puts (dlerror ()); } /* dlclose (self); */ } else puts (dlerror ()); return status; }] _LT_EOF if AC_TRY_EVAL(ac_link) && test -s conftest${ac_exeext} 2>/dev/null; then (./conftest; exit; ) >&AS_MESSAGE_LOG_FD 2>/dev/null lt_status=$? case x$lt_status in x$lt_dlno_uscore) $1 ;; x$lt_dlneed_uscore) $2 ;; x$lt_dlunknown|x*) $3 ;; esac else : # compilation failed $3 fi fi rm -fr conftest* ])# _LT_TRY_DLOPEN_SELF # LT_SYS_DLOPEN_SELF # ------------------ AC_DEFUN([LT_SYS_DLOPEN_SELF], [m4_require([_LT_HEADER_DLFCN])dnl if test "x$enable_dlopen" != xyes; then enable_dlopen=unknown enable_dlopen_self=unknown enable_dlopen_self_static=unknown else lt_cv_dlopen=no lt_cv_dlopen_libs= case $host_os in beos*) lt_cv_dlopen="load_add_on" lt_cv_dlopen_libs= lt_cv_dlopen_self=yes ;; mingw* | pw32* | cegcc*) lt_cv_dlopen="LoadLibrary" lt_cv_dlopen_libs= ;; cygwin*) lt_cv_dlopen="dlopen" lt_cv_dlopen_libs= ;; darwin*) # if libdl is installed we need to link against it AC_CHECK_LIB([dl], [dlopen], [lt_cv_dlopen="dlopen" lt_cv_dlopen_libs="-ldl"],[ lt_cv_dlopen="dyld" lt_cv_dlopen_libs= lt_cv_dlopen_self=yes ]) ;; *) AC_CHECK_FUNC([shl_load], [lt_cv_dlopen="shl_load"], [AC_CHECK_LIB([dld], [shl_load], [lt_cv_dlopen="shl_load" lt_cv_dlopen_libs="-ldld"], [AC_CHECK_FUNC([dlopen], [lt_cv_dlopen="dlopen"], [AC_CHECK_LIB([dl], [dlopen], [lt_cv_dlopen="dlopen" lt_cv_dlopen_libs="-ldl"], [AC_CHECK_LIB([svld], [dlopen], [lt_cv_dlopen="dlopen" lt_cv_dlopen_libs="-lsvld"], [AC_CHECK_LIB([dld], [dld_link], [lt_cv_dlopen="dld_link" lt_cv_dlopen_libs="-ldld"]) ]) ]) ]) ]) ]) ;; esac if test "x$lt_cv_dlopen" != xno; then enable_dlopen=yes else enable_dlopen=no fi case $lt_cv_dlopen in dlopen) save_CPPFLAGS="$CPPFLAGS" test "x$ac_cv_header_dlfcn_h" = xyes && CPPFLAGS="$CPPFLAGS -DHAVE_DLFCN_H" save_LDFLAGS="$LDFLAGS" wl=$lt_prog_compiler_wl eval LDFLAGS=\"\$LDFLAGS $export_dynamic_flag_spec\" save_LIBS="$LIBS" LIBS="$lt_cv_dlopen_libs $LIBS" AC_CACHE_CHECK([whether a program can dlopen itself], lt_cv_dlopen_self, [dnl _LT_TRY_DLOPEN_SELF( lt_cv_dlopen_self=yes, lt_cv_dlopen_self=yes, lt_cv_dlopen_self=no, lt_cv_dlopen_self=cross) ]) if test "x$lt_cv_dlopen_self" = xyes; then wl=$lt_prog_compiler_wl eval LDFLAGS=\"\$LDFLAGS $lt_prog_compiler_static\" AC_CACHE_CHECK([whether a statically linked program can dlopen itself], lt_cv_dlopen_self_static, [dnl _LT_TRY_DLOPEN_SELF( lt_cv_dlopen_self_static=yes, lt_cv_dlopen_self_static=yes, lt_cv_dlopen_self_static=no, lt_cv_dlopen_self_static=cross) ]) fi CPPFLAGS="$save_CPPFLAGS" LDFLAGS="$save_LDFLAGS" LIBS="$save_LIBS" ;; esac case $lt_cv_dlopen_self in yes|no) enable_dlopen_self=$lt_cv_dlopen_self ;; *) enable_dlopen_self=unknown ;; esac case $lt_cv_dlopen_self_static in yes|no) enable_dlopen_self_static=$lt_cv_dlopen_self_static ;; *) enable_dlopen_self_static=unknown ;; esac fi _LT_DECL([dlopen_support], [enable_dlopen], [0], [Whether dlopen is supported]) _LT_DECL([dlopen_self], [enable_dlopen_self], [0], [Whether dlopen of programs is supported]) _LT_DECL([dlopen_self_static], [enable_dlopen_self_static], [0], [Whether dlopen of statically linked programs is supported]) ])# LT_SYS_DLOPEN_SELF # Old name: AU_ALIAS([AC_LIBTOOL_DLOPEN_SELF], [LT_SYS_DLOPEN_SELF]) dnl aclocal-1.4 backwards compatibility: dnl AC_DEFUN([AC_LIBTOOL_DLOPEN_SELF], []) # _LT_COMPILER_C_O([TAGNAME]) # --------------------------- # Check to see if options -c and -o are simultaneously supported by compiler. # This macro does not hard code the compiler like AC_PROG_CC_C_O. m4_defun([_LT_COMPILER_C_O], [m4_require([_LT_DECL_SED])dnl m4_require([_LT_FILEUTILS_DEFAULTS])dnl m4_require([_LT_TAG_COMPILER])dnl AC_CACHE_CHECK([if $compiler supports -c -o file.$ac_objext], [_LT_TAGVAR(lt_cv_prog_compiler_c_o, $1)], [_LT_TAGVAR(lt_cv_prog_compiler_c_o, $1)=no $RM -r conftest 2>/dev/null mkdir conftest cd conftest mkdir out echo "$lt_simple_compile_test_code" > conftest.$ac_ext lt_compiler_flag="-o out/conftest2.$ac_objext" # Insert the option either (1) after the last *FLAGS variable, or # (2) before a word containing "conftest.", or (3) at the end. # Note that $ac_compile itself does not contain backslashes and begins # with a dollar sign (not a hyphen), so the echo should work correctly. lt_compile=`echo "$ac_compile" | $SED \ -e 's:.*FLAGS}\{0,1\} :&$lt_compiler_flag :; t' \ -e 's: [[^ ]]*conftest\.: $lt_compiler_flag&:; t' \ -e 's:$: $lt_compiler_flag:'` (eval echo "\"\$as_me:$LINENO: $lt_compile\"" >&AS_MESSAGE_LOG_FD) (eval "$lt_compile" 2>out/conftest.err) ac_status=$? cat out/conftest.err >&AS_MESSAGE_LOG_FD echo "$as_me:$LINENO: \$? = $ac_status" >&AS_MESSAGE_LOG_FD if (exit $ac_status) && test -s out/conftest2.$ac_objext then # The compiler can only warn and ignore the option if not recognized # So say no if there are warnings $ECHO "$_lt_compiler_boilerplate" | $SED '/^$/d' > out/conftest.exp $SED '/^$/d; /^ *+/d' out/conftest.err >out/conftest.er2 if test ! -s out/conftest.er2 || diff out/conftest.exp out/conftest.er2 >/dev/null; then _LT_TAGVAR(lt_cv_prog_compiler_c_o, $1)=yes fi fi chmod u+w . 2>&AS_MESSAGE_LOG_FD $RM conftest* # SGI C++ compiler will create directory out/ii_files/ for # template instantiation test -d out/ii_files && $RM out/ii_files/* && rmdir out/ii_files $RM out/* && rmdir out cd .. $RM -r conftest $RM conftest* ]) _LT_TAGDECL([compiler_c_o], [lt_cv_prog_compiler_c_o], [1], [Does compiler simultaneously support -c and -o options?]) ])# _LT_COMPILER_C_O # _LT_COMPILER_FILE_LOCKS([TAGNAME]) # ---------------------------------- # Check to see if we can do hard links to lock some files if needed m4_defun([_LT_COMPILER_FILE_LOCKS], [m4_require([_LT_ENABLE_LOCK])dnl m4_require([_LT_FILEUTILS_DEFAULTS])dnl _LT_COMPILER_C_O([$1]) hard_links="nottested" if test "$_LT_TAGVAR(lt_cv_prog_compiler_c_o, $1)" = no && test "$need_locks" != no; then # do not overwrite the value of need_locks provided by the user AC_MSG_CHECKING([if we can lock with hard links]) hard_links=yes $RM conftest* ln conftest.a conftest.b 2>/dev/null && hard_links=no touch conftest.a ln conftest.a conftest.b 2>&5 || hard_links=no ln conftest.a conftest.b 2>/dev/null && hard_links=no AC_MSG_RESULT([$hard_links]) if test "$hard_links" = no; then AC_MSG_WARN([`$CC' does not support `-c -o', so `make -j' may be unsafe]) need_locks=warn fi else need_locks=no fi _LT_DECL([], [need_locks], [1], [Must we lock files when doing compilation?]) ])# _LT_COMPILER_FILE_LOCKS # _LT_CHECK_OBJDIR # ---------------- m4_defun([_LT_CHECK_OBJDIR], [AC_CACHE_CHECK([for objdir], [lt_cv_objdir], [rm -f .libs 2>/dev/null mkdir .libs 2>/dev/null if test -d .libs; then lt_cv_objdir=.libs else # MS-DOS does not allow filenames that begin with a dot. lt_cv_objdir=_libs fi rmdir .libs 2>/dev/null]) objdir=$lt_cv_objdir _LT_DECL([], [objdir], [0], [The name of the directory that contains temporary libtool files])dnl m4_pattern_allow([LT_OBJDIR])dnl AC_DEFINE_UNQUOTED(LT_OBJDIR, "$lt_cv_objdir/", [Define to the sub-directory in which libtool stores uninstalled libraries.]) ])# _LT_CHECK_OBJDIR # _LT_LINKER_HARDCODE_LIBPATH([TAGNAME]) # -------------------------------------- # Check hardcoding attributes. m4_defun([_LT_LINKER_HARDCODE_LIBPATH], [AC_MSG_CHECKING([how to hardcode library paths into programs]) _LT_TAGVAR(hardcode_action, $1)= if test -n "$_LT_TAGVAR(hardcode_libdir_flag_spec, $1)" || test -n "$_LT_TAGVAR(runpath_var, $1)" || test "X$_LT_TAGVAR(hardcode_automatic, $1)" = "Xyes" ; then # We can hardcode non-existent directories. if test "$_LT_TAGVAR(hardcode_direct, $1)" != no && # If the only mechanism to avoid hardcoding is shlibpath_var, we # have to relink, otherwise we might link with an installed library # when we should be linking with a yet-to-be-installed one ## test "$_LT_TAGVAR(hardcode_shlibpath_var, $1)" != no && test "$_LT_TAGVAR(hardcode_minus_L, $1)" != no; then # Linking always hardcodes the temporary library directory. _LT_TAGVAR(hardcode_action, $1)=relink else # We can link without hardcoding, and we can hardcode nonexisting dirs. _LT_TAGVAR(hardcode_action, $1)=immediate fi else # We cannot hardcode anything, or else we can only hardcode existing # directories. _LT_TAGVAR(hardcode_action, $1)=unsupported fi AC_MSG_RESULT([$_LT_TAGVAR(hardcode_action, $1)]) if test "$_LT_TAGVAR(hardcode_action, $1)" = relink || test "$_LT_TAGVAR(inherit_rpath, $1)" = yes; then # Fast installation is not supported enable_fast_install=no elif test "$shlibpath_overrides_runpath" = yes || test "$enable_shared" = no; then # Fast installation is not necessary enable_fast_install=needless fi _LT_TAGDECL([], [hardcode_action], [0], [How to hardcode a shared library path into an executable]) ])# _LT_LINKER_HARDCODE_LIBPATH # _LT_CMD_STRIPLIB # ---------------- m4_defun([_LT_CMD_STRIPLIB], [m4_require([_LT_DECL_EGREP]) striplib= old_striplib= AC_MSG_CHECKING([whether stripping libraries is possible]) if test -n "$STRIP" && $STRIP -V 2>&1 | $GREP "GNU strip" >/dev/null; then test -z "$old_striplib" && old_striplib="$STRIP --strip-debug" test -z "$striplib" && striplib="$STRIP --strip-unneeded" AC_MSG_RESULT([yes]) else # FIXME - insert some real tests, host_os isn't really good enough case $host_os in darwin*) if test -n "$STRIP" ; then striplib="$STRIP -x" old_striplib="$STRIP -S" AC_MSG_RESULT([yes]) else AC_MSG_RESULT([no]) fi ;; *) AC_MSG_RESULT([no]) ;; esac fi _LT_DECL([], [old_striplib], [1], [Commands to strip libraries]) _LT_DECL([], [striplib], [1]) ])# _LT_CMD_STRIPLIB # _LT_SYS_DYNAMIC_LINKER([TAG]) # ----------------------------- # PORTME Fill in your ld.so characteristics m4_defun([_LT_SYS_DYNAMIC_LINKER], [AC_REQUIRE([AC_CANONICAL_HOST])dnl m4_require([_LT_DECL_EGREP])dnl m4_require([_LT_FILEUTILS_DEFAULTS])dnl m4_require([_LT_DECL_OBJDUMP])dnl m4_require([_LT_DECL_SED])dnl m4_require([_LT_CHECK_SHELL_FEATURES])dnl AC_MSG_CHECKING([dynamic linker characteristics]) m4_if([$1], [], [ if test "$GCC" = yes; then case $host_os in darwin*) lt_awk_arg="/^libraries:/,/LR/" ;; *) lt_awk_arg="/^libraries:/" ;; esac case $host_os in mingw* | cegcc*) lt_sed_strip_eq="s,=\([[A-Za-z]]:\),\1,g" ;; *) lt_sed_strip_eq="s,=/,/,g" ;; esac lt_search_path_spec=`$CC -print-search-dirs | awk $lt_awk_arg | $SED -e "s/^libraries://" -e $lt_sed_strip_eq` case $lt_search_path_spec in *\;*) # if the path contains ";" then we assume it to be the separator # otherwise default to the standard path separator (i.e. ":") - it is # assumed that no part of a normal pathname contains ";" but that should # okay in the real world where ";" in dirpaths is itself problematic. lt_search_path_spec=`$ECHO "$lt_search_path_spec" | $SED 's/;/ /g'` ;; *) lt_search_path_spec=`$ECHO "$lt_search_path_spec" | $SED "s/$PATH_SEPARATOR/ /g"` ;; esac # Ok, now we have the path, separated by spaces, we can step through it # and add multilib dir if necessary. lt_tmp_lt_search_path_spec= lt_multi_os_dir=`$CC $CPPFLAGS $CFLAGS $LDFLAGS -print-multi-os-directory 2>/dev/null` for lt_sys_path in $lt_search_path_spec; do if test -d "$lt_sys_path/$lt_multi_os_dir"; then lt_tmp_lt_search_path_spec="$lt_tmp_lt_search_path_spec $lt_sys_path/$lt_multi_os_dir" else test -d "$lt_sys_path" && \ lt_tmp_lt_search_path_spec="$lt_tmp_lt_search_path_spec $lt_sys_path" fi done lt_search_path_spec=`$ECHO "$lt_tmp_lt_search_path_spec" | awk ' BEGIN {RS=" "; FS="/|\n";} { lt_foo=""; lt_count=0; for (lt_i = NF; lt_i > 0; lt_i--) { if ($lt_i != "" && $lt_i != ".") { if ($lt_i == "..") { lt_count++; } else { if (lt_count == 0) { lt_foo="/" $lt_i lt_foo; } else { lt_count--; } } } } if (lt_foo != "") { lt_freq[[lt_foo]]++; } if (lt_freq[[lt_foo]] == 1) { print lt_foo; } }'` # AWK program above erroneously prepends '/' to C:/dos/paths # for these hosts. case $host_os in mingw* | cegcc*) lt_search_path_spec=`$ECHO "$lt_search_path_spec" |\ $SED 's,/\([[A-Za-z]]:\),\1,g'` ;; esac sys_lib_search_path_spec=`$ECHO "$lt_search_path_spec" | $lt_NL2SP` else sys_lib_search_path_spec="/lib /usr/lib /usr/local/lib" fi]) library_names_spec= libname_spec='lib$name' soname_spec= shrext_cmds=".so" postinstall_cmds= postuninstall_cmds= finish_cmds= finish_eval= shlibpath_var= shlibpath_overrides_runpath=unknown version_type=none dynamic_linker="$host_os ld.so" sys_lib_dlsearch_path_spec="/lib /usr/lib" need_lib_prefix=unknown hardcode_into_libs=no # when you set need_version to no, make sure it does not cause -set_version # flags to be left without arguments need_version=unknown case $host_os in aix3*) version_type=linux # correct to gnu/linux during the next big refactor library_names_spec='${libname}${release}${shared_ext}$versuffix $libname.a' shlibpath_var=LIBPATH # AIX 3 has no versioning support, so we append a major version to the name. soname_spec='${libname}${release}${shared_ext}$major' ;; aix[[4-9]]*) version_type=linux # correct to gnu/linux during the next big refactor need_lib_prefix=no need_version=no hardcode_into_libs=yes if test "$host_cpu" = ia64; then # AIX 5 supports IA64 library_names_spec='${libname}${release}${shared_ext}$major ${libname}${release}${shared_ext}$versuffix $libname${shared_ext}' shlibpath_var=LD_LIBRARY_PATH else # With GCC up to 2.95.x, collect2 would create an import file # for dependence libraries. The import file would start with # the line `#! .'. This would cause the generated library to # depend on `.', always an invalid library. This was fixed in # development snapshots of GCC prior to 3.0. case $host_os in aix4 | aix4.[[01]] | aix4.[[01]].*) if { echo '#if __GNUC__ > 2 || (__GNUC__ == 2 && __GNUC_MINOR__ >= 97)' echo ' yes ' echo '#endif'; } | ${CC} -E - | $GREP yes > /dev/null; then : else can_build_shared=no fi ;; esac # AIX (on Power*) has no versioning support, so currently we can not hardcode correct # soname into executable. Probably we can add versioning support to # collect2, so additional links can be useful in future. if test "$aix_use_runtimelinking" = yes; then # If using run time linking (on AIX 4.2 or later) use lib.so # instead of lib.a to let people know that these are not # typical AIX shared libraries. library_names_spec='${libname}${release}${shared_ext}$versuffix ${libname}${release}${shared_ext}$major $libname${shared_ext}' else # We preserve .a as extension for shared libraries through AIX4.2 # and later when we are not doing run time linking. library_names_spec='${libname}${release}.a $libname.a' soname_spec='${libname}${release}${shared_ext}$major' fi shlibpath_var=LIBPATH fi ;; amigaos*) case $host_cpu in powerpc) # Since July 2007 AmigaOS4 officially supports .so libraries. # When compiling the executable, add -use-dynld -Lsobjs: to the compileline. library_names_spec='${libname}${release}${shared_ext}$versuffix ${libname}${release}${shared_ext}$major $libname${shared_ext}' ;; m68k) library_names_spec='$libname.ixlibrary $libname.a' # Create ${libname}_ixlibrary.a entries in /sys/libs. finish_eval='for lib in `ls $libdir/*.ixlibrary 2>/dev/null`; do libname=`func_echo_all "$lib" | $SED '\''s%^.*/\([[^/]]*\)\.ixlibrary$%\1%'\''`; test $RM /sys/libs/${libname}_ixlibrary.a; $show "cd /sys/libs && $LN_S $lib ${libname}_ixlibrary.a"; cd /sys/libs && $LN_S $lib ${libname}_ixlibrary.a || exit 1; done' ;; esac ;; beos*) library_names_spec='${libname}${shared_ext}' dynamic_linker="$host_os ld.so" shlibpath_var=LIBRARY_PATH ;; bsdi[[45]]*) version_type=linux # correct to gnu/linux during the next big refactor need_version=no library_names_spec='${libname}${release}${shared_ext}$versuffix ${libname}${release}${shared_ext}$major $libname${shared_ext}' soname_spec='${libname}${release}${shared_ext}$major' finish_cmds='PATH="\$PATH:/sbin" ldconfig $libdir' shlibpath_var=LD_LIBRARY_PATH sys_lib_search_path_spec="/shlib /usr/lib /usr/X11/lib /usr/contrib/lib /lib /usr/local/lib" sys_lib_dlsearch_path_spec="/shlib /usr/lib /usr/local/lib" # the default ld.so.conf also contains /usr/contrib/lib and # /usr/X11R6/lib (/usr/X11 is a link to /usr/X11R6), but let us allow # libtool to hard-code these into programs ;; cygwin* | mingw* | pw32* | cegcc*) version_type=windows shrext_cmds=".dll" need_version=no need_lib_prefix=no case $GCC,$cc_basename in yes,*) # gcc library_names_spec='$libname.dll.a' # DLL is installed to $(libdir)/../bin by postinstall_cmds postinstall_cmds='base_file=`basename \${file}`~ dlpath=`$SHELL 2>&1 -c '\''. $dir/'\''\${base_file}'\''i; echo \$dlname'\''`~ dldir=$destdir/`dirname \$dlpath`~ test -d \$dldir || mkdir -p \$dldir~ $install_prog $dir/$dlname \$dldir/$dlname~ chmod a+x \$dldir/$dlname~ if test -n '\''$stripme'\'' && test -n '\''$striplib'\''; then eval '\''$striplib \$dldir/$dlname'\'' || exit \$?; fi' postuninstall_cmds='dldll=`$SHELL 2>&1 -c '\''. $file; echo \$dlname'\''`~ dlpath=$dir/\$dldll~ $RM \$dlpath' shlibpath_overrides_runpath=yes case $host_os in cygwin*) # Cygwin DLLs use 'cyg' prefix rather than 'lib' soname_spec='`echo ${libname} | sed -e 's/^lib/cyg/'``echo ${release} | $SED -e 's/[[.]]/-/g'`${versuffix}${shared_ext}' m4_if([$1], [],[ sys_lib_search_path_spec="$sys_lib_search_path_spec /usr/lib/w32api"]) ;; mingw* | cegcc*) # MinGW DLLs use traditional 'lib' prefix soname_spec='${libname}`echo ${release} | $SED -e 's/[[.]]/-/g'`${versuffix}${shared_ext}' ;; pw32*) # pw32 DLLs use 'pw' prefix rather than 'lib' library_names_spec='`echo ${libname} | sed -e 's/^lib/pw/'``echo ${release} | $SED -e 's/[[.]]/-/g'`${versuffix}${shared_ext}' ;; esac dynamic_linker='Win32 ld.exe' ;; *,cl*) # Native MSVC libname_spec='$name' soname_spec='${libname}`echo ${release} | $SED -e 's/[[.]]/-/g'`${versuffix}${shared_ext}' library_names_spec='${libname}.dll.lib' case $build_os in mingw*) sys_lib_search_path_spec= lt_save_ifs=$IFS IFS=';' for lt_path in $LIB do IFS=$lt_save_ifs # Let DOS variable expansion print the short 8.3 style file name. lt_path=`cd "$lt_path" 2>/dev/null && cmd //C "for %i in (".") do @echo %~si"` sys_lib_search_path_spec="$sys_lib_search_path_spec $lt_path" done IFS=$lt_save_ifs # Convert to MSYS style. sys_lib_search_path_spec=`$ECHO "$sys_lib_search_path_spec" | sed -e 's|\\\\|/|g' -e 's| \\([[a-zA-Z]]\\):| /\\1|g' -e 's|^ ||'` ;; cygwin*) # Convert to unix form, then to dos form, then back to unix form # but this time dos style (no spaces!) so that the unix form looks # like /cygdrive/c/PROGRA~1:/cygdr... sys_lib_search_path_spec=`cygpath --path --unix "$LIB"` sys_lib_search_path_spec=`cygpath --path --dos "$sys_lib_search_path_spec" 2>/dev/null` sys_lib_search_path_spec=`cygpath --path --unix "$sys_lib_search_path_spec" | $SED -e "s/$PATH_SEPARATOR/ /g"` ;; *) sys_lib_search_path_spec="$LIB" if $ECHO "$sys_lib_search_path_spec" | [$GREP ';[c-zC-Z]:/' >/dev/null]; then # It is most probably a Windows format PATH. sys_lib_search_path_spec=`$ECHO "$sys_lib_search_path_spec" | $SED -e 's/;/ /g'` else sys_lib_search_path_spec=`$ECHO "$sys_lib_search_path_spec" | $SED -e "s/$PATH_SEPARATOR/ /g"` fi # FIXME: find the short name or the path components, as spaces are # common. (e.g. "Program Files" -> "PROGRA~1") ;; esac # DLL is installed to $(libdir)/../bin by postinstall_cmds postinstall_cmds='base_file=`basename \${file}`~ dlpath=`$SHELL 2>&1 -c '\''. $dir/'\''\${base_file}'\''i; echo \$dlname'\''`~ dldir=$destdir/`dirname \$dlpath`~ test -d \$dldir || mkdir -p \$dldir~ $install_prog $dir/$dlname \$dldir/$dlname' postuninstall_cmds='dldll=`$SHELL 2>&1 -c '\''. $file; echo \$dlname'\''`~ dlpath=$dir/\$dldll~ $RM \$dlpath' shlibpath_overrides_runpath=yes dynamic_linker='Win32 link.exe' ;; *) # Assume MSVC wrapper library_names_spec='${libname}`echo ${release} | $SED -e 's/[[.]]/-/g'`${versuffix}${shared_ext} $libname.lib' dynamic_linker='Win32 ld.exe' ;; esac # FIXME: first we should search . and the directory the executable is in shlibpath_var=PATH ;; darwin* | rhapsody*) dynamic_linker="$host_os dyld" version_type=darwin need_lib_prefix=no need_version=no library_names_spec='${libname}${release}${major}$shared_ext ${libname}$shared_ext' soname_spec='${libname}${release}${major}$shared_ext' shlibpath_overrides_runpath=yes shlibpath_var=DYLD_LIBRARY_PATH shrext_cmds='`test .$module = .yes && echo .so || echo .dylib`' m4_if([$1], [],[ sys_lib_search_path_spec="$sys_lib_search_path_spec /usr/local/lib"]) sys_lib_dlsearch_path_spec='/usr/local/lib /lib /usr/lib' ;; dgux*) version_type=linux # correct to gnu/linux during the next big refactor need_lib_prefix=no need_version=no library_names_spec='${libname}${release}${shared_ext}$versuffix ${libname}${release}${shared_ext}$major $libname$shared_ext' soname_spec='${libname}${release}${shared_ext}$major' shlibpath_var=LD_LIBRARY_PATH ;; freebsd* | dragonfly*) # DragonFly does not have aout. When/if they implement a new # versioning mechanism, adjust this. if test -x /usr/bin/objformat; then objformat=`/usr/bin/objformat` else case $host_os in freebsd[[23]].*) objformat=aout ;; *) objformat=elf ;; esac fi version_type=freebsd-$objformat case $version_type in freebsd-elf*) library_names_spec='${libname}${release}${shared_ext}$versuffix ${libname}${release}${shared_ext} $libname${shared_ext}' need_version=no need_lib_prefix=no ;; freebsd-*) library_names_spec='${libname}${release}${shared_ext}$versuffix $libname${shared_ext}$versuffix' need_version=yes ;; esac shlibpath_var=LD_LIBRARY_PATH case $host_os in freebsd2.*) shlibpath_overrides_runpath=yes ;; freebsd3.[[01]]* | freebsdelf3.[[01]]*) shlibpath_overrides_runpath=yes hardcode_into_libs=yes ;; freebsd3.[[2-9]]* | freebsdelf3.[[2-9]]* | \ freebsd4.[[0-5]] | freebsdelf4.[[0-5]] | freebsd4.1.1 | freebsdelf4.1.1) shlibpath_overrides_runpath=no hardcode_into_libs=yes ;; *) # from 4.6 on, and DragonFly shlibpath_overrides_runpath=yes hardcode_into_libs=yes ;; esac ;; haiku*) version_type=linux # correct to gnu/linux during the next big refactor need_lib_prefix=no need_version=no dynamic_linker="$host_os runtime_loader" library_names_spec='${libname}${release}${shared_ext}$versuffix ${libname}${release}${shared_ext}${major} ${libname}${shared_ext}' soname_spec='${libname}${release}${shared_ext}$major' shlibpath_var=LIBRARY_PATH shlibpath_overrides_runpath=yes sys_lib_dlsearch_path_spec='/boot/home/config/lib /boot/common/lib /boot/system/lib' hardcode_into_libs=yes ;; hpux9* | hpux10* | hpux11*) # Give a soname corresponding to the major version so that dld.sl refuses to # link against other versions. version_type=sunos need_lib_prefix=no need_version=no case $host_cpu in ia64*) shrext_cmds='.so' hardcode_into_libs=yes dynamic_linker="$host_os dld.so" shlibpath_var=LD_LIBRARY_PATH shlibpath_overrides_runpath=yes # Unless +noenvvar is specified. library_names_spec='${libname}${release}${shared_ext}$versuffix ${libname}${release}${shared_ext}$major $libname${shared_ext}' soname_spec='${libname}${release}${shared_ext}$major' if test "X$HPUX_IA64_MODE" = X32; then sys_lib_search_path_spec="/usr/lib/hpux32 /usr/local/lib/hpux32 /usr/local/lib" else sys_lib_search_path_spec="/usr/lib/hpux64 /usr/local/lib/hpux64" fi sys_lib_dlsearch_path_spec=$sys_lib_search_path_spec ;; hppa*64*) shrext_cmds='.sl' hardcode_into_libs=yes dynamic_linker="$host_os dld.sl" shlibpath_var=LD_LIBRARY_PATH # How should we handle SHLIB_PATH shlibpath_overrides_runpath=yes # Unless +noenvvar is specified. library_names_spec='${libname}${release}${shared_ext}$versuffix ${libname}${release}${shared_ext}$major $libname${shared_ext}' soname_spec='${libname}${release}${shared_ext}$major' sys_lib_search_path_spec="/usr/lib/pa20_64 /usr/ccs/lib/pa20_64" sys_lib_dlsearch_path_spec=$sys_lib_search_path_spec ;; *) shrext_cmds='.sl' dynamic_linker="$host_os dld.sl" shlibpath_var=SHLIB_PATH shlibpath_overrides_runpath=no # +s is required to enable SHLIB_PATH library_names_spec='${libname}${release}${shared_ext}$versuffix ${libname}${release}${shared_ext}$major $libname${shared_ext}' soname_spec='${libname}${release}${shared_ext}$major' ;; esac # HP-UX runs *really* slowly unless shared libraries are mode 555, ... postinstall_cmds='chmod 555 $lib' # or fails outright, so override atomically: install_override_mode=555 ;; interix[[3-9]]*) version_type=linux # correct to gnu/linux during the next big refactor need_lib_prefix=no need_version=no library_names_spec='${libname}${release}${shared_ext}$versuffix ${libname}${release}${shared_ext}$major ${libname}${shared_ext}' soname_spec='${libname}${release}${shared_ext}$major' dynamic_linker='Interix 3.x ld.so.1 (PE, like ELF)' shlibpath_var=LD_LIBRARY_PATH shlibpath_overrides_runpath=no hardcode_into_libs=yes ;; irix5* | irix6* | nonstopux*) case $host_os in nonstopux*) version_type=nonstopux ;; *) if test "$lt_cv_prog_gnu_ld" = yes; then version_type=linux # correct to gnu/linux during the next big refactor else version_type=irix fi ;; esac need_lib_prefix=no need_version=no soname_spec='${libname}${release}${shared_ext}$major' library_names_spec='${libname}${release}${shared_ext}$versuffix ${libname}${release}${shared_ext}$major ${libname}${release}${shared_ext} $libname${shared_ext}' case $host_os in irix5* | nonstopux*) libsuff= shlibsuff= ;; *) case $LD in # libtool.m4 will add one of these switches to LD *-32|*"-32 "|*-melf32bsmip|*"-melf32bsmip ") libsuff= shlibsuff= libmagic=32-bit;; *-n32|*"-n32 "|*-melf32bmipn32|*"-melf32bmipn32 ") libsuff=32 shlibsuff=N32 libmagic=N32;; *-64|*"-64 "|*-melf64bmip|*"-melf64bmip ") libsuff=64 shlibsuff=64 libmagic=64-bit;; *) libsuff= shlibsuff= libmagic=never-match;; esac ;; esac shlibpath_var=LD_LIBRARY${shlibsuff}_PATH shlibpath_overrides_runpath=no sys_lib_search_path_spec="/usr/lib${libsuff} /lib${libsuff} /usr/local/lib${libsuff}" sys_lib_dlsearch_path_spec="/usr/lib${libsuff} /lib${libsuff}" hardcode_into_libs=yes ;; # No shared lib support for Linux oldld, aout, or coff. linux*oldld* | linux*aout* | linux*coff*) dynamic_linker=no ;; # This must be glibc/ELF. linux* | k*bsd*-gnu | kopensolaris*-gnu | gnu*) version_type=linux # correct to gnu/linux during the next big refactor need_lib_prefix=no need_version=no library_names_spec='${libname}${release}${shared_ext}$versuffix ${libname}${release}${shared_ext}$major $libname${shared_ext}' soname_spec='${libname}${release}${shared_ext}$major' finish_cmds='PATH="\$PATH:/sbin" ldconfig -n $libdir' shlibpath_var=LD_LIBRARY_PATH shlibpath_overrides_runpath=no # Some binutils ld are patched to set DT_RUNPATH AC_CACHE_VAL([lt_cv_shlibpath_overrides_runpath], [lt_cv_shlibpath_overrides_runpath=no save_LDFLAGS=$LDFLAGS save_libdir=$libdir eval "libdir=/foo; wl=\"$_LT_TAGVAR(lt_prog_compiler_wl, $1)\"; \ LDFLAGS=\"\$LDFLAGS $_LT_TAGVAR(hardcode_libdir_flag_spec, $1)\"" AC_LINK_IFELSE([AC_LANG_PROGRAM([],[])], [AS_IF([ ($OBJDUMP -p conftest$ac_exeext) 2>/dev/null | grep "RUNPATH.*$libdir" >/dev/null], [lt_cv_shlibpath_overrides_runpath=yes])]) LDFLAGS=$save_LDFLAGS libdir=$save_libdir ]) shlibpath_overrides_runpath=$lt_cv_shlibpath_overrides_runpath # This implies no fast_install, which is unacceptable. # Some rework will be needed to allow for fast_install # before this can be enabled. hardcode_into_libs=yes # Append ld.so.conf contents to the search path if test -f /etc/ld.so.conf; then lt_ld_extra=`awk '/^include / { system(sprintf("cd /etc; cat %s 2>/dev/null", \[$]2)); skip = 1; } { if (!skip) print \[$]0; skip = 0; }' < /etc/ld.so.conf | $SED -e 's/#.*//;/^[ ]*hwcap[ ]/d;s/[:, ]/ /g;s/=[^=]*$//;s/=[^= ]* / /g;s/"//g;/^$/d' | tr '\n' ' '` sys_lib_dlsearch_path_spec="/lib /usr/lib $lt_ld_extra" fi # We used to test for /lib/ld.so.1 and disable shared libraries on # powerpc, because MkLinux only supported shared libraries with the # GNU dynamic linker. Since this was broken with cross compilers, # most powerpc-linux boxes support dynamic linking these days and # people can always --disable-shared, the test was removed, and we # assume the GNU/Linux dynamic linker is in use. dynamic_linker='GNU/Linux ld.so' ;; netbsdelf*-gnu) version_type=linux need_lib_prefix=no need_version=no library_names_spec='${libname}${release}${shared_ext}$versuffix ${libname}${release}${shared_ext}$major ${libname}${shared_ext}' soname_spec='${libname}${release}${shared_ext}$major' shlibpath_var=LD_LIBRARY_PATH shlibpath_overrides_runpath=no hardcode_into_libs=yes dynamic_linker='NetBSD ld.elf_so' ;; netbsd*) version_type=sunos need_lib_prefix=no need_version=no if echo __ELF__ | $CC -E - | $GREP __ELF__ >/dev/null; then library_names_spec='${libname}${release}${shared_ext}$versuffix ${libname}${shared_ext}$versuffix' finish_cmds='PATH="\$PATH:/sbin" ldconfig -m $libdir' dynamic_linker='NetBSD (a.out) ld.so' else library_names_spec='${libname}${release}${shared_ext}$versuffix ${libname}${release}${shared_ext}$major ${libname}${shared_ext}' soname_spec='${libname}${release}${shared_ext}$major' dynamic_linker='NetBSD ld.elf_so' fi shlibpath_var=LD_LIBRARY_PATH shlibpath_overrides_runpath=yes hardcode_into_libs=yes ;; newsos6) version_type=linux # correct to gnu/linux during the next big refactor library_names_spec='${libname}${release}${shared_ext}$versuffix ${libname}${release}${shared_ext}$major $libname${shared_ext}' shlibpath_var=LD_LIBRARY_PATH shlibpath_overrides_runpath=yes ;; *nto* | *qnx*) version_type=qnx need_lib_prefix=no need_version=no library_names_spec='${libname}${release}${shared_ext}$versuffix ${libname}${release}${shared_ext}$major $libname${shared_ext}' soname_spec='${libname}${release}${shared_ext}$major' shlibpath_var=LD_LIBRARY_PATH shlibpath_overrides_runpath=no hardcode_into_libs=yes dynamic_linker='ldqnx.so' ;; openbsd*) version_type=sunos sys_lib_dlsearch_path_spec="/usr/lib" need_lib_prefix=no # Some older versions of OpenBSD (3.3 at least) *do* need versioned libs. case $host_os in openbsd3.3 | openbsd3.3.*) need_version=yes ;; *) need_version=no ;; esac library_names_spec='${libname}${release}${shared_ext}$versuffix ${libname}${shared_ext}$versuffix' finish_cmds='PATH="\$PATH:/sbin" ldconfig -m $libdir' shlibpath_var=LD_LIBRARY_PATH if test -z "`echo __ELF__ | $CC -E - | $GREP __ELF__`" || test "$host_os-$host_cpu" = "openbsd2.8-powerpc"; then case $host_os in openbsd2.[[89]] | openbsd2.[[89]].*) shlibpath_overrides_runpath=no ;; *) shlibpath_overrides_runpath=yes ;; esac else shlibpath_overrides_runpath=yes fi ;; os2*) libname_spec='$name' shrext_cmds=".dll" need_lib_prefix=no library_names_spec='$libname${shared_ext} $libname.a' dynamic_linker='OS/2 ld.exe' shlibpath_var=LIBPATH ;; osf3* | osf4* | osf5*) version_type=osf need_lib_prefix=no need_version=no soname_spec='${libname}${release}${shared_ext}$major' library_names_spec='${libname}${release}${shared_ext}$versuffix ${libname}${release}${shared_ext}$major $libname${shared_ext}' shlibpath_var=LD_LIBRARY_PATH sys_lib_search_path_spec="/usr/shlib /usr/ccs/lib /usr/lib/cmplrs/cc /usr/lib /usr/local/lib /var/shlib" sys_lib_dlsearch_path_spec="$sys_lib_search_path_spec" ;; rdos*) dynamic_linker=no ;; solaris*) version_type=linux # correct to gnu/linux during the next big refactor need_lib_prefix=no need_version=no library_names_spec='${libname}${release}${shared_ext}$versuffix ${libname}${release}${shared_ext}$major $libname${shared_ext}' soname_spec='${libname}${release}${shared_ext}$major' shlibpath_var=LD_LIBRARY_PATH shlibpath_overrides_runpath=yes hardcode_into_libs=yes # ldd complains unless libraries are executable postinstall_cmds='chmod +x $lib' ;; sunos4*) version_type=sunos library_names_spec='${libname}${release}${shared_ext}$versuffix ${libname}${shared_ext}$versuffix' finish_cmds='PATH="\$PATH:/usr/etc" ldconfig $libdir' shlibpath_var=LD_LIBRARY_PATH shlibpath_overrides_runpath=yes if test "$with_gnu_ld" = yes; then need_lib_prefix=no fi need_version=yes ;; sysv4 | sysv4.3*) version_type=linux # correct to gnu/linux during the next big refactor library_names_spec='${libname}${release}${shared_ext}$versuffix ${libname}${release}${shared_ext}$major $libname${shared_ext}' soname_spec='${libname}${release}${shared_ext}$major' shlibpath_var=LD_LIBRARY_PATH case $host_vendor in sni) shlibpath_overrides_runpath=no need_lib_prefix=no runpath_var=LD_RUN_PATH ;; siemens) need_lib_prefix=no ;; motorola) need_lib_prefix=no need_version=no shlibpath_overrides_runpath=no sys_lib_search_path_spec='/lib /usr/lib /usr/ccs/lib' ;; esac ;; sysv4*MP*) if test -d /usr/nec ;then version_type=linux # correct to gnu/linux during the next big refactor library_names_spec='$libname${shared_ext}.$versuffix $libname${shared_ext}.$major $libname${shared_ext}' soname_spec='$libname${shared_ext}.$major' shlibpath_var=LD_LIBRARY_PATH fi ;; sysv5* | sco3.2v5* | sco5v6* | unixware* | OpenUNIX* | sysv4*uw2*) version_type=freebsd-elf need_lib_prefix=no need_version=no library_names_spec='${libname}${release}${shared_ext}$versuffix ${libname}${release}${shared_ext} $libname${shared_ext}' soname_spec='${libname}${release}${shared_ext}$major' shlibpath_var=LD_LIBRARY_PATH shlibpath_overrides_runpath=yes hardcode_into_libs=yes if test "$with_gnu_ld" = yes; then sys_lib_search_path_spec='/usr/local/lib /usr/gnu/lib /usr/ccs/lib /usr/lib /lib' else sys_lib_search_path_spec='/usr/ccs/lib /usr/lib' case $host_os in sco3.2v5*) sys_lib_search_path_spec="$sys_lib_search_path_spec /lib" ;; esac fi sys_lib_dlsearch_path_spec='/usr/lib' ;; tpf*) # TPF is a cross-target only. Preferred cross-host = GNU/Linux. version_type=linux # correct to gnu/linux during the next big refactor need_lib_prefix=no need_version=no library_names_spec='${libname}${release}${shared_ext}$versuffix ${libname}${release}${shared_ext}$major $libname${shared_ext}' shlibpath_var=LD_LIBRARY_PATH shlibpath_overrides_runpath=no hardcode_into_libs=yes ;; uts4*) version_type=linux # correct to gnu/linux during the next big refactor library_names_spec='${libname}${release}${shared_ext}$versuffix ${libname}${release}${shared_ext}$major $libname${shared_ext}' soname_spec='${libname}${release}${shared_ext}$major' shlibpath_var=LD_LIBRARY_PATH ;; *) dynamic_linker=no ;; esac AC_MSG_RESULT([$dynamic_linker]) test "$dynamic_linker" = no && can_build_shared=no variables_saved_for_relink="PATH $shlibpath_var $runpath_var" if test "$GCC" = yes; then variables_saved_for_relink="$variables_saved_for_relink GCC_EXEC_PREFIX COMPILER_PATH LIBRARY_PATH" fi if test "${lt_cv_sys_lib_search_path_spec+set}" = set; then sys_lib_search_path_spec="$lt_cv_sys_lib_search_path_spec" fi if test "${lt_cv_sys_lib_dlsearch_path_spec+set}" = set; then sys_lib_dlsearch_path_spec="$lt_cv_sys_lib_dlsearch_path_spec" fi _LT_DECL([], [variables_saved_for_relink], [1], [Variables whose values should be saved in libtool wrapper scripts and restored at link time]) _LT_DECL([], [need_lib_prefix], [0], [Do we need the "lib" prefix for modules?]) _LT_DECL([], [need_version], [0], [Do we need a version for libraries?]) _LT_DECL([], [version_type], [0], [Library versioning type]) _LT_DECL([], [runpath_var], [0], [Shared library runtime path variable]) _LT_DECL([], [shlibpath_var], [0],[Shared library path variable]) _LT_DECL([], [shlibpath_overrides_runpath], [0], [Is shlibpath searched before the hard-coded library search path?]) _LT_DECL([], [libname_spec], [1], [Format of library name prefix]) _LT_DECL([], [library_names_spec], [1], [[List of archive names. First name is the real one, the rest are links. The last name is the one that the linker finds with -lNAME]]) _LT_DECL([], [soname_spec], [1], [[The coded name of the library, if different from the real name]]) _LT_DECL([], [install_override_mode], [1], [Permission mode override for installation of shared libraries]) _LT_DECL([], [postinstall_cmds], [2], [Command to use after installation of a shared archive]) _LT_DECL([], [postuninstall_cmds], [2], [Command to use after uninstallation of a shared archive]) _LT_DECL([], [finish_cmds], [2], [Commands used to finish a libtool library installation in a directory]) _LT_DECL([], [finish_eval], [1], [[As "finish_cmds", except a single script fragment to be evaled but not shown]]) _LT_DECL([], [hardcode_into_libs], [0], [Whether we should hardcode library paths into libraries]) _LT_DECL([], [sys_lib_search_path_spec], [2], [Compile-time system search path for libraries]) _LT_DECL([], [sys_lib_dlsearch_path_spec], [2], [Run-time system search path for libraries]) ])# _LT_SYS_DYNAMIC_LINKER # _LT_PATH_TOOL_PREFIX(TOOL) # -------------------------- # find a file program which can recognize shared library AC_DEFUN([_LT_PATH_TOOL_PREFIX], [m4_require([_LT_DECL_EGREP])dnl AC_MSG_CHECKING([for $1]) AC_CACHE_VAL(lt_cv_path_MAGIC_CMD, [case $MAGIC_CMD in [[\\/*] | ?:[\\/]*]) lt_cv_path_MAGIC_CMD="$MAGIC_CMD" # Let the user override the test with a path. ;; *) lt_save_MAGIC_CMD="$MAGIC_CMD" lt_save_ifs="$IFS"; IFS=$PATH_SEPARATOR dnl $ac_dummy forces splitting on constant user-supplied paths. dnl POSIX.2 word splitting is done only on the output of word expansions, dnl not every word. This closes a longstanding sh security hole. ac_dummy="m4_if([$2], , $PATH, [$2])" for ac_dir in $ac_dummy; do IFS="$lt_save_ifs" test -z "$ac_dir" && ac_dir=. if test -f $ac_dir/$1; then lt_cv_path_MAGIC_CMD="$ac_dir/$1" if test -n "$file_magic_test_file"; then case $deplibs_check_method in "file_magic "*) file_magic_regex=`expr "$deplibs_check_method" : "file_magic \(.*\)"` MAGIC_CMD="$lt_cv_path_MAGIC_CMD" if eval $file_magic_cmd \$file_magic_test_file 2> /dev/null | $EGREP "$file_magic_regex" > /dev/null; then : else cat <<_LT_EOF 1>&2 *** Warning: the command libtool uses to detect shared libraries, *** $file_magic_cmd, produces output that libtool cannot recognize. *** The result is that libtool may fail to recognize shared libraries *** as such. This will affect the creation of libtool libraries that *** depend on shared libraries, but programs linked with such libtool *** libraries will work regardless of this problem. Nevertheless, you *** may want to report the problem to your system manager and/or to *** bug-libtool@gnu.org _LT_EOF fi ;; esac fi break fi done IFS="$lt_save_ifs" MAGIC_CMD="$lt_save_MAGIC_CMD" ;; esac]) MAGIC_CMD="$lt_cv_path_MAGIC_CMD" if test -n "$MAGIC_CMD"; then AC_MSG_RESULT($MAGIC_CMD) else AC_MSG_RESULT(no) fi _LT_DECL([], [MAGIC_CMD], [0], [Used to examine libraries when file_magic_cmd begins with "file"])dnl ])# _LT_PATH_TOOL_PREFIX # Old name: AU_ALIAS([AC_PATH_TOOL_PREFIX], [_LT_PATH_TOOL_PREFIX]) dnl aclocal-1.4 backwards compatibility: dnl AC_DEFUN([AC_PATH_TOOL_PREFIX], []) # _LT_PATH_MAGIC # -------------- # find a file program which can recognize a shared library m4_defun([_LT_PATH_MAGIC], [_LT_PATH_TOOL_PREFIX(${ac_tool_prefix}file, /usr/bin$PATH_SEPARATOR$PATH) if test -z "$lt_cv_path_MAGIC_CMD"; then if test -n "$ac_tool_prefix"; then _LT_PATH_TOOL_PREFIX(file, /usr/bin$PATH_SEPARATOR$PATH) else MAGIC_CMD=: fi fi ])# _LT_PATH_MAGIC # LT_PATH_LD # ---------- # find the pathname to the GNU or non-GNU linker AC_DEFUN([LT_PATH_LD], [AC_REQUIRE([AC_PROG_CC])dnl AC_REQUIRE([AC_CANONICAL_HOST])dnl AC_REQUIRE([AC_CANONICAL_BUILD])dnl m4_require([_LT_DECL_SED])dnl m4_require([_LT_DECL_EGREP])dnl m4_require([_LT_PROG_ECHO_BACKSLASH])dnl AC_ARG_WITH([gnu-ld], [AS_HELP_STRING([--with-gnu-ld], [assume the C compiler uses GNU ld @<:@default=no@:>@])], [test "$withval" = no || with_gnu_ld=yes], [with_gnu_ld=no])dnl ac_prog=ld if test "$GCC" = yes; then # Check if gcc -print-prog-name=ld gives a path. AC_MSG_CHECKING([for ld used by $CC]) case $host in *-*-mingw*) # gcc leaves a trailing carriage return which upsets mingw ac_prog=`($CC -print-prog-name=ld) 2>&5 | tr -d '\015'` ;; *) ac_prog=`($CC -print-prog-name=ld) 2>&5` ;; esac case $ac_prog in # Accept absolute paths. [[\\/]]* | ?:[[\\/]]*) re_direlt='/[[^/]][[^/]]*/\.\./' # Canonicalize the pathname of ld ac_prog=`$ECHO "$ac_prog"| $SED 's%\\\\%/%g'` while $ECHO "$ac_prog" | $GREP "$re_direlt" > /dev/null 2>&1; do ac_prog=`$ECHO $ac_prog| $SED "s%$re_direlt%/%"` done test -z "$LD" && LD="$ac_prog" ;; "") # If it fails, then pretend we aren't using GCC. ac_prog=ld ;; *) # If it is relative, then search for the first ld in PATH. with_gnu_ld=unknown ;; esac elif test "$with_gnu_ld" = yes; then AC_MSG_CHECKING([for GNU ld]) else AC_MSG_CHECKING([for non-GNU ld]) fi AC_CACHE_VAL(lt_cv_path_LD, [if test -z "$LD"; then lt_save_ifs="$IFS"; IFS=$PATH_SEPARATOR for ac_dir in $PATH; do IFS="$lt_save_ifs" test -z "$ac_dir" && ac_dir=. if test -f "$ac_dir/$ac_prog" || test -f "$ac_dir/$ac_prog$ac_exeext"; then lt_cv_path_LD="$ac_dir/$ac_prog" # Check to see if the program is GNU ld. I'd rather use --version, # but apparently some variants of GNU ld only accept -v. # Break only if it was the GNU/non-GNU ld that we prefer. case `"$lt_cv_path_LD" -v 2>&1 &1 /dev/null 2>&1; then lt_cv_deplibs_check_method='file_magic ^x86 archive import|^x86 DLL' lt_cv_file_magic_cmd='func_win32_libid' else # Keep this pattern in sync with the one in func_win32_libid. lt_cv_deplibs_check_method='file_magic file format (pei*-i386(.*architecture: i386)?|pe-arm-wince|pe-x86-64)' lt_cv_file_magic_cmd='$OBJDUMP -f' fi ;; cegcc*) # use the weaker test based on 'objdump'. See mingw*. lt_cv_deplibs_check_method='file_magic file format pe-arm-.*little(.*architecture: arm)?' lt_cv_file_magic_cmd='$OBJDUMP -f' ;; darwin* | rhapsody*) lt_cv_deplibs_check_method=pass_all ;; freebsd* | dragonfly*) if echo __ELF__ | $CC -E - | $GREP __ELF__ > /dev/null; then case $host_cpu in i*86 ) # Not sure whether the presence of OpenBSD here was a mistake. # Let's accept both of them until this is cleared up. lt_cv_deplibs_check_method='file_magic (FreeBSD|OpenBSD|DragonFly)/i[[3-9]]86 (compact )?demand paged shared library' lt_cv_file_magic_cmd=/usr/bin/file lt_cv_file_magic_test_file=`echo /usr/lib/libc.so.*` ;; esac else lt_cv_deplibs_check_method=pass_all fi ;; haiku*) lt_cv_deplibs_check_method=pass_all ;; hpux10.20* | hpux11*) lt_cv_file_magic_cmd=/usr/bin/file case $host_cpu in ia64*) lt_cv_deplibs_check_method='file_magic (s[[0-9]][[0-9]][[0-9]]|ELF-[[0-9]][[0-9]]) shared object file - IA64' lt_cv_file_magic_test_file=/usr/lib/hpux32/libc.so ;; hppa*64*) [lt_cv_deplibs_check_method='file_magic (s[0-9][0-9][0-9]|ELF[ -][0-9][0-9])(-bit)?( [LM]SB)? shared object( file)?[, -]* PA-RISC [0-9]\.[0-9]'] lt_cv_file_magic_test_file=/usr/lib/pa20_64/libc.sl ;; *) lt_cv_deplibs_check_method='file_magic (s[[0-9]][[0-9]][[0-9]]|PA-RISC[[0-9]]\.[[0-9]]) shared library' lt_cv_file_magic_test_file=/usr/lib/libc.sl ;; esac ;; interix[[3-9]]*) # PIC code is broken on Interix 3.x, that's why |\.a not |_pic\.a here lt_cv_deplibs_check_method='match_pattern /lib[[^/]]+(\.so|\.a)$' ;; irix5* | irix6* | nonstopux*) case $LD in *-32|*"-32 ") libmagic=32-bit;; *-n32|*"-n32 ") libmagic=N32;; *-64|*"-64 ") libmagic=64-bit;; *) libmagic=never-match;; esac lt_cv_deplibs_check_method=pass_all ;; # This must be glibc/ELF. linux* | k*bsd*-gnu | kopensolaris*-gnu | gnu*) lt_cv_deplibs_check_method=pass_all ;; netbsd* | netbsdelf*-gnu) if echo __ELF__ | $CC -E - | $GREP __ELF__ > /dev/null; then lt_cv_deplibs_check_method='match_pattern /lib[[^/]]+(\.so\.[[0-9]]+\.[[0-9]]+|_pic\.a)$' else lt_cv_deplibs_check_method='match_pattern /lib[[^/]]+(\.so|_pic\.a)$' fi ;; newos6*) lt_cv_deplibs_check_method='file_magic ELF [[0-9]][[0-9]]*-bit [[ML]]SB (executable|dynamic lib)' lt_cv_file_magic_cmd=/usr/bin/file lt_cv_file_magic_test_file=/usr/lib/libnls.so ;; *nto* | *qnx*) lt_cv_deplibs_check_method=pass_all ;; openbsd*) if test -z "`echo __ELF__ | $CC -E - | $GREP __ELF__`" || test "$host_os-$host_cpu" = "openbsd2.8-powerpc"; then lt_cv_deplibs_check_method='match_pattern /lib[[^/]]+(\.so\.[[0-9]]+\.[[0-9]]+|\.so|_pic\.a)$' else lt_cv_deplibs_check_method='match_pattern /lib[[^/]]+(\.so\.[[0-9]]+\.[[0-9]]+|_pic\.a)$' fi ;; osf3* | osf4* | osf5*) lt_cv_deplibs_check_method=pass_all ;; rdos*) lt_cv_deplibs_check_method=pass_all ;; solaris*) lt_cv_deplibs_check_method=pass_all ;; sysv5* | sco3.2v5* | sco5v6* | unixware* | OpenUNIX* | sysv4*uw2*) lt_cv_deplibs_check_method=pass_all ;; sysv4 | sysv4.3*) case $host_vendor in motorola) lt_cv_deplibs_check_method='file_magic ELF [[0-9]][[0-9]]*-bit [[ML]]SB (shared object|dynamic lib) M[[0-9]][[0-9]]* Version [[0-9]]' lt_cv_file_magic_test_file=`echo /usr/lib/libc.so*` ;; ncr) lt_cv_deplibs_check_method=pass_all ;; sequent) lt_cv_file_magic_cmd='/bin/file' lt_cv_deplibs_check_method='file_magic ELF [[0-9]][[0-9]]*-bit [[LM]]SB (shared object|dynamic lib )' ;; sni) lt_cv_file_magic_cmd='/bin/file' lt_cv_deplibs_check_method="file_magic ELF [[0-9]][[0-9]]*-bit [[LM]]SB dynamic lib" lt_cv_file_magic_test_file=/lib/libc.so ;; siemens) lt_cv_deplibs_check_method=pass_all ;; pc) lt_cv_deplibs_check_method=pass_all ;; esac ;; tpf*) lt_cv_deplibs_check_method=pass_all ;; esac ]) file_magic_glob= want_nocaseglob=no if test "$build" = "$host"; then case $host_os in mingw* | pw32*) if ( shopt | grep nocaseglob ) >/dev/null 2>&1; then want_nocaseglob=yes else file_magic_glob=`echo aAbBcCdDeEfFgGhHiIjJkKlLmMnNoOpPqQrRsStTuUvVwWxXyYzZ | $SED -e "s/\(..\)/s\/[[\1]]\/[[\1]]\/g;/g"` fi ;; esac fi file_magic_cmd=$lt_cv_file_magic_cmd deplibs_check_method=$lt_cv_deplibs_check_method test -z "$deplibs_check_method" && deplibs_check_method=unknown _LT_DECL([], [deplibs_check_method], [1], [Method to check whether dependent libraries are shared objects]) _LT_DECL([], [file_magic_cmd], [1], [Command to use when deplibs_check_method = "file_magic"]) _LT_DECL([], [file_magic_glob], [1], [How to find potential files when deplibs_check_method = "file_magic"]) _LT_DECL([], [want_nocaseglob], [1], [Find potential files using nocaseglob when deplibs_check_method = "file_magic"]) ])# _LT_CHECK_MAGIC_METHOD # LT_PATH_NM # ---------- # find the pathname to a BSD- or MS-compatible name lister AC_DEFUN([LT_PATH_NM], [AC_REQUIRE([AC_PROG_CC])dnl AC_CACHE_CHECK([for BSD- or MS-compatible name lister (nm)], lt_cv_path_NM, [if test -n "$NM"; then # Let the user override the test. lt_cv_path_NM="$NM" else lt_nm_to_check="${ac_tool_prefix}nm" if test -n "$ac_tool_prefix" && test "$build" = "$host"; then lt_nm_to_check="$lt_nm_to_check nm" fi for lt_tmp_nm in $lt_nm_to_check; do lt_save_ifs="$IFS"; IFS=$PATH_SEPARATOR for ac_dir in $PATH /usr/ccs/bin/elf /usr/ccs/bin /usr/ucb /bin; do IFS="$lt_save_ifs" test -z "$ac_dir" && ac_dir=. tmp_nm="$ac_dir/$lt_tmp_nm" if test -f "$tmp_nm" || test -f "$tmp_nm$ac_exeext" ; then # Check to see if the nm accepts a BSD-compat flag. # Adding the `sed 1q' prevents false positives on HP-UX, which says: # nm: unknown option "B" ignored # Tru64's nm complains that /dev/null is an invalid object file case `"$tmp_nm" -B /dev/null 2>&1 | sed '1q'` in */dev/null* | *'Invalid file or object type'*) lt_cv_path_NM="$tmp_nm -B" break ;; *) case `"$tmp_nm" -p /dev/null 2>&1 | sed '1q'` in */dev/null*) lt_cv_path_NM="$tmp_nm -p" break ;; *) lt_cv_path_NM=${lt_cv_path_NM="$tmp_nm"} # keep the first match, but continue # so that we can try to find one that supports BSD flags ;; esac ;; esac fi done IFS="$lt_save_ifs" done : ${lt_cv_path_NM=no} fi]) if test "$lt_cv_path_NM" != "no"; then NM="$lt_cv_path_NM" else # Didn't find any BSD compatible name lister, look for dumpbin. if test -n "$DUMPBIN"; then : # Let the user override the test. else AC_CHECK_TOOLS(DUMPBIN, [dumpbin "link -dump"], :) case `$DUMPBIN -symbols /dev/null 2>&1 | sed '1q'` in *COFF*) DUMPBIN="$DUMPBIN -symbols" ;; *) DUMPBIN=: ;; esac fi AC_SUBST([DUMPBIN]) if test "$DUMPBIN" != ":"; then NM="$DUMPBIN" fi fi test -z "$NM" && NM=nm AC_SUBST([NM]) _LT_DECL([], [NM], [1], [A BSD- or MS-compatible name lister])dnl AC_CACHE_CHECK([the name lister ($NM) interface], [lt_cv_nm_interface], [lt_cv_nm_interface="BSD nm" echo "int some_variable = 0;" > conftest.$ac_ext (eval echo "\"\$as_me:$LINENO: $ac_compile\"" >&AS_MESSAGE_LOG_FD) (eval "$ac_compile" 2>conftest.err) cat conftest.err >&AS_MESSAGE_LOG_FD (eval echo "\"\$as_me:$LINENO: $NM \\\"conftest.$ac_objext\\\"\"" >&AS_MESSAGE_LOG_FD) (eval "$NM \"conftest.$ac_objext\"" 2>conftest.err > conftest.out) cat conftest.err >&AS_MESSAGE_LOG_FD (eval echo "\"\$as_me:$LINENO: output\"" >&AS_MESSAGE_LOG_FD) cat conftest.out >&AS_MESSAGE_LOG_FD if $GREP 'External.*some_variable' conftest.out > /dev/null; then lt_cv_nm_interface="MS dumpbin" fi rm -f conftest*]) ])# LT_PATH_NM # Old names: AU_ALIAS([AM_PROG_NM], [LT_PATH_NM]) AU_ALIAS([AC_PROG_NM], [LT_PATH_NM]) dnl aclocal-1.4 backwards compatibility: dnl AC_DEFUN([AM_PROG_NM], []) dnl AC_DEFUN([AC_PROG_NM], []) # _LT_CHECK_SHAREDLIB_FROM_LINKLIB # -------------------------------- # how to determine the name of the shared library # associated with a specific link library. # -- PORTME fill in with the dynamic library characteristics m4_defun([_LT_CHECK_SHAREDLIB_FROM_LINKLIB], [m4_require([_LT_DECL_EGREP]) m4_require([_LT_DECL_OBJDUMP]) m4_require([_LT_DECL_DLLTOOL]) AC_CACHE_CHECK([how to associate runtime and link libraries], lt_cv_sharedlib_from_linklib_cmd, [lt_cv_sharedlib_from_linklib_cmd='unknown' case $host_os in cygwin* | mingw* | pw32* | cegcc*) # two different shell functions defined in ltmain.sh # decide which to use based on capabilities of $DLLTOOL case `$DLLTOOL --help 2>&1` in *--identify-strict*) lt_cv_sharedlib_from_linklib_cmd=func_cygming_dll_for_implib ;; *) lt_cv_sharedlib_from_linklib_cmd=func_cygming_dll_for_implib_fallback ;; esac ;; *) # fallback: assume linklib IS sharedlib lt_cv_sharedlib_from_linklib_cmd="$ECHO" ;; esac ]) sharedlib_from_linklib_cmd=$lt_cv_sharedlib_from_linklib_cmd test -z "$sharedlib_from_linklib_cmd" && sharedlib_from_linklib_cmd=$ECHO _LT_DECL([], [sharedlib_from_linklib_cmd], [1], [Command to associate shared and link libraries]) ])# _LT_CHECK_SHAREDLIB_FROM_LINKLIB # _LT_PATH_MANIFEST_TOOL # ---------------------- # locate the manifest tool m4_defun([_LT_PATH_MANIFEST_TOOL], [AC_CHECK_TOOL(MANIFEST_TOOL, mt, :) test -z "$MANIFEST_TOOL" && MANIFEST_TOOL=mt AC_CACHE_CHECK([if $MANIFEST_TOOL is a manifest tool], [lt_cv_path_mainfest_tool], [lt_cv_path_mainfest_tool=no echo "$as_me:$LINENO: $MANIFEST_TOOL '-?'" >&AS_MESSAGE_LOG_FD $MANIFEST_TOOL '-?' 2>conftest.err > conftest.out cat conftest.err >&AS_MESSAGE_LOG_FD if $GREP 'Manifest Tool' conftest.out > /dev/null; then lt_cv_path_mainfest_tool=yes fi rm -f conftest*]) if test "x$lt_cv_path_mainfest_tool" != xyes; then MANIFEST_TOOL=: fi _LT_DECL([], [MANIFEST_TOOL], [1], [Manifest tool])dnl ])# _LT_PATH_MANIFEST_TOOL # LT_LIB_M # -------- # check for math library AC_DEFUN([LT_LIB_M], [AC_REQUIRE([AC_CANONICAL_HOST])dnl LIBM= case $host in *-*-beos* | *-*-cegcc* | *-*-cygwin* | *-*-haiku* | *-*-pw32* | *-*-darwin*) # These system don't have libm, or don't need it ;; *-ncr-sysv4.3*) AC_CHECK_LIB(mw, _mwvalidcheckl, LIBM="-lmw") AC_CHECK_LIB(m, cos, LIBM="$LIBM -lm") ;; *) AC_CHECK_LIB(m, cos, LIBM="-lm") ;; esac AC_SUBST([LIBM]) ])# LT_LIB_M # Old name: AU_ALIAS([AC_CHECK_LIBM], [LT_LIB_M]) dnl aclocal-1.4 backwards compatibility: dnl AC_DEFUN([AC_CHECK_LIBM], []) # _LT_COMPILER_NO_RTTI([TAGNAME]) # ------------------------------- m4_defun([_LT_COMPILER_NO_RTTI], [m4_require([_LT_TAG_COMPILER])dnl _LT_TAGVAR(lt_prog_compiler_no_builtin_flag, $1)= if test "$GCC" = yes; then case $cc_basename in nvcc*) _LT_TAGVAR(lt_prog_compiler_no_builtin_flag, $1)=' -Xcompiler -fno-builtin' ;; *) _LT_TAGVAR(lt_prog_compiler_no_builtin_flag, $1)=' -fno-builtin' ;; esac _LT_COMPILER_OPTION([if $compiler supports -fno-rtti -fno-exceptions], lt_cv_prog_compiler_rtti_exceptions, [-fno-rtti -fno-exceptions], [], [_LT_TAGVAR(lt_prog_compiler_no_builtin_flag, $1)="$_LT_TAGVAR(lt_prog_compiler_no_builtin_flag, $1) -fno-rtti -fno-exceptions"]) fi _LT_TAGDECL([no_builtin_flag], [lt_prog_compiler_no_builtin_flag], [1], [Compiler flag to turn off builtin functions]) ])# _LT_COMPILER_NO_RTTI # _LT_CMD_GLOBAL_SYMBOLS # ---------------------- m4_defun([_LT_CMD_GLOBAL_SYMBOLS], [AC_REQUIRE([AC_CANONICAL_HOST])dnl AC_REQUIRE([AC_PROG_CC])dnl AC_REQUIRE([AC_PROG_AWK])dnl AC_REQUIRE([LT_PATH_NM])dnl AC_REQUIRE([LT_PATH_LD])dnl m4_require([_LT_DECL_SED])dnl m4_require([_LT_DECL_EGREP])dnl m4_require([_LT_TAG_COMPILER])dnl # Check for command to grab the raw symbol name followed by C symbol from nm. AC_MSG_CHECKING([command to parse $NM output from $compiler object]) AC_CACHE_VAL([lt_cv_sys_global_symbol_pipe], [ # These are sane defaults that work on at least a few old systems. # [They come from Ultrix. What could be older than Ultrix?!! ;)] # Character class describing NM global symbol codes. symcode='[[BCDEGRST]]' # Regexp to match symbols that can be accessed directly from C. sympat='\([[_A-Za-z]][[_A-Za-z0-9]]*\)' # Define system-specific variables. case $host_os in aix*) symcode='[[BCDT]]' ;; cygwin* | mingw* | pw32* | cegcc*) symcode='[[ABCDGISTW]]' ;; hpux*) if test "$host_cpu" = ia64; then symcode='[[ABCDEGRST]]' fi ;; irix* | nonstopux*) symcode='[[BCDEGRST]]' ;; osf*) symcode='[[BCDEGQRST]]' ;; solaris*) symcode='[[BDRT]]' ;; sco3.2v5*) symcode='[[DT]]' ;; sysv4.2uw2*) symcode='[[DT]]' ;; sysv5* | sco5v6* | unixware* | OpenUNIX*) symcode='[[ABDT]]' ;; sysv4) symcode='[[DFNSTU]]' ;; esac # If we're using GNU nm, then use its standard symbol codes. case `$NM -V 2>&1` in *GNU* | *'with BFD'*) symcode='[[ABCDGIRSTW]]' ;; esac # Transform an extracted symbol line into a proper C declaration. # Some systems (esp. on ia64) link data and code symbols differently, # so use this general approach. lt_cv_sys_global_symbol_to_cdecl="sed -n -e 's/^T .* \(.*\)$/extern int \1();/p' -e 's/^$symcode* .* \(.*\)$/extern char \1;/p'" # Transform an extracted symbol line into symbol name and symbol address lt_cv_sys_global_symbol_to_c_name_address="sed -n -e 's/^: \([[^ ]]*\)[[ ]]*$/ {\\\"\1\\\", (void *) 0},/p' -e 's/^$symcode* \([[^ ]]*\) \([[^ ]]*\)$/ {\"\2\", (void *) \&\2},/p'" lt_cv_sys_global_symbol_to_c_name_address_lib_prefix="sed -n -e 's/^: \([[^ ]]*\)[[ ]]*$/ {\\\"\1\\\", (void *) 0},/p' -e 's/^$symcode* \([[^ ]]*\) \(lib[[^ ]]*\)$/ {\"\2\", (void *) \&\2},/p' -e 's/^$symcode* \([[^ ]]*\) \([[^ ]]*\)$/ {\"lib\2\", (void *) \&\2},/p'" # Handle CRLF in mingw tool chain opt_cr= case $build_os in mingw*) opt_cr=`$ECHO 'x\{0,1\}' | tr x '\015'` # option cr in regexp ;; esac # Try without a prefix underscore, then with it. for ac_symprfx in "" "_"; do # Transform symcode, sympat, and symprfx into a raw symbol and a C symbol. symxfrm="\\1 $ac_symprfx\\2 \\2" # Write the raw and C identifiers. if test "$lt_cv_nm_interface" = "MS dumpbin"; then # Fake it for dumpbin and say T for any non-static function # and D for any global variable. # Also find C++ and __fastcall symbols from MSVC++, # which start with @ or ?. lt_cv_sys_global_symbol_pipe="$AWK ['"\ " {last_section=section; section=\$ 3};"\ " /^COFF SYMBOL TABLE/{for(i in hide) delete hide[i]};"\ " /Section length .*#relocs.*(pick any)/{hide[last_section]=1};"\ " \$ 0!~/External *\|/{next};"\ " / 0+ UNDEF /{next}; / UNDEF \([^|]\)*()/{next};"\ " {if(hide[section]) next};"\ " {f=0}; \$ 0~/\(\).*\|/{f=1}; {printf f ? \"T \" : \"D \"};"\ " {split(\$ 0, a, /\||\r/); split(a[2], s)};"\ " s[1]~/^[@?]/{print s[1], s[1]; next};"\ " s[1]~prfx {split(s[1],t,\"@\"); print t[1], substr(t[1],length(prfx))}"\ " ' prfx=^$ac_symprfx]" else lt_cv_sys_global_symbol_pipe="sed -n -e 's/^.*[[ ]]\($symcode$symcode*\)[[ ]][[ ]]*$ac_symprfx$sympat$opt_cr$/$symxfrm/p'" fi lt_cv_sys_global_symbol_pipe="$lt_cv_sys_global_symbol_pipe | sed '/ __gnu_lto/d'" # Check to see that the pipe works correctly. pipe_works=no rm -f conftest* cat > conftest.$ac_ext <<_LT_EOF #ifdef __cplusplus extern "C" { #endif char nm_test_var; void nm_test_func(void); void nm_test_func(void){} #ifdef __cplusplus } #endif int main(){nm_test_var='a';nm_test_func();return(0);} _LT_EOF if AC_TRY_EVAL(ac_compile); then # Now try to grab the symbols. nlist=conftest.nm if AC_TRY_EVAL(NM conftest.$ac_objext \| "$lt_cv_sys_global_symbol_pipe" \> $nlist) && test -s "$nlist"; then # Try sorting and uniquifying the output. if sort "$nlist" | uniq > "$nlist"T; then mv -f "$nlist"T "$nlist" else rm -f "$nlist"T fi # Make sure that we snagged all the symbols we need. if $GREP ' nm_test_var$' "$nlist" >/dev/null; then if $GREP ' nm_test_func$' "$nlist" >/dev/null; then cat <<_LT_EOF > conftest.$ac_ext /* Keep this code in sync between libtool.m4, ltmain, lt_system.h, and tests. */ #if defined(_WIN32) || defined(__CYGWIN__) || defined(_WIN32_WCE) /* DATA imports from DLLs on WIN32 con't be const, because runtime relocations are performed -- see ld's documentation on pseudo-relocs. */ # define LT@&t@_DLSYM_CONST #elif defined(__osf__) /* This system does not cope well with relocations in const data. */ # define LT@&t@_DLSYM_CONST #else # define LT@&t@_DLSYM_CONST const #endif #ifdef __cplusplus extern "C" { #endif _LT_EOF # Now generate the symbol file. eval "$lt_cv_sys_global_symbol_to_cdecl"' < "$nlist" | $GREP -v main >> conftest.$ac_ext' cat <<_LT_EOF >> conftest.$ac_ext /* The mapping between symbol names and symbols. */ LT@&t@_DLSYM_CONST struct { const char *name; void *address; } lt__PROGRAM__LTX_preloaded_symbols[[]] = { { "@PROGRAM@", (void *) 0 }, _LT_EOF $SED "s/^$symcode$symcode* \(.*\) \(.*\)$/ {\"\2\", (void *) \&\2},/" < "$nlist" | $GREP -v main >> conftest.$ac_ext cat <<\_LT_EOF >> conftest.$ac_ext {0, (void *) 0} }; /* This works around a problem in FreeBSD linker */ #ifdef FREEBSD_WORKAROUND static const void *lt_preloaded_setup() { return lt__PROGRAM__LTX_preloaded_symbols; } #endif #ifdef __cplusplus } #endif _LT_EOF # Now try linking the two files. mv conftest.$ac_objext conftstm.$ac_objext lt_globsym_save_LIBS=$LIBS lt_globsym_save_CFLAGS=$CFLAGS LIBS="conftstm.$ac_objext" CFLAGS="$CFLAGS$_LT_TAGVAR(lt_prog_compiler_no_builtin_flag, $1)" if AC_TRY_EVAL(ac_link) && test -s conftest${ac_exeext}; then pipe_works=yes fi LIBS=$lt_globsym_save_LIBS CFLAGS=$lt_globsym_save_CFLAGS else echo "cannot find nm_test_func in $nlist" >&AS_MESSAGE_LOG_FD fi else echo "cannot find nm_test_var in $nlist" >&AS_MESSAGE_LOG_FD fi else echo "cannot run $lt_cv_sys_global_symbol_pipe" >&AS_MESSAGE_LOG_FD fi else echo "$progname: failed program was:" >&AS_MESSAGE_LOG_FD cat conftest.$ac_ext >&5 fi rm -rf conftest* conftst* # Do not use the global_symbol_pipe unless it works. if test "$pipe_works" = yes; then break else lt_cv_sys_global_symbol_pipe= fi done ]) if test -z "$lt_cv_sys_global_symbol_pipe"; then lt_cv_sys_global_symbol_to_cdecl= fi if test -z "$lt_cv_sys_global_symbol_pipe$lt_cv_sys_global_symbol_to_cdecl"; then AC_MSG_RESULT(failed) else AC_MSG_RESULT(ok) fi # Response file support. if test "$lt_cv_nm_interface" = "MS dumpbin"; then nm_file_list_spec='@' elif $NM --help 2>/dev/null | grep '[[@]]FILE' >/dev/null; then nm_file_list_spec='@' fi _LT_DECL([global_symbol_pipe], [lt_cv_sys_global_symbol_pipe], [1], [Take the output of nm and produce a listing of raw symbols and C names]) _LT_DECL([global_symbol_to_cdecl], [lt_cv_sys_global_symbol_to_cdecl], [1], [Transform the output of nm in a proper C declaration]) _LT_DECL([global_symbol_to_c_name_address], [lt_cv_sys_global_symbol_to_c_name_address], [1], [Transform the output of nm in a C name address pair]) _LT_DECL([global_symbol_to_c_name_address_lib_prefix], [lt_cv_sys_global_symbol_to_c_name_address_lib_prefix], [1], [Transform the output of nm in a C name address pair when lib prefix is needed]) _LT_DECL([], [nm_file_list_spec], [1], [Specify filename containing input files for $NM]) ]) # _LT_CMD_GLOBAL_SYMBOLS # _LT_COMPILER_PIC([TAGNAME]) # --------------------------- m4_defun([_LT_COMPILER_PIC], [m4_require([_LT_TAG_COMPILER])dnl _LT_TAGVAR(lt_prog_compiler_wl, $1)= _LT_TAGVAR(lt_prog_compiler_pic, $1)= _LT_TAGVAR(lt_prog_compiler_static, $1)= m4_if([$1], [CXX], [ # C++ specific cases for pic, static, wl, etc. if test "$GXX" = yes; then _LT_TAGVAR(lt_prog_compiler_wl, $1)='-Wl,' _LT_TAGVAR(lt_prog_compiler_static, $1)='-static' case $host_os in aix*) # All AIX code is PIC. if test "$host_cpu" = ia64; then # AIX 5 now supports IA64 processor _LT_TAGVAR(lt_prog_compiler_static, $1)='-Bstatic' fi ;; amigaos*) case $host_cpu in powerpc) # see comment about AmigaOS4 .so support _LT_TAGVAR(lt_prog_compiler_pic, $1)='-fPIC' ;; m68k) # FIXME: we need at least 68020 code to build shared libraries, but # adding the `-m68020' flag to GCC prevents building anything better, # like `-m68040'. _LT_TAGVAR(lt_prog_compiler_pic, $1)='-m68020 -resident32 -malways-restore-a4' ;; esac ;; beos* | irix5* | irix6* | nonstopux* | osf3* | osf4* | osf5*) # PIC is the default for these OSes. ;; mingw* | cygwin* | os2* | pw32* | cegcc*) # This hack is so that the source file can tell whether it is being # built for inclusion in a dll (and should export symbols for example). # Although the cygwin gcc ignores -fPIC, still need this for old-style # (--disable-auto-import) libraries m4_if([$1], [GCJ], [], [_LT_TAGVAR(lt_prog_compiler_pic, $1)='-DDLL_EXPORT']) ;; darwin* | rhapsody*) # PIC is the default on this platform # Common symbols not allowed in MH_DYLIB files _LT_TAGVAR(lt_prog_compiler_pic, $1)='-fno-common' ;; *djgpp*) # DJGPP does not support shared libraries at all _LT_TAGVAR(lt_prog_compiler_pic, $1)= ;; haiku*) # PIC is the default for Haiku. # The "-static" flag exists, but is broken. _LT_TAGVAR(lt_prog_compiler_static, $1)= ;; interix[[3-9]]*) # Interix 3.x gcc -fpic/-fPIC options generate broken code. # Instead, we relocate shared libraries at runtime. ;; sysv4*MP*) if test -d /usr/nec; then _LT_TAGVAR(lt_prog_compiler_pic, $1)=-Kconform_pic fi ;; hpux*) # PIC is the default for 64-bit PA HP-UX, but not for 32-bit # PA HP-UX. On IA64 HP-UX, PIC is the default but the pic flag # sets the default TLS model and affects inlining. case $host_cpu in hppa*64*) ;; *) _LT_TAGVAR(lt_prog_compiler_pic, $1)='-fPIC' ;; esac ;; *qnx* | *nto*) # QNX uses GNU C++, but need to define -shared option too, otherwise # it will coredump. _LT_TAGVAR(lt_prog_compiler_pic, $1)='-fPIC -shared' ;; *) _LT_TAGVAR(lt_prog_compiler_pic, $1)='-fPIC' ;; esac else case $host_os in aix[[4-9]]*) # All AIX code is PIC. if test "$host_cpu" = ia64; then # AIX 5 now supports IA64 processor _LT_TAGVAR(lt_prog_compiler_static, $1)='-Bstatic' else _LT_TAGVAR(lt_prog_compiler_static, $1)='-bnso -bI:/lib/syscalls.exp' fi ;; chorus*) case $cc_basename in cxch68*) # Green Hills C++ Compiler # _LT_TAGVAR(lt_prog_compiler_static, $1)="--no_auto_instantiation -u __main -u __premain -u _abort -r $COOL_DIR/lib/libOrb.a $MVME_DIR/lib/CC/libC.a $MVME_DIR/lib/classix/libcx.s.a" ;; esac ;; mingw* | cygwin* | os2* | pw32* | cegcc*) # This hack is so that the source file can tell whether it is being # built for inclusion in a dll (and should export symbols for example). m4_if([$1], [GCJ], [], [_LT_TAGVAR(lt_prog_compiler_pic, $1)='-DDLL_EXPORT']) ;; dgux*) case $cc_basename in ec++*) _LT_TAGVAR(lt_prog_compiler_pic, $1)='-KPIC' ;; ghcx*) # Green Hills C++ Compiler _LT_TAGVAR(lt_prog_compiler_pic, $1)='-pic' ;; *) ;; esac ;; freebsd* | dragonfly*) # FreeBSD uses GNU C++ ;; hpux9* | hpux10* | hpux11*) case $cc_basename in CC*) _LT_TAGVAR(lt_prog_compiler_wl, $1)='-Wl,' _LT_TAGVAR(lt_prog_compiler_static, $1)='${wl}-a ${wl}archive' if test "$host_cpu" != ia64; then _LT_TAGVAR(lt_prog_compiler_pic, $1)='+Z' fi ;; aCC*) _LT_TAGVAR(lt_prog_compiler_wl, $1)='-Wl,' _LT_TAGVAR(lt_prog_compiler_static, $1)='${wl}-a ${wl}archive' case $host_cpu in hppa*64*|ia64*) # +Z the default ;; *) _LT_TAGVAR(lt_prog_compiler_pic, $1)='+Z' ;; esac ;; *) ;; esac ;; interix*) # This is c89, which is MS Visual C++ (no shared libs) # Anyone wants to do a port? ;; irix5* | irix6* | nonstopux*) case $cc_basename in CC*) _LT_TAGVAR(lt_prog_compiler_wl, $1)='-Wl,' _LT_TAGVAR(lt_prog_compiler_static, $1)='-non_shared' # CC pic flag -KPIC is the default. ;; *) ;; esac ;; linux* | k*bsd*-gnu | kopensolaris*-gnu | gnu*) case $cc_basename in KCC*) # KAI C++ Compiler _LT_TAGVAR(lt_prog_compiler_wl, $1)='--backend -Wl,' _LT_TAGVAR(lt_prog_compiler_pic, $1)='-fPIC' ;; ecpc* ) # old Intel C++ for x86_64 which still supported -KPIC. _LT_TAGVAR(lt_prog_compiler_wl, $1)='-Wl,' _LT_TAGVAR(lt_prog_compiler_pic, $1)='-KPIC' _LT_TAGVAR(lt_prog_compiler_static, $1)='-static' ;; icpc* ) # Intel C++, used to be incompatible with GCC. # ICC 10 doesn't accept -KPIC any more. _LT_TAGVAR(lt_prog_compiler_wl, $1)='-Wl,' _LT_TAGVAR(lt_prog_compiler_pic, $1)='-fPIC' _LT_TAGVAR(lt_prog_compiler_static, $1)='-static' ;; pgCC* | pgcpp*) # Portland Group C++ compiler _LT_TAGVAR(lt_prog_compiler_wl, $1)='-Wl,' _LT_TAGVAR(lt_prog_compiler_pic, $1)='-fpic' _LT_TAGVAR(lt_prog_compiler_static, $1)='-Bstatic' ;; cxx*) # Compaq C++ # Make sure the PIC flag is empty. It appears that all Alpha # Linux and Compaq Tru64 Unix objects are PIC. _LT_TAGVAR(lt_prog_compiler_pic, $1)= _LT_TAGVAR(lt_prog_compiler_static, $1)='-non_shared' ;; xlc* | xlC* | bgxl[[cC]]* | mpixl[[cC]]*) # IBM XL 8.0, 9.0 on PPC and BlueGene _LT_TAGVAR(lt_prog_compiler_wl, $1)='-Wl,' _LT_TAGVAR(lt_prog_compiler_pic, $1)='-qpic' _LT_TAGVAR(lt_prog_compiler_static, $1)='-qstaticlink' ;; *) case `$CC -V 2>&1 | sed 5q` in *Sun\ C*) # Sun C++ 5.9 _LT_TAGVAR(lt_prog_compiler_pic, $1)='-KPIC' _LT_TAGVAR(lt_prog_compiler_static, $1)='-Bstatic' _LT_TAGVAR(lt_prog_compiler_wl, $1)='-Qoption ld ' ;; esac ;; esac ;; lynxos*) ;; m88k*) ;; mvs*) case $cc_basename in cxx*) _LT_TAGVAR(lt_prog_compiler_pic, $1)='-W c,exportall' ;; *) ;; esac ;; netbsd* | netbsdelf*-gnu) ;; *qnx* | *nto*) # QNX uses GNU C++, but need to define -shared option too, otherwise # it will coredump. _LT_TAGVAR(lt_prog_compiler_pic, $1)='-fPIC -shared' ;; osf3* | osf4* | osf5*) case $cc_basename in KCC*) _LT_TAGVAR(lt_prog_compiler_wl, $1)='--backend -Wl,' ;; RCC*) # Rational C++ 2.4.1 _LT_TAGVAR(lt_prog_compiler_pic, $1)='-pic' ;; cxx*) # Digital/Compaq C++ _LT_TAGVAR(lt_prog_compiler_wl, $1)='-Wl,' # Make sure the PIC flag is empty. It appears that all Alpha # Linux and Compaq Tru64 Unix objects are PIC. _LT_TAGVAR(lt_prog_compiler_pic, $1)= _LT_TAGVAR(lt_prog_compiler_static, $1)='-non_shared' ;; *) ;; esac ;; psos*) ;; solaris*) case $cc_basename in CC* | sunCC*) # Sun C++ 4.2, 5.x and Centerline C++ _LT_TAGVAR(lt_prog_compiler_pic, $1)='-KPIC' _LT_TAGVAR(lt_prog_compiler_static, $1)='-Bstatic' _LT_TAGVAR(lt_prog_compiler_wl, $1)='-Qoption ld ' ;; gcx*) # Green Hills C++ Compiler _LT_TAGVAR(lt_prog_compiler_pic, $1)='-PIC' ;; *) ;; esac ;; sunos4*) case $cc_basename in CC*) # Sun C++ 4.x _LT_TAGVAR(lt_prog_compiler_pic, $1)='-pic' _LT_TAGVAR(lt_prog_compiler_static, $1)='-Bstatic' ;; lcc*) # Lucid _LT_TAGVAR(lt_prog_compiler_pic, $1)='-pic' ;; *) ;; esac ;; sysv5* | unixware* | sco3.2v5* | sco5v6* | OpenUNIX*) case $cc_basename in CC*) _LT_TAGVAR(lt_prog_compiler_wl, $1)='-Wl,' _LT_TAGVAR(lt_prog_compiler_pic, $1)='-KPIC' _LT_TAGVAR(lt_prog_compiler_static, $1)='-Bstatic' ;; esac ;; tandem*) case $cc_basename in NCC*) # NonStop-UX NCC 3.20 _LT_TAGVAR(lt_prog_compiler_pic, $1)='-KPIC' ;; *) ;; esac ;; vxworks*) ;; *) _LT_TAGVAR(lt_prog_compiler_can_build_shared, $1)=no ;; esac fi ], [ if test "$GCC" = yes; then _LT_TAGVAR(lt_prog_compiler_wl, $1)='-Wl,' _LT_TAGVAR(lt_prog_compiler_static, $1)='-static' case $host_os in aix*) # All AIX code is PIC. if test "$host_cpu" = ia64; then # AIX 5 now supports IA64 processor _LT_TAGVAR(lt_prog_compiler_static, $1)='-Bstatic' fi ;; amigaos*) case $host_cpu in powerpc) # see comment about AmigaOS4 .so support _LT_TAGVAR(lt_prog_compiler_pic, $1)='-fPIC' ;; m68k) # FIXME: we need at least 68020 code to build shared libraries, but # adding the `-m68020' flag to GCC prevents building anything better, # like `-m68040'. _LT_TAGVAR(lt_prog_compiler_pic, $1)='-m68020 -resident32 -malways-restore-a4' ;; esac ;; beos* | irix5* | irix6* | nonstopux* | osf3* | osf4* | osf5*) # PIC is the default for these OSes. ;; mingw* | cygwin* | pw32* | os2* | cegcc*) # This hack is so that the source file can tell whether it is being # built for inclusion in a dll (and should export symbols for example). # Although the cygwin gcc ignores -fPIC, still need this for old-style # (--disable-auto-import) libraries m4_if([$1], [GCJ], [], [_LT_TAGVAR(lt_prog_compiler_pic, $1)='-DDLL_EXPORT']) ;; darwin* | rhapsody*) # PIC is the default on this platform # Common symbols not allowed in MH_DYLIB files _LT_TAGVAR(lt_prog_compiler_pic, $1)='-fno-common' ;; haiku*) # PIC is the default for Haiku. # The "-static" flag exists, but is broken. _LT_TAGVAR(lt_prog_compiler_static, $1)= ;; hpux*) # PIC is the default for 64-bit PA HP-UX, but not for 32-bit # PA HP-UX. On IA64 HP-UX, PIC is the default but the pic flag # sets the default TLS model and affects inlining. case $host_cpu in hppa*64*) # +Z the default ;; *) _LT_TAGVAR(lt_prog_compiler_pic, $1)='-fPIC' ;; esac ;; interix[[3-9]]*) # Interix 3.x gcc -fpic/-fPIC options generate broken code. # Instead, we relocate shared libraries at runtime. ;; msdosdjgpp*) # Just because we use GCC doesn't mean we suddenly get shared libraries # on systems that don't support them. _LT_TAGVAR(lt_prog_compiler_can_build_shared, $1)=no enable_shared=no ;; *nto* | *qnx*) # QNX uses GNU C++, but need to define -shared option too, otherwise # it will coredump. _LT_TAGVAR(lt_prog_compiler_pic, $1)='-fPIC -shared' ;; sysv4*MP*) if test -d /usr/nec; then _LT_TAGVAR(lt_prog_compiler_pic, $1)=-Kconform_pic fi ;; *) _LT_TAGVAR(lt_prog_compiler_pic, $1)='-fPIC' ;; esac case $cc_basename in nvcc*) # Cuda Compiler Driver 2.2 _LT_TAGVAR(lt_prog_compiler_wl, $1)='-Xlinker ' if test -n "$_LT_TAGVAR(lt_prog_compiler_pic, $1)"; then _LT_TAGVAR(lt_prog_compiler_pic, $1)="-Xcompiler $_LT_TAGVAR(lt_prog_compiler_pic, $1)" fi ;; esac else # PORTME Check for flag to pass linker flags through the system compiler. case $host_os in aix*) _LT_TAGVAR(lt_prog_compiler_wl, $1)='-Wl,' if test "$host_cpu" = ia64; then # AIX 5 now supports IA64 processor _LT_TAGVAR(lt_prog_compiler_static, $1)='-Bstatic' else _LT_TAGVAR(lt_prog_compiler_static, $1)='-bnso -bI:/lib/syscalls.exp' fi ;; mingw* | cygwin* | pw32* | os2* | cegcc*) # This hack is so that the source file can tell whether it is being # built for inclusion in a dll (and should export symbols for example). m4_if([$1], [GCJ], [], [_LT_TAGVAR(lt_prog_compiler_pic, $1)='-DDLL_EXPORT']) ;; hpux9* | hpux10* | hpux11*) _LT_TAGVAR(lt_prog_compiler_wl, $1)='-Wl,' # PIC is the default for IA64 HP-UX and 64-bit HP-UX, but # not for PA HP-UX. case $host_cpu in hppa*64*|ia64*) # +Z the default ;; *) _LT_TAGVAR(lt_prog_compiler_pic, $1)='+Z' ;; esac # Is there a better lt_prog_compiler_static that works with the bundled CC? _LT_TAGVAR(lt_prog_compiler_static, $1)='${wl}-a ${wl}archive' ;; irix5* | irix6* | nonstopux*) _LT_TAGVAR(lt_prog_compiler_wl, $1)='-Wl,' # PIC (with -KPIC) is the default. _LT_TAGVAR(lt_prog_compiler_static, $1)='-non_shared' ;; linux* | k*bsd*-gnu | kopensolaris*-gnu | gnu*) case $cc_basename in # old Intel for x86_64 which still supported -KPIC. ecc*) _LT_TAGVAR(lt_prog_compiler_wl, $1)='-Wl,' _LT_TAGVAR(lt_prog_compiler_pic, $1)='-KPIC' _LT_TAGVAR(lt_prog_compiler_static, $1)='-static' ;; # icc used to be incompatible with GCC. # ICC 10 doesn't accept -KPIC any more. icc* | ifort*) _LT_TAGVAR(lt_prog_compiler_wl, $1)='-Wl,' _LT_TAGVAR(lt_prog_compiler_pic, $1)='-fPIC' _LT_TAGVAR(lt_prog_compiler_static, $1)='-static' ;; # Lahey Fortran 8.1. lf95*) _LT_TAGVAR(lt_prog_compiler_wl, $1)='-Wl,' _LT_TAGVAR(lt_prog_compiler_pic, $1)='--shared' _LT_TAGVAR(lt_prog_compiler_static, $1)='--static' ;; nagfor*) # NAG Fortran compiler _LT_TAGVAR(lt_prog_compiler_wl, $1)='-Wl,-Wl,,' _LT_TAGVAR(lt_prog_compiler_pic, $1)='-PIC' _LT_TAGVAR(lt_prog_compiler_static, $1)='-Bstatic' ;; pgcc* | pgf77* | pgf90* | pgf95* | pgfortran*) # Portland Group compilers (*not* the Pentium gcc compiler, # which looks to be a dead project) _LT_TAGVAR(lt_prog_compiler_wl, $1)='-Wl,' _LT_TAGVAR(lt_prog_compiler_pic, $1)='-fpic' _LT_TAGVAR(lt_prog_compiler_static, $1)='-Bstatic' ;; ccc*) _LT_TAGVAR(lt_prog_compiler_wl, $1)='-Wl,' # All Alpha code is PIC. _LT_TAGVAR(lt_prog_compiler_static, $1)='-non_shared' ;; xl* | bgxl* | bgf* | mpixl*) # IBM XL C 8.0/Fortran 10.1, 11.1 on PPC and BlueGene _LT_TAGVAR(lt_prog_compiler_wl, $1)='-Wl,' _LT_TAGVAR(lt_prog_compiler_pic, $1)='-qpic' _LT_TAGVAR(lt_prog_compiler_static, $1)='-qstaticlink' ;; *) case `$CC -V 2>&1 | sed 5q` in *Sun\ Ceres\ Fortran* | *Sun*Fortran*\ [[1-7]].* | *Sun*Fortran*\ 8.[[0-3]]*) # Sun Fortran 8.3 passes all unrecognized flags to the linker _LT_TAGVAR(lt_prog_compiler_pic, $1)='-KPIC' _LT_TAGVAR(lt_prog_compiler_static, $1)='-Bstatic' _LT_TAGVAR(lt_prog_compiler_wl, $1)='' ;; *Sun\ F* | *Sun*Fortran*) _LT_TAGVAR(lt_prog_compiler_pic, $1)='-KPIC' _LT_TAGVAR(lt_prog_compiler_static, $1)='-Bstatic' _LT_TAGVAR(lt_prog_compiler_wl, $1)='-Qoption ld ' ;; *Sun\ C*) # Sun C 5.9 _LT_TAGVAR(lt_prog_compiler_pic, $1)='-KPIC' _LT_TAGVAR(lt_prog_compiler_static, $1)='-Bstatic' _LT_TAGVAR(lt_prog_compiler_wl, $1)='-Wl,' ;; *Intel*\ [[CF]]*Compiler*) _LT_TAGVAR(lt_prog_compiler_wl, $1)='-Wl,' _LT_TAGVAR(lt_prog_compiler_pic, $1)='-fPIC' _LT_TAGVAR(lt_prog_compiler_static, $1)='-static' ;; *Portland\ Group*) _LT_TAGVAR(lt_prog_compiler_wl, $1)='-Wl,' _LT_TAGVAR(lt_prog_compiler_pic, $1)='-fpic' _LT_TAGVAR(lt_prog_compiler_static, $1)='-Bstatic' ;; esac ;; esac ;; newsos6) _LT_TAGVAR(lt_prog_compiler_pic, $1)='-KPIC' _LT_TAGVAR(lt_prog_compiler_static, $1)='-Bstatic' ;; *nto* | *qnx*) # QNX uses GNU C++, but need to define -shared option too, otherwise # it will coredump. _LT_TAGVAR(lt_prog_compiler_pic, $1)='-fPIC -shared' ;; osf3* | osf4* | osf5*) _LT_TAGVAR(lt_prog_compiler_wl, $1)='-Wl,' # All OSF/1 code is PIC. _LT_TAGVAR(lt_prog_compiler_static, $1)='-non_shared' ;; rdos*) _LT_TAGVAR(lt_prog_compiler_static, $1)='-non_shared' ;; solaris*) _LT_TAGVAR(lt_prog_compiler_pic, $1)='-KPIC' _LT_TAGVAR(lt_prog_compiler_static, $1)='-Bstatic' case $cc_basename in f77* | f90* | f95* | sunf77* | sunf90* | sunf95*) _LT_TAGVAR(lt_prog_compiler_wl, $1)='-Qoption ld ';; *) _LT_TAGVAR(lt_prog_compiler_wl, $1)='-Wl,';; esac ;; sunos4*) _LT_TAGVAR(lt_prog_compiler_wl, $1)='-Qoption ld ' _LT_TAGVAR(lt_prog_compiler_pic, $1)='-PIC' _LT_TAGVAR(lt_prog_compiler_static, $1)='-Bstatic' ;; sysv4 | sysv4.2uw2* | sysv4.3*) _LT_TAGVAR(lt_prog_compiler_wl, $1)='-Wl,' _LT_TAGVAR(lt_prog_compiler_pic, $1)='-KPIC' _LT_TAGVAR(lt_prog_compiler_static, $1)='-Bstatic' ;; sysv4*MP*) if test -d /usr/nec ;then _LT_TAGVAR(lt_prog_compiler_pic, $1)='-Kconform_pic' _LT_TAGVAR(lt_prog_compiler_static, $1)='-Bstatic' fi ;; sysv5* | unixware* | sco3.2v5* | sco5v6* | OpenUNIX*) _LT_TAGVAR(lt_prog_compiler_wl, $1)='-Wl,' _LT_TAGVAR(lt_prog_compiler_pic, $1)='-KPIC' _LT_TAGVAR(lt_prog_compiler_static, $1)='-Bstatic' ;; unicos*) _LT_TAGVAR(lt_prog_compiler_wl, $1)='-Wl,' _LT_TAGVAR(lt_prog_compiler_can_build_shared, $1)=no ;; uts4*) _LT_TAGVAR(lt_prog_compiler_pic, $1)='-pic' _LT_TAGVAR(lt_prog_compiler_static, $1)='-Bstatic' ;; *) _LT_TAGVAR(lt_prog_compiler_can_build_shared, $1)=no ;; esac fi ]) case $host_os in # For platforms which do not support PIC, -DPIC is meaningless: *djgpp*) _LT_TAGVAR(lt_prog_compiler_pic, $1)= ;; *) _LT_TAGVAR(lt_prog_compiler_pic, $1)="$_LT_TAGVAR(lt_prog_compiler_pic, $1)@&t@m4_if([$1],[],[ -DPIC],[m4_if([$1],[CXX],[ -DPIC],[])])" ;; esac AC_CACHE_CHECK([for $compiler option to produce PIC], [_LT_TAGVAR(lt_cv_prog_compiler_pic, $1)], [_LT_TAGVAR(lt_cv_prog_compiler_pic, $1)=$_LT_TAGVAR(lt_prog_compiler_pic, $1)]) _LT_TAGVAR(lt_prog_compiler_pic, $1)=$_LT_TAGVAR(lt_cv_prog_compiler_pic, $1) # # Check to make sure the PIC flag actually works. # if test -n "$_LT_TAGVAR(lt_prog_compiler_pic, $1)"; then _LT_COMPILER_OPTION([if $compiler PIC flag $_LT_TAGVAR(lt_prog_compiler_pic, $1) works], [_LT_TAGVAR(lt_cv_prog_compiler_pic_works, $1)], [$_LT_TAGVAR(lt_prog_compiler_pic, $1)@&t@m4_if([$1],[],[ -DPIC],[m4_if([$1],[CXX],[ -DPIC],[])])], [], [case $_LT_TAGVAR(lt_prog_compiler_pic, $1) in "" | " "*) ;; *) _LT_TAGVAR(lt_prog_compiler_pic, $1)=" $_LT_TAGVAR(lt_prog_compiler_pic, $1)" ;; esac], [_LT_TAGVAR(lt_prog_compiler_pic, $1)= _LT_TAGVAR(lt_prog_compiler_can_build_shared, $1)=no]) fi _LT_TAGDECL([pic_flag], [lt_prog_compiler_pic], [1], [Additional compiler flags for building library objects]) _LT_TAGDECL([wl], [lt_prog_compiler_wl], [1], [How to pass a linker flag through the compiler]) # # Check to make sure the static flag actually works. # wl=$_LT_TAGVAR(lt_prog_compiler_wl, $1) eval lt_tmp_static_flag=\"$_LT_TAGVAR(lt_prog_compiler_static, $1)\" _LT_LINKER_OPTION([if $compiler static flag $lt_tmp_static_flag works], _LT_TAGVAR(lt_cv_prog_compiler_static_works, $1), $lt_tmp_static_flag, [], [_LT_TAGVAR(lt_prog_compiler_static, $1)=]) _LT_TAGDECL([link_static_flag], [lt_prog_compiler_static], [1], [Compiler flag to prevent dynamic linking]) ])# _LT_COMPILER_PIC # _LT_LINKER_SHLIBS([TAGNAME]) # ---------------------------- # See if the linker supports building shared libraries. m4_defun([_LT_LINKER_SHLIBS], [AC_REQUIRE([LT_PATH_LD])dnl AC_REQUIRE([LT_PATH_NM])dnl m4_require([_LT_PATH_MANIFEST_TOOL])dnl m4_require([_LT_FILEUTILS_DEFAULTS])dnl m4_require([_LT_DECL_EGREP])dnl m4_require([_LT_DECL_SED])dnl m4_require([_LT_CMD_GLOBAL_SYMBOLS])dnl m4_require([_LT_TAG_COMPILER])dnl AC_MSG_CHECKING([whether the $compiler linker ($LD) supports shared libraries]) m4_if([$1], [CXX], [ _LT_TAGVAR(export_symbols_cmds, $1)='$NM $libobjs $convenience | $global_symbol_pipe | $SED '\''s/.* //'\'' | sort | uniq > $export_symbols' _LT_TAGVAR(exclude_expsyms, $1)=['_GLOBAL_OFFSET_TABLE_|_GLOBAL__F[ID]_.*'] case $host_os in aix[[4-9]]*) # If we're using GNU nm, then we don't want the "-C" option. # -C means demangle to AIX nm, but means don't demangle with GNU nm # Also, AIX nm treats weak defined symbols like other global defined # symbols, whereas GNU nm marks them as "W". if $NM -V 2>&1 | $GREP 'GNU' > /dev/null; then _LT_TAGVAR(export_symbols_cmds, $1)='$NM -Bpg $libobjs $convenience | awk '\''{ if (((\$ 2 == "T") || (\$ 2 == "D") || (\$ 2 == "B") || (\$ 2 == "W")) && ([substr](\$ 3,1,1) != ".")) { print \$ 3 } }'\'' | sort -u > $export_symbols' else _LT_TAGVAR(export_symbols_cmds, $1)='$NM -BCpg $libobjs $convenience | awk '\''{ if (((\$ 2 == "T") || (\$ 2 == "D") || (\$ 2 == "B")) && ([substr](\$ 3,1,1) != ".")) { print \$ 3 } }'\'' | sort -u > $export_symbols' fi ;; pw32*) _LT_TAGVAR(export_symbols_cmds, $1)="$ltdll_cmds" ;; cygwin* | mingw* | cegcc*) case $cc_basename in cl*) _LT_TAGVAR(exclude_expsyms, $1)='_NULL_IMPORT_DESCRIPTOR|_IMPORT_DESCRIPTOR_.*' ;; *) _LT_TAGVAR(export_symbols_cmds, $1)='$NM $libobjs $convenience | $global_symbol_pipe | $SED -e '\''/^[[BCDGRS]][[ ]]/s/.*[[ ]]\([[^ ]]*\)/\1 DATA/;s/^.*[[ ]]__nm__\([[^ ]]*\)[[ ]][[^ ]]*/\1 DATA/;/^I[[ ]]/d;/^[[AITW]][[ ]]/s/.* //'\'' | sort | uniq > $export_symbols' _LT_TAGVAR(exclude_expsyms, $1)=['[_]+GLOBAL_OFFSET_TABLE_|[_]+GLOBAL__[FID]_.*|[_]+head_[A-Za-z0-9_]+_dll|[A-Za-z0-9_]+_dll_iname'] ;; esac ;; linux* | k*bsd*-gnu | gnu*) _LT_TAGVAR(link_all_deplibs, $1)=no ;; *) _LT_TAGVAR(export_symbols_cmds, $1)='$NM $libobjs $convenience | $global_symbol_pipe | $SED '\''s/.* //'\'' | sort | uniq > $export_symbols' ;; esac ], [ runpath_var= _LT_TAGVAR(allow_undefined_flag, $1)= _LT_TAGVAR(always_export_symbols, $1)=no _LT_TAGVAR(archive_cmds, $1)= _LT_TAGVAR(archive_expsym_cmds, $1)= _LT_TAGVAR(compiler_needs_object, $1)=no _LT_TAGVAR(enable_shared_with_static_runtimes, $1)=no _LT_TAGVAR(export_dynamic_flag_spec, $1)= _LT_TAGVAR(export_symbols_cmds, $1)='$NM $libobjs $convenience | $global_symbol_pipe | $SED '\''s/.* //'\'' | sort | uniq > $export_symbols' _LT_TAGVAR(hardcode_automatic, $1)=no _LT_TAGVAR(hardcode_direct, $1)=no _LT_TAGVAR(hardcode_direct_absolute, $1)=no _LT_TAGVAR(hardcode_libdir_flag_spec, $1)= _LT_TAGVAR(hardcode_libdir_separator, $1)= _LT_TAGVAR(hardcode_minus_L, $1)=no _LT_TAGVAR(hardcode_shlibpath_var, $1)=unsupported _LT_TAGVAR(inherit_rpath, $1)=no _LT_TAGVAR(link_all_deplibs, $1)=unknown _LT_TAGVAR(module_cmds, $1)= _LT_TAGVAR(module_expsym_cmds, $1)= _LT_TAGVAR(old_archive_from_new_cmds, $1)= _LT_TAGVAR(old_archive_from_expsyms_cmds, $1)= _LT_TAGVAR(thread_safe_flag_spec, $1)= _LT_TAGVAR(whole_archive_flag_spec, $1)= # include_expsyms should be a list of space-separated symbols to be *always* # included in the symbol list _LT_TAGVAR(include_expsyms, $1)= # exclude_expsyms can be an extended regexp of symbols to exclude # it will be wrapped by ` (' and `)$', so one must not match beginning or # end of line. Example: `a|bc|.*d.*' will exclude the symbols `a' and `bc', # as well as any symbol that contains `d'. _LT_TAGVAR(exclude_expsyms, $1)=['_GLOBAL_OFFSET_TABLE_|_GLOBAL__F[ID]_.*'] # Although _GLOBAL_OFFSET_TABLE_ is a valid symbol C name, most a.out # platforms (ab)use it in PIC code, but their linkers get confused if # the symbol is explicitly referenced. Since portable code cannot # rely on this symbol name, it's probably fine to never include it in # preloaded symbol tables. # Exclude shared library initialization/finalization symbols. dnl Note also adjust exclude_expsyms for C++ above. extract_expsyms_cmds= case $host_os in cygwin* | mingw* | pw32* | cegcc*) # FIXME: the MSVC++ port hasn't been tested in a loooong time # When not using gcc, we currently assume that we are using # Microsoft Visual C++. if test "$GCC" != yes; then with_gnu_ld=no fi ;; interix*) # we just hope/assume this is gcc and not c89 (= MSVC++) with_gnu_ld=yes ;; openbsd*) with_gnu_ld=no ;; linux* | k*bsd*-gnu | gnu*) _LT_TAGVAR(link_all_deplibs, $1)=no ;; esac _LT_TAGVAR(ld_shlibs, $1)=yes # On some targets, GNU ld is compatible enough with the native linker # that we're better off using the native interface for both. lt_use_gnu_ld_interface=no if test "$with_gnu_ld" = yes; then case $host_os in aix*) # The AIX port of GNU ld has always aspired to compatibility # with the native linker. However, as the warning in the GNU ld # block says, versions before 2.19.5* couldn't really create working # shared libraries, regardless of the interface used. case `$LD -v 2>&1` in *\ \(GNU\ Binutils\)\ 2.19.5*) ;; *\ \(GNU\ Binutils\)\ 2.[[2-9]]*) ;; *\ \(GNU\ Binutils\)\ [[3-9]]*) ;; *) lt_use_gnu_ld_interface=yes ;; esac ;; *) lt_use_gnu_ld_interface=yes ;; esac fi if test "$lt_use_gnu_ld_interface" = yes; then # If archive_cmds runs LD, not CC, wlarc should be empty wlarc='${wl}' # Set some defaults for GNU ld with shared library support. These # are reset later if shared libraries are not supported. Putting them # here allows them to be overridden if necessary. runpath_var=LD_RUN_PATH _LT_TAGVAR(hardcode_libdir_flag_spec, $1)='${wl}-rpath ${wl}$libdir' _LT_TAGVAR(export_dynamic_flag_spec, $1)='${wl}--export-dynamic' # ancient GNU ld didn't support --whole-archive et. al. if $LD --help 2>&1 | $GREP 'no-whole-archive' > /dev/null; then _LT_TAGVAR(whole_archive_flag_spec, $1)="$wlarc"'--whole-archive$convenience '"$wlarc"'--no-whole-archive' else _LT_TAGVAR(whole_archive_flag_spec, $1)= fi supports_anon_versioning=no case `$LD -v 2>&1` in *GNU\ gold*) supports_anon_versioning=yes ;; *\ [[01]].* | *\ 2.[[0-9]].* | *\ 2.10.*) ;; # catch versions < 2.11 *\ 2.11.93.0.2\ *) supports_anon_versioning=yes ;; # RH7.3 ... *\ 2.11.92.0.12\ *) supports_anon_versioning=yes ;; # Mandrake 8.2 ... *\ 2.11.*) ;; # other 2.11 versions *) supports_anon_versioning=yes ;; esac # See if GNU ld supports shared libraries. case $host_os in aix[[3-9]]*) # On AIX/PPC, the GNU linker is very broken if test "$host_cpu" != ia64; then _LT_TAGVAR(ld_shlibs, $1)=no cat <<_LT_EOF 1>&2 *** Warning: the GNU linker, at least up to release 2.19, is reported *** to be unable to reliably create shared libraries on AIX. *** Therefore, libtool is disabling shared libraries support. If you *** really care for shared libraries, you may want to install binutils *** 2.20 or above, or modify your PATH so that a non-GNU linker is found. *** You will then need to restart the configuration process. _LT_EOF fi ;; amigaos*) case $host_cpu in powerpc) # see comment about AmigaOS4 .so support _LT_TAGVAR(archive_cmds, $1)='$CC -shared $libobjs $deplibs $compiler_flags ${wl}-soname $wl$soname -o $lib' _LT_TAGVAR(archive_expsym_cmds, $1)='' ;; m68k) _LT_TAGVAR(archive_cmds, $1)='$RM $output_objdir/a2ixlibrary.data~$ECHO "#define NAME $libname" > $output_objdir/a2ixlibrary.data~$ECHO "#define LIBRARY_ID 1" >> $output_objdir/a2ixlibrary.data~$ECHO "#define VERSION $major" >> $output_objdir/a2ixlibrary.data~$ECHO "#define REVISION $revision" >> $output_objdir/a2ixlibrary.data~$AR $AR_FLAGS $lib $libobjs~$RANLIB $lib~(cd $output_objdir && a2ixlibrary -32)' _LT_TAGVAR(hardcode_libdir_flag_spec, $1)='-L$libdir' _LT_TAGVAR(hardcode_minus_L, $1)=yes ;; esac ;; beos*) if $LD --help 2>&1 | $GREP ': supported targets:.* elf' > /dev/null; then _LT_TAGVAR(allow_undefined_flag, $1)=unsupported # Joseph Beckenbach says some releases of gcc # support --undefined. This deserves some investigation. FIXME _LT_TAGVAR(archive_cmds, $1)='$CC -nostart $libobjs $deplibs $compiler_flags ${wl}-soname $wl$soname -o $lib' else _LT_TAGVAR(ld_shlibs, $1)=no fi ;; cygwin* | mingw* | pw32* | cegcc*) # _LT_TAGVAR(hardcode_libdir_flag_spec, $1) is actually meaningless, # as there is no search path for DLLs. _LT_TAGVAR(hardcode_libdir_flag_spec, $1)='-L$libdir' _LT_TAGVAR(export_dynamic_flag_spec, $1)='${wl}--export-all-symbols' _LT_TAGVAR(allow_undefined_flag, $1)=unsupported _LT_TAGVAR(always_export_symbols, $1)=no _LT_TAGVAR(enable_shared_with_static_runtimes, $1)=yes _LT_TAGVAR(export_symbols_cmds, $1)='$NM $libobjs $convenience | $global_symbol_pipe | $SED -e '\''/^[[BCDGRS]][[ ]]/s/.*[[ ]]\([[^ ]]*\)/\1 DATA/;s/^.*[[ ]]__nm__\([[^ ]]*\)[[ ]][[^ ]]*/\1 DATA/;/^I[[ ]]/d;/^[[AITW]][[ ]]/s/.* //'\'' | sort | uniq > $export_symbols' _LT_TAGVAR(exclude_expsyms, $1)=['[_]+GLOBAL_OFFSET_TABLE_|[_]+GLOBAL__[FID]_.*|[_]+head_[A-Za-z0-9_]+_dll|[A-Za-z0-9_]+_dll_iname'] if $LD --help 2>&1 | $GREP 'auto-import' > /dev/null; then _LT_TAGVAR(archive_cmds, $1)='$CC -shared $libobjs $deplibs $compiler_flags -o $output_objdir/$soname ${wl}--enable-auto-image-base -Xlinker --out-implib -Xlinker $lib' # If the export-symbols file already is a .def file (1st line # is EXPORTS), use it as is; otherwise, prepend... _LT_TAGVAR(archive_expsym_cmds, $1)='if test "x`$SED 1q $export_symbols`" = xEXPORTS; then cp $export_symbols $output_objdir/$soname.def; else echo EXPORTS > $output_objdir/$soname.def; cat $export_symbols >> $output_objdir/$soname.def; fi~ $CC -shared $output_objdir/$soname.def $libobjs $deplibs $compiler_flags -o $output_objdir/$soname ${wl}--enable-auto-image-base -Xlinker --out-implib -Xlinker $lib' else _LT_TAGVAR(ld_shlibs, $1)=no fi ;; haiku*) _LT_TAGVAR(archive_cmds, $1)='$CC -shared $libobjs $deplibs $compiler_flags ${wl}-soname $wl$soname -o $lib' _LT_TAGVAR(link_all_deplibs, $1)=yes ;; interix[[3-9]]*) _LT_TAGVAR(hardcode_direct, $1)=no _LT_TAGVAR(hardcode_shlibpath_var, $1)=no _LT_TAGVAR(hardcode_libdir_flag_spec, $1)='${wl}-rpath,$libdir' _LT_TAGVAR(export_dynamic_flag_spec, $1)='${wl}-E' # Hack: On Interix 3.x, we cannot compile PIC because of a broken gcc. # Instead, shared libraries are loaded at an image base (0x10000000 by # default) and relocated if they conflict, which is a slow very memory # consuming and fragmenting process. To avoid this, we pick a random, # 256 KiB-aligned image base between 0x50000000 and 0x6FFC0000 at link # time. Moving up from 0x10000000 also allows more sbrk(2) space. _LT_TAGVAR(archive_cmds, $1)='$CC -shared $pic_flag $libobjs $deplibs $compiler_flags ${wl}-h,$soname ${wl}--image-base,`expr ${RANDOM-$$} % 4096 / 2 \* 262144 + 1342177280` -o $lib' _LT_TAGVAR(archive_expsym_cmds, $1)='sed "s,^,_," $export_symbols >$output_objdir/$soname.expsym~$CC -shared $pic_flag $libobjs $deplibs $compiler_flags ${wl}-h,$soname ${wl}--retain-symbols-file,$output_objdir/$soname.expsym ${wl}--image-base,`expr ${RANDOM-$$} % 4096 / 2 \* 262144 + 1342177280` -o $lib' ;; gnu* | linux* | tpf* | k*bsd*-gnu | kopensolaris*-gnu) tmp_diet=no if test "$host_os" = linux-dietlibc; then case $cc_basename in diet\ *) tmp_diet=yes;; # linux-dietlibc with static linking (!diet-dyn) esac fi if $LD --help 2>&1 | $EGREP ': supported targets:.* elf' > /dev/null \ && test "$tmp_diet" = no then tmp_addflag=' $pic_flag' tmp_sharedflag='-shared' case $cc_basename,$host_cpu in pgcc*) # Portland Group C compiler _LT_TAGVAR(whole_archive_flag_spec, $1)='${wl}--whole-archive`for conv in $convenience\"\"; do test -n \"$conv\" && new_convenience=\"$new_convenience,$conv\"; done; func_echo_all \"$new_convenience\"` ${wl}--no-whole-archive' tmp_addflag=' $pic_flag' ;; pgf77* | pgf90* | pgf95* | pgfortran*) # Portland Group f77 and f90 compilers _LT_TAGVAR(whole_archive_flag_spec, $1)='${wl}--whole-archive`for conv in $convenience\"\"; do test -n \"$conv\" && new_convenience=\"$new_convenience,$conv\"; done; func_echo_all \"$new_convenience\"` ${wl}--no-whole-archive' tmp_addflag=' $pic_flag -Mnomain' ;; ecc*,ia64* | icc*,ia64*) # Intel C compiler on ia64 tmp_addflag=' -i_dynamic' ;; efc*,ia64* | ifort*,ia64*) # Intel Fortran compiler on ia64 tmp_addflag=' -i_dynamic -nofor_main' ;; ifc* | ifort*) # Intel Fortran compiler tmp_addflag=' -nofor_main' ;; lf95*) # Lahey Fortran 8.1 _LT_TAGVAR(whole_archive_flag_spec, $1)= tmp_sharedflag='--shared' ;; xl[[cC]]* | bgxl[[cC]]* | mpixl[[cC]]*) # IBM XL C 8.0 on PPC (deal with xlf below) tmp_sharedflag='-qmkshrobj' tmp_addflag= ;; nvcc*) # Cuda Compiler Driver 2.2 _LT_TAGVAR(whole_archive_flag_spec, $1)='${wl}--whole-archive`for conv in $convenience\"\"; do test -n \"$conv\" && new_convenience=\"$new_convenience,$conv\"; done; func_echo_all \"$new_convenience\"` ${wl}--no-whole-archive' _LT_TAGVAR(compiler_needs_object, $1)=yes ;; esac case `$CC -V 2>&1 | sed 5q` in *Sun\ C*) # Sun C 5.9 _LT_TAGVAR(whole_archive_flag_spec, $1)='${wl}--whole-archive`new_convenience=; for conv in $convenience\"\"; do test -z \"$conv\" || new_convenience=\"$new_convenience,$conv\"; done; func_echo_all \"$new_convenience\"` ${wl}--no-whole-archive' _LT_TAGVAR(compiler_needs_object, $1)=yes tmp_sharedflag='-G' ;; *Sun\ F*) # Sun Fortran 8.3 tmp_sharedflag='-G' ;; esac _LT_TAGVAR(archive_cmds, $1)='$CC '"$tmp_sharedflag""$tmp_addflag"' $libobjs $deplibs $compiler_flags ${wl}-soname $wl$soname -o $lib' if test "x$supports_anon_versioning" = xyes; then _LT_TAGVAR(archive_expsym_cmds, $1)='echo "{ global:" > $output_objdir/$libname.ver~ cat $export_symbols | sed -e "s/\(.*\)/\1;/" >> $output_objdir/$libname.ver~ echo "local: *; };" >> $output_objdir/$libname.ver~ $CC '"$tmp_sharedflag""$tmp_addflag"' $libobjs $deplibs $compiler_flags ${wl}-soname $wl$soname ${wl}-version-script ${wl}$output_objdir/$libname.ver -o $lib' fi case $cc_basename in xlf* | bgf* | bgxlf* | mpixlf*) # IBM XL Fortran 10.1 on PPC cannot create shared libs itself _LT_TAGVAR(whole_archive_flag_spec, $1)='--whole-archive$convenience --no-whole-archive' _LT_TAGVAR(hardcode_libdir_flag_spec, $1)='${wl}-rpath ${wl}$libdir' _LT_TAGVAR(archive_cmds, $1)='$LD -shared $libobjs $deplibs $linker_flags -soname $soname -o $lib' if test "x$supports_anon_versioning" = xyes; then _LT_TAGVAR(archive_expsym_cmds, $1)='echo "{ global:" > $output_objdir/$libname.ver~ cat $export_symbols | sed -e "s/\(.*\)/\1;/" >> $output_objdir/$libname.ver~ echo "local: *; };" >> $output_objdir/$libname.ver~ $LD -shared $libobjs $deplibs $linker_flags -soname $soname -version-script $output_objdir/$libname.ver -o $lib' fi ;; esac else _LT_TAGVAR(ld_shlibs, $1)=no fi ;; netbsd* | netbsdelf*-gnu) if echo __ELF__ | $CC -E - | $GREP __ELF__ >/dev/null; then _LT_TAGVAR(archive_cmds, $1)='$LD -Bshareable $libobjs $deplibs $linker_flags -o $lib' wlarc= else _LT_TAGVAR(archive_cmds, $1)='$CC -shared $pic_flag $libobjs $deplibs $compiler_flags ${wl}-soname $wl$soname -o $lib' _LT_TAGVAR(archive_expsym_cmds, $1)='$CC -shared $pic_flag $libobjs $deplibs $compiler_flags ${wl}-soname $wl$soname ${wl}-retain-symbols-file $wl$export_symbols -o $lib' fi ;; solaris*) if $LD -v 2>&1 | $GREP 'BFD 2\.8' > /dev/null; then _LT_TAGVAR(ld_shlibs, $1)=no cat <<_LT_EOF 1>&2 *** Warning: The releases 2.8.* of the GNU linker cannot reliably *** create shared libraries on Solaris systems. Therefore, libtool *** is disabling shared libraries support. We urge you to upgrade GNU *** binutils to release 2.9.1 or newer. Another option is to modify *** your PATH or compiler configuration so that the native linker is *** used, and then restart. _LT_EOF elif $LD --help 2>&1 | $GREP ': supported targets:.* elf' > /dev/null; then _LT_TAGVAR(archive_cmds, $1)='$CC -shared $pic_flag $libobjs $deplibs $compiler_flags ${wl}-soname $wl$soname -o $lib' _LT_TAGVAR(archive_expsym_cmds, $1)='$CC -shared $pic_flag $libobjs $deplibs $compiler_flags ${wl}-soname $wl$soname ${wl}-retain-symbols-file $wl$export_symbols -o $lib' else _LT_TAGVAR(ld_shlibs, $1)=no fi ;; sysv5* | sco3.2v5* | sco5v6* | unixware* | OpenUNIX*) case `$LD -v 2>&1` in *\ [[01]].* | *\ 2.[[0-9]].* | *\ 2.1[[0-5]].*) _LT_TAGVAR(ld_shlibs, $1)=no cat <<_LT_EOF 1>&2 *** Warning: Releases of the GNU linker prior to 2.16.91.0.3 can not *** reliably create shared libraries on SCO systems. Therefore, libtool *** is disabling shared libraries support. We urge you to upgrade GNU *** binutils to release 2.16.91.0.3 or newer. Another option is to modify *** your PATH or compiler configuration so that the native linker is *** used, and then restart. _LT_EOF ;; *) # For security reasons, it is highly recommended that you always # use absolute paths for naming shared libraries, and exclude the # DT_RUNPATH tag from executables and libraries. But doing so # requires that you compile everything twice, which is a pain. if $LD --help 2>&1 | $GREP ': supported targets:.* elf' > /dev/null; then _LT_TAGVAR(hardcode_libdir_flag_spec, $1)='${wl}-rpath ${wl}$libdir' _LT_TAGVAR(archive_cmds, $1)='$CC -shared $libobjs $deplibs $compiler_flags ${wl}-soname $wl$soname -o $lib' _LT_TAGVAR(archive_expsym_cmds, $1)='$CC -shared $libobjs $deplibs $compiler_flags ${wl}-soname $wl$soname ${wl}-retain-symbols-file $wl$export_symbols -o $lib' else _LT_TAGVAR(ld_shlibs, $1)=no fi ;; esac ;; sunos4*) _LT_TAGVAR(archive_cmds, $1)='$LD -assert pure-text -Bshareable -o $lib $libobjs $deplibs $linker_flags' wlarc= _LT_TAGVAR(hardcode_direct, $1)=yes _LT_TAGVAR(hardcode_shlibpath_var, $1)=no ;; *) if $LD --help 2>&1 | $GREP ': supported targets:.* elf' > /dev/null; then _LT_TAGVAR(archive_cmds, $1)='$CC -shared $pic_flag $libobjs $deplibs $compiler_flags ${wl}-soname $wl$soname -o $lib' _LT_TAGVAR(archive_expsym_cmds, $1)='$CC -shared $pic_flag $libobjs $deplibs $compiler_flags ${wl}-soname $wl$soname ${wl}-retain-symbols-file $wl$export_symbols -o $lib' else _LT_TAGVAR(ld_shlibs, $1)=no fi ;; esac if test "$_LT_TAGVAR(ld_shlibs, $1)" = no; then runpath_var= _LT_TAGVAR(hardcode_libdir_flag_spec, $1)= _LT_TAGVAR(export_dynamic_flag_spec, $1)= _LT_TAGVAR(whole_archive_flag_spec, $1)= fi else # PORTME fill in a description of your system's linker (not GNU ld) case $host_os in aix3*) _LT_TAGVAR(allow_undefined_flag, $1)=unsupported _LT_TAGVAR(always_export_symbols, $1)=yes _LT_TAGVAR(archive_expsym_cmds, $1)='$LD -o $output_objdir/$soname $libobjs $deplibs $linker_flags -bE:$export_symbols -T512 -H512 -bM:SRE~$AR $AR_FLAGS $lib $output_objdir/$soname' # Note: this linker hardcodes the directories in LIBPATH if there # are no directories specified by -L. _LT_TAGVAR(hardcode_minus_L, $1)=yes if test "$GCC" = yes && test -z "$lt_prog_compiler_static"; then # Neither direct hardcoding nor static linking is supported with a # broken collect2. _LT_TAGVAR(hardcode_direct, $1)=unsupported fi ;; aix[[4-9]]*) if test "$host_cpu" = ia64; then # On IA64, the linker does run time linking by default, so we don't # have to do anything special. aix_use_runtimelinking=no exp_sym_flag='-Bexport' no_entry_flag="" else # If we're using GNU nm, then we don't want the "-C" option. # -C means demangle to AIX nm, but means don't demangle with GNU nm # Also, AIX nm treats weak defined symbols like other global # defined symbols, whereas GNU nm marks them as "W". if $NM -V 2>&1 | $GREP 'GNU' > /dev/null; then _LT_TAGVAR(export_symbols_cmds, $1)='$NM -Bpg $libobjs $convenience | awk '\''{ if (((\$ 2 == "T") || (\$ 2 == "D") || (\$ 2 == "B") || (\$ 2 == "W")) && ([substr](\$ 3,1,1) != ".")) { print \$ 3 } }'\'' | sort -u > $export_symbols' else _LT_TAGVAR(export_symbols_cmds, $1)='$NM -BCpg $libobjs $convenience | awk '\''{ if (((\$ 2 == "T") || (\$ 2 == "D") || (\$ 2 == "B")) && ([substr](\$ 3,1,1) != ".")) { print \$ 3 } }'\'' | sort -u > $export_symbols' fi aix_use_runtimelinking=no # Test if we are trying to use run time linking or normal # AIX style linking. If -brtl is somewhere in LDFLAGS, we # need to do runtime linking. case $host_os in aix4.[[23]]|aix4.[[23]].*|aix[[5-9]]*) for ld_flag in $LDFLAGS; do if (test $ld_flag = "-brtl" || test $ld_flag = "-Wl,-brtl"); then aix_use_runtimelinking=yes break fi done ;; esac exp_sym_flag='-bexport' no_entry_flag='-bnoentry' fi # When large executables or shared objects are built, AIX ld can # have problems creating the table of contents. If linking a library # or program results in "error TOC overflow" add -mminimal-toc to # CXXFLAGS/CFLAGS for g++/gcc. In the cases where that is not # enough to fix the problem, add -Wl,-bbigtoc to LDFLAGS. _LT_TAGVAR(archive_cmds, $1)='' _LT_TAGVAR(hardcode_direct, $1)=yes _LT_TAGVAR(hardcode_direct_absolute, $1)=yes _LT_TAGVAR(hardcode_libdir_separator, $1)=':' _LT_TAGVAR(link_all_deplibs, $1)=yes _LT_TAGVAR(file_list_spec, $1)='${wl}-f,' if test "$GCC" = yes; then case $host_os in aix4.[[012]]|aix4.[[012]].*) # We only want to do this on AIX 4.2 and lower, the check # below for broken collect2 doesn't work under 4.3+ collect2name=`${CC} -print-prog-name=collect2` if test -f "$collect2name" && strings "$collect2name" | $GREP resolve_lib_name >/dev/null then # We have reworked collect2 : else # We have old collect2 _LT_TAGVAR(hardcode_direct, $1)=unsupported # It fails to find uninstalled libraries when the uninstalled # path is not listed in the libpath. Setting hardcode_minus_L # to unsupported forces relinking _LT_TAGVAR(hardcode_minus_L, $1)=yes _LT_TAGVAR(hardcode_libdir_flag_spec, $1)='-L$libdir' _LT_TAGVAR(hardcode_libdir_separator, $1)= fi ;; esac shared_flag='-shared' if test "$aix_use_runtimelinking" = yes; then shared_flag="$shared_flag "'${wl}-G' fi _LT_TAGVAR(link_all_deplibs, $1)=no else # not using gcc if test "$host_cpu" = ia64; then # VisualAge C++, Version 5.5 for AIX 5L for IA-64, Beta 3 Release # chokes on -Wl,-G. The following line is correct: shared_flag='-G' else if test "$aix_use_runtimelinking" = yes; then shared_flag='${wl}-G' else shared_flag='${wl}-bM:SRE' fi fi fi _LT_TAGVAR(export_dynamic_flag_spec, $1)='${wl}-bexpall' # It seems that -bexpall does not export symbols beginning with # underscore (_), so it is better to generate a list of symbols to export. _LT_TAGVAR(always_export_symbols, $1)=yes if test "$aix_use_runtimelinking" = yes; then # Warning - without using the other runtime loading flags (-brtl), # -berok will link without error, but may produce a broken library. _LT_TAGVAR(allow_undefined_flag, $1)='-berok' # Determine the default libpath from the value encoded in an # empty executable. _LT_SYS_MODULE_PATH_AIX([$1]) _LT_TAGVAR(hardcode_libdir_flag_spec, $1)='${wl}-blibpath:$libdir:'"$aix_libpath" _LT_TAGVAR(archive_expsym_cmds, $1)='$CC -o $output_objdir/$soname $libobjs $deplibs '"\${wl}$no_entry_flag"' $compiler_flags `if test "x${allow_undefined_flag}" != "x"; then func_echo_all "${wl}${allow_undefined_flag}"; else :; fi` '"\${wl}$exp_sym_flag:\$export_symbols $shared_flag" else if test "$host_cpu" = ia64; then _LT_TAGVAR(hardcode_libdir_flag_spec, $1)='${wl}-R $libdir:/usr/lib:/lib' _LT_TAGVAR(allow_undefined_flag, $1)="-z nodefs" _LT_TAGVAR(archive_expsym_cmds, $1)="\$CC $shared_flag"' -o $output_objdir/$soname $libobjs $deplibs '"\${wl}$no_entry_flag"' $compiler_flags ${wl}${allow_undefined_flag} '"\${wl}$exp_sym_flag:\$export_symbols" else # Determine the default libpath from the value encoded in an # empty executable. _LT_SYS_MODULE_PATH_AIX([$1]) _LT_TAGVAR(hardcode_libdir_flag_spec, $1)='${wl}-blibpath:$libdir:'"$aix_libpath" # Warning - without using the other run time loading flags, # -berok will link without error, but may produce a broken library. _LT_TAGVAR(no_undefined_flag, $1)=' ${wl}-bernotok' _LT_TAGVAR(allow_undefined_flag, $1)=' ${wl}-berok' if test "$with_gnu_ld" = yes; then # We only use this code for GNU lds that support --whole-archive. _LT_TAGVAR(whole_archive_flag_spec, $1)='${wl}--whole-archive$convenience ${wl}--no-whole-archive' else # Exported symbols can be pulled into shared objects from archives _LT_TAGVAR(whole_archive_flag_spec, $1)='$convenience' fi _LT_TAGVAR(archive_cmds_need_lc, $1)=yes # This is similar to how AIX traditionally builds its shared libraries. _LT_TAGVAR(archive_expsym_cmds, $1)="\$CC $shared_flag"' -o $output_objdir/$soname $libobjs $deplibs ${wl}-bnoentry $compiler_flags ${wl}-bE:$export_symbols${allow_undefined_flag}~$AR $AR_FLAGS $output_objdir/$libname$release.a $output_objdir/$soname' fi fi ;; amigaos*) case $host_cpu in powerpc) # see comment about AmigaOS4 .so support _LT_TAGVAR(archive_cmds, $1)='$CC -shared $libobjs $deplibs $compiler_flags ${wl}-soname $wl$soname -o $lib' _LT_TAGVAR(archive_expsym_cmds, $1)='' ;; m68k) _LT_TAGVAR(archive_cmds, $1)='$RM $output_objdir/a2ixlibrary.data~$ECHO "#define NAME $libname" > $output_objdir/a2ixlibrary.data~$ECHO "#define LIBRARY_ID 1" >> $output_objdir/a2ixlibrary.data~$ECHO "#define VERSION $major" >> $output_objdir/a2ixlibrary.data~$ECHO "#define REVISION $revision" >> $output_objdir/a2ixlibrary.data~$AR $AR_FLAGS $lib $libobjs~$RANLIB $lib~(cd $output_objdir && a2ixlibrary -32)' _LT_TAGVAR(hardcode_libdir_flag_spec, $1)='-L$libdir' _LT_TAGVAR(hardcode_minus_L, $1)=yes ;; esac ;; bsdi[[45]]*) _LT_TAGVAR(export_dynamic_flag_spec, $1)=-rdynamic ;; cygwin* | mingw* | pw32* | cegcc*) # When not using gcc, we currently assume that we are using # Microsoft Visual C++. # hardcode_libdir_flag_spec is actually meaningless, as there is # no search path for DLLs. case $cc_basename in cl*) # Native MSVC _LT_TAGVAR(hardcode_libdir_flag_spec, $1)=' ' _LT_TAGVAR(allow_undefined_flag, $1)=unsupported _LT_TAGVAR(always_export_symbols, $1)=yes _LT_TAGVAR(file_list_spec, $1)='@' # Tell ltmain to make .lib files, not .a files. libext=lib # Tell ltmain to make .dll files, not .so files. shrext_cmds=".dll" # FIXME: Setting linknames here is a bad hack. _LT_TAGVAR(archive_cmds, $1)='$CC -o $output_objdir/$soname $libobjs $compiler_flags $deplibs -Wl,-dll~linknames=' _LT_TAGVAR(archive_expsym_cmds, $1)='if test "x`$SED 1q $export_symbols`" = xEXPORTS; then sed -n -e 's/\\\\\\\(.*\\\\\\\)/-link\\\ -EXPORT:\\\\\\\1/' -e '1\\\!p' < $export_symbols > $output_objdir/$soname.exp; else sed -e 's/\\\\\\\(.*\\\\\\\)/-link\\\ -EXPORT:\\\\\\\1/' < $export_symbols > $output_objdir/$soname.exp; fi~ $CC -o $tool_output_objdir$soname $libobjs $compiler_flags $deplibs "@$tool_output_objdir$soname.exp" -Wl,-DLL,-IMPLIB:"$tool_output_objdir$libname.dll.lib"~ linknames=' # The linker will not automatically build a static lib if we build a DLL. # _LT_TAGVAR(old_archive_from_new_cmds, $1)='true' _LT_TAGVAR(enable_shared_with_static_runtimes, $1)=yes _LT_TAGVAR(exclude_expsyms, $1)='_NULL_IMPORT_DESCRIPTOR|_IMPORT_DESCRIPTOR_.*' _LT_TAGVAR(export_symbols_cmds, $1)='$NM $libobjs $convenience | $global_symbol_pipe | $SED -e '\''/^[[BCDGRS]][[ ]]/s/.*[[ ]]\([[^ ]]*\)/\1,DATA/'\'' | $SED -e '\''/^[[AITW]][[ ]]/s/.*[[ ]]//'\'' | sort | uniq > $export_symbols' # Don't use ranlib _LT_TAGVAR(old_postinstall_cmds, $1)='chmod 644 $oldlib' _LT_TAGVAR(postlink_cmds, $1)='lt_outputfile="@OUTPUT@"~ lt_tool_outputfile="@TOOL_OUTPUT@"~ case $lt_outputfile in *.exe|*.EXE) ;; *) lt_outputfile="$lt_outputfile.exe" lt_tool_outputfile="$lt_tool_outputfile.exe" ;; esac~ if test "$MANIFEST_TOOL" != ":" && test -f "$lt_outputfile.manifest"; then $MANIFEST_TOOL -manifest "$lt_tool_outputfile.manifest" -outputresource:"$lt_tool_outputfile" || exit 1; $RM "$lt_outputfile.manifest"; fi' ;; *) # Assume MSVC wrapper _LT_TAGVAR(hardcode_libdir_flag_spec, $1)=' ' _LT_TAGVAR(allow_undefined_flag, $1)=unsupported # Tell ltmain to make .lib files, not .a files. libext=lib # Tell ltmain to make .dll files, not .so files. shrext_cmds=".dll" # FIXME: Setting linknames here is a bad hack. _LT_TAGVAR(archive_cmds, $1)='$CC -o $lib $libobjs $compiler_flags `func_echo_all "$deplibs" | $SED '\''s/ -lc$//'\''` -link -dll~linknames=' # The linker will automatically build a .lib file if we build a DLL. _LT_TAGVAR(old_archive_from_new_cmds, $1)='true' # FIXME: Should let the user specify the lib program. _LT_TAGVAR(old_archive_cmds, $1)='lib -OUT:$oldlib$oldobjs$old_deplibs' _LT_TAGVAR(enable_shared_with_static_runtimes, $1)=yes ;; esac ;; darwin* | rhapsody*) _LT_DARWIN_LINKER_FEATURES($1) ;; dgux*) _LT_TAGVAR(archive_cmds, $1)='$LD -G -h $soname -o $lib $libobjs $deplibs $linker_flags' _LT_TAGVAR(hardcode_libdir_flag_spec, $1)='-L$libdir' _LT_TAGVAR(hardcode_shlibpath_var, $1)=no ;; # FreeBSD 2.2.[012] allows us to include c++rt0.o to get C++ constructor # support. Future versions do this automatically, but an explicit c++rt0.o # does not break anything, and helps significantly (at the cost of a little # extra space). freebsd2.2*) _LT_TAGVAR(archive_cmds, $1)='$LD -Bshareable -o $lib $libobjs $deplibs $linker_flags /usr/lib/c++rt0.o' _LT_TAGVAR(hardcode_libdir_flag_spec, $1)='-R$libdir' _LT_TAGVAR(hardcode_direct, $1)=yes _LT_TAGVAR(hardcode_shlibpath_var, $1)=no ;; # Unfortunately, older versions of FreeBSD 2 do not have this feature. freebsd2.*) _LT_TAGVAR(archive_cmds, $1)='$LD -Bshareable -o $lib $libobjs $deplibs $linker_flags' _LT_TAGVAR(hardcode_direct, $1)=yes _LT_TAGVAR(hardcode_minus_L, $1)=yes _LT_TAGVAR(hardcode_shlibpath_var, $1)=no ;; # FreeBSD 3 and greater uses gcc -shared to do shared libraries. freebsd* | dragonfly*) _LT_TAGVAR(archive_cmds, $1)='$CC -shared $pic_flag -o $lib $libobjs $deplibs $compiler_flags' _LT_TAGVAR(hardcode_libdir_flag_spec, $1)='-R$libdir' _LT_TAGVAR(hardcode_direct, $1)=yes _LT_TAGVAR(hardcode_shlibpath_var, $1)=no ;; hpux9*) if test "$GCC" = yes; then _LT_TAGVAR(archive_cmds, $1)='$RM $output_objdir/$soname~$CC -shared $pic_flag ${wl}+b ${wl}$install_libdir -o $output_objdir/$soname $libobjs $deplibs $compiler_flags~test $output_objdir/$soname = $lib || mv $output_objdir/$soname $lib' else _LT_TAGVAR(archive_cmds, $1)='$RM $output_objdir/$soname~$LD -b +b $install_libdir -o $output_objdir/$soname $libobjs $deplibs $linker_flags~test $output_objdir/$soname = $lib || mv $output_objdir/$soname $lib' fi _LT_TAGVAR(hardcode_libdir_flag_spec, $1)='${wl}+b ${wl}$libdir' _LT_TAGVAR(hardcode_libdir_separator, $1)=: _LT_TAGVAR(hardcode_direct, $1)=yes # hardcode_minus_L: Not really in the search PATH, # but as the default location of the library. _LT_TAGVAR(hardcode_minus_L, $1)=yes _LT_TAGVAR(export_dynamic_flag_spec, $1)='${wl}-E' ;; hpux10*) if test "$GCC" = yes && test "$with_gnu_ld" = no; then _LT_TAGVAR(archive_cmds, $1)='$CC -shared $pic_flag ${wl}+h ${wl}$soname ${wl}+b ${wl}$install_libdir -o $lib $libobjs $deplibs $compiler_flags' else _LT_TAGVAR(archive_cmds, $1)='$LD -b +h $soname +b $install_libdir -o $lib $libobjs $deplibs $linker_flags' fi if test "$with_gnu_ld" = no; then _LT_TAGVAR(hardcode_libdir_flag_spec, $1)='${wl}+b ${wl}$libdir' _LT_TAGVAR(hardcode_libdir_separator, $1)=: _LT_TAGVAR(hardcode_direct, $1)=yes _LT_TAGVAR(hardcode_direct_absolute, $1)=yes _LT_TAGVAR(export_dynamic_flag_spec, $1)='${wl}-E' # hardcode_minus_L: Not really in the search PATH, # but as the default location of the library. _LT_TAGVAR(hardcode_minus_L, $1)=yes fi ;; hpux11*) if test "$GCC" = yes && test "$with_gnu_ld" = no; then case $host_cpu in hppa*64*) _LT_TAGVAR(archive_cmds, $1)='$CC -shared ${wl}+h ${wl}$soname -o $lib $libobjs $deplibs $compiler_flags' ;; ia64*) _LT_TAGVAR(archive_cmds, $1)='$CC -shared $pic_flag ${wl}+h ${wl}$soname ${wl}+nodefaultrpath -o $lib $libobjs $deplibs $compiler_flags' ;; *) _LT_TAGVAR(archive_cmds, $1)='$CC -shared $pic_flag ${wl}+h ${wl}$soname ${wl}+b ${wl}$install_libdir -o $lib $libobjs $deplibs $compiler_flags' ;; esac else case $host_cpu in hppa*64*) _LT_TAGVAR(archive_cmds, $1)='$CC -b ${wl}+h ${wl}$soname -o $lib $libobjs $deplibs $compiler_flags' ;; ia64*) _LT_TAGVAR(archive_cmds, $1)='$CC -b ${wl}+h ${wl}$soname ${wl}+nodefaultrpath -o $lib $libobjs $deplibs $compiler_flags' ;; *) m4_if($1, [], [ # Older versions of the 11.00 compiler do not understand -b yet # (HP92453-01 A.11.01.20 doesn't, HP92453-01 B.11.X.35175-35176.GP does) _LT_LINKER_OPTION([if $CC understands -b], _LT_TAGVAR(lt_cv_prog_compiler__b, $1), [-b], [_LT_TAGVAR(archive_cmds, $1)='$CC -b ${wl}+h ${wl}$soname ${wl}+b ${wl}$install_libdir -o $lib $libobjs $deplibs $compiler_flags'], [_LT_TAGVAR(archive_cmds, $1)='$LD -b +h $soname +b $install_libdir -o $lib $libobjs $deplibs $linker_flags'])], [_LT_TAGVAR(archive_cmds, $1)='$CC -b ${wl}+h ${wl}$soname ${wl}+b ${wl}$install_libdir -o $lib $libobjs $deplibs $compiler_flags']) ;; esac fi if test "$with_gnu_ld" = no; then _LT_TAGVAR(hardcode_libdir_flag_spec, $1)='${wl}+b ${wl}$libdir' _LT_TAGVAR(hardcode_libdir_separator, $1)=: case $host_cpu in hppa*64*|ia64*) _LT_TAGVAR(hardcode_direct, $1)=no _LT_TAGVAR(hardcode_shlibpath_var, $1)=no ;; *) _LT_TAGVAR(hardcode_direct, $1)=yes _LT_TAGVAR(hardcode_direct_absolute, $1)=yes _LT_TAGVAR(export_dynamic_flag_spec, $1)='${wl}-E' # hardcode_minus_L: Not really in the search PATH, # but as the default location of the library. _LT_TAGVAR(hardcode_minus_L, $1)=yes ;; esac fi ;; irix5* | irix6* | nonstopux*) if test "$GCC" = yes; then _LT_TAGVAR(archive_cmds, $1)='$CC -shared $pic_flag $libobjs $deplibs $compiler_flags ${wl}-soname ${wl}$soname `test -n "$verstring" && func_echo_all "${wl}-set_version ${wl}$verstring"` ${wl}-update_registry ${wl}${output_objdir}/so_locations -o $lib' # Try to use the -exported_symbol ld option, if it does not # work, assume that -exports_file does not work either and # implicitly export all symbols. # This should be the same for all languages, so no per-tag cache variable. AC_CACHE_CHECK([whether the $host_os linker accepts -exported_symbol], [lt_cv_irix_exported_symbol], [save_LDFLAGS="$LDFLAGS" LDFLAGS="$LDFLAGS -shared ${wl}-exported_symbol ${wl}foo ${wl}-update_registry ${wl}/dev/null" AC_LINK_IFELSE( [AC_LANG_SOURCE( [AC_LANG_CASE([C], [[int foo (void) { return 0; }]], [C++], [[int foo (void) { return 0; }]], [Fortran 77], [[ subroutine foo end]], [Fortran], [[ subroutine foo end]])])], [lt_cv_irix_exported_symbol=yes], [lt_cv_irix_exported_symbol=no]) LDFLAGS="$save_LDFLAGS"]) if test "$lt_cv_irix_exported_symbol" = yes; then _LT_TAGVAR(archive_expsym_cmds, $1)='$CC -shared $pic_flag $libobjs $deplibs $compiler_flags ${wl}-soname ${wl}$soname `test -n "$verstring" && func_echo_all "${wl}-set_version ${wl}$verstring"` ${wl}-update_registry ${wl}${output_objdir}/so_locations ${wl}-exports_file ${wl}$export_symbols -o $lib' fi else _LT_TAGVAR(archive_cmds, $1)='$CC -shared $libobjs $deplibs $compiler_flags -soname $soname `test -n "$verstring" && func_echo_all "-set_version $verstring"` -update_registry ${output_objdir}/so_locations -o $lib' _LT_TAGVAR(archive_expsym_cmds, $1)='$CC -shared $libobjs $deplibs $compiler_flags -soname $soname `test -n "$verstring" && func_echo_all "-set_version $verstring"` -update_registry ${output_objdir}/so_locations -exports_file $export_symbols -o $lib' fi _LT_TAGVAR(archive_cmds_need_lc, $1)='no' _LT_TAGVAR(hardcode_libdir_flag_spec, $1)='${wl}-rpath ${wl}$libdir' _LT_TAGVAR(hardcode_libdir_separator, $1)=: _LT_TAGVAR(inherit_rpath, $1)=yes _LT_TAGVAR(link_all_deplibs, $1)=yes ;; netbsd* | netbsdelf*-gnu) if echo __ELF__ | $CC -E - | $GREP __ELF__ >/dev/null; then _LT_TAGVAR(archive_cmds, $1)='$LD -Bshareable -o $lib $libobjs $deplibs $linker_flags' # a.out else _LT_TAGVAR(archive_cmds, $1)='$LD -shared -o $lib $libobjs $deplibs $linker_flags' # ELF fi _LT_TAGVAR(hardcode_libdir_flag_spec, $1)='-R$libdir' _LT_TAGVAR(hardcode_direct, $1)=yes _LT_TAGVAR(hardcode_shlibpath_var, $1)=no ;; newsos6) _LT_TAGVAR(archive_cmds, $1)='$LD -G -h $soname -o $lib $libobjs $deplibs $linker_flags' _LT_TAGVAR(hardcode_direct, $1)=yes _LT_TAGVAR(hardcode_libdir_flag_spec, $1)='${wl}-rpath ${wl}$libdir' _LT_TAGVAR(hardcode_libdir_separator, $1)=: _LT_TAGVAR(hardcode_shlibpath_var, $1)=no ;; *nto* | *qnx*) ;; openbsd*) if test -f /usr/libexec/ld.so; then _LT_TAGVAR(hardcode_direct, $1)=yes _LT_TAGVAR(hardcode_shlibpath_var, $1)=no _LT_TAGVAR(hardcode_direct_absolute, $1)=yes if test -z "`echo __ELF__ | $CC -E - | $GREP __ELF__`" || test "$host_os-$host_cpu" = "openbsd2.8-powerpc"; then _LT_TAGVAR(archive_cmds, $1)='$CC -shared $pic_flag -o $lib $libobjs $deplibs $compiler_flags' _LT_TAGVAR(archive_expsym_cmds, $1)='$CC -shared $pic_flag -o $lib $libobjs $deplibs $compiler_flags ${wl}-retain-symbols-file,$export_symbols' _LT_TAGVAR(hardcode_libdir_flag_spec, $1)='${wl}-rpath,$libdir' _LT_TAGVAR(export_dynamic_flag_spec, $1)='${wl}-E' else case $host_os in openbsd[[01]].* | openbsd2.[[0-7]] | openbsd2.[[0-7]].*) _LT_TAGVAR(archive_cmds, $1)='$LD -Bshareable -o $lib $libobjs $deplibs $linker_flags' _LT_TAGVAR(hardcode_libdir_flag_spec, $1)='-R$libdir' ;; *) _LT_TAGVAR(archive_cmds, $1)='$CC -shared $pic_flag -o $lib $libobjs $deplibs $compiler_flags' _LT_TAGVAR(hardcode_libdir_flag_spec, $1)='${wl}-rpath,$libdir' ;; esac fi else _LT_TAGVAR(ld_shlibs, $1)=no fi ;; os2*) _LT_TAGVAR(hardcode_libdir_flag_spec, $1)='-L$libdir' _LT_TAGVAR(hardcode_minus_L, $1)=yes _LT_TAGVAR(allow_undefined_flag, $1)=unsupported _LT_TAGVAR(archive_cmds, $1)='$ECHO "LIBRARY $libname INITINSTANCE" > $output_objdir/$libname.def~$ECHO "DESCRIPTION \"$libname\"" >> $output_objdir/$libname.def~echo DATA >> $output_objdir/$libname.def~echo " SINGLE NONSHARED" >> $output_objdir/$libname.def~echo EXPORTS >> $output_objdir/$libname.def~emxexp $libobjs >> $output_objdir/$libname.def~$CC -Zdll -Zcrtdll -o $lib $libobjs $deplibs $compiler_flags $output_objdir/$libname.def' _LT_TAGVAR(old_archive_from_new_cmds, $1)='emximp -o $output_objdir/$libname.a $output_objdir/$libname.def' ;; osf3*) if test "$GCC" = yes; then _LT_TAGVAR(allow_undefined_flag, $1)=' ${wl}-expect_unresolved ${wl}\*' _LT_TAGVAR(archive_cmds, $1)='$CC -shared${allow_undefined_flag} $libobjs $deplibs $compiler_flags ${wl}-soname ${wl}$soname `test -n "$verstring" && func_echo_all "${wl}-set_version ${wl}$verstring"` ${wl}-update_registry ${wl}${output_objdir}/so_locations -o $lib' else _LT_TAGVAR(allow_undefined_flag, $1)=' -expect_unresolved \*' _LT_TAGVAR(archive_cmds, $1)='$CC -shared${allow_undefined_flag} $libobjs $deplibs $compiler_flags -soname $soname `test -n "$verstring" && func_echo_all "-set_version $verstring"` -update_registry ${output_objdir}/so_locations -o $lib' fi _LT_TAGVAR(archive_cmds_need_lc, $1)='no' _LT_TAGVAR(hardcode_libdir_flag_spec, $1)='${wl}-rpath ${wl}$libdir' _LT_TAGVAR(hardcode_libdir_separator, $1)=: ;; osf4* | osf5*) # as osf3* with the addition of -msym flag if test "$GCC" = yes; then _LT_TAGVAR(allow_undefined_flag, $1)=' ${wl}-expect_unresolved ${wl}\*' _LT_TAGVAR(archive_cmds, $1)='$CC -shared${allow_undefined_flag} $pic_flag $libobjs $deplibs $compiler_flags ${wl}-msym ${wl}-soname ${wl}$soname `test -n "$verstring" && func_echo_all "${wl}-set_version ${wl}$verstring"` ${wl}-update_registry ${wl}${output_objdir}/so_locations -o $lib' _LT_TAGVAR(hardcode_libdir_flag_spec, $1)='${wl}-rpath ${wl}$libdir' else _LT_TAGVAR(allow_undefined_flag, $1)=' -expect_unresolved \*' _LT_TAGVAR(archive_cmds, $1)='$CC -shared${allow_undefined_flag} $libobjs $deplibs $compiler_flags -msym -soname $soname `test -n "$verstring" && func_echo_all "-set_version $verstring"` -update_registry ${output_objdir}/so_locations -o $lib' _LT_TAGVAR(archive_expsym_cmds, $1)='for i in `cat $export_symbols`; do printf "%s %s\\n" -exported_symbol "\$i" >> $lib.exp; done; printf "%s\\n" "-hidden">> $lib.exp~ $CC -shared${allow_undefined_flag} ${wl}-input ${wl}$lib.exp $compiler_flags $libobjs $deplibs -soname $soname `test -n "$verstring" && $ECHO "-set_version $verstring"` -update_registry ${output_objdir}/so_locations -o $lib~$RM $lib.exp' # Both c and cxx compiler support -rpath directly _LT_TAGVAR(hardcode_libdir_flag_spec, $1)='-rpath $libdir' fi _LT_TAGVAR(archive_cmds_need_lc, $1)='no' _LT_TAGVAR(hardcode_libdir_separator, $1)=: ;; solaris*) _LT_TAGVAR(no_undefined_flag, $1)=' -z defs' if test "$GCC" = yes; then wlarc='${wl}' _LT_TAGVAR(archive_cmds, $1)='$CC -shared $pic_flag ${wl}-z ${wl}text ${wl}-h ${wl}$soname -o $lib $libobjs $deplibs $compiler_flags' _LT_TAGVAR(archive_expsym_cmds, $1)='echo "{ global:" > $lib.exp~cat $export_symbols | $SED -e "s/\(.*\)/\1;/" >> $lib.exp~echo "local: *; };" >> $lib.exp~ $CC -shared $pic_flag ${wl}-z ${wl}text ${wl}-M ${wl}$lib.exp ${wl}-h ${wl}$soname -o $lib $libobjs $deplibs $compiler_flags~$RM $lib.exp' else case `$CC -V 2>&1` in *"Compilers 5.0"*) wlarc='' _LT_TAGVAR(archive_cmds, $1)='$LD -G${allow_undefined_flag} -h $soname -o $lib $libobjs $deplibs $linker_flags' _LT_TAGVAR(archive_expsym_cmds, $1)='echo "{ global:" > $lib.exp~cat $export_symbols | $SED -e "s/\(.*\)/\1;/" >> $lib.exp~echo "local: *; };" >> $lib.exp~ $LD -G${allow_undefined_flag} -M $lib.exp -h $soname -o $lib $libobjs $deplibs $linker_flags~$RM $lib.exp' ;; *) wlarc='${wl}' _LT_TAGVAR(archive_cmds, $1)='$CC -G${allow_undefined_flag} -h $soname -o $lib $libobjs $deplibs $compiler_flags' _LT_TAGVAR(archive_expsym_cmds, $1)='echo "{ global:" > $lib.exp~cat $export_symbols | $SED -e "s/\(.*\)/\1;/" >> $lib.exp~echo "local: *; };" >> $lib.exp~ $CC -G${allow_undefined_flag} -M $lib.exp -h $soname -o $lib $libobjs $deplibs $compiler_flags~$RM $lib.exp' ;; esac fi _LT_TAGVAR(hardcode_libdir_flag_spec, $1)='-R$libdir' _LT_TAGVAR(hardcode_shlibpath_var, $1)=no case $host_os in solaris2.[[0-5]] | solaris2.[[0-5]].*) ;; *) # The compiler driver will combine and reorder linker options, # but understands `-z linker_flag'. GCC discards it without `$wl', # but is careful enough not to reorder. # Supported since Solaris 2.6 (maybe 2.5.1?) if test "$GCC" = yes; then _LT_TAGVAR(whole_archive_flag_spec, $1)='${wl}-z ${wl}allextract$convenience ${wl}-z ${wl}defaultextract' else _LT_TAGVAR(whole_archive_flag_spec, $1)='-z allextract$convenience -z defaultextract' fi ;; esac _LT_TAGVAR(link_all_deplibs, $1)=yes ;; sunos4*) if test "x$host_vendor" = xsequent; then # Use $CC to link under sequent, because it throws in some extra .o # files that make .init and .fini sections work. _LT_TAGVAR(archive_cmds, $1)='$CC -G ${wl}-h $soname -o $lib $libobjs $deplibs $compiler_flags' else _LT_TAGVAR(archive_cmds, $1)='$LD -assert pure-text -Bstatic -o $lib $libobjs $deplibs $linker_flags' fi _LT_TAGVAR(hardcode_libdir_flag_spec, $1)='-L$libdir' _LT_TAGVAR(hardcode_direct, $1)=yes _LT_TAGVAR(hardcode_minus_L, $1)=yes _LT_TAGVAR(hardcode_shlibpath_var, $1)=no ;; sysv4) case $host_vendor in sni) _LT_TAGVAR(archive_cmds, $1)='$LD -G -h $soname -o $lib $libobjs $deplibs $linker_flags' _LT_TAGVAR(hardcode_direct, $1)=yes # is this really true??? ;; siemens) ## LD is ld it makes a PLAMLIB ## CC just makes a GrossModule. _LT_TAGVAR(archive_cmds, $1)='$LD -G -o $lib $libobjs $deplibs $linker_flags' _LT_TAGVAR(reload_cmds, $1)='$CC -r -o $output$reload_objs' _LT_TAGVAR(hardcode_direct, $1)=no ;; motorola) _LT_TAGVAR(archive_cmds, $1)='$LD -G -h $soname -o $lib $libobjs $deplibs $linker_flags' _LT_TAGVAR(hardcode_direct, $1)=no #Motorola manual says yes, but my tests say they lie ;; esac runpath_var='LD_RUN_PATH' _LT_TAGVAR(hardcode_shlibpath_var, $1)=no ;; sysv4.3*) _LT_TAGVAR(archive_cmds, $1)='$LD -G -h $soname -o $lib $libobjs $deplibs $linker_flags' _LT_TAGVAR(hardcode_shlibpath_var, $1)=no _LT_TAGVAR(export_dynamic_flag_spec, $1)='-Bexport' ;; sysv4*MP*) if test -d /usr/nec; then _LT_TAGVAR(archive_cmds, $1)='$LD -G -h $soname -o $lib $libobjs $deplibs $linker_flags' _LT_TAGVAR(hardcode_shlibpath_var, $1)=no runpath_var=LD_RUN_PATH hardcode_runpath_var=yes _LT_TAGVAR(ld_shlibs, $1)=yes fi ;; sysv4*uw2* | sysv5OpenUNIX* | sysv5UnixWare7.[[01]].[[10]]* | unixware7* | sco3.2v5.0.[[024]]*) _LT_TAGVAR(no_undefined_flag, $1)='${wl}-z,text' _LT_TAGVAR(archive_cmds_need_lc, $1)=no _LT_TAGVAR(hardcode_shlibpath_var, $1)=no runpath_var='LD_RUN_PATH' if test "$GCC" = yes; then _LT_TAGVAR(archive_cmds, $1)='$CC -shared ${wl}-h,$soname -o $lib $libobjs $deplibs $compiler_flags' _LT_TAGVAR(archive_expsym_cmds, $1)='$CC -shared ${wl}-Bexport:$export_symbols ${wl}-h,$soname -o $lib $libobjs $deplibs $compiler_flags' else _LT_TAGVAR(archive_cmds, $1)='$CC -G ${wl}-h,$soname -o $lib $libobjs $deplibs $compiler_flags' _LT_TAGVAR(archive_expsym_cmds, $1)='$CC -G ${wl}-Bexport:$export_symbols ${wl}-h,$soname -o $lib $libobjs $deplibs $compiler_flags' fi ;; sysv5* | sco3.2v5* | sco5v6*) # Note: We can NOT use -z defs as we might desire, because we do not # link with -lc, and that would cause any symbols used from libc to # always be unresolved, which means just about no library would # ever link correctly. If we're not using GNU ld we use -z text # though, which does catch some bad symbols but isn't as heavy-handed # as -z defs. _LT_TAGVAR(no_undefined_flag, $1)='${wl}-z,text' _LT_TAGVAR(allow_undefined_flag, $1)='${wl}-z,nodefs' _LT_TAGVAR(archive_cmds_need_lc, $1)=no _LT_TAGVAR(hardcode_shlibpath_var, $1)=no _LT_TAGVAR(hardcode_libdir_flag_spec, $1)='${wl}-R,$libdir' _LT_TAGVAR(hardcode_libdir_separator, $1)=':' _LT_TAGVAR(link_all_deplibs, $1)=yes _LT_TAGVAR(export_dynamic_flag_spec, $1)='${wl}-Bexport' runpath_var='LD_RUN_PATH' if test "$GCC" = yes; then _LT_TAGVAR(archive_cmds, $1)='$CC -shared ${wl}-h,$soname -o $lib $libobjs $deplibs $compiler_flags' _LT_TAGVAR(archive_expsym_cmds, $1)='$CC -shared ${wl}-Bexport:$export_symbols ${wl}-h,$soname -o $lib $libobjs $deplibs $compiler_flags' else _LT_TAGVAR(archive_cmds, $1)='$CC -G ${wl}-h,$soname -o $lib $libobjs $deplibs $compiler_flags' _LT_TAGVAR(archive_expsym_cmds, $1)='$CC -G ${wl}-Bexport:$export_symbols ${wl}-h,$soname -o $lib $libobjs $deplibs $compiler_flags' fi ;; uts4*) _LT_TAGVAR(archive_cmds, $1)='$LD -G -h $soname -o $lib $libobjs $deplibs $linker_flags' _LT_TAGVAR(hardcode_libdir_flag_spec, $1)='-L$libdir' _LT_TAGVAR(hardcode_shlibpath_var, $1)=no ;; *) _LT_TAGVAR(ld_shlibs, $1)=no ;; esac if test x$host_vendor = xsni; then case $host in sysv4 | sysv4.2uw2* | sysv4.3* | sysv5*) _LT_TAGVAR(export_dynamic_flag_spec, $1)='${wl}-Blargedynsym' ;; esac fi fi ]) AC_MSG_RESULT([$_LT_TAGVAR(ld_shlibs, $1)]) test "$_LT_TAGVAR(ld_shlibs, $1)" = no && can_build_shared=no _LT_TAGVAR(with_gnu_ld, $1)=$with_gnu_ld _LT_DECL([], [libext], [0], [Old archive suffix (normally "a")])dnl _LT_DECL([], [shrext_cmds], [1], [Shared library suffix (normally ".so")])dnl _LT_DECL([], [extract_expsyms_cmds], [2], [The commands to extract the exported symbol list from a shared archive]) # # Do we need to explicitly link libc? # case "x$_LT_TAGVAR(archive_cmds_need_lc, $1)" in x|xyes) # Assume -lc should be added _LT_TAGVAR(archive_cmds_need_lc, $1)=yes if test "$enable_shared" = yes && test "$GCC" = yes; then case $_LT_TAGVAR(archive_cmds, $1) in *'~'*) # FIXME: we may have to deal with multi-command sequences. ;; '$CC '*) # Test whether the compiler implicitly links with -lc since on some # systems, -lgcc has to come before -lc. If gcc already passes -lc # to ld, don't add -lc before -lgcc. AC_CACHE_CHECK([whether -lc should be explicitly linked in], [lt_cv_]_LT_TAGVAR(archive_cmds_need_lc, $1), [$RM conftest* echo "$lt_simple_compile_test_code" > conftest.$ac_ext if AC_TRY_EVAL(ac_compile) 2>conftest.err; then soname=conftest lib=conftest libobjs=conftest.$ac_objext deplibs= wl=$_LT_TAGVAR(lt_prog_compiler_wl, $1) pic_flag=$_LT_TAGVAR(lt_prog_compiler_pic, $1) compiler_flags=-v linker_flags=-v verstring= output_objdir=. libname=conftest lt_save_allow_undefined_flag=$_LT_TAGVAR(allow_undefined_flag, $1) _LT_TAGVAR(allow_undefined_flag, $1)= if AC_TRY_EVAL(_LT_TAGVAR(archive_cmds, $1) 2\>\&1 \| $GREP \" -lc \" \>/dev/null 2\>\&1) then lt_cv_[]_LT_TAGVAR(archive_cmds_need_lc, $1)=no else lt_cv_[]_LT_TAGVAR(archive_cmds_need_lc, $1)=yes fi _LT_TAGVAR(allow_undefined_flag, $1)=$lt_save_allow_undefined_flag else cat conftest.err 1>&5 fi $RM conftest* ]) _LT_TAGVAR(archive_cmds_need_lc, $1)=$lt_cv_[]_LT_TAGVAR(archive_cmds_need_lc, $1) ;; esac fi ;; esac _LT_TAGDECL([build_libtool_need_lc], [archive_cmds_need_lc], [0], [Whether or not to add -lc for building shared libraries]) _LT_TAGDECL([allow_libtool_libs_with_static_runtimes], [enable_shared_with_static_runtimes], [0], [Whether or not to disallow shared libs when runtime libs are static]) _LT_TAGDECL([], [export_dynamic_flag_spec], [1], [Compiler flag to allow reflexive dlopens]) _LT_TAGDECL([], [whole_archive_flag_spec], [1], [Compiler flag to generate shared objects directly from archives]) _LT_TAGDECL([], [compiler_needs_object], [1], [Whether the compiler copes with passing no objects directly]) _LT_TAGDECL([], [old_archive_from_new_cmds], [2], [Create an old-style archive from a shared archive]) _LT_TAGDECL([], [old_archive_from_expsyms_cmds], [2], [Create a temporary old-style archive to link instead of a shared archive]) _LT_TAGDECL([], [archive_cmds], [2], [Commands used to build a shared archive]) _LT_TAGDECL([], [archive_expsym_cmds], [2]) _LT_TAGDECL([], [module_cmds], [2], [Commands used to build a loadable module if different from building a shared archive.]) _LT_TAGDECL([], [module_expsym_cmds], [2]) _LT_TAGDECL([], [with_gnu_ld], [1], [Whether we are building with GNU ld or not]) _LT_TAGDECL([], [allow_undefined_flag], [1], [Flag that allows shared libraries with undefined symbols to be built]) _LT_TAGDECL([], [no_undefined_flag], [1], [Flag that enforces no undefined symbols]) _LT_TAGDECL([], [hardcode_libdir_flag_spec], [1], [Flag to hardcode $libdir into a binary during linking. This must work even if $libdir does not exist]) _LT_TAGDECL([], [hardcode_libdir_separator], [1], [Whether we need a single "-rpath" flag with a separated argument]) _LT_TAGDECL([], [hardcode_direct], [0], [Set to "yes" if using DIR/libNAME${shared_ext} during linking hardcodes DIR into the resulting binary]) _LT_TAGDECL([], [hardcode_direct_absolute], [0], [Set to "yes" if using DIR/libNAME${shared_ext} during linking hardcodes DIR into the resulting binary and the resulting library dependency is "absolute", i.e impossible to change by setting ${shlibpath_var} if the library is relocated]) _LT_TAGDECL([], [hardcode_minus_L], [0], [Set to "yes" if using the -LDIR flag during linking hardcodes DIR into the resulting binary]) _LT_TAGDECL([], [hardcode_shlibpath_var], [0], [Set to "yes" if using SHLIBPATH_VAR=DIR during linking hardcodes DIR into the resulting binary]) _LT_TAGDECL([], [hardcode_automatic], [0], [Set to "yes" if building a shared library automatically hardcodes DIR into the library and all subsequent libraries and executables linked against it]) _LT_TAGDECL([], [inherit_rpath], [0], [Set to yes if linker adds runtime paths of dependent libraries to runtime path list]) _LT_TAGDECL([], [link_all_deplibs], [0], [Whether libtool must link a program against all its dependency libraries]) _LT_TAGDECL([], [always_export_symbols], [0], [Set to "yes" if exported symbols are required]) _LT_TAGDECL([], [export_symbols_cmds], [2], [The commands to list exported symbols]) _LT_TAGDECL([], [exclude_expsyms], [1], [Symbols that should not be listed in the preloaded symbols]) _LT_TAGDECL([], [include_expsyms], [1], [Symbols that must always be exported]) _LT_TAGDECL([], [prelink_cmds], [2], [Commands necessary for linking programs (against libraries) with templates]) _LT_TAGDECL([], [postlink_cmds], [2], [Commands necessary for finishing linking programs]) _LT_TAGDECL([], [file_list_spec], [1], [Specify filename containing input files]) dnl FIXME: Not yet implemented dnl _LT_TAGDECL([], [thread_safe_flag_spec], [1], dnl [Compiler flag to generate thread safe objects]) ])# _LT_LINKER_SHLIBS # _LT_LANG_C_CONFIG([TAG]) # ------------------------ # Ensure that the configuration variables for a C compiler are suitably # defined. These variables are subsequently used by _LT_CONFIG to write # the compiler configuration to `libtool'. m4_defun([_LT_LANG_C_CONFIG], [m4_require([_LT_DECL_EGREP])dnl lt_save_CC="$CC" AC_LANG_PUSH(C) # Source file extension for C test sources. ac_ext=c # Object file extension for compiled C test sources. objext=o _LT_TAGVAR(objext, $1)=$objext # Code to be used in simple compile tests lt_simple_compile_test_code="int some_variable = 0;" # Code to be used in simple link tests lt_simple_link_test_code='int main(){return(0);}' _LT_TAG_COMPILER # Save the default compiler, since it gets overwritten when the other # tags are being tested, and _LT_TAGVAR(compiler, []) is a NOP. compiler_DEFAULT=$CC # save warnings/boilerplate of simple test code _LT_COMPILER_BOILERPLATE _LT_LINKER_BOILERPLATE ## CAVEAT EMPTOR: ## There is no encapsulation within the following macros, do not change ## the running order or otherwise move them around unless you know exactly ## what you are doing... if test -n "$compiler"; then _LT_COMPILER_NO_RTTI($1) _LT_COMPILER_PIC($1) _LT_COMPILER_C_O($1) _LT_COMPILER_FILE_LOCKS($1) _LT_LINKER_SHLIBS($1) _LT_SYS_DYNAMIC_LINKER($1) _LT_LINKER_HARDCODE_LIBPATH($1) LT_SYS_DLOPEN_SELF _LT_CMD_STRIPLIB # Report which library types will actually be built AC_MSG_CHECKING([if libtool supports shared libraries]) AC_MSG_RESULT([$can_build_shared]) AC_MSG_CHECKING([whether to build shared libraries]) test "$can_build_shared" = "no" && enable_shared=no # On AIX, shared libraries and static libraries use the same namespace, and # are all built from PIC. case $host_os in aix3*) test "$enable_shared" = yes && enable_static=no if test -n "$RANLIB"; then archive_cmds="$archive_cmds~\$RANLIB \$lib" postinstall_cmds='$RANLIB $lib' fi ;; aix[[4-9]]*) if test "$host_cpu" != ia64 && test "$aix_use_runtimelinking" = no ; then test "$enable_shared" = yes && enable_static=no fi ;; esac AC_MSG_RESULT([$enable_shared]) AC_MSG_CHECKING([whether to build static libraries]) # Make sure either enable_shared or enable_static is yes. test "$enable_shared" = yes || enable_static=yes AC_MSG_RESULT([$enable_static]) _LT_CONFIG($1) fi AC_LANG_POP CC="$lt_save_CC" ])# _LT_LANG_C_CONFIG # _LT_LANG_CXX_CONFIG([TAG]) # -------------------------- # Ensure that the configuration variables for a C++ compiler are suitably # defined. These variables are subsequently used by _LT_CONFIG to write # the compiler configuration to `libtool'. m4_defun([_LT_LANG_CXX_CONFIG], [m4_require([_LT_FILEUTILS_DEFAULTS])dnl m4_require([_LT_DECL_EGREP])dnl m4_require([_LT_PATH_MANIFEST_TOOL])dnl if test -n "$CXX" && ( test "X$CXX" != "Xno" && ( (test "X$CXX" = "Xg++" && `g++ -v >/dev/null 2>&1` ) || (test "X$CXX" != "Xg++"))) ; then AC_PROG_CXXCPP else _lt_caught_CXX_error=yes fi AC_LANG_PUSH(C++) _LT_TAGVAR(archive_cmds_need_lc, $1)=no _LT_TAGVAR(allow_undefined_flag, $1)= _LT_TAGVAR(always_export_symbols, $1)=no _LT_TAGVAR(archive_expsym_cmds, $1)= _LT_TAGVAR(compiler_needs_object, $1)=no _LT_TAGVAR(export_dynamic_flag_spec, $1)= _LT_TAGVAR(hardcode_direct, $1)=no _LT_TAGVAR(hardcode_direct_absolute, $1)=no _LT_TAGVAR(hardcode_libdir_flag_spec, $1)= _LT_TAGVAR(hardcode_libdir_separator, $1)= _LT_TAGVAR(hardcode_minus_L, $1)=no _LT_TAGVAR(hardcode_shlibpath_var, $1)=unsupported _LT_TAGVAR(hardcode_automatic, $1)=no _LT_TAGVAR(inherit_rpath, $1)=no _LT_TAGVAR(module_cmds, $1)= _LT_TAGVAR(module_expsym_cmds, $1)= _LT_TAGVAR(link_all_deplibs, $1)=unknown _LT_TAGVAR(old_archive_cmds, $1)=$old_archive_cmds _LT_TAGVAR(reload_flag, $1)=$reload_flag _LT_TAGVAR(reload_cmds, $1)=$reload_cmds _LT_TAGVAR(no_undefined_flag, $1)= _LT_TAGVAR(whole_archive_flag_spec, $1)= _LT_TAGVAR(enable_shared_with_static_runtimes, $1)=no # Source file extension for C++ test sources. ac_ext=cpp # Object file extension for compiled C++ test sources. objext=o _LT_TAGVAR(objext, $1)=$objext # No sense in running all these tests if we already determined that # the CXX compiler isn't working. Some variables (like enable_shared) # are currently assumed to apply to all compilers on this platform, # and will be corrupted by setting them based on a non-working compiler. if test "$_lt_caught_CXX_error" != yes; then # Code to be used in simple compile tests lt_simple_compile_test_code="int some_variable = 0;" # Code to be used in simple link tests lt_simple_link_test_code='int main(int, char *[[]]) { return(0); }' # ltmain only uses $CC for tagged configurations so make sure $CC is set. _LT_TAG_COMPILER # save warnings/boilerplate of simple test code _LT_COMPILER_BOILERPLATE _LT_LINKER_BOILERPLATE # Allow CC to be a program name with arguments. lt_save_CC=$CC lt_save_CFLAGS=$CFLAGS lt_save_LD=$LD lt_save_GCC=$GCC GCC=$GXX lt_save_with_gnu_ld=$with_gnu_ld lt_save_path_LD=$lt_cv_path_LD if test -n "${lt_cv_prog_gnu_ldcxx+set}"; then lt_cv_prog_gnu_ld=$lt_cv_prog_gnu_ldcxx else $as_unset lt_cv_prog_gnu_ld fi if test -n "${lt_cv_path_LDCXX+set}"; then lt_cv_path_LD=$lt_cv_path_LDCXX else $as_unset lt_cv_path_LD fi test -z "${LDCXX+set}" || LD=$LDCXX CC=${CXX-"c++"} CFLAGS=$CXXFLAGS compiler=$CC _LT_TAGVAR(compiler, $1)=$CC _LT_CC_BASENAME([$compiler]) if test -n "$compiler"; then # We don't want -fno-exception when compiling C++ code, so set the # no_builtin_flag separately if test "$GXX" = yes; then _LT_TAGVAR(lt_prog_compiler_no_builtin_flag, $1)=' -fno-builtin' else _LT_TAGVAR(lt_prog_compiler_no_builtin_flag, $1)= fi if test "$GXX" = yes; then # Set up default GNU C++ configuration LT_PATH_LD # Check if GNU C++ uses GNU ld as the underlying linker, since the # archiving commands below assume that GNU ld is being used. if test "$with_gnu_ld" = yes; then _LT_TAGVAR(archive_cmds, $1)='$CC $pic_flag -shared -nostdlib $predep_objects $libobjs $deplibs $postdep_objects $compiler_flags ${wl}-soname $wl$soname -o $lib' _LT_TAGVAR(archive_expsym_cmds, $1)='$CC $pic_flag -shared -nostdlib $predep_objects $libobjs $deplibs $postdep_objects $compiler_flags ${wl}-soname $wl$soname ${wl}-retain-symbols-file $wl$export_symbols -o $lib' _LT_TAGVAR(hardcode_libdir_flag_spec, $1)='${wl}-rpath ${wl}$libdir' _LT_TAGVAR(export_dynamic_flag_spec, $1)='${wl}--export-dynamic' # If archive_cmds runs LD, not CC, wlarc should be empty # XXX I think wlarc can be eliminated in ltcf-cxx, but I need to # investigate it a little bit more. (MM) wlarc='${wl}' # ancient GNU ld didn't support --whole-archive et. al. if eval "`$CC -print-prog-name=ld` --help 2>&1" | $GREP 'no-whole-archive' > /dev/null; then _LT_TAGVAR(whole_archive_flag_spec, $1)="$wlarc"'--whole-archive$convenience '"$wlarc"'--no-whole-archive' else _LT_TAGVAR(whole_archive_flag_spec, $1)= fi else with_gnu_ld=no wlarc= # A generic and very simple default shared library creation # command for GNU C++ for the case where it uses the native # linker, instead of GNU ld. If possible, this setting should # overridden to take advantage of the native linker features on # the platform it is being used on. _LT_TAGVAR(archive_cmds, $1)='$CC -shared -nostdlib $predep_objects $libobjs $deplibs $postdep_objects $compiler_flags -o $lib' fi # Commands to make compiler produce verbose output that lists # what "hidden" libraries, object files and flags are used when # linking a shared library. output_verbose_link_cmd='$CC -shared $CFLAGS -v conftest.$objext 2>&1 | $GREP -v "^Configured with:" | $GREP "\-L"' else GXX=no with_gnu_ld=no wlarc= fi # PORTME: fill in a description of your system's C++ link characteristics AC_MSG_CHECKING([whether the $compiler linker ($LD) supports shared libraries]) _LT_TAGVAR(ld_shlibs, $1)=yes case $host_os in aix3*) # FIXME: insert proper C++ library support _LT_TAGVAR(ld_shlibs, $1)=no ;; aix[[4-9]]*) if test "$host_cpu" = ia64; then # On IA64, the linker does run time linking by default, so we don't # have to do anything special. aix_use_runtimelinking=no exp_sym_flag='-Bexport' no_entry_flag="" else aix_use_runtimelinking=no # Test if we are trying to use run time linking or normal # AIX style linking. If -brtl is somewhere in LDFLAGS, we # need to do runtime linking. case $host_os in aix4.[[23]]|aix4.[[23]].*|aix[[5-9]]*) for ld_flag in $LDFLAGS; do case $ld_flag in *-brtl*) aix_use_runtimelinking=yes break ;; esac done ;; esac exp_sym_flag='-bexport' no_entry_flag='-bnoentry' fi # When large executables or shared objects are built, AIX ld can # have problems creating the table of contents. If linking a library # or program results in "error TOC overflow" add -mminimal-toc to # CXXFLAGS/CFLAGS for g++/gcc. In the cases where that is not # enough to fix the problem, add -Wl,-bbigtoc to LDFLAGS. _LT_TAGVAR(archive_cmds, $1)='' _LT_TAGVAR(hardcode_direct, $1)=yes _LT_TAGVAR(hardcode_direct_absolute, $1)=yes _LT_TAGVAR(hardcode_libdir_separator, $1)=':' _LT_TAGVAR(link_all_deplibs, $1)=yes _LT_TAGVAR(file_list_spec, $1)='${wl}-f,' if test "$GXX" = yes; then case $host_os in aix4.[[012]]|aix4.[[012]].*) # We only want to do this on AIX 4.2 and lower, the check # below for broken collect2 doesn't work under 4.3+ collect2name=`${CC} -print-prog-name=collect2` if test -f "$collect2name" && strings "$collect2name" | $GREP resolve_lib_name >/dev/null then # We have reworked collect2 : else # We have old collect2 _LT_TAGVAR(hardcode_direct, $1)=unsupported # It fails to find uninstalled libraries when the uninstalled # path is not listed in the libpath. Setting hardcode_minus_L # to unsupported forces relinking _LT_TAGVAR(hardcode_minus_L, $1)=yes _LT_TAGVAR(hardcode_libdir_flag_spec, $1)='-L$libdir' _LT_TAGVAR(hardcode_libdir_separator, $1)= fi esac shared_flag='-shared' if test "$aix_use_runtimelinking" = yes; then shared_flag="$shared_flag "'${wl}-G' fi else # not using gcc if test "$host_cpu" = ia64; then # VisualAge C++, Version 5.5 for AIX 5L for IA-64, Beta 3 Release # chokes on -Wl,-G. The following line is correct: shared_flag='-G' else if test "$aix_use_runtimelinking" = yes; then shared_flag='${wl}-G' else shared_flag='${wl}-bM:SRE' fi fi fi _LT_TAGVAR(export_dynamic_flag_spec, $1)='${wl}-bexpall' # It seems that -bexpall does not export symbols beginning with # underscore (_), so it is better to generate a list of symbols to # export. _LT_TAGVAR(always_export_symbols, $1)=yes if test "$aix_use_runtimelinking" = yes; then # Warning - without using the other runtime loading flags (-brtl), # -berok will link without error, but may produce a broken library. _LT_TAGVAR(allow_undefined_flag, $1)='-berok' # Determine the default libpath from the value encoded in an empty # executable. _LT_SYS_MODULE_PATH_AIX([$1]) _LT_TAGVAR(hardcode_libdir_flag_spec, $1)='${wl}-blibpath:$libdir:'"$aix_libpath" _LT_TAGVAR(archive_expsym_cmds, $1)='$CC -o $output_objdir/$soname $libobjs $deplibs '"\${wl}$no_entry_flag"' $compiler_flags `if test "x${allow_undefined_flag}" != "x"; then func_echo_all "${wl}${allow_undefined_flag}"; else :; fi` '"\${wl}$exp_sym_flag:\$export_symbols $shared_flag" else if test "$host_cpu" = ia64; then _LT_TAGVAR(hardcode_libdir_flag_spec, $1)='${wl}-R $libdir:/usr/lib:/lib' _LT_TAGVAR(allow_undefined_flag, $1)="-z nodefs" _LT_TAGVAR(archive_expsym_cmds, $1)="\$CC $shared_flag"' -o $output_objdir/$soname $libobjs $deplibs '"\${wl}$no_entry_flag"' $compiler_flags ${wl}${allow_undefined_flag} '"\${wl}$exp_sym_flag:\$export_symbols" else # Determine the default libpath from the value encoded in an # empty executable. _LT_SYS_MODULE_PATH_AIX([$1]) _LT_TAGVAR(hardcode_libdir_flag_spec, $1)='${wl}-blibpath:$libdir:'"$aix_libpath" # Warning - without using the other run time loading flags, # -berok will link without error, but may produce a broken library. _LT_TAGVAR(no_undefined_flag, $1)=' ${wl}-bernotok' _LT_TAGVAR(allow_undefined_flag, $1)=' ${wl}-berok' if test "$with_gnu_ld" = yes; then # We only use this code for GNU lds that support --whole-archive. _LT_TAGVAR(whole_archive_flag_spec, $1)='${wl}--whole-archive$convenience ${wl}--no-whole-archive' else # Exported symbols can be pulled into shared objects from archives _LT_TAGVAR(whole_archive_flag_spec, $1)='$convenience' fi _LT_TAGVAR(archive_cmds_need_lc, $1)=yes # This is similar to how AIX traditionally builds its shared # libraries. _LT_TAGVAR(archive_expsym_cmds, $1)="\$CC $shared_flag"' -o $output_objdir/$soname $libobjs $deplibs ${wl}-bnoentry $compiler_flags ${wl}-bE:$export_symbols${allow_undefined_flag}~$AR $AR_FLAGS $output_objdir/$libname$release.a $output_objdir/$soname' fi fi ;; beos*) if $LD --help 2>&1 | $GREP ': supported targets:.* elf' > /dev/null; then _LT_TAGVAR(allow_undefined_flag, $1)=unsupported # Joseph Beckenbach says some releases of gcc # support --undefined. This deserves some investigation. FIXME _LT_TAGVAR(archive_cmds, $1)='$CC -nostart $libobjs $deplibs $compiler_flags ${wl}-soname $wl$soname -o $lib' else _LT_TAGVAR(ld_shlibs, $1)=no fi ;; chorus*) case $cc_basename in *) # FIXME: insert proper C++ library support _LT_TAGVAR(ld_shlibs, $1)=no ;; esac ;; cygwin* | mingw* | pw32* | cegcc*) case $GXX,$cc_basename in ,cl* | no,cl*) # Native MSVC # hardcode_libdir_flag_spec is actually meaningless, as there is # no search path for DLLs. _LT_TAGVAR(hardcode_libdir_flag_spec, $1)=' ' _LT_TAGVAR(allow_undefined_flag, $1)=unsupported _LT_TAGVAR(always_export_symbols, $1)=yes _LT_TAGVAR(file_list_spec, $1)='@' # Tell ltmain to make .lib files, not .a files. libext=lib # Tell ltmain to make .dll files, not .so files. shrext_cmds=".dll" # FIXME: Setting linknames here is a bad hack. _LT_TAGVAR(archive_cmds, $1)='$CC -o $output_objdir/$soname $libobjs $compiler_flags $deplibs -Wl,-dll~linknames=' _LT_TAGVAR(archive_expsym_cmds, $1)='if test "x`$SED 1q $export_symbols`" = xEXPORTS; then $SED -n -e 's/\\\\\\\(.*\\\\\\\)/-link\\\ -EXPORT:\\\\\\\1/' -e '1\\\!p' < $export_symbols > $output_objdir/$soname.exp; else $SED -e 's/\\\\\\\(.*\\\\\\\)/-link\\\ -EXPORT:\\\\\\\1/' < $export_symbols > $output_objdir/$soname.exp; fi~ $CC -o $tool_output_objdir$soname $libobjs $compiler_flags $deplibs "@$tool_output_objdir$soname.exp" -Wl,-DLL,-IMPLIB:"$tool_output_objdir$libname.dll.lib"~ linknames=' # The linker will not automatically build a static lib if we build a DLL. # _LT_TAGVAR(old_archive_from_new_cmds, $1)='true' _LT_TAGVAR(enable_shared_with_static_runtimes, $1)=yes # Don't use ranlib _LT_TAGVAR(old_postinstall_cmds, $1)='chmod 644 $oldlib' _LT_TAGVAR(postlink_cmds, $1)='lt_outputfile="@OUTPUT@"~ lt_tool_outputfile="@TOOL_OUTPUT@"~ case $lt_outputfile in *.exe|*.EXE) ;; *) lt_outputfile="$lt_outputfile.exe" lt_tool_outputfile="$lt_tool_outputfile.exe" ;; esac~ func_to_tool_file "$lt_outputfile"~ if test "$MANIFEST_TOOL" != ":" && test -f "$lt_outputfile.manifest"; then $MANIFEST_TOOL -manifest "$lt_tool_outputfile.manifest" -outputresource:"$lt_tool_outputfile" || exit 1; $RM "$lt_outputfile.manifest"; fi' ;; *) # g++ # _LT_TAGVAR(hardcode_libdir_flag_spec, $1) is actually meaningless, # as there is no search path for DLLs. _LT_TAGVAR(hardcode_libdir_flag_spec, $1)='-L$libdir' _LT_TAGVAR(export_dynamic_flag_spec, $1)='${wl}--export-all-symbols' _LT_TAGVAR(allow_undefined_flag, $1)=unsupported _LT_TAGVAR(always_export_symbols, $1)=no _LT_TAGVAR(enable_shared_with_static_runtimes, $1)=yes if $LD --help 2>&1 | $GREP 'auto-import' > /dev/null; then _LT_TAGVAR(archive_cmds, $1)='$CC -shared -nostdlib $predep_objects $libobjs $deplibs $postdep_objects $compiler_flags -o $output_objdir/$soname ${wl}--enable-auto-image-base -Xlinker --out-implib -Xlinker $lib' # If the export-symbols file already is a .def file (1st line # is EXPORTS), use it as is; otherwise, prepend... _LT_TAGVAR(archive_expsym_cmds, $1)='if test "x`$SED 1q $export_symbols`" = xEXPORTS; then cp $export_symbols $output_objdir/$soname.def; else echo EXPORTS > $output_objdir/$soname.def; cat $export_symbols >> $output_objdir/$soname.def; fi~ $CC -shared -nostdlib $output_objdir/$soname.def $predep_objects $libobjs $deplibs $postdep_objects $compiler_flags -o $output_objdir/$soname ${wl}--enable-auto-image-base -Xlinker --out-implib -Xlinker $lib' else _LT_TAGVAR(ld_shlibs, $1)=no fi ;; esac ;; darwin* | rhapsody*) _LT_DARWIN_LINKER_FEATURES($1) ;; dgux*) case $cc_basename in ec++*) # FIXME: insert proper C++ library support _LT_TAGVAR(ld_shlibs, $1)=no ;; ghcx*) # Green Hills C++ Compiler # FIXME: insert proper C++ library support _LT_TAGVAR(ld_shlibs, $1)=no ;; *) # FIXME: insert proper C++ library support _LT_TAGVAR(ld_shlibs, $1)=no ;; esac ;; freebsd2.*) # C++ shared libraries reported to be fairly broken before # switch to ELF _LT_TAGVAR(ld_shlibs, $1)=no ;; freebsd-elf*) _LT_TAGVAR(archive_cmds_need_lc, $1)=no ;; freebsd* | dragonfly*) # FreeBSD 3 and later use GNU C++ and GNU ld with standard ELF # conventions _LT_TAGVAR(ld_shlibs, $1)=yes ;; haiku*) _LT_TAGVAR(archive_cmds, $1)='$CC -shared $libobjs $deplibs $compiler_flags ${wl}-soname $wl$soname -o $lib' _LT_TAGVAR(link_all_deplibs, $1)=yes ;; hpux9*) _LT_TAGVAR(hardcode_libdir_flag_spec, $1)='${wl}+b ${wl}$libdir' _LT_TAGVAR(hardcode_libdir_separator, $1)=: _LT_TAGVAR(export_dynamic_flag_spec, $1)='${wl}-E' _LT_TAGVAR(hardcode_direct, $1)=yes _LT_TAGVAR(hardcode_minus_L, $1)=yes # Not in the search PATH, # but as the default # location of the library. case $cc_basename in CC*) # FIXME: insert proper C++ library support _LT_TAGVAR(ld_shlibs, $1)=no ;; aCC*) _LT_TAGVAR(archive_cmds, $1)='$RM $output_objdir/$soname~$CC -b ${wl}+b ${wl}$install_libdir -o $output_objdir/$soname $predep_objects $libobjs $deplibs $postdep_objects $compiler_flags~test $output_objdir/$soname = $lib || mv $output_objdir/$soname $lib' # Commands to make compiler produce verbose output that lists # what "hidden" libraries, object files and flags are used when # linking a shared library. # # There doesn't appear to be a way to prevent this compiler from # explicitly linking system object files so we need to strip them # from the output so that they don't get included in the library # dependencies. output_verbose_link_cmd='templist=`($CC -b $CFLAGS -v conftest.$objext 2>&1) | $EGREP "\-L"`; list=""; for z in $templist; do case $z in conftest.$objext) list="$list $z";; *.$objext);; *) list="$list $z";;esac; done; func_echo_all "$list"' ;; *) if test "$GXX" = yes; then _LT_TAGVAR(archive_cmds, $1)='$RM $output_objdir/$soname~$CC -shared -nostdlib $pic_flag ${wl}+b ${wl}$install_libdir -o $output_objdir/$soname $predep_objects $libobjs $deplibs $postdep_objects $compiler_flags~test $output_objdir/$soname = $lib || mv $output_objdir/$soname $lib' else # FIXME: insert proper C++ library support _LT_TAGVAR(ld_shlibs, $1)=no fi ;; esac ;; hpux10*|hpux11*) if test $with_gnu_ld = no; then _LT_TAGVAR(hardcode_libdir_flag_spec, $1)='${wl}+b ${wl}$libdir' _LT_TAGVAR(hardcode_libdir_separator, $1)=: case $host_cpu in hppa*64*|ia64*) ;; *) _LT_TAGVAR(export_dynamic_flag_spec, $1)='${wl}-E' ;; esac fi case $host_cpu in hppa*64*|ia64*) _LT_TAGVAR(hardcode_direct, $1)=no _LT_TAGVAR(hardcode_shlibpath_var, $1)=no ;; *) _LT_TAGVAR(hardcode_direct, $1)=yes _LT_TAGVAR(hardcode_direct_absolute, $1)=yes _LT_TAGVAR(hardcode_minus_L, $1)=yes # Not in the search PATH, # but as the default # location of the library. ;; esac case $cc_basename in CC*) # FIXME: insert proper C++ library support _LT_TAGVAR(ld_shlibs, $1)=no ;; aCC*) case $host_cpu in hppa*64*) _LT_TAGVAR(archive_cmds, $1)='$CC -b ${wl}+h ${wl}$soname -o $lib $predep_objects $libobjs $deplibs $postdep_objects $compiler_flags' ;; ia64*) _LT_TAGVAR(archive_cmds, $1)='$CC -b ${wl}+h ${wl}$soname ${wl}+nodefaultrpath -o $lib $predep_objects $libobjs $deplibs $postdep_objects $compiler_flags' ;; *) _LT_TAGVAR(archive_cmds, $1)='$CC -b ${wl}+h ${wl}$soname ${wl}+b ${wl}$install_libdir -o $lib $predep_objects $libobjs $deplibs $postdep_objects $compiler_flags' ;; esac # Commands to make compiler produce verbose output that lists # what "hidden" libraries, object files and flags are used when # linking a shared library. # # There doesn't appear to be a way to prevent this compiler from # explicitly linking system object files so we need to strip them # from the output so that they don't get included in the library # dependencies. output_verbose_link_cmd='templist=`($CC -b $CFLAGS -v conftest.$objext 2>&1) | $GREP "\-L"`; list=""; for z in $templist; do case $z in conftest.$objext) list="$list $z";; *.$objext);; *) list="$list $z";;esac; done; func_echo_all "$list"' ;; *) if test "$GXX" = yes; then if test $with_gnu_ld = no; then case $host_cpu in hppa*64*) _LT_TAGVAR(archive_cmds, $1)='$CC -shared -nostdlib -fPIC ${wl}+h ${wl}$soname -o $lib $predep_objects $libobjs $deplibs $postdep_objects $compiler_flags' ;; ia64*) _LT_TAGVAR(archive_cmds, $1)='$CC -shared -nostdlib $pic_flag ${wl}+h ${wl}$soname ${wl}+nodefaultrpath -o $lib $predep_objects $libobjs $deplibs $postdep_objects $compiler_flags' ;; *) _LT_TAGVAR(archive_cmds, $1)='$CC -shared -nostdlib $pic_flag ${wl}+h ${wl}$soname ${wl}+b ${wl}$install_libdir -o $lib $predep_objects $libobjs $deplibs $postdep_objects $compiler_flags' ;; esac fi else # FIXME: insert proper C++ library support _LT_TAGVAR(ld_shlibs, $1)=no fi ;; esac ;; interix[[3-9]]*) _LT_TAGVAR(hardcode_direct, $1)=no _LT_TAGVAR(hardcode_shlibpath_var, $1)=no _LT_TAGVAR(hardcode_libdir_flag_spec, $1)='${wl}-rpath,$libdir' _LT_TAGVAR(export_dynamic_flag_spec, $1)='${wl}-E' # Hack: On Interix 3.x, we cannot compile PIC because of a broken gcc. # Instead, shared libraries are loaded at an image base (0x10000000 by # default) and relocated if they conflict, which is a slow very memory # consuming and fragmenting process. To avoid this, we pick a random, # 256 KiB-aligned image base between 0x50000000 and 0x6FFC0000 at link # time. Moving up from 0x10000000 also allows more sbrk(2) space. _LT_TAGVAR(archive_cmds, $1)='$CC -shared $pic_flag $libobjs $deplibs $compiler_flags ${wl}-h,$soname ${wl}--image-base,`expr ${RANDOM-$$} % 4096 / 2 \* 262144 + 1342177280` -o $lib' _LT_TAGVAR(archive_expsym_cmds, $1)='sed "s,^,_," $export_symbols >$output_objdir/$soname.expsym~$CC -shared $pic_flag $libobjs $deplibs $compiler_flags ${wl}-h,$soname ${wl}--retain-symbols-file,$output_objdir/$soname.expsym ${wl}--image-base,`expr ${RANDOM-$$} % 4096 / 2 \* 262144 + 1342177280` -o $lib' ;; irix5* | irix6*) case $cc_basename in CC*) # SGI C++ _LT_TAGVAR(archive_cmds, $1)='$CC -shared -all -multigot $predep_objects $libobjs $deplibs $postdep_objects $compiler_flags -soname $soname `test -n "$verstring" && func_echo_all "-set_version $verstring"` -update_registry ${output_objdir}/so_locations -o $lib' # Archives containing C++ object files must be created using # "CC -ar", where "CC" is the IRIX C++ compiler. This is # necessary to make sure instantiated templates are included # in the archive. _LT_TAGVAR(old_archive_cmds, $1)='$CC -ar -WR,-u -o $oldlib $oldobjs' ;; *) if test "$GXX" = yes; then if test "$with_gnu_ld" = no; then _LT_TAGVAR(archive_cmds, $1)='$CC -shared $pic_flag -nostdlib $predep_objects $libobjs $deplibs $postdep_objects $compiler_flags ${wl}-soname ${wl}$soname `test -n "$verstring" && func_echo_all "${wl}-set_version ${wl}$verstring"` ${wl}-update_registry ${wl}${output_objdir}/so_locations -o $lib' else _LT_TAGVAR(archive_cmds, $1)='$CC -shared $pic_flag -nostdlib $predep_objects $libobjs $deplibs $postdep_objects $compiler_flags ${wl}-soname ${wl}$soname `test -n "$verstring" && func_echo_all "${wl}-set_version ${wl}$verstring"` -o $lib' fi fi _LT_TAGVAR(link_all_deplibs, $1)=yes ;; esac _LT_TAGVAR(hardcode_libdir_flag_spec, $1)='${wl}-rpath ${wl}$libdir' _LT_TAGVAR(hardcode_libdir_separator, $1)=: _LT_TAGVAR(inherit_rpath, $1)=yes ;; linux* | k*bsd*-gnu | kopensolaris*-gnu | gnu*) case $cc_basename in KCC*) # Kuck and Associates, Inc. (KAI) C++ Compiler # KCC will only create a shared library if the output file # ends with ".so" (or ".sl" for HP-UX), so rename the library # to its proper name (with version) after linking. _LT_TAGVAR(archive_cmds, $1)='tempext=`echo $shared_ext | $SED -e '\''s/\([[^()0-9A-Za-z{}]]\)/\\\\\1/g'\''`; templib=`echo $lib | $SED -e "s/\${tempext}\..*/.so/"`; $CC $predep_objects $libobjs $deplibs $postdep_objects $compiler_flags --soname $soname -o \$templib; mv \$templib $lib' _LT_TAGVAR(archive_expsym_cmds, $1)='tempext=`echo $shared_ext | $SED -e '\''s/\([[^()0-9A-Za-z{}]]\)/\\\\\1/g'\''`; templib=`echo $lib | $SED -e "s/\${tempext}\..*/.so/"`; $CC $predep_objects $libobjs $deplibs $postdep_objects $compiler_flags --soname $soname -o \$templib ${wl}-retain-symbols-file,$export_symbols; mv \$templib $lib' # Commands to make compiler produce verbose output that lists # what "hidden" libraries, object files and flags are used when # linking a shared library. # # There doesn't appear to be a way to prevent this compiler from # explicitly linking system object files so we need to strip them # from the output so that they don't get included in the library # dependencies. output_verbose_link_cmd='templist=`$CC $CFLAGS -v conftest.$objext -o libconftest$shared_ext 2>&1 | $GREP "ld"`; rm -f libconftest$shared_ext; list=""; for z in $templist; do case $z in conftest.$objext) list="$list $z";; *.$objext);; *) list="$list $z";;esac; done; func_echo_all "$list"' _LT_TAGVAR(hardcode_libdir_flag_spec, $1)='${wl}-rpath,$libdir' _LT_TAGVAR(export_dynamic_flag_spec, $1)='${wl}--export-dynamic' # Archives containing C++ object files must be created using # "CC -Bstatic", where "CC" is the KAI C++ compiler. _LT_TAGVAR(old_archive_cmds, $1)='$CC -Bstatic -o $oldlib $oldobjs' ;; icpc* | ecpc* ) # Intel C++ with_gnu_ld=yes # version 8.0 and above of icpc choke on multiply defined symbols # if we add $predep_objects and $postdep_objects, however 7.1 and # earlier do not add the objects themselves. case `$CC -V 2>&1` in *"Version 7."*) _LT_TAGVAR(archive_cmds, $1)='$CC -shared $predep_objects $libobjs $deplibs $postdep_objects $compiler_flags ${wl}-soname $wl$soname -o $lib' _LT_TAGVAR(archive_expsym_cmds, $1)='$CC -shared $predep_objects $libobjs $deplibs $postdep_objects $compiler_flags ${wl}-soname $wl$soname ${wl}-retain-symbols-file $wl$export_symbols -o $lib' ;; *) # Version 8.0 or newer tmp_idyn= case $host_cpu in ia64*) tmp_idyn=' -i_dynamic';; esac _LT_TAGVAR(archive_cmds, $1)='$CC -shared'"$tmp_idyn"' $libobjs $deplibs $compiler_flags ${wl}-soname $wl$soname -o $lib' _LT_TAGVAR(archive_expsym_cmds, $1)='$CC -shared'"$tmp_idyn"' $libobjs $deplibs $compiler_flags ${wl}-soname $wl$soname ${wl}-retain-symbols-file $wl$export_symbols -o $lib' ;; esac _LT_TAGVAR(archive_cmds_need_lc, $1)=no _LT_TAGVAR(hardcode_libdir_flag_spec, $1)='${wl}-rpath,$libdir' _LT_TAGVAR(export_dynamic_flag_spec, $1)='${wl}--export-dynamic' _LT_TAGVAR(whole_archive_flag_spec, $1)='${wl}--whole-archive$convenience ${wl}--no-whole-archive' ;; pgCC* | pgcpp*) # Portland Group C++ compiler case `$CC -V` in *pgCC\ [[1-5]].* | *pgcpp\ [[1-5]].*) _LT_TAGVAR(prelink_cmds, $1)='tpldir=Template.dir~ rm -rf $tpldir~ $CC --prelink_objects --instantiation_dir $tpldir $objs $libobjs $compile_deplibs~ compile_command="$compile_command `find $tpldir -name \*.o | sort | $NL2SP`"' _LT_TAGVAR(old_archive_cmds, $1)='tpldir=Template.dir~ rm -rf $tpldir~ $CC --prelink_objects --instantiation_dir $tpldir $oldobjs$old_deplibs~ $AR $AR_FLAGS $oldlib$oldobjs$old_deplibs `find $tpldir -name \*.o | sort | $NL2SP`~ $RANLIB $oldlib' _LT_TAGVAR(archive_cmds, $1)='tpldir=Template.dir~ rm -rf $tpldir~ $CC --prelink_objects --instantiation_dir $tpldir $predep_objects $libobjs $deplibs $convenience $postdep_objects~ $CC -shared $pic_flag $predep_objects $libobjs $deplibs `find $tpldir -name \*.o | sort | $NL2SP` $postdep_objects $compiler_flags ${wl}-soname ${wl}$soname -o $lib' _LT_TAGVAR(archive_expsym_cmds, $1)='tpldir=Template.dir~ rm -rf $tpldir~ $CC --prelink_objects --instantiation_dir $tpldir $predep_objects $libobjs $deplibs $convenience $postdep_objects~ $CC -shared $pic_flag $predep_objects $libobjs $deplibs `find $tpldir -name \*.o | sort | $NL2SP` $postdep_objects $compiler_flags ${wl}-soname ${wl}$soname ${wl}-retain-symbols-file ${wl}$export_symbols -o $lib' ;; *) # Version 6 and above use weak symbols _LT_TAGVAR(archive_cmds, $1)='$CC -shared $pic_flag $predep_objects $libobjs $deplibs $postdep_objects $compiler_flags ${wl}-soname ${wl}$soname -o $lib' _LT_TAGVAR(archive_expsym_cmds, $1)='$CC -shared $pic_flag $predep_objects $libobjs $deplibs $postdep_objects $compiler_flags ${wl}-soname ${wl}$soname ${wl}-retain-symbols-file ${wl}$export_symbols -o $lib' ;; esac _LT_TAGVAR(hardcode_libdir_flag_spec, $1)='${wl}--rpath ${wl}$libdir' _LT_TAGVAR(export_dynamic_flag_spec, $1)='${wl}--export-dynamic' _LT_TAGVAR(whole_archive_flag_spec, $1)='${wl}--whole-archive`for conv in $convenience\"\"; do test -n \"$conv\" && new_convenience=\"$new_convenience,$conv\"; done; func_echo_all \"$new_convenience\"` ${wl}--no-whole-archive' ;; cxx*) # Compaq C++ _LT_TAGVAR(archive_cmds, $1)='$CC -shared $predep_objects $libobjs $deplibs $postdep_objects $compiler_flags ${wl}-soname $wl$soname -o $lib' _LT_TAGVAR(archive_expsym_cmds, $1)='$CC -shared $predep_objects $libobjs $deplibs $postdep_objects $compiler_flags ${wl}-soname $wl$soname -o $lib ${wl}-retain-symbols-file $wl$export_symbols' runpath_var=LD_RUN_PATH _LT_TAGVAR(hardcode_libdir_flag_spec, $1)='-rpath $libdir' _LT_TAGVAR(hardcode_libdir_separator, $1)=: # Commands to make compiler produce verbose output that lists # what "hidden" libraries, object files and flags are used when # linking a shared library. # # There doesn't appear to be a way to prevent this compiler from # explicitly linking system object files so we need to strip them # from the output so that they don't get included in the library # dependencies. output_verbose_link_cmd='templist=`$CC -shared $CFLAGS -v conftest.$objext 2>&1 | $GREP "ld"`; templist=`func_echo_all "$templist" | $SED "s/\(^.*ld.*\)\( .*ld .*$\)/\1/"`; list=""; for z in $templist; do case $z in conftest.$objext) list="$list $z";; *.$objext);; *) list="$list $z";;esac; done; func_echo_all "X$list" | $Xsed' ;; xl* | mpixl* | bgxl*) # IBM XL 8.0 on PPC, with GNU ld _LT_TAGVAR(hardcode_libdir_flag_spec, $1)='${wl}-rpath ${wl}$libdir' _LT_TAGVAR(export_dynamic_flag_spec, $1)='${wl}--export-dynamic' _LT_TAGVAR(archive_cmds, $1)='$CC -qmkshrobj $libobjs $deplibs $compiler_flags ${wl}-soname $wl$soname -o $lib' if test "x$supports_anon_versioning" = xyes; then _LT_TAGVAR(archive_expsym_cmds, $1)='echo "{ global:" > $output_objdir/$libname.ver~ cat $export_symbols | sed -e "s/\(.*\)/\1;/" >> $output_objdir/$libname.ver~ echo "local: *; };" >> $output_objdir/$libname.ver~ $CC -qmkshrobj $libobjs $deplibs $compiler_flags ${wl}-soname $wl$soname ${wl}-version-script ${wl}$output_objdir/$libname.ver -o $lib' fi ;; *) case `$CC -V 2>&1 | sed 5q` in *Sun\ C*) # Sun C++ 5.9 _LT_TAGVAR(no_undefined_flag, $1)=' -zdefs' _LT_TAGVAR(archive_cmds, $1)='$CC -G${allow_undefined_flag} -h$soname -o $lib $predep_objects $libobjs $deplibs $postdep_objects $compiler_flags' _LT_TAGVAR(archive_expsym_cmds, $1)='$CC -G${allow_undefined_flag} -h$soname -o $lib $predep_objects $libobjs $deplibs $postdep_objects $compiler_flags ${wl}-retain-symbols-file ${wl}$export_symbols' _LT_TAGVAR(hardcode_libdir_flag_spec, $1)='-R$libdir' _LT_TAGVAR(whole_archive_flag_spec, $1)='${wl}--whole-archive`new_convenience=; for conv in $convenience\"\"; do test -z \"$conv\" || new_convenience=\"$new_convenience,$conv\"; done; func_echo_all \"$new_convenience\"` ${wl}--no-whole-archive' _LT_TAGVAR(compiler_needs_object, $1)=yes # Not sure whether something based on # $CC $CFLAGS -v conftest.$objext -o libconftest$shared_ext 2>&1 # would be better. output_verbose_link_cmd='func_echo_all' # Archives containing C++ object files must be created using # "CC -xar", where "CC" is the Sun C++ compiler. This is # necessary to make sure instantiated templates are included # in the archive. _LT_TAGVAR(old_archive_cmds, $1)='$CC -xar -o $oldlib $oldobjs' ;; esac ;; esac ;; lynxos*) # FIXME: insert proper C++ library support _LT_TAGVAR(ld_shlibs, $1)=no ;; m88k*) # FIXME: insert proper C++ library support _LT_TAGVAR(ld_shlibs, $1)=no ;; mvs*) case $cc_basename in cxx*) # FIXME: insert proper C++ library support _LT_TAGVAR(ld_shlibs, $1)=no ;; *) # FIXME: insert proper C++ library support _LT_TAGVAR(ld_shlibs, $1)=no ;; esac ;; netbsd*) if echo __ELF__ | $CC -E - | $GREP __ELF__ >/dev/null; then _LT_TAGVAR(archive_cmds, $1)='$LD -Bshareable -o $lib $predep_objects $libobjs $deplibs $postdep_objects $linker_flags' wlarc= _LT_TAGVAR(hardcode_libdir_flag_spec, $1)='-R$libdir' _LT_TAGVAR(hardcode_direct, $1)=yes _LT_TAGVAR(hardcode_shlibpath_var, $1)=no fi # Workaround some broken pre-1.5 toolchains output_verbose_link_cmd='$CC -shared $CFLAGS -v conftest.$objext 2>&1 | $GREP conftest.$objext | $SED -e "s:-lgcc -lc -lgcc::"' ;; *nto* | *qnx*) _LT_TAGVAR(ld_shlibs, $1)=yes ;; openbsd2*) # C++ shared libraries are fairly broken _LT_TAGVAR(ld_shlibs, $1)=no ;; openbsd*) if test -f /usr/libexec/ld.so; then _LT_TAGVAR(hardcode_direct, $1)=yes _LT_TAGVAR(hardcode_shlibpath_var, $1)=no _LT_TAGVAR(hardcode_direct_absolute, $1)=yes _LT_TAGVAR(archive_cmds, $1)='$CC -shared $pic_flag $predep_objects $libobjs $deplibs $postdep_objects $compiler_flags -o $lib' _LT_TAGVAR(hardcode_libdir_flag_spec, $1)='${wl}-rpath,$libdir' if test -z "`echo __ELF__ | $CC -E - | grep __ELF__`" || test "$host_os-$host_cpu" = "openbsd2.8-powerpc"; then _LT_TAGVAR(archive_expsym_cmds, $1)='$CC -shared $pic_flag $predep_objects $libobjs $deplibs $postdep_objects $compiler_flags ${wl}-retain-symbols-file,$export_symbols -o $lib' _LT_TAGVAR(export_dynamic_flag_spec, $1)='${wl}-E' _LT_TAGVAR(whole_archive_flag_spec, $1)="$wlarc"'--whole-archive$convenience '"$wlarc"'--no-whole-archive' fi output_verbose_link_cmd=func_echo_all else _LT_TAGVAR(ld_shlibs, $1)=no fi ;; osf3* | osf4* | osf5*) case $cc_basename in KCC*) # Kuck and Associates, Inc. (KAI) C++ Compiler # KCC will only create a shared library if the output file # ends with ".so" (or ".sl" for HP-UX), so rename the library # to its proper name (with version) after linking. _LT_TAGVAR(archive_cmds, $1)='tempext=`echo $shared_ext | $SED -e '\''s/\([[^()0-9A-Za-z{}]]\)/\\\\\1/g'\''`; templib=`echo "$lib" | $SED -e "s/\${tempext}\..*/.so/"`; $CC $predep_objects $libobjs $deplibs $postdep_objects $compiler_flags --soname $soname -o \$templib; mv \$templib $lib' _LT_TAGVAR(hardcode_libdir_flag_spec, $1)='${wl}-rpath,$libdir' _LT_TAGVAR(hardcode_libdir_separator, $1)=: # Archives containing C++ object files must be created using # the KAI C++ compiler. case $host in osf3*) _LT_TAGVAR(old_archive_cmds, $1)='$CC -Bstatic -o $oldlib $oldobjs' ;; *) _LT_TAGVAR(old_archive_cmds, $1)='$CC -o $oldlib $oldobjs' ;; esac ;; RCC*) # Rational C++ 2.4.1 # FIXME: insert proper C++ library support _LT_TAGVAR(ld_shlibs, $1)=no ;; cxx*) case $host in osf3*) _LT_TAGVAR(allow_undefined_flag, $1)=' ${wl}-expect_unresolved ${wl}\*' _LT_TAGVAR(archive_cmds, $1)='$CC -shared${allow_undefined_flag} $predep_objects $libobjs $deplibs $postdep_objects $compiler_flags ${wl}-soname $soname `test -n "$verstring" && func_echo_all "${wl}-set_version $verstring"` -update_registry ${output_objdir}/so_locations -o $lib' _LT_TAGVAR(hardcode_libdir_flag_spec, $1)='${wl}-rpath ${wl}$libdir' ;; *) _LT_TAGVAR(allow_undefined_flag, $1)=' -expect_unresolved \*' _LT_TAGVAR(archive_cmds, $1)='$CC -shared${allow_undefined_flag} $predep_objects $libobjs $deplibs $postdep_objects $compiler_flags -msym -soname $soname `test -n "$verstring" && func_echo_all "-set_version $verstring"` -update_registry ${output_objdir}/so_locations -o $lib' _LT_TAGVAR(archive_expsym_cmds, $1)='for i in `cat $export_symbols`; do printf "%s %s\\n" -exported_symbol "\$i" >> $lib.exp; done~ echo "-hidden">> $lib.exp~ $CC -shared$allow_undefined_flag $predep_objects $libobjs $deplibs $postdep_objects $compiler_flags -msym -soname $soname ${wl}-input ${wl}$lib.exp `test -n "$verstring" && $ECHO "-set_version $verstring"` -update_registry ${output_objdir}/so_locations -o $lib~ $RM $lib.exp' _LT_TAGVAR(hardcode_libdir_flag_spec, $1)='-rpath $libdir' ;; esac _LT_TAGVAR(hardcode_libdir_separator, $1)=: # Commands to make compiler produce verbose output that lists # what "hidden" libraries, object files and flags are used when # linking a shared library. # # There doesn't appear to be a way to prevent this compiler from # explicitly linking system object files so we need to strip them # from the output so that they don't get included in the library # dependencies. output_verbose_link_cmd='templist=`$CC -shared $CFLAGS -v conftest.$objext 2>&1 | $GREP "ld" | $GREP -v "ld:"`; templist=`func_echo_all "$templist" | $SED "s/\(^.*ld.*\)\( .*ld.*$\)/\1/"`; list=""; for z in $templist; do case $z in conftest.$objext) list="$list $z";; *.$objext);; *) list="$list $z";;esac; done; func_echo_all "$list"' ;; *) if test "$GXX" = yes && test "$with_gnu_ld" = no; then _LT_TAGVAR(allow_undefined_flag, $1)=' ${wl}-expect_unresolved ${wl}\*' case $host in osf3*) _LT_TAGVAR(archive_cmds, $1)='$CC -shared -nostdlib ${allow_undefined_flag} $predep_objects $libobjs $deplibs $postdep_objects $compiler_flags ${wl}-soname ${wl}$soname `test -n "$verstring" && func_echo_all "${wl}-set_version ${wl}$verstring"` ${wl}-update_registry ${wl}${output_objdir}/so_locations -o $lib' ;; *) _LT_TAGVAR(archive_cmds, $1)='$CC -shared $pic_flag -nostdlib ${allow_undefined_flag} $predep_objects $libobjs $deplibs $postdep_objects $compiler_flags ${wl}-msym ${wl}-soname ${wl}$soname `test -n "$verstring" && func_echo_all "${wl}-set_version ${wl}$verstring"` ${wl}-update_registry ${wl}${output_objdir}/so_locations -o $lib' ;; esac _LT_TAGVAR(hardcode_libdir_flag_spec, $1)='${wl}-rpath ${wl}$libdir' _LT_TAGVAR(hardcode_libdir_separator, $1)=: # Commands to make compiler produce verbose output that lists # what "hidden" libraries, object files and flags are used when # linking a shared library. output_verbose_link_cmd='$CC -shared $CFLAGS -v conftest.$objext 2>&1 | $GREP -v "^Configured with:" | $GREP "\-L"' else # FIXME: insert proper C++ library support _LT_TAGVAR(ld_shlibs, $1)=no fi ;; esac ;; psos*) # FIXME: insert proper C++ library support _LT_TAGVAR(ld_shlibs, $1)=no ;; sunos4*) case $cc_basename in CC*) # Sun C++ 4.x # FIXME: insert proper C++ library support _LT_TAGVAR(ld_shlibs, $1)=no ;; lcc*) # Lucid # FIXME: insert proper C++ library support _LT_TAGVAR(ld_shlibs, $1)=no ;; *) # FIXME: insert proper C++ library support _LT_TAGVAR(ld_shlibs, $1)=no ;; esac ;; solaris*) case $cc_basename in CC* | sunCC*) # Sun C++ 4.2, 5.x and Centerline C++ _LT_TAGVAR(archive_cmds_need_lc,$1)=yes _LT_TAGVAR(no_undefined_flag, $1)=' -zdefs' _LT_TAGVAR(archive_cmds, $1)='$CC -G${allow_undefined_flag} -h$soname -o $lib $predep_objects $libobjs $deplibs $postdep_objects $compiler_flags' _LT_TAGVAR(archive_expsym_cmds, $1)='echo "{ global:" > $lib.exp~cat $export_symbols | $SED -e "s/\(.*\)/\1;/" >> $lib.exp~echo "local: *; };" >> $lib.exp~ $CC -G${allow_undefined_flag} ${wl}-M ${wl}$lib.exp -h$soname -o $lib $predep_objects $libobjs $deplibs $postdep_objects $compiler_flags~$RM $lib.exp' _LT_TAGVAR(hardcode_libdir_flag_spec, $1)='-R$libdir' _LT_TAGVAR(hardcode_shlibpath_var, $1)=no case $host_os in solaris2.[[0-5]] | solaris2.[[0-5]].*) ;; *) # The compiler driver will combine and reorder linker options, # but understands `-z linker_flag'. # Supported since Solaris 2.6 (maybe 2.5.1?) _LT_TAGVAR(whole_archive_flag_spec, $1)='-z allextract$convenience -z defaultextract' ;; esac _LT_TAGVAR(link_all_deplibs, $1)=yes output_verbose_link_cmd='func_echo_all' # Archives containing C++ object files must be created using # "CC -xar", where "CC" is the Sun C++ compiler. This is # necessary to make sure instantiated templates are included # in the archive. _LT_TAGVAR(old_archive_cmds, $1)='$CC -xar -o $oldlib $oldobjs' ;; gcx*) # Green Hills C++ Compiler _LT_TAGVAR(archive_cmds, $1)='$CC -shared $predep_objects $libobjs $deplibs $postdep_objects $compiler_flags ${wl}-h $wl$soname -o $lib' # The C++ compiler must be used to create the archive. _LT_TAGVAR(old_archive_cmds, $1)='$CC $LDFLAGS -archive -o $oldlib $oldobjs' ;; *) # GNU C++ compiler with Solaris linker if test "$GXX" = yes && test "$with_gnu_ld" = no; then _LT_TAGVAR(no_undefined_flag, $1)=' ${wl}-z ${wl}defs' if $CC --version | $GREP -v '^2\.7' > /dev/null; then _LT_TAGVAR(archive_cmds, $1)='$CC -shared $pic_flag -nostdlib $LDFLAGS $predep_objects $libobjs $deplibs $postdep_objects $compiler_flags ${wl}-h $wl$soname -o $lib' _LT_TAGVAR(archive_expsym_cmds, $1)='echo "{ global:" > $lib.exp~cat $export_symbols | $SED -e "s/\(.*\)/\1;/" >> $lib.exp~echo "local: *; };" >> $lib.exp~ $CC -shared $pic_flag -nostdlib ${wl}-M $wl$lib.exp -o $lib $predep_objects $libobjs $deplibs $postdep_objects $compiler_flags~$RM $lib.exp' # Commands to make compiler produce verbose output that lists # what "hidden" libraries, object files and flags are used when # linking a shared library. output_verbose_link_cmd='$CC -shared $CFLAGS -v conftest.$objext 2>&1 | $GREP -v "^Configured with:" | $GREP "\-L"' else # g++ 2.7 appears to require `-G' NOT `-shared' on this # platform. _LT_TAGVAR(archive_cmds, $1)='$CC -G -nostdlib $LDFLAGS $predep_objects $libobjs $deplibs $postdep_objects $compiler_flags ${wl}-h $wl$soname -o $lib' _LT_TAGVAR(archive_expsym_cmds, $1)='echo "{ global:" > $lib.exp~cat $export_symbols | $SED -e "s/\(.*\)/\1;/" >> $lib.exp~echo "local: *; };" >> $lib.exp~ $CC -G -nostdlib ${wl}-M $wl$lib.exp -o $lib $predep_objects $libobjs $deplibs $postdep_objects $compiler_flags~$RM $lib.exp' # Commands to make compiler produce verbose output that lists # what "hidden" libraries, object files and flags are used when # linking a shared library. output_verbose_link_cmd='$CC -G $CFLAGS -v conftest.$objext 2>&1 | $GREP -v "^Configured with:" | $GREP "\-L"' fi _LT_TAGVAR(hardcode_libdir_flag_spec, $1)='${wl}-R $wl$libdir' case $host_os in solaris2.[[0-5]] | solaris2.[[0-5]].*) ;; *) _LT_TAGVAR(whole_archive_flag_spec, $1)='${wl}-z ${wl}allextract$convenience ${wl}-z ${wl}defaultextract' ;; esac fi ;; esac ;; sysv4*uw2* | sysv5OpenUNIX* | sysv5UnixWare7.[[01]].[[10]]* | unixware7* | sco3.2v5.0.[[024]]*) _LT_TAGVAR(no_undefined_flag, $1)='${wl}-z,text' _LT_TAGVAR(archive_cmds_need_lc, $1)=no _LT_TAGVAR(hardcode_shlibpath_var, $1)=no runpath_var='LD_RUN_PATH' case $cc_basename in CC*) _LT_TAGVAR(archive_cmds, $1)='$CC -G ${wl}-h,$soname -o $lib $libobjs $deplibs $compiler_flags' _LT_TAGVAR(archive_expsym_cmds, $1)='$CC -G ${wl}-Bexport:$export_symbols ${wl}-h,$soname -o $lib $libobjs $deplibs $compiler_flags' ;; *) _LT_TAGVAR(archive_cmds, $1)='$CC -shared ${wl}-h,$soname -o $lib $libobjs $deplibs $compiler_flags' _LT_TAGVAR(archive_expsym_cmds, $1)='$CC -shared ${wl}-Bexport:$export_symbols ${wl}-h,$soname -o $lib $libobjs $deplibs $compiler_flags' ;; esac ;; sysv5* | sco3.2v5* | sco5v6*) # Note: We can NOT use -z defs as we might desire, because we do not # link with -lc, and that would cause any symbols used from libc to # always be unresolved, which means just about no library would # ever link correctly. If we're not using GNU ld we use -z text # though, which does catch some bad symbols but isn't as heavy-handed # as -z defs. _LT_TAGVAR(no_undefined_flag, $1)='${wl}-z,text' _LT_TAGVAR(allow_undefined_flag, $1)='${wl}-z,nodefs' _LT_TAGVAR(archive_cmds_need_lc, $1)=no _LT_TAGVAR(hardcode_shlibpath_var, $1)=no _LT_TAGVAR(hardcode_libdir_flag_spec, $1)='${wl}-R,$libdir' _LT_TAGVAR(hardcode_libdir_separator, $1)=':' _LT_TAGVAR(link_all_deplibs, $1)=yes _LT_TAGVAR(export_dynamic_flag_spec, $1)='${wl}-Bexport' runpath_var='LD_RUN_PATH' case $cc_basename in CC*) _LT_TAGVAR(archive_cmds, $1)='$CC -G ${wl}-h,$soname -o $lib $libobjs $deplibs $compiler_flags' _LT_TAGVAR(archive_expsym_cmds, $1)='$CC -G ${wl}-Bexport:$export_symbols ${wl}-h,$soname -o $lib $libobjs $deplibs $compiler_flags' _LT_TAGVAR(old_archive_cmds, $1)='$CC -Tprelink_objects $oldobjs~ '"$_LT_TAGVAR(old_archive_cmds, $1)" _LT_TAGVAR(reload_cmds, $1)='$CC -Tprelink_objects $reload_objs~ '"$_LT_TAGVAR(reload_cmds, $1)" ;; *) _LT_TAGVAR(archive_cmds, $1)='$CC -shared ${wl}-h,$soname -o $lib $libobjs $deplibs $compiler_flags' _LT_TAGVAR(archive_expsym_cmds, $1)='$CC -shared ${wl}-Bexport:$export_symbols ${wl}-h,$soname -o $lib $libobjs $deplibs $compiler_flags' ;; esac ;; tandem*) case $cc_basename in NCC*) # NonStop-UX NCC 3.20 # FIXME: insert proper C++ library support _LT_TAGVAR(ld_shlibs, $1)=no ;; *) # FIXME: insert proper C++ library support _LT_TAGVAR(ld_shlibs, $1)=no ;; esac ;; vxworks*) # FIXME: insert proper C++ library support _LT_TAGVAR(ld_shlibs, $1)=no ;; *) # FIXME: insert proper C++ library support _LT_TAGVAR(ld_shlibs, $1)=no ;; esac AC_MSG_RESULT([$_LT_TAGVAR(ld_shlibs, $1)]) test "$_LT_TAGVAR(ld_shlibs, $1)" = no && can_build_shared=no _LT_TAGVAR(GCC, $1)="$GXX" _LT_TAGVAR(LD, $1)="$LD" ## CAVEAT EMPTOR: ## There is no encapsulation within the following macros, do not change ## the running order or otherwise move them around unless you know exactly ## what you are doing... _LT_SYS_HIDDEN_LIBDEPS($1) _LT_COMPILER_PIC($1) _LT_COMPILER_C_O($1) _LT_COMPILER_FILE_LOCKS($1) _LT_LINKER_SHLIBS($1) _LT_SYS_DYNAMIC_LINKER($1) _LT_LINKER_HARDCODE_LIBPATH($1) _LT_CONFIG($1) fi # test -n "$compiler" CC=$lt_save_CC CFLAGS=$lt_save_CFLAGS LDCXX=$LD LD=$lt_save_LD GCC=$lt_save_GCC with_gnu_ld=$lt_save_with_gnu_ld lt_cv_path_LDCXX=$lt_cv_path_LD lt_cv_path_LD=$lt_save_path_LD lt_cv_prog_gnu_ldcxx=$lt_cv_prog_gnu_ld lt_cv_prog_gnu_ld=$lt_save_with_gnu_ld fi # test "$_lt_caught_CXX_error" != yes AC_LANG_POP ])# _LT_LANG_CXX_CONFIG # _LT_FUNC_STRIPNAME_CNF # ---------------------- # func_stripname_cnf prefix suffix name # strip PREFIX and SUFFIX off of NAME. # PREFIX and SUFFIX must not contain globbing or regex special # characters, hashes, percent signs, but SUFFIX may contain a leading # dot (in which case that matches only a dot). # # This function is identical to the (non-XSI) version of func_stripname, # except this one can be used by m4 code that may be executed by configure, # rather than the libtool script. m4_defun([_LT_FUNC_STRIPNAME_CNF],[dnl AC_REQUIRE([_LT_DECL_SED]) AC_REQUIRE([_LT_PROG_ECHO_BACKSLASH]) func_stripname_cnf () { case ${2} in .*) func_stripname_result=`$ECHO "${3}" | $SED "s%^${1}%%; s%\\\\${2}\$%%"`;; *) func_stripname_result=`$ECHO "${3}" | $SED "s%^${1}%%; s%${2}\$%%"`;; esac } # func_stripname_cnf ])# _LT_FUNC_STRIPNAME_CNF # _LT_SYS_HIDDEN_LIBDEPS([TAGNAME]) # --------------------------------- # Figure out "hidden" library dependencies from verbose # compiler output when linking a shared library. # Parse the compiler output and extract the necessary # objects, libraries and library flags. m4_defun([_LT_SYS_HIDDEN_LIBDEPS], [m4_require([_LT_FILEUTILS_DEFAULTS])dnl AC_REQUIRE([_LT_FUNC_STRIPNAME_CNF])dnl # Dependencies to place before and after the object being linked: _LT_TAGVAR(predep_objects, $1)= _LT_TAGVAR(postdep_objects, $1)= _LT_TAGVAR(predeps, $1)= _LT_TAGVAR(postdeps, $1)= _LT_TAGVAR(compiler_lib_search_path, $1)= dnl we can't use the lt_simple_compile_test_code here, dnl because it contains code intended for an executable, dnl not a library. It's possible we should let each dnl tag define a new lt_????_link_test_code variable, dnl but it's only used here... m4_if([$1], [], [cat > conftest.$ac_ext <<_LT_EOF int a; void foo (void) { a = 0; } _LT_EOF ], [$1], [CXX], [cat > conftest.$ac_ext <<_LT_EOF class Foo { public: Foo (void) { a = 0; } private: int a; }; _LT_EOF ], [$1], [F77], [cat > conftest.$ac_ext <<_LT_EOF subroutine foo implicit none integer*4 a a=0 return end _LT_EOF ], [$1], [FC], [cat > conftest.$ac_ext <<_LT_EOF subroutine foo implicit none integer a a=0 return end _LT_EOF ], [$1], [GCJ], [cat > conftest.$ac_ext <<_LT_EOF public class foo { private int a; public void bar (void) { a = 0; } }; _LT_EOF ], [$1], [GO], [cat > conftest.$ac_ext <<_LT_EOF package foo func foo() { } _LT_EOF ]) _lt_libdeps_save_CFLAGS=$CFLAGS case "$CC $CFLAGS " in #( *\ -flto*\ *) CFLAGS="$CFLAGS -fno-lto" ;; *\ -fwhopr*\ *) CFLAGS="$CFLAGS -fno-whopr" ;; *\ -fuse-linker-plugin*\ *) CFLAGS="$CFLAGS -fno-use-linker-plugin" ;; esac dnl Parse the compiler output and extract the necessary dnl objects, libraries and library flags. if AC_TRY_EVAL(ac_compile); then # Parse the compiler output and extract the necessary # objects, libraries and library flags. # Sentinel used to keep track of whether or not we are before # the conftest object file. pre_test_object_deps_done=no for p in `eval "$output_verbose_link_cmd"`; do case ${prev}${p} in -L* | -R* | -l*) # Some compilers place space between "-{L,R}" and the path. # Remove the space. if test $p = "-L" || test $p = "-R"; then prev=$p continue fi # Expand the sysroot to ease extracting the directories later. if test -z "$prev"; then case $p in -L*) func_stripname_cnf '-L' '' "$p"; prev=-L; p=$func_stripname_result ;; -R*) func_stripname_cnf '-R' '' "$p"; prev=-R; p=$func_stripname_result ;; -l*) func_stripname_cnf '-l' '' "$p"; prev=-l; p=$func_stripname_result ;; esac fi case $p in =*) func_stripname_cnf '=' '' "$p"; p=$lt_sysroot$func_stripname_result ;; esac if test "$pre_test_object_deps_done" = no; then case ${prev} in -L | -R) # Internal compiler library paths should come after those # provided the user. The postdeps already come after the # user supplied libs so there is no need to process them. if test -z "$_LT_TAGVAR(compiler_lib_search_path, $1)"; then _LT_TAGVAR(compiler_lib_search_path, $1)="${prev}${p}" else _LT_TAGVAR(compiler_lib_search_path, $1)="${_LT_TAGVAR(compiler_lib_search_path, $1)} ${prev}${p}" fi ;; # The "-l" case would never come before the object being # linked, so don't bother handling this case. esac else if test -z "$_LT_TAGVAR(postdeps, $1)"; then _LT_TAGVAR(postdeps, $1)="${prev}${p}" else _LT_TAGVAR(postdeps, $1)="${_LT_TAGVAR(postdeps, $1)} ${prev}${p}" fi fi prev= ;; *.lto.$objext) ;; # Ignore GCC LTO objects *.$objext) # This assumes that the test object file only shows up # once in the compiler output. if test "$p" = "conftest.$objext"; then pre_test_object_deps_done=yes continue fi if test "$pre_test_object_deps_done" = no; then if test -z "$_LT_TAGVAR(predep_objects, $1)"; then _LT_TAGVAR(predep_objects, $1)="$p" else _LT_TAGVAR(predep_objects, $1)="$_LT_TAGVAR(predep_objects, $1) $p" fi else if test -z "$_LT_TAGVAR(postdep_objects, $1)"; then _LT_TAGVAR(postdep_objects, $1)="$p" else _LT_TAGVAR(postdep_objects, $1)="$_LT_TAGVAR(postdep_objects, $1) $p" fi fi ;; *) ;; # Ignore the rest. esac done # Clean up. rm -f a.out a.exe else echo "libtool.m4: error: problem compiling $1 test program" fi $RM -f confest.$objext CFLAGS=$_lt_libdeps_save_CFLAGS # PORTME: override above test on systems where it is broken m4_if([$1], [CXX], [case $host_os in interix[[3-9]]*) # Interix 3.5 installs completely hosed .la files for C++, so rather than # hack all around it, let's just trust "g++" to DTRT. _LT_TAGVAR(predep_objects,$1)= _LT_TAGVAR(postdep_objects,$1)= _LT_TAGVAR(postdeps,$1)= ;; linux*) case `$CC -V 2>&1 | sed 5q` in *Sun\ C*) # Sun C++ 5.9 # The more standards-conforming stlport4 library is # incompatible with the Cstd library. Avoid specifying # it if it's in CXXFLAGS. Ignore libCrun as # -library=stlport4 depends on it. case " $CXX $CXXFLAGS " in *" -library=stlport4 "*) solaris_use_stlport4=yes ;; esac if test "$solaris_use_stlport4" != yes; then _LT_TAGVAR(postdeps,$1)='-library=Cstd -library=Crun' fi ;; esac ;; solaris*) case $cc_basename in CC* | sunCC*) # The more standards-conforming stlport4 library is # incompatible with the Cstd library. Avoid specifying # it if it's in CXXFLAGS. Ignore libCrun as # -library=stlport4 depends on it. case " $CXX $CXXFLAGS " in *" -library=stlport4 "*) solaris_use_stlport4=yes ;; esac # Adding this requires a known-good setup of shared libraries for # Sun compiler versions before 5.6, else PIC objects from an old # archive will be linked into the output, leading to subtle bugs. if test "$solaris_use_stlport4" != yes; then _LT_TAGVAR(postdeps,$1)='-library=Cstd -library=Crun' fi ;; esac ;; esac ]) case " $_LT_TAGVAR(postdeps, $1) " in *" -lc "*) _LT_TAGVAR(archive_cmds_need_lc, $1)=no ;; esac _LT_TAGVAR(compiler_lib_search_dirs, $1)= if test -n "${_LT_TAGVAR(compiler_lib_search_path, $1)}"; then _LT_TAGVAR(compiler_lib_search_dirs, $1)=`echo " ${_LT_TAGVAR(compiler_lib_search_path, $1)}" | ${SED} -e 's! -L! !g' -e 's!^ !!'` fi _LT_TAGDECL([], [compiler_lib_search_dirs], [1], [The directories searched by this compiler when creating a shared library]) _LT_TAGDECL([], [predep_objects], [1], [Dependencies to place before and after the objects being linked to create a shared library]) _LT_TAGDECL([], [postdep_objects], [1]) _LT_TAGDECL([], [predeps], [1]) _LT_TAGDECL([], [postdeps], [1]) _LT_TAGDECL([], [compiler_lib_search_path], [1], [The library search path used internally by the compiler when linking a shared library]) ])# _LT_SYS_HIDDEN_LIBDEPS # _LT_LANG_F77_CONFIG([TAG]) # -------------------------- # Ensure that the configuration variables for a Fortran 77 compiler are # suitably defined. These variables are subsequently used by _LT_CONFIG # to write the compiler configuration to `libtool'. m4_defun([_LT_LANG_F77_CONFIG], [AC_LANG_PUSH(Fortran 77) if test -z "$F77" || test "X$F77" = "Xno"; then _lt_disable_F77=yes fi _LT_TAGVAR(archive_cmds_need_lc, $1)=no _LT_TAGVAR(allow_undefined_flag, $1)= _LT_TAGVAR(always_export_symbols, $1)=no _LT_TAGVAR(archive_expsym_cmds, $1)= _LT_TAGVAR(export_dynamic_flag_spec, $1)= _LT_TAGVAR(hardcode_direct, $1)=no _LT_TAGVAR(hardcode_direct_absolute, $1)=no _LT_TAGVAR(hardcode_libdir_flag_spec, $1)= _LT_TAGVAR(hardcode_libdir_separator, $1)= _LT_TAGVAR(hardcode_minus_L, $1)=no _LT_TAGVAR(hardcode_automatic, $1)=no _LT_TAGVAR(inherit_rpath, $1)=no _LT_TAGVAR(module_cmds, $1)= _LT_TAGVAR(module_expsym_cmds, $1)= _LT_TAGVAR(link_all_deplibs, $1)=unknown _LT_TAGVAR(old_archive_cmds, $1)=$old_archive_cmds _LT_TAGVAR(reload_flag, $1)=$reload_flag _LT_TAGVAR(reload_cmds, $1)=$reload_cmds _LT_TAGVAR(no_undefined_flag, $1)= _LT_TAGVAR(whole_archive_flag_spec, $1)= _LT_TAGVAR(enable_shared_with_static_runtimes, $1)=no # Source file extension for f77 test sources. ac_ext=f # Object file extension for compiled f77 test sources. objext=o _LT_TAGVAR(objext, $1)=$objext # No sense in running all these tests if we already determined that # the F77 compiler isn't working. Some variables (like enable_shared) # are currently assumed to apply to all compilers on this platform, # and will be corrupted by setting them based on a non-working compiler. if test "$_lt_disable_F77" != yes; then # Code to be used in simple compile tests lt_simple_compile_test_code="\ subroutine t return end " # Code to be used in simple link tests lt_simple_link_test_code="\ program t end " # ltmain only uses $CC for tagged configurations so make sure $CC is set. _LT_TAG_COMPILER # save warnings/boilerplate of simple test code _LT_COMPILER_BOILERPLATE _LT_LINKER_BOILERPLATE # Allow CC to be a program name with arguments. lt_save_CC="$CC" lt_save_GCC=$GCC lt_save_CFLAGS=$CFLAGS CC=${F77-"f77"} CFLAGS=$FFLAGS compiler=$CC _LT_TAGVAR(compiler, $1)=$CC _LT_CC_BASENAME([$compiler]) GCC=$G77 if test -n "$compiler"; then AC_MSG_CHECKING([if libtool supports shared libraries]) AC_MSG_RESULT([$can_build_shared]) AC_MSG_CHECKING([whether to build shared libraries]) test "$can_build_shared" = "no" && enable_shared=no # On AIX, shared libraries and static libraries use the same namespace, and # are all built from PIC. case $host_os in aix3*) test "$enable_shared" = yes && enable_static=no if test -n "$RANLIB"; then archive_cmds="$archive_cmds~\$RANLIB \$lib" postinstall_cmds='$RANLIB $lib' fi ;; aix[[4-9]]*) if test "$host_cpu" != ia64 && test "$aix_use_runtimelinking" = no ; then test "$enable_shared" = yes && enable_static=no fi ;; esac AC_MSG_RESULT([$enable_shared]) AC_MSG_CHECKING([whether to build static libraries]) # Make sure either enable_shared or enable_static is yes. test "$enable_shared" = yes || enable_static=yes AC_MSG_RESULT([$enable_static]) _LT_TAGVAR(GCC, $1)="$G77" _LT_TAGVAR(LD, $1)="$LD" ## CAVEAT EMPTOR: ## There is no encapsulation within the following macros, do not change ## the running order or otherwise move them around unless you know exactly ## what you are doing... _LT_COMPILER_PIC($1) _LT_COMPILER_C_O($1) _LT_COMPILER_FILE_LOCKS($1) _LT_LINKER_SHLIBS($1) _LT_SYS_DYNAMIC_LINKER($1) _LT_LINKER_HARDCODE_LIBPATH($1) _LT_CONFIG($1) fi # test -n "$compiler" GCC=$lt_save_GCC CC="$lt_save_CC" CFLAGS="$lt_save_CFLAGS" fi # test "$_lt_disable_F77" != yes AC_LANG_POP ])# _LT_LANG_F77_CONFIG # _LT_LANG_FC_CONFIG([TAG]) # ------------------------- # Ensure that the configuration variables for a Fortran compiler are # suitably defined. These variables are subsequently used by _LT_CONFIG # to write the compiler configuration to `libtool'. m4_defun([_LT_LANG_FC_CONFIG], [AC_LANG_PUSH(Fortran) if test -z "$FC" || test "X$FC" = "Xno"; then _lt_disable_FC=yes fi _LT_TAGVAR(archive_cmds_need_lc, $1)=no _LT_TAGVAR(allow_undefined_flag, $1)= _LT_TAGVAR(always_export_symbols, $1)=no _LT_TAGVAR(archive_expsym_cmds, $1)= _LT_TAGVAR(export_dynamic_flag_spec, $1)= _LT_TAGVAR(hardcode_direct, $1)=no _LT_TAGVAR(hardcode_direct_absolute, $1)=no _LT_TAGVAR(hardcode_libdir_flag_spec, $1)= _LT_TAGVAR(hardcode_libdir_separator, $1)= _LT_TAGVAR(hardcode_minus_L, $1)=no _LT_TAGVAR(hardcode_automatic, $1)=no _LT_TAGVAR(inherit_rpath, $1)=no _LT_TAGVAR(module_cmds, $1)= _LT_TAGVAR(module_expsym_cmds, $1)= _LT_TAGVAR(link_all_deplibs, $1)=unknown _LT_TAGVAR(old_archive_cmds, $1)=$old_archive_cmds _LT_TAGVAR(reload_flag, $1)=$reload_flag _LT_TAGVAR(reload_cmds, $1)=$reload_cmds _LT_TAGVAR(no_undefined_flag, $1)= _LT_TAGVAR(whole_archive_flag_spec, $1)= _LT_TAGVAR(enable_shared_with_static_runtimes, $1)=no # Source file extension for fc test sources. ac_ext=${ac_fc_srcext-f} # Object file extension for compiled fc test sources. objext=o _LT_TAGVAR(objext, $1)=$objext # No sense in running all these tests if we already determined that # the FC compiler isn't working. Some variables (like enable_shared) # are currently assumed to apply to all compilers on this platform, # and will be corrupted by setting them based on a non-working compiler. if test "$_lt_disable_FC" != yes; then # Code to be used in simple compile tests lt_simple_compile_test_code="\ subroutine t return end " # Code to be used in simple link tests lt_simple_link_test_code="\ program t end " # ltmain only uses $CC for tagged configurations so make sure $CC is set. _LT_TAG_COMPILER # save warnings/boilerplate of simple test code _LT_COMPILER_BOILERPLATE _LT_LINKER_BOILERPLATE # Allow CC to be a program name with arguments. lt_save_CC="$CC" lt_save_GCC=$GCC lt_save_CFLAGS=$CFLAGS CC=${FC-"f95"} CFLAGS=$FCFLAGS compiler=$CC GCC=$ac_cv_fc_compiler_gnu _LT_TAGVAR(compiler, $1)=$CC _LT_CC_BASENAME([$compiler]) if test -n "$compiler"; then AC_MSG_CHECKING([if libtool supports shared libraries]) AC_MSG_RESULT([$can_build_shared]) AC_MSG_CHECKING([whether to build shared libraries]) test "$can_build_shared" = "no" && enable_shared=no # On AIX, shared libraries and static libraries use the same namespace, and # are all built from PIC. case $host_os in aix3*) test "$enable_shared" = yes && enable_static=no if test -n "$RANLIB"; then archive_cmds="$archive_cmds~\$RANLIB \$lib" postinstall_cmds='$RANLIB $lib' fi ;; aix[[4-9]]*) if test "$host_cpu" != ia64 && test "$aix_use_runtimelinking" = no ; then test "$enable_shared" = yes && enable_static=no fi ;; esac AC_MSG_RESULT([$enable_shared]) AC_MSG_CHECKING([whether to build static libraries]) # Make sure either enable_shared or enable_static is yes. test "$enable_shared" = yes || enable_static=yes AC_MSG_RESULT([$enable_static]) _LT_TAGVAR(GCC, $1)="$ac_cv_fc_compiler_gnu" _LT_TAGVAR(LD, $1)="$LD" ## CAVEAT EMPTOR: ## There is no encapsulation within the following macros, do not change ## the running order or otherwise move them around unless you know exactly ## what you are doing... _LT_SYS_HIDDEN_LIBDEPS($1) _LT_COMPILER_PIC($1) _LT_COMPILER_C_O($1) _LT_COMPILER_FILE_LOCKS($1) _LT_LINKER_SHLIBS($1) _LT_SYS_DYNAMIC_LINKER($1) _LT_LINKER_HARDCODE_LIBPATH($1) _LT_CONFIG($1) fi # test -n "$compiler" GCC=$lt_save_GCC CC=$lt_save_CC CFLAGS=$lt_save_CFLAGS fi # test "$_lt_disable_FC" != yes AC_LANG_POP ])# _LT_LANG_FC_CONFIG # _LT_LANG_GCJ_CONFIG([TAG]) # -------------------------- # Ensure that the configuration variables for the GNU Java Compiler compiler # are suitably defined. These variables are subsequently used by _LT_CONFIG # to write the compiler configuration to `libtool'. m4_defun([_LT_LANG_GCJ_CONFIG], [AC_REQUIRE([LT_PROG_GCJ])dnl AC_LANG_SAVE # Source file extension for Java test sources. ac_ext=java # Object file extension for compiled Java test sources. objext=o _LT_TAGVAR(objext, $1)=$objext # Code to be used in simple compile tests lt_simple_compile_test_code="class foo {}" # Code to be used in simple link tests lt_simple_link_test_code='public class conftest { public static void main(String[[]] argv) {}; }' # ltmain only uses $CC for tagged configurations so make sure $CC is set. _LT_TAG_COMPILER # save warnings/boilerplate of simple test code _LT_COMPILER_BOILERPLATE _LT_LINKER_BOILERPLATE # Allow CC to be a program name with arguments. lt_save_CC=$CC lt_save_CFLAGS=$CFLAGS lt_save_GCC=$GCC GCC=yes CC=${GCJ-"gcj"} CFLAGS=$GCJFLAGS compiler=$CC _LT_TAGVAR(compiler, $1)=$CC _LT_TAGVAR(LD, $1)="$LD" _LT_CC_BASENAME([$compiler]) # GCJ did not exist at the time GCC didn't implicitly link libc in. _LT_TAGVAR(archive_cmds_need_lc, $1)=no _LT_TAGVAR(old_archive_cmds, $1)=$old_archive_cmds _LT_TAGVAR(reload_flag, $1)=$reload_flag _LT_TAGVAR(reload_cmds, $1)=$reload_cmds ## CAVEAT EMPTOR: ## There is no encapsulation within the following macros, do not change ## the running order or otherwise move them around unless you know exactly ## what you are doing... if test -n "$compiler"; then _LT_COMPILER_NO_RTTI($1) _LT_COMPILER_PIC($1) _LT_COMPILER_C_O($1) _LT_COMPILER_FILE_LOCKS($1) _LT_LINKER_SHLIBS($1) _LT_LINKER_HARDCODE_LIBPATH($1) _LT_CONFIG($1) fi AC_LANG_RESTORE GCC=$lt_save_GCC CC=$lt_save_CC CFLAGS=$lt_save_CFLAGS ])# _LT_LANG_GCJ_CONFIG # _LT_LANG_GO_CONFIG([TAG]) # -------------------------- # Ensure that the configuration variables for the GNU Go compiler # are suitably defined. These variables are subsequently used by _LT_CONFIG # to write the compiler configuration to `libtool'. m4_defun([_LT_LANG_GO_CONFIG], [AC_REQUIRE([LT_PROG_GO])dnl AC_LANG_SAVE # Source file extension for Go test sources. ac_ext=go # Object file extension for compiled Go test sources. objext=o _LT_TAGVAR(objext, $1)=$objext # Code to be used in simple compile tests lt_simple_compile_test_code="package main; func main() { }" # Code to be used in simple link tests lt_simple_link_test_code='package main; func main() { }' # ltmain only uses $CC for tagged configurations so make sure $CC is set. _LT_TAG_COMPILER # save warnings/boilerplate of simple test code _LT_COMPILER_BOILERPLATE _LT_LINKER_BOILERPLATE # Allow CC to be a program name with arguments. lt_save_CC=$CC lt_save_CFLAGS=$CFLAGS lt_save_GCC=$GCC GCC=yes CC=${GOC-"gccgo"} CFLAGS=$GOFLAGS compiler=$CC _LT_TAGVAR(compiler, $1)=$CC _LT_TAGVAR(LD, $1)="$LD" _LT_CC_BASENAME([$compiler]) # Go did not exist at the time GCC didn't implicitly link libc in. _LT_TAGVAR(archive_cmds_need_lc, $1)=no _LT_TAGVAR(old_archive_cmds, $1)=$old_archive_cmds _LT_TAGVAR(reload_flag, $1)=$reload_flag _LT_TAGVAR(reload_cmds, $1)=$reload_cmds ## CAVEAT EMPTOR: ## There is no encapsulation within the following macros, do not change ## the running order or otherwise move them around unless you know exactly ## what you are doing... if test -n "$compiler"; then _LT_COMPILER_NO_RTTI($1) _LT_COMPILER_PIC($1) _LT_COMPILER_C_O($1) _LT_COMPILER_FILE_LOCKS($1) _LT_LINKER_SHLIBS($1) _LT_LINKER_HARDCODE_LIBPATH($1) _LT_CONFIG($1) fi AC_LANG_RESTORE GCC=$lt_save_GCC CC=$lt_save_CC CFLAGS=$lt_save_CFLAGS ])# _LT_LANG_GO_CONFIG # _LT_LANG_RC_CONFIG([TAG]) # ------------------------- # Ensure that the configuration variables for the Windows resource compiler # are suitably defined. These variables are subsequently used by _LT_CONFIG # to write the compiler configuration to `libtool'. m4_defun([_LT_LANG_RC_CONFIG], [AC_REQUIRE([LT_PROG_RC])dnl AC_LANG_SAVE # Source file extension for RC test sources. ac_ext=rc # Object file extension for compiled RC test sources. objext=o _LT_TAGVAR(objext, $1)=$objext # Code to be used in simple compile tests lt_simple_compile_test_code='sample MENU { MENUITEM "&Soup", 100, CHECKED }' # Code to be used in simple link tests lt_simple_link_test_code="$lt_simple_compile_test_code" # ltmain only uses $CC for tagged configurations so make sure $CC is set. _LT_TAG_COMPILER # save warnings/boilerplate of simple test code _LT_COMPILER_BOILERPLATE _LT_LINKER_BOILERPLATE # Allow CC to be a program name with arguments. lt_save_CC="$CC" lt_save_CFLAGS=$CFLAGS lt_save_GCC=$GCC GCC= CC=${RC-"windres"} CFLAGS= compiler=$CC _LT_TAGVAR(compiler, $1)=$CC _LT_CC_BASENAME([$compiler]) _LT_TAGVAR(lt_cv_prog_compiler_c_o, $1)=yes if test -n "$compiler"; then : _LT_CONFIG($1) fi GCC=$lt_save_GCC AC_LANG_RESTORE CC=$lt_save_CC CFLAGS=$lt_save_CFLAGS ])# _LT_LANG_RC_CONFIG # LT_PROG_GCJ # ----------- AC_DEFUN([LT_PROG_GCJ], [m4_ifdef([AC_PROG_GCJ], [AC_PROG_GCJ], [m4_ifdef([A][M_PROG_GCJ], [A][M_PROG_GCJ], [AC_CHECK_TOOL(GCJ, gcj,) test "x${GCJFLAGS+set}" = xset || GCJFLAGS="-g -O2" AC_SUBST(GCJFLAGS)])])[]dnl ]) # Old name: AU_ALIAS([LT_AC_PROG_GCJ], [LT_PROG_GCJ]) dnl aclocal-1.4 backwards compatibility: dnl AC_DEFUN([LT_AC_PROG_GCJ], []) # LT_PROG_GO # ---------- AC_DEFUN([LT_PROG_GO], [AC_CHECK_TOOL(GOC, gccgo,) ]) # LT_PROG_RC # ---------- AC_DEFUN([LT_PROG_RC], [AC_CHECK_TOOL(RC, windres,) ]) # Old name: AU_ALIAS([LT_AC_PROG_RC], [LT_PROG_RC]) dnl aclocal-1.4 backwards compatibility: dnl AC_DEFUN([LT_AC_PROG_RC], []) # _LT_DECL_EGREP # -------------- # If we don't have a new enough Autoconf to choose the best grep # available, choose the one first in the user's PATH. m4_defun([_LT_DECL_EGREP], [AC_REQUIRE([AC_PROG_EGREP])dnl AC_REQUIRE([AC_PROG_FGREP])dnl test -z "$GREP" && GREP=grep _LT_DECL([], [GREP], [1], [A grep program that handles long lines]) _LT_DECL([], [EGREP], [1], [An ERE matcher]) _LT_DECL([], [FGREP], [1], [A literal string matcher]) dnl Non-bleeding-edge autoconf doesn't subst GREP, so do it here too AC_SUBST([GREP]) ]) # _LT_DECL_OBJDUMP # -------------- # If we don't have a new enough Autoconf to choose the best objdump # available, choose the one first in the user's PATH. m4_defun([_LT_DECL_OBJDUMP], [AC_CHECK_TOOL(OBJDUMP, objdump, false) test -z "$OBJDUMP" && OBJDUMP=objdump _LT_DECL([], [OBJDUMP], [1], [An object symbol dumper]) AC_SUBST([OBJDUMP]) ]) # _LT_DECL_DLLTOOL # ---------------- # Ensure DLLTOOL variable is set. m4_defun([_LT_DECL_DLLTOOL], [AC_CHECK_TOOL(DLLTOOL, dlltool, false) test -z "$DLLTOOL" && DLLTOOL=dlltool _LT_DECL([], [DLLTOOL], [1], [DLL creation program]) AC_SUBST([DLLTOOL]) ]) # _LT_DECL_SED # ------------ # Check for a fully-functional sed program, that truncates # as few characters as possible. Prefer GNU sed if found. m4_defun([_LT_DECL_SED], [AC_PROG_SED test -z "$SED" && SED=sed Xsed="$SED -e 1s/^X//" _LT_DECL([], [SED], [1], [A sed program that does not truncate output]) _LT_DECL([], [Xsed], ["\$SED -e 1s/^X//"], [Sed that helps us avoid accidentally triggering echo(1) options like -n]) ])# _LT_DECL_SED m4_ifndef([AC_PROG_SED], [ ############################################################ # NOTE: This macro has been submitted for inclusion into # # GNU Autoconf as AC_PROG_SED. When it is available in # # a released version of Autoconf we should remove this # # macro and use it instead. # ############################################################ m4_defun([AC_PROG_SED], [AC_MSG_CHECKING([for a sed that does not truncate output]) AC_CACHE_VAL(lt_cv_path_SED, [# Loop through the user's path and test for sed and gsed. # Then use that list of sed's as ones to test for truncation. as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for lt_ac_prog in sed gsed; do for ac_exec_ext in '' $ac_executable_extensions; do if $as_executable_p "$as_dir/$lt_ac_prog$ac_exec_ext"; then lt_ac_sed_list="$lt_ac_sed_list $as_dir/$lt_ac_prog$ac_exec_ext" fi done done done IFS=$as_save_IFS lt_ac_max=0 lt_ac_count=0 # Add /usr/xpg4/bin/sed as it is typically found on Solaris # along with /bin/sed that truncates output. for lt_ac_sed in $lt_ac_sed_list /usr/xpg4/bin/sed; do test ! -f $lt_ac_sed && continue cat /dev/null > conftest.in lt_ac_count=0 echo $ECHO_N "0123456789$ECHO_C" >conftest.in # Check for GNU sed and select it if it is found. if "$lt_ac_sed" --version 2>&1 < /dev/null | grep 'GNU' > /dev/null; then lt_cv_path_SED=$lt_ac_sed break fi while true; do cat conftest.in conftest.in >conftest.tmp mv conftest.tmp conftest.in cp conftest.in conftest.nl echo >>conftest.nl $lt_ac_sed -e 's/a$//' < conftest.nl >conftest.out || break cmp -s conftest.out conftest.nl || break # 10000 chars as input seems more than enough test $lt_ac_count -gt 10 && break lt_ac_count=`expr $lt_ac_count + 1` if test $lt_ac_count -gt $lt_ac_max; then lt_ac_max=$lt_ac_count lt_cv_path_SED=$lt_ac_sed fi done done ]) SED=$lt_cv_path_SED AC_SUBST([SED]) AC_MSG_RESULT([$SED]) ])#AC_PROG_SED ])#m4_ifndef # Old name: AU_ALIAS([LT_AC_PROG_SED], [AC_PROG_SED]) dnl aclocal-1.4 backwards compatibility: dnl AC_DEFUN([LT_AC_PROG_SED], []) # _LT_CHECK_SHELL_FEATURES # ------------------------ # Find out whether the shell is Bourne or XSI compatible, # or has some other useful features. m4_defun([_LT_CHECK_SHELL_FEATURES], [AC_MSG_CHECKING([whether the shell understands some XSI constructs]) # Try some XSI features xsi_shell=no ( _lt_dummy="a/b/c" test "${_lt_dummy##*/},${_lt_dummy%/*},${_lt_dummy#??}"${_lt_dummy%"$_lt_dummy"}, \ = c,a/b,b/c, \ && eval 'test $(( 1 + 1 )) -eq 2 \ && test "${#_lt_dummy}" -eq 5' ) >/dev/null 2>&1 \ && xsi_shell=yes AC_MSG_RESULT([$xsi_shell]) _LT_CONFIG_LIBTOOL_INIT([xsi_shell='$xsi_shell']) AC_MSG_CHECKING([whether the shell understands "+="]) lt_shell_append=no ( foo=bar; set foo baz; eval "$[1]+=\$[2]" && test "$foo" = barbaz ) \ >/dev/null 2>&1 \ && lt_shell_append=yes AC_MSG_RESULT([$lt_shell_append]) _LT_CONFIG_LIBTOOL_INIT([lt_shell_append='$lt_shell_append']) if ( (MAIL=60; unset MAIL) || exit) >/dev/null 2>&1; then lt_unset=unset else lt_unset=false fi _LT_DECL([], [lt_unset], [0], [whether the shell understands "unset"])dnl # test EBCDIC or ASCII case `echo X|tr X '\101'` in A) # ASCII based system # \n is not interpreted correctly by Solaris 8 /usr/ucb/tr lt_SP2NL='tr \040 \012' lt_NL2SP='tr \015\012 \040\040' ;; *) # EBCDIC based system lt_SP2NL='tr \100 \n' lt_NL2SP='tr \r\n \100\100' ;; esac _LT_DECL([SP2NL], [lt_SP2NL], [1], [turn spaces into newlines])dnl _LT_DECL([NL2SP], [lt_NL2SP], [1], [turn newlines into spaces])dnl ])# _LT_CHECK_SHELL_FEATURES # _LT_PROG_FUNCTION_REPLACE (FUNCNAME, REPLACEMENT-BODY) # ------------------------------------------------------ # In `$cfgfile', look for function FUNCNAME delimited by `^FUNCNAME ()$' and # '^} FUNCNAME ', and replace its body with REPLACEMENT-BODY. m4_defun([_LT_PROG_FUNCTION_REPLACE], [dnl { sed -e '/^$1 ()$/,/^} # $1 /c\ $1 ()\ {\ m4_bpatsubsts([$2], [$], [\\], [^\([ ]\)], [\\\1]) } # Extended-shell $1 implementation' "$cfgfile" > $cfgfile.tmp \ && mv -f "$cfgfile.tmp" "$cfgfile" \ || (rm -f "$cfgfile" && cp "$cfgfile.tmp" "$cfgfile" && rm -f "$cfgfile.tmp") test 0 -eq $? || _lt_function_replace_fail=: ]) # _LT_PROG_REPLACE_SHELLFNS # ------------------------- # Replace existing portable implementations of several shell functions with # equivalent extended shell implementations where those features are available.. m4_defun([_LT_PROG_REPLACE_SHELLFNS], [if test x"$xsi_shell" = xyes; then _LT_PROG_FUNCTION_REPLACE([func_dirname], [dnl case ${1} in */*) func_dirname_result="${1%/*}${2}" ;; * ) func_dirname_result="${3}" ;; esac]) _LT_PROG_FUNCTION_REPLACE([func_basename], [dnl func_basename_result="${1##*/}"]) _LT_PROG_FUNCTION_REPLACE([func_dirname_and_basename], [dnl case ${1} in */*) func_dirname_result="${1%/*}${2}" ;; * ) func_dirname_result="${3}" ;; esac func_basename_result="${1##*/}"]) _LT_PROG_FUNCTION_REPLACE([func_stripname], [dnl # pdksh 5.2.14 does not do ${X%$Y} correctly if both X and Y are # positional parameters, so assign one to ordinary parameter first. func_stripname_result=${3} func_stripname_result=${func_stripname_result#"${1}"} func_stripname_result=${func_stripname_result%"${2}"}]) _LT_PROG_FUNCTION_REPLACE([func_split_long_opt], [dnl func_split_long_opt_name=${1%%=*} func_split_long_opt_arg=${1#*=}]) _LT_PROG_FUNCTION_REPLACE([func_split_short_opt], [dnl func_split_short_opt_arg=${1#??} func_split_short_opt_name=${1%"$func_split_short_opt_arg"}]) _LT_PROG_FUNCTION_REPLACE([func_lo2o], [dnl case ${1} in *.lo) func_lo2o_result=${1%.lo}.${objext} ;; *) func_lo2o_result=${1} ;; esac]) _LT_PROG_FUNCTION_REPLACE([func_xform], [ func_xform_result=${1%.*}.lo]) _LT_PROG_FUNCTION_REPLACE([func_arith], [ func_arith_result=$(( $[*] ))]) _LT_PROG_FUNCTION_REPLACE([func_len], [ func_len_result=${#1}]) fi if test x"$lt_shell_append" = xyes; then _LT_PROG_FUNCTION_REPLACE([func_append], [ eval "${1}+=\\${2}"]) _LT_PROG_FUNCTION_REPLACE([func_append_quoted], [dnl func_quote_for_eval "${2}" dnl m4 expansion turns \\\\ into \\, and then the shell eval turns that into \ eval "${1}+=\\\\ \\$func_quote_for_eval_result"]) # Save a `func_append' function call where possible by direct use of '+=' sed -e 's%func_append \([[a-zA-Z_]]\{1,\}\) "%\1+="%g' $cfgfile > $cfgfile.tmp \ && mv -f "$cfgfile.tmp" "$cfgfile" \ || (rm -f "$cfgfile" && cp "$cfgfile.tmp" "$cfgfile" && rm -f "$cfgfile.tmp") test 0 -eq $? || _lt_function_replace_fail=: else # Save a `func_append' function call even when '+=' is not available sed -e 's%func_append \([[a-zA-Z_]]\{1,\}\) "%\1="$\1%g' $cfgfile > $cfgfile.tmp \ && mv -f "$cfgfile.tmp" "$cfgfile" \ || (rm -f "$cfgfile" && cp "$cfgfile.tmp" "$cfgfile" && rm -f "$cfgfile.tmp") test 0 -eq $? || _lt_function_replace_fail=: fi if test x"$_lt_function_replace_fail" = x":"; then AC_MSG_WARN([Unable to substitute extended shell functions in $ofile]) fi ]) # _LT_PATH_CONVERSION_FUNCTIONS # ----------------------------- # Determine which file name conversion functions should be used by # func_to_host_file (and, implicitly, by func_to_host_path). These are needed # for certain cross-compile configurations and native mingw. m4_defun([_LT_PATH_CONVERSION_FUNCTIONS], [AC_REQUIRE([AC_CANONICAL_HOST])dnl AC_REQUIRE([AC_CANONICAL_BUILD])dnl AC_MSG_CHECKING([how to convert $build file names to $host format]) AC_CACHE_VAL(lt_cv_to_host_file_cmd, [case $host in *-*-mingw* ) case $build in *-*-mingw* ) # actually msys lt_cv_to_host_file_cmd=func_convert_file_msys_to_w32 ;; *-*-cygwin* ) lt_cv_to_host_file_cmd=func_convert_file_cygwin_to_w32 ;; * ) # otherwise, assume *nix lt_cv_to_host_file_cmd=func_convert_file_nix_to_w32 ;; esac ;; *-*-cygwin* ) case $build in *-*-mingw* ) # actually msys lt_cv_to_host_file_cmd=func_convert_file_msys_to_cygwin ;; *-*-cygwin* ) lt_cv_to_host_file_cmd=func_convert_file_noop ;; * ) # otherwise, assume *nix lt_cv_to_host_file_cmd=func_convert_file_nix_to_cygwin ;; esac ;; * ) # unhandled hosts (and "normal" native builds) lt_cv_to_host_file_cmd=func_convert_file_noop ;; esac ]) to_host_file_cmd=$lt_cv_to_host_file_cmd AC_MSG_RESULT([$lt_cv_to_host_file_cmd]) _LT_DECL([to_host_file_cmd], [lt_cv_to_host_file_cmd], [0], [convert $build file names to $host format])dnl AC_MSG_CHECKING([how to convert $build file names to toolchain format]) AC_CACHE_VAL(lt_cv_to_tool_file_cmd, [#assume ordinary cross tools, or native build. lt_cv_to_tool_file_cmd=func_convert_file_noop case $host in *-*-mingw* ) case $build in *-*-mingw* ) # actually msys lt_cv_to_tool_file_cmd=func_convert_file_msys_to_w32 ;; esac ;; esac ]) to_tool_file_cmd=$lt_cv_to_tool_file_cmd AC_MSG_RESULT([$lt_cv_to_tool_file_cmd]) _LT_DECL([to_tool_file_cmd], [lt_cv_to_tool_file_cmd], [0], [convert $build files to toolchain format])dnl ])# _LT_PATH_CONVERSION_FUNCTIONS smalltalk-3.2.5/build-aux/sigaltstack-siglongjmp.m40000644000175000017500000000535712123404352017250 00000000000000# sigaltstack-siglongjmp.m4 serial 3 (libsigsegv-2.4) dnl Copyright (C) 2002-2003, 2006 Bruno Haible dnl This file is free software, distributed under the terms of the GNU dnl General Public License. As a special exception to the GNU General dnl Public License, this file may be distributed as part of a program dnl that contains a configuration script generated by Autoconf, under dnl the same distribution terms as the rest of that program. dnl How to siglongjmp out of a signal handler, in such a way that the dnl alternate signal stack remains functional. dnl SV_TRY_LEAVE_HANDLER_SIGLONGJMP(KIND, CACHESYMBOL, KNOWN-SYSTEMS, dnl INCLUDES, RESETCODE) AC_DEFUN([SV_TRY_LEAVE_HANDLER_SIGLONGJMP], [ AC_REQUIRE([AC_PROG_CC]) AC_REQUIRE([AC_CANONICAL_HOST]) AC_CACHE_CHECK([whether a signal handler can be left through siglongjmp$1], [$2], [ AC_RUN_IFELSE([ AC_LANG_SOURCE([[ #include #include #include $4 #if HAVE_SETRLIMIT # include # include # include #endif sigjmp_buf mainloop; int pass = 0; void stackoverflow_handler (int sig) { pass++; { $5 } siglongjmp (mainloop, pass); } volatile int * recurse_1 (volatile int n, volatile int *p) { if (n >= 0) *recurse_1 (n + 1, p) += n; return p; } volatile int recurse (volatile int n) { int sum = 0; return *recurse_1 (n, &sum); } char mystack[16384]; int main () { stack_t altstack; struct sigaction action; #ifdef __BEOS__ /* On BeOS, this would hang, burning CPU time. Better fail than hang. */ exit (1); #endif #if defined HAVE_SETRLIMIT && defined RLIMIT_STACK /* Before starting the endless recursion, try to be friendly to the user's machine. On some Linux 2.2.x systems, there is no stack limit for user processes at all. We don't want to kill such systems. */ struct rlimit rl; rl.rlim_cur = rl.rlim_max = 0x100000; /* 1 MB */ setrlimit (RLIMIT_STACK, &rl); #endif /* Install the alternate stack. */ altstack.ss_sp = mystack; altstack.ss_size = sizeof (mystack); altstack.ss_flags = 0; /* no SS_DISABLE */ if (sigaltstack (&altstack, NULL) < 0) exit (1); /* Install the SIGSEGV handler. */ sigemptyset (&action.sa_mask); action.sa_handler = &stackoverflow_handler; action.sa_flags = SA_ONSTACK; sigaction (SIGSEGV, &action, (struct sigaction *) NULL); sigaction (SIGBUS, &action, (struct sigaction *) NULL); /* Provoke two stack overflows in a row. */ if (sigsetjmp (mainloop, 1) < 2) { recurse (0); exit (2); } exit (0); }]])], [$2=yes], [$2=no], [case "$host" in m4_if([$3], [], [], [[$3]) $2=yes ;;]) *) $2="guessing no" ;; esac ]) ]) ]) smalltalk-3.2.5/build-aux/ext_goto.m40000644000175000017500000000067612123404352014417 00000000000000dnl I'd like this to be edited in -*- Autoconf -*- mode... dnl AC_DEFUN([GST_C_GOTO_VOID_P], [ AC_CACHE_CHECK(for goto void *, gst_cv_c_goto_void_p, [AC_COMPILE_IFELSE([AC_LANG_PROGRAM([[]], [[ void *x = &&label; goto *x; label: ]])],gst_cv_c_goto_void_p=yes,gst_cv_c_goto_void_p=no) ]) test $gst_cv_c_goto_void_p = yes && \ AC_DEFINE(HAVE_GOTO_VOID_P, 1, [Define if your CC has the '&&' and 'goto void *' GCC extensions.]) ])dnl smalltalk-3.2.5/build-aux/gcc.m40000644000175000017500000000706212123404352013317 00000000000000dnl I'd like this to be edited in -*- Autoconf -*- mode... dnl dnl Calls several commonly used macros; also provides support for dnl selectively enabling or disabling optimizations and warnings dnl AC_DEFUN([GST_PROG_CC], [ AC_REQUIRE([AC_PROG_CC]) AC_REQUIRE([AC_PROG_CPP]) AC_REQUIRE([AC_USE_SYSTEM_EXTENSIONS]) AC_ARG_ENABLE(warnings, [ --enable-warnings enable compiler warnings (default=no)], , enable_warnings=no) AC_CACHE_CHECK([whether $CFLAGS produces any warnings], ac_cv_prog_cc_warnings, [ac_save_c_werror_flag=$ac_c_werror_flag ac_c_werror_flag=yes ac_cv_prog_cc_warnings=no _AC_COMPILE_IFELSE([AC_LANG_PROGRAM()], [ac_cv_prog_cc_warnings=no], [ac_cv_prog_cc_warnings=yes]) ac_c_werror_flag=$ac_save_c_werror_flag]) if test $ac_cv_prog_cc_warnings = yes; then AC_MSG_WARN([$CC $CFLAGS produced warnings. This usually means]) AC_MSG_WARN([that $CFLAGS is incorrect, and could cause problems]) AC_MSG_WARN([in the rest of the configure script.]) fi if test "$GCC" = yes; then ifelse([$1$2$3$4$5], , , [dnl changequote(<<, >>) case "`$CC --version 2>&1`" in # This assumes egcs 1.1.2 *gcc-2.9[0-4]*) gcc_help="echo -fbranch-probabilities \ -foptimize-register-moves -fcaller-saves -fcse-follow-jumps \ -fcse-skip-blocks -fdelayed-branch -fexpensive-optimizations \ -ffast-math -ffloat-store -fforce-addr -fforce-mem \ -ffunction-sections -fgcse -finline-functions \ -fkeep-inline-functions -fdefault-inline -fdefer-pop \ -ffunction-cse -finline -fpeephole -fomit-frame-pointer \ -fregmove -frerun-cse-after-loop -frerun-loop-opt -fschedule-insns \ -fschedule-insns2 -fstrength-reduce -fthread-jumps \ -funroll-all-loops -funroll-loops -fmove-all-movables \ -freduce-all-givs -fstrict-aliasing -fstructure-noalias " ;; # This assumes GCC 2.7 *gcc-2.[0-8]*) gcc_help="echo -ffloat-store -fdefault-inline -fdefer-pop \ -fforce-mem -fforce-addr -fomit-frame-pointer -finline \ -finline-functions -fkeep-inline-functions -ffunction-cse -ffast-math \ -fstrength-reduce -fthread-jumps -fcse-follow-jumps \ -fcse-skip-blocks -frerun-cse-after-loop -fexpensive-optimizations \ -fdelayed-branch -fschedule-insns -fschedule-insns2 \ -fcaller-saves -funroll-loops -funroll-all-loops -fpeephole " ;; # For GCC 2.95 and later, we have help available *) gcc_help="$CC -v --help" ;; esac changequote([, ]) # Build a sed command line that changes the help set dummy -e h ifelse([$1], , , [ for i in $1; do set "[$]@" -e g -e ["s/.*-f\($i\)[ ].*/-f\1 /p"] done ])dnl ifelse([$2], , , [ for i in $2; do set "[$]@" -e g -e ["s/.*-f\($i\)[ ].*/-fno-\1 /p"] done ])dnl ])dnl wall=: wextra=: ifelse([$3], , , [ for i in $3; do case $i in all) wall=false; CFLAGS="$CFLAGS -Wall" ;; extra) wextra=false; set "[$]@" -e g -e ["s/-W[ ]/-W /p" -e g -e "s/-Wextra[ ]/-Wextra /p" ;;] *) set "[$]@" -e g -e ["s/.*-W\($i\)[ ].*/-W\1 /p" ;;] esac done ])dnl ifelse([$4], , , [ for i in $4; do case $i in all) wall= ;; extra) wextra=false ;; *) set "[$]@" -e g -e ["s/.*-W\($i\)[ ].*/-Wno-\1 /p" ;;] esac done ])dnl if test "$enable_warnings" != no; then $wall && CFLAGS="$CFLAGS -Wall" $wextra && set "[$]@" -e g -e ["s/-W[ ]/-W /p" -e g -e "s/-Wextra[ ]/-Wextra /p" ] ifelse([$5], , , [ for i in $5; do set "[$]@" -e g -e ["s/.*-W\($i\)[ ].*/-W\1 /p"] done ])dnl fi set "[$]@" -e d shift CFLAGS="$CFLAGS `$gcc_help 2>&1 | sed "[$]@" | sed -e H -e '$!d' -e g -e 's/\n//g'`" fi ])dnl smalltalk-3.2.5/build-aux/codeset.m40000644000175000017500000000162412123404352014207 00000000000000# codeset.m4 serial AM1 (gettext-0.10.40) dnl Copyright (C) 2000-2002 Free Software Foundation, Inc. dnl This file is free software, distributed under the terms of the GNU dnl General Public License. As a special exception to the GNU General dnl Public License, this file may be distributed as part of a program dnl that contains a configuration script generated by Autoconf, under dnl the same distribution terms as the rest of that program. dnl From Bruno Haible. AC_DEFUN([AM_LANGINFO_CODESET], [ AC_CACHE_CHECK([for nl_langinfo and CODESET], am_cv_langinfo_codeset, [AC_LINK_IFELSE([AC_LANG_PROGRAM([[#include ]], [[char* cs = nl_langinfo(CODESET);]])], am_cv_langinfo_codeset=yes,am_cv_langinfo_codeset=no) ]) if test $am_cv_langinfo_codeset = yes; then AC_DEFINE(HAVE_LANGINFO_CODESET, 1, [Define if you have and nl_langinfo(CODESET).]) fi ]) smalltalk-3.2.5/build-aux/gst.m40000644000175000017500000000311412123404352013352 00000000000000dnl I'd like this to be edited in -*- Autoconf -*- mode... dnl dnl AM_PATH_GST(MIN-REQ-VERSION, [ACTION-IF-FOUND [, ACTION-IF-NOT-FOUND]]) dnl AC_DEFUN([AM_PATH_GST],[ dnl Various autoconf user options AC_ARG_WITH(gst, AS_HELP_STRING([--with-gst=PFX], [Prefix where GNU Smalltalk is installed]), gst_prefix="$withval", gst_prefix="") gst_old_PKG_CONFIG_PATH_set=${PKG_CONFIG_PATH+set} gst_old_PKG_CONFIG_PATH=${PKG_CONFIG_PATH} if test x$gst_prefix != x; then : ${GST="$gst_prefix/bin/gst"} : ${GST_CONFIG="$gst_prefix/bin/gst-config"} : ${GST_PACKAGE="$gst_prefix/bin/gst-package"} gst_config_path=$gst_prefix/lib/pkgconfig PKG_CONFIG_PATH=$gst_config_path${PKG_CONFIG_PATH+:$PKG_CONFIG_PATH} export PKG_CONFIG_PATH fi PKG_PROG_PKG_CONFIG([0.7]) AC_PATH_PROG([GST], [gst], no) AC_PATH_PROG([GST_CONFIG], [gst-config], no) AC_PATH_PROG([GST_PACKAGE], [gst-package], no) export PKG_CONFIG_PATH PKG_CHECK_MODULES(GST, [gnu-smalltalk[]m4_if([$1],[],[],[ >= $1])], [gstlibdir=`$PKG_CONFIG --variable=libdir gnu-smalltalk` gstdatadir=`$PKG_CONFIG --variable=pkgdatadir gnu-smalltalk` gstmoduledir=`$PKG_CONFIG --variable=moduledir gnu-smalltalk` gstmoduleexecdir='${gstmoduledir}' have_gst=yes], [have_gst=no]) PKG_CONFIG_PATH=$gst_old_PKG_CONFIG_PATH export PKG_CONFIG_PATH test x$gst_old_PKG_CONFIG_PATH_set = xset || unset PKG_CONFIG_PATH AS_IF([test $have_gst = yes], [$2], [$3]) AC_SUBST(gstlibdir) AC_SUBST(gstdatadir) AC_SUBST(gstmoduledir) AC_SUBST(gstmoduleexecdir) ]) smalltalk-3.2.5/build-aux/modules.m40000644000175000017500000000056012123404352014227 00000000000000dnl I'd like this to be edited in -*- Autoconf -*- mode... dnl AC_DEFUN([GST_ARG_ENABLE_MODULES], [ AC_ARG_ENABLE(modules, [ --enable-modules=list add these packages to the pre-built image]) test "$enable_modules" = "yes" && enable_modules="$1" test "$enable_modules" = "no" && enable_modules= MODULES=`echo $enable_modules | sed "s/,/ /g"` AC_SUBST(MODULES) ]) smalltalk-3.2.5/build-aux/bold.m40000644000175000017500000000430612123404352013501 00000000000000# bold.m4 serial 1 (libsigsegv-2.0) dnl Copyright (C) 1999-2002 Ralf S. Engelschall dnl Copyright (C) 2002 Bruno Haible dnl This file is free software, distributed under the terms of the GNU dnl General Public License. As a special exception to the GNU General dnl Public License, this file may be distributed as part of a program dnl that contains a configuration script generated by Autoconf, under dnl the same distribution terms as the rest of that program. # Determine the escape sequences for switching bold output on and off. AC_DEFUN([RSE_BOLD], [ dnl Not pretty. dnl AC_REQUIRE([AC_PROG_AWK]) case $TERM in # for the most important terminal types we directly know the sequences xterm*|vt220*) term_bold=`${AWK:-awk} 'BEGIN { printf("%c%c%c%c", 27, 91, 49, 109); }' /dev/null` term_norm=`${AWK:-awk} 'BEGIN { printf("%c%c%c", 27, 91, 109); }' /dev/null` ;; vt100*) term_bold=`${AWK:-awk} 'BEGIN { printf("%c%c%c%c%c%c", 27, 91, 49, 109, 0, 0); }' /dev/null` term_norm=`${AWK:-awk} 'BEGIN { printf("%c%c%c%c%c", 27, 91, 109, 0, 0); }' /dev/null` ;; # for all others, we try to use a possibly existing `tput' or `tcout' utility *) paths=`echo "$PATH" | sed -e 's/:/ /g'` for tool in tput tcout; do for dir in $paths; do if test -r "$dir/$tool"; then for seq in bold md smso; do # 'smso' is last bold="`$dir/$tool $seq 2>/dev/null`" if test -n "$bold"; then term_bold="$bold" break fi done if test -n "$term_bold"; then for seq in sgr0 me rmso reset; do # 'reset' is last norm="`$dir/$tool $seq 2>/dev/null`" if test -n "$norm"; then term_norm="$norm" break fi done fi break fi done if test -n "$term_bold" && test -n "$term_norm"; then break fi done ;; esac echo "$term_bold" | tr -d '\n' > termbold echo "$term_norm" | tr -d '\n' > termnorm ]) smalltalk-3.2.5/build-aux/help2man0000755000175000017500000003057012123404352013755 00000000000000#!/usr/bin/env perl # Generate a short man page from --help and --version output. # Copyright (C) 1997, 1998, 1999, 2000, 2001, 2002 Free Software # Foundation, Inc. # This program is free software; you can redistribute it and/or modify # it under the terms of the GNU General Public License as published by # the Free Software Foundation; either version 2, or (at your option) # any later version. # This program is distributed in the hope that it will be useful, # but WITHOUT ANY WARRANTY; without even the implied warranty of # MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the # GNU General Public License for more details. # You should have received a copy of the GNU General Public License # along with this program; if not, write to the Free Software Foundation, # Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. # Written by Brendan O'Dea # Available from ftp://ftp.gnu.org/gnu/help2man/ use 5.005; use strict; use Getopt::Long; use Text::Tabs qw(expand); use POSIX qw(strftime setlocale LC_TIME); my $this_program = 'help2man'; my $this_version = '1.28'; my $version_info = < EOT my $help_info = <. EOT my $section = 1; my $manual = ''; my $source = ''; my $help_option = '--help'; my $version_option = '--version'; my ($opt_name, @opt_include, $opt_output, $opt_info, $opt_no_info); my %opt_def = ( 'n|name=s' => \$opt_name, 's|section=s' => \$section, 'm|manual=s' => \$manual, 'S|source=s' => \$source, 'i|include=s' => sub { push @opt_include, [ pop, 1 ] }, 'I|opt-include=s' => sub { push @opt_include, [ pop, 0 ] }, 'o|output=s' => \$opt_output, 'p|info-page=s' => \$opt_info, 'N|no-info' => \$opt_no_info, 'h|help-option=s' => \$help_option, 'v|version-option=s' => \$version_option, ); # Parse options. Getopt::Long::config('bundling'); GetOptions (%opt_def, help => sub { print $help_info; exit }, version => sub { print $version_info; exit }, ) or die $help_info; die $help_info unless @ARGV == 1; my %include = (); my %append = (); my @include = (); # retain order given in include file # Process include file (if given). Format is: # # [section name] # verbatim text # # or # # /pattern/ # verbatim text # while (@opt_include) { my ($inc, $required) = @{shift @opt_include}; next unless -f $inc or $required; die "$this_program: can't open `$inc' ($!)\n" unless open INC, $inc; my $key; my $hash = \%include; while () { # [section] if (/^\[([^]]+)\]/) { $key = uc $1; $key =~ s/^\s+//; $key =~ s/\s+$//; $hash = \%include; push @include, $key unless $include{$key}; next; } # /pattern/ if (m!^/(.*)/([ims]*)!) { my $pat = $2 ? "(?$2)$1" : $1; # Check pattern. eval { $key = qr($pat) }; if ($@) { $@ =~ s/ at .*? line \d.*//; die "$inc:$.:$@"; } $hash = \%append; next; } # Check for options before the first section--anything else is # silently ignored, allowing the first for comments and # revision info. unless ($key) { # handle options if (/^-/) { local @ARGV = split; GetOptions %opt_def; } next; } $hash->{$key} ||= ''; $hash->{$key} .= $_; } close INC; die "$this_program: no valid information found in `$inc'\n" unless $key; } # Compress trailing blank lines. for my $hash (\(%include, %append)) { for (keys %$hash) { $hash->{$_} =~ s/\n+$/\n/ } } # Turn off localisation of executable's ouput. @ENV{qw(LANGUAGE LANG LC_ALL)} = ('C') x 3; # Turn off localisation of date (for strftime). setlocale LC_TIME, 'C'; # Grab help and version info from executable. my ($help_text, $version_text) = map { join '', map { s/ +$//; expand $_ } `$ARGV[0] $_ 2>/dev/null` or die "$this_program: can't get `$_' info from $ARGV[0]\n" } $help_option, $version_option; my $date = strftime "%B %Y", localtime; (my $program = $ARGV[0]) =~ s!.*/!!; my $package = $program; my $version; if ($opt_output) { unlink $opt_output or die "$this_program: can't unlink $opt_output ($!)\n" if -e $opt_output; open STDOUT, ">$opt_output" or die "$this_program: can't create $opt_output ($!)\n"; } # The first line of the --version information is assumed to be in one # of the following formats: # # # # {GNU,Free} # ({GNU,Free} ) # - {GNU,Free} # # and seperated from any copyright/author details by a blank line. ($_, $version_text) = split /\n+/, $version_text, 2; if (/^(\S+) +\(((?:GNU|Free) +[^)]+)\) +(.*)/ or /^(\S+) +- *((?:GNU|Free) +\S+) +(.*)/) { $program = $1; $package = $2; $version = $3; } elsif (/^((?:GNU|Free) +)?(\S+) +(.*)/) { $program = $2; $package = $1 ? "$1$2" : $2; $version = $3; } else { $version = $_; } $program =~ s!.*/!!; # No info for `info' itself. $opt_no_info = 1 if $program eq 'info'; # --name overrides --include contents. $include{NAME} = "$program \\- $opt_name\n" if $opt_name; # Default (useless) NAME paragraph. $include{NAME} ||= "$program \\- manual page for $program $version\n"; # Man pages traditionally have the page title in caps. my $PROGRAM = uc $program; # Set default page head/footers $source ||= "$program $version"; unless ($manual) { for ($section) { if (/^(1[Mm]|8)/) { $manual = 'System Administration Utilities' } elsif (/^6/) { $manual = 'Games' } else { $manual = 'User Commands' } } } # Extract usage clause(s) [if any] for SYNOPSIS. if ($help_text =~ s/^Usage:( +(\S+))(.*)((?:\n(?: {6}\1| *or: +\S).*)*)//m) { my @syn = $2 . $3; if ($_ = $4) { s/^\n//; for (split /\n/) { s/^ *(or: +)?//; push @syn, $_ } } my $synopsis = ''; for (@syn) { $synopsis .= ".br\n" if $synopsis; s!^\S*/!!; s/^(\S+) *//; $synopsis .= ".B $1\n"; s/\s+$//; s/(([][]|\.\.+)+)/\\fR$1\\fI/g; s/^/\\fI/ unless s/^\\fR//; $_ .= '\fR'; s/(\\fI)( *)/$2$1/g; s/\\fI\\fR//g; s/^\\fR//; s/\\fI$//; s/^\./\\&./; $synopsis .= "$_\n"; } $include{SYNOPSIS} ||= $synopsis; } # Process text, initial section is DESCRIPTION. my $sect = 'DESCRIPTION'; $_ = "$help_text\n\n$version_text"; # Normalise paragraph breaks. s/^\n+//; s/\n*$/\n/; s/\n\n+/\n\n/g; # Temporarily exchange leading dots, apostrophes and backslashes for # tokens. s/^\./\x80/mg; s/^'/\x81/mg; s/\\/\x82/g; # Start a new paragraph (if required) for these. s/([^\n])\n(Report +bugs|Email +bug +reports +to|Written +by)/$1\n\n$2/g; sub convert_option; while (length) { # Convert some standard paragraph names. if (s/^(Options|Examples): *\n//) { $sect = uc $1; next; } # Copyright section if (/^Copyright +[(\xa9]/) { $sect = 'COPYRIGHT'; $include{$sect} ||= ''; $include{$sect} .= ".PP\n" if $include{$sect}; my $copy; ($copy, $_) = split /\n\n/, $_, 2; for ($copy) { # Add back newline s/\n*$/\n/; # Convert iso9959-1 copyright symbol or (c) to nroff # character. s/^Copyright +(?:\xa9|\([Cc]\))/Copyright \\(co/mg; # Insert line breaks before additional copyright messages # and the disclaimer. s/(.)\n(Copyright |This +is +free +software)/$1\n.br\n$2/g; # Join hyphenated lines. s/([A-Za-z])-\n */$1/g; } $include{$sect} .= $copy; $_ ||= ''; next; } # Catch bug report text. if (/^(Report +bugs|Email +bug +reports +to) /) { $sect = 'REPORTING BUGS'; } # Author section. elsif (/^Written +by/) { $sect = 'AUTHOR'; } # Examples, indicated by an indented leading $, % or > are # rendered in a constant width font. if (/^( +)([\$\%>] )\S/) { my $indent = $1; my $prefix = $2; my $break = '.IP'; $include{$sect} ||= ''; while (s/^$indent\Q$prefix\E(\S.*)\n*//) { $include{$sect} .= "$break\n\\f(CW$prefix$1\\fR\n"; $break = '.br'; } next; } my $matched = ''; $include{$sect} ||= ''; # Sub-sections have a trailing colon and the second line indented. if (s/^(\S.*:) *\n / /) { $matched .= $& if %append; $include{$sect} .= qq(.SS "$1"\n); } my $indent = 0; my $content = ''; # Option with description. if (s/^( {1,10}([+-]\S.*?))(?:( +(?!-))|\n( {20,}))(\S.*)\n//) { $matched .= $& if %append; $indent = length ($4 || "$1$3"); $content = ".TP\n\x83$2\n\x83$5\n"; unless ($4) { # Indent may be different on second line. $indent = length $& if /^ {20,}/; } } # Option without description. elsif (s/^ {1,10}([+-]\S.*)\n//) { $matched .= $& if %append; $content = ".HP\n\x83$1\n"; $indent = 80; # not continued } # Indented paragraph with tag. elsif (s/^( +(\S.*?) +)(\S.*)\n//) { $matched .= $& if %append; $indent = length $1; $content = ".TP\n\x83$2\n\x83$3\n"; } # Indented paragraph. elsif (s/^( +)(\S.*)\n//) { $matched .= $& if %append; $indent = length $1; $content = ".IP\n\x83$2\n"; } # Left justified paragraph. else { s/(.*)\n//; $matched .= $& if %append; $content = ".PP\n" if $include{$sect}; $content .= "$1\n"; } # Append continuations. while (s/^ {$indent}(\S.*)\n//) { $matched .= $& if %append; $content .= "\x83$1\n" } # Move to next paragraph. s/^\n+//; for ($content) { # Leading dot and apostrophe protection. s/\x83\./\x80/g; s/\x83'/\x81/g; s/\x83//g; # Convert options. s/(^| )(-[][\w=-]+)/$1 . convert_option $2/mge; } # Check if matched paragraph contains /pat/. if (%append) { for my $pat (keys %append) { if ($matched =~ $pat) { $content .= ".PP\n" unless $append{$pat} =~ /^\./; $content .= $append{$pat}; } } } $include{$sect} .= $content; } # Refer to the real documentation. unless ($opt_no_info) { my $info_page = $opt_info || $program; $sect = 'SEE ALSO'; $include{$sect} ||= ''; $include{$sect} .= ".PP\n" if $include{$sect}; $include{$sect} .= <&2 exit 1;; esac shift;; -o) chowncmd="$chownprog $2" shift;; -s) stripcmd=$stripprog;; -t) dst_arg=$2 # Protect names problematic for `test' and other utilities. case $dst_arg in -* | [=\(\)!]) dst_arg=./$dst_arg;; esac shift;; -T) no_target_directory=true;; --version) echo "$0 $scriptversion"; exit $?;; --) shift break;; -*) echo "$0: invalid option: $1" >&2 exit 1;; *) break;; esac shift done if test $# -ne 0 && test -z "$dir_arg$dst_arg"; then # When -d is used, all remaining arguments are directories to create. # When -t is used, the destination is already specified. # Otherwise, the last argument is the destination. Remove it from $@. for arg do if test -n "$dst_arg"; then # $@ is not empty: it contains at least $arg. set fnord "$@" "$dst_arg" shift # fnord fi shift # arg dst_arg=$arg # Protect names problematic for `test' and other utilities. case $dst_arg in -* | [=\(\)!]) dst_arg=./$dst_arg;; esac done fi if test $# -eq 0; then if test -z "$dir_arg"; then echo "$0: no input file specified." >&2 exit 1 fi # It's OK to call `install-sh -d' without argument. # This can happen when creating conditional directories. exit 0 fi if test -z "$dir_arg"; then do_exit='(exit $ret); exit $ret' trap "ret=129; $do_exit" 1 trap "ret=130; $do_exit" 2 trap "ret=141; $do_exit" 13 trap "ret=143; $do_exit" 15 # Set umask so as not to create temps with too-generous modes. # However, 'strip' requires both read and write access to temps. case $mode in # Optimize common cases. *644) cp_umask=133;; *755) cp_umask=22;; *[0-7]) if test -z "$stripcmd"; then u_plus_rw= else u_plus_rw='% 200' fi cp_umask=`expr '(' 777 - $mode % 1000 ')' $u_plus_rw`;; *) if test -z "$stripcmd"; then u_plus_rw= else u_plus_rw=,u+rw fi cp_umask=$mode$u_plus_rw;; esac fi for src do # Protect names problematic for `test' and other utilities. case $src in -* | [=\(\)!]) src=./$src;; esac if test -n "$dir_arg"; then dst=$src dstdir=$dst test -d "$dstdir" dstdir_status=$? else # Waiting for this to be detected by the "$cpprog $src $dsttmp" command # might cause directories to be created, which would be especially bad # if $src (and thus $dsttmp) contains '*'. if test ! -f "$src" && test ! -d "$src"; then echo "$0: $src does not exist." >&2 exit 1 fi if test -z "$dst_arg"; then echo "$0: no destination specified." >&2 exit 1 fi dst=$dst_arg # If destination is a directory, append the input filename; won't work # if double slashes aren't ignored. if test -d "$dst"; then if test -n "$no_target_directory"; then echo "$0: $dst_arg: Is a directory" >&2 exit 1 fi dstdir=$dst dst=$dstdir/`basename "$src"` dstdir_status=0 else # Prefer dirname, but fall back on a substitute if dirname fails. dstdir=` (dirname "$dst") 2>/dev/null || expr X"$dst" : 'X\(.*[^/]\)//*[^/][^/]*/*$' \| \ X"$dst" : 'X\(//\)[^/]' \| \ X"$dst" : 'X\(//\)$' \| \ X"$dst" : 'X\(/\)' \| . 2>/dev/null || echo X"$dst" | sed '/^X\(.*[^/]\)\/\/*[^/][^/]*\/*$/{ s//\1/ q } /^X\(\/\/\)[^/].*/{ s//\1/ q } /^X\(\/\/\)$/{ s//\1/ q } /^X\(\/\).*/{ s//\1/ q } s/.*/./; q' ` test -d "$dstdir" dstdir_status=$? fi fi obsolete_mkdir_used=false if test $dstdir_status != 0; then case $posix_mkdir in '') # Create intermediate dirs using mode 755 as modified by the umask. # This is like FreeBSD 'install' as of 1997-10-28. umask=`umask` case $stripcmd.$umask in # Optimize common cases. *[2367][2367]) mkdir_umask=$umask;; .*0[02][02] | .[02][02] | .[02]) mkdir_umask=22;; *[0-7]) mkdir_umask=`expr $umask + 22 \ - $umask % 100 % 40 + $umask % 20 \ - $umask % 10 % 4 + $umask % 2 `;; *) mkdir_umask=$umask,go-w;; esac # With -d, create the new directory with the user-specified mode. # Otherwise, rely on $mkdir_umask. if test -n "$dir_arg"; then mkdir_mode=-m$mode else mkdir_mode= fi posix_mkdir=false case $umask in *[123567][0-7][0-7]) # POSIX mkdir -p sets u+wx bits regardless of umask, which # is incompatible with FreeBSD 'install' when (umask & 300) != 0. ;; *) tmpdir=${TMPDIR-/tmp}/ins$RANDOM-$$ trap 'ret=$?; rmdir "$tmpdir/d" "$tmpdir" 2>/dev/null; exit $ret' 0 if (umask $mkdir_umask && exec $mkdirprog $mkdir_mode -p -- "$tmpdir/d") >/dev/null 2>&1 then if test -z "$dir_arg" || { # Check for POSIX incompatibilities with -m. # HP-UX 11.23 and IRIX 6.5 mkdir -m -p sets group- or # other-writeable bit of parent directory when it shouldn't. # FreeBSD 6.1 mkdir -m -p sets mode of existing directory. ls_ld_tmpdir=`ls -ld "$tmpdir"` case $ls_ld_tmpdir in d????-?r-*) different_mode=700;; d????-?--*) different_mode=755;; *) false;; esac && $mkdirprog -m$different_mode -p -- "$tmpdir" && { ls_ld_tmpdir_1=`ls -ld "$tmpdir"` test "$ls_ld_tmpdir" = "$ls_ld_tmpdir_1" } } then posix_mkdir=: fi rmdir "$tmpdir/d" "$tmpdir" else # Remove any dirs left behind by ancient mkdir implementations. rmdir ./$mkdir_mode ./-p ./-- 2>/dev/null fi trap '' 0;; esac;; esac if $posix_mkdir && ( umask $mkdir_umask && $doit_exec $mkdirprog $mkdir_mode -p -- "$dstdir" ) then : else # The umask is ridiculous, or mkdir does not conform to POSIX, # or it failed possibly due to a race condition. Create the # directory the slow way, step by step, checking for races as we go. case $dstdir in /*) prefix='/';; [-=\(\)!]*) prefix='./';; *) prefix='';; esac eval "$initialize_posix_glob" oIFS=$IFS IFS=/ $posix_glob set -f set fnord $dstdir shift $posix_glob set +f IFS=$oIFS prefixes= for d do test X"$d" = X && continue prefix=$prefix$d if test -d "$prefix"; then prefixes= else if $posix_mkdir; then (umask=$mkdir_umask && $doit_exec $mkdirprog $mkdir_mode -p -- "$dstdir") && break # Don't fail if two instances are running concurrently. test -d "$prefix" || exit 1 else case $prefix in *\'*) qprefix=`echo "$prefix" | sed "s/'/'\\\\\\\\''/g"`;; *) qprefix=$prefix;; esac prefixes="$prefixes '$qprefix'" fi fi prefix=$prefix/ done if test -n "$prefixes"; then # Don't fail if two instances are running concurrently. (umask $mkdir_umask && eval "\$doit_exec \$mkdirprog $prefixes") || test -d "$dstdir" || exit 1 obsolete_mkdir_used=true fi fi fi if test -n "$dir_arg"; then { test -z "$chowncmd" || $doit $chowncmd "$dst"; } && { test -z "$chgrpcmd" || $doit $chgrpcmd "$dst"; } && { test "$obsolete_mkdir_used$chowncmd$chgrpcmd" = false || test -z "$chmodcmd" || $doit $chmodcmd $mode "$dst"; } || exit 1 else # Make a couple of temp file names in the proper directory. dsttmp=$dstdir/_inst.$$_ rmtmp=$dstdir/_rm.$$_ # Trap to clean up those temp files at exit. trap 'ret=$?; rm -f "$dsttmp" "$rmtmp" && exit $ret' 0 # Copy the file name to the temp name. (umask $cp_umask && $doit_exec $cpprog "$src" "$dsttmp") && # and set any options; do chmod last to preserve setuid bits. # # If any of these fail, we abort the whole thing. If we want to # ignore errors from any of these, just make sure not to ignore # errors from the above "$doit $cpprog $src $dsttmp" command. # { test -z "$chowncmd" || $doit $chowncmd "$dsttmp"; } && { test -z "$chgrpcmd" || $doit $chgrpcmd "$dsttmp"; } && { test -z "$stripcmd" || $doit $stripcmd "$dsttmp"; } && { test -z "$chmodcmd" || $doit $chmodcmd $mode "$dsttmp"; } && # If -C, don't bother to copy if it wouldn't change the file. if $copy_on_change && old=`LC_ALL=C ls -dlL "$dst" 2>/dev/null` && new=`LC_ALL=C ls -dlL "$dsttmp" 2>/dev/null` && eval "$initialize_posix_glob" && $posix_glob set -f && set X $old && old=:$2:$4:$5:$6 && set X $new && new=:$2:$4:$5:$6 && $posix_glob set +f && test "$old" = "$new" && $cmpprog "$dst" "$dsttmp" >/dev/null 2>&1 then rm -f "$dsttmp" else # Rename the file to the real destination. $doit $mvcmd -f "$dsttmp" "$dst" 2>/dev/null || # The rename failed, perhaps because mv can't rename something else # to itself, or perhaps because mv is so ancient that it does not # support -f. { # Now remove or move aside any old file at destination location. # We try this two ways since rm can't unlink itself on some # systems and the destination file might be busy for other # reasons. In this case, the final cleanup might fail but the new # file should still install successfully. { test ! -f "$dst" || $doit $rmcmd -f "$dst" 2>/dev/null || { $doit $mvcmd -f "$dst" "$rmtmp" 2>/dev/null && { $doit $rmcmd -f "$rmtmp" 2>/dev/null; :; } } || { echo "$0: cannot unlink or rename $dst" >&2 (exit 1); exit 1 } } && # Now rename the file to the real destination. $doit $mvcmd "$dsttmp" "$dst" } fi || exit 1 trap '' 0 fi done # Local variables: # eval: (add-hook 'write-file-hooks 'time-stamp) # time-stamp-start: "scriptversion=" # time-stamp-format: "%:y-%02m-%02d.%02H" # time-stamp-time-zone: "UTC" # time-stamp-end: "; # UTC" # End: smalltalk-3.2.5/build-aux/glib-2.0.m40000644000175000017500000002001712123404352013770 00000000000000# Configure paths for GLIB # Owen Taylor 1997-2001 dnl AM_PATH_GLIB_2_0([MINIMUM-VERSION, [ACTION-IF-FOUND [, ACTION-IF-NOT-FOUND [, MODULES]]]]) dnl Test for GLIB, and define GLIB_CFLAGS and GLIB_LIBS, if gmodule, gobject or dnl gthread is specified in MODULES, pass to pkg-config dnl AC_DEFUN([AM_PATH_GLIB_2_0], [dnl dnl Get the cflags and libraries from pkg-config dnl AC_ARG_ENABLE(glibtest, [ --disable-glibtest do not try to compile and run a test GLIB program], , enable_glibtest=yes) pkg_config_args=glib-2.0 for module in . $4 do case "$module" in gmodule) pkg_config_args="$pkg_config_args gmodule-2.0" ;; gobject) pkg_config_args="$pkg_config_args gobject-2.0" ;; gthread) pkg_config_args="$pkg_config_args gthread-2.0" ;; esac done AC_PATH_PROG(PKG_CONFIG, pkg-config, no) no_glib="" if test x$PKG_CONFIG != xno ; then if $PKG_CONFIG --atleast-pkgconfig-version 0.7 ; then : else echo *** pkg-config too old; version 0.7 or better required. no_glib=yes PKG_CONFIG=no fi else no_glib=yes fi min_glib_version=ifelse([$1], ,2.0.0,$1) AC_MSG_CHECKING(for GLIB - version >= $min_glib_version) if test x$PKG_CONFIG != xno ; then ## don't try to run the test against uninstalled libtool libs if $PKG_CONFIG --uninstalled $pkg_config_args; then echo "Will use uninstalled version of GLib found in PKG_CONFIG_PATH" enable_glibtest=no fi if $PKG_CONFIG --atleast-version $min_glib_version $pkg_config_args; then : else no_glib=yes fi fi if test x"$no_glib" = x ; then GLIB_GENMARSHAL=`$PKG_CONFIG --variable=glib_genmarshal glib-2.0` GOBJECT_QUERY=`$PKG_CONFIG --variable=gobject_query glib-2.0` GLIB_MKENUMS=`$PKG_CONFIG --variable=glib_mkenums glib-2.0` GLIB_CFLAGS=`$PKG_CONFIG --cflags $pkg_config_args` GLIB_LIBS=`$PKG_CONFIG --libs $pkg_config_args` glib_config_major_version=`$PKG_CONFIG --modversion glib-2.0 | \ sed 's/\([[0-9]]*\).\([[0-9]]*\).\([[0-9]]*\)/\1/'` glib_config_minor_version=`$PKG_CONFIG --modversion glib-2.0 | \ sed 's/\([[0-9]]*\).\([[0-9]]*\).\([[0-9]]*\)/\2/'` glib_config_micro_version=`$PKG_CONFIG --modversion glib-2.0 | \ sed 's/\([[0-9]]*\).\([[0-9]]*\).\([[0-9]]*\)/\3/'` if test "x$enable_glibtest" = "xyes" ; then ac_save_CFLAGS="$CFLAGS" ac_save_LIBS="$LIBS" CFLAGS="$CFLAGS $GLIB_CFLAGS" LIBS="$GLIB_LIBS $LIBS" dnl dnl Now check if the installed GLIB is sufficiently new. (Also sanity dnl checks the results of pkg-config to some extent) dnl rm -f conf.glibtest AC_RUN_IFELSE([AC_LANG_SOURCE([[ #include #include #include int main () { int major, minor, micro; char *tmp_version; system ("touch conf.glibtest"); /* HP/UX 9 (%@#!) writes to sscanf strings */ tmp_version = g_strdup("$min_glib_version"); if (sscanf(tmp_version, "%d.%d.%d", &major, &minor, µ) != 3) { printf("%s, bad version string\n", "$min_glib_version"); exit(1); } if ((glib_major_version != $glib_config_major_version) || (glib_minor_version != $glib_config_minor_version) || (glib_micro_version != $glib_config_micro_version)) { printf("\n*** 'pkg-config --modversion glib-2.0' returned %d.%d.%d, but GLIB (%d.%d.%d)\n", $glib_config_major_version, $glib_config_minor_version, $glib_config_micro_version, glib_major_version, glib_minor_version, glib_micro_version); printf ("*** was found! If pkg-config was correct, then it is best\n"); printf ("*** to remove the old version of GLib. You may also be able to fix the error\n"); printf("*** by modifying your LD_LIBRARY_PATH enviroment variable, or by editing\n"); printf("*** /etc/ld.so.conf. Make sure you have run ldconfig if that is\n"); printf("*** required on your system.\n"); printf("*** If pkg-config was wrong, set the environment variable PKG_CONFIG_PATH\n"); printf("*** to point to the correct configuration files\n"); } else if ((glib_major_version != GLIB_MAJOR_VERSION) || (glib_minor_version != GLIB_MINOR_VERSION) || (glib_micro_version != GLIB_MICRO_VERSION)) { printf("*** GLIB header files (version %d.%d.%d) do not match\n", GLIB_MAJOR_VERSION, GLIB_MINOR_VERSION, GLIB_MICRO_VERSION); printf("*** library (version %d.%d.%d)\n", glib_major_version, glib_minor_version, glib_micro_version); } else { if ((glib_major_version > major) || ((glib_major_version == major) && (glib_minor_version > minor)) || ((glib_major_version == major) && (glib_minor_version == minor) && (glib_micro_version >= micro))) { return 0; } else { printf("\n*** An old version of GLIB (%d.%d.%d) was found.\n", glib_major_version, glib_minor_version, glib_micro_version); printf("*** You need a version of GLIB newer than %d.%d.%d. The latest version of\n", major, minor, micro); printf("*** GLIB is always available from ftp://ftp.gtk.org.\n"); printf("***\n"); printf("*** If you have already installed a sufficiently new version, this error\n"); printf("*** probably means that the wrong copy of the pkg-config shell script is\n"); printf("*** being found. The easiest way to fix this is to remove the old version\n"); printf("*** of GLIB, but you can also set the PKG_CONFIG environment to point to the\n"); printf("*** correct copy of pkg-config. (In this case, you will have to\n"); printf("*** modify your LD_LIBRARY_PATH enviroment variable, or edit /etc/ld.so.conf\n"); printf("*** so that the correct libraries are found at run-time))\n"); } } return 1; } ]])],[],[no_glib=yes],[echo $ac_n "cross compiling; assumed OK... $ac_c"]) CFLAGS="$ac_save_CFLAGS" LIBS="$ac_save_LIBS" fi fi if test "x$no_glib" = x ; then AC_MSG_RESULT(yes (version $glib_config_major_version.$glib_config_minor_version.$glib_config_micro_version)) ifelse([$2], , :, [$2]) else AC_MSG_RESULT(no) if test "$PKG_CONFIG" = "no" ; then echo "*** A new enough version of pkg-config was not found." echo "*** See http://www.freedesktop.org/software/pkgconfig/" else if test -f conf.glibtest ; then : else echo "*** Could not run GLIB test program, checking why..." ac_save_CFLAGS="$CFLAGS" ac_save_LIBS="$LIBS" CFLAGS="$CFLAGS $GLIB_CFLAGS" LIBS="$LIBS $GLIB_LIBS" AC_LINK_IFELSE([AC_LANG_PROGRAM([[ #include #include ]], [[ return ((glib_major_version) || (glib_minor_version) || (glib_micro_version)); ]])],[ echo "*** The test program compiled, but did not run. This usually means" echo "*** that the run-time linker is not finding GLIB or finding the wrong" echo "*** version of GLIB. If it is not finding GLIB, you'll need to set your" echo "*** LD_LIBRARY_PATH environment variable, or edit /etc/ld.so.conf to point" echo "*** to the installed location Also, make sure you have run ldconfig if that" echo "*** is required on your system" echo "***" echo "*** If you have an old version installed, it is best to remove it, although" echo "*** you may also be able to get things to work by modifying LD_LIBRARY_PATH" ],[ echo "*** The test program failed to compile or link. See the file config.log for the" echo "*** exact error that occured. This usually means GLIB is incorrectly installed."]) CFLAGS="$ac_save_CFLAGS" LIBS="$ac_save_LIBS" fi fi GLIB_CFLAGS="" GLIB_LIBS="" GLIB_GENMARSHAL="" GOBJECT_QUERY="" GLIB_MKENUMS="" ifelse([$3], , :, [$3]) fi AC_SUBST(GLIB_CFLAGS) AC_SUBST(GLIB_LIBS) AC_SUBST(GLIB_GENMARSHAL) AC_SUBST(GOBJECT_QUERY) AC_SUBST(GLIB_MKENUMS) rm -f conf.glibtest ]) smalltalk-3.2.5/build-aux/tcltk.m40000644000175000017500000001332012123404352013676 00000000000000dnl I'd like this to be edited in -*- Autoconf -*- mode... dnl AC_DEFUN([GST_HAVE_TCLTK], [ AC_ARG_WITH(tcl, [ --with-tcl=path set path to tclConfig.sh [default=ask tclsh]]) AC_ARG_WITH(tk, [ --with-tk=path set path to tkConfig.sh [default=same as Tcl]]) if test "x$with_tcl" = x || test "$with_tcl" = yes; then AC_MSG_CHECKING(for tclsh) exec AS_MESSAGE_FD([])>/dev/null AC_PATH_PROG(TCLSH, tclsh) case $libdir in $bindir | $prefix | '${prefix}') libpath=lib ;; *) libpath=`echo ${libdir} | sed s:.*/::` ;; esac dataroot2lib='s,\(.*\)/'`echo ${datarootdir} | sed s:.*/::`,'\1'/$libpath, test "$silent" != yes && exec AS_MESSAGE_FD([])>&1 if test -n "$TCLSH"; then for i in ${TCLSH}*; do if test -x $i; then with_tcl=`echo 'puts $tcl_library' | $i 2> /dev/null` if test "x$with_tcl" != x; then # Assign the name we found to the TCLSH variable, and try # to remove the last component from the path and to change # /usr/share to /usr/lib TCLSH=$i test -f "$with_tcl/../../tclConfig.sh" && with_tcl="$with_tcl/../.." && break test -f "$with_tcl/../tclConfig.sh" && with_tcl="$with_tcl/.." && break test -f "$with_tcl/tclConfig.sh" && break with_tcl=`echo "$with_tcl" | sed $dataroot2lib` # Do not bother testing /usr/lib/tcl8.5/tclConfig.sh if there is one # in /usr/lib. if test -f "$with_tcl/../tclConfig.sh"; then :; else test -f "$with_tcl/tclConfig.sh" && break fi with_tcl=`echo "$with_tcl" | sed 's:/[[^/]]*/\{0,1\}$::'` if test -f "$with_tcl/../tclConfig.sh"; then :; else test -f "$with_tcl/tclConfig.sh" && break fi with_tcl=`echo "$with_tcl" | sed 's:/[[^/]]*/\{0,1\}$::'` test -f "$with_tcl/tclConfig.sh" && break fi with_tcl=no TCLSH=no fi done else with_tcl=no TCLSH=no fi AC_MSG_RESULT($TCLSH) fi if test "x$with_tk" = x || test "$with_tk" = yes; then with_tk=`echo "$with_tcl" | sed -e 's/tcl/tk/g' -e 's/tktk/tcltk/g' -e 's/Tcl/Tk/g'` test -f "$with_tk/tkConfig.sh" || with_tk=no fi if test "$with_tcl" != no; then with_tcl=`cd $with_tcl && pwd` test -f "$with_tcl/tclConfig.sh" || with_tcl=no fi if test "$with_tk" != no; then with_tk=`cd $with_tk && pwd` test -f "$with_tk/tkConfig.sh" || with_tk=no fi AC_MSG_CHECKING(for Tcl 8.x) AC_MSG_RESULT($with_tcl) AC_MSG_CHECKING(for Tk 8.x) AC_MSG_RESULT($with_tk) save_cppflags="$CPPFLAGS" save_libs="$LIBS" AC_CACHE_CHECK(the include path for Tcl/Tk 8.x, gst_cv_tcltk_includes, [ exec AS_MESSAGE_FD([])>/dev/null gst_cv_tcltk_includes="not found" if test "$with_tcl" != no && test "$with_tk" != no; then # Get the values we need from the Tcl/Tk configuration files . $with_tcl/tclConfig.sh . $with_tk/tkConfig.sh # search for the header files, because some implementations of tclConfig.sh # do not deliver correct header includes for trial in 0 1 2 3 4; do case $trial in 0) gst_cv_tcltk_includes="$TK_XINCLUDES $TCL_INCLUDE_SPEC" ;; 1) gst_cv_tcltk_includes="$TK_XINCLUDES -I$TCL_PREFIX/include" test "$TCL_PREFIX" != "$TCL_EXEC_PREFIX" && gst_cv_tcltk_includes="$gst_cv_tcltk_includes -I$TCL_EXEC_PREFIX/include" test "$TCL_PREFIX" != "$TK_PREFIX" && gst_cv_tcltk_includes="$gst_cv_tcltk_includes -I$TK_PREFIX/include" test "$TK_PREFIX" != "$TK_EXEC_PREFIX" && gst_cv_tcltk_includes="$gst_cv_tcltk_includes -I$TK_EXEC_PREFIX/include" ;; 2) gst_cv_tcltk_includes="$TK_XINCLUDES -I$TCL_SRC_DIR/.." test "$TCL_SRC_DIR" != "$TK_SRC_DIR" && gst_cv_tcltk_includes="$gst_cv_tcltk_includes -I$TK_SRC_DIR/.." ;; 3) gst_cv_tcltk_includes="$TK_XINCLUDES -I$TCL_SRC_DIR/include" test "$TCL_SRC_DIR" != "$TK_SRC_DIR" && gst_cv_tcltk_includes="$gst_cv_tcltk_includes -I$TK_SRC_DIR/include" ;; 4) gst_cv_tcltk_includes="$TK_XINCLUDES -I$TCL_PREFIX/include/tcl$TCL_VERSION -I$TK_PREFIX/include/tk$TK_VERSION" test "$TCL_PREFIX" != "$TCL_EXEC_PREFIX" && gst_cv_tcltk_includes="$gst_cv_tcltk_includes -I$TCL_EXEC_PREFIX/include/tcl$TCL_VERSION" test "$TK_PREFIX" != "$TK_EXEC_PREFIX" && gst_cv_tcltk_includes="$gst_cv_tcltk_includes -I$TK_EXEC_PREFIX/include/tk$TK_VERSION" ;; esac CPPFLAGS="$save_cppflags $gst_cv_tcltk_includes" AC_EGREP_CPP(everything_fine, [ #include #include #ifdef TCL_MAJOR_VERSION #ifdef TK_MAJOR_VERSION #if ((TCL_MAJOR_VERSION == $TCL_MAJOR_VERSION) && (TCL_MINOR_VERSION == $TCL_MINOR_VERSION)) #if ((TK_MAJOR_VERSION == $TK_MAJOR_VERSION) && (TCL_MINOR_VERSION == $TCL_MINOR_VERSION)) everything_fine #endif #endif #endif #endif], break) gst_cv_tcltk_includes="not found" done fi test "$silent" != yes && exec AS_MESSAGE_FD([])>&1 ]) AC_CACHE_CHECK(how to link with Tcl/Tk 8.x, gst_cv_tcltk_libs, [ gst_cv_tcltk_libs="not found" exec AS_MESSAGE_FD([])>/dev/null if test "$gst_cv_tcltk_includes" != "not found"; then # The indirection is required by Tcl/Tk gst_cv_tcltk_libs="$TCL_LIBS $TK_XLIBSW $TCL_LIB_SPEC $TK_LIB_SPEC" gst_cv_tcltk_libs=`eval echo $gst_cv_tcltk_libs` CPPFLAGS="$save_cppflags $gst_cv_tcltk_includes" LIBS="$save_libs $gst_cv_tcltk_libs" AC_CHECK_FUNC(Tcl_ObjSetVar2, , gst_cv_tcltk_libs="not found") AC_CHECK_FUNC(Tk_CreatePhotoImageFormat, , gst_cv_tcltk_libs="not found") fi test "$silent" != yes && exec AS_MESSAGE_FD([])>&1 ]) CPPFLAGS="$save_cppflags" LIBS="$save_libs" if test "$gst_cv_tcltk_libs" != "not found"; then LIBTCLTK="$gst_cv_tcltk_libs" INCTCLTK="$gst_cv_tcltk_includes" AC_DEFINE(HAVE_TCLTK, 1, [Define if your system has Tcl/Tk, 8.0 or later, installed.]) fi AC_SUBST(LIBTCLTK) AC_SUBST(INCTCLTK) ])dnl smalltalk-3.2.5/build-aux/wine.m40000644000175000017500000000050512123404352013520 00000000000000AC_DEFUN([GST_WINE_IF], [AC_REQUIRE([GST_WINE]) AS_IF([test "x$gst_cv_wine" = xyes], $@)]) AC_DEFUN([GST_WINE], [AC_CACHE_CHECK([whether cross-compiling under Wine], [gst_cv_wine], [case $host:$build in *mingw*:*mingw* | *mingw*:*cygwin* ) gst_cv_wine=no ;; *mingw*:*) gst_cv_wine=yes ;; *) gst_cv_wine=no ;; esac])]) smalltalk-3.2.5/build-aux/lib-ld.m40000644000175000017500000000626012123404352013725 00000000000000# lib-ld.m4 serial 1 (gettext-0.11) dnl Copyright (C) 1996-2002 Free Software Foundation, Inc. dnl This file is free software, distributed under the terms of the GNU dnl General Public License. As a special exception to the GNU General dnl Public License, this file may be distributed as part of a program dnl that contains a configuration script generated by Autoconf, under dnl the same distribution terms as the rest of that program. dnl Subroutines of libtool.m4, dnl with replacements s/AC_/AC_LIB/ and s/lt_cv/acl_cv/ to avoid collision dnl with libtool.m4. dnl From libtool-1.4. Sets the variable with_gnu_ld to yes or no. AC_DEFUN([AC_LIB_PROG_LD_GNU], [AC_CACHE_CHECK([if the linker ($LD) is GNU ld], acl_cv_prog_gnu_ld, [# I'd rather use --version here, but apparently some GNU ld's only accept -v. if $LD -v 2>&1 &5; then acl_cv_prog_gnu_ld=yes else acl_cv_prog_gnu_ld=no fi]) with_gnu_ld=$acl_cv_prog_gnu_ld ]) dnl From libtool-1.4. Sets the variable LD. AC_DEFUN([AC_LIB_PROG_LD], [AC_ARG_WITH(gnu-ld, [ --with-gnu-ld assume the C compiler uses GNU ld [default=no]], test "$withval" = no || with_gnu_ld=yes, with_gnu_ld=no) AC_REQUIRE([AC_PROG_CC])dnl AC_REQUIRE([AC_CANONICAL_HOST])dnl ac_prog=ld if test "$GCC" = yes; then # Check if gcc -print-prog-name=ld gives a path. AC_MSG_CHECKING([for ld used by GCC]) case $host in *-*-mingw*) # gcc leaves a trailing carriage return which upsets mingw ac_prog=`($CC -print-prog-name=ld) 2>&5 | tr -d '\015'` ;; *) ac_prog=`($CC -print-prog-name=ld) 2>&5` ;; esac case $ac_prog in # Accept absolute paths. [[\\/]* | [A-Za-z]:[\\/]*)] [re_direlt='/[^/][^/]*/\.\./'] # Canonicalize the path of ld ac_prog=`echo $ac_prog| sed 's%\\\\%/%g'` while echo $ac_prog | grep "$re_direlt" > /dev/null 2>&1; do ac_prog=`echo $ac_prog| sed "s%$re_direlt%/%"` done test -z "$LD" && LD="$ac_prog" ;; "") # If it fails, then pretend we aren't using GCC. ac_prog=ld ;; *) # If it is relative, then search for the first ld in PATH. with_gnu_ld=unknown ;; esac elif test "$with_gnu_ld" = yes; then AC_MSG_CHECKING([for GNU ld]) else AC_MSG_CHECKING([for non-GNU ld]) fi AC_CACHE_VAL(acl_cv_path_LD, [if test -z "$LD"; then IFS="${IFS= }"; ac_save_ifs="$IFS"; IFS="${IFS}${PATH_SEPARATOR-:}" for ac_dir in $PATH; do test -z "$ac_dir" && ac_dir=. if test -f "$ac_dir/$ac_prog" || test -f "$ac_dir/$ac_prog$ac_exeext"; then acl_cv_path_LD="$ac_dir/$ac_prog" # Check to see if the program is GNU ld. I'd rather use --version, # but apparently some GNU ld's only accept -v. # Break only if it was the GNU/non-GNU ld that we prefer. if "$acl_cv_path_LD" -v 2>&1 < /dev/null | egrep '(GNU|with BFD)' > /dev/null; then test "$with_gnu_ld" != no && break else test "$with_gnu_ld" != yes && break fi fi done IFS="$ac_save_ifs" else acl_cv_path_LD="$LD" # Let the user override the test with a path. fi]) LD="$acl_cv_path_LD" if test -n "$LD"; then AC_MSG_RESULT($LD) else AC_MSG_RESULT(no) fi test -z "$LD" && AC_MSG_ERROR([no acceptable ld found in \$PATH]) AC_LIB_PROG_LD_GNU ]) smalltalk-3.2.5/build-aux/libc-so-name.m40000644000175000017500000000502012130343734015025 00000000000000# libc-so-name.m4 serial 1 dnl Copyright (C) 2003, 2009 Free Software Foundation, Inc. dnl This file is free software, distributed under the terms of the GNU dnl General Public License. As a special exception to the GNU General dnl Public License, this file may be distributed as part of a program dnl that contains a configuration script generated by Autoconf, under dnl the same distribution terms as the rest of that program. dnl Sets the variables LIBC_SO_NAME and LIBC_SO_DIR to the directory dnl and basename for the C library. AC_DEFUN([GST_LIBC_SO_NAME], [AC_CACHE_CHECK([whether lt_dlopenext("libc") works], gst_cv_libc_dlopen_works, [save_CFLAGS=$CFLAGS save_LIBS=$LIBS CFLAGS="$CFLAGS $INCLTDL" LIBS="$CFLAGS $LIBLTDL" AC_RUN_IFELSE([AC_LANG_PROGRAM([[ #include `test $with_system_libltdl = no && echo '#include "ltdl.c"' ` ]], [[ lt_dlinit(); return lt_dlopenext("libc") == NULL ? 1 : 0; ]])], [gst_cv_libc_dlopen_works=yes], [gst_cv_libc_dlopen_works=no], [gst_cv_libc_dlopen_works=no]) CFLAGS=$save_CFLAGS LIBS=$save_LIBS ]) AM_CONDITIONAL([NEED_LIBC_LA], [test "$gst_cv_libc_dlopen_works" = no]) if test "$gst_cv_libc_dlopen_works" = no; then AC_CONFIG_FILES(libc.la) fi AC_CACHE_CHECK([how to dlopen the C library], gst_cv_libc_so_name, [ gst_lib_path= if test $GCC = yes; then if $CC -print-multiarch >/dev/null 2>&1; then gst_lib_path=`$CC -print-multiarch $CFLAGS $CPPFLAGS` fi if test -z "$gst_lib_path"; then gst_lib_path=`$CC --print-multi-os-directory $CFLAGS $CPPFLAGS` fi case $gst_lib_path in .) gst_lib_path= ;; *) gst_lib_path=$gst_lib_path/ ;; esac fi case $gst_lib_path in /*) gst_libc_search_path="${gst_lib_path}libc.so* ${gst_lib_path}libc-*.so ${gst_lib_path}libc.sl ${gst_lib_path}libSystem.dylib" ;; *) gst_libc_search_path="/shlib/libc.so \ /lib/${gst_lib_path}libc.so* \ /usr/lib/${gst_lib_path}libc.so.* \ /usr/lib/${gst_lib_path}libc.sl \ /lib/${gst_lib_path}libc-*.so \ /System/Library/Frameworks/System.framework/System \ /usr/lib/libSystem.dylib" esac gst_lib_sysroot=`$CC --print-sysroot` for i in $gst_libc_search_path; do if test -f "$gst_lib_sysroot$i"; then oldwd=`pwd` gst_cv_libc_so_name=`basename $i` gst_cv_libc_so_dir=`dirname $i` cd "$gst_cv_libc_so_dir" && gst_cv_libc_so_dir=`pwd` cd $oldwd break fi done]) LIBC_SO_NAME=$gst_cv_libc_so_name LIBC_SO_DIR=$gst_cv_libc_so_dir AC_SUBST(LIBC_SO_NAME) AC_SUBST(LIBC_SO_DIR) ]) smalltalk-3.2.5/build-aux/gmp.m40000644000175000017500000000230712123404352013343 00000000000000dnl I'd like this to be edited in -*- Autoconf -*- mode... dnl AC_DEFUN([GST_HAVE_GMP], [ AC_ARG_WITH(gmp, [ --with-gmp=path set path to the GMP library --without-gmp don't try to detect and use GMP]) if test "$with_gmp" != no; then AC_CACHE_CHECK(how to link with GMP, gst_cv_gmp_libs, [ if test "$with_gmp" && test -d "$with_gmp"; then gst_cv_gmp_libs="-L$with_gmp -lgmp" CPPFLAGS="$CPPFLAGS -I$with_gmp/../include" else gst_cv_gmp_libs="-lgmp" fi ac_save_LIBS="$LIBS" LIBS="$ac_save_LIBS $gst_cv_gmp_libs" AC_LINK_IFELSE([AC_LANG_PROGRAM([[ #include #include ]], [[ #if __GNU_MP_VERSION < 4 you lose #endif mpz_t z; mp_limb_t n[10]; mpn_tdiv_qr (n, n, 10, n, 10, n, 10); mpz_init_set_str (z, "123456", 0); ]])],[],[gst_cv_gmp_libs="not found"]) LIBS="$ac_save_LIBS" ]) if test "$gst_cv_gmp_libs" != "not found"; then LIBGMP="$gst_cv_gmp_libs" AC_SUBST(LIBGMP) AC_DEFINE(HAVE_GMP, 1, [Define if your system has the GNU MP library.]) AC_CHECK_SIZEOF(mp_limb_t, , [ #include #include ]) fi fi ])dnl smalltalk-3.2.5/build-aux/texi2html0000755000175000017500000037156212123404352014200 00000000000000#! /usr/bin/env perl 'di '; 'ig 00 '; #+############################################################################## # # texi2html: Program to transform Texinfo documents to HTML # # Copyright (C) 1999, 2000, 2001 Free Software Foundation, Inc. # # This program is free software; you can redistribute it and/or modify # it under the terms of the GNU General Public License as published by # the Free Software Foundation; either version 2 of the License, or # (at your option) any later version. # # This program is distributed in the hope that it will be useful, # but WITHOUT ANY WARRANTY; without even the implied warranty of # MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the # GNU General Public License for more details. # # You should have received a copy of the GNU General Public License # along with this program; if not, write to the Free Software # Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA # #-############################################################################## # Summary of changes by Paolo Bonzini: # - Extensive modifications to texi2html.init to produce a nicer navigation # bar # - Removed support for an external texi2html.init # - Removed support for latex2html # - Don't use latex2html to produce smallcaps (@sc) # - Produce a navigation bar for each chapter # - Split at sections only, not at every node, if `-split section' is given # on the command line # - Produce amp/lt/gt entities instead of #38/#60/#62 # - Produce lowercase html # This requires perl version 5 or higher require 5.0; # Homepage: $T2H_HOMEPAGE = < (original author) Karl Berry Olaf Bachmann and many others. Maintained by: Olaf Bachmann Adapted by: Paolo Bonzini EOT # Version: set in configure.in $THISVERSION = '1.64a'; $THISPROG = "texi2html $THISVERSION"; # program name and version # The man page for this program is included at the end of this file and can be # viewed using the command 'nroff -man texi2html'. # Identity: $T2H_TODAY = &pretty_date; # like "20 September 1993" #+++############################################################################ # # # Initialization # # Pasted content of File $(srcdir)/texi2html.init: Default initializations # # # #---############################################################################ ###################################################################### # File: texi2html.init # # Sets default values for command-line arguments and for various customizable # procedures # # A copy of this file is pasted into the beginning of texi2html by # 'make texi2html' # # Copy this file and make changes to it, if you like. # Afterwards, either, load it with command-line option -init_file # # $Id: texi2html.init,v 1.34 2000/07/27 14:09:02 obachman Exp $ ###################################################################### # stuff which can also be set by command-line options # # # Note: values set here, overwrite values set by the command-line # options before -init_file and might still be overwritten by # command-line arguments following the -init_file option # # T2H_OPTIONS is a hash whose keys are the (long) names of valid # command-line options and whose values are a hash with the following keys: # type ==> one of !|=i|:i|=s|:s (see GetOpt::Long for more info) # linkage ==> ref to scalar, array, or subroutine (see GetOpt::Long for more info) # verbose ==> short description of option (displayed by -h) # noHelp ==> if 1 -> for "not so important options": only print description on -h 1 # 2 -> for obsolete options: only print description on -h 2 $T2H_DEBUG = 0; $T2H_OPTIONS -> {debug} = { type => '=i', linkage => \$main::T2H_DEBUG, verbose => 'output HTML with debuging information', }; $T2H_DOCTYPE = ''; $T2H_OPTIONS -> {doctype} = { type => '=s', linkage => \$main::T2H_DOCTYPE, verbose => 'document type which is output in header of HTML files', noHelp => 1 }; $T2H_CHECK = 0; $T2H_OPTIONS -> {check} = { type => '!', linkage => \$main::T2H_CHECK, verbose => 'if set, only check files and output all things that may be Texinfo commands', noHelp => 1 }; # -expand # if set to "tex" (or, "info") expand @iftex and @tex (or, @ifinfo) sections # else, neither expand @iftex, @tex, nor @ifinfo sections $T2H_EXPAND = "none"; $T2H_OPTIONS -> {expand} = { type => '=s', linkage => \$T2H_EXPAND, verbose => 'Expand info|tex|none section of texinfo source', }; # - glossary #if set, uses section named `Footnotes' for glossary $T2H_USE_GLOSSARY = 0; T2H_OPTIONS -> {glossary} = { type => '!', linkage => \$T2H_USE_GLOSSARY, verbose => "if set, uses section named `Footnotes' for glossary", noHelp => 1, }; # -invisible # $T2H_INVISIBLE_MARK is the text used to create invisible destination # anchors for index links (you can for instance use the invisible.xbm # file shipped with this program). This is a workaround for a known # bug of many WWW browsers, including netscape. # For me, it works fine without it -- on the contrary: if there, it # inserts space between headers and start of text (obachman 3/99) $T2H_INVISIBLE_MARK = ''; # $T2H_INVISIBLE_MARK = ' '; $T2H_OPTIONS -> {invisible} = { type => '=s', linkage => \$T2H_INVISIBLE_MARK, verbose => 'use text in invisble anchot', noHelp => 1, }; # -iso # if set, ISO8879 characters are used for special symbols (like copyright, etc) $T2H_USE_ISO = 0; $T2H_OPTIONS -> {iso} = { type => 'iso', linkage => \$T2H_USE_ISO, verbose => 'if set, ISO8879 characters are used for special symbols (like copyright, etc)', noHelp => 1, }; # -I # list directories where @include files are searched for (besides the # directory of the doc file) additional '-I' args add to this list @T2H_INCLUDE_DIRS = ("."); $T2H_OPTIONS -> {I} = { type => '=s', linkage => \@T2H_INCLUDE_DIRS, verbose => 'append $s to the @include search path', }; # -top_file # uses file of this name for top-level file # extension is manipulated appropriately, if necessary. # If empty, .html is used # Typically, you would set this to "index.html". $T2H_TOP_FILE = ''; $T2H_OPTIONS -> {top_file} = { type => '=s', linkage => \$T2H_TOP_FILE, verbose => 'use $s as top file, instead of .html', }; # -toc_file # uses file of this name for table of contents file # extension is manipulated appropriately, if necessary. # If empty, _toc.html is used $T2H_TOC_FILE = ''; $T2H_OPTIONS -> {toc_file} = { type => '=s', linkage => \$T2H_TOC_FILE, verbose => 'use $s as ToC file, instead of _toc.html', }; # -frames # if set, output two additional files which use HTML 4.0 "frames". $T2H_FRAMES = 0; $T2H_OPTIONS -> {frames} = { type => '!', linkage => \$T2H_FRAMES, verbose => 'output files which use HTML 4.0 frames (experimental)', noHelp => 1, }; # -menu | -nomenu # if set, show the Texinfo menus $T2H_SHOW_MENU = 1; $T2H_OPTIONS -> {menu} = { type => '!', linkage => \$T2H_SHOW_MENU, verbose => 'ouput Texinfo menus', }; # -number | -nonumber # if set, number sections and show section names and numbers in references # and menus $T2H_NUMBER_SECTIONS = 1; $T2H_OPTIONS -> {number} = { type => '!', linkage => \$T2H_NUMBER_SECTIONS, verbose => 'use numbered sections' }; # if set, and T2H_NUMBER_SECTIONS is set, then use node names in menu # entries, instead of section names $T2H_NODE_NAME_IN_MENU = 0; # if set and menu entry equals menu descr, then do not print menu descr. # Likewise, if node name equals entry name, do not print entry name. $T2H_AVOID_MENU_REDUNDANCY = 1; # -split section|chapter|none # if set to 'section' (resp. 'chapter') create one html file per (sub)section # (resp. chapter) and separate pages for Top, ToC, Overview, Index, # Glossary, About. # otherwise, create monolithic html file which contains whole document #$T2H_SPLIT = 'section'; $T2H_SPLIT = ''; $T2H_OPTIONS -> {split} = { type => '=s', linkage => \$T2H_SPLIT, verbose => 'split document on section|chapter else no splitting', }; # -section_navigation|-no-section_navigation # if set, then navigation panels are printed at the beginning of each section # and, possibly at the end (depending on whether or not there were more than # $T2H_WORDS_IN_PAGE words on page # This is most useful if you do not want to have section navigation # on -split chapter $T2H_SECTION_NAVIGATION = 0; # -subdir # if set put result files in this directory # if not set result files are put into current directory #$T2H_SUBDIR = 'html'; $T2H_SUBDIR = ''; $T2H_OPTIONS -> {subdir} = { type => '=s', linkage => \$T2H_SUBDIR, verbose => 'put HTML files in directory $s, instead of $cwd', }; # -short_extn # If this is set all HTML file will have extension ".htm" instead of # ".html". This is helpful when shipping the document to PC systems. $T2H_SHORTEXTN = 0; $T2H_OPTIONS -> {short_ext} = { type => '!', linkage => \$T2H_SHORTEXTN, verbose => 'use "htm" extension for output HTML files', }; # -prefix # Set the output file prefix, prepended to all .html, .gif and .pl files. # By default, this is the basename of the document $T2H_PREFIX = ''; $T2H_OPTIONS -> {prefix} = { type => '=s', linkage => \$T2H_PREFIX, verbose => 'use as prefix for output files, instead of ', }; # -o filename # If set, generate monolithic document output html into $filename $T2H_OUT = ''; $T2H_OPTIONS -> {out_file} = { type => '=s', linkage => sub {$main::T2H_OUT = @_[1]; $T2H_SPLIT = '';}, verbose => 'if set, all HTML output goes into file $s', }; # -short_ref #if set cross-references are given without section numbers $T2H_SHORT_REF = ''; $T2H_OPTIONS -> {short_ref} = { type => '!', linkage => \$T2H_SHORT_REF, verbose => 'if set, references are without section numbers', }; # -idx_sum # if value is set, then for each @prinindex $what # $docu_name_$what.idx is created which contains lines of the form # $key\t$ref sorted alphabetically (case matters) $T2H_IDX_SUMMARY = 0; $T2H_OPTIONS -> {idx_sum} = { type => '!', linkage => \$T2H_IDX_SUMMARY, verbose => 'if set, also output index summary', noHelp => 1, }; # -verbose # if set, chatter about what we are doing $T2H_VERBOSE = ''; $T2H_OPTIONS -> {Verbose} = { type => '!', linkage => \$T2H_VERBOSE, verbose => 'print progress info to stdout', }; # -lang # For page titles use $T2H_WORDS->{$T2H_LANG}->{...} as title. # To add a new language, supply list of titles (see $T2H_WORDS below). # and use ISO 639 language codes (see e.g. perl module Locale-Codes-1.02 # for definitions) # Default's to 'en' if not set or no @documentlanguage is specified $T2H_LANG = ''; $T2H_OPTIONS -> {lang} = { type => '=s', linkage => sub {SetDocumentLanguage($_[1])}, verbose => 'use $s as document language (ISO 639 encoding)', }; $T2H_OPTIONS -> {D} = { type => '=s', linkage => sub {$main::value{@_[1]} = 1;}, verbose => 'equivalent to Texinfo "@set $s 1"', noHelp => 1, }; $T2H_OPTIONS -> {init_file} = { type => '=s', linkage => \&LoadInitFile, verbose => 'load init file $s' }; ############################################################################## # # The following can only be set in the init file # ############################################################################## # if set, center @image by default # otherwise, do not center by default $T2H_CENTER_IMAGE = 1; # used as identation for block enclosing command @example, etc # If not empty, must be enclosed in $T2H_EXAMPLE_INDENT_CELL = ' '; # same as above, only for @small $T2H_SMALL_EXAMPLE_INDENT_CELL = ' '; # font size for @small $T2H_SMALL_FONT_SIZE = '-1'; # if non-empty, and no @..heading appeared in Top node, then # use this as header for top node/section, otherwise use value of # @settitle or @shorttitle (in that order) $T2H_TOP_HEADING = ''; # if set, use this chapter for 'Index' button, else # use first chapter whose name matches 'index' (case insensitive) $T2H_INDEX_CHAPTER = ''; # if set and $T2H_SPLIT is set, then split index pages at the next letter # after they have more than that many entries $T2H_SPLIT_INDEX = 100; # if set (e.g., to index.html) replace hrefs to this file # (i.e., to index.html) by ./ $T2H_HREF_DIR_INSTEAD_FILE = ''; ######################################################################## # Language dependencies: # To add a new language extend T2H_WORDS hash and create $T2H_<...>_WORDS hash # To redefine one word, simply do: # $T2H_WORDS->{}->{} = 'whatever' in your personal init file. # $T2H_WORDS_EN = { # titles of pages 'ToC_Title' => 'Table of Contents', 'Overview_Title' => 'Short Table of Contents', 'Index_Title' => 'Index', 'About_Title' => 'About this document', 'Footnotes_Title' => 'Footnotes', 'See' => 'See', 'see' => 'see', 'section' => 'section', # If necessary, we could extend this as follows: # # text for buttons # 'Top_Button' => 'Top', # 'ToC_Button' => 'Contents', # 'Overview_Button' => 'Overview', # 'Index_button' => 'Index', # 'Back_Button' => 'Back', # 'FastBack_Button' => 'FastBack', # 'Prev_Button' => 'Prev', # 'Up_Button' => 'Up', # 'Next_Button' => 'Next', # 'Forward_Button' =>'Forward', # 'FastWorward_Button' => 'FastForward', # 'First_Button' => 'First', # 'Last_Button' => 'Last', # 'About_Button' => 'About' }; $T2H_WORD_DE = { 'ToC_Title' => 'Inhaltsverzeichniss', 'Overview_Title' => 'Kurzes Inhaltsverzeichniss', 'Index_Title' => 'Index', 'About_Title' => 'Über dieses Dokument', 'Footnotes_Title' => 'Fußnoten', 'See' => 'Siehe', 'see' => 'siehe', 'section' => 'Abschnitt', }; $T2H_WORD_NL = { 'ToC_Title' => 'Inhoudsopgave', 'Overview_Title' => 'Korte inhoudsopgave', 'Index_Title' => 'Index', #Not sure ;-) 'About_Title' => 'No translation available!', #No translation available! 'Footnotes_Title' => 'No translation available!', #No translation available! 'See' => 'Zie', 'see' => 'zie', 'section' => 'sectie', }; $T2H_WORD_ES = { 'ToC_Title' => 'índice General', 'Overview_Title' => 'Resumen del Contenido', 'Index_Title' => 'Index', #Not sure ;-) 'About_Title' => 'No translation available!', #No translation available! 'Footnotes_Title' => 'Fußnoten', 'See' => 'Véase', 'see' => 'véase', 'section' => 'sección', }; $T2H_WORD_NO = { 'ToC_Title' => 'Innholdsfortegnelse', 'Overview_Title' => 'Kort innholdsfortegnelse', 'Index_Title' => 'Indeks', #Not sure ;-) 'About_Title' => 'No translation available!', #No translation available! 'Footnotes_Title' => 'No translation available!', 'See' => 'Se', 'see' => 'se', 'section' => 'avsnitt', }; $T2H_WORD_PT = { 'ToC_Title' => 'Sumário', 'Overview_Title' => 'Breve Sumário', 'Index_Title' => 'Índice', #Not sure ;-) 'About_Title' => 'No translation available!', #No translation available! 'Footnotes_Title' => 'No translation available!', 'See' => 'Veja', 'see' => 'veja', 'section' => 'Seção', }; $T2H_WORDS = { 'en' => $T2H_WORDS_EN, 'de' => $T2H_WORDS_DE, 'nl' => $T2H_WORDS_NL, 'es' => $T2H_WORDS_ES, 'no' => $T2H_WORDS_NO, 'pt' => $T2H_WORDS_PT }; @MONTH_NAMES_EN = ( 'January', 'February', 'March', 'April', 'May', 'June', 'July', 'August', 'September', 'October', 'November', 'December' ); @MONTH_NAMES_DE = ( 'Januar', 'Februar', 'März', 'April', 'Mai', 'Juni', 'Juli', 'August', 'September', 'Oktober', 'November', 'Dezember' ); @MONTH_NAMES_NL = ( 'Januari', 'Februari', 'Maart', 'April', 'Mei', 'Juni', 'Juli', 'Augustus', 'September', 'Oktober', 'November', 'December' ); @MONTH_NAMES_ES = ( 'enero', 'febrero', 'marzo', 'abril', 'mayo', 'junio', 'julio', 'agosto', 'septiembre', 'octubre', 'noviembre', 'diciembre' ); @MONTH_NAMES_NO = ( 'januar', 'februar', 'mars', 'april', 'mai', 'juni', 'juli', 'august', 'september', 'oktober', 'november', 'desember' ); @MONTH_NAMES_PT = ( 'Janeiro', 'Fevereiro', 'Março', 'Abril', 'Maio', 'Junho', 'Julho', 'Agosto', 'Setembro', 'Outubro', 'Novembro', 'Dezembro' ); $MONTH_NAMES = { 'en' => \@MONTH_NAMES_EN, 'de' => \@MONTH_NAMES_DE, 'es' => \@MONTH_NAMES_ES, 'nl' => \@MONTH_NAMES_NL, 'no' => \@MONTH_NAMES_NO, 'pt' => \@MONTH_NAMES_PT }; ######################################################################## # Control of Page layout: # You can make changes of the Page layout at two levels: # 1.) For small changes, it is often enough to change the value of # some global string/hash/array variables # 2.) For larger changes, reimplement one of the T2H_DEFAULT_* routines, # give them another name, and assign them to the respective # $T2H_ variable. # As a general interface, the hashes T2H_HREF, T2H_NAME, T2H_NODE hold # href, html-name, node-name of # This -- current section (resp. html page) # Top -- top page ($T2H_TOP_FILE) # Contents -- Table of contents # Overview -- Short table of contents # Index -- Index page # About -- page which explain "navigation buttons" # First -- first node # Last -- last node # # Whether or not the following hash values are set, depends on the context # (all values are w.r.t. 'This' section) # Next -- next node of texinfo # Prev -- previous node of texinfo # Up -- up node of texinfo # Forward -- next node in reading order # Back -- previous node in reading order # FastForward -- if leave node, up and next, else next node # FastBackward-- if leave node, up and prev, else prev node # # Furthermore, the following global variabels are set: # $T2H_THISDOC{title} -- title as set by @setttile # $T2H_THISDOC{fulltitle} -- full title as set by @title... # $T2H_THISDOC{subtitle} -- subtitle as set by @subtitle # $T2H_THISDOC{author} -- author as set by @author # # and pointer to arrays of lines which need to be printed by t2h_print_lines # $T2H_OVERVIEW -- lines of short table of contents # $T2H_TOC -- lines of table of contents # $T2H_TOP -- lines of Top texinfo node # $T2H_THIS_SECTION -- lines of 'This' section # # There are the following subs which control the layout: # $T2H_print_section = \&T2H_DEFAULT_print_section; $T2H_print_Top_header = \&T2H_DEFAULT_print_Top_header; $T2H_print_Top_footer = \&T2H_DEFAULT_print_Top_footer; $T2H_print_Top = \&T2H_DEFAULT_print_Top; $T2H_print_Toc = \&T2H_DEFAULT_print_Toc; $T2H_print_Overview = \&T2H_DEFAULT_print_Overview; $T2H_print_Footnotes = \&T2H_DEFAULT_print_Footnotes; $T2H_print_About = \&T2H_DEFAULT_print_About; $T2H_print_misc_header = \&T2H_DEFAULT_print_misc_header; $T2H_print_misc_footer = \&T2H_DEFAULT_print_misc_footer; $T2H_print_misc = \&T2H_DEFAULT_print_misc; $T2H_print_chapter_header = \&T2H_DEFAULT_print_chapter_header; $T2H_print_chapter_footer = \&T2H_DEFAULT_print_chapter_footer; $T2H_print_page_head = \&T2H_DEFAULT_print_page_head; $T2H_print_page_foot = \&T2H_DEFAULT_print_page_foot; $T2H_print_head_navigation = \&T2H_DEFAULT_print_head_navigation; $T2H_print_foot_navigation = \&T2H_DEFAULT_print_foot_navigation; $T2H_button_icon_img = \&T2H_DEFAULT_button_icon_img; $T2H_print_navigation = \&T2H_DEFAULT_print_navigation; $T2H_about_body = \&T2H_DEFAULT_about_body; $T2H_print_frame = \&T2H_DEFAULT_print_frame; $T2H_print_toc_frame = \&T2H_DEFAULT_print_toc_frame; ######################################################################## # Layout for html for every sections # sub T2H_DEFAULT_print_section { my $fh = shift; my $nw = t2h_print_lines($fh); print $fh '
' . "\n"; } ################################################################### # Layout of top-page I recommend that you use @ifnothtml, @ifhtml, # @html within the Top texinfo node to specify content of top-level # page. # # If you enclose everything in @ifnothtml, then title, subtitle, # author and overview is printed # T2H_HREF of Next, Prev, Up, Forward, Back are not defined # if $T2H_SPLIT then Top page is in its own html file sub T2H_DEFAULT_print_Top_header { &$T2H_print_page_head(@_) if $T2H_SPLIT; t2h_print_label(@_); # this needs to be called, otherwise no label set &$T2H_print_head_navigation(@_); } sub T2H_DEFAULT_print_Top_footer { &$T2H_print_foot_navigation(@_); &$T2H_print_page_foot(@_) if $T2H_SPLIT; } sub T2H_DEFAULT_print_Top { my $fh = shift; # for redefining navigation buttons use: # local $T2H_BUTTONS = [...]; # as it is, 'Top', 'Contents', 'Index', 'About' are printed local $T2H_BUTTONS = \@T2H_MISC_BUTTONS; &$T2H_print_Top_header($fh); if ($T2H_THIS_SECTION) { # if top-level node has content, then print it with extra header print $fh "

$T2H_NAME{Top}

" unless ($T2H_HAS_TOP_HEADING); t2h_print_lines($fh, $T2H_THIS_SECTION) } else { # top-level node is fully enclosed in @ifnothtml # print fulltitle, subtitle, author, Overview print $fh "
\n

" . join("

\n

", split(/\n/, $T2H_THISDOC{fulltitle})) . "

\n"; print $fh "

$T2H_THISDOC{subtitle}

\n" if $T2H_THISDOC{subtitle}; print $fh "$T2H_THISDOC{author}\n" if $T2H_THISDOC{author}; print $fh <

overview:

EOT t2h_print_lines($fh, $T2H_OVERVIEW); print $fh "
\n"; } &$T2H_print_Top_footer($fh); } ################################################################### # Layout of Toc, Overview, and Footnotes pages # By default, we use "normal" layout # T2H_HREF of Next, Prev, Up, Forward, Back, etc are not defined # use: local $T2H_BUTTONS = [...] to redefine navigation buttons sub T2H_DEFAULT_print_Toc { return &$T2H_print_misc(@_); } sub T2H_DEFAULT_print_Overview { return &$T2H_print_misc(@_); } sub T2H_DEFAULT_print_Footnotes { return &$T2H_print_misc(@_); } sub T2H_DEFAULT_print_About { return &$T2H_print_misc(@_); } sub T2H_DEFAULT_print_misc_header { &$T2H_print_page_head(@_) if $T2H_SPLIT; # this needs to be called, otherwise, no labels are set t2h_print_label(@_); &$T2H_print_head_navigation(@_); } sub T2H_DEFAULT_print_misc_footer { &$T2H_print_foot_navigation(@_); &$T2H_print_page_foot(@_) if $T2H_SPLIT; } sub T2H_DEFAULT_print_misc { my $fh = shift; local $T2H_BUTTONS = \@T2H_MISC_BUTTONS; &$T2H_print_misc_header($fh); print $fh "

$T2H_NAME{This}

\n"; t2h_print_lines($fh); &$T2H_print_misc_footer($fh); } ################################################################### # chapter_header and chapter_footer are only called if # T2H_SPLIT eq 'chapter' # chapter_header: after print_page_header, before print_section # chapter_footer: after print_section of last section, before print_page_footer # # If you want to get rid of navigation stuff after each section, # redefine print_section such that it does not call print_navigation, # and put print_navigation into print_chapter_header @T2H_CHAPTER_BUTTONS = ( 'FastBack', 'FastForward', ' ', 'Top', 'Contents', 'Index', 'About', ); @T2H_SECTION_BUTTONS = ( 'Back', 'Up', 'Forward', ' ', 'Top', 'Contents', 'Index', 'About', ); sub T2H_DEFAULT_print_chapter_header { #if ($T2H_SPLIT) #{ my $fh = shift; local $T2H_BUTTONS = \@T2H_CHAPTER_BUTTONS if $T2H_SPLIT ne 'section'; local $T2H_BUTTONS = \@T2H_SECTION_BUTTONS if $T2H_SPLIT eq 'section'; &$T2H_print_head_navigation($fh); #} } sub T2H_DEFAULT_print_chapter_footer { #if ($T2H_SPLIT) #{ my $fh = shift; local $T2H_BUTTONS = \@T2H_CHAPTER_BUTTONS if $T2H_SPLIT ne 'chapter'; local $T2H_BUTTONS = \@T2H_SECTION_BUTTONS if $T2H_SPLIT eq 'section'; &$T2H_print_foot_navigation($fh); #} } ################################################################### $T2H_TODAY = &pretty_date; # like "20 September 1993" sub pretty_date { local($sec, $min, $hour, $mday, $mon, $year, $wday, $yday, $isdst); ($sec, $min, $hour, $mday, $mon, $year, $wday, $yday, $isdst) = localtime(time); $year += ($year < 70) ? 2000 : 1900; # obachman: Let's do it as the Americans do return($MONTH_NAMES->{$T2H_LANG}[$mon] . ", " . $mday . " " . $year); } ################################################################### # Layout of standard header and footer # # Set the default body text, inserted between ###$T2H_BODYTEXT = 'lang="en" bgcolor="#ffffff" text="#000000" link="#0000ff" vlink="#800080" alink="#ff0000"'; $T2H_BODYTEXT = 'lang="' . $t2h_lang . '" bgcolor="#ffffff" text="#000000" link="#0000ff" vlink="#800080" alink="#ff0000"'; # text inserted after $T2H_AFTER_BODY_OPEN = ''; #text inserted before $T2H_PRE_BODY_CLOSE = ''; # this is used in footer $T2H_ADDRESS = "on $T2H_TODAY"; # this is added inside after and some META NAME stuff # can be used for <style> <script>, <meta> tags $T2H_EXTRA_HEAD = ' <script language="Javascript"> <!-- // Check the browser version. function checkVersion() { if (navigator.appVersion.charAt(0)>=3) return true; if (navigator.appVersion.charAt(0)>=4) return true; else return false; } if (checkVersion()) { homeon = new Image(); homeon.src = "images/homeon.png"; homeoff = new Image(); homeoff.src = "images/home.png"; tocon = new Image(); tocon.src = "images/tocon.png"; tocoff = new Image(); tocoff.src = "images/toc.png"; indexon = new Image(); indexon.src = "images/indexon.png"; indexoff = new Image(); indexoff.src = "images/index.png"; helpon = new Image(); helpon.src = "images/helpon.png"; helpoff = new Image(); helpoff.src = "images/help.png"; backon = new Image(); backon.src = "images/backon.png"; backoff = new Image(); backoff.src = "images/back.png"; forwardon = new Image(); forwardon.src = "images/forwardon.png"; forwardoff = new Image(); forwardoff.src = "images/forward.png"; prevon = new Image(); prevon.src = "images/prevon.png"; prevoff = new Image(); prevoff.src = "images/prev.png"; nexton = new Image(); nexton.src = "images/nexton.png"; nextoff = new Image(); nextoff.src = "images/next.png"; upon = new Image(); upon.src = "images/upon.png"; upoff = new Image(); upoff.src = "images/up.png"; } function img_act(imgName) { if (checkVersion()) { imgOn = eval(imgName + "on.src"); document [imgName].src = imgOn; } } function img_inact(imgName) { if (checkVersion()) { imgOff = eval(imgName + "off.src"); document [imgName].src = imgOff; } } // --> </script> '; sub T2H_DEFAULT_print_page_head { my $fh = shift; my $longtitle = "$T2H_THISDOC{title}: $T2H_NAME{This}"; print $fh <<EOT; <html> $T2H_DOCTYPE <!-- Created on $T2H_TODAY by $THISPROG --> <!-- $T2H_AUTHORS --> <head> <title>$longtitle $T2H_EXTRA_HEAD $T2H_AFTER_BODY_OPEN EOT } sub T2H_DEFAULT_print_page_foot { my $fh = shift; print $fh <
This document was generated $T2H_ADDRESS using
texi2html $T2H_PRE_BODY_CLOSE EOT } ################################################################### # Layout of navigation panel sub T2H_DEFAULT_print_head_navigation { my $fh = shift; &$T2H_print_navigation($fh); print $fh "
\n"; } sub T2H_DEFAULT_print_foot_navigation { my $fh = shift; my $nwords = shift; print $fh "
\n"; &$T2H_print_navigation($fh); print $fh "
\n"; } ###################################################################### # navigation panel # # specify in this array which "buttons" should appear in which order # in the navigation panel for sections; use ' ' for empty buttons (space) # buttons for misc stuff @T2H_MISC_BUTTONS = ('Top', 'Contents', 'Index', 'About'); # insert here name of icon images for buttons # Icons are used, if $T2H_ICONS and resp. value are set %T2H_ACTIVE_ICONS = ( 'Top', 'home', 'Contents', 'toc', 'Overview', '', 'Index', 'index', 'Back', 'prev', 'FastBack', 'back', 'Prev', '', 'Up', 'up', 'Next', 'next', 'Forward', 'next', 'FastForward', 'forward', 'About' , 'help', 'First', '', 'Last', '', ' ', '' ); # insert here name of icon images for these, if button is inactive %T2H_PASSIVE_ICONS = ( 'Top', 'inactive', 'Contents', 'inactive', 'Overview', 'inactive', 'Index', 'inactive', 'Back', 'inactive', 'FastBack', 'inactive', 'Prev', 'inactive', 'Up', 'inactive', 'Next', 'inactive', 'Forward', 'inactive', 'FastForward', 'inactive', 'About', 'inactive', 'First', 'inactive', 'Last', 'inactive', ); # how to create IMG tag sub T2H_DEFAULT_button_icon_img { my $button = shift; my $icon = shift; my $name = shift; return qq{$button: $name}; } # Names of text as alternative for icons %T2H_NAVIGATION_TEXT = ( 'Top', 'Top', 'Contents', 'Contents', 'Overview', 'Overview', 'Index', 'Index', ' ', '   ', 'Back', ' < ', 'FastBack', ' << ', 'Prev', 'Prev', 'Up', ' Up ', 'Next', 'Next', 'Forward', ' > ', 'FastForward', ' >> ', 'About', ' ? ', 'First', ' |< ', 'Last', ' >| ' ); sub T2H_DEFAULT_print_navigation { my $fh = shift; my $spacing = 1; print $fh "\n"; print $fh "\n"; for $button (@$T2H_BUTTONS) { print $fh "\n"; } print $fh "\n"; print $fh "
"; if (ref($button) eq 'CODE') { &$button($fh, 1); } elsif ($button eq ' ') { # handle space button print $fh " "; } elsif ($T2H_HREF{$button}) { # button is active print $fh $T2H_ACTIVE_ICONS{$button} ? # use icon ? t2h_anchor('', $T2H_HREF{$button}, # yes &$T2H_button_icon_img($button, $T2H_ACTIVE_ICONS{$button}, $T2H_NAME{$button}), 0, "onMouseover=\"img_act('" . $T2H_ACTIVE_ICONS{$button} ."')\" " . "onMouseout=\"img_inact('" . $T2H_ACTIVE_ICONS{$button} ."')\" ") : ""; } else { # button is passive print $fh $T2H_PASSIVE_ICONS{$button} ? &$T2H_button_icon_img($button, $T2H_PASSIVE_ICONS{$button}, $T2H_NAME{$button}) : ""; } print $fh "
\n"; } ###################################################################### # Frames: this is from "Richard Y. Kim" # Should be improved to be more conforming to other _print* functions sub T2H_DEFAULT_print_frame { my $fh = shift; print $fh < $T2H_THISDOC{title} EOT } sub T2H_DEFAULT_print_toc_frame { my $fh = shift; &$T2H_print_page_head($fh); print $fh <Content EOT print $fh map {s/href=/target=\"main\" href=/i; $_;} @stoc_lines; print $fh "\n"; } ###################################################################### # About page # # T2H_PRE_ABOUT might be a function $T2H_PRE_ABOUT = <texi2html

EOT $T2H_AFTER_ABOUT = ''; sub T2H_DEFAULT_about_body { my $about; if (ref($T2H_PRE_ABOUT) eq 'CODE') { $about = &$T2H_PRE_ABOUT(); } else { $about = $T2H_PRE_ABOUT; } $about .= <

EOT for $button (@T2H_SECTION_BUTTONS) { next if $button eq ' ' || ref($button) eq 'CODE'; $about .= < EOT } $about .= <

where the Example assumes that the current position is at Subsubsection One-Two-Three of a document of the following structure:
  • 1. Section One
    • 1.1 Subsection One-One
      • ...
    • 1.2 Subsection One-Two
      • 1.2.1 Subsubsection One-Two-One
      • 1.2.2 Subsubsection One-Two-Two
      • 1.2.3 Subsubsection One-Two-Three     <== Current Position
      • 1.2.4 Subsubsection One-Two-Four
    • 1.3 Subsection One-Three
      • ...
    • 1.4 Subsection One-Four
$T2H_AFTER_ABOUT EOT return $about; } %T2H_BUTTONS_GOTO = ( 'Top', 'cover (top) of document', 'Contents', 'table of contents', 'Overview', 'short table of contents', 'Index', 'concept index', 'Back', 'previous section in reading order', 'FastBack', 'previous or up-and-previous section ', 'Prev', 'previous section same level', 'Up', 'up section', 'Next', 'next section same level', 'Forward', 'next section in reading order', 'FastForward', 'next or up-and-next section', 'About' , 'this page', 'First', 'first section in reading order', 'Last', 'last section in reading order', ); # # Options controlling Titles, File-Names, Tracing and Sectioning # $TITLE = ''; $SHORTEXTN = 0; $LONG_TITLES = 0; $DESTDIR = ''; # should be overwritten by cmd-line argument $NO_SUBDIR = 0;# should be overwritten by cmd-line argument $PREFIX = ''; # should be overwritten by cmd-line argument $AUTO_PREFIX = 0; # this is needed, so that prefix settings are used $AUTO_LINK = 0; $SPLIT = 0; $MAX_LINK_DEPTH = 0; $TMP = ''; # should be overwritten by cmd-line argument $DEBUG = 0; $VERBOSE = 1; # # Options controlling Extensions and Special Features # $HTML_VERSION = "3.2"; $TEXDEFS = 1; # we absolutely need that $EXTERNAL_FILE = ''; $SCALABLE_FONTS = 1; $NO_SIMPLE_MATH = 1; $LOCAL_ICONS = 1; $SHORT_INDEX = 0; $NO_FOOTNODE = 1; $ADDRESS = ''; $INFO = ''; # # Switches controlling Image Generation # $ASCII_MODE = 0; $NOLATEX = 0; $EXTERNAL_IMAGES = 0; $PS_IMAGES = 0; $NO_IMAGES = 0; $IMAGES_ONLY = 0; $REUSE = 2; $ANTI_ALIAS = 1; $ANTI_ALIAS_TEXT = 1; # #Switches controlling Navigation Panels # $NO_NAVIGATION = 1; $ADDRESS = ''; $INFO = 0; # 0 = do not make a "About this document..." section # #Switches for Linking to other documents # # actuall -- we don't care $MAX_SPLIT_DEPTH = 0; # Stop making separate files at this depth $MAX_LINK_DEPTH = 0; # Stop showing child nodes at this depth $NOLATEX = 0; # 1 = do not pass unknown environments to Latex $EXTERNAL_IMAGES = 0; # 1 = leave the images outside the document $ASCII_MODE = 0; # 1 = do not use any icons or internal images # 1 = use links to external postscript images rather than inlined bitmap # images. $PS_IMAGES = 0; $SHOW_SECTION_NUMBERS = 0; ### Other global variables ############################################### $CHILDLINE = ""; # This is the line width measured in pixels and it is used to right justify # equations and equation arrays; $LINE_WIDTH = 500; # Used in conjunction with AUTO_NAVIGATION $WORDS_IN_PAGE = 300; # Affects ONLY the way accents are processed $default_language = 'english'; # The value of this variable determines how many words to use in each # title that is added to the navigation panel (see below) # $WORDS_IN_NAVIGATION_PANEL_TITLES = 0; # This number will determine the size of the equations, special characters, # and anything which will be converted into an inlined image # *except* "image generating environments" such as "figure", "table" # or "minipage". # Effective values are those greater than 0. # Sensible values are between 0.1 - 4. $MATH_SCALE_FACTOR = 1.5; # This number will determine the size of # image generating environments such as "figure", "table" or "minipage". # Effective values are those greater than 0. # Sensible values are between 0.1 - 4. $FIGURE_SCALE_FACTOR = 1.6; # If both of the following two variables are set then the "Up" button # of the navigation panel in the first node/page of a converted document # will point to $EXTERNAL_UP_LINK. $EXTERNAL_UP_TITLE should be set # to some text which describes this external link. $EXTERNAL_UP_LINK = ""; $EXTERNAL_UP_TITLE = ""; # If this is set then the resulting HTML will look marginally better if viewed # with Netscape. $NETSCAPE_HTML = 1; # Valid paper sizes are "letter", "legal", "a4","a3","a2" and "a0" # Paper sizes has no effect other than in the time it takes to create inlined # images and in whether large images can be created at all ie # - larger paper sizes *MAY* help with large image problems # - smaller paper sizes are quicker to handle $PAPERSIZE = "a4"; # Replace "english" with another language in order to tell LaTeX2HTML that you # want some generated section titles (eg "Table of Contents" or "References") # to appear in a different language. Currently only "english" and "french" # is supported but it is very easy to add your own. See the example in the # file "latex2html.config" $TITLES_LANGUAGE = "english"; 1; # This must be the last non-comment line # End File texi2html.init ###################################################################### #+++############################################################################ # # # Initialization # # Pasted content of File $(srcdir)/MySimple.pm: Command-line processing # # # #---############################################################################ # leave this within comments, and keep the require statement # This way, you can directly run texi2html.pl, if $ENV{T2H_HOME}/texi2html.init # exists. # package Getopt::MySimple; # Name: # Getopt::MySimple. # # Documentation: # POD-style (incomplete) documentation is in file MySimple.pod # # Tabs: # 4 spaces || die. # # Author: # Ron Savage rpsavage@ozemail.com.au. # 1.00 19-Aug-97 Initial version. # 1.10 13-Oct-97 Add arrays of switches (eg '=s@'). # 1.20 3-Dec-97 Add 'Help' on a per-switch basis. # 1.30 11-Dec-97 Change 'Help' to 'verbose'. Make all hash keys lowercase. # 1.40 10-Nov-98 Change width of help report. Restructure tests. # 1-Jul-00 Modifications for Texi2html # -------------------------------------------------------------------------- # Locally modified by obachman (Display type instead of env, order by cmp) # $Id: MySimple.pm,v 1.1 2000/07/03 08:44:13 obachman Exp $ # use strict; # no strict 'refs'; use vars qw(@EXPORT @EXPORT_OK @ISA); use vars qw($fieldWidth $opt $VERSION); use Exporter(); use Getopt::Long; @ISA = qw(Exporter); @EXPORT = qw(); @EXPORT_OK = qw($opt); # An alias for $self -> {'opt'}. # -------------------------------------------------------------------------- $fieldWidth = 20; $VERSION = '1.41'; # -------------------------------------------------------------------------- sub byOrder { my($self) = @_; return uc($a) cmp (uc($b)); } # -------------------------------------------------------------------------- sub dumpOptions { my($self) = @_; print 'Option', ' ' x ($fieldWidth - length('Option') ), "Value\n"; for (sort byOrder keys(%{$self -> {'opt'} }) ) { print "-$_", ' ' x ($fieldWidth - (1 + length) ), "${$self->{'opt'} }{$_}\n"; } print "\n"; } # End of dumpOptions. # -------------------------------------------------------------------------- # Return: # 0 -> Error. # 1 -> Ok. sub getOptions { push(@_, 0) if ($#_ == 2); # Default for $ignoreCase is 0. push(@_, 1) if ($#_ == 3); # Default for $helpThenExit is 1. my($self, $default, $helpText, $versionText, $helpThenExit, $versionThenExit, $ignoreCase) = @_; $helpThenExit = 1 unless (defined($helpThenExit)); $versionThenExit = 1 unless (defined($versionThenExit)); $ignoreCase = 0 unless (defined($ignoreCase)); $self -> {'default'} = $default; $self -> {'helpText'} = $helpText; $self -> {'versionText'} = $versionText; $Getopt::Long::ignorecase = $ignoreCase; unless (defined($self -> {'default'}{'help'})) { $self -> {'default'}{'help'} = { type => ':i', default => '', linkage => sub {$self->helpOptions($_[1]); exit (0) if $helpThenExit;}, verbose => "print help and exit" }; } unless (defined($self -> {'default'}{'version'})) { $self -> {'default'}{'version'} = { type => '', default => '', linkage => sub {print $self->{'versionText'}; exit (0) if versionTheExit;}, verbose => "print version and exit" }; } for (keys(%{$self -> {'default'} }) ) { my $type = ${$self -> {'default'} }{$_}{'type'}; push(@{$self -> {'type'} }, "$_$type"); $self->{'opt'}->{$_} = ${$self -> {'default'} }{$_}{'linkage'} if ${$self -> {'default'} }{$_}{'linkage'}; } my($result) = &GetOptions($self -> {'opt'}, @{$self -> {'type'} }); return $result unless $result; for (keys(%{$self -> {'default'} }) ) { if (! defined(${$self -> {'opt'} }{$_})) #{ { ${$self -> {'opt'} }{$_} = ${$self -> {'default'} }{$_}{'default'}; } } $result; } # End of getOptions. # -------------------------------------------------------------------------- sub helpOptions { my($self) = shift; my($noHelp) = shift; $noHelp = 0 unless $noHelp; my($optwidth, $typewidth, $defaultwidth, $maxlinewidth, $valind, $valwidth) = (10, 5, 9, 78, 4, 11); print "$self->{'helpText'}" if ($self -> {'helpText'}); print ' Option', ' ' x ($optwidth - length('Option') -1 ), 'Type', ' ' x ($typewidth - length('Type') + 1), 'Default', ' ' x ($defaultwidth - length('Default') ), "Description\n"; for (sort byOrder keys(%{$self -> {'default'} }) ) { my($line, $help, $option, $val); $option = $_; next if ${$self->{'default'} }{$_}{'noHelp'} && ${$self->{'default'} }{$_}{'noHelp'} > $noHelp; $line = " -$_ " . ' ' x ($optwidth - (2 + length) ) . "${$self->{'default'} }{$_}{'type'} ". ' ' x ($typewidth - (1+length(${$self -> {'default'} }{$_}{'type'}) )); $val = ${$self->{'default'} }{$_}{'linkage'}; if ($val) { if (ref($val) eq 'SCALAR') { $val = $$val; } else { $val = ''; } } else { $val = ${$self->{'default'} }{$_}{'default'}; } $line .= "$val "; $line .= ' ' x ($optwidth + $typewidth + $defaultwidth + 1 - length($line)); if (defined(${$self -> {'default'} }{$_}{'verbose'}) && ${$self -> {'default'} }{$_}{'verbose'} ne '') { $help = "${$self->{'default'} }{$_}{'verbose'}"; } else { $help = ' '; } if ((length("$line") + length($help)) < $maxlinewidth) { print $line , $help, "\n"; } else { print $line, "\n", ' ' x $valind, $help, "\n"; } for $val (sort byOrder keys(%{${$self->{'default'}}{$option}{'values'}})) { print ' ' x ($valind + 2); print $val, ' ', ' ' x ($valwidth - length($val) - 2); print ${$self->{'default'}}{$option}{'values'}{$val}, "\n"; } } print <| ! no argument: variable is set to 1 on -foo (or, to 0 on -nofoo) =s | :s mandatory (or, optional) string argument =i | :i mandatory (or, optional) integer argument EOT } # End of helpOptions. #------------------------------------------------------------------- sub new { my($class) = @_; my($self) = {}; $self -> {'default'} = {}; $self -> {'helpText'} = ''; $self -> {'opt'} = {}; $opt = $self -> {'opt'}; # An alias for $self -> {'opt'}. $self -> {'type'} = (); return bless $self, $class; } # End of new. # -------------------------------------------------------------------------- 1; # End MySimple.pm package main; #+++############################################################################ # # # Constants # # # #---############################################################################ $DEBUG_TOC = 1; $DEBUG_INDEX = 2; $DEBUG_BIB = 4; $DEBUG_GLOSS = 8; $DEBUG_DEF = 16; $DEBUG_HTML = 32; $DEBUG_USER = 64; $BIBRE = '\[[\w\/-]+\]'; # RE for a bibliography reference $FILERE = '[\/\w.+-]+'; # RE for a file name $VARRE = '[^\s\{\}]+'; # RE for a variable name $NODERE = '[^,:]+'; # RE for a node name $NODESRE = '[^:]+'; # RE for a list of node names $ERROR = "***"; # prefix for errors $WARN = "**"; # prefix for warnings # program home page $PROTECTTAG = "_ThisIsProtected_"; # tag to recognize protected sections $CHAPTEREND = "\n"; # to know where a chpater ends $SECTIONEND = "\n"; # to know where section ends $TOPEND = "\n"; # to know where top ends # # pre-defined indices # $index_properties = { 'c' => { name => 'cp'}, 'f' => { name => 'fn', code => 1}, 'v' => { name => 'vr', code => 1}, 'k' => { name => 'ky', code => 1}, 'p' => { name => 'pg', code => 1}, 't' => { name => 'tp', code => 1} }; %predefined_index = ( 'cp', 'c', 'fn', 'f', 'vr', 'v', 'ky', 'k', 'pg', 'p', 'tp', 't', ); # # valid indices # %valid_index = ( 'c', 1, 'f', 1, 'v', 1, 'k', 1, 'p', 1, 't', 1, ); # # texinfo section names to level # %sec2level = ( 'top', 0, 'chapter', 1, 'unnumbered', 1, 'majorheading', 1, 'chapheading', 1, 'appendix', 1, 'section', 2, 'unnumberedsec', 2, 'heading', 2, 'appendixsec', 2, 'appendixsection', 2, 'subsection', 3, 'unnumberedsubsec', 3, 'subheading', 3, 'appendixsubsec', 3, 'subsubsection', 4, 'unnumberedsubsubsec', 4, 'subsubheading', 4, 'appendixsubsubsec', 4, ); # # accent map, TeX command to ISO name # %accent_map = ( '"', 'uml', '~', 'tilde', '^', 'circ', '`', 'grave', '\'', 'acute', ); # # texinfo "simple things" (@foo) to HTML ones # %simple_map = ( # cf. makeinfo.c "*", "
", # HTML+ " ", " ", "\t", " ", "-", "­", # soft hyphen "\n", "\n", "|", "", 'tab', '<\/td>
Button Name Go to From 1.2.3 go to
EOT $about .= ($T2H_ICONS && $T2H_ACTIVE_ICONS{$button} ? &$T2H_button_icon_img($button, $T2H_ACTIVE_ICONS{$button}) : " [" . $T2H_NAVIGATION_TEXT{$button} . "] "); $about .= < $button $T2H_BUTTONS_GOTO{$button}
', # spacing commands ":", "", "!", "!", "?", "?", ".", ".", "-", "", ); # # texinfo "things" (@foo{}) to HTML ones # %things_map = ( 'TeX', 'TeX', 'br', '

', # paragraph break 'bullet', '*', 'copyright', '(C)', 'dots', '...<\/small>', 'enddots', '....<\/small>', 'equiv', '==', 'error', 'error-->', 'expansion', '==>', 'minus', '-', 'point', '-!-', 'print', '-|', 'result', '=>', 'today', $T2H_TODAY, 'aa', 'å', 'AA', 'Å', 'ae', 'æ', 'oe', 'œ', 'AE', 'Æ', 'OE', 'Œ', 'o', 'ø', 'O', 'Ø', 'ss', 'ß', 'l', '\/l', 'L', '\/L', 'exclamdown', '¡', 'questiondown', '¿', 'pounds', '£' ); # # texinfo styles (@foo{bar}) to HTML ones # %style_map = ( 'acronym', '&do_acronym', 'asis', '', 'b', 'B', 'cite', 'CITE', 'code', 'CODE', 'command', 'CODE', 'ctrl', '&do_ctrl', # special case 'dfn', 'EM', # DFN tag is illegal in the standard 'dmn', '', # useless 'email', '&do_email', # insert a clickable email address 'emph', 'EM', 'env', 'CODE', 'file', '"TT', # will put quotes, cf. &apply_style 'i', 'I', 'kbd', 'KBD', 'key', 'KBD', 'math', '&do_math', 'option', '"SAMP', # will put quotes, cf. &apply_style 'r', '', # unsupported 'samp', '"SAMP', # will put quotes, cf. &apply_style 'sc', '&do_sc', # special case 'strong', 'STRONG', 't', 'TT', 'titlefont', '', # useless 'uref', '&do_uref', # insert a clickable URL 'url', '&do_url', # insert a clickable URL 'var', 'VAR', 'w', '', # unsupported 'H', '&do_accent', 'dotaccent', '&do_accent', 'ringaccent','&do_accent', 'tieaccent', '&do_accent', 'u','&do_accent', 'ubaraccent','&do_accent', 'udotaccent','&do_accent', 'v', '&do_accent', ',', '&do_accent', 'dotless', '&do_accent' ); # # texinfo format (@foo/@end foo) to HTML ones # %format_map = ( 'quotation', 'blockquote', # lists 'itemize', 'ul', 'enumerate', 'ol', # poorly supported 'flushleft', 'pre', 'flushright', 'pre', ); # # an eval of these $complex_format_map->{what}->[0] yields beginning # an eval of these $complex_format_map->{what}->[1] yieleds end $complex_format_map = { example => [ q{"$T2H_EXAMPLE_INDENT_CELL
"},
  q{'
'} ], smallexample => [ q{"$T2H_SMALL_EXAMPLE_INDENT_CELL
"},
  q{'
'} ], display => [ q{"$T2H_EXAMPLE_INDENT_CELL
'},
  q{'
'} ], smalldisplay => [ q{"$T2H_SMALL_EXAMPLE_INDENT_CELL
'},
  q{'
'} ] }; $complex_format_map->{lisp} = $complex_format_map->{example}; $complex_format_map->{smalllisp} = $complex_format_map->{smallexample}; $complex_format_map->{format} = $complex_format_map->{display}; $complex_format_map->{smallformat} = $complex_format_map->{smalldisplay}; # # texinfo definition shortcuts to real ones # %def_map = ( # basic commands 'deffn', 0, 'defvr', 0, 'deftypefn', 0, 'deftypevr', 0, 'defcv', 0, 'defop', 0, 'deftp', 0, # basic x commands 'deffnx', 0, 'defvrx', 0, 'deftypefnx', 0, 'deftypevrx', 0, 'defcvx', 0, 'defopx', 0, 'deftpx', 0, # shortcuts 'defun', 'deffn Function', 'defmac', 'deffn Macro', 'defspec', 'deffn {Special Form}', 'defvar', 'defvr Variable', 'defopt', 'defvr {User Option}', 'deftypefun', 'deftypefn Function', 'deftypevar', 'deftypevr Variable', 'defivar', 'defcv {Instance Variable}', 'deftypeivar', 'defcv {Instance Variable}', # NEW: FIXME 'defmethod', 'defop Method', 'deftypemethod', 'defop Method', # NEW:FIXME # x shortcuts 'defunx', 'deffnx Function', 'defmacx', 'deffnx Macro', 'defspecx', 'deffnx {Special Form}', 'defvarx', 'defvrx Variable', 'defoptx', 'defvrx {User Option}', 'deftypefunx', 'deftypefnx Function', 'deftypevarx', 'deftypevrx Variable', 'defivarx', 'defcvx {Instance Variable}', 'defmethodx', 'defopx Method', ); # # things to skip # %to_skip = ( # comments 'c', 1, 'comment', 1, 'ifhtml', 1, 'end ifhtml', 1, # useless 'detailmenu', 1, 'direntry', 1, 'contents', 1, 'shortcontents', 1, 'summarycontents', 1, 'footnotestyle', 1, 'end ifclear', 1, 'end ifset', 1, 'titlepage', 1, 'end titlepage', 1, # unsupported commands (formatting) 'afourpaper', 1, 'cropmarks', 1, 'finalout', 1, 'headings', 1, 'sp', 1, 'need', 1, 'page', 1, 'setchapternewpage', 1, 'everyheading', 1, 'everyfooting', 1, 'evenheading', 1, 'evenfooting', 1, 'oddheading', 1, 'oddfooting', 1, 'smallbook', 1, 'vskip', 1, 'filbreak', 1, 'paragraphindent', 1, # unsupported formats 'cartouche', 1, 'end cartouche', 1, 'group', 1, 'end group', 1, ); #+++############################################################################ # # # Argument parsing, initialisation # # # #---############################################################################ # # flush stdout and stderr after every write # select(STDERR); $| = 1; select(STDOUT); $| = 1; %value = (); # hold texinfo variables, see also -D $use_bibliography = 1; $use_acc = 1; # # called on -init-file sub LoadInitFile { my $init_file = shift; # second argument is value of options $init_file = shift; if (-f $init_file) { print "# reading initialization file from $init_file\n" if ($T2H_VERBOSE); require($init_file); } else { print "$ERROR Error: can't read init file $int_file\n"; $init_file = ''; } } # # called on -lang sub SetDocumentLanguage { my $lang = shift; if (! exists($T2H_WORDS->{$lang})) { warn "$ERROR: Language specs for '$lang' do not exists. Reverting to '" . ($T2H_LANG ? T2H_LANG : "en") . "'\n"; } else { print "# using '$lang' as document language\n" if ($T2H_VERBOSE); $T2H_LANG = $lang; } } ## ## obsolete cmd line options ## $T2H_OBSOLETE_OPTIONS -> {'no-section_navigation'} = { type => '!', linkage => sub {$main::T2H_SECTION_NAVIGATION = 0;}, verbose => 'obsolete, use -nosec_nav', noHelp => 2, }; $T2H_OBSOLETE_OPTIONS -> {use_acc} = { type => '!', linkage => \$use_acc, verbose => 'obsolete', noHelp => 2 }; $T2H_OBSOLETE_OPTIONS -> {expandinfo} = { type => '!', linkage => sub {$main::T2H_EXPAND = 'info';}, verbose => 'obsolete, use "-expand info" instead', noHelp => 2, }; $T2H_OBSOLETE_OPTIONS -> {expandtex} = { type => '!', linkage => sub {$main::T2H_EXPAND = 'tex';}, verbose => 'obsolete, use "-expand tex" instead', noHelp => 2, }; $T2H_OBSOLETE_OPTIONS -> {monolithic} = { type => '!', linkage => sub {$main::T2H_SPLIT = '';}, verbose => 'obsolete, use "-split no" instead', noHelp => 2 }; $T2H_OBSOLETE_OPTIONS -> {split_node} = { type => '!', linkage => sub{$main::T2H_SPLIT = 'section';}, verbose => 'obsolete, use "-split section" instead', noHelp => 2, }; $T2H_OBSOLETE_OPTIONS -> {split_chapter} = { type => '!', linkage => sub{$main::T2H_SPLIT = 'chapter';}, verbose => 'obsolete, use "-split chapter" instead', noHelp => 2, }; $T2H_OBSOLETE_OPTIONS -> {no_verbose} = { type => '!', linkage => sub {$main::T2H_VERBOSE = 0;}, verbose => 'obsolete, use -noverbose instead', noHelp => 2, }; $T2H_OBSOLETE_OPTIONS -> {output_file} = { type => '=s', linkage => sub {$main::T2H_OUT = @_[1]; $T2H_SPLIT = '';}, verbose => 'obsolete, use -out_file instead', noHelp => 2 }; $T2H_OBSOLETE_OPTIONS -> {section_navigation} = { type => '!', linkage => \$T2H_SECTION_NAVIGATION, verbose => 'obsolete, use -sec_nav instead', noHelp => 2, }; $T2H_OBSOLETE_OPTIONS -> {verbose} = { type => '!', linkage => \$T2H_VERBOSE, verbose => 'obsolete, use -Verbose instead', noHelp => 2 }; # read initialzation from $sysconfdir/texi2htmlrc or $HOME/.texi2htmlrc my $home = $ENV{HOME}; defined($home) or $home = ''; foreach $i ('/usr/local/etc/texi2htmlrc', "$home/.texi2htmlrc") { if (-f $i) { print "# reading initialization file from $i\n" if ($T2H_VERBOSE); require($i); } } #+++############################################################################ # # # parse command-line options # # #---############################################################################ $T2H_USAGE_TEXT = <getOptions($T2H_OPTIONS, $T2H_USAGE_TEXT, "$THISVERSION\n")) { print $Configure_failed if $Configure_failed; die $T2H_FAILURE_TEXT; } if (@ARGV > 1) { eval {Getopt::Long::Configure("no_pass_through");}; if (! $options->getOptions($T2H_OBSOLETE_OPTIONS, $T2H_USAGE_TEXT, "$THISVERSION\n")) { print $Configure_failed if $Configure_failed; die $T2H_FAILURE_TEXT; } } if ($T2H_CHECK) { die "Need file to check\n$T2H_FAILURE_TEXT" unless @ARGV > 0; ✓ exit; } #+++############################################################################ # # # evaluation of cmd line options # # #---############################################################################ $T2H_EXPAND = "html" if $T2H_EXPAND eq "none"; foreach $i ('info', 'html', 'tex') { if ($T2H_EXPAND eq $i) { $to_skip{"if$i"} = 1; $to_skip{"end if$i"} = 1; } else { $to_skip{"ifnot$i"} = 1; $to_skip{"end ifnot$i"} = 1; } } $T2H_INVISIBLE_MARK = '' if $T2H_INVISIBLE_MARK eq 'xbm'; # # file name buisness # die "Need exactly one file to translate\n$T2H_FAILURE_TEXT" unless @ARGV == 1; $docu = shift(@ARGV); if ($docu =~ /.*\//) { chop($docu_dir = $&); $docu_name = $'; } else { $docu_dir = '.'; $docu_name = $docu; } unshift(@T2H_INCLUDE_DIRS, $docu_dir); $docu_name =~ s/\.te?x(i|info)?$//; # basename of the document $docu_name = $T2H_PREFIX if ($T2H_PREFIX); # subdir if ($T2H_SUBDIR && ! $T2H_OUT) { $T2H_SUBDIR =~ s|/*$||; unless (-d "$T2H_SUBDIR" && -w "$T2H_SUBDIR") { if ( mkdir($T2H_SUBDIR, oct(755))) { print "# created directory $T2H_SUBDIR\n" if ($T2H_VERBOSE); } else { warn "$ERROR can't create directory $T2H_SUBDIR. Put results into current directory\n"; $T2H_SUBDIR = ''; } } } if ($T2H_SUBDIR && ! $T2H_OUT) { $docu_rdir = "$T2H_SUBDIR/"; print "# putting result files into directory $docu_rdir\n" if ($T2H_VERBOSE); } else { if ($T2H_OUT && $T2H_OUT =~ m|(.*)/|) { $docu_rdir = "$1/"; print "# putting result files into directory $docu_rdir\n" if ($T2H_VERBOSE); } else { print "# putting result files into current directory \n" if ($T2H_VERBOSE); $docu_rdir = ''; } } # extension if ($T2H_SHORTEXTN) { $docu_ext = "htm"; } else { $docu_ext = "html"; } if ($T2H_TOP_FILE =~ /\..*$/) { $T2H_TOP_FILE = $`.".$docu_ext"; } # result files if (! $T2H_OUT && ($T2H_SPLIT =~ /section/i || $T2H_SPLIT =~ /node/i)) { $T2H_SPLIT = 'section'; } elsif (! $T2H_OUT && $T2H_SPLIT =~ /chapter/i) { $T2H_SPLIT = 'chapter' } else { undef $T2H_SPLIT; } $docu_doc = "$docu_name.$docu_ext"; # document's contents $docu_doc_file = "$docu_rdir$docu_doc"; if ($T2H_SPLIT) { $docu_toc = $T2H_TOC_FILE || "${docu_name}_toc.$docu_ext"; # document's table of contents $docu_stoc = "${docu_name}_ovr.$docu_ext"; # document's short toc $docu_foot = "${docu_name}_fot.$docu_ext"; # document's footnotes $docu_about = "${docu_name}_abt.$docu_ext"; # about this document $docu_top = $T2H_TOP_FILE || $docu_doc; } else { if ($T2H_OUT) { $docu_doc = $T2H_OUT; $docu_doc =~ s|.*/||; } $docu_toc = $docu_foot = $docu_stoc = $docu_about = $docu_top = $docu_doc; } $docu_toc_file = "$docu_rdir$docu_toc"; $docu_stoc_file = "$docu_rdir$docu_stoc"; $docu_foot_file = "$docu_rdir$docu_foot"; $docu_about_file = "$docu_rdir$docu_about"; $docu_top_file = "$docu_rdir$docu_top"; $docu_frame_file = "$docu_rdir${docu_name}_frame.$docu_ext"; $docu_toc_frame_file = "$docu_rdir${docu_name}_toc_frame.$docu_ext"; # # variables # $value{'html'} = 1; # predefine html (the output format) $value{'texi2html'} = $THISVERSION; # predefine texi2html (the translator) # _foo: internal to track @foo foreach ('_author', '_title', '_subtitle', '_settitle', '_setfilename', '_shorttitle') { $value{$_} = ''; # prevent -w warnings } %node2sec = (); # node to section name %sec2node = (); # section to node name %sec2number = (); # section to number %number2sec = (); # number to section %idx2node = (); # index keys to node %node2href = (); # node to HREF %node2next = (); # node to next %node2prev = (); # node to prev %node2up = (); # node to up %bib2href = (); # bibliography reference to HREF %gloss2href = (); # glossary term to HREF @sections = (); # list of sections %tag2pro = (); # protected sections # # initial indexes # $bib_num = 0; $foot_num = 0; $gloss_num = 0; $idx_num = 0; $sec_num = 0; $doc_num = 0; $html_num = 0; # # can I use ISO8879 characters? (HTML+) # if ($T2H_USE_ISO) { $things_map{'bullet'} = "•"; $things_map{'copyright'} = "©"; $things_map{'dots'} = "…"; $things_map{'equiv'} = "≡"; $things_map{'expansion'} = "→"; $things_map{'point'} = "∗"; $things_map{'result'} = "⇒"; } print "# reading from $docu\n" if $T2H_VERBOSE; #+++############################################################################ # # # Pass 1: read source, handle command, variable, simple substitution # # # #---############################################################################ @lines = (); # whole document @toc_lines = (); # table of contents @stoc_lines = (); # table of contents $curlevel = 0; # current level in TOC $node = ''; # current node name $node_next = ''; # current node next name $node_prev = ''; # current node prev name $node_up = ''; # current node up name $in_table = 0; # am I inside a table $table_type = ''; # type of table ('', 'f', 'v', 'multi') @tables = (); # nested table support $in_bibliography = 0; # am I inside a bibliography $in_glossary = 0; # am I inside a glossary $in_top = 0; # am I inside the top node $has_top = 0; # did I see a top node? $has_top_command = 0; # did I see @top for automatic pointers? $in_pre = 0; # am I inside a preformatted section $in_list = 0; # am I inside a list $in_html = 0; # am I inside an HTML section $first_line = 1; # is it the first line $dont_html = 0; # don't protect HTML on this line $deferred_ref = ''; # deferred reference for indexes @html_stack = (); # HTML elements stack $html_element = ''; # current HTML element &html_reset; %macros = (); # macros # build code for simple substitutions # the maps used (%simple_map and %things_map) MUST be aware of this # watch out for regexps, / and escaped characters! $subst_code = ''; foreach (keys(%simple_map)) { ($re = $_) =~ s/(\W)/\\$1/g; # protect regexp chars $subst_code .= "s/\\\@$re/$simple_map{$_}/g;\n"; } foreach (keys(%things_map)) { $subst_code .= "s/\\\@$_\\{\\}/$things_map{$_}/g;\n"; } if ($use_acc) { # accentuated characters foreach (keys(%accent_map)) { if ($_ eq "`") { $subst_code .= "s/$;3"; } elsif ($_ eq "'") { $subst_code .= "s/$;4"; } else { $subst_code .= "s/\\\@\\$_"; } $subst_code .= "([a-z])/&\${1}$accent_map{$_};/gi;\n"; } } eval("sub simple_substitutions { $subst_code }"); &init_input; INPUT_LINE: while ($_ = &next_line) { # # remove \input on the first lines only # if ($first_line) { next if /^\\input/; $first_line = 0; } # non-@ substitutions cf. texinfmt.el # # parse texinfo tags # $tag = ''; $end_tag = ''; if (/^\s*\@end\s+(\w+)\b/) { $end_tag = $1; } elsif (/^\s*\@(\w+)\b/) { $tag = $1; } # # handle @html / @end html # if ($in_html) { if ($end_tag eq 'html') { $in_html = 0; } else { $tag2pro{$in_html} .= $_; } next; } elsif ($tag eq 'html') { $in_html = $PROTECTTAG . ++$html_num; push(@lines, $in_html); next; } # # try to remove inlined comments # syntax from tex-mode.el comment-start-skip # s/((^|[^\@])(\@\@)*)\@c(omment | |\{|$).*/$1/; # Sometimes I use @c right at the end of a line ( to suppress the line feed ) # s/((^|[^\@])(\@\@)*)\@c(omment)?$/$1/; # s/((^|[^\@])(\@\@)*)\@c(omment)? .*/$1/; # s/(.*)\@c{.*?}(.*)/$1$2/; # s/(.*)\@comment{.*?}(.*)/$1$2/; # s/^(.*)\@c /$1/; # s/^(.*)\@comment /$1/; ############################################################# # value substitution before macro expansion, so that # it works in macro arguments s/\@value{($VARRE)}/$value{$1}/eg; ############################################################# # macro substitution while (/\@(\w+)/g) { if (exists($macros->{$1})) { my $before = $`; my $name = $1; my $after = $'; my @args; my $args; if ($after =~ /^\s*{(.*?[^\\])}(.*)/) { $args = $1; $after = $2; } elsif (@{$macros->{$name}->{Args}} == 1) { $args = $after; $args =~ s/^\s*//; $args =~ s/\s*$//; $after = ''; } $args =~ s|\\\\|\\|g; $args =~ s|\\{|{|g; $args =~ s|\\}|}|g; if (@{$macros->{$name}->{Args}} > 1) { $args =~ s/(^|[^\\]),/$1$;/g ; $args =~ s|\\,|,|g; @args = split(/$;\s*/, $args) if (@{$macros->{$name}->{Args}} > 1); } else { $args =~ s|\\,|,|g; @args = ($args); } my $macrobody = $macros->{$name}->{Body}; for ($i=0; $i<=$#args; $i++) { $macrobody =~ s|\\$macros->{$name}->{Args}->[$i]\\|$args[$i]|g; } $macrobody =~ s|\\\\|\\|g; $_ = $before . $macrobody . $after; unshift @input_spool, map {$_ = $_."\n"} split(/\n/, $_); next INPUT_LINE; } } # # # try to skip the line # if ($end_tag) { $in_titlepage = 0 if $end_tag eq 'titlepage'; next if $to_skip{"end $end_tag"}; } elsif ($tag) { $in_titlepage = 1 if $tag eq 'titlepage'; next if $to_skip{$tag}; last if $tag eq 'bye'; } if ($in_top) { # parsing the top node if ($tag eq 'node' || ($sec2level{$tag} && $tag !~ /unnumbered/ && $tag !~ /heading/)) { # no more in top $in_top = 0; push(@lines, $TOPEND); } } unless ($in_pre) { s/``/\"/g; s/''/\"/g; s/([\w ])---([\w ])/$1--$2/g; } # # analyze the tag # if ($tag) { # skip lines &skip_until($tag), next if $tag eq 'ignore'; &skip_until($tag), next if $tag eq 'ifnothtml'; if ($tag eq 'ifinfo') { &skip_until($tag), next unless $T2H_EXPAND eq 'info'; } if ($tag eq 'iftex') { &skip_until($tag), next unless $T2H_EXPAND eq 'tex'; } if ($tag eq 'ifnotinfo') { &skip_until($tag), next if $T2H_EXPAND eq 'info'; } if ($tag eq 'ifnottex') { &skip_until($tag), next if $T2H_EXPAND eq 'tex'; } if ($tag eq 'ifhtml') { &skip_until($tag), next unless $T2H_EXPAND eq 'html'; } if ($tag eq 'tex') { &skip_until($tag); next; } if ($tag eq 'titlepage') { next; } # handle special tables if ($tag =~ /^(|f|v|multi)table$/) { $table_type = $1; $tag = 'table'; } # special cases if ($tag eq 'top' || ($tag eq 'node' && /^\@node\s+top\s*,/i)) { $in_top = 1; $has_top = 1; $has_top_command = 1 if $tag eq 'top'; @lines = (); # ignore all lines before top (title page garbage) next; } elsif ($tag eq 'node') { if ($in_top) { $in_top = 0; push(@lines, $TOPEND); } warn "$ERROR Bad node line: $_" unless $_ =~ /^\@node\s$NODESRE$/o; # request of "Richard Y. Kim" s/^\@node\s+//; $_ = &protect_html($_); # if node contains '&' for instance ($node, $node_next, $node_prev, $node_up) = split(/,/); &normalise_node($node); &normalise_node($node_next); &normalise_node($node_prev); &normalise_node($node_up); $node =~ /\"/ ? push @lines, &html_debug("\n", __LINE__) : push @lines, &html_debug("\n", __LINE__); next; } elsif ($tag eq 'include') { if (/^\@include\s+($FILERE)\s*$/o) { $file = LocateIncludeFile($1); if ($file && -e $file) { &open($file); print "# including $file\n" if $T2H_VERBOSE; } else { warn "$ERROR Can't find $1, skipping"; } } else { warn "$ERROR Bad include line: $_"; } next; } elsif ($tag eq 'ifclear') { if (/^\@ifclear\s+($VARRE)\s*$/o) { next unless defined($value{$1}); &skip_until($tag); } else { warn "$ERROR Bad ifclear line: $_"; } next; } elsif ($tag eq 'ifset') { if (/^\@ifset\s+($VARRE)\s*$/o) { next if defined($value{$1}); &skip_until($tag); } else { warn "$ERROR Bad ifset line: $_"; } next; } elsif ($tag eq 'menu') { unless ($T2H_SHOW_MENU) { &skip_until($tag); next; } &html_push_if($tag); push(@lines, &html_debug('', __LINE__)); } elsif ($format_map{$tag}) { $in_pre = 1 if $format_map{$tag} eq 'pre'; &html_push_if($format_map{$tag}); push(@lines, &html_debug('', __LINE__)); $in_list++ if $format_map{$tag} eq 'ul' || $format_map{$tag} eq 'ol' ; # push(@lines, &debug("

\n", __LINE__)) # if $tag =~ /example/i; # sunshine@sunshineco.com:
bla
looks better than #
\nbla
(at least on NeXTstep browser push(@lines, &debug("<$format_map{$tag}>" . ($in_pre ? '' : "\n"), __LINE__)); next; } elsif (exists $complex_format_map->{$tag}) { my $start = eval $complex_format_map->{$tag}->[0]; if ($@) { print "$ERROR: eval of complex_format_map->{$tag}->[0] $complex_format_map->{$tag}->[0]: $@"; $start = '
'
	  }
	  $in_pre = 1 if $start =~ /
\n", __LINE__));
		    &html_push_if('table');
		} else {
		    push(@lines, &debug("
\n", __LINE__)); &html_push_if('dl'); } push(@lines, &html_debug('', __LINE__)); } else { warn "$ERROR Bad table line: $_"; } next; } elsif ($tag eq 'synindex' || $tag eq 'syncodeindex') { if (/^\@$tag\s+(\w+)\s+(\w+)\s*$/) { my $from = $1; my $to = $2; my $prefix_from = IndexName2Prefix($from); my $prefix_to = IndexName2Prefix($to); warn("$ERROR unknown from index name $from ind syn*index line: $_"), next unless $prefix_from; warn("$ERROR unknown to index name $to ind syn*index line: $_"), next unless $prefix_to; if ($tag eq 'syncodeindex') { $index_properties->{$prefix_to}->{'from_code'}->{$prefix_from} = 1; } else { $index_properties->{$prefix_to}->{'from'}->{$prefix_from} = 1; } } else { warn "$ERROR Bad syn*index line: $_"; } next; } elsif ($tag eq 'defindex' || $tag eq 'defcodeindex') { if (/^\@$tag\s+(\w+)\s*$/) { my $name = $1; $index_properties->{$name}->{name} = $name; $index_properties->{$name}->{code} = 1 if $tag eq 'defcodeindex'; } else { warn "$ERROR Bad defindex line: $_"; } next; } elsif (/^\@printindex/) { push (@lines, "$_"); next; } elsif ($tag eq 'sp') { push(@lines, &debug("

\n", __LINE__)); next; } elsif ($tag eq 'center') { push(@lines, &debug("

\n", __LINE__)); s/\@center//; } elsif ($tag eq 'setref') { &protect_html; # if setref contains '&' for instance if (/^\@$tag\s*{($NODERE)}\s*$/) { $setref = $1; $setref =~ s/\s+/ /g; # normalize $setref =~ s/ $//; $node2sec{$setref} = $name; $sec2node{$name} = $setref; $node2href{$setref} = "$docu_doc#$docid"; } else { warn "$ERROR Bad setref line: $_"; } next; } elsif ($tag eq 'lowersections') { local ($sec, $level); while (($sec, $level) = each %sec2level) { $sec2level{$sec} = $level + 1; } next; } elsif ($tag eq 'raisesections') { local ($sec, $level); while (($sec, $level) = each %sec2level) { $sec2level{$sec} = $level - 1; } next; } elsif ($tag eq 'macro' || $tag eq 'rmacro') { if (/^\@$tag\s*(\w+)\s*(.*)/) { my $name = $1; my @args; @args = split(/\s*,\s*/ , $1) if ($2 =~ /^\s*{(.*)}\s*/); $macros->{$name}->{Args} = \@args; $macros->{$name}->{Body} = ''; while (($_ = &next_line) && $_ !~ /\@end $tag/) { $macros->{$name}->{Body} .= $_; } die "ERROR: No closing '\@end $tag' found for macro definition of '$name'\n" unless (/\@end $tag/); chomp $macros->{$name}->{Body}; } else { warn "$ERROR: Bad macro defintion $_" } next; } elsif ($tag eq 'unmacro') { delete $macros->{$1} if (/^\@unmacro\s*(\w+)/); next; } elsif ($tag eq 'documentlanguage') { SetDocumentLanguage($1) if (!$T2H_LANG && /documentlanguage\s*(\w+)/); } elsif (defined($def_map{$tag})) { if ($def_map{$tag}) { s/^\@$tag\s+//; $tag = $def_map{$tag}; $_ = "\@$tag $_"; $tag =~ s/\s.*//; } } elsif (defined($user_sub{$tag})) { s/^\@$tag\s+//; $sub = $user_sub{$tag}; print "# user $tag = $sub, arg: $_" if $T2H_DEBUG & $DEBUG_USER; if (defined(&$sub)) { chop($_); &$sub($_); } else { warn "$ERROR Bad user sub for $tag: $sub\n"; } next; } if (defined($def_map{$tag})) { s/^\@$tag\s+//; if ($tag =~ /x$/) { # extra definition line $tag = $`; $is_extra = 1; } else { $is_extra = 0; } while (/\{([^\{\}]*)\}/) { # this is a {} construct ($before, $contents, $after) = ($`, $1, $'); # protect spaces $contents =~ s/\s+/$;9/g; # restore $_ protecting {} $_ = "$before$;7$contents$;8$after"; } @args = split(/\s+/, &protect_html($_)); foreach (@args) { s/$;9/ /g; # unprotect spaces s/$;7/\{/g; # ... { s/$;8/\}/g; # ... } } $type = shift(@args); $type =~ s/^\{(.*)\}$/$1/; print "# def ($tag): {$type} ", join(', ', @args), "\n" if $T2H_DEBUG & $DEBUG_DEF; $type .= ':'; # it's nicer like this my $name = shift(@args); $name =~ s/^\{(.*)\}$/$1/; if ($is_extra) { $_ = &debug("
", __LINE__); } else { $_ = &debug("
\n
", __LINE__); } if ($tag eq 'deffn' || $tag eq 'defvr' || $tag eq 'deftp') { $_ .= "$type $name"; $_ .= " @args" if @args; } elsif ($tag eq 'deftypefn' || $tag eq 'deftypevr' || $tag eq 'defcv' || $tag eq 'defop') { $ftype = $name; $name = shift(@args); $name =~ s/^\{(.*)\}$/$1/; $_ .= "$type $ftype $name"; $_ .= " @args" if @args; } else { warn "$ERROR Unknown definition type: $tag\n"; $_ .= "$type $name"; $_ .= " @args" if @args; } $_ .= &debug("\n
", __LINE__); $name = &unprotect_html($name); if ($tag eq 'deffn' || $tag eq 'deftypefn') { EnterIndexEntry('f', $name, $docu_doc, $section, \@lines); # unshift(@input_spool, "\@findex $name\n"); } elsif ($tag eq 'defop') { EnterIndexEntry('f', "$name on $ftype", $docu_doc, $section, \@lines); # unshift(@input_spool, "\@findex $name on $ftype\n"); } elsif ($tag eq 'defvr' || $tag eq 'deftypevr' || $tag eq 'defcv') { EnterIndexEntry('v', $name, $docu_doc, $section, \@lines); # unshift(@input_spool, "\@vindex $name\n"); } else { EnterIndexEntry('t', $name, $docu_doc, $section, \@lines); # unshift(@input_spool, "\@tindex $name\n"); } $dont_html = 1; } } elsif ($end_tag) { if ($format_map{$end_tag}) { $in_pre = 0 if $format_map{$end_tag} eq 'pre'; $in_list-- if $format_map{$end_tag} eq 'ul' || $format_map{$end_tag} eq 'ol' ; &html_pop_if('p'); &html_pop_if('li'); &html_pop_if(); push(@lines, &debug("\n", __LINE__)); push(@lines, &html_debug('', __LINE__)); } elsif (exists $complex_format_map->{$end_tag}) { my $end = eval $complex_format_map->{$end_tag}->[1]; if ($@) { print "$ERROR: eval of complex_format_map->{$end_tag}->[1] $complex_format_map->{$end_tag}->[0]: $@"; $end = '
' } $in_pre = 0 if $end =~ m|
|; push(@lines, html_debug($end, __LINE__)); } elsif ($end_tag =~ /^(|f|v|multi)table$/) { unless (@tables) { warn "$ERROR \@end $end_tag without \@*table\n"; next; } &html_pop_if('p'); ($table_type, $in_table) = split($;, shift(@tables)); unless ($1 eq $table_type) { warn "$ERROR \@end $end_tag without matching \@$end_tag\n"; next; } if ($table_type eq "multi") { push(@lines, "
\n"); &html_pop_if('tr'); } else { push(@lines, "\n"); &html_pop_if('dd'); } &html_pop_if(); if (@tables) { ($table_type, $in_table) = split($;, $tables[0]); } else { $in_table = 0; } } elsif (defined($def_map{$end_tag})) { push(@lines, &debug("\n", __LINE__)); } elsif ($end_tag eq 'menu') { &html_pop_if(); push(@lines, $_); # must keep it for pass 2 } next; } ############################################################# # anchor insertion while (/\@anchor\s*\{(.*?)\}/) { $_ = $`.$'; my $anchor = $1; $anchor = &normalise_node($anchor); push @lines, &html_debug("\n"); $node2href{$anchor} = "$docu_doc#$anchor"; next INPUT_LINE if $_ =~ /^\s*$/; } ############################################################# # index entry generation, after value substitutions if (/^\@(\w+?)index\s+/) { EnterIndexEntry($1, $', $docu_doc, $section, \@lines); next; } # # protect texi and HTML things &protect_texi; $_ = &protect_html($_) unless $dont_html; $dont_html = 0; # substitution (unsupported things) s/^\@exdent\s+//g; s/\@noindent\s+//g; s/\@refill\s+//g; # other substitutions &simple_substitutions; s/\@footnote\{/\@footnote$docu_doc\{/g; # mark footnotes, cf. pass 4 # # analyze the tag again # if ($tag) { if (defined($sec2level{$tag}) && $sec2level{$tag} > 0) { if (/^\@$tag\s+(.+)$/) { $name = $1; $name = &normalise_node($name); $level = $sec2level{$tag}; # check for index $first_index_chapter = $name if ($level == 1 && !$first_index_chapter && $name =~ /index/i); if ($in_top && /heading/){ $T2H_HAS_TOP_HEADING = 1; $_ = &debug("$name\n", __LINE__); &html_push_if('body'); print "# top heading, section $name, level $level\n" if $T2H_DEBUG & $DEBUG_TOC; } else { unless (/^\@\w*heading/) { my $here_split = 0; unless (/^\@unnumbered/) { my $number = &update_sec_num($tag, $level); $name = $number. ' ' . $name if $T2H_NUMBER_SECTIONS; $sec2number{$name} = $number; $number2sec{$number} = $name; } if (defined($toplevel)) { if ($level==$toplevel) { $here_split = $T2H_SPLIT; push @lines, $CHAPTEREND; } else { $here_split = $T2H_SPLIT eq 'section' && $level==$toplevel+1; push @lines, $SECTIONEND; } } else { # first time we see a "section" unless ($level == 1) { warn "$WARN The first section found is not of level 1: $_"; } $toplevel = $level; $here_split = $T2H_SPLIT; } push(@sections, $name); if ($here_split) { next_doc(); } } $sec_num++; $docid = "SEC$sec_num"; $tocid = (/^\@\w*heading/ ? undef : "TOC$sec_num"); # check biblio and glossary $in_bibliography = ($name =~ /^([A-Z]|\d+)?(\.\d+)*\s*bibliography$/i); $in_glossary = ($name =~ /^([A-Z]|\d+)?(\.\d+)*\s*glossary$/i); # check node if ($node) { warn "$ERROR Duplicate node found: $node\n" if ($node2sec{$node}); } else { $name .= ' ' while ($node2sec{$name}); $node = $name; } $name .= ' ' while ($sec2node{$name}); $section = $name; $node2sec{$node} = $name; $sec2node{$name} = $node; $node2href{$node} = "$docu_doc#$docid"; $node2next{$node} = $node_next; $node2prev{$node} = $node_prev; $node2up{$node} = $node_up; print "# section $name, level $level, file $docu_doc\n" if $T2H_DEBUG & $DEBUG_TOC; $node = ''; $node_next = ''; $node_prev = ''; $node_next = ''; if ($tocid) { # update TOC while ($level > $curlevel) { $curlevel++; push(@toc_lines, "
    \n"); } while ($level < $curlevel) { $curlevel--; push(@toc_lines, "
\n"); } $_ = &t2h_anchor($tocid, "$docu_doc#$docid", $name, 1); $_ = &substitute_style($_); push(@stoc_lines, "$_
\n") if ($level == 1); if ($T2H_NUMBER_SECTIONS) { push(@toc_lines, $_ . "
\n") } else { push(@toc_lines, "
  • " . $_ ."
  • "); } } else { push(@lines, &html_debug("\n", __LINE__)); } # update DOC push(@lines, &html_debug('', __LINE__)); &html_reset; $_ = " $name \n\n"; $_ = &debug($_, __LINE__); push(@lines, &html_debug('', __LINE__)); } # update DOC foreach $line (split(/\n+/, $_)) { push(@lines, "$line\n"); } next; } else { warn "$ERROR Bad section line: $_"; } } else { # track variables $value{$1} = Unprotect_texi($2), next if /^\@set\s+($VARRE)\s+(.*)$/o; delete $value{$1}, next if /^\@clear\s+($VARRE)\s*$/o; # store things $value{'_shorttitle'} = Unprotect_texi($1), next if /^\@shorttitle\s+(.*)$/; $value{'_setfilename'} = Unprotect_texi($1), next if /^\@setfilename\s+(.*)$/; $value{'_settitle'} = Unprotect_texi($1), next if /^\@settitle\s+(.*)$/; $value{'_author'} .= Unprotect_texi($1)."\n", next if /^\@author\s+(.*)$/; $value{'_subtitle'} .= Unprotect_texi($1)."\n", next if /^\@subtitle\s+(.*)$/; $value{'_title'} .= Unprotect_texi($1)."\n", next if /^\@title\s+(.*)$/; # list item if (/^\s*\@itemx?\s+/) { $what = $'; $what =~ s/\s+$//; if ($in_bibliography && $use_bibliography) { if ($what =~ /^$BIBRE$/o) { $id = 'BIB' . ++$bib_num; $bib2href{$what} = "$docu_doc#$id"; print "# found bibliography for '$what' id $id\n" if $T2H_DEBUG & $DEBUG_BIB; $what = &t2h_anchor($id, '', $what); } } elsif ($in_glossary && $T2H_USE_GLOSSARY) { $id = 'GLOSS' . ++$gloss_num; $entry = $what; $entry =~ tr/A-Z/a-z/ unless $entry =~ /^[A-Z\s]+$/; $gloss2href{$entry} = "$docu_doc#$id"; print "# found glossary for '$entry' id $id\n" if $T2H_DEBUG & $DEBUG_GLOSS; $what = &t2h_anchor($id, '', $what); } elsif ($in_table && ($table_type eq 'f' || $table_type eq 'v')) { EnterIndexEntry($table_type, $what, $docu_doc, $section, \@lines); } &html_pop_if('p'); if ($html_element eq 'dl' || $html_element eq 'dd') { if ($things_map{$in_table} && !$what) { # special case to allow @table @bullet for instance push(@lines, &debug("
    $things_map{$in_table}\n", __LINE__)); } else { push(@lines, &debug("
    \@$in_table\{$what\}\n", __LINE__)); } push(@lines, "
    "); &html_push('dd') unless $html_element eq 'dd'; if ($table_type) { # add also an index unshift(@input_spool, "\@${table_type}index $what\n"); } } elsif ($html_element eq 'table') { push(@lines, &debug("$what\n", __LINE__)); &html_push('tr'); } elsif ($html_element eq 'tr') { push(@lines, &debug("\n", __LINE__)); push(@lines, &debug("$what\n", __LINE__)); } else { push(@lines, &debug("
  • $what\n", __LINE__)); &html_push('li') unless $html_element eq 'li'; } push(@lines, &html_debug('', __LINE__)); if ($deferred_ref) { push(@lines, &debug("$deferred_ref\n", __LINE__)); $deferred_ref = ''; } next; } elsif (/^\@tab\s+(.*)$/) { push(@lines, "$1\n"); next; } } } # paragraph separator if ($_ eq "\n" && ! $in_pre) { next if $#lines >= 0 && $lines[$#lines] eq "\n"; if ($html_element eq 'p') { push (@lines, &debug("

    \n", __LINE__)); } # else # { # push(@lines, "

    \n"); # $_ = &debug("

    \n", __LINE__); # } elsif ($html_element eq 'body' || $html_element eq 'blockquote' || $html_element eq 'dd' || $html_element eq 'li') { &html_push('p'); push(@lines, &debug("

    \n", __LINE__)); } } # otherwise push(@lines, $_) unless $in_titlepage; push(@lines, &debug("

  • \n", __LINE__)) if ($tag eq 'center'); } # finish TOC $level = 0; while ($level < $curlevel) { $curlevel--; push(@toc_lines, "\n"); } print "# end of pass 1\n" if $T2H_VERBOSE; SetDocumentLanguage('en') unless ($T2H_LANG); #+++############################################################################ # # # Stuff related to Index generation # # # #---############################################################################ sub EnterIndexEntry { my $prefix = shift; my $key = shift; my $docu_doc = shift; my $section = shift; my $lines = shift; local $_; warn "$ERROR Undefined index command: $_", next unless (exists ($index_properties->{$prefix})); $key =~ s/\s+$//; $_ = $key; &protect_texi; $key = $_; $_ = &protect_html($_); my $html_key = substitute_style($_); my $id; $key = remove_style($key); $key = remove_things($key); $_ = $key; &unprotect_texi; $key = $_; while (exists $index->{$prefix}->{$key}) {$key .= ' '}; if ($lines->[$#lines] =~ /^$/) { $id = $1; } else { $id = 'IDX' . ++$idx_num; push(@$lines, &t2h_anchor($id, '', $T2H_INVISIBLE_MARK, !$in_pre)); } $index->{$prefix}->{$key}->{html_key} = $html_key; $index->{$prefix}->{$key}->{section} = $section; $index->{$prefix}->{$key}->{href} = "$docu_doc#$id"; print "# found ${prefix}index for '$key' with id $id\n" if $T2H_DEBUG & $DEBUG_INDEX; } sub IndexName2Prefix { my $name = shift; my $prefix; for $prefix (keys %$index_properties) { return $prefix if ($index_properties->{$prefix}->{name} eq $name); } return undef; } sub GetIndexEntries { my $normal = shift; my $code = shift; my ($entries, $prefix, $key) = ({}); for $prefix (keys %$normal) { for $key (keys %{$index->{$prefix}}) { $entries->{$key} = {%{$index->{$prefix}->{$key}}}; } } if (defined($code)) { for $prefix (keys %$code) { unless (exists $normal->{$keys}) { for $key (keys %{$index->{$prefix}}) { $entries->{$key} = {%{$index->{$prefix}->{$key}}}; $entries->{$key}->{html_key} = "$entries->{$key}->{html_key}"; } } } } return $entries; } sub byAlpha { if ($a =~ /^[A-Za-z]/) { if ($b =~ /^[A-Za-z]/) { return lc($a) cmp lc($b); } else { return 1; } } elsif ($b =~ /^[A-Za-z]/) { return -1; } else { return lc($a) cmp lc($b); } } sub GetIndexPages { my $entries = shift; my (@Letters, $key); my ($EntriesByLetter, $Pages, $page) = ({}, [], {}); my @keys = sort byAlpha keys %$entries; for $key (@keys) { push @{$EntriesByLetter->{uc(substr($key,0, 1))}} , $entries->{$key}; } @Letters = sort byAlpha keys %$EntriesByLetter; $T2H_SPLIT_INDEX = 0 unless ($T2H_SPLIT); unless ($T2H_SPLIT_INDEX) { $page->{First} = $Letters[0]; $page->{Last} = $Letters[$#Letters]; $page->{Letters} = \@Letters; $page->{EntriesByLetter} = $EntriesByLetter; push @$Pages, $page; return $Pages; } if ($T2H_SPLIT_INDEX =~ /^\d+$/) { my $i = 0; my ($prev_letter, $letter); $page->{First} = $Letters[0]; for $letter (@Letters) { if ($i > $T2H_SPLIT_INDEX) { $page->{Last} = $prev_letter; push @$Pages, {%$page}; $page->{Letters} = []; $page->{EntriesByLetter} = {}; $page->{First} = $letter; $i=0; } push @{$page->{Letters}}, $letter; $page->{EntriesByLetter}->{$letter} = [@{$EntriesByLetter->{$letter}}]; $i += scalar(@{$EntriesByLetter->{$letter}}); $prev_letter = $letter; } $page->{Last} = $Letters[$#Letters]; push @$Pages, {%$page}; } return $Pages; } sub GetIndexSummary { my $first_page = shift; my $Pages = shift; my $name = shift; my ($page, $letter, $summary, $i, $l1, $l2, $l); $i = 0; $summary = '
    Jump to:   '; for $page ($first_page, @$Pages) { for $letter (@{$page->{Letters}}) { $l = t2h_anchor('', "$page->{href}#${name}_$letter", "$letter", 0, 'style="text-decoration:none"') . "\n   \n"; if ($letter =~ /^[A-Za-z]/) { $l2 .= $l; } else { $l1 .= $l; } } } $summary .= $l1 . "
    \n" if ($l1); $summary .= $l2 . '

    '; return $summary; } sub PrintIndexPage { my $lines = shift; my $summary = shift; my $page = shift; my $name = shift; push @$lines, $summary; push @$lines , <

    EOT for $letter (@{$page->{Letters}}) { push @$lines, "\n"; for $entry (@{$page->{EntriesByLetter}->{$letter}}) { push @$lines, "\n"; } push @$lines, "\n"; } push @$lines, "
    Index Entry Section

    $letter
    " . t2h_anchor('', $entry->{href}, $entry->{html_key}) . "" . t2h_anchor('', sec_href($entry->{section}), clean_name($entry->{section})) . "

    "; push @$lines, $summary; } sub PrintIndex { my $lines = shift; my $name = shift; my $section = shift; $section = 'Top' unless $section; my $prefix = IndexName2Prefix($name); warn ("$ERROR printindex: bad index name: $name"), return unless $prefix; if ($index_properties->{$prefix}->{code}) { $index_properties->{$prefix}->{from_code}->{$prefix} = 1; } else { $index_properties->{$prefix}->{from}->{$prefix}= 1; } my $Entries = GetIndexEntries($index_properties->{$prefix}->{from}, $index_properties->{$prefix}->{from_code}); return unless %$Entries; if ($T2H_IDX_SUMMARY) { my $key; open(FHIDX, ">$docu_rdir$docu_name" . "_$name.idx") || die "Can't open > $docu_rdir$docu_name" . "_$name.idx for writing: $!\n"; print "# writing $name index summary in $docu_rdir$docu_name" . "_$name.idx...\n" if $T2H_VERBOSE; for $key (sort keys %$Entries) { print FHIDX "$key\t$Entries->{$key}->{href}\n"; } } my $Pages = GetIndexPages($Entries); my $page; my $first_page = shift @$Pages; my $sec_name = $section; # remove section number $sec_name =~ s/.*? // if $sec_name =~ /^([A-Z]|\d+)\./; ($first_page->{href} = sec_href($section)) =~ s/\#.*$//; # Update tree structure of document if (@$Pages) { my $sec; my @after; while (@sections && $sections[$#sections] ne $section) { unshift @after, pop @sections; } for $page (@$Pages) { my $node = ($page->{First} ne $page->{Last} ? "$sec_name: $page->{First} -- $page->{Last}" : "$sec_name: $page->{First}"); push @sections, $node; $node2sec{$node} = $node; $sec2node{$node} = $node; $node2up{$node} = $section; $page->{href} = next_doc(); $page->{name} = $node; $node2href{$node} = $page->{href}; if ($prev_node) { $node2next{$prev_node} = $node; $node2prev{$node} = $prev_node; } $prev_node = $node; } push @sections, @after; } my $summary = GetIndexSummary($first_page, $Pages, $name); PrintIndexPage($lines, $summary, $first_page, $name); for $page (@$Pages) { push @$lines, ($T2H_SPLIT eq 'chapter' ? $CHAPTEREND : $SECTIONEND); push @$lines, "

    $page->{name}

    \n"; PrintIndexPage($lines, $summary, $page, $name); } } #+++############################################################################ # # # Pass 2/3: handle style, menu, index, cross-reference # # # #---############################################################################ @lines2 = (); # whole document (2nd pass) @lines3 = (); # whole document (3rd pass) $in_menu = 0; # am I inside a menu while (@lines) { $_ = shift(@lines); # # special case (protected sections) # if (/^$PROTECTTAG/o) { push(@lines2, $_); next; } # # menu # if (/^\@menu\b/) { $in_menu = 1; $in_menu_listing = 1; push(@lines2, &debug("
    \n", __LINE__)); next; } if (/^\@end\s+menu\b/) { if ($in_menu_listing) { push(@lines2, &debug("
    \n", __LINE__)); } else { push(@lines2, &debug("\n", __LINE__)); } $in_menu = 0; $in_menu_listing = 0; next; } if ($in_menu) { my ($node, $name, $descr); if (/^\*\s+($NODERE)::/o) { $node = $1; $descr = $'; } elsif (/^\*\s+(.+):\s+([^\t,\.\n]+)[\t,\.\n]/) { $name = $1; $node = $2; $descr = $'; } elsif (/^\*/) { warn "$ERROR Bad menu line: $_"; } else { if ($in_menu_listing) { $in_menu_listing = 0; push(@lines2, &debug("\n", __LINE__)); } # should be like verbatim -- preseve spaces, etc s/ /\ /g; $_ .= "
    \n"; push(@lines2, $_); } if ($node) { if (! $in_menu_listing) { $in_menu_listing = 1; push(@lines2, &debug("\n", __LINE__)); } # look for continuation while ($lines[0] =~ /^\s+\w+/) { $descr .= shift(@lines); } &menu_entry($node, $name, $descr); } next; } # # printindex # PrintIndex(\@lines2, $2, $1), next if (/^\@printindex\s+(\w+)/); # # simple style substitutions # $_ = &substitute_style($_); # # xref # while (/\@(x|px|info|)ref{([^{}]+)(}?)/) { # note: Texinfo may accept other characters ($type, $nodes, $full) = ($1, $2, $3); ($before, $after) = ($`, $'); if (! $full && $after) { warn "$ERROR Bad xref (no ending } on line): $_"; $_ = "$before$;0${type}ref\{$nodes$after"; next; # while xref } if ($type eq 'x') { $type = "$T2H_WORDS->{$T2H_LANG}->{'See'} "; } elsif ($type eq 'px') { $type = "$T2H_WORDS->{$T2H_LANG}->{'see'} "; } elsif ($type eq 'info') { $type = "$T2H_WORDS->{$T2H_LANG}->{'See'} Info"; } else { $type = ''; } unless ($full) { $next = shift(@lines); $next = &substitute_style($next); chop($nodes); # remove final newline if ($next =~ /\}/) { # split on 2 lines $nodes .= " $`"; $after = $'; } else { $nodes .= " $next"; $next = shift(@lines); $next = &substitute_style($next); chop($nodes); if ($next =~ /\}/) { # split on 3 lines $nodes .= " $`"; $after = $'; } else { warn "$ERROR Bad xref (no ending }): $_"; $_ = "$before$;0xref\{$nodes$after"; unshift(@lines, $next); next; # while xref } } } $nodes =~ s/\s+/ /g; # remove useless spaces @args = split(/\s*,\s*/, $nodes); $node = $args[0]; # the node is always the first arg $node = &normalise_node($node); $sec = $args[2] || $args[1] || $node2sec{$node}; $href = $node2href{$node}; if (@args == 5) { # reference to another manual $sec = $args[2] || $node; $man = $args[4] || $args[3]; $_ = "${before}${type}$T2H_WORDS->{$T2H_LANG}->{'section'} `$sec' in \@cite{$man}$after"; } elsif ($type =~ /Info/) { # inforef warn "$ERROR Wrong number of arguments: $_" unless @args == 3; ($nn, $_, $in) = @args; $_ = "${before}${type} file `$in', node `$nn'$after"; } elsif ($sec && $href && ! $T2H_SHORT_REF) { $_ = "${before}${type}"; $_ .= "$T2H_WORDS->{$T2H_LANG}->{'section'} " if ${type}; $_ .= &t2h_anchor('', $href, $sec) . $after; } elsif ($href) { $_ = "${before}${type} " . &t2h_anchor('', $href, $args[2] || $args[1] || $node) . $after; } else { warn "$ERROR Undefined node ($node): $_"; $_ = "$before$;0xref{$nodes}$after"; } } # replace images s[\@image\s*{(.+?)}] { my @args = split (/\s*,\s*/, $1); my $base = $args[0]; my $image = LocateIncludeFile("$base.png") || LocateIncludeFile("$base.jpg") || LocateIncludeFile("$base.gif"); warn "$ERROR no image file for $base: $_" unless ($image && -e $image); "\"$base\""; ($T2H_CENTER_IMAGE ? "
    \"$base\"
    " : "\"$base\""); }eg; # # try to guess bibliography references or glossary terms # unless (/^/) { $done .= $pre . &t2h_anchor('', $href, $what); } else { $done .= "$pre$what"; } $_ = $post; } $_ = $done . $_; } if ($T2H_USE_GLOSSARY) { $done = ''; while (/\b\w+\b/) { ($pre, $what, $post) = ($`, $&, $'); $entry = $what; $entry =~ tr/A-Z/a-z/ unless $entry =~ /^[A-Z\s]+$/; $href = $gloss2href{$entry}; if (defined($href) && $post !~ /^[^<]*<\/A>/) { $done .= $pre . &t2h_anchor('', $href, $what); } else { $done .= "$pre$what"; } $_ = $post; } $_ = $done . $_; } } # otherwise push(@lines2, $_); } print "# end of pass 2\n" if $T2H_VERBOSE; # # split style substitutions # while (@lines2) { $_ = shift(@lines2); # # special case (protected sections) # if (/^$PROTECTTAG/o) { push(@lines3, $_); next; } # # split style substitutions # $old = ''; while ($old ne $_) { $old = $_; if (/\@(\w+)\{/) { ($before, $style, $after) = ($`, $1, $'); if (defined($style_map{$style})) { $_ = $after; $text = ''; $after = ''; $failed = 1; while (@lines2) { if (/\}/) { $text .= $`; $after = $'; $failed = 0; last; } else { $text .= $_; $_ = shift(@lines2); } } if ($failed) { die "* Bad syntax (\@$style) after: $before\n"; } else { $text = &apply_style($style, $text); $_ = "$before$text$after"; } } } } # otherwise push(@lines3, $_); } print "# end of pass 3\n" if $T2H_VERBOSE; #+++############################################################################ # # # Pass 4: foot notes, final cleanup # # # #---############################################################################ @foot_lines = (); # footnotes @doc_lines = (); # final document $end_of_para = 0; # true if last line is

    while (@lines3) { $_ = shift(@lines3); # # special case (protected sections) # if (/^$PROTECTTAG/o) { push(@doc_lines, $_); $end_of_para = 0; next; } # # footnotes # while (/\@footnote([^\{\s]+)\{/) { ($before, $d, $after) = ($`, $1, $'); $_ = $after; $text = ''; $after = ''; $failed = 1; while (@lines3) { if (/\}/) { $text .= $`; $after = $'; $failed = 0; last; } else { $text .= $_; $_ = shift(@lines3); } } if ($failed) { die "* Bad syntax (\@footnote) after: $before\n"; } else { $foot_num++; $docid = "DOCF$foot_num"; $footid = "FOOT$foot_num"; $foot = "($foot_num)"; push(@foot_lines, "

    " . &t2h_anchor($footid, "$d#$docid", $foot) . "

    \n"); $text = "

    $text" unless $text =~ /^\s*

    /i; push(@foot_lines, "$text\n"); $_ = $before . &t2h_anchor($docid, "$docu_foot#$footid", $foot) . $after; } } # # remove unnecessary

    # if (/^\s*

    \s*$/i) { next if $end_of_para++; } else { $end_of_para = 0; } # otherwise push(@doc_lines, $_); } print "# end of pass 4\n" if $T2H_VERBOSE; #+++############################################################################ # # # Pass 5: print things # # # #---############################################################################ # fix node2up, node2prev, node2next, if desired if ($has_top_command) { for $section (keys %sec2number) { $node = $sec2node{$section}; $node2up{$node} = Sec2UpNode($section) unless $node2up{$node}; $node2prev{$node} = Sec2PrevNode($section) unless $node2prev{$node}; $node2next{$node} = Sec2NextNode($section) unless $node2next{$node}; } } # prepare %T2H_THISDOC $T2H_THISDOC{fulltitle} = $value{'_title'} || $value{'_settitle'} || "Untitled Document"; $T2H_THISDOC{title} = $value{'_settitle'} || $T2H_THISDOC{fulltitle}; $T2H_THISDOC{author} = $value{'_author'}; $T2H_THISDOC{subtitle} = $value{'_subtitle'}; $T2H_THISDOC{shorttitle} = $value{'_shorttitle'}; for $key (keys %T2H_THISDOC) { $_ = &substitute_style($T2H_THISDOC{$key}); &unprotect_texi; s/\s*$//; $T2H_THISDOC{$key} = $_; } # if no sections, then simply print document as is unless (@sections) { print "# Writing content into $docu_top_file \n" if $T2H_VERBOSE; open(FILE, "> $docu_top_file") || die "$ERROR: Can't open $docu_top_file for writing: $!\n"; &$T2H_print_page_head(\*FILE); $T2H_THIS_SECTION = \@doc_lines; t2h_print_lines(\*FILE); &$T2H_print_foot_navigation(\*FILE); &$T2H_print_page_foot(\*FILE); close(FILE); goto Finish; } # initialize $T2H_HREF, $T2H_NAME %T2H_HREF = ( 'First' , sec_href($sections[0]), 'Last', sec_href($sections[$#sections]), 'About', $docu_about. '#SEC_About', ); # prepare TOC, OVERVIEW, TOP $T2H_TOC = \@toc_lines; $T2H_OVERVIEW = \@stoc_lines; if ($has_top) { while (1) { $_ = shift @doc_lines; last if /$TOPEND/; push @$T2H_TOP, $_; } $T2H_HREF{'Top'} = $docu_top . '#SEC_Top'; } else { $T2H_HREF{'Top'} = $T2H_HREF{First}; } $node2href{Top} = $T2H_HREF{Top}; $T2H_HREF{Contents} = $docu_toc.'#SEC_Contents' if @toc_lines; $T2H_HREF{Overview} = $docu_stoc.'#SEC_OVERVIEW' if @stoc_lines; # settle on index if ($T2H_INDEX_CHAPTER) { $T2H_HREF{Index} = $node2href{normalise_node($T2H_INDEX_CHAPTER)}; warn "$ERROR T2H_INDEX_CHAPTER '$T2H_INDEX_CHAPTER' not found\n" unless $T2H_HREF{Index}; } if (! $T2H_HREF{Index} && $first_index_chapter) { $T2H_INDEX_CHAPTER = $first_index_chapter; $T2H_HREF{Index} = $node2href{$T2H_INDEX_CHAPTER}; } print "# Using '" . clean_name($T2H_INDEX_CHAPTER) . "' as index page\n" if ($T2H_VERBOSE && $T2H_HREF{Index}); %T2H_NAME = ( 'First', clean_name($sec2node{$sections[0]}), 'Last', clean_name($sec2node{$sections[$#sections]}), 'About', $T2H_WORDS->{$T2H_LANG}->{'About_Title'}, 'Contents', $T2H_WORDS->{$T2H_LANG}->{'ToC_Title'}, 'Overview', $T2H_WORDS->{$T2H_LANG}->{'Overview_Title'}, 'Index' , clean_name($T2H_INDEX_CHAPTER), 'Top', clean_name($T2H_TOP_HEADING || $T2H_THISDOC{'title'} || $T2H_THISDOC{'shorttitle'}), ); ############################################################################# # print frame and frame toc file # if ( $T2H_FRAMES ) { open(FILE, "> $docu_frame_file") || die "$ERROR: Can't open $docu_frame_file for writing: $!\n"; print "# Creating frame in $docu_frame_file ...\n" if $T2H_VERBOSE; &$T2H_print_frame(\*FILE); close(FILE); open(FILE, "> $docu_toc_frame_file") || die "$ERROR: Can't open $docu_toc_frame_file for writing: $!\n"; print "# Creating toc frame in $docu_frame_file ...\n" if $T2H_VERBOSE; &$T2H_print_toc_frame(\*FILE); close(FILE); } ############################################################################# # print Top # open(FILE, "> $docu_top_file") || die "$ERROR: Can't open $docu_top_file for writing: $!\n"; &$T2H_print_page_head(\*FILE) unless ($T2H_SPLIT); if ($has_top) { print "# Creating Top in $docu_top_file ...\n" if $T2H_VERBOSE; $T2H_THIS_SECTION = $T2H_TOP; $T2H_HREF{This} = $T2H_HREF{Top}; $T2H_NAME{This} = $T2H_NAME{Top}; &$T2H_print_Top(\*FILE); } close(FILE) if $T2H_SPLIT; ############################################################################# # Print sections # $T2H_NODE{Forward} = $sec2node{$sections[0]}; $T2H_NAME{Forward} = &clean_name($sec2node{$sections[0]}); $T2H_HREF{Forward} = sec_href($sections[0]); $T2H_NODE{This} = 'Top'; $T2H_NAME{This} = $T2H_NAME{Top}; $T2H_HREF{This} = $T2H_HREF{Top}; if ($T2H_SPLIT) { print "# writing " . scalar(@sections) . " sections in $docu_rdir$docu_name"."_[1..$doc_num]" if $T2H_VERBOSE; undef $FH; $doc_num = 0; } else { print "# writing " . scalar(@sections) . " sections in $docu_top_file ..." if $T2H_VERBOSE; $FH = \*FILE; } $previous = ($T2H_SPLIT eq 'section' ? $SECTIONEND : $CHAPTEREND); $counter = 0; # loop through sections while ($section = shift(@sections)) { my $old_file = $T2H_HREF{This}; my $file = $T2H_HREF{Forward}; $old_file =~ s/\#.*$//; $file =~ s/\#.*$//; if ($old_file ne $file) { if ($FH) { #close previous page &$T2H_print_chapter_footer($FH); &$T2H_print_page_foot($FH); close($FH); undef $FH; } } elsif ($previous eq $CHAPTEREND) { &$T2H_print_chapter_footer($FH); } $T2H_NAME{Back} = $T2H_NAME{This}; $T2H_HREF{Back} = $T2H_HREF{This}; $T2H_NODE{Back} = $T2H_NODE{This}; $T2H_NAME{This} = $T2H_NAME{Forward}; $T2H_HREF{This} = $T2H_HREF{Forward}; $T2H_NODE{This} = $T2H_NODE{Forward}; if ($sections[0]) { $T2H_NODE{Forward} = $sec2node{$sections[0]}; $T2H_NAME{Forward} = &clean_name($T2H_NODE{Forward}); $T2H_HREF{Forward} = sec_href($sections[0]); } else { undef $T2H_HREF{Forward}, $T2H_NODE{Forward}, $T2H_NAME{Forward}; } $node = $node2up{$T2H_NODE{This}}; $T2H_HREF{Up} = $node2href{$node}; if ($T2H_HREF{Up} eq $T2H_HREF{This} || ! $T2H_HREF{Up}) { $T2H_NAME{Up} = $T2H_NAME{Top}; $T2H_HREF{Up} = $T2H_HREF{Top}; $T2H_NODE{Up} = 'Up'; } else { $T2H_NAME{Up} = &clean_name($node); $T2H_NODE{Up} = $node; } $node = $T2H_NODE{This}; $node = $node2prev{$node}; $T2H_NAME{Prev} = &clean_name($node); $T2H_HREF{Prev} = $node2href{$node}; $T2H_NODE{Prev} = $node; $node = $T2H_NODE{This}; if ($node2up{$node} && $node2up{$node} ne 'Top'&& ($node2prev{$node} eq $T2H_NODE{Back} || ! $node2prev{$node})) { $node = $node2up{$node}; while ($node && $node ne $node2up{$node} && ! $node2prev{$node}) { $node = $node2up{$node}; } $node = $node2prev{$node} unless $node2up{$node} eq 'Top' || ! $node2up{$node}; } else { $node = $node2prev{$node}; } $T2H_NAME{FastBack} = &clean_name($node); $T2H_HREF{FastBack} = $node2href{$node}; $T2H_NODE{FastBack} = $node; $node = $T2H_NODE{This}; $node = $node2next{$node}; $T2H_NAME{Next} = &clean_name($node); $T2H_HREF{Next} = $node2href{$node}; $T2H_NODE{Next} = $node; $node = $T2H_NODE{This}; if ($node2up{$node} && $node2up{$node} ne 'Top'&& ($node2next{$node} eq $T2H_NODE{Forward} || ! $node2next{$node})) { $node = $node2up{$node}; while ($node && $node ne $node2up{$node} && ! $node2next{$node}) { $node = $node2up{$node}; } } $node = $node2next{$node}; $T2H_NAME{FastForward} = &clean_name($node); $T2H_HREF{FastForward} = $node2href{$node}; $T2H_NODE{FastForward} = $node; if (! defined($FH)) { open(FILE, "> $docu_rdir$file") || die "$ERROR: Can't open $docu_rdir$file for writing: $!\n"; $FH = \*FILE; &$T2H_print_page_head($FH); t2h_print_label($FH); &$T2H_print_chapter_header($FH); } else { t2h_print_label($FH); &$T2H_print_chapter_header($FH) if $previous eq $CHAPTEREND; } $T2H_THIS_SECTION = []; while (@doc_lines) { $_ = shift(@doc_lines); last if ($_ eq $SECTIONEND || $_ eq $CHAPTEREND); push(@$T2H_THIS_SECTION, $_); } $previous = $_; &$T2H_print_section($FH); if ($T2H_VERBOSE) { $counter++; print "." if $counter =~ /00$/; } } &$T2H_print_chapter_footer($FH); if ($T2H_SPLIT) { &$T2H_print_page_foot($FH); close($FH); } print "\n" if $T2H_VERBOSE; ############################################################################# # Print ToC, Overview, Footnotes # undef $T2H_HREF{Prev}; undef $T2H_HREF{Next}; undef $T2H_HREF{Back}; undef $T2H_HREF{Forward}; undef $T2H_HREF{Up}; if (@foot_lines) { print "# writing Footnotes in $docu_foot_file...\n" if $T2H_VERBOSE; open (FILE, "> $docu_foot_file") || die "$ERROR: Can't open $docu_foot_file for writing: $!\n" if $T2H_SPLIT; $T2H_HREF{This} = $docu_foot; $T2H_NAME{This} = $T2H_WORDS->{$T2H_LANG}->{'Footnotes_Title'}; $T2H_THIS_SECTION = \@foot_lines; &$T2H_print_Footnotes(\*FILE); close(FILE) if $T2H_SPLIT; } if (@toc_lines) { print "# writing Toc in $docu_toc_file...\n" if $T2H_VERBOSE; open (FILE, "> $docu_toc_file") || die "$ERROR: Can't open $docu_toc_file for writing: $!\n" if $T2H_SPLIT; $T2H_HREF{This} = $T2H_HREF{Contents}; $T2H_NAME{This} = $T2H_NAME{Contents}; $T2H_THIS_SECTION = \@toc_lines; &$T2H_print_Toc(\*FILE); close(FILE) if $T2H_SPLIT; } if (@stoc_lines) { print "# writing Overview in $docu_stoc_file...\n" if $T2H_VERBOSE; open (FILE, "> $docu_stoc_file") || die "$ERROR: Can't open $docu_stoc_file for writing: $!\n" if $T2H_SPLIT; $T2H_HREF{This} = $T2H_HREF{Overview}; $T2H_NAME{This} = $T2H_NAME{Overview}; $T2H_THIS_SECTION = \@stoc_lines; unshift @$T2H_THIS_SECTION, "

    \n"; push @$T2H_THIS_SECTION, "\n
    \n"; &$T2H_print_Overview(\*FILE); close(FILE) if $T2H_SPLIT; } if ($about_body = &$T2H_about_body()) { print "# writing About in $docu_about_file...\n" if $T2H_VERBOSE; open (FILE, "> $docu_about_file") || die "$ERROR: Can't open $docu_about_file for writing: $!\n" if $T2H_SPLIT; $T2H_HREF{This} = $T2H_HREF{About}; $T2H_NAME{This} = $T2H_NAME{About}; $T2H_THIS_SECTION = [$about_body]; &$T2H_print_About(\*FILE); close(FILE) if $T2H_SPLIT; } unless ($T2H_SPLIT) { &$T2H_print_page_foot(\*FILE); close (FILE); } Finish: print "# that's all folks\n" if $T2H_VERBOSE; exit(0); #+++############################################################################ # # # Low level functions # # # #---############################################################################ sub LocateIncludeFile { my $file = shift; my $dir; return $file if (-e $file && -r $file); foreach $dir (@T2H_INCLUDE_DIRS) { return "$dir/$file" if (-e "$dir/$file" && -r "$dir/$file"); } return undef; } sub clean_name { local ($_); $_ = &remove_style($_[0]); &unprotect_texi; return $_; } sub update_sec_num { local($name, $level) = @_; my $ret; $level--; # here we start at 0 if ($name =~ /^appendix/ || defined(@appendix_sec_num)) { # appendix style if (defined(@appendix_sec_num)) { &incr_sec_num($level, @appendix_sec_num); } else { @appendix_sec_num = ('A', 0, 0, 0); } $ret = join('.', @appendix_sec_num[0..$level]); } else { # normal style if (defined(@normal_sec_num)) { &incr_sec_num($level, @normal_sec_num); } else { @normal_sec_num = (1, 0, 0, 0); } $ret = join('.', @normal_sec_num[0..$level]); } $ret .= "." if $level == 0; return $ret; } sub incr_sec_num { local($level, $l); $level = shift(@_); $_[$level]++; foreach $l ($level+1 .. 3) { $_[$l] = 0; } } sub Sec2UpNode { my $sec = shift; my $num = $sec2number{$sec}; return '' unless $num; return 'Top' unless $num =~ /\.\d+/; $num =~ s/\.[^\.]*$//; $num = $num . '.' unless $num =~ /\./; return $sec2node{$number2sec{$num}}; } sub Sec2PrevNode { my $sec = shift; my $num = $sec2number{$sec}; my ($i, $post); if ($num =~ /(\w+)(\.$|$)/) { $num = $`; $i = $1; $post = $2; if ($i eq 'A') { $i = $normal_sec_num[0]; } elsif ($i ne '1') { # unfortunately, -- operator is not magical $i = chr(ord($i) + 1); } else { return ''; } return $sec2node{$number2sec{$num . $i . $post}} } return ''; } sub Sec2NextNode { my $sec = shift; my $num = $sec2number{$sec}; my $i; if ($num =~ /(\w+)(\.$|$)/) { $num = $`; $i = $1; $post = $2; if ($post eq '.' && $i eq $normal_sec_num[0]) { $i = 'A'; } else { $i++; } return $sec2node{$number2sec{$num . $i . $post}} } return ''; } sub check { local($_, %seen, %context, $before, $match, $after); while (<>) { if (/\@(\*|\.|\:|\@|\{|\})/) { $seen{$&}++; $context{$&} .= "> $_" if $T2H_VERBOSE; $_ = "$`XX$'"; redo; } if (/\@(\w+)/) { ($before, $match, $after) = ($`, $&, $'); if ($before =~ /\b[\w-]+$/ && $after =~ /^[\w-.]*\b/) { # e-mail address $seen{'e-mail address'}++; $context{'e-mail address'} .= "> $_" if $T2H_VERBOSE; } else { $seen{$match}++; $context{$match} .= "> $_" if $T2H_VERBOSE; } $match =~ s/^\@/X/; $_ = "$before$match$after"; redo; } } foreach (sort(keys(%seen))) { if ($T2H_VERBOSE) { print "$_\n"; print $context{$_}; } else { print "$_ ($seen{$_})\n"; } } } sub open { local($name) = @_; ++$fh_name; if (open($fh_name, $name)) { unshift(@fhs, $fh_name); } else { warn "$ERROR Can't read file $name: $!\n"; } } sub init_input { @fhs = (); # hold the file handles to read @input_spool = (); # spooled lines to read $fh_name = 'FH000'; &open($docu); } sub next_line { local($fh, $line); if (@input_spool) { $line = shift(@input_spool); return($line); } while (@fhs) { $fh = $fhs[0]; $line = <$fh>; return($line) if $line; close($fh); shift(@fhs); } return(undef); } # used in pass 1, use &next_line sub skip_until { local($tag) = @_; local($_); while ($_ = &next_line) { return if /^\@end\s+$tag\s*$/; } die "* Failed to find '$tag' after: " . $lines[$#lines]; } # # HTML stacking to have a better HTML output # sub html_reset { @html_stack = ('html'); $html_element = 'body'; } sub html_push { local($what) = @_; push(@html_stack, $html_element); $html_element = $what; } sub html_push_if { local($what) = @_; push(@html_stack, $html_element) if ($html_element && $html_element ne 'p'); $html_element = $what; } sub html_pop { $html_element = pop(@html_stack); } sub html_pop_if { local($elt); if (@_) { foreach $elt (@_) { if ($elt eq $html_element) { $html_element = pop(@html_stack) if @html_stack; last; } } } else { $html_element = pop(@html_stack) if @html_stack; } } sub html_debug { local($what, $line) = @_; if ($T2H_DEBUG & $DEBUG_HTML) { $what = "\n" unless $what; return("$what") } return($what); } # to debug the output... sub debug { local($what, $line) = @_; return("$what") if $T2H_DEBUG & $DEBUG_HTML; return($what); } sub SimpleTexi2Html { local $_ = $_[0]; &protect_texi; &protect_html; $_ = substitute_style($_); $_[0] = $_; } sub normalise_node { local $_ = $_[0]; s/\s+/ /g; s/ $//; s/^ //; &protect_texi; &protect_html; $_ = substitute_style($_); $_[0] = $_; } sub menu_entry { my ($node, $name, $descr) = @_; my ($href, $entry); &normalise_node($node); $href = $node2href{$node}; if ($href) { $descr =~ s/^\s+//; $descr =~ s/\s*$//; $descr = SimpleTexi2Html($descr); if ($T2H_NUMBER_SECTIONS && !$T2H_NODE_NAME_IN_MENU && $node2sec{$node}) { $entry = $node2sec{$node}; $name = ''; } else { &normalise_node($name); $entry = ($name && ($name ne $node || ! $T2H_AVOID_MENU_REDUNDANCY) ? "$name : $node" : $node); } if ($T2H_AVOID_MENU_REDUNDANCY && $descr) { my $clean_entry = $entry; $clean_entry =~ s/^.*? // if ($clean_entry =~ /^([A-Z]|\d+)\.[\d\.]* /); $clean_entry =~ s/[^\w]//g; my $clean_descr = $descr; $clean_descr =~ s/[^\w]//g; $descr = '' if ($clean_entry eq $clean_descr) } push(@lines2,&debug('
    \n", __LINE__)); } elsif ($node =~ /^\(.*\)\w+/) { push(@lines2,&debug('\n", __LINE__)) } else { warn "$ERROR Undefined node of menu_entry ($node): $_"; } } sub do_ctrl { "^$_[0]" } sub do_email { local($addr, $text) = split(/,\s*/, $_[0]); $text = $addr unless $text; &t2h_anchor('', "mailto:$addr", $text); } sub do_sc { $_ = $_[0]; s/([a-z]*)/\U\1\E<\/small>/g; return $_; } sub do_math { return "$_[0]"; } sub do_uref { local($url, $text, $only_text) = split(/,\s*/, $_[0]); $text = $only_text if $only_text; $text = $url unless $text; &t2h_anchor('', $url, $text); } sub do_url { &t2h_anchor('', $_[0], $_[0]) } sub do_acronym { return "$_[0]"; } sub do_accent { return "&$_[0]acute;" if $_[1] eq 'H'; return "$_[0]." if $_[1] eq 'dotaccent'; return "$_[0]*" if $_[1] eq 'ringaccent'; return "$_[0]".'[' if $_[1] eq 'tieaccent'; return "$_[0]".'(' if $_[1] eq 'u'; return "$_[0]_" if $_[1] eq 'ubaraccent'; return ".$_[0]" if $_[1] eq 'udotaccent'; return "$_[0]<" if $_[1] eq 'v'; return "&$_[0]cedil;" if $_[1] eq ','; return "$_[0]" if $_[1] eq 'dotless'; return undef; } sub apply_style { local($texi_style, $text) = @_; local($style); $style = $style_map{$texi_style}; if (defined($style)) { # known style if ($style =~ /^\"/) { # add quotes $style = $'; $text = "\`$text\'"; } if ($style =~ /^\&/) { # custom $style = $'; $text = &$style($text, $texi_style); } elsif ($style) { # good style $text = "<$style>$text"; } else { # no style } } else { # unknown style $text = undef; } return($text); } # remove Texinfo styles sub remove_style { local($_) = @_; 1 while(s/\@\w+{([^\{\}]+)}/$1/g); return($_); } sub remove_things { local ($_) = @_; s|\@(\w+)\{\}|$1|g; return $_; } sub substitute_style { local($_) = @_; local($changed, $done, $style, $text); &simple_substitutions; $changed = 1; while ($changed) { $changed = 0; $done = ''; while (/\@(\w+){([^\{\}]+)}/ || /\@(,){([^\{\}]+)}/) { $text = &apply_style($1, $2); if ($text) { $_ = "$`$text$'"; $changed = 1; } else { $done .= "$`\@$1"; $_ = "{$2}$'"; } } $_ = $done . $_; } return($_); } sub t2h_anchor { local($name, $href, $text, $newline, $extra_attribs) = @_; local($result); $result = " $what =~ s/\&/\&/g; $what =~ s/\/\>/g; # restore anything in quotes # this fixes my problem where I had: # < IMG SRC="leftarrow.gif" ALT="<--" > but what if I wanted < in my ALT text ?? # maybe byte stuffing or some other technique should be used. $what =~ s/\"([^\&]+)\<(.*)\"/"$1<$2"/g; $what =~ s/\"([^\&]+)\>(.*)\"/"$1>$2"/g; $what =~ s/\"([^\&]+)\&(.*)\"/"$1&$2"/g; # but recognize some HTML things $what =~ s/\<\/a\>/<\/a>/g; # $what =~ s/\<a ([^\&]+)\>//g; # $what =~ s/\<img ([^\&]+)\>//g; # return($what); } sub unprotect_texi { s/$;0/\@/go; s/$;1/\{/go; s/$;2/\}/go; s/$;3/\`/go; s/$;4/\'/go; } sub Unprotect_texi { local $_ = shift; &unprotect_texi; return($_); } sub unprotect_html { local($what) = @_; $what =~ s/\&/\&/g; $what =~ s/\</\/g; return($what); } sub t2h_print_label { my $fh = shift; my $href = shift || $T2H_HREF{This}; $href =~ s/.*#(.*)$/$1/; print $fh qq{\n}; } ############################################################################## # These next few lines are legal in both Perl and nroff. .00 ; # finish .ig 'di \" finish diversion--previous line must be blank .nr nl 0-1 \" fake up transition to first page again .nr % 0 \" start at page 1 '; __END__ ############# From here on it's a standard manual page ############ .so /usr/local/man/man1/texi2html.1 smalltalk-3.2.5/build-aux/sigaltstack-longjmp.m40000644000175000017500000000546012123404352016540 00000000000000# sigaltstack-longjmp.m4 serial 3 (libsigsegv-2.4) dnl Copyright (C) 2002-2003, 2006 Bruno Haible dnl This file is free software, distributed under the terms of the GNU dnl General Public License. As a special exception to the GNU General dnl Public License, this file may be distributed as part of a program dnl that contains a configuration script generated by Autoconf, under dnl the same distribution terms as the rest of that program. dnl How to longjmp out of a signal handler, in such a way that the dnl alternate signal stack remains functional. dnl SV_TRY_LEAVE_HANDLER_LONGJMP(KIND, CACHESYMBOL, KNOWN-SYSTEMS, dnl INCLUDES, RESETCODE) AC_DEFUN([SV_TRY_LEAVE_HANDLER_LONGJMP], [ AC_REQUIRE([AC_PROG_CC]) AC_REQUIRE([AC_CANONICAL_HOST]) AC_CACHE_CHECK([whether a signal handler can be left through longjmp$1], [$2], [ AC_RUN_IFELSE([ AC_LANG_SOURCE([[ #include #include #include $4 #if HAVE_SETRLIMIT # include # include # include #endif jmp_buf mainloop; sigset_t mainsigset; int pass = 0; void stackoverflow_handler (int sig) { pass++; sigprocmask (SIG_SETMASK, &mainsigset, NULL); { $5 } longjmp (mainloop, pass); } volatile int * recurse_1 (volatile int n, volatile int *p) { if (n >= 0) *recurse_1 (n + 1, p) += n; return p; } volatile int recurse (volatile int n) { int sum = 0; return *recurse_1 (n, &sum); } char mystack[16384]; int main () { stack_t altstack; struct sigaction action; sigset_t emptyset; #if defined HAVE_SETRLIMIT && defined RLIMIT_STACK /* Before starting the endless recursion, try to be friendly to the user's machine. On some Linux 2.2.x systems, there is no stack limit for user processes at all. We don't want to kill such systems. */ struct rlimit rl; rl.rlim_cur = rl.rlim_max = 0x100000; /* 1 MB */ setrlimit (RLIMIT_STACK, &rl); #endif /* Install the alternate stack. */ altstack.ss_sp = mystack; altstack.ss_size = sizeof (mystack); altstack.ss_flags = 0; /* no SS_DISABLE */ if (sigaltstack (&altstack, NULL) < 0) exit (1); /* Install the SIGSEGV handler. */ sigemptyset (&action.sa_mask); action.sa_handler = &stackoverflow_handler; action.sa_flags = SA_ONSTACK; sigaction (SIGSEGV, &action, (struct sigaction *) NULL); sigaction (SIGBUS, &action, (struct sigaction *) NULL); /* Save the current signal mask. */ sigemptyset (&emptyset); sigprocmask (SIG_BLOCK, &emptyset, &mainsigset); /* Provoke two stack overflows in a row. */ if (setjmp (mainloop) < 2) { recurse (0); exit (2); } exit (0); }]])], [$2=yes], [$2=no], [case "$host" in m4_if([$3], [], [], [[$3]) $2=yes ;;]) *) $2="guessing no" ;; esac ]) ]) ]) smalltalk-3.2.5/build-aux/strtoul.m40000644000175000017500000000153012123404352014271 00000000000000dnl I'd like this to be edited in -*- Autoconf -*- mode... dnl AC_DEFUN([GST_FUNC_STRTOUL], [ # Check for strtoul. Under some versions of AIX, strtoul returns # an incorrect terminator pointer for the string "0". AC_CACHE_CHECK(for working strtoul, gst_cv_working_strtoul, [ exec AS_MESSAGE_FD([])>/dev/null AC_CHECK_FUNC(strtoul, gst_cv_working_strtoul=yes, gst_cv_working_strtoul=no) if test $gst_cv_working_strtoul = yes; then AC_RUN_IFELSE([AC_LANG_SOURCE([[ extern int strtoul(); int main() { char *string = "0"; char *term; int value; value = strtoul(string, &term, 0); exit((value != 0) || (term != (string+1))); }]])],[],[gst_cv_working_strtoul=no],[gst_cv_working_strtoul=no]) fi test "$silent" != yes && exec AS_MESSAGE_FD([])>&1 ]) test "$gst_cv_working_strtoul" != yes && AC_LIBOBJ(strtoul) ])dnl smalltalk-3.2.5/build-aux/config.sub0000755000175000017500000010532712130455425014314 00000000000000#! /bin/sh # Configuration validation subroutine script. # Copyright (C) 1992, 1993, 1994, 1995, 1996, 1997, 1998, 1999, # 2000, 2001, 2002, 2003, 2004, 2005, 2006, 2007, 2008, 2009, 2010, # 2011, 2012 Free Software Foundation, Inc. timestamp='2012-04-18' # This file is (in principle) common to ALL GNU software. # The presence of a machine in this file suggests that SOME GNU software # can handle that machine. It does not imply ALL GNU software can. # # This file is free software; you can redistribute it and/or modify # it under the terms of the GNU General Public License as published by # the Free Software Foundation; either version 2 of the License, or # (at your option) any later version. # # This program is distributed in the hope that it will be useful, # but WITHOUT ANY WARRANTY; without even the implied warranty of # MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the # GNU General Public License for more details. # # You should have received a copy of the GNU General Public License # along with this program; if not, see . # # As a special exception to the GNU General Public License, if you # distribute this file as part of a program that contains a # configuration script generated by Autoconf, you may include it under # the same distribution terms that you use for the rest of that program. # Please send patches to . Submit a context # diff and a properly formatted GNU ChangeLog entry. # # Configuration subroutine to validate and canonicalize a configuration type. # Supply the specified configuration type as an argument. # If it is invalid, we print an error message on stderr and exit with code 1. # Otherwise, we print the canonical config type on stdout and succeed. # You can get the latest version of this script from: # http://git.savannah.gnu.org/gitweb/?p=config.git;a=blob_plain;f=config.sub;hb=HEAD # This file is supposed to be the same for all GNU packages # and recognize all the CPU types, system types and aliases # that are meaningful with *any* GNU software. # Each package is responsible for reporting which valid configurations # it does not support. The user should be able to distinguish # a failure to support a valid configuration from a meaningless # configuration. # The goal of this file is to map all the various variations of a given # machine specification into a single specification in the form: # CPU_TYPE-MANUFACTURER-OPERATING_SYSTEM # or in some cases, the newer four-part form: # CPU_TYPE-MANUFACTURER-KERNEL-OPERATING_SYSTEM # It is wrong to echo any other type of specification. me=`echo "$0" | sed -e 's,.*/,,'` usage="\ Usage: $0 [OPTION] CPU-MFR-OPSYS $0 [OPTION] ALIAS Canonicalize a configuration name. Operation modes: -h, --help print this help, then exit -t, --time-stamp print date of last modification, then exit -v, --version print version number, then exit Report bugs and patches to ." version="\ GNU config.sub ($timestamp) Copyright (C) 1992, 1993, 1994, 1995, 1996, 1997, 1998, 1999, 2000, 2001, 2002, 2003, 2004, 2005, 2006, 2007, 2008, 2009, 2010, 2011, 2012 Free Software Foundation, Inc. This is free software; see the source for copying conditions. There is NO warranty; not even for MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE." help=" Try \`$me --help' for more information." # Parse command line while test $# -gt 0 ; do case $1 in --time-stamp | --time* | -t ) echo "$timestamp" ; exit ;; --version | -v ) echo "$version" ; exit ;; --help | --h* | -h ) echo "$usage"; exit ;; -- ) # Stop option processing shift; break ;; - ) # Use stdin as input. break ;; -* ) echo "$me: invalid option $1$help" exit 1 ;; *local*) # First pass through any local machine types. echo $1 exit ;; * ) break ;; esac done case $# in 0) echo "$me: missing argument$help" >&2 exit 1;; 1) ;; *) echo "$me: too many arguments$help" >&2 exit 1;; esac # Separate what the user gave into CPU-COMPANY and OS or KERNEL-OS (if any). # Here we must recognize all the valid KERNEL-OS combinations. maybe_os=`echo $1 | sed 's/^\(.*\)-\([^-]*-[^-]*\)$/\2/'` case $maybe_os in nto-qnx* | linux-gnu* | linux-android* | linux-dietlibc | linux-newlib* | \ linux-uclibc* | uclinux-uclibc* | uclinux-gnu* | kfreebsd*-gnu* | \ knetbsd*-gnu* | netbsd*-gnu* | \ kopensolaris*-gnu* | \ storm-chaos* | os2-emx* | rtmk-nova*) os=-$maybe_os basic_machine=`echo $1 | sed 's/^\(.*\)-\([^-]*-[^-]*\)$/\1/'` ;; android-linux) os=-linux-android basic_machine=`echo $1 | sed 's/^\(.*\)-\([^-]*-[^-]*\)$/\1/'`-unknown ;; *) basic_machine=`echo $1 | sed 's/-[^-]*$//'` if [ $basic_machine != $1 ] then os=`echo $1 | sed 's/.*-/-/'` else os=; fi ;; esac ### Let's recognize common machines as not being operating systems so ### that things like config.sub decstation-3100 work. We also ### recognize some manufacturers as not being operating systems, so we ### can provide default operating systems below. case $os in -sun*os*) # Prevent following clause from handling this invalid input. ;; -dec* | -mips* | -sequent* | -encore* | -pc532* | -sgi* | -sony* | \ -att* | -7300* | -3300* | -delta* | -motorola* | -sun[234]* | \ -unicom* | -ibm* | -next | -hp | -isi* | -apollo | -altos* | \ -convergent* | -ncr* | -news | -32* | -3600* | -3100* | -hitachi* |\ -c[123]* | -convex* | -sun | -crds | -omron* | -dg | -ultra | -tti* | \ -harris | -dolphin | -highlevel | -gould | -cbm | -ns | -masscomp | \ -apple | -axis | -knuth | -cray | -microblaze) os= basic_machine=$1 ;; -bluegene*) os=-cnk ;; -sim | -cisco | -oki | -wec | -winbond) os= basic_machine=$1 ;; -scout) ;; -wrs) os=-vxworks basic_machine=$1 ;; -chorusos*) os=-chorusos basic_machine=$1 ;; -chorusrdb) os=-chorusrdb basic_machine=$1 ;; -hiux*) os=-hiuxwe2 ;; -sco6) os=-sco5v6 basic_machine=`echo $1 | sed -e 's/86-.*/86-pc/'` ;; -sco5) os=-sco3.2v5 basic_machine=`echo $1 | sed -e 's/86-.*/86-pc/'` ;; -sco4) os=-sco3.2v4 basic_machine=`echo $1 | sed -e 's/86-.*/86-pc/'` ;; -sco3.2.[4-9]*) os=`echo $os | sed -e 's/sco3.2./sco3.2v/'` basic_machine=`echo $1 | sed -e 's/86-.*/86-pc/'` ;; -sco3.2v[4-9]*) # Don't forget version if it is 3.2v4 or newer. basic_machine=`echo $1 | sed -e 's/86-.*/86-pc/'` ;; -sco5v6*) # Don't forget version if it is 3.2v4 or newer. basic_machine=`echo $1 | sed -e 's/86-.*/86-pc/'` ;; -sco*) os=-sco3.2v2 basic_machine=`echo $1 | sed -e 's/86-.*/86-pc/'` ;; -udk*) basic_machine=`echo $1 | sed -e 's/86-.*/86-pc/'` ;; -isc) os=-isc2.2 basic_machine=`echo $1 | sed -e 's/86-.*/86-pc/'` ;; -clix*) basic_machine=clipper-intergraph ;; -isc*) basic_machine=`echo $1 | sed -e 's/86-.*/86-pc/'` ;; -lynx*178) os=-lynxos178 ;; -lynx*5) os=-lynxos5 ;; -lynx*) os=-lynxos ;; -ptx*) basic_machine=`echo $1 | sed -e 's/86-.*/86-sequent/'` ;; -windowsnt*) os=`echo $os | sed -e 's/windowsnt/winnt/'` ;; -psos*) os=-psos ;; -mint | -mint[0-9]*) basic_machine=m68k-atari os=-mint ;; esac # Decode aliases for certain CPU-COMPANY combinations. case $basic_machine in # Recognize the basic CPU types without company name. # Some are omitted here because they have special meanings below. 1750a | 580 \ | a29k \ | aarch64 | aarch64_be \ | alpha | alphaev[4-8] | alphaev56 | alphaev6[78] | alphapca5[67] \ | alpha64 | alpha64ev[4-8] | alpha64ev56 | alpha64ev6[78] | alpha64pca5[67] \ | am33_2.0 \ | arc | arm | arm[bl]e | arme[lb] | armv[2345] | armv[345][lb] | avr | avr32 \ | be32 | be64 \ | bfin \ | c4x | clipper \ | d10v | d30v | dlx | dsp16xx \ | epiphany \ | fido | fr30 | frv \ | h8300 | h8500 | hppa | hppa1.[01] | hppa2.0 | hppa2.0[nw] | hppa64 \ | hexagon \ | i370 | i860 | i960 | ia64 \ | ip2k | iq2000 \ | le32 | le64 \ | lm32 \ | m32c | m32r | m32rle | m68000 | m68k | m88k \ | maxq | mb | microblaze | mcore | mep | metag \ | mips | mipsbe | mipseb | mipsel | mipsle \ | mips16 \ | mips64 | mips64el \ | mips64octeon | mips64octeonel \ | mips64orion | mips64orionel \ | mips64r5900 | mips64r5900el \ | mips64vr | mips64vrel \ | mips64vr4100 | mips64vr4100el \ | mips64vr4300 | mips64vr4300el \ | mips64vr5000 | mips64vr5000el \ | mips64vr5900 | mips64vr5900el \ | mipsisa32 | mipsisa32el \ | mipsisa32r2 | mipsisa32r2el \ | mipsisa64 | mipsisa64el \ | mipsisa64r2 | mipsisa64r2el \ | mipsisa64sb1 | mipsisa64sb1el \ | mipsisa64sr71k | mipsisa64sr71kel \ | mipstx39 | mipstx39el \ | mn10200 | mn10300 \ | moxie \ | mt \ | msp430 \ | nds32 | nds32le | nds32be \ | nios | nios2 \ | ns16k | ns32k \ | open8 \ | or32 \ | pdp10 | pdp11 | pj | pjl \ | powerpc | powerpc64 | powerpc64le | powerpcle \ | pyramid \ | rl78 | rx \ | score \ | sh | sh[1234] | sh[24]a | sh[24]aeb | sh[23]e | sh[34]eb | sheb | shbe | shle | sh[1234]le | sh3ele \ | sh64 | sh64le \ | sparc | sparc64 | sparc64b | sparc64v | sparc86x | sparclet | sparclite \ | sparcv8 | sparcv9 | sparcv9b | sparcv9v \ | spu \ | tahoe | tic4x | tic54x | tic55x | tic6x | tic80 | tron \ | ubicom32 \ | v850 | v850e | v850e1 | v850e2 | v850es | v850e2v3 \ | we32k \ | x86 | xc16x | xstormy16 | xtensa \ | z8k | z80) basic_machine=$basic_machine-unknown ;; c54x) basic_machine=tic54x-unknown ;; c55x) basic_machine=tic55x-unknown ;; c6x) basic_machine=tic6x-unknown ;; m6811 | m68hc11 | m6812 | m68hc12 | m68hcs12x | picochip) basic_machine=$basic_machine-unknown os=-none ;; m88110 | m680[12346]0 | m683?2 | m68360 | m5200 | v70 | w65 | z8k) ;; ms1) basic_machine=mt-unknown ;; strongarm | thumb | xscale) basic_machine=arm-unknown ;; xgate) basic_machine=$basic_machine-unknown os=-none ;; xscaleeb) basic_machine=armeb-unknown ;; xscaleel) basic_machine=armel-unknown ;; # We use `pc' rather than `unknown' # because (1) that's what they normally are, and # (2) the word "unknown" tends to confuse beginning users. i*86 | x86_64) basic_machine=$basic_machine-pc ;; # Object if more than one company name word. *-*-*) echo Invalid configuration \`$1\': machine \`$basic_machine\' not recognized 1>&2 exit 1 ;; # Recognize the basic CPU types with company name. 580-* \ | a29k-* \ | aarch64-* | aarch64_be-* \ | alpha-* | alphaev[4-8]-* | alphaev56-* | alphaev6[78]-* \ | alpha64-* | alpha64ev[4-8]-* | alpha64ev56-* | alpha64ev6[78]-* \ | alphapca5[67]-* | alpha64pca5[67]-* | arc-* \ | arm-* | armbe-* | armle-* | armeb-* | armv*-* \ | avr-* | avr32-* \ | be32-* | be64-* \ | bfin-* | bs2000-* \ | c[123]* | c30-* | [cjt]90-* | c4x-* \ | clipper-* | craynv-* | cydra-* \ | d10v-* | d30v-* | dlx-* \ | elxsi-* \ | f30[01]-* | f700-* | fido-* | fr30-* | frv-* | fx80-* \ | h8300-* | h8500-* \ | hppa-* | hppa1.[01]-* | hppa2.0-* | hppa2.0[nw]-* | hppa64-* \ | hexagon-* \ | i*86-* | i860-* | i960-* | ia64-* \ | ip2k-* | iq2000-* \ | le32-* | le64-* \ | lm32-* \ | m32c-* | m32r-* | m32rle-* \ | m68000-* | m680[012346]0-* | m68360-* | m683?2-* | m68k-* \ | m88110-* | m88k-* | maxq-* | mcore-* | metag-* | microblaze-* \ | mips-* | mipsbe-* | mipseb-* | mipsel-* | mipsle-* \ | mips16-* \ | mips64-* | mips64el-* \ | mips64octeon-* | mips64octeonel-* \ | mips64orion-* | mips64orionel-* \ | mips64r5900-* | mips64r5900el-* \ | mips64vr-* | mips64vrel-* \ | mips64vr4100-* | mips64vr4100el-* \ | mips64vr4300-* | mips64vr4300el-* \ | mips64vr5000-* | mips64vr5000el-* \ | mips64vr5900-* | mips64vr5900el-* \ | mipsisa32-* | mipsisa32el-* \ | mipsisa32r2-* | mipsisa32r2el-* \ | mipsisa64-* | mipsisa64el-* \ | mipsisa64r2-* | mipsisa64r2el-* \ | mipsisa64sb1-* | mipsisa64sb1el-* \ | mipsisa64sr71k-* | mipsisa64sr71kel-* \ | mipstx39-* | mipstx39el-* \ | mmix-* \ | mt-* \ | msp430-* \ | nds32-* | nds32le-* | nds32be-* \ | nios-* | nios2-* \ | none-* | np1-* | ns16k-* | ns32k-* \ | open8-* \ | orion-* \ | pdp10-* | pdp11-* | pj-* | pjl-* | pn-* | power-* \ | powerpc-* | powerpc64-* | powerpc64le-* | powerpcle-* \ | pyramid-* \ | rl78-* | romp-* | rs6000-* | rx-* \ | sh-* | sh[1234]-* | sh[24]a-* | sh[24]aeb-* | sh[23]e-* | sh[34]eb-* | sheb-* | shbe-* \ | shle-* | sh[1234]le-* | sh3ele-* | sh64-* | sh64le-* \ | sparc-* | sparc64-* | sparc64b-* | sparc64v-* | sparc86x-* | sparclet-* \ | sparclite-* \ | sparcv8-* | sparcv9-* | sparcv9b-* | sparcv9v-* | sv1-* | sx?-* \ | tahoe-* \ | tic30-* | tic4x-* | tic54x-* | tic55x-* | tic6x-* | tic80-* \ | tile*-* \ | tron-* \ | ubicom32-* \ | v850-* | v850e-* | v850e1-* | v850es-* | v850e2-* | v850e2v3-* \ | vax-* \ | we32k-* \ | x86-* | x86_64-* | xc16x-* | xps100-* \ | xstormy16-* | xtensa*-* \ | ymp-* \ | z8k-* | z80-*) ;; # Recognize the basic CPU types without company name, with glob match. xtensa*) basic_machine=$basic_machine-unknown ;; # Recognize the various machine names and aliases which stand # for a CPU type and a company and sometimes even an OS. 386bsd) basic_machine=i386-unknown os=-bsd ;; 3b1 | 7300 | 7300-att | att-7300 | pc7300 | safari | unixpc) basic_machine=m68000-att ;; 3b*) basic_machine=we32k-att ;; a29khif) basic_machine=a29k-amd os=-udi ;; abacus) basic_machine=abacus-unknown ;; adobe68k) basic_machine=m68010-adobe os=-scout ;; alliant | fx80) basic_machine=fx80-alliant ;; altos | altos3068) basic_machine=m68k-altos ;; am29k) basic_machine=a29k-none os=-bsd ;; amd64) basic_machine=x86_64-pc ;; amd64-*) basic_machine=x86_64-`echo $basic_machine | sed 's/^[^-]*-//'` ;; amdahl) basic_machine=580-amdahl os=-sysv ;; amiga | amiga-*) basic_machine=m68k-unknown ;; amigaos | amigados) basic_machine=m68k-unknown os=-amigaos ;; amigaunix | amix) basic_machine=m68k-unknown os=-sysv4 ;; apollo68) basic_machine=m68k-apollo os=-sysv ;; apollo68bsd) basic_machine=m68k-apollo os=-bsd ;; aros) basic_machine=i386-pc os=-aros ;; aux) basic_machine=m68k-apple os=-aux ;; balance) basic_machine=ns32k-sequent os=-dynix ;; blackfin) basic_machine=bfin-unknown os=-linux ;; blackfin-*) basic_machine=bfin-`echo $basic_machine | sed 's/^[^-]*-//'` os=-linux ;; bluegene*) basic_machine=powerpc-ibm os=-cnk ;; c54x-*) basic_machine=tic54x-`echo $basic_machine | sed 's/^[^-]*-//'` ;; c55x-*) basic_machine=tic55x-`echo $basic_machine | sed 's/^[^-]*-//'` ;; c6x-*) basic_machine=tic6x-`echo $basic_machine | sed 's/^[^-]*-//'` ;; c90) basic_machine=c90-cray os=-unicos ;; cegcc) basic_machine=arm-unknown os=-cegcc ;; convex-c1) basic_machine=c1-convex os=-bsd ;; convex-c2) basic_machine=c2-convex os=-bsd ;; convex-c32) basic_machine=c32-convex os=-bsd ;; convex-c34) basic_machine=c34-convex os=-bsd ;; convex-c38) basic_machine=c38-convex os=-bsd ;; cray | j90) basic_machine=j90-cray os=-unicos ;; craynv) basic_machine=craynv-cray os=-unicosmp ;; cr16 | cr16-*) basic_machine=cr16-unknown os=-elf ;; crds | unos) basic_machine=m68k-crds ;; crisv32 | crisv32-* | etraxfs*) basic_machine=crisv32-axis ;; cris | cris-* | etrax*) basic_machine=cris-axis ;; crx) basic_machine=crx-unknown os=-elf ;; da30 | da30-*) basic_machine=m68k-da30 ;; decstation | decstation-3100 | pmax | pmax-* | pmin | dec3100 | decstatn) basic_machine=mips-dec ;; decsystem10* | dec10*) basic_machine=pdp10-dec os=-tops10 ;; decsystem20* | dec20*) basic_machine=pdp10-dec os=-tops20 ;; delta | 3300 | motorola-3300 | motorola-delta \ | 3300-motorola | delta-motorola) basic_machine=m68k-motorola ;; delta88) basic_machine=m88k-motorola os=-sysv3 ;; dicos) basic_machine=i686-pc os=-dicos ;; djgpp) basic_machine=i586-pc os=-msdosdjgpp ;; dpx20 | dpx20-*) basic_machine=rs6000-bull os=-bosx ;; dpx2* | dpx2*-bull) basic_machine=m68k-bull os=-sysv3 ;; ebmon29k) basic_machine=a29k-amd os=-ebmon ;; elxsi) basic_machine=elxsi-elxsi os=-bsd ;; encore | umax | mmax) basic_machine=ns32k-encore ;; es1800 | OSE68k | ose68k | ose | OSE) basic_machine=m68k-ericsson os=-ose ;; fx2800) basic_machine=i860-alliant ;; genix) basic_machine=ns32k-ns ;; gmicro) basic_machine=tron-gmicro os=-sysv ;; go32) basic_machine=i386-pc os=-go32 ;; h3050r* | hiux*) basic_machine=hppa1.1-hitachi os=-hiuxwe2 ;; h8300hms) basic_machine=h8300-hitachi os=-hms ;; h8300xray) basic_machine=h8300-hitachi os=-xray ;; h8500hms) basic_machine=h8500-hitachi os=-hms ;; harris) basic_machine=m88k-harris os=-sysv3 ;; hp300-*) basic_machine=m68k-hp ;; hp300bsd) basic_machine=m68k-hp os=-bsd ;; hp300hpux) basic_machine=m68k-hp os=-hpux ;; hp3k9[0-9][0-9] | hp9[0-9][0-9]) basic_machine=hppa1.0-hp ;; hp9k2[0-9][0-9] | hp9k31[0-9]) basic_machine=m68000-hp ;; hp9k3[2-9][0-9]) basic_machine=m68k-hp ;; hp9k6[0-9][0-9] | hp6[0-9][0-9]) basic_machine=hppa1.0-hp ;; hp9k7[0-79][0-9] | hp7[0-79][0-9]) basic_machine=hppa1.1-hp ;; hp9k78[0-9] | hp78[0-9]) # FIXME: really hppa2.0-hp basic_machine=hppa1.1-hp ;; hp9k8[67]1 | hp8[67]1 | hp9k80[24] | hp80[24] | hp9k8[78]9 | hp8[78]9 | hp9k893 | hp893) # FIXME: really hppa2.0-hp basic_machine=hppa1.1-hp ;; hp9k8[0-9][13679] | hp8[0-9][13679]) basic_machine=hppa1.1-hp ;; hp9k8[0-9][0-9] | hp8[0-9][0-9]) basic_machine=hppa1.0-hp ;; hppa-next) os=-nextstep3 ;; hppaosf) basic_machine=hppa1.1-hp os=-osf ;; hppro) basic_machine=hppa1.1-hp os=-proelf ;; i370-ibm* | ibm*) basic_machine=i370-ibm ;; i*86v32) basic_machine=`echo $1 | sed -e 's/86.*/86-pc/'` os=-sysv32 ;; i*86v4*) basic_machine=`echo $1 | sed -e 's/86.*/86-pc/'` os=-sysv4 ;; i*86v) basic_machine=`echo $1 | sed -e 's/86.*/86-pc/'` os=-sysv ;; i*86sol2) basic_machine=`echo $1 | sed -e 's/86.*/86-pc/'` os=-solaris2 ;; i386mach) basic_machine=i386-mach os=-mach ;; i386-vsta | vsta) basic_machine=i386-unknown os=-vsta ;; iris | iris4d) basic_machine=mips-sgi case $os in -irix*) ;; *) os=-irix4 ;; esac ;; isi68 | isi) basic_machine=m68k-isi os=-sysv ;; m68knommu) basic_machine=m68k-unknown os=-linux ;; m68knommu-*) basic_machine=m68k-`echo $basic_machine | sed 's/^[^-]*-//'` os=-linux ;; m88k-omron*) basic_machine=m88k-omron ;; magnum | m3230) basic_machine=mips-mips os=-sysv ;; merlin) basic_machine=ns32k-utek os=-sysv ;; microblaze) basic_machine=microblaze-xilinx ;; mingw32) basic_machine=i386-pc os=-mingw32 ;; mingw32ce) basic_machine=arm-unknown os=-mingw32ce ;; miniframe) basic_machine=m68000-convergent ;; *mint | -mint[0-9]* | *MiNT | *MiNT[0-9]*) basic_machine=m68k-atari os=-mint ;; mips3*-*) basic_machine=`echo $basic_machine | sed -e 's/mips3/mips64/'` ;; mips3*) basic_machine=`echo $basic_machine | sed -e 's/mips3/mips64/'`-unknown ;; monitor) basic_machine=m68k-rom68k os=-coff ;; morphos) basic_machine=powerpc-unknown os=-morphos ;; msdos) basic_machine=i386-pc os=-msdos ;; ms1-*) basic_machine=`echo $basic_machine | sed -e 's/ms1-/mt-/'` ;; msys) basic_machine=i386-pc os=-msys ;; mvs) basic_machine=i370-ibm os=-mvs ;; nacl) basic_machine=le32-unknown os=-nacl ;; ncr3000) basic_machine=i486-ncr os=-sysv4 ;; netbsd386) basic_machine=i386-unknown os=-netbsd ;; netwinder) basic_machine=armv4l-rebel os=-linux ;; news | news700 | news800 | news900) basic_machine=m68k-sony os=-newsos ;; news1000) basic_machine=m68030-sony os=-newsos ;; news-3600 | risc-news) basic_machine=mips-sony os=-newsos ;; necv70) basic_machine=v70-nec os=-sysv ;; next | m*-next ) basic_machine=m68k-next case $os in -nextstep* ) ;; -ns2*) os=-nextstep2 ;; *) os=-nextstep3 ;; esac ;; nh3000) basic_machine=m68k-harris os=-cxux ;; nh[45]000) basic_machine=m88k-harris os=-cxux ;; nindy960) basic_machine=i960-intel os=-nindy ;; mon960) basic_machine=i960-intel os=-mon960 ;; nonstopux) basic_machine=mips-compaq os=-nonstopux ;; np1) basic_machine=np1-gould ;; neo-tandem) basic_machine=neo-tandem ;; nse-tandem) basic_machine=nse-tandem ;; nsr-tandem) basic_machine=nsr-tandem ;; op50n-* | op60c-*) basic_machine=hppa1.1-oki os=-proelf ;; openrisc | openrisc-*) basic_machine=or32-unknown ;; os400) basic_machine=powerpc-ibm os=-os400 ;; OSE68000 | ose68000) basic_machine=m68000-ericsson os=-ose ;; os68k) basic_machine=m68k-none os=-os68k ;; pa-hitachi) basic_machine=hppa1.1-hitachi os=-hiuxwe2 ;; paragon) basic_machine=i860-intel os=-osf ;; parisc) basic_machine=hppa-unknown os=-linux ;; parisc-*) basic_machine=hppa-`echo $basic_machine | sed 's/^[^-]*-//'` os=-linux ;; pbd) basic_machine=sparc-tti ;; pbb) basic_machine=m68k-tti ;; pc532 | pc532-*) basic_machine=ns32k-pc532 ;; pc98) basic_machine=i386-pc ;; pc98-*) basic_machine=i386-`echo $basic_machine | sed 's/^[^-]*-//'` ;; pentium | p5 | k5 | k6 | nexgen | viac3) basic_machine=i586-pc ;; pentiumpro | p6 | 6x86 | athlon | athlon_*) basic_machine=i686-pc ;; pentiumii | pentium2 | pentiumiii | pentium3) basic_machine=i686-pc ;; pentium4) basic_machine=i786-pc ;; pentium-* | p5-* | k5-* | k6-* | nexgen-* | viac3-*) basic_machine=i586-`echo $basic_machine | sed 's/^[^-]*-//'` ;; pentiumpro-* | p6-* | 6x86-* | athlon-*) basic_machine=i686-`echo $basic_machine | sed 's/^[^-]*-//'` ;; pentiumii-* | pentium2-* | pentiumiii-* | pentium3-*) basic_machine=i686-`echo $basic_machine | sed 's/^[^-]*-//'` ;; pentium4-*) basic_machine=i786-`echo $basic_machine | sed 's/^[^-]*-//'` ;; pn) basic_machine=pn-gould ;; power) basic_machine=power-ibm ;; ppc | ppcbe) basic_machine=powerpc-unknown ;; ppc-* | ppcbe-*) basic_machine=powerpc-`echo $basic_machine | sed 's/^[^-]*-//'` ;; ppcle | powerpclittle | ppc-le | powerpc-little) basic_machine=powerpcle-unknown ;; ppcle-* | powerpclittle-*) basic_machine=powerpcle-`echo $basic_machine | sed 's/^[^-]*-//'` ;; ppc64) basic_machine=powerpc64-unknown ;; ppc64-*) basic_machine=powerpc64-`echo $basic_machine | sed 's/^[^-]*-//'` ;; ppc64le | powerpc64little | ppc64-le | powerpc64-little) basic_machine=powerpc64le-unknown ;; ppc64le-* | powerpc64little-*) basic_machine=powerpc64le-`echo $basic_machine | sed 's/^[^-]*-//'` ;; ps2) basic_machine=i386-ibm ;; pw32) basic_machine=i586-unknown os=-pw32 ;; rdos) basic_machine=i386-pc os=-rdos ;; rom68k) basic_machine=m68k-rom68k os=-coff ;; rm[46]00) basic_machine=mips-siemens ;; rtpc | rtpc-*) basic_machine=romp-ibm ;; s390 | s390-*) basic_machine=s390-ibm ;; s390x | s390x-*) basic_machine=s390x-ibm ;; sa29200) basic_machine=a29k-amd os=-udi ;; sb1) basic_machine=mipsisa64sb1-unknown ;; sb1el) basic_machine=mipsisa64sb1el-unknown ;; sde) basic_machine=mipsisa32-sde os=-elf ;; sei) basic_machine=mips-sei os=-seiux ;; sequent) basic_machine=i386-sequent ;; sh) basic_machine=sh-hitachi os=-hms ;; sh5el) basic_machine=sh5le-unknown ;; sh64) basic_machine=sh64-unknown ;; sparclite-wrs | simso-wrs) basic_machine=sparclite-wrs os=-vxworks ;; sps7) basic_machine=m68k-bull os=-sysv2 ;; spur) basic_machine=spur-unknown ;; st2000) basic_machine=m68k-tandem ;; stratus) basic_machine=i860-stratus os=-sysv4 ;; strongarm-* | thumb-*) basic_machine=arm-`echo $basic_machine | sed 's/^[^-]*-//'` ;; sun2) basic_machine=m68000-sun ;; sun2os3) basic_machine=m68000-sun os=-sunos3 ;; sun2os4) basic_machine=m68000-sun os=-sunos4 ;; sun3os3) basic_machine=m68k-sun os=-sunos3 ;; sun3os4) basic_machine=m68k-sun os=-sunos4 ;; sun4os3) basic_machine=sparc-sun os=-sunos3 ;; sun4os4) basic_machine=sparc-sun os=-sunos4 ;; sun4sol2) basic_machine=sparc-sun os=-solaris2 ;; sun3 | sun3-*) basic_machine=m68k-sun ;; sun4) basic_machine=sparc-sun ;; sun386 | sun386i | roadrunner) basic_machine=i386-sun ;; sv1) basic_machine=sv1-cray os=-unicos ;; symmetry) basic_machine=i386-sequent os=-dynix ;; t3e) basic_machine=alphaev5-cray os=-unicos ;; t90) basic_machine=t90-cray os=-unicos ;; tile*) basic_machine=$basic_machine-unknown os=-linux-gnu ;; tx39) basic_machine=mipstx39-unknown ;; tx39el) basic_machine=mipstx39el-unknown ;; toad1) basic_machine=pdp10-xkl os=-tops20 ;; tower | tower-32) basic_machine=m68k-ncr ;; tpf) basic_machine=s390x-ibm os=-tpf ;; udi29k) basic_machine=a29k-amd os=-udi ;; ultra3) basic_machine=a29k-nyu os=-sym1 ;; v810 | necv810) basic_machine=v810-nec os=-none ;; vaxv) basic_machine=vax-dec os=-sysv ;; vms) basic_machine=vax-dec os=-vms ;; vpp*|vx|vx-*) basic_machine=f301-fujitsu ;; vxworks960) basic_machine=i960-wrs os=-vxworks ;; vxworks68) basic_machine=m68k-wrs os=-vxworks ;; vxworks29k) basic_machine=a29k-wrs os=-vxworks ;; w65*) basic_machine=w65-wdc os=-none ;; w89k-*) basic_machine=hppa1.1-winbond os=-proelf ;; xbox) basic_machine=i686-pc os=-mingw32 ;; xps | xps100) basic_machine=xps100-honeywell ;; xscale-* | xscalee[bl]-*) basic_machine=`echo $basic_machine | sed 's/^xscale/arm/'` ;; ymp) basic_machine=ymp-cray os=-unicos ;; z8k-*-coff) basic_machine=z8k-unknown os=-sim ;; z80-*-coff) basic_machine=z80-unknown os=-sim ;; none) basic_machine=none-none os=-none ;; # Here we handle the default manufacturer of certain CPU types. It is in # some cases the only manufacturer, in others, it is the most popular. w89k) basic_machine=hppa1.1-winbond ;; op50n) basic_machine=hppa1.1-oki ;; op60c) basic_machine=hppa1.1-oki ;; romp) basic_machine=romp-ibm ;; mmix) basic_machine=mmix-knuth ;; rs6000) basic_machine=rs6000-ibm ;; vax) basic_machine=vax-dec ;; pdp10) # there are many clones, so DEC is not a safe bet basic_machine=pdp10-unknown ;; pdp11) basic_machine=pdp11-dec ;; we32k) basic_machine=we32k-att ;; sh[1234] | sh[24]a | sh[24]aeb | sh[34]eb | sh[1234]le | sh[23]ele) basic_machine=sh-unknown ;; sparc | sparcv8 | sparcv9 | sparcv9b | sparcv9v) basic_machine=sparc-sun ;; cydra) basic_machine=cydra-cydrome ;; orion) basic_machine=orion-highlevel ;; orion105) basic_machine=clipper-highlevel ;; mac | mpw | mac-mpw) basic_machine=m68k-apple ;; pmac | pmac-mpw) basic_machine=powerpc-apple ;; *-unknown) # Make sure to match an already-canonicalized machine name. ;; *) echo Invalid configuration \`$1\': machine \`$basic_machine\' not recognized 1>&2 exit 1 ;; esac # Here we canonicalize certain aliases for manufacturers. case $basic_machine in *-digital*) basic_machine=`echo $basic_machine | sed 's/digital.*/dec/'` ;; *-commodore*) basic_machine=`echo $basic_machine | sed 's/commodore.*/cbm/'` ;; *) ;; esac # Decode manufacturer-specific aliases for certain operating systems. if [ x"$os" != x"" ] then case $os in # First match some system type aliases # that might get confused with valid system types. # -solaris* is a basic system type, with this one exception. -auroraux) os=-auroraux ;; -solaris1 | -solaris1.*) os=`echo $os | sed -e 's|solaris1|sunos4|'` ;; -solaris) os=-solaris2 ;; -svr4*) os=-sysv4 ;; -unixware*) os=-sysv4.2uw ;; -gnu/linux*) os=`echo $os | sed -e 's|gnu/linux|linux-gnu|'` ;; # First accept the basic system types. # The portable systems comes first. # Each alternative MUST END IN A *, to match a version number. # -sysv* is not here because it comes later, after sysvr4. -gnu* | -bsd* | -mach* | -minix* | -genix* | -ultrix* | -irix* \ | -*vms* | -sco* | -esix* | -isc* | -aix* | -cnk* | -sunos | -sunos[34]*\ | -hpux* | -unos* | -osf* | -luna* | -dgux* | -auroraux* | -solaris* \ | -sym* | -kopensolaris* \ | -amigaos* | -amigados* | -msdos* | -newsos* | -unicos* | -aof* \ | -aos* | -aros* \ | -nindy* | -vxsim* | -vxworks* | -ebmon* | -hms* | -mvs* \ | -clix* | -riscos* | -uniplus* | -iris* | -rtu* | -xenix* \ | -hiux* | -386bsd* | -knetbsd* | -mirbsd* | -netbsd* \ | -openbsd* | -solidbsd* \ | -ekkobsd* | -kfreebsd* | -freebsd* | -riscix* | -lynxos* \ | -bosx* | -nextstep* | -cxux* | -aout* | -elf* | -oabi* \ | -ptx* | -coff* | -ecoff* | -winnt* | -domain* | -vsta* \ | -udi* | -eabi* | -lites* | -ieee* | -go32* | -aux* \ | -chorusos* | -chorusrdb* | -cegcc* \ | -cygwin* | -msys* | -pe* | -psos* | -moss* | -proelf* | -rtems* \ | -mingw32* | -linux-gnu* | -linux-android* \ | -linux-newlib* | -linux-uclibc* \ | -uxpv* | -beos* | -mpeix* | -udk* \ | -interix* | -uwin* | -mks* | -rhapsody* | -darwin* | -opened* \ | -openstep* | -oskit* | -conix* | -pw32* | -nonstopux* \ | -storm-chaos* | -tops10* | -tenex* | -tops20* | -its* \ | -os2* | -vos* | -palmos* | -uclinux* | -nucleus* \ | -morphos* | -superux* | -rtmk* | -rtmk-nova* | -windiss* \ | -powermax* | -dnix* | -nx6 | -nx7 | -sei* | -dragonfly* \ | -skyos* | -haiku* | -rdos* | -toppers* | -drops* | -es*) # Remember, each alternative MUST END IN *, to match a version number. ;; -qnx*) case $basic_machine in x86-* | i*86-*) ;; *) os=-nto$os ;; esac ;; -nto-qnx*) ;; -nto*) os=`echo $os | sed -e 's|nto|nto-qnx|'` ;; -sim | -es1800* | -hms* | -xray | -os68k* | -none* | -v88r* \ | -windows* | -osx | -abug | -netware* | -os9* | -beos* | -haiku* \ | -macos* | -mpw* | -magic* | -mmixware* | -mon960* | -lnews*) ;; -mac*) os=`echo $os | sed -e 's|mac|macos|'` ;; -linux-dietlibc) os=-linux-dietlibc ;; -linux*) os=`echo $os | sed -e 's|linux|linux-gnu|'` ;; -sunos5*) os=`echo $os | sed -e 's|sunos5|solaris2|'` ;; -sunos6*) os=`echo $os | sed -e 's|sunos6|solaris3|'` ;; -opened*) os=-openedition ;; -os400*) os=-os400 ;; -wince*) os=-wince ;; -osfrose*) os=-osfrose ;; -osf*) os=-osf ;; -utek*) os=-bsd ;; -dynix*) os=-bsd ;; -acis*) os=-aos ;; -atheos*) os=-atheos ;; -syllable*) os=-syllable ;; -386bsd) os=-bsd ;; -ctix* | -uts*) os=-sysv ;; -nova*) os=-rtmk-nova ;; -ns2 ) os=-nextstep2 ;; -nsk*) os=-nsk ;; # Preserve the version number of sinix5. -sinix5.*) os=`echo $os | sed -e 's|sinix|sysv|'` ;; -sinix*) os=-sysv4 ;; -tpf*) os=-tpf ;; -triton*) os=-sysv3 ;; -oss*) os=-sysv3 ;; -svr4) os=-sysv4 ;; -svr3) os=-sysv3 ;; -sysvr4) os=-sysv4 ;; # This must come after -sysvr4. -sysv*) ;; -ose*) os=-ose ;; -es1800*) os=-ose ;; -xenix) os=-xenix ;; -*mint | -mint[0-9]* | -*MiNT | -MiNT[0-9]*) os=-mint ;; -aros*) os=-aros ;; -kaos*) os=-kaos ;; -zvmoe) os=-zvmoe ;; -dicos*) os=-dicos ;; -nacl*) ;; -none) ;; *) # Get rid of the `-' at the beginning of $os. os=`echo $os | sed 's/[^-]*-//'` echo Invalid configuration \`$1\': system \`$os\' not recognized 1>&2 exit 1 ;; esac else # Here we handle the default operating systems that come with various machines. # The value should be what the vendor currently ships out the door with their # machine or put another way, the most popular os provided with the machine. # Note that if you're going to try to match "-MANUFACTURER" here (say, # "-sun"), then you have to tell the case statement up towards the top # that MANUFACTURER isn't an operating system. Otherwise, code above # will signal an error saying that MANUFACTURER isn't an operating # system, and we'll never get to this point. case $basic_machine in score-*) os=-elf ;; spu-*) os=-elf ;; *-acorn) os=-riscix1.2 ;; arm*-rebel) os=-linux ;; arm*-semi) os=-aout ;; c4x-* | tic4x-*) os=-coff ;; hexagon-*) os=-elf ;; tic54x-*) os=-coff ;; tic55x-*) os=-coff ;; tic6x-*) os=-coff ;; # This must come before the *-dec entry. pdp10-*) os=-tops20 ;; pdp11-*) os=-none ;; *-dec | vax-*) os=-ultrix4.2 ;; m68*-apollo) os=-domain ;; i386-sun) os=-sunos4.0.2 ;; m68000-sun) os=-sunos3 ;; m68*-cisco) os=-aout ;; mep-*) os=-elf ;; mips*-cisco) os=-elf ;; mips*-*) os=-elf ;; or32-*) os=-coff ;; *-tti) # must be before sparc entry or we get the wrong os. os=-sysv3 ;; sparc-* | *-sun) os=-sunos4.1.1 ;; *-be) os=-beos ;; *-haiku) os=-haiku ;; *-ibm) os=-aix ;; *-knuth) os=-mmixware ;; *-wec) os=-proelf ;; *-winbond) os=-proelf ;; *-oki) os=-proelf ;; *-hp) os=-hpux ;; *-hitachi) os=-hiux ;; i860-* | *-att | *-ncr | *-altos | *-motorola | *-convergent) os=-sysv ;; *-cbm) os=-amigaos ;; *-dg) os=-dgux ;; *-dolphin) os=-sysv3 ;; m68k-ccur) os=-rtu ;; m88k-omron*) os=-luna ;; *-next ) os=-nextstep ;; *-sequent) os=-ptx ;; *-crds) os=-unos ;; *-ns) os=-genix ;; i370-*) os=-mvs ;; *-next) os=-nextstep3 ;; *-gould) os=-sysv ;; *-highlevel) os=-bsd ;; *-encore) os=-bsd ;; *-sgi) os=-irix ;; *-siemens) os=-sysv4 ;; *-masscomp) os=-rtu ;; f30[01]-fujitsu | f700-fujitsu) os=-uxpv ;; *-rom68k) os=-coff ;; *-*bug) os=-coff ;; *-apple) os=-macos ;; *-atari*) os=-mint ;; *) os=-none ;; esac fi # Here we handle the case where we know the os, and the CPU type, but not the # manufacturer. We pick the logical manufacturer. vendor=unknown case $basic_machine in *-unknown) case $os in -riscix*) vendor=acorn ;; -sunos*) vendor=sun ;; -cnk*|-aix*) vendor=ibm ;; -beos*) vendor=be ;; -hpux*) vendor=hp ;; -mpeix*) vendor=hp ;; -hiux*) vendor=hitachi ;; -unos*) vendor=crds ;; -dgux*) vendor=dg ;; -luna*) vendor=omron ;; -genix*) vendor=ns ;; -mvs* | -opened*) vendor=ibm ;; -os400*) vendor=ibm ;; -ptx*) vendor=sequent ;; -tpf*) vendor=ibm ;; -vxsim* | -vxworks* | -windiss*) vendor=wrs ;; -aux*) vendor=apple ;; -hms*) vendor=hitachi ;; -mpw* | -macos*) vendor=apple ;; -*mint | -mint[0-9]* | -*MiNT | -MiNT[0-9]*) vendor=atari ;; -vos*) vendor=stratus ;; esac basic_machine=`echo $basic_machine | sed "s/unknown/$vendor/"` ;; esac echo $basic_machine$os exit # Local variables: # eval: (add-hook 'write-file-hooks 'time-stamp) # time-stamp-start: "timestamp='" # time-stamp-format: "%:y-%02m-%02d" # time-stamp-end: "'" # End: smalltalk-3.2.5/build-aux/lock.m40000644000175000017500000001332412123404352013511 00000000000000# lock.m4 serial 8 (gettext-0.18) dnl Copyright (C) 2005-2009 Free Software Foundation, Inc. dnl This file is free software; the Free Software Foundation dnl gives unlimited permission to copy and/or distribute it, dnl with or without modifications, as long as this notice is preserved. dnl From Bruno Haible. dnl GST_LOCK dnl ------- dnl Tests for a multithreading library to be used. dnl Defines at most one of the macros USE_POSIX_THREADS or USE_WIN32_THREADS. dnl Sets the variables LIBTHREAD to the linker options for use in a Makefile. dnl Adds to CPPFLAGS the flag -D_REENTRANT or -D_THREAD_SAFE if needed for dnl multithread-safe programs. AC_DEFUN([GST_LOCK], [ AC_REQUIRE([AC_CANONICAL_HOST]) AC_REQUIRE([AC_USE_SYSTEM_EXTENSIONS]) # Prerequisites of lib-src/lock.c. AC_REQUIRE([AC_C_INLINE]) gst_threads_api=none LIBTHREAD= dnl Check for multithreading. # Some systems optimize for single-threaded programs by default, and # need special flags to disable these optimizations. For example, the # definition of 'errno' in . # On OSF/1, the compiler needs the flag -D_REENTRANT so that it # groks . cc also understands the flag -pthread, but # we don't use it because 1. gcc-2.95 doesn't understand -pthread, # 2. putting a flag into CPPFLAGS that has an effect on the linker # causes the AC_TRY_LINK test below to succeed unexpectedly, # leading to wrong values of LIBTHREAD. # On Solaris and HP-UX, most pthread functions exist also in libc. # However, pthread_create from libc will fail. case "$host_os" in osf*) CPPFLAGS="$CPPFLAGS -D_REENTRANT" ;; aix*) CPPFLAGS="$CPPFLAGS -D_THREAD_SAFE" ;; freebsd*) CPPFLAGS="$CPPFLAGS -D_THREAD_SAFE" LIBTHREAD=-pthread ;; solaris*) CPPFLAGS="$CPPFLAGS -D_REENTRANT" LIBTHREAD=-lpthread ;; hpux*) LIBTHREAD=-lpthread ;; esac AC_CHECK_HEADER(pthread.h, gst_have_pthread_h=yes, gst_have_pthread_h=no) if { case "$host_os" in mingw*) true;; *) false;; esac }; then gst_threads_api=win32 AC_DEFINE([USE_WIN32_THREADS], 1, [Define if the Win32 multithreading API can be used.]) elif test "$gst_have_pthread_h" = yes; then # Test whether both pthread_mutex_lock and pthread_mutexattr_init exist # in libc. IRIX 6.5 has the first one in both libc and libpthread, but # the second one only in libpthread. FreeBSD has libc_r. gst_save_CFLAGS=$CFLAGS gst_save_LIBS=$LIBS CFLAGS="$CFLAGS $LIBTHREAD" gst_have_pthread=yes AC_SEARCH_LIBS([pthread_mutexattr_init], [pthread pthreads c_r], , [gst_have_pthread=no]) AC_SEARCH_LIBS([pthread_mutex_lock], [pthread pthreads c_r], , [gst_have_pthread=no]) CFLAGS=$gst_save_CFLAGS LIBS=$gst_save_LIBS if test "$gst_have_pthread" = yes; then if test "$ac_cv_search_pthread_mutex_lock" != "none required"; then LIBTHREAD="$LIBTHREAD $ac_cv_search_pthread_mutex_lock" fi gst_threads_api=posix AC_DEFINE([USE_POSIX_THREADS], 1, [Define if the POSIX multithreading library can be used.]) # OSF/1 4.0 and MacOS X 10.1 lack the pthread_rwlock_t type and the # pthread_rwlock_* functions. AC_CHECK_TYPE([pthread_rwlock_t], [AC_DEFINE([HAVE_PTHREAD_RWLOCK], 1, [Define if the POSIX multithreading library has read/write locks.])], [], [#include ]) # glibc defines PTHREAD_MUTEX_RECURSIVE as enum, not as a macro. AC_TRY_COMPILE([#include ], [#if __FreeBSD__ == 4 error "No, in FreeBSD 4.0 recursive mutexes actually don't work." #else int x = (int)PTHREAD_MUTEX_RECURSIVE; return !x; #endif], [AC_DEFINE([HAVE_PTHREAD_MUTEX_RECURSIVE], 1, [Define if the defines PTHREAD_MUTEX_RECURSIVE.])]) fi fi AC_MSG_CHECKING([for multithread API to use]) AC_MSG_RESULT([$gst_threads_api]) AC_SUBST(LIBTHREAD) ]) dnl Survey of platforms: dnl dnl Platform Available Compiler Supports test-lock dnl flavours option weak result dnl --------------- --------- --------- -------- --------- dnl Linux 2.4/glibc posix -lpthread Y OK dnl dnl GNU Hurd/glibc posix dnl dnl FreeBSD 5.3 posix -lc_r Y dnl posix -lkse ? Y dnl posix -lpthread ? Y dnl posix -lthr Y dnl dnl FreeBSD 5.2 posix -lc_r Y dnl posix -lkse Y dnl posix -lthr Y dnl dnl FreeBSD 4.0,4.10 posix -lc_r Y OK dnl dnl NetBSD 1.6 -- dnl dnl OpenBSD 3.4 posix -lpthread Y OK dnl dnl MacOS X 10.[123] posix -lpthread Y OK dnl dnl Solaris 7,8,9 posix -lpthread Y Sol 7,8: 0.0; Sol 9: OK dnl solaris -lthread Y Sol 7,8: 0.0; Sol 9: OK dnl dnl HP-UX 11 posix -lpthread N (cc) OK dnl Y (gcc) dnl dnl IRIX 6.5 posix -lpthread Y 0.5 dnl dnl AIX 4.3,5.1 posix -lpthread N AIX 4: 0.5; AIX 5: OK dnl dnl OSF/1 4.0,5.1 posix -pthread (cc) N OK dnl -lpthread (gcc) Y dnl dnl Cygwin posix -lpthread Y OK dnl dnl Mingw win32 N OK dnl dnl BeOS 5 -- dnl dnl The test-lock result shows what happens if in test-lock.c EXPLICIT_YIELD is dnl turned off: dnl OK if all three tests terminate OK, dnl 0.5 if the first test terminates OK but the second one loops endlessly, dnl 0.0 if the first test already loops endlessly. smalltalk-3.2.5/build-aux/lrint.m40000644000175000017500000000142512123404352013710 00000000000000dnl I'd like this to be edited in -*- Autoconf -*- mode... dnl AC_DEFUN([GST_FUNC_LRINT], [ # Check for lrint. Under ia64-linux, lrint returns # incorrect values for bit 31. AC_CACHE_CHECK(for working lrint, gst_cv_working_lrint, [ exec AS_MESSAGE_FD([])>/dev/null AC_CHECK_FUNC(lrint, gst_cv_working_lrint=yes, gst_cv_working_lrint=no) if test $gst_cv_working_lrint = yes; then AC_RUN_IFELSE([AC_LANG_SOURCE([[ double d = 14988885582133630.0; int main() { extern long int lrint (double); long int l = lrint (d); exit(sizeof (l) >= 8 && l != 14988885582133630); }]])],[],[gst_cv_working_lrint=no],[gst_cv_working_lrint=no]) fi test "$silent" != yes && exec AS_MESSAGE_FD([])>&1 ]) test "$gst_cv_working_lrint" != yes && AC_LIBOBJ(lrint) ])dnl smalltalk-3.2.5/build-aux/ln.m40000644000175000017500000000116112123404352013166 00000000000000AC_DEFUN([GST_PROG_LN], [AC_MSG_CHECKING([whether ln works]) rm -f conf$$ conf$$.exe conf$$.file echo >conf$$.file if ln conf$$.file conf$$ 2>/dev/null; then # We could just check for DJGPP; but this test works, is more generic # and will remain valid once DJGPP supports symlinks (DJGPP 2.04). if test -f conf$$.exe; then # Don't use ln at all; we don't have any links LN='cp -p' else LN='ln' fi else LN=m4_if([$1], [], [$as_ln_s], [$1]) fi rm -f conf$$ conf$$.exe conf$$.file AC_SUBST([LN])dnl if test "$LN" = ln; then AC_MSG_RESULT([yes]) else AC_MSG_RESULT([no, using $LN]) fi ])# GST_PROG_LN smalltalk-3.2.5/build-aux/emacs-pkg.m40000644000175000017500000000067712123404352014437 00000000000000AC_DEFUN([GST_EMACS_PACKAGE], [ AC_CACHE_CHECK([for $1.el], [ac_cv_emacs_[]AS_TR_SH([$1])], [ ac_cv_emacs_[]AS_TR_SH([$1])=no if test $EMACS != no; then echo "AS_ESCAPE([(require '$1)])" > conftest $EMACS -batch -q -no-site-file -l conftest 2>&1 | \ grep 'Cannot open load file' > /dev/null 2>&1 || \ ac_cv_emacs_[]AS_TR_SH([$1])=yes rm conftest fi ]) AS_IF([test $ac_cv_emacs_[]AS_TR_SH([$1]) = yes], [$2], [$3]) ]) smalltalk-3.2.5/build-aux/long-double.m40000644000175000017500000000452012123404352014766 00000000000000dnl I'd like this to be edited in -*- Autoconf -*- mode... dnl AC_DEFUN([GST_C_LONG_DOUBLE], [AC_CACHE_CHECK([whether -Wno-long-double is needed], gst_cv_c_wno_long_double, [gst_cv_c_wno_long_double=no save_CFLAGS="$CFLAGS" CFLAGS="$CFLAGS -Werror" AC_COMPILE_IFELSE([AC_LANG_SOURCE([long double a;])], [gst_cv_c_wno_long_double=no; break], [CFLAGS="$CFLAGS -Wno-long-double" AC_COMPILE_IFELSE([AC_LANG_SOURCE([long double a;])], [gst_cv_c_wno_long_double=yes; break], [AC_MSG_ERROR([compiler does not have long double])])]) CFLAGS="$save_CFLAGS" ]) if test $gst_cv_c_wno_long_double = yes; then CFLAGS="$CFLAGS -Wno-long-double" fi AC_CACHE_CHECK([the number of mantissa digits in long doubles], gst_cv_ldbl_mant_dig, [AC_COMPUTE_INT([gst_cv_ldbl_mant_dig], [LDBL_MANT_DIG], [AC_INCLUDES_DEFAULT @%:@include ], [gst_cv_ldbl_mant_dig=unknown]) ]) AC_CACHE_CHECK([whether this long double format is supported], gst_cv_long_double_ok, [if test $gst_cv_ldbl_mant_dig = 106; then save_CFLAGS="$CFLAGS" CFLAGS="$CFLAGS -mlong-double-64" AC_COMPILE_IFELSE([AC_LANG_PROGRAM], [gst_cv_long_double_ok='no, disabling'], [gst_cv_long_double_ok=no]) CFLAGS="$save_CFLAGS" else gst_cv_long_double_ok=yes fi]) if test "$gst_cv_long_double_ok" != yes; then case $host in powerpc*-*-darwin*) # Darwin provides both 64-bit and 128-bit long double functions in # its libc ;; *) # A glibc installations for a compiler that defaults to -mlong-double-128 # won't work for -mlong-double-64. We may instead want to use a switch # to use doubles directly instead of -mlong-double-64. ac_cv_func_floorl=no ac_cv_func_ceill=no ac_cv_func_sqrtl=no ac_cv_func_frexpl=no ac_cv_func_ldexpl=no ac_cv_func_asinl=no ac_cv_func_acosl=no ac_cv_func_atanl=no ac_cv_func_logl=no ac_cv_func_expl=no ac_cv_func_tanl=no ac_cv_func_sinl=no ac_cv_func_cosl=no ac_cv_func_powl=no ac_cv_func_truncl=no ac_cv_func_lrintl=no ;; esac case $gst_cv_long_double_ok in "no, disabling") CFLAGS="$CFLAGS -mlong-double-64" ;; no) AC_MSG_WARN([cannot disable IBM extended long doubles, floating-point tests may fail]) ;; esac fi ])# GST_C_LONG_DOUBLE smalltalk-3.2.5/build-aux/poll.m40000644000175000017500000000374612123404352013536 00000000000000# sigaltstack.m4 serial 3 (libsigsegv-2.2) dnl Copyright (C) 2002-2003 Bruno Haible dnl This file is free software, distributed under the terms of the GNU dnl General Public License. As a special exception to the GNU General dnl Public License, this file may be distributed as part of a program dnl that contains a configuration script generated by Autoconf, under dnl the same distribution terms as the rest of that program. AC_DEFUN([GST_REPLACE_POLL], [ AC_CACHE_CHECK(for working poll, gst_cv_func_poll, [ exec AS_MESSAGE_FD([])>/dev/null AC_CHECK_FUNC(poll, [ # Check whether poll() works on special files (like /dev/null) and # and ttys (like /dev/tty). On MacOS X 10.4.0, it doesn't. AC_TRY_RUN([ #include #include int main() { struct pollfd ufd; /* Try /dev/null for reading. */ ufd.fd = open ("/dev/null", O_RDONLY); if (ufd.fd < 0) /* If /dev/null does not exist, it's not MacOS X. */ return 0; ufd.events = POLLIN; ufd.revents = 0; if (!(poll (&ufd, 1, 0) == 1 && ufd.revents == POLLIN)) return 1; /* Try /dev/null for writing. */ ufd.fd = open ("/dev/null", O_WRONLY); if (ufd.fd < 0) /* If /dev/null does not exist, it's not MacOS X. */ return 0; ufd.events = POLLOUT; ufd.revents = 0; if (!(poll (&ufd, 1, 0) == 1 && ufd.revents == POLLOUT)) return 1; /* Trying /dev/tty may be too environment dependent. */ return 0; }], [gst_cv_func_poll=yes], [gst_cv_func_poll=no], [ # When cross-compiling, assume that poll() works everywhere except on # MacOS X, regardless of its version. AC_EGREP_CPP([MacOSX], [ #if defined(__APPLE__) && defined(__MACH__) This is MacOSX #endif ], [gst_cv_func_poll='possibly not'], [gst_cv_func_poll=yes])]) ], [gst_cv_func_poll=no]) test "$silent" != yes && exec AS_MESSAGE_FD([])>&1 ]) if test $gst_cv_func_poll != yes; then AC_LIBOBJ(poll) AC_DEFINE(poll, rpl_poll, [Define to rpl_poll if the replacement function should be used.]) fi ]) smalltalk-3.2.5/build-aux/lib-link.m40000644000175000017500000005567712123404352014303 00000000000000# lib-link.m4 serial 3 (gettext-0.11.3) dnl Copyright (C) 2001-2002 Free Software Foundation, Inc. dnl This file is free software, distributed under the terms of the GNU dnl General Public License. As a special exception to the GNU General dnl Public License, this file may be distributed as part of a program dnl that contains a configuration script generated by Autoconf, under dnl the same distribution terms as the rest of that program. dnl From Bruno Haible. dnl AC_LIB_LINKFLAGS(name [, dependencies]) searches for libname and dnl the libraries corresponding to explicit and implicit dependencies. dnl Sets and AC_SUBSTs the LIB${NAME} and LTLIB${NAME} variables and dnl augments the CPPFLAGS variable. AC_DEFUN([AC_LIB_LINKFLAGS], [ AC_REQUIRE([AC_LIB_PREPARE_PREFIX]) AC_REQUIRE([AC_LIB_RPATH]) define([Name],[translit([$1],[./-], [___])]) define([NAME],[translit([$1],[abcdefghijklmnopqrstuvwxyz./-], [ABCDEFGHIJKLMNOPQRSTUVWXYZ___])]) AC_CACHE_CHECK([how to link with lib[]$1], [ac_cv_lib[]Name[]_libs], [ AC_LIB_LINKFLAGS_BODY([$1], [$2]) ac_cv_lib[]Name[]_libs="$LIB[]NAME" ac_cv_lib[]Name[]_ltlibs="$LTLIB[]NAME" ac_cv_lib[]Name[]_cppflags="$INC[]NAME" ]) LIB[]NAME="$ac_cv_lib[]Name[]_libs" LTLIB[]NAME="$ac_cv_lib[]Name[]_ltlibs" INC[]NAME="$ac_cv_lib[]Name[]_cppflags" AC_LIB_APPENDTOVAR([CPPFLAGS], [$INC]NAME) AC_SUBST([LIB]NAME) AC_SUBST([LTLIB]NAME) dnl Also set HAVE_LIB[]NAME so that AC_LIB_HAVE_LINKFLAGS can reuse the dnl results of this search when this library appears as a dependency. HAVE_LIB[]NAME=yes undefine([Name]) undefine([NAME]) ]) dnl AC_LIB_HAVE_LINKFLAGS(name, dependencies, includes, testcode) dnl searches for libname and the libraries corresponding to explicit and dnl implicit dependencies, together with the specified include files and dnl the ability to compile and link the specified testcode. If found, it dnl sets and AC_SUBSTs HAVE_LIB${NAME}=yes and the LIB${NAME} and dnl LTLIB${NAME} variables and augments the CPPFLAGS variable, and dnl #defines HAVE_LIB${NAME} to 1. Otherwise, it sets and AC_SUBSTs dnl HAVE_LIB${NAME}=no and LIB${NAME} and LTLIB${NAME} to empty. AC_DEFUN([AC_LIB_HAVE_LINKFLAGS], [ AC_REQUIRE([AC_LIB_PREPARE_PREFIX]) AC_REQUIRE([AC_LIB_RPATH]) define([Name],[translit([$1],[./-], [___])]) define([NAME],[translit([$1],[abcdefghijklmnopqrstuvwxyz./-], [ABCDEFGHIJKLMNOPQRSTUVWXYZ___])]) dnl Search for lib[]Name and define LIB[]NAME, LTLIB[]NAME and INC[]NAME dnl accordingly. AC_LIB_LINKFLAGS_BODY([$1], [$2]) dnl Add $INC[]NAME to CPPFLAGS before performing the following checks, dnl because if the user has installed lib[]Name and not disabled its use dnl via --without-lib[]Name-prefix, he wants to use it. ac_save_CPPFLAGS="$CPPFLAGS" AC_LIB_APPENDTOVAR([CPPFLAGS], [$INC]NAME) AC_CACHE_CHECK([for lib[]$1], [ac_cv_lib[]Name], [ ac_save_LIBS="$LIBS" LIBS="$LIBS $LIB[]NAME" AC_LINK_IFELSE([AC_LANG_PROGRAM([[$3]], [[$4]])], [ac_cv_lib[]Name=yes], [ac_cv_lib[]Name=no]) LIBS="$ac_save_LIBS" ]) if test "$ac_cv_lib[]Name" = yes; then HAVE_LIB[]NAME=yes AC_DEFINE([HAVE_LIB]NAME, 1, [Define if you have the $1 library.]) AC_MSG_CHECKING([how to link with lib[]$1]) AC_MSG_RESULT([$LIB[]NAME]) else HAVE_LIB[]NAME=no dnl If $LIB[]NAME didn't lead to a usable library, we don't need dnl $INC[]NAME either. CPPFLAGS="$ac_save_CPPFLAGS" LIB[]NAME= LTLIB[]NAME= fi AC_SUBST([HAVE_LIB]NAME) AC_SUBST([LIB]NAME) AC_SUBST([LTLIB]NAME) undefine([Name]) undefine([NAME]) ]) dnl Determine the platform dependent parameters needed to use rpath: dnl libext, shlibext, hardcode_libdir_flag_spec, hardcode_libdir_separator, dnl hardcode_direct, hardcode_minus_L, dnl sys_lib_search_path_spec, sys_lib_dlsearch_path_spec. AC_DEFUN([AC_LIB_RPATH], [ AC_REQUIRE([AC_PROG_CC]) dnl we use $CC, $GCC, $LDFLAGS AC_REQUIRE([AC_LIB_PROG_LD]) dnl we use $LD, $with_gnu_ld AC_REQUIRE([AC_CANONICAL_HOST]) dnl we use $host AC_REQUIRE([AC_CONFIG_AUX_DIR_DEFAULT]) dnl we use $ac_aux_dir AC_CACHE_CHECK([for shared library run path origin], acl_cv_rpath, [ CC="$CC" GCC="$GCC" LDFLAGS="$LDFLAGS" LD="$LD" with_gnu_ld="$with_gnu_ld" \ ${CONFIG_SHELL-/bin/sh} "$ac_aux_dir/config.rpath" "$host" > conftest.sh . ./conftest.sh rm -f ./conftest.sh acl_cv_rpath=done ]) wl="$acl_cv_wl" libext="$acl_cv_libext" shlibext="$acl_cv_shlibext" hardcode_libdir_flag_spec="$acl_cv_hardcode_libdir_flag_spec" hardcode_libdir_separator="$acl_cv_hardcode_libdir_separator" hardcode_direct="$acl_cv_hardcode_direct" hardcode_minus_L="$acl_cv_hardcode_minus_L" sys_lib_search_path_spec="$acl_cv_sys_lib_search_path_spec" sys_lib_dlsearch_path_spec="$acl_cv_sys_lib_dlsearch_path_spec" dnl Determine whether the user wants rpath handling at all. AC_ARG_ENABLE(rpath, [ --disable-rpath do not hardcode runtime library paths], :, enable_rpath=yes) ]) dnl AC_LIB_LINKFLAGS_BODY(name [, dependencies]) searches for libname and dnl the libraries corresponding to explicit and implicit dependencies. dnl Sets the LIB${NAME}, LTLIB${NAME} and INC${NAME} variables. AC_DEFUN([AC_LIB_LINKFLAGS_BODY], [ define([NAME],[translit([$1],[abcdefghijklmnopqrstuvwxyz./-], [ABCDEFGHIJKLMNOPQRSTUVWXYZ___])]) dnl By default, look in $includedir and $libdir. use_additional=yes AC_LIB_WITH_FINAL_PREFIX([ eval additional_includedir=\"$includedir\" eval additional_libdir=\"$libdir\" ]) AC_ARG_WITH([lib$1-prefix], [ --with-lib$1-prefix[=DIR] search for lib$1 in DIR/include and DIR/lib --without-lib$1-prefix don't search for lib$1 in includedir and libdir], [ if test "X$withval" = "Xno"; then use_additional=no else if test "X$withval" = "X"; then AC_LIB_WITH_FINAL_PREFIX([ eval additional_includedir=\"$includedir\" eval additional_libdir=\"$libdir\" ]) else additional_includedir="$withval/include" additional_libdir="$withval/lib" fi fi ]) dnl Search the library and its dependencies in $additional_libdir and dnl $LDFLAGS. Using breadth-first-seach. LIB[]NAME= LTLIB[]NAME= INC[]NAME= rpathdirs= ltrpathdirs= names_already_handled= names_next_round='$1 $2' while test -n "$names_next_round"; do names_this_round="$names_next_round" names_next_round= for name in $names_this_round; do already_handled= for n in $names_already_handled; do if test "$n" = "$name"; then already_handled=yes break fi done if test -z "$already_handled"; then names_already_handled="$names_already_handled $name" dnl See if it was already located by an earlier AC_LIB_LINKFLAGS dnl or AC_LIB_HAVE_LINKFLAGS call. uppername=`echo "$name" | sed -e 'y|abcdefghijklmnopqrstuvwxyz./-|ABCDEFGHIJKLMNOPQRSTUVWXYZ___|'` eval value=\"\$HAVE_LIB$uppername\" if test -n "$value"; then if test "$value" = yes; then eval value=\"\$LIB$uppername\" test -z "$value" || LIB[]NAME="${LIB[]NAME}${LIB[]NAME:+ }$value" eval value=\"\$LTLIB$uppername\" test -z "$value" || LTLIB[]NAME="${LTLIB[]NAME}${LTLIB[]NAME:+ }$value" else dnl An earlier call to AC_LIB_HAVE_LINKFLAGS has determined dnl that this library doesn't exist. So just drop it. : fi else dnl Search the library lib$name in $additional_libdir and $LDFLAGS dnl and the already constructed $LIBNAME/$LTLIBNAME. found_dir= found_la= found_so= found_a= if test $use_additional = yes; then if test -n "$shlibext" && test -f "$additional_libdir/lib$name.$shlibext"; then found_dir="$additional_libdir" found_so="$additional_libdir/lib$name.$shlibext" if test -f "$additional_libdir/lib$name.la"; then found_la="$additional_libdir/lib$name.la" fi else if test -f "$additional_libdir/lib$name.$libext"; then found_dir="$additional_libdir" found_a="$additional_libdir/lib$name.$libext" if test -f "$additional_libdir/lib$name.la"; then found_la="$additional_libdir/lib$name.la" fi fi fi fi if test "X$found_dir" = "X"; then for x in $LDFLAGS $LTLIB[]NAME; do AC_LIB_WITH_FINAL_PREFIX([eval x=\"$x\"]) case "$x" in -L*) dir=`echo "X$x" | sed -e 's/^X-L//'` if test -n "$shlibext" && test -f "$dir/lib$name.$shlibext"; then found_dir="$dir" found_so="$dir/lib$name.$shlibext" if test -f "$dir/lib$name.la"; then found_la="$dir/lib$name.la" fi else if test -f "$dir/lib$name.$libext"; then found_dir="$dir" found_a="$dir/lib$name.$libext" if test -f "$dir/lib$name.la"; then found_la="$dir/lib$name.la" fi fi fi ;; esac if test "X$found_dir" != "X"; then break fi done fi if test "X$found_dir" != "X"; then dnl Found the library. LTLIB[]NAME="${LTLIB[]NAME}${LTLIB[]NAME:+ }-L$found_dir -l$name" if test "X$found_so" != "X"; then dnl Linking with a shared library. We attempt to hardcode its dnl directory into the executable's runpath, unless it's the dnl standard /usr/lib. if test "$enable_rpath" = no || test "X$found_dir" = "X/usr/lib"; then dnl No hardcoding is needed. LIB[]NAME="${LIB[]NAME}${LIB[]NAME:+ }$found_so" else dnl Use an explicit option to hardcode DIR into the resulting dnl binary. dnl Potentially add DIR to ltrpathdirs. dnl The ltrpathdirs will be appended to $LTLIBNAME at the end. haveit= for x in $ltrpathdirs; do if test "X$x" = "X$found_dir"; then haveit=yes break fi done if test -z "$haveit"; then ltrpathdirs="$ltrpathdirs $found_dir" fi dnl The hardcoding into $LIBNAME is system dependent. if test "$hardcode_direct" = yes; then dnl Using DIR/libNAME.so during linking hardcodes DIR into the dnl resulting binary. LIB[]NAME="${LIB[]NAME}${LIB[]NAME:+ }$found_so" else if test -n "$hardcode_libdir_flag_spec" && test "$hardcode_minus_L" = no; then dnl Use an explicit option to hardcode DIR into the resulting dnl binary. LIB[]NAME="${LIB[]NAME}${LIB[]NAME:+ }$found_so" dnl Potentially add DIR to rpathdirs. dnl The rpathdirs will be appended to $LIBNAME at the end. haveit= for x in $rpathdirs; do if test "X$x" = "X$found_dir"; then haveit=yes break fi done if test -z "$haveit"; then rpathdirs="$rpathdirs $found_dir" fi else dnl Rely on "-L$found_dir". dnl But don't add it if it's already contained in the LDFLAGS dnl or the already constructed $LIBNAME haveit= for x in $LDFLAGS $LIB[]NAME; do AC_LIB_WITH_FINAL_PREFIX([eval x=\"$x\"]) if test "X$x" = "X-L$found_dir"; then haveit=yes break fi done if test -z "$haveit"; then LIB[]NAME="${LIB[]NAME}${LIB[]NAME:+ }-L$found_dir" fi if test "$hardcode_minus_L" != no; then dnl FIXME: Not sure whether we should use dnl "-L$found_dir -l$name" or "-L$found_dir $found_so" dnl here. LIB[]NAME="${LIB[]NAME}${LIB[]NAME:+ }$found_so" else dnl We cannot use $hardcode_runpath_var and LD_RUN_PATH dnl here, because this doesn't fit in flags passed to the dnl compiler. So give up. No hardcoding. This affects only dnl very old systems. dnl FIXME: Not sure whether we should use dnl "-L$found_dir -l$name" or "-L$found_dir $found_so" dnl here. LIB[]NAME="${LIB[]NAME}${LIB[]NAME:+ }-l$name" fi fi fi fi else if test "X$found_a" != "X"; then dnl Linking with a static library. LIB[]NAME="${LIB[]NAME}${LIB[]NAME:+ }$found_a" else dnl We shouldn't come here, but anyway it's good to have a dnl fallback. LIB[]NAME="${LIB[]NAME}${LIB[]NAME:+ }-L$found_dir -l$name" fi fi dnl Assume the include files are nearby. additional_includedir= case "$found_dir" in */lib | */lib/) basedir=`echo "X$found_dir" | sed -e 's,^X,,' -e 's,/lib/*$,,'` additional_includedir="$basedir/include" ;; esac if test "X$additional_includedir" != "X"; then dnl Potentially add $additional_includedir to $INCNAME. dnl But don't add it dnl 1. if it's the standard /usr/include, dnl 2. if it's /usr/local/include and we are using GCC on Linux, dnl 3. if it's already present in $CPPFLAGS or the already dnl constructed $INCNAME, dnl 4. if it doesn't exist as a directory. if test "X$additional_includedir" != "X/usr/include"; then haveit= if test "X$additional_includedir" = "X/usr/local/include"; then if test -n "$GCC"; then case $host_os in linux*) haveit=yes;; esac fi fi if test -z "$haveit"; then for x in $CPPFLAGS $INC[]NAME; do AC_LIB_WITH_FINAL_PREFIX([eval x=\"$x\"]) if test "X$x" = "X-I$additional_includedir"; then haveit=yes break fi done if test -z "$haveit"; then if test -d "$additional_includedir"; then dnl Really add $additional_includedir to $INCNAME. INC[]NAME="${INC[]NAME}${INC[]NAME:+ }-I$additional_includedir" fi fi fi fi fi dnl Look for dependencies. if test -n "$found_la"; then dnl Read the .la file. It defines the variables dnl dlname, library_names, old_library, dependency_libs, current, dnl age, revision, installed, dlopen, dlpreopen, libdir. save_libdir="$libdir" case "$found_la" in */* | *\\*) . "$found_la" ;; *) . "./$found_la" ;; esac libdir="$save_libdir" dnl We use only dependency_libs. for dep in $dependency_libs; do case "$dep" in -L*) additional_libdir=`echo "X$dep" | sed -e 's/^X-L//'` dnl Potentially add $additional_libdir to $LIBNAME and $LTLIBNAME. dnl But don't add it dnl 1. if it's the standard /usr/lib, dnl 2. if it's /usr/local/lib and we are using GCC on Linux, dnl 3. if it's already present in $LDFLAGS or the already dnl constructed $LIBNAME, dnl 4. if it doesn't exist as a directory. if test "X$additional_libdir" != "X/usr/lib"; then haveit= if test "X$additional_libdir" = "X/usr/local/lib"; then if test -n "$GCC"; then case $host_os in linux*) haveit=yes;; esac fi fi if test -z "$haveit"; then haveit= for x in $LDFLAGS $LIB[]NAME; do AC_LIB_WITH_FINAL_PREFIX([eval x=\"$x\"]) if test "X$x" = "X-L$additional_libdir"; then haveit=yes break fi done if test -z "$haveit"; then if test -d "$additional_libdir"; then dnl Really add $additional_libdir to $LIBNAME. LIB[]NAME="${LIB[]NAME}${LIB[]NAME:+ }-L$additional_libdir" fi fi haveit= for x in $LDFLAGS $LTLIB[]NAME; do AC_LIB_WITH_FINAL_PREFIX([eval x=\"$x\"]) if test "X$x" = "X-L$additional_libdir"; then haveit=yes break fi done if test -z "$haveit"; then if test -d "$additional_libdir"; then dnl Really add $additional_libdir to $LTLIBNAME. LTLIB[]NAME="${LTLIB[]NAME}${LTLIB[]NAME:+ }-L$additional_libdir" fi fi fi fi ;; -R*) dir=`echo "X$dep" | sed -e 's/^X-R//'` if test "$enable_rpath" != no; then dnl Potentially add DIR to rpathdirs. dnl The rpathdirs will be appended to $LIBNAME at the end. haveit= for x in $rpathdirs; do if test "X$x" = "X$dir"; then haveit=yes break fi done if test -z "$haveit"; then rpathdirs="$rpathdirs $dir" fi dnl Potentially add DIR to ltrpathdirs. dnl The ltrpathdirs will be appended to $LTLIBNAME at the end. haveit= for x in $ltrpathdirs; do if test "X$x" = "X$dir"; then haveit=yes break fi done if test -z "$haveit"; then ltrpathdirs="$ltrpathdirs $dir" fi fi ;; -l*) dnl Handle this in the next round. names_next_round="$names_next_round "`echo "X$dep" | sed -e 's/^X-l//'` ;; *.la) dnl Handle this in the next round. Throw away the .la's dnl directory; it is already contained in a preceding -L dnl option. names_next_round="$names_next_round "`echo "X$dep" | sed -e 's,^X.*/,,' -e 's,^lib,,' -e 's,\.la$,,'` ;; *) dnl Most likely an immediate library name. LIB[]NAME="${LIB[]NAME}${LIB[]NAME:+ }$dep" LTLIB[]NAME="${LTLIB[]NAME}${LTLIB[]NAME:+ }$dep" ;; esac done fi else dnl Didn't find the library; assume it is in the system directories dnl known to the linker and runtime loader. (All the system dnl directories known to the linker should also be known to the dnl runtime loader, otherwise the system is severely misconfigured.) LIB[]NAME="${LIB[]NAME}${LIB[]NAME:+ }-l$name" LTLIB[]NAME="${LTLIB[]NAME}${LTLIB[]NAME:+ }-l$name" fi fi fi done done if test "X$rpathdirs" != "X"; then if test -n "$hardcode_libdir_separator"; then dnl Weird platform: only the last -rpath option counts, the user must dnl pass all path elements in one option. We can arrange that for a dnl single library, but not when more than one $LIBNAMEs are used. alldirs= for found_dir in $rpathdirs; do alldirs="${alldirs}${alldirs:+$hardcode_libdir_separator}$found_dir" done dnl Note: hardcode_libdir_flag_spec uses $libdir and $wl. acl_save_libdir="$libdir" libdir="$alldirs" eval flag=\"$hardcode_libdir_flag_spec\" libdir="$acl_save_libdir" LIB[]NAME="${LIB[]NAME}${LIB[]NAME:+ }$flag" else dnl The -rpath options are cumulative. for found_dir in $rpathdirs; do acl_save_libdir="$libdir" libdir="$found_dir" eval flag=\"$hardcode_libdir_flag_spec\" libdir="$acl_save_libdir" LIB[]NAME="${LIB[]NAME}${LIB[]NAME:+ }$flag" done fi fi if test "X$ltrpathdirs" != "X"; then dnl When using libtool, the option that works for both libraries and dnl executables is -R. The -R options are cumulative. for found_dir in $ltrpathdirs; do LTLIB[]NAME="${LTLIB[]NAME}${LTLIB[]NAME:+ }-R$found_dir" done fi ]) dnl AC_LIB_APPENDTOVAR(VAR, CONTENTS) appends the elements of CONTENTS to VAR, dnl unless already present in VAR. dnl Works only for CPPFLAGS, not for LIB* variables because that sometimes dnl contains two or three consecutive elements that belong together. AC_DEFUN([AC_LIB_APPENDTOVAR], [ for element in [$2]; do haveit= for x in $[$1]; do AC_LIB_WITH_FINAL_PREFIX([eval x=\"$x\"]) if test "X$x" = "X$element"; then haveit=yes break fi done if test -z "$haveit"; then [$1]="${[$1]}${[$1]:+ }$element" fi done ]) smalltalk-3.2.5/build-aux/config.guess0000755000175000017500000012743212130455425014652 00000000000000#! /bin/sh # Attempt to guess a canonical system name. # Copyright (C) 1992, 1993, 1994, 1995, 1996, 1997, 1998, 1999, # 2000, 2001, 2002, 2003, 2004, 2005, 2006, 2007, 2008, 2009, 2010, # 2011, 2012 Free Software Foundation, Inc. timestamp='2012-02-10' # This file is free software; you can redistribute it and/or modify it # under the terms of the GNU General Public License as published by # the Free Software Foundation; either version 2 of the License, or # (at your option) any later version. # # This program is distributed in the hope that it will be useful, but # WITHOUT ANY WARRANTY; without even the implied warranty of # MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU # General Public License for more details. # # You should have received a copy of the GNU General Public License # along with this program; if not, see . # # As a special exception to the GNU General Public License, if you # distribute this file as part of a program that contains a # configuration script generated by Autoconf, you may include it under # the same distribution terms that you use for the rest of that program. # Originally written by Per Bothner. Please send patches (context # diff format) to and include a ChangeLog # entry. # # This script attempts to guess a canonical system name similar to # config.sub. If it succeeds, it prints the system name on stdout, and # exits with 0. Otherwise, it exits with 1. # # You can get the latest version of this script from: # http://git.savannah.gnu.org/gitweb/?p=config.git;a=blob_plain;f=config.guess;hb=HEAD me=`echo "$0" | sed -e 's,.*/,,'` usage="\ Usage: $0 [OPTION] Output the configuration name of the system \`$me' is run on. Operation modes: -h, --help print this help, then exit -t, --time-stamp print date of last modification, then exit -v, --version print version number, then exit Report bugs and patches to ." version="\ GNU config.guess ($timestamp) Originally written by Per Bothner. Copyright (C) 1992, 1993, 1994, 1995, 1996, 1997, 1998, 1999, 2000, 2001, 2002, 2003, 2004, 2005, 2006, 2007, 2008, 2009, 2010, 2011, 2012 Free Software Foundation, Inc. This is free software; see the source for copying conditions. There is NO warranty; not even for MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE." help=" Try \`$me --help' for more information." # Parse command line while test $# -gt 0 ; do case $1 in --time-stamp | --time* | -t ) echo "$timestamp" ; exit ;; --version | -v ) echo "$version" ; exit ;; --help | --h* | -h ) echo "$usage"; exit ;; -- ) # Stop option processing shift; break ;; - ) # Use stdin as input. break ;; -* ) echo "$me: invalid option $1$help" >&2 exit 1 ;; * ) break ;; esac done if test $# != 0; then echo "$me: too many arguments$help" >&2 exit 1 fi trap 'exit 1' 1 2 15 # CC_FOR_BUILD -- compiler used by this script. Note that the use of a # compiler to aid in system detection is discouraged as it requires # temporary files to be created and, as you can see below, it is a # headache to deal with in a portable fashion. # Historically, `CC_FOR_BUILD' used to be named `HOST_CC'. We still # use `HOST_CC' if defined, but it is deprecated. # Portable tmp directory creation inspired by the Autoconf team. set_cc_for_build=' trap "exitcode=\$?; (rm -f \$tmpfiles 2>/dev/null; rmdir \$tmp 2>/dev/null) && exit \$exitcode" 0 ; trap "rm -f \$tmpfiles 2>/dev/null; rmdir \$tmp 2>/dev/null; exit 1" 1 2 13 15 ; : ${TMPDIR=/tmp} ; { tmp=`(umask 077 && mktemp -d "$TMPDIR/cgXXXXXX") 2>/dev/null` && test -n "$tmp" && test -d "$tmp" ; } || { test -n "$RANDOM" && tmp=$TMPDIR/cg$$-$RANDOM && (umask 077 && mkdir $tmp) ; } || { tmp=$TMPDIR/cg-$$ && (umask 077 && mkdir $tmp) && echo "Warning: creating insecure temp directory" >&2 ; } || { echo "$me: cannot create a temporary directory in $TMPDIR" >&2 ; exit 1 ; } ; dummy=$tmp/dummy ; tmpfiles="$dummy.c $dummy.o $dummy.rel $dummy" ; case $CC_FOR_BUILD,$HOST_CC,$CC in ,,) echo "int x;" > $dummy.c ; for c in cc gcc c89 c99 ; do if ($c -c -o $dummy.o $dummy.c) >/dev/null 2>&1 ; then CC_FOR_BUILD="$c"; break ; fi ; done ; if test x"$CC_FOR_BUILD" = x ; then CC_FOR_BUILD=no_compiler_found ; fi ;; ,,*) CC_FOR_BUILD=$CC ;; ,*,*) CC_FOR_BUILD=$HOST_CC ;; esac ; set_cc_for_build= ;' # This is needed to find uname on a Pyramid OSx when run in the BSD universe. # (ghazi@noc.rutgers.edu 1994-08-24) if (test -f /.attbin/uname) >/dev/null 2>&1 ; then PATH=$PATH:/.attbin ; export PATH fi UNAME_MACHINE=`(uname -m) 2>/dev/null` || UNAME_MACHINE=unknown UNAME_RELEASE=`(uname -r) 2>/dev/null` || UNAME_RELEASE=unknown UNAME_SYSTEM=`(uname -s) 2>/dev/null` || UNAME_SYSTEM=unknown UNAME_VERSION=`(uname -v) 2>/dev/null` || UNAME_VERSION=unknown # Note: order is significant - the case branches are not exclusive. case "${UNAME_MACHINE}:${UNAME_SYSTEM}:${UNAME_RELEASE}:${UNAME_VERSION}" in *:NetBSD:*:*) # NetBSD (nbsd) targets should (where applicable) match one or # more of the tuples: *-*-netbsdelf*, *-*-netbsdaout*, # *-*-netbsdecoff* and *-*-netbsd*. For targets that recently # switched to ELF, *-*-netbsd* would select the old # object file format. This provides both forward # compatibility and a consistent mechanism for selecting the # object file format. # # Note: NetBSD doesn't particularly care about the vendor # portion of the name. We always set it to "unknown". sysctl="sysctl -n hw.machine_arch" UNAME_MACHINE_ARCH=`(/sbin/$sysctl 2>/dev/null || \ /usr/sbin/$sysctl 2>/dev/null || echo unknown)` case "${UNAME_MACHINE_ARCH}" in armeb) machine=armeb-unknown ;; arm*) machine=arm-unknown ;; sh3el) machine=shl-unknown ;; sh3eb) machine=sh-unknown ;; sh5el) machine=sh5le-unknown ;; *) machine=${UNAME_MACHINE_ARCH}-unknown ;; esac # The Operating System including object format, if it has switched # to ELF recently, or will in the future. case "${UNAME_MACHINE_ARCH}" in arm*|i386|m68k|ns32k|sh3*|sparc|vax) eval $set_cc_for_build if echo __ELF__ | $CC_FOR_BUILD -E - 2>/dev/null \ | grep -q __ELF__ then # Once all utilities can be ECOFF (netbsdecoff) or a.out (netbsdaout). # Return netbsd for either. FIX? os=netbsd else os=netbsdelf fi ;; *) os=netbsd ;; esac # The OS release # Debian GNU/NetBSD machines have a different userland, and # thus, need a distinct triplet. However, they do not need # kernel version information, so it can be replaced with a # suitable tag, in the style of linux-gnu. case "${UNAME_VERSION}" in Debian*) release='-gnu' ;; *) release=`echo ${UNAME_RELEASE}|sed -e 's/[-_].*/\./'` ;; esac # Since CPU_TYPE-MANUFACTURER-KERNEL-OPERATING_SYSTEM: # contains redundant information, the shorter form: # CPU_TYPE-MANUFACTURER-OPERATING_SYSTEM is used. echo "${machine}-${os}${release}" exit ;; *:OpenBSD:*:*) UNAME_MACHINE_ARCH=`arch | sed 's/OpenBSD.//'` echo ${UNAME_MACHINE_ARCH}-unknown-openbsd${UNAME_RELEASE} exit ;; *:ekkoBSD:*:*) echo ${UNAME_MACHINE}-unknown-ekkobsd${UNAME_RELEASE} exit ;; *:SolidBSD:*:*) echo ${UNAME_MACHINE}-unknown-solidbsd${UNAME_RELEASE} exit ;; macppc:MirBSD:*:*) echo powerpc-unknown-mirbsd${UNAME_RELEASE} exit ;; *:MirBSD:*:*) echo ${UNAME_MACHINE}-unknown-mirbsd${UNAME_RELEASE} exit ;; alpha:OSF1:*:*) case $UNAME_RELEASE in *4.0) UNAME_RELEASE=`/usr/sbin/sizer -v | awk '{print $3}'` ;; *5.*) UNAME_RELEASE=`/usr/sbin/sizer -v | awk '{print $4}'` ;; esac # According to Compaq, /usr/sbin/psrinfo has been available on # OSF/1 and Tru64 systems produced since 1995. I hope that # covers most systems running today. This code pipes the CPU # types through head -n 1, so we only detect the type of CPU 0. ALPHA_CPU_TYPE=`/usr/sbin/psrinfo -v | sed -n -e 's/^ The alpha \(.*\) processor.*$/\1/p' | head -n 1` case "$ALPHA_CPU_TYPE" in "EV4 (21064)") UNAME_MACHINE="alpha" ;; "EV4.5 (21064)") UNAME_MACHINE="alpha" ;; "LCA4 (21066/21068)") UNAME_MACHINE="alpha" ;; "EV5 (21164)") UNAME_MACHINE="alphaev5" ;; "EV5.6 (21164A)") UNAME_MACHINE="alphaev56" ;; "EV5.6 (21164PC)") UNAME_MACHINE="alphapca56" ;; "EV5.7 (21164PC)") UNAME_MACHINE="alphapca57" ;; "EV6 (21264)") UNAME_MACHINE="alphaev6" ;; "EV6.7 (21264A)") UNAME_MACHINE="alphaev67" ;; "EV6.8CB (21264C)") UNAME_MACHINE="alphaev68" ;; "EV6.8AL (21264B)") UNAME_MACHINE="alphaev68" ;; "EV6.8CX (21264D)") UNAME_MACHINE="alphaev68" ;; "EV6.9A (21264/EV69A)") UNAME_MACHINE="alphaev69" ;; "EV7 (21364)") UNAME_MACHINE="alphaev7" ;; "EV7.9 (21364A)") UNAME_MACHINE="alphaev79" ;; esac # A Pn.n version is a patched version. # A Vn.n version is a released version. # A Tn.n version is a released field test version. # A Xn.n version is an unreleased experimental baselevel. # 1.2 uses "1.2" for uname -r. echo ${UNAME_MACHINE}-dec-osf`echo ${UNAME_RELEASE} | sed -e 's/^[PVTX]//' | tr 'ABCDEFGHIJKLMNOPQRSTUVWXYZ' 'abcdefghijklmnopqrstuvwxyz'` # Reset EXIT trap before exiting to avoid spurious non-zero exit code. exitcode=$? trap '' 0 exit $exitcode ;; Alpha\ *:Windows_NT*:*) # How do we know it's Interix rather than the generic POSIX subsystem? # Should we change UNAME_MACHINE based on the output of uname instead # of the specific Alpha model? echo alpha-pc-interix exit ;; 21064:Windows_NT:50:3) echo alpha-dec-winnt3.5 exit ;; Amiga*:UNIX_System_V:4.0:*) echo m68k-unknown-sysv4 exit ;; *:[Aa]miga[Oo][Ss]:*:*) echo ${UNAME_MACHINE}-unknown-amigaos exit ;; *:[Mm]orph[Oo][Ss]:*:*) echo ${UNAME_MACHINE}-unknown-morphos exit ;; *:OS/390:*:*) echo i370-ibm-openedition exit ;; *:z/VM:*:*) echo s390-ibm-zvmoe exit ;; *:OS400:*:*) echo powerpc-ibm-os400 exit ;; arm:RISC*:1.[012]*:*|arm:riscix:1.[012]*:*) echo arm-acorn-riscix${UNAME_RELEASE} exit ;; arm:riscos:*:*|arm:RISCOS:*:*) echo arm-unknown-riscos exit ;; SR2?01:HI-UX/MPP:*:* | SR8000:HI-UX/MPP:*:*) echo hppa1.1-hitachi-hiuxmpp exit ;; Pyramid*:OSx*:*:* | MIS*:OSx*:*:* | MIS*:SMP_DC-OSx*:*:*) # akee@wpdis03.wpafb.af.mil (Earle F. Ake) contributed MIS and NILE. if test "`(/bin/universe) 2>/dev/null`" = att ; then echo pyramid-pyramid-sysv3 else echo pyramid-pyramid-bsd fi exit ;; NILE*:*:*:dcosx) echo pyramid-pyramid-svr4 exit ;; DRS?6000:unix:4.0:6*) echo sparc-icl-nx6 exit ;; DRS?6000:UNIX_SV:4.2*:7* | DRS?6000:isis:4.2*:7*) case `/usr/bin/uname -p` in sparc) echo sparc-icl-nx7; exit ;; esac ;; s390x:SunOS:*:*) echo ${UNAME_MACHINE}-ibm-solaris2`echo ${UNAME_RELEASE}|sed -e 's/[^.]*//'` exit ;; sun4H:SunOS:5.*:*) echo sparc-hal-solaris2`echo ${UNAME_RELEASE}|sed -e 's/[^.]*//'` exit ;; sun4*:SunOS:5.*:* | tadpole*:SunOS:5.*:*) echo sparc-sun-solaris2`echo ${UNAME_RELEASE}|sed -e 's/[^.]*//'` exit ;; i86pc:AuroraUX:5.*:* | i86xen:AuroraUX:5.*:*) echo i386-pc-auroraux${UNAME_RELEASE} exit ;; i86pc:SunOS:5.*:* | i86xen:SunOS:5.*:*) eval $set_cc_for_build SUN_ARCH="i386" # If there is a compiler, see if it is configured for 64-bit objects. # Note that the Sun cc does not turn __LP64__ into 1 like gcc does. # This test works for both compilers. if [ "$CC_FOR_BUILD" != 'no_compiler_found' ]; then if (echo '#ifdef __amd64'; echo IS_64BIT_ARCH; echo '#endif') | \ (CCOPTS= $CC_FOR_BUILD -E - 2>/dev/null) | \ grep IS_64BIT_ARCH >/dev/null then SUN_ARCH="x86_64" fi fi echo ${SUN_ARCH}-pc-solaris2`echo ${UNAME_RELEASE}|sed -e 's/[^.]*//'` exit ;; sun4*:SunOS:6*:*) # According to config.sub, this is the proper way to canonicalize # SunOS6. Hard to guess exactly what SunOS6 will be like, but # it's likely to be more like Solaris than SunOS4. echo sparc-sun-solaris3`echo ${UNAME_RELEASE}|sed -e 's/[^.]*//'` exit ;; sun4*:SunOS:*:*) case "`/usr/bin/arch -k`" in Series*|S4*) UNAME_RELEASE=`uname -v` ;; esac # Japanese Language versions have a version number like `4.1.3-JL'. echo sparc-sun-sunos`echo ${UNAME_RELEASE}|sed -e 's/-/_/'` exit ;; sun3*:SunOS:*:*) echo m68k-sun-sunos${UNAME_RELEASE} exit ;; sun*:*:4.2BSD:*) UNAME_RELEASE=`(sed 1q /etc/motd | awk '{print substr($5,1,3)}') 2>/dev/null` test "x${UNAME_RELEASE}" = "x" && UNAME_RELEASE=3 case "`/bin/arch`" in sun3) echo m68k-sun-sunos${UNAME_RELEASE} ;; sun4) echo sparc-sun-sunos${UNAME_RELEASE} ;; esac exit ;; aushp:SunOS:*:*) echo sparc-auspex-sunos${UNAME_RELEASE} exit ;; # The situation for MiNT is a little confusing. The machine name # can be virtually everything (everything which is not # "atarist" or "atariste" at least should have a processor # > m68000). The system name ranges from "MiNT" over "FreeMiNT" # to the lowercase version "mint" (or "freemint"). Finally # the system name "TOS" denotes a system which is actually not # MiNT. But MiNT is downward compatible to TOS, so this should # be no problem. atarist[e]:*MiNT:*:* | atarist[e]:*mint:*:* | atarist[e]:*TOS:*:*) echo m68k-atari-mint${UNAME_RELEASE} exit ;; atari*:*MiNT:*:* | atari*:*mint:*:* | atarist[e]:*TOS:*:*) echo m68k-atari-mint${UNAME_RELEASE} exit ;; *falcon*:*MiNT:*:* | *falcon*:*mint:*:* | *falcon*:*TOS:*:*) echo m68k-atari-mint${UNAME_RELEASE} exit ;; milan*:*MiNT:*:* | milan*:*mint:*:* | *milan*:*TOS:*:*) echo m68k-milan-mint${UNAME_RELEASE} exit ;; hades*:*MiNT:*:* | hades*:*mint:*:* | *hades*:*TOS:*:*) echo m68k-hades-mint${UNAME_RELEASE} exit ;; *:*MiNT:*:* | *:*mint:*:* | *:*TOS:*:*) echo m68k-unknown-mint${UNAME_RELEASE} exit ;; m68k:machten:*:*) echo m68k-apple-machten${UNAME_RELEASE} exit ;; powerpc:machten:*:*) echo powerpc-apple-machten${UNAME_RELEASE} exit ;; RISC*:Mach:*:*) echo mips-dec-mach_bsd4.3 exit ;; RISC*:ULTRIX:*:*) echo mips-dec-ultrix${UNAME_RELEASE} exit ;; VAX*:ULTRIX*:*:*) echo vax-dec-ultrix${UNAME_RELEASE} exit ;; 2020:CLIX:*:* | 2430:CLIX:*:*) echo clipper-intergraph-clix${UNAME_RELEASE} exit ;; mips:*:*:UMIPS | mips:*:*:RISCos) eval $set_cc_for_build sed 's/^ //' << EOF >$dummy.c #ifdef __cplusplus #include /* for printf() prototype */ int main (int argc, char *argv[]) { #else int main (argc, argv) int argc; char *argv[]; { #endif #if defined (host_mips) && defined (MIPSEB) #if defined (SYSTYPE_SYSV) printf ("mips-mips-riscos%ssysv\n", argv[1]); exit (0); #endif #if defined (SYSTYPE_SVR4) printf ("mips-mips-riscos%ssvr4\n", argv[1]); exit (0); #endif #if defined (SYSTYPE_BSD43) || defined(SYSTYPE_BSD) printf ("mips-mips-riscos%sbsd\n", argv[1]); exit (0); #endif #endif exit (-1); } EOF $CC_FOR_BUILD -o $dummy $dummy.c && dummyarg=`echo "${UNAME_RELEASE}" | sed -n 's/\([0-9]*\).*/\1/p'` && SYSTEM_NAME=`$dummy $dummyarg` && { echo "$SYSTEM_NAME"; exit; } echo mips-mips-riscos${UNAME_RELEASE} exit ;; Motorola:PowerMAX_OS:*:*) echo powerpc-motorola-powermax exit ;; Motorola:*:4.3:PL8-*) echo powerpc-harris-powermax exit ;; Night_Hawk:*:*:PowerMAX_OS | Synergy:PowerMAX_OS:*:*) echo powerpc-harris-powermax exit ;; Night_Hawk:Power_UNIX:*:*) echo powerpc-harris-powerunix exit ;; m88k:CX/UX:7*:*) echo m88k-harris-cxux7 exit ;; m88k:*:4*:R4*) echo m88k-motorola-sysv4 exit ;; m88k:*:3*:R3*) echo m88k-motorola-sysv3 exit ;; AViiON:dgux:*:*) # DG/UX returns AViiON for all architectures UNAME_PROCESSOR=`/usr/bin/uname -p` if [ $UNAME_PROCESSOR = mc88100 ] || [ $UNAME_PROCESSOR = mc88110 ] then if [ ${TARGET_BINARY_INTERFACE}x = m88kdguxelfx ] || \ [ ${TARGET_BINARY_INTERFACE}x = x ] then echo m88k-dg-dgux${UNAME_RELEASE} else echo m88k-dg-dguxbcs${UNAME_RELEASE} fi else echo i586-dg-dgux${UNAME_RELEASE} fi exit ;; M88*:DolphinOS:*:*) # DolphinOS (SVR3) echo m88k-dolphin-sysv3 exit ;; M88*:*:R3*:*) # Delta 88k system running SVR3 echo m88k-motorola-sysv3 exit ;; XD88*:*:*:*) # Tektronix XD88 system running UTekV (SVR3) echo m88k-tektronix-sysv3 exit ;; Tek43[0-9][0-9]:UTek:*:*) # Tektronix 4300 system running UTek (BSD) echo m68k-tektronix-bsd exit ;; *:IRIX*:*:*) echo mips-sgi-irix`echo ${UNAME_RELEASE}|sed -e 's/-/_/g'` exit ;; ????????:AIX?:[12].1:2) # AIX 2.2.1 or AIX 2.1.1 is RT/PC AIX. echo romp-ibm-aix # uname -m gives an 8 hex-code CPU id exit ;; # Note that: echo "'`uname -s`'" gives 'AIX ' i*86:AIX:*:*) echo i386-ibm-aix exit ;; ia64:AIX:*:*) if [ -x /usr/bin/oslevel ] ; then IBM_REV=`/usr/bin/oslevel` else IBM_REV=${UNAME_VERSION}.${UNAME_RELEASE} fi echo ${UNAME_MACHINE}-ibm-aix${IBM_REV} exit ;; *:AIX:2:3) if grep bos325 /usr/include/stdio.h >/dev/null 2>&1; then eval $set_cc_for_build sed 's/^ //' << EOF >$dummy.c #include main() { if (!__power_pc()) exit(1); puts("powerpc-ibm-aix3.2.5"); exit(0); } EOF if $CC_FOR_BUILD -o $dummy $dummy.c && SYSTEM_NAME=`$dummy` then echo "$SYSTEM_NAME" else echo rs6000-ibm-aix3.2.5 fi elif grep bos324 /usr/include/stdio.h >/dev/null 2>&1; then echo rs6000-ibm-aix3.2.4 else echo rs6000-ibm-aix3.2 fi exit ;; *:AIX:*:[4567]) IBM_CPU_ID=`/usr/sbin/lsdev -C -c processor -S available | sed 1q | awk '{ print $1 }'` if /usr/sbin/lsattr -El ${IBM_CPU_ID} | grep ' POWER' >/dev/null 2>&1; then IBM_ARCH=rs6000 else IBM_ARCH=powerpc fi if [ -x /usr/bin/oslevel ] ; then IBM_REV=`/usr/bin/oslevel` else IBM_REV=${UNAME_VERSION}.${UNAME_RELEASE} fi echo ${IBM_ARCH}-ibm-aix${IBM_REV} exit ;; *:AIX:*:*) echo rs6000-ibm-aix exit ;; ibmrt:4.4BSD:*|romp-ibm:BSD:*) echo romp-ibm-bsd4.4 exit ;; ibmrt:*BSD:*|romp-ibm:BSD:*) # covers RT/PC BSD and echo romp-ibm-bsd${UNAME_RELEASE} # 4.3 with uname added to exit ;; # report: romp-ibm BSD 4.3 *:BOSX:*:*) echo rs6000-bull-bosx exit ;; DPX/2?00:B.O.S.:*:*) echo m68k-bull-sysv3 exit ;; 9000/[34]??:4.3bsd:1.*:*) echo m68k-hp-bsd exit ;; hp300:4.4BSD:*:* | 9000/[34]??:4.3bsd:2.*:*) echo m68k-hp-bsd4.4 exit ;; 9000/[34678]??:HP-UX:*:*) HPUX_REV=`echo ${UNAME_RELEASE}|sed -e 's/[^.]*.[0B]*//'` case "${UNAME_MACHINE}" in 9000/31? ) HP_ARCH=m68000 ;; 9000/[34]?? ) HP_ARCH=m68k ;; 9000/[678][0-9][0-9]) if [ -x /usr/bin/getconf ]; then sc_cpu_version=`/usr/bin/getconf SC_CPU_VERSION 2>/dev/null` sc_kernel_bits=`/usr/bin/getconf SC_KERNEL_BITS 2>/dev/null` case "${sc_cpu_version}" in 523) HP_ARCH="hppa1.0" ;; # CPU_PA_RISC1_0 528) HP_ARCH="hppa1.1" ;; # CPU_PA_RISC1_1 532) # CPU_PA_RISC2_0 case "${sc_kernel_bits}" in 32) HP_ARCH="hppa2.0n" ;; 64) HP_ARCH="hppa2.0w" ;; '') HP_ARCH="hppa2.0" ;; # HP-UX 10.20 esac ;; esac fi if [ "${HP_ARCH}" = "" ]; then eval $set_cc_for_build sed 's/^ //' << EOF >$dummy.c #define _HPUX_SOURCE #include #include int main () { #if defined(_SC_KERNEL_BITS) long bits = sysconf(_SC_KERNEL_BITS); #endif long cpu = sysconf (_SC_CPU_VERSION); switch (cpu) { case CPU_PA_RISC1_0: puts ("hppa1.0"); break; case CPU_PA_RISC1_1: puts ("hppa1.1"); break; case CPU_PA_RISC2_0: #if defined(_SC_KERNEL_BITS) switch (bits) { case 64: puts ("hppa2.0w"); break; case 32: puts ("hppa2.0n"); break; default: puts ("hppa2.0"); break; } break; #else /* !defined(_SC_KERNEL_BITS) */ puts ("hppa2.0"); break; #endif default: puts ("hppa1.0"); break; } exit (0); } EOF (CCOPTS= $CC_FOR_BUILD -o $dummy $dummy.c 2>/dev/null) && HP_ARCH=`$dummy` test -z "$HP_ARCH" && HP_ARCH=hppa fi ;; esac if [ ${HP_ARCH} = "hppa2.0w" ] then eval $set_cc_for_build # hppa2.0w-hp-hpux* has a 64-bit kernel and a compiler generating # 32-bit code. hppa64-hp-hpux* has the same kernel and a compiler # generating 64-bit code. GNU and HP use different nomenclature: # # $ CC_FOR_BUILD=cc ./config.guess # => hppa2.0w-hp-hpux11.23 # $ CC_FOR_BUILD="cc +DA2.0w" ./config.guess # => hppa64-hp-hpux11.23 if echo __LP64__ | (CCOPTS= $CC_FOR_BUILD -E - 2>/dev/null) | grep -q __LP64__ then HP_ARCH="hppa2.0w" else HP_ARCH="hppa64" fi fi echo ${HP_ARCH}-hp-hpux${HPUX_REV} exit ;; ia64:HP-UX:*:*) HPUX_REV=`echo ${UNAME_RELEASE}|sed -e 's/[^.]*.[0B]*//'` echo ia64-hp-hpux${HPUX_REV} exit ;; 3050*:HI-UX:*:*) eval $set_cc_for_build sed 's/^ //' << EOF >$dummy.c #include int main () { long cpu = sysconf (_SC_CPU_VERSION); /* The order matters, because CPU_IS_HP_MC68K erroneously returns true for CPU_PA_RISC1_0. CPU_IS_PA_RISC returns correct results, however. */ if (CPU_IS_PA_RISC (cpu)) { switch (cpu) { case CPU_PA_RISC1_0: puts ("hppa1.0-hitachi-hiuxwe2"); break; case CPU_PA_RISC1_1: puts ("hppa1.1-hitachi-hiuxwe2"); break; case CPU_PA_RISC2_0: puts ("hppa2.0-hitachi-hiuxwe2"); break; default: puts ("hppa-hitachi-hiuxwe2"); break; } } else if (CPU_IS_HP_MC68K (cpu)) puts ("m68k-hitachi-hiuxwe2"); else puts ("unknown-hitachi-hiuxwe2"); exit (0); } EOF $CC_FOR_BUILD -o $dummy $dummy.c && SYSTEM_NAME=`$dummy` && { echo "$SYSTEM_NAME"; exit; } echo unknown-hitachi-hiuxwe2 exit ;; 9000/7??:4.3bsd:*:* | 9000/8?[79]:4.3bsd:*:* ) echo hppa1.1-hp-bsd exit ;; 9000/8??:4.3bsd:*:*) echo hppa1.0-hp-bsd exit ;; *9??*:MPE/iX:*:* | *3000*:MPE/iX:*:*) echo hppa1.0-hp-mpeix exit ;; hp7??:OSF1:*:* | hp8?[79]:OSF1:*:* ) echo hppa1.1-hp-osf exit ;; hp8??:OSF1:*:*) echo hppa1.0-hp-osf exit ;; i*86:OSF1:*:*) if [ -x /usr/sbin/sysversion ] ; then echo ${UNAME_MACHINE}-unknown-osf1mk else echo ${UNAME_MACHINE}-unknown-osf1 fi exit ;; parisc*:Lites*:*:*) echo hppa1.1-hp-lites exit ;; C1*:ConvexOS:*:* | convex:ConvexOS:C1*:*) echo c1-convex-bsd exit ;; C2*:ConvexOS:*:* | convex:ConvexOS:C2*:*) if getsysinfo -f scalar_acc then echo c32-convex-bsd else echo c2-convex-bsd fi exit ;; C34*:ConvexOS:*:* | convex:ConvexOS:C34*:*) echo c34-convex-bsd exit ;; C38*:ConvexOS:*:* | convex:ConvexOS:C38*:*) echo c38-convex-bsd exit ;; C4*:ConvexOS:*:* | convex:ConvexOS:C4*:*) echo c4-convex-bsd exit ;; CRAY*Y-MP:*:*:*) echo ymp-cray-unicos${UNAME_RELEASE} | sed -e 's/\.[^.]*$/.X/' exit ;; CRAY*[A-Z]90:*:*:*) echo ${UNAME_MACHINE}-cray-unicos${UNAME_RELEASE} \ | sed -e 's/CRAY.*\([A-Z]90\)/\1/' \ -e y/ABCDEFGHIJKLMNOPQRSTUVWXYZ/abcdefghijklmnopqrstuvwxyz/ \ -e 's/\.[^.]*$/.X/' exit ;; CRAY*TS:*:*:*) echo t90-cray-unicos${UNAME_RELEASE} | sed -e 's/\.[^.]*$/.X/' exit ;; CRAY*T3E:*:*:*) echo alphaev5-cray-unicosmk${UNAME_RELEASE} | sed -e 's/\.[^.]*$/.X/' exit ;; CRAY*SV1:*:*:*) echo sv1-cray-unicos${UNAME_RELEASE} | sed -e 's/\.[^.]*$/.X/' exit ;; *:UNICOS/mp:*:*) echo craynv-cray-unicosmp${UNAME_RELEASE} | sed -e 's/\.[^.]*$/.X/' exit ;; F30[01]:UNIX_System_V:*:* | F700:UNIX_System_V:*:*) FUJITSU_PROC=`uname -m | tr 'ABCDEFGHIJKLMNOPQRSTUVWXYZ' 'abcdefghijklmnopqrstuvwxyz'` FUJITSU_SYS=`uname -p | tr 'ABCDEFGHIJKLMNOPQRSTUVWXYZ' 'abcdefghijklmnopqrstuvwxyz' | sed -e 's/\///'` FUJITSU_REL=`echo ${UNAME_RELEASE} | sed -e 's/ /_/'` echo "${FUJITSU_PROC}-fujitsu-${FUJITSU_SYS}${FUJITSU_REL}" exit ;; 5000:UNIX_System_V:4.*:*) FUJITSU_SYS=`uname -p | tr 'ABCDEFGHIJKLMNOPQRSTUVWXYZ' 'abcdefghijklmnopqrstuvwxyz' | sed -e 's/\///'` FUJITSU_REL=`echo ${UNAME_RELEASE} | tr 'ABCDEFGHIJKLMNOPQRSTUVWXYZ' 'abcdefghijklmnopqrstuvwxyz' | sed -e 's/ /_/'` echo "sparc-fujitsu-${FUJITSU_SYS}${FUJITSU_REL}" exit ;; i*86:BSD/386:*:* | i*86:BSD/OS:*:* | *:Ascend\ Embedded/OS:*:*) echo ${UNAME_MACHINE}-pc-bsdi${UNAME_RELEASE} exit ;; sparc*:BSD/OS:*:*) echo sparc-unknown-bsdi${UNAME_RELEASE} exit ;; *:BSD/OS:*:*) echo ${UNAME_MACHINE}-unknown-bsdi${UNAME_RELEASE} exit ;; *:FreeBSD:*:*) UNAME_PROCESSOR=`/usr/bin/uname -p` case ${UNAME_PROCESSOR} in amd64) echo x86_64-unknown-freebsd`echo ${UNAME_RELEASE}|sed -e 's/[-(].*//'` ;; *) echo ${UNAME_PROCESSOR}-unknown-freebsd`echo ${UNAME_RELEASE}|sed -e 's/[-(].*//'` ;; esac exit ;; i*:CYGWIN*:*) echo ${UNAME_MACHINE}-pc-cygwin exit ;; *:MINGW*:*) echo ${UNAME_MACHINE}-pc-mingw32 exit ;; i*:MSYS*:*) echo ${UNAME_MACHINE}-pc-msys exit ;; i*:windows32*:*) # uname -m includes "-pc" on this system. echo ${UNAME_MACHINE}-mingw32 exit ;; i*:PW*:*) echo ${UNAME_MACHINE}-pc-pw32 exit ;; *:Interix*:*) case ${UNAME_MACHINE} in x86) echo i586-pc-interix${UNAME_RELEASE} exit ;; authenticamd | genuineintel | EM64T) echo x86_64-unknown-interix${UNAME_RELEASE} exit ;; IA64) echo ia64-unknown-interix${UNAME_RELEASE} exit ;; esac ;; [345]86:Windows_95:* | [345]86:Windows_98:* | [345]86:Windows_NT:*) echo i${UNAME_MACHINE}-pc-mks exit ;; 8664:Windows_NT:*) echo x86_64-pc-mks exit ;; i*:Windows_NT*:* | Pentium*:Windows_NT*:*) # How do we know it's Interix rather than the generic POSIX subsystem? # It also conflicts with pre-2.0 versions of AT&T UWIN. Should we # UNAME_MACHINE based on the output of uname instead of i386? echo i586-pc-interix exit ;; i*:UWIN*:*) echo ${UNAME_MACHINE}-pc-uwin exit ;; amd64:CYGWIN*:*:* | x86_64:CYGWIN*:*:*) echo x86_64-unknown-cygwin exit ;; p*:CYGWIN*:*) echo powerpcle-unknown-cygwin exit ;; prep*:SunOS:5.*:*) echo powerpcle-unknown-solaris2`echo ${UNAME_RELEASE}|sed -e 's/[^.]*//'` exit ;; *:GNU:*:*) # the GNU system echo `echo ${UNAME_MACHINE}|sed -e 's,[-/].*$,,'`-unknown-gnu`echo ${UNAME_RELEASE}|sed -e 's,/.*$,,'` exit ;; *:GNU/*:*:*) # other systems with GNU libc and userland echo ${UNAME_MACHINE}-unknown-`echo ${UNAME_SYSTEM} | sed 's,^[^/]*/,,' | tr '[A-Z]' '[a-z]'``echo ${UNAME_RELEASE}|sed -e 's/[-(].*//'`-gnu exit ;; i*86:Minix:*:*) echo ${UNAME_MACHINE}-pc-minix exit ;; aarch64:Linux:*:*) echo ${UNAME_MACHINE}-unknown-linux-gnu exit ;; aarch64_be:Linux:*:*) UNAME_MACHINE=aarch64_be echo ${UNAME_MACHINE}-unknown-linux-gnu exit ;; alpha:Linux:*:*) case `sed -n '/^cpu model/s/^.*: \(.*\)/\1/p' < /proc/cpuinfo` in EV5) UNAME_MACHINE=alphaev5 ;; EV56) UNAME_MACHINE=alphaev56 ;; PCA56) UNAME_MACHINE=alphapca56 ;; PCA57) UNAME_MACHINE=alphapca56 ;; EV6) UNAME_MACHINE=alphaev6 ;; EV67) UNAME_MACHINE=alphaev67 ;; EV68*) UNAME_MACHINE=alphaev68 ;; esac objdump --private-headers /bin/sh | grep -q ld.so.1 if test "$?" = 0 ; then LIBC="libc1" ; else LIBC="" ; fi echo ${UNAME_MACHINE}-unknown-linux-gnu${LIBC} exit ;; arm*:Linux:*:*) eval $set_cc_for_build if echo __ARM_EABI__ | $CC_FOR_BUILD -E - 2>/dev/null \ | grep -q __ARM_EABI__ then echo ${UNAME_MACHINE}-unknown-linux-gnu else if echo __ARM_PCS_VFP | $CC_FOR_BUILD -E - 2>/dev/null \ | grep -q __ARM_PCS_VFP then echo ${UNAME_MACHINE}-unknown-linux-gnueabi else echo ${UNAME_MACHINE}-unknown-linux-gnueabihf fi fi exit ;; avr32*:Linux:*:*) echo ${UNAME_MACHINE}-unknown-linux-gnu exit ;; cris:Linux:*:*) echo ${UNAME_MACHINE}-axis-linux-gnu exit ;; crisv32:Linux:*:*) echo ${UNAME_MACHINE}-axis-linux-gnu exit ;; frv:Linux:*:*) echo ${UNAME_MACHINE}-unknown-linux-gnu exit ;; hexagon:Linux:*:*) echo ${UNAME_MACHINE}-unknown-linux-gnu exit ;; i*86:Linux:*:*) LIBC=gnu eval $set_cc_for_build sed 's/^ //' << EOF >$dummy.c #ifdef __dietlibc__ LIBC=dietlibc #endif EOF eval `$CC_FOR_BUILD -E $dummy.c 2>/dev/null | grep '^LIBC'` echo "${UNAME_MACHINE}-pc-linux-${LIBC}" exit ;; ia64:Linux:*:*) echo ${UNAME_MACHINE}-unknown-linux-gnu exit ;; m32r*:Linux:*:*) echo ${UNAME_MACHINE}-unknown-linux-gnu exit ;; m68*:Linux:*:*) echo ${UNAME_MACHINE}-unknown-linux-gnu exit ;; mips:Linux:*:* | mips64:Linux:*:*) eval $set_cc_for_build sed 's/^ //' << EOF >$dummy.c #undef CPU #undef ${UNAME_MACHINE} #undef ${UNAME_MACHINE}el #if defined(__MIPSEL__) || defined(__MIPSEL) || defined(_MIPSEL) || defined(MIPSEL) CPU=${UNAME_MACHINE}el #else #if defined(__MIPSEB__) || defined(__MIPSEB) || defined(_MIPSEB) || defined(MIPSEB) CPU=${UNAME_MACHINE} #else CPU= #endif #endif EOF eval `$CC_FOR_BUILD -E $dummy.c 2>/dev/null | grep '^CPU'` test x"${CPU}" != x && { echo "${CPU}-unknown-linux-gnu"; exit; } ;; or32:Linux:*:*) echo ${UNAME_MACHINE}-unknown-linux-gnu exit ;; padre:Linux:*:*) echo sparc-unknown-linux-gnu exit ;; parisc64:Linux:*:* | hppa64:Linux:*:*) echo hppa64-unknown-linux-gnu exit ;; parisc:Linux:*:* | hppa:Linux:*:*) # Look for CPU level case `grep '^cpu[^a-z]*:' /proc/cpuinfo 2>/dev/null | cut -d' ' -f2` in PA7*) echo hppa1.1-unknown-linux-gnu ;; PA8*) echo hppa2.0-unknown-linux-gnu ;; *) echo hppa-unknown-linux-gnu ;; esac exit ;; ppc64:Linux:*:*) echo powerpc64-unknown-linux-gnu exit ;; ppc:Linux:*:*) echo powerpc-unknown-linux-gnu exit ;; s390:Linux:*:* | s390x:Linux:*:*) echo ${UNAME_MACHINE}-ibm-linux exit ;; sh64*:Linux:*:*) echo ${UNAME_MACHINE}-unknown-linux-gnu exit ;; sh*:Linux:*:*) echo ${UNAME_MACHINE}-unknown-linux-gnu exit ;; sparc:Linux:*:* | sparc64:Linux:*:*) echo ${UNAME_MACHINE}-unknown-linux-gnu exit ;; tile*:Linux:*:*) echo ${UNAME_MACHINE}-unknown-linux-gnu exit ;; vax:Linux:*:*) echo ${UNAME_MACHINE}-dec-linux-gnu exit ;; x86_64:Linux:*:*) echo ${UNAME_MACHINE}-unknown-linux-gnu exit ;; xtensa*:Linux:*:*) echo ${UNAME_MACHINE}-unknown-linux-gnu exit ;; i*86:DYNIX/ptx:4*:*) # ptx 4.0 does uname -s correctly, with DYNIX/ptx in there. # earlier versions are messed up and put the nodename in both # sysname and nodename. echo i386-sequent-sysv4 exit ;; i*86:UNIX_SV:4.2MP:2.*) # Unixware is an offshoot of SVR4, but it has its own version # number series starting with 2... # I am not positive that other SVR4 systems won't match this, # I just have to hope. -- rms. # Use sysv4.2uw... so that sysv4* matches it. echo ${UNAME_MACHINE}-pc-sysv4.2uw${UNAME_VERSION} exit ;; i*86:OS/2:*:*) # If we were able to find `uname', then EMX Unix compatibility # is probably installed. echo ${UNAME_MACHINE}-pc-os2-emx exit ;; i*86:XTS-300:*:STOP) echo ${UNAME_MACHINE}-unknown-stop exit ;; i*86:atheos:*:*) echo ${UNAME_MACHINE}-unknown-atheos exit ;; i*86:syllable:*:*) echo ${UNAME_MACHINE}-pc-syllable exit ;; i*86:LynxOS:2.*:* | i*86:LynxOS:3.[01]*:* | i*86:LynxOS:4.[02]*:*) echo i386-unknown-lynxos${UNAME_RELEASE} exit ;; i*86:*DOS:*:*) echo ${UNAME_MACHINE}-pc-msdosdjgpp exit ;; i*86:*:4.*:* | i*86:SYSTEM_V:4.*:*) UNAME_REL=`echo ${UNAME_RELEASE} | sed 's/\/MP$//'` if grep Novell /usr/include/link.h >/dev/null 2>/dev/null; then echo ${UNAME_MACHINE}-univel-sysv${UNAME_REL} else echo ${UNAME_MACHINE}-pc-sysv${UNAME_REL} fi exit ;; i*86:*:5:[678]*) # UnixWare 7.x, OpenUNIX and OpenServer 6. case `/bin/uname -X | grep "^Machine"` in *486*) UNAME_MACHINE=i486 ;; *Pentium) UNAME_MACHINE=i586 ;; *Pent*|*Celeron) UNAME_MACHINE=i686 ;; esac echo ${UNAME_MACHINE}-unknown-sysv${UNAME_RELEASE}${UNAME_SYSTEM}${UNAME_VERSION} exit ;; i*86:*:3.2:*) if test -f /usr/options/cb.name; then UNAME_REL=`sed -n 's/.*Version //p' /dev/null >/dev/null ; then UNAME_REL=`(/bin/uname -X|grep Release|sed -e 's/.*= //')` (/bin/uname -X|grep i80486 >/dev/null) && UNAME_MACHINE=i486 (/bin/uname -X|grep '^Machine.*Pentium' >/dev/null) \ && UNAME_MACHINE=i586 (/bin/uname -X|grep '^Machine.*Pent *II' >/dev/null) \ && UNAME_MACHINE=i686 (/bin/uname -X|grep '^Machine.*Pentium Pro' >/dev/null) \ && UNAME_MACHINE=i686 echo ${UNAME_MACHINE}-pc-sco$UNAME_REL else echo ${UNAME_MACHINE}-pc-sysv32 fi exit ;; pc:*:*:*) # Left here for compatibility: # uname -m prints for DJGPP always 'pc', but it prints nothing about # the processor, so we play safe by assuming i586. # Note: whatever this is, it MUST be the same as what config.sub # prints for the "djgpp" host, or else GDB configury will decide that # this is a cross-build. echo i586-pc-msdosdjgpp exit ;; Intel:Mach:3*:*) echo i386-pc-mach3 exit ;; paragon:*:*:*) echo i860-intel-osf1 exit ;; i860:*:4.*:*) # i860-SVR4 if grep Stardent /usr/include/sys/uadmin.h >/dev/null 2>&1 ; then echo i860-stardent-sysv${UNAME_RELEASE} # Stardent Vistra i860-SVR4 else # Add other i860-SVR4 vendors below as they are discovered. echo i860-unknown-sysv${UNAME_RELEASE} # Unknown i860-SVR4 fi exit ;; mini*:CTIX:SYS*5:*) # "miniframe" echo m68010-convergent-sysv exit ;; mc68k:UNIX:SYSTEM5:3.51m) echo m68k-convergent-sysv exit ;; M680?0:D-NIX:5.3:*) echo m68k-diab-dnix exit ;; M68*:*:R3V[5678]*:*) test -r /sysV68 && { echo 'm68k-motorola-sysv'; exit; } ;; 3[345]??:*:4.0:3.0 | 3[34]??A:*:4.0:3.0 | 3[34]??,*:*:4.0:3.0 | 3[34]??/*:*:4.0:3.0 | 4400:*:4.0:3.0 | 4850:*:4.0:3.0 | SKA40:*:4.0:3.0 | SDS2:*:4.0:3.0 | SHG2:*:4.0:3.0 | S7501*:*:4.0:3.0) OS_REL='' test -r /etc/.relid \ && OS_REL=.`sed -n 's/[^ ]* [^ ]* \([0-9][0-9]\).*/\1/p' < /etc/.relid` /bin/uname -p 2>/dev/null | grep 86 >/dev/null \ && { echo i486-ncr-sysv4.3${OS_REL}; exit; } /bin/uname -p 2>/dev/null | /bin/grep entium >/dev/null \ && { echo i586-ncr-sysv4.3${OS_REL}; exit; } ;; 3[34]??:*:4.0:* | 3[34]??,*:*:4.0:*) /bin/uname -p 2>/dev/null | grep 86 >/dev/null \ && { echo i486-ncr-sysv4; exit; } ;; NCR*:*:4.2:* | MPRAS*:*:4.2:*) OS_REL='.3' test -r /etc/.relid \ && OS_REL=.`sed -n 's/[^ ]* [^ ]* \([0-9][0-9]\).*/\1/p' < /etc/.relid` /bin/uname -p 2>/dev/null | grep 86 >/dev/null \ && { echo i486-ncr-sysv4.3${OS_REL}; exit; } /bin/uname -p 2>/dev/null | /bin/grep entium >/dev/null \ && { echo i586-ncr-sysv4.3${OS_REL}; exit; } /bin/uname -p 2>/dev/null | /bin/grep pteron >/dev/null \ && { echo i586-ncr-sysv4.3${OS_REL}; exit; } ;; m68*:LynxOS:2.*:* | m68*:LynxOS:3.0*:*) echo m68k-unknown-lynxos${UNAME_RELEASE} exit ;; mc68030:UNIX_System_V:4.*:*) echo m68k-atari-sysv4 exit ;; TSUNAMI:LynxOS:2.*:*) echo sparc-unknown-lynxos${UNAME_RELEASE} exit ;; rs6000:LynxOS:2.*:*) echo rs6000-unknown-lynxos${UNAME_RELEASE} exit ;; PowerPC:LynxOS:2.*:* | PowerPC:LynxOS:3.[01]*:* | PowerPC:LynxOS:4.[02]*:*) echo powerpc-unknown-lynxos${UNAME_RELEASE} exit ;; SM[BE]S:UNIX_SV:*:*) echo mips-dde-sysv${UNAME_RELEASE} exit ;; RM*:ReliantUNIX-*:*:*) echo mips-sni-sysv4 exit ;; RM*:SINIX-*:*:*) echo mips-sni-sysv4 exit ;; *:SINIX-*:*:*) if uname -p 2>/dev/null >/dev/null ; then UNAME_MACHINE=`(uname -p) 2>/dev/null` echo ${UNAME_MACHINE}-sni-sysv4 else echo ns32k-sni-sysv fi exit ;; PENTIUM:*:4.0*:*) # Unisys `ClearPath HMP IX 4000' SVR4/MP effort # says echo i586-unisys-sysv4 exit ;; *:UNIX_System_V:4*:FTX*) # From Gerald Hewes . # How about differentiating between stratus architectures? -djm echo hppa1.1-stratus-sysv4 exit ;; *:*:*:FTX*) # From seanf@swdc.stratus.com. echo i860-stratus-sysv4 exit ;; i*86:VOS:*:*) # From Paul.Green@stratus.com. echo ${UNAME_MACHINE}-stratus-vos exit ;; *:VOS:*:*) # From Paul.Green@stratus.com. echo hppa1.1-stratus-vos exit ;; mc68*:A/UX:*:*) echo m68k-apple-aux${UNAME_RELEASE} exit ;; news*:NEWS-OS:6*:*) echo mips-sony-newsos6 exit ;; R[34]000:*System_V*:*:* | R4000:UNIX_SYSV:*:* | R*000:UNIX_SV:*:*) if [ -d /usr/nec ]; then echo mips-nec-sysv${UNAME_RELEASE} else echo mips-unknown-sysv${UNAME_RELEASE} fi exit ;; BeBox:BeOS:*:*) # BeOS running on hardware made by Be, PPC only. echo powerpc-be-beos exit ;; BeMac:BeOS:*:*) # BeOS running on Mac or Mac clone, PPC only. echo powerpc-apple-beos exit ;; BePC:BeOS:*:*) # BeOS running on Intel PC compatible. echo i586-pc-beos exit ;; BePC:Haiku:*:*) # Haiku running on Intel PC compatible. echo i586-pc-haiku exit ;; SX-4:SUPER-UX:*:*) echo sx4-nec-superux${UNAME_RELEASE} exit ;; SX-5:SUPER-UX:*:*) echo sx5-nec-superux${UNAME_RELEASE} exit ;; SX-6:SUPER-UX:*:*) echo sx6-nec-superux${UNAME_RELEASE} exit ;; SX-7:SUPER-UX:*:*) echo sx7-nec-superux${UNAME_RELEASE} exit ;; SX-8:SUPER-UX:*:*) echo sx8-nec-superux${UNAME_RELEASE} exit ;; SX-8R:SUPER-UX:*:*) echo sx8r-nec-superux${UNAME_RELEASE} exit ;; Power*:Rhapsody:*:*) echo powerpc-apple-rhapsody${UNAME_RELEASE} exit ;; *:Rhapsody:*:*) echo ${UNAME_MACHINE}-apple-rhapsody${UNAME_RELEASE} exit ;; *:Darwin:*:*) UNAME_PROCESSOR=`uname -p` || UNAME_PROCESSOR=unknown case $UNAME_PROCESSOR in i386) eval $set_cc_for_build if [ "$CC_FOR_BUILD" != 'no_compiler_found' ]; then if (echo '#ifdef __LP64__'; echo IS_64BIT_ARCH; echo '#endif') | \ (CCOPTS= $CC_FOR_BUILD -E - 2>/dev/null) | \ grep IS_64BIT_ARCH >/dev/null then UNAME_PROCESSOR="x86_64" fi fi ;; unknown) UNAME_PROCESSOR=powerpc ;; esac echo ${UNAME_PROCESSOR}-apple-darwin${UNAME_RELEASE} exit ;; *:procnto*:*:* | *:QNX:[0123456789]*:*) UNAME_PROCESSOR=`uname -p` if test "$UNAME_PROCESSOR" = "x86"; then UNAME_PROCESSOR=i386 UNAME_MACHINE=pc fi echo ${UNAME_PROCESSOR}-${UNAME_MACHINE}-nto-qnx${UNAME_RELEASE} exit ;; *:QNX:*:4*) echo i386-pc-qnx exit ;; NEO-?:NONSTOP_KERNEL:*:*) echo neo-tandem-nsk${UNAME_RELEASE} exit ;; NSE-?:NONSTOP_KERNEL:*:*) echo nse-tandem-nsk${UNAME_RELEASE} exit ;; NSR-?:NONSTOP_KERNEL:*:*) echo nsr-tandem-nsk${UNAME_RELEASE} exit ;; *:NonStop-UX:*:*) echo mips-compaq-nonstopux exit ;; BS2000:POSIX*:*:*) echo bs2000-siemens-sysv exit ;; DS/*:UNIX_System_V:*:*) echo ${UNAME_MACHINE}-${UNAME_SYSTEM}-${UNAME_RELEASE} exit ;; *:Plan9:*:*) # "uname -m" is not consistent, so use $cputype instead. 386 # is converted to i386 for consistency with other x86 # operating systems. if test "$cputype" = "386"; then UNAME_MACHINE=i386 else UNAME_MACHINE="$cputype" fi echo ${UNAME_MACHINE}-unknown-plan9 exit ;; *:TOPS-10:*:*) echo pdp10-unknown-tops10 exit ;; *:TENEX:*:*) echo pdp10-unknown-tenex exit ;; KS10:TOPS-20:*:* | KL10:TOPS-20:*:* | TYPE4:TOPS-20:*:*) echo pdp10-dec-tops20 exit ;; XKL-1:TOPS-20:*:* | TYPE5:TOPS-20:*:*) echo pdp10-xkl-tops20 exit ;; *:TOPS-20:*:*) echo pdp10-unknown-tops20 exit ;; *:ITS:*:*) echo pdp10-unknown-its exit ;; SEI:*:*:SEIUX) echo mips-sei-seiux${UNAME_RELEASE} exit ;; *:DragonFly:*:*) echo ${UNAME_MACHINE}-unknown-dragonfly`echo ${UNAME_RELEASE}|sed -e 's/[-(].*//'` exit ;; *:*VMS:*:*) UNAME_MACHINE=`(uname -p) 2>/dev/null` case "${UNAME_MACHINE}" in A*) echo alpha-dec-vms ; exit ;; I*) echo ia64-dec-vms ; exit ;; V*) echo vax-dec-vms ; exit ;; esac ;; *:XENIX:*:SysV) echo i386-pc-xenix exit ;; i*86:skyos:*:*) echo ${UNAME_MACHINE}-pc-skyos`echo ${UNAME_RELEASE}` | sed -e 's/ .*$//' exit ;; i*86:rdos:*:*) echo ${UNAME_MACHINE}-pc-rdos exit ;; i*86:AROS:*:*) echo ${UNAME_MACHINE}-pc-aros exit ;; x86_64:VMkernel:*:*) echo ${UNAME_MACHINE}-unknown-esx exit ;; esac #echo '(No uname command or uname output not recognized.)' 1>&2 #echo "${UNAME_MACHINE}:${UNAME_SYSTEM}:${UNAME_RELEASE}:${UNAME_VERSION}" 1>&2 eval $set_cc_for_build cat >$dummy.c < # include #endif main () { #if defined (sony) #if defined (MIPSEB) /* BFD wants "bsd" instead of "newsos". Perhaps BFD should be changed, I don't know.... */ printf ("mips-sony-bsd\n"); exit (0); #else #include printf ("m68k-sony-newsos%s\n", #ifdef NEWSOS4 "4" #else "" #endif ); exit (0); #endif #endif #if defined (__arm) && defined (__acorn) && defined (__unix) printf ("arm-acorn-riscix\n"); exit (0); #endif #if defined (hp300) && !defined (hpux) printf ("m68k-hp-bsd\n"); exit (0); #endif #if defined (NeXT) #if !defined (__ARCHITECTURE__) #define __ARCHITECTURE__ "m68k" #endif int version; version=`(hostinfo | sed -n 's/.*NeXT Mach \([0-9]*\).*/\1/p') 2>/dev/null`; if (version < 4) printf ("%s-next-nextstep%d\n", __ARCHITECTURE__, version); else printf ("%s-next-openstep%d\n", __ARCHITECTURE__, version); exit (0); #endif #if defined (MULTIMAX) || defined (n16) #if defined (UMAXV) printf ("ns32k-encore-sysv\n"); exit (0); #else #if defined (CMU) printf ("ns32k-encore-mach\n"); exit (0); #else printf ("ns32k-encore-bsd\n"); exit (0); #endif #endif #endif #if defined (__386BSD__) printf ("i386-pc-bsd\n"); exit (0); #endif #if defined (sequent) #if defined (i386) printf ("i386-sequent-dynix\n"); exit (0); #endif #if defined (ns32000) printf ("ns32k-sequent-dynix\n"); exit (0); #endif #endif #if defined (_SEQUENT_) struct utsname un; uname(&un); if (strncmp(un.version, "V2", 2) == 0) { printf ("i386-sequent-ptx2\n"); exit (0); } if (strncmp(un.version, "V1", 2) == 0) { /* XXX is V1 correct? */ printf ("i386-sequent-ptx1\n"); exit (0); } printf ("i386-sequent-ptx\n"); exit (0); #endif #if defined (vax) # if !defined (ultrix) # include # if defined (BSD) # if BSD == 43 printf ("vax-dec-bsd4.3\n"); exit (0); # else # if BSD == 199006 printf ("vax-dec-bsd4.3reno\n"); exit (0); # else printf ("vax-dec-bsd\n"); exit (0); # endif # endif # else printf ("vax-dec-bsd\n"); exit (0); # endif # else printf ("vax-dec-ultrix\n"); exit (0); # endif #endif #if defined (alliant) && defined (i860) printf ("i860-alliant-bsd\n"); exit (0); #endif exit (1); } EOF $CC_FOR_BUILD -o $dummy $dummy.c 2>/dev/null && SYSTEM_NAME=`$dummy` && { echo "$SYSTEM_NAME"; exit; } # Apollos put the system type in the environment. test -d /usr/apollo && { echo ${ISP}-apollo-${SYSTYPE}; exit; } # Convex versions that predate uname can use getsysinfo(1) if [ -x /usr/convex/getsysinfo ] then case `getsysinfo -f cpu_type` in c1*) echo c1-convex-bsd exit ;; c2*) if getsysinfo -f scalar_acc then echo c32-convex-bsd else echo c2-convex-bsd fi exit ;; c34*) echo c34-convex-bsd exit ;; c38*) echo c38-convex-bsd exit ;; c4*) echo c4-convex-bsd exit ;; esac fi cat >&2 < in order to provide the needed information to handle your system. config.guess timestamp = $timestamp uname -m = `(uname -m) 2>/dev/null || echo unknown` uname -r = `(uname -r) 2>/dev/null || echo unknown` uname -s = `(uname -s) 2>/dev/null || echo unknown` uname -v = `(uname -v) 2>/dev/null || echo unknown` /usr/bin/uname -p = `(/usr/bin/uname -p) 2>/dev/null` /bin/uname -X = `(/bin/uname -X) 2>/dev/null` hostinfo = `(hostinfo) 2>/dev/null` /bin/universe = `(/bin/universe) 2>/dev/null` /usr/bin/arch -k = `(/usr/bin/arch -k) 2>/dev/null` /bin/arch = `(/bin/arch) 2>/dev/null` /usr/bin/oslevel = `(/usr/bin/oslevel) 2>/dev/null` /usr/convex/getsysinfo = `(/usr/convex/getsysinfo) 2>/dev/null` UNAME_MACHINE = ${UNAME_MACHINE} UNAME_RELEASE = ${UNAME_RELEASE} UNAME_SYSTEM = ${UNAME_SYSTEM} UNAME_VERSION = ${UNAME_VERSION} EOF exit 1 # Local variables: # eval: (add-hook 'write-file-hooks 'time-stamp) # time-stamp-start: "timestamp='" # time-stamp-format: "%:y-%02m-%02d" # time-stamp-end: "'" # End: smalltalk-3.2.5/build-aux/readline.m40000644000175000017500000000511312123404352014341 00000000000000dnl I'd like this to be edited in -*- Autoconf -*- mode... dnl AC_DEFUN([GST_HAVE_READLINE], [ AC_ARG_WITH(readline, [ --with-readline=path set path to readline and termcap libraries --without-readline don't try to detect readline]) if test "$with_readline" != no; then AC_CACHE_CHECK(how to link with readline, gst_cv_readline_libs, [ test "$with_readline" && test -d "$with_readline" && \ LDFLAGS="$LDFLAGS -L$with_readline" \ CPPFLAGS="$CPPFLAGS -I$with_readline/../include" gst_cv_readline_libs="not found" ac_save_LIBS="$LIBS" for lib in "" -ltermcap -ltermlib -lncurses; do LIBS="$ac_save_LIBS -lreadline $lib" cat > conftest.$ac_ext <<\EOF #include #include char *readline_quote_filename (const char *s, int rtype, const char *qcp) { return (NULL); } int main() { rl_bind_key ('\t', rl_insert); /* This is missing in BSD libedit! */ rl_filename_quoting_function = (CPFunction *) readline_quote_filename; exit(0); } EOF # Link the program. If not cross-compiling, run it too, # to detect shared library dependancies. ok=yes (AC_TRY_EVAL(ac_link) && test -s conftest${ac_exeext}) || ok=no test $cross_compiling = no && test $ok = yes && (./conftest; exit) || ok=no rm -rf conftest* if test $ok = yes; then gst_cv_readline_libs="-lreadline $lib" test "x$with_readline" != x && test "$with_readline" != yes \ && test -d "$with_readline" \ && gst_cv_readline_libs="-L$with_readline $gst_cv_readline_libs" break fi done LIBS="$ac_save_LIBS" ]) if test "$gst_cv_readline_libs" != "not found"; then LIBREADLINE="$gst_cv_readline_libs" AC_SUBST(LIBREADLINE) AC_DEFINE(HAVE_READLINE, 1, [Define if your system has the GNU readline library.]) # Readline's ABI changed around version 4.2; test which # version is ours and work around the change if they have # an older readline. ac_save_LIBS="$LIBS" LIBS="$LIBS $LIBREADLINE" AC_CHECK_FUNC(rl_completion_matches, , [ AC_DEFINE(rl_filename_completion_function, filename_completion_function, [Define to filename_completion_function if you have an older readline]) AC_DEFINE(rl_username_completion_function, username_completion_function, [Define to username_completion_function if you have an older readline]) AC_DEFINE(rl_completion_matches, completion_matches, [Define to completion_matches if you have an older readline]) ]) LIBS="$ac_save_LIBS" fi fi ])dnl smalltalk-3.2.5/build-aux/gawk.m40000644000175000017500000000040612123404352013507 00000000000000AC_DEFUN([GST_PROG_GAWK], [AC_BEFORE([$0], [AC_PROG_AWK])dnl AC_CHECK_PROGS(AWK, gawk awk, ) case $AWK in *gawk) ;; *) case `"$AWK" --version 2>&1` in *GNU*) ;; *) AC_MSG_ERROR([Building GNU Smalltalk requires GNU awk.]) ;; esac ;; esac]) smalltalk-3.2.5/build-aux/setenv.m40000644000175000017500000000166512123404352014072 00000000000000# setenv.m4 serial 6 dnl Copyright (C) 2001-2004, 2006 Free Software Foundation, Inc. dnl This file is free software; the Free Software Foundation dnl gives unlimited permission to copy and/or distribute it, dnl with or without modifications, as long as this notice is preserved. AC_DEFUN([gt_FUNC_SETENV], [ AC_REPLACE_FUNCS(setenv) gt_CHECK_VAR_DECL([#include ], environ) ]) # Check if a variable is properly declared. # gt_CHECK_VAR_DECL(includes,variable) AC_DEFUN([gt_CHECK_VAR_DECL], [ define([gt_cv_var], [gt_cv_var_]$2[_declaration]) AC_MSG_CHECKING([if $2 is properly declared]) AC_CACHE_VAL(gt_cv_var, [ AC_TRY_COMPILE([$1 extern struct { int foo; } $2;], [$2.foo = 1;], gt_cv_var=no, gt_cv_var=yes)]) AC_MSG_RESULT($gt_cv_var) if test $gt_cv_var = yes; then AC_DEFINE([HAVE_]translit($2, [a-z], [A-Z])[_DECL], 1, [Define if you have the declaration of $2.]) fi ]) smalltalk-3.2.5/build-aux/gtk-2.0.m40000644000175000017500000001660712123404352013652 00000000000000# Configure paths for GTK+ # Owen Taylor 1997-2001 dnl AM_PATH_GTK_2_0([MINIMUM-VERSION, [ACTION-IF-FOUND [, ACTION-IF-NOT-FOUND [, MODULES]]]]) dnl Test for GTK+, and define GTK_CFLAGS and GTK_LIBS, if gthread is specified in MODULES, dnl pass to pkg-config dnl AC_DEFUN([AM_PATH_GTK_2_0], [dnl dnl Get the cflags and libraries from pkg-config dnl AC_ARG_ENABLE(gtktest, [ --disable-gtktest do not try to compile and run a test GTK+ program], , enable_gtktest=yes) pkg_config_args=gtk+-2.0 for module in . $4 do case "$module" in gthread) pkg_config_args="$pkg_config_args gthread-2.0" ;; esac done no_gtk="" AC_PATH_PROG(PKG_CONFIG, pkg-config, no) if test x$PKG_CONFIG != xno ; then if pkg-config --atleast-pkgconfig-version 0.7 ; then : else echo *** pkg-config too old; version 0.7 or better required. no_gtk=yes PKG_CONFIG=no fi else no_gtk=yes fi min_gtk_version=ifelse([$1], ,2.0.0,$1) AC_MSG_CHECKING(for GTK+ - version >= $min_gtk_version) if test x$PKG_CONFIG != xno ; then ## don't try to run the test against uninstalled libtool libs if $PKG_CONFIG --uninstalled $pkg_config_args; then echo "Will use uninstalled version of GTK+ found in PKG_CONFIG_PATH" enable_gtktest=no fi if $PKG_CONFIG --atleast-version $min_gtk_version $pkg_config_args; then : else no_gtk=yes fi fi if test x"$no_gtk" = x ; then GTK_CFLAGS=`$PKG_CONFIG $pkg_config_args --cflags` GTK_LIBS=`$PKG_CONFIG $pkg_config_args --libs` gtk_config_major_version=`$PKG_CONFIG --modversion gtk+-2.0 | \ sed 's/\([[0-9]]*\).\([[0-9]]*\).\([[0-9]]*\)/\1/'` gtk_config_minor_version=`$PKG_CONFIG --modversion gtk+-2.0 | \ sed 's/\([[0-9]]*\).\([[0-9]]*\).\([[0-9]]*\)/\2/'` gtk_config_micro_version=`$PKG_CONFIG --modversion gtk+-2.0 | \ sed 's/\([[0-9]]*\).\([[0-9]]*\).\([[0-9]]*\)/\3/'` if test "x$enable_gtktest" = "xyes" ; then ac_save_CFLAGS="$CFLAGS" ac_save_LIBS="$LIBS" CFLAGS="$CFLAGS $GTK_CFLAGS" LIBS="$GTK_LIBS $LIBS" dnl dnl Now check if the installed GTK+ is sufficiently new. (Also sanity dnl checks the results of pkg-config to some extent) dnl rm -f conf.gtktest AC_RUN_IFELSE([AC_LANG_SOURCE([[ #include #include #include int main () { int major, minor, micro; char *tmp_version; system ("touch conf.gtktest"); /* HP/UX 9 (%@#!) writes to sscanf strings */ tmp_version = g_strdup("$min_gtk_version"); if (sscanf(tmp_version, "%d.%d.%d", &major, &minor, µ) != 3) { printf("%s, bad version string\n", "$min_gtk_version"); exit(1); } if ((gtk_major_version != $gtk_config_major_version) || (gtk_minor_version != $gtk_config_minor_version) || (gtk_micro_version != $gtk_config_micro_version)) { printf("\n*** 'pkg-config --modversion gtk+-2.0' returned %d.%d.%d, but GTK+ (%d.%d.%d)\n", $gtk_config_major_version, $gtk_config_minor_version, $gtk_config_micro_version, gtk_major_version, gtk_minor_version, gtk_micro_version); printf ("*** was found! If pkg-config was correct, then it is best\n"); printf ("*** to remove the old version of GTK+. You may also be able to fix the error\n"); printf("*** by modifying your LD_LIBRARY_PATH enviroment variable, or by editing\n"); printf("*** /etc/ld.so.conf. Make sure you have run ldconfig if that is\n"); printf("*** required on your system.\n"); printf("*** If pkg-config was wrong, set the environment variable PKG_CONFIG_PATH\n"); printf("*** to point to the correct configuration files\n"); } else if ((gtk_major_version != GTK_MAJOR_VERSION) || (gtk_minor_version != GTK_MINOR_VERSION) || (gtk_micro_version != GTK_MICRO_VERSION)) { printf("*** GTK+ header files (version %d.%d.%d) do not match\n", GTK_MAJOR_VERSION, GTK_MINOR_VERSION, GTK_MICRO_VERSION); printf("*** library (version %d.%d.%d)\n", gtk_major_version, gtk_minor_version, gtk_micro_version); } else { if ((gtk_major_version > major) || ((gtk_major_version == major) && (gtk_minor_version > minor)) || ((gtk_major_version == major) && (gtk_minor_version == minor) && (gtk_micro_version >= micro))) { return 0; } else { printf("\n*** An old version of GTK+ (%d.%d.%d) was found.\n", gtk_major_version, gtk_minor_version, gtk_micro_version); printf("*** You need a version of GTK+ newer than %d.%d.%d. The latest version of\n", major, minor, micro); printf("*** GTK+ is always available from ftp://ftp.gtk.org.\n"); printf("***\n"); printf("*** If you have already installed a sufficiently new version, this error\n"); printf("*** probably means that the wrong copy of the pkg-config shell script is\n"); printf("*** being found. The easiest way to fix this is to remove the old version\n"); printf("*** of GTK+, but you can also set the PKG_CONFIG environment to point to the\n"); printf("*** correct copy of pkg-config. (In this case, you will have to\n"); printf("*** modify your LD_LIBRARY_PATH enviroment variable, or edit /etc/ld.so.conf\n"); printf("*** so that the correct libraries are found at run-time))\n"); } } return 1; } ]])],[],[no_gtk=yes],[echo $ac_n "cross compiling; assumed OK... $ac_c"]) CFLAGS="$ac_save_CFLAGS" LIBS="$ac_save_LIBS" fi fi if test "x$no_gtk" = x ; then AC_MSG_RESULT(yes (version $gtk_config_major_version.$gtk_config_minor_version.$gtk_config_micro_version)) ifelse([$2], , :, [$2]) else AC_MSG_RESULT(no) if test "$PKG_CONFIG" = "no" ; then echo "*** A new enough version of pkg-config was not found." echo "*** See http://pkgconfig.sourceforge.net" else if test -f conf.gtktest ; then : else echo "*** Could not run GTK+ test program, checking why..." ac_save_CFLAGS="$CFLAGS" ac_save_LIBS="$LIBS" CFLAGS="$CFLAGS $GTK_CFLAGS" LIBS="$LIBS $GTK_LIBS" AC_LINK_IFELSE([AC_LANG_PROGRAM([[ #include #include ]], [[ return ((gtk_major_version) || (gtk_minor_version) || (gtk_micro_version)); ]])],[ echo "*** The test program compiled, but did not run. This usually means" echo "*** that the run-time linker is not finding GTK+ or finding the wrong" echo "*** version of GTK+. If it is not finding GTK+, you'll need to set your" echo "*** LD_LIBRARY_PATH environment variable, or edit /etc/ld.so.conf to point" echo "*** to the installed location Also, make sure you have run ldconfig if that" echo "*** is required on your system" echo "***" echo "*** If you have an old version installed, it is best to remove it, although" echo "*** you may also be able to get things to work by modifying LD_LIBRARY_PATH" ],[ echo "*** The test program failed to compile or link. See the file config.log for the" echo "*** exact error that occured. This usually means GTK+ is incorrectly installed."]) CFLAGS="$ac_save_CFLAGS" LIBS="$ac_save_LIBS" fi fi GTK_CFLAGS="" GTK_LIBS="" ifelse([$3], , :, [$3]) fi AC_SUBST(GTK_CFLAGS) AC_SUBST(GTK_LIBS) rm -f conf.gtktest ]) smalltalk-3.2.5/build-aux/ltmain.sh0000644000175000017500000105202612130455416014147 00000000000000 # libtool (GNU libtool) 2.4.2 # Written by Gordon Matzigkeit , 1996 # Copyright (C) 1996, 1997, 1998, 1999, 2000, 2001, 2003, 2004, 2005, 2006, # 2007, 2008, 2009, 2010, 2011 Free Software Foundation, Inc. # This is free software; see the source for copying conditions. There is NO # warranty; not even for MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. # GNU Libtool is free software; you can redistribute it and/or modify # it under the terms of the GNU General Public License as published by # the Free Software Foundation; either version 2 of the License, or # (at your option) any later version. # # As a special exception to the GNU General Public License, # if you distribute this file as part of a program or library that # is built using GNU Libtool, you may include this file under the # same distribution terms that you use for the rest of that program. # # GNU Libtool is distributed in the hope that it will be useful, but # WITHOUT ANY WARRANTY; without even the implied warranty of # MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU # General Public License for more details. # # You should have received a copy of the GNU General Public License # along with GNU Libtool; see the file COPYING. If not, a copy # can be downloaded from http://www.gnu.org/licenses/gpl.html, # or obtained by writing to the Free Software Foundation, Inc., # 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. # Usage: $progname [OPTION]... [MODE-ARG]... # # Provide generalized library-building support services. # # --config show all configuration variables # --debug enable verbose shell tracing # -n, --dry-run display commands without modifying any files # --features display basic configuration information and exit # --mode=MODE use operation mode MODE # --preserve-dup-deps don't remove duplicate dependency libraries # --quiet, --silent don't print informational messages # --no-quiet, --no-silent # print informational messages (default) # --no-warn don't display warning messages # --tag=TAG use configuration variables from tag TAG # -v, --verbose print more informational messages than default # --no-verbose don't print the extra informational messages # --version print version information # -h, --help, --help-all print short, long, or detailed help message # # MODE must be one of the following: # # clean remove files from the build directory # compile compile a source file into a libtool object # execute automatically set library path, then run a program # finish complete the installation of libtool libraries # install install libraries or executables # link create a library or an executable # uninstall remove libraries from an installed directory # # MODE-ARGS vary depending on the MODE. When passed as first option, # `--mode=MODE' may be abbreviated as `MODE' or a unique abbreviation of that. # Try `$progname --help --mode=MODE' for a more detailed description of MODE. # # When reporting a bug, please describe a test case to reproduce it and # include the following information: # # host-triplet: $host # shell: $SHELL # compiler: $LTCC # compiler flags: $LTCFLAGS # linker: $LD (gnu? $with_gnu_ld) # $progname: (GNU libtool) 2.4.2 Debian-2.4.2-1.2 # automake: $automake_version # autoconf: $autoconf_version # # Report bugs to . # GNU libtool home page: . # General help using GNU software: . PROGRAM=libtool PACKAGE=libtool VERSION="2.4.2 Debian-2.4.2-1.2" TIMESTAMP="" package_revision=1.3337 # Be Bourne compatible if test -n "${ZSH_VERSION+set}" && (emulate sh) >/dev/null 2>&1; then emulate sh NULLCMD=: # Zsh 3.x and 4.x performs word splitting on ${1+"$@"}, which # is contrary to our usage. Disable this feature. alias -g '${1+"$@"}'='"$@"' setopt NO_GLOB_SUBST else case `(set -o) 2>/dev/null` in *posix*) set -o posix;; esac fi BIN_SH=xpg4; export BIN_SH # for Tru64 DUALCASE=1; export DUALCASE # for MKS sh # A function that is used when there is no print builtin or printf. func_fallback_echo () { eval 'cat <<_LTECHO_EOF $1 _LTECHO_EOF' } # NLS nuisances: We save the old values to restore during execute mode. lt_user_locale= lt_safe_locale= for lt_var in LANG LANGUAGE LC_ALL LC_CTYPE LC_COLLATE LC_MESSAGES do eval "if test \"\${$lt_var+set}\" = set; then save_$lt_var=\$$lt_var $lt_var=C export $lt_var lt_user_locale=\"$lt_var=\\\$save_\$lt_var; \$lt_user_locale\" lt_safe_locale=\"$lt_var=C; \$lt_safe_locale\" fi" done LC_ALL=C LANGUAGE=C export LANGUAGE LC_ALL $lt_unset CDPATH # Work around backward compatibility issue on IRIX 6.5. On IRIX 6.4+, sh # is ksh but when the shell is invoked as "sh" and the current value of # the _XPG environment variable is not equal to 1 (one), the special # positional parameter $0, within a function call, is the name of the # function. progpath="$0" : ${CP="cp -f"} test "${ECHO+set}" = set || ECHO=${as_echo-'printf %s\n'} : ${MAKE="make"} : ${MKDIR="mkdir"} : ${MV="mv -f"} : ${RM="rm -f"} : ${SHELL="${CONFIG_SHELL-/bin/sh}"} : ${Xsed="$SED -e 1s/^X//"} # Global variables: EXIT_SUCCESS=0 EXIT_FAILURE=1 EXIT_MISMATCH=63 # $? = 63 is used to indicate version mismatch to missing. EXIT_SKIP=77 # $? = 77 is used to indicate a skipped test to automake. exit_status=$EXIT_SUCCESS # Make sure IFS has a sensible default lt_nl=' ' IFS=" $lt_nl" dirname="s,/[^/]*$,," basename="s,^.*/,," # func_dirname file append nondir_replacement # Compute the dirname of FILE. If nonempty, add APPEND to the result, # otherwise set result to NONDIR_REPLACEMENT. func_dirname () { func_dirname_result=`$ECHO "${1}" | $SED "$dirname"` if test "X$func_dirname_result" = "X${1}"; then func_dirname_result="${3}" else func_dirname_result="$func_dirname_result${2}" fi } # func_dirname may be replaced by extended shell implementation # func_basename file func_basename () { func_basename_result=`$ECHO "${1}" | $SED "$basename"` } # func_basename may be replaced by extended shell implementation # func_dirname_and_basename file append nondir_replacement # perform func_basename and func_dirname in a single function # call: # dirname: Compute the dirname of FILE. If nonempty, # add APPEND to the result, otherwise set result # to NONDIR_REPLACEMENT. # value returned in "$func_dirname_result" # basename: Compute filename of FILE. # value retuned in "$func_basename_result" # Implementation must be kept synchronized with func_dirname # and func_basename. For efficiency, we do not delegate to # those functions but instead duplicate the functionality here. func_dirname_and_basename () { # Extract subdirectory from the argument. func_dirname_result=`$ECHO "${1}" | $SED -e "$dirname"` if test "X$func_dirname_result" = "X${1}"; then func_dirname_result="${3}" else func_dirname_result="$func_dirname_result${2}" fi func_basename_result=`$ECHO "${1}" | $SED -e "$basename"` } # func_dirname_and_basename may be replaced by extended shell implementation # func_stripname prefix suffix name # strip PREFIX and SUFFIX off of NAME. # PREFIX and SUFFIX must not contain globbing or regex special # characters, hashes, percent signs, but SUFFIX may contain a leading # dot (in which case that matches only a dot). # func_strip_suffix prefix name func_stripname () { case ${2} in .*) func_stripname_result=`$ECHO "${3}" | $SED "s%^${1}%%; s%\\\\${2}\$%%"`;; *) func_stripname_result=`$ECHO "${3}" | $SED "s%^${1}%%; s%${2}\$%%"`;; esac } # func_stripname may be replaced by extended shell implementation # These SED scripts presuppose an absolute path with a trailing slash. pathcar='s,^/\([^/]*\).*$,\1,' pathcdr='s,^/[^/]*,,' removedotparts=':dotsl s@/\./@/@g t dotsl s,/\.$,/,' collapseslashes='s@/\{1,\}@/@g' finalslash='s,/*$,/,' # func_normal_abspath PATH # Remove doubled-up and trailing slashes, "." path components, # and cancel out any ".." path components in PATH after making # it an absolute path. # value returned in "$func_normal_abspath_result" func_normal_abspath () { # Start from root dir and reassemble the path. func_normal_abspath_result= func_normal_abspath_tpath=$1 func_normal_abspath_altnamespace= case $func_normal_abspath_tpath in "") # Empty path, that just means $cwd. func_stripname '' '/' "`pwd`" func_normal_abspath_result=$func_stripname_result return ;; # The next three entries are used to spot a run of precisely # two leading slashes without using negated character classes; # we take advantage of case's first-match behaviour. ///*) # Unusual form of absolute path, do nothing. ;; //*) # Not necessarily an ordinary path; POSIX reserves leading '//' # and for example Cygwin uses it to access remote file shares # over CIFS/SMB, so we conserve a leading double slash if found. func_normal_abspath_altnamespace=/ ;; /*) # Absolute path, do nothing. ;; *) # Relative path, prepend $cwd. func_normal_abspath_tpath=`pwd`/$func_normal_abspath_tpath ;; esac # Cancel out all the simple stuff to save iterations. We also want # the path to end with a slash for ease of parsing, so make sure # there is one (and only one) here. func_normal_abspath_tpath=`$ECHO "$func_normal_abspath_tpath" | $SED \ -e "$removedotparts" -e "$collapseslashes" -e "$finalslash"` while :; do # Processed it all yet? if test "$func_normal_abspath_tpath" = / ; then # If we ascended to the root using ".." the result may be empty now. if test -z "$func_normal_abspath_result" ; then func_normal_abspath_result=/ fi break fi func_normal_abspath_tcomponent=`$ECHO "$func_normal_abspath_tpath" | $SED \ -e "$pathcar"` func_normal_abspath_tpath=`$ECHO "$func_normal_abspath_tpath" | $SED \ -e "$pathcdr"` # Figure out what to do with it case $func_normal_abspath_tcomponent in "") # Trailing empty path component, ignore it. ;; ..) # Parent dir; strip last assembled component from result. func_dirname "$func_normal_abspath_result" func_normal_abspath_result=$func_dirname_result ;; *) # Actual path component, append it. func_normal_abspath_result=$func_normal_abspath_result/$func_normal_abspath_tcomponent ;; esac done # Restore leading double-slash if one was found on entry. func_normal_abspath_result=$func_normal_abspath_altnamespace$func_normal_abspath_result } # func_relative_path SRCDIR DSTDIR # generates a relative path from SRCDIR to DSTDIR, with a trailing # slash if non-empty, suitable for immediately appending a filename # without needing to append a separator. # value returned in "$func_relative_path_result" func_relative_path () { func_relative_path_result= func_normal_abspath "$1" func_relative_path_tlibdir=$func_normal_abspath_result func_normal_abspath "$2" func_relative_path_tbindir=$func_normal_abspath_result # Ascend the tree starting from libdir while :; do # check if we have found a prefix of bindir case $func_relative_path_tbindir in $func_relative_path_tlibdir) # found an exact match func_relative_path_tcancelled= break ;; $func_relative_path_tlibdir*) # found a matching prefix func_stripname "$func_relative_path_tlibdir" '' "$func_relative_path_tbindir" func_relative_path_tcancelled=$func_stripname_result if test -z "$func_relative_path_result"; then func_relative_path_result=. fi break ;; *) func_dirname $func_relative_path_tlibdir func_relative_path_tlibdir=${func_dirname_result} if test "x$func_relative_path_tlibdir" = x ; then # Have to descend all the way to the root! func_relative_path_result=../$func_relative_path_result func_relative_path_tcancelled=$func_relative_path_tbindir break fi func_relative_path_result=../$func_relative_path_result ;; esac done # Now calculate path; take care to avoid doubling-up slashes. func_stripname '' '/' "$func_relative_path_result" func_relative_path_result=$func_stripname_result func_stripname '/' '/' "$func_relative_path_tcancelled" if test "x$func_stripname_result" != x ; then func_relative_path_result=${func_relative_path_result}/${func_stripname_result} fi # Normalisation. If bindir is libdir, return empty string, # else relative path ending with a slash; either way, target # file name can be directly appended. if test ! -z "$func_relative_path_result"; then func_stripname './' '' "$func_relative_path_result/" func_relative_path_result=$func_stripname_result fi } # The name of this program: func_dirname_and_basename "$progpath" progname=$func_basename_result # Make sure we have an absolute path for reexecution: case $progpath in [\\/]*|[A-Za-z]:\\*) ;; *[\\/]*) progdir=$func_dirname_result progdir=`cd "$progdir" && pwd` progpath="$progdir/$progname" ;; *) save_IFS="$IFS" IFS=${PATH_SEPARATOR-:} for progdir in $PATH; do IFS="$save_IFS" test -x "$progdir/$progname" && break done IFS="$save_IFS" test -n "$progdir" || progdir=`pwd` progpath="$progdir/$progname" ;; esac # Sed substitution that helps us do robust quoting. It backslashifies # metacharacters that are still active within double-quoted strings. Xsed="${SED}"' -e 1s/^X//' sed_quote_subst='s/\([`"$\\]\)/\\\1/g' # Same as above, but do not quote variable references. double_quote_subst='s/\(["`\\]\)/\\\1/g' # Sed substitution that turns a string into a regex matching for the # string literally. sed_make_literal_regex='s,[].[^$\\*\/],\\&,g' # Sed substitution that converts a w32 file name or path # which contains forward slashes, into one that contains # (escaped) backslashes. A very naive implementation. lt_sed_naive_backslashify='s|\\\\*|\\|g;s|/|\\|g;s|\\|\\\\|g' # Re-`\' parameter expansions in output of double_quote_subst that were # `\'-ed in input to the same. If an odd number of `\' preceded a '$' # in input to double_quote_subst, that '$' was protected from expansion. # Since each input `\' is now two `\'s, look for any number of runs of # four `\'s followed by two `\'s and then a '$'. `\' that '$'. bs='\\' bs2='\\\\' bs4='\\\\\\\\' dollar='\$' sed_double_backslash="\ s/$bs4/&\\ /g s/^$bs2$dollar/$bs&/ s/\\([^$bs]\\)$bs2$dollar/\\1$bs2$bs$dollar/g s/\n//g" # Standard options: opt_dry_run=false opt_help=false opt_quiet=false opt_verbose=false opt_warning=: # func_echo arg... # Echo program name prefixed message, along with the current mode # name if it has been set yet. func_echo () { $ECHO "$progname: ${opt_mode+$opt_mode: }$*" } # func_verbose arg... # Echo program name prefixed message in verbose mode only. func_verbose () { $opt_verbose && func_echo ${1+"$@"} # A bug in bash halts the script if the last line of a function # fails when set -e is in force, so we need another command to # work around that: : } # func_echo_all arg... # Invoke $ECHO with all args, space-separated. func_echo_all () { $ECHO "$*" } # func_error arg... # Echo program name prefixed message to standard error. func_error () { $ECHO "$progname: ${opt_mode+$opt_mode: }"${1+"$@"} 1>&2 } # func_warning arg... # Echo program name prefixed warning message to standard error. func_warning () { $opt_warning && $ECHO "$progname: ${opt_mode+$opt_mode: }warning: "${1+"$@"} 1>&2 # bash bug again: : } # func_fatal_error arg... # Echo program name prefixed message to standard error, and exit. func_fatal_error () { func_error ${1+"$@"} exit $EXIT_FAILURE } # func_fatal_help arg... # Echo program name prefixed message to standard error, followed by # a help hint, and exit. func_fatal_help () { func_error ${1+"$@"} func_fatal_error "$help" } help="Try \`$progname --help' for more information." ## default # func_grep expression filename # Check whether EXPRESSION matches any line of FILENAME, without output. func_grep () { $GREP "$1" "$2" >/dev/null 2>&1 } # func_mkdir_p directory-path # Make sure the entire path to DIRECTORY-PATH is available. func_mkdir_p () { my_directory_path="$1" my_dir_list= if test -n "$my_directory_path" && test "$opt_dry_run" != ":"; then # Protect directory names starting with `-' case $my_directory_path in -*) my_directory_path="./$my_directory_path" ;; esac # While some portion of DIR does not yet exist... while test ! -d "$my_directory_path"; do # ...make a list in topmost first order. Use a colon delimited # list incase some portion of path contains whitespace. my_dir_list="$my_directory_path:$my_dir_list" # If the last portion added has no slash in it, the list is done case $my_directory_path in */*) ;; *) break ;; esac # ...otherwise throw away the child directory and loop my_directory_path=`$ECHO "$my_directory_path" | $SED -e "$dirname"` done my_dir_list=`$ECHO "$my_dir_list" | $SED 's,:*$,,'` save_mkdir_p_IFS="$IFS"; IFS=':' for my_dir in $my_dir_list; do IFS="$save_mkdir_p_IFS" # mkdir can fail with a `File exist' error if two processes # try to create one of the directories concurrently. Don't # stop in that case! $MKDIR "$my_dir" 2>/dev/null || : done IFS="$save_mkdir_p_IFS" # Bail out if we (or some other process) failed to create a directory. test -d "$my_directory_path" || \ func_fatal_error "Failed to create \`$1'" fi } # func_mktempdir [string] # Make a temporary directory that won't clash with other running # libtool processes, and avoids race conditions if possible. If # given, STRING is the basename for that directory. func_mktempdir () { my_template="${TMPDIR-/tmp}/${1-$progname}" if test "$opt_dry_run" = ":"; then # Return a directory name, but don't create it in dry-run mode my_tmpdir="${my_template}-$$" else # If mktemp works, use that first and foremost my_tmpdir=`mktemp -d "${my_template}-XXXXXXXX" 2>/dev/null` if test ! -d "$my_tmpdir"; then # Failing that, at least try and use $RANDOM to avoid a race my_tmpdir="${my_template}-${RANDOM-0}$$" save_mktempdir_umask=`umask` umask 0077 $MKDIR "$my_tmpdir" umask $save_mktempdir_umask fi # If we're not in dry-run mode, bomb out on failure test -d "$my_tmpdir" || \ func_fatal_error "cannot create temporary directory \`$my_tmpdir'" fi $ECHO "$my_tmpdir" } # func_quote_for_eval arg # Aesthetically quote ARG to be evaled later. # This function returns two values: FUNC_QUOTE_FOR_EVAL_RESULT # is double-quoted, suitable for a subsequent eval, whereas # FUNC_QUOTE_FOR_EVAL_UNQUOTED_RESULT has merely all characters # which are still active within double quotes backslashified. func_quote_for_eval () { case $1 in *[\\\`\"\$]*) func_quote_for_eval_unquoted_result=`$ECHO "$1" | $SED "$sed_quote_subst"` ;; *) func_quote_for_eval_unquoted_result="$1" ;; esac case $func_quote_for_eval_unquoted_result in # Double-quote args containing shell metacharacters to delay # word splitting, command substitution and and variable # expansion for a subsequent eval. # Many Bourne shells cannot handle close brackets correctly # in scan sets, so we specify it separately. *[\[\~\#\^\&\*\(\)\{\}\|\;\<\>\?\'\ \ ]*|*]*|"") func_quote_for_eval_result="\"$func_quote_for_eval_unquoted_result\"" ;; *) func_quote_for_eval_result="$func_quote_for_eval_unquoted_result" esac } # func_quote_for_expand arg # Aesthetically quote ARG to be evaled later; same as above, # but do not quote variable references. func_quote_for_expand () { case $1 in *[\\\`\"]*) my_arg=`$ECHO "$1" | $SED \ -e "$double_quote_subst" -e "$sed_double_backslash"` ;; *) my_arg="$1" ;; esac case $my_arg in # Double-quote args containing shell metacharacters to delay # word splitting and command substitution for a subsequent eval. # Many Bourne shells cannot handle close brackets correctly # in scan sets, so we specify it separately. *[\[\~\#\^\&\*\(\)\{\}\|\;\<\>\?\'\ \ ]*|*]*|"") my_arg="\"$my_arg\"" ;; esac func_quote_for_expand_result="$my_arg" } # func_show_eval cmd [fail_exp] # Unless opt_silent is true, then output CMD. Then, if opt_dryrun is # not true, evaluate CMD. If the evaluation of CMD fails, and FAIL_EXP # is given, then evaluate it. func_show_eval () { my_cmd="$1" my_fail_exp="${2-:}" ${opt_silent-false} || { func_quote_for_expand "$my_cmd" eval "func_echo $func_quote_for_expand_result" } if ${opt_dry_run-false}; then :; else eval "$my_cmd" my_status=$? if test "$my_status" -eq 0; then :; else eval "(exit $my_status); $my_fail_exp" fi fi } # func_show_eval_locale cmd [fail_exp] # Unless opt_silent is true, then output CMD. Then, if opt_dryrun is # not true, evaluate CMD. If the evaluation of CMD fails, and FAIL_EXP # is given, then evaluate it. Use the saved locale for evaluation. func_show_eval_locale () { my_cmd="$1" my_fail_exp="${2-:}" ${opt_silent-false} || { func_quote_for_expand "$my_cmd" eval "func_echo $func_quote_for_expand_result" } if ${opt_dry_run-false}; then :; else eval "$lt_user_locale $my_cmd" my_status=$? eval "$lt_safe_locale" if test "$my_status" -eq 0; then :; else eval "(exit $my_status); $my_fail_exp" fi fi } # func_tr_sh # Turn $1 into a string suitable for a shell variable name. # Result is stored in $func_tr_sh_result. All characters # not in the set a-zA-Z0-9_ are replaced with '_'. Further, # if $1 begins with a digit, a '_' is prepended as well. func_tr_sh () { case $1 in [0-9]* | *[!a-zA-Z0-9_]*) func_tr_sh_result=`$ECHO "$1" | $SED 's/^\([0-9]\)/_\1/; s/[^a-zA-Z0-9_]/_/g'` ;; * ) func_tr_sh_result=$1 ;; esac } # func_version # Echo version message to standard output and exit. func_version () { $opt_debug $SED -n '/(C)/!b go :more /\./!{ N s/\n# / / b more } :go /^# '$PROGRAM' (GNU /,/# warranty; / { s/^# // s/^# *$// s/\((C)\)[ 0-9,-]*\( [1-9][0-9]*\)/\1\2/ p }' < "$progpath" exit $? } # func_usage # Echo short help message to standard output and exit. func_usage () { $opt_debug $SED -n '/^# Usage:/,/^# *.*--help/ { s/^# // s/^# *$// s/\$progname/'$progname'/ p }' < "$progpath" echo $ECHO "run \`$progname --help | more' for full usage" exit $? } # func_help [NOEXIT] # Echo long help message to standard output and exit, # unless 'noexit' is passed as argument. func_help () { $opt_debug $SED -n '/^# Usage:/,/# Report bugs to/ { :print s/^# // s/^# *$// s*\$progname*'$progname'* s*\$host*'"$host"'* s*\$SHELL*'"$SHELL"'* s*\$LTCC*'"$LTCC"'* s*\$LTCFLAGS*'"$LTCFLAGS"'* s*\$LD*'"$LD"'* s/\$with_gnu_ld/'"$with_gnu_ld"'/ s/\$automake_version/'"`(${AUTOMAKE-automake} --version) 2>/dev/null |$SED 1q`"'/ s/\$autoconf_version/'"`(${AUTOCONF-autoconf} --version) 2>/dev/null |$SED 1q`"'/ p d } /^# .* home page:/b print /^# General help using/b print ' < "$progpath" ret=$? if test -z "$1"; then exit $ret fi } # func_missing_arg argname # Echo program name prefixed message to standard error and set global # exit_cmd. func_missing_arg () { $opt_debug func_error "missing argument for $1." exit_cmd=exit } # func_split_short_opt shortopt # Set func_split_short_opt_name and func_split_short_opt_arg shell # variables after splitting SHORTOPT after the 2nd character. func_split_short_opt () { my_sed_short_opt='1s/^\(..\).*$/\1/;q' my_sed_short_rest='1s/^..\(.*\)$/\1/;q' func_split_short_opt_name=`$ECHO "$1" | $SED "$my_sed_short_opt"` func_split_short_opt_arg=`$ECHO "$1" | $SED "$my_sed_short_rest"` } # func_split_short_opt may be replaced by extended shell implementation # func_split_long_opt longopt # Set func_split_long_opt_name and func_split_long_opt_arg shell # variables after splitting LONGOPT at the `=' sign. func_split_long_opt () { my_sed_long_opt='1s/^\(--[^=]*\)=.*/\1/;q' my_sed_long_arg='1s/^--[^=]*=//' func_split_long_opt_name=`$ECHO "$1" | $SED "$my_sed_long_opt"` func_split_long_opt_arg=`$ECHO "$1" | $SED "$my_sed_long_arg"` } # func_split_long_opt may be replaced by extended shell implementation exit_cmd=: magic="%%%MAGIC variable%%%" magic_exe="%%%MAGIC EXE variable%%%" # Global variables. nonopt= preserve_args= lo2o="s/\\.lo\$/.${objext}/" o2lo="s/\\.${objext}\$/.lo/" extracted_archives= extracted_serial=0 # If this variable is set in any of the actions, the command in it # will be execed at the end. This prevents here-documents from being # left over by shells. exec_cmd= # func_append var value # Append VALUE to the end of shell variable VAR. func_append () { eval "${1}=\$${1}\${2}" } # func_append may be replaced by extended shell implementation # func_append_quoted var value # Quote VALUE and append to the end of shell variable VAR, separated # by a space. func_append_quoted () { func_quote_for_eval "${2}" eval "${1}=\$${1}\\ \$func_quote_for_eval_result" } # func_append_quoted may be replaced by extended shell implementation # func_arith arithmetic-term... func_arith () { func_arith_result=`expr "${@}"` } # func_arith may be replaced by extended shell implementation # func_len string # STRING may not start with a hyphen. func_len () { func_len_result=`expr "${1}" : ".*" 2>/dev/null || echo $max_cmd_len` } # func_len may be replaced by extended shell implementation # func_lo2o object func_lo2o () { func_lo2o_result=`$ECHO "${1}" | $SED "$lo2o"` } # func_lo2o may be replaced by extended shell implementation # func_xform libobj-or-source func_xform () { func_xform_result=`$ECHO "${1}" | $SED 's/\.[^.]*$/.lo/'` } # func_xform may be replaced by extended shell implementation # func_fatal_configuration arg... # Echo program name prefixed message to standard error, followed by # a configuration failure hint, and exit. func_fatal_configuration () { func_error ${1+"$@"} func_error "See the $PACKAGE documentation for more information." func_fatal_error "Fatal configuration error." } # func_config # Display the configuration for all the tags in this script. func_config () { re_begincf='^# ### BEGIN LIBTOOL' re_endcf='^# ### END LIBTOOL' # Default configuration. $SED "1,/$re_begincf CONFIG/d;/$re_endcf CONFIG/,\$d" < "$progpath" # Now print the configurations for the tags. for tagname in $taglist; do $SED -n "/$re_begincf TAG CONFIG: $tagname\$/,/$re_endcf TAG CONFIG: $tagname\$/p" < "$progpath" done exit $? } # func_features # Display the features supported by this script. func_features () { echo "host: $host" if test "$build_libtool_libs" = yes; then echo "enable shared libraries" else echo "disable shared libraries" fi if test "$build_old_libs" = yes; then echo "enable static libraries" else echo "disable static libraries" fi exit $? } # func_enable_tag tagname # Verify that TAGNAME is valid, and either flag an error and exit, or # enable the TAGNAME tag. We also add TAGNAME to the global $taglist # variable here. func_enable_tag () { # Global variable: tagname="$1" re_begincf="^# ### BEGIN LIBTOOL TAG CONFIG: $tagname\$" re_endcf="^# ### END LIBTOOL TAG CONFIG: $tagname\$" sed_extractcf="/$re_begincf/,/$re_endcf/p" # Validate tagname. case $tagname in *[!-_A-Za-z0-9,/]*) func_fatal_error "invalid tag name: $tagname" ;; esac # Don't test for the "default" C tag, as we know it's # there but not specially marked. case $tagname in CC) ;; *) if $GREP "$re_begincf" "$progpath" >/dev/null 2>&1; then taglist="$taglist $tagname" # Evaluate the configuration. Be careful to quote the path # and the sed script, to avoid splitting on whitespace, but # also don't use non-portable quotes within backquotes within # quotes we have to do it in 2 steps: extractedcf=`$SED -n -e "$sed_extractcf" < "$progpath"` eval "$extractedcf" else func_error "ignoring unknown tag $tagname" fi ;; esac } # func_check_version_match # Ensure that we are using m4 macros, and libtool script from the same # release of libtool. func_check_version_match () { if test "$package_revision" != "$macro_revision"; then if test "$VERSION" != "$macro_version"; then if test -z "$macro_version"; then cat >&2 <<_LT_EOF $progname: Version mismatch error. This is $PACKAGE $VERSION, but the $progname: definition of this LT_INIT comes from an older release. $progname: You should recreate aclocal.m4 with macros from $PACKAGE $VERSION $progname: and run autoconf again. _LT_EOF else cat >&2 <<_LT_EOF $progname: Version mismatch error. This is $PACKAGE $VERSION, but the $progname: definition of this LT_INIT comes from $PACKAGE $macro_version. $progname: You should recreate aclocal.m4 with macros from $PACKAGE $VERSION $progname: and run autoconf again. _LT_EOF fi else cat >&2 <<_LT_EOF $progname: Version mismatch error. This is $PACKAGE $VERSION, revision $package_revision, $progname: but the definition of this LT_INIT comes from revision $macro_revision. $progname: You should recreate aclocal.m4 with macros from revision $package_revision $progname: of $PACKAGE $VERSION and run autoconf again. _LT_EOF fi exit $EXIT_MISMATCH fi } # Shorthand for --mode=foo, only valid as the first argument case $1 in clean|clea|cle|cl) shift; set dummy --mode clean ${1+"$@"}; shift ;; compile|compil|compi|comp|com|co|c) shift; set dummy --mode compile ${1+"$@"}; shift ;; execute|execut|execu|exec|exe|ex|e) shift; set dummy --mode execute ${1+"$@"}; shift ;; finish|finis|fini|fin|fi|f) shift; set dummy --mode finish ${1+"$@"}; shift ;; install|instal|insta|inst|ins|in|i) shift; set dummy --mode install ${1+"$@"}; shift ;; link|lin|li|l) shift; set dummy --mode link ${1+"$@"}; shift ;; uninstall|uninstal|uninsta|uninst|unins|unin|uni|un|u) shift; set dummy --mode uninstall ${1+"$@"}; shift ;; esac # Option defaults: opt_debug=: opt_dry_run=false opt_config=false opt_preserve_dup_deps=false opt_features=false opt_finish=false opt_help=false opt_help_all=false opt_silent=: opt_warning=: opt_verbose=: opt_silent=false opt_verbose=false # Parse options once, thoroughly. This comes as soon as possible in the # script to make things like `--version' happen as quickly as we can. { # this just eases exit handling while test $# -gt 0; do opt="$1" shift case $opt in --debug|-x) opt_debug='set -x' func_echo "enabling shell trace mode" $opt_debug ;; --dry-run|--dryrun|-n) opt_dry_run=: ;; --config) opt_config=: func_config ;; --dlopen|-dlopen) optarg="$1" opt_dlopen="${opt_dlopen+$opt_dlopen }$optarg" shift ;; --preserve-dup-deps) opt_preserve_dup_deps=: ;; --features) opt_features=: func_features ;; --finish) opt_finish=: set dummy --mode finish ${1+"$@"}; shift ;; --help) opt_help=: ;; --help-all) opt_help_all=: opt_help=': help-all' ;; --mode) test $# = 0 && func_missing_arg $opt && break optarg="$1" opt_mode="$optarg" case $optarg in # Valid mode arguments: clean|compile|execute|finish|install|link|relink|uninstall) ;; # Catch anything else as an error *) func_error "invalid argument for $opt" exit_cmd=exit break ;; esac shift ;; --no-silent|--no-quiet) opt_silent=false func_append preserve_args " $opt" ;; --no-warning|--no-warn) opt_warning=false func_append preserve_args " $opt" ;; --no-verbose) opt_verbose=false func_append preserve_args " $opt" ;; --silent|--quiet) opt_silent=: func_append preserve_args " $opt" opt_verbose=false ;; --verbose|-v) opt_verbose=: func_append preserve_args " $opt" opt_silent=false ;; --tag) test $# = 0 && func_missing_arg $opt && break optarg="$1" opt_tag="$optarg" func_append preserve_args " $opt $optarg" func_enable_tag "$optarg" shift ;; -\?|-h) func_usage ;; --help) func_help ;; --version) func_version ;; # Separate optargs to long options: --*=*) func_split_long_opt "$opt" set dummy "$func_split_long_opt_name" "$func_split_long_opt_arg" ${1+"$@"} shift ;; # Separate non-argument short options: -\?*|-h*|-n*|-v*) func_split_short_opt "$opt" set dummy "$func_split_short_opt_name" "-$func_split_short_opt_arg" ${1+"$@"} shift ;; --) break ;; -*) func_fatal_help "unrecognized option \`$opt'" ;; *) set dummy "$opt" ${1+"$@"}; shift; break ;; esac done # Validate options: # save first non-option argument if test "$#" -gt 0; then nonopt="$opt" shift fi # preserve --debug test "$opt_debug" = : || func_append preserve_args " --debug" case $host in *cygwin* | *mingw* | *pw32* | *cegcc*) # don't eliminate duplications in $postdeps and $predeps opt_duplicate_compiler_generated_deps=: ;; *) opt_duplicate_compiler_generated_deps=$opt_preserve_dup_deps ;; esac $opt_help || { # Sanity checks first: func_check_version_match if test "$build_libtool_libs" != yes && test "$build_old_libs" != yes; then func_fatal_configuration "not configured to build any kind of library" fi # Darwin sucks eval std_shrext=\"$shrext_cmds\" # Only execute mode is allowed to have -dlopen flags. if test -n "$opt_dlopen" && test "$opt_mode" != execute; then func_error "unrecognized option \`-dlopen'" $ECHO "$help" 1>&2 exit $EXIT_FAILURE fi # Change the help message to a mode-specific one. generic_help="$help" help="Try \`$progname --help --mode=$opt_mode' for more information." } # Bail if the options were screwed $exit_cmd $EXIT_FAILURE } ## ----------- ## ## Main. ## ## ----------- ## # func_lalib_p file # True iff FILE is a libtool `.la' library or `.lo' object file. # This function is only a basic sanity check; it will hardly flush out # determined imposters. func_lalib_p () { test -f "$1" && $SED -e 4q "$1" 2>/dev/null \ | $GREP "^# Generated by .*$PACKAGE" > /dev/null 2>&1 } # func_lalib_unsafe_p file # True iff FILE is a libtool `.la' library or `.lo' object file. # This function implements the same check as func_lalib_p without # resorting to external programs. To this end, it redirects stdin and # closes it afterwards, without saving the original file descriptor. # As a safety measure, use it only where a negative result would be # fatal anyway. Works if `file' does not exist. func_lalib_unsafe_p () { lalib_p=no if test -f "$1" && test -r "$1" && exec 5<&0 <"$1"; then for lalib_p_l in 1 2 3 4 do read lalib_p_line case "$lalib_p_line" in \#\ Generated\ by\ *$PACKAGE* ) lalib_p=yes; break;; esac done exec 0<&5 5<&- fi test "$lalib_p" = yes } # func_ltwrapper_script_p file # True iff FILE is a libtool wrapper script # This function is only a basic sanity check; it will hardly flush out # determined imposters. func_ltwrapper_script_p () { func_lalib_p "$1" } # func_ltwrapper_executable_p file # True iff FILE is a libtool wrapper executable # This function is only a basic sanity check; it will hardly flush out # determined imposters. func_ltwrapper_executable_p () { func_ltwrapper_exec_suffix= case $1 in *.exe) ;; *) func_ltwrapper_exec_suffix=.exe ;; esac $GREP "$magic_exe" "$1$func_ltwrapper_exec_suffix" >/dev/null 2>&1 } # func_ltwrapper_scriptname file # Assumes file is an ltwrapper_executable # uses $file to determine the appropriate filename for a # temporary ltwrapper_script. func_ltwrapper_scriptname () { func_dirname_and_basename "$1" "" "." func_stripname '' '.exe' "$func_basename_result" func_ltwrapper_scriptname_result="$func_dirname_result/$objdir/${func_stripname_result}_ltshwrapper" } # func_ltwrapper_p file # True iff FILE is a libtool wrapper script or wrapper executable # This function is only a basic sanity check; it will hardly flush out # determined imposters. func_ltwrapper_p () { func_ltwrapper_script_p "$1" || func_ltwrapper_executable_p "$1" } # func_execute_cmds commands fail_cmd # Execute tilde-delimited COMMANDS. # If FAIL_CMD is given, eval that upon failure. # FAIL_CMD may read-access the current command in variable CMD! func_execute_cmds () { $opt_debug save_ifs=$IFS; IFS='~' for cmd in $1; do IFS=$save_ifs eval cmd=\"$cmd\" func_show_eval "$cmd" "${2-:}" done IFS=$save_ifs } # func_source file # Source FILE, adding directory component if necessary. # Note that it is not necessary on cygwin/mingw to append a dot to # FILE even if both FILE and FILE.exe exist: automatic-append-.exe # behavior happens only for exec(3), not for open(2)! Also, sourcing # `FILE.' does not work on cygwin managed mounts. func_source () { $opt_debug case $1 in */* | *\\*) . "$1" ;; *) . "./$1" ;; esac } # func_resolve_sysroot PATH # Replace a leading = in PATH with a sysroot. Store the result into # func_resolve_sysroot_result func_resolve_sysroot () { func_resolve_sysroot_result=$1 case $func_resolve_sysroot_result in =*) func_stripname '=' '' "$func_resolve_sysroot_result" func_resolve_sysroot_result=$lt_sysroot$func_stripname_result ;; esac } # func_replace_sysroot PATH # If PATH begins with the sysroot, replace it with = and # store the result into func_replace_sysroot_result. func_replace_sysroot () { case "$lt_sysroot:$1" in ?*:"$lt_sysroot"*) func_stripname "$lt_sysroot" '' "$1" func_replace_sysroot_result="=$func_stripname_result" ;; *) # Including no sysroot. func_replace_sysroot_result=$1 ;; esac } # func_infer_tag arg # Infer tagged configuration to use if any are available and # if one wasn't chosen via the "--tag" command line option. # Only attempt this if the compiler in the base compile # command doesn't match the default compiler. # arg is usually of the form 'gcc ...' func_infer_tag () { $opt_debug if test -n "$available_tags" && test -z "$tagname"; then CC_quoted= for arg in $CC; do func_append_quoted CC_quoted "$arg" done CC_expanded=`func_echo_all $CC` CC_quoted_expanded=`func_echo_all $CC_quoted` case $@ in # Blanks in the command may have been stripped by the calling shell, # but not from the CC environment variable when configure was run. " $CC "* | "$CC "* | " $CC_expanded "* | "$CC_expanded "* | \ " $CC_quoted"* | "$CC_quoted "* | " $CC_quoted_expanded "* | "$CC_quoted_expanded "*) ;; # Blanks at the start of $base_compile will cause this to fail # if we don't check for them as well. *) for z in $available_tags; do if $GREP "^# ### BEGIN LIBTOOL TAG CONFIG: $z$" < "$progpath" > /dev/null; then # Evaluate the configuration. eval "`${SED} -n -e '/^# ### BEGIN LIBTOOL TAG CONFIG: '$z'$/,/^# ### END LIBTOOL TAG CONFIG: '$z'$/p' < $progpath`" CC_quoted= for arg in $CC; do # Double-quote args containing other shell metacharacters. func_append_quoted CC_quoted "$arg" done CC_expanded=`func_echo_all $CC` CC_quoted_expanded=`func_echo_all $CC_quoted` case "$@ " in " $CC "* | "$CC "* | " $CC_expanded "* | "$CC_expanded "* | \ " $CC_quoted"* | "$CC_quoted "* | " $CC_quoted_expanded "* | "$CC_quoted_expanded "*) # The compiler in the base compile command matches # the one in the tagged configuration. # Assume this is the tagged configuration we want. tagname=$z break ;; esac fi done # If $tagname still isn't set, then no tagged configuration # was found and let the user know that the "--tag" command # line option must be used. if test -z "$tagname"; then func_echo "unable to infer tagged configuration" func_fatal_error "specify a tag with \`--tag'" # else # func_verbose "using $tagname tagged configuration" fi ;; esac fi } # func_write_libtool_object output_name pic_name nonpic_name # Create a libtool object file (analogous to a ".la" file), # but don't create it if we're doing a dry run. func_write_libtool_object () { write_libobj=${1} if test "$build_libtool_libs" = yes; then write_lobj=\'${2}\' else write_lobj=none fi if test "$build_old_libs" = yes; then write_oldobj=\'${3}\' else write_oldobj=none fi $opt_dry_run || { cat >${write_libobj}T </dev/null` if test "$?" -eq 0 && test -n "${func_convert_core_file_wine_to_w32_tmp}"; then func_convert_core_file_wine_to_w32_result=`$ECHO "$func_convert_core_file_wine_to_w32_tmp" | $SED -e "$lt_sed_naive_backslashify"` else func_convert_core_file_wine_to_w32_result= fi fi } # end: func_convert_core_file_wine_to_w32 # func_convert_core_path_wine_to_w32 ARG # Helper function used by path conversion functions when $build is *nix, and # $host is mingw, cygwin, or some other w32 environment. Relies on a correctly # configured wine environment available, with the winepath program in $build's # $PATH. Assumes ARG has no leading or trailing path separator characters. # # ARG is path to be converted from $build format to win32. # Result is available in $func_convert_core_path_wine_to_w32_result. # Unconvertible file (directory) names in ARG are skipped; if no directory names # are convertible, then the result may be empty. func_convert_core_path_wine_to_w32 () { $opt_debug # unfortunately, winepath doesn't convert paths, only file names func_convert_core_path_wine_to_w32_result="" if test -n "$1"; then oldIFS=$IFS IFS=: for func_convert_core_path_wine_to_w32_f in $1; do IFS=$oldIFS func_convert_core_file_wine_to_w32 "$func_convert_core_path_wine_to_w32_f" if test -n "$func_convert_core_file_wine_to_w32_result" ; then if test -z "$func_convert_core_path_wine_to_w32_result"; then func_convert_core_path_wine_to_w32_result="$func_convert_core_file_wine_to_w32_result" else func_append func_convert_core_path_wine_to_w32_result ";$func_convert_core_file_wine_to_w32_result" fi fi done IFS=$oldIFS fi } # end: func_convert_core_path_wine_to_w32 # func_cygpath ARGS... # Wrapper around calling the cygpath program via LT_CYGPATH. This is used when # when (1) $build is *nix and Cygwin is hosted via a wine environment; or (2) # $build is MSYS and $host is Cygwin, or (3) $build is Cygwin. In case (1) or # (2), returns the Cygwin file name or path in func_cygpath_result (input # file name or path is assumed to be in w32 format, as previously converted # from $build's *nix or MSYS format). In case (3), returns the w32 file name # or path in func_cygpath_result (input file name or path is assumed to be in # Cygwin format). Returns an empty string on error. # # ARGS are passed to cygpath, with the last one being the file name or path to # be converted. # # Specify the absolute *nix (or w32) name to cygpath in the LT_CYGPATH # environment variable; do not put it in $PATH. func_cygpath () { $opt_debug if test -n "$LT_CYGPATH" && test -f "$LT_CYGPATH"; then func_cygpath_result=`$LT_CYGPATH "$@" 2>/dev/null` if test "$?" -ne 0; then # on failure, ensure result is empty func_cygpath_result= fi else func_cygpath_result= func_error "LT_CYGPATH is empty or specifies non-existent file: \`$LT_CYGPATH'" fi } #end: func_cygpath # func_convert_core_msys_to_w32 ARG # Convert file name or path ARG from MSYS format to w32 format. Return # result in func_convert_core_msys_to_w32_result. func_convert_core_msys_to_w32 () { $opt_debug # awkward: cmd appends spaces to result func_convert_core_msys_to_w32_result=`( cmd //c echo "$1" ) 2>/dev/null | $SED -e 's/[ ]*$//' -e "$lt_sed_naive_backslashify"` } #end: func_convert_core_msys_to_w32 # func_convert_file_check ARG1 ARG2 # Verify that ARG1 (a file name in $build format) was converted to $host # format in ARG2. Otherwise, emit an error message, but continue (resetting # func_to_host_file_result to ARG1). func_convert_file_check () { $opt_debug if test -z "$2" && test -n "$1" ; then func_error "Could not determine host file name corresponding to" func_error " \`$1'" func_error "Continuing, but uninstalled executables may not work." # Fallback: func_to_host_file_result="$1" fi } # end func_convert_file_check # func_convert_path_check FROM_PATHSEP TO_PATHSEP FROM_PATH TO_PATH # Verify that FROM_PATH (a path in $build format) was converted to $host # format in TO_PATH. Otherwise, emit an error message, but continue, resetting # func_to_host_file_result to a simplistic fallback value (see below). func_convert_path_check () { $opt_debug if test -z "$4" && test -n "$3"; then func_error "Could not determine the host path corresponding to" func_error " \`$3'" func_error "Continuing, but uninstalled executables may not work." # Fallback. This is a deliberately simplistic "conversion" and # should not be "improved". See libtool.info. if test "x$1" != "x$2"; then lt_replace_pathsep_chars="s|$1|$2|g" func_to_host_path_result=`echo "$3" | $SED -e "$lt_replace_pathsep_chars"` else func_to_host_path_result="$3" fi fi } # end func_convert_path_check # func_convert_path_front_back_pathsep FRONTPAT BACKPAT REPL ORIG # Modifies func_to_host_path_result by prepending REPL if ORIG matches FRONTPAT # and appending REPL if ORIG matches BACKPAT. func_convert_path_front_back_pathsep () { $opt_debug case $4 in $1 ) func_to_host_path_result="$3$func_to_host_path_result" ;; esac case $4 in $2 ) func_append func_to_host_path_result "$3" ;; esac } # end func_convert_path_front_back_pathsep ################################################## # $build to $host FILE NAME CONVERSION FUNCTIONS # ################################################## # invoked via `$to_host_file_cmd ARG' # # In each case, ARG is the path to be converted from $build to $host format. # Result will be available in $func_to_host_file_result. # func_to_host_file ARG # Converts the file name ARG from $build format to $host format. Return result # in func_to_host_file_result. func_to_host_file () { $opt_debug $to_host_file_cmd "$1" } # end func_to_host_file # func_to_tool_file ARG LAZY # converts the file name ARG from $build format to toolchain format. Return # result in func_to_tool_file_result. If the conversion in use is listed # in (the comma separated) LAZY, no conversion takes place. func_to_tool_file () { $opt_debug case ,$2, in *,"$to_tool_file_cmd",*) func_to_tool_file_result=$1 ;; *) $to_tool_file_cmd "$1" func_to_tool_file_result=$func_to_host_file_result ;; esac } # end func_to_tool_file # func_convert_file_noop ARG # Copy ARG to func_to_host_file_result. func_convert_file_noop () { func_to_host_file_result="$1" } # end func_convert_file_noop # func_convert_file_msys_to_w32 ARG # Convert file name ARG from (mingw) MSYS to (mingw) w32 format; automatic # conversion to w32 is not available inside the cwrapper. Returns result in # func_to_host_file_result. func_convert_file_msys_to_w32 () { $opt_debug func_to_host_file_result="$1" if test -n "$1"; then func_convert_core_msys_to_w32 "$1" func_to_host_file_result="$func_convert_core_msys_to_w32_result" fi func_convert_file_check "$1" "$func_to_host_file_result" } # end func_convert_file_msys_to_w32 # func_convert_file_cygwin_to_w32 ARG # Convert file name ARG from Cygwin to w32 format. Returns result in # func_to_host_file_result. func_convert_file_cygwin_to_w32 () { $opt_debug func_to_host_file_result="$1" if test -n "$1"; then # because $build is cygwin, we call "the" cygpath in $PATH; no need to use # LT_CYGPATH in this case. func_to_host_file_result=`cygpath -m "$1"` fi func_convert_file_check "$1" "$func_to_host_file_result" } # end func_convert_file_cygwin_to_w32 # func_convert_file_nix_to_w32 ARG # Convert file name ARG from *nix to w32 format. Requires a wine environment # and a working winepath. Returns result in func_to_host_file_result. func_convert_file_nix_to_w32 () { $opt_debug func_to_host_file_result="$1" if test -n "$1"; then func_convert_core_file_wine_to_w32 "$1" func_to_host_file_result="$func_convert_core_file_wine_to_w32_result" fi func_convert_file_check "$1" "$func_to_host_file_result" } # end func_convert_file_nix_to_w32 # func_convert_file_msys_to_cygwin ARG # Convert file name ARG from MSYS to Cygwin format. Requires LT_CYGPATH set. # Returns result in func_to_host_file_result. func_convert_file_msys_to_cygwin () { $opt_debug func_to_host_file_result="$1" if test -n "$1"; then func_convert_core_msys_to_w32 "$1" func_cygpath -u "$func_convert_core_msys_to_w32_result" func_to_host_file_result="$func_cygpath_result" fi func_convert_file_check "$1" "$func_to_host_file_result" } # end func_convert_file_msys_to_cygwin # func_convert_file_nix_to_cygwin ARG # Convert file name ARG from *nix to Cygwin format. Requires Cygwin installed # in a wine environment, working winepath, and LT_CYGPATH set. Returns result # in func_to_host_file_result. func_convert_file_nix_to_cygwin () { $opt_debug func_to_host_file_result="$1" if test -n "$1"; then # convert from *nix to w32, then use cygpath to convert from w32 to cygwin. func_convert_core_file_wine_to_w32 "$1" func_cygpath -u "$func_convert_core_file_wine_to_w32_result" func_to_host_file_result="$func_cygpath_result" fi func_convert_file_check "$1" "$func_to_host_file_result" } # end func_convert_file_nix_to_cygwin ############################################# # $build to $host PATH CONVERSION FUNCTIONS # ############################################# # invoked via `$to_host_path_cmd ARG' # # In each case, ARG is the path to be converted from $build to $host format. # The result will be available in $func_to_host_path_result. # # Path separators are also converted from $build format to $host format. If # ARG begins or ends with a path separator character, it is preserved (but # converted to $host format) on output. # # All path conversion functions are named using the following convention: # file name conversion function : func_convert_file_X_to_Y () # path conversion function : func_convert_path_X_to_Y () # where, for any given $build/$host combination the 'X_to_Y' value is the # same. If conversion functions are added for new $build/$host combinations, # the two new functions must follow this pattern, or func_init_to_host_path_cmd # will break. # func_init_to_host_path_cmd # Ensures that function "pointer" variable $to_host_path_cmd is set to the # appropriate value, based on the value of $to_host_file_cmd. to_host_path_cmd= func_init_to_host_path_cmd () { $opt_debug if test -z "$to_host_path_cmd"; then func_stripname 'func_convert_file_' '' "$to_host_file_cmd" to_host_path_cmd="func_convert_path_${func_stripname_result}" fi } # func_to_host_path ARG # Converts the path ARG from $build format to $host format. Return result # in func_to_host_path_result. func_to_host_path () { $opt_debug func_init_to_host_path_cmd $to_host_path_cmd "$1" } # end func_to_host_path # func_convert_path_noop ARG # Copy ARG to func_to_host_path_result. func_convert_path_noop () { func_to_host_path_result="$1" } # end func_convert_path_noop # func_convert_path_msys_to_w32 ARG # Convert path ARG from (mingw) MSYS to (mingw) w32 format; automatic # conversion to w32 is not available inside the cwrapper. Returns result in # func_to_host_path_result. func_convert_path_msys_to_w32 () { $opt_debug func_to_host_path_result="$1" if test -n "$1"; then # Remove leading and trailing path separator characters from ARG. MSYS # behavior is inconsistent here; cygpath turns them into '.;' and ';.'; # and winepath ignores them completely. func_stripname : : "$1" func_to_host_path_tmp1=$func_stripname_result func_convert_core_msys_to_w32 "$func_to_host_path_tmp1" func_to_host_path_result="$func_convert_core_msys_to_w32_result" func_convert_path_check : ";" \ "$func_to_host_path_tmp1" "$func_to_host_path_result" func_convert_path_front_back_pathsep ":*" "*:" ";" "$1" fi } # end func_convert_path_msys_to_w32 # func_convert_path_cygwin_to_w32 ARG # Convert path ARG from Cygwin to w32 format. Returns result in # func_to_host_file_result. func_convert_path_cygwin_to_w32 () { $opt_debug func_to_host_path_result="$1" if test -n "$1"; then # See func_convert_path_msys_to_w32: func_stripname : : "$1" func_to_host_path_tmp1=$func_stripname_result func_to_host_path_result=`cygpath -m -p "$func_to_host_path_tmp1"` func_convert_path_check : ";" \ "$func_to_host_path_tmp1" "$func_to_host_path_result" func_convert_path_front_back_pathsep ":*" "*:" ";" "$1" fi } # end func_convert_path_cygwin_to_w32 # func_convert_path_nix_to_w32 ARG # Convert path ARG from *nix to w32 format. Requires a wine environment and # a working winepath. Returns result in func_to_host_file_result. func_convert_path_nix_to_w32 () { $opt_debug func_to_host_path_result="$1" if test -n "$1"; then # See func_convert_path_msys_to_w32: func_stripname : : "$1" func_to_host_path_tmp1=$func_stripname_result func_convert_core_path_wine_to_w32 "$func_to_host_path_tmp1" func_to_host_path_result="$func_convert_core_path_wine_to_w32_result" func_convert_path_check : ";" \ "$func_to_host_path_tmp1" "$func_to_host_path_result" func_convert_path_front_back_pathsep ":*" "*:" ";" "$1" fi } # end func_convert_path_nix_to_w32 # func_convert_path_msys_to_cygwin ARG # Convert path ARG from MSYS to Cygwin format. Requires LT_CYGPATH set. # Returns result in func_to_host_file_result. func_convert_path_msys_to_cygwin () { $opt_debug func_to_host_path_result="$1" if test -n "$1"; then # See func_convert_path_msys_to_w32: func_stripname : : "$1" func_to_host_path_tmp1=$func_stripname_result func_convert_core_msys_to_w32 "$func_to_host_path_tmp1" func_cygpath -u -p "$func_convert_core_msys_to_w32_result" func_to_host_path_result="$func_cygpath_result" func_convert_path_check : : \ "$func_to_host_path_tmp1" "$func_to_host_path_result" func_convert_path_front_back_pathsep ":*" "*:" : "$1" fi } # end func_convert_path_msys_to_cygwin # func_convert_path_nix_to_cygwin ARG # Convert path ARG from *nix to Cygwin format. Requires Cygwin installed in a # a wine environment, working winepath, and LT_CYGPATH set. Returns result in # func_to_host_file_result. func_convert_path_nix_to_cygwin () { $opt_debug func_to_host_path_result="$1" if test -n "$1"; then # Remove leading and trailing path separator characters from # ARG. msys behavior is inconsistent here, cygpath turns them # into '.;' and ';.', and winepath ignores them completely. func_stripname : : "$1" func_to_host_path_tmp1=$func_stripname_result func_convert_core_path_wine_to_w32 "$func_to_host_path_tmp1" func_cygpath -u -p "$func_convert_core_path_wine_to_w32_result" func_to_host_path_result="$func_cygpath_result" func_convert_path_check : : \ "$func_to_host_path_tmp1" "$func_to_host_path_result" func_convert_path_front_back_pathsep ":*" "*:" : "$1" fi } # end func_convert_path_nix_to_cygwin # func_mode_compile arg... func_mode_compile () { $opt_debug # Get the compilation command and the source file. base_compile= srcfile="$nonopt" # always keep a non-empty value in "srcfile" suppress_opt=yes suppress_output= arg_mode=normal libobj= later= pie_flag= for arg do case $arg_mode in arg ) # do not "continue". Instead, add this to base_compile lastarg="$arg" arg_mode=normal ;; target ) libobj="$arg" arg_mode=normal continue ;; normal ) # Accept any command-line options. case $arg in -o) test -n "$libobj" && \ func_fatal_error "you cannot specify \`-o' more than once" arg_mode=target continue ;; -pie | -fpie | -fPIE) func_append pie_flag " $arg" continue ;; -shared | -static | -prefer-pic | -prefer-non-pic) func_append later " $arg" continue ;; -no-suppress) suppress_opt=no continue ;; -Xcompiler) arg_mode=arg # the next one goes into the "base_compile" arg list continue # The current "srcfile" will either be retained or ;; # replaced later. I would guess that would be a bug. -Wc,*) func_stripname '-Wc,' '' "$arg" args=$func_stripname_result lastarg= save_ifs="$IFS"; IFS=',' for arg in $args; do IFS="$save_ifs" func_append_quoted lastarg "$arg" done IFS="$save_ifs" func_stripname ' ' '' "$lastarg" lastarg=$func_stripname_result # Add the arguments to base_compile. func_append base_compile " $lastarg" continue ;; *) # Accept the current argument as the source file. # The previous "srcfile" becomes the current argument. # lastarg="$srcfile" srcfile="$arg" ;; esac # case $arg ;; esac # case $arg_mode # Aesthetically quote the previous argument. func_append_quoted base_compile "$lastarg" done # for arg case $arg_mode in arg) func_fatal_error "you must specify an argument for -Xcompile" ;; target) func_fatal_error "you must specify a target with \`-o'" ;; *) # Get the name of the library object. test -z "$libobj" && { func_basename "$srcfile" libobj="$func_basename_result" } ;; esac # Recognize several different file suffixes. # If the user specifies -o file.o, it is replaced with file.lo case $libobj in *.[cCFSifmso] | \ *.ada | *.adb | *.ads | *.asm | \ *.c++ | *.cc | *.ii | *.class | *.cpp | *.cxx | \ *.[fF][09]? | *.for | *.java | *.go | *.obj | *.sx | *.cu | *.cup) func_xform "$libobj" libobj=$func_xform_result ;; esac case $libobj in *.lo) func_lo2o "$libobj"; obj=$func_lo2o_result ;; *) func_fatal_error "cannot determine name of library object from \`$libobj'" ;; esac func_infer_tag $base_compile for arg in $later; do case $arg in -shared) test "$build_libtool_libs" != yes && \ func_fatal_configuration "can not build a shared library" build_old_libs=no continue ;; -static) build_libtool_libs=no build_old_libs=yes continue ;; -prefer-pic) pic_mode=yes continue ;; -prefer-non-pic) pic_mode=no continue ;; esac done func_quote_for_eval "$libobj" test "X$libobj" != "X$func_quote_for_eval_result" \ && $ECHO "X$libobj" | $GREP '[]~#^*{};<>?"'"'"' &()|`$[]' \ && func_warning "libobj name \`$libobj' may not contain shell special characters." func_dirname_and_basename "$obj" "/" "" objname="$func_basename_result" xdir="$func_dirname_result" lobj=${xdir}$objdir/$objname test -z "$base_compile" && \ func_fatal_help "you must specify a compilation command" # Delete any leftover library objects. if test "$build_old_libs" = yes; then removelist="$obj $lobj $libobj ${libobj}T" else removelist="$lobj $libobj ${libobj}T" fi # On Cygwin there's no "real" PIC flag so we must build both object types case $host_os in cygwin* | mingw* | pw32* | os2* | cegcc*) pic_mode=default ;; esac if test "$pic_mode" = no && test "$deplibs_check_method" != pass_all; then # non-PIC code in shared libraries is not supported pic_mode=default fi # Calculate the filename of the output object if compiler does # not support -o with -c if test "$compiler_c_o" = no; then output_obj=`$ECHO "$srcfile" | $SED 's%^.*/%%; s%\.[^.]*$%%'`.${objext} lockfile="$output_obj.lock" else output_obj= need_locks=no lockfile= fi # Lock this critical section if it is needed # We use this script file to make the link, it avoids creating a new file if test "$need_locks" = yes; then until $opt_dry_run || ln "$progpath" "$lockfile" 2>/dev/null; do func_echo "Waiting for $lockfile to be removed" sleep 2 done elif test "$need_locks" = warn; then if test -f "$lockfile"; then $ECHO "\ *** ERROR, $lockfile exists and contains: `cat $lockfile 2>/dev/null` This indicates that another process is trying to use the same temporary object file, and libtool could not work around it because your compiler does not support \`-c' and \`-o' together. If you repeat this compilation, it may succeed, by chance, but you had better avoid parallel builds (make -j) in this platform, or get a better compiler." $opt_dry_run || $RM $removelist exit $EXIT_FAILURE fi func_append removelist " $output_obj" $ECHO "$srcfile" > "$lockfile" fi $opt_dry_run || $RM $removelist func_append removelist " $lockfile" trap '$opt_dry_run || $RM $removelist; exit $EXIT_FAILURE' 1 2 15 func_to_tool_file "$srcfile" func_convert_file_msys_to_w32 srcfile=$func_to_tool_file_result func_quote_for_eval "$srcfile" qsrcfile=$func_quote_for_eval_result # Only build a PIC object if we are building libtool libraries. if test "$build_libtool_libs" = yes; then # Without this assignment, base_compile gets emptied. fbsd_hideous_sh_bug=$base_compile if test "$pic_mode" != no; then command="$base_compile $qsrcfile $pic_flag" else # Don't build PIC code command="$base_compile $qsrcfile" fi func_mkdir_p "$xdir$objdir" if test -z "$output_obj"; then # Place PIC objects in $objdir func_append command " -o $lobj" fi func_show_eval_locale "$command" \ 'test -n "$output_obj" && $RM $removelist; exit $EXIT_FAILURE' if test "$need_locks" = warn && test "X`cat $lockfile 2>/dev/null`" != "X$srcfile"; then $ECHO "\ *** ERROR, $lockfile contains: `cat $lockfile 2>/dev/null` but it should contain: $srcfile This indicates that another process is trying to use the same temporary object file, and libtool could not work around it because your compiler does not support \`-c' and \`-o' together. If you repeat this compilation, it may succeed, by chance, but you had better avoid parallel builds (make -j) in this platform, or get a better compiler." $opt_dry_run || $RM $removelist exit $EXIT_FAILURE fi # Just move the object if needed, then go on to compile the next one if test -n "$output_obj" && test "X$output_obj" != "X$lobj"; then func_show_eval '$MV "$output_obj" "$lobj"' \ 'error=$?; $opt_dry_run || $RM $removelist; exit $error' fi # Allow error messages only from the first compilation. if test "$suppress_opt" = yes; then suppress_output=' >/dev/null 2>&1' fi fi # Only build a position-dependent object if we build old libraries. if test "$build_old_libs" = yes; then if test "$pic_mode" != yes; then # Don't build PIC code command="$base_compile $qsrcfile$pie_flag" else command="$base_compile $qsrcfile $pic_flag" fi if test "$compiler_c_o" = yes; then func_append command " -o $obj" fi # Suppress compiler output if we already did a PIC compilation. func_append command "$suppress_output" func_show_eval_locale "$command" \ '$opt_dry_run || $RM $removelist; exit $EXIT_FAILURE' if test "$need_locks" = warn && test "X`cat $lockfile 2>/dev/null`" != "X$srcfile"; then $ECHO "\ *** ERROR, $lockfile contains: `cat $lockfile 2>/dev/null` but it should contain: $srcfile This indicates that another process is trying to use the same temporary object file, and libtool could not work around it because your compiler does not support \`-c' and \`-o' together. If you repeat this compilation, it may succeed, by chance, but you had better avoid parallel builds (make -j) in this platform, or get a better compiler." $opt_dry_run || $RM $removelist exit $EXIT_FAILURE fi # Just move the object if needed if test -n "$output_obj" && test "X$output_obj" != "X$obj"; then func_show_eval '$MV "$output_obj" "$obj"' \ 'error=$?; $opt_dry_run || $RM $removelist; exit $error' fi fi $opt_dry_run || { func_write_libtool_object "$libobj" "$objdir/$objname" "$objname" # Unlock the critical section if it was locked if test "$need_locks" != no; then removelist=$lockfile $RM "$lockfile" fi } exit $EXIT_SUCCESS } $opt_help || { test "$opt_mode" = compile && func_mode_compile ${1+"$@"} } func_mode_help () { # We need to display help for each of the modes. case $opt_mode in "") # Generic help is extracted from the usage comments # at the start of this file. func_help ;; clean) $ECHO \ "Usage: $progname [OPTION]... --mode=clean RM [RM-OPTION]... FILE... Remove files from the build directory. RM is the name of the program to use to delete files associated with each FILE (typically \`/bin/rm'). RM-OPTIONS are options (such as \`-f') to be passed to RM. If FILE is a libtool library, object or program, all the files associated with it are deleted. Otherwise, only FILE itself is deleted using RM." ;; compile) $ECHO \ "Usage: $progname [OPTION]... --mode=compile COMPILE-COMMAND... SOURCEFILE Compile a source file into a libtool library object. This mode accepts the following additional options: -o OUTPUT-FILE set the output file name to OUTPUT-FILE -no-suppress do not suppress compiler output for multiple passes -prefer-pic try to build PIC objects only -prefer-non-pic try to build non-PIC objects only -shared do not build a \`.o' file suitable for static linking -static only build a \`.o' file suitable for static linking -Wc,FLAG pass FLAG directly to the compiler COMPILE-COMMAND is a command to be used in creating a \`standard' object file from the given SOURCEFILE. The output file name is determined by removing the directory component from SOURCEFILE, then substituting the C source code suffix \`.c' with the library object suffix, \`.lo'." ;; execute) $ECHO \ "Usage: $progname [OPTION]... --mode=execute COMMAND [ARGS]... Automatically set library path, then run a program. This mode accepts the following additional options: -dlopen FILE add the directory containing FILE to the library path This mode sets the library path environment variable according to \`-dlopen' flags. If any of the ARGS are libtool executable wrappers, then they are translated into their corresponding uninstalled binary, and any of their required library directories are added to the library path. Then, COMMAND is executed, with ARGS as arguments." ;; finish) $ECHO \ "Usage: $progname [OPTION]... --mode=finish [LIBDIR]... Complete the installation of libtool libraries. Each LIBDIR is a directory that contains libtool libraries. The commands that this mode executes may require superuser privileges. Use the \`--dry-run' option if you just want to see what would be executed." ;; install) $ECHO \ "Usage: $progname [OPTION]... --mode=install INSTALL-COMMAND... Install executables or libraries. INSTALL-COMMAND is the installation command. The first component should be either the \`install' or \`cp' program. The following components of INSTALL-COMMAND are treated specially: -inst-prefix-dir PREFIX-DIR Use PREFIX-DIR as a staging area for installation The rest of the components are interpreted as arguments to that command (only BSD-compatible install options are recognized)." ;; link) $ECHO \ "Usage: $progname [OPTION]... --mode=link LINK-COMMAND... Link object files or libraries together to form another library, or to create an executable program. LINK-COMMAND is a command using the C compiler that you would use to create a program from several object files. The following components of LINK-COMMAND are treated specially: -all-static do not do any dynamic linking at all -avoid-version do not add a version suffix if possible -bindir BINDIR specify path to binaries directory (for systems where libraries must be found in the PATH setting at runtime) -dlopen FILE \`-dlpreopen' FILE if it cannot be dlopened at runtime -dlpreopen FILE link in FILE and add its symbols to lt_preloaded_symbols -export-dynamic allow symbols from OUTPUT-FILE to be resolved with dlsym(3) -export-symbols SYMFILE try to export only the symbols listed in SYMFILE -export-symbols-regex REGEX try to export only the symbols matching REGEX -LLIBDIR search LIBDIR for required installed libraries -lNAME OUTPUT-FILE requires the installed library libNAME -module build a library that can dlopened -no-fast-install disable the fast-install mode -no-install link a not-installable executable -no-undefined declare that a library does not refer to external symbols -o OUTPUT-FILE create OUTPUT-FILE from the specified objects -objectlist FILE Use a list of object files found in FILE to specify objects -precious-files-regex REGEX don't remove output files matching REGEX -release RELEASE specify package release information -rpath LIBDIR the created library will eventually be installed in LIBDIR -R[ ]LIBDIR add LIBDIR to the runtime path of programs and libraries -shared only do dynamic linking of libtool libraries -shrext SUFFIX override the standard shared library file extension -static do not do any dynamic linking of uninstalled libtool libraries -static-libtool-libs do not do any dynamic linking of libtool libraries -version-info CURRENT[:REVISION[:AGE]] specify library version info [each variable defaults to 0] -weak LIBNAME declare that the target provides the LIBNAME interface -Wc,FLAG -Xcompiler FLAG pass linker-specific FLAG directly to the compiler -Wl,FLAG -Xlinker FLAG pass linker-specific FLAG directly to the linker -XCClinker FLAG pass link-specific FLAG to the compiler driver (CC) All other options (arguments beginning with \`-') are ignored. Every other argument is treated as a filename. Files ending in \`.la' are treated as uninstalled libtool libraries, other files are standard or library object files. If the OUTPUT-FILE ends in \`.la', then a libtool library is created, only library objects (\`.lo' files) may be specified, and \`-rpath' is required, except when creating a convenience library. If OUTPUT-FILE ends in \`.a' or \`.lib', then a standard library is created using \`ar' and \`ranlib', or on Windows using \`lib'. If OUTPUT-FILE ends in \`.lo' or \`.${objext}', then a reloadable object file is created, otherwise an executable program is created." ;; uninstall) $ECHO \ "Usage: $progname [OPTION]... --mode=uninstall RM [RM-OPTION]... FILE... Remove libraries from an installation directory. RM is the name of the program to use to delete files associated with each FILE (typically \`/bin/rm'). RM-OPTIONS are options (such as \`-f') to be passed to RM. If FILE is a libtool library, all the files associated with it are deleted. Otherwise, only FILE itself is deleted using RM." ;; *) func_fatal_help "invalid operation mode \`$opt_mode'" ;; esac echo $ECHO "Try \`$progname --help' for more information about other modes." } # Now that we've collected a possible --mode arg, show help if necessary if $opt_help; then if test "$opt_help" = :; then func_mode_help else { func_help noexit for opt_mode in compile link execute install finish uninstall clean; do func_mode_help done } | sed -n '1p; 2,$s/^Usage:/ or: /p' { func_help noexit for opt_mode in compile link execute install finish uninstall clean; do echo func_mode_help done } | sed '1d /^When reporting/,/^Report/{ H d } $x /information about other modes/d /more detailed .*MODE/d s/^Usage:.*--mode=\([^ ]*\) .*/Description of \1 mode:/' fi exit $? fi # func_mode_execute arg... func_mode_execute () { $opt_debug # The first argument is the command name. cmd="$nonopt" test -z "$cmd" && \ func_fatal_help "you must specify a COMMAND" # Handle -dlopen flags immediately. for file in $opt_dlopen; do test -f "$file" \ || func_fatal_help "\`$file' is not a file" dir= case $file in *.la) func_resolve_sysroot "$file" file=$func_resolve_sysroot_result # Check to see that this really is a libtool archive. func_lalib_unsafe_p "$file" \ || func_fatal_help "\`$lib' is not a valid libtool archive" # Read the libtool library. dlname= library_names= func_source "$file" # Skip this library if it cannot be dlopened. if test -z "$dlname"; then # Warn if it was a shared library. test -n "$library_names" && \ func_warning "\`$file' was not linked with \`-export-dynamic'" continue fi func_dirname "$file" "" "." dir="$func_dirname_result" if test -f "$dir/$objdir/$dlname"; then func_append dir "/$objdir" else if test ! -f "$dir/$dlname"; then func_fatal_error "cannot find \`$dlname' in \`$dir' or \`$dir/$objdir'" fi fi ;; *.lo) # Just add the directory containing the .lo file. func_dirname "$file" "" "." dir="$func_dirname_result" ;; *) func_warning "\`-dlopen' is ignored for non-libtool libraries and objects" continue ;; esac # Get the absolute pathname. absdir=`cd "$dir" && pwd` test -n "$absdir" && dir="$absdir" # Now add the directory to shlibpath_var. if eval "test -z \"\$$shlibpath_var\""; then eval "$shlibpath_var=\"\$dir\"" else eval "$shlibpath_var=\"\$dir:\$$shlibpath_var\"" fi done # This variable tells wrapper scripts just to set shlibpath_var # rather than running their programs. libtool_execute_magic="$magic" # Check if any of the arguments is a wrapper script. args= for file do case $file in -* | *.la | *.lo ) ;; *) # Do a test to see if this is really a libtool program. if func_ltwrapper_script_p "$file"; then func_source "$file" # Transform arg to wrapped name. file="$progdir/$program" elif func_ltwrapper_executable_p "$file"; then func_ltwrapper_scriptname "$file" func_source "$func_ltwrapper_scriptname_result" # Transform arg to wrapped name. file="$progdir/$program" fi ;; esac # Quote arguments (to preserve shell metacharacters). func_append_quoted args "$file" done if test "X$opt_dry_run" = Xfalse; then if test -n "$shlibpath_var"; then # Export the shlibpath_var. eval "export $shlibpath_var" fi # Restore saved environment variables for lt_var in LANG LANGUAGE LC_ALL LC_CTYPE LC_COLLATE LC_MESSAGES do eval "if test \"\${save_$lt_var+set}\" = set; then $lt_var=\$save_$lt_var; export $lt_var else $lt_unset $lt_var fi" done # Now prepare to actually exec the command. exec_cmd="\$cmd$args" else # Display what would be done. if test -n "$shlibpath_var"; then eval "\$ECHO \"\$shlibpath_var=\$$shlibpath_var\"" echo "export $shlibpath_var" fi $ECHO "$cmd$args" exit $EXIT_SUCCESS fi } test "$opt_mode" = execute && func_mode_execute ${1+"$@"} # func_mode_finish arg... func_mode_finish () { $opt_debug libs= libdirs= admincmds= for opt in "$nonopt" ${1+"$@"} do if test -d "$opt"; then func_append libdirs " $opt" elif test -f "$opt"; then if func_lalib_unsafe_p "$opt"; then func_append libs " $opt" else func_warning "\`$opt' is not a valid libtool archive" fi else func_fatal_error "invalid argument \`$opt'" fi done if test -n "$libs"; then if test -n "$lt_sysroot"; then sysroot_regex=`$ECHO "$lt_sysroot" | $SED "$sed_make_literal_regex"` sysroot_cmd="s/\([ ']\)$sysroot_regex/\1/g;" else sysroot_cmd= fi # Remove sysroot references if $opt_dry_run; then for lib in $libs; do echo "removing references to $lt_sysroot and \`=' prefixes from $lib" done else tmpdir=`func_mktempdir` for lib in $libs; do sed -e "${sysroot_cmd} s/\([ ']-[LR]\)=/\1/g; s/\([ ']\)=/\1/g" $lib \ > $tmpdir/tmp-la mv -f $tmpdir/tmp-la $lib done ${RM}r "$tmpdir" fi fi if test -n "$finish_cmds$finish_eval" && test -n "$libdirs"; then for libdir in $libdirs; do if test -n "$finish_cmds"; then # Do each command in the finish commands. func_execute_cmds "$finish_cmds" 'admincmds="$admincmds '"$cmd"'"' fi if test -n "$finish_eval"; then # Do the single finish_eval. eval cmds=\"$finish_eval\" $opt_dry_run || eval "$cmds" || func_append admincmds " $cmds" fi done fi # Exit here if they wanted silent mode. $opt_silent && exit $EXIT_SUCCESS if test -n "$finish_cmds$finish_eval" && test -n "$libdirs"; then echo "----------------------------------------------------------------------" echo "Libraries have been installed in:" for libdir in $libdirs; do $ECHO " $libdir" done echo echo "If you ever happen to want to link against installed libraries" echo "in a given directory, LIBDIR, you must either use libtool, and" echo "specify the full pathname of the library, or use the \`-LLIBDIR'" echo "flag during linking and do at least one of the following:" if test -n "$shlibpath_var"; then echo " - add LIBDIR to the \`$shlibpath_var' environment variable" echo " during execution" fi if test -n "$runpath_var"; then echo " - add LIBDIR to the \`$runpath_var' environment variable" echo " during linking" fi if test -n "$hardcode_libdir_flag_spec"; then libdir=LIBDIR eval flag=\"$hardcode_libdir_flag_spec\" $ECHO " - use the \`$flag' linker flag" fi if test -n "$admincmds"; then $ECHO " - have your system administrator run these commands:$admincmds" fi if test -f /etc/ld.so.conf; then echo " - have your system administrator add LIBDIR to \`/etc/ld.so.conf'" fi echo echo "See any operating system documentation about shared libraries for" case $host in solaris2.[6789]|solaris2.1[0-9]) echo "more information, such as the ld(1), crle(1) and ld.so(8) manual" echo "pages." ;; *) echo "more information, such as the ld(1) and ld.so(8) manual pages." ;; esac echo "----------------------------------------------------------------------" fi exit $EXIT_SUCCESS } test "$opt_mode" = finish && func_mode_finish ${1+"$@"} # func_mode_install arg... func_mode_install () { $opt_debug # There may be an optional sh(1) argument at the beginning of # install_prog (especially on Windows NT). if test "$nonopt" = "$SHELL" || test "$nonopt" = /bin/sh || # Allow the use of GNU shtool's install command. case $nonopt in *shtool*) :;; *) false;; esac; then # Aesthetically quote it. func_quote_for_eval "$nonopt" install_prog="$func_quote_for_eval_result " arg=$1 shift else install_prog= arg=$nonopt fi # The real first argument should be the name of the installation program. # Aesthetically quote it. func_quote_for_eval "$arg" func_append install_prog "$func_quote_for_eval_result" install_shared_prog=$install_prog case " $install_prog " in *[\\\ /]cp\ *) install_cp=: ;; *) install_cp=false ;; esac # We need to accept at least all the BSD install flags. dest= files= opts= prev= install_type= isdir=no stripme= no_mode=: for arg do arg2= if test -n "$dest"; then func_append files " $dest" dest=$arg continue fi case $arg in -d) isdir=yes ;; -f) if $install_cp; then :; else prev=$arg fi ;; -g | -m | -o) prev=$arg ;; -s) stripme=" -s" continue ;; -*) ;; *) # If the previous option needed an argument, then skip it. if test -n "$prev"; then if test "x$prev" = x-m && test -n "$install_override_mode"; then arg2=$install_override_mode no_mode=false fi prev= else dest=$arg continue fi ;; esac # Aesthetically quote the argument. func_quote_for_eval "$arg" func_append install_prog " $func_quote_for_eval_result" if test -n "$arg2"; then func_quote_for_eval "$arg2" fi func_append install_shared_prog " $func_quote_for_eval_result" done test -z "$install_prog" && \ func_fatal_help "you must specify an install program" test -n "$prev" && \ func_fatal_help "the \`$prev' option requires an argument" if test -n "$install_override_mode" && $no_mode; then if $install_cp; then :; else func_quote_for_eval "$install_override_mode" func_append install_shared_prog " -m $func_quote_for_eval_result" fi fi if test -z "$files"; then if test -z "$dest"; then func_fatal_help "no file or destination specified" else func_fatal_help "you must specify a destination" fi fi # Strip any trailing slash from the destination. func_stripname '' '/' "$dest" dest=$func_stripname_result # Check to see that the destination is a directory. test -d "$dest" && isdir=yes if test "$isdir" = yes; then destdir="$dest" destname= else func_dirname_and_basename "$dest" "" "." destdir="$func_dirname_result" destname="$func_basename_result" # Not a directory, so check to see that there is only one file specified. set dummy $files; shift test "$#" -gt 1 && \ func_fatal_help "\`$dest' is not a directory" fi case $destdir in [\\/]* | [A-Za-z]:[\\/]*) ;; *) for file in $files; do case $file in *.lo) ;; *) func_fatal_help "\`$destdir' must be an absolute directory name" ;; esac done ;; esac # This variable tells wrapper scripts just to set variables rather # than running their programs. libtool_install_magic="$magic" staticlibs= future_libdirs= current_libdirs= for file in $files; do # Do each installation. case $file in *.$libext) # Do the static libraries later. func_append staticlibs " $file" ;; *.la) func_resolve_sysroot "$file" file=$func_resolve_sysroot_result # Check to see that this really is a libtool archive. func_lalib_unsafe_p "$file" \ || func_fatal_help "\`$file' is not a valid libtool archive" library_names= old_library= relink_command= func_source "$file" # Add the libdir to current_libdirs if it is the destination. if test "X$destdir" = "X$libdir"; then case "$current_libdirs " in *" $libdir "*) ;; *) func_append current_libdirs " $libdir" ;; esac else # Note the libdir as a future libdir. case "$future_libdirs " in *" $libdir "*) ;; *) func_append future_libdirs " $libdir" ;; esac fi func_dirname "$file" "/" "" dir="$func_dirname_result" func_append dir "$objdir" if test -n "$relink_command"; then # Determine the prefix the user has applied to our future dir. inst_prefix_dir=`$ECHO "$destdir" | $SED -e "s%$libdir\$%%"` # Don't allow the user to place us outside of our expected # location b/c this prevents finding dependent libraries that # are installed to the same prefix. # At present, this check doesn't affect windows .dll's that # are installed into $libdir/../bin (currently, that works fine) # but it's something to keep an eye on. test "$inst_prefix_dir" = "$destdir" && \ func_fatal_error "error: cannot install \`$file' to a directory not ending in $libdir" if test -n "$inst_prefix_dir"; then # Stick the inst_prefix_dir data into the link command. relink_command=`$ECHO "$relink_command" | $SED "s%@inst_prefix_dir@%-inst-prefix-dir $inst_prefix_dir%"` else relink_command=`$ECHO "$relink_command" | $SED "s%@inst_prefix_dir@%%"` fi func_warning "relinking \`$file'" func_show_eval "$relink_command" \ 'func_fatal_error "error: relink \`$file'\'' with the above command before installing it"' fi # See the names of the shared library. set dummy $library_names; shift if test -n "$1"; then realname="$1" shift srcname="$realname" test -n "$relink_command" && srcname="$realname"T # Install the shared library and build the symlinks. func_show_eval "$install_shared_prog $dir/$srcname $destdir/$realname" \ 'exit $?' tstripme="$stripme" case $host_os in cygwin* | mingw* | pw32* | cegcc*) case $realname in *.dll.a) tstripme="" ;; esac ;; esac if test -n "$tstripme" && test -n "$striplib"; then func_show_eval "$striplib $destdir/$realname" 'exit $?' fi if test "$#" -gt 0; then # Delete the old symlinks, and create new ones. # Try `ln -sf' first, because the `ln' binary might depend on # the symlink we replace! Solaris /bin/ln does not understand -f, # so we also need to try rm && ln -s. for linkname do test "$linkname" != "$realname" \ && func_show_eval "(cd $destdir && { $LN_S -f $realname $linkname || { $RM $linkname && $LN_S $realname $linkname; }; })" done fi # Do each command in the postinstall commands. lib="$destdir/$realname" func_execute_cmds "$postinstall_cmds" 'exit $?' fi # Install the pseudo-library for information purposes. func_basename "$file" name="$func_basename_result" instname="$dir/$name"i func_show_eval "$install_prog $instname $destdir/$name" 'exit $?' # Maybe install the static library, too. test -n "$old_library" && func_append staticlibs " $dir/$old_library" ;; *.lo) # Install (i.e. copy) a libtool object. # Figure out destination file name, if it wasn't already specified. if test -n "$destname"; then destfile="$destdir/$destname" else func_basename "$file" destfile="$func_basename_result" destfile="$destdir/$destfile" fi # Deduce the name of the destination old-style object file. case $destfile in *.lo) func_lo2o "$destfile" staticdest=$func_lo2o_result ;; *.$objext) staticdest="$destfile" destfile= ;; *) func_fatal_help "cannot copy a libtool object to \`$destfile'" ;; esac # Install the libtool object if requested. test -n "$destfile" && \ func_show_eval "$install_prog $file $destfile" 'exit $?' # Install the old object if enabled. if test "$build_old_libs" = yes; then # Deduce the name of the old-style object file. func_lo2o "$file" staticobj=$func_lo2o_result func_show_eval "$install_prog \$staticobj \$staticdest" 'exit $?' fi exit $EXIT_SUCCESS ;; *) # Figure out destination file name, if it wasn't already specified. if test -n "$destname"; then destfile="$destdir/$destname" else func_basename "$file" destfile="$func_basename_result" destfile="$destdir/$destfile" fi # If the file is missing, and there is a .exe on the end, strip it # because it is most likely a libtool script we actually want to # install stripped_ext="" case $file in *.exe) if test ! -f "$file"; then func_stripname '' '.exe' "$file" file=$func_stripname_result stripped_ext=".exe" fi ;; esac # Do a test to see if this is really a libtool program. case $host in *cygwin* | *mingw*) if func_ltwrapper_executable_p "$file"; then func_ltwrapper_scriptname "$file" wrapper=$func_ltwrapper_scriptname_result else func_stripname '' '.exe' "$file" wrapper=$func_stripname_result fi ;; *) wrapper=$file ;; esac if func_ltwrapper_script_p "$wrapper"; then notinst_deplibs= relink_command= func_source "$wrapper" # Check the variables that should have been set. test -z "$generated_by_libtool_version" && \ func_fatal_error "invalid libtool wrapper script \`$wrapper'" finalize=yes for lib in $notinst_deplibs; do # Check to see that each library is installed. libdir= if test -f "$lib"; then func_source "$lib" fi libfile="$libdir/"`$ECHO "$lib" | $SED 's%^.*/%%g'` ### testsuite: skip nested quoting test if test -n "$libdir" && test ! -f "$libfile"; then func_warning "\`$lib' has not been installed in \`$libdir'" finalize=no fi done relink_command= func_source "$wrapper" outputname= if test "$fast_install" = no && test -n "$relink_command"; then $opt_dry_run || { if test "$finalize" = yes; then tmpdir=`func_mktempdir` func_basename "$file$stripped_ext" file="$func_basename_result" outputname="$tmpdir/$file" # Replace the output file specification. relink_command=`$ECHO "$relink_command" | $SED 's%@OUTPUT@%'"$outputname"'%g'` $opt_silent || { func_quote_for_expand "$relink_command" eval "func_echo $func_quote_for_expand_result" } if eval "$relink_command"; then : else func_error "error: relink \`$file' with the above command before installing it" $opt_dry_run || ${RM}r "$tmpdir" continue fi file="$outputname" else func_warning "cannot relink \`$file'" fi } else # Install the binary that we compiled earlier. file=`$ECHO "$file$stripped_ext" | $SED "s%\([^/]*\)$%$objdir/\1%"` fi fi # remove .exe since cygwin /usr/bin/install will append another # one anyway case $install_prog,$host in */usr/bin/install*,*cygwin*) case $file:$destfile in *.exe:*.exe) # this is ok ;; *.exe:*) destfile=$destfile.exe ;; *:*.exe) func_stripname '' '.exe' "$destfile" destfile=$func_stripname_result ;; esac ;; esac func_show_eval "$install_prog\$stripme \$file \$destfile" 'exit $?' $opt_dry_run || if test -n "$outputname"; then ${RM}r "$tmpdir" fi ;; esac done for file in $staticlibs; do func_basename "$file" name="$func_basename_result" # Set up the ranlib parameters. oldlib="$destdir/$name" func_to_tool_file "$oldlib" func_convert_file_msys_to_w32 tool_oldlib=$func_to_tool_file_result func_show_eval "$install_prog \$file \$oldlib" 'exit $?' if test -n "$stripme" && test -n "$old_striplib"; then func_show_eval "$old_striplib $tool_oldlib" 'exit $?' fi # Do each command in the postinstall commands. func_execute_cmds "$old_postinstall_cmds" 'exit $?' done test -n "$future_libdirs" && \ func_warning "remember to run \`$progname --finish$future_libdirs'" if test -n "$current_libdirs"; then # Maybe just do a dry run. $opt_dry_run && current_libdirs=" -n$current_libdirs" exec_cmd='$SHELL $progpath $preserve_args --finish$current_libdirs' else exit $EXIT_SUCCESS fi } test "$opt_mode" = install && func_mode_install ${1+"$@"} # func_generate_dlsyms outputname originator pic_p # Extract symbols from dlprefiles and create ${outputname}S.o with # a dlpreopen symbol table. func_generate_dlsyms () { $opt_debug my_outputname="$1" my_originator="$2" my_pic_p="${3-no}" my_prefix=`$ECHO "$my_originator" | sed 's%[^a-zA-Z0-9]%_%g'` my_dlsyms= if test -n "$dlfiles$dlprefiles" || test "$dlself" != no; then if test -n "$NM" && test -n "$global_symbol_pipe"; then my_dlsyms="${my_outputname}S.c" else func_error "not configured to extract global symbols from dlpreopened files" fi fi if test -n "$my_dlsyms"; then case $my_dlsyms in "") ;; *.c) # Discover the nlist of each of the dlfiles. nlist="$output_objdir/${my_outputname}.nm" func_show_eval "$RM $nlist ${nlist}S ${nlist}T" # Parse the name list into a source file. func_verbose "creating $output_objdir/$my_dlsyms" $opt_dry_run || $ECHO > "$output_objdir/$my_dlsyms" "\ /* $my_dlsyms - symbol resolution table for \`$my_outputname' dlsym emulation. */ /* Generated by $PROGRAM (GNU $PACKAGE$TIMESTAMP) $VERSION */ #ifdef __cplusplus extern \"C\" { #endif #if defined(__GNUC__) && (((__GNUC__ == 4) && (__GNUC_MINOR__ >= 4)) || (__GNUC__ > 4)) #pragma GCC diagnostic ignored \"-Wstrict-prototypes\" #endif /* Keep this code in sync between libtool.m4, ltmain, lt_system.h, and tests. */ #if defined(_WIN32) || defined(__CYGWIN__) || defined(_WIN32_WCE) /* DATA imports from DLLs on WIN32 con't be const, because runtime relocations are performed -- see ld's documentation on pseudo-relocs. */ # define LT_DLSYM_CONST #elif defined(__osf__) /* This system does not cope well with relocations in const data. */ # define LT_DLSYM_CONST #else # define LT_DLSYM_CONST const #endif /* External symbol declarations for the compiler. */\ " if test "$dlself" = yes; then func_verbose "generating symbol list for \`$output'" $opt_dry_run || echo ': @PROGRAM@ ' > "$nlist" # Add our own program objects to the symbol list. progfiles=`$ECHO "$objs$old_deplibs" | $SP2NL | $SED "$lo2o" | $NL2SP` for progfile in $progfiles; do func_to_tool_file "$progfile" func_convert_file_msys_to_w32 func_verbose "extracting global C symbols from \`$func_to_tool_file_result'" $opt_dry_run || eval "$NM $func_to_tool_file_result | $global_symbol_pipe >> '$nlist'" done if test -n "$exclude_expsyms"; then $opt_dry_run || { eval '$EGREP -v " ($exclude_expsyms)$" "$nlist" > "$nlist"T' eval '$MV "$nlist"T "$nlist"' } fi if test -n "$export_symbols_regex"; then $opt_dry_run || { eval '$EGREP -e "$export_symbols_regex" "$nlist" > "$nlist"T' eval '$MV "$nlist"T "$nlist"' } fi # Prepare the list of exported symbols if test -z "$export_symbols"; then export_symbols="$output_objdir/$outputname.exp" $opt_dry_run || { $RM $export_symbols eval "${SED} -n -e '/^: @PROGRAM@ $/d' -e 's/^.* \(.*\)$/\1/p' "'< "$nlist" > "$export_symbols"' case $host in *cygwin* | *mingw* | *cegcc* ) eval "echo EXPORTS "'> "$output_objdir/$outputname.def"' eval 'cat "$export_symbols" >> "$output_objdir/$outputname.def"' ;; esac } else $opt_dry_run || { eval "${SED} -e 's/\([].[*^$]\)/\\\\\1/g' -e 's/^/ /' -e 's/$/$/'"' < "$export_symbols" > "$output_objdir/$outputname.exp"' eval '$GREP -f "$output_objdir/$outputname.exp" < "$nlist" > "$nlist"T' eval '$MV "$nlist"T "$nlist"' case $host in *cygwin* | *mingw* | *cegcc* ) eval "echo EXPORTS "'> "$output_objdir/$outputname.def"' eval 'cat "$nlist" >> "$output_objdir/$outputname.def"' ;; esac } fi fi for dlprefile in $dlprefiles; do func_verbose "extracting global C symbols from \`$dlprefile'" func_basename "$dlprefile" name="$func_basename_result" case $host in *cygwin* | *mingw* | *cegcc* ) # if an import library, we need to obtain dlname if func_win32_import_lib_p "$dlprefile"; then func_tr_sh "$dlprefile" eval "curr_lafile=\$libfile_$func_tr_sh_result" dlprefile_dlbasename="" if test -n "$curr_lafile" && func_lalib_p "$curr_lafile"; then # Use subshell, to avoid clobbering current variable values dlprefile_dlname=`source "$curr_lafile" && echo "$dlname"` if test -n "$dlprefile_dlname" ; then func_basename "$dlprefile_dlname" dlprefile_dlbasename="$func_basename_result" else # no lafile. user explicitly requested -dlpreopen . $sharedlib_from_linklib_cmd "$dlprefile" dlprefile_dlbasename=$sharedlib_from_linklib_result fi fi $opt_dry_run || { if test -n "$dlprefile_dlbasename" ; then eval '$ECHO ": $dlprefile_dlbasename" >> "$nlist"' else func_warning "Could not compute DLL name from $name" eval '$ECHO ": $name " >> "$nlist"' fi func_to_tool_file "$dlprefile" func_convert_file_msys_to_w32 eval "$NM \"$func_to_tool_file_result\" 2>/dev/null | $global_symbol_pipe | $SED -e '/I __imp/d' -e 's/I __nm_/D /;s/_nm__//' >> '$nlist'" } else # not an import lib $opt_dry_run || { eval '$ECHO ": $name " >> "$nlist"' func_to_tool_file "$dlprefile" func_convert_file_msys_to_w32 eval "$NM \"$func_to_tool_file_result\" 2>/dev/null | $global_symbol_pipe >> '$nlist'" } fi ;; *) $opt_dry_run || { eval '$ECHO ": $name " >> "$nlist"' func_to_tool_file "$dlprefile" func_convert_file_msys_to_w32 eval "$NM \"$func_to_tool_file_result\" 2>/dev/null | $global_symbol_pipe >> '$nlist'" } ;; esac done $opt_dry_run || { # Make sure we have at least an empty file. test -f "$nlist" || : > "$nlist" if test -n "$exclude_expsyms"; then $EGREP -v " ($exclude_expsyms)$" "$nlist" > "$nlist"T $MV "$nlist"T "$nlist" fi # Try sorting and uniquifying the output. if $GREP -v "^: " < "$nlist" | if sort -k 3 /dev/null 2>&1; then sort -k 3 else sort +2 fi | uniq > "$nlist"S; then : else $GREP -v "^: " < "$nlist" > "$nlist"S fi if test -f "$nlist"S; then eval "$global_symbol_to_cdecl"' < "$nlist"S >> "$output_objdir/$my_dlsyms"' else echo '/* NONE */' >> "$output_objdir/$my_dlsyms" fi echo >> "$output_objdir/$my_dlsyms" "\ /* The mapping between symbol names and symbols. */ typedef struct { const char *name; void *address; } lt_dlsymlist; extern LT_DLSYM_CONST lt_dlsymlist lt_${my_prefix}_LTX_preloaded_symbols[]; LT_DLSYM_CONST lt_dlsymlist lt_${my_prefix}_LTX_preloaded_symbols[] = {\ { \"$my_originator\", (void *) 0 }," case $need_lib_prefix in no) eval "$global_symbol_to_c_name_address" < "$nlist" >> "$output_objdir/$my_dlsyms" ;; *) eval "$global_symbol_to_c_name_address_lib_prefix" < "$nlist" >> "$output_objdir/$my_dlsyms" ;; esac echo >> "$output_objdir/$my_dlsyms" "\ {0, (void *) 0} }; /* This works around a problem in FreeBSD linker */ #ifdef FREEBSD_WORKAROUND static const void *lt_preloaded_setup() { return lt_${my_prefix}_LTX_preloaded_symbols; } #endif #ifdef __cplusplus } #endif\ " } # !$opt_dry_run pic_flag_for_symtable= case "$compile_command " in *" -static "*) ;; *) case $host in # compiling the symbol table file with pic_flag works around # a FreeBSD bug that causes programs to crash when -lm is # linked before any other PIC object. But we must not use # pic_flag when linking with -static. The problem exists in # FreeBSD 2.2.6 and is fixed in FreeBSD 3.1. *-*-freebsd2.*|*-*-freebsd3.0*|*-*-freebsdelf3.0*) pic_flag_for_symtable=" $pic_flag -DFREEBSD_WORKAROUND" ;; *-*-hpux*) pic_flag_for_symtable=" $pic_flag" ;; *) if test "X$my_pic_p" != Xno; then pic_flag_for_symtable=" $pic_flag" fi ;; esac ;; esac symtab_cflags= for arg in $LTCFLAGS; do case $arg in -pie | -fpie | -fPIE) ;; *) func_append symtab_cflags " $arg" ;; esac done # Now compile the dynamic symbol file. func_show_eval '(cd $output_objdir && $LTCC$symtab_cflags -c$no_builtin_flag$pic_flag_for_symtable "$my_dlsyms")' 'exit $?' # Clean up the generated files. func_show_eval '$RM "$output_objdir/$my_dlsyms" "$nlist" "${nlist}S" "${nlist}T"' # Transform the symbol file into the correct name. symfileobj="$output_objdir/${my_outputname}S.$objext" case $host in *cygwin* | *mingw* | *cegcc* ) if test -f "$output_objdir/$my_outputname.def"; then compile_command=`$ECHO "$compile_command" | $SED "s%@SYMFILE@%$output_objdir/$my_outputname.def $symfileobj%"` finalize_command=`$ECHO "$finalize_command" | $SED "s%@SYMFILE@%$output_objdir/$my_outputname.def $symfileobj%"` else compile_command=`$ECHO "$compile_command" | $SED "s%@SYMFILE@%$symfileobj%"` finalize_command=`$ECHO "$finalize_command" | $SED "s%@SYMFILE@%$symfileobj%"` fi ;; *) compile_command=`$ECHO "$compile_command" | $SED "s%@SYMFILE@%$symfileobj%"` finalize_command=`$ECHO "$finalize_command" | $SED "s%@SYMFILE@%$symfileobj%"` ;; esac ;; *) func_fatal_error "unknown suffix for \`$my_dlsyms'" ;; esac else # We keep going just in case the user didn't refer to # lt_preloaded_symbols. The linker will fail if global_symbol_pipe # really was required. # Nullify the symbol file. compile_command=`$ECHO "$compile_command" | $SED "s% @SYMFILE@%%"` finalize_command=`$ECHO "$finalize_command" | $SED "s% @SYMFILE@%%"` fi } # func_win32_libid arg # return the library type of file 'arg' # # Need a lot of goo to handle *both* DLLs and import libs # Has to be a shell function in order to 'eat' the argument # that is supplied when $file_magic_command is called. # Despite the name, also deal with 64 bit binaries. func_win32_libid () { $opt_debug win32_libid_type="unknown" win32_fileres=`file -L $1 2>/dev/null` case $win32_fileres in *ar\ archive\ import\ library*) # definitely import win32_libid_type="x86 archive import" ;; *ar\ archive*) # could be an import, or static # Keep the egrep pattern in sync with the one in _LT_CHECK_MAGIC_METHOD. if eval $OBJDUMP -f $1 | $SED -e '10q' 2>/dev/null | $EGREP 'file format (pei*-i386(.*architecture: i386)?|pe-arm-wince|pe-x86-64)' >/dev/null; then func_to_tool_file "$1" func_convert_file_msys_to_w32 win32_nmres=`eval $NM -f posix -A \"$func_to_tool_file_result\" | $SED -n -e ' 1,100{ / I /{ s,.*,import, p q } }'` case $win32_nmres in import*) win32_libid_type="x86 archive import";; *) win32_libid_type="x86 archive static";; esac fi ;; *DLL*) win32_libid_type="x86 DLL" ;; *executable*) # but shell scripts are "executable" too... case $win32_fileres in *MS\ Windows\ PE\ Intel*) win32_libid_type="x86 DLL" ;; esac ;; esac $ECHO "$win32_libid_type" } # func_cygming_dll_for_implib ARG # # Platform-specific function to extract the # name of the DLL associated with the specified # import library ARG. # Invoked by eval'ing the libtool variable # $sharedlib_from_linklib_cmd # Result is available in the variable # $sharedlib_from_linklib_result func_cygming_dll_for_implib () { $opt_debug sharedlib_from_linklib_result=`$DLLTOOL --identify-strict --identify "$1"` } # func_cygming_dll_for_implib_fallback_core SECTION_NAME LIBNAMEs # # The is the core of a fallback implementation of a # platform-specific function to extract the name of the # DLL associated with the specified import library LIBNAME. # # SECTION_NAME is either .idata$6 or .idata$7, depending # on the platform and compiler that created the implib. # # Echos the name of the DLL associated with the # specified import library. func_cygming_dll_for_implib_fallback_core () { $opt_debug match_literal=`$ECHO "$1" | $SED "$sed_make_literal_regex"` $OBJDUMP -s --section "$1" "$2" 2>/dev/null | $SED '/^Contents of section '"$match_literal"':/{ # Place marker at beginning of archive member dllname section s/.*/====MARK====/ p d } # These lines can sometimes be longer than 43 characters, but # are always uninteresting /:[ ]*file format pe[i]\{,1\}-/d /^In archive [^:]*:/d # Ensure marker is printed /^====MARK====/p # Remove all lines with less than 43 characters /^.\{43\}/!d # From remaining lines, remove first 43 characters s/^.\{43\}//' | $SED -n ' # Join marker and all lines until next marker into a single line /^====MARK====/ b para H $ b para b :para x s/\n//g # Remove the marker s/^====MARK====// # Remove trailing dots and whitespace s/[\. \t]*$// # Print /./p' | # we now have a list, one entry per line, of the stringified # contents of the appropriate section of all members of the # archive which possess that section. Heuristic: eliminate # all those which have a first or second character that is # a '.' (that is, objdump's representation of an unprintable # character.) This should work for all archives with less than # 0x302f exports -- but will fail for DLLs whose name actually # begins with a literal '.' or a single character followed by # a '.'. # # Of those that remain, print the first one. $SED -e '/^\./d;/^.\./d;q' } # func_cygming_gnu_implib_p ARG # This predicate returns with zero status (TRUE) if # ARG is a GNU/binutils-style import library. Returns # with nonzero status (FALSE) otherwise. func_cygming_gnu_implib_p () { $opt_debug func_to_tool_file "$1" func_convert_file_msys_to_w32 func_cygming_gnu_implib_tmp=`$NM "$func_to_tool_file_result" | eval "$global_symbol_pipe" | $EGREP ' (_head_[A-Za-z0-9_]+_[ad]l*|[A-Za-z0-9_]+_[ad]l*_iname)$'` test -n "$func_cygming_gnu_implib_tmp" } # func_cygming_ms_implib_p ARG # This predicate returns with zero status (TRUE) if # ARG is an MS-style import library. Returns # with nonzero status (FALSE) otherwise. func_cygming_ms_implib_p () { $opt_debug func_to_tool_file "$1" func_convert_file_msys_to_w32 func_cygming_ms_implib_tmp=`$NM "$func_to_tool_file_result" | eval "$global_symbol_pipe" | $GREP '_NULL_IMPORT_DESCRIPTOR'` test -n "$func_cygming_ms_implib_tmp" } # func_cygming_dll_for_implib_fallback ARG # Platform-specific function to extract the # name of the DLL associated with the specified # import library ARG. # # This fallback implementation is for use when $DLLTOOL # does not support the --identify-strict option. # Invoked by eval'ing the libtool variable # $sharedlib_from_linklib_cmd # Result is available in the variable # $sharedlib_from_linklib_result func_cygming_dll_for_implib_fallback () { $opt_debug if func_cygming_gnu_implib_p "$1" ; then # binutils import library sharedlib_from_linklib_result=`func_cygming_dll_for_implib_fallback_core '.idata$7' "$1"` elif func_cygming_ms_implib_p "$1" ; then # ms-generated import library sharedlib_from_linklib_result=`func_cygming_dll_for_implib_fallback_core '.idata$6' "$1"` else # unknown sharedlib_from_linklib_result="" fi } # func_extract_an_archive dir oldlib func_extract_an_archive () { $opt_debug f_ex_an_ar_dir="$1"; shift f_ex_an_ar_oldlib="$1" if test "$lock_old_archive_extraction" = yes; then lockfile=$f_ex_an_ar_oldlib.lock until $opt_dry_run || ln "$progpath" "$lockfile" 2>/dev/null; do func_echo "Waiting for $lockfile to be removed" sleep 2 done fi func_show_eval "(cd \$f_ex_an_ar_dir && $AR x \"\$f_ex_an_ar_oldlib\")" \ 'stat=$?; rm -f "$lockfile"; exit $stat' if test "$lock_old_archive_extraction" = yes; then $opt_dry_run || rm -f "$lockfile" fi if ($AR t "$f_ex_an_ar_oldlib" | sort | sort -uc >/dev/null 2>&1); then : else func_fatal_error "object name conflicts in archive: $f_ex_an_ar_dir/$f_ex_an_ar_oldlib" fi } # func_extract_archives gentop oldlib ... func_extract_archives () { $opt_debug my_gentop="$1"; shift my_oldlibs=${1+"$@"} my_oldobjs="" my_xlib="" my_xabs="" my_xdir="" for my_xlib in $my_oldlibs; do # Extract the objects. case $my_xlib in [\\/]* | [A-Za-z]:[\\/]*) my_xabs="$my_xlib" ;; *) my_xabs=`pwd`"/$my_xlib" ;; esac func_basename "$my_xlib" my_xlib="$func_basename_result" my_xlib_u=$my_xlib while :; do case " $extracted_archives " in *" $my_xlib_u "*) func_arith $extracted_serial + 1 extracted_serial=$func_arith_result my_xlib_u=lt$extracted_serial-$my_xlib ;; *) break ;; esac done extracted_archives="$extracted_archives $my_xlib_u" my_xdir="$my_gentop/$my_xlib_u" func_mkdir_p "$my_xdir" case $host in *-darwin*) func_verbose "Extracting $my_xabs" # Do not bother doing anything if just a dry run $opt_dry_run || { darwin_orig_dir=`pwd` cd $my_xdir || exit $? darwin_archive=$my_xabs darwin_curdir=`pwd` darwin_base_archive=`basename "$darwin_archive"` darwin_arches=`$LIPO -info "$darwin_archive" 2>/dev/null | $GREP Architectures 2>/dev/null || true` if test -n "$darwin_arches"; then darwin_arches=`$ECHO "$darwin_arches" | $SED -e 's/.*are://'` darwin_arch= func_verbose "$darwin_base_archive has multiple architectures $darwin_arches" for darwin_arch in $darwin_arches ; do func_mkdir_p "unfat-$$/${darwin_base_archive}-${darwin_arch}" $LIPO -thin $darwin_arch -output "unfat-$$/${darwin_base_archive}-${darwin_arch}/${darwin_base_archive}" "${darwin_archive}" cd "unfat-$$/${darwin_base_archive}-${darwin_arch}" func_extract_an_archive "`pwd`" "${darwin_base_archive}" cd "$darwin_curdir" $RM "unfat-$$/${darwin_base_archive}-${darwin_arch}/${darwin_base_archive}" done # $darwin_arches ## Okay now we've a bunch of thin objects, gotta fatten them up :) darwin_filelist=`find unfat-$$ -type f -name \*.o -print -o -name \*.lo -print | $SED -e "$basename" | sort -u` darwin_file= darwin_files= for darwin_file in $darwin_filelist; do darwin_files=`find unfat-$$ -name $darwin_file -print | sort | $NL2SP` $LIPO -create -output "$darwin_file" $darwin_files done # $darwin_filelist $RM -rf unfat-$$ cd "$darwin_orig_dir" else cd $darwin_orig_dir func_extract_an_archive "$my_xdir" "$my_xabs" fi # $darwin_arches } # !$opt_dry_run ;; *) func_extract_an_archive "$my_xdir" "$my_xabs" ;; esac my_oldobjs="$my_oldobjs "`find $my_xdir -name \*.$objext -print -o -name \*.lo -print | sort | $NL2SP` done func_extract_archives_result="$my_oldobjs" } # func_emit_wrapper [arg=no] # # Emit a libtool wrapper script on stdout. # Don't directly open a file because we may want to # incorporate the script contents within a cygwin/mingw # wrapper executable. Must ONLY be called from within # func_mode_link because it depends on a number of variables # set therein. # # ARG is the value that the WRAPPER_SCRIPT_BELONGS_IN_OBJDIR # variable will take. If 'yes', then the emitted script # will assume that the directory in which it is stored is # the $objdir directory. This is a cygwin/mingw-specific # behavior. func_emit_wrapper () { func_emit_wrapper_arg1=${1-no} $ECHO "\ #! $SHELL # $output - temporary wrapper script for $objdir/$outputname # Generated by $PROGRAM (GNU $PACKAGE$TIMESTAMP) $VERSION # # The $output program cannot be directly executed until all the libtool # libraries that it depends on are installed. # # This wrapper script should never be moved out of the build directory. # If it is, it will not operate correctly. # Sed substitution that helps us do robust quoting. It backslashifies # metacharacters that are still active within double-quoted strings. sed_quote_subst='$sed_quote_subst' # Be Bourne compatible if test -n \"\${ZSH_VERSION+set}\" && (emulate sh) >/dev/null 2>&1; then emulate sh NULLCMD=: # Zsh 3.x and 4.x performs word splitting on \${1+\"\$@\"}, which # is contrary to our usage. Disable this feature. alias -g '\${1+\"\$@\"}'='\"\$@\"' setopt NO_GLOB_SUBST else case \`(set -o) 2>/dev/null\` in *posix*) set -o posix;; esac fi BIN_SH=xpg4; export BIN_SH # for Tru64 DUALCASE=1; export DUALCASE # for MKS sh # The HP-UX ksh and POSIX shell print the target directory to stdout # if CDPATH is set. (unset CDPATH) >/dev/null 2>&1 && unset CDPATH relink_command=\"$relink_command\" # This environment variable determines our operation mode. if test \"\$libtool_install_magic\" = \"$magic\"; then # install mode needs the following variables: generated_by_libtool_version='$macro_version' notinst_deplibs='$notinst_deplibs' else # When we are sourced in execute mode, \$file and \$ECHO are already set. if test \"\$libtool_execute_magic\" != \"$magic\"; then file=\"\$0\"" qECHO=`$ECHO "$ECHO" | $SED "$sed_quote_subst"` $ECHO "\ # A function that is used when there is no print builtin or printf. func_fallback_echo () { eval 'cat <<_LTECHO_EOF \$1 _LTECHO_EOF' } ECHO=\"$qECHO\" fi # Very basic option parsing. These options are (a) specific to # the libtool wrapper, (b) are identical between the wrapper # /script/ and the wrapper /executable/ which is used only on # windows platforms, and (c) all begin with the string "--lt-" # (application programs are unlikely to have options which match # this pattern). # # There are only two supported options: --lt-debug and # --lt-dump-script. There is, deliberately, no --lt-help. # # The first argument to this parsing function should be the # script's $0 value, followed by "$@". lt_option_debug= func_parse_lt_options () { lt_script_arg0=\$0 shift for lt_opt do case \"\$lt_opt\" in --lt-debug) lt_option_debug=1 ;; --lt-dump-script) lt_dump_D=\`\$ECHO \"X\$lt_script_arg0\" | $SED -e 's/^X//' -e 's%/[^/]*$%%'\` test \"X\$lt_dump_D\" = \"X\$lt_script_arg0\" && lt_dump_D=. lt_dump_F=\`\$ECHO \"X\$lt_script_arg0\" | $SED -e 's/^X//' -e 's%^.*/%%'\` cat \"\$lt_dump_D/\$lt_dump_F\" exit 0 ;; --lt-*) \$ECHO \"Unrecognized --lt- option: '\$lt_opt'\" 1>&2 exit 1 ;; esac done # Print the debug banner immediately: if test -n \"\$lt_option_debug\"; then echo \"${outputname}:${output}:\${LINENO}: libtool wrapper (GNU $PACKAGE$TIMESTAMP) $VERSION\" 1>&2 fi } # Used when --lt-debug. Prints its arguments to stdout # (redirection is the responsibility of the caller) func_lt_dump_args () { lt_dump_args_N=1; for lt_arg do \$ECHO \"${outputname}:${output}:\${LINENO}: newargv[\$lt_dump_args_N]: \$lt_arg\" lt_dump_args_N=\`expr \$lt_dump_args_N + 1\` done } # Core function for launching the target application func_exec_program_core () { " case $host in # Backslashes separate directories on plain windows *-*-mingw | *-*-os2* | *-cegcc*) $ECHO "\ if test -n \"\$lt_option_debug\"; then \$ECHO \"${outputname}:${output}:\${LINENO}: newargv[0]: \$progdir\\\\\$program\" 1>&2 func_lt_dump_args \${1+\"\$@\"} 1>&2 fi exec \"\$progdir\\\\\$program\" \${1+\"\$@\"} " ;; *) $ECHO "\ if test -n \"\$lt_option_debug\"; then \$ECHO \"${outputname}:${output}:\${LINENO}: newargv[0]: \$progdir/\$program\" 1>&2 func_lt_dump_args \${1+\"\$@\"} 1>&2 fi exec \"\$progdir/\$program\" \${1+\"\$@\"} " ;; esac $ECHO "\ \$ECHO \"\$0: cannot exec \$program \$*\" 1>&2 exit 1 } # A function to encapsulate launching the target application # Strips options in the --lt-* namespace from \$@ and # launches target application with the remaining arguments. func_exec_program () { case \" \$* \" in *\\ --lt-*) for lt_wr_arg do case \$lt_wr_arg in --lt-*) ;; *) set x \"\$@\" \"\$lt_wr_arg\"; shift;; esac shift done ;; esac func_exec_program_core \${1+\"\$@\"} } # Parse options func_parse_lt_options \"\$0\" \${1+\"\$@\"} # Find the directory that this script lives in. thisdir=\`\$ECHO \"\$file\" | $SED 's%/[^/]*$%%'\` test \"x\$thisdir\" = \"x\$file\" && thisdir=. # Follow symbolic links until we get to the real thisdir. file=\`ls -ld \"\$file\" | $SED -n 's/.*-> //p'\` while test -n \"\$file\"; do destdir=\`\$ECHO \"\$file\" | $SED 's%/[^/]*\$%%'\` # If there was a directory component, then change thisdir. if test \"x\$destdir\" != \"x\$file\"; then case \"\$destdir\" in [\\\\/]* | [A-Za-z]:[\\\\/]*) thisdir=\"\$destdir\" ;; *) thisdir=\"\$thisdir/\$destdir\" ;; esac fi file=\`\$ECHO \"\$file\" | $SED 's%^.*/%%'\` file=\`ls -ld \"\$thisdir/\$file\" | $SED -n 's/.*-> //p'\` done # Usually 'no', except on cygwin/mingw when embedded into # the cwrapper. WRAPPER_SCRIPT_BELONGS_IN_OBJDIR=$func_emit_wrapper_arg1 if test \"\$WRAPPER_SCRIPT_BELONGS_IN_OBJDIR\" = \"yes\"; then # special case for '.' if test \"\$thisdir\" = \".\"; then thisdir=\`pwd\` fi # remove .libs from thisdir case \"\$thisdir\" in *[\\\\/]$objdir ) thisdir=\`\$ECHO \"\$thisdir\" | $SED 's%[\\\\/][^\\\\/]*$%%'\` ;; $objdir ) thisdir=. ;; esac fi # Try to get the absolute directory name. absdir=\`cd \"\$thisdir\" && pwd\` test -n \"\$absdir\" && thisdir=\"\$absdir\" " if test "$fast_install" = yes; then $ECHO "\ program=lt-'$outputname'$exeext progdir=\"\$thisdir/$objdir\" if test ! -f \"\$progdir/\$program\" || { file=\`ls -1dt \"\$progdir/\$program\" \"\$progdir/../\$program\" 2>/dev/null | ${SED} 1q\`; \\ test \"X\$file\" != \"X\$progdir/\$program\"; }; then file=\"\$\$-\$program\" if test ! -d \"\$progdir\"; then $MKDIR \"\$progdir\" else $RM \"\$progdir/\$file\" fi" $ECHO "\ # relink executable if necessary if test -n \"\$relink_command\"; then if relink_command_output=\`eval \$relink_command 2>&1\`; then : else $ECHO \"\$relink_command_output\" >&2 $RM \"\$progdir/\$file\" exit 1 fi fi $MV \"\$progdir/\$file\" \"\$progdir/\$program\" 2>/dev/null || { $RM \"\$progdir/\$program\"; $MV \"\$progdir/\$file\" \"\$progdir/\$program\"; } $RM \"\$progdir/\$file\" fi" else $ECHO "\ program='$outputname' progdir=\"\$thisdir/$objdir\" " fi $ECHO "\ if test -f \"\$progdir/\$program\"; then" # fixup the dll searchpath if we need to. # # Fix the DLL searchpath if we need to. Do this before prepending # to shlibpath, because on Windows, both are PATH and uninstalled # libraries must come first. if test -n "$dllsearchpath"; then $ECHO "\ # Add the dll search path components to the executable PATH PATH=$dllsearchpath:\$PATH " fi # Export our shlibpath_var if we have one. if test "$shlibpath_overrides_runpath" = yes && test -n "$shlibpath_var" && test -n "$temp_rpath"; then $ECHO "\ # Add our own library path to $shlibpath_var $shlibpath_var=\"$temp_rpath\$$shlibpath_var\" # Some systems cannot cope with colon-terminated $shlibpath_var # The second colon is a workaround for a bug in BeOS R4 sed $shlibpath_var=\`\$ECHO \"\$$shlibpath_var\" | $SED 's/::*\$//'\` export $shlibpath_var " fi $ECHO "\ if test \"\$libtool_execute_magic\" != \"$magic\"; then # Run the actual program with our arguments. func_exec_program \${1+\"\$@\"} fi else # The program doesn't exist. \$ECHO \"\$0: error: \\\`\$progdir/\$program' does not exist\" 1>&2 \$ECHO \"This script is just a wrapper for \$program.\" 1>&2 \$ECHO \"See the $PACKAGE documentation for more information.\" 1>&2 exit 1 fi fi\ " } # func_emit_cwrapperexe_src # emit the source code for a wrapper executable on stdout # Must ONLY be called from within func_mode_link because # it depends on a number of variable set therein. func_emit_cwrapperexe_src () { cat < #include #ifdef _MSC_VER # include # include # include #else # include # include # ifdef __CYGWIN__ # include # endif #endif #include #include #include #include #include #include #include #include /* declarations of non-ANSI functions */ #if defined(__MINGW32__) # ifdef __STRICT_ANSI__ int _putenv (const char *); # endif #elif defined(__CYGWIN__) # ifdef __STRICT_ANSI__ char *realpath (const char *, char *); int putenv (char *); int setenv (const char *, const char *, int); # endif /* #elif defined (other platforms) ... */ #endif /* portability defines, excluding path handling macros */ #if defined(_MSC_VER) # define setmode _setmode # define stat _stat # define chmod _chmod # define getcwd _getcwd # define putenv _putenv # define S_IXUSR _S_IEXEC # ifndef _INTPTR_T_DEFINED # define _INTPTR_T_DEFINED # define intptr_t int # endif #elif defined(__MINGW32__) # define setmode _setmode # define stat _stat # define chmod _chmod # define getcwd _getcwd # define putenv _putenv #elif defined(__CYGWIN__) # define HAVE_SETENV # define FOPEN_WB "wb" /* #elif defined (other platforms) ... */ #endif #if defined(PATH_MAX) # define LT_PATHMAX PATH_MAX #elif defined(MAXPATHLEN) # define LT_PATHMAX MAXPATHLEN #else # define LT_PATHMAX 1024 #endif #ifndef S_IXOTH # define S_IXOTH 0 #endif #ifndef S_IXGRP # define S_IXGRP 0 #endif /* path handling portability macros */ #ifndef DIR_SEPARATOR # define DIR_SEPARATOR '/' # define PATH_SEPARATOR ':' #endif #if defined (_WIN32) || defined (__MSDOS__) || defined (__DJGPP__) || \ defined (__OS2__) # define HAVE_DOS_BASED_FILE_SYSTEM # define FOPEN_WB "wb" # ifndef DIR_SEPARATOR_2 # define DIR_SEPARATOR_2 '\\' # endif # ifndef PATH_SEPARATOR_2 # define PATH_SEPARATOR_2 ';' # endif #endif #ifndef DIR_SEPARATOR_2 # define IS_DIR_SEPARATOR(ch) ((ch) == DIR_SEPARATOR) #else /* DIR_SEPARATOR_2 */ # define IS_DIR_SEPARATOR(ch) \ (((ch) == DIR_SEPARATOR) || ((ch) == DIR_SEPARATOR_2)) #endif /* DIR_SEPARATOR_2 */ #ifndef PATH_SEPARATOR_2 # define IS_PATH_SEPARATOR(ch) ((ch) == PATH_SEPARATOR) #else /* PATH_SEPARATOR_2 */ # define IS_PATH_SEPARATOR(ch) ((ch) == PATH_SEPARATOR_2) #endif /* PATH_SEPARATOR_2 */ #ifndef FOPEN_WB # define FOPEN_WB "w" #endif #ifndef _O_BINARY # define _O_BINARY 0 #endif #define XMALLOC(type, num) ((type *) xmalloc ((num) * sizeof(type))) #define XFREE(stale) do { \ if (stale) { free ((void *) stale); stale = 0; } \ } while (0) #if defined(LT_DEBUGWRAPPER) static int lt_debug = 1; #else static int lt_debug = 0; #endif const char *program_name = "libtool-wrapper"; /* in case xstrdup fails */ void *xmalloc (size_t num); char *xstrdup (const char *string); const char *base_name (const char *name); char *find_executable (const char *wrapper); char *chase_symlinks (const char *pathspec); int make_executable (const char *path); int check_executable (const char *path); char *strendzap (char *str, const char *pat); void lt_debugprintf (const char *file, int line, const char *fmt, ...); void lt_fatal (const char *file, int line, const char *message, ...); static const char *nonnull (const char *s); static const char *nonempty (const char *s); void lt_setenv (const char *name, const char *value); char *lt_extend_str (const char *orig_value, const char *add, int to_end); void lt_update_exe_path (const char *name, const char *value); void lt_update_lib_path (const char *name, const char *value); char **prepare_spawn (char **argv); void lt_dump_script (FILE *f); EOF cat <= 0) && (st.st_mode & (S_IXUSR | S_IXGRP | S_IXOTH))) return 1; else return 0; } int make_executable (const char *path) { int rval = 0; struct stat st; lt_debugprintf (__FILE__, __LINE__, "(make_executable): %s\n", nonempty (path)); if ((!path) || (!*path)) return 0; if (stat (path, &st) >= 0) { rval = chmod (path, st.st_mode | S_IXOTH | S_IXGRP | S_IXUSR); } return rval; } /* Searches for the full path of the wrapper. Returns newly allocated full path name if found, NULL otherwise Does not chase symlinks, even on platforms that support them. */ char * find_executable (const char *wrapper) { int has_slash = 0; const char *p; const char *p_next; /* static buffer for getcwd */ char tmp[LT_PATHMAX + 1]; int tmp_len; char *concat_name; lt_debugprintf (__FILE__, __LINE__, "(find_executable): %s\n", nonempty (wrapper)); if ((wrapper == NULL) || (*wrapper == '\0')) return NULL; /* Absolute path? */ #if defined (HAVE_DOS_BASED_FILE_SYSTEM) if (isalpha ((unsigned char) wrapper[0]) && wrapper[1] == ':') { concat_name = xstrdup (wrapper); if (check_executable (concat_name)) return concat_name; XFREE (concat_name); } else { #endif if (IS_DIR_SEPARATOR (wrapper[0])) { concat_name = xstrdup (wrapper); if (check_executable (concat_name)) return concat_name; XFREE (concat_name); } #if defined (HAVE_DOS_BASED_FILE_SYSTEM) } #endif for (p = wrapper; *p; p++) if (*p == '/') { has_slash = 1; break; } if (!has_slash) { /* no slashes; search PATH */ const char *path = getenv ("PATH"); if (path != NULL) { for (p = path; *p; p = p_next) { const char *q; size_t p_len; for (q = p; *q; q++) if (IS_PATH_SEPARATOR (*q)) break; p_len = q - p; p_next = (*q == '\0' ? q : q + 1); if (p_len == 0) { /* empty path: current directory */ if (getcwd (tmp, LT_PATHMAX) == NULL) lt_fatal (__FILE__, __LINE__, "getcwd failed: %s", nonnull (strerror (errno))); tmp_len = strlen (tmp); concat_name = XMALLOC (char, tmp_len + 1 + strlen (wrapper) + 1); memcpy (concat_name, tmp, tmp_len); concat_name[tmp_len] = '/'; strcpy (concat_name + tmp_len + 1, wrapper); } else { concat_name = XMALLOC (char, p_len + 1 + strlen (wrapper) + 1); memcpy (concat_name, p, p_len); concat_name[p_len] = '/'; strcpy (concat_name + p_len + 1, wrapper); } if (check_executable (concat_name)) return concat_name; XFREE (concat_name); } } /* not found in PATH; assume curdir */ } /* Relative path | not found in path: prepend cwd */ if (getcwd (tmp, LT_PATHMAX) == NULL) lt_fatal (__FILE__, __LINE__, "getcwd failed: %s", nonnull (strerror (errno))); tmp_len = strlen (tmp); concat_name = XMALLOC (char, tmp_len + 1 + strlen (wrapper) + 1); memcpy (concat_name, tmp, tmp_len); concat_name[tmp_len] = '/'; strcpy (concat_name + tmp_len + 1, wrapper); if (check_executable (concat_name)) return concat_name; XFREE (concat_name); return NULL; } char * chase_symlinks (const char *pathspec) { #ifndef S_ISLNK return xstrdup (pathspec); #else char buf[LT_PATHMAX]; struct stat s; char *tmp_pathspec = xstrdup (pathspec); char *p; int has_symlinks = 0; while (strlen (tmp_pathspec) && !has_symlinks) { lt_debugprintf (__FILE__, __LINE__, "checking path component for symlinks: %s\n", tmp_pathspec); if (lstat (tmp_pathspec, &s) == 0) { if (S_ISLNK (s.st_mode) != 0) { has_symlinks = 1; break; } /* search backwards for last DIR_SEPARATOR */ p = tmp_pathspec + strlen (tmp_pathspec) - 1; while ((p > tmp_pathspec) && (!IS_DIR_SEPARATOR (*p))) p--; if ((p == tmp_pathspec) && (!IS_DIR_SEPARATOR (*p))) { /* no more DIR_SEPARATORS left */ break; } *p = '\0'; } else { lt_fatal (__FILE__, __LINE__, "error accessing file \"%s\": %s", tmp_pathspec, nonnull (strerror (errno))); } } XFREE (tmp_pathspec); if (!has_symlinks) { return xstrdup (pathspec); } tmp_pathspec = realpath (pathspec, buf); if (tmp_pathspec == 0) { lt_fatal (__FILE__, __LINE__, "could not follow symlinks for %s", pathspec); } return xstrdup (tmp_pathspec); #endif } char * strendzap (char *str, const char *pat) { size_t len, patlen; assert (str != NULL); assert (pat != NULL); len = strlen (str); patlen = strlen (pat); if (patlen <= len) { str += len - patlen; if (strcmp (str, pat) == 0) *str = '\0'; } return str; } void lt_debugprintf (const char *file, int line, const char *fmt, ...) { va_list args; if (lt_debug) { (void) fprintf (stderr, "%s:%s:%d: ", program_name, file, line); va_start (args, fmt); (void) vfprintf (stderr, fmt, args); va_end (args); } } static void lt_error_core (int exit_status, const char *file, int line, const char *mode, const char *message, va_list ap) { fprintf (stderr, "%s:%s:%d: %s: ", program_name, file, line, mode); vfprintf (stderr, message, ap); fprintf (stderr, ".\n"); if (exit_status >= 0) exit (exit_status); } void lt_fatal (const char *file, int line, const char *message, ...) { va_list ap; va_start (ap, message); lt_error_core (EXIT_FAILURE, file, line, "FATAL", message, ap); va_end (ap); } static const char * nonnull (const char *s) { return s ? s : "(null)"; } static const char * nonempty (const char *s) { return (s && !*s) ? "(empty)" : nonnull (s); } void lt_setenv (const char *name, const char *value) { lt_debugprintf (__FILE__, __LINE__, "(lt_setenv) setting '%s' to '%s'\n", nonnull (name), nonnull (value)); { #ifdef HAVE_SETENV /* always make a copy, for consistency with !HAVE_SETENV */ char *str = xstrdup (value); setenv (name, str, 1); #else int len = strlen (name) + 1 + strlen (value) + 1; char *str = XMALLOC (char, len); sprintf (str, "%s=%s", name, value); if (putenv (str) != EXIT_SUCCESS) { XFREE (str); } #endif } } char * lt_extend_str (const char *orig_value, const char *add, int to_end) { char *new_value; if (orig_value && *orig_value) { int orig_value_len = strlen (orig_value); int add_len = strlen (add); new_value = XMALLOC (char, add_len + orig_value_len + 1); if (to_end) { strcpy (new_value, orig_value); strcpy (new_value + orig_value_len, add); } else { strcpy (new_value, add); strcpy (new_value + add_len, orig_value); } } else { new_value = xstrdup (add); } return new_value; } void lt_update_exe_path (const char *name, const char *value) { lt_debugprintf (__FILE__, __LINE__, "(lt_update_exe_path) modifying '%s' by prepending '%s'\n", nonnull (name), nonnull (value)); if (name && *name && value && *value) { char *new_value = lt_extend_str (getenv (name), value, 0); /* some systems can't cope with a ':'-terminated path #' */ int len = strlen (new_value); while (((len = strlen (new_value)) > 0) && IS_PATH_SEPARATOR (new_value[len-1])) { new_value[len-1] = '\0'; } lt_setenv (name, new_value); XFREE (new_value); } } void lt_update_lib_path (const char *name, const char *value) { lt_debugprintf (__FILE__, __LINE__, "(lt_update_lib_path) modifying '%s' by prepending '%s'\n", nonnull (name), nonnull (value)); if (name && *name && value && *value) { char *new_value = lt_extend_str (getenv (name), value, 0); lt_setenv (name, new_value); XFREE (new_value); } } EOF case $host_os in mingw*) cat <<"EOF" /* Prepares an argument vector before calling spawn(). Note that spawn() does not by itself call the command interpreter (getenv ("COMSPEC") != NULL ? getenv ("COMSPEC") : ({ OSVERSIONINFO v; v.dwOSVersionInfoSize = sizeof(OSVERSIONINFO); GetVersionEx(&v); v.dwPlatformId == VER_PLATFORM_WIN32_NT; }) ? "cmd.exe" : "command.com"). Instead it simply concatenates the arguments, separated by ' ', and calls CreateProcess(). We must quote the arguments since Win32 CreateProcess() interprets characters like ' ', '\t', '\\', '"' (but not '<' and '>') in a special way: - Space and tab are interpreted as delimiters. They are not treated as delimiters if they are surrounded by double quotes: "...". - Unescaped double quotes are removed from the input. Their only effect is that within double quotes, space and tab are treated like normal characters. - Backslashes not followed by double quotes are not special. - But 2*n+1 backslashes followed by a double quote become n backslashes followed by a double quote (n >= 0): \" -> " \\\" -> \" \\\\\" -> \\" */ #define SHELL_SPECIAL_CHARS "\"\\ \001\002\003\004\005\006\007\010\011\012\013\014\015\016\017\020\021\022\023\024\025\026\027\030\031\032\033\034\035\036\037" #define SHELL_SPACE_CHARS " \001\002\003\004\005\006\007\010\011\012\013\014\015\016\017\020\021\022\023\024\025\026\027\030\031\032\033\034\035\036\037" char ** prepare_spawn (char **argv) { size_t argc; char **new_argv; size_t i; /* Count number of arguments. */ for (argc = 0; argv[argc] != NULL; argc++) ; /* Allocate new argument vector. */ new_argv = XMALLOC (char *, argc + 1); /* Put quoted arguments into the new argument vector. */ for (i = 0; i < argc; i++) { const char *string = argv[i]; if (string[0] == '\0') new_argv[i] = xstrdup ("\"\""); else if (strpbrk (string, SHELL_SPECIAL_CHARS) != NULL) { int quote_around = (strpbrk (string, SHELL_SPACE_CHARS) != NULL); size_t length; unsigned int backslashes; const char *s; char *quoted_string; char *p; length = 0; backslashes = 0; if (quote_around) length++; for (s = string; *s != '\0'; s++) { char c = *s; if (c == '"') length += backslashes + 1; length++; if (c == '\\') backslashes++; else backslashes = 0; } if (quote_around) length += backslashes + 1; quoted_string = XMALLOC (char, length + 1); p = quoted_string; backslashes = 0; if (quote_around) *p++ = '"'; for (s = string; *s != '\0'; s++) { char c = *s; if (c == '"') { unsigned int j; for (j = backslashes + 1; j > 0; j--) *p++ = '\\'; } *p++ = c; if (c == '\\') backslashes++; else backslashes = 0; } if (quote_around) { unsigned int j; for (j = backslashes; j > 0; j--) *p++ = '\\'; *p++ = '"'; } *p = '\0'; new_argv[i] = quoted_string; } else new_argv[i] = (char *) string; } new_argv[argc] = NULL; return new_argv; } EOF ;; esac cat <<"EOF" void lt_dump_script (FILE* f) { EOF func_emit_wrapper yes | $SED -n -e ' s/^\(.\{79\}\)\(..*\)/\1\ \2/ h s/\([\\"]\)/\\\1/g s/$/\\n/ s/\([^\n]*\).*/ fputs ("\1", f);/p g D' cat <<"EOF" } EOF } # end: func_emit_cwrapperexe_src # func_win32_import_lib_p ARG # True if ARG is an import lib, as indicated by $file_magic_cmd func_win32_import_lib_p () { $opt_debug case `eval $file_magic_cmd \"\$1\" 2>/dev/null | $SED -e 10q` in *import*) : ;; *) false ;; esac } # func_mode_link arg... func_mode_link () { $opt_debug case $host in *-*-cygwin* | *-*-mingw* | *-*-pw32* | *-*-os2* | *-cegcc*) # It is impossible to link a dll without this setting, and # we shouldn't force the makefile maintainer to figure out # which system we are compiling for in order to pass an extra # flag for every libtool invocation. # allow_undefined=no # FIXME: Unfortunately, there are problems with the above when trying # to make a dll which has undefined symbols, in which case not # even a static library is built. For now, we need to specify # -no-undefined on the libtool link line when we can be certain # that all symbols are satisfied, otherwise we get a static library. allow_undefined=yes ;; *) allow_undefined=yes ;; esac libtool_args=$nonopt base_compile="$nonopt $@" compile_command=$nonopt finalize_command=$nonopt compile_rpath= finalize_rpath= compile_shlibpath= finalize_shlibpath= convenience= old_convenience= deplibs= old_deplibs= compiler_flags= linker_flags= dllsearchpath= lib_search_path=`pwd` inst_prefix_dir= new_inherited_linker_flags= avoid_version=no bindir= dlfiles= dlprefiles= dlself=no export_dynamic=no export_symbols= export_symbols_regex= generated= libobjs= ltlibs= module=no no_install=no objs= non_pic_objects= precious_files_regex= prefer_static_libs=no preload=no prev= prevarg= release= rpath= xrpath= perm_rpath= temp_rpath= thread_safe=no vinfo= vinfo_number=no weak_libs= single_module="${wl}-single_module" func_infer_tag $base_compile # We need to know -static, to get the right output filenames. for arg do case $arg in -shared) test "$build_libtool_libs" != yes && \ func_fatal_configuration "can not build a shared library" build_old_libs=no break ;; -all-static | -static | -static-libtool-libs) case $arg in -all-static) if test "$build_libtool_libs" = yes && test -z "$link_static_flag"; then func_warning "complete static linking is impossible in this configuration" fi if test -n "$link_static_flag"; then dlopen_self=$dlopen_self_static fi prefer_static_libs=yes ;; -static) if test -z "$pic_flag" && test -n "$link_static_flag"; then dlopen_self=$dlopen_self_static fi prefer_static_libs=built ;; -static-libtool-libs) if test -z "$pic_flag" && test -n "$link_static_flag"; then dlopen_self=$dlopen_self_static fi prefer_static_libs=yes ;; esac build_libtool_libs=no build_old_libs=yes break ;; esac done # See if our shared archives depend on static archives. test -n "$old_archive_from_new_cmds" && build_old_libs=yes # Go through the arguments, transforming them on the way. while test "$#" -gt 0; do arg="$1" shift func_quote_for_eval "$arg" qarg=$func_quote_for_eval_unquoted_result func_append libtool_args " $func_quote_for_eval_result" # If the previous option needs an argument, assign it. if test -n "$prev"; then case $prev in output) func_append compile_command " @OUTPUT@" func_append finalize_command " @OUTPUT@" ;; esac case $prev in bindir) bindir="$arg" prev= continue ;; dlfiles|dlprefiles) if test "$preload" = no; then # Add the symbol object into the linking commands. func_append compile_command " @SYMFILE@" func_append finalize_command " @SYMFILE@" preload=yes fi case $arg in *.la | *.lo) ;; # We handle these cases below. force) if test "$dlself" = no; then dlself=needless export_dynamic=yes fi prev= continue ;; self) if test "$prev" = dlprefiles; then dlself=yes elif test "$prev" = dlfiles && test "$dlopen_self" != yes; then dlself=yes else dlself=needless export_dynamic=yes fi prev= continue ;; *) if test "$prev" = dlfiles; then func_append dlfiles " $arg" else func_append dlprefiles " $arg" fi prev= continue ;; esac ;; expsyms) export_symbols="$arg" test -f "$arg" \ || func_fatal_error "symbol file \`$arg' does not exist" prev= continue ;; expsyms_regex) export_symbols_regex="$arg" prev= continue ;; framework) case $host in *-*-darwin*) case "$deplibs " in *" $qarg.ltframework "*) ;; *) func_append deplibs " $qarg.ltframework" # this is fixed later ;; esac ;; esac prev= continue ;; inst_prefix) inst_prefix_dir="$arg" prev= continue ;; objectlist) if test -f "$arg"; then save_arg=$arg moreargs= for fil in `cat "$save_arg"` do # func_append moreargs " $fil" arg=$fil # A libtool-controlled object. # Check to see that this really is a libtool object. if func_lalib_unsafe_p "$arg"; then pic_object= non_pic_object= # Read the .lo file func_source "$arg" if test -z "$pic_object" || test -z "$non_pic_object" || test "$pic_object" = none && test "$non_pic_object" = none; then func_fatal_error "cannot find name of object for \`$arg'" fi # Extract subdirectory from the argument. func_dirname "$arg" "/" "" xdir="$func_dirname_result" if test "$pic_object" != none; then # Prepend the subdirectory the object is found in. pic_object="$xdir$pic_object" if test "$prev" = dlfiles; then if test "$build_libtool_libs" = yes && test "$dlopen_support" = yes; then func_append dlfiles " $pic_object" prev= continue else # If libtool objects are unsupported, then we need to preload. prev=dlprefiles fi fi # CHECK ME: I think I busted this. -Ossama if test "$prev" = dlprefiles; then # Preload the old-style object. func_append dlprefiles " $pic_object" prev= fi # A PIC object. func_append libobjs " $pic_object" arg="$pic_object" fi # Non-PIC object. if test "$non_pic_object" != none; then # Prepend the subdirectory the object is found in. non_pic_object="$xdir$non_pic_object" # A standard non-PIC object func_append non_pic_objects " $non_pic_object" if test -z "$pic_object" || test "$pic_object" = none ; then arg="$non_pic_object" fi else # If the PIC object exists, use it instead. # $xdir was prepended to $pic_object above. non_pic_object="$pic_object" func_append non_pic_objects " $non_pic_object" fi else # Only an error if not doing a dry-run. if $opt_dry_run; then # Extract subdirectory from the argument. func_dirname "$arg" "/" "" xdir="$func_dirname_result" func_lo2o "$arg" pic_object=$xdir$objdir/$func_lo2o_result non_pic_object=$xdir$func_lo2o_result func_append libobjs " $pic_object" func_append non_pic_objects " $non_pic_object" else func_fatal_error "\`$arg' is not a valid libtool object" fi fi done else func_fatal_error "link input file \`$arg' does not exist" fi arg=$save_arg prev= continue ;; precious_regex) precious_files_regex="$arg" prev= continue ;; release) release="-$arg" prev= continue ;; rpath | xrpath) # We need an absolute path. case $arg in [\\/]* | [A-Za-z]:[\\/]*) ;; *) func_fatal_error "only absolute run-paths are allowed" ;; esac if test "$prev" = rpath; then case "$rpath " in *" $arg "*) ;; *) func_append rpath " $arg" ;; esac else case "$xrpath " in *" $arg "*) ;; *) func_append xrpath " $arg" ;; esac fi prev= continue ;; shrext) shrext_cmds="$arg" prev= continue ;; weak) func_append weak_libs " $arg" prev= continue ;; xcclinker) func_append linker_flags " $qarg" func_append compiler_flags " $qarg" prev= func_append compile_command " $qarg" func_append finalize_command " $qarg" continue ;; xcompiler) func_append compiler_flags " $qarg" prev= func_append compile_command " $qarg" func_append finalize_command " $qarg" continue ;; xlinker) func_append linker_flags " $qarg" func_append compiler_flags " $wl$qarg" prev= func_append compile_command " $wl$qarg" func_append finalize_command " $wl$qarg" continue ;; *) eval "$prev=\"\$arg\"" prev= continue ;; esac fi # test -n "$prev" prevarg="$arg" case $arg in -all-static) if test -n "$link_static_flag"; then # See comment for -static flag below, for more details. func_append compile_command " $link_static_flag" func_append finalize_command " $link_static_flag" fi continue ;; -allow-undefined) # FIXME: remove this flag sometime in the future. func_fatal_error "\`-allow-undefined' must not be used because it is the default" ;; -avoid-version) avoid_version=yes continue ;; -bindir) prev=bindir continue ;; -dlopen) prev=dlfiles continue ;; -dlpreopen) prev=dlprefiles continue ;; -export-dynamic) export_dynamic=yes continue ;; -export-symbols | -export-symbols-regex) if test -n "$export_symbols" || test -n "$export_symbols_regex"; then func_fatal_error "more than one -exported-symbols argument is not allowed" fi if test "X$arg" = "X-export-symbols"; then prev=expsyms else prev=expsyms_regex fi continue ;; -framework) prev=framework continue ;; -inst-prefix-dir) prev=inst_prefix continue ;; # The native IRIX linker understands -LANG:*, -LIST:* and -LNO:* # so, if we see these flags be careful not to treat them like -L -L[A-Z][A-Z]*:*) case $with_gcc/$host in no/*-*-irix* | /*-*-irix*) func_append compile_command " $arg" func_append finalize_command " $arg" ;; esac continue ;; -L*) func_stripname "-L" '' "$arg" if test -z "$func_stripname_result"; then if test "$#" -gt 0; then func_fatal_error "require no space between \`-L' and \`$1'" else func_fatal_error "need path for \`-L' option" fi fi func_resolve_sysroot "$func_stripname_result" dir=$func_resolve_sysroot_result # We need an absolute path. case $dir in [\\/]* | [A-Za-z]:[\\/]*) ;; *) absdir=`cd "$dir" && pwd` test -z "$absdir" && \ func_fatal_error "cannot determine absolute directory name of \`$dir'" dir="$absdir" ;; esac case "$deplibs " in *" -L$dir "* | *" $arg "*) # Will only happen for absolute or sysroot arguments ;; *) # Preserve sysroot, but never include relative directories case $dir in [\\/]* | [A-Za-z]:[\\/]* | =*) func_append deplibs " $arg" ;; *) func_append deplibs " -L$dir" ;; esac func_append lib_search_path " $dir" ;; esac case $host in *-*-cygwin* | *-*-mingw* | *-*-pw32* | *-*-os2* | *-cegcc*) testbindir=`$ECHO "$dir" | $SED 's*/lib$*/bin*'` case :$dllsearchpath: in *":$dir:"*) ;; ::) dllsearchpath=$dir;; *) func_append dllsearchpath ":$dir";; esac case :$dllsearchpath: in *":$testbindir:"*) ;; ::) dllsearchpath=$testbindir;; *) func_append dllsearchpath ":$testbindir";; esac ;; esac continue ;; -l*) if test "X$arg" = "X-lc" || test "X$arg" = "X-lm"; then case $host in *-*-cygwin* | *-*-mingw* | *-*-pw32* | *-*-beos* | *-cegcc* | *-*-haiku*) # These systems don't actually have a C or math library (as such) continue ;; *-*-os2*) # These systems don't actually have a C library (as such) test "X$arg" = "X-lc" && continue ;; *-*-openbsd* | *-*-freebsd* | *-*-dragonfly*) # Do not include libc due to us having libc/libc_r. test "X$arg" = "X-lc" && continue ;; *-*-rhapsody* | *-*-darwin1.[012]) # Rhapsody C and math libraries are in the System framework func_append deplibs " System.ltframework" continue ;; *-*-sco3.2v5* | *-*-sco5v6*) # Causes problems with __ctype test "X$arg" = "X-lc" && continue ;; *-*-sysv4.2uw2* | *-*-sysv5* | *-*-unixware* | *-*-OpenUNIX*) # Compiler inserts libc in the correct place for threads to work test "X$arg" = "X-lc" && continue ;; esac elif test "X$arg" = "X-lc_r"; then case $host in *-*-openbsd* | *-*-freebsd* | *-*-dragonfly*) # Do not include libc_r directly, use -pthread flag. continue ;; esac fi func_append deplibs " $arg" continue ;; -module) module=yes continue ;; # Tru64 UNIX uses -model [arg] to determine the layout of C++ # classes, name mangling, and exception handling. # Darwin uses the -arch flag to determine output architecture. -model|-arch|-isysroot|--sysroot) func_append compiler_flags " $arg" func_append compile_command " $arg" func_append finalize_command " $arg" prev=xcompiler continue ;; -mt|-mthreads|-kthread|-Kthread|-pthread|-pthreads|--thread-safe \ |-threads|-fopenmp|-openmp|-mp|-xopenmp|-omp|-qsmp=*) func_append compiler_flags " $arg" func_append compile_command " $arg" func_append finalize_command " $arg" case "$new_inherited_linker_flags " in *" $arg "*) ;; * ) func_append new_inherited_linker_flags " $arg" ;; esac continue ;; -multi_module) single_module="${wl}-multi_module" continue ;; -no-fast-install) fast_install=no continue ;; -no-install) case $host in *-*-cygwin* | *-*-mingw* | *-*-pw32* | *-*-os2* | *-*-darwin* | *-cegcc*) # The PATH hackery in wrapper scripts is required on Windows # and Darwin in order for the loader to find any dlls it needs. func_warning "\`-no-install' is ignored for $host" func_warning "assuming \`-no-fast-install' instead" fast_install=no ;; *) no_install=yes ;; esac continue ;; -no-undefined) allow_undefined=no continue ;; -objectlist) prev=objectlist continue ;; -o) prev=output ;; -precious-files-regex) prev=precious_regex continue ;; -release) prev=release continue ;; -rpath) prev=rpath continue ;; -R) prev=xrpath continue ;; -R*) func_stripname '-R' '' "$arg" dir=$func_stripname_result # We need an absolute path. case $dir in [\\/]* | [A-Za-z]:[\\/]*) ;; =*) func_stripname '=' '' "$dir" dir=$lt_sysroot$func_stripname_result ;; *) func_fatal_error "only absolute run-paths are allowed" ;; esac case "$xrpath " in *" $dir "*) ;; *) func_append xrpath " $dir" ;; esac continue ;; -shared) # The effects of -shared are defined in a previous loop. continue ;; -shrext) prev=shrext continue ;; -static | -static-libtool-libs) # The effects of -static are defined in a previous loop. # We used to do the same as -all-static on platforms that # didn't have a PIC flag, but the assumption that the effects # would be equivalent was wrong. It would break on at least # Digital Unix and AIX. continue ;; -thread-safe) thread_safe=yes continue ;; -version-info) prev=vinfo continue ;; -version-number) prev=vinfo vinfo_number=yes continue ;; -weak) prev=weak continue ;; -Wc,*) func_stripname '-Wc,' '' "$arg" args=$func_stripname_result arg= save_ifs="$IFS"; IFS=',' for flag in $args; do IFS="$save_ifs" func_quote_for_eval "$flag" func_append arg " $func_quote_for_eval_result" func_append compiler_flags " $func_quote_for_eval_result" done IFS="$save_ifs" func_stripname ' ' '' "$arg" arg=$func_stripname_result ;; -Wl,*) func_stripname '-Wl,' '' "$arg" args=$func_stripname_result arg= save_ifs="$IFS"; IFS=',' for flag in $args; do IFS="$save_ifs" func_quote_for_eval "$flag" func_append arg " $wl$func_quote_for_eval_result" func_append compiler_flags " $wl$func_quote_for_eval_result" func_append linker_flags " $func_quote_for_eval_result" done IFS="$save_ifs" func_stripname ' ' '' "$arg" arg=$func_stripname_result ;; -Xcompiler) prev=xcompiler continue ;; -Xlinker) prev=xlinker continue ;; -XCClinker) prev=xcclinker continue ;; # -msg_* for osf cc -msg_*) func_quote_for_eval "$arg" arg="$func_quote_for_eval_result" ;; # Flags to be passed through unchanged, with rationale: # -64, -mips[0-9] enable 64-bit mode for the SGI compiler # -r[0-9][0-9]* specify processor for the SGI compiler # -xarch=*, -xtarget=* enable 64-bit mode for the Sun compiler # +DA*, +DD* enable 64-bit mode for the HP compiler # -q* compiler args for the IBM compiler # -m*, -t[45]*, -txscale* architecture-specific flags for GCC # -F/path path to uninstalled frameworks, gcc on darwin # -p, -pg, --coverage, -fprofile-* profiling flags for GCC # @file GCC response files # -tp=* Portland pgcc target processor selection # --sysroot=* for sysroot support # -O*, -flto*, -fwhopr*, -fuse-linker-plugin GCC link-time optimization -64|-mips[0-9]|-r[0-9][0-9]*|-xarch=*|-xtarget=*|+DA*|+DD*|-q*|-m*| \ -t[45]*|-txscale*|-p|-pg|--coverage|-fprofile-*|-F*|@*|-tp=*|--sysroot=*| \ -O*|-flto*|-fwhopr*|-fuse-linker-plugin) func_quote_for_eval "$arg" arg="$func_quote_for_eval_result" func_append compile_command " $arg" func_append finalize_command " $arg" func_append compiler_flags " $arg" continue ;; # Some other compiler flag. -* | +*) func_quote_for_eval "$arg" arg="$func_quote_for_eval_result" ;; *.$objext) # A standard object. func_append objs " $arg" ;; *.lo) # A libtool-controlled object. # Check to see that this really is a libtool object. if func_lalib_unsafe_p "$arg"; then pic_object= non_pic_object= # Read the .lo file func_source "$arg" if test -z "$pic_object" || test -z "$non_pic_object" || test "$pic_object" = none && test "$non_pic_object" = none; then func_fatal_error "cannot find name of object for \`$arg'" fi # Extract subdirectory from the argument. func_dirname "$arg" "/" "" xdir="$func_dirname_result" if test "$pic_object" != none; then # Prepend the subdirectory the object is found in. pic_object="$xdir$pic_object" if test "$prev" = dlfiles; then if test "$build_libtool_libs" = yes && test "$dlopen_support" = yes; then func_append dlfiles " $pic_object" prev= continue else # If libtool objects are unsupported, then we need to preload. prev=dlprefiles fi fi # CHECK ME: I think I busted this. -Ossama if test "$prev" = dlprefiles; then # Preload the old-style object. func_append dlprefiles " $pic_object" prev= fi # A PIC object. func_append libobjs " $pic_object" arg="$pic_object" fi # Non-PIC object. if test "$non_pic_object" != none; then # Prepend the subdirectory the object is found in. non_pic_object="$xdir$non_pic_object" # A standard non-PIC object func_append non_pic_objects " $non_pic_object" if test -z "$pic_object" || test "$pic_object" = none ; then arg="$non_pic_object" fi else # If the PIC object exists, use it instead. # $xdir was prepended to $pic_object above. non_pic_object="$pic_object" func_append non_pic_objects " $non_pic_object" fi else # Only an error if not doing a dry-run. if $opt_dry_run; then # Extract subdirectory from the argument. func_dirname "$arg" "/" "" xdir="$func_dirname_result" func_lo2o "$arg" pic_object=$xdir$objdir/$func_lo2o_result non_pic_object=$xdir$func_lo2o_result func_append libobjs " $pic_object" func_append non_pic_objects " $non_pic_object" else func_fatal_error "\`$arg' is not a valid libtool object" fi fi ;; *.$libext) # An archive. func_append deplibs " $arg" func_append old_deplibs " $arg" continue ;; *.la) # A libtool-controlled library. func_resolve_sysroot "$arg" if test "$prev" = dlfiles; then # This library was specified with -dlopen. func_append dlfiles " $func_resolve_sysroot_result" prev= elif test "$prev" = dlprefiles; then # The library was specified with -dlpreopen. func_append dlprefiles " $func_resolve_sysroot_result" prev= else func_append deplibs " $func_resolve_sysroot_result" fi continue ;; # Some other compiler argument. *) # Unknown arguments in both finalize_command and compile_command need # to be aesthetically quoted because they are evaled later. func_quote_for_eval "$arg" arg="$func_quote_for_eval_result" ;; esac # arg # Now actually substitute the argument into the commands. if test -n "$arg"; then func_append compile_command " $arg" func_append finalize_command " $arg" fi done # argument parsing loop test -n "$prev" && \ func_fatal_help "the \`$prevarg' option requires an argument" if test "$export_dynamic" = yes && test -n "$export_dynamic_flag_spec"; then eval arg=\"$export_dynamic_flag_spec\" func_append compile_command " $arg" func_append finalize_command " $arg" fi oldlibs= # calculate the name of the file, without its directory func_basename "$output" outputname="$func_basename_result" libobjs_save="$libobjs" if test -n "$shlibpath_var"; then # get the directories listed in $shlibpath_var eval shlib_search_path=\`\$ECHO \"\${$shlibpath_var}\" \| \$SED \'s/:/ /g\'\` else shlib_search_path= fi eval sys_lib_search_path=\"$sys_lib_search_path_spec\" eval sys_lib_dlsearch_path=\"$sys_lib_dlsearch_path_spec\" func_dirname "$output" "/" "" output_objdir="$func_dirname_result$objdir" func_to_tool_file "$output_objdir/" tool_output_objdir=$func_to_tool_file_result # Create the object directory. func_mkdir_p "$output_objdir" # Determine the type of output case $output in "") func_fatal_help "you must specify an output file" ;; *.$libext) linkmode=oldlib ;; *.lo | *.$objext) linkmode=obj ;; *.la) linkmode=lib ;; *) linkmode=prog ;; # Anything else should be a program. esac specialdeplibs= libs= # Find all interdependent deplibs by searching for libraries # that are linked more than once (e.g. -la -lb -la) for deplib in $deplibs; do if $opt_preserve_dup_deps ; then case "$libs " in *" $deplib "*) func_append specialdeplibs " $deplib" ;; esac fi func_append libs " $deplib" done if test "$linkmode" = lib; then libs="$predeps $libs $compiler_lib_search_path $postdeps" # Compute libraries that are listed more than once in $predeps # $postdeps and mark them as special (i.e., whose duplicates are # not to be eliminated). pre_post_deps= if $opt_duplicate_compiler_generated_deps; then for pre_post_dep in $predeps $postdeps; do case "$pre_post_deps " in *" $pre_post_dep "*) func_append specialdeplibs " $pre_post_deps" ;; esac func_append pre_post_deps " $pre_post_dep" done fi pre_post_deps= fi deplibs= newdependency_libs= newlib_search_path= need_relink=no # whether we're linking any uninstalled libtool libraries notinst_deplibs= # not-installed libtool libraries notinst_path= # paths that contain not-installed libtool libraries case $linkmode in lib) passes="conv dlpreopen link" for file in $dlfiles $dlprefiles; do case $file in *.la) ;; *) func_fatal_help "libraries can \`-dlopen' only libtool libraries: $file" ;; esac done ;; prog) compile_deplibs= finalize_deplibs= alldeplibs=no newdlfiles= newdlprefiles= passes="conv scan dlopen dlpreopen link" ;; *) passes="conv" ;; esac for pass in $passes; do # The preopen pass in lib mode reverses $deplibs; put it back here # so that -L comes before libs that need it for instance... if test "$linkmode,$pass" = "lib,link"; then ## FIXME: Find the place where the list is rebuilt in the wrong ## order, and fix it there properly tmp_deplibs= for deplib in $deplibs; do tmp_deplibs="$deplib $tmp_deplibs" done deplibs="$tmp_deplibs" fi if test "$linkmode,$pass" = "lib,link" || test "$linkmode,$pass" = "prog,scan"; then libs="$deplibs" deplibs= fi if test "$linkmode" = prog; then case $pass in dlopen) libs="$dlfiles" ;; dlpreopen) libs="$dlprefiles" ;; link) libs="$deplibs %DEPLIBS%" test "X$link_all_deplibs" != Xno && libs="$libs $dependency_libs" ;; esac fi if test "$linkmode,$pass" = "lib,dlpreopen"; then # Collect and forward deplibs of preopened libtool libs for lib in $dlprefiles; do # Ignore non-libtool-libs dependency_libs= func_resolve_sysroot "$lib" case $lib in *.la) func_source "$func_resolve_sysroot_result" ;; esac # Collect preopened libtool deplibs, except any this library # has declared as weak libs for deplib in $dependency_libs; do func_basename "$deplib" deplib_base=$func_basename_result case " $weak_libs " in *" $deplib_base "*) ;; *) func_append deplibs " $deplib" ;; esac done done libs="$dlprefiles" fi if test "$pass" = dlopen; then # Collect dlpreopened libraries save_deplibs="$deplibs" deplibs= fi for deplib in $libs; do lib= found=no case $deplib in -mt|-mthreads|-kthread|-Kthread|-pthread|-pthreads|--thread-safe \ |-threads|-fopenmp|-openmp|-mp|-xopenmp|-omp|-qsmp=*) if test "$linkmode,$pass" = "prog,link"; then compile_deplibs="$deplib $compile_deplibs" finalize_deplibs="$deplib $finalize_deplibs" else func_append compiler_flags " $deplib" if test "$linkmode" = lib ; then case "$new_inherited_linker_flags " in *" $deplib "*) ;; * ) func_append new_inherited_linker_flags " $deplib" ;; esac fi fi continue ;; -l*) if test "$linkmode" != lib && test "$linkmode" != prog; then func_warning "\`-l' is ignored for archives/objects" continue fi func_stripname '-l' '' "$deplib" name=$func_stripname_result if test "$linkmode" = lib; then searchdirs="$newlib_search_path $lib_search_path $compiler_lib_search_dirs $sys_lib_search_path $shlib_search_path" else searchdirs="$newlib_search_path $lib_search_path $sys_lib_search_path $shlib_search_path" fi for searchdir in $searchdirs; do for search_ext in .la $std_shrext .so .a; do # Search the libtool library lib="$searchdir/lib${name}${search_ext}" if test -f "$lib"; then if test "$search_ext" = ".la"; then found=yes else found=no fi break 2 fi done done if test "$found" != yes; then # deplib doesn't seem to be a libtool library if test "$linkmode,$pass" = "prog,link"; then compile_deplibs="$deplib $compile_deplibs" finalize_deplibs="$deplib $finalize_deplibs" else deplibs="$deplib $deplibs" test "$linkmode" = lib && newdependency_libs="$deplib $newdependency_libs" fi continue else # deplib is a libtool library # If $allow_libtool_libs_with_static_runtimes && $deplib is a stdlib, # We need to do some special things here, and not later. if test "X$allow_libtool_libs_with_static_runtimes" = "Xyes" ; then case " $predeps $postdeps " in *" $deplib "*) if func_lalib_p "$lib"; then library_names= old_library= func_source "$lib" for l in $old_library $library_names; do ll="$l" done if test "X$ll" = "X$old_library" ; then # only static version available found=no func_dirname "$lib" "" "." ladir="$func_dirname_result" lib=$ladir/$old_library if test "$linkmode,$pass" = "prog,link"; then compile_deplibs="$deplib $compile_deplibs" finalize_deplibs="$deplib $finalize_deplibs" else deplibs="$deplib $deplibs" test "$linkmode" = lib && newdependency_libs="$deplib $newdependency_libs" fi continue fi fi ;; *) ;; esac fi fi ;; # -l *.ltframework) if test "$linkmode,$pass" = "prog,link"; then compile_deplibs="$deplib $compile_deplibs" finalize_deplibs="$deplib $finalize_deplibs" else deplibs="$deplib $deplibs" if test "$linkmode" = lib ; then case "$new_inherited_linker_flags " in *" $deplib "*) ;; * ) func_append new_inherited_linker_flags " $deplib" ;; esac fi fi continue ;; -L*) case $linkmode in lib) deplibs="$deplib $deplibs" test "$pass" = conv && continue newdependency_libs="$deplib $newdependency_libs" func_stripname '-L' '' "$deplib" func_resolve_sysroot "$func_stripname_result" func_append newlib_search_path " $func_resolve_sysroot_result" ;; prog) if test "$pass" = conv; then deplibs="$deplib $deplibs" continue fi if test "$pass" = scan; then deplibs="$deplib $deplibs" else compile_deplibs="$deplib $compile_deplibs" finalize_deplibs="$deplib $finalize_deplibs" fi func_stripname '-L' '' "$deplib" func_resolve_sysroot "$func_stripname_result" func_append newlib_search_path " $func_resolve_sysroot_result" ;; *) func_warning "\`-L' is ignored for archives/objects" ;; esac # linkmode continue ;; # -L -R*) if test "$pass" = link; then func_stripname '-R' '' "$deplib" func_resolve_sysroot "$func_stripname_result" dir=$func_resolve_sysroot_result # Make sure the xrpath contains only unique directories. case "$xrpath " in *" $dir "*) ;; *) func_append xrpath " $dir" ;; esac fi deplibs="$deplib $deplibs" continue ;; *.la) func_resolve_sysroot "$deplib" lib=$func_resolve_sysroot_result ;; *.$libext) if test "$pass" = conv; then deplibs="$deplib $deplibs" continue fi case $linkmode in lib) # Linking convenience modules into shared libraries is allowed, # but linking other static libraries is non-portable. case " $dlpreconveniencelibs " in *" $deplib "*) ;; *) valid_a_lib=no case $deplibs_check_method in match_pattern*) set dummy $deplibs_check_method; shift match_pattern_regex=`expr "$deplibs_check_method" : "$1 \(.*\)"` if eval "\$ECHO \"$deplib\"" 2>/dev/null | $SED 10q \ | $EGREP "$match_pattern_regex" > /dev/null; then valid_a_lib=yes fi ;; pass_all) valid_a_lib=yes ;; esac if test "$valid_a_lib" != yes; then echo $ECHO "*** Warning: Trying to link with static lib archive $deplib." echo "*** I have the capability to make that library automatically link in when" echo "*** you link to this library. But I can only do this if you have a" echo "*** shared version of the library, which you do not appear to have" echo "*** because the file extensions .$libext of this argument makes me believe" echo "*** that it is just a static archive that I should not use here." else echo $ECHO "*** Warning: Linking the shared library $output against the" $ECHO "*** static library $deplib is not portable!" deplibs="$deplib $deplibs" fi ;; esac continue ;; prog) if test "$pass" != link; then deplibs="$deplib $deplibs" else compile_deplibs="$deplib $compile_deplibs" finalize_deplibs="$deplib $finalize_deplibs" fi continue ;; esac # linkmode ;; # *.$libext *.lo | *.$objext) if test "$pass" = conv; then deplibs="$deplib $deplibs" elif test "$linkmode" = prog; then if test "$pass" = dlpreopen || test "$dlopen_support" != yes || test "$build_libtool_libs" = no; then # If there is no dlopen support or we're linking statically, # we need to preload. func_append newdlprefiles " $deplib" compile_deplibs="$deplib $compile_deplibs" finalize_deplibs="$deplib $finalize_deplibs" else func_append newdlfiles " $deplib" fi fi continue ;; %DEPLIBS%) alldeplibs=yes continue ;; esac # case $deplib if test "$found" = yes || test -f "$lib"; then : else func_fatal_error "cannot find the library \`$lib' or unhandled argument \`$deplib'" fi # Check to see that this really is a libtool archive. func_lalib_unsafe_p "$lib" \ || func_fatal_error "\`$lib' is not a valid libtool archive" func_dirname "$lib" "" "." ladir="$func_dirname_result" dlname= dlopen= dlpreopen= libdir= library_names= old_library= inherited_linker_flags= # If the library was installed with an old release of libtool, # it will not redefine variables installed, or shouldnotlink installed=yes shouldnotlink=no avoidtemprpath= # Read the .la file func_source "$lib" # Convert "-framework foo" to "foo.ltframework" if test -n "$inherited_linker_flags"; then tmp_inherited_linker_flags=`$ECHO "$inherited_linker_flags" | $SED 's/-framework \([^ $]*\)/\1.ltframework/g'` for tmp_inherited_linker_flag in $tmp_inherited_linker_flags; do case " $new_inherited_linker_flags " in *" $tmp_inherited_linker_flag "*) ;; *) func_append new_inherited_linker_flags " $tmp_inherited_linker_flag";; esac done fi dependency_libs=`$ECHO " $dependency_libs" | $SED 's% \([^ $]*\).ltframework% -framework \1%g'` if test "$linkmode,$pass" = "lib,link" || test "$linkmode,$pass" = "prog,scan" || { test "$linkmode" != prog && test "$linkmode" != lib; }; then test -n "$dlopen" && func_append dlfiles " $dlopen" test -n "$dlpreopen" && func_append dlprefiles " $dlpreopen" fi if test "$pass" = conv; then # Only check for convenience libraries deplibs="$lib $deplibs" if test -z "$libdir"; then if test -z "$old_library"; then func_fatal_error "cannot find name of link library for \`$lib'" fi # It is a libtool convenience library, so add in its objects. func_append convenience " $ladir/$objdir/$old_library" func_append old_convenience " $ladir/$objdir/$old_library" tmp_libs= for deplib in $dependency_libs; do deplibs="$deplib $deplibs" if $opt_preserve_dup_deps ; then case "$tmp_libs " in *" $deplib "*) func_append specialdeplibs " $deplib" ;; esac fi func_append tmp_libs " $deplib" done elif test "$linkmode" != prog && test "$linkmode" != lib; then func_fatal_error "\`$lib' is not a convenience library" fi continue fi # $pass = conv # Get the name of the library we link against. linklib= if test -n "$old_library" && { test "$prefer_static_libs" = yes || test "$prefer_static_libs,$installed" = "built,no"; }; then linklib=$old_library else for l in $old_library $library_names; do linklib="$l" done fi if test -z "$linklib"; then func_fatal_error "cannot find name of link library for \`$lib'" fi # This library was specified with -dlopen. if test "$pass" = dlopen; then if test -z "$libdir"; then func_fatal_error "cannot -dlopen a convenience library: \`$lib'" fi if test -z "$dlname" || test "$dlopen_support" != yes || test "$build_libtool_libs" = no; then # If there is no dlname, no dlopen support or we're linking # statically, we need to preload. We also need to preload any # dependent libraries so libltdl's deplib preloader doesn't # bomb out in the load deplibs phase. func_append dlprefiles " $lib $dependency_libs" else func_append newdlfiles " $lib" fi continue fi # $pass = dlopen # We need an absolute path. case $ladir in [\\/]* | [A-Za-z]:[\\/]*) abs_ladir="$ladir" ;; *) abs_ladir=`cd "$ladir" && pwd` if test -z "$abs_ladir"; then func_warning "cannot determine absolute directory name of \`$ladir'" func_warning "passing it literally to the linker, although it might fail" abs_ladir="$ladir" fi ;; esac func_basename "$lib" laname="$func_basename_result" # Find the relevant object directory and library name. if test "X$installed" = Xyes; then if test ! -f "$lt_sysroot$libdir/$linklib" && test -f "$abs_ladir/$linklib"; then func_warning "library \`$lib' was moved." dir="$ladir" absdir="$abs_ladir" libdir="$abs_ladir" else dir="$lt_sysroot$libdir" absdir="$lt_sysroot$libdir" fi test "X$hardcode_automatic" = Xyes && avoidtemprpath=yes else if test ! -f "$ladir/$objdir/$linklib" && test -f "$abs_ladir/$linklib"; then dir="$ladir" absdir="$abs_ladir" # Remove this search path later func_append notinst_path " $abs_ladir" else dir="$ladir/$objdir" absdir="$abs_ladir/$objdir" # Remove this search path later func_append notinst_path " $abs_ladir" fi fi # $installed = yes func_stripname 'lib' '.la' "$laname" name=$func_stripname_result # This library was specified with -dlpreopen. if test "$pass" = dlpreopen; then if test -z "$libdir" && test "$linkmode" = prog; then func_fatal_error "only libraries may -dlpreopen a convenience library: \`$lib'" fi case "$host" in # special handling for platforms with PE-DLLs. *cygwin* | *mingw* | *cegcc* ) # Linker will automatically link against shared library if both # static and shared are present. Therefore, ensure we extract # symbols from the import library if a shared library is present # (otherwise, the dlopen module name will be incorrect). We do # this by putting the import library name into $newdlprefiles. # We recover the dlopen module name by 'saving' the la file # name in a special purpose variable, and (later) extracting the # dlname from the la file. if test -n "$dlname"; then func_tr_sh "$dir/$linklib" eval "libfile_$func_tr_sh_result=\$abs_ladir/\$laname" func_append newdlprefiles " $dir/$linklib" else func_append newdlprefiles " $dir/$old_library" # Keep a list of preopened convenience libraries to check # that they are being used correctly in the link pass. test -z "$libdir" && \ func_append dlpreconveniencelibs " $dir/$old_library" fi ;; * ) # Prefer using a static library (so that no silly _DYNAMIC symbols # are required to link). if test -n "$old_library"; then func_append newdlprefiles " $dir/$old_library" # Keep a list of preopened convenience libraries to check # that they are being used correctly in the link pass. test -z "$libdir" && \ func_append dlpreconveniencelibs " $dir/$old_library" # Otherwise, use the dlname, so that lt_dlopen finds it. elif test -n "$dlname"; then func_append newdlprefiles " $dir/$dlname" else func_append newdlprefiles " $dir/$linklib" fi ;; esac fi # $pass = dlpreopen if test -z "$libdir"; then # Link the convenience library if test "$linkmode" = lib; then deplibs="$dir/$old_library $deplibs" elif test "$linkmode,$pass" = "prog,link"; then compile_deplibs="$dir/$old_library $compile_deplibs" finalize_deplibs="$dir/$old_library $finalize_deplibs" else deplibs="$lib $deplibs" # used for prog,scan pass fi continue fi if test "$linkmode" = prog && test "$pass" != link; then func_append newlib_search_path " $ladir" deplibs="$lib $deplibs" linkalldeplibs=no if test "$link_all_deplibs" != no || test -z "$library_names" || test "$build_libtool_libs" = no; then linkalldeplibs=yes fi tmp_libs= for deplib in $dependency_libs; do case $deplib in -L*) func_stripname '-L' '' "$deplib" func_resolve_sysroot "$func_stripname_result" func_append newlib_search_path " $func_resolve_sysroot_result" ;; esac # Need to link against all dependency_libs? if test "$linkalldeplibs" = yes; then deplibs="$deplib $deplibs" else # Need to hardcode shared library paths # or/and link against static libraries newdependency_libs="$deplib $newdependency_libs" fi if $opt_preserve_dup_deps ; then case "$tmp_libs " in *" $deplib "*) func_append specialdeplibs " $deplib" ;; esac fi func_append tmp_libs " $deplib" done # for deplib continue fi # $linkmode = prog... if test "$linkmode,$pass" = "prog,link"; then if test -n "$library_names" && { { test "$prefer_static_libs" = no || test "$prefer_static_libs,$installed" = "built,yes"; } || test -z "$old_library"; }; then # We need to hardcode the library path if test -n "$shlibpath_var" && test -z "$avoidtemprpath" ; then # Make sure the rpath contains only unique directories. case "$temp_rpath:" in *"$absdir:"*) ;; *) func_append temp_rpath "$absdir:" ;; esac fi # Hardcode the library path. # Skip directories that are in the system default run-time # search path. case " $sys_lib_dlsearch_path " in *" $absdir "*) ;; *) case "$compile_rpath " in *" $absdir "*) ;; *) func_append compile_rpath " $absdir" ;; esac ;; esac case " $sys_lib_dlsearch_path " in *" $libdir "*) ;; *) case "$finalize_rpath " in *" $libdir "*) ;; *) func_append finalize_rpath " $libdir" ;; esac ;; esac fi # $linkmode,$pass = prog,link... if test "$alldeplibs" = yes && { test "$deplibs_check_method" = pass_all || { test "$build_libtool_libs" = yes && test -n "$library_names"; }; }; then # We only need to search for static libraries continue fi fi link_static=no # Whether the deplib will be linked statically use_static_libs=$prefer_static_libs if test "$use_static_libs" = built && test "$installed" = yes; then use_static_libs=no fi if test -n "$library_names" && { test "$use_static_libs" = no || test -z "$old_library"; }; then case $host in *cygwin* | *mingw* | *cegcc*) # No point in relinking DLLs because paths are not encoded func_append notinst_deplibs " $lib" need_relink=no ;; *) if test "$installed" = no; then func_append notinst_deplibs " $lib" need_relink=yes fi ;; esac # This is a shared library # Warn about portability, can't link against -module's on some # systems (darwin). Don't bleat about dlopened modules though! dlopenmodule="" for dlpremoduletest in $dlprefiles; do if test "X$dlpremoduletest" = "X$lib"; then dlopenmodule="$dlpremoduletest" break fi done if test -z "$dlopenmodule" && test "$shouldnotlink" = yes && test "$pass" = link; then echo if test "$linkmode" = prog; then $ECHO "*** Warning: Linking the executable $output against the loadable module" else $ECHO "*** Warning: Linking the shared library $output against the loadable module" fi $ECHO "*** $linklib is not portable!" fi if test "$linkmode" = lib && test "$hardcode_into_libs" = yes; then # Hardcode the library path. # Skip directories that are in the system default run-time # search path. case " $sys_lib_dlsearch_path " in *" $absdir "*) ;; *) case "$compile_rpath " in *" $absdir "*) ;; *) func_append compile_rpath " $absdir" ;; esac ;; esac case " $sys_lib_dlsearch_path " in *" $libdir "*) ;; *) case "$finalize_rpath " in *" $libdir "*) ;; *) func_append finalize_rpath " $libdir" ;; esac ;; esac fi if test -n "$old_archive_from_expsyms_cmds"; then # figure out the soname set dummy $library_names shift realname="$1" shift libname=`eval "\\$ECHO \"$libname_spec\""` # use dlname if we got it. it's perfectly good, no? if test -n "$dlname"; then soname="$dlname" elif test -n "$soname_spec"; then # bleh windows case $host in *cygwin* | mingw* | *cegcc*) func_arith $current - $age major=$func_arith_result versuffix="-$major" ;; esac eval soname=\"$soname_spec\" else soname="$realname" fi # Make a new name for the extract_expsyms_cmds to use soroot="$soname" func_basename "$soroot" soname="$func_basename_result" func_stripname 'lib' '.dll' "$soname" newlib=libimp-$func_stripname_result.a # If the library has no export list, then create one now if test -f "$output_objdir/$soname-def"; then : else func_verbose "extracting exported symbol list from \`$soname'" func_execute_cmds "$extract_expsyms_cmds" 'exit $?' fi # Create $newlib if test -f "$output_objdir/$newlib"; then :; else func_verbose "generating import library for \`$soname'" func_execute_cmds "$old_archive_from_expsyms_cmds" 'exit $?' fi # make sure the library variables are pointing to the new library dir=$output_objdir linklib=$newlib fi # test -n "$old_archive_from_expsyms_cmds" if test "$linkmode" = prog || test "$opt_mode" != relink; then add_shlibpath= add_dir= add= lib_linked=yes case $hardcode_action in immediate | unsupported) if test "$hardcode_direct" = no; then add="$dir/$linklib" case $host in *-*-sco3.2v5.0.[024]*) add_dir="-L$dir" ;; *-*-sysv4*uw2*) add_dir="-L$dir" ;; *-*-sysv5OpenUNIX* | *-*-sysv5UnixWare7.[01].[10]* | \ *-*-unixware7*) add_dir="-L$dir" ;; *-*-darwin* ) # if the lib is a (non-dlopened) module then we can not # link against it, someone is ignoring the earlier warnings if /usr/bin/file -L $add 2> /dev/null | $GREP ": [^:]* bundle" >/dev/null ; then if test "X$dlopenmodule" != "X$lib"; then $ECHO "*** Warning: lib $linklib is a module, not a shared library" if test -z "$old_library" ; then echo echo "*** And there doesn't seem to be a static archive available" echo "*** The link will probably fail, sorry" else add="$dir/$old_library" fi elif test -n "$old_library"; then add="$dir/$old_library" fi fi esac elif test "$hardcode_minus_L" = no; then case $host in *-*-sunos*) add_shlibpath="$dir" ;; esac add_dir="-L$dir" add="-l$name" elif test "$hardcode_shlibpath_var" = no; then add_shlibpath="$dir" add="-l$name" else lib_linked=no fi ;; relink) if test "$hardcode_direct" = yes && test "$hardcode_direct_absolute" = no; then add="$dir/$linklib" elif test "$hardcode_minus_L" = yes; then add_dir="-L$absdir" # Try looking first in the location we're being installed to. if test -n "$inst_prefix_dir"; then case $libdir in [\\/]*) func_append add_dir " -L$inst_prefix_dir$libdir" ;; esac fi add="-l$name" elif test "$hardcode_shlibpath_var" = yes; then add_shlibpath="$dir" add="-l$name" else lib_linked=no fi ;; *) lib_linked=no ;; esac if test "$lib_linked" != yes; then func_fatal_configuration "unsupported hardcode properties" fi if test -n "$add_shlibpath"; then case :$compile_shlibpath: in *":$add_shlibpath:"*) ;; *) func_append compile_shlibpath "$add_shlibpath:" ;; esac fi if test "$linkmode" = prog; then test -n "$add_dir" && compile_deplibs="$add_dir $compile_deplibs" test -n "$add" && compile_deplibs="$add $compile_deplibs" else test -n "$add_dir" && deplibs="$add_dir $deplibs" test -n "$add" && deplibs="$add $deplibs" if test "$hardcode_direct" != yes && test "$hardcode_minus_L" != yes && test "$hardcode_shlibpath_var" = yes; then case :$finalize_shlibpath: in *":$libdir:"*) ;; *) func_append finalize_shlibpath "$libdir:" ;; esac fi fi fi if test "$linkmode" = prog || test "$opt_mode" = relink; then add_shlibpath= add_dir= add= # Finalize command for both is simple: just hardcode it. if test "$hardcode_direct" = yes && test "$hardcode_direct_absolute" = no; then add="$libdir/$linklib" elif test "$hardcode_minus_L" = yes; then add_dir="-L$libdir" add="-l$name" elif test "$hardcode_shlibpath_var" = yes; then case :$finalize_shlibpath: in *":$libdir:"*) ;; *) func_append finalize_shlibpath "$libdir:" ;; esac add="-l$name" elif test "$hardcode_automatic" = yes; then if test -n "$inst_prefix_dir" && test -f "$inst_prefix_dir$libdir/$linklib" ; then add="$inst_prefix_dir$libdir/$linklib" else add="$libdir/$linklib" fi else # We cannot seem to hardcode it, guess we'll fake it. add_dir="-L$libdir" # Try looking first in the location we're being installed to. if test -n "$inst_prefix_dir"; then case $libdir in [\\/]*) func_append add_dir " -L$inst_prefix_dir$libdir" ;; esac fi add="-l$name" fi if test "$linkmode" = prog; then test -n "$add_dir" && finalize_deplibs="$add_dir $finalize_deplibs" test -n "$add" && finalize_deplibs="$add $finalize_deplibs" else test -n "$add_dir" && deplibs="$add_dir $deplibs" test -n "$add" && deplibs="$add $deplibs" fi fi elif test "$linkmode" = prog; then # Here we assume that one of hardcode_direct or hardcode_minus_L # is not unsupported. This is valid on all known static and # shared platforms. if test "$hardcode_direct" != unsupported; then test -n "$old_library" && linklib="$old_library" compile_deplibs="$dir/$linklib $compile_deplibs" finalize_deplibs="$dir/$linklib $finalize_deplibs" else compile_deplibs="-l$name -L$dir $compile_deplibs" finalize_deplibs="-l$name -L$dir $finalize_deplibs" fi elif test "$build_libtool_libs" = yes; then # Not a shared library if test "$deplibs_check_method" != pass_all; then # We're trying link a shared library against a static one # but the system doesn't support it. # Just print a warning and add the library to dependency_libs so # that the program can be linked against the static library. echo $ECHO "*** Warning: This system can not link to static lib archive $lib." echo "*** I have the capability to make that library automatically link in when" echo "*** you link to this library. But I can only do this if you have a" echo "*** shared version of the library, which you do not appear to have." if test "$module" = yes; then echo "*** But as you try to build a module library, libtool will still create " echo "*** a static module, that should work as long as the dlopening application" echo "*** is linked with the -dlopen flag to resolve symbols at runtime." if test -z "$global_symbol_pipe"; then echo echo "*** However, this would only work if libtool was able to extract symbol" echo "*** lists from a program, using \`nm' or equivalent, but libtool could" echo "*** not find such a program. So, this module is probably useless." echo "*** \`nm' from GNU binutils and a full rebuild may help." fi if test "$build_old_libs" = no; then build_libtool_libs=module build_old_libs=yes else build_libtool_libs=no fi fi else deplibs="$dir/$old_library $deplibs" link_static=yes fi fi # link shared/static library? if test "$linkmode" = lib; then if test -n "$dependency_libs" && { test "$hardcode_into_libs" != yes || test "$build_old_libs" = yes || test "$link_static" = yes; }; then # Extract -R from dependency_libs temp_deplibs= for libdir in $dependency_libs; do case $libdir in -R*) func_stripname '-R' '' "$libdir" temp_xrpath=$func_stripname_result case " $xrpath " in *" $temp_xrpath "*) ;; *) func_append xrpath " $temp_xrpath";; esac;; *) func_append temp_deplibs " $libdir";; esac done dependency_libs="$temp_deplibs" fi func_append newlib_search_path " $absdir" # Link against this library test "$link_static" = no && newdependency_libs="$abs_ladir/$laname $newdependency_libs" # ... and its dependency_libs tmp_libs= for deplib in $dependency_libs; do newdependency_libs="$deplib $newdependency_libs" case $deplib in -L*) func_stripname '-L' '' "$deplib" func_resolve_sysroot "$func_stripname_result";; *) func_resolve_sysroot "$deplib" ;; esac if $opt_preserve_dup_deps ; then case "$tmp_libs " in *" $func_resolve_sysroot_result "*) func_append specialdeplibs " $func_resolve_sysroot_result" ;; esac fi func_append tmp_libs " $func_resolve_sysroot_result" done if test "$link_all_deplibs" != no; then # Add the search paths of all dependency libraries for deplib in $dependency_libs; do path= case $deplib in -L*) path="$deplib" ;; *.la) func_resolve_sysroot "$deplib" deplib=$func_resolve_sysroot_result func_dirname "$deplib" "" "." dir=$func_dirname_result # We need an absolute path. case $dir in [\\/]* | [A-Za-z]:[\\/]*) absdir="$dir" ;; *) absdir=`cd "$dir" && pwd` if test -z "$absdir"; then func_warning "cannot determine absolute directory name of \`$dir'" absdir="$dir" fi ;; esac if $GREP "^installed=no" $deplib > /dev/null; then case $host in *-*-darwin*) depdepl= eval deplibrary_names=`${SED} -n -e 's/^library_names=\(.*\)$/\1/p' $deplib` if test -n "$deplibrary_names" ; then for tmp in $deplibrary_names ; do depdepl=$tmp done if test -f "$absdir/$objdir/$depdepl" ; then depdepl="$absdir/$objdir/$depdepl" darwin_install_name=`${OTOOL} -L $depdepl | awk '{if (NR == 2) {print $1;exit}}'` if test -z "$darwin_install_name"; then darwin_install_name=`${OTOOL64} -L $depdepl | awk '{if (NR == 2) {print $1;exit}}'` fi func_append compiler_flags " ${wl}-dylib_file ${wl}${darwin_install_name}:${depdepl}" func_append linker_flags " -dylib_file ${darwin_install_name}:${depdepl}" path= fi fi ;; *) path="-L$absdir/$objdir" ;; esac else eval libdir=`${SED} -n -e 's/^libdir=\(.*\)$/\1/p' $deplib` test -z "$libdir" && \ func_fatal_error "\`$deplib' is not a valid libtool archive" test "$absdir" != "$libdir" && \ func_warning "\`$deplib' seems to be moved" path="-L$absdir" fi ;; esac case " $deplibs " in *" $path "*) ;; *) deplibs="$path $deplibs" ;; esac done fi # link_all_deplibs != no fi # linkmode = lib done # for deplib in $libs if test "$pass" = link; then if test "$linkmode" = "prog"; then compile_deplibs="$new_inherited_linker_flags $compile_deplibs" finalize_deplibs="$new_inherited_linker_flags $finalize_deplibs" else compiler_flags="$compiler_flags "`$ECHO " $new_inherited_linker_flags" | $SED 's% \([^ $]*\).ltframework% -framework \1%g'` fi fi dependency_libs="$newdependency_libs" if test "$pass" = dlpreopen; then # Link the dlpreopened libraries before other libraries for deplib in $save_deplibs; do deplibs="$deplib $deplibs" done fi if test "$pass" != dlopen; then if test "$pass" != conv; then # Make sure lib_search_path contains only unique directories. lib_search_path= for dir in $newlib_search_path; do case "$lib_search_path " in *" $dir "*) ;; *) func_append lib_search_path " $dir" ;; esac done newlib_search_path= fi if test "$linkmode,$pass" != "prog,link"; then vars="deplibs" else vars="compile_deplibs finalize_deplibs" fi for var in $vars dependency_libs; do # Add libraries to $var in reverse order eval tmp_libs=\"\$$var\" new_libs= for deplib in $tmp_libs; do # FIXME: Pedantically, this is the right thing to do, so # that some nasty dependency loop isn't accidentally # broken: #new_libs="$deplib $new_libs" # Pragmatically, this seems to cause very few problems in # practice: case $deplib in -L*) new_libs="$deplib $new_libs" ;; -R*) ;; *) # And here is the reason: when a library appears more # than once as an explicit dependence of a library, or # is implicitly linked in more than once by the # compiler, it is considered special, and multiple # occurrences thereof are not removed. Compare this # with having the same library being listed as a # dependency of multiple other libraries: in this case, # we know (pedantically, we assume) the library does not # need to be listed more than once, so we keep only the # last copy. This is not always right, but it is rare # enough that we require users that really mean to play # such unportable linking tricks to link the library # using -Wl,-lname, so that libtool does not consider it # for duplicate removal. case " $specialdeplibs " in *" $deplib "*) new_libs="$deplib $new_libs" ;; *) case " $new_libs " in *" $deplib "*) ;; *) new_libs="$deplib $new_libs" ;; esac ;; esac ;; esac done tmp_libs= for deplib in $new_libs; do case $deplib in -L*) case " $tmp_libs " in *" $deplib "*) ;; *) func_append tmp_libs " $deplib" ;; esac ;; *) func_append tmp_libs " $deplib" ;; esac done eval $var=\"$tmp_libs\" done # for var fi # Last step: remove runtime libs from dependency_libs # (they stay in deplibs) tmp_libs= for i in $dependency_libs ; do case " $predeps $postdeps $compiler_lib_search_path " in *" $i "*) i="" ;; esac if test -n "$i" ; then func_append tmp_libs " $i" fi done dependency_libs=$tmp_libs done # for pass if test "$linkmode" = prog; then dlfiles="$newdlfiles" fi if test "$linkmode" = prog || test "$linkmode" = lib; then dlprefiles="$newdlprefiles" fi case $linkmode in oldlib) if test -n "$dlfiles$dlprefiles" || test "$dlself" != no; then func_warning "\`-dlopen' is ignored for archives" fi case " $deplibs" in *\ -l* | *\ -L*) func_warning "\`-l' and \`-L' are ignored for archives" ;; esac test -n "$rpath" && \ func_warning "\`-rpath' is ignored for archives" test -n "$xrpath" && \ func_warning "\`-R' is ignored for archives" test -n "$vinfo" && \ func_warning "\`-version-info/-version-number' is ignored for archives" test -n "$release" && \ func_warning "\`-release' is ignored for archives" test -n "$export_symbols$export_symbols_regex" && \ func_warning "\`-export-symbols' is ignored for archives" # Now set the variables for building old libraries. build_libtool_libs=no oldlibs="$output" func_append objs "$old_deplibs" ;; lib) # Make sure we only generate libraries of the form `libNAME.la'. case $outputname in lib*) func_stripname 'lib' '.la' "$outputname" name=$func_stripname_result eval shared_ext=\"$shrext_cmds\" eval libname=\"$libname_spec\" ;; *) test "$module" = no && \ func_fatal_help "libtool library \`$output' must begin with \`lib'" if test "$need_lib_prefix" != no; then # Add the "lib" prefix for modules if required func_stripname '' '.la' "$outputname" name=$func_stripname_result eval shared_ext=\"$shrext_cmds\" eval libname=\"$libname_spec\" else func_stripname '' '.la' "$outputname" libname=$func_stripname_result fi ;; esac if test -n "$objs"; then if test "$deplibs_check_method" != pass_all; then func_fatal_error "cannot build libtool library \`$output' from non-libtool objects on this host:$objs" else echo $ECHO "*** Warning: Linking the shared library $output against the non-libtool" $ECHO "*** objects $objs is not portable!" func_append libobjs " $objs" fi fi test "$dlself" != no && \ func_warning "\`-dlopen self' is ignored for libtool libraries" set dummy $rpath shift test "$#" -gt 1 && \ func_warning "ignoring multiple \`-rpath's for a libtool library" install_libdir="$1" oldlibs= if test -z "$rpath"; then if test "$build_libtool_libs" = yes; then # Building a libtool convenience library. # Some compilers have problems with a `.al' extension so # convenience libraries should have the same extension an # archive normally would. oldlibs="$output_objdir/$libname.$libext $oldlibs" build_libtool_libs=convenience build_old_libs=yes fi test -n "$vinfo" && \ func_warning "\`-version-info/-version-number' is ignored for convenience libraries" test -n "$release" && \ func_warning "\`-release' is ignored for convenience libraries" else # Parse the version information argument. save_ifs="$IFS"; IFS=':' set dummy $vinfo 0 0 0 shift IFS="$save_ifs" test -n "$7" && \ func_fatal_help "too many parameters to \`-version-info'" # convert absolute version numbers to libtool ages # this retains compatibility with .la files and attempts # to make the code below a bit more comprehensible case $vinfo_number in yes) number_major="$1" number_minor="$2" number_revision="$3" # # There are really only two kinds -- those that # use the current revision as the major version # and those that subtract age and use age as # a minor version. But, then there is irix # which has an extra 1 added just for fun # case $version_type in # correct linux to gnu/linux during the next big refactor darwin|linux|osf|windows|none) func_arith $number_major + $number_minor current=$func_arith_result age="$number_minor" revision="$number_revision" ;; freebsd-aout|freebsd-elf|qnx|sunos) current="$number_major" revision="$number_minor" age="0" ;; irix|nonstopux) func_arith $number_major + $number_minor current=$func_arith_result age="$number_minor" revision="$number_minor" lt_irix_increment=no ;; *) func_fatal_configuration "$modename: unknown library version type \`$version_type'" ;; esac ;; no) current="$1" revision="$2" age="$3" ;; esac # Check that each of the things are valid numbers. case $current in 0|[1-9]|[1-9][0-9]|[1-9][0-9][0-9]|[1-9][0-9][0-9][0-9]|[1-9][0-9][0-9][0-9][0-9]) ;; *) func_error "CURRENT \`$current' must be a nonnegative integer" func_fatal_error "\`$vinfo' is not valid version information" ;; esac case $revision in 0|[1-9]|[1-9][0-9]|[1-9][0-9][0-9]|[1-9][0-9][0-9][0-9]|[1-9][0-9][0-9][0-9][0-9]) ;; *) func_error "REVISION \`$revision' must be a nonnegative integer" func_fatal_error "\`$vinfo' is not valid version information" ;; esac case $age in 0|[1-9]|[1-9][0-9]|[1-9][0-9][0-9]|[1-9][0-9][0-9][0-9]|[1-9][0-9][0-9][0-9][0-9]) ;; *) func_error "AGE \`$age' must be a nonnegative integer" func_fatal_error "\`$vinfo' is not valid version information" ;; esac if test "$age" -gt "$current"; then func_error "AGE \`$age' is greater than the current interface number \`$current'" func_fatal_error "\`$vinfo' is not valid version information" fi # Calculate the version variables. major= versuffix= verstring= case $version_type in none) ;; darwin) # Like Linux, but with the current version available in # verstring for coding it into the library header func_arith $current - $age major=.$func_arith_result versuffix="$major.$age.$revision" # Darwin ld doesn't like 0 for these options... func_arith $current + 1 minor_current=$func_arith_result xlcverstring="${wl}-compatibility_version ${wl}$minor_current ${wl}-current_version ${wl}$minor_current.$revision" verstring="-compatibility_version $minor_current -current_version $minor_current.$revision" ;; freebsd-aout) major=".$current" versuffix=".$current.$revision"; ;; freebsd-elf) major=".$current" versuffix=".$current" ;; irix | nonstopux) if test "X$lt_irix_increment" = "Xno"; then func_arith $current - $age else func_arith $current - $age + 1 fi major=$func_arith_result case $version_type in nonstopux) verstring_prefix=nonstopux ;; *) verstring_prefix=sgi ;; esac verstring="$verstring_prefix$major.$revision" # Add in all the interfaces that we are compatible with. loop=$revision while test "$loop" -ne 0; do func_arith $revision - $loop iface=$func_arith_result func_arith $loop - 1 loop=$func_arith_result verstring="$verstring_prefix$major.$iface:$verstring" done # Before this point, $major must not contain `.'. major=.$major versuffix="$major.$revision" ;; linux) # correct to gnu/linux during the next big refactor func_arith $current - $age major=.$func_arith_result versuffix="$major.$age.$revision" ;; osf) func_arith $current - $age major=.$func_arith_result versuffix=".$current.$age.$revision" verstring="$current.$age.$revision" # Add in all the interfaces that we are compatible with. loop=$age while test "$loop" -ne 0; do func_arith $current - $loop iface=$func_arith_result func_arith $loop - 1 loop=$func_arith_result verstring="$verstring:${iface}.0" done # Make executables depend on our current version. func_append verstring ":${current}.0" ;; qnx) major=".$current" versuffix=".$current" ;; sunos) major=".$current" versuffix=".$current.$revision" ;; windows) # Use '-' rather than '.', since we only want one # extension on DOS 8.3 filesystems. func_arith $current - $age major=$func_arith_result versuffix="-$major" ;; *) func_fatal_configuration "unknown library version type \`$version_type'" ;; esac # Clear the version info if we defaulted, and they specified a release. if test -z "$vinfo" && test -n "$release"; then major= case $version_type in darwin) # we can't check for "0.0" in archive_cmds due to quoting # problems, so we reset it completely verstring= ;; *) verstring="0.0" ;; esac if test "$need_version" = no; then versuffix= else versuffix=".0.0" fi fi # Remove version info from name if versioning should be avoided if test "$avoid_version" = yes && test "$need_version" = no; then major= versuffix= verstring="" fi # Check to see if the archive will have undefined symbols. if test "$allow_undefined" = yes; then if test "$allow_undefined_flag" = unsupported; then func_warning "undefined symbols not allowed in $host shared libraries" build_libtool_libs=no build_old_libs=yes fi else # Don't allow undefined symbols. allow_undefined_flag="$no_undefined_flag" fi fi func_generate_dlsyms "$libname" "$libname" "yes" func_append libobjs " $symfileobj" test "X$libobjs" = "X " && libobjs= if test "$opt_mode" != relink; then # Remove our outputs, but don't remove object files since they # may have been created when compiling PIC objects. removelist= tempremovelist=`$ECHO "$output_objdir/*"` for p in $tempremovelist; do case $p in *.$objext | *.gcno) ;; $output_objdir/$outputname | $output_objdir/$libname.* | $output_objdir/${libname}${release}.*) if test "X$precious_files_regex" != "X"; then if $ECHO "$p" | $EGREP -e "$precious_files_regex" >/dev/null 2>&1 then continue fi fi func_append removelist " $p" ;; *) ;; esac done test -n "$removelist" && \ func_show_eval "${RM}r \$removelist" fi # Now set the variables for building old libraries. if test "$build_old_libs" = yes && test "$build_libtool_libs" != convenience ; then func_append oldlibs " $output_objdir/$libname.$libext" # Transform .lo files to .o files. oldobjs="$objs "`$ECHO "$libobjs" | $SP2NL | $SED "/\.${libext}$/d; $lo2o" | $NL2SP` fi # Eliminate all temporary directories. #for path in $notinst_path; do # lib_search_path=`$ECHO "$lib_search_path " | $SED "s% $path % %g"` # deplibs=`$ECHO "$deplibs " | $SED "s% -L$path % %g"` # dependency_libs=`$ECHO "$dependency_libs " | $SED "s% -L$path % %g"` #done if test -n "$xrpath"; then # If the user specified any rpath flags, then add them. temp_xrpath= for libdir in $xrpath; do func_replace_sysroot "$libdir" func_append temp_xrpath " -R$func_replace_sysroot_result" case "$finalize_rpath " in *" $libdir "*) ;; *) func_append finalize_rpath " $libdir" ;; esac done if test "$hardcode_into_libs" != yes || test "$build_old_libs" = yes; then dependency_libs="$temp_xrpath $dependency_libs" fi fi # Make sure dlfiles contains only unique files that won't be dlpreopened old_dlfiles="$dlfiles" dlfiles= for lib in $old_dlfiles; do case " $dlprefiles $dlfiles " in *" $lib "*) ;; *) func_append dlfiles " $lib" ;; esac done # Make sure dlprefiles contains only unique files old_dlprefiles="$dlprefiles" dlprefiles= for lib in $old_dlprefiles; do case "$dlprefiles " in *" $lib "*) ;; *) func_append dlprefiles " $lib" ;; esac done if test "$build_libtool_libs" = yes; then if test -n "$rpath"; then case $host in *-*-cygwin* | *-*-mingw* | *-*-pw32* | *-*-os2* | *-*-beos* | *-cegcc* | *-*-haiku*) # these systems don't actually have a c library (as such)! ;; *-*-rhapsody* | *-*-darwin1.[012]) # Rhapsody C library is in the System framework func_append deplibs " System.ltframework" ;; *-*-netbsd*) # Don't link with libc until the a.out ld.so is fixed. ;; *-*-openbsd* | *-*-freebsd* | *-*-dragonfly*) # Do not include libc due to us having libc/libc_r. ;; *-*-sco3.2v5* | *-*-sco5v6*) # Causes problems with __ctype ;; *-*-sysv4.2uw2* | *-*-sysv5* | *-*-unixware* | *-*-OpenUNIX*) # Compiler inserts libc in the correct place for threads to work ;; *) # Add libc to deplibs on all other systems if necessary. if test "$build_libtool_need_lc" = "yes"; then func_append deplibs " -lc" fi ;; esac fi # Transform deplibs into only deplibs that can be linked in shared. name_save=$name libname_save=$libname release_save=$release versuffix_save=$versuffix major_save=$major # I'm not sure if I'm treating the release correctly. I think # release should show up in the -l (ie -lgmp5) so we don't want to # add it in twice. Is that correct? release="" versuffix="" major="" newdeplibs= droppeddeps=no case $deplibs_check_method in pass_all) # Don't check for shared/static. Everything works. # This might be a little naive. We might want to check # whether the library exists or not. But this is on # osf3 & osf4 and I'm not really sure... Just # implementing what was already the behavior. newdeplibs=$deplibs ;; test_compile) # This code stresses the "libraries are programs" paradigm to its # limits. Maybe even breaks it. We compile a program, linking it # against the deplibs as a proxy for the library. Then we can check # whether they linked in statically or dynamically with ldd. $opt_dry_run || $RM conftest.c cat > conftest.c </dev/null` $nocaseglob else potential_libs=`ls $i/$libnameglob[.-]* 2>/dev/null` fi for potent_lib in $potential_libs; do # Follow soft links. if ls -lLd "$potent_lib" 2>/dev/null | $GREP " -> " >/dev/null; then continue fi # The statement above tries to avoid entering an # endless loop below, in case of cyclic links. # We might still enter an endless loop, since a link # loop can be closed while we follow links, # but so what? potlib="$potent_lib" while test -h "$potlib" 2>/dev/null; do potliblink=`ls -ld $potlib | ${SED} 's/.* -> //'` case $potliblink in [\\/]* | [A-Za-z]:[\\/]*) potlib="$potliblink";; *) potlib=`$ECHO "$potlib" | $SED 's,[^/]*$,,'`"$potliblink";; esac done if eval $file_magic_cmd \"\$potlib\" 2>/dev/null | $SED -e 10q | $EGREP "$file_magic_regex" > /dev/null; then func_append newdeplibs " $a_deplib" a_deplib="" break 2 fi done done fi if test -n "$a_deplib" ; then droppeddeps=yes echo $ECHO "*** Warning: linker path does not have real file for library $a_deplib." echo "*** I have the capability to make that library automatically link in when" echo "*** you link to this library. But I can only do this if you have a" echo "*** shared version of the library, which you do not appear to have" echo "*** because I did check the linker path looking for a file starting" if test -z "$potlib" ; then $ECHO "*** with $libname but no candidates were found. (...for file magic test)" else $ECHO "*** with $libname and none of the candidates passed a file format test" $ECHO "*** using a file magic. Last file checked: $potlib" fi fi ;; *) # Add a -L argument. func_append newdeplibs " $a_deplib" ;; esac done # Gone through all deplibs. ;; match_pattern*) set dummy $deplibs_check_method; shift match_pattern_regex=`expr "$deplibs_check_method" : "$1 \(.*\)"` for a_deplib in $deplibs; do case $a_deplib in -l*) func_stripname -l '' "$a_deplib" name=$func_stripname_result if test "X$allow_libtool_libs_with_static_runtimes" = "Xyes" ; then case " $predeps $postdeps " in *" $a_deplib "*) func_append newdeplibs " $a_deplib" a_deplib="" ;; esac fi if test -n "$a_deplib" ; then libname=`eval "\\$ECHO \"$libname_spec\""` for i in $lib_search_path $sys_lib_search_path $shlib_search_path; do potential_libs=`ls $i/$libname[.-]* 2>/dev/null` for potent_lib in $potential_libs; do potlib="$potent_lib" # see symlink-check above in file_magic test if eval "\$ECHO \"$potent_lib\"" 2>/dev/null | $SED 10q | \ $EGREP "$match_pattern_regex" > /dev/null; then func_append newdeplibs " $a_deplib" a_deplib="" break 2 fi done done fi if test -n "$a_deplib" ; then droppeddeps=yes echo $ECHO "*** Warning: linker path does not have real file for library $a_deplib." echo "*** I have the capability to make that library automatically link in when" echo "*** you link to this library. But I can only do this if you have a" echo "*** shared version of the library, which you do not appear to have" echo "*** because I did check the linker path looking for a file starting" if test -z "$potlib" ; then $ECHO "*** with $libname but no candidates were found. (...for regex pattern test)" else $ECHO "*** with $libname and none of the candidates passed a file format test" $ECHO "*** using a regex pattern. Last file checked: $potlib" fi fi ;; *) # Add a -L argument. func_append newdeplibs " $a_deplib" ;; esac done # Gone through all deplibs. ;; none | unknown | *) newdeplibs="" tmp_deplibs=`$ECHO " $deplibs" | $SED 's/ -lc$//; s/ -[LR][^ ]*//g'` if test "X$allow_libtool_libs_with_static_runtimes" = "Xyes" ; then for i in $predeps $postdeps ; do # can't use Xsed below, because $i might contain '/' tmp_deplibs=`$ECHO " $tmp_deplibs" | $SED "s,$i,,"` done fi case $tmp_deplibs in *[!\ \ ]*) echo if test "X$deplibs_check_method" = "Xnone"; then echo "*** Warning: inter-library dependencies are not supported in this platform." else echo "*** Warning: inter-library dependencies are not known to be supported." fi echo "*** All declared inter-library dependencies are being dropped." droppeddeps=yes ;; esac ;; esac versuffix=$versuffix_save major=$major_save release=$release_save libname=$libname_save name=$name_save case $host in *-*-rhapsody* | *-*-darwin1.[012]) # On Rhapsody replace the C library with the System framework newdeplibs=`$ECHO " $newdeplibs" | $SED 's/ -lc / System.ltframework /'` ;; esac if test "$droppeddeps" = yes; then if test "$module" = yes; then echo echo "*** Warning: libtool could not satisfy all declared inter-library" $ECHO "*** dependencies of module $libname. Therefore, libtool will create" echo "*** a static module, that should work as long as the dlopening" echo "*** application is linked with the -dlopen flag." if test -z "$global_symbol_pipe"; then echo echo "*** However, this would only work if libtool was able to extract symbol" echo "*** lists from a program, using \`nm' or equivalent, but libtool could" echo "*** not find such a program. So, this module is probably useless." echo "*** \`nm' from GNU binutils and a full rebuild may help." fi if test "$build_old_libs" = no; then oldlibs="$output_objdir/$libname.$libext" build_libtool_libs=module build_old_libs=yes else build_libtool_libs=no fi else echo "*** The inter-library dependencies that have been dropped here will be" echo "*** automatically added whenever a program is linked with this library" echo "*** or is declared to -dlopen it." if test "$allow_undefined" = no; then echo echo "*** Since this library must not contain undefined symbols," echo "*** because either the platform does not support them or" echo "*** it was explicitly requested with -no-undefined," echo "*** libtool will only create a static version of it." if test "$build_old_libs" = no; then oldlibs="$output_objdir/$libname.$libext" build_libtool_libs=module build_old_libs=yes else build_libtool_libs=no fi fi fi fi # Done checking deplibs! deplibs=$newdeplibs fi # Time to change all our "foo.ltframework" stuff back to "-framework foo" case $host in *-*-darwin*) newdeplibs=`$ECHO " $newdeplibs" | $SED 's% \([^ $]*\).ltframework% -framework \1%g'` new_inherited_linker_flags=`$ECHO " $new_inherited_linker_flags" | $SED 's% \([^ $]*\).ltframework% -framework \1%g'` deplibs=`$ECHO " $deplibs" | $SED 's% \([^ $]*\).ltframework% -framework \1%g'` ;; esac # move library search paths that coincide with paths to not yet # installed libraries to the beginning of the library search list new_libs= for path in $notinst_path; do case " $new_libs " in *" -L$path/$objdir "*) ;; *) case " $deplibs " in *" -L$path/$objdir "*) func_append new_libs " -L$path/$objdir" ;; esac ;; esac done for deplib in $deplibs; do case $deplib in -L*) case " $new_libs " in *" $deplib "*) ;; *) func_append new_libs " $deplib" ;; esac ;; *) func_append new_libs " $deplib" ;; esac done deplibs="$new_libs" # All the library-specific variables (install_libdir is set above). library_names= old_library= dlname= # Test again, we may have decided not to build it any more if test "$build_libtool_libs" = yes; then # Remove ${wl} instances when linking with ld. # FIXME: should test the right _cmds variable. case $archive_cmds in *\$LD\ *) wl= ;; esac if test "$hardcode_into_libs" = yes; then # Hardcode the library paths hardcode_libdirs= dep_rpath= rpath="$finalize_rpath" test "$opt_mode" != relink && rpath="$compile_rpath$rpath" for libdir in $rpath; do if test -n "$hardcode_libdir_flag_spec"; then if test -n "$hardcode_libdir_separator"; then func_replace_sysroot "$libdir" libdir=$func_replace_sysroot_result if test -z "$hardcode_libdirs"; then hardcode_libdirs="$libdir" else # Just accumulate the unique libdirs. case $hardcode_libdir_separator$hardcode_libdirs$hardcode_libdir_separator in *"$hardcode_libdir_separator$libdir$hardcode_libdir_separator"*) ;; *) func_append hardcode_libdirs "$hardcode_libdir_separator$libdir" ;; esac fi else eval flag=\"$hardcode_libdir_flag_spec\" func_append dep_rpath " $flag" fi elif test -n "$runpath_var"; then case "$perm_rpath " in *" $libdir "*) ;; *) func_append perm_rpath " $libdir" ;; esac fi done # Substitute the hardcoded libdirs into the rpath. if test -n "$hardcode_libdir_separator" && test -n "$hardcode_libdirs"; then libdir="$hardcode_libdirs" eval "dep_rpath=\"$hardcode_libdir_flag_spec\"" fi if test -n "$runpath_var" && test -n "$perm_rpath"; then # We should set the runpath_var. rpath= for dir in $perm_rpath; do func_append rpath "$dir:" done eval "$runpath_var='$rpath\$$runpath_var'; export $runpath_var" fi test -n "$dep_rpath" && deplibs="$dep_rpath $deplibs" fi shlibpath="$finalize_shlibpath" test "$opt_mode" != relink && shlibpath="$compile_shlibpath$shlibpath" if test -n "$shlibpath"; then eval "$shlibpath_var='$shlibpath\$$shlibpath_var'; export $shlibpath_var" fi # Get the real and link names of the library. eval shared_ext=\"$shrext_cmds\" eval library_names=\"$library_names_spec\" set dummy $library_names shift realname="$1" shift if test -n "$soname_spec"; then eval soname=\"$soname_spec\" else soname="$realname" fi if test -z "$dlname"; then dlname=$soname fi lib="$output_objdir/$realname" linknames= for link do func_append linknames " $link" done # Use standard objects if they are pic test -z "$pic_flag" && libobjs=`$ECHO "$libobjs" | $SP2NL | $SED "$lo2o" | $NL2SP` test "X$libobjs" = "X " && libobjs= delfiles= if test -n "$export_symbols" && test -n "$include_expsyms"; then $opt_dry_run || cp "$export_symbols" "$output_objdir/$libname.uexp" export_symbols="$output_objdir/$libname.uexp" func_append delfiles " $export_symbols" fi orig_export_symbols= case $host_os in cygwin* | mingw* | cegcc*) if test -n "$export_symbols" && test -z "$export_symbols_regex"; then # exporting using user supplied symfile if test "x`$SED 1q $export_symbols`" != xEXPORTS; then # and it's NOT already a .def file. Must figure out # which of the given symbols are data symbols and tag # them as such. So, trigger use of export_symbols_cmds. # export_symbols gets reassigned inside the "prepare # the list of exported symbols" if statement, so the # include_expsyms logic still works. orig_export_symbols="$export_symbols" export_symbols= always_export_symbols=yes fi fi ;; esac # Prepare the list of exported symbols if test -z "$export_symbols"; then if test "$always_export_symbols" = yes || test -n "$export_symbols_regex"; then func_verbose "generating symbol list for \`$libname.la'" export_symbols="$output_objdir/$libname.exp" $opt_dry_run || $RM $export_symbols cmds=$export_symbols_cmds save_ifs="$IFS"; IFS='~' for cmd1 in $cmds; do IFS="$save_ifs" # Take the normal branch if the nm_file_list_spec branch # doesn't work or if tool conversion is not needed. case $nm_file_list_spec~$to_tool_file_cmd in *~func_convert_file_noop | *~func_convert_file_msys_to_w32 | ~*) try_normal_branch=yes eval cmd=\"$cmd1\" func_len " $cmd" len=$func_len_result ;; *) try_normal_branch=no ;; esac if test "$try_normal_branch" = yes \ && { test "$len" -lt "$max_cmd_len" \ || test "$max_cmd_len" -le -1; } then func_show_eval "$cmd" 'exit $?' skipped_export=false elif test -n "$nm_file_list_spec"; then func_basename "$output" output_la=$func_basename_result save_libobjs=$libobjs save_output=$output output=${output_objdir}/${output_la}.nm func_to_tool_file "$output" libobjs=$nm_file_list_spec$func_to_tool_file_result func_append delfiles " $output" func_verbose "creating $NM input file list: $output" for obj in $save_libobjs; do func_to_tool_file "$obj" $ECHO "$func_to_tool_file_result" done > "$output" eval cmd=\"$cmd1\" func_show_eval "$cmd" 'exit $?' output=$save_output libobjs=$save_libobjs skipped_export=false else # The command line is too long to execute in one step. func_verbose "using reloadable object file for export list..." skipped_export=: # Break out early, otherwise skipped_export may be # set to false by a later but shorter cmd. break fi done IFS="$save_ifs" if test -n "$export_symbols_regex" && test "X$skipped_export" != "X:"; then func_show_eval '$EGREP -e "$export_symbols_regex" "$export_symbols" > "${export_symbols}T"' func_show_eval '$MV "${export_symbols}T" "$export_symbols"' fi fi fi if test -n "$export_symbols" && test -n "$include_expsyms"; then tmp_export_symbols="$export_symbols" test -n "$orig_export_symbols" && tmp_export_symbols="$orig_export_symbols" $opt_dry_run || eval '$ECHO "$include_expsyms" | $SP2NL >> "$tmp_export_symbols"' fi if test "X$skipped_export" != "X:" && test -n "$orig_export_symbols"; then # The given exports_symbols file has to be filtered, so filter it. func_verbose "filter symbol list for \`$libname.la' to tag DATA exports" # FIXME: $output_objdir/$libname.filter potentially contains lots of # 's' commands which not all seds can handle. GNU sed should be fine # though. Also, the filter scales superlinearly with the number of # global variables. join(1) would be nice here, but unfortunately # isn't a blessed tool. $opt_dry_run || $SED -e '/[ ,]DATA/!d;s,\(.*\)\([ \,].*\),s|^\1$|\1\2|,' < $export_symbols > $output_objdir/$libname.filter func_append delfiles " $export_symbols $output_objdir/$libname.filter" export_symbols=$output_objdir/$libname.def $opt_dry_run || $SED -f $output_objdir/$libname.filter < $orig_export_symbols > $export_symbols fi tmp_deplibs= for test_deplib in $deplibs; do case " $convenience " in *" $test_deplib "*) ;; *) func_append tmp_deplibs " $test_deplib" ;; esac done deplibs="$tmp_deplibs" if test -n "$convenience"; then if test -n "$whole_archive_flag_spec" && test "$compiler_needs_object" = yes && test -z "$libobjs"; then # extract the archives, so we have objects to list. # TODO: could optimize this to just extract one archive. whole_archive_flag_spec= fi if test -n "$whole_archive_flag_spec"; then save_libobjs=$libobjs eval libobjs=\"\$libobjs $whole_archive_flag_spec\" test "X$libobjs" = "X " && libobjs= else gentop="$output_objdir/${outputname}x" func_append generated " $gentop" func_extract_archives $gentop $convenience func_append libobjs " $func_extract_archives_result" test "X$libobjs" = "X " && libobjs= fi fi if test "$thread_safe" = yes && test -n "$thread_safe_flag_spec"; then eval flag=\"$thread_safe_flag_spec\" func_append linker_flags " $flag" fi # Make a backup of the uninstalled library when relinking if test "$opt_mode" = relink; then $opt_dry_run || eval '(cd $output_objdir && $RM ${realname}U && $MV $realname ${realname}U)' || exit $? fi # Do each of the archive commands. if test "$module" = yes && test -n "$module_cmds" ; then if test -n "$export_symbols" && test -n "$module_expsym_cmds"; then eval test_cmds=\"$module_expsym_cmds\" cmds=$module_expsym_cmds else eval test_cmds=\"$module_cmds\" cmds=$module_cmds fi else if test -n "$export_symbols" && test -n "$archive_expsym_cmds"; then eval test_cmds=\"$archive_expsym_cmds\" cmds=$archive_expsym_cmds else eval test_cmds=\"$archive_cmds\" cmds=$archive_cmds fi fi if test "X$skipped_export" != "X:" && func_len " $test_cmds" && len=$func_len_result && test "$len" -lt "$max_cmd_len" || test "$max_cmd_len" -le -1; then : else # The command line is too long to link in one step, link piecewise # or, if using GNU ld and skipped_export is not :, use a linker # script. # Save the value of $output and $libobjs because we want to # use them later. If we have whole_archive_flag_spec, we # want to use save_libobjs as it was before # whole_archive_flag_spec was expanded, because we can't # assume the linker understands whole_archive_flag_spec. # This may have to be revisited, in case too many # convenience libraries get linked in and end up exceeding # the spec. if test -z "$convenience" || test -z "$whole_archive_flag_spec"; then save_libobjs=$libobjs fi save_output=$output func_basename "$output" output_la=$func_basename_result # Clear the reloadable object creation command queue and # initialize k to one. test_cmds= concat_cmds= objlist= last_robj= k=1 if test -n "$save_libobjs" && test "X$skipped_export" != "X:" && test "$with_gnu_ld" = yes; then output=${output_objdir}/${output_la}.lnkscript func_verbose "creating GNU ld script: $output" echo 'INPUT (' > $output for obj in $save_libobjs do func_to_tool_file "$obj" $ECHO "$func_to_tool_file_result" >> $output done echo ')' >> $output func_append delfiles " $output" func_to_tool_file "$output" output=$func_to_tool_file_result elif test -n "$save_libobjs" && test "X$skipped_export" != "X:" && test "X$file_list_spec" != X; then output=${output_objdir}/${output_la}.lnk func_verbose "creating linker input file list: $output" : > $output set x $save_libobjs shift firstobj= if test "$compiler_needs_object" = yes; then firstobj="$1 " shift fi for obj do func_to_tool_file "$obj" $ECHO "$func_to_tool_file_result" >> $output done func_append delfiles " $output" func_to_tool_file "$output" output=$firstobj\"$file_list_spec$func_to_tool_file_result\" else if test -n "$save_libobjs"; then func_verbose "creating reloadable object files..." output=$output_objdir/$output_la-${k}.$objext eval test_cmds=\"$reload_cmds\" func_len " $test_cmds" len0=$func_len_result len=$len0 # Loop over the list of objects to be linked. for obj in $save_libobjs do func_len " $obj" func_arith $len + $func_len_result len=$func_arith_result if test "X$objlist" = X || test "$len" -lt "$max_cmd_len"; then func_append objlist " $obj" else # The command $test_cmds is almost too long, add a # command to the queue. if test "$k" -eq 1 ; then # The first file doesn't have a previous command to add. reload_objs=$objlist eval concat_cmds=\"$reload_cmds\" else # All subsequent reloadable object files will link in # the last one created. reload_objs="$objlist $last_robj" eval concat_cmds=\"\$concat_cmds~$reload_cmds~\$RM $last_robj\" fi last_robj=$output_objdir/$output_la-${k}.$objext func_arith $k + 1 k=$func_arith_result output=$output_objdir/$output_la-${k}.$objext objlist=" $obj" func_len " $last_robj" func_arith $len0 + $func_len_result len=$func_arith_result fi done # Handle the remaining objects by creating one last # reloadable object file. All subsequent reloadable object # files will link in the last one created. test -z "$concat_cmds" || concat_cmds=$concat_cmds~ reload_objs="$objlist $last_robj" eval concat_cmds=\"\${concat_cmds}$reload_cmds\" if test -n "$last_robj"; then eval concat_cmds=\"\${concat_cmds}~\$RM $last_robj\" fi func_append delfiles " $output" else output= fi if ${skipped_export-false}; then func_verbose "generating symbol list for \`$libname.la'" export_symbols="$output_objdir/$libname.exp" $opt_dry_run || $RM $export_symbols libobjs=$output # Append the command to create the export file. test -z "$concat_cmds" || concat_cmds=$concat_cmds~ eval concat_cmds=\"\$concat_cmds$export_symbols_cmds\" if test -n "$last_robj"; then eval concat_cmds=\"\$concat_cmds~\$RM $last_robj\" fi fi test -n "$save_libobjs" && func_verbose "creating a temporary reloadable object file: $output" # Loop through the commands generated above and execute them. save_ifs="$IFS"; IFS='~' for cmd in $concat_cmds; do IFS="$save_ifs" $opt_silent || { func_quote_for_expand "$cmd" eval "func_echo $func_quote_for_expand_result" } $opt_dry_run || eval "$cmd" || { lt_exit=$? # Restore the uninstalled library and exit if test "$opt_mode" = relink; then ( cd "$output_objdir" && \ $RM "${realname}T" && \ $MV "${realname}U" "$realname" ) fi exit $lt_exit } done IFS="$save_ifs" if test -n "$export_symbols_regex" && ${skipped_export-false}; then func_show_eval '$EGREP -e "$export_symbols_regex" "$export_symbols" > "${export_symbols}T"' func_show_eval '$MV "${export_symbols}T" "$export_symbols"' fi fi if ${skipped_export-false}; then if test -n "$export_symbols" && test -n "$include_expsyms"; then tmp_export_symbols="$export_symbols" test -n "$orig_export_symbols" && tmp_export_symbols="$orig_export_symbols" $opt_dry_run || eval '$ECHO "$include_expsyms" | $SP2NL >> "$tmp_export_symbols"' fi if test -n "$orig_export_symbols"; then # The given exports_symbols file has to be filtered, so filter it. func_verbose "filter symbol list for \`$libname.la' to tag DATA exports" # FIXME: $output_objdir/$libname.filter potentially contains lots of # 's' commands which not all seds can handle. GNU sed should be fine # though. Also, the filter scales superlinearly with the number of # global variables. join(1) would be nice here, but unfortunately # isn't a blessed tool. $opt_dry_run || $SED -e '/[ ,]DATA/!d;s,\(.*\)\([ \,].*\),s|^\1$|\1\2|,' < $export_symbols > $output_objdir/$libname.filter func_append delfiles " $export_symbols $output_objdir/$libname.filter" export_symbols=$output_objdir/$libname.def $opt_dry_run || $SED -f $output_objdir/$libname.filter < $orig_export_symbols > $export_symbols fi fi libobjs=$output # Restore the value of output. output=$save_output if test -n "$convenience" && test -n "$whole_archive_flag_spec"; then eval libobjs=\"\$libobjs $whole_archive_flag_spec\" test "X$libobjs" = "X " && libobjs= fi # Expand the library linking commands again to reset the # value of $libobjs for piecewise linking. # Do each of the archive commands. if test "$module" = yes && test -n "$module_cmds" ; then if test -n "$export_symbols" && test -n "$module_expsym_cmds"; then cmds=$module_expsym_cmds else cmds=$module_cmds fi else if test -n "$export_symbols" && test -n "$archive_expsym_cmds"; then cmds=$archive_expsym_cmds else cmds=$archive_cmds fi fi fi if test -n "$delfiles"; then # Append the command to remove temporary files to $cmds. eval cmds=\"\$cmds~\$RM $delfiles\" fi # Add any objects from preloaded convenience libraries if test -n "$dlprefiles"; then gentop="$output_objdir/${outputname}x" func_append generated " $gentop" func_extract_archives $gentop $dlprefiles func_append libobjs " $func_extract_archives_result" test "X$libobjs" = "X " && libobjs= fi save_ifs="$IFS"; IFS='~' for cmd in $cmds; do IFS="$save_ifs" eval cmd=\"$cmd\" $opt_silent || { func_quote_for_expand "$cmd" eval "func_echo $func_quote_for_expand_result" } $opt_dry_run || eval "$cmd" || { lt_exit=$? # Restore the uninstalled library and exit if test "$opt_mode" = relink; then ( cd "$output_objdir" && \ $RM "${realname}T" && \ $MV "${realname}U" "$realname" ) fi exit $lt_exit } done IFS="$save_ifs" # Restore the uninstalled library and exit if test "$opt_mode" = relink; then $opt_dry_run || eval '(cd $output_objdir && $RM ${realname}T && $MV $realname ${realname}T && $MV ${realname}U $realname)' || exit $? if test -n "$convenience"; then if test -z "$whole_archive_flag_spec"; then func_show_eval '${RM}r "$gentop"' fi fi exit $EXIT_SUCCESS fi # Create links to the real library. for linkname in $linknames; do if test "$realname" != "$linkname"; then func_show_eval '(cd "$output_objdir" && $RM "$linkname" && $LN_S "$realname" "$linkname")' 'exit $?' fi done # If -module or -export-dynamic was specified, set the dlname. if test "$module" = yes || test "$export_dynamic" = yes; then # On all known operating systems, these are identical. dlname="$soname" fi fi ;; obj) if test -n "$dlfiles$dlprefiles" || test "$dlself" != no; then func_warning "\`-dlopen' is ignored for objects" fi case " $deplibs" in *\ -l* | *\ -L*) func_warning "\`-l' and \`-L' are ignored for objects" ;; esac test -n "$rpath" && \ func_warning "\`-rpath' is ignored for objects" test -n "$xrpath" && \ func_warning "\`-R' is ignored for objects" test -n "$vinfo" && \ func_warning "\`-version-info' is ignored for objects" test -n "$release" && \ func_warning "\`-release' is ignored for objects" case $output in *.lo) test -n "$objs$old_deplibs" && \ func_fatal_error "cannot build library object \`$output' from non-libtool objects" libobj=$output func_lo2o "$libobj" obj=$func_lo2o_result ;; *) libobj= obj="$output" ;; esac # Delete the old objects. $opt_dry_run || $RM $obj $libobj # Objects from convenience libraries. This assumes # single-version convenience libraries. Whenever we create # different ones for PIC/non-PIC, this we'll have to duplicate # the extraction. reload_conv_objs= gentop= # reload_cmds runs $LD directly, so let us get rid of # -Wl from whole_archive_flag_spec and hope we can get by with # turning comma into space.. wl= if test -n "$convenience"; then if test -n "$whole_archive_flag_spec"; then eval tmp_whole_archive_flags=\"$whole_archive_flag_spec\" reload_conv_objs=$reload_objs\ `$ECHO "$tmp_whole_archive_flags" | $SED 's|,| |g'` else gentop="$output_objdir/${obj}x" func_append generated " $gentop" func_extract_archives $gentop $convenience reload_conv_objs="$reload_objs $func_extract_archives_result" fi fi # If we're not building shared, we need to use non_pic_objs test "$build_libtool_libs" != yes && libobjs="$non_pic_objects" # Create the old-style object. reload_objs="$objs$old_deplibs "`$ECHO "$libobjs" | $SP2NL | $SED "/\.${libext}$/d; /\.lib$/d; $lo2o" | $NL2SP`" $reload_conv_objs" ### testsuite: skip nested quoting test output="$obj" func_execute_cmds "$reload_cmds" 'exit $?' # Exit if we aren't doing a library object file. if test -z "$libobj"; then if test -n "$gentop"; then func_show_eval '${RM}r "$gentop"' fi exit $EXIT_SUCCESS fi if test "$build_libtool_libs" != yes; then if test -n "$gentop"; then func_show_eval '${RM}r "$gentop"' fi # Create an invalid libtool object if no PIC, so that we don't # accidentally link it into a program. # $show "echo timestamp > $libobj" # $opt_dry_run || eval "echo timestamp > $libobj" || exit $? exit $EXIT_SUCCESS fi if test -n "$pic_flag" || test "$pic_mode" != default; then # Only do commands if we really have different PIC objects. reload_objs="$libobjs $reload_conv_objs" output="$libobj" func_execute_cmds "$reload_cmds" 'exit $?' fi if test -n "$gentop"; then func_show_eval '${RM}r "$gentop"' fi exit $EXIT_SUCCESS ;; prog) case $host in *cygwin*) func_stripname '' '.exe' "$output" output=$func_stripname_result.exe;; esac test -n "$vinfo" && \ func_warning "\`-version-info' is ignored for programs" test -n "$release" && \ func_warning "\`-release' is ignored for programs" test "$preload" = yes \ && test "$dlopen_support" = unknown \ && test "$dlopen_self" = unknown \ && test "$dlopen_self_static" = unknown && \ func_warning "\`LT_INIT([dlopen])' not used. Assuming no dlopen support." case $host in *-*-rhapsody* | *-*-darwin1.[012]) # On Rhapsody replace the C library is the System framework compile_deplibs=`$ECHO " $compile_deplibs" | $SED 's/ -lc / System.ltframework /'` finalize_deplibs=`$ECHO " $finalize_deplibs" | $SED 's/ -lc / System.ltframework /'` ;; esac case $host in *-*-darwin*) # Don't allow lazy linking, it breaks C++ global constructors # But is supposedly fixed on 10.4 or later (yay!). if test "$tagname" = CXX ; then case ${MACOSX_DEPLOYMENT_TARGET-10.0} in 10.[0123]) func_append compile_command " ${wl}-bind_at_load" func_append finalize_command " ${wl}-bind_at_load" ;; esac fi # Time to change all our "foo.ltframework" stuff back to "-framework foo" compile_deplibs=`$ECHO " $compile_deplibs" | $SED 's% \([^ $]*\).ltframework% -framework \1%g'` finalize_deplibs=`$ECHO " $finalize_deplibs" | $SED 's% \([^ $]*\).ltframework% -framework \1%g'` ;; esac # move library search paths that coincide with paths to not yet # installed libraries to the beginning of the library search list new_libs= for path in $notinst_path; do case " $new_libs " in *" -L$path/$objdir "*) ;; *) case " $compile_deplibs " in *" -L$path/$objdir "*) func_append new_libs " -L$path/$objdir" ;; esac ;; esac done for deplib in $compile_deplibs; do case $deplib in -L*) case " $new_libs " in *" $deplib "*) ;; *) func_append new_libs " $deplib" ;; esac ;; *) func_append new_libs " $deplib" ;; esac done compile_deplibs="$new_libs" func_append compile_command " $compile_deplibs" func_append finalize_command " $finalize_deplibs" if test -n "$rpath$xrpath"; then # If the user specified any rpath flags, then add them. for libdir in $rpath $xrpath; do # This is the magic to use -rpath. case "$finalize_rpath " in *" $libdir "*) ;; *) func_append finalize_rpath " $libdir" ;; esac done fi # Now hardcode the library paths rpath= hardcode_libdirs= for libdir in $compile_rpath $finalize_rpath; do if test -n "$hardcode_libdir_flag_spec"; then if test -n "$hardcode_libdir_separator"; then if test -z "$hardcode_libdirs"; then hardcode_libdirs="$libdir" else # Just accumulate the unique libdirs. case $hardcode_libdir_separator$hardcode_libdirs$hardcode_libdir_separator in *"$hardcode_libdir_separator$libdir$hardcode_libdir_separator"*) ;; *) func_append hardcode_libdirs "$hardcode_libdir_separator$libdir" ;; esac fi else eval flag=\"$hardcode_libdir_flag_spec\" func_append rpath " $flag" fi elif test -n "$runpath_var"; then case "$perm_rpath " in *" $libdir "*) ;; *) func_append perm_rpath " $libdir" ;; esac fi case $host in *-*-cygwin* | *-*-mingw* | *-*-pw32* | *-*-os2* | *-cegcc*) testbindir=`${ECHO} "$libdir" | ${SED} -e 's*/lib$*/bin*'` case :$dllsearchpath: in *":$libdir:"*) ;; ::) dllsearchpath=$libdir;; *) func_append dllsearchpath ":$libdir";; esac case :$dllsearchpath: in *":$testbindir:"*) ;; ::) dllsearchpath=$testbindir;; *) func_append dllsearchpath ":$testbindir";; esac ;; esac done # Substitute the hardcoded libdirs into the rpath. if test -n "$hardcode_libdir_separator" && test -n "$hardcode_libdirs"; then libdir="$hardcode_libdirs" eval rpath=\" $hardcode_libdir_flag_spec\" fi compile_rpath="$rpath" rpath= hardcode_libdirs= for libdir in $finalize_rpath; do if test -n "$hardcode_libdir_flag_spec"; then if test -n "$hardcode_libdir_separator"; then if test -z "$hardcode_libdirs"; then hardcode_libdirs="$libdir" else # Just accumulate the unique libdirs. case $hardcode_libdir_separator$hardcode_libdirs$hardcode_libdir_separator in *"$hardcode_libdir_separator$libdir$hardcode_libdir_separator"*) ;; *) func_append hardcode_libdirs "$hardcode_libdir_separator$libdir" ;; esac fi else eval flag=\"$hardcode_libdir_flag_spec\" func_append rpath " $flag" fi elif test -n "$runpath_var"; then case "$finalize_perm_rpath " in *" $libdir "*) ;; *) func_append finalize_perm_rpath " $libdir" ;; esac fi done # Substitute the hardcoded libdirs into the rpath. if test -n "$hardcode_libdir_separator" && test -n "$hardcode_libdirs"; then libdir="$hardcode_libdirs" eval rpath=\" $hardcode_libdir_flag_spec\" fi finalize_rpath="$rpath" if test -n "$libobjs" && test "$build_old_libs" = yes; then # Transform all the library objects into standard objects. compile_command=`$ECHO "$compile_command" | $SP2NL | $SED "$lo2o" | $NL2SP` finalize_command=`$ECHO "$finalize_command" | $SP2NL | $SED "$lo2o" | $NL2SP` fi func_generate_dlsyms "$outputname" "@PROGRAM@" "no" # template prelinking step if test -n "$prelink_cmds"; then func_execute_cmds "$prelink_cmds" 'exit $?' fi wrappers_required=yes case $host in *cegcc* | *mingw32ce*) # Disable wrappers for cegcc and mingw32ce hosts, we are cross compiling anyway. wrappers_required=no ;; *cygwin* | *mingw* ) if test "$build_libtool_libs" != yes; then wrappers_required=no fi ;; *) if test "$need_relink" = no || test "$build_libtool_libs" != yes; then wrappers_required=no fi ;; esac if test "$wrappers_required" = no; then # Replace the output file specification. compile_command=`$ECHO "$compile_command" | $SED 's%@OUTPUT@%'"$output"'%g'` link_command="$compile_command$compile_rpath" # We have no uninstalled library dependencies, so finalize right now. exit_status=0 func_show_eval "$link_command" 'exit_status=$?' if test -n "$postlink_cmds"; then func_to_tool_file "$output" postlink_cmds=`func_echo_all "$postlink_cmds" | $SED -e 's%@OUTPUT@%'"$output"'%g' -e 's%@TOOL_OUTPUT@%'"$func_to_tool_file_result"'%g'` func_execute_cmds "$postlink_cmds" 'exit $?' fi # Delete the generated files. if test -f "$output_objdir/${outputname}S.${objext}"; then func_show_eval '$RM "$output_objdir/${outputname}S.${objext}"' fi exit $exit_status fi if test -n "$compile_shlibpath$finalize_shlibpath"; then compile_command="$shlibpath_var=\"$compile_shlibpath$finalize_shlibpath\$$shlibpath_var\" $compile_command" fi if test -n "$finalize_shlibpath"; then finalize_command="$shlibpath_var=\"$finalize_shlibpath\$$shlibpath_var\" $finalize_command" fi compile_var= finalize_var= if test -n "$runpath_var"; then if test -n "$perm_rpath"; then # We should set the runpath_var. rpath= for dir in $perm_rpath; do func_append rpath "$dir:" done compile_var="$runpath_var=\"$rpath\$$runpath_var\" " fi if test -n "$finalize_perm_rpath"; then # We should set the runpath_var. rpath= for dir in $finalize_perm_rpath; do func_append rpath "$dir:" done finalize_var="$runpath_var=\"$rpath\$$runpath_var\" " fi fi if test "$no_install" = yes; then # We don't need to create a wrapper script. link_command="$compile_var$compile_command$compile_rpath" # Replace the output file specification. link_command=`$ECHO "$link_command" | $SED 's%@OUTPUT@%'"$output"'%g'` # Delete the old output file. $opt_dry_run || $RM $output # Link the executable and exit func_show_eval "$link_command" 'exit $?' if test -n "$postlink_cmds"; then func_to_tool_file "$output" postlink_cmds=`func_echo_all "$postlink_cmds" | $SED -e 's%@OUTPUT@%'"$output"'%g' -e 's%@TOOL_OUTPUT@%'"$func_to_tool_file_result"'%g'` func_execute_cmds "$postlink_cmds" 'exit $?' fi exit $EXIT_SUCCESS fi if test "$hardcode_action" = relink; then # Fast installation is not supported link_command="$compile_var$compile_command$compile_rpath" relink_command="$finalize_var$finalize_command$finalize_rpath" func_warning "this platform does not like uninstalled shared libraries" func_warning "\`$output' will be relinked during installation" else if test "$fast_install" != no; then link_command="$finalize_var$compile_command$finalize_rpath" if test "$fast_install" = yes; then relink_command=`$ECHO "$compile_var$compile_command$compile_rpath" | $SED 's%@OUTPUT@%\$progdir/\$file%g'` else # fast_install is set to needless relink_command= fi else link_command="$compile_var$compile_command$compile_rpath" relink_command="$finalize_var$finalize_command$finalize_rpath" fi fi # Replace the output file specification. link_command=`$ECHO "$link_command" | $SED 's%@OUTPUT@%'"$output_objdir/$outputname"'%g'` # Delete the old output files. $opt_dry_run || $RM $output $output_objdir/$outputname $output_objdir/lt-$outputname func_show_eval "$link_command" 'exit $?' if test -n "$postlink_cmds"; then func_to_tool_file "$output_objdir/$outputname" postlink_cmds=`func_echo_all "$postlink_cmds" | $SED -e 's%@OUTPUT@%'"$output_objdir/$outputname"'%g' -e 's%@TOOL_OUTPUT@%'"$func_to_tool_file_result"'%g'` func_execute_cmds "$postlink_cmds" 'exit $?' fi # Now create the wrapper script. func_verbose "creating $output" # Quote the relink command for shipping. if test -n "$relink_command"; then # Preserve any variables that may affect compiler behavior for var in $variables_saved_for_relink; do if eval test -z \"\${$var+set}\"; then relink_command="{ test -z \"\${$var+set}\" || $lt_unset $var || { $var=; export $var; }; }; $relink_command" elif eval var_value=\$$var; test -z "$var_value"; then relink_command="$var=; export $var; $relink_command" else func_quote_for_eval "$var_value" relink_command="$var=$func_quote_for_eval_result; export $var; $relink_command" fi done relink_command="(cd `pwd`; $relink_command)" relink_command=`$ECHO "$relink_command" | $SED "$sed_quote_subst"` fi # Only actually do things if not in dry run mode. $opt_dry_run || { # win32 will think the script is a binary if it has # a .exe suffix, so we strip it off here. case $output in *.exe) func_stripname '' '.exe' "$output" output=$func_stripname_result ;; esac # test for cygwin because mv fails w/o .exe extensions case $host in *cygwin*) exeext=.exe func_stripname '' '.exe' "$outputname" outputname=$func_stripname_result ;; *) exeext= ;; esac case $host in *cygwin* | *mingw* ) func_dirname_and_basename "$output" "" "." output_name=$func_basename_result output_path=$func_dirname_result cwrappersource="$output_path/$objdir/lt-$output_name.c" cwrapper="$output_path/$output_name.exe" $RM $cwrappersource $cwrapper trap "$RM $cwrappersource $cwrapper; exit $EXIT_FAILURE" 1 2 15 func_emit_cwrapperexe_src > $cwrappersource # The wrapper executable is built using the $host compiler, # because it contains $host paths and files. If cross- # compiling, it, like the target executable, must be # executed on the $host or under an emulation environment. $opt_dry_run || { $LTCC $LTCFLAGS -o $cwrapper $cwrappersource $STRIP $cwrapper } # Now, create the wrapper script for func_source use: func_ltwrapper_scriptname $cwrapper $RM $func_ltwrapper_scriptname_result trap "$RM $func_ltwrapper_scriptname_result; exit $EXIT_FAILURE" 1 2 15 $opt_dry_run || { # note: this script will not be executed, so do not chmod. if test "x$build" = "x$host" ; then $cwrapper --lt-dump-script > $func_ltwrapper_scriptname_result else func_emit_wrapper no > $func_ltwrapper_scriptname_result fi } ;; * ) $RM $output trap "$RM $output; exit $EXIT_FAILURE" 1 2 15 func_emit_wrapper no > $output chmod +x $output ;; esac } exit $EXIT_SUCCESS ;; esac # See if we need to build an old-fashioned archive. for oldlib in $oldlibs; do if test "$build_libtool_libs" = convenience; then oldobjs="$libobjs_save $symfileobj" addlibs="$convenience" build_libtool_libs=no else if test "$build_libtool_libs" = module; then oldobjs="$libobjs_save" build_libtool_libs=no else oldobjs="$old_deplibs $non_pic_objects" if test "$preload" = yes && test -f "$symfileobj"; then func_append oldobjs " $symfileobj" fi fi addlibs="$old_convenience" fi if test -n "$addlibs"; then gentop="$output_objdir/${outputname}x" func_append generated " $gentop" func_extract_archives $gentop $addlibs func_append oldobjs " $func_extract_archives_result" fi # Do each command in the archive commands. if test -n "$old_archive_from_new_cmds" && test "$build_libtool_libs" = yes; then cmds=$old_archive_from_new_cmds else # Add any objects from preloaded convenience libraries if test -n "$dlprefiles"; then gentop="$output_objdir/${outputname}x" func_append generated " $gentop" func_extract_archives $gentop $dlprefiles func_append oldobjs " $func_extract_archives_result" fi # POSIX demands no paths to be encoded in archives. We have # to avoid creating archives with duplicate basenames if we # might have to extract them afterwards, e.g., when creating a # static archive out of a convenience library, or when linking # the entirety of a libtool archive into another (currently # not supported by libtool). if (for obj in $oldobjs do func_basename "$obj" $ECHO "$func_basename_result" done | sort | sort -uc >/dev/null 2>&1); then : else echo "copying selected object files to avoid basename conflicts..." gentop="$output_objdir/${outputname}x" func_append generated " $gentop" func_mkdir_p "$gentop" save_oldobjs=$oldobjs oldobjs= counter=1 for obj in $save_oldobjs do func_basename "$obj" objbase="$func_basename_result" case " $oldobjs " in " ") oldobjs=$obj ;; *[\ /]"$objbase "*) while :; do # Make sure we don't pick an alternate name that also # overlaps. newobj=lt$counter-$objbase func_arith $counter + 1 counter=$func_arith_result case " $oldobjs " in *[\ /]"$newobj "*) ;; *) if test ! -f "$gentop/$newobj"; then break; fi ;; esac done func_show_eval "ln $obj $gentop/$newobj || cp $obj $gentop/$newobj" func_append oldobjs " $gentop/$newobj" ;; *) func_append oldobjs " $obj" ;; esac done fi func_to_tool_file "$oldlib" func_convert_file_msys_to_w32 tool_oldlib=$func_to_tool_file_result eval cmds=\"$old_archive_cmds\" func_len " $cmds" len=$func_len_result if test "$len" -lt "$max_cmd_len" || test "$max_cmd_len" -le -1; then cmds=$old_archive_cmds elif test -n "$archiver_list_spec"; then func_verbose "using command file archive linking..." for obj in $oldobjs do func_to_tool_file "$obj" $ECHO "$func_to_tool_file_result" done > $output_objdir/$libname.libcmd func_to_tool_file "$output_objdir/$libname.libcmd" oldobjs=" $archiver_list_spec$func_to_tool_file_result" cmds=$old_archive_cmds else # the command line is too long to link in one step, link in parts func_verbose "using piecewise archive linking..." save_RANLIB=$RANLIB RANLIB=: objlist= concat_cmds= save_oldobjs=$oldobjs oldobjs= # Is there a better way of finding the last object in the list? for obj in $save_oldobjs do last_oldobj=$obj done eval test_cmds=\"$old_archive_cmds\" func_len " $test_cmds" len0=$func_len_result len=$len0 for obj in $save_oldobjs do func_len " $obj" func_arith $len + $func_len_result len=$func_arith_result func_append objlist " $obj" if test "$len" -lt "$max_cmd_len"; then : else # the above command should be used before it gets too long oldobjs=$objlist if test "$obj" = "$last_oldobj" ; then RANLIB=$save_RANLIB fi test -z "$concat_cmds" || concat_cmds=$concat_cmds~ eval concat_cmds=\"\${concat_cmds}$old_archive_cmds\" objlist= len=$len0 fi done RANLIB=$save_RANLIB oldobjs=$objlist if test "X$oldobjs" = "X" ; then eval cmds=\"\$concat_cmds\" else eval cmds=\"\$concat_cmds~\$old_archive_cmds\" fi fi fi func_execute_cmds "$cmds" 'exit $?' done test -n "$generated" && \ func_show_eval "${RM}r$generated" # Now create the libtool archive. case $output in *.la) old_library= test "$build_old_libs" = yes && old_library="$libname.$libext" func_verbose "creating $output" # Preserve any variables that may affect compiler behavior for var in $variables_saved_for_relink; do if eval test -z \"\${$var+set}\"; then relink_command="{ test -z \"\${$var+set}\" || $lt_unset $var || { $var=; export $var; }; }; $relink_command" elif eval var_value=\$$var; test -z "$var_value"; then relink_command="$var=; export $var; $relink_command" else func_quote_for_eval "$var_value" relink_command="$var=$func_quote_for_eval_result; export $var; $relink_command" fi done # Quote the link command for shipping. relink_command="(cd `pwd`; $SHELL $progpath $preserve_args --mode=relink $libtool_args @inst_prefix_dir@)" relink_command=`$ECHO "$relink_command" | $SED "$sed_quote_subst"` if test "$hardcode_automatic" = yes ; then relink_command= fi # Only create the output if not a dry run. $opt_dry_run || { for installed in no yes; do if test "$installed" = yes; then if test -z "$install_libdir"; then break fi output="$output_objdir/$outputname"i # Replace all uninstalled libtool libraries with the installed ones newdependency_libs= for deplib in $dependency_libs; do case $deplib in *.la) func_basename "$deplib" name="$func_basename_result" func_resolve_sysroot "$deplib" eval libdir=`${SED} -n -e 's/^libdir=\(.*\)$/\1/p' $func_resolve_sysroot_result` test -z "$libdir" && \ func_fatal_error "\`$deplib' is not a valid libtool archive" func_append newdependency_libs " ${lt_sysroot:+=}$libdir/$name" ;; -L*) func_stripname -L '' "$deplib" func_replace_sysroot "$func_stripname_result" func_append newdependency_libs " -L$func_replace_sysroot_result" ;; -R*) func_stripname -R '' "$deplib" func_replace_sysroot "$func_stripname_result" func_append newdependency_libs " -R$func_replace_sysroot_result" ;; *) func_append newdependency_libs " $deplib" ;; esac done dependency_libs="$newdependency_libs" newdlfiles= for lib in $dlfiles; do case $lib in *.la) func_basename "$lib" name="$func_basename_result" eval libdir=`${SED} -n -e 's/^libdir=\(.*\)$/\1/p' $lib` test -z "$libdir" && \ func_fatal_error "\`$lib' is not a valid libtool archive" func_append newdlfiles " ${lt_sysroot:+=}$libdir/$name" ;; *) func_append newdlfiles " $lib" ;; esac done dlfiles="$newdlfiles" newdlprefiles= for lib in $dlprefiles; do case $lib in *.la) # Only pass preopened files to the pseudo-archive (for # eventual linking with the app. that links it) if we # didn't already link the preopened objects directly into # the library: func_basename "$lib" name="$func_basename_result" eval libdir=`${SED} -n -e 's/^libdir=\(.*\)$/\1/p' $lib` test -z "$libdir" && \ func_fatal_error "\`$lib' is not a valid libtool archive" func_append newdlprefiles " ${lt_sysroot:+=}$libdir/$name" ;; esac done dlprefiles="$newdlprefiles" else newdlfiles= for lib in $dlfiles; do case $lib in [\\/]* | [A-Za-z]:[\\/]*) abs="$lib" ;; *) abs=`pwd`"/$lib" ;; esac func_append newdlfiles " $abs" done dlfiles="$newdlfiles" newdlprefiles= for lib in $dlprefiles; do case $lib in [\\/]* | [A-Za-z]:[\\/]*) abs="$lib" ;; *) abs=`pwd`"/$lib" ;; esac func_append newdlprefiles " $abs" done dlprefiles="$newdlprefiles" fi $RM $output # place dlname in correct position for cygwin # In fact, it would be nice if we could use this code for all target # systems that can't hard-code library paths into their executables # and that have no shared library path variable independent of PATH, # but it turns out we can't easily determine that from inspecting # libtool variables, so we have to hard-code the OSs to which it # applies here; at the moment, that means platforms that use the PE # object format with DLL files. See the long comment at the top of # tests/bindir.at for full details. tdlname=$dlname case $host,$output,$installed,$module,$dlname in *cygwin*,*lai,yes,no,*.dll | *mingw*,*lai,yes,no,*.dll | *cegcc*,*lai,yes,no,*.dll) # If a -bindir argument was supplied, place the dll there. if test "x$bindir" != x ; then func_relative_path "$install_libdir" "$bindir" tdlname=$func_relative_path_result$dlname else # Otherwise fall back on heuristic. tdlname=../bin/$dlname fi ;; esac $ECHO > $output "\ # $outputname - a libtool library file # Generated by $PROGRAM (GNU $PACKAGE$TIMESTAMP) $VERSION # # Please DO NOT delete this file! # It is necessary for linking the library. # The name that we can dlopen(3). dlname='$tdlname' # Names of this library. library_names='$library_names' # The name of the static archive. old_library='$old_library' # Linker flags that can not go in dependency_libs. inherited_linker_flags='$new_inherited_linker_flags' # Libraries that this one depends upon. dependency_libs='$dependency_libs' # Names of additional weak libraries provided by this library weak_library_names='$weak_libs' # Version information for $libname. current=$current age=$age revision=$revision # Is this an already installed library? installed=$installed # Should we warn about portability when linking against -modules? shouldnotlink=$module # Files to dlopen/dlpreopen dlopen='$dlfiles' dlpreopen='$dlprefiles' # Directory that this library needs to be installed in: libdir='$install_libdir'" if test "$installed" = no && test "$need_relink" = yes; then $ECHO >> $output "\ relink_command=\"$relink_command\"" fi done } # Do a symbolic link so that the libtool archive can be found in # LD_LIBRARY_PATH before the program is installed. func_show_eval '( cd "$output_objdir" && $RM "$outputname" && $LN_S "../$outputname" "$outputname" )' 'exit $?' ;; esac exit $EXIT_SUCCESS } { test "$opt_mode" = link || test "$opt_mode" = relink; } && func_mode_link ${1+"$@"} # func_mode_uninstall arg... func_mode_uninstall () { $opt_debug RM="$nonopt" files= rmforce= exit_status=0 # This variable tells wrapper scripts just to set variables rather # than running their programs. libtool_install_magic="$magic" for arg do case $arg in -f) func_append RM " $arg"; rmforce=yes ;; -*) func_append RM " $arg" ;; *) func_append files " $arg" ;; esac done test -z "$RM" && \ func_fatal_help "you must specify an RM program" rmdirs= for file in $files; do func_dirname "$file" "" "." dir="$func_dirname_result" if test "X$dir" = X.; then odir="$objdir" else odir="$dir/$objdir" fi func_basename "$file" name="$func_basename_result" test "$opt_mode" = uninstall && odir="$dir" # Remember odir for removal later, being careful to avoid duplicates if test "$opt_mode" = clean; then case " $rmdirs " in *" $odir "*) ;; *) func_append rmdirs " $odir" ;; esac fi # Don't error if the file doesn't exist and rm -f was used. if { test -L "$file"; } >/dev/null 2>&1 || { test -h "$file"; } >/dev/null 2>&1 || test -f "$file"; then : elif test -d "$file"; then exit_status=1 continue elif test "$rmforce" = yes; then continue fi rmfiles="$file" case $name in *.la) # Possibly a libtool archive, so verify it. if func_lalib_p "$file"; then func_source $dir/$name # Delete the libtool libraries and symlinks. for n in $library_names; do func_append rmfiles " $odir/$n" done test -n "$old_library" && func_append rmfiles " $odir/$old_library" case "$opt_mode" in clean) case " $library_names " in *" $dlname "*) ;; *) test -n "$dlname" && func_append rmfiles " $odir/$dlname" ;; esac test -n "$libdir" && func_append rmfiles " $odir/$name $odir/${name}i" ;; uninstall) if test -n "$library_names"; then # Do each command in the postuninstall commands. func_execute_cmds "$postuninstall_cmds" 'test "$rmforce" = yes || exit_status=1' fi if test -n "$old_library"; then # Do each command in the old_postuninstall commands. func_execute_cmds "$old_postuninstall_cmds" 'test "$rmforce" = yes || exit_status=1' fi # FIXME: should reinstall the best remaining shared library. ;; esac fi ;; *.lo) # Possibly a libtool object, so verify it. if func_lalib_p "$file"; then # Read the .lo file func_source $dir/$name # Add PIC object to the list of files to remove. if test -n "$pic_object" && test "$pic_object" != none; then func_append rmfiles " $dir/$pic_object" fi # Add non-PIC object to the list of files to remove. if test -n "$non_pic_object" && test "$non_pic_object" != none; then func_append rmfiles " $dir/$non_pic_object" fi fi ;; *) if test "$opt_mode" = clean ; then noexename=$name case $file in *.exe) func_stripname '' '.exe' "$file" file=$func_stripname_result func_stripname '' '.exe' "$name" noexename=$func_stripname_result # $file with .exe has already been added to rmfiles, # add $file without .exe func_append rmfiles " $file" ;; esac # Do a test to see if this is a libtool program. if func_ltwrapper_p "$file"; then if func_ltwrapper_executable_p "$file"; then func_ltwrapper_scriptname "$file" relink_command= func_source $func_ltwrapper_scriptname_result func_append rmfiles " $func_ltwrapper_scriptname_result" else relink_command= func_source $dir/$noexename fi # note $name still contains .exe if it was in $file originally # as does the version of $file that was added into $rmfiles func_append rmfiles " $odir/$name $odir/${name}S.${objext}" if test "$fast_install" = yes && test -n "$relink_command"; then func_append rmfiles " $odir/lt-$name" fi if test "X$noexename" != "X$name" ; then func_append rmfiles " $odir/lt-${noexename}.c" fi fi fi ;; esac func_show_eval "$RM $rmfiles" 'exit_status=1' done # Try to remove the ${objdir}s in the directories where we deleted files for dir in $rmdirs; do if test -d "$dir"; then func_show_eval "rmdir $dir >/dev/null 2>&1" fi done exit $exit_status } { test "$opt_mode" = uninstall || test "$opt_mode" = clean; } && func_mode_uninstall ${1+"$@"} test -z "$opt_mode" && { help="$generic_help" func_fatal_help "you must specify a MODE" } test -z "$exec_cmd" && \ func_fatal_help "invalid operation mode \`$opt_mode'" if test -n "$exec_cmd"; then eval exec "$exec_cmd" exit $EXIT_FAILURE fi exit $exit_status # The TAGs below are defined such that we never get into a situation # in which we disable both kinds of libraries. Given conflicting # choices, we go for a static library, that is the most portable, # since we can't tell whether shared libraries were disabled because # the user asked for that or because the platform doesn't support # them. This is particularly important on AIX, because we don't # support having both static and shared libraries enabled at the same # time on that platform, so we default to a shared-only configuration. # If a disable-shared tag is given, we'll fallback to a static-only # configuration. But we'll never go from static-only to shared-only. # ### BEGIN LIBTOOL TAG CONFIG: disable-shared build_libtool_libs=no build_old_libs=yes # ### END LIBTOOL TAG CONFIG: disable-shared # ### BEGIN LIBTOOL TAG CONFIG: disable-static build_old_libs=`case $build_libtool_libs in yes) echo no;; *) echo yes;; esac` # ### END LIBTOOL TAG CONFIG: disable-static # Local Variables: # mode:shell-script # sh-indentation:2 # End: # vi:sw=2 smalltalk-3.2.5/build-aux/vis-hidden.m40000644000175000017500000000113712123404352014612 00000000000000dnl I'd like this to be edited in -*- Autoconf -*- mode... dnl AC_DEFUN([GST_C_HIDDEN_VISIBILITY], [AC_CACHE_CHECK([for hidden visibility], gst_cv_c_visibility_hidden, [gst_cv_c_visibility_hidden=no save_CFLAGS="$CFLAGS" CFLAGS="$CFLAGS -Werror" AC_COMPILE_IFELSE([AC_LANG_SOURCE([char *c __attribute__ ((visibility ("hidden")));])], [gst_cv_c_visibility_hidden=yes; break]) CFLAGS="$save_CFLAGS" ]) if test $gst_cv_c_visibility_hidden = yes; then AC_DEFINE(HAVE_VISIBILITY_HIDDEN,, [Define if the C compiler support the ELF hidden visibility]) fi ])# GST_C_HIDDEN_VISIBILITY smalltalk-3.2.5/build-aux/mdate-sh0000755000175000017500000001371712130455425013762 00000000000000#!/bin/sh # Get modification time of a file or directory and pretty-print it. scriptversion=2010-08-21.06; # UTC # Copyright (C) 1995, 1996, 1997, 2003, 2004, 2005, 2007, 2009, 2010 # Free Software Foundation, Inc. # written by Ulrich Drepper , June 1995 # # This program is free software; you can redistribute it and/or modify # it under the terms of the GNU General Public License as published by # the Free Software Foundation; either version 2, or (at your option) # any later version. # # This program is distributed in the hope that it will be useful, # but WITHOUT ANY WARRANTY; without even the implied warranty of # MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the # GNU General Public License for more details. # # You should have received a copy of the GNU General Public License # along with this program. If not, see . # As a special exception to the GNU General Public License, if you # distribute this file as part of a program that contains a # configuration script generated by Autoconf, you may include it under # the same distribution terms that you use for the rest of that program. # This file is maintained in Automake, please report # bugs to or send patches to # . if test -n "${ZSH_VERSION+set}" && (emulate sh) >/dev/null 2>&1; then emulate sh NULLCMD=: # Pre-4.2 versions of Zsh do word splitting on ${1+"$@"}, which # is contrary to our usage. Disable this feature. alias -g '${1+"$@"}'='"$@"' setopt NO_GLOB_SUBST fi case $1 in '') echo "$0: No file. Try \`$0 --help' for more information." 1>&2 exit 1; ;; -h | --h*) cat <<\EOF Usage: mdate-sh [--help] [--version] FILE Pretty-print the modification day of FILE, in the format: 1 January 1970 Report bugs to . EOF exit $? ;; -v | --v*) echo "mdate-sh $scriptversion" exit $? ;; esac error () { echo "$0: $1" >&2 exit 1 } # Prevent date giving response in another language. LANG=C export LANG LC_ALL=C export LC_ALL LC_TIME=C export LC_TIME # GNU ls changes its time format in response to the TIME_STYLE # variable. Since we cannot assume `unset' works, revert this # variable to its documented default. if test "${TIME_STYLE+set}" = set; then TIME_STYLE=posix-long-iso export TIME_STYLE fi save_arg1=$1 # Find out how to get the extended ls output of a file or directory. if ls -L /dev/null 1>/dev/null 2>&1; then ls_command='ls -L -l -d' else ls_command='ls -l -d' fi # Avoid user/group names that might have spaces, when possible. if ls -n /dev/null 1>/dev/null 2>&1; then ls_command="$ls_command -n" fi # A `ls -l' line looks as follows on OS/2. # drwxrwx--- 0 Aug 11 2001 foo # This differs from Unix, which adds ownership information. # drwxrwx--- 2 root root 4096 Aug 11 2001 foo # # To find the date, we split the line on spaces and iterate on words # until we find a month. This cannot work with files whose owner is a # user named `Jan', or `Feb', etc. However, it's unlikely that `/' # will be owned by a user whose name is a month. So we first look at # the extended ls output of the root directory to decide how many # words should be skipped to get the date. # On HPUX /bin/sh, "set" interprets "-rw-r--r--" as options, so the "x" below. set x`$ls_command /` # Find which argument is the month. month= command= until test $month do test $# -gt 0 || error "failed parsing \`$ls_command /' output" shift # Add another shift to the command. command="$command shift;" case $1 in Jan) month=January; nummonth=1;; Feb) month=February; nummonth=2;; Mar) month=March; nummonth=3;; Apr) month=April; nummonth=4;; May) month=May; nummonth=5;; Jun) month=June; nummonth=6;; Jul) month=July; nummonth=7;; Aug) month=August; nummonth=8;; Sep) month=September; nummonth=9;; Oct) month=October; nummonth=10;; Nov) month=November; nummonth=11;; Dec) month=December; nummonth=12;; esac done test -n "$month" || error "failed parsing \`$ls_command /' output" # Get the extended ls output of the file or directory. set dummy x`eval "$ls_command \"\\\$save_arg1\""` # Remove all preceding arguments eval $command # Because of the dummy argument above, month is in $2. # # On a POSIX system, we should have # # $# = 5 # $1 = file size # $2 = month # $3 = day # $4 = year or time # $5 = filename # # On Darwin 7.7.0 and 7.6.0, we have # # $# = 4 # $1 = day # $2 = month # $3 = year or time # $4 = filename # Get the month. case $2 in Jan) month=January; nummonth=1;; Feb) month=February; nummonth=2;; Mar) month=March; nummonth=3;; Apr) month=April; nummonth=4;; May) month=May; nummonth=5;; Jun) month=June; nummonth=6;; Jul) month=July; nummonth=7;; Aug) month=August; nummonth=8;; Sep) month=September; nummonth=9;; Oct) month=October; nummonth=10;; Nov) month=November; nummonth=11;; Dec) month=December; nummonth=12;; esac case $3 in ???*) day=$1;; *) day=$3; shift;; esac # Here we have to deal with the problem that the ls output gives either # the time of day or the year. case $3 in *:*) set `date`; eval year=\$$# case $2 in Jan) nummonthtod=1;; Feb) nummonthtod=2;; Mar) nummonthtod=3;; Apr) nummonthtod=4;; May) nummonthtod=5;; Jun) nummonthtod=6;; Jul) nummonthtod=7;; Aug) nummonthtod=8;; Sep) nummonthtod=9;; Oct) nummonthtod=10;; Nov) nummonthtod=11;; Dec) nummonthtod=12;; esac # For the first six month of the year the time notation can also # be used for files modified in the last year. if (expr $nummonth \> $nummonthtod) > /dev/null; then year=`expr $year - 1` fi;; *) year=$3;; esac # The result. echo $day $month $year # Local Variables: # mode: shell-script # sh-indentation: 2 # eval: (add-hook 'write-file-hooks 'time-stamp) # time-stamp-start: "scriptversion=" # time-stamp-format: "%:y-%02m-%02d.%02H" # time-stamp-time-zone: "UTC" # time-stamp-end: "; # UTC" # End: smalltalk-3.2.5/build-aux/localtime.m40000644000175000017500000000300112123404352014521 00000000000000dnl I'd like this to be edited in -*- Autoconf -*- mode... dnl AC_DEFUN([GST_FUNC_LOCALTIME], [ AC_CACHE_CHECK(whether localtime caches the timezone, emacs_cv_localtime_cache, [AC_REQUIRE([AC_HEADER_TIME]) AC_TRY_RUN( [#if defined(HAVE_SYS_TIME_H) || defined(TIME_WITH_SYS_TIME) # include #endif #if !defined(HAVE_SYS_TIME_H) || defined(TIME_WITH_SYS_TIME) # include #endif #if STDC_HEADERS # include #endif extern char **environ; unset_TZ () { char **from, **to; for (to = from = environ; (*to = *from); from++) if (! (to[0][0] == 'T' && to[0][1] == 'Z' && to[0][2] == '=')) to++; } char TZ_GMT0[] = "TZ=GMT0"; char TZ_PST8[] = "TZ=PST8"; main() { time_t now = time ((time_t *) 0); int hour_GMT0, hour_unset; if (putenv (TZ_GMT0) != 0) exit (1); hour_GMT0 = localtime (&now)->tm_hour; unset_TZ (); hour_unset = localtime (&now)->tm_hour; if (putenv (TZ_PST8) != 0) exit (1); if (localtime (&now)->tm_hour == hour_GMT0) exit (1); unset_TZ (); if (localtime (&now)->tm_hour != hour_unset) exit (1); exit (0); }], emacs_cv_localtime_cache=no, emacs_cv_localtime_cache=yes, [# Assume the worst when cross-compiling. emacs_cv_localtime_cache=yes]) ]) test $emacs_cv_localtime_cache = yes && \ AC_DEFINE(LOCALTIME_CACHE, 1, [Define if your system's localtime(3) caches the timezone.]) ])dnl smalltalk-3.2.5/build-aux/lib.m40000644000175000017500000000022712123404352013325 00000000000000dnl I'd like this to be edited in -*- Autoconf -*- mode... dnl AC_DEFUN([GST_HAVE_LIB], [ save_LIBS="$LIBS" AC_CHECK_LIB($@) LIBS="$save_LIBS" ])dnl smalltalk-3.2.5/build-aux/lightning.m40000644000175000017500000000400612123404352014541 00000000000000dnl I'd like this to be edited in -*- Autoconf -*- mode... dnl # serial 2 LIGHTNING_CONFIGURE_IF_NOT_FOUND m4_define([LIGHTNING_BACKENDS], [i386:-32 i386:-64 sparc ppc]) AC_DEFUN([LIGHTNING_CONFIGURE_LINKS_PREREQ], [ lightning_frag=/dev/null AC_SUBST_FILE(lightning_frag)]) AC_DEFUN([LIGHTNING_CONFIGURE_LINKS], [ AC_REQUIRE([LIGHTNING_CONFIGURE_LINKS_PREREQ]) suffix= case "$host_cpu" in i?86) cpu=i386; suffix=-32 ;; x86_64) cpu=i386; suffix=-64 ;; sparc*) cpu=sparc ;; powerpc) cpu=ppc ;; *) ;; esac if test -n "$cpu" && test -d "$srcdir/lightning/$cpu"; then $1 lightning_frag=`cd $srcdir && pwd`/lightning/$cpu/Makefile.frag test -f $lightning_frag || lightning_frag=/dev/null asm_src=lightning/$cpu/asm.h test -f $srcdir/lightning/$cpu/asm$suffix.h && asm_src=lightning/$cpu/asm$suffix.h AC_CONFIG_LINKS(lightning/asm.h:$asm_src, [], [asm_src=$asm_src]) fp_src=lightning/$cpu/fp.h test -f $srcdir/lightning/$cpu/fp$suffix.h && fp_src=lightning/$cpu/fp$suffix.h AC_CONFIG_LINKS(lightning/fp.h:$fp_src, [], [fp_src=$fp_src]) core_src=lightning/$cpu/core.h test -f $srcdir/lightning/$cpu/core$suffix.h && core_src=lightning/$cpu/core$suffix.h AC_CONFIG_LINKS(lightning/core.h:$core_src, [], [core_src=$core_src]) funcs_src=lightning/$cpu/funcs.h test -f $srcdir/lightning/$cpu/funcs$suffix.h && funcs_src=lightning/$cpu/funcs$suffix.h AC_CONFIG_LINKS(lightning/funcs.h:$funcs_src, [], [funcs_src=$funcs_src]) else $2 fi ]) AC_DEFUN([LIGHTNING_CONFIGURE_IF_NOT_FOUND], [ AC_REQUIRE([AC_PROG_LN_S])dnl AC_REQUIRE([AC_CANONICAL_HOST])dnl AC_CHECK_HEADER(lightning.h) AM_CONDITIONAL(LIGHTNING_MAIN, (exit 1)) AM_CONDITIONAL(HAVE_INSTALLED_LIGHTNING, test "$ac_cv_header_lightning_h" = yes) lightning= AS_IF([test "$ac_cv_header_lightning_h" = yes], [lightning=yes], [LIGHTNING_CONFIGURE_LINKS(lightning=yes, lightning=no)]) AS_IF([test "$lightning" = yes], [ AC_DEFINE(HAVE_LIGHTNING, 1, [Define if GNU lightning can be used]) $1 ], [$2]) unset lightning ])dnl smalltalk-3.2.5/build-aux/compile0000755000175000017500000001615212130455376013711 00000000000000#! /bin/sh # Wrapper for compilers which do not understand '-c -o'. scriptversion=2012-03-05.13; # UTC # Copyright (C) 1999, 2000, 2003, 2004, 2005, 2009, 2010, 2012 Free # Software Foundation, Inc. # Written by Tom Tromey . # # This program is free software; you can redistribute it and/or modify # it under the terms of the GNU General Public License as published by # the Free Software Foundation; either version 2, or (at your option) # any later version. # # This program is distributed in the hope that it will be useful, # but WITHOUT ANY WARRANTY; without even the implied warranty of # MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the # GNU General Public License for more details. # # You should have received a copy of the GNU General Public License # along with this program. If not, see . # As a special exception to the GNU General Public License, if you # distribute this file as part of a program that contains a # configuration script generated by Autoconf, you may include it under # the same distribution terms that you use for the rest of that program. # This file is maintained in Automake, please report # bugs to or send patches to # . nl=' ' # We need space, tab and new line, in precisely that order. Quoting is # there to prevent tools from complaining about whitespace usage. IFS=" "" $nl" file_conv= # func_file_conv build_file lazy # Convert a $build file to $host form and store it in $file # Currently only supports Windows hosts. If the determined conversion # type is listed in (the comma separated) LAZY, no conversion will # take place. func_file_conv () { file=$1 case $file in / | /[!/]*) # absolute file, and not a UNC file if test -z "$file_conv"; then # lazily determine how to convert abs files case `uname -s` in MINGW*) file_conv=mingw ;; CYGWIN*) file_conv=cygwin ;; *) file_conv=wine ;; esac fi case $file_conv/,$2, in *,$file_conv,*) ;; mingw/*) file=`cmd //C echo "$file " | sed -e 's/"\(.*\) " *$/\1/'` ;; cygwin/*) file=`cygpath -m "$file" || echo "$file"` ;; wine/*) file=`winepath -w "$file" || echo "$file"` ;; esac ;; esac } # func_cl_dashL linkdir # Make cl look for libraries in LINKDIR func_cl_dashL () { func_file_conv "$1" if test -z "$lib_path"; then lib_path=$file else lib_path="$lib_path;$file" fi linker_opts="$linker_opts -LIBPATH:$file" } # func_cl_dashl library # Do a library search-path lookup for cl func_cl_dashl () { lib=$1 found=no save_IFS=$IFS IFS=';' for dir in $lib_path $LIB do IFS=$save_IFS if $shared && test -f "$dir/$lib.dll.lib"; then found=yes lib=$dir/$lib.dll.lib break fi if test -f "$dir/$lib.lib"; then found=yes lib=$dir/$lib.lib break fi done IFS=$save_IFS if test "$found" != yes; then lib=$lib.lib fi } # func_cl_wrapper cl arg... # Adjust compile command to suit cl func_cl_wrapper () { # Assume a capable shell lib_path= shared=: linker_opts= for arg do if test -n "$eat"; then eat= else case $1 in -o) # configure might choose to run compile as 'compile cc -o foo foo.c'. eat=1 case $2 in *.o | *.[oO][bB][jJ]) func_file_conv "$2" set x "$@" -Fo"$file" shift ;; *) func_file_conv "$2" set x "$@" -Fe"$file" shift ;; esac ;; -I) eat=1 func_file_conv "$2" mingw set x "$@" -I"$file" shift ;; -I*) func_file_conv "${1#-I}" mingw set x "$@" -I"$file" shift ;; -l) eat=1 func_cl_dashl "$2" set x "$@" "$lib" shift ;; -l*) func_cl_dashl "${1#-l}" set x "$@" "$lib" shift ;; -L) eat=1 func_cl_dashL "$2" ;; -L*) func_cl_dashL "${1#-L}" ;; -static) shared=false ;; -Wl,*) arg=${1#-Wl,} save_ifs="$IFS"; IFS=',' for flag in $arg; do IFS="$save_ifs" linker_opts="$linker_opts $flag" done IFS="$save_ifs" ;; -Xlinker) eat=1 linker_opts="$linker_opts $2" ;; -*) set x "$@" "$1" shift ;; *.cc | *.CC | *.cxx | *.CXX | *.[cC]++) func_file_conv "$1" set x "$@" -Tp"$file" shift ;; *.c | *.cpp | *.CPP | *.lib | *.LIB | *.Lib | *.OBJ | *.obj | *.[oO]) func_file_conv "$1" mingw set x "$@" "$file" shift ;; *) set x "$@" "$1" shift ;; esac fi shift done if test -n "$linker_opts"; then linker_opts="-link$linker_opts" fi exec "$@" $linker_opts exit 1 } eat= case $1 in '') echo "$0: No command. Try '$0 --help' for more information." 1>&2 exit 1; ;; -h | --h*) cat <<\EOF Usage: compile [--help] [--version] PROGRAM [ARGS] Wrapper for compilers which do not understand '-c -o'. Remove '-o dest.o' from ARGS, run PROGRAM with the remaining arguments, and rename the output as expected. If you are trying to build a whole package this is not the right script to run: please start by reading the file 'INSTALL'. Report bugs to . EOF exit $? ;; -v | --v*) echo "compile $scriptversion" exit $? ;; cl | *[/\\]cl | cl.exe | *[/\\]cl.exe ) func_cl_wrapper "$@" # Doesn't return... ;; esac ofile= cfile= for arg do if test -n "$eat"; then eat= else case $1 in -o) # configure might choose to run compile as 'compile cc -o foo foo.c'. # So we strip '-o arg' only if arg is an object. eat=1 case $2 in *.o | *.obj) ofile=$2 ;; *) set x "$@" -o "$2" shift ;; esac ;; *.c) cfile=$1 set x "$@" "$1" shift ;; *) set x "$@" "$1" shift ;; esac fi shift done if test -z "$ofile" || test -z "$cfile"; then # If no '-o' option was seen then we might have been invoked from a # pattern rule where we don't need one. That is ok -- this is a # normal compilation that the losing compiler can handle. If no # '.c' file was seen then we are probably linking. That is also # ok. exec "$@" fi # Name of file we expect compiler to create. cofile=`echo "$cfile" | sed 's|^.*[\\/]||; s|^[a-zA-Z]:||; s/\.c$/.o/'` # Create the lock directory. # Note: use '[/\\:.-]' here to ensure that we don't use the same name # that we are using for the .o file. Also, base the name on the expected # object file name, since that is what matters with a parallel build. lockdir=`echo "$cofile" | sed -e 's|[/\\:.-]|_|g'`.d while true; do if mkdir "$lockdir" >/dev/null 2>&1; then break fi sleep 1 done # FIXME: race condition here if user kills between mkdir and trap. trap "rmdir '$lockdir'; exit 1" 1 2 15 # Run the compile. "$@" ret=$? if test -f "$cofile"; then test "$cofile" = "$ofile" || mv "$cofile" "$ofile" elif test -f "${cofile}bj"; then test "${cofile}bj" = "$ofile" || mv "${cofile}bj" "$ofile" fi rmdir "$lockdir" exit $ret # Local Variables: # mode: shell-script # sh-indentation: 2 # eval: (add-hook 'write-file-hooks 'time-stamp) # time-stamp-start: "scriptversion=" # time-stamp-format: "%:y-%02m-%02d.%02H" # time-stamp-time-zone: "UTC" # time-stamp-end: "; # UTC" # End: smalltalk-3.2.5/build-aux/gl.m40000644000175000017500000000323712123404352013165 00000000000000dnl I'd like this to be edited in -*- Autoconf -*- mode... dnl AC_DEFUN([GST_HAVE_OPENGL], [ AC_REQUIRE([AC_PATH_XTRA]) AC_CHECK_HEADERS([OpenGL/gl.h OpenGL/glu.h GL/gl.h GL/glu.h]) AC_CACHE_CHECK([how to link with OpenGL libraries], gst_cv_opengl_libs, [ if test $ac_cv_header_OpenGL_gl_h = no && \ test $ac_cv_header_GL_gl_h = no; then gst_cv_opengl_libs='not found' elif test $ac_cv_header_OpenGL_glu_h = no && \ test $ac_cv_header_GL_glu_h = no; then gst_cv_opengl_libs='not found' else save_LIBS=$LIBS case $host in *-*-mingw* | *-*-cygwin*) gst_cv_opengl_libs='-lopengl32 -lglu32' ;; *-*-beos* | *-*-qnx*) gst_cv_opengl_libs='-lGL' ;; *-*-darwin*) gst_cv_opengl_libs='-Wl,-framework,OpenGL' ;; *) gst_cv_opengl_libs="-lGL -lGLU $X_LIBS $X_PRE_LIBS -lX11" ;; esac LIBS="$LIBS $gst_cv_opengl_libs" AC_LINK_IFELSE([AC_LANG_PROGRAM([ #ifdef HAVE_GL_GL_H #include #else #include #endif], [glBegin(GL_TRIANGLES)])], [], [gst_cv_opengl_libs='not found']) LIBS=$save_LIBS fi ]) if test "$gst_cv_opengl_libs" != "not found"; then LIBOPENGL="$gst_cv_opengl_libs" AC_DEFINE(HAVE_OPENGL, 1, [Define if your system has OpenGL installed.]) if test $ac_cv_header_OpenGL_gl_h = yes; then gst_cv_opengl_header_dir='OpenGL' else gst_cv_opengl_header_dir='GL' fi AC_DEFINE_UNQUOTED(GL_GL_H, [<$gst_cv_opengl_header_dir/gl.h>], [Define to the #include directive for OpenGL.]) AC_DEFINE_UNQUOTED(GL_GLU_H, [<$gst_cv_opengl_header_dir/glu.h>], [Define to the #include directive for OpenGL glu functions.]) fi AC_SUBST(LIBOPENGL) ])dnl smalltalk-3.2.5/build-aux/lt~obsolete.m40000644000175000017500000001375612130455417015152 00000000000000# lt~obsolete.m4 -- aclocal satisfying obsolete definitions. -*-Autoconf-*- # # Copyright (C) 2004, 2005, 2007, 2009 Free Software Foundation, Inc. # Written by Scott James Remnant, 2004. # # This file is free software; the Free Software Foundation gives # unlimited permission to copy and/or distribute it, with or without # modifications, as long as this notice is preserved. # serial 5 lt~obsolete.m4 # These exist entirely to fool aclocal when bootstrapping libtool. # # In the past libtool.m4 has provided macros via AC_DEFUN (or AU_DEFUN) # which have later been changed to m4_define as they aren't part of the # exported API, or moved to Autoconf or Automake where they belong. # # The trouble is, aclocal is a bit thick. It'll see the old AC_DEFUN # in /usr/share/aclocal/libtool.m4 and remember it, then when it sees us # using a macro with the same name in our local m4/libtool.m4 it'll # pull the old libtool.m4 in (it doesn't see our shiny new m4_define # and doesn't know about Autoconf macros at all.) # # So we provide this file, which has a silly filename so it's always # included after everything else. This provides aclocal with the # AC_DEFUNs it wants, but when m4 processes it, it doesn't do anything # because those macros already exist, or will be overwritten later. # We use AC_DEFUN over AU_DEFUN for compatibility with aclocal-1.6. # # Anytime we withdraw an AC_DEFUN or AU_DEFUN, remember to add it here. # Yes, that means every name once taken will need to remain here until # we give up compatibility with versions before 1.7, at which point # we need to keep only those names which we still refer to. # This is to help aclocal find these macros, as it can't see m4_define. AC_DEFUN([LTOBSOLETE_VERSION], [m4_if([1])]) m4_ifndef([AC_LIBTOOL_LINKER_OPTION], [AC_DEFUN([AC_LIBTOOL_LINKER_OPTION])]) m4_ifndef([AC_PROG_EGREP], [AC_DEFUN([AC_PROG_EGREP])]) m4_ifndef([_LT_AC_PROG_ECHO_BACKSLASH], [AC_DEFUN([_LT_AC_PROG_ECHO_BACKSLASH])]) m4_ifndef([_LT_AC_SHELL_INIT], [AC_DEFUN([_LT_AC_SHELL_INIT])]) m4_ifndef([_LT_AC_SYS_LIBPATH_AIX], [AC_DEFUN([_LT_AC_SYS_LIBPATH_AIX])]) m4_ifndef([_LT_PROG_LTMAIN], [AC_DEFUN([_LT_PROG_LTMAIN])]) m4_ifndef([_LT_AC_TAGVAR], [AC_DEFUN([_LT_AC_TAGVAR])]) m4_ifndef([AC_LTDL_ENABLE_INSTALL], [AC_DEFUN([AC_LTDL_ENABLE_INSTALL])]) m4_ifndef([AC_LTDL_PREOPEN], [AC_DEFUN([AC_LTDL_PREOPEN])]) m4_ifndef([_LT_AC_SYS_COMPILER], [AC_DEFUN([_LT_AC_SYS_COMPILER])]) m4_ifndef([_LT_AC_LOCK], [AC_DEFUN([_LT_AC_LOCK])]) m4_ifndef([AC_LIBTOOL_SYS_OLD_ARCHIVE], [AC_DEFUN([AC_LIBTOOL_SYS_OLD_ARCHIVE])]) m4_ifndef([_LT_AC_TRY_DLOPEN_SELF], [AC_DEFUN([_LT_AC_TRY_DLOPEN_SELF])]) m4_ifndef([AC_LIBTOOL_PROG_CC_C_O], [AC_DEFUN([AC_LIBTOOL_PROG_CC_C_O])]) m4_ifndef([AC_LIBTOOL_SYS_HARD_LINK_LOCKS], [AC_DEFUN([AC_LIBTOOL_SYS_HARD_LINK_LOCKS])]) m4_ifndef([AC_LIBTOOL_OBJDIR], [AC_DEFUN([AC_LIBTOOL_OBJDIR])]) m4_ifndef([AC_LTDL_OBJDIR], [AC_DEFUN([AC_LTDL_OBJDIR])]) m4_ifndef([AC_LIBTOOL_PROG_LD_HARDCODE_LIBPATH], [AC_DEFUN([AC_LIBTOOL_PROG_LD_HARDCODE_LIBPATH])]) m4_ifndef([AC_LIBTOOL_SYS_LIB_STRIP], [AC_DEFUN([AC_LIBTOOL_SYS_LIB_STRIP])]) m4_ifndef([AC_PATH_MAGIC], [AC_DEFUN([AC_PATH_MAGIC])]) m4_ifndef([AC_PROG_LD_GNU], [AC_DEFUN([AC_PROG_LD_GNU])]) m4_ifndef([AC_PROG_LD_RELOAD_FLAG], [AC_DEFUN([AC_PROG_LD_RELOAD_FLAG])]) m4_ifndef([AC_DEPLIBS_CHECK_METHOD], [AC_DEFUN([AC_DEPLIBS_CHECK_METHOD])]) m4_ifndef([AC_LIBTOOL_PROG_COMPILER_NO_RTTI], [AC_DEFUN([AC_LIBTOOL_PROG_COMPILER_NO_RTTI])]) m4_ifndef([AC_LIBTOOL_SYS_GLOBAL_SYMBOL_PIPE], [AC_DEFUN([AC_LIBTOOL_SYS_GLOBAL_SYMBOL_PIPE])]) m4_ifndef([AC_LIBTOOL_PROG_COMPILER_PIC], [AC_DEFUN([AC_LIBTOOL_PROG_COMPILER_PIC])]) m4_ifndef([AC_LIBTOOL_PROG_LD_SHLIBS], [AC_DEFUN([AC_LIBTOOL_PROG_LD_SHLIBS])]) m4_ifndef([AC_LIBTOOL_POSTDEP_PREDEP], [AC_DEFUN([AC_LIBTOOL_POSTDEP_PREDEP])]) m4_ifndef([LT_AC_PROG_EGREP], [AC_DEFUN([LT_AC_PROG_EGREP])]) m4_ifndef([LT_AC_PROG_SED], [AC_DEFUN([LT_AC_PROG_SED])]) m4_ifndef([_LT_CC_BASENAME], [AC_DEFUN([_LT_CC_BASENAME])]) m4_ifndef([_LT_COMPILER_BOILERPLATE], [AC_DEFUN([_LT_COMPILER_BOILERPLATE])]) m4_ifndef([_LT_LINKER_BOILERPLATE], [AC_DEFUN([_LT_LINKER_BOILERPLATE])]) m4_ifndef([_AC_PROG_LIBTOOL], [AC_DEFUN([_AC_PROG_LIBTOOL])]) m4_ifndef([AC_LIBTOOL_SETUP], [AC_DEFUN([AC_LIBTOOL_SETUP])]) m4_ifndef([_LT_AC_CHECK_DLFCN], [AC_DEFUN([_LT_AC_CHECK_DLFCN])]) m4_ifndef([AC_LIBTOOL_SYS_DYNAMIC_LINKER], [AC_DEFUN([AC_LIBTOOL_SYS_DYNAMIC_LINKER])]) m4_ifndef([_LT_AC_TAGCONFIG], [AC_DEFUN([_LT_AC_TAGCONFIG])]) m4_ifndef([AC_DISABLE_FAST_INSTALL], [AC_DEFUN([AC_DISABLE_FAST_INSTALL])]) m4_ifndef([_LT_AC_LANG_CXX], [AC_DEFUN([_LT_AC_LANG_CXX])]) m4_ifndef([_LT_AC_LANG_F77], [AC_DEFUN([_LT_AC_LANG_F77])]) m4_ifndef([_LT_AC_LANG_GCJ], [AC_DEFUN([_LT_AC_LANG_GCJ])]) m4_ifndef([AC_LIBTOOL_LANG_C_CONFIG], [AC_DEFUN([AC_LIBTOOL_LANG_C_CONFIG])]) m4_ifndef([_LT_AC_LANG_C_CONFIG], [AC_DEFUN([_LT_AC_LANG_C_CONFIG])]) m4_ifndef([AC_LIBTOOL_LANG_CXX_CONFIG], [AC_DEFUN([AC_LIBTOOL_LANG_CXX_CONFIG])]) m4_ifndef([_LT_AC_LANG_CXX_CONFIG], [AC_DEFUN([_LT_AC_LANG_CXX_CONFIG])]) m4_ifndef([AC_LIBTOOL_LANG_F77_CONFIG], [AC_DEFUN([AC_LIBTOOL_LANG_F77_CONFIG])]) m4_ifndef([_LT_AC_LANG_F77_CONFIG], [AC_DEFUN([_LT_AC_LANG_F77_CONFIG])]) m4_ifndef([AC_LIBTOOL_LANG_GCJ_CONFIG], [AC_DEFUN([AC_LIBTOOL_LANG_GCJ_CONFIG])]) m4_ifndef([_LT_AC_LANG_GCJ_CONFIG], [AC_DEFUN([_LT_AC_LANG_GCJ_CONFIG])]) m4_ifndef([AC_LIBTOOL_LANG_RC_CONFIG], [AC_DEFUN([AC_LIBTOOL_LANG_RC_CONFIG])]) m4_ifndef([_LT_AC_LANG_RC_CONFIG], [AC_DEFUN([_LT_AC_LANG_RC_CONFIG])]) m4_ifndef([AC_LIBTOOL_CONFIG], [AC_DEFUN([AC_LIBTOOL_CONFIG])]) m4_ifndef([_LT_AC_FILE_LTDLL_C], [AC_DEFUN([_LT_AC_FILE_LTDLL_C])]) m4_ifndef([_LT_REQUIRED_DARWIN_CHECKS], [AC_DEFUN([_LT_REQUIRED_DARWIN_CHECKS])]) m4_ifndef([_LT_AC_PROG_CXXCPP], [AC_DEFUN([_LT_AC_PROG_CXXCPP])]) m4_ifndef([_LT_PREPARE_SED_QUOTE_VARS], [AC_DEFUN([_LT_PREPARE_SED_QUOTE_VARS])]) m4_ifndef([_LT_PROG_ECHO_BACKSLASH], [AC_DEFUN([_LT_PROG_ECHO_BACKSLASH])]) m4_ifndef([_LT_PROG_F77], [AC_DEFUN([_LT_PROG_F77])]) m4_ifndef([_LT_PROG_FC], [AC_DEFUN([_LT_PROG_FC])]) m4_ifndef([_LT_PROG_CXX], [AC_DEFUN([_LT_PROG_CXX])]) smalltalk-3.2.5/build-aux/ltdl-gst.m40000644000175000017500000002766512130343734014334 00000000000000## ltdl.m4 - Configure ltdl for the target system. -*-Autoconf-*- ## Copyright (C) 1999-2009 Free Software Foundation, Inc. ## ## This program is free software; you can redistribute it and/or modify ## it under the terms of the GNU General Public License as published by ## the Free Software Foundation; either version 2 of the License, or ## (at your option) any later version. ## ## This program is distributed in the hope that it will be useful, but ## WITHOUT ANY WARRANTY; without even the implied warranty of ## MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU ## General Public License for more details. ## ## You should have received a copy of the GNU General Public License ## along with this program; if not, write to the Free Software ## Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. ## ## As a special exception to the GNU General Public License, if you ## distribute this file as part of a program that contains a ## configuration script generated by Autoconf, you may include it under ## the same distribution terms that you use for the rest of that program. # GST_LIB_LTDL # ----------- # Perform all the checks necessary for compilation of the ltdl objects # -- including compiler checks and header checks. AC_DEFUN([GST_LIB_LTDL], [AC_PREREQ(2.50) AC_REQUIRE([AC_PROG_CC]) AC_REQUIRE([AC_C_CONST]) AC_REQUIRE([AC_HEADER_STDC]) AC_REQUIRE([AC_HEADER_DIRENT]) AC_REQUIRE([_LT_AC_CHECK_DLFCN]) AC_REQUIRE([AC_LTDL_SHLIBEXT]) AC_REQUIRE([AC_LTDL_SHLIBPATH]) AC_REQUIRE([AC_LTDL_SYSSEARCHPATH]) AC_REQUIRE([AC_LTDL_OBJDIR]) AC_REQUIRE([AC_LTDL_DLPREOPEN]) AC_REQUIRE([AC_LTDL_DLLIB]) AC_REQUIRE([AC_LTDL_SYMBOL_USCORE]) AC_REQUIRE([AC_LTDL_DLSYM_USCORE]) AC_REQUIRE([AC_LTDL_SYS_DLOPEN_DEPLIBS]) AC_REQUIRE([AC_LTDL_FUNC_ARGZ]) AC_CHECK_HEADERS([assert.h ctype.h errno.h malloc.h memory.h stdlib.h \ stdio.h unistd.h]) AC_CHECK_HEADERS([dl.h sys/dl.h dld.h mach-o/dyld.h]) AC_CHECK_HEADERS([string.h strings.h], [break]) AC_CHECK_FUNCS([strchr index], [break]) AC_CHECK_FUNCS([strrchr rindex], [break]) AC_CHECK_FUNCS([memcpy bcopy], [break]) AC_CHECK_FUNCS([memmove strcmp]) AC_CHECK_FUNCS([closedir opendir readdir]) ])# AC_LIB_LTDL # AC_LTDL_SYS_DLOPEN_DEPLIBS # -------------------------- AC_DEFUN([AC_LTDL_SYS_DLOPEN_DEPLIBS], [AC_REQUIRE([AC_CANONICAL_HOST]) AC_CACHE_CHECK([whether deplibs are loaded by dlopen], [libltdl_cv_sys_dlopen_deplibs], [# PORTME does your system automatically load deplibs for dlopen? # or its logical equivalent (e.g. shl_load for HP-UX < 11) # For now, we just catch OSes we know something about -- in the # future, we'll try test this programmatically. libltdl_cv_sys_dlopen_deplibs=unknown case "$host_os" in aix3*|aix4.1.*|aix4.2.*) # Unknown whether this is true for these versions of AIX, but # we want this `case' here to explicitly catch those versions. libltdl_cv_sys_dlopen_deplibs=unknown ;; aix[[45]]*) libltdl_cv_sys_dlopen_deplibs=yes ;; darwin*) # Assuming the user has installed a libdl from somewhere, this is true # If you are looking for one http://www.opendarwin.org/projects/dlcompat libltdl_cv_sys_dlopen_deplibs=yes ;; kfreebsd*-gnu) libltdl_cv_sys_dlopen_deplibs=yes ;; gnu*) libltdl_cv_sys_dlopen_deplibs=yes ;; hpux10*|hpux11*) libltdl_cv_sys_dlopen_deplibs=yes ;; irix[[12345]]*|irix6.[[01]]*) # Catch all versions of IRIX before 6.2, and indicate that we don't # know how it worked for any of those versions. libltdl_cv_sys_dlopen_deplibs=unknown ;; irix*) # The case above catches anything before 6.2, and it's known that # at 6.2 and later dlopen does load deplibs. libltdl_cv_sys_dlopen_deplibs=yes ;; linux*) libltdl_cv_sys_dlopen_deplibs=yes ;; netbsd*) libltdl_cv_sys_dlopen_deplibs=yes ;; openbsd*) libltdl_cv_sys_dlopen_deplibs=yes ;; osf[[1234]]*) # dlopen did load deplibs (at least at 4.x), but until the 5.x series, # it did *not* use an RPATH in a shared library to find objects the # library depends on, so we explictly say `no'. libltdl_cv_sys_dlopen_deplibs=no ;; osf5.0|osf5.0a|osf5.1) # dlopen *does* load deplibs and with the right loader patch applied # it even uses RPATH in a shared library to search for shared objects # that the library depends on, but there's no easy way to know if that # patch is installed. Since this is the case, all we can really # say is unknown -- it depends on the patch being installed. If # it is, this changes to `yes'. Without it, it would be `no'. libltdl_cv_sys_dlopen_deplibs=unknown ;; osf*) # the two cases above should catch all versions of osf <= 5.1. Read # the comments above for what we know about them. # At > 5.1, deplibs are loaded *and* any RPATH in a shared library # is used to find them so we can finally say `yes'. libltdl_cv_sys_dlopen_deplibs=yes ;; solaris*) libltdl_cv_sys_dlopen_deplibs=yes ;; esac ]) if test "$libltdl_cv_sys_dlopen_deplibs" != yes; then AC_DEFINE([LTDL_DLOPEN_DEPLIBS], [1], [Define if the OS needs help to load dependent libraries for dlopen().]) fi ])# AC_LTDL_SYS_DLOPEN_DEPLIBS # AC_LTDL_SHLIBEXT # ---------------- AC_DEFUN([AC_LTDL_SHLIBEXT], [AC_REQUIRE([AC_LIBTOOL_SYS_DYNAMIC_LINKER]) AC_CACHE_CHECK([which extension is used for loadable modules], [libltdl_cv_shlibext], [ module=yes eval libltdl_cv_moduleext=$shrext_cmds module=no eval libltdl_cv_shlibext=$shrext_cmds if test $libltdl_cv_shlibext != $libltdl_cv_moduleext; then libltdl_cv_shlibext="$libltdl_cv_moduleext\\0$libltdl_cv_shlibext" fi ]) if test -n "$libltdl_cv_shlibext"; then AC_DEFINE_UNQUOTED(LTDL_SHLIB_EXT, "$libltdl_cv_shlibext", [Define to the extension used for shared libraries, say, ".so".]) fi ])# AC_LTDL_SHLIBEXT # AC_LTDL_SHLIBPATH # ----------------- AC_DEFUN([AC_LTDL_SHLIBPATH], [AC_REQUIRE([AC_LIBTOOL_SYS_DYNAMIC_LINKER]) AC_CACHE_CHECK([which variable specifies run-time library path], [libltdl_cv_shlibpath_var], [libltdl_cv_shlibpath_var="$shlibpath_var"]) if test -n "$libltdl_cv_shlibpath_var"; then AC_DEFINE_UNQUOTED(LTDL_SHLIBPATH_VAR, "$libltdl_cv_shlibpath_var", [Define to the name of the environment variable that determines the dynamic library search path.]) fi ])# AC_LTDL_SHLIBPATH # AC_LTDL_SYSSEARCHPATH # --------------------- AC_DEFUN([AC_LTDL_SYSSEARCHPATH], [AC_REQUIRE([AC_LIBTOOL_SYS_DYNAMIC_LINKER]) AC_CACHE_CHECK([for the default library search path], [libltdl_cv_sys_search_path], [libltdl_cv_sys_search_path="$sys_lib_dlsearch_path_spec"]) if test -n "$libltdl_cv_sys_search_path"; then sys_search_path= for dir in $libltdl_cv_sys_search_path; do if test -z "$sys_search_path"; then sys_search_path="$dir" else sys_search_path="$sys_search_path$PATH_SEPARATOR$dir" fi done AC_DEFINE_UNQUOTED(LTDL_SYSSEARCHPATH, "$sys_search_path", [Define to the system default library search path.]) fi ])# AC_LTDL_SYSSEARCHPATH # AC_LTDL_OBJDIR # -------------- AC_DEFUN([AC_LTDL_OBJDIR], [AC_CACHE_CHECK([for objdir], [libltdl_cv_objdir], [libltdl_cv_objdir="$objdir" if test -n "$objdir"; then : else rm -f .libs 2>/dev/null mkdir .libs 2>/dev/null if test -d .libs; then libltdl_cv_objdir=.libs else # MS-DOS does not allow filenames that begin with a dot. libltdl_cv_objdir=_libs fi rmdir .libs 2>/dev/null fi ]) AC_DEFINE_UNQUOTED(LTDL_OBJDIR, "$libltdl_cv_objdir/", [Define to the sub-directory in which libtool stores uninstalled libraries.]) ])# AC_LTDL_OBJDIR # AC_LTDL_DLPREOPEN # ----------------- AC_DEFUN([AC_LTDL_DLPREOPEN], [AC_REQUIRE([AC_LIBTOOL_SYS_GLOBAL_SYMBOL_PIPE]) AC_CACHE_CHECK([whether libtool supports -dlopen/-dlpreopen], [libltdl_cv_preloaded_symbols], [if test -n "$lt_cv_sys_global_symbol_pipe"; then libltdl_cv_preloaded_symbols=yes else libltdl_cv_preloaded_symbols=no fi ]) if test x"$libltdl_cv_preloaded_symbols" = xyes; then AC_DEFINE(HAVE_PRELOADED_SYMBOLS, 1, [Define if libtool can extract symbol lists from object files.]) fi ])# AC_LTDL_DLPREOPEN # AC_LTDL_DLLIB # ------------- AC_DEFUN([AC_LTDL_DLLIB], [LIBADD_DL= AC_SUBST(LIBADD_DL) AC_LANG_PUSH([C]) AC_CHECK_FUNC([shl_load], [AC_DEFINE([HAVE_SHL_LOAD], [1], [Define if you have the shl_load function.])], [AC_CHECK_LIB([dld], [shl_load], [AC_DEFINE([HAVE_SHL_LOAD], [1], [Define if you have the shl_load function.]) LIBADD_DL="$LIBADD_DL -ldld"], [AC_CHECK_LIB([dl], [dlopen], [AC_DEFINE([HAVE_LIBDL], [1], [Define if you have the libdl library or equivalent.]) LIBADD_DL="-ldl" libltdl_cv_lib_dl_dlopen="yes"], [AC_TRY_LINK([#if HAVE_DLFCN_H # include #endif ], [dlopen(0, 0);], [AC_DEFINE([HAVE_LIBDL], [1], [Define if you have the libdl library or equivalent.]) libltdl_cv_func_dlopen="yes"], [AC_CHECK_LIB([svld], [dlopen], [AC_DEFINE([HAVE_LIBDL], [1], [Define if you have the libdl library or equivalent.]) LIBADD_DL="-lsvld" libltdl_cv_func_dlopen="yes"], [AC_CHECK_LIB([dld], [dld_link], [AC_DEFINE([HAVE_DLD], [1], [Define if you have the GNU dld library.]) LIBADD_DL="$LIBADD_DL -ldld"], [AC_CHECK_FUNC([_dyld_func_lookup], [AC_DEFINE([HAVE_DYLD], [1], [Define if you have the _dyld_func_lookup function.])]) ]) ]) ]) ]) ]) ]) if test x"$libltdl_cv_func_dlopen" = xyes || test x"$libltdl_cv_lib_dl_dlopen" = xyes then lt_save_LIBS="$LIBS" LIBS="$LIBS $LIBADD_DL" AC_CHECK_FUNCS([dlerror]) LIBS="$lt_save_LIBS" fi AC_LANG_POP ])# AC_LTDL_DLLIB # AC_LTDL_SYMBOL_USCORE # --------------------- # does the compiler prefix global symbols with an underscore? AC_DEFUN([AC_LTDL_SYMBOL_USCORE], [AC_REQUIRE([AC_LIBTOOL_SYS_GLOBAL_SYMBOL_PIPE]) AC_CACHE_CHECK([for _ prefix in compiled symbols], [ac_cv_sys_symbol_underscore], [ac_cv_sys_symbol_underscore=no cat > conftest.$ac_ext < $ac_nlist) && test -s "$ac_nlist"; then # See whether the symbols have a leading underscore. if grep '^. _nm_test_func' "$ac_nlist" >/dev/null; then ac_cv_sys_symbol_underscore=yes else if grep '^. nm_test_func ' "$ac_nlist" >/dev/null; then : else echo "configure: cannot find nm_test_func in $ac_nlist" >&AC_FD_CC fi fi else echo "configure: cannot run $lt_cv_sys_global_symbol_pipe" >&AC_FD_CC fi else echo "configure: failed program was:" >&AC_FD_CC cat conftest.c >&AC_FD_CC fi rm -rf conftest* ]) ])# AC_LTDL_SYMBOL_USCORE # AC_LTDL_DLSYM_USCORE # -------------------- AC_DEFUN([AC_LTDL_DLSYM_USCORE], [AC_REQUIRE([AC_LTDL_SYMBOL_USCORE]) if test x"$ac_cv_sys_symbol_underscore" = xyes; then if test x"$libltdl_cv_func_dlopen" = xyes || test x"$libltdl_cv_lib_dl_dlopen" = xyes ; then AC_CACHE_CHECK([whether we have to add an underscore for dlsym], [libltdl_cv_need_uscore], [libltdl_cv_need_uscore=unknown save_LIBS="$LIBS" LIBS="$LIBS $LIBADD_DL" _LT_AC_TRY_DLOPEN_SELF( [libltdl_cv_need_uscore=no], [libltdl_cv_need_uscore=yes], [], [libltdl_cv_need_uscore=cross]) LIBS="$save_LIBS" ]) fi fi if test x"$libltdl_cv_need_uscore" = xyes; then AC_DEFINE(NEED_USCORE, 1, [Define if dlsym() requires a leading underscore in symbol names.]) fi ])# AC_LTDL_DLSYM_USCORE # AC_LTDL_FUNC_ARGZ # ----------------- AC_DEFUN([AC_LTDL_FUNC_ARGZ], [AC_CHECK_HEADERS([argz.h]) AC_CHECK_TYPES([error_t], [], [AC_DEFINE([error_t], [int], [Define to a type to use for `error_t' if it is not otherwise available.])], [#if HAVE_ARGZ_H # include #endif]) AC_CHECK_FUNCS([argz_append argz_create_sep argz_insert argz_next argz_stringify]) ])# AC_LTDL_FUNC_ARGZ smalltalk-3.2.5/build-aux/missing0000755000175000017500000002415212130455425013724 00000000000000#! /bin/sh # Common stub for a few missing GNU programs while installing. scriptversion=2012-01-06.13; # UTC # Copyright (C) 1996, 1997, 1999, 2000, 2002, 2003, 2004, 2005, 2006, # 2008, 2009, 2010, 2011, 2012 Free Software Foundation, Inc. # Originally by Fran,cois Pinard , 1996. # This program is free software; you can redistribute it and/or modify # it under the terms of the GNU General Public License as published by # the Free Software Foundation; either version 2, or (at your option) # any later version. # This program is distributed in the hope that it will be useful, # but WITHOUT ANY WARRANTY; without even the implied warranty of # MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the # GNU General Public License for more details. # You should have received a copy of the GNU General Public License # along with this program. If not, see . # As a special exception to the GNU General Public License, if you # distribute this file as part of a program that contains a # configuration script generated by Autoconf, you may include it under # the same distribution terms that you use for the rest of that program. if test $# -eq 0; then echo 1>&2 "Try \`$0 --help' for more information" exit 1 fi run=: sed_output='s/.* --output[ =]\([^ ]*\).*/\1/p' sed_minuso='s/.* -o \([^ ]*\).*/\1/p' # In the cases where this matters, `missing' is being run in the # srcdir already. if test -f configure.ac; then configure_ac=configure.ac else configure_ac=configure.in fi msg="missing on your system" case $1 in --run) # Try to run requested program, and just exit if it succeeds. run= shift "$@" && exit 0 # Exit code 63 means version mismatch. This often happens # when the user try to use an ancient version of a tool on # a file that requires a minimum version. In this case we # we should proceed has if the program had been absent, or # if --run hadn't been passed. if test $? = 63; then run=: msg="probably too old" fi ;; -h|--h|--he|--hel|--help) echo "\ $0 [OPTION]... PROGRAM [ARGUMENT]... Handle \`PROGRAM [ARGUMENT]...' for when PROGRAM is missing, or return an error status if there is no known handling for PROGRAM. Options: -h, --help display this help and exit -v, --version output version information and exit --run try to run the given command, and emulate it if it fails Supported PROGRAM values: aclocal touch file \`aclocal.m4' autoconf touch file \`configure' autoheader touch file \`config.h.in' autom4te touch the output file, or create a stub one automake touch all \`Makefile.in' files bison create \`y.tab.[ch]', if possible, from existing .[ch] flex create \`lex.yy.c', if possible, from existing .c help2man touch the output file lex create \`lex.yy.c', if possible, from existing .c makeinfo touch the output file yacc create \`y.tab.[ch]', if possible, from existing .[ch] Version suffixes to PROGRAM as well as the prefixes \`gnu-', \`gnu', and \`g' are ignored when checking the name. Send bug reports to ." exit $? ;; -v|--v|--ve|--ver|--vers|--versi|--versio|--version) echo "missing $scriptversion (GNU Automake)" exit $? ;; -*) echo 1>&2 "$0: Unknown \`$1' option" echo 1>&2 "Try \`$0 --help' for more information" exit 1 ;; esac # normalize program name to check for. program=`echo "$1" | sed ' s/^gnu-//; t s/^gnu//; t s/^g//; t'` # Now exit if we have it, but it failed. Also exit now if we # don't have it and --version was passed (most likely to detect # the program). This is about non-GNU programs, so use $1 not # $program. case $1 in lex*|yacc*) # Not GNU programs, they don't have --version. ;; *) if test -z "$run" && ($1 --version) > /dev/null 2>&1; then # We have it, but it failed. exit 1 elif test "x$2" = "x--version" || test "x$2" = "x--help"; then # Could not run --version or --help. This is probably someone # running `$TOOL --version' or `$TOOL --help' to check whether # $TOOL exists and not knowing $TOOL uses missing. exit 1 fi ;; esac # If it does not exist, or fails to run (possibly an outdated version), # try to emulate it. case $program in aclocal*) echo 1>&2 "\ WARNING: \`$1' is $msg. You should only need it if you modified \`acinclude.m4' or \`${configure_ac}'. You might want to install the \`Automake' and \`Perl' packages. Grab them from any GNU archive site." touch aclocal.m4 ;; autoconf*) echo 1>&2 "\ WARNING: \`$1' is $msg. You should only need it if you modified \`${configure_ac}'. You might want to install the \`Autoconf' and \`GNU m4' packages. Grab them from any GNU archive site." touch configure ;; autoheader*) echo 1>&2 "\ WARNING: \`$1' is $msg. You should only need it if you modified \`acconfig.h' or \`${configure_ac}'. You might want to install the \`Autoconf' and \`GNU m4' packages. Grab them from any GNU archive site." files=`sed -n 's/^[ ]*A[CM]_CONFIG_HEADER(\([^)]*\)).*/\1/p' ${configure_ac}` test -z "$files" && files="config.h" touch_files= for f in $files; do case $f in *:*) touch_files="$touch_files "`echo "$f" | sed -e 's/^[^:]*://' -e 's/:.*//'`;; *) touch_files="$touch_files $f.in";; esac done touch $touch_files ;; automake*) echo 1>&2 "\ WARNING: \`$1' is $msg. You should only need it if you modified \`Makefile.am', \`acinclude.m4' or \`${configure_ac}'. You might want to install the \`Automake' and \`Perl' packages. Grab them from any GNU archive site." find . -type f -name Makefile.am -print | sed 's/\.am$/.in/' | while read f; do touch "$f"; done ;; autom4te*) echo 1>&2 "\ WARNING: \`$1' is needed, but is $msg. You might have modified some files without having the proper tools for further handling them. You can get \`$1' as part of \`Autoconf' from any GNU archive site." file=`echo "$*" | sed -n "$sed_output"` test -z "$file" && file=`echo "$*" | sed -n "$sed_minuso"` if test -f "$file"; then touch $file else test -z "$file" || exec >$file echo "#! /bin/sh" echo "# Created by GNU Automake missing as a replacement of" echo "# $ $@" echo "exit 0" chmod +x $file exit 1 fi ;; bison*|yacc*) echo 1>&2 "\ WARNING: \`$1' $msg. You should only need it if you modified a \`.y' file. You may need the \`Bison' package in order for those modifications to take effect. You can get \`Bison' from any GNU archive site." rm -f y.tab.c y.tab.h if test $# -ne 1; then eval LASTARG=\${$#} case $LASTARG in *.y) SRCFILE=`echo "$LASTARG" | sed 's/y$/c/'` if test -f "$SRCFILE"; then cp "$SRCFILE" y.tab.c fi SRCFILE=`echo "$LASTARG" | sed 's/y$/h/'` if test -f "$SRCFILE"; then cp "$SRCFILE" y.tab.h fi ;; esac fi if test ! -f y.tab.h; then echo >y.tab.h fi if test ! -f y.tab.c; then echo 'main() { return 0; }' >y.tab.c fi ;; lex*|flex*) echo 1>&2 "\ WARNING: \`$1' is $msg. You should only need it if you modified a \`.l' file. You may need the \`Flex' package in order for those modifications to take effect. You can get \`Flex' from any GNU archive site." rm -f lex.yy.c if test $# -ne 1; then eval LASTARG=\${$#} case $LASTARG in *.l) SRCFILE=`echo "$LASTARG" | sed 's/l$/c/'` if test -f "$SRCFILE"; then cp "$SRCFILE" lex.yy.c fi ;; esac fi if test ! -f lex.yy.c; then echo 'main() { return 0; }' >lex.yy.c fi ;; help2man*) echo 1>&2 "\ WARNING: \`$1' is $msg. You should only need it if you modified a dependency of a manual page. You may need the \`Help2man' package in order for those modifications to take effect. You can get \`Help2man' from any GNU archive site." file=`echo "$*" | sed -n "$sed_output"` test -z "$file" && file=`echo "$*" | sed -n "$sed_minuso"` if test -f "$file"; then touch $file else test -z "$file" || exec >$file echo ".ab help2man is required to generate this page" exit $? fi ;; makeinfo*) echo 1>&2 "\ WARNING: \`$1' is $msg. You should only need it if you modified a \`.texi' or \`.texinfo' file, or any other file indirectly affecting the aspect of the manual. The spurious call might also be the consequence of using a buggy \`make' (AIX, DU, IRIX). You might want to install the \`Texinfo' package or the \`GNU make' package. Grab either from any GNU archive site." # The file to touch is that specified with -o ... file=`echo "$*" | sed -n "$sed_output"` test -z "$file" && file=`echo "$*" | sed -n "$sed_minuso"` if test -z "$file"; then # ... or it is the one specified with @setfilename ... infile=`echo "$*" | sed 's/.* \([^ ]*\) *$/\1/'` file=`sed -n ' /^@setfilename/{ s/.* \([^ ]*\) *$/\1/ p q }' $infile` # ... or it is derived from the source name (dir/f.texi becomes f.info) test -z "$file" && file=`echo "$infile" | sed 's,.*/,,;s,.[^.]*$,,'`.info fi # If the file does not exist, the user really needs makeinfo; # let's fail without touching anything. test -f $file || exit 1 touch $file ;; *) echo 1>&2 "\ WARNING: \`$1' is needed, and is $msg. You might have modified some files without having the proper tools for further handling them. Check the \`README' file, it often tells you about the needed prerequisites for installing this package. You may also peek at any GNU archive site, in case some other package would contain this missing \`$1' program." exit 1 ;; esac exit 0 # Local variables: # eval: (add-hook 'write-file-hooks 'time-stamp) # time-stamp-start: "scriptversion=" # time-stamp-format: "%:y-%02m-%02d.%02H" # time-stamp-time-zone: "UTC" # time-stamp-end: "; # UTC" # End: smalltalk-3.2.5/build-aux/getpagesize.m40000644000175000017500000000401012123404352015060 00000000000000# getpagesize.m4 serial 2 (libsigsegv-2.2) dnl Copyright (C) 2002-2003 Bruno Haible dnl This file is free software, distributed under the terms of the GNU dnl General Public License. As a special exception to the GNU General dnl Public License, this file may be distributed as part of a program dnl that contains a configuration script generated by Autoconf, under dnl the same distribution terms as the rest of that program. # How to determine the memory page size. AC_DEFUN([SV_GETPAGESIZE], [ AC_REQUIRE([AC_PROG_CC]) AC_CHECK_HEADERS(unistd.h) dnl 1) getpagesize(). AC_CACHE_CHECK([for getpagesize], sv_cv_func_getpagesize, [ AC_LINK_IFELSE([ AC_LANG_PROGRAM([[ #if HAVE_UNISTD_H #include #include #endif ]], [[int pgsz = getpagesize();]])], [sv_cv_func_getpagesize=yes], [sv_cv_func_getpagesize=no])]) if test $sv_cv_func_getpagesize = yes; then AC_DEFINE(HAVE_GETPAGESIZE, 1, [Define if getpagesize() is available as a function or a macro.]) fi dnl 2) sysconf(_SC_PAGESIZE). AC_CACHE_CHECK([for sysconf(_SC_PAGESIZE)], sv_cv_func_sysconf_pagesize, [ AC_LINK_IFELSE([ AC_LANG_PROGRAM([[ #if HAVE_UNISTD_H #include #include #endif ]], [[int pgsz = sysconf (_SC_PAGESIZE);]])], [sv_cv_func_sysconf_pagesize=yes], [sv_cv_func_sysconf_pagesize=no])]) if test $sv_cv_func_sysconf_pagesize = yes; then AC_DEFINE(HAVE_SYSCONF_PAGESIZE, 1, [Define if sysconf(_SC_PAGESIZE) is available as a function or a macro.]) fi dnl 3) PAGESIZE. AC_CACHE_CHECK([for PAGESIZE in limits.h], sv_cv_macro_pagesize, [ AC_LINK_IFELSE([ AC_LANG_PROGRAM([[#include ]], [[int pgsz = PAGESIZE;]])], [sv_cv_macro_pagesize=yes], [sv_cv_macro_pagesize=no])]) if test $sv_cv_macro_pagesize = yes; then AC_DEFINE(HAVE_PAGESIZE, 1, [Define if PAGESIZE is available as a macro.]) fi dnl 4) On BeOS, you need to include and use B_PAGE_SIZE. ]) smalltalk-3.2.5/build-aux/sync-builtins.m40000644000175000017500000000255712123404352015372 00000000000000dnl Check whether the host supports synchronization builtins. AC_DEFUN([GST_C_SYNC_BUILTINS], [ AC_REQUIRE([AC_CANONICAL_HOST]) AC_CACHE_CHECK([whether the host supports __sync_fetch_and_add], gst_cv_have_sync_fetch_and_add, [ save_CFLAGS="$CFLAGS" case $host in i?86-apple-darwin*) ;; i?86-*-*) CFLAGS="$CFLAGS -march=i486" ;; esac AC_LINK_IFELSE([AC_LANG_PROGRAM([[int foovar = 0;]], [[ if (foovar <= 0) return __sync_fetch_and_add (&foovar, 1); if (foovar > 10) return __sync_add_and_fetch (&foovar, -1);]])], [gst_cv_have_sync_fetch_and_add=yes], [gst_cv_have_sync_fetch_and_add=no]) CFLAGS="$save_CFLAGS" ]) if test $gst_cv_have_sync_fetch_and_add = yes; then AC_DEFINE(HAVE_SYNC_BUILTINS, 1, [Define to 1 if the host supports __sync_* builtins]) AC_CACHE_CHECK([whether the host is i386], gst_cv_cc_arch_i386, [ AC_LINK_IFELSE([AC_LANG_PROGRAM([[int foovar = 0;]], [[ if (foovar <= 0) return __sync_fetch_and_add (&foovar, 1); if (foovar > 10) return __sync_add_and_fetch (&foovar, -1);]])], [gst_cv_cc_arch_i386=no], [gst_cv_cc_arch_i386=yes]) ]) if test $gst_cv_cc_arch_i386 = yes; then AC_MSG_WARN([$PACKAGE_NAME will be compiled for i486]) SYNC_CFLAGS="-march=i486" else SYNC_CFLAGS= fi fi AC_SUBST([SYNC_CFLAGS]) ]) smalltalk-3.2.5/build-aux/depcomp0000755000175000017500000005064312130455426013707 00000000000000#! /bin/sh # depcomp - compile a program generating dependencies as side-effects scriptversion=2012-03-27.16; # UTC # Copyright (C) 1999, 2000, 2003, 2004, 2005, 2006, 2007, 2009, 2010, # 2011, 2012 Free Software Foundation, Inc. # This program is free software; you can redistribute it and/or modify # it under the terms of the GNU General Public License as published by # the Free Software Foundation; either version 2, or (at your option) # any later version. # This program is distributed in the hope that it will be useful, # but WITHOUT ANY WARRANTY; without even the implied warranty of # MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the # GNU General Public License for more details. # You should have received a copy of the GNU General Public License # along with this program. If not, see . # As a special exception to the GNU General Public License, if you # distribute this file as part of a program that contains a # configuration script generated by Autoconf, you may include it under # the same distribution terms that you use for the rest of that program. # Originally written by Alexandre Oliva . case $1 in '') echo "$0: No command. Try '$0 --help' for more information." 1>&2 exit 1; ;; -h | --h*) cat <<\EOF Usage: depcomp [--help] [--version] PROGRAM [ARGS] Run PROGRAMS ARGS to compile a file, generating dependencies as side-effects. Environment variables: depmode Dependency tracking mode. source Source file read by 'PROGRAMS ARGS'. object Object file output by 'PROGRAMS ARGS'. DEPDIR directory where to store dependencies. depfile Dependency file to output. tmpdepfile Temporary file to use when outputting dependencies. libtool Whether libtool is used (yes/no). Report bugs to . EOF exit $? ;; -v | --v*) echo "depcomp $scriptversion" exit $? ;; esac # A tabulation character. tab=' ' # A newline character. nl=' ' if test -z "$depmode" || test -z "$source" || test -z "$object"; then echo "depcomp: Variables source, object and depmode must be set" 1>&2 exit 1 fi # Dependencies for sub/bar.o or sub/bar.obj go into sub/.deps/bar.Po. depfile=${depfile-`echo "$object" | sed 's|[^\\/]*$|'${DEPDIR-.deps}'/&|;s|\.\([^.]*\)$|.P\1|;s|Pobj$|Po|'`} tmpdepfile=${tmpdepfile-`echo "$depfile" | sed 's/\.\([^.]*\)$/.T\1/'`} rm -f "$tmpdepfile" # Some modes work just like other modes, but use different flags. We # parameterize here, but still list the modes in the big case below, # to make depend.m4 easier to write. Note that we *cannot* use a case # here, because this file can only contain one case statement. if test "$depmode" = hp; then # HP compiler uses -M and no extra arg. gccflag=-M depmode=gcc fi if test "$depmode" = dashXmstdout; then # This is just like dashmstdout with a different argument. dashmflag=-xM depmode=dashmstdout fi cygpath_u="cygpath -u -f -" if test "$depmode" = msvcmsys; then # This is just like msvisualcpp but w/o cygpath translation. # Just convert the backslash-escaped backslashes to single forward # slashes to satisfy depend.m4 cygpath_u='sed s,\\\\,/,g' depmode=msvisualcpp fi if test "$depmode" = msvc7msys; then # This is just like msvc7 but w/o cygpath translation. # Just convert the backslash-escaped backslashes to single forward # slashes to satisfy depend.m4 cygpath_u='sed s,\\\\,/,g' depmode=msvc7 fi if test "$depmode" = xlc; then # IBM C/C++ Compilers xlc/xlC can output gcc-like dependency informations. gccflag=-qmakedep=gcc,-MF depmode=gcc fi case "$depmode" in gcc3) ## gcc 3 implements dependency tracking that does exactly what ## we want. Yay! Note: for some reason libtool 1.4 doesn't like ## it if -MD -MP comes after the -MF stuff. Hmm. ## Unfortunately, FreeBSD c89 acceptance of flags depends upon ## the command line argument order; so add the flags where they ## appear in depend2.am. Note that the slowdown incurred here ## affects only configure: in makefiles, %FASTDEP% shortcuts this. for arg do case $arg in -c) set fnord "$@" -MT "$object" -MD -MP -MF "$tmpdepfile" "$arg" ;; *) set fnord "$@" "$arg" ;; esac shift # fnord shift # $arg done "$@" stat=$? if test $stat -eq 0; then : else rm -f "$tmpdepfile" exit $stat fi mv "$tmpdepfile" "$depfile" ;; gcc) ## There are various ways to get dependency output from gcc. Here's ## why we pick this rather obscure method: ## - Don't want to use -MD because we'd like the dependencies to end ## up in a subdir. Having to rename by hand is ugly. ## (We might end up doing this anyway to support other compilers.) ## - The DEPENDENCIES_OUTPUT environment variable makes gcc act like ## -MM, not -M (despite what the docs say). ## - Using -M directly means running the compiler twice (even worse ## than renaming). if test -z "$gccflag"; then gccflag=-MD, fi "$@" -Wp,"$gccflag$tmpdepfile" stat=$? if test $stat -eq 0; then : else rm -f "$tmpdepfile" exit $stat fi rm -f "$depfile" echo "$object : \\" > "$depfile" alpha=ABCDEFGHIJKLMNOPQRSTUVWXYZabcdefghijklmnopqrstuvwxyz ## The second -e expression handles DOS-style file names with drive letters. sed -e 's/^[^:]*: / /' \ -e 's/^['$alpha']:\/[^:]*: / /' < "$tmpdepfile" >> "$depfile" ## This next piece of magic avoids the "deleted header file" problem. ## The problem is that when a header file which appears in a .P file ## is deleted, the dependency causes make to die (because there is ## typically no way to rebuild the header). We avoid this by adding ## dummy dependencies for each header file. Too bad gcc doesn't do ## this for us directly. tr ' ' "$nl" < "$tmpdepfile" | ## Some versions of gcc put a space before the ':'. On the theory ## that the space means something, we add a space to the output as ## well. hp depmode also adds that space, but also prefixes the VPATH ## to the object. Take care to not repeat it in the output. ## Some versions of the HPUX 10.20 sed can't process this invocation ## correctly. Breaking it into two sed invocations is a workaround. sed -e 's/^\\$//' -e '/^$/d' -e "s|.*$object$||" -e '/:$/d' \ | sed -e 's/$/ :/' >> "$depfile" rm -f "$tmpdepfile" ;; hp) # This case exists only to let depend.m4 do its work. It works by # looking at the text of this script. This case will never be run, # since it is checked for above. exit 1 ;; sgi) if test "$libtool" = yes; then "$@" "-Wp,-MDupdate,$tmpdepfile" else "$@" -MDupdate "$tmpdepfile" fi stat=$? if test $stat -eq 0; then : else rm -f "$tmpdepfile" exit $stat fi rm -f "$depfile" if test -f "$tmpdepfile"; then # yes, the sourcefile depend on other files echo "$object : \\" > "$depfile" # Clip off the initial element (the dependent). Don't try to be # clever and replace this with sed code, as IRIX sed won't handle # lines with more than a fixed number of characters (4096 in # IRIX 6.2 sed, 8192 in IRIX 6.5). We also remove comment lines; # the IRIX cc adds comments like '#:fec' to the end of the # dependency line. tr ' ' "$nl" < "$tmpdepfile" \ | sed -e 's/^.*\.o://' -e 's/#.*$//' -e '/^$/ d' | \ tr "$nl" ' ' >> "$depfile" echo >> "$depfile" # The second pass generates a dummy entry for each header file. tr ' ' "$nl" < "$tmpdepfile" \ | sed -e 's/^.*\.o://' -e 's/#.*$//' -e '/^$/ d' -e 's/$/:/' \ >> "$depfile" else # The sourcefile does not contain any dependencies, so just # store a dummy comment line, to avoid errors with the Makefile # "include basename.Plo" scheme. echo "#dummy" > "$depfile" fi rm -f "$tmpdepfile" ;; xlc) # This case exists only to let depend.m4 do its work. It works by # looking at the text of this script. This case will never be run, # since it is checked for above. exit 1 ;; aix) # The C for AIX Compiler uses -M and outputs the dependencies # in a .u file. In older versions, this file always lives in the # current directory. Also, the AIX compiler puts '$object:' at the # start of each line; $object doesn't have directory information. # Version 6 uses the directory in both cases. dir=`echo "$object" | sed -e 's|/[^/]*$|/|'` test "x$dir" = "x$object" && dir= base=`echo "$object" | sed -e 's|^.*/||' -e 's/\.o$//' -e 's/\.lo$//'` if test "$libtool" = yes; then tmpdepfile1=$dir$base.u tmpdepfile2=$base.u tmpdepfile3=$dir.libs/$base.u "$@" -Wc,-M else tmpdepfile1=$dir$base.u tmpdepfile2=$dir$base.u tmpdepfile3=$dir$base.u "$@" -M fi stat=$? if test $stat -eq 0; then : else rm -f "$tmpdepfile1" "$tmpdepfile2" "$tmpdepfile3" exit $stat fi for tmpdepfile in "$tmpdepfile1" "$tmpdepfile2" "$tmpdepfile3" do test -f "$tmpdepfile" && break done if test -f "$tmpdepfile"; then # Each line is of the form 'foo.o: dependent.h'. # Do two passes, one to just change these to # '$object: dependent.h' and one to simply 'dependent.h:'. sed -e "s,^.*\.[a-z]*:,$object:," < "$tmpdepfile" > "$depfile" sed -e 's,^.*\.[a-z]*:['"$tab"' ]*,,' -e 's,$,:,' < "$tmpdepfile" >> "$depfile" else # The sourcefile does not contain any dependencies, so just # store a dummy comment line, to avoid errors with the Makefile # "include basename.Plo" scheme. echo "#dummy" > "$depfile" fi rm -f "$tmpdepfile" ;; icc) # Intel's C compiler anf tcc (Tiny C Compiler) understand '-MD -MF file'. # However on # $CC -MD -MF foo.d -c -o sub/foo.o sub/foo.c # ICC 7.0 will fill foo.d with something like # foo.o: sub/foo.c # foo.o: sub/foo.h # which is wrong. We want # sub/foo.o: sub/foo.c # sub/foo.o: sub/foo.h # sub/foo.c: # sub/foo.h: # ICC 7.1 will output # foo.o: sub/foo.c sub/foo.h # and will wrap long lines using '\': # foo.o: sub/foo.c ... \ # sub/foo.h ... \ # ... # tcc 0.9.26 (FIXME still under development at the moment of writing) # will emit a similar output, but also prepend the continuation lines # with horizontal tabulation characters. "$@" -MD -MF "$tmpdepfile" stat=$? if test $stat -eq 0; then : else rm -f "$tmpdepfile" exit $stat fi rm -f "$depfile" # Each line is of the form 'foo.o: dependent.h', # or 'foo.o: dep1.h dep2.h \', or ' dep3.h dep4.h \'. # Do two passes, one to just change these to # '$object: dependent.h' and one to simply 'dependent.h:'. sed -e "s/^[ $tab][ $tab]*/ /" -e "s,^[^:]*:,$object :," \ < "$tmpdepfile" > "$depfile" sed ' s/[ '"$tab"'][ '"$tab"']*/ /g s/^ *// s/ *\\*$// s/^[^:]*: *// /^$/d /:$/d s/$/ :/ ' < "$tmpdepfile" >> "$depfile" rm -f "$tmpdepfile" ;; hp2) # The "hp" stanza above does not work with aCC (C++) and HP's ia64 # compilers, which have integrated preprocessors. The correct option # to use with these is +Maked; it writes dependencies to a file named # 'foo.d', which lands next to the object file, wherever that # happens to be. # Much of this is similar to the tru64 case; see comments there. dir=`echo "$object" | sed -e 's|/[^/]*$|/|'` test "x$dir" = "x$object" && dir= base=`echo "$object" | sed -e 's|^.*/||' -e 's/\.o$//' -e 's/\.lo$//'` if test "$libtool" = yes; then tmpdepfile1=$dir$base.d tmpdepfile2=$dir.libs/$base.d "$@" -Wc,+Maked else tmpdepfile1=$dir$base.d tmpdepfile2=$dir$base.d "$@" +Maked fi stat=$? if test $stat -eq 0; then : else rm -f "$tmpdepfile1" "$tmpdepfile2" exit $stat fi for tmpdepfile in "$tmpdepfile1" "$tmpdepfile2" do test -f "$tmpdepfile" && break done if test -f "$tmpdepfile"; then sed -e "s,^.*\.[a-z]*:,$object:," "$tmpdepfile" > "$depfile" # Add 'dependent.h:' lines. sed -ne '2,${ s/^ *// s/ \\*$// s/$/:/ p }' "$tmpdepfile" >> "$depfile" else echo "#dummy" > "$depfile" fi rm -f "$tmpdepfile" "$tmpdepfile2" ;; tru64) # The Tru64 compiler uses -MD to generate dependencies as a side # effect. 'cc -MD -o foo.o ...' puts the dependencies into 'foo.o.d'. # At least on Alpha/Redhat 6.1, Compaq CCC V6.2-504 seems to put # dependencies in 'foo.d' instead, so we check for that too. # Subdirectories are respected. dir=`echo "$object" | sed -e 's|/[^/]*$|/|'` test "x$dir" = "x$object" && dir= base=`echo "$object" | sed -e 's|^.*/||' -e 's/\.o$//' -e 's/\.lo$//'` if test "$libtool" = yes; then # With Tru64 cc, shared objects can also be used to make a # static library. This mechanism is used in libtool 1.4 series to # handle both shared and static libraries in a single compilation. # With libtool 1.4, dependencies were output in $dir.libs/$base.lo.d. # # With libtool 1.5 this exception was removed, and libtool now # generates 2 separate objects for the 2 libraries. These two # compilations output dependencies in $dir.libs/$base.o.d and # in $dir$base.o.d. We have to check for both files, because # one of the two compilations can be disabled. We should prefer # $dir$base.o.d over $dir.libs/$base.o.d because the latter is # automatically cleaned when .libs/ is deleted, while ignoring # the former would cause a distcleancheck panic. tmpdepfile1=$dir.libs/$base.lo.d # libtool 1.4 tmpdepfile2=$dir$base.o.d # libtool 1.5 tmpdepfile3=$dir.libs/$base.o.d # libtool 1.5 tmpdepfile4=$dir.libs/$base.d # Compaq CCC V6.2-504 "$@" -Wc,-MD else tmpdepfile1=$dir$base.o.d tmpdepfile2=$dir$base.d tmpdepfile3=$dir$base.d tmpdepfile4=$dir$base.d "$@" -MD fi stat=$? if test $stat -eq 0; then : else rm -f "$tmpdepfile1" "$tmpdepfile2" "$tmpdepfile3" "$tmpdepfile4" exit $stat fi for tmpdepfile in "$tmpdepfile1" "$tmpdepfile2" "$tmpdepfile3" "$tmpdepfile4" do test -f "$tmpdepfile" && break done if test -f "$tmpdepfile"; then sed -e "s,^.*\.[a-z]*:,$object:," < "$tmpdepfile" > "$depfile" sed -e 's,^.*\.[a-z]*:['"$tab"' ]*,,' -e 's,$,:,' < "$tmpdepfile" >> "$depfile" else echo "#dummy" > "$depfile" fi rm -f "$tmpdepfile" ;; msvc7) if test "$libtool" = yes; then showIncludes=-Wc,-showIncludes else showIncludes=-showIncludes fi "$@" $showIncludes > "$tmpdepfile" stat=$? grep -v '^Note: including file: ' "$tmpdepfile" if test "$stat" = 0; then : else rm -f "$tmpdepfile" exit $stat fi rm -f "$depfile" echo "$object : \\" > "$depfile" # The first sed program below extracts the file names and escapes # backslashes for cygpath. The second sed program outputs the file # name when reading, but also accumulates all include files in the # hold buffer in order to output them again at the end. This only # works with sed implementations that can handle large buffers. sed < "$tmpdepfile" -n ' /^Note: including file: *\(.*\)/ { s//\1/ s/\\/\\\\/g p }' | $cygpath_u | sort -u | sed -n ' s/ /\\ /g s/\(.*\)/'"$tab"'\1 \\/p s/.\(.*\) \\/\1:/ H $ { s/.*/'"$tab"'/ G p }' >> "$depfile" rm -f "$tmpdepfile" ;; msvc7msys) # This case exists only to let depend.m4 do its work. It works by # looking at the text of this script. This case will never be run, # since it is checked for above. exit 1 ;; #nosideeffect) # This comment above is used by automake to tell side-effect # dependency tracking mechanisms from slower ones. dashmstdout) # Important note: in order to support this mode, a compiler *must* # always write the preprocessed file to stdout, regardless of -o. "$@" || exit $? # Remove the call to Libtool. if test "$libtool" = yes; then while test "X$1" != 'X--mode=compile'; do shift done shift fi # Remove '-o $object'. IFS=" " for arg do case $arg in -o) shift ;; $object) shift ;; *) set fnord "$@" "$arg" shift # fnord shift # $arg ;; esac done test -z "$dashmflag" && dashmflag=-M # Require at least two characters before searching for ':' # in the target name. This is to cope with DOS-style filenames: # a dependency such as 'c:/foo/bar' could be seen as target 'c' otherwise. "$@" $dashmflag | sed 's:^['"$tab"' ]*[^:'"$tab"' ][^:][^:]*\:['"$tab"' ]*:'"$object"'\: :' > "$tmpdepfile" rm -f "$depfile" cat < "$tmpdepfile" > "$depfile" tr ' ' "$nl" < "$tmpdepfile" | \ ## Some versions of the HPUX 10.20 sed can't process this invocation ## correctly. Breaking it into two sed invocations is a workaround. sed -e 's/^\\$//' -e '/^$/d' -e '/:$/d' | sed -e 's/$/ :/' >> "$depfile" rm -f "$tmpdepfile" ;; dashXmstdout) # This case only exists to satisfy depend.m4. It is never actually # run, as this mode is specially recognized in the preamble. exit 1 ;; makedepend) "$@" || exit $? # Remove any Libtool call if test "$libtool" = yes; then while test "X$1" != 'X--mode=compile'; do shift done shift fi # X makedepend shift cleared=no eat=no for arg do case $cleared in no) set ""; shift cleared=yes ;; esac if test $eat = yes; then eat=no continue fi case "$arg" in -D*|-I*) set fnord "$@" "$arg"; shift ;; # Strip any option that makedepend may not understand. Remove # the object too, otherwise makedepend will parse it as a source file. -arch) eat=yes ;; -*|$object) ;; *) set fnord "$@" "$arg"; shift ;; esac done obj_suffix=`echo "$object" | sed 's/^.*\././'` touch "$tmpdepfile" ${MAKEDEPEND-makedepend} -o"$obj_suffix" -f"$tmpdepfile" "$@" rm -f "$depfile" # makedepend may prepend the VPATH from the source file name to the object. # No need to regex-escape $object, excess matching of '.' is harmless. sed "s|^.*\($object *:\)|\1|" "$tmpdepfile" > "$depfile" sed '1,2d' "$tmpdepfile" | tr ' ' "$nl" | \ ## Some versions of the HPUX 10.20 sed can't process this invocation ## correctly. Breaking it into two sed invocations is a workaround. sed -e 's/^\\$//' -e '/^$/d' -e '/:$/d' | sed -e 's/$/ :/' >> "$depfile" rm -f "$tmpdepfile" "$tmpdepfile".bak ;; cpp) # Important note: in order to support this mode, a compiler *must* # always write the preprocessed file to stdout. "$@" || exit $? # Remove the call to Libtool. if test "$libtool" = yes; then while test "X$1" != 'X--mode=compile'; do shift done shift fi # Remove '-o $object'. IFS=" " for arg do case $arg in -o) shift ;; $object) shift ;; *) set fnord "$@" "$arg" shift # fnord shift # $arg ;; esac done "$@" -E | sed -n -e '/^# [0-9][0-9]* "\([^"]*\)".*/ s:: \1 \\:p' \ -e '/^#line [0-9][0-9]* "\([^"]*\)".*/ s:: \1 \\:p' | sed '$ s: \\$::' > "$tmpdepfile" rm -f "$depfile" echo "$object : \\" > "$depfile" cat < "$tmpdepfile" >> "$depfile" sed < "$tmpdepfile" '/^$/d;s/^ //;s/ \\$//;s/$/ :/' >> "$depfile" rm -f "$tmpdepfile" ;; msvisualcpp) # Important note: in order to support this mode, a compiler *must* # always write the preprocessed file to stdout. "$@" || exit $? # Remove the call to Libtool. if test "$libtool" = yes; then while test "X$1" != 'X--mode=compile'; do shift done shift fi IFS=" " for arg do case "$arg" in -o) shift ;; $object) shift ;; "-Gm"|"/Gm"|"-Gi"|"/Gi"|"-ZI"|"/ZI") set fnord "$@" shift shift ;; *) set fnord "$@" "$arg" shift shift ;; esac done "$@" -E 2>/dev/null | sed -n '/^#line [0-9][0-9]* "\([^"]*\)"/ s::\1:p' | $cygpath_u | sort -u > "$tmpdepfile" rm -f "$depfile" echo "$object : \\" > "$depfile" sed < "$tmpdepfile" -n -e 's% %\\ %g' -e '/^\(.*\)$/ s::'"$tab"'\1 \\:p' >> "$depfile" echo "$tab" >> "$depfile" sed < "$tmpdepfile" -n -e 's% %\\ %g' -e '/^\(.*\)$/ s::\1\::p' >> "$depfile" rm -f "$tmpdepfile" ;; msvcmsys) # This case exists only to let depend.m4 do its work. It works by # looking at the text of this script. This case will never be run, # since it is checked for above. exit 1 ;; none) exec "$@" ;; *) echo "Unknown depmode $depmode" 1>&2 exit 1 ;; esac exit 0 # Local Variables: # mode: shell-script # sh-indentation: 2 # eval: (add-hook 'write-file-hooks 'time-stamp) # time-stamp-start: "scriptversion=" # time-stamp-format: "%:y-%02m-%02d.%02H" # time-stamp-time-zone: "UTC" # time-stamp-end: "; # UTC" # End: smalltalk-3.2.5/build-aux/lib-prefix.m40000644000175000017500000001175512123404352014630 00000000000000# lib-prefix.m4 serial 1 (gettext-0.11) dnl Copyright (C) 2001-2002 Free Software Foundation, Inc. dnl This file is free software, distributed under the terms of the GNU dnl General Public License. As a special exception to the GNU General dnl Public License, this file may be distributed as part of a program dnl that contains a configuration script generated by Autoconf, under dnl the same distribution terms as the rest of that program. dnl From Bruno Haible. dnl AC_LIB_PREFIX adds to the CPPFLAGS and LDFLAGS the flags that are needed dnl to access previously installed libraries. The basic assumption is that dnl a user will want packages to use other packages he previously installed dnl with the same --prefix option. dnl This macro is not needed if only AC_LIB_LINKFLAGS is used to locate dnl libraries, but is otherwise very convenient. AC_DEFUN([AC_LIB_PREFIX], [ AC_BEFORE([$0], [AC_LIB_LINKFLAGS]) AC_REQUIRE([AC_PROG_CC]) AC_REQUIRE([AC_CANONICAL_HOST]) AC_REQUIRE([AC_LIB_PREPARE_PREFIX]) dnl By default, look in $includedir and $libdir. use_additional=yes AC_LIB_WITH_FINAL_PREFIX([ eval additional_includedir=\"$includedir\" eval additional_libdir=\"$libdir\" ]) AC_ARG_WITH([lib-prefix], [ --with-lib-prefix[=DIR] search for libraries in DIR/include and DIR/lib --without-lib-prefix don't search for libraries in includedir and libdir], [ if test "X$withval" = "Xno"; then use_additional=no else if test "X$withval" = "X"; then AC_LIB_WITH_FINAL_PREFIX([ eval additional_includedir=\"$includedir\" eval additional_libdir=\"$libdir\" ]) else additional_includedir="$withval/include" additional_libdir="$withval/lib" fi fi ]) if test $use_additional = yes; then dnl Potentially add $additional_includedir to $CPPFLAGS. dnl But don't add it dnl 1. if it's the standard /usr/include, dnl 2. if it's already present in $CPPFLAGS, dnl 3. if it's /usr/local/include and we are using GCC on Linux, dnl 4. if it doesn't exist as a directory. if test "X$additional_includedir" != "X/usr/include"; then haveit= for x in $CPPFLAGS; do AC_LIB_WITH_FINAL_PREFIX([eval x=\"$x\"]) if test "X$x" = "X-I$additional_includedir"; then haveit=yes break fi done if test -z "$haveit"; then if test "X$additional_includedir" = "X/usr/local/include"; then if test -n "$GCC"; then case $host_os in linux*) haveit=yes;; esac fi fi if test -z "$haveit"; then if test -d "$additional_includedir"; then dnl Really add $additional_includedir to $CPPFLAGS. CPPFLAGS="${CPPFLAGS}${CPPFLAGS:+ }-I$additional_includedir" fi fi fi fi dnl Potentially add $additional_libdir to $LDFLAGS. dnl But don't add it dnl 1. if it's the standard /usr/lib, dnl 2. if it's already present in $LDFLAGS, dnl 3. if it's /usr/local/lib and we are using GCC on Linux, dnl 4. if it doesn't exist as a directory. if test "X$additional_libdir" != "X/usr/lib"; then haveit= for x in $LDFLAGS; do AC_LIB_WITH_FINAL_PREFIX([eval x=\"$x\"]) if test "X$x" = "X-L$additional_libdir"; then haveit=yes break fi done if test -z "$haveit"; then if test "X$additional_libdir" = "X/usr/local/lib"; then if test -n "$GCC"; then case $host_os in linux*) haveit=yes;; esac fi fi if test -z "$haveit"; then if test -d "$additional_libdir"; then dnl Really add $additional_libdir to $LDFLAGS. LDFLAGS="${LDFLAGS}${LDFLAGS:+ }-L$additional_libdir" fi fi fi fi fi ]) dnl AC_LIB_PREPARE_PREFIX creates variables acl_final_prefix, dnl acl_final_exec_prefix, containing the values to which $prefix and dnl $exec_prefix will expand at the end of the configure script. AC_DEFUN([AC_LIB_PREPARE_PREFIX], [ dnl Unfortunately, prefix and exec_prefix get only finally determined dnl at the end of configure. if test "X$prefix" = "XNONE"; then acl_final_prefix="$ac_default_prefix" else acl_final_prefix="$prefix" fi if test "X$exec_prefix" = "XNONE"; then acl_final_exec_prefix='${prefix}' else acl_final_exec_prefix="$exec_prefix" fi acl_save_prefix="$prefix" prefix="$acl_final_prefix" eval acl_final_exec_prefix=\"$acl_final_exec_prefix\" prefix="$acl_save_prefix" ]) dnl AC_LIB_WITH_FINAL_PREFIX([statement]) evaluates statement, with the dnl variables prefix and exec_prefix bound to the values they will have dnl at the end of the configure script. AC_DEFUN([AC_LIB_WITH_FINAL_PREFIX], [ acl_save_prefix="$prefix" prefix="$acl_final_prefix" acl_save_exec_prefix="$exec_prefix" exec_prefix="$acl_final_exec_prefix" $1 exec_prefix="$acl_save_exec_prefix" prefix="$acl_save_prefix" ]) smalltalk-3.2.5/build-aux/version.m40000644000175000017500000000177012123404352014250 00000000000000dnl I'd like this to be edited in -*- Autoconf -*- mode... dnl AC_DEFUN([GST_REVISION], [ VERSION=$PACKAGE_VERSION VERSION_INFO=$1 # Split the version number [ ST_MAJOR_VERSION=`echo $VERSION| sed 's%\..*%%'` ST_MINOR_VERSION=`echo $VERSION| sed 's%[0-9]*\.\([0-9]*\).*%\1%'` case $VERSION in *.*.*) ST_EDIT_VERSION=`echo $VERSION| sed 's%\([0-9]*\)\.%%g'` ;; *.*[a-z]) ST_EDIT_VERSION=\'`echo $VERSION| sed 's%[0-9.]*%%'`\' ;; *) ST_EDIT_VERSION=0 ;; esac ] AC_DEFINE_UNQUOTED(ST_MAJOR_VERSION, $ST_MAJOR_VERSION, [Major version of GNU Smalltalk]) AC_DEFINE_UNQUOTED(ST_MINOR_VERSION, $ST_MINOR_VERSION, [Minor version of GNU Smalltalk]) AC_DEFINE_UNQUOTED(ST_EDIT_VERSION, $ST_EDIT_VERSION, [Patch level version of GNU Smalltalk]) AC_DEFINE_UNQUOTED(MAINTAINER, "$MAINTAINER", [E-Mail address of the person maintaining this package]) AC_SUBST(PACKAGE) AC_SUBST(VERSION) AC_SUBST(VERSION_INFO) AC_SUBST(MAINTAINER) ]) smalltalk-3.2.5/build-aux/ltoptions.m40000644000175000017500000003007312130455416014621 00000000000000# Helper functions for option handling. -*- Autoconf -*- # # Copyright (C) 2004, 2005, 2007, 2008, 2009 Free Software Foundation, # Inc. # Written by Gary V. Vaughan, 2004 # # This file is free software; the Free Software Foundation gives # unlimited permission to copy and/or distribute it, with or without # modifications, as long as this notice is preserved. # serial 7 ltoptions.m4 # This is to help aclocal find these macros, as it can't see m4_define. AC_DEFUN([LTOPTIONS_VERSION], [m4_if([1])]) # _LT_MANGLE_OPTION(MACRO-NAME, OPTION-NAME) # ------------------------------------------ m4_define([_LT_MANGLE_OPTION], [[_LT_OPTION_]m4_bpatsubst($1__$2, [[^a-zA-Z0-9_]], [_])]) # _LT_SET_OPTION(MACRO-NAME, OPTION-NAME) # --------------------------------------- # Set option OPTION-NAME for macro MACRO-NAME, and if there is a # matching handler defined, dispatch to it. Other OPTION-NAMEs are # saved as a flag. m4_define([_LT_SET_OPTION], [m4_define(_LT_MANGLE_OPTION([$1], [$2]))dnl m4_ifdef(_LT_MANGLE_DEFUN([$1], [$2]), _LT_MANGLE_DEFUN([$1], [$2]), [m4_warning([Unknown $1 option `$2'])])[]dnl ]) # _LT_IF_OPTION(MACRO-NAME, OPTION-NAME, IF-SET, [IF-NOT-SET]) # ------------------------------------------------------------ # Execute IF-SET if OPTION is set, IF-NOT-SET otherwise. m4_define([_LT_IF_OPTION], [m4_ifdef(_LT_MANGLE_OPTION([$1], [$2]), [$3], [$4])]) # _LT_UNLESS_OPTIONS(MACRO-NAME, OPTION-LIST, IF-NOT-SET) # ------------------------------------------------------- # Execute IF-NOT-SET unless all options in OPTION-LIST for MACRO-NAME # are set. m4_define([_LT_UNLESS_OPTIONS], [m4_foreach([_LT_Option], m4_split(m4_normalize([$2])), [m4_ifdef(_LT_MANGLE_OPTION([$1], _LT_Option), [m4_define([$0_found])])])[]dnl m4_ifdef([$0_found], [m4_undefine([$0_found])], [$3 ])[]dnl ]) # _LT_SET_OPTIONS(MACRO-NAME, OPTION-LIST) # ---------------------------------------- # OPTION-LIST is a space-separated list of Libtool options associated # with MACRO-NAME. If any OPTION has a matching handler declared with # LT_OPTION_DEFINE, dispatch to that macro; otherwise complain about # the unknown option and exit. m4_defun([_LT_SET_OPTIONS], [# Set options m4_foreach([_LT_Option], m4_split(m4_normalize([$2])), [_LT_SET_OPTION([$1], _LT_Option)]) m4_if([$1],[LT_INIT],[ dnl dnl Simply set some default values (i.e off) if boolean options were not dnl specified: _LT_UNLESS_OPTIONS([LT_INIT], [dlopen], [enable_dlopen=no ]) _LT_UNLESS_OPTIONS([LT_INIT], [win32-dll], [enable_win32_dll=no ]) dnl dnl If no reference was made to various pairs of opposing options, then dnl we run the default mode handler for the pair. For example, if neither dnl `shared' nor `disable-shared' was passed, we enable building of shared dnl archives by default: _LT_UNLESS_OPTIONS([LT_INIT], [shared disable-shared], [_LT_ENABLE_SHARED]) _LT_UNLESS_OPTIONS([LT_INIT], [static disable-static], [_LT_ENABLE_STATIC]) _LT_UNLESS_OPTIONS([LT_INIT], [pic-only no-pic], [_LT_WITH_PIC]) _LT_UNLESS_OPTIONS([LT_INIT], [fast-install disable-fast-install], [_LT_ENABLE_FAST_INSTALL]) ]) ])# _LT_SET_OPTIONS ## --------------------------------- ## ## Macros to handle LT_INIT options. ## ## --------------------------------- ## # _LT_MANGLE_DEFUN(MACRO-NAME, OPTION-NAME) # ----------------------------------------- m4_define([_LT_MANGLE_DEFUN], [[_LT_OPTION_DEFUN_]m4_bpatsubst(m4_toupper([$1__$2]), [[^A-Z0-9_]], [_])]) # LT_OPTION_DEFINE(MACRO-NAME, OPTION-NAME, CODE) # ----------------------------------------------- m4_define([LT_OPTION_DEFINE], [m4_define(_LT_MANGLE_DEFUN([$1], [$2]), [$3])[]dnl ])# LT_OPTION_DEFINE # dlopen # ------ LT_OPTION_DEFINE([LT_INIT], [dlopen], [enable_dlopen=yes ]) AU_DEFUN([AC_LIBTOOL_DLOPEN], [_LT_SET_OPTION([LT_INIT], [dlopen]) AC_DIAGNOSE([obsolete], [$0: Remove this warning and the call to _LT_SET_OPTION when you put the `dlopen' option into LT_INIT's first parameter.]) ]) dnl aclocal-1.4 backwards compatibility: dnl AC_DEFUN([AC_LIBTOOL_DLOPEN], []) # win32-dll # --------- # Declare package support for building win32 dll's. LT_OPTION_DEFINE([LT_INIT], [win32-dll], [enable_win32_dll=yes case $host in *-*-cygwin* | *-*-mingw* | *-*-pw32* | *-*-cegcc*) AC_CHECK_TOOL(AS, as, false) AC_CHECK_TOOL(DLLTOOL, dlltool, false) AC_CHECK_TOOL(OBJDUMP, objdump, false) ;; esac test -z "$AS" && AS=as _LT_DECL([], [AS], [1], [Assembler program])dnl test -z "$DLLTOOL" && DLLTOOL=dlltool _LT_DECL([], [DLLTOOL], [1], [DLL creation program])dnl test -z "$OBJDUMP" && OBJDUMP=objdump _LT_DECL([], [OBJDUMP], [1], [Object dumper program])dnl ])# win32-dll AU_DEFUN([AC_LIBTOOL_WIN32_DLL], [AC_REQUIRE([AC_CANONICAL_HOST])dnl _LT_SET_OPTION([LT_INIT], [win32-dll]) AC_DIAGNOSE([obsolete], [$0: Remove this warning and the call to _LT_SET_OPTION when you put the `win32-dll' option into LT_INIT's first parameter.]) ]) dnl aclocal-1.4 backwards compatibility: dnl AC_DEFUN([AC_LIBTOOL_WIN32_DLL], []) # _LT_ENABLE_SHARED([DEFAULT]) # ---------------------------- # implement the --enable-shared flag, and supports the `shared' and # `disable-shared' LT_INIT options. # DEFAULT is either `yes' or `no'. If omitted, it defaults to `yes'. m4_define([_LT_ENABLE_SHARED], [m4_define([_LT_ENABLE_SHARED_DEFAULT], [m4_if($1, no, no, yes)])dnl AC_ARG_ENABLE([shared], [AS_HELP_STRING([--enable-shared@<:@=PKGS@:>@], [build shared libraries @<:@default=]_LT_ENABLE_SHARED_DEFAULT[@:>@])], [p=${PACKAGE-default} case $enableval in yes) enable_shared=yes ;; no) enable_shared=no ;; *) enable_shared=no # Look at the argument we got. We use all the common list separators. lt_save_ifs="$IFS"; IFS="${IFS}$PATH_SEPARATOR," for pkg in $enableval; do IFS="$lt_save_ifs" if test "X$pkg" = "X$p"; then enable_shared=yes fi done IFS="$lt_save_ifs" ;; esac], [enable_shared=]_LT_ENABLE_SHARED_DEFAULT) _LT_DECL([build_libtool_libs], [enable_shared], [0], [Whether or not to build shared libraries]) ])# _LT_ENABLE_SHARED LT_OPTION_DEFINE([LT_INIT], [shared], [_LT_ENABLE_SHARED([yes])]) LT_OPTION_DEFINE([LT_INIT], [disable-shared], [_LT_ENABLE_SHARED([no])]) # Old names: AC_DEFUN([AC_ENABLE_SHARED], [_LT_SET_OPTION([LT_INIT], m4_if([$1], [no], [disable-])[shared]) ]) AC_DEFUN([AC_DISABLE_SHARED], [_LT_SET_OPTION([LT_INIT], [disable-shared]) ]) AU_DEFUN([AM_ENABLE_SHARED], [AC_ENABLE_SHARED($@)]) AU_DEFUN([AM_DISABLE_SHARED], [AC_DISABLE_SHARED($@)]) dnl aclocal-1.4 backwards compatibility: dnl AC_DEFUN([AM_ENABLE_SHARED], []) dnl AC_DEFUN([AM_DISABLE_SHARED], []) # _LT_ENABLE_STATIC([DEFAULT]) # ---------------------------- # implement the --enable-static flag, and support the `static' and # `disable-static' LT_INIT options. # DEFAULT is either `yes' or `no'. If omitted, it defaults to `yes'. m4_define([_LT_ENABLE_STATIC], [m4_define([_LT_ENABLE_STATIC_DEFAULT], [m4_if($1, no, no, yes)])dnl AC_ARG_ENABLE([static], [AS_HELP_STRING([--enable-static@<:@=PKGS@:>@], [build static libraries @<:@default=]_LT_ENABLE_STATIC_DEFAULT[@:>@])], [p=${PACKAGE-default} case $enableval in yes) enable_static=yes ;; no) enable_static=no ;; *) enable_static=no # Look at the argument we got. We use all the common list separators. lt_save_ifs="$IFS"; IFS="${IFS}$PATH_SEPARATOR," for pkg in $enableval; do IFS="$lt_save_ifs" if test "X$pkg" = "X$p"; then enable_static=yes fi done IFS="$lt_save_ifs" ;; esac], [enable_static=]_LT_ENABLE_STATIC_DEFAULT) _LT_DECL([build_old_libs], [enable_static], [0], [Whether or not to build static libraries]) ])# _LT_ENABLE_STATIC LT_OPTION_DEFINE([LT_INIT], [static], [_LT_ENABLE_STATIC([yes])]) LT_OPTION_DEFINE([LT_INIT], [disable-static], [_LT_ENABLE_STATIC([no])]) # Old names: AC_DEFUN([AC_ENABLE_STATIC], [_LT_SET_OPTION([LT_INIT], m4_if([$1], [no], [disable-])[static]) ]) AC_DEFUN([AC_DISABLE_STATIC], [_LT_SET_OPTION([LT_INIT], [disable-static]) ]) AU_DEFUN([AM_ENABLE_STATIC], [AC_ENABLE_STATIC($@)]) AU_DEFUN([AM_DISABLE_STATIC], [AC_DISABLE_STATIC($@)]) dnl aclocal-1.4 backwards compatibility: dnl AC_DEFUN([AM_ENABLE_STATIC], []) dnl AC_DEFUN([AM_DISABLE_STATIC], []) # _LT_ENABLE_FAST_INSTALL([DEFAULT]) # ---------------------------------- # implement the --enable-fast-install flag, and support the `fast-install' # and `disable-fast-install' LT_INIT options. # DEFAULT is either `yes' or `no'. If omitted, it defaults to `yes'. m4_define([_LT_ENABLE_FAST_INSTALL], [m4_define([_LT_ENABLE_FAST_INSTALL_DEFAULT], [m4_if($1, no, no, yes)])dnl AC_ARG_ENABLE([fast-install], [AS_HELP_STRING([--enable-fast-install@<:@=PKGS@:>@], [optimize for fast installation @<:@default=]_LT_ENABLE_FAST_INSTALL_DEFAULT[@:>@])], [p=${PACKAGE-default} case $enableval in yes) enable_fast_install=yes ;; no) enable_fast_install=no ;; *) enable_fast_install=no # Look at the argument we got. We use all the common list separators. lt_save_ifs="$IFS"; IFS="${IFS}$PATH_SEPARATOR," for pkg in $enableval; do IFS="$lt_save_ifs" if test "X$pkg" = "X$p"; then enable_fast_install=yes fi done IFS="$lt_save_ifs" ;; esac], [enable_fast_install=]_LT_ENABLE_FAST_INSTALL_DEFAULT) _LT_DECL([fast_install], [enable_fast_install], [0], [Whether or not to optimize for fast installation])dnl ])# _LT_ENABLE_FAST_INSTALL LT_OPTION_DEFINE([LT_INIT], [fast-install], [_LT_ENABLE_FAST_INSTALL([yes])]) LT_OPTION_DEFINE([LT_INIT], [disable-fast-install], [_LT_ENABLE_FAST_INSTALL([no])]) # Old names: AU_DEFUN([AC_ENABLE_FAST_INSTALL], [_LT_SET_OPTION([LT_INIT], m4_if([$1], [no], [disable-])[fast-install]) AC_DIAGNOSE([obsolete], [$0: Remove this warning and the call to _LT_SET_OPTION when you put the `fast-install' option into LT_INIT's first parameter.]) ]) AU_DEFUN([AC_DISABLE_FAST_INSTALL], [_LT_SET_OPTION([LT_INIT], [disable-fast-install]) AC_DIAGNOSE([obsolete], [$0: Remove this warning and the call to _LT_SET_OPTION when you put the `disable-fast-install' option into LT_INIT's first parameter.]) ]) dnl aclocal-1.4 backwards compatibility: dnl AC_DEFUN([AC_ENABLE_FAST_INSTALL], []) dnl AC_DEFUN([AM_DISABLE_FAST_INSTALL], []) # _LT_WITH_PIC([MODE]) # -------------------- # implement the --with-pic flag, and support the `pic-only' and `no-pic' # LT_INIT options. # MODE is either `yes' or `no'. If omitted, it defaults to `both'. m4_define([_LT_WITH_PIC], [AC_ARG_WITH([pic], [AS_HELP_STRING([--with-pic@<:@=PKGS@:>@], [try to use only PIC/non-PIC objects @<:@default=use both@:>@])], [lt_p=${PACKAGE-default} case $withval in yes|no) pic_mode=$withval ;; *) pic_mode=default # Look at the argument we got. We use all the common list separators. lt_save_ifs="$IFS"; IFS="${IFS}$PATH_SEPARATOR," for lt_pkg in $withval; do IFS="$lt_save_ifs" if test "X$lt_pkg" = "X$lt_p"; then pic_mode=yes fi done IFS="$lt_save_ifs" ;; esac], [pic_mode=default]) test -z "$pic_mode" && pic_mode=m4_default([$1], [default]) _LT_DECL([], [pic_mode], [0], [What type of objects to build])dnl ])# _LT_WITH_PIC LT_OPTION_DEFINE([LT_INIT], [pic-only], [_LT_WITH_PIC([yes])]) LT_OPTION_DEFINE([LT_INIT], [no-pic], [_LT_WITH_PIC([no])]) # Old name: AU_DEFUN([AC_LIBTOOL_PICMODE], [_LT_SET_OPTION([LT_INIT], [pic-only]) AC_DIAGNOSE([obsolete], [$0: Remove this warning and the call to _LT_SET_OPTION when you put the `pic-only' option into LT_INIT's first parameter.]) ]) dnl aclocal-1.4 backwards compatibility: dnl AC_DEFUN([AC_LIBTOOL_PICMODE], []) ## ----------------- ## ## LTDL_INIT Options ## ## ----------------- ## m4_define([_LTDL_MODE], []) LT_OPTION_DEFINE([LTDL_INIT], [nonrecursive], [m4_define([_LTDL_MODE], [nonrecursive])]) LT_OPTION_DEFINE([LTDL_INIT], [recursive], [m4_define([_LTDL_MODE], [recursive])]) LT_OPTION_DEFINE([LTDL_INIT], [subproject], [m4_define([_LTDL_MODE], [subproject])]) m4_define([_LTDL_TYPE], []) LT_OPTION_DEFINE([LTDL_INIT], [installable], [m4_define([_LTDL_TYPE], [installable])]) LT_OPTION_DEFINE([LTDL_INIT], [convenience], [m4_define([_LTDL_TYPE], [convenience])]) smalltalk-3.2.5/build-aux/ylwrap0000755000175000017500000001435712130455425013577 00000000000000#! /bin/sh # ylwrap - wrapper for lex/yacc invocations. scriptversion=2011-08-25.18; # UTC # Copyright (C) 1996, 1997, 1998, 1999, 2001, 2002, 2003, 2004, 2005, # 2007, 2009, 2010, 2011 Free Software Foundation, Inc. # # Written by Tom Tromey . # # This program is free software; you can redistribute it and/or modify # it under the terms of the GNU General Public License as published by # the Free Software Foundation; either version 2, or (at your option) # any later version. # # This program is distributed in the hope that it will be useful, # but WITHOUT ANY WARRANTY; without even the implied warranty of # MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the # GNU General Public License for more details. # # You should have received a copy of the GNU General Public License # along with this program. If not, see . # As a special exception to the GNU General Public License, if you # distribute this file as part of a program that contains a # configuration script generated by Autoconf, you may include it under # the same distribution terms that you use for the rest of that program. # This file is maintained in Automake, please report # bugs to or send patches to # . case "$1" in '') echo "$0: No files given. Try \`$0 --help' for more information." 1>&2 exit 1 ;; --basedir) basedir=$2 shift 2 ;; -h|--h*) cat <<\EOF Usage: ylwrap [--help|--version] INPUT [OUTPUT DESIRED]... -- PROGRAM [ARGS]... Wrapper for lex/yacc invocations, renaming files as desired. INPUT is the input file OUTPUT is one file PROG generates DESIRED is the file we actually want instead of OUTPUT PROGRAM is program to run ARGS are passed to PROG Any number of OUTPUT,DESIRED pairs may be used. Report bugs to . EOF exit $? ;; -v|--v*) echo "ylwrap $scriptversion" exit $? ;; esac # The input. input="$1" shift case "$input" in [\\/]* | ?:[\\/]*) # Absolute path; do nothing. ;; *) # Relative path. Make it absolute. input="`pwd`/$input" ;; esac pairlist= while test "$#" -ne 0; do if test "$1" = "--"; then shift break fi pairlist="$pairlist $1" shift done # The program to run. prog="$1" shift # Make any relative path in $prog absolute. case "$prog" in [\\/]* | ?:[\\/]*) ;; *[\\/]*) prog="`pwd`/$prog" ;; esac # FIXME: add hostname here for parallel makes that run commands on # other machines. But that might take us over the 14-char limit. dirname=ylwrap$$ do_exit="cd '`pwd`' && rm -rf $dirname > /dev/null 2>&1;"' (exit $ret); exit $ret' trap "ret=129; $do_exit" 1 trap "ret=130; $do_exit" 2 trap "ret=141; $do_exit" 13 trap "ret=143; $do_exit" 15 mkdir $dirname || exit 1 cd $dirname case $# in 0) "$prog" "$input" ;; *) "$prog" "$@" "$input" ;; esac ret=$? if test $ret -eq 0; then set X $pairlist shift first=yes # Since DOS filename conventions don't allow two dots, # the DOS version of Bison writes out y_tab.c instead of y.tab.c # and y_tab.h instead of y.tab.h. Test to see if this is the case. y_tab_nodot="no" if test -f y_tab.c || test -f y_tab.h; then y_tab_nodot="yes" fi # The directory holding the input. input_dir=`echo "$input" | sed -e 's,\([\\/]\)[^\\/]*$,\1,'` # Quote $INPUT_DIR so we can use it in a regexp. # FIXME: really we should care about more than `.' and `\'. input_rx=`echo "$input_dir" | sed 's,\\\\,\\\\\\\\,g;s,\\.,\\\\.,g'` while test "$#" -ne 0; do from="$1" # Handle y_tab.c and y_tab.h output by DOS if test $y_tab_nodot = "yes"; then if test $from = "y.tab.c"; then from="y_tab.c" else if test $from = "y.tab.h"; then from="y_tab.h" fi fi fi if test -f "$from"; then # If $2 is an absolute path name, then just use that, # otherwise prepend `../'. case "$2" in [\\/]* | ?:[\\/]*) target="$2";; *) target="../$2";; esac # We do not want to overwrite a header file if it hasn't # changed. This avoid useless recompilations. However the # parser itself (the first file) should always be updated, # because it is the destination of the .y.c rule in the # Makefile. Divert the output of all other files to a temporary # file so we can compare them to existing versions. if test $first = no; then realtarget="$target" target="tmp-`echo $target | sed s/.*[\\/]//g`" fi # Edit out `#line' or `#' directives. # # We don't want the resulting debug information to point at # an absolute srcdir; it is better for it to just mention the # .y file with no path. # # We want to use the real output file name, not yy.lex.c for # instance. # # We want the include guards to be adjusted too. FROM=`echo "$from" | sed \ -e 'y/abcdefghijklmnopqrstuvwxyz/ABCDEFGHIJKLMNOPQRSTUVWXYZ/'\ -e 's/[^ABCDEFGHIJKLMNOPQRSTUVWXYZ]/_/g'` TARGET=`echo "$2" | sed \ -e 'y/abcdefghijklmnopqrstuvwxyz/ABCDEFGHIJKLMNOPQRSTUVWXYZ/'\ -e 's/[^ABCDEFGHIJKLMNOPQRSTUVWXYZ]/_/g'` sed -e "/^#/!b" -e "s,$input_rx,," -e "s,$from,$2," \ -e "s,$FROM,$TARGET," "$from" >"$target" || ret=$? # Check whether header files must be updated. if test $first = no; then if test -f "$realtarget" && cmp -s "$realtarget" "$target"; then echo "$2" is unchanged rm -f "$target" else echo updating "$2" mv -f "$target" "$realtarget" fi fi else # A missing file is only an error for the first file. This # is a blatant hack to let us support using "yacc -d". If -d # is not specified, we don't want an error when the header # file is "missing". if test $first = yes; then ret=1 fi fi shift shift first=no done else ret=$? fi # Remove the directory. cd .. rm -rf $dirname exit $ret # Local Variables: # mode: shell-script # sh-indentation: 2 # eval: (add-hook 'write-file-hooks 'time-stamp) # time-stamp-start: "scriptversion=" # time-stamp-format: "%:y-%02m-%02d.%02H" # time-stamp-time-zone: "UTC" # time-stamp-end: "; # UTC" # End: smalltalk-3.2.5/build-aux/elisp-comp0000755000175000017500000000536712130455426014333 00000000000000#!/bin/sh # Copyright (C) 1995, 2000, 2003, 2004, 2005, 2009, 2010 Free Software # Foundation, Inc. scriptversion=2010-02-06.18; # UTC # Franc,ois Pinard , 1995. # # This program is free software; you can redistribute it and/or modify # it under the terms of the GNU General Public License as published by # the Free Software Foundation; either version 2, or (at your option) # any later version. # # This program is distributed in the hope that it will be useful, # but WITHOUT ANY WARRANTY; without even the implied warranty of # MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the # GNU General Public License for more details. # # You should have received a copy of the GNU General Public License # along with this program. If not, see . # As a special exception to the GNU General Public License, if you # distribute this file as part of a program that contains a # configuration script generated by Autoconf, you may include it under # the same distribution terms that you use for the rest of that program. # This file is maintained in Automake, please report # bugs to or send patches to # . case $1 in '') echo "$0: No files. Try \`$0 --help' for more information." 1>&2 exit 1; ;; -h | --h*) cat <<\EOF Usage: elisp-comp [--help] [--version] FILES... This script byte-compiles all `.el' files listed as FILES using GNU Emacs, and put the resulting `.elc' files into the current directory, so disregarding the original directories used in `.el' arguments. This script manages in such a way that all Emacs LISP files to be compiled are made visible between themselves, in the event they require or load-library one another. Report bugs to . EOF exit $? ;; -v | --v*) echo "elisp-comp $scriptversion" exit $? ;; esac if test -z "$EMACS" || test "$EMACS" = "t"; then # Value of "t" means we are running in a shell under Emacs. # Just assume Emacs is called "emacs". EMACS=emacs fi tempdir=elc.$$ # Cleanup the temporary directory on exit. trap 'ret=$?; rm -rf "$tempdir" && exit $ret' 0 do_exit='(exit $ret); exit $ret' trap "ret=129; $do_exit" 1 trap "ret=130; $do_exit" 2 trap "ret=141; $do_exit" 13 trap "ret=143; $do_exit" 15 mkdir $tempdir cp "$@" $tempdir ( cd $tempdir echo "(setq load-path (cons nil load-path))" > script $EMACS -batch -q -l script -f batch-byte-compile *.el || exit $? mv *.elc .. ) || exit $? (exit 0); exit 0 # Local Variables: # mode: shell-script # sh-indentation: 2 # eval: (add-hook 'write-file-hooks 'time-stamp) # time-stamp-start: "scriptversion=" # time-stamp-format: "%:y-%02m-%02d.%02H" # time-stamp-time-zone: "UTC" # time-stamp-end: "; # UTC" # End: smalltalk-3.2.5/build-aux/config.rpath0000755000175000017500000003522312123404352014631 00000000000000#! /bin/sh # Output a system dependent set of variables, describing how to set the # run time search path of shared libraries in an executable. # # Copyright 1996-2003 Free Software Foundation, Inc. # Taken from GNU libtool, 2001 # Originally by Gordon Matzigkeit , 1996 # # This program is free software; you can redistribute it and/or modify # it under the terms of the GNU General Public License as published by # the Free Software Foundation; either version 2 of the License, or # (at your option) any later version. # # This program is distributed in the hope that it will be useful, but # WITHOUT ANY WARRANTY; without even the implied warranty of # MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU # General Public License for more details. # # You should have received a copy of the GNU General Public License # along with this program; if not, write to the Free Software # Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. # # As a special exception to the GNU General Public License, if you # distribute this file as part of a program that contains a # configuration script generated by Autoconf, you may include it under # the same distribution terms that you use for the rest of that program. # # The first argument passed to this file is the canonical host specification, # CPU_TYPE-MANUFACTURER-OPERATING_SYSTEM # or # CPU_TYPE-MANUFACTURER-KERNEL-OPERATING_SYSTEM # The environment variables CC, GCC, LDFLAGS, LD, with_gnu_ld # should be set by the caller. # # The set of defined variables is at the end of this script. # Known limitations: # - On IRIX 6.5 with CC="cc", the run time search patch must not be longer # than 256 bytes, otherwise the compiler driver will dump core. The only # known workaround is to choose shorter directory names for the build # directory and/or the installation directory. # All known linkers require a `.a' archive for static linking (except M$VC, # which needs '.lib'). libext=a shrext=.so host="$1" host_cpu=`echo "$host" | sed 's/^\([^-]*\)-\([^-]*\)-\(.*\)$/\1/'` host_vendor=`echo "$host" | sed 's/^\([^-]*\)-\([^-]*\)-\(.*\)$/\2/'` host_os=`echo "$host" | sed 's/^\([^-]*\)-\([^-]*\)-\(.*\)$/\3/'` # Code taken from libtool.m4's AC_LIBTOOL_PROG_COMPILER_PIC. wl= if test "$GCC" = yes; then wl='-Wl,' else case "$host_os" in aix*) wl='-Wl,' ;; mingw* | pw32* | os2*) ;; hpux9* | hpux10* | hpux11*) wl='-Wl,' ;; irix5* | irix6* | nonstopux*) wl='-Wl,' ;; newsos6) ;; linux*) case $CC in icc|ecc) wl='-Wl,' ;; ccc) wl='-Wl,' ;; esac ;; osf3* | osf4* | osf5*) wl='-Wl,' ;; sco3.2v5*) ;; solaris*) wl='-Wl,' ;; sunos4*) wl='-Qoption ld ' ;; sysv4 | sysv4.2uw2* | sysv4.3* | sysv5*) wl='-Wl,' ;; sysv4*MP*) ;; uts4*) ;; esac fi # Code taken from libtool.m4's AC_LIBTOOL_PROG_LD_SHLIBS. hardcode_libdir_flag_spec= hardcode_libdir_separator= hardcode_direct=no hardcode_minus_L=no case "$host_os" in cygwin* | mingw* | pw32*) # FIXME: the MSVC++ port hasn't been tested in a loooong time # When not using gcc, we currently assume that we are using # Microsoft Visual C++. if test "$GCC" != yes; then with_gnu_ld=no fi ;; openbsd*) with_gnu_ld=no ;; esac ld_shlibs=yes if test "$with_gnu_ld" = yes; then case "$host_os" in aix3* | aix4* | aix5*) # On AIX/PPC, the GNU linker is very broken if test "$host_cpu" != ia64; then ld_shlibs=no fi ;; amigaos*) hardcode_libdir_flag_spec='-L$libdir' hardcode_minus_L=yes # Samuel A. Falvo II reports # that the semantics of dynamic libraries on AmigaOS, at least up # to version 4, is to share data among multiple programs linked # with the same dynamic library. Since this doesn't match the # behavior of shared libraries on other platforms, we can use # them. ld_shlibs=no ;; beos*) if $LD --help 2>&1 | egrep ': supported targets:.* elf' > /dev/null; then : else ld_shlibs=no fi ;; cygwin* | mingw* | pw32*) # hardcode_libdir_flag_spec is actually meaningless, as there is # no search path for DLLs. hardcode_libdir_flag_spec='-L$libdir' if $LD --help 2>&1 | grep 'auto-import' > /dev/null; then : else ld_shlibs=no fi ;; netbsd*) ;; solaris* | sysv5*) if $LD -v 2>&1 | egrep 'BFD 2\.8' > /dev/null; then ld_shlibs=no elif $LD --help 2>&1 | egrep ': supported targets:.* elf' > /dev/null; then : else ld_shlibs=no fi ;; sunos4*) hardcode_direct=yes ;; *) if $LD --help 2>&1 | egrep ': supported targets:.* elf' > /dev/null; then : else ld_shlibs=no fi ;; esac if test "$ld_shlibs" = yes; then # Unlike libtool, we use -rpath here, not --rpath, since the documented # option of GNU ld is called -rpath, not --rpath. hardcode_libdir_flag_spec='${wl}-rpath ${wl}$libdir' fi else case "$host_os" in aix3*) # Note: this linker hardcodes the directories in LIBPATH if there # are no directories specified by -L. hardcode_minus_L=yes if test "$GCC" = yes; then # Neither direct hardcoding nor static linking is supported with a # broken collect2. hardcode_direct=unsupported fi ;; aix4* | aix5*) if test "$host_cpu" = ia64; then # On IA64, the linker does run time linking by default, so we don't # have to do anything special. aix_use_runtimelinking=no else aix_use_runtimelinking=no # Test if we are trying to use run time linking or normal # AIX style linking. If -brtl is somewhere in LDFLAGS, we # need to do runtime linking. case $host_os in aix4.[23]|aix4.[23].*|aix5*) for ld_flag in $LDFLAGS; do if (test $ld_flag = "-brtl" || test $ld_flag = "-Wl,-brtl"); then aix_use_runtimelinking=yes break fi done esac fi hardcode_direct=yes hardcode_libdir_separator=':' if test "$GCC" = yes; then case $host_os in aix4.[012]|aix4.[012].*) collect2name=`${CC} -print-prog-name=collect2` if test -f "$collect2name" && \ strings "$collect2name" | grep resolve_lib_name >/dev/null then # We have reworked collect2 hardcode_direct=yes else # We have old collect2 hardcode_direct=unsupported hardcode_minus_L=yes hardcode_libdir_flag_spec='-L$libdir' hardcode_libdir_separator= fi esac fi # Begin _LT_AC_SYS_LIBPATH_AIX. echo 'int main () { return 0; }' > conftest.c ${CC} ${LDFLAGS} conftest.c -o conftest aix_libpath=`dump -H conftest 2>/dev/null | sed -n -e '/Import File Strings/,/^$/ { /^0/ { s/^0 *\(.*\)$/\1/; p; } }'` if test -z "$aix_libpath"; then aix_libpath=`dump -HX64 conftest 2>/dev/null | sed -n -e '/Import File Strings/,/^$/ { /^0/ { s/^0 *\(.*\)$/\1/; p; } }'` fi if test -z "$aix_libpath"; then aix_libpath="/usr/lib:/lib" fi rm -f conftest.c conftest # End _LT_AC_SYS_LIBPATH_AIX. if test "$aix_use_runtimelinking" = yes; then hardcode_libdir_flag_spec='${wl}-blibpath:$libdir:'"$aix_libpath" else if test "$host_cpu" = ia64; then hardcode_libdir_flag_spec='${wl}-R $libdir:/usr/lib:/lib' else hardcode_libdir_flag_spec='${wl}-blibpath:$libdir:'"$aix_libpath" fi fi ;; amigaos*) hardcode_libdir_flag_spec='-L$libdir' hardcode_minus_L=yes # see comment about different semantics on the GNU ld section ld_shlibs=no ;; bsdi4*) ;; cygwin* | mingw* | pw32*) # When not using gcc, we currently assume that we are using # Microsoft Visual C++. # hardcode_libdir_flag_spec is actually meaningless, as there is # no search path for DLLs. hardcode_libdir_flag_spec=' ' libext=lib ;; darwin* | rhapsody*) if $CC -v 2>&1 | grep 'Apple' >/dev/null ; then hardcode_direct=no fi ;; dgux*) hardcode_libdir_flag_spec='-L$libdir' ;; freebsd1*) ld_shlibs=no ;; freebsd2.2*) hardcode_libdir_flag_spec='-R$libdir' hardcode_direct=yes ;; freebsd2*) hardcode_direct=yes hardcode_minus_L=yes ;; freebsd*) hardcode_libdir_flag_spec='-R$libdir' hardcode_direct=yes ;; hpux9*) hardcode_libdir_flag_spec='${wl}+b ${wl}$libdir' hardcode_libdir_separator=: hardcode_direct=yes # hardcode_minus_L: Not really in the search PATH, # but as the default location of the library. hardcode_minus_L=yes ;; hpux10* | hpux11*) if test "$with_gnu_ld" = no; then case "$host_cpu" in hppa*64*) hardcode_libdir_flag_spec='${wl}+b ${wl}$libdir' hardcode_libdir_separator=: hardcode_direct=no ;; ia64*) hardcode_libdir_flag_spec='-L$libdir' hardcode_direct=no # hardcode_minus_L: Not really in the search PATH, # but as the default location of the library. hardcode_minus_L=yes ;; *) hardcode_libdir_flag_spec='${wl}+b ${wl}$libdir' hardcode_libdir_separator=: hardcode_direct=yes # hardcode_minus_L: Not really in the search PATH, # but as the default location of the library. hardcode_minus_L=yes ;; esac fi ;; irix5* | irix6* | nonstopux*) hardcode_libdir_flag_spec='${wl}-rpath ${wl}$libdir' hardcode_libdir_separator=: ;; netbsd*) hardcode_libdir_flag_spec='-R$libdir' hardcode_direct=yes ;; newsos6) hardcode_direct=yes hardcode_libdir_flag_spec='${wl}-rpath ${wl}$libdir' hardcode_libdir_separator=: ;; openbsd*) hardcode_direct=yes if test -z "`echo __ELF__ | $CC -E - | grep __ELF__`" || test "$host_os-$host_cpu" = "openbsd2.8-powerpc"; then hardcode_libdir_flag_spec='${wl}-rpath,$libdir' else case "$host_os" in openbsd[01].* | openbsd2.[0-7] | openbsd2.[0-7].*) hardcode_libdir_flag_spec='-R$libdir' ;; *) hardcode_libdir_flag_spec='${wl}-rpath,$libdir' ;; esac fi ;; os2*) hardcode_libdir_flag_spec='-L$libdir' hardcode_minus_L=yes ;; osf3*) hardcode_libdir_flag_spec='${wl}-rpath ${wl}$libdir' hardcode_libdir_separator=: ;; osf4* | osf5*) if test "$GCC" = yes; then hardcode_libdir_flag_spec='${wl}-rpath ${wl}$libdir' else # Both cc and cxx compiler support -rpath directly hardcode_libdir_flag_spec='-rpath $libdir' fi hardcode_libdir_separator=: ;; sco3.2v5*) ;; solaris*) hardcode_libdir_flag_spec='-R$libdir' ;; sunos4*) hardcode_libdir_flag_spec='-L$libdir' hardcode_direct=yes hardcode_minus_L=yes ;; sysv4) case $host_vendor in sni) hardcode_direct=yes # is this really true??? ;; siemens) hardcode_direct=no ;; motorola) hardcode_direct=no #Motorola manual says yes, but my tests say they lie ;; esac ;; sysv4.3*) ;; sysv4*MP*) if test -d /usr/nec; then ld_shlibs=yes fi ;; sysv4.2uw2*) hardcode_direct=yes hardcode_minus_L=no ;; sysv5OpenUNIX8* | sysv5UnixWare7* | sysv5uw[78]* | unixware7*) ;; sysv5*) hardcode_libdir_flag_spec= ;; uts4*) hardcode_libdir_flag_spec='-L$libdir' ;; *) ld_shlibs=no ;; esac fi # Check dynamic linker characteristics # Code taken from libtool.m4's AC_LIBTOOL_SYS_DYNAMIC_LINKER. libname_spec='lib$name' case "$host_os" in aix3*) ;; aix4* | aix5*) ;; amigaos*) ;; beos*) ;; bsdi4*) ;; cygwin* | mingw* | pw32*) shrext=.dll ;; darwin* | rhapsody*) shrext=.dylib ;; dgux*) ;; freebsd1*) ;; freebsd*) ;; gnu*) ;; hpux9* | hpux10* | hpux11*) case "$host_cpu" in ia64*) shrext=.so ;; hppa*64*) shrext=.sl ;; *) shrext=.sl ;; esac ;; irix5* | irix6* | nonstopux*) case "$host_os" in irix5* | nonstopux*) libsuff= shlibsuff= ;; *) case $LD in *-32|*"-32 "|*-melf32bsmip|*"-melf32bsmip ") libsuff= shlibsuff= ;; *-n32|*"-n32 "|*-melf32bmipn32|*"-melf32bmipn32 ") libsuff=32 shlibsuff=N32 ;; *-64|*"-64 "|*-melf64bmip|*"-melf64bmip ") libsuff=64 shlibsuff=64 ;; *) libsuff= shlibsuff= ;; esac ;; esac ;; linux*oldld* | linux*aout* | linux*coff*) ;; linux*) ;; netbsd*) ;; newsos6) ;; nto-qnx) ;; openbsd*) ;; os2*) libname_spec='$name' shrext=.dll ;; osf3* | osf4* | osf5*) ;; sco3.2v5*) ;; solaris*) ;; sunos4*) ;; sysv4 | sysv4.2uw2* | sysv4.3* | sysv5*) ;; sysv4*MP*) ;; uts4*) ;; esac sed_quote_subst='s/\(["`$\\]\)/\\\1/g' escaped_wl=`echo "X$wl" | sed -e 's/^X//' -e "$sed_quote_subst"` shlibext=`echo "$shrext" | sed -e 's,^\.,,'` escaped_hardcode_libdir_flag_spec=`echo "X$hardcode_libdir_flag_spec" | sed -e 's/^X//' -e "$sed_quote_subst"` sed -e 's/^\([a-zA-Z0-9_]*\)=/acl_cv_\1=/' <. % % As a special exception, when this file is read by TeX when processing % a Texinfo source document, you may use the result without % restriction. (This has been our intent since Texinfo was invented.) % % Please try the latest version of texinfo.tex before submitting bug % reports; you can get the latest version from: % http://www.gnu.org/software/texinfo/ (the Texinfo home page), or % ftp://tug.org/tex/texinfo.tex % (and all CTAN mirrors, see http://www.ctan.org). % The texinfo.tex in any given distribution could well be out % of date, so if that's what you're using, please check. % % Send bug reports to bug-texinfo@gnu.org. Please include including a % complete document in each bug report with which we can reproduce the % problem. Patches are, of course, greatly appreciated. % % To process a Texinfo manual with TeX, it's most reliable to use the % texi2dvi shell script that comes with the distribution. For a simple % manual foo.texi, however, you can get away with this: % tex foo.texi % texindex foo.?? % tex foo.texi % tex foo.texi % dvips foo.dvi -o # or whatever; this makes foo.ps. % The extra TeX runs get the cross-reference information correct. % Sometimes one run after texindex suffices, and sometimes you need more % than two; texi2dvi does it as many times as necessary. % % It is possible to adapt texinfo.tex for other languages, to some % extent. You can get the existing language-specific files from the % full Texinfo distribution. % % The GNU Texinfo home page is http://www.gnu.org/software/texinfo. \message{Loading texinfo [version \texinfoversion]:} % If in a .fmt file, print the version number % and turn on active characters that we couldn't do earlier because % they might have appeared in the input file name. \everyjob{\message{[Texinfo version \texinfoversion]}% \catcode`+=\active \catcode`\_=\active} \chardef\other=12 % We never want plain's \outer definition of \+ in Texinfo. % For @tex, we can use \tabalign. \let\+ = \relax % Save some plain tex macros whose names we will redefine. \let\ptexb=\b \let\ptexbullet=\bullet \let\ptexc=\c \let\ptexcomma=\, \let\ptexdot=\. \let\ptexdots=\dots \let\ptexend=\end \let\ptexequiv=\equiv \let\ptexexclam=\! \let\ptexfootnote=\footnote \let\ptexgtr=> \let\ptexhat=^ \let\ptexi=\i \let\ptexindent=\indent \let\ptexinsert=\insert \let\ptexlbrace=\{ \let\ptexless=< \let\ptexnewwrite\newwrite \let\ptexnoindent=\noindent \let\ptexplus=+ \let\ptexraggedright=\raggedright \let\ptexrbrace=\} \let\ptexslash=\/ \let\ptexstar=\* \let\ptext=\t \let\ptextop=\top {\catcode`\'=\active \global\let\ptexquoteright'}% active in plain's math mode % If this character appears in an error message or help string, it % starts a new line in the output. \newlinechar = `^^J % Use TeX 3.0's \inputlineno to get the line number, for better error % messages, but if we're using an old version of TeX, don't do anything. % \ifx\inputlineno\thisisundefined \let\linenumber = \empty % Pre-3.0. \else \def\linenumber{l.\the\inputlineno:\space} \fi % Set up fixed words for English if not already set. \ifx\putwordAppendix\undefined \gdef\putwordAppendix{Appendix}\fi \ifx\putwordChapter\undefined \gdef\putwordChapter{Chapter}\fi \ifx\putworderror\undefined \gdef\putworderror{error}\fi \ifx\putwordfile\undefined \gdef\putwordfile{file}\fi \ifx\putwordin\undefined \gdef\putwordin{in}\fi \ifx\putwordIndexIsEmpty\undefined \gdef\putwordIndexIsEmpty{(Index is empty)}\fi \ifx\putwordIndexNonexistent\undefined \gdef\putwordIndexNonexistent{(Index is nonexistent)}\fi \ifx\putwordInfo\undefined \gdef\putwordInfo{Info}\fi \ifx\putwordInstanceVariableof\undefined \gdef\putwordInstanceVariableof{Instance Variable of}\fi \ifx\putwordMethodon\undefined \gdef\putwordMethodon{Method on}\fi \ifx\putwordNoTitle\undefined \gdef\putwordNoTitle{No Title}\fi \ifx\putwordof\undefined \gdef\putwordof{of}\fi \ifx\putwordon\undefined \gdef\putwordon{on}\fi \ifx\putwordpage\undefined \gdef\putwordpage{page}\fi \ifx\putwordsection\undefined \gdef\putwordsection{section}\fi \ifx\putwordSection\undefined \gdef\putwordSection{Section}\fi \ifx\putwordsee\undefined \gdef\putwordsee{see}\fi \ifx\putwordSee\undefined \gdef\putwordSee{See}\fi \ifx\putwordShortTOC\undefined \gdef\putwordShortTOC{Short Contents}\fi \ifx\putwordTOC\undefined \gdef\putwordTOC{Table of Contents}\fi % \ifx\putwordMJan\undefined \gdef\putwordMJan{January}\fi \ifx\putwordMFeb\undefined \gdef\putwordMFeb{February}\fi \ifx\putwordMMar\undefined \gdef\putwordMMar{March}\fi \ifx\putwordMApr\undefined \gdef\putwordMApr{April}\fi \ifx\putwordMMay\undefined \gdef\putwordMMay{May}\fi \ifx\putwordMJun\undefined \gdef\putwordMJun{June}\fi \ifx\putwordMJul\undefined \gdef\putwordMJul{July}\fi \ifx\putwordMAug\undefined \gdef\putwordMAug{August}\fi \ifx\putwordMSep\undefined \gdef\putwordMSep{September}\fi \ifx\putwordMOct\undefined \gdef\putwordMOct{October}\fi \ifx\putwordMNov\undefined \gdef\putwordMNov{November}\fi \ifx\putwordMDec\undefined \gdef\putwordMDec{December}\fi % \ifx\putwordDefmac\undefined \gdef\putwordDefmac{Macro}\fi \ifx\putwordDefspec\undefined \gdef\putwordDefspec{Special Form}\fi \ifx\putwordDefvar\undefined \gdef\putwordDefvar{Variable}\fi \ifx\putwordDefopt\undefined \gdef\putwordDefopt{User Option}\fi \ifx\putwordDeffunc\undefined \gdef\putwordDeffunc{Function}\fi % Since the category of space is not known, we have to be careful. \chardef\spacecat = 10 \def\spaceisspace{\catcode`\ =\spacecat} % sometimes characters are active, so we need control sequences. \chardef\ampChar = `\& \chardef\colonChar = `\: \chardef\commaChar = `\, \chardef\dashChar = `\- \chardef\dotChar = `\. \chardef\exclamChar= `\! \chardef\hashChar = `\# \chardef\lquoteChar= `\` \chardef\questChar = `\? \chardef\rquoteChar= `\' \chardef\semiChar = `\; \chardef\slashChar = `\/ \chardef\underChar = `\_ % Ignore a token. % \def\gobble#1{} % The following is used inside several \edef's. \def\makecsname#1{\expandafter\noexpand\csname#1\endcsname} % Hyphenation fixes. \hyphenation{ Flor-i-da Ghost-script Ghost-view Mac-OS Post-Script ap-pen-dix bit-map bit-maps data-base data-bases eshell fall-ing half-way long-est man-u-script man-u-scripts mini-buf-fer mini-buf-fers over-view par-a-digm par-a-digms rath-er rec-tan-gu-lar ro-bot-ics se-vere-ly set-up spa-ces spell-ing spell-ings stand-alone strong-est time-stamp time-stamps which-ever white-space wide-spread wrap-around } % Margin to add to right of even pages, to left of odd pages. \newdimen\bindingoffset \newdimen\normaloffset \newdimen\pagewidth \newdimen\pageheight % For a final copy, take out the rectangles % that mark overfull boxes (in case you have decided % that the text looks ok even though it passes the margin). % \def\finalout{\overfullrule=0pt } % Sometimes it is convenient to have everything in the transcript file % and nothing on the terminal. We don't just call \tracingall here, % since that produces some useless output on the terminal. We also make % some effort to order the tracing commands to reduce output in the log % file; cf. trace.sty in LaTeX. % \def\gloggingall{\begingroup \globaldefs = 1 \loggingall \endgroup}% \def\loggingall{% \tracingstats2 \tracingpages1 \tracinglostchars2 % 2 gives us more in etex \tracingparagraphs1 \tracingoutput1 \tracingmacros2 \tracingrestores1 \showboxbreadth\maxdimen \showboxdepth\maxdimen \ifx\eTeXversion\thisisundefined\else % etex gives us more logging \tracingscantokens1 \tracingifs1 \tracinggroups1 \tracingnesting2 \tracingassigns1 \fi \tracingcommands3 % 3 gives us more in etex \errorcontextlines16 }% % @errormsg{MSG}. Do the index-like expansions on MSG, but if things % aren't perfect, it's not the end of the world, being an error message, % after all. % \def\errormsg{\begingroup \indexnofonts \doerrormsg} \def\doerrormsg#1{\errmessage{#1}} % add check for \lastpenalty to plain's definitions. If the last thing % we did was a \nobreak, we don't want to insert more space. % \def\smallbreak{\ifnum\lastpenalty<10000\par\ifdim\lastskip<\smallskipamount \removelastskip\penalty-50\smallskip\fi\fi} \def\medbreak{\ifnum\lastpenalty<10000\par\ifdim\lastskip<\medskipamount \removelastskip\penalty-100\medskip\fi\fi} \def\bigbreak{\ifnum\lastpenalty<10000\par\ifdim\lastskip<\bigskipamount \removelastskip\penalty-200\bigskip\fi\fi} % Do @cropmarks to get crop marks. % \newif\ifcropmarks \let\cropmarks = \cropmarkstrue % % Dimensions to add cropmarks at corners. % Added by P. A. MacKay, 12 Nov. 1986 % \newdimen\outerhsize \newdimen\outervsize % set by the paper size routines \newdimen\cornerlong \cornerlong=1pc \newdimen\cornerthick \cornerthick=.3pt \newdimen\topandbottommargin \topandbottommargin=.75in % Output a mark which sets \thischapter, \thissection and \thiscolor. % We dump everything together because we only have one kind of mark. % This works because we only use \botmark / \topmark, not \firstmark. % % A mark contains a subexpression of the \ifcase ... \fi construct. % \get*marks macros below extract the needed part using \ifcase. % % Another complication is to let the user choose whether \thischapter % (\thissection) refers to the chapter (section) in effect at the top % of a page, or that at the bottom of a page. The solution is % described on page 260 of The TeXbook. It involves outputting two % marks for the sectioning macros, one before the section break, and % one after. I won't pretend I can describe this better than DEK... \def\domark{% \toks0=\expandafter{\lastchapterdefs}% \toks2=\expandafter{\lastsectiondefs}% \toks4=\expandafter{\prevchapterdefs}% \toks6=\expandafter{\prevsectiondefs}% \toks8=\expandafter{\lastcolordefs}% \mark{% \the\toks0 \the\toks2 \noexpand\or \the\toks4 \the\toks6 \noexpand\else \the\toks8 }% } % \topmark doesn't work for the very first chapter (after the title % page or the contents), so we use \firstmark there -- this gets us % the mark with the chapter defs, unless the user sneaks in, e.g., % @setcolor (or @url, or @link, etc.) between @contents and the very % first @chapter. \def\gettopheadingmarks{% \ifcase0\topmark\fi \ifx\thischapter\empty \ifcase0\firstmark\fi \fi } \def\getbottomheadingmarks{\ifcase1\botmark\fi} \def\getcolormarks{\ifcase2\topmark\fi} % Avoid "undefined control sequence" errors. \def\lastchapterdefs{} \def\lastsectiondefs{} \def\prevchapterdefs{} \def\prevsectiondefs{} \def\lastcolordefs{} % Main output routine. \chardef\PAGE = 255 \output = {\onepageout{\pagecontents\PAGE}} \newbox\headlinebox \newbox\footlinebox % \onepageout takes a vbox as an argument. Note that \pagecontents % does insertions, but you have to call it yourself. \def\onepageout#1{% \ifcropmarks \hoffset=0pt \else \hoffset=\normaloffset \fi % \ifodd\pageno \advance\hoffset by \bindingoffset \else \advance\hoffset by -\bindingoffset\fi % % Do this outside of the \shipout so @code etc. will be expanded in % the headline as they should be, not taken literally (outputting ''code). \ifodd\pageno \getoddheadingmarks \else \getevenheadingmarks \fi \setbox\headlinebox = \vbox{\let\hsize=\pagewidth \makeheadline}% \ifodd\pageno \getoddfootingmarks \else \getevenfootingmarks \fi \setbox\footlinebox = \vbox{\let\hsize=\pagewidth \makefootline}% % {% % Have to do this stuff outside the \shipout because we want it to % take effect in \write's, yet the group defined by the \vbox ends % before the \shipout runs. % \indexdummies % don't expand commands in the output. \normalturnoffactive % \ in index entries must not stay \, e.g., if % the page break happens to be in the middle of an example. % We don't want .vr (or whatever) entries like this: % \entry{{\tt \indexbackslash }acronym}{32}{\code {\acronym}} % "\acronym" won't work when it's read back in; % it needs to be % {\code {{\tt \backslashcurfont }acronym} \shipout\vbox{% % Do this early so pdf references go to the beginning of the page. \ifpdfmakepagedest \pdfdest name{\the\pageno} xyz\fi % \ifcropmarks \vbox to \outervsize\bgroup \hsize = \outerhsize \vskip-\topandbottommargin \vtop to0pt{% \line{\ewtop\hfil\ewtop}% \nointerlineskip \line{% \vbox{\moveleft\cornerthick\nstop}% \hfill \vbox{\moveright\cornerthick\nstop}% }% \vss}% \vskip\topandbottommargin \line\bgroup \hfil % center the page within the outer (page) hsize. \ifodd\pageno\hskip\bindingoffset\fi \vbox\bgroup \fi % \unvbox\headlinebox \pagebody{#1}% \ifdim\ht\footlinebox > 0pt % Only leave this space if the footline is nonempty. % (We lessened \vsize for it in \oddfootingyyy.) % The \baselineskip=24pt in plain's \makefootline has no effect. \vskip 24pt \unvbox\footlinebox \fi % \ifcropmarks \egroup % end of \vbox\bgroup \hfil\egroup % end of (centering) \line\bgroup \vskip\topandbottommargin plus1fill minus1fill \boxmaxdepth = \cornerthick \vbox to0pt{\vss \line{% \vbox{\moveleft\cornerthick\nsbot}% \hfill \vbox{\moveright\cornerthick\nsbot}% }% \nointerlineskip \line{\ewbot\hfil\ewbot}% }% \egroup % \vbox from first cropmarks clause \fi }% end of \shipout\vbox }% end of group with \indexdummies \advancepageno \ifnum\outputpenalty>-20000 \else\dosupereject\fi } \newinsert\margin \dimen\margin=\maxdimen \def\pagebody#1{\vbox to\pageheight{\boxmaxdepth=\maxdepth #1}} {\catcode`\@ =11 \gdef\pagecontents#1{\ifvoid\topins\else\unvbox\topins\fi % marginal hacks, juha@viisa.uucp (Juha Takala) \ifvoid\margin\else % marginal info is present \rlap{\kern\hsize\vbox to\z@{\kern1pt\box\margin \vss}}\fi \dimen@=\dp#1\relax \unvbox#1\relax \ifvoid\footins\else\vskip\skip\footins\footnoterule \unvbox\footins\fi \ifr@ggedbottom \kern-\dimen@ \vfil \fi} } % Here are the rules for the cropmarks. Note that they are % offset so that the space between them is truly \outerhsize or \outervsize % (P. A. MacKay, 12 November, 1986) % \def\ewtop{\vrule height\cornerthick depth0pt width\cornerlong} \def\nstop{\vbox {\hrule height\cornerthick depth\cornerlong width\cornerthick}} \def\ewbot{\vrule height0pt depth\cornerthick width\cornerlong} \def\nsbot{\vbox {\hrule height\cornerlong depth\cornerthick width\cornerthick}} % Parse an argument, then pass it to #1. The argument is the rest of % the input line (except we remove a trailing comment). #1 should be a % macro which expects an ordinary undelimited TeX argument. % \def\parsearg{\parseargusing{}} \def\parseargusing#1#2{% \def\argtorun{#2}% \begingroup \obeylines \spaceisspace #1% \parseargline\empty% Insert the \empty token, see \finishparsearg below. } {\obeylines % \gdef\parseargline#1^^M{% \endgroup % End of the group started in \parsearg. \argremovecomment #1\comment\ArgTerm% }% } % First remove any @comment, then any @c comment. \def\argremovecomment#1\comment#2\ArgTerm{\argremovec #1\c\ArgTerm} \def\argremovec#1\c#2\ArgTerm{\argcheckspaces#1\^^M\ArgTerm} % Each occurrence of `\^^M' or `\^^M' is replaced by a single space. % % \argremovec might leave us with trailing space, e.g., % @end itemize @c foo % This space token undergoes the same procedure and is eventually removed % by \finishparsearg. % \def\argcheckspaces#1\^^M{\argcheckspacesX#1\^^M \^^M} \def\argcheckspacesX#1 \^^M{\argcheckspacesY#1\^^M} \def\argcheckspacesY#1\^^M#2\^^M#3\ArgTerm{% \def\temp{#3}% \ifx\temp\empty % Do not use \next, perhaps the caller of \parsearg uses it; reuse \temp: \let\temp\finishparsearg \else \let\temp\argcheckspaces \fi % Put the space token in: \temp#1 #3\ArgTerm } % If a _delimited_ argument is enclosed in braces, they get stripped; so % to get _exactly_ the rest of the line, we had to prevent such situation. % We prepended an \empty token at the very beginning and we expand it now, % just before passing the control to \argtorun. % (Similarly, we have to think about #3 of \argcheckspacesY above: it is % either the null string, or it ends with \^^M---thus there is no danger % that a pair of braces would be stripped. % % But first, we have to remove the trailing space token. % \def\finishparsearg#1 \ArgTerm{\expandafter\argtorun\expandafter{#1}} % \parseargdef\foo{...} % is roughly equivalent to % \def\foo{\parsearg\Xfoo} % \def\Xfoo#1{...} % % Actually, I use \csname\string\foo\endcsname, ie. \\foo, as it is my % favourite TeX trick. --kasal, 16nov03 \def\parseargdef#1{% \expandafter \doparseargdef \csname\string#1\endcsname #1% } \def\doparseargdef#1#2{% \def#2{\parsearg#1}% \def#1##1% } % Several utility definitions with active space: { \obeyspaces \gdef\obeyedspace{ } % Make each space character in the input produce a normal interword % space in the output. Don't allow a line break at this space, as this % is used only in environments like @example, where each line of input % should produce a line of output anyway. % \gdef\sepspaces{\obeyspaces\let =\tie} % If an index command is used in an @example environment, any spaces % therein should become regular spaces in the raw index file, not the % expansion of \tie (\leavevmode \penalty \@M \ ). \gdef\unsepspaces{\let =\space} } \def\flushcr{\ifx\par\lisppar \def\next##1{}\else \let\next=\relax \fi \next} % Define the framework for environments in texinfo.tex. It's used like this: % % \envdef\foo{...} % \def\Efoo{...} % % It's the responsibility of \envdef to insert \begingroup before the % actual body; @end closes the group after calling \Efoo. \envdef also % defines \thisenv, so the current environment is known; @end checks % whether the environment name matches. The \checkenv macro can also be % used to check whether the current environment is the one expected. % % Non-false conditionals (@iftex, @ifset) don't fit into this, so they % are not treated as environments; they don't open a group. (The % implementation of @end takes care not to call \endgroup in this % special case.) % At run-time, environments start with this: \def\startenvironment#1{\begingroup\def\thisenv{#1}} % initialize \let\thisenv\empty % ... but they get defined via ``\envdef\foo{...}'': \long\def\envdef#1#2{\def#1{\startenvironment#1#2}} \def\envparseargdef#1#2{\parseargdef#1{\startenvironment#1#2}} % Check whether we're in the right environment: \def\checkenv#1{% \def\temp{#1}% \ifx\thisenv\temp \else \badenverr \fi } % Environment mismatch, #1 expected: \def\badenverr{% \errhelp = \EMsimple \errmessage{This command can appear only \inenvironment\temp, not \inenvironment\thisenv}% } \def\inenvironment#1{% \ifx#1\empty outside of any environment% \else in environment \expandafter\string#1% \fi } % @end foo executes the definition of \Efoo. % But first, it executes a specialized version of \checkenv % \parseargdef\end{% \if 1\csname iscond.#1\endcsname \else % The general wording of \badenverr may not be ideal. \expandafter\checkenv\csname#1\endcsname \csname E#1\endcsname \endgroup \fi } \newhelp\EMsimple{Press RETURN to continue.} % Be sure we're in horizontal mode when doing a tie, since we make space % equivalent to this in @example-like environments. Otherwise, a space % at the beginning of a line will start with \penalty -- and % since \penalty is valid in vertical mode, we'd end up putting the % penalty on the vertical list instead of in the new paragraph. {\catcode`@ = 11 % Avoid using \@M directly, because that causes trouble % if the definition is written into an index file. \global\let\tiepenalty = \@M \gdef\tie{\leavevmode\penalty\tiepenalty\ } } % @: forces normal size whitespace following. \def\:{\spacefactor=1000 } % @* forces a line break. \def\*{\hfil\break\hbox{}\ignorespaces} % @/ allows a line break. \let\/=\allowbreak % @. is an end-of-sentence period. \def\.{.\spacefactor=\endofsentencespacefactor\space} % @! is an end-of-sentence bang. \def\!{!\spacefactor=\endofsentencespacefactor\space} % @? is an end-of-sentence query. \def\?{?\spacefactor=\endofsentencespacefactor\space} % @frenchspacing on|off says whether to put extra space after punctuation. % \def\onword{on} \def\offword{off} % \parseargdef\frenchspacing{% \def\temp{#1}% \ifx\temp\onword \plainfrenchspacing \else\ifx\temp\offword \plainnonfrenchspacing \else \errhelp = \EMsimple \errmessage{Unknown @frenchspacing option `\temp', must be on|off}% \fi\fi } % @w prevents a word break. Without the \leavevmode, @w at the % beginning of a paragraph, when TeX is still in vertical mode, would % produce a whole line of output instead of starting the paragraph. \def\w#1{\leavevmode\hbox{#1}} % @group ... @end group forces ... to be all on one page, by enclosing % it in a TeX vbox. We use \vtop instead of \vbox to construct the box % to keep its height that of a normal line. According to the rules for % \topskip (p.114 of the TeXbook), the glue inserted is % max (\topskip - \ht (first item), 0). If that height is large, % therefore, no glue is inserted, and the space between the headline and % the text is small, which looks bad. % % Another complication is that the group might be very large. This can % cause the glue on the previous page to be unduly stretched, because it % does not have much material. In this case, it's better to add an % explicit \vfill so that the extra space is at the bottom. The % threshold for doing this is if the group is more than \vfilllimit % percent of a page (\vfilllimit can be changed inside of @tex). % \newbox\groupbox \def\vfilllimit{0.7} % \envdef\group{% \ifnum\catcode`\^^M=\active \else \errhelp = \groupinvalidhelp \errmessage{@group invalid in context where filling is enabled}% \fi \startsavinginserts % \setbox\groupbox = \vtop\bgroup % Do @comment since we are called inside an environment such as % @example, where each end-of-line in the input causes an % end-of-line in the output. We don't want the end-of-line after % the `@group' to put extra space in the output. Since @group % should appear on a line by itself (according to the Texinfo % manual), we don't worry about eating any user text. \comment } % % The \vtop produces a box with normal height and large depth; thus, TeX puts % \baselineskip glue before it, and (when the next line of text is done) % \lineskip glue after it. Thus, space below is not quite equal to space % above. But it's pretty close. \def\Egroup{% % To get correct interline space between the last line of the group % and the first line afterwards, we have to propagate \prevdepth. \endgraf % Not \par, as it may have been set to \lisppar. \global\dimen1 = \prevdepth \egroup % End the \vtop. % \dimen0 is the vertical size of the group's box. \dimen0 = \ht\groupbox \advance\dimen0 by \dp\groupbox % \dimen2 is how much space is left on the page (more or less). \dimen2 = \pageheight \advance\dimen2 by -\pagetotal % if the group doesn't fit on the current page, and it's a big big % group, force a page break. \ifdim \dimen0 > \dimen2 \ifdim \pagetotal < \vfilllimit\pageheight \page \fi \fi \box\groupbox \prevdepth = \dimen1 \checkinserts } % % TeX puts in an \escapechar (i.e., `@') at the beginning of the help % message, so this ends up printing `@group can only ...'. % \newhelp\groupinvalidhelp{% group can only be used in environments such as @example,^^J% where each line of input produces a line of output.} % @need space-in-mils % forces a page break if there is not space-in-mils remaining. \newdimen\mil \mil=0.001in \parseargdef\need{% % Ensure vertical mode, so we don't make a big box in the middle of a % paragraph. \par % % If the @need value is less than one line space, it's useless. \dimen0 = #1\mil \dimen2 = \ht\strutbox \advance\dimen2 by \dp\strutbox \ifdim\dimen0 > \dimen2 % % Do a \strut just to make the height of this box be normal, so the % normal leading is inserted relative to the preceding line. % And a page break here is fine. \vtop to #1\mil{\strut\vfil}% % % TeX does not even consider page breaks if a penalty added to the % main vertical list is 10000 or more. But in order to see if the % empty box we just added fits on the page, we must make it consider % page breaks. On the other hand, we don't want to actually break the % page after the empty box. So we use a penalty of 9999. % % There is an extremely small chance that TeX will actually break the % page at this \penalty, if there are no other feasible breakpoints in % sight. (If the user is using lots of big @group commands, which % almost-but-not-quite fill up a page, TeX will have a hard time doing % good page breaking, for example.) However, I could not construct an % example where a page broke at this \penalty; if it happens in a real % document, then we can reconsider our strategy. \penalty9999 % % Back up by the size of the box, whether we did a page break or not. \kern -#1\mil % % Do not allow a page break right after this kern. \nobreak \fi } % @br forces paragraph break (and is undocumented). \let\br = \par % @page forces the start of a new page. % \def\page{\par\vfill\supereject} % @exdent text.... % outputs text on separate line in roman font, starting at standard page margin % This records the amount of indent in the innermost environment. % That's how much \exdent should take out. \newskip\exdentamount % This defn is used inside fill environments such as @defun. \parseargdef\exdent{\hfil\break\hbox{\kern -\exdentamount{\rm#1}}\hfil\break} % This defn is used inside nofill environments such as @example. \parseargdef\nofillexdent{{\advance \leftskip by -\exdentamount \leftline{\hskip\leftskip{\rm#1}}}} % @inmargin{WHICH}{TEXT} puts TEXT in the WHICH margin next to the current % paragraph. For more general purposes, use the \margin insertion % class. WHICH is `l' or `r'. Not documented, written for gawk manual. % \newskip\inmarginspacing \inmarginspacing=1cm \def\strutdepth{\dp\strutbox} % \def\doinmargin#1#2{\strut\vadjust{% \nobreak \kern-\strutdepth \vtop to \strutdepth{% \baselineskip=\strutdepth \vss % if you have multiple lines of stuff to put here, you'll need to % make the vbox yourself of the appropriate size. \ifx#1l% \llap{\ignorespaces #2\hskip\inmarginspacing}% \else \rlap{\hskip\hsize \hskip\inmarginspacing \ignorespaces #2}% \fi \null }% }} \def\inleftmargin{\doinmargin l} \def\inrightmargin{\doinmargin r} % % @inmargin{TEXT [, RIGHT-TEXT]} % (if RIGHT-TEXT is given, use TEXT for left page, RIGHT-TEXT for right; % else use TEXT for both). % \def\inmargin#1{\parseinmargin #1,,\finish} \def\parseinmargin#1,#2,#3\finish{% not perfect, but better than nothing. \setbox0 = \hbox{\ignorespaces #2}% \ifdim\wd0 > 0pt \def\lefttext{#1}% have both texts \def\righttext{#2}% \else \def\lefttext{#1}% have only one text \def\righttext{#1}% \fi % \ifodd\pageno \def\temp{\inrightmargin\righttext}% odd page -> outside is right margin \else \def\temp{\inleftmargin\lefttext}% \fi \temp } % @| inserts a changebar to the left of the current line. It should % surround any changed text. This approach does *not* work if the % change spans more than two lines of output. To handle that, we would % have adopt a much more difficult approach (putting marks into the main % vertical list for the beginning and end of each change). This command % is not documented, not supported, and doesn't work. % \def\|{% % \vadjust can only be used in horizontal mode. \leavevmode % % Append this vertical mode material after the current line in the output. \vadjust{% % We want to insert a rule with the height and depth of the current % leading; that is exactly what \strutbox is supposed to record. \vskip-\baselineskip % % \vadjust-items are inserted at the left edge of the type. So % the \llap here moves out into the left-hand margin. \llap{% % % For a thicker or thinner bar, change the `1pt'. \vrule height\baselineskip width1pt % % This is the space between the bar and the text. \hskip 12pt }% }% } % @include FILE -- \input text of FILE. % \def\include{\parseargusing\filenamecatcodes\includezzz} \def\includezzz#1{% \pushthisfilestack \def\thisfile{#1}% {% \makevalueexpandable % we want to expand any @value in FILE. \turnoffactive % and allow special characters in the expansion \indexnofonts % Allow `@@' and other weird things in file names. \wlog{texinfo.tex: doing @include of #1^^J}% \edef\temp{\noexpand\input #1 }% % % This trickery is to read FILE outside of a group, in case it makes % definitions, etc. \expandafter }\temp \popthisfilestack } \def\filenamecatcodes{% \catcode`\\=\other \catcode`~=\other \catcode`^=\other \catcode`_=\other \catcode`|=\other \catcode`<=\other \catcode`>=\other \catcode`+=\other \catcode`-=\other \catcode`\`=\other \catcode`\'=\other } \def\pushthisfilestack{% \expandafter\pushthisfilestackX\popthisfilestack\StackTerm } \def\pushthisfilestackX{% \expandafter\pushthisfilestackY\thisfile\StackTerm } \def\pushthisfilestackY #1\StackTerm #2\StackTerm {% \gdef\popthisfilestack{\gdef\thisfile{#1}\gdef\popthisfilestack{#2}}% } \def\popthisfilestack{\errthisfilestackempty} \def\errthisfilestackempty{\errmessage{Internal error: the stack of filenames is empty.}} % \def\thisfile{} % @center line % outputs that line, centered. % \parseargdef\center{% \ifhmode \let\centersub\centerH \else \let\centersub\centerV \fi \centersub{\hfil \ignorespaces#1\unskip \hfil}% \let\centersub\relax % don't let the definition persist, just in case } \def\centerH#1{{% \hfil\break \advance\hsize by -\leftskip \advance\hsize by -\rightskip \line{#1}% \break }} % \newcount\centerpenalty \def\centerV#1{% % The idea here is the same as in \startdefun, \cartouche, etc.: if % @center is the first thing after a section heading, we need to wipe % out the negative parskip inserted by \sectionheading, but still % prevent a page break here. \centerpenalty = \lastpenalty \ifnum\centerpenalty>10000 \vskip\parskip \fi \ifnum\centerpenalty>9999 \penalty\centerpenalty \fi \line{\kern\leftskip #1\kern\rightskip}% } % @sp n outputs n lines of vertical space % \parseargdef\sp{\vskip #1\baselineskip} % @comment ...line which is ignored... % @c is the same as @comment % @ignore ... @end ignore is another way to write a comment % \def\comment{\begingroup \catcode`\^^M=\other% \catcode`\@=\other \catcode`\{=\other \catcode`\}=\other% \commentxxx} {\catcode`\^^M=\other \gdef\commentxxx#1^^M{\endgroup}} % \let\c=\comment % @paragraphindent NCHARS % We'll use ems for NCHARS, close enough. % NCHARS can also be the word `asis' or `none'. % We cannot feasibly implement @paragraphindent asis, though. % \def\asisword{asis} % no translation, these are keywords \def\noneword{none} % \parseargdef\paragraphindent{% \def\temp{#1}% \ifx\temp\asisword \else \ifx\temp\noneword \defaultparindent = 0pt \else \defaultparindent = #1em \fi \fi \parindent = \defaultparindent } % @exampleindent NCHARS % We'll use ems for NCHARS like @paragraphindent. % It seems @exampleindent asis isn't necessary, but % I preserve it to make it similar to @paragraphindent. \parseargdef\exampleindent{% \def\temp{#1}% \ifx\temp\asisword \else \ifx\temp\noneword \lispnarrowing = 0pt \else \lispnarrowing = #1em \fi \fi } % @firstparagraphindent WORD % If WORD is `none', then suppress indentation of the first paragraph % after a section heading. If WORD is `insert', then do indent at such % paragraphs. % % The paragraph indentation is suppressed or not by calling % \suppressfirstparagraphindent, which the sectioning commands do. % We switch the definition of this back and forth according to WORD. % By default, we suppress indentation. % \def\suppressfirstparagraphindent{\dosuppressfirstparagraphindent} \def\insertword{insert} % \parseargdef\firstparagraphindent{% \def\temp{#1}% \ifx\temp\noneword \let\suppressfirstparagraphindent = \dosuppressfirstparagraphindent \else\ifx\temp\insertword \let\suppressfirstparagraphindent = \relax \else \errhelp = \EMsimple \errmessage{Unknown @firstparagraphindent option `\temp'}% \fi\fi } % Here is how we actually suppress indentation. Redefine \everypar to % \kern backwards by \parindent, and then reset itself to empty. % % We also make \indent itself not actually do anything until the next % paragraph. % \gdef\dosuppressfirstparagraphindent{% \gdef\indent{% \restorefirstparagraphindent \indent }% \gdef\noindent{% \restorefirstparagraphindent \noindent }% \global\everypar = {% \kern -\parindent \restorefirstparagraphindent }% } \gdef\restorefirstparagraphindent{% \global \let \indent = \ptexindent \global \let \noindent = \ptexnoindent \global \everypar = {}% } % @refill is a no-op. \let\refill=\relax % If working on a large document in chapters, it is convenient to % be able to disable indexing, cross-referencing, and contents, for test runs. % This is done with @novalidate (before @setfilename). % \newif\iflinks \linkstrue % by default we want the aux files. \let\novalidate = \linksfalse % @setfilename is done at the beginning of every texinfo file. % So open here the files we need to have open while reading the input. % This makes it possible to make a .fmt file for texinfo. \def\setfilename{% \fixbackslash % Turn off hack to swallow `\input texinfo'. \iflinks \tryauxfile % Open the new aux file. TeX will close it automatically at exit. \immediate\openout\auxfile=\jobname.aux \fi % \openindices needs to do some work in any case. \openindices \let\setfilename=\comment % Ignore extra @setfilename cmds. % % If texinfo.cnf is present on the system, read it. % Useful for site-wide @afourpaper, etc. \openin 1 texinfo.cnf \ifeof 1 \else \input texinfo.cnf \fi \closein 1 % \comment % Ignore the actual filename. } % Called from \setfilename. % \def\openindices{% \newindex{cp}% \newcodeindex{fn}% \newcodeindex{vr}% \newcodeindex{tp}% \newcodeindex{ky}% \newcodeindex{pg}% } % @bye. \outer\def\bye{\pagealignmacro\tracingstats=1\ptexend} \message{pdf,} % adobe `portable' document format \newcount\tempnum \newcount\lnkcount \newtoks\filename \newcount\filenamelength \newcount\pgn \newtoks\toksA \newtoks\toksB \newtoks\toksC \newtoks\toksD \newbox\boxA \newcount\countA \newif\ifpdf \newif\ifpdfmakepagedest % when pdftex is run in dvi mode, \pdfoutput is defined (so \pdfoutput=1 % can be set). So we test for \relax and 0 as well as being undefined. \ifx\pdfoutput\thisisundefined \else \ifx\pdfoutput\relax \else \ifcase\pdfoutput \else \pdftrue \fi \fi \fi % PDF uses PostScript string constants for the names of xref targets, % for display in the outlines, and in other places. Thus, we have to % double any backslashes. Otherwise, a name like "\node" will be % interpreted as a newline (\n), followed by o, d, e. Not good. % % See http://www.ntg.nl/pipermail/ntg-pdftex/2004-July/000654.html and % related messages. The final outcome is that it is up to the TeX user % to double the backslashes and otherwise make the string valid, so % that's what we do. pdftex 1.30.0 (ca.2005) introduced a primitive to % do this reliably, so we use it. % #1 is a control sequence in which to do the replacements, % which we \xdef. \def\txiescapepdf#1{% \ifx\pdfescapestring\relax % No primitive available; should we give a warning or log? % Many times it won't matter. \else % The expandable \pdfescapestring primitive escapes parentheses, % backslashes, and other special chars. \xdef#1{\pdfescapestring{#1}}% \fi } \newhelp\nopdfimagehelp{Texinfo supports .png, .jpg, .jpeg, and .pdf images with PDF output, and none of those formats could be found. (.eps cannot be supported due to the design of the PDF format; use regular TeX (DVI output) for that.)} \ifpdf % % Color manipulation macros based on pdfcolor.tex, % except using rgb instead of cmyk; the latter is said to render as a % very dark gray on-screen and a very dark halftone in print, instead % of actual black. \def\rgbDarkRed{0.50 0.09 0.12} \def\rgbBlack{0 0 0} % % k sets the color for filling (usual text, etc.); % K sets the color for stroking (thin rules, e.g., normal _'s). \def\pdfsetcolor#1{\pdfliteral{#1 rg #1 RG}} % % Set color, and create a mark which defines \thiscolor accordingly, % so that \makeheadline knows which color to restore. \def\setcolor#1{% \xdef\lastcolordefs{\gdef\noexpand\thiscolor{#1}}% \domark \pdfsetcolor{#1}% } % \def\maincolor{\rgbBlack} \pdfsetcolor{\maincolor} \edef\thiscolor{\maincolor} \def\lastcolordefs{} % \def\makefootline{% \baselineskip24pt \line{\pdfsetcolor{\maincolor}\the\footline}% } % \def\makeheadline{% \vbox to 0pt{% \vskip-22.5pt \line{% \vbox to8.5pt{}% % Extract \thiscolor definition from the marks. \getcolormarks % Typeset the headline with \maincolor, then restore the color. \pdfsetcolor{\maincolor}\the\headline\pdfsetcolor{\thiscolor}% }% \vss }% \nointerlineskip } % % \pdfcatalog{/PageMode /UseOutlines} % % #1 is image name, #2 width (might be empty/whitespace), #3 height (ditto). \def\dopdfimage#1#2#3{% \def\pdfimagewidth{#2}\setbox0 = \hbox{\ignorespaces #2}% \def\pdfimageheight{#3}\setbox2 = \hbox{\ignorespaces #3}% % % pdftex (and the PDF format) support .pdf, .png, .jpg (among % others). Let's try in that order, PDF first since if % someone has a scalable image, presumably better to use that than a % bitmap. \let\pdfimgext=\empty \begingroup \openin 1 #1.pdf \ifeof 1 \openin 1 #1.PDF \ifeof 1 \openin 1 #1.png \ifeof 1 \openin 1 #1.jpg \ifeof 1 \openin 1 #1.jpeg \ifeof 1 \openin 1 #1.JPG \ifeof 1 \errhelp = \nopdfimagehelp \errmessage{Could not find image file #1 for pdf}% \else \gdef\pdfimgext{JPG}% \fi \else \gdef\pdfimgext{jpeg}% \fi \else \gdef\pdfimgext{jpg}% \fi \else \gdef\pdfimgext{png}% \fi \else \gdef\pdfimgext{PDF}% \fi \else \gdef\pdfimgext{pdf}% \fi \closein 1 \endgroup % % without \immediate, ancient pdftex seg faults when the same image is % included twice. (Version 3.14159-pre-1.0-unofficial-20010704.) \ifnum\pdftexversion < 14 \immediate\pdfimage \else \immediate\pdfximage \fi \ifdim \wd0 >0pt width \pdfimagewidth \fi \ifdim \wd2 >0pt height \pdfimageheight \fi \ifnum\pdftexversion<13 #1.\pdfimgext \else {#1.\pdfimgext}% \fi \ifnum\pdftexversion < 14 \else \pdfrefximage \pdflastximage \fi} % \def\pdfmkdest#1{{% % We have to set dummies so commands such as @code, and characters % such as \, aren't expanded when present in a section title. \indexnofonts \turnoffactive \makevalueexpandable \def\pdfdestname{#1}% \txiescapepdf\pdfdestname \safewhatsit{\pdfdest name{\pdfdestname} xyz}% }} % % used to mark target names; must be expandable. \def\pdfmkpgn#1{#1} % % by default, use a color that is dark enough to print on paper as % nearly black, but still distinguishable for online viewing. \def\urlcolor{\rgbDarkRed} \def\linkcolor{\rgbDarkRed} \def\endlink{\setcolor{\maincolor}\pdfendlink} % % Adding outlines to PDF; macros for calculating structure of outlines % come from Petr Olsak \def\expnumber#1{\expandafter\ifx\csname#1\endcsname\relax 0% \else \csname#1\endcsname \fi} \def\advancenumber#1{\tempnum=\expnumber{#1}\relax \advance\tempnum by 1 \expandafter\xdef\csname#1\endcsname{\the\tempnum}} % % #1 is the section text, which is what will be displayed in the % outline by the pdf viewer. #2 is the pdf expression for the number % of subentries (or empty, for subsubsections). #3 is the node text, % which might be empty if this toc entry had no corresponding node. % #4 is the page number % \def\dopdfoutline#1#2#3#4{% % Generate a link to the node text if that exists; else, use the % page number. We could generate a destination for the section % text in the case where a section has no node, but it doesn't % seem worth the trouble, since most documents are normally structured. \edef\pdfoutlinedest{#3}% \ifx\pdfoutlinedest\empty \def\pdfoutlinedest{#4}% \else \txiescapepdf\pdfoutlinedest \fi % % Also escape PDF chars in the display string. \edef\pdfoutlinetext{#1}% \txiescapepdf\pdfoutlinetext % \pdfoutline goto name{\pdfmkpgn{\pdfoutlinedest}}#2{\pdfoutlinetext}% } % \def\pdfmakeoutlines{% \begingroup % Read toc silently, to get counts of subentries for \pdfoutline. \def\partentry##1##2##3##4{}% ignore parts in the outlines \def\numchapentry##1##2##3##4{% \def\thischapnum{##2}% \def\thissecnum{0}% \def\thissubsecnum{0}% }% \def\numsecentry##1##2##3##4{% \advancenumber{chap\thischapnum}% \def\thissecnum{##2}% \def\thissubsecnum{0}% }% \def\numsubsecentry##1##2##3##4{% \advancenumber{sec\thissecnum}% \def\thissubsecnum{##2}% }% \def\numsubsubsecentry##1##2##3##4{% \advancenumber{subsec\thissubsecnum}% }% \def\thischapnum{0}% \def\thissecnum{0}% \def\thissubsecnum{0}% % % use \def rather than \let here because we redefine \chapentry et % al. a second time, below. \def\appentry{\numchapentry}% \def\appsecentry{\numsecentry}% \def\appsubsecentry{\numsubsecentry}% \def\appsubsubsecentry{\numsubsubsecentry}% \def\unnchapentry{\numchapentry}% \def\unnsecentry{\numsecentry}% \def\unnsubsecentry{\numsubsecentry}% \def\unnsubsubsecentry{\numsubsubsecentry}% \readdatafile{toc}% % % Read toc second time, this time actually producing the outlines. % The `-' means take the \expnumber as the absolute number of % subentries, which we calculated on our first read of the .toc above. % % We use the node names as the destinations. \def\numchapentry##1##2##3##4{% \dopdfoutline{##1}{count-\expnumber{chap##2}}{##3}{##4}}% \def\numsecentry##1##2##3##4{% \dopdfoutline{##1}{count-\expnumber{sec##2}}{##3}{##4}}% \def\numsubsecentry##1##2##3##4{% \dopdfoutline{##1}{count-\expnumber{subsec##2}}{##3}{##4}}% \def\numsubsubsecentry##1##2##3##4{% count is always zero \dopdfoutline{##1}{}{##3}{##4}}% % % PDF outlines are displayed using system fonts, instead of % document fonts. Therefore we cannot use special characters, % since the encoding is unknown. For example, the eogonek from % Latin 2 (0xea) gets translated to a | character. Info from % Staszek Wawrykiewicz, 19 Jan 2004 04:09:24 +0100. % % TODO this right, we have to translate 8-bit characters to % their "best" equivalent, based on the @documentencoding. Too % much work for too little return. Just use the ASCII equivalents % we use for the index sort strings. % \indexnofonts \setupdatafile % We can have normal brace characters in the PDF outlines, unlike % Texinfo index files. So set that up. \def\{{\lbracecharliteral}% \def\}{\rbracecharliteral}% \catcode`\\=\active \otherbackslash \input \tocreadfilename \endgroup } {\catcode`[=1 \catcode`]=2 \catcode`{=\other \catcode`}=\other \gdef\lbracecharliteral[{]% \gdef\rbracecharliteral[}]% ] % \def\skipspaces#1{\def\PP{#1}\def\D{|}% \ifx\PP\D\let\nextsp\relax \else\let\nextsp\skipspaces \ifx\p\space\else\addtokens{\filename}{\PP}% \advance\filenamelength by 1 \fi \fi \nextsp} \def\getfilename#1{% \filenamelength=0 % If we don't expand the argument now, \skipspaces will get % snagged on things like "@value{foo}". \edef\temp{#1}% \expandafter\skipspaces\temp|\relax } \ifnum\pdftexversion < 14 \let \startlink \pdfannotlink \else \let \startlink \pdfstartlink \fi % make a live url in pdf output. \def\pdfurl#1{% \begingroup % it seems we really need yet another set of dummies; have not % tried to figure out what each command should do in the context % of @url. for now, just make @/ a no-op, that's the only one % people have actually reported a problem with. % \normalturnoffactive \def\@{@}% \let\/=\empty \makevalueexpandable % do we want to go so far as to use \indexnofonts instead of just % special-casing \var here? \def\var##1{##1}% % \leavevmode\setcolor{\urlcolor}% \startlink attr{/Border [0 0 0]}% user{/Subtype /Link /A << /S /URI /URI (#1) >>}% \endgroup} \def\pdfgettoks#1.{\setbox\boxA=\hbox{\toksA={#1.}\toksB={}\maketoks}} \def\addtokens#1#2{\edef\addtoks{\noexpand#1={\the#1#2}}\addtoks} \def\adn#1{\addtokens{\toksC}{#1}\global\countA=1\let\next=\maketoks} \def\poptoks#1#2|ENDTOKS|{\let\first=#1\toksD={#1}\toksA={#2}} \def\maketoks{% \expandafter\poptoks\the\toksA|ENDTOKS|\relax \ifx\first0\adn0 \else\ifx\first1\adn1 \else\ifx\first2\adn2 \else\ifx\first3\adn3 \else\ifx\first4\adn4 \else\ifx\first5\adn5 \else\ifx\first6\adn6 \else\ifx\first7\adn7 \else\ifx\first8\adn8 \else\ifx\first9\adn9 \else \ifnum0=\countA\else\makelink\fi \ifx\first.\let\next=\done\else \let\next=\maketoks \addtokens{\toksB}{\the\toksD} \ifx\first,\addtokens{\toksB}{\space}\fi \fi \fi\fi\fi\fi\fi\fi\fi\fi\fi\fi \next} \def\makelink{\addtokens{\toksB}% {\noexpand\pdflink{\the\toksC}}\toksC={}\global\countA=0} \def\pdflink#1{% \startlink attr{/Border [0 0 0]} goto name{\pdfmkpgn{#1}} \setcolor{\linkcolor}#1\endlink} \def\done{\edef\st{\global\noexpand\toksA={\the\toksB}}\st} \else % non-pdf mode \let\pdfmkdest = \gobble \let\pdfurl = \gobble \let\endlink = \relax \let\setcolor = \gobble \let\pdfsetcolor = \gobble \let\pdfmakeoutlines = \relax \fi % \ifx\pdfoutput \message{fonts,} % Change the current font style to #1, remembering it in \curfontstyle. % For now, we do not accumulate font styles: @b{@i{foo}} prints foo in % italics, not bold italics. % \def\setfontstyle#1{% \def\curfontstyle{#1}% not as a control sequence, because we are \edef'd. \csname ten#1\endcsname % change the current font } % Select #1 fonts with the current style. % \def\selectfonts#1{\csname #1fonts\endcsname \csname\curfontstyle\endcsname} \def\rm{\fam=0 \setfontstyle{rm}} \def\it{\fam=\itfam \setfontstyle{it}} \def\sl{\fam=\slfam \setfontstyle{sl}} \def\bf{\fam=\bffam \setfontstyle{bf}}\def\bfstylename{bf} \def\tt{\fam=\ttfam \setfontstyle{tt}} % Unfortunately, we have to override this for titles and the like, since % in those cases "rm" is bold. Sigh. \def\rmisbold{\rm\def\curfontstyle{bf}} % Texinfo sort of supports the sans serif font style, which plain TeX does not. % So we set up a \sf. \newfam\sffam \def\sf{\fam=\sffam \setfontstyle{sf}} \let\li = \sf % Sometimes we call it \li, not \sf. % We don't need math for this font style. \def\ttsl{\setfontstyle{ttsl}} % Default leading. \newdimen\textleading \textleading = 13.2pt % Set the baselineskip to #1, and the lineskip and strut size % correspondingly. There is no deep meaning behind these magic numbers % used as factors; they just match (closely enough) what Knuth defined. % \def\lineskipfactor{.08333} \def\strutheightpercent{.70833} \def\strutdepthpercent {.29167} % % can get a sort of poor man's double spacing by redefining this. \def\baselinefactor{1} % \def\setleading#1{% \dimen0 = #1\relax \normalbaselineskip = \baselinefactor\dimen0 \normallineskip = \lineskipfactor\normalbaselineskip \normalbaselines \setbox\strutbox =\hbox{% \vrule width0pt height\strutheightpercent\baselineskip depth \strutdepthpercent \baselineskip }% } % PDF CMaps. See also LaTeX's t1.cmap. % % do nothing with this by default. \expandafter\let\csname cmapOT1\endcsname\gobble \expandafter\let\csname cmapOT1IT\endcsname\gobble \expandafter\let\csname cmapOT1TT\endcsname\gobble % if we are producing pdf, and we have \pdffontattr, then define cmaps. % (\pdffontattr was introduced many years ago, but people still run % older pdftex's; it's easy to conditionalize, so we do.) \ifpdf \ifx\pdffontattr\thisisundefined \else \begingroup \catcode`\^^M=\active \def^^M{^^J}% Output line endings as the ^^J char. \catcode`\%=12 \immediate\pdfobj stream {%!PS-Adobe-3.0 Resource-CMap %%DocumentNeededResources: ProcSet (CIDInit) %%IncludeResource: ProcSet (CIDInit) %%BeginResource: CMap (TeX-OT1-0) %%Title: (TeX-OT1-0 TeX OT1 0) %%Version: 1.000 %%EndComments /CIDInit /ProcSet findresource begin 12 dict begin begincmap /CIDSystemInfo << /Registry (TeX) /Ordering (OT1) /Supplement 0 >> def /CMapName /TeX-OT1-0 def /CMapType 2 def 1 begincodespacerange <00> <7F> endcodespacerange 8 beginbfrange <00> <01> <0393> <09> <0A> <03A8> <23> <26> <0023> <28> <3B> <0028> <3F> <5B> <003F> <5D> <5E> <005D> <61> <7A> <0061> <7B> <7C> <2013> endbfrange 40 beginbfchar <02> <0398> <03> <039B> <04> <039E> <05> <03A0> <06> <03A3> <07> <03D2> <08> <03A6> <0B> <00660066> <0C> <00660069> <0D> <0066006C> <0E> <006600660069> <0F> <00660066006C> <10> <0131> <11> <0237> <12> <0060> <13> <00B4> <14> <02C7> <15> <02D8> <16> <00AF> <17> <02DA> <18> <00B8> <19> <00DF> <1A> <00E6> <1B> <0153> <1C> <00F8> <1D> <00C6> <1E> <0152> <1F> <00D8> <21> <0021> <22> <201D> <27> <2019> <3C> <00A1> <3D> <003D> <3E> <00BF> <5C> <201C> <5F> <02D9> <60> <2018> <7D> <02DD> <7E> <007E> <7F> <00A8> endbfchar endcmap CMapName currentdict /CMap defineresource pop end end %%EndResource %%EOF }\endgroup \expandafter\edef\csname cmapOT1\endcsname#1{% \pdffontattr#1{/ToUnicode \the\pdflastobj\space 0 R}% }% % % \cmapOT1IT \begingroup \catcode`\^^M=\active \def^^M{^^J}% Output line endings as the ^^J char. \catcode`\%=12 \immediate\pdfobj stream {%!PS-Adobe-3.0 Resource-CMap %%DocumentNeededResources: ProcSet (CIDInit) %%IncludeResource: ProcSet (CIDInit) %%BeginResource: CMap (TeX-OT1IT-0) %%Title: (TeX-OT1IT-0 TeX OT1IT 0) %%Version: 1.000 %%EndComments /CIDInit /ProcSet findresource begin 12 dict begin begincmap /CIDSystemInfo << /Registry (TeX) /Ordering (OT1IT) /Supplement 0 >> def /CMapName /TeX-OT1IT-0 def /CMapType 2 def 1 begincodespacerange <00> <7F> endcodespacerange 8 beginbfrange <00> <01> <0393> <09> <0A> <03A8> <25> <26> <0025> <28> <3B> <0028> <3F> <5B> <003F> <5D> <5E> <005D> <61> <7A> <0061> <7B> <7C> <2013> endbfrange 42 beginbfchar <02> <0398> <03> <039B> <04> <039E> <05> <03A0> <06> <03A3> <07> <03D2> <08> <03A6> <0B> <00660066> <0C> <00660069> <0D> <0066006C> <0E> <006600660069> <0F> <00660066006C> <10> <0131> <11> <0237> <12> <0060> <13> <00B4> <14> <02C7> <15> <02D8> <16> <00AF> <17> <02DA> <18> <00B8> <19> <00DF> <1A> <00E6> <1B> <0153> <1C> <00F8> <1D> <00C6> <1E> <0152> <1F> <00D8> <21> <0021> <22> <201D> <23> <0023> <24> <00A3> <27> <2019> <3C> <00A1> <3D> <003D> <3E> <00BF> <5C> <201C> <5F> <02D9> <60> <2018> <7D> <02DD> <7E> <007E> <7F> <00A8> endbfchar endcmap CMapName currentdict /CMap defineresource pop end end %%EndResource %%EOF }\endgroup \expandafter\edef\csname cmapOT1IT\endcsname#1{% \pdffontattr#1{/ToUnicode \the\pdflastobj\space 0 R}% }% % % \cmapOT1TT \begingroup \catcode`\^^M=\active \def^^M{^^J}% Output line endings as the ^^J char. \catcode`\%=12 \immediate\pdfobj stream {%!PS-Adobe-3.0 Resource-CMap %%DocumentNeededResources: ProcSet (CIDInit) %%IncludeResource: ProcSet (CIDInit) %%BeginResource: CMap (TeX-OT1TT-0) %%Title: (TeX-OT1TT-0 TeX OT1TT 0) %%Version: 1.000 %%EndComments /CIDInit /ProcSet findresource begin 12 dict begin begincmap /CIDSystemInfo << /Registry (TeX) /Ordering (OT1TT) /Supplement 0 >> def /CMapName /TeX-OT1TT-0 def /CMapType 2 def 1 begincodespacerange <00> <7F> endcodespacerange 5 beginbfrange <00> <01> <0393> <09> <0A> <03A8> <21> <26> <0021> <28> <5F> <0028> <61> <7E> <0061> endbfrange 32 beginbfchar <02> <0398> <03> <039B> <04> <039E> <05> <03A0> <06> <03A3> <07> <03D2> <08> <03A6> <0B> <2191> <0C> <2193> <0D> <0027> <0E> <00A1> <0F> <00BF> <10> <0131> <11> <0237> <12> <0060> <13> <00B4> <14> <02C7> <15> <02D8> <16> <00AF> <17> <02DA> <18> <00B8> <19> <00DF> <1A> <00E6> <1B> <0153> <1C> <00F8> <1D> <00C6> <1E> <0152> <1F> <00D8> <20> <2423> <27> <2019> <60> <2018> <7F> <00A8> endbfchar endcmap CMapName currentdict /CMap defineresource pop end end %%EndResource %%EOF }\endgroup \expandafter\edef\csname cmapOT1TT\endcsname#1{% \pdffontattr#1{/ToUnicode \the\pdflastobj\space 0 R}% }% \fi\fi % Set the font macro #1 to the font named #2, adding on the % specified font prefix (normally `cm'). % #3 is the font's design size, #4 is a scale factor, #5 is the CMap % encoding (currently only OT1, OT1IT and OT1TT are allowed, pass % empty to omit). \def\setfont#1#2#3#4#5{% \font#1=\fontprefix#2#3 scaled #4 \csname cmap#5\endcsname#1% } % This is what gets called when #5 of \setfont is empty. \let\cmap\gobble % emacs-page end of cmaps % Use cm as the default font prefix. % To specify the font prefix, you must define \fontprefix % before you read in texinfo.tex. \ifx\fontprefix\thisisundefined \def\fontprefix{cm} \fi % Support font families that don't use the same naming scheme as CM. \def\rmshape{r} \def\rmbshape{bx} %where the normal face is bold \def\bfshape{b} \def\bxshape{bx} \def\ttshape{tt} \def\ttbshape{tt} \def\ttslshape{sltt} \def\itshape{ti} \def\itbshape{bxti} \def\slshape{sl} \def\slbshape{bxsl} \def\sfshape{ss} \def\sfbshape{ss} \def\scshape{csc} \def\scbshape{csc} % Definitions for a main text size of 11pt. This is the default in % Texinfo. % \def\definetextfontsizexi{% % Text fonts (11.2pt, magstep1). \def\textnominalsize{11pt} \edef\mainmagstep{\magstephalf} \setfont\textrm\rmshape{10}{\mainmagstep}{OT1} \setfont\texttt\ttshape{10}{\mainmagstep}{OT1TT} \setfont\textbf\bfshape{10}{\mainmagstep}{OT1} \setfont\textit\itshape{10}{\mainmagstep}{OT1IT} \setfont\textsl\slshape{10}{\mainmagstep}{OT1} \setfont\textsf\sfshape{10}{\mainmagstep}{OT1} \setfont\textsc\scshape{10}{\mainmagstep}{OT1} \setfont\textttsl\ttslshape{10}{\mainmagstep}{OT1TT} \font\texti=cmmi10 scaled \mainmagstep \font\textsy=cmsy10 scaled \mainmagstep \def\textecsize{1095} % A few fonts for @defun names and args. \setfont\defbf\bfshape{10}{\magstep1}{OT1} \setfont\deftt\ttshape{10}{\magstep1}{OT1TT} \setfont\defttsl\ttslshape{10}{\magstep1}{OT1TT} \def\df{\let\tentt=\deftt \let\tenbf = \defbf \let\tenttsl=\defttsl \bf} % Fonts for indices, footnotes, small examples (9pt). \def\smallnominalsize{9pt} \setfont\smallrm\rmshape{9}{1000}{OT1} \setfont\smalltt\ttshape{9}{1000}{OT1TT} \setfont\smallbf\bfshape{10}{900}{OT1} \setfont\smallit\itshape{9}{1000}{OT1IT} \setfont\smallsl\slshape{9}{1000}{OT1} \setfont\smallsf\sfshape{9}{1000}{OT1} \setfont\smallsc\scshape{10}{900}{OT1} \setfont\smallttsl\ttslshape{10}{900}{OT1TT} \font\smalli=cmmi9 \font\smallsy=cmsy9 \def\smallecsize{0900} % Fonts for small examples (8pt). \def\smallernominalsize{8pt} \setfont\smallerrm\rmshape{8}{1000}{OT1} \setfont\smallertt\ttshape{8}{1000}{OT1TT} \setfont\smallerbf\bfshape{10}{800}{OT1} \setfont\smallerit\itshape{8}{1000}{OT1IT} \setfont\smallersl\slshape{8}{1000}{OT1} \setfont\smallersf\sfshape{8}{1000}{OT1} \setfont\smallersc\scshape{10}{800}{OT1} \setfont\smallerttsl\ttslshape{10}{800}{OT1TT} \font\smalleri=cmmi8 \font\smallersy=cmsy8 \def\smallerecsize{0800} % Fonts for title page (20.4pt): \def\titlenominalsize{20pt} \setfont\titlerm\rmbshape{12}{\magstep3}{OT1} \setfont\titleit\itbshape{10}{\magstep4}{OT1IT} \setfont\titlesl\slbshape{10}{\magstep4}{OT1} \setfont\titlett\ttbshape{12}{\magstep3}{OT1TT} \setfont\titlettsl\ttslshape{10}{\magstep4}{OT1TT} \setfont\titlesf\sfbshape{17}{\magstep1}{OT1} \let\titlebf=\titlerm \setfont\titlesc\scbshape{10}{\magstep4}{OT1} \font\titlei=cmmi12 scaled \magstep3 \font\titlesy=cmsy10 scaled \magstep4 \def\titleecsize{2074} % Chapter (and unnumbered) fonts (17.28pt). \def\chapnominalsize{17pt} \setfont\chaprm\rmbshape{12}{\magstep2}{OT1} \setfont\chapit\itbshape{10}{\magstep3}{OT1IT} \setfont\chapsl\slbshape{10}{\magstep3}{OT1} \setfont\chaptt\ttbshape{12}{\magstep2}{OT1TT} \setfont\chapttsl\ttslshape{10}{\magstep3}{OT1TT} \setfont\chapsf\sfbshape{17}{1000}{OT1} \let\chapbf=\chaprm \setfont\chapsc\scbshape{10}{\magstep3}{OT1} \font\chapi=cmmi12 scaled \magstep2 \font\chapsy=cmsy10 scaled \magstep3 \def\chapecsize{1728} % Section fonts (14.4pt). \def\secnominalsize{14pt} \setfont\secrm\rmbshape{12}{\magstep1}{OT1} \setfont\secit\itbshape{10}{\magstep2}{OT1IT} \setfont\secsl\slbshape{10}{\magstep2}{OT1} \setfont\sectt\ttbshape{12}{\magstep1}{OT1TT} \setfont\secttsl\ttslshape{10}{\magstep2}{OT1TT} \setfont\secsf\sfbshape{12}{\magstep1}{OT1} \let\secbf\secrm \setfont\secsc\scbshape{10}{\magstep2}{OT1} \font\seci=cmmi12 scaled \magstep1 \font\secsy=cmsy10 scaled \magstep2 \def\sececsize{1440} % Subsection fonts (13.15pt). \def\ssecnominalsize{13pt} \setfont\ssecrm\rmbshape{12}{\magstephalf}{OT1} \setfont\ssecit\itbshape{10}{1315}{OT1IT} \setfont\ssecsl\slbshape{10}{1315}{OT1} \setfont\ssectt\ttbshape{12}{\magstephalf}{OT1TT} \setfont\ssecttsl\ttslshape{10}{1315}{OT1TT} \setfont\ssecsf\sfbshape{12}{\magstephalf}{OT1} \let\ssecbf\ssecrm \setfont\ssecsc\scbshape{10}{1315}{OT1} \font\sseci=cmmi12 scaled \magstephalf \font\ssecsy=cmsy10 scaled 1315 \def\ssececsize{1200} % Reduced fonts for @acro in text (10pt). \def\reducednominalsize{10pt} \setfont\reducedrm\rmshape{10}{1000}{OT1} \setfont\reducedtt\ttshape{10}{1000}{OT1TT} \setfont\reducedbf\bfshape{10}{1000}{OT1} \setfont\reducedit\itshape{10}{1000}{OT1IT} \setfont\reducedsl\slshape{10}{1000}{OT1} \setfont\reducedsf\sfshape{10}{1000}{OT1} \setfont\reducedsc\scshape{10}{1000}{OT1} \setfont\reducedttsl\ttslshape{10}{1000}{OT1TT} \font\reducedi=cmmi10 \font\reducedsy=cmsy10 \def\reducedecsize{1000} \textleading = 13.2pt % line spacing for 11pt CM \textfonts % reset the current fonts \rm } % end of 11pt text font size definitions % Definitions to make the main text be 10pt Computer Modern, with % section, chapter, etc., sizes following suit. This is for the GNU % Press printing of the Emacs 22 manual. Maybe other manuals in the % future. Used with @smallbook, which sets the leading to 12pt. % \def\definetextfontsizex{% % Text fonts (10pt). \def\textnominalsize{10pt} \edef\mainmagstep{1000} \setfont\textrm\rmshape{10}{\mainmagstep}{OT1} \setfont\texttt\ttshape{10}{\mainmagstep}{OT1TT} \setfont\textbf\bfshape{10}{\mainmagstep}{OT1} \setfont\textit\itshape{10}{\mainmagstep}{OT1IT} \setfont\textsl\slshape{10}{\mainmagstep}{OT1} \setfont\textsf\sfshape{10}{\mainmagstep}{OT1} \setfont\textsc\scshape{10}{\mainmagstep}{OT1} \setfont\textttsl\ttslshape{10}{\mainmagstep}{OT1TT} \font\texti=cmmi10 scaled \mainmagstep \font\textsy=cmsy10 scaled \mainmagstep \def\textecsize{1000} % A few fonts for @defun names and args. \setfont\defbf\bfshape{10}{\magstephalf}{OT1} \setfont\deftt\ttshape{10}{\magstephalf}{OT1TT} \setfont\defttsl\ttslshape{10}{\magstephalf}{OT1TT} \def\df{\let\tentt=\deftt \let\tenbf = \defbf \let\tenttsl=\defttsl \bf} % Fonts for indices, footnotes, small examples (9pt). \def\smallnominalsize{9pt} \setfont\smallrm\rmshape{9}{1000}{OT1} \setfont\smalltt\ttshape{9}{1000}{OT1TT} \setfont\smallbf\bfshape{10}{900}{OT1} \setfont\smallit\itshape{9}{1000}{OT1IT} \setfont\smallsl\slshape{9}{1000}{OT1} \setfont\smallsf\sfshape{9}{1000}{OT1} \setfont\smallsc\scshape{10}{900}{OT1} \setfont\smallttsl\ttslshape{10}{900}{OT1TT} \font\smalli=cmmi9 \font\smallsy=cmsy9 \def\smallecsize{0900} % Fonts for small examples (8pt). \def\smallernominalsize{8pt} \setfont\smallerrm\rmshape{8}{1000}{OT1} \setfont\smallertt\ttshape{8}{1000}{OT1TT} \setfont\smallerbf\bfshape{10}{800}{OT1} \setfont\smallerit\itshape{8}{1000}{OT1IT} \setfont\smallersl\slshape{8}{1000}{OT1} \setfont\smallersf\sfshape{8}{1000}{OT1} \setfont\smallersc\scshape{10}{800}{OT1} \setfont\smallerttsl\ttslshape{10}{800}{OT1TT} \font\smalleri=cmmi8 \font\smallersy=cmsy8 \def\smallerecsize{0800} % Fonts for title page (20.4pt): \def\titlenominalsize{20pt} \setfont\titlerm\rmbshape{12}{\magstep3}{OT1} \setfont\titleit\itbshape{10}{\magstep4}{OT1IT} \setfont\titlesl\slbshape{10}{\magstep4}{OT1} \setfont\titlett\ttbshape{12}{\magstep3}{OT1TT} \setfont\titlettsl\ttslshape{10}{\magstep4}{OT1TT} \setfont\titlesf\sfbshape{17}{\magstep1}{OT1} \let\titlebf=\titlerm \setfont\titlesc\scbshape{10}{\magstep4}{OT1} \font\titlei=cmmi12 scaled \magstep3 \font\titlesy=cmsy10 scaled \magstep4 \def\titleecsize{2074} % Chapter fonts (14.4pt). \def\chapnominalsize{14pt} \setfont\chaprm\rmbshape{12}{\magstep1}{OT1} \setfont\chapit\itbshape{10}{\magstep2}{OT1IT} \setfont\chapsl\slbshape{10}{\magstep2}{OT1} \setfont\chaptt\ttbshape{12}{\magstep1}{OT1TT} \setfont\chapttsl\ttslshape{10}{\magstep2}{OT1TT} \setfont\chapsf\sfbshape{12}{\magstep1}{OT1} \let\chapbf\chaprm \setfont\chapsc\scbshape{10}{\magstep2}{OT1} \font\chapi=cmmi12 scaled \magstep1 \font\chapsy=cmsy10 scaled \magstep2 \def\chapecsize{1440} % Section fonts (12pt). \def\secnominalsize{12pt} \setfont\secrm\rmbshape{12}{1000}{OT1} \setfont\secit\itbshape{10}{\magstep1}{OT1IT} \setfont\secsl\slbshape{10}{\magstep1}{OT1} \setfont\sectt\ttbshape{12}{1000}{OT1TT} \setfont\secttsl\ttslshape{10}{\magstep1}{OT1TT} \setfont\secsf\sfbshape{12}{1000}{OT1} \let\secbf\secrm \setfont\secsc\scbshape{10}{\magstep1}{OT1} \font\seci=cmmi12 \font\secsy=cmsy10 scaled \magstep1 \def\sececsize{1200} % Subsection fonts (10pt). \def\ssecnominalsize{10pt} \setfont\ssecrm\rmbshape{10}{1000}{OT1} \setfont\ssecit\itbshape{10}{1000}{OT1IT} \setfont\ssecsl\slbshape{10}{1000}{OT1} \setfont\ssectt\ttbshape{10}{1000}{OT1TT} \setfont\ssecttsl\ttslshape{10}{1000}{OT1TT} \setfont\ssecsf\sfbshape{10}{1000}{OT1} \let\ssecbf\ssecrm \setfont\ssecsc\scbshape{10}{1000}{OT1} \font\sseci=cmmi10 \font\ssecsy=cmsy10 \def\ssececsize{1000} % Reduced fonts for @acro in text (9pt). \def\reducednominalsize{9pt} \setfont\reducedrm\rmshape{9}{1000}{OT1} \setfont\reducedtt\ttshape{9}{1000}{OT1TT} \setfont\reducedbf\bfshape{10}{900}{OT1} \setfont\reducedit\itshape{9}{1000}{OT1IT} \setfont\reducedsl\slshape{9}{1000}{OT1} \setfont\reducedsf\sfshape{9}{1000}{OT1} \setfont\reducedsc\scshape{10}{900}{OT1} \setfont\reducedttsl\ttslshape{10}{900}{OT1TT} \font\reducedi=cmmi9 \font\reducedsy=cmsy9 \def\reducedecsize{0900} \divide\parskip by 2 % reduce space between paragraphs \textleading = 12pt % line spacing for 10pt CM \textfonts % reset the current fonts \rm } % end of 10pt text font size definitions % We provide the user-level command % @fonttextsize 10 % (or 11) to redefine the text font size. pt is assumed. % \def\xiword{11} \def\xword{10} \def\xwordpt{10pt} % \parseargdef\fonttextsize{% \def\textsizearg{#1}% %\wlog{doing @fonttextsize \textsizearg}% % % Set \globaldefs so that documents can use this inside @tex, since % makeinfo 4.8 does not support it, but we need it nonetheless. % \begingroup \globaldefs=1 \ifx\textsizearg\xword \definetextfontsizex \else \ifx\textsizearg\xiword \definetextfontsizexi \else \errhelp=\EMsimple \errmessage{@fonttextsize only supports `10' or `11', not `\textsizearg'} \fi\fi \endgroup } % In order for the font changes to affect most math symbols and letters, % we have to define the \textfont of the standard families. Since % texinfo doesn't allow for producing subscripts and superscripts except % in the main text, we don't bother to reset \scriptfont and % \scriptscriptfont (which would also require loading a lot more fonts). % \def\resetmathfonts{% \textfont0=\tenrm \textfont1=\teni \textfont2=\tensy \textfont\itfam=\tenit \textfont\slfam=\tensl \textfont\bffam=\tenbf \textfont\ttfam=\tentt \textfont\sffam=\tensf } % The font-changing commands redefine the meanings of \tenSTYLE, instead % of just \STYLE. We do this because \STYLE needs to also set the % current \fam for math mode. Our \STYLE (e.g., \rm) commands hardwire % \tenSTYLE to set the current font. % % Each font-changing command also sets the names \lsize (one size lower) % and \lllsize (three sizes lower). These relative commands are used in % the LaTeX logo and acronyms. % % This all needs generalizing, badly. % \def\textfonts{% \let\tenrm=\textrm \let\tenit=\textit \let\tensl=\textsl \let\tenbf=\textbf \let\tentt=\texttt \let\smallcaps=\textsc \let\tensf=\textsf \let\teni=\texti \let\tensy=\textsy \let\tenttsl=\textttsl \def\curfontsize{text}% \def\lsize{reduced}\def\lllsize{smaller}% \resetmathfonts \setleading{\textleading}} \def\titlefonts{% \let\tenrm=\titlerm \let\tenit=\titleit \let\tensl=\titlesl \let\tenbf=\titlebf \let\tentt=\titlett \let\smallcaps=\titlesc \let\tensf=\titlesf \let\teni=\titlei \let\tensy=\titlesy \let\tenttsl=\titlettsl \def\curfontsize{title}% \def\lsize{chap}\def\lllsize{subsec}% \resetmathfonts \setleading{27pt}} \def\titlefont#1{{\titlefonts\rmisbold #1}} \def\chapfonts{% \let\tenrm=\chaprm \let\tenit=\chapit \let\tensl=\chapsl \let\tenbf=\chapbf \let\tentt=\chaptt \let\smallcaps=\chapsc \let\tensf=\chapsf \let\teni=\chapi \let\tensy=\chapsy \let\tenttsl=\chapttsl \def\curfontsize{chap}% \def\lsize{sec}\def\lllsize{text}% \resetmathfonts \setleading{19pt}} \def\secfonts{% \let\tenrm=\secrm \let\tenit=\secit \let\tensl=\secsl \let\tenbf=\secbf \let\tentt=\sectt \let\smallcaps=\secsc \let\tensf=\secsf \let\teni=\seci \let\tensy=\secsy \let\tenttsl=\secttsl \def\curfontsize{sec}% \def\lsize{subsec}\def\lllsize{reduced}% \resetmathfonts \setleading{16pt}} \def\subsecfonts{% \let\tenrm=\ssecrm \let\tenit=\ssecit \let\tensl=\ssecsl \let\tenbf=\ssecbf \let\tentt=\ssectt \let\smallcaps=\ssecsc \let\tensf=\ssecsf \let\teni=\sseci \let\tensy=\ssecsy \let\tenttsl=\ssecttsl \def\curfontsize{ssec}% \def\lsize{text}\def\lllsize{small}% \resetmathfonts \setleading{15pt}} \let\subsubsecfonts = \subsecfonts \def\reducedfonts{% \let\tenrm=\reducedrm \let\tenit=\reducedit \let\tensl=\reducedsl \let\tenbf=\reducedbf \let\tentt=\reducedtt \let\reducedcaps=\reducedsc \let\tensf=\reducedsf \let\teni=\reducedi \let\tensy=\reducedsy \let\tenttsl=\reducedttsl \def\curfontsize{reduced}% \def\lsize{small}\def\lllsize{smaller}% \resetmathfonts \setleading{10.5pt}} \def\smallfonts{% \let\tenrm=\smallrm \let\tenit=\smallit \let\tensl=\smallsl \let\tenbf=\smallbf \let\tentt=\smalltt \let\smallcaps=\smallsc \let\tensf=\smallsf \let\teni=\smalli \let\tensy=\smallsy \let\tenttsl=\smallttsl \def\curfontsize{small}% \def\lsize{smaller}\def\lllsize{smaller}% \resetmathfonts \setleading{10.5pt}} \def\smallerfonts{% \let\tenrm=\smallerrm \let\tenit=\smallerit \let\tensl=\smallersl \let\tenbf=\smallerbf \let\tentt=\smallertt \let\smallcaps=\smallersc \let\tensf=\smallersf \let\teni=\smalleri \let\tensy=\smallersy \let\tenttsl=\smallerttsl \def\curfontsize{smaller}% \def\lsize{smaller}\def\lllsize{smaller}% \resetmathfonts \setleading{9.5pt}} % Fonts for short table of contents. \setfont\shortcontrm\rmshape{12}{1000}{OT1} \setfont\shortcontbf\bfshape{10}{\magstep1}{OT1} % no cmb12 \setfont\shortcontsl\slshape{12}{1000}{OT1} \setfont\shortconttt\ttshape{12}{1000}{OT1TT} % Define these just so they can be easily changed for other fonts. \def\angleleft{$\langle$} \def\angleright{$\rangle$} % Set the fonts to use with the @small... environments. \let\smallexamplefonts = \smallfonts % About \smallexamplefonts. If we use \smallfonts (9pt), @smallexample % can fit this many characters: % 8.5x11=86 smallbook=72 a4=90 a5=69 % If we use \scriptfonts (8pt), then we can fit this many characters: % 8.5x11=90+ smallbook=80 a4=90+ a5=77 % For me, subjectively, the few extra characters that fit aren't worth % the additional smallness of 8pt. So I'm making the default 9pt. % % By the way, for comparison, here's what fits with @example (10pt): % 8.5x11=71 smallbook=60 a4=75 a5=58 % --karl, 24jan03. % Set up the default fonts, so we can use them for creating boxes. % \definetextfontsizexi \message{markup,} % Check if we are currently using a typewriter font. Since all the % Computer Modern typewriter fonts have zero interword stretch (and % shrink), and it is reasonable to expect all typewriter fonts to have % this property, we can check that font parameter. % \def\ifmonospace{\ifdim\fontdimen3\font=0pt } % Markup style infrastructure. \defmarkupstylesetup\INITMACRO will % define and register \INITMACRO to be called on markup style changes. % \INITMACRO can check \currentmarkupstyle for the innermost % style and the set of \ifmarkupSTYLE switches for all styles % currently in effect. \newif\ifmarkupvar \newif\ifmarkupsamp \newif\ifmarkupkey %\newif\ifmarkupfile % @file == @samp. %\newif\ifmarkupoption % @option == @samp. \newif\ifmarkupcode \newif\ifmarkupkbd %\newif\ifmarkupenv % @env == @code. %\newif\ifmarkupcommand % @command == @code. \newif\ifmarkuptex % @tex (and part of @math, for now). \newif\ifmarkupexample \newif\ifmarkupverb \newif\ifmarkupverbatim \let\currentmarkupstyle\empty \def\setupmarkupstyle#1{% \csname markup#1true\endcsname \def\currentmarkupstyle{#1}% \markupstylesetup } \let\markupstylesetup\empty \def\defmarkupstylesetup#1{% \expandafter\def\expandafter\markupstylesetup \expandafter{\markupstylesetup #1}% \def#1% } % Markup style setup for left and right quotes. \defmarkupstylesetup\markupsetuplq{% \expandafter\let\expandafter \temp \csname markupsetuplq\currentmarkupstyle\endcsname \ifx\temp\relax \markupsetuplqdefault \else \temp \fi } \defmarkupstylesetup\markupsetuprq{% \expandafter\let\expandafter \temp \csname markupsetuprq\currentmarkupstyle\endcsname \ifx\temp\relax \markupsetuprqdefault \else \temp \fi } { \catcode`\'=\active \catcode`\`=\active \gdef\markupsetuplqdefault{\let`\lq} \gdef\markupsetuprqdefault{\let'\rq} \gdef\markupsetcodequoteleft{\let`\codequoteleft} \gdef\markupsetcodequoteright{\let'\codequoteright} \gdef\markupsetnoligaturesquoteleft{\let`\noligaturesquoteleft} } \let\markupsetuplqcode \markupsetcodequoteleft \let\markupsetuprqcode \markupsetcodequoteright % \let\markupsetuplqexample \markupsetcodequoteleft \let\markupsetuprqexample \markupsetcodequoteright % \let\markupsetuplqsamp \markupsetcodequoteleft \let\markupsetuprqsamp \markupsetcodequoteright % \let\markupsetuplqverb \markupsetcodequoteleft \let\markupsetuprqverb \markupsetcodequoteright % \let\markupsetuplqverbatim \markupsetcodequoteleft \let\markupsetuprqverbatim \markupsetcodequoteright \let\markupsetuplqkbd \markupsetnoligaturesquoteleft % Allow an option to not use regular directed right quote/apostrophe % (char 0x27), but instead the undirected quote from cmtt (char 0x0d). % The undirected quote is ugly, so don't make it the default, but it % works for pasting with more pdf viewers (at least evince), the % lilypond developers report. xpdf does work with the regular 0x27. % \def\codequoteright{% \expandafter\ifx\csname SETtxicodequoteundirected\endcsname\relax \expandafter\ifx\csname SETcodequoteundirected\endcsname\relax '% \else \char'15 \fi \else \char'15 \fi } % % and a similar option for the left quote char vs. a grave accent. % Modern fonts display ASCII 0x60 as a grave accent, so some people like % the code environments to do likewise. % \def\codequoteleft{% \expandafter\ifx\csname SETtxicodequotebacktick\endcsname\relax \expandafter\ifx\csname SETcodequotebacktick\endcsname\relax % [Knuth] pp. 380,381,391 % \relax disables Spanish ligatures ?` and !` of \tt font. \relax`% \else \char'22 \fi \else \char'22 \fi } % Commands to set the quote options. % \parseargdef\codequoteundirected{% \def\temp{#1}% \ifx\temp\onword \expandafter\let\csname SETtxicodequoteundirected\endcsname = t% \else\ifx\temp\offword \expandafter\let\csname SETtxicodequoteundirected\endcsname = \relax \else \errhelp = \EMsimple \errmessage{Unknown @codequoteundirected value `\temp', must be on|off}% \fi\fi } % \parseargdef\codequotebacktick{% \def\temp{#1}% \ifx\temp\onword \expandafter\let\csname SETtxicodequotebacktick\endcsname = t% \else\ifx\temp\offword \expandafter\let\csname SETtxicodequotebacktick\endcsname = \relax \else \errhelp = \EMsimple \errmessage{Unknown @codequotebacktick value `\temp', must be on|off}% \fi\fi } % [Knuth] pp. 380,381,391, disable Spanish ligatures ?` and !` of \tt font. \def\noligaturesquoteleft{\relax\lq} % Count depth in font-changes, for error checks \newcount\fontdepth \fontdepth=0 % Font commands. % #1 is the font command (\sl or \it), #2 is the text to slant. % If we are in a monospaced environment, however, 1) always use \ttsl, % and 2) do not add an italic correction. \def\dosmartslant#1#2{% \ifusingtt {{\ttsl #2}\let\next=\relax}% {\def\next{{#1#2}\futurelet\next\smartitaliccorrection}}% \next } \def\smartslanted{\dosmartslant\sl} \def\smartitalic{\dosmartslant\it} % Output an italic correction unless \next (presumed to be the following % character) is such as not to need one. \def\smartitaliccorrection{% \ifx\next,% \else\ifx\next-% \else\ifx\next.% \else\ptexslash \fi\fi\fi \aftersmartic } % like \smartslanted except unconditionally uses \ttsl, and no ic. % @var is set to this for defun arguments. \def\ttslanted#1{{\ttsl #1}} % @cite is like \smartslanted except unconditionally use \sl. We never want % ttsl for book titles, do we? \def\cite#1{{\sl #1}\futurelet\next\smartitaliccorrection} \def\aftersmartic{} \def\var#1{% \let\saveaftersmartic = \aftersmartic \def\aftersmartic{\null\let\aftersmartic=\saveaftersmartic}% \smartslanted{#1}% } \let\i=\smartitalic \let\slanted=\smartslanted \let\dfn=\smartslanted \let\emph=\smartitalic % Explicit font changes: @r, @sc, undocumented @ii. \def\r#1{{\rm #1}} % roman font \def\sc#1{{\smallcaps#1}} % smallcaps font \def\ii#1{{\it #1}} % italic font % @b, explicit bold. Also @strong. \def\b#1{{\bf #1}} \let\strong=\b % @sansserif, explicit sans. \def\sansserif#1{{\sf #1}} % We can't just use \exhyphenpenalty, because that only has effect at % the end of a paragraph. Restore normal hyphenation at the end of the % group within which \nohyphenation is presumably called. % \def\nohyphenation{\hyphenchar\font = -1 \aftergroup\restorehyphenation} \def\restorehyphenation{\hyphenchar\font = `- } % Set sfcode to normal for the chars that usually have another value. % Can't use plain's \frenchspacing because it uses the `\x notation, and % sometimes \x has an active definition that messes things up. % \catcode`@=11 \def\plainfrenchspacing{% \sfcode\dotChar =\@m \sfcode\questChar=\@m \sfcode\exclamChar=\@m \sfcode\colonChar=\@m \sfcode\semiChar =\@m \sfcode\commaChar =\@m \def\endofsentencespacefactor{1000}% for @. and friends } \def\plainnonfrenchspacing{% \sfcode`\.3000\sfcode`\?3000\sfcode`\!3000 \sfcode`\:2000\sfcode`\;1500\sfcode`\,1250 \def\endofsentencespacefactor{3000}% for @. and friends } \catcode`@=\other \def\endofsentencespacefactor{3000}% default % @t, explicit typewriter. \def\t#1{% {\tt \rawbackslash \plainfrenchspacing #1}% \null } % @samp. \def\samp#1{{\setupmarkupstyle{samp}\lq\tclose{#1}\rq\null}} % definition of @key that produces a lozenge. Doesn't adjust to text size. %\setfont\keyrm\rmshape{8}{1000}{OT1} %\font\keysy=cmsy9 %\def\key#1{{\keyrm\textfont2=\keysy \leavevmode\hbox{% % \raise0.4pt\hbox{\angleleft}\kern-.08em\vtop{% % \vbox{\hrule\kern-0.4pt % \hbox{\raise0.4pt\hbox{\vphantom{\angleleft}}#1}}% % \kern-0.4pt\hrule}% % \kern-.06em\raise0.4pt\hbox{\angleright}}}} % definition of @key with no lozenge. If the current font is already % monospace, don't change it; that way, we respect @kbdinputstyle. But % if it isn't monospace, then use \tt. % \def\key#1{{\setupmarkupstyle{key}% \nohyphenation \ifmonospace\else\tt\fi #1}\null} % ctrl is no longer a Texinfo command. \def\ctrl #1{{\tt \rawbackslash \hat}#1} % @file, @option are the same as @samp. \let\file=\samp \let\option=\samp % @code is a modification of @t, % which makes spaces the same size as normal in the surrounding text. \def\tclose#1{% {% % Change normal interword space to be same as for the current font. \spaceskip = \fontdimen2\font % % Switch to typewriter. \tt % % But `\ ' produces the large typewriter interword space. \def\ {{\spaceskip = 0pt{} }}% % % Turn off hyphenation. \nohyphenation % \rawbackslash \plainfrenchspacing #1% }% \null % reset spacefactor to 1000 } % We *must* turn on hyphenation at `-' and `_' in @code. % Otherwise, it is too hard to avoid overfull hboxes % in the Emacs manual, the Library manual, etc. % Unfortunately, TeX uses one parameter (\hyphenchar) to control % both hyphenation at - and hyphenation within words. % We must therefore turn them both off (\tclose does that) % and arrange explicitly to hyphenate at a dash. % -- rms. { \catcode`\-=\active \catcode`\_=\active \catcode`\'=\active \catcode`\`=\active \global\let'=\rq \global\let`=\lq % default definitions % \global\def\code{\begingroup \setupmarkupstyle{code}% % The following should really be moved into \setupmarkupstyle handlers. \catcode\dashChar=\active \catcode\underChar=\active \ifallowcodebreaks \let-\codedash \let_\codeunder \else \let-\realdash \let_\realunder \fi \codex } } \def\codex #1{\tclose{#1}\endgroup} \def\realdash{-} \def\codedash{-\discretionary{}{}{}} \def\codeunder{% % this is all so @math{@code{var_name}+1} can work. In math mode, _ % is "active" (mathcode"8000) and \normalunderscore (or \char95, etc.) % will therefore expand the active definition of _, which is us % (inside @code that is), therefore an endless loop. \ifusingtt{\ifmmode \mathchar"075F % class 0=ordinary, family 7=ttfam, pos 0x5F=_. \else\normalunderscore \fi \discretionary{}{}{}}% {\_}% } % An additional complication: the above will allow breaks after, e.g., % each of the four underscores in __typeof__. This is undesirable in % some manuals, especially if they don't have long identifiers in % general. @allowcodebreaks provides a way to control this. % \newif\ifallowcodebreaks \allowcodebreakstrue \def\keywordtrue{true} \def\keywordfalse{false} \parseargdef\allowcodebreaks{% \def\txiarg{#1}% \ifx\txiarg\keywordtrue \allowcodebreakstrue \else\ifx\txiarg\keywordfalse \allowcodebreaksfalse \else \errhelp = \EMsimple \errmessage{Unknown @allowcodebreaks option `\txiarg', must be true|false}% \fi\fi } % @uref (abbreviation for `urlref') takes an optional (comma-separated) % second argument specifying the text to display and an optional third % arg as text to display instead of (rather than in addition to) the url % itself. First (mandatory) arg is the url. % (This \urefnobreak definition isn't used now, leaving it for a while % for comparison.) \def\urefnobreak#1{\dourefnobreak #1,,,\finish} \def\dourefnobreak#1,#2,#3,#4\finish{\begingroup \unsepspaces \pdfurl{#1}% \setbox0 = \hbox{\ignorespaces #3}% \ifdim\wd0 > 0pt \unhbox0 % third arg given, show only that \else \setbox0 = \hbox{\ignorespaces #2}% \ifdim\wd0 > 0pt \ifpdf \unhbox0 % PDF: 2nd arg given, show only it \else \unhbox0\ (\code{#1})% DVI: 2nd arg given, show both it and url \fi \else \code{#1}% only url given, so show it \fi \fi \endlink \endgroup} % This \urefbreak definition is the active one. \def\urefbreak{\begingroup \urefcatcodes \dourefbreak} \let\uref=\urefbreak \def\dourefbreak#1{\urefbreakfinish #1,,,\finish} \def\urefbreakfinish#1,#2,#3,#4\finish{% doesn't work in @example \unsepspaces \pdfurl{#1}% \setbox0 = \hbox{\ignorespaces #3}% \ifdim\wd0 > 0pt \unhbox0 % third arg given, show only that \else \setbox0 = \hbox{\ignorespaces #2}% \ifdim\wd0 > 0pt \ifpdf \unhbox0 % PDF: 2nd arg given, show only it \else \unhbox0\ (\urefcode{#1})% DVI: 2nd arg given, show both it and url \fi \else \urefcode{#1}% only url given, so show it \fi \fi \endlink \endgroup} % Allow line breaks around only a few characters (only). \def\urefcatcodes{% \catcode\ampChar=\active \catcode\dotChar=\active \catcode\hashChar=\active \catcode\questChar=\active \catcode\slashChar=\active } { \urefcatcodes % \global\def\urefcode{\begingroup \setupmarkupstyle{code}% \urefcatcodes \let&\urefcodeamp \let.\urefcodedot \let#\urefcodehash \let?\urefcodequest \let/\urefcodeslash \codex } % % By default, they are just regular characters. \global\def&{\normalamp} \global\def.{\normaldot} \global\def#{\normalhash} \global\def?{\normalquest} \global\def/{\normalslash} } % we put a little stretch before and after the breakable chars, to help % line breaking of long url's. The unequal skips make look better in % cmtt at least, especially for dots. \def\urefprestretch{\urefprebreak \hskip0pt plus.13em } \def\urefpoststretch{\urefpostbreak \hskip0pt plus.1em } % \def\urefcodeamp{\urefprestretch \&\urefpoststretch} \def\urefcodedot{\urefprestretch .\urefpoststretch} \def\urefcodehash{\urefprestretch \#\urefpoststretch} \def\urefcodequest{\urefprestretch ?\urefpoststretch} \def\urefcodeslash{\futurelet\next\urefcodeslashfinish} { \catcode`\/=\active \global\def\urefcodeslashfinish{% \urefprestretch \slashChar % Allow line break only after the final / in a sequence of % slashes, to avoid line break between the slashes in http://. \ifx\next/\else \urefpoststretch \fi } } % One more complication: by default we'll break after the special % characters, but some people like to break before the special chars, so % allow that. Also allow no breaking at all, for manual control. % \parseargdef\urefbreakstyle{% \def\txiarg{#1}% \ifx\txiarg\wordnone \def\urefprebreak{\nobreak}\def\urefpostbreak{\nobreak} \else\ifx\txiarg\wordbefore \def\urefprebreak{\allowbreak}\def\urefpostbreak{\nobreak} \else\ifx\txiarg\wordafter \def\urefprebreak{\nobreak}\def\urefpostbreak{\allowbreak} \else \errhelp = \EMsimple \errmessage{Unknown @urefbreakstyle setting `\txiarg'}% \fi\fi\fi } \def\wordafter{after} \def\wordbefore{before} \def\wordnone{none} \urefbreakstyle after % @url synonym for @uref, since that's how everyone uses it. % \let\url=\uref % rms does not like angle brackets --karl, 17may97. % So now @email is just like @uref, unless we are pdf. % %\def\email#1{\angleleft{\tt #1}\angleright} \ifpdf \def\email#1{\doemail#1,,\finish} \def\doemail#1,#2,#3\finish{\begingroup \unsepspaces \pdfurl{mailto:#1}% \setbox0 = \hbox{\ignorespaces #2}% \ifdim\wd0>0pt\unhbox0\else\code{#1}\fi \endlink \endgroup} \else \let\email=\uref \fi % @kbd is like @code, except that if the argument is just one @key command, % then @kbd has no effect. \def\kbd#1{{\setupmarkupstyle{kbd}\def\look{#1}\expandafter\kbdfoo\look??\par}} % @kbdinputstyle -- arg is `distinct' (@kbd uses slanted tty font always), % `example' (@kbd uses ttsl only inside of @example and friends), % or `code' (@kbd uses normal tty font always). \parseargdef\kbdinputstyle{% \def\txiarg{#1}% \ifx\txiarg\worddistinct \gdef\kbdexamplefont{\ttsl}\gdef\kbdfont{\ttsl}% \else\ifx\txiarg\wordexample \gdef\kbdexamplefont{\ttsl}\gdef\kbdfont{\tt}% \else\ifx\txiarg\wordcode \gdef\kbdexamplefont{\tt}\gdef\kbdfont{\tt}% \else \errhelp = \EMsimple \errmessage{Unknown @kbdinputstyle setting `\txiarg'}% \fi\fi\fi } \def\worddistinct{distinct} \def\wordexample{example} \def\wordcode{code} % Default is `distinct'. \kbdinputstyle distinct \def\xkey{\key} \def\kbdfoo#1#2#3\par{\def\one{#1}\def\three{#3}\def\threex{??}% \ifx\one\xkey\ifx\threex\three \key{#2}% \else{\tclose{\kbdfont\setupmarkupstyle{kbd}\look}}\fi \else{\tclose{\kbdfont\setupmarkupstyle{kbd}\look}}\fi} % For @indicateurl, @env, @command quotes seem unnecessary, so use \code. \let\indicateurl=\code \let\env=\code \let\command=\code % @clicksequence{File @click{} Open ...} \def\clicksequence#1{\begingroup #1\endgroup} % @clickstyle @arrow (by default) \parseargdef\clickstyle{\def\click{#1}} \def\click{\arrow} % Typeset a dimension, e.g., `in' or `pt'. The only reason for the % argument is to make the input look right: @dmn{pt} instead of @dmn{}pt. % \def\dmn#1{\thinspace #1} % @l was never documented to mean ``switch to the Lisp font'', % and it is not used as such in any manual I can find. We need it for % Polish suppressed-l. --karl, 22sep96. %\def\l#1{{\li #1}\null} % @acronym for "FBI", "NATO", and the like. % We print this one point size smaller, since it's intended for % all-uppercase. % \def\acronym#1{\doacronym #1,,\finish} \def\doacronym#1,#2,#3\finish{% {\selectfonts\lsize #1}% \def\temp{#2}% \ifx\temp\empty \else \space ({\unsepspaces \ignorespaces \temp \unskip})% \fi \null % reset \spacefactor=1000 } % @abbr for "Comput. J." and the like. % No font change, but don't do end-of-sentence spacing. % \def\abbr#1{\doabbr #1,,\finish} \def\doabbr#1,#2,#3\finish{% {\plainfrenchspacing #1}% \def\temp{#2}% \ifx\temp\empty \else \space ({\unsepspaces \ignorespaces \temp \unskip})% \fi \null % reset \spacefactor=1000 } % @asis just yields its argument. Used with @table, for example. % \def\asis#1{#1} % @math outputs its argument in math mode. % % One complication: _ usually means subscripts, but it could also mean % an actual _ character, as in @math{@var{some_variable} + 1}. So make % _ active, and distinguish by seeing if the current family is \slfam, % which is what @var uses. { \catcode`\_ = \active \gdef\mathunderscore{% \catcode`\_=\active \def_{\ifnum\fam=\slfam \_\else\sb\fi}% } } % Another complication: we want \\ (and @\) to output a math (or tt) \. % FYI, plain.tex uses \\ as a temporary control sequence (for no % particular reason), but this is not advertised and we don't care. % % The \mathchar is class=0=ordinary, family=7=ttfam, position=5C=\. \def\mathbackslash{\ifnum\fam=\ttfam \mathchar"075C \else\backslash \fi} % \def\math{% \tex \mathunderscore \let\\ = \mathbackslash \mathactive % make the texinfo accent commands work in math mode \let\"=\ddot \let\'=\acute \let\==\bar \let\^=\hat \let\`=\grave \let\u=\breve \let\v=\check \let\~=\tilde \let\dotaccent=\dot $\finishmath } \def\finishmath#1{#1$\endgroup} % Close the group opened by \tex. % Some active characters (such as <) are spaced differently in math. % We have to reset their definitions in case the @math was an argument % to a command which sets the catcodes (such as @item or @section). % { \catcode`^ = \active \catcode`< = \active \catcode`> = \active \catcode`+ = \active \catcode`' = \active \gdef\mathactive{% \let^ = \ptexhat \let< = \ptexless \let> = \ptexgtr \let+ = \ptexplus \let' = \ptexquoteright } } % @inlinefmt{FMTNAME,PROCESSED-TEXT} and @inlineraw{FMTNAME,RAW-TEXT}. % Ignore unless FMTNAME == tex; then it is like @iftex and @tex, % except specified as a normal braced arg, so no newlines to worry about. % \def\outfmtnametex{tex} % \long\def\inlinefmt#1{\doinlinefmt #1,\finish} \long\def\doinlinefmt#1,#2,\finish{% \def\inlinefmtname{#1}% \ifx\inlinefmtname\outfmtnametex \ignorespaces #2\fi } % For raw, must switch into @tex before parsing the argument, to avoid % setting catcodes prematurely. Doing it this way means that, for % example, @inlineraw{html, foo{bar} gets a parse error instead of being % ignored. But this isn't important because if people want a literal % *right* brace they would have to use a command anyway, so they may as % well use a command to get a left brace too. We could re-use the % delimiter character idea from \verb, but it seems like overkill. % \long\def\inlineraw{\tex \doinlineraw} \long\def\doinlineraw#1{\doinlinerawtwo #1,\finish} \def\doinlinerawtwo#1,#2,\finish{% \def\inlinerawname{#1}% \ifx\inlinerawname\outfmtnametex \ignorespaces #2\fi \endgroup % close group opened by \tex. } \message{glyphs,} % and logos. % @@ prints an @, as does @atchar{}. \def\@{\char64 } \let\atchar=\@ % @{ @} @lbracechar{} @rbracechar{} all generate brace characters. % Unless we're in typewriter, use \ecfont because the CM text fonts do % not have braces, and we don't want to switch into math. \def\mylbrace{{\ifmonospace\else\ecfont\fi \char123}} \def\myrbrace{{\ifmonospace\else\ecfont\fi \char125}} \let\{=\mylbrace \let\lbracechar=\{ \let\}=\myrbrace \let\rbracechar=\} \begingroup % Definitions to produce \{ and \} commands for indices, % and @{ and @} for the aux/toc files. \catcode`\{ = \other \catcode`\} = \other \catcode`\[ = 1 \catcode`\] = 2 \catcode`\! = 0 \catcode`\\ = \other !gdef!lbracecmd[\{]% !gdef!rbracecmd[\}]% !gdef!lbraceatcmd[@{]% !gdef!rbraceatcmd[@}]% !endgroup % @comma{} to avoid , parsing problems. \let\comma = , % Accents: @, @dotaccent @ringaccent @ubaraccent @udotaccent % Others are defined by plain TeX: @` @' @" @^ @~ @= @u @v @H. \let\, = \ptexc \let\dotaccent = \ptexdot \def\ringaccent#1{{\accent23 #1}} \let\tieaccent = \ptext \let\ubaraccent = \ptexb \let\udotaccent = \d % Other special characters: @questiondown @exclamdown @ordf @ordm % Plain TeX defines: @AA @AE @O @OE @L (plus lowercase versions) @ss. \def\questiondown{?`} \def\exclamdown{!`} \def\ordf{\leavevmode\raise1ex\hbox{\selectfonts\lllsize \underbar{a}}} \def\ordm{\leavevmode\raise1ex\hbox{\selectfonts\lllsize \underbar{o}}} % Dotless i and dotless j, used for accents. \def\imacro{i} \def\jmacro{j} \def\dotless#1{% \def\temp{#1}% \ifx\temp\imacro \ifmmode\imath \else\ptexi \fi \else\ifx\temp\jmacro \ifmmode\jmath \else\j \fi \else \errmessage{@dotless can be used only with i or j}% \fi\fi } % The \TeX{} logo, as in plain, but resetting the spacing so that a % period following counts as ending a sentence. (Idea found in latex.) % \edef\TeX{\TeX \spacefactor=1000 } % @LaTeX{} logo. Not quite the same results as the definition in % latex.ltx, since we use a different font for the raised A; it's most % convenient for us to use an explicitly smaller font, rather than using % the \scriptstyle font (since we don't reset \scriptstyle and % \scriptscriptstyle). % \def\LaTeX{% L\kern-.36em {\setbox0=\hbox{T}% \vbox to \ht0{\hbox{% \ifx\textnominalsize\xwordpt % for 10pt running text, \lllsize (8pt) is too small for the A in LaTeX. % Revert to plain's \scriptsize, which is 7pt. \count255=\the\fam $\fam\count255 \scriptstyle A$% \else % For 11pt, we can use our lllsize. \selectfonts\lllsize A% \fi }% \vss }}% \kern-.15em \TeX } % Some math mode symbols. \def\bullet{$\ptexbullet$} \def\geq{\ifmmode \ge\else $\ge$\fi} \def\leq{\ifmmode \le\else $\le$\fi} \def\minus{\ifmmode -\else $-$\fi} % @dots{} outputs an ellipsis using the current font. % We do .5em per period so that it has the same spacing in the cm % typewriter fonts as three actual period characters; on the other hand, % in other typewriter fonts three periods are wider than 1.5em. So do % whichever is larger. % \def\dots{% \leavevmode \setbox0=\hbox{...}% get width of three periods \ifdim\wd0 > 1.5em \dimen0 = \wd0 \else \dimen0 = 1.5em \fi \hbox to \dimen0{% \hskip 0pt plus.25fil .\hskip 0pt plus1fil .\hskip 0pt plus1fil .\hskip 0pt plus.5fil }% } % @enddots{} is an end-of-sentence ellipsis. % \def\enddots{% \dots \spacefactor=\endofsentencespacefactor } % @point{}, @result{}, @expansion{}, @print{}, @equiv{}. % % Since these characters are used in examples, they should be an even number of % \tt widths. Each \tt character is 1en, so two makes it 1em. % \def\point{$\star$} \def\arrow{\leavevmode\raise.05ex\hbox to 1em{\hfil$\rightarrow$\hfil}} \def\result{\leavevmode\raise.05ex\hbox to 1em{\hfil$\Rightarrow$\hfil}} \def\expansion{\leavevmode\hbox to 1em{\hfil$\mapsto$\hfil}} \def\print{\leavevmode\lower.1ex\hbox to 1em{\hfil$\dashv$\hfil}} \def\equiv{\leavevmode\hbox to 1em{\hfil$\ptexequiv$\hfil}} % The @error{} command. % Adapted from the TeXbook's \boxit. % \newbox\errorbox % {\tentt \global\dimen0 = 3em}% Width of the box. \dimen2 = .55pt % Thickness of rules % The text. (`r' is open on the right, `e' somewhat less so on the left.) \setbox0 = \hbox{\kern-.75pt \reducedsf \putworderror\kern-1.5pt} % \setbox\errorbox=\hbox to \dimen0{\hfil \hsize = \dimen0 \advance\hsize by -5.8pt % Space to left+right. \advance\hsize by -2\dimen2 % Rules. \vbox{% \hrule height\dimen2 \hbox{\vrule width\dimen2 \kern3pt % Space to left of text. \vtop{\kern2.4pt \box0 \kern2.4pt}% Space above/below. \kern3pt\vrule width\dimen2}% Space to right. \hrule height\dimen2} \hfil} % \def\error{\leavevmode\lower.7ex\copy\errorbox} % @pounds{} is a sterling sign, which Knuth put in the CM italic font. % \def\pounds{{\it\$}} % @euro{} comes from a separate font, depending on the current style. % We use the free feym* fonts from the eurosym package by Henrik % Theiling, which support regular, slanted, bold and bold slanted (and % "outlined" (blackboard board, sort of) versions, which we don't need). % It is available from http://www.ctan.org/tex-archive/fonts/eurosym. % % Although only regular is the truly official Euro symbol, we ignore % that. The Euro is designed to be slightly taller than the regular % font height. % % feymr - regular % feymo - slanted % feybr - bold % feybo - bold slanted % % There is no good (free) typewriter version, to my knowledge. % A feymr10 euro is ~7.3pt wide, while a normal cmtt10 char is ~5.25pt wide. % Hmm. % % Also doesn't work in math. Do we need to do math with euro symbols? % Hope not. % % \def\euro{{\eurofont e}} \def\eurofont{% % We set the font at each command, rather than predefining it in % \textfonts and the other font-switching commands, so that % installations which never need the symbol don't have to have the % font installed. % % There is only one designed size (nominal 10pt), so we always scale % that to the current nominal size. % % By the way, simply using "at 1em" works for cmr10 and the like, but % does not work for cmbx10 and other extended/shrunken fonts. % \def\eurosize{\csname\curfontsize nominalsize\endcsname}% % \ifx\curfontstyle\bfstylename % bold: \font\thiseurofont = \ifusingit{feybo10}{feybr10} at \eurosize \else % regular: \font\thiseurofont = \ifusingit{feymo10}{feymr10} at \eurosize \fi \thiseurofont } % Glyphs from the EC fonts. We don't use \let for the aliases, because % sometimes we redefine the original macro, and the alias should reflect % the redefinition. % % Use LaTeX names for the Icelandic letters. \def\DH{{\ecfont \char"D0}} % Eth \def\dh{{\ecfont \char"F0}} % eth \def\TH{{\ecfont \char"DE}} % Thorn \def\th{{\ecfont \char"FE}} % thorn % \def\guillemetleft{{\ecfont \char"13}} \def\guillemotleft{\guillemetleft} \def\guillemetright{{\ecfont \char"14}} \def\guillemotright{\guillemetright} \def\guilsinglleft{{\ecfont \char"0E}} \def\guilsinglright{{\ecfont \char"0F}} \def\quotedblbase{{\ecfont \char"12}} \def\quotesinglbase{{\ecfont \char"0D}} % % This positioning is not perfect (see the ogonek LaTeX package), but % we have the precomposed glyphs for the most common cases. We put the % tests to use those glyphs in the single \ogonek macro so we have fewer % dummy definitions to worry about for index entries, etc. % % ogonek is also used with other letters in Lithuanian (IOU), but using % the precomposed glyphs for those is not so easy since they aren't in % the same EC font. \def\ogonek#1{{% \def\temp{#1}% \ifx\temp\macrocharA\Aogonek \else\ifx\temp\macrochara\aogonek \else\ifx\temp\macrocharE\Eogonek \else\ifx\temp\macrochare\eogonek \else \ecfont \setbox0=\hbox{#1}% \ifdim\ht0=1ex\accent"0C #1% \else\ooalign{\unhbox0\crcr\hidewidth\char"0C \hidewidth}% \fi \fi\fi\fi\fi }% } \def\Aogonek{{\ecfont \char"81}}\def\macrocharA{A} \def\aogonek{{\ecfont \char"A1}}\def\macrochara{a} \def\Eogonek{{\ecfont \char"86}}\def\macrocharE{E} \def\eogonek{{\ecfont \char"A6}}\def\macrochare{e} % % Use the ec* fonts (cm-super in outline format) for non-CM glyphs. \def\ecfont{% % We can't distinguish serif/sans and italic/slanted, but this % is used for crude hacks anyway (like adding French and German % quotes to documents typeset with CM, where we lose kerning), so % hopefully nobody will notice/care. \edef\ecsize{\csname\curfontsize ecsize\endcsname}% \edef\nominalsize{\csname\curfontsize nominalsize\endcsname}% \ifx\curfontstyle\bfstylename % bold: \font\thisecfont = ecb\ifusingit{i}{x}\ecsize \space at \nominalsize \else % regular: \font\thisecfont = ec\ifusingit{ti}{rm}\ecsize \space at \nominalsize \fi \thisecfont } % @registeredsymbol - R in a circle. The font for the R should really % be smaller yet, but lllsize is the best we can do for now. % Adapted from the plain.tex definition of \copyright. % \def\registeredsymbol{% $^{{\ooalign{\hfil\raise.07ex\hbox{\selectfonts\lllsize R}% \hfil\crcr\Orb}}% }$% } % @textdegree - the normal degrees sign. % \def\textdegree{$^\circ$} % Laurent Siebenmann reports \Orb undefined with: % Textures 1.7.7 (preloaded format=plain 93.10.14) (68K) 16 APR 2004 02:38 % so we'll define it if necessary. % \ifx\Orb\thisisundefined \def\Orb{\mathhexbox20D} \fi % Quotes. \chardef\quotedblleft="5C \chardef\quotedblright=`\" \chardef\quoteleft=`\` \chardef\quoteright=`\' \message{page headings,} \newskip\titlepagetopglue \titlepagetopglue = 1.5in \newskip\titlepagebottomglue \titlepagebottomglue = 2pc % First the title page. Must do @settitle before @titlepage. \newif\ifseenauthor \newif\iffinishedtitlepage % Do an implicit @contents or @shortcontents after @end titlepage if the % user says @setcontentsaftertitlepage or @setshortcontentsaftertitlepage. % \newif\ifsetcontentsaftertitlepage \let\setcontentsaftertitlepage = \setcontentsaftertitlepagetrue \newif\ifsetshortcontentsaftertitlepage \let\setshortcontentsaftertitlepage = \setshortcontentsaftertitlepagetrue \parseargdef\shorttitlepage{% \begingroup \hbox{}\vskip 1.5in \chaprm \centerline{#1}% \endgroup\page\hbox{}\page} \envdef\titlepage{% % Open one extra group, as we want to close it in the middle of \Etitlepage. \begingroup \parindent=0pt \textfonts % Leave some space at the very top of the page. \vglue\titlepagetopglue % No rule at page bottom unless we print one at the top with @title. \finishedtitlepagetrue % % Most title ``pages'' are actually two pages long, with space % at the top of the second. We don't want the ragged left on the second. \let\oldpage = \page \def\page{% \iffinishedtitlepage\else \finishtitlepage \fi \let\page = \oldpage \page \null }% } \def\Etitlepage{% \iffinishedtitlepage\else \finishtitlepage \fi % It is important to do the page break before ending the group, % because the headline and footline are only empty inside the group. % If we use the new definition of \page, we always get a blank page % after the title page, which we certainly don't want. \oldpage \endgroup % % Need this before the \...aftertitlepage checks so that if they are % in effect the toc pages will come out with page numbers. \HEADINGSon % % If they want short, they certainly want long too. \ifsetshortcontentsaftertitlepage \shortcontents \contents \global\let\shortcontents = \relax \global\let\contents = \relax \fi % \ifsetcontentsaftertitlepage \contents \global\let\contents = \relax \global\let\shortcontents = \relax \fi } \def\finishtitlepage{% \vskip4pt \hrule height 2pt width \hsize \vskip\titlepagebottomglue \finishedtitlepagetrue } % Macros to be used within @titlepage: \let\subtitlerm=\tenrm \def\subtitlefont{\subtitlerm \normalbaselineskip = 13pt \normalbaselines} \parseargdef\title{% \checkenv\titlepage \leftline{\titlefonts\rmisbold #1} % print a rule at the page bottom also. \finishedtitlepagefalse \vskip4pt \hrule height 4pt width \hsize \vskip4pt } \parseargdef\subtitle{% \checkenv\titlepage {\subtitlefont \rightline{#1}}% } % @author should come last, but may come many times. % It can also be used inside @quotation. % \parseargdef\author{% \def\temp{\quotation}% \ifx\thisenv\temp \def\quotationauthor{#1}% printed in \Equotation. \else \checkenv\titlepage \ifseenauthor\else \vskip 0pt plus 1filll \seenauthortrue \fi {\secfonts\rmisbold \leftline{#1}}% \fi } % Set up page headings and footings. \let\thispage=\folio \newtoks\evenheadline % headline on even pages \newtoks\oddheadline % headline on odd pages \newtoks\evenfootline % footline on even pages \newtoks\oddfootline % footline on odd pages % Now make TeX use those variables \headline={{\textfonts\rm \ifodd\pageno \the\oddheadline \else \the\evenheadline \fi}} \footline={{\textfonts\rm \ifodd\pageno \the\oddfootline \else \the\evenfootline \fi}\HEADINGShook} \let\HEADINGShook=\relax % Commands to set those variables. % For example, this is what @headings on does % @evenheading @thistitle|@thispage|@thischapter % @oddheading @thischapter|@thispage|@thistitle % @evenfooting @thisfile|| % @oddfooting ||@thisfile \def\evenheading{\parsearg\evenheadingxxx} \def\evenheadingxxx #1{\evenheadingyyy #1\|\|\|\|\finish} \def\evenheadingyyy #1\|#2\|#3\|#4\finish{% \global\evenheadline={\rlap{\centerline{#2}}\line{#1\hfil#3}}} \def\oddheading{\parsearg\oddheadingxxx} \def\oddheadingxxx #1{\oddheadingyyy #1\|\|\|\|\finish} \def\oddheadingyyy #1\|#2\|#3\|#4\finish{% \global\oddheadline={\rlap{\centerline{#2}}\line{#1\hfil#3}}} \parseargdef\everyheading{\oddheadingxxx{#1}\evenheadingxxx{#1}}% \def\evenfooting{\parsearg\evenfootingxxx} \def\evenfootingxxx #1{\evenfootingyyy #1\|\|\|\|\finish} \def\evenfootingyyy #1\|#2\|#3\|#4\finish{% \global\evenfootline={\rlap{\centerline{#2}}\line{#1\hfil#3}}} \def\oddfooting{\parsearg\oddfootingxxx} \def\oddfootingxxx #1{\oddfootingyyy #1\|\|\|\|\finish} \def\oddfootingyyy #1\|#2\|#3\|#4\finish{% \global\oddfootline = {\rlap{\centerline{#2}}\line{#1\hfil#3}}% % % Leave some space for the footline. Hopefully ok to assume % @evenfooting will not be used by itself. \global\advance\pageheight by -12pt \global\advance\vsize by -12pt } \parseargdef\everyfooting{\oddfootingxxx{#1}\evenfootingxxx{#1}} % @evenheadingmarks top \thischapter <- chapter at the top of a page % @evenheadingmarks bottom \thischapter <- chapter at the bottom of a page % % The same set of arguments for: % % @oddheadingmarks % @evenfootingmarks % @oddfootingmarks % @everyheadingmarks % @everyfootingmarks \def\evenheadingmarks{\headingmarks{even}{heading}} \def\oddheadingmarks{\headingmarks{odd}{heading}} \def\evenfootingmarks{\headingmarks{even}{footing}} \def\oddfootingmarks{\headingmarks{odd}{footing}} \def\everyheadingmarks#1 {\headingmarks{even}{heading}{#1} \headingmarks{odd}{heading}{#1} } \def\everyfootingmarks#1 {\headingmarks{even}{footing}{#1} \headingmarks{odd}{footing}{#1} } % #1 = even/odd, #2 = heading/footing, #3 = top/bottom. \def\headingmarks#1#2#3 {% \expandafter\let\expandafter\temp \csname get#3headingmarks\endcsname \global\expandafter\let\csname get#1#2marks\endcsname \temp } \everyheadingmarks bottom \everyfootingmarks bottom % @headings double turns headings on for double-sided printing. % @headings single turns headings on for single-sided printing. % @headings off turns them off. % @headings on same as @headings double, retained for compatibility. % @headings after turns on double-sided headings after this page. % @headings doubleafter turns on double-sided headings after this page. % @headings singleafter turns on single-sided headings after this page. % By default, they are off at the start of a document, % and turned `on' after @end titlepage. \def\headings #1 {\csname HEADINGS#1\endcsname} \def\headingsoff{% non-global headings elimination \evenheadline={\hfil}\evenfootline={\hfil}% \oddheadline={\hfil}\oddfootline={\hfil}% } \def\HEADINGSoff{{\globaldefs=1 \headingsoff}} % global setting \HEADINGSoff % it's the default % When we turn headings on, set the page number to 1. % For double-sided printing, put current file name in lower left corner, % chapter name on inside top of right hand pages, document % title on inside top of left hand pages, and page numbers on outside top % edge of all pages. \def\HEADINGSdouble{% \global\pageno=1 \global\evenfootline={\hfil} \global\oddfootline={\hfil} \global\evenheadline={\line{\folio\hfil\thistitle}} \global\oddheadline={\line{\thischapter\hfil\folio}} \global\let\contentsalignmacro = \chapoddpage } \let\contentsalignmacro = \chappager % For single-sided printing, chapter title goes across top left of page, % page number on top right. \def\HEADINGSsingle{% \global\pageno=1 \global\evenfootline={\hfil} \global\oddfootline={\hfil} \global\evenheadline={\line{\thischapter\hfil\folio}} \global\oddheadline={\line{\thischapter\hfil\folio}} \global\let\contentsalignmacro = \chappager } \def\HEADINGSon{\HEADINGSdouble} \def\HEADINGSafter{\let\HEADINGShook=\HEADINGSdoublex} \let\HEADINGSdoubleafter=\HEADINGSafter \def\HEADINGSdoublex{% \global\evenfootline={\hfil} \global\oddfootline={\hfil} \global\evenheadline={\line{\folio\hfil\thistitle}} \global\oddheadline={\line{\thischapter\hfil\folio}} \global\let\contentsalignmacro = \chapoddpage } \def\HEADINGSsingleafter{\let\HEADINGShook=\HEADINGSsinglex} \def\HEADINGSsinglex{% \global\evenfootline={\hfil} \global\oddfootline={\hfil} \global\evenheadline={\line{\thischapter\hfil\folio}} \global\oddheadline={\line{\thischapter\hfil\folio}} \global\let\contentsalignmacro = \chappager } % Subroutines used in generating headings % This produces Day Month Year style of output. % Only define if not already defined, in case a txi-??.tex file has set % up a different format (e.g., txi-cs.tex does this). \ifx\today\thisisundefined \def\today{% \number\day\space \ifcase\month \or\putwordMJan\or\putwordMFeb\or\putwordMMar\or\putwordMApr \or\putwordMMay\or\putwordMJun\or\putwordMJul\or\putwordMAug \or\putwordMSep\or\putwordMOct\or\putwordMNov\or\putwordMDec \fi \space\number\year} \fi % @settitle line... specifies the title of the document, for headings. % It generates no output of its own. \def\thistitle{\putwordNoTitle} \def\settitle{\parsearg{\gdef\thistitle}} \message{tables,} % Tables -- @table, @ftable, @vtable, @item(x). % default indentation of table text \newdimen\tableindent \tableindent=.8in % default indentation of @itemize and @enumerate text \newdimen\itemindent \itemindent=.3in % margin between end of table item and start of table text. \newdimen\itemmargin \itemmargin=.1in % used internally for \itemindent minus \itemmargin \newdimen\itemmax % Note @table, @ftable, and @vtable define @item, @itemx, etc., with % these defs. % They also define \itemindex % to index the item name in whatever manner is desired (perhaps none). \newif\ifitemxneedsnegativevskip \def\itemxpar{\par\ifitemxneedsnegativevskip\nobreak\vskip-\parskip\nobreak\fi} \def\internalBitem{\smallbreak \parsearg\itemzzz} \def\internalBitemx{\itemxpar \parsearg\itemzzz} \def\itemzzz #1{\begingroup % \advance\hsize by -\rightskip \advance\hsize by -\tableindent \setbox0=\hbox{\itemindicate{#1}}% \itemindex{#1}% \nobreak % This prevents a break before @itemx. % % If the item text does not fit in the space we have, put it on a line % by itself, and do not allow a page break either before or after that % line. We do not start a paragraph here because then if the next % command is, e.g., @kindex, the whatsit would get put into the % horizontal list on a line by itself, resulting in extra blank space. \ifdim \wd0>\itemmax % % Make this a paragraph so we get the \parskip glue and wrapping, % but leave it ragged-right. \begingroup \advance\leftskip by-\tableindent \advance\hsize by\tableindent \advance\rightskip by0pt plus1fil\relax \leavevmode\unhbox0\par \endgroup % % We're going to be starting a paragraph, but we don't want the % \parskip glue -- logically it's part of the @item we just started. \nobreak \vskip-\parskip % % Stop a page break at the \parskip glue coming up. However, if % what follows is an environment such as @example, there will be no % \parskip glue; then the negative vskip we just inserted would % cause the example and the item to crash together. So we use this % bizarre value of 10001 as a signal to \aboveenvbreak to insert % \parskip glue after all. Section titles are handled this way also. % \penalty 10001 \endgroup \itemxneedsnegativevskipfalse \else % The item text fits into the space. Start a paragraph, so that the % following text (if any) will end up on the same line. \noindent % Do this with kerns and \unhbox so that if there is a footnote in % the item text, it can migrate to the main vertical list and % eventually be printed. \nobreak\kern-\tableindent \dimen0 = \itemmax \advance\dimen0 by \itemmargin \advance\dimen0 by -\wd0 \unhbox0 \nobreak\kern\dimen0 \endgroup \itemxneedsnegativevskiptrue \fi } \def\item{\errmessage{@item while not in a list environment}} \def\itemx{\errmessage{@itemx while not in a list environment}} % @table, @ftable, @vtable. \envdef\table{% \let\itemindex\gobble \tablecheck{table}% } \envdef\ftable{% \def\itemindex ##1{\doind {fn}{\code{##1}}}% \tablecheck{ftable}% } \envdef\vtable{% \def\itemindex ##1{\doind {vr}{\code{##1}}}% \tablecheck{vtable}% } \def\tablecheck#1{% \ifnum \the\catcode`\^^M=\active \endgroup \errmessage{This command won't work in this context; perhaps the problem is that we are \inenvironment\thisenv}% \def\next{\doignore{#1}}% \else \let\next\tablex \fi \next } \def\tablex#1{% \def\itemindicate{#1}% \parsearg\tabley } \def\tabley#1{% {% \makevalueexpandable \edef\temp{\noexpand\tablez #1\space\space\space}% \expandafter }\temp \endtablez } \def\tablez #1 #2 #3 #4\endtablez{% \aboveenvbreak \ifnum 0#1>0 \advance \leftskip by #1\mil \fi \ifnum 0#2>0 \tableindent=#2\mil \fi \ifnum 0#3>0 \advance \rightskip by #3\mil \fi \itemmax=\tableindent \advance \itemmax by -\itemmargin \advance \leftskip by \tableindent \exdentamount=\tableindent \parindent = 0pt \parskip = \smallskipamount \ifdim \parskip=0pt \parskip=2pt \fi \let\item = \internalBitem \let\itemx = \internalBitemx } \def\Etable{\endgraf\afterenvbreak} \let\Eftable\Etable \let\Evtable\Etable \let\Eitemize\Etable \let\Eenumerate\Etable % This is the counter used by @enumerate, which is really @itemize \newcount \itemno \envdef\itemize{\parsearg\doitemize} \def\doitemize#1{% \aboveenvbreak \itemmax=\itemindent \advance\itemmax by -\itemmargin \advance\leftskip by \itemindent \exdentamount=\itemindent \parindent=0pt \parskip=\smallskipamount \ifdim\parskip=0pt \parskip=2pt \fi % % Try typesetting the item mark that if the document erroneously says % something like @itemize @samp (intending @table), there's an error % right away at the @itemize. It's not the best error message in the % world, but it's better than leaving it to the @item. This means if % the user wants an empty mark, they have to say @w{} not just @w. \def\itemcontents{#1}% \setbox0 = \hbox{\itemcontents}% % % @itemize with no arg is equivalent to @itemize @bullet. \ifx\itemcontents\empty\def\itemcontents{\bullet}\fi % \let\item=\itemizeitem } % Definition of @item while inside @itemize and @enumerate. % \def\itemizeitem{% \advance\itemno by 1 % for enumerations {\let\par=\endgraf \smallbreak}% reasonable place to break {% % If the document has an @itemize directly after a section title, a % \nobreak will be last on the list, and \sectionheading will have % done a \vskip-\parskip. In that case, we don't want to zero % parskip, or the item text will crash with the heading. On the % other hand, when there is normal text preceding the item (as there % usually is), we do want to zero parskip, or there would be too much % space. In that case, we won't have a \nobreak before. At least % that's the theory. \ifnum\lastpenalty<10000 \parskip=0in \fi \noindent \hbox to 0pt{\hss \itemcontents \kern\itemmargin}% % \vadjust{\penalty 1200}}% not good to break after first line of item. \flushcr } % \splitoff TOKENS\endmark defines \first to be the first token in % TOKENS, and \rest to be the remainder. % \def\splitoff#1#2\endmark{\def\first{#1}\def\rest{#2}}% % Allow an optional argument of an uppercase letter, lowercase letter, % or number, to specify the first label in the enumerated list. No % argument is the same as `1'. % \envparseargdef\enumerate{\enumeratey #1 \endenumeratey} \def\enumeratey #1 #2\endenumeratey{% % If we were given no argument, pretend we were given `1'. \def\thearg{#1}% \ifx\thearg\empty \def\thearg{1}\fi % % Detect if the argument is a single token. If so, it might be a % letter. Otherwise, the only valid thing it can be is a number. % (We will always have one token, because of the test we just made. % This is a good thing, since \splitoff doesn't work given nothing at % all -- the first parameter is undelimited.) \expandafter\splitoff\thearg\endmark \ifx\rest\empty % Only one token in the argument. It could still be anything. % A ``lowercase letter'' is one whose \lccode is nonzero. % An ``uppercase letter'' is one whose \lccode is both nonzero, and % not equal to itself. % Otherwise, we assume it's a number. % % We need the \relax at the end of the \ifnum lines to stop TeX from % continuing to look for a . % \ifnum\lccode\expandafter`\thearg=0\relax \numericenumerate % a number (we hope) \else % It's a letter. \ifnum\lccode\expandafter`\thearg=\expandafter`\thearg\relax \lowercaseenumerate % lowercase letter \else \uppercaseenumerate % uppercase letter \fi \fi \else % Multiple tokens in the argument. We hope it's a number. \numericenumerate \fi } % An @enumerate whose labels are integers. The starting integer is % given in \thearg. % \def\numericenumerate{% \itemno = \thearg \startenumeration{\the\itemno}% } % The starting (lowercase) letter is in \thearg. \def\lowercaseenumerate{% \itemno = \expandafter`\thearg \startenumeration{% % Be sure we're not beyond the end of the alphabet. \ifnum\itemno=0 \errmessage{No more lowercase letters in @enumerate; get a bigger alphabet}% \fi \char\lccode\itemno }% } % The starting (uppercase) letter is in \thearg. \def\uppercaseenumerate{% \itemno = \expandafter`\thearg \startenumeration{% % Be sure we're not beyond the end of the alphabet. \ifnum\itemno=0 \errmessage{No more uppercase letters in @enumerate; get a bigger alphabet} \fi \char\uccode\itemno }% } % Call \doitemize, adding a period to the first argument and supplying the % common last two arguments. Also subtract one from the initial value in % \itemno, since @item increments \itemno. % \def\startenumeration#1{% \advance\itemno by -1 \doitemize{#1.}\flushcr } % @alphaenumerate and @capsenumerate are abbreviations for giving an arg % to @enumerate. % \def\alphaenumerate{\enumerate{a}} \def\capsenumerate{\enumerate{A}} \def\Ealphaenumerate{\Eenumerate} \def\Ecapsenumerate{\Eenumerate} % @multitable macros % Amy Hendrickson, 8/18/94, 3/6/96 % % @multitable ... @end multitable will make as many columns as desired. % Contents of each column will wrap at width given in preamble. Width % can be specified either with sample text given in a template line, % or in percent of \hsize, the current width of text on page. % Table can continue over pages but will only break between lines. % To make preamble: % % Either define widths of columns in terms of percent of \hsize: % @multitable @columnfractions .25 .3 .45 % @item ... % % Numbers following @columnfractions are the percent of the total % current hsize to be used for each column. You may use as many % columns as desired. % Or use a template: % @multitable {Column 1 template} {Column 2 template} {Column 3 template} % @item ... % using the widest term desired in each column. % Each new table line starts with @item, each subsequent new column % starts with @tab. Empty columns may be produced by supplying @tab's % with nothing between them for as many times as empty columns are needed, % ie, @tab@tab@tab will produce two empty columns. % @item, @tab do not need to be on their own lines, but it will not hurt % if they are. % Sample multitable: % @multitable {Column 1 template} {Column 2 template} {Column 3 template} % @item first col stuff @tab second col stuff @tab third col % @item % first col stuff % @tab % second col stuff % @tab % third col % @item first col stuff @tab second col stuff % @tab Many paragraphs of text may be used in any column. % % They will wrap at the width determined by the template. % @item@tab@tab This will be in third column. % @end multitable % Default dimensions may be reset by user. % @multitableparskip is vertical space between paragraphs in table. % @multitableparindent is paragraph indent in table. % @multitablecolmargin is horizontal space to be left between columns. % @multitablelinespace is space to leave between table items, baseline % to baseline. % 0pt means it depends on current normal line spacing. % \newskip\multitableparskip \newskip\multitableparindent \newdimen\multitablecolspace \newskip\multitablelinespace \multitableparskip=0pt \multitableparindent=6pt \multitablecolspace=12pt \multitablelinespace=0pt % Macros used to set up halign preamble: % \let\endsetuptable\relax \def\xendsetuptable{\endsetuptable} \let\columnfractions\relax \def\xcolumnfractions{\columnfractions} \newif\ifsetpercent % #1 is the @columnfraction, usually a decimal number like .5, but might % be just 1. We just use it, whatever it is. % \def\pickupwholefraction#1 {% \global\advance\colcount by 1 \expandafter\xdef\csname col\the\colcount\endcsname{#1\hsize}% \setuptable } \newcount\colcount \def\setuptable#1{% \def\firstarg{#1}% \ifx\firstarg\xendsetuptable \let\go = \relax \else \ifx\firstarg\xcolumnfractions \global\setpercenttrue \else \ifsetpercent \let\go\pickupwholefraction \else \global\advance\colcount by 1 \setbox0=\hbox{#1\unskip\space}% Add a normal word space as a % separator; typically that is always in the input, anyway. \expandafter\xdef\csname col\the\colcount\endcsname{\the\wd0}% \fi \fi \ifx\go\pickupwholefraction % Put the argument back for the \pickupwholefraction call, so % we'll always have a period there to be parsed. \def\go{\pickupwholefraction#1}% \else \let\go = \setuptable \fi% \fi \go } % multitable-only commands. % % @headitem starts a heading row, which we typeset in bold. % Assignments have to be global since we are inside the implicit group % of an alignment entry. \everycr resets \everytab so we don't have to % undo it ourselves. \def\headitemfont{\b}% for people to use in the template row; not changeable \def\headitem{% \checkenv\multitable \crcr \global\everytab={\bf}% can't use \headitemfont since the parsing differs \the\everytab % for the first item }% % % A \tab used to include \hskip1sp. But then the space in a template % line is not enough. That is bad. So let's go back to just `&' until % we again encounter the problem the 1sp was intended to solve. % --karl, nathan@acm.org, 20apr99. \def\tab{\checkenv\multitable &\the\everytab}% % @multitable ... @end multitable definitions: % \newtoks\everytab % insert after every tab. % \envdef\multitable{% \vskip\parskip \startsavinginserts % % @item within a multitable starts a normal row. % We use \def instead of \let so that if one of the multitable entries % contains an @itemize, we don't choke on the \item (seen as \crcr aka % \endtemplate) expanding \doitemize. \def\item{\crcr}% % \tolerance=9500 \hbadness=9500 \setmultitablespacing \parskip=\multitableparskip \parindent=\multitableparindent \overfullrule=0pt \global\colcount=0 % \everycr = {% \noalign{% \global\everytab={}% \global\colcount=0 % Reset the column counter. % Check for saved footnotes, etc. \checkinserts % Keeps underfull box messages off when table breaks over pages. %\filbreak % Maybe so, but it also creates really weird page breaks when the % table breaks over pages. Wouldn't \vfil be better? Wait until the % problem manifests itself, so it can be fixed for real --karl. }% }% % \parsearg\domultitable } \def\domultitable#1{% % To parse everything between @multitable and @item: \setuptable#1 \endsetuptable % % This preamble sets up a generic column definition, which will % be used as many times as user calls for columns. % \vtop will set a single line and will also let text wrap and % continue for many paragraphs if desired. \halign\bgroup &% \global\advance\colcount by 1 \multistrut \vtop{% % Use the current \colcount to find the correct column width: \hsize=\expandafter\csname col\the\colcount\endcsname % % In order to keep entries from bumping into each other % we will add a \leftskip of \multitablecolspace to all columns after % the first one. % % If a template has been used, we will add \multitablecolspace % to the width of each template entry. % % If the user has set preamble in terms of percent of \hsize we will % use that dimension as the width of the column, and the \leftskip % will keep entries from bumping into each other. Table will start at % left margin and final column will justify at right margin. % % Make sure we don't inherit \rightskip from the outer environment. \rightskip=0pt \ifnum\colcount=1 % The first column will be indented with the surrounding text. \advance\hsize by\leftskip \else \ifsetpercent \else % If user has not set preamble in terms of percent of \hsize % we will advance \hsize by \multitablecolspace. \advance\hsize by \multitablecolspace \fi % In either case we will make \leftskip=\multitablecolspace: \leftskip=\multitablecolspace \fi % Ignoring space at the beginning and end avoids an occasional spurious % blank line, when TeX decides to break the line at the space before the % box from the multistrut, so the strut ends up on a line by itself. % For example: % @multitable @columnfractions .11 .89 % @item @code{#} % @tab Legal holiday which is valid in major parts of the whole country. % Is automatically provided with highlighting sequences respectively % marking characters. \noindent\ignorespaces##\unskip\multistrut }\cr } \def\Emultitable{% \crcr \egroup % end the \halign \global\setpercentfalse } \def\setmultitablespacing{% \def\multistrut{\strut}% just use the standard line spacing % % Compute \multitablelinespace (if not defined by user) for use in % \multitableparskip calculation. We used define \multistrut based on % this, but (ironically) that caused the spacing to be off. % See bug-texinfo report from Werner Lemberg, 31 Oct 2004 12:52:20 +0100. \ifdim\multitablelinespace=0pt \setbox0=\vbox{X}\global\multitablelinespace=\the\baselineskip \global\advance\multitablelinespace by-\ht0 \fi % Test to see if parskip is larger than space between lines of % table. If not, do nothing. % If so, set to same dimension as multitablelinespace. \ifdim\multitableparskip>\multitablelinespace \global\multitableparskip=\multitablelinespace \global\advance\multitableparskip-7pt % to keep parskip somewhat smaller % than skip between lines in the table. \fi% \ifdim\multitableparskip=0pt \global\multitableparskip=\multitablelinespace \global\advance\multitableparskip-7pt % to keep parskip somewhat smaller % than skip between lines in the table. \fi} \message{conditionals,} % @iftex, @ifnotdocbook, @ifnothtml, @ifnotinfo, @ifnotplaintext, % @ifnotxml always succeed. They currently do nothing; we don't % attempt to check whether the conditionals are properly nested. But we % have to remember that they are conditionals, so that @end doesn't % attempt to close an environment group. % \def\makecond#1{% \expandafter\let\csname #1\endcsname = \relax \expandafter\let\csname iscond.#1\endcsname = 1 } \makecond{iftex} \makecond{ifnotdocbook} \makecond{ifnothtml} \makecond{ifnotinfo} \makecond{ifnotplaintext} \makecond{ifnotxml} % Ignore @ignore, @ifhtml, @ifinfo, and the like. % \def\direntry{\doignore{direntry}} \def\documentdescription{\doignore{documentdescription}} \def\docbook{\doignore{docbook}} \def\html{\doignore{html}} \def\ifdocbook{\doignore{ifdocbook}} \def\ifhtml{\doignore{ifhtml}} \def\ifinfo{\doignore{ifinfo}} \def\ifnottex{\doignore{ifnottex}} \def\ifplaintext{\doignore{ifplaintext}} \def\ifxml{\doignore{ifxml}} \def\ignore{\doignore{ignore}} \def\menu{\doignore{menu}} \def\xml{\doignore{xml}} % Ignore text until a line `@end #1', keeping track of nested conditionals. % % A count to remember the depth of nesting. \newcount\doignorecount \def\doignore#1{\begingroup % Scan in ``verbatim'' mode: \obeylines \catcode`\@ = \other \catcode`\{ = \other \catcode`\} = \other % % Make sure that spaces turn into tokens that match what \doignoretext wants. \spaceisspace % % Count number of #1's that we've seen. \doignorecount = 0 % % Swallow text until we reach the matching `@end #1'. \dodoignore{#1}% } { \catcode`_=11 % We want to use \_STOP_ which cannot appear in texinfo source. \obeylines % % \gdef\dodoignore#1{% % #1 contains the command name as a string, e.g., `ifinfo'. % % Define a command to find the next `@end #1'. \long\def\doignoretext##1^^M@end #1{% \doignoretextyyy##1^^M@#1\_STOP_}% % % And this command to find another #1 command, at the beginning of a % line. (Otherwise, we would consider a line `@c @ifset', for % example, to count as an @ifset for nesting.) \long\def\doignoretextyyy##1^^M@#1##2\_STOP_{\doignoreyyy{##2}\_STOP_}% % % And now expand that command. \doignoretext ^^M% }% } \def\doignoreyyy#1{% \def\temp{#1}% \ifx\temp\empty % Nothing found. \let\next\doignoretextzzz \else % Found a nested condition, ... \advance\doignorecount by 1 \let\next\doignoretextyyy % ..., look for another. % If we're here, #1 ends with ^^M\ifinfo (for example). \fi \next #1% the token \_STOP_ is present just after this macro. } % We have to swallow the remaining "\_STOP_". % \def\doignoretextzzz#1{% \ifnum\doignorecount = 0 % We have just found the outermost @end. \let\next\enddoignore \else % Still inside a nested condition. \advance\doignorecount by -1 \let\next\doignoretext % Look for the next @end. \fi \next } % Finish off ignored text. { \obeylines% % Ignore anything after the last `@end #1'; this matters in verbatim % environments, where otherwise the newline after an ignored conditional % would result in a blank line in the output. \gdef\enddoignore#1^^M{\endgroup\ignorespaces}% } % @set VAR sets the variable VAR to an empty value. % @set VAR REST-OF-LINE sets VAR to the value REST-OF-LINE. % % Since we want to separate VAR from REST-OF-LINE (which might be % empty), we can't just use \parsearg; we have to insert a space of our % own to delimit the rest of the line, and then take it out again if we % didn't need it. % We rely on the fact that \parsearg sets \catcode`\ =10. % \parseargdef\set{\setyyy#1 \endsetyyy} \def\setyyy#1 #2\endsetyyy{% {% \makevalueexpandable \def\temp{#2}% \edef\next{\gdef\makecsname{SET#1}}% \ifx\temp\empty \next{}% \else \setzzz#2\endsetzzz \fi }% } % Remove the trailing space \setxxx inserted. \def\setzzz#1 \endsetzzz{\next{#1}} % @clear VAR clears (i.e., unsets) the variable VAR. % \parseargdef\clear{% {% \makevalueexpandable \global\expandafter\let\csname SET#1\endcsname=\relax }% } % @value{foo} gets the text saved in variable foo. \def\value{\begingroup\makevalueexpandable\valuexxx} \def\valuexxx#1{\expandablevalue{#1}\endgroup} { \catcode`\- = \active \catcode`\_ = \active % \gdef\makevalueexpandable{% \let\value = \expandablevalue % We don't want these characters active, ... \catcode`\-=\other \catcode`\_=\other % ..., but we might end up with active ones in the argument if % we're called from @code, as @code{@value{foo-bar_}}, though. % So \let them to their normal equivalents. \let-\realdash \let_\normalunderscore } } % We have this subroutine so that we can handle at least some @value's % properly in indexes (we call \makevalueexpandable in \indexdummies). % The command has to be fully expandable (if the variable is set), since % the result winds up in the index file. This means that if the % variable's value contains other Texinfo commands, it's almost certain % it will fail (although perhaps we could fix that with sufficient work % to do a one-level expansion on the result, instead of complete). % \def\expandablevalue#1{% \expandafter\ifx\csname SET#1\endcsname\relax {[No value for ``#1'']}% \message{Variable `#1', used in @value, is not set.}% \else \csname SET#1\endcsname \fi } % @ifset VAR ... @end ifset reads the `...' iff VAR has been defined % with @set. % % To get special treatment of `@end ifset,' call \makeond and the redefine. % \makecond{ifset} \def\ifset{\parsearg{\doifset{\let\next=\ifsetfail}}} \def\doifset#1#2{% {% \makevalueexpandable \let\next=\empty \expandafter\ifx\csname SET#2\endcsname\relax #1% If not set, redefine \next. \fi \expandafter }\next } \def\ifsetfail{\doignore{ifset}} % @ifclear VAR ... @end ifclear reads the `...' iff VAR has never been % defined with @set, or has been undefined with @clear. % % The `\else' inside the `\doifset' parameter is a trick to reuse the % above code: if the variable is not set, do nothing, if it is set, % then redefine \next to \ifclearfail. % \makecond{ifclear} \def\ifclear{\parsearg{\doifset{\else \let\next=\ifclearfail}}} \def\ifclearfail{\doignore{ifclear}} % @dircategory CATEGORY -- specify a category of the dir file % which this file should belong to. Ignore this in TeX. \let\dircategory=\comment % @defininfoenclose. \let\definfoenclose=\comment \message{indexing,} % Index generation facilities % Define \newwrite to be identical to plain tex's \newwrite % except not \outer, so it can be used within macros and \if's. \edef\newwrite{\makecsname{ptexnewwrite}} % \newindex {foo} defines an index named foo. % It automatically defines \fooindex such that % \fooindex ...rest of line... puts an entry in the index foo. % It also defines \fooindfile to be the number of the output channel for % the file that accumulates this index. The file's extension is foo. % The name of an index should be no more than 2 characters long % for the sake of vms. % \def\newindex#1{% \iflinks \expandafter\newwrite \csname#1indfile\endcsname \openout \csname#1indfile\endcsname \jobname.#1 % Open the file \fi \expandafter\xdef\csname#1index\endcsname{% % Define @#1index \noexpand\doindex{#1}} } % @defindex foo == \newindex{foo} % \def\defindex{\parsearg\newindex} % Define @defcodeindex, like @defindex except put all entries in @code. % \def\defcodeindex{\parsearg\newcodeindex} % \def\newcodeindex#1{% \iflinks \expandafter\newwrite \csname#1indfile\endcsname \openout \csname#1indfile\endcsname \jobname.#1 \fi \expandafter\xdef\csname#1index\endcsname{% \noexpand\docodeindex{#1}}% } % @synindex foo bar makes index foo feed into index bar. % Do this instead of @defindex foo if you don't want it as a separate index. % % @syncodeindex foo bar similar, but put all entries made for index foo % inside @code. % \def\synindex#1 #2 {\dosynindex\doindex{#1}{#2}} \def\syncodeindex#1 #2 {\dosynindex\docodeindex{#1}{#2}} % #1 is \doindex or \docodeindex, #2 the index getting redefined (foo), % #3 the target index (bar). \def\dosynindex#1#2#3{% % Only do \closeout if we haven't already done it, else we'll end up % closing the target index. \expandafter \ifx\csname donesynindex#2\endcsname \relax % The \closeout helps reduce unnecessary open files; the limit on the % Acorn RISC OS is a mere 16 files. \expandafter\closeout\csname#2indfile\endcsname \expandafter\let\csname donesynindex#2\endcsname = 1 \fi % redefine \fooindfile: \expandafter\let\expandafter\temp\expandafter=\csname#3indfile\endcsname \expandafter\let\csname#2indfile\endcsname=\temp % redefine \fooindex: \expandafter\xdef\csname#2index\endcsname{\noexpand#1{#3}}% } % Define \doindex, the driver for all \fooindex macros. % Argument #1 is generated by the calling \fooindex macro, % and it is "foo", the name of the index. % \doindex just uses \parsearg; it calls \doind for the actual work. % This is because \doind is more useful to call from other macros. % There is also \dosubind {index}{topic}{subtopic} % which makes an entry in a two-level index such as the operation index. \def\doindex#1{\edef\indexname{#1}\parsearg\singleindexer} \def\singleindexer #1{\doind{\indexname}{#1}} % like the previous two, but they put @code around the argument. \def\docodeindex#1{\edef\indexname{#1}\parsearg\singlecodeindexer} \def\singlecodeindexer #1{\doind{\indexname}{\code{#1}}} % Take care of Texinfo commands that can appear in an index entry. % Since there are some commands we want to expand, and others we don't, % we have to laboriously prevent expansion for those that we don't. % \def\indexdummies{% \escapechar = `\\ % use backslash in output files. \def\@{@}% change to @@ when we switch to @ as escape char in index files. \def\ {\realbackslash\space }% % % Need these unexpandable (because we define \tt as a dummy) % definitions when @{ or @} appear in index entry text. Also, more % complicated, when \tex is in effect and \{ is a \delimiter again. % We can't use \lbracecmd and \rbracecmd because texindex assumes % braces and backslashes are used only as delimiters. Perhaps we % should define @lbrace and @rbrace commands a la @comma. \def\{{{\tt\char123}}% \def\}{{\tt\char125}}% % % I don't entirely understand this, but when an index entry is % generated from a macro call, the \endinput which \scanmacro inserts % causes processing to be prematurely terminated. This is, % apparently, because \indexsorttmp is fully expanded, and \endinput % is an expandable command. The redefinition below makes \endinput % disappear altogether for that purpose -- although logging shows that % processing continues to some further point. On the other hand, it % seems \endinput does not hurt in the printed index arg, since that % is still getting written without apparent harm. % % Sample source (mac-idx3.tex, reported by Graham Percival to % help-texinfo, 22may06): % @macro funindex {WORD} % @findex xyz % @end macro % ... % @funindex commtest % % The above is not enough to reproduce the bug, but it gives the flavor. % % Sample whatsit resulting: % .@write3{\entry{xyz}{@folio }{@code {xyz@endinput }}} % % So: \let\endinput = \empty % % Do the redefinitions. \commondummies } % For the aux and toc files, @ is the escape character. So we want to % redefine everything using @ as the escape character (instead of % \realbackslash, still used for index files). When everything uses @, % this will be simpler. % \def\atdummies{% \def\@{@@}% \def\ {@ }% \let\{ = \lbraceatcmd \let\} = \rbraceatcmd % % Do the redefinitions. \commondummies \otherbackslash } % Called from \indexdummies and \atdummies. % \def\commondummies{% % % \definedummyword defines \#1 as \string\#1\space, thus effectively % preventing its expansion. This is used only for control words, % not control letters, because the \space would be incorrect for % control characters, but is needed to separate the control word % from whatever follows. % % For control letters, we have \definedummyletter, which omits the % space. % % These can be used both for control words that take an argument and % those that do not. If it is followed by {arg} in the input, then % that will dutifully get written to the index (or wherever). % \def\definedummyword ##1{\def##1{\string##1\space}}% \def\definedummyletter##1{\def##1{\string##1}}% \let\definedummyaccent\definedummyletter % \commondummiesnofonts % \definedummyletter\_% \definedummyletter\-% % % Non-English letters. \definedummyword\AA \definedummyword\AE \definedummyword\DH \definedummyword\L \definedummyword\O \definedummyword\OE \definedummyword\TH \definedummyword\aa \definedummyword\ae \definedummyword\dh \definedummyword\exclamdown \definedummyword\l \definedummyword\o \definedummyword\oe \definedummyword\ordf \definedummyword\ordm \definedummyword\questiondown \definedummyword\ss \definedummyword\th % % Although these internal commands shouldn't show up, sometimes they do. \definedummyword\bf \definedummyword\gtr \definedummyword\hat \definedummyword\less \definedummyword\sf \definedummyword\sl \definedummyword\tclose \definedummyword\tt % \definedummyword\LaTeX \definedummyword\TeX % % Assorted special characters. \definedummyword\arrow \definedummyword\bullet \definedummyword\comma \definedummyword\copyright \definedummyword\registeredsymbol \definedummyword\dots \definedummyword\enddots \definedummyword\entrybreak \definedummyword\equiv \definedummyword\error \definedummyword\euro \definedummyword\expansion \definedummyword\geq \definedummyword\guillemetleft \definedummyword\guillemetright \definedummyword\guilsinglleft \definedummyword\guilsinglright \definedummyword\leq \definedummyword\minus \definedummyword\ogonek \definedummyword\pounds \definedummyword\point \definedummyword\print \definedummyword\quotedblbase \definedummyword\quotedblleft \definedummyword\quotedblright \definedummyword\quoteleft \definedummyword\quoteright \definedummyword\quotesinglbase \definedummyword\result \definedummyword\textdegree % % We want to disable all macros so that they are not expanded by \write. \macrolist % \normalturnoffactive % % Handle some cases of @value -- where it does not contain any % (non-fully-expandable) commands. \makevalueexpandable } % \commondummiesnofonts: common to \commondummies and \indexnofonts. % \def\commondummiesnofonts{% % Control letters and accents. \definedummyletter\!% \definedummyaccent\"% \definedummyaccent\'% \definedummyletter\*% \definedummyaccent\,% \definedummyletter\.% \definedummyletter\/% \definedummyletter\:% \definedummyaccent\=% \definedummyletter\?% \definedummyaccent\^% \definedummyaccent\`% \definedummyaccent\~% \definedummyword\u \definedummyword\v \definedummyword\H \definedummyword\dotaccent \definedummyword\ogonek \definedummyword\ringaccent \definedummyword\tieaccent \definedummyword\ubaraccent \definedummyword\udotaccent \definedummyword\dotless % % Texinfo font commands. \definedummyword\b \definedummyword\i \definedummyword\r \definedummyword\sansserif \definedummyword\sc \definedummyword\slanted \definedummyword\t % % Commands that take arguments. \definedummyword\acronym \definedummyword\anchor \definedummyword\cite \definedummyword\code \definedummyword\command \definedummyword\dfn \definedummyword\dmn \definedummyword\email \definedummyword\emph \definedummyword\env \definedummyword\file \definedummyword\indicateurl \definedummyword\kbd \definedummyword\key \definedummyword\math \definedummyword\option \definedummyword\pxref \definedummyword\ref \definedummyword\samp \definedummyword\strong \definedummyword\tie \definedummyword\uref \definedummyword\url \definedummyword\var \definedummyword\verb \definedummyword\w \definedummyword\xref } % \indexnofonts is used when outputting the strings to sort the index % by, and when constructing control sequence names. It eliminates all % control sequences and just writes whatever the best ASCII sort string % would be for a given command (usually its argument). % \def\indexnofonts{% % Accent commands should become @asis. \def\definedummyaccent##1{\let##1\asis}% % We can just ignore other control letters. \def\definedummyletter##1{\let##1\empty}% % All control words become @asis by default; overrides below. \let\definedummyword\definedummyaccent % \commondummiesnofonts % % Don't no-op \tt, since it isn't a user-level command % and is used in the definitions of the active chars like <, >, |, etc. % Likewise with the other plain tex font commands. %\let\tt=\asis % \def\ { }% \def\@{@}% \def\_{\normalunderscore}% \def\-{}% @- shouldn't affect sorting % % Unfortunately, texindex is not prepared to handle braces in the % content at all. So for index sorting, we map @{ and @} to strings % starting with |, since that ASCII character is between ASCII { and }. \def\{{|a}% \def\}{|b}% % % Non-English letters. \def\AA{AA}% \def\AE{AE}% \def\DH{DZZ}% \def\L{L}% \def\OE{OE}% \def\O{O}% \def\TH{ZZZ}% \def\aa{aa}% \def\ae{ae}% \def\dh{dzz}% \def\exclamdown{!}% \def\l{l}% \def\oe{oe}% \def\ordf{a}% \def\ordm{o}% \def\o{o}% \def\questiondown{?}% \def\ss{ss}% \def\th{zzz}% % \def\LaTeX{LaTeX}% \def\TeX{TeX}% % % Assorted special characters. % (The following {} will end up in the sort string, but that's ok.) \def\arrow{->}% \def\bullet{bullet}% \def\comma{,}% \def\copyright{copyright}% \def\dots{...}% \def\enddots{...}% \def\equiv{==}% \def\error{error}% \def\euro{euro}% \def\expansion{==>}% \def\geq{>=}% \def\guillemetleft{<<}% \def\guillemetright{>>}% \def\guilsinglleft{<}% \def\guilsinglright{>}% \def\leq{<=}% \def\minus{-}% \def\point{.}% \def\pounds{pounds}% \def\print{-|}% \def\quotedblbase{"}% \def\quotedblleft{"}% \def\quotedblright{"}% \def\quoteleft{`}% \def\quoteright{'}% \def\quotesinglbase{,}% \def\registeredsymbol{R}% \def\result{=>}% \def\textdegree{o}% % \expandafter\ifx\csname SETtxiindexlquoteignore\endcsname\relax \else \indexlquoteignore \fi % % We need to get rid of all macros, leaving only the arguments (if present). % Of course this is not nearly correct, but it is the best we can do for now. % makeinfo does not expand macros in the argument to @deffn, which ends up % writing an index entry, and texindex isn't prepared for an index sort entry % that starts with \. % % Since macro invocations are followed by braces, we can just redefine them % to take a single TeX argument. The case of a macro invocation that % goes to end-of-line is not handled. % \macrolist } % Undocumented (for FSFS 2nd ed.): @set txiindexlquoteignore makes us % ignore left quotes in the sort term. {\catcode`\`=\active \gdef\indexlquoteignore{\let`=\empty}} \let\indexbackslash=0 %overridden during \printindex. \let\SETmarginindex=\relax % put index entries in margin (undocumented)? % Most index entries go through here, but \dosubind is the general case. % #1 is the index name, #2 is the entry text. \def\doind#1#2{\dosubind{#1}{#2}{}} % Workhorse for all \fooindexes. % #1 is name of index, #2 is stuff to put there, #3 is subentry -- % empty if called from \doind, as we usually are (the main exception % is with most defuns, which call us directly). % \def\dosubind#1#2#3{% \iflinks {% % Store the main index entry text (including the third arg). \toks0 = {#2}% % If third arg is present, precede it with a space. \def\thirdarg{#3}% \ifx\thirdarg\empty \else \toks0 = \expandafter{\the\toks0 \space #3}% \fi % \edef\writeto{\csname#1indfile\endcsname}% % \safewhatsit\dosubindwrite }% \fi } % Write the entry in \toks0 to the index file: % \def\dosubindwrite{% % Put the index entry in the margin if desired. \ifx\SETmarginindex\relax\else \insert\margin{\hbox{\vrule height8pt depth3pt width0pt \the\toks0}}% \fi % % Remember, we are within a group. \indexdummies % Must do this here, since \bf, etc expand at this stage \def\backslashcurfont{\indexbackslash}% \indexbackslash isn't defined now % so it will be output as is; and it will print as backslash. % % Process the index entry with all font commands turned off, to % get the string to sort by. {\indexnofonts \edef\temp{\the\toks0}% need full expansion \xdef\indexsorttmp{\temp}% }% % % Set up the complete index entry, with both the sort key and % the original text, including any font commands. We write % three arguments to \entry to the .?? file (four in the % subentry case), texindex reduces to two when writing the .??s % sorted result. \edef\temp{% \write\writeto{% \string\entry{\indexsorttmp}{\noexpand\folio}{\the\toks0}}% }% \temp } % Take care of unwanted page breaks/skips around a whatsit: % % If a skip is the last thing on the list now, preserve it % by backing up by \lastskip, doing the \write, then inserting % the skip again. Otherwise, the whatsit generated by the % \write or \pdfdest will make \lastskip zero. The result is that % sequences like this: % @end defun % @tindex whatever % @defun ... % will have extra space inserted, because the \medbreak in the % start of the @defun won't see the skip inserted by the @end of % the previous defun. % % But don't do any of this if we're not in vertical mode. We % don't want to do a \vskip and prematurely end a paragraph. % % Avoid page breaks due to these extra skips, too. % % But wait, there is a catch there: % We'll have to check whether \lastskip is zero skip. \ifdim is not % sufficient for this purpose, as it ignores stretch and shrink parts % of the skip. The only way seems to be to check the textual % representation of the skip. % % The following is almost like \def\zeroskipmacro{0.0pt} except that % the ``p'' and ``t'' characters have catcode \other, not 11 (letter). % \edef\zeroskipmacro{\expandafter\the\csname z@skip\endcsname} % \newskip\whatsitskip \newcount\whatsitpenalty % % ..., ready, GO: % \def\safewhatsit#1{\ifhmode #1% \else % \lastskip and \lastpenalty cannot both be nonzero simultaneously. \whatsitskip = \lastskip \edef\lastskipmacro{\the\lastskip}% \whatsitpenalty = \lastpenalty % % If \lastskip is nonzero, that means the last item was a % skip. And since a skip is discardable, that means this % -\whatsitskip glue we're inserting is preceded by a % non-discardable item, therefore it is not a potential % breakpoint, therefore no \nobreak needed. \ifx\lastskipmacro\zeroskipmacro \else \vskip-\whatsitskip \fi % #1% % \ifx\lastskipmacro\zeroskipmacro % If \lastskip was zero, perhaps the last item was a penalty, and % perhaps it was >=10000, e.g., a \nobreak. In that case, we want % to re-insert the same penalty (values >10000 are used for various % signals); since we just inserted a non-discardable item, any % following glue (such as a \parskip) would be a breakpoint. For example: % @deffn deffn-whatever % @vindex index-whatever % Description. % would allow a break between the index-whatever whatsit % and the "Description." paragraph. \ifnum\whatsitpenalty>9999 \penalty\whatsitpenalty \fi \else % On the other hand, if we had a nonzero \lastskip, % this make-up glue would be preceded by a non-discardable item % (the whatsit from the \write), so we must insert a \nobreak. \nobreak\vskip\whatsitskip \fi \fi} % The index entry written in the file actually looks like % \entry {sortstring}{page}{topic} % or % \entry {sortstring}{page}{topic}{subtopic} % The texindex program reads in these files and writes files % containing these kinds of lines: % \initial {c} % before the first topic whose initial is c % \entry {topic}{pagelist} % for a topic that is used without subtopics % \primary {topic} % for the beginning of a topic that is used with subtopics % \secondary {subtopic}{pagelist} % for each subtopic. % Define the user-accessible indexing commands % @findex, @vindex, @kindex, @cindex. \def\findex {\fnindex} \def\kindex {\kyindex} \def\cindex {\cpindex} \def\vindex {\vrindex} \def\tindex {\tpindex} \def\pindex {\pgindex} \def\cindexsub {\begingroup\obeylines\cindexsub} {\obeylines % \gdef\cindexsub "#1" #2^^M{\endgroup % \dosubind{cp}{#2}{#1}}} % Define the macros used in formatting output of the sorted index material. % @printindex causes a particular index (the ??s file) to get printed. % It does not print any chapter heading (usually an @unnumbered). % \parseargdef\printindex{\begingroup \dobreak \chapheadingskip{10000}% % \smallfonts \rm \tolerance = 9500 \plainfrenchspacing \everypar = {}% don't want the \kern\-parindent from indentation suppression. % % See if the index file exists and is nonempty. % Change catcode of @ here so that if the index file contains % \initial {@} % as its first line, TeX doesn't complain about mismatched braces % (because it thinks @} is a control sequence). \catcode`\@ = 11 \openin 1 \jobname.#1s \ifeof 1 % \enddoublecolumns gets confused if there is no text in the index, % and it loses the chapter title and the aux file entries for the % index. The easiest way to prevent this problem is to make sure % there is some text. \putwordIndexNonexistent \else % % If the index file exists but is empty, then \openin leaves \ifeof % false. We have to make TeX try to read something from the file, so % it can discover if there is anything in it. \read 1 to \temp \ifeof 1 \putwordIndexIsEmpty \else % Index files are almost Texinfo source, but we use \ as the escape % character. It would be better to use @, but that's too big a change % to make right now. \def\indexbackslash{\backslashcurfont}% \catcode`\\ = 0 \escapechar = `\\ \begindoublecolumns \input \jobname.#1s \enddoublecolumns \fi \fi \closein 1 \endgroup} % These macros are used by the sorted index file itself. % Change them to control the appearance of the index. \def\initial#1{{% % Some minor font changes for the special characters. \let\tentt=\sectt \let\tt=\sectt \let\sf=\sectt % % Remove any glue we may have, we'll be inserting our own. \removelastskip % % We like breaks before the index initials, so insert a bonus. \nobreak \vskip 0pt plus 3\baselineskip \penalty 0 \vskip 0pt plus -3\baselineskip % % Typeset the initial. Making this add up to a whole number of % baselineskips increases the chance of the dots lining up from column % to column. It still won't often be perfect, because of the stretch % we need before each entry, but it's better. % % No shrink because it confuses \balancecolumns. \vskip 1.67\baselineskip plus .5\baselineskip \leftline{\secbf #1}% % Do our best not to break after the initial. \nobreak \vskip .33\baselineskip plus .1\baselineskip }} % \entry typesets a paragraph consisting of the text (#1), dot leaders, and % then page number (#2) flushed to the right margin. It is used for index % and table of contents entries. The paragraph is indented by \leftskip. % % A straightforward implementation would start like this: % \def\entry#1#2{... % But this freezes the catcodes in the argument, and can cause problems to % @code, which sets - active. This problem was fixed by a kludge--- % ``-'' was active throughout whole index, but this isn't really right. % The right solution is to prevent \entry from swallowing the whole text. % --kasal, 21nov03 \def\entry{% \begingroup % % Start a new paragraph if necessary, so our assignments below can't % affect previous text. \par % % Do not fill out the last line with white space. \parfillskip = 0in % % No extra space above this paragraph. \parskip = 0in % % Do not prefer a separate line ending with a hyphen to fewer lines. \finalhyphendemerits = 0 % % \hangindent is only relevant when the entry text and page number % don't both fit on one line. In that case, bob suggests starting the % dots pretty far over on the line. Unfortunately, a large % indentation looks wrong when the entry text itself is broken across % lines. So we use a small indentation and put up with long leaders. % % \hangafter is reset to 1 (which is the value we want) at the start % of each paragraph, so we need not do anything with that. \hangindent = 2em % % When the entry text needs to be broken, just fill out the first line % with blank space. \rightskip = 0pt plus1fil % % A bit of stretch before each entry for the benefit of balancing % columns. \vskip 0pt plus1pt % % When reading the text of entry, convert explicit line breaks % from @* into spaces. The user might give these in long section % titles, for instance. \def\*{\unskip\space\ignorespaces}% \def\entrybreak{\hfil\break}% % % Swallow the left brace of the text (first parameter): \afterassignment\doentry \let\temp = } \def\entrybreak{\unskip\space\ignorespaces}% \def\doentry{% \bgroup % Instead of the swallowed brace. \noindent \aftergroup\finishentry % And now comes the text of the entry. } \def\finishentry#1{% % #1 is the page number. % % The following is kludged to not output a line of dots in the index if % there are no page numbers. The next person who breaks this will be % cursed by a Unix daemon. \setbox\boxA = \hbox{#1}% \ifdim\wd\boxA = 0pt \ % \else % % If we must, put the page number on a line of its own, and fill out % this line with blank space. (The \hfil is overwhelmed with the % fill leaders glue in \indexdotfill if the page number does fit.) \hfil\penalty50 \null\nobreak\indexdotfill % Have leaders before the page number. % % The `\ ' here is removed by the implicit \unskip that TeX does as % part of (the primitive) \par. Without it, a spurious underfull % \hbox ensues. \ifpdf \pdfgettoks#1.% \ \the\toksA \else \ #1% \fi \fi \par \endgroup } % Like plain.tex's \dotfill, except uses up at least 1 em. \def\indexdotfill{\cleaders \hbox{$\mathsurround=0pt \mkern1.5mu.\mkern1.5mu$}\hskip 1em plus 1fill} \def\primary #1{\line{#1\hfil}} \newskip\secondaryindent \secondaryindent=0.5cm \def\secondary#1#2{{% \parfillskip=0in \parskip=0in \hangindent=1in \hangafter=1 \noindent\hskip\secondaryindent\hbox{#1}\indexdotfill \ifpdf \pdfgettoks#2.\ \the\toksA % The page number ends the paragraph. \else #2 \fi \par }} % Define two-column mode, which we use to typeset indexes. % Adapted from the TeXbook, page 416, which is to say, % the manmac.tex format used to print the TeXbook itself. \catcode`\@=11 \newbox\partialpage \newdimen\doublecolumnhsize \def\begindoublecolumns{\begingroup % ended by \enddoublecolumns % Grab any single-column material above us. \output = {% % % Here is a possibility not foreseen in manmac: if we accumulate a % whole lot of material, we might end up calling this \output % routine twice in a row (see the doublecol-lose test, which is % essentially a couple of indexes with @setchapternewpage off). In % that case we just ship out what is in \partialpage with the normal % output routine. Generally, \partialpage will be empty when this % runs and this will be a no-op. See the indexspread.tex test case. \ifvoid\partialpage \else \onepageout{\pagecontents\partialpage}% \fi % \global\setbox\partialpage = \vbox{% % Unvbox the main output page. \unvbox\PAGE \kern-\topskip \kern\baselineskip }% }% \eject % run that output routine to set \partialpage % % Use the double-column output routine for subsequent pages. \output = {\doublecolumnout}% % % Change the page size parameters. We could do this once outside this % routine, in each of @smallbook, @afourpaper, and the default 8.5x11 % format, but then we repeat the same computation. Repeating a couple % of assignments once per index is clearly meaningless for the % execution time, so we may as well do it in one place. % % First we halve the line length, less a little for the gutter between % the columns. We compute the gutter based on the line length, so it % changes automatically with the paper format. The magic constant % below is chosen so that the gutter has the same value (well, +-<1pt) % as it did when we hard-coded it. % % We put the result in a separate register, \doublecolumhsize, so we % can restore it in \pagesofar, after \hsize itself has (potentially) % been clobbered. % \doublecolumnhsize = \hsize \advance\doublecolumnhsize by -.04154\hsize \divide\doublecolumnhsize by 2 \hsize = \doublecolumnhsize % % Double the \vsize as well. (We don't need a separate register here, % since nobody clobbers \vsize.) \vsize = 2\vsize } % The double-column output routine for all double-column pages except % the last. % \def\doublecolumnout{% \splittopskip=\topskip \splitmaxdepth=\maxdepth % Get the available space for the double columns -- the normal % (undoubled) page height minus any material left over from the % previous page. \dimen@ = \vsize \divide\dimen@ by 2 \advance\dimen@ by -\ht\partialpage % % box0 will be the left-hand column, box2 the right. \setbox0=\vsplit255 to\dimen@ \setbox2=\vsplit255 to\dimen@ \onepageout\pagesofar \unvbox255 \penalty\outputpenalty } % % Re-output the contents of the output page -- any previous material, % followed by the two boxes we just split, in box0 and box2. \def\pagesofar{% \unvbox\partialpage % \hsize = \doublecolumnhsize \wd0=\hsize \wd2=\hsize \hbox to\pagewidth{\box0\hfil\box2}% } % % All done with double columns. \def\enddoublecolumns{% % The following penalty ensures that the page builder is exercised % _before_ we change the output routine. This is necessary in the % following situation: % % The last section of the index consists only of a single entry. % Before this section, \pagetotal is less than \pagegoal, so no % break occurs before the last section starts. However, the last % section, consisting of \initial and the single \entry, does not % fit on the page and has to be broken off. Without the following % penalty the page builder will not be exercised until \eject % below, and by that time we'll already have changed the output % routine to the \balancecolumns version, so the next-to-last % double-column page will be processed with \balancecolumns, which % is wrong: The two columns will go to the main vertical list, with % the broken-off section in the recent contributions. As soon as % the output routine finishes, TeX starts reconsidering the page % break. The two columns and the broken-off section both fit on the % page, because the two columns now take up only half of the page % goal. When TeX sees \eject from below which follows the final % section, it invokes the new output routine that we've set after % \balancecolumns below; \onepageout will try to fit the two columns % and the final section into the vbox of \pageheight (see % \pagebody), causing an overfull box. % % Note that glue won't work here, because glue does not exercise the % page builder, unlike penalties (see The TeXbook, pp. 280-281). \penalty0 % \output = {% % Split the last of the double-column material. Leave it on the % current page, no automatic page break. \balancecolumns % % If we end up splitting too much material for the current page, % though, there will be another page break right after this \output % invocation ends. Having called \balancecolumns once, we do not % want to call it again. Therefore, reset \output to its normal % definition right away. (We hope \balancecolumns will never be % called on to balance too much material, but if it is, this makes % the output somewhat more palatable.) \global\output = {\onepageout{\pagecontents\PAGE}}% }% \eject \endgroup % started in \begindoublecolumns % % \pagegoal was set to the doubled \vsize above, since we restarted % the current page. We're now back to normal single-column % typesetting, so reset \pagegoal to the normal \vsize (after the % \endgroup where \vsize got restored). \pagegoal = \vsize } % % Called at the end of the double column material. \def\balancecolumns{% \setbox0 = \vbox{\unvbox255}% like \box255 but more efficient, see p.120. \dimen@ = \ht0 \advance\dimen@ by \topskip \advance\dimen@ by-\baselineskip \divide\dimen@ by 2 % target to split to %debug\message{final 2-column material height=\the\ht0, target=\the\dimen@.}% \splittopskip = \topskip % Loop until we get a decent breakpoint. {% \vbadness = 10000 \loop \global\setbox3 = \copy0 \global\setbox1 = \vsplit3 to \dimen@ \ifdim\ht3>\dimen@ \global\advance\dimen@ by 1pt \repeat }% %debug\message{split to \the\dimen@, column heights: \the\ht1, \the\ht3.}% \setbox0=\vbox to\dimen@{\unvbox1}% \setbox2=\vbox to\dimen@{\unvbox3}% % \pagesofar } \catcode`\@ = \other \message{sectioning,} % Chapters, sections, etc. % Let's start with @part. \outer\parseargdef\part{\partzzz{#1}} \def\partzzz#1{% \chapoddpage \null \vskip.3\vsize % move it down on the page a bit \begingroup \noindent \titlefonts\rmisbold #1\par % the text \let\lastnode=\empty % no node to associate with \writetocentry{part}{#1}{}% but put it in the toc \headingsoff % no headline or footline on the part page \chapoddpage \endgroup } % \unnumberedno is an oxymoron. But we count the unnumbered % sections so that we can refer to them unambiguously in the pdf % outlines by their "section number". We avoid collisions with chapter % numbers by starting them at 10000. (If a document ever has 10000 % chapters, we're in trouble anyway, I'm sure.) \newcount\unnumberedno \unnumberedno = 10000 \newcount\chapno \newcount\secno \secno=0 \newcount\subsecno \subsecno=0 \newcount\subsubsecno \subsubsecno=0 % This counter is funny since it counts through charcodes of letters A, B, ... \newcount\appendixno \appendixno = `\@ % % \def\appendixletter{\char\the\appendixno} % We do the following ugly conditional instead of the above simple % construct for the sake of pdftex, which needs the actual % letter in the expansion, not just typeset. % \def\appendixletter{% \ifnum\appendixno=`A A% \else\ifnum\appendixno=`B B% \else\ifnum\appendixno=`C C% \else\ifnum\appendixno=`D D% \else\ifnum\appendixno=`E E% \else\ifnum\appendixno=`F F% \else\ifnum\appendixno=`G G% \else\ifnum\appendixno=`H H% \else\ifnum\appendixno=`I I% \else\ifnum\appendixno=`J J% \else\ifnum\appendixno=`K K% \else\ifnum\appendixno=`L L% \else\ifnum\appendixno=`M M% \else\ifnum\appendixno=`N N% \else\ifnum\appendixno=`O O% \else\ifnum\appendixno=`P P% \else\ifnum\appendixno=`Q Q% \else\ifnum\appendixno=`R R% \else\ifnum\appendixno=`S S% \else\ifnum\appendixno=`T T% \else\ifnum\appendixno=`U U% \else\ifnum\appendixno=`V V% \else\ifnum\appendixno=`W W% \else\ifnum\appendixno=`X X% \else\ifnum\appendixno=`Y Y% \else\ifnum\appendixno=`Z Z% % The \the is necessary, despite appearances, because \appendixletter is % expanded while writing the .toc file. \char\appendixno is not % expandable, thus it is written literally, thus all appendixes come out % with the same letter (or @) in the toc without it. \else\char\the\appendixno \fi\fi\fi\fi\fi\fi\fi\fi\fi\fi\fi\fi\fi \fi\fi\fi\fi\fi\fi\fi\fi\fi\fi\fi\fi\fi} % Each @chapter defines these (using marks) as the number+name, number % and name of the chapter. Page headings and footings can use % these. @section does likewise. \def\thischapter{} \def\thischapternum{} \def\thischaptername{} \def\thissection{} \def\thissectionnum{} \def\thissectionname{} \newcount\absseclevel % used to calculate proper heading level \newcount\secbase\secbase=0 % @raisesections/@lowersections modify this count % @raisesections: treat @section as chapter, @subsection as section, etc. \def\raisesections{\global\advance\secbase by -1} \let\up=\raisesections % original BFox name % @lowersections: treat @chapter as section, @section as subsection, etc. \def\lowersections{\global\advance\secbase by 1} \let\down=\lowersections % original BFox name % we only have subsub. \chardef\maxseclevel = 3 % % A numbered section within an unnumbered changes to unnumbered too. % To achieve this, remember the "biggest" unnum. sec. we are currently in: \chardef\unnlevel = \maxseclevel % % Trace whether the current chapter is an appendix or not: % \chapheadtype is "N" or "A", unnumbered chapters are ignored. \def\chapheadtype{N} % Choose a heading macro % #1 is heading type % #2 is heading level % #3 is text for heading \def\genhead#1#2#3{% % Compute the abs. sec. level: \absseclevel=#2 \advance\absseclevel by \secbase % Make sure \absseclevel doesn't fall outside the range: \ifnum \absseclevel < 0 \absseclevel = 0 \else \ifnum \absseclevel > 3 \absseclevel = 3 \fi \fi % The heading type: \def\headtype{#1}% \if \headtype U% \ifnum \absseclevel < \unnlevel \chardef\unnlevel = \absseclevel \fi \else % Check for appendix sections: \ifnum \absseclevel = 0 \edef\chapheadtype{\headtype}% \else \if \headtype A\if \chapheadtype N% \errmessage{@appendix... within a non-appendix chapter}% \fi\fi \fi % Check for numbered within unnumbered: \ifnum \absseclevel > \unnlevel \def\headtype{U}% \else \chardef\unnlevel = 3 \fi \fi % Now print the heading: \if \headtype U% \ifcase\absseclevel \unnumberedzzz{#3}% \or \unnumberedseczzz{#3}% \or \unnumberedsubseczzz{#3}% \or \unnumberedsubsubseczzz{#3}% \fi \else \if \headtype A% \ifcase\absseclevel \appendixzzz{#3}% \or \appendixsectionzzz{#3}% \or \appendixsubseczzz{#3}% \or \appendixsubsubseczzz{#3}% \fi \else \ifcase\absseclevel \chapterzzz{#3}% \or \seczzz{#3}% \or \numberedsubseczzz{#3}% \or \numberedsubsubseczzz{#3}% \fi \fi \fi \suppressfirstparagraphindent } % an interface: \def\numhead{\genhead N} \def\apphead{\genhead A} \def\unnmhead{\genhead U} % @chapter, @appendix, @unnumbered. Increment top-level counter, reset % all lower-level sectioning counters to zero. % % Also set \chaplevelprefix, which we prepend to @float sequence numbers % (e.g., figures), q.v. By default (before any chapter), that is empty. \let\chaplevelprefix = \empty % \outer\parseargdef\chapter{\numhead0{#1}} % normally numhead0 calls chapterzzz \def\chapterzzz#1{% % section resetting is \global in case the chapter is in a group, such % as an @include file. \global\secno=0 \global\subsecno=0 \global\subsubsecno=0 \global\advance\chapno by 1 % % Used for \float. \gdef\chaplevelprefix{\the\chapno.}% \resetallfloatnos % % \putwordChapter can contain complex things in translations. \toks0=\expandafter{\putwordChapter}% \message{\the\toks0 \space \the\chapno}% % % Write the actual heading. \chapmacro{#1}{Ynumbered}{\the\chapno}% % % So @section and the like are numbered underneath this chapter. \global\let\section = \numberedsec \global\let\subsection = \numberedsubsec \global\let\subsubsection = \numberedsubsubsec } \outer\parseargdef\appendix{\apphead0{#1}} % normally calls appendixzzz % \def\appendixzzz#1{% \global\secno=0 \global\subsecno=0 \global\subsubsecno=0 \global\advance\appendixno by 1 \gdef\chaplevelprefix{\appendixletter.}% \resetallfloatnos % % \putwordAppendix can contain complex things in translations. \toks0=\expandafter{\putwordAppendix}% \message{\the\toks0 \space \appendixletter}% % \chapmacro{#1}{Yappendix}{\appendixletter}% % \global\let\section = \appendixsec \global\let\subsection = \appendixsubsec \global\let\subsubsection = \appendixsubsubsec } % normally unnmhead0 calls unnumberedzzz: \outer\parseargdef\unnumbered{\unnmhead0{#1}} \def\unnumberedzzz#1{% \global\secno=0 \global\subsecno=0 \global\subsubsecno=0 \global\advance\unnumberedno by 1 % % Since an unnumbered has no number, no prefix for figures. \global\let\chaplevelprefix = \empty \resetallfloatnos % % This used to be simply \message{#1}, but TeX fully expands the % argument to \message. Therefore, if #1 contained @-commands, TeX % expanded them. For example, in `@unnumbered The @cite{Book}', TeX % expanded @cite (which turns out to cause errors because \cite is meant % to be executed, not expanded). % % Anyway, we don't want the fully-expanded definition of @cite to appear % as a result of the \message, we just want `@cite' itself. We use % \the to achieve this: TeX expands \the only once, % simply yielding the contents of . (We also do this for % the toc entries.) \toks0 = {#1}% \message{(\the\toks0)}% % \chapmacro{#1}{Ynothing}{\the\unnumberedno}% % \global\let\section = \unnumberedsec \global\let\subsection = \unnumberedsubsec \global\let\subsubsection = \unnumberedsubsubsec } % @centerchap is like @unnumbered, but the heading is centered. \outer\parseargdef\centerchap{% % Well, we could do the following in a group, but that would break % an assumption that \chapmacro is called at the outermost level. % Thus we are safer this way: --kasal, 24feb04 \let\centerparametersmaybe = \centerparameters \unnmhead0{#1}% \let\centerparametersmaybe = \relax } % @top is like @unnumbered. \let\top\unnumbered % Sections. % \outer\parseargdef\numberedsec{\numhead1{#1}} % normally calls seczzz \def\seczzz#1{% \global\subsecno=0 \global\subsubsecno=0 \global\advance\secno by 1 \sectionheading{#1}{sec}{Ynumbered}{\the\chapno.\the\secno}% } % normally calls appendixsectionzzz: \outer\parseargdef\appendixsection{\apphead1{#1}} \def\appendixsectionzzz#1{% \global\subsecno=0 \global\subsubsecno=0 \global\advance\secno by 1 \sectionheading{#1}{sec}{Yappendix}{\appendixletter.\the\secno}% } \let\appendixsec\appendixsection % normally calls unnumberedseczzz: \outer\parseargdef\unnumberedsec{\unnmhead1{#1}} \def\unnumberedseczzz#1{% \global\subsecno=0 \global\subsubsecno=0 \global\advance\secno by 1 \sectionheading{#1}{sec}{Ynothing}{\the\unnumberedno.\the\secno}% } % Subsections. % % normally calls numberedsubseczzz: \outer\parseargdef\numberedsubsec{\numhead2{#1}} \def\numberedsubseczzz#1{% \global\subsubsecno=0 \global\advance\subsecno by 1 \sectionheading{#1}{subsec}{Ynumbered}{\the\chapno.\the\secno.\the\subsecno}% } % normally calls appendixsubseczzz: \outer\parseargdef\appendixsubsec{\apphead2{#1}} \def\appendixsubseczzz#1{% \global\subsubsecno=0 \global\advance\subsecno by 1 \sectionheading{#1}{subsec}{Yappendix}% {\appendixletter.\the\secno.\the\subsecno}% } % normally calls unnumberedsubseczzz: \outer\parseargdef\unnumberedsubsec{\unnmhead2{#1}} \def\unnumberedsubseczzz#1{% \global\subsubsecno=0 \global\advance\subsecno by 1 \sectionheading{#1}{subsec}{Ynothing}% {\the\unnumberedno.\the\secno.\the\subsecno}% } % Subsubsections. % % normally numberedsubsubseczzz: \outer\parseargdef\numberedsubsubsec{\numhead3{#1}} \def\numberedsubsubseczzz#1{% \global\advance\subsubsecno by 1 \sectionheading{#1}{subsubsec}{Ynumbered}% {\the\chapno.\the\secno.\the\subsecno.\the\subsubsecno}% } % normally appendixsubsubseczzz: \outer\parseargdef\appendixsubsubsec{\apphead3{#1}} \def\appendixsubsubseczzz#1{% \global\advance\subsubsecno by 1 \sectionheading{#1}{subsubsec}{Yappendix}% {\appendixletter.\the\secno.\the\subsecno.\the\subsubsecno}% } % normally unnumberedsubsubseczzz: \outer\parseargdef\unnumberedsubsubsec{\unnmhead3{#1}} \def\unnumberedsubsubseczzz#1{% \global\advance\subsubsecno by 1 \sectionheading{#1}{subsubsec}{Ynothing}% {\the\unnumberedno.\the\secno.\the\subsecno.\the\subsubsecno}% } % These macros control what the section commands do, according % to what kind of chapter we are in (ordinary, appendix, or unnumbered). % Define them by default for a numbered chapter. \let\section = \numberedsec \let\subsection = \numberedsubsec \let\subsubsection = \numberedsubsubsec % Define @majorheading, @heading and @subheading % NOTE on use of \vbox for chapter headings, section headings, and such: % 1) We use \vbox rather than the earlier \line to permit % overlong headings to fold. % 2) \hyphenpenalty is set to 10000 because hyphenation in a % heading is obnoxious; this forbids it. % 3) Likewise, headings look best if no \parindent is used, and % if justification is not attempted. Hence \raggedright. \def\majorheading{% {\advance\chapheadingskip by 10pt \chapbreak }% \parsearg\chapheadingzzz } \def\chapheading{\chapbreak \parsearg\chapheadingzzz} \def\chapheadingzzz#1{% {\chapfonts \vbox{\hyphenpenalty=10000\tolerance=5000 \parindent=0pt\ptexraggedright \rmisbold #1\hfill}}% \bigskip \par\penalty 200\relax \suppressfirstparagraphindent } % @heading, @subheading, @subsubheading. \parseargdef\heading{\sectionheading{#1}{sec}{Yomitfromtoc}{} \suppressfirstparagraphindent} \parseargdef\subheading{\sectionheading{#1}{subsec}{Yomitfromtoc}{} \suppressfirstparagraphindent} \parseargdef\subsubheading{\sectionheading{#1}{subsubsec}{Yomitfromtoc}{} \suppressfirstparagraphindent} % These macros generate a chapter, section, etc. heading only % (including whitespace, linebreaking, etc. around it), % given all the information in convenient, parsed form. % Args are the skip and penalty (usually negative) \def\dobreak#1#2{\par\ifdim\lastskip<#1\removelastskip\penalty#2\vskip#1\fi} % Parameter controlling skip before chapter headings (if needed) \newskip\chapheadingskip % Define plain chapter starts, and page on/off switching for it. \def\chapbreak{\dobreak \chapheadingskip {-4000}} \def\chappager{\par\vfill\supereject} % Because \domark is called before \chapoddpage, the filler page will % get the headings for the next chapter, which is wrong. But we don't % care -- we just disable all headings on the filler page. \def\chapoddpage{% \chappager \ifodd\pageno \else \begingroup \headingsoff \null \chappager \endgroup \fi } \def\setchapternewpage #1 {\csname CHAPPAG#1\endcsname} \def\CHAPPAGoff{% \global\let\contentsalignmacro = \chappager \global\let\pchapsepmacro=\chapbreak \global\let\pagealignmacro=\chappager} \def\CHAPPAGon{% \global\let\contentsalignmacro = \chappager \global\let\pchapsepmacro=\chappager \global\let\pagealignmacro=\chappager \global\def\HEADINGSon{\HEADINGSsingle}} \def\CHAPPAGodd{% \global\let\contentsalignmacro = \chapoddpage \global\let\pchapsepmacro=\chapoddpage \global\let\pagealignmacro=\chapoddpage \global\def\HEADINGSon{\HEADINGSdouble}} \CHAPPAGon % Chapter opening. % % #1 is the text, #2 is the section type (Ynumbered, Ynothing, % Yappendix, Yomitfromtoc), #3 the chapter number. % % To test against our argument. \def\Ynothingkeyword{Ynothing} \def\Yomitfromtockeyword{Yomitfromtoc} \def\Yappendixkeyword{Yappendix} % \def\chapmacro#1#2#3{% % Insert the first mark before the heading break (see notes for \domark). \let\prevchapterdefs=\lastchapterdefs \let\prevsectiondefs=\lastsectiondefs \gdef\lastsectiondefs{\gdef\thissectionname{}\gdef\thissectionnum{}% \gdef\thissection{}}% % \def\temptype{#2}% \ifx\temptype\Ynothingkeyword \gdef\lastchapterdefs{\gdef\thischaptername{#1}\gdef\thischapternum{}% \gdef\thischapter{\thischaptername}}% \else\ifx\temptype\Yomitfromtockeyword \gdef\lastchapterdefs{\gdef\thischaptername{#1}\gdef\thischapternum{}% \gdef\thischapter{}}% \else\ifx\temptype\Yappendixkeyword \toks0={#1}% \xdef\lastchapterdefs{% \gdef\noexpand\thischaptername{\the\toks0}% \gdef\noexpand\thischapternum{\appendixletter}% % \noexpand\putwordAppendix avoids expanding indigestible % commands in some of the translations. \gdef\noexpand\thischapter{\noexpand\putwordAppendix{} \noexpand\thischapternum: \noexpand\thischaptername}% }% \else \toks0={#1}% \xdef\lastchapterdefs{% \gdef\noexpand\thischaptername{\the\toks0}% \gdef\noexpand\thischapternum{\the\chapno}% % \noexpand\putwordChapter avoids expanding indigestible % commands in some of the translations. \gdef\noexpand\thischapter{\noexpand\putwordChapter{} \noexpand\thischapternum: \noexpand\thischaptername}% }% \fi\fi\fi % % Output the mark. Pass it through \safewhatsit, to take care of % the preceding space. \safewhatsit\domark % % Insert the chapter heading break. \pchapsepmacro % % Now the second mark, after the heading break. No break points % between here and the heading. \let\prevchapterdefs=\lastchapterdefs \let\prevsectiondefs=\lastsectiondefs \domark % {% \chapfonts \rmisbold % % Have to define \lastsection before calling \donoderef, because the % xref code eventually uses it. On the other hand, it has to be called % after \pchapsepmacro, or the headline will change too soon. \gdef\lastsection{#1}% % % Only insert the separating space if we have a chapter/appendix % number, and don't print the unnumbered ``number''. \ifx\temptype\Ynothingkeyword \setbox0 = \hbox{}% \def\toctype{unnchap}% \else\ifx\temptype\Yomitfromtockeyword \setbox0 = \hbox{}% contents like unnumbered, but no toc entry \def\toctype{omit}% \else\ifx\temptype\Yappendixkeyword \setbox0 = \hbox{\putwordAppendix{} #3\enspace}% \def\toctype{app}% \else \setbox0 = \hbox{#3\enspace}% \def\toctype{numchap}% \fi\fi\fi % % Write the toc entry for this chapter. Must come before the % \donoderef, because we include the current node name in the toc % entry, and \donoderef resets it to empty. \writetocentry{\toctype}{#1}{#3}% % % For pdftex, we have to write out the node definition (aka, make % the pdfdest) after any page break, but before the actual text has % been typeset. If the destination for the pdf outline is after the % text, then jumping from the outline may wind up with the text not % being visible, for instance under high magnification. \donoderef{#2}% % % Typeset the actual heading. \nobreak % Avoid page breaks at the interline glue. \vbox{\hyphenpenalty=10000 \tolerance=5000 \parindent=0pt \ptexraggedright \hangindent=\wd0 \centerparametersmaybe \unhbox0 #1\par}% }% \nobreak\bigskip % no page break after a chapter title \nobreak } % @centerchap -- centered and unnumbered. \let\centerparametersmaybe = \relax \def\centerparameters{% \advance\rightskip by 3\rightskip \leftskip = \rightskip \parfillskip = 0pt } % I don't think this chapter style is supported any more, so I'm not % updating it with the new noderef stuff. We'll see. --karl, 11aug03. % \def\setchapterstyle #1 {\csname CHAPF#1\endcsname} % \def\unnchfopen #1{% \chapoddpage {\chapfonts \vbox{\hyphenpenalty=10000\tolerance=5000 \parindent=0pt\ptexraggedright \rmisbold #1\hfill}}\bigskip \par\nobreak } \def\chfopen #1#2{\chapoddpage {\chapfonts \vbox to 3in{\vfil \hbox to\hsize{\hfil #2} \hbox to\hsize{\hfil #1} \vfil}}% \par\penalty 5000 % } \def\centerchfopen #1{% \chapoddpage {\chapfonts \vbox{\hyphenpenalty=10000\tolerance=5000 \parindent=0pt \hfill {\rmisbold #1}\hfill}}\bigskip \par\nobreak } \def\CHAPFopen{% \global\let\chapmacro=\chfopen \global\let\centerchapmacro=\centerchfopen} % Section titles. These macros combine the section number parts and % call the generic \sectionheading to do the printing. % \newskip\secheadingskip \def\secheadingbreak{\dobreak \secheadingskip{-1000}} % Subsection titles. \newskip\subsecheadingskip \def\subsecheadingbreak{\dobreak \subsecheadingskip{-500}} % Subsubsection titles. \def\subsubsecheadingskip{\subsecheadingskip} \def\subsubsecheadingbreak{\subsecheadingbreak} % Print any size, any type, section title. % % #1 is the text, #2 is the section level (sec/subsec/subsubsec), #3 is % the section type for xrefs (Ynumbered, Ynothing, Yappendix), #4 is the % section number. % \def\seckeyword{sec} % \def\sectionheading#1#2#3#4{% {% \checkenv{}% should not be in an environment. % % Switch to the right set of fonts. \csname #2fonts\endcsname \rmisbold % \def\sectionlevel{#2}% \def\temptype{#3}% % % Insert first mark before the heading break (see notes for \domark). \let\prevsectiondefs=\lastsectiondefs \ifx\temptype\Ynothingkeyword \ifx\sectionlevel\seckeyword \gdef\lastsectiondefs{\gdef\thissectionname{#1}\gdef\thissectionnum{}% \gdef\thissection{\thissectionname}}% \fi \else\ifx\temptype\Yomitfromtockeyword % Don't redefine \thissection. \else\ifx\temptype\Yappendixkeyword \ifx\sectionlevel\seckeyword \toks0={#1}% \xdef\lastsectiondefs{% \gdef\noexpand\thissectionname{\the\toks0}% \gdef\noexpand\thissectionnum{#4}% % \noexpand\putwordSection avoids expanding indigestible % commands in some of the translations. \gdef\noexpand\thissection{\noexpand\putwordSection{} \noexpand\thissectionnum: \noexpand\thissectionname}% }% \fi \else \ifx\sectionlevel\seckeyword \toks0={#1}% \xdef\lastsectiondefs{% \gdef\noexpand\thissectionname{\the\toks0}% \gdef\noexpand\thissectionnum{#4}% % \noexpand\putwordSection avoids expanding indigestible % commands in some of the translations. \gdef\noexpand\thissection{\noexpand\putwordSection{} \noexpand\thissectionnum: \noexpand\thissectionname}% }% \fi \fi\fi\fi % % Go into vertical mode. Usually we'll already be there, but we % don't want the following whatsit to end up in a preceding paragraph % if the document didn't happen to have a blank line. \par % % Output the mark. Pass it through \safewhatsit, to take care of % the preceding space. \safewhatsit\domark % % Insert space above the heading. \csname #2headingbreak\endcsname % % Now the second mark, after the heading break. No break points % between here and the heading. \let\prevsectiondefs=\lastsectiondefs \domark % % Only insert the space after the number if we have a section number. \ifx\temptype\Ynothingkeyword \setbox0 = \hbox{}% \def\toctype{unn}% \gdef\lastsection{#1}% \else\ifx\temptype\Yomitfromtockeyword % for @headings -- no section number, don't include in toc, % and don't redefine \lastsection. \setbox0 = \hbox{}% \def\toctype{omit}% \let\sectionlevel=\empty \else\ifx\temptype\Yappendixkeyword \setbox0 = \hbox{#4\enspace}% \def\toctype{app}% \gdef\lastsection{#1}% \else \setbox0 = \hbox{#4\enspace}% \def\toctype{num}% \gdef\lastsection{#1}% \fi\fi\fi % % Write the toc entry (before \donoderef). See comments in \chapmacro. \writetocentry{\toctype\sectionlevel}{#1}{#4}% % % Write the node reference (= pdf destination for pdftex). % Again, see comments in \chapmacro. \donoderef{#3}% % % Interline glue will be inserted when the vbox is completed. % That glue will be a valid breakpoint for the page, since it'll be % preceded by a whatsit (usually from the \donoderef, or from the % \writetocentry if there was no node). We don't want to allow that % break, since then the whatsits could end up on page n while the % section is on page n+1, thus toc/etc. are wrong. Debian bug 276000. \nobreak % % Output the actual section heading. \vbox{\hyphenpenalty=10000 \tolerance=5000 \parindent=0pt \ptexraggedright \hangindent=\wd0 % zero if no section number \unhbox0 #1}% }% % Add extra space after the heading -- half of whatever came above it. % Don't allow stretch, though. \kern .5 \csname #2headingskip\endcsname % % Do not let the kern be a potential breakpoint, as it would be if it % was followed by glue. \nobreak % % We'll almost certainly start a paragraph next, so don't let that % glue accumulate. (Not a breakpoint because it's preceded by a % discardable item.) However, when a paragraph is not started next % (\startdefun, \cartouche, \center, etc.), this needs to be wiped out % or the negative glue will cause weirdly wrong output, typically % obscuring the section heading with something else. \vskip-\parskip % % This is so the last item on the main vertical list is a known % \penalty > 10000, so \startdefun, etc., can recognize the situation % and do the needful. \penalty 10001 } \message{toc,} % Table of contents. \newwrite\tocfile % Write an entry to the toc file, opening it if necessary. % Called from @chapter, etc. % % Example usage: \writetocentry{sec}{Section Name}{\the\chapno.\the\secno} % We append the current node name (if any) and page number as additional % arguments for the \{chap,sec,...}entry macros which will eventually % read this. The node name is used in the pdf outlines as the % destination to jump to. % % We open the .toc file for writing here instead of at @setfilename (or % any other fixed time) so that @contents can be anywhere in the document. % But if #1 is `omit', then we don't do anything. This is used for the % table of contents chapter openings themselves. % \newif\iftocfileopened \def\omitkeyword{omit}% % \def\writetocentry#1#2#3{% \edef\writetoctype{#1}% \ifx\writetoctype\omitkeyword \else \iftocfileopened\else \immediate\openout\tocfile = \jobname.toc \global\tocfileopenedtrue \fi % \iflinks {\atdummies \edef\temp{% \write\tocfile{@#1entry{#2}{#3}{\lastnode}{\noexpand\folio}}}% \temp }% \fi \fi % % Tell \shipout to create a pdf destination on each page, if we're % writing pdf. These are used in the table of contents. We can't % just write one on every page because the title pages are numbered % 1 and 2 (the page numbers aren't printed), and so are the first % two pages of the document. Thus, we'd have two destinations named % `1', and two named `2'. \ifpdf \global\pdfmakepagedesttrue \fi } % These characters do not print properly in the Computer Modern roman % fonts, so we must take special care. This is more or less redundant % with the Texinfo input format setup at the end of this file. % \def\activecatcodes{% \catcode`\"=\active \catcode`\$=\active \catcode`\<=\active \catcode`\>=\active \catcode`\\=\active \catcode`\^=\active \catcode`\_=\active \catcode`\|=\active \catcode`\~=\active } % Read the toc file, which is essentially Texinfo input. \def\readtocfile{% \setupdatafile \activecatcodes \input \tocreadfilename } \newskip\contentsrightmargin \contentsrightmargin=1in \newcount\savepageno \newcount\lastnegativepageno \lastnegativepageno = -1 % Prepare to read what we've written to \tocfile. % \def\startcontents#1{% % If @setchapternewpage on, and @headings double, the contents should % start on an odd page, unlike chapters. Thus, we maintain % \contentsalignmacro in parallel with \pagealignmacro. % From: Torbjorn Granlund \contentsalignmacro \immediate\closeout\tocfile % % Don't need to put `Contents' or `Short Contents' in the headline. % It is abundantly clear what they are. \chapmacro{#1}{Yomitfromtoc}{}% % \savepageno = \pageno \begingroup % Set up to handle contents files properly. \raggedbottom % Worry more about breakpoints than the bottom. \advance\hsize by -\contentsrightmargin % Don't use the full line length. % % Roman numerals for page numbers. \ifnum \pageno>0 \global\pageno = \lastnegativepageno \fi } % redefined for the two-volume lispref. We always output on % \jobname.toc even if this is redefined. % \def\tocreadfilename{\jobname.toc} % Normal (long) toc. % \def\contents{% \startcontents{\putwordTOC}% \openin 1 \tocreadfilename\space \ifeof 1 \else \readtocfile \fi \vfill \eject \contentsalignmacro % in case @setchapternewpage odd is in effect \ifeof 1 \else \pdfmakeoutlines \fi \closein 1 \endgroup \lastnegativepageno = \pageno \global\pageno = \savepageno } % And just the chapters. \def\summarycontents{% \startcontents{\putwordShortTOC}% % \let\partentry = \shortpartentry \let\numchapentry = \shortchapentry \let\appentry = \shortchapentry \let\unnchapentry = \shortunnchapentry % We want a true roman here for the page numbers. \secfonts \let\rm=\shortcontrm \let\bf=\shortcontbf \let\sl=\shortcontsl \let\tt=\shortconttt \rm \hyphenpenalty = 10000 \advance\baselineskip by 1pt % Open it up a little. \def\numsecentry##1##2##3##4{} \let\appsecentry = \numsecentry \let\unnsecentry = \numsecentry \let\numsubsecentry = \numsecentry \let\appsubsecentry = \numsecentry \let\unnsubsecentry = \numsecentry \let\numsubsubsecentry = \numsecentry \let\appsubsubsecentry = \numsecentry \let\unnsubsubsecentry = \numsecentry \openin 1 \tocreadfilename\space \ifeof 1 \else \readtocfile \fi \closein 1 \vfill \eject \contentsalignmacro % in case @setchapternewpage odd is in effect \endgroup \lastnegativepageno = \pageno \global\pageno = \savepageno } \let\shortcontents = \summarycontents % Typeset the label for a chapter or appendix for the short contents. % The arg is, e.g., `A' for an appendix, or `3' for a chapter. % \def\shortchaplabel#1{% % This space should be enough, since a single number is .5em, and the % widest letter (M) is 1em, at least in the Computer Modern fonts. % But use \hss just in case. % (This space doesn't include the extra space that gets added after % the label; that gets put in by \shortchapentry above.) % % We'd like to right-justify chapter numbers, but that looks strange % with appendix letters. And right-justifying numbers and % left-justifying letters looks strange when there is less than 10 % chapters. Have to read the whole toc once to know how many chapters % there are before deciding ... \hbox to 1em{#1\hss}% } % These macros generate individual entries in the table of contents. % The first argument is the chapter or section name. % The last argument is the page number. % The arguments in between are the chapter number, section number, ... % Parts, in the main contents. Replace the part number, which doesn't % exist, with an empty box. Let's hope all the numbers have the same width. % Also ignore the page number, which is conventionally not printed. \def\numeralbox{\setbox0=\hbox{8}\hbox to \wd0{\hfil}} \def\partentry#1#2#3#4{\dochapentry{\numeralbox\labelspace#1}{}} % % Parts, in the short toc. \def\shortpartentry#1#2#3#4{% \penalty-300 \vskip.5\baselineskip plus.15\baselineskip minus.1\baselineskip \shortchapentry{{\bf #1}}{\numeralbox}{}{}% } % Chapters, in the main contents. \def\numchapentry#1#2#3#4{\dochapentry{#2\labelspace#1}{#4}} % % Chapters, in the short toc. % See comments in \dochapentry re vbox and related settings. \def\shortchapentry#1#2#3#4{% \tocentry{\shortchaplabel{#2}\labelspace #1}{\doshortpageno\bgroup#4\egroup}% } % Appendices, in the main contents. % Need the word Appendix, and a fixed-size box. % \def\appendixbox#1{% % We use M since it's probably the widest letter. \setbox0 = \hbox{\putwordAppendix{} M}% \hbox to \wd0{\putwordAppendix{} #1\hss}} % \def\appentry#1#2#3#4{\dochapentry{\appendixbox{#2}\labelspace#1}{#4}} % Unnumbered chapters. \def\unnchapentry#1#2#3#4{\dochapentry{#1}{#4}} \def\shortunnchapentry#1#2#3#4{\tocentry{#1}{\doshortpageno\bgroup#4\egroup}} % Sections. \def\numsecentry#1#2#3#4{\dosecentry{#2\labelspace#1}{#4}} \let\appsecentry=\numsecentry \def\unnsecentry#1#2#3#4{\dosecentry{#1}{#4}} % Subsections. \def\numsubsecentry#1#2#3#4{\dosubsecentry{#2\labelspace#1}{#4}} \let\appsubsecentry=\numsubsecentry \def\unnsubsecentry#1#2#3#4{\dosubsecentry{#1}{#4}} % And subsubsections. \def\numsubsubsecentry#1#2#3#4{\dosubsubsecentry{#2\labelspace#1}{#4}} \let\appsubsubsecentry=\numsubsubsecentry \def\unnsubsubsecentry#1#2#3#4{\dosubsubsecentry{#1}{#4}} % This parameter controls the indentation of the various levels. % Same as \defaultparindent. \newdimen\tocindent \tocindent = 15pt % Now for the actual typesetting. In all these, #1 is the text and #2 is the % page number. % % If the toc has to be broken over pages, we want it to be at chapters % if at all possible; hence the \penalty. \def\dochapentry#1#2{% \penalty-300 \vskip1\baselineskip plus.33\baselineskip minus.25\baselineskip \begingroup \chapentryfonts \tocentry{#1}{\dopageno\bgroup#2\egroup}% \endgroup \nobreak\vskip .25\baselineskip plus.1\baselineskip } \def\dosecentry#1#2{\begingroup \secentryfonts \leftskip=\tocindent \tocentry{#1}{\dopageno\bgroup#2\egroup}% \endgroup} \def\dosubsecentry#1#2{\begingroup \subsecentryfonts \leftskip=2\tocindent \tocentry{#1}{\dopageno\bgroup#2\egroup}% \endgroup} \def\dosubsubsecentry#1#2{\begingroup \subsubsecentryfonts \leftskip=3\tocindent \tocentry{#1}{\dopageno\bgroup#2\egroup}% \endgroup} % We use the same \entry macro as for the index entries. \let\tocentry = \entry % Space between chapter (or whatever) number and the title. \def\labelspace{\hskip1em \relax} \def\dopageno#1{{\rm #1}} \def\doshortpageno#1{{\rm #1}} \def\chapentryfonts{\secfonts \rm} \def\secentryfonts{\textfonts} \def\subsecentryfonts{\textfonts} \def\subsubsecentryfonts{\textfonts} \message{environments,} % @foo ... @end foo. % @tex ... @end tex escapes into raw TeX temporarily. % One exception: @ is still an escape character, so that @end tex works. % But \@ or @@ will get a plain @ character. \envdef\tex{% \setupmarkupstyle{tex}% \catcode `\\=0 \catcode `\{=1 \catcode `\}=2 \catcode `\$=3 \catcode `\&=4 \catcode `\#=6 \catcode `\^=7 \catcode `\_=8 \catcode `\~=\active \let~=\tie \catcode `\%=14 \catcode `\+=\other \catcode `\"=\other \catcode `\|=\other \catcode `\<=\other \catcode `\>=\other \catcode`\`=\other \catcode`\'=\other \escapechar=`\\ % % ' is active in math mode (mathcode"8000). So reset it, and all our % other math active characters (just in case), to plain's definitions. \mathactive % \let\b=\ptexb \let\bullet=\ptexbullet \let\c=\ptexc \let\,=\ptexcomma \let\.=\ptexdot \let\dots=\ptexdots \let\equiv=\ptexequiv \let\!=\ptexexclam \let\i=\ptexi \let\indent=\ptexindent \let\noindent=\ptexnoindent \let\{=\ptexlbrace \let\+=\tabalign \let\}=\ptexrbrace \let\/=\ptexslash \let\*=\ptexstar \let\t=\ptext \expandafter \let\csname top\endcsname=\ptextop % outer \let\frenchspacing=\plainfrenchspacing % \def\endldots{\mathinner{\ldots\ldots\ldots\ldots}}% \def\enddots{\relax\ifmmode\endldots\else$\mathsurround=0pt \endldots\,$\fi}% \def\@{@}% } % There is no need to define \Etex. % Define @lisp ... @end lisp. % @lisp environment forms a group so it can rebind things, % including the definition of @end lisp (which normally is erroneous). % Amount to narrow the margins by for @lisp. \newskip\lispnarrowing \lispnarrowing=0.4in % This is the definition that ^^M gets inside @lisp, @example, and other % such environments. \null is better than a space, since it doesn't % have any width. \def\lisppar{\null\endgraf} % This space is always present above and below environments. \newskip\envskipamount \envskipamount = 0pt % Make spacing and below environment symmetrical. We use \parskip here % to help in doing that, since in @example-like environments \parskip % is reset to zero; thus the \afterenvbreak inserts no space -- but the % start of the next paragraph will insert \parskip. % \def\aboveenvbreak{{% % =10000 instead of <10000 because of a special case in \itemzzz and % \sectionheading, q.v. \ifnum \lastpenalty=10000 \else \advance\envskipamount by \parskip \endgraf \ifdim\lastskip<\envskipamount \removelastskip % it's not a good place to break if the last penalty was \nobreak % or better ... \ifnum\lastpenalty<10000 \penalty-50 \fi \vskip\envskipamount \fi \fi }} \let\afterenvbreak = \aboveenvbreak % \nonarrowing is a flag. If "set", @lisp etc don't narrow margins; it will % also clear it, so that its embedded environments do the narrowing again. \let\nonarrowing=\relax % @cartouche ... @end cartouche: draw rectangle w/rounded corners around % environment contents. \font\circle=lcircle10 \newdimen\circthick \newdimen\cartouter\newdimen\cartinner \newskip\normbskip\newskip\normpskip\newskip\normlskip \circthick=\fontdimen8\circle % \def\ctl{{\circle\char'013\hskip -6pt}}% 6pt from pl file: 1/2charwidth \def\ctr{{\hskip 6pt\circle\char'010}} \def\cbl{{\circle\char'012\hskip -6pt}} \def\cbr{{\hskip 6pt\circle\char'011}} \def\carttop{\hbox to \cartouter{\hskip\lskip \ctl\leaders\hrule height\circthick\hfil\ctr \hskip\rskip}} \def\cartbot{\hbox to \cartouter{\hskip\lskip \cbl\leaders\hrule height\circthick\hfil\cbr \hskip\rskip}} % \newskip\lskip\newskip\rskip \envdef\cartouche{% \ifhmode\par\fi % can't be in the midst of a paragraph. \startsavinginserts \lskip=\leftskip \rskip=\rightskip \leftskip=0pt\rightskip=0pt % we want these *outside*. \cartinner=\hsize \advance\cartinner by-\lskip \advance\cartinner by-\rskip \cartouter=\hsize \advance\cartouter by 18.4pt % allow for 3pt kerns on either % side, and for 6pt waste from % each corner char, and rule thickness \normbskip=\baselineskip \normpskip=\parskip \normlskip=\lineskip % Flag to tell @lisp, etc., not to narrow margin. \let\nonarrowing = t% % % If this cartouche directly follows a sectioning command, we need the % \parskip glue (backspaced over by default) or the cartouche can % collide with the section heading. \ifnum\lastpenalty>10000 \vskip\parskip \penalty\lastpenalty \fi % \vbox\bgroup \baselineskip=0pt\parskip=0pt\lineskip=0pt \carttop \hbox\bgroup \hskip\lskip \vrule\kern3pt \vbox\bgroup \kern3pt \hsize=\cartinner \baselineskip=\normbskip \lineskip=\normlskip \parskip=\normpskip \vskip -\parskip \comment % For explanation, see the end of def\group. } \def\Ecartouche{% \ifhmode\par\fi \kern3pt \egroup \kern3pt\vrule \hskip\rskip \egroup \cartbot \egroup \checkinserts } % This macro is called at the beginning of all the @example variants, % inside a group. \newdimen\nonfillparindent \def\nonfillstart{% \aboveenvbreak \hfuzz = 12pt % Don't be fussy \sepspaces % Make spaces be word-separators rather than space tokens. \let\par = \lisppar % don't ignore blank lines \obeylines % each line of input is a line of output \parskip = 0pt % Turn off paragraph indentation but redefine \indent to emulate % the normal \indent. \nonfillparindent=\parindent \parindent = 0pt \let\indent\nonfillindent % \emergencystretch = 0pt % don't try to avoid overfull boxes \ifx\nonarrowing\relax \advance \leftskip by \lispnarrowing \exdentamount=\lispnarrowing \else \let\nonarrowing = \relax \fi \let\exdent=\nofillexdent } \begingroup \obeyspaces % We want to swallow spaces (but not other tokens) after the fake % @indent in our nonfill-environments, where spaces are normally % active and set to @tie, resulting in them not being ignored after % @indent. \gdef\nonfillindent{\futurelet\temp\nonfillindentcheck}% \gdef\nonfillindentcheck{% \ifx\temp % \expandafter\nonfillindentgobble% \else% \leavevmode\nonfillindentbox% \fi% }% \endgroup \def\nonfillindentgobble#1{\nonfillindent} \def\nonfillindentbox{\hbox to \nonfillparindent{\hss}} % If you want all examples etc. small: @set dispenvsize small. % If you want even small examples the full size: @set dispenvsize nosmall. % This affects the following displayed environments: % @example, @display, @format, @lisp % \def\smallword{small} \def\nosmallword{nosmall} \let\SETdispenvsize\relax \def\setnormaldispenv{% \ifx\SETdispenvsize\smallword % end paragraph for sake of leading, in case document has no blank % line. This is redundant with what happens in \aboveenvbreak, but % we need to do it before changing the fonts, and it's inconvenient % to change the fonts afterward. \ifnum \lastpenalty=10000 \else \endgraf \fi \smallexamplefonts \rm \fi } \def\setsmalldispenv{% \ifx\SETdispenvsize\nosmallword \else \ifnum \lastpenalty=10000 \else \endgraf \fi \smallexamplefonts \rm \fi } % We often define two environments, @foo and @smallfoo. % Let's do it in one command. #1 is the env name, #2 the definition. \def\makedispenvdef#1#2{% \expandafter\envdef\csname#1\endcsname {\setnormaldispenv #2}% \expandafter\envdef\csname small#1\endcsname {\setsmalldispenv #2}% \expandafter\let\csname E#1\endcsname \afterenvbreak \expandafter\let\csname Esmall#1\endcsname \afterenvbreak } % Define two environment synonyms (#1 and #2) for an environment. \def\maketwodispenvdef#1#2#3{% \makedispenvdef{#1}{#3}% \makedispenvdef{#2}{#3}% } % % @lisp: indented, narrowed, typewriter font; % @example: same as @lisp. % % @smallexample and @smalllisp: use smaller fonts. % Originally contributed by Pavel@xerox. % \maketwodispenvdef{lisp}{example}{% \nonfillstart \tt\setupmarkupstyle{example}% \let\kbdfont = \kbdexamplefont % Allow @kbd to do something special. \gobble % eat return } % @display/@smalldisplay: same as @lisp except keep current font. % \makedispenvdef{display}{% \nonfillstart \gobble } % @format/@smallformat: same as @display except don't narrow margins. % \makedispenvdef{format}{% \let\nonarrowing = t% \nonfillstart \gobble } % @flushleft: same as @format, but doesn't obey \SETdispenvsize. \envdef\flushleft{% \let\nonarrowing = t% \nonfillstart \gobble } \let\Eflushleft = \afterenvbreak % @flushright. % \envdef\flushright{% \let\nonarrowing = t% \nonfillstart \advance\leftskip by 0pt plus 1fill\relax \gobble } \let\Eflushright = \afterenvbreak % @raggedright does more-or-less normal line breaking but no right % justification. From plain.tex. \envdef\raggedright{% \rightskip0pt plus2em \spaceskip.3333em \xspaceskip.5em\relax } \let\Eraggedright\par \envdef\raggedleft{% \parindent=0pt \leftskip0pt plus2em \spaceskip.3333em \xspaceskip.5em \parfillskip=0pt \hbadness=10000 % Last line will usually be underfull, so turn off % badness reporting. } \let\Eraggedleft\par \envdef\raggedcenter{% \parindent=0pt \rightskip0pt plus1em \leftskip0pt plus1em \spaceskip.3333em \xspaceskip.5em \parfillskip=0pt \hbadness=10000 % Last line will usually be underfull, so turn off % badness reporting. } \let\Eraggedcenter\par % @quotation does normal linebreaking (hence we can't use \nonfillstart) % and narrows the margins. We keep \parskip nonzero in general, since % we're doing normal filling. So, when using \aboveenvbreak and % \afterenvbreak, temporarily make \parskip 0. % \makedispenvdef{quotation}{\quotationstart} % \def\quotationstart{% {\parskip=0pt \aboveenvbreak}% because \aboveenvbreak inserts \parskip \parindent=0pt % % @cartouche defines \nonarrowing to inhibit narrowing at next level down. \ifx\nonarrowing\relax \advance\leftskip by \lispnarrowing \advance\rightskip by \lispnarrowing \exdentamount = \lispnarrowing \else \let\nonarrowing = \relax \fi \parsearg\quotationlabel } % We have retained a nonzero parskip for the environment, since we're % doing normal filling. % \def\Equotation{% \par \ifx\quotationauthor\thisisundefined\else % indent a bit. \leftline{\kern 2\leftskip \sl ---\quotationauthor}% \fi {\parskip=0pt \afterenvbreak}% } \def\Esmallquotation{\Equotation} % If we're given an argument, typeset it in bold with a colon after. \def\quotationlabel#1{% \def\temp{#1}% \ifx\temp\empty \else {\bf #1: }% \fi } % LaTeX-like @verbatim...@end verbatim and @verb{...} % If we want to allow any as delimiter, % we need the curly braces so that makeinfo sees the @verb command, eg: % `@verbx...x' would look like the '@verbx' command. --janneke@gnu.org % % [Knuth]: Donald Ervin Knuth, 1996. The TeXbook. % % [Knuth] p.344; only we need to do the other characters Texinfo sets % active too. Otherwise, they get lost as the first character on a % verbatim line. \def\dospecials{% \do\ \do\\\do\{\do\}\do\$\do\&% \do\#\do\^\do\^^K\do\_\do\^^A\do\%\do\~% \do\<\do\>\do\|\do\@\do+\do\"% % Don't do the quotes -- if we do, @set txicodequoteundirected and % @set txicodequotebacktick will not have effect on @verb and % @verbatim, and ?` and !` ligatures won't get disabled. %\do\`\do\'% } % % [Knuth] p. 380 \def\uncatcodespecials{% \def\do##1{\catcode`##1=\other}\dospecials} % % Setup for the @verb command. % % Eight spaces for a tab \begingroup \catcode`\^^I=\active \gdef\tabeightspaces{\catcode`\^^I=\active\def^^I{\ \ \ \ \ \ \ \ }} \endgroup % \def\setupverb{% \tt % easiest (and conventionally used) font for verbatim \def\par{\leavevmode\endgraf}% \setupmarkupstyle{verb}% \tabeightspaces % Respect line breaks, % print special symbols as themselves, and % make each space count % must do in this order: \obeylines \uncatcodespecials \sepspaces } % Setup for the @verbatim environment % % Real tab expansion. \newdimen\tabw \setbox0=\hbox{\tt\space} \tabw=8\wd0 % tab amount % % We typeset each line of the verbatim in an \hbox, so we can handle % tabs. The \global is in case the verbatim line starts with an accent, % or some other command that starts with a begin-group. Otherwise, the % entire \verbbox would disappear at the corresponding end-group, before % it is typeset. Meanwhile, we can't have nested verbatim commands % (can we?), so the \global won't be overwriting itself. \newbox\verbbox \def\starttabbox{\global\setbox\verbbox=\hbox\bgroup} % \begingroup \catcode`\^^I=\active \gdef\tabexpand{% \catcode`\^^I=\active \def^^I{\leavevmode\egroup \dimen\verbbox=\wd\verbbox % the width so far, or since the previous tab \divide\dimen\verbbox by\tabw \multiply\dimen\verbbox by\tabw % compute previous multiple of \tabw \advance\dimen\verbbox by\tabw % advance to next multiple of \tabw \wd\verbbox=\dimen\verbbox \box\verbbox \starttabbox }% } \endgroup % start the verbatim environment. \def\setupverbatim{% \let\nonarrowing = t% \nonfillstart \tt % easiest (and conventionally used) font for verbatim % The \leavevmode here is for blank lines. Otherwise, we would % never \starttabox and the \egroup would end verbatim mode. \def\par{\leavevmode\egroup\box\verbbox\endgraf}% \tabexpand \setupmarkupstyle{verbatim}% % Respect line breaks, % print special symbols as themselves, and % make each space count. % Must do in this order: \obeylines \uncatcodespecials \sepspaces \everypar{\starttabbox}% } % Do the @verb magic: verbatim text is quoted by unique % delimiter characters. Before first delimiter expect a % right brace, after last delimiter expect closing brace: % % \def\doverb'{'#1'}'{#1} % % [Knuth] p. 382; only eat outer {} \begingroup \catcode`[=1\catcode`]=2\catcode`\{=\other\catcode`\}=\other \gdef\doverb{#1[\def\next##1#1}[##1\endgroup]\next] \endgroup % \def\verb{\begingroup\setupverb\doverb} % % % Do the @verbatim magic: define the macro \doverbatim so that % the (first) argument ends when '@end verbatim' is reached, ie: % % \def\doverbatim#1@end verbatim{#1} % % For Texinfo it's a lot easier than for LaTeX, % because texinfo's \verbatim doesn't stop at '\end{verbatim}': % we need not redefine '\', '{' and '}'. % % Inspired by LaTeX's verbatim command set [latex.ltx] % \begingroup \catcode`\ =\active \obeylines % % ignore everything up to the first ^^M, that's the newline at the end % of the @verbatim input line itself. Otherwise we get an extra blank % line in the output. \xdef\doverbatim#1^^M#2@end verbatim{#2\noexpand\end\gobble verbatim}% % We really want {...\end verbatim} in the body of the macro, but % without the active space; thus we have to use \xdef and \gobble. \endgroup % \envdef\verbatim{% \setupverbatim\doverbatim } \let\Everbatim = \afterenvbreak % @verbatiminclude FILE - insert text of file in verbatim environment. % \def\verbatiminclude{\parseargusing\filenamecatcodes\doverbatiminclude} % \def\doverbatiminclude#1{% {% \makevalueexpandable \setupverbatim \indexnofonts % Allow `@@' and other weird things in file names. \wlog{texinfo.tex: doing @verbatiminclude of #1^^J}% \input #1 \afterenvbreak }% } % @copying ... @end copying. % Save the text away for @insertcopying later. % % We save the uninterpreted tokens, rather than creating a box. % Saving the text in a box would be much easier, but then all the % typesetting commands (@smallbook, font changes, etc.) have to be done % beforehand -- and a) we want @copying to be done first in the source % file; b) letting users define the frontmatter in as flexible order as % possible is very desirable. % \def\copying{\checkenv{}\begingroup\scanargctxt\docopying} \def\docopying#1@end copying{\endgroup\def\copyingtext{#1}} % \def\insertcopying{% \begingroup \parindent = 0pt % paragraph indentation looks wrong on title page \scanexp\copyingtext \endgroup } \message{defuns,} % @defun etc. \newskip\defbodyindent \defbodyindent=.4in \newskip\defargsindent \defargsindent=50pt \newskip\deflastargmargin \deflastargmargin=18pt \newcount\defunpenalty % Start the processing of @deffn: \def\startdefun{% \ifnum\lastpenalty<10000 \medbreak \defunpenalty=10003 % Will keep this @deffn together with the % following @def command, see below. \else % If there are two @def commands in a row, we'll have a \nobreak, % which is there to keep the function description together with its % header. But if there's nothing but headers, we need to allow a % break somewhere. Check specifically for penalty 10002, inserted % by \printdefunline, instead of 10000, since the sectioning % commands also insert a nobreak penalty, and we don't want to allow % a break between a section heading and a defun. % % As a further refinement, we avoid "club" headers by signalling % with penalty of 10003 after the very first @deffn in the % sequence (see above), and penalty of 10002 after any following % @def command. \ifnum\lastpenalty=10002 \penalty2000 \else \defunpenalty=10002 \fi % % Similarly, after a section heading, do not allow a break. % But do insert the glue. \medskip % preceded by discardable penalty, so not a breakpoint \fi % \parindent=0in \advance\leftskip by \defbodyindent \exdentamount=\defbodyindent } \def\dodefunx#1{% % First, check whether we are in the right environment: \checkenv#1% % % As above, allow line break if we have multiple x headers in a row. % It's not a great place, though. \ifnum\lastpenalty=10002 \penalty3000 \else \defunpenalty=10002 \fi % % And now, it's time to reuse the body of the original defun: \expandafter\gobbledefun#1% } \def\gobbledefun#1\startdefun{} % \printdefunline \deffnheader{text} % \def\printdefunline#1#2{% \begingroup % call \deffnheader: #1#2 \endheader % common ending: \interlinepenalty = 10000 \advance\rightskip by 0pt plus 1fil\relax \endgraf \nobreak\vskip -\parskip \penalty\defunpenalty % signal to \startdefun and \dodefunx % Some of the @defun-type tags do not enable magic parentheses, % rendering the following check redundant. But we don't optimize. \checkparencounts \endgroup } \def\Edefun{\endgraf\medbreak} % \makedefun{deffn} creates \deffn, \deffnx and \Edeffn; % the only thing remaining is to define \deffnheader. % \def\makedefun#1{% \expandafter\let\csname E#1\endcsname = \Edefun \edef\temp{\noexpand\domakedefun \makecsname{#1}\makecsname{#1x}\makecsname{#1header}}% \temp } % \domakedefun \deffn \deffnx \deffnheader % % Define \deffn and \deffnx, without parameters. % \deffnheader has to be defined explicitly. % \def\domakedefun#1#2#3{% \envdef#1{% \startdefun \doingtypefnfalse % distinguish typed functions from all else \parseargusing\activeparens{\printdefunline#3}% }% \def#2{\dodefunx#1}% \def#3% } \newif\ifdoingtypefn % doing typed function? \newif\ifrettypeownline % typeset return type on its own line? % @deftypefnnewline on|off says whether the return type of typed functions % are printed on their own line. This affects @deftypefn, @deftypefun, % @deftypeop, and @deftypemethod. % \parseargdef\deftypefnnewline{% \def\temp{#1}% \ifx\temp\onword \expandafter\let\csname SETtxideftypefnnl\endcsname = \empty \else\ifx\temp\offword \expandafter\let\csname SETtxideftypefnnl\endcsname = \relax \else \errhelp = \EMsimple \errmessage{Unknown @txideftypefnnl value `\temp', must be on|off}% \fi\fi } % Untyped functions: % @deffn category name args \makedefun{deffn}{\deffngeneral{}} % @deffn category class name args \makedefun{defop}#1 {\defopon{#1\ \putwordon}} % \defopon {category on}class name args \def\defopon#1#2 {\deffngeneral{\putwordon\ \code{#2}}{#1\ \code{#2}} } % \deffngeneral {subind}category name args % \def\deffngeneral#1#2 #3 #4\endheader{% % Remember that \dosubind{fn}{foo}{} is equivalent to \doind{fn}{foo}. \dosubind{fn}{\code{#3}}{#1}% \defname{#2}{}{#3}\magicamp\defunargs{#4\unskip}% } % Typed functions: % @deftypefn category type name args \makedefun{deftypefn}{\deftypefngeneral{}} % @deftypeop category class type name args \makedefun{deftypeop}#1 {\deftypeopon{#1\ \putwordon}} % \deftypeopon {category on}class type name args \def\deftypeopon#1#2 {\deftypefngeneral{\putwordon\ \code{#2}}{#1\ \code{#2}} } % \deftypefngeneral {subind}category type name args % \def\deftypefngeneral#1#2 #3 #4 #5\endheader{% \dosubind{fn}{\code{#4}}{#1}% \doingtypefntrue \defname{#2}{#3}{#4}\defunargs{#5\unskip}% } % Typed variables: % @deftypevr category type var args \makedefun{deftypevr}{\deftypecvgeneral{}} % @deftypecv category class type var args \makedefun{deftypecv}#1 {\deftypecvof{#1\ \putwordof}} % \deftypecvof {category of}class type var args \def\deftypecvof#1#2 {\deftypecvgeneral{\putwordof\ \code{#2}}{#1\ \code{#2}} } % \deftypecvgeneral {subind}category type var args % \def\deftypecvgeneral#1#2 #3 #4 #5\endheader{% \dosubind{vr}{\code{#4}}{#1}% \defname{#2}{#3}{#4}\defunargs{#5\unskip}% } % Untyped variables: % @defvr category var args \makedefun{defvr}#1 {\deftypevrheader{#1} {} } % @defcv category class var args \makedefun{defcv}#1 {\defcvof{#1\ \putwordof}} % \defcvof {category of}class var args \def\defcvof#1#2 {\deftypecvof{#1}#2 {} } % Types: % @deftp category name args \makedefun{deftp}#1 #2 #3\endheader{% \doind{tp}{\code{#2}}% \defname{#1}{}{#2}\defunargs{#3\unskip}% } % Remaining @defun-like shortcuts: \makedefun{defun}{\deffnheader{\putwordDeffunc} } \makedefun{defmac}{\deffnheader{\putwordDefmac} } \makedefun{defspec}{\deffnheader{\putwordDefspec} } \makedefun{deftypefun}{\deftypefnheader{\putwordDeffunc} } \makedefun{defvar}{\defvrheader{\putwordDefvar} } \makedefun{defopt}{\defvrheader{\putwordDefopt} } \makedefun{deftypevar}{\deftypevrheader{\putwordDefvar} } \makedefun{defmethod}{\defopon\putwordMethodon} \makedefun{deftypemethod}{\deftypeopon\putwordMethodon} \makedefun{defivar}{\defcvof\putwordInstanceVariableof} \makedefun{deftypeivar}{\deftypecvof\putwordInstanceVariableof} % \defname, which formats the name of the @def (not the args). % #1 is the category, such as "Function". % #2 is the return type, if any. % #3 is the function name. % % We are followed by (but not passed) the arguments, if any. % \def\defname#1#2#3{% \par % Get the values of \leftskip and \rightskip as they were outside the @def... \advance\leftskip by -\defbodyindent % % Determine if we are typesetting the return type of a typed function % on a line by itself. \rettypeownlinefalse \ifdoingtypefn % doing a typed function specifically? % then check user option for putting return type on its own line: \expandafter\ifx\csname SETtxideftypefnnl\endcsname\relax \else \rettypeownlinetrue \fi \fi % % How we'll format the category name. Putting it in brackets helps % distinguish it from the body text that may end up on the next line % just below it. \def\temp{#1}% \setbox0=\hbox{\kern\deflastargmargin \ifx\temp\empty\else [\rm\temp]\fi} % % Figure out line sizes for the paragraph shape. We'll always have at % least two. \tempnum = 2 % % The first line needs space for \box0; but if \rightskip is nonzero, % we need only space for the part of \box0 which exceeds it: \dimen0=\hsize \advance\dimen0 by -\wd0 \advance\dimen0 by \rightskip % % If doing a return type on its own line, we'll have another line. \ifrettypeownline \advance\tempnum by 1 \def\maybeshapeline{0in \hsize}% \else \def\maybeshapeline{}% \fi % % The continuations: \dimen2=\hsize \advance\dimen2 by -\defargsindent % % The final paragraph shape: \parshape \tempnum 0in \dimen0 \maybeshapeline \defargsindent \dimen2 % % Put the category name at the right margin. \noindent \hbox to 0pt{% \hfil\box0 \kern-\hsize % \hsize has to be shortened this way: \kern\leftskip % Intentionally do not respect \rightskip, since we need the space. }% % % Allow all lines to be underfull without complaint: \tolerance=10000 \hbadness=10000 \exdentamount=\defbodyindent {% % defun fonts. We use typewriter by default (used to be bold) because: % . we're printing identifiers, they should be in tt in principle. % . in languages with many accents, such as Czech or French, it's % common to leave accents off identifiers. The result looks ok in % tt, but exceedingly strange in rm. % . we don't want -- and --- to be treated as ligatures. % . this still does not fix the ?` and !` ligatures, but so far no % one has made identifiers using them :). \df \tt \def\temp{#2}% text of the return type \ifx\temp\empty\else \tclose{\temp}% typeset the return type \ifrettypeownline % put return type on its own line; prohibit line break following: \hfil\vadjust{\nobreak}\break \else \space % type on same line, so just followed by a space \fi \fi % no return type #3% output function name }% {\rm\enskip}% hskip 0.5 em of \tenrm % \boldbrax % arguments will be output next, if any. } % Print arguments in slanted roman (not ttsl), inconsistently with using % tt for the name. This is because literal text is sometimes needed in % the argument list (groff manual), and ttsl and tt are not very % distinguishable. Prevent hyphenation at `-' chars. % \def\defunargs#1{% % use sl by default (not ttsl), % tt for the names. \df \sl \hyphenchar\font=0 % % On the other hand, if an argument has two dashes (for instance), we % want a way to get ttsl. Let's try @var for that. \def\var##1{{\setupmarkupstyle{var}\ttslanted{##1}}}% #1% \sl\hyphenchar\font=45 } % We want ()&[] to print specially on the defun line. % \def\activeparens{% \catcode`\(=\active \catcode`\)=\active \catcode`\[=\active \catcode`\]=\active \catcode`\&=\active } % Make control sequences which act like normal parenthesis chars. \let\lparen = ( \let\rparen = ) % Be sure that we always have a definition for `(', etc. For example, % if the fn name has parens in it, \boldbrax will not be in effect yet, % so TeX would otherwise complain about undefined control sequence. { \activeparens \global\let(=\lparen \global\let)=\rparen \global\let[=\lbrack \global\let]=\rbrack \global\let& = \& \gdef\boldbrax{\let(=\opnr\let)=\clnr\let[=\lbrb\let]=\rbrb} \gdef\magicamp{\let&=\amprm} } \newcount\parencount % If we encounter &foo, then turn on ()-hacking afterwards \newif\ifampseen \def\amprm#1 {\ampseentrue{\bf\ }} \def\parenfont{% \ifampseen % At the first level, print parens in roman, % otherwise use the default font. \ifnum \parencount=1 \rm \fi \else % The \sf parens (in \boldbrax) actually are a little bolder than % the contained text. This is especially needed for [ and ] . \sf \fi } \def\infirstlevel#1{% \ifampseen \ifnum\parencount=1 #1% \fi \fi } \def\bfafterword#1 {#1 \bf} \def\opnr{% \global\advance\parencount by 1 {\parenfont(}% \infirstlevel \bfafterword } \def\clnr{% {\parenfont)}% \infirstlevel \sl \global\advance\parencount by -1 } \newcount\brackcount \def\lbrb{% \global\advance\brackcount by 1 {\bf[}% } \def\rbrb{% {\bf]}% \global\advance\brackcount by -1 } \def\checkparencounts{% \ifnum\parencount=0 \else \badparencount \fi \ifnum\brackcount=0 \else \badbrackcount \fi } % these should not use \errmessage; the glibc manual, at least, actually % has such constructs (when documenting function pointers). \def\badparencount{% \message{Warning: unbalanced parentheses in @def...}% \global\parencount=0 } \def\badbrackcount{% \message{Warning: unbalanced square brackets in @def...}% \global\brackcount=0 } \message{macros,} % @macro. % To do this right we need a feature of e-TeX, \scantokens, % which we arrange to emulate with a temporary file in ordinary TeX. \ifx\eTeXversion\thisisundefined \newwrite\macscribble \def\scantokens#1{% \toks0={#1}% \immediate\openout\macscribble=\jobname.tmp \immediate\write\macscribble{\the\toks0}% \immediate\closeout\macscribble \input \jobname.tmp } \fi \def\scanmacro#1{\begingroup \newlinechar`\^^M \let\xeatspaces\eatspaces % % Undo catcode changes of \startcontents and \doprintindex % When called from @insertcopying or (short)caption, we need active % backslash to get it printed correctly. Previously, we had % \catcode`\\=\other instead. We'll see whether a problem appears % with macro expansion. --kasal, 19aug04 \catcode`\@=0 \catcode`\\=\active \escapechar=`\@ % % ... and for \example: \spaceisspace % % The \empty here causes a following catcode 5 newline to be eaten as % part of reading whitespace after a control sequence. It does not % eat a catcode 13 newline. There's no good way to handle the two % cases (untried: maybe e-TeX's \everyeof could help, though plain TeX % would then have different behavior). See the Macro Details node in % the manual for the workaround we recommend for macros and % line-oriented commands. % \scantokens{#1\empty}% \endgroup} \def\scanexp#1{% \edef\temp{\noexpand\scanmacro{#1}}% \temp } \newcount\paramno % Count of parameters \newtoks\macname % Macro name \newif\ifrecursive % Is it recursive? % List of all defined macros in the form % \definedummyword\macro1\definedummyword\macro2... % Currently is also contains all @aliases; the list can be split % if there is a need. \def\macrolist{} % Add the macro to \macrolist \def\addtomacrolist#1{\expandafter \addtomacrolistxxx \csname#1\endcsname} \def\addtomacrolistxxx#1{% \toks0 = \expandafter{\macrolist\definedummyword#1}% \xdef\macrolist{\the\toks0}% } % Utility routines. % This does \let #1 = #2, with \csnames; that is, % \let \csname#1\endcsname = \csname#2\endcsname % (except of course we have to play expansion games). % \def\cslet#1#2{% \expandafter\let \csname#1\expandafter\endcsname \csname#2\endcsname } % Trim leading and trailing spaces off a string. % Concepts from aro-bend problem 15 (see CTAN). {\catcode`\@=11 \gdef\eatspaces #1{\expandafter\trim@\expandafter{#1 }} \gdef\trim@ #1{\trim@@ @#1 @ #1 @ @@} \gdef\trim@@ #1@ #2@ #3@@{\trim@@@\empty #2 @} \def\unbrace#1{#1} \unbrace{\gdef\trim@@@ #1 } #2@{#1} } % Trim a single trailing ^^M off a string. {\catcode`\^^M=\other \catcode`\Q=3% \gdef\eatcr #1{\eatcra #1Q^^MQ}% \gdef\eatcra#1^^MQ{\eatcrb#1Q}% \gdef\eatcrb#1Q#2Q{#1}% } % Macro bodies are absorbed as an argument in a context where % all characters are catcode 10, 11 or 12, except \ which is active % (as in normal texinfo). It is necessary to change the definition of \ % to recognize macro arguments; this is the job of \mbodybackslash. % % Non-ASCII encodings make 8-bit characters active, so un-activate % them to avoid their expansion. Must do this non-globally, to % confine the change to the current group. % % It's necessary to have hard CRs when the macro is executed. This is % done by making ^^M (\endlinechar) catcode 12 when reading the macro % body, and then making it the \newlinechar in \scanmacro. % \def\scanctxt{% used as subroutine \catcode`\"=\other \catcode`\+=\other \catcode`\<=\other \catcode`\>=\other \catcode`\@=\other \catcode`\^=\other \catcode`\_=\other \catcode`\|=\other \catcode`\~=\other \ifx\declaredencoding\ascii \else \setnonasciicharscatcodenonglobal\other \fi } \def\scanargctxt{% used for copying and captions, not macros. \scanctxt \catcode`\\=\other \catcode`\^^M=\other } \def\macrobodyctxt{% used for @macro definitions \scanctxt \catcode`\{=\other \catcode`\}=\other \catcode`\^^M=\other \usembodybackslash } \def\macroargctxt{% used when scanning invocations \scanctxt \catcode`\\=0 } % why catcode 0 for \ in the above? To recognize \\ \{ \} as "escapes" % for the single characters \ { }. Thus, we end up with the "commands" % that would be written @\ @{ @} in a Texinfo document. % % We already have @{ and @}. For @\, we define it here, and only for % this purpose, to produce a typewriter backslash (so, the @\ that we % define for @math can't be used with @macro calls): % \def\\{\normalbackslash}% % % We would like to do this for \, too, since that is what makeinfo does. % But it is not possible, because Texinfo already has a command @, for a % cedilla accent. Documents must use @comma{} instead. % % \anythingelse will almost certainly be an error of some kind. % \mbodybackslash is the definition of \ in @macro bodies. % It maps \foo\ => \csname macarg.foo\endcsname => #N % where N is the macro parameter number. % We define \csname macarg.\endcsname to be \realbackslash, so % \\ in macro replacement text gets you a backslash. % {\catcode`@=0 @catcode`@\=@active @gdef@usembodybackslash{@let\=@mbodybackslash} @gdef@mbodybackslash#1\{@csname macarg.#1@endcsname} } \expandafter\def\csname macarg.\endcsname{\realbackslash} \def\margbackslash#1{\char`\#1 } \def\macro{\recursivefalse\parsearg\macroxxx} \def\rmacro{\recursivetrue\parsearg\macroxxx} \def\macroxxx#1{% \getargs{#1}% now \macname is the macname and \argl the arglist \ifx\argl\empty % no arguments \paramno=0\relax \else \expandafter\parsemargdef \argl;% \if\paramno>256\relax \ifx\eTeXversion\thisisundefined \errhelp = \EMsimple \errmessage{You need eTeX to compile a file with macros with more than 256 arguments} \fi \fi \fi \if1\csname ismacro.\the\macname\endcsname \message{Warning: redefining \the\macname}% \else \expandafter\ifx\csname \the\macname\endcsname \relax \else \errmessage{Macro name \the\macname\space already defined}\fi \global\cslet{macsave.\the\macname}{\the\macname}% \global\expandafter\let\csname ismacro.\the\macname\endcsname=1% \addtomacrolist{\the\macname}% \fi \begingroup \macrobodyctxt \ifrecursive \expandafter\parsermacbody \else \expandafter\parsemacbody \fi} \parseargdef\unmacro{% \if1\csname ismacro.#1\endcsname \global\cslet{#1}{macsave.#1}% \global\expandafter\let \csname ismacro.#1\endcsname=0% % Remove the macro name from \macrolist: \begingroup \expandafter\let\csname#1\endcsname \relax \let\definedummyword\unmacrodo \xdef\macrolist{\macrolist}% \endgroup \else \errmessage{Macro #1 not defined}% \fi } % Called by \do from \dounmacro on each macro. The idea is to omit any % macro definitions that have been changed to \relax. % \def\unmacrodo#1{% \ifx #1\relax % remove this \else \noexpand\definedummyword \noexpand#1% \fi } % This makes use of the obscure feature that if the last token of a % is #, then the preceding argument is delimited by % an opening brace, and that opening brace is not consumed. \def\getargs#1{\getargsxxx#1{}} \def\getargsxxx#1#{\getmacname #1 \relax\getmacargs} \def\getmacname#1 #2\relax{\macname={#1}} \def\getmacargs#1{\def\argl{#1}} % For macro processing make @ a letter so that we can make Texinfo private macro names. \edef\texiatcatcode{\the\catcode`\@} \catcode `@=11\relax % Parse the optional {params} list. Set up \paramno and \paramlist % so \defmacro knows what to do. Define \macarg.BLAH for each BLAH % in the params list to some hook where the argument si to be expanded. If % there are less than 10 arguments that hook is to be replaced by ##N where N % is the position in that list, that is to say the macro arguments are to be % defined `a la TeX in the macro body. % % That gets used by \mbodybackslash (above). % % We need to get `macro parameter char #' into several definitions. % The technique used is stolen from LaTeX: let \hash be something % unexpandable, insert that wherever you need a #, and then redefine % it to # just before using the token list produced. % % The same technique is used to protect \eatspaces till just before % the macro is used. % % If there are 10 or more arguments, a different technique is used, where the % hook remains in the body, and when macro is to be expanded the body is % processed again to replace the arguments. % % In that case, the hook is \the\toks N-1, and we simply set \toks N-1 to the % argument N value and then \edef the body (nothing else will expand because of % the catcode regime underwhich the body was input). % % If you compile with TeX (not eTeX), and you have macros with 10 or more % arguments, you need that no macro has more than 256 arguments, otherwise an % error is produced. \def\parsemargdef#1;{% \paramno=0\def\paramlist{}% \let\hash\relax \let\xeatspaces\relax \parsemargdefxxx#1,;,% % In case that there are 10 or more arguments we parse again the arguments % list to set new definitions for the \macarg.BLAH macros corresponding to % each BLAH argument. It was anyhow needed to parse already once this list % in order to count the arguments, and as macros with at most 9 arguments % are by far more frequent than macro with 10 or more arguments, defining % twice the \macarg.BLAH macros does not cost too much processing power. \ifnum\paramno<10\relax\else \paramno0\relax \parsemmanyargdef@@#1,;,% 10 or more arguments \fi } \def\parsemargdefxxx#1,{% \if#1;\let\next=\relax \else \let\next=\parsemargdefxxx \advance\paramno by 1 \expandafter\edef\csname macarg.\eatspaces{#1}\endcsname {\xeatspaces{\hash\the\paramno}}% \edef\paramlist{\paramlist\hash\the\paramno,}% \fi\next} \def\parsemmanyargdef@@#1,{% \if#1;\let\next=\relax \else \let\next=\parsemmanyargdef@@ \edef\tempb{\eatspaces{#1}}% \expandafter\def\expandafter\tempa \expandafter{\csname macarg.\tempb\endcsname}% % Note that we need some extra \noexpand\noexpand, this is because we % don't want \the to be expanded in the \parsermacbody as it uses an % \xdef . \expandafter\edef\tempa {\noexpand\noexpand\noexpand\the\toks\the\paramno}% \advance\paramno by 1\relax \fi\next} % These two commands read recursive and nonrecursive macro bodies. % (They're different since rec and nonrec macros end differently.) % \catcode `\@\texiatcatcode \long\def\parsemacbody#1@end macro% {\xdef\temp{\eatcr{#1}}\endgroup\defmacro}% \long\def\parsermacbody#1@end rmacro% {\xdef\temp{\eatcr{#1}}\endgroup\defmacro}% \catcode `\@=11\relax \let\endargs@\relax \let\nil@\relax \def\nilm@{\nil@}% \long\def\nillm@{\nil@}% % This macro is expanded during the Texinfo macro expansion, not during its % definition. It gets all the arguments values and assigns them to macros % macarg.ARGNAME % % #1 is the macro name % #2 is the list of argument names % #3 is the list of argument values \def\getargvals@#1#2#3{% \def\macargdeflist@{}% \def\saveparamlist@{#2}% Need to keep a copy for parameter expansion. \def\paramlist{#2,\nil@}% \def\macroname{#1}% \begingroup \macroargctxt \def\argvaluelist{#3,\nil@}% \def\@tempa{#3}% \ifx\@tempa\empty \setemptyargvalues@ \else \getargvals@@ \fi } % \def\getargvals@@{% \ifx\paramlist\nilm@ % Some sanity check needed here that \argvaluelist is also empty. \ifx\argvaluelist\nillm@ \else \errhelp = \EMsimple \errmessage{Too many arguments in macro `\macroname'!}% \fi \let\next\macargexpandinbody@ \else \ifx\argvaluelist\nillm@ % No more arguments values passed to macro. Set remaining named-arg % macros to empty. \let\next\setemptyargvalues@ \else % pop current arg name into \@tempb \def\@tempa##1{\pop@{\@tempb}{\paramlist}##1\endargs@}% \expandafter\@tempa\expandafter{\paramlist}% % pop current argument value into \@tempc \def\@tempa##1{\longpop@{\@tempc}{\argvaluelist}##1\endargs@}% \expandafter\@tempa\expandafter{\argvaluelist}% % Here \@tempb is the current arg name and \@tempc is the current arg value. % First place the new argument macro definition into \@tempd \expandafter\macname\expandafter{\@tempc}% \expandafter\let\csname macarg.\@tempb\endcsname\relax \expandafter\def\expandafter\@tempe\expandafter{% \csname macarg.\@tempb\endcsname}% \edef\@tempd{\long\def\@tempe{\the\macname}}% \push@\@tempd\macargdeflist@ \let\next\getargvals@@ \fi \fi \next } \def\push@#1#2{% \expandafter\expandafter\expandafter\def \expandafter\expandafter\expandafter#2% \expandafter\expandafter\expandafter{% \expandafter#1#2}% } % Replace arguments by their values in the macro body, and place the result % in macro \@tempa \def\macvalstoargs@{% % To do this we use the property that token registers that are \the'ed % within an \edef expand only once. So we are going to place all argument % values into respective token registers. % % First we save the token context, and initialize argument numbering. \begingroup \paramno0\relax % Then, for each argument number #N, we place the corresponding argument % value into a new token list register \toks#N \expandafter\putargsintokens@\saveparamlist@,;,% % Then, we expand the body so that argument are replaced by their % values. The trick for values not to be expanded themselves is that they % are within tokens and that tokens expand only once in an \edef . \edef\@tempc{\csname mac.\macroname .body\endcsname}% % Now we restore the token stack pointer to free the token list registers % which we have used, but we make sure that expanded body is saved after % group. \expandafter \endgroup \expandafter\def\expandafter\@tempa\expandafter{\@tempc}% } \def\macargexpandinbody@{% %% Define the named-macro outside of this group and then close this group. \expandafter \endgroup \macargdeflist@ % First the replace in body the macro arguments by their values, the result % is in \@tempa . \macvalstoargs@ % Then we point at the \norecurse or \gobble (for recursive) macro value % with \@tempb . \expandafter\let\expandafter\@tempb\csname mac.\macroname .recurse\endcsname % Depending on whether it is recursive or not, we need some tailing % \egroup . \ifx\@tempb\gobble \let\@tempc\relax \else \let\@tempc\egroup \fi % And now we do the real job: \edef\@tempd{\noexpand\@tempb{\macroname}\noexpand\scanmacro{\@tempa}\@tempc}% \@tempd } \def\putargsintokens@#1,{% \if#1;\let\next\relax \else \let\next\putargsintokens@ % First we allocate the new token list register, and give it a temporary % alias \@tempb . \toksdef\@tempb\the\paramno % Then we place the argument value into that token list register. \expandafter\let\expandafter\@tempa\csname macarg.#1\endcsname \expandafter\@tempb\expandafter{\@tempa}% \advance\paramno by 1\relax \fi \next } % Save the token stack pointer into macro #1 \def\texisavetoksstackpoint#1{\edef#1{\the\@cclvi}} % Restore the token stack pointer from number in macro #1 \def\texirestoretoksstackpoint#1{\expandafter\mathchardef\expandafter\@cclvi#1\relax} % newtoks that can be used non \outer . \def\texinonouternewtoks{\alloc@ 5\toks \toksdef \@cclvi} % Tailing missing arguments are set to empty \def\setemptyargvalues@{% \ifx\paramlist\nilm@ \let\next\macargexpandinbody@ \else \expandafter\setemptyargvaluesparser@\paramlist\endargs@ \let\next\setemptyargvalues@ \fi \next } \def\setemptyargvaluesparser@#1,#2\endargs@{% \expandafter\def\expandafter\@tempa\expandafter{% \expandafter\def\csname macarg.#1\endcsname{}}% \push@\@tempa\macargdeflist@ \def\paramlist{#2}% } % #1 is the element target macro % #2 is the list macro % #3,#4\endargs@ is the list value \def\pop@#1#2#3,#4\endargs@{% \def#1{#3}% \def#2{#4}% } \long\def\longpop@#1#2#3,#4\endargs@{% \long\def#1{#3}% \long\def#2{#4}% } % This defines a Texinfo @macro. There are eight cases: recursive and % nonrecursive macros of zero, one, up to nine, and many arguments. % Much magic with \expandafter here. % \xdef is used so that macro definitions will survive the file % they're defined in; @include reads the file inside a group. % \def\defmacro{% \let\hash=##% convert placeholders to macro parameter chars \ifrecursive \ifcase\paramno % 0 \expandafter\xdef\csname\the\macname\endcsname{% \noexpand\scanmacro{\temp}}% \or % 1 \expandafter\xdef\csname\the\macname\endcsname{% \bgroup\noexpand\macroargctxt \noexpand\braceorline \expandafter\noexpand\csname\the\macname xxx\endcsname}% \expandafter\xdef\csname\the\macname xxx\endcsname##1{% \egroup\noexpand\scanmacro{\temp}}% \else \ifnum\paramno<10\relax % at most 9 \expandafter\xdef\csname\the\macname\endcsname{% \bgroup\noexpand\macroargctxt \noexpand\csname\the\macname xx\endcsname}% \expandafter\xdef\csname\the\macname xx\endcsname##1{% \expandafter\noexpand\csname\the\macname xxx\endcsname ##1,}% \expandafter\expandafter \expandafter\xdef \expandafter\expandafter \csname\the\macname xxx\endcsname \paramlist{\egroup\noexpand\scanmacro{\temp}}% \else % 10 or more \expandafter\xdef\csname\the\macname\endcsname{% \noexpand\getargvals@{\the\macname}{\argl}% }% \global\expandafter\let\csname mac.\the\macname .body\endcsname\temp \global\expandafter\let\csname mac.\the\macname .recurse\endcsname\gobble \fi \fi \else \ifcase\paramno % 0 \expandafter\xdef\csname\the\macname\endcsname{% \noexpand\norecurse{\the\macname}% \noexpand\scanmacro{\temp}\egroup}% \or % 1 \expandafter\xdef\csname\the\macname\endcsname{% \bgroup\noexpand\macroargctxt \noexpand\braceorline \expandafter\noexpand\csname\the\macname xxx\endcsname}% \expandafter\xdef\csname\the\macname xxx\endcsname##1{% \egroup \noexpand\norecurse{\the\macname}% \noexpand\scanmacro{\temp}\egroup}% \else % at most 9 \ifnum\paramno<10\relax \expandafter\xdef\csname\the\macname\endcsname{% \bgroup\noexpand\macroargctxt \expandafter\noexpand\csname\the\macname xx\endcsname}% \expandafter\xdef\csname\the\macname xx\endcsname##1{% \expandafter\noexpand\csname\the\macname xxx\endcsname ##1,}% \expandafter\expandafter \expandafter\xdef \expandafter\expandafter \csname\the\macname xxx\endcsname \paramlist{% \egroup \noexpand\norecurse{\the\macname}% \noexpand\scanmacro{\temp}\egroup}% \else % 10 or more: \expandafter\xdef\csname\the\macname\endcsname{% \noexpand\getargvals@{\the\macname}{\argl}% }% \global\expandafter\let\csname mac.\the\macname .body\endcsname\temp \global\expandafter\let\csname mac.\the\macname .recurse\endcsname\norecurse \fi \fi \fi} \catcode `\@\texiatcatcode\relax \def\norecurse#1{\bgroup\cslet{#1}{macsave.#1}} % \braceorline decides whether the next nonwhitespace character is a % {. If so it reads up to the closing }, if not, it reads the whole % line. Whatever was read is then fed to the next control sequence % as an argument (by \parsebrace or \parsearg). % \def\braceorline#1{\let\macnamexxx=#1\futurelet\nchar\braceorlinexxx} \def\braceorlinexxx{% \ifx\nchar\bgroup\else \expandafter\parsearg \fi \macnamexxx} % @alias. % We need some trickery to remove the optional spaces around the equal % sign. Make them active and then expand them all to nothing. % \def\alias{\parseargusing\obeyspaces\aliasxxx} \def\aliasxxx #1{\aliasyyy#1\relax} \def\aliasyyy #1=#2\relax{% {% \expandafter\let\obeyedspace=\empty \addtomacrolist{#1}% \xdef\next{\global\let\makecsname{#1}=\makecsname{#2}}% }% \next } \message{cross references,} \newwrite\auxfile \newif\ifhavexrefs % True if xref values are known. \newif\ifwarnedxrefs % True if we warned once that they aren't known. % @inforef is relatively simple. \def\inforef #1{\inforefzzz #1,,,,**} \def\inforefzzz #1,#2,#3,#4**{% \putwordSee{} \putwordInfo{} \putwordfile{} \file{\ignorespaces #3{}}, node \samp{\ignorespaces#1{}}} % @node's only job in TeX is to define \lastnode, which is used in % cross-references. The @node line might or might not have commas, and % might or might not have spaces before the first comma, like: % @node foo , bar , ... % We don't want such trailing spaces in the node name. % \parseargdef\node{\checkenv{}\donode #1 ,\finishnodeparse} % % also remove a trailing comma, in case of something like this: % @node Help-Cross, , , Cross-refs \def\donode#1 ,#2\finishnodeparse{\dodonode #1,\finishnodeparse} \def\dodonode#1,#2\finishnodeparse{\gdef\lastnode{#1}} \let\nwnode=\node \let\lastnode=\empty % Write a cross-reference definition for the current node. #1 is the % type (Ynumbered, Yappendix, Ynothing). % \def\donoderef#1{% \ifx\lastnode\empty\else \setref{\lastnode}{#1}% \global\let\lastnode=\empty \fi } % @anchor{NAME} -- define xref target at arbitrary point. % \newcount\savesfregister % \def\savesf{\relax \ifhmode \savesfregister=\spacefactor \fi} \def\restoresf{\relax \ifhmode \spacefactor=\savesfregister \fi} \def\anchor#1{\savesf \setref{#1}{Ynothing}\restoresf \ignorespaces} % \setref{NAME}{SNT} defines a cross-reference point NAME (a node or an % anchor), which consists of three parts: % 1) NAME-title - the current sectioning name taken from \lastsection, % or the anchor name. % 2) NAME-snt - section number and type, passed as the SNT arg, or % empty for anchors. % 3) NAME-pg - the page number. % % This is called from \donoderef, \anchor, and \dofloat. In the case of % floats, there is an additional part, which is not written here: % 4) NAME-lof - the text as it should appear in a @listoffloats. % \def\setref#1#2{% \pdfmkdest{#1}% \iflinks {% \atdummies % preserve commands, but don't expand them \edef\writexrdef##1##2{% \write\auxfile{@xrdef{#1-% #1 of \setref, expanded by the \edef ##1}{##2}}% these are parameters of \writexrdef }% \toks0 = \expandafter{\lastsection}% \immediate \writexrdef{title}{\the\toks0 }% \immediate \writexrdef{snt}{\csname #2\endcsname}% \Ynumbered etc. \safewhatsit{\writexrdef{pg}{\folio}}% will be written later, at \shipout }% \fi } % @xrefautosectiontitle on|off says whether @section(ing) names are used % automatically in xrefs, if the third arg is not explicitly specified. % This was provided as a "secret" @set xref-automatic-section-title % variable, now it's official. % \parseargdef\xrefautomaticsectiontitle{% \def\temp{#1}% \ifx\temp\onword \expandafter\let\csname SETxref-automatic-section-title\endcsname = \empty \else\ifx\temp\offword \expandafter\let\csname SETxref-automatic-section-title\endcsname = \relax \else \errhelp = \EMsimple \errmessage{Unknown @xrefautomaticsectiontitle value `\temp', must be on|off}% \fi\fi } % @xref, @pxref, and @ref generate cross-references. For \xrefX, #1 is % the node name, #2 the name of the Info cross-reference, #3 the printed % node name, #4 the name of the Info file, #5 the name of the printed % manual. All but the node name can be omitted. % \def\pxref#1{\putwordsee{} \xrefX[#1,,,,,,,]} \def\xref#1{\putwordSee{} \xrefX[#1,,,,,,,]} \def\ref#1{\xrefX[#1,,,,,,,]} % \newbox\topbox \newbox\printedrefnamebox \newbox\printedmanualbox % \def\xrefX[#1,#2,#3,#4,#5,#6]{\begingroup \unsepspaces % \def\printedrefname{\ignorespaces #3}% \setbox\printedrefnamebox = \hbox{\printedrefname\unskip}% % \def\printedmanual{\ignorespaces #5}% \setbox\printedmanualbox = \hbox{\printedmanual\unskip}% % % If the printed reference name (arg #3) was not explicitly given in % the @xref, figure out what we want to use. \ifdim \wd\printedrefnamebox = 0pt % No printed node name was explicitly given. \expandafter\ifx\csname SETxref-automatic-section-title\endcsname \relax % Not auto section-title: use node name inside the square brackets. \def\printedrefname{\ignorespaces #1}% \else % Auto section-title: use chapter/section title inside % the square brackets if we have it. \ifdim \wd\printedmanualbox > 0pt % It is in another manual, so we don't have it; use node name. \def\printedrefname{\ignorespaces #1}% \else \ifhavexrefs % We (should) know the real title if we have the xref values. \def\printedrefname{\refx{#1-title}{}}% \else % Otherwise just copy the Info node name. \def\printedrefname{\ignorespaces #1}% \fi% \fi \fi \fi % % Make link in pdf output. \ifpdf {\indexnofonts \turnoffactive \makevalueexpandable % This expands tokens, so do it after making catcode changes, so _ % etc. don't get their TeX definitions. \getfilename{#4}% % \edef\pdfxrefdest{#1}% \txiescapepdf\pdfxrefdest % \leavevmode \startlink attr{/Border [0 0 0]}% \ifnum\filenamelength>0 goto file{\the\filename.pdf} name{\pdfxrefdest}% \else goto name{\pdfmkpgn{\pdfxrefdest}}% \fi }% \setcolor{\linkcolor}% \fi % % Float references are printed completely differently: "Figure 1.2" % instead of "[somenode], p.3". We distinguish them by the % LABEL-title being set to a magic string. {% % Have to otherify everything special to allow the \csname to % include an _ in the xref name, etc. \indexnofonts \turnoffactive \expandafter\global\expandafter\let\expandafter\Xthisreftitle \csname XR#1-title\endcsname }% \iffloat\Xthisreftitle % If the user specified the print name (third arg) to the ref, % print it instead of our usual "Figure 1.2". \ifdim\wd\printedrefnamebox = 0pt \refx{#1-snt}{}% \else \printedrefname \fi % % if the user also gave the printed manual name (fifth arg), append % "in MANUALNAME". \ifdim \wd\printedmanualbox > 0pt \space \putwordin{} \cite{\printedmanual}% \fi \else % node/anchor (non-float) references. % % If we use \unhbox to print the node names, TeX does not insert % empty discretionaries after hyphens, which means that it will not % find a line break at a hyphen in a node names. Since some manuals % are best written with fairly long node names, containing hyphens, % this is a loss. Therefore, we give the text of the node name % again, so it is as if TeX is seeing it for the first time. % % Cross-manual reference. Only include the "Section ``foo'' in" if % the foo is neither missing or Top. Thus, @xref{,,,foo,The Foo Manual} % outputs simply "see The Foo Manual". \ifdim \wd\printedmanualbox > 0pt % What is the 7sp about? The idea is that we also want to omit % the Section part if we would be printing "Top", since they are % clearly trying to refer to the whole manual. But, this being % TeX, we can't easily compare strings while ignoring the possible % spaces before and after in the input. By adding the arbitrary % 7sp, we make it much less likely that a real node name would % happen to have the same width as "Top" (e.g., in a monospaced font). % I hope it will never happen in practice. % % For the same basic reason, we retypeset the "Top" at every % reference, since the current font is indeterminate. % \setbox\topbox = \hbox{Top\kern7sp}% \setbox2 = \hbox{\ignorespaces \printedrefname \unskip \kern7sp}% \ifdim \wd2 > 7sp \ifdim \wd2 = \wd\topbox \else \putwordSection{} ``\printedrefname'' \putwordin{}\space \fi \fi \cite{\printedmanual}% \else % Reference in this manual. % % _ (for example) has to be the character _ for the purposes of the % control sequence corresponding to the node, but it has to expand % into the usual \leavevmode...\vrule stuff for purposes of % printing. So we \turnoffactive for the \refx-snt, back on for the % printing, back off for the \refx-pg. {\turnoffactive % Only output a following space if the -snt ref is nonempty; for % @unnumbered and @anchor, it won't be. \setbox2 = \hbox{\ignorespaces \refx{#1-snt}{}}% \ifdim \wd2 > 0pt \refx{#1-snt}\space\fi }% % output the `[mynode]' via the macro below so it can be overridden. \xrefprintnodename\printedrefname % % But we always want a comma and a space: ,\space % % output the `page 3'. \turnoffactive \putwordpage\tie\refx{#1-pg}{}% \fi \fi \endlink \endgroup} % This macro is called from \xrefX for the `[nodename]' part of xref % output. It's a separate macro only so it can be changed more easily, % since square brackets don't work well in some documents. Particularly % one that Bob is working on :). % \def\xrefprintnodename#1{[#1]} % Things referred to by \setref. % \def\Ynothing{} \def\Yomitfromtoc{} \def\Ynumbered{% \ifnum\secno=0 \putwordChapter@tie \the\chapno \else \ifnum\subsecno=0 \putwordSection@tie \the\chapno.\the\secno \else \ifnum\subsubsecno=0 \putwordSection@tie \the\chapno.\the\secno.\the\subsecno \else \putwordSection@tie \the\chapno.\the\secno.\the\subsecno.\the\subsubsecno \fi\fi\fi } \def\Yappendix{% \ifnum\secno=0 \putwordAppendix@tie @char\the\appendixno{}% \else \ifnum\subsecno=0 \putwordSection@tie @char\the\appendixno.\the\secno \else \ifnum\subsubsecno=0 \putwordSection@tie @char\the\appendixno.\the\secno.\the\subsecno \else \putwordSection@tie @char\the\appendixno.\the\secno.\the\subsecno.\the\subsubsecno \fi\fi\fi } % Define \refx{NAME}{SUFFIX} to reference a cross-reference string named NAME. % If its value is nonempty, SUFFIX is output afterward. % \def\refx#1#2{% {% \indexnofonts \otherbackslash \expandafter\global\expandafter\let\expandafter\thisrefX \csname XR#1\endcsname }% \ifx\thisrefX\relax % If not defined, say something at least. \angleleft un\-de\-fined\angleright \iflinks \ifhavexrefs {\toks0 = {#1}% avoid expansion of possibly-complex value \message{\linenumber Undefined cross reference `\the\toks0'.}}% \else \ifwarnedxrefs\else \global\warnedxrefstrue \message{Cross reference values unknown; you must run TeX again.}% \fi \fi \fi \else % It's defined, so just use it. \thisrefX \fi #2% Output the suffix in any case. } % This is the macro invoked by entries in the aux file. Usually it's % just a \def (we prepend XR to the control sequence name to avoid % collisions). But if this is a float type, we have more work to do. % \def\xrdef#1#2{% {% The node name might contain 8-bit characters, which in our current % implementation are changed to commands like @'e. Don't let these % mess up the control sequence name. \indexnofonts \turnoffactive \xdef\safexrefname{#1}% }% % \expandafter\gdef\csname XR\safexrefname\endcsname{#2}% remember this xref % % Was that xref control sequence that we just defined for a float? \expandafter\iffloat\csname XR\safexrefname\endcsname % it was a float, and we have the (safe) float type in \iffloattype. \expandafter\let\expandafter\floatlist \csname floatlist\iffloattype\endcsname % % Is this the first time we've seen this float type? \expandafter\ifx\floatlist\relax \toks0 = {\do}% yes, so just \do \else % had it before, so preserve previous elements in list. \toks0 = \expandafter{\floatlist\do}% \fi % % Remember this xref in the control sequence \floatlistFLOATTYPE, % for later use in \listoffloats. \expandafter\xdef\csname floatlist\iffloattype\endcsname{\the\toks0 {\safexrefname}}% \fi } % Read the last existing aux file, if any. No error if none exists. % \def\tryauxfile{% \openin 1 \jobname.aux \ifeof 1 \else \readdatafile{aux}% \global\havexrefstrue \fi \closein 1 } \def\setupdatafile{% \catcode`\^^@=\other \catcode`\^^A=\other \catcode`\^^B=\other \catcode`\^^C=\other \catcode`\^^D=\other \catcode`\^^E=\other \catcode`\^^F=\other \catcode`\^^G=\other \catcode`\^^H=\other \catcode`\^^K=\other \catcode`\^^L=\other \catcode`\^^N=\other \catcode`\^^P=\other \catcode`\^^Q=\other \catcode`\^^R=\other \catcode`\^^S=\other \catcode`\^^T=\other \catcode`\^^U=\other \catcode`\^^V=\other \catcode`\^^W=\other \catcode`\^^X=\other \catcode`\^^Z=\other \catcode`\^^[=\other \catcode`\^^\=\other \catcode`\^^]=\other \catcode`\^^^=\other \catcode`\^^_=\other % It was suggested to set the catcode of ^ to 7, which would allow ^^e4 etc. % in xref tags, i.e., node names. But since ^^e4 notation isn't % supported in the main text, it doesn't seem desirable. Furthermore, % that is not enough: for node names that actually contain a ^ % character, we would end up writing a line like this: 'xrdef {'hat % b-title}{'hat b} and \xrdef does a \csname...\endcsname on the first % argument, and \hat is not an expandable control sequence. It could % all be worked out, but why? Either we support ^^ or we don't. % % The other change necessary for this was to define \auxhat: % \def\auxhat{\def^{'hat }}% extra space so ok if followed by letter % and then to call \auxhat in \setq. % \catcode`\^=\other % % Special characters. Should be turned off anyway, but... \catcode`\~=\other \catcode`\[=\other \catcode`\]=\other \catcode`\"=\other \catcode`\_=\other \catcode`\|=\other \catcode`\<=\other \catcode`\>=\other \catcode`\$=\other \catcode`\#=\other \catcode`\&=\other \catcode`\%=\other \catcode`+=\other % avoid \+ for paranoia even though we've turned it off % % This is to support \ in node names and titles, since the \ % characters end up in a \csname. It's easier than % leaving it active and making its active definition an actual \ % character. What I don't understand is why it works in the *value* % of the xrdef. Seems like it should be a catcode12 \, and that % should not typeset properly. But it works, so I'm moving on for % now. --karl, 15jan04. \catcode`\\=\other % % Make the characters 128-255 be printing characters. {% \count1=128 \def\loop{% \catcode\count1=\other \advance\count1 by 1 \ifnum \count1<256 \loop \fi }% }% % % @ is our escape character in .aux files, and we need braces. \catcode`\{=1 \catcode`\}=2 \catcode`\@=0 } \def\readdatafile#1{% \begingroup \setupdatafile \input\jobname.#1 \endgroup} \message{insertions,} % including footnotes. \newcount \footnoteno % The trailing space in the following definition for supereject is % vital for proper filling; pages come out unaligned when you do a % pagealignmacro call if that space before the closing brace is % removed. (Generally, numeric constants should always be followed by a % space to prevent strange expansion errors.) \def\supereject{\par\penalty -20000\footnoteno =0 } % @footnotestyle is meaningful for Info output only. \let\footnotestyle=\comment {\catcode `\@=11 % % Auto-number footnotes. Otherwise like plain. \gdef\footnote{% \let\indent=\ptexindent \let\noindent=\ptexnoindent \global\advance\footnoteno by \@ne \edef\thisfootno{$^{\the\footnoteno}$}% % % In case the footnote comes at the end of a sentence, preserve the % extra spacing after we do the footnote number. \let\@sf\empty \ifhmode\edef\@sf{\spacefactor\the\spacefactor}\ptexslash\fi % % Remove inadvertent blank space before typesetting the footnote number. \unskip \thisfootno\@sf \dofootnote }% % Don't bother with the trickery in plain.tex to not require the % footnote text as a parameter. Our footnotes don't need to be so general. % % Oh yes, they do; otherwise, @ifset (and anything else that uses % \parseargline) fails inside footnotes because the tokens are fixed when % the footnote is read. --karl, 16nov96. % \gdef\dofootnote{% \insert\footins\bgroup % We want to typeset this text as a normal paragraph, even if the % footnote reference occurs in (for example) a display environment. % So reset some parameters. \hsize=\pagewidth \interlinepenalty\interfootnotelinepenalty \splittopskip\ht\strutbox % top baseline for broken footnotes \splitmaxdepth\dp\strutbox \floatingpenalty\@MM \leftskip\z@skip \rightskip\z@skip \spaceskip\z@skip \xspaceskip\z@skip \parindent\defaultparindent % \smallfonts \rm % % Because we use hanging indentation in footnotes, a @noindent appears % to exdent this text, so make it be a no-op. makeinfo does not use % hanging indentation so @noindent can still be needed within footnote % text after an @example or the like (not that this is good style). \let\noindent = \relax % % Hang the footnote text off the number. Use \everypar in case the % footnote extends for more than one paragraph. \everypar = {\hang}% \textindent{\thisfootno}% % % Don't crash into the line above the footnote text. Since this % expands into a box, it must come within the paragraph, lest it % provide a place where TeX can split the footnote. \footstrut % % Invoke rest of plain TeX footnote routine. \futurelet\next\fo@t } }%end \catcode `\@=11 % In case a @footnote appears in a vbox, save the footnote text and create % the real \insert just after the vbox finished. Otherwise, the insertion % would be lost. % Similarly, if a @footnote appears inside an alignment, save the footnote % text to a box and make the \insert when a row of the table is finished. % And the same can be done for other insert classes. --kasal, 16nov03. % Replace the \insert primitive by a cheating macro. % Deeper inside, just make sure that the saved insertions are not spilled % out prematurely. % \def\startsavinginserts{% \ifx \insert\ptexinsert \let\insert\saveinsert \else \let\checkinserts\relax \fi } % This \insert replacement works for both \insert\footins{foo} and % \insert\footins\bgroup foo\egroup, but it doesn't work for \insert27{foo}. % \def\saveinsert#1{% \edef\next{\noexpand\savetobox \makeSAVEname#1}% \afterassignment\next % swallow the left brace \let\temp = } \def\makeSAVEname#1{\makecsname{SAVE\expandafter\gobble\string#1}} \def\savetobox#1{\global\setbox#1 = \vbox\bgroup \unvbox#1} \def\checksaveins#1{\ifvoid#1\else \placesaveins#1\fi} \def\placesaveins#1{% \ptexinsert \csname\expandafter\gobblesave\string#1\endcsname {\box#1}% } % eat @SAVE -- beware, all of them have catcode \other: { \def\dospecials{\do S\do A\do V\do E} \uncatcodespecials % ;-) \gdef\gobblesave @SAVE{} } % initialization: \def\newsaveins #1{% \edef\next{\noexpand\newsaveinsX \makeSAVEname#1}% \next } \def\newsaveinsX #1{% \csname newbox\endcsname #1% \expandafter\def\expandafter\checkinserts\expandafter{\checkinserts \checksaveins #1}% } % initialize: \let\checkinserts\empty \newsaveins\footins \newsaveins\margin % @image. We use the macros from epsf.tex to support this. % If epsf.tex is not installed and @image is used, we complain. % % Check for and read epsf.tex up front. If we read it only at @image % time, we might be inside a group, and then its definitions would get % undone and the next image would fail. \openin 1 = epsf.tex \ifeof 1 \else % Do not bother showing banner with epsf.tex v2.7k (available in % doc/epsf.tex and on ctan). \def\epsfannounce{\toks0 = }% \input epsf.tex \fi \closein 1 % % We will only complain once about lack of epsf.tex. \newif\ifwarnednoepsf \newhelp\noepsfhelp{epsf.tex must be installed for images to work. It is also included in the Texinfo distribution, or you can get it from ftp://tug.org/tex/epsf.tex.} % \def\image#1{% \ifx\epsfbox\thisisundefined \ifwarnednoepsf \else \errhelp = \noepsfhelp \errmessage{epsf.tex not found, images will be ignored}% \global\warnednoepsftrue \fi \else \imagexxx #1,,,,,\finish \fi } % % Arguments to @image: % #1 is (mandatory) image filename; we tack on .eps extension. % #2 is (optional) width, #3 is (optional) height. % #4 is (ignored optional) html alt text. % #5 is (ignored optional) extension. % #6 is just the usual extra ignored arg for parsing stuff. \newif\ifimagevmode \def\imagexxx#1,#2,#3,#4,#5,#6\finish{\begingroup \catcode`\^^M = 5 % in case we're inside an example \normalturnoffactive % allow _ et al. in names % If the image is by itself, center it. \ifvmode \imagevmodetrue \else \ifx\centersub\centerV % for @center @image, we need a vbox so we can have our vertical space \imagevmodetrue \vbox\bgroup % vbox has better behavior than vtop herev \fi\fi % \ifimagevmode \nobreak\medskip % Usually we'll have text after the image which will insert % \parskip glue, so insert it here too to equalize the space % above and below. \nobreak\vskip\parskip \nobreak \fi % % Leave vertical mode so that indentation from an enclosing % environment such as @quotation is respected. % However, if we're at the top level, we don't want the % normal paragraph indentation. % On the other hand, if we are in the case of @center @image, we don't % want to start a paragraph, which will create a hsize-width box and % eradicate the centering. \ifx\centersub\centerV\else \noindent \fi % % Output the image. \ifpdf \dopdfimage{#1}{#2}{#3}% \else % \epsfbox itself resets \epsf?size at each figure. \setbox0 = \hbox{\ignorespaces #2}\ifdim\wd0 > 0pt \epsfxsize=#2\relax \fi \setbox0 = \hbox{\ignorespaces #3}\ifdim\wd0 > 0pt \epsfysize=#3\relax \fi \epsfbox{#1.eps}% \fi % \ifimagevmode \medskip % space after a standalone image \fi \ifx\centersub\centerV \egroup \fi \endgroup} % @float FLOATTYPE,LABEL,LOC ... @end float for displayed figures, tables, % etc. We don't actually implement floating yet, we always include the % float "here". But it seemed the best name for the future. % \envparseargdef\float{\eatcommaspace\eatcommaspace\dofloat#1, , ,\finish} % There may be a space before second and/or third parameter; delete it. \def\eatcommaspace#1, {#1,} % #1 is the optional FLOATTYPE, the text label for this float, typically % "Figure", "Table", "Example", etc. Can't contain commas. If omitted, % this float will not be numbered and cannot be referred to. % % #2 is the optional xref label. Also must be present for the float to % be referable. % % #3 is the optional positioning argument; for now, it is ignored. It % will somehow specify the positions allowed to float to (here, top, bottom). % % We keep a separate counter for each FLOATTYPE, which we reset at each % chapter-level command. \let\resetallfloatnos=\empty % \def\dofloat#1,#2,#3,#4\finish{% \let\thiscaption=\empty \let\thisshortcaption=\empty % % don't lose footnotes inside @float. % % BEWARE: when the floats start float, we have to issue warning whenever an % insert appears inside a float which could possibly float. --kasal, 26may04 % \startsavinginserts % % We can't be used inside a paragraph. \par % \vtop\bgroup \def\floattype{#1}% \def\floatlabel{#2}% \def\floatloc{#3}% we do nothing with this yet. % \ifx\floattype\empty \let\safefloattype=\empty \else {% % the floattype might have accents or other special characters, % but we need to use it in a control sequence name. \indexnofonts \turnoffactive \xdef\safefloattype{\floattype}% }% \fi % % If label is given but no type, we handle that as the empty type. \ifx\floatlabel\empty \else % We want each FLOATTYPE to be numbered separately (Figure 1, % Table 1, Figure 2, ...). (And if no label, no number.) % \expandafter\getfloatno\csname\safefloattype floatno\endcsname \global\advance\floatno by 1 % {% % This magic value for \lastsection is output by \setref as the % XREFLABEL-title value. \xrefX uses it to distinguish float % labels (which have a completely different output format) from % node and anchor labels. And \xrdef uses it to construct the % lists of floats. % \edef\lastsection{\floatmagic=\safefloattype}% \setref{\floatlabel}{Yfloat}% }% \fi % % start with \parskip glue, I guess. \vskip\parskip % % Don't suppress indentation if a float happens to start a section. \restorefirstparagraphindent } % we have these possibilities: % @float Foo,lbl & @caption{Cap}: Foo 1.1: Cap % @float Foo,lbl & no caption: Foo 1.1 % @float Foo & @caption{Cap}: Foo: Cap % @float Foo & no caption: Foo % @float ,lbl & Caption{Cap}: 1.1: Cap % @float ,lbl & no caption: 1.1 % @float & @caption{Cap}: Cap % @float & no caption: % \def\Efloat{% \let\floatident = \empty % % In all cases, if we have a float type, it comes first. \ifx\floattype\empty \else \def\floatident{\floattype}\fi % % If we have an xref label, the number comes next. \ifx\floatlabel\empty \else \ifx\floattype\empty \else % if also had float type, need tie first. \appendtomacro\floatident{\tie}% \fi % the number. \appendtomacro\floatident{\chaplevelprefix\the\floatno}% \fi % % Start the printed caption with what we've constructed in % \floatident, but keep it separate; we need \floatident again. \let\captionline = \floatident % \ifx\thiscaption\empty \else \ifx\floatident\empty \else \appendtomacro\captionline{: }% had ident, so need a colon between \fi % % caption text. \appendtomacro\captionline{\scanexp\thiscaption}% \fi % % If we have anything to print, print it, with space before. % Eventually this needs to become an \insert. \ifx\captionline\empty \else \vskip.5\parskip \captionline % % Space below caption. \vskip\parskip \fi % % If have an xref label, write the list of floats info. Do this % after the caption, to avoid chance of it being a breakpoint. \ifx\floatlabel\empty \else % Write the text that goes in the lof to the aux file as % \floatlabel-lof. Besides \floatident, we include the short % caption if specified, else the full caption if specified, else nothing. {% \atdummies % % since we read the caption text in the macro world, where ^^M % is turned into a normal character, we have to scan it back, so % we don't write the literal three characters "^^M" into the aux file. \scanexp{% \xdef\noexpand\gtemp{% \ifx\thisshortcaption\empty \thiscaption \else \thisshortcaption \fi }% }% \immediate\write\auxfile{@xrdef{\floatlabel-lof}{\floatident \ifx\gtemp\empty \else : \gtemp \fi}}% }% \fi \egroup % end of \vtop % % place the captured inserts % % BEWARE: when the floats start floating, we have to issue warning % whenever an insert appears inside a float which could possibly % float. --kasal, 26may04 % \checkinserts } % Append the tokens #2 to the definition of macro #1, not expanding either. % \def\appendtomacro#1#2{% \expandafter\def\expandafter#1\expandafter{#1#2}% } % @caption, @shortcaption % \def\caption{\docaption\thiscaption} \def\shortcaption{\docaption\thisshortcaption} \def\docaption{\checkenv\float \bgroup\scanargctxt\defcaption} \def\defcaption#1#2{\egroup \def#1{#2}} % The parameter is the control sequence identifying the counter we are % going to use. Create it if it doesn't exist and assign it to \floatno. \def\getfloatno#1{% \ifx#1\relax % Haven't seen this figure type before. \csname newcount\endcsname #1% % % Remember to reset this floatno at the next chap. \expandafter\gdef\expandafter\resetallfloatnos \expandafter{\resetallfloatnos #1=0 }% \fi \let\floatno#1% } % \setref calls this to get the XREFLABEL-snt value. We want an @xref % to the FLOATLABEL to expand to "Figure 3.1". We call \setref when we % first read the @float command. % \def\Yfloat{\floattype@tie \chaplevelprefix\the\floatno}% % Magic string used for the XREFLABEL-title value, so \xrefX can % distinguish floats from other xref types. \def\floatmagic{!!float!!} % #1 is the control sequence we are passed; we expand into a conditional % which is true if #1 represents a float ref. That is, the magic % \lastsection value which we \setref above. % \def\iffloat#1{\expandafter\doiffloat#1==\finish} % % #1 is (maybe) the \floatmagic string. If so, #2 will be the % (safe) float type for this float. We set \iffloattype to #2. % \def\doiffloat#1=#2=#3\finish{% \def\temp{#1}% \def\iffloattype{#2}% \ifx\temp\floatmagic } % @listoffloats FLOATTYPE - print a list of floats like a table of contents. % \parseargdef\listoffloats{% \def\floattype{#1}% floattype {% % the floattype might have accents or other special characters, % but we need to use it in a control sequence name. \indexnofonts \turnoffactive \xdef\safefloattype{\floattype}% }% % % \xrdef saves the floats as a \do-list in \floatlistSAFEFLOATTYPE. \expandafter\ifx\csname floatlist\safefloattype\endcsname \relax \ifhavexrefs % if the user said @listoffloats foo but never @float foo. \message{\linenumber No `\safefloattype' floats to list.}% \fi \else \begingroup \leftskip=\tocindent % indent these entries like a toc \let\do=\listoffloatsdo \csname floatlist\safefloattype\endcsname \endgroup \fi } % This is called on each entry in a list of floats. We're passed the % xref label, in the form LABEL-title, which is how we save it in the % aux file. We strip off the -title and look up \XRLABEL-lof, which % has the text we're supposed to typeset here. % % Figures without xref labels will not be included in the list (since % they won't appear in the aux file). % \def\listoffloatsdo#1{\listoffloatsdoentry#1\finish} \def\listoffloatsdoentry#1-title\finish{{% % Can't fully expand XR#1-lof because it can contain anything. Just % pass the control sequence. On the other hand, XR#1-pg is just the % page number, and we want to fully expand that so we can get a link % in pdf output. \toksA = \expandafter{\csname XR#1-lof\endcsname}% % % use the same \entry macro we use to generate the TOC and index. \edef\writeentry{\noexpand\entry{\the\toksA}{\csname XR#1-pg\endcsname}}% \writeentry }} \message{localization,} % For single-language documents, @documentlanguage is usually given very % early, just after @documentencoding. Single argument is the language % (de) or locale (de_DE) abbreviation. % { \catcode`\_ = \active \globaldefs=1 \parseargdef\documentlanguage{\begingroup \let_=\normalunderscore % normal _ character for filenames \tex % read txi-??.tex file in plain TeX. % Read the file by the name they passed if it exists. \openin 1 txi-#1.tex \ifeof 1 \documentlanguagetrywithoutunderscore{#1_\finish}% \else \globaldefs = 1 % everything in the txi-LL files needs to persist \input txi-#1.tex \fi \closein 1 \endgroup % end raw TeX \endgroup} % % If they passed de_DE, and txi-de_DE.tex doesn't exist, % try txi-de.tex. % \gdef\documentlanguagetrywithoutunderscore#1_#2\finish{% \openin 1 txi-#1.tex \ifeof 1 \errhelp = \nolanghelp \errmessage{Cannot read language file txi-#1.tex}% \else \globaldefs = 1 % everything in the txi-LL files needs to persist \input txi-#1.tex \fi \closein 1 } }% end of special _ catcode % \newhelp\nolanghelp{The given language definition file cannot be found or is empty. Maybe you need to install it? Putting it in the current directory should work if nowhere else does.} % This macro is called from txi-??.tex files; the first argument is the % \language name to set (without the "\lang@" prefix), the second and % third args are \{left,right}hyphenmin. % % The language names to pass are determined when the format is built. % See the etex.log file created at that time, e.g., % /usr/local/texlive/2008/texmf-var/web2c/pdftex/etex.log. % % With TeX Live 2008, etex now includes hyphenation patterns for all % available languages. This means we can support hyphenation in % Texinfo, at least to some extent. (This still doesn't solve the % accented characters problem.) % \catcode`@=11 \def\txisetlanguage#1#2#3{% % do not set the language if the name is undefined in the current TeX. \expandafter\ifx\csname lang@#1\endcsname \relax \message{no patterns for #1}% \else \global\language = \csname lang@#1\endcsname \fi % but there is no harm in adjusting the hyphenmin values regardless. \global\lefthyphenmin = #2\relax \global\righthyphenmin = #3\relax } % Helpers for encodings. % Set the catcode of characters 128 through 255 to the specified number. % \def\setnonasciicharscatcode#1{% \count255=128 \loop\ifnum\count255<256 \global\catcode\count255=#1\relax \advance\count255 by 1 \repeat } \def\setnonasciicharscatcodenonglobal#1{% \count255=128 \loop\ifnum\count255<256 \catcode\count255=#1\relax \advance\count255 by 1 \repeat } % @documentencoding sets the definition of non-ASCII characters % according to the specified encoding. % \parseargdef\documentencoding{% % Encoding being declared for the document. \def\declaredencoding{\csname #1.enc\endcsname}% % % Supported encodings: names converted to tokens in order to be able % to compare them with \ifx. \def\ascii{\csname US-ASCII.enc\endcsname}% \def\latnine{\csname ISO-8859-15.enc\endcsname}% \def\latone{\csname ISO-8859-1.enc\endcsname}% \def\lattwo{\csname ISO-8859-2.enc\endcsname}% \def\utfeight{\csname UTF-8.enc\endcsname}% % \ifx \declaredencoding \ascii \asciichardefs % \else \ifx \declaredencoding \lattwo \setnonasciicharscatcode\active \lattwochardefs % \else \ifx \declaredencoding \latone \setnonasciicharscatcode\active \latonechardefs % \else \ifx \declaredencoding \latnine \setnonasciicharscatcode\active \latninechardefs % \else \ifx \declaredencoding \utfeight \setnonasciicharscatcode\active \utfeightchardefs % \else \message{Unknown document encoding #1, ignoring.}% % \fi % utfeight \fi % latnine \fi % latone \fi % lattwo \fi % ascii } % A message to be logged when using a character that isn't available % the default font encoding (OT1). % \def\missingcharmsg#1{\message{Character missing in OT1 encoding: #1.}} % Take account of \c (plain) vs. \, (Texinfo) difference. \def\cedilla#1{\ifx\c\ptexc\c{#1}\else\,{#1}\fi} % First, make active non-ASCII characters in order for them to be % correctly categorized when TeX reads the replacement text of % macros containing the character definitions. \setnonasciicharscatcode\active % % Latin1 (ISO-8859-1) character definitions. \def\latonechardefs{% \gdef^^a0{\tie} \gdef^^a1{\exclamdown} \gdef^^a2{\missingcharmsg{CENT SIGN}} \gdef^^a3{{\pounds}} \gdef^^a4{\missingcharmsg{CURRENCY SIGN}} \gdef^^a5{\missingcharmsg{YEN SIGN}} \gdef^^a6{\missingcharmsg{BROKEN BAR}} \gdef^^a7{\S} \gdef^^a8{\"{}} \gdef^^a9{\copyright} \gdef^^aa{\ordf} \gdef^^ab{\guillemetleft} \gdef^^ac{$\lnot$} \gdef^^ad{\-} \gdef^^ae{\registeredsymbol} \gdef^^af{\={}} % \gdef^^b0{\textdegree} \gdef^^b1{$\pm$} \gdef^^b2{$^2$} \gdef^^b3{$^3$} \gdef^^b4{\'{}} \gdef^^b5{$\mu$} \gdef^^b6{\P} % \gdef^^b7{$^.$} \gdef^^b8{\cedilla\ } \gdef^^b9{$^1$} \gdef^^ba{\ordm} % \gdef^^bb{\guillemetright} \gdef^^bc{$1\over4$} \gdef^^bd{$1\over2$} \gdef^^be{$3\over4$} \gdef^^bf{\questiondown} % \gdef^^c0{\`A} \gdef^^c1{\'A} \gdef^^c2{\^A} \gdef^^c3{\~A} \gdef^^c4{\"A} \gdef^^c5{\ringaccent A} \gdef^^c6{\AE} \gdef^^c7{\cedilla C} \gdef^^c8{\`E} \gdef^^c9{\'E} \gdef^^ca{\^E} \gdef^^cb{\"E} \gdef^^cc{\`I} \gdef^^cd{\'I} \gdef^^ce{\^I} \gdef^^cf{\"I} % \gdef^^d0{\DH} \gdef^^d1{\~N} \gdef^^d2{\`O} \gdef^^d3{\'O} \gdef^^d4{\^O} \gdef^^d5{\~O} \gdef^^d6{\"O} \gdef^^d7{$\times$} \gdef^^d8{\O} \gdef^^d9{\`U} \gdef^^da{\'U} \gdef^^db{\^U} \gdef^^dc{\"U} \gdef^^dd{\'Y} \gdef^^de{\TH} \gdef^^df{\ss} % \gdef^^e0{\`a} \gdef^^e1{\'a} \gdef^^e2{\^a} \gdef^^e3{\~a} \gdef^^e4{\"a} \gdef^^e5{\ringaccent a} \gdef^^e6{\ae} \gdef^^e7{\cedilla c} \gdef^^e8{\`e} \gdef^^e9{\'e} \gdef^^ea{\^e} \gdef^^eb{\"e} \gdef^^ec{\`{\dotless i}} \gdef^^ed{\'{\dotless i}} \gdef^^ee{\^{\dotless i}} \gdef^^ef{\"{\dotless i}} % \gdef^^f0{\dh} \gdef^^f1{\~n} \gdef^^f2{\`o} \gdef^^f3{\'o} \gdef^^f4{\^o} \gdef^^f5{\~o} \gdef^^f6{\"o} \gdef^^f7{$\div$} \gdef^^f8{\o} \gdef^^f9{\`u} \gdef^^fa{\'u} \gdef^^fb{\^u} \gdef^^fc{\"u} \gdef^^fd{\'y} \gdef^^fe{\th} \gdef^^ff{\"y} } % Latin9 (ISO-8859-15) encoding character definitions. \def\latninechardefs{% % Encoding is almost identical to Latin1. \latonechardefs % \gdef^^a4{\euro} \gdef^^a6{\v S} \gdef^^a8{\v s} \gdef^^b4{\v Z} \gdef^^b8{\v z} \gdef^^bc{\OE} \gdef^^bd{\oe} \gdef^^be{\"Y} } % Latin2 (ISO-8859-2) character definitions. \def\lattwochardefs{% \gdef^^a0{\tie} \gdef^^a1{\ogonek{A}} \gdef^^a2{\u{}} \gdef^^a3{\L} \gdef^^a4{\missingcharmsg{CURRENCY SIGN}} \gdef^^a5{\v L} \gdef^^a6{\'S} \gdef^^a7{\S} \gdef^^a8{\"{}} \gdef^^a9{\v S} \gdef^^aa{\cedilla S} \gdef^^ab{\v T} \gdef^^ac{\'Z} \gdef^^ad{\-} \gdef^^ae{\v Z} \gdef^^af{\dotaccent Z} % \gdef^^b0{\textdegree} \gdef^^b1{\ogonek{a}} \gdef^^b2{\ogonek{ }} \gdef^^b3{\l} \gdef^^b4{\'{}} \gdef^^b5{\v l} \gdef^^b6{\'s} \gdef^^b7{\v{}} \gdef^^b8{\cedilla\ } \gdef^^b9{\v s} \gdef^^ba{\cedilla s} \gdef^^bb{\v t} \gdef^^bc{\'z} \gdef^^bd{\H{}} \gdef^^be{\v z} \gdef^^bf{\dotaccent z} % \gdef^^c0{\'R} \gdef^^c1{\'A} \gdef^^c2{\^A} \gdef^^c3{\u A} \gdef^^c4{\"A} \gdef^^c5{\'L} \gdef^^c6{\'C} \gdef^^c7{\cedilla C} \gdef^^c8{\v C} \gdef^^c9{\'E} \gdef^^ca{\ogonek{E}} \gdef^^cb{\"E} \gdef^^cc{\v E} \gdef^^cd{\'I} \gdef^^ce{\^I} \gdef^^cf{\v D} % \gdef^^d0{\DH} \gdef^^d1{\'N} \gdef^^d2{\v N} \gdef^^d3{\'O} \gdef^^d4{\^O} \gdef^^d5{\H O} \gdef^^d6{\"O} \gdef^^d7{$\times$} \gdef^^d8{\v R} \gdef^^d9{\ringaccent U} \gdef^^da{\'U} \gdef^^db{\H U} \gdef^^dc{\"U} \gdef^^dd{\'Y} \gdef^^de{\cedilla T} \gdef^^df{\ss} % \gdef^^e0{\'r} \gdef^^e1{\'a} \gdef^^e2{\^a} \gdef^^e3{\u a} \gdef^^e4{\"a} \gdef^^e5{\'l} \gdef^^e6{\'c} \gdef^^e7{\cedilla c} \gdef^^e8{\v c} \gdef^^e9{\'e} \gdef^^ea{\ogonek{e}} \gdef^^eb{\"e} \gdef^^ec{\v e} \gdef^^ed{\'{\dotless{i}}} \gdef^^ee{\^{\dotless{i}}} \gdef^^ef{\v d} % \gdef^^f0{\dh} \gdef^^f1{\'n} \gdef^^f2{\v n} \gdef^^f3{\'o} \gdef^^f4{\^o} \gdef^^f5{\H o} \gdef^^f6{\"o} \gdef^^f7{$\div$} \gdef^^f8{\v r} \gdef^^f9{\ringaccent u} \gdef^^fa{\'u} \gdef^^fb{\H u} \gdef^^fc{\"u} \gdef^^fd{\'y} \gdef^^fe{\cedilla t} \gdef^^ff{\dotaccent{}} } % UTF-8 character definitions. % % This code to support UTF-8 is based on LaTeX's utf8.def, with some % changes for Texinfo conventions. It is included here under the GPL by % permission from Frank Mittelbach and the LaTeX team. % \newcount\countUTFx \newcount\countUTFy \newcount\countUTFz \gdef\UTFviiiTwoOctets#1#2{\expandafter \UTFviiiDefined\csname u8:#1\string #2\endcsname} % \gdef\UTFviiiThreeOctets#1#2#3{\expandafter \UTFviiiDefined\csname u8:#1\string #2\string #3\endcsname} % \gdef\UTFviiiFourOctets#1#2#3#4{\expandafter \UTFviiiDefined\csname u8:#1\string #2\string #3\string #4\endcsname} \gdef\UTFviiiDefined#1{% \ifx #1\relax \message{\linenumber Unicode char \string #1 not defined for Texinfo}% \else \expandafter #1% \fi } \begingroup \catcode`\~13 \catcode`\"12 \def\UTFviiiLoop{% \global\catcode\countUTFx\active \uccode`\~\countUTFx \uppercase\expandafter{\UTFviiiTmp}% \advance\countUTFx by 1 \ifnum\countUTFx < \countUTFy \expandafter\UTFviiiLoop \fi} \countUTFx = "C2 \countUTFy = "E0 \def\UTFviiiTmp{% \xdef~{\noexpand\UTFviiiTwoOctets\string~}} \UTFviiiLoop \countUTFx = "E0 \countUTFy = "F0 \def\UTFviiiTmp{% \xdef~{\noexpand\UTFviiiThreeOctets\string~}} \UTFviiiLoop \countUTFx = "F0 \countUTFy = "F4 \def\UTFviiiTmp{% \xdef~{\noexpand\UTFviiiFourOctets\string~}} \UTFviiiLoop \endgroup \begingroup \catcode`\"=12 \catcode`\<=12 \catcode`\.=12 \catcode`\,=12 \catcode`\;=12 \catcode`\!=12 \catcode`\~=13 \gdef\DeclareUnicodeCharacter#1#2{% \countUTFz = "#1\relax %\wlog{\space\space defining Unicode char U+#1 (decimal \the\countUTFz)}% \begingroup \parseXMLCharref \def\UTFviiiTwoOctets##1##2{% \csname u8:##1\string ##2\endcsname}% \def\UTFviiiThreeOctets##1##2##3{% \csname u8:##1\string ##2\string ##3\endcsname}% \def\UTFviiiFourOctets##1##2##3##4{% \csname u8:##1\string ##2\string ##3\string ##4\endcsname}% \expandafter\expandafter\expandafter\expandafter \expandafter\expandafter\expandafter \gdef\UTFviiiTmp{#2}% \endgroup} \gdef\parseXMLCharref{% \ifnum\countUTFz < "A0\relax \errhelp = \EMsimple \errmessage{Cannot define Unicode char value < 00A0}% \else\ifnum\countUTFz < "800\relax \parseUTFviiiA,% \parseUTFviiiB C\UTFviiiTwoOctets.,% \else\ifnum\countUTFz < "10000\relax \parseUTFviiiA;% \parseUTFviiiA,% \parseUTFviiiB E\UTFviiiThreeOctets.{,;}% \else \parseUTFviiiA;% \parseUTFviiiA,% \parseUTFviiiA!% \parseUTFviiiB F\UTFviiiFourOctets.{!,;}% \fi\fi\fi } \gdef\parseUTFviiiA#1{% \countUTFx = \countUTFz \divide\countUTFz by 64 \countUTFy = \countUTFz \multiply\countUTFz by 64 \advance\countUTFx by -\countUTFz \advance\countUTFx by 128 \uccode `#1\countUTFx \countUTFz = \countUTFy} \gdef\parseUTFviiiB#1#2#3#4{% \advance\countUTFz by "#10\relax \uccode `#3\countUTFz \uppercase{\gdef\UTFviiiTmp{#2#3#4}}} \endgroup \def\utfeightchardefs{% \DeclareUnicodeCharacter{00A0}{\tie} \DeclareUnicodeCharacter{00A1}{\exclamdown} \DeclareUnicodeCharacter{00A3}{\pounds} \DeclareUnicodeCharacter{00A8}{\"{ }} \DeclareUnicodeCharacter{00A9}{\copyright} \DeclareUnicodeCharacter{00AA}{\ordf} \DeclareUnicodeCharacter{00AB}{\guillemetleft} \DeclareUnicodeCharacter{00AD}{\-} \DeclareUnicodeCharacter{00AE}{\registeredsymbol} \DeclareUnicodeCharacter{00AF}{\={ }} \DeclareUnicodeCharacter{00B0}{\ringaccent{ }} \DeclareUnicodeCharacter{00B4}{\'{ }} \DeclareUnicodeCharacter{00B8}{\cedilla{ }} \DeclareUnicodeCharacter{00BA}{\ordm} \DeclareUnicodeCharacter{00BB}{\guillemetright} \DeclareUnicodeCharacter{00BF}{\questiondown} \DeclareUnicodeCharacter{00C0}{\`A} \DeclareUnicodeCharacter{00C1}{\'A} \DeclareUnicodeCharacter{00C2}{\^A} \DeclareUnicodeCharacter{00C3}{\~A} \DeclareUnicodeCharacter{00C4}{\"A} \DeclareUnicodeCharacter{00C5}{\AA} \DeclareUnicodeCharacter{00C6}{\AE} \DeclareUnicodeCharacter{00C7}{\cedilla{C}} \DeclareUnicodeCharacter{00C8}{\`E} \DeclareUnicodeCharacter{00C9}{\'E} \DeclareUnicodeCharacter{00CA}{\^E} \DeclareUnicodeCharacter{00CB}{\"E} \DeclareUnicodeCharacter{00CC}{\`I} \DeclareUnicodeCharacter{00CD}{\'I} \DeclareUnicodeCharacter{00CE}{\^I} \DeclareUnicodeCharacter{00CF}{\"I} \DeclareUnicodeCharacter{00D0}{\DH} \DeclareUnicodeCharacter{00D1}{\~N} \DeclareUnicodeCharacter{00D2}{\`O} \DeclareUnicodeCharacter{00D3}{\'O} \DeclareUnicodeCharacter{00D4}{\^O} \DeclareUnicodeCharacter{00D5}{\~O} \DeclareUnicodeCharacter{00D6}{\"O} \DeclareUnicodeCharacter{00D8}{\O} \DeclareUnicodeCharacter{00D9}{\`U} \DeclareUnicodeCharacter{00DA}{\'U} \DeclareUnicodeCharacter{00DB}{\^U} \DeclareUnicodeCharacter{00DC}{\"U} \DeclareUnicodeCharacter{00DD}{\'Y} \DeclareUnicodeCharacter{00DE}{\TH} \DeclareUnicodeCharacter{00DF}{\ss} \DeclareUnicodeCharacter{00E0}{\`a} \DeclareUnicodeCharacter{00E1}{\'a} \DeclareUnicodeCharacter{00E2}{\^a} \DeclareUnicodeCharacter{00E3}{\~a} \DeclareUnicodeCharacter{00E4}{\"a} \DeclareUnicodeCharacter{00E5}{\aa} \DeclareUnicodeCharacter{00E6}{\ae} \DeclareUnicodeCharacter{00E7}{\cedilla{c}} \DeclareUnicodeCharacter{00E8}{\`e} \DeclareUnicodeCharacter{00E9}{\'e} \DeclareUnicodeCharacter{00EA}{\^e} \DeclareUnicodeCharacter{00EB}{\"e} \DeclareUnicodeCharacter{00EC}{\`{\dotless{i}}} \DeclareUnicodeCharacter{00ED}{\'{\dotless{i}}} \DeclareUnicodeCharacter{00EE}{\^{\dotless{i}}} \DeclareUnicodeCharacter{00EF}{\"{\dotless{i}}} \DeclareUnicodeCharacter{00F0}{\dh} \DeclareUnicodeCharacter{00F1}{\~n} \DeclareUnicodeCharacter{00F2}{\`o} \DeclareUnicodeCharacter{00F3}{\'o} \DeclareUnicodeCharacter{00F4}{\^o} \DeclareUnicodeCharacter{00F5}{\~o} \DeclareUnicodeCharacter{00F6}{\"o} \DeclareUnicodeCharacter{00F8}{\o} \DeclareUnicodeCharacter{00F9}{\`u} \DeclareUnicodeCharacter{00FA}{\'u} \DeclareUnicodeCharacter{00FB}{\^u} \DeclareUnicodeCharacter{00FC}{\"u} \DeclareUnicodeCharacter{00FD}{\'y} \DeclareUnicodeCharacter{00FE}{\th} \DeclareUnicodeCharacter{00FF}{\"y} \DeclareUnicodeCharacter{0100}{\=A} \DeclareUnicodeCharacter{0101}{\=a} \DeclareUnicodeCharacter{0102}{\u{A}} \DeclareUnicodeCharacter{0103}{\u{a}} \DeclareUnicodeCharacter{0104}{\ogonek{A}} \DeclareUnicodeCharacter{0105}{\ogonek{a}} \DeclareUnicodeCharacter{0106}{\'C} \DeclareUnicodeCharacter{0107}{\'c} \DeclareUnicodeCharacter{0108}{\^C} \DeclareUnicodeCharacter{0109}{\^c} \DeclareUnicodeCharacter{0118}{\ogonek{E}} \DeclareUnicodeCharacter{0119}{\ogonek{e}} \DeclareUnicodeCharacter{010A}{\dotaccent{C}} \DeclareUnicodeCharacter{010B}{\dotaccent{c}} \DeclareUnicodeCharacter{010C}{\v{C}} \DeclareUnicodeCharacter{010D}{\v{c}} \DeclareUnicodeCharacter{010E}{\v{D}} \DeclareUnicodeCharacter{0112}{\=E} \DeclareUnicodeCharacter{0113}{\=e} \DeclareUnicodeCharacter{0114}{\u{E}} \DeclareUnicodeCharacter{0115}{\u{e}} \DeclareUnicodeCharacter{0116}{\dotaccent{E}} \DeclareUnicodeCharacter{0117}{\dotaccent{e}} \DeclareUnicodeCharacter{011A}{\v{E}} \DeclareUnicodeCharacter{011B}{\v{e}} \DeclareUnicodeCharacter{011C}{\^G} \DeclareUnicodeCharacter{011D}{\^g} \DeclareUnicodeCharacter{011E}{\u{G}} \DeclareUnicodeCharacter{011F}{\u{g}} \DeclareUnicodeCharacter{0120}{\dotaccent{G}} \DeclareUnicodeCharacter{0121}{\dotaccent{g}} \DeclareUnicodeCharacter{0124}{\^H} \DeclareUnicodeCharacter{0125}{\^h} \DeclareUnicodeCharacter{0128}{\~I} \DeclareUnicodeCharacter{0129}{\~{\dotless{i}}} \DeclareUnicodeCharacter{012A}{\=I} \DeclareUnicodeCharacter{012B}{\={\dotless{i}}} \DeclareUnicodeCharacter{012C}{\u{I}} \DeclareUnicodeCharacter{012D}{\u{\dotless{i}}} \DeclareUnicodeCharacter{0130}{\dotaccent{I}} \DeclareUnicodeCharacter{0131}{\dotless{i}} \DeclareUnicodeCharacter{0132}{IJ} \DeclareUnicodeCharacter{0133}{ij} \DeclareUnicodeCharacter{0134}{\^J} \DeclareUnicodeCharacter{0135}{\^{\dotless{j}}} \DeclareUnicodeCharacter{0139}{\'L} \DeclareUnicodeCharacter{013A}{\'l} \DeclareUnicodeCharacter{0141}{\L} \DeclareUnicodeCharacter{0142}{\l} \DeclareUnicodeCharacter{0143}{\'N} \DeclareUnicodeCharacter{0144}{\'n} \DeclareUnicodeCharacter{0147}{\v{N}} \DeclareUnicodeCharacter{0148}{\v{n}} \DeclareUnicodeCharacter{014C}{\=O} \DeclareUnicodeCharacter{014D}{\=o} \DeclareUnicodeCharacter{014E}{\u{O}} \DeclareUnicodeCharacter{014F}{\u{o}} \DeclareUnicodeCharacter{0150}{\H{O}} \DeclareUnicodeCharacter{0151}{\H{o}} \DeclareUnicodeCharacter{0152}{\OE} \DeclareUnicodeCharacter{0153}{\oe} \DeclareUnicodeCharacter{0154}{\'R} \DeclareUnicodeCharacter{0155}{\'r} \DeclareUnicodeCharacter{0158}{\v{R}} \DeclareUnicodeCharacter{0159}{\v{r}} \DeclareUnicodeCharacter{015A}{\'S} \DeclareUnicodeCharacter{015B}{\'s} \DeclareUnicodeCharacter{015C}{\^S} \DeclareUnicodeCharacter{015D}{\^s} \DeclareUnicodeCharacter{015E}{\cedilla{S}} \DeclareUnicodeCharacter{015F}{\cedilla{s}} \DeclareUnicodeCharacter{0160}{\v{S}} \DeclareUnicodeCharacter{0161}{\v{s}} \DeclareUnicodeCharacter{0162}{\cedilla{t}} \DeclareUnicodeCharacter{0163}{\cedilla{T}} \DeclareUnicodeCharacter{0164}{\v{T}} \DeclareUnicodeCharacter{0168}{\~U} \DeclareUnicodeCharacter{0169}{\~u} \DeclareUnicodeCharacter{016A}{\=U} \DeclareUnicodeCharacter{016B}{\=u} \DeclareUnicodeCharacter{016C}{\u{U}} \DeclareUnicodeCharacter{016D}{\u{u}} \DeclareUnicodeCharacter{016E}{\ringaccent{U}} \DeclareUnicodeCharacter{016F}{\ringaccent{u}} \DeclareUnicodeCharacter{0170}{\H{U}} \DeclareUnicodeCharacter{0171}{\H{u}} \DeclareUnicodeCharacter{0174}{\^W} \DeclareUnicodeCharacter{0175}{\^w} \DeclareUnicodeCharacter{0176}{\^Y} \DeclareUnicodeCharacter{0177}{\^y} \DeclareUnicodeCharacter{0178}{\"Y} \DeclareUnicodeCharacter{0179}{\'Z} \DeclareUnicodeCharacter{017A}{\'z} \DeclareUnicodeCharacter{017B}{\dotaccent{Z}} \DeclareUnicodeCharacter{017C}{\dotaccent{z}} \DeclareUnicodeCharacter{017D}{\v{Z}} \DeclareUnicodeCharacter{017E}{\v{z}} \DeclareUnicodeCharacter{01C4}{D\v{Z}} \DeclareUnicodeCharacter{01C5}{D\v{z}} \DeclareUnicodeCharacter{01C6}{d\v{z}} \DeclareUnicodeCharacter{01C7}{LJ} \DeclareUnicodeCharacter{01C8}{Lj} \DeclareUnicodeCharacter{01C9}{lj} \DeclareUnicodeCharacter{01CA}{NJ} \DeclareUnicodeCharacter{01CB}{Nj} \DeclareUnicodeCharacter{01CC}{nj} \DeclareUnicodeCharacter{01CD}{\v{A}} \DeclareUnicodeCharacter{01CE}{\v{a}} \DeclareUnicodeCharacter{01CF}{\v{I}} \DeclareUnicodeCharacter{01D0}{\v{\dotless{i}}} \DeclareUnicodeCharacter{01D1}{\v{O}} \DeclareUnicodeCharacter{01D2}{\v{o}} \DeclareUnicodeCharacter{01D3}{\v{U}} \DeclareUnicodeCharacter{01D4}{\v{u}} \DeclareUnicodeCharacter{01E2}{\={\AE}} \DeclareUnicodeCharacter{01E3}{\={\ae}} \DeclareUnicodeCharacter{01E6}{\v{G}} \DeclareUnicodeCharacter{01E7}{\v{g}} \DeclareUnicodeCharacter{01E8}{\v{K}} \DeclareUnicodeCharacter{01E9}{\v{k}} \DeclareUnicodeCharacter{01F0}{\v{\dotless{j}}} \DeclareUnicodeCharacter{01F1}{DZ} \DeclareUnicodeCharacter{01F2}{Dz} \DeclareUnicodeCharacter{01F3}{dz} \DeclareUnicodeCharacter{01F4}{\'G} \DeclareUnicodeCharacter{01F5}{\'g} \DeclareUnicodeCharacter{01F8}{\`N} \DeclareUnicodeCharacter{01F9}{\`n} \DeclareUnicodeCharacter{01FC}{\'{\AE}} \DeclareUnicodeCharacter{01FD}{\'{\ae}} \DeclareUnicodeCharacter{01FE}{\'{\O}} \DeclareUnicodeCharacter{01FF}{\'{\o}} \DeclareUnicodeCharacter{021E}{\v{H}} \DeclareUnicodeCharacter{021F}{\v{h}} \DeclareUnicodeCharacter{0226}{\dotaccent{A}} \DeclareUnicodeCharacter{0227}{\dotaccent{a}} \DeclareUnicodeCharacter{0228}{\cedilla{E}} \DeclareUnicodeCharacter{0229}{\cedilla{e}} \DeclareUnicodeCharacter{022E}{\dotaccent{O}} \DeclareUnicodeCharacter{022F}{\dotaccent{o}} \DeclareUnicodeCharacter{0232}{\=Y} \DeclareUnicodeCharacter{0233}{\=y} \DeclareUnicodeCharacter{0237}{\dotless{j}} \DeclareUnicodeCharacter{02DB}{\ogonek{ }} \DeclareUnicodeCharacter{1E02}{\dotaccent{B}} \DeclareUnicodeCharacter{1E03}{\dotaccent{b}} \DeclareUnicodeCharacter{1E04}{\udotaccent{B}} \DeclareUnicodeCharacter{1E05}{\udotaccent{b}} \DeclareUnicodeCharacter{1E06}{\ubaraccent{B}} \DeclareUnicodeCharacter{1E07}{\ubaraccent{b}} \DeclareUnicodeCharacter{1E0A}{\dotaccent{D}} \DeclareUnicodeCharacter{1E0B}{\dotaccent{d}} \DeclareUnicodeCharacter{1E0C}{\udotaccent{D}} \DeclareUnicodeCharacter{1E0D}{\udotaccent{d}} \DeclareUnicodeCharacter{1E0E}{\ubaraccent{D}} \DeclareUnicodeCharacter{1E0F}{\ubaraccent{d}} \DeclareUnicodeCharacter{1E1E}{\dotaccent{F}} \DeclareUnicodeCharacter{1E1F}{\dotaccent{f}} \DeclareUnicodeCharacter{1E20}{\=G} \DeclareUnicodeCharacter{1E21}{\=g} \DeclareUnicodeCharacter{1E22}{\dotaccent{H}} \DeclareUnicodeCharacter{1E23}{\dotaccent{h}} \DeclareUnicodeCharacter{1E24}{\udotaccent{H}} \DeclareUnicodeCharacter{1E25}{\udotaccent{h}} \DeclareUnicodeCharacter{1E26}{\"H} \DeclareUnicodeCharacter{1E27}{\"h} \DeclareUnicodeCharacter{1E30}{\'K} \DeclareUnicodeCharacter{1E31}{\'k} \DeclareUnicodeCharacter{1E32}{\udotaccent{K}} \DeclareUnicodeCharacter{1E33}{\udotaccent{k}} \DeclareUnicodeCharacter{1E34}{\ubaraccent{K}} \DeclareUnicodeCharacter{1E35}{\ubaraccent{k}} \DeclareUnicodeCharacter{1E36}{\udotaccent{L}} \DeclareUnicodeCharacter{1E37}{\udotaccent{l}} \DeclareUnicodeCharacter{1E3A}{\ubaraccent{L}} \DeclareUnicodeCharacter{1E3B}{\ubaraccent{l}} \DeclareUnicodeCharacter{1E3E}{\'M} \DeclareUnicodeCharacter{1E3F}{\'m} \DeclareUnicodeCharacter{1E40}{\dotaccent{M}} \DeclareUnicodeCharacter{1E41}{\dotaccent{m}} \DeclareUnicodeCharacter{1E42}{\udotaccent{M}} \DeclareUnicodeCharacter{1E43}{\udotaccent{m}} \DeclareUnicodeCharacter{1E44}{\dotaccent{N}} \DeclareUnicodeCharacter{1E45}{\dotaccent{n}} \DeclareUnicodeCharacter{1E46}{\udotaccent{N}} \DeclareUnicodeCharacter{1E47}{\udotaccent{n}} \DeclareUnicodeCharacter{1E48}{\ubaraccent{N}} \DeclareUnicodeCharacter{1E49}{\ubaraccent{n}} \DeclareUnicodeCharacter{1E54}{\'P} \DeclareUnicodeCharacter{1E55}{\'p} \DeclareUnicodeCharacter{1E56}{\dotaccent{P}} \DeclareUnicodeCharacter{1E57}{\dotaccent{p}} \DeclareUnicodeCharacter{1E58}{\dotaccent{R}} \DeclareUnicodeCharacter{1E59}{\dotaccent{r}} \DeclareUnicodeCharacter{1E5A}{\udotaccent{R}} \DeclareUnicodeCharacter{1E5B}{\udotaccent{r}} \DeclareUnicodeCharacter{1E5E}{\ubaraccent{R}} \DeclareUnicodeCharacter{1E5F}{\ubaraccent{r}} \DeclareUnicodeCharacter{1E60}{\dotaccent{S}} \DeclareUnicodeCharacter{1E61}{\dotaccent{s}} \DeclareUnicodeCharacter{1E62}{\udotaccent{S}} \DeclareUnicodeCharacter{1E63}{\udotaccent{s}} \DeclareUnicodeCharacter{1E6A}{\dotaccent{T}} \DeclareUnicodeCharacter{1E6B}{\dotaccent{t}} \DeclareUnicodeCharacter{1E6C}{\udotaccent{T}} \DeclareUnicodeCharacter{1E6D}{\udotaccent{t}} \DeclareUnicodeCharacter{1E6E}{\ubaraccent{T}} \DeclareUnicodeCharacter{1E6F}{\ubaraccent{t}} \DeclareUnicodeCharacter{1E7C}{\~V} \DeclareUnicodeCharacter{1E7D}{\~v} \DeclareUnicodeCharacter{1E7E}{\udotaccent{V}} \DeclareUnicodeCharacter{1E7F}{\udotaccent{v}} \DeclareUnicodeCharacter{1E80}{\`W} \DeclareUnicodeCharacter{1E81}{\`w} \DeclareUnicodeCharacter{1E82}{\'W} \DeclareUnicodeCharacter{1E83}{\'w} \DeclareUnicodeCharacter{1E84}{\"W} \DeclareUnicodeCharacter{1E85}{\"w} \DeclareUnicodeCharacter{1E86}{\dotaccent{W}} \DeclareUnicodeCharacter{1E87}{\dotaccent{w}} \DeclareUnicodeCharacter{1E88}{\udotaccent{W}} \DeclareUnicodeCharacter{1E89}{\udotaccent{w}} \DeclareUnicodeCharacter{1E8A}{\dotaccent{X}} \DeclareUnicodeCharacter{1E8B}{\dotaccent{x}} \DeclareUnicodeCharacter{1E8C}{\"X} \DeclareUnicodeCharacter{1E8D}{\"x} \DeclareUnicodeCharacter{1E8E}{\dotaccent{Y}} \DeclareUnicodeCharacter{1E8F}{\dotaccent{y}} \DeclareUnicodeCharacter{1E90}{\^Z} \DeclareUnicodeCharacter{1E91}{\^z} \DeclareUnicodeCharacter{1E92}{\udotaccent{Z}} \DeclareUnicodeCharacter{1E93}{\udotaccent{z}} \DeclareUnicodeCharacter{1E94}{\ubaraccent{Z}} \DeclareUnicodeCharacter{1E95}{\ubaraccent{z}} \DeclareUnicodeCharacter{1E96}{\ubaraccent{h}} \DeclareUnicodeCharacter{1E97}{\"t} \DeclareUnicodeCharacter{1E98}{\ringaccent{w}} \DeclareUnicodeCharacter{1E99}{\ringaccent{y}} \DeclareUnicodeCharacter{1EA0}{\udotaccent{A}} \DeclareUnicodeCharacter{1EA1}{\udotaccent{a}} \DeclareUnicodeCharacter{1EB8}{\udotaccent{E}} \DeclareUnicodeCharacter{1EB9}{\udotaccent{e}} \DeclareUnicodeCharacter{1EBC}{\~E} \DeclareUnicodeCharacter{1EBD}{\~e} \DeclareUnicodeCharacter{1ECA}{\udotaccent{I}} \DeclareUnicodeCharacter{1ECB}{\udotaccent{i}} \DeclareUnicodeCharacter{1ECC}{\udotaccent{O}} \DeclareUnicodeCharacter{1ECD}{\udotaccent{o}} \DeclareUnicodeCharacter{1EE4}{\udotaccent{U}} \DeclareUnicodeCharacter{1EE5}{\udotaccent{u}} \DeclareUnicodeCharacter{1EF2}{\`Y} \DeclareUnicodeCharacter{1EF3}{\`y} \DeclareUnicodeCharacter{1EF4}{\udotaccent{Y}} \DeclareUnicodeCharacter{1EF8}{\~Y} \DeclareUnicodeCharacter{1EF9}{\~y} \DeclareUnicodeCharacter{2013}{--} \DeclareUnicodeCharacter{2014}{---} \DeclareUnicodeCharacter{2018}{\quoteleft} \DeclareUnicodeCharacter{2019}{\quoteright} \DeclareUnicodeCharacter{201A}{\quotesinglbase} \DeclareUnicodeCharacter{201C}{\quotedblleft} \DeclareUnicodeCharacter{201D}{\quotedblright} \DeclareUnicodeCharacter{201E}{\quotedblbase} \DeclareUnicodeCharacter{2022}{\bullet} \DeclareUnicodeCharacter{2026}{\dots} \DeclareUnicodeCharacter{2039}{\guilsinglleft} \DeclareUnicodeCharacter{203A}{\guilsinglright} \DeclareUnicodeCharacter{20AC}{\euro} \DeclareUnicodeCharacter{2192}{\expansion} \DeclareUnicodeCharacter{21D2}{\result} \DeclareUnicodeCharacter{2212}{\minus} \DeclareUnicodeCharacter{2217}{\point} \DeclareUnicodeCharacter{2261}{\equiv} }% end of \utfeightchardefs % US-ASCII character definitions. \def\asciichardefs{% nothing need be done \relax } % Make non-ASCII characters printable again for compatibility with % existing Texinfo documents that may use them, even without declaring a % document encoding. % \setnonasciicharscatcode \other \message{formatting,} \newdimen\defaultparindent \defaultparindent = 15pt \chapheadingskip = 15pt plus 4pt minus 2pt \secheadingskip = 12pt plus 3pt minus 2pt \subsecheadingskip = 9pt plus 2pt minus 2pt % Prevent underfull vbox error messages. \vbadness = 10000 % Don't be very finicky about underfull hboxes, either. \hbadness = 6666 % Following George Bush, get rid of widows and orphans. \widowpenalty=10000 \clubpenalty=10000 % Use TeX 3.0's \emergencystretch to help line breaking, but if we're % using an old version of TeX, don't do anything. We want the amount of % stretch added to depend on the line length, hence the dependence on % \hsize. We call this whenever the paper size is set. % \def\setemergencystretch{% \ifx\emergencystretch\thisisundefined % Allow us to assign to \emergencystretch anyway. \def\emergencystretch{\dimen0}% \else \emergencystretch = .15\hsize \fi } % Parameters in order: 1) textheight; 2) textwidth; % 3) voffset; 4) hoffset; 5) binding offset; 6) topskip; % 7) physical page height; 8) physical page width. % % We also call \setleading{\textleading}, so the caller should define % \textleading. The caller should also set \parskip. % \def\internalpagesizes#1#2#3#4#5#6#7#8{% \voffset = #3\relax \topskip = #6\relax \splittopskip = \topskip % \vsize = #1\relax \advance\vsize by \topskip \outervsize = \vsize \advance\outervsize by 2\topandbottommargin \pageheight = \vsize % \hsize = #2\relax \outerhsize = \hsize \advance\outerhsize by 0.5in \pagewidth = \hsize % \normaloffset = #4\relax \bindingoffset = #5\relax % \ifpdf \pdfpageheight #7\relax \pdfpagewidth #8\relax % if we don't reset these, they will remain at "1 true in" of % whatever layout pdftex was dumped with. \pdfhorigin = 1 true in \pdfvorigin = 1 true in \fi % \setleading{\textleading} % \parindent = \defaultparindent \setemergencystretch } % @letterpaper (the default). \def\letterpaper{{\globaldefs = 1 \parskip = 3pt plus 2pt minus 1pt \textleading = 13.2pt % % If page is nothing but text, make it come out even. \internalpagesizes{607.2pt}{6in}% that's 46 lines {\voffset}{.25in}% {\bindingoffset}{36pt}% {11in}{8.5in}% }} % Use @smallbook to reset parameters for 7x9.25 trim size. \def\smallbook{{\globaldefs = 1 \parskip = 2pt plus 1pt \textleading = 12pt % \internalpagesizes{7.5in}{5in}% {-.2in}{0in}% {\bindingoffset}{16pt}% {9.25in}{7in}% % \lispnarrowing = 0.3in \tolerance = 700 \hfuzz = 1pt \contentsrightmargin = 0pt \defbodyindent = .5cm }} % Use @smallerbook to reset parameters for 6x9 trim size. % (Just testing, parameters still in flux.) \def\smallerbook{{\globaldefs = 1 \parskip = 1.5pt plus 1pt \textleading = 12pt % \internalpagesizes{7.4in}{4.8in}% {-.2in}{-.4in}% {0pt}{14pt}% {9in}{6in}% % \lispnarrowing = 0.25in \tolerance = 700 \hfuzz = 1pt \contentsrightmargin = 0pt \defbodyindent = .4cm }} % Use @afourpaper to print on European A4 paper. \def\afourpaper{{\globaldefs = 1 \parskip = 3pt plus 2pt minus 1pt \textleading = 13.2pt % % Double-side printing via postscript on Laserjet 4050 % prints double-sided nicely when \bindingoffset=10mm and \hoffset=-6mm. % To change the settings for a different printer or situation, adjust % \normaloffset until the front-side and back-side texts align. Then % do the same for \bindingoffset. You can set these for testing in % your texinfo source file like this: % @tex % \global\normaloffset = -6mm % \global\bindingoffset = 10mm % @end tex \internalpagesizes{673.2pt}{160mm}% that's 51 lines {\voffset}{\hoffset}% {\bindingoffset}{44pt}% {297mm}{210mm}% % \tolerance = 700 \hfuzz = 1pt \contentsrightmargin = 0pt \defbodyindent = 5mm }} % Use @afivepaper to print on European A5 paper. % From romildo@urano.iceb.ufop.br, 2 July 2000. % He also recommends making @example and @lisp be small. \def\afivepaper{{\globaldefs = 1 \parskip = 2pt plus 1pt minus 0.1pt \textleading = 12.5pt % \internalpagesizes{160mm}{120mm}% {\voffset}{\hoffset}% {\bindingoffset}{8pt}% {210mm}{148mm}% % \lispnarrowing = 0.2in \tolerance = 800 \hfuzz = 1.2pt \contentsrightmargin = 0pt \defbodyindent = 2mm \tableindent = 12mm }} % A specific text layout, 24x15cm overall, intended for A4 paper. \def\afourlatex{{\globaldefs = 1 \afourpaper \internalpagesizes{237mm}{150mm}% {\voffset}{4.6mm}% {\bindingoffset}{7mm}% {297mm}{210mm}% % % Must explicitly reset to 0 because we call \afourpaper. \globaldefs = 0 }} % Use @afourwide to print on A4 paper in landscape format. \def\afourwide{{\globaldefs = 1 \afourpaper \internalpagesizes{241mm}{165mm}% {\voffset}{-2.95mm}% {\bindingoffset}{7mm}% {297mm}{210mm}% \globaldefs = 0 }} % @pagesizes TEXTHEIGHT[,TEXTWIDTH] % Perhaps we should allow setting the margins, \topskip, \parskip, % and/or leading, also. Or perhaps we should compute them somehow. % \parseargdef\pagesizes{\pagesizesyyy #1,,\finish} \def\pagesizesyyy#1,#2,#3\finish{{% \setbox0 = \hbox{\ignorespaces #2}\ifdim\wd0 > 0pt \hsize=#2\relax \fi \globaldefs = 1 % \parskip = 3pt plus 2pt minus 1pt \setleading{\textleading}% % \dimen0 = #1\relax \advance\dimen0 by \voffset % \dimen2 = \hsize \advance\dimen2 by \normaloffset % \internalpagesizes{#1}{\hsize}% {\voffset}{\normaloffset}% {\bindingoffset}{44pt}% {\dimen0}{\dimen2}% }} % Set default to letter. % \letterpaper \message{and turning on texinfo input format.} \def^^L{\par} % remove \outer, so ^L can appear in an @comment % DEL is a comment character, in case @c does not suffice. \catcode`\^^? = 14 % Define macros to output various characters with catcode for normal text. \catcode`\"=\other \def\normaldoublequote{"} \catcode`\$=\other \def\normaldollar{$}%$ font-lock fix \catcode`\+=\other \def\normalplus{+} \catcode`\<=\other \def\normalless{<} \catcode`\>=\other \def\normalgreater{>} \catcode`\^=\other \def\normalcaret{^} \catcode`\_=\other \def\normalunderscore{_} \catcode`\|=\other \def\normalverticalbar{|} \catcode`\~=\other \def\normaltilde{~} % This macro is used to make a character print one way in \tt % (where it can probably be output as-is), and another way in other fonts, % where something hairier probably needs to be done. % % #1 is what to print if we are indeed using \tt; #2 is what to print % otherwise. Since all the Computer Modern typewriter fonts have zero % interword stretch (and shrink), and it is reasonable to expect all % typewriter fonts to have this, we can check that font parameter. % \def\ifusingtt#1#2{\ifdim \fontdimen3\font=0pt #1\else #2\fi} % Same as above, but check for italic font. Actually this also catches % non-italic slanted fonts since it is impossible to distinguish them from % italic fonts. But since this is only used by $ and it uses \sl anyway % this is not a problem. \def\ifusingit#1#2{\ifdim \fontdimen1\font>0pt #1\else #2\fi} % Turn off all special characters except @ % (and those which the user can use as if they were ordinary). % Most of these we simply print from the \tt font, but for some, we can % use math or other variants that look better in normal text. \catcode`\"=\active \def\activedoublequote{{\tt\char34}} \let"=\activedoublequote \catcode`\~=\active \def~{{\tt\char126}} \chardef\hat=`\^ \catcode`\^=\active \def^{{\tt \hat}} \catcode`\_=\active \def_{\ifusingtt\normalunderscore\_} \let\realunder=_ % Subroutine for the previous macro. \def\_{\leavevmode \kern.07em \vbox{\hrule width.3em height.1ex}\kern .07em } \catcode`\|=\active \def|{{\tt\char124}} \chardef \less=`\< \catcode`\<=\active \def<{{\tt \less}} \chardef \gtr=`\> \catcode`\>=\active \def>{{\tt \gtr}} \catcode`\+=\active \def+{{\tt \char 43}} \catcode`\$=\active \def${\ifusingit{{\sl\$}}\normaldollar}%$ font-lock fix % If a .fmt file is being used, characters that might appear in a file % name cannot be active until we have parsed the command line. % So turn them off again, and have \everyjob (or @setfilename) turn them on. % \otherifyactive is called near the end of this file. \def\otherifyactive{\catcode`+=\other \catcode`\_=\other} % Used sometimes to turn off (effectively) the active characters even after % parsing them. \def\turnoffactive{% \normalturnoffactive \otherbackslash } \catcode`\@=0 % \backslashcurfont outputs one backslash character in current font, % as in \char`\\. \global\chardef\backslashcurfont=`\\ \global\let\rawbackslashxx=\backslashcurfont % let existing .??s files work % \realbackslash is an actual character `\' with catcode other, and % \doublebackslash is two of them (for the pdf outlines). {\catcode`\\=\other @gdef@realbackslash{\} @gdef@doublebackslash{\\}} % In texinfo, backslash is an active character; it prints the backslash % in fixed width font. \catcode`\\=\active % @ for escape char from now on. % The story here is that in math mode, the \char of \backslashcurfont % ends up printing the roman \ from the math symbol font (because \char % in math mode uses the \mathcode, and plain.tex sets % \mathcode`\\="026E). It seems better for @backslashchar{} to always % print a typewriter backslash, hence we use an explicit \mathchar, % which is the decimal equivalent of "715c (class 7, e.g., use \fam; % ignored family value; char position "5C). We can't use " for the % usual hex value because it has already been made active. @def@normalbackslash{{@tt @ifmmode @mathchar29020 @else @backslashcurfont @fi}} @let@backslashchar = @normalbackslash % @backslashchar{} is for user documents. % On startup, @fixbackslash assigns: % @let \ = @normalbackslash % \rawbackslash defines an active \ to do \backslashcurfont. % \otherbackslash defines an active \ to be a literal `\' character with % catcode other. We switch back and forth between these. @gdef@rawbackslash{@let\=@backslashcurfont} @gdef@otherbackslash{@let\=@realbackslash} % Same as @turnoffactive except outputs \ as {\tt\char`\\} instead of % the literal character `\'. % @def@normalturnoffactive{% @let"=@normaldoublequote @let$=@normaldollar %$ font-lock fix @let+=@normalplus @let<=@normalless @let>=@normalgreater @let\=@normalbackslash @let^=@normalcaret @let_=@normalunderscore @let|=@normalverticalbar @let~=@normaltilde @markupsetuplqdefault @markupsetuprqdefault @unsepspaces } % Make _ and + \other characters, temporarily. % This is canceled by @fixbackslash. @otherifyactive % If a .fmt file is being used, we don't want the `\input texinfo' to show up. % That is what \eatinput is for; after that, the `\' should revert to printing % a backslash. % @gdef@eatinput input texinfo{@fixbackslash} @global@let\ = @eatinput % On the other hand, perhaps the file did not have a `\input texinfo'. Then % the first `\' in the file would cause an error. This macro tries to fix % that, assuming it is called before the first `\' could plausibly occur. % Also turn back on active characters that might appear in the input % file name, in case not using a pre-dumped format. % @gdef@fixbackslash{% @ifx\@eatinput @let\ = @normalbackslash @fi @catcode`+=@active @catcode`@_=@active } % Say @foo, not \foo, in error messages. @escapechar = `@@ % These (along with & and #) are made active for url-breaking, so need % active definitions as the normal characters. @def@normaldot{.} @def@normalquest{?} @def@normalslash{/} % These look ok in all fonts, so just make them not special. % @hashchar{} gets its own user-level command, because of #line. @catcode`@& = @other @def@normalamp{&} @catcode`@# = @other @def@normalhash{#} @catcode`@% = @other @def@normalpercent{%} @let @hashchar = @normalhash @c Finally, make ` and ' active, so that txicodequoteundirected and @c txicodequotebacktick work right in, e.g., @w{@code{`foo'}}. If we @c don't make ` and ' active, @code will not get them as active chars. @c Do this last of all since we use ` in the previous @catcode assignments. @catcode`@'=@active @catcode`@`=@active @markupsetuplqdefault @markupsetuprqdefault @c Local variables: @c eval: (add-hook 'write-file-hooks 'time-stamp) @c page-delimiter: "^\\\\message" @c time-stamp-start: "def\\\\texinfoversion{" @c time-stamp-format: "%:y-%02m-%02d.%02H" @c time-stamp-end: "}" @c End: @c vim:sw=2: @ignore arch-tag: e1b36e32-c96e-4135-a41a-0b2efa2ea115 @end ignore smalltalk-3.2.5/build-aux/relocatable.m40000644000175000017500000000741612123404352015043 00000000000000# relocatable.m4 serial 1 (gettext-0.12) dnl Copyright (C) 2003 Free Software Foundation, Inc. dnl This file is free software, distributed under the terms of the GNU dnl General Public License. As a special exception to the GNU General dnl Public License, this file may be distributed as part of a program dnl that contains a configuration script generated by Autoconf, under dnl the same distribution terms as the rest of that program. dnl From Bruno Haible. dnl Support for relocateble programs. AC_DEFUN([AC_RELOCATABLE], [ AC_REQUIRE([AC_PROG_INSTALL]) AC_BEFORE([AC_PROG_INSTALL],[AC_RELOCATABLE]) AC_REQUIRE([AC_LIB_LIBPATH]) AC_REQUIRE([AC_RELOCATABLE_LIBRARY]) use_elf_origin_trick=no if test $RELOCATABLE = yes; then # --enable-relocatable implies --disable-rpath enable_rpath=no AC_LIBOBJ([relocatable]) AC_DEFINE([ENABLE_RELOCATABLE], 1, [Define to 1 if the package shall run at any location in the filesystem.]) case "$host_os" in linux*) use_elf_origin_trick=yes ;; esac if test $use_elf_origin_trick = yes; then dnl Use the dynamic linker's support for relocatable programs. case "$ac_aux_dir" in /*) reloc_ldflags="$ac_aux_dir/reloc-ldflags" ;; *) reloc_ldflags="\$(top_builddir)/$ac_aux_dir/reloc-ldflags" ;; esac SET_RELOCATABLE="RELOCATABLE_LDFLAGS = \"$reloc_ldflags\" \"@host@\" \"\$(RELOCATABLE_LIBRARY_PATH)\"" else dnl Unfortunately we cannot define INSTALL_PROGRAM to a command dnl consisting of more than one word - libtool doesn't support this. dnl So we abuse the INSTALL_PROGRAM_ENV hook, originally meant for the dnl 'install-strip' target. SET_RELOCATABLE="INSTALL_PROGRAM_ENV = RELOC_LIBRARY_PATH_VAR=\"$shlibpath_var\" RELOC_LIBRARY_PATH_VALUE=\"\$(RELOCATABLE_LIBRARY_PATH)\" RELOC_PREFIX=\"\$(prefix)\" RELOC_COMPILE_COMMAND=\"\$(CC) \$(CPPFLAGS) \$(CFLAGS) \$(LDFLAGS)\" RELOC_SRCDIR=\"\$(RELOCATABLE_SRC_DIR)\" RELOC_BUILDDIR=\"\$(RELOCATABLE_BUILD_DIR)\" RELOC_CONFIG_H_DIR=\"\$(RELOCATABLE_CONFIG_H_DIR)\" RELOC_INSTALL_PROG=\"$INSTALL_PROGRAM\"" case "$ac_aux_dir" in /*) INSTALL_PROGRAM="$ac_aux_dir/install-reloc" ;; *) INSTALL_PROGRAM="\$(top_builddir)/$ac_aux_dir/install-reloc" ;; esac fi else SET_RELOCATABLE= fi AC_SUBST([SET_RELOCATABLE]) AM_CONDITIONAL([RELOCATABLE_VIA_LD], [test $use_elf_origin_trick = yes]) ]) dnl Support for relocatable libraries. AC_DEFUN([AC_RELOCATABLE_LIBRARY], [ AC_REQUIRE([AC_RELOCATABLE_NOP]) dnl Easier to put this here once, instead of into the DEFS of each Makefile. if test "X$prefix" = "XNONE"; then reloc_final_prefix="$ac_default_prefix" else reloc_final_prefix="$prefix" fi AC_DEFINE_UNQUOTED([INSTALLPREFIX], ["${reloc_final_prefix}"], [Define to the value of ${prefix}, as a string.]) ]) dnl Support for relocatable packages for which it is a nop. AC_DEFUN([AC_RELOCATABLE_NOP], [ AC_ARG_ENABLE(relocatable, [ --enable-relocatable install a package that can be moved in the filesystem], [if test "$enableval" != no; then RELOCATABLE=yes else RELOCATABLE=no fi ], RELOCATABLE=yes) AC_SUBST(RELOCATABLE) ]) dnl Determine the platform dependent parameters needed to use relocatability: dnl shlibpath_var. AC_DEFUN([AC_LIB_LIBPATH], [ AC_REQUIRE([AC_LIB_PROG_LD]) dnl we use $LD AC_REQUIRE([AC_CANONICAL_HOST]) dnl we use $host AC_REQUIRE([AC_CONFIG_AUX_DIR_DEFAULT]) dnl we use $ac_aux_dir AC_CACHE_CHECK([for shared library path variable], acl_cv_libpath, [ LD="$LD" \ ${CONFIG_SHELL-/bin/sh} "$ac_aux_dir/config.libpath" "$host" > conftest.sh . ./conftest.sh rm -f ./conftest.sh acl_cv_libpath=${acl_cv_shlibpath_var:-none} ]) shlibpath_var="$acl_cv_shlibpath_var" ]) smalltalk-3.2.5/build-aux/emacs-site-start.m40000644000175000017500000000303212123404352015741 00000000000000AC_DEFUN([GST_PATH_LISPSTARTDIR], [ AC_ARG_WITH([lispstartdir], [AC_HELP_STRING([--with-lispstartdir], [directory for Emacs startup files])]) AC_REQUIRE([AM_PATH_LISPDIR]) gst_save_prefix=$prefix if test "${prefix}" = NONE; then prefix=$ac_default_prefix fi if test $cross_compiling = yes; then AC_MSG_WARN([cross compiling, guessing ${lispdir}/site-start.d]) elif test -d `eval echo ${sysconfdir}`/emacs/site-start.d; then gst_cv_lispstartdir='${sysconfdir}/emacs/site-start.d' elif test -f `eval eval echo ${lispdir}`/site-start.el && test -d `eval eval echo ${lispdir}`/site-start.d; then gst_cv_lispstartdir='${lispdir}/site-start.d' elif test -d /etc/emacs/site-start.d; then AC_MSG_WARN([found /etc/emacs/site-start.d on your system]) AC_MSG_WARN([maybe you forgot --with-lispstartdir?]) gst_cv_lispstartdir='${sysconfdir}/emacs/site-start.d' else gst_lispstartdir_for_echo=`eval eval echo ${lispdir}/site-start.d` AC_MSG_WARN([Emacs start directory not detected, guessing]) AC_MSG_WARN([ ${gst_lispstartdir_for_echo}]) AC_MSG_WARN([you may need this in your .emacs or site-start.el file:]) AC_MSG_WARN([ (mapc 'load (directory-files]) AC_MSG_WARN([ "${gst_lispstartdir_for_echo}"]) AC_MSG_WARN([ t "\\.el\\'"))]) gst_cv_lispstartdir='${lispdir}/site-start.d' fi lispstartdir=$gst_cv_lispstartdir prefix=$gst_save_prefix AC_MSG_CHECKING([where to place Emacs startup files]) AC_MSG_RESULT([$lispstartdir]) AC_SUBST([lispstartdir]) ]) smalltalk-3.2.5/build-aux/pkg.m40000644000175000017500000001214512123404352013342 00000000000000# pkg.m4 - Macros to locate and utilise pkg-config. -*- Autoconf -*- # # Copyright © 2004 Scott James Remnant . # # This program is free software; you can redistribute it and/or modify # it under the terms of the GNU General Public License as published by # the Free Software Foundation; either version 2 of the License, or # (at your option) any later version. # # This program is distributed in the hope that it will be useful, but # WITHOUT ANY WARRANTY; without even the implied warranty of # MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU # General Public License for more details. # # You should have received a copy of the GNU General Public License # along with this program; if not, write to the Free Software # Foundation, Inc., 59 Temple Place - Suite 330, Boston, MA 02111-1307, USA. # # As a special exception to the GNU General Public License, if you # distribute this file as part of a program that contains a # configuration script generated by Autoconf, you may include it under # the same distribution terms that you use for the rest of that program. # PKG_PROG_PKG_CONFIG([MIN-VERSION]) # ---------------------------------- AC_DEFUN([PKG_PROG_PKG_CONFIG], [m4_pattern_forbid([^_?PKG_[A-Z_]+$]) m4_pattern_allow([^PKG_CONFIG(_PATH)?$]) AC_ARG_VAR([PKG_CONFIG], [path to pkg-config utility])dnl if test "x$ac_cv_env_PKG_CONFIG_set" != "xset"; then AC_PATH_TOOL([PKG_CONFIG], [pkg-config]) fi if test -n "$PKG_CONFIG"; then _pkg_min_version=m4_default([$1], [0.9.0]) AC_MSG_CHECKING([pkg-config is at least version $_pkg_min_version]) if $PKG_CONFIG --atleast-pkgconfig-version $_pkg_min_version; then AC_MSG_RESULT([yes]) else AC_MSG_RESULT([no]) PKG_CONFIG="" fi fi[]dnl ])# PKG_PROG_PKG_CONFIG # PKG_CHECK_EXISTS(MODULES, [ACTION-IF-FOUND], [ACTION-IF-NOT-FOUND]) # # Check to see whether a particular set of modules exists. Similar # to PKG_CHECK_MODULES(), but does not set variables or print errors. # # # Similar to PKG_CHECK_MODULES, make sure that the first instance of # this or PKG_CHECK_MODULES is called, or make sure to call # PKG_CHECK_EXISTS manually # -------------------------------------------------------------- AC_DEFUN([PKG_CHECK_EXISTS], [AC_REQUIRE([PKG_PROG_PKG_CONFIG])dnl if test -n "$PKG_CONFIG" && \ AC_RUN_LOG([$PKG_CONFIG --exists --print-errors "$1"]); then m4_ifval([$2], [$2], [:]) m4_ifvaln([$3], [else $3])dnl fi]) # _PKG_CONFIG([VARIABLE], [COMMAND], [MODULES]) # --------------------------------------------- m4_define([_PKG_CONFIG], [if test -n "$PKG_CONFIG"; then if test -n "$$1"; then pkg_cv_[]$1="$$1" else PKG_CHECK_EXISTS([$3], [pkg_cv_[]$1=`$PKG_CONFIG --[]$2 "$3" 2>/dev/null`], [pkg_failed=yes]) fi else pkg_failed=untried fi[]dnl ])# _PKG_CONFIG # _PKG_SHORT_ERRORS_SUPPORTED # ----------------------------- AC_DEFUN([_PKG_SHORT_ERRORS_SUPPORTED], [AC_REQUIRE([PKG_PROG_PKG_CONFIG]) if $PKG_CONFIG --atleast-pkgconfig-version 0.20; then _pkg_short_errors_supported=yes else _pkg_short_errors_supported=no fi[]dnl ])# _PKG_SHORT_ERRORS_SUPPORTED # PKG_CHECK_MODULES(VARIABLE-PREFIX, MODULES, [ACTION-IF-FOUND], # [ACTION-IF-NOT-FOUND]) # # # Note that if there is a possibility the first call to # PKG_CHECK_MODULES might not happen, you should be sure to include an # explicit call to PKG_PROG_PKG_CONFIG in your configure.ac # # # -------------------------------------------------------------- AC_DEFUN([PKG_CHECK_MODULES], [AC_REQUIRE([PKG_PROG_PKG_CONFIG])dnl AC_ARG_VAR([$1][_CFLAGS], [C compiler flags for $1, overriding pkg-config])dnl AC_ARG_VAR([$1][_LIBS], [linker flags for $1, overriding pkg-config])dnl pkg_failed=no AC_MSG_CHECKING([for $1]) _PKG_CONFIG([$1][_CFLAGS], [cflags], [$2]) _PKG_CONFIG([$1][_LIBS], [libs], [$2]) m4_define([_PKG_TEXT], [Alternatively, you may set the environment variables $1[]_CFLAGS and $1[]_LIBS to avoid the need to call pkg-config. See the pkg-config man page for more details.]) if test $pkg_failed = yes; then _PKG_SHORT_ERRORS_SUPPORTED if test $_pkg_short_errors_supported = yes; then $1[]_PKG_ERRORS=`$PKG_CONFIG --short-errors --errors-to-stdout --print-errors "$2"` else $1[]_PKG_ERRORS=`$PKG_CONFIG --errors-to-stdout --print-errors "$2"` fi # Put the nasty error message in config.log where it belongs echo "$$1[]_PKG_ERRORS" >&AS_MESSAGE_LOG_FD ifelse([$4], , [AC_MSG_ERROR(dnl [Package requirements ($2) were not met: $$1_PKG_ERRORS Consider adjusting the PKG_CONFIG_PATH environment variable if you installed software in a non-standard prefix. _PKG_TEXT ])], [AC_MSG_RESULT([no]) $4]) elif test $pkg_failed = untried; then ifelse([$4], , [AC_MSG_FAILURE(dnl [The pkg-config script could not be found or is too old. Make sure it is in your PATH or set the PKG_CONFIG environment variable to the full path to pkg-config. _PKG_TEXT To get pkg-config, see .])], [$4]) else $1[]_CFLAGS=$pkg_cv_[]$1[]_CFLAGS $1[]_LIBS=$pkg_cv_[]$1[]_LIBS AC_MSG_RESULT([yes]) ifelse([$3], , :, [$3]) fi[]dnl ])# PKG_CHECK_MODULES smalltalk-3.2.5/build-aux/gst-package.m40000644000175000017500000001077512123404352014756 00000000000000dnl I'd like this to be edited in -*- Autoconf -*- mode... dnl dnl GST_PACKAGE_ENABLE(NAME, DIR, [TESTS], [VARS-TO-TEST], [CONFIG-FILES], [LIBS]) dnl ------------------------------------------------------------------------ dnl Arrange for installation of package NAME in directory DIR (prefixed dnl by whatever was set up with GST_PACKAGE_PREFIX. dnl TESTS are run and VARS-TO-TEST are inspected after running them -- if dnl any of them is 'no' or 'not found' the package will not be built. dnl CONFIG-FILES (prefixed by DIR) are created from corresponding .in files; dnl it is important to specify package.xml here if it is automatically dnl generated. LIBS are libraries (possibly with .la extensions) that are dnl built and will be preloaded by the wrapper script in `tests/gst'. AC_DEFUN([GST_PACKAGE_ALLOW_DISABLING], [dnl m4_undefine([_GST_EXTRA_VARS])dnl m4_copy([_GST_ENABLE_VAR], [_GST_EXTRA_VARS])]) m4_define([_GST_EXTRA_VARS]), []) m4_define([_GST_ENABLE_VAR], [ enable_[]AS_TR_SH(m4_tolower([$1]))]) AC_DEFUN([GST_PACKAGE_PREFIX], [dnl m4_define([_GST_PKG_PREFIX], [$1/])]) m4_define([_GST_PKG_PREFIX], []) AC_DEFUN([GST_PACKAGE_DEPENDENCIES], [dnl m4_define([_GST_PKG_DEPENDENCIES], [$1])]) m4_define([_GST_PKG_DEPENDENCIES], []) m4_define([_GST_RULES_PREPARE], [m4_expand_once([ PACKAGE_RULES=pkgrules.tmp rm -f pkgrules.tmp]) AC_SUBST_FILE([PACKAGE_RULES])]) m4_define([_GST_PKG_ENABLE], [ cat >> pkgrules.tmp << \EOF install-data-hook:: $1.star $(GST_[]PACKAGE) --srcdir $(srcdir) --target-directory=$(gstdatadir) --destdir="$(DESTDIR)" $1.star uninstall-local:: $(GST_[]PACKAGE) --srcdir $(srcdir) --target-directory=$(gstdatadir) --destdir="$(DESTDIR)" --uninstall $(DESTDIR)$(gstdatadir)/$1.star -include $(srcdir)/_GST_PKG_MK all-local: $1.star EOF m4_if([$3], [], [], [PACKAGE_DLOPEN_FLAGS="$PACKAGE_DLOPEN_FLAGS[]m4_foreach_w(GST_Lib, [$3], [ -dlopen \"\${abs_top_builddir}/_GST_PKG_DIR/GST_Lib\"])"]) m4_foreach_w(GST_File, [$2], [m4_if(GST_File, Makefile, [BUILT_PACKAGES="$BUILT_PACKAGES _GST_PKG_DIR"])])]) m4_define([_GST_PKG_IF_FILE], [dnl m4_define([_GST_COND], [$4])dnl m4_foreach_w(GST_File, [$1], [m4_if(GST_File, $2, [m4_define([_GST_COND], [$3])])])dnl _GST_COND]) AC_DEFUN([GST_PACKAGE_ENABLE], [ $3 AC_MSG_CHECKING([whether to install $1]) _GST_RULES_PREPARE m4_define([_GST_PKG_VARS], [$4]m4_quote(_GST_EXTRA_VARS([$1])))dnl m4_define([_GST_PKG_DIR], [_GST_PKG_PREFIX[]$2])dnl m4_define([_GST_PKG_XML], [_GST_PKG_DIR/package.xml])dnl m4_define([_GST_PKG_DISTDIR], [$(distdir)/_GST_PKG_DIR])dnl m4_define([_GST_PKG_STAMP], [_GST_PKG_DIR/stamp-classes])dnl m4_define([_GST_PKG_MK], [_GST_PKG_DIR/Makefile.frag])dnl m4_define([_GST_PKG_XML_IN], [_GST_PKG_IF_FILE([$5], [package.xml], [$(srcdir)/_GST_PKG_DIR/package.xml.in], [_GST_PKG_XML])])dnl cat >> pkgrules.tmp << \EOF all-local: $(srcdir)/_GST_PKG_STAMP $1.star: _GST_PKG_XML $(srcdir)/_GST_PKG_STAMP _GST_PKG_DEPENDENCIES _GST_PKG_IF_FILE([$5], [Makefile], [cd _GST_PKG_DIR && $(MAKE) ])$(GST_[]PACKAGE) --srcdir=$(srcdir) --target-directory=. $< clean-local:: -rm -f $1.star dist-hook:: _GST_PKG_XML $(GST_[]PACKAGE) --srcdir=$(srcdir) --target-directory=_GST_PKG_DISTDIR --dist $< dist-hook:: $(srcdir)/_GST_PKG_STAMP $(srcdir)/_GST_PKG_MK cp -p $(srcdir)/_GST_PKG_STAMP _GST_PKG_DISTDIR/stamp-classes cp -p $(srcdir)/_GST_PKG_MK _GST_PKG_DISTDIR/Makefile.frag $(srcdir)/_GST_PKG_MK: _GST_PKG_XML_IN (echo '$1_FILES = \'; \ $(GST_[]PACKAGE) --srcdir=$(srcdir) --vpath --list-files $1 $< | \ tr -d \\r | tr \\n " "; \ echo; \ echo '$$($1_FILES):'; \ echo '$$(srcdir)/_GST_PKG_STAMP: $$($1_FILES)'; \ echo ' touch $$(srcdir)/_GST_PKG_STAMP') > $(srcdir)/_GST_PKG_MK EOF m4_ifset([_GST_PKG_VARS], [(for i in _GST_PKG_VARS; do case $i in #(( enable_*) eval ac_var='${'$i'-yes}' ;; *) eval ac_var='${'$i'-bad}' ;; esac case $ac_var in #(( no* ) exit 1 ;; bad ) AC_MSG_WARN([variable $i not set, proceeding as if \"no\"]) exit 1 ;; esac done) if test $? = 0; then _GST_PKG_ENABLE([$1], [$5], [$6]) AC_MSG_RESULT([yes]) else AC_MSG_RESULT([no]) fi ], [_GST_PKG_ENABLE([$1], [$5], [$6]) AC_MSG_RESULT([yes])]) m4_if([$5], [], [], [_GST_PKG_IF_FILE([$5], [Makefile], [ALL_PACKAGES="$ALL_PACKAGES _GST_PKG_DIR"]) AC_CONFIG_FILES(m4_foreach_w(GST_File, [$5], [_GST_PKG_DIR/GST_File ])) ]) AC_SUBST([ALL_PACKAGES]) AC_SUBST([BUILT_PACKAGES]) AC_SUBST([PACKAGE_DLOPEN_FLAGS]) ])dnl smalltalk-3.2.5/build-aux/sigaltstack.m40000644000175000017500000000747412123404352015103 00000000000000# sigaltstack.m4 serial 6 (libsigsegv-2.4) dnl Copyright (C) 2002-2006 Bruno Haible dnl This file is free software, distributed under the terms of the GNU dnl General Public License. As a special exception to the GNU General dnl Public License, this file may be distributed as part of a program dnl that contains a configuration script generated by Autoconf, under dnl the same distribution terms as the rest of that program. AC_DEFUN([SV_SIGALTSTACK], [ AC_REQUIRE([AC_PROG_CC]) AC_REQUIRE([AC_CANONICAL_HOST]) AC_CHECK_FUNCS(sigaltstack) if test "$ac_cv_func_sigaltstack" = yes; then AC_CHECK_TYPE(stack_t, , [AC_DEFINE(stack_t, [struct sigaltstack], [Define to 'struct sigaltstack' if that's the type of the argument to sigaltstack]) ], [ #include #if HAVE_SYS_SIGNAL_H # include #endif ]) fi AC_CACHE_CHECK([for working sigaltstack], sv_cv_sigaltstack, [ if test "$ac_cv_func_sigaltstack" = yes; then case "$host_os" in macos* | darwin[[6-9]]* | darwin[[1-9]][[0-9]]*) # On MacOS X 10.2 or newer, just assume that if it compiles, it will # work. If we were to perform the real test, 1 Crash Report dialog # window would pop up. AC_LINK_IFELSE([ AC_LANG_PROGRAM([[#include ]], [[int x = SA_ONSTACK; stack_t ss; sigaltstack ((stack_t*)0, &ss);]])], [sv_cv_sigaltstack="guessing yes"], [sv_cv_sigaltstack=no]) ;; *) AC_RUN_IFELSE([ AC_LANG_SOURCE([[ #include #include #if HAVE_SYS_SIGNAL_H # include #endif #if HAVE_SETRLIMIT # include # include # include #endif void stackoverflow_handler (int sig) { /* If we get here, the stack overflow was caught. */ exit (0); } volatile int * recurse_1 (volatile int n, volatile int *p) { if (n >= 0) *recurse_1 (n + 1, p) += n; return p; } volatile int recurse (volatile int n) { int sum = 0; return *recurse_1 (n, &sum); } char mystack[16384]; int main () { stack_t altstack; struct sigaction action; #if defined HAVE_SETRLIMIT && defined RLIMIT_STACK /* Before starting the endless recursion, try to be friendly to the user's machine. On some Linux 2.2.x systems, there is no stack limit for user processes at all. We don't want to kill such systems. */ struct rlimit rl; rl.rlim_cur = rl.rlim_max = 0x100000; /* 1 MB */ setrlimit (RLIMIT_STACK, &rl); #endif /* Install the alternate stack. */ altstack.ss_sp = mystack; altstack.ss_size = sizeof (mystack); altstack.ss_flags = 0; /* no SS_DISABLE */ if (sigaltstack (&altstack, NULL) < 0) exit (1); /* Install the SIGSEGV handler. */ sigemptyset (&action.sa_mask); action.sa_handler = &stackoverflow_handler; action.sa_flags = SA_ONSTACK; sigaction (SIGSEGV, &action, (struct sigaction *) NULL); sigaction (SIGBUS, &action, (struct sigaction *) NULL); /* Provoke a stack overflow. */ recurse (0); exit (2); }]])], [sv_cv_sigaltstack=yes], [sv_cv_sigaltstack=no], [ dnl FIXME: Put in some more known values here. case "$host_os" in *) AC_LINK_IFELSE([ AC_LANG_PROGRAM([[#include ]], [[int x = SA_ONSTACK; stack_t ss; sigaltstack ((stack_t*)0, &ss);]])], [sv_cv_sigaltstack="guessing yes"], [sv_cv_sigaltstack=no]) ;; esac ]) ;; esac else sv_cv_sigaltstack=no fi ]) if test "$sv_cv_sigaltstack" != no; then AC_DEFINE(HAVE_WORKING_SIGALTSTACK, 1, [Define if you have the sigaltstack() function and it works.]) fi ]) smalltalk-3.2.5/build-aux/mmap-anon.m40000644000175000017500000000775212123404352014454 00000000000000# mmap-anon.m4 serial 2 (libsigsegv-2.2) dnl Copyright (C) 2002-2003 Bruno Haible dnl This file is free software, distributed under the terms of the GNU dnl General Public License. As a special exception to the GNU General dnl Public License, this file may be distributed as part of a program dnl that contains a configuration script generated by Autoconf, under dnl the same distribution terms as the rest of that program. # How to allocate fresh memory using mmap. AC_DEFUN([SV_MMAP_ANON], [ AC_REQUIRE([AC_PROG_CC]) AC_REQUIRE([AC_CANONICAL_HOST]) dnl 1) MAP_ANON AC_CACHE_CHECK([for mmap with MAP_ANON], sv_cv_func_mmap_anon, [ AC_RUN_IFELSE([ AC_LANG_SOURCE([[ #include #include int main () { void *p = mmap (0, 0x10000, PROT_READ | PROT_WRITE, MAP_ANON | MAP_PRIVATE, -1, 0); return (p == (void *)(-1)); }]])], [sv_cv_func_mmap_anon=yes], [sv_cv_func_mmap_anon=no], [ dnl FIXME: Put in some more known values here. case "$host_os" in freebsd* | linux* | osf*) sv_cv_func_mmap_anon=yes ;; *) AC_LINK_IFELSE([ AC_LANG_PROGRAM([[ #include #include ]], [[mmap (0, 0x10000, PROT_READ | PROT_WRITE, MAP_ANON | MAP_PRIVATE, -1, 0);]])], [sv_cv_func_mmap_anon="guessing yes"], [sv_cv_func_mmap_anon=no]) ;; esac ]) ]) if test "$sv_cv_func_mmap_anon" != no; then AC_DEFINE(HAVE_MMAP_ANON, 1, [Define if defines MAP_ANON and mmaping with MAP_ANON works.]) fi dnl 2) MAP_ANONYMOUS AC_CACHE_CHECK([for mmap with MAP_ANONYMOUS], sv_cv_func_mmap_anonymous, [ AC_RUN_IFELSE([ AC_LANG_SOURCE([[ #include #include int main () { void *p = mmap (0, 0x10000, PROT_READ | PROT_WRITE, MAP_ANONYMOUS | MAP_PRIVATE, -1, 0); return (p == (void *)(-1)); }]])], [sv_cv_func_mmap_anonymous=yes], [sv_cv_func_mmap_anonymous=no], [ dnl FIXME: Put in some more known values here. case "$host_os" in hpux* | linux* | osf*) sv_cv_func_mmap_anonymous=yes ;; *) AC_LINK_IFELSE([ AC_LANG_PROGRAM([[ #include #include ]], [[mmap (0, 0x10000, PROT_READ | PROT_WRITE, MAP_ANONYMOUS | MAP_PRIVATE, -1, 0);]])], [sv_cv_func_mmap_anonymous="guessing yes"], [sv_cv_func_mmap_anonymous=no]) ;; esac ]) ]) if test "$sv_cv_func_mmap_anonymous" != no; then AC_DEFINE(HAVE_MMAP_ANONYMOUS, 1, [Define if defines MAP_ANONYMOUS and mmaping with MAP_ANONYMOUS works.]) fi dnl 3) MAP_FILE of /dev/zero AC_CACHE_CHECK([for mmap of /dev/zero], sv_cv_func_mmap_devzero, [ AC_RUN_IFELSE([ AC_LANG_SOURCE([[ #include #include #include #ifndef MAP_FILE #define MAP_FILE 0 #endif int main () { int fd; void *p; fd = open ("/dev/zero", O_RDONLY, 0666); if (fd < 0) return 1; p = mmap (0, 0x10000, PROT_READ | PROT_WRITE, MAP_FILE | MAP_PRIVATE, fd, 0); return (p == (void *)(-1)); }]])], [sv_cv_func_mmap_devzero=yes], [sv_cv_func_mmap_devzero=no], [ dnl FIXME: Put in some more known values here. case "$host_os" in freebsd* | irix* | linux* | osf* | solaris* | sunos4*) sv_cv_func_mmap_devzero=yes ;; *) AC_LINK_IFELSE([ AC_LANG_PROGRAM([[ #include #include #ifndef MAP_FILE #define MAP_FILE 0 #endif ]], [[mmap (0, 0x10000, PROT_READ | PROT_WRITE, MAP_FILE | MAP_PRIVATE, 7, 0);]])], [sv_cv_func_mmap_devzero="guessing yes"], [sv_cv_func_mmap_devzero=no]) ;; esac ]) ]) if test "$sv_cv_func_mmap_devzero" != no; then AC_DEFINE(HAVE_MMAP_DEVZERO, 1, [Define if mmaping of the special device /dev/zero works.]) fi ]) smalltalk-3.2.5/build-aux/iconv.m40000644000175000017500000000675512123404352013711 00000000000000# iconv.m4 serial AM4 (gettext-0.11.3) dnl Copyright (C) 2000-2002 Free Software Foundation, Inc. dnl This file is free software, distributed under the terms of the GNU dnl General Public License. As a special exception to the GNU General dnl Public License, this file may be distributed as part of a program dnl that contains a configuration script generated by Autoconf, under dnl the same distribution terms as the rest of that program. dnl From Bruno Haible. AC_DEFUN([AM_ICONV_LINKFLAGS_BODY], [ dnl Prerequisites of AC_LIB_LINKFLAGS_BODY. AC_REQUIRE([AC_LIB_PREPARE_PREFIX]) AC_REQUIRE([AC_LIB_RPATH]) dnl Search for libiconv and define LIBICONV, LTLIBICONV and INCICONV dnl accordingly. AC_LIB_LINKFLAGS_BODY([iconv]) ]) AC_DEFUN([AM_ICONV_LINK], [ dnl Some systems have iconv in libc, some have it in libiconv (OSF/1 and dnl those with the standalone portable GNU libiconv installed). dnl Search for libiconv and define LIBICONV, LTLIBICONV and INCICONV dnl accordingly. AC_REQUIRE([AM_ICONV_LINKFLAGS_BODY]) dnl Add $INCICONV to CPPFLAGS before performing the following checks, dnl because if the user has installed libiconv and not disabled its use dnl via --without-libiconv-prefix, he wants to use it. The first dnl AC_LINK_IFELSE will then fail, the second AC_LINK_IFELSE will succeed. am_save_CPPFLAGS="$CPPFLAGS" AC_LIB_APPENDTOVAR([CPPFLAGS], [$INCICONV]) AC_CACHE_CHECK(for iconv, am_cv_func_iconv, [ am_cv_func_iconv="no, consider installing GNU libiconv" am_cv_lib_iconv=no AC_LINK_IFELSE([AC_LANG_PROGRAM([[#include #include ]], [[iconv_t cd = iconv_open("",""); iconv(cd,NULL,NULL,NULL,NULL); iconv_close(cd);]])],[am_cv_func_iconv=yes],[]) if test "$am_cv_func_iconv" != yes; then am_save_LIBS="$LIBS" LIBS="$LIBS $LIBICONV" AC_LINK_IFELSE([AC_LANG_PROGRAM([[#include #include ]], [[iconv_t cd = iconv_open("",""); iconv(cd,NULL,NULL,NULL,NULL); iconv_close(cd);]])],[am_cv_lib_iconv=yes am_cv_func_iconv=yes],[]) LIBS="$am_save_LIBS" fi ]) if test "$am_cv_func_iconv" = yes; then AC_DEFINE(HAVE_ICONV, 1, [Define if you have the iconv() function.]) fi if test "$am_cv_lib_iconv" = yes; then AC_MSG_CHECKING([how to link with libiconv]) AC_MSG_RESULT([$LIBICONV]) else dnl If $LIBICONV didn't lead to a usable library, we don't need $INCICONV dnl either. CPPFLAGS="$am_save_CPPFLAGS" LIBICONV= LTLIBICONV= fi AC_SUBST(LIBICONV) AC_SUBST(LTLIBICONV) ]) AC_DEFUN([AM_ICONV], [ AM_ICONV_LINK if test "$am_cv_func_iconv" = yes; then AC_MSG_CHECKING([for iconv declaration]) AC_CACHE_VAL(am_cv_proto_iconv, [ AC_COMPILE_IFELSE([AC_LANG_PROGRAM([[ #include #include extern #ifdef __cplusplus "C" #endif #if defined(__STDC__) || defined(__cplusplus) size_t iconv (iconv_t cd, char * *inbuf, size_t *inbytesleft, char * *outbuf, size_t *outbytesleft); #else size_t iconv(); #endif ]], [[]])],[am_cv_proto_iconv_arg1=""],[am_cv_proto_iconv_arg1="const"]) am_cv_proto_iconv="extern size_t iconv (iconv_t cd, $am_cv_proto_iconv_arg1 char * *inbuf, size_t *inbytesleft, char * *outbuf, size_t *outbytesleft);"]) am_cv_proto_iconv=`echo "[$]am_cv_proto_iconv" | tr -s ' ' | sed -e 's/( /(/'` AC_MSG_RESULT([$]{ac_t:- }[$]am_cv_proto_iconv) AC_DEFINE_UNQUOTED(ICONV_CONST, $am_cv_proto_iconv_arg1, [Define as const if the declaration of iconv() needs const.]) fi ]) smalltalk-3.2.5/build-aux/ltversion.m40000644000175000017500000000126212130455417014612 00000000000000# ltversion.m4 -- version numbers -*- Autoconf -*- # # Copyright (C) 2004 Free Software Foundation, Inc. # Written by Scott James Remnant, 2004 # # This file is free software; the Free Software Foundation gives # unlimited permission to copy and/or distribute it, with or without # modifications, as long as this notice is preserved. # @configure_input@ # serial 3337 ltversion.m4 # This file is part of GNU Libtool m4_define([LT_PACKAGE_VERSION], [2.4.2]) m4_define([LT_PACKAGE_REVISION], [1.3337]) AC_DEFUN([LTVERSION_VERSION], [macro_version='2.4.2' macro_revision='1.3337' _LT_DECL(, macro_version, 0, [Which release of libtool.m4 was used?]) _LT_DECL(, macro_revision, 0) ]) smalltalk-3.2.5/build-aux/glut.m40000644000175000017500000000312012123404352013525 00000000000000dnl I'd like this to be edited in -*- Autoconf -*- mode... dnl AC_DEFUN([GST_HAVE_GLUT], [ AC_REQUIRE([AC_PATH_XTRA]) AC_CACHE_VAL(gst_cv_glut_header_file, [ gst_cv_glut_header_file='not found' AC_CHECK_HEADERS([GLUT/freeglut.h GL/freeglut.h GLUT/glut.h GL/glut.h], [ if test $ac_cv_header_GLUT_freeglut_h = yes; then gst_cv_glut_header_file='GLUT/freeglut.h' elif test $ac_cv_header_GL_freeglut_h = yes; then gst_cv_glut_header_file='GL/freeglut.h' elif test $ac_cv_header_GLUT_glut_h = yes; then gst_cv_glut_header_file='GLUT/glut.h' else gst_cv_glut_header_file='GL/glut.h' fi break;])]) AC_MSG_CHECKING([for GLUT header files]) AC_MSG_RESULT([$gst_cv_glut_header_file]) AC_CACHE_CHECK([how to link with GLUT], gst_cv_glut_libs, [ if test "$gst_cv_opengl_libs" = 'not found' || \ test $gst_cv_glut_header_file = 'not found'; then gst_cv_glut_libs='not found' else save_LIBS=$LIBS case $host in *-*-darwin*) gst_cv_glut_libs='-Wl,-framework,GLUT' ;; *) gst_cv_glut_libs="-lglut $X_LIBS $X_PRE_LIBS -lX11" ;; esac LIBS="$LIBS -lglut $gst_cv_opengl_libs" AC_LINK_IFELSE([AC_LANG_PROGRAM([ #include <$gst_cv_glut_header_file>], [glutInit])], [], [gst_cv_glut_libs='not found']) LIBS=$save_LIBS fi ]) if test "$gst_cv_glut_libs" != "not found"; then LIBGLUT="$gst_cv_glut_libs" AC_DEFINE(HAVE_GLUT, 1, [Define if your system has GLUT installed.]) AC_DEFINE_UNQUOTED(GL_GLUT_H, [<$gst_cv_glut_header_file>], [Define to the #include directive for GLUT.]) fi AC_SUBST(LIBGLUT) ])dnl smalltalk-3.2.5/build-aux/texi2dvi0000755000175000017500000005324412123404352014010 00000000000000#! /bin/sh # texi2dvi --- produce DVI (or PDF) files from Texinfo (or LaTeX) sources. # $Id: texi2dvi,v 0.51 2002/04/01 14:20:59 karl Exp $ # # Copyright (C) 1992, 93, 94, 95, 96, 97, 98, 99, 2001, 02 # Free Software Foundation, Inc. # # This program is free software; you can redistribute it and/or modify # it under the terms of the GNU General Public License as published by # the Free Software Foundation; either version 2, or (at your option) # any later version. # # This program is distributed in the hope that it will be useful, # but WITHOUT ANY WARRANTY; without even the implied warranty of # MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the # GNU General Public License for more details. # # You should have received a copy of the GNU General Public License # along with this program; if not, you can either send email to this # program's maintainer or write to: The Free Software Foundation, # Inc.; 51 Franklin Street, Fifth Floor; Boston, MA 02110-1301, USA. # # Original author: Noah Friedman . # # Please send bug reports, etc. to bug-texinfo@gnu.org. # If possible, please send a copy of the output of the script called with # the `--debug' option when making a bug report. if ! command -v tex >/dev/null 2>&1; then cat <<%EOM% You don't have a working TeX binary installed, but the texi2dvi script can't proceed without it. If you want to use this script, you have to install some kind of TeX, for example teTeX Debian packages. You can do that with this command: apt-get install tetex-bin %EOM% exit 1 fi # This string is expanded by rcs automatically when this file is checked out. rcs_revision='$Revision: 0.51 $' rcs_version=`set - $rcs_revision; echo $2` program=`echo $0 | sed -e 's!.*/!!'` version="texi2dvi (GNU Texinfo 4.2) $rcs_version Copyright (C) 2002 Free Software Foundation, Inc. There is NO warranty. You may redistribute this software under the terms of the GNU General Public License. For more information about these matters, see the files named COPYING." usage="Usage: $program [OPTION]... FILE... Run each Texinfo or LaTeX FILE through TeX in turn until all cross-references are resolved, building all indices. The directory containing each FILE is searched for included files. The suffix of FILE is used to determine its language (LaTeX or Texinfo). Makeinfo is used to perform Texinfo macro expansion before running TeX when needed. Operation modes: -b, --batch no interaction -c, --clean remove all auxiliary files -D, --debug turn on shell debugging (set -x) -h, --help display this help and exit successfully -o, --output=OFILE leave output in OFILE (implies --clean); Only one input FILE may be specified in this case -q, --quiet no output unless errors (implies --batch) -s, --silent same as --quiet -v, --version display version information and exit successfully -V, --verbose report on what is done TeX tuning: -@ use @input instead of \input; for preloaded Texinfo -e, --expand force macro expansion using makeinfo -I DIR search DIR for Texinfo files -l, --language=LANG specify the LANG of FILE (LaTeX or Texinfo) -p, --pdf use pdftex or pdflatex for processing -t, --texinfo=CMD insert CMD after @setfilename in copy of input file multiple values accumulate The values of the BIBTEX, LATEX (or PDFLATEX), MAKEINDEX, MAKEINFO, TEX (or PDFTEX), and TEXINDEX environment variables are used to run those commands, if they are set. Email bug reports to , general questions and discussion to . Texinfo home page: http://www.gnu.org/software/texinfo/" # Initialize variables for option overriding and otherwise. # Don't use `unset' since old bourne shells don't have this command. # Instead, assign them an empty value. batch=false # eval for batch mode clean= debug= escape='\' expand= # t for expansion via makeinfo miincludes= # makeinfo include path oformat=dvi oname= # --output quiet= # by default let the tools' message be displayed set_language= textra= tmpdir=${TMPDIR:-/tmp}/t2d$$ # avoid collisions on 8.3 filesystems. txincludes= # TEXINPUTS extensions txiprereq=19990129 # minimum texinfo.tex version to have macro expansion verbose=false # echo for verbose mode orig_pwd=`pwd` # Systems which define $COMSPEC or $ComSpec use semicolons to separate # directories in TEXINPUTS. if test -n "$COMSPEC$ComSpec"; then path_sep=";" else path_sep=":" fi # Save this so we can construct a new TEXINPUTS path for each file. TEXINPUTS_orig="$TEXINPUTS" # Unfortunately makeindex does not read TEXINPUTS. INDEXSTYLE_orig="$INDEXSTYLE" export TEXINPUTS INDEXSTYLE # Push a token among the arguments that will be used to notice when we # ended options/arguments parsing. # Use "set dummy ...; shift" rather than 'set - ..." because on # Solaris set - turns off set -x (but keeps set -e). # Use ${1+"$@"} rather than "$@" because Digital Unix and Ultrix 4.3 # still expand "$@" to a single argument (the empty string) rather # than nothing at all. arg_sep="$$--$$" set dummy ${1+"$@"} "$arg_sep"; shift # # Parse command line arguments. while test x"$1" != x"$arg_sep"; do # Handle --option=value by splitting apart and putting back on argv. case "$1" in --*=*) opt=`echo "$1" | sed -e 's/=.*//'` val=`echo "$1" | sed -e 's/[^=]*=//'` shift set dummy "$opt" "$val" ${1+"$@"}; shift ;; esac # This recognizes --quark as --quiet. So what. case "$1" in -@ ) escape=@;; # Silently and without documentation accept -b and --b[atch] as synonyms. -b | --b*) batch=eval;; -q | -s | --q* | --s*) quiet=t; batch=eval;; -c | --c*) clean=t;; -D | --d*) debug=t;; -e | --e*) expand=t;; -h | --h*) echo "$usage"; exit 0;; -I | --I*) shift miincludes="$miincludes -I $1" txincludes="$txincludes$path_sep$1" ;; -l | --l*) shift; set_language=$1;; -o | --o*) shift clean=t case "$1" in /* | ?:/*) oname=$1;; *) oname="$orig_pwd/$1";; esac;; -p | --p*) oformat=pdf;; -t | --t*) shift; textra="$textra\\ $1";; -v | --vers*) echo "$version"; exit 0;; -V | --verb*) verbose=echo;; --) # What remains are not options. shift while test x"$1" != x"$arg_sep"; do set dummy ${1+"$@"} "$1"; shift shift done break;; -*) echo "$0: Unknown or ambiguous option \`$1'." >&2 echo "$0: Try \`--help' for more information." >&2 exit 1;; *) set dummy ${1+"$@"} "$1"; shift;; esac shift done # Pop the token shift # Interpret remaining command line args as filenames. case $# in 0) echo "$0: Missing file arguments." >&2 echo "$0: Try \`--help' for more information." >&2 exit 2 ;; 1) ;; *) if test -n "$oname"; then echo "$0: Can't use option \`--output' with more than one argument." >&2 exit 2 fi ;; esac # Prepare the temporary directory. Remove it at exit, unless debugging. if test -z "$debug"; then trap "cd / && rm -rf $tmpdir" 0 1 2 15 fi # Create the temporary directory with strict rights (umask 077 && mkdir $tmpdir) || exit 1 # Prepare the tools we might need. This may be extra work in some # cases, but improves the readibility of the script. utildir=$tmpdir/utils mkdir $utildir || exit 1 # A sed script that preprocesses Texinfo sources in order to keep the # iftex sections only. We want to remove non TeX sections, and # comment (with `@c texi2dvi') TeX sections so that makeinfo does not # try to parse them. Nevertheless, while commenting TeX sections, # don't comment @macro/@end macro so that makeinfo does propagate # them. Unfortunately makeinfo --iftex --no-ifhtml --no-ifinfo # doesn't work well enough (yet) to use that, so work around with sed. comment_iftex_sed=$utildir/comment.sed cat <$comment_iftex_sed /^@tex/,/^@end tex/{ s/^/@c texi2dvi/ } /^@iftex/,/^@end iftex/{ s/^/@c texi2dvi/ /^@c texi2dvi@macro/,/^@c texi2dvi@end macro/{ s/^@c texi2dvi// } } /^@html/,/^@end html/{ s/^/@c (texi2dvi)/ } /^@ifhtml/,/^@end ifhtml/{ s/^/@c (texi2dvi)/ } /^@ifnottex/,/^@end ifnottex/{ s/^/@c (texi2dvi)/ } /^@ifinfo/,/^@end ifinfo/{ /^@node/p /^@menu/,/^@end menu/p t s/^/@c (texi2dvi)/ } s/^@ifnotinfo/@c texi2dvi@ifnotinfo/ s/^@end ifnotinfo/@c texi2dvi@end ifnotinfo/ EOF # Uncommenting is simple: Remove any leading `@c texi2dvi'. uncomment_iftex_sed=$utildir/uncomment.sed cat <$uncomment_iftex_sed s/^@c texi2dvi// EOF # A shell script that computes the list of xref files. # Takes the filename (without extension) of which we look for xref # files as argument. The index files must be reported last. get_xref_files=$utildir/get_xref.sh cat <<\EOF >$get_xref_files #! /bin/sh # Get list of xref files (indexes, tables and lists). # Find all files having root filename with a two-letter extension, # saves the ones that are really Texinfo-related files. .?o? catches # LaTeX tables and lists. for this_file in "$1".?o? "$1".aux "$1".?? "$1".idx; do # If file is empty, skip it. test -s "$this_file" || continue # If the file is not suitable to be an index or xref file, don't # process it. The file can't be if its first character is not a # backslash or single quote. first_character=`sed -n '1s/^\(.\).*$/\1/p;q' $this_file` if test "x$first_character" = "x\\" \ || test "x$first_character" = "x'"; then xref_files="$xref_files ./$this_file" fi done echo "$xref_files" EOF chmod 500 $get_xref_files # File descriptor usage: # 0 standard input # 1 standard output (--verbose messages) # 2 standard error # 3 some systems may open it to /dev/tty # 4 used on the Kubota Titan # 5 tools output (turned off by --quiet) # Tools' output. If quiet, discard, else redirect to the message flow. if test "$quiet" = t; then exec 5>/dev/null else exec 5>&1 fi # Enable tracing test "$debug" = t && set -x # # TeXify files. for command_line_filename in ${1+"$@"}; do $verbose "Processing $command_line_filename ..." # If the COMMAND_LINE_FILENAME is not absolute (e.g., --debug.tex), # prepend `./' in order to avoid that the tools take it as an option. echo "$command_line_filename" | egrep '^(/|[[:alpha:]]:/)' >/dev/null \ || command_line_filename="./$command_line_filename" # See if the file exists. If it doesn't we're in trouble since, even # though the user may be able to reenter a valid filename at the tex # prompt (assuming they're attending the terminal), this script won't # be able to find the right xref files and so forth. if test ! -r "$command_line_filename"; then echo "$0: Could not read $command_line_filename, skipping." >&2 continue fi # Get the name of the current directory. We want the full path # because in clean mode we are in tmp, in which case a relative # path has no meaning. filename_dir=`echo $command_line_filename | sed 's!/[^/]*$!!;s!^$!.!'` filename_dir=`cd "$filename_dir" >/dev/null && pwd` # Strip directory part but leave extension. filename_ext=`basename "$command_line_filename"` # Strip extension. filename_noext=`echo "$filename_ext" | sed 's/\.[^.]*$//'` ext=`echo "$filename_ext" | sed 's/^.*\.//'` # _src. Use same basename since we want to generate aux files with # the same basename as the manual. If --expand, then output the # macro-expanded file to here, else copy the original file. tmpdir_src=$tmpdir/src filename_src=$tmpdir_src/$filename_noext.$ext # _xtr. The file with the user's extra commands. tmpdir_xtr=$tmpdir/xtr filename_xtr=$tmpdir_xtr/$filename_noext.$ext # _bak. Copies of the previous xref files (another round is run if # they differ from the new one). tmpdir_bak=$tmpdir/bak # Make all those directories and give up if we can't succeed. mkdir $tmpdir_src $tmpdir_xtr $tmpdir_bak || exit 1 # Source file might include additional sources. Put `.' and # directory where source file(s) reside in TEXINPUTS before anything # else. `.' goes first to ensure that any old .aux, .cps, # etc. files in ${directory} don't get used in preference to fresher # files in `.'. Include orig_pwd in case we are in clean mode, where # we've cd'd to a temp directory. common=".$path_sep$orig_pwd$path_sep$filename_dir$path_sep$txincludes$path_sep" TEXINPUTS="$common$TEXINPUTS_orig" INDEXSTYLE="$common$INDEXSTYLE_orig" # If the user explicitly specified the language, use that. # Otherwise, if the first line is \input texinfo, assume it's texinfo. # Otherwise, guess from the file extension. if test -n "$set_language"; then language=$set_language elif sed 1q "$command_line_filename" | fgrep 'input texinfo' >/dev/null; then language=texinfo else language= fi # Get the type of the file (latex or texinfo) from the given language # we just guessed, or from the file extension if not set yet. case ${language:-$filename_ext} in [lL]a[tT]e[xX] | *.ltx | *.tex) # Assume a LaTeX file. LaTeX needs bibtex and uses latex for # compilation. No makeinfo. bibtex=${BIBTEX:-bibtex} makeinfo= # no point in running makeinfo on latex source. texindex=${MAKEINDEX:-makeindex} if test $oformat = dvi; then tex=${LATEX:-latex} else tex=${PDFLATEX:-pdflatex} fi ;; *) # Assume a Texinfo file. Texinfo files need makeinfo, texindex and tex. bibtex= texindex=${TEXINDEX:-texindex} if test $oformat = dvi; then tex=${TEX:-tex} else tex=${PDFTEX:-pdftex} fi # Unless required by the user, makeinfo expansion is wanted only # if texinfo.tex is too old. if test "$expand" = t; then makeinfo=${MAKEINFO:-makeinfo} else # Check if texinfo.tex performs macro expansion by looking for # its version. The version is a date of the form YEAR-MO-DA. # We don't need to use [0-9] to match the digits since anyway # the comparison with $txiprereq, a number, will fail with non # digits. txiversion_tex=txiversion.tex echo '\input texinfo.tex @bye' >$tmpdir/$txiversion_tex # Run in the tmpdir to avoid leaving files. eval `cd $tmpdir >/dev/null && $tex $txiversion_tex 2>/dev/null | sed -n 's/^.*\[\(.*\)version \(....\)-\(..\)-\(..\).*$/txiformat=\1 txiversion="\2\3\4"/p'` $verbose "texinfo.tex preloaded as \`$txiformat', version is \`$txiversion' ..." if test "$txiprereq" -le "$txiversion" >/dev/null 2>&1; then makeinfo= else makeinfo=${MAKEINFO:-makeinfo} fi # As long as we had to run TeX, offer the user this convenience if test "$txiformat" = Texinfo; then escape=@ fi fi ;; esac # Expand macro commands in the original source file using Makeinfo. # Always use `end' footnote style, since the `separate' style # generates different output (arguably this is a bug in -E). # Discard main info output, the user asked to run TeX, not makeinfo. if test -n "$makeinfo"; then $verbose "Macro-expanding $command_line_filename to $filename_src ..." sed -f $comment_iftex_sed "$command_line_filename" \ | $makeinfo --footnote-style=end -I "$filename_dir" $miincludes \ -o /dev/null --macro-expand=- \ | sed -f $uncomment_iftex_sed >"$filename_src" filename_input=$filename_src fi # If makeinfo failed (or was not even run), use the original file as input. if test $? -ne 0 \ || test ! -r "$filename_src"; then $verbose "Reverting to $command_line_filename ..." filename_input=$filename_dir/$filename_ext fi # Used most commonly for @finalout, @smallbook, etc. if test -n "$textra"; then $verbose "Inserting extra commands: $textra" sed '/^@setfilename/a\ '"$textra" "$filename_input" >$filename_xtr filename_input=$filename_xtr fi # If clean mode was specified, then move to the temporary directory. if test "$clean" = t; then $verbose "cd $tmpdir_src" cd "$tmpdir_src" || exit 1 fi while :; do # will break out of loop below orig_xref_files=`$get_xref_files "$filename_noext"` # Save copies of originals for later comparison. if test -n "$orig_xref_files"; then $verbose "Backing up xref files: `echo $orig_xref_files | sed 's|\./||g'`" cp $orig_xref_files $tmpdir_bak fi # Run bibtex on current file. # - If its input (AUX) exists. # - If AUX contains both `\bibdata' and `\bibstyle'. # - If some citations are missing (LOG contains `Citation'). # or the LOG complains of a missing .bbl # # We run bibtex first, because I can see reasons for the indexes # to change after bibtex is run, but I see no reason for the # converse. # # Don't try to be too smart. Running bibtex only if the bbl file # exists and is older than the LaTeX file is wrong, since the # document might include files that have changed. Because there # can be several AUX (if there are \include's), but a single LOG, # looking for missing citations in LOG is easier, though we take # the risk to match false messages. if test -n "$bibtex" \ && test -r "$filename_noext.aux" \ && test -r "$filename_noext.log" \ && (grep '^\\bibdata[{]' "$filename_noext.aux" \ && grep '^\\bibstyle[{]' "$filename_noext.aux" \ && (grep 'Warning:.*Citation.*undefined' "$filename_noext.log" \ || grep 'No file .*\.bbl\.' "$filename_noext.log")) \ >/dev/null 2>&1; \ then $verbose "Running $bibtex $filename_noext ..." if $bibtex "$filename_noext" >&5; then :; else echo "$0: $bibtex exited with bad status, quitting." >&2 exit 1 fi fi # What we'll run texindex on -- exclude non-index files. # Since we know index files are last, it is correct to remove everything # before .aux and .?o?. index_files=`echo "$orig_xref_files" \ | sed "s!.*\.aux!!g; s!./$filename_noext\..o.!!g; s/^[ ]*//;s/[ ]*$//"` # Run texindex (or makeindex) on current index files. If they # already exist, and after running TeX a first time the index # files don't change, then there's no reason to run TeX again. # But we won't know that if the index files are out of date or # nonexistent. if test -n "$texindex" && test -n "$index_files"; then $verbose "Running $texindex $index_files ..." if $texindex $index_files 2>&5 1>&2; then :; else echo "$0: $texindex exited with bad status, quitting." >&2 exit 1 fi fi # Finally, run TeX. # Prevent $ESCAPE from being interpreted by the shell if it happens # to be `/'. $batch tex_args="\\${escape}nonstopmode\ \\${escape}input" cmd="$tex $tex_args $filename_input" $verbose "Running $cmd ..." if $cmd >&5; then :; else echo "$0: $tex exited with bad status, quitting." >&2 echo "$0: see $filename_noext.log for errors." >&2 test "$clean" = t \ && cp "$filename_noext.log" "$orig_pwd" exit 1 fi # Decide if looping again is needed. finished=t # LaTeX (and the package changebar) report in the LOG file if it # should be rerun. This is needed for files included from # subdirs, since texi2dvi does not try to compare xref files in # subdirs. Performing xref files test is still good since LaTeX # does not report changes in xref files. if fgrep "Rerun to get" "$filename_noext.log" >/dev/null 2>&1; then finished= fi # Check if xref files changed. new_xref_files=`$get_xref_files "$filename_noext"` $verbose "Original xref files = `echo $orig_xref_files | sed 's|\./||g'`" $verbose "New xref files = `echo $new_xref_files | sed 's|\./||g'`" # If old and new lists don't at least have the same file list, # then one file or another has definitely changed. test "x$orig_xref_files" != "x$new_xref_files" && finished= # File list is the same. We must compare each file until we find # a difference. if test -n "$finished"; then for this_file in $new_xref_files; do $verbose "Comparing xref file `echo $this_file | sed 's|\./||g'` ..." # cmp -s returns nonzero exit status if files differ. if cmp -s "$this_file" "$tmpdir_bak/$this_file"; then :; else # We only need to keep comparing until we find one that # differs, because we'll have to run texindex & tex again no # matter how many more there might be. finished= $verbose "xref file `echo $this_file | sed 's|\./||g'` differed ..." test "$debug" = t && diff -c "$tmpdir_bak/$this_file" "$this_file" break fi done fi # If finished, exit the loop, else rerun the loop. test -n "$finished" && break done # If we were in clean mode, compilation was in a tmp directory. # Copy the DVI (or PDF) file into the directory where the compilation # has been done. (The temp dir is about to get removed anyway.) # We also return to the original directory so that # - the next file is processed in correct conditions # - the temporary file can be removed if test -n "$clean"; then if test -n "$oname"; then dest=$oname else dest=$orig_pwd fi $verbose "Copying $oformat file from `pwd` to $dest" cp -p "./$filename_noext.$oformat" "$dest" cd / # in case $orig_pwd is on a different drive (for DOS) cd $orig_pwd || exit 1 fi # Remove temporary files. if test "x$debug" = "x"; then $verbose "Removing $tmpdir_src $tmpdir_xtr $tmpdir_bak ..." cd / rm -rf $tmpdir_src $tmpdir_xtr $tmpdir_bak fi done $verbose "$0 done." exit 0 # exit successfully, not however we ended the loop. smalltalk-3.2.5/build-aux/sockets.m40000644000175000017500000000333612123404352014236 00000000000000dnl I'd like this to be edited in -*- Autoconf -*- mode... dnl AC_DEFUN([GST_SOCKETS], [ AC_SEARCH_LIBS(listen, socket, [], [ dnl Check for listen on MinGW. We need to include dnl to get the correct __stdcall name decoration AC_CACHE_CHECK([for listen in -lws2_32], [ac_cv_lib_ws2_32_listen], [ OLD_LIBS="$LIBS" LIBS="-lws2_32 $LIBS" AC_LINK_IFELSE([AC_LANG_PROGRAM([[#include ]], [[listen(0,0);]])], [ac_cv_lib_ws2_32_listen=yes], [ac_cv_lib_ws2_32_listen=no]) LIBS="$OLD_LIBS"])]) AC_SEARCH_LIBS(gethostbyname, nsl) gst_cv_sockets=yes AC_CHECK_FUNC(socket, , gst_cv_sockets=no) AC_CHECK_HEADERS(arpa/inet.h netdb.h netinet/in.h, , gst_cv_sockets=no) if test "$ac_cv_lib_ws2_32_listen" = "yes"; then gst_cv_sockets=yes AC_CHECK_HEADERS([ws2tcpip.h]) SOCKET_LIBS='-lws2_32' fi AC_SUBST(SOCKET_LIBS) AC_CHECK_DECLS([getaddrinfo, freeaddrinfo, gai_strerror, getnameinfo], [], [], [#ifdef HAVE_NETDB_H #include #endif #ifdef HAVE_WS2TCPIP_H #include #endif]) AC_CHECK_MEMBER([struct addrinfo.ai_family], [AC_DEFINE(HAVE_STRUCT_ADDRINFO, 1, [Define if your system's netdb.h has struct addrinfo])], [], [#ifdef HAVE_NETDB_H #include #endif #ifdef HAVE_WS2TCPIP_H #include #endif]) dnl This is wrong for Windows, but anyway Windows does not have sa_len AC_CHECK_MEMBERS([struct sockaddr.sa_len], , , [#include ]) if test $gst_cv_sockets = yes; then GST_SOCKET_FAMILIES AC_CHECK_FUNCS(getipnodebyaddr) AC_REPLACE_FUNCS(getaddrinfo inet_ntop) AC_DEFINE(HAVE_SOCKETS, 1, [Define if your system has sockets.]) fi ])dnl smalltalk-3.2.5/build-aux/ltsugar.m40000644000175000017500000001042412130455417014246 00000000000000# ltsugar.m4 -- libtool m4 base layer. -*-Autoconf-*- # # Copyright (C) 2004, 2005, 2007, 2008 Free Software Foundation, Inc. # Written by Gary V. Vaughan, 2004 # # This file is free software; the Free Software Foundation gives # unlimited permission to copy and/or distribute it, with or without # modifications, as long as this notice is preserved. # serial 6 ltsugar.m4 # This is to help aclocal find these macros, as it can't see m4_define. AC_DEFUN([LTSUGAR_VERSION], [m4_if([0.1])]) # lt_join(SEP, ARG1, [ARG2...]) # ----------------------------- # Produce ARG1SEPARG2...SEPARGn, omitting [] arguments and their # associated separator. # Needed until we can rely on m4_join from Autoconf 2.62, since all earlier # versions in m4sugar had bugs. m4_define([lt_join], [m4_if([$#], [1], [], [$#], [2], [[$2]], [m4_if([$2], [], [], [[$2]_])$0([$1], m4_shift(m4_shift($@)))])]) m4_define([_lt_join], [m4_if([$#$2], [2], [], [m4_if([$2], [], [], [[$1$2]])$0([$1], m4_shift(m4_shift($@)))])]) # lt_car(LIST) # lt_cdr(LIST) # ------------ # Manipulate m4 lists. # These macros are necessary as long as will still need to support # Autoconf-2.59 which quotes differently. m4_define([lt_car], [[$1]]) m4_define([lt_cdr], [m4_if([$#], 0, [m4_fatal([$0: cannot be called without arguments])], [$#], 1, [], [m4_dquote(m4_shift($@))])]) m4_define([lt_unquote], $1) # lt_append(MACRO-NAME, STRING, [SEPARATOR]) # ------------------------------------------ # Redefine MACRO-NAME to hold its former content plus `SEPARATOR'`STRING'. # Note that neither SEPARATOR nor STRING are expanded; they are appended # to MACRO-NAME as is (leaving the expansion for when MACRO-NAME is invoked). # No SEPARATOR is output if MACRO-NAME was previously undefined (different # than defined and empty). # # This macro is needed until we can rely on Autoconf 2.62, since earlier # versions of m4sugar mistakenly expanded SEPARATOR but not STRING. m4_define([lt_append], [m4_define([$1], m4_ifdef([$1], [m4_defn([$1])[$3]])[$2])]) # lt_combine(SEP, PREFIX-LIST, INFIX, SUFFIX1, [SUFFIX2...]) # ---------------------------------------------------------- # Produce a SEP delimited list of all paired combinations of elements of # PREFIX-LIST with SUFFIX1 through SUFFIXn. Each element of the list # has the form PREFIXmINFIXSUFFIXn. # Needed until we can rely on m4_combine added in Autoconf 2.62. m4_define([lt_combine], [m4_if(m4_eval([$# > 3]), [1], [m4_pushdef([_Lt_sep], [m4_define([_Lt_sep], m4_defn([lt_car]))])]]dnl [[m4_foreach([_Lt_prefix], [$2], [m4_foreach([_Lt_suffix], ]m4_dquote(m4_dquote(m4_shift(m4_shift(m4_shift($@)))))[, [_Lt_sep([$1])[]m4_defn([_Lt_prefix])[$3]m4_defn([_Lt_suffix])])])])]) # lt_if_append_uniq(MACRO-NAME, VARNAME, [SEPARATOR], [UNIQ], [NOT-UNIQ]) # ----------------------------------------------------------------------- # Iff MACRO-NAME does not yet contain VARNAME, then append it (delimited # by SEPARATOR if supplied) and expand UNIQ, else NOT-UNIQ. m4_define([lt_if_append_uniq], [m4_ifdef([$1], [m4_if(m4_index([$3]m4_defn([$1])[$3], [$3$2$3]), [-1], [lt_append([$1], [$2], [$3])$4], [$5])], [lt_append([$1], [$2], [$3])$4])]) # lt_dict_add(DICT, KEY, VALUE) # ----------------------------- m4_define([lt_dict_add], [m4_define([$1($2)], [$3])]) # lt_dict_add_subkey(DICT, KEY, SUBKEY, VALUE) # -------------------------------------------- m4_define([lt_dict_add_subkey], [m4_define([$1($2:$3)], [$4])]) # lt_dict_fetch(DICT, KEY, [SUBKEY]) # ---------------------------------- m4_define([lt_dict_fetch], [m4_ifval([$3], m4_ifdef([$1($2:$3)], [m4_defn([$1($2:$3)])]), m4_ifdef([$1($2)], [m4_defn([$1($2)])]))]) # lt_if_dict_fetch(DICT, KEY, [SUBKEY], VALUE, IF-TRUE, [IF-FALSE]) # ----------------------------------------------------------------- m4_define([lt_if_dict_fetch], [m4_if(lt_dict_fetch([$1], [$2], [$3]), [$4], [$5], [$6])]) # lt_dict_filter(DICT, [SUBKEY], VALUE, [SEPARATOR], KEY, [...]) # -------------------------------------------------------------- m4_define([lt_dict_filter], [m4_if([$5], [], [], [lt_join(m4_quote(m4_default([$4], [[, ]])), lt_unquote(m4_split(m4_normalize(m4_foreach(_Lt_key, lt_car([m4_shiftn(4, $@)]), [lt_if_dict_fetch([$1], _Lt_key, [$2], [$3], [_Lt_key ])])))))])[]dnl ]) smalltalk-3.2.5/build-aux/snprintfv.m40000644000175000017500000000704212123404352014612 00000000000000dnl AC_SNPRINTFV_CONVENIENCE[(dir)] - sets LIBSNPRINTFV to the link flags for dnl the snprintfv convenience library and INCSNPRINTFV to the include flags for dnl the snprintfv header and adds --enable-snprintfv-convenience to the dnl configure arguments. Note that AC_CONFIG_SUBDIRS is not called. If DIR dnl is not provided, it is assumed to be `snprintfv'. LIBSNPRINTFV will be dnl prefixed with '${top_builddir}/' and INCSNPRINTFV will be prefixed with dnl '${top_srcdir}/' (note the single quotes!). If your package is not dnl flat and you're not using automake, define top_builddir and dnl top_srcdir appropriately in the Makefiles. AC_DEFUN([AC_SNPRINTFV_CONVENIENCE], [case $enable_snprintfv_convenience in no) AC_MSG_ERROR([this package needs a convenience snprintfv]) ;; "") enable_snprintfv_convenience=yes ac_configure_args="$ac_configure_args --enable-snprintfv-convenience" ;; esac LIBSNPRINTFV='${top_builddir}/'ifelse($#,1,[$1],['snprintfv'])/snprintfv/libsnprintfvc.la INCSNPRINTFV='-I${top_builddir}/'ifelse($#,1,[$1],['snprintfv'])' -I${top_srcdir}/'ifelse($#,1,[$1],['snprintfv']) AC_SUBST(LIBSNPRINTFV) AC_SUBST(INCSNPRINTFV) ]) dnl AC_SNPRINTFV_INSTALLABLE[(dir)] - sets LIBSNPRINTFV to the link flags for dnl the snprintfv installable library and INCSNPRINTFV to the include flags for dnl the snprintfv header and adds --enable-snprintfv-install to the dnl configure arguments. Note that AC_CONFIG_SUBDIRS is not called. If DIR dnl is not provided and an installed libsnprintfv is not found, it is assumed dnl to be `snprintfv'. LIBSNPRINTFV will be prefixed with '${top_builddir}/' dnl and INCSNPRINTFV will be prefixed with # '${top_srcdir}/' (note the single dnl quotes!). If your package is not flat and you're not using automake, dnl define top_builddir and top_srcdir appropriately in the Makefiles. dnl In the future, this macro may have to be called after AC_PROG_LIBTOOL. AC_DEFUN([AC_SNPRINTFV_INSTALLABLE], [AC_BEFORE([$0],[AC_LIBTOOL_SETUP])dnl AC_REQUIRE([AC_CANONICAL_HOST])dnl AC_CHECK_LIB(snprintfv, snv_printf, [test x"$enable_snprintfv_install" != xyes && enable_snprintfv_install=no], [if test x"$enable_snprintfv_install" = xno; then AC_MSG_WARN([snprintfv not installed, but installation disabled]) else enable_snprintfv_install=yes # ---------------------------------------------------------------------- # Win32 objects need to tell the header whether they will be linking # with a dll or static archive in order that everything is imported # to the object in the same way that it was exported from the # archive (``extern'' for static, ``__declspec(dllimport)'' for dlls). # ---------------------------------------------------------------------- case "$host" in *-*-cygwin* | *-*-mingw* | *-*-os2) AC_DEFINE([LIBSNPRINTFV_DLL_IMPORT], , [Defined to 1 to work around Windows' broken implementation of exported data symbols]) echo '#define LIBSNPRINTFV_DLL_IMPORT 1' >> $tmpfile fi ;; esac fi ]) if test x"$enable_snprintfv_install" = x"yes"; then ac_configure_args="$ac_configure_args --enable-snprintfv-install" LIBSNPRINTFV='${top_builddir}/'ifelse($#,1,[$1],['snprintfv'])/snprintfv/libsnprintfv.la INCSNPRINTFV='-I${top_srcdir}/'ifelse($#,1,[$1],['snprintfv']) INCSNPRINTFV='-I${top_builddir}/'ifelse($#,1,[$1],['snprintfv'])' -I${top_srcdir}/'ifelse($#,1,[$1],['snprintfv']) else ac_configure_args="$ac_configure_args --enable-snprintfv-install=no" LIBSNPRINTFV="-lsnprintfv" INCSNPRINTFV= fi ]) smalltalk-3.2.5/build-aux/sockpfaf.m40000644000175000017500000000361412123404352014356 00000000000000# sockpfaf.m4 serial 5 dnl Copyright (C) 2004, 2006 Free Software Foundation, Inc. dnl This file is free software; the Free Software Foundation dnl gives unlimited permission to copy and/or distribute it, dnl with or without modifications, as long as this notice is preserved. dnl Test for some common socket protocol families (PF_INET, PF_INET6, ...) dnl and some common address families (AF_INET, AF_INET6, ...). dnl This test assumes that a system supports an address family if and only if dnl it supports the corresponding protocol family. dnl From Bruno Haible. AC_DEFUN([GST_SOCKET_FAMILIES], [ AC_CHECK_HEADERS([netinet/in.h]) AC_MSG_CHECKING(for IPv4 sockets) AC_CACHE_VAL(gst_cv_socket_ipv4, [AC_TRY_COMPILE([#include #ifdef HAVE_SYS_SOCKET_H #include #endif #ifdef HAVE_NETINET_IN_H #include #endif #ifdef HAVE_WINSOCK2_H #include #endif #ifdef HAVE_WS2TCPIP_H #include #endif], [int x = AF_INET; struct in_addr y; struct sockaddr_in z; if (&x && &y && &z) return 0;], gst_cv_socket_ipv4=yes, gst_cv_socket_ipv4=no)]) AC_MSG_RESULT($gst_cv_socket_ipv4) if test $gst_cv_socket_ipv4 = yes; then AC_DEFINE(HAVE_IPV4, 1, [Define to 1 if defines AF_INET.]) fi AC_MSG_CHECKING(for IPv6 sockets) AC_CACHE_VAL(gst_cv_socket_ipv6, [AC_TRY_COMPILE([#include #ifdef HAVE_SYS_SOCKET_H #include #endif #ifdef HAVE_NETINET_IN_H #include #endif #ifdef HAVE_WINSOCK2_H #include #endif #ifdef HAVE_WS2TCPIP_H #include #endif], [int x = AF_INET6; struct in6_addr y; struct sockaddr_in6 z; if (&x && &y && &z) return 0;], gst_cv_socket_ipv6=yes, gst_cv_socket_ipv6=no)]) AC_MSG_RESULT($gst_cv_socket_ipv6) if test $gst_cv_socket_ipv6 = yes; then AC_DEFINE(HAVE_IPV6, 1, [Define to 1 if defines AF_INET6.]) fi ]) smalltalk-3.2.5/Makefile.am0000644000175000017500000002063212130343734012465 00000000000000# Copyright 2000, 2001, 2002, 2003, 2004, 2005, 2006, 2007, 2008, 2009 # Free Software Foundation, Inc. # This program is free software; you can redistribute it and/or modify # it under the terms of the GNU General Public License as published by # the Free Software Foundation; either version 2, or (at your option) # any later version. # This program is distributed in the hope that it will be useful, # but WITHOUT ANY WARRANTY; without even the implied warranty of # MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the # GNU General Public License for more details. # You should have received a copy of the GNU General Public License # along with this program; if not, write to the Free Software # Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. # Automake requirements AUTOMAKE_OPTIONS = gnu 1.11 dist-xz ACLOCAL_AMFLAGS = -I build-aux DISTCHECK_CONFIGURE_FLAGS=--without-system-libltdl --without-system-libsigsegv --without-system-libffi PACKAGE=smalltalk gstdatadir=$(pkgdatadir) DIST_SUBDIRS = lib-src snprintfv lightning sigsegv libffi opcode libgst \ . $(ALL_PACKAGES) tests doc SUBDIRS = lib-src lightning $(subdirs) if ENABLE_DISASSEMBLER SUBDIRS += opcode endif SUBDIRS += libgst . $(BUILT_PACKAGES) doc tests # Running gst inside the build directory... GST_OPTS = --kernel-dir "@srcdir@/kernel" --image gst.im GST = $(WINEWRAPPER) ./gst$(EXEEXT) --no-user-files $(GST_OPTS) GST_PACKAGE = XZIP="$(XZIP)" $(WINEWRAPPER) ./gst-tool$(EXEEXT) gst-package $(GST_OPTS) ########################################################### # # Rules for configuration files # ########################################################### aclocaldir = $(datadir)/aclocal dist_aclocal_DATA = build-aux/gst.m4 build-aux/gst-package.m4 dist_noinst_DATA = Doxyfile dist_noinst_SCRIPTS = build-aux/texi2dvi build-aux/texi2html \ build-aux/help2man build-aux/config.rpath ########################################################### # # Rules for scripts and data files # ########################################################### pkgconfigdir = $(libdir)/pkgconfig nodist_pkgconfig_DATA = gnu-smalltalk.pc if NEED_LIBC_LA module_DATA = libc.la endif noinst_DATA = gst.im dist_noinst_DATA += smalltalk-mode-init.el.in gst-mode.el.in \ .gdbinit scripts/Finish.st gsticon.ico packages/xml/ChangeLog \ packages/seaside/PORTING bin_SCRIPTS = gst-config DISTCLEANFILES = termbold termnorm pkgrules.tmp CLEANFILES = gst.im $(nodist_lisp_LISP) $(nodist_lispstart_LISP) if WITH_EMACS dist_lisp_LISP = smalltalk-mode.el nodist_lispstart_LISP = smalltalk-mode-init.el if WITH_EMACS_COMINT nodist_lisp_LISP = gst-mode.el endif endif if WITH_EMACS_COMINT LISP_WITH_EMACS_COMINT = else LISP_WITH_EMACS_COMINT = ; endif smalltalk-mode-init.el: smalltalk-mode-init.el.in $(SED) -e "s,@\(lispdir\)@,$(lispdir)," \ -e "s/@\(WITH_EMACS_COMINT_TRUE\)@/$(LISP_WITH_EMACS_COMINT)/" \ $(srcdir)/smalltalk-mode-init.el.in > smalltalk-mode-init.el gst-mode.el: gst-mode.el.in $(SED) -e "s,@\(bindir\)@,$(bindir)," $(srcdir)/gst-mode.el.in \ > gst-mode.el ########################################################### # # Rules for building the VM # ########################################################### AM_CPPFLAGS = -I$(top_srcdir)/libgst \ -I$(top_srcdir)/lib-src \ -DCMD_XZIP="\"$(XZIP)\"" \ -DCMD_INSTALL="\"$(INSTALL)\"" \ -DCMD_LN_S="\"$(LN_S)\"" \ $(RELOC_CPPFLAGS) bin_PROGRAMS = gst gst_SOURCES = main.c gst_LDADD = libgst/libgst.la lib-src/library.la @ICON@ gst_DEPENDENCIES = libgst/libgst.la lib-src/library.la @ICON@ gst_LDFLAGS = -export-dynamic $(RELOC_LDFLAGS) $(LIBFFI_EXECUTABLE_LDFLAGS) if ENABLE_DISASSEMBLER gst_LDADD += opcode/libdisass.la gst_DEPENDENCIES += opcode/libdisass.la AM_CPPFLAGS += -I$(top_srcdir)/opcode endif # The single gst-tool executable is installed with multiple names, hence # we use noinst here. noinst_PROGRAMS = gst-tool gst_tool_SOURCES = gst-tool.c gst_tool_LDADD = libgst/libgst.la lib-src/library.la @ICON@ gst_tool_DEPENDENCIES = libgst/libgst.la lib-src/library.la @ICON@ gst_tool_LDFLAGS = -export-dynamic $(RELOC_LDFLAGS) $(LIBFFI_EXECUTABLE_LDFLAGS) # Used to call the Unix zip from Wine EXTRA_PROGRAMS = winewrapper winewrapper_SOURCES = winewrapper.c GST_EXTRA_TOOLS = gst-reload gst-sunit gst-blox gst-package gst-convert \ gst-doc gst-remote gst-profile gst-browser uninstall-local:: @for i in gst-load $(GST_EXTRA_TOOLS); do \ echo rm -f "$(DESTDIR)$(bindir)/$$i$(EXEEXT)"; \ rm -f "$(DESTDIR)$(bindir)/$$i$(EXEEXT)"; \ done install-exec-hook:: $(INSTALL_PROGRAM_ENV) $(LIBTOOL) --mode=install $(INSTALL) gst-tool$(EXEEXT) "$(DESTDIR)$(bindir)/gst-load$(EXEEXT)" @for i in $(GST_EXTRA_TOOLS); do \ echo $(LN) -f "$(DESTDIR)$(bindir)/gst-load$(EXEEXT)" "$(DESTDIR)$(bindir)/$$i$(EXEEXT)"; \ $(LN) -f "$(DESTDIR)$(bindir)/gst-load$(EXEEXT)" "$(DESTDIR)$(bindir)/$$i$(EXEEXT)"; \ done nodist_noinst_HEADERS = config.h DISTCLEANFILES += config.h # These two lines add a beatiful icon to the Win32 executable gsticon.o: gsticon.ico cd $(srcdir) && echo ProgramIcon ICON `$(CYGPATH_W) gsticon.ico` | \ $(WINDRES) -o $(abs_builddir)/gsticon.o gst.im: $(bin_PROGRAMS) $(srcdir)/kernel/stamp-classes $(WINEWRAPPERDEP) $(GST) -iQ /dev/null ########################################################### # # Rules for distributing the superops program # ########################################################### dist_noinst_DATA += \ superops/ChangeLog superops/Makefile superops/README \ superops/bool-array.cc superops/bool-array.h superops/bool-array.icc \ superops/byte_def.cc superops/byte_def.h superops/hash-table.cc \ superops/hash-table.h superops/hash.cc superops/hash.h \ superops/keyword-list.cc superops/keyword-list.h superops/keyword-list.icc \ superops/keyword.cc superops/keyword.h superops/keyword.icc \ superops/observer-list.cc superops/observer-list.h superops/options.cc \ superops/options.h superops/options.icc superops/positions.cc \ superops/positions.h superops/positions.icc superops/search.cc \ superops/search.h superops/superops.cc superops/table.cc superops/table.h \ superops/vm_def.cc superops/vm_def.h ########################################################### # # Rules for installing and distributing # # More rules are created by the GST_PACKAGE macros, # including the stamp files used for building the # documentation. Here we mimic those rules for the # kernel, whose file list lives in packages.xml # ########################################################### -include $(srcdir)/kernel/Makefile.frag all-local: $(srcdir)/kernel/stamp-classes # The slow rule for building the stamp-classes files uses gst-package, and # depends on packages.xml in order to run when the list of files in the # package might have changed. The fast rule just touches the file. We # could actually do without double-colon rules by using another stamp file # which depends on packages.xml and rebuilds all the stamp-classes files. $(srcdir)/kernel/Makefile.frag: $(srcdir)/packages.xml $(WINEWRAPPERDEP) (echo '$$(srcdir)/kernel/stamp-classes: \'; \ $(GST_PACKAGE) --list-files Kernel --vpath --srcdir="$(srcdir)" $(srcdir)/packages.xml | \ tr -d \\r | tr \\n ' '; \ echo; \ echo ' touch $$(srcdir)/kernel/stamp-classes') \ > $(srcdir)/kernel/Makefile.frag all-local: clean-local:: dist-hook:: $(GST_PACKAGE) --dist \ --distdir="$(distdir)" --srcdir="$(srcdir)" \ $(srcdir)/packages.xml cp -p $(srcdir)/kernel/stamp-classes $(distdir)/kernel/stamp-classes cp -p $(srcdir)/kernel/Makefile.frag $(distdir)/kernel/Makefile.frag # Build an image after installing the data; install-data runs after # install-exec, so the gst executable is already in bindir. # To install the kernel files, we use gst-package in --dist mode. install-data-hook:: $(GST_PACKAGE) --dist --copy --all-files \ --destdir="$(DESTDIR)" --target-dir="$(pkgdatadir)" \ --srcdir "$(srcdir)" $(srcdir)/packages.xml $(mkdir_p) $(DESTDIR)$(imagedir) cd $(DESTDIR)$(imagedir) && \ $(WINEWRAPPER) "$(abs_top_builddir)/gst$(EXEEXT)" --no-user-files -iS \ --kernel-dir "$(DESTDIR)$(pkgdatadir)/kernel" \ --image "$(DESTDIR)$(imagedir)/gst.im" \ -f "@abs_top_srcdir@/scripts/Finish.st" \ "$(imagedir)" $(MODULES) uninstall-local:: gst-tool$(EXEEXT) $(WINEWRAPPER) $(GST_PACKAGE) \ --uninstall --destdir="$(DESTDIR)" --target-dir "$(pkgdatadir)" \ --srcdir $(srcdir) $(DESTDIR)$(pkgdatadir)/packages.xml -rm -f $(DESTDIR)$(imagedir)/gst.im @PACKAGE_RULES@ smalltalk-3.2.5/smalltalk-mode.el0000644000175000017500000012024612123404352013657 00000000000000;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;; ;;; ;;; Copyright 1988-92, 1994-95, 1999, 2000, 2003, 2007, 2008, 2009 ;;; Free Software Foundation, Inc. ;;; Written by Steve Byrne. ;;; ;;; This file is part of GNU Smalltalk. ;;; ;;; GNU Smalltalk is free software; you can redistribute it and/or modify it ;;; under the terms of the GNU General Public License as published by the Free ;;; Software Foundation; either version 2, or (at your option) any later ;;; version. ;;; ;;; GNU Smalltalk is distributed in the hope that it will be useful, but ;;; WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY ;;; or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License ;;; for more details. ;;; ;;; You should have received a copy of the GNU General Public License along ;;; with GNU Smalltalk; see the file COPYING. If not, write to the Free ;;; Software Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. ;;; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;; ;;; Incorporates Frank Caggiano's changes for Emacs 19. ;;; Updates and changes for Emacs 20 and 21 by David Forster ;; ===[ Variables and constants ]===================================== (defvar smalltalk-name-regexp "[A-z][A-z0-9_]*" "A regular expression that matches a Smalltalk identifier") (defvar smalltalk-keyword-regexp (concat smalltalk-name-regexp ":") "A regular expression that matches a Smalltalk keyword") (defvar smalltalk-name-chars "A-z0-9" "The collection of character that can compose a Smalltalk identifier") (defvar smalltalk-whitespace " \t\n\f") (defconst smalltalk-indent-amount 4 "*'Tab size'; used for simple indentation alignment.") ;; ---[ Syntax Table ]------------------------------------------------ ;; This may very well be a bug, but certin chars like ?+ are set to be ;; punctuation, when in fact one might think of them as words (that ;; is, they are valid selector names). Some functions will fail ;; however, (like smalltalk-begin-of-defun) so there punctuation. ;; Works for now... (defvar smalltalk-mode-syntax-table (let ((table (make-syntax-table))) ;; Make sure A-z0-9 are set to "w " for completeness (let ((c 0)) (setq c ?0) (while (<= c ?9) (setq c (1+ c)) (modify-syntax-entry c "w " table)) (setq c ?A) (while (<= c ?Z) (setq c (1+ c)) (modify-syntax-entry c "w " table)) (setq c ?a) (while (<= c ?z) (setq c (1+ c)) (modify-syntax-entry c "w " table))) (modify-syntax-entry 10 " > " table) ; Comment (generic) (modify-syntax-entry ?: ". " table) ; Symbol-char (modify-syntax-entry ?_ "_ " table) ; Symbol-char (modify-syntax-entry ?\" "!1 " table) ; Comment (generic) (modify-syntax-entry ?' "\" " table) ; String (modify-syntax-entry ?# "' " table) ; Symbol or Array constant (modify-syntax-entry ?\( "() " table) ; Grouping (modify-syntax-entry ?\) ")( " table) ; Grouping (modify-syntax-entry ?\[ "(] " table) ; Block-open (modify-syntax-entry ?\] ")[ " table) ; Block-close (modify-syntax-entry ?{ "(} " table) ; Array-open (modify-syntax-entry ?} "){ " table) ; Array-close (modify-syntax-entry ?$ "/ " table) ; Character literal (modify-syntax-entry ?! ". " table) ; End message / Delimit defs (modify-syntax-entry ?\; ". " table) ; Cascade (modify-syntax-entry ?| ". " table) ; Temporaries (modify-syntax-entry ?^ ". " table) ; Return ;; Just to make sure these are not set to "w " (modify-syntax-entry ?< ". " table) (modify-syntax-entry ?> ". " table) (modify-syntax-entry ?+ ". " table) ; math (modify-syntax-entry ?- ". " table) ; math (modify-syntax-entry ?* ". " table) ; math (modify-syntax-entry ?/ ".2 " table) ; math (modify-syntax-entry ?= ". " table) ; bool/assign (modify-syntax-entry ?% ". " table) ; valid selector (modify-syntax-entry ?& ". " table) ; boolean (modify-syntax-entry ?\\ ". " table) ; ??? (modify-syntax-entry ?~ ". " table) ; misc. selector (modify-syntax-entry ?@ ". " table) ; Point (modify-syntax-entry ?, ". " table) ; concat table) "Syntax table used by Smalltalk mode") ;; ---[ Abbrev table ]------------------------------------------------ (defvar smalltalk-mode-abbrev-table nil "Abbrev table in use in smalltalk-mode buffers.") (define-abbrev-table 'smalltalk-mode-abbrev-table ()) ;; ---[ Keymap ]------------------------------------------------------ (defvar smalltalk-template-map (let ((keymap (make-sparse-keymap))) (define-key keymap "p" 'smalltalk-private-template) (define-key keymap "c" 'smalltalk-class-template) (define-key keymap "i" 'smalltalk-instance-template) keymap) "Keymap of template creation keys") (defvar smalltalk-mode-map (let ((keymap (make-sparse-keymap))) (define-key keymap "\n" 'smalltalk-newline-and-indent) (define-key keymap "\C-c\C-a" 'smalltalk-begin-of-defun) (define-key keymap "\C-c\C-e" 'smalltalk-end-of-defun) (define-key keymap "\C-c\C-f" 'smalltalk-forward-sexp) (define-key keymap "\C-c\C-b" 'smalltalk-backward-sexp) (define-key keymap "\C-c\C-p" 'smalltalk-goto-previous-keyword) (define-key keymap "\C-c\C-n" 'smalltalk-goto-next-keyword) ;; the following three are deprecated (define-key keymap "\C-\M-a" 'smalltalk-begin-of-defun) (define-key keymap "\C-\M-f" 'smalltalk-forward-sexp) (define-key keymap "\C-\M-b" 'smalltalk-backward-sexp) (define-key keymap "!" 'smalltalk-bang) (define-key keymap ":" 'smalltalk-colon) (define-key keymap "\C-ct" smalltalk-template-map) ;; ----- (define-key keymap "\C-cd" 'smalltalk-doit) (define-key keymap "\C-cf" 'smalltalk-filein-buffer) (define-key keymap "\C-cm" 'gst) (define-key keymap "\C-cp" 'smalltalk-print) (define-key keymap "\C-cq" 'smalltalk-quit) (define-key keymap "\C-cs" 'smalltalk-snapshot) keymap) "Keymap for Smalltalk mode") (defconst smalltalk-binsel "\\([-+*/~,<>=&?]\\{1,2\\}\\|:=\\|||\\)" "Smalltalk binary selectors") (defconst smalltalk-font-lock-keywords (list '("#[A-z][A-z0-9_]*" . font-lock-constant-face) '("\\<[A-z][A-z0-9_]*:" . font-lock-function-name-face) (cons smalltalk-binsel 'font-lock-function-name-face) ; '("\\^" . font-lock-keyword-face) '("\\$." . font-lock-string-face) ;; Chars '("\\<[A-Z]\\sw*\\>" . font-lock-type-face)) "Basic Smalltalk keywords font-locking") (defconst smalltalk-font-lock-keywords-1 smalltalk-font-lock-keywords "Level 1 Smalltalk font-locking keywords") (defconst smalltalk-font-lock-keywords-2 (append smalltalk-font-lock-keywords-1 (list '("\\<\\(true\\|false\\|nil\\|self\\|super\\)\\>" . font-lock-builtin-face) '(":[a-z][A-z0-9_]*" . font-lock-variable-name-face) '(" |" . font-lock-type-face) '("<.*>" . font-lock-builtin-face))) "Level 2 Smalltalk font-locking keywords") (defvar smalltalk-last-category "" "Category of last method") ;; ---[ Interactive functions ]--------------------------------------- (defun smalltalk-mode () "Major mode for editing Smalltalk code. Commands: \\{smalltalk-mode-map} " (interactive) (kill-all-local-variables) (setq major-mode 'smalltalk-mode) (setq mode-name "Smalltalk") (use-local-map smalltalk-mode-map) (set-syntax-table smalltalk-mode-syntax-table) (setq local-abbrev-table smalltalk-mode-abbrev-table) ;; Buffer locals (set (make-local-variable 'paragraph-start) (concat "^$\\|" page-delimiter)) (set (make-local-variable 'paragraph-separate) paragraph-start) (set (make-local-variable 'paragraph-ignore-fill-prefix) t) (set (make-local-variable 'indent-line-function) 'smalltalk-indent-line) (set (make-local-variable 'require-final-newline) t) (set (make-local-variable 'comment-start) "\"") (set (make-local-variable 'comment-end) "\"") (set (make-local-variable 'comment-column) 32) (set (make-local-variable 'comment-start-skip) "\" *") ;; Doesn't seem useful...? (set (make-local-variable 'comment-indent-function) 'smalltalk-comment-indent) ;; For interactive f-b sexp (set (make-local-variable 'parse-sexp-ignore-comments) t) ;; font-locking (set (make-local-variable 'font-lock-defaults) '((smalltalk-font-lock-keywords smalltalk-font-lock-keywords-1 smalltalk-font-lock-keywords-2) nil nil nil nil)) ;; tags (set (make-local-variable 'find-tag-default-function) 'smalltalk-find-message) ;; Run hooks, must be last (run-hooks 'smalltalk-mode-hook)) (defun smalltalk-tab () (interactive) (let (col) ;; round up, with overflow (setq col (* (/ (+ (current-column) smalltalk-indent-amount) smalltalk-indent-amount) smalltalk-indent-amount)) (indent-to-column col))) (defun smalltalk-bang-begin-of-defun () (let ((parse-sexp-ignore-comments t) here delim start) (setq here (point)) (while (and (search-backward "!" nil 'to-end) (setq delim (smalltalk-in-string))) (search-backward delim)) (setq start (point)) (if (looking-at "!") (forward-char 1)) (smalltalk-forward-whitespace) ;; check to see if we were already at the start of a method ;; in which case, the semantics are to go to the one preceeding ;; this one (if (and (= here (point)) (/= start (point-min))) (progn (goto-char start) (smalltalk-backward-whitespace) ;may be at ! "foo" ! (if (= (preceding-char) ?!) (backward-char 1)) (smalltalk-begin-of-defun))))) ;and go to the next one (defun smalltalk-scope-begin-of-defun () (let (here prev (start (smalltalk-current-scope-point))) (if (and start (/= (point) start)) (progn (backward-char 1) (skip-chars-backward " \t") (if (bolp) (backward-char 1) (end-of-line)) (setq here (point)) (goto-char start) (skip-chars-forward "^[") (forward-char 1) (condition-case nil (while (< (point) here) (if (looking-at "[ \t]*\\[") (setq prev (point))) (forward-sexp 1)) (error t)) (if prev (progn (goto-char prev) (condition-case nil (progn (forward-sexp 1) (if (and (< (point) here) (= (char-before) ?\])) (progn (skip-syntax-forward " \t") (setq prev (point))))) (error t)) (goto-char prev) (beginning-of-line) (skip-chars-forward " \t")) (goto-char start)))))) (defun smalltalk-begin-of-defun () "Skips to the beginning of the current method. If already at the beginning of a method, skips to the beginning of the previous one." (interactive) (if (smalltalk-in-bang-syntax) (smalltalk-bang-begin-of-defun) (smalltalk-scope-begin-of-defun))) (defun smalltalk-begin-of-scope () "Skips to the beginning of the current method. If already at the beginning of a method, skips to the beginning of the previous one." (interactive) (let ((start (smalltalk-current-scope-point))) (if start (goto-char start)))) (defun smalltalk-forward-sexp (n) "Move point left to the next smalltalk expression." (interactive "p") (let (i) (cond ((< n 0) (smalltalk-backward-sexp (- n))) ((null parse-sexp-ignore-comments) (forward-sexp n)) (t (while (> n 0) (smalltalk-forward-whitespace) (forward-sexp 1) (setq n (1- n))))))) (defun smalltalk-backward-sexp (n) "Move point right to the next smalltalk expression." (interactive "p") (let (i) (cond ((< n 0) (smalltalk-forward-sexp (- n))) ((null parse-sexp-ignore-comments) (backward-sexp n)) (t (while (> n 0) (smalltalk-backward-whitespace) (backward-sexp 1) (setq n (1- n))))))) (defun smalltalk-reindent () (interactive) (smalltalk-indent-line)) (defun smalltalk-newline-and-indent () "Called basically to do newline and indent. Sees if the current line is a new statement, in which case the indentation is the same as the previous statement (if there is one), or is determined by context; or, if the current line is not the start of a new statement, in which case the start of the previous line is used, except if that is the start of a new line in which case it indents by smalltalk-indent-amount." (interactive) (newline) (smalltalk-indent-line)) (defun smalltalk-colon () "Possibly reindents a line when a colon is typed. If the colon appears on a keyword that's at the start of the line (ignoring whitespace, of course), then the previous line is examined to see if there is a colon on that line, in which case this colon should be aligned with the left most character of that keyword. This function is not fooled by nested expressions." (interactive) (let (needs-indent state (parse-sexp-ignore-comments t)) (setq state (parse-partial-sexp (point-min) (point))) (if (null (nth 3 state)) ;we're not in string or comment (progn (save-excursion (skip-chars-backward "A-z0-9_") (if (and (looking-at smalltalk-name-regexp) (not (smalltalk-at-begin-of-defun))) (setq needs-indent (smalltalk-white-to-bolp)))) (and needs-indent (smalltalk-indent-for-colon)))) ;; out temporarily ;; (expand-abbrev) ;I don't think this is the "correct" ;; ;way to do this...I suspect that ;; ;some flavor of "call interactively" ;; ;is better. (self-insert-command 1))) (defun smalltalk-bang () "Go to the end of the method definition" (interactive) (cond ((or (smalltalk-in-string) (smalltalk-in-comment)) (insert "!")) ((smalltalk-in-bang-syntax) (progn (insert "!") (save-excursion (beginning-of-line) (if (looking-at "^[ \t]+!") (delete-horizontal-space))))) (t (smalltalk-end-of-defun)))) (defun smalltalk-end-of-defun () (interactive) (if (smalltalk-in-bang-syntax) (progn (search-forward "!") (forward-char 1) (if (looking-at "[ \t\n]+!") (progn (search-forward 1) (forward-char 1)))) (progn (end-of-line) (smalltalk-begin-of-defun) (skip-chars-forward "^[") (forward-sexp 1) (skip-chars-forward " \t\n")))) (defun smalltalk-last-category-name () smalltalk-last-category) (defun smalltalk-insert-indented-line (string) (insert (format "%s\n" string)) (save-excursion (backward-char 1) (smalltalk-indent-line))) (defun smalltalk-maybe-insert-spacing-line (n) (if (not (save-excursion (previous-line n) (looking-at "^[ \t]*$"))) (insert "\n"))) (defun smalltalk-insert-method-body (selector-name category-name) (let (insert-at-top) (beginning-of-line) (smalltalk-forward-whitespace) (beginning-of-line) (setq insert-at-top (smalltalk-at-begin-of-defun)) (if (not insert-at-top) (progn (smalltalk-end-of-defun) (beginning-of-line))) (smalltalk-maybe-insert-spacing-line 1) (smalltalk-insert-indented-line (format "%s [" selector-name)) (save-excursion (insert "\n") (if (not (equal category-name "")) (smalltalk-insert-indented-line (format "" category-name))) (smalltalk-insert-indented-line "]") (smalltalk-maybe-insert-spacing-line 0)) (smalltalk-indent-line) (end-of-line))) (defun smalltalk-instance-template-fn (class-name selector-name category-name) (setq smalltalk-last-category category-name) (smalltalk-exit-class-scope) (smalltalk-insert-method-body (if (equal class-name (smalltalk-current-class-name)) selector-name (format "%s >> %s" class-name selector-name)) category-name)) (defun smalltalk-class-template-fn (class-name selector-name category-name) (setq smalltalk-last-category category-name) (if (and (equal selector-name "") (equal class-name (smalltalk-current-class-name))) (progn (smalltalk-insert-method-body (format " %s class" class-name) "") (setq smalltalk-last-category "instance creation")) (smalltalk-insert-method-body (if (and (smalltalk-in-class-scope) (equal class-name (smalltalk-current-class-name))) selector-name (format "%s class >> %s" class-name selector-name)) category-name))) (defun smalltalk-private-template-fn (class-name selector-name) (if (smalltalk-in-class-scope) (smalltalk-class-template-fn class-name selector-name "private") (smalltalk-instance-template-fn class-name selector-name "private"))) (defun smalltalk-maybe-read-class (with-class) (if (= with-class 1) (smalltalk-current-class-name) (read-string "Class: " (smalltalk-current-class-name)))) (defun smalltalk-instance-template (with-class) (interactive "p") (smalltalk-instance-template-fn (smalltalk-maybe-read-class with-class) (read-string "Selector: ") (read-string "Category: " (smalltalk-last-category-name)))) (defun smalltalk-class-template (with-class) (interactive "p") (let* ((class-name (smalltalk-maybe-read-class with-class)) (selector-name (read-string "Selector: ")) (category-name (if (equal selector-name "") "" (read-string "Category: " (smalltalk-last-category-name))))) (smalltalk-class-template-fn class-name selector-name category-name))) (defun smalltalk-private-template (with-class) (interactive "p") (smalltalk-private-template-fn (smalltalk-maybe-read-class with-class) (read-string "Selector: "))) ;; ---[ Non-interactive functions ]----------------------------------- ;; This is used by indent-for-comment ;; to decide how much to indent a comment in Smalltalk code ;; based on its context. (defun smalltalk-comment-indent () (if (looking-at "^\"") 0 ;Existing comment at bol stays there. (save-excursion (skip-chars-backward " \t") (max (1+ (current-column)) ;Else indent at comment column comment-column)))) ; except leave at least one space. (defun smalltalk-indent-line () (smalltalk-indent-to-column (save-excursion (beginning-of-line) (skip-chars-forward " \t") (if (and (not (smalltalk-in-comment)) (looking-at "[A-z][A-z0-9_]*:") (not (smalltalk-at-begin-of-defun))) (smalltalk-indent-for-colon) (smalltalk-calculate-indent))))) (defun smalltalk-toplevel-indent (for-scope) (let (orig) (condition-case nil (save-excursion (save-restriction (widen) (end-of-line) (setq orig (line-number-at-pos)) (if for-scope (smalltalk-begin-of-scope) (smalltalk-begin-of-defun)) (smalltalk-forward-whitespace) (if (= orig (line-number-at-pos)) (smalltalk-current-column) (+ smalltalk-indent-amount (smalltalk-current-column))))) (error 0)))) (defun smalltalk-statement-indent () (let (needs-indent indent-amount done c state orig start-of-line close (parse-sexp-ignore-comments nil)) (save-excursion (save-restriction (widen) (beginning-of-line) (setq close (looking-at "[ \t]*\]")) (narrow-to-region (point-min) (point)) ;only care about what's before (setq state (parse-partial-sexp (point-min) (point))) (cond ((nth 4 state) ;in a comment (save-excursion (smalltalk-backward-comment) (setq indent-amount (+ (current-column) (if (= (current-column) 0) 0 1))))) ((equal (nth 3 state) ?') ;in a string (setq indent-amount 0)) (close ;just before a closing bracket (save-excursion (condition-case nil (progn (widen) (smalltalk-forward-whitespace) (forward-char) (backward-sexp 1) (beginning-of-line) (smalltalk-forward-whitespace) (setq indent-amount (current-column)))))) (t (save-excursion (smalltalk-backward-whitespace) (if (or (bobp) (= (preceding-char) ?!)) (setq indent-amount 0))))) (if (null indent-amount) (progn (smalltalk-narrow-to-method) (beginning-of-line) (setq state (smalltalk-parse-sexp-and-narrow-to-paren)) (smalltalk-backward-whitespace) (cond ((bobp) ;must be first statment in block or exp (if (nth 1 state) ;we're in a paren exp (if (looking-at "$") ;; block with no statements, indent by 4 (setq indent-amount (+ (smalltalk-current-indent) smalltalk-indent-amount)) ;; block with statements, indent to first non-whitespace (setq indent-amount (smalltalk-current-column))) ;; we're top level (setq indent-amount (smalltalk-toplevel-indent nil)))) ((smalltalk-at-end-of-statement) ;end of statement or after temps (smalltalk-find-statement-begin) (setq indent-amount (smalltalk-current-column))) ((= (preceding-char) ?:) (beginning-of-line) (smalltalk-forward-whitespace) (setq indent-amount (+ (smalltalk-current-column) smalltalk-indent-amount))) ((= (preceding-char) ?>) ;maybe (save-excursion (beginning-of-line) (if (looking-at "[ \t]*<[ \t]*[a-zA-Z]+:") (setq indent-amount (smalltalk-toplevel-indent nil)))))))) (or indent-amount (save-excursion (condition-case nil (smalltalk-find-statement-begin) (error (beginning-of-line))) (+ (smalltalk-current-column) smalltalk-indent-amount))))))) (defun smalltalk-at-end-of-statement () (save-excursion (or (= (preceding-char) ?.) (and (= (preceding-char) ?|) (progn (backward-char 1) (while (and (not (bobp)) (looking-back "[ \t\na-zA-Z]")) (skip-chars-backward " \t\n") (skip-chars-backward "a-zA-Z")) (if (= (preceding-char) ?|) (progn (backward-char 1) (skip-chars-backward " \t\n"))) (bobp)))))) (defun smalltalk-calculate-indent () (cond ((smalltalk-at-begin-of-scope) (smalltalk-toplevel-indent t)) ((smalltalk-at-begin-of-defun) (smalltalk-toplevel-indent t)) (t (smalltalk-statement-indent)))) (defun smalltalk-in-string () "Returns non-nil delimiter as a string if the current location is actually inside a string or string like context." (let (state) (setq state (parse-partial-sexp (point-min) (point))) (and (nth 3 state) (char-to-string (nth 3 state))))) (defun smalltalk-in-comment () "Returns non-nil if the current location is inside a comment" (let (state) (setq state (parse-partial-sexp (point-min) (point))) (nth 4 state))) (defun smalltalk-forward-whitespace () "Skip white space and comments forward, stopping at end of buffer or non-white space, non-comment character" (while (looking-at (concat "[" smalltalk-whitespace "]")) (skip-chars-forward smalltalk-whitespace) (if (= (following-char) ?\") (forward-comment 1)))) ;; (defun smalltalk-forward-whitespace () ;; "Skip white space and comments forward, stopping at end of buffer ;; or non-white space, non-comment character" ;; (forward-comment 1) ;; (if (= (following-char) ?\n) ;; (forward-char))) (defun smalltalk-backward-whitespace () "Like forward whitespace only going towards the start of the buffer" (while (progn (skip-chars-backward smalltalk-whitespace) (= (preceding-char) ?\")) (search-backward "\"" nil t 2))) (defun smalltalk-current-column () "Returns the current column of the given line, regardless of narrowed buffer." (save-restriction (widen) (current-column))) ;this changed in 18.56 (defun smalltalk-current-indent () "Returns the indentation of the given line, regardless of narrowed buffer." (save-excursion (save-restriction (widen) (beginning-of-line) (skip-chars-forward " \t") (current-column)))) (defun smalltalk-find-statement-begin () "Leaves the point at the first non-blank, non-comment character of a new statement. If begininning of buffer is reached, then the point is left there. This routine only will return with the point pointing at the first non-blank on a line; it won't be fooled by multiple statements on a line into stopping prematurely. Also, goes to start of method if we started in the method selector." (let (start ch) (if (= (preceding-char) ?.) ;if we start at eos (backward-char 1)) ;we find the begin of THAT stmt (while (and (null start) (not (bobp))) (smalltalk-backward-whitespace) (cond ((= (setq ch (preceding-char)) ?.) (let (saved-point) (setq saved-point (point)) (smalltalk-forward-whitespace) (if (smalltalk-white-to-bolp) (setq start (point)) (goto-char saved-point) (smalltalk-backward-sexp 1)) )) ((= ch ?^) ;HACK -- presuming that when we back ;up into a return that we're at the ;start of a statement (backward-char 1) (setq start (point))) ((= ch ?!) (smalltalk-forward-whitespace) (setq start (point))) (t (smalltalk-backward-sexp 1)))) (if (null start) (progn (goto-char (point-min)) (smalltalk-forward-whitespace) (setq start (point)))) start)) (defun smalltalk-match-paren (state) "Answer the closest previous open paren. Actually, skips over any block parameters, and skips over the whitespace following on the same line." (let ((paren-addr (nth 1 state)) start c done) (if (not paren-addr) () (save-excursion (goto-char paren-addr) (setq c (following-char)) (cond ((or (eq c ?\() (eq c ?{)) (1+ (point))) ((eq c ?\[) (forward-char 1) ;; Now skip over the block parameters, if any (setq done nil) (while (not done) (skip-chars-forward " \t") (setq c (following-char)) (cond ((eq c ?:) (smalltalk-forward-sexp 1)) ((eq c ?|) (forward-char 1) ;skip vbar (skip-chars-forward " \t") (setq done t)) ;and leave (t (setq done t)))) ;; Now skip over the block temporaries, if any (cond ((eq (following-char) ?|) (setq done nil) (forward-char 1)) (t (setq done t))) (while (not done) (skip-chars-forward " \t") (setq c (following-char)) (cond ((eq c ?|) (forward-char 1) ;skip vbar (skip-chars-forward " \t") (setq done t)) ;and leave (t (smalltalk-forward-sexp 1)))) (point))))))) (defun smalltalk-parse-sexp-and-narrow-to-paren () "Narrows the region to between point and the closest previous open paren. Actually, skips over any block parameters, and skips over the whitespace following on the same line." (let* ((parse-sexp-ignore-comments t) (state (parse-partial-sexp (point-min) (point))) (start (smalltalk-match-paren state))) (if (null start) () (narrow-to-region start (point))) state)) (defun smalltalk-at-begin-of-scope () "Returns T if at the beginning of a class or namespace definition, otherwise nil" (save-excursion (end-of-line) (if (smalltalk-in-bang-syntax) (let ((parse-sexp-ignore-comments t)) (and (bolp) (progn (smalltalk-backward-whitespace) (= (preceding-char) ?!)))) (let ((curr-line-pos (line-number-at-pos))) (if (smalltalk-begin-of-scope) (= curr-line-pos (line-number-at-pos))))))) (defun smalltalk-at-begin-of-defun () "Returns T if at the beginning of a method definition, otherwise nil" (save-excursion (end-of-line) (if (smalltalk-in-bang-syntax) (let ((parse-sexp-ignore-comments t)) (and (bolp) (progn (smalltalk-backward-whitespace) (= (preceding-char) ?!)))) (let ((curr-line-pos (line-number-at-pos))) (if (smalltalk-begin-of-defun) (= curr-line-pos (line-number-at-pos))))))) (defun smalltalk-indent-for-colon () (let (indent-amount c start-line state done default-amount (parse-sexp-ignore-comments t)) ;; we're called only for lines which look like "foo:" (save-excursion (save-restriction (widen) (beginning-of-line) (smalltalk-end-of-paren) (smalltalk-narrow-to-method) (setq state (smalltalk-parse-sexp-and-narrow-to-paren)) (narrow-to-region (point-min) (point)) (setq start-line (point)) (smalltalk-backward-whitespace) (cond ((bobp) (setq indent-amount (smalltalk-toplevel-indent t))) ((eq (setq c (preceding-char)) ?\;) ; cascade before, treat as stmt continuation (smalltalk-find-statement-begin) (setq indent-amount (+ (smalltalk-current-column) smalltalk-indent-amount))) ((eq c ?.) ; stmt end, indent like it (syntax error here?) (smalltalk-find-statement-begin) (setq indent-amount (smalltalk-current-column))) (t ;could be a winner (smalltalk-find-statement-begin) ;; we know that since we weren't at bobp above after backing ;; up over white space, and we didn't run into a ., we aren't ;; at the beginning of a statement, so the default indentation ;; is one level from statement begin (setq default-amount (+ (smalltalk-current-column) ;just in case smalltalk-indent-amount)) ;; might be at the beginning of a method (the selector), decide ;; this here (if (not (looking-at smalltalk-keyword-regexp )) ;; not a method selector (while (and (not done) (not (eobp))) (smalltalk-forward-sexp 1) ;skip over receiver (smalltalk-forward-whitespace) (cond ((eq (following-char) ?\;) (setq done t) (setq indent-amount default-amount)) ((and (null indent-amount) ;pick up only first one (looking-at smalltalk-keyword-regexp)) (setq indent-amount (smalltalk-current-column)))))) (and (null indent-amount) (setq indent-amount default-amount)))))) (or indent-amount (smalltalk-current-indent)))) (defun smalltalk-end-of-paren () (let ((prev-point (point))) (smalltalk-safe-forward-sexp) (while (not (= (point) prev-point)) (setq prev-point (point)) (smalltalk-safe-forward-sexp)))) (defun smalltalk-indent-to-column (col) (if (/= col (smalltalk-current-indent)) (save-excursion (beginning-of-line) (delete-horizontal-space) (indent-to col))) (if (bolp) ;;delete horiz space may have moved us to bol instead of staying where ;; we were. this fixes it up. (move-to-column col))) (defun smalltalk-narrow-to-method () "Narrows the buffer to the contents of the method, exclusive of the method selector and temporaries." (let ((end (point)) (parse-sexp-ignore-comments t) done handled) (save-excursion (smalltalk-begin-of-defun) (if (looking-at "[a-zA-z]") ;either unary or keyword msg ;; or maybe an immediate expression... (progn (forward-sexp) (if (= (following-char) ?:) ;keyword selector (progn ;parse full keyword selector (backward-sexp 1) ;setup for common code (smalltalk-forward-keyword-selector)) ;; else maybe just a unary selector or maybe not ;; see if there's stuff following this guy on the same line (let (here eol-point) (setq here (point)) (end-of-line) (setq eol-point (point)) (goto-char here) (smalltalk-forward-whitespace) (if (< (point) eol-point) ;if there is, we're not a method ; (a heuristic guess) (beginning-of-line) (goto-char here))))) ;else we're a unary method (guess) ;; this must be a binary selector, or a temporary (if (= (following-char) ?|) (progn ;could be temporary (end-of-line) (smalltalk-backward-whitespace) (if (= (preceding-char) ?|) (progn (setq handled t))) (beginning-of-line))) (if (not handled) (progn (skip-chars-forward (concat "^" smalltalk-whitespace)) (smalltalk-forward-whitespace) (skip-chars-forward smalltalk-name-chars)))) ;skip over operand (if (not (smalltalk-in-bang-syntax)) (progn (skip-chars-forward "^[") (forward-char))) (smalltalk-forward-whitespace) ;;sbb 6-Sep-93 14:58:54 attempted fix(skip-chars-forward smalltalk-whitespace) (if (= (following-char) ?|) ;scan for temporaries (progn (forward-char) ;skip over | (smalltalk-forward-whitespace) (while (and (not (eobp)) (looking-at "[a-zA-Z_]")) (skip-chars-forward smalltalk-name-chars) (smalltalk-forward-whitespace) ) (if (and (= (following-char) ?|) ;only if a matching | as a temp (< (point) end)) ;and we're after the temps (narrow-to-region (1+ (point)) end))) ;do we limit the buffer ;; added "and <..." Dec 29 1991 as a test (and (< (point) end) (narrow-to-region (point) end)))))) (defun smalltalk-forward-keyword-selector () "Starting on a keyword, this function skips forward over a keyword selector. It is typically used to skip over the actual selector for a method." (let (done) (while (not done) (if (not (looking-at "[a-zA-Z_]")) (setq done t) (skip-chars-forward smalltalk-name-chars) (if (= (following-char) ?:) (progn (forward-char) (smalltalk-forward-sexp 1) (smalltalk-forward-whitespace)) (setq done t) (backward-sexp 1)))))) (defun smalltalk-white-to-bolp () "Returns T if from the current position to beginning of line is whitespace. Whitespace is defined as spaces, tabs, and comments." (let (done is-white line-start-pos) (save-excursion (save-excursion (beginning-of-line) (setq line-start-pos (point))) (while (not done) (and (not (bolp)) (skip-chars-backward " \t")) (cond ((bolp) (setq done t) (setq is-white t)) ((= (char-after (1- (point))) ?\") (backward-sexp) (if (< (point) line-start-pos) ;comment is multi line (setq done t))) (t (setq done t)))) is-white))) (defun smalltalk-backward-comment () (search-backward "\"") ;find its start (while (= (preceding-char) ?\") ;skip over doubled ones (backward-char 1) (search-backward "\""))) (defun smalltalk-current-class () (let ((here (point)) curr-hit-point curr-hit new-hit-point new-hit) (save-excursion (if (setq curr-hit-point (search-backward-regexp "^![ \t]*\\(\\(\\w+\\.\\)*\\w+\\)[ \t]+" nil t)) (setq curr-hit (buffer-substring (match-beginning 1) (match-end 1))))) (save-excursion (if (setq new-hit-point (search-backward-regexp "^[ \t]*\\(\\w+\\)[ \t]+class[ \t]+\\[" nil t)) (setq new-hit (buffer-substring (match-beginning 1) (match-end 1))))) (if (and new-hit-point (or (not curr-hit-point) (> new-hit-point curr-hit-point)) (smalltalk-in-class-scope-of here new-hit-point)) (progn (setq curr-hit-point new-hit-point) (setq curr-hit new-hit))) (save-excursion (if (setq new-hit-point (search-backward-regexp "^[ \t]*\\(\\(\\w+\\.\\)*\\w+\\)[ \t]+extend[ \t]+\\[" nil t)) (setq new-hit (buffer-substring (match-beginning 1) (match-end 1))))) (if (and new-hit-point (or (not curr-hit-point) (> new-hit-point curr-hit-point))) (progn (setq curr-hit-point new-hit-point) (setq curr-hit new-hit))) (save-excursion (if (setq new-hit-point (search-backward-regexp "^[ \t]*\\(\\w+\\.\\)*\\w+[ \t]+\\(variable\\|variableWord\\|variableByte\\)?subclass:[ \t]+#?\\(\\w+\\)" nil t)) (setq new-hit (buffer-substring (match-beginning 3) (match-end 3))))) (if (and new-hit-point (or (not curr-hit-point) (> new-hit-point curr-hit-point))) (progn (setq curr-hit-point new-hit-point) (setq curr-hit new-hit))) (cons curr-hit curr-hit-point))) (defun smalltalk-current-scope-point () (defun smalltalk-update-hit-point (current search) (save-excursion (let ((new-hit-point (funcall search))) (if (and new-hit-point (or (not current) (> new-hit-point current))) new-hit-point current)))) (let ((curr-hit-point (smalltalk-current-class-point))) (setq curr-hit-point (smalltalk-update-hit-point curr-hit-point #'(lambda ()(search-backward-regexp "^[ \t]*Eval[ \t]+\\[" nil t)))) (setq curr-hit-point (smalltalk-update-hit-point curr-hit-point #'(lambda ()(search-backward-regexp "^[ \t]*Namespace[ \t]+current:[ \t]+[A-Za-z0-9_.]+[ \t]+\\[" nil t)))) curr-hit-point)) (defun smalltalk-current-class-point () (cdr (smalltalk-current-class))) (defun smalltalk-current-class-name () (car (smalltalk-current-class))) (defun smalltalk-in-bang-syntax () (let ((curr-hit-point (smalltalk-current-class-point))) (and curr-hit-point (save-excursion (goto-char curr-hit-point) (beginning-of-line) (looking-at "!"))))) (defun smalltalk-in-class-scope-of (orig curr-hit-point) (save-excursion (goto-char curr-hit-point) (skip-chars-forward " \t") (skip-chars-forward smalltalk-name-chars) (skip-chars-forward " \t") (and (= (following-char) ?c) ;; check if the class scope ends after the point (condition-case nil (progn (skip-chars-forward "^[") (forward-sexp 1) (> (point) orig)) (error t))))) (defun smalltalk-in-class-scope () (let ((curr-hit-point (smalltalk-current-class-point))) (and curr-hit-point (smalltalk-in-class-scope-of (point) curr-hit-point)))) (defun smalltalk-exit-class-scope () (interactive) (if (smalltalk-in-class-scope) (progn (smalltalk-begin-of-scope) (skip-chars-forward "^[") (smalltalk-end-of-defun)))) (defun smalltalk-find-message () (save-excursion (smalltalk-goto-beginning-of-statement) (cond ((smalltalk-looking-at-unary-send) (if (not (smalltalk-has-sender)) (progn (smalltalk-safe-forward-sexp) (smalltalk-safe-forward-sexp) (smalltalk-find-message)) (buffer-substring-no-properties (point) (progn (smalltalk-safe-forward-sexp)(point))))) ((smalltalk-looking-at-keyword-send) (concat (smalltalk-find-beginning-of-keyword-send) (smalltalk-find-end-of-keyword-send)))))) (defun smalltalk-safe-backward-sexp () (let (prev-point) (condition-case nil (progn (setq prev-point (point)) (smalltalk-backward-sexp 1)) (error (goto-char prev-point))))) (defun smalltalk-safe-forward-sexp () (let (prev-point) (condition-case nil (progn (setq prev-point (point)) (smalltalk-forward-sexp 1)) (error (goto-char prev-point))))) (defun smalltalk-goto-beginning-of-statement () (if (not (looking-back "[ \t\n]")) (smalltalk-safe-backward-sexp))) (defun smalltalk-has-sender () (save-excursion (smalltalk-backward-whitespace) (looking-back "[]})A-Za-z0-9']"))) (defun smalltalk-looking-at-binary-send () (looking-at "[^]A-Za-z0-9:_(){}[;.\'\"]+[ \t\n]")) (defun smalltalk-looking-at-unary-send () (looking-at "[A-Za-z][A-Za-z0-9]*[ \t\n]")) (defun smalltalk-looking-at-keyword-send () (looking-at "[A-Za-z][A-Za-z0-9_]*:")) (defun smalltalk-looking-back-keyword-send () (looking-back "[A-z][A-z0-9_]*:")) (defun smalltalk-find-end-of-keyword-send () (save-excursion (smalltalk-forward-whitespace) (if (or (looking-at "[.;]") (= (smalltalk-next-keyword) (point))) "" (progn (smalltalk-goto-next-keyword) (concat (buffer-substring-no-properties (save-excursion (progn (smalltalk-safe-backward-sexp) (point))) (point)) (smalltalk-find-end-of-keyword-send)))))) (defun smalltalk-find-beginning-of-keyword-send () (save-excursion (let ((begin-of-defun (smalltalk-at-begin-of-defun))) (smalltalk-backward-whitespace) (if (or (if begin-of-defun (looking-back "[].;]") (looking-back "[.;]")) (= (smalltalk-previous-keyword) (point))) "" (progn (smalltalk-goto-previous-keyword) (concat (smalltalk-find-beginning-of-keyword-send) (buffer-substring-no-properties (point) (progn (smalltalk-safe-forward-sexp)(+ (point) 1))))))))) (defun smalltalk-goto-previous-keyword () "Go to the previous keyword of the current message send" (goto-char (smalltalk-previous-keyword))) (defun smalltalk-goto-next-keyword () "Go to the next keyword of the current message send" (goto-char (smalltalk-next-keyword))) (defun smalltalk-previous-keyword-1 () (smalltalk-backward-whitespace) (if (looking-back "[>[({.^]") ;; not really ok when > is sent in a keyword arg nil (if (= (point) (save-excursion (smalltalk-safe-backward-sexp) (point))) nil (progn (smalltalk-safe-backward-sexp) (if (smalltalk-looking-at-keyword-send) (point) (smalltalk-previous-keyword-1)))))) (defun smalltalk-next-keyword-1 () (smalltalk-forward-whitespace) (if (looking-at "[])};.]") nil (if (= (point) (save-excursion (smalltalk-safe-forward-sexp) (point))) nil (progn (smalltalk-safe-forward-sexp) (skip-chars-forward ":") (if (smalltalk-looking-back-keyword-send) (point) (smalltalk-next-keyword-1)))))) (defun smalltalk-previous-keyword () (or (save-excursion (smalltalk-previous-keyword-1)) (point))) (defun smalltalk-next-keyword () (or (save-excursion (smalltalk-next-keyword-1)) (point))) (provide 'smalltalk-mode) smalltalk-3.2.5/superops/0000755000175000017500000000000012130456002012357 500000000000000smalltalk-3.2.5/superops/vm_def.h0000644000175000017500000000307312123404352013716 00000000000000/////////////////////////////// -*- C++ -*- /////////////////////////// // // Program to extract superoperators from a GNU Smalltalk image. // vm.def creation header. // /////////////////////////////////////////////////////////////////////// /////////////////////////////////////////////////////////////////////// // // Copyright 2003 Free Software Foundation, Inc. // Written by Paolo Bonzini. // // This file is part of GNU Smalltalk. // // GNU Smalltalk is free software; you can redistribute it and/or modify it // under the terms of the GNU General Public License as published by the Free // Software Foundation; either version 2, or (at your option) any later // version. // // GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT // ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or // FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for // more details. // // You should have received a copy of the GNU General Public License along with // GNU Smalltalk; see the file COPYING. If not, write to the Free Software // Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. // /////////////////////////////////////////////////////////////////////// #ifndef SUPEROPS_VM_DEF_H #define SUPEROPS_VM_DEF_H #include "observer-list.h" #include class vm_def_builder : public observer { public: std::ofstream fs; vm_def_builder (); ~vm_def_builder (); void with_fixed_arg_1 (int new_bc, int bc1, int arg, int bc2); void with_fixed_arg_2 (int new_bc, int bc1, int bc2, int arg); }; #endif smalltalk-3.2.5/superops/bool-array.cc0000644000175000017500000000305212123404352014660 00000000000000/* Fast lookup table abstraction implemented as an Iteration Number Array Copyright (C) 1989-1998, 2002 Free Software Foundation, Inc. Written by Douglas C. Schmidt and Bruno Haible . This file is part of GNU GPERF. GNU GPERF is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2, or (at your option) any later version. GNU GPERF is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; see the file COPYING. If not, write to the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. */ /* Specification. */ #include "bool-array.h" #include #include #include "options.h" /* Frees this object. */ Bool_Array::~Bool_Array () { /* Print out debugging diagnostics. */ if (option[DEBUG]) fprintf (stderr, "\ndumping boolean array information\n" "size = %d\niteration number = %d\nend of array dump\n", _size, _iteration_number); delete[] const_cast(_storage_array); } #ifndef __OPTIMIZE__ #define INLINE /* not inline */ #include "bool-array.icc" #undef INLINE #endif /* not defined __OPTIMIZE__ */ smalltalk-3.2.5/superops/table.cc0000644000175000017500000000461412123404352013705 00000000000000/////////////////////////////// -*- C++ -*- /////////////////////////// // // Program to extract superoperators from a GNU Smalltalk image. // Table creation routines for CompildCode.st. // /////////////////////////////////////////////////////////////////////// /////////////////////////////////////////////////////////////////////// // // Copyright 2003, 2007 Free Software Foundation, Inc. // Written by Paolo Bonzini. // // This file is part of GNU Smalltalk. // // GNU Smalltalk is free software; you can redistribute it and/or modify it // under the terms of the GNU General Public License as published by the Free // Software Foundation; either version 2, or (at your option) any later // version. // // GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT // ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or // FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for // more details. // // You should have received a copy of the GNU General Public License along with // GNU Smalltalk; see the file COPYING. If not, write to the Free Software // Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. // /////////////////////////////////////////////////////////////////////// #if defined __GNUC__ && __GNUC__ < 3 #error Sorry, you need a recent C++ compiler to compile this program. #endif #include "table.h" #include #include #include superop_table_builder::superop_table_builder () : fs ("table.st") { fs << "\"Automatically generated by superops. Do not modify this definition!\"" << std::endl; memset (table, 0, sizeof (table)); table[54*4+3] = 128; } superop_table_builder::~superop_table_builder () { std::cout << "Smalltalk description (for CompildCode.st) written to table.st." << std::endl; fs << "#["; for (int i = 0; i < 1024; i++) fs << (i & 31 ? " " : "\n ") << table[i]; fs << " ]"; } void superop_table_builder::with_fixed_arg_1 (int new_bc, int bc1, int arg, int bc2) { table[new_bc*4] = bc1; table[new_bc*4+1] = bc2; table[new_bc*4+2] = arg; table[new_bc*4+3] = ((table[bc1*4+3] | table[bc2*4+3]) & 128); } void superop_table_builder::with_fixed_arg_2 (int new_bc, int bc1, int bc2, int arg) { table[new_bc*4] = bc1; table[new_bc*4+1] = bc2; table[new_bc*4+2] = arg; table[new_bc*4+3] = ((table[bc1*4+3] | table[bc2*4+3]) & 128) + 1; } smalltalk-3.2.5/superops/keyword-list.icc0000644000175000017500000000304012123404352015414 00000000000000/* Inline Functions for keyword-list.{h,cc}. Copyright (C) 2002-2003 Free Software Foundation, Inc. Written by Bruno Haible . This file is part of GNU GPERF. GNU GPERF is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2, or (at your option) any later version. GNU GPERF is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; see the file COPYING. If not, write to the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. */ /* -------------------------- Keyword_List class --------------------------- */ /* Access to first element of list. */ INLINE Keyword * Keyword_List::first () const { return _car; } /* Access to next element of list. */ INLINE Keyword_List *& Keyword_List::rest () { return _cdr; } /* ------------------------- KeywordExt_List class ------------------------- */ /* Access to first element of list. */ INLINE KeywordExt * KeywordExt_List::first () const { return static_cast(_car); } /* Access to next element of list. */ INLINE KeywordExt_List *& KeywordExt_List::rest () { return *reinterpret_cast(&_cdr); } smalltalk-3.2.5/superops/hash.h0000644000175000017500000000336512123404352013405 00000000000000/////////////////////////////// -*- C++ -*- /////////////////////////// // // Program to extract superoperators from a GNU Smalltalk image. // Hash table creation header. // /////////////////////////////////////////////////////////////////////// /////////////////////////////////////////////////////////////////////// // // Copyright 2003 Free Software Foundation, Inc. // Written by Paolo Bonzini. // // This file is part of GNU Smalltalk. // // GNU Smalltalk is free software; you can redistribute it and/or modify it // under the terms of the GNU General Public License as published by the Free // Software Foundation; either version 2, or (at your option) any later // version. // // GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT // ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or // FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for // more details. // // You should have received a copy of the GNU General Public License along with // GNU Smalltalk; see the file COPYING. If not, write to the Free Software // Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. // /////////////////////////////////////////////////////////////////////// #ifndef SUPEROPS_HASH_H #define SUPEROPS_HASH_H #include "observer-list.h" class KeywordExt_List; class Positions; class hash_builder : public observer_list { KeywordExt_List* list1; KeywordExt_List* list2; void output1 (); void output2 (); void search (Positions &p, KeywordExt_List *list, const char *type, const char *file); public: hash_builder (); void with_fixed_arg_1 (int new_bc, int bc1, int arg, int bc2); void with_fixed_arg_2 (int new_bc, int bc1, int bc2, int arg); void output (); }; #endif smalltalk-3.2.5/superops/hash-table.cc0000644000175000017500000001277012123404352014630 00000000000000/* Hash table for checking keyword links. Implemented using double hashing. Copyright (C) 1989-1998, 2000, 2002 Free Software Foundation, Inc. Written by Douglas C. Schmidt and Bruno Haible . This file is part of GNU GPERF. GNU GPERF is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2, or (at your option) any later version. GNU GPERF is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; see the file COPYING. If not, write to the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. */ /* Specification. */ #include "hash-table.h" #include #include /* declares memset(), strcmp() */ #include "options.h" /* We use a hash table with double hashing. This is the simplest kind of hash table, given that we always only insert and never remove entries from the hash table. */ /* To make double hashing efficient, there need to be enough spare entries. */ static const int size_factor = 10; /* a hash function for char[] arrays using the method described in Aho, Sethi, & Ullman, p 436. */ static unsigned int hashpjw (const unsigned char *string, unsigned int len); /* We make the size of the hash table a power of 2. This allows for two optimizations: It eliminates the modulo instruction, and allows for an easy secondary hashing function. */ /* Constructor. */ Hash_Table::Hash_Table (unsigned int size, bool ignore_length) : _ignore_length (ignore_length), _collisions (0) { /* There need to be enough spare entries. */ size = size * size_factor; /* Find smallest power of 2 that is >= size. */ unsigned int shift = 0; if ((size >> 16) > 0) { size = size >> 16; shift += 16; } if ((size >> 8) > 0) { size = size >> 8; shift += 8; } if ((size >> 4) > 0) { size = size >> 4; shift += 4; } if ((size >> 2) > 0) { size = size >> 2; shift += 2; } if ((size >> 1) > 0) { size = size >> 1; shift += 1; } _log_size = shift; _size = 1 << shift; /* Allocate table. */ _table = new KeywordExt*[_size]; memset (_table, 0, _size * sizeof (*_table)); } /* Destructor. */ Hash_Table::~Hash_Table () { delete[] _table; } /* Print the table's contents. */ void Hash_Table::dump () const { int field_width; field_width = 0; { for (int i = _size - 1; i >= 0; i--) if (_table[i]) if (field_width < _table[i]->_selchars_length) field_width = _table[i]->_selchars_length; } fprintf (stderr, "\ndumping the hash table\n" "total available table slots = %d, total bytes = %d, total collisions = %d\n" "location, %*s, keyword\n", _size, _size * static_cast(sizeof (*_table)), _collisions, field_width, "keysig"); for (int i = _size - 1; i >= 0; i--) if (_table[i]) { fprintf (stderr, "%8d, ", i); if (field_width > _table[i]->_selchars_length) fprintf (stderr, "%*s", field_width - _table[i]->_selchars_length, ""); for (int j = 0; j < _table[i]->_selchars_length; j++) putc (_table[i]->_selchars[j], stderr); fprintf (stderr, ", %.*s\n", _table[i]->_allchars_length, _table[i]->_allchars); } fprintf (stderr, "\nend dumping hash table\n\n"); } /* Compares two items. */ inline bool Hash_Table::equal (KeywordExt *item1, KeywordExt *item2) const { return item1->_selchars_length == item2->_selchars_length && memcmp (item1->_selchars, item2->_selchars, item2->_selchars_length * sizeof (unsigned int)) == 0 && (_ignore_length || item1->_allchars_length == item2->_allchars_length); } /* Attempts to insert ITEM in the table. If there is already an equal entry in it, returns it. Otherwise inserts ITEM and returns NULL. */ KeywordExt * Hash_Table::insert (KeywordExt *item) { unsigned hash_val = hashpjw (reinterpret_cast(item->_selchars), item->_selchars_length * sizeof (unsigned int)); unsigned int probe = hash_val & (_size - 1); unsigned int increment = (((hash_val >> _log_size) ^ (_ignore_length ? 0 : item->_allchars_length)) << 1) + 1; /* Note that because _size is a power of 2 and increment is odd, we have gcd(increment,_size) = 1, which guarantees that we'll find an empty entry during the loop. */ while (_table[probe] != NULL) { if (equal (_table[probe], item)) return _table[probe]; _collisions++; probe = (probe + increment) & (_size - 1); } _table[probe] = item; return NULL; } /* Some useful hash function. It's not a particularly good hash function (<< 5 would be better than << 4), but people believe in it because it comes from Dragon book. */ unsigned int hashpjw (const unsigned char *x, unsigned int len) // From Dragon book, p436 { unsigned int h = 0; unsigned int g; for (; len > 0; len--) { h = (h << 4) + *x++; if ((g = h & 0xf0000000) != 0) h = (h ^ (g >> 24)) ^ g; } return h; } smalltalk-3.2.5/superops/bool-array.icc0000644000175000017500000000467412123404352015044 00000000000000/* Inline Functions for bool-array.{h,cc}. Copyright (C) 1989-1998, 2002 Free Software Foundation, Inc. Written by Douglas C. Schmidt and Bruno Haible . This file is part of GNU GPERF. GNU GPERF is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2, or (at your option) any later version. GNU GPERF is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; see the file COPYING. If not, write to the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. */ // This needs: //#include //#include //#include "options.h" /* Initializes the bit array with room for SIZE bits, numbered from 0 to SIZE-1. */ INLINE Bool_Array::Bool_Array (unsigned int size) : _size (size), _iteration_number (1), _storage_array (new unsigned int [size]) { memset (_storage_array, 0, size * sizeof (_storage_array[0])); if (option[DEBUG]) fprintf (stderr, "\nbool array size = %d, total bytes = %d\n", _size, static_cast (_size * sizeof (_storage_array[0]))); } /* Sets the specified bit to true. Returns its previous value (false or true). */ INLINE bool Bool_Array::set_bit (unsigned int index) { if (_storage_array[index] == _iteration_number) /* The bit was set since the last clear() call. */ return true; else { /* The last operation on this bit was clear(). Set it now. */ _storage_array[index] = _iteration_number; return false; } } /* Resets all bits to zero. */ INLINE void Bool_Array::clear () { /* If we wrap around it's time to zero things out again! However, this only occurs once about every 2^32 iterations, so it will not happen more frequently than once per second. */ if (++_iteration_number == 0) { _iteration_number = 1; memset (_storage_array, 0, _size * sizeof (_storage_array[0])); if (option[DEBUG]) { fprintf (stderr, "(re-initialized bool_array)\n"); fflush (stderr); } } } smalltalk-3.2.5/superops/positions.h0000644000175000017500000001331212123404352014502 00000000000000/* This may look like C code, but it is really -*- C++ -*- */ /* A set of byte positions. Copyright (C) 1989-1998, 2000, 2002 Free Software Foundation, Inc. Written by Douglas C. Schmidt and Bruno Haible . This file is part of GNU GPERF. GNU GPERF is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2, or (at your option) any later version. GNU GPERF is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; see the file COPYING. If not, write to the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. */ #ifndef positions_h #define positions_h 1 class PositionIterator; class PositionReverseIterator; /* This class denotes a set of byte positions, used to access a keyword. */ class Positions { friend class PositionIterator; friend class PositionReverseIterator; public: /* Denotes the last char of a keyword, depending on the keyword's length. */ enum { LASTCHAR = -1 }; /* Maximum key position specifiable by the user, 1-based. Note that MAX_KEY_POS-1 must fit into the element type of _positions[], below. */ enum { MAX_KEY_POS = 255 }; /* Maximum possible size. Since duplicates are eliminated and the possible 0-based positions are -1 .. MAX_KEY_POS-1, this is: */ enum { MAX_SIZE = MAX_KEY_POS + 1 }; /* Constructors. */ Positions (); Positions (int pos1); Positions (int pos1, int pos2); /* Copy constructor. */ Positions (const Positions& src); /* Assignment operator. */ Positions& operator= (const Positions& src); /* Accessors. */ bool is_useall () const; int operator[] (unsigned int index) const; unsigned int get_size () const; /* Write access. */ void set_useall (bool useall); int * pointer (); void set_size (unsigned int size); /* Sorts the array in reverse order. Returns true if there are no duplicates, false otherwise. */ bool sort (); /* Creates an iterator, returning the positions in descending order. */ PositionIterator iterator () const; /* Creates an iterator, returning the positions in descending order, that apply to strings of length <= maxlen. */ PositionIterator iterator (int maxlen) const; /* Creates an iterator, returning the positions in ascending order. */ PositionReverseIterator reviterator () const; /* Creates an iterator, returning the positions in ascending order, that apply to strings of length <= maxlen. */ PositionReverseIterator reviterator (int maxlen) const; /* Set operations. Assumes the array is in reverse order. */ bool contains (int pos) const; void add (int pos); void remove (int pos); /* Output in external syntax. */ void print () const; private: /* The special case denoted by '*'. */ bool _useall; /* Number of positions. */ unsigned int _size; /* Array of positions. 0 for the first char, 1 for the second char etc., LASTCHAR for the last char. */ int _positions[MAX_SIZE]; }; /* This class denotes an iterator through a set of byte positions. */ class PositionIterator { friend class Positions; public: /* Copy constructor. */ PositionIterator (const PositionIterator& src); /* End of iteration marker. */ enum { EOS = -2 }; /* Retrieves the next position, or EOS past the end. */ int next (); /* Returns the number of remaining positions, i.e. how often next() will return a value != EOS. */ unsigned int remaining () const; private: /* Initializes an iterator through POSITIONS. */ PositionIterator (Positions const& positions); /* Initializes an iterator through POSITIONS, ignoring positions >= maxlen. */ PositionIterator (Positions const& positions, int maxlen); const Positions& _set; unsigned int _index; }; /* This class denotes an iterator in reverse direction through a set of byte positions. */ class PositionReverseIterator { friend class Positions; public: /* Copy constructor. */ PositionReverseIterator (const PositionReverseIterator& src); /* End of iteration marker. */ enum { EOS = -2 }; /* Retrieves the next position, or EOS past the end. */ int next (); /* Returns the number of remaining positions, i.e. how often next() will return a value != EOS. */ unsigned int remaining () const; private: /* Initializes an iterator through POSITIONS. */ PositionReverseIterator (Positions const& positions); /* Initializes an iterator through POSITIONS, ignoring positions >= maxlen. */ PositionReverseIterator (Positions const& positions, int maxlen); const Positions& _set; unsigned int _index; unsigned int _minindex; }; #ifdef __OPTIMIZE__ #include #define INLINE inline #include "positions.icc" #undef INLINE #endif #endif smalltalk-3.2.5/superops/keyword-list.cc0000644000175000017500000001116712123404352015254 00000000000000/* Keyword list. Copyright (C) 2002 Free Software Foundation, Inc. Written by Bruno Haible . This file is part of GNU GPERF. GNU GPERF is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2, or (at your option) any later version. GNU GPERF is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; see the file COPYING. If not, write to the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. */ /* Specification. */ #include "keyword-list.h" #include /* -------------------------- Keyword_List class --------------------------- */ /* Constructor. */ Keyword_List::Keyword_List (Keyword *car) : _cdr (NULL), _car (car) { } /* ------------------------- KeywordExt_List class ------------------------- */ /* Constructor. */ KeywordExt_List::KeywordExt_List (KeywordExt *car) : Keyword_List (car) { } /* ------------------------ Keyword_List functions ------------------------- */ /* Copies a linear list, sharing the list elements. */ Keyword_List * copy_list (Keyword_List *list) { Keyword_List *result; Keyword_List **lastp = &result; while (list != NULL) { Keyword_List *new_cons = new Keyword_List (list->first()); *lastp = new_cons; lastp = &new_cons->rest(); list = list->rest(); } *lastp = NULL; return result; } /* Copies a linear list, sharing the list elements. */ KeywordExt_List * copy_list (KeywordExt_List *list) { return static_cast (copy_list (static_cast (list))); } /* Deletes a linear list, keeping the list elements in memory. */ void delete_list (Keyword_List *list) { while (list != NULL) { Keyword_List *rest = list->rest(); delete list; list = rest; } } /* Type of a comparison function. */ typedef bool (*Keyword_Comparison) (Keyword *keyword1, Keyword *keyword2); /* Merges two sorted lists together to form one sorted list. */ static Keyword_List * merge (Keyword_List *list1, Keyword_List *list2, Keyword_Comparison less) { Keyword_List *result; Keyword_List **resultp = &result; for (;;) { if (!list1) { *resultp = list2; break; } if (!list2) { *resultp = list1; break; } if (less (list2->first(), list1->first())) { *resultp = list2; resultp = &list2->rest(); /* We would have a stable sorting if the next line would read: list2 = *resultp; */ list2 = list1; list1 = *resultp; } else { *resultp = list1; resultp = &list1->rest(); list1 = *resultp; } } return result; } /* Sorts a linear list, given a comparison function. Note: This uses a variant of mergesort that is *not* a stable sorting algorithm. */ Keyword_List * mergesort_list (Keyword_List *list, Keyword_Comparison less) { if (list == NULL || list->rest() == NULL) /* List of length 0 or 1. Nothing to do. */ return list; else { /* Determine a list node in the middle. */ Keyword_List *middle = list; for (Keyword_List *temp = list->rest();;) { temp = temp->rest(); if (temp == NULL) break; temp = temp->rest(); middle = middle->rest(); if (temp == NULL) break; } /* Cut the list into two halves. If the list has n elements, the left half has ceiling(n/2) elements and the right half has floor(n/2) elements. */ Keyword_List *right_half = middle->rest(); middle->rest() = NULL; /* Sort the two halves, then merge them. */ return merge (mergesort_list (list, less), mergesort_list (right_half, less), less); } } KeywordExt_List * mergesort_list (KeywordExt_List *list, bool (*less) (KeywordExt *keyword1, KeywordExt *keyword2)) { return static_cast (mergesort_list (static_cast (list), reinterpret_cast (less))); } #ifndef __OPTIMIZE__ #define INLINE /* not inline */ #include "keyword-list.icc" #undef INLINE #endif /* not defined __OPTIMIZE__ */ smalltalk-3.2.5/superops/keyword.h0000644000175000017500000001002312123404352014133 00000000000000/* This may look like C code, but it is really -*- C++ -*- */ /* Keyword data. Copyright (C) 1989-1998, 2000, 2002 Free Software Foundation, Inc. Written by Douglas C. Schmidt and Bruno Haible . This file is part of GNU GPERF. GNU GPERF is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2, or (at your option) any later version. GNU GPERF is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; see the file COPYING. If not, write to the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. */ #ifndef keyword_h #define keyword_h 1 /* Class defined in "positions.h". */ class Positions; /* An instance of this class is a keyword, as specified in the input file. */ struct Keyword { /* Constructor. */ Keyword (const char *allchars, int allchars_length, const char *rest); /* Data members defined immediately by the input file. */ /* The keyword as a string, possibly containing NUL bytes. */ const char *const _allchars; int const _allchars_length; /* Additional stuff seen on the same line of the input file. */ const char *const _rest; /* Line number of this keyword in the input file. */ unsigned int _lineno; }; /* A keyword, in the context of a given keyposition list. */ struct KeywordExt : public Keyword { /* Constructor. */ KeywordExt (const char *allchars, int allchars_length, const char *rest); /* Data members depending on the keyposition list. */ /* The selected characters that participate for the hash function, selected according to the keyposition list, as a canonically reordered multiset. */ const unsigned int * _selchars; int _selchars_length; /* Chained list of keywords having the same _selchars and - if !option[NOLENGTH] - also the same _allchars_length. Note that these duplicates are not members of the main keyword list. */ KeywordExt * _duplicate_link; /* Methods depending on the keyposition list. */ /* Initializes selchars and selchars_length, without reordering. */ void init_selchars_tuple (const Positions& positions, const unsigned int *alpha_unify); /* Initializes selchars and selchars_length, with reordering. */ void init_selchars_multiset (const Positions& positions, const unsigned int *alpha_unify, const unsigned int *alpha_inc); /* Deletes selchars. */ void delete_selchars (); /* Data members used by the algorithm. */ int _hash_value; /* Hash value for the keyword. */ /* Data members used by the output routines. */ int _final_index; private: unsigned int * init_selchars_low (const Positions& positions, const unsigned int *alpha_unify, const unsigned int *alpha_inc); }; /* An abstract factory for creating Keyword instances. This factory is used to make the Input class independent of the concrete class KeywordExt. */ class Keyword_Factory { public: /* Constructor. */ Keyword_Factory (); /* Destructor. */ virtual ~Keyword_Factory (); /* Creates a new Keyword. */ virtual /*abstract*/ Keyword * create_keyword (const char *allchars, int allchars_length, const char *rest) = 0; }; /* A statically allocated empty string. */ extern char empty_string[1]; #ifdef __OPTIMIZE__ #define INLINE inline #include "keyword.icc" #undef INLINE #endif #endif smalltalk-3.2.5/superops/keyword-list.h0000644000175000017500000000520412123404352015111 00000000000000/* This may look like C code, but it is really -*- C++ -*- */ /* Keyword list. Copyright (C) 2002 Free Software Foundation, Inc. Written by Bruno Haible . This file is part of GNU GPERF. GNU GPERF is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2, or (at your option) any later version. GNU GPERF is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; see the file COPYING. If not, write to the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. */ #ifndef keyword_list_h #define keyword_list_h 1 #include "keyword.h" /* List node of a linear list of Keyword. */ class Keyword_List { public: /* Constructor. */ Keyword_List (Keyword *car); /* Access to first element of list. */ Keyword * first () const; /* Access to next element of list. */ Keyword_List *& rest (); protected: Keyword_List * _cdr; Keyword * const _car; }; /* List node of a linear list of KeywordExt. */ class KeywordExt_List : public Keyword_List { public: /* Constructor. */ KeywordExt_List (KeywordExt *car); /* Access to first element of list. */ KeywordExt * first () const; /* Access to next element of list. */ KeywordExt_List *& rest (); }; /* Copies a linear list, sharing the list elements. */ extern Keyword_List * copy_list (Keyword_List *list); extern KeywordExt_List * copy_list (KeywordExt_List *list); /* Deletes a linear list, keeping the list elements in memory. */ extern void delete_list (Keyword_List *list); /* Sorts a linear list, given a comparison function. Note: This uses a variant of mergesort that is *not* a stable sorting algorithm. */ extern Keyword_List * mergesort_list (Keyword_List *list, bool (*less) (Keyword *keyword1, Keyword *keyword2)); extern KeywordExt_List * mergesort_list (KeywordExt_List *list, bool (*less) (KeywordExt *keyword1, KeywordExt *keyword2)); #ifdef __OPTIMIZE__ #define INLINE inline #include "keyword-list.icc" #undef INLINE #endif #endif smalltalk-3.2.5/superops/bool-array.h0000644000175000017500000000505112123404352014523 00000000000000/* This may look like C code, but it is really -*- C++ -*- */ /* Simple lookup table abstraction implemented as an Iteration Number Array. Copyright (C) 1989-1998, 2002 Free Software Foundation, Inc. Written by Douglas C. Schmidt and Bruno Haible . This file is part of GNU GPERF. GNU GPERF is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2, or (at your option) any later version. GNU GPERF is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; see the file COPYING. If not, write to the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. */ #ifndef bool_array_h #define bool_array_h 1 /* A Bool_Array instance is a bit array of fixed size, optimized for being filled sparsely and cleared frequently. For example, when processing tests/chill.gperf, the array will be: - of size 15391, - clear will be called 3509 times, - set_bit will be called 300394 times. With a conventional bit array implementation, clear would be too slow. With a tree/hash based bit array implementation, set_bit would be slower. */ class Bool_Array { public: /* Initializes the bit array with room for SIZE bits, numbered from 0 to SIZE-1. */ Bool_Array (unsigned int size); /* Frees this object. */ ~Bool_Array (); /* Resets all bits to zero. */ void clear (); /* Sets the specified bit to true. Returns its previous value (false or true). */ bool set_bit (unsigned int index); private: /* Size of array. */ unsigned int const _size; /* Current iteration number. Always nonzero. Starts out as 1, and is incremented each time clear() is called. */ unsigned int _iteration_number; /* For each index, we store in storage_array[index] the iteration_number at the time set_bit(index) was last called. */ unsigned int * const _storage_array; }; #ifdef __OPTIMIZE__ /* efficiency hack! */ #include #include #include "options.h" #define INLINE inline #include "bool-array.icc" #undef INLINE #endif #endif smalltalk-3.2.5/superops/options.h0000644000175000017500000000715012123404352014151 00000000000000/* This may look like C code, but it is really -*- C++ -*- */ /* Handles parsing the Options provided to the user. Copyright (C) 1989-1998, 2000, 2002-2003 Free Software Foundation, Inc. Written by Douglas C. Schmidt and Bruno Haible . This file is part of GNU GPERF. GNU GPERF is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2, or (at your option) any later version. GNU GPERF is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; see the file COPYING. If not, write to the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. */ /* This module provides a uniform interface to the various options available to a user of the gperf hash function generator. */ #ifndef options_h #define options_h 1 #include #include "positions.h" /* Enumeration of the possible boolean options. */ enum Option_Type { /* --- Input file interpretation --- */ /* Ignore case of ASCII characters. */ UPPERLOWER = 1 << 1, /* --- Details in the output code --- */ /* Assume 7-bit, not 8-bit, characters. */ SEVENBIT = 1 << 6, /* --- Algorithm employed by gperf --- */ /* Use the given key positions. */ POSITIONS = 1 << 17, /* Handle duplicate hash values for keywords. */ DUP = 1 << 18, /* Don't include keyword length in hash computations. */ NOLENGTH = 1 << 19, /* Randomly initialize the associated values table. */ RANDOM = 1 << 20, /* --- Informative output --- */ /* Enable debugging (prints diagnostics to stderr). */ DEBUG = 1 << 21 }; /* Class manager for gperf program Options. */ struct Options { public: /* Constructor. */ Options (); /* Accessors. */ /* Tests a given boolean option. Returns true if set, false otherwise. */ bool operator[] (Option_Type option) const; /* Sets a given boolean option. */ void set (Option_Type option); /* Returns the jump value. */ int get_jump () const; /* Returns the initial associated character value. */ int get_initial_asso_value () const; /* Returns the number of iterations for finding good asso_values. */ int get_asso_iterations () const; /* Returns the factor by which to multiply the generated table's size. */ float get_size_multiple () const; /* Returns key positions. */ const Positions& get_key_positions () const; /* Holds the boolean options. */ int _option_word; /* Jump length when trying alternative values. */ int _jump; /* Initial value for asso_values table. */ int _initial_asso_value; /* Number of attempts at finding good asso_values. */ int _asso_iterations; /* Factor by which to multiply the generated table's size. */ float _size_multiple; /* Contains user-specified key choices. */ Positions _key_positions; }; /* Global option coordinator for the entire program. */ extern Options option; #ifdef __OPTIMIZE__ #define INLINE inline #include "options.icc" #undef INLINE #endif #endif smalltalk-3.2.5/superops/options.icc0000644000175000017500000000372012123404352014457 00000000000000/* Inline Functions for options.{h,cc}. Copyright (C) 1989-1998, 2000, 2002-2003 Free Software Foundation, Inc. Written by Douglas C. Schmidt and Bruno Haible . This file is part of GNU GPERF. GNU GPERF is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2, or (at your option) any later version. GNU GPERF is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; see the file COPYING. If not, write to the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. */ /* ----------------------------- Class Options ----------------------------- */ /* Tests a given boolean option. Returns true if set, false otherwise. */ INLINE bool Options::operator[] (Option_Type option) const { return _option_word & option; } /* Sets a given boolean option. */ INLINE void Options::set (Option_Type option) { _option_word |= option; } /* Returns the jump value. */ INLINE int Options::get_jump () const { return _jump; } /* Returns the initial associated character value. */ INLINE int Options::get_initial_asso_value () const { return _initial_asso_value; } /* Returns the number of iterations for finding finding good asso_values. */ INLINE int Options::get_asso_iterations () const { return _asso_iterations; } /* Returns the factor by which to multiply the generated table's size. */ INLINE float Options::get_size_multiple () const { return _size_multiple; } /* Returns key positions. */ INLINE const Positions& Options::get_key_positions () const { return _key_positions; } smalltalk-3.2.5/superops/ChangeLog0000644000175000017500000000543312123404352014061 000000000000002011-02-24 Paolo Bonzini * superops/superops.cc: Fix for 9bc2bf59. 2011-02-24 Gwenael Casaccio * superops/byte_def.cc: Add missing includes. * superops/hash.cc: Add missing includes. * superops/positions.h: Add missing forward references. * superops/superops.cc: Add missing includes. * superops/table.cc: Add missing includes. * superops/vm_def.cc: Add missing includes. 2008-07-14 Paolo Bonzini * superops/vm_def.cc: Use a proper subclass to emit ADVANCE instead of PREFETCH for jumps. 2007-08-20 Paolo Bonzini * superops/byte_def.cc: Abort on superoperators. Remove "COLON". * superops/vm_def.cc: Abort on superoperators. Emit ADVANCE instead of PREFETCH for jumps. Remove "COLON". * superops/superops.cc: Filter out superoperators here. Be resilient to errors before the code runs. * superops/table.cc: Clear memory. 2007-08-20 Paolo Bonzini * superops/superops.cc: Split after push/store literal variable. 2006-12-05 Paolo Bonzini *** Version 2.3 released. 2003-09-13 Paolo Bonzini * observer-list.cc: new file * observer-list.h: new file * superops.cc: use observer pattern * table.cc: new file * table.h: new file 2003-09-11 Paolo Bonzini * vm_def.cc: new file * vm_def.h: new file * superops.cc: create vm.def too 2003-09-10 Paolo Bonzini * byte_def.cc: new file * byte_def.h: new file * hash.cc: new file from output.cc and output.h * hash.h: new file * output.cc: merged into hash.cc * output.h: merged into hash.cc * superops.cc: create byte.def too 2003-09-09 Paolo Bonzini * bool-array.cc: included from GPERF 3.0.1. * bool-array.h: included from GPERF 3.0.1. * bool-array.icc: included from GPERF 3.0.1. * hash-table.cc: included from GPERF 3.0.1. * hash-table.h: included from GPERF 3.0.1. * keyword-list.cc: included from GPERF 3.0.1. * keyword-list.h: included from GPERF 3.0.1. * keyword-list.icc: included from GPERF 3.0.1. * keyword.cc: included from GPERF 3.0.1. * keyword.h: included from GPERF 3.0.1. * keyword.icc: included from GPERF 3.0.1. * options.cc: trimmed down from GPERF 3.0.1. * options.h: trimmed down from GPERF 3.0.1. * options.icc: trimmed down from GPERF 3.0.1. * output.cc: trimmed down from GPERF 3.0.1, use iostreams. * output.h: trimmed down from GPERF 3.0.1, use iostreams. * positions.cc: included from GPERF 3.0.1. * positions.h: included from GPERF 3.0.1. * positions.icc: included from GPERF 3.0.1. * search.cc: included from GPERF 3.0.1. * search.h: included from GPERF 3.0.1. * superops.cc: interface to the GPERF routines. 2003-09-07 Paolo Bonzini * superops.cc: Done the searching part. smalltalk-3.2.5/superops/observer-list.h0000644000175000017500000000326012123404352015254 00000000000000/////////////////////////////// -*- C++ -*- /////////////////////////// // // Program to extract superoperators from a GNU Smalltalk image. // Observer pattern. // /////////////////////////////////////////////////////////////////////// /////////////////////////////////////////////////////////////////////// // // Copyright 2003 Free Software Foundation, Inc. // Written by Paolo Bonzini. // // This file is part of GNU Smalltalk. // // GNU Smalltalk is free software; you can redistribute it and/or modify it // under the terms of the GNU General Public License as published by the Free // Software Foundation; either version 2, or (at your option) any later // version. // // GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT // ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or // FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for // more details. // // You should have received a copy of the GNU General Public License along with // GNU Smalltalk; see the file COPYING. If not, write to the Free Software // Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. // /////////////////////////////////////////////////////////////////////// #ifndef SUPEROPS_OBSERVER_H #define SUPEROPS_OBSERVER_H #include class observer { public: virtual void with_fixed_arg_1 (int new_bc, int bc1, int arg, int bc2) = 0; virtual void with_fixed_arg_2 (int new_bc, int bc1, int bc2, int arg) = 0; }; class observer_list : public std::list, public observer { public: void with_fixed_arg_1 (int new_bc, int bc1, int arg, int bc2); void with_fixed_arg_2 (int new_bc, int bc1, int bc2, int arg); }; #endif smalltalk-3.2.5/superops/table.h0000644000175000017500000000314312123404352013543 00000000000000/////////////////////////////// -*- C++ -*- /////////////////////////// // // Program to extract superoperators from a GNU Smalltalk image. // byte.def creation header. // /////////////////////////////////////////////////////////////////////// /////////////////////////////////////////////////////////////////////// // // Copyright 2003 Free Software Foundation, Inc. // Written by Paolo Bonzini. // // This file is part of GNU Smalltalk. // // GNU Smalltalk is free software; you can redistribute it and/or modify it // under the terms of the GNU General Public License as published by the Free // Software Foundation; either version 2, or (at your option) any later // version. // // GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT // ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or // FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for // more details. // // You should have received a copy of the GNU General Public License along with // GNU Smalltalk; see the file COPYING. If not, write to the Free Software // Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. // /////////////////////////////////////////////////////////////////////// #ifndef SUPEROPS_TABLE_H #define SUPEROPS_TABLE_H #include "observer-list.h" #include class superop_table_builder : public observer { std::ofstream fs; int table[1024]; public: superop_table_builder (); ~superop_table_builder (); void with_fixed_arg_1 (int new_bc, int bc1, int arg, int bc2); void with_fixed_arg_2 (int new_bc, int bc1, int bc2, int arg); }; #endif smalltalk-3.2.5/superops/byte_def.cc0000644000175000017500000004364612123404352014407 00000000000000/////////////////////////////// -*- C++ -*- /////////////////////////// // // Program to extract superoperators from a GNU Smalltalk image. // byte.def creation routines. // /////////////////////////////////////////////////////////////////////// /////////////////////////////////////////////////////////////////////// // // Copyright 2003, 2007 Free Software Foundation, Inc. // Written by Paolo Bonzini. // // This file is part of GNU Smalltalk. // // GNU Smalltalk is free software; you can redistribute it and/or modify it // under the terms of the GNU General Public License as published by the Free // Software Foundation; either version 2, or (at your option) any later // version. // // GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT // ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or // FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for // more details. // // You should have received a copy of the GNU General Public License along with // GNU Smalltalk; see the file COPYING. If not, write to the Free Software // Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. // /////////////////////////////////////////////////////////////////////// #if defined __GNUC__ && __GNUC__ < 3 #error Sorry, you need a recent C++ compiler to compile this program. #endif #include "byte_def.h" #include #include #include #include #include namespace { struct bytecode { static bytecode *bytecodes[256]; std::string str; int num; bytecode (int _num); bytecode (int _num, const char *_str); virtual void write_byte_def (std::ostream &os); virtual void write_byte_def_ext_arg (std::ostream &os, int arg) = 0; virtual void write_byte_def_fixed_arg (std::ostream &os, int arg) = 0; virtual void write_byte_def_var_arg (std::ostream &os) = 0; }; struct bytecode_elementary : bytecode { const char *name; bytecode_elementary (int _num, const char *_name, const char *_str); }; struct bytecode_noarg : bytecode_elementary { bytecode_noarg (int _num, const char *_name, const char *_str); void write_byte_def_ext_arg (std::ostream &os, int arg); void write_byte_def_fixed_arg (std::ostream &os, int arg); void write_byte_def_var_arg (std::ostream &os); }; struct bytecode_fast_send : bytecode_noarg { bytecode_fast_send (int _num, const char *_name, const char *_str); void write_byte_def_fixed_arg (std::ostream &os, int arg); }; struct bytecode_invalid : bytecode { bytecode_invalid (int _num); void write_byte_def_ext_arg (std::ostream &os, int arg); void write_byte_def_fixed_arg (std::ostream &os, int arg); void write_byte_def_var_arg (std::ostream &os); }; struct bytecode_unary : bytecode_elementary { bytecode_unary (int _num, const char *_name, const char *_str); void write_byte_def_ext_arg (std::ostream &os, int arg); void write_byte_def_fixed_arg (std::ostream &os, int arg); void write_byte_def_var_arg (std::ostream &os); }; struct bytecode_ext : bytecode_elementary { bytecode_ext (int _num, const char *_name, const char *_str); void write_byte_def (std::ostream &os); void write_byte_def_ext_arg (std::ostream &os, int arg); void write_byte_def_fixed_arg (std::ostream &os, int arg); void write_byte_def_var_arg (std::ostream &os); }; struct bytecode_jump : bytecode_elementary { const char *sign; bytecode_jump (int _num, const char *_name, bool minus, const char *_str); void write_byte_def_ext_arg (std::ostream &os, int arg); void write_byte_def_fixed_arg (std::ostream &os, int arg); void write_byte_def_var_arg (std::ostream &os); }; struct bytecode_binary : bytecode_elementary { bytecode_binary (int _num, const char *_name, const char *_str); void write_byte_def_ext_arg (std::ostream &os, int arg); void write_byte_def_fixed_arg (std::ostream &os, int arg); void write_byte_def_var_arg (std::ostream &os); }; struct bytecode_send : bytecode_elementary { bytecode_send (int _num, const char *_name, const char *_str); void write_byte_def_ext_arg (std::ostream &os, int arg); void write_byte_def_fixed_arg (std::ostream &os, int arg); void write_byte_def_var_arg (std::ostream &os); }; struct bytecode_send_imm : bytecode_elementary { bytecode_send_imm (int _num, const char *_name, const char *_str); void write_byte_def_ext_arg (std::ostream &os, int arg); void write_byte_def_fixed_arg (std::ostream &os, int arg); void write_byte_def_var_arg (std::ostream &os); }; struct bytecode_superoperator : bytecode { bytecode *bc1, *bc2; int fixed_arg; bytecode_superoperator (int _num, int _bc1, int _bc2, int _arg); }; struct bytecode_with_fixed_arg_1 : bytecode_superoperator { bytecode_with_fixed_arg_1 (int _num, int _bc1, int _bc2, int _arg); void write_byte_def_ext_arg (std::ostream &os, int arg); void write_byte_def_fixed_arg (std::ostream &os, int arg); void write_byte_def_var_arg (std::ostream &os); }; struct bytecode_with_fixed_arg_2 : bytecode_superoperator { bytecode_with_fixed_arg_2 (int _num, int _bc1, int _bc2, int _arg); void write_byte_def_ext_arg (std::ostream &os, int arg); void write_byte_def_fixed_arg (std::ostream &os, int arg); void write_byte_def_var_arg (std::ostream &os); }; void bytecode::write_byte_def (std::ostream & os) { os << "/* " << str << " */" << std::endl; os << num << " {" << std::endl; os << " extract opcode (8), arg_lsb (8);" << std::endl; write_byte_def_var_arg (os); os << "}" << std::endl << std::endl; }; bytecode::bytecode (int _num): num (_num), str () { bytecodes[num] = this; }; bytecode::bytecode (int _num, const char *_str): num (_num), str (_str) { bytecodes[num] = this; }; bytecode_elementary::bytecode_elementary (int _num, const char *_name, const char *_str): bytecode (_num, _str), name (_name) { }; bytecode_noarg::bytecode_noarg (int _num, const char *_name, const char *_str): bytecode_elementary (_num, _name, _str) { }; void bytecode_noarg::write_byte_def_ext_arg (std::ostream & os, int arg) { write_byte_def_fixed_arg (os, arg); } void bytecode_noarg::write_byte_def_fixed_arg (std::ostream & os, int arg) { os << " dispatch " << name << ';' << std::endl; } void bytecode_noarg::write_byte_def_var_arg (std::ostream & os) { write_byte_def_fixed_arg (os, 0); } bytecode_fast_send::bytecode_fast_send (int _num, const char *_name, const char *_str): bytecode_noarg (_num, _name, _str) { }; void bytecode_fast_send::write_byte_def_fixed_arg (std::ostream & os, int arg) { os << " dispatch " << name << " (" << (num & 15) << ");" << std::endl; } bytecode_invalid::bytecode_invalid (int _num): bytecode (_num, "invalid bytecode") { }; void bytecode_invalid::write_byte_def_ext_arg (std::ostream & os, int arg) { abort (); } void bytecode_invalid::write_byte_def_fixed_arg (std::ostream & os, int arg) { abort (); } void bytecode_invalid::write_byte_def_var_arg (std::ostream & os) { os << " dispatch INVALID (" << num << ", arg | arg_lsb);" << std::endl; } bytecode_unary::bytecode_unary (int _num, const char *_name, const char *_str): bytecode_elementary (_num, _name, _str) { }; void bytecode_unary::write_byte_def_ext_arg (std::ostream & os, int arg) { os << " dispatch " << name << " (" << (arg << 8) << " | arg_lsb);" << std::endl; } void bytecode_unary::write_byte_def_fixed_arg (std::ostream & os, int arg) { os << " dispatch " << name << " (" << arg << ");" << std::endl; } void bytecode_unary::write_byte_def_var_arg (std::ostream & os) { os << " dispatch " << name << " (arg | arg_lsb);" << std::endl; } bytecode_ext::bytecode_ext (int _num, const char *_name, const char *_str): bytecode_elementary (_num, _name, _str) { }; void bytecode_ext::write_byte_def (std::ostream & os) { os << "/* " << str << " */" << std::endl; os << num << " {" << std::endl; os << " extract opcode (8), arg_lsb (8);" << std::endl; write_byte_def_var_arg (os); os << " continue;" << std::endl; os << "}" << std::endl << std::endl; }; void bytecode_ext::write_byte_def_ext_arg (std::ostream & os, int arg) { write_byte_def_fixed_arg (os, arg); write_byte_def_var_arg (os); } void bytecode_ext::write_byte_def_fixed_arg (std::ostream & os, int arg) { os << " arg = (arg | " << arg << ") << 8);" << std::endl; } void bytecode_ext::write_byte_def_var_arg (std::ostream & os) { os << " arg = (arg | arg_lsb) << 8;" << std::endl; } bytecode_jump::bytecode_jump (int _num, const char *_name, bool minus, const char *_str): bytecode_elementary (_num, _name, _str) { sign = minus ? "IP - IP0 - " : "IP - IP0 + "; } void bytecode_jump::write_byte_def_ext_arg (std::ostream & os, int arg) { os << " dispatch " << name << " (" << sign << '(' << (arg << 8) << " | arg_lsb));" << std::endl; } void bytecode_jump::write_byte_def_fixed_arg (std::ostream & os, int arg) { os << " dispatch " << name << " (" << sign << arg << "));" << std::endl; } void bytecode_jump::write_byte_def_var_arg (std::ostream & os) { os << " dispatch " << name << " (" << sign << "(arg | arg_lsb));" << std::endl; } bytecode_binary::bytecode_binary (int _num, const char *_name, const char *_str): bytecode_elementary (_num, _name, _str) { }; void bytecode_binary::write_byte_def_ext_arg (std::ostream & os, int arg) { os << " dispatch " << name << " (arg | arg_lsb, " << arg << ");" << std::endl; } void bytecode_binary::write_byte_def_fixed_arg (std::ostream & os, int arg) { os << " dispatch " << name << " (" << (arg >> 8) << ", " << (arg & 255) << ");" << std::endl; } void bytecode_binary::write_byte_def_var_arg (std::ostream & os) { os << " dispatch " << name << " (arg >> 8, arg_lsb);" << std::endl; } bytecode_send::bytecode_send (int _num, const char *_name, const char *_str): bytecode_elementary (_num, _name, _str) { }; void bytecode_send::write_byte_def_ext_arg (std::ostream & os, int arg) { os << " dispatch " << name << " (arg | arg_lsb, " << (num & 1) << ", " << arg << ");" << std::endl; } void bytecode_send::write_byte_def_fixed_arg (std::ostream & os, int arg) { os << " dispatch " << name << " (" << (arg >> 8) << ", " << (num & 1) << ", " << (arg & 255) << ");" << std::endl; } void bytecode_send::write_byte_def_var_arg (std::ostream & os) { os << " dispatch " << name << " (arg >> 8, " << (num & 1) << ", arg_lsb);" << std::endl; } bytecode_send_imm::bytecode_send_imm (int _num, const char *_name, const char *_str): bytecode_elementary (_num, _name, _str) { }; void bytecode_send_imm::write_byte_def_ext_arg (std::ostream & os, int arg) { os << " dispatch " << name << " (" << (arg << 8) << " | arg_lsb, " << (num & 1) << ");" << std::endl; } void bytecode_send_imm::write_byte_def_fixed_arg (std::ostream & os, int arg) { os << " dispatch " << name << " (" << arg << ", " << (num & 1) << ");" << std::endl; } void bytecode_send_imm::write_byte_def_var_arg (std::ostream & os) { os << " dispatch " << name << " (arg | arg_lsb, " << (num & 1) << ");" << std::endl; } bytecode_superoperator::bytecode_superoperator (int _num, int _bc1, int _bc2, int _arg): bytecode (_num), bc1 (bytecodes[_bc1]), bc2 (bytecodes[_bc2]), fixed_arg (_arg) { if (!bc1 || !bc2) abort (); } bytecode_with_fixed_arg_1::bytecode_with_fixed_arg_1 (int _num, int _bc1, int _bc2, int _arg): bytecode_superoperator (_num, _bc1, _bc2, _arg) { std::string::iterator i; std::ostringstream os; os << _arg; str.append (bc1->str); str.append ("\n "); str.append (bc2->str); for (i = str.begin (); *i != '*'; i++); str.replace (i, i + 1, os.str ()); } void bytecode_with_fixed_arg_1::write_byte_def_ext_arg (std::ostream & os, int arg) { abort (); } void bytecode_with_fixed_arg_1::write_byte_def_fixed_arg (std::ostream & os, int arg) { bc1->write_byte_def_fixed_arg (os, fixed_arg); bc2->write_byte_def_fixed_arg (os, arg); } void bytecode_with_fixed_arg_1::write_byte_def_var_arg (std::ostream & os) { bc1->write_byte_def_fixed_arg (os, fixed_arg); bc2->write_byte_def_var_arg (os); } bytecode_with_fixed_arg_2::bytecode_with_fixed_arg_2 (int _num, int _bc1, int _bc2, int _arg): bytecode_with_fixed_arg_2::bytecode_superoperator (_num, _bc1, _bc2, _arg) { std::string::iterator i; std::ostringstream os; os << _arg; str.append (bc1->str); str.append ("\n "); str.append (bc2->str); for (i = str.end (); *--i != '*';); str.replace (i, i + 1, os.str ()); } void bytecode_with_fixed_arg_2::write_byte_def_ext_arg (std::ostream & os, int arg) { abort (); } void bytecode_with_fixed_arg_2::write_byte_def_fixed_arg (std::ostream & os, int arg) { if (bc1 == bytecodes[EXT_BYTE]) bc2->write_byte_def_fixed_arg (os, (arg << 8) + fixed_arg); else { bc1->write_byte_def_fixed_arg (os, arg); bc2->write_byte_def_fixed_arg (os, fixed_arg); } } void bytecode_with_fixed_arg_2::write_byte_def_var_arg (std::ostream & os) { if (bc1 == bytecodes[EXT_BYTE]) bc2->write_byte_def_ext_arg (os, fixed_arg); else { bc1->write_byte_def_var_arg (os); bc2->write_byte_def_fixed_arg (os, fixed_arg); } } bytecode *bytecode::bytecodes[256]; bytecode_fast_send bc0 (0, "SEND_ARITH", "PLUS_SPECIAL(*)"); bytecode_fast_send bc1 (1, "SEND_ARITH", "MINUS_SPECIAL(*)"); bytecode_fast_send bc2 (2, "SEND_ARITH", "LESS_THAN_SPECIAL(*)"); bytecode_fast_send bc3 (3, "SEND_ARITH", "GREATER_THAN_SPECIAL(*)"); bytecode_fast_send bc4 (4, "SEND_ARITH", "LESS_EQUAL_SPECIAL(*)"); bytecode_fast_send bc5 (5, "SEND_ARITH", "GREATER_EQUAL_SPECIAL(*)"); bytecode_fast_send bc6 (6, "SEND_ARITH", "EQUAL_SPECIAL(*)"); bytecode_fast_send bc7 (7, "SEND_ARITH", "NOT_EQUAL_SPECIAL(*)"); bytecode_fast_send bc8 (8, "SEND_ARITH", "TIMES_SPECIAL(*)"); bytecode_fast_send bc9 (9, "SEND_ARITH", "DIVIDE_SPECIAL(*)"); bytecode_fast_send bc10 (10, "SEND_ARITH", "REMAINDER_SPECIAL(*)"); bytecode_fast_send bc11 (11, "SEND_ARITH", "BIT_XOR_SPECIAL(*)"); bytecode_fast_send bc12 (12, "SEND_ARITH", "BIT_SHIFT_SPECIAL(*)"); bytecode_fast_send bc13 (13, "SEND_ARITH", "INTEGER_DIVIDE_SPECIAL(*)"); bytecode_fast_send bc14 (14, "SEND_ARITH", "BIT_AND_SPECIAL(*)"); bytecode_fast_send bc15 (15, "SEND_ARITH", "BIT_OR_SPECIAL(*)"); bytecode_fast_send bc16 (16, "SEND_SPECIAL", "AT_SPECIAL(*)"); bytecode_fast_send bc17 (17, "SEND_SPECIAL", "AT_PUT_SPECIAL(*)"); bytecode_fast_send bc18 (18, "SEND_SPECIAL", "SIZE_SPECIAL(*)"); bytecode_fast_send bc19 (19, "SEND_SPECIAL", "CLASS_SPECIAL(*)"); bytecode_fast_send bc20 (20, "SEND_SPECIAL", "IS_NIL_SPECIAL(*)"); bytecode_fast_send bc21 (21, "SEND_SPECIAL", "NOT_NIL_SPECIAL(*)"); bytecode_fast_send bc22 (22, "SEND_SPECIAL", "VALUE_SPECIAL(*)"); bytecode_fast_send bc23 (23, "SEND_SPECIAL", "VALUE_COLON_SPECIAL(*)"); bytecode_fast_send bc24 (24, "SEND_SPECIAL", "SAME_OBJECT_SPECIAL(*)"); bytecode_fast_send bc25 (25, "SEND_SPECIAL", "JAVA_AS_INT_SPECIAL(*)"); bytecode_fast_send bc26 (26, "SEND_SPECIAL", "JAVA_AS_LONG_SPECIAL(*)"); bytecode_send bc28 (28, "SEND", "SEND(*)"); bytecode_send bc29 (29, "SEND", "SEND_SUPER(*)"); bytecode_send_imm bc30 (30, "SEND_IMMEDIATE", "SEND_IMMEDIATE(*)"); bytecode_send_imm bc31 (31, "SEND_IMMEDIATE", "SEND_SUPER_IMMEDIATE(*)"); bytecode_unary bc32 (32, "PUSH_TEMPORARY_VARIABLE", "PUSH_TEMPORARY_VARIABLE(*)"); bytecode_binary bc33 (33, "PUSH_OUTER_TEMP", "PUSH_OUTER_TEMP(*)"); bytecode_unary bc34 (34, "PUSH_LIT_VARIABLE", "PUSH_LIT_VARIABLE(*)"); bytecode_unary bc35 (35, "PUSH_RECEIVER_VARIABLE", "PUSH_RECEIVER_VARIABLE(*)"); bytecode_unary bc36 (36, "STORE_TEMPORARY_VARIABLE", "STORE_TEMPORARY_VARIABLE(*)"); bytecode_binary bc37 (37, "STORE_OUTER_TEMP", "STORE_OUTER_TEMP(*)"); bytecode_unary bc38 (38, "STORE_LIT_VARIABLE", "STORE_LIT_VARIABLE(*)"); bytecode_unary bc39 (39, "STORE_RECEIVER_VARIABLE", "STORE_RECEIVER_VARIABLE(*)"); bytecode_jump bc40 (40, "JUMP", true, "JUMP_BACK(*)"); bytecode_jump bc41 (41, "JUMP", false, "JUMP(*)"); bytecode_jump bc42 (42, "POP_JUMP_TRUE", false, "POP_JUMP_TRUE(*)"); bytecode_jump bc43 (43, "POP_JUMP_FALSE", false, "POP_JUMP_FALSE(*)"); bytecode_unary bc44 (44, "PUSH_INTEGER", "PUSH_INTEGER(*)"); bytecode_unary bc45 (45, "PUSH_SPECIAL", "PUSH_SPECIAL(*)"); bytecode_unary bc46 (46, "PUSH_LIT_CONSTANT", "PUSH_LIT_CONSTANT(*)"); bytecode_unary bc47 (47, "POP_INTO_NEW_STACKTOP", "POP_INTO_NEW_STACKTOP(*)"); bytecode_noarg bc48 (48, "POP_STACK_TOP", "POP_STACK_TOP(*)"); bytecode_noarg bc49 (49, "MAKE_DIRTY_BLOCK", "MAKE_DIRTY_BLOCK(*)"); bytecode_noarg bc50 (50, "RETURN_METHOD_STACK_TOP", "RETURN_METHOD_STACK_TOP(*)"); bytecode_noarg bc51 (51, "RETURN_CONTEXT_STACK_TOP", "RETURN_CONTEXT_STACK_TOP(*)"); bytecode_noarg bc52 (52, "DUP_STACK_TOP", "DUP_STACK_TOP(*)"); bytecode_noarg bc53 (53, "EXIT_INTERPRETER", "EXIT_INTERPRETER(*)"); bytecode_unary bc54 (54, "LINE_NUMBER_BYTECODE", "LINE_NUMBER_BYTECODE(*)"); bytecode_ext bc55 (55, "EXT_BYTE", "EXT_BYTE(*)"); bytecode_noarg bc56 (56, "PUSH_SELF", "PUSH_SELF(*)"); } byte_def_builder::byte_def_builder () : fs ("byte.def") { fs << "/* Automatically generated by superops. Do not modify past this line! */" << std::endl; for (int i = 0; i < 64; i++) { if (!bytecode::bytecodes[i]) bytecode::bytecodes[i] = new bytecode_invalid (i); bytecode::bytecodes[i]->write_byte_def (fs); } } byte_def_builder::~byte_def_builder () { std::cout << "genbc script (recognizer) written to byte.def." << std::endl; } void byte_def_builder::with_fixed_arg_1 (int new_bc, int bc1, int arg, int bc2) { bytecode *bc = new bytecode_with_fixed_arg_1 (new_bc, bc1, bc2, arg); bc->write_byte_def (fs); std::string short_str = bc->str; int n; while ((n = short_str.find ("\n ")) > -1) short_str.replace (n, 3, ","); std::cout << short_str << std::endl; } void byte_def_builder::with_fixed_arg_2 (int new_bc, int bc1, int bc2, int arg) { bytecode *bc = new bytecode_with_fixed_arg_2 (new_bc, bc1, bc2, arg); bc->write_byte_def (fs); std::string short_str = bc->str; int n; while ((n = short_str.find ("\n ")) > -1) short_str.replace (n, 3, ","); std::cout << short_str << std::endl; } smalltalk-3.2.5/superops/options.cc0000644000175000017500000000366412123404352014315 00000000000000/* Handles parsing the Options provided to the user. Copyright (C) 1989-1998, 2000, 2002-2003 Free Software Foundation, Inc. Written by Douglas C. Schmidt and Bruno Haible . This file is part of GNU GPERF. GNU GPERF is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2, or (at your option) any later version. GNU GPERF is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; see the file COPYING. If not, write to the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. */ /* Specification. */ #include "options.h" #include #include /* declares atoi(), abs(), exit() */ #include /* declares strcmp() */ #include /* declares isdigit() */ #include /* defines CHAR_MAX */ #include "getopt.h" /* Global option coordinator for the entire program. */ Options option; /* Size to jump on a collision. */ static const int DEFAULT_JUMP_VALUE = 5; /* ------------------------------------------------------------------------- */ /* Sets the default Options. */ Options::Options () : _option_word (RANDOM), _jump (DEFAULT_JUMP_VALUE), _initial_asso_value (0), _asso_iterations (0), _size_multiple (1), _key_positions () { } /* Dumps option status when debugging is enabled. */ /* ------------------------------------------------------------------------- */ #ifndef __OPTIMIZE__ #define INLINE /* not inline */ #include "options.icc" #undef INLINE #endif /* not defined __OPTIMIZE__ */ smalltalk-3.2.5/superops/byte_def.h0000644000175000017500000000317712123404352014244 00000000000000/////////////////////////////// -*- C++ -*- /////////////////////////// // // Program to extract superoperators from a GNU Smalltalk image. // byte.def creation header. // /////////////////////////////////////////////////////////////////////// /////////////////////////////////////////////////////////////////////// // // Copyright 2003 Free Software Foundation, Inc. // Written by Paolo Bonzini. // // This file is part of GNU Smalltalk. // // GNU Smalltalk is free software; you can redistribute it and/or modify it // under the terms of the GNU General Public License as published by the Free // Software Foundation; either version 2, or (at your option) any later // version. // // GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT // ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or // FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for // more details. // // You should have received a copy of the GNU General Public License along with // GNU Smalltalk; see the file COPYING. If not, write to the Free Software // Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. // /////////////////////////////////////////////////////////////////////// #ifndef SUPEROPS_BYTE_DEF_H #define SUPEROPS_BYTE_DEF_H #include "observer-list.h" enum { LINE_NUMBER_BYTECODE = 54, EXT_BYTE = 55 }; #include class byte_def_builder : public observer { public: std::ofstream fs; byte_def_builder (); ~byte_def_builder (); void with_fixed_arg_1 (int new_bc, int bc1, int arg, int bc2); void with_fixed_arg_2 (int new_bc, int bc1, int bc2, int arg); }; #endif smalltalk-3.2.5/superops/README0000644000175000017500000000405012123404352013161 00000000000000This is a C++ program to look for candidate superoperators, make a perfect hash function for them, and write out the tables needed and the perfect hash functions. Much of the code in this directory is taken from GPERF, as a result, it is written in a different style than superops.cc which is the main driver program (e.g. superops.cc uses the STL, many other files do not). The reason why I used GPERF's code instead of using GPERF directly (as I do for the builtins.gperf hash function, for example) is that: 1) I would still have needed to write code to glue the superoperator search with GPERF. 2) I needed a completely different calling convention and implementation of the lookup function than the usual one: so instead of hacking and sed'ing GPERF's output I decided that modifying GPERF's output routines would have been more maintainable. 3) I had already written the superoperator search program in C++, which made it easier to put in GPERF's code. 4) It is unlikely that GPERF changes significantly enough (and that superops be ever used again to generate a new bytecode set) to consider merging the upstream modifications into superops. The GPERF code was taken almost unmodified with the exception of options.cc (because most options that only affected output are not needed anymore, and because I stripped the getopt code). Of course, input.cc and main.cc are not there anymore, their function is done by the single file hash.cc, which also includes much of output.cc. Run the program, and it will automagically generate: 1) superop1.inl and superop2.inl, which contain the hash tables and the tables for writing the hash lookup function. 2) byte.def, the final part of the input to genbc (used for decoding the instructions). 3) vm.def, the final part of the input to genvm (used for executing the instructions in the virtual machine proper). 4) table.st, the superoperator table to be included in CompildCode.st. This is strictly a maintainer tool, so it is written for a recent C++ compiler and does not even use autoconf. Paolo smalltalk-3.2.5/superops/positions.icc0000644000175000017500000001472712123404352015024 00000000000000/* Inline Functions for positions.{h,cc}. Copyright (C) 1989-1998, 2000, 2002 Free Software Foundation, Inc. Written by Douglas C. Schmidt and Bruno Haible . This file is part of GNU GPERF. GNU GPERF is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2, or (at your option) any later version. GNU GPERF is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; see the file COPYING. If not, write to the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. */ // This needs: //#include /* ---------------------------- Class Positions ---------------------------- */ /* Constructors. */ INLINE Positions::Positions () : _useall (false), _size (0) { } INLINE Positions::Positions (int pos1) : _useall (false), _size (1) { _positions[0] = pos1; } INLINE Positions::Positions (int pos1, int pos2) : _useall (false), _size (2) { _positions[0] = pos1; _positions[1] = pos2; } /* Copy constructor. */ INLINE Positions::Positions (const Positions& src) : _useall (src._useall), _size (src._size) { memcpy (_positions, src._positions, _size * sizeof (_positions[0])); } /* Assignment operator. */ INLINE Positions& Positions::operator= (const Positions& src) { _useall = src._useall; _size = src._size; memcpy (_positions, src._positions, _size * sizeof (_positions[0])); return *this; } /* Accessors. */ INLINE bool Positions::is_useall () const { return _useall; } INLINE int Positions::operator[] (unsigned int index) const { return _positions[index]; } INLINE unsigned int Positions::get_size () const { return _size; } /* Write access. */ INLINE void Positions::set_useall (bool useall) { _useall = useall; if (useall) { /* The positions are 0, 1, ..., MAX_KEY_POS-1, in descending order. */ _size = MAX_KEY_POS; int *ptr = _positions; for (int i = MAX_KEY_POS - 1; i >= 0; i--) *ptr++ = i; } } INLINE int * Positions::pointer () { return _positions; } INLINE void Positions::set_size (unsigned int size) { _size = size; } /* Sorts the array in reverse order. Returns true if there are no duplicates, false otherwise. */ INLINE bool Positions::sort () { if (_useall) return true; /* Bubble sort. */ bool duplicate_free = true; int *base = _positions; unsigned int len = _size; for (unsigned int i = 1; i < len; i++) { unsigned int j; int tmp; for (j = i, tmp = base[j]; j > 0 && tmp >= base[j - 1]; j--) if ((base[j] = base[j - 1]) == tmp) /* oh no, a duplicate!!! */ duplicate_free = false; base[j] = tmp; } return duplicate_free; } /* Creates an iterator, returning the positions in descending order. */ INLINE PositionIterator Positions::iterator () const { return PositionIterator (*this); } /* Creates an iterator, returning the positions in descending order, that apply to strings of length <= maxlen. */ INLINE PositionIterator Positions::iterator (int maxlen) const { return PositionIterator (*this, maxlen); } /* Creates an iterator, returning the positions in ascending order. */ INLINE PositionReverseIterator Positions::reviterator () const { return PositionReverseIterator (*this); } /* Creates an iterator, returning the positions in ascending order, that apply to strings of length <= maxlen. */ INLINE PositionReverseIterator Positions::reviterator (int maxlen) const { return PositionReverseIterator (*this, maxlen); } /* ------------------------- Class PositionIterator ------------------------ */ /* Initializes an iterator through POSITIONS. */ INLINE PositionIterator::PositionIterator (Positions const& positions) : _set (positions), _index (0) { } /* Initializes an iterator through POSITIONS, ignoring positions >= maxlen. */ INLINE PositionIterator::PositionIterator (Positions const& positions, int maxlen) : _set (positions) { if (positions._useall) _index = (maxlen <= Positions::MAX_KEY_POS ? Positions::MAX_KEY_POS - maxlen : 0); else { unsigned int index; for (index = 0; index < positions._size && positions._positions[index] >= maxlen; index++) ; _index = index; } } /* Retrieves the next position, or EOS past the end. */ INLINE int PositionIterator::next () { return (_index < _set._size ? _set._positions[_index++] : EOS); } /* Returns the number of remaining positions, i.e. how often next() will return a value != EOS. */ INLINE unsigned int PositionIterator::remaining () const { return _set._size - _index; } /* Copy constructor. */ INLINE PositionIterator::PositionIterator (const PositionIterator& src) : _set (src._set), _index (src._index) { } /* --------------------- Class PositionReverseIterator --------------------- */ /* Initializes an iterator through POSITIONS. */ INLINE PositionReverseIterator::PositionReverseIterator (Positions const& positions) : _set (positions), _index (_set._size), _minindex (0) { } /* Initializes an iterator through POSITIONS, ignoring positions >= maxlen. */ INLINE PositionReverseIterator::PositionReverseIterator (Positions const& positions, int maxlen) : _set (positions), _index (_set._size) { if (positions._useall) _minindex = (maxlen <= Positions::MAX_KEY_POS ? Positions::MAX_KEY_POS - maxlen : 0); else { unsigned int index; for (index = 0; index < positions._size && positions._positions[index] >= maxlen; index++) ; _minindex = index; } } /* Retrieves the next position, or EOS past the end. */ INLINE int PositionReverseIterator::next () { return (_index > _minindex ? _set._positions[--_index] : EOS); } /* Returns the number of remaining positions, i.e. how often next() will return a value != EOS. */ INLINE unsigned int PositionReverseIterator::remaining () const { return _index - _minindex; } /* Copy constructor. */ INLINE PositionReverseIterator::PositionReverseIterator (const PositionReverseIterator& src) : _set (src._set), _index (src._index), _minindex (src._minindex) { } smalltalk-3.2.5/superops/observer-list.cc0000644000175000017500000000313112123404352015407 00000000000000/////////////////////////////// -*- C++ -*- /////////////////////////// // // Program to extract superoperators from a GNU Smalltalk image. // Observer pattern. // /////////////////////////////////////////////////////////////////////// /////////////////////////////////////////////////////////////////////// // // Copyright 2003 Free Software Foundation, Inc. // Written by Paolo Bonzini. // // This file is part of GNU Smalltalk. // // GNU Smalltalk is free software; you can redistribute it and/or modify it // under the terms of the GNU General Public License as published by the Free // Software Foundation; either version 2, or (at your option) any later // version. // // GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT // ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or // FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for // more details. // // You should have received a copy of the GNU General Public License along with // GNU Smalltalk; see the file COPYING. If not, write to the Free Software // Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. // /////////////////////////////////////////////////////////////////////// #include "observer-list.h" void observer_list::with_fixed_arg_1 (int new_bc, int bc1, int arg, int bc2) { for (iterator i = begin (); i != end (); i++) (*i)->with_fixed_arg_1 (new_bc, bc1, arg, bc2); } void observer_list::with_fixed_arg_2 (int new_bc, int bc1, int bc2, int arg) { for (iterator i = begin (); i != end (); i++) (*i)->with_fixed_arg_2 (new_bc, bc1, bc2, arg); } smalltalk-3.2.5/superops/search.h0000644000175000017500000001357512123404352013733 00000000000000/* This may look like C code, but it is really -*- C++ -*- */ /* Search algorithm. Copyright (C) 1989-1998, 2000, 2002 Free Software Foundation, Inc. Written by Douglas C. Schmidt and Bruno Haible . This file is part of GNU GPERF. GNU GPERF is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2, or (at your option) any later version. GNU GPERF is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; see the file COPYING. If not, write to the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. */ #ifndef search_h #define search_h 1 #include "keyword-list.h" #include "positions.h" #include "bool-array.h" struct EquivalenceClass; class Search { public: Search (KeywordExt_List *list); ~Search (); void optimize (); private: void prepare (); /* Computes the upper bound on the indices passed to asso_values[], assuming no alpha_increments. */ unsigned int compute_alpha_size () const; /* Computes the unification rules between different asso_values[c], assuming no alpha_increments. */ unsigned int * compute_alpha_unify () const; /* Initializes each keyword's _selchars array. */ void init_selchars_tuple (const Positions& positions, const unsigned int *alpha_unify) const; /* Deletes each keyword's _selchars array. */ void delete_selchars () const; /* Count the duplicate keywords that occur with a given set of positions. */ unsigned int count_duplicates_tuple (const Positions& positions, const unsigned int *alpha_unify) const; /* Find good key positions. */ void find_positions (); /* Count the duplicate keywords that occur with the found set of positions. */ unsigned int count_duplicates_tuple () const; /* Computes the upper bound on the indices passed to asso_values[]. */ unsigned int compute_alpha_size (const unsigned int *alpha_inc) const; /* Computes the unification rules between different asso_values[c]. */ unsigned int * compute_alpha_unify (const Positions& positions, const unsigned int *alpha_inc) const; /* Initializes each keyword's _selchars array. */ void init_selchars_multiset (const Positions& positions, const unsigned int *alpha_unify, const unsigned int *alpha_inc) const; /* Count the duplicate keywords that occur with the given set of positions and a given alpha_inc[] array. */ unsigned int count_duplicates_multiset (const unsigned int *alpha_inc) const; /* Find good _alpha_inc[]. */ void find_alpha_inc (); /* Initializes the asso_values[] related parameters. */ void prepare_asso_values (); EquivalenceClass * compute_partition (bool *undetermined) const; unsigned int count_possible_collisions (EquivalenceClass *partition, unsigned int c) const; bool unchanged_partition (EquivalenceClass *partition, unsigned int c) const; /* Finds some _asso_values[] that fit. */ void find_asso_values (); /* Computes a keyword's hash value, relative to the current _asso_values[], and stores it in keyword->_hash_value. */ int compute_hash (KeywordExt *keyword) const; /* Finds good _asso_values[]. */ void find_good_asso_values (); /* Sorts the keyword list by hash value. */ void sort (); public: /* Linked list of keywords. */ KeywordExt_List * _head; /* Total number of keywords, counting duplicates. */ int _total_keys; /* Maximum length of the longest keyword. */ int _max_key_len; /* Minimum length of the shortest keyword. */ int _min_key_len; /* User-specified or computed key positions. */ Positions _key_positions; /* Adjustments to add to bytes add specific key positions. */ unsigned int * _alpha_inc; /* Size of alphabet. */ unsigned int _alpha_size; /* Alphabet character unification, either the identity or a mapping from upper case characters to lower case characters (and maybe more). */ unsigned int * _alpha_unify; /* Maximum _selchars_length over all keywords. */ unsigned int _max_selchars_length; /* Total number of duplicates that have been moved to _duplicate_link lists (not counting their representatives which stay on the main list). */ int _total_duplicates; /* Counts occurrences of each key set character. _occurrences[c] is the number of times that c occurs among the _selchars of a keyword. */ int * _occurrences; /* Value associated with each character. */ int * _asso_values; private: /* Length of _head list. Number of keywords, not counting duplicates. */ int _list_len; /* Exclusive upper bound for every _asso_values[c]. A power of 2. */ unsigned int _asso_value_max; /* Initial value for asso_values table. -1 means random. */ int _initial_asso_value; /* Jump length when trying alternative values. 0 means random. */ int _jump; /* Maximal possible hash value. */ int _max_hash_value; /* Sparse bit vector for collision detection. */ Bool_Array * _collision_detector; }; #endif smalltalk-3.2.5/superops/hash.cc0000644000175000017500000003116212123404352013537 00000000000000/////////////////////////////// -*- C++ -*- /////////////////////////// // // Program to extract superoperators from a GNU Smalltalk image. // Hash table creation routines (interfacing with GPERF). // /////////////////////////////////////////////////////////////////////// /////////////////////////////////////////////////////////////////////// // // Copyright 2003 Free Software Foundation, Inc. // Written by Paolo Bonzini. // // This file is part of GNU Smalltalk. // // GNU Smalltalk is free software; you can redistribute it and/or modify it // under the terms of the GNU General Public License as published by the Free // Software Foundation; either version 2, or (at your option) any later // version. // // GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT // ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or // FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for // more details. // // You should have received a copy of the GNU General Public License along with // GNU Smalltalk; see the file COPYING. If not, write to the Free Software // Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. // /////////////////////////////////////////////////////////////////////// #include /* defines SCHAR_MAX etc. */ #include #include #include #include "hash.h" #include "options.h" #include "search.h" #include "keyword.h" #include "keyword-list.h" #include "positions.h" #include class Output { public: /* Constructor. */ Output (std::ostream &os, KeywordExt_List *head, const char *wordlist_eltype, const int *asso_values); /* Generates the hash function and the key word recognizer function. */ void output () const; private: /* Computes the minimum and maximum hash values, and stores them in _min_hash_value and _max_hash_value. */ void compute_min_max (); /* Outputs the maximum and minimum hash values etc. */ void output_constants (struct Output_Constants&) const; /* Outputs a keyword, as an array of bytes. */ void output_key (const char *key, int len) const; /* Same as above, but including the other fields and enclosed in braces. */ void output_keyword_entry (KeywordExt *temp, const char *indent) const; /* Outputs several null entries. */ void output_keyword_blank_entries (int count, const char *indent) const; /* Outputs a type with a const specifier, followed by a space. */ void output_const_type (const char *type_string) const; /* Generates C code for the hash function that returns the proper encoding for each keyword. */ void output_asso_values () const; /* Prints out the array containing the keywords for the hash function. */ void output_keyword_table () const; /* Output destination. */ std::ostream & _os; /* Linked list of keywords. */ KeywordExt_List * _head; /* Element type of keyword array. */ const char * _wordlist_eltype; /* Minimum hash value for all keywords. */ int _min_hash_value; /* Maximum hash value for all keywords. */ int _max_hash_value; /* Value associated with each character. */ const int * const _asso_values; }; /* Returns the smallest unsigned C type capable of holding integers up to N. */ static const char * smallest_integral_type (int n) { if (n <= UCHAR_MAX) return "unsigned char"; if (n <= USHRT_MAX) return "unsigned short"; return "unsigned int"; } /* Returns the smallest signed C type capable of holding integers from MIN to MAX. */ static const char * smallest_integral_type (int min, int max) { if (min >= SCHAR_MIN && max <= SCHAR_MAX) return "signed char"; if (min >= SHRT_MIN && max <= SHRT_MAX) return "short"; return "int"; } /* ------------------------------------------------------------------------- */ /* Constructor. Note about the keyword list starting at head: - The list is ordered by increasing _hash_value. This has been achieved by Search::sort(). - Duplicates, i.e. keywords with the same _selchars set, are chained through the _duplicate_link pointer. Only one representative per duplicate equivalence class remains on the linear keyword list. - Accidental duplicates, i.e. keywords for which the _asso_values[] search couldn't achieve different hash values, cannot occur on the linear keyword list. Search::optimize would catch this mistake. */ Output::Output (std::ostream &os, KeywordExt_List *head, const char *wordlist_eltype, const int *asso_values) : _os(os), _head (head), _wordlist_eltype (wordlist_eltype), _asso_values (asso_values) { compute_min_max (); } /* ------------------------------------------------------------------------- */ /* Computes the minimum and maximum hash values, and stores them in _min_hash_value and _max_hash_value. */ void Output::compute_min_max () { /* Since the list is already sorted by hash value all we need to do is to look at the first and the last element of the list. */ _min_hash_value = _head->first()->_hash_value; KeywordExt_List *temp; for (temp = _head; temp->rest(); temp = temp->rest()) ; _max_hash_value = temp->first()->_hash_value; } /* -------------------- Output_Constants and subclasses -------------------- */ /* This class outputs an enumeration using 'enum'. */ struct Output_Constants { virtual void output_start (); virtual void output_item (const char *name, int value); virtual void output_end (); Output_Constants (std::ostream &os, const char *indent) : _os(os), _indentation (indent) {} virtual ~Output_Constants () {} private: std::ostream &_os; const char *_indentation; bool _pending_comma; }; void Output_Constants::output_start () { _os << _indentation << "enum" << std::endl << _indentation << " {" << std::endl; _pending_comma = false; } void Output_Constants::output_item (const char *name, int value) { if (_pending_comma) _os << ',' << std::endl; _os << _indentation << " " << name << " = " << value; _pending_comma = true; } void Output_Constants::output_end () { if (_pending_comma) _os << std::endl; _os << _indentation << " };" << std::endl << std::endl; } /* Outputs the maximum and minimum hash values etc. */ void Output::output_constants (struct Output_Constants& style) const { style.output_start (); style.output_item ("MIN_HASH_VALUE", _min_hash_value); style.output_item ("MAX_HASH_VALUE", _max_hash_value); style.output_end (); } /* ------------------------------------------------------------------------- */ /* Outputs a keyword, as an array of bytes. */ void Output::output_key (const char *key, int len) const { _os << '{'; if (key[len-1] == 0) { while (len > 0 && key[len-1] == 0) len--; len++; } for (; len > 0; len--) { unsigned char c = static_cast(*key++); _os << ' ' << (int) c; if (len > 1) _os << ','; } _os << '}'; } /* ------------------------------------------------------------------------- */ /* Outputs a type with a const specifier, followed by a space. */ void Output::output_const_type (const char *type_string) const { if (type_string[strlen(type_string)-1] == '*') /* For pointer types, put the 'const' after the type. */ _os << type_string << " const "; else /* For scalar or struct types, put the 'const' before the type. */ _os << "const " << type_string << ' '; } /* --------------------- Output_Compare and subclasses --------------------- */ /* Generates C code for the hash function that returns the proper encoding for each keyword. The hash function has the signature unsigned int (const char *str, unsigned int len). */ void Output::output_asso_values () const { _os << " static const " << smallest_integral_type (_max_hash_value + 1) << " asso_values[] =" << std::endl << " {"; const int columns = 10; /* Calculate maximum number of digits required for MAX_HASH_VALUE. */ int field_width = 2; for (int trunc = _max_hash_value; (trunc /= 10) > 0;) field_width++; for (unsigned int count = 0; count < 256; count++) { if (count > 0) _os << ','; if ((count % columns) == 0) _os << std::endl << " "; _os << std::setw(field_width) << _asso_values[count] << std::setw(0); } _os << std::endl << " };" << std::endl; } /* ------------------------------------------------------------------------- */ void Output::output_keyword_entry (KeywordExt *temp, const char *indent) const { _os << indent << " {"; output_key (temp->_allchars, temp->_allchars_length); if (strlen (temp->_rest) > 0) _os << ", " << temp->_rest; _os << '}'; } void Output::output_keyword_blank_entries (int count, const char *indent) const { int column = 0; for (int i = 0; i < count; i++) { if ((column % 6) == 0) { if (i > 0) _os << ',' << std::endl; _os << indent << " "; } else { if (i > 0) _os << ", "; } _os << "{{}, -1 }"; column++; } } /* Prints out the array containing the keywords for the hash function. */ void Output::output_keyword_table () const { const char *indent = " "; int index; KeywordExt_List *temp; _os << indent << "static "; output_const_type (_wordlist_eltype); _os << "keylist[] =" << std::endl << indent << " {" << std::endl; /* Generate an array of reserved words at appropriate locations. */ for (temp = _head, index = 0; temp; temp = temp->rest()) { KeywordExt *keyword = temp->first(); if (index > 0) { _os << ',' << std::endl; if (index < keyword->_hash_value) { /* Some blank entries. */ output_keyword_blank_entries (keyword->_hash_value - index, indent); _os << ',' << std::endl; index = keyword->_hash_value; } } keyword->_final_index = index; output_keyword_entry (keyword, indent); index++; } if (index > 0) _os << std::endl; _os << indent << " };" << std::endl << std::endl; } /* ------------------------------------------------------------------------- */ /* Generates the hash function and the key word recognizer function based upon the user's Options. */ void Output::output () const { Output_Constants style (_os, " "); output_constants (style); output_asso_values (); output_keyword_table (); } hash_builder::hash_builder () : list1(NULL), list2(NULL) { option.set (RANDOM); option.set (NOLENGTH); }; void hash_builder::with_fixed_arg_1 (int new_bc, int bc1, int arg, int bc2) { char *c = new char[3]; c[0] = bc1; c[1] = bc2; c[2] = arg; char *rest = new char[10]; sprintf (rest, "%d", new_bc); KeywordExt *k = new KeywordExt(c, 3, rest); KeywordExt_List *new_head = new KeywordExt_List(k); new_head->rest() = list1; list1 = new_head; } void hash_builder::with_fixed_arg_2 (int new_bc, int bc1, int bc2, int arg) { char *c = new char[3]; c[0] = bc1; c[1] = bc2; c[2] = arg; char *rest = new char[10]; sprintf (rest, "%d", new_bc); KeywordExt *k = new KeywordExt(c, 3, rest); KeywordExt_List *new_head = new KeywordExt_List(k); new_head->rest() = list2; list2 = new_head; } void hash_builder::search (Positions &p, KeywordExt_List *list, const char *type, const char *file) { std::cout << "Hash function written to " << file << ", hash positions "; std::cout.flush (); p.print(); fflush (stdout); std::cout << std::endl; option._key_positions = p; option.set (POSITIONS); Search searcher (list); searcher.optimize (); std::ofstream fs (file); fs << "/* Automagically generated by superops, do not edit! */" << std::endl; if (!fs) { std::cerr << "Cannot open output file '" << file << '\'' << std::endl; std::exit (1); } Output outputter (fs, searcher._head, type, searcher._asso_values); outputter.output (); } void hash_builder::output1 () { Positions p; p.add(0); p.add(1); p.add(2); search (p, list1, "struct superop_with_fixed_arg_1_type", "superop1.inl"); } void hash_builder::output2 () { Positions p; p.add(0); p.add(1); p.add(2); search (p, list2, "struct superop_with_fixed_arg_2_type", "superop2.inl"); } void hash_builder::output () { output1 (); output2 (); } smalltalk-3.2.5/superops/keyword.cc0000644000175000017500000001137112123404352014300 00000000000000/* Keyword data. Copyright (C) 1989-1998, 2000, 2002 Free Software Foundation, Inc. Written by Douglas C. Schmidt and Bruno Haible . This file is part of GNU GPERF. GNU GPERF is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2, or (at your option) any later version. GNU GPERF is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; see the file COPYING. If not, write to the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. */ /* Specification. */ #include "keyword.h" #include #include #include #include "positions.h" /* --------------------------- KeywordExt class --------------------------- */ /* Sort a small set of 'unsigned int', base[0..len-1], in place. */ static inline void sort_char_set (unsigned int *base, int len) { /* Bubble sort is sufficient here. */ for (int i = 1; i < len; i++) { int j; unsigned int tmp; for (j = i, tmp = base[j]; j > 0 && tmp < base[j - 1]; j--) base[j] = base[j - 1]; base[j] = tmp; } } /* Initializes selchars and selchars_length. General idea: The hash function will be computed as asso_values[allchars[key_pos[0]]] + asso_values[allchars[key_pos[1]]] + ... We compute selchars as the multiset { allchars[key_pos[0]], allchars[key_pos[1]], ... } so that the hash function becomes asso_values[selchars[0]] + asso_values[selchars[1]] + ... Furthermore we sort the selchars array, to ease detection of duplicates later. More in detail: The arguments alpha_unify (used for case-insensitive hash functions) and alpha_inc (used to disambiguate permutations) apply slight modifications. The hash function will be computed as sum (j=0,1,...: k = key_pos[j]: asso_values[alpha_unify[allchars[k]+alpha_inc[k]]]) + (allchars_length if !option[NOLENGTH], 0 otherwise). We compute selchars as the multiset { alpha_unify[allchars[k]+alpha_inc[k]] : j=0,1,..., k = key_pos[j] } so that the hash function becomes asso_values[selchars[0]] + asso_values[selchars[1]] + ... + (allchars_length if !option[NOLENGTH], 0 otherwise). */ unsigned int * KeywordExt::init_selchars_low (const Positions& positions, const unsigned int *alpha_unify, const unsigned int *alpha_inc) { /* Iterate through the list of positions, initializing selchars (via ptr). */ PositionIterator iter = positions.iterator(_allchars_length); unsigned int *key_set = new unsigned int[iter.remaining()]; unsigned int *ptr = key_set; for (int i; (i = iter.next ()) != PositionIterator::EOS; ) { unsigned int c; if (i == Positions::LASTCHAR) /* Special notation for last KEY position, i.e. '$'. */ c = static_cast(_allchars[_allchars_length - 1]); else if (i < _allchars_length) { /* Within range of KEY length, so we'll keep it. */ c = static_cast(_allchars[i]); if (alpha_inc) c += alpha_inc[i]; } else /* Out of range of KEY length, the iterator should not have produced this. */ abort (); if (alpha_unify) c = alpha_unify[c]; *ptr = c; ptr++; } _selchars = key_set; _selchars_length = ptr - key_set; return key_set; } void KeywordExt::init_selchars_tuple (const Positions& positions, const unsigned int *alpha_unify) { init_selchars_low (positions, alpha_unify, NULL); } void KeywordExt::init_selchars_multiset (const Positions& positions, const unsigned int *alpha_unify, const unsigned int *alpha_inc) { unsigned int *selchars = init_selchars_low (positions, alpha_unify, alpha_inc); /* Sort the selchars elements alphabetically. */ sort_char_set (selchars, _selchars_length); } /* Deletes selchars. */ void KeywordExt::delete_selchars () { delete[] const_cast(_selchars); } /* ------------------------- Keyword_Factory class ------------------------- */ Keyword_Factory::Keyword_Factory () { } Keyword_Factory::~Keyword_Factory () { } /* ------------------------------------------------------------------------- */ char empty_string[1] = ""; #ifndef __OPTIMIZE__ #define INLINE /* not inline */ #include "keyword.icc" #undef INLINE #endif /* not defined __OPTIMIZE__ */ smalltalk-3.2.5/superops/search.cc0000644000175000017500000016333112123404352014065 00000000000000/* Search algorithm. Copyright (C) 1989-1998, 2000, 2002 Free Software Foundation, Inc. Written by Douglas C. Schmidt and Bruno Haible . This file is part of GNU GPERF. GNU GPERF is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2, or (at your option) any later version. GNU GPERF is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; see the file COPYING. If not, write to the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. */ /* Specification. */ #include "search.h" #include #include /* declares exit(), rand(), srand() */ #include /* declares memset(), memcmp() */ #include /* declares time() */ #include /* declares exp() */ #include /* defines INT_MIN, INT_MAX, UINT_MAX */ #include "options.h" #include "hash-table.h" /* ================================ Theory ================================= */ /* The general form of the hash function is hash (keyword) = sum (asso_values[keyword[i] + alpha_inc[i]] : i in Pos) + len (keyword) where Pos is a set of byte positions, each alpha_inc[i] is a nonnegative integer, each asso_values[c] is a nonnegative integer, len (keyword) is the keyword's length if !option[NOLENGTH], or 0 otherwise. Theorem 1: If all keywords are different, there is a set Pos such that all tuples (keyword[i] : i in Pos) are different. Theorem 2: If all tuples (keyword[i] : i in Pos) are different, there are nonnegative integers alpha_inc[i] such that all multisets {keyword[i] + alpha_inc[i] : i in Pos} are different. Define selchars[keyword] := {keyword[i] + alpha_inc[i] : i in Pos}. Theorem 3: If all multisets selchars[keyword] are different, there are nonnegative integers asso_values[c] such that all hash values sum (asso_values[c] : c in selchars[keyword]) are different. Based on these three facts, we find the hash function in three steps: Step 1 (Finding good byte positions): Find a set Pos, as small as possible, such that all tuples (keyword[i] : i in Pos) are different. Step 2 (Finding good alpha increments): Find nonnegative integers alpha_inc[i], as many of them as possible being zero, and the others being as small as possible, such that all multisets {keyword[i] + alpha_inc[i] : i in Pos} are different. Step 3 (Finding good asso_values): Find asso_values[c] such that all hash (keyword) are different. In other words, each step finds a projection that is injective on the given finite set: proj1 : String --> Map (Pos --> N) proj2 : Map (Pos --> N) --> Map (Pos --> N) / S(Pos) proj3 : Map (Pos --> N) / S(Pos) --> N where N denotes the set of nonnegative integers, Map (A --> B) := Hom_Set (A, B) is the set of maps from A to B, and S(Pos) is the symmetric group over Pos. This was the theory for option[NOLENGTH]; if !option[NOLENGTH], slight modifications apply: proj1 : String --> Map (Pos --> N) x N proj2 : Map (Pos --> N) x N --> Map (Pos --> N) / S(Pos) x N proj3 : Map (Pos --> N) / S(Pos) x N --> N For a case-insensitive hash function, the general form is hash (keyword) = sum (asso_values[alpha_unify[keyword[i] + alpha_inc[i]]] : i in Pos) + len (keyword) where alpha_unify[c] is chosen so that an upper/lower case change in keyword[i] doesn't change alpha_unify[keyword[i] + alpha_inc[i]]. */ /* ==================== Initialization and Preparation ===================== */ Search::Search (KeywordExt_List *list) : _head (list) { } void Search::prepare () { /* Compute the total number of keywords. */ _total_keys = 0; for (KeywordExt_List *temp = _head; temp; temp = temp->rest()) _total_keys++; /* Compute the minimum and maximum keyword length. */ _max_key_len = INT_MIN; _min_key_len = INT_MAX; for (KeywordExt_List *temp = _head; temp; temp = temp->rest()) { KeywordExt *keyword = temp->first(); if (_max_key_len < keyword->_allchars_length) _max_key_len = keyword->_allchars_length; if (_min_key_len > keyword->_allchars_length) _min_key_len = keyword->_allchars_length; } /* Exit program if an empty string is used as keyword, since the comparison expressions don't work correctly for looking up an empty string. */ if (_min_key_len == 0) { fprintf (stderr, "Empty input keyword is not allowed.\n" "To recognize an empty input keyword, your code should check for\n" "len == 0 before calling the gperf generated lookup function.\n"); exit (1); } /* Exit program if the characters in the keywords are not in the required range. */ if (option[SEVENBIT]) for (KeywordExt_List *temp = _head; temp; temp = temp->rest()) { KeywordExt *keyword = temp->first(); const char *k = keyword->_allchars; for (int i = keyword->_allchars_length; i > 0; k++, i--) if (!(static_cast(*k) < 128)) { fprintf (stderr, "Option --seven-bit has been specified,\n" "but keyword \"%.*s\" contains non-ASCII characters.\n" "Try removing option --seven-bit.\n", keyword->_allchars_length, keyword->_allchars); exit (1); } } } /* ====================== Finding good byte positions ====================== */ /* Computes the upper bound on the indices passed to asso_values[], assuming no alpha_increments. */ unsigned int Search::compute_alpha_size () const { return (option[SEVENBIT] ? 128 : 256); } /* Computes the unification rules between different asso_values[c], assuming no alpha_increments. */ unsigned int * Search::compute_alpha_unify () const { if (option[UPPERLOWER]) { /* Uppercase to lowercase mapping. */ unsigned int alpha_size = compute_alpha_size(); unsigned int *alpha_unify = new unsigned int[alpha_size]; for (unsigned int c = 0; c < alpha_size; c++) alpha_unify[c] = c; for (unsigned int c = 'A'; c <= 'Z'; c++) alpha_unify[c] = c + ('a'-'A'); return alpha_unify; } else /* Identity mapping. */ return NULL; } /* Initializes each keyword's _selchars array. */ void Search::init_selchars_tuple (const Positions& positions, const unsigned int *alpha_unify) const { for (KeywordExt_List *temp = _head; temp; temp = temp->rest()) temp->first()->init_selchars_tuple(positions, alpha_unify); } /* Deletes each keyword's _selchars array. */ void Search::delete_selchars () const { for (KeywordExt_List *temp = _head; temp; temp = temp->rest()) temp->first()->delete_selchars(); } /* Count the duplicate keywords that occur with a given set of positions. In other words, it returns the difference # K - # proj1 (K) where K is the multiset of given keywords. */ unsigned int Search::count_duplicates_tuple (const Positions& positions, const unsigned int *alpha_unify) const { /* Run through the keyword list and count the duplicates incrementally. The result does not depend on the order of the keyword list, thanks to the formula above. */ init_selchars_tuple (positions, alpha_unify); unsigned int count = 0; { Hash_Table representatives (_total_keys, option[NOLENGTH]); for (KeywordExt_List *temp = _head; temp; temp = temp->rest()) { KeywordExt *keyword = temp->first(); if (representatives.insert (keyword)) count++; } } delete_selchars (); return count; } /* Find good key positions. */ void Search::find_positions () { /* If the user gave the key positions, we use them. */ if (option[POSITIONS]) { _key_positions = option.get_key_positions(); return; } /* Compute preliminary alpha_unify table. */ unsigned int *alpha_unify = compute_alpha_unify (); /* 1. Find positions that must occur in order to distinguish duplicates. */ Positions mandatory; if (!option[DUP]) { for (KeywordExt_List *l1 = _head; l1 && l1->rest(); l1 = l1->rest()) { KeywordExt *keyword1 = l1->first(); for (KeywordExt_List *l2 = l1->rest(); l2; l2 = l2->rest()) { KeywordExt *keyword2 = l2->first(); /* If keyword1 and keyword2 have the same length and differ in just one position, and it is not the last character, this position is mandatory. */ if (keyword1->_allchars_length == keyword2->_allchars_length) { int n = keyword1->_allchars_length; int i; for (i = 0; i < n - 1; i++) { unsigned char c1 = keyword1->_allchars[i]; unsigned char c2 = keyword2->_allchars[i]; if (option[UPPERLOWER]) { if (c1 >= 'A' && c1 <= 'Z') c1 += 'a' - 'A'; if (c2 >= 'A' && c2 <= 'Z') c2 += 'a' - 'A'; } if (c1 != c2) break; } if (i < n - 1) { int j; for (j = i + 1; j < n; j++) { unsigned char c1 = keyword1->_allchars[j]; unsigned char c2 = keyword2->_allchars[j]; if (option[UPPERLOWER]) { if (c1 >= 'A' && c1 <= 'Z') c1 += 'a' - 'A'; if (c2 >= 'A' && c2 <= 'Z') c2 += 'a' - 'A'; } if (c1 != c2) break; } if (j >= n) { /* Position i is mandatory. */ if (!mandatory.contains (i)) mandatory.add (i); } } } } } } /* 2. Add positions, as long as this decreases the duplicates count. */ int imax = (_max_key_len - 1 < Positions::MAX_KEY_POS - 1 ? _max_key_len - 1 : Positions::MAX_KEY_POS - 1); Positions current = mandatory; unsigned int current_duplicates_count = count_duplicates_tuple (current, alpha_unify); for (;;) { Positions best; unsigned int best_duplicates_count = UINT_MAX; for (int i = imax; i >= -1; i--) if (!current.contains (i)) { Positions tryal = current; tryal.add (i); unsigned int try_duplicates_count = count_duplicates_tuple (tryal, alpha_unify); /* We prefer 'try' to 'best' if it produces less duplicates, or if it produces the same number of duplicates but with a more efficient hash function. */ if (try_duplicates_count < best_duplicates_count || (try_duplicates_count == best_duplicates_count && i >= 0)) { best = tryal; best_duplicates_count = try_duplicates_count; } } /* Stop adding positions when it gives no improvement. */ if (best_duplicates_count >= current_duplicates_count) break; current = best; current_duplicates_count = best_duplicates_count; } /* 3. Remove positions, as long as this doesn't increase the duplicates count. */ for (;;) { Positions best; unsigned int best_duplicates_count = UINT_MAX; for (int i = imax; i >= -1; i--) if (current.contains (i) && !mandatory.contains (i)) { Positions tryal = current; tryal.remove (i); unsigned int try_duplicates_count = count_duplicates_tuple (tryal, alpha_unify); /* We prefer 'try' to 'best' if it produces less duplicates, or if it produces the same number of duplicates but with a more efficient hash function. */ if (try_duplicates_count < best_duplicates_count || (try_duplicates_count == best_duplicates_count && i == -1)) { best = tryal; best_duplicates_count = try_duplicates_count; } } /* Stop removing positions when it gives no improvement. */ if (best_duplicates_count > current_duplicates_count) break; current = best; current_duplicates_count = best_duplicates_count; } /* 4. Replace two positions by one, as long as this doesn't increase the duplicates count. */ for (;;) { Positions best; unsigned int best_duplicates_count = UINT_MAX; for (int i1 = imax; i1 >= -1; i1--) if (current.contains (i1) && !mandatory.contains (i1)) for (int i2 = imax; i2 >= -1; i2--) if (current.contains (i2) && !mandatory.contains (i2) && i2 != i1) for (int i3 = imax; i3 >= 0; i3--) if (!current.contains (i3)) { Positions tryal = current; tryal.remove (i1); tryal.remove (i2); tryal.add (i3); unsigned int try_duplicates_count = count_duplicates_tuple (tryal, alpha_unify); /* We prefer 'try' to 'best' if it produces less duplicates, or if it produces the same number of duplicates but with a more efficient hash function. */ if (try_duplicates_count < best_duplicates_count || (try_duplicates_count == best_duplicates_count && (i1 == -1 || i2 == -1 || i3 >= 0))) { best = tryal; best_duplicates_count = try_duplicates_count; } } /* Stop removing positions when it gives no improvement. */ if (best_duplicates_count > current_duplicates_count) break; current = best; current_duplicates_count = best_duplicates_count; } /* That's it. Hope it's good enough. */ _key_positions = current; if (option[DEBUG]) { /* Print the result. */ fprintf (stderr, "\nComputed positions: "); PositionReverseIterator iter = _key_positions.reviterator(); bool seen_lastchar = false; bool first = true; for (int i; (i = iter.next ()) != PositionReverseIterator::EOS; ) { if (!first) fprintf (stderr, ", "); if (i == Positions::LASTCHAR) seen_lastchar = true; else { fprintf (stderr, "%d", i + 1); first = false; } } if (seen_lastchar) { if (!first) fprintf (stderr, ", "); fprintf (stderr, "$"); } fprintf (stderr, "\n"); } /* Free preliminary alpha_unify table. */ delete[] alpha_unify; } /* Count the duplicate keywords that occur with the found set of positions. In other words, it returns the difference # K - # proj1 (K) where K is the multiset of given keywords. */ unsigned int Search::count_duplicates_tuple () const { unsigned int *alpha_unify = compute_alpha_unify (); unsigned int count = count_duplicates_tuple (_key_positions, alpha_unify); delete[] alpha_unify; return count; } /* ===================== Finding good alpha increments ===================== */ /* Computes the upper bound on the indices passed to asso_values[]. */ unsigned int Search::compute_alpha_size (const unsigned int *alpha_inc) const { unsigned int max_alpha_inc = 0; for (int i = 0; i < _max_key_len; i++) if (max_alpha_inc < alpha_inc[i]) max_alpha_inc = alpha_inc[i]; return (option[SEVENBIT] ? 128 : 256) + max_alpha_inc; } /* Computes the unification rules between different asso_values[c]. */ unsigned int * Search::compute_alpha_unify (const Positions& positions, const unsigned int *alpha_inc) const { if (option[UPPERLOWER]) { /* Without alpha increments, we would simply unify 'A' -> 'a', ..., 'Z' -> 'z'. But when a keyword contains at position i a character c, we have the constraint asso_values[tolower(c) + alpha_inc[i]] == asso_values[toupper(c) + alpha_inc[i]]. This introduces a unification toupper(c) + alpha_inc[i] -> tolower(c) + alpha_inc[i]. Note that this unification can extend outside the range of ASCII letters! But still every unified character pair is at a distance of 'a'-'A' = 32, or (after chained unification) at a multiple of 32. So in the end the alpha_unify vector has the form c -> c + 32 * f(c) where f(c) is a nonnegative integer. */ unsigned int alpha_size = compute_alpha_size (alpha_inc); unsigned int *alpha_unify = new unsigned int[alpha_size]; for (unsigned int c = 0; c < alpha_size; c++) alpha_unify[c] = c; for (KeywordExt_List *temp = _head; temp; temp = temp->rest()) { KeywordExt *keyword = temp->first(); /* Iterate through the selected character positions. */ PositionIterator iter = positions.iterator(keyword->_allchars_length); for (int i; (i = iter.next ()) != PositionIterator::EOS; ) { unsigned int c; if (i == Positions::LASTCHAR) c = static_cast(keyword->_allchars[keyword->_allchars_length - 1]); else if (i < keyword->_allchars_length) c = static_cast(keyword->_allchars[i]); else abort (); if (c >= 'A' && c <= 'Z') c += 'a' - 'A'; if (c >= 'a' && c <= 'z') { if (i != Positions::LASTCHAR) c += alpha_inc[i]; /* Unify c with c - ('a'-'A'). */ unsigned int d = alpha_unify[c]; unsigned int b = c - ('a'-'A'); for (int a = b; a >= 0 && alpha_unify[a] == b; a -= ('a'-'A')) alpha_unify[a] = d; } } } return alpha_unify; } else /* Identity mapping. */ return NULL; } /* Initializes each keyword's _selchars array. */ void Search::init_selchars_multiset (const Positions& positions, const unsigned int *alpha_unify, const unsigned int *alpha_inc) const { for (KeywordExt_List *temp = _head; temp; temp = temp->rest()) temp->first()->init_selchars_multiset(positions, alpha_unify, alpha_inc); } /* Count the duplicate keywords that occur with the given set of positions and a given alpha_inc[] array. In other words, it returns the difference # K - # proj2 (proj1 (K)) where K is the multiset of given keywords. */ unsigned int Search::count_duplicates_multiset (const unsigned int *alpha_inc) const { /* Run through the keyword list and count the duplicates incrementally. The result does not depend on the order of the keyword list, thanks to the formula above. */ unsigned int *alpha_unify = compute_alpha_unify (_key_positions, alpha_inc); init_selchars_multiset (_key_positions, alpha_unify, alpha_inc); unsigned int count = 0; { Hash_Table representatives (_total_keys, option[NOLENGTH]); for (KeywordExt_List *temp = _head; temp; temp = temp->rest()) { KeywordExt *keyword = temp->first(); if (representatives.insert (keyword)) count++; } } delete_selchars (); delete[] alpha_unify; return count; } /* Find good _alpha_inc[]. */ void Search::find_alpha_inc () { /* The goal is to choose _alpha_inc[] such that it doesn't introduce artificial duplicates. In other words, the goal is # proj2 (proj1 (K)) = # proj1 (K). */ unsigned int duplicates_goal = count_duplicates_tuple (); /* Start with zero increments. This is sufficient in most cases. */ unsigned int *current = new unsigned int [_max_key_len]; for (int i = 0; i < _max_key_len; i++) current[i] = 0; unsigned int current_duplicates_count = count_duplicates_multiset (current); if (current_duplicates_count > duplicates_goal) { /* Look which _alpha_inc[i] we are free to increment. */ unsigned int nindices; { nindices = 0; PositionIterator iter = _key_positions.iterator(_max_key_len); for (;;) { int key_pos = iter.next (); if (key_pos == PositionIterator::EOS) break; if (key_pos != Positions::LASTCHAR) nindices++; } } unsigned int *indices = new unsigned int[nindices]; { unsigned int j = 0; PositionIterator iter = _key_positions.iterator(_max_key_len); for (;;) { int key_pos = iter.next (); if (key_pos == PositionIterator::EOS) break; if (key_pos != Positions::LASTCHAR) indices[j++] = key_pos; } if (!(j == nindices)) abort (); } /* Perform several rounds of searching for a good alpha increment. Each round reduces the number of artificial collisions by adding an increment in a single key position. */ unsigned int *best = new unsigned int[_max_key_len]; unsigned int *tryal = new unsigned int[_max_key_len]; do { /* An increment of 1 is not always enough. Try higher increments also. */ for (unsigned int inc = 1; ; inc++) { unsigned int best_duplicates_count = UINT_MAX; for (unsigned int j = 0; j < nindices; j++) { memcpy (tryal, current, _max_key_len * sizeof (unsigned int)); tryal[indices[j]] += inc; unsigned int try_duplicates_count = count_duplicates_multiset (tryal); /* We prefer 'try' to 'best' if it produces less duplicates. */ if (try_duplicates_count < best_duplicates_count) { memcpy (best, tryal, _max_key_len * sizeof (unsigned int)); best_duplicates_count = try_duplicates_count; } } /* Stop this round when we got an improvement. */ if (best_duplicates_count < current_duplicates_count) { memcpy (current, best, _max_key_len * sizeof (unsigned int)); current_duplicates_count = best_duplicates_count; break; } } } while (current_duplicates_count > duplicates_goal); delete[] tryal; delete[] best; if (option[DEBUG]) { /* Print the result. */ fprintf (stderr, "\nComputed alpha increments: "); bool first = true; for (unsigned int j = nindices; j-- > 0; ) if (current[indices[j]] != 0) { if (!first) fprintf (stderr, ", "); fprintf (stderr, "%u:+%u", indices[j] + 1, current[indices[j]]); first = false; } fprintf (stderr, "\n"); } delete[] indices; } _alpha_inc = current; _alpha_size = compute_alpha_size (_alpha_inc); _alpha_unify = compute_alpha_unify (_key_positions, _alpha_inc); } /* ======================= Finding good asso_values ======================== */ /* Initializes the asso_values[] related parameters. */ void Search::prepare_asso_values () { KeywordExt_List *temp; /* Initialize each keyword's _selchars array. */ init_selchars_multiset(_key_positions, _alpha_unify, _alpha_inc); /* Compute the maximum _selchars_length over all keywords. */ _max_selchars_length = _key_positions.iterator(_max_key_len).remaining(); /* Check for duplicates, i.e. keywords with the same _selchars array (and - if !option[NOLENGTH] - also the same length). We deal with these by building an equivalence class, so that only 1 keyword is representative of the entire collection. Only this representative remains in the keyword list; the others are accessible through the _duplicate_link chain, starting at the representative. This *greatly* simplifies processing during later stages of the program. Set _total_duplicates and _list_len = _total_keys - _total_duplicates. */ { _list_len = _total_keys; _total_duplicates = 0; /* Make hash table for efficiency. */ Hash_Table representatives (_list_len, option[NOLENGTH]); KeywordExt_List *prev = NULL; /* list node before temp */ for (temp = _head; temp; ) { KeywordExt *keyword = temp->first(); KeywordExt *other_keyword = representatives.insert (keyword); KeywordExt_List *garbage = NULL; if (other_keyword) { _total_duplicates++; _list_len--; /* Remove keyword from the main list. */ prev->rest() = temp->rest(); garbage = temp; /* And insert it on other_keyword's duplicate list. */ keyword->_duplicate_link = other_keyword->_duplicate_link; other_keyword->_duplicate_link = keyword; /* Complain if user hasn't enabled the duplicate option. */ if (!option[DUP] || option[DEBUG]) { fprintf (stderr, "Key link: \"%.*s\" = \"%.*s\", with key set \"", keyword->_allchars_length, keyword->_allchars, other_keyword->_allchars_length, other_keyword->_allchars); for (int j = 0; j < keyword->_selchars_length; j++) putc (keyword->_selchars[j], stderr); fprintf (stderr, "\".\n"); } } else { keyword->_duplicate_link = NULL; prev = temp; } temp = temp->rest(); if (garbage) delete garbage; } if (option[DEBUG]) representatives.dump(); } /* Exit program if duplicates exists and option[DUP] not set, since we don't want to continue in this case. (We don't want to turn on option[DUP] implicitly, because the generated code is usually much slower. */ if (_total_duplicates) { if (option[DUP]) fprintf (stderr, "%d input keys have identical hash values, examine output carefully...\n", _total_duplicates); else { fprintf (stderr, "%d input keys have identical hash values,\n", _total_duplicates); if (option[POSITIONS]) fprintf (stderr, "try different key positions or use option -D.\n"); else fprintf (stderr, "use option -D.\n"); exit (1); } } /* Compute the occurrences of each character in the alphabet. */ _occurrences = new int[_alpha_size]; memset (_occurrences, 0, _alpha_size * sizeof (_occurrences[0])); for (temp = _head; temp; temp = temp->rest()) { KeywordExt *keyword = temp->first(); const unsigned int *ptr = keyword->_selchars; for (int count = keyword->_selchars_length; count > 0; ptr++, count--) _occurrences[*ptr]++; } /* Memory allocation. */ _asso_values = new int[_alpha_size]; int non_linked_length = _list_len; unsigned int asso_value_max; asso_value_max = static_cast(non_linked_length * option.get_size_multiple()); /* Round up to the next power of two. This makes it easy to ensure an _asso_value[c] is >= 0 and < asso_value_max. Also, the jump value being odd, it guarantees that Search::try_asso_value() will iterate through different values for _asso_value[c]. */ if (asso_value_max == 0) asso_value_max = 1; asso_value_max |= asso_value_max >> 1; asso_value_max |= asso_value_max >> 2; asso_value_max |= asso_value_max >> 4; asso_value_max |= asso_value_max >> 8; asso_value_max |= asso_value_max >> 16; asso_value_max++; _asso_value_max = asso_value_max; /* Given the bound for _asso_values[c], we have a bound for the possible hash values, as computed in compute_hash(). */ _max_hash_value = (option[NOLENGTH] ? 0 : _max_key_len) + (_asso_value_max - 1) * _max_selchars_length; /* Allocate a sparse bit vector for detection of collisions of hash values. */ _collision_detector = new Bool_Array (_max_hash_value + 1); if (option[DEBUG]) { fprintf (stderr, "total non-linked keys = %d\nmaximum associated value is %d" "\nmaximum size of generated hash table is %d\n", non_linked_length, asso_value_max, _max_hash_value); int field_width; field_width = 0; { for (KeywordExt_List *temp = _head; temp; temp = temp->rest()) { KeywordExt *keyword = temp->first(); if (field_width < keyword->_selchars_length) field_width = keyword->_selchars_length; } } fprintf (stderr, "\ndumping the keyword list without duplicates\n"); fprintf (stderr, "keyword #, %*s, keyword\n", field_width, "keysig"); int i = 0; for (KeywordExt_List *temp = _head; temp; temp = temp->rest()) { KeywordExt *keyword = temp->first(); fprintf (stderr, "%9d, ", ++i); if (field_width > keyword->_selchars_length) fprintf (stderr, "%*s", field_width - keyword->_selchars_length, ""); for (int j = 0; j < keyword->_selchars_length; j++) putc (keyword->_selchars[j], stderr); fprintf (stderr, ", %.*s\n", keyword->_allchars_length, keyword->_allchars); } fprintf (stderr, "\nend of keyword list\n\n"); } if (option[RANDOM] || option.get_jump () == 0) /* We will use rand(), so initialize the random number generator. */ srand (static_cast(time (0))); _initial_asso_value = (option[RANDOM] ? -1 : option.get_initial_asso_value ()); _jump = option.get_jump (); } /* Finds some _asso_values[] that fit. */ /* The idea is to choose the _asso_values[] one by one, in a way that a choice that has been made never needs to be undone later. This means that we split the work into several steps. Each step chooses one or more _asso_values[c]. The result of choosing one or more _asso_values[c] is that the partitioning of the keyword set gets broader. Look at this partitioning: After every step, the _asso_values[] of a certain set C of characters are undetermined. (At the beginning, C is the set of characters c with _occurrences[c] > 0. At the end, C is empty.) To each keyword K, we associate the multiset of _selchars for which the _asso_values[] are undetermined: K --> K->_selchars intersect C. Consider two keywords equivalent if their value under this mapping is the same. This introduces an equivalence relation on the set of keywords. The equivalence classes partition the keyword set. (At the beginning, the partition is the finest possible: each K is an equivalence class by itself, because all K have a different _selchars. At the end, all K have been merged into a single equivalence class.) The partition before a step is always a refinement of the partition after the step. We choose the steps in such a way that the partition really becomes broader at each step. (A step that only chooses an _asso_values[c] without changing the partition is better merged with the previous step, to avoid useless backtracking.) */ struct EquivalenceClass { /* The keywords in this equivalence class. */ KeywordExt_List * _keywords; KeywordExt_List * _keywords_last; /* The number of keywords in this equivalence class. */ unsigned int _cardinality; /* The undetermined selected characters for the keywords in this equivalence class, as a canonically reordered multiset. */ unsigned int * _undetermined_chars; unsigned int _undetermined_chars_length; EquivalenceClass * _next; }; struct Step { /* The characters whose values are being determined in this step. */ unsigned int _changing_count; unsigned int * _changing; /* Exclusive upper bound for the _asso_values[c] of this step. A power of 2. */ unsigned int _asso_value_max; /* The characters whose values will be determined after this step. */ bool * _undetermined; /* The keyword set partition after this step. */ EquivalenceClass * _partition; /* The expected number of iterations in this step. */ double _expected_lower; double _expected_upper; Step * _next; }; static inline bool equals (const unsigned int *ptr1, const unsigned int *ptr2, unsigned int len) { while (len > 0) { if (*ptr1 != *ptr2) return false; ptr1++; ptr2++; len--; } return true; } EquivalenceClass * Search::compute_partition (bool *undetermined) const { EquivalenceClass *partition = NULL; EquivalenceClass *partition_last = NULL; for (KeywordExt_List *temp = _head; temp; temp = temp->rest()) { KeywordExt *keyword = temp->first(); /* Compute the undetermined characters for this keyword. */ unsigned int *undetermined_chars = new unsigned int[keyword->_selchars_length]; unsigned int undetermined_chars_length = 0; for (int i = 0; i < keyword->_selchars_length; i++) if (undetermined[keyword->_selchars[i]]) undetermined_chars[undetermined_chars_length++] = keyword->_selchars[i]; /* Look up the equivalence class to which this keyword belongs. */ EquivalenceClass *equclass; for (equclass = partition; equclass; equclass = equclass->_next) if (equclass->_undetermined_chars_length == undetermined_chars_length && equals (equclass->_undetermined_chars, undetermined_chars, undetermined_chars_length)) break; if (equclass == NULL) { equclass = new EquivalenceClass(); equclass->_keywords = NULL; equclass->_keywords_last = NULL; equclass->_cardinality = 0; equclass->_undetermined_chars = undetermined_chars; equclass->_undetermined_chars_length = undetermined_chars_length; equclass->_next = NULL; if (partition) partition_last->_next = equclass; else partition = equclass; partition_last = equclass; } else delete[] undetermined_chars; /* Add the keyword to the equivalence class. */ KeywordExt_List *cons = new KeywordExt_List(keyword); if (equclass->_keywords) equclass->_keywords_last->rest() = cons; else equclass->_keywords = cons; equclass->_keywords_last = cons; equclass->_cardinality++; } /* Free some of the allocated memory. The caller doesn't need it. */ for (EquivalenceClass *cls = partition; cls; cls = cls->_next) delete[] cls->_undetermined_chars; return partition; } static void delete_partition (EquivalenceClass *partition) { while (partition != NULL) { EquivalenceClass *equclass = partition; partition = equclass->_next; delete_list (equclass->_keywords); //delete[] equclass->_undetermined_chars; // already freed above delete equclass; } } /* Compute the possible number of collisions when _asso_values[c] is chosen, leading to the given partition. */ unsigned int Search::count_possible_collisions (EquivalenceClass *partition, unsigned int c) const { /* Every equivalence class p is split according to the frequency of occurrence of c, leading to equivalence classes p1, p2, ... This leads to (|p|^2 - |p1|^2 - |p2|^2 - ...)/2 possible collisions. Return the sum of this expression over all equivalence classes. */ unsigned int sum = 0; unsigned int m = _max_selchars_length; unsigned int *split_cardinalities = new unsigned int[m + 1]; for (EquivalenceClass *cls = partition; cls; cls = cls->_next) { for (unsigned int i = 0; i <= m; i++) split_cardinalities[i] = 0; for (KeywordExt_List *temp = cls->_keywords; temp; temp = temp->rest()) { KeywordExt *keyword = temp->first(); unsigned int count = 0; for (int i = 0; i < keyword->_selchars_length; i++) if (keyword->_selchars[i] == c) count++; split_cardinalities[count]++; } sum += cls->_cardinality * cls->_cardinality; for (unsigned int i = 0; i <= m; i++) sum -= split_cardinalities[i] * split_cardinalities[i]; } delete[] split_cardinalities; return sum; } /* Test whether adding c to the undetermined characters changes the given partition. */ bool Search::unchanged_partition (EquivalenceClass *partition, unsigned int c) const { for (EquivalenceClass *cls = partition; cls; cls = cls->_next) { unsigned int first_count = UINT_MAX; for (KeywordExt_List *temp = cls->_keywords; temp; temp = temp->rest()) { KeywordExt *keyword = temp->first(); unsigned int count = 0; for (int i = 0; i < keyword->_selchars_length; i++) if (keyword->_selchars[i] == c) count++; if (temp == cls->_keywords) first_count = count; else if (count != first_count) /* c would split this equivalence class. */ return false; } } return true; } void Search::find_asso_values () { Step *steps; /* Determine the steps, starting with the last one. */ { bool *undetermined; bool *determined; steps = NULL; undetermined = new bool[_alpha_size]; for (unsigned int c = 0; c < _alpha_size; c++) undetermined[c] = false; determined = new bool[_alpha_size]; for (unsigned int c = 0; c < _alpha_size; c++) determined[c] = true; for (;;) { /* Compute the partition that needs to be refined. */ EquivalenceClass *partition = compute_partition (undetermined); /* Determine the main character to be chosen in this step. Choosing such a character c has the effect of splitting every equivalence class (according the the frequency of occurrence of c). We choose the c with the minimum number of possible collisions, so that characters which lead to a large number of collisions get handled early during the search. */ unsigned int chosen_c; unsigned int chosen_possible_collisions; { unsigned int best_c = 0; unsigned int best_possible_collisions = UINT_MAX; for (unsigned int c = 0; c < _alpha_size; c++) if (_occurrences[c] > 0 && determined[c]) { unsigned int possible_collisions = count_possible_collisions (partition, c); if (possible_collisions < best_possible_collisions) { best_c = c; best_possible_collisions = possible_collisions; } } if (best_possible_collisions == UINT_MAX) { /* All c with _occurrences[c] > 0 are undetermined. We are are the starting situation and don't need any more step. */ delete_partition (partition); break; } chosen_c = best_c; chosen_possible_collisions = best_possible_collisions; } /* We need one more step. */ Step *step = new Step(); step->_undetermined = new bool[_alpha_size]; memcpy (step->_undetermined, undetermined, _alpha_size*sizeof(bool)); step->_partition = partition; /* Now determine how the equivalence classes will be before this step. */ undetermined[chosen_c] = true; partition = compute_partition (undetermined); /* Now determine which other characters should be determined in this step, because they will not change the equivalence classes at this point. It is the set of all c which, for all equivalence classes, have the same frequency of occurrence in every keyword of the equivalence class. */ for (unsigned int c = 0; c < _alpha_size; c++) if (_occurrences[c] > 0 && determined[c] && unchanged_partition (partition, c)) { undetermined[c] = true; determined[c] = false; } /* main_c must be one of these. */ if (determined[chosen_c]) abort (); /* Now the set of changing characters of this step. */ unsigned int changing_count; changing_count = 0; for (unsigned int c = 0; c < _alpha_size; c++) if (undetermined[c] && !step->_undetermined[c]) changing_count++; unsigned int *changing = new unsigned int[changing_count]; changing_count = 0; for (unsigned int c = 0; c < _alpha_size; c++) if (undetermined[c] && !step->_undetermined[c]) changing[changing_count++] = c; step->_changing = changing; step->_changing_count = changing_count; step->_asso_value_max = _asso_value_max; step->_expected_lower = exp (static_cast(chosen_possible_collisions) / static_cast(_max_hash_value)); step->_expected_upper = exp (static_cast(chosen_possible_collisions) / static_cast(_asso_value_max)); delete_partition (partition); step->_next = steps; steps = step; } delete[] determined; delete[] undetermined; } if (option[DEBUG]) { unsigned int stepno = 0; for (Step *step = steps; step; step = step->_next) { stepno++; fprintf (stderr, "Step %u chooses _asso_values[", stepno); for (unsigned int i = 0; i < step->_changing_count; i++) { if (i > 0) fprintf (stderr, ","); fprintf (stderr, "'%c'", step->_changing[i]); } fprintf (stderr, "], expected number of iterations between %g and %g.\n", step->_expected_lower, step->_expected_upper); fprintf (stderr, "Keyword equivalence classes:\n"); for (EquivalenceClass *cls = step->_partition; cls; cls = cls->_next) { fprintf (stderr, "\n"); for (KeywordExt_List *temp = cls->_keywords; temp; temp = temp->rest()) { KeywordExt *keyword = temp->first(); fprintf (stderr, " %.*s\n", keyword->_allchars_length, keyword->_allchars); } } fprintf (stderr, "\n"); } } /* Initialize _asso_values[]. (The value given here matters only for those c which occur in all keywords with equal multiplicity.) */ for (unsigned int c = 0; c < _alpha_size; c++) _asso_values[c] = 0; unsigned int stepno = 0; for (Step *step = steps; step; step = step->_next) { stepno++; /* Initialize the asso_values[]. */ unsigned int k = step->_changing_count; for (unsigned int i = 0; i < k; i++) { unsigned int c = step->_changing[i]; _asso_values[c] = (_initial_asso_value < 0 ? rand () : _initial_asso_value) & (step->_asso_value_max - 1); } unsigned int iterations = 0; unsigned int *iter = new unsigned int[k]; for (unsigned int i = 0; i < k; i++) iter[i] = 0; unsigned int ii = (_jump != 0 ? k - 1 : 0); for (;;) { /* Test whether these asso_values[] lead to collisions among the equivalence classes that should be collision-free. */ bool has_collision = false; for (EquivalenceClass *cls = step->_partition; cls; cls = cls->_next) { /* Iteration Number array is a win, O(1) initialization time! */ _collision_detector->clear (); for (KeywordExt_List *ptr = cls->_keywords; ptr; ptr = ptr->rest()) { KeywordExt *keyword = ptr->first(); /* Compute the new hash code for the keyword, leaving apart the yet undetermined asso_values[]. */ int hashcode; { int sum = option[NOLENGTH] ? 0 : keyword->_allchars_length; const unsigned int *p = keyword->_selchars; int i = keyword->_selchars_length; for (; i > 0; p++, i--) if (!step->_undetermined[*p]) sum += _asso_values[*p]; hashcode = sum; } /* See whether it collides with another keyword's hash code, from the same equivalence class. */ if (_collision_detector->set_bit (hashcode)) { has_collision = true; break; } } /* Don't need to continue looking at the other equivalence classes if we already have found a collision. */ if (has_collision) break; } iterations++; if (!has_collision) break; /* Try other asso_values[]. */ if (_jump != 0) { /* The way we try various values for asso_values[step->_changing[0],...step->_changing[k-1]] is like this: for (bound = 0,1,...) for (ii = 0,...,k-1) iter[ii] := bound iter[0..ii-1] := values <= bound iter[ii+1..k-1] := values < bound and asso_values[step->_changing[i]] = _initial_asso_value + iter[i] * _jump. This makes it more likely to find small asso_values[]. */ unsigned int bound = iter[ii]; unsigned int i = 0; while (i < ii) { unsigned int c = step->_changing[i]; iter[i]++; _asso_values[c] = (_asso_values[c] + _jump) & (step->_asso_value_max - 1); if (iter[i] <= bound) goto found_next; _asso_values[c] = (_asso_values[c] - iter[i] * _jump) & (step->_asso_value_max - 1); iter[i] = 0; i++; } i = ii + 1; while (i < k) { unsigned int c = step->_changing[i]; iter[i]++; _asso_values[c] = (_asso_values[c] + _jump) & (step->_asso_value_max - 1); if (iter[i] < bound) goto found_next; _asso_values[c] = (_asso_values[c] - iter[i] * _jump) & (step->_asso_value_max - 1); iter[i] = 0; i++; } /* Switch from one ii to the next. */ { unsigned int c = step->_changing[ii]; _asso_values[c] = (_asso_values[c] - bound * _jump) & (step->_asso_value_max - 1); iter[ii] = 0; } /* Here all iter[i] == 0. */ ii++; if (ii == k) { ii = 0; bound++; if (bound == step->_asso_value_max) { /* Out of search space! We can either backtrack, or increase the available search space of this step. It seems simpler to choose the latter solution. */ step->_asso_value_max = 2 * step->_asso_value_max; if (step->_asso_value_max > _asso_value_max) { _asso_value_max = step->_asso_value_max; /* Reinitialize _max_hash_value. */ _max_hash_value = (option[NOLENGTH] ? 0 : _max_key_len) + (_asso_value_max - 1) * _max_selchars_length; /* Reinitialize _collision_detector. */ delete _collision_detector; _collision_detector = new Bool_Array (_max_hash_value + 1); } } } { unsigned int c = step->_changing[ii]; iter[ii] = bound; _asso_values[c] = (_asso_values[c] + bound * _jump) & (step->_asso_value_max - 1); } found_next: ; } else { /* Random. */ unsigned int c = step->_changing[ii]; _asso_values[c] = (_asso_values[c] + rand ()) & (step->_asso_value_max - 1); /* Next time, change the next c. */ ii++; if (ii == k) ii = 0; } } delete[] iter; if (option[DEBUG]) { fprintf (stderr, "Step %u chose _asso_values[", stepno); for (unsigned int i = 0; i < step->_changing_count; i++) { if (i > 0) fprintf (stderr, ","); fprintf (stderr, "'%c'", step->_changing[i]); } fprintf (stderr, "] in %u iterations.\n", iterations); } } /* Free allocated memory. */ while (steps != NULL) { Step *step = steps; steps = step->_next; delete[] step->_changing; delete[] step->_undetermined; delete_partition (step->_partition); delete step; } } /* Computes a keyword's hash value, relative to the current _asso_values[], and stores it in keyword->_hash_value. */ inline int Search::compute_hash (KeywordExt *keyword) const { int sum = option[NOLENGTH] ? 0 : keyword->_allchars_length; const unsigned int *p = keyword->_selchars; int i = keyword->_selchars_length; for (; i > 0; p++, i--) sum += _asso_values[*p]; return keyword->_hash_value = sum; } /* Finds good _asso_values[]. */ void Search::find_good_asso_values () { prepare_asso_values (); /* Search for good _asso_values[]. */ int asso_iteration; if ((asso_iteration = option.get_asso_iterations ()) == 0) /* Try only the given _initial_asso_value and _jump. */ find_asso_values (); else { /* Try different pairs of _initial_asso_value and _jump, in the following order: (0, 1) (1, 1) (2, 1) (0, 3) (3, 1) (1, 3) (4, 1) (2, 3) (0, 5) (5, 1) (3, 3) (1, 5) ..... */ KeywordExt_List *saved_head = _head; int best_initial_asso_value = 0; int best_jump = 1; int *best_asso_values = new int[_alpha_size]; int best_collisions = INT_MAX; int best_max_hash_value = INT_MAX; _initial_asso_value = 0; _jump = 1; for (;;) { /* Restore the keyword list in its original order. */ _head = copy_list (saved_head); /* Find good _asso_values[]. */ find_asso_values (); /* Test whether it is the best solution so far. */ int collisions = 0; int max_hash_value = INT_MIN; _collision_detector->clear (); for (KeywordExt_List *ptr = _head; ptr; ptr = ptr->rest()) { KeywordExt *keyword = ptr->first(); int hashcode = compute_hash (keyword); if (max_hash_value < hashcode) max_hash_value = hashcode; if (_collision_detector->set_bit (hashcode)) collisions++; } if (collisions < best_collisions || (collisions == best_collisions && max_hash_value < best_max_hash_value)) { memcpy (best_asso_values, _asso_values, _alpha_size * sizeof (_asso_values[0])); best_collisions = collisions; best_max_hash_value = max_hash_value; } /* Delete the copied keyword list. */ delete_list (_head); if (--asso_iteration == 0) break; /* Prepare for next iteration. */ if (_initial_asso_value >= 2) _initial_asso_value -= 2, _jump += 2; else _initial_asso_value += _jump, _jump = 1; } _head = saved_head; /* Install the best found asso_values. */ _initial_asso_value = best_initial_asso_value; _jump = best_jump; memcpy (_asso_values, best_asso_values, _alpha_size * sizeof (_asso_values[0])); delete[] best_asso_values; /* The keywords' _hash_value fields are recomputed below. */ } } /* ========================================================================= */ /* Comparison function for sorting by increasing _hash_value. */ static bool less_by_hash_value (KeywordExt *keyword1, KeywordExt *keyword2) { return keyword1->_hash_value < keyword2->_hash_value; } /* Sorts the keyword list by hash value. */ void Search::sort () { _head = mergesort_list (_head, less_by_hash_value); } void Search::optimize () { /* Preparations. */ prepare (); /* Step 1: Finding good byte positions. */ find_positions (); /* Step 2: Finding good alpha increments. */ find_alpha_inc (); /* Step 3: Finding good asso_values. */ find_good_asso_values (); /* Make one final check, just to make sure nothing weird happened.... */ _collision_detector->clear (); for (KeywordExt_List *curr_ptr = _head; curr_ptr; curr_ptr = curr_ptr->rest()) { KeywordExt *curr = curr_ptr->first(); unsigned int hashcode = compute_hash (curr); if (_collision_detector->set_bit (hashcode)) { /* This shouldn't happen. proj1, proj2, proj3 must have been computed to be injective on the given keyword set. */ fprintf (stderr, "\nInternal error, unexpected duplicate hash code\n"); if (option[POSITIONS]) fprintf (stderr, "try options -m or -r, or use new key positions.\n\n"); else fprintf (stderr, "try options -m or -r.\n\n"); exit (1); } } /* Sorts the keyword list by hash value. */ sort (); /* Set unused asso_values[c] to max_hash_value + 1. This is not absolutely necessary, but speeds up the lookup function in many cases of lookup failure: no string comparison is needed once the hash value of a string is larger than the hash value of any keyword. */ int max_hash_value; { KeywordExt_List *temp; for (temp = _head; temp->rest(); temp = temp->rest()) ; max_hash_value = temp->first()->_hash_value; } for (unsigned int c = 0; c < _alpha_size; c++) if (_occurrences[c] == 0) _asso_values[c] = max_hash_value + 1; /* Propagate unified asso_values. */ if (_alpha_unify) for (unsigned int c = 0; c < _alpha_size; c++) if (_alpha_unify[c] != c) _asso_values[c] = _asso_values[_alpha_unify[c]]; } /* Prints out some diagnostics upon completion. */ Search::~Search () { delete _collision_detector; if (option[DEBUG]) { fprintf (stderr, "\ndumping occurrence and associated values tables\n"); for (unsigned int i = 0; i < _alpha_size; i++) if (_occurrences[i]) fprintf (stderr, "asso_values[%c] = %6d, occurrences[%c] = %6d\n", i, _asso_values[i], i, _occurrences[i]); fprintf (stderr, "end table dumping\n"); fprintf (stderr, "\nDumping key list information:\ntotal non-static linked keywords = %d" "\ntotal keywords = %d\ntotal duplicates = %d\nmaximum key length = %d\n", _list_len, _total_keys, _total_duplicates, _max_key_len); int field_width = _max_selchars_length; fprintf (stderr, "\nList contents are:\n(hash value, key length, index, %*s, keyword):\n", field_width, "selchars"); for (KeywordExt_List *ptr = _head; ptr; ptr = ptr->rest()) { fprintf (stderr, "%11d,%11d,%6d, ", ptr->first()->_hash_value, ptr->first()->_allchars_length, ptr->first()->_final_index); if (field_width > ptr->first()->_selchars_length) fprintf (stderr, "%*s", field_width - ptr->first()->_selchars_length, ""); for (int j = 0; j < ptr->first()->_selchars_length; j++) putc (ptr->first()->_selchars[j], stderr); fprintf (stderr, ", %.*s\n", ptr->first()->_allchars_length, ptr->first()->_allchars); } fprintf (stderr, "End dumping list.\n\n"); } delete[] _asso_values; delete[] _occurrences; delete[] _alpha_unify; delete[] _alpha_inc; } smalltalk-3.2.5/superops/keyword.icc0000644000175000017500000000273212123404352014452 00000000000000/* Inline Functions for keyword.{h,cc}. Copyright (C) 1989-1998, 2000, 2002 Free Software Foundation, Inc. Written by Douglas C. Schmidt and Bruno Haible . This file is part of GNU GPERF. GNU GPERF is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2, or (at your option) any later version. GNU GPERF is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; see the file COPYING. If not, write to the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. */ /* ----------------------------- Keyword class ----------------------------- */ /* Constructor. */ INLINE Keyword::Keyword (const char *allchars, int allchars_length, const char *rest) : _allchars (allchars), _allchars_length (allchars_length), _rest (rest) { } /* --------------------------- KeywordExt class --------------------------- */ /* Constructor. */ INLINE KeywordExt::KeywordExt (const char *allchars, int allchars_length, const char *rest) : Keyword (allchars, allchars_length, rest), _final_index (-1) { } smalltalk-3.2.5/superops/positions.cc0000644000175000017500000000766312123404352014654 00000000000000/* A set of byte positions. Copyright (C) 1989-1998, 2000, 2002 Free Software Foundation, Inc. Written by Douglas C. Schmidt and Bruno Haible . This file is part of GNU GPERF. GNU GPERF is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2, or (at your option) any later version. GNU GPERF is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; see the file COPYING. If not, write to the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. */ /* Specification. */ #include "positions.h" #include #include /* declares exit() */ #include /* ---------------------------- Class Positions ---------------------------- */ /* Set operations. Assumes the array is in reverse order. */ bool Positions::contains (int pos) const { unsigned int count = _size; const int *p = _positions + _size - 1; for (; count > 0; p--, count--) { if (*p == pos) return true; if (*p > pos) break; } return false; } void Positions::add (int pos) { set_useall (false); unsigned int count = _size; if (count == MAX_SIZE) { fprintf (stderr, "Positions::add internal error: overflow\n"); exit (1); } int *p = _positions + _size - 1; for (; count > 0; p--, count--) { if (*p == pos) { fprintf (stderr, "Positions::add internal error: duplicate\n"); exit (1); } if (*p > pos) break; p[1] = p[0]; } p[1] = pos; _size++; } void Positions::remove (int pos) { set_useall (false); unsigned int count = _size; if (count > 0) { int *p = _positions + _size - 1; if (*p == pos) { _size--; return; } if (*p < pos) { int prev = *p; for (;;) { p--; count--; if (count == 0) break; if (*p == pos) { *p = prev; _size--; return; } if (*p > pos) break; int curr = *p; *p = prev; prev = curr; } } } fprintf (stderr, "Positions::remove internal error: not found\n"); exit (1); } /* Output in external syntax. */ void Positions::print () const { if (_useall) printf ("*"); else { bool first = true; bool seen_LASTCHAR = false; unsigned int count = _size; const int *p = _positions + _size - 1; for (; count > 0; p--) { count--; if (*p == LASTCHAR) seen_LASTCHAR = true; else { if (!first) printf (","); printf ("%d", *p + 1); if (count > 0 && p[-1] == *p + 1) { printf ("-"); do { p--; count--; } while (count > 0 && p[-1] == *p + 1); printf ("%d", *p + 1); } first = false; } } if (seen_LASTCHAR) { if (!first) printf (","); printf ("$"); } } } /* ------------------------------------------------------------------------- */ #ifndef __OPTIMIZE__ #define INLINE /* not inline */ #include "positions.icc" #undef INLINE #endif /* not defined __OPTIMIZE__ */ smalltalk-3.2.5/superops/superops.cc0000644000175000017500000004015012123404352014471 00000000000000/////////////////////////////// -*- C++ -*- /////////////////////////// // // Program to extract superoperators from a GNU Smalltalk image. // // Should only be of interest to the maintainer and to // casual hackers. // // Sorry for writing this in C++, did not feel like writing hash // table code for the 200th time in my (so far) short life :-) -- // and later it turned out to be good for integrating gperf... // /////////////////////////////////////////////////////////////////////// /////////////////////////////////////////////////////////////////////// // // Copyright 2003, 2007 Free Software Foundation, Inc. // Written by Paolo Bonzini. // // This file is part of GNU Smalltalk. // // GNU Smalltalk is free software; you can redistribute it and/or modify it // under the terms of the GNU General Public License as published by the Free // Software Foundation; either version 2, or (at your option) any later // version. // // GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT // ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or // FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for // more details. // // You should have received a copy of the GNU General Public License along with // GNU Smalltalk; see the file COPYING. If not, write to the Free Software // Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. // /////////////////////////////////////////////////////////////////////// #if defined __GNUC__ && __GNUC__ < 3 #error Sorry, you need a recent C++ compiler to compile this program. #endif #include #include #include #include #include #include #include #include #include #include #include "observer-list.h" #include "byte_def.h" #include "vm_def.h" #include "table.h" #include "hash.h" // GPERF include files #include "options.h" #include "search.h" #include "keyword.h" #include "keyword-list.h" #include "positions.h" bool isLineNo[256]; struct superop_collector; struct sequence; // This class collects the (bytecode,bytecode,arg) triplets // that are candidates for superoperators and keeps in a // heap data structure // the best ones class superop_collector { // This class represents a sequence that is a candidate // for becoming a superoperator struct triplet { int bc1, bc2, arg, occurrences; triplet (int bc1_, int bc2_, int arg_) : bc1 (bc1_), bc2(bc2_), arg(arg_), occurrences (0) { } bool operator== (const triplet& them) const { return bc1 == them.bc1 && bc2 == them.bc2 && arg == them.arg; } bool operator< (const triplet& them) const { if (bc1 < them.bc1) return true; if (bc1 > them.bc1) return false; if (bc2 < them.bc2) return true; if (bc2 > them.bc2) return false; return (arg < them.arg); } }; // This class does the actual work of maintaining the table // of superoperator candidates. The containing class keeps // two of them, one when the fixed argument is the second // bytecode's argument, and one when it is the first bytecode's // argument. // // This a simple heap data structure implemented on top of a // std::vector, with some additional glue to find an item in // the heap: the map associates each superoperator candidate // to its current index in the vector. class triplet_collector { typedef std::vector triplet_heap; typedef std::map triplet_map; triplet_heap heap; triplet_map triplets; int map_at (triplet& t); void map_at_put (triplet& t, int index); public: triplet_collector() : heap (), triplets () { } ~triplet_collector(); void add (int bc1, int bc2, int arg); triplet& top () const { return *heap[0]; } }; triplet_collector heap1; triplet_collector heap2; bool found[256]; public: superop_collector (); void found_bytecode (int bc) { found[bc] = true; }; void with_fixed_arg_1 (int bc1, int arg1, int bc2); void with_fixed_arg_2 (int bc1, int bc2, int arg2); bool replace_best_in_sequences (observer_list &obs, sequence *s) const; }; // This class represents a bytecode sequence from which to derive // the superoperators. struct sequence { sequence *next; int n; unsigned char *seq; sequence (sequence *next_, std::istream& is); int all_count (); bool all_visit (observer_list& obs); void all_replace_with_fixed_arg_1 (int new_bc, int bc1, int arg1, int bc2); void all_replace_with_fixed_arg_2 (int new_bc, int bc1, int bc2, int arg2); void visit (superop_collector& sc); void replace_with_fixed_arg_1 (int new_bc, int bc1, int arg1, int bc2); void replace_with_fixed_arg_2 (int new_bc, int bc1, int bc2, int arg2); bool includes_superoperators (); }; superop_collector::triplet_collector::~triplet_collector () { while (heap.size ()) { triplet *t = heap.back (); heap.pop_back (); delete t; } } int superop_collector::triplet_collector::map_at (triplet& t) { triplet_map::iterator it = triplets.find (t); if (it == triplets.end ()) { // Add a triplet to the end of the heap. triplet_map::value_type key_val (t, heap.size ()); triplets.insert (key_val); heap.push_back (new triplet (t)); return key_val.second; } else return it->second; } void superop_collector::triplet_collector::map_at_put (triplet& t, int index) { // Find the triplet in the map and set its index. triplet_map::iterator it = triplets.find (t); // Should already be in the map! if (it == triplets.end ()) abort (); else it->second = index; } void superop_collector::triplet_collector::add (int bc1, int bc2, int arg) { triplet t = triplet (bc1, bc2, arg); int index = map_at (t); triplet& this_triplet = *heap[index]; // Give a penalty to superoperators that include the line number // bytecode, because it is a nop and saves only the decoding, // without giving advantages in instruction scheduling and // stack movement (simply speaking, a pop/push superoperator // is more useful than a line/pop superoperator). if (isLineNo[bc1] || isLineNo[bc2]) this_triplet.occurrences++; else this_triplet.occurrences += 2; #if DEBUG std::cout << " with weight " << this_triplet.occurrences << " was at index " << index; #endif // Percolate the element towards the top of the heap. // // Yes my Standard C++ Library knowledge is limited. I did // not find a standard algorithm to percolate an item already // in the heap, so I wrote the heap code myself. while (index > 0) { int parent = index / 2; triplet& parent_triplet = *heap[parent]; if (parent_triplet.occurrences < this_triplet.occurrences) { // Swap parent and child heap[parent] = &this_triplet; heap[index] = &parent_triplet; map_at_put (this_triplet, parent); map_at_put (parent_triplet, index); } else break; index = parent; } #if DEBUG std::cout << " now at index " << index << std::endl; #endif } superop_collector::superop_collector () : heap1(), heap2 () { for (int i = 0; i < 256; i++) found[i] = false; } void superop_collector::with_fixed_arg_1 (int bc1, int arg1, int bc2) { #if DEBUG std::cout << "Candidate " << bc1 << '(' << arg1 << "), " << bc2; #endif heap1.add (bc1, bc2, arg1); } void superop_collector::with_fixed_arg_2 (int bc1, int bc2, int arg2) { #if DEBUG std::cout << "Candidate " << bc1 << ", " << bc2 << '(' << arg2 << ')'; #endif heap2.add (bc1, bc2, arg2); } bool superop_collector::replace_best_in_sequences (observer_list &obs, sequence * s) const { triplet heap1_best = heap1.top (); triplet heap2_best = heap2.top (); // Look for the bytecode int new_bc; for (new_bc = 64; found[new_bc]; new_bc++) if (new_bc == 255) return false; if (heap2_best.occurrences > heap1_best.occurrences) { isLineNo[new_bc] = isLineNo[heap2_best.bc1] || isLineNo[heap2_best.bc2]; int bc1 = heap2_best.bc1; int bc2 = heap2_best.bc2; int arg = heap2_best.arg; obs.with_fixed_arg_2 (new_bc, bc1, bc2, arg); s->all_replace_with_fixed_arg_2 (new_bc, bc1, bc2, arg); } else { isLineNo[new_bc] = isLineNo[heap1_best.bc1] || isLineNo[heap1_best.bc2]; int bc1 = heap1_best.bc1; int arg = heap1_best.arg; int bc2 = heap1_best.bc2; obs.with_fixed_arg_1 (new_bc, bc1, arg, bc2); s->all_replace_with_fixed_arg_1 (new_bc, bc1, arg, bc2); } return true; } // Load the sequence from the input stream, IS. sequence::sequence (sequence * next_, std::istream& is) : next (next_) { is >> n; seq = new unsigned char[n]; for (int i = 0; i < n; i++) { int bc; is >> bc; seq[i] = bc; } } bool sequence::includes_superoperators () { for (int i = 0; i < n; i += 2) if (seq[i] >= 64) return true; return false; } // Count the total length of the sequences. int sequence::all_count () { int total = 0; for (sequence *s = this; s; s = s->next) total += s->n; return total; } // Pass all the sequences in the list to SC. bool sequence::all_visit (observer_list& obs) { superop_collector sc; for (sequence *s = this; s; s = s->next) s->visit (sc); return sc.replace_best_in_sequences (obs, this); } // Replace the given superoperator into all the sequences with // the bytecode NEW_BC. void sequence::all_replace_with_fixed_arg_1 (int new_bc, int bc1, int arg1, int bc2) { for (sequence *s = this; s; s = s->next) s->replace_with_fixed_arg_1 (new_bc, bc1, arg1, bc2); } // Replace the given superoperator into all the sequences with // the bytecode NEW_BC. void sequence::all_replace_with_fixed_arg_2 (int new_bc, int bc1, int bc2, int arg2) { for (sequence *s = this; s; s = s->next) s->replace_with_fixed_arg_2 (new_bc, bc1, bc2, arg2); } // Print the sequence represented by S on the output stream, OS. std::ostream& operator<< (std::ostream& os, const sequence& s) { os << s.n; for (int i = 0; i < s.n; i++) os << ' ' << (int) s.seq[i]; return os; } // Pass the candidate superoperators in this sequence to SC. void sequence::visit (superop_collector& sc) { #ifdef DEBUG std::cout << "Visiting " << *this << std::endl; #endif // Also mark the first bytecode as used! sc.found_bytecode (seq[0]); for (int i = 2; i < n; i += 2) { sc.found_bytecode (seq[i]); int bc1 = seq[i-2]; int arg1 = seq[i-1]; int bc2 = seq[i]; int arg2 = seq[i+1]; if (bc2 == EXT_BYTE) continue; if ((i == 2 || seq[i-4] != EXT_BYTE) && bc1 != EXT_BYTE && !isLineNo[bc1]) sc.with_fixed_arg_1 (bc1, arg1, bc2); if (!isLineNo[bc2]) sc.with_fixed_arg_2 (bc1, bc2, arg2); } } // Replace the given superoperator into this sequences with // the bytecode NEW_BC. void sequence::replace_with_fixed_arg_1 (int new_bc, int bc1, int arg1, int bc2) { #ifdef DEBUG std::cout << "Replacing in " << *this << std::endl; #endif for (int i = 2; i < n; i += 2) if (seq[i-2] == bc1 && seq[i-1] == arg1 && seq[i] == bc2 && (i == 2 || seq[i-4] != EXT_BYTE)) { seq[i-2] = new_bc; seq[i-1] = seq[i+1]; std::memmove (&seq[i], &seq[i+2], n - (i+2)); n -= 2; } #ifdef DEBUG std::cout << "Rewritten as " << *this << std::endl; #endif } // Replace the given superoperator into this sequences with // the bytecode NEW_BC. void sequence::replace_with_fixed_arg_2 (int new_bc, int bc1, int bc2, int arg2) { #ifdef DEBUG std::cout << "Replacing in " << *this << std::endl; #endif for (int i = 2; i < n; i += 2) if (seq[i-2] == bc1 && seq[i] == bc2 && seq[i+1] == arg2) { seq[i-2] = new_bc; std::memmove (&seq[i], &seq[i+2], n - (i+2)); n -= 2; } #ifdef DEBUG std::cout << "Rewritten as " << *this << std::endl; #endif } int main (int argc, char **argv) { int rfd[2], wfd[2]; /* ?fd[0] is for the parent, ?fd[1] is for the child. */ pipe (rfd); wfd[0] = rfd[1]; wfd[1] = rfd[0]; pipe (rfd); if (fork () == 0) { close (0); dup (wfd[1]); close (1); dup (rfd[1]); execl ("../gst", "../gst", "-Q", "-I", "../gst.im", NULL); } // A simple script to collect the superoperator candidates // from the current image. const char gst_script[] = " CompiledCode extend [" " allSuperoperatorBreaks [" " | breaks |" " breaks := SortedCollection new." " self allByteCodeIndicesDo: [ :i :b :op |" ///////// "Split where jumps land" " (b >= 40 and: [ b <= 43 ])" " ifTrue: [ breaks add: (self jumpDestinationAt: i forward: b > 40) ]." ///////// "Split after returns" " (b >= 50 and: [ b <= 51 ])" " ifTrue: [ breaks add: (self nextBytecodeIndex: i) ]." ///////// "Split after jumps" " (b >= 40 and: [ b <= 43 ])" " ifTrue: [ breaks add: (self nextBytecodeIndex: i) ]." ///////// "Split after push/store literal variable" " (b = 34 or: [ b = 38 ])" " ifTrue: [ breaks add: (self nextBytecodeIndex: i) ]." ///////// "Split after sends" " (b < 32 and: [ (b + 12 bitAnd: 250) ~= 32 ])" " ifTrue: [ breaks add: (self nextBytecodeIndex: i) ]" " ]." " ^breaks ]" " allOptimizableSequencesDo: aBlock [" " | breaks ws |" " breaks := self allSuperoperatorBreaks." " ({1}, breaks)" " with: (breaks asArray copyWith: self numBytecodes + 1)" " do: [ :begin :end |" " end - begin > 2 ifTrue: [" " aBlock value: (self copyFrom: begin to: end - 1) ]" " ] ]" " printAllOptimizableSequences [" " self allOptimizableSequencesDo: [ :seq |" " seq size printOn: stdout." " seq do: [ :each | stdout space. each printOn: stdout ]." " stdout nl" " ] ] ]." " Eval [ " " stdout nextPutAll: 'BEGIN'; nl." " CompiledMethod allInstancesDo: [ :each |" " each descriptor notNil" " ifTrue: [ each printAllOptimizableSequences ] ]." " CompiledBlock allInstancesDo: [ :each |" " each method notNil" " ifTrue: [ each printAllOptimizableSequences ] ]." " stdout nl." " ObjectMemory quit ]"; write (wfd[0], gst_script, sizeof (gst_script) - 1); // Load the Smalltalk script's output into a buffer int nread = 0, nthis; char *total = NULL; char buf[8192]; do { nthis = read (rfd[0], buf, 8192); total = (char *) realloc (total, nread + nthis); std::memcpy (total + nread, buf, nthis); nread += nthis; } while (nthis > 0 && !(total[nread - 1] == '\n' && total[nread - 2] == '\n')); total = strstr (total, "BEGIN\n") + 6; // Parse sequences from the buffer until we reach its end // (which is marked by an empty sequence). Don't save sequences // whose length is 2 because they produce no superoperators. std::string istr (total, nread); std::istringstream is (istr); sequence *seqs = NULL; int bad_seqs = 0; do { seqs = new sequence (seqs, is); sequence *first = seqs; if (first->includes_superoperators ()) { bad_seqs++; seqs = seqs->next; delete first; } } while (is.tellg () > 0); if (bad_seqs) { std::cout << "Discarded " << bad_seqs << " sequences. " << (bad_seqs > 200 ? "Was gst compiled with NO_SUPEROPERATORS?" : "") << std::endl; } // Statistics are fun... int before = seqs->all_count(); std::cout << before << " bytecodes read." << std::endl; // Now do the job until no bytecodes are free. isLineNo[LINE_NUMBER_BYTECODE] = true; superop_table_builder stb; hash_builder hb; byte_def_builder bdb; vm_def_builder vdb; observer_list obs; obs.push_back (&hb); obs.push_back (&bdb); obs.push_back (&vdb); obs.push_back (&stb); while (seqs->all_visit (obs)); // Statistics can be even more fun... int after = seqs->all_count(); int ratio_1000 = int (1000 * (double (after) / before)); std::cout << after << " bytecodes remain, " << double (1000 - ratio_1000) / 10.0 << "% savings." << std::endl; // And now invoke gperf. hb.output (); int pid; wait (&pid); } smalltalk-3.2.5/superops/hash-table.h0000644000175000017500000000445012123404352014466 00000000000000/* This may look like C code, but it is really -*- C++ -*- */ /* Hash table used to check for duplicate keyword entries. Copyright (C) 1989-1998, 2000, 2002 Free Software Foundation, Inc. Written by Douglas C. Schmidt and Bruno Haible . This file is part of GNU GPERF. GNU GPERF is free software; you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation; either version 2, or (at your option) any later version. GNU GPERF is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program; see the file COPYING. If not, write to the Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. */ #ifndef hash_table_h #define hash_table_h 1 #include "keyword.h" /* Hash table of KeywordExt* entries. Two entries are considered equal if their _selchars are the same and - if !ignore_length - if their _allchars_length are the same. */ class Hash_Table { public: /* Constructor. size is the maximum number of entries. ignore_length determines a detail in the comparison function. */ Hash_Table (unsigned int size, bool ignore_length); /* Destructor. */ ~Hash_Table (); /* Attempts to insert ITEM in the table. If there is already an equal entry in it, returns it. Otherwise inserts ITEM and returns NULL. */ KeywordExt * insert (KeywordExt *item); /* Print the table's contents. */ void dump () const; private: /* Vector of entries. */ KeywordExt ** _table; /* Size of the vector. */ unsigned int _size; /* log2(_size). */ unsigned int _log_size; /* A detail of the comparison function. */ bool const _ignore_length; /* Statistics: Number of collisions so far. */ unsigned int _collisions; /* Compares two items. */ bool equal (KeywordExt *item1, KeywordExt *item2) const; }; #endif smalltalk-3.2.5/superops/vm_def.cc0000644000175000017500000002670212123404352014060 00000000000000/////////////////////////////// -*- C++ -*- /////////////////////////// // // Program to extract superoperators from a GNU Smalltalk image. // vm.def creation routines. // /////////////////////////////////////////////////////////////////////// /////////////////////////////////////////////////////////////////////// // // Copyright 2003, 2007, 2008 Free Software Foundation, Inc. // Written by Paolo Bonzini. // // This file is part of GNU Smalltalk. // // GNU Smalltalk is free software; you can redistribute it and/or modify it // under the terms of the GNU General Public License as published by the Free // Software Foundation; either version 2, or (at your option) any later // version. // // GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT // ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or // FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for // more details. // // You should have received a copy of the GNU General Public License along with // GNU Smalltalk; see the file COPYING. If not, write to the Free Software // Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. // /////////////////////////////////////////////////////////////////////// #if defined __GNUC__ && __GNUC__ < 3 #error Sorry, you need a recent C++ compiler to compile this program. #endif #include "byte_def.h" #include "vm_def.h" #include #include #include namespace { struct bytecode { static bytecode *bytecodes[256]; int num; bytecode (int _num); virtual void write_prefetch (std::ostream &os); virtual void write_vm_def (std::ostream &os); virtual void write_vm_def_ext_arg (std::ostream &os, int arg) = 0; virtual void write_vm_def_fixed_arg (std::ostream &os, int arg) = 0; virtual void write_vm_def_var_arg (std::ostream &os) = 0; }; struct bytecode_elementary : bytecode { const char *name; bytecode_elementary (int _num, const char *_name); }; struct bytecode_noarg : bytecode_elementary { bytecode_noarg (int _num, const char *_name); void write_vm_def_ext_arg (std::ostream &os, int arg); void write_vm_def_fixed_arg (std::ostream &os, int arg); void write_vm_def_var_arg (std::ostream &os); }; struct bytecode_unary : bytecode_elementary { bytecode_unary (int _num, const char *_name); void write_vm_def_ext_arg (std::ostream &os, int arg); void write_vm_def_fixed_arg (std::ostream &os, int arg); void write_vm_def_var_arg (std::ostream &os); }; struct bytecode_jump : bytecode_unary { bytecode_jump (int _num, const char *_name); void write_prefetch (std::ostream &os); }; struct bytecode_ext : bytecode_noarg { bytecode_ext (int _num, const char *_name); void write_vm_def (std::ostream &os); void write_vm_def_ext_arg (std::ostream &os, int arg); }; struct bytecode_binary : bytecode_elementary { bytecode_binary (int _num, const char *_name); void write_vm_def_ext_arg (std::ostream &os, int arg); void write_vm_def_fixed_arg (std::ostream &os, int arg); void write_vm_def_var_arg (std::ostream &os); }; struct bytecode_superoperator : bytecode { bytecode *bc1, *bc2; int fixed_arg; bytecode_superoperator (int _num, int _bc1, int _bc2, int _arg); void write_prefetch (std::ostream &os); }; struct bytecode_with_fixed_arg_1 : bytecode_superoperator { bytecode_with_fixed_arg_1 (int _num, int _bc1, int _bc2, int _arg); void write_vm_def_ext_arg (std::ostream &os, int arg); void write_vm_def_fixed_arg (std::ostream &os, int arg); void write_vm_def_var_arg (std::ostream &os); }; struct bytecode_with_fixed_arg_2 : bytecode_superoperator { bytecode_with_fixed_arg_2 (int _num, int _bc1, int _bc2, int _arg); void write_vm_def_ext_arg (std::ostream &os, int arg); void write_vm_def_fixed_arg (std::ostream &os, int arg); void write_vm_def_var_arg (std::ostream &os); }; void bytecode::write_prefetch (std::ostream & os) { os << " PREFETCH ();" << std::endl; } void bytecode::write_vm_def (std::ostream & os) { os << " " << num << " = bytecode bc" << num << " {" << std::endl; write_prefetch (os); write_vm_def_var_arg (os); os << " }" << std::endl << std::endl; }; bytecode::bytecode (int _num): num (_num) { bytecodes[num] = this; }; bytecode_elementary::bytecode_elementary (int _num, const char *_name): bytecode (_num), name (_name) { }; bytecode_noarg::bytecode_noarg (int _num, const char *_name): bytecode_elementary (_num, _name) { }; void bytecode_noarg::write_vm_def_ext_arg (std::ostream & os, int arg) { write_vm_def_fixed_arg (os, arg); } void bytecode_noarg::write_vm_def_fixed_arg (std::ostream & os, int arg) { os << " " << name << " ();" << std::endl; } void bytecode_noarg::write_vm_def_var_arg (std::ostream & os) { write_vm_def_fixed_arg (os, 0); } bytecode_unary::bytecode_unary (int _num, const char *_name): bytecode_elementary (_num, _name) { }; void bytecode_unary::write_vm_def_ext_arg (std::ostream & os, int arg) { os << " " << name << " (" << (arg << 8) << " | arg);" << std::endl; } void bytecode_unary::write_vm_def_fixed_arg (std::ostream & os, int arg) { os << " " << name << " (" << arg << ");" << std::endl; } void bytecode_unary::write_vm_def_var_arg (std::ostream & os) { os << " " << name << " (arg);" << std::endl; } bytecode_jump::bytecode_jump (int _num, const char *_name): bytecode_unary (_num, _name) { }; void bytecode_jump::write_prefetch (std::ostream & os) { os << " ADVANCE ();" << std::endl; } bytecode_ext::bytecode_ext (int _num, const char *_name): bytecode_noarg (_num, _name) { }; void bytecode_ext::write_vm_def (std::ostream & os) { os << " " << num << " = bytecode bc" << num << " {" << std::endl; write_vm_def_var_arg (os); os << " }" << std::endl << std::endl; }; void bytecode_ext::write_vm_def_ext_arg (std::ostream & os, int arg) { abort (); } bytecode_binary::bytecode_binary (int _num, const char *_name): bytecode_elementary (_num, _name) { }; void bytecode_binary::write_vm_def_ext_arg (std::ostream & os, int arg) { os << " " << name << " (arg, " << arg << ");" << std::endl; } void bytecode_binary::write_vm_def_fixed_arg (std::ostream & os, int arg) { os << " " << name << " (" << (arg >> 8) << ", " << (arg & 255) << ");" << std::endl; } void bytecode_binary::write_vm_def_var_arg (std::ostream & os) { os << " " << name << " (arg >> 8, arg & 255);" << std::endl; } bytecode_superoperator::bytecode_superoperator (int _num, int _bc1, int _bc2, int _arg): bytecode (_num), bc1 (bytecodes[_bc1]), bc2 (bytecodes[_bc2]), fixed_arg (_arg) { if (!bc1 || !bc2) abort (); } void bytecode_superoperator::write_prefetch (std::ostream & os) { bc2->write_prefetch (os); } bytecode_with_fixed_arg_1::bytecode_with_fixed_arg_1 (int _num, int _bc1, int _bc2, int _arg): bytecode_superoperator (_num, _bc1, _bc2, _arg) { } void bytecode_with_fixed_arg_1::write_vm_def_ext_arg (std::ostream & os, int arg) { abort (); } void bytecode_with_fixed_arg_1::write_vm_def_fixed_arg (std::ostream & os, int arg) { bc1->write_vm_def_fixed_arg (os, fixed_arg); bc2->write_vm_def_fixed_arg (os, arg); } void bytecode_with_fixed_arg_1::write_vm_def_var_arg (std::ostream & os) { bc1->write_vm_def_fixed_arg (os, fixed_arg); bc2->write_vm_def_var_arg (os); } bytecode_with_fixed_arg_2::bytecode_with_fixed_arg_2 (int _num, int _bc1, int _bc2, int _arg): bytecode_with_fixed_arg_2::bytecode_superoperator (_num, _bc1, _bc2, _arg) { } void bytecode_with_fixed_arg_2::write_vm_def_ext_arg (std::ostream & os, int arg) { abort (); } void bytecode_with_fixed_arg_2::write_vm_def_fixed_arg (std::ostream & os, int arg) { if (bc1 == bytecodes[EXT_BYTE]) bc2->write_vm_def_fixed_arg (os, (arg << 8) + fixed_arg); else { bc1->write_vm_def_fixed_arg (os, arg); bc2->write_vm_def_fixed_arg (os, fixed_arg); } } void bytecode_with_fixed_arg_2::write_vm_def_var_arg (std::ostream & os) { if (bc1 == bytecodes[EXT_BYTE]) bc2->write_vm_def_ext_arg (os, fixed_arg); else { bc1->write_vm_def_var_arg (os); bc2->write_vm_def_fixed_arg (os, fixed_arg); } } bytecode *bytecode::bytecodes[256]; bytecode_noarg bc0 (0, "PLUS_SPECIAL"); bytecode_noarg bc1 (1, "MINUS_SPECIAL"); bytecode_noarg bc2 (2, "LESS_THAN_SPECIAL"); bytecode_noarg bc3 (3, "GREATER_THAN_SPECIAL"); bytecode_noarg bc4 (4, "LESS_EQUAL_SPECIAL"); bytecode_noarg bc5 (5, "GREATER_EQUAL_SPECIAL"); bytecode_noarg bc6 (6, "EQUAL_SPECIAL"); bytecode_noarg bc7 (7, "NOT_EQUAL_SPECIAL"); bytecode_noarg bc8 (8, "TIMES_SPECIAL"); bytecode_noarg bc9 (9, "DIVIDE_SPECIAL"); bytecode_noarg bc10 (10, "REMAINDER_SPECIAL"); bytecode_noarg bc11 (11, "BIT_XOR_SPECIAL"); bytecode_noarg bc12 (12, "BIT_SHIFT_SPECIAL"); bytecode_noarg bc13 (13, "INTEGER_DIVIDE_SPECIAL"); bytecode_noarg bc14 (14, "BIT_AND_SPECIAL"); bytecode_noarg bc15 (15, "BIT_OR_SPECIAL"); bytecode_noarg bc16 (16, "AT_SPECIAL"); bytecode_noarg bc17 (17, "AT_PUT_SPECIAL"); bytecode_noarg bc18 (18, "SIZE_SPECIAL"); bytecode_noarg bc19 (19, "CLASS_SPECIAL"); bytecode_noarg bc20 (20, "IS_NIL_SPECIAL"); bytecode_noarg bc21 (21, "NOT_NIL_SPECIAL"); bytecode_noarg bc22 (22, "VALUE_SPECIAL"); bytecode_noarg bc23 (23, "VALUE_COLON_SPECIAL"); bytecode_noarg bc24 (24, "SAME_OBJECT_SPECIAL"); bytecode_noarg bc25 (25, "JAVA_AS_INT_SPECIAL"); bytecode_noarg bc26 (26, "JAVA_AS_LONG_SPECIAL"); bytecode_binary bc28 (28, "SEND"); bytecode_binary bc29 (29, "SEND_SUPER"); bytecode_unary bc30 (30, "SEND_IMMEDIATE"); bytecode_unary bc31 (31, "SEND_SUPER_IMMEDIATE"); bytecode_unary bc32 (32, "PUSH_TEMPORARY_VARIABLE"); bytecode_binary bc33 (33, "PUSH_OUTER_TEMP"); bytecode_unary bc34 (34, "PUSH_LIT_VARIABLE"); bytecode_unary bc35 (35, "PUSH_RECEIVER_VARIABLE"); bytecode_unary bc36 (36, "STORE_TEMPORARY_VARIABLE"); bytecode_binary bc37 (37, "STORE_OUTER_TEMP"); bytecode_unary bc38 (38, "STORE_LIT_VARIABLE"); bytecode_unary bc39 (39, "STORE_RECEIVER_VARIABLE"); bytecode_jump bc40 (40, "JUMP_BACK"); bytecode_jump bc41 (41, "JUMP"); bytecode_unary bc42 (42, "POP_JUMP_TRUE"); bytecode_unary bc43 (43, "POP_JUMP_FALSE"); bytecode_unary bc44 (44, "PUSH_INTEGER"); bytecode_unary bc45 (45, "PUSH_SPECIAL"); bytecode_unary bc46 (46, "PUSH_LIT_CONSTANT"); bytecode_unary bc47 (47, "POP_INTO_NEW_STACKTOP"); bytecode_noarg bc48 (48, "POP_STACK_TOP"); bytecode_noarg bc49 (49, "MAKE_DIRTY_BLOCK"); bytecode_noarg bc50 (50, "RETURN_METHOD_STACK_TOP"); bytecode_noarg bc51 (51, "RETURN_CONTEXT_STACK_TOP"); bytecode_noarg bc52 (52, "DUP_STACK_TOP"); bytecode_noarg bc53 (53, "EXIT_INTERPRETER"); bytecode_noarg bc54 (54, "LINE_NUMBER_BYTECODE"); bytecode_ext bc55 (55, "EXT_BYTE"); bytecode_noarg bc56 (56, "PUSH_SELF"); } vm_def_builder::vm_def_builder () : fs ("vm.def") { fs << "/* Automatically generated by superops. Do not modify past this line! */" << std::endl; fs << "table normal_byte_codes {" << std::endl; for (int i = 0; i < 64; i++) { if (!bytecode::bytecodes[i]) bytecode::bytecodes[i] = new bytecode_unary (i, "INVALID"); bytecode::bytecodes[i]->write_vm_def (fs); } } vm_def_builder::~vm_def_builder () { fs << "}"; std::cout << "genvm script (interpreter) written to vm.def." << std::endl; } void vm_def_builder::with_fixed_arg_1 (int new_bc, int bc1, int arg, int bc2) { (new bytecode_with_fixed_arg_1 (new_bc, bc1, bc2, arg))->write_vm_def (fs); } void vm_def_builder::with_fixed_arg_2 (int new_bc, int bc1, int bc2, int arg) { (new bytecode_with_fixed_arg_2 (new_bc, bc1, bc2, arg))->write_vm_def (fs); } smalltalk-3.2.5/superops/Makefile0000644000175000017500000000672112123404352013750 00000000000000# Makefile for gperf/src # Copyright (C) 1989,1992,1993,1998,2000,2002 Free Software Foundation, Inc. # Written by Douglas C. Schmidt # and Bruno Haible . # # This file is part of GNU GPERF. # # GNU GPERF is free software; you can redistribute it and/or modify # it under the terms of the GNU General Public License as published by # the Free Software Foundation; either version 2, or (at your option) # any later version. # # GNU GPERF is distributed in the hope that it will be useful, # but WITHOUT ANY WARRANTY; without even the implied warranty of # MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the # GNU General Public License for more details. # # You should have received a copy of the GNU General Public License # along with this program; see the file COPYING. # If not, write to the Free Software Foundation, Inc., # 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. */ #### Start of system configuration section. #### srcdir = . VPATH = $(srcdir) CXX = g++ CXXFLAGS = -O2 -g OBJECTS = bool-array.o hash-table.o keyword-list.o keyword.o \ options.o positions.o search.o superops.o \ byte_def.o vm_def.o hash.o observer-list.o table.o LIBS = -lm CPPFLAGS = -I. TARGETPROG = superops all : $(TARGETPROG) $(TARGETPROG): $(OBJECTS) $(CXX) $(CXXFLAGS) $(LDFLAGS) -o $(TARGETPROG) $(OBJECTS) $(LIBS) # Dependencies. POSITIONS_H = positions.h positions.icc OPTIONS_H = options.h options.icc $(POSITIONS_H) KEYWORD_H = keyword.h keyword.icc KEYWORD_LIST_H = keyword-list.h keyword-list.icc $(KEYWORD_H) INPUT_H = input.h $(KEYWORD_LIST_H) BOOL_ARRAY_H = bool-array.h bool-array.icc $(OPTIONS_H) HASH_TABLE_H = hash-table.h $(KEYWORD_H) SEARCH_H = search.h $(KEYWORD_LIST_H) $(POSITIONS_H) $(BOOL_ARRAY_H) positions.o : positions.cc $(POSITIONS_H) $(CXX) $(CXXFLAGS) $(CPPFLAGS) -c $(srcdir)/positions.cc options.o : options.cc $(OPTIONS_H) $(CXX) $(CXXFLAGS) $(CPPFLAGS) -c $(srcdir)/options.cc keyword.o : keyword.cc $(KEYWORD_H) $(POSITIONS_H) $(CXX) $(CXXFLAGS) $(CPPFLAGS) -c $(srcdir)/keyword.cc keyword-list.o : keyword-list.cc $(KEYWORD_LIST_H) $(CXX) $(CXXFLAGS) $(CPPFLAGS) -c $(srcdir)/keyword-list.cc input.o : input.cc $(INPUT_H) $(OPTIONS_H) $(CXX) $(CXXFLAGS) $(CPPFLAGS) -c $(srcdir)/input.cc bool-array.o : bool-array.cc $(BOOL_ARRAY_H) $(OPTIONS_H) $(CXX) $(CXXFLAGS) $(CPPFLAGS) -c $(srcdir)/bool-array.cc hash-table.o : hash-table.cc $(HASH_TABLE_H) $(OPTIONS_H) $(CXX) $(CXXFLAGS) $(CPPFLAGS) -c $(srcdir)/hash-table.cc search.o : search.cc $(SEARCH_H) $(OPTIONS_H) $(HASH_TABLE_H) $(CXX) $(CXXFLAGS) $(CPPFLAGS) -c $(srcdir)/search.cc superops.o : superops.cc $(OPTIONS_H) $(KEYWORD_H) $(SEARCH_H) $(OUTPUT_H) \ $(KEYWORD_LIST_H) hash.h byte_def.h vm_def.h observer-list.h $(CXX) $(CXXFLAGS) $(CPPFLAGS) -c $(srcdir)/superops.cc observer-list.o : observer-list.cc observer-list.h $(CXX) $(CXXFLAGS) $(CPPFLAGS) -c $(srcdir)/observer-list.cc table.o : table.cc table.h observer-list.h $(CXX) $(CXXFLAGS) $(CPPFLAGS) -c $(srcdir)/table.cc hash.o : hash.cc hash.h observer-list.h $(CXX) $(CXXFLAGS) $(CPPFLAGS) -c $(srcdir)/hash.cc byte_def.o : byte_def.cc byte_def.h observer-list.h $(CXX) $(CXXFLAGS) $(CPPFLAGS) -c $(srcdir)/byte_def.cc vm_def.o : vm_def.cc vm_def.h observer-list.h $(CXX) $(CXXFLAGS) $(CPPFLAGS) -c $(srcdir)/vm_def.cc mostlyclean : clean clean : $(RM) *~ *.s *.o *.a $(TARGETPROG) core distclean : clean maintainer-clean : distclean .PHONY : all mostlyclean clean distclean maintainer-clean smalltalk-3.2.5/main.c0000644000175000017500000003324212123404352011516 00000000000000/*********************************************************************** * * Main Module * * ***********************************************************************/ /*********************************************************************** * * Copyright 1988,89,90,91,92,94,95,99,2000,2001,2002,2004,2006,2008,2009 * Free Software Foundation, Inc. * Written by Steve Byrne. * * This file is part of GNU Smalltalk. * * GNU Smalltalk is free software; you can redistribute it and/or modify it * under the terms of the GNU General Public License as published by the Free * Software Foundation; either version 2, or (at your option) any later * version. * * Linking GNU Smalltalk statically or dynamically with other modules is * making a combined work based on GNU Smalltalk. Thus, the terms and * conditions of the GNU General Public License cover the whole * combination. * * In addition, as a special exception, the Free Software Foundation * give you permission to combine GNU Smalltalk with free software * programs or libraries that are released under the GNU LGPL and with * independent programs running under the GNU Smalltalk virtual machine. * * You may copy and distribute such a system following the terms of the * GNU GPL for GNU Smalltalk and the licenses of the other code * concerned, provided that you include the source code of that other * code when and as the GNU GPL requires distribution of source code. * * Note that people who make modified versions of GNU Smalltalk are not * obligated to grant this special exception for their modified * versions; it is their choice whether to do so. The GNU General * Public License gives permission to release a modified version without * this exception; this exception also makes it possible to release a * modified version which carries forward this exception. * * GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or * FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for * more details. * * You should have received a copy of the GNU General Public License along with * GNU Smalltalk; see the file COPYING. If not, write to the Free Software * Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * ***********************************************************************/ #ifdef HAVE_CONFIG_H #include "config.h" #endif #include "gstpub.h" #include "getopt.h" #include #include #include #include #include #ifdef ENABLE_DISASSEMBLER #define TRUE_FALSE_ALREADY_DEFINED #include "dis-asm.h" #endif static const char help_text[] = "GNU Smalltalk usage:" "\n" "\n gst [ flag ... ] [ file ... ]" "\n gst [ flag ... ] { -f | --file } file [ args ... ]" "\n" "\nShort flags can appear either as -xyz or as -x -y -z. If an option is" "\nmandatory for a long option, it is also mandatory for a short one. The" "\ncurrently defined set of flags is:" "\n -a --smalltalk-args\t\t Pass the remaining arguments to Smalltalk." "\n -c --core-dump\t\t Dump core on fatal signal." "\n -D --declaration-trace\t Trace compilation of all loaded files." "\n -E --execution-trace\t\t Trace execution of all loaded files." "\n -g --no-gc-message\t\t Do not print garbage collection messages." "\n -H --help\t\t\t Print this message and exit." "\n -i --rebuild-image\t\t Ignore the image file; rebuild it from scratch." "\n --maybe-rebuild-image\t Rebuild the image file from scratch if\n\t\t\t\t any kernel file is newer." "\n -I --image FILE\t\t Instead of `gst.im', use FILE as the image\n\t\t\t\t file, and ignore the kernel files' timestamps.\n" "\n -K --kernel-file FILE\t Make FILE's path relative to the image path." "\n -q --quiet --silent\t\t Do not print execution information." "\n -r --regression-test\t\t Run in regression test mode, i.e. make\n\t\t\t\t printed messages constant." "\n -S --snapshot\t\t Save a snapshot just before exiting." "\n -v --version\t\t\t Print the Smalltalk version number and exit." "\n -V --verbose\t\t\t Show names of loaded files and execution stats." "\n --emacs-mode\t\t Execute as a `process' (from within Emacs)" "\n --kernel-directory DIR\t Look for kernel files in directory DIR." "\n --no-user-files\t\t Don't read user customization files.\n" "\n -\t\t\t\t Read input from standard input explicitly." "\n" "\nFiles are loaded one after the other. After the last one is loaded," "\nSmalltalk will exit. If no files are specified, Smalltalk reads from" "\nthe terminal, with prompts." "\n" "\nIn the second form, the file after -f is the last loaded file; any" "\nparameter after that file is passed to the Smalltalk program." "\n" "\nReport bugs to " "\nGNU Smalltalk home page: ." "\nGeneral help using GNU software: ." "\n\n"; static const char copyright_and_legal_stuff_text[] = "GNU Smalltalk version %s%s" "\nCopyright 2009 Free Software Foundation, Inc." "\nWritten by Steve Byrne (sbb@gnu.org) and Paolo Bonzini (bonzini@gnu.org)" "\n" "\nGNU Smalltalk comes with NO WARRANTY, to the extent permitted by law." "\nYou may redistribute copies of GNU Smalltalk under the terms of the" "\nGNU General Public License. For more information, see the file named" "\nCOPYING." "\n" "\nUsing default kernel path: %s" "\nUsing default image path: %s" "\n\n"; #define OPT_KERNEL_DIR 2 #define OPT_NO_USER 3 #define OPT_EMACS_MODE 4 #define OPT_MAYBE_REBUILD 5 #define OPTIONS "-acDEf:ghiI:K:lL:QqrSvV" static const struct option long_options[] = { {"smalltalk-args", 0, 0, 'a'}, {"core-dump", 0, 0, 'c'}, {"declaration-trace", 0, 0, 'D'}, {"execution-trace", 0, 0, 'E'}, {"file", 0, 0, 'f'}, {"kernel-directory", 1, 0, OPT_KERNEL_DIR}, {"no-user-files", 0, 0, OPT_NO_USER}, {"no-gc-message", 0, 0, 'g'}, {"help", 0, 0, 'h'}, {"maybe-rebuild-image", 0, 0, OPT_MAYBE_REBUILD}, {"rebuild-image", 0, 0, 'i'}, {"image-file", 1, 0, 'I'}, {"kernel-file", 1, 0, 'K'}, {"emacs-mode", 0, 0, OPT_EMACS_MODE}, {"quiet", 0, 0, 'q'}, {"no-messages", 0, 0, 'q'}, {"silent", 0, 0, 'q'}, {"regression-test", 0, 0, 'r'}, {"snapshot", 0, 0, 'S'}, {"version", 0, 0, 'v'}, {"verbose", 0, 0, 'V'}, {NULL, 0, 0, 0} }; struct loaded_file { mst_Boolean kernel_path; const char *file_name; }; static struct loaded_file *loaded_files; int n_loaded_files; /* These contain the default path that was picked (after looking at the environment variables) for the kernel files and the image. */ char *kernel_dir = NULL; /* Mapped to the corresponding GST variable, with additional care to handle more than 1 occurrence of the option. */ int declare_tracing; int execution_tracing; /* Flags to be passed to gst_initialize. Set mostly from command-line variables. */ int flags; /* We implement -S ourselves. This flag is set to 1 if -S is passed. */ mst_Boolean snapshot_after_load; /* This is the name of the binary image to load. If it is not NULL after the command line is parsed, the checking of the dates of the kernel source files against the image file date is overridden. If it is NULL, it is set to default_image_name. */ const char *image_file = NULL; /* Prompt; modified if --emacs-process is given to add a ^A in front of it. */ const char *stdin_prompt = "st> "; #define EMACS_PROCESS_MARKER "\001" void parse_args (int argc, const char **argv) { int ch, prev_optind = 1, minus_a_optind = -1; /* get rid of getopt's own error reporting for invalid options */ opterr = 1; while ((ch = getopt_long (argc, (char **) argv, OPTIONS, long_options, NULL)) != -1) { #if DEBUG_GETOPT printf ("%c \"%s\" %d %d %d\n", ch, optarg ? optarg : "", optind, prev_optind, minus_a_optind); #endif switch (ch) { case 'c': gst_set_var (GST_MAKE_CORE_FILE, true); break; case 'D': declare_tracing++; break; case 'E': execution_tracing++; break; case 'g': gst_set_var (GST_GC_MESSAGE, false); break; case OPT_MAYBE_REBUILD: flags |= GST_MAYBE_REBUILD_IMAGE; break; case 'i': flags |= GST_REBUILD_IMAGE; break; case OPT_EMACS_MODE: stdin_prompt = EMACS_PROCESS_MARKER "st> "; gst_set_var (GST_VERBOSITY, 1); flags |= GST_NO_TTY; break; case 'q': case 'Q': gst_set_var (GST_VERBOSITY, 1); break; case 'r': gst_set_var (GST_REGRESSION_TESTING, true); break; case 'S': snapshot_after_load = true; break; case 'V': gst_set_var (GST_VERBOSITY, 3); break; case 'f': /* Same as -q, passing a file, and -a. */ gst_set_var (GST_VERBOSITY, 0); loaded_files[n_loaded_files].kernel_path = false; loaded_files[n_loaded_files++].file_name = optarg; case 'a': /* "Officially", the C command line ends here. The Smalltalk command line, instead, starts right after the parameter containing -a. -a is handled specially by the code that tests the minus_a_optind variable, so that ./gst -aI xxx yyy for example interprets xxx as the image to be loaded. */ minus_a_optind = optind; break; case 'I': if (image_file) { fprintf (stderr, "gst: Only one -I option should be given\n"); exit (1); } image_file = optarg; break; case 'K': loaded_files[n_loaded_files].kernel_path = true; loaded_files[n_loaded_files++].file_name = optarg; break; case OPT_KERNEL_DIR: if (kernel_dir) { fprintf (stderr, "gst: Only one --kernel-directory option should" " be given\n"); exit (1); } kernel_dir = optarg; break; case OPT_NO_USER: flags |= GST_IGNORE_USER_FILES; break; case 'v': printf (copyright_and_legal_stuff_text, VERSION, PACKAGE_GIT_REVISION, gst_relocate_path (KERNEL_PATH), gst_relocate_path (IMAGE_PATH)); exit (0); case '\1': loaded_files[n_loaded_files].kernel_path = false; loaded_files[n_loaded_files++].file_name = optarg; break; default: /* Fall through and show help message */ case 'h': printf (help_text); exit (ch == 'h' ? 1 : 0); } if (minus_a_optind > -1 && (ch == '\1' || ch == 'f' || optind > prev_optind || optind > minus_a_optind)) { /* If the first argument was not an option, undo and leave. */ if (ch == '\1') optind--; /* If the first argument after -a was not an option, or if there is nothing after -a, or if we finished processing the argument which included -a, leave. */ gst_smalltalk_args (argc - optind, argv + optind); break; } prev_optind = optind; } } int main(int argc, const char **argv) { int result; struct loaded_file *file; loaded_files = (struct loaded_file *) alloca (sizeof (struct loaded_file) * argc); gst_set_executable_path (argv[0]); #ifdef __APPLE__ if (argc >= 2 && strncmp (argv[1], "-psn", 4) == 0) gst_smalltalk_args (argc - 1, argv + 1); else #endif parse_args (argc, argv); /* These might go away in the next release. */ if (!kernel_dir) { kernel_dir = getenv ("SMALLTALK_KERNEL"); if (kernel_dir) { flags |= GST_IGNORE_BAD_KERNEL_PATH; fprintf (stderr, "gst: SMALLTALK_KERNEL variable deprecated, " "use --kernel-directory instead\n"); } } if (!image_file) { const char *image_dir = getenv ("SMALLTALK_IMAGE"); flags |= GST_MAYBE_REBUILD_IMAGE; if (image_dir) { int len = strlen (image_dir); char *p = malloc (len + 8); memcpy (p, image_dir, len); strcpy (p + len, "/gst.im"); image_file = p; flags |= GST_IGNORE_BAD_IMAGE_PATH; fprintf (stderr, "gst: SMALLTALK_IMAGE variable deprecated, " "use -I instead\n"); } } gst_set_var (GST_DECLARE_TRACING, declare_tracing > 1); gst_set_var (GST_EXECUTION_TRACING, execution_tracing > 1); result = gst_initialize (kernel_dir, image_file, flags); if (result) exit (result); gst_set_var (GST_DECLARE_TRACING, declare_tracing > 0); gst_set_var (GST_EXECUTION_TRACING, execution_tracing > 0); for (file = loaded_files; file < &loaded_files[n_loaded_files]; file++) { /* - by itself indicates standard input */ if (!file->kernel_path && !strcmp (file->file_name, "-")) gst_process_stdin (stdin_prompt); else { errno = 0; if (!gst_process_file (file->file_name, file->kernel_path ? GST_DIR_BASE : GST_DIR_ABS)) { if (file->kernel_path) fprintf (stderr, "gst: Couldn't open kernel file `%s': %s\n", file->file_name, strerror (errno)); else fprintf (stderr, "gst: Couldn't open file `%s': %s\n", file->file_name, strerror (errno)); } } } if (n_loaded_files == 0) gst_process_stdin (stdin_prompt); if (snapshot_after_load) gst_msg_sendf (NULL, "%v %o snapshot: %o", gst_class_name_to_oop ("ObjectMemory"), gst_str_msg_send (gst_class_name_to_oop ("File"), "image", NULL)); gst_invoke_hook (GST_ABOUT_TO_QUIT); exit (0); } #ifdef ENABLE_DISASSEMBLER void disassemble(stream, from, to) FILE *stream; char *from, *to; { disassemble_info info; bfd_vma pc = (bfd_vma) from; bfd_vma end = (bfd_vma) to; INIT_DISASSEMBLE_INFO(info, stream, fprintf); info.buffer = NULL; info.buffer_vma = 0; info.buffer_length = end; while (pc < end) { fprintf_vma(stream, pc); putc('\t', stream); #ifdef __i386__ pc += print_insn_i386(pc, &info); #endif #ifdef __ppc__ pc += print_insn_big_powerpc(pc, &info); #endif #ifdef __sparc__ pc += print_insn_sparc(pc, &info); #endif putc('\n', stream); } } #endif smalltalk-3.2.5/makesetup.in0000644000175000017500000003570612130343734012767 00000000000000#! /bin/bash # NSIS installer generator for GNU Smalltalk # Written by Paolo Bonzini. # Copyright (C) 2010 Free Software Foundation, Inc. # # This program is free software: you can redistribute it and/or modify # it under the terms of the GNU General Public License as published by # the Free Software Foundation; either version 2 of the License, or # (at your option) any later version. # # This program is distributed in the hope that it will be useful, # but WITHOUT ANY WARRANTY; without even the implied warranty of # MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the # GNU General Public License for more details. # # You should have received a copy of the GNU General Public License # along with this program. If not, see . # Caveats: # 0) Only Fedora is supported as a cross-compilation environment # 1) Install all mingw packages and wine; start a random wine app # to ensure you have ~/.wine/drive_c # 2) cp -R /usr/i686-pc-mingw32/sys-root/mingw/ ~/.wine/drive_c/mingw # 3) Configure gst as follows: # ../configure \ # --host=i686-pc-mingw32 \ # --prefix=/nonexistent \ # --exec-prefix=/nonexistent \ # --bindir=/nonexistent \ # --datarootdir=/nonexistent \ # --with-imagedir=/nonexistent/image \ # --with-moduledir=/nonexistent/modules \ # --disable-glibtest \ # --disable-gtktest \ # LDFLAGS=-L/usr/i686-pc-mingw32/sys-root/mingw/lib/ # 4) Run ./makesetup unset BASH_ENV CDPATH ENV MAIL MAILPATH export LC_ALL=C LANGUAGE=C (echo <(echo)) >/dev/null 2>&1 || exec bash "$0" "$@" BS="\\" set -e # -------------------------------------------------------------------------- # Autoconf data # -------------------------------------------------------------------------- PACKAGE='@PACKAGE@' PACKAGE_NAME='@PACKAGE_NAME@' PACKAGE_URL='@PACKAGE_URL@' VERSION='@VERSION@' prefix='@prefix@' exec_prefix='@exec_prefix@' datarootdir=@datarootdir@ datadir=@datadir@ pkgdatadir=@pkgdatadir@ bindir=@bindir@ localstatedir=@localstatedir@ imagedir=@imagedir@ libexecdir=@libexecdir@ moduledir=@moduledir@ # -------------------------------------------------------------------------- # Extra definitions # -------------------------------------------------------------------------- builddir=$PWD MINGWROOT=/usr/i686-pc-mingw32/sys-root/mingw # -------------------------------------------------------------------------- # Shell functions # -------------------------------------------------------------------------- array_set() { local name name=$1 shift eval "$name=(\"\$@\")" } array_append() { local name name=$1 shift eval "$name+=(\"\$@\")" } array_copy() { eval "$1=(\"\${$2[@]}\")" } array_concat() { eval "$1+=(\"\${$2[@]}\")" } array_lines() { local template template="%s\n" eval printf \$template "\"\${$1[@]}\"" } array_readfile() { local IFS IFS=$'\n' read -a $1 -d$'\001' -r < $2 || : } array_sort() { local -a _copy local name name=$1 shift array_copy _copy $name array_readfile $name <(array_lines _copy | sort "$@") } array_sub() { local -a _copy array_copy _copy $1 array_readfile $1 <(array_lines _copy | grep -Fvxf <(array_lines $2)) } xargs_dirname() { sed 's/^\(.*[^/]\)\/\/*[^/][^/]*\/*$/\1/; t s/^\(\/\/\)[^/].*/\1/; t s/^\(\/\/\)$/\1/; t s/^\(\/\).*/\1/; t s/.*/./; t' } xargs_basename() { sed 's/^.*\/\([^/][^/]*\)\/*$/\1/; t s/^\/\(\/\/\)$/\1/; t s/^\/\(\/\).*/\1/; t s/.*/./; t' } # -------------------------------------------------------------------------- # Build # -------------------------------------------------------------------------- DESTDIR=$builddir/stage rm -rf $DESTDIR make install DESTDIR=$DESTDIR cd $DESTDIR/nonexistent # not distributed rm -f smalltalk/VFSAddOns.star # no need to manually load dependencies find . -name "*.la" | xargs sed -i "s/^dependency_libs=.*/dependency_libs=''/" # -------------------------------------------------------------------------- # Shell functions to build installation sections # -------------------------------------------------------------------------- n=1 add_section() { eval $1=\$n array_append sections "$2" array_append section_descriptions "$3" shift shift shift array_set outfiles$n "$@" ((n++)) } add_to_section() { local id id=$1 shift array_append outfiles$id "$@" } distribute_mingw_file() { case $1 in /usr/*) return 1 ;; bin/*.dll) return 0 ;; bin/*) return 1 ;; include/*) return 1 ;; */*.def) return 1 ;; */*.o) return 1 ;; */*.a) return 1 ;; */*.la) return 1 ;; */*.pc) return 1 ;; */*.h) return 1 ;; */*.py*) return 1 ;; */*.mo) return 1 ;; # debatable, but saves 6 MB lib/gettext/*) return 1 ;; share/aclocal/*) return 1 ;; share/doc/*) return 1 ;; share/gtk-2.0/demo/*) return 1 ;; share/gtk-doc) return 1 ;; share/info/*) return 1 ;; share/gettext/*) return 1 ;; share/*/gettext/*) return 1 ;; share/*/gettext-tools.mo) return 1 ;; share/man/*) return 1 ;; *) return 0 ;; esac } add_mingw_rpms () { local -a files instfiles local name package dest name=$1 shift for package; do rpm -qi $package >/dev/null || exit 1 array_readfile files <(rpm -ql $package) array_readfile instfiles <( for i in "${files[@]}"; do test -d "$i" && continue dest=${i#$MINGWROOT/} if distribute_mingw_file $dest; then dest=${dest#bin/} mkdir -p `dirname $dest` ln -sf $i $dest echo $dest fi done) array_concat outfiles$name instfiles done } # -------------------------------------------------------------------------- # Installation sections # -------------------------------------------------------------------------- add_section basic \ "Basic installation" \ "Basic installation of GNU Smalltalk, including network access" \ gst.exe \ ./libgst*.dll \ image/gst.im add_mingw_rpms $basic \ mingw32-runtime \ mingw32-libffi \ mingw32-libltdl \ mingw32-libsigsegv add_section ide \ "IDE" \ "IDE for GNU Smalltalk" \ ./gst-browser.exe \ ./gst-blox.exe \ smalltalk/BLOXBrowser.star \ smalltalk/Blox.star \ smalltalk/BloxGTK.star \ smalltalk/Cairo.star \ smalltalk/GTK.star \ smalltalk/VisualGST.star \ smalltalk/examples/Man.st \ smalltalk/examples/Tetris.st \ modules/gst-gtk*.dll \ modules/gst-gtk.la add_mingw_rpms $ide \ mingw32-glib2 mingw32-gtk2 mingw32-pango mingw32-atk \ mingw32-cairo mingw32-pixman \ mingw32-fontconfig mingw32-freetype \ mingw32-jasper mingw32-libjpeg mingw32-libpng \ mingw32-gettext \ mingw32-iconv \ mingw32-zlib add_section devel \ "Module development" \ "Files needed to write extension modules for GNU Smalltalk" \ gst-config \ `find include -type f` \ `find lib -type f` add_section expat \ "Expat" \ "Expat bindings for GNU Smalltalk" \ smalltalk/XML-Expat.star \ modules/expat*.dll \ modules/expat.la add_mingw_rpms $expat mingw32-expat add_section cairo \ "Cairo" \ "Cairo bindings for GNU Smalltalk" \ smalltalk/Cairo.star add_mingw_rpms $cairo mingw32-cairo mingw32-pixman add_section sdl \ "SDL" \ "LibSDL bindings for GNU Smalltalk" \ smalltalk/Cairo.star \ smalltalk/CairoSDL.star \ smalltalk/LibSDL.star \ smalltalk/LibSDL_GL.star \ smalltalk/OpenGL.star \ smalltalk/examples/Cairo*.st \ modules/gstopengl*.dll \ modules/gstopengl.la \ modules/sdl*.dll \ modules/sdl.la add_mingw_rpms $sdl mingw32-cairo mingw32-pixman mingw32-SDL add_section iconv \ "Unicode" \ "Unicode support for GNU Smalltalk (required by Iliad and Seaside)" \ smalltalk/Iconv.star \ modules/iconv*.dll \ modules/iconv.la add_mingw_rpms $iconv mingw32-iconv add_section zlib \ "zlib" \ "zlib bindings for GNU Smalltalk" \ smalltalk/Zlib.star \ modules/zlib*.dll \ modules/zlib.la add_mingw_rpms $zlib mingw32-zlib add_section sqlite \ "sqlite" \ "SQLite bindings for GNU Smalltalk" \ smalltalk/DBD-SQLite.star \ modules/dbd-sqlite3*.dll \ modules/dbd-sqlite3.la add_mingw_rpms $sqlite mingw32-sqlite add_section gdbm \ "GDBM" \ "GDBM bindings for GNU Smalltalk" \ smalltalk/GDBM.star \ modules/gdbm*.dll \ modules/gdbm.la add_mingw_rpms $gdbm mingw32-gdbm add_section gtk \ "GTK+" \ "GTK+ bindings for GNU Smalltalk" \ smalltalk/BLOXBrowser.star \ smalltalk/Blox.star \ smalltalk/BloxGTK.star \ smalltalk/Cairo.star \ smalltalk/GTK.star \ smalltalk/VisualGST.star \ smalltalk/examples/Man.st \ smalltalk/examples/Tetris.st \ modules/gst-gtk*.dll \ modules/gst-gtk.la add_mingw_rpms $gtk \ mingw32-glib2 mingw32-gtk2 mingw32-pango mingw32-atk \ mingw32-cairo mingw32-pixman \ mingw32-fontconfig mingw32-freetype \ mingw32-jasper mingw32-libjpeg mingw32-libpng \ mingw32-gettext \ mingw32-iconv \ mingw32-zlib # Add all other .star files to the Basic section outfiles=() n=1 for i in "${sections[@]}"; do array_concat outfiles outfiles$n ((n++)) done array_readfile packages <( find . -name "gst*.exe" find smalltalk -type f find modules -type f \! -name "*.a") array_sub packages outfiles add_to_section $basic "${packages[@]}" # -------------------------------------------------------------------------- # Prologue # -------------------------------------------------------------------------- declare -a outfiles exec 3>&1 exec > setup.nsi cat << EOF ; ${PACKAGE_NAME} Windows(R) installation script ; Copyright (C) Free Software Foundation, Inc. ; Written by Paolo Bonzini ; Product defines !define PRODUCT_NAME "${PACKAGE_NAME}" !define PRODUCT_WEB_SITE "${PACKAGE_URL}" !define PRODUCT_VERSION "${VERSION}" !define PRODUCT_STARTMENU "${PACKAGE_NAME}" EOF case ${VERSION} in ?*.*.*.*) echo "!define PRODUCT_VERSIONINFO_VERSION \"${VERSION}\"" ;; ?*.*.*) echo "!define PRODUCT_VERSIONINFO_VERSION \"${VERSION}.0\"" ;; ?*.*) echo "!define PRODUCT_VERSIONINFO_VERSION \"${VERSION}.0.0\"" ;; ?*) echo "!define PRODUCT_VERSIONINFO_VERSION \"${VERSION}.0.0.0\"" ;; '') echo "!define PRODUCT_VERSIONINFO_VERSION \"0.0.0.0\"" ;; esac # -------------------------------------------------------------------------- cat << \EOF !define PRODUCT_PUBLISHER "Free Software Foundation, Inc." !define PRODUCT_UNINST_ROOT_KEY "HKLM" !define PRODUCT_UNINST_KEY "Software\Microsoft\Windows\CurrentVersion\Uninstall\${PRODUCT_NAME}" !define PRODUCT_INSTDIR "$PROGRAMFILES\${PRODUCT_NAME}" !define OUTFILE_NAME "setup.exe" ; Include required libraries !include "MUI2.nsh" !include "LogicLib.nsh" !include "WinVer.nsh" !include "x64.nsh" !include "Sections.nsh" ; MUI Settings ; !define MUI_HEADERIMAGE ; !define MUI_HEADERIMAGE_BITMAP "graphics\RHrgbjpg.bmp" !define MUI_ICON "${NSISDIR}\Contrib\Graphics\Icons\modern-install.ico" !define MUI_UNICON "${NSISDIR}\Contrib\Graphics\Icons\modern-uninstall.ico" !define MUI_LICENSEPAGE_CHECKBOX ; MUI pages !insertmacro MUI_PAGE_WELCOME !insertmacro MUI_PAGE_COMPONENTS !insertmacro MUI_PAGE_DIRECTORY !insertmacro MUI_PAGE_INSTFILES !insertmacro MUI_PAGE_FINISH ; Uninstaller pages !insertmacro MUI_UNPAGE_CONFIRM !insertmacro MUI_UNPAGE_INSTFILES ; Language files !insertmacro MUI_LANGUAGE "English" ; NSIS declarations Name "${PRODUCT_NAME} ${PRODUCT_VERSION}" OutFile "${OUTFILE_NAME}" Icon "${MUI_ICON}" UninstallIcon "${MUI_UNICON}" InstallDir "${PRODUCT_INSTDIR}" RequestExecutionLevel admin VIProductVersion "${PRODUCT_VERSIONINFO_VERSION}" VIAddVersionKey /LANG=${LANG_ENGLISH} "ProductName" "${PRODUCT_NAME}" VIAddVersionKey /LANG=${LANG_ENGLISH} "CompanyName" "${PRODUCT_PUBLISHER}" VIAddVersionKey /LANG=${LANG_ENGLISH} "LegalCopyright" "Copyright (C) ${PRODUCT_PUBLISHER}" VIAddVersionKey /LANG=${LANG_ENGLISH} "FileDescription" "${PRODUCT_NAME} Installer" VIAddVersionKey /LANG=${LANG_ENGLISH} "FileVersion" "${PRODUCT_VERSION:-0.0}" EOF # -------------------------------------------------------------------------- # File list # -------------------------------------------------------------------------- n=1 outfiles=() for i in "${sections[@]}"; do echo "Section \"$i\" SEC$n" test $n = 1 && echo ' SectionIn RO' test $n = 1 && echo ' SetOverwrite try' array_concat outfiles outfiles$n array_lines outfiles$n | sort -u | { prevdir=--- while read i; do winpath=`echo "$i" | tr / "$BS$BS" ` dir=`dirname $i` test "$dir" = "$prevdir" || { windirpath='$INSTDIR\'`echo "$dir" | tr / "$BS$BS" ` echo " SetOutPath \"$windirpath\"" } prevdir=$dir echo " File \"$winpath\"" done } echo SectionEnd echo ((n++)) done array_sort outfiles # -------------------------------------------------------------------------- # Post-install # -------------------------------------------------------------------------- cat << \EOF Section -AdditionalIcons CreateDirectory "$SMPROGRAMS\${PRODUCT_STARTMENU}" CreateShortCut "$SMPROGRAMS\${PRODUCT_STARTMENU}\Uninstall.lnk" "$INSTDIR\uninst.exe" EOF n=1 for i in "${sections[@]}"; do cat << EOF !insertmacro SectionFlagIsSet SEC$n \${SF_SELECTED} sec${n}_yes sec${n}_no sec${n}_yes: EOF exe=`array_lines outfiles$n | grep '\.exe$' | head -1` if test -n "$exe"; then name='\$SMPROGRAMS\\\${PRODUCT_STARTMENU}\\${PRODUCT_NAME}' if test $n != 1; then name="$name $i" fi exe='$INSTDIR\'`echo $exe | tr '/' "$BS$BS" ` echo " CreateShortCut \"$name.lnk\" \"$exe\"" fi echo " sec${n}_no:" ((n++)) done cat << \EOF SectionEnd Section -Post WriteUninstaller "$INSTDIR\uninst.exe" WriteRegStr ${PRODUCT_UNINST_ROOT_KEY} "${PRODUCT_UNINST_KEY}" "DisplayName" "$(^Name)" WriteRegStr ${PRODUCT_UNINST_ROOT_KEY} "${PRODUCT_UNINST_KEY}" "UninstallString" "$INSTDIR\uninst.exe" WriteRegStr ${PRODUCT_UNINST_ROOT_KEY} "${PRODUCT_UNINST_KEY}" "DisplayVersion" "${PRODUCT_VERSION}" WriteRegStr ${PRODUCT_UNINST_ROOT_KEY} "${PRODUCT_UNINST_KEY}" "URLInfoAbout" "${PRODUCT_WEB_SITE}" WriteRegStr ${PRODUCT_UNINST_ROOT_KEY} "${PRODUCT_UNINST_KEY}" "Publisher" "${PRODUCT_PUBLISHER}" SectionEnd ; Section descriptions !insertmacro MUI_FUNCTION_DESCRIPTION_BEGIN EOF n=1 for i in "${section_descriptions[@]}"; do echo "!insertmacro MUI_DESCRIPTION_TEXT \${SEC$n} \"$i\"" ((n++)) done cat << \EOF !insertmacro MUI_FUNCTION_DESCRIPTION_END ; Uninstaller Section Uninstall SetOutPath "\" EOF array_lines outfiles | sort -ru | tr '/' "$BS$BS" | \ sed 's/.*/ Delete "$INSTDIR\\&"/' array_lines outfiles | xargs_dirname | sort -ru | tr '/' "$BS$BS" | \ sed '$d; s/.*/ RMDir "$INSTDIR\\&"/' cat << \EOF RMDir "$INSTDIR" Delete "$SMPROGRAMS\${PRODUCT_STARTMENU}\Uninstall.lnk" EOF for i in "${sections[@]}"; do if array_lines outfiles$n | grep '\.exe$' > /dev/null 2>&1; then name='\$SMPROGRAMS\\\${PRODUCT_STARTMENU}\\${PRODUCT_NAME}' if test $n != 1; then name="$name $i" fi echo " Delete \"$name.lnk\"" fi ((n++)) done cat << \EOF RMDir "$SMPROGRAMS\${PRODUCT_STARTMENU}" DeleteRegKey ${PRODUCT_UNINST_ROOT_KEY} "${PRODUCT_UNINST_KEY}" SectionEnd EOF exec >&3- makensis setup.nsi chmod +x setup.exe mv setup.nsi setup.exe ../.. smalltalk-3.2.5/doc/0000755000175000017500000000000012130456010011243 500000000000000smalltalk-3.2.5/doc/gst-base.info0000644000175000017500000013450012130456007013556 00000000000000This is gst-base.info, produced by makeinfo version 4.13 from /home/ich/source/smalltalk/release/smalltalk/doc/gst-base-fixed.texi. INFO-DIR-SECTION Software development START-INFO-DIR-ENTRY * Smalltalk base classes: (gst-base). The GNU Smalltalk base classes. END-INFO-DIR-ENTRY Permission is granted to copy, distribute and/or modify this document under the terms of the GNU Free Documentation License, Version 1.2 or any later version published by the Free Software Foundation; with no Invariant Sections, with no Front-Cover Texts, and with no Back-Cover Texts. A copy of the license is included in the section entitled "GNU Free Documentation License".  Indirect: gst-base.info-1: 694 gst-base.info-2: 300324 gst-base.info-3: 600230 gst-base.info-4: 846615 gst-base.info-5: 1336690  Tag Table: (Indirect) Node: Top694 Node: Base classes1630 Node: AbstractNamespace11930 Node: AbstractNamespace class-instance creation12679 Node: AbstractNamespace-accessing13118 Node: AbstractNamespace-compiling14350 Node: AbstractNamespace-copying14961 Node: AbstractNamespace-namespace hierarchy15411 Node: AbstractNamespace-overrides for superspaces17807 Node: AbstractNamespace-printing18833 Node: AbstractNamespace-testing19418 Node: AlternativeObjectProxy19669 Node: AlternativeObjectProxy class-instance creation20411 Node: AlternativeObjectProxy-accessing21356 Node: ArithmeticError21920 Node: ArithmeticError-description22380 Node: Array22678 Node: Array class-instance creation23392 Node: Array-built ins23707 Node: Array-mutating objects24224 Node: Array-printing24560 Node: Array-testing25054 Node: ArrayedCollection25207 Node: ArrayedCollection class-instance creation26131 Node: ArrayedCollection-basic27828 Node: ArrayedCollection-built ins28966 Node: ArrayedCollection-compiler29231 Node: ArrayedCollection-copying Collections29543 Node: ArrayedCollection-enumerating the elements of a collection31307 Node: ArrayedCollection-sorting32464 Node: ArrayedCollection-storing33037 Node: ArrayedCollection-streams33335 Node: Association33583 Node: Association class-basic34268 Node: Association-accessing34519 Node: Association-finalization35139 Node: Association-printing35372 Node: Association-storing35632 Node: Association-testing35898 Node: Autoload36396 Node: Autoload class-instance creation37064 Node: Autoload-accessing38092 Node: Bag38432 Node: Bag class-basic39140 Node: Bag-adding39409 Node: Bag-enumerating the elements of a collection39902 Node: Bag-extracting items40272 Node: Bag-printing40564 Node: Bag-removing40781 Node: Bag-storing41103 Node: Bag-testing collections41333 Node: Behavior41831 Node: Behavior-accessing class hierarchy43667 Node: Behavior-accessing instances and variables44406 Node: Behavior-accessing the method dictionary46217 Node: Behavior-built ins48068 Node: Behavior-builtin49778 Node: Behavior-compilation50534 Node: Behavior-compilation (alternative)50852 Node: Behavior-compiling51679 Node: Behavior-compiling methods51979 Node: Behavior-creating a class hierarchy52563 Node: Behavior-enumerating53014 Node: Behavior-evaluating54082 Node: Behavior-instance creation55381 Node: Behavior-instance variables56175 Node: Behavior-method dictionary56740 Node: Behavior-parsing class declarations60291 Node: Behavior-pluggable behavior (not yet implemented)60969 Node: Behavior-printing hierarchy61882 Node: Behavior-source code62388 Node: Behavior-still unclassified62728 Node: Behavior-support for lightweight classes63454 Node: Behavior-testing functionality64644 Node: Behavior-testing the class hierarchy64927 Node: Behavior-testing the form of the instances65982 Node: Behavior-testing the method dictionary66919 Node: BindingDictionary68320 Node: BindingDictionary-accessing69227 Node: BindingDictionary-basic & copying71131 Node: BindingDictionary-copying71687 Node: BindingDictionary-forward declarations72368 Node: BindingDictionary-printing72806 Node: BindingDictionary-testing73214 Node: BlockClosure73443 Node: BlockClosure class-instance creation74676 Node: BlockClosure class-testing75558 Node: BlockClosure-accessing75866 Node: BlockClosure-built ins77468 Node: BlockClosure-control structures78491 Node: BlockClosure-exception handling79168 Node: BlockClosure-multiple process81184 Node: BlockClosure-overriding82552 Node: BlockClosure-testing82829 Node: BlockClosure-unwind protection83103 Node: BlockContext84588 Node: BlockContext-accessing85417 Node: BlockContext-debugging86932 Node: BlockContext-printing87351 Node: Boolean87590 Node: Boolean class-testing88351 Node: Boolean-basic88668 Node: Boolean-C hacks89964 Node: Boolean-overriding90226 Node: Boolean-storing90469 Node: ByteArray90885 Node: ByteArray class-instance creation91583 Node: ByteArray-basic91915 Node: ByteArray-built ins92554 Node: ByteArray-CObject93757 Node: ByteArray-converting94127 Node: ByteArray-more advanced accessing94584 Node: ByteArray-storing101504 Node: CAggregate101928 Node: CAggregate class-accessing102232 Node: CAggregate-accessing102522 Node: CallinProcess102760 Node: CallinProcess-debugging103329 Node: CArray103571 Node: CArray-accessing103824 Node: CArrayCType104031 Node: CArrayCType class-instance creation104412 Node: CArrayCType-accessing105107 Node: CArrayCType-basic105511 Node: CArrayCType-storing105807 Node: CBoolean105998 Node: CBoolean class-conversion106344 Node: CBoolean-accessing106556 Node: CByte106921 Node: CByte class-conversion107238 Node: CByte-accessing107531 Node: CCallable107943 Node: CCallable class-instance creation108622 Node: CCallable-accessing109093 Node: CCallable-calling109387 Node: CCallable-restoring111226 Node: CCallbackDescriptor111437 Node: CCallbackDescriptor class-instance creation111970 Node: CCallbackDescriptor-accessing112364 Node: CCallbackDescriptor-restoring112772 Node: CChar113052 Node: CChar class-accessing113370 Node: CChar-accessing113737 Node: CChar-conversion114082 Node: CCompound114483 Node: CCompound class-instance creation114827 Node: CCompound class-subclass creation115252 Node: CCompound-debugging116882 Node: CDouble117239 Node: CDouble class-accessing117521 Node: CDouble-accessing117898 Node: CFloat118228 Node: CFloat class-accessing118516 Node: CFloat-accessing118888 Node: CFunctionDescriptor119213 Node: CFunctionDescriptor class-instance creation120003 Node: CFunctionDescriptor class-testing120439 Node: CFunctionDescriptor-accessing120950 Node: CFunctionDescriptor-printing121384 Node: CFunctionDescriptor-restoring121697 Node: Character121976 Node: Character class-built ins123279 Node: Character class-constants123933 Node: Character class-initializing lookup tables124802 Node: Character class-instance creation125452 Node: Character class-testing125824 Node: Character-built ins126114 Node: Character-coercion methods126903 Node: Character-comparing127682 Node: Character-converting128329 Node: Character-printing128718 Node: Character-storing129206 Node: Character-testing129550 Node: Character-testing functionality130438 Node: CharacterArray130686 Node: CharacterArray class-basic131510 Node: CharacterArray class-multibyte encodings131997 Node: CharacterArray-basic132376 Node: CharacterArray-built ins132780 Node: CharacterArray-comparing133209 Node: CharacterArray-converting135387 Node: CharacterArray-multibyte encodings136929 Node: CharacterArray-still unclassified137505 Node: CharacterArray-string processing137976 Node: CharacterArray-testing functionality141833 Node: CInt142095 Node: CInt class-accessing142366 Node: CInt-accessing142708 Node: Class143043 Node: Class class-initialize144037 Node: Class-accessing instances and variables144284 Node: Class-filing146238 Node: Class-instance creation146670 Node: Class-instance creation - alternative149741 Node: Class-pragmas151919 Node: Class-printing152433 Node: Class-saving and loading152830 Node: Class-security154212 Node: Class-still unclassified154523 Node: Class-testing154895 Node: Class-testing functionality155150 Node: ClassDescription155383 Node: ClassDescription-compiling156167 Node: ClassDescription-conversion157009 Node: ClassDescription-copying157476 Node: ClassDescription-filing158687 Node: ClassDescription-organization of messages and classes159484 Node: ClassDescription-parsing class declarations160913 Node: ClassDescription-printing161422 Node: ClassDescription-still unclassified162219 Node: CLong162772 Node: CLong class-accessing163056 Node: CLong-accessing163423 Node: CLongDouble163743 Node: CLongDouble class-accessing164044 Node: CLongDouble-accessing164441 Node: CLongLong164791 Node: CLongLong class-accessing165086 Node: CLongLong-accessing165473 Node: CObject165813 Node: CObject class-conversion166878 Node: CObject class-instance creation167142 Node: CObject class-primitive allocation167836 Node: CObject class-subclass creation168284 Node: CObject-accessing168661 Node: CObject-basic169612 Node: CObject-C data access169887 Node: CObject-conversion170501 Node: CObject-finalization171164 Node: CObject-pointer-like behavior171642 Node: CObject-testing173942 Node: CObject-testing functionality174188 Node: Collection174398 Node: Collection class-instance creation175558 Node: Collection class-multibyte encodings177006 Node: Collection-adding177346 Node: Collection-compiler177707 Node: Collection-concatenating177970 Node: Collection-converting178532 Node: Collection-copying Collections179798 Node: Collection-copying SequenceableCollections180370 Node: Collection-enumeration180757 Node: Collection-finalization182404 Node: Collection-printing182725 Node: Collection-removing183172 Node: Collection-sorting184128 Node: Collection-storing184715 Node: Collection-testing collections184987 Node: CompiledBlock185937 Node: CompiledBlock class-instance creation186445 Node: CompiledBlock-accessing187214 Node: CompiledBlock-basic188562 Node: CompiledBlock-printing189285 Node: CompiledBlock-saving and loading189566 Node: CompiledCode189992 Node: CompiledCode class-cache flushing190855 Node: CompiledCode class-instance creation191225 Node: CompiledCode class-tables191824 Node: CompiledCode-accessing193059 Node: CompiledCode-basic194787 Node: CompiledCode-copying195690 Node: CompiledCode-debugging195929 Node: CompiledCode-decoding bytecodes196213 Node: CompiledCode-literals - iteration196638 Node: CompiledCode-security197200 Node: CompiledCode-testing accesses197532 Node: CompiledCode-translation198790 Node: CompiledMethod199064 Node: CompiledMethod class-c call-outs200107 Node: CompiledMethod class-instance creation200659 Node: CompiledMethod class-lean images201576 Node: CompiledMethod-accessing201911 Node: CompiledMethod-attributes203797 Node: CompiledMethod-basic204753 Node: CompiledMethod-c call-outs205070 Node: CompiledMethod-compiling205627 Node: CompiledMethod-invoking206477 Node: CompiledMethod-printing207524 Node: CompiledMethod-saving and loading207884 Node: CompiledMethod-source code208345 Node: CompiledMethod-testing209051 Node: ContextPart209800 Node: ContextPart class-built ins210621 Node: ContextPart class-exception handling210936 Node: ContextPart-accessing211384 Node: ContextPart-built ins215309 Node: ContextPart-copying216009 Node: ContextPart-debugging216369 Node: ContextPart-enumerating217482 Node: ContextPart-printing218090 Node: ContextPart-security checks218496 Node: Continuation219062 Node: Continuation class-instance creation219732 Node: Continuation-invocation220406 Node: CPtr221773 Node: CPtr-accessing222015 Node: CPtrCType222564 Node: CPtrCType class-instance creation222924 Node: CPtrCType-accessing223295 Node: CPtrCType-basic223564 Node: CPtrCType-storing223848 Node: CScalar224029 Node: CScalar class-instance creation224325 Node: CScalar-accessing224928 Node: CScalarCType225457 Node: CScalarCType-accessing225755 Node: CScalarCType-storing226097 Node: CShort226333 Node: CShort class-accessing226617 Node: CShort-accessing226989 Node: CSmalltalk227314 Node: CSmalltalk class-accessing227609 Node: CSmalltalk-accessing228001 Node: CString228346 Node: CString class-accessing229394 Node: CString class-instance creation229688 Node: CString-accessing230192 Node: CStringCType230721 Node: CStringCType-accessing230990 Node: CStruct231205 Node: CStruct class-subclass creation231465 Node: CType231706 Node: CType class-C instance creation232898 Node: CType class-initialization233592 Node: CType-accessing233849 Node: CType-basic234895 Node: CType-C instance creation235167 Node: CType-storing236115 Node: CUChar236326 Node: CUChar class-getting info236601 Node: CUChar-accessing236982 Node: CUInt237310 Node: CUInt class-accessing237579 Node: CUInt-accessing237946 Node: CULong238266 Node: CULong class-accessing238543 Node: CULong-accessing238915 Node: CULongLong239240 Node: CULongLong class-accessing239534 Node: CULongLong-accessing239926 Node: CUnion240271 Node: CUnion class-subclass creation240527 Node: CUShort240764 Node: CUShort class-accessing241041 Node: CUShort-accessing241418 Node: Date241748 Node: Date class-basic243260 Node: Date class-instance creation (ANSI)244388 Node: Date class-instance creation (Blue Book)244878 Node: Date-basic246198 Node: Date-compatibility (non-ANSI)246773 Node: Date-date computations247186 Node: Date-printing248897 Node: Date-still unclassified249136 Node: Date-storing249407 Node: Date-testing249640 Node: DateTime249961 Node: DateTime class-information250623 Node: DateTime class-instance creation250914 Node: DateTime class-instance creation (non-ANSI)252313 Node: DateTime-basic253523 Node: DateTime-computations253876 Node: DateTime-printing254568 Node: DateTime-splitting in dates & times254834 Node: DateTime-storing255433 Node: DateTime-testing255698 Node: DateTime-time zones256073 Node: DeferredVariableBinding257203 Node: DeferredVariableBinding class-basic257804 Node: DeferredVariableBinding-basic258443 Node: DeferredVariableBinding-storing258931 Node: Delay259312 Node: Delay class-instance creation260260 Node: Delay class-still unclassified260953 Node: Delay class-timer process261258 Node: Delay-accessing262138 Node: Delay-comparing262765 Node: Delay-copying263045 Node: Delay-delaying263291 Node: Delay-initialization263814 Node: Delay-instance creation264086 Node: Delay-testing264384 Node: Delay-timeout264604 Node: DelayedAdaptor264942 Node: DelayedAdaptor-accessing265474 Node: Dictionary265853 Node: Dictionary class-instance creation267136 Node: Dictionary-accessing267580 Node: Dictionary-awful ST-80 compatibility hacks269558 Node: Dictionary-compilation270010 Node: Dictionary-dictionary enumerating270363 Node: Dictionary-dictionary removing271431 Node: Dictionary-dictionary testing272300 Node: Dictionary-namespace protocol272974 Node: Dictionary-printing275105 Node: Dictionary-rehashing275473 Node: Dictionary-removing275693 Node: Dictionary-storing275978 Node: Dictionary-testing276239 Node: DirectedMessage276515 Node: DirectedMessage class-creating instances277091 Node: DirectedMessage-accessing277817 Node: DirectedMessage-basic278125 Node: DirectedMessage-multiple process279041 Node: DirectedMessage-saving and loading279639 Node: Directory280077 Node: Directory class-file name management280850 Node: Directory class-file operations281389 Node: Directory class-reading system defaults282074 Node: DLD283349 Node: DLD class-C call-outs284029 Node: DLD class-dynamic linking284281 Node: DumperProxy285765 Node: DumperProxy class-accessing286301 Node: DumperProxy class-instance creation286766 Node: DumperProxy-saving and restoring287271 Node: Duration287686 Node: Duration class-instance creation288175 Node: Duration class-instance creation (non ANSI)288887 Node: Duration-arithmetics289366 Node: Duration-processes290669 Node: Duration-storing290959 Node: DynamicVariable291182 Node: DynamicVariable class-evaluating291807 Node: Error292097 Node: Error-exception description292429 Node: Exception292770 Node: Exception class-comparison293910 Node: Exception class-creating ExceptionCollections294379 Node: Exception class-instance creation294806 Node: Exception class-interoperability with TrappableEvents295405 Node: Exception-accessing295767 Node: Exception-built ins296404 Node: Exception-comparison296728 Node: Exception-copying297065 Node: Exception-exception description297358 Node: Exception-exception handling297797 Node: Exception-exception signaling300324 Node: Exception-still unclassified300753 Node: ExceptionSet301140 Node: ExceptionSet class-instance creation301754 Node: ExceptionSet-enumerating302019 Node: ExceptionSet-instance creation302622 Node: False302956 Node: False-basic303355 Node: False-C hacks304349 Node: False-printing304529 Node: File304730 Node: File class-C functions305481 Node: File class-file operations305757 Node: File class-initialization306676 Node: File class-instance creation306945 Node: File class-reading system defaults307432 Node: File class-testing307786 Node: File-accessing308438 Node: File-basic310186 Node: File-directory operations310474 Node: File-file name management310875 Node: File-file operations311272 Node: File-still unclassified312316 Node: File-testing312605 Node: FileDescriptor313453 Node: FileDescriptor class-initialization314789 Node: FileDescriptor class-instance creation315127 Node: FileDescriptor class-still unclassified320223 Node: FileDescriptor-accessing321293 Node: FileDescriptor-basic322610 Node: FileDescriptor-binary I/O324201 Node: FileDescriptor-built ins325770 Node: FileDescriptor-class type methods327858 Node: FileDescriptor-initialize-release328288 Node: FileDescriptor-low-level access328802 Node: FileDescriptor-overriding inherited methods329351 Node: FileDescriptor-polymorphism329963 Node: FileDescriptor-positioning330284 Node: FileDescriptor-printing330591 Node: FileDescriptor-testing330874 Node: FilePath331098 Node: FilePath class-file name management332096 Node: FilePath class-still unclassified333760 Node: FilePath-accessing334067 Node: FilePath-converting336394 Node: FilePath-decoration336607 Node: FilePath-directory operations337089 Node: FilePath-enumerating337603 Node: FilePath-file name management340011 Node: FilePath-file operations341165 Node: FilePath-printing343237 Node: FilePath-still unclassified343743 Node: FilePath-testing344083 Node: FilePath-virtual filesystems345444 Node: FileSegment345647 Node: FileSegment class-basic346297 Node: FileSegment class-installing346814 Node: FileSegment-basic347164 Node: FileSegment-equality348187 Node: FileSegment-printing348499 Node: FileStream348947 Node: FileStream class-file-in349709 Node: FileStream class-standard streams353246 Node: FileStream-basic353986 Node: FileStream-buffering354872 Node: FileStream-compiling356005 Node: FileStream-initialize-release356370 Node: FileStream-overriding inherited methods356665 Node: FileStream-testing357552 Node: Float357774 Node: Float class-byte-order dependancies358868 Node: Float class-characterization359148 Node: Float-arithmetic360170 Node: Float-basic360580 Node: Float-built ins360868 Node: Float-coercing361809 Node: Float-coercion362313 Node: Float-comparing362576 Node: Float-compiler363226 Node: Float-converting363459 Node: Float-floating point363685 Node: Float-misc math363924 Node: Float-printing364146 Node: Float-storing364373 Node: Float-testing364783 Node: Float-testing functionality365642 Node: Float-transcendental operations365880 Node: Float-truncation and round off366538 Node: FloatD366800 Node: FloatD class-byte-order dependencies367339 Node: FloatD class-characterization367734 Node: FloatD class-converting369008 Node: FloatD-built ins369264 Node: FloatD-coercing370501 Node: FloatD-converting370930 Node: FloatE371116 Node: FloatE class-byte-order dependancies371705 Node: FloatE class-byte-order dependencies371997 Node: FloatE class-characterization372363 Node: FloatE class-converting373925 Node: FloatE-built ins374181 Node: FloatE-coercing375418 Node: FloatE-converting375847 Node: FloatQ376033 Node: FloatQ class-byte-order dependancies376580 Node: FloatQ class-characterization376865 Node: FloatQ class-converting378427 Node: FloatQ-built ins378683 Node: FloatQ-coercing379920 Node: FloatQ-converting380349 Node: Fraction380535 Node: Fraction class-converting381326 Node: Fraction class-instance creation381570 Node: Fraction-accessing381955 Node: Fraction-arithmetic382245 Node: Fraction-coercing382969 Node: Fraction-coercion383607 Node: Fraction-comparing383888 Node: Fraction-converting384390 Node: Fraction-optimized cases384959 Node: Fraction-printing385444 Node: Fraction-testing385776 Node: Generator385983 Node: Generator class-instance creation388289 Node: Generator-stream protocol389036 Node: Getopt390099 Node: Getopt class-instance creation390465 Node: Halt393104 Node: Halt-description393402 Node: HashedCollection393653 Node: HashedCollection class-instance creation394514 Node: HashedCollection-accessing394986 Node: HashedCollection-builtins395566 Node: HashedCollection-copying396343 Node: HashedCollection-enumerating the elements of a collection396821 Node: HashedCollection-rehashing397197 Node: HashedCollection-removing397483 Node: HashedCollection-saving and loading397892 Node: HashedCollection-storing398406 Node: HashedCollection-testing collections398733 Node: HomedAssociation399680 Node: HomedAssociation class-basic400250 Node: HomedAssociation-accessing400552 Node: HomedAssociation-finalization400918 Node: HomedAssociation-storing401538 Node: IdentityDictionary401807 Node: IdentitySet402200 Node: IdentitySet-testing402599 Node: Integer402860 Node: Integer class-converting403689 Node: Integer-accessing403921 Node: Integer-basic404160 Node: Integer-bit operators404370 Node: Integer-converting405853 Node: Integer-extension406579 Node: Integer-iterators406892 Node: Integer-math methods407258 Node: Integer-printing408159 Node: Integer-storing410154 Node: Integer-testing functionality410481 Node: Interval410755 Node: Interval class-instance creation411349 Node: Interval-basic411951 Node: Interval-printing412745 Node: Interval-storing413077 Node: Interval-testing413324 Node: Iterable413783 Node: Iterable class-multibyte encodings414336 Node: Iterable-enumeration414628 Node: Iterable-iteration417408 Node: Iterable-streaming418128 Node: LargeArray418426 Node: LargeArray-overridden418829 Node: LargeArrayedCollection419021 Node: LargeArrayedCollection class-instance creation419561 Node: LargeArrayedCollection-accessing419920 Node: LargeArrayedCollection-basic420424 Node: LargeByteArray420825 Node: LargeByteArray-overridden421253 Node: LargeInteger421694 Node: LargeInteger-accessing422529 Node: LargeInteger-arithmetic422768 Node: LargeInteger-bit operations423895 Node: LargeInteger-built-ins424570 Node: LargeInteger-coercion425668 Node: LargeInteger-disabled426214 Node: LargeInteger-primitive operations426589 Node: LargeInteger-testing427069 Node: LargeNegativeInteger427713 Node: LargeNegativeInteger-converting428415 Node: LargeNegativeInteger-numeric testing428803 Node: LargeNegativeInteger-reverting to LargePositiveInteger429338 Node: LargePositiveInteger429910 Node: LargePositiveInteger-arithmetic430789 Node: LargePositiveInteger-converting431267 Node: LargePositiveInteger-helper byte-level methods431823 Node: LargePositiveInteger-numeric testing433562 Node: LargePositiveInteger-primitive operations434100 Node: LargeWordArray434796 Node: LargeWordArray-overridden435228 Node: LargeZeroInteger435529 Node: LargeZeroInteger-accessing436359 Node: LargeZeroInteger-arithmetic436626 Node: LargeZeroInteger-numeric testing437558 Node: LargeZeroInteger-printing437897 Node: Link438197 Node: Link class-instance creation438744 Node: Link-basic438978 Node: Link-iteration439233 Node: LinkedList439696 Node: LinkedList-accessing440343 Node: LinkedList-adding440661 Node: LinkedList-enumerating441396 Node: LinkedList-iteration441880 Node: LinkedList-testing442271 Node: LookupKey442627 Node: LookupKey class-basic443183 Node: LookupKey-accessing443427 Node: LookupKey-printing443694 Node: LookupKey-storing443943 Node: LookupKey-testing444201 Node: LookupTable444637 Node: LookupTable class-instance creation445512 Node: LookupTable-accessing445774 Node: LookupTable-enumerating446583 Node: LookupTable-hashing447108 Node: LookupTable-rehashing447349 Node: LookupTable-removing447574 Node: LookupTable-storing448076 Node: Magnitude448315 Node: Magnitude-basic448771 Node: Magnitude-misc methods449303 Node: MappedCollection449719 Node: MappedCollection class-instance creation451094 Node: MappedCollection-basic451547 Node: Memory453302 Node: Memory class-accessing453862 Node: Message457994 Node: Message class-creating instances458670 Node: Message-accessing459063 Node: Message-basic459505 Node: Message-printing459804 Node: MessageNotUnderstood460136 Node: MessageNotUnderstood-accessing460631 Node: MessageNotUnderstood-description460970 Node: Metaclass461345 Node: Metaclass class-instance creation462388 Node: Metaclass-accessing462673 Node: Metaclass-basic463119 Node: Metaclass-compiling methods464470 Node: Metaclass-delegation464729 Node: Metaclass-filing466409 Node: Metaclass-printing466700 Node: Metaclass-testing functionality467255 Node: MethodContext467516 Node: MethodContext-accessing468058 Node: MethodContext-debugging469611 Node: MethodContext-printing470393 Node: MethodDictionary470639 Node: MethodDictionary-adding471177 Node: MethodDictionary-rehashing471426 Node: MethodDictionary-removing471680 Node: MethodInfo472092 Node: MethodInfo-accessing472578 Node: MethodInfo-equality473523 Node: Namespace473816 Node: Namespace class-accessing474424 Node: Namespace class-disabling instance creation474827 Node: Namespace class-initialization475223 Node: Namespace-accessing475660 Node: Namespace-namespace hierarchy475949 Node: Namespace-overrides for superspaces476447 Node: Namespace-printing478244 Node: NetClients.URIResolver478748 Node: NetClients.URIResolver class-api479203 Node: NetClients.URIResolver class-instance creation480353 Node: NetClients.URL480730 Node: NetClients.URL class-encoding URLs481501 Node: NetClients.URL class-instance creation482006 Node: NetClients.URL-accessing482958 Node: NetClients.URL-comparing485932 Node: NetClients.URL-copying486458 Node: NetClients.URL-initialize-release486995 Node: NetClients.URL-printing487294 Node: NetClients.URL-still unclassified487599 Node: NetClients.URL-testing487926 Node: NetClients.URL-utilities488712 Node: Notification489024 Node: Notification-exception description489477 Node: NullProxy489939 Node: NullProxy class-instance creation490551 Node: NullProxy-accessing490822 Node: NullValueHolder491074 Node: NullValueHolder class-creating instances491663 Node: NullValueHolder-accessing492010 Node: Number492358 Node: Number class-converting493286 Node: Number class-testing494058 Node: Number-arithmetic494326 Node: Number-coercion495658 Node: Number-comparing495931 Node: Number-converting496482 Node: Number-copying498171 Node: Number-error raising498486 Node: Number-misc math498857 Node: Number-point creation501022 Node: Number-retrying501319 Node: Number-shortcuts and iterators503124 Node: Number-testing504373 Node: Number-truncation and round off506056 Node: Object506871 Node: Object class-initialization507896 Node: Object-built ins508495 Node: Object-change and update517489 Node: Object-class type methods518696 Node: Object-compiler519511 Node: Object-conversion519761 Node: Object-copying519998 Node: Object-debugging520662 Node: Object-dependents access521218 Node: Object-error raising521922 Node: Object-finalization522505 Node: Object-introspection523503 Node: Object-printing523874 Node: Object-relational operators525599 Node: Object-saving and loading525963 Node: Object-storing526966 Node: Object-syntax shortcuts527664 Node: Object-testing functionality527991 Node: Object-VM callbacks529590 Node: ObjectDumper530075 Node: ObjectDumper class-establishing proxy classes531280 Node: ObjectDumper class-instance creation532129 Node: ObjectDumper class-shortcuts532542 Node: ObjectDumper class-testing532936 Node: ObjectDumper-accessing533380 Node: ObjectDumper-loading/dumping objects533888 Node: ObjectDumper-stream interface534328 Node: ObjectMemory534710 Node: ObjectMemory class-accessing535795 Node: ObjectMemory class-builtins536062 Node: ObjectMemory class-initialization539351 Node: ObjectMemory class-saving the image539681 Node: ObjectMemory-accessing540067 Node: ObjectMemory-builtins545021 Node: ObjectMemory-derived information545306 Node: OrderedCollection546293 Node: OrderedCollection class-instance creation547105 Node: OrderedCollection-accessing547463 Node: OrderedCollection-adding548028 Node: OrderedCollection-built ins550093 Node: OrderedCollection-enumerating550571 Node: OrderedCollection-removing550879 Node: Package551801 Node: Package class-accessing552395 Node: Package class-instance creation552598 Node: Package-accessing552886 Node: Package-still unclassified556822 Node: Package-version parsing557258 Node: PackageLoader557473 Node: PackageLoader class-accessing558037 Node: PackageLoader class-loading560749 Node: PackageLoader class-testing561149 Node: Permission561440 Node: Permission class-testing561909 Node: Permission-accessing562659 Node: Permission-testing563237 Node: PluggableAdaptor563487 Node: PluggableAdaptor class-creating instances564124 Node: PluggableAdaptor-accessing565205 Node: PluggableProxy565506 Node: PluggableProxy class-accessing566144 Node: PluggableProxy-saving and restoring566594 Node: Point567029 Node: Point class-instance creation567768 Node: Point-accessing568081 Node: Point-arithmetic568515 Node: Point-comparing569234 Node: Point-converting570047 Node: Point-point functions570566 Node: Point-printing571514 Node: Point-storing571748 Node: Point-truncation and round off571996 Node: PositionableStream572408 Node: PositionableStream class-instance creation573426 Node: PositionableStream-accessing-reading573951 Node: PositionableStream-class type methods576063 Node: PositionableStream-compiling576598 Node: PositionableStream-positioning577092 Node: PositionableStream-still unclassified577999 Node: PositionableStream-testing578341 Node: PositionableStream-truncating578830 Node: Process579130 Node: Process-accessing579744 Node: Process-basic580987 Node: Process-builtins582699 Node: Process-debugging583820 Node: Process-printing584057 Node: ProcessEnvironment584272 Node: ProcessEnvironment class-disabled585075 Node: ProcessEnvironment class-singleton585368 Node: ProcessEnvironment-accessing585702 Node: ProcessEnvironment-dictionary removing586984 Node: ProcessEnvironment-dictionary testing587811 Node: ProcessorScheduler588122 Node: ProcessorScheduler class-instance creation588820 Node: ProcessorScheduler-basic589134 Node: ProcessorScheduler-built ins590987 Node: ProcessorScheduler-idle tasks591677 Node: ProcessorScheduler-printing592452 Node: ProcessorScheduler-priorities592771 Node: ProcessorScheduler-storing594476 Node: ProcessorScheduler-timed invocation594817 Node: ProcessVariable595394 Node: ProcessVariable class-accessing595898 Node: ProcessVariable-accessing596799 Node: Promise597537 Node: Promise class-creating instances598161 Node: Promise-accessing598572 Node: Promise-initializing599027 Node: Promise-printing599271 Node: Promise-still unclassified599513 Node: Random599769 Node: Random class-instance creation600230 Node: Random class-shortcuts600612 Node: Random-basic601002 Node: Random-testing601432 Node: ReadStream601758 Node: ReadStream class-instance creation602165 Node: ReadWriteStream602585 Node: ReadWriteStream class-instance creation603083 Node: ReadWriteStream-positioning603721 Node: Rectangle604040 Node: Rectangle class-instance creation604841 Node: Rectangle-accessing605523 Node: Rectangle-copying607937 Node: Rectangle-printing608171 Node: Rectangle-rectangle functions608513 Node: Rectangle-testing610416 Node: Rectangle-transforming611246 Node: Rectangle-truncation and round off611886 Node: RecursionLock612191 Node: RecursionLock class-instance creation612595 Node: RecursionLock-accessing612845 Node: RecursionLock-mutual exclusion613458 Node: RecursionLock-printing613833 Node: Regex614099 Node: Regex class-instance creation615114 Node: Regex-basic615373 Node: Regex-conversion615795 Node: Regex-printing616101 Node: RegexResults616761 Node: RegexResults-accessing617379 Node: RegexResults-testing619035 Node: RootNamespace620067 Node: RootNamespace class-instance creation620627 Node: RootNamespace-namespace hierarchy620976 Node: RootNamespace-overrides for superspaces621423 Node: RootNamespace-printing622054 Node: RunArray622578 Node: RunArray class-instance creation623551 Node: RunArray-accessing623839 Node: RunArray-adding624189 Node: RunArray-basic625277 Node: RunArray-copying625598 Node: RunArray-enumerating625970 Node: RunArray-removing626446 Node: RunArray-searching626927 Node: RunArray-testing627357 Node: ScaledDecimal627616 Node: ScaledDecimal class-instance creation628394 Node: ScaledDecimal-arithmetic628809 Node: ScaledDecimal-coercion629544 Node: ScaledDecimal-comparing630575 Node: ScaledDecimal-constants631227 Node: ScaledDecimal-printing631545 Node: ScaledDecimal-storing632021 Node: SecurityPolicy632462 Node: SecurityPolicy-modifying633050 Node: SecurityPolicy-querying633402 Node: Semaphore633661 Node: Semaphore class-instance creation634337 Node: Semaphore-accessing634726 Node: Semaphore-builtins635226 Node: Semaphore-mutual exclusion636648 Node: Semaphore-printing636998 Node: SequenceableCollection637244 Node: SequenceableCollection class-instance creation638276 Node: SequenceableCollection-basic638770 Node: SequenceableCollection-comparing643414 Node: SequenceableCollection-concatenating643943 Node: SequenceableCollection-copying SequenceableCollections645372 Node: SequenceableCollection-enumerating648155 Node: SequenceableCollection-manipulation651711 Node: SequenceableCollection-replacing items652096 Node: SequenceableCollection-sorting653060 Node: SequenceableCollection-still unclassified653966 Node: SequenceableCollection-testing654329 Node: SequenceableCollection-testing collections654948 Node: Set655284 Node: Set-arithmetic655716 Node: Set-awful ST-80 compatibility hacks656061 Node: Set-comparing656438 Node: SharedQueue656849 Node: SharedQueue class-instance creation657391 Node: SharedQueue-accessing657776 Node: SingletonProxy658294 Node: SingletonProxy class-accessing658915 Node: SingletonProxy class-instance creation659296 Node: SingletonProxy-saving and restoring659753 Node: SmallInteger660196 Node: SmallInteger class-getting limits660933 Node: SmallInteger class-testing661435 Node: SmallInteger-bit arithmetic661747 Node: SmallInteger-built ins662114 Node: SmallInteger-builtins664544 Node: SmallInteger-coercion665303 Node: SmallInteger-coercion methods665617 Node: SmallInteger-testing functionality665989 Node: SortedCollection666238 Node: SortedCollection class-hacking667423 Node: SortedCollection class-instance creation667708 Node: SortedCollection-basic668237 Node: SortedCollection-copying668798 Node: SortedCollection-disabled669121 Node: SortedCollection-enumerating669991 Node: SortedCollection-saving and loading670337 Node: SortedCollection-searching670699 Node: SortedCollection-sorting671335 Node: Stream672059 Node: Stream-accessing-reading673250 Node: Stream-accessing-writing676206 Node: Stream-basic676919 Node: Stream-buffering677110 Node: Stream-built ins677747 Node: Stream-character writing678869 Node: Stream-compiling679736 Node: Stream-concatenating680082 Node: Stream-enumerating680747 Node: Stream-filing out681125 Node: Stream-filtering681487 Node: Stream-polymorphism683080 Node: Stream-positioning683486 Node: Stream-printing684635 Node: Stream-still unclassified685401 Node: Stream-storing685669 Node: Stream-streaming protocol686058 Node: Stream-testing686520 Node: String687045 Node: String class-instance creation688224 Node: String class-multibyte encodings688708 Node: String-accessing689036 Node: String-basic689433 Node: String-built ins690215 Node: String-CObject691945 Node: String-converting692235 Node: String-filesystem692714 Node: String-printing693086 Node: String-regex693934 Node: String-still unclassified701138 Node: String-testing functionality701441 Node: Symbol701658 Node: Symbol class-built ins702551 Node: Symbol class-instance creation702782 Node: Symbol class-symbol table703937 Node: Symbol-accessing the method dictionary705371 Node: Symbol-basic705770 Node: Symbol-built ins706552 Node: Symbol-converting706877 Node: Symbol-misc707233 Node: Symbol-storing707413 Node: Symbol-testing708319 Node: Symbol-testing functionality708605 Node: SymLink708842 Node: SymLink class-instance creation709403 Node: SymLink-accessing709739 Node: SymLink-iteration710090 Node: SymLink-printing710321 Node: SystemDictionary710537 Node: SystemDictionary class-initialization711537 Node: SystemDictionary-basic711812 Node: SystemDictionary-builtins712155 Node: SystemDictionary-c call-outs713501 Node: SystemDictionary-command-line713996 Node: SystemDictionary-miscellaneous716687 Node: SystemDictionary-printing717153 Node: SystemDictionary-profiling717580 Node: SystemDictionary-special accessing717927 Node: SystemDictionary-testing718541 Node: SystemExceptions.AlreadyDefined718893 Node: SystemExceptions.AlreadyDefined-accessing719419 Node: SystemExceptions.ArgumentOutOfRange719687 Node: SystemExceptions.ArgumentOutOfRange class-signaling720287 Node: SystemExceptions.ArgumentOutOfRange-accessing720709 Node: SystemExceptions.BadReturn721303 Node: SystemExceptions.BadReturn-accessing721793 Node: SystemExceptions.CInterfaceError722053 Node: SystemExceptions.CInterfaceError-accessing722564 Node: SystemExceptions.EmptyCollection722848 Node: SystemExceptions.EmptyCollection-accessing723345 Node: SystemExceptions.EndOfStream723629 Node: SystemExceptions.EndOfStream class-signaling724130 Node: SystemExceptions.EndOfStream-accessing724486 Node: SystemExceptions.FileError724922 Node: SystemExceptions.FileError-accessing725411 Node: SystemExceptions.IndexOutOfRange725671 Node: SystemExceptions.IndexOutOfRange class-signaling726267 Node: SystemExceptions.IndexOutOfRange-accessing726649 Node: SystemExceptions.InvalidArgument727179 Node: SystemExceptions.InvalidArgument-accessing727686 Node: SystemExceptions.InvalidProcessState727959 Node: SystemExceptions.InvalidProcessState-accessing728500 Node: SystemExceptions.InvalidSize728800 Node: SystemExceptions.InvalidSize-accessing729277 Node: SystemExceptions.InvalidState729545 Node: SystemExceptions.InvalidState-accessing730080 Node: SystemExceptions.InvalidValue730341 Node: SystemExceptions.InvalidValue class-signaling730879 Node: SystemExceptions.InvalidValue-accessing731344 Node: SystemExceptions.MustBeBoolean731851 Node: SystemExceptions.MustBeBoolean class-signaling732342 Node: SystemExceptions.MutationError732672 Node: SystemExceptions.MutationError class-instance creation733211 Node: SystemExceptions.MutationError-accessing733604 Node: SystemExceptions.NoRunnableProcess733943 Node: SystemExceptions.NoRunnableProcess-accessing734449 Node: SystemExceptions.NotEnoughElements734741 Node: SystemExceptions.NotEnoughElements class-signaling735307 Node: SystemExceptions.NotEnoughElements-accessing735692 Node: SystemExceptions.NotFound736244 Node: SystemExceptions.NotFound class-accessing736770 Node: SystemExceptions.NotFound-accessing737265 Node: SystemExceptions.NotImplemented737571 Node: SystemExceptions.NotImplemented-accessing738039 Node: SystemExceptions.NotIndexable738319 Node: SystemExceptions.NotIndexable-accessing738792 Node: SystemExceptions.NotYetImplemented739064 Node: SystemExceptions.NotYetImplemented-accessing739590 Node: SystemExceptions.PackageNotAvailable739882 Node: SystemExceptions.PackageNotAvailable class-still unclassified740406 Node: SystemExceptions.PackageNotAvailable-description740991 Node: SystemExceptions.PrimitiveFailed741428 Node: SystemExceptions.PrimitiveFailed-accessing741925 Node: SystemExceptions.ProcessBeingTerminated742209 Node: SystemExceptions.ProcessBeingTerminated class-still unclassified742781 Node: SystemExceptions.ProcessBeingTerminated-accessing743163 Node: SystemExceptions.ProcessTerminated743700 Node: SystemExceptions.ProcessTerminated-accessing744235 Node: SystemExceptions.ReadOnlyObject744527 Node: SystemExceptions.ReadOnlyObject-accessing745013 Node: SystemExceptions.SecurityError745293 Node: SystemExceptions.SecurityError class-accessing745867 Node: SystemExceptions.SecurityError-accessing746263 Node: SystemExceptions.ShouldNotImplement746749 Node: SystemExceptions.ShouldNotImplement-accessing747288 Node: SystemExceptions.SubclassResponsibility747584 Node: SystemExceptions.SubclassResponsibility-accessing748169 Node: SystemExceptions.UnhandledException748481 Node: SystemExceptions.UnhandledException-accessing748993 Node: SystemExceptions.UserInterrupt749469 Node: SystemExceptions.UserInterrupt-accessing749937 Node: SystemExceptions.VerificationError750213 Node: SystemExceptions.VerificationError-accessing750698 Node: SystemExceptions.VMError750990 Node: SystemExceptions.VMError-accessing751430 Node: SystemExceptions.WrongArgumentCount751682 Node: SystemExceptions.WrongArgumentCount-accessing752248 Node: SystemExceptions.WrongClass752544 Node: SystemExceptions.WrongClass class-signaling753172 Node: SystemExceptions.WrongClass-accessing753844 Node: SystemExceptions.WrongMessageSent754513 Node: SystemExceptions.WrongMessageSent class-signaling755170 Node: SystemExceptions.WrongMessageSent-accessing755603 Node: TextCollector756208 Node: TextCollector class-accessing756918 Node: TextCollector-accessing757431 Node: TextCollector-printing758339 Node: TextCollector-set up758687 Node: TextCollector-storing759266 Node: Time759610 Node: Time class-basic (UTC)760394 Node: Time class-builtins760948 Node: Time class-clocks762433 Node: Time class-initialization763149 Node: Time class-instance creation763509 Node: Time-accessing (ANSI for DateAndTimes)764760 Node: Time-accessing (non ANSI & for Durations)765292 Node: Time-arithmetic765829 Node: Time-comparing766420 Node: True766721 Node: True-basic767101 Node: True-C hacks768067 Node: True-printing768243 Node: UndefinedObject768441 Node: UndefinedObject-basic769270 Node: UndefinedObject-class creation - alternative769569 Node: UndefinedObject-class polymorphism771858 Node: UndefinedObject-CObject interoperability774936 Node: UndefinedObject-dependents access775364 Node: UndefinedObject-iteration775754 Node: UndefinedObject-printing776523 Node: UndefinedObject-still unclassified777020 Node: UndefinedObject-storing777341 Node: UndefinedObject-testing777830 Node: UnicodeCharacter778779 Node: UnicodeCharacter class-built ins779421 Node: UnicodeCharacter-coercion methods779984 Node: UnicodeString780276 Node: UnicodeString class-converting780895 Node: UnicodeString class-multibyte encodings781273 Node: UnicodeString-built ins781772 Node: UnicodeString-built-ins782092 Node: UnicodeString-converting782349 Node: UnicodeString-multibyte encodings783089 Node: ValueAdaptor783597 Node: ValueAdaptor class-creating instances784091 Node: ValueAdaptor-accessing784395 Node: ValueAdaptor-printing784818 Node: ValueHolder785047 Node: ValueHolder class-creating instances785672 Node: ValueHolder-accessing786071 Node: ValueHolder-initializing786380 Node: VariableBinding786619 Node: VariableBinding-compiler787304 Node: VariableBinding-printing787563 Node: VariableBinding-saving and loading787927 Node: VariableBinding-storing788391 Node: VariableBinding-testing788882 Node: VersionableObjectProxy789156 Node: VersionableObjectProxy class-saving and restoring790057 Node: VersionableObjectProxy-saving and restoring791088 Node: VFS.ArchiveFile791438 Node: VFS.ArchiveFile-ArchiveMember protocol792338 Node: VFS.ArchiveFile-directory operations793407 Node: VFS.ArchiveFile-querying794149 Node: VFS.ArchiveFile-still unclassified794592 Node: VFS.ArchiveFile-TmpFileArchiveMember protocol794945 Node: VFS.ArchiveMember795508 Node: VFS.ArchiveMember-accessing796292 Node: VFS.ArchiveMember-basic797623 Node: VFS.ArchiveMember-delegation797981 Node: VFS.ArchiveMember-directory operations798288 Node: VFS.ArchiveMember-file operations798893 Node: VFS.ArchiveMember-initializing799533 Node: VFS.ArchiveMember-still unclassified800194 Node: VFS.ArchiveMember-testing800720 Node: VFS.FileWrapper801848 Node: VFS.FileWrapper class-initializing802553 Node: VFS.FileWrapper class-instance creation802988 Node: VFS.FileWrapper-accessing803393 Node: VFS.FileWrapper-basic804262 Node: VFS.FileWrapper-delegation804608 Node: VFS.FileWrapper-enumerating806406 Node: VFS.FileWrapper-file operations806764 Node: VFS.FileWrapper-testing807442 Node: VFS.StoredZipMember808166 Node: VFS.StoredZipMember-accessing808641 Node: VFS.StoredZipMember-opening808913 Node: VFS.TmpFileArchiveMember809171 Node: VFS.TmpFileArchiveMember-directory operations809633 Node: VFS.TmpFileArchiveMember-finalization810139 Node: VFS.TmpFileArchiveMember-still unclassified810549 Node: VFS.ZipFile810885 Node: VFS.ZipFile-members811229 Node: Warning812060 Node: Warning-exception description812388 Node: WeakArray812608 Node: WeakArray class-instance creation813113 Node: WeakArray-accessing813412 Node: WeakArray-conversion815076 Node: WeakArray-loading815727 Node: WeakIdentitySet816008 Node: WeakIdentitySet-accessing816525 Node: WeakKeyDictionary816815 Node: WeakKeyDictionary class-hacks817419 Node: WeakKeyDictionary-accessing817751 Node: WeakKeyIdentityDictionary818086 Node: WeakSet818626 Node: WeakSet-accessing819158 Node: WeakSet-copying819541 Node: WeakSet-loading819935 Node: WeakValueIdentityDictionary820203 Node: WeakValueLookupTable820761 Node: WeakValueLookupTable class-hacks821427 Node: WeakValueLookupTable-hacks821741 Node: WeakValueLookupTable-rehashing822355 Node: WordArray822594 Node: WordArray-built ins822949 Node: WriteStream823173 Node: WriteStream class-instance creation823673 Node: WriteStream-accessing-writing824367 Node: WriteStream-positioning825209 Node: ZeroDivide825435 Node: ZeroDivide class-instance creation825940 Node: ZeroDivide-accessing826336 Node: ZeroDivide-description826605 Node: Class index826836 Node: Method index846615 Node: Cross-reference1336690  End Tag Table smalltalk-3.2.5/doc/dbi.texi0000644000175000017500000003651612130455700012634 00000000000000@c Define the class index, method index, and selector cross-reference @ifclear CLASS-INDICES @set CLASS-INDICES @defindex cl @defcodeindex me @defcodeindex sl @end ifclear @c These are used for both TeX and HTML @set BEFORE1 @set AFTER1 @set BEFORE2 @set AFTER2 @ifinfo @c Use asis so that leading and trailing spaces are meaningful. @c Remember we're inside a @menu command, hence the blanks are @c kept in the output. @set BEFORE1 @asis{* } @set AFTER1 @asis{::} @set BEFORE2 @asis{ (} @set AFTER2 @asis{)} @end ifinfo @macro class {a,b} @value{BEFORE1}\a\\a\@b{\b\}@value{AFTER1} @end macro @macro superclass {a,b} \a\\a\@value{BEFORE2}@i{\b\}@value{AFTER2} @end macro @ifnotinfo @macro begindetailmenu @display @end macro @macro enddetailmenu @end display @end macro @end ifnotinfo @ifinfo @macro begindetailmenu @detailmenu @end macro @macro enddetailmenu @end detailmenu @end macro @end ifinfo @iftex @macro beginmenu @end macro @macro endmenu @end macro @end iftex @ifnottex @macro beginmenu @menu @end macro @macro endmenu @end menu @end macro @end ifnottex @beginmenu @ifnottex Alphabetic list: * DBI.ColumnInfo:: * DBI.Connection:: * DBI.ConnectionInfo:: * DBI.FieldConverter:: * DBI.ResultSet:: * DBI.Row:: * DBI.Statement:: * DBI.Table:: @end ifnottex @ifinfo Class tree: @end ifinfo @iftex @section Tree @end iftex @ifnotinfo Classes documented in this manual are @b{boldfaced}. @end ifnotinfo @begindetailmenu @superclass{@t{}, DBI.ROE.RASQLRelation} @class{@t{ }, DBI.Table} @superclass{@t{}, Object} @class{@t{ }, DBI.ColumnInfo} @class{@t{ }, DBI.Connection} @class{@t{ }, DBI.ConnectionInfo} @class{@t{ }, DBI.FieldConverter} @class{@t{ }, DBI.Row} @class{@t{ }, DBI.Statement} @superclass{@t{ }, Iterable} @superclass{@t{ }, Stream} @class{@t{ }, DBI.ResultSet} @enddetailmenu @endmenu @unmacro class @unmacro superclass @unmacro endmenu @unmacro beginmenu @unmacro enddetailmenu @unmacro begindetailmenu @node DBI.ColumnInfo @section DBI.ColumnInfo @clindex DBI.ColumnInfo @table @b @item Defined in namespace DBI @itemx Superclass: Object @itemx Category: DBI-Framework @end table @menu * DBI.ColumnInfo-accessing:: (instance) * DBI.ColumnInfo-printing:: (instance) @end menu @node DBI.ColumnInfo-accessing @subsection DBI.ColumnInfo:@- accessing @table @b @meindex index @item index Return the 1-based index of the column in the result set (abstract). @meindex isNullable @item isNullable Return whether the column can be NULL (always returns true in ColumnInfo). @meindex name @item name Return the name of the column (abstract). @meindex size @item size Return the size of the column (abstract). @meindex type @item type Return a string containing the type of the column (abstract). @end table @node DBI.ColumnInfo-printing @subsection DBI.ColumnInfo:@- printing @table @b @meindex displayOn:@- @item displayOn:@- aStream Print a representation of the receiver on aStream. @meindex printOn:@- @item printOn:@- aStream Print a representation of the receiver on aStream. @end table @node DBI.Connection @section DBI.Connection @clindex DBI.Connection @table @b @item Defined in namespace DBI @itemx Superclass: Object @itemx Category: DBI-Framework I represent a connection to a database. @end table @menu * DBI.Connection class-connecting:: (class) * DBI.Connection class-initialization:: (class) * DBI.Connection-accessing:: (instance) * DBI.Connection-connecting:: (instance) * DBI.Connection-querying:: (instance) @end menu @node DBI.Connection class-connecting @subsection DBI.Connection class:@- connecting @table @b @meindex connect:@-user:@-password:@- @item connect:@- aDSN user:@- aUserName password:@- aPassword Connect to the database server identified by aDSN using the given username and password. The DSN is in the format dbi:@-DriverName:@-dbname=database_name;host=hostname;port=port Where dbi is constant, DriverName is the name of the driver, and everything else is parameters in the form name1=value1;name2=value2;... Individual drivers may parse the parameters differently, though the existing ones all support parameters dbname, host and port. @meindex paramConnect:@-user:@-password:@- @item paramConnect:@- params user:@- aUserName password:@- aPassword Connect to the database server using the parameters in params (a Dictionary) and the given username and password (abstract). @end table @node DBI.Connection class-initialization @subsection DBI.Connection class:@- initialization @table @b @meindex updateDriverList @item updateDriverList Private - Look for new subclasses of Connection. @end table @node DBI.Connection-accessing @subsection DBI.Connection:@- accessing @table @b @meindex >> @item >> aString Returns a Table object corresponding to the given table. @meindex database @item database Returns the database name for this connection. This corresponds to the catalog in SQL standard parlance (abstract). @meindex fieldConverter @item fieldConverter Returns a FieldConverter that can be used to insert Smalltalk objects into queries. @meindex tableAt:@- @item tableAt:@- aString Returns a Table object corresponding to the given table. @meindex tableAt:@-ifAbsent:@- @item tableAt:@- aString ifAbsent:@- aBlock Returns a Table object corresponding to the given table. @end table @node DBI.Connection-connecting @subsection DBI.Connection:@- connecting @table @b @meindex close @item close Close the connection now; should happen on GC too (abstract). @end table @node DBI.Connection-querying @subsection DBI.Connection:@- querying @table @b @meindex do:@- @slindex rowsAffected @item do:@- aSQLQuery Executes a SQL statement (usually one that doesn't return a result set). Return value is a ResultSet, to which you can send #rowsAffected (abstract). @meindex prepare:@- @item prepare:@- aSQLQuery Creates a statement object, that can be executed (with parameters, if applicable) repeatedly (abstract). @meindex primTableAt:@-ifAbsent:@- @item primTableAt:@- aString ifAbsent:@- aBlock Returns a Table object corresponding to the given table. Should be overridden by subclasses. @meindex select:@- @item select:@- aSQLQuery Prepares and executes a SQL statement. Returns the result set or throws an exception on failure (abstract). @end table @node DBI.ConnectionInfo @section DBI.ConnectionInfo @clindex DBI.ConnectionInfo @table @b @item Defined in namespace DBI @itemx Superclass: Object @itemx Category: DBI-Framework A utility class to contain connection info. @end table @menu * DBI.ConnectionInfo class-instance creation:: (class) * DBI.ConnectionInfo-accessing:: (instance) @end menu @node DBI.ConnectionInfo class-instance creation @subsection DBI.ConnectionInfo class:@- instance creation @table @b @meindex fromDSN:@- @item fromDSN:@- aDSN Parse a DSN in the format dbi:@-DriverName:@-dbname=database_name;host=hostname;port=port where dbi is constant, DriverName is the name of the driver, and everything else is parameters in the form name1=value1;name2=value2;... @end table @node DBI.ConnectionInfo-accessing @subsection DBI.ConnectionInfo:@- accessing @table @b @meindex driver @item driver Answer the driver; this is not the driver class. @meindex driver:@- @item driver:@- aString Set the driver; this is not the driver class. @meindex paramString:@- @item paramString:@- aString Set the parameter list. @meindex params @item params Return the parsed parameters in a Dictionary. @meindex scheme @item scheme Answer the scheme; the only supported one is 'dbi'. @meindex scheme:@- @item scheme:@- aString Set the scheme; the only supported one is 'dbi'. @end table @node DBI.FieldConverter @section DBI.FieldConverter @clindex DBI.FieldConverter @table @b @item Defined in namespace DBI @itemx Superclass: Object @itemx Category: DBI @end table @menu * DBI.FieldConverter class-instance creation:: (class) * DBI.FieldConverter-actions:: (instance) * DBI.FieldConverter-converting-smalltalk:: (instance) @end menu @node DBI.FieldConverter class-instance creation @subsection DBI.FieldConverter class:@- instance creation @table @b @meindex new @item new Not commented. @meindex uniqueInstance @item uniqueInstance Not commented. @end table @node DBI.FieldConverter-actions @subsection DBI.FieldConverter:@- actions @table @b @meindex print:@-on:@- @item print:@- aValue on:@- aStream Not commented. @meindex printString:@- @item printString:@- aValue Not commented. @end table @node DBI.FieldConverter-converting-smalltalk @subsection DBI.FieldConverter:@- converting-smalltalk @table @b @meindex writeBoolean:@-on:@- @item writeBoolean:@- aBoolean on:@- aStream Not commented. @meindex writeDate:@-on:@- @item writeDate:@- aDate on:@- aStream Not commented. @meindex writeDateTime:@-on:@- @item writeDateTime:@- aDateTime on:@- aStream Not commented. @meindex writeFloat:@-on:@- @item writeFloat:@- aFloat on:@- aStream Not commented. @meindex writeInteger:@-on:@- @item writeInteger:@- anInteger on:@- aStream Not commented. @meindex writeQuotedDate:@-on:@- @item writeQuotedDate:@- aDate on:@- aStream Not commented. @meindex writeQuotedTime:@-on:@- @item writeQuotedTime:@- aDate on:@- aStream Not commented. @meindex writeTime:@-on:@- @item writeTime:@- aTime on:@- aStream Not commented. @end table @node DBI.ResultSet @section DBI.ResultSet @clindex DBI.ResultSet @table @b @item Defined in namespace DBI @itemx Superclass: Stream @itemx Category: DBI-Framework I represent a result set, ie. the set of rows returned from a SELECT statement. I may also be returned for DML statements (INSERT, UPDATE, DELETE), in which case I only hold the number of rows affected. @end table @menu * DBI.ResultSet-accessing:: (instance) * DBI.ResultSet-cursor access:: (instance) * DBI.ResultSet-printing:: (instance) * DBI.ResultSet-stream protocol:: (instance) @end menu @node DBI.ResultSet-accessing @subsection DBI.ResultSet:@- accessing @table @b @meindex columnAt:@- @item columnAt:@- aIndex Answer the aIndex'th column name. @meindex columnNames @item columnNames Answer an array of column names in order (abstract). @meindex columns @item columns Answer a Dictionary of column name -> ColumnInfo pairs (abstract). @meindex isDML @item isDML Returns true if the statement was not a SELECT or similar operation (e.g. SHOW, DESCRIBE, EXPLAIN). @meindex isSelect @item isSelect Returns true if the statement was a SELECT or similar operation (e.g. SHOW, DESCRIBE, EXPLAIN), false otherwise. @meindex rowCount @item rowCount Returns the number of rows in the result set; error for DML statements. @meindex rows @item rows Answer the contents of the execution result as array of Rows. @meindex rowsAffected @item rowsAffected For DML statments, returns the number of rows affected; error for SELECT statements. @meindex statement @item statement Return the Statement, if any, that generated the result set. @end table @node DBI.ResultSet-cursor access @subsection DBI.ResultSet:@- cursor access @table @b @meindex atEnd @item atEnd Return whether all the rows in the result set have been consumed. (abstract). @meindex fetch @item fetch Return the next row, or nil if at the end of the result set. @meindex next @item next Return the next row, or raise an error if at the end of the stream (abstract). @end table @node DBI.ResultSet-printing @subsection DBI.ResultSet:@- printing @table @b @meindex printOn:@- @item printOn:@- aStream Print a representation of the receiver on aStream. @end table @node DBI.ResultSet-stream protocol @subsection DBI.ResultSet:@- stream protocol @table @b @meindex position @item position Returns the current row index (0-based) in the result set (abstract). @meindex position:@- @item position:@- anInteger Sets the current row index (0-based) in the result set (abstract). @meindex size @item size Returns the number of rows in the result set. @end table @node DBI.Row @section DBI.Row @clindex DBI.Row @table @b @item Defined in namespace DBI @itemx Superclass: Object @itemx Category: DBI-Framework I represent a row in a result set. @end table @menu * DBI.Row-accessing:: (instance) * DBI.Row-printing:: (instance) @end menu @node DBI.Row-accessing @subsection DBI.Row:@- accessing @table @b @meindex asArray @item asArray Return the values of the columns. @meindex asDictionary @item asDictionary Return the names and values of the columns as a dictionary. @meindex at:@- @item at:@- aColumnName Return the value of the named column (abstract). @meindex atIndex:@- @item atIndex:@- aColumnIndex Return the value of the column at the given 1-based index (abstract). @meindex columnAt:@- @item columnAt:@- aIndex Return a ColumnInfo object for the aIndex-th column in the row. @meindex columnCount @item columnCount Return the number of columns in the row. @meindex columnNames @item columnNames Return an array of column names for the columns in the row. @meindex columns @item columns Return a Dictionary of ColumnInfo objects for the columns in the row, where the keys are the column names. @meindex keysAndValuesDo:@- @item keysAndValuesDo:@- aBlock Pass to aBlock each column name and the corresponding value. @meindex resultSet @item resultSet Return the result set that includes the receiver. @end table @node DBI.Row-printing @subsection DBI.Row:@- printing @table @b @meindex printOn:@- @item printOn:@- aStream Print a representation of the receiver on aStream. @end table @node DBI.Statement @section DBI.Statement @clindex DBI.Statement @table @b @item Defined in namespace DBI @itemx Superclass: Object @itemx Category: DBI-Framework I represent a prepared statement. @end table @menu * DBI.Statement class-instance creation:: (class) * DBI.Statement-querying:: (instance) @end menu @node DBI.Statement class-instance creation @subsection DBI.Statement class:@- instance creation @table @b @meindex on:@- @item on:@- aConnection Return a new statement for this connection. @end table @node DBI.Statement-querying @subsection DBI.Statement:@- querying @table @b @meindex execute @item execute Execute with no parameters (abstract). @meindex executeWith:@- @item executeWith:@- aParameter Execute with one parameters. @meindex executeWith:@-with:@- @item executeWith:@- aParam1 with:@- aParam2 Execute with two parameters. @meindex executeWith:@-with:@-with:@- @item executeWith:@- aParam1 with:@- aParam2 with:@- aParam3 Execute with three parameters. @meindex executeWithAll:@- @item executeWithAll:@- aParams Execute taking parameters from the Collection aParams (abstract). @end table @node DBI.Table @section DBI.Table @clindex DBI.Table @table @b @item Defined in namespace DBI @itemx Superclass: DBI.ROE.RASQLRelation @itemx Category: DBI @end table @menu * DBI.Table-accessing:: (instance) * DBI.Table-core:: (instance) * DBI.Table-printing:: (instance) @end menu @node DBI.Table-accessing @subsection DBI.Table:@- accessing @table @b @meindex columnAt:@- @item columnAt:@- aIndex Answer the aIndex'th column name. @meindex columnNames @item columnNames Answer an array of column names in order (abstract). @meindex columns @item columns Not commented. @meindex database @item database Returns the database name for this table. This corresponds to the catalog in SQL standard parlance. @end table @node DBI.Table-core @subsection DBI.Table:@- core @table @b @meindex size @item size Not commented. @end table @node DBI.Table-printing @subsection DBI.Table:@- printing @table @b @meindex print:@-on:@- @item print:@- anObject on:@- aStream Not commented. @end table smalltalk-3.2.5/doc/gst.texi0000644000175000017500000060517612123404352012676 00000000000000\input texinfo.tex @c -*- texinfo -*- @c %**start of header (This is for running Texinfo on a region.) @setfilename gst.info @settitle GNU Smalltalk User's Guide @setchapternewpage odd @c %**end of header (This is for running Texinfo on a region.) @c ******************************************* Values and macros ********* @include vers-gst.texi @ifclear UPDATE-MONTH @set UPDATE-MONTH @value{UPDATED} @end ifclear @macro bulletize{a} @item \a\ @end macro @ifinfo @set SMILE ;-) @end ifinfo @ifnotinfo @set SMILE @end ifnotinfo @c Preferred layout than @uref's @macro hlink{url, link} \link\@footnote{\link\, \url\} @end macro @macro mailto{mail} \mail\ @end macro @ifhtml @unmacro hlink @unmacro mailto @macro hlink{url, link} @uref{\url\, \link\} @end macro @macro mailto{mail} @uref{mailto:\mail\, , \mail\} @end macro @macro url{url} @uref{\url\} @end macro @end ifhtml @macro gst{} @sc{gnu} Smalltalk @end macro @macro gnu{} @sc{gnu} @end macro @dircategory Software development @direntry * Smalltalk: (gst). The @gst{} user's guide. @end direntry @copying @quotation Permission is granted to copy, distribute and/or modify this document under the terms of the GNU Free Documentation License, Version 1.2 or any later version published by the Free Software Foundation; with no Invariant Sections, with no Front-Cover Texts, and with no Back-Cover Texts. A copy of the license is included in the section entitled ``GNU Free Documentation License''. @end quotation @end copying @titlepage @title @sc{gnu} Smalltalk User's Guide @subtitle Version @value{VERSION} @subtitle @value{UPDATE-MONTH} @author by Steven B. Byrne, Paolo Bonzini, Andy Valencia. @comment The following two commands start the copyright page. @page @vskip 0pt plus 1filll @insertcopying @end titlepage @node Top, , , (DIR) @top @ifnottex This document describes installing and operating the @gst{} programming environment. @insertcopying @end ifnottex @menu * Overview:: What @gst{} is. * Using GNU Smalltalk:: Running @gst{}. * Features:: A description of @gst{}'s special features. * Packages:: An easy way to install Smalltalk code into an image. * Emacs:: @gst{} and Emacs. * C and Smalltalk:: @gst{}'s C/Smalltalk interoperability features. * Tutorial:: An introduction to Smalltalk and OOP. @detailmenu --- The detailed node listing --- Using GNU Smalltalk: * Invocation:: What you can specify on the command line. * Operation:: A step-by-step description of the startup process and a short description of how to interact with @gst{}. * Syntax:: A description of the input file syntax * Test suite:: How to run the test suite system. * Legal concerns:: Licensing of GNU Smalltalk Operation: * Command-line processing:: Picking an image path and a kernel path. * Loading or creating an image:: Loading an image or creating a new one. * Starting the system:: After the image is created or restored. Legal concerns: * GPL:: Complying with the GNU GPL. * LGPL:: Complying with the GNU LGPL. Features: * Extended streams:: Extensions to streams, and generators * Regular expressions:: String matching extensions * Namespaces:: Avoiding clashes between class names. * Disk file-IO:: Methods for reading and writing disk files. * Object dumping:: Methods that read and write objects in binary format. * Dynamic loading:: Picking external libraries and modules at run-time. * Documentation:: Automatic documentation generation. * Memory access:: The direct memory accessing classes and methods, plus broadcasts from the virtual machine. * GC:: The @gst{} memory manager. * Security:: Sandboxing and access control. * Special objects:: Methods to assign particular properties to objects. Packages * GTK and VisualGST: GUI. * Parser, STInST, Compiler: Smalltalk-in-Smalltalk. * DBI: Database. * I18N: Locales. * Seaside: Seaside. * Swazoo: Swazoo. * SUnit: SUnit. * Sockets, WebServer, NetClients: Network support. * XML, XPath, XSL: XML. * Other packages: Other packages. Emacs * Editing:: Autoindent and more for @gst{}. * Interactor:: Smalltalk interactor mode. C and Smalltalk: * External modules:: Linking your libraries to the virtual machine * C callout:: Calls from Smalltalk to C * C data types:: Manipulating C data from Smalltalk * Smalltalk types:: Manipulating Smalltalk data from C * Smalltalk callin:: Calls from C to Smalltalk * Object representation:: Manipulating your own Smalltalk objects * Incubator:: Protecting newly created objects from garbage collections * Other C functions:: Handling and creating OOPs * Using Smalltalk:: The Smalltalk environment as an extension library Tutorial: * Getting started:: Starting to explore @gst{} * Some classes:: Using some of the Smalltalk classes * The hierarchy:: The Smalltalk class hierarchy * Creating classes:: Creating a new class of objects * Creating subclasses:: Adding subclasses to another class * Code blocks (I):: Control structures in Smalltalk * Code blocks (II):: Guess what? More control structures * Debugging:: Things go bad in Smalltalk too! * More subclassing:: Coexisting in the class hierarchy * Streams:: Something really powerful * Exception handling:: More sophisticated error handling * Behind the scenes:: Some nice stuff from the Smalltalk innards * And now:: Some final words * The syntax:: For the most die-hard computer scientists @end detailmenu @end menu @node Overview @unnumbered Introduction @gst{} is an implementation that closely follows the Smalltalk-80 language as described in the book @cite{Smalltalk-80: the Language and its Implementation} by Adele Goldberg and David Robson, which will hereinafter be referred to as @cite{the Blue Book}. The Smalltalk programming language is an object oriented programming language. This means, for one thing, that when programming you are thinking of not only the data that an object contains, but also of the operations available on that object. The object's data representation capabilities and the operations available on the object are ``inseparable''; the set of things that you can do with an object is defined precisely by the set of operations, which Smalltalk calls @dfn{methods}, that are available for that object: each object belongs to a @dfn{class} (a datatype and the set of functions that operate on it) or, better, it is an @dfn{instance} of that class. You cannot even examine the contents of an object from the outside---to an outsider, the object is a black box that has some state and some operations available, but that's all you know: when you want to perform an operation on an object, you can only send it a @dfn{message}, and the object picks up the method that corresponds to that message. In the Smalltalk language, everything is an object. This includes not only numbers and all data structures, but even classes, methods, pieces of code within a method (@dfn{blocks} or @dfn{closures}), stack frames (@dfn{contexts}), etc. Even @code{if} and @code{while} structures are implemented as methods sent to particular objects. Unlike other Smalltalks (including Smalltalk-80), @gst{} emphasizes Smalltalk's rapid prototyping features rather than the graphical and easy-to-use nature of the programming environment (did you know that the first GUIs ever ran under Smalltalk?). The availability of a large body of system classes, once you master them, makes it pretty easy to write complex programs which are usually a task for the so called @dfn{scripting languages}. Therefore, even though we have a @sc{gui} environment based on GTK (@pxref{GUI, , GTK and VisualGST}), the goal of the @gst{} project is currently to produce a complete system to be used to write your scripts in a clear, aesthetically pleasing, and philosophically appealing programming language. An example of what can be obtained with Smalltalk in this novel way can be found in @ref{Top, , Class reference, gst-libs, the @gst{} Library Reference}. That part of the manual is entirely generated by a Smalltalk program, starting from the source code for the class libraries distributed together with the system. @node Using GNU Smalltalk @chapter Using @gst{} @menu * Invocation:: What you can specify on the command line. * Operation:: A step-by-step description of the startup process and a short description of how to interact with @gst{}. * Syntax:: A description of the input file syntax * Test suite:: How to run the test suite system. * Legal concerns:: Licensing of GNU Smalltalk @end menu @node Invocation @section Command line arguments The @gst{} virtual machine may be invoked via the following command: @example gst [ flags @dots{} ] [ file @dots{} ] @end example When you invoke @gst{}, it will ensure that the binary image file (called @file{gst.im}) is up to date; if not, it will build a new one as described in @ref{Loading or creating an image,, Loading an image or creating a new one}. Your first invocation should look something like this: @display "Global garbage collection... done" @gst{} ready st> @end display If you specify one or more @var{file}s, they will be read and executed in order, and Smalltalk will exit when end of file is reached. If you don't specify @var{file}, @gst{} reads standard input, issuing a @samp{st>} prompt if the standard input is a terminal. You may specify @option{-} for the name of a file to invoke an explicit read from standard input. @cindex saving @cindex quitting @cindex exiting @findex quit @findex snapshot To exit while at the @samp{st>} prompt, use @kbd{Ctrl-d}, or type @kbd{ObjectMemory quit} followed by @key{RET}. Use @kbd{ObjectMemory snapshot} first to save a new image that you can reload later, if you wish. As is standard for @acronym{GNU}-style options, specifying @option{--} stops the interpretation of options so that every argument that follows is considered a file name even if it begins with a @samp{-}. You can specify both short and long flags; for example, @option{--version} is exactly the same as @option{-v}, but is easier to remember. Short flags may be specified one at a time, or in a group. A short flag or a group of short flags always starts off with a single dash to indicate that what follows is a flag or set of flags instead of a file name; a long flag starts off with two consecutive dashes, without spaces between them. In the current implementation the flags can be intermixed with file names, but their effect is as if they were all specified first. The various flags are interpreted as follows: @table @option @item -a @itemx --smalltalk-args @findex arguments Treat all options afterward as arguments to be given to Smalltalk code retrievable with @code{Smalltalk arguments}, ignoring them as arguments to @gst{} itself. Examples: @multitable {@option{--verbose -aq -c}} {Options seen by @sc{gnu} Smalltalk} {@code{Smalltalk arguments}} @item command line @tab Options seen by @gst{} @tab @code{Smalltalk arguments} @item (empty) @tab (none) @tab @code{#()} @item @option{-Via foo bar} @tab @option{-Vi} @tab @code{#('foo' 'bar')} @item @option{-Vai test} @tab @option{-Vi} @tab @code{#('test')} @item @option{-Vaq} @tab @option{-Vq} @tab @code{#()} @item @option{--verbose -aq -c } @tab @option{--verbose -q} @tab @code{#('-c')} @end multitable @item -c @itemx --core-dump When a fatal signal occurs, produce a core dump before terminating. Without this option, only a backtrace is provided. @item -D @itemx --declaration-trace Print the class name, the method name, and the byte codes that the compiler generates as it compiles methods. Only applies to files that are named explicitly on the command line, unless the flag is given multiple times on the command line. @item -E @itemx --execution-trace Print the byte codes being executed as the interpreter operates. Only works for statements explicitly issued by the user (either interactively or from files given on the command line), unless the flag is given multiple times on the command line. @ignore This option is disabled when the dynamic translator (@pxref{Dynamic translator}) is enabled. @end ignore @item --kernel-directory Specify the directory from which the kernel source files will be loaded. This is used mostly while compiling @gst{} itself. Smalltalk code can retrieve this information with @code{Directory kernel}. @item --no-user-files Don't load any files from @file{~/.st/} (@pxref{Loading or creating an image,, Loading an image or creating a new one}).@footnote{The directory would be called @file{_st/} under MS-DOS. Under OSes that don't use home directories, it would be looked for in the current directory.} This is used mostly while compiling @gst{} itself, to ensure that the installed image is built only from files in the source tree. @item -K @var{file} @itemx --kernel-file @var{file} Load @var{file} in the usual way, but look for it relative to the kernel directory's parent directory, which is usually @file{/usr/local/share/smalltalk/}. See @option{--kernel-dir} above. @cindex shell scripts @item -f @itemx --file The following two command lines are equivalent: @example gst -f @var{file} @file{args...} gst -q @var{file} -a @file{args...} @end example This is meant to be used in the so called ``sharp-bang'' sequence at the beginning of a file, as in @example #! /usr/bin/gst -f @r{@i{@dots{} Smalltalk source code @dots{}}} @end example @gst{} treats the first line as a comment, and the @option{-f} option ensures that the arguments are passed properly to the script. Use this instead to avoid hard-coding the path to @command{gst}:@footnote{The words in the shell command @command{exec} are all quoted, so GNU Smalltalk parses them as five separate comments.} @example #! /bin/sh "exec" "gst" "-f" "$0" "$@@" @r{@i{@dots{} Smalltalk source code @dots{}}} @end example @item -g @itemx --no-gc-messages Suppress garbage collection messages. @item -h @itemx --help Print out a brief summary of the command line syntax of @gst{}, including the definitions of all of the option flags, and then exit. @item -i @itemx --rebuild-image Always build and save a new image file; see @ref{Loading or creating an image,, Loading an image or creating a new one}. @item --maybe-rebuild-image Perform the image checks and rebuild as described in @ref{Loading or creating an image,, Loading an image or creating a new one}. This is the default when @option{-I} is not given. @cindex image path @item -I @var{file} @itemx --image-file @var{file} Use the image file named @var{file} as the image file to load instead of the default location, and set @var{file}'s directory part as the image path. This option completely bypasses checking the file dates on the kernel files; use @option{--maybe-rebuild-image} to restore the usual behavior, writing the newly built image to @var{file} if needed. @item -q @itemx --quiet @itemx --silent Suppress the printing of answered values from top-level expressions while @gst{} runs. @item -r @itemx --regression-test This is used by the regression testing system and is probably not of interest to the general user. It controls printing of certain information. @item -S @itemx --snapshot Save the image after loading files from the command line. Of course this ``snapshot'' is not saved if you include - (stdin) on the command line and exit by typing @kbd{Ctrl-c}. @item -v @itemx --version Print out the @gst{} version number, then exit. @item -V @itemx --verbose Print various diagnostic messages while executing (the name of each file as it's loaded, plus messages about the beginning of execution or how many byte codes were executed). @end table @node Operation @section Startup sequence @strong{Caveat}: @emph{The startup sequence is pretty complicated. If you are not interested in its customization, you can skip the first two sections below. These two sections also don't apply when using the command-line option @option{-I}, unless also using @option{--maybe-rebuild-image}.} You can abort @gst{} at any time during this procedure with @kbd{Ctrl-c}. @menu * Command-line processing:: Picking an image path and a kernel path. * Loading or creating an image:: Loading an image or creating a new one. * Starting the system:: After the image is created or restored. @end menu @node Command-line processing @subsection Picking an image path and a kernel path @cindex image path When @gst{} is invoked, it first chooses two paths, the ``image path'' and the ``kernel path''. The image path is set by considering these paths in succession: @itemize @item the directory part of the @option{--image-file} option if it is given; @item the value of the @env{SMALLTALK_IMAGE} environment variable if it is defined and readable; this step will disappear in a future release; @item the path compiled in the binary (usually, under Unix systems, @file{/usr/local/var/lib/smalltalk} or a similar path under @file{/var}) if it exists and it is readable; @item the current directory. The current directory is also used if the image has to be rebuilt but you cannot write to a directory chosen according to the previous criteria. @end itemize @cindex kernel path The ``kernel path'' is the directory in which to look for Smalltalk code compiled into the base image. The possibilities in this case are: @itemize @item the argument to the @option{--kernel-dir} option if it is given; @item the value of the @env{SMALLTALK_KERNEL} environment variable if it is defined and readable; this step will disappear in a future release; @item the path compiled in the binary (usually, under Unix systems, @file{/usr/local/share/smalltalk/kernel} or a similar data file path) if it exists and it is readable; @item a subdirectory named @file{kernel} of the image path. @end itemize @node Loading or creating an image @subsection Loading an image or creating a new one @cindex compatible images @cindex images, loading @gst{} can load images created on any system with the same pointer size as its host system by approximately the same version of @gst{}, even if they have different endianness. For example, images created on 32-bit PowerPC can be loaded with a 32-bit x86 @command{gst} @acronym{VM}, provided that the @gst{} versions are similar enough. Such images are called @dfn{compatible images}. It cannot load images created on systems with different pointer sizes; for example, our x86 @command{gst} cannot load an image created on x86-64. Unless the @option{-i} flag is used, @gst{} first tries to load the file named by @option{--image-file}, defaulting to @file{gst.im} in the image path. If this is found, @gst{} ensures the image is ``not stale'', meaning its write date is newer than the write dates of all of the kernel method definition files. It also ensures that the image is ``compatible'', as described above. If both tests pass, @gst{} loads the image and continues with @ref{Starting the system,, After the image is created or restored}. If that fails, a new image has to be created. The image path may now be changed to the current directory if the previous choice is not writeable. @cindex kernel, loading To build an image, @gst{} loads the set of files that make up the kernel, one at a time. The list can be found in @file{libgst/lib.c}, in the @code{standard_files} variable. You can override kernel files by placing your own copies in @file{~/.st/kernel/}.@footnote{The directory is called @file{_st/kernel} under MS-DOS. Under OSes that don't use home directories, it is looked for in the current directory.} For example, if you create a file @file{~/.st/kernel/Builtins.st}, it will be loaded instead of the @file{Builtins.st} in the kernel path. @cindex @file{pre.st} @cindex @file{site-pre.st} To aid with image customization and local bug fixes, @gst{} loads two more files (if present) before saving the image. The first is @file{site-pre.st}, found in the parent directory of the kernel directory. Unless users at a site change the kernel directory when running @command{gst}, @file{/usr/local/share/smalltalk/site-pre.st} provides a convenient place for site-wide customization. The second is @file{~/.st/pre.st}, which can be different for each user's home directory.@footnote{The file is looked up as @file{_st/pre.st} under MS-DOS and again, under OSes that don't use home directories it is looked for as @file{pre.st} in the current directory.}. Before the next steps, @gst{} takes a snapshot of the new memory image, saving it over the old image file if it can, or in the current directory otherwise. @node Starting the system @subsection After the image is created or restored @c so it's not a "function"... it's an operation @findex returnFromSnapshot @cindex @file{init.st} Next, @gst{} sends the @code{returnFromSnapshot} event to the dependents of the special class @code{ObjectMemory} (@pxref{Memory access}). Afterwards, it loads @file{~/.st/init.st} if available.@footnote{The same considerations made above hold here too. The file is called @file{_st/init.st} under MS-DOS, and is looked for in the current directory under OSes that don't use home directories.} @cindex startup, customizing @cindex customizing startup You can remember the difference between @file{pre.st} and @file{init.st} by remembering that @file{pre.st} is the @emph{pre}-snapshot file and @file{init.st} is the post-image-load @emph{init}ialization file. Finally, @gst{} loads files listed on the command line, or prompts for input at the terminal, as described in @ref{Invocation,, Command line arguments}. @node Syntax @section Syntax of @gst{} The language that @gst{} accepts is basically the same that other Smalltalk environment accept and the same syntax used in the @dfn{Blue Book}, also known as @cite{Smalltalk-80: The Language and Its Implementation}. The return operator, which is represented in the Blue Book as an up-arrow, is mapped to the ASCII caret symbol @code{^}; the assignment operator (left-arrow) is usually represented as @code{:=}@footnote{It also bears mentioning that there are two assignment operators: @code{_} and @code{:=}. Both are usable interchangeably, provided that they are surrounded by spaces. The @gst{} kernel code uses the @code{:=} form exclusively, but @code{_} is supported a) for compatibility with previous versions of @gst{} b) because this is the correct mapping between the assignment operator mentioned in the Blue Book and the current ASCII definition. In the ancient days (like the middle 70's), the ASCII underscore character was also printed as a back-arrow, and many terminals would display it that way, thus its current usage. Anyway, using @code{_} may lead to portability problems.}. Actually, the grammar of @gst{} is slightly different from the grammar of other Smalltalk environments in order to simplify interaction with the system in a command-line environment as well as in full-screen editors. Statements are executed one by one; multiple statements are separated by a period. At end-of-line, if a valid statement is complete, a period is implicit. For example, @example 8r300. 16rFFFF @end example @noindent prints out the decimal value of octal @code{300} and hex @code{FFFF}, each followed by a newline. Multiple statements share the same local variables, which are automatically declared. To delete the local variables, terminate a statement with @code{!} rather than @code{.} or newline. Here, @example a := 42 a! a @end example @noindent the first two @code{a}s are printed as @code{42}, but the third one is uninitialized and thus printed as @code{nil}. In order to evaluate multiple statements in a single block, wrap them into an @dfn{eval block} as follows: @example Eval [ a := 42. a printString ] @end example @noindent This won't print the intermediate result (the integer 42), only the final result (the string @code{'42'}). @example ObjectMemory quit @end example @noindent exits from the system. You can also type a @kbd{C-d} to exit from Smalltalk if it's reading statements from standard input. @gst{} provides three extensions to the language that make it simpler to write complete programs in an editor. However, it is also compatible with the @dfn{file out} syntax as shown in the @dfn{Green Book} (also known as @cite{Smalltalk-80: Bits of History, Words of Advice} by Glenn Krasner). A new class is created using this syntax: @display @var{superclass-name} @t{subclass:} @var{new-class-name} @t{[} @t{|} @var{instance variables} @t{|} @var{pragmas} @var{message-pattern-1} @t{[} @var{statements} @t{]} @var{message-pattern-2} @t{[} @var{statements} @t{]} @dots{} @var{class-variable-1} @t{:=} @var{expression}@t{.} @var{class-variable-2} @t{:=} @var{expression}@t{.} @dots{} @t{]} @end display In short: @itemize @bullet @item Instance variables are defined with the same syntax as method temporary variables. @item Unlike other Smalltalks, method statements are inside brackets. @item Class variables are defined the same as variable assignments. @item Pragmas define class comment, class category, imported namespaces, and the shape of indexed instance variables. @example @end example @end itemize A similar syntax is used to define new methods in an existing class. @display @var{class-expression} @t{extend} @t{[} @dots{} @t{]} @end display The @var{class-expression} is an expression that evaluates to a class object, which is typically just the name of a class, although it can be the name of a class followed by the word @code{class}, which causes the method definitions that follow to apply to the named class itself, rather than to its instances. @example Number extend [ radiusToArea [ ^self squared * Float pi ] radiusToCircumference [ ^self * 2 * Float pi ] ] @end example A complete treatment of the Smalltalk syntax and of the class library can be found in the included tutorial and class reference (@pxref{Top, , Class Reference, gst-base, the @gst{} Library Reference}). More information on the implementation of the language can be found in the @cite{Blue Book}; the relevant parts are available, scanned, at @url{http://stephane.ducasse.free.fr/FreeBooks/BlueBook/Bluebook.pdf}. @node Test suite @section Running the test suite @gst{} comes with a set of files that provides a simple regression test suite. To run the test suite, you should be connected to the top-level Smalltalk directory. Type @example make check @end example You should see the names of the test suite files as they are processed, but that's it. Any other output indicates some problem. @node Legal concerns @section Licensing of @gst{} Different parts of @gst{} comes under two licenses: the virtual machine and the development environment (compiler and browser) come under the @gnu{} General Public License, while the system class libraries come under the Lesser General Public License. @menu * GPL:: Complying with the GNU GPL. * LGPL:: Complying with the GNU LGPL. @end menu @node GPL @subsection Complying with the @gnu{} @acronym{GPL} The @acronym{GPL} licensing of the virtual machine means that all derivatives of the virtual machine must be put under the same license. In other words, it is strictly forbidden to distribute programs that include the @gst{} virtual machine under a license that is not the GPL. This also includes any bindings to external libraries. For example, the bindings to Gtk+ are released under the @acronym{GPL}. In principle, the @acronym{GPL} would not extend to Smalltalk programs, since these are merely input data for the virtual machine. On the other hand, using bindings that are under the @acronym{GPL} via dynamic linking would constitute combining two parts (the Smalltalk program and the bindings) into one program. Therefore, we added a special exception to the @acronym{GPL} in order to avoid gray areas that could adversely hit both the project and its users: @quotation In addition, as a special exception, the Free Software Foundation give you permission to combine @gst{} with free software programs or libraries that are released under the @gnu{} @acronym{LGPL} and with independent programs running under the @gst{} virtual machine. You may copy and distribute such a system following the terms of the @gnu{} @acronym{GPL} for @gst{} and the licenses of the other code concerned, provided that you include the source code of that other code when and as the @gnu{} @acronym{GPL} requires distribution of source code. Note that people who make modified versions of @gst{} are not obligated to grant this special exception for their modified versions; it is their choice whether to do so. The @gnu{} General Public License gives permission to release a modified version without this exception; this exception also makes it possible to release a modified version which carries forward this exception. @end quotation @node LGPL @subsection Complying with the @gnu{} @acronym{LGPL} Smalltalk programs that run under @gst{} are linked with the system classes in @gst{} class library. Therefore, they must respect the terms of the Lesser General Public License@footnote{Of course, they may be more constrained by usage of @acronym{GPL} class libraries.}. The interpretation of this license for architectures different from that of the C language is often difficult; the accepted one for Smalltalk is as follows. The image file can be considered as an object file, falling under Subsection 6a of the license, as long as it allows a user to load an image, upgrade the library or otherwise apply modifications to it, and save a modified image: this is most conveniently obtained by allowing the user to use the read-eval-print loop that is embedded in the @gst{} virtual machine. In other words, provided that you leave access to the loop in a documented way, or that you provide a way to file in arbitrary files in an image and save the result to a new image, you are obeying Subsection 6a of the Lesser General Public License, which is reported here: @quotation a) Accompany the work with the complete corresponding machine-readable source code for the Library including whatever changes were used in the work (which must be distributed under Sections 1 and 2 above); and, if the work is an executable linked with the Library, with the complete machine-readable "work that uses the Library", as object code and/or source code, so that the user can modify the Library and then relink to produce a modified executable containing the modified Library. (It is understood that the user who changes the contents of definitions files in the Library will not necessarily be able to recompile the application to use the modified definitions.) @end quotation In the future, alternative mechanisms similar to shared libraries may be provided, so that it is possible to comply with the @gnu{} @acronym{LGPL} in other ways. @node Features @chapter Features of @gst{} In this section, the features which are specific to @gst{} are described. These features include support for calling C functions from within Smalltalk, accessing environment variables, and controlling various aspects of compilation and execution monitoring. Note that, in general, @gst{} is much more powerful than the original Smalltalk-80, as it contains a lot of methods that are common in today's Smalltalk implementation and are present in the ANSI Standard for Smalltalk, but were absent in the Blue Book. Examples include Collection's @code{allSatisfy:} and @code{anySatisfy:} methods and many methods in SystemDictionary (the Smalltalk dictionary's class). @menu * Extended streams:: Extensions to streams, and generators * Regular expressions:: String matching extensions * Namespaces:: Avoiding clashes between class names. * Disk file-IO:: Methods for reading and writing disk files. * Object dumping:: Methods that read and write objects in binary format. * Dynamic loading:: Picking external libraries and modules at run-time. * Documentation:: Automatic documentation generation. * Memory access:: The direct memory accessing classes and methods, plus broadcasts from the virtual machine. * GC:: The @gst{} memory manager. * Security:: Sandboxing and access control. * Special objects:: Methods to assign particular properties to objects. @end menu @node Extended streams @section Extended streams The basic image in @gst{} includes powerful extensions to the @emph{Stream} hierarchy found in ANSI Smalltalk (and Smalltalk-80). In particular: @itemize @bullet @item Read streams support all the iteration protocols available for collections. In some cases (like @code{fold:}, @code{detect:}, @code{inject:into:}) these are completely identical. For messages that return a new stream, such as @code{select:} and @code{collect:}, the blocks are evaluated lazily, as elements are requested from the stream using @code{next}. @item Read streams can be concatenated using @code{,} like SequenceableCollections. @item @dfn{Generators} are supported as a quick way to create a Stream. A generator is a kind of pluggable stream, in that a user-supplied blocks defines which values are in a stream. For example, here is an empty generator and two infinite generators: @example "Returns an empty stream" Generator on: [ :gen | ] "Return an infinite stream of 1's" Generator on: [ :gen | [ gen yield: 1 ] repeat ] "Return an infinite stream of integers counting up from 1" Generator inject: 1 into: [ :value | value + 1 ] @end example The block is put ``on hold'' and starts executing as soon as @code{#next} or @code{#atEnd} are sent to the generator. When the block sends @code{#yield:} to the generator, it is again put on hold and the argument becomes the next object in the stream. Generators use @dfn{continuations}, but they shield the users from their complexity by presenting the same simple interface as streams. @end itemize @node Regular expressions @section Regular expression matching @emph{Regular expressions}, or "regexes", are a sophisticated way to efficiently match patterns of text. If you are unfamiliar with regular expressions in general, see @ref{Regexps, Syntax of Regular Expressions, 20.5 Syntax of Regular Expressions, emacs, GNU Emacs Manual}, for a guide for those who have never used regular expressions. @gst{} supports regular expressions in the core image with methods on @code{String}. The @gst{} regular expression library is derived from GNU libc, with modifications made originally for Ruby to support Perl-like syntax. It will always use its included library, and never the ones installed on your system; this may change in the future in backwards-compatible ways. Regular expressions are currently 8-bit clean, meaning they can work with any ordinary String, but do not support full Unicode, even when package @code{I18N} is loaded. Broadly speaking, these regexes support Perl 5 syntax; register groups @samp{()} and repetition @samp{@{@}} must not be given with backslashes, and their counterpart literal characters should. For example, @samp{\@{@{1,3@}} matches @samp{@{}, @samp{@{@{}, @samp{@{@{@{}; correspondingly, @samp{(a)(\()} matches @samp{a(}, with @samp{a} and @samp{(} as the first and second register groups respectively. @gst{} also supports the regex modifiers @samp{imsx}, as in Perl. You can't put regex modifiers like @samp{im} after Smalltalk strings to specify them, because they aren't part of Smalltalk syntax. Instead, use the inline modifier syntax. For example, @samp{(?is:abc.)} is equivalent to @samp{[Aa][Bb][Cc](?:.|\n)}. In most cases, you should specify regular expressions as ordinary strings. @gst{} always caches compiled regexes, and uses a special high-efficiency caching when looking up literal strings (i.e. most regexes), to hide the compiled @code{Regex} objects from most code. For special cases where this caching is not good enough, simply send @code{#asRegex} to a string to retrieved a compiled form, which works in all places in the public API where you would specify a regex string. You should always rely on the cache until you have demonstrated that using Regex objects makes a noticeable performance difference in your code. Smalltalk strings only have one escape, the @samp{'} given by @samp{''}, so backslashes used in regular expression strings will be understood as backslashes, and a literal backslash can be given directly with @samp{\\}@footnote{Whereas it must be given as @samp{\\\\} in a literal Emacs Lisp string, for example.}. The methods on the compiled Regex object are private to this interface. As a public interface, @gst{} provides methods on String, in the category @samp{regex}. There are several methods for matching, replacing, pattern expansion, iterating over matches, and other useful things. The fundamental operator is @code{#searchRegex:}, usually written as @code{#=~}, reminiscent of Perl syntax. This method will always return a @code{RegexResults}, which you can query for whether the regex matched, the location Interval and contents of the match and any register groups as a collection, and other features. For example, here is a simple configuration file line parser: @example | file config | config := LookupTable new. file := (File name: 'myapp.conf') readStream. file linesDo: [:line | (line =~ '(\w+)\s*=\s*((?: ?\w+)+)') ifMatched: [:match | config at: (match at: 1) put: (match at: 2)]]. file close. config printNl. @end example As with Perl, @code{=~} will scan the entire string and answer the leftmost match if any is to be found, consuming as many characters as possible from that position. You can anchor the search with variant messages like @code{#matchRegex:}, or of course @code{^} and @code{$} with their usual semantics if you prefer. You shouldn't modify the string while you want a particular RegexResults object matched on it to remain valid, because changes to the matched text may propagate to the RegexResults object. @c (currently "will", but best to leave open) Analogously to the Perl @code{s} operator, @gst{} provides @code{#replacingRegex:with:}. Unlike Perl, @gst{} employs the pattern expansion syntax of the @code{#%} message here. For example, @code{'The ratio is 16/9.' replacingRegex: '(\d+)/(\d+)' with: '$%1\over%2$'} answers @code{'The ratio is $16\over9$.'}. In place of the @code{g} modifier, use the @code{#replacingAllRegex:with:} message instead. One other interesting String message is @code{#onOccurrencesOfRegex:do:}, which invokes its second argument, a block, on every successful match found in the receiver. Internally, every search will start at the end of the previous successful match. For example, this will print all the words in a stream: @example stream contents onOccurrencesOfRegex: '\w+' do: [:each | each match printNl] @end example @node Namespaces @section Namespaces @i{[This section (and the implementation of namespaces in @gst{}) is based on the paper @cite{Structured Symbolic Name Spaces in Smalltalk}, by Augustin Mrazik.]} @subsection Introduction The Smalltalk-80 programming environment, upon which @gst{} is historically based, supports symbolic identification of objects in one global namespace---in the @code{Smalltalk} system dictionary. This means that each global variable in the system has its unique name which is used for symbolic identification of the particular object in the source code (e.g.@: in expressions or methods). The most important of these global variables are classes defining the behavior of objects. In development dealing with modelling of real systems, @dfn{polymorphic symbolic identification} is often needed. By this, we mean that it should be possible to use the same name for different classes or other global variables. Selection of the proper variable binding should be context-specific. By way of illustration, let us consider class @code{Statement} as an example which would mean totally different things in different domains: @table @asis @item @gst{} or other programming language An expression in the top level of a code body, possibly with special syntax available such as assignment or branching. @item Bank A customer's trace report of recent transactions. @item AI, logical derivation An assertion of a truth within a logical system. @end table This issue becomes inevitable if we start to work persistently, using @code{ObjectMemory snapshot} to save after each session for later resumption. For example, you might have the class @code{Statement} already in your image with the ``Bank'' meaning above (e.g.@: in the live bank support systems we all run in our images) and you might decide to start developing @acronym{YAC} [Yet Another C]. Upon starting to write parse nodes for the compiler, you would find that @code{#Statement} is boundk in the banking package. You could replace it with your parse node class, and the bank's @code{Statement} could remain in the system as an unbound class with full functionality; however, it could not be accessed anymore at the symbolic level in the source code. Whether this would be a problem or not would depend on whether any of the bank's code refers to the class @code{Statement}, and when these references occur. Objects which have to be identified in source code by their names are included in @code{Smalltalk}, the sole instance of @code{SystemDictionary}. Such objects may be identified simply by writing their names as you would any variable names. The code is compiled in the default environment, and if the variable is found in @code{Smalltalk}, without being shadowed by a class pool or local variables, its value is retrieved and used as the value of the expression. In this way @code{Smalltalk} represents the sole symbolic namespace. In the following text the symbolic namespace, as a concept, will be called simply @dfn{environment} to make the text more clear. @subsection Concepts To support polymorphic symbolical identification several environments will be needed. The same name may exist concurrently in several environments as a key, pointing to diverse objects in each. Symbolic navigation between these environments is needed. Before approaching the problem of the syntax and semantics to be implemented, we have to decide on structural relations to be established between environments. Since the environment must first be symbolically identified to direct access to its global variables, it must first itself be a global variable in another environment. @code{Smalltalk} is a great choice for the root environment, from which selection of other environments and their variables begins. From @code{Smalltalk} some of the existing sub-environments may be seen; from these other sub-environments may be seen, etc. This means that environments represent nodes in a graph where symbolic selections from one environment to another one represent branches. The symbolic identification should be unambiguous, although it will be polymorphic. This is why we should avoid cycles in the environment graph. Cycles in the graph could cause also other problems in the implementation, e.g.@: inability to use trivially recursive algorithms. Thus, in general, the environments must build a directed acyclic graph; @gst{} currently limits this to an n-ary tree, with the extra feature that environments can be used as pool dictionaries. Let us call the partial ordering relation which occurs between environments @dfn{inheritance}. Sub-environments inherit from their super-environments. The feature of inheritance in the meaning of object-orientation is associated with this relation: all associations of the super-environment are valid also in its sub-environments, unless they are locally redefined in the sub-environment. A super-environment includes all its sub-enviroments as @code{Association}s under their names. The sub-environment includes its super-environment under the symbol @code{#Super}. Most environments inherit from @code{Smalltalk}, the standard root environment, but they are not required to do so; this is similar to how most classes derive from @code{Object}, yet one can derive a class directly from @code{nil}. Since they all inherit @code{Smalltalk}'s global variables, it is not necessary to define @code{Smalltalk} as pointing to @code{Smalltalk}'s @code{Smalltalk} in each environment. The inheritance links to the super-environments are used in the lookup for a potentially inherited global variable. This includes lookups by a compiler searching for a variable binding and lookups via methods such as @code{#at:} and @code{#includesKey:}. @subsection Syntax Global objects of an environment, be they local or inherited, may be referenced by their symbol variable names used in the source code, e.g. @example John goHome @end example @noindent if the @code{#John -> aMan} association exists in the particular environment or one of its super-environments, all along the way to the root environment. If an object must be referenced from another environment (i.e.@: which is not one of its sub-environments) it has to be referenced either @emph{relatively} to the position of the current environment, using the @code{Super} symbol, or @emph{absolutely}, using the ``full pathname'' of the object, navigating from the tree root (usually @code{Smalltalk}) through the tree of sub-environments. For the identification of global objects in another environment, we use a ``pathname'' of symbols. The symbols are separated by periods; the ``look'' to appear is that of @example Smalltalk.Tasks.MyTask @end example @noindent and of @example Super.Super.Peter. @end example As is custom in Smalltalk, we are reminded by capitalization that we are accessing global objects. Another syntax returns the @dfn{variable binding}, the @code{Association} for a particular global. The first example above is equivalently: @example #@{Smalltalk.Tasks.MyTask@} value @end example The latter syntax, a @dfn{variable binding}, is also valid inside literal arrays. @subsection Implementation A superclass of @code{SystemDictionary} called @code{RootNamespace} is defined, and many of the features of the Smalltalk-80 @code{SystemDictionary} will be hosted by that class. @code{Namespace} and @code{RootNamespace} are in turn subclasses of @code{AbstractNamespace}. To handle inheritance, the following methods have to be defined or redefined in Namespace (@emph{not} in RootNamespace): @table @asis @item Accessors like @code{#at:ifAbsent:} and @code{#includesKey:} Inheritance must be implemented. When @code{Namespace}, trying to read a variable, finds an association in its own dictionary or a super-environment dictionary, it uses that; for @code{Dictionary}'s writes and when a new association must be created, @code{Namespace} creates it in its own dictionary. There are special methods like @code{#set:to:} for cases in which you want to modify a binding in a super-environment if that is the relevant variable's binding. @c this needs more clarity for #at:put: #set:to: disambig @item Enumerators like @code{#do:} and @code{#keys} This should return @strong{all} the objects in the namespace, including those which are inherited. @item Hierarchy access @code{AbstractNamespace} will also implement a new set of methods that allow one to navigate through the namespace hierarchy; these parallel those found in @code{Behavior} for the class hierarchy. @end table The most important task of the @code{Namespace} class is to provide organization for the most important global objects in the Smalltalk system---for the classes. This importance becomes even more crucial in a structure of multiple environments intended to change the semantics of code compiled for those classes. In Smalltalk the classes have the instance variable @code{name} which holds the name of the class. Each @dfn{defined class} is included in @code{Smalltalk}, or another environment, under this name. In a framework with several environments the class should know the environment in which it has been created and compiled. This is a new property of @code{Class} which must be defined and properly used in relevant methods. In the mother environment the class shall be included under its name. Any class, as with any other object, may be included concurrently in several environments, even under different symbols in the same or in diverse environments. We can consider these ``alias names'' of the particular class or other value. A class may be referenced under the other names or in other environments than its mother environment, e.g.@: for the purpose of instance creation or messages to the class, but it should not compile code in these environments, even if this compilation is requested from another environment. If the syntax is not correct in the mother environment, a compilation error occurs. This follows from the existence of class ``mother environments'', as a class is responsible for compiling its own methods. An important issue is also the name of the class answered by the class for the purpose of its identification in diverse tools (e.g.@: in a browser). This must be changed to reflect the environment in which it is shown, i.e.@: the method @samp{nameIn: environment} must be implemented and used in proper places. Other changes must be made to the Smalltalk system to achieve the full functionality of structured environments. In particular, changes have to be made to the behavior classes, the user interface, the compiler, and a few classes supporting persistance. One small detail of note is that evaluation in the @acronym{REPL} or @samp{Workspace}, implemented by compiling methods on @code{UndefinedObject}, make more sense if @code{UndefinedObject}'s environment is the ``current environment'' as reachable by @code{Namespace current}, even though its mother environment by any other sensibility is @code{Smalltalk}. @subsection Using namespaces Using namespaces is often merely a matter of adding a @samp{namespace} option to the @gst{} @acronym{XML} package description used by @code{PackageLoader}, or wrapping your code like this: @example Namespace current: NewNS [ @r{@dots{}} ] @end example Namespaces can be imported into classes like this: @example Stream subclass: EncodedStream [ ] @end example @noindent Alternatively, paths to classes (and other objects) in the namespaces will have to be specified completely. Importing a namespace into a class is similar to C++'s @code{using namespace} declaration within the class proper's definition. Finally, be careful when working with fundamental system classes. Although you can use code like @example Namespace current: NewNS [ Smalltalk.Set subclass: Set [ @r{@dots{}} ] ] @end example @noindent this approach won't work when applied to core classes. For example, you might be successful with a @code{Set} or @code{WriteStream} object, but subclassing @code{SmallInteger} this way can bite you in strange ways: integer literals will still belong to the @code{Smalltalk} dictionary's version of the class (this holds for @code{Array}s, @code{String}s, etc.@: too), primitive operations will still answer standard Smalltalk @code{SmallIntegers}, and so on. Similarly, word-shaped will recognize 32-bit @code{Smalltalk.LargeInteger} objects, but not @code{LargeInteger}s belonging to your own namespace. Unfortunately, this problem is not easy to solve since Smalltalk has to know the @acronym{OOP}s of determinate class objects for speed---it would not be feasible to lookup the environment to which sender of a message belongs every time the @code{+} message was sent to an Integer. So, @gst{} namespaces cannot yet solve 100% of the problem of clashes between extensions to a class---for that you'll still have to rely on prefixes to method names. But they @emph{do} solve the problem of clashes between class names, or between class names and pool dictionary names. Namespaces are unrelated from packages; loading a package does not import the corresponding namespace. @node Disk file-IO @section Disk file-IO primitive messages Four classes (@code{FileDescriptor}, @code{FileStream}, @code{File}, @code{Directory}) allow you to create files and access the file system in a fully object-oriented way. @code{FileDescriptor} and @code{FileStream} are much more powerful than the corresponding C language facilities (the difference between the two is that, like the C @code{stdio} library, @code{FileStream} does buffering). For one thing, they allow you to write raw binary data in a portable endian-neutral format. But, more importantly, these classes transparently implement virtual filesystems and asynchronous I/O. Asynchronous I/O means that an input/output operation blocks the Smalltalk Process that is doing it, but not the others, which makes them very useful in the context of network programming. Virtual file systems mean that these objects can transparently extract files from archives such as @file{tar} and @file{gzip} files, through a mechanism that can be extended through either shell scripting or Smalltalk programming. For more information on these classes, look in the class reference, under the @code{VFS} namespace. @acronym{URL}s may be used as file names; though, unless you have loaded the @code{NetClients} package (@pxref{Network support}), only @code{file} @acronym{URL}s will be accepted. In addition, the three files, @code{stdin}, @code{stdout}, and @code{stderr} are declared as global instances of @code{FileStream} that are bound to the proper values as passed to the C virtual machine. They can be accessed as either @code{stdout} and @code{FileStream stdout}---the former is easier to type, but the latter can be clearer. Finally, @code{Object} defines four other methods: @code{print} and @code{printNl}, @code{store} and @code{storeNl}. These do a @code{printOn:} or @code{storeOn:} to the ``Transcript'' object; this object, which is the sole instance of class @code{TextCollector}, normally delegates write operations to @code{stdout}. If you load the VisualGST @sc{gui}, instead, the Transcript Window will be attached to the Transcript object (@pxref{GUI, , GTK and VisualGST}). The @code{fileIn:} message sent to the FileStream class, with a file name as a string argument, will cause that file to be loaded into Smalltalk. For example, @example FileStream fileIn: 'foo.st' ! @end example @noindent will cause @file{foo.st} to be loaded into @gst{}. @node Object dumping @section The @gst{} ObjectDumper Another @gst{}-specific class, the @code{ObjectDumper} class, allows you to dump objects in a portable, endian-neutral, binary format. Note that you can use the @code{ObjectDumper} on ByteArrays too, thanks to another @gst{}-specific class, @code{ByteStream}, which allows you to treat ByteArrays the same way you would treat disk files. For more information on the usage of the @code{ObjectDumper}, look in the class reference. @node Dynamic loading @section Dynamic loading The @code{DLD} class enhances the C callout mechanism to automatically look for unresolved functions in a series of program-specified libraries. To add a library to the list, evaluate code like the following: @example DLD addLibrary: 'libc' @end example The extension (@file{.so}, @file{.sl}, @file{.a}, @file{.dll} depending on your operating system) will be added automatically. You are advised not to specify it for portability reasons. You will then be able to use the standard C call-out mechanisms to define all the functions in the C run-time library. Note that this is a potential security problem (especially if your program is SUID root under Unix), so you might want to disable dynamic loading when using @gst{} as an extension language. To disable dynamic loading, configure @gst{} passing the @option{--disable-dld} switch. Note that a @code{DLD} class will be present even if dynamic loading is disabled (either because your system is not supported, or by the @option{--disable-dld} configure switch) but any attempt to perform dynamic linking will result in an error. @node Documentation @section Automatic documentation generator @gst{} includes an automatic documentation generator invoked via the @command{gst-doc} command. The code is actually part of the @code{ClassPublisher} package, and @command{gst-doc} takes care of reading the code to be documented and firing a @code{ClassPublisher}. Currently, @command{gst-doc} can only generate output in Texinfo format, though this will change in future releases. @command{gst-doc} can document code that is already in the image, or it can load external files and packages. Note that the latter approach will not work for files and packages that programmatically create code or file in other files/packages. @command{gst-doc} is invoked as follows: @example gst-doc [ @var{flag} ... ] @var{class} ... @end example The following options are supported: @table @option @item -p @var{package} @itemx --package=@var{package} Produce documentation for the classes inside the @var{package} package. @item -f @var{file} @itemx --file=@var{file} Produce documentation for the classes inside the @var{file} file. @item -I @itemx --image-file Produce documentation for the code that is already in the given image. @item -o @itemx --output=@var{file} Emit documentation in the named file. @end table @var{class} is either a class name, or a namespace name followed by @code{.*}. Documentation will be written for classes that are specified in the command line. @var{class} can be omitted if a @option{-f} or @option{-p} option is given. In this case, documentation will be written for all the classes in the package. @node Memory access @section Memory accessing methods @gst{} provides methods to query its own internal data structures. You may determine the real memory address of an object or the real memory address of the OOP table that points to a given object, by using messages to the @code{Memory} class, described below. @defmethod Object asOop Returns the index of the OOP for anObject. This index is immume from garbage collection and is the same value used by default as an hash value for anObject (it is returned by Object's implementation of @code{hash} and @code{identityHash}). @end defmethod @defmethod Integer asObject Converts the given OOP @emph{index} (not address) back to an object. Fails if no object is associated to the given index. @end defmethod @defmethod Integer asObjectNoFail Converts the given OOP @emph{index} (not address) back to an object. Returns nil if no object is associated to the given index. @end defmethod Other methods in ByteArray and Memory allow to read various C types (@code{doubleAt:}, @code{ucharAt:}, etc.). These are mostly obsoleted by @code{CObject} which, in newer versions of @gst{}, supports manually managed heap-backed memory as well as garbage collected ByteArray-backed memory. Another interesting class is ObjectMemory. This provides a few methods that enable one to tune the virtual machine's usage of memory; many methods that in the past were instance methods of Smalltalk or class methods of Memory are now class methods of ObjectMemory. In addition, and that's what the rest of this section is about, the virtual machines signals events to its dependents exactly through this class. The events that can be received are @table @dfn @item returnFromSnapshot This is sent every time an image is restarted, and substitutes the concept of an @dfn{init block} that was present in previous versions. @item aboutToQuit This is sent just before the interpreter is exiting, either because @code{ObjectMemory quit} was sent or because the specified files were all filed in. Exiting from within this event might cause an infinite loop, so be careful. @item aboutToSnapshot This is sent just before an image file is created. Exiting from within this event will leave any preexisting image untouched. @item finishedSnapshot This is sent just after an image file is created. Exiting from within this event will not make the image unusable. @end table @node GC @section Memory management in @gst{} The @gst{} virtual machine is equipped with a garbage collector, a facility that reclaims the space occupied by objects that are no longer accessible from the system roots. The collector is composed of several parts, each of which can be invoked by the virtual machine using various tunable strategies, or invoked manually by the programmer. These parts include a @dfn{generation scavenger}, a @dfn{mark & sweep} collectory with an incremental sweep phase, and a @dfn{compactor}. All these facilities work on different memory spaces and differs from the other in its scope, speed and disadvantages (which are hopefully balanced by the availability of different algorithms). What follows is a description of these algorithms and of the memory spaces they work in. @dfn{NewSpace} is the memory space where young objects live. It is composed of three sub-spaces: an object-creation space (@dfn{Eden}) and two @dfn{SurvivorSpaces}. When an object is first created, it is placed in Eden. When Eden starts to fill up (i.e., when the number of used bytes in Eden exceeds the scavenge threshold), objects that are housed in Eden or in the occupied SurvivorSpace and that are still reachable from the system roots are copied to the unoccupied SurvivorSpace. As an object survives different scavenging passes, it will be shuffled by the scavenger from the occupied SurvivorSpace to the unoccupied one. When the number of used bytes in SurvivorSpace is high enough that the scavenge pause might be excessively long, the scavenger will move some of the older surviving objects from NewSpace to @dfn{OldSpace}. In the garbage collection jargon, we say that such objects are being @dfn{tenured} to OldSpace. This garbage collection algorithm is designed to reclaim short-lived objects, that is those objects that expire while residing in NewSpace, and to decide when enough data is residing in NewSpace that it is useful to move some of it in OldSpace. A @dfn{copying} garbage collector is particularly efficient in an object population whose members are more likely to die than survive, because this kind of scavenger spends most of its time copying survivors, who will be few in number in such populations, rather than tracing corpses, who will be many in number. This fact makes copying collection especially well suited to NewSpace, where a percentage of 90% or more objects often fails to survive across a single scavenge. The particular structure of NewSpace has many advantages. On one hand, having a large Eden and two small SurvivorSpaces has a smaller memory footprint than having two equally big semi-spaces and allocating new objects directly from the occupied one (by default, @gst{} uses 420=300+60*2 kilobytes of memory, while a simpler configuration would use 720=360*2 kilobytes). On the other hand, it makes tenuring decisions particularly simple: the copying order is such that short-lived objects tend to be copied last, while objects that are being referred from OldSpace tend to be copied first: this is because the tenuring strategy of the scavenger is simply to treat the destination SurvivorSpace as a circular buffer, tenuring objects with a First-In-First-Out policy. An object might become part of the scavenger root set for several reasons: objects that have been tenured are roots if their data lives in an OldSpace page that has been written to since the last scavenge (more on this later), plus all objects can be roots if they are known to be referenced from C code or from the Smalltalk stacks. In turn, some of the old objects can be made to live in a special area, called @dfn{FixedSpace}. Objects that reside in FixedSpace are special in that their body is guaranteed to remain at a fixed address (in general, @gst{} only ensures that the header of the object remains at a fixed address in the Object Table). Because the garbage collector can and does move objects, passing objects to foreign code which uses the object's address as a fixed key, or which uses a ByteArray as a buffer, presents difficulties. One can use @code{CObject} to manipulate C data on the @code{malloc} heap, which indeed does not move, but this can be tedious and requires the same attentions to avoid memory leaks as coding in C. FixedSpace provides a much more convenient mechanism: once an object is deemed fixed, the object's body will never move through-out its life-time; the space it occupies will however still be returned automatically to the FixedSpace pool when the object is garbage collected. Note that because objects in FixedSpace cannot move, FixedSpace cannot be compacted and can therefore suffer from extensive fragmentation. For this reason, FixedSpace should be used carefully. FixedSpace however is rebuilt (of course) every time an image is brought up, so a kind of compaction of FixedSpace can be achieved by saving a snapshot, quitting, and then restarting the newly saved image. Memory for OldSpace and FixedSpace is allocated using a variation of the system allocator @code{malloc}: in fact, @gst{} uses the same allocator for its own internal needs, for OldSpace and for FixedSpace, but it ensures that a given memory page never hosts objects that reside in separate spaces. New pages are mapped into the address space as needed and devoted to OldSpace or FixedSpace segments; similarly, when unused they may be subsequently unmapped, or they might be left in place waiting to be reused by @code{malloc} or by another Smalltalk data space. Garbage that is created among old objects is taken care of by a mark & sweep collector which, unlike the scavenger which only reclaims objects in NewSpace, can only reclaim objects in OldSpace. Note that as objects are allocated, they will not only use the space that was previously occupied in the Eden by objects that have survived, but they will also reuse the entries in the global Object Table that have been freed by object that the scavenger could reclaim. This quest for free object table entries can be combined with the sweep phase of the OldSpace collector, which can then be done incrementally, limiting the disruptive part of OldSpace garbage collection to the mark phase. Several runs of the mark & sweep collector can lead to fragmentation (where objects are allocated from several pages, and then become garbage in an order such that a bunch of objects remain in each page and the system is not able to recycle them). For this reason, the system periodically tries to compact OldSpace. It does so simply by looping through every old object and copying it into a new OldSpace. Since the OldSpace allocator does not suffer from fragmentation until objects start to be freed nor after all objects are freed, at the end of the copy all the pages in the fragmented OldSpace will have been returned to the system (some of them might already have been used by the compacted OldSpace), and the new, compacted OldSpace is ready to be used as the system OldSpace. Growing the object heap (which is done when it is found to be quite full even after a mark & sweep collection) automatically triggers a compaction. You can run the compactor without marking live objects. Since the amount of garbage in OldSpace is usually quite limited, the overhead incurred by copying potentially dead objects is small enough that the compactor still runs considerably faster than a full garbage collection, and can still give the application some breathing room. Keeping OldSpace and FixedSpace in the same heap would then make compaction of OldSpace (whereby it is rebuilt from time to time in order to limit fragmentation) much less effective. Also, the @code{malloc} heap is not used for FixedSpace objects because @gst{} needs to track writes to OldSpace and FixedSpace in order to support efficient scavenging of young objects. To do so, the grey page table@footnote{The denomination @dfn{grey} comes from the lexicon of @dfn{tri-color marking}, which is an abstraction of every possible garbage collection algorithm: in tri-color marking, grey objects are those that are known to be reachable or that we are not interested in reclaiming, yet have not been scanned to mark the objects that they refer to as reachable.} contains one entry for each page in OldSpace or FixedSpace that is thought to contain at least a reference to an object housed in NewSpace. Every page in OldSpace is created as grey, and is considered grey until a scavenging pass finds out that it actually does not contain pointers to NewSpace. Then the page is recolored black@footnote{Black objects are those that are known to be reachable or that we are not interested in reclaiming, and are known to have references only to other black or grey objects (in case you're curious, the tri-color marking algorithm goes on like this: object not yet known to be reachable are white, and when all objects are either black or white, the white ones are garbage).}, and will stay black until it is written to or another object is allocated in it (either a new fixed object, or a young object being tenured). The grey page table is expanded and shrunk as needed by the virtual machine. Drawing an histogram of object sizes shows that there are only a few sources of large objects on average (i.e., objects greater than a page in size), but that enough of these objects are created dynamically that they must be handled specially. Such objects should not be allocated in NewSpace along with ordinary objects, since they would fill up NewSpace prematurely (or might not even fit in it), thus accelerating the scavenging rate, reducing performance and resulting in an increase in tenured garbage. Even though this is not an optimal solution because it effectively tenures these objects at the time they are created, a benefit can be obtained by allocating these objects directly in FixedSpace. The reason why FixedSpace is used is that these objects are big enough that they don't result in fragmentation@footnote{Remember that free pages are shared among the three heaps, that is, OldSpace, FixedSpace and the @code{malloc} heap. When a large object is freed, the memory that it used can be reused by @code{malloc} or by OldSpace allocation}; and using FixedSpace instead of OldSpace avoids that the compactor copies them because this would not provide any benefit in terms of reduced fragmentation. Smalltalk activation records are allocated from another special heap, the context pool. This is because it is often the case that they can be deallocated in a Last-In-First-Out (stack) fashion, thereby saving the work needed to allocate entries in the object table for them, and quickly reusing the memory that they use. When the activation record is accessed by Smalltalk, however, the activation record must be turned into a first-class @code{OOP}@footnote{This is short for @dfn{Ordinary Object Pointer}.}. Since even these objects are usually very short-lived, the data is however not copied to the Eden: the eviction of the object bodies from the context pool is delayed to the next scavenging, which will also empty the context pool just like it empties Eden. If few objects are allocated and the context pool turns full before the Eden, a scavenging is also triggered; this is however quite rare. Optionally, @gst{} can avoid the overhead of interpretation by executing a given Smalltalk method only after that method has been compiled into the underlying microprocessor's machine code. This machine-code generation is performed automatically, and the resulting machine code is then placed in @code{malloc}-managed memory. Once executed, a method's machine code is left there for subsequent execution. However, since it would require way too much memory to permanently house the machine-code version of every Smalltalk method, methods might be compiled more than once: when a translation is not used at the time that two garbage collection actions are taken (scavenges and global garbage collections count equally), the incremental sweeper discards it, so that it will be recomputed if and when necessary. @node Security @section Security in @gst{} @node Special objects @section Special kinds of objects A few methods in Object support the creation of particular objects. This include: @itemize @bullet @item finalizable objects @item weak and ephemeron objects (i.e. objects whose contents are considered specially, during the heap scanning phase of garbage collection). @item read-only objects (like literals found in methods) @item fixed objects (guaranteed not to move across garbage collections) @end itemize They are: @defmethod Object makeWeak Marks the object so that it is considered weak in subsequent garbage collection passes. The garbage collector will consider dead an object which has references only inside weak objects, and will replace references to such an ``almost-dead'' object with nils, and then send the @code{mourn} message to the object. @end defmethod @defmethod Object makeEphemeron Marks the object so that it is considered specially in subsequent garbage collection passes. Ephemeron objects are sent the message @code{mourn} when the first instance variable is not referenced or is referenced @emph{only through another instance variable in the ephemeron}. Ephemerons provide a very versatile base on which complex interactions with the garbage collector can be programmed (for example, finalization which is described below is implemented with ephemerons). @end defmethod @defmethod Object addToBeFinalized Marks the object so that, as soon as it becomes unreferenced, its @code{finalize} method is called. Before @code{finalize} is called, the VM implicitly removes the objects from the list of finalizable ones. If necessary, the @code{finalize} method can mark again the object as finalizable, but by default finalization will only occur once. Note that a finalizable object is kept in memory even when it has no references, because tricky finalizers might ``resuscitate'' the object; automatic marking of the object as not to be finalized has the nice side effect that the VM can simply delay the releasing of the memory associated to the object, instead of being forced to waste memory even after finalization happens. An object must be explicitly marked as to be finalized @emph{every time the image is loaded}; that is, finalizability is not preserved by an image save. This was done because in most cases finalization is used together with operating system resources that would be stale when the image is loaded again. For @code{CObject}s, in particular, freeing them would cause a segmentation violation. @end defmethod @defmethod Object removeToBeFinalized Removes the to-be-finalized mark from the object. As I noted above, the finalize code for the object does not have to do this explicitly. @end defmethod @defmethod Object finalize This method is called by the VM when there are no more references to the object (or, of course, if it only has references inside weak objects). @end defmethod @defmethod Object isReadOnly This method answers whether the VM will refuse to make changes to the objects when methods like @code{become:}, @code{basicAt:put:}, and possibly @code{at:put:} too (depending on the implementation of the method). Note that @gst{} won't try to intercept assignments to fixed instance variables, nor assignments via @code{instVarAt:put:}. Many objects (Characters, @code{nil}, @code{true}, @code{false}, method literals) are read-only by default. @end defmethod @defmethod Object makeReadOnly: aBoolean Changes the read-only or read-write status of the receiver to that indicated by @code{aBoolean}. @end defmethod @defmethod Object basicNewInFixedSpace Same as @code{#basicNew}, but the object won't move across garbage collections. @end defmethod @defmethod Object basicNewInFixedSpace: Same as @code{#basicNew:}, but the object won't move across garbage collections. @end defmethod @defmethod Object makeFixed Ensure that the receiver won't move across garbage collections. This can be used either if you decide after its creation that an object must be fixed, or if a class does not support using @code{#new} or @code{#new:} to create an object @end defmethod Note that, although particular applications will indeed have a need for fixed, read-only or finalizable objects, the @code{#makeWeak} primitive is seldom needed and weak objects are normally used only indirectly, through the so called @dfn{weak collections}. These are easier to use because they provide additional functionality (for example, @code{WeakArray} is able to determine whether an item has been garbage collected, and @code{WeakSet} implements hash table functionality); they are: @itemize @bullet @bulletize @code{WeakArray} @bulletize @code{WeakSet} @bulletize @code{WeakKeyDictionary} @bulletize @code{WeakValueLookupTable} @bulletize @code{WeakIdentitySet} @bulletize @code{WeakKeyIdentityDictionary} @bulletize @code{WeakValueIdentityDictionary} @end itemize Versions of @gst{} preceding 2.1 included a @code{WeakKeyLookupTable} class which has been replaced by @code{WeakKeyDictionary}; the usage is completely identical, but the implementation was changed to use a more efficient approach based on ephemeron objects. @node Packages @chapter Packages @gst{} includes a packaging system which allows one to file in components (often called @dfn{goodies} in Smalltalk lore) without caring of whether they need other goodies to be loaded first. The packaging system is implemented by a Smalltalk class, @code{PackageLoader}, which looks for information about packages in various places: @itemize @item the kernel directory's parent directory; this is where an installed @file{packages.xml} resides, in a system-wide data directory such as @file{/usr/local/share/smalltalk}; @item the above directory's @file{site-packages} subdirectory, for example @file{/usr/local/share/smalltalk/site-packages}; @item in the file @file{.st/packages.xml}, hosting per-user packages; @item finally, there can be a @file{packages.xml} in the same directory as the current image. @end itemize Each of this directories can contain package descriptions in an XML file named (guess what) @file{packages.xml}, as well as standalone packages in files named @file{*.star} (short for @cite{Smalltalk archive}). Later in this section you will find information about @command{gst-package}, a program that helps you create @file{.star} files. There are two ways to load something using the packaging system. The first way is to use the PackageLoader's @code{fileInPackage:} and @code{fileInPackages:} methods. For example: @example PackageLoader fileInPackages: #('DBD-MySQL' 'DBD-SQLite'). PackageLoader fileInPackage: 'Sockets'. @end example The second way is to use the @file{gst-load} script which is installed together with the virtual machine. For example, you can do: @t{@ @ @ @ gst-load DBD-MySQL DBD-SQLite DBI} @noindent and @gst{} will automatically file in: @itemize @bullet @bulletize DBI, loaded first because it is needed by the other two packages @bulletize Sockets and Digest, not specified, but needed by DBD-MySQL @bulletize DBD-MySQL @bulletize DBD-SQLite @end itemize @noindent Notice how DBI has already been loaded. Then it will save the Smalltalk image, and finally exit. @file{gst-load} supports several options: @table @option @item -I @itemx --image-file Load the packages inside the given image. @item -i @itemx --rebuild-image Build an image from scratch and load the package into it. Useful when the image specified with @option{-I} does not exist yet. @item -q @itemx --quiet Hide the script's output. @item -v @itemx --verbose Show which files are loaded, one by one. @item -f @itemx --force If a package given on the command-line is already present, reload it. This does not apply to automatically selected prerequisites. @item -t @itemx --test Run the package testsuite before installing, and exit with a failure if the tests fail. Currently, the testsuites are placed in the image together with the package, but this may change in future versions. @item -n @item --dry-run Do not save the image after loading. @item --start[=ARG] Start the services identified by the package. If an argument is given, only one package can be specified on the command-line. If at least one package specifies a startup script, @code{gst-load} won't exit. @end table To provide support for this system, you have to give away with your @gst{} goodies a small file (usually called @file{package.xml}) which looks like this: @example DBD-SQLite DBI.SQLite DBI dbd-sqlite3 DBI.SQLite.SQLiteTestSuite SQLiteTests.st SQLite.st Connection.st ResultSet.st Statement.st Row.st ColumnInfo.st Table.st TableColumnInfo.st SQLiteTests.st ChangeLog @end example Other tags exist: @table @code @item url Specifies a URL at which a repository for the package can be found. The repository, when checked out, should contain a @file{package.xml} file at its root. The contents of this tag are not used for local packages; they are used when using the @option{--download} option to @command{gst-package}. @item library Loads a dynamic shared object and registers the functions in it so that they can all be called from Smalltalk code. The @code{GTK} package registers the GTK+ library in this way, so that the bindings can use them. @item callout Instructs to load the package only if the C function whose name is within the tag is available to be called from Smalltalk code. @item start Specifies a Smalltalk script that @file{gst-load} and @file{gst-remote} will execute in order to start the execution of the service implemented in the package. Before executing the script, @code{%1} is replaced with either @code{nil} or a String literal. @item stop Specifies a Smalltalk script that @file{gst-remote} will execute in order to shut down the service implemented in the package. Before executing the script, @code{%1} is replaced with either @code{nil} or a String literal. @item dir Should include a @code{name} attribute. The @code{file}, @code{filein} and @code{built-file} tags that are nested within a @code{dir} tag are prepended with the directory specified by the attribute. @item test Specifies a subpackage that is only loaded by @file{gst-sunit} in order to test the package. The subpackage may include arbitrary tags (including @code{file}, @code{filein} and @code{sunit}) but not @code{name}. @item provides In some cases, a single functionality can be provided by multiple modules. For example, @gst{} includes two browsers but only one should be loaded at any time. To this end, a dummy package @code{Browser} is created pointing to the default browser (@code{VisualGST}), but both browsers use @code{provides} so that if the old BLOX browser is in the image, loading @code{Browser} will have no effect. @end table To install your package, you only have to do @example gst-package path/to/package.xml @end example @command{gst-package} is a Smalltalk script which will create a @file{.star} archive in the current image directory, with the files specified in the @code{file}, @code{filein} and @code{built-file} tags. By default the package is placed in the system-wide package directory; you can use the option @option{--target-directory} to create the @file{.star} file elsewhere. Instead of a local @file{package.xml} file, you can give: @itemize @bullet @item a local @file{.star} file or a @code{URL} to such a file. The file will be downloaded if necessary, and copied to the target directory; @item a URL to a @file{package.xml} file. The @code{url} tag in the file will be used to find a source code repository (@command{git} or @command{svn}) or as a redirect to another @file{package.xml} file. @end itemize @noindent There is also a short form for specifying @file{package.xml} file on @gst{}'s web site, so that the following two commands are equivalent: @example gst-package http://smalltalk.gnu.org/project/Iliad/package.xml gst-package --download Iliad @end example When downloading remote @file{package.xml} files, @command{gst-package} also performs a special check to detect multiple packages in the same repository. If the following conditions are met: @itemize @bullet @item a package named @code{@var{package}} has a prerequisite @code{@var{package}-@var{subpackage}}; @item there is a toplevel subdirectory @var{subpackage} in the repository; @item the subdirectory has a @file{package.xml} file in it @end itemize @noindent then the @file{@var{subpackage}/package.xml} will be installed as well. @command{gst-package} does not check if the file actually defines a package with the correct name, but this may change in future versions. Alternatively, @code{gst-package} can be used to create a skeleton @gnu{} style source tree. This includes a @file{configure.ac} that will find the installation path of @gst{}, and a @file{Makefile.am} to support all the standard Makefile targets (including @command{make install} and @command{make dist}). To do so, go in the directory that is to become the top of the source tree and type. @example gst-package --prepare path1/package.xml path2/package.xml @end example In this case the generated configure script and Makefile will use more features of @command{gst-package}, which are yet to be documented. The @gst{} makefile similarly uses @command{gst-package} to install packages and to prepare the distribution tarballs. The rest of this chapter discusses some of the packages provided with @gst{}. @menu * GTK and VisualGST: GUI. * Parser, STInST, Compiler: Smalltalk-in-Smalltalk. * DBI: Database. * I18N: Locales. * Seaside: Seaside. * Swazoo: Swazoo. * SUnit: SUnit. * Sockets, WebServer, NetClients: Network support. * XML, XPath, XSL: XML. * Other packages: Other packages. @end menu @node GUI @section GTK and VisualGST @gst{} comes with GTK bindings and with a browser based on it. The system can be started as @command{gst-browser} and will allow the programmer to view the source code for existing classes, to modify existing classes and methods, to get detailed information about the classes and methods, and to evaluate code within the browser. In addition, simple debugging and unit testing tools are provided. An Inspector window allows the programmer to graphically inspect and modify the representation of an object and a walkback inspector was designed which will display a backtrace when the program encounters an error. SUnit tests (@pxref{SUnit}) can be run from the browser in order to easily support test driven development. The Transcript global object is redirected to print to the transcript window instead of printing to stdout, and the transcript window as well as the workspaces, unlike the console read-eval-print loop, support variables that live across multiple evaluations: @example a := 2 "Do-it" a + 2 "Print-it: 4 will be shown" @end example To start the browser you can simply type: @example gst-browser @end example This will load any requested packages, then, if all goes well, a @emph{launcher} window combining all the basic tools will appear on your display. @node Smalltalk-in-Smalltalk @section The Smalltalk-in-Smalltalk library The Smalltalk-in-Smalltalk library is a set of classes for looking at Smalltalk code, constructing models of Smalltalk classes that can later be created for real, analyzing and performing changes to the image, finding smelly code and automatically doing repetitive changes. This package incredibly enhances the reflective capabilities of Smalltalk. @ignore Being quite big (20000 source code lines) this package is split into three different packages: @code{Parser} loads the parser only, @code{STInST} loads various other tools (which compose the ``Refactoring Browser'' package by John Brant and Don Roberts and will be the foundation for @gst{}'s next generation browser), @code{STInSTTest} performs comprehensive unit tests@footnote{ The tests can take @strong{hours} to complete!} (@pxref{SUnit}). Porting of the @code{STInST} package will be completed in @gst{} 2.2. @end ignore A fundamental part of the system is the recursive-descent parser which creates parse nodes in the form of instances of subclasses of @code{RBProgramNode}. The parser's extreme flexibility can be exploited in three ways, all of which are demonstrated by source code available in the distribution: @itemize @bullet @item First, actions are not hard-coded in the parser itself: the parser creates a parse tree, then hands it to methods in @code{RBParser} that can be overridden in different @code{RBParser} subclasses. This is done by the compiler itself, in which a subclass of @code{RBParser} (class @code{STFileInParser}) hands the parse trees to the @code{STCompiler} class. @item Second, an implementation of the ``visitor'' pattern is provided to help in dealing with parse trees created along the way; this approach is demonstrated by the Smalltalk code pretty-printer in class @code{RBFormatter}, by the syntax highlighting engine included with the browser, and by the compiler. @item The parser is able to perform complex tree searches and rewrites, through the ParseTreeSearcher and ParseTreeRewriter classes. @ignore This mechanism is exploited by most of the tools loaded by the @code{STInST} package. @end ignore @end itemize In addition, two applications were created on top of this library which are specific to @gst{}. The first is a compiler for Smalltalk methods written in Smalltalk itself, whose source code provides good insights into the @gst{} virtual machine. The second is the automatic documentation extractor. @code{gst-doc} is able to create documentation even if the library cannot be loaded (for example, if loading it requires a running X server). To do so it uses @code{STClassLoader} from the @file{Parser} package to load and interpret Smalltalk source code, creating objects for the classes and methods being read in; then, polymorphism allows one to treat these exactly like usual classes. @node Database @section Database connectivity @gst{} includes support for connecting to databases. Currently this support is limited to retrieving result sets from @acronym{SQL} selection queries and executing @acronym{SQL} data manipulation queries; in the future however a full object model will be available that hides the usage of @acronym{SQL}. Classes that are independent of the database management system that is in use reside in package @code{DBI}, while the drivers proper reside in separate packages which have @code{DBI} as a prerequisite; currently, drivers are supplied for @emph{MySQL} and @emph{PostgreSQL}, in packages @code{DBD-MySQL} and @code{DBD-PostgreSQL} respectively. Using the library is fairly simple. To execute a query you need to create a connection to the database, create a statement on the connection, and execute your query. For example, let's say I want to connect to the @file{test} database on the localhost. My user name is @code{doe} and my password is @code{mypass}. @example | connection statement result | connection := DBI.Connection connect: 'dbi:MySQL:dbname=test;hostname=localhost' user: 'doe' password: 'mypass'). @end example You can see that the @acronym{DBMS}-specific classes live in a sub-namespace of @code{DBI}, while @acronym{DBMS}-independent classes live in @code{DBI}. Here is how I execute a query. @example statement := connection execute: 'insert into aTable (aField) values (123)'. @end example The result that is returned is a @code{ResultSet}. For write queries the object returns the number of rows affected. For read queries (such as selection queries) the result set supports standard stream protocol (@code{next}, @code{atEnd} to read rows off the result stream) and can also supply collection of column information. These are instances of @code{ColumnInfo}) and describe the type, size, and other characteristics of the returned column. A common usage of a ResultSet would be: @example | resultSet values | [resultSet atEnd] whileFalse: [values add: (resultSet next at: 'columnName') ]. @end example @node Locales @section Internationalization and localization support Different countries and cultures have varying conventions for how to communicate. These conventions range from very simple ones, such as the format for representing dates and times, to very complex ones, such as the language spoken. Provided the programs are written to obey the choice of conventions, they will follow the conventions preferred by the user. @gst{} provides two packages to ease you in doing so. The @code{I18N} package covers both @dfn{internationalization} and @dfn{multilingualization}; the lighter-weight @code{Iconv} package covers only the latter, as it is a prerequisite for correct internationalization. @dfn{Multilingualizing} software means programming it to be able to support languages from every part of the world. In particular, it includes understanding multi-byte character sets (such as UTF-8) and Unicode characters whose @dfn{code point} (the equivalent of the ASCII value) is above 127. To this end, @gst{} provides the @code{UnicodeString} class that stores its data as 32-bit Unicode values. In addition, @code{Character} will provide support for all the over one million available code points in Unicode. Loading the @code{I18N} package improves this support through the @code{EncodedStream} class@footnote{All the classes mentioned in this section reside in the @code{I18N} namespace.}, which interprets and transcodes non-ASCII Unicode characters. This support is mostly transparent, because the base classes @code{Character}, @code{UnicodeCharacter} and @code{UnicodeString} are enhanced to use it. Sending @code{asString} or @code{printString} to an instance of @code{Character} and @code{UnicodeString} will convert Unicode characters so that they are printed correctly in the current locale. For example, @samp{$<279> printNl} will print a small Latin letter @samp{e} with a dot above, when the @code{I18N} package is loaded. Dually, you can convert @code{String} or @code{ByteArray} objects to Unicode with a single method call. If the current locale's encoding is UTF-8, @samp{#[196 151] asUnicodeString} will return a Unicode string with the same character as above, the small Latin letter @samp{e} with a dot above. The implementation of multilingualization support is not yet complete. For example, methods such as @code{asLowercase}, @code{asUppercase}, @code{isLetter} do not yet recognize Unicode characters. You need to exercise some care, or your program will be buggy when Unicode characters are used. In particular, Characters must @strong{not} be compared with @code{==}@footnote{Character equality with @code{=} will be as fast as with @code{==}.} and should be printed on a Stream with @code{display:} rather than @code{nextPut:}. Also, Characters need to be created with the class method @code{codePoint:} if you are referring to their Unicode value; @code{codePoint:} is also the only method to create characters that is accepted by the ANSI Standard for Smalltalk. The method @code{value:}, instead, should be used if you are referring to a byte in a particular encoding. This subtle difference means that, for example, the last two of the following examples will fail: @example "Correct. Use #value: with Strings, #codePoint: with UnicodeString." String with: (Character value: 65) String with: (Character value: 128) UnicodeString with: (Character codePoint: 65) UnicodeString with: (Character codePoint: 128) "Correct. Only works for characters in the 0-127 range, which may be considered as defensive programming." String with: (Character codePoint: 65) "Dubious, and only works for characters in the 0-127 range. With UnicodeString, probably you always want #codePoint:." UnicodeString with: (Character value: 65) "Fails, we try to use a high character in a String" String with: (Character codePoint: 128) "Fails, we try to use an encoding in a Unicode string" UnicodeString with: (Character value: 128) @end example @dfn{Internationalizing} software, instead, means programming it to be able to adapt to the user's favorite conventions. These conventions can get pretty complex; for example, the user might specify the locale `espana-castellano' for most purposes, but specify the locale `usa-english' for currency formatting: this might make sense if the user is a Spanish-speaking American, working in Spanish, but representing monetary amounts in US dollars. You can see that this system is simple but, at the same time, very complete. This manual, however, is not the right place for a thorough discussion of how an user would set up his system for these conventions; for more information, refer to your operating system's manual or to the @gnu{} C library's manual. @gst{} inherits from @sc{iso} C the concept of a @dfn{locale}, that is, a collection of conventions, one convention for each purpose, and maps each of these purposes to a Smalltalk class defined by the @code{I18N} package, and these classes form a small hierarchy with class @code{Locale} as its roots: @itemize @bullet @ignore @item @code{LcCollate} defines the collating sequence for the local language and character set. @end ignore @item @code{LcNumeric} formats numbers; @code{LcMonetary} and @code{LcMonetaryISO} format currency amounts. @item @code{LcTime} formats dates and times. @item @code{LcMessages} translates your program's output. Of course, the package can't automatically translate your program's output messages into other languages; the only way you can support output in the user's favorite language is to translate these messages by hand. The package does, though, provide methods to easily handle translations into multiple languages. @end itemize Basic usage of the @code{I18N} package involves a single selector, the question mark (@code{?}), which is a rarely used yet valid character for a Smalltalk binary message. The meaning of the question mark selector is ``How do you say @dots{} under your convention?''. You can send @code{?} to either a specific instance of a subclass of @code{Locale}, or to the class itself; in this case, rules for the default locale (which is specified via environment variables) apply. You might say, for example, @code{LcTime ? Date today} or, for example, @code{germanMonetaryLocale ? account balance}. This syntax can be at first confusing, but turns out to be convenient because of its consistency and overall simplicity. Here is how @code{?} works for different classes: @ignore @defmethod LcCollate ? aString Answer an instance of LcCollationKey; code like @code{LcCollate ? string1 < string2} will compare the two strings under the rules of the default locale @end defmethod @end ignore @defmethod LcTime ? aString Format a date, a time or a timestamp (@code{DateTime} object). @end defmethod @defmethod LcNumber ? aString Format a number. @end defmethod @defmethod LcMonetary ? aString Format a monetary value together with its currency symbol. @end defmethod @defmethod LcMonetaryISO ? aString Format a monetary value together with its @sc{iso} currency symbol. @end defmethod @defmethod LcMessages ? aString Answer an @code{LcMessagesDomain} that retrieves translations from the specified file. @end defmethod @defmethod LcMessagesDomain ? aString Retrieve the translation of the given string.@footnote{The @code{?} method does not apply to the LcMessagesDomain class itself, but only to its instances. This is because LcMessagesDomain is not a subclass of Locale.} @end defmethod These two packages provides much more functionality, including more advanced formatting options support for Unicode, and conversion to and from several character sets. For more information, refer to @ref{I18N, , Multilingual and international support with Iconv and I18N, gst-libs, the @gst{} Library Reference}. As an aside, the representation of locales that the package uses is exactly the same as the C library, which has many advantages: the burden of mantaining locale data is removed from @gst{}'s mantainers; the need of having two copies of the same data is removed from @gst{}'s users; and finally, uniformity of the conventions assumed by different internationalized programs is guaranteed to the end user. In addition, the representation of translated strings is the standard @sc{mo} file format adopted by the @gnu{} @code{gettext} library. @node Seaside @section The Seaside web framework Seaside is a framework to build highly interactive web applications quickly, reusably and maintainably. Features of Seaside include callback-based request handling, hierarchical (component-based) page design, and modal session management to easily implement complex workflows. A simple Seaside component looks like this: @example Seaside.WAComponent subclass: MyCounter [ | count | MyCounter class >> canBeRoot [ ^true ] initialize [ super initialize. count := 0. ] states [ ^@{ self @} ] renderContentOn: html [ html heading: count. html anchor callback: [ count := count + 1 ]; with: '++'. html space. html anchor callback: [ count := count - 1 ]; with: '--'. ] ] MyCounter registerAsApplication: 'mycounter' @end example Most of the time, you will run Seaside in a background virtual machine. First of all, you should load the Seaside packages into a new image like this: @example $ gst-load -iI seaside.im Seaside Seaside-Development Seaside-Examples @end example @noindent Then, you can start Seaside with either of these commands @example $ gst-load -I seaside.im --start Seaside $ gst-remote -I seaside.im --daemon --start=Seaside @end example @noindent which will start serving pages at @url{http://localhost:8080/seaside}. The former starts the server in foreground, the latter instead runs a virtual machine that you can control using further invocations of @command{gst-remote}. For example, you can stop serving Seaside pages, and bring down the server, respectively with these commands: @example $ gst-remote --stop=Seaside $ gst-remote --kill @end example @node Swazoo @section The Swazoo web server Swazoo (Smalltalk Web Application Zoo) is a free Smalltalk HTTP server supporting both static web serving and a fully-featured web request resolution framework. The server can be started using @example $ gst-load --start@i{[=@var{ARG}]} Swazoo @end example @noindent or loaded into a background @gst{} virtual machine with @example $ gst-remote --start=Swazoo@i{[:@var{ARG}]} @end example Usually, the first time you start Swazoo @var{ARG} is @code{swazoodemo} (which starts a simple ``Hello, World!'' servlet) or a path to a configuration file like this one: @example @end example After this initial step, @var{ARG} can take the following meanings: @itemize @bullet @item if omitted altogether, all the sites registered on the server are started; @item if a number, all the sites registered on the server on that port are started; @item if a configuration file name, the server configuration is @emph{replaced} with the one loaded from that file; @item if any other string, the site named @var{ARG} is started. @end itemize In addition, a background server can be stopped using @example $ gst-remote --stop=Swazoo@i{[:@var{ARG}]} @end example @noindent where @var{ARG} can have the same meanings, except for being a configuration file. In addition, package @code{WebServer} implements an older web server engine which is now superseded by Swazoo. It is based on the @sc{gpl}'ed WikiWorks project. Apart from porting to @gst{}, a number of changes were made to the code, including refactoring of classes, better aesthetics, authentication support, virtual hosting, and @sc{http} 1.1 compliance. @node SUnit @section The SUnit testing package @code{SUnit} is a framework to write and perform test cases in Smalltalk, originarily written by the father of Extreme Programming@footnote{Extreme Programming is a software engineering technique that focuses on team work (to the point that a programmer looks in real-time at what another one is typing), frequent testing of the program, and incremental design.}, Kent Beck. @code{SUnit} allows one to write the tests and check results in Smalltalk; while this approach has the disadvantage that testers need to be able to write simple Smalltalk programs, the resulting tests are very stable. What follows is a description of the philosophy of @code{SUnit} and a description of its usage, excerpted from Kent Beck's paper in which he describes @code{SUnit}. @subsection Where should you start? Testing is one of those impossible tasks. You'd like to be absolutely complete, so you can be sure the software will work. On the other hand, the number of possible states of your program is so large that you can't possibly test all combinations. If you start with a vague idea of what you'll be testing, you'll never get started. Far better to @emph{start with a single configuration whose behavior is predictable}. As you get more experience with your software, you will be able to add to the list of configurations. Such a configuration is called a @dfn{fixture}. Two example fixtures for testing Floats can be @code{1.0} and @code{2.0}; two fixtures for testing Arrays can be @code{#()} and @code{#(1 2 3)}. By choosing a fixture you are saying what you will and won't test for. A complete set of tests for a community of objects will have many fixtures, each of which will be tested many ways. To design a test fixture you have to @itemize @bulletize{Subclass TestCase} @bulletize{Add an instance variable for each known object in the fixture} @bulletize{Override setUp to initialize the variables} @end itemize @subsection How do you represent a single unit of testing? You can predict the results of sending a message to a fixture. You need to represent such a predictable situation somehow. The simplest way to represent this is interactively. You open an Inspector on your fixture and you start sending it messages. There are two drawbacks to this method. First, you keep sending messages to the same fixture. If a test happens to mess that object up, all subsequent tests will fail, even though the code may be correct. More importantly, though, you can't easily communicate interactive tests to others. If you give someone else your objects, the only way they have of testing them is to have you come and inspect them. By representing each predictable situation as an object, each with its own fixture, no two tests will ever interfere. Also, you can easily give tests to others to run. @emph{Represent a predictable reaction of a fixture as a method.} Add a method to TestCase subclass, and stimulate the fixture in the method. @subsection How do you test for expected results? If you're testing interactively, you check for expected results directly, by printing and inspecting your objects. Since tests are in their own objects, you need a way to programmatically look for problems. One way to accomplish this is to use the standard error handling mechanism (@code{#error:}) with testing logic to signal errors: @example 2 + 3 = 5 ifFalse: [self error: 'Wrong answer'] @end example When you're testing, you'd like to distinguish between errors you are checking for, like getting six as the sum of two and three, and errors you didn't anticipate, like subscripts being out of bounds or messages not being understood. There's not a lot you can do about unanticipated errors (if you did something about them, they wouldn't be unanticipated any more, would they?) When a catastrophic error occurs, the framework stops running the test case, records the error, and runs the next test case. Since each test case has its own fixture, the error in the previous case will not affect the next. The testing framework makes checking for expected values simple by providing a method, @code{#should:}, that takes a Block as an argument. If the Block evaluates to true, everything is fine. Otherwise, the test case stops running, the failure is recorded, and the next test case runs. So, you have to @emph{turn checks into a Block evaluating to a Boolean, and send the Block as the parameter to @code{#should:}}. In the example, after stimulating the fixture by adding an object to an empty Set, we want to check and make sure it's in there: @example SetTestCase>>#testAdd empty add: 5. self should: [empty includes: 5] @end example There is a variant on @code{TestCase>>#should:}. @code{TestCase>>#shouldnt:} causes the test case to fail if the Block argument evaluates to true. It is there so you don't have to use @code{(...) not}. Once you have a test case this far, you can run it. Create an instance of your TestCase subclass, giving it the selector of the testing method. Send @code{run} to the resulting object: @example (SetTestCase selector: #testAdd) run @end example If it runs to completion, the test worked. If you get a walkback, something went wrong. @subsection How do you collect and run many different test cases? As soon as you have two test cases running, you'll want to run them both one after the other without having to execute two do it's. You could just string together a bunch of expressions to create and run test cases. However, when you then wanted to run ``this bunch of cases and that bunch of cases'' you'd be stuck. The testing framework provides an object to represent @dfn{a bunch of tests}, @code{TestSuite}. A @code{TestSuite} runs a collection of test cases and reports their results all at once. Taking advantage of polymorphism, @code{TestSuites} can also contain other @code{TestSuites}, so you can put Joe's tests and Tammy's tests together by creating a higher level suite. @emph{Combine test cases into a test suite.} @example (TestSuite named: 'Money') add: (MoneyTestCase selector: #testAdd); add: (MoneyTestCase selector: #testSubtract); run @end example The result of sending @code{#run} to a @code{TestSuite} is a @code{TestResult} object. It records all the test cases that caused failures or errors, and the time at which the suite was run. All of these objects are suitable for being stored in the image and retrieved. You can easily store a suite, then bring it in and run it, comparing results with previous runs. @subsection Running testsuites from the command line @gst{} includes a Smalltalk script to simplify running SUnit test suites. It is called @command{gst-sunit}. The command-line to @command{gst-sunit} specifies the packages, files and classes to test: @table @option @item -I @itemx --image-file Run tests inside the given image. @item -q @itemx --quiet Hide the program's output. The results are still communicated with the program's exit code. @item -v @itemx --verbose Be more verbose, in particular this will cause @command{gst-sunit} to write which test is currently being executed. @item -f @var{FILE} @itemx --file=@var{FILE} Load @var{FILE} before running the required test cases. @item -p @var{PACKAGE} @item --package=@var{PACKAGE} Load @var{PACKAGE} and its dependencies, and add @var{PACKAGE}'s tests to the set of test cases to run. @item @var{CLASS} @itemx @var{CLASS}* Add @var{CLASS} to the set of test cases to run. An asterisk after the class name adds all the classes in @var{CLASS}'s hierarchy. In particular, each selector whose name starts with @code{test} constitutes a separate test case. @item @var{VAR}=@var{VALUE} Associate variable @var{VAR} with a value. Variables allow customization of the testing environment. For example, the username with which to access a database can be specified with variables. From within a test, variables are accessible with code like this: @example TestSuitesScripter variableAt: 'mysqluser' ifAbsent: [ 'root' ] @end example Note that a @code{#variableAt:} variant does @emph{not} exist, because the testsuite should pick default values in case the variables are not specified by the user. @end table @node Network support @section Sockets, WebServer, NetClients @gst{} includes an almost complete abstraction of the @sc{tcp}, @sc{udp} and @sc{ip} protocols. Although based on the standard @sc{bsd} sockets, this library provides facilities such as buffering and preemptive I/O which a C programmer usually has to implement manually. The distribution includes a few tests (mostly loopback tests that demonstrate both client and server connection), which are class methods in @code{Socket}. This code should guide you in the process of creating and using both server and client sockets; after creation, sockets behave practically the same as standard Smalltalk streams, so you should not have particular problems. For more information, refer to @ref{Sockets, , Network programming with Sockets, gst-libs, the @gst{} Library Reference}. The library is also used by many other packages, including Swazoo and the MySQL driver. There is also code implementing the most popular Internet protocols: @sc{ftp}, @sc{http}, @sc{nntp}, @sc{smtp}, @sc{pop3} and @sc{imap}. These classes, loaded by the @code{NetClients} package, are derived from multiple public domain and free software packages available for other Smalltalk dialects and ported to @gst{}. Future version of @gst{} will include documentation for these as well. @node XML @section An XML parser and object model for @gst{} The @sc{xml} parser library for Smalltalk, loaded as package @code{XML} includes a validating @sc{xml} parser and Document Object Model. This library is rapidly becoming a standard in the Smalltalk world and a @sc{xslr} interpreter based on it is bundled with @gst{} as well (see packages @code{XPath} and @code{XSL}). Parts of the basic XML package can be loaded independently using packages @code{XML-DOM}, @code{XML-SAXParser}, @code{XML-XMLParser}, @code{XML-SAXDriver}, @code{XML-XMLNodeBuilder}. @node Other packages @section Other packages Various other ``minor'' packages are provided, typically as examples of writing modules for @gst{} (@pxref{External modules, , Linking your libraries to the virtual machine}). These include: @table @i @item Complex which adds transparent operations with complex numbers @item @sc{gdbm} which is an interface to the @gnu{} database manager @item Digest which provides two easy to use classes to quickly compute cryptographically strong hash values using the MD5 and SHA1 algorithms. @item NCurses which provides bindings to @i{ncurses} @item Continuations which provides more examples and tests for continuations (an advanced feature to support complex control flow). @item DebugTools which provides a way to attach to another Smalltalk process and execute it a bytecode or a method at a time. @end table @node Emacs @chapter Smalltalk interface for @gnu{} Emacs @gst{} comes with its own Emacs mode for hacking Smalltalk code. It also provides tools for interacting with a running Smalltalk system in an Emacs subwindow. Emacs will automatically go into Smalltalk mode when you edit a Smalltalk file (one with the extension @file{.st}). @menu * Editing:: Autoindent and more for @gst{}. * Interactor:: Smalltalk interactor mode. @end menu @node Editing @section Smalltalk editing mode The @gst{} editing mode is there to assist you in editing your Smalltalk code. It tries to be smart about indentation and provides a few cooked templates to save you keystrokes. Since Smalltalk syntax is highly context sensitive, the Smalltalk editing mode will occasionally get confused when you are editing expressions instead of method definitions. In particular, using local variables, thus: @example | foo | foo := 3. ^foo squared ! @end example @noindent will confuse the Smalltalk editing mode, as this might also be a definition the binary operator @code{|}, with second argument called @samp{foo}. If you find yourself confused when editing this type of expression, put a dummy method name before the start of the expression, and take it out when you're done editing, thus: @example x | foo | foo := 3. ^foo squared ! @end example @node Interactor @section Smalltalk interactor mode An interesting feature of Emacs Smalltalk is the Smalltalk interactor, which basically allows you run in @gnu{} Emacs with Smalltalk files in one window, and Smalltalk in the other. You can, with a single command, edit and change method definitions in the live Smalltalk system, evaluate expressions, make image snapshots of the system so you can pick up where you left off, file in an entire Smalltalk file, etc. It makes a tremendous difference in the productivity and enjoyment that you'll have when using @gst{}. To start up the Smalltalk interactor, you must be running @gnu{} Emacs and in a buffer that's in Smalltalk mode. Then, if you type @kbd{C-c m}. A second window will appear with @gst{} running in it. This window is in most respects like a Shell mode window. You can type Smalltalk expressions to it directly and re-execute previous things in the window by moving the cursor back to the line that contains the expression that you wish to re-execute and typing return. Notice the status in the mode line (e.g. @samp{starting-up}, @samp{idle}, etc). This status will change when you issue various commands from Smalltalk mode. When you first fire up the Smalltalk interactor, it puts you in the window in which Smalltalk is running. You'll want to switch back to the window with your file in it to explore the rest of the interactor mode, so do it now. To execute a range of code, mark the region around and type @kbd{C-c e}. The expression in the region is sent to Smalltalk and evaluated. The status will change to indicate that the expression is executing. This will work for any region that you create. If the region does not end with an exclamation point (which is syntactically required by Smalltalk), one will be added for you. There is also a shortcut, @kbd{C-c d} (also invokeable as @kbd{M-x smalltalk-doit}), which uses a simple heuristic to figure out the start and end of the expression: it searches forward for a line that begins with an exclamation point, and backward for a line that does not begin with space, tab, or the comment character, and sends all the text in between to Smalltalk. If you provide a prefix argument (by typing @kbd{C-u C-c d} for instance), it will bypass the heuristic and use the region instead (just like @kbd{C-c e} does). @kbd{C-c c} will compile a method; it uses a similar heuristic to determine the bounds of the method definition. Typically, you'll change a method definition, type @kbd{C-c c} and move on to whatever's next. If you want to compile a whole bunch of method definitions, you'll have to mark the entire set of method definitions (from the @code{methodsFor:} line to the @code{! !}) as the region and use @kbd{C-c e}. After you've compiled and executed some expressions, you may want to take a snapshot of your work so that you don't have to re-do things next time you fire up Smalltalk. To do this, you use the @kbd{C-c s} command, which invokes @code{ObjectMemory snapshot}. If you invoke this command with a prefix argument, you can specify a different name for the image file, and you can have that image file loaded instead of the default one by using the @code{-I} flag on the command line when invoking Smalltalk. You can also evaluate an expression and have the result of the evaluation printed by using the @kbd{C-c p} command. Mark the region and use the command. To file in an entire file (perhaps the one that you currently have in the buffer that you are working on), type @kbd{C-c f}. You can type the name of a file to load at the prompt, or just type return and the file associated with the current buffer will be loaded into Smalltalk. When you're ready to quit using @gst{}, you can quit cleanly by using the @kbd{C-c q} command. If you want to fire up Smalltalk again, or if (heaven forbid) Smalltalk dies on you, you can use the @kbd{C-c m} command, and Smalltalk will be reincarnated. Even if it's running, but the Smalltalk window is not visible, @kbd{C-c m} will cause it to be displayed right away. You might notice that as you use this mode, the Smalltalk window will scroll to keep the bottom of the buffer in focus, even when the Smalltalk window is not the current window. This was a design choice that I made to see how it would work. On the whole, I guess I'm pretty happy with it, but I am interested in hearing your opinions on the subject. @node C and Smalltalk @chapter Interoperability between C and @gst{} @menu * External modules:: Linking your libraries to the virtual machine * C callout:: Calls from Smalltalk to C * C data types:: Manipulating C data from Smalltalk * Smalltalk types:: Manipulating Smalltalk data from C * Smalltalk callin:: Calls from C to Smalltalk * Smalltalk callbacks:: Smalltalk blocks as C function pointers * Object representation:: Manipulating your own Smalltalk objects * Incubator:: Protecting newly created objects from garbage collections * Other C functions:: Handling and creating OOPs * Using Smalltalk:: The Smalltalk environment as an extension library @end menu @node External modules @section Linking your libraries to the virtual machine A nice thing you can do with @gst{} is enhancing it with your own goodies. If they're written in Smalltalk only, no problem: getting them to work as packages (@pxref{Packages}), and to fit in with the @gst{} packaging system, is likely to be a five-minutes task. If your goodie is creating a binding to an external C library and you do not need particular glue to link it to Smalltalk (for example, there are no callbacks from C code to Smalltalk code), you can use the @code{dynamic library linking} system. When using this system, you have to link @gst{} with the library at run-time using @sc{dld}, using either @code{DLD class>>#addLibrary:} or a @code{} tag in a @file{package.xml} file (@pxref{Packages}). The following line: @example DLD addLibrary: 'libc' @end example @noindent is often used to use the standard C library functions from Smalltalk. However, if you want to provide a more intimate link between C and Smalltalk, as is the case with for example the GTK bindings, you should use the @code{dynamic module linking} system. This section explains what to do, taking the Digest library as a guide. A module is distinguished from a standard shared library because it has a function which Smalltalk calls to initialize the module; the name of this function must be @code{gst_initModule}. Here is the initialization function used by Digest: @example void gst_initModule(proxy) VMProxy *proxy; @{ vmProxy = proxy; vmProxy->defineCFunc ("MD5AllocOOP", MD5AllocOOP); vmProxy->defineCFunc ("MD5Update", md5_process_bytes); vmProxy->defineCFunc ("MD5Final", md5_finish_ctx); vmProxy->defineCFunc ("SHA1AllocOOP", SHA1AllocOOP); vmProxy->defineCFunc ("SHA1Update", sha1_process_bytes); vmProxy->defineCFunc ("SHA1Final", sha1_finish_ctx); @} @end example Note that the @code{defineCFunc} function is called through a function pointer in @code{gst_initModule}, and that the value of its parameter is saved in order to use it elsewhere in its code. This is not strictly necessary on many platforms, namely those where the module is effectively @emph{linked with the Smalltalk virtual machine} at run-time; but since some@footnote{The most notable are @sc{aix} and Windows.} cannot obtain this, for maximum portability you must always call the virtual machine through the proxy and never refer to any symbol which the virtual machine exports. For uniformity, even programs that link with @file{libgst.a} should not call these functions directly, but through a @code{VMProxy} exported by @file{libgst.a} and accessible through the @code{gst_interpreter_proxy} variable. Modules are shared libraries; the default directory in which modules are searched for is stored in a @file{gnu-smalltalk.pc} file that is installed by @gst{} so that it can be used with @command{pkg-config}. An Autoconf macro @code{AM_PATH_GST} is also installed that will put the directory in the @code{gstmoduledir} Autoconf substitution. When using @gnu{} Automake and Libtool, you can then build modules by including something like this in @file{Makefile.am}: @example gstmodule_LTLIBRARIES = libdigest.la libdigest_la_LDFLAGS = -module -no-undefined @dfn{... more flags ...} libdigest_la_SOURCES = @dfn{... your source files ...} @end example While you can use @code{DLD class>>#addModule:} to link a module into the virtual machine at run time, usually bindings that require a module are complex enough to be packaged as @file{.star} files. In this case, you will have to add the name of the module in a package file (@pxref{Packages}). In this case, the relevant entry in the file will be @example Digest digest.st md5.st sha1.st digest MD5Test SHA1Test mdtests.st @end example There is also a third case, in which the bindings are a mixture of code written specially for @gst{}, and the normal C library. In this case, you can use a combination of dynamic shared libraries and dynamic modules. To do this, you can specify both @code{} and @code{} tags in the @file{package.xml} file; alternatively, the following functions allow you to call @code{DLD class>>#addLibrary:} from within a module. @deftypefun mst_Boolean dlOpen (void *filename, int module) Open the library pointed to by with @var{filename} (which need not include an extension), and invoke gst_initModule if it is found in the library. If @var{module} is false, add the file to the list of libraries that Smalltalk searches for external symbols. Return true if the library was found. @end deftypefun @deftypefun void dlAddSearchDir (const char *dir) Add @var{dir} at the beginning of the search path of @code{dlOpen}. @end deftypefun @deftypefun void dlPushSearchPath (void) Save the current value of the search path for @code{dlOpen}. This can be used to temporarily add the search path for the libraries added by a module, without affecting subsequent libraries manually opened with the @code{DLD} class. @end deftypefun @deftypefun void dlPopSearchPath (void) Restore the last saved value of the search path. @end deftypefun @node C callout @section Using the C callout mechanism To use the C callout mechanism, you first need to inform Smalltalk about the C functions that you wish to call. You currently need to do this in two places: 1) you need to establish the mapping between your C function's address and the name that you wish to refer to it by, and 2) define that function along with how the argument objects should be mapped to C data types to the Smalltalk interpreter. As an example, let us use the pre-defined (to @gst{}) functions of @code{system} and @code{getenv}. First, the mapping between these functions and string names for the functions needs to be established in your module. If you are writing an external Smalltalk module (which can look at Smalltalk objects and manipulate them), see @ref{External modules, , Linking your libraries to the virtual machine}; if you are using function from a dynamically loaded library, see @ref{Dynamic loading}. Second, we need to define a method that will invoke these C functions and describe its arguments to the Smalltalk runtime system. Such a method is defined with a primitive-like syntax, similar to the following example (taken from @file{kernel/CFuncs.st}) @example system: aString getenv: aString @end example These methods were defined on class @code{SystemDictionary}, so that we would invoke it thus: @example Smalltalk system: 'lpr README' ! @end example However, there is no special significance to which class receives the method; it could have just as well been Float, but it might look kind of strange to see: @example 1701.0 system: 'mail help-smalltalk@@g@:nu.org' ! @end example The various keyword arguments are described below. @table @b @item @code{cCall: 'system'} This says that we are defining the C function @code{system}. This name must be @strong{exactly} the same as the string passed to @code{defineCFunc}. The name of the method does not have to match the name of the C function; we could have just as easily defined the selector to be @code{'rambo: fooFoo'}; it's just good practice to define the method with a similar name and the argument names to reflect the data types that should be passed. @item @code{returning: #int} This defines the C data type that will be returned. It is converted to the corresponding Smalltalk data type. The set of valid return types is: @table @code @item char Single C character value @item string A C char *, converted to a Smalltalk string @item stringOut A C char *, converted to a Smalltalk string and then freed. @item symbol A C char *, converted to a Smalltalk symbol @item symbolOut A C char *, converted to a Smalltalk symbol and then freed. @item int A C int value @item uInt A C unsigned int value @item long A C long value @item uLong A C unsigned long value @item double A C double, converted to an instance of FloatD @item longDouble A C long double, converted to an instance of FloatQ @item void No returned value (@code{self} returned from Smalltalk) @item wchar Single C wide character (@code{wchar_t}) value @item wstring Wide C string (@code{wchar_t *}), converted to a UnicodeString @item wstringOut Wide C string (@code{wchar_t *}), converted to a UnicodeString and then freed @item cObject An anonymous C pointer; useful to pass back to some C function later @item smalltalk An anonymous (to C) Smalltalk object pointer; should have been passed to C at some point in the past or created by the program by calling other public @gst{} functions (@pxref{Smalltalk types}). @item @var{ctype} You can pass an instance of CType or one of its subclasses (@pxref{C data types}). In this case the object will be sent @code{#narrow} before being returned: an example of this feature is given in the experimental Gtk+ bindings. @end table @item @code{args: #(#string)} This is an array of symbols that describes the types of the arguments in order. For example, to specify a call to open(2), the arguments might look something like: @example args: #(#string #int #int) @end example The following argument types are supported; see above for details. @table @code @item unknown Smalltalk will make the best conversion that it can guess for this object; see the mapping table below @item boolean passed as @code{char}, which is promoted to @code{int} @item char passed as @code{char}, which is promoted to @code{int} @item wchar passed as @code{wchar_t} @item string passed as @code{char *} @item byteArrayOut passed as @code{char *}. The contents are expected to be overwritten with a new C string, and copied back to the object that was passed on return from the C function @item stringOut passed as @code{char *}, the contents are expected to be overwritten with a new C string, and the object that was passed becomes the new string on return @item wstring passed as @code{wchar_t *} @item wstringOut passed as @code{wchar_t *}, the contents are expected to be overwritten with a new C wide string, and the object that was passed becomes the new string on return @item symbol passed as @code{char *} @item byteArray passed as @code{char *}, even though may contain NUL's @item int passed as @code{int} @item uInt passed as @code{unsigned int} @item long passed as @code{long} @item uLong passed as @code{unsigned long} @item double passed as @code{double} @item longDouble passed as @code{long double} @item cObject C object value passed as @code{void *}. Any class with non-pointer indexed instance variables can be passed as a @code{#cObject}, and @gst{} will pass the address of the first indexed instance variable. This however should never be done for functions that allocate objects, call back into Smalltalk code or otherwise may cause a garbage collection: after a GC, pointers passed as @code{#cObject} may be invalidated. In this case, it is safer to pass every object as @code{#smalltalk}, or to only pass @code{CObject}s that were returned by a C function previously. In addition, @code{#cObject} can be used for function pointers. These are instances of @code{CCallable} or one of its subclasses. See @ref{Smalltalk callbacks} for more information on how to create function pointers for Smalltalk blocks. @item cObjectPtr Pointer to C object value passed as @code{void **}. The @code{CObject} is modified on output to reflect the value stored into the passed object. @item smalltalk Pass the object pointer to C. The C routine should treat the value as a pointer to anonymous storage. This pointer can be returned to Smalltalk at some later point in time. @item variadic @itemx variadicSmalltalk an Array is expected, each of the elements of the array will be converted like an @code{unknown} parameter if @code{variadic} is used, or passed as a raw object pointer for @code{variadicSmalltalk}. @item self @itemx selfSmalltalk Pass the receiver, converting it to C like an @code{unknown} parameter if @code{self} is used or passing the raw object pointer for @code{selfSmalltalk}. Parameters passed this way don't map to the message's arguments, instead they map to the message's receiver. @end table @end table Table of parameter conversions: @multitable {Declared param type} {Boolean (True, False)} {@code{int} (C promotion rule)} @item Declared param type @tab Object type @tab C parameter type used @item boolean @tab Boolean (True, False)@tab int @item byteArray @tab ByteArray @tab char * @item cObject @tab CObject @tab void * @item cObject @tab ByteArray, etc. @tab void * @item cObjectPtr @tab CObject @tab void ** @item char @tab Boolean (True, False)@tab int @item char @tab Character @tab int (C promotion rule) @item char @tab Integer @tab int @item double @tab Float @tab double (C promotion) @item longDouble @tab Float @tab long double @item int @tab Boolean (True, False)@tab int @item int @tab Integer @tab int @item uInt @tab Boolean (True, False)@tab unsigned int @item uInt @tab Integer @tab unsigned int @item long @tab Boolean (True, False)@tab long @item long @tab Integer @tab long @item uLong @tab Boolean (True, False)@tab unsigned long @item uLong @tab Integer @tab unsigned long @item smalltalk, selfSmalltalk @tab anything @tab OOP @item string @tab String @tab char * @item string @tab Symbol @tab char * @item stringOut @tab String @tab char * @item symbol @tab Symbol @tab char * @item unknown, self @tab Boolean (True, False)@tab int @item unknown, self @tab ByteArray @tab char * @item unknown, self @tab CObject @tab void * @item unknown, self @tab Character @tab int @item unknown, self @tab Float @tab double @item unknown, self @tab Integer @tab long @item unknown, self @tab String @tab char * @item unknown, self @tab Symbol @tab char * @item unknown, self @tab anything else @tab OOP @item variadic @tab Array @tab each element is passed according to "unknown" @item variadicSmalltalk @tab Array @tab each element is passed as an OOP @item wchar @tab Character @tab wchar_t @item wstring @tab UnicodeString @tab wchar_t * @item wstringOut @tab UnicodeString @tab wchar_t * @end multitable When your call-out returns @code{#void}, depending on your application you might consider using @dfn{asynchronous call-outs}. These are call-outs that do not suspend the process that initiated them, so the process might be scheduled again, executing the code that follows the call-out, during the execution of the call-out itself. This is particularly handy when writing event loops (the most common place where you call back into Smalltalk) because then @emph{you can handle events that arrive during the handling of an outer event} before the outer event's processing has ended. Depending on your application this might be correct or not, of course. In the future, asynchronous call-outs might be started into a separate thread. An asynchronous call-out is defined using an alternate primitive-like syntax, @code{asyncCCall:args:}. Note that the returned value parameter is missing because an asynchronous call-out always returns @code{nil}. @node C data types @section The C data type manipulation system @c rewrite this..... @code{CType} is a class used to represent C data types themselves (no storage, just the type). There are subclasses called things like @code{C@var{mumble}CType}. The instances can answer their size and alignment. Their @code{valueType} is the underlying type of data. It's either an integer, which is interpreted by the interpreter as the scalar type, or the underlying element type, which is another @code{CType} subclass instance. To make life easier, there are global variables which hold onto instances of @code{CScalarCType}: they are called @code{C@var{mumble}Type} (like @code{CIntType}, not like @code{CIntCType}), and can be used wherever a C datatype is used. If you had an array of strings, the elements would be CStringType's (a specific instance of CScalarCType). @code{CObject} is the base class of the instances of C data. It has a subclass called @code{CScalar}, which has subclasses called @code{C@var{mumble}}. These subclasses can answer size and alignment information. Instances of @code{CObject} can hold a raw C pointer (for example in @code{malloc}ed heap)), or can delegate their storage to a @code{ByteArray}. In the latter case, the storage is automatically garbage collected when the @code{CObject} becomes dead, and the VM checks accesses to make sure they are in bounds. On the other hand, the storage may move, and for this reason extra care must be put when using this kind of @code{CObject} with C routines that call back into Smalltalk, or that store the passed pointer somewhere. Instances of @code{CObject} can be created in many ways: @itemize @item creating an instance with @code{@var{class} new} initializes the pointer to @code{NULL}; @item doing @code{@var{type} new}, where @var{type} is a @code{CType} subclass instance, allocates a new instance with @code{malloc}. @item doing @code{@var{type} gcNew}, where @var{type} is a @code{CType} subclass instance, allocates a new instance backed by garbage-collected storage. @end itemize @code{CStruct} and @code{CUnion} subclasses are special. First, @code{new} allocates a new instance with @code{malloc} instead of initializing the pointer to @code{NULL}. Second, they support @code{gcNew} which creates a new instance backed by garbage-collected storage. @code{CObject}s created by the C callout mechanism are never backed by garbage-collected storage. @code{CObject} and its subclasses represent a pointer to a C object and as such provide the full range of operations supported by C pointers. For example, @code{+} @code{anInteger} which returns a CObject which is higher in memory by @code{anInteger} times the size of each item. There is also @code{-} which acts like @code{+} if it is given an integer as its parameter. If a CObject is given, it returns the difference between the two pointers. @code{incr}, @code{decr}, @code{incrBy:}, @code{decrBy:} adjust the string either forward or backward, by either 1 or @code{n} characters. Only the pointer to the string is changed; the actual characters in the string remain untouched. CObjects can be divided into two families, scalars and non-scalars, just like C data types. Scalars fetch a Smalltalk object when sent the @code{value} message, and change their value when sent the @code{value:} message. Non-scalars do not support these two messages. Non-scalars include instances of @code{CArray} and subclasses of @code{CStruct} and @code{CUnion} (but not @code{CPtr}). @code{CPtr}s and @code{CArray}s get their underlying element type through a @code{CType} subclass instance which is associated with the @code{CArray} or @code{CPtr} instance. @code{CPtr}'s @code{value} and @code{value:} method get or change the underlying value that's pointed to. @code{value} returns another @code{CObject} corresponding to the pointed value. That's because, for example, a @code{CPtr} to @code{long} points to a place in memory where a pointer to long is stored. It is really a @code{long **} and must be dereferenced twice with @code{cPtr value value} to get the @code{long}. @code{CString} is a subclass of @code{CPtr} that answers a Smalltalk @code{String} when sent @code{value}, and automatically allocates storage to copy and null-terminate a Smalltalk @code{String} when sent @code{value:}. @code{replaceWith:} replaces the string the instance points to with a new string or @code{ByteArray}, passed as the argument. Actually, it copies the bytes from the Smalltalk @code{String} instance aString into the same buffer already pointed to by the @code{CString}, with a null terminator. Finally, there are @code{CStruct} and @code{CUnion}, which are abstract subclasses of @code{CObject}@footnote{Actually they have a common superclass named @code{CCompound}.}. The following will refer to CStruct, but the same considerations apply to CUnion as well, with the only difference that CUnions of course implement the semantics of a C union. These classes provide direct access to C data structures including @itemize @bullet @bulletize @code{long} (unsigned too) @bulletize @code{short} (unsigned too) @bulletize @code{char} (unsigned too) & byte type @bulletize @code{double}, @code{long double}, @code{float} @bulletize @code{string} (NUL terminated char *, with special accessors) @bulletize arrays of any type @bulletize pointers to any type @bulletize other structs containing any fixed size types @end itemize Here is an example struct decl in C: @example struct audio_prinfo @{ unsigned channels; unsigned precision; unsigned encoding; unsigned gain; unsigned port; unsigned _xxx[4]; unsigned samples; unsigned eof; unsigned char pause; unsigned char error; unsigned char waiting; unsigned char _ccc[3]; unsigned char open; unsigned char active; @}; struct audio_info @{ audio_prinfo_t play; audio_prinfo_t record; unsigned monitor_gain; unsigned _yyy[4]; @}; @end example And here is a Smalltalk equivalent decision: @example CStruct subclass: AudioPrinfo [ ] CStruct subclass: AudioInfo [ ] @end example This creates two new subclasses of @code{CStruct} called @code{AudioPrinfo} and @code{AudioInfo}, with the given fields. The syntax is the same as for creating standard subclasses, with the additional metadata @code{declaration:}. You can make C functions return @code{CObject}s that are instances of these classes by passing @code{AudioPrinfo type} as the parameter to the @code{returning:} keyword. AudioPrinfo has methods defined on it like: @example #sampleRate #channels #precision #encoding @end example @noindent etc. These access the various data members. The array element accessors (xxx, ccc) just return a pointer to the array itself. For simple scalar types, just list the type name after the variable. Here's the set of scalars names, as defined in @file{kernel/CStruct.st}: @example #long CLong #uLong CULong #ulong CULong #byte CByte #char CChar #uChar CUChar #uchar CUChar #short CShort #uShort CUShort #ushort CUShort #int CInt #uInt CUInt #uint CUInt #float CFloat #double CDouble #longDouble CLongDouble #string CString #smalltalk CSmalltalk #@{...@} @r{A given subclass of @code{CObject}} @end example The @code{#@{@dots{}@}} syntax is not in the Blue Book, but it is present in @gst{} and other Smalltalks; it returns an Association object corresponding to a global variable. To have a pointer to a type, use something like: @example (#example (#ptr #long)) @end example To have an array pointer of size @var{size}, use: @example (#example (#array #string @var{size})) @end example Note that this maps to @code{char *example[@var{size}]} in C. The objects returned by using the fields are CObjects; there is no implicit value fetching currently. For example, suppose you somehow got ahold of an instance of class AudioPrinfo as described above (the instance is a CObject subclass and points to a real C structure somewhere). Let's say you stored this object in variable @code{audioInfo}. To get the current gain value, do @example audioInfo gain value @end example @noindent to change the gain value in the structure, do @example audioInfo gain value: 255 @end example The structure member message just answers a @code{CObject} instance, so you can hang onto it to directly refer to that structure member, or you can use the @code{value} or @code{value:} methods to access or change the value of the member. Note that this is the same kind of access you get if you use the @code{addressAt:} method on CStrings or CArrays or CPtrs: they return a CObject which points to a C object of the right type and you need to use @code{value} and @code{value:} to access and modify the actual C variable. @node Smalltalk types @section Manipulating Smalltalk data from C @gst{} internally maps every object except Integers to a data structure named an @dfn{OOP} (which is short for @dfn{Ordinary Object Pointer}). An OOP is a pointer to an internal data structure; this data structure basically adds a level of indirection in the representation of objects, since it contains @itemize @bullet @item a pointer to the actual object data @item a bunch of flags, most of which interest the garbage collection process @end itemize This additional level of indirection makes garbage collection very efficient, since the collector is free to move an object in memory without updating every reference to that object in the heap, thereby keeping the heap fully compact and allowing very fast allocation of new objects. However, it makes C code that wants to deal with objects even more messy than it would be without; if you want some examples, look at the hairy code in @gst{} that deals with processes. To shield you as much as possible from the complications of doing object-oriented programming in a non-object-oriented environment like C, @gst{} provides friendly functions to map between common Smalltalk objects and C types. This way you can simply declare OOP variables and then use these functions to treat their contents like C data. These functions are passed to a module via the @code{VMProxy} struct, a pointer to which is passed to the module, as shown in @ref{External modules, , Linking your libraries to the virtual machine}. They can be divided in two groups, those that map @emph{from Smalltalk objects to C data types} and those that map @emph{from C data types to Smalltalk objects}. Here are those in the former group (Smalltalk to C); you can see that they all begin with @code{OOPTo}: @deftypefun long OOPToInt (OOP) This function assumes that the passed OOP is an Integer and returns the C @code{signed long} for that integer. @end deftypefun @deftypefun long OOPToId (OOP) This function returns an unique identifier for the given OOP, valid until the OOP is garbage-collected. @end deftypefun @deftypefun double OOPToFloat (OOP) This function assumes that the passed OOP is an Integer or Float and returns the C @code{double} for that object. @end deftypefun @deftypefun {long double} OOPToLongDouble (OOP) This function assumes that the passed OOP is an Integer or Float and returns the C @code{long double} for that object. @end deftypefun @deftypefun int OOPToBool (OOP) This function returns a C integer which is true (i.e. @code{!= 0}) if the given OOP is the @code{true} object, false (i.e. @code{== 0}) otherwise. @end deftypefun @deftypefun char OOPToChar (OOP) This function assumes that the passed OOP is a Character and returns the C @code{char} for that integer. @end deftypefun @deftypefun wchar_t OOPToWChar (OOP) This function assumes that the passed OOP is a Character or UnicodeCharacter and returns the C @code{wchar_t} for that integer. @end deftypefun @deftypefun char *OOPToString (OOP) This function assumes that the passed OOP is a String or ByteArray and returns a C null-terminated @code{char *} with the same contents. It is the caller's responsibility to free the pointer and to handle possible @samp{NUL} characters inside the Smalltalk object. @end deftypefun @deftypefun wchar_t *OOPToWString (OOP) This function assumes that the passed OOP is a UnicodeString and returns a C null-terminated @code{wchar_t *} with the same contents. It is the caller's responsibility to free the pointer and to handle possible @samp{NUL} characters inside the Smalltalk object. @end deftypefun @deftypefun char *OOPToByteArray (OOP) This function assumes that the passed OOP is a String or ByteArray and returns a C @code{char *} with the same contents, without null-terminating it. It is the caller's responsibility to free the pointer. @end deftypefun @deftypefun PTR OOPToCObject (OOP) This functions assumes that the passed OOP is a kind of CObject and returns a C @code{PTR} to the C data pointed to by the object. The caller should not free the pointer, nor assume anything about its size and contents, unless it @b{exactly} knows what it's doing. A @code{PTR} is a @code{void *} if supported, or otherwise a @code{char *}. @end deftypefun @deftypefun long OOPToC (OOP) This functions assumes that the passed OOP is a String, a ByteArray, a CObject, or a built-in object (@code{nil}, @code{true}, @code{false}, character, integer). If the OOP is @code{nil}, it answers 0; else the mapping for each object is exactly the same as for the above functions. Note that, even though the function is declared as returning a @code{long}, you might need to cast it to either a @code{char *} or @code{PTR}. @end deftypefun While special care is needed to use the functions above (you will probably want to know at least the type of the Smalltalk object you're converting), the functions below, which convert C data to Smalltalk objects, are easier to use and also put objects in the incubator so that they are not swept by a garbage collection (@pxref{Incubator}). These functions all @dfn{end} with @code{ToOOP}, except @code{cObjectToTypedOOP}: @deftypefun OOP intToOOP (long) This object returns a Smalltalk @code{Integer} which contains the same value as the passed C @code{long}. @end deftypefun @deftypefun OOP uintToOOP (unsigned long) This object returns a Smalltalk @code{Integer} which contains the same value as the passed C @code{unsigned long}. @end deftypefun @deftypefun OOP idToOOP (OOP) This function returns an OOP from a unique identifier returned by @code{OOPToId}. The OOP will be the same that was passed to @code{OOPToId} only if the original OOP has not been garbage-collected since the call to @code{OOPToId}. @end deftypefun @deftypefun OOP floatToOOP (double) This object returns a Smalltalk @code{FloatD} which contains the same value as the passed @code{double}. Unlike Integers, FloatDs have exactly the same precision as C doubles. @end deftypefun @deftypefun OOP longDoubleToOOP (long double) This object returns a Smalltalk @code{FloatQ} which contains the same value as the passed @code{long double}. Unlike Integers, FloatQs have exactly the same precision as C long doubles. @end deftypefun @deftypefun OOP boolToOOP (int) This object returns a Smalltalk @code{Boolean} which contains the same boolean value as the passed C @code{int}. That is, the returned OOP is the sole instance of either @code{False} or @code{True}, depending on where the parameter is zero or not. @end deftypefun @deftypefun OOP charToOOP (char) This object returns a Smalltalk @code{Character} which represents the same char as the passed C @code{char}. @end deftypefun @deftypefun OOP charToOOP (wchar_t) This object returns a Smalltalk @code{Character} or @code{UnicodeCharacter} which represents the same char as the passed C @code{wchar_t}. @end deftypefun @deftypefun OOP classNameToOOP (char *) This method returns the Smalltalk class (i.e. an instance of a subclass of Class) whose name is the given parameter. Namespaces are supported; the parameter must give the complete path to the class starting from the @code{Smalltalk} dictionary. @code{NULL} is returned if the class is not found. This method is slow; you can safely cache its result. @end deftypefun @deftypefun OOP stringToOOP (char *) This method returns a String which maps to the given null-terminated C string, or the builtin object @code{nil} if the parameter points to address 0 (zero). @end deftypefun @deftypefun OOP wstringToOOP (wchar_t *) This method returns a UnicodeString which maps to the given null-terminated C wide string, or the builtin object @code{nil} if the parameter points to address 0 (zero). @end deftypefun @deftypefun OOP byteArrayToOOP (char *, int) This method returns a ByteArray which maps to the bytes that the first parameters points to; the second parameter gives the size of the ByteArray. The builtin object @code{nil} is returned if the first parameter points to address 0 (zero). @end deftypefun @deftypefun OOP symbolToOOP (char *) This method returns a String which maps to the given null-terminated C string, or the builtin object @code{nil} if the parameter points to address 0 (zero). @end deftypefun @deftypefun OOP cObjectToOOP (PTR) This method returns a CObject which maps to the given C pointer, or the builtin object @code{nil} if the parameter points to address 0 (zero). The returned value has no precise CType assigned. To assign one, use @code{cObjectToTypedOOP}. @end deftypefun @deftypefun OOP cObjectToTypedOOP (PTR, OOP) This method returns a CObject which maps to the given C pointer, or the builtin object @code{nil} if the parameter points to address 0 (zero). The returned value has the second parameter as its type; to get possible types you can use @code{typeNameToOOP}. @end deftypefun @deftypefun OOP typeNameToOOP (char *) All this method actually does is evaluating its parameter as Smalltalk code; so you can, for example, use it in any of these ways: @example cIntType = typeNameToOOP("CIntType"); myOwnCStructType = typeNameToOOP("MyOwnCStruct type"); @end example This method is primarily used by @code{msgSendf} (@pxref{Smalltalk callin}), but it can be useful if you use lower level call-in methods. This method is slow too; you can safely cache its result. @end deftypefun As said above, the C to Smalltalk layer automatically puts the objects it creates in the incubator which prevents objects from being collected as garbage. A plugin, however, has limited control on the incubator, and the incubator itself is not at all useful when objects should be kept registered for a relatively long time, and whose lives in the registry typically overlap. To avoid garbage collection of such object, you can use these functions, which access a separate registry: @deftypefun OOP registerOOP (OOP) Puts the given OOP in the registry. If you register an object multiple times, you will need to unregister it the same number of times. You may want to register objects returned by Smalltalk call-ins. @end deftypefun @deftypefun void unregisterOOP (OOP) Removes an occurrence of the given OOP from the registry. @end deftypefun @deftypefun void registerOOPArray (OOP **, OOP **) Tells the garbage collector that an array of objects must be made part of the root set. The two parameters point indirectly to the base and the top of the array; that is, they are pointers to variables holding the base and the top of the array: having indirect pointers allows you to dynamically change the size of the array and even to relocate it in memory without having to unregister and re-register it every time you modify it. If you register an array multiple times, you will need to unregister it the same number of times. @end deftypefun @deftypefun void unregisterOOPArray (OOP **) Removes the array with the given base from the registry. @end deftypefun @node Smalltalk callin @section Calls from C to Smalltalk @gst{} provides seven different function calls that allow you to call Smalltalk methods in a different execution context than the current one. The priority in which the method will execute will be the same as the one of Smalltalk process which is currently active. Four of these functions are more low level and are more suited when the Smalltalk program itself gave a receiver, a selector and maybe some parameters; the others, instead, are more versatile. One of them (@code{msgSendf}) automatically handles most conversions between C data types and Smalltalk objects, while the others takes care of compiling full snippets of Smalltalk code. All these functions handle properly the case of specifying, say, 5 arguments for a 3-argument selector---see the description of the single functions for more information). In all cases except @code{msgSendf}, passing NULL as the selector will expect the receiver to be a block and evaluate it. @deftypefun OOP msgSend (OOP receiver, OOP selector, @dots{}) This function sends the given selector (should be a Symbol, otherwise @code{nilOOP} is returned) to the given receiver. The message arguments should also be OOPs (otherwise, an access violation exception is pretty likely) and are passed in a NULL-terminated list after the selector. The value returned from the method is passed back as an OOP to the C program as the result of @code{msgSend}, or @code{nilOOP} if the number of arguments is wrong. Example (same as @code{1 + 2}): @example OOP shouldBeThreeOOP = vmProxy->msgSend( intToOOP(1), symbolToOOP("+"), intToOOP(2), NULL); @end example @end deftypefun @deftypefun OOP strMsgSend (OOP receiver, char *selector, @dots{}) This function is the same as above, but the selector is passed as a C string and is automatically converted to a Smalltalk symbol. Theoretically, this function is a bit slower than @code{msgSend} if your program has some way to cache the selector and avoiding a call to @code{symbolToOOP} on every call-in. However, this is not so apparent in ``real'' code because the time spent in the Smalltalk interpreter will usually be much higher than the time spent converting the selector to a Symbol object. Example: @example OOP shouldBeThreeOOP = vmProxy->strMsgSend( intToOOP(1), "+", intToOOP(2), NULL); @end example @end deftypefun @deftypefun OOP vmsgSend (OOP receiver, OOP selector, OOP *args) This function is the same as msgSend, but accepts a pointer to the NULL-terminated list of arguments, instead of being a variable-arguments functions. Example: @example OOP arguments[2], shouldBeThreeOOP; arguments[0] = intToOOP(2); arguments[1] = NULL; /* @dots{} some more code here @dots{} */ shouldBeThreeOOP = vmProxy->vmsgSend( intToOOP(1), symbolToOOP("+"), arguments); @end example @end deftypefun @deftypefun OOP nvmsgSend (OOP receiver, OOP selector, OOP *args, int nargs) This function is the same as msgSend, but accepts an additional parameter containing the number of arguments to be passed to the Smalltalk method, instead of relying on the NULL-termination of args. Example: @example OOP argument, shouldBeThreeOOP; argument = intToOOP(2); /* @dots{} some more code here @dots{} */ shouldBeThreeOOP = vmProxy->nvmsgSend( intToOOP(1), symbolToOOP("+"), &argument, 1); @end example @end deftypefun @deftypefun OOP perform (OOP, OOP) Shortcut function to invoke a unary selector. The first parameter is the receiver, and the second is the selector. @end deftypefun @deftypefun OOP performWith (OOP, OOP, OOP) Shortcut function to invoke a one-argument selector. The first parameter is the receiver, the second is the selector, the third is the sole argument. @end deftypefun @deftypefun OOP invokeHook (int) Calls into Smalltalk to process a @code{ObjectMemory} hook given by the parameter. In practice, @code{changed:} is sent to @code{ObjectMemory} with a symbol derived from the parameter. The parameter can be one of: @itemize @item @code{GST_BEFORE_EVAL} @item @code{GST_AFTER_EVAL} @item @code{GST_ABOUT_TO_QUIT} @item @code{GST_RETURN_FROM_SNAPSHOT} @item @code{GST_ABOUT_TO_SNAPSHOT} @item @code{GST_FINISHED_SNAPSHOT} @end itemize All cases where the last three should be used should be covered in @gst{}'s source code. The first three, however, can actually be useful in user code. @end deftypefun The two functions that directly accept Smalltalk code are named @code{evalCode} and @code{evalExpr}, and they're basically the same. They both accept a single parameter, a pointer to the code to be submitted to the parser. The main difference is that @code{evalCode} discards the result, while @code{evalExpr} returns it to the caller as an OOP. @code{msgSendf}, instead, has a radically different syntax. Let's first look at some examples. @example /* 1 + 2 */ int shouldBeThree; vmProxy->msgSendf(&shouldBeThree, "%i %i + %i", 1, 2) /* aCollection includes: 'abc' */ OOP aCollection; int aBoolean; vmProxy->msgSendf(&aBoolean, "%b %o includes: %s", aCollection, "abc") /* 'This is a test' printNl -- in two different ways */ vmProxy->msgSendf(NULL, "%v %s printNl", "This is a test"); vmProxy->msgSendf(NULL, "%s %s printNl", "This is a test"); /* 'This is a test', ' ok?' */ char *str; vmProxy->msgSendf(&str, "%s %s , %s", "This is a test", " ok?"); @end example As you can see, the parameters to msgSendf are, in order: @itemize @bullet @item A pointer to the variable which will contain the record. If this pointer is @code{NULL}, it is discarded. @item A description of the method's interface in this format (the object types, after percent signs, will be explained later in this section) @example %result_type %receiver_type selector %param1_type %param2_type @end example @item A C variable or Smalltalk object (depending on the type specifier) for the receiver @item If needed, the C variables and/or Smalltalk object (depending on the type specifiers) for the arguments. @end itemize Note that the receiver and parameters are NOT registered in the object registry (@pxref{Smalltalk types}). @dfn{receiver_type} and @dfn{paramX_type} can be any of these characters, with these meanings: @example Specifier C data type equivalent Smalltalk class i long Integer (see intToOOP) f double Float (see floatToOOP) F long double Float (see longDoubleToOOP) b int True or False (see boolToOOP) B OOP BlockClosure c char Character (see charToOOP) C PTR CObject (see cObjToOOP) s char * String (see stringToOOP) S char * Symbol (see symbolToOOP) o OOP any t char *, PTR CObject (see below) T OOP, PTR CObject (see below) w wchar_t Character (see wcharToOOP) W wchar_t * UnicodeString (see wstringToOOP) @end example @noindent @samp{%t} and @samp{%T} are particular in the sense that you need to pass @dfn{two} additional arguments to @code{msgSendf}, not one. The first will be a description of the type of the CObject to be created, the second instead will be the CObject's address. If you specify @samp{%t}, the first of the two arguments will be converted to a Smalltalk @code{CType} via @code{typeNameToOOP} (@pxref{Smalltalk types}); instead, if you specify @samp{%T}, you will have to directly pass an OOP for the new CObject's type. For @samp{%B} you should not pass a selector, and the block will be evaluated. The type specifiers you can pass for @dfn{result_type} are a bit different: @example Result Specifier if nil C data type expected result i 0L long nil or an Integer f 0.0 double nil or a Float F 0.0 long double nil or a Float b 0 int nil or a Boolean c '\0' char nil or a Character C NULL PTR nil or a CObject s NULL char * nil, a String, or a Symbol ? 0 char *, PTR See oopToC o nilOOP OOP any (result is not converted) w '\0' wchar_t nil or a Character W NULL wchar_t * nil or a UnicodeString v / any (result is discarded) @end example Note that, if resultPtr is @code{NULL}, the @dfn{result_type} is always treated as @samp{%v}. If an error occurs, the value in the `result if nil' column is returned. @node Smalltalk callbacks @section Smalltalk blocks as C function pointers The Smalltalk callin mechanism can be used effectively to construct bindings to C libraries that require callbacks into Smalltalk. However, it is a ``static'' mechanism, as the callback functions passed to the libraries have to be written in C and their type signatures are fixed. If the signatures of the callbacks are not known in advance, and the only way to define callbacks is via C function pointers (as opposed to reflective mechanisms such as the ones in GTK+), then the @code{VMProxy} functions for Smalltalk callin are not enough. @gst{} provides a more dynamic way to convert Smalltalk blocks into C function pointers through the @code{CCallbackDescriptor} class. This class has a constructor method that is similar to the @code{cCall:} annotation used for callouts. The method is called @code{for:returning:withArgs:} and its parameters are: @itemize @bullet @item a block, whose number of arguments is variable @item a symbol representing the return type @item an array representing the type of the arguments. @end itemize The array passed as the third parameter represents values that are passed @emph{from C to Smalltalk} and, as such, should be filled with the same rules that are used by the @emph{return type} of a C callout. In particular, if the C callback accepts an @code{int *} it is possible (and indeed useful) to specify the type of the argument as @code{#@{CInt@}}, so that the block will receive a @code{CInt} object. Here is an example of creating a callback which is passed to @code{glutReshapeFunc}@footnote{The GLUT bindings use a different scheme for setting up callbacks.}. The desired signature in C is @code{void (*) (int, int)}. @example | glut | @r{@dots{}} glut glutReshapeFunc: (CCallbackDescriptor for: [ :x :y | self reshape: x@@y ] returning: #void withArgs: #(#int #int)) @end example It is important to note that this kind of callback does not survive across an image load (this restriction may be lifted in a future version). When the image is loaded, it has to be reset by sending it the @code{link} message before it is passed to any C function. Sending the @code{link} message to an already valid callback is harmless and cheap. @node Other C functions @section Other functions available to modules In addition to the functions described so far, the @code{VMProxy} that is available to modules contains entry-points for many functions that aid in developing @gst{} extensions in C. This node documents these functions and the macros that are defined by @file{libgst/gstpub.h}. @deftypefun void asyncCall (void (*) (OOP), OOP) This functions accepts a function pointer and an OOP (or @code{NULL}, but not an arbitrary pointer) and sets up the interpreter to call the function as soon as the next message send is executed. @emph{Caution:} This and the next two are the only functions in the @code{intepreterProxy} that are thread-safe. @end deftypefun @deftypefun void asyncSignal (OOP) This functions accepts an OOP for a @code{Semaphore} object and signals that object so that one of the processes waiting on that semaphore is waken up. Since a Smalltalk call-in is not an atomic operation, the correct way to signal a semaphore is not to send the @code{signal} method to the object but, rather, to use: @example asyncSignal(semaphoreOOP) @end example The signal request will be processed as soon as the next message send is executed. @end deftypefun @deftypefun void asyncSignalAndUnregister (OOP) This functions accepts an OOP for a @code{Semaphore} object and signals that object so that one of the processes waiting on that semaphore is waken up; the signal request will be processed as soon as the next message send is executed. The object is then removed from the registry. @end deftypefun @deftypefun void wakeUp (void) When no Smalltalk process is running, @gst{} tries to limit CPU usage by pausing until it gets a signal from the OS. @code{wakeUp} is an alternative way to wake up the main Smalltalk loop. This should rarely be necessary, since the above functions already call it automatically. @end deftypefun @deftypefun void syncSignal (OOP, mst_Boolean) This functions accepts an OOP for a @code{Semaphore} object and signals that object so that one of the processes waiting on that semaphore is waken up. If the semaphore has no process waiting in the queue and the second argument is true, an excess signal is added to the semaphore. Since a Smalltalk call-in is not an atomic operation, the correct way to signal a semaphore is not to send the @code{signal} or @code{notify} methods to the object but, rather, to use: @example syncSignal(semaphoreOOP, true) @end example The @code{sync} in the name of this function distinguishes it from @code{asyncSignal}, in that it can only be called from a procedure already scheduled with @code{asyncCall}. It cannot be called from a call-in, or from other threads than the interpreter thread. @end deftypefun @deftypefun void syncWait (OOP) This function is present for backwards-compatibility only and should not be used. @end deftypefun @deftypefun void showBacktrace (FILE *) This functions show a backtrace on the given file. @end deftypefun @deftypefun OOP objectAlloc (OOP, int) The @code{objectAlloc} function allocates an OOP for a newly created instance of the class whose OOP is passed as the first parameter; if that parameter is not a class the results are undefined (for now, read as ``the program will most likely core dump'', but that could change in a future version). The second parameter is used only if the class is an indexable one, otherwise it is discarded: it contains the number of indexed instance variables in the object that is going to be created. Simple uses of @code{objectAlloc} include: @example OOP myClassOOP; OOP myNewObject; myNewObjectData obj; @r{@dots{}} myNewObject = objectAlloc(myClassOOP, 0); obj = (myNewObjectData) OOP_TO_OBJ (myNewObject); obj->arguments = objectAlloc(classNameToOOP("Array"), 10); @r{@dots{}} @end example @end deftypefun @deftypefun size_t OOPSize (OOP) Return the number of indexed instance variables in the given object. @end deftypefun @deftypefun OOP OOPAt (OOP, size_t) Return an indexed instance variable of the given object. The index is in the second parameter and is zero-based. The function aborts if the index is out of range. @end deftypefun @deftypefun OOP OOPAtPut (OOP, size_t, OOP) Put the object given as the third parameter into an indexed instance variable of the object given as the first parameter. The index in the second parameter and is zero-based. The function aborts if the index is out of range. The function returns the old value of the indexed instance variable. @end deftypefun @deftypefun {enum gst_indexed_kind} OOPIndexedKind (OOP) Return the kind of indexed instance variables that the given object has. @end deftypefun @deftypefun {void *} OOPIndexedBase (OOP) Return a pointer to the first indexed instance variable of the given object. The program should first retrieve the kind of data using OOPIndexedKind. @end deftypefun @deftypefun OOP getObjectClass (OOP) Return the class of the Smalltalk object passed as a parameter. @end deftypefun @deftypefun OOP getSuperclass (OOP) Return the superclass of the class given by the Smalltalk object, that is passed as a parameter. @end deftypefun @deftypefun mst_Boolean classIsKindOf (OOP, OOP) Return true if the class given as the first parameter, is the same or a superclass of the class given as the second parameter. @end deftypefun @deftypefun mst_Boolean objectIsKindOf (OOP, OOP) Return true if the object given as the first parameter is an instance of the class given as the second parameter, or of any of its subclasses. @end deftypefun @deftypefun mst_Boolean classImplementsSelector (OOP, OOP) Return true if the class given as the first parameter implements or overrides the method whose selector is given as the second parameter. @end deftypefun @deftypefun mst_Boolean classCanUnderstand (OOP, OOP) Return true if instances of the class given as the first parameter respond to the message whose selector is given as the second parameter. @end deftypefun @deftypefun mst_Boolean respondsTo (OOP, OOP) Return true if the object given as the first parameter responds to the message whose selector is given as the second parameter. @end deftypefun Finally, several slots of the interpreter proxy provide access to the system objects and to the most important classes. These are: @itemize @item @code{nilOOP}, @code{trueOOP}, @code{falseOOP}, @code{processorOOP} @item @code{objectClass}, @code{arrayClass}, @code{stringClass}, @code{characterClass}, @code{smallIntegerClass}, @code{floatDClass}, @code{floatEClass}, @code{byteArrayClass}, @code{objectMemoryClass}, @code{classClass}, @code{behaviorClass}, @code{blockClosureClass}, @code{contextPartClass}, @code{blockContextClass}, @code{methodContextClass}, @code{compiledMethodClass}, @code{compiledBlockClass}, @code{fileDescriptorClass}, @code{fileStreamClass}, @code{processClass}, @code{semaphoreClass}, @code{cObjectClass} @end itemize More may be added in the future The macros are@footnote{IS_NIL and IS_CLASS have been removed because they are problematic in shared libraries (modules), where they caused undefined symbols to be present in the shared library. These are now private to @file{libgst.a}. You should use the @code{nilOOP} field of the interpreter proxy, or @code{getObjectClass}.}: @defmac gst_object OOP_TO_OBJ (OOP) Dereference a pointer to an OOP into a pointer to the actual object data (@pxref{Object representation}). The result of @code{OOP_TO_OBJ} is not valid anymore if a garbage-collection happens; for this reason, you should assume that a pointer to object data is not valid after doing a call-in, calling @code{objectAlloc}, and caling any of the ``C to Smalltalk'' functions (@pxref{Smalltalk types}). @end defmac @defmac OOP OOP_CLASS (OOP) Return the OOP for the class of the given object. For example, @code{OOP_CLASS(proxy->stringToOOP("Wonderful @gst{}"))} is the @code{String} class, as returned by @code{classNameToOOP("String")}. @end defmac @defmac mst_Boolean IS_INT (OOP) Return a Boolean indicating whether or not the OOP is an Integer object; the value of SmallInteger objects is encoded directly in the OOP, not separately in a @code{gst_object} structure. It is not safe to use @code{OOP_TO_OBJ} and @code{OOP_CLASS} if @code{isInt} returns false. @end defmac @defmac mst_Boolean IS_OOP (OOP) Return a Boolean indicating whether or not the OOP is a `real' object (and not a SmallInteger). It is safe to use @code{OOP_TO_OBJ} and @code{OOP_CLASS} only if @code{IS_OOP} returns true. @end defmac @defmac mst_Boolean ARRAY_OOP_AT (gst_object, int) Access the character given in the second parameter of the given Array object. Note that this is necessary because of the way @code{gst_object} is defined, which prevents @code{indexedOOP} from working. @end defmac @defmac mst_Boolean STRING_OOP_AT (gst_object, int) Access the character given in the second parameter of the given String or ByteArray object. Note that this is necessary because of the way @code{gst_object} is defined, which prevents @code{indexedByte} from working. @end defmac @defmac mst_Boolean INDEXED_WORD (@var{some-object-type}, int) Access the given indexed instance variable in a @code{variableWordSubclass}. The first parameter must be a structure declared as described in @ref{Object representation}). @end defmac @defmac mst_Boolean INDEXED_BYTE (@var{some-object-type}, int) Access the given indexed instance variable in a @code{variableByteSubclass}. The first parameter must be a structure declared as described in @ref{Object representation}). @end defmac @defmac mst_Boolean INDEXED_OOP (@var{some-object-type}, int) Access the given indexed instance variable in a @code{variableSubclass}. The first parameter must be a structure declared as described in @ref{Object representation}). @end defmac @node Object representation @section Manipulating instances of your own Smalltalk classes from C Although @gst{}'s library exposes functions to deal with instances of the most common base class, it's likely that, sooner or later, you'll want your C code to directly deal with instances of classes defined by your program. There are three steps in doing so: @itemize @bullet @bulletize Defining the Smalltalk class @bulletize Defining a C @code{struct} that maps the representation of the class @bulletize Actually using the C struct @end itemize In this chapter you will be taken through these steps considering the hypotetical task of defining a Smalltalk interface to an SQL server. The first part is also the simplest, since defining the Smalltalk class can be done in a single way which is also easy and very practical; just evaluate the standard Smalltalk code that does that: @example Object subclass: SQLAction [ | database request | ] SQLAction subclass: SQLRequest [ | returnedRows | ] @end example To define the C @code{struct} for a class derived from Object, @gst{}'s @code{gstpub.h} include file defines an @code{OBJ_HEADER} macro which defines the fields that constitute the header of every object. Defining a @code{struct} for SQLAction results then in the following code: @example struct st_SQLAction @{ OBJ_HEADER; OOP database; OOP request; @} @end example The representation of SQLRequest in memory is this: @example .------------------------------. | common object header | 2 longs |------------------------------| | SQLAction instance variables | | database | 2 longs | request | |------------------------------| | SQLRequest instance variable | | returnedRows | 1 long '------------------------------' @end example A first way to define the struct would then be: @example typedef struct st_SQLAction @{ OBJ_HEADER; OOP database; OOP request; OOP returnedRows; @} *SQLAction; @end example @noindent but this results in a lot of duplicated code. Think of what would happen if you had other subclasses of @code{SQLAction} such as @code{SQLObjectCreation}, @code{SQLUpdateQuery}, and so on! The solution, which is also the one used in @gst{}'s source code is to define a macro for each superclass, in this way: @example /* SQLAction |-- SQLRequest | `-- SQLUpdateQuery `-- SQLObjectCreation */ #define ST_SQLACTION_HEADER \ OBJ_HEADER; \ OOP database; \ OOP request /* no semicolon */ #define ST_SQLREQUEST_HEADER \ ST_SQLACTION_HEADER; \ OOP returnedRows /* no semicolon */ typedef struct st_SQLAction @{ ST_SQLACTION_HEADER; @} *SQLAction; typedef struct st_SQLRequest @{ ST_SQLREQUEST_HEADER; @} *SQLRequest; typedef struct st_SQLObjectCreation @{ ST_SQLACTION_HEADER; OOP newDBObject; @} *SQLObjectCreation; typedef struct st_SQLUpdateQuery @{ ST_SQLREQUEST_HEADER; OOP numUpdatedRows; @} *SQLUpdateQuery; @end example Note that the macro you declare is used instead of @code{OBJ_HEADER} in the declaration of both the superclass and the subclasses. Although this example does not show that, please note that you should not declare anything if the class has indexed instance variables. The first step in actually using your structs is obtaining a pointer to an OOP which is an instance of your class. Ways to do so include doing a call-in, receiving the object from a call-out (using @code{#smalltalk}, @code{#self} or @code{#selfSmalltalk} as the type specifier). Let's assume that the @code{oop} variable contains such an object. Then, you have to dereference the OOP (which, as you might recall from @ref{Smalltalk types}, point to the actual object only indirectly) and get a pointer to the actual data. You do that with the @code{OOP_TO_OBJ} macro (note the type casting): @example SQLAction action = (SQLAction) OOP_TO_OBJ(oop); @end example Now you can use the fields in the object like in this pseudo-code: @example /* These are retrieved via classNameToOOP and then cached in global variables */ OOP sqlUpdateQueryClass, sqlActionClass, sqlObjectCreationClass; @r{@dots{}} invoke_sql_query( vmProxy->oopToCObject(action->database), vmProxy->oopToString(action->request), query_completed_callback, /* Callback function */ oop); /* Passed to the callback */ @dots{} /* Imagine that invoke_sql_query runs asynchronously and calls this when the job is done. */ void query_completed_callback(result, database, request, clientData) struct query_result *result; struct db *database; char *request; OOP clientData; @{ SQLUpdateQuery query; OOP rows; OOP cObject; /* Free the memory allocated by oopToString */ free(request); if (OOP_CLASS (oop) == sqlActionClass) return; if (OOP_CLASS (oop) == sqlObjectCreationClass) @{ SQLObjectCreation oc; oc = (SQLObjectCreation) OOP_TO_OBJ (clientData); cObject = vmProxy->cObjectToOOP (result->dbObject) oc->newDBObject = cObject; @} else @{ /* SQLRequest or SQLUpdateQuery */ cObject = vmProxy->cObjectToOOP (result->rows); query = (SQLUpdateQuery) OOP_TO_OBJ (clientData); query->returnedRows = cObject; if (OOP_CLASS (oop) == sqlUpdateQueryClass) query->numReturnedRows = vmProxy->intToOOP (result->count); @} @} @end example Note that the result of @code{OOP_TO_OBJ} is not valid anymore if a garbage-collection happens; for this reason, you should assume that a pointer to object data is not valid after doing a call-in, calling @code{objectAlloc}, and using any of the ``C to Smalltalk'' functions except @code{intToOOP} (@pxref{Smalltalk types}). That's why I passed the OOP to the callback, not the object pointer itself. If your class has indexed instance variables, you can use the @code{INDEXED_WORD}, @code{INDEXED_OOP} and @code{INDEXED_BYTE} macros declared in @code{gstpub.h}, which return an lvalue for the given indexed instance variable---for more information, @pxref{Other C functions}. @node Using Smalltalk @section Using the Smalltalk environment as an extension library If you are reading this chapter because you are going to write extensions to @gst{}, this section won't probably interest you. But if you intend to use @gst{} as a scripting language or an extension language for your future marvellous software projects, you might be interest. How to initialize @gst{} is most briefly and easily explained by looking at @gst{}'s own source code. For this reason, here is a simplified snippet from @file{gst-tool.c}. @example int main(argc, argv) int argc; char **argv; @{ gst_set_var (GST_VERBOSITY, 1); gst_smalltalk_args (argc - 1, argv + 1); gst_set_executable_path (argv[0]); result = gst_initialize ("@var{kernel-dir}", "@var{image-file}", GST_NO_TTY); if (result != 0) exit (result < 0 ? 1 : result); if (!gst_process_file ("@var{source-file}", GST_DIR_KERNEL_SYSTEM)) perror ("gst: couldn't load `@var{source-file}'"); gst_invoke_hook (GST_ABOUT_TO_QUIT); exit (0); @} @end example Your initialization code will be almost the same as that in @gst{}'s @code{main()}, with the exception of the call to @code{gst_process_file}. All you'll have to do is to pass some arguments to the @gst{} library via @code{gst_smalltalk_args}, possibly modify some defaults using @code{gst_get_var} and @code{gst_set_var}, and then call @code{gst_initialize}. Variable indices that can be passed to @code{gst_get_var} and @code{gst_set_var} include: @table @code @item GST_DECLARE_TRACING @item GST_EXECUTION_TRACING @item GST_EXECUTION_TRACING_VERBOSE @item GST_GC_MESSAGE @item GST_VERBOSITY @item GST_MAKE_CORE_FILE @item GST_REGRESSION_TESTING @end table While the flags that can be passed as the last parameter to @code{gst_initialize} are any combination of these: @table @code @item GST_REBUILD_IMAGE @item GST_MAYBE_REBUILD_IMAGE @item GST_IGNORE_USER_FILES @item GST_IGNORE_BAD_IMAGE_NAME @item GST_IGNORE_BAD_IMAGE_PATH @item GST_IGNORE_BAD_KERNEL_PATH @item GST_NO_TTY @end table Note that @code{gst_initialize} will likely take some time (from a tenth of a second to 3-4 seconds), because it has to check if the image file must be be rebuilt and, if so, it reloads and recompiles the over 50,000 lines of Smalltalk code that form a basic image. To avoid this check, pass a valid image file as the second argument to @code{gst_initialize}. The result of @code{gst_init_smalltalk} is @code{0} for success, while anything else is an error code. If you're using @gst{} as an extension library, you might also want to disable the two @code{ObjectMemory} class methods, @code{quit} and @code{quit:} method. I advice you not to change the Smalltalk kernel code. Instead, in the script that loads your extension classes add these two lines: @example ObjectMemory class compile: 'quit self shouldNotImplement'! ObjectMemory class compile: 'quit: n self shouldNotImplement'! @end example @noindent which will effectively disable the two offending methods. Other possibilities include using @code{atexit} (from the C library) to exit your program in a less traumatic way, or redefining these two methods to exit through a call out to a C routine in your program. Also, note that it is not a problem if you develop the class libraries for your programs within @gst{}'s environment (which will not call @code{defineCFunc} for your own C call-outs), since the addresses of the C call-outs are looked up again when an image is restored. @node Incubator @section Incubator support The incubator concept provides a mechanism to protect newly created objects from being accidentally garbage collected before they can be attached to some object which is reachable from the root set. If you are creating some set of objects which will not be immediately (that means, before the next object is allocated from the Smalltalk memory system) be attached to an object which is still ``live'' (reachable from the root set of objects), you'll need to use this interface. If you are writing a C call-out from Smalltalk (for example, inside a module), you will not have direct access to the incubator; instead the functions described in @ref{Smalltalk types} automatically put the objects that they create in the incubator, and the virtual machine takes care of wrapping C call-outs so that the incubator state is restored at the end of the call. This section describes its usage from the point of view of a program that is linking with @code{libgst.a}. Such a program has much finer control to the incubator. The interface provides the following operations: @defmac void INC_ADD_OOP (OOP anOOP) Adds a new object to the protected set. @end defmac @defmac inc_ptr INC_SAVE_POINTER () Retrieves the current incubator pointer. Think of the incubator as a stack, and this operation returns the current stack pointer for later use (restoration) with the incRestorePointer function. @end defmac @defmac void INC_RESTORE_POINTER (inc_ptr ptr) Sets (restores) the incubator pointer to the given pointer value. @end defmac Typically, when you are within a function which allocates more than one object at a time, either directly or indirectly, you'd want to use the incubator mechanism. First you'd save a copy of the current pointer in a local variable. Then, for each object you allocate (except the last, if you want to be optimal), after you create the object you add it to the incubator's list. When you return, you need to restore the incubator's pointer to the value you got with @code{INC_SAVE_POINTER} using the @code{INC_RESTORE_POINTER} macro. Here's an example from cint.c: The old code was (the comments are added for this example): @example desc = (_gst_cfunc_descriptor) new_instance_with (cFuncDescriptorClass, numArgs); desc->cFunction = _gst_cobject_new (funcAddr); // 1 desc->cFunctionName = _gst_string_new (funcName); // 2 desc->numFixedArgs = FROM_INT (numArgs); desc->returnType = _gst_classify_type_symbol (returnTypeOOP, true); for (i = 1; i <= numArgs; i++) @{ desc->argTypes[i - 1] = _gst_classify_type_symbol(ARRAY_AT(argsOOP, i), false); @} return (_gst_alloc_oop(desc)); @end example @code{desc} is originally allocated via @code{newInstanceWith} and @code{allocOOP}, two private routines which are encapsulated by the public routine @code{objectAlloc}. At ``1'', more storage is allocated, and the garbage collector has the potential to run and free (since no live object is referring to it) desc's storage. At ``2'' another object is allocated, and again the potential for losing both @code{desc} and @code{desc->cFunction} is there if the GC runs (this actually happened!). To fix this code to use the incubator, modify it like this: @example OOP descOOP; IncPtr ptr; incPtr = INC_SAVE_POINTER(); desc = (_gst_cfunc_descriptor) new_instance_with (cFuncDescriptorClass, numArgs); descOOP = _gst_alloc_oop(desc); INC_ADD_OOP (descOOP); desc->cFunction = _gst_cobject_new (funcAddr); // 1 INC_ADD_OOP (desc->cFunction); desc->cFunctionName = _gst_string_new (funcName); // 2 /* @r{since none of the rest of the function (or the functions it calls)} * @r{allocates any storage, we don't have to add desc->cFunctionName} * @r{to the incubator's set of objects, although we could if we wanted} * @r{to be completely safe against changes to the implementations of} * @r{the functions called from this function.} */ desc->numFixedArgs = FROM_INT (numArgs); desc->returnType = _gst_classify_type_symbol (returnTypeOOP, true); for (i = 1; i <= numArgs; i++) @{ desc->argTypes[i - 1] = _gst_classify_type_symbol(ARRAY_AT(argsOOP, i), false); @} return (_gst_alloc_oop(desc)); @end example Note that it is permissible for two or more functions to cooperate with their use of the incubator. For example, say function A allocates some objects, then calls function B which allocates some more objects, and then control returns to A where it does some more execution with the allocated objects. If B is only called by A, B can leave the management of the incubator pointer up to A, and just register the objects it allocates with the incubator. When A does a @code{INC_RESTORE_POINTER}, it automatically clears out the objects that B has registered from the incubator's set of objects as well; the incubator doesn't know about functions A & B, so as far as it is concerned, all of the registered objects were registered from the same function. @node Tutorial @chapter Tutorial @include tutorial.texi @iftex @contents @end iftex @bye Local Variables: compile-command: "makeinfo -fc 72 gst.texi" fill-column: 72 End: smalltalk-3.2.5/doc/gst-libs.texi0000644000175000017500000000702512130455701013614 00000000000000\input texinfo.tex @c -*- texinfo -*- @c %**start of header (This is for running Texinfo on a region.) @setfilename gst-libs.info @settitle GNU Smalltalk Library Reference @setchapternewpage odd @c %**end of header (This is for running Texinfo on a region.) @c ******************************************* Values and macros ********* @include vers-libs.texi @ifclear UPDATE-MONTH @set UPDATE-MONTH @value{UPDATED} @end ifclear @macro bulletize{a} @item \a\ @end macro @c ********************************************** Texinfo 4.0 macros ***** @c Emulate the `@ifnottex' command which is found in Texinfo 4.0 @iftex @set IS_TEX @end iftex @c *********************************************************************** @macro gst{} @sc{gnu} Smalltalk @end macro @macro gnu{} @sc{gnu} @end macro @dircategory Software development @direntry * Smalltalk libraries: (gst-libs). The GNU Smalltalk class libraries. @end direntry @copying @quotation Permission is granted to copy, distribute and/or modify this document under the terms of the GNU Free Documentation License, Version 1.2 or any later version published by the Free Software Foundation; with no Invariant Sections, with no Front-Cover Texts, and with no Back-Cover Texts. A copy of the license is included in the section entitled ``GNU Free Documentation License''. @end quotation @end copying @setchapternewpage odd @titlepage @title @sc{gnu} Smalltalk Library Reference @subtitle Version @value{VERSION} @subtitle @value{UPDATE-MONTH} @author by Paolo Bonzini @comment The following two commands start the copyright page. @page @vskip 0pt plus 1filll @insertcopying @end titlepage @node Top, , , (DIR) @top @ifnottex This document describes the class libraries that are distributed together with the @gst{} programming language. @insertcopying @end ifnottex @menu * BLOX package:: The GUI library * Complex package:: Complex number computations * DBI package:: The database connectivity library * DebugTools package:: Controlling the execution of Smalltalk processes * Sockets package:: The sockets library * Iconv/I18N packages:: The internationalization library * XML/XPath/XSL packages:: Using the XML library * ZLib package:: Bindings to the popular data compression library * Class index:: Index to the classes in the class reference * Method index:: Index to the method selectors in the class reference * Cross-reference:: Cross-reference between selectors @end menu @node BLOX package @chapter Graphical users interfaces with BLOX @include blox.texi @node Complex package @chapter Complex number computations @include complex.texi @node DBI package @chapter Database connectivity with DBI @include dbi.texi @node DebugTools package @chapter Controlling Smalltalk processes with DebugTools @include debug.texi @node Iconv/I18N packages @chapter Multilingual and international support with Iconv and I18N @include i18n.texi @node Sockets package @chapter Network programming with Sockets @include sockets.texi @node ZLib package @chapter Compressing and decompressing data with ZLib @include zlib.texi @node XML/XPath/XSL packages @chapter Libraries for the SAX, DOM, XPath and XSLT standards @include using-xml.texi @node Class index @unnumbered Class index @printindex cl @node Method index @unnumbered Method index @printindex me @node Cross-reference @unnumbered Selector cross-reference @printindex sl @iftex @contents @end iftex @bye Local Variables: compile-command: "makeinfo -fc 72 gst-libs.texi" fill-column: 72 End: smalltalk-3.2.5/doc/i18n.texi0000644000175000017500000015402412130455677012665 00000000000000@c Define the class index, method index, and selector cross-reference @ifclear CLASS-INDICES @set CLASS-INDICES @defindex cl @defcodeindex me @defcodeindex sl @end ifclear @c These are used for both TeX and HTML @set BEFORE1 @set AFTER1 @set BEFORE2 @set AFTER2 @ifinfo @c Use asis so that leading and trailing spaces are meaningful. @c Remember we're inside a @menu command, hence the blanks are @c kept in the output. @set BEFORE1 @asis{* } @set AFTER1 @asis{::} @set BEFORE2 @asis{ (} @set AFTER2 @asis{)} @end ifinfo @macro class {a,b} @value{BEFORE1}\a\\a\@b{\b\}@value{AFTER1} @end macro @macro superclass {a,b} \a\\a\@value{BEFORE2}@i{\b\}@value{AFTER2} @end macro @ifnotinfo @macro begindetailmenu @display @end macro @macro enddetailmenu @end display @end macro @end ifnotinfo @ifinfo @macro begindetailmenu @detailmenu @end macro @macro enddetailmenu @end detailmenu @end macro @end ifinfo @iftex @macro beginmenu @end macro @macro endmenu @end macro @end iftex @ifnottex @macro beginmenu @menu @end macro @macro endmenu @end menu @end macro @end ifnottex @beginmenu @ifnottex Alphabetic list: * I18N.BigEndianFileStream:: * I18N.EncodedStream:: * I18N.EncodedString:: * I18N.EncodedStringFactory:: * I18N.Encoder:: * I18N.FileStreamSegment:: * I18N.IncompleteSequenceError:: * I18N.InvalidCharsetError:: * I18N.InvalidSequenceError:: * I18N.LcMessages:: * I18N.LcMessagesCatalog:: * I18N.LcMessagesDomain:: * I18N.LcMessagesDummyDomain:: * I18N.LcMessagesMoFileVersion0:: * I18N.LcMessagesTerritoryDomain:: * I18N.LcMonetary:: * I18N.LcMonetaryISO:: * I18N.LcNumeric:: * I18N.LcPrintFormats:: * I18N.LcTime:: * I18N.Locale:: * I18N.LocaleConventions:: * I18N.LocaleData:: * I18N.RTEAlternativeNode:: * I18N.RTEBinaryNode:: * I18N.RTELiteralNode:: * I18N.RTENegationNode:: * I18N.RTEParameterNode:: * I18N.RunTimeExpression:: @end ifnottex @ifinfo Class tree: @end ifinfo @iftex @section Tree @end iftex @ifnotinfo Classes documented in this manual are @b{boldfaced}. @end ifnotinfo @begindetailmenu @superclass{@t{}, Object} @superclass{@t{ }, Exception} @superclass{@t{ }, Error} @class{@t{ }, I18N.IncompleteSequenceError} @class{@t{ }, I18N.InvalidSequenceError} @superclass{@t{ }, SystemExceptions.InvalidValue} @superclass{@t{ }, SystemExceptions.SystemExceptions.InvalidArgument} @class{@t{ }, I18N.InvalidCharsetError} @superclass{@t{ }, FileSegment} @class{@t{ }, I18N.FileStreamSegment} @class{@t{ }, I18N.EncodedStringFactory} @class{@t{ }, I18N.LocaleData} @class{@t{ }, I18N.LcMessagesDomain} @class{@t{ }, I18N.LcMessagesCatalog} @class{@t{ }, I18N.LcMessagesMoFileVersion0} @class{@t{ }, I18N.LcMessagesDummyDomain} @class{@t{ }, I18N.LcMessagesTerritoryDomain} @class{@t{ }, I18N.Locale} @class{@t{ }, I18N.LocaleConventions} @class{@t{ }, I18N.LcMessages} @class{@t{ }, I18N.LcPrintFormats} @class{@t{ }, I18N.LcNumeric} @class{@t{ }, I18N.LcMonetary} @class{@t{ }, I18N.LcMonetaryISO} @class{@t{ }, I18N.LcTime} @class{@t{ }, I18N.RunTimeExpression} @class{@t{ }, I18N.RTEAlternativeNode} @class{@t{ }, I18N.RTEBinaryNode} @class{@t{ }, I18N.RTELiteralNode} @class{@t{ }, I18N.RTENegationNode} @class{@t{ }, I18N.RTEParameterNode} @superclass{@t{ }, Iterable} @superclass{@t{ }, Collection} @superclass{@t{ }, SequenceableCollection} @superclass{@t{ }, ArrayedCollection} @superclass{@t{ }, CharacterArray} @class{@t{ }, I18N.EncodedString} @superclass{@t{ }, Stream} @superclass{@t{ }, FileDescriptor} @superclass{@t{ }, FileStream} @class{@t{ }, I18N.BigEndianFileStream} @class{@t{ }, I18N.EncodedStream} @class{@t{ }, I18N.Encoder} @enddetailmenu @endmenu @unmacro class @unmacro superclass @unmacro endmenu @unmacro beginmenu @unmacro enddetailmenu @unmacro begindetailmenu @node I18N.BigEndianFileStream @section I18N.BigEndianFileStream @clindex I18N.BigEndianFileStream @table @b @item Defined in namespace I18N @itemx Superclass: FileStream @itemx Category: i18n-Messages Unlike ByteStream and FileStream, this retrieves integer numbers in big-endian (68000, PowerPC, SPARC) order. @end table @menu @end menu @node I18N.EncodedStream @section I18N.EncodedStream @clindex I18N.EncodedStream @table @b @item Defined in namespace I18N @itemx Superclass: Stream @itemx Category: i18n-Character sets This class is a factory for subclasses of Encoder. Encoders act as parts of a pipe, hence this class provides methods that construct an appropriate pipe. @end table @menu * I18N.EncodedStream class-initializing:: (class) * I18N.EncodedStream class-instance creation:: (class) @end menu @node I18N.EncodedStream class-initializing @subsection I18N.EncodedStream class:@- initializing @table @b @meindex initialize @item initialize Initialize the registry of the encoders to include the standard encoders contained in the library. @meindex registerEncoderFor:@-toUTF32:@-fromUTF32:@- @slindex next @item registerEncoderFor:@- arrayOfAliases toUTF32:@- toUTF32Class fromUTF32:@- fromUTF32Class Register the two classes that will respectively convert from the charsets in arrayOfAliases to UTF-32 and vice versa. The former class is a stream that accepts characters and returns (via #next) integers representing UTF-32 character codes, while the latter accepts UTF-32 character codes and converts them to characters. For an example see respectively FromUTF7 and ToUTF7 (I admit it is not a trivial example). @end table @node I18N.EncodedStream class-instance creation @subsection I18N.EncodedStream class:@- instance creation @table @b @meindex encoding:@- @item encoding:@- anUnicodeString Answer a pipe of encoders that converts anUnicodeString to default encoding for strings (the current locale's default charset if none is specified). @meindex encoding:@-as:@- @item encoding:@- aStringOrStream as:@- toEncoding Answer a pipe of encoders that converts anUnicodeString (which contains to the supplied encoding (which can be an ASCII String or Symbol). @meindex on:@-from:@- @item on:@- aStringOrStream from:@- fromEncoding Answer a pipe of encoders that converts aStringOrStream (which can be a string or another stream) from the given encoding to the default locale's default charset. @meindex on:@-from:@-to:@- @item on:@- aStringOrStream from:@- fromEncoding to:@- toEncoding Answer a pipe of encoders that converts aStringOrStream (which can be a string or another stream) between the two supplied encodings (which can be ASCII Strings or Symbols) @meindex on:@-to:@- @item on:@- aStringOrStream to:@- toEncoding Answer a pipe of encoders that converts aStringOrStream (which can be a string or another stream) from the default locale's default charset to the given encoding. @meindex unicodeOn:@- @item unicodeOn:@- aStringOrStream Answer a pipe of encoders that converts aStringOrStream (which can be a string or another stream) from its encoding (or the current locale's default charset, if the encoding cannot be determined) to integers representing Unicode character codes. @meindex unicodeOn:@-encoding:@- @item unicodeOn:@- aStringOrStream encoding:@- fromEncoding Answer a pipe of encoders that converts aStringOrStream (which can be a string or another stream) from the supplied encoding (which can be an ASCII String or Symbol) to integers representing Unicode character codes. @end table @node I18N.EncodedString @section I18N.EncodedString @clindex I18N.EncodedString @table @b @item Defined in namespace I18N @itemx Superclass: CharacterArray @itemx Category: i18n-Character sets An EncodedString, like a String, is a sequence of bytes representing a specific encoding of a UnicodeString. Unlike a String, however, the encoding name is known, rather than detected, irrelevant or assumed to be the system default. @end table @menu * I18N.EncodedString class-accessing:: (class) * I18N.EncodedString class-instance creation:: (class) * I18N.EncodedString-accessing:: (instance) * I18N.EncodedString-copying:: (instance) * I18N.EncodedString-initializing:: (instance) * I18N.EncodedString-printing:: (instance) @end menu @node I18N.EncodedString class-accessing @subsection I18N.EncodedString class:@- accessing @table @b @meindex isUnicode @item isUnicode Answer false; the receiver stores bytes (i.e. an encoded form), not characters. @end table @node I18N.EncodedString class-instance creation @subsection I18N.EncodedString class:@- instance creation @table @b @meindex fromString:@- @item fromString:@- aString Not commented. @meindex fromString:@-encoding:@- @item fromString:@- aString encoding:@- encoding Not commented. @meindex new @item new This method should not be called for instances of this class. @meindex new:@- @item new:@- size This method should not be called for instances of this class. @end table @node I18N.EncodedString-accessing @subsection I18N.EncodedString:@- accessing @table @b @meindex asString @item asString Answer `string'. @meindex asUnicodeString @item asUnicodeString Not commented. @meindex at:@- @item at:@- anIndex Not commented. @meindex at:@-put:@- @item at:@- anIndex put:@- anObject Not commented. @meindex do:@- @item do:@- aBlock Not commented. @meindex encoding @item encoding Not commented. @meindex hash @item hash Not commented. @meindex size @item size Not commented. @meindex species @item species Not commented. @meindex utf16Encoding @item utf16Encoding Not commented. @meindex utf32Encoding @item utf32Encoding Not commented. @meindex valueAt:@- @item valueAt:@- anIndex Not commented. @meindex valueAt:@-put:@- @item valueAt:@- anIndex put:@- anObject Not commented. @end table @node I18N.EncodedString-copying @subsection I18N.EncodedString:@- copying @table @b @meindex copy @item copy Not commented. @meindex copyEmpty @item copyEmpty Not commented. @meindex copyEmpty:@- @item copyEmpty:@- size Not commented. @end table @node I18N.EncodedString-initializing @subsection I18N.EncodedString:@- initializing @table @b @meindex encoding:@- @item encoding:@- aString Not commented. @meindex setString:@- @item setString:@- aString Not commented. @end table @node I18N.EncodedString-printing @subsection I18N.EncodedString:@- printing @table @b @meindex displayOn:@- @slindex printOn:@- @item displayOn:@- aStream Print a representation of the receiver on aStream. Unlike #printOn:@-, this method does not display the encoding and enclosing quotes. @meindex printOn:@- @item printOn:@- aStream Print a representation of the receiver on aStream. @end table @node I18N.EncodedStringFactory @section I18N.EncodedStringFactory @clindex I18N.EncodedStringFactory @table @b @item Defined in namespace I18N @itemx Superclass: Object @itemx Category: i18n-Character sets An EncodedStringFactory is used (in place of class objects) so that Encoders can return EncodedString objects with the correct encoding. @end table @menu * I18N.EncodedStringFactory class-instance creation:: (class) * I18N.EncodedStringFactory-accessing:: (instance) * I18N.EncodedStringFactory-instance creation:: (instance) @end menu @node I18N.EncodedStringFactory class-instance creation @subsection I18N.EncodedStringFactory class:@- instance creation @table @b @meindex encoding:@- @item encoding:@- aString Answer a new EncodedStringFactory, creating strings with the given encoding. @end table @node I18N.EncodedStringFactory-accessing @subsection I18N.EncodedStringFactory:@- accessing @table @b @meindex isUnicode @item isUnicode Answer false; the receiver stores bytes (i.e. an encoded form), not characters. @end table @node I18N.EncodedStringFactory-instance creation @subsection I18N.EncodedStringFactory:@- instance creation @table @b @meindex encoding @item encoding Answer the encoding used for the created Strings. @meindex encoding:@- @item encoding:@- aString Set the encoding used for the created Strings. @meindex fromString:@- @item fromString:@- aString Answer an EncodedString based on aString and in the encoding represented by the receiver. @meindex new @item new Answer a new, empty EncodedString using the encoding represented by the receiver. @meindex new:@- @item new:@- size Answer a new EncodedString of the given size, using the encoding represented by the receiver. @end table @node I18N.Encoder @section I18N.Encoder @clindex I18N.Encoder @table @b @item Defined in namespace I18N @itemx Superclass: Stream @itemx Category: i18n-Character sets This class is the superclass of streams that take an origin and encode it to another character set. The subclasses are are for internal use unless you are writing support for your own encodings. @end table @menu * I18N.Encoder class-instance creation:: (class) * I18N.Encoder-stream operations:: (instance) @end menu @node I18N.Encoder class-instance creation @subsection I18N.Encoder class:@- instance creation @table @b @meindex on:@-from:@-to:@- @item on:@- aStringOrStream from:@- fromEncoding to:@- toEncoding Answer a new encoder that translates from fromEncoding to toEncoding. The encodings are guaranteed to be those for which the encoder was registered. @end table @node I18N.Encoder-stream operations @subsection I18N.Encoder:@- stream operations @table @b @meindex atEnd @item atEnd Return whether the receiver can produce another character in the receiver; by default, this is true if there is another character in the origin. @meindex atEndOfInput @item atEndOfInput Return whether there is another character in the origin. This method is for private use by encoders, calling it outside won't corrupt the internal state of the encoder but the result probably won't be meaningful (depending on the innards of the encoder). @meindex next @item next Return the next character in the receiver; by default, this is the next character in the origin. @meindex nextInput @item nextInput Return the next character in the origin. This method is for private use by encoders, calling it outside may corrupt the internal state of the encoder. @meindex nextInputAvailable:@-into:@-startingAt:@- @item nextInputAvailable:@- n into:@- aCollection startingAt:@- pos Place up to N characters from the origin in aCollection. This method is for private use by encoders, calling it outside may corrupt the internal state of the encoder. @meindex peekInput @item peekInput Return the next character in the origin without advancing it. @meindex species @item species We answer a string of Characters encoded in our destination encoding. @end table @node I18N.FileStreamSegment @section I18N.FileStreamSegment @clindex I18N.FileStreamSegment @table @b @item Defined in namespace I18N @itemx Superclass: FileSegment @itemx Category: i18n-Messages Unlike FileSegment, this object assumes that the `file' instance variable is a FileStream, not a file name. @end table @menu * I18N.FileStreamSegment-basic:: (instance) @end menu @node I18N.FileStreamSegment-basic @subsection I18N.FileStreamSegment:@- basic @table @b @meindex fileName @item fileName Answer the name of the file containing the segment @meindex withFileDo:@- @item withFileDo:@- aBlock Evaluate aBlock, passing a FileStream corresponding to the file @end table @node I18N.IncompleteSequenceError @section I18N.IncompleteSequenceError @clindex I18N.IncompleteSequenceError @table @b @item Defined in namespace I18N @itemx Superclass: Error @itemx Category: i18n-Character sets I am raised if an invalid sequence is found while converting a string from a charset to another. In particular, I am raised if the input stream ends abruptly in the middle of a multi-byte sequence. @end table @menu * I18N.IncompleteSequenceError-accessing:: (instance) @end menu @node I18N.IncompleteSequenceError-accessing @subsection I18N.IncompleteSequenceError:@- accessing @table @b @meindex description @item description Answer a textual description of the exception. @end table @node I18N.InvalidCharsetError @section I18N.InvalidCharsetError @clindex I18N.InvalidCharsetError @table @b @item Defined in namespace I18N @itemx Superclass: SystemExceptions.SystemExceptions.InvalidArgument @itemx Category: i18n-Character sets I am raised if the user tries to encode from or to an unknown encoding @end table @menu * I18N.InvalidCharsetError-accessing:: (instance) @end menu @node I18N.InvalidCharsetError-accessing @subsection I18N.InvalidCharsetError:@- accessing @table @b @meindex description @item description Answer a textual description of the exception. @end table @node I18N.InvalidSequenceError @section I18N.InvalidSequenceError @clindex I18N.InvalidSequenceError @table @b @item Defined in namespace I18N @itemx Superclass: Error @itemx Category: i18n-Character sets I am raised if an invalid sequence is found while converting a string from a charset to another @end table @menu * I18N.InvalidSequenceError-accessing:: (instance) @end menu @node I18N.InvalidSequenceError-accessing @subsection I18N.InvalidSequenceError:@- accessing @table @b @meindex description @item description Answer a textual description of the exception. @end table @node I18N.LcMessages @section I18N.LcMessages @clindex I18N.LcMessages @table @b @item Defined in namespace I18N @itemx Superclass: I18N.LocaleConventions @itemx Category: i18n-Messages This object is a factory of LcMessagesDomain objects @end table @menu * I18N.LcMessages class-accessing:: (class) * I18N.LcMessages-accessing:: (instance) * I18N.LcMessages-opening MO files:: (instance) @end menu @node I18N.LcMessages class-accessing @subsection I18N.LcMessages class:@- accessing @table @b @meindex category @item category Answer the environment variable used to determine the default locale @meindex selector @item selector Answer the selector that accesses the receiver when sent to a Locale object. @end table @node I18N.LcMessages-accessing @subsection I18N.LcMessages:@- accessing @table @b @meindex languageDirectory @item languageDirectory Answer the directory holding MO files for the language @meindex languageDirectory:@- @item languageDirectory:@- rootDirectory Answer the directory holding MO files for the language, given the root directory of the locale data. @meindex territoryDirectory @item territoryDirectory Answer the directory holding MO files for the language, specific to the territory @meindex territoryDirectory:@- @item territoryDirectory:@- rootDirectory Answer the directory holding MO files for the language, specific to the territory, given the root directory of the locale data. @end table @node I18N.LcMessages-opening MO files @subsection I18N.LcMessages:@- opening MO files @table @b @meindex ? @item ? aString Answer an object for the aString domain, querying both the language catalog (e.g. pt) and the territory catalog (e.g. pt_BR or pt_PT). @meindex domain:@- @item domain:@- aString Answer an object for the aString domain, querying both the language catalog (e.g. pt) and the territory catalog (e.g. pt_BR or pt_PT). @meindex domain:@-localeDirectory:@- @item domain:@- aString localeDirectory:@- rootDirectory Answer an object for the aString domain, querying both the language catalog (e.g. pt) and the territory catalog (e.g. pt_BR or pt_PT). The localeDirectory is usually '/share/locale'. @end table @node I18N.LcMessagesCatalog @section I18N.LcMessagesCatalog @clindex I18N.LcMessagesCatalog @table @b @item Defined in namespace I18N @itemx Superclass: I18N.LcMessagesDomain @itemx Category: i18n-Messages This object is an abstract superclass of objects that retrieve translated strings from a file. @end table @menu @end menu @node I18N.LcMessagesDomain @section I18N.LcMessagesDomain @clindex I18N.LcMessagesDomain @table @b @item Defined in namespace I18N @itemx Superclass: I18N.LocaleData @itemx Category: i18n-Messages This object is an abstract superclass for message domains (catalogs). It contains methods to create instances of its subclasses, but they are commonly used only by LcMessages. Translations are accessed using either #at:@- or the shortcut binary messages `?'. This way, common idioms to access translated strings will be string := NLS? 'abc'. string := self? 'abc'. (in the first case NLS is a class variable, in the second the receiver implements #? through delegation) which is only five or six characters longer than the traditional string := 'abc'. (cfr. the _("abc") idiom used by GNU gettext) @end table @menu * I18N.LcMessagesDomain class-opening MO files:: (class) * I18N.LcMessagesDomain-handling the cache:: (instance) * I18N.LcMessagesDomain-querying:: (instance) @end menu @node I18N.LcMessagesDomain class-opening MO files @subsection I18N.LcMessagesDomain class:@- opening MO files @table @b @meindex id:@-on:@- @item id:@- anArray on:@- aFileName Create an instance of the receiver with a given locale identifier from a path to the MO file @end table @node I18N.LcMessagesDomain-handling the cache @subsection I18N.LcMessagesDomain:@- handling the cache @table @b @meindex flush @item flush Flush the receiver's cache of translations @meindex shouldCache @item shouldCache Answer whether translations should be cached. Never override this method to always answer false, because that would cause bugs when transliteration is being used. @end table @node I18N.LcMessagesDomain-querying @subsection I18N.LcMessagesDomain:@- querying @table @b @meindex ? @item ? aString Answer the translation of `aString', or answer aString itself if none is available. @meindex at:@- @item at:@- aString Answer the translation of `aString', or answer aString itself if none is available. @meindex at:@-plural:@-with:@- @item at:@- singularString plural:@- pluralString with:@- n Answer either the translation of pluralString with `%1' replaced by n if n ~= 1, or the translation of singularString if n = 1. @meindex at:@-put:@- @item at:@- aString put:@- anotherString This method should not be called for instances of this class. @meindex translatorInformation @item translatorInformation Answer information on the translation, or nil if there is none. This information is stored as the `translation' of an empty string. @meindex translatorInformationAt:@- @item translatorInformationAt:@- key Answer information on the translation associated to a given key @meindex translatorInformationAt:@-at:@- @item translatorInformationAt:@- key at:@- subkey Answer information on the translation associated to a given key and to a subkey of the key @end table @node I18N.LcMessagesDummyDomain @section I18N.LcMessagesDummyDomain @clindex I18N.LcMessagesDummyDomain @table @b @item Defined in namespace I18N @itemx Superclass: I18N.LcMessagesDomain @itemx Category: i18n-Messages This object does no attempt to translate strings, returning instead the same string passed as an argument to #?. @end table @menu @end menu @node I18N.LcMessagesMoFileVersion0 @section I18N.LcMessagesMoFileVersion0 @clindex I18N.LcMessagesMoFileVersion0 @table @b @item Defined in namespace I18N @itemx Superclass: I18N.LcMessagesCatalog @itemx Category: i18n-Messages This object is an concrete class that retrieves translated strings from a GNU gettext MO file. The class method #fileFormatDescription contains an explanation of the file format. @end table @menu * I18N.LcMessagesMoFileVersion0 class-documentation:: (class) * I18N.LcMessagesMoFileVersion0 class-plurals:: (class) * I18N.LcMessagesMoFileVersion0-flushing the cache:: (instance) @end menu @node I18N.LcMessagesMoFileVersion0 class-documentation @subsection I18N.LcMessagesMoFileVersion0 class:@- documentation @table @b @meindex fileFormatDescription @item fileFormatDescription The Format of GNU MO Files (excerpt of the GNU gettext manual) ============================================================== The format of the generated MO files is best described by a picture, which appears below. The first two words serve the identification of the file. The magic number will always signal GNU MO files. The number is stored in the byte order of the generating machine, so the magic number really is two numbers:@- `0x950412de' and `0xde120495'. The second word describes the current revision of the file format. For now the revision is 0. This might change in future versions, and ensures that the readers of MO files can distinguish new formats from old ones, so that both can be handled correctly. The version is kept separate from the magic number, instead of using different magic numbers for different formats, mainly because `/etc/magic' is not updated often. It might be better to have magic separated from internal format version identification. Follow a number of pointers to later tables in the file, allowing for the extension of the prefix part of MO files without having to recompile programs reading them. This might become useful for later inserting a few flag bits, indication about the charset used, new tables, or other things. Then, at offset O and offset T in the picture, two tables of string descriptors can be found. In both tables, each string descriptor uses two 32 bits integers, one for the string length, another for the offset of the string in the MO file, counting in bytes from the start of the file. The first table contains descriptors for the original strings, and is sorted so the original strings are in increasing lexicographical order. The second table contains descriptors for the translated strings, and is parallel to the first table:@- to find the corresponding translation one has to access the array slot in the second array with the same index. Having the original strings sorted enables the use of simple binary search, for when the MO file does not contain an hashing table, or for when it is not practical to use the hashing table provided in the MO file. This also has another advantage, as the empty string in a PO file GNU `gettext' is usually *translated* into some system information attached to that particular MO file, and the empty string necessarily becomes the first in both the original and translated tables, making the system information very easy to find. The size S of the hash table can be zero. In this case, the hash table itself is not contained in the MO file. Some people might prefer this because a precomputed hashing table takes disk space, and does not win *that* much speed. The hash table contains indices to the sorted array of strings in the MO file. Conflict resolution is done by double hashing. The precise hashing algorithm used is fairly dependent of GNU `gettext' code, and is not documented here. As for the strings themselves, they follow the hash file, and each is terminated with a , and this is not counted in the length which appears in the string descriptor. The `msgfmt' program has an option selecting the alignment for MO file strings. With this option, each string is separately aligned so it starts at an offset which is a multiple of the alignment value. On some RISC machines, a correct alignment will speed things up. Nothing prevents a MO file from having embedded s in strings. However, the program interface currently used already presumes that strings are terminated, so embedded s are somewhat useless. But MO file format is general enough so other interfaces would be later possible, if for example, we ever want to implement wide characters right in MO files, where bytes may accidently appear. This particular issue has been strongly debated in the GNU `gettext' development forum, and it is expectable that MO file format will evolve or change over time. It is even possible that many formats may later be supported concurrently. But surely, we have to start somewhere, and the MO file format described here is a good start. Nothing is cast in concrete, and the format may later evolve fairly easily, so we should feel comfortable with the current approach. byte +------------------------------------------+ 0 | magic number = 0x950412de | | | 4 | file format revision = 0 | | | 8 | number of strings | == N | | 12 | offset of table with original strings | == O | | 16 | offset of table with translation strings | == T | | 20 | size of hashing table | == S | | 24 | offset of hashing table | == H | | . . . (possibly more entries later) . . . | | O | length & offset 0th string ----------------. O + 8 | length & offset 1st string ------------------. ... ... | | O + ((N-1)*8)| length & offset (N-1)th string | | | | | | | T | length & offset 0th translation ---------------. T + 8 | length & offset 1st translation -----------------. ... ... | | | | T + ((N-1)*8)| length & offset (N-1)th translation | | | | | | | | | | | H | start hash table | | | | | ... ... | | | | H + S * 4 | end hash table | | | | | | | | | | | | NUL terminated 0th string <----------------' | | | | | | | | | NUL terminated 1st string <------------------' | | | | | | ... ... | | | | | | | NUL terminated 0th translation <---------------' | | | | | NUL terminated 1st translation <-----------------' | | ... ... | | +------------------------------------------+ Locating Message Catalog Files ------------------------------ Because many different languages for many different packages have to be stored we need some way to add these information to file message catalog files. The way usually used in Unix environments is have this encoding in the file name. This is also done here. The directory name given in `bindtextdomain's second argument (or the default directory), followed by the value and name of the locale and the domain name are concatenated:@- DIR_NAME/LOCALE/LC_CATEGORY/DOMAIN_NAME.mo The default value for DIR_NAME is system specific. For the GNU library, and for packages adhering to its conventions, it's:@- /usr/local/share/locale LOCALE is the value of the locale whose name is this `LC_CATEGORY'. For `gettext' and `dgettext' this locale is always `LC_MESSAGES'. @end table @node I18N.LcMessagesMoFileVersion0 class-plurals @subsection I18N.LcMessagesMoFileVersion0 class:@- plurals @table @b @meindex initialize @item initialize Initialize a table with the expressions computing the plurals for the most common languages @meindex pluralExpressionFor:@-ifAbsent:@- @item pluralExpressionFor:@- locale ifAbsent:@- aBlock Answer a RunTimeExpression yielding the plural form for the given language and territory, if one is known, else evaluate aBlock and answer it. @end table @node I18N.LcMessagesMoFileVersion0-flushing the cache @subsection I18N.LcMessagesMoFileVersion0:@- flushing the cache @table @b @meindex flush @item flush Flush the cache and reread the catalog's metadata. @meindex shouldCache @item shouldCache Answer true, we always cache translations if they are read from a file @end table @node I18N.LcMessagesTerritoryDomain @section I18N.LcMessagesTerritoryDomain @clindex I18N.LcMessagesTerritoryDomain @table @b @item Defined in namespace I18N @itemx Superclass: I18N.LcMessagesDomain @itemx Category: i18n-Messages This object asks for strings to a primary domain (e.g. it_IT) and a secondary one (e.g. it). @end table @menu * I18N.LcMessagesTerritoryDomain class-instance creation:: (class) @end menu @node I18N.LcMessagesTerritoryDomain class-instance creation @subsection I18N.LcMessagesTerritoryDomain class:@- instance creation @table @b @meindex primary:@-secondary:@- @item primary:@- domain1 secondary:@- domain2 Answer an instance of the receiver that queries, in sequence, domain1 and domain2 @end table @node I18N.LcMonetary @section I18N.LcMonetary @clindex I18N.LcMonetary @table @b @item Defined in namespace I18N @itemx Superclass: I18N.LcNumeric @itemx Category: i18n-Printing Sending either #?, #printString:@- or #print:@-on:@- converts a Number to a String according to the rules that are mandated by ISO for printing currency amounts in the current locale. @end table @menu * I18N.LcMonetary class-accessing:: (class) * I18N.LcMonetary-printing:: (instance) @end menu @node I18N.LcMonetary class-accessing @subsection I18N.LcMonetary class:@- accessing @table @b @meindex category @item category Answer the environment variable used to determine the default locale @meindex selector @item selector Answer the selector that accesses the receiver when sent to a Locale object. @end table @node I18N.LcMonetary-printing @subsection I18N.LcMonetary:@- printing @table @b @meindex print:@-on:@- @item print:@- aNumber on:@- aStream Print aNumber on aStream according to the receiver's formatting conventions. Always print a currency sign and don't force to print negative numbers by putting parentheses around them. @meindex print:@-on:@-currency:@-parentheses:@- @item print:@- aNumber on:@- aStream currency:@- currency parentheses:@- p Print aNumber on aStream according to the receiver's formatting conventions. If currency is true, print a currency sign, and if p is true force to print negative numbers by putting parentheses around them. If p is true, for positive numbers spaces are put around the number to keep them aligned. @end table @node I18N.LcMonetaryISO @section I18N.LcMonetaryISO @clindex I18N.LcMonetaryISO @table @b @item Defined in namespace I18N @itemx Superclass: I18N.LcMonetary @itemx Category: i18n-Printing @end table @menu * I18N.LcMonetaryISO class-accessing:: (class) @end menu @node I18N.LcMonetaryISO class-accessing @subsection I18N.LcMonetaryISO class:@- accessing @table @b @meindex selector @item selector Answer the selector that accesses the receiver when sent to a Locale object. @end table @node I18N.LcNumeric @section I18N.LcNumeric @clindex I18N.LcNumeric @table @b @item Defined in namespace I18N @itemx Superclass: I18N.LcPrintFormats @itemx Category: i18n-Printing Sending either #?, #printString:@- or #print:@-on:@- converts a Number to a String according to the rules that are used in the given locale. @end table @menu * I18N.LcNumeric class-accessing:: (class) * I18N.LcNumeric-printing:: (instance) @end menu @node I18N.LcNumeric class-accessing @subsection I18N.LcNumeric class:@- accessing @table @b @meindex category @item category Answer the environment variable used to determine the default locale @meindex selector @item selector Answer the selector that accesses the receiver when sent to a Locale object. @end table @node I18N.LcNumeric-printing @subsection I18N.LcNumeric:@- printing @table @b @meindex basicPrint:@-on:@- @item basicPrint:@- aNumber on:@- aStream Print aNumber on aStream according to the receiver's formatting conventions, without currency signs or anything like that. This method must not be overridden. @meindex print:@-on:@- @item print:@- aNumber on:@- aStream Print aNumber on aStream according to the receiver's formatting conventions. @end table @node I18N.LcPrintFormats @section I18N.LcPrintFormats @clindex I18N.LcPrintFormats @table @b @item Defined in namespace I18N @itemx Superclass: I18N.LocaleConventions @itemx Category: i18n-Messages LcPrintFormats subclasses have instances that understand #?, #printString:@- and #print:@-on:@- (the last of which is abstract) which provide a means to convert miscellaneous objects to Strings according to the rules that are used in the given locale. @end table @menu * I18N.LcPrintFormats-printing:: (instance) @end menu @node I18N.LcPrintFormats-printing @subsection I18N.LcPrintFormats:@- printing @table @b @meindex ? @item ? anObject Answer how anObject must be printed according to the receiver's formatting conventions. @meindex print:@-on:@- @item print:@- anObject on:@- aStream Print anObject on aStream according to the receiver's formatting conventions. @meindex printString:@- @item printString:@- anObject Answer how anObject must be printed according to the receiver's formatting conventions. @end table @node I18N.LcTime @section I18N.LcTime @clindex I18N.LcTime @table @b @item Defined in namespace I18N @itemx Superclass: I18N.LcPrintFormats @itemx Category: i18n-Printing Sending either #?, #printString:@- or #print:@-on:@- converts a Date or Time to a String according to the rules that are used in the given locale. @end table @menu * I18N.LcTime class-accessing:: (class) * I18N.LcTime-printing:: (instance) * I18N.LcTime-tests:: (instance) @end menu @node I18N.LcTime class-accessing @subsection I18N.LcTime class:@- accessing @table @b @meindex category @item category Answer the environment variable used to determine the default locale @meindex selector @item selector Answer the selector that accesses the receiver when sent to a Locale object. @end table @node I18N.LcTime-printing @subsection I18N.LcTime:@- printing @table @b @meindex print:@-on:@- @item print:@- aDateOrTimeOrArray on:@- aStream Print aDateOrTimeOrArray on aStream according to the receiver's formatting conventions. It can be a Date, Time, DateTime, or an array made of a Date and a Time @meindex print:@-on:@-ifFull:@-ifDate:@-ifTime:@- @slindex print:@-time:@-format:@-on:@- @item print:@- aDateOrTimeOrArray on:@- aStream ifFull:@- fullFmt ifDate:@- dateFmt ifTime:@- timeFmt Print aDateOrTimeOrArray on aStream according to the receiver's formatting conventions. It can be a Date, Time, DateTime, or an array made of a Date and a Time:@- Date is printed with dateFmt and Time with timeFmt, while in the other cases fullFmt is used. For information on the formatting codes, see #print:@-time:@-format:@-on:@-. @meindex print:@-time:@-format:@-on:@- @item print:@- aDate time:@- aTime format:@- aString on:@- aStream Print the specified date and time on aStream according to the receiver's formatting conventions, using the given format. The valid abbreviations are the same used by the C function strftime:@- abbreviated weekday (%a) weekday (%A) abbreviated month (%b) month (%B) date & time (%c) century (%C) day of the month (%d) date (US) (%D) day of the month (%e) year for the ISO week (%g) year for the ISO week (%G) abbreviated month (%h) hours (%H) hours (AM/PM) (%I) day of the year (%j) hours (%k) hours (AM/PM) (%l) month (%m) minutes (%M) AM/PM (%p) lowercase AM/PM (%P) AM/PM time (%r) time (US) (%R) time_t (%s) seconds (%S) time (US) (%T) day of the week (%u) week number starting at Sun (%U) week number starting at Thu (%V) day of the week, Sunday=0 (%w) week number starting at Mon (%W) date (%x) time (%X) year (2-digit) (%y) year (4-digit) (%Y). @end table @node I18N.LcTime-tests @subsection I18N.LcTime:@- tests @table @b @meindex allFormatsExample @item allFormatsExample Answer a long string that includes all the possible formats @end table @node I18N.Locale @section I18N.Locale @clindex I18N.Locale @table @b @item Defined in namespace I18N @itemx Superclass: I18N.LocaleData @itemx Category: i18n-Messages This object is an abstract superclass of objects related to the territory and language in which the program is being used. Instances of it are asked about information on the current locale, and provide a means to be asked for things with a common idiom, the #? binary message. @end table @menu * I18N.Locale class-C call-outs:: (class) * I18N.Locale class-initialization:: (class) * I18N.Locale class-instance creation:: (class) * I18N.Locale-C call-outs:: (instance) * I18N.Locale-subobjects:: (instance) @end menu @node I18N.Locale class-C call-outs @subsection I18N.Locale class:@- C call-outs @table @b @meindex primRootDirectory @item primRootDirectory Not commented. @end table @node I18N.Locale class-initialization @subsection I18N.Locale class:@- initialization @table @b @meindex rootDirectory @item rootDirectory Answer the directory under which locale definition files are found. @meindex rootDirectory:@- @item rootDirectory:@- aString Set under which directory locale definition files are found. @end table @node I18N.Locale class-instance creation @subsection I18N.Locale class:@- instance creation @table @b @meindex default @item default Answer an instance of the receiver that accesses the default locale. @meindex flush @item flush Flush the information on locales that are not valid across an image save/load. @meindex fromString:@- @item fromString:@- aString Answer an instance of the receiver that accesses the given locale (in the form language[_territory][.charset]). @meindex posix @item posix Answer an instance of the receiver that accesses the POSIX locale. @end table @node I18N.Locale-C call-outs @subsection I18N.Locale:@- C call-outs @table @b @meindex load:@- @item load:@- name Not commented. @end table @node I18N.Locale-subobjects @subsection I18N.Locale:@- subobjects @table @b @meindex messages @item messages Answer the LcMessages object for the locale represented by the receiver. @meindex monetary @item monetary Answer the LcMonetary object for the locale represented by the receiver. @meindex monetaryIso @item monetaryIso Answer the LcMonetaryISO object for the locale represented by the receiver. @meindex numeric @item numeric Answer the LcNumeric object for the locale represented by the receiver. @meindex time @item time Answer the LcTime object for the locale represented by the receiver. @end table @node I18N.LocaleConventions @section I18N.LocaleConventions @clindex I18N.LocaleConventions @table @b @item Defined in namespace I18N @itemx Superclass: I18N.LocaleData @itemx Category: i18n-Messages I am an abstract superclass of objects that are referred to by a Locale object. @end table @menu * I18N.LocaleConventions class-accessing:: (class) * I18N.LocaleConventions-accessing:: (instance) @end menu @node I18N.LocaleConventions class-accessing @subsection I18N.LocaleConventions class:@- accessing @table @b @meindex ? @item ? anObject Query the default object, forwarding the message to it. @meindex default @item default Answer an instance of the receiver that accesses the default locale. @meindex fromString:@- @item fromString:@- aString Answer an instance of the receiver that accesses the given locale (in the form language[_territory][.charset]). @meindex posix @item posix Answer an instance of the receiver that accesses the POSIX locale. @meindex selector @item selector This method's functionality should be implemented by subclasses of LocaleConventions @end table @node I18N.LocaleConventions-accessing @subsection I18N.LocaleConventions:@- accessing @table @b @meindex ? @item ? anObject This method's functionality should be implemented by subclasses of LocaleConventions @end table @node I18N.LocaleData @section I18N.LocaleData @clindex I18N.LocaleData @table @b @item Defined in namespace I18N @itemx Superclass: Object @itemx Category: i18n-Messages I am an abstract superclass of objects that represent localization information. @end table @menu * I18N.LocaleData class-accessing:: (class) * I18N.LocaleData class-database:: (class) * I18N.LocaleData-accessing:: (instance) * I18N.LocaleData-initialization:: (instance) @end menu @node I18N.LocaleData class-accessing @subsection I18N.LocaleData class:@- accessing @table @b @meindex category @item category Answer `nil'. @meindex default @item default This method's functionality should be implemented by subclasses of LocaleData @meindex flush @item flush Flush the contents of the instances of each subclass of LocaleData. @meindex fromString:@- @item fromString:@- lang This method's functionality should be implemented by subclasses of LocaleData @meindex language:@- @item language:@- lang Answer the local object for the given language. @meindex language:@-territory:@- @item language:@- lang territory:@- territory Answer the local object for the given language and territory. @meindex language:@-territory:@-charset:@- @item language:@- lang territory:@- territory charset:@- charset Answer the local object for the given language, territory and charset. @meindex new @item new This method should not be called for instances of this class. @meindex posix @item posix This method's functionality should be implemented by subclasses of LocaleData @meindex update:@- @item update:@- aspect Flush instances of the receiver when an image is loaded. @end table @node I18N.LocaleData class-database @subsection I18N.LocaleData class:@- database @table @b @meindex defaultCharset @item defaultCharset Answer the default charset used when nothing is specified. @meindex defaultCharset:@- @item defaultCharset:@- aString Set the default charset used when nothing is specified. @meindex defaults @item defaults Answer the default territory-language and language-charset associations. @meindex initialize @item initialize Initialize the receiver's class variables. @meindex languages @item languages ISO639 language codes @meindex territories @item territories ISO3166 territory codes @end table @node I18N.LocaleData-accessing @subsection I18N.LocaleData:@- accessing @table @b @meindex charset @item charset Return the charset supported by the receiver. @meindex id @item id Return the identifier of the locale supported by the receiver. @meindex isPosixLocale @item isPosixLocale Answer whether the receiver implements the default POSIX behavior for a locale. @meindex language @item language Return the language supported by the receiver. @meindex languageDirectory @item languageDirectory Answer the directory where data files for the current language reside. @meindex languageDirectory:@- @item languageDirectory:@- rootDirectory Answer the directory where data files for the current language reside, given the root directory of the locale data. @meindex territory @item territory Return the territory supported by the receiver. @meindex territoryDirectory @item territoryDirectory Answer the directory where data files for the current language, specific to the territory, reside. @meindex territoryDirectory:@- @item territoryDirectory:@- rootDirectory Answer the directory where data files for the current language, specific to the territory, reside, given the root directory of the locale data. @end table @node I18N.LocaleData-initialization @subsection I18N.LocaleData:@- initialization @table @b @meindex id:@- @item id:@- anArray Private - Set which locale the receiver contains data for @meindex initialize:@- @item initialize:@- aString Set which locale the receiver contains data for, starting from a string describing the locale. @end table @node I18N.RTEAlternativeNode @section I18N.RTEAlternativeNode @clindex I18N.RTEAlternativeNode @table @b @item Defined in namespace I18N @itemx Superclass: I18N.RunTimeExpression @itemx Category: i18n-Messages @end table @menu * I18N.RTEAlternativeNode class-compiling:: (class) * I18N.RTEAlternativeNode-computing:: (instance) @end menu @node I18N.RTEAlternativeNode class-compiling @subsection I18N.RTEAlternativeNode class:@- compiling @table @b @meindex condition:@-ifTrue:@-ifFalse:@- @item condition:@- cond ifTrue:@- trueNode ifFalse:@- falseNode Private - Create a node in the parse tree for the run-time expression, mapping s to a Smalltalk arithmetic selector @end table @node I18N.RTEAlternativeNode-computing @subsection I18N.RTEAlternativeNode:@- computing @table @b @meindex condition:@-ifTrue:@-ifFalse:@- @item condition:@- condNode ifTrue:@- trueNode ifFalse:@- falseNode Initialize the children of the receiver and the conditional expression to choose between them @meindex printOn:@- @item printOn:@- aStream Print a representation of the receiver on aStream @meindex send:@- @item send:@- parameter Evaluate the receiver by conditionally choosing one of its children and evaluating it @end table @node I18N.RTEBinaryNode @section I18N.RTEBinaryNode @clindex I18N.RTEBinaryNode @table @b @item Defined in namespace I18N @itemx Superclass: I18N.RunTimeExpression @itemx Category: i18n-Messages @end table @menu * I18N.RTEBinaryNode class-compiling:: (class) * I18N.RTEBinaryNode-compiling:: (instance) * I18N.RTEBinaryNode-computing:: (instance) @end menu @node I18N.RTEBinaryNode class-compiling @subsection I18N.RTEBinaryNode class:@- compiling @table @b @meindex lhs:@-op:@-rhs:@- @item lhs:@- lhs op:@- op rhs:@- rhs Private - Create a node in the parse tree for the run-time expression, mapping s to a Smalltalk arithmetic selector @end table @node I18N.RTEBinaryNode-compiling @subsection I18N.RTEBinaryNode:@- compiling @table @b @meindex lhs @item lhs Answer `lhs'. @meindex op @item op Answer `op'. @meindex rhs @item rhs Answer `rhs'. @end table @node I18N.RTEBinaryNode-computing @subsection I18N.RTEBinaryNode:@- computing @table @b @meindex lhs:@-op:@-rhs:@- @item lhs:@- lhsNode op:@- aSymbol rhs:@- rhsNode Initialize the children of the receiver and the operation to be done between them @meindex printOn:@- @item printOn:@- aStream Print a representation of the receiver on aStream @meindex send:@- @item send:@- parameter Private - Evaluate the receiver by evaluating both children and performing an arithmetic operation between them. @end table @node I18N.RTELiteralNode @section I18N.RTELiteralNode @clindex I18N.RTELiteralNode @table @b @item Defined in namespace I18N @itemx Superclass: I18N.RunTimeExpression @itemx Category: i18n-Messages @end table @menu * I18N.RTELiteralNode class-initializing:: (class) * I18N.RTELiteralNode-computing:: (instance) @end menu @node I18N.RTELiteralNode class-initializing @subsection I18N.RTELiteralNode class:@- initializing @table @b @meindex parseFrom:@- @item parseFrom:@- aStream Parse a literal number from aStream and return a new node @end table @node I18N.RTELiteralNode-computing @subsection I18N.RTELiteralNode:@- computing @table @b @meindex n:@- @item n:@- value Set the value of the literal that the node represents @meindex printOn:@- @item printOn:@- aStream Print a representation of the receiver on aStream @meindex send:@- @item send:@- parameter Answer a fixed value, the literal encoded in the node @end table @node I18N.RTENegationNode @section I18N.RTENegationNode @clindex I18N.RTENegationNode @table @b @item Defined in namespace I18N @itemx Superclass: I18N.RunTimeExpression @itemx Category: i18n-Messages @end table @menu * I18N.RTENegationNode class-initializing:: (class) * I18N.RTENegationNode-computing:: (instance) @end menu @node I18N.RTENegationNode class-initializing @subsection I18N.RTENegationNode class:@- initializing @table @b @meindex child:@- @item child:@- aNode Answer a new node representing the logical negation of aNode @end table @node I18N.RTENegationNode-computing @subsection I18N.RTENegationNode:@- computing @table @b @meindex child:@- @item child:@- value Set the child of which the receiver will compute the negation @meindex printOn:@- @item printOn:@- aStream Print a representation of the receiver on aStream @meindex send:@- @item send:@- parameter Evaluate the receiver by computing the child's logical negation @end table @node I18N.RTEParameterNode @section I18N.RTEParameterNode @clindex I18N.RTEParameterNode @table @b @item Defined in namespace I18N @itemx Superclass: I18N.RunTimeExpression @itemx Category: i18n-Messages @end table @menu * I18N.RTEParameterNode-computing:: (instance) @end menu @node I18N.RTEParameterNode-computing @subsection I18N.RTEParameterNode:@- computing @table @b @meindex printOn:@- @item printOn:@- aStream Print a representation of the receiver on aStream @meindex send:@- @item send:@- parameter Evaluate the receiver by answering the parameter @end table @node I18N.RunTimeExpression @section I18N.RunTimeExpression @clindex I18N.RunTimeExpression @table @b @item Defined in namespace I18N @itemx Superclass: Object @itemx Category: i18n-Messages @end table @menu * I18N.RunTimeExpression class-compiling:: (class) * I18N.RunTimeExpression class-initializing:: (class) * I18N.RunTimeExpression class-instance creation:: (class) * I18N.RunTimeExpression-computing:: (instance) @end menu @node I18N.RunTimeExpression class-compiling @subsection I18N.RunTimeExpression class:@- compiling @table @b @meindex parseExpression:@- @item parseExpression:@- stream Private - Compile the expression in the stream @meindex parseOperand:@- @item parseOperand:@- stream Parse an operand from the stream (i.e. an unary negation, a parenthesized subexpression, `n' or a number) and answer the corresponding parse node. @meindex parseOperator:@- @item parseOperator:@- stream Answer a Symbol for an operator read from stream, or nil if something else is found. @end table @node I18N.RunTimeExpression class-initializing @subsection I18N.RunTimeExpression class:@- initializing @table @b @meindex initialize @item initialize Private - Initialize internal tables for the parser @end table @node I18N.RunTimeExpression class-instance creation @subsection I18N.RunTimeExpression class:@- instance creation @table @b @meindex on:@- @item on:@- aString Compile aString and answer a RunTimeExpression @end table @node I18N.RunTimeExpression-computing @subsection I18N.RunTimeExpression:@- computing @table @b @meindex send:@- @item send:@- parameter This method's functionality should be implemented by subclasses of RunTimeExpression @meindex value:@- @item value:@- parameter Evaluate the receiver, and answer its value as an integer @end table smalltalk-3.2.5/doc/gst-libs.info-30000644000175000017500000067147412130456010013747 00000000000000This is gst-libs.info, produced by makeinfo version 4.13 from /home/ich/source/smalltalk/release/smalltalk/doc/gst-libs-fixed.texi. INFO-DIR-SECTION Software development START-INFO-DIR-ENTRY * Smalltalk libraries: (gst-libs). The GNU Smalltalk class libraries. END-INFO-DIR-ENTRY Permission is granted to copy, distribute and/or modify this document under the terms of the GNU Free Documentation License, Version 1.2 or any later version published by the Free Software Foundation; with no Invariant Sections, with no Front-Cover Texts, and with no Back-Cover Texts. A copy of the license is included in the section entitled "GNU Free Documentation License".  File: gst-libs.info, Node: Method index, Next: Cross-reference, Prev: Class index, Up: Top Method index ************ [index] * Menu: * *: Complex-math. (line 6) * +: Complex-math. (line 9) * -: Complex-math. (line 12) * /: Complex-math. (line 15) * <: Complex-comparing. (line 6) * <=: Complex-comparing. (line 9) * = <1>: Sockets.UnixAddress-accessing. (line 6) * = <2>: Sockets.SocketAddress-accessing. (line 6) * =: Complex-comparing. (line 12) * >: Complex-comparing. (line 15) * >=: Complex-comparing. (line 18) * >>: DBI.Connection-accessing. (line 6) * ? <1>: I18N.LocaleConventions-accessing. (line 6) * ? <2>: I18N.LocaleConventions class-accessing. (line 6) * ? <3>: I18N.LcPrintFormats-printing. (line 6) * ? <4>: I18N.LcMessagesDomain-querying. (line 6) * ?: I18N.LcMessages-opening MO files. (line 6) * abs: Complex-math. (line 18) * absSquared: Complex-math. (line 21) * accept: Sockets.ServerSocket-accessing. (line 6) * accept_ <1>: Sockets.ServerSocket-accessing. (line 10) * accept_: Sockets.AbstractSocketImpl-socket operations. (line 6) * accept_peer_addrLen_ <1>: Sockets.AbstractSocketImpl-C call-outs. (line 6) * accept_peer_addrLen_: Sockets.AbstractSocketImpl class-C call-outs. (line 6) * activate: BLOX.BWidget-widget protocol. (line 6) * activateNext: BLOX.BWidget-widget protocol. (line 22) * activatePrevious: BLOX.BWidget-widget protocol. (line 27) * active: BLOX.Blox class-utility. (line 6) * activeBackground: BLOX.BMenuObject-accessing. (line 6) * activeBackground_: BLOX.BMenuObject-accessing. (line 16) * activeForeground: BLOX.BMenuObject-accessing. (line 26) * activeForeground_: BLOX.BMenuObject-accessing. (line 32) * add_: BLOX.BMenuBar-accessing. (line 6) * add_afterIndex_ <1>: BLOX.BList-accessing. (line 6) * add_afterIndex_: BLOX.BDropDown-list box accessing. (line 6) * add_element_afterIndex_ <1>: BLOX.BList-accessing. (line 11) * add_element_afterIndex_: BLOX.BDropDown-list box accessing. (line 11) * addButton_receiver_index_: BLOX.BDialog-accessing. (line 6) * addButton_receiver_message_: BLOX.BDialog-accessing. (line 12) * addButton_receiver_message_argument_: BLOX.BDialog-accessing. (line 17) * addChild_ <1>: BLOX.BWidget-customization. (line 6) * addChild_ <2>: BLOX.BPopupWindow-geometry management. (line 6) * addChild_ <3>: BLOX.Blox-customization. (line 6) * addChild_: BLOX.BCanvas-geometry management. (line 6) * addEventSet_: BLOX.BEventTarget-intercepting events. (line 6) * addLast_ <1>: BLOX.BList-accessing. (line 23) * addLast_: BLOX.BDropDown-list box accessing. (line 23) * addLast_element_ <1>: BLOX.BList-accessing. (line 28) * addLast_element_: BLOX.BDropDown-list box accessing. (line 28) * addLine: BLOX.BMenu-callback registration. (line 6) * addMenuItemFor_notifying_: BLOX.BMenu-callback registration. (line 9) * address <1>: Sockets.StreamSocket-accessing. (line 6) * address <2>: Sockets.ServerSocket-accessing. (line 15) * address <3>: Sockets.DatagramSocket-accessing. (line 6) * address <4>: Sockets.Datagram-accessing. (line 6) * address: Sockets.AbstractSocket-accessing. (line 6) * address_: Sockets.Datagram-accessing. (line 9) * addressClass <1>: Sockets.IPAddress-accessing. (line 6) * addressClass: Sockets.AbstractSocketImpl class-abstract. (line 6) * addressFamily <1>: Sockets.UnixAddress class-C constants. (line 6) * addressFamily <2>: Sockets.SocketAddress class-C constants. (line 6) * addressFamily <3>: Sockets.IPAddress class-C constants. (line 6) * addressFamily: Sockets.IP6Address class-C constants. (line 6) * addressSize <1>: Sockets.IPAddress class-constants. (line 6) * addressSize: Sockets.IP6Address class-constants. (line 6) * aiAddr: Sockets.CAddrInfoStruct-C call-outs. (line 6) * aiAddrconfig: Sockets.SocketAddress class-C constants. (line 9) * aiAll: Sockets.IP6Address class-C constants. (line 9) * aiCanonname <1>: Sockets.SocketAddress class-C constants. (line 12) * aiCanonname: Sockets.CAddrInfoStruct-C call-outs. (line 9) * aiV4mapped: Sockets.IP6Address class-C constants. (line 12) * alignment: BLOX.BLabel-accessing. (line 6) * alignment_: BLOX.BLabel-accessing. (line 16) * allByName_: Sockets.SocketAddress class-host name lookup. (line 6) * allFormatsExample: I18N.LcTime-tests. (line 6) * anyLocalAddress: Sockets.SocketAddress class-accessing. (line 6) * anyLocalAddress_: Sockets.SocketAddress class-initialization. (line 6) * arcTan: Complex-transcendental functions. (line 6) * arcTan_: Complex-transcendental functions. (line 9) * arg: Complex-transcendental functions. (line 12) * asArray: DBI.Row-accessing. (line 6) * asByteArray <1>: Sockets.SocketAddress-accessing. (line 13) * asByteArray <2>: Sockets.IPAddress-accessing. (line 10) * asByteArray: Sockets.IP6Address-accessing. (line 6) * asDictionary: DBI.Row-accessing. (line 9) * asExactFraction: Complex-converting. (line 6) * asFloat: Complex-converting. (line 9) * asFloatD: Complex-converting. (line 12) * asFloatE: Complex-converting. (line 15) * asFloatQ: Complex-converting. (line 18) * asFraction: Complex-converting. (line 21) * asPrimitiveWidget <1>: BLOX.BPrimitive-accessing. (line 6) * asPrimitiveWidget <2>: BLOX.BMenuObject-accessing. (line 38) * asPrimitiveWidget <3>: BLOX.Blox-widget protocol. (line 6) * asPrimitiveWidget: BLOX.BExtended-accessing. (line 6) * associationAt_ <1>: BLOX.BList-accessing. (line 39) * associationAt_: BLOX.BDropDown-list box accessing. (line 39) * asString: I18N.EncodedString-accessing. (line 6) * asUnicodeString: I18N.EncodedString-accessing. (line 9) * at_ <1>: I18N.LcMessagesDomain-querying. (line 10) * at_ <2>: I18N.EncodedString-accessing. (line 12) * at_ <3>: DBI.Row-accessing. (line 12) * at_ <4>: BLOX.Blox class-utility. (line 10) * at_ <5>: BLOX.BList-accessing. (line 44) * at_ <6>: BLOX.BDropDown-list box accessing. (line 44) * at_: BLOX.BCanvas-widget protocol. (line 6) * at_cache_: Sockets.SocketAddress class-accessing. (line 9) * at_plural_with_: I18N.LcMessagesDomain-querying. (line 14) * at_put_ <1>: I18N.LcMessagesDomain-querying. (line 18) * at_put_: I18N.EncodedString-accessing. (line 15) * atEnd <1>: ZLib.ZlibReadStream-streaming. (line 6) * atEnd <2>: Sockets.StreamSocket-stream protocol. (line 6) * atEnd <3>: Sockets.ReadBuffer-buffer handling. (line 6) * atEnd <4>: Sockets.AbstractSocket-stream protocol. (line 6) * atEnd <5>: I18N.Encoder-stream operations. (line 6) * atEnd: DBI.ResultSet-cursor access. (line 6) * atEndOfInput: I18N.Encoder-stream operations. (line 11) * atIndex_: DBI.Row-accessing. (line 15) * atMouse: BLOX.Blox class-utility. (line 15) * available: Sockets.AbstractSocket-accessing. (line 11) * availableBytes <1>: Sockets.StreamSocket-stream protocol. (line 9) * availableBytes: Sockets.ReadBuffer-buffer handling. (line 9) * backgroundColor <1>: BLOX.BTextAttributes-setting attributes. (line 6) * backgroundColor <2>: BLOX.BText-accessing. (line 6) * backgroundColor <3>: BLOX.BProgress-accessing. (line 6) * backgroundColor <4>: BLOX.BMenuObject-accessing. (line 41) * backgroundColor <5>: BLOX.BList-accessing. (line 47) * backgroundColor <6>: BLOX.BLabel-accessing. (line 26) * backgroundColor <7>: BLOX.BImage-accessing. (line 6) * backgroundColor <8>: BLOX.BForm-accessing. (line 6) * backgroundColor <9>: BLOX.BEdit-accessing. (line 6) * backgroundColor <10>: BLOX.BDropDown-accessing. (line 6) * backgroundColor <11>: BLOX.BCanvas-accessing. (line 6) * backgroundColor: BLOX.BButton-accessing. (line 6) * backgroundColor_ <1>: BLOX.BTextAttributes-setting attributes. (line 13) * backgroundColor_ <2>: BLOX.BTextAttributes class-instance-creation shortcuts. (line 6) * backgroundColor_ <3>: BLOX.BText-accessing. (line 12) * backgroundColor_ <4>: BLOX.BProgress-accessing. (line 11) * backgroundColor_ <5>: BLOX.BMenuObject-accessing. (line 47) * backgroundColor_ <6>: BLOX.BList-accessing. (line 53) * backgroundColor_ <7>: BLOX.BLabel-accessing. (line 32) * backgroundColor_ <8>: BLOX.BImage-accessing. (line 12) * backgroundColor_ <9>: BLOX.BForm-accessing. (line 12) * backgroundColor_ <10>: BLOX.BEdit-accessing. (line 12) * backgroundColor_ <11>: BLOX.BDropDownList-accessing. (line 6) * backgroundColor_ <12>: BLOX.BDropDownEdit-accessing. (line 6) * backgroundColor_ <13>: BLOX.BDropDown-accessing. (line 15) * backgroundColor_ <14>: BLOX.BCanvas-accessing. (line 12) * backgroundColor_: BLOX.BButton-accessing. (line 12) * balloonDelayTime: BLOX.BBalloon class-accessing. (line 6) * balloonDelayTime_: BLOX.BBalloon class-accessing. (line 10) * basicAddChild_: BLOX.Blox-customization. (line 13) * basicPrint_on_: I18N.LcNumeric-printing. (line 6) * beep: BLOX.Blox class-utility. (line 20) * between_and_do_: BLOX.BCanvas-widget protocol. (line 10) * bind_to_addrLen_ <1>: Sockets.AbstractSocketImpl-C call-outs. (line 9) * bind_to_addrLen_: Sockets.AbstractSocketImpl class-C call-outs. (line 9) * bindTo_port_: Sockets.AbstractSocketImpl-socket operations. (line 11) * black <1>: BLOX.BTextAttributes-colors. (line 6) * black: BLOX.BTextAttributes class-instance-creation shortcuts. (line 10) * blank: BLOX.BImage-image management. (line 6) * blox <1>: BLOX.Gui-accessing. (line 6) * blox: BLOX.BCanvasObject-accessing. (line 6) * blox_: BLOX.Gui-accessing. (line 9) * blue <1>: BLOX.BTextAttributes-colors. (line 9) * blue: BLOX.BTextAttributes class-instance-creation shortcuts. (line 13) * borderWidth: BLOX.BWidget-accessing. (line 6) * borderWidth_: BLOX.BWidget-accessing. (line 15) * boundingBox <1>: BLOX.BWidget-geometry management. (line 6) * boundingBox <2>: BLOX.BPolyline-accessing. (line 6) * boundingBox <3>: BLOX.BCanvasObject-accessing. (line 9) * boundingBox <4>: BLOX.BCanvas-widget protocol. (line 15) * boundingBox: BLOX.BBoundingBox-accessing. (line 6) * boundingBox_: BLOX.BWidget-geometry management. (line 9) * bringToTop: BLOX.BWidget-widget protocol. (line 32) * bufferContents <1>: Sockets.StreamSocket-stream protocol. (line 13) * bufferContents: Sockets.ReadBuffer-buffer handling. (line 12) * bufferSize <1>: ZLib.ZlibStream class-accessing. (line 6) * bufferSize <2>: Sockets.DatagramSocketImpl-accessing. (line 6) * bufferSize: Sockets.DatagramSocket-accessing. (line 9) * bufferSize_ <1>: ZLib.ZlibStream class-accessing. (line 10) * bufferSize_ <2>: Sockets.DatagramSocketImpl-accessing. (line 9) * bufferSize_: Sockets.DatagramSocket-accessing. (line 12) * byName_: Sockets.SocketAddress class-host name lookup. (line 12) * callback <1>: BLOX.BWindow-accessing. (line 6) * callback <2>: BLOX.BText-accessing. (line 18) * callback <3>: BLOX.BMenuObject-callback. (line 6) * callback <4>: BLOX.BList-widget protocol. (line 6) * callback <5>: BLOX.BEdit-accessing. (line 18) * callback <6>: BLOX.BDropDown-callbacks. (line 6) * callback <7>: BLOX.BButtonLike-accessing. (line 6) * callback: BLOX.BButton-accessing. (line 18) * callback_message_ <1>: BLOX.BWindow-accessing. (line 10) * callback_message_ <2>: BLOX.BToggle-accessing. (line 6) * callback_message_ <3>: BLOX.BText-accessing. (line 22) * callback_message_ <4>: BLOX.BRadioButton-accessing. (line 6) * callback_message_ <5>: BLOX.BMenuObject-callback. (line 10) * callback_message_ <6>: BLOX.BList-widget protocol. (line 10) * callback_message_ <7>: BLOX.BEdit-accessing. (line 22) * callback_message_ <8>: BLOX.BDropDownList-callbacks. (line 6) * callback_message_ <9>: BLOX.BDropDown-callbacks. (line 10) * callback_message_ <10>: BLOX.BButtonLike-accessing. (line 10) * callback_message_: BLOX.BButton-accessing. (line 22) * callback_message_argument_: BLOX.BMenuObject-callback. (line 15) * callback_using_: BLOX.BMenu-callback registration. (line 17) * canRead <1>: Sockets.StreamSocket-stream protocol. (line 16) * canRead <2>: Sockets.OOBSocketImpl-implementation. (line 6) * canRead: Sockets.AbstractSocket-accessing. (line 15) * canWrite <1>: Sockets.Socket-stream protocol. (line 6) * canWrite: Sockets.AbstractSocket-accessing. (line 18) * cap <1>: BLOX.BPolyline-accessing. (line 9) * cap: BLOX.BLine-accessing. (line 6) * cap_ <1>: BLOX.BPolyline-accessing. (line 16) * cap_: BLOX.BLine-accessing. (line 11) * category <1>: I18N.LocaleData class-accessing. (line 6) * category <2>: I18N.LcTime class-accessing. (line 6) * category <3>: I18N.LcNumeric class-accessing. (line 6) * category <4>: I18N.LcMonetary class-accessing. (line 6) * category: I18N.LcMessages class-accessing. (line 6) * ceiling: Complex-converting. (line 24) * center <1>: BLOX.BWindow-widget protocol. (line 6) * center <2>: BLOX.BTextAttributes-setting attributes. (line 20) * center <3>: BLOX.BTextAttributes class-instance-creation shortcuts. (line 16) * center <4>: BLOX.BDialog-widget protocol. (line 6) * center: BLOX.BBoundingBox-accessing. (line 9) * center_extent_: BLOX.BBoundingBox-accessing. (line 12) * centerIn_ <1>: BLOX.BWindow-widget protocol. (line 9) * centerIn_: BLOX.BDialog-widget protocol. (line 9) * charset: I18N.LocaleData-accessing. (line 6) * charsInLine_: BLOX.BText-position & lines. (line 6) * checkPeriod: Sockets.AbstractSocket class-timed-out operations. (line 6) * checkPeriod_: Sockets.AbstractSocket class-timed-out operations. (line 11) * child_ <1>: I18N.RTENegationNode-computing. (line 6) * child_: I18N.RTENegationNode class-initializing. (line 6) * child_height_ <1>: BLOX.BWidget-geometry management. (line 12) * child_height_ <2>: BLOX.BText-geometry management. (line 6) * child_height_ <3>: BLOX.BPopupWindow-geometry management. (line 14) * child_height_: BLOX.BCanvas-geometry management. (line 13) * child_heightOffset_ <1>: BLOX.BWidget-geometry management. (line 23) * child_heightOffset_ <2>: BLOX.BText-geometry management. (line 9) * child_heightOffset_ <3>: BLOX.BPopupWindow-geometry management. (line 18) * child_heightOffset_: BLOX.BCanvas-geometry management. (line 16) * child_stretch_: BLOX.BWidget-geometry management. (line 33) * child_width_ <1>: BLOX.BWidget-geometry management. (line 40) * child_width_ <2>: BLOX.BText-geometry management. (line 13) * child_width_ <3>: BLOX.BPopupWindow-geometry management. (line 21) * child_width_: BLOX.BCanvas-geometry management. (line 19) * child_widthOffset_ <1>: BLOX.BWidget-geometry management. (line 51) * child_widthOffset_ <2>: BLOX.BText-geometry management. (line 16) * child_widthOffset_ <3>: BLOX.BPopupWindow-geometry management. (line 25) * child_widthOffset_: BLOX.BCanvas-geometry management. (line 22) * child_x_ <1>: BLOX.BWidget-geometry management. (line 61) * child_x_ <2>: BLOX.BText-geometry management. (line 20) * child_x_ <3>: BLOX.BPopupWindow-geometry management. (line 28) * child_x_: BLOX.BCanvas-geometry management. (line 25) * child_xOffset_ <1>: BLOX.BWidget-geometry management. (line 71) * child_xOffset_ <2>: BLOX.BText-geometry management. (line 24) * child_xOffset_ <3>: BLOX.BPopupWindow-geometry management. (line 32) * child_xOffset_: BLOX.BCanvas-geometry management. (line 29) * child_y_ <1>: BLOX.BWidget-geometry management. (line 81) * child_y_ <2>: BLOX.BText-geometry management. (line 27) * child_y_ <3>: BLOX.BPopupWindow-geometry management. (line 35) * child_y_: BLOX.BCanvas-geometry management. (line 32) * child_yOffset_ <1>: BLOX.BWidget-geometry management. (line 91) * child_yOffset_ <2>: BLOX.BText-geometry management. (line 31) * child_yOffset_ <3>: BLOX.BPopupWindow-geometry management. (line 39) * child_yOffset_: BLOX.BCanvas-geometry management. (line 36) * childrenCount: BLOX.Blox-widget protocol. (line 9) * childrenDo_: BLOX.Blox-widget protocol. (line 12) * chooseColor_label_default_: BLOX.BDialog class-prompters. (line 6) * chooseFileToOpen_label_default_defaultExtension_types_: BLOX.BDialog class-prompters. (line 14) * chooseFileToSave_label_default_defaultExtension_types_: BLOX.BDialog class-prompters. (line 42) * clearClipboard: BLOX.Blox class-utility. (line 23) * clipboard: BLOX.Blox class-utility. (line 26) * clipboard_: BLOX.Blox class-utility. (line 29) * close <1>: ZLib.ZlibWriteStream-streaming. (line 6) * close <2>: Sockets.WriteBuffer-buffer handling. (line 6) * close <3>: Sockets.UnixSocketImpl-socket operations. (line 6) * close <4>: Sockets.UnixDatagramSocketImpl-socket operations. (line 6) * close <5>: Sockets.StreamSocket-stream protocol. (line 20) * close <6>: Sockets.ReadBuffer-buffer handling. (line 15) * close <7>: Sockets.AbstractSocket-accessing. (line 21) * close: DBI.Connection-connecting. (line 6) * closed: BLOX.BPolyline-accessing. (line 23) * closed_: BLOX.BPolyline-accessing. (line 26) * coerce_: Complex-creation/coercion. (line 6) * color <1>: BLOX.BColorButton-accessing. (line 6) * color: BLOX.BCanvasObject-accessing. (line 12) * color_ <1>: BLOX.BColorButton-accessing. (line 9) * color_: BLOX.BCanvasObject-accessing. (line 15) * columnAt_ <1>: DBI.Table-accessing. (line 6) * columnAt_ <2>: DBI.Row-accessing. (line 19) * columnAt_: DBI.ResultSet-accessing. (line 6) * columnCount: DBI.Row-accessing. (line 22) * columnNames <1>: DBI.Table-accessing. (line 9) * columnNames <2>: DBI.Row-accessing. (line 25) * columnNames: DBI.ResultSet-accessing. (line 9) * columns <1>: DBI.Table-accessing. (line 12) * columns <2>: DBI.Row-accessing. (line 28) * columns: DBI.ResultSet-accessing. (line 12) * compressingTo_ <1>: ZLib.RawDeflateStream class-instance creation. (line 6) * compressingTo_ <2>: ZLib.GZipDeflateStream class-instance creation. (line 6) * compressingTo_: ZLib.DeflateStream class-instance creation. (line 6) * compressingTo_level_ <1>: ZLib.RawDeflateStream class-instance creation. (line 10) * compressingTo_level_ <2>: ZLib.GZipDeflateStream class-instance creation. (line 10) * compressingTo_level_: ZLib.DeflateStream class-instance creation. (line 10) * condition_ifTrue_ifFalse_ <1>: I18N.RTEAlternativeNode-computing. (line 6) * condition_ifTrue_ifFalse_: I18N.RTEAlternativeNode class-compiling. (line 6) * conjugate: Complex-math. (line 24) * connect_to_addrLen_ <1>: Sockets.AbstractSocketImpl-C call-outs. (line 12) * connect_to_addrLen_: Sockets.AbstractSocketImpl class-C call-outs. (line 12) * connect_user_password_: DBI.Connection class-connecting. (line 6) * connected: BLOX.BViewport-accessing. (line 6) * connectTo_port_ <1>: Sockets.SocketImpl-socket operations. (line 6) * connectTo_port_: Sockets.AbstractSocketImpl-accessing. (line 6) * contents <1>: ZLib.ZlibWriteStream-streaming. (line 11) * contents <2>: BLOX.BText-accessing. (line 27) * contents <3>: BLOX.BEdit-accessing. (line 27) * contents: BLOX.BDialog-accessing. (line 23) * contents_ <1>: BLOX.BText-accessing. (line 30) * contents_ <2>: BLOX.BList-accessing. (line 59) * contents_ <3>: BLOX.BEdit-accessing. (line 30) * contents_ <4>: BLOX.BDropDown-list box accessing. (line 47) * contents_: BLOX.BDialog-accessing. (line 27) * contents_elements_ <1>: BLOX.BList-accessing. (line 63) * contents_elements_: BLOX.BDropDown-list box accessing. (line 51) * continue: Debugger-stepping commands. (line 6) * copy: I18N.EncodedString-copying. (line 6) * copyEmpty: I18N.EncodedString-copying. (line 9) * copyEmpty_: I18N.EncodedString-copying. (line 12) * copyFrom_to_: ZLib.RawInflateStream-positioning. (line 6) * copyInto_ <1>: BLOX.BEmbeddedImage-accessing. (line 6) * copyInto_: BLOX.BCanvasObject-accessing. (line 18) * copyObject: BLOX.BCanvasObject-accessing. (line 23) * corner: BLOX.BBoundingBox-accessing. (line 18) * corner_: BLOX.BBoundingBox-accessing. (line 21) * cos: Complex-transcendental functions. (line 15) * cosh: Complex-transcendental functions. (line 18) * create <1>: BLOX.BWidget-customization. (line 13) * create <2>: BLOX.BExtended-customization. (line 6) * create: BLOX.BCanvasObject-widget protocol. (line 6) * create_type_protocol_ <1>: Sockets.AbstractSocketImpl-C call-outs. (line 15) * create_type_protocol_: Sockets.AbstractSocketImpl class-C call-outs. (line 15) * createColor_green_blue_: BLOX.Blox class-utility. (line 33) * createColor_magenta_yellow_: BLOX.Blox class-utility. (line 38) * createColor_magenta_yellow_black_: BLOX.Blox class-utility. (line 43) * createColor_saturation_value_: BLOX.Blox class-utility. (line 48) * createCopy: BLOX.BCanvasObject-accessing. (line 30) * createCopyInto_: BLOX.BCanvasObject-accessing. (line 37) * created: BLOX.BCanvasObject-widget protocol. (line 10) * createList: BLOX.BDropDown-flexibility. (line 6) * createLoopbackHost <1>: Sockets.UnixAddress class-initialization. (line 6) * createLoopbackHost <2>: Sockets.SocketAddress class-initialization. (line 10) * createLoopbackHost <3>: Sockets.IPAddress class-initialization. (line 6) * createLoopbackHost: Sockets.IP6Address class-initialization. (line 6) * createTextWidget: BLOX.BDropDown-flexibility. (line 11) * createUnknownAddress <1>: Sockets.UnixAddress class-initialization. (line 10) * createUnknownAddress <2>: Sockets.SocketAddress class-initialization. (line 14) * createUnknownAddress <3>: Sockets.IPAddress class-initialization. (line 10) * createUnknownAddress: Sockets.IP6Address class-initialization. (line 10) * currentColumn: BLOX.BText-position & lines. (line 9) * currentLine <1>: Debugger-inferior process properties. (line 6) * currentLine: BLOX.BText-position & lines. (line 13) * currentLineIn_: Debugger class-source code. (line 6) * currentPosition: BLOX.BText-position & lines. (line 17) * currentPosition_: BLOX.BText-position & lines. (line 23) * cursor: BLOX.BWidget-accessing. (line 24) * cursor_: BLOX.BWidget-accessing. (line 31) * cyan <1>: BLOX.BTextAttributes-colors. (line 12) * cyan: BLOX.BTextAttributes class-instance-creation shortcuts. (line 20) * darkCyan <1>: BLOX.BTextAttributes-colors. (line 15) * darkCyan: BLOX.BTextAttributes class-instance-creation shortcuts. (line 23) * darkGreen <1>: BLOX.BTextAttributes-colors. (line 18) * darkGreen: BLOX.BTextAttributes class-instance-creation shortcuts. (line 26) * darkMagenta <1>: BLOX.BTextAttributes-colors. (line 21) * darkMagenta: BLOX.BTextAttributes class-instance-creation shortcuts. (line 29) * data <1>: Sockets.Datagram-accessing. (line 12) * data: BLOX.BEmbeddedImage-accessing. (line 11) * data_ <1>: Sockets.Datagram-accessing. (line 15) * data_ <2>: Sockets.Datagram class-instance creation. (line 6) * data_ <3>: BLOX.BImage-image management. (line 9) * data_: BLOX.BEmbeddedImage-accessing. (line 16) * data_address_port_: Sockets.Datagram class-instance creation. (line 9) * database <1>: DBI.Table-accessing. (line 15) * database: DBI.Connection-accessing. (line 9) * datagramClass <1>: Sockets.DatagramSocketImpl class-parameters. (line 6) * datagramClass: Sockets.DatagramSocket-accessing. (line 15) * datagramLoopbackTest: Sockets.Socket class-tests. (line 6) * datagramLoopbackTestOn_: Sockets.Socket class-tests. (line 11) * dataSize: Sockets.Datagram-accessing. (line 18) * dataSize_: Sockets.Datagram-accessing. (line 21) * debuggerClass: Debugger class-disabling debugging. (line 6) * deepCopy <1>: BLOX.Blox-basic. (line 6) * deepCopy: BLOX.BCanvasObject-accessing. (line 42) * default <1>: I18N.LocaleData class-accessing. (line 9) * default <2>: I18N.LocaleConventions class-accessing. (line 9) * default: I18N.Locale class-instance creation. (line 6) * defaultAddressClass: Sockets.AbstractSocket class-defaults. (line 6) * defaultAddressClass_: Sockets.AbstractSocket class-defaults. (line 11) * defaultBufferSize: Sockets.DatagramSocket class-accessing. (line 6) * defaultBufferSize_: Sockets.DatagramSocket class-accessing. (line 9) * defaultCharset: I18N.LocaleData class-database. (line 6) * defaultCharset_: I18N.LocaleData class-database. (line 9) * defaultCompressionLevel: ZLib.ZlibStream class-accessing. (line 14) * defaultCompressionLevel_: ZLib.ZlibStream class-accessing. (line 17) * defaultDatagramSocketImplClass: Sockets.SocketAddress class-accessing. (line 14) * defaultDatagramSocketImplClass_: Sockets.SocketAddress class-accessing. (line 18) * defaultFont: BLOX.Blox class-utility. (line 53) * defaultHeight: BLOX.BForm-accessing. (line 18) * defaultHeight_: BLOX.BForm-accessing. (line 25) * defaultImplementationClassFor_ <1>: Sockets.StreamSocket class-accessing. (line 6) * defaultImplementationClassFor_ <2>: Sockets.ServerSocket class-accessing. (line 6) * defaultImplementationClassFor_ <3>: Sockets.DatagramSocket class-accessing. (line 12) * defaultImplementationClassFor_: Sockets.AbstractSocket class-defaults. (line 16) * defaultPortAt_: Sockets.AbstractSocket class-well known ports. (line 6) * defaultPortAt_ifAbsent_: Sockets.AbstractSocket class-well known ports. (line 10) * defaultPortAt_put_: Sockets.AbstractSocket class-well known ports. (line 14) * defaultQueueSize: Sockets.ServerSocket class-instance creation. (line 6) * defaultRawSocketImplClass: Sockets.SocketAddress class-accessing. (line 22) * defaultRawSocketImplClass_: Sockets.SocketAddress class-accessing. (line 26) * defaults: I18N.LocaleData class-database. (line 12) * defaultStreamSocketImplClass: Sockets.SocketAddress class-accessing. (line 30) * defaultStreamSocketImplClass_: Sockets.SocketAddress class-accessing. (line 34) * defaultWidth: BLOX.BForm-accessing. (line 32) * defaultWidth_: BLOX.BForm-accessing. (line 39) * description <1>: I18N.InvalidSequenceError-accessing. (line 6) * description <2>: I18N.InvalidCharsetError-accessing. (line 6) * description: I18N.IncompleteSequenceError-accessing. (line 6) * destroy <1>: BLOX.BMenu-callback registration. (line 23) * destroy: BLOX.Blox-widget protocol. (line 16) * destroyed <1>: BLOX.BRadioGroup-widget protocol. (line 6) * destroyed <2>: BLOX.BImage-widget protocol. (line 6) * destroyed <3>: BLOX.BEdit-widget protocol. (line 6) * destroyed <4>: BLOX.BDialog-widget protocol. (line 12) * destroyed: BLOX.BCanvas-widget protocol. (line 18) * directory: BLOX.BImage class-small icons. (line 6) * dispatchEvents: BLOX.Blox class-event dispatching. (line 6) * dispatchEvents_: BLOX.Blox class-event dispatching. (line 12) * displayHeight: BLOX.BImage-accessing. (line 18) * displayHeight_: BLOX.BImage-accessing. (line 25) * displayOn_ <1>: I18N.EncodedString-printing. (line 6) * displayOn_: DBI.ColumnInfo-printing. (line 6) * displayWidth: BLOX.BImage-accessing. (line 32) * displayWidth_: BLOX.BImage-accessing. (line 39) * dither: BLOX.BImage-image management. (line 13) * do_ <1>: I18N.EncodedString-accessing. (line 18) * do_ <2>: DBI.Connection-querying. (line 6) * do_ <3>: BLOX.BList-accessing. (line 68) * do_ <4>: BLOX.BDropDown-list box accessing. (line 56) * do_: BLOX.BCanvas-widget protocol. (line 22) * domain_: I18N.LcMessages-opening MO files. (line 11) * domain_localeDirectory_: I18N.LcMessages-opening MO files. (line 16) * downArrow: BLOX.BImage class-arrows. (line 6) * drawingArea: BLOX.Blox-widget protocol. (line 19) * driver: DBI.ConnectionInfo-accessing. (line 6) * driver_: DBI.ConnectionInfo-accessing. (line 9) * dropdown: BLOX.BDropDown-widget protocol. (line 14) * droppedRows: BLOX.BDropDown-accessing. (line 24) * droppedRows_: BLOX.BDropDown-accessing. (line 28) * dropRectangle: BLOX.BDropDown-widget protocol. (line 6) * effect: BLOX.BWidget-accessing. (line 38) * effect_: BLOX.BWidget-accessing. (line 51) * elements: BLOX.BList-accessing. (line 71) * elements_ <1>: BLOX.BList-accessing. (line 75) * elements_: BLOX.BDropDown-list box accessing. (line 59) * emacsLike: BLOX.BText class-accessing. (line 6) * emacsLike_: BLOX.BText class-accessing. (line 9) * empty <1>: BLOX.BMenu-callback registration. (line 27) * empty: BLOX.BCanvas-widget protocol. (line 25) * enabled: BLOX.Blox-widget protocol. (line 26) * enabled_: BLOX.Blox-widget protocol. (line 31) * encoding <1>: I18N.EncodedStringFactory-instance creation. (line 6) * encoding: I18N.EncodedString-accessing. (line 21) * encoding_ <1>: I18N.EncodedStringFactory-instance creation. (line 9) * encoding_ <2>: I18N.EncodedStringFactory class-instance creation. (line 6) * encoding_ <3>: I18N.EncodedString-initializing. (line 6) * encoding_: I18N.EncodedStream class-instance creation. (line 6) * encoding_as_: I18N.EncodedStream class-instance creation. (line 11) * endAngle: BLOX.BArc-accessing. (line 6) * endAngle_: BLOX.BArc-accessing. (line 10) * ensureReadable <1>: Sockets.OOBSocketImpl-implementation. (line 9) * ensureReadable: Sockets.AbstractSocketImpl-asynchronous operations. (line 6) * ensureWriteable <1>: Sockets.Socket-stream protocol. (line 10) * ensureWriteable: Sockets.AbstractSocketImpl-asynchronous operations. (line 10) * evalIn_tcl_: BLOX.Blox class-C call-outs. (line 6) * events: BLOX.BTextAttributes-setting attributes. (line 23) * events_ <1>: BLOX.BTextAttributes-setting attributes. (line 27) * events_: BLOX.BTextAttributes class-instance-creation shortcuts. (line 32) * exclaim: BLOX.BImage class-icons. (line 6) * execute: DBI.Statement-querying. (line 6) * executeWith_: DBI.Statement-querying. (line 9) * executeWith_with_: DBI.Statement-querying. (line 12) * executeWith_with_with_: DBI.Statement-querying. (line 15) * executeWithAll_: DBI.Statement-querying. (line 18) * exists: BLOX.Blox-widget protocol. (line 36) * exp: Complex-transcendental functions. (line 21) * extent <1>: BLOX.BWidget-geometry management. (line 101) * extent: BLOX.BBoundingBox-accessing. (line 27) * extent_ <1>: BLOX.BWidget-geometry management. (line 104) * extent_: BLOX.BBoundingBox-accessing. (line 30) * extractFromSockAddr_port_: Sockets.SocketAddress class-abstract. (line 6) * extraSpace: BLOX.BCanvas-widget protocol. (line 28) * extraSpace_: BLOX.BCanvas-widget protocol. (line 32) * fetch: DBI.ResultSet-cursor access. (line 10) * fieldConverter: DBI.Connection-accessing. (line 13) * file: BLOX.BImage class-small icons. (line 9) * fileFormatDescription: I18N.LcMessagesMoFileVersion0 class-documentation. (line 6) * fileName: I18N.FileStreamSegment-basic. (line 6) * fileOp_: Sockets.AbstractSocketImpl-socket operations. (line 15) * fileOp_ifFail_: Sockets.AbstractSocketImpl-socket operations. (line 19) * fileOp_with_: Sockets.AbstractSocketImpl-socket operations. (line 23) * fileOp_with_ifFail_: Sockets.AbstractSocketImpl-socket operations. (line 27) * fileOp_with_with_: Sockets.AbstractSocketImpl-socket operations. (line 31) * fileOp_with_with_ifFail_: Sockets.AbstractSocketImpl-socket operations. (line 35) * fileOp_with_with_with_: Sockets.AbstractSocketImpl-socket operations. (line 39) * fileOp_with_with_with_ifFail_: Sockets.AbstractSocketImpl-socket operations. (line 43) * fill <1>: Sockets.StreamSocket-stream protocol. (line 23) * fill: Sockets.ReadBuffer-buffer handling. (line 18) * fillBlock_: Sockets.ReadBuffer-buffer handling. (line 22) * fillChord: BLOX.BArc-accessing. (line 14) * filledColor: BLOX.BProgress-accessing. (line 16) * filledColor_: BLOX.BProgress-accessing. (line 19) * fillFrom_extent_color_: BLOX.BImage-image management. (line 22) * fillFrom_to_color_: BLOX.BImage-image management. (line 26) * fillRectangle_color_: BLOX.BImage-image management. (line 29) * fillSlice: BLOX.BArc-accessing. (line 18) * finish <1>: ZLib.ZlibWriteStream-streaming. (line 16) * finish: Debugger-stepping commands. (line 10) * finish_: Debugger-stepping commands. (line 13) * floor: Complex-converting. (line 27) * flush <1>: ZLib.ZlibWriteStream-streaming. (line 20) * flush <2>: Sockets.WriteBuffer-buffer handling. (line 9) * flush <3>: Sockets.SocketAddress class-initialization. (line 18) * flush <4>: Sockets.Socket-stream protocol. (line 14) * flush <5>: Sockets.AbstractSocket-accessing. (line 24) * flush <6>: I18N.LocaleData class-accessing. (line 13) * flush <7>: I18N.Locale class-instance creation. (line 10) * flush <8>: I18N.LcMessagesMoFileVersion0-flushing the cache. (line 6) * flush: I18N.LcMessagesDomain-handling the cache. (line 6) * flushBlock_: Sockets.WriteBuffer-buffer handling. (line 12) * flushBuffer: ZLib.ZlibWriteStream-streaming. (line 24) * flushDictionary: ZLib.ZlibWriteStream-streaming. (line 27) * font <1>: BLOX.BTextAttributes-setting attributes. (line 31) * font <2>: BLOX.BText-accessing. (line 33) * font <3>: BLOX.BList-accessing. (line 79) * font <4>: BLOX.BLabel-accessing. (line 38) * font <5>: BLOX.BEmbeddedText-accessing. (line 6) * font <6>: BLOX.BEdit-accessing. (line 33) * font <7>: BLOX.BDropDown-accessing. (line 32) * font: BLOX.BButton-accessing. (line 27) * font_ <1>: BLOX.BTextAttributes-setting attributes. (line 52) * font_ <2>: BLOX.BTextAttributes class-instance-creation shortcuts. (line 36) * font_ <3>: BLOX.BText-accessing. (line 56) * font_ <4>: BLOX.BList-accessing. (line 102) * font_ <5>: BLOX.BLabel-accessing. (line 61) * font_ <6>: BLOX.BEmbeddedText-accessing. (line 29) * font_ <7>: BLOX.BEdit-accessing. (line 56) * font_ <8>: BLOX.BDropDownList-accessing. (line 14) * font_ <9>: BLOX.BDropDownEdit-accessing. (line 12) * font_ <10>: BLOX.BDropDown-accessing. (line 58) * font_: BLOX.BButton-accessing. (line 50) * fontHeight_: BLOX.Blox-widget protocol. (line 40) * fonts: BLOX.Blox class-utility. (line 56) * fontWidth_: BLOX.Blox-widget protocol. (line 45) * foregroundColor <1>: BLOX.BTextAttributes-setting attributes. (line 73) * foregroundColor <2>: BLOX.BText-accessing. (line 79) * foregroundColor <3>: BLOX.BProgress-accessing. (line 22) * foregroundColor <4>: BLOX.BMenuObject-accessing. (line 53) * foregroundColor <5>: BLOX.BList-accessing. (line 125) * foregroundColor <6>: BLOX.BLabel-accessing. (line 84) * foregroundColor <7>: BLOX.BImage-accessing. (line 46) * foregroundColor <8>: BLOX.BEdit-accessing. (line 79) * foregroundColor <9>: BLOX.BDropDown-accessing. (line 84) * foregroundColor <10>: BLOX.BCanvas-accessing. (line 18) * foregroundColor: BLOX.BButton-accessing. (line 73) * foregroundColor_ <1>: BLOX.BTextAttributes-setting attributes. (line 80) * foregroundColor_ <2>: BLOX.BTextAttributes class-instance-creation shortcuts. (line 57) * foregroundColor_ <3>: BLOX.BText-accessing. (line 85) * foregroundColor_ <4>: BLOX.BProgress-accessing. (line 27) * foregroundColor_ <5>: BLOX.BMenuObject-accessing. (line 59) * foregroundColor_ <6>: BLOX.BList-accessing. (line 131) * foregroundColor_ <7>: BLOX.BLabel-accessing. (line 90) * foregroundColor_ <8>: BLOX.BImage-accessing. (line 52) * foregroundColor_ <9>: BLOX.BEdit-accessing. (line 85) * foregroundColor_ <10>: BLOX.BDropDownList-accessing. (line 37) * foregroundColor_ <11>: BLOX.BDropDownEdit-accessing. (line 35) * foregroundColor_ <12>: BLOX.BDropDown-accessing. (line 93) * foregroundColor_ <13>: BLOX.BCanvas-accessing. (line 24) * foregroundColor_: BLOX.BButton-accessing. (line 79) * free: Sockets.CAddrInfoStruct-C call-outs. (line 12) * from: BLOX.BArc-accessing. (line 23) * from_: BLOX.BArc-accessing. (line 26) * from_to_: BLOX.BArc-accessing. (line 29) * fromArray_ <1>: Sockets.IPAddress class-instance creation. (line 6) * fromArray_: Sockets.IP6Address class-instance creation. (line 6) * fromBytes_ <1>: Sockets.IPAddress class-instance creation. (line 11) * fromBytes_: Sockets.IP6Address class-instance creation. (line 11) * fromDSN_: DBI.ConnectionInfo class-instance creation. (line 6) * fromSockAddr_port_ <1>: Sockets.UnixAddress class-instance creation. (line 6) * fromSockAddr_port_ <2>: Sockets.SocketAddress class-abstract. (line 11) * fromSockAddr_port_ <3>: Sockets.IPAddress class-instance creation. (line 16) * fromSockAddr_port_: Sockets.IP6Address class-instance creation. (line 16) * fromString_ <1>: Sockets.IPAddress class-instance creation. (line 21) * fromString_ <2>: Sockets.IP6Address class-instance creation. (line 21) * fromString_ <3>: I18N.LocaleData class-accessing. (line 16) * fromString_ <4>: I18N.LocaleConventions class-accessing. (line 13) * fromString_ <5>: I18N.Locale class-instance creation. (line 14) * fromString_ <6>: I18N.EncodedStringFactory-instance creation. (line 12) * fromString_: I18N.EncodedString class-instance creation. (line 6) * fromString_encoding_: I18N.EncodedString class-instance creation. (line 9) * gamma: BLOX.BImage-accessing. (line 58) * gamma_: BLOX.BImage-accessing. (line 70) * generality: Complex-creation/coercion. (line 9) * get: Sockets.Datagram-accessing. (line 24) * getaddrinfo_: Sockets.CAddrInfoStruct-C function wrappers. (line 6) * getaddrinfo_service_: Sockets.CAddrInfoStruct-C function wrappers. (line 9) * getaddrinfo_service_hints_result_: Sockets.CAddrInfoStruct class-C call-outs. (line 6) * getPeerName: Sockets.SocketImpl-socket operations. (line 10) * getPeerName_addr_addrLen_ <1>: Sockets.AbstractSocketImpl-C call-outs. (line 18) * getPeerName_addr_addrLen_: Sockets.AbstractSocketImpl class-C call-outs. (line 18) * getSelection: BLOX.BText-accessing. (line 91) * getSockName: Sockets.AbstractSocketImpl-socket operations. (line 47) * getSockName_addr_addrLen_ <1>: Sockets.AbstractSocketImpl-C call-outs. (line 21) * getSockName_addr_addrLen_: Sockets.AbstractSocketImpl class-C call-outs. (line 21) * getThrough_: Sockets.Datagram-accessing. (line 29) * gnu: BLOX.BImage class-GNU. (line 6) * gotoLine_end_: BLOX.BText-position & lines. (line 29) * grayOut: BLOX.BCanvasObject-accessing. (line 46) * green <1>: BLOX.BTextAttributes-colors. (line 24) * green: BLOX.BTextAttributes class-instance-creation shortcuts. (line 61) * hash <1>: Sockets.UnixAddress-accessing. (line 10) * hash <2>: Sockets.SocketAddress-accessing. (line 17) * hash <3>: I18N.EncodedString-accessing. (line 24) * hash: Complex-comparing. (line 21) * hasSelection: BLOX.BEdit-widget protocol. (line 10) * height <1>: BLOX.BWindow-widget protocol. (line 12) * height: BLOX.BWidget-geometry management. (line 108) * height_ <1>: BLOX.BWindow-widget protocol. (line 16) * height_: BLOX.BWidget-geometry management. (line 120) * heightAbsolute <1>: BLOX.BWindow-widget protocol. (line 19) * heightAbsolute: BLOX.BWidget-geometry management. (line 127) * heightChild_ <1>: BLOX.BWidget-geometry management. (line 131) * heightChild_ <2>: BLOX.BText-geometry management. (line 34) * heightChild_ <3>: BLOX.BPopupWindow-geometry management. (line 42) * heightChild_: BLOX.BCanvas-geometry management. (line 39) * heightOffset: BLOX.BWidget-geometry management. (line 141) * heightOffset_ <1>: BLOX.BWindow-widget protocol. (line 23) * heightOffset_: BLOX.BWidget-geometry management. (line 146) * heightPixels_: BLOX.BWidget-geometry management. (line 152) * highlight_: BLOX.BList-widget protocol. (line 18) * highlightBackground <1>: BLOX.BList-accessing. (line 137) * highlightBackground: BLOX.BDropDown-accessing. (line 102) * highlightBackground_ <1>: BLOX.BList-accessing. (line 143) * highlightBackground_ <2>: BLOX.BDropDownList-accessing. (line 45) * highlightBackground_ <3>: BLOX.BDropDownEdit-accessing. (line 41) * highlightBackground_: BLOX.BDropDown-accessing. (line 108) * highlightForeground <1>: BLOX.BList-accessing. (line 149) * highlightForeground: BLOX.BDropDown-accessing. (line 114) * highlightForeground_ <1>: BLOX.BList-accessing. (line 155) * highlightForeground_ <2>: BLOX.BDropDownList-accessing. (line 52) * highlightForeground_ <3>: BLOX.BDropDownEdit-accessing. (line 47) * highlightForeground_: BLOX.BDropDown-accessing. (line 120) * horizontal: BLOX.BViewport-scrollbars. (line 6) * horizontal_: BLOX.BViewport-scrollbars. (line 10) * horizontalNeeded: BLOX.BViewport-scrollbars. (line 14) * horizontalShown: BLOX.BViewport-scrollbars. (line 18) * host: Sockets.IPAddress-accessing. (line 14) * i <1>: Complex-creation/coercion. (line 12) * i: Complex class-instance creation. (line 6) * iconify: BLOX.BWindow-widget protocol. (line 26) * id: I18N.LocaleData-accessing. (line 9) * id_: I18N.LocaleData-initialization. (line 6) * id_on_: I18N.LcMessagesDomain class-opening MO files. (line 6) * idle: BLOX.Blox class-C call-outs. (line 9) * image_: BLOX.BImage-image management. (line 33) * imageHeight: BLOX.BImage-image management. (line 37) * imageWidth: BLOX.BImage-image management. (line 44) * imaginary: Complex-creation/coercion. (line 15) * index <1>: DBI.ColumnInfo-accessing. (line 6) * index <2>: BLOX.BList-accessing. (line 161) * index: BLOX.BDropDownList-list box accessing. (line 6) * index_: BLOX.BDropDown-list box accessing. (line 63) * indexAt_ <1>: BLOX.BText-position & lines. (line 35) * indexAt_: BLOX.BList-accessing. (line 168) * info: BLOX.BImage class-icons. (line 9) * initialize <1>: Sockets.UnixAddress class-initialization. (line 14) * initialize <2>: Sockets.StreamSocket class-initialize. (line 6) * initialize <3>: Sockets.Socket class-well known ports. (line 6) * initialize <4>: Sockets.IPAddress class-initialization. (line 14) * initialize <5>: Sockets.IP6Address class-initialization. (line 14) * initialize <6>: Sockets.DatagramSocket class-initialization. (line 6) * initialize <7>: I18N.RunTimeExpression class-initializing. (line 6) * initialize <8>: I18N.LocaleData class-database. (line 16) * initialize <9>: I18N.LcMessagesMoFileVersion0 class-plurals. (line 6) * initialize <10>: I18N.EncodedStream class-initializing. (line 6) * initialize <11>: Complex class-instance creation. (line 9) * initialize: BLOX.BLabel class-initialization. (line 6) * initialize_ <1>: I18N.LocaleData-initialization. (line 9) * initialize_ <2>: BLOX.BWidget-customization. (line 20) * initialize_ <3>: BLOX.BEventSet-initializing. (line 6) * initialize_: BLOX.BBalloon-initializing. (line 6) * initLocalAddresses: Sockets.SocketAddress class-initialization. (line 21) * insertAtEnd_ <1>: BLOX.BText-inserting text. (line 6) * insertAtEnd_ <2>: BLOX.BEdit-widget protocol. (line 13) * insertAtEnd_: BLOX.BDropDownEdit-text accessing. (line 6) * insertAtEnd_attribute_: BLOX.BText-attributes. (line 6) * insertImage_: BLOX.BText-images. (line 6) * insertImage_at_: BLOX.BText-images. (line 12) * insertImageAtEnd_: BLOX.BText-images. (line 22) * insertSelectedText_: BLOX.BText-inserting text. (line 9) * insertText_ <1>: BLOX.BText-inserting text. (line 14) * insertText_: BLOX.BEdit-widget protocol. (line 16) * insertText_at_: BLOX.BText-inserting text. (line 18) * insertText_attribute_: BLOX.BText-attributes. (line 10) * insertTextSelection_: BLOX.BText-inserting text. (line 24) * inset_: BLOX.BWidget-geometry management. (line 158) * interface: Sockets.MulticastSocket-instance creation. (line 6) * interface_: Sockets.MulticastSocket-instance creation. (line 10) * invokeCallback <1>: BLOX.BWindow-accessing. (line 20) * invokeCallback <2>: BLOX.BToggle-accessing. (line 14) * invokeCallback <3>: BLOX.BText-inserting text. (line 28) * invokeCallback <4>: BLOX.BMenuObject-callback. (line 22) * invokeCallback <5>: BLOX.BList-widget protocol. (line 21) * invokeCallback <6>: BLOX.BEdit-widget protocol. (line 20) * invokeCallback <7>: BLOX.BDropDownList-callbacks. (line 14) * invokeCallback <8>: BLOX.BDropDown-callbacks. (line 15) * invokeCallback <9>: BLOX.BCheckMenuItem-accessing. (line 6) * invokeCallback <10>: BLOX.BButtonLike-accessing. (line 15) * invokeCallback: BLOX.BButton-accessing. (line 85) * invokeCallback_: BLOX.BDialog-widget protocol. (line 16) * ipAddMembership: Sockets.DatagramSocketImpl-C constants. (line 6) * ipDropMembership: Sockets.DatagramSocketImpl-C constants. (line 9) * ipMulticastIf <1>: Sockets.UDPSocketImpl-multicasting. (line 6) * ipMulticastIf <2>: Sockets.MulticastSocketImpl-multicasting. (line 6) * ipMulticastIf: Sockets.DatagramSocketImpl-C constants. (line 12) * ipMulticastIf_ <1>: Sockets.UDPSocketImpl-multicasting. (line 10) * ipMulticastIf_: Sockets.MulticastSocketImpl-multicasting. (line 10) * ipMulticastTtl: Sockets.DatagramSocketImpl-C constants. (line 15) * ipprotoIp: Sockets.UDPSocketImpl class-C constants. (line 6) * ipprotoTcp: Sockets.TCPSocketImpl class-C constants. (line 6) * isActive <1>: Debugger-inferior process properties. (line 9) * isActive: BLOX.BWidget-widget protocol. (line 37) * isCentered: BLOX.BTextAttributes-setting attributes. (line 87) * isComplex: Complex-creation/coercion. (line 18) * isDigitAddress_: Sockets.SocketAddress class-accessing. (line 38) * isDML: DBI.ResultSet-accessing. (line 15) * isDropdownVisible: BLOX.BDropDown-widget protocol. (line 17) * isEmpty: Sockets.ReadBuffer-buffer handling. (line 27) * isExact: Complex-testing. (line 6) * isExternalStream <1>: ZLib.ZlibStream-streaming. (line 6) * isExternalStream: Sockets.AbstractSocket-testing. (line 6) * isFull <1>: Sockets.WriteBuffer-testing. (line 6) * isFull: Sockets.ReadBuffer-buffer handling. (line 30) * isMapped: BLOX.BWindow-widget protocol. (line 31) * isMulticast <1>: Sockets.UnixAddress-testing. (line 6) * isMulticast <2>: Sockets.SocketAddress-testing. (line 6) * isMulticast <3>: Sockets.IPAddress-accessing. (line 19) * isMulticast: Sockets.IP6Address-accessing. (line 10) * isNullable: DBI.ColumnInfo-accessing. (line 10) * isOpen: Sockets.AbstractSocket-accessing. (line 27) * isPeerAlive <1>: Sockets.StreamSocket-stream protocol. (line 26) * isPeerAlive: Sockets.AbstractSocket-accessing. (line 31) * isPositionable: ZLib.RawInflateStream-positioning. (line 14) * isPosixLocale: I18N.LocaleData-accessing. (line 12) * isSelect: DBI.ResultSet-accessing. (line 19) * isSelected_: BLOX.BList-accessing. (line 174) * isStruckout: BLOX.BTextAttributes-setting attributes. (line 91) * isUnderlined: BLOX.BTextAttributes-setting attributes. (line 95) * isUnicode <1>: I18N.EncodedStringFactory-accessing. (line 6) * isUnicode: I18N.EncodedString class-accessing. (line 6) * isWindow <1>: BLOX.BWindow-widget protocol. (line 34) * isWindow: BLOX.Blox-widget protocol. (line 50) * itemHeight: BLOX.BDropDown-flexibility. (line 15) * items: BLOX.BCanvas-widget protocol. (line 36) * join: BLOX.BPolyline-accessing. (line 30) * join_ <1>: Sockets.UDPSocketImpl-multicasting. (line 14) * join_ <2>: Sockets.MulticastSocketImpl-multicasting. (line 14) * join_ <3>: Sockets.MulticastSocket-instance creation. (line 14) * join_: BLOX.BPolyline-accessing. (line 37) * justify: BLOX.BEmbeddedText-accessing. (line 52) * justify_: BLOX.BEmbeddedText-accessing. (line 55) * keysAndValuesDo_: DBI.Row-accessing. (line 32) * label <1>: BLOX.BWindow-accessing. (line 24) * label <2>: BLOX.BMenuItem-accessing. (line 6) * label <3>: BLOX.BMenu-accessing. (line 6) * label <4>: BLOX.BList-accessing. (line 178) * label <5>: BLOX.BLabel-accessing. (line 96) * label: BLOX.BButton-accessing. (line 88) * label_ <1>: BLOX.BWindow-accessing. (line 32) * label_ <2>: BLOX.BMenuItem-accessing. (line 14) * label_ <3>: BLOX.BMenu-accessing. (line 14) * label_ <4>: BLOX.BList-accessing. (line 181) * label_ <5>: BLOX.BLabel-accessing. (line 104) * label_: BLOX.BButton-accessing. (line 96) * labelAt_ <1>: BLOX.BList-accessing. (line 184) * labelAt_: BLOX.BDropDown-list box accessing. (line 67) * labels: BLOX.BList-accessing. (line 187) * labelsDo_ <1>: BLOX.BList-accessing. (line 190) * labelsDo_: BLOX.BDropDown-list box accessing. (line 70) * language: I18N.LocaleData-accessing. (line 16) * language_: I18N.LocaleData class-accessing. (line 20) * language_territory_: I18N.LocaleData class-accessing. (line 23) * language_territory_charset_: I18N.LocaleData class-accessing. (line 26) * languageDirectory <1>: I18N.LocaleData-accessing. (line 19) * languageDirectory: I18N.LcMessages-accessing. (line 6) * languageDirectory_ <1>: I18N.LocaleData-accessing. (line 23) * languageDirectory_: I18N.LcMessages-accessing. (line 9) * languages: I18N.LocaleData class-database. (line 19) * leave_ <1>: Sockets.UDPSocketImpl-multicasting. (line 17) * leave_ <2>: Sockets.MulticastSocketImpl-multicasting. (line 17) * leave_: Sockets.MulticastSocket-instance creation. (line 17) * left_top_right_bottom_: BLOX.BWidget-geometry management. (line 161) * leftArrow: BLOX.BImage class-arrows. (line 9) * lhs: I18N.RTEBinaryNode-compiling. (line 6) * lhs_op_rhs_ <1>: I18N.RTEBinaryNode-computing. (line 6) * lhs_op_rhs_: I18N.RTEBinaryNode class-compiling. (line 6) * lineAt_: BLOX.BText-position & lines. (line 40) * lineFrom_extent_color_: BLOX.BImage-image management. (line 51) * lineFrom_to_color_: BLOX.BImage-image management. (line 55) * lineFrom_toX_color_: BLOX.BImage-image management. (line 58) * lineFrom_toY_color_: BLOX.BImage-image management. (line 62) * lineInside_color_: BLOX.BImage-image management. (line 66) * listCallback: BLOX.BDropDown-flexibility. (line 20) * listen_: Sockets.AbstractSocketImpl-socket operations. (line 51) * listen_log_ <1>: Sockets.AbstractSocketImpl-C call-outs. (line 24) * listen_log_: Sockets.AbstractSocketImpl class-C call-outs. (line 24) * listSelectAt_: BLOX.BDropDown-flexibility. (line 24) * listText: BLOX.BDropDown-flexibility. (line 29) * ln: Complex-transcendental functions. (line 24) * load_: I18N.Locale-C call-outs. (line 6) * local_port_: Sockets.DatagramSocket class-instance creation. (line 6) * localAddress <1>: Sockets.AbstractSocketImpl-accessing. (line 10) * localAddress: Sockets.AbstractSocket-accessing. (line 35) * localHostName: Sockets.SocketAddress class-accessing. (line 42) * localPort <1>: Sockets.AbstractSocketImpl-accessing. (line 15) * localPort: Sockets.AbstractSocket-accessing. (line 38) * log: Complex-transcendental functions. (line 27) * loop: BLOX.BDialog-widget protocol. (line 21) * loopbackHost: Sockets.SocketAddress class-accessing. (line 45) * loopbackTest: Sockets.Socket class-tests. (line 16) * loopbackTest_: Sockets.Socket class-tests. (line 20) * loopbackTest_addressClass_: Sockets.Socket class-tests. (line 25) * loopbackTestOn_: Sockets.Socket class-tests. (line 31) * lower: BLOX.BCanvasObject-widget protocol. (line 14) * magenta <1>: BLOX.BTextAttributes-colors. (line 27) * magenta: BLOX.BTextAttributes class-instance-creation shortcuts. (line 64) * make_: BLOX.Blox-creating children. (line 6) * make_on_: BLOX.Blox-creating children. (line 15) * makeChild_on_: BLOX.Blox-creating children. (line 20) * map <1>: BLOX.BWindow-widget protocol. (line 37) * map: BLOX.BTransientWindow-widget protocol. (line 6) * mapPoint_: BLOX.BCanvas-widget protocol. (line 39) * menu_: BLOX.BWindow-accessing. (line 40) * messages: I18N.Locale-subobjects. (line 6) * microTest: Sockets.Socket class-tests. (line 36) * modalMap: BLOX.BWindow-widget protocol. (line 40) * mode: BLOX.BList-accessing. (line 193) * mode_: BLOX.BList-accessing. (line 236) * monetary: I18N.Locale-subobjects. (line 10) * monetaryIso: I18N.Locale-subobjects. (line 14) * mousePointer: BLOX.Blox class-utility. (line 60) * moveBy_: BLOX.BBoundingBox-accessing. (line 36) * msgOOB: Sockets.OOBSocketImpl-C constants. (line 6) * msgPeek: Sockets.DatagramSocketImpl-C constants. (line 18) * n_: I18N.RTELiteralNode-computing. (line 6) * name <1>: ZLib.ZlibStream-streaming. (line 9) * name <2>: Sockets.SocketAddress-accessing. (line 20) * name: DBI.ColumnInfo-accessing. (line 14) * network: Sockets.IPAddress-accessing. (line 23) * new <1>: ZLib.ZlibStream class-instance creation. (line 6) * new <2>: Sockets.IPAddress class-instance creation. (line 71) * new <3>: Sockets.IP6Address class-instance creation. (line 25) * new <4>: Sockets.DatagramSocket class-instance creation. (line 10) * new <5>: Sockets.AbstractSocket class-instance creation. (line 6) * new <6>: I18N.LocaleData class-accessing. (line 30) * new <7>: I18N.EncodedStringFactory-instance creation. (line 16) * new <8>: I18N.EncodedString class-instance creation. (line 12) * new <9>: DBI.FieldConverter class-instance creation. (line 6) * new <10>: Complex class-instance creation. (line 12) * new <11>: BLOX.BWindow class-instance creation. (line 6) * new <12>: BLOX.BWidget class-popups. (line 6) * new <13>: BLOX.BTransientWindow class-instance creation. (line 6) * new <14>: BLOX.BTextBindings class-instance creation. (line 6) * new <15>: BLOX.Blox class-instance creation. (line 6) * new <16>: BLOX.BEventSet class-initializing. (line 6) * new: BLOX.BCanvasObject class-instance creation. (line 6) * new_ <1>: Sockets.AbstractSocket class-instance creation. (line 9) * new_ <2>: I18N.EncodedStringFactory-instance creation. (line 20) * new_ <3>: I18N.EncodedString class-instance creation. (line 15) * new_ <4>: BLOX.BWindow class-instance creation. (line 9) * new_ <5>: BLOX.BTransientWindow class-instance creation. (line 9) * new_ <6>: BLOX.BMenuItem class-instance creation. (line 6) * new_ <7>: BLOX.Blox class-instance creation. (line 9) * new_ <8>: BLOX.BEventSet class-initializing. (line 9) * new_ <9>: BLOX.BDialog class-instance creation. (line 6) * new_ <10>: BLOX.BCheckMenuItem class-instance creation. (line 6) * new_: BLOX.BCanvasObject class-instance creation. (line 9) * new_addressClass_: Sockets.AbstractSocket class-instance creation. (line 14) * new_contents_: BLOX.BEdit class-instance creation. (line 6) * new_data_: BLOX.BImage class-instance creation. (line 6) * new_image_: BLOX.BImage class-instance creation. (line 11) * new_in_: BLOX.BTransientWindow class-instance creation. (line 13) * new_label_ <1>: BLOX.BMenuItem class-instance creation. (line 9) * new_label_ <2>: BLOX.BMenu class-instance creation. (line 6) * new_label_ <3>: BLOX.BLabel class-instance creation. (line 6) * new_label_ <4>: BLOX.BDialog class-instance creation. (line 11) * new_label_: BLOX.BButton class-instance creation. (line 6) * new_label_prompt_: BLOX.BDialog class-instance creation. (line 16) * new_size_: BLOX.BImage class-instance creation. (line 15) * newFor_: Sockets.AbstractSocketImpl class-socket creation. (line 6) * newPrimitive: BLOX.BExtended-customization. (line 17) * newRawSocket: Sockets.SocketAddress class-creating sockets. (line 6) * newReadOnly_: BLOX.BText class-instance creation. (line 6) * next <1>: ZLib.ZlibReadStream-streaming. (line 9) * next <2>: Sockets.StreamSocket-stream protocol. (line 30) * next <3>: Sockets.DatagramSocketImpl-socket operations. (line 6) * next <4>: Sockets.DatagramSocket-accessing. (line 18) * next <5>: Sockets.AbstractSocket-stream protocol. (line 9) * next <6>: I18N.Encoder-stream operations. (line 17) * next <7>: Debugger-stepping commands. (line 16) * next: DBI.ResultSet-cursor access. (line 13) * next_putAll_startingAt_ <1>: ZLib.ZlibWriteStream-streaming. (line 31) * next_putAll_startingAt_ <2>: Sockets.WriteBuffer-accessing-writing. (line 6) * next_putAll_startingAt_ <3>: Sockets.Socket-stream protocol. (line 17) * next_putAll_startingAt_: Sockets.AbstractSocket-stream protocol. (line 13) * nextAvailable_into_startingAt_ <1>: ZLib.ZlibReadStream-accessing-reading. (line 6) * nextAvailable_into_startingAt_ <2>: Sockets.StreamSocket-accessing-reading. (line 6) * nextAvailable_into_startingAt_: Sockets.ReadBuffer-accessing-reading. (line 6) * nextAvailable_putAllOn_ <1>: ZLib.ZlibReadStream-accessing-reading. (line 11) * nextAvailable_putAllOn_ <2>: Sockets.StreamSocket-accessing-reading. (line 11) * nextAvailable_putAllOn_: Sockets.ReadBuffer-accessing-reading. (line 11) * nextFrom_port_: Sockets.DatagramSocket-direct operations. (line 6) * nextInput: I18N.Encoder-stream operations. (line 21) * nextInputAvailable_into_startingAt_: I18N.Encoder-stream operations. (line 26) * nextPut_ <1>: ZLib.ZlibWriteStream-streaming. (line 35) * nextPut_ <2>: Sockets.Socket-stream protocol. (line 22) * nextPut_ <3>: Sockets.DatagramSocketImpl-socket operations. (line 10) * nextPut_ <4>: Sockets.DatagramSocket-accessing. (line 21) * nextPut_ <5>: Sockets.AbstractSocket-stream protocol. (line 17) * nextPut_ <6>: BLOX.BText-inserting text. (line 31) * nextPut_: BLOX.BEdit-widget protocol. (line 23) * nextPut_timeToLive_: Sockets.MulticastSocket-instance creation. (line 20) * nextPutAll_ <1>: BLOX.BText-inserting text. (line 34) * nextPutAll_: BLOX.BEdit-widget protocol. (line 26) * nl <1>: BLOX.BText-inserting text. (line 37) * nl: BLOX.BEdit-widget protocol. (line 29) * notEmpty: Sockets.ReadBuffer-buffer handling. (line 33) * numberOfLines: BLOX.BText-position & lines. (line 43) * numberOfStrings <1>: BLOX.BList-accessing. (line 279) * numberOfStrings: BLOX.BDropDown-list box accessing. (line 74) * numeric: I18N.Locale-subobjects. (line 18) * object_address_port_: Sockets.Datagram class-instance creation. (line 13) * object_objectDumper_address_port_: Sockets.Datagram class-instance creation. (line 21) * on_ <1>: ZLib.ZlibStream class-instance creation. (line 9) * on_ <2>: ZLib.RawDeflateWriteStream class-instance creation. (line 6) * on_ <3>: ZLib.RawDeflateStream class-instance creation. (line 14) * on_ <4>: Sockets.ReadBuffer class-instance creation. (line 6) * on_ <5>: I18N.RunTimeExpression class-instance creation. (line 6) * on_ <6>: Debugger class-instance creation. (line 6) * on_: DBI.Statement class-instance creation. (line 6) * on_from_: I18N.EncodedStream class-instance creation. (line 16) * on_from_to_ <1>: I18N.Encoder class-instance creation. (line 6) * on_from_to_: I18N.EncodedStream class-instance creation. (line 21) * on_level_ <1>: ZLib.RawDeflateWriteStream class-instance creation. (line 10) * on_level_: ZLib.RawDeflateStream class-instance creation. (line 18) * on_to_: I18N.EncodedStream class-instance creation. (line 26) * onAsciiKeyEventSend_to_: BLOX.BEventTarget-intercepting events. (line 11) * onDestroySend_to_: BLOX.BEventTarget-intercepting events. (line 16) * one: Complex-creation/coercion. (line 21) * onFocusEnterEventSend_to_: BLOX.BEventTarget-intercepting events. (line 20) * onFocusLeaveEventSend_to_: BLOX.BEventTarget-intercepting events. (line 24) * onKeyEvent_send_to_: BLOX.BEventTarget-intercepting events. (line 28) * onKeyEventSend_to_: BLOX.BEventTarget-intercepting events. (line 43) * onKeyUpEventSend_to_: BLOX.BEventTarget-intercepting events. (line 52) * onMouseDoubleEvent_send_to_: BLOX.BEventTarget-intercepting events. (line 61) * onMouseDoubleEventSend_to_: BLOX.BEventTarget-intercepting events. (line 66) * onMouseDownEvent_send_to_: BLOX.BEventTarget-intercepting events. (line 72) * onMouseDownEventSend_to_: BLOX.BEventTarget-intercepting events. (line 77) * onMouseEnterEventSend_to_: BLOX.BEventTarget-intercepting events. (line 83) * onMouseLeaveEventSend_to_: BLOX.BEventTarget-intercepting events. (line 87) * onMouseMoveEvent_send_to_: BLOX.BEventTarget-intercepting events. (line 91) * onMouseMoveEventSend_to_: BLOX.BEventTarget-intercepting events. (line 96) * onMouseTripleEvent_send_to_: BLOX.BEventTarget-intercepting events. (line 101) * onMouseTripleEventSend_to_: BLOX.BEventTarget-intercepting events. (line 106) * onMouseUpEvent_send_to_: BLOX.BEventTarget-intercepting events. (line 112) * onMouseUpEventSend_to_: BLOX.BEventTarget-intercepting events. (line 117) * onResizeSend_to_: BLOX.BEventTarget-intercepting events. (line 123) * op: I18N.RTEBinaryNode-compiling. (line 9) * option_level_at_get_size_ <1>: Sockets.AbstractSocketImpl-C call-outs. (line 27) * option_level_at_get_size_: Sockets.AbstractSocketImpl class-C call-outs. (line 27) * option_level_at_put_size_ <1>: Sockets.AbstractSocketImpl-C call-outs. (line 30) * option_level_at_put_size_: Sockets.AbstractSocketImpl class-C call-outs. (line 30) * optionAt_level_put_: Sockets.AbstractSocketImpl-socket options. (line 6) * optionAt_level_size_: Sockets.AbstractSocketImpl-socket options. (line 13) * origin: BLOX.BBoundingBox-accessing. (line 42) * origin_: BLOX.BBoundingBox-accessing. (line 45) * origin_corner_: BLOX.BBoundingBox-accessing. (line 51) * origin_extent_: BLOX.BBoundingBox-accessing. (line 59) * outlineColor <1>: BLOX.BRectangle-accessing. (line 6) * outlineColor: BLOX.BPolyline-accessing. (line 44) * outlineColor_ <1>: BLOX.BRectangle-accessing. (line 9) * outlineColor_: BLOX.BPolyline-accessing. (line 48) * outOfBand: Sockets.StreamSocket-out-of-band data. (line 6) * outOfBandImplClass: Sockets.SocketImpl-abstract. (line 6) * paramConnect_user_password_: DBI.Connection class-connecting. (line 17) * params: DBI.ConnectionInfo-accessing. (line 15) * paramString_: DBI.ConnectionInfo-accessing. (line 12) * parent: BLOX.Blox-widget protocol. (line 53) * parseExpression_: I18N.RunTimeExpression class-compiling. (line 6) * parseFrom_: I18N.RTELiteralNode class-initializing. (line 6) * parseOperand_: I18N.RunTimeExpression class-compiling. (line 9) * parseOperator_: I18N.RunTimeExpression class-compiling. (line 14) * partialFlush: ZLib.ZlibWriteStream-streaming. (line 39) * pastEnd: Sockets.ReadBuffer-buffer handling. (line 37) * peek <1>: ZLib.ZlibReadStream-streaming. (line 12) * peek <2>: Sockets.StreamSocket-stream protocol. (line 34) * peek <3>: Sockets.DatagramSocketImpl-socket operations. (line 13) * peek: Sockets.DatagramSocket-accessing. (line 24) * peek_ <1>: Sockets.DatagramSocketImpl-socket operations. (line 17) * peek_: Sockets.DatagramSocket-accessing. (line 27) * peekFor_ <1>: ZLib.ZlibReadStream-streaming. (line 16) * peekFor_: Sockets.StreamSocket-stream protocol. (line 39) * peekInput: I18N.Encoder-stream operations. (line 31) * platform: BLOX.Blox class-utility. (line 69) * pluralExpressionFor_ifAbsent_: I18N.LcMessagesMoFileVersion0 class-plurals. (line 10) * points: BLOX.BPolyline-accessing. (line 52) * points_: BLOX.BPolyline-accessing. (line 55) * popup: BLOX.BPopupMenu-widget protocol. (line 6) * popup_ <1>: BLOX.BWindow class-instance creation. (line 13) * popup_: BLOX.BWidget class-popups. (line 15) * port <1>: Sockets.StreamSocket-accessing. (line 9) * port <2>: Sockets.ServerSocket-accessing. (line 18) * port <3>: Sockets.DatagramSocket-accessing. (line 31) * port <4>: Sockets.Datagram-accessing. (line 36) * port: Sockets.AbstractSocket-accessing. (line 41) * port_ <1>: Sockets.ServerSocket class-instance creation. (line 11) * port_ <2>: Sockets.DatagramSocket class-instance creation. (line 14) * port_: Sockets.Datagram-accessing. (line 39) * port_bindTo_: Sockets.ServerSocket class-instance creation. (line 15) * port_queueSize_: Sockets.ServerSocket class-instance creation. (line 19) * port_queueSize_bindTo_ <1>: Sockets.ServerSocket-initializing. (line 6) * port_queueSize_bindTo_: Sockets.ServerSocket class-instance creation. (line 23) * portCmdServer: Sockets.AbstractSocket class-well known ports. (line 17) * portDayTime: Sockets.AbstractSocket class-well known ports. (line 23) * portDiscard: Sockets.AbstractSocket class-well known ports. (line 26) * portDNS: Sockets.AbstractSocket class-well known ports. (line 20) * portEcho: Sockets.AbstractSocket class-well known ports. (line 29) * portExecServer: Sockets.AbstractSocket class-well known ports. (line 32) * portFinger: Sockets.AbstractSocket class-well known ports. (line 38) * portFTP: Sockets.AbstractSocket class-well known ports. (line 35) * portGopher: Sockets.AbstractSocket class-well known ports. (line 41) * portHTTP: Sockets.AbstractSocket class-well known ports. (line 44) * portLoginServer: Sockets.AbstractSocket class-well known ports. (line 47) * portNetStat: Sockets.AbstractSocket class-well known ports. (line 53) * portNNTP: Sockets.AbstractSocket class-well known ports. (line 50) * portPOP3: Sockets.AbstractSocket class-well known ports. (line 56) * portReserved: Sockets.AbstractSocket class-well known ports. (line 59) * portSMTP: Sockets.AbstractSocket class-well known ports. (line 62) * portSSH: Sockets.AbstractSocket class-well known ports. (line 65) * portSystat: Sockets.AbstractSocket class-well known ports. (line 68) * portTelnet: Sockets.AbstractSocket class-well known ports. (line 71) * portTimeServer: Sockets.AbstractSocket class-well known ports. (line 74) * portWhois: Sockets.AbstractSocket class-well known ports. (line 77) * pos_: BLOX.BWidget-geometry management. (line 164) * posHoriz_: BLOX.BWidget-geometry management. (line 168) * position <1>: ZLib.ZlibWriteStream-streaming. (line 43) * position <2>: ZLib.ZlibReadStream-streaming. (line 21) * position: DBI.ResultSet-stream protocol. (line 6) * position_ <1>: ZLib.RawInflateStream-positioning. (line 17) * position_: DBI.ResultSet-stream protocol. (line 10) * posix <1>: I18N.LocaleData class-accessing. (line 33) * posix <2>: I18N.LocaleConventions class-accessing. (line 17) * posix: I18N.Locale class-instance creation. (line 18) * posVert_: BLOX.BWidget-geometry management. (line 171) * prepare_: DBI.Connection-querying. (line 11) * pressed <1>: BLOX.BColorButton-accessing. (line 12) * pressed: BLOX.BButtonLike-accessing. (line 18) * primAccept_: Sockets.ServerSocket-accessing. (line 22) * primary_secondary_: I18N.LcMessagesTerritoryDomain class-instance creation. (line 6) * primJoinLeave_option_: Sockets.UDPSocketImpl-multicasting. (line 20) * primLocalName: Sockets.SocketAddress class-C call-outs. (line 6) * primName_len_type_: Sockets.SocketAddress class-C call-outs. (line 9) * primRootDirectory: I18N.Locale class-C call-outs. (line 6) * primTableAt_ifAbsent_: DBI.Connection-querying. (line 15) * print_on_ <1>: I18N.LcTime-printing. (line 6) * print_on_ <2>: I18N.LcPrintFormats-printing. (line 10) * print_on_ <3>: I18N.LcNumeric-printing. (line 11) * print_on_ <4>: I18N.LcMonetary-printing. (line 6) * print_on_ <5>: DBI.Table-printing. (line 6) * print_on_: DBI.FieldConverter-actions. (line 6) * print_on_currency_parentheses_: I18N.LcMonetary-printing. (line 11) * print_on_ifFull_ifDate_ifTime_: I18N.LcTime-printing. (line 11) * print_time_format_on_: I18N.LcTime-printing. (line 18) * printOn_ <1>: Sockets.UnixAddress-printing. (line 6) * printOn_ <2>: Sockets.StreamSocket-printing. (line 6) * printOn_ <3>: Sockets.IPAddress-printing. (line 6) * printOn_ <4>: Sockets.IP6Address-printing. (line 6) * printOn_ <5>: Sockets.AbstractSocket-printing. (line 6) * printOn_ <6>: I18N.RTEParameterNode-computing. (line 6) * printOn_ <7>: I18N.RTENegationNode-computing. (line 9) * printOn_ <8>: I18N.RTELiteralNode-computing. (line 9) * printOn_ <9>: I18N.RTEBinaryNode-computing. (line 10) * printOn_ <10>: I18N.RTEAlternativeNode-computing. (line 10) * printOn_ <11>: I18N.EncodedString-printing. (line 11) * printOn_ <12>: DBI.Row-printing. (line 6) * printOn_ <13>: DBI.ResultSet-printing. (line 6) * printOn_ <14>: DBI.ColumnInfo-printing. (line 9) * printOn_: Complex-printing. (line 6) * printString_ <1>: I18N.LcPrintFormats-printing. (line 14) * printString_: DBI.FieldConverter-actions. (line 9) * process: Debugger-inferior process properties. (line 12) * producerConsumerTest: Sockets.Socket class-tests. (line 39) * producerConsumerTestOn_: Sockets.Socket class-tests. (line 44) * protocol <1>: Sockets.UDPSocketImpl class-C constants. (line 9) * protocol <2>: Sockets.TCPSocketImpl class-C constants. (line 9) * protocol <3>: Sockets.ICMPSocketImpl class-C constants. (line 6) * protocol <4>: Sockets.ICMP6SocketImpl class-C constants. (line 6) * protocol: Sockets.AbstractSocketImpl class-abstract. (line 10) * protocolFamily <1>: Sockets.UnixAddress class-C constants. (line 9) * protocolFamily <2>: Sockets.SocketAddress class-C constants. (line 15) * protocolFamily <3>: Sockets.IPAddress class-C constants. (line 9) * protocolFamily: Sockets.IP6Address class-C constants. (line 15) * question: BLOX.BImage class-icons. (line 12) * queueSize_: Sockets.ServerSocket class-instance creation. (line 27) * queueSize_bindTo_: Sockets.ServerSocket class-instance creation. (line 31) * raise: BLOX.BCanvasObject-widget protocol. (line 20) * readBufferSize: Sockets.StreamSocket class-accessing. (line 12) * readBufferSize_ <1>: Sockets.StreamSocket-stream protocol. (line 44) * readBufferSize_: Sockets.StreamSocket class-accessing. (line 15) * readStream: ZLib.ZlibWriteStream-streaming. (line 46) * real: Complex-creation/coercion. (line 24) * real_imaginary_: Complex class-instance creation. (line 15) * realResult_imaginary_: Complex class-instance creation. (line 18) * receive_ <1>: Sockets.DatagramSocketImpl-socket operations. (line 21) * receive_: Sockets.DatagramSocket-accessing. (line 34) * receive_buffer_size_flags_from_size_ <1>: Sockets.AbstractSocketImpl-C call-outs. (line 33) * receive_buffer_size_flags_from_size_: Sockets.AbstractSocketImpl class-C call-outs. (line 33) * receive_datagram_: Sockets.DatagramSocketImpl-socket operations. (line 25) * reciprocal: Complex-math. (line 27) * red <1>: BLOX.BTextAttributes-colors. (line 30) * red: BLOX.BTextAttributes class-instance-creation shortcuts. (line 67) * redraw <1>: BLOX.BEmbeddedText-accessing. (line 59) * redraw <2>: BLOX.BEmbeddedImage-accessing. (line 21) * redraw: BLOX.BCanvasObject-widget protocol. (line 26) * refuseTabs: BLOX.BText-inserting text. (line 41) * registerEncoderFor_toUTF32_fromUTF32_: I18N.EncodedStream class-initializing. (line 10) * registerImage_: BLOX.BText-images. (line 28) * release: BLOX.Blox-basic. (line 10) * remote_port_: Sockets.StreamSocket class-instance creation. (line 6) * remote_port_local_port_ <1>: Sockets.StreamSocket class-instance creation. (line 11) * remote_port_local_port_: Sockets.DatagramSocket class-instance creation. (line 18) * remoteAddress <1>: Sockets.AbstractSocketImpl-accessing. (line 20) * remoteAddress: Sockets.AbstractSocket-accessing. (line 46) * remotePort <1>: Sockets.AbstractSocketImpl-accessing. (line 25) * remotePort: Sockets.AbstractSocket-accessing. (line 49) * remove: BLOX.BCanvasObject-widget protocol. (line 31) * remove_: BLOX.BMenuBar-accessing. (line 9) * removeAtIndex_ <1>: BLOX.BList-accessing. (line 282) * removeAtIndex_: BLOX.BDropDown-list box accessing. (line 77) * removeAttributes: BLOX.BText-attributes. (line 15) * removeAttributesFrom_to_: BLOX.BText-attributes. (line 18) * replaceSelection_ <1>: BLOX.BText-inserting text. (line 45) * replaceSelection_ <2>: BLOX.BEdit-widget protocol. (line 33) * replaceSelection_: BLOX.BDropDownEdit-text accessing. (line 10) * reset: ZLib.RawInflateStream-positioning. (line 23) * resizable: BLOX.BWindow-accessing. (line 49) * resizable_: BLOX.BWindow-accessing. (line 58) * resultIn_: BLOX.Blox class-C call-outs. (line 12) * resultSet: DBI.Row-accessing. (line 35) * rho_theta_: Complex class-instance creation. (line 22) * rhs: I18N.RTEBinaryNode-compiling. (line 12) * rightArrow: BLOX.BImage class-arrows. (line 12) * rootDirectory: I18N.Locale class-initialization. (line 6) * rootDirectory_: I18N.Locale class-initialization. (line 9) * rounded: Complex-converting. (line 30) * rowCount: DBI.ResultSet-accessing. (line 23) * rows: DBI.ResultSet-accessing. (line 27) * rowsAffected: DBI.ResultSet-accessing. (line 30) * scheme: DBI.ConnectionInfo-accessing. (line 18) * scheme_: DBI.ConnectionInfo-accessing. (line 21) * screenOrigin: BLOX.Blox class-utility. (line 73) * screenResolution: BLOX.Blox class-utility. (line 79) * screenSize: BLOX.Blox class-utility. (line 83) * searchString_: BLOX.BText-inserting text. (line 50) * select_ <1>: DBI.Connection-querying. (line 19) * select_: BLOX.BList-widget protocol. (line 24) * selectAll <1>: BLOX.BEdit-widget protocol. (line 38) * selectAll: BLOX.BDropDownEdit-text accessing. (line 15) * selectBackground <1>: BLOX.BText-accessing. (line 95) * selectBackground: BLOX.BEdit-accessing. (line 91) * selectBackground_ <1>: BLOX.BText-accessing. (line 101) * selectBackground_: BLOX.BEdit-accessing. (line 97) * selectForeground <1>: BLOX.BText-accessing. (line 107) * selectForeground: BLOX.BEdit-accessing. (line 103) * selectForeground_ <1>: BLOX.BText-accessing. (line 113) * selectForeground_: BLOX.BEdit-accessing. (line 109) * selectFrom_to_ <1>: BLOX.BText-position & lines. (line 46) * selectFrom_to_ <2>: BLOX.BEdit-widget protocol. (line 41) * selectFrom_to_: BLOX.BDropDownEdit-text accessing. (line 18) * selection <1>: BLOX.BEdit-widget protocol. (line 48) * selection: BLOX.BDropDownEdit-text accessing. (line 25) * selectionRange <1>: BLOX.BEdit-widget protocol. (line 52) * selectionRange: BLOX.BDropDownEdit-text accessing. (line 29) * selector <1>: I18N.LocaleConventions class-accessing. (line 20) * selector <2>: I18N.LcTime class-accessing. (line 10) * selector <3>: I18N.LcNumeric class-accessing. (line 10) * selector <4>: I18N.LcMonetaryISO class-accessing. (line 6) * selector <5>: I18N.LcMonetary class-accessing. (line 10) * selector: I18N.LcMessages class-accessing. (line 10) * send_ <1>: I18N.RunTimeExpression-computing. (line 6) * send_ <2>: I18N.RTEParameterNode-computing. (line 9) * send_ <3>: I18N.RTENegationNode-computing. (line 12) * send_ <4>: I18N.RTELiteralNode-computing. (line 12) * send_ <5>: I18N.RTEBinaryNode-computing. (line 13) * send_: I18N.RTEAlternativeNode-computing. (line 13) * send_buffer_size_flags_to_size_ <1>: Sockets.AbstractSocketImpl-C call-outs. (line 36) * send_buffer_size_flags_to_size_: Sockets.AbstractSocketImpl class-C call-outs. (line 36) * send_to_port_: Sockets.DatagramSocketImpl-socket operations. (line 31) * sendTest: Sockets.Socket class-tests. (line 48) * sendTest_: Sockets.Socket class-tests. (line 51) * sendToBack: BLOX.BWidget-widget protocol. (line 41) * setAttributes_from_to_: BLOX.BText-attributes. (line 24) * setInitialSize: BLOX.BWidget-customization. (line 29) * setReal_imaginary_: Complex-creation/coercion. (line 27) * setString_: I18N.EncodedString-initializing. (line 9) * setToEnd: BLOX.BText-position & lines. (line 52) * setVerticalLayout_: BLOX.BContainer-accessing. (line 6) * shallowCopy <1>: BLOX.Blox-basic. (line 14) * shallowCopy: BLOX.BCanvasObject-accessing. (line 49) * shouldCache <1>: I18N.LcMessagesMoFileVersion0-flushing the cache. (line 9) * shouldCache: I18N.LcMessagesDomain-handling the cache. (line 9) * show: BLOX.BCanvasObject-widget protocol. (line 34) * show_: BLOX.BList-widget protocol. (line 30) * shown <1>: BLOX.BBalloon-accessing. (line 6) * shown: BLOX.BBalloon class-accessing. (line 13) * sin: Complex-transcendental functions. (line 30) * sinh: Complex-transcendental functions. (line 33) * size <1>: Sockets.Datagram-accessing. (line 42) * size <2>: I18N.EncodedString-accessing. (line 27) * size <3>: DBI.Table-core. (line 6) * size <4>: DBI.ResultSet-stream protocol. (line 13) * size <5>: DBI.ColumnInfo-accessing. (line 17) * size <6>: BLOX.BList-accessing. (line 287) * size: BLOX.BDropDown-list box accessing. (line 82) * skip_: ZLib.RawInflateStream-positioning. (line 26) * slowFinish: Debugger-stepping commands. (line 20) * slowFinish_: Debugger-stepping commands. (line 23) * smoothness: BLOX.BSpline-accessing. (line 6) * smoothness_: BLOX.BSpline-accessing. (line 10) * sockDgram: Sockets.AbstractSocketImpl class-C constants. (line 12) * socketType <1>: Sockets.SocketImpl class-parameters. (line 6) * socketType <2>: Sockets.RawSocketImpl class-parameters. (line 6) * socketType <3>: Sockets.DatagramSocketImpl class-parameters. (line 10) * socketType: Sockets.AbstractSocketImpl class-abstract. (line 13) * sockRaw: Sockets.AbstractSocketImpl class-C constants. (line 18) * sockRDM: Sockets.AbstractSocketImpl class-C constants. (line 15) * sockStream: Sockets.AbstractSocketImpl class-C constants. (line 21) * soError_: Sockets.AbstractSocketImpl-C constants. (line 6) * soLinger <1>: Sockets.AbstractSocketImpl-socket options. (line 19) * soLinger <2>: Sockets.AbstractSocketImpl class-C constants. (line 6) * soLinger: Sockets.AbstractSocket-socket options. (line 6) * soLinger_ <1>: Sockets.AbstractSocketImpl-socket options. (line 24) * soLinger_: Sockets.AbstractSocket-socket options. (line 12) * soLingerOff: Sockets.AbstractSocket-socket options. (line 17) * solSocket: Sockets.AbstractSocketImpl class-C constants. (line 24) * soReuseAddr <1>: Sockets.AbstractSocketImpl-socket options. (line 30) * soReuseAddr: Sockets.AbstractSocketImpl class-C constants. (line 9) * soReuseAddr_: Sockets.AbstractSocketImpl-socket options. (line 39) * space <1>: BLOX.BText-inserting text. (line 55) * space: BLOX.BEdit-widget protocol. (line 58) * species <1>: ZLib.ZlibStream-streaming. (line 12) * species <2>: Sockets.AbstractSocket-socket options. (line 22) * species <3>: I18N.Encoder-stream operations. (line 34) * species: I18N.EncodedString-accessing. (line 30) * sqrt: Complex-transcendental functions. (line 36) * startAngle: BLOX.BArc-accessing. (line 32) * startAngle_: BLOX.BArc-accessing. (line 36) * state <1>: BLOX.BWindow-widget protocol. (line 64) * state: BLOX.Blox-accessing. (line 6) * state_ <1>: BLOX.BWindow-widget protocol. (line 70) * state_: BLOX.Blox-accessing. (line 18) * statement: DBI.ResultSet-accessing. (line 34) * step: Debugger-stepping commands. (line 26) * stepBytecode: Debugger-stepping commands. (line 30) * stop: BLOX.BImage class-icons. (line 15) * stopInferior: Debugger-stepping commands. (line 33) * stopInferior_: Debugger-stepping commands. (line 37) * storeOn_: Complex-printing. (line 9) * stream <1>: ZLib.ZlibStream-streaming. (line 15) * stream: ZLib.ZlibError-accessing. (line 6) * stream_: ZLib.ZlibError-accessing. (line 9) * stretch_: BLOX.BWidget-geometry management. (line 174) * strikeout <1>: BLOX.BTextAttributes-setting attributes. (line 99) * strikeout: BLOX.BTextAttributes class-instance-creation shortcuts. (line 70) * subnet: Sockets.IPAddress-accessing. (line 28) * suspendedContext: Debugger-inferior process properties. (line 15) * sweepAngle: BLOX.BArc-accessing. (line 40) * sweepAngle_: BLOX.BArc-accessing. (line 44) * syncFlush: ZLib.ZlibWriteStream-streaming. (line 51) * tableAt_: DBI.Connection-accessing. (line 17) * tableAt_ifAbsent_: DBI.Connection-accessing. (line 20) * tabStop: BLOX.BWidget-accessing. (line 64) * tabStop_: BLOX.BWidget-accessing. (line 80) * tan: Complex-transcendental functions. (line 39) * tanh: Complex-transcendental functions. (line 42) * tclInit: BLOX.Blox class-C call-outs. (line 15) * tcpNodelay: Sockets.TCPSocketImpl class-C constants. (line 12) * terminateMainLoop: BLOX.Blox class-event dispatching. (line 17) * territories: I18N.LocaleData class-database. (line 22) * territory: I18N.LocaleData-accessing. (line 27) * territoryDirectory <1>: I18N.LocaleData-accessing. (line 30) * territoryDirectory: I18N.LcMessages-accessing. (line 13) * territoryDirectory_ <1>: I18N.LocaleData-accessing. (line 34) * territoryDirectory_: I18N.LcMessages-accessing. (line 17) * testPort2For_: Sockets.Socket class-tests. (line 56) * testPortFor_: Sockets.Socket class-tests. (line 59) * text <1>: BLOX.BEmbeddedText-accessing. (line 64) * text <2>: BLOX.BDropDownList-accessing. (line 59) * text <3>: BLOX.BDropDownEdit-accessing-overrides. (line 6) * text <4>: BLOX.BDropDown-flexibility. (line 34) * text: BLOX.BBalloon-accessing. (line 9) * text_ <1>: BLOX.BEmbeddedText-accessing. (line 67) * text_ <2>: BLOX.BDropDownEdit-text accessing. (line 35) * text_ <3>: BLOX.BDropDown-flexibility. (line 39) * text_: BLOX.BBalloon-accessing. (line 12) * time: I18N.Locale-subobjects. (line 22) * timeout: Sockets.AbstractSocket class-timed-out operations. (line 15) * timeout_: Sockets.AbstractSocket class-timed-out operations. (line 20) * timeToLive <1>: Sockets.UDPSocketImpl-multicasting. (line 23) * timeToLive <2>: Sockets.MulticastSocketImpl-multicasting. (line 20) * timeToLive: Sockets.MulticastSocket-instance creation. (line 23) * timeToLive_ <1>: Sockets.UDPSocketImpl-multicasting. (line 27) * timeToLive_ <2>: Sockets.MulticastSocketImpl-multicasting. (line 24) * timeToLive_: Sockets.MulticastSocket-instance creation. (line 26) * to: BLOX.BArc-accessing. (line 48) * to_: BLOX.BArc-accessing. (line 51) * toggle: BLOX.BDropDown-widget protocol. (line 20) * toplevel: BLOX.Blox-widget protocol. (line 56) * translatorInformation: I18N.LcMessagesDomain-querying. (line 21) * translatorInformationAt_: I18N.LcMessagesDomain-querying. (line 25) * translatorInformationAt_at_: I18N.LcMessagesDomain-querying. (line 28) * truncated: Complex-converting. (line 33) * tweakedLoopbackTest: Sockets.Socket class-tests. (line 62) * type: DBI.ColumnInfo-accessing. (line 20) * underline <1>: BLOX.BTextAttributes-setting attributes. (line 102) * underline: BLOX.BTextAttributes class-instance-creation shortcuts. (line 73) * unhighlight: BLOX.BList-widget protocol. (line 34) * unicodeOn_: I18N.EncodedStream class-instance creation. (line 31) * unicodeOn_encoding_: I18N.EncodedStream class-instance creation. (line 37) * uniqueInstance <1>: Sockets.UnixAddress class-instance creation. (line 11) * uniqueInstance: DBI.FieldConverter class-instance creation. (line 9) * unknownAddress: Sockets.SocketAddress class-accessing. (line 49) * unmap: BLOX.BWindow-widget protocol. (line 73) * unmapList: BLOX.BDropDown-widget protocol. (line 23) * unselect_: BLOX.BList-widget protocol. (line 37) * upArrow: BLOX.BImage class-arrows. (line 15) * update_ <1>: Sockets.SocketAddress class-initialization. (line 25) * update_ <2>: I18N.LocaleData class-accessing. (line 37) * update_: BLOX.Blox class-event dispatching. (line 21) * updateDriverList: DBI.Connection class-initialization. (line 6) * upTo_: Sockets.ReadBuffer-accessing-reading. (line 15) * upToEnd: Sockets.ReadBuffer-accessing-reading. (line 20) * utf16Encoding: I18N.EncodedString-accessing. (line 33) * utf32Encoding: I18N.EncodedString-accessing. (line 36) * value <1>: BLOX.BToggle-accessing. (line 17) * value <2>: BLOX.BRadioGroup-accessing. (line 6) * value <3>: BLOX.BRadioButton-accessing. (line 14) * value <4>: BLOX.BProgress-accessing. (line 32) * value: BLOX.BCheckMenuItem-accessing. (line 9) * value_ <1>: I18N.RunTimeExpression-computing. (line 10) * value_ <2>: BLOX.BToggle-accessing. (line 20) * value_ <3>: BLOX.BRadioGroup-accessing. (line 11) * value_ <4>: BLOX.BRadioButton-accessing. (line 18) * value_ <5>: BLOX.BProgress-accessing. (line 35) * value_: BLOX.BCheckMenuItem-accessing. (line 12) * valueAt_: I18N.EncodedString-accessing. (line 39) * valueAt_put_: I18N.EncodedString-accessing. (line 42) * valueWithoutBuffering_ <1>: Sockets.TCPSocketImpl-socket options. (line 6) * valueWithoutBuffering_: Sockets.AbstractSocketImpl-socket options. (line 43) * variable_: BLOX.BToggle-accessing. (line 24) * version <1>: Sockets.IPAddress class-constants. (line 9) * version: Sockets.IP6Address class-constants. (line 9) * vertical: BLOX.BViewport-scrollbars. (line 21) * vertical_: BLOX.BViewport-scrollbars. (line 25) * verticalNeeded: BLOX.BViewport-scrollbars. (line 28) * verticalShown: BLOX.BViewport-scrollbars. (line 32) * waitForConnection: Sockets.ServerSocket-accessing. (line 26) * waitForException: Sockets.AbstractSocketImpl-asynchronous operations. (line 14) * white <1>: BLOX.BTextAttributes-colors. (line 33) * white: BLOX.BTextAttributes class-instance-creation shortcuts. (line 76) * widget: BLOX.BEventSet-accessing. (line 6) * width <1>: BLOX.BWindow-widget protocol. (line 77) * width <2>: BLOX.BWidget-geometry management. (line 180) * width <3>: BLOX.BRectangle-accessing. (line 12) * width <4>: BLOX.BPolyline-accessing. (line 62) * width: BLOX.BLine-accessing. (line 15) * width_ <1>: BLOX.BWindow-widget protocol. (line 81) * width_ <2>: BLOX.BWidget-geometry management. (line 192) * width_ <3>: BLOX.BRectangle-accessing. (line 15) * width_ <4>: BLOX.BPolyline-accessing. (line 66) * width_: BLOX.BLine-accessing. (line 18) * width_height_ <1>: BLOX.BWindow-widget protocol. (line 84) * width_height_: BLOX.BWidget-geometry management. (line 199) * widthAbsolute <1>: BLOX.BWindow-widget protocol. (line 88) * widthAbsolute: BLOX.BWidget-geometry management. (line 203) * widthChild_ <1>: BLOX.BWidget-geometry management. (line 207) * widthChild_ <2>: BLOX.BText-geometry management. (line 37) * widthChild_ <3>: BLOX.BPopupWindow-geometry management. (line 46) * widthChild_: BLOX.BCanvas-geometry management. (line 42) * widthOffset: BLOX.BWidget-geometry management. (line 217) * widthOffset_ <1>: BLOX.BWindow-widget protocol. (line 92) * widthOffset_: BLOX.BWidget-geometry management. (line 222) * widthPixels_: BLOX.BWidget-geometry management. (line 228) * window <1>: BLOX.BWindow-widget protocol. (line 95) * window: BLOX.Blox-widget protocol. (line 60) * with_with_with_with_: Sockets.IPAddress class-instance creation. (line 74) * withChildrenDo_: BLOX.Blox-widget protocol. (line 64) * withFileDo_: I18N.FileStreamSegment-basic. (line 9) * wrap: BLOX.BText-accessing. (line 119) * wrap_: BLOX.BText-accessing. (line 132) * writeBoolean_on_: DBI.FieldConverter-converting-smalltalk. (line 6) * writeBufferSize: Sockets.Socket class-accessing. (line 6) * writeBufferSize_ <1>: Sockets.Socket-stream protocol. (line 27) * writeBufferSize_: Sockets.Socket class-accessing. (line 9) * writeDate_on_: DBI.FieldConverter-converting-smalltalk. (line 9) * writeDateTime_on_: DBI.FieldConverter-converting-smalltalk. (line 12) * writeFloat_on_: DBI.FieldConverter-converting-smalltalk. (line 15) * writeInteger_on_: DBI.FieldConverter-converting-smalltalk. (line 18) * writeQuotedDate_on_: DBI.FieldConverter-converting-smalltalk. (line 21) * writeQuotedTime_on_: DBI.FieldConverter-converting-smalltalk. (line 24) * writeTime_on_: DBI.FieldConverter-converting-smalltalk. (line 27) * x <1>: BLOX.BWindow-widget protocol. (line 98) * x: BLOX.BWidget-geometry management. (line 234) * x_ <1>: BLOX.BWindow-widget protocol. (line 103) * x_: BLOX.BWidget-geometry management. (line 245) * x_y_ <1>: BLOX.BWindow-widget protocol. (line 107) * x_y_: BLOX.BWidget-geometry management. (line 252) * x_y_width_height_ <1>: BLOX.BWindow-widget protocol. (line 111) * x_y_width_height_: BLOX.BWidget-geometry management. (line 256) * xAbsolute <1>: BLOX.BWindow-widget protocol. (line 115) * xAbsolute: BLOX.BWidget-geometry management. (line 259) * xChild_ <1>: BLOX.BWidget-geometry management. (line 263) * xChild_ <2>: BLOX.BText-geometry management. (line 40) * xChild_ <3>: BLOX.BPopupWindow-geometry management. (line 50) * xChild_: BLOX.BCanvas-geometry management. (line 45) * xOffset: BLOX.BWidget-geometry management. (line 273) * xOffset_ <1>: BLOX.BWindow-widget protocol. (line 120) * xOffset_: BLOX.BWidget-geometry management. (line 278) * xPixels_: BLOX.BWidget-geometry management. (line 284) * xRoot: BLOX.BWidget-geometry management. (line 290) * y <1>: BLOX.BWindow-widget protocol. (line 123) * y: BLOX.BWidget-geometry management. (line 295) * y_ <1>: BLOX.BWindow-widget protocol. (line 128) * y_: BLOX.BWidget-geometry management. (line 306) * yAbsolute <1>: BLOX.BWindow-widget protocol. (line 132) * yAbsolute: BLOX.BWidget-geometry management. (line 313) * yChild_ <1>: BLOX.BWidget-geometry management. (line 317) * yChild_ <2>: BLOX.BText-geometry management. (line 45) * yChild_ <3>: BLOX.BPopupWindow-geometry management. (line 54) * yChild_: BLOX.BCanvas-geometry management. (line 49) * yellow <1>: BLOX.BTextAttributes-colors. (line 36) * yellow: BLOX.BTextAttributes class-instance-creation shortcuts. (line 79) * yOffset: BLOX.BWidget-geometry management. (line 327) * yOffset_ <1>: BLOX.BWindow-widget protocol. (line 137) * yOffset_: BLOX.BWidget-geometry management. (line 332) * yPixels_: BLOX.BWidget-geometry management. (line 338) * yRoot: BLOX.BWidget-geometry management. (line 344) * zero: Complex-creation/coercion. (line 30) * ~=: Complex-comparing. (line 24)  File: gst-libs.info, Node: Cross-reference, Prev: Method index, Up: Top Selector cross-reference ************************ [index] * Menu: * accept: Sockets.ServerSocket class-instance creation. (line 6) * addChild_: BLOX.Blox-customization. (line 13) * addEventSet_: BLOX.BEventSet class-initializing. (line 9) * addMenuItemFor_notifying_: BLOX.BMenu-callback registration. (line 17) * at_ <1>: BLOX.BList-accessing. (line 282) * at_: BLOX.BDropDown-list box accessing. (line 77) * backgroundColor_: BLOX.Blox-creating children. (line 6) * basicAddChild_ <1>: BLOX.BPopupWindow-geometry management. (line 6) * basicAddChild_ <2>: BLOX.Blox-customization. (line 6) * basicAddChild_: BLOX.BCanvas-geometry management. (line 6) * bevel: BLOX.BPolyline-accessing. (line 37) * bottomCenter: BLOX.BLabel-accessing. (line 6) * bottomLeft: BLOX.BLabel-accessing. (line 6) * bottomRight: BLOX.BLabel-accessing. (line 6) * butt <1>: BLOX.BPolyline-accessing. (line 16) * butt: BLOX.BLine-accessing. (line 6) * canRead: Sockets.AbstractSocket-accessing. (line 11) * center <1>: BLOX.BLabel-accessing. (line 6) * center: BLOX.BEmbeddedText-accessing. (line 55) * char: BLOX.BText-accessing. (line 119) * contents: ZLib.ZlibWriteStream-streaming. (line 11) * copy: BLOX.BCanvasObject-accessing. (line 23) * copyObject: BLOX.BCanvasObject-accessing. (line 23) * create <1>: BLOX.BPolyline-accessing. (line 55) * create <2>: BLOX.BExtended-customization. (line 6) * create: BLOX.BBoundingBox-accessing. (line 12) * destroy: BLOX.BWidget class-popups. (line 6) * dispatch_: BLOX.BDialog-accessing. (line 6) * dispatchEvents: BLOX.Blox class-event dispatching. (line 6) * eventTest: BLOX.BEventTarget-intercepting events. (line 43) * font <1>: BLOX.Blox-widget protocol. (line 40) * font: BLOX.BDropDown-flexibility. (line 15) * fromString_ <1>: Sockets.SocketAddress class-host name lookup. (line 12) * fromString_: Sockets.IPAddress-accessing. (line 6) * height: BLOX.BWidget-geometry management. (line 12) * height_ <1>: BLOX.BWidget-geometry management. (line 12) * height_: BLOX.Blox-creating children. (line 6) * heightOffset_: BLOX.BWidget-geometry management. (line 23) * initialize_: BLOX.BWidget-customization. (line 29) * inset_: BLOX.BWidget-geometry management. (line 146) * left: BLOX.BEmbeddedText-accessing. (line 55) * leftCenter: BLOX.BLabel-accessing. (line 6) * loopbackHost: Sockets.IPAddress class-instance creation. (line 21) * macintosh: BLOX.Blox class-utility. (line 69) * make_: BLOX.Blox-creating children. (line 15) * map: BLOX.BWindow-widget protocol. (line 70) * miter: BLOX.BPolyline-accessing. (line 37) * modalMap: BLOX.BDialog-widget protocol. (line 21) * new_: BLOX.BWidget-customization. (line 20) * newPrimitive: BLOX.BExtended-customization. (line 6) * next: I18N.EncodedStream class-initializing. (line 10) * nextPut_ <1>: ZLib.RawDeflateStream class-instance creation. (line 6) * nextPut_ <2>: ZLib.GZipDeflateStream class-instance creation. (line 6) * nextPut_: ZLib.DeflateStream class-instance creation. (line 6) * none: BLOX.BText-accessing. (line 119) * object_address_port_: Sockets.Datagram-accessing. (line 24) * object_objectDumper_address_port_ <1>: Sockets.Datagram-accessing. (line 29) * object_objectDumper_address_port_: Sockets.Datagram class-instance creation. (line 13) * onKeyEvent_send_to_: BLOX.BEventTarget-intercepting events. (line 43) * position: ZLib.RawInflateStream-positioning. (line 6) * print_time_format_on_: I18N.LcTime-printing. (line 11) * printOn_: I18N.EncodedString-printing. (line 6) * projecting <1>: BLOX.BPolyline-accessing. (line 16) * projecting: BLOX.BLine-accessing. (line 6) * readStream: ZLib.ZlibWriteStream-streaming. (line 46) * redraw <1>: BLOX.BPolyline-accessing. (line 55) * redraw: BLOX.BBoundingBox-accessing. (line 12) * registerImage_: BLOX.BText-images. (line 6) * right: BLOX.BEmbeddedText-accessing. (line 55) * rightCenter: BLOX.BLabel-accessing. (line 6) * round <1>: BLOX.BPolyline-accessing. (line 16) * round: BLOX.BLine-accessing. (line 6) * rowsAffected: DBI.Connection-querying. (line 6) * skip_: ZLib.RawInflateStream-positioning. (line 14) * state: BLOX.Blox-widget protocol. (line 26) * state_: BLOX.Blox-widget protocol. (line 31) * tabStop_: BLOX.BWidget-widget protocol. (line 22) * terminateMainLoop: BLOX.Blox class-event dispatching. (line 6) * topCenter: BLOX.BLabel-accessing. (line 6) * topLeft: BLOX.BLabel-accessing. (line 6) * toplevel: BLOX.Blox-widget protocol. (line 60) * topRight: BLOX.BLabel-accessing. (line 6) * unix: BLOX.Blox class-utility. (line 69) * unmap: BLOX.BWindow-widget protocol. (line 70) * upTo_: ZLib.ZlibStream-streaming. (line 12) * width: BLOX.BWidget-geometry management. (line 40) * width_ <1>: BLOX.BWidget-geometry management. (line 40) * width_: BLOX.Blox-creating children. (line 6) * widthOffset_: BLOX.BWidget-geometry management. (line 51) * windows: BLOX.Blox class-utility. (line 69) * word: BLOX.BText-accessing. (line 119) * x: BLOX.BWidget-geometry management. (line 61) * x_: BLOX.BWidget-geometry management. (line 61) * xOffset_: BLOX.BWidget-geometry management. (line 71) * y: BLOX.BWidget-geometry management. (line 81) * y_: BLOX.BWidget-geometry management. (line 81) * yOffset_: BLOX.BWidget-geometry management. (line 91) smalltalk-3.2.5/doc/gst-libs.info-10000644000175000017500000111175412130456010013734 00000000000000This is gst-libs.info, produced by makeinfo version 4.13 from /home/ich/source/smalltalk/release/smalltalk/doc/gst-libs-fixed.texi. INFO-DIR-SECTION Software development START-INFO-DIR-ENTRY * Smalltalk libraries: (gst-libs). The GNU Smalltalk class libraries. END-INFO-DIR-ENTRY Permission is granted to copy, distribute and/or modify this document under the terms of the GNU Free Documentation License, Version 1.2 or any later version published by the Free Software Foundation; with no Invariant Sections, with no Front-Cover Texts, and with no Back-Cover Texts. A copy of the license is included in the section entitled "GNU Free Documentation License".  File: gst-libs.info, Node: Top, Up: (DIR) GNU Smalltalk Library Reference ******************************* GNU Smalltalk Library Reference This document describes the class libraries that are distributed together with the GNU Smalltalk programming language. Permission is granted to copy, distribute and/or modify this document under the terms of the GNU Free Documentation License, Version 1.2 or any later version published by the Free Software Foundation; with no Invariant Sections, with no Front-Cover Texts, and with no Back-Cover Texts. A copy of the license is included in the section entitled "GNU Free Documentation License". * Menu: * BLOX package:: The GUI library * Complex package:: Complex number computations * DBI package:: The database connectivity library * DebugTools package:: Controlling the execution of Smalltalk processes * Sockets package:: The sockets library * Iconv/I18N packages:: The internationalization library * XML/XPath/XSL packages:: Using the XML library * ZLib package:: Bindings to the popular data compression library * Class index:: Index to the classes in the class reference * Method index:: Index to the method selectors in the class reference * Cross-reference:: Cross-reference between selectors  File: gst-libs.info, Node: BLOX package, Next: Complex package, Prev: Top, Up: Top 1 Graphical users interfaces with BLOX ************************************** * Menu: Alphabetic list: * BLOX.BArc:: * BLOX.BBalloon:: * BLOX.BBoundingBox:: * BLOX.BButton:: * BLOX.BButtonLike:: * BLOX.BCanvas:: * BLOX.BCanvasObject:: * BLOX.BCheckMenuItem:: * BLOX.BColorButton:: * BLOX.BContainer:: * BLOX.BDialog:: * BLOX.BDropDown:: * BLOX.BDropDownEdit:: * BLOX.BDropDownList:: * BLOX.BEdit:: * BLOX.BEmbeddedImage:: * BLOX.BEmbeddedText:: * BLOX.BEventSet:: * BLOX.BEventTarget:: * BLOX.BExtended:: * BLOX.BForm:: * BLOX.BImage:: * BLOX.BLabel:: * BLOX.BLine:: * BLOX.BList:: * BLOX.Blox:: * BLOX.BMenu:: * BLOX.BMenuBar:: * BLOX.BMenuItem:: * BLOX.BMenuObject:: * BLOX.BOval:: * BLOX.BPolyline:: * BLOX.BPopupMenu:: * BLOX.BPopupWindow:: * BLOX.BPrimitive:: * BLOX.BProgress:: * BLOX.BRadioButton:: * BLOX.BRadioGroup:: * BLOX.BRectangle:: * BLOX.BScrolledCanvas:: * BLOX.BSpline:: * BLOX.BText:: * BLOX.BTextAttributes:: * BLOX.BTextBindings:: * BLOX.BTextTags:: * BLOX.BToggle:: * BLOX.BTransientWindow:: * BLOX.BViewport:: * BLOX.BWidget:: * BLOX.BWindow:: * BLOX.Gui:: Class tree: (Object) * BLOX.BEventTarget:: * BLOX.BCanvasObject:: * BLOX.BBoundingBox:: * BLOX.BEmbeddedImage:: * BLOX.BEmbeddedText:: * BLOX.BLine:: * BLOX.BRectangle:: * BLOX.BOval:: * BLOX.BArc:: * BLOX.BPolyline:: * BLOX.BSpline:: * BLOX.BEventSet:: * BLOX.BBalloon:: * BLOX.Blox:: * BLOX.BMenuObject:: * BLOX.BMenu:: * BLOX.BPopupMenu:: * BLOX.BMenuBar:: * BLOX.BMenuItem:: * BLOX.BCheckMenuItem:: * BLOX.BWidget:: * BLOX.BExtended:: * BLOX.BButtonLike:: * BLOX.BColorButton:: * BLOX.BDropDown:: * BLOX.BDropDownEdit:: * BLOX.BDropDownList:: * BLOX.BProgress:: * BLOX.BPrimitive:: * BLOX.BButton:: * BLOX.BRadioButton:: * BLOX.BToggle:: * BLOX.BEdit:: * BLOX.BForm:: * BLOX.BContainer:: * BLOX.BRadioGroup:: * BLOX.BDialog:: * BLOX.BWindow:: * BLOX.BPopupWindow:: * BLOX.BTransientWindow:: * BLOX.BImage:: * BLOX.BLabel:: * BLOX.BViewport:: * BLOX.BCanvas:: * BLOX.BScrolledCanvas:: * BLOX.BList:: * BLOX.BText:: * BLOX.BTextBindings:: * BLOX.BTextAttributes:: * BLOX.BTextTags:: * BLOX.Gui::  File: gst-libs.info, Node: BLOX.BArc, Next: BLOX.BBalloon, Up: BLOX package 1.1 BLOX.BArc ============= Defined in namespace BLOX Superclass: BLOX.BOval Category: Graphics-Windows I can draw arcs, pie slices (don't eat them!!), chords, and... nothing more. * Menu: * BLOX.BArc-accessing:: (instance)  File: gst-libs.info, Node: BLOX.BArc-accessing, Up: BLOX.BArc 1.1.1 BLOX.BArc: accessing -------------------------- endAngle Answer the ending of the angular range that is occupied by the arc, expressed in degrees endAngle: angle Set the ending of the angular range that is occupied by the arc, expressed in degrees fillChord Specify that the arc will be filled by painting an area delimited by the arc and the chord that joins the arc's endpoints. fillSlice Specify that the arc will be filled by painting an area delimited by the arc and the two radii joins the center of the arc with each of the endpoints (that is, that a pie slice will be drawn). from Answer the starting point of the arc in cartesian coordinates from: aPoint Set the starting point of the arc in cartesian coordinates from: start to: end Set the two starting points of the arc in cartesian coordinates startAngle Answer the beginning of the angular range that is occupied by the arc, expressed in degrees startAngle: angle Set the beginning of the angular range that is occupied by the arc, expressed in degrees sweepAngle Answer the size of the angular range that is occupied by the arc, expressed in degrees sweepAngle: angle Set the size of the angular range that is occupied by the arc, expressed in degrees to Answer the ending point of the arc in cartesian coordinates to: aPoint Set the ending point of the arc in cartesian coordinates  File: gst-libs.info, Node: BLOX.BBalloon, Next: BLOX.BBoundingBox, Prev: BLOX.BArc, Up: BLOX package 1.2 BLOX.BBalloon ================= Defined in namespace BLOX Superclass: BLOX.BEventSet Category: Graphics-Examples This event set allows a widget to show explanatory information when the mouse lingers over it for a while. * Menu: * BLOX.BBalloon class-accessing:: (class) * BLOX.BBalloon-accessing:: (instance) * BLOX.BBalloon-initializing:: (instance)  File: gst-libs.info, Node: BLOX.BBalloon class-accessing, Next: BLOX.BBalloon-accessing, Up: BLOX.BBalloon 1.2.1 BLOX.BBalloon class: accessing ------------------------------------ balloonDelayTime Answer the time after which the balloon is shown (default is half a second). balloonDelayTime: milliseconds Set the time after which the balloon is shown. shown Answer whether a balloon is displayed  File: gst-libs.info, Node: BLOX.BBalloon-accessing, Next: BLOX.BBalloon-initializing, Prev: BLOX.BBalloon class-accessing, Up: BLOX.BBalloon 1.2.2 BLOX.BBalloon: accessing ------------------------------ shown Answer whether the receiver's balloon is displayed text Answer the text displayed in the balloon text: aString Set the text displayed in the balloon to aString  File: gst-libs.info, Node: BLOX.BBalloon-initializing, Prev: BLOX.BBalloon-accessing, Up: BLOX.BBalloon 1.2.3 BLOX.BBalloon: initializing --------------------------------- initialize: aBWidget Initialize the event sets for the receiver  File: gst-libs.info, Node: BLOX.BBoundingBox, Next: BLOX.BButton, Prev: BLOX.BBalloon, Up: BLOX package 1.3 BLOX.BBoundingBox ===================== Defined in namespace BLOX Superclass: BLOX.BCanvasObject Category: Graphics-Windows I am the ultimate ancestor of all items that you can put in a BCanvas and which are well defined by their bounding box - i.e. everything except BPolylines and BSplines. * Menu: * BLOX.BBoundingBox-accessing:: (instance)  File: gst-libs.info, Node: BLOX.BBoundingBox-accessing, Up: BLOX.BBoundingBox 1.3.1 BLOX.BBoundingBox: accessing ---------------------------------- boundingBox Answer a Rectangle enclosing all of the receiver center Answer the center point of the receiver center: center extent: extent Move the object so that it is centered around the center Point and its size is given by the extent Point. No changes take place until you invoke the #create (if the object has not been inserted in the canvas yet) or the #redraw method. corner Answer the Point specifying the lower-right corner of the receiver corner: pointOrArray Set the Point specifying the lower-right corner of the receiver; pointOrArray can be a Point or a two-item Array. No changes take place until you invoke the #create (if the object has not been inserted in the canvas yet) or the #redraw method. extent Answer a Point specifying the size of the receiver extent: pointOrArray Set the Point specifying the size of the receiver; pointOrArray can be a Point or a two-item Array. No changes take place until you invoke the #create (if the object has not been inserted in the canvas yet) or the #redraw method. moveBy: pointOrArray Move the object by the amount indicated by pointOrArray: that is, its whole bounding box is shifted by that amount. No changes take place until you invoke the #create (if the object has not been inserted in the canvas yet) or the #redraw method. origin Answer the Point specifying the top-left corner of the receiver origin: pointOrArray Set the Point specifying the top-left corner of the receiver; pointOrArray can be a Point or a two-item Array. No changes take place until you invoke the #create (if the object has not been inserted in the canvas yet) or the #redraw method. origin: originPointOrArray corner: cornerPointOrArray Set the bounding box of the object, based on a Point specifying the top-left corner of the receiver and another specifying the bottom-right corner; the two parameters can both be Points or two-item Arrays. No changes take place until you invoke the #create (if the object has not been inserted in the canvas yet) or the #redraw method. origin: originPointOrArray extent: extentPointOrArray Set the bounding box of the object, based on a Point specifying the top-left corner of the receiver and another specifying its size; the two parameters can both be Points or two-item Arrays. No changes take place until you invoke the #create (if the object has not been inserted in the canvas yet) or the #redraw method.  File: gst-libs.info, Node: BLOX.BButton, Next: BLOX.BButtonLike, Prev: BLOX.BBoundingBox, Up: BLOX package 1.4 BLOX.BButton ================ Defined in namespace BLOX Superclass: BLOX.BPrimitive Category: Graphics-Windows I am a button that a user can click. In fact I am at the head of a small hierarchy of objects which exhibit button-like look and behavior * Menu: * BLOX.BButton class-instance creation:: (class) * BLOX.BButton-accessing:: (instance)  File: gst-libs.info, Node: BLOX.BButton class-instance creation, Next: BLOX.BButton-accessing, Up: BLOX.BButton 1.4.1 BLOX.BButton class: instance creation ------------------------------------------- new: parent label: label Answer a new BButton widget laid inside the given parent widget, showing by default the `label' String.  File: gst-libs.info, Node: BLOX.BButton-accessing, Prev: BLOX.BButton class-instance creation, Up: BLOX.BButton 1.4.2 BLOX.BButton: accessing ----------------------------- backgroundColor Answer the value of the backgroundColor option for the widget. Specifies the normal background color to use when displaying the widget. backgroundColor: value Set the value of the backgroundColor option for the widget. Specifies the normal background color to use when displaying the widget. callback Answer a DirectedMessage that is sent when the receiver is clicked, or nil if none has been set up. callback: aReceiver message: aSymbol Set up so that aReceiver is sent the aSymbol message (the name of a zero- or one-argument selector) when the receiver is clicked. If the method accepts an argument, the receiver is passed. font Answer the value of the font option for the widget. Specifies the font to use when drawing text inside the widget. The font can be given as either an X font name or a Blox font description string. X font names are given as many fields, each led by a minus, and each of which can be replaced by an * to indicate a default value is ok: foundry, family, weight, slant, setwidth, addstyle, pixel size, point size (the same as pixel size for historical reasons), horizontal resolution, vertical resolution, spacing, width, charset and character encoding. Blox font description strings have three fields, which must be separated by a space and of which only the first is mandatory: the font family, the font size in points (or in pixels if a negative value is supplied), and a number of styles separated by a space (valid styles are normal, bold, italic, underline and overstrike). Examples of valid fonts are "Helvetica 10 Bold", "Times -14", "Futura Bold Underline". You must enclose the font family in braces if it is made of two or more words. font: value Set the value of the font option for the widget. Specifies the font to use when drawing text inside the widget. The font can be given as either an X font name or a Blox font description string. X font names are given as many fields, each led by a minus, and each of which can be replaced by an * to indicate a default value is ok: foundry, family, weight, slant, setwidth, addstyle, pixel size, point size (the same as pixel size for historical reasons), horizontal resolution, vertical resolution, spacing, width, charset and character encoding. Blox font description strings have three fields, which must be separated by a space and of which only the first is mandatory: the font family, the font size in points (or in pixels if a negative value is supplied), and a number of styles separated by a space (valid styles are normal, bold, italic, underline and overstrike). Examples of valid fonts are "Helvetica 10 Bold", "Times -14", "Futura Bold Underline". You must enclose the font family in braces if it is made of two or more words. foregroundColor Answer the value of the foregroundColor option for the widget. Specifies the normal foreground color to use when displaying the widget. foregroundColor: value Set the value of the foregroundColor option for the widget. Specifies the normal foreground color to use when displaying the widget. invokeCallback Generate a synthetic callback label Answer the value of the label option for the widget. Specifies a string to be displayed inside the widget. The way in which the string is displayed depends on the particular widget and may be determined by other options, such as anchor. For windows, this is the title of the window. label: value Set the value of the label option for the widget. Specifies a string to be displayed inside the widget. The way in which the string is displayed depends on the particular widget and may be determined by other options, such as anchor. For windows, this is the title of the window.  File: gst-libs.info, Node: BLOX.BButtonLike, Next: BLOX.BCanvas, Prev: BLOX.BButton, Up: BLOX package 1.5 BLOX.BButtonLike ==================== Defined in namespace BLOX Superclass: BLOX.BExtended Category: Graphics-Examples I am an object whose 3-D appearance resembles that of buttons. * Menu: * BLOX.BButtonLike-accessing:: (instance)  File: gst-libs.info, Node: BLOX.BButtonLike-accessing, Up: BLOX.BButtonLike 1.5.1 BLOX.BButtonLike: accessing --------------------------------- callback Answer a DirectedMessage that is sent when the receiver is clicked, or nil if none has been set up. callback: aReceiver message: aSymbol Set up so that aReceiver is sent the aSymbol message (the name of a zero- or one-argument selector) when the receiver is clicked. If the method accepts an argument, the receiver is passed. invokeCallback Generate a synthetic callback pressed This is the default callback for the widget; it does nothing if you don't override it. Of course if a subclass overriddes this you (user of the class) might desire to call this method from your own callback.  File: gst-libs.info, Node: BLOX.BCanvas, Next: BLOX.BCanvasObject, Prev: BLOX.BButtonLike, Up: BLOX package 1.6 BLOX.BCanvas ================ Defined in namespace BLOX Superclass: BLOX.BViewport Category: Graphics-Windows I am an host for whatever geometric shape you want. If you want to do some fancy graphics with Smalltalk, I'll be happy to help. My friends derived from BCanvasObject ask me all sort of things to do, so I am the real worker, not they! BCanvasObject: I am BCanvas: No I am BCanvasObject: No I am BCanvas: No I am well, you know, he always has something to object. * Menu: * BLOX.BCanvas-accessing:: (instance) * BLOX.BCanvas-geometry management:: (instance) * BLOX.BCanvas-widget protocol:: (instance)  File: gst-libs.info, Node: BLOX.BCanvas-accessing, Next: BLOX.BCanvas-geometry management, Up: BLOX.BCanvas 1.6.1 BLOX.BCanvas: accessing ----------------------------- backgroundColor Answer the value of the backgroundColor option for the widget. Specifies the normal background color to use when displaying the widget. backgroundColor: value Set the value of the backgroundColor option for the widget. Specifies the normal background color to use when displaying the widget. foregroundColor Answer the value of the foregroundColor option for the widget. Specifies the normal foreground color to use when displaying the widget. foregroundColor: value Set the value of the foregroundColor option for the widget. Specifies the normal foreground color to use when displaying the widget.  File: gst-libs.info, Node: BLOX.BCanvas-geometry management, Next: BLOX.BCanvas-widget protocol, Prev: BLOX.BCanvas-accessing, Up: BLOX.BCanvas 1.6.2 BLOX.BCanvas: geometry management --------------------------------------- addChild: child The widget identified by child has been added to the receiver. This method is public not because you can call it, but because it can be useful to override it, not forgetting the call to either the superclass implementation or #basicAddChild:, to perform some initialization on the children just added. Answer the new child. child: child height: value Set the given child's height. child: child heightOffset: value Offset the given child's height by value pixels. child: child width: value Set the given child's width. child: child widthOffset: value Offset the given child's width by value pixels. child: child x: value Set the given child's top-left corner's x coordinate, in pixels in the canvas' coordinate system. child: child xOffset: value Offset the given child's top-left x by value pixels. child: child y: value Set the given child's top-left corner's y coordinate, in pixels in the canvas' coordinate system. child: child yOffset: value Offset the given child's top-left y by value pixels. heightChild: child Answer the given child's height in pixels. widthChild: child Answer the given child's width in pixels. xChild: child Answer the given child's top-left corner's x coordinate, in pixels in the canvas' coordinate system. yChild: child Answer the given child's top-left corner's y coordinate, in pixels in the canvas' coordinate system.  File: gst-libs.info, Node: BLOX.BCanvas-widget protocol, Prev: BLOX.BCanvas-geometry management, Up: BLOX.BCanvas 1.6.3 BLOX.BCanvas: widget protocol ----------------------------------- at: aPoint Selects the topmost item in the canvas overlapping the point given by aPoint. between: origin and: corner do: aBlock Evaluate aBlock for each item whose bounding box intersects the rectangle between the two Points, origin and corner. Pass the item to the block. boundingBox Answer the bounding box of all the items in the canvas destroyed The widget has been destroyed. Tell all of its items about this fact. do: aBlock Evaluate aBlock, passing each item to it. empty Remove all the items from the canvas, leaving it empty extraSpace Answer the amount of space that is left as a border around the canvas items. extraSpace: aPoint Set the amount of space that is left as a border around the canvas items. items Answer an Array containing all the items in the canvas mapPoint: aPoint Given aPoint, a point expressed in window coordinates, answer the corresponding canvas coordinates that are displayed at that location.  File: gst-libs.info, Node: BLOX.BCanvasObject, Next: BLOX.BCheckMenuItem, Prev: BLOX.BCanvas, Up: BLOX package 1.7 BLOX.BCanvasObject ====================== Defined in namespace BLOX Superclass: BLOX.BEventTarget Category: Graphics-Windows I am the ultimate ancestor of all items that you can put in a BCanvas. I provide some general methods to my concrete offspring. * Menu: * BLOX.BCanvasObject class-instance creation:: (class) * BLOX.BCanvasObject-accessing:: (instance) * BLOX.BCanvasObject-widget protocol:: (instance)  File: gst-libs.info, Node: BLOX.BCanvasObject class-instance creation, Next: BLOX.BCanvasObject-accessing, Up: BLOX.BCanvasObject 1.7.1 BLOX.BCanvasObject class: instance creation ------------------------------------------------- new This method should not be called for instances of this class. new: parentCanvas Answer a new instance of the receiver, displayed into the given parentCanvas.  File: gst-libs.info, Node: BLOX.BCanvasObject-accessing, Next: BLOX.BCanvasObject-widget protocol, Prev: BLOX.BCanvasObject class-instance creation, Up: BLOX.BCanvasObject 1.7.2 BLOX.BCanvasObject: accessing ----------------------------------- blox Answer the parent canvas of the receiver boundingBox Answer a Rectangle enclosing all of the receiver color Answer the color to be used to fill this item's area. color: color Set the color to be used to fill this item's area. copyInto: newCanvas Answer a new BCanvasObject identical to this but displayed into another canvas, newCanvas. The new instance is not created at the time it is returned. copyObject Answer a new BCanvasObject identical to this. Unlike #copy, which merely creates a new Smalltalk object with the same data and referring to the same canvas item, the object created with #copyObject is physically distinct from the original. The new instance is not created at the time it is returned. createCopy Answer a new BCanvasObject identical to this. Unlike #copy, which merely creates a new Smalltalk object with the same data and referring to the same canvas item, the object created with #copyObject is physically distinct from the original. The new instance has already been created at the time it is returned. createCopyInto: newCanvas Answer a new BCanvasObject identical to this but displayed into another canvas, newCanvas. The new instance has already been created at the time it is returned. deepCopy It does not make sense to make a copy, because it would make data inconsistent across different objects; so answer the receiver grayOut Apply a 50% gray stippling pattern to the object shallowCopy It does not make sense to make a copy, because it would make data inconsistent across different objects; so answer the receiver  File: gst-libs.info, Node: BLOX.BCanvasObject-widget protocol, Prev: BLOX.BCanvasObject-accessing, Up: BLOX.BCanvasObject 1.7.3 BLOX.BCanvasObject: widget protocol ----------------------------------------- create If the object has not been created yet and has been initialized correctly, insert it for real in the parent canvas created Answer whether the object is just a placeholder or has already been inserted for real in the parent canvas lower Move the item to the lowest position in the display list. Child widgets always obscure other item types, and the stacking order of window items is determined by sending methods to the widget object directly. raise Move the item to the highest position in the display list. Child widgets always obscure other item types, and the stacking order of window items is determined by sending methods to the widget object directly. redraw Force the object to be displayed in the parent canvas, creating it if it has not been inserted for real in the parent, and refresh its position if it has changed. remove Remove the object from the canvas show Ensure that the object is visible in the center of the canvas, scrolling it if necessary.  File: gst-libs.info, Node: BLOX.BCheckMenuItem, Next: BLOX.BColorButton, Prev: BLOX.BCanvasObject, Up: BLOX package 1.8 BLOX.BCheckMenuItem ======================= Defined in namespace BLOX Superclass: BLOX.BMenuItem Category: Graphics-Windows I am a menu item which can be toggled between two states, marked and unmarked. * Menu: * BLOX.BCheckMenuItem class-instance creation:: (class) * BLOX.BCheckMenuItem-accessing:: (instance)  File: gst-libs.info, Node: BLOX.BCheckMenuItem class-instance creation, Next: BLOX.BCheckMenuItem-accessing, Up: BLOX.BCheckMenuItem 1.8.1 BLOX.BCheckMenuItem class: instance creation -------------------------------------------------- new: parent This method should not be called for instances of this class.  File: gst-libs.info, Node: BLOX.BCheckMenuItem-accessing, Prev: BLOX.BCheckMenuItem class-instance creation, Up: BLOX.BCheckMenuItem 1.8.2 BLOX.BCheckMenuItem: accessing ------------------------------------ invokeCallback Generate a synthetic callback value Answer whether the menu item is in a selected (checked) state. value: aBoolean Set whether the button is in a selected (checked) state and generates a callback accordingly.  File: gst-libs.info, Node: BLOX.BColorButton, Next: BLOX.BContainer, Prev: BLOX.BCheckMenuItem, Up: BLOX package 1.9 BLOX.BColorButton ===================== Defined in namespace BLOX Superclass: BLOX.BButtonLike Category: Graphics-Examples I am a button that shows a color and that, unless a different callback is used, lets you choose a color when it is clicked. * Menu: * BLOX.BColorButton-accessing:: (instance)  File: gst-libs.info, Node: BLOX.BColorButton-accessing, Up: BLOX.BColorButton 1.9.1 BLOX.BColorButton: accessing ---------------------------------- color Set the color that the receiver is painted in. color: aString Set the color that the receiver is painted in. pressed This is the default callback; it brings up a `choose-a-color' window and, if `Ok' is pressed in the window, sets the receiver to be painted in the chosen color.  File: gst-libs.info, Node: BLOX.BContainer, Next: BLOX.BDialog, Prev: BLOX.BColorButton, Up: BLOX package 1.10 BLOX.BContainer ==================== Defined in namespace BLOX Superclass: BLOX.BForm Category: Graphics-Windows I am used to group many widgets together. I can perform simple management by putting widgets next to each other, from left to right or from top to bottom. * Menu: * BLOX.BContainer-accessing:: (instance)  File: gst-libs.info, Node: BLOX.BContainer-accessing, Up: BLOX.BContainer 1.10.1 BLOX.BContainer: accessing --------------------------------- setVerticalLayout: aBoolean Answer whether the container will align the widgets vertically or horizontally. Horizontal alignment means that widgets are packed from left to right, while vertical alignment means that widgets are packed from the top to the bottom of the widget. Widgets that are set to be "stretched" will share all the space that is not allocated to non-stretched widgets. The layout of the widget can only be set before the first child is inserted in the widget.  File: gst-libs.info, Node: BLOX.BDialog, Next: BLOX.BDropDown, Prev: BLOX.BContainer, Up: BLOX package 1.11 BLOX.BDialog ================= Defined in namespace BLOX Superclass: BLOX.BForm Category: Graphics-Windows I am a facility for implementing dialogs with many possible choices and requests. In addition I provide support for a few platform native common dialog boxes, such as choose-a-file and choose-a-color. * Menu: * BLOX.BDialog class-instance creation:: (class) * BLOX.BDialog class-prompters:: (class) * BLOX.BDialog-accessing:: (instance) * BLOX.BDialog-widget protocol:: (instance)  File: gst-libs.info, Node: BLOX.BDialog class-instance creation, Next: BLOX.BDialog class-prompters, Up: BLOX.BDialog 1.11.1 BLOX.BDialog class: instance creation -------------------------------------------- new: parent Answer a new dialog handler (containing a label widget and some button widgets) laid out within the given parent window. The label widget, when it is created, is empty. new: parent label: aLabel Answer a new dialog handler (containing a label widget and some button widgets) laid out within the given parent window. The label widget, when it is created, contains aLabel. new: parent label: aLabel prompt: aString Answer a new dialog handler (containing a label widget, some button widgets, and an edit window showing aString by default) laid out within the given parent window. The label widget, when it is created, contains aLabel.  File: gst-libs.info, Node: BLOX.BDialog class-prompters, Next: BLOX.BDialog-accessing, Prev: BLOX.BDialog class-instance creation, Up: BLOX.BDialog 1.11.2 BLOX.BDialog class: prompters ------------------------------------ chooseColor: parent label: aLabel default: color Prompt for a color. The dialog box is created with the given parent window and with aLabel as its title bar text, and initially it selects the color given in the color parameter. If the dialog box is canceled, nil is answered, else the selected color is returned as a String with its RGB value. chooseFileToOpen: parent label: aLabel default: name defaultExtension: ext types: typeList Pop up a dialog box for the user to select a file to open. Its purpose is for the user to select an existing file only. If the user enters an non-existent file, the dialog box gives the user an error prompt and requires the user to give an alternative selection or to cancel the selection. If an application allows the user to create new files, it should do so by providing a separate New menu command. If the dialog box is canceled, nil is answered, else the selected file name is returned as a String. The dialog box is created with the given parent window and with aLabel as its title bar text. The name parameter indicates which file is initially selected, and the default extension specifies a string that will be appended to the filename if the user enters a filename without an extension. The typeList parameter is an array of arrays, like #(('Text files' '.txt' '.diz') ('Smalltalk files' '.st')), and is used to construct a listbox of file types. When the user chooses a file type in the listbox, only the files of that type are listed. Each item in the array contains a list of strings: the first one is the name of the file type described by a particular file pattern, and is the text string that appears in the File types listbox, while the other ones are the possible extensions that belong to this particular file type. chooseFileToSave: parent label: aLabel default: name defaultExtension: ext types: typeList Pop up a dialog box for the user to select a file to save; this differs from the file open dialog box in that non-existent file names are accepted and existing file names trigger a confirmation dialog box, asking the user whether the file should be overwritten or not. If the dialog box is canceled, nil is answered, else the selected file name is returned as a String. The dialog box is created with the given parent window and with aLabel as its title bar text. The name parameter indicates which file is initially selected, and the default extension specifies a string that will be appended to the filename if the user enters a filename without an extension. The typeList parameter is an array of arrays, like #(('Text files' '.txt' '.diz') ('Smalltalk files' '.st')), and is used to construct a listbox of file types. When the user chooses a file type in the listbox, only the files of that type are listed. Each item in the array contains a list of strings: the first one is the name of the file type described by a particular file pattern, and is the text string that appears in the File types listbox, while the other ones are the possible extensions that belong to this particular file type.  File: gst-libs.info, Node: BLOX.BDialog-accessing, Next: BLOX.BDialog-widget protocol, Prev: BLOX.BDialog class-prompters, Up: BLOX.BDialog 1.11.3 BLOX.BDialog: accessing ------------------------------ addButton: aLabel receiver: anObject index: anInt Add a button to the dialog box that, when clicked, will cause the #dispatch: method to be triggered in anObject, passing anInt as the argument of the callback. The caption of the button is set to aLabel. addButton: aLabel receiver: anObject message: aSymbol Add a button to the dialog box that, when clicked, will cause the aSymbol unary selector to be sent to anObject. The caption of the button is set to aLabel. addButton: aLabel receiver: anObject message: aSymbol argument: arg Add a button to the dialog box that, when clicked, will cause the aSymbol one-argument selector to be sent to anObject, passing arg as the argument of the callback. The caption of the button is set to aLabel. contents Answer the text that is displayed in the entry widget associated to the dialog box. contents: newText Display newText in the entry widget associated to the dialog box.  File: gst-libs.info, Node: BLOX.BDialog-widget protocol, Prev: BLOX.BDialog-accessing, Up: BLOX.BDialog 1.11.4 BLOX.BDialog: widget protocol ------------------------------------ center Center the dialog box's parent window in the screen centerIn: view Center the dialog box's parent window in the given widget destroyed Private - The receiver has been destroyed, clear the corresponding Tcl variable to avoid memory leaks. invokeCallback: index Generate a synthetic callback corresponding to the index-th button being pressed, and destroy the parent window (triggering its callback if one was established). loop Map the parent window modally. In other words, an event loop is started that ends only after the window has been destroyed. For more information on the treatment of events for modal windows, refer to BWindow>>#modalMap.  File: gst-libs.info, Node: BLOX.BDropDown, Next: BLOX.BDropDownEdit, Prev: BLOX.BDialog, Up: BLOX package 1.12 BLOX.BDropDown =================== Defined in namespace BLOX Superclass: BLOX.BExtended Category: Graphics-Examples This class is an abstract superclass for widgets offering the ability to pick items from a pre-built list. The list is usually hidden, but a button on the right of this widgets makes it pop up. This widget is thus composed of three parts: an unspecified text widget (shown on the left of the button and always visible), the button widget (shown on the right, it depicts a down arrow, and is always visible), and the pop-up list widget. * Menu: * BLOX.BDropDown-accessing:: (instance) * BLOX.BDropDown-callbacks:: (instance) * BLOX.BDropDown-flexibility:: (instance) * BLOX.BDropDown-list box accessing:: (instance) * BLOX.BDropDown-widget protocol:: (instance)  File: gst-libs.info, Node: BLOX.BDropDown-accessing, Next: BLOX.BDropDown-callbacks, Up: BLOX.BDropDown 1.12.1 BLOX.BDropDown: accessing -------------------------------- backgroundColor Answer the value of the backgroundColor for the widget, which in this class is only set for the list widget (that is, the pop-up widget). Subclasses should override this method so that the color is set properly for the text widget as well. Specifies the normal background color to use when displaying the widget. backgroundColor: aColor Set the value of the backgroundColor for the widget, which in this class is only set for the list widget (that is, the pop-up widget). Subclasses should override this method so that the color is set properly for the text widget as well. Specifies the normal background color to use when displaying the widget. droppedRows Answer the number of items that are visible at any time in the listbox. droppedRows: anInteger Set the number of items that are visible at any time in the listbox. font Answer the value of the font option for the widget, which in this class is only set for the list widget (that is, the pop-up widget). Subclasses should override this method so that the color is set properly for the text widget as well. Specifies the font to use when drawing text inside the widget. The font can be given as either an X font name or a Blox font description string. X font names are given as many fields, each led by a minus, and each of which can be replaced by an * to indicate a default value is ok: foundry, family, weight, slant, setwidth, addstyle, pixel size, point size (the same as pixel size for historical reasons), horizontal resolution, vertical resolution, spacing, width, charset and character encoding. Blox font description strings have three fields, which must be separated by a space and of which only the first is mandatory: the font family, the font size in points (or in pixels if a negative value is supplied), and a number of styles separated by a space (valid styles are normal, bold, italic, underline and overstrike). Examples of valid fonts are "Helvetica 10 Bold", "Times -14", "Futura Bold Underline". You must enclose the font family in braces if it is made of two or more words. font: value Set the value of the font option for the widget, which in this class is only set for the list widget (that is, the pop-up widget). Subclasses should override this method so that the color is set properly for the text widget as well. Specifies the font to use when drawing text inside the widget. The font can be given as either an X font name or a Blox font description string. X font names are given as many fields, each led by a minus, and each of which can be replaced by an * to indicate a default value is ok: foundry, family, weight, slant, setwidth, addstyle, pixel size, point size (the same as pixel size for historical reasons), horizontal resolution, vertical resolution, spacing, width, charset and character encoding. Blox font description strings have three fields, which must be separated by a space and of which only the first is mandatory: the font family, the font size in points (or in pixels if a negative value is supplied), and a number of styles separated by a space (valid styles are normal, bold, italic, underline and overstrike). Examples of valid fonts are "Helvetica 10 Bold", "Times -14", "Futura Bold Underline". You must enclose the font family in braces if it is made of two or more words. foregroundColor Answer the value of the foregroundColor for the widget, which in this class is only set for the list widget (that is, the pop-up widget). Subclasses should override this method so that the color is set properly for the text widget as well. Specifies the normal foreground color to use when displaying the widget. foregroundColor: aColor Set the value of the foregroundColor for the widget, which in this class is only set for the list widget (that is, the pop-up widget). Subclasses should override this method so that the color is set properly for the text widget as well. Specifies the normal foreground color to use when displaying the widget. highlightBackground Answer the value of the highlightBackground option for the widget. Specifies the background color to use when displaying selected items in the list widget. highlightBackground: aColor Set the value of the highlightBackground option for the widget. Specifies the background color to use when displaying selected items in the list widget. highlightForeground Answer the value of the highlightForeground option for the widget. Specifies the foreground color to use when displaying selected items in the list widget. highlightForeground: aColor Set the value of the highlightForeground option for the widget. Specifies the foreground color to use when displaying selected items in the list widget.  File: gst-libs.info, Node: BLOX.BDropDown-callbacks, Next: BLOX.BDropDown-flexibility, Prev: BLOX.BDropDown-accessing, Up: BLOX.BDropDown 1.12.2 BLOX.BDropDown: callbacks -------------------------------- callback Answer a DirectedMessage that is sent when the receiver is clicked, or nil if none has been set up. callback: aReceiver message: aSymbol Set up so that aReceiver is sent the aSymbol message (the name of a zero- or one-argument selector) when the receiver is clicked. If the method accepts an argument, the receiver is passed. invokeCallback Generate a synthetic callback  File: gst-libs.info, Node: BLOX.BDropDown-flexibility, Next: BLOX.BDropDown-list box accessing, Prev: BLOX.BDropDown-callbacks, Up: BLOX.BDropDown 1.12.3 BLOX.BDropDown: flexibility ---------------------------------- createList Create the popup widget to be used for the `drop-down list'. It is a BList by default, but you can use any other widget, overriding the `list box accessing' methods if necessary. createTextWidget Create the widget that will hold the string chosen from the list box and answer it. The widget must be a child of `self primitive'. itemHeight Answer the height of an item in the drop-down list. The default implementation assumes that the receiver understands #font, but you can modify it if you want. listCallback Called when an item of the listbox is highlighted. Do nothing by default listSelectAt: aPoint Select the item lying at the given position in the list box. The default implementation assumes that list is a BList, but you can modify it if you want. listText Answer the text currently chosen in the list box. The default implementation assumes that list is a BList, but you can modify it if you want. text Answer the text that the user has picked from the widget and/or typed in the control (the exact way the text is entered will be established by subclasses, since this is an abstract method). text: aString Set the text widget to aString  File: gst-libs.info, Node: BLOX.BDropDown-list box accessing, Next: BLOX.BDropDown-widget protocol, Prev: BLOX.BDropDown-flexibility, Up: BLOX.BDropDown 1.12.4 BLOX.BDropDown: list box accessing ----------------------------------------- add: anObject afterIndex: index Add an element with the given value after another element whose index is contained in the index parameter. The label displayed in the widget is anObject's displayString. Answer anObject. add: aString element: anObject afterIndex: index Add an element with the aString label after another element whose index is contained in the index parameter. This method allows the client to decide autonomously the label that the widget will display. If anObject is nil, then string is used as the element as well. If aString is nil, then the element's displayString is used as the label. Answer anObject or, if it is nil, aString. addLast: anObject Add an element with the given value at the end of the listbox. The label displayed in the widget is anObject's displayString. Answer anObject. addLast: aString element: anObject Add an element with the given value at the end of the listbox. This method allows the client to decide autonomously the label that the widget will display. If anObject is nil, then string is used as the element as well. If aString is nil, then the element's displayString is used as the label. Answer anObject or, if it is nil, aString. associationAt: anIndex Answer an association whose key is the item at the given position in the listbox and whose value is the label used to display that item. at: anIndex Answer the element displayed at the given position in the list box. contents: stringCollection Set the elements displayed in the listbox, and set the labels to be their displayStrings. contents: stringCollection elements: elementList Set the elements displayed in the listbox to be those in elementList, and set the labels to be the corresponding elements in stringCollection. The two collections must have the same size. do: aBlock Iterate over each element of the listbox and pass it to aBlock. elements: elementList Set the elements displayed in the listbox, and set the labels to be their displayStrings. index: newIndex Highlight the item at the given position in the listbox, and transfer the text in the list box to the text widget. labelAt: anIndex Answer the label displayed at the given position in the list box. labelsDo: aBlock Iterate over the labels in the list widget and pass each of them to aBlock. numberOfStrings Answer the number of items in the list box removeAtIndex: index Remove the item at the given index in the list box, answering the object associated to the element (i.e. the value that #at: would have returned for the given index) size Answer the number of items in the list box  File: gst-libs.info, Node: BLOX.BDropDown-widget protocol, Prev: BLOX.BDropDown-list box accessing, Up: BLOX.BDropDown 1.12.5 BLOX.BDropDown: widget protocol -------------------------------------- dropRectangle Answer the rectangle in which the list widget will pop-up. If possible, this is situated below the drop-down widget's bottom side, but if the screen space there is not enough it could be above the drop-down widget's above side. If there is no screen space above as well, we pick the side where we can offer the greatest number of lines in the pop-up widget. dropdown Force the pop-up list widget to be visible. isDropdownVisible Answer whether the pop-up widget is visible toggle Toggle the visibility of the pop-up widget. unmapList Unmap the pop-up widget from the screen, transfer its selected item to the always visible text widget, and generate a callback.  File: gst-libs.info, Node: BLOX.BDropDownEdit, Next: BLOX.BDropDownList, Prev: BLOX.BDropDown, Up: BLOX package 1.13 BLOX.BDropDownEdit ======================= Defined in namespace BLOX Superclass: BLOX.BDropDown Category: Graphics-Examples This class resembles an edit widget, but it has an arrow button that allows the user to pick an item from a pre-built list. * Menu: * BLOX.BDropDownEdit-accessing:: (instance) * BLOX.BDropDownEdit-accessing-overrides:: (instance) * BLOX.BDropDownEdit-text accessing:: (instance)  File: gst-libs.info, Node: BLOX.BDropDownEdit-accessing, Next: BLOX.BDropDownEdit-accessing-overrides, Up: BLOX.BDropDownEdit 1.13.1 BLOX.BDropDownEdit: accessing ------------------------------------ backgroundColor: aColor Set the value of the backgroundColor option for the widget. Specifies the normal background color to use when displaying the widget. font: aString Set the value of the font option for the widget. Specifies the font to use when drawing text inside the widget. The font can be given as either an X font name or a Blox font description string. X font names are given as many fields, each led by a minus, and each of which can be replaced by an * to indicate a default value is ok: foundry, family, weight, slant, setwidth, addstyle, pixel size, point size (the same as pixel size for historical reasons), horizontal resolution, vertical resolution, spacing, width, charset and character encoding. Blox font description strings have three fields, which must be separated by a space and of which only the first is mandatory: the font family, the font size in points (or in pixels if a negative value is supplied), and a number of styles separated by a space (valid styles are normal, bold, italic, underline and overstrike). Examples of valid fonts are "Helvetica 10 Bold", "Times -14", "Futura Bold Underline". You must enclose the font family in braces if it is made of two or more words. foregroundColor: aColor Set the value of the foregroundColor option for the widget. Specifies the normal foreground color to use when displaying the widget. highlightBackground: aColor Set the value of the highlightBackground option for the widget. Specifies the background color to use when displaying selected items in the list widget and the selection in the text widget. highlightForeground: aColor Set the value of the highlightBackground option for the widget. Specifies the background color to use when displaying selected items in the list widget and the selection in the text widget.  File: gst-libs.info, Node: BLOX.BDropDownEdit-accessing-overrides, Next: BLOX.BDropDownEdit-text accessing, Prev: BLOX.BDropDownEdit-accessing, Up: BLOX.BDropDownEdit 1.13.2 BLOX.BDropDownEdit: accessing-overrides ---------------------------------------------- text Answer the text shown in the widget  File: gst-libs.info, Node: BLOX.BDropDownEdit-text accessing, Prev: BLOX.BDropDownEdit-accessing-overrides, Up: BLOX.BDropDownEdit 1.13.3 BLOX.BDropDownEdit: text accessing ----------------------------------------- insertAtEnd: aString Clear the selection and append aString at the end of the text widget. replaceSelection: aString Insert aString in the text widget at the current insertion point, replacing the currently selected text (if any), and leaving the text selected. selectAll Select the whole contents of the text widget selectFrom: first to: last Sets the selection of the text widget to include the characters starting with the one indexed by first (the very first character in the widget having index 1) and ending with the one just before last. If last refers to the same character as first or an earlier one, then the text widget's selection is cleared. selection Answer an empty string if the text widget has no selection, else answer the currently selected text selectionRange Answer nil if the text widget has no selection, else answer an Interval object whose first item is the index of the first character in the selection, and whose last item is the index of the character just after the last one in the selection. text: aString Set the contents of the text widget and select them.  File: gst-libs.info, Node: BLOX.BDropDownList, Next: BLOX.BEdit, Prev: BLOX.BDropDownEdit, Up: BLOX package 1.14 BLOX.BDropDownList ======================= Defined in namespace BLOX Superclass: BLOX.BDropDown Category: Graphics-Examples This class resembles a list box widget, but its actual list shows up only when you click the arrow button beside the currently selected item. * Menu: * BLOX.BDropDownList-accessing:: (instance) * BLOX.BDropDownList-callbacks:: (instance) * BLOX.BDropDownList-list box accessing:: (instance)  File: gst-libs.info, Node: BLOX.BDropDownList-accessing, Next: BLOX.BDropDownList-callbacks, Up: BLOX.BDropDownList 1.14.1 BLOX.BDropDownList: accessing ------------------------------------ backgroundColor: aColor Set the value of the backgroundColor for the widget, which in this class is set for the list widget and, when the focus is outside the control, for the text widget as well. Specifies the normal background color to use when displaying the widget. font: aString Set the value of the font option for the widget. Specifies the font to use when drawing text inside the widget. The font can be given as either an X font name or a Blox font description string. X font names are given as many fields, each led by a minus, and each of which can be replaced by an * to indicate a default value is ok: foundry, family, weight, slant, setwidth, addstyle, pixel size, point size (the same as pixel size for historical reasons), horizontal resolution, vertical resolution, spacing, width, charset and character encoding. Blox font description strings have three fields, which must be separated by a space and of which only the first is mandatory: the font family, the font size in points (or in pixels if a negative value is supplied), and a number of styles separated by a space (valid styles are normal, bold, italic, underline and overstrike). Examples of valid fonts are "Helvetica 10 Bold", "Times -14", "Futura Bold Underline". You must enclose the font family in braces if it is made of two or more words. foregroundColor: aColor Set the value of the foregroundColor for the widget, which in this class is set for the list widget and, when the focus is outside the control, for the text widget as well. Specifies the normal foreground color to use when displaying the widget. highlightBackground: aColor Answer the value of the highlightBackground option for the widget. Specifies the background color to use when displaying selected items in the list widget and, when the focus is inside the control, for the text widget as well. highlightForeground: aColor Answer the value of the highlightForeground option for the widget. Specifies the foreground color to use when displaying selected items in the list widget and, when the focus is inside the control, for the text widget as well. text Answer the text that the user has picked from the widget and/or typed in the control (the exact way the text is entered will be established by subclasses, since this is an abstract method).  File: gst-libs.info, Node: BLOX.BDropDownList-callbacks, Next: BLOX.BDropDownList-list box accessing, Prev: BLOX.BDropDownList-accessing, Up: BLOX.BDropDownList 1.14.2 BLOX.BDropDownList: callbacks ------------------------------------ callback: aReceiver message: aSymbol Set up so that aReceiver is sent the aSymbol message (the name of a selector with at most two arguemtnts) when the active item in the receiver changegs. If the method accepts two arguments, the receiver is passed as the first parameter. If the method accepts one or two arguments, the selected index is passed as the last parameter. invokeCallback Generate a synthetic callback.  File: gst-libs.info, Node: BLOX.BDropDownList-list box accessing, Prev: BLOX.BDropDownList-callbacks, Up: BLOX.BDropDownList 1.14.3 BLOX.BDropDownList: list box accessing --------------------------------------------- index Answer the value of the index option for the widget. Since it is not possible to modify an item once it has been picked from the list widget, this is always defined for BDropDownList widgets.  File: gst-libs.info, Node: BLOX.BEdit, Next: BLOX.BEmbeddedImage, Prev: BLOX.BDropDownList, Up: BLOX package 1.15 BLOX.BEdit =============== Defined in namespace BLOX Superclass: BLOX.BPrimitive Category: Graphics-Windows I am a widget showing one line of modifiable text. * Menu: * BLOX.BEdit class-instance creation:: (class) * BLOX.BEdit-accessing:: (instance) * BLOX.BEdit-widget protocol:: (instance)  File: gst-libs.info, Node: BLOX.BEdit class-instance creation, Next: BLOX.BEdit-accessing, Up: BLOX.BEdit 1.15.1 BLOX.BEdit class: instance creation ------------------------------------------ new: parent contents: aString Answer a new BEdit widget laid inside the given parent widget, with a default content of aString  File: gst-libs.info, Node: BLOX.BEdit-accessing, Next: BLOX.BEdit-widget protocol, Prev: BLOX.BEdit class-instance creation, Up: BLOX.BEdit 1.15.2 BLOX.BEdit: accessing ---------------------------- backgroundColor Answer the value of the backgroundColor option for the widget. Specifies the normal background color to use when displaying the widget. backgroundColor: value Set the value of the backgroundColor option for the widget. Specifies the normal background color to use when displaying the widget. callback Answer a DirectedMessage that is sent when the receiver is modified, or nil if none has been set up. callback: aReceiver message: aSymbol Set up so that aReceiver is sent the aSymbol message (the name of a zero- or one-argument selector) when the receiver is modified. If the method accepts an argument, the receiver is passed. contents Return the contents of the widget contents: newText Set the contents of the widget font Answer the value of the font option for the widget. Specifies the font to use when drawing text inside the widget. The font can be given as either an X font name or a Blox font description string. X font names are given as many fields, each led by a minus, and each of which can be replaced by an * to indicate a default value is ok: foundry, family, weight, slant, setwidth, addstyle, pixel size, point size (the same as pixel size for historical reasons), horizontal resolution, vertical resolution, spacing, width, charset and character encoding. Blox font description strings have three fields, which must be separated by a space and of which only the first is mandatory: the font family, the font size in points (or in pixels if a negative value is supplied), and a number of styles separated by a space (valid styles are normal, bold, italic, underline and overstrike). Examples of valid fonts are "Helvetica 10 Bold", "Times -14", "Futura Bold Underline". You must enclose the font family in braces if it is made of two or more words. font: value Set the value of the font option for the widget. Specifies the font to use when drawing text inside the widget. The font can be given as either an X font name or a Blox font description string. X font names are given as many fields, each led by a minus, and each of which can be replaced by an * to indicate a default value is ok: foundry, family, weight, slant, setwidth, addstyle, pixel size, point size (the same as pixel size for historical reasons), horizontal resolution, vertical resolution, spacing, width, charset and character encoding. Blox font description strings have three fields, which must be separated by a space and of which only the first is mandatory: the font family, the font size in points (or in pixels if a negative value is supplied), and a number of styles separated by a space (valid styles are normal, bold, italic, underline and overstrike). Examples of valid fonts are "Helvetica 10 Bold", "Times -14", "Futura Bold Underline". You must enclose the font family in braces if it is made of two or more words. foregroundColor Answer the value of the foregroundColor option for the widget. Specifies the normal foreground color to use when displaying the widget. foregroundColor: value Set the value of the foregroundColor option for the widget. Specifies the normal foreground color to use when displaying the widget. selectBackground Answer the value of the selectBackground option for the widget. Specifies the background color to use when displaying selected parts of the widget. selectBackground: value Set the value of the selectBackground option for the widget. Specifies the background color to use when displaying selected parts of the widget. selectForeground Answer the value of the selectForeground option for the widget. Specifies the foreground color to use when displaying selected parts of the widget. selectForeground: value Set the value of the selectForeground option for the widget. Specifies the foreground color to use when displaying selected parts of the widget.  File: gst-libs.info, Node: BLOX.BEdit-widget protocol, Prev: BLOX.BEdit-accessing, Up: BLOX.BEdit 1.15.3 BLOX.BEdit: widget protocol ---------------------------------- destroyed Private - The receiver has been destroyed, clear the corresponding Tcl variable to avoid memory leaks. hasSelection Answer whether there is selected text in the widget insertAtEnd: aString Clear the selection and append aString at the end of the widget. insertText: aString Insert aString in the widget at the current insertion point, replacing the currently selected text (if any). invokeCallback Generate a synthetic callback. nextPut: aCharacter Clear the selection and append aCharacter at the end of the widget. nextPutAll: aString Clear the selection and append aString at the end of the widget. nl Clear the selection and append a linefeed character at the end of the widget. replaceSelection: aString Insert aString in the widget at the current insertion point, replacing the currently selected text (if any), and leaving the text selected. selectAll Select the whole contents of the widget. selectFrom: first to: last Sets the selection to include the characters starting with the one indexed by first (the very first character in the widget having index 1) and ending with the one just before last. If last refers to the same character as first or an earlier one, then the widget's selection is cleared. selection Answer an empty string if the widget has no selection, else answer the currently selected text selectionRange Answer nil if the widget has no selection, else answer an Interval object whose first item is the index of the first character in the selection, and whose last item is the index of the character just after the last one in the selection. space Clear the selection and append a space at the end of the widget.  File: gst-libs.info, Node: BLOX.BEmbeddedImage, Next: BLOX.BEmbeddedText, Prev: BLOX.BEdit, Up: BLOX package 1.16 BLOX.BEmbeddedImage ======================== Defined in namespace BLOX Superclass: BLOX.BBoundingBox Category: Graphics-Windows I can draw a colorful image inside the canvas. * Menu: * BLOX.BEmbeddedImage-accessing:: (instance)  File: gst-libs.info, Node: BLOX.BEmbeddedImage-accessing, Up: BLOX.BEmbeddedImage 1.16.1 BLOX.BEmbeddedImage: accessing ------------------------------------- copyInto: aBlox Answer a new BCanvasObject identical to this but displayed into another canvas, newCanvas. The new instance is not created at the time it is returned. data Answer the data of the image. The result will be a String containing image data either as Base-64 encoded GIF data, as XPM data, or as PPM data. data: aString Set the data of the image. aString may contain the data either as Base-64 encoded GIF data, as XPM data, or as PPM data. No changes are visible until you toggle a redraw using the appropriate method. redraw Force the object to be displayed in the parent canvas, creating it if it has not been inserted for real in the parent, and refresh its position and image data if it has changed.  File: gst-libs.info, Node: BLOX.BEmbeddedText, Next: BLOX.BEventSet, Prev: BLOX.BEmbeddedImage, Up: BLOX package 1.17 BLOX.BEmbeddedText ======================= Defined in namespace BLOX Superclass: BLOX.BBoundingBox Category: Graphics-Windows I can draw text in all sorts of colors, sizes and fonts. * Menu: * BLOX.BEmbeddedText-accessing:: (instance)  File: gst-libs.info, Node: BLOX.BEmbeddedText-accessing, Up: BLOX.BEmbeddedText 1.17.1 BLOX.BEmbeddedText: accessing ------------------------------------ font Answer the value of the font option for the canvas object. Specifies the font to use when drawing text inside the widget. The font can be given as either an X font name or a Blox font description string. X font names are given as many fields, each led by a minus, and each of which can be replaced by an * to indicate a default value is ok: foundry, family, weight, slant, setwidth, addstyle, pixel size, point size (the same as pixel size for historical reasons), horizontal resolution, vertical resolution, spacing, width, charset and character encoding. Blox font description strings have three fields, which must be separated by a space and of which only the first is mandatory: the font family, the font size in points (or in pixels if a negative value is supplied), and a number of styles separated by a space (valid styles are normal, bold, italic, underline and overstrike). Examples of valid fonts are "Helvetica 10 Bold", "Times -14", "Futura Bold Underline". You must enclose the font family in braces if it is made of two or more words. font: font Set the value of the font option for the canvas object. Specifies the font to use when drawing text inside the widget. The font can be given as either an X font name or a Blox font description string. X font names are given as many fields, each led by a minus, and each of which can be replaced by an * to indicate a default value is ok: foundry, family, weight, slant, setwidth, addstyle, pixel size, point size (the same as pixel size for historical reasons), horizontal resolution, vertical resolution, spacing, width, charset and character encoding. Blox font description strings have three fields, which must be separated by a space and of which only the first is mandatory: the font family, the font size in points (or in pixels if a negative value is supplied), and a number of styles separated by a space (valid styles are normal, bold, italic, underline and overstrike). Examples of valid fonts are "Helvetica 10 Bold", "Times -14", "Futura Bold Underline". You must enclose the font family in braces if it is made of two or more words. justify Answer how to justify the text within its bounding region. justify: aSymbol Sets how to justify the text within its bounding region. Can be #left, #right or #center (the default). redraw Force the object to be displayed in the parent canvas, creating it if it has not been inserted for real in the parent, and refresh its position. text Answer the text that is printed by the object text: aString Set the text that is printed by the object  File: gst-libs.info, Node: BLOX.BEventSet, Next: BLOX.BEventTarget, Prev: BLOX.BEmbeddedText, Up: BLOX package 1.18 BLOX.BEventSet =================== Defined in namespace BLOX Superclass: BLOX.BEventTarget Category: Graphics-Windows I combine event handlers and let you apply them to many objects. Basically, you derive a class from me, override the #initialize: method to establish the handlers, then use the #addEventSet: method understood by every Blox class to add the event handlers specified by the receiver to the object. * Menu: * BLOX.BEventSet class-initializing:: (class) * BLOX.BEventSet-accessing:: (instance) * BLOX.BEventSet-initializing:: (instance)  File: gst-libs.info, Node: BLOX.BEventSet class-initializing, Next: BLOX.BEventSet-accessing, Up: BLOX.BEventSet 1.18.1 BLOX.BEventSet class: initializing ----------------------------------------- new This method should not be called for instances of this class. new: widget Private - Create a new event set object that will attach to the given widget. Answer the object. Note: this method should be called by #addEventSet:, not directly  File: gst-libs.info, Node: BLOX.BEventSet-accessing, Next: BLOX.BEventSet-initializing, Prev: BLOX.BEventSet class-initializing, Up: BLOX.BEventSet 1.18.2 BLOX.BEventSet: accessing -------------------------------- widget Answer the widget to which the receiver is attached.  File: gst-libs.info, Node: BLOX.BEventSet-initializing, Prev: BLOX.BEventSet-accessing, Up: BLOX.BEventSet 1.18.3 BLOX.BEventSet: initializing ----------------------------------- initialize: aBWidget Initialize the receiver's event handlers to attach to aBWidget. You can override this of course, but don't forget to call the superclass implementation first.  File: gst-libs.info, Node: BLOX.BEventTarget, Next: BLOX.BExtended, Prev: BLOX.BEventSet, Up: BLOX package 1.19 BLOX.BEventTarget ====================== Defined in namespace BLOX Superclass: Object Category: Graphics-Windows I track all the event handling procedures that you apply to an object. * Menu: * BLOX.BEventTarget-intercepting events:: (instance)  File: gst-libs.info, Node: BLOX.BEventTarget-intercepting events, Up: BLOX.BEventTarget 1.19.1 BLOX.BEventTarget: intercepting events --------------------------------------------- addEventSet: aBEventSetSublass Add to the receiver the event handlers implemented by an instance of aBEventSetSubclass. Answer the new instance of aBEventSetSublass. onAsciiKeyEventSend: aSelector to: anObject When an ASCII key is pressed and the receiver has the focus, send the 1-argument message identified by aSelector to anObject, passing to it a Character. onDestroySend: aSelector to: anObject When the receiver is destroyed, send the unary message identified by aSelector to anObject. onFocusEnterEventSend: aSelector to: anObject When the focus enters the receiver, send the unary message identified by aSelector to anObject. onFocusLeaveEventSend: aSelector to: anObject When the focus leaves the receiver, send the unary message identified by aSelector to anObject. onKeyEvent: key send: aSelector to: anObject When the given key is pressed and the receiver has the focus, send the unary message identified by aSelector to anObject. Examples for key are: 'Ctrl-1', 'Alt-X', 'Meta-plus', 'enter'. The last two cases include example of special key identifiers; these include: 'backslash', 'exclam', 'quotedbl', 'dollar', 'asterisk', 'less', 'greater', 'asciicircum' (caret), 'question', 'equal', 'parenleft', 'parenright', 'colon', 'semicolon', 'bar' (pipe sign), 'underscore', 'percent', 'minus', 'plus', 'BackSpace', 'Delete', 'Insert', 'Return', 'End', 'Home', 'Prior' (Pgup), 'Next' (Pgdn), 'F1'..'F24', 'Caps_Lock', 'Num_Lock', 'Tab', 'Left', 'Right', 'Up', 'Down'. There are in addition four special identifiers which map to platform-specific keys: '', '', '', '' (all with the angular brackets!). onKeyEventSend: aSelector to: anObject When a key is pressed and the receiver has the focus, send the 1-argument message identified by aSelector to anObject. The pressed key will be passed as a String parameter; some of the keys will send special key identifiers such as those explained in the documentation for #onKeyEvent:send:to: Look at the #eventTest test program in the BloxTestSuite to find out the parameters passed to such an event procedure onKeyUpEventSend: aSelector to: anObject When a key has been released and the receiver has the focus, send the 1-argument message identified by aSelector to anObject. The released key will be passed as a String parameter; some of the keys will send special key identifiers such as those explained in the documentation for #onKeyEvent:send:to: Look at the #eventTest test program in the BloxTestSuite to find out the parameters passed to such an event procedure onMouseDoubleEvent: button send: aSelector to: anObject When the given button is double-clicked on the mouse, send the 1-argument message identified by aSelector to anObject. The mouse position will be passed as a Point. onMouseDoubleEventSend: aSelector to: anObject When a button is double-clicked on the mouse, send the 2-argument message identified by aSelector to anObject. The mouse position will be passed as a Point in the first parameter, the button number will be passed as an Integer in the second parameter. onMouseDownEvent: button send: aSelector to: anObject When the given button is pressed on the mouse, send the 1-argument message identified by aSelector to anObject. The mouse position will be passed as a Point. onMouseDownEventSend: aSelector to: anObject When a button is pressed on the mouse, send the 2-argument message identified by aSelector to anObject. The mouse position will be passed as a Point in the first parameter, the button number will be passed as an Integer in the second parameter. onMouseEnterEventSend: aSelector to: anObject When the mouse enters the widget, send the unary message identified by aSelector to anObject. onMouseLeaveEventSend: aSelector to: anObject When the mouse leaves the widget, send the unary message identified by aSelector to anObject. onMouseMoveEvent: button send: aSelector to: anObject When the mouse is moved while the given button is pressed on the mouse, send the 1-argument message identified by aSelector to anObject. The mouse position will be passed as a Point. onMouseMoveEventSend: aSelector to: anObject When the mouse is moved, send the 1-argument message identified by aSelector to anObject. The mouse position will be passed as a Point. onMouseTripleEvent: button send: aSelector to: anObject When the given button is triple-clicked on the mouse, send the 1-argument message identified by aSelector to anObject. The mouse position will be passed as a Point. onMouseTripleEventSend: aSelector to: anObject When a button is triple-clicked on the mouse, send the 2-argument message identified by aSelector to anObject. The mouse position will be passed as a Point in the first parameter, the button number will be passed as an Integer in the second parameter. onMouseUpEvent: button send: aSelector to: anObject When the given button is released on the mouse, send the 1-argument message identified by aSelector to anObject. The mouse position will be passed as a Point. onMouseUpEventSend: aSelector to: anObject When a button is released on the mouse, send the 2-argument message identified by aSelector to anObject. The mouse position will be passed as a Point in the first parameter, the button number will be passed as an Integer in the second parameter. onResizeSend: aSelector to: anObject When the receiver is resized, send the 1-argument message identified by aSelector to anObject. The new size will be passed as a Point.  File: gst-libs.info, Node: BLOX.BExtended, Next: BLOX.BForm, Prev: BLOX.BEventTarget, Up: BLOX package 1.20 BLOX.BExtended =================== Defined in namespace BLOX Superclass: BLOX.BWidget Category: Graphics-Windows Just like Gui, I serve as a base for complex objects which expose an individual protocol but internally use a Blox widget for creating their user interface. Unlike Gui, however, the instances of my subclasses understand the standard widget protocol. Just override my newPrimitive method to return another widget, and you'll get a class which interacts with the user like that widget (a list box, a text box, or even a label) but exposes a different protocol. * Menu: * BLOX.BExtended-accessing:: (instance) * BLOX.BExtended-customization:: (instance)  File: gst-libs.info, Node: BLOX.BExtended-accessing, Next: BLOX.BExtended-customization, Up: BLOX.BExtended 1.20.1 BLOX.BExtended: accessing -------------------------------- asPrimitiveWidget Answer the primitive widget that implements the receiver.  File: gst-libs.info, Node: BLOX.BExtended-customization, Prev: BLOX.BExtended-accessing, Up: BLOX.BExtended 1.20.2 BLOX.BExtended: customization ------------------------------------ create After this method is called (the call is made automatically) the receiver will be attached to a `primitive' widget (which can be in turn another extended widget). This method is public not because you can call it, but because it can be useful to override it, not forgetting the call to super (which only calls #newPrimitive and saves the result), to perform some initialization on the primitive widget just created; overriding #create is in fact more generic than overriding #newPrimitive. For an example of this, see the implementation of BButtonLike. newPrimitive Create and answer a new widget on which the implementation of the receiver will be based. You should not call this method directly; instead you must override it in BExtended's subclasses.  File: gst-libs.info, Node: BLOX.BForm, Next: BLOX.BImage, Prev: BLOX.BExtended, Up: BLOX package 1.21 BLOX.BForm =============== Defined in namespace BLOX Superclass: BLOX.BPrimitive Category: Graphics-Windows I am used to group many widgets together. I leave the heavy task of managing their position to the user. * Menu: * BLOX.BForm-accessing:: (instance)  File: gst-libs.info, Node: BLOX.BForm-accessing, Up: BLOX.BForm 1.21.1 BLOX.BForm: accessing ---------------------------- backgroundColor Answer the value of the backgroundColor option for the widget. Specifies the normal background color to use when displaying the widget. backgroundColor: value Set the value of the backgroundColor option for the widget. Specifies the normal background color to use when displaying the widget. defaultHeight Answer the value of the defaultHeight option for the widget. Specifies the desired height for the form in pixels. If this option is less than or equal to zero then the window will not request any size at all. defaultHeight: value Set the value of the defaultHeight option for the widget. Specifies the desired height for the form in pixels. If this option is less than or equal to zero then the window will not request any size at all. defaultWidth Answer the value of the defaultWidth option for the widget. Specifies the desired width for the form in pixels. If this option is less than or equal to zero then the window will not request any size at all. defaultWidth: value Set the value of the defaultWidth option for the widget. Specifies the desired width for the form in pixels. If this option is less than or equal to zero then the window will not request any size at all.  File: gst-libs.info, Node: BLOX.BImage, Next: BLOX.BLabel, Prev: BLOX.BForm, Up: BLOX package 1.22 BLOX.BImage ================ Defined in namespace BLOX Superclass: BLOX.BPrimitive Category: Graphics-Windows I can display colorful images. * Menu: * BLOX.BImage class-arrows:: (class) * BLOX.BImage class-GNU:: (class) * BLOX.BImage class-icons:: (class) * BLOX.BImage class-instance creation:: (class) * BLOX.BImage class-small icons:: (class) * BLOX.BImage-accessing:: (instance) * BLOX.BImage-image management:: (instance) * BLOX.BImage-widget protocol:: (instance)  File: gst-libs.info, Node: BLOX.BImage class-arrows, Next: BLOX.BImage class-GNU, Up: BLOX.BImage 1.22.1 BLOX.BImage class: arrows -------------------------------- downArrow Answer the XPM representation of a 12x12 arrow pointing downwards. leftArrow Answer the XPM representation of a 12x12 arrow pointing leftwards. rightArrow Answer the XPM representation of a 12x12 arrow pointing rightwards. upArrow Answer the XPM representation of a 12x12 arrow pointing upwards.  File: gst-libs.info, Node: BLOX.BImage class-GNU, Next: BLOX.BImage class-icons, Prev: BLOX.BImage class-arrows, Up: BLOX.BImage 1.22.2 BLOX.BImage class: GNU ----------------------------- gnu Answer the XPM representation of a 48x48 GNU.  File: gst-libs.info, Node: BLOX.BImage class-icons, Next: BLOX.BImage class-instance creation, Prev: BLOX.BImage class-GNU, Up: BLOX.BImage 1.22.3 BLOX.BImage class: icons ------------------------------- exclaim Answer the XPM representation of a 32x32 exclamation mark icon. info Answer the XPM representation of a 32x32 `information' icon. question Answer the XPM representation of a 32x32 question mark icon. stop Answer the XPM representation of a 32x32 `critical stop' icon.  File: gst-libs.info, Node: BLOX.BImage class-instance creation, Next: BLOX.BImage class-small icons, Prev: BLOX.BImage class-icons, Up: BLOX.BImage 1.22.4 BLOX.BImage class: instance creation ------------------------------------------- new: parent data: aString Answer a new BImage widget laid inside the given parent widget, loading data from the given string (Base-64 encoded GIF, XPM, PPM are supported). new: parent image: aFileStream Answer a new BImage widget laid inside the given parent widget, loading data from the given file (GIF, XPM, PPM are supported). new: parent size: aPoint Answer a new BImage widget laid inside the given parent widget, showing by default a transparent image of aPoint size.  File: gst-libs.info, Node: BLOX.BImage class-small icons, Next: BLOX.BImage-accessing, Prev: BLOX.BImage class-instance creation, Up: BLOX.BImage 1.22.5 BLOX.BImage class: small icons ------------------------------------- directory Answer the Base-64 GIF representation of a `directory folder' icon. file Answer the Base-64 GIF representation of a `file' icon.  File: gst-libs.info, Node: BLOX.BImage-accessing, Next: BLOX.BImage-image management, Prev: BLOX.BImage class-small icons, Up: BLOX.BImage 1.22.6 BLOX.BImage: accessing ----------------------------- backgroundColor Answer the value of the backgroundColor option for the widget. Specifies the normal background color to use when displaying the widget. backgroundColor: value Set the value of the backgroundColor option for the widget. Specifies the normal background color to use when displaying the widget. displayHeight Answer the value of the displayHeight option for the widget. Specifies the height of the image in pixels. This is not the height of the widget, but specifies the area of the widget that will be taken by the image. displayHeight: value Set the value of the displayHeight option for the widget. Specifies the height of the image in pixels. This is not the height of the widget, but specifies the area of the widget that will be taken by the image. displayWidth Answer the value of the displayWidth option for the widget. Specifies the width of the image in pixels. This is not the width of the widget, but specifies the area of the widget that will be taken by the image. displayWidth: value Set the value of the displayWidth option for the widget. Specifies the width of the image in pixels. This is not the width of the widget, but specifies the area of the widget that will be taken by the image. foregroundColor Answer the value of the foregroundColor option for the widget. Specifies the normal foreground color to use when displaying the widget. foregroundColor: value Set the value of the foregroundColor option for the widget. Specifies the normal foreground color to use when displaying the widget. gamma Answer the value of the gamma option for the widget. Specifies that the colors allocated for displaying the image widget should be corrected for a non-linear display with the specified gamma exponent value. (The intensity produced by most CRT displays is a power function of the input value, to a good approximation; gamma is the exponent and is typically around 2). The value specified must be greater than zero. The default value is one (no correction). In general, values greater than one will make the image lighter, and values less than one will make it darker. gamma: value Set the value of the gamma option for the widget. Specifies that the colors allocated for displaying the image widget should be corrected for a non-linear display with the specified gamma exponent value. (The intensity produced by most CRT displays is a power function of the input value, to a good approximation; gamma is the exponent and is typically around 2). The value specified must be greater than zero. The default value is one (no correction). In general, values greater than one will make the image lighter, and values less than one will make it darker.  File: gst-libs.info, Node: BLOX.BImage-image management, Next: BLOX.BImage-widget protocol, Prev: BLOX.BImage-accessing, Up: BLOX.BImage 1.22.7 BLOX.BImage: image management ------------------------------------ blank Blank the corresponding image data: aString Set the image to be drawn to aString, which can be a GIF in Base-64 representation or an X pixelmap. dither Recalculate the dithered image in the window where the image is displayed. The dithering algorithm used in displaying images propagates quantization errors from one pixel to its neighbors. If the image data is supplied in pieces, the dithered image may not be exactly correct. Normally the difference is not noticeable, but if it is a problem, this command can be used to fix it. fillFrom: origin extent: extent color: color Fill a rectangle with the given origin and extent, using the given color. fillFrom: origin to: corner color: color Fill a rectangle between the given corners, using the given color. fillRectangle: rectangle color: color Fill a rectangle having the given bounding box, using the given color. image: aFileStream Read a GIF or XPM image from aFileStream. The whole contents of the file are read, not only from the file position. imageHeight Specifies the height of the image, in pixels. This option is useful primarily in situations where you wish to build up the contents of the image piece by piece. A value of zero (the default) allows the image to expand or shrink vertically to fit the data stored in it. imageWidth Specifies the width of the image, in pixels. This option is useful primarily in situations where you wish to build up the contents of the image piece by piece. A value of zero (the default) allows the image to expand or shrink horizontally to fit the data stored in it. lineFrom: origin extent: extent color: color Draw a line with the given origin and extent, using the given color. lineFrom: origin to: corner color: color This method's functionality has not been implemented yet. lineFrom: origin toX: endX color: color Draw an horizontal line between the given corners, using the given color. lineFrom: origin toY: endY color: color Draw a vertical line between the given corners, using the given color. lineInside: rectangle color: color Draw a line having the given bounding box, using the given color.  File: gst-libs.info, Node: BLOX.BImage-widget protocol, Prev: BLOX.BImage-image management, Up: BLOX.BImage 1.22.8 BLOX.BImage: widget protocol ----------------------------------- destroyed Private - The receiver has been destroyed, clear the corresponding Tcl image to avoid memory leaks.  File: gst-libs.info, Node: BLOX.BLabel, Next: BLOX.BLine, Prev: BLOX.BImage, Up: BLOX package 1.23 BLOX.BLabel ================ Defined in namespace BLOX Superclass: BLOX.BPrimitive Category: Graphics-Windows I am a label showing static text. * Menu: * BLOX.BLabel class-initialization:: (class) * BLOX.BLabel class-instance creation:: (class) * BLOX.BLabel-accessing:: (instance)  File: gst-libs.info, Node: BLOX.BLabel class-initialization, Next: BLOX.BLabel class-instance creation, Up: BLOX.BLabel 1.23.1 BLOX.BLabel class: initialization ---------------------------------------- initialize Private - Initialize the receiver's class variables.  File: gst-libs.info, Node: BLOX.BLabel class-instance creation, Next: BLOX.BLabel-accessing, Prev: BLOX.BLabel class-initialization, Up: BLOX.BLabel 1.23.2 BLOX.BLabel class: instance creation ------------------------------------------- new: parent label: label Answer a new BLabel widget laid inside the given parent widget, showing by default the `label' String.  File: gst-libs.info, Node: BLOX.BLabel-accessing, Prev: BLOX.BLabel class-instance creation, Up: BLOX.BLabel 1.23.3 BLOX.BLabel: accessing ----------------------------- alignment Answer the value of the anchor option for the widget. Specifies how the information in a widget (e.g. text or a bitmap) is to be displayed in the widget. Must be one of the symbols #topLeft, #topCenter, #topRight, #leftCenter, #center, #rightCenter, #bottomLeft, #bottomCenter, #bottomRight. For example, #topLeft means display the information such that its top-left corner is at the top-left corner of the widget. alignment: aSymbol Set the value of the anchor option for the widget. Specifies how the information in a widget (e.g. text or a bitmap) is to be displayed in the widget. Must be one of the symbols #topLeft, #topCenter, #topRight, #leftCenter, #center, #rightCenter, #bottomLeft, #bottomCenter, #bottomRight. For example, #topLeft means display the information such that its top-left corner is at the top-left corner of the widget. backgroundColor Answer the value of the backgroundColor option for the widget. Specifies the normal background color to use when displaying the widget. backgroundColor: value Set the value of the backgroundColor option for the widget. Specifies the normal background color to use when displaying the widget. font Answer the value of the font option for the widget. Specifies the font to use when drawing text inside the widget. The font can be given as either an X font name or a Blox font description string. X font names are given as many fields, each led by a minus, and each of which can be replaced by an * to indicate a default value is ok: foundry, family, weight, slant, setwidth, addstyle, pixel size, point size (the same as pixel size for historical reasons), horizontal resolution, vertical resolution, spacing, width, charset and character encoding. Blox font description strings have three fields, which must be separated by a space and of which only the first is mandatory: the font family, the font size in points (or in pixels if a negative value is supplied), and a number of styles separated by a space (valid styles are normal, bold, italic, underline and overstrike). Examples of valid fonts are "Helvetica 10 Bold", "Times -14", "Futura Bold Underline". You must enclose the font family in braces if it is made of two or more words. font: value Set the value of the font option for the widget. Specifies the font to use when drawing text inside the widget. The font can be given as either an X font name or a Blox font description string. X font names are given as many fields, each led by a minus, and each of which can be replaced by an * to indicate a default value is ok: foundry, family, weight, slant, setwidth, addstyle, pixel size, point size (the same as pixel size for historical reasons), horizontal resolution, vertical resolution, spacing, width, charset and character encoding. Blox font description strings have three fields, which must be separated by a space and of which only the first is mandatory: the font family, the font size in points (or in pixels if a negative value is supplied), and a number of styles separated by a space (valid styles are normal, bold, italic, underline and overstrike). Examples of valid fonts are "Helvetica 10 Bold", "Times -14", "Futura Bold Underline". You must enclose the font family in braces if it is made of two or more words. foregroundColor Answer the value of the foregroundColor option for the widget. Specifies the normal foreground color to use when displaying the widget. foregroundColor: value Set the value of the foregroundColor option for the widget. Specifies the normal foreground color to use when displaying the widget. label Answer the value of the label option for the widget. Specifies a string to be displayed inside the widget. The way in which the string is displayed depends on the particular widget and may be determined by other options, such as anchor. For windows, this is the title of the window. label: value Set the value of the label option for the widget. Specifies a string to be displayed inside the widget. The way in which the string is displayed depends on the particular widget and may be determined by other options, such as anchor. For windows, this is the title of the window.  File: gst-libs.info, Node: BLOX.BLine, Next: BLOX.BList, Prev: BLOX.BLabel, Up: BLOX package 1.24 BLOX.BLine =============== Defined in namespace BLOX Superclass: BLOX.BBoundingBox Category: Graphics-Windows I only draw straight lines but I can do that very well, even without a ruler... * Menu: * BLOX.BLine-accessing:: (instance)  File: gst-libs.info, Node: BLOX.BLine-accessing, Up: BLOX.BLine 1.24.1 BLOX.BLine: accessing ---------------------------- cap Answer the way in which caps are to be drawn at the endpoints of the line. The answer may be #butt (the default), #projecting, or #round). cap: aSymbol Set the way in which caps are to be drawn at the endpoints of the line. aSymbol may be #butt (the default), #projecting, or #round). width Answer the width with which the line is drawn. width: pixels Set the width with which the line is drawn.  File: gst-libs.info, Node: BLOX.BList, Next: BLOX.Blox, Prev: BLOX.BLine, Up: BLOX package 1.25 BLOX.BList =============== Defined in namespace BLOX Superclass: BLOX.BViewport Category: Graphics-Windows I represent a list box from which you can choose one or more elements. * Menu: * BLOX.BList-accessing:: (instance) * BLOX.BList-widget protocol:: (instance)  File: gst-libs.info, Node: BLOX.BList-accessing, Next: BLOX.BList-widget protocol, Up: BLOX.BList 1.25.1 BLOX.BList: accessing ---------------------------- add: anObject afterIndex: index Add an element with the given value after another element whose index is contained in the index parameter. The label displayed in the widget is anObject's displayString. Answer anObject. add: aString element: anObject afterIndex: index Add an element with the aString label after another element whose index is contained in the index parameter. This method allows the client to decide autonomously the label that the widget will display. If anObject is nil, then string is used as the element as well. If aString is nil, then the element's displayString is used as the label. Answer anObject or, if it is nil, aString. addLast: anObject Add an element with the given value at the end of the listbox. The label displayed in the widget is anObject's displayString. Answer anObject. addLast: aString element: anObject Add an element with the given value at the end of the listbox. This method allows the client to decide autonomously the label that the widget will display. If anObject is nil, then string is used as the element as well. If aString is nil, then the element's displayString is used as the label. Answer anObject or, if it is nil, aString. associationAt: anIndex Answer an association whose key is the item at the given position in the listbox and whose value is the label used to display that item. at: anIndex Answer the element displayed at the given position in the list box. backgroundColor Answer the value of the backgroundColor option for the widget. Specifies the normal background color to use when displaying the widget. backgroundColor: value Set the value of the backgroundColor option for the widget. Specifies the normal background color to use when displaying the widget. contents: elementList Set the elements displayed in the listbox, and set the labels to be their displayStrings. contents: stringCollection elements: elementList Set the elements displayed in the listbox to be those in elementList, and set the labels to be the corresponding elements in stringCollection. The two collections must have the same size. do: aBlock Iterate over each element of the listbox and pass it to aBlock. elements Answer the collection of objects that represent the elements displayed by the list box. elements: elementList Set the elements displayed in the listbox, and set the labels to be their displayStrings. font Answer the value of the font option for the widget. Specifies the font to use when drawing text inside the widget. The font can be given as either an X font name or a Blox font description string. X font names are given as many fields, each led by a minus, and each of which can be replaced by an * to indicate a default value is ok: foundry, family, weight, slant, setwidth, addstyle, pixel size, point size (the same as pixel size for historical reasons), horizontal resolution, vertical resolution, spacing, width, charset and character encoding. Blox font description strings have three fields, which must be separated by a space and of which only the first is mandatory: the font family, the font size in points (or in pixels if a negative value is supplied), and a number of styles separated by a space (valid styles are normal, bold, italic, underline and overstrike). Examples of valid fonts are "Helvetica 10 Bold", "Times -14", "Futura Bold Underline". You must enclose the font family in braces if it is made of two or more words. font: value Set the value of the font option for the widget. Specifies the font to use when drawing text inside the widget. The font can be given as either an X font name or a Blox font description string. X font names are given as many fields, each led by a minus, and each of which can be replaced by an * to indicate a default value is ok: foundry, family, weight, slant, setwidth, addstyle, pixel size, point size (the same as pixel size for historical reasons), horizontal resolution, vertical resolution, spacing, width, charset and character encoding. Blox font description strings have three fields, which must be separated by a space and of which only the first is mandatory: the font family, the font size in points (or in pixels if a negative value is supplied), and a number of styles separated by a space (valid styles are normal, bold, italic, underline and overstrike). Examples of valid fonts are "Helvetica 10 Bold", "Times -14", "Futura Bold Underline". You must enclose the font family in braces if it is made of two or more words. foregroundColor Answer the value of the foregroundColor option for the widget. Specifies the normal foreground color to use when displaying the widget. foregroundColor: value Set the value of the foregroundColor option for the widget. Specifies the normal foreground color to use when displaying the widget. highlightBackground Answer the value of the highlightBackground option for the widget. Specifies the background color to use when displaying selected items in the widget. highlightBackground: value Set the value of the highlightBackground option for the widget. Specifies the background color to use when displaying selected items in the widget. highlightForeground Answer the value of the highlightForeground option for the widget. Specifies the foreground color to use when displaying selected items in the widget. highlightForeground: value Set the value of the highlightForeground option for the widget. Specifies the foreground color to use when displaying selected items in the widget. index Answer the value of the index option for the widget. Indicates the element that has the location cursor. This item will be displayed in the highlightForeground color, and with the corresponding background color. indexAt: point Answer the index of the element that covers the point in the listbox window specified by x and y (in pixel coordinates). If no element covers that point, then the closest element to that point is used. isSelected: index Answer whether the element indicated by index is currently selected. label Return nil, it is here for Gtk+ support label: aString Do nothing, it is here for Gtk+ support labelAt: anIndex Answer the label displayed at the given position in the list box. labels Answer the labels displayed by the list box. labelsDo: aBlock Iterate over each listbox element's label and pass it to aBlock. mode Answer the value of the mode option for the widget. Specifies one of several styles for manipulating the selection. The value of the option may be either single, browse, multiple, or extended. If the selection mode is single or browse, at most one element can be selected in the listbox at once. Clicking button 1 on an unselected element selects it and deselects any other selected item, while clicking on a selected element has no effect. In browse mode it is also possible to drag the selection with button 1. That is, moving the mouse while button 1 is pressed keeps the item under the cursor selected. If the selection mode is multiple or extended, any number of elements may be selected at once, including discontiguous ranges. In multiple mode, clicking button 1 on an element toggles its selection state without affecting any other elements. In extended mode, pressing button 1 on an element selects it, deselects everything else, and sets the anchor to the element under the mouse; dragging the mouse with button 1 down extends the selection to include all the elements between the anchor and the element under the mouse, inclusive. In extended mode, the selected range can be adjusted by pressing button 1 with the Shift key down: this modifies the selection to consist of the elements between the anchor and the element under the mouse, inclusive. The un-anchored end of this new selection can also be dragged with the button down. Also in extended mode, pressing button 1 with the Control key down starts a toggle operation: the anchor is set to the element under the mouse, and its selection state is reversed. The selection state of other elements is not changed. If the mouse is dragged with button 1 down, then the selection state of all elements between the anchor and the element under the mouse is set to match that of the anchor element; the selection state of all other elements remains what it was before the toggle operation began. Most people will probably want to use browse mode for single selections and extended mode for multiple selections; the other modes appear to be useful only in special situations. mode: value Set the value of the mode option for the widget. Specifies one of several styles for manipulating the selection. The value of the option may be either single, browse, multiple, or extended. If the selection mode is single or browse, at most one element can be selected in the listbox at once. Clicking button 1 on an unselected element selects it and deselects any other selected item, while clicking on a selected element has no effect. In browse mode it is also possible to drag the selection with button 1. That is, moving the mouse while button 1 is pressed keeps the item under the cursor selected. If the selection mode is multiple or extended, any number of elements may be selected at once, including discontiguous ranges. In multiple mode, clicking button 1 on an element toggles its selection state without affecting any other elements. In extended mode, pressing button 1 on an element selects it, deselects everything else, and sets the anchor to the element under the mouse; dragging the mouse with button 1 down extends the selection to include all the elements between the anchor and the element under the mouse, inclusive. In extended mode, the selected range can be adjusted by pressing button 1 with the Shift key down: this modifies the selection to consist of the elements between the anchor and the element under the mouse, inclusive. The un-anchored end of this new selection can also be dragged with the button down. Also in extended mode, pressing button 1 with the Control key down starts a toggle operation: the anchor is set to the element under the mouse, and its selection state is reversed. The selection state of other elements is not changed. If the mouse is dragged with button 1 down, then the selection state of all elements between the anchor and the element under the mouse is set to match that of the anchor element; the selection state of all other elements remains what it was before the toggle operation began. Most people will probably want to use browse mode for single selections and extended mode for multiple selections; the other modes appear to be useful only in special situations. numberOfStrings Answer the number of items in the list box removeAtIndex: index Remove the item at the given index in the list box, answering the object associated to the element (i.e. the value that #at: would have returned for the given index) size Answer the number of items in the list box  File: gst-libs.info, Node: BLOX.BList-widget protocol, Prev: BLOX.BList-accessing, Up: BLOX.BList 1.25.2 BLOX.BList: widget protocol ---------------------------------- callback Answer a DirectedMessage that is sent when the active item in the receiver changes, or nil if none has been set up. callback: aReceiver message: aSymbol Set up so that aReceiver is sent the aSymbol message (the name of a selector with at most two arguemtnts) when the active item in the receiver changegs. If the method accepts two arguments, the receiver is passed as the first parameter. If the method accepts one or two arguments, the selected index is passed as the last parameter. highlight: index Highlight the item at the given position in the listbox. invokeCallback Generate a synthetic callback. select: index Highlight the item at the given position in the listbox, without unhighlighting other items. This is meant for multiple- or extended-mode listboxes, but can be used with other selection mode in particular cases. show: index Ensure that the item at the given position in the listbox is visible. unhighlight Unhighlight all the items in the listbox. unselect: index Unhighlight the item at the given position in the listbox, without affecting the state of the other items.  File: gst-libs.info, Node: BLOX.Blox, Next: BLOX.BMenu, Prev: BLOX.BList, Up: BLOX package 1.26 BLOX.Blox ============== Defined in namespace BLOX Superclass: BLOX.BEventTarget Category: Graphics-Windows I am the superclass for every visible user interface object (excluding canvas items, which are pretty different). I provide common methods and a simple Tcl interface for internal use. In addition, I expose class methods that do many interesting event-handling things. NOTE: some of the methods (notably geometry methods) may not be suitable for all Blox subclasses and may be included only for backwards compatibility towards 1.1.5 BLOX. You should use geometry methods only for subclasses of BWidget. * Menu: * BLOX.Blox class-C call-outs:: (class) * BLOX.Blox class-event dispatching:: (class) * BLOX.Blox class-instance creation:: (class) * BLOX.Blox class-utility:: (class) * BLOX.Blox-accessing:: (instance) * BLOX.Blox-basic:: (instance) * BLOX.Blox-creating children:: (instance) * BLOX.Blox-customization:: (instance) * BLOX.Blox-widget protocol:: (instance)  File: gst-libs.info, Node: BLOX.Blox class-C call-outs, Next: BLOX.Blox class-event dispatching, Up: BLOX.Blox 1.26.1 BLOX.Blox class: C call-outs ----------------------------------- evalIn: interp tcl: cmd Not commented. idle Not commented. resultIn: interp Not commented. tclInit Not commented.  File: gst-libs.info, Node: BLOX.Blox class-event dispatching, Next: BLOX.Blox class-instance creation, Prev: BLOX.Blox class-C call-outs, Up: BLOX.Blox 1.26.2 BLOX.Blox class: event dispatching ----------------------------------------- dispatchEvents If this is the outermost dispatching loop that is started, dispatch events until the number of calls to #terminateMainLoop balances the number of calls to #dispatchEvents; return instantly if this is not the outermost dispatching loop that is started. dispatchEvents: mainWindow Dispatch some events; return upon destruction of the `mainWindow' widget (which can be any kind of BWidget, but will be typically a BWindow). terminateMainLoop Terminate the event dispatching loop if this call to #terminateMainLoop balances the number of calls to #dispatchEvents. update: aspect Initialize the Tcl and Blox environments; executed automatically on startup.  File: gst-libs.info, Node: BLOX.Blox class-instance creation, Next: BLOX.Blox class-utility, Prev: BLOX.Blox class-event dispatching, Up: BLOX.Blox 1.26.3 BLOX.Blox class: instance creation ----------------------------------------- new This method should not be called for instances of this class. new: parent Create a new widget of the type identified by the receiver, inside the given parent widget. Answer the new widget  File: gst-libs.info, Node: BLOX.Blox class-utility, Next: BLOX.Blox-accessing, Prev: BLOX.Blox class-instance creation, Up: BLOX.Blox 1.26.4 BLOX.Blox class: utility ------------------------------- active Answer the currently active Blox, or nil if the focus does not belong to a Smalltalk window. at: aPoint Answer the Blox containing the given point on the screen, or nil if no Blox contains the given point (either because no Smalltalk window is there or because it is covered by another window). atMouse Answer the Blox under the mouse cursor's hot spot, or nil if no Blox contains the given point (either because no Smalltalk window is there or because it is covered by another window). beep Produce a bell clearClipboard Clear the clipboard, answer its old contents. clipboard Retrieve the text in the clipboard. clipboard: aString Set the contents of the clipboard to aString (or empty the clipboard if aString is nil). createColor: red green: green blue: blue Answer a color that can be passed to methods such as `backgroundColor:'. The color will have the given RGB components (range is 0~65535). createColor: cyan magenta: magenta yellow: yellow Answer a color that can be passed to methods such as `backgroundColor:'. The color will have the given CMY components (range is 0~65535). createColor: cyan magenta: magenta yellow: yellow black: black Answer a color that can be passed to methods such as `backgroundColor:'. The color will have the given CMYK components (range is 0~65535). createColor: hue saturation: sat value: value Answer a color that can be passed to methods such as `backgroundColor:'. The color will have the given HSV components (range is 0~65535). defaultFont Answer the default font used by Blox. fonts Answer the names of the font families in the system. Additionally, `Times', `Courier' and `Helvetica' are always made available. mousePointer If the mouse pointer is on the same screen as the application's windows, returns a Point containing the pointer's x and y coordinates measured in pixels in the screen's root window (under X, if a virtual root window is in use on the screen, the position is computed in the whole desktop, not relative to the top-left corner of the currently shown portion). If the mouse pointer isn't on the same screen as window then answer nil. platform Answer the platform on which Blox is running; it can be either #unix, #macintosh or #windows. screenOrigin Answer a Point indicating the coordinates of the upper left point of the screen in the virtual root window on which the application's windows are drawn (under Windows and the Macintosh, that's always 0 @ 0) screenResolution Answer a Point containing the resolution in dots per inch of the screen, in the x and y directions. screenSize Answer a Point containing the size of the virtual root window on which the application's windows are drawn (under Windows and the Macintosh, that's the size of the screen)  File: gst-libs.info, Node: BLOX.Blox-accessing, Next: BLOX.Blox-basic, Prev: BLOX.Blox class-utility, Up: BLOX.Blox 1.26.5 BLOX.Blox: accessing --------------------------- state Answer the value of the state option for the widget. Specifies one of three states for the button: normal, active, or disabled. In normal state the button is displayed using the foreground and background options. The active state is typically used when the pointer is over the button. In active state the button is displayed using the activeForeground and activeBackground options. Disabled state means that the button should be insensitive: the application will refuse to activate the widget and will ignore mouse button presses. state: value Set the value of the state option for the widget. Specifies one of three states for the button: normal, active, or disabled. In normal state the button is displayed using the foreground and background options. The active state is typically used when the pointer is over the button. In active state the button is displayed using the activeForeground and activeBackground options. Disabled state means that the button should be insensitive: the application will refuse to activate the widget and will ignore mouse button presses.  File: gst-libs.info, Node: BLOX.Blox-basic, Next: BLOX.Blox-creating children, Prev: BLOX.Blox-accessing, Up: BLOX.Blox 1.26.6 BLOX.Blox: basic ----------------------- deepCopy It does not make sense to make a copy, because it would make data inconsistent across different objects; so answer the receiver release Destroy the receiver if it still exists, then perform the usual task of removing the dependency links shallowCopy It does not make sense to make a copy, because it would make data inconsistent across different objects; so answer the receiver  File: gst-libs.info, Node: BLOX.Blox-creating children, Next: BLOX.Blox-customization, Prev: BLOX.Blox-basic, Up: BLOX.Blox 1.26.7 BLOX.Blox: creating children ----------------------------------- make: array Create children of the receiver. Answer a Dictionary of the children. Each element of array is an Array including: a string which becomes the Dictionary's key, a binding like #{Blox.BWindow} identifying the class name, an array with the parameters to be set (for example #(#width: 50 #height: 30 #backgroundColor: 'blue')), and afterwards the children of the widget, described as arrays with this same format. make: array on: result Private - Create children of the receiver, adding them to result; answer result. array has the format described in the comment to #make: makeChild: each on: result Private - Create a child of the receiver, adding them to result; each is a single element of the array described in the comment to #make:  File: gst-libs.info, Node: BLOX.Blox-customization, Next: BLOX.Blox-widget protocol, Prev: BLOX.Blox-creating children, Up: BLOX.Blox 1.26.8 BLOX.Blox: customization ------------------------------- addChild: child The widget identified by child has been added to the receiver. This method is public not because you can call it, but because it can be useful to override it, not forgetting the call to either the superclass implementation or #basicAddChild:, to perform some initialization on the children just added. Answer the new child. basicAddChild: child The widget identified by child has been added to the receiver. Add it to the children collection and answer the new child. This method is public because you can call it from #addChild:.  File: gst-libs.info, Node: BLOX.Blox-widget protocol, Prev: BLOX.Blox-customization, Up: BLOX.Blox 1.26.9 BLOX.Blox: widget protocol --------------------------------- asPrimitiveWidget Answer the primitive widget that implements the receiver. childrenCount Answer how many children the receiver has childrenDo: aBlock Evaluate aBlock once for each of the receiver's child widgets, passing the widget to aBlock as a parameter destroy Destroy the receiver drawingArea Answer a Rectangle identifying the receiver's drawing area. The rectangle's corners specify the upper-left and lower-right corners of the client area. Because coordinates are relative to the upper-left corner of a window's drawing area, the coordinates of the rectangle's corner are (0,0). enabled Answer whether the receiver is enabled to input. Although defined here, this method is only used for widgets that define a #state method enabled: enabled Set whether the receiver is enabled to input (enabled is a boolean). Although defined here, this method is only used for widgets that define a #state: method exists Answer whether the receiver has been destroyed or not (answer false in the former case, true in the latter). fontHeight: aString Answer the height of aString in pixels, when displayed in the same font as the receiver. Although defined here, this method is only used for widgets that define a #font method fontWidth: aString Answer the width of aString in pixels, when displayed in the same font as the receiver. Although defined here, this method is only used for widgets that define a #font method isWindow Answer whether the receiver represents a window on the screen. parent Answer the receiver's parent (or nil for a top-level window). toplevel Answer the top-level object (typically a BWindow or BPopupWindow) connected to the receiver. window Answer the window in which the receiver stays. Note that while #toplevel won't answer a BTransientWindow, this method will. withChildrenDo: aBlock Evaluate aBlock passing the receiver, and then once for each of the receiver's child widgets.  File: gst-libs.info, Node: BLOX.BMenu, Next: BLOX.BMenuBar, Prev: BLOX.Blox, Up: BLOX package 1.27 BLOX.BMenu =============== Defined in namespace BLOX Superclass: BLOX.BMenuObject Category: Graphics-Windows I am a Menu that is part of a menu bar. * Menu: * BLOX.BMenu class-instance creation:: (class) * BLOX.BMenu-accessing:: (instance) * BLOX.BMenu-callback registration:: (instance)  File: gst-libs.info, Node: BLOX.BMenu class-instance creation, Next: BLOX.BMenu-accessing, Up: BLOX.BMenu 1.27.1 BLOX.BMenu class: instance creation ------------------------------------------ new: parent label: label Add a new menu to the parent window's menu bar, with `label' as its caption (for popup menus, parent is the widget over which the menu pops up as the right button is pressed).  File: gst-libs.info, Node: BLOX.BMenu-accessing, Next: BLOX.BMenu-callback registration, Prev: BLOX.BMenu class-instance creation, Up: BLOX.BMenu 1.27.2 BLOX.BMenu: accessing ---------------------------- label Answer the value of the label option for the widget. Specifies a string to be displayed inside the widget. The way in which the string is displayed depends on the particular widget and may be determined by other options, such as anchor. For windows, this is the title of the window. label: value Set the value of the label option for the widget. Specifies a string to be displayed inside the widget. The way in which the string is displayed depends on the particular widget and may be determined by other options, such as anchor. For windows, this is the title of the window.  File: gst-libs.info, Node: BLOX.BMenu-callback registration, Prev: BLOX.BMenu-accessing, Up: BLOX.BMenu 1.27.3 BLOX.BMenu: callback registration ---------------------------------------- addLine Add a separator item at the end of the menu addMenuItemFor: anArray notifying: receiver Add a menu item described by anArray at the end of the menu. If anArray is empty, insert a separator line. If anArray has a single item, a menu item is created without a callback. If anArray has two or three items, the second one is used as the selector sent to receiver, and the third one (if present) is passed to the selector. callback: receiver using: selectorPairs Add menu items described by anArray at the end of the menu. Each element of selectorPairs must be in the format described in BMenu>>#addMenuItemFor:notifying:. All the callbacks will be sent to receiver. destroy Destroy the menu widget; that is, simply remove ourselves from the parent menu bar. empty Empty the menu widget; that is, remove all the children  File: gst-libs.info, Node: BLOX.BMenuBar, Next: BLOX.BMenuItem, Prev: BLOX.BMenu, Up: BLOX package 1.28 BLOX.BMenuBar ================== Defined in namespace BLOX Superclass: BLOX.BMenuObject Category: Graphics-Windows I am the Menu Bar, the top widget in a full menu structure. * Menu: * BLOX.BMenuBar-accessing:: (instance)  File: gst-libs.info, Node: BLOX.BMenuBar-accessing, Up: BLOX.BMenuBar 1.28.1 BLOX.BMenuBar: accessing ------------------------------- add: aMenu Add aMenu to the menu bar remove: aMenu Remove aMenu from the menu bar  File: gst-libs.info, Node: BLOX.BMenuItem, Next: BLOX.BMenuObject, Prev: BLOX.BMenuBar, Up: BLOX package 1.29 BLOX.BMenuItem =================== Defined in namespace BLOX Superclass: BLOX.BMenuObject Category: Graphics-Windows I am the tiny and humble Menu Item, a single command choice in the menu structure. But if it wasn't for me, nothing could be done... eh eh eh!! * Menu: * BLOX.BMenuItem class-instance creation:: (class) * BLOX.BMenuItem-accessing:: (instance)  File: gst-libs.info, Node: BLOX.BMenuItem class-instance creation, Next: BLOX.BMenuItem-accessing, Up: BLOX.BMenuItem 1.29.1 BLOX.BMenuItem class: instance creation ---------------------------------------------- new: parent Add a new separator item to the specified menu. new: parent label: label Add a new menu item to the specified menu (parent) , with `label' as its caption.  File: gst-libs.info, Node: BLOX.BMenuItem-accessing, Prev: BLOX.BMenuItem class-instance creation, Up: BLOX.BMenuItem 1.29.2 BLOX.BMenuItem: accessing -------------------------------- label Answer the value of the label option for the widget. Specifies a string to be displayed inside the widget. The way in which the string is displayed depends on the particular widget and may be determined by other options, such as anchor. For windows, this is the title of the window. label: value Set the value of the label option for the widget. Specifies a string to be displayed inside the widget. The way in which the string is displayed depends on the particular widget and may be determined by other options, such as anchor. For windows, this is the title of the window.  File: gst-libs.info, Node: BLOX.BMenuObject, Next: BLOX.BOval, Prev: BLOX.BMenuItem, Up: BLOX package 1.30 BLOX.BMenuObject ===================== Defined in namespace BLOX Superclass: BLOX.Blox Category: Graphics-Windows I am an abstract superclass for widgets which make up a menu structure. * Menu: * BLOX.BMenuObject-accessing:: (instance) * BLOX.BMenuObject-callback:: (instance)  File: gst-libs.info, Node: BLOX.BMenuObject-accessing, Next: BLOX.BMenuObject-callback, Up: BLOX.BMenuObject 1.30.1 BLOX.BMenuObject: accessing ---------------------------------- activeBackground Answer the value of the activeBackground option for the widget. Specifies background color to use when drawing active elements. An element (a widget or portion of a widget) is active if the mouse cursor is positioned over the element and pressing a mouse button will cause some action to occur. For some elements on Windows and Macintosh systems, the active color will only be used while mouse button 1 is pressed over the element. activeBackground: value Set the value of the activeBackground option for the widget. Specifies background color to use when drawing active elements. An element (a widget or portion of a widget) is active if the mouse cursor is positioned over the element and pressing a mouse button will cause some action to occur. For some elements on Windows and Macintosh systems, the active color will only be used while mouse button 1 is pressed over the element. activeForeground Answer the value of the activeForeground option for the widget. Specifies foreground color to use when drawing active elements. See above for definition of active elements. activeForeground: value Set the value of the activeForeground option for the widget. Specifies foreground color to use when drawing active elements. See above for definition of active elements. asPrimitiveWidget Answer the primitive widget that implements the receiver. backgroundColor Answer the value of the backgroundColor option for the widget. Specifies the normal background color to use when displaying the widget. backgroundColor: value Set the value of the backgroundColor option for the widget. Specifies the normal background color to use when displaying the widget. foregroundColor Answer the value of the foregroundColor option for the widget. Specifies the normal foreground color to use when displaying the widget. foregroundColor: value Set the value of the foregroundColor option for the widget. Specifies the normal foreground color to use when displaying the widget.  File: gst-libs.info, Node: BLOX.BMenuObject-callback, Prev: BLOX.BMenuObject-accessing, Up: BLOX.BMenuObject 1.30.2 BLOX.BMenuObject: callback --------------------------------- callback Answer a DirectedMessage that is sent when the receiver is modified, or nil if none has been set up. callback: aReceiver message: aSymbol Set up so that aReceiver is sent the aSymbol message (the name of a zero- or one-argument selector) when the receiver is clicked. If the method accepts an argument, the receiver is passed. callback: aReceiver message: aSymbol argument: anObject Set up so that aReceiver is sent the aSymbol message (the name of a one- or two-argument selector) when the receiver is clicked. If the method accepts two argument, the receiver is passed together with anObject; if it accepts a single one, instead, only anObject is passed. invokeCallback Generate a synthetic callback  File: gst-libs.info, Node: BLOX.BOval, Next: BLOX.BPolyline, Prev: BLOX.BMenuObject, Up: BLOX package 1.31 BLOX.BOval =============== Defined in namespace BLOX Superclass: BLOX.BRectangle Category: Graphics-Windows I can draw ovals (ok, if you're a mathematic, they're really ellipses), or even circles. * Menu:  File: gst-libs.info, Node: BLOX.BPolyline, Next: BLOX.BPopupMenu, Prev: BLOX.BOval, Up: BLOX package 1.32 BLOX.BPolyline =================== Defined in namespace BLOX Superclass: BLOX.BCanvasObject Category: Graphics-Windows I can draw closed or open polylines, and even fill them! * Menu: * BLOX.BPolyline-accessing:: (instance)  File: gst-libs.info, Node: BLOX.BPolyline-accessing, Up: BLOX.BPolyline 1.32.1 BLOX.BPolyline: accessing -------------------------------- boundingBox Answer `boundingBox'. cap Answer the way in which caps are to be drawn at the endpoints of the line. This option is only available for open polylines. If you want to set it for a closed polylines, draw an open one on top of it. cap: aSymbol Set the way in which caps are to be drawn at the endpoints of the line. aSymbol may be #butt (the default), #projecting, or #round). This option is only available for open polylines. If you want to set it for a closed polylines, draw an open one on top of it. closed Answer whether the polyline is an open or a closed one. closed: aBoolean Set whether the polyline is an open or a closed one. This option may be set only once. join Answer the way in which joints are to be drawn at the vertices of the line. This option is only available for open polylines. If you want to set it for a closed polylines, draw an open one on top of it. join: aSymbol Answer the way in which joints are to be drawn at the vertices of the line. aSymbol can be #bevel, #miter (the default) or #round. This option is only available for open polylines. If you want to set it for a closed polylines, draw an open one on top of it. outlineColor Answer the color with which the outline of the polyline is drawn. This option is only available for closed polylines. outlineColor: color Set the color with which the outline of the polyline is drawn. This option is only available for closed polylines. points Answer the points that are vertices of the polyline. points: arrayOfPointsOrArrays Set the points that are vertices of the polyline. Each of the items of arrayOfPointsOrArrays can be a Point or a two-element Array. Note that no changes take place until you invoke the #create (if the object has not been inserted in the canvas yet) or the #redraw method. width Answer the width with which the polyline (or its outline if it is a closed one) is drawn. width: pixels Set the width with which the polyline (or its outline if it is a closed one) is drawn.  File: gst-libs.info, Node: BLOX.BPopupMenu, Next: BLOX.BPopupWindow, Prev: BLOX.BPolyline, Up: BLOX package 1.33 BLOX.BPopupMenu ==================== Defined in namespace BLOX Superclass: BLOX.BMenu Category: Graphics-Windows I am a class that provides the ability to show popup menus when the right button (Button 3) is clicked on another window. * Menu: * BLOX.BPopupMenu-widget protocol:: (instance)  File: gst-libs.info, Node: BLOX.BPopupMenu-widget protocol, Up: BLOX.BPopupMenu 1.33.1 BLOX.BPopupMenu: widget protocol --------------------------------------- popup Generate a synthetic menu popup event  File: gst-libs.info, Node: BLOX.BPopupWindow, Next: BLOX.BPrimitive, Prev: BLOX.BPopupMenu, Up: BLOX package 1.34 BLOX.BPopupWindow ====================== Defined in namespace BLOX Superclass: BLOX.BWindow Category: Graphics-Windows I am a pseudo-window that has no decorations and no ability to interact with the user. My main usage, as my name says, is to provide pop-up functionality for other widgets. Actually there should be no need to directly use me - always rely on the #new and #popup: class methods. * Menu: * BLOX.BPopupWindow-geometry management:: (instance)  File: gst-libs.info, Node: BLOX.BPopupWindow-geometry management, Up: BLOX.BPopupWindow 1.34.1 BLOX.BPopupWindow: geometry management --------------------------------------------- addChild: w Private - The widget identified by child has been added to the receiver. This method is public not because you can call it, but because it can be useful to override it, not forgetting the call to either the superclass implementation or #basicAddChild:, to perform some initialization on the children just added. Answer the new child. child: child height: value Set the given child's height. This is done by setting its parent window's (that is, our) height. child: child heightOffset: value This method should not be called for instances of this class. child: child width: value Set the given child's width. This is done by setting its parent window's (that is, our) width. child: child widthOffset: value This method should not be called for instances of this class. child: child x: value Set the x coordinate of the given child's top-left corner. This is done by setting its parent window's (that is, our) x. child: child xOffset: value This method should not be called for instances of this class. child: child y: value Set the y coordinate of the given child's top-left corner. This is done by setting its parent window's (that is, our) y. child: child yOffset: value This method should not be called for instances of this class. heightChild: child Answer the given child's height, which is the height that was imposed on the popup window. widthChild: child Answer the given child's width in pixels, which is the width that was imposed on the popup window. xChild: child Answer the x coordinate of the given child's top-left corner, which is desumed by the position of the popup window. yChild: child Answer the y coordinate of the given child's top-left corner, which is desumed by the position of the popup window.  File: gst-libs.info, Node: BLOX.BPrimitive, Next: BLOX.BProgress, Prev: BLOX.BPopupWindow, Up: BLOX package 1.35 BLOX.BPrimitive ==================== Defined in namespace BLOX Superclass: BLOX.BWidget Category: Graphics-Windows I am the superclass for every widget (except menus) directly provided by the underlying GUI system. * Menu: * BLOX.BPrimitive-accessing:: (instance)  File: gst-libs.info, Node: BLOX.BPrimitive-accessing, Up: BLOX.BPrimitive 1.35.1 BLOX.BPrimitive: accessing --------------------------------- asPrimitiveWidget Answer the primitive widget that implements the receiver.  File: gst-libs.info, Node: BLOX.BProgress, Next: BLOX.BRadioButton, Prev: BLOX.BPrimitive, Up: BLOX package 1.36 BLOX.BProgress =================== Defined in namespace BLOX Superclass: BLOX.BExtended Category: Graphics-Examples I show how much of a task has been completed. * Menu: * BLOX.BProgress-accessing:: (instance)  File: gst-libs.info, Node: BLOX.BProgress-accessing, Up: BLOX.BProgress 1.36.1 BLOX.BProgress: accessing -------------------------------- backgroundColor Answer the background color of the widget. This is used for the background of the non-filled part, as well as for the foreground of the filled part. backgroundColor: aColor Set the background color of the widget. This is used for the background of the non-filled part, as well as for the foreground of the filled part. filledColor Answer the background color of the widget's filled part. filledColor: aColor Set the background color of the widget's filled part. foregroundColor Set the foreground color of the widget. This is used for the non-filled part, while the background color also works as the foreground of the filled part. foregroundColor: aColor Set the foreground color of the widget. This is used for the non-filled part, while the background color also works as the foreground of the filled part. value Answer the filled percentage of the receiver (0..1) value: newValue Set the filled percentage of the receiver and update the appearance. newValue must be between 0 and 1.  File: gst-libs.info, Node: BLOX.BRadioButton, Next: BLOX.BRadioGroup, Prev: BLOX.BProgress, Up: BLOX package 1.37 BLOX.BRadioButton ====================== Defined in namespace BLOX Superclass: BLOX.BButton Category: Graphics-Windows I am just one in a group of mutually exclusive buttons. * Menu: * BLOX.BRadioButton-accessing:: (instance)  File: gst-libs.info, Node: BLOX.BRadioButton-accessing, Up: BLOX.BRadioButton 1.37.1 BLOX.BRadioButton: accessing ----------------------------------- callback: aReceiver message: aSymbol Set up so that aReceiver is sent the aSymbol message (the name of a selector accepting at most two arguments) when the receiver is clicked. If the method accepts two arguments, the receiver is passed as the first parameter. If the method accepts one or two arguments, true is passed as the last parameter for interoperability with BToggle widgets. value Answer whether this widget is the selected one in its radio button group. value: aBoolean Answer whether this widget is the selected one in its radio button group. Setting this property to false for a group's currently selected button unhighlights all the buttons in that group.  File: gst-libs.info, Node: BLOX.BRadioGroup, Next: BLOX.BRectangle, Prev: BLOX.BRadioButton, Up: BLOX package 1.38 BLOX.BRadioGroup ===================== Defined in namespace BLOX Superclass: BLOX.BContainer Category: Graphics-Windows I am used to group many mutually-exclusive radio buttons together. In addition, just like every BContainer I can perform simple management by putting widgets next to each other, from left to right or (which is more useful in this particular case...) from top to bottom. * Menu: * BLOX.BRadioGroup-accessing:: (instance) * BLOX.BRadioGroup-widget protocol:: (instance)  File: gst-libs.info, Node: BLOX.BRadioGroup-accessing, Next: BLOX.BRadioGroup-widget protocol, Up: BLOX.BRadioGroup 1.38.1 BLOX.BRadioGroup: accessing ---------------------------------- value Answer the index of the button that is currently selected, 1 being the first button added to the radio button group. 0 means that no button is selected value: value Force the value-th button added to the radio button group to be the selected one.  File: gst-libs.info, Node: BLOX.BRadioGroup-widget protocol, Prev: BLOX.BRadioGroup-accessing, Up: BLOX.BRadioGroup 1.38.2 BLOX.BRadioGroup: widget protocol ---------------------------------------- destroyed Private - The receiver has been destroyed, clear the corresponding Tcl variable to avoid memory leaks.  File: gst-libs.info, Node: BLOX.BRectangle, Next: BLOX.BScrolledCanvas, Prev: BLOX.BRadioGroup, Up: BLOX package 1.39 BLOX.BRectangle ==================== Defined in namespace BLOX Superclass: BLOX.BBoundingBox Category: Graphics-Windows I only draw rectangles but I can do that very well. * Menu: * BLOX.BRectangle-accessing:: (instance)  File: gst-libs.info, Node: BLOX.BRectangle-accessing, Up: BLOX.BRectangle 1.39.1 BLOX.BRectangle: accessing --------------------------------- outlineColor Answer the color with which the outline of the rectangle is drawn. outlineColor: color Set the color with which the outline of the rectangle is drawn. width Answer the width with which the outline of the rectangle is drawn. width: pixels Set the width with which the outline of the rectangle is drawn.  File: gst-libs.info, Node: BLOX.BScrolledCanvas, Next: BLOX.BSpline, Prev: BLOX.BRectangle, Up: BLOX package 1.40 BLOX.BScrolledCanvas ========================= Defined in namespace BLOX Superclass: BLOX.BCanvas Category: Graphics-Windows I am much similar to BCanvas, but I sport, in addition, two fancy scroll bars. This is just a convenience, since it could be easily done when creating the canvas... * Menu:  File: gst-libs.info, Node: BLOX.BSpline, Next: BLOX.BText, Prev: BLOX.BScrolledCanvas, Up: BLOX package 1.41 BLOX.BSpline ================= Defined in namespace BLOX Superclass: BLOX.BPolyline Category: Graphics-Windows Unlike my father BPolyline, I am more smooth at doing my job. * Menu: * BLOX.BSpline-accessing:: (instance)  File: gst-libs.info, Node: BLOX.BSpline-accessing, Up: BLOX.BSpline 1.41.1 BLOX.BSpline: accessing ------------------------------ smoothness Answer the degree of smoothness desired for curves. Each spline will be approximated with this number of line segments. smoothness: anInteger Set the degree of smoothness desired for curves. Each spline will be approximated with this number of line segments.  File: gst-libs.info, Node: BLOX.BText, Next: BLOX.BTextAttributes, Prev: BLOX.BSpline, Up: BLOX package 1.42 BLOX.BText =============== Defined in namespace BLOX Superclass: BLOX.BViewport Category: Graphics-Windows I represent a text viewer with pretty good formatting options. * Menu: * BLOX.BText class-accessing:: (class) * BLOX.BText class-instance creation:: (class) * BLOX.BText-accessing:: (instance) * BLOX.BText-attributes:: (instance) * BLOX.BText-geometry management:: (instance) * BLOX.BText-images:: (instance) * BLOX.BText-inserting text:: (instance) * BLOX.BText-position & lines:: (instance)  File: gst-libs.info, Node: BLOX.BText class-accessing, Next: BLOX.BText class-instance creation, Up: BLOX.BText 1.42.1 BLOX.BText class: accessing ---------------------------------- emacsLike Answer whether we are using Emacs or Motif key bindings. emacsLike: aBoolean Set whether we are using Emacs or Motif key bindings.  File: gst-libs.info, Node: BLOX.BText class-instance creation, Next: BLOX.BText-accessing, Prev: BLOX.BText class-accessing, Up: BLOX.BText 1.42.2 BLOX.BText class: instance creation ------------------------------------------ newReadOnly: parent Answer a new read-only text widget (read-only is achieved simply by setting its state to be disabled)  File: gst-libs.info, Node: BLOX.BText-accessing, Next: BLOX.BText-attributes, Prev: BLOX.BText class-instance creation, Up: BLOX.BText 1.42.3 BLOX.BText: accessing ---------------------------- backgroundColor Answer the value of the backgroundColor option for the widget. Specifies the normal background color to use when displaying the widget. backgroundColor: value Set the value of the backgroundColor option for the widget. Specifies the normal background color to use when displaying the widget. callback Answer a DirectedMessage that is sent when the receiver is modified, or nil if none has been set up. callback: aReceiver message: aSymbol Set up so that aReceiver is sent the aSymbol message (the name of a zero- or one-argument selector) when the receiver is modified. If the method accepts an argument, the receiver is passed. contents Return the contents of the widget contents: aString Set the contents of the widget font Answer the value of the font option for the widget. Specifies the font to use when drawing text inside the widget. The font can be given as either an X font name or a Blox font description string. X font names are given as many fields, each led by a minus, and each of which can be replaced by an * to indicate a default value is ok: foundry, family, weight, slant, setwidth, addstyle, pixel size, point size (the same as pixel size for historical reasons), horizontal resolution, vertical resolution, spacing, width, charset and character encoding. Blox font description strings have three fields, which must be separated by a space and of which only the first is mandatory: the font family, the font size in points (or in pixels if a negative value is supplied), and a number of styles separated by a space (valid styles are normal, bold, italic, underline and overstrike). Examples of valid fonts are "Helvetica 10 Bold", "Times -14", "Futura Bold Underline". You must enclose the font family in braces if it is made of two or more words. font: value Set the value of the font option for the widget. Specifies the font to use when drawing text inside the widget. The font can be given as either an X font name or a Blox font description string. X font names are given as many fields, each led by a minus, and each of which can be replaced by an * to indicate a default value is ok: foundry, family, weight, slant, setwidth, addstyle, pixel size, point size (the same as pixel size for historical reasons), horizontal resolution, vertical resolution, spacing, width, charset and character encoding. Blox font description strings have three fields, which must be separated by a space and of which only the first is mandatory: the font family, the font size in points (or in pixels if a negative value is supplied), and a number of styles separated by a space (valid styles are normal, bold, italic, underline and overstrike). Examples of valid fonts are "Helvetica 10 Bold", "Times -14", "Futura Bold Underline". You must enclose the font family in braces if it is made of two or more words. foregroundColor Answer the value of the foregroundColor option for the widget. Specifies the normal foreground color to use when displaying the widget. foregroundColor: value Set the value of the foregroundColor option for the widget. Specifies the normal foreground color to use when displaying the widget. getSelection Answer an empty string if the widget has no selection, else answer the currently selected text selectBackground Answer the value of the selectBackground option for the widget. Specifies the background color to use when displaying selected parts of the widget. selectBackground: value Set the value of the selectBackground option for the widget. Specifies the background color to use when displaying selected parts of the widget. selectForeground Answer the value of the selectForeground option for the widget. Specifies the foreground color to use when displaying selected parts of the widget. selectForeground: value Set the value of the selectForeground option for the widget. Specifies the foreground color to use when displaying selected parts of the widget. wrap Answer the value of the wrap option for the widget. Specifies how to handle lines in the text that are too long to be displayed in a single line of the text's window. The value must be #none or #char or #word. A wrap mode of none means that each line of text appears as exactly one line on the screen; extra characters that do not fit on the screen are not displayed. In the other modes each line of text will be broken up into several screen lines if necessary to keep all the characters visible. In char mode a screen line break may occur after any character; in word mode a line break will only be made at word boundaries. wrap: value Set the value of the wrap option for the widget. Specifies how to handle lines in the text that are too long to be displayed in a single line of the text's window. The value must be #none or #char or #word. A wrap mode of none means that each line of text appears as exactly one line on the screen; extra characters that do not fit on the screen are not displayed. In the other modes each line of text will be broken up into several screen lines if necessary to keep all the characters visible. In char mode a screen line break may occur after any character; in word mode a line break will only be made at word boundaries.  File: gst-libs.info, Node: BLOX.BText-attributes, Next: BLOX.BText-geometry management, Prev: BLOX.BText-accessing, Up: BLOX.BText 1.42.4 BLOX.BText: attributes ----------------------------- insertAtEnd: aString attribute: attr Clear the selection and append aString at the end of the widget. Use the given attributes to format the text. insertText: aString attribute: attr Insert aString in the widget at the current insertion point, replacing the currently selected text (if any). Use the given attributes to format the text. removeAttributes Remove any kind of formatting from the text in the widget removeAttributesFrom: aPoint to: endPoint Remove any kind of formatting from the text in the widget between the given endpoints. The two endpoints are Point objects in which both coordinates are 1-based: the first line is line 1, and the first character in the first line is character 1. setAttributes: attr from: aPoint to: endPoint Add the formatting given by attr to the text in the widget between the given endpoints. The two endpoints are Point objects in which both coordinates are 1-based: the first line is line 1, and the first character in the first line is character 1.  File: gst-libs.info, Node: BLOX.BText-geometry management, Next: BLOX.BText-images, Prev: BLOX.BText-attributes, Up: BLOX.BText 1.42.5 BLOX.BText: geometry management -------------------------------------- child: child height: value Set the height of the given child to be `value' pixels. child: child heightOffset: value Adjust the height of the given child to be given by `value' more pixels. child: child width: value Set the width of the given child to be `value' pixels. child: child widthOffset: value Adjust the width of the given child to be given by `value' more pixels. child: child x: value Never fail and do nothing, the children stay where the text ended at the time each child was added in the widget child: child xOffset: value This method should not be called for instances of this class. child: child y: value Never fail and do nothing, the children stay where the text ended at the time each child was added in the widget child: child yOffset: value This method should not be called for instances of this class. heightChild: child Answer the given child's height in pixels. widthChild: child Answer the given child's width in pixels. xChild: child Answer the given child's top-left border's x coordinate. We always answer 0 since the children actually move when the text widget scrolls yChild: child Answer the given child's top-left border's y coordinate. We always answer 0 since the children actually move when the text widget scrolls  File: gst-libs.info, Node: BLOX.BText-images, Next: BLOX.BText-inserting text, Prev: BLOX.BText-geometry management, Up: BLOX.BText 1.42.6 BLOX.BText: images ------------------------- insertImage: anObject Insert an image where the insertion point currently lies in the widget. anObject can be a String containing image data (either Base-64 encoded GIF data, XPM data, or PPM data), or the result or registering an image with #registerImage: insertImage: anObject at: position Insert an image at the given position in the widget. The position is a Point object in which both coordinates are 1-based: the first line is line 1, and the first character in the first line is character 1. anObject can be a String containing image data (either Base-64 encoded GIF data, XPM data, or PPM data), or the result or registering an image with #registerImage: insertImageAtEnd: anObject Insert an image at the end of the widgets text. anObject can be a String containing image data (either Base-64 encoded GIF data, XPM data, or PPM data), or the result or registering an image with #registerImage: registerImage: anObject Register an image (whose data is in anObject, a String including Base-64 encoded GIF data, XPM data, or PPM data) to be used in the widget. If the same image must be used a lot of times, it is better to register it once and then pass the result of #registerImage: to the image insertion methods. Registered image are private within each BText widget. Registering an image with a widget and using it with another could give unpredictable results.  File: gst-libs.info, Node: BLOX.BText-inserting text, Next: BLOX.BText-position & lines, Prev: BLOX.BText-images, Up: BLOX.BText 1.42.7 BLOX.BText: inserting text --------------------------------- insertAtEnd: aString Clear the selection and append aString at the end of the widget. insertSelectedText: aString Insert aString in the widget at the current insertion point, leaving the currently selected text (if any) in place, and selecting the text. insertText: aString Insert aString in the widget at the current insertion point, replacing the currently selected text (if any). insertText: aString at: position Insert aString in the widget at the given position, replacing the currently selected text (if any). The position is a Point object in which both coordinates are 1-based: the first line is line 1, and the first character in the first line is character 1. insertTextSelection: aString Insert aString in the widget after the current selection, leaving the currently selected text (if any) intact. invokeCallback Generate a synthetic callback. nextPut: aCharacter Clear the selection and append aCharacter at the end of the widget. nextPutAll: aString Clear the selection and append aString at the end of the widget. nl Clear the selection and append a linefeed character at the end of the widget. refuseTabs Arrange so that Tab characters, instead of being inserted in the widget, traverse the widgets in the parent window. replaceSelection: aString Insert aString in the widget at the current insertion point, replacing the currently selected text (if any), and leaving the text selected. searchString: aString Search aString in the widget. If it is not found, answer zero, else answer the 1-based line number and move the insertion point to the place where the string was found. space Clear the selection and append a space at the end of the widget.  File: gst-libs.info, Node: BLOX.BText-position & lines, Prev: BLOX.BText-inserting text, Up: BLOX.BText 1.42.8 BLOX.BText: position & lines ----------------------------------- charsInLine: number Answer how many characters are there in the number-th line currentColumn Answer the 1-based column number where the insertion point currently lies. currentLine Answer the 1-based line number where the insertion point currently lies. currentPosition Answer a Point representing where the insertion point currently lies. Both coordinates in the answer are 1-based: the first line is line 1, and the first character in the first line is character 1. currentPosition: aPoint Move the insertion point to the position given by aPoint. Both coordinates in aPoint are interpreted as 1-based: the first line is line 1, and the first character in the first line is character 1. gotoLine: line end: aBoolean If aBoolean is true, move the insertion point to the last character of the line-th line (1 being the first line in the widget); if aBoolean is false, move it to the start of the line-th line. indexAt: point Answer the position of the character that covers the pixel whose coordinates within the text's window are given by the supplied Point object. lineAt: number Answer the number-th line of text in the widget numberOfLines Answer the number of lines in the widget selectFrom: first to: last Select the text between the given endpoints. The two endpoints are Point objects in which both coordinates are 1-based: the first line is line 1, and the first character in the first line is character 1. setToEnd Move the insertion point to the end of the widget  File: gst-libs.info, Node: BLOX.BTextAttributes, Next: BLOX.BTextBindings, Prev: BLOX.BText, Up: BLOX package 1.43 BLOX.BTextAttributes ========================= Defined in namespace BLOX Superclass: Object Category: Graphics-Windows I help you creating wonderful, colorful BTexts. * Menu: * BLOX.BTextAttributes class-instance-creation shortcuts:: (class) * BLOX.BTextAttributes-colors:: (instance) * BLOX.BTextAttributes-setting attributes:: (instance)  File: gst-libs.info, Node: BLOX.BTextAttributes class-instance-creation shortcuts, Next: BLOX.BTextAttributes-colors, Up: BLOX.BTextAttributes 1.43.1 BLOX.BTextAttributes class: instance-creation shortcuts -------------------------------------------------------------- backgroundColor: color Create a new BTextAttributes object resulting in text with the given background color. black Create a new BTextAttributes object resulting in black text. blue Create a new BTextAttributes object resulting in blue text. center Create a new BTextAttributes object resulting in centered paragraphs. cyan Create a new BTextAttributes object resulting in cyan text. darkCyan Create a new BTextAttributes object resulting in dark cyan text. darkGreen Create a new BTextAttributes object resulting in dark green text. darkMagenta Create a new BTextAttributes object resulting in dark purple text. events: aBTextBindings Create a new BTextAttributes object for text that responds to events according to the callbacks established in aBTextBindings. font: font Create a new BTextAttributes object resulting in text with the given font. The font can be given as either an X font name or a Blox font description string. X font names are given as many fields, each led by a minus, and each of which can be replaced by an * to indicate a default value is ok: foundry, family, weight, slant, setwidth, addstyle, pixel size, point size (the same as pixel size for historical reasons), horizontal resolution, vertical resolution, spacing, width, charset and character encoding. Blox font description strings have three fields, which must be separated by a space and of which only the first is mandatory: the font family, the font size in points (or in pixels if a negative value is supplied), and a number of styles separated by a space (valid styles are normal, bold, italic, underline and overstrike). Examples of valid fonts are "Helvetica 10 Bold", "Times -14", "Futura Bold Underline". You must enclose the font family in braces if it is made of two or more words. foregroundColor: color Create a new BTextAttributes object resulting in text with the given foreground color. green Create a new BTextAttributes object resulting in green text. magenta Create a new BTextAttributes object resulting in magenta text. red Create a new BTextAttributes object resulting in red text. strikeout Create a new BTextAttributes object resulting in struck-out text. underline Create a new BTextAttributes object resulting in underlined text. white Create a new BTextAttributes object resulting in white text. yellow Create a new BTextAttributes object resulting in yellow text.  File: gst-libs.info, Node: BLOX.BTextAttributes-colors, Next: BLOX.BTextAttributes-setting attributes, Prev: BLOX.BTextAttributes class-instance-creation shortcuts, Up: BLOX.BTextAttributes 1.43.2 BLOX.BTextAttributes: colors ----------------------------------- black Set the receiver so that applying it results in black text. blue Set the receiver so that applying it results in blue text. cyan Set the receiver so that applying it results in cyan text. darkCyan Set the receiver so that applying it results in dark cyan text. darkGreen Set the receiver so that applying it results in dark green text. darkMagenta Set the receiver so that applying it results in dark magenta text. green Set the receiver so that applying it results in green text. magenta Set the receiver so that applying it results in magenta text. red Set the receiver so that applying it results in red text. white Set the receiver so that applying it results in white text. yellow Set the receiver so that applying it results in black text.  File: gst-libs.info, Node: BLOX.BTextAttributes-setting attributes, Prev: BLOX.BTextAttributes-colors, Up: BLOX.BTextAttributes 1.43.3 BLOX.BTextAttributes: setting attributes ----------------------------------------------- backgroundColor Answer the value of the backgroundColor option for the text. Specifies the background color to use when displaying text with these attributes. nil indicates that the default value is not overridden. backgroundColor: color Set the value of the backgroundColor option for the text. Specifies the background color to use when displaying text with these attributes. nil indicates that the default value is not overridden. center Center the text to which these attributes are applied events Answer the event bindings which apply to text subject to these attributes events: aBTextBindings Set the event bindings which apply to text subject to these attributes font Answer the value of the font option for the text. The font can be given as either an X font name or a Blox font description string, or nil if you want the widget's default font to apply. X font names are given as many fields, each led by a minus, and each of which can be replaced by an * to indicate a default value is ok: foundry, family, weight, slant, setwidth, addstyle, pixel size, point size (the same as pixel size for historical reasons), horizontal resolution, vertical resolution, spacing, width, charset and character encoding. Blox font description strings have three fields, which must be separated by a space and of which only the first is mandatory: the font family, the font size in points (or in pixels if a negative value is supplied), and a number of styles separated by a space (valid styles are normal, bold, italic, underline and overstrike). Examples of valid fonts are "Helvetica 10 Bold", "Times -14", "Futura Bold Underline". You must enclose the font family in braces if it is made of two or more words. font: fontName Set the value of the font option for the text. The font can be given as either an X font name or a Blox font description string, or nil if you want the widget's default font to apply. X font names are given as many fields, each led by a minus, and each of which can be replaced by an * to indicate a default value is ok: foundry, family, weight, slant, setwidth, addstyle, pixel size, point size (the same as pixel size for historical reasons), horizontal resolution, vertical resolution, spacing, width, charset and character encoding. Blox font description strings have three fields, which must be separated by a space and of which only the first is mandatory: the font family, the font size in points (or in pixels if a negative value is supplied), and a number of styles separated by a space (valid styles are normal, bold, italic, underline and overstrike). Examples of valid fonts are "Helvetica 10 Bold", "Times -14", "Futura Bold Underline". You must enclose the font family in braces if it is made of two or more words. foregroundColor Answer the value of the foregroundColor option for the text. Specifies the foreground color to use when displaying text with these attributes. nil indicates that the default value is not overridden. foregroundColor: color Set the value of the foregroundColor option for the text. Specifies the foreground color to use when displaying text with these attributes. nil indicates that the default value is not overridden. isCentered Answer whether the text to which these attributes are applied is centered isStruckout Answer whether the text to which these attributes are applied is struckout isUnderlined Answer whether the text to which these attributes are applied is underlined strikeout Strike out the text to which these attributes are applied underline Underline the text to which these attributes are applied  File: gst-libs.info, Node: BLOX.BTextBindings, Next: BLOX.BTextTags, Prev: BLOX.BTextAttributes, Up: BLOX package 1.44 BLOX.BTextBindings ======================= Defined in namespace BLOX Superclass: BLOX.BEventTarget Category: Graphics-Windows This object is used to assign event handlers to particular sections of text in a BText widget. To use it, you simply have to add event handlers to it, and then create a BTextAttributes object that refers to it. * Menu: * BLOX.BTextBindings class-instance creation:: (class)  File: gst-libs.info, Node: BLOX.BTextBindings class-instance creation, Up: BLOX.BTextBindings 1.44.1 BLOX.BTextBindings class: instance creation -------------------------------------------------- new Create a new instance of the receiver.  File: gst-libs.info, Node: BLOX.BTextTags, Next: BLOX.BToggle, Prev: BLOX.BTextBindings, Up: BLOX package 1.45 BLOX.BTextTags =================== Defined in namespace BLOX Superclass: Object Category: Graphics-Windows I am a private class. I sit between a BText and BTextAttributes, helping the latter in telling the former which attributes to use. * Menu:  File: gst-libs.info, Node: BLOX.BToggle, Next: BLOX.BTransientWindow, Prev: BLOX.BTextTags, Up: BLOX package 1.46 BLOX.BToggle ================= Defined in namespace BLOX Superclass: BLOX.BButton Category: Graphics-Windows I represent a button whose choice can be included (by checking me) or excluded (by leaving me unchecked). * Menu: * BLOX.BToggle-accessing:: (instance)  File: gst-libs.info, Node: BLOX.BToggle-accessing, Up: BLOX.BToggle 1.46.1 BLOX.BToggle: accessing ------------------------------ callback: aReceiver message: aSymbol Set up so that aReceiver is sent the aSymbol message (the name of a selector accepting at most two arguments) when the receiver is clicked. If the method accepts two arguments, the receiver is passed as the first parameter. If the method accepts one or two arguments, the state of the widget (true if it is selected, false if it is not) is passed as the last parameter. invokeCallback Generate a synthetic callback. value Answer whether the button is in a selected (checked) state. value: aBoolean Set whether the button is in a selected (checked) state and generates a callback accordingly. variable: value Set the value of Tk's variable option for the widget.  File: gst-libs.info, Node: BLOX.BTransientWindow, Next: BLOX.BViewport, Prev: BLOX.BToggle, Up: BLOX package 1.47 BLOX.BTransientWindow ========================== Defined in namespace BLOX Superclass: BLOX.BWindow Category: Graphics-Windows I am almost a boss. I represent a window which is logically linked to another which sits higher in the widget hierarchy, e.g. a dialog box * Menu: * BLOX.BTransientWindow class-instance creation:: (class) * BLOX.BTransientWindow-widget protocol:: (instance)  File: gst-libs.info, Node: BLOX.BTransientWindow class-instance creation, Next: BLOX.BTransientWindow-widget protocol, Up: BLOX.BTransientWindow 1.47.1 BLOX.BTransientWindow class: instance creation ----------------------------------------------------- new This method should not be called for instances of this class. new: parentWindow Answer a new transient window attached to the given parent window and with nothing in its title bar caption. new: label in: parentWindow Answer a new transient window attached to the given parent window and with `label' as its title bar caption.  File: gst-libs.info, Node: BLOX.BTransientWindow-widget protocol, Prev: BLOX.BTransientWindow class-instance creation, Up: BLOX.BTransientWindow 1.47.2 BLOX.BTransientWindow: widget protocol --------------------------------------------- map Map the window and inform the windows manager that the receiver is a transient window working on behalf of its parent. The window is also put in its parent window's window group: the window manager might use this information, for example, to unmap all of the windows in a group when the group's leader is iconified.  File: gst-libs.info, Node: BLOX.BViewport, Next: BLOX.BWidget, Prev: BLOX.BTransientWindow, Up: BLOX package 1.48 BLOX.BViewport =================== Defined in namespace BLOX Superclass: BLOX.BPrimitive Category: Graphics-Windows I represent an interface which is common to widgets that can be scrolled, like list boxes or text widgets. * Menu: * BLOX.BViewport-accessing:: (instance) * BLOX.BViewport-scrollbars:: (instance)  File: gst-libs.info, Node: BLOX.BViewport-accessing, Next: BLOX.BViewport-scrollbars, Up: BLOX.BViewport 1.48.1 BLOX.BViewport: accessing -------------------------------- connected Private - Answer the name of Tk widget for the connected widget.  File: gst-libs.info, Node: BLOX.BViewport-scrollbars, Prev: BLOX.BViewport-accessing, Up: BLOX.BViewport 1.48.2 BLOX.BViewport: scrollbars --------------------------------- horizontal Answer whether an horizontal scrollbar is drawn in the widget if needed. horizontal: aBoolean Set whether an horizontal scrollbar is drawn in the widget if needed. horizontalNeeded Answer whether an horizontal scrollbar is needed to show all the information in the widget. horizontalShown Answer whether an horizontal scrollbar is drawn in the widget. vertical Answer whether a vertical scrollbar is drawn in the widget if needed. vertical: aBoolean Set whether a vertical scrollbar is drawn in the widget if needed. verticalNeeded Answer whether a vertical scrollbar is needed to show all the information in the widget. verticalShown Answer whether a vertical scrollbar is drawn in the widget.  File: gst-libs.info, Node: BLOX.BWidget, Next: BLOX.BWindow, Prev: BLOX.BViewport, Up: BLOX package 1.49 BLOX.BWidget ================= Defined in namespace BLOX Superclass: BLOX.Blox Category: Graphics-Windows I am the superclass for every widget except those related to menus. I provide more common methods and geometry management * Menu: * BLOX.BWidget class-popups:: (class) * BLOX.BWidget-accessing:: (instance) * BLOX.BWidget-customization:: (instance) * BLOX.BWidget-geometry management:: (instance) * BLOX.BWidget-widget protocol:: (instance)  File: gst-libs.info, Node: BLOX.BWidget class-popups, Next: BLOX.BWidget-accessing, Up: BLOX.BWidget 1.49.1 BLOX.BWidget class: popups --------------------------------- new Create an instance of the receiver inside a BPopupWindow; do not map the window, answer the new widget. The created widget will become a child of the window and be completely attached to it (e.g. the geometry methods will modify the window's geometry). Note that while the widget *seems* to be directly painted on the root window, it actually belongs to the BPopupWindow; so don't send #destroy to the widget to remove it, but rather to the window. popup: initializationBlock Create an instance of the receiver inside a BPopupWindow; before returning, pass the widget to the supplied initializationBlock, then map the window. Answer the new widget. The created widget will become a child of the window and be completely attached to it (e.g. the geometry methods will modify the window's geometry). Note that while the widget *seems* to be directly painted on the root window, it actually belongs to the BPopupWindow; so don't send #destroy to the widget to remove it, but rather to the window.  File: gst-libs.info, Node: BLOX.BWidget-accessing, Next: BLOX.BWidget-customization, Prev: BLOX.BWidget class-popups, Up: BLOX.BWidget 1.49.2 BLOX.BWidget: accessing ------------------------------ borderWidth Answer the value of the borderWidth option for the widget. Specifies a non-negative value indicating the width of the 3-D border to draw around the outside of the widget (if such a border is being drawn; the effect option typically determines this). The value may also be used when drawing 3-D effects in the interior of the widget. The value is measured in pixels. borderWidth: value Set the value of the borderWidth option for the widget. Specifies a non-negative value indicating the width of the 3-D border to draw around the outside of the widget (if such a border is being drawn; the effect option typically determines this). The value may also be used when drawing 3-D effects in the interior of the widget. The value is measured in pixels. cursor Answer the value of the cursor option for the widget. Specifies the mouse cursor to be used for the widget. The value of the option is given by the standard X cursor cursor, i.e., any of the names defined in cursorcursor.h, without the leading XC_. cursor: value Set the value of the cursor option for the widget. Specifies the mouse cursor to be used for the widget. The value of the option is given by the standard X cursor cursor, i.e., any of the names defined in cursorcursor.h, without the leading XC_. effect Answer the value of the effect option for the widget. Specifies the effect desired for the widget's border. Acceptable values are raised, sunken, flat, ridge, solid, and groove. The value indicates how the interior of the widget should appear relative to its exterior; for example, raised means the interior of the widget should appear to protrude from the screen, relative to the exterior of the widget. Raised and sunken give the traditional 3-D appearance (for example, that of Xaw3D), while ridge and groove give a "chiseled" appearance like that of Swing or GTK+'s Metal theme. Flat and solid are not 3-D. effect: value Set the value of the effect option for the widget. Specifies the effect desired for the widget's border. Acceptable values are raised, sunken, flat, ridge, solid, and groove. The value indicates how the interior of the widget should appear relative to its exterior; for example, raised means the interior of the widget should appear to protrude from the screen, relative to the exterior of the widget. Raised and sunken give the traditional 3-D appearance (for example, that of Xaw3D), while ridge and groove give a "chiseled" appearance like that of Swing or GTK+'s Metal theme. Flat and solid are not 3-D. tabStop Answer the value of the tabStop option for the widget. Determines whether the window accepts the focus during keyboard traversal (e.g., Tab and Shift-Tab). Before setting the focus to a window, Blox consults the value of the tabStop option. A value of false means that the window should be skipped entirely during keyboard traversal. true means that the window should receive the input focus as long as it is viewable (it and all of its ancestors are mapped). If you do not set this option, Blox makes the decision about whether or not to focus on the window: the current algorithm is to skip the window if it is disabled, it has no key bindings, or if it is not viewable. Of the standard widgets, BForm, BContainer, BLabel and BImage have no key bindings by default. tabStop: value Set the value of the tabStop option for the widget. Determines whether the window accepts the focus during keyboard traversal (e.g., Tab and Shift-Tab). Before setting the focus to a window, Blox consults the value of the tabStop option. A value of false means that the window should be skipped entirely during keyboard traversal. true means that the window should receive the input focus as long as it is viewable (it and all of its ancestors are mapped). If you do not set this option, Blox makes the decision about whether or not to focus on the window: the current algorithm is to skip the window if it is disabled, it has no key bindings, or if it is not viewable. Of the standard widgets, BForm, BContainer, BLabel and BImage have no key bindings by default.  File: gst-libs.info, Node: BLOX.BWidget-customization, Next: BLOX.BWidget-geometry management, Prev: BLOX.BWidget-accessing, Up: BLOX.BWidget 1.49.3 BLOX.BWidget: customization ---------------------------------- addChild: child The widget identified by child has been added to the receiver. This method is public not because you can call it, but because it can be useful to override it, not forgetting the call to basicAddChild, to perform some initialization on the children just added. Answer the new child. create Make the receiver able to respond to its widget protocol. This method is public not because you can call it, but because it can be useful to override it, not forgetting the call to super, to perform some initialization on the primitive widget just created; for an example of this, see the implementation of BButtonLike. initialize: parentWidget This is called by #new: to initialize the widget (as the name says...). The default implementation calls all the other methods in the `customization' protocol and some private ones that take care of making the receiver's status consistent, so you should usually call it instead of doing everything by hand. This method is public not because you can call it, but because it might be useful to override it. Always answer the receiver. setInitialSize This is called by #initialize: to set the widget's initial size. The whole area is occupied by default. This method is public not because you can call it, but because it can be useful to override it.  File: gst-libs.info, Node: BLOX.BWidget-geometry management, Next: BLOX.BWidget-widget protocol, Prev: BLOX.BWidget-customization, Up: BLOX.BWidget 1.49.4 BLOX.BWidget: geometry management ---------------------------------------- boundingBox Answer a Rectangle containing the bounding box of the receiver boundingBox: rect Set the bounding box of the receiver to rect (a Rectangle). child: child height: value Set the given child's height to value. The default implementation of this method uses `rubber-sheet' geometry management as explained in the comment to BWidget's #height method. You should not use this method, which is automatically called by the child's #height: method, but you might want to override it. The child's property slots whose name ends with `Geom' are reserved for this method. This method should never fail - if it doesn't apply to the kind of geometry management that the receiver does, just do nothing. child: child heightOffset: value Adjust the given child's height by a fixed amount of value pixel. This is meaningful for the default implementation, using `rubber-sheet' geometry management as explained in the comment to BWidget's #height and #heightOffset: methods. You should not use this method, which is automatically called by the child's #heightOffset: method, but you might want to override it. if it doesn't apply to the kind of geometry management that the receiver does, just add value to the current height of the widget. child: child stretch: aBoolean This method is only used when on the path from the receiver to its toplevel there is a BContainer. It decides whether child is among the widgets that are stretched to fill the entire width of the BContainer; if this has not been set for this widget, it is propagated along the widget hierarchy. child: child width: value Set the given child's width to value. The default implementation of this method uses `rubber-sheet' geometry management as explained in the comment to BWidget's #width method. You should not use this method, which is automatically called by the child's #width: method, but you might want to override it. The child's property slots whose name ends with `Geom' are reserved for this method. This method should never fail - if it doesn't apply to the kind of geometry management that the receiver does, just do nothing. child: child widthOffset: value Adjust the given child's width by a fixed amount of value pixel. This is meaningful for the default implementation, using `rubber-sheet' geometry management as explained in the comment to BWidget's #width and #widthOffset: methods. You should not use this method, which is automatically called by the child's #widthOffset: method, but you might want to override it. if it doesn't apply to the kind of geometry management that the receiver does, just add value to the current width of the widget. child: child x: value Set the given child's x to value. The default implementation of this method uses `rubber-sheet' geometry management as explained in the comment to BWidget's #x method. You should not use this method, which is automatically called by the child's #x: method, but you might want to override it. The child's property slots whose name ends with `Geom' are reserved for this method. This method should never fail - if it doesn't apply to the kind of geometry management that the receiver does, just do nothing. child: child xOffset: value Adjust the given child's x by a fixed amount of value pixel. This is meaningful for the default implementation, using `rubber-sheet' geometry management as explained in the comment to BWidget's #x and #xOffset: methods. You should not use this method, which is automatically called by the child's #xOffset: method, but you might want to override it. if it doesn't apply to the kind of geometry management that the receiver does, just add value to the current x of the widget. child: child y: value Set the given child's y to value. The default implementation of this method uses `rubber-sheet' geometry management as explained in the comment to BWidget's #y method. You should not use this method, which is automatically called by the child's #y: method, but you might want to override it. The child's property slots whose name ends with `Geom' are reserved for this method. This method should never fail - if it doesn't apply to the kind of geometry management that the receiver does, just do nothing. child: child yOffset: value Adjust the given child's y by a fixed amount of value pixel. This is meaningful for the default implementation, using `rubber-sheet' geometry management as explained in the comment to BWidget's #y and #yOffset: methods. You should not use this method, which is automatically called by the child's #yOffset: method, but you might want to override it. if it doesn't apply to the kind of geometry management that the receiver does, just add value to the current y of the widget. extent Answer a Point containing the receiver's size extent: extent Set the receiver's size to the width and height contained in extent (a Point). height Answer the `variable' part of the receiver's height within the parent widget. The value returned does not include any fixed amount of pixels indicated by #heightOffset: and must be interpreted in a relative fashion: the ratio of the returned value to the current size of the parent will be preserved upon resize. This apparently complicated method is known as `rubber sheet' geometry management. Behavior if the left or right edges are not within the client area of the parent is not defined - the window might be clamped or might be positioned according to the specification. height: value Set to `value' the height of the widget within the parent widget. The value is specified in a relative fashion as an integer, so that the ratio of `value' to the current size of the parent will be preserved upon resize. This apparently complicated method is known as `rubber sheet' geometry management. heightAbsolute Force a recalculation of the layout of widgets in the receiver's parent, then answer the current height of the receiver in pixels. heightChild: child Answer the given child's height. The default implementation of this method uses `rubber-sheet' geometry management as explained in the comment to BWidget's #height method. You should not use this method, which is automatically called by the child's #height method, but you might want to override. The child's property slots whose name ends with `Geom' are reserved for this method. This method should never fail - if it doesn't apply to the kind of geometry management that the receiver does, just return 0. heightOffset Private - Answer the pixels to be added or subtracted to the height of the receiver, with respect to the value set in a relative fashion through the #height: method. heightOffset: value Add or subtract to the height of the receiver a fixed amount of `value' pixels, with respect to the value set in a relative fashion through the #height: method. Usage of this method is deprecated; use #inset: and BContainers instead. heightPixels: value Set the current height of the receiver to `value' pixels. Note that, after calling this method, #height will answer 0, which is logical considering that there is no `variable' part of the size (refer to #height and #height: for more explanations). inset: pixels Inset the receiver's bounding box by the specified amount. left: left top: top right: right bottom: bottom Set the bounding box of the receiver through its components. pos: position Set the receiver's origin to the width and height contained in position (a Point). posHoriz: aBlox Position the receiver immediately to the right of aBlox. posVert: aBlox Position the receiver just below aBlox. stretch: aBoolean This method is only considered when on the path from the receiver to its toplevel there is a BContainer. It decides whether we are among the widgets that are stretched to fill the entire width of the BContainer. width Answer the `variable' part of the receiver's width within the parent widget. The value returned does not include any fixed amount of pixels indicated by #widthOffset: and must be interpreted in a relative fashion: the ratio of the returned value to the current size of the parent will be preserved upon resize. This apparently complicated method is known as `rubber sheet' geometry management. Behavior if the left or right edges are not within the client area of the parent is not defined - the window might be clamped or might be positioned according to the specification. width: value Set to `value' the width of the widget within the parent widget. The value is specified in a relative fashion as an integer, so that the ratio of `value' to the current size of the parent will be preserved upon resize. This apparently complicated method is known as `rubber sheet' geometry management. width: xSize height: ySize Set the size of the receiver through its components xSize and ySize. widthAbsolute Force a recalculation of the layout of widgets in the receiver's parent, then answer the current width of the receiver in pixels. widthChild: child Answer the given child's width. The default implementation of this method uses `rubber-sheet' geometry management as explained in the comment to BWidget's #width method. You should not use this method, which is automatically called by the child's #width method, but you might want to override. The child's property slots whose name ends with `Geom' are reserved for this method. This method should never fail - if it doesn't apply to the kind of geometry management that the receiver does, just return 0. widthOffset Private - Answer the pixels to be added or subtracted to the width of the receiver, with respect to the value set in a relative fashion through the #width: method. widthOffset: value Add or subtract to the width of the receiver a fixed amount of `value' pixels, with respect to the value set in a relative fashion through the #width: method. Usage of this method is deprecated; use #inset: and BContainers instead. widthPixels: value Set the current width of the receiver to `value' pixels. Note that, after calling this method, #width will answer 0, which is logical considering that there is no `variable' part of the size (refer to #width and #width: for more explanations). x Answer the `variable' part of the receiver's x within the parent widget. The value returned does not include any fixed amount of pixels indicated by #xOffset: and must be interpreted in a relative fashion: the ratio of the returned value to the current size of the parent will be preserved upon resize. This apparently complicated method is known as `rubber sheet' geometry management. Behavior if the left or right edges are not within the client area of the parent is not defined - the window might be clamped or might be positioned according to the specification. x: value Set to `value' the x of the widget within the parent widget. The value is specified in a relative fashion as an integer, so that the ratio of `value' to the current size of the parent will be preserved upon resize. This apparently complicated method is known as `rubber sheet' geometry management. x: xPos y: yPos Set the origin of the receiver through its components xPos and yPos. x: xPos y: yPos width: xSize height: ySize Set the bounding box of the receiver through its origin and size. xAbsolute Force a recalculation of the layout of widgets in the receiver's parent, then answer the current x of the receiver in pixels. xChild: child Answer the given child's x. The default implementation of this method uses `rubber-sheet' geometry management as explained in the comment to BWidget's #x method. You should not use this method, which is automatically called by the child's #x method, but you might want to override. The child's property slots whose name ends with `Geom' are reserved for this method. This method should never fail - if it doesn't apply to the kind of geometry management that the receiver does, just return 0. xOffset Private - Answer the pixels to be added or subtracted to the x of the receiver, with respect to the value set in a relative fashion through the #x: method. xOffset: value Add or subtract to the x of the receiver a fixed amount of `value' pixels, with respect to the value set in a relative fashion through the #x: method. Usage of this method is deprecated; use #inset: and BContainers instead. xPixels: value Set the current x of the receiver to `value' pixels. Note that, after calling this method, #x will answer 0, which is logical considering that there is no `variable' part of the size (refer to #x and #x: for more explanations). xRoot Answer the x position of the receiver with respect to the top-left corner of the desktop (including the offset of the virtual root window under X). y Answer the `variable' part of the receiver's y within the parent widget. The value returned does not include any fixed amount of pixels indicated by #yOffset: and must be interpreted in a relative fashion: the ratio of the returned value to the current size of the parent will be preserved upon resize. This apparently complicated method is known as `rubber sheet' geometry management. Behavior if the left or right edges are not within the client area of the parent is not defined - the window might be clamped or might be positioned according to the specification. y: value Set to `value' the y of the widget within the parent widget. The value is specified in a relative fashion as an integer, so that the ratio of `value' to the current size of the parent will be preserved upon resize. This apparently complicated method is known as `rubber sheet' geometry management. yAbsolute Force a recalculation of the layout of widgets in the receiver's parent, then answer the current y of the receiver in pixels. yChild: child Answer the given child's y. The default implementation of this method uses `rubber-sheet' geometry management as explained in the comment to BWidget's #y method. You should not use this method, which is automatically called by the child's #y method, but you might want to override. The child's property slots whose name ends with `Geom' are reserved for this method. This method should never fail - if it doesn't apply to the kind of geometry management that the receiver does, just return 0. yOffset Private - Answer the pixels to be added or subtracted to the y of the receiver, with respect to the value set in a relative fashion through the #y: method. yOffset: value Add or subtract to the y of the receiver a fixed amount of `value' pixels, with respect to the value set in a relative fashion through the #y: method. Usage of this method is deprecated; use #inset: and BContainers instead. yPixels: value Set the current y of the receiver to `value' pixels. Note that, after calling this method, #y will answer 0, which is logical considering that there is no `variable' part of the size (refer to #y and #y: for more explanations). yRoot Answer the y position of the receiver with respect to the top-left corner of the desktop (including the offset of the virtual root window under X).  File: gst-libs.info, Node: BLOX.BWidget-widget protocol, Prev: BLOX.BWidget-geometry management, Up: BLOX.BWidget 1.49.5 BLOX.BWidget: widget protocol ------------------------------------ activate At any given time, one window on each display is designated as the focus window; any key press or key release events for the display are sent to that window. This method allows one to choose which window will have the focus in the receiver's display If the application currently has the input focus on the receiver's display, this method resets the input focus for the receiver's display to the receiver. If the application doesn't currently have the input focus on the receiver's display, Blox will remember the receiver as the focus for its top-level; the next time the focus arrives at the top-level, it will be redirected to the receiver (this is because most window managers will set the focus only to top-level windows, leaving it up to the application to redirect the focus among the children of the top-level). activateNext Activate the next widget in the focus `tabbing' order. The focus order depends on the widget creation order; you can set which widgets are in the order with the #tabStop: method. activatePrevious Activate the previous widget in the focus `tabbing' order. The focus order depends on the widget creation order; you can set which widgets are in the order with the #tabStop: method. bringToTop Raise the receiver so that it is above all of its siblings in the widgets' z-order; the receiver will not be obscured by any siblings and will obscure any siblings that overlap it. isActive Return whether the receiver is the window that currently owns the focus on its display. sendToBack Lower the receiver so that it is below all of its siblings in the widgets' z-order; the receiver will be obscured by any siblings that overlap it and will not obscure any siblings.  File: gst-libs.info, Node: BLOX.BWindow, Next: BLOX.Gui, Prev: BLOX.BWidget, Up: BLOX package 1.50 BLOX.BWindow ================= Defined in namespace BLOX Superclass: BLOX.BForm Category: Graphics-Windows I am the boss. Nothing else could be viewed or interacted with if it wasn't for me... )):-> * Menu: * BLOX.BWindow class-instance creation:: (class) * BLOX.BWindow-accessing:: (instance) * BLOX.BWindow-widget protocol:: (instance)  File: gst-libs.info, Node: BLOX.BWindow class-instance creation, Next: BLOX.BWindow-accessing, Up: BLOX.BWindow 1.50.1 BLOX.BWindow class: instance creation -------------------------------------------- new Answer a new top-level window. new: label Answer a new top-level window with `label' as its title bar caption. popup: initializationBlock This method should not be called for instances of this class.  File: gst-libs.info, Node: BLOX.BWindow-accessing, Next: BLOX.BWindow-widget protocol, Prev: BLOX.BWindow class-instance creation, Up: BLOX.BWindow 1.50.2 BLOX.BWindow: accessing ------------------------------ callback Answer a DirectedMessage that is sent to verify whether the receiver must be destroyed when the user asks to unmap it. callback: aReceiver message: aSymbol Set up so that aReceiver is sent the aSymbol message (the name of a zero- or one-argument selector) when the user asks to unmap the receiver. If the method accepts an argument, the receiver is passed. If the method returns true, the window and its children are destroyed (which is the default action, taken if no callback is set up). If the method returns false, the window is left in place. invokeCallback Generate a synthetic callback, destroying the window if no callback was set up or if the callback method answers true. label Answer the value of the label option for the widget. Specifies a string to be displayed inside the widget. The way in which the string is displayed depends on the particular widget and may be determined by other options, such as anchor. For windows, this is the title of the window. label: value Set the value of the label option for the widget. Specifies a string to be displayed inside the widget. The way in which the string is displayed depends on the particular widget and may be determined by other options, such as anchor. For windows, this is the title of the window. menu: value Set the value of the menu option for the widget. Specifies a menu widget to be used as a menubar. On the Macintosh, the menubar will be displayed accross the top of the main monitor. On Microsoft Windows and all UNIX platforms, the menu will appear accross the toplevel window as part of the window dressing maintained by the window manager. resizable Answer the value of the resizable option for the widget. Answer whether the user can be resize the window or not. If resizing is disabled, then the window's size will be the size from the most recent interactive resize or geometry-setting method. If there has been no such operation then the window's natural size will be used. resizable: value Set the value of the resizable option for the widget. Answer whether the user can be resize the window or not. If resizing is disabled, then the window's size will be the size from the most recent interactive resize or geometry-setting method. If there has been no such operation then the window's natural size will be used.  File: gst-libs.info, Node: BLOX.BWindow-widget protocol, Prev: BLOX.BWindow-accessing, Up: BLOX.BWindow 1.50.3 BLOX.BWindow: widget protocol ------------------------------------ center Center the window in the screen centerIn: view Center the window in the given widget height Answer the height of the window, as deduced from the geometry that the window manager imposed on the window. height: anInteger Ask the window manager to give the given height to the window. heightAbsolute Answer the height of the window, as deduced from the geometry that the window manager imposed on the window. heightOffset: value This method should not be called for instances of this class. iconify Map a window and in iconified state. If a window has not been mapped yet, this is achieved by mapping the window in withdrawn state first, and then iconifying it. isMapped Answer whether the window is mapped isWindow Answer `true'. map Map the window and bring it to the topmost position in the Z-order. modalMap Map the window while establishing an application-local grab for it. An event loop is started that ends only after the window has been destroyed. When a grab is set for a particular window, all pointer events are restructed to the grab window and its descendants in Blox's window hierarchy. Whenever the pointer is within the grab window's subtree, the pointer will behave exactly the same as if there had been no grab grab at all and all events will be reported in the normal fashion. When the pointer is outside the window's tree, button presses and releases and mouse motion events are reported to the grabbing window, and window entry and window exit events are ignored. In other words, windows outside the grab subtree will be visible on the screen but they will be insensitive until the grab is released. The tree of windows underneath the grab window can include top-level windows, in which case all of those top-level windows and their descendants will continue to receive mouse events during the grab. Keyboard events (key presses and key releases) are delivered as usual: the window manager controls which application receives keyboard events, and if they are sent to any window in the grabbing application then they are redirected to the window owning the focus. state Set the value of the state option for the window. Specifies one of four states for the window: either normal, iconic, withdrawn, or (Windows only) zoomed. state: aSymbol Raise an error. To set a BWindow's state, use #map and #unmap. unmap Unmap a window, causing it to be forgotten about by the window manager width Answer the width of the window, as deduced from the geometry that the window manager imposed on the window. width: anInteger Ask the window manager to give the given width to the window. width: xSize height: ySize Ask the window manager to give the given width and height to the window. widthAbsolute Answer the width of the window, as deduced from the geometry that the window manager imposed on the window. widthOffset: value This method should not be called for instances of this class. window Answer the receiver. x Answer the x coordinate of the window's top-left corner, as deduced from the geometry that the window manager imposed on the window. x: anInteger Ask the window manager to move the window's left border to the given x coordinate, keeping the size unchanged x: xPos y: yPos Ask the window manager to move the window's top-left corner to the given coordinates, keeping the size unchanged x: xPos y: yPos width: xSize height: ySize Ask the window manager to give the requested geometry to the window. xAbsolute Answer the x coordinate of the window's top-left corner, as deduced from the geometry that the window manager imposed on the window. xOffset: value This method should not be called for instances of this class. y Answer the y coordinate of the window's top-left corner, as deduced from the geometry that the window manager imposed on the window. y: anInteger Ask the window manager to move the window's left border to the given y coordinate, keeping the size unchanged yAbsolute Answer the y coordinate of the window's top-left corner, as deduced from the geometry that the window manager imposed on the window. yOffset: value This method should not be called for instances of this class.  File: gst-libs.info, Node: BLOX.Gui, Prev: BLOX.BWindow, Up: BLOX package 1.51 BLOX.Gui ============= Defined in namespace BLOX Superclass: Object Category: Graphics-Windows I am a small class which serves as a base for complex objects which expose an individual protocol but internally use a Blox widget for creating their user interface. * Menu: * BLOX.Gui-accessing:: (instance)  File: gst-libs.info, Node: BLOX.Gui-accessing, Up: BLOX.Gui 1.51.1 BLOX.Gui: accessing -------------------------- blox Return instance of blox subclass which implements window blox: aBlox Set instance of blox subclass which implements window  File: gst-libs.info, Node: Complex package, Next: DBI package, Prev: BLOX package, Up: Top 2 Complex number computations ***************************** * Menu: Alphabetic list: * Complex:: Class tree: (Object) (Magnitude) (Number) * Complex::  File: gst-libs.info, Node: Complex, Up: Complex package 2.1 Complex =========== Defined in namespace Smalltalk Superclass: Number Category: Examples-Useful I provide complex numbers, with full interoperability with other kinds of numbers. Complex numbers can be created from imaginary numbers, which in turn are created with `Complex i' or the #i method (e.g. `3 i'). Alternatively, they can be created from polar numbers. * Menu: * Complex class-instance creation:: (class) * Complex-comparing:: (instance) * Complex-converting:: (instance) * Complex-creation/coercion:: (instance) * Complex-math:: (instance) * Complex-printing:: (instance) * Complex-testing:: (instance) * Complex-transcendental functions:: (instance)  File: gst-libs.info, Node: Complex class-instance creation, Next: Complex-comparing, Up: Complex 2.1.1 Complex class: instance creation -------------------------------------- i Return the imaginary unit, -1 sqrt. initialize Initialize some common complex numbers. new This method should not be called for instances of this class. real: re imaginary: im Return a complex number with the given real and imaginary parts. realResult: re imaginary: im Private - Return a new complex number knowing that re and im have the same generality. rho: dist theta: angle Return a complex number whose absolute value is dist and whose argument is angle.  File: gst-libs.info, Node: Complex-comparing, Next: Complex-converting, Prev: Complex class-instance creation, Up: Complex 2.1.2 Complex: comparing ------------------------ < aNumber Not commented. <= aNumber Not commented. = aNumber Not commented. > aNumber Not commented. >= aNumber Not commented. hash Not commented. ~= aNumber Not commented.  File: gst-libs.info, Node: Complex-converting, Next: Complex-creation/coercion, Prev: Complex-comparing, Up: Complex 2.1.3 Complex: converting ------------------------- asExactFraction Not commented. asFloat Not commented. asFloatD Not commented. asFloatE Not commented. asFloatQ Not commented. asFraction Not commented. ceiling Not commented. floor Not commented. rounded Not commented. truncated Not commented.  File: gst-libs.info, Node: Complex-creation/coercion, Next: Complex-math, Prev: Complex-converting, Up: Complex 2.1.4 Complex: creation/coercion -------------------------------- coerce: aNumber Not commented. generality Not commented. i Return the receiver multiplied by the imaginary unit. imaginary Answer `im'. isComplex Answer `true'. one Answer `One'. real Answer `re'. setReal: real imaginary: imag Not commented. zero Answer `Zero'.  File: gst-libs.info, Node: Complex-math, Next: Complex-printing, Prev: Complex-creation/coercion, Up: Complex 2.1.5 Complex: math ------------------- * z Multiply the receiver by the (real or complex) number z. + z Sum the receiver with the (real or complex) number z. - z Subtract the (real or complex) number z from the receiver. / z Divide the receiver by the (real or complex) number z. abs Return the absolute value of the receiver. absSquared Return the squared absolute value of the receiver. conjugate Return the complex conjugate of the receiver. reciprocal Return the reciprocal of the receiver.  File: gst-libs.info, Node: Complex-printing, Next: Complex-testing, Prev: Complex-math, Up: Complex 2.1.6 Complex: printing ----------------------- printOn: aStream Not commented. storeOn: aStream Not commented.  File: gst-libs.info, Node: Complex-testing, Next: Complex-transcendental functions, Prev: Complex-printing, Up: Complex 2.1.7 Complex: testing ---------------------- isExact Answer whether the receiver performs exact arithmetic. Complex numbers do so as long as both parts, real and imaginary, are exact.  File: gst-libs.info, Node: Complex-transcendental functions, Prev: Complex-testing, Up: Complex 2.1.8 Complex: transcendental functions --------------------------------------- arcTan Return the arc-tangent of the receiver. arcTan: aNumber Return the arc-tangent of aNumber divided by the receiver. arg Return the argument of the receiver. cos Return the cosine of the receiver. cosh Return the hyperbolic cosine of the receiver. exp Return e raised to the receiver. ln Return the natural logarithm of the receiver. log Return the base-10 logarithm of the receiver. sin Return the sine of the receiver. sinh Return the hyperbolic sine of the receiver. sqrt Return the square root of the receiver. Can be improved! tan Return the tangent of the receiver. tanh Return the hyperbolic tangent of the receiver.  File: gst-libs.info, Node: DBI package, Next: DebugTools package, Prev: Complex package, Up: Top 3 Database connectivity with DBI ******************************** * Menu: Alphabetic list: * DBI.ColumnInfo:: * DBI.Connection:: * DBI.ConnectionInfo:: * DBI.FieldConverter:: * DBI.ResultSet:: * DBI.Row:: * DBI.Statement:: * DBI.Table:: Class tree: (DBI.ROE.RASQLRelation) * DBI.Table:: (Object) * DBI.ColumnInfo:: * DBI.Connection:: * DBI.ConnectionInfo:: * DBI.FieldConverter:: * DBI.Row:: * DBI.Statement:: (Iterable) (Stream) * DBI.ResultSet::  File: gst-libs.info, Node: DBI.ColumnInfo, Next: DBI.Connection, Up: DBI package 3.1 DBI.ColumnInfo ================== Defined in namespace DBI Superclass: Object Category: DBI-Framework * Menu: * DBI.ColumnInfo-accessing:: (instance) * DBI.ColumnInfo-printing:: (instance)  File: gst-libs.info, Node: DBI.ColumnInfo-accessing, Next: DBI.ColumnInfo-printing, Up: DBI.ColumnInfo 3.1.1 DBI.ColumnInfo: accessing ------------------------------- index Return the 1-based index of the column in the result set (abstract). isNullable Return whether the column can be NULL (always returns true in ColumnInfo). name Return the name of the column (abstract). size Return the size of the column (abstract). type Return a string containing the type of the column (abstract).  File: gst-libs.info, Node: DBI.ColumnInfo-printing, Prev: DBI.ColumnInfo-accessing, Up: DBI.ColumnInfo 3.1.2 DBI.ColumnInfo: printing ------------------------------ displayOn: aStream Print a representation of the receiver on aStream. printOn: aStream Print a representation of the receiver on aStream.  File: gst-libs.info, Node: DBI.Connection, Next: DBI.ConnectionInfo, Prev: DBI.ColumnInfo, Up: DBI package 3.2 DBI.Connection ================== Defined in namespace DBI Superclass: Object Category: DBI-Framework I represent a connection to a database. * Menu: * DBI.Connection class-connecting:: (class) * DBI.Connection class-initialization:: (class) * DBI.Connection-accessing:: (instance) * DBI.Connection-connecting:: (instance) * DBI.Connection-querying:: (instance)  File: gst-libs.info, Node: DBI.Connection class-connecting, Next: DBI.Connection class-initialization, Up: DBI.Connection 3.2.1 DBI.Connection class: connecting -------------------------------------- connect: aDSN user: aUserName password: aPassword Connect to the database server identified by aDSN using the given username and password. The DSN is in the format dbi:DriverName:dbname=database_name;host=hostname;port=port Where dbi is constant, DriverName is the name of the driver, and everything else is parameters in the form name1=value1;name2=value2;... Individual drivers may parse the parameters differently, though the existing ones all support parameters dbname, host and port. paramConnect: params user: aUserName password: aPassword Connect to the database server using the parameters in params (a Dictionary) and the given username and password (abstract).  File: gst-libs.info, Node: DBI.Connection class-initialization, Next: DBI.Connection-accessing, Prev: DBI.Connection class-connecting, Up: DBI.Connection 3.2.2 DBI.Connection class: initialization ------------------------------------------ updateDriverList Private - Look for new subclasses of Connection.  File: gst-libs.info, Node: DBI.Connection-accessing, Next: DBI.Connection-connecting, Prev: DBI.Connection class-initialization, Up: DBI.Connection 3.2.3 DBI.Connection: accessing ------------------------------- >> aString Returns a Table object corresponding to the given table. database Returns the database name for this connection. This corresponds to the catalog in SQL standard parlance (abstract). fieldConverter Returns a FieldConverter that can be used to insert Smalltalk objects into queries. tableAt: aString Returns a Table object corresponding to the given table. tableAt: aString ifAbsent: aBlock Returns a Table object corresponding to the given table.  File: gst-libs.info, Node: DBI.Connection-connecting, Next: DBI.Connection-querying, Prev: DBI.Connection-accessing, Up: DBI.Connection 3.2.4 DBI.Connection: connecting -------------------------------- close Close the connection now; should happen on GC too (abstract).  File: gst-libs.info, Node: DBI.Connection-querying, Prev: DBI.Connection-connecting, Up: DBI.Connection 3.2.5 DBI.Connection: querying ------------------------------ do: aSQLQuery Executes a SQL statement (usually one that doesn't return a result set). Return value is a ResultSet, to which you can send #rowsAffected (abstract). prepare: aSQLQuery Creates a statement object, that can be executed (with parameters, if applicable) repeatedly (abstract). primTableAt: aString ifAbsent: aBlock Returns a Table object corresponding to the given table. Should be overridden by subclasses. select: aSQLQuery Prepares and executes a SQL statement. Returns the result set or throws an exception on failure (abstract).  File: gst-libs.info, Node: DBI.ConnectionInfo, Next: DBI.FieldConverter, Prev: DBI.Connection, Up: DBI package 3.3 DBI.ConnectionInfo ====================== Defined in namespace DBI Superclass: Object Category: DBI-Framework A utility class to contain connection info. * Menu: * DBI.ConnectionInfo class-instance creation:: (class) * DBI.ConnectionInfo-accessing:: (instance)  File: gst-libs.info, Node: DBI.ConnectionInfo class-instance creation, Next: DBI.ConnectionInfo-accessing, Up: DBI.ConnectionInfo 3.3.1 DBI.ConnectionInfo class: instance creation ------------------------------------------------- fromDSN: aDSN Parse a DSN in the format dbi:DriverName:dbname=database_name;host=hostname;port=port where dbi is constant, DriverName is the name of the driver, and everything else is parameters in the form name1=value1;name2=value2;...  File: gst-libs.info, Node: DBI.ConnectionInfo-accessing, Prev: DBI.ConnectionInfo class-instance creation, Up: DBI.ConnectionInfo 3.3.2 DBI.ConnectionInfo: accessing ----------------------------------- driver Answer the driver; this is not the driver class. driver: aString Set the driver; this is not the driver class. paramString: aString Set the parameter list. params Return the parsed parameters in a Dictionary. scheme Answer the scheme; the only supported one is 'dbi'. scheme: aString Set the scheme; the only supported one is 'dbi'.  File: gst-libs.info, Node: DBI.FieldConverter, Next: DBI.ResultSet, Prev: DBI.ConnectionInfo, Up: DBI package 3.4 DBI.FieldConverter ====================== Defined in namespace DBI Superclass: Object Category: DBI * Menu: * DBI.FieldConverter class-instance creation:: (class) * DBI.FieldConverter-actions:: (instance) * DBI.FieldConverter-converting-smalltalk:: (instance)  File: gst-libs.info, Node: DBI.FieldConverter class-instance creation, Next: DBI.FieldConverter-actions, Up: DBI.FieldConverter 3.4.1 DBI.FieldConverter class: instance creation ------------------------------------------------- new Not commented. uniqueInstance Not commented.  File: gst-libs.info, Node: DBI.FieldConverter-actions, Next: DBI.FieldConverter-converting-smalltalk, Prev: DBI.FieldConverter class-instance creation, Up: DBI.FieldConverter 3.4.2 DBI.FieldConverter: actions --------------------------------- print: aValue on: aStream Not commented. printString: aValue Not commented.  File: gst-libs.info, Node: DBI.FieldConverter-converting-smalltalk, Prev: DBI.FieldConverter-actions, Up: DBI.FieldConverter 3.4.3 DBI.FieldConverter: converting-smalltalk ---------------------------------------------- writeBoolean: aBoolean on: aStream Not commented. writeDate: aDate on: aStream Not commented. writeDateTime: aDateTime on: aStream Not commented. writeFloat: aFloat on: aStream Not commented. writeInteger: anInteger on: aStream Not commented. writeQuotedDate: aDate on: aStream Not commented. writeQuotedTime: aDate on: aStream Not commented. writeTime: aTime on: aStream Not commented.  File: gst-libs.info, Node: DBI.ResultSet, Next: DBI.Row, Prev: DBI.FieldConverter, Up: DBI package 3.5 DBI.ResultSet ================= Defined in namespace DBI Superclass: Stream Category: DBI-Framework I represent a result set, ie. the set of rows returned from a SELECT statement. I may also be returned for DML statements (INSERT, UPDATE, DELETE), in which case I only hold the number of rows affected. * Menu: * DBI.ResultSet-accessing:: (instance) * DBI.ResultSet-cursor access:: (instance) * DBI.ResultSet-printing:: (instance) * DBI.ResultSet-stream protocol:: (instance)  File: gst-libs.info, Node: DBI.ResultSet-accessing, Next: DBI.ResultSet-cursor access, Up: DBI.ResultSet 3.5.1 DBI.ResultSet: accessing ------------------------------ columnAt: aIndex Answer the aIndex'th column name. columnNames Answer an array of column names in order (abstract). columns Answer a Dictionary of column name -> ColumnInfo pairs (abstract). isDML Returns true if the statement was not a SELECT or similar operation (e.g. SHOW, DESCRIBE, EXPLAIN). isSelect Returns true if the statement was a SELECT or similar operation (e.g. SHOW, DESCRIBE, EXPLAIN), false otherwise. rowCount Returns the number of rows in the result set; error for DML statements. rows Answer the contents of the execution result as array of Rows. rowsAffected For DML statments, returns the number of rows affected; error for SELECT statements. statement Return the Statement, if any, that generated the result set.  File: gst-libs.info, Node: DBI.ResultSet-cursor access, Next: DBI.ResultSet-printing, Prev: DBI.ResultSet-accessing, Up: DBI.ResultSet 3.5.2 DBI.ResultSet: cursor access ---------------------------------- atEnd Return whether all the rows in the result set have been consumed. (abstract). fetch Return the next row, or nil if at the end of the result set. next Return the next row, or raise an error if at the end of the stream (abstract).  File: gst-libs.info, Node: DBI.ResultSet-printing, Next: DBI.ResultSet-stream protocol, Prev: DBI.ResultSet-cursor access, Up: DBI.ResultSet 3.5.3 DBI.ResultSet: printing ----------------------------- printOn: aStream Print a representation of the receiver on aStream.  File: gst-libs.info, Node: DBI.ResultSet-stream protocol, Prev: DBI.ResultSet-printing, Up: DBI.ResultSet 3.5.4 DBI.ResultSet: stream protocol ------------------------------------ position Returns the current row index (0-based) in the result set (abstract). position: anInteger Sets the current row index (0-based) in the result set (abstract). size Returns the number of rows in the result set.  File: gst-libs.info, Node: DBI.Row, Next: DBI.Statement, Prev: DBI.ResultSet, Up: DBI package 3.6 DBI.Row =========== Defined in namespace DBI Superclass: Object Category: DBI-Framework I represent a row in a result set. * Menu: * DBI.Row-accessing:: (instance) * DBI.Row-printing:: (instance)  File: gst-libs.info, Node: DBI.Row-accessing, Next: DBI.Row-printing, Up: DBI.Row 3.6.1 DBI.Row: accessing ------------------------ asArray Return the values of the columns. asDictionary Return the names and values of the columns as a dictionary. at: aColumnName Return the value of the named column (abstract). atIndex: aColumnIndex Return the value of the column at the given 1-based index (abstract). columnAt: aIndex Return a ColumnInfo object for the aIndex-th column in the row. columnCount Return the number of columns in the row. columnNames Return an array of column names for the columns in the row. columns Return a Dictionary of ColumnInfo objects for the columns in the row, where the keys are the column names. keysAndValuesDo: aBlock Pass to aBlock each column name and the corresponding value. resultSet Return the result set that includes the receiver.  File: gst-libs.info, Node: DBI.Row-printing, Prev: DBI.Row-accessing, Up: DBI.Row 3.6.2 DBI.Row: printing ----------------------- printOn: aStream Print a representation of the receiver on aStream.  File: gst-libs.info, Node: DBI.Statement, Next: DBI.Table, Prev: DBI.Row, Up: DBI package 3.7 DBI.Statement ================= Defined in namespace DBI Superclass: Object Category: DBI-Framework I represent a prepared statement. * Menu: * DBI.Statement class-instance creation:: (class) * DBI.Statement-querying:: (instance)  File: gst-libs.info, Node: DBI.Statement class-instance creation, Next: DBI.Statement-querying, Up: DBI.Statement 3.7.1 DBI.Statement class: instance creation -------------------------------------------- on: aConnection Return a new statement for this connection.  File: gst-libs.info, Node: DBI.Statement-querying, Prev: DBI.Statement class-instance creation, Up: DBI.Statement 3.7.2 DBI.Statement: querying ----------------------------- execute Execute with no parameters (abstract). executeWith: aParameter Execute with one parameters. executeWith: aParam1 with: aParam2 Execute with two parameters. executeWith: aParam1 with: aParam2 with: aParam3 Execute with three parameters. executeWithAll: aParams Execute taking parameters from the Collection aParams (abstract).  File: gst-libs.info, Node: DBI.Table, Prev: DBI.Statement, Up: DBI package 3.8 DBI.Table ============= Defined in namespace DBI Superclass: DBI.ROE.RASQLRelation Category: DBI * Menu: * DBI.Table-accessing:: (instance) * DBI.Table-core:: (instance) * DBI.Table-printing:: (instance)  File: gst-libs.info, Node: DBI.Table-accessing, Next: DBI.Table-core, Up: DBI.Table 3.8.1 DBI.Table: accessing -------------------------- columnAt: aIndex Answer the aIndex'th column name. columnNames Answer an array of column names in order (abstract). columns Not commented. database Returns the database name for this table. This corresponds to the catalog in SQL standard parlance.  File: gst-libs.info, Node: DBI.Table-core, Next: DBI.Table-printing, Prev: DBI.Table-accessing, Up: DBI.Table 3.8.2 DBI.Table: core --------------------- size Not commented.  File: gst-libs.info, Node: DBI.Table-printing, Prev: DBI.Table-core, Up: DBI.Table 3.8.3 DBI.Table: printing ------------------------- print: anObject on: aStream Not commented.  File: gst-libs.info, Node: DebugTools package, Next: Sockets package, Prev: DBI package, Up: Top 4 Controlling Smalltalk processes with DebugTools ************************************************* * Menu: Alphabetic list: * Debugger:: Class tree: (Object) * Debugger::  File: gst-libs.info, Node: Debugger, Up: DebugTools package 4.1 Debugger ============ Defined in namespace Smalltalk Superclass: Object Category: System-Debugging I provide debugging facilities for another inferior process. I have methods that allow the controlled process to proceed with varying granularity. In addition, I keep a cache mapping instruction pointer bytecodes to line numbers. * Menu: * Debugger class-disabling debugging:: (class) * Debugger class-instance creation:: (class) * Debugger class-source code:: (class) * Debugger-inferior process properties:: (instance) * Debugger-stepping commands:: (instance)  File: gst-libs.info, Node: Debugger class-disabling debugging, Next: Debugger class-instance creation, Up: Debugger 4.1.1 Debugger class: disabling debugging ----------------------------------------- debuggerClass Answer `nil'.  File: gst-libs.info, Node: Debugger class-instance creation, Next: Debugger class-source code, Prev: Debugger class-disabling debugging, Up: Debugger 4.1.2 Debugger class: instance creation --------------------------------------- on: aProcess Suspend aProcess and return a new Debugger that controls aProcess. aProcess must not be the currently running process.  File: gst-libs.info, Node: Debugger class-source code, Next: Debugger-inferior process properties, Prev: Debugger class-instance creation, Up: Debugger 4.1.3 Debugger class: source code --------------------------------- currentLineIn: aContext Not commented.  File: gst-libs.info, Node: Debugger-inferior process properties, Next: Debugger-stepping commands, Prev: Debugger class-source code, Up: Debugger 4.1.4 Debugger: inferior process properties ------------------------------------------- currentLine Return the line number in traced process. isActive Answer true if the inferior process is still running. process Answer the inferior process. suspendedContext Answer the suspended execution state of the inferior process.  File: gst-libs.info, Node: Debugger-stepping commands, Prev: Debugger-inferior process properties, Up: Debugger 4.1.5 Debugger: stepping commands --------------------------------- continue Terminate the controlling process and continue execution of the traced process. finish Run to the next return. finish: aContext Run up until aContext returns. next Run to the end of the current line in the inferior process, skipping over message sends. slowFinish Run in single-step mode up to the next return. slowFinish: aContext Run in single-step mode until aContext returns. step Run to the end of the current line in the inferior process or to the next message send. stepBytecode Run a single bytecode in the inferior process. stopInferior Suspend the inferior process and raise a DebuggerReentered notification in the controlling process. stopInferior: anObject Suspend the inferior process and raise a DebuggerReentered notification in the controlling process with anObject as the exception's message.  File: gst-libs.info, Node: Iconv/I18N packages, Next: XML/XPath/XSL packages, Prev: Sockets package, Up: Top 5 Multilingual and international support with Iconv and I18N ************************************************************ * Menu: Alphabetic list: * I18N.BigEndianFileStream:: * I18N.EncodedStream:: * I18N.EncodedString:: * I18N.EncodedStringFactory:: * I18N.Encoder:: * I18N.FileStreamSegment:: * I18N.IncompleteSequenceError:: * I18N.InvalidCharsetError:: * I18N.InvalidSequenceError:: * I18N.LcMessages:: * I18N.LcMessagesCatalog:: * I18N.LcMessagesDomain:: * I18N.LcMessagesDummyDomain:: * I18N.LcMessagesMoFileVersion0:: * I18N.LcMessagesTerritoryDomain:: * I18N.LcMonetary:: * I18N.LcMonetaryISO:: * I18N.LcNumeric:: * I18N.LcPrintFormats:: * I18N.LcTime:: * I18N.Locale:: * I18N.LocaleConventions:: * I18N.LocaleData:: * I18N.RTEAlternativeNode:: * I18N.RTEBinaryNode:: * I18N.RTELiteralNode:: * I18N.RTENegationNode:: * I18N.RTEParameterNode:: * I18N.RunTimeExpression:: Class tree: (Object) (Exception) (Error) * I18N.IncompleteSequenceError:: * I18N.InvalidSequenceError:: (SystemExceptions.InvalidValue) (SystemExceptions.SystemExceptions.InvalidArgument) * I18N.InvalidCharsetError:: (FileSegment) * I18N.FileStreamSegment:: * I18N.EncodedStringFactory:: * I18N.LocaleData:: * I18N.LcMessagesDomain:: * I18N.LcMessagesCatalog:: * I18N.LcMessagesMoFileVersion0:: * I18N.LcMessagesDummyDomain:: * I18N.LcMessagesTerritoryDomain:: * I18N.Locale:: * I18N.LocaleConventions:: * I18N.LcMessages:: * I18N.LcPrintFormats:: * I18N.LcNumeric:: * I18N.LcMonetary:: * I18N.LcMonetaryISO:: * I18N.LcTime:: * I18N.RunTimeExpression:: * I18N.RTEAlternativeNode:: * I18N.RTEBinaryNode:: * I18N.RTELiteralNode:: * I18N.RTENegationNode:: * I18N.RTEParameterNode:: (Iterable) (Collection) (SequenceableCollection) (ArrayedCollection) (CharacterArray) * I18N.EncodedString:: (Stream) (FileDescriptor) (FileStream) * I18N.BigEndianFileStream:: * I18N.EncodedStream:: * I18N.Encoder::  File: gst-libs.info, Node: I18N.BigEndianFileStream, Next: I18N.EncodedStream, Up: Iconv/I18N packages 5.1 I18N.BigEndianFileStream ============================ Defined in namespace I18N Superclass: FileStream Category: i18n-Messages Unlike ByteStream and FileStream, this retrieves integer numbers in big-endian (68000, PowerPC, SPARC) order. * Menu:  File: gst-libs.info, Node: I18N.EncodedStream, Next: I18N.EncodedString, Prev: I18N.BigEndianFileStream, Up: Iconv/I18N packages 5.2 I18N.EncodedStream ====================== Defined in namespace I18N Superclass: Stream Category: i18n-Character sets This class is a factory for subclasses of Encoder. Encoders act as parts of a pipe, hence this class provides methods that construct an appropriate pipe. * Menu: * I18N.EncodedStream class-initializing:: (class) * I18N.EncodedStream class-instance creation:: (class)  File: gst-libs.info, Node: I18N.EncodedStream class-initializing, Next: I18N.EncodedStream class-instance creation, Up: I18N.EncodedStream 5.2.1 I18N.EncodedStream class: initializing -------------------------------------------- initialize Initialize the registry of the encoders to include the standard encoders contained in the library. registerEncoderFor: arrayOfAliases toUTF32: toUTF32Class fromUTF32: fromUTF32Class Register the two classes that will respectively convert from the charsets in arrayOfAliases to UTF-32 and vice versa. The former class is a stream that accepts characters and returns (via #next) integers representing UTF-32 character codes, while the latter accepts UTF-32 character codes and converts them to characters. For an example see respectively FromUTF7 and ToUTF7 (I admit it is not a trivial example).  File: gst-libs.info, Node: I18N.EncodedStream class-instance creation, Prev: I18N.EncodedStream class-initializing, Up: I18N.EncodedStream 5.2.2 I18N.EncodedStream class: instance creation ------------------------------------------------- encoding: anUnicodeString Answer a pipe of encoders that converts anUnicodeString to default encoding for strings (the current locale's default charset if none is specified). encoding: aStringOrStream as: toEncoding Answer a pipe of encoders that converts anUnicodeString (which contains to the supplied encoding (which can be an ASCII String or Symbol). on: aStringOrStream from: fromEncoding Answer a pipe of encoders that converts aStringOrStream (which can be a string or another stream) from the given encoding to the default locale's default charset. on: aStringOrStream from: fromEncoding to: toEncoding Answer a pipe of encoders that converts aStringOrStream (which can be a string or another stream) between the two supplied encodings (which can be ASCII Strings or Symbols) on: aStringOrStream to: toEncoding Answer a pipe of encoders that converts aStringOrStream (which can be a string or another stream) from the default locale's default charset to the given encoding. unicodeOn: aStringOrStream Answer a pipe of encoders that converts aStringOrStream (which can be a string or another stream) from its encoding (or the current locale's default charset, if the encoding cannot be determined) to integers representing Unicode character codes. unicodeOn: aStringOrStream encoding: fromEncoding Answer a pipe of encoders that converts aStringOrStream (which can be a string or another stream) from the supplied encoding (which can be an ASCII String or Symbol) to integers representing Unicode character codes.  File: gst-libs.info, Node: I18N.EncodedString, Next: I18N.EncodedStringFactory, Prev: I18N.EncodedStream, Up: Iconv/I18N packages 5.3 I18N.EncodedString ====================== Defined in namespace I18N Superclass: CharacterArray Category: i18n-Character sets An EncodedString, like a String, is a sequence of bytes representing a specific encoding of a UnicodeString. Unlike a String, however, the encoding name is known, rather than detected, irrelevant or assumed to be the system default. * Menu: * I18N.EncodedString class-accessing:: (class) * I18N.EncodedString class-instance creation:: (class) * I18N.EncodedString-accessing:: (instance) * I18N.EncodedString-copying:: (instance) * I18N.EncodedString-initializing:: (instance) * I18N.EncodedString-printing:: (instance)  File: gst-libs.info, Node: I18N.EncodedString class-accessing, Next: I18N.EncodedString class-instance creation, Up: I18N.EncodedString 5.3.1 I18N.EncodedString class: accessing ----------------------------------------- isUnicode Answer false; the receiver stores bytes (i.e. an encoded form), not characters.  File: gst-libs.info, Node: I18N.EncodedString class-instance creation, Next: I18N.EncodedString-accessing, Prev: I18N.EncodedString class-accessing, Up: I18N.EncodedString 5.3.2 I18N.EncodedString class: instance creation ------------------------------------------------- fromString: aString Not commented. fromString: aString encoding: encoding Not commented. new This method should not be called for instances of this class. new: size This method should not be called for instances of this class.  File: gst-libs.info, Node: I18N.EncodedString-accessing, Next: I18N.EncodedString-copying, Prev: I18N.EncodedString class-instance creation, Up: I18N.EncodedString 5.3.3 I18N.EncodedString: accessing ----------------------------------- asString Answer `string'. asUnicodeString Not commented. at: anIndex Not commented. at: anIndex put: anObject Not commented. do: aBlock Not commented. encoding Not commented. hash Not commented. size Not commented. species Not commented. utf16Encoding Not commented. utf32Encoding Not commented. valueAt: anIndex Not commented. valueAt: anIndex put: anObject Not commented.  File: gst-libs.info, Node: I18N.EncodedString-copying, Next: I18N.EncodedString-initializing, Prev: I18N.EncodedString-accessing, Up: I18N.EncodedString 5.3.4 I18N.EncodedString: copying --------------------------------- copy Not commented. copyEmpty Not commented. copyEmpty: size Not commented.  File: gst-libs.info, Node: I18N.EncodedString-initializing, Next: I18N.EncodedString-printing, Prev: I18N.EncodedString-copying, Up: I18N.EncodedString 5.3.5 I18N.EncodedString: initializing -------------------------------------- encoding: aString Not commented. setString: aString Not commented.  File: gst-libs.info, Node: I18N.EncodedString-printing, Prev: I18N.EncodedString-initializing, Up: I18N.EncodedString 5.3.6 I18N.EncodedString: printing ---------------------------------- displayOn: aStream Print a representation of the receiver on aStream. Unlike #printOn:, this method does not display the encoding and enclosing quotes. printOn: aStream Print a representation of the receiver on aStream.  File: gst-libs.info, Node: I18N.EncodedStringFactory, Next: I18N.Encoder, Prev: I18N.EncodedString, Up: Iconv/I18N packages 5.4 I18N.EncodedStringFactory ============================= Defined in namespace I18N Superclass: Object Category: i18n-Character sets An EncodedStringFactory is used (in place of class objects) so that Encoders can return EncodedString objects with the correct encoding. * Menu: * I18N.EncodedStringFactory class-instance creation:: (class) * I18N.EncodedStringFactory-accessing:: (instance) * I18N.EncodedStringFactory-instance creation:: (instance)  File: gst-libs.info, Node: I18N.EncodedStringFactory class-instance creation, Next: I18N.EncodedStringFactory-accessing, Up: I18N.EncodedStringFactory 5.4.1 I18N.EncodedStringFactory class: instance creation -------------------------------------------------------- encoding: aString Answer a new EncodedStringFactory, creating strings with the given encoding.  File: gst-libs.info, Node: I18N.EncodedStringFactory-accessing, Next: I18N.EncodedStringFactory-instance creation, Prev: I18N.EncodedStringFactory class-instance creation, Up: I18N.EncodedStringFactory 5.4.2 I18N.EncodedStringFactory: accessing ------------------------------------------ isUnicode Answer false; the receiver stores bytes (i.e. an encoded form), not characters.  File: gst-libs.info, Node: I18N.EncodedStringFactory-instance creation, Prev: I18N.EncodedStringFactory-accessing, Up: I18N.EncodedStringFactory 5.4.3 I18N.EncodedStringFactory: instance creation -------------------------------------------------- encoding Answer the encoding used for the created Strings. encoding: aString Set the encoding used for the created Strings. fromString: aString Answer an EncodedString based on aString and in the encoding represented by the receiver. new Answer a new, empty EncodedString using the encoding represented by the receiver. new: size Answer a new EncodedString of the given size, using the encoding represented by the receiver.  File: gst-libs.info, Node: I18N.Encoder, Next: I18N.FileStreamSegment, Prev: I18N.EncodedStringFactory, Up: Iconv/I18N packages 5.5 I18N.Encoder ================ Defined in namespace I18N Superclass: Stream Category: i18n-Character sets This class is the superclass of streams that take an origin and encode it to another character set. The subclasses are are for internal use unless you are writing support for your own encodings. * Menu: * I18N.Encoder class-instance creation:: (class) * I18N.Encoder-stream operations:: (instance)  File: gst-libs.info, Node: I18N.Encoder class-instance creation, Next: I18N.Encoder-stream operations, Up: I18N.Encoder 5.5.1 I18N.Encoder class: instance creation ------------------------------------------- on: aStringOrStream from: fromEncoding to: toEncoding Answer a new encoder that translates from fromEncoding to toEncoding. The encodings are guaranteed to be those for which the encoder was registered.  File: gst-libs.info, Node: I18N.Encoder-stream operations, Prev: I18N.Encoder class-instance creation, Up: I18N.Encoder 5.5.2 I18N.Encoder: stream operations ------------------------------------- atEnd Return whether the receiver can produce another character in the receiver; by default, this is true if there is another character in the origin. atEndOfInput Return whether there is another character in the origin. This method is for private use by encoders, calling it outside won't corrupt the internal state of the encoder but the result probably won't be meaningful (depending on the innards of the encoder). next Return the next character in the receiver; by default, this is the next character in the origin. nextInput Return the next character in the origin. This method is for private use by encoders, calling it outside may corrupt the internal state of the encoder. nextInputAvailable: n into: aCollection startingAt: pos Place up to N characters from the origin in aCollection. This method is for private use by encoders, calling it outside may corrupt the internal state of the encoder. peekInput Return the next character in the origin without advancing it. species We answer a string of Characters encoded in our destination encoding.  File: gst-libs.info, Node: I18N.FileStreamSegment, Next: I18N.IncompleteSequenceError, Prev: I18N.Encoder, Up: Iconv/I18N packages 5.6 I18N.FileStreamSegment ========================== Defined in namespace I18N Superclass: FileSegment Category: i18n-Messages Unlike FileSegment, this object assumes that the `file' instance variable is a FileStream, not a file name. * Menu: * I18N.FileStreamSegment-basic:: (instance)  File: gst-libs.info, Node: I18N.FileStreamSegment-basic, Up: I18N.FileStreamSegment 5.6.1 I18N.FileStreamSegment: basic ----------------------------------- fileName Answer the name of the file containing the segment withFileDo: aBlock Evaluate aBlock, passing a FileStream corresponding to the file  File: gst-libs.info, Node: I18N.IncompleteSequenceError, Next: I18N.InvalidCharsetError, Prev: I18N.FileStreamSegment, Up: Iconv/I18N packages 5.7 I18N.IncompleteSequenceError ================================ Defined in namespace I18N Superclass: Error Category: i18n-Character sets I am raised if an invalid sequence is found while converting a string from a charset to another. In particular, I am raised if the input stream ends abruptly in the middle of a multi-byte sequence. * Menu: * I18N.IncompleteSequenceError-accessing:: (instance)  File: gst-libs.info, Node: I18N.IncompleteSequenceError-accessing, Up: I18N.IncompleteSequenceError 5.7.1 I18N.IncompleteSequenceError: accessing --------------------------------------------- description Answer a textual description of the exception.  File: gst-libs.info, Node: I18N.InvalidCharsetError, Next: I18N.InvalidSequenceError, Prev: I18N.IncompleteSequenceError, Up: Iconv/I18N packages 5.8 I18N.InvalidCharsetError ============================ Defined in namespace I18N Superclass: SystemExceptions.SystemExceptions.InvalidArgument Category: i18n-Character sets I am raised if the user tries to encode from or to an unknown encoding * Menu: * I18N.InvalidCharsetError-accessing:: (instance)  File: gst-libs.info, Node: I18N.InvalidCharsetError-accessing, Up: I18N.InvalidCharsetError 5.8.1 I18N.InvalidCharsetError: accessing ----------------------------------------- description Answer a textual description of the exception.  File: gst-libs.info, Node: I18N.InvalidSequenceError, Next: I18N.LcMessages, Prev: I18N.InvalidCharsetError, Up: Iconv/I18N packages 5.9 I18N.InvalidSequenceError ============================= Defined in namespace I18N Superclass: Error Category: i18n-Character sets I am raised if an invalid sequence is found while converting a string from a charset to another * Menu: * I18N.InvalidSequenceError-accessing:: (instance)  File: gst-libs.info, Node: I18N.InvalidSequenceError-accessing, Up: I18N.InvalidSequenceError 5.9.1 I18N.InvalidSequenceError: accessing ------------------------------------------ description Answer a textual description of the exception.  File: gst-libs.info, Node: I18N.LcMessages, Next: I18N.LcMessagesCatalog, Prev: I18N.InvalidSequenceError, Up: Iconv/I18N packages 5.10 I18N.LcMessages ==================== Defined in namespace I18N Superclass: I18N.LocaleConventions Category: i18n-Messages This object is a factory of LcMessagesDomain objects * Menu: * I18N.LcMessages class-accessing:: (class) * I18N.LcMessages-accessing:: (instance) * I18N.LcMessages-opening MO files:: (instance)  File: gst-libs.info, Node: I18N.LcMessages class-accessing, Next: I18N.LcMessages-accessing, Up: I18N.LcMessages 5.10.1 I18N.LcMessages class: accessing --------------------------------------- category Answer the environment variable used to determine the default locale selector Answer the selector that accesses the receiver when sent to a Locale object.  File: gst-libs.info, Node: I18N.LcMessages-accessing, Next: I18N.LcMessages-opening MO files, Prev: I18N.LcMessages class-accessing, Up: I18N.LcMessages 5.10.2 I18N.LcMessages: accessing --------------------------------- languageDirectory Answer the directory holding MO files for the language languageDirectory: rootDirectory Answer the directory holding MO files for the language, given the root directory of the locale data. territoryDirectory Answer the directory holding MO files for the language, specific to the territory territoryDirectory: rootDirectory Answer the directory holding MO files for the language, specific to the territory, given the root directory of the locale data.  File: gst-libs.info, Node: I18N.LcMessages-opening MO files, Prev: I18N.LcMessages-accessing, Up: I18N.LcMessages 5.10.3 I18N.LcMessages: opening MO files ---------------------------------------- ? aString Answer an object for the aString domain, querying both the language catalog (e.g. pt) and the territory catalog (e.g. pt_BR or pt_PT). domain: aString Answer an object for the aString domain, querying both the language catalog (e.g. pt) and the territory catalog (e.g. pt_BR or pt_PT). domain: aString localeDirectory: rootDirectory Answer an object for the aString domain, querying both the language catalog (e.g. pt) and the territory catalog (e.g. pt_BR or pt_PT). The localeDirectory is usually '/share/locale'.  File: gst-libs.info, Node: I18N.LcMessagesCatalog, Next: I18N.LcMessagesDomain, Prev: I18N.LcMessages, Up: Iconv/I18N packages 5.11 I18N.LcMessagesCatalog =========================== Defined in namespace I18N Superclass: I18N.LcMessagesDomain Category: i18n-Messages This object is an abstract superclass of objects that retrieve translated strings from a file. * Menu:  File: gst-libs.info, Node: I18N.LcMessagesDomain, Next: I18N.LcMessagesDummyDomain, Prev: I18N.LcMessagesCatalog, Up: Iconv/I18N packages 5.12 I18N.LcMessagesDomain ========================== Defined in namespace I18N Superclass: I18N.LocaleData Category: i18n-Messages This object is an abstract superclass for message domains (catalogs). It contains methods to create instances of its subclasses, but they are commonly used only by LcMessages. Translations are accessed using either #at: or the shortcut binary messages `?'. This way, common idioms to access translated strings will be string := NLS? 'abc'. string := self? 'abc'. (in the first case NLS is a class variable, in the second the receiver implements #? through delegation) which is only five or six characters longer than the traditional string := 'abc'. (cfr. the _("abc") idiom used by GNU gettext) * Menu: * I18N.LcMessagesDomain class-opening MO files:: (class) * I18N.LcMessagesDomain-handling the cache:: (instance) * I18N.LcMessagesDomain-querying:: (instance)  File: gst-libs.info, Node: I18N.LcMessagesDomain class-opening MO files, Next: I18N.LcMessagesDomain-handling the cache, Up: I18N.LcMessagesDomain 5.12.1 I18N.LcMessagesDomain class: opening MO files ---------------------------------------------------- id: anArray on: aFileName Create an instance of the receiver with a given locale identifier from a path to the MO file  File: gst-libs.info, Node: I18N.LcMessagesDomain-handling the cache, Next: I18N.LcMessagesDomain-querying, Prev: I18N.LcMessagesDomain class-opening MO files, Up: I18N.LcMessagesDomain 5.12.2 I18N.LcMessagesDomain: handling the cache ------------------------------------------------ flush Flush the receiver's cache of translations shouldCache Answer whether translations should be cached. Never override this method to always answer false, because that would cause bugs when transliteration is being used.  File: gst-libs.info, Node: I18N.LcMessagesDomain-querying, Prev: I18N.LcMessagesDomain-handling the cache, Up: I18N.LcMessagesDomain 5.12.3 I18N.LcMessagesDomain: querying -------------------------------------- ? aString Answer the translation of `aString', or answer aString itself if none is available. at: aString Answer the translation of `aString', or answer aString itself if none is available. at: singularString plural: pluralString with: n Answer either the translation of pluralString with `%1' replaced by n if n ~= 1, or the translation of singularString if n = 1. at: aString put: anotherString This method should not be called for instances of this class. translatorInformation Answer information on the translation, or nil if there is none. This information is stored as the `translation' of an empty string. translatorInformationAt: key Answer information on the translation associated to a given key translatorInformationAt: key at: subkey Answer information on the translation associated to a given key and to a subkey of the key  File: gst-libs.info, Node: I18N.LcMessagesDummyDomain, Next: I18N.LcMessagesMoFileVersion0, Prev: I18N.LcMessagesDomain, Up: Iconv/I18N packages 5.13 I18N.LcMessagesDummyDomain =============================== Defined in namespace I18N Superclass: I18N.LcMessagesDomain Category: i18n-Messages This object does no attempt to translate strings, returning instead the same string passed as an argument to #?. * Menu:  File: gst-libs.info, Node: I18N.LcMessagesMoFileVersion0, Next: I18N.LcMessagesTerritoryDomain, Prev: I18N.LcMessagesDummyDomain, Up: Iconv/I18N packages 5.14 I18N.LcMessagesMoFileVersion0 ================================== Defined in namespace I18N Superclass: I18N.LcMessagesCatalog Category: i18n-Messages This object is an concrete class that retrieves translated strings from a GNU gettext MO file. The class method #fileFormatDescription contains an explanation of the file format. * Menu: * I18N.LcMessagesMoFileVersion0 class-documentation:: (class) * I18N.LcMessagesMoFileVersion0 class-plurals:: (class) * I18N.LcMessagesMoFileVersion0-flushing the cache:: (instance)  File: gst-libs.info, Node: I18N.LcMessagesMoFileVersion0 class-documentation, Next: I18N.LcMessagesMoFileVersion0 class-plurals, Up: I18N.LcMessagesMoFileVersion0 5.14.1 I18N.LcMessagesMoFileVersion0 class: documentation --------------------------------------------------------- fileFormatDescription The Format of GNU MO Files (excerpt of the GNU gettext manual) ============================================================== The format of the generated MO files is best described by a picture, which appears below. The first two words serve the identification of the file. The magic number will always signal GNU MO files. The number is stored in the byte order of the generating machine, so the magic number really is two numbers: `0x950412de' and `0xde120495'. The second word describes the current revision of the file format. For now the revision is 0. This might change in future versions, and ensures that the readers of MO files can distinguish new formats from old ones, so that both can be handled correctly. The version is kept separate from the magic number, instead of using different magic numbers for different formats, mainly because `/etc/magic' is not updated often. It might be better to have magic separated from internal format version identification. Follow a number of pointers to later tables in the file, allowing for the extension of the prefix part of MO files without having to recompile programs reading them. This might become useful for later inserting a few flag bits, indication about the charset used, new tables, or other things. Then, at offset O and offset T in the picture, two tables of string descriptors can be found. In both tables, each string descriptor uses two 32 bits integers, one for the string length, another for the offset of the string in the MO file, counting in bytes from the start of the file. The first table contains descriptors for the original strings, and is sorted so the original strings are in increasing lexicographical order. The second table contains descriptors for the translated strings, and is parallel to the first table: to find the corresponding translation one has to access the array slot in the second array with the same index. Having the original strings sorted enables the use of simple binary search, for when the MO file does not contain an hashing table, or for when it is not practical to use the hashing table provided in the MO file. This also has another advantage, as the empty string in a PO file GNU `gettext' is usually *translated* into some system information attached to that particular MO file, and the empty string necessarily becomes the first in both the original and translated tables, making the system information very easy to find. The size S of the hash table can be zero. In this case, the hash table itself is not contained in the MO file. Some people might prefer this because a precomputed hashing table takes disk space, and does not win *that* much speed. The hash table contains indices to the sorted array of strings in the MO file. Conflict resolution is done by double hashing. The precise hashing algorithm used is fairly dependent of GNU `gettext' code, and is not documented here. As for the strings themselves, they follow the hash file, and each is terminated with a , and this is not counted in the length which appears in the string descriptor. The `msgfmt' program has an option selecting the alignment for MO file strings. With this option, each string is separately aligned so it starts at an offset which is a multiple of the alignment value. On some RISC machines, a correct alignment will speed things up. Nothing prevents a MO file from having embedded s in strings. However, the program interface currently used already presumes that strings are terminated, so embedded s are somewhat useless. But MO file format is general enough so other interfaces would be later possible, if for example, we ever want to implement wide characters right in MO files, where bytes may accidently appear. This particular issue has been strongly debated in the GNU `gettext' development forum, and it is expectable that MO file format will evolve or change over time. It is even possible that many formats may later be supported concurrently. But surely, we have to start somewhere, and the MO file format described here is a good start. Nothing is cast in concrete, and the format may later evolve fairly easily, so we should feel comfortable with the current approach. byte +-----------------------------------------+ 0 | magic number = 0x950412de | | | 4 | file format revision = 0 | | | 8 | number of strings | == N | | 12 | offset of table with original strings | == O | | 16 | offset of table with translation strings | == T | | 20 | size of hashing table | == S | | 24 | offset of hashing table | == H | | . . . (possibly more entries later) . . . | | O | length & offset 0th string ---------------. O + 8 | length & offset 1st string -----------------. ... ... | | O + ((N-1)*8)| length & offset (N-1)th string | | | | | | | T | length & offset 0th translation --------------. T + 8 | length & offset 1st translation ----------------. ... ... | | | | T + ((N-1)*8)| length & offset (N-1)th translation | | | | | | | | | | | H | start hash table | | | | | ... ... | | | | H + S * 4 | end hash table | | | | | | | | | | | | NUL terminated 0th string <---------------' | | | | | | | | | NUL terminated 1st string <-----------------' | | | | | | ... ... | | | | | | | NUL terminated 0th translation <--------------' | | | | | NUL terminated 1st translation <----------------' | | ... ... | | +-----------------------------------------+ Locating Message Catalog Files ----------------------------- Because many different languages for many different packages have to be stored we need some way to add these information to file message catalog files. The way usually used in Unix environments is have this encoding in the file name. This is also done here. The directory name given in `bindtextdomain's second argument (or the default directory), followed by the value and name of the locale and the domain name are concatenated: DIR_NAME/LOCALE/LC_CATEGORY/DOMAIN_NAME.mo The default value for DIR_NAME is system specific. For the GNU library, and for packages adhering to its conventions, it's: /usr/local/share/locale LOCALE is the value of the locale whose name is this `LC_CATEGORY'. For `gettext' and `dgettext' this locale is always `LC_MESSAGES'.  File: gst-libs.info, Node: I18N.LcMessagesMoFileVersion0 class-plurals, Next: I18N.LcMessagesMoFileVersion0-flushing the cache, Prev: I18N.LcMessagesMoFileVersion0 class-documentation, Up: I18N.LcMessagesMoFileVersion0 5.14.2 I18N.LcMessagesMoFileVersion0 class: plurals --------------------------------------------------- initialize Initialize a table with the expressions computing the plurals for the most common languages pluralExpressionFor: locale ifAbsent: aBlock Answer a RunTimeExpression yielding the plural form for the given language and territory, if one is known, else evaluate aBlock and answer it.  File: gst-libs.info, Node: I18N.LcMessagesMoFileVersion0-flushing the cache, Prev: I18N.LcMessagesMoFileVersion0 class-plurals, Up: I18N.LcMessagesMoFileVersion0 5.14.3 I18N.LcMessagesMoFileVersion0: flushing the cache -------------------------------------------------------- flush Flush the cache and reread the catalog's metadata. shouldCache Answer true, we always cache translations if they are read from a file  File: gst-libs.info, Node: I18N.LcMessagesTerritoryDomain, Next: I18N.LcMonetary, Prev: I18N.LcMessagesMoFileVersion0, Up: Iconv/I18N packages 5.15 I18N.LcMessagesTerritoryDomain =================================== Defined in namespace I18N Superclass: I18N.LcMessagesDomain Category: i18n-Messages This object asks for strings to a primary domain (e.g. it_IT) and a secondary one (e.g. it). * Menu: * I18N.LcMessagesTerritoryDomain class-instance creation:: (class)  File: gst-libs.info, Node: I18N.LcMessagesTerritoryDomain class-instance creation, Up: I18N.LcMessagesTerritoryDomain 5.15.1 I18N.LcMessagesTerritoryDomain class: instance creation -------------------------------------------------------------- primary: domain1 secondary: domain2 Answer an instance of the receiver that queries, in sequence, domain1 and domain2  File: gst-libs.info, Node: I18N.LcMonetary, Next: I18N.LcMonetaryISO, Prev: I18N.LcMessagesTerritoryDomain, Up: Iconv/I18N packages 5.16 I18N.LcMonetary ==================== Defined in namespace I18N Superclass: I18N.LcNumeric Category: i18n-Printing Sending either #?, #printString: or #print:on: converts a Number to a String according to the rules that are mandated by ISO for printing currency amounts in the current locale. * Menu: * I18N.LcMonetary class-accessing:: (class) * I18N.LcMonetary-printing:: (instance)  File: gst-libs.info, Node: I18N.LcMonetary class-accessing, Next: I18N.LcMonetary-printing, Up: I18N.LcMonetary 5.16.1 I18N.LcMonetary class: accessing --------------------------------------- category Answer the environment variable used to determine the default locale selector Answer the selector that accesses the receiver when sent to a Locale object.  File: gst-libs.info, Node: I18N.LcMonetary-printing, Prev: I18N.LcMonetary class-accessing, Up: I18N.LcMonetary 5.16.2 I18N.LcMonetary: printing -------------------------------- print: aNumber on: aStream Print aNumber on aStream according to the receiver's formatting conventions. Always print a currency sign and don't force to print negative numbers by putting parentheses around them. print: aNumber on: aStream currency: currency parentheses: p Print aNumber on aStream according to the receiver's formatting conventions. If currency is true, print a currency sign, and if p is true force to print negative numbers by putting parentheses around them. If p is true, for positive numbers spaces are put around the number to keep them aligned.  File: gst-libs.info, Node: I18N.LcMonetaryISO, Next: I18N.LcNumeric, Prev: I18N.LcMonetary, Up: Iconv/I18N packages 5.17 I18N.LcMonetaryISO ======================= Defined in namespace I18N Superclass: I18N.LcMonetary Category: i18n-Printing * Menu: * I18N.LcMonetaryISO class-accessing:: (class)  File: gst-libs.info, Node: I18N.LcMonetaryISO class-accessing, Up: I18N.LcMonetaryISO 5.17.1 I18N.LcMonetaryISO class: accessing ------------------------------------------ selector Answer the selector that accesses the receiver when sent to a Locale object.  File: gst-libs.info, Node: I18N.LcNumeric, Next: I18N.LcPrintFormats, Prev: I18N.LcMonetaryISO, Up: Iconv/I18N packages 5.18 I18N.LcNumeric =================== Defined in namespace I18N Superclass: I18N.LcPrintFormats Category: i18n-Printing Sending either #?, #printString: or #print:on: converts a Number to a String according to the rules that are used in the given locale. * Menu: * I18N.LcNumeric class-accessing:: (class) * I18N.LcNumeric-printing:: (instance)  File: gst-libs.info, Node: I18N.LcNumeric class-accessing, Next: I18N.LcNumeric-printing, Up: I18N.LcNumeric 5.18.1 I18N.LcNumeric class: accessing -------------------------------------- category Answer the environment variable used to determine the default locale selector Answer the selector that accesses the receiver when sent to a Locale object.  File: gst-libs.info, Node: I18N.LcNumeric-printing, Prev: I18N.LcNumeric class-accessing, Up: I18N.LcNumeric 5.18.2 I18N.LcNumeric: printing ------------------------------- basicPrint: aNumber on: aStream Print aNumber on aStream according to the receiver's formatting conventions, without currency signs or anything like that. This method must not be overridden. print: aNumber on: aStream Print aNumber on aStream according to the receiver's formatting conventions.  File: gst-libs.info, Node: I18N.LcPrintFormats, Next: I18N.LcTime, Prev: I18N.LcNumeric, Up: Iconv/I18N packages 5.19 I18N.LcPrintFormats ======================== Defined in namespace I18N Superclass: I18N.LocaleConventions Category: i18n-Messages LcPrintFormats subclasses have instances that understand #?, #printString: and #print:on: (the last of which is abstract) which provide a means to convert miscellaneous objects to Strings according to the rules that are used in the given locale. * Menu: * I18N.LcPrintFormats-printing:: (instance)  File: gst-libs.info, Node: I18N.LcPrintFormats-printing, Up: I18N.LcPrintFormats 5.19.1 I18N.LcPrintFormats: printing ------------------------------------ ? anObject Answer how anObject must be printed according to the receiver's formatting conventions. print: anObject on: aStream Print anObject on aStream according to the receiver's formatting conventions. printString: anObject Answer how anObject must be printed according to the receiver's formatting conventions.  File: gst-libs.info, Node: I18N.LcTime, Next: I18N.Locale, Prev: I18N.LcPrintFormats, Up: Iconv/I18N packages 5.20 I18N.LcTime ================ Defined in namespace I18N Superclass: I18N.LcPrintFormats Category: i18n-Printing Sending either #?, #printString: or #print:on: converts a Date or Time to a String according to the rules that are used in the given locale. * Menu: * I18N.LcTime class-accessing:: (class) * I18N.LcTime-printing:: (instance) * I18N.LcTime-tests:: (instance)  File: gst-libs.info, Node: I18N.LcTime class-accessing, Next: I18N.LcTime-printing, Up: I18N.LcTime 5.20.1 I18N.LcTime class: accessing ----------------------------------- category Answer the environment variable used to determine the default locale selector Answer the selector that accesses the receiver when sent to a Locale object.  File: gst-libs.info, Node: I18N.LcTime-printing, Next: I18N.LcTime-tests, Prev: I18N.LcTime class-accessing, Up: I18N.LcTime 5.20.2 I18N.LcTime: printing ---------------------------- print: aDateOrTimeOrArray on: aStream Print aDateOrTimeOrArray on aStream according to the receiver's formatting conventions. It can be a Date, Time, DateTime, or an array made of a Date and a Time print: aDateOrTimeOrArray on: aStream ifFull: fullFmt ifDate: dateFmt ifTime: timeFmt Print aDateOrTimeOrArray on aStream according to the receiver's formatting conventions. It can be a Date, Time, DateTime, or an array made of a Date and a Time: Date is printed with dateFmt and Time with timeFmt, while in the other cases fullFmt is used. For information on the formatting codes, see #print:time:format:on:. print: aDate time: aTime format: aString on: aStream Print the specified date and time on aStream according to the receiver's formatting conventions, using the given format. The valid abbreviations are the same used by the C function strftime: abbreviated weekday (%a) weekday (%A) abbreviated month (%b) month (%B) date & time (%c) century (%C) day of the month (%d) date (US) (%D) day of the month (%e) year for the ISO week (%g) year for the ISO week (%G) abbreviated month (%h) hours (%H) hours (AM/PM) (%I) day of the year (%j) hours (%k) hours (AM/PM) (%l) month (%m) minutes (%M) AM/PM (%p) lowercase AM/PM (%P) AM/PM time (%r) time (US) (%R) time_t (%s) seconds (%S) time (US) (%T) day of the week (%u) week number starting at Sun (%U) week number starting at Thu (%V) day of the week, Sunday=0 (%w) week number starting at Mon (%W) date (%x) time (%X) year (2-digit) (%y) year (4-digit) (%Y).  File: gst-libs.info, Node: I18N.LcTime-tests, Prev: I18N.LcTime-printing, Up: I18N.LcTime 5.20.3 I18N.LcTime: tests ------------------------- allFormatsExample Answer a long string that includes all the possible formats  File: gst-libs.info, Node: I18N.Locale, Next: I18N.LocaleConventions, Prev: I18N.LcTime, Up: Iconv/I18N packages 5.21 I18N.Locale ================ Defined in namespace I18N Superclass: I18N.LocaleData Category: i18n-Messages This object is an abstract superclass of objects related to the territory and language in which the program is being used. Instances of it are asked about information on the current locale, and provide a means to be asked for things with a common idiom, the #? binary message. * Menu: * I18N.Locale class-C call-outs:: (class) * I18N.Locale class-initialization:: (class) * I18N.Locale class-instance creation:: (class) * I18N.Locale-C call-outs:: (instance) * I18N.Locale-subobjects:: (instance)  File: gst-libs.info, Node: I18N.Locale class-C call-outs, Next: I18N.Locale class-initialization, Up: I18N.Locale 5.21.1 I18N.Locale class: C call-outs ------------------------------------- primRootDirectory Not commented.  File: gst-libs.info, Node: I18N.Locale class-initialization, Next: I18N.Locale class-instance creation, Prev: I18N.Locale class-C call-outs, Up: I18N.Locale 5.21.2 I18N.Locale class: initialization ---------------------------------------- rootDirectory Answer the directory under which locale definition files are found. rootDirectory: aString Set under which directory locale definition files are found.  File: gst-libs.info, Node: I18N.Locale class-instance creation, Next: I18N.Locale-C call-outs, Prev: I18N.Locale class-initialization, Up: I18N.Locale 5.21.3 I18N.Locale class: instance creation ------------------------------------------- default Answer an instance of the receiver that accesses the default locale. flush Flush the information on locales that are not valid across an image save/load. fromString: aString Answer an instance of the receiver that accesses the given locale (in the form language[_territory][.charset]). posix Answer an instance of the receiver that accesses the POSIX locale.  File: gst-libs.info, Node: I18N.Locale-C call-outs, Next: I18N.Locale-subobjects, Prev: I18N.Locale class-instance creation, Up: I18N.Locale 5.21.4 I18N.Locale: C call-outs ------------------------------- load: name Not commented.  File: gst-libs.info, Node: I18N.Locale-subobjects, Prev: I18N.Locale-C call-outs, Up: I18N.Locale 5.21.5 I18N.Locale: subobjects ------------------------------ messages Answer the LcMessages object for the locale represented by the receiver. monetary Answer the LcMonetary object for the locale represented by the receiver. monetaryIso Answer the LcMonetaryISO object for the locale represented by the receiver. numeric Answer the LcNumeric object for the locale represented by the receiver. time Answer the LcTime object for the locale represented by the receiver.  File: gst-libs.info, Node: I18N.LocaleConventions, Next: I18N.LocaleData, Prev: I18N.Locale, Up: Iconv/I18N packages 5.22 I18N.LocaleConventions =========================== Defined in namespace I18N Superclass: I18N.LocaleData Category: i18n-Messages I am an abstract superclass of objects that are referred to by a Locale object. * Menu: * I18N.LocaleConventions class-accessing:: (class) * I18N.LocaleConventions-accessing:: (instance)  File: gst-libs.info, Node: I18N.LocaleConventions class-accessing, Next: I18N.LocaleConventions-accessing, Up: I18N.LocaleConventions 5.22.1 I18N.LocaleConventions class: accessing ---------------------------------------------- ? anObject Query the default object, forwarding the message to it. default Answer an instance of the receiver that accesses the default locale. fromString: aString Answer an instance of the receiver that accesses the given locale (in the form language[_territory][.charset]). posix Answer an instance of the receiver that accesses the POSIX locale. selector This method's functionality should be implemented by subclasses of LocaleConventions  File: gst-libs.info, Node: I18N.LocaleConventions-accessing, Prev: I18N.LocaleConventions class-accessing, Up: I18N.LocaleConventions 5.22.2 I18N.LocaleConventions: accessing ---------------------------------------- ? anObject This method's functionality should be implemented by subclasses of LocaleConventions  File: gst-libs.info, Node: I18N.LocaleData, Next: I18N.RTEAlternativeNode, Prev: I18N.LocaleConventions, Up: Iconv/I18N packages 5.23 I18N.LocaleData ==================== Defined in namespace I18N Superclass: Object Category: i18n-Messages I am an abstract superclass of objects that represent localization information. * Menu: * I18N.LocaleData class-accessing:: (class) * I18N.LocaleData class-database:: (class) * I18N.LocaleData-accessing:: (instance) * I18N.LocaleData-initialization:: (instance)  File: gst-libs.info, Node: I18N.LocaleData class-accessing, Next: I18N.LocaleData class-database, Up: I18N.LocaleData 5.23.1 I18N.LocaleData class: accessing --------------------------------------- category Answer `nil'. default This method's functionality should be implemented by subclasses of LocaleData flush Flush the contents of the instances of each subclass of LocaleData. fromString: lang This method's functionality should be implemented by subclasses of LocaleData language: lang Answer the local object for the given language. language: lang territory: territory Answer the local object for the given language and territory. language: lang territory: territory charset: charset Answer the local object for the given language, territory and charset. new This method should not be called for instances of this class. posix This method's functionality should be implemented by subclasses of LocaleData update: aspect Flush instances of the receiver when an image is loaded.  File: gst-libs.info, Node: I18N.LocaleData class-database, Next: I18N.LocaleData-accessing, Prev: I18N.LocaleData class-accessing, Up: I18N.LocaleData 5.23.2 I18N.LocaleData class: database -------------------------------------- defaultCharset Answer the default charset used when nothing is specified. defaultCharset: aString Set the default charset used when nothing is specified. defaults Answer the default territory-language and language-charset associations. initialize Initialize the receiver's class variables. languages ISO639 language codes territories ISO3166 territory codes  File: gst-libs.info, Node: I18N.LocaleData-accessing, Next: I18N.LocaleData-initialization, Prev: I18N.LocaleData class-database, Up: I18N.LocaleData 5.23.3 I18N.LocaleData: accessing --------------------------------- charset Return the charset supported by the receiver. id Return the identifier of the locale supported by the receiver. isPosixLocale Answer whether the receiver implements the default POSIX behavior for a locale. language Return the language supported by the receiver. languageDirectory Answer the directory where data files for the current language reside. languageDirectory: rootDirectory Answer the directory where data files for the current language reside, given the root directory of the locale data. territory Return the territory supported by the receiver. territoryDirectory Answer the directory where data files for the current language, specific to the territory, reside. territoryDirectory: rootDirectory Answer the directory where data files for the current language, specific to the territory, reside, given the root directory of the locale data.  File: gst-libs.info, Node: I18N.LocaleData-initialization, Prev: I18N.LocaleData-accessing, Up: I18N.LocaleData 5.23.4 I18N.LocaleData: initialization -------------------------------------- id: anArray Private - Set which locale the receiver contains data for initialize: aString Set which locale the receiver contains data for, starting from a string describing the locale.  File: gst-libs.info, Node: I18N.RTEAlternativeNode, Next: I18N.RTEBinaryNode, Prev: I18N.LocaleData, Up: Iconv/I18N packages 5.24 I18N.RTEAlternativeNode ============================ Defined in namespace I18N Superclass: I18N.RunTimeExpression Category: i18n-Messages * Menu: * I18N.RTEAlternativeNode class-compiling:: (class) * I18N.RTEAlternativeNode-computing:: (instance)  File: gst-libs.info, Node: I18N.RTEAlternativeNode class-compiling, Next: I18N.RTEAlternativeNode-computing, Up: I18N.RTEAlternativeNode 5.24.1 I18N.RTEAlternativeNode class: compiling ----------------------------------------------- condition: cond ifTrue: trueNode ifFalse: falseNode Private - Create a node in the parse tree for the run-time expression, mapping s to a Smalltalk arithmetic selector  File: gst-libs.info, Node: I18N.RTEAlternativeNode-computing, Prev: I18N.RTEAlternativeNode class-compiling, Up: I18N.RTEAlternativeNode 5.24.2 I18N.RTEAlternativeNode: computing ----------------------------------------- condition: condNode ifTrue: trueNode ifFalse: falseNode Initialize the children of the receiver and the conditional expression to choose between them printOn: aStream Print a representation of the receiver on aStream send: parameter Evaluate the receiver by conditionally choosing one of its children and evaluating it  File: gst-libs.info, Node: I18N.RTEBinaryNode, Next: I18N.RTELiteralNode, Prev: I18N.RTEAlternativeNode, Up: Iconv/I18N packages 5.25 I18N.RTEBinaryNode ======================= Defined in namespace I18N Superclass: I18N.RunTimeExpression Category: i18n-Messages * Menu: * I18N.RTEBinaryNode class-compiling:: (class) * I18N.RTEBinaryNode-compiling:: (instance) * I18N.RTEBinaryNode-computing:: (instance)  File: gst-libs.info, Node: I18N.RTEBinaryNode class-compiling, Next: I18N.RTEBinaryNode-compiling, Up: I18N.RTEBinaryNode 5.25.1 I18N.RTEBinaryNode class: compiling ------------------------------------------ lhs: lhs op: op rhs: rhs Private - Create a node in the parse tree for the run-time expression, mapping s to a Smalltalk arithmetic selector  File: gst-libs.info, Node: I18N.RTEBinaryNode-compiling, Next: I18N.RTEBinaryNode-computing, Prev: I18N.RTEBinaryNode class-compiling, Up: I18N.RTEBinaryNode 5.25.2 I18N.RTEBinaryNode: compiling ------------------------------------ lhs Answer `lhs'. op Answer `op'. rhs Answer `rhs'.  File: gst-libs.info, Node: I18N.RTEBinaryNode-computing, Prev: I18N.RTEBinaryNode-compiling, Up: I18N.RTEBinaryNode 5.25.3 I18N.RTEBinaryNode: computing ------------------------------------ lhs: lhsNode op: aSymbol rhs: rhsNode Initialize the children of the receiver and the operation to be done between them printOn: aStream Print a representation of the receiver on aStream send: parameter Private - Evaluate the receiver by evaluating both children and performing an arithmetic operation between them.  File: gst-libs.info, Node: I18N.RTELiteralNode, Next: I18N.RTENegationNode, Prev: I18N.RTEBinaryNode, Up: Iconv/I18N packages 5.26 I18N.RTELiteralNode ======================== Defined in namespace I18N Superclass: I18N.RunTimeExpression Category: i18n-Messages * Menu: * I18N.RTELiteralNode class-initializing:: (class) * I18N.RTELiteralNode-computing:: (instance)  File: gst-libs.info, Node: I18N.RTELiteralNode class-initializing, Next: I18N.RTELiteralNode-computing, Up: I18N.RTELiteralNode 5.26.1 I18N.RTELiteralNode class: initializing ---------------------------------------------- parseFrom: aStream Parse a literal number from aStream and return a new node  File: gst-libs.info, Node: I18N.RTELiteralNode-computing, Prev: I18N.RTELiteralNode class-initializing, Up: I18N.RTELiteralNode 5.26.2 I18N.RTELiteralNode: computing ------------------------------------- n: value Set the value of the literal that the node represents printOn: aStream Print a representation of the receiver on aStream send: parameter Answer a fixed value, the literal encoded in the node  File: gst-libs.info, Node: I18N.RTENegationNode, Next: I18N.RTEParameterNode, Prev: I18N.RTELiteralNode, Up: Iconv/I18N packages 5.27 I18N.RTENegationNode ========================= Defined in namespace I18N Superclass: I18N.RunTimeExpression Category: i18n-Messages * Menu: * I18N.RTENegationNode class-initializing:: (class) * I18N.RTENegationNode-computing:: (instance)  File: gst-libs.info, Node: I18N.RTENegationNode class-initializing, Next: I18N.RTENegationNode-computing, Up: I18N.RTENegationNode 5.27.1 I18N.RTENegationNode class: initializing ----------------------------------------------- child: aNode Answer a new node representing the logical negation of aNode  File: gst-libs.info, Node: I18N.RTENegationNode-computing, Prev: I18N.RTENegationNode class-initializing, Up: I18N.RTENegationNode 5.27.2 I18N.RTENegationNode: computing -------------------------------------- child: value Set the child of which the receiver will compute the negation printOn: aStream Print a representation of the receiver on aStream send: parameter Evaluate the receiver by computing the child's logical negation  File: gst-libs.info, Node: I18N.RTEParameterNode, Next: I18N.RunTimeExpression, Prev: I18N.RTENegationNode, Up: Iconv/I18N packages 5.28 I18N.RTEParameterNode ========================== Defined in namespace I18N Superclass: I18N.RunTimeExpression Category: i18n-Messages * Menu: * I18N.RTEParameterNode-computing:: (instance)  File: gst-libs.info, Node: I18N.RTEParameterNode-computing, Up: I18N.RTEParameterNode 5.28.1 I18N.RTEParameterNode: computing --------------------------------------- printOn: aStream Print a representation of the receiver on aStream send: parameter Evaluate the receiver by answering the parameter  File: gst-libs.info, Node: I18N.RunTimeExpression, Prev: I18N.RTEParameterNode, Up: Iconv/I18N packages 5.29 I18N.RunTimeExpression =========================== Defined in namespace I18N Superclass: Object Category: i18n-Messages * Menu: * I18N.RunTimeExpression class-compiling:: (class) * I18N.RunTimeExpression class-initializing:: (class) * I18N.RunTimeExpression class-instance creation:: (class) * I18N.RunTimeExpression-computing:: (instance)  File: gst-libs.info, Node: I18N.RunTimeExpression class-compiling, Next: I18N.RunTimeExpression class-initializing, Up: I18N.RunTimeExpression 5.29.1 I18N.RunTimeExpression class: compiling ---------------------------------------------- parseExpression: stream Private - Compile the expression in the stream parseOperand: stream Parse an operand from the stream (i.e. an unary negation, a parenthesized subexpression, `n' or a number) and answer the corresponding parse node. parseOperator: stream Answer a Symbol for an operator read from stream, or nil if something else is found.  File: gst-libs.info, Node: I18N.RunTimeExpression class-initializing, Next: I18N.RunTimeExpression class-instance creation, Prev: I18N.RunTimeExpression class-compiling, Up: I18N.RunTimeExpression 5.29.2 I18N.RunTimeExpression class: initializing ------------------------------------------------- initialize Private - Initialize internal tables for the parser  File: gst-libs.info, Node: I18N.RunTimeExpression class-instance creation, Next: I18N.RunTimeExpression-computing, Prev: I18N.RunTimeExpression class-initializing, Up: I18N.RunTimeExpression 5.29.3 I18N.RunTimeExpression class: instance creation ------------------------------------------------------ on: aString Compile aString and answer a RunTimeExpression  File: gst-libs.info, Node: I18N.RunTimeExpression-computing, Prev: I18N.RunTimeExpression class-instance creation, Up: I18N.RunTimeExpression 5.29.4 I18N.RunTimeExpression: computing ---------------------------------------- send: parameter This method's functionality should be implemented by subclasses of RunTimeExpression value: parameter Evaluate the receiver, and answer its value as an integer  File: gst-libs.info, Node: Sockets package, Next: Iconv/I18N packages, Prev: DebugTools package, Up: Top 6 Network programming with Sockets ********************************** * Menu: Alphabetic list: * Sockets.AbstractSocket:: * Sockets.AbstractSocketImpl:: * Sockets.CAddrInfoStruct:: * Sockets.CSockAddrIn6Struct:: * Sockets.Datagram:: * Sockets.DatagramSocket:: * Sockets.DatagramSocketImpl:: * Sockets.DummyStream:: * Sockets.ICMP6SocketImpl:: * Sockets.ICMPSocketImpl:: * Sockets.IP6Address:: * Sockets.IPAddress:: * Sockets.MulticastSocket:: * Sockets.MulticastSocketImpl:: * Sockets.OOBSocketImpl:: * Sockets.RawSocketImpl:: * Sockets.ReadBuffer:: * Sockets.ServerSocket:: * Sockets.Socket:: * Sockets.SocketAddress:: * Sockets.SocketImpl:: * Sockets.StreamSocket:: * Sockets.TCPSocketImpl:: * Sockets.UDPSocketImpl:: * Sockets.UnixAddress:: * Sockets.UnixDatagramSocketImpl:: * Sockets.UnixSocketImpl:: * Sockets.WriteBuffer:: Class tree: (Object) (CObject) (CCompound) (CStruct) * Sockets.CAddrInfoStruct:: * Sockets.CSockAddrIn6Struct:: (Iterable) (Stream) (FileDescriptor) * Sockets.AbstractSocketImpl:: * Sockets.DatagramSocketImpl:: * Sockets.MulticastSocketImpl:: * Sockets.UDPSocketImpl:: * Sockets.OOBSocketImpl:: * Sockets.RawSocketImpl:: * Sockets.ICMP6SocketImpl:: * Sockets.ICMPSocketImpl:: * Sockets.UnixDatagramSocketImpl:: * Sockets.SocketImpl:: * Sockets.TCPSocketImpl:: * Sockets.UnixSocketImpl:: (PositionableStream) (ReadStream) * Sockets.ReadBuffer:: (WriteStream) * Sockets.WriteBuffer:: * Sockets.AbstractSocket:: * Sockets.DatagramSocket:: * Sockets.MulticastSocket:: * Sockets.ServerSocket:: * Sockets.StreamSocket:: * Sockets.Socket:: * Sockets.DummyStream:: * Sockets.Datagram:: * Sockets.SocketAddress:: * Sockets.IP6Address:: * Sockets.IPAddress:: * Sockets.UnixAddress::  File: gst-libs.info, Node: Sockets.AbstractSocket, Next: Sockets.AbstractSocketImpl, Up: Sockets package 6.1 Sockets.AbstractSocket ========================== Defined in namespace Sockets Superclass: Stream Category: Sockets-Streams This class models a client site socket. A socket is a TCP/IP endpoint for network communications conceptually similar to a file handle. This class only takes care of buffering and blocking if requested. It uses an underlying socket implementation object which is a subclass of AbstractSocketImpl. This is necessary to hide some methods in FileDescriptor that are not relevant to sockets, as well as to implement buffering independently of the implementation nuances required by the different address families. The address family class (a subclass of SocketAddress) acts as a factory for socket implementation objects. * Menu: * Sockets.AbstractSocket class-defaults:: (class) * Sockets.AbstractSocket class-instance creation:: (class) * Sockets.AbstractSocket class-timed-out operations:: (class) * Sockets.AbstractSocket class-well known ports:: (class) * Sockets.AbstractSocket-accessing:: (instance) * Sockets.AbstractSocket-printing:: (instance) * Sockets.AbstractSocket-socket options:: (instance) * Sockets.AbstractSocket-stream protocol:: (instance) * Sockets.AbstractSocket-testing:: (instance)  File: gst-libs.info, Node: Sockets.AbstractSocket class-defaults, Next: Sockets.AbstractSocket class-instance creation, Up: Sockets.AbstractSocket 6.1.1 Sockets.AbstractSocket class: defaults -------------------------------------------- defaultAddressClass Answer the default address family to be used. In the library, the address family is represented by a subclass of SocketAddress which is by default IPAddress. defaultAddressClass: class Set the default address family to be used. In the library, the address family is represented by a subclass of SocketAddress which is by default IPAddress. defaultImplementationClassFor: aSocketAddressClass Answer the default implementation class. Depending on the subclass, this might be the default stream socket implementation class of the given address class, or rather its default datagram socket implementation class.  File: gst-libs.info, Node: Sockets.AbstractSocket class-instance creation, Next: Sockets.AbstractSocket class-timed-out operations, Prev: Sockets.AbstractSocket class-defaults, Up: Sockets.AbstractSocket 6.1.2 Sockets.AbstractSocket class: instance creation ----------------------------------------------------- new This method should not be called for instances of this class. new: implementation Answer a new instance of the receiver, using as the underlying layer the object passed as the `implementation' parameter; the object is probably going to be some kind of AbstractSocketImpl. new: implClass addressClass: addressClass Answer a new instance of the receiver, using as the underlying layer a new instance of `implementationClass' and using the protocol family of `addressClass'.  File: gst-libs.info, Node: Sockets.AbstractSocket class-timed-out operations, Next: Sockets.AbstractSocket class-well known ports, Prev: Sockets.AbstractSocket class-instance creation, Up: Sockets.AbstractSocket 6.1.3 Sockets.AbstractSocket class: timed-out operations -------------------------------------------------------- checkPeriod Answer the period that is to elapse between socket polls if data data is not ready and the connection is still open (in milliseconds) checkPeriod: anInteger Set the period that is to elapse between socket polls if data data is not ready and the connection is still open (in milliseconds) timeout Answer the period that is to elapse between the request for (yet unavailable) data and the moment when the connection is considered dead (in milliseconds) timeout: anInteger Set the period that is to elapse between the request for (yet unavailable) data and the moment when the connection is considered dead (in milliseconds) smalltalk-3.2.5/doc/gst.10000644000175000017500000000624312130455701012055 00000000000000.\" DO NOT MODIFY THIS FILE! It was generated by help2man 1.28. .TH SMALLTALK "1" "April 2013" "Smalltalk version 3.2.5-4dc033e" "User Commands" .SH NAME Smalltalk \- the GNU Smalltalk virtual machine .SH DESCRIPTION GNU Smalltalk usage: .IP gst [ flag ... ] [ file ... ] gst [ flag ... ] { \fB\-f\fR | \fB\-\-file\fR } file [ args ... ] .PP Short flags can appear either as \fB\-xyz\fR or as \fB\-x\fR \fB\-y\fR \fB\-z\fR. If an option is mandatory for a long option, it is also mandatory for a short one. The currently defined set of flags is: .TP \fB\-a\fR \fB\-\-smalltalk\-args\fR Pass the remaining arguments to Smalltalk. .TP \fB\-c\fR \fB\-\-core\-dump\fR Dump core on fatal signal. .TP \fB\-D\fR \fB\-\-declaration\-trace\fR Trace compilation of all loaded files. .TP \fB\-E\fR \fB\-\-execution\-trace\fR Trace execution of all loaded files. .TP \fB\-g\fR \fB\-\-no\-gc\-message\fR Do not print garbage collection messages. .TP \fB\-H\fR \fB\-\-help\fR Print this message and exit. .TP \fB\-i\fR \fB\-\-rebuild\-image\fR Ignore the image file; rebuild it from scratch. .TP \fB\-\-maybe\-rebuild\-image\fR Rebuild the image file from scratch if any kernel file is newer. .TP \fB\-I\fR \fB\-\-image\fR FILE Instead of `gst.im', use FILE as the image file, and ignore the kernel files' timestamps. .TP \fB\-K\fR \fB\-\-kernel\-file\fR FILE Make FILE's path relative to the image path. .TP \fB\-q\fR \fB\-\-quiet\fR \fB\-\-silent\fR Do not print execution information. .TP \fB\-r\fR \fB\-\-regression\-test\fR Run in regression test mode, i.e. make printed messages constant. .TP \fB\-S\fR \fB\-\-snapshot\fR Save a snapshot just before exiting. .TP \fB\-v\fR \fB\-\-version\fR Print the Smalltalk version number and exit. .TP \fB\-V\fR \fB\-\-verbose\fR Show names of loaded files and execution stats. .TP \fB\-\-emacs\-mode\fR Execute as a `process' (from within Emacs) .TP \fB\-\-kernel\-directory\fR DIR Look for kernel files in directory DIR. .TP \fB\-\-no\-user\-files\fR Don't read user customization files. .TP - Read input from standard input explicitly. .PP Files are loaded one after the other. After the last one is loaded, Smalltalk will exit. If no files are specified, Smalltalk reads from the terminal, with prompts. .PP In the second form, the file after \fB\-f\fR is the last loaded file; any parameter after that file is passed to the Smalltalk program. .SH AUTHOR Written by Steve Byrne (sbb@gnu.org) and Paolo Bonzini (bonzini@gnu.org) .PP GNU Smalltalk comes with NO WARRANTY, to the extent permitted by law. You may redistribute copies of GNU Smalltalk under the terms of the GNU General Public License. For more information, see the file named COPYING. .PP Using default kernel path: (null) Using default image path: (null) .SH "REPORTING BUGS" Report bugs to GNU Smalltalk home page: . General help using GNU software: . .PP Copyright 2009 Free Software Foundation, Inc. .SH "SEE ALSO" The full documentation for .B Smalltalk is maintained as a Texinfo manual. If the .B info and .B Smalltalk programs are properly installed at your site, the command .IP .B info gst .PP should give you access to the complete manual. smalltalk-3.2.5/doc/gst-package.10000644000175000017500000000553112130455702013446 00000000000000.\" DO NOT MODIFY THIS FILE! It was generated by help2man 1.28. .TH GST-PACKAGE "1" "April 2013" "gst-package version 3.2.5-4dc033e" "User Commands" .SH NAME gst-package \- create and install GNU Smalltalk .star package files .SH DESCRIPTION .SS "Usage:" .IP gst-package [OPTION]... ARGS... .SS "Operation modes:" .TP \fB\-\-install\fR make or install STAR packages (default) .TP \fB\-\-uninstall\fR remove the packages mentioned in the FILES .TP \fB\-\-dist\fR copy files instead of creating STAR files. .TP \fB\-\-prepare\fR create configure.ac or Makefile.am .TP \fB\-\-list\-files\fR PKG just output the list of files in the package .TP \fB\-\-list\-packages\fR just output the list of packages in the files .TP \fB\-\-download\fR, \fB\-\-update\fR download package from smalltalk.gnu.org or from its specified URL .TP \fB\-\-help\fR display this message and exit .TP \fB\-\-version\fR print version information and exit .SS "Common suboptions:" .TP \fB\-n\fR, \fB\-\-dry\-run\fR print commands without running them .TP \fB\-\-srcdir\fR DIR look for non-built files in directory DIR .TP \fB\-\-distdir\fR DIR for \fB\-\-dist\fR, place files in directory DIR .TP \fB\-\-destdir\fR DIR prefix the destination directory with DIR .TP \fB\-\-target\-directory\fR DIR install the files in DIR (unused for \fB\-\-dist\fR) .TP \fB\-I\fR, \fB\-\-image\-file\fR=\fIFILE\fR load into the specified image .TP \fB\-\-kernel\-dir\fR=\fIPATH\fR use the specified kernel directory .TP \fB\-v\fR, \fB\-\-verbose\fR print extra information while processing .SS "--install suboptions:" .TP \fB\-\-test\fR run unit tests after merging .TP \fB\-\-load\fR also load the Smalltalk files in the image .SS "--list-files suboptions:" .TP \fB\-\-load\fR only list files that are filed in when loading .TP \fB\-\-test\fR with \fB\-\-load\fR, also include unit test files .TP \fB\-\-vpath\fR Omit path to srcdir for files that are there .SS "--dist suboptions:" .TP \fB\-\-all\-files\fR Process all files, not just non-built ones .TP \fB\-\-copy\fR Do not create symbolic links .PP All operation modes except \fB\-\-download\fR (or its synonym \fB\-\-update\fR) accept paths to package.xml files or .star files, including remote URLs. \fB\-\-download\fR and \fB\-\-update\fR accept names of packages, which will be searched in the current system or on smalltalk.gnu.org) or URLs to package.xml or .star files. .PP Except in uninstall and list files mode, gst-package requires write access to the GNU Smalltalk image directory, and merges the XML package files on the command line with that file. .PP The default target directory is /home/ich/source/smalltalk/release/smalltalk .SH "SEE ALSO" The full documentation for .B gst-package is maintained as a Texinfo manual. If the .B info and .B gst-package programs are properly installed at your site, the command .IP .B info gst .PP should give you access to the complete manual. smalltalk-3.2.5/doc/blox.texi0000644000175000017500000063473212130455676013062 00000000000000@c Define the class index, method index, and selector cross-reference @ifclear CLASS-INDICES @set CLASS-INDICES @defindex cl @defcodeindex me @defcodeindex sl @end ifclear @c These are used for both TeX and HTML @set BEFORE1 @set AFTER1 @set BEFORE2 @set AFTER2 @ifinfo @c Use asis so that leading and trailing spaces are meaningful. @c Remember we're inside a @menu command, hence the blanks are @c kept in the output. @set BEFORE1 @asis{* } @set AFTER1 @asis{::} @set BEFORE2 @asis{ (} @set AFTER2 @asis{)} @end ifinfo @macro class {a,b} @value{BEFORE1}\a\\a\@b{\b\}@value{AFTER1} @end macro @macro superclass {a,b} \a\\a\@value{BEFORE2}@i{\b\}@value{AFTER2} @end macro @ifnotinfo @macro begindetailmenu @display @end macro @macro enddetailmenu @end display @end macro @end ifnotinfo @ifinfo @macro begindetailmenu @detailmenu @end macro @macro enddetailmenu @end detailmenu @end macro @end ifinfo @iftex @macro beginmenu @end macro @macro endmenu @end macro @end iftex @ifnottex @macro beginmenu @menu @end macro @macro endmenu @end menu @end macro @end ifnottex @beginmenu @ifnottex Alphabetic list: * BLOX.BArc:: * BLOX.BBalloon:: * BLOX.BBoundingBox:: * BLOX.BButton:: * BLOX.BButtonLike:: * BLOX.BCanvas:: * BLOX.BCanvasObject:: * BLOX.BCheckMenuItem:: * BLOX.BColorButton:: * BLOX.BContainer:: * BLOX.BDialog:: * BLOX.BDropDown:: * BLOX.BDropDownEdit:: * BLOX.BDropDownList:: * BLOX.BEdit:: * BLOX.BEmbeddedImage:: * BLOX.BEmbeddedText:: * BLOX.BEventSet:: * BLOX.BEventTarget:: * BLOX.BExtended:: * BLOX.BForm:: * BLOX.BImage:: * BLOX.BLabel:: * BLOX.BLine:: * BLOX.BList:: * BLOX.Blox:: * BLOX.BMenu:: * BLOX.BMenuBar:: * BLOX.BMenuItem:: * BLOX.BMenuObject:: * BLOX.BOval:: * BLOX.BPolyline:: * BLOX.BPopupMenu:: * BLOX.BPopupWindow:: * BLOX.BPrimitive:: * BLOX.BProgress:: * BLOX.BRadioButton:: * BLOX.BRadioGroup:: * BLOX.BRectangle:: * BLOX.BScrolledCanvas:: * BLOX.BSpline:: * BLOX.BText:: * BLOX.BTextAttributes:: * BLOX.BTextBindings:: * BLOX.BTextTags:: * BLOX.BToggle:: * BLOX.BTransientWindow:: * BLOX.BViewport:: * BLOX.BWidget:: * BLOX.BWindow:: * BLOX.Gui:: @end ifnottex @ifinfo Class tree: @end ifinfo @iftex @section Tree @end iftex @ifnotinfo Classes documented in this manual are @b{boldfaced}. @end ifnotinfo @begindetailmenu @superclass{@t{}, Object} @class{@t{ }, BLOX.BEventTarget} @class{@t{ }, BLOX.BCanvasObject} @class{@t{ }, BLOX.BBoundingBox} @class{@t{ }, BLOX.BEmbeddedImage} @class{@t{ }, BLOX.BEmbeddedText} @class{@t{ }, BLOX.BLine} @class{@t{ }, BLOX.BRectangle} @class{@t{ }, BLOX.BOval} @class{@t{ }, BLOX.BArc} @class{@t{ }, BLOX.BPolyline} @class{@t{ }, BLOX.BSpline} @class{@t{ }, BLOX.BEventSet} @class{@t{ }, BLOX.BBalloon} @class{@t{ }, BLOX.Blox} @class{@t{ }, BLOX.BMenuObject} @class{@t{ }, BLOX.BMenu} @class{@t{ }, BLOX.BPopupMenu} @class{@t{ }, BLOX.BMenuBar} @class{@t{ }, BLOX.BMenuItem} @class{@t{ }, BLOX.BCheckMenuItem} @class{@t{ }, BLOX.BWidget} @class{@t{ }, BLOX.BExtended} @class{@t{ }, BLOX.BButtonLike} @class{@t{ }, BLOX.BColorButton} @class{@t{ }, BLOX.BDropDown} @class{@t{ }, BLOX.BDropDownEdit} @class{@t{ }, BLOX.BDropDownList} @class{@t{ }, BLOX.BProgress} @class{@t{ }, BLOX.BPrimitive} @class{@t{ }, BLOX.BButton} @class{@t{ }, BLOX.BRadioButton} @class{@t{ }, BLOX.BToggle} @class{@t{ }, BLOX.BEdit} @class{@t{ }, BLOX.BForm} @class{@t{ }, BLOX.BContainer} @class{@t{ }, BLOX.BRadioGroup} @class{@t{ }, BLOX.BDialog} @class{@t{ }, BLOX.BWindow} @class{@t{ }, BLOX.BPopupWindow} @class{@t{ }, BLOX.BTransientWindow} @class{@t{ }, BLOX.BImage} @class{@t{ }, BLOX.BLabel} @class{@t{ }, BLOX.BViewport} @class{@t{ }, BLOX.BCanvas} @class{@t{ }, BLOX.BScrolledCanvas} @class{@t{ }, BLOX.BList} @class{@t{ }, BLOX.BText} @class{@t{ }, BLOX.BTextBindings} @class{@t{ }, BLOX.BTextAttributes} @class{@t{ }, BLOX.BTextTags} @class{@t{ }, BLOX.Gui} @enddetailmenu @endmenu @unmacro class @unmacro superclass @unmacro endmenu @unmacro beginmenu @unmacro enddetailmenu @unmacro begindetailmenu @node BLOX.BArc @section BLOX.BArc @clindex BLOX.BArc @table @b @item Defined in namespace BLOX @itemx Superclass: BLOX.BOval @itemx Category: Graphics-Windows I can draw arcs, pie slices (don't eat them!!), chords, and... nothing more. @end table @menu * BLOX.BArc-accessing:: (instance) @end menu @node BLOX.BArc-accessing @subsection BLOX.BArc:@- accessing @table @b @meindex endAngle @item endAngle Answer the ending of the angular range that is occupied by the arc, expressed in degrees @meindex endAngle:@- @item endAngle:@- angle Set the ending of the angular range that is occupied by the arc, expressed in degrees @meindex fillChord @item fillChord Specify that the arc will be filled by painting an area delimited by the arc and the chord that joins the arc's endpoints. @meindex fillSlice @item fillSlice Specify that the arc will be filled by painting an area delimited by the arc and the two radii joins the center of the arc with each of the endpoints (that is, that a pie slice will be drawn). @meindex from @item from Answer the starting point of the arc in cartesian coordinates @meindex from:@- @item from:@- aPoint Set the starting point of the arc in cartesian coordinates @meindex from:@-to:@- @item from:@- start to:@- end Set the two starting points of the arc in cartesian coordinates @meindex startAngle @item startAngle Answer the beginning of the angular range that is occupied by the arc, expressed in degrees @meindex startAngle:@- @item startAngle:@- angle Set the beginning of the angular range that is occupied by the arc, expressed in degrees @meindex sweepAngle @item sweepAngle Answer the size of the angular range that is occupied by the arc, expressed in degrees @meindex sweepAngle:@- @item sweepAngle:@- angle Set the size of the angular range that is occupied by the arc, expressed in degrees @meindex to @item to Answer the ending point of the arc in cartesian coordinates @meindex to:@- @item to:@- aPoint Set the ending point of the arc in cartesian coordinates @end table @node BLOX.BBalloon @section BLOX.BBalloon @clindex BLOX.BBalloon @table @b @item Defined in namespace BLOX @itemx Superclass: BLOX.BEventSet @itemx Category: Graphics-Examples This event set allows a widget to show explanatory information when the mouse lingers over it for a while. @end table @menu * BLOX.BBalloon class-accessing:: (class) * BLOX.BBalloon-accessing:: (instance) * BLOX.BBalloon-initializing:: (instance) @end menu @node BLOX.BBalloon class-accessing @subsection BLOX.BBalloon class:@- accessing @table @b @meindex balloonDelayTime @item balloonDelayTime Answer the time after which the balloon is shown (default is half a second). @meindex balloonDelayTime:@- @item balloonDelayTime:@- milliseconds Set the time after which the balloon is shown. @meindex shown @item shown Answer whether a balloon is displayed @end table @node BLOX.BBalloon-accessing @subsection BLOX.BBalloon:@- accessing @table @b @meindex shown @item shown Answer whether the receiver's balloon is displayed @meindex text @item text Answer the text displayed in the balloon @meindex text:@- @item text:@- aString Set the text displayed in the balloon to aString @end table @node BLOX.BBalloon-initializing @subsection BLOX.BBalloon:@- initializing @table @b @meindex initialize:@- @item initialize:@- aBWidget Initialize the event sets for the receiver @end table @node BLOX.BBoundingBox @section BLOX.BBoundingBox @clindex BLOX.BBoundingBox @table @b @item Defined in namespace BLOX @itemx Superclass: BLOX.BCanvasObject @itemx Category: Graphics-Windows I am the ultimate ancestor of all items that you can put in a BCanvas and which are well defined by their bounding box - i.e. everything except BPolylines and BSplines. @end table @menu * BLOX.BBoundingBox-accessing:: (instance) @end menu @node BLOX.BBoundingBox-accessing @subsection BLOX.BBoundingBox:@- accessing @table @b @meindex boundingBox @item boundingBox Answer a Rectangle enclosing all of the receiver @meindex center @item center Answer the center point of the receiver @meindex center:@-extent:@- @slindex create @slindex redraw @item center:@- center extent:@- extent Move the object so that it is centered around the center Point and its size is given by the extent Point. No changes take place until you invoke the #create (if the object has not been inserted in the canvas yet) or the #redraw method. @meindex corner @item corner Answer the Point specifying the lower-right corner of the receiver @meindex corner:@- @slindex create @slindex redraw @item corner:@- pointOrArray Set the Point specifying the lower-right corner of the receiver; pointOrArray can be a Point or a two-item Array. No changes take place until you invoke the #create (if the object has not been inserted in the canvas yet) or the #redraw method. @meindex extent @item extent Answer a Point specifying the size of the receiver @meindex extent:@- @slindex create @slindex redraw @item extent:@- pointOrArray Set the Point specifying the size of the receiver; pointOrArray can be a Point or a two-item Array. No changes take place until you invoke the #create (if the object has not been inserted in the canvas yet) or the #redraw method. @meindex moveBy:@- @slindex create @slindex redraw @item moveBy:@- pointOrArray Move the object by the amount indicated by pointOrArray:@- that is, its whole bounding box is shifted by that amount. No changes take place until you invoke the #create (if the object has not been inserted in the canvas yet) or the #redraw method. @meindex origin @item origin Answer the Point specifying the top-left corner of the receiver @meindex origin:@- @slindex create @slindex redraw @item origin:@- pointOrArray Set the Point specifying the top-left corner of the receiver; pointOrArray can be a Point or a two-item Array. No changes take place until you invoke the #create (if the object has not been inserted in the canvas yet) or the #redraw method. @meindex origin:@-corner:@- @slindex create @slindex redraw @item origin:@- originPointOrArray corner:@- cornerPointOrArray Set the bounding box of the object, based on a Point specifying the top-left corner of the receiver and another specifying the bottom-right corner; the two parameters can both be Points or two-item Arrays. No changes take place until you invoke the #create (if the object has not been inserted in the canvas yet) or the #redraw method. @meindex origin:@-extent:@- @slindex create @slindex redraw @item origin:@- originPointOrArray extent:@- extentPointOrArray Set the bounding box of the object, based on a Point specifying the top-left corner of the receiver and another specifying its size; the two parameters can both be Points or two-item Arrays. No changes take place until you invoke the #create (if the object has not been inserted in the canvas yet) or the #redraw method. @end table @node BLOX.BButton @section BLOX.BButton @clindex BLOX.BButton @table @b @item Defined in namespace BLOX @itemx Superclass: BLOX.BPrimitive @itemx Category: Graphics-Windows I am a button that a user can click. In fact I am at the head of a small hierarchy of objects which exhibit button-like look and behavior @end table @menu * BLOX.BButton class-instance creation:: (class) * BLOX.BButton-accessing:: (instance) @end menu @node BLOX.BButton class-instance creation @subsection BLOX.BButton class:@- instance creation @table @b @meindex new:@-label:@- @item new:@- parent label:@- label Answer a new BButton widget laid inside the given parent widget, showing by default the `label' String. @end table @node BLOX.BButton-accessing @subsection BLOX.BButton:@- accessing @table @b @meindex backgroundColor @item backgroundColor Answer the value of the backgroundColor option for the widget. Specifies the normal background color to use when displaying the widget. @meindex backgroundColor:@- @item backgroundColor:@- value Set the value of the backgroundColor option for the widget. Specifies the normal background color to use when displaying the widget. @meindex callback @item callback Answer a DirectedMessage that is sent when the receiver is clicked, or nil if none has been set up. @meindex callback:@-message:@- @item callback:@- aReceiver message:@- aSymbol Set up so that aReceiver is sent the aSymbol message (the name of a zero- or one-argument selector) when the receiver is clicked. If the method accepts an argument, the receiver is passed. @meindex font @item font Answer the value of the font option for the widget. Specifies the font to use when drawing text inside the widget. The font can be given as either an X font name or a Blox font description string. X font names are given as many fields, each led by a minus, and each of which can be replaced by an * to indicate a default value is ok:@- foundry, family, weight, slant, setwidth, addstyle, pixel size, point size (the same as pixel size for historical reasons), horizontal resolution, vertical resolution, spacing, width, charset and character encoding. Blox font description strings have three fields, which must be separated by a space and of which only the first is mandatory:@- the font family, the font size in points (or in pixels if a negative value is supplied), and a number of styles separated by a space (valid styles are normal, bold, italic, underline and overstrike). Examples of valid fonts are ``Helvetica 10 Bold'', ``Times -14'', ``Futura Bold Underline''. You must enclose the font family in braces if it is made of two or more words. @meindex font:@- @item font:@- value Set the value of the font option for the widget. Specifies the font to use when drawing text inside the widget. The font can be given as either an X font name or a Blox font description string. X font names are given as many fields, each led by a minus, and each of which can be replaced by an * to indicate a default value is ok:@- foundry, family, weight, slant, setwidth, addstyle, pixel size, point size (the same as pixel size for historical reasons), horizontal resolution, vertical resolution, spacing, width, charset and character encoding. Blox font description strings have three fields, which must be separated by a space and of which only the first is mandatory:@- the font family, the font size in points (or in pixels if a negative value is supplied), and a number of styles separated by a space (valid styles are normal, bold, italic, underline and overstrike). Examples of valid fonts are ``Helvetica 10 Bold'', ``Times -14'', ``Futura Bold Underline''. You must enclose the font family in braces if it is made of two or more words. @meindex foregroundColor @item foregroundColor Answer the value of the foregroundColor option for the widget. Specifies the normal foreground color to use when displaying the widget. @meindex foregroundColor:@- @item foregroundColor:@- value Set the value of the foregroundColor option for the widget. Specifies the normal foreground color to use when displaying the widget. @meindex invokeCallback @item invokeCallback Generate a synthetic callback @meindex label @item label Answer the value of the label option for the widget. Specifies a string to be displayed inside the widget. The way in which the string is displayed depends on the particular widget and may be determined by other options, such as anchor. For windows, this is the title of the window. @meindex label:@- @item label:@- value Set the value of the label option for the widget. Specifies a string to be displayed inside the widget. The way in which the string is displayed depends on the particular widget and may be determined by other options, such as anchor. For windows, this is the title of the window. @end table @node BLOX.BButtonLike @section BLOX.BButtonLike @clindex BLOX.BButtonLike @table @b @item Defined in namespace BLOX @itemx Superclass: BLOX.BExtended @itemx Category: Graphics-Examples I am an object whose 3-D appearance resembles that of buttons. @end table @menu * BLOX.BButtonLike-accessing:: (instance) @end menu @node BLOX.BButtonLike-accessing @subsection BLOX.BButtonLike:@- accessing @table @b @meindex callback @item callback Answer a DirectedMessage that is sent when the receiver is clicked, or nil if none has been set up. @meindex callback:@-message:@- @item callback:@- aReceiver message:@- aSymbol Set up so that aReceiver is sent the aSymbol message (the name of a zero- or one-argument selector) when the receiver is clicked. If the method accepts an argument, the receiver is passed. @meindex invokeCallback @item invokeCallback Generate a synthetic callback @meindex pressed @item pressed This is the default callback for the widget; it does nothing if you don't override it. Of course if a subclass overriddes this you (user of the class) might desire to call this method from your own callback. @end table @node BLOX.BCanvas @section BLOX.BCanvas @clindex BLOX.BCanvas @table @b @item Defined in namespace BLOX @itemx Superclass: BLOX.BViewport @itemx Category: Graphics-Windows I am an host for whatever geometric shape you want. If you want to do some fancy graphics with Smalltalk, I'll be happy to help. My friends derived from BCanvasObject ask me all sort of things to do, so I am the real worker, not they! BCanvasObject:@- I am BCanvas:@- No I am BCanvasObject:@- No I am BCanvas:@- No I am well, you know, he always has something to object. @end table @menu * BLOX.BCanvas-accessing:: (instance) * BLOX.BCanvas-geometry management:: (instance) * BLOX.BCanvas-widget protocol:: (instance) @end menu @node BLOX.BCanvas-accessing @subsection BLOX.BCanvas:@- accessing @table @b @meindex backgroundColor @item backgroundColor Answer the value of the backgroundColor option for the widget. Specifies the normal background color to use when displaying the widget. @meindex backgroundColor:@- @item backgroundColor:@- value Set the value of the backgroundColor option for the widget. Specifies the normal background color to use when displaying the widget. @meindex foregroundColor @item foregroundColor Answer the value of the foregroundColor option for the widget. Specifies the normal foreground color to use when displaying the widget. @meindex foregroundColor:@- @item foregroundColor:@- value Set the value of the foregroundColor option for the widget. Specifies the normal foreground color to use when displaying the widget. @end table @node BLOX.BCanvas-geometry management @subsection BLOX.BCanvas:@- geometry management @table @b @meindex addChild:@- @slindex basicAddChild:@- @item addChild:@- child The widget identified by child has been added to the receiver. This method is public not because you can call it, but because it can be useful to override it, not forgetting the call to either the superclass implementation or #basicAddChild:@-, to perform some initialization on the children just added. Answer the new child. @meindex child:@-height:@- @item child:@- child height:@- value Set the given child's height. @meindex child:@-heightOffset:@- @item child:@- child heightOffset:@- value Offset the given child's height by value pixels. @meindex child:@-width:@- @item child:@- child width:@- value Set the given child's width. @meindex child:@-widthOffset:@- @item child:@- child widthOffset:@- value Offset the given child's width by value pixels. @meindex child:@-x:@- @item child:@- child x:@- value Set the given child's top-left corner's x coordinate, in pixels in the canvas' coordinate system. @meindex child:@-xOffset:@- @item child:@- child xOffset:@- value Offset the given child's top-left x by value pixels. @meindex child:@-y:@- @item child:@- child y:@- value Set the given child's top-left corner's y coordinate, in pixels in the canvas' coordinate system. @meindex child:@-yOffset:@- @item child:@- child yOffset:@- value Offset the given child's top-left y by value pixels. @meindex heightChild:@- @item heightChild:@- child Answer the given child's height in pixels. @meindex widthChild:@- @item widthChild:@- child Answer the given child's width in pixels. @meindex xChild:@- @item xChild:@- child Answer the given child's top-left corner's x coordinate, in pixels in the canvas' coordinate system. @meindex yChild:@- @item yChild:@- child Answer the given child's top-left corner's y coordinate, in pixels in the canvas' coordinate system. @end table @node BLOX.BCanvas-widget protocol @subsection BLOX.BCanvas:@- widget protocol @table @b @meindex at:@- @item at:@- aPoint Selects the topmost item in the canvas overlapping the point given by aPoint. @meindex between:@-and:@-do:@- @item between:@- origin and:@- corner do:@- aBlock Evaluate aBlock for each item whose bounding box intersects the rectangle between the two Points, origin and corner. Pass the item to the block. @meindex boundingBox @item boundingBox Answer the bounding box of all the items in the canvas @meindex destroyed @item destroyed The widget has been destroyed. Tell all of its items about this fact. @meindex do:@- @item do:@- aBlock Evaluate aBlock, passing each item to it. @meindex empty @item empty Remove all the items from the canvas, leaving it empty @meindex extraSpace @item extraSpace Answer the amount of space that is left as a border around the canvas items. @meindex extraSpace:@- @item extraSpace:@- aPoint Set the amount of space that is left as a border around the canvas items. @meindex items @item items Answer an Array containing all the items in the canvas @meindex mapPoint:@- @item mapPoint:@- aPoint Given aPoint, a point expressed in window coordinates, answer the corresponding canvas coordinates that are displayed at that location. @end table @node BLOX.BCanvasObject @section BLOX.BCanvasObject @clindex BLOX.BCanvasObject @table @b @item Defined in namespace BLOX @itemx Superclass: BLOX.BEventTarget @itemx Category: Graphics-Windows I am the ultimate ancestor of all items that you can put in a BCanvas. I provide some general methods to my concrete offspring. @end table @menu * BLOX.BCanvasObject class-instance creation:: (class) * BLOX.BCanvasObject-accessing:: (instance) * BLOX.BCanvasObject-widget protocol:: (instance) @end menu @node BLOX.BCanvasObject class-instance creation @subsection BLOX.BCanvasObject class:@- instance creation @table @b @meindex new @item new This method should not be called for instances of this class. @meindex new:@- @item new:@- parentCanvas Answer a new instance of the receiver, displayed into the given parentCanvas. @end table @node BLOX.BCanvasObject-accessing @subsection BLOX.BCanvasObject:@- accessing @table @b @meindex blox @item blox Answer the parent canvas of the receiver @meindex boundingBox @item boundingBox Answer a Rectangle enclosing all of the receiver @meindex color @item color Answer the color to be used to fill this item's area. @meindex color:@- @item color:@- color Set the color to be used to fill this item's area. @meindex copyInto:@- @item copyInto:@- newCanvas Answer a new BCanvasObject identical to this but displayed into another canvas, newCanvas. The new instance is not created at the time it is returned. @meindex copyObject @slindex copy @slindex copyObject @item copyObject Answer a new BCanvasObject identical to this. Unlike #copy, which merely creates a new Smalltalk object with the same data and referring to the same canvas item, the object created with #copyObject is physically distinct from the original. The new instance is not created at the time it is returned. @meindex createCopy @slindex copy @slindex copyObject @item createCopy Answer a new BCanvasObject identical to this. Unlike #copy, which merely creates a new Smalltalk object with the same data and referring to the same canvas item, the object created with #copyObject is physically distinct from the original. The new instance has already been created at the time it is returned. @meindex createCopyInto:@- @item createCopyInto:@- newCanvas Answer a new BCanvasObject identical to this but displayed into another canvas, newCanvas. The new instance has already been created at the time it is returned. @meindex deepCopy @item deepCopy It does not make sense to make a copy, because it would make data inconsistent across different objects; so answer the receiver @meindex grayOut @item grayOut Apply a 50% gray stippling pattern to the object @meindex shallowCopy @item shallowCopy It does not make sense to make a copy, because it would make data inconsistent across different objects; so answer the receiver @end table @node BLOX.BCanvasObject-widget protocol @subsection BLOX.BCanvasObject:@- widget protocol @table @b @meindex create @item create If the object has not been created yet and has been initialized correctly, insert it for real in the parent canvas @meindex created @item created Answer whether the object is just a placeholder or has already been inserted for real in the parent canvas @meindex lower @item lower Move the item to the lowest position in the display list. Child widgets always obscure other item types, and the stacking order of window items is determined by sending methods to the widget object directly. @meindex raise @item raise Move the item to the highest position in the display list. Child widgets always obscure other item types, and the stacking order of window items is determined by sending methods to the widget object directly. @meindex redraw @item redraw Force the object to be displayed in the parent canvas, creating it if it has not been inserted for real in the parent, and refresh its position if it has changed. @meindex remove @item remove Remove the object from the canvas @meindex show @item show Ensure that the object is visible in the center of the canvas, scrolling it if necessary. @end table @node BLOX.BCheckMenuItem @section BLOX.BCheckMenuItem @clindex BLOX.BCheckMenuItem @table @b @item Defined in namespace BLOX @itemx Superclass: BLOX.BMenuItem @itemx Category: Graphics-Windows I am a menu item which can be toggled between two states, marked and unmarked. @end table @menu * BLOX.BCheckMenuItem class-instance creation:: (class) * BLOX.BCheckMenuItem-accessing:: (instance) @end menu @node BLOX.BCheckMenuItem class-instance creation @subsection BLOX.BCheckMenuItem class:@- instance creation @table @b @meindex new:@- @item new:@- parent This method should not be called for instances of this class. @end table @node BLOX.BCheckMenuItem-accessing @subsection BLOX.BCheckMenuItem:@- accessing @table @b @meindex invokeCallback @item invokeCallback Generate a synthetic callback @meindex value @item value Answer whether the menu item is in a selected (checked) state. @meindex value:@- @item value:@- aBoolean Set whether the button is in a selected (checked) state and generates a callback accordingly. @end table @node BLOX.BColorButton @section BLOX.BColorButton @clindex BLOX.BColorButton @table @b @item Defined in namespace BLOX @itemx Superclass: BLOX.BButtonLike @itemx Category: Graphics-Examples I am a button that shows a color and that, unless a different callback is used, lets you choose a color when it is clicked. @end table @menu * BLOX.BColorButton-accessing:: (instance) @end menu @node BLOX.BColorButton-accessing @subsection BLOX.BColorButton:@- accessing @table @b @meindex color @item color Set the color that the receiver is painted in. @meindex color:@- @item color:@- aString Set the color that the receiver is painted in. @meindex pressed @item pressed This is the default callback; it brings up a `choose-a-color' window and, if `Ok' is pressed in the window, sets the receiver to be painted in the chosen color. @end table @node BLOX.BContainer @section BLOX.BContainer @clindex BLOX.BContainer @table @b @item Defined in namespace BLOX @itemx Superclass: BLOX.BForm @itemx Category: Graphics-Windows I am used to group many widgets together. I can perform simple management by putting widgets next to each other, from left to right or from top to bottom. @end table @menu * BLOX.BContainer-accessing:: (instance) @end menu @node BLOX.BContainer-accessing @subsection BLOX.BContainer:@- accessing @table @b @meindex setVerticalLayout:@- @item setVerticalLayout:@- aBoolean Answer whether the container will align the widgets vertically or horizontally. Horizontal alignment means that widgets are packed from left to right, while vertical alignment means that widgets are packed from the top to the bottom of the widget. Widgets that are set to be ``stretched'' will share all the space that is not allocated to non-stretched widgets. The layout of the widget can only be set before the first child is inserted in the widget. @end table @node BLOX.BDialog @section BLOX.BDialog @clindex BLOX.BDialog @table @b @item Defined in namespace BLOX @itemx Superclass: BLOX.BForm @itemx Category: Graphics-Windows I am a facility for implementing dialogs with many possible choices and requests. In addition I provide support for a few platform native common dialog boxes, such as choose-a-file and choose-a-color. @end table @menu * BLOX.BDialog class-instance creation:: (class) * BLOX.BDialog class-prompters:: (class) * BLOX.BDialog-accessing:: (instance) * BLOX.BDialog-widget protocol:: (instance) @end menu @node BLOX.BDialog class-instance creation @subsection BLOX.BDialog class:@- instance creation @table @b @meindex new:@- @item new:@- parent Answer a new dialog handler (containing a label widget and some button widgets) laid out within the given parent window. The label widget, when it is created, is empty. @meindex new:@-label:@- @item new:@- parent label:@- aLabel Answer a new dialog handler (containing a label widget and some button widgets) laid out within the given parent window. The label widget, when it is created, contains aLabel. @meindex new:@-label:@-prompt:@- @item new:@- parent label:@- aLabel prompt:@- aString Answer a new dialog handler (containing a label widget, some button widgets, and an edit window showing aString by default) laid out within the given parent window. The label widget, when it is created, contains aLabel. @end table @node BLOX.BDialog class-prompters @subsection BLOX.BDialog class:@- prompters @table @b @meindex chooseColor:@-label:@-default:@- @item chooseColor:@- parent label:@- aLabel default:@- color Prompt for a color. The dialog box is created with the given parent window and with aLabel as its title bar text, and initially it selects the color given in the color parameter. If the dialog box is canceled, nil is answered, else the selected color is returned as a String with its RGB value. @meindex chooseFileToOpen:@-label:@-default:@-defaultExtension:@-types:@- @item chooseFileToOpen:@- parent label:@- aLabel default:@- name defaultExtension:@- ext types:@- typeList Pop up a dialog box for the user to select a file to open. Its purpose is for the user to select an existing file only. If the user enters an non-existent file, the dialog box gives the user an error prompt and requires the user to give an alternative selection or to cancel the selection. If an application allows the user to create new files, it should do so by providing a separate New menu command. If the dialog box is canceled, nil is answered, else the selected file name is returned as a String. The dialog box is created with the given parent window and with aLabel as its title bar text. The name parameter indicates which file is initially selected, and the default extension specifies a string that will be appended to the filename if the user enters a filename without an extension. The typeList parameter is an array of arrays, like #(('Text files' '.txt' '.diz') ('Smalltalk files' '.st')), and is used to construct a listbox of file types. When the user chooses a file type in the listbox, only the files of that type are listed. Each item in the array contains a list of strings:@- the first one is the name of the file type described by a particular file pattern, and is the text string that appears in the File types listbox, while the other ones are the possible extensions that belong to this particular file type. @meindex chooseFileToSave:@-label:@-default:@-defaultExtension:@-types:@- @item chooseFileToSave:@- parent label:@- aLabel default:@- name defaultExtension:@- ext types:@- typeList Pop up a dialog box for the user to select a file to save; this differs from the file open dialog box in that non-existent file names are accepted and existing file names trigger a confirmation dialog box, asking the user whether the file should be overwritten or not. If the dialog box is canceled, nil is answered, else the selected file name is returned as a String. The dialog box is created with the given parent window and with aLabel as its title bar text. The name parameter indicates which file is initially selected, and the default extension specifies a string that will be appended to the filename if the user enters a filename without an extension. The typeList parameter is an array of arrays, like #(('Text files' '.txt' '.diz') ('Smalltalk files' '.st')), and is used to construct a listbox of file types. When the user chooses a file type in the listbox, only the files of that type are listed. Each item in the array contains a list of strings:@- the first one is the name of the file type described by a particular file pattern, and is the text string that appears in the File types listbox, while the other ones are the possible extensions that belong to this particular file type. @end table @node BLOX.BDialog-accessing @subsection BLOX.BDialog:@- accessing @table @b @meindex addButton:@-receiver:@-index:@- @slindex dispatch:@- @item addButton:@- aLabel receiver:@- anObject index:@- anInt Add a button to the dialog box that, when clicked, will cause the #dispatch:@- method to be triggered in anObject, passing anInt as the argument of the callback. The caption of the button is set to aLabel. @meindex addButton:@-receiver:@-message:@- @item addButton:@- aLabel receiver:@- anObject message:@- aSymbol Add a button to the dialog box that, when clicked, will cause the aSymbol unary selector to be sent to anObject. The caption of the button is set to aLabel. @meindex addButton:@-receiver:@-message:@-argument:@- @item addButton:@- aLabel receiver:@- anObject message:@- aSymbol argument:@- arg Add a button to the dialog box that, when clicked, will cause the aSymbol one-argument selector to be sent to anObject, passing arg as the argument of the callback. The caption of the button is set to aLabel. @meindex contents @item contents Answer the text that is displayed in the entry widget associated to the dialog box. @meindex contents:@- @item contents:@- newText Display newText in the entry widget associated to the dialog box. @end table @node BLOX.BDialog-widget protocol @subsection BLOX.BDialog:@- widget protocol @table @b @meindex center @item center Center the dialog box's parent window in the screen @meindex centerIn:@- @item centerIn:@- view Center the dialog box's parent window in the given widget @meindex destroyed @item destroyed Private - The receiver has been destroyed, clear the corresponding Tcl variable to avoid memory leaks. @meindex invokeCallback:@- @item invokeCallback:@- index Generate a synthetic callback corresponding to the index-th button being pressed, and destroy the parent window (triggering its callback if one was established). @meindex loop @slindex modalMap @item loop Map the parent window modally. In other words, an event loop is started that ends only after the window has been destroyed. For more information on the treatment of events for modal windows, refer to BWindow>>@-#modalMap. @end table @node BLOX.BDropDown @section BLOX.BDropDown @clindex BLOX.BDropDown @table @b @item Defined in namespace BLOX @itemx Superclass: BLOX.BExtended @itemx Category: Graphics-Examples This class is an abstract superclass for widgets offering the ability to pick items from a pre-built list. The list is usually hidden, but a button on the right of this widgets makes it pop up. This widget is thus composed of three parts:@- an unspecified text widget (shown on the left of the button and always visible), the button widget (shown on the right, it depicts a down arrow, and is always visible), and the pop-up list widget. @end table @menu * BLOX.BDropDown-accessing:: (instance) * BLOX.BDropDown-callbacks:: (instance) * BLOX.BDropDown-flexibility:: (instance) * BLOX.BDropDown-list box accessing:: (instance) * BLOX.BDropDown-widget protocol:: (instance) @end menu @node BLOX.BDropDown-accessing @subsection BLOX.BDropDown:@- accessing @table @b @meindex backgroundColor @item backgroundColor Answer the value of the backgroundColor for the widget, which in this class is only set for the list widget (that is, the pop-up widget). Subclasses should override this method so that the color is set properly for the text widget as well. Specifies the normal background color to use when displaying the widget. @meindex backgroundColor:@- @item backgroundColor:@- aColor Set the value of the backgroundColor for the widget, which in this class is only set for the list widget (that is, the pop-up widget). Subclasses should override this method so that the color is set properly for the text widget as well. Specifies the normal background color to use when displaying the widget. @meindex droppedRows @item droppedRows Answer the number of items that are visible at any time in the listbox. @meindex droppedRows:@- @item droppedRows:@- anInteger Set the number of items that are visible at any time in the listbox. @meindex font @item font Answer the value of the font option for the widget, which in this class is only set for the list widget (that is, the pop-up widget). Subclasses should override this method so that the color is set properly for the text widget as well. Specifies the font to use when drawing text inside the widget. The font can be given as either an X font name or a Blox font description string. X font names are given as many fields, each led by a minus, and each of which can be replaced by an * to indicate a default value is ok:@- foundry, family, weight, slant, setwidth, addstyle, pixel size, point size (the same as pixel size for historical reasons), horizontal resolution, vertical resolution, spacing, width, charset and character encoding. Blox font description strings have three fields, which must be separated by a space and of which only the first is mandatory:@- the font family, the font size in points (or in pixels if a negative value is supplied), and a number of styles separated by a space (valid styles are normal, bold, italic, underline and overstrike). Examples of valid fonts are ``Helvetica 10 Bold'', ``Times -14'', ``Futura Bold Underline''. You must enclose the font family in braces if it is made of two or more words. @meindex font:@- @item font:@- value Set the value of the font option for the widget, which in this class is only set for the list widget (that is, the pop-up widget). Subclasses should override this method so that the color is set properly for the text widget as well. Specifies the font to use when drawing text inside the widget. The font can be given as either an X font name or a Blox font description string. X font names are given as many fields, each led by a minus, and each of which can be replaced by an * to indicate a default value is ok:@- foundry, family, weight, slant, setwidth, addstyle, pixel size, point size (the same as pixel size for historical reasons), horizontal resolution, vertical resolution, spacing, width, charset and character encoding. Blox font description strings have three fields, which must be separated by a space and of which only the first is mandatory:@- the font family, the font size in points (or in pixels if a negative value is supplied), and a number of styles separated by a space (valid styles are normal, bold, italic, underline and overstrike). Examples of valid fonts are ``Helvetica 10 Bold'', ``Times -14'', ``Futura Bold Underline''. You must enclose the font family in braces if it is made of two or more words. @meindex foregroundColor @item foregroundColor Answer the value of the foregroundColor for the widget, which in this class is only set for the list widget (that is, the pop-up widget). Subclasses should override this method so that the color is set properly for the text widget as well. Specifies the normal foreground color to use when displaying the widget. @meindex foregroundColor:@- @item foregroundColor:@- aColor Set the value of the foregroundColor for the widget, which in this class is only set for the list widget (that is, the pop-up widget). Subclasses should override this method so that the color is set properly for the text widget as well. Specifies the normal foreground color to use when displaying the widget. @meindex highlightBackground @item highlightBackground Answer the value of the highlightBackground option for the widget. Specifies the background color to use when displaying selected items in the list widget. @meindex highlightBackground:@- @item highlightBackground:@- aColor Set the value of the highlightBackground option for the widget. Specifies the background color to use when displaying selected items in the list widget. @meindex highlightForeground @item highlightForeground Answer the value of the highlightForeground option for the widget. Specifies the foreground color to use when displaying selected items in the list widget. @meindex highlightForeground:@- @item highlightForeground:@- aColor Set the value of the highlightForeground option for the widget. Specifies the foreground color to use when displaying selected items in the list widget. @end table @node BLOX.BDropDown-callbacks @subsection BLOX.BDropDown:@- callbacks @table @b @meindex callback @item callback Answer a DirectedMessage that is sent when the receiver is clicked, or nil if none has been set up. @meindex callback:@-message:@- @item callback:@- aReceiver message:@- aSymbol Set up so that aReceiver is sent the aSymbol message (the name of a zero- or one-argument selector) when the receiver is clicked. If the method accepts an argument, the receiver is passed. @meindex invokeCallback @item invokeCallback Generate a synthetic callback @end table @node BLOX.BDropDown-flexibility @subsection BLOX.BDropDown:@- flexibility @table @b @meindex createList @item createList Create the popup widget to be used for the `drop-down list'. It is a BList by default, but you can use any other widget, overriding the `list box accessing' methods if necessary. @meindex createTextWidget @item createTextWidget Create the widget that will hold the string chosen from the list box and answer it. The widget must be a child of `self primitive'. @meindex itemHeight @slindex font @item itemHeight Answer the height of an item in the drop-down list. The default implementation assumes that the receiver understands #font, but you can modify it if you want. @meindex listCallback @item listCallback Called when an item of the listbox is highlighted. Do nothing by default @meindex listSelectAt:@- @item listSelectAt:@- aPoint Select the item lying at the given position in the list box. The default implementation assumes that list is a BList, but you can modify it if you want. @meindex listText @item listText Answer the text currently chosen in the list box. The default implementation assumes that list is a BList, but you can modify it if you want. @meindex text @item text Answer the text that the user has picked from the widget and/or typed in the control (the exact way the text is entered will be established by subclasses, since this is an abstract method). @meindex text:@- @item text:@- aString Set the text widget to aString @end table @node BLOX.BDropDown-list box accessing @subsection BLOX.BDropDown:@- list box accessing @table @b @meindex add:@-afterIndex:@- @item add:@- anObject afterIndex:@- index Add an element with the given value after another element whose index is contained in the index parameter. The label displayed in the widget is anObject's displayString. Answer anObject. @meindex add:@-element:@-afterIndex:@- @item add:@- aString element:@- anObject afterIndex:@- index Add an element with the aString label after another element whose index is contained in the index parameter. This method allows the client to decide autonomously the label that the widget will display. If anObject is nil, then string is used as the element as well. If aString is nil, then the element's displayString is used as the label. Answer anObject or, if it is nil, aString. @meindex addLast:@- @item addLast:@- anObject Add an element with the given value at the end of the listbox. The label displayed in the widget is anObject's displayString. Answer anObject. @meindex addLast:@-element:@- @item addLast:@- aString element:@- anObject Add an element with the given value at the end of the listbox. This method allows the client to decide autonomously the label that the widget will display. If anObject is nil, then string is used as the element as well. If aString is nil, then the element's displayString is used as the label. Answer anObject or, if it is nil, aString. @meindex associationAt:@- @item associationAt:@- anIndex Answer an association whose key is the item at the given position in the listbox and whose value is the label used to display that item. @meindex at:@- @item at:@- anIndex Answer the element displayed at the given position in the list box. @meindex contents:@- @item contents:@- stringCollection Set the elements displayed in the listbox, and set the labels to be their displayStrings. @meindex contents:@-elements:@- @item contents:@- stringCollection elements:@- elementList Set the elements displayed in the listbox to be those in elementList, and set the labels to be the corresponding elements in stringCollection. The two collections must have the same size. @meindex do:@- @item do:@- aBlock Iterate over each element of the listbox and pass it to aBlock. @meindex elements:@- @item elements:@- elementList Set the elements displayed in the listbox, and set the labels to be their displayStrings. @meindex index:@- @item index:@- newIndex Highlight the item at the given position in the listbox, and transfer the text in the list box to the text widget. @meindex labelAt:@- @item labelAt:@- anIndex Answer the label displayed at the given position in the list box. @meindex labelsDo:@- @item labelsDo:@- aBlock Iterate over the labels in the list widget and pass each of them to aBlock. @meindex numberOfStrings @item numberOfStrings Answer the number of items in the list box @meindex removeAtIndex:@- @slindex at:@- @item removeAtIndex:@- index Remove the item at the given index in the list box, answering the object associated to the element (i.e. the value that #at:@- would have returned for the given index) @meindex size @item size Answer the number of items in the list box @end table @node BLOX.BDropDown-widget protocol @subsection BLOX.BDropDown:@- widget protocol @table @b @meindex dropRectangle @item dropRectangle Answer the rectangle in which the list widget will pop-up. If possible, this is situated below the drop-down widget's bottom side, but if the screen space there is not enough it could be above the drop-down widget's above side. If there is no screen space above as well, we pick the side where we can offer the greatest number of lines in the pop-up widget. @meindex dropdown @item dropdown Force the pop-up list widget to be visible. @meindex isDropdownVisible @item isDropdownVisible Answer whether the pop-up widget is visible @meindex toggle @item toggle Toggle the visibility of the pop-up widget. @meindex unmapList @item unmapList Unmap the pop-up widget from the screen, transfer its selected item to the always visible text widget, and generate a callback. @end table @node BLOX.BDropDownEdit @section BLOX.BDropDownEdit @clindex BLOX.BDropDownEdit @table @b @item Defined in namespace BLOX @itemx Superclass: BLOX.BDropDown @itemx Category: Graphics-Examples This class resembles an edit widget, but it has an arrow button that allows the user to pick an item from a pre-built list. @end table @menu * BLOX.BDropDownEdit-accessing:: (instance) * BLOX.BDropDownEdit-accessing-overrides:: (instance) * BLOX.BDropDownEdit-text accessing:: (instance) @end menu @node BLOX.BDropDownEdit-accessing @subsection BLOX.BDropDownEdit:@- accessing @table @b @meindex backgroundColor:@- @item backgroundColor:@- aColor Set the value of the backgroundColor option for the widget. Specifies the normal background color to use when displaying the widget. @meindex font:@- @item font:@- aString Set the value of the font option for the widget. Specifies the font to use when drawing text inside the widget. The font can be given as either an X font name or a Blox font description string. X font names are given as many fields, each led by a minus, and each of which can be replaced by an * to indicate a default value is ok:@- foundry, family, weight, slant, setwidth, addstyle, pixel size, point size (the same as pixel size for historical reasons), horizontal resolution, vertical resolution, spacing, width, charset and character encoding. Blox font description strings have three fields, which must be separated by a space and of which only the first is mandatory:@- the font family, the font size in points (or in pixels if a negative value is supplied), and a number of styles separated by a space (valid styles are normal, bold, italic, underline and overstrike). Examples of valid fonts are ``Helvetica 10 Bold'', ``Times -14'', ``Futura Bold Underline''. You must enclose the font family in braces if it is made of two or more words. @meindex foregroundColor:@- @item foregroundColor:@- aColor Set the value of the foregroundColor option for the widget. Specifies the normal foreground color to use when displaying the widget. @meindex highlightBackground:@- @item highlightBackground:@- aColor Set the value of the highlightBackground option for the widget. Specifies the background color to use when displaying selected items in the list widget and the selection in the text widget. @meindex highlightForeground:@- @item highlightForeground:@- aColor Set the value of the highlightBackground option for the widget. Specifies the background color to use when displaying selected items in the list widget and the selection in the text widget. @end table @node BLOX.BDropDownEdit-accessing-overrides @subsection BLOX.BDropDownEdit:@- accessing-overrides @table @b @meindex text @item text Answer the text shown in the widget @end table @node BLOX.BDropDownEdit-text accessing @subsection BLOX.BDropDownEdit:@- text accessing @table @b @meindex insertAtEnd:@- @item insertAtEnd:@- aString Clear the selection and append aString at the end of the text widget. @meindex replaceSelection:@- @item replaceSelection:@- aString Insert aString in the text widget at the current insertion point, replacing the currently selected text (if any), and leaving the text selected. @meindex selectAll @item selectAll Select the whole contents of the text widget @meindex selectFrom:@-to:@- @item selectFrom:@- first to:@- last Sets the selection of the text widget to include the characters starting with the one indexed by first (the very first character in the widget having index 1) and ending with the one just before last. If last refers to the same character as first or an earlier one, then the text widget's selection is cleared. @meindex selection @item selection Answer an empty string if the text widget has no selection, else answer the currently selected text @meindex selectionRange @item selectionRange Answer nil if the text widget has no selection, else answer an Interval object whose first item is the index of the first character in the selection, and whose last item is the index of the character just after the last one in the selection. @meindex text:@- @item text:@- aString Set the contents of the text widget and select them. @end table @node BLOX.BDropDownList @section BLOX.BDropDownList @clindex BLOX.BDropDownList @table @b @item Defined in namespace BLOX @itemx Superclass: BLOX.BDropDown @itemx Category: Graphics-Examples This class resembles a list box widget, but its actual list shows up only when you click the arrow button beside the currently selected item. @end table @menu * BLOX.BDropDownList-accessing:: (instance) * BLOX.BDropDownList-callbacks:: (instance) * BLOX.BDropDownList-list box accessing:: (instance) @end menu @node BLOX.BDropDownList-accessing @subsection BLOX.BDropDownList:@- accessing @table @b @meindex backgroundColor:@- @item backgroundColor:@- aColor Set the value of the backgroundColor for the widget, which in this class is set for the list widget and, when the focus is outside the control, for the text widget as well. Specifies the normal background color to use when displaying the widget. @meindex font:@- @item font:@- aString Set the value of the font option for the widget. Specifies the font to use when drawing text inside the widget. The font can be given as either an X font name or a Blox font description string. X font names are given as many fields, each led by a minus, and each of which can be replaced by an * to indicate a default value is ok:@- foundry, family, weight, slant, setwidth, addstyle, pixel size, point size (the same as pixel size for historical reasons), horizontal resolution, vertical resolution, spacing, width, charset and character encoding. Blox font description strings have three fields, which must be separated by a space and of which only the first is mandatory:@- the font family, the font size in points (or in pixels if a negative value is supplied), and a number of styles separated by a space (valid styles are normal, bold, italic, underline and overstrike). Examples of valid fonts are ``Helvetica 10 Bold'', ``Times -14'', ``Futura Bold Underline''. You must enclose the font family in braces if it is made of two or more words. @meindex foregroundColor:@- @item foregroundColor:@- aColor Set the value of the foregroundColor for the widget, which in this class is set for the list widget and, when the focus is outside the control, for the text widget as well. Specifies the normal foreground color to use when displaying the widget. @meindex highlightBackground:@- @item highlightBackground:@- aColor Answer the value of the highlightBackground option for the widget. Specifies the background color to use when displaying selected items in the list widget and, when the focus is inside the control, for the text widget as well. @meindex highlightForeground:@- @item highlightForeground:@- aColor Answer the value of the highlightForeground option for the widget. Specifies the foreground color to use when displaying selected items in the list widget and, when the focus is inside the control, for the text widget as well. @meindex text @item text Answer the text that the user has picked from the widget and/or typed in the control (the exact way the text is entered will be established by subclasses, since this is an abstract method). @end table @node BLOX.BDropDownList-callbacks @subsection BLOX.BDropDownList:@- callbacks @table @b @meindex callback:@-message:@- @item callback:@- aReceiver message:@- aSymbol Set up so that aReceiver is sent the aSymbol message (the name of a selector with at most two arguemtnts) when the active item in the receiver changegs. If the method accepts two arguments, the receiver is passed as the first parameter. If the method accepts one or two arguments, the selected index is passed as the last parameter. @meindex invokeCallback @item invokeCallback Generate a synthetic callback. @end table @node BLOX.BDropDownList-list box accessing @subsection BLOX.BDropDownList:@- list box accessing @table @b @meindex index @item index Answer the value of the index option for the widget. Since it is not possible to modify an item once it has been picked from the list widget, this is always defined for BDropDownList widgets. @end table @node BLOX.BEdit @section BLOX.BEdit @clindex BLOX.BEdit @table @b @item Defined in namespace BLOX @itemx Superclass: BLOX.BPrimitive @itemx Category: Graphics-Windows I am a widget showing one line of modifiable text. @end table @menu * BLOX.BEdit class-instance creation:: (class) * BLOX.BEdit-accessing:: (instance) * BLOX.BEdit-widget protocol:: (instance) @end menu @node BLOX.BEdit class-instance creation @subsection BLOX.BEdit class:@- instance creation @table @b @meindex new:@-contents:@- @item new:@- parent contents:@- aString Answer a new BEdit widget laid inside the given parent widget, with a default content of aString @end table @node BLOX.BEdit-accessing @subsection BLOX.BEdit:@- accessing @table @b @meindex backgroundColor @item backgroundColor Answer the value of the backgroundColor option for the widget. Specifies the normal background color to use when displaying the widget. @meindex backgroundColor:@- @item backgroundColor:@- value Set the value of the backgroundColor option for the widget. Specifies the normal background color to use when displaying the widget. @meindex callback @item callback Answer a DirectedMessage that is sent when the receiver is modified, or nil if none has been set up. @meindex callback:@-message:@- @item callback:@- aReceiver message:@- aSymbol Set up so that aReceiver is sent the aSymbol message (the name of a zero- or one-argument selector) when the receiver is modified. If the method accepts an argument, the receiver is passed. @meindex contents @item contents Return the contents of the widget @meindex contents:@- @item contents:@- newText Set the contents of the widget @meindex font @item font Answer the value of the font option for the widget. Specifies the font to use when drawing text inside the widget. The font can be given as either an X font name or a Blox font description string. X font names are given as many fields, each led by a minus, and each of which can be replaced by an * to indicate a default value is ok:@- foundry, family, weight, slant, setwidth, addstyle, pixel size, point size (the same as pixel size for historical reasons), horizontal resolution, vertical resolution, spacing, width, charset and character encoding. Blox font description strings have three fields, which must be separated by a space and of which only the first is mandatory:@- the font family, the font size in points (or in pixels if a negative value is supplied), and a number of styles separated by a space (valid styles are normal, bold, italic, underline and overstrike). Examples of valid fonts are ``Helvetica 10 Bold'', ``Times -14'', ``Futura Bold Underline''. You must enclose the font family in braces if it is made of two or more words. @meindex font:@- @item font:@- value Set the value of the font option for the widget. Specifies the font to use when drawing text inside the widget. The font can be given as either an X font name or a Blox font description string. X font names are given as many fields, each led by a minus, and each of which can be replaced by an * to indicate a default value is ok:@- foundry, family, weight, slant, setwidth, addstyle, pixel size, point size (the same as pixel size for historical reasons), horizontal resolution, vertical resolution, spacing, width, charset and character encoding. Blox font description strings have three fields, which must be separated by a space and of which only the first is mandatory:@- the font family, the font size in points (or in pixels if a negative value is supplied), and a number of styles separated by a space (valid styles are normal, bold, italic, underline and overstrike). Examples of valid fonts are ``Helvetica 10 Bold'', ``Times -14'', ``Futura Bold Underline''. You must enclose the font family in braces if it is made of two or more words. @meindex foregroundColor @item foregroundColor Answer the value of the foregroundColor option for the widget. Specifies the normal foreground color to use when displaying the widget. @meindex foregroundColor:@- @item foregroundColor:@- value Set the value of the foregroundColor option for the widget. Specifies the normal foreground color to use when displaying the widget. @meindex selectBackground @item selectBackground Answer the value of the selectBackground option for the widget. Specifies the background color to use when displaying selected parts of the widget. @meindex selectBackground:@- @item selectBackground:@- value Set the value of the selectBackground option for the widget. Specifies the background color to use when displaying selected parts of the widget. @meindex selectForeground @item selectForeground Answer the value of the selectForeground option for the widget. Specifies the foreground color to use when displaying selected parts of the widget. @meindex selectForeground:@- @item selectForeground:@- value Set the value of the selectForeground option for the widget. Specifies the foreground color to use when displaying selected parts of the widget. @end table @node BLOX.BEdit-widget protocol @subsection BLOX.BEdit:@- widget protocol @table @b @meindex destroyed @item destroyed Private - The receiver has been destroyed, clear the corresponding Tcl variable to avoid memory leaks. @meindex hasSelection @item hasSelection Answer whether there is selected text in the widget @meindex insertAtEnd:@- @item insertAtEnd:@- aString Clear the selection and append aString at the end of the widget. @meindex insertText:@- @item insertText:@- aString Insert aString in the widget at the current insertion point, replacing the currently selected text (if any). @meindex invokeCallback @item invokeCallback Generate a synthetic callback. @meindex nextPut:@- @item nextPut:@- aCharacter Clear the selection and append aCharacter at the end of the widget. @meindex nextPutAll:@- @item nextPutAll:@- aString Clear the selection and append aString at the end of the widget. @meindex nl @item nl Clear the selection and append a linefeed character at the end of the widget. @meindex replaceSelection:@- @item replaceSelection:@- aString Insert aString in the widget at the current insertion point, replacing the currently selected text (if any), and leaving the text selected. @meindex selectAll @item selectAll Select the whole contents of the widget. @meindex selectFrom:@-to:@- @item selectFrom:@- first to:@- last Sets the selection to include the characters starting with the one indexed by first (the very first character in the widget having index 1) and ending with the one just before last. If last refers to the same character as first or an earlier one, then the widget's selection is cleared. @meindex selection @item selection Answer an empty string if the widget has no selection, else answer the currently selected text @meindex selectionRange @item selectionRange Answer nil if the widget has no selection, else answer an Interval object whose first item is the index of the first character in the selection, and whose last item is the index of the character just after the last one in the selection. @meindex space @item space Clear the selection and append a space at the end of the widget. @end table @node BLOX.BEmbeddedImage @section BLOX.BEmbeddedImage @clindex BLOX.BEmbeddedImage @table @b @item Defined in namespace BLOX @itemx Superclass: BLOX.BBoundingBox @itemx Category: Graphics-Windows I can draw a colorful image inside the canvas. @end table @menu * BLOX.BEmbeddedImage-accessing:: (instance) @end menu @node BLOX.BEmbeddedImage-accessing @subsection BLOX.BEmbeddedImage:@- accessing @table @b @meindex copyInto:@- @item copyInto:@- aBlox Answer a new BCanvasObject identical to this but displayed into another canvas, newCanvas. The new instance is not created at the time it is returned. @meindex data @item data Answer the data of the image. The result will be a String containing image data either as Base-64 encoded GIF data, as XPM data, or as PPM data. @meindex data:@- @item data:@- aString Set the data of the image. aString may contain the data either as Base-64 encoded GIF data, as XPM data, or as PPM data. No changes are visible until you toggle a redraw using the appropriate method. @meindex redraw @item redraw Force the object to be displayed in the parent canvas, creating it if it has not been inserted for real in the parent, and refresh its position and image data if it has changed. @end table @node BLOX.BEmbeddedText @section BLOX.BEmbeddedText @clindex BLOX.BEmbeddedText @table @b @item Defined in namespace BLOX @itemx Superclass: BLOX.BBoundingBox @itemx Category: Graphics-Windows I can draw text in all sorts of colors, sizes and fonts. @end table @menu * BLOX.BEmbeddedText-accessing:: (instance) @end menu @node BLOX.BEmbeddedText-accessing @subsection BLOX.BEmbeddedText:@- accessing @table @b @meindex font @item font Answer the value of the font option for the canvas object. Specifies the font to use when drawing text inside the widget. The font can be given as either an X font name or a Blox font description string. X font names are given as many fields, each led by a minus, and each of which can be replaced by an * to indicate a default value is ok:@- foundry, family, weight, slant, setwidth, addstyle, pixel size, point size (the same as pixel size for historical reasons), horizontal resolution, vertical resolution, spacing, width, charset and character encoding. Blox font description strings have three fields, which must be separated by a space and of which only the first is mandatory:@- the font family, the font size in points (or in pixels if a negative value is supplied), and a number of styles separated by a space (valid styles are normal, bold, italic, underline and overstrike). Examples of valid fonts are ``Helvetica 10 Bold'', ``Times -14'', ``Futura Bold Underline''. You must enclose the font family in braces if it is made of two or more words. @meindex font:@- @item font:@- font Set the value of the font option for the canvas object. Specifies the font to use when drawing text inside the widget. The font can be given as either an X font name or a Blox font description string. X font names are given as many fields, each led by a minus, and each of which can be replaced by an * to indicate a default value is ok:@- foundry, family, weight, slant, setwidth, addstyle, pixel size, point size (the same as pixel size for historical reasons), horizontal resolution, vertical resolution, spacing, width, charset and character encoding. Blox font description strings have three fields, which must be separated by a space and of which only the first is mandatory:@- the font family, the font size in points (or in pixels if a negative value is supplied), and a number of styles separated by a space (valid styles are normal, bold, italic, underline and overstrike). Examples of valid fonts are ``Helvetica 10 Bold'', ``Times -14'', ``Futura Bold Underline''. You must enclose the font family in braces if it is made of two or more words. @meindex justify @item justify Answer how to justify the text within its bounding region. @meindex justify:@- @slindex left @slindex right @slindex center @item justify:@- aSymbol Sets how to justify the text within its bounding region. Can be #left, #right or #center (the default). @meindex redraw @item redraw Force the object to be displayed in the parent canvas, creating it if it has not been inserted for real in the parent, and refresh its position. @meindex text @item text Answer the text that is printed by the object @meindex text:@- @item text:@- aString Set the text that is printed by the object @end table @node BLOX.BEventSet @section BLOX.BEventSet @clindex BLOX.BEventSet @table @b @item Defined in namespace BLOX @itemx Superclass: BLOX.BEventTarget @itemx Category: Graphics-Windows I combine event handlers and let you apply them to many objects. Basically, you derive a class from me, override the #initialize:@- method to establish the handlers, then use the #addEventSet:@- method understood by every Blox class to add the event handlers specified by the receiver to the object. @end table @menu * BLOX.BEventSet class-initializing:: (class) * BLOX.BEventSet-accessing:: (instance) * BLOX.BEventSet-initializing:: (instance) @end menu @node BLOX.BEventSet class-initializing @subsection BLOX.BEventSet class:@- initializing @table @b @meindex new @item new This method should not be called for instances of this class. @meindex new:@- @slindex addEventSet:@- @item new:@- widget Private - Create a new event set object that will attach to the given widget. Answer the object. Note:@- this method should be called by #addEventSet:@-, not directly @end table @node BLOX.BEventSet-accessing @subsection BLOX.BEventSet:@- accessing @table @b @meindex widget @item widget Answer the widget to which the receiver is attached. @end table @node BLOX.BEventSet-initializing @subsection BLOX.BEventSet:@- initializing @table @b @meindex initialize:@- @item initialize:@- aBWidget Initialize the receiver's event handlers to attach to aBWidget. You can override this of course, but don't forget to call the superclass implementation first. @end table @node BLOX.BEventTarget @section BLOX.BEventTarget @clindex BLOX.BEventTarget @table @b @item Defined in namespace BLOX @itemx Superclass: Object @itemx Category: Graphics-Windows I track all the event handling procedures that you apply to an object. @end table @menu * BLOX.BEventTarget-intercepting events:: (instance) @end menu @node BLOX.BEventTarget-intercepting events @subsection BLOX.BEventTarget:@- intercepting events @table @b @meindex addEventSet:@- @item addEventSet:@- aBEventSetSublass Add to the receiver the event handlers implemented by an instance of aBEventSetSubclass. Answer the new instance of aBEventSetSublass. @meindex onAsciiKeyEventSend:@-to:@- @item onAsciiKeyEventSend:@- aSelector to:@- anObject When an ASCII key is pressed and the receiver has the focus, send the 1-argument message identified by aSelector to anObject, passing to it a Character. @meindex onDestroySend:@-to:@- @item onDestroySend:@- aSelector to:@- anObject When the receiver is destroyed, send the unary message identified by aSelector to anObject. @meindex onFocusEnterEventSend:@-to:@- @item onFocusEnterEventSend:@- aSelector to:@- anObject When the focus enters the receiver, send the unary message identified by aSelector to anObject. @meindex onFocusLeaveEventSend:@-to:@- @item onFocusLeaveEventSend:@- aSelector to:@- anObject When the focus leaves the receiver, send the unary message identified by aSelector to anObject. @meindex onKeyEvent:@-send:@-to:@- @item onKeyEvent:@- key send:@- aSelector to:@- anObject When the given key is pressed and the receiver has the focus, send the unary message identified by aSelector to anObject. Examples for key are:@- 'Ctrl-1', 'Alt-X', 'Meta-plus', 'enter'. The last two cases include example of special key identifiers; these include:@- 'backslash', 'exclam', 'quotedbl', 'dollar', 'asterisk', 'less', 'greater', 'asciicircum' (caret), 'question', 'equal', 'parenleft', 'parenright', 'colon', 'semicolon', 'bar' (pipe sign), 'underscore', 'percent', 'minus', 'plus', 'BackSpace', 'Delete', 'Insert', 'Return', 'End', 'Home', 'Prior' (Pgup), 'Next' (Pgdn), 'F1'..'F24', 'Caps_Lock', 'Num_Lock', 'Tab', 'Left', 'Right', 'Up', 'Down'. There are in addition four special identifiers which map to platform-specific keys:@- '', '', '', '' (all with the angular brackets!). @meindex onKeyEventSend:@-to:@- @slindex onKeyEvent:@-send:@-to:@- @slindex eventTest @item onKeyEventSend:@- aSelector to:@- anObject When a key is pressed and the receiver has the focus, send the 1-argument message identified by aSelector to anObject. The pressed key will be passed as a String parameter; some of the keys will send special key identifiers such as those explained in the documentation for #onKeyEvent:@-send:@-to:@- Look at the #eventTest test program in the BloxTestSuite to find out the parameters passed to such an event procedure @meindex onKeyUpEventSend:@-to:@- @slindex onKeyEvent:@-send:@-to:@- @slindex eventTest @item onKeyUpEventSend:@- aSelector to:@- anObject When a key has been released and the receiver has the focus, send the 1-argument message identified by aSelector to anObject. The released key will be passed as a String parameter; some of the keys will send special key identifiers such as those explained in the documentation for #onKeyEvent:@-send:@-to:@- Look at the #eventTest test program in the BloxTestSuite to find out the parameters passed to such an event procedure @meindex onMouseDoubleEvent:@-send:@-to:@- @item onMouseDoubleEvent:@- button send:@- aSelector to:@- anObject When the given button is double-clicked on the mouse, send the 1-argument message identified by aSelector to anObject. The mouse position will be passed as a Point. @meindex onMouseDoubleEventSend:@-to:@- @item onMouseDoubleEventSend:@- aSelector to:@- anObject When a button is double-clicked on the mouse, send the 2-argument message identified by aSelector to anObject. The mouse position will be passed as a Point in the first parameter, the button number will be passed as an Integer in the second parameter. @meindex onMouseDownEvent:@-send:@-to:@- @item onMouseDownEvent:@- button send:@- aSelector to:@- anObject When the given button is pressed on the mouse, send the 1-argument message identified by aSelector to anObject. The mouse position will be passed as a Point. @meindex onMouseDownEventSend:@-to:@- @item onMouseDownEventSend:@- aSelector to:@- anObject When a button is pressed on the mouse, send the 2-argument message identified by aSelector to anObject. The mouse position will be passed as a Point in the first parameter, the button number will be passed as an Integer in the second parameter. @meindex onMouseEnterEventSend:@-to:@- @item onMouseEnterEventSend:@- aSelector to:@- anObject When the mouse enters the widget, send the unary message identified by aSelector to anObject. @meindex onMouseLeaveEventSend:@-to:@- @item onMouseLeaveEventSend:@- aSelector to:@- anObject When the mouse leaves the widget, send the unary message identified by aSelector to anObject. @meindex onMouseMoveEvent:@-send:@-to:@- @item onMouseMoveEvent:@- button send:@- aSelector to:@- anObject When the mouse is moved while the given button is pressed on the mouse, send the 1-argument message identified by aSelector to anObject. The mouse position will be passed as a Point. @meindex onMouseMoveEventSend:@-to:@- @item onMouseMoveEventSend:@- aSelector to:@- anObject When the mouse is moved, send the 1-argument message identified by aSelector to anObject. The mouse position will be passed as a Point. @meindex onMouseTripleEvent:@-send:@-to:@- @item onMouseTripleEvent:@- button send:@- aSelector to:@- anObject When the given button is triple-clicked on the mouse, send the 1-argument message identified by aSelector to anObject. The mouse position will be passed as a Point. @meindex onMouseTripleEventSend:@-to:@- @item onMouseTripleEventSend:@- aSelector to:@- anObject When a button is triple-clicked on the mouse, send the 2-argument message identified by aSelector to anObject. The mouse position will be passed as a Point in the first parameter, the button number will be passed as an Integer in the second parameter. @meindex onMouseUpEvent:@-send:@-to:@- @item onMouseUpEvent:@- button send:@- aSelector to:@- anObject When the given button is released on the mouse, send the 1-argument message identified by aSelector to anObject. The mouse position will be passed as a Point. @meindex onMouseUpEventSend:@-to:@- @item onMouseUpEventSend:@- aSelector to:@- anObject When a button is released on the mouse, send the 2-argument message identified by aSelector to anObject. The mouse position will be passed as a Point in the first parameter, the button number will be passed as an Integer in the second parameter. @meindex onResizeSend:@-to:@- @item onResizeSend:@- aSelector to:@- anObject When the receiver is resized, send the 1-argument message identified by aSelector to anObject. The new size will be passed as a Point. @end table @node BLOX.BExtended @section BLOX.BExtended @clindex BLOX.BExtended @table @b @item Defined in namespace BLOX @itemx Superclass: BLOX.BWidget @itemx Category: Graphics-Windows Just like Gui, I serve as a base for complex objects which expose an individual protocol but internally use a Blox widget for creating their user interface. Unlike Gui, however, the instances of my subclasses understand the standard widget protocol. Just override my newPrimitive method to return another widget, and you'll get a class which interacts with the user like that widget (a list box, a text box, or even a label) but exposes a different protocol. @end table @menu * BLOX.BExtended-accessing:: (instance) * BLOX.BExtended-customization:: (instance) @end menu @node BLOX.BExtended-accessing @subsection BLOX.BExtended:@- accessing @table @b @meindex asPrimitiveWidget @item asPrimitiveWidget Answer the primitive widget that implements the receiver. @end table @node BLOX.BExtended-customization @subsection BLOX.BExtended:@- customization @table @b @meindex create @slindex newPrimitive @slindex create @slindex newPrimitive @item create After this method is called (the call is made automatically) the receiver will be attached to a `primitive' widget (which can be in turn another extended widget). This method is public not because you can call it, but because it can be useful to override it, not forgetting the call to super (which only calls #newPrimitive and saves the result), to perform some initialization on the primitive widget just created; overriding #create is in fact more generic than overriding #newPrimitive. For an example of this, see the implementation of BButtonLike. @meindex newPrimitive @item newPrimitive Create and answer a new widget on which the implementation of the receiver will be based. You should not call this method directly; instead you must override it in BExtended's subclasses. @end table @node BLOX.BForm @section BLOX.BForm @clindex BLOX.BForm @table @b @item Defined in namespace BLOX @itemx Superclass: BLOX.BPrimitive @itemx Category: Graphics-Windows I am used to group many widgets together. I leave the heavy task of managing their position to the user. @end table @menu * BLOX.BForm-accessing:: (instance) @end menu @node BLOX.BForm-accessing @subsection BLOX.BForm:@- accessing @table @b @meindex backgroundColor @item backgroundColor Answer the value of the backgroundColor option for the widget. Specifies the normal background color to use when displaying the widget. @meindex backgroundColor:@- @item backgroundColor:@- value Set the value of the backgroundColor option for the widget. Specifies the normal background color to use when displaying the widget. @meindex defaultHeight @item defaultHeight Answer the value of the defaultHeight option for the widget. Specifies the desired height for the form in pixels. If this option is less than or equal to zero then the window will not request any size at all. @meindex defaultHeight:@- @item defaultHeight:@- value Set the value of the defaultHeight option for the widget. Specifies the desired height for the form in pixels. If this option is less than or equal to zero then the window will not request any size at all. @meindex defaultWidth @item defaultWidth Answer the value of the defaultWidth option for the widget. Specifies the desired width for the form in pixels. If this option is less than or equal to zero then the window will not request any size at all. @meindex defaultWidth:@- @item defaultWidth:@- value Set the value of the defaultWidth option for the widget. Specifies the desired width for the form in pixels. If this option is less than or equal to zero then the window will not request any size at all. @end table @node BLOX.BImage @section BLOX.BImage @clindex BLOX.BImage @table @b @item Defined in namespace BLOX @itemx Superclass: BLOX.BPrimitive @itemx Category: Graphics-Windows I can display colorful images. @end table @menu * BLOX.BImage class-arrows:: (class) * BLOX.BImage class-GNU:: (class) * BLOX.BImage class-icons:: (class) * BLOX.BImage class-instance creation:: (class) * BLOX.BImage class-small icons:: (class) * BLOX.BImage-accessing:: (instance) * BLOX.BImage-image management:: (instance) * BLOX.BImage-widget protocol:: (instance) @end menu @node BLOX.BImage class-arrows @subsection BLOX.BImage class:@- arrows @table @b @meindex downArrow @item downArrow Answer the XPM representation of a 12x12 arrow pointing downwards. @meindex leftArrow @item leftArrow Answer the XPM representation of a 12x12 arrow pointing leftwards. @meindex rightArrow @item rightArrow Answer the XPM representation of a 12x12 arrow pointing rightwards. @meindex upArrow @item upArrow Answer the XPM representation of a 12x12 arrow pointing upwards. @end table @node BLOX.BImage class-GNU @subsection BLOX.BImage class:@- GNU @table @b @meindex gnu @item gnu Answer the XPM representation of a 48x48 GNU. @end table @node BLOX.BImage class-icons @subsection BLOX.BImage class:@- icons @table @b @meindex exclaim @item exclaim Answer the XPM representation of a 32x32 exclamation mark icon. @meindex info @item info Answer the XPM representation of a 32x32 `information' icon. @meindex question @item question Answer the XPM representation of a 32x32 question mark icon. @meindex stop @item stop Answer the XPM representation of a 32x32 `critical stop' icon. @end table @node BLOX.BImage class-instance creation @subsection BLOX.BImage class:@- instance creation @table @b @meindex new:@-data:@- @item new:@- parent data:@- aString Answer a new BImage widget laid inside the given parent widget, loading data from the given string (Base-64 encoded GIF, XPM, PPM are supported). @meindex new:@-image:@- @item new:@- parent image:@- aFileStream Answer a new BImage widget laid inside the given parent widget, loading data from the given file (GIF, XPM, PPM are supported). @meindex new:@-size:@- @item new:@- parent size:@- aPoint Answer a new BImage widget laid inside the given parent widget, showing by default a transparent image of aPoint size. @end table @node BLOX.BImage class-small icons @subsection BLOX.BImage class:@- small icons @table @b @meindex directory @item directory Answer the Base-64 GIF representation of a `directory folder' icon. @meindex file @item file Answer the Base-64 GIF representation of a `file' icon. @end table @node BLOX.BImage-accessing @subsection BLOX.BImage:@- accessing @table @b @meindex backgroundColor @item backgroundColor Answer the value of the backgroundColor option for the widget. Specifies the normal background color to use when displaying the widget. @meindex backgroundColor:@- @item backgroundColor:@- value Set the value of the backgroundColor option for the widget. Specifies the normal background color to use when displaying the widget. @meindex displayHeight @item displayHeight Answer the value of the displayHeight option for the widget. Specifies the height of the image in pixels. This is not the height of the widget, but specifies the area of the widget that will be taken by the image. @meindex displayHeight:@- @item displayHeight:@- value Set the value of the displayHeight option for the widget. Specifies the height of the image in pixels. This is not the height of the widget, but specifies the area of the widget that will be taken by the image. @meindex displayWidth @item displayWidth Answer the value of the displayWidth option for the widget. Specifies the width of the image in pixels. This is not the width of the widget, but specifies the area of the widget that will be taken by the image. @meindex displayWidth:@- @item displayWidth:@- value Set the value of the displayWidth option for the widget. Specifies the width of the image in pixels. This is not the width of the widget, but specifies the area of the widget that will be taken by the image. @meindex foregroundColor @item foregroundColor Answer the value of the foregroundColor option for the widget. Specifies the normal foreground color to use when displaying the widget. @meindex foregroundColor:@- @item foregroundColor:@- value Set the value of the foregroundColor option for the widget. Specifies the normal foreground color to use when displaying the widget. @meindex gamma @item gamma Answer the value of the gamma option for the widget. Specifies that the colors allocated for displaying the image widget should be corrected for a non-linear display with the specified gamma exponent value. (The intensity produced by most CRT displays is a power function of the input value, to a good approximation; gamma is the exponent and is typically around 2). The value specified must be greater than zero. The default value is one (no correction). In general, values greater than one will make the image lighter, and values less than one will make it darker. @meindex gamma:@- @item gamma:@- value Set the value of the gamma option for the widget. Specifies that the colors allocated for displaying the image widget should be corrected for a non-linear display with the specified gamma exponent value. (The intensity produced by most CRT displays is a power function of the input value, to a good approximation; gamma is the exponent and is typically around 2). The value specified must be greater than zero. The default value is one (no correction). In general, values greater than one will make the image lighter, and values less than one will make it darker. @end table @node BLOX.BImage-image management @subsection BLOX.BImage:@- image management @table @b @meindex blank @item blank Blank the corresponding image @meindex data:@- @item data:@- aString Set the image to be drawn to aString, which can be a GIF in Base-64 representation or an X pixelmap. @meindex dither @item dither Recalculate the dithered image in the window where the image is displayed. The dithering algorithm used in displaying images propagates quantization errors from one pixel to its neighbors. If the image data is supplied in pieces, the dithered image may not be exactly correct. Normally the difference is not noticeable, but if it is a problem, this command can be used to fix it. @meindex fillFrom:@-extent:@-color:@- @item fillFrom:@- origin extent:@- extent color:@- color Fill a rectangle with the given origin and extent, using the given color. @meindex fillFrom:@-to:@-color:@- @item fillFrom:@- origin to:@- corner color:@- color Fill a rectangle between the given corners, using the given color. @meindex fillRectangle:@-color:@- @item fillRectangle:@- rectangle color:@- color Fill a rectangle having the given bounding box, using the given color. @meindex image:@- @item image:@- aFileStream Read a GIF or XPM image from aFileStream. The whole contents of the file are read, not only from the file position. @meindex imageHeight @item imageHeight Specifies the height of the image, in pixels. This option is useful primarily in situations where you wish to build up the contents of the image piece by piece. A value of zero (the default) allows the image to expand or shrink vertically to fit the data stored in it. @meindex imageWidth @item imageWidth Specifies the width of the image, in pixels. This option is useful primarily in situations where you wish to build up the contents of the image piece by piece. A value of zero (the default) allows the image to expand or shrink horizontally to fit the data stored in it. @meindex lineFrom:@-extent:@-color:@- @item lineFrom:@- origin extent:@- extent color:@- color Draw a line with the given origin and extent, using the given color. @meindex lineFrom:@-to:@-color:@- @item lineFrom:@- origin to:@- corner color:@- color This method's functionality has not been implemented yet. @meindex lineFrom:@-toX:@-color:@- @item lineFrom:@- origin toX:@- endX color:@- color Draw an horizontal line between the given corners, using the given color. @meindex lineFrom:@-toY:@-color:@- @item lineFrom:@- origin toY:@- endY color:@- color Draw a vertical line between the given corners, using the given color. @meindex lineInside:@-color:@- @item lineInside:@- rectangle color:@- color Draw a line having the given bounding box, using the given color. @end table @node BLOX.BImage-widget protocol @subsection BLOX.BImage:@- widget protocol @table @b @meindex destroyed @item destroyed Private - The receiver has been destroyed, clear the corresponding Tcl image to avoid memory leaks. @end table @node BLOX.BLabel @section BLOX.BLabel @clindex BLOX.BLabel @table @b @item Defined in namespace BLOX @itemx Superclass: BLOX.BPrimitive @itemx Category: Graphics-Windows I am a label showing static text. @end table @menu * BLOX.BLabel class-initialization:: (class) * BLOX.BLabel class-instance creation:: (class) * BLOX.BLabel-accessing:: (instance) @end menu @node BLOX.BLabel class-initialization @subsection BLOX.BLabel class:@- initialization @table @b @meindex initialize @item initialize Private - Initialize the receiver's class variables. @end table @node BLOX.BLabel class-instance creation @subsection BLOX.BLabel class:@- instance creation @table @b @meindex new:@-label:@- @item new:@- parent label:@- label Answer a new BLabel widget laid inside the given parent widget, showing by default the `label' String. @end table @node BLOX.BLabel-accessing @subsection BLOX.BLabel:@- accessing @table @b @meindex alignment @slindex topLeft @slindex topCenter @slindex topRight @slindex leftCenter @slindex center @slindex rightCenter @slindex bottomLeft @slindex bottomCenter @slindex bottomRight @slindex topLeft @item alignment Answer the value of the anchor option for the widget. Specifies how the information in a widget (e.g. text or a bitmap) is to be displayed in the widget. Must be one of the symbols #topLeft, #topCenter, #topRight, #leftCenter, #center, #rightCenter, #bottomLeft, #bottomCenter, #bottomRight. For example, #topLeft means display the information such that its top-left corner is at the top-left corner of the widget. @meindex alignment:@- @slindex topLeft @slindex topCenter @slindex topRight @slindex leftCenter @slindex center @slindex rightCenter @slindex bottomLeft @slindex bottomCenter @slindex bottomRight @slindex topLeft @item alignment:@- aSymbol Set the value of the anchor option for the widget. Specifies how the information in a widget (e.g. text or a bitmap) is to be displayed in the widget. Must be one of the symbols #topLeft, #topCenter, #topRight, #leftCenter, #center, #rightCenter, #bottomLeft, #bottomCenter, #bottomRight. For example, #topLeft means display the information such that its top-left corner is at the top-left corner of the widget. @meindex backgroundColor @item backgroundColor Answer the value of the backgroundColor option for the widget. Specifies the normal background color to use when displaying the widget. @meindex backgroundColor:@- @item backgroundColor:@- value Set the value of the backgroundColor option for the widget. Specifies the normal background color to use when displaying the widget. @meindex font @item font Answer the value of the font option for the widget. Specifies the font to use when drawing text inside the widget. The font can be given as either an X font name or a Blox font description string. X font names are given as many fields, each led by a minus, and each of which can be replaced by an * to indicate a default value is ok:@- foundry, family, weight, slant, setwidth, addstyle, pixel size, point size (the same as pixel size for historical reasons), horizontal resolution, vertical resolution, spacing, width, charset and character encoding. Blox font description strings have three fields, which must be separated by a space and of which only the first is mandatory:@- the font family, the font size in points (or in pixels if a negative value is supplied), and a number of styles separated by a space (valid styles are normal, bold, italic, underline and overstrike). Examples of valid fonts are ``Helvetica 10 Bold'', ``Times -14'', ``Futura Bold Underline''. You must enclose the font family in braces if it is made of two or more words. @meindex font:@- @item font:@- value Set the value of the font option for the widget. Specifies the font to use when drawing text inside the widget. The font can be given as either an X font name or a Blox font description string. X font names are given as many fields, each led by a minus, and each of which can be replaced by an * to indicate a default value is ok:@- foundry, family, weight, slant, setwidth, addstyle, pixel size, point size (the same as pixel size for historical reasons), horizontal resolution, vertical resolution, spacing, width, charset and character encoding. Blox font description strings have three fields, which must be separated by a space and of which only the first is mandatory:@- the font family, the font size in points (or in pixels if a negative value is supplied), and a number of styles separated by a space (valid styles are normal, bold, italic, underline and overstrike). Examples of valid fonts are ``Helvetica 10 Bold'', ``Times -14'', ``Futura Bold Underline''. You must enclose the font family in braces if it is made of two or more words. @meindex foregroundColor @item foregroundColor Answer the value of the foregroundColor option for the widget. Specifies the normal foreground color to use when displaying the widget. @meindex foregroundColor:@- @item foregroundColor:@- value Set the value of the foregroundColor option for the widget. Specifies the normal foreground color to use when displaying the widget. @meindex label @item label Answer the value of the label option for the widget. Specifies a string to be displayed inside the widget. The way in which the string is displayed depends on the particular widget and may be determined by other options, such as anchor. For windows, this is the title of the window. @meindex label:@- @item label:@- value Set the value of the label option for the widget. Specifies a string to be displayed inside the widget. The way in which the string is displayed depends on the particular widget and may be determined by other options, such as anchor. For windows, this is the title of the window. @end table @node BLOX.BLine @section BLOX.BLine @clindex BLOX.BLine @table @b @item Defined in namespace BLOX @itemx Superclass: BLOX.BBoundingBox @itemx Category: Graphics-Windows I only draw straight lines but I can do that very well, even without a ruler... @end table @menu * BLOX.BLine-accessing:: (instance) @end menu @node BLOX.BLine-accessing @subsection BLOX.BLine:@- accessing @table @b @meindex cap @slindex butt @slindex projecting @slindex round @item cap Answer the way in which caps are to be drawn at the endpoints of the line. The answer may be #butt (the default), #projecting, or #round). @meindex cap:@- @slindex butt @slindex projecting @slindex round @item cap:@- aSymbol Set the way in which caps are to be drawn at the endpoints of the line. aSymbol may be #butt (the default), #projecting, or #round). @meindex width @item width Answer the width with which the line is drawn. @meindex width:@- @item width:@- pixels Set the width with which the line is drawn. @end table @node BLOX.BList @section BLOX.BList @clindex BLOX.BList @table @b @item Defined in namespace BLOX @itemx Superclass: BLOX.BViewport @itemx Category: Graphics-Windows I represent a list box from which you can choose one or more elements. @end table @menu * BLOX.BList-accessing:: (instance) * BLOX.BList-widget protocol:: (instance) @end menu @node BLOX.BList-accessing @subsection BLOX.BList:@- accessing @table @b @meindex add:@-afterIndex:@- @item add:@- anObject afterIndex:@- index Add an element with the given value after another element whose index is contained in the index parameter. The label displayed in the widget is anObject's displayString. Answer anObject. @meindex add:@-element:@-afterIndex:@- @item add:@- aString element:@- anObject afterIndex:@- index Add an element with the aString label after another element whose index is contained in the index parameter. This method allows the client to decide autonomously the label that the widget will display. If anObject is nil, then string is used as the element as well. If aString is nil, then the element's displayString is used as the label. Answer anObject or, if it is nil, aString. @meindex addLast:@- @item addLast:@- anObject Add an element with the given value at the end of the listbox. The label displayed in the widget is anObject's displayString. Answer anObject. @meindex addLast:@-element:@- @item addLast:@- aString element:@- anObject Add an element with the given value at the end of the listbox. This method allows the client to decide autonomously the label that the widget will display. If anObject is nil, then string is used as the element as well. If aString is nil, then the element's displayString is used as the label. Answer anObject or, if it is nil, aString. @meindex associationAt:@- @item associationAt:@- anIndex Answer an association whose key is the item at the given position in the listbox and whose value is the label used to display that item. @meindex at:@- @item at:@- anIndex Answer the element displayed at the given position in the list box. @meindex backgroundColor @item backgroundColor Answer the value of the backgroundColor option for the widget. Specifies the normal background color to use when displaying the widget. @meindex backgroundColor:@- @item backgroundColor:@- value Set the value of the backgroundColor option for the widget. Specifies the normal background color to use when displaying the widget. @meindex contents:@- @item contents:@- elementList Set the elements displayed in the listbox, and set the labels to be their displayStrings. @meindex contents:@-elements:@- @item contents:@- stringCollection elements:@- elementList Set the elements displayed in the listbox to be those in elementList, and set the labels to be the corresponding elements in stringCollection. The two collections must have the same size. @meindex do:@- @item do:@- aBlock Iterate over each element of the listbox and pass it to aBlock. @meindex elements @item elements Answer the collection of objects that represent the elements displayed by the list box. @meindex elements:@- @item elements:@- elementList Set the elements displayed in the listbox, and set the labels to be their displayStrings. @meindex font @item font Answer the value of the font option for the widget. Specifies the font to use when drawing text inside the widget. The font can be given as either an X font name or a Blox font description string. X font names are given as many fields, each led by a minus, and each of which can be replaced by an * to indicate a default value is ok:@- foundry, family, weight, slant, setwidth, addstyle, pixel size, point size (the same as pixel size for historical reasons), horizontal resolution, vertical resolution, spacing, width, charset and character encoding. Blox font description strings have three fields, which must be separated by a space and of which only the first is mandatory:@- the font family, the font size in points (or in pixels if a negative value is supplied), and a number of styles separated by a space (valid styles are normal, bold, italic, underline and overstrike). Examples of valid fonts are ``Helvetica 10 Bold'', ``Times -14'', ``Futura Bold Underline''. You must enclose the font family in braces if it is made of two or more words. @meindex font:@- @item font:@- value Set the value of the font option for the widget. Specifies the font to use when drawing text inside the widget. The font can be given as either an X font name or a Blox font description string. X font names are given as many fields, each led by a minus, and each of which can be replaced by an * to indicate a default value is ok:@- foundry, family, weight, slant, setwidth, addstyle, pixel size, point size (the same as pixel size for historical reasons), horizontal resolution, vertical resolution, spacing, width, charset and character encoding. Blox font description strings have three fields, which must be separated by a space and of which only the first is mandatory:@- the font family, the font size in points (or in pixels if a negative value is supplied), and a number of styles separated by a space (valid styles are normal, bold, italic, underline and overstrike). Examples of valid fonts are ``Helvetica 10 Bold'', ``Times -14'', ``Futura Bold Underline''. You must enclose the font family in braces if it is made of two or more words. @meindex foregroundColor @item foregroundColor Answer the value of the foregroundColor option for the widget. Specifies the normal foreground color to use when displaying the widget. @meindex foregroundColor:@- @item foregroundColor:@- value Set the value of the foregroundColor option for the widget. Specifies the normal foreground color to use when displaying the widget. @meindex highlightBackground @item highlightBackground Answer the value of the highlightBackground option for the widget. Specifies the background color to use when displaying selected items in the widget. @meindex highlightBackground:@- @item highlightBackground:@- value Set the value of the highlightBackground option for the widget. Specifies the background color to use when displaying selected items in the widget. @meindex highlightForeground @item highlightForeground Answer the value of the highlightForeground option for the widget. Specifies the foreground color to use when displaying selected items in the widget. @meindex highlightForeground:@- @item highlightForeground:@- value Set the value of the highlightForeground option for the widget. Specifies the foreground color to use when displaying selected items in the widget. @meindex index @item index Answer the value of the index option for the widget. Indicates the element that has the location cursor. This item will be displayed in the highlightForeground color, and with the corresponding background color. @meindex indexAt:@- @item indexAt:@- point Answer the index of the element that covers the point in the listbox window specified by x and y (in pixel coordinates). If no element covers that point, then the closest element to that point is used. @meindex isSelected:@- @item isSelected:@- index Answer whether the element indicated by index is currently selected. @meindex label @item label Return nil, it is here for Gtk+ support @meindex label:@- @item label:@- aString Do nothing, it is here for Gtk+ support @meindex labelAt:@- @item labelAt:@- anIndex Answer the label displayed at the given position in the list box. @meindex labels @item labels Answer the labels displayed by the list box. @meindex labelsDo:@- @item labelsDo:@- aBlock Iterate over each listbox element's label and pass it to aBlock. @meindex mode @item mode Answer the value of the mode option for the widget. Specifies one of several styles for manipulating the selection. The value of the option may be either single, browse, multiple, or extended. If the selection mode is single or browse, at most one element can be selected in the listbox at once. Clicking button 1 on an unselected element selects it and deselects any other selected item, while clicking on a selected element has no effect. In browse mode it is also possible to drag the selection with button 1. That is, moving the mouse while button 1 is pressed keeps the item under the cursor selected. If the selection mode is multiple or extended, any number of elements may be selected at once, including discontiguous ranges. In multiple mode, clicking button 1 on an element toggles its selection state without affecting any other elements. In extended mode, pressing button 1 on an element selects it, deselects everything else, and sets the anchor to the element under the mouse; dragging the mouse with button 1 down extends the selection to include all the elements between the anchor and the element under the mouse, inclusive. In extended mode, the selected range can be adjusted by pressing button 1 with the Shift key down:@- this modifies the selection to consist of the elements between the anchor and the element under the mouse, inclusive. The un-anchored end of this new selection can also be dragged with the button down. Also in extended mode, pressing button 1 with the Control key down starts a toggle operation:@- the anchor is set to the element under the mouse, and its selection state is reversed. The selection state of other elements is not changed. If the mouse is dragged with button 1 down, then the selection state of all elements between the anchor and the element under the mouse is set to match that of the anchor element; the selection state of all other elements remains what it was before the toggle operation began. Most people will probably want to use browse mode for single selections and extended mode for multiple selections; the other modes appear to be useful only in special situations. @meindex mode:@- @item mode:@- value Set the value of the mode option for the widget. Specifies one of several styles for manipulating the selection. The value of the option may be either single, browse, multiple, or extended. If the selection mode is single or browse, at most one element can be selected in the listbox at once. Clicking button 1 on an unselected element selects it and deselects any other selected item, while clicking on a selected element has no effect. In browse mode it is also possible to drag the selection with button 1. That is, moving the mouse while button 1 is pressed keeps the item under the cursor selected. If the selection mode is multiple or extended, any number of elements may be selected at once, including discontiguous ranges. In multiple mode, clicking button 1 on an element toggles its selection state without affecting any other elements. In extended mode, pressing button 1 on an element selects it, deselects everything else, and sets the anchor to the element under the mouse; dragging the mouse with button 1 down extends the selection to include all the elements between the anchor and the element under the mouse, inclusive. In extended mode, the selected range can be adjusted by pressing button 1 with the Shift key down:@- this modifies the selection to consist of the elements between the anchor and the element under the mouse, inclusive. The un-anchored end of this new selection can also be dragged with the button down. Also in extended mode, pressing button 1 with the Control key down starts a toggle operation:@- the anchor is set to the element under the mouse, and its selection state is reversed. The selection state of other elements is not changed. If the mouse is dragged with button 1 down, then the selection state of all elements between the anchor and the element under the mouse is set to match that of the anchor element; the selection state of all other elements remains what it was before the toggle operation began. Most people will probably want to use browse mode for single selections and extended mode for multiple selections; the other modes appear to be useful only in special situations. @meindex numberOfStrings @item numberOfStrings Answer the number of items in the list box @meindex removeAtIndex:@- @slindex at:@- @item removeAtIndex:@- index Remove the item at the given index in the list box, answering the object associated to the element (i.e. the value that #at:@- would have returned for the given index) @meindex size @item size Answer the number of items in the list box @end table @node BLOX.BList-widget protocol @subsection BLOX.BList:@- widget protocol @table @b @meindex callback @item callback Answer a DirectedMessage that is sent when the active item in the receiver changes, or nil if none has been set up. @meindex callback:@-message:@- @item callback:@- aReceiver message:@- aSymbol Set up so that aReceiver is sent the aSymbol message (the name of a selector with at most two arguemtnts) when the active item in the receiver changegs. If the method accepts two arguments, the receiver is passed as the first parameter. If the method accepts one or two arguments, the selected index is passed as the last parameter. @meindex highlight:@- @item highlight:@- index Highlight the item at the given position in the listbox. @meindex invokeCallback @item invokeCallback Generate a synthetic callback. @meindex select:@- @item select:@- index Highlight the item at the given position in the listbox, without unhighlighting other items. This is meant for multiple- or extended-mode listboxes, but can be used with other selection mode in particular cases. @meindex show:@- @item show:@- index Ensure that the item at the given position in the listbox is visible. @meindex unhighlight @item unhighlight Unhighlight all the items in the listbox. @meindex unselect:@- @item unselect:@- index Unhighlight the item at the given position in the listbox, without affecting the state of the other items. @end table @node BLOX.Blox @section BLOX.Blox @clindex BLOX.Blox @table @b @item Defined in namespace BLOX @itemx Superclass: BLOX.BEventTarget @itemx Category: Graphics-Windows I am the superclass for every visible user interface object (excluding canvas items, which are pretty different). I provide common methods and a simple Tcl interface for internal use. In addition, I expose class methods that do many interesting event-handling things. NOTE:@- some of the methods (notably geometry methods) may not be suitable for all Blox subclasses and may be included only for backwards compatibility towards 1.1.5 BLOX. You should use geometry methods only for subclasses of BWidget. @end table @menu * BLOX.Blox class-C call-outs:: (class) * BLOX.Blox class-event dispatching:: (class) * BLOX.Blox class-instance creation:: (class) * BLOX.Blox class-utility:: (class) * BLOX.Blox-accessing:: (instance) * BLOX.Blox-basic:: (instance) * BLOX.Blox-creating children:: (instance) * BLOX.Blox-customization:: (instance) * BLOX.Blox-widget protocol:: (instance) @end menu @node BLOX.Blox class-C call-outs @subsection BLOX.Blox class:@- C call-outs @table @b @meindex evalIn:@-tcl:@- @item evalIn:@- interp tcl:@- cmd Not commented. @meindex idle @item idle Not commented. @meindex resultIn:@- @item resultIn:@- interp Not commented. @meindex tclInit @item tclInit Not commented. @end table @node BLOX.Blox class-event dispatching @subsection BLOX.Blox class:@- event dispatching @table @b @meindex dispatchEvents @slindex terminateMainLoop @slindex dispatchEvents @item dispatchEvents If this is the outermost dispatching loop that is started, dispatch events until the number of calls to #terminateMainLoop balances the number of calls to #dispatchEvents; return instantly if this is not the outermost dispatching loop that is started. @meindex dispatchEvents:@- @item dispatchEvents:@- mainWindow Dispatch some events; return upon destruction of the `mainWindow' widget (which can be any kind of BWidget, but will be typically a BWindow). @meindex terminateMainLoop @slindex terminateMainLoop @slindex dispatchEvents @item terminateMainLoop Terminate the event dispatching loop if this call to #terminateMainLoop balances the number of calls to #dispatchEvents. @meindex update:@- @item update:@- aspect Initialize the Tcl and Blox environments; executed automatically on startup. @end table @node BLOX.Blox class-instance creation @subsection BLOX.Blox class:@- instance creation @table @b @meindex new @item new This method should not be called for instances of this class. @meindex new:@- @item new:@- parent Create a new widget of the type identified by the receiver, inside the given parent widget. Answer the new widget @end table @node BLOX.Blox class-utility @subsection BLOX.Blox class:@- utility @table @b @meindex active @item active Answer the currently active Blox, or nil if the focus does not belong to a Smalltalk window. @meindex at:@- @item at:@- aPoint Answer the Blox containing the given point on the screen, or nil if no Blox contains the given point (either because no Smalltalk window is there or because it is covered by another window). @meindex atMouse @item atMouse Answer the Blox under the mouse cursor's hot spot, or nil if no Blox contains the given point (either because no Smalltalk window is there or because it is covered by another window). @meindex beep @item beep Produce a bell @meindex clearClipboard @item clearClipboard Clear the clipboard, answer its old contents. @meindex clipboard @item clipboard Retrieve the text in the clipboard. @meindex clipboard:@- @item clipboard:@- aString Set the contents of the clipboard to aString (or empty the clipboard if aString is nil). @meindex createColor:@-green:@-blue:@- @item createColor:@- red green:@- green blue:@- blue Answer a color that can be passed to methods such as `backgroundColor:@-'. The color will have the given RGB components (range is 0~65535). @meindex createColor:@-magenta:@-yellow:@- @item createColor:@- cyan magenta:@- magenta yellow:@- yellow Answer a color that can be passed to methods such as `backgroundColor:@-'. The color will have the given CMY components (range is 0~65535). @meindex createColor:@-magenta:@-yellow:@-black:@- @item createColor:@- cyan magenta:@- magenta yellow:@- yellow black:@- black Answer a color that can be passed to methods such as `backgroundColor:@-'. The color will have the given CMYK components (range is 0~65535). @meindex createColor:@-saturation:@-value:@- @item createColor:@- hue saturation:@- sat value:@- value Answer a color that can be passed to methods such as `backgroundColor:@-'. The color will have the given HSV components (range is 0~65535). @meindex defaultFont @item defaultFont Answer the default font used by Blox. @meindex fonts @item fonts Answer the names of the font families in the system. Additionally, `Times', `Courier' and `Helvetica' are always made available. @meindex mousePointer @item mousePointer If the mouse pointer is on the same screen as the application's windows, returns a Point containing the pointer's x and y coordinates measured in pixels in the screen's root window (under X, if a virtual root window is in use on the screen, the position is computed in the whole desktop, not relative to the top-left corner of the currently shown portion). If the mouse pointer isn't on the same screen as window then answer nil. @meindex platform @slindex unix @slindex macintosh @slindex windows @item platform Answer the platform on which Blox is running; it can be either #unix, #macintosh or #windows. @meindex screenOrigin @item screenOrigin Answer a Point indicating the coordinates of the upper left point of the screen in the virtual root window on which the application's windows are drawn (under Windows and the Macintosh, that's always 0 @@ 0) @meindex screenResolution @item screenResolution Answer a Point containing the resolution in dots per inch of the screen, in the x and y directions. @meindex screenSize @item screenSize Answer a Point containing the size of the virtual root window on which the application's windows are drawn (under Windows and the Macintosh, that's the size of the screen) @end table @node BLOX.Blox-accessing @subsection BLOX.Blox:@- accessing @table @b @meindex state @item state Answer the value of the state option for the widget. Specifies one of three states for the button:@- normal, active, or disabled. In normal state the button is displayed using the foreground and background options. The active state is typically used when the pointer is over the button. In active state the button is displayed using the activeForeground and activeBackground options. Disabled state means that the button should be insensitive:@- the application will refuse to activate the widget and will ignore mouse button presses. @meindex state:@- @item state:@- value Set the value of the state option for the widget. Specifies one of three states for the button:@- normal, active, or disabled. In normal state the button is displayed using the foreground and background options. The active state is typically used when the pointer is over the button. In active state the button is displayed using the activeForeground and activeBackground options. Disabled state means that the button should be insensitive:@- the application will refuse to activate the widget and will ignore mouse button presses. @end table @node BLOX.Blox-basic @subsection BLOX.Blox:@- basic @table @b @meindex deepCopy @item deepCopy It does not make sense to make a copy, because it would make data inconsistent across different objects; so answer the receiver @meindex release @item release Destroy the receiver if it still exists, then perform the usual task of removing the dependency links @meindex shallowCopy @item shallowCopy It does not make sense to make a copy, because it would make data inconsistent across different objects; so answer the receiver @end table @node BLOX.Blox-creating children @subsection BLOX.Blox:@- creating children @table @b @meindex make:@- @slindex width:@- @slindex height:@- @slindex backgroundColor:@- @item make:@- array Create children of the receiver. Answer a Dictionary of the children. Each element of array is an Array including:@- a string which becomes the Dictionary's key, a binding like #@{Blox.BWindow@} identifying the class name, an array with the parameters to be set (for example #(@-#width:@- 50 #height:@- 30 #backgroundColor:@- 'blue')), and afterwards the children of the widget, described as arrays with this same format. @meindex make:@-on:@- @slindex make:@- @item make:@- array on:@- result Private - Create children of the receiver, adding them to result; answer result. array has the format described in the comment to #make:@- @meindex makeChild:@-on:@- @slindex make:@- @item makeChild:@- each on:@- result Private - Create a child of the receiver, adding them to result; each is a single element of the array described in the comment to #make:@- @end table @node BLOX.Blox-customization @subsection BLOX.Blox:@- customization @table @b @meindex addChild:@- @slindex basicAddChild:@- @item addChild:@- child The widget identified by child has been added to the receiver. This method is public not because you can call it, but because it can be useful to override it, not forgetting the call to either the superclass implementation or #basicAddChild:@-, to perform some initialization on the children just added. Answer the new child. @meindex basicAddChild:@- @slindex addChild:@- @item basicAddChild:@- child The widget identified by child has been added to the receiver. Add it to the children collection and answer the new child. This method is public because you can call it from #addChild:@-. @end table @node BLOX.Blox-widget protocol @subsection BLOX.Blox:@- widget protocol @table @b @meindex asPrimitiveWidget @item asPrimitiveWidget Answer the primitive widget that implements the receiver. @meindex childrenCount @item childrenCount Answer how many children the receiver has @meindex childrenDo:@- @item childrenDo:@- aBlock Evaluate aBlock once for each of the receiver's child widgets, passing the widget to aBlock as a parameter @meindex destroy @item destroy Destroy the receiver @meindex drawingArea @item drawingArea Answer a Rectangle identifying the receiver's drawing area. The rectangle's corners specify the upper-left and lower-right corners of the client area. Because coordinates are relative to the upper-left corner of a window's drawing area, the coordinates of the rectangle's corner are (0,0). @meindex enabled @slindex state @item enabled Answer whether the receiver is enabled to input. Although defined here, this method is only used for widgets that define a #state method @meindex enabled:@- @slindex state:@- @item enabled:@- enabled Set whether the receiver is enabled to input (enabled is a boolean). Although defined here, this method is only used for widgets that define a #state:@- method @meindex exists @item exists Answer whether the receiver has been destroyed or not (answer false in the former case, true in the latter). @meindex fontHeight:@- @slindex font @item fontHeight:@- aString Answer the height of aString in pixels, when displayed in the same font as the receiver. Although defined here, this method is only used for widgets that define a #font method @meindex fontWidth:@- @slindex font @item fontWidth:@- aString Answer the width of aString in pixels, when displayed in the same font as the receiver. Although defined here, this method is only used for widgets that define a #font method @meindex isWindow @item isWindow Answer whether the receiver represents a window on the screen. @meindex parent @item parent Answer the receiver's parent (or nil for a top-level window). @meindex toplevel @item toplevel Answer the top-level object (typically a BWindow or BPopupWindow) connected to the receiver. @meindex window @slindex toplevel @item window Answer the window in which the receiver stays. Note that while #toplevel won't answer a BTransientWindow, this method will. @meindex withChildrenDo:@- @item withChildrenDo:@- aBlock Evaluate aBlock passing the receiver, and then once for each of the receiver's child widgets. @end table @node BLOX.BMenu @section BLOX.BMenu @clindex BLOX.BMenu @table @b @item Defined in namespace BLOX @itemx Superclass: BLOX.BMenuObject @itemx Category: Graphics-Windows I am a Menu that is part of a menu bar. @end table @menu * BLOX.BMenu class-instance creation:: (class) * BLOX.BMenu-accessing:: (instance) * BLOX.BMenu-callback registration:: (instance) @end menu @node BLOX.BMenu class-instance creation @subsection BLOX.BMenu class:@- instance creation @table @b @meindex new:@-label:@- @item new:@- parent label:@- label Add a new menu to the parent window's menu bar, with `label' as its caption (for popup menus, parent is the widget over which the menu pops up as the right button is pressed). @end table @node BLOX.BMenu-accessing @subsection BLOX.BMenu:@- accessing @table @b @meindex label @item label Answer the value of the label option for the widget. Specifies a string to be displayed inside the widget. The way in which the string is displayed depends on the particular widget and may be determined by other options, such as anchor. For windows, this is the title of the window. @meindex label:@- @item label:@- value Set the value of the label option for the widget. Specifies a string to be displayed inside the widget. The way in which the string is displayed depends on the particular widget and may be determined by other options, such as anchor. For windows, this is the title of the window. @end table @node BLOX.BMenu-callback registration @subsection BLOX.BMenu:@- callback registration @table @b @meindex addLine @item addLine Add a separator item at the end of the menu @meindex addMenuItemFor:@-notifying:@- @item addMenuItemFor:@- anArray notifying:@- receiver Add a menu item described by anArray at the end of the menu. If anArray is empty, insert a separator line. If anArray has a single item, a menu item is created without a callback. If anArray has two or three items, the second one is used as the selector sent to receiver, and the third one (if present) is passed to the selector. @meindex callback:@-using:@- @slindex addMenuItemFor:@-notifying:@- @item callback:@- receiver using:@- selectorPairs Add menu items described by anArray at the end of the menu. Each element of selectorPairs must be in the format described in BMenu>>@-#addMenuItemFor:@-notifying:@-. All the callbacks will be sent to receiver. @meindex destroy @item destroy Destroy the menu widget; that is, simply remove ourselves from the parent menu bar. @meindex empty @item empty Empty the menu widget; that is, remove all the children @end table @node BLOX.BMenuBar @section BLOX.BMenuBar @clindex BLOX.BMenuBar @table @b @item Defined in namespace BLOX @itemx Superclass: BLOX.BMenuObject @itemx Category: Graphics-Windows I am the Menu Bar, the top widget in a full menu structure. @end table @menu * BLOX.BMenuBar-accessing:: (instance) @end menu @node BLOX.BMenuBar-accessing @subsection BLOX.BMenuBar:@- accessing @table @b @meindex add:@- @item add:@- aMenu Add aMenu to the menu bar @meindex remove:@- @item remove:@- aMenu Remove aMenu from the menu bar @end table @node BLOX.BMenuItem @section BLOX.BMenuItem @clindex BLOX.BMenuItem @table @b @item Defined in namespace BLOX @itemx Superclass: BLOX.BMenuObject @itemx Category: Graphics-Windows I am the tiny and humble Menu Item, a single command choice in the menu structure. But if it wasn't for me, nothing could be done... eh eh eh!! @end table @menu * BLOX.BMenuItem class-instance creation:: (class) * BLOX.BMenuItem-accessing:: (instance) @end menu @node BLOX.BMenuItem class-instance creation @subsection BLOX.BMenuItem class:@- instance creation @table @b @meindex new:@- @item new:@- parent Add a new separator item to the specified menu. @meindex new:@-label:@- @item new:@- parent label:@- label Add a new menu item to the specified menu (parent) , with `label' as its caption. @end table @node BLOX.BMenuItem-accessing @subsection BLOX.BMenuItem:@- accessing @table @b @meindex label @item label Answer the value of the label option for the widget. Specifies a string to be displayed inside the widget. The way in which the string is displayed depends on the particular widget and may be determined by other options, such as anchor. For windows, this is the title of the window. @meindex label:@- @item label:@- value Set the value of the label option for the widget. Specifies a string to be displayed inside the widget. The way in which the string is displayed depends on the particular widget and may be determined by other options, such as anchor. For windows, this is the title of the window. @end table @node BLOX.BMenuObject @section BLOX.BMenuObject @clindex BLOX.BMenuObject @table @b @item Defined in namespace BLOX @itemx Superclass: BLOX.Blox @itemx Category: Graphics-Windows I am an abstract superclass for widgets which make up a menu structure. @end table @menu * BLOX.BMenuObject-accessing:: (instance) * BLOX.BMenuObject-callback:: (instance) @end menu @node BLOX.BMenuObject-accessing @subsection BLOX.BMenuObject:@- accessing @table @b @meindex activeBackground @item activeBackground Answer the value of the activeBackground option for the widget. Specifies background color to use when drawing active elements. An element (a widget or portion of a widget) is active if the mouse cursor is positioned over the element and pressing a mouse button will cause some action to occur. For some elements on Windows and Macintosh systems, the active color will only be used while mouse button 1 is pressed over the element. @meindex activeBackground:@- @item activeBackground:@- value Set the value of the activeBackground option for the widget. Specifies background color to use when drawing active elements. An element (a widget or portion of a widget) is active if the mouse cursor is positioned over the element and pressing a mouse button will cause some action to occur. For some elements on Windows and Macintosh systems, the active color will only be used while mouse button 1 is pressed over the element. @meindex activeForeground @item activeForeground Answer the value of the activeForeground option for the widget. Specifies foreground color to use when drawing active elements. See above for definition of active elements. @meindex activeForeground:@- @item activeForeground:@- value Set the value of the activeForeground option for the widget. Specifies foreground color to use when drawing active elements. See above for definition of active elements. @meindex asPrimitiveWidget @item asPrimitiveWidget Answer the primitive widget that implements the receiver. @meindex backgroundColor @item backgroundColor Answer the value of the backgroundColor option for the widget. Specifies the normal background color to use when displaying the widget. @meindex backgroundColor:@- @item backgroundColor:@- value Set the value of the backgroundColor option for the widget. Specifies the normal background color to use when displaying the widget. @meindex foregroundColor @item foregroundColor Answer the value of the foregroundColor option for the widget. Specifies the normal foreground color to use when displaying the widget. @meindex foregroundColor:@- @item foregroundColor:@- value Set the value of the foregroundColor option for the widget. Specifies the normal foreground color to use when displaying the widget. @end table @node BLOX.BMenuObject-callback @subsection BLOX.BMenuObject:@- callback @table @b @meindex callback @item callback Answer a DirectedMessage that is sent when the receiver is modified, or nil if none has been set up. @meindex callback:@-message:@- @item callback:@- aReceiver message:@- aSymbol Set up so that aReceiver is sent the aSymbol message (the name of a zero- or one-argument selector) when the receiver is clicked. If the method accepts an argument, the receiver is passed. @meindex callback:@-message:@-argument:@- @item callback:@- aReceiver message:@- aSymbol argument:@- anObject Set up so that aReceiver is sent the aSymbol message (the name of a one- or two-argument selector) when the receiver is clicked. If the method accepts two argument, the receiver is passed together with anObject; if it accepts a single one, instead, only anObject is passed. @meindex invokeCallback @item invokeCallback Generate a synthetic callback @end table @node BLOX.BOval @section BLOX.BOval @clindex BLOX.BOval @table @b @item Defined in namespace BLOX @itemx Superclass: BLOX.BRectangle @itemx Category: Graphics-Windows I can draw ovals (ok, if you're a mathematic, they're really ellipses), or even circles. @end table @menu @end menu @node BLOX.BPolyline @section BLOX.BPolyline @clindex BLOX.BPolyline @table @b @item Defined in namespace BLOX @itemx Superclass: BLOX.BCanvasObject @itemx Category: Graphics-Windows I can draw closed or open polylines, and even fill them! @end table @menu * BLOX.BPolyline-accessing:: (instance) @end menu @node BLOX.BPolyline-accessing @subsection BLOX.BPolyline:@- accessing @table @b @meindex boundingBox @item boundingBox Answer `boundingBox'. @meindex cap @item cap Answer the way in which caps are to be drawn at the endpoints of the line. This option is only available for open polylines. If you want to set it for a closed polylines, draw an open one on top of it. @meindex cap:@- @slindex butt @slindex projecting @slindex round @item cap:@- aSymbol Set the way in which caps are to be drawn at the endpoints of the line. aSymbol may be #butt (the default), #projecting, or #round). This option is only available for open polylines. If you want to set it for a closed polylines, draw an open one on top of it. @meindex closed @item closed Answer whether the polyline is an open or a closed one. @meindex closed:@- @item closed:@- aBoolean Set whether the polyline is an open or a closed one. This option may be set only once. @meindex join @item join Answer the way in which joints are to be drawn at the vertices of the line. This option is only available for open polylines. If you want to set it for a closed polylines, draw an open one on top of it. @meindex join:@- @slindex bevel @slindex miter @slindex round @item join:@- aSymbol Answer the way in which joints are to be drawn at the vertices of the line. aSymbol can be #bevel, #miter (the default) or #round. This option is only available for open polylines. If you want to set it for a closed polylines, draw an open one on top of it. @meindex outlineColor @item outlineColor Answer the color with which the outline of the polyline is drawn. This option is only available for closed polylines. @meindex outlineColor:@- @item outlineColor:@- color Set the color with which the outline of the polyline is drawn. This option is only available for closed polylines. @meindex points @item points Answer the points that are vertices of the polyline. @meindex points:@- @slindex create @slindex redraw @item points:@- arrayOfPointsOrArrays Set the points that are vertices of the polyline. Each of the items of arrayOfPointsOrArrays can be a Point or a two-element Array. Note that no changes take place until you invoke the #create (if the object has not been inserted in the canvas yet) or the #redraw method. @meindex width @item width Answer the width with which the polyline (or its outline if it is a closed one) is drawn. @meindex width:@- @item width:@- pixels Set the width with which the polyline (or its outline if it is a closed one) is drawn. @end table @node BLOX.BPopupMenu @section BLOX.BPopupMenu @clindex BLOX.BPopupMenu @table @b @item Defined in namespace BLOX @itemx Superclass: BLOX.BMenu @itemx Category: Graphics-Windows I am a class that provides the ability to show popup menus when the right button (Button 3) is clicked on another window. @end table @menu * BLOX.BPopupMenu-widget protocol:: (instance) @end menu @node BLOX.BPopupMenu-widget protocol @subsection BLOX.BPopupMenu:@- widget protocol @table @b @meindex popup @item popup Generate a synthetic menu popup event @end table @node BLOX.BPopupWindow @section BLOX.BPopupWindow @clindex BLOX.BPopupWindow @table @b @item Defined in namespace BLOX @itemx Superclass: BLOX.BWindow @itemx Category: Graphics-Windows I am a pseudo-window that has no decorations and no ability to interact with the user. My main usage, as my name says, is to provide pop-up functionality for other widgets. Actually there should be no need to directly use me - always rely on the #new and #popup:@- class methods. @end table @menu * BLOX.BPopupWindow-geometry management:: (instance) @end menu @node BLOX.BPopupWindow-geometry management @subsection BLOX.BPopupWindow:@- geometry management @table @b @meindex addChild:@- @slindex basicAddChild:@- @item addChild:@- w Private - The widget identified by child has been added to the receiver. This method is public not because you can call it, but because it can be useful to override it, not forgetting the call to either the superclass implementation or #basicAddChild:@-, to perform some initialization on the children just added. Answer the new child. @meindex child:@-height:@- @item child:@- child height:@- value Set the given child's height. This is done by setting its parent window's (that is, our) height. @meindex child:@-heightOffset:@- @item child:@- child heightOffset:@- value This method should not be called for instances of this class. @meindex child:@-width:@- @item child:@- child width:@- value Set the given child's width. This is done by setting its parent window's (that is, our) width. @meindex child:@-widthOffset:@- @item child:@- child widthOffset:@- value This method should not be called for instances of this class. @meindex child:@-x:@- @item child:@- child x:@- value Set the x coordinate of the given child's top-left corner. This is done by setting its parent window's (that is, our) x. @meindex child:@-xOffset:@- @item child:@- child xOffset:@- value This method should not be called for instances of this class. @meindex child:@-y:@- @item child:@- child y:@- value Set the y coordinate of the given child's top-left corner. This is done by setting its parent window's (that is, our) y. @meindex child:@-yOffset:@- @item child:@- child yOffset:@- value This method should not be called for instances of this class. @meindex heightChild:@- @item heightChild:@- child Answer the given child's height, which is the height that was imposed on the popup window. @meindex widthChild:@- @item widthChild:@- child Answer the given child's width in pixels, which is the width that was imposed on the popup window. @meindex xChild:@- @item xChild:@- child Answer the x coordinate of the given child's top-left corner, which is desumed by the position of the popup window. @meindex yChild:@- @item yChild:@- child Answer the y coordinate of the given child's top-left corner, which is desumed by the position of the popup window. @end table @node BLOX.BPrimitive @section BLOX.BPrimitive @clindex BLOX.BPrimitive @table @b @item Defined in namespace BLOX @itemx Superclass: BLOX.BWidget @itemx Category: Graphics-Windows I am the superclass for every widget (except menus) directly provided by the underlying GUI system. @end table @menu * BLOX.BPrimitive-accessing:: (instance) @end menu @node BLOX.BPrimitive-accessing @subsection BLOX.BPrimitive:@- accessing @table @b @meindex asPrimitiveWidget @item asPrimitiveWidget Answer the primitive widget that implements the receiver. @end table @node BLOX.BProgress @section BLOX.BProgress @clindex BLOX.BProgress @table @b @item Defined in namespace BLOX @itemx Superclass: BLOX.BExtended @itemx Category: Graphics-Examples I show how much of a task has been completed. @end table @menu * BLOX.BProgress-accessing:: (instance) @end menu @node BLOX.BProgress-accessing @subsection BLOX.BProgress:@- accessing @table @b @meindex backgroundColor @item backgroundColor Answer the background color of the widget. This is used for the background of the non-filled part, as well as for the foreground of the filled part. @meindex backgroundColor:@- @item backgroundColor:@- aColor Set the background color of the widget. This is used for the background of the non-filled part, as well as for the foreground of the filled part. @meindex filledColor @item filledColor Answer the background color of the widget's filled part. @meindex filledColor:@- @item filledColor:@- aColor Set the background color of the widget's filled part. @meindex foregroundColor @item foregroundColor Set the foreground color of the widget. This is used for the non-filled part, while the background color also works as the foreground of the filled part. @meindex foregroundColor:@- @item foregroundColor:@- aColor Set the foreground color of the widget. This is used for the non-filled part, while the background color also works as the foreground of the filled part. @meindex value @item value Answer the filled percentage of the receiver (0..1) @meindex value:@- @item value:@- newValue Set the filled percentage of the receiver and update the appearance. newValue must be between 0 and 1. @end table @node BLOX.BRadioButton @section BLOX.BRadioButton @clindex BLOX.BRadioButton @table @b @item Defined in namespace BLOX @itemx Superclass: BLOX.BButton @itemx Category: Graphics-Windows I am just one in a group of mutually exclusive buttons. @end table @menu * BLOX.BRadioButton-accessing:: (instance) @end menu @node BLOX.BRadioButton-accessing @subsection BLOX.BRadioButton:@- accessing @table @b @meindex callback:@-message:@- @item callback:@- aReceiver message:@- aSymbol Set up so that aReceiver is sent the aSymbol message (the name of a selector accepting at most two arguments) when the receiver is clicked. If the method accepts two arguments, the receiver is passed as the first parameter. If the method accepts one or two arguments, true is passed as the last parameter for interoperability with BToggle widgets. @meindex value @item value Answer whether this widget is the selected one in its radio button group. @meindex value:@- @item value:@- aBoolean Answer whether this widget is the selected one in its radio button group. Setting this property to false for a group's currently selected button unhighlights all the buttons in that group. @end table @node BLOX.BRadioGroup @section BLOX.BRadioGroup @clindex BLOX.BRadioGroup @table @b @item Defined in namespace BLOX @itemx Superclass: BLOX.BContainer @itemx Category: Graphics-Windows I am used to group many mutually-exclusive radio buttons together. In addition, just like every BContainer I can perform simple management by putting widgets next to each other, from left to right or (which is more useful in this particular case...) from top to bottom. @end table @menu * BLOX.BRadioGroup-accessing:: (instance) * BLOX.BRadioGroup-widget protocol:: (instance) @end menu @node BLOX.BRadioGroup-accessing @subsection BLOX.BRadioGroup:@- accessing @table @b @meindex value @item value Answer the index of the button that is currently selected, 1 being the first button added to the radio button group. 0 means that no button is selected @meindex value:@- @item value:@- value Force the value-th button added to the radio button group to be the selected one. @end table @node BLOX.BRadioGroup-widget protocol @subsection BLOX.BRadioGroup:@- widget protocol @table @b @meindex destroyed @item destroyed Private - The receiver has been destroyed, clear the corresponding Tcl variable to avoid memory leaks. @end table @node BLOX.BRectangle @section BLOX.BRectangle @clindex BLOX.BRectangle @table @b @item Defined in namespace BLOX @itemx Superclass: BLOX.BBoundingBox @itemx Category: Graphics-Windows I only draw rectangles but I can do that very well. @end table @menu * BLOX.BRectangle-accessing:: (instance) @end menu @node BLOX.BRectangle-accessing @subsection BLOX.BRectangle:@- accessing @table @b @meindex outlineColor @item outlineColor Answer the color with which the outline of the rectangle is drawn. @meindex outlineColor:@- @item outlineColor:@- color Set the color with which the outline of the rectangle is drawn. @meindex width @item width Answer the width with which the outline of the rectangle is drawn. @meindex width:@- @item width:@- pixels Set the width with which the outline of the rectangle is drawn. @end table @node BLOX.BScrolledCanvas @section BLOX.BScrolledCanvas @clindex BLOX.BScrolledCanvas @table @b @item Defined in namespace BLOX @itemx Superclass: BLOX.BCanvas @itemx Category: Graphics-Windows I am much similar to BCanvas, but I sport, in addition, two fancy scroll bars. This is just a convenience, since it could be easily done when creating the canvas... @end table @menu @end menu @node BLOX.BSpline @section BLOX.BSpline @clindex BLOX.BSpline @table @b @item Defined in namespace BLOX @itemx Superclass: BLOX.BPolyline @itemx Category: Graphics-Windows Unlike my father BPolyline, I am more smooth at doing my job. @end table @menu * BLOX.BSpline-accessing:: (instance) @end menu @node BLOX.BSpline-accessing @subsection BLOX.BSpline:@- accessing @table @b @meindex smoothness @item smoothness Answer the degree of smoothness desired for curves. Each spline will be approximated with this number of line segments. @meindex smoothness:@- @item smoothness:@- anInteger Set the degree of smoothness desired for curves. Each spline will be approximated with this number of line segments. @end table @node BLOX.BText @section BLOX.BText @clindex BLOX.BText @table @b @item Defined in namespace BLOX @itemx Superclass: BLOX.BViewport @itemx Category: Graphics-Windows I represent a text viewer with pretty good formatting options. @end table @menu * BLOX.BText class-accessing:: (class) * BLOX.BText class-instance creation:: (class) * BLOX.BText-accessing:: (instance) * BLOX.BText-attributes:: (instance) * BLOX.BText-geometry management:: (instance) * BLOX.BText-images:: (instance) * BLOX.BText-inserting text:: (instance) * BLOX.BText-position & lines:: (instance) @end menu @node BLOX.BText class-accessing @subsection BLOX.BText class:@- accessing @table @b @meindex emacsLike @item emacsLike Answer whether we are using Emacs or Motif key bindings. @meindex emacsLike:@- @item emacsLike:@- aBoolean Set whether we are using Emacs or Motif key bindings. @end table @node BLOX.BText class-instance creation @subsection BLOX.BText class:@- instance creation @table @b @meindex newReadOnly:@- @item newReadOnly:@- parent Answer a new read-only text widget (read-only is achieved simply by setting its state to be disabled) @end table @node BLOX.BText-accessing @subsection BLOX.BText:@- accessing @table @b @meindex backgroundColor @item backgroundColor Answer the value of the backgroundColor option for the widget. Specifies the normal background color to use when displaying the widget. @meindex backgroundColor:@- @item backgroundColor:@- value Set the value of the backgroundColor option for the widget. Specifies the normal background color to use when displaying the widget. @meindex callback @item callback Answer a DirectedMessage that is sent when the receiver is modified, or nil if none has been set up. @meindex callback:@-message:@- @item callback:@- aReceiver message:@- aSymbol Set up so that aReceiver is sent the aSymbol message (the name of a zero- or one-argument selector) when the receiver is modified. If the method accepts an argument, the receiver is passed. @meindex contents @item contents Return the contents of the widget @meindex contents:@- @item contents:@- aString Set the contents of the widget @meindex font @item font Answer the value of the font option for the widget. Specifies the font to use when drawing text inside the widget. The font can be given as either an X font name or a Blox font description string. X font names are given as many fields, each led by a minus, and each of which can be replaced by an * to indicate a default value is ok:@- foundry, family, weight, slant, setwidth, addstyle, pixel size, point size (the same as pixel size for historical reasons), horizontal resolution, vertical resolution, spacing, width, charset and character encoding. Blox font description strings have three fields, which must be separated by a space and of which only the first is mandatory:@- the font family, the font size in points (or in pixels if a negative value is supplied), and a number of styles separated by a space (valid styles are normal, bold, italic, underline and overstrike). Examples of valid fonts are ``Helvetica 10 Bold'', ``Times -14'', ``Futura Bold Underline''. You must enclose the font family in braces if it is made of two or more words. @meindex font:@- @item font:@- value Set the value of the font option for the widget. Specifies the font to use when drawing text inside the widget. The font can be given as either an X font name or a Blox font description string. X font names are given as many fields, each led by a minus, and each of which can be replaced by an * to indicate a default value is ok:@- foundry, family, weight, slant, setwidth, addstyle, pixel size, point size (the same as pixel size for historical reasons), horizontal resolution, vertical resolution, spacing, width, charset and character encoding. Blox font description strings have three fields, which must be separated by a space and of which only the first is mandatory:@- the font family, the font size in points (or in pixels if a negative value is supplied), and a number of styles separated by a space (valid styles are normal, bold, italic, underline and overstrike). Examples of valid fonts are ``Helvetica 10 Bold'', ``Times -14'', ``Futura Bold Underline''. You must enclose the font family in braces if it is made of two or more words. @meindex foregroundColor @item foregroundColor Answer the value of the foregroundColor option for the widget. Specifies the normal foreground color to use when displaying the widget. @meindex foregroundColor:@- @item foregroundColor:@- value Set the value of the foregroundColor option for the widget. Specifies the normal foreground color to use when displaying the widget. @meindex getSelection @item getSelection Answer an empty string if the widget has no selection, else answer the currently selected text @meindex selectBackground @item selectBackground Answer the value of the selectBackground option for the widget. Specifies the background color to use when displaying selected parts of the widget. @meindex selectBackground:@- @item selectBackground:@- value Set the value of the selectBackground option for the widget. Specifies the background color to use when displaying selected parts of the widget. @meindex selectForeground @item selectForeground Answer the value of the selectForeground option for the widget. Specifies the foreground color to use when displaying selected parts of the widget. @meindex selectForeground:@- @item selectForeground:@- value Set the value of the selectForeground option for the widget. Specifies the foreground color to use when displaying selected parts of the widget. @meindex wrap @slindex none @slindex char @slindex word @item wrap Answer the value of the wrap option for the widget. Specifies how to handle lines in the text that are too long to be displayed in a single line of the text's window. The value must be #none or #char or #word. A wrap mode of none means that each line of text appears as exactly one line on the screen; extra characters that do not fit on the screen are not displayed. In the other modes each line of text will be broken up into several screen lines if necessary to keep all the characters visible. In char mode a screen line break may occur after any character; in word mode a line break will only be made at word boundaries. @meindex wrap:@- @slindex none @slindex char @slindex word @item wrap:@- value Set the value of the wrap option for the widget. Specifies how to handle lines in the text that are too long to be displayed in a single line of the text's window. The value must be #none or #char or #word. A wrap mode of none means that each line of text appears as exactly one line on the screen; extra characters that do not fit on the screen are not displayed. In the other modes each line of text will be broken up into several screen lines if necessary to keep all the characters visible. In char mode a screen line break may occur after any character; in word mode a line break will only be made at word boundaries. @end table @node BLOX.BText-attributes @subsection BLOX.BText:@- attributes @table @b @meindex insertAtEnd:@-attribute:@- @item insertAtEnd:@- aString attribute:@- attr Clear the selection and append aString at the end of the widget. Use the given attributes to format the text. @meindex insertText:@-attribute:@- @item insertText:@- aString attribute:@- attr Insert aString in the widget at the current insertion point, replacing the currently selected text (if any). Use the given attributes to format the text. @meindex removeAttributes @item removeAttributes Remove any kind of formatting from the text in the widget @meindex removeAttributesFrom:@-to:@- @item removeAttributesFrom:@- aPoint to:@- endPoint Remove any kind of formatting from the text in the widget between the given endpoints. The two endpoints are Point objects in which both coordinates are 1-based:@- the first line is line 1, and the first character in the first line is character 1. @meindex setAttributes:@-from:@-to:@- @item setAttributes:@- attr from:@- aPoint to:@- endPoint Add the formatting given by attr to the text in the widget between the given endpoints. The two endpoints are Point objects in which both coordinates are 1-based:@- the first line is line 1, and the first character in the first line is character 1. @end table @node BLOX.BText-geometry management @subsection BLOX.BText:@- geometry management @table @b @meindex child:@-height:@- @item child:@- child height:@- value Set the height of the given child to be `value' pixels. @meindex child:@-heightOffset:@- @item child:@- child heightOffset:@- value Adjust the height of the given child to be given by `value' more pixels. @meindex child:@-width:@- @item child:@- child width:@- value Set the width of the given child to be `value' pixels. @meindex child:@-widthOffset:@- @item child:@- child widthOffset:@- value Adjust the width of the given child to be given by `value' more pixels. @meindex child:@-x:@- @item child:@- child x:@- value Never fail and do nothing, the children stay where the text ended at the time each child was added in the widget @meindex child:@-xOffset:@- @item child:@- child xOffset:@- value This method should not be called for instances of this class. @meindex child:@-y:@- @item child:@- child y:@- value Never fail and do nothing, the children stay where the text ended at the time each child was added in the widget @meindex child:@-yOffset:@- @item child:@- child yOffset:@- value This method should not be called for instances of this class. @meindex heightChild:@- @item heightChild:@- child Answer the given child's height in pixels. @meindex widthChild:@- @item widthChild:@- child Answer the given child's width in pixels. @meindex xChild:@- @item xChild:@- child Answer the given child's top-left border's x coordinate. We always answer 0 since the children actually move when the text widget scrolls @meindex yChild:@- @item yChild:@- child Answer the given child's top-left border's y coordinate. We always answer 0 since the children actually move when the text widget scrolls @end table @node BLOX.BText-images @subsection BLOX.BText:@- images @table @b @meindex insertImage:@- @slindex registerImage:@- @item insertImage:@- anObject Insert an image where the insertion point currently lies in the widget. anObject can be a String containing image data (either Base-64 encoded GIF data, XPM data, or PPM data), or the result or registering an image with #registerImage:@- @meindex insertImage:@-at:@- @slindex registerImage:@- @item insertImage:@- anObject at:@- position Insert an image at the given position in the widget. The position is a Point object in which both coordinates are 1-based:@- the first line is line 1, and the first character in the first line is character 1. anObject can be a String containing image data (either Base-64 encoded GIF data, XPM data, or PPM data), or the result or registering an image with #registerImage:@- @meindex insertImageAtEnd:@- @slindex registerImage:@- @item insertImageAtEnd:@- anObject Insert an image at the end of the widgets text. anObject can be a String containing image data (either Base-64 encoded GIF data, XPM data, or PPM data), or the result or registering an image with #registerImage:@- @meindex registerImage:@- @slindex registerImage:@- @item registerImage:@- anObject Register an image (whose data is in anObject, a String including Base-64 encoded GIF data, XPM data, or PPM data) to be used in the widget. If the same image must be used a lot of times, it is better to register it once and then pass the result of #registerImage:@- to the image insertion methods. Registered image are private within each BText widget. Registering an image with a widget and using it with another could give unpredictable results. @end table @node BLOX.BText-inserting text @subsection BLOX.BText:@- inserting text @table @b @meindex insertAtEnd:@- @item insertAtEnd:@- aString Clear the selection and append aString at the end of the widget. @meindex insertSelectedText:@- @item insertSelectedText:@- aString Insert aString in the widget at the current insertion point, leaving the currently selected text (if any) in place, and selecting the text. @meindex insertText:@- @item insertText:@- aString Insert aString in the widget at the current insertion point, replacing the currently selected text (if any). @meindex insertText:@-at:@- @item insertText:@- aString at:@- position Insert aString in the widget at the given position, replacing the currently selected text (if any). The position is a Point object in which both coordinates are 1-based:@- the first line is line 1, and the first character in the first line is character 1. @meindex insertTextSelection:@- @item insertTextSelection:@- aString Insert aString in the widget after the current selection, leaving the currently selected text (if any) intact. @meindex invokeCallback @item invokeCallback Generate a synthetic callback. @meindex nextPut:@- @item nextPut:@- aCharacter Clear the selection and append aCharacter at the end of the widget. @meindex nextPutAll:@- @item nextPutAll:@- aString Clear the selection and append aString at the end of the widget. @meindex nl @item nl Clear the selection and append a linefeed character at the end of the widget. @meindex refuseTabs @item refuseTabs Arrange so that Tab characters, instead of being inserted in the widget, traverse the widgets in the parent window. @meindex replaceSelection:@- @item replaceSelection:@- aString Insert aString in the widget at the current insertion point, replacing the currently selected text (if any), and leaving the text selected. @meindex searchString:@- @item searchString:@- aString Search aString in the widget. If it is not found, answer zero, else answer the 1-based line number and move the insertion point to the place where the string was found. @meindex space @item space Clear the selection and append a space at the end of the widget. @end table @node BLOX.BText-position & lines @subsection BLOX.BText:@- position & lines @table @b @meindex charsInLine:@- @item charsInLine:@- number Answer how many characters are there in the number-th line @meindex currentColumn @item currentColumn Answer the 1-based column number where the insertion point currently lies. @meindex currentLine @item currentLine Answer the 1-based line number where the insertion point currently lies. @meindex currentPosition @item currentPosition Answer a Point representing where the insertion point currently lies. Both coordinates in the answer are 1-based:@- the first line is line 1, and the first character in the first line is character 1. @meindex currentPosition:@- @item currentPosition:@- aPoint Move the insertion point to the position given by aPoint. Both coordinates in aPoint are interpreted as 1-based:@- the first line is line 1, and the first character in the first line is character 1. @meindex gotoLine:@-end:@- @item gotoLine:@- line end:@- aBoolean If aBoolean is true, move the insertion point to the last character of the line-th line (1 being the first line in the widget); if aBoolean is false, move it to the start of the line-th line. @meindex indexAt:@- @item indexAt:@- point Answer the position of the character that covers the pixel whose coordinates within the text's window are given by the supplied Point object. @meindex lineAt:@- @item lineAt:@- number Answer the number-th line of text in the widget @meindex numberOfLines @item numberOfLines Answer the number of lines in the widget @meindex selectFrom:@-to:@- @item selectFrom:@- first to:@- last Select the text between the given endpoints. The two endpoints are Point objects in which both coordinates are 1-based:@- the first line is line 1, and the first character in the first line is character 1. @meindex setToEnd @item setToEnd Move the insertion point to the end of the widget @end table @node BLOX.BTextAttributes @section BLOX.BTextAttributes @clindex BLOX.BTextAttributes @table @b @item Defined in namespace BLOX @itemx Superclass: Object @itemx Category: Graphics-Windows I help you creating wonderful, colorful BTexts. @end table @menu * BLOX.BTextAttributes class-instance-creation shortcuts:: (class) * BLOX.BTextAttributes-colors:: (instance) * BLOX.BTextAttributes-setting attributes:: (instance) @end menu @node BLOX.BTextAttributes class-instance-creation shortcuts @subsection BLOX.BTextAttributes class:@- instance-creation shortcuts @table @b @meindex backgroundColor:@- @item backgroundColor:@- color Create a new BTextAttributes object resulting in text with the given background color. @meindex black @item black Create a new BTextAttributes object resulting in black text. @meindex blue @item blue Create a new BTextAttributes object resulting in blue text. @meindex center @item center Create a new BTextAttributes object resulting in centered paragraphs. @meindex cyan @item cyan Create a new BTextAttributes object resulting in cyan text. @meindex darkCyan @item darkCyan Create a new BTextAttributes object resulting in dark cyan text. @meindex darkGreen @item darkGreen Create a new BTextAttributes object resulting in dark green text. @meindex darkMagenta @item darkMagenta Create a new BTextAttributes object resulting in dark purple text. @meindex events:@- @item events:@- aBTextBindings Create a new BTextAttributes object for text that responds to events according to the callbacks established in aBTextBindings. @meindex font:@- @item font:@- font Create a new BTextAttributes object resulting in text with the given font. The font can be given as either an X font name or a Blox font description string. X font names are given as many fields, each led by a minus, and each of which can be replaced by an * to indicate a default value is ok:@- foundry, family, weight, slant, setwidth, addstyle, pixel size, point size (the same as pixel size for historical reasons), horizontal resolution, vertical resolution, spacing, width, charset and character encoding. Blox font description strings have three fields, which must be separated by a space and of which only the first is mandatory:@- the font family, the font size in points (or in pixels if a negative value is supplied), and a number of styles separated by a space (valid styles are normal, bold, italic, underline and overstrike). Examples of valid fonts are ``Helvetica 10 Bold'', ``Times -14'', ``Futura Bold Underline''. You must enclose the font family in braces if it is made of two or more words. @meindex foregroundColor:@- @item foregroundColor:@- color Create a new BTextAttributes object resulting in text with the given foreground color. @meindex green @item green Create a new BTextAttributes object resulting in green text. @meindex magenta @item magenta Create a new BTextAttributes object resulting in magenta text. @meindex red @item red Create a new BTextAttributes object resulting in red text. @meindex strikeout @item strikeout Create a new BTextAttributes object resulting in struck-out text. @meindex underline @item underline Create a new BTextAttributes object resulting in underlined text. @meindex white @item white Create a new BTextAttributes object resulting in white text. @meindex yellow @item yellow Create a new BTextAttributes object resulting in yellow text. @end table @node BLOX.BTextAttributes-colors @subsection BLOX.BTextAttributes:@- colors @table @b @meindex black @item black Set the receiver so that applying it results in black text. @meindex blue @item blue Set the receiver so that applying it results in blue text. @meindex cyan @item cyan Set the receiver so that applying it results in cyan text. @meindex darkCyan @item darkCyan Set the receiver so that applying it results in dark cyan text. @meindex darkGreen @item darkGreen Set the receiver so that applying it results in dark green text. @meindex darkMagenta @item darkMagenta Set the receiver so that applying it results in dark magenta text. @meindex green @item green Set the receiver so that applying it results in green text. @meindex magenta @item magenta Set the receiver so that applying it results in magenta text. @meindex red @item red Set the receiver so that applying it results in red text. @meindex white @item white Set the receiver so that applying it results in white text. @meindex yellow @item yellow Set the receiver so that applying it results in black text. @end table @node BLOX.BTextAttributes-setting attributes @subsection BLOX.BTextAttributes:@- setting attributes @table @b @meindex backgroundColor @item backgroundColor Answer the value of the backgroundColor option for the text. Specifies the background color to use when displaying text with these attributes. nil indicates that the default value is not overridden. @meindex backgroundColor:@- @item backgroundColor:@- color Set the value of the backgroundColor option for the text. Specifies the background color to use when displaying text with these attributes. nil indicates that the default value is not overridden. @meindex center @item center Center the text to which these attributes are applied @meindex events @item events Answer the event bindings which apply to text subject to these attributes @meindex events:@- @item events:@- aBTextBindings Set the event bindings which apply to text subject to these attributes @meindex font @item font Answer the value of the font option for the text. The font can be given as either an X font name or a Blox font description string, or nil if you want the widget's default font to apply. X font names are given as many fields, each led by a minus, and each of which can be replaced by an * to indicate a default value is ok:@- foundry, family, weight, slant, setwidth, addstyle, pixel size, point size (the same as pixel size for historical reasons), horizontal resolution, vertical resolution, spacing, width, charset and character encoding. Blox font description strings have three fields, which must be separated by a space and of which only the first is mandatory:@- the font family, the font size in points (or in pixels if a negative value is supplied), and a number of styles separated by a space (valid styles are normal, bold, italic, underline and overstrike). Examples of valid fonts are ``Helvetica 10 Bold'', ``Times -14'', ``Futura Bold Underline''. You must enclose the font family in braces if it is made of two or more words. @meindex font:@- @item font:@- fontName Set the value of the font option for the text. The font can be given as either an X font name or a Blox font description string, or nil if you want the widget's default font to apply. X font names are given as many fields, each led by a minus, and each of which can be replaced by an * to indicate a default value is ok:@- foundry, family, weight, slant, setwidth, addstyle, pixel size, point size (the same as pixel size for historical reasons), horizontal resolution, vertical resolution, spacing, width, charset and character encoding. Blox font description strings have three fields, which must be separated by a space and of which only the first is mandatory:@- the font family, the font size in points (or in pixels if a negative value is supplied), and a number of styles separated by a space (valid styles are normal, bold, italic, underline and overstrike). Examples of valid fonts are ``Helvetica 10 Bold'', ``Times -14'', ``Futura Bold Underline''. You must enclose the font family in braces if it is made of two or more words. @meindex foregroundColor @item foregroundColor Answer the value of the foregroundColor option for the text. Specifies the foreground color to use when displaying text with these attributes. nil indicates that the default value is not overridden. @meindex foregroundColor:@- @item foregroundColor:@- color Set the value of the foregroundColor option for the text. Specifies the foreground color to use when displaying text with these attributes. nil indicates that the default value is not overridden. @meindex isCentered @item isCentered Answer whether the text to which these attributes are applied is centered @meindex isStruckout @item isStruckout Answer whether the text to which these attributes are applied is struckout @meindex isUnderlined @item isUnderlined Answer whether the text to which these attributes are applied is underlined @meindex strikeout @item strikeout Strike out the text to which these attributes are applied @meindex underline @item underline Underline the text to which these attributes are applied @end table @node BLOX.BTextBindings @section BLOX.BTextBindings @clindex BLOX.BTextBindings @table @b @item Defined in namespace BLOX @itemx Superclass: BLOX.BEventTarget @itemx Category: Graphics-Windows This object is used to assign event handlers to particular sections of text in a BText widget. To use it, you simply have to add event handlers to it, and then create a BTextAttributes object that refers to it. @end table @menu * BLOX.BTextBindings class-instance creation:: (class) @end menu @node BLOX.BTextBindings class-instance creation @subsection BLOX.BTextBindings class:@- instance creation @table @b @meindex new @item new Create a new instance of the receiver. @end table @node BLOX.BTextTags @section BLOX.BTextTags @clindex BLOX.BTextTags @table @b @item Defined in namespace BLOX @itemx Superclass: Object @itemx Category: Graphics-Windows I am a private class. I sit between a BText and BTextAttributes, helping the latter in telling the former which attributes to use. @end table @menu @end menu @node BLOX.BToggle @section BLOX.BToggle @clindex BLOX.BToggle @table @b @item Defined in namespace BLOX @itemx Superclass: BLOX.BButton @itemx Category: Graphics-Windows I represent a button whose choice can be included (by checking me) or excluded (by leaving me unchecked). @end table @menu * BLOX.BToggle-accessing:: (instance) @end menu @node BLOX.BToggle-accessing @subsection BLOX.BToggle:@- accessing @table @b @meindex callback:@-message:@- @item callback:@- aReceiver message:@- aSymbol Set up so that aReceiver is sent the aSymbol message (the name of a selector accepting at most two arguments) when the receiver is clicked. If the method accepts two arguments, the receiver is passed as the first parameter. If the method accepts one or two arguments, the state of the widget (true if it is selected, false if it is not) is passed as the last parameter. @meindex invokeCallback @item invokeCallback Generate a synthetic callback. @meindex value @item value Answer whether the button is in a selected (checked) state. @meindex value:@- @item value:@- aBoolean Set whether the button is in a selected (checked) state and generates a callback accordingly. @meindex variable:@- @item variable:@- value Set the value of Tk's variable option for the widget. @end table @node BLOX.BTransientWindow @section BLOX.BTransientWindow @clindex BLOX.BTransientWindow @table @b @item Defined in namespace BLOX @itemx Superclass: BLOX.BWindow @itemx Category: Graphics-Windows I am almost a boss. I represent a window which is logically linked to another which sits higher in the widget hierarchy, e.g. a dialog box @end table @menu * BLOX.BTransientWindow class-instance creation:: (class) * BLOX.BTransientWindow-widget protocol:: (instance) @end menu @node BLOX.BTransientWindow class-instance creation @subsection BLOX.BTransientWindow class:@- instance creation @table @b @meindex new @item new This method should not be called for instances of this class. @meindex new:@- @item new:@- parentWindow Answer a new transient window attached to the given parent window and with nothing in its title bar caption. @meindex new:@-in:@- @item new:@- label in:@- parentWindow Answer a new transient window attached to the given parent window and with `label' as its title bar caption. @end table @node BLOX.BTransientWindow-widget protocol @subsection BLOX.BTransientWindow:@- widget protocol @table @b @meindex map @item map Map the window and inform the windows manager that the receiver is a transient window working on behalf of its parent. The window is also put in its parent window's window group:@- the window manager might use this information, for example, to unmap all of the windows in a group when the group's leader is iconified. @end table @node BLOX.BViewport @section BLOX.BViewport @clindex BLOX.BViewport @table @b @item Defined in namespace BLOX @itemx Superclass: BLOX.BPrimitive @itemx Category: Graphics-Windows I represent an interface which is common to widgets that can be scrolled, like list boxes or text widgets. @end table @menu * BLOX.BViewport-accessing:: (instance) * BLOX.BViewport-scrollbars:: (instance) @end menu @node BLOX.BViewport-accessing @subsection BLOX.BViewport:@- accessing @table @b @meindex connected @item connected Private - Answer the name of Tk widget for the connected widget. @end table @node BLOX.BViewport-scrollbars @subsection BLOX.BViewport:@- scrollbars @table @b @meindex horizontal @item horizontal Answer whether an horizontal scrollbar is drawn in the widget if needed. @meindex horizontal:@- @item horizontal:@- aBoolean Set whether an horizontal scrollbar is drawn in the widget if needed. @meindex horizontalNeeded @item horizontalNeeded Answer whether an horizontal scrollbar is needed to show all the information in the widget. @meindex horizontalShown @item horizontalShown Answer whether an horizontal scrollbar is drawn in the widget. @meindex vertical @item vertical Answer whether a vertical scrollbar is drawn in the widget if needed. @meindex vertical:@- @item vertical:@- aBoolean Set whether a vertical scrollbar is drawn in the widget if needed. @meindex verticalNeeded @item verticalNeeded Answer whether a vertical scrollbar is needed to show all the information in the widget. @meindex verticalShown @item verticalShown Answer whether a vertical scrollbar is drawn in the widget. @end table @node BLOX.BWidget @section BLOX.BWidget @clindex BLOX.BWidget @table @b @item Defined in namespace BLOX @itemx Superclass: BLOX.Blox @itemx Category: Graphics-Windows I am the superclass for every widget except those related to menus. I provide more common methods and geometry management @end table @menu * BLOX.BWidget class-popups:: (class) * BLOX.BWidget-accessing:: (instance) * BLOX.BWidget-customization:: (instance) * BLOX.BWidget-geometry management:: (instance) * BLOX.BWidget-widget protocol:: (instance) @end menu @node BLOX.BWidget class-popups @subsection BLOX.BWidget class:@- popups @table @b @meindex new @slindex destroy @item new Create an instance of the receiver inside a BPopupWindow; do not map the window, answer the new widget. The created widget will become a child of the window and be completely attached to it (e.g. the geometry methods will modify the window's geometry). Note that while the widget *seems* to be directly painted on the root window, it actually belongs to the BPopupWindow; so don't send #destroy to the widget to remove it, but rather to the window. @meindex popup:@- @slindex destroy @item popup:@- initializationBlock Create an instance of the receiver inside a BPopupWindow; before returning, pass the widget to the supplied initializationBlock, then map the window. Answer the new widget. The created widget will become a child of the window and be completely attached to it (e.g. the geometry methods will modify the window's geometry). Note that while the widget *seems* to be directly painted on the root window, it actually belongs to the BPopupWindow; so don't send #destroy to the widget to remove it, but rather to the window. @end table @node BLOX.BWidget-accessing @subsection BLOX.BWidget:@- accessing @table @b @meindex borderWidth @item borderWidth Answer the value of the borderWidth option for the widget. Specifies a non-negative value indicating the width of the 3-D border to draw around the outside of the widget (if such a border is being drawn; the effect option typically determines this). The value may also be used when drawing 3-D effects in the interior of the widget. The value is measured in pixels. @meindex borderWidth:@- @item borderWidth:@- value Set the value of the borderWidth option for the widget. Specifies a non-negative value indicating the width of the 3-D border to draw around the outside of the widget (if such a border is being drawn; the effect option typically determines this). The value may also be used when drawing 3-D effects in the interior of the widget. The value is measured in pixels. @meindex cursor @item cursor Answer the value of the cursor option for the widget. Specifies the mouse cursor to be used for the widget. The value of the option is given by the standard X cursor cursor, i.e., any of the names defined in cursorcursor.h, without the leading XC_. @meindex cursor:@- @item cursor:@- value Set the value of the cursor option for the widget. Specifies the mouse cursor to be used for the widget. The value of the option is given by the standard X cursor cursor, i.e., any of the names defined in cursorcursor.h, without the leading XC_. @meindex effect @item effect Answer the value of the effect option for the widget. Specifies the effect desired for the widget's border. Acceptable values are raised, sunken, flat, ridge, solid, and groove. The value indicates how the interior of the widget should appear relative to its exterior; for example, raised means the interior of the widget should appear to protrude from the screen, relative to the exterior of the widget. Raised and sunken give the traditional 3-D appearance (for example, that of Xaw3D), while ridge and groove give a ``chiseled'' appearance like that of Swing or GTK+'s Metal theme. Flat and solid are not 3-D. @meindex effect:@- @item effect:@- value Set the value of the effect option for the widget. Specifies the effect desired for the widget's border. Acceptable values are raised, sunken, flat, ridge, solid, and groove. The value indicates how the interior of the widget should appear relative to its exterior; for example, raised means the interior of the widget should appear to protrude from the screen, relative to the exterior of the widget. Raised and sunken give the traditional 3-D appearance (for example, that of Xaw3D), while ridge and groove give a ``chiseled'' appearance like that of Swing or GTK+'s Metal theme. Flat and solid are not 3-D. @meindex tabStop @item tabStop Answer the value of the tabStop option for the widget. Determines whether the window accepts the focus during keyboard traversal (e.g., Tab and Shift-Tab). Before setting the focus to a window, Blox consults the value of the tabStop option. A value of false means that the window should be skipped entirely during keyboard traversal. true means that the window should receive the input focus as long as it is viewable (it and all of its ancestors are mapped). If you do not set this option, Blox makes the decision about whether or not to focus on the window:@- the current algorithm is to skip the window if it is disabled, it has no key bindings, or if it is not viewable. Of the standard widgets, BForm, BContainer, BLabel and BImage have no key bindings by default. @meindex tabStop:@- @item tabStop:@- value Set the value of the tabStop option for the widget. Determines whether the window accepts the focus during keyboard traversal (e.g., Tab and Shift-Tab). Before setting the focus to a window, Blox consults the value of the tabStop option. A value of false means that the window should be skipped entirely during keyboard traversal. true means that the window should receive the input focus as long as it is viewable (it and all of its ancestors are mapped). If you do not set this option, Blox makes the decision about whether or not to focus on the window:@- the current algorithm is to skip the window if it is disabled, it has no key bindings, or if it is not viewable. Of the standard widgets, BForm, BContainer, BLabel and BImage have no key bindings by default. @end table @node BLOX.BWidget-customization @subsection BLOX.BWidget:@- customization @table @b @meindex addChild:@- @item addChild:@- child The widget identified by child has been added to the receiver. This method is public not because you can call it, but because it can be useful to override it, not forgetting the call to basicAddChild, to perform some initialization on the children just added. Answer the new child. @meindex create @item create Make the receiver able to respond to its widget protocol. This method is public not because you can call it, but because it can be useful to override it, not forgetting the call to super, to perform some initialization on the primitive widget just created; for an example of this, see the implementation of BButtonLike. @meindex initialize:@- @slindex new:@- @item initialize:@- parentWidget This is called by #new:@- to initialize the widget (as the name says...). The default implementation calls all the other methods in the `customization' protocol and some private ones that take care of making the receiver's status consistent, so you should usually call it instead of doing everything by hand. This method is public not because you can call it, but because it might be useful to override it. Always answer the receiver. @meindex setInitialSize @slindex initialize:@- @item setInitialSize This is called by #initialize:@- to set the widget's initial size. The whole area is occupied by default. This method is public not because you can call it, but because it can be useful to override it. @end table @node BLOX.BWidget-geometry management @subsection BLOX.BWidget:@- geometry management @table @b @meindex boundingBox @item boundingBox Answer a Rectangle containing the bounding box of the receiver @meindex boundingBox:@- @item boundingBox:@- rect Set the bounding box of the receiver to rect (a Rectangle). @meindex child:@-height:@- @slindex height @slindex height:@- @item child:@- child height:@- value Set the given child's height to value. The default implementation of this method uses `rubber-sheet' geometry management as explained in the comment to BWidget's #height method. You should not use this method, which is automatically called by the child's #height:@- method, but you might want to override it. The child's property slots whose name ends with `Geom' are reserved for this method. This method should never fail -- if it doesn't apply to the kind of geometry management that the receiver does, just do nothing. @meindex child:@-heightOffset:@- @slindex height @slindex heightOffset:@- @slindex heightOffset:@- @item child:@- child heightOffset:@- value Adjust the given child's height by a fixed amount of value pixel. This is meaningful for the default implementation, using `rubber-sheet' geometry management as explained in the comment to BWidget's #height and #heightOffset:@- methods. You should not use this method, which is automatically called by the child's #heightOffset:@- method, but you might want to override it. if it doesn't apply to the kind of geometry management that the receiver does, just add value to the current height of the widget. @meindex child:@-stretch:@- @item child:@- child stretch:@- aBoolean This method is only used when on the path from the receiver to its toplevel there is a BContainer. It decides whether child is among the widgets that are stretched to fill the entire width of the BContainer; if this has not been set for this widget, it is propagated along the widget hierarchy. @meindex child:@-width:@- @slindex width @slindex width:@- @item child:@- child width:@- value Set the given child's width to value. The default implementation of this method uses `rubber-sheet' geometry management as explained in the comment to BWidget's #width method. You should not use this method, which is automatically called by the child's #width:@- method, but you might want to override it. The child's property slots whose name ends with `Geom' are reserved for this method. This method should never fail -- if it doesn't apply to the kind of geometry management that the receiver does, just do nothing. @meindex child:@-widthOffset:@- @slindex width @slindex widthOffset:@- @slindex widthOffset:@- @item child:@- child widthOffset:@- value Adjust the given child's width by a fixed amount of value pixel. This is meaningful for the default implementation, using `rubber-sheet' geometry management as explained in the comment to BWidget's #width and #widthOffset:@- methods. You should not use this method, which is automatically called by the child's #widthOffset:@- method, but you might want to override it. if it doesn't apply to the kind of geometry management that the receiver does, just add value to the current width of the widget. @meindex child:@-x:@- @slindex x @slindex x:@- @item child:@- child x:@- value Set the given child's x to value. The default implementation of this method uses `rubber-sheet' geometry management as explained in the comment to BWidget's #x method. You should not use this method, which is automatically called by the child's #x:@- method, but you might want to override it. The child's property slots whose name ends with `Geom' are reserved for this method. This method should never fail -- if it doesn't apply to the kind of geometry management that the receiver does, just do nothing. @meindex child:@-xOffset:@- @slindex x @slindex xOffset:@- @slindex xOffset:@- @item child:@- child xOffset:@- value Adjust the given child's x by a fixed amount of value pixel. This is meaningful for the default implementation, using `rubber-sheet' geometry management as explained in the comment to BWidget's #x and #xOffset:@- methods. You should not use this method, which is automatically called by the child's #xOffset:@- method, but you might want to override it. if it doesn't apply to the kind of geometry management that the receiver does, just add value to the current x of the widget. @meindex child:@-y:@- @slindex y @slindex y:@- @item child:@- child y:@- value Set the given child's y to value. The default implementation of this method uses `rubber-sheet' geometry management as explained in the comment to BWidget's #y method. You should not use this method, which is automatically called by the child's #y:@- method, but you might want to override it. The child's property slots whose name ends with `Geom' are reserved for this method. This method should never fail -- if it doesn't apply to the kind of geometry management that the receiver does, just do nothing. @meindex child:@-yOffset:@- @slindex y @slindex yOffset:@- @slindex yOffset:@- @item child:@- child yOffset:@- value Adjust the given child's y by a fixed amount of value pixel. This is meaningful for the default implementation, using `rubber-sheet' geometry management as explained in the comment to BWidget's #y and #yOffset:@- methods. You should not use this method, which is automatically called by the child's #yOffset:@- method, but you might want to override it. if it doesn't apply to the kind of geometry management that the receiver does, just add value to the current y of the widget. @meindex extent @item extent Answer a Point containing the receiver's size @meindex extent:@- @item extent:@- extent Set the receiver's size to the width and height contained in extent (a Point). @meindex height @slindex heightOffset:@- @item height Answer the `variable' part of the receiver's height within the parent widget. The value returned does not include any fixed amount of pixels indicated by #heightOffset:@- and must be interpreted in a relative fashion:@- the ratio of the returned value to the current size of the parent will be preserved upon resize. This apparently complicated method is known as `rubber sheet' geometry management. Behavior if the left or right edges are not within the client area of the parent is not defined -- the window might be clamped or might be positioned according to the specification. @meindex height:@- @item height:@- value Set to `value' the height of the widget within the parent widget. The value is specified in a relative fashion as an integer, so that the ratio of `value' to the current size of the parent will be preserved upon resize. This apparently complicated method is known as `rubber sheet' geometry management. @meindex heightAbsolute @item heightAbsolute Force a recalculation of the layout of widgets in the receiver's parent, then answer the current height of the receiver in pixels. @meindex heightChild:@- @slindex height @slindex height @item heightChild:@- child Answer the given child's height. The default implementation of this method uses `rubber-sheet' geometry management as explained in the comment to BWidget's #height method. You should not use this method, which is automatically called by the child's #height method, but you might want to override. The child's property slots whose name ends with `Geom' are reserved for this method. This method should never fail -- if it doesn't apply to the kind of geometry management that the receiver does, just return 0. @meindex heightOffset @slindex height:@- @item heightOffset Private - Answer the pixels to be added or subtracted to the height of the receiver, with respect to the value set in a relative fashion through the #height:@- method. @meindex heightOffset:@- @slindex height:@- @slindex inset:@- @item heightOffset:@- value Add or subtract to the height of the receiver a fixed amount of `value' pixels, with respect to the value set in a relative fashion through the #height:@- method. Usage of this method is deprecated; use #inset:@- and BContainers instead. @meindex heightPixels:@- @slindex height @slindex height @slindex height:@- @item heightPixels:@- value Set the current height of the receiver to `value' pixels. Note that, after calling this method, #height will answer 0, which is logical considering that there is no `variable' part of the size (refer to #height and #height:@- for more explanations). @meindex inset:@- @item inset:@- pixels Inset the receiver's bounding box by the specified amount. @meindex left:@-top:@-right:@-bottom:@- @item left:@- left top:@- top right:@- right bottom:@- bottom Set the bounding box of the receiver through its components. @meindex pos:@- @item pos:@- position Set the receiver's origin to the width and height contained in position (a Point). @meindex posHoriz:@- @item posHoriz:@- aBlox Position the receiver immediately to the right of aBlox. @meindex posVert:@- @item posVert:@- aBlox Position the receiver just below aBlox. @meindex stretch:@- @item stretch:@- aBoolean This method is only considered when on the path from the receiver to its toplevel there is a BContainer. It decides whether we are among the widgets that are stretched to fill the entire width of the BContainer. @meindex width @slindex widthOffset:@- @item width Answer the `variable' part of the receiver's width within the parent widget. The value returned does not include any fixed amount of pixels indicated by #widthOffset:@- and must be interpreted in a relative fashion:@- the ratio of the returned value to the current size of the parent will be preserved upon resize. This apparently complicated method is known as `rubber sheet' geometry management. Behavior if the left or right edges are not within the client area of the parent is not defined -- the window might be clamped or might be positioned according to the specification. @meindex width:@- @item width:@- value Set to `value' the width of the widget within the parent widget. The value is specified in a relative fashion as an integer, so that the ratio of `value' to the current size of the parent will be preserved upon resize. This apparently complicated method is known as `rubber sheet' geometry management. @meindex width:@-height:@- @item width:@- xSize height:@- ySize Set the size of the receiver through its components xSize and ySize. @meindex widthAbsolute @item widthAbsolute Force a recalculation of the layout of widgets in the receiver's parent, then answer the current width of the receiver in pixels. @meindex widthChild:@- @slindex width @slindex width @item widthChild:@- child Answer the given child's width. The default implementation of this method uses `rubber-sheet' geometry management as explained in the comment to BWidget's #width method. You should not use this method, which is automatically called by the child's #width method, but you might want to override. The child's property slots whose name ends with `Geom' are reserved for this method. This method should never fail -- if it doesn't apply to the kind of geometry management that the receiver does, just return 0. @meindex widthOffset @slindex width:@- @item widthOffset Private - Answer the pixels to be added or subtracted to the width of the receiver, with respect to the value set in a relative fashion through the #width:@- method. @meindex widthOffset:@- @slindex width:@- @slindex inset:@- @item widthOffset:@- value Add or subtract to the width of the receiver a fixed amount of `value' pixels, with respect to the value set in a relative fashion through the #width:@- method. Usage of this method is deprecated; use #inset:@- and BContainers instead. @meindex widthPixels:@- @slindex width @slindex width @slindex width:@- @item widthPixels:@- value Set the current width of the receiver to `value' pixels. Note that, after calling this method, #width will answer 0, which is logical considering that there is no `variable' part of the size (refer to #width and #width:@- for more explanations). @meindex x @slindex xOffset:@- @item x Answer the `variable' part of the receiver's x within the parent widget. The value returned does not include any fixed amount of pixels indicated by #xOffset:@- and must be interpreted in a relative fashion:@- the ratio of the returned value to the current size of the parent will be preserved upon resize. This apparently complicated method is known as `rubber sheet' geometry management. Behavior if the left or right edges are not within the client area of the parent is not defined -- the window might be clamped or might be positioned according to the specification. @meindex x:@- @item x:@- value Set to `value' the x of the widget within the parent widget. The value is specified in a relative fashion as an integer, so that the ratio of `value' to the current size of the parent will be preserved upon resize. This apparently complicated method is known as `rubber sheet' geometry management. @meindex x:@-y:@- @item x:@- xPos y:@- yPos Set the origin of the receiver through its components xPos and yPos. @meindex x:@-y:@-width:@-height:@- @item x:@- xPos y:@- yPos width:@- xSize height:@- ySize Set the bounding box of the receiver through its origin and size. @meindex xAbsolute @item xAbsolute Force a recalculation of the layout of widgets in the receiver's parent, then answer the current x of the receiver in pixels. @meindex xChild:@- @slindex x @slindex x @item xChild:@- child Answer the given child's x. The default implementation of this method uses `rubber-sheet' geometry management as explained in the comment to BWidget's #x method. You should not use this method, which is automatically called by the child's #x method, but you might want to override. The child's property slots whose name ends with `Geom' are reserved for this method. This method should never fail -- if it doesn't apply to the kind of geometry management that the receiver does, just return 0. @meindex xOffset @slindex x:@- @item xOffset Private - Answer the pixels to be added or subtracted to the x of the receiver, with respect to the value set in a relative fashion through the #x:@- method. @meindex xOffset:@- @slindex x:@- @slindex inset:@- @item xOffset:@- value Add or subtract to the x of the receiver a fixed amount of `value' pixels, with respect to the value set in a relative fashion through the #x:@- method. Usage of this method is deprecated; use #inset:@- and BContainers instead. @meindex xPixels:@- @slindex x @slindex x @slindex x:@- @item xPixels:@- value Set the current x of the receiver to `value' pixels. Note that, after calling this method, #x will answer 0, which is logical considering that there is no `variable' part of the size (refer to #x and #x:@- for more explanations). @meindex xRoot @item xRoot Answer the x position of the receiver with respect to the top-left corner of the desktop (including the offset of the virtual root window under X). @meindex y @slindex yOffset:@- @item y Answer the `variable' part of the receiver's y within the parent widget. The value returned does not include any fixed amount of pixels indicated by #yOffset:@- and must be interpreted in a relative fashion:@- the ratio of the returned value to the current size of the parent will be preserved upon resize. This apparently complicated method is known as `rubber sheet' geometry management. Behavior if the left or right edges are not within the client area of the parent is not defined -- the window might be clamped or might be positioned according to the specification. @meindex y:@- @item y:@- value Set to `value' the y of the widget within the parent widget. The value is specified in a relative fashion as an integer, so that the ratio of `value' to the current size of the parent will be preserved upon resize. This apparently complicated method is known as `rubber sheet' geometry management. @meindex yAbsolute @item yAbsolute Force a recalculation of the layout of widgets in the receiver's parent, then answer the current y of the receiver in pixels. @meindex yChild:@- @slindex y @slindex y @item yChild:@- child Answer the given child's y. The default implementation of this method uses `rubber-sheet' geometry management as explained in the comment to BWidget's #y method. You should not use this method, which is automatically called by the child's #y method, but you might want to override. The child's property slots whose name ends with `Geom' are reserved for this method. This method should never fail -- if it doesn't apply to the kind of geometry management that the receiver does, just return 0. @meindex yOffset @slindex y:@- @item yOffset Private - Answer the pixels to be added or subtracted to the y of the receiver, with respect to the value set in a relative fashion through the #y:@- method. @meindex yOffset:@- @slindex y:@- @slindex inset:@- @item yOffset:@- value Add or subtract to the y of the receiver a fixed amount of `value' pixels, with respect to the value set in a relative fashion through the #y:@- method. Usage of this method is deprecated; use #inset:@- and BContainers instead. @meindex yPixels:@- @slindex y @slindex y @slindex y:@- @item yPixels:@- value Set the current y of the receiver to `value' pixels. Note that, after calling this method, #y will answer 0, which is logical considering that there is no `variable' part of the size (refer to #y and #y:@- for more explanations). @meindex yRoot @item yRoot Answer the y position of the receiver with respect to the top-left corner of the desktop (including the offset of the virtual root window under X). @end table @node BLOX.BWidget-widget protocol @subsection BLOX.BWidget:@- widget protocol @table @b @meindex activate @item activate At any given time, one window on each display is designated as the focus window; any key press or key release events for the display are sent to that window. This method allows one to choose which window will have the focus in the receiver's display If the application currently has the input focus on the receiver's display, this method resets the input focus for the receiver's display to the receiver. If the application doesn't currently have the input focus on the receiver's display, Blox will remember the receiver as the focus for its top-level; the next time the focus arrives at the top-level, it will be redirected to the receiver (this is because most window managers will set the focus only to top-level windows, leaving it up to the application to redirect the focus among the children of the top-level). @meindex activateNext @slindex tabStop:@- @item activateNext Activate the next widget in the focus `tabbing' order. The focus order depends on the widget creation order; you can set which widgets are in the order with the #tabStop:@- method. @meindex activatePrevious @slindex tabStop:@- @item activatePrevious Activate the previous widget in the focus `tabbing' order. The focus order depends on the widget creation order; you can set which widgets are in the order with the #tabStop:@- method. @meindex bringToTop @item bringToTop Raise the receiver so that it is above all of its siblings in the widgets' z-order; the receiver will not be obscured by any siblings and will obscure any siblings that overlap it. @meindex isActive @item isActive Return whether the receiver is the window that currently owns the focus on its display. @meindex sendToBack @item sendToBack Lower the receiver so that it is below all of its siblings in the widgets' z-order; the receiver will be obscured by any siblings that overlap it and will not obscure any siblings. @end table @node BLOX.BWindow @section BLOX.BWindow @clindex BLOX.BWindow @table @b @item Defined in namespace BLOX @itemx Superclass: BLOX.BForm @itemx Category: Graphics-Windows I am the boss. Nothing else could be viewed or interacted with if it wasn't for me... )):@--> @end table @menu * BLOX.BWindow class-instance creation:: (class) * BLOX.BWindow-accessing:: (instance) * BLOX.BWindow-widget protocol:: (instance) @end menu @node BLOX.BWindow class-instance creation @subsection BLOX.BWindow class:@- instance creation @table @b @meindex new @item new Answer a new top-level window. @meindex new:@- @item new:@- label Answer a new top-level window with `label' as its title bar caption. @meindex popup:@- @item popup:@- initializationBlock This method should not be called for instances of this class. @end table @node BLOX.BWindow-accessing @subsection BLOX.BWindow:@- accessing @table @b @meindex callback @item callback Answer a DirectedMessage that is sent to verify whether the receiver must be destroyed when the user asks to unmap it. @meindex callback:@-message:@- @item callback:@- aReceiver message:@- aSymbol Set up so that aReceiver is sent the aSymbol message (the name of a zero- or one-argument selector) when the user asks to unmap the receiver. If the method accepts an argument, the receiver is passed. If the method returns true, the window and its children are destroyed (which is the default action, taken if no callback is set up). If the method returns false, the window is left in place. @meindex invokeCallback @item invokeCallback Generate a synthetic callback, destroying the window if no callback was set up or if the callback method answers true. @meindex label @item label Answer the value of the label option for the widget. Specifies a string to be displayed inside the widget. The way in which the string is displayed depends on the particular widget and may be determined by other options, such as anchor. For windows, this is the title of the window. @meindex label:@- @item label:@- value Set the value of the label option for the widget. Specifies a string to be displayed inside the widget. The way in which the string is displayed depends on the particular widget and may be determined by other options, such as anchor. For windows, this is the title of the window. @meindex menu:@- @item menu:@- value Set the value of the menu option for the widget. Specifies a menu widget to be used as a menubar. On the Macintosh, the menubar will be displayed accross the top of the main monitor. On Microsoft Windows and all UNIX platforms, the menu will appear accross the toplevel window as part of the window dressing maintained by the window manager. @meindex resizable @item resizable Answer the value of the resizable option for the widget. Answer whether the user can be resize the window or not. If resizing is disabled, then the window's size will be the size from the most recent interactive resize or geometry-setting method. If there has been no such operation then the window's natural size will be used. @meindex resizable:@- @item resizable:@- value Set the value of the resizable option for the widget. Answer whether the user can be resize the window or not. If resizing is disabled, then the window's size will be the size from the most recent interactive resize or geometry-setting method. If there has been no such operation then the window's natural size will be used. @end table @node BLOX.BWindow-widget protocol @subsection BLOX.BWindow:@- widget protocol @table @b @meindex center @item center Center the window in the screen @meindex centerIn:@- @item centerIn:@- view Center the window in the given widget @meindex height @item height Answer the height of the window, as deduced from the geometry that the window manager imposed on the window. @meindex height:@- @item height:@- anInteger Ask the window manager to give the given height to the window. @meindex heightAbsolute @item heightAbsolute Answer the height of the window, as deduced from the geometry that the window manager imposed on the window. @meindex heightOffset:@- @item heightOffset:@- value This method should not be called for instances of this class. @meindex iconify @item iconify Map a window and in iconified state. If a window has not been mapped yet, this is achieved by mapping the window in withdrawn state first, and then iconifying it. @meindex isMapped @item isMapped Answer whether the window is mapped @meindex isWindow @item isWindow Answer `true'. @meindex map @item map Map the window and bring it to the topmost position in the Z-order. @meindex modalMap @item modalMap Map the window while establishing an application-local grab for it. An event loop is started that ends only after the window has been destroyed. When a grab is set for a particular window, all pointer events are restructed to the grab window and its descendants in Blox's window hierarchy. Whenever the pointer is within the grab window's subtree, the pointer will behave exactly the same as if there had been no grab grab at all and all events will be reported in the normal fashion. When the pointer is outside the window's tree, button presses and releases and mouse motion events are reported to the grabbing window, and window entry and window exit events are ignored. In other words, windows outside the grab subtree will be visible on the screen but they will be insensitive until the grab is released. The tree of windows underneath the grab window can include top-level windows, in which case all of those top-level windows and their descendants will continue to receive mouse events during the grab. Keyboard events (key presses and key releases) are delivered as usual:@- the window manager controls which application receives keyboard events, and if they are sent to any window in the grabbing application then they are redirected to the window owning the focus. @meindex state @item state Set the value of the state option for the window. Specifies one of four states for the window:@- either normal, iconic, withdrawn, or (Windows only) zoomed. @meindex state:@- @slindex map @slindex unmap @item state:@- aSymbol Raise an error. To set a BWindow's state, use #map and #unmap. @meindex unmap @item unmap Unmap a window, causing it to be forgotten about by the window manager @meindex width @item width Answer the width of the window, as deduced from the geometry that the window manager imposed on the window. @meindex width:@- @item width:@- anInteger Ask the window manager to give the given width to the window. @meindex width:@-height:@- @item width:@- xSize height:@- ySize Ask the window manager to give the given width and height to the window. @meindex widthAbsolute @item widthAbsolute Answer the width of the window, as deduced from the geometry that the window manager imposed on the window. @meindex widthOffset:@- @item widthOffset:@- value This method should not be called for instances of this class. @meindex window @item window Answer the receiver. @meindex x @item x Answer the x coordinate of the window's top-left corner, as deduced from the geometry that the window manager imposed on the window. @meindex x:@- @item x:@- anInteger Ask the window manager to move the window's left border to the given x coordinate, keeping the size unchanged @meindex x:@-y:@- @item x:@- xPos y:@- yPos Ask the window manager to move the window's top-left corner to the given coordinates, keeping the size unchanged @meindex x:@-y:@-width:@-height:@- @item x:@- xPos y:@- yPos width:@- xSize height:@- ySize Ask the window manager to give the requested geometry to the window. @meindex xAbsolute @item xAbsolute Answer the x coordinate of the window's top-left corner, as deduced from the geometry that the window manager imposed on the window. @meindex xOffset:@- @item xOffset:@- value This method should not be called for instances of this class. @meindex y @item y Answer the y coordinate of the window's top-left corner, as deduced from the geometry that the window manager imposed on the window. @meindex y:@- @item y:@- anInteger Ask the window manager to move the window's left border to the given y coordinate, keeping the size unchanged @meindex yAbsolute @item yAbsolute Answer the y coordinate of the window's top-left corner, as deduced from the geometry that the window manager imposed on the window. @meindex yOffset:@- @item yOffset:@- value This method should not be called for instances of this class. @end table @node BLOX.Gui @section BLOX.Gui @clindex BLOX.Gui @table @b @item Defined in namespace BLOX @itemx Superclass: Object @itemx Category: Graphics-Windows I am a small class which serves as a base for complex objects which expose an individual protocol but internally use a Blox widget for creating their user interface. @end table @menu * BLOX.Gui-accessing:: (instance) @end menu @node BLOX.Gui-accessing @subsection BLOX.Gui:@- accessing @table @b @meindex blox @item blox Return instance of blox subclass which implements window @meindex blox:@- @item blox:@- aBlox Set instance of blox subclass which implements window @end table smalltalk-3.2.5/doc/gst-base.info-20000644000175000017500000111307012130456007013715 00000000000000This is gst-base.info, produced by makeinfo version 4.13 from /home/ich/source/smalltalk/release/smalltalk/doc/gst-base-fixed.texi. INFO-DIR-SECTION Software development START-INFO-DIR-ENTRY * Smalltalk base classes: (gst-base). The GNU Smalltalk base classes. END-INFO-DIR-ENTRY Permission is granted to copy, distribute and/or modify this document under the terms of the GNU Free Documentation License, Version 1.2 or any later version published by the Free Software Foundation; with no Invariant Sections, with no Front-Cover Texts, and with no Back-Cover Texts. A copy of the license is included in the section entitled "GNU Free Documentation License".  File: gst-base.info, Node: Exception-exception signaling, Next: Exception-still unclassified, Prev: Exception-exception handling, Up: Exception 1.72.11 Exception: exception signaling -------------------------------------- signal Raise the exceptional event represented by the receiver signal: messageText Raise the exceptional event represented by the receiver, setting its message text to messageText.  File: gst-base.info, Node: Exception-still unclassified, Prev: Exception-exception signaling, Up: Exception 1.72.12 Exception: still unclassified ------------------------------------- signalingContext Return the execution context for the place that signaled the exception, or nil if it is not available anymore (for example if the exception handler has returned.  File: gst-base.info, Node: ExceptionSet, Next: False, Prev: Exception, Up: Base classes 1.73 ExceptionSet ================= Defined in namespace Smalltalk Superclass: Object Category: Language-Exceptions My instances are not real exceptions: they can only be used as arguments to #on:do:... methods in BlockClosure. They act as shortcuts that allows you to use the same handler for many exceptions without having to write duplicate code * Menu: * ExceptionSet class-instance creation:: (class) * ExceptionSet-enumerating:: (instance) * ExceptionSet-instance creation:: (instance)  File: gst-base.info, Node: ExceptionSet class-instance creation, Next: ExceptionSet-enumerating, Up: ExceptionSet 1.73.1 ExceptionSet class: instance creation -------------------------------------------- new Private - Answer a new, empty ExceptionSet  File: gst-base.info, Node: ExceptionSet-enumerating, Next: ExceptionSet-instance creation, Prev: ExceptionSet class-instance creation, Up: ExceptionSet 1.73.2 ExceptionSet: enumerating -------------------------------- allExceptionsDo: aBlock Private - Evaluate aBlock for every exception in the receiver. Answer the receiver goodness: exception Answer how good the receiver is at handling the given exception. A negative value indicates that the receiver is not able to handle the exception. handles: exception Answer whether the receiver handles `exception'.  File: gst-base.info, Node: ExceptionSet-instance creation, Prev: ExceptionSet-enumerating, Up: ExceptionSet 1.73.3 ExceptionSet: instance creation -------------------------------------- , aTrappableEvent Answer an ExceptionSet containing all the exceptions in the receiver and all the exceptions in aTrappableEvent  File: gst-base.info, Node: False, Next: File, Prev: ExceptionSet, Up: Base classes 1.74 False ========== Defined in namespace Smalltalk Superclass: Boolean Category: Language-Data types I always tell lies. I have a single instance in the system, which represents the value false. * Menu: * False-basic:: (instance) * False-C hacks:: (instance) * False-printing:: (instance)  File: gst-base.info, Node: False-basic, Next: False-C hacks, Up: False 1.74.1 False: basic ------------------- & aBoolean We are false - anded with anything, we always answer false and: aBlock We are false - anded with anything, we always answer false eqv: aBoolean Answer whether the receiver and aBoolean represent the same boolean value ifFalse: falseBlock We are false - evaluate the falseBlock ifFalse: falseBlock ifTrue: trueBlock We are false - evaluate the falseBlock ifTrue: trueBlock We are false - answer nil ifTrue: trueBlock ifFalse: falseBlock We are false - evaluate the falseBlock not We are false - answer true or: aBlock We are false - ored with anything, we always answer the other operand, so evaluate aBlock xor: aBoolean Answer whether the receiver and aBoolean represent different boolean values | aBoolean We are false - ored with anything, we always answer the other operand  File: gst-base.info, Node: False-C hacks, Next: False-printing, Prev: False-basic, Up: False 1.74.2 False: C hacks --------------------- asCBooleanValue Answer `0'.  File: gst-base.info, Node: False-printing, Prev: False-C hacks, Up: False 1.74.3 False: printing ---------------------- printOn: aStream Print a representation of the receiver on aStream  File: gst-base.info, Node: File, Next: FileDescriptor, Prev: False, Up: Base classes 1.75 File ========= Defined in namespace Smalltalk Superclass: FilePath Category: Streams-Files I enable access to the properties of files that are on disk. * Menu: * File class-C functions:: (class) * File class-file operations:: (class) * File class-initialization:: (class) * File class-instance creation:: (class) * File class-reading system defaults:: (class) * File class-testing:: (class) * File-accessing:: (instance) * File-basic:: (instance) * File-directory operations:: (instance) * File-file name management:: (instance) * File-file operations:: (instance) * File-still unclassified:: (instance) * File-testing:: (instance)  File: gst-base.info, Node: File class-C functions, Next: File class-file operations, Up: File 1.75.1 File class: C functions ------------------------------ errno Answer the current value of C errno. stringError: errno Answer C strerror's result for errno.  File: gst-base.info, Node: File class-file operations, Next: File class-initialization, Prev: File class-C functions, Up: File 1.75.2 File class: file operations ---------------------------------- checkError Return whether an error had been reported or not. If there had been one, raise an exception too checkError: errno The error with the C code `errno' has been reported. If errno >= 1, raise an exception remove: fileName Remove the file with the given path name rename: oldFileName to: newFileName Rename the file with the given path name oldFileName to newFileName symlink: srcName as: destName Create a symlink for the srcName file with the given path name symlink: destName from: srcName Create a symlink named destName file from the given path (relative to destName) touch: fileName Update the timestamp of the file with the given path name.  File: gst-base.info, Node: File class-initialization, Next: File class-instance creation, Prev: File class-file operations, Up: File 1.75.3 File class: initialization --------------------------------- initialize Initialize the receiver's class variables  File: gst-base.info, Node: File class-instance creation, Next: File class-reading system defaults, Prev: File class-initialization, Up: File 1.75.4 File class: instance creation ------------------------------------ name: aName Answer a new file with the given path. The path is turned into an absolute path. path: aString Answer a new file with the given path. The path is not validated until some of the fields of the newly created objects are accessed  File: gst-base.info, Node: File class-reading system defaults, Next: File class-testing, Prev: File class-instance creation, Up: File 1.75.5 File class: reading system defaults ------------------------------------------ executable Answer the full path to the executable being run. image Answer the full path to the image being used.  File: gst-base.info, Node: File class-testing, Next: File-accessing, Prev: File class-reading system defaults, Up: File 1.75.6 File class: testing -------------------------- exists: fileName Answer whether a file with the given name exists isAccessible: fileName Answer whether a directory with the given name exists and can be accessed isExecutable: fileName Answer whether a file with the given name exists and can be executed isReadable: fileName Answer whether a file with the given name exists and is readable isWriteable: fileName Answer whether a file with the given name exists and is writeable  File: gst-base.info, Node: File-accessing, Next: File-basic, Prev: File class-testing, Up: File 1.75.7 File: accessing ---------------------- asString Answer the name of the file identified by the receiver at: aString Answer a File or Directory object as appropriate for a file named 'aName' in the directory represented by the receiver. creationTime Answer the creation time of the file identified by the receiver. On some operating systems, this could actually be the last change time (the `last change time' has to do with permissions, ownership and the like). isDirectory Answer whether the file is a directory. isSocket Answer whether the file is an AF_UNIX socket. isSymbolicLink Answer whether the file is a symbolic link. lastAccessTime Answer the last access time of the file identified by the receiver lastChangeTime Answer the last change time of the file identified by the receiver (the `last change time' has to do with permissions, ownership and the like). On some operating systems, this could actually be the file creation time. lastModifyTime Answer the last modify time of the file identified by the receiver (the `last modify time' has to do with the actual file contents). mode Answer the permission bits for the file identified by the receiver mode: anInteger Set the permission bits for the file identified by the receiver to be anInteger. name Answer the name of the file identified by the receiver pathTo: destName Compute the relative path from the receiver to destName. refresh Refresh the statistics for the receiver size Answer the size of the file identified by the receiver  File: gst-base.info, Node: File-basic, Next: File-directory operations, Prev: File-accessing, Up: File 1.75.8 File: basic ------------------ = aFile Answer whether the receiver represents the same file as the receiver. hash Answer a hash value for the receiver.  File: gst-base.info, Node: File-directory operations, Next: File-file name management, Prev: File-basic, Up: File 1.75.9 File: directory operations --------------------------------- createDirectory Create the receiver as a directory. namesDo: aBlock Evaluate aBlock once for each file in the directory represented by the receiver, passing its name. aBlock should not return.  File: gst-base.info, Node: File-file name management, Next: File-file operations, Prev: File-directory operations, Up: File 1.75.10 File: file name management ---------------------------------- full Answer the full name of the receiver, resolving the `.' and `..' directory entries, and answer the result. Answer nil if the name is invalid (such as '/usr/../../badname')  File: gst-base.info, Node: File-file operations, Next: File-still unclassified, Prev: File-file name management, Up: File 1.75.11 File: file operations ----------------------------- lastAccessTime: accessDateTime lastModifyTime: modifyDateTime Set the receiver's timestamps to be accessDateTime and modifyDateTime. open: class mode: mode ifFail: aBlock Open the receiver in the given mode (as answered by FileStream's class constant methods) owner: ownerString group: groupString Set the receiver's owner and group to be ownerString and groupString. pathFrom: dir Compute the relative path from the directory dirName to the receiver remove Remove the file with the given path name renameTo: newFileName Rename the file with the given path name to newFileName symlinkAs: destName Create destName as a symbolic link of the receiver. The appropriate relative path is computed automatically. symlinkFrom: srcName Create the receiver as a symlink from path destName  File: gst-base.info, Node: File-still unclassified, Next: File-testing, Prev: File-file operations, Up: File 1.75.12 File: still unclassified -------------------------------- , aName Answer an object of the same kind as the receiver, whose name is suffixed with aName.  File: gst-base.info, Node: File-testing, Prev: File-still unclassified, Up: File 1.75.13 File: testing --------------------- exists Answer whether a file with the name contained in the receiver does exist. isAbsolute Answer whether the receiver identifies an absolute path. isAccessible Answer whether a directory with the name contained in the receiver does exist and is accessible isExecutable Answer whether a file with the name contained in the receiver does exist and is executable isFileSystemPath Answer whether the receiver corresponds to a real filesystem path. isReadable Answer whether a file with the name contained in the receiver does exist and is readable isWriteable Answer whether a file with the name contained in the receiver does exist and is writeable  File: gst-base.info, Node: FileDescriptor, Next: FilePath, Prev: File, Up: Base classes 1.76 FileDescriptor =================== Defined in namespace Smalltalk Superclass: Stream Category: Streams-Files My instances are what conventional programmers think of as files. My instance creation methods accept the name of a disk file (or any named file object, such as /dev/rmt0 on UNIX or MTA0: on VMS). In addition, they accept a virtual filesystem path like `configure.gz#ugz' which can be used to transparently extract or decompress files from archives, or do arbitrary processing on the files. * Menu: * FileDescriptor class-initialization:: (class) * FileDescriptor class-instance creation:: (class) * FileDescriptor class-still unclassified:: (class) * FileDescriptor-accessing:: (instance) * FileDescriptor-basic:: (instance) * FileDescriptor-binary I/O:: (instance) * FileDescriptor-built ins:: (instance) * FileDescriptor-class type methods:: (instance) * FileDescriptor-initialize-release:: (instance) * FileDescriptor-low-level access:: (instance) * FileDescriptor-overriding inherited methods:: (instance) * FileDescriptor-polymorphism:: (instance) * FileDescriptor-positioning:: (instance) * FileDescriptor-printing:: (instance) * FileDescriptor-testing:: (instance)  File: gst-base.info, Node: FileDescriptor class-initialization, Next: FileDescriptor class-instance creation, Up: FileDescriptor 1.76.1 FileDescriptor class: initialization ------------------------------------------- initialize Initialize the receiver's class variables update: aspect Close open files before quitting  File: gst-base.info, Node: FileDescriptor class-instance creation, Next: FileDescriptor class-still unclassified, Prev: FileDescriptor class-initialization, Up: FileDescriptor 1.76.2 FileDescriptor class: instance creation ---------------------------------------------- append Open for writing. The file is created if it does not exist. The stream is positioned at the end of the file. create Open for reading and writing. The file is created if it does not exist, otherwise it is truncated. The stream is positioned at the beginning of the file. fopen: fileName mode: fileMode Open fileName in the required mode - answered by #append, #create, #readWrite, #read or #write - and fail if the file cannot be opened. Else answer a new FileStream. For mode anyway you can use any standard C non-binary fopen mode. The file will be automatically closed upon GC if the object is not referenced anymore, but it is better to close it as soon as you're finished with it anyway, using #close. To keep a file open even when no references exist anymore, send it #removeToBeFinalized fopen: fileName mode: fileMode ifFail: aBlock Open fileName in the required mode - answered by #append, #create, #readWrite, #read or #write - and evaluate aBlock if the file cannot be opened. Else answer a new FileStream. For mode anyway you can use any The file will be automatically closed upon GC if the object is not referenced anymore, but it is better to close it as soon as you're finished with it anyway, using #close. To keep a file open even when no references exist anymore, send it #removeToBeFinalized on: fd Open a FileDescriptor on the given file descriptor. Read-write access is assumed. open: fileName Open fileName in read-write mode - fail if the file cannot be opened. Else answer a new FileStream. The file will be automatically closed upon GC if the object is not referenced anymore, but you should close it with #close anyway. To keep a file open, send it #removeToBeFinalized open: fileName mode: fileMode ifFail: aBlock Open fileName in the required mode - answered by #append, #create, #readWrite, #read or #write - and evaluate aBlock if the file cannot be opened. Else answer a new instance of the receiver. For mode anyway you can use any standard C non-binary fopen mode. fileName can be a `virtual filesystem' path, including URLs and '#' suffixes that are inspected by the virtual filesystem layers and replaced with tasks such as un-gzipping a file or extracting a file from an archive. The file will be automatically closed upon GC if the object is not referenced anymore, but it is better to close it as soon as you're finished with it anyway, using #close. To keep a file open even when no references exist anymore, send it #removeToBeFinalized openTemporaryFile: baseName Open for writing a file whose name starts with baseName, followed by six random alphanumeric characters. The file is created with mode read/write and permissions 0666 or 0600 on most recent operating systems (beware, the former behavior might constitute a security problem). The file is opened with the O_EXCL flag, guaranteeing that when the method returns successfully we are the only user. popen: commandName dir: direction Open a pipe on the given command and fail if the file cannot be opened. Else answer a new FileStream. The pipe will not be automatically closed upon GC, even if the object is not referenced anymore, because when you close a pipe you have to wait for the associated process to terminate. direction is returned by #read or #write ('r' or 'w') and is interpreted from the point of view of Smalltalk: reading means Smalltalk reads the standard output of the command, writing means Smalltalk writes the standard input of the command. The other channel (stdin when reading, stdout when writing) is the same as GST's, unless commandName alters it. popen: commandName dir: direction ifFail: aBlock Open a pipe on the given command and evaluate aBlock file cannot be opened. Else answer a new FileStream. The pipe will not be automatically closed upon GC, even if the object is not referenced anymore, because when you close a pipe you have to wait for the associated process to terminate. direction is interpreted from the point of view of Smalltalk: reading means that Smalltalk reads the standard output of the command, writing means that Smalltalk writes the standard input of the command read Open text file for reading. The stream is positioned at the beginning of the file. readWrite Open for reading and writing. The stream is positioned at the beginning of the file. write Truncate file to zero length or create text file for writing. The stream is positioned at the beginning of the file.  File: gst-base.info, Node: FileDescriptor class-still unclassified, Next: FileDescriptor-accessing, Prev: FileDescriptor class-instance creation, Up: FileDescriptor 1.76.3 FileDescriptor class: still unclassified ----------------------------------------------- open: fileName mode: fileMode Open fileName in the required mode - answered by #append, #create, #readWrite, #read or #write - and fail if the file cannot be opened. Else answer a new FileStream. For mode anyway you can use any standard C non-binary fopen mode. fileName can be a `virtual filesystem' path, including URLs and '#' suffixes that are inspected by the virtual filesystem layers and replaced with tasks such as un-gzipping a file or extracting a file from an archive. The file will be automatically closed upon GC if the object is not referenced anymore, but it is better to close it as soon as you're finished with it anyway, using #close. To keep a file open even when no references exist anymore, send it #removeToBeFinalized  File: gst-base.info, Node: FileDescriptor-accessing, Next: FileDescriptor-basic, Prev: FileDescriptor class-still unclassified, Up: FileDescriptor 1.76.4 FileDescriptor: accessing -------------------------------- canRead Answer whether the file is open and we can read from it canWrite Answer whether the file is open and we can write from it ensureReadable If the file is open, wait until data can be read from it. The wait allows other Processes to run. ensureWriteable If the file is open, wait until we can write to it. The wait allows other Processes to run. exceptionalCondition Answer whether the file is open and an exceptional condition (such as presence of out of band data) has occurred on it fd Return the OS file descriptor of the file file Return the name of the file isOpen Answer whether the file is still open isPeerAlive Present for compatibility with sockets. For files, it answers whether the file is still open isPipe Answer whether the file is a pipe or an actual disk file name Return the name of the file waitForException If the file is open, wait until an exceptional condition (such as presence of out of band data) has occurred on it. The wait allows other Processes to run.  File: gst-base.info, Node: FileDescriptor-basic, Next: FileDescriptor-binary I/O, Prev: FileDescriptor-accessing, Up: FileDescriptor 1.76.5 FileDescriptor: basic ---------------------------- checkError Perform error checking. By default, we call File class>>#checkError. close Close the file contents Answer the whole contents of the file copyFrom: from to: to Answer the contents of the file between the two given positions finalize Close the file if it is still open by the time the object becomes garbage. invalidate Invalidate a file descriptor next Return the next character in the file, or nil at eof nextByte Return the next byte in the file, or nil at eof nextPut: aCharacter Store aCharacter on the file nextPutByte: anInteger Store the byte, anInteger, on the file nextPutByteArray: aByteArray Store aByteArray on the file peek Returns the next element of the stream without moving the pointer. Returns nil when at end of stream. peekFor: anObject Returns whether the next element of the stream is equal to anObject, without moving the pointer if it is not. position Answer the zero-based position from the start of the file position: n Set the file pointer to the zero-based position n reset Reset the stream to its beginning shutdown Close the transmission side of a full-duplex connection. This is useful on read-write pipes. size Return the current size of the file, in bytes truncate Truncate the file at the current position  File: gst-base.info, Node: FileDescriptor-binary I/O, Next: FileDescriptor-built ins, Prev: FileDescriptor-basic, Up: FileDescriptor 1.76.6 FileDescriptor: binary I/O --------------------------------- nextByteArray: numBytes Return the next numBytes bytes in the byte array nextDouble Return the next 64-bit float in the byte array nextFloat Return the next 32-bit float in the byte array nextLong Return the next 4 bytes in the byte array, interpreted as a 32 bit signed int nextLongLong Return the next 8 bytes in the byte array, interpreted as a 64 bit signed int nextPutDouble: aDouble Store aDouble as a 64-bit float in the byte array nextPutFloat: aFloat Return the next 32-bit float in the byte array nextPutInt64: anInteger Store anInteger (range: -2^63..2^64-1) on the byte array as 8 bytes nextPutLong: anInteger Store anInteger (range: -2^31..2^32-1) on the byte array as 4 bytes nextPutShort: anInteger Store anInteger (range: -32768..65535) on the byte array as 2 bytes nextShort Return the next 2 bytes in the byte array, interpreted as a 16 bit signed int nextSignedByte Return the next byte in the byte array, interpreted as a 8 bit signed number nextUint64 Return the next 8 bytes in the byte array, interpreted as a 64 bit unsigned int nextUlong Return the next 4 bytes in the byte array, interpreted as a 32 bit unsigned int nextUshort Return the next 2 bytes in the byte array, interpreted as a 16 bit unsigned int  File: gst-base.info, Node: FileDescriptor-built ins, Next: FileDescriptor-class type methods, Prev: FileDescriptor-binary I/O, Up: FileDescriptor 1.76.7 FileDescriptor: built ins -------------------------------- fileIn File in the contents of the receiver. During a file in operation, global variables (starting with an uppercase letter) that are not declared don't yield an `unknown variable' error. Instead, they are defined as nil in the `Undeclared' dictionary (a global variable residing in Smalltalk). As soon as you add the variable to a namespace (for example by creating a class) the Association will be removed from Undeclared and reused in the namespace, so that the old references will automagically point to the new value. fileOp: ioFuncIndex Private - Used to limit the number of primitives used by FileStreams fileOp: ioFuncIndex ifFail: aBlock Private - Used to limit the number of primitives used by FileStreams. fileOp: ioFuncIndex with: arg1 Private - Used to limit the number of primitives used by FileStreams fileOp: ioFuncIndex with: arg1 ifFail: aBlock Private - Used to limit the number of primitives used by FileStreams. fileOp: ioFuncIndex with: arg1 with: arg2 Private - Used to limit the number of primitives used by FileStreams fileOp: ioFuncIndex with: arg1 with: arg2 ifFail: aBlock Private - Used to limit the number of primitives used by FileStreams. fileOp: ioFuncIndex with: arg1 with: arg2 with: arg3 Private - Used to limit the number of primitives used by FileStreams fileOp: ioFuncIndex with: arg1 with: arg2 with: arg3 ifFail: aBlock Private - Used to limit the number of primitives used by FileStreams. fileOp: ioFuncIndex with: arg1 with: arg2 with: arg3 with: arg4 Private - Used to limit the number of primitives used by FileStreams fileOp: ioFuncIndex with: arg1 with: arg2 with: arg3 with: arg4 ifFail: aBlock Private - Used to limit the number of primitives used by FileStreams.  File: gst-base.info, Node: FileDescriptor-class type methods, Next: FileDescriptor-initialize-release, Prev: FileDescriptor-built ins, Up: FileDescriptor 1.76.8 FileDescriptor: class type methods ----------------------------------------- isBinary We answer characters, so answer false isExternalStream We stream on an external entity (a file), so answer true isText We answer characters, so answer true  File: gst-base.info, Node: FileDescriptor-initialize-release, Next: FileDescriptor-low-level access, Prev: FileDescriptor-class type methods, Up: FileDescriptor 1.76.9 FileDescriptor: initialize-release ----------------------------------------- addToBeFinalized Add me to the list of open files. initialize Initialize the receiver's instance variables readStream Answer myself, or an alternate stream coerced for reading. removeToBeFinalized Remove me from the list of open files.  File: gst-base.info, Node: FileDescriptor-low-level access, Next: FileDescriptor-overriding inherited methods, Prev: FileDescriptor-initialize-release, Up: FileDescriptor 1.76.10 FileDescriptor: low-level access ---------------------------------------- next: n putAll: aCollection startingAt: position Put the characters in the supplied range of aCollection in the file nextAvailable: n into: aCollection startingAt: position Ignoring any buffering, try to fill the given range of aCollection with the contents of the file  File: gst-base.info, Node: FileDescriptor-overriding inherited methods, Next: FileDescriptor-polymorphism, Prev: FileDescriptor-low-level access, Up: FileDescriptor 1.76.11 FileDescriptor: overriding inherited methods ---------------------------------------------------- isEmpty Answer whether the receiver is empty nextPutAllOn: aStream Put all the characters of the receiver in aStream. reverseContents Return the contents of the file from the last byte to the first setToEnd Reset the file pointer to the end of the file skip: anInteger Skip anInteger bytes in the file  File: gst-base.info, Node: FileDescriptor-polymorphism, Next: FileDescriptor-positioning, Prev: FileDescriptor-overriding inherited methods, Up: FileDescriptor 1.76.12 FileDescriptor: polymorphism ------------------------------------ pastEnd The end of the stream has been reached. Signal a Notification.  File: gst-base.info, Node: FileDescriptor-positioning, Next: FileDescriptor-printing, Prev: FileDescriptor-polymorphism, Up: FileDescriptor 1.76.13 FileDescriptor: positioning ----------------------------------- isPositionable Answer true if the stream supports moving backwards with #skip:.  File: gst-base.info, Node: FileDescriptor-printing, Next: FileDescriptor-testing, Prev: FileDescriptor-positioning, Up: FileDescriptor 1.76.14 FileDescriptor: printing -------------------------------- printOn: aStream Print a representation of the receiver on aStream  File: gst-base.info, Node: FileDescriptor-testing, Prev: FileDescriptor-printing, Up: FileDescriptor 1.76.15 FileDescriptor: testing ------------------------------- atEnd Answer whether data has come to an end  File: gst-base.info, Node: FilePath, Next: FileSegment, Prev: FileDescriptor, Up: Base classes 1.77 FilePath ============= Defined in namespace Smalltalk Superclass: Object Category: Streams-Files I expose the syntax of file names, including paths. I know how to manipulate such a path by splitting it into its components. In addition, I expose information about files (both real and virtual) such as their size and timestamps. * Menu: * FilePath class-file name management:: (class) * FilePath class-still unclassified:: (class) * FilePath-accessing:: (instance) * FilePath-converting:: (instance) * FilePath-decoration:: (instance) * FilePath-directory operations:: (instance) * FilePath-enumerating:: (instance) * FilePath-file name management:: (instance) * FilePath-file operations:: (instance) * FilePath-printing:: (instance) * FilePath-still unclassified:: (instance) * FilePath-testing:: (instance) * FilePath-virtual filesystems:: (instance)  File: gst-base.info, Node: FilePath class-file name management, Next: FilePath class-still unclassified, Up: FilePath 1.77.1 FilePath class: file name management ------------------------------------------- append: fileName to: directory Answer the name of a file named `fileName' which resides in a directory named `directory'. extensionFor: aString Answer the extension of a file named `aString'. Note: the extension includes an initial dot. fullNameFor: aString Answer the full path to a file called `aString', resolving the `.' and `..' directory entries, and answer the result. `/..' is the same as '/'. pathFor: aString Determine the path of the name of a file called `aString', and answer the result. With the exception of the root directory, the final slash is stripped. pathFor: aString ifNone: aBlock Determine the path of the name of a file called `aString', and answer the result. With the exception of the root directory, the final slash is stripped. If there is no path, evaluate aBlock and return the result. pathFrom: srcName to: destName Answer the relative path to destName when the current directory is srcName's directory. stripExtensionFrom: aString Remove the extension from the name of a file called `aString', and answer the result. stripFileNameFor: aString Determine the path of the name of a file called `aString', and answer the result as a directory name including the final slash. stripPathFrom: aString Remove the path from the name of a file called `aString', and answer the file name plus extension.  File: gst-base.info, Node: FilePath class-still unclassified, Next: FilePath-accessing, Prev: FilePath class-file name management, Up: FilePath 1.77.2 FilePath class: still unclassified ----------------------------------------- isAbsolute: aString Answer whether aString is an absolute ptah.  File: gst-base.info, Node: FilePath-accessing, Next: FilePath-converting, Prev: FilePath class-still unclassified, Up: FilePath 1.77.3 FilePath: accessing -------------------------- at: aName Answer a File or Directory object as appropriate for a file named 'aName' in the directory represented by the receiver. creationTime Answer the creation time of the file identified by the receiver. On some operating systems, this could actually be the last change time (the `last change time' has to do with permissions, ownership and the like). group: aString Set the group of the file identified by the receiver to be aString. includes: aName Answer whether a file named `aName' exists in the directory represented by the receiver. lastAccessTime Answer the last access time of the file identified by the receiver lastAccessTime: aDateTime Update the last access time of the file corresponding to the receiver, to be aDateTime. lastAccessTime: accessDateTime lastModifyTime: modifyDateTime Update the timestamps of the file corresponding to the receiver, to be accessDateTime and modifyDateTime. lastChangeTime Answer the last change time of the file identified by the receiver (the `last change time' has to do with permissions, ownership and the like). On some operating systems, this could actually be the file creation time. lastModifyTime Answer the last modify time of the file identified by the receiver (the `last modify time' has to do with the actual file contents). lastModifyTime: aDateTime Update the last modification timestamp of the file corresponding to the receiver, to be aDateTime. mode Answer the permission bits for the file identified by the receiver mode: anInteger Set the permission bits for the file identified by the receiver to be anInteger. owner: aString Set the owner of the file identified by the receiver to be aString. owner: ownerString group: groupString Set the owner and group of the file identified by the receiver to be aString. pathTo: destName Compute the relative path from the receiver to destName. refresh Refresh the statistics for the receiver size Answer the size of the file identified by the receiver  File: gst-base.info, Node: FilePath-converting, Next: FilePath-decoration, Prev: FilePath-accessing, Up: FilePath 1.77.4 FilePath: converting --------------------------- asFile Answer the receiver.  File: gst-base.info, Node: FilePath-decoration, Next: FilePath-directory operations, Prev: FilePath-converting, Up: FilePath 1.77.5 FilePath: decoration --------------------------- all Return a decorator of the receiver that will provide recursive descent into directories for iteration methods. Furthermore, iteration on the returned wrapper will not include '.' or '..' directory entries, and will include the receiver (directly, not via '.').  File: gst-base.info, Node: FilePath-directory operations, Next: FilePath-enumerating, Prev: FilePath-decoration, Up: FilePath 1.77.6 FilePath: directory operations ------------------------------------- createDirectories Create the receiver as a directory, together with all its parents. createDirectory Create the receiver as a directory, together with all its parents. nameAt: aName Answer a FilePath for a file named `aName' residing in the directory represented by the receiver.  File: gst-base.info, Node: FilePath-enumerating, Next: FilePath-file name management, Prev: FilePath-directory operations, Up: FilePath 1.77.7 FilePath: enumerating ---------------------------- allFilesMatching: aPattern do: aBlock Evaluate aBlock on the File objects that match aPattern (according to String>>#match:) in the directory named by the receiver. Recursively descend into directories. directories Answer an Array with Directory objects for the subdirectories of the directory represented by the receiver. do: aBlock Evaluate aBlock once for each file in the directory represented by the receiver, passing a FilePath object (or a subclass) to it. It depends on the subclass whether iteration will include the '.' and '..' directory entries. entries Answer an Array with File or Directory objects for the contents of the directory represented by the receiver. entryNames Answer an Array with the names of the files in the directory represented by the receiver. files Answer an Array with File objects for the contents of the directory represented by the receiver. filesMatching: aPattern Evaluate aBlock once for each file in the directory represented by the receiver, passing a File or Directory object to aBlock. Returns the *names* of the files for which aBlock returns true. filesMatching: aPattern do: block Evaluate block on the File objects that match aPattern (according to String>>#match:) in the directory named by the receiver. namesDo: aBlock Evaluate aBlock once for each file in the directory represented by the receiver, passing its name. It depends on the subclass whether iteration will include the '.' and '..' directory entries. namesMatching: aPattern do: block Evaluate block on the file names that match aPattern (according to String>>#match:) in the directory named by the receiver. reject: aBlock Evaluate aBlock once for each file in the directory represented by the receiver, passing a File or Directory object to aBlock. Returns the *names* of the files for which aBlock returns true. select: aBlock Evaluate aBlock once for each file in the directory represented by the receiver, passing a File or Directory object to aBlock. Returns the *names* of the files for which aBlock returns true.  File: gst-base.info, Node: FilePath-file name management, Next: FilePath-file operations, Prev: FilePath-enumerating, Up: FilePath 1.77.8 FilePath: file name management ------------------------------------- directory Answer the Directory object for the receiver's path extension Answer the extension of the receiver full Answer the full name of the receiver, resolving the `.' and `..' directory entries, and answer the result. Answer nil if the name is invalid (such as '/usr/../../badname') fullName Answer a String with the full path to the receiver (same as #name; it is useless to override this method). name Answer String with the full path to the receiver (same as #fullName). parent Answer the Directory object for the receiver's path path Answer the path (if any) of the receiver stripExtension Answer the path (if any) and file name of the receiver stripFileName Answer the path of the receiver, always including a directory name (possibly `.') and the final directory separator stripPath Answer the file name and extension (if any) of the receiver  File: gst-base.info, Node: FilePath-file operations, Next: FilePath-printing, Prev: FilePath-file name management, Up: FilePath 1.77.9 FilePath: file operations -------------------------------- contents Open a read-only FileStream on the receiver, read its contents, close the stream and answer the contents fileIn File in the receiver open: mode Open the receiver in the given mode (as answered by FileStream's class constant methods) open: mode ifFail: aBlock Open the receiver in the given mode (as answered by FileStream's class constant methods). Upon failure, evaluate aBlock. open: class mode: mode ifFail: aBlock Open the receiver in the given mode (as answered by FileStream's class constant methods) openDescriptor: mode Open the receiver in the given mode (as answered by FileStream's class constant methods) openDescriptor: mode ifFail: aBlock Open the receiver in the given mode (as answered by FileStream's class constant methods). Upon failure, evaluate aBlock. pathFrom: dirName Compute the relative path from the directory dirName to the receiver readStream Open a read-only FileStream on the receiver remove Remove the file identified by the receiver renameTo: newName Rename the file identified by the receiver to newName symlinkAs: destName Create destName as a symbolic link of the receiver. The appropriate relative path is computed automatically. symlinkFrom: srcName Create the receiver as a symbolic link from srcName (relative to the path of the receiver). touch Update the timestamp of the file corresponding to the receiver. withReadStreamDo: aBlock Answer the result of invoking aBlock with a reading stream open on me, closing it when the dynamic extent of aBlock ends. withWriteStreamDo: aBlock Answer the result of invoking aBlock with a writing stream open on me, closing it when the dynamic extent of aBlock ends. writeStream Open a write-only FileStream on the receiver  File: gst-base.info, Node: FilePath-printing, Next: FilePath-still unclassified, Prev: FilePath-file operations, Up: FilePath 1.77.10 FilePath: printing -------------------------- asString Print a representation of the receiver on aStream. displayOn: aStream Print a representation of the receiver on aStream. printOn: aStream Print a representation of the receiver on aStream. withShellEscapes Return the representation of the receiver with shell characters escaped.  File: gst-base.info, Node: FilePath-still unclassified, Next: FilePath-testing, Prev: FilePath-printing, Up: FilePath 1.77.11 FilePath: still unclassified ------------------------------------ / aName Answer a File or Directory object as appropriate for a file named 'aName' in the directory represented by the receiver.  File: gst-base.info, Node: FilePath-testing, Next: FilePath-virtual filesystems, Prev: FilePath-still unclassified, Up: FilePath 1.77.12 FilePath: testing ------------------------- exists Answer whether a file with the name contained in the receiver does exist. isAbsolute Answer whether the receiver identifies an absolute path. isAccessible Answer whether a directory with the name contained in the receiver does exist and can be accessed isDirectory Answer whether a file with the name contained in the receiver does exist and identifies a directory. isExecutable Answer whether a file with the name contained in the receiver does exist and is executable isFile Answer whether a file with the name contained in the receiver does exist and does not identify a directory. isFileSystemPath Answer whether the receiver corresponds to a real filesystem path. isReadable Answer whether a file with the name contained in the receiver does exist and is readable isRelative Answer whether the receiver identifies a relative path. isSymbolicLink Answer whether a file with the name contained in the receiver does exist and identifies a symbolic link. isWriteable Answer whether a file with the name contained in the receiver does exist and is writeable  File: gst-base.info, Node: FilePath-virtual filesystems, Prev: FilePath-testing, Up: FilePath 1.77.13 FilePath: virtual filesystems ------------------------------------- zip Not commented.  File: gst-base.info, Node: FileSegment, Next: FileStream, Prev: FilePath, Up: Base classes 1.78 FileSegment ================ Defined in namespace Smalltalk Superclass: Object Category: Language-Implementation My instances represent sections of files. I am primarily used by the compiler to record source code locations. I am not a part of the normal Smalltalk-80 kernel; I am specific to the GNU Smalltalk implementation. * Menu: * FileSegment class-basic:: (class) * FileSegment class-installing:: (class) * FileSegment-basic:: (instance) * FileSegment-equality:: (instance) * FileSegment-printing:: (instance)  File: gst-base.info, Node: FileSegment class-basic, Next: FileSegment class-installing, Up: FileSegment 1.78.1 FileSegment class: basic ------------------------------- on: aFile startingAt: startPos for: sizeInteger Create a new FileSegment referring to the contents of the given file, from the startPos-th byte and for sizeInteger bytes. Note that FileSegments should always be created with full paths because relative paths are interpreted to be relative to the kernel directory.  File: gst-base.info, Node: FileSegment class-installing, Next: FileSegment-basic, Prev: FileSegment class-basic, Up: FileSegment 1.78.2 FileSegment class: installing ------------------------------------ relocate Remove the kernel path from all paths that start with it. Needed to support $(DESTDIR) and relocatable installation.  File: gst-base.info, Node: FileSegment-basic, Next: FileSegment-equality, Prev: FileSegment class-installing, Up: FileSegment 1.78.3 FileSegment: basic ------------------------- asString Answer a String containing the required segment of the file copyFrom: from to: to Answer a String containing the given subsegment of the file. As for streams, from and to are 0-based. file Answer the File object for the file containing the segment fileName Answer the name of the file containing the segment filePos Answer the position in the file where the segment starts relocateFrom: startPath map: map If the path starts with startPath, remove that part of the path. map is a Dictionary that is used so that equal filenames stay equal, without increasing the amount of memory that the image uses. size Answer the length of the segment withFileDo: aBlock Evaluate aBlock passing it the FileStream in which the segment identified by the receiver is stored  File: gst-base.info, Node: FileSegment-equality, Next: FileSegment-printing, Prev: FileSegment-basic, Up: FileSegment 1.78.4 FileSegment: equality ---------------------------- = aFileSegment Answer whether the receiver and aFileSegment are equal. hash Answer an hash value for the receiver.  File: gst-base.info, Node: FileSegment-printing, Prev: FileSegment-equality, Up: FileSegment 1.78.5 FileSegment: printing ---------------------------- printedFileName Answer a printed representation of the file containing the segment. While introducing some ambiguity, this representation is compact eliminates the path for kernel files, and produces a relative path from the current working directory for other files.  File: gst-base.info, Node: FileStream, Next: Float, Prev: FileSegment, Up: Base classes 1.79 FileStream =============== Defined in namespace Smalltalk Superclass: FileDescriptor Category: Streams-Files My instances are what conventional programmers think of as files. My instance creation methods accept the name of a disk file (or any named file object, such as /dev/rmt0 on UNIX or MTA0: on VMS). * Menu: * FileStream class-file-in:: (class) * FileStream class-standard streams:: (class) * FileStream-basic:: (instance) * FileStream-buffering:: (instance) * FileStream-compiling:: (instance) * FileStream-initialize-release:: (instance) * FileStream-overriding inherited methods:: (instance) * FileStream-testing:: (instance)  File: gst-base.info, Node: FileStream class-file-in, Next: FileStream class-standard streams, Up: FileStream 1.79.1 FileStream class: file-in -------------------------------- fileIn: aFileName File in the aFileName file. During a file in operation, global variables (starting with an uppercase letter) that are not declared yet don't yield an `unknown variable' error. Instead, they are defined as nil in the `Undeclared' dictionary (a global variable residing in Smalltalk). As soon as you add the variable to a namespace (for example by creating a class) the Association will be removed from Undeclared and reused in the namespace, so that the old references will automagically point to the new value. fileIn: aFileName ifMissing: aSymbol Conditionally do a file in, only if the key (often a class) specified by 'aSymbol' is not present in the Smalltalk system dictionary already. During a file in operation, global variables (starting with an uppercase letter) that are not declared don't yield an `unknown variable' error. Instead, they are defined as nil in the `Undeclared' dictionary (a global variable residing in Smalltalk). As soon as you add the variable to a namespace (for example by creating a class) the Association will be removed from Undeclared and reused in the namespace, so that the old references will automagically point to the new value. fileIn: aFileName ifTrue: aBoolean Conditionally do a file in, only if the supplied boolean is true. During a file in operation, global variables (starting with an uppercase letter) that are not declared don't yield an `unknown variable' error. Instead, they are defined as nil in the `Undeclared' dictionary (a global variable residing in Smalltalk). As soon as you add the variable to a namespace (for example by creating a class) the Association will be removed from Undeclared and reused in the namespace, so that the old references will automagically point to the new value. fileIn: aFileName line: lineInteger from: realFileName at: aCharPos File in the aFileName file giving errors such as if it was loaded from the given line, file name and starting position (instead of 1). generateMakefileOnto: aStream Generate a make file for the file-ins since record was last set to true. Store it on aStream initialize Private - Initialize the receiver's class variables record: recordFlag Set whether Smalltalk should record information about nested file-ins. When recording is enabled, use #generateMakefileOnto: to automatically generate a valid makefile for the intervening file-ins. require: assoc Conditionally do a file in from the value of assoc, only if the key of assoc is not present in the Smalltalk system dictionary already. During a file in operation, global variables (starting with an uppercase letter) that are not declared don't yield an `unknown variable' error. Instead, they are defined as nil in the `Undeclared' dictionary (a global variable residing in Smalltalk). As soon as you add the variable to a namespace (for example by creating a class) the Association will be removed from Undeclared and reused in the namespace, so that the old references will automagically point to the new value. verbose: verboseFlag Set whether Smalltalk should output debugging messages when filing in  File: gst-base.info, Node: FileStream class-standard streams, Next: FileStream-basic, Prev: FileStream class-file-in, Up: FileStream 1.79.2 FileStream class: standard streams ----------------------------------------- stderr Answer a FileStream that is attached the Smalltalk program's standard error file handle, which can be used for error messages and diagnostics issued by the program. stdin Answer a FileStream that is attached the Smalltalk program's standard input file handle, which is the normal source of input for the program. stdout Answer a FileStream that is attached the Smalltalk program's standard output file handle; this is used for normal output from the program.  File: gst-base.info, Node: FileStream-basic, Next: FileStream-buffering, Prev: FileStream class-standard streams, Up: FileStream 1.79.3 FileStream: basic ------------------------ bufferStart Private - Answer the offset from the start of the file corresponding to the beginning of the read buffer. copyFrom: from to: to Answer the contents of the file between the two given positions next Return the next character in the file, or nil at eof nextPut: aCharacter Store aCharacter on the file peek Return the next character in the file, or nil at eof. Don't advance the file pointer. position Answer the zero-based position from the start of the file position: n Set the file pointer to the zero-based position n size Return the current size of the file, in bytes truncate Truncate the file at the current position  File: gst-base.info, Node: FileStream-buffering, Next: FileStream-compiling, Prev: FileStream-basic, Up: FileStream 1.79.4 FileStream: buffering ---------------------------- bufferSize Answer the file's current buffer bufferSize: bufSize Flush the file and set the buffer's size to bufSize clean Synchronize the file descriptor's state with the object's state. fill Private - Fill the input buffer flush Flush the output buffer. newBuffer Private - Answer a String to be used as the receiver's buffer next: n bufferAll: aCollection startingAt: pos Private - Assuming that the buffer has space for n characters, store n characters of aCollection in the buffer, starting from the pos-th. nextAvailable: anInteger into: aCollection startingAt: pos Read up to anInteger bytes from the stream and store them into aCollection. Return the number of bytes read. nextAvailable: anInteger putAllOn: aStream Copy up to anInteger bytes from the stream into aStream. Return the number of bytes read. pendingWrite Answer whether the output buffer is full.  File: gst-base.info, Node: FileStream-compiling, Next: FileStream-initialize-release, Prev: FileStream-buffering, Up: FileStream 1.79.5 FileStream: compiling ---------------------------- segmentFrom: startPos to: endPos Answer an object that, when sent #asString, will yield the result of sending `copyFrom: startPos to: endPos' to the receiver  File: gst-base.info, Node: FileStream-initialize-release, Next: FileStream-overriding inherited methods, Prev: FileStream-compiling, Up: FileStream 1.79.6 FileStream: initialize-release ------------------------------------- initialize Initialize the receiver's instance variables  File: gst-base.info, Node: FileStream-overriding inherited methods, Next: FileStream-testing, Prev: FileStream-initialize-release, Up: FileStream 1.79.7 FileStream: overriding inherited methods ----------------------------------------------- next: n putAll: aCollection startingAt: pos Write n values from aCollection, the first being at pos. nextLine Returns a collection of the same type that the stream accesses, containing the next line up to the next new-line character. Returns the entire rest of the stream's contents if no new-line character is found. nextPutAllOn: aStream Put all the characters of the receiver in aStream. upTo: aCharacter Returns a collection of the same type that the stream accesses, containing data up to aCharacter. Returns the entire rest of the stream's contents if no such character is found.  File: gst-base.info, Node: FileStream-testing, Prev: FileStream-overriding inherited methods, Up: FileStream 1.79.8 FileStream: testing -------------------------- atEnd Answer whether data has come to an end  File: gst-base.info, Node: Float, Next: FloatD, Prev: FileStream, Up: Base classes 1.80 Float ========== Defined in namespace Smalltalk Superclass: Number Category: Language-Data types My instances represent floating point numbers that have arbitrary precision. Besides the standard numerical operations, they provide transcendental operations too. They implement IEEE-754 correctly if the hardware supports it. * Menu: * Float class-byte-order dependancies:: (class) * Float class-characterization:: (class) * Float-arithmetic:: (instance) * Float-basic:: (instance) * Float-built ins:: (instance) * Float-coercing:: (instance) * Float-coercion:: (instance) * Float-comparing:: (instance) * Float-compiler:: (instance) * Float-converting:: (instance) * Float-floating point:: (instance) * Float-misc math:: (instance) * Float-printing:: (instance) * Float-storing:: (instance) * Float-testing:: (instance) * Float-testing functionality:: (instance) * Float-transcendental operations:: (instance) * Float-truncation and round off:: (instance)  File: gst-base.info, Node: Float class-byte-order dependancies, Next: Float class-characterization, Up: Float 1.80.1 Float class: byte-order dependancies ------------------------------------------- signByte Answer the byte of the receiver that contains the sign bit  File: gst-base.info, Node: Float class-characterization, Next: Float-arithmetic, Prev: Float class-byte-order dependancies, Up: Float 1.80.2 Float class: characterization ------------------------------------ denormalized Answer whether instances of the receiver can be in denormalized form. e Returns the value of e. Hope is that it is precise enough epsilon Return the smallest Float x for which is 1 + x ~= 1 fmin Return the smallest Float that is > 0. fminDenormalized Return the smallest Float that is > 0 if denormalized values are supported, else return 0. ln10 Returns the value of ln 10. Hope is that it is precise enough log10Base2 Returns the value of log2 10. Hope is that it is precise enough pi Returns the value of pi. Hope is that it is precise enough radix Answer the base in which computations between instances of the receiver are made. This should be 2 on about every known computer, so GNU Smalltalk always answers 2.  File: gst-base.info, Node: Float-arithmetic, Next: Float-basic, Prev: Float class-characterization, Up: Float 1.80.3 Float: arithmetic ------------------------ integerPart Return the receiver's integer part negated Return the negation of the receiver. Unlike 0-self, this converts correctly signed zeros. raisedToInteger: anInteger Return self raised to the anInteger-th power  File: gst-base.info, Node: Float-basic, Next: Float-built ins, Prev: Float-arithmetic, Up: Float 1.80.4 Float: basic ------------------- hash Answer an hash value for the receiver. Not-a-number values do not have a hash code and cannot be put in a hashed collection.  File: gst-base.info, Node: Float-built ins, Next: Float-coercing, Prev: Float-basic, Up: Float 1.80.5 Float: built ins ----------------------- arcCos Answer the arc-cosine of the receiver arcSin Answer the arc-sine of the receiver arcTan Answer the arc-tangent of the receiver ceiling Answer the integer part of the receiver, truncated towards +infinity cos Answer the cosine of the receiver exp Answer 'e' (2.718281828459...) raised to the receiver floor Answer the integer part of the receiver, truncated towards -infinity ln Answer the logarithm of the receiver in base 'e' (2.718281828459...) primHash Private - Answer an hash value for the receiver raisedTo: aNumber Answer the receiver raised to its aNumber power sin Answer the sine of the receiver sqrt Answer the square root of the receiver tan Answer the tangent of the receiver  File: gst-base.info, Node: Float-coercing, Next: Float-coercion, Prev: Float-built ins, Up: Float 1.80.6 Float: coercing ---------------------- asExactFraction Convert the receiver into a fraction with optimal approximation, but with usually huge terms. asFraction Convert the receiver into a fraction with a good (but undefined) approximation truncated Convert the receiver to an Integer. Only used for LargeIntegers, there are primitives for the other cases.  File: gst-base.info, Node: Float-coercion, Next: Float-comparing, Prev: Float-coercing, Up: Float 1.80.7 Float: coercion ---------------------- asCNumber Convert the receiver to a kind of number that is understood by the C call-out mechanism.  File: gst-base.info, Node: Float-comparing, Next: Float-compiler, Prev: Float-coercion, Up: Float 1.80.8 Float: comparing ----------------------- max: aNumber Answer the maximum between the receiver and aNumber. Redefine in subclasses if necessary to ensure that if either self or aNumber is a NaN, it is always answered. min: aNumber Answer the minimum between the receiver and aNumber. Redefine in subclasses if necessary to ensure that if either self or aNumber is a NaN, it is always answered. withSignOf: aNumber Answer the receiver, with its sign possibly changed to match that of aNumber.  File: gst-base.info, Node: Float-compiler, Next: Float-converting, Prev: Float-comparing, Up: Float 1.80.9 Float: compiler ---------------------- literalEquals: anObject Not commented. literalHash Not commented.  File: gst-base.info, Node: Float-converting, Next: Float-floating point, Prev: Float-compiler, Up: Float 1.80.10 Float: converting ------------------------- half Answer 0.5 in the representation of the receiver  File: gst-base.info, Node: Float-floating point, Next: Float-misc math, Prev: Float-converting, Up: Float 1.80.11 Float: floating point ----------------------------- predecessor Not commented. successor Not commented.  File: gst-base.info, Node: Float-misc math, Next: Float-printing, Prev: Float-floating point, Up: Float 1.80.12 Float: misc math ------------------------ log: aNumber Answer log base aNumber of the receiver  File: gst-base.info, Node: Float-printing, Next: Float-storing, Prev: Float-misc math, Up: Float 1.80.13 Float: printing ----------------------- printOn: aStream Print a representation of the receiver on aStream  File: gst-base.info, Node: Float-storing, Next: Float-testing, Prev: Float-printing, Up: Float 1.80.14 Float: storing ---------------------- isLiteralObject Answer whether the receiver is expressible as a Smalltalk literal. storeLiteralOn: aStream Store on aStream some Smalltalk code which compiles to the receiver storeOn: aStream Print a representation of the receiver on aStream  File: gst-base.info, Node: Float-testing, Next: Float-testing functionality, Prev: Float-storing, Up: Float 1.80.15 Float: testing ---------------------- isExact Answer whether the receiver performs exact arithmetic. Floats do not. isFinite Answer whether the receiver does not represent infinity, nor a NaN isInfinite Answer whether the receiver represents positive or negative infinity isNaN Answer whether the receiver represents a NaN negative Answer whether the receiver is negative positive Answer whether the receiver is positive. Negative zero is not positive, so the definition is not simply >= 0. sign Answer 1 if the receiver is greater than 0, -1 if less than 0, else 0. Negative zero is the same as positive zero. strictlyPositive Answer whether the receiver is > 0  File: gst-base.info, Node: Float-testing functionality, Next: Float-transcendental operations, Prev: Float-testing, Up: Float 1.80.16 Float: testing functionality ------------------------------------ isFloat Answer `true'.  File: gst-base.info, Node: Float-transcendental operations, Next: Float-truncation and round off, Prev: Float-testing functionality, Up: Float 1.80.17 Float: transcendental operations ---------------------------------------- asFloat Just defined for completeness. Return the receiver. ceilingLog: radix Answer (self log: radix) ceiling. Use exact arithmetic if radix is not a floating point value. estimatedLog Answer an estimate of (self abs floorLog: 10) floorLog: radix Answer (self log: radix) floor. Use exact arithmetic if radix is not a floating point value. log Answer log base 10 of the receiver.  File: gst-base.info, Node: Float-truncation and round off, Prev: Float-transcendental operations, Up: Float 1.80.18 Float: truncation and round off --------------------------------------- rounded Answer the receiver, rounded to the nearest integer  File: gst-base.info, Node: FloatD, Next: FloatE, Prev: Float, Up: Base classes 1.81 FloatD =========== Defined in namespace Smalltalk Superclass: Float Category: Language-Data types My instances represent floating point numbers that have the same accuracy as C's "double" numbers. * Menu: * FloatD class-byte-order dependencies:: (class) * FloatD class-characterization:: (class) * FloatD class-converting:: (class) * FloatD-built ins:: (instance) * FloatD-coercing:: (instance) * FloatD-converting:: (instance)  File: gst-base.info, Node: FloatD class-byte-order dependencies, Next: FloatD class-characterization, Up: FloatD 1.81.1 FloatD class: byte-order dependencies -------------------------------------------- fromBytes: aByteArray Answer a float with the bytes in aByteArray, which are in big-endian format. signByte Answer the byte of the receiver that contains the sign bit  File: gst-base.info, Node: FloatD class-characterization, Next: FloatD class-converting, Prev: FloatD class-byte-order dependencies, Up: FloatD 1.81.2 FloatD class: characterization ------------------------------------- decimalDigits Return the number of decimal digits of precision for a FloatD. Technically, if P is the precision for the representation, then the decimal precision Q is the maximum number of decimal digits such that any floating point number with Q base 10 digits can be rounded to a floating point number with P base 2 digits and back again, without change to the Q decimal digits. emax Return the maximum allowable exponent for a FloatD that is finite. emin Return the maximum allowable exponent for a FloatD that is finite. fmax Return the largest normalized FloatD that is not infinite. fminNormalized Return the smallest normalized FloatD that is > 0 infinity Return a FloatD that represents positive infinity. nan Return a FloatD that represents a mathematically indeterminate value (e.g. Inf - Inf, Inf / Inf). negativeInfinity Return a FloatD that represents negative infinity. precision Answer the number of bits in the mantissa. 1 + (2^-precision) = 1  File: gst-base.info, Node: FloatD class-converting, Next: FloatD-built ins, Prev: FloatD class-characterization, Up: FloatD 1.81.3 FloatD class: converting ------------------------------- coerce: aNumber Answer aNumber converted to a FloatD  File: gst-base.info, Node: FloatD-built ins, Next: FloatD-coercing, Prev: FloatD class-converting, Up: FloatD 1.81.4 FloatD: built ins ------------------------ * arg Multiply the receiver and arg and answer another Number + arg Sum the receiver and arg and answer another Number - arg Subtract arg from the receiver and answer another Number / arg Divide the receiver by arg and answer another FloatD < arg Answer whether the receiver is less than arg <= arg Answer whether the receiver is less than or equal to arg = arg Answer whether the receiver is equal to arg > arg Answer whether the receiver is greater than arg >= arg Answer whether the receiver is greater than or equal to arg asFloatE Answer the receiver converted to a FloatE asFloatQ Answer the receiver converted to a FloatQ exponent Answer the exponent of the receiver in mantissa*2^exponent representation ( |mantissa|<=1 ) fractionPart Answer the fractional part of the receiver timesTwoPower: arg Answer the receiver multiplied by 2^arg truncated Truncate the receiver towards zero and answer the result ~= arg Answer whether the receiver is not equal to arg  File: gst-base.info, Node: FloatD-coercing, Next: FloatD-converting, Prev: FloatD-built ins, Up: FloatD 1.81.5 FloatD: coercing ----------------------- asFloatD Just defined for completeness. Return the receiver. coerce: aNumber Coerce aNumber to the receiver's class generality Answer the receiver's generality unity Coerce 1 to the receiver's class zero Coerce 0 to the receiver's class  File: gst-base.info, Node: FloatD-converting, Prev: FloatD-coercing, Up: FloatD 1.81.6 FloatD: converting ------------------------- half Coerce 0.5 to the receiver's class  File: gst-base.info, Node: FloatE, Next: FloatQ, Prev: FloatD, Up: Base classes 1.82 FloatE =========== Defined in namespace Smalltalk Superclass: Float Category: Language-Data types My instances represent floating point numbers that have the same accuracy as C's "float" numbers. * Menu: * FloatE class-byte-order dependancies:: (class) * FloatE class-byte-order dependencies:: (class) * FloatE class-characterization:: (class) * FloatE class-converting:: (class) * FloatE-built ins:: (instance) * FloatE-coercing:: (instance) * FloatE-converting:: (instance)  File: gst-base.info, Node: FloatE class-byte-order dependancies, Next: FloatE class-byte-order dependencies, Up: FloatE 1.82.1 FloatE class: byte-order dependancies -------------------------------------------- signByte Answer the byte of the receiver that contains the sign bit  File: gst-base.info, Node: FloatE class-byte-order dependencies, Next: FloatE class-characterization, Prev: FloatE class-byte-order dependancies, Up: FloatE 1.82.2 FloatE class: byte-order dependencies -------------------------------------------- fromBytes: aByteArray Answer a float with the bytes in aByteArray, which are in big-endian format.  File: gst-base.info, Node: FloatE class-characterization, Next: FloatE class-converting, Prev: FloatE class-byte-order dependencies, Up: FloatE 1.82.3 FloatE class: characterization ------------------------------------- decimalDigits Return the number of decimal digits of precision for a FloatE. Technically, if P is the precision for the representation, then the decimal precision Q is the maximum number of decimal digits such that any floating point number with Q base 10 digits can be rounded to a floating point number with P base 2 digits and back again, without change to the Q decimal digits. e Returns the value of e. Hope is that it is precise enough emax Return the maximum allowable exponent for a FloatE that is finite. emin Return the maximum allowable exponent for a FloatE that is finite. fmax Return the largest normalized FloatE that is not infinite. fminNormalized Return the smallest normalized FloatE that is > 0 infinity Return a FloatE that represents positive infinity. ln10 Returns the value of ln 10. Hope is that it is precise enough log10Base2 Returns the value of log2 10. Hope is that it is precise enough nan Return a FloatE that represents a mathematically indeterminate value (e.g. Inf - Inf, Inf / Inf). negativeInfinity Return a FloatE that represents negative infinity. pi Returns the value of pi. Hope is that it is precise enough precision Answer the number of bits in the mantissa. 1 + (2^-precision) = 1  File: gst-base.info, Node: FloatE class-converting, Next: FloatE-built ins, Prev: FloatE class-characterization, Up: FloatE 1.82.4 FloatE class: converting ------------------------------- coerce: aNumber Answer aNumber converted to a FloatE  File: gst-base.info, Node: FloatE-built ins, Next: FloatE-coercing, Prev: FloatE class-converting, Up: FloatE 1.82.5 FloatE: built ins ------------------------ * arg Multiply the receiver and arg and answer another Number + arg Sum the receiver and arg and answer another Number - arg Subtract arg from the receiver and answer another Number / arg Divide the receiver by arg and answer another FloatE < arg Answer whether the receiver is less than arg <= arg Answer whether the receiver is less than or equal to arg = arg Answer whether the receiver is equal to arg > arg Answer whether the receiver is greater than arg >= arg Answer whether the receiver is greater than or equal to arg asFloatD Answer the receiver converted to a FloatD asFloatQ Answer the receiver converted to a FloatQ exponent Answer the exponent of the receiver in mantissa*2^exponent representation ( |mantissa|<=1 ) fractionPart Answer the fractional part of the receiver timesTwoPower: arg Answer the receiver multiplied by 2^arg truncated Truncate the receiver towards zero and answer the result ~= arg Answer whether the receiver is not equal to arg  File: gst-base.info, Node: FloatE-coercing, Next: FloatE-converting, Prev: FloatE-built ins, Up: FloatE 1.82.6 FloatE: coercing ----------------------- asFloatE Just defined for completeness. Return the receiver. coerce: aNumber Coerce aNumber to the receiver's class generality Answer the receiver's generality unity Coerce 1 to the receiver's class zero Coerce 0 to the receiver's class  File: gst-base.info, Node: FloatE-converting, Prev: FloatE-coercing, Up: FloatE 1.82.7 FloatE: converting ------------------------- half Coerce 0.5 to the receiver's class  File: gst-base.info, Node: FloatQ, Next: Fraction, Prev: FloatE, Up: Base classes 1.83 FloatQ =========== Defined in namespace Smalltalk Superclass: Float Category: Language-Data types My instances represent floating point numbers that have the same accuracy as C's "long double" numbers. * Menu: * FloatQ class-byte-order dependancies:: (class) * FloatQ class-characterization:: (class) * FloatQ class-converting:: (class) * FloatQ-built ins:: (instance) * FloatQ-coercing:: (instance) * FloatQ-converting:: (instance)  File: gst-base.info, Node: FloatQ class-byte-order dependancies, Next: FloatQ class-characterization, Up: FloatQ 1.83.1 FloatQ class: byte-order dependancies -------------------------------------------- signByte Answer the byte of the receiver that contains the sign bit  File: gst-base.info, Node: FloatQ class-characterization, Next: FloatQ class-converting, Prev: FloatQ class-byte-order dependancies, Up: FloatQ 1.83.2 FloatQ class: characterization ------------------------------------- decimalDigits Return the number of decimal digits of precision for a FloatQ. Technically, if P is the precision for the representation, then the decimal precision Q is the maximum number of decimal digits such that any floating point number with Q base 10 digits can be rounded to a floating point number with P base 2 digits and back again, without change to the Q decimal digits. e Returns the value of e. Hope is that it is precise enough emax Return the maximum allowable exponent for a FloatQ that is finite. emin Return the maximum allowable exponent for a FloatQ that is finite. fmax Return the largest normalized FloatQ that is not infinite. fminNormalized Return the smallest normalized FloatQ that is > 0 infinity Return a FloatQ that represents positive infinity. ln10 Returns the value of ln 10. Hope is that it is precise enough log10Base2 Returns the value of log2 10. Hope is that it is precise enough nan Return a FloatQ that represents a mathematically indeterminate value (e.g. Inf - Inf, Inf / Inf). negativeInfinity Return a FloatQ that represents negative infinity. pi Returns the value of pi. Hope is that it is precise enough precision Answer the number of bits in the mantissa. 1 + (2^-precision) = 1  File: gst-base.info, Node: FloatQ class-converting, Next: FloatQ-built ins, Prev: FloatQ class-characterization, Up: FloatQ 1.83.3 FloatQ class: converting ------------------------------- coerce: aNumber Answer aNumber converted to a FloatQ  File: gst-base.info, Node: FloatQ-built ins, Next: FloatQ-coercing, Prev: FloatQ class-converting, Up: FloatQ 1.83.4 FloatQ: built ins ------------------------ * arg Multiply the receiver and arg and answer another Number + arg Sum the receiver and arg and answer another Number - arg Subtract arg from the receiver and answer another Number / arg Divide the receiver by arg and answer another FloatQ < arg Answer whether the receiver is less than arg <= arg Answer whether the receiver is less than or equal to arg = arg Answer whether the receiver is equal to arg > arg Answer whether the receiver is greater than arg >= arg Answer whether the receiver is greater than or equal to arg asFloatD Answer the receiver converted to a FloatD asFloatE Answer the receiver converted to a FloatE exponent Answer the exponent of the receiver in mantissa*2^exponent representation ( |mantissa|<=1 ) fractionPart Answer the fractional part of the receiver timesTwoPower: arg Answer the receiver multiplied by 2^arg truncated Truncate the receiver towards zero and answer the result ~= arg Answer whether the receiver is not equal to arg  File: gst-base.info, Node: FloatQ-coercing, Next: FloatQ-converting, Prev: FloatQ-built ins, Up: FloatQ 1.83.5 FloatQ: coercing ----------------------- asFloatQ Just defined for completeness. Return the receiver. coerce: aNumber Coerce aNumber to the receiver's class generality Answer the receiver's generality unity Coerce 1 to the receiver's class zero Coerce 0 to the receiver's class  File: gst-base.info, Node: FloatQ-converting, Prev: FloatQ-coercing, Up: FloatQ 1.83.6 FloatQ: converting ------------------------- half Coerce 0.5 to the receiver's class  File: gst-base.info, Node: Fraction, Next: Generator, Prev: FloatQ, Up: Base classes 1.84 Fraction ============= Defined in namespace Smalltalk Superclass: Number Category: Language-Data types I represent rational numbers in the form (p/q) where p and q are integers. The arithmetic operations *, +, -, /, on fractions, all return a reduced fraction. * Menu: * Fraction class-converting:: (class) * Fraction class-instance creation:: (class) * Fraction-accessing:: (instance) * Fraction-arithmetic:: (instance) * Fraction-coercing:: (instance) * Fraction-coercion:: (instance) * Fraction-comparing:: (instance) * Fraction-converting:: (instance) * Fraction-optimized cases:: (instance) * Fraction-printing:: (instance) * Fraction-testing:: (instance)  File: gst-base.info, Node: Fraction class-converting, Next: Fraction class-instance creation, Up: Fraction 1.84.1 Fraction class: converting --------------------------------- coerce: aNumber Answer aNumber converted to a Fraction  File: gst-base.info, Node: Fraction class-instance creation, Next: Fraction-accessing, Prev: Fraction class-converting, Up: Fraction 1.84.2 Fraction class: instance creation ---------------------------------------- initialize Initialize the receiver's class variables numerator: nInteger denominator: dInteger Answer a new instance of fraction (nInteger/dInteger)  File: gst-base.info, Node: Fraction-accessing, Next: Fraction-arithmetic, Prev: Fraction class-instance creation, Up: Fraction 1.84.3 Fraction: accessing -------------------------- denominator Answer the receiver's denominator numerator Answer the receiver's numerator  File: gst-base.info, Node: Fraction-arithmetic, Next: Fraction-coercing, Prev: Fraction-accessing, Up: Fraction 1.84.4 Fraction: arithmetic --------------------------- * aNumber Multiply two numbers and answer the result. + aNumber Sum two numbers and answer the result. - aNumber Subtract aNumber from the receiver and answer the result. / aNumber Divide the receiver by aNumber and answer the result. // aNumber Return the integer quotient of dividing the receiver by aNumber with truncation towards negative infinity. \\ aNumber Return the remainder from dividing the receiver by aNumber, (using //). estimatedLog Answer an estimate of (self abs floorLog: 10)  File: gst-base.info, Node: Fraction-coercing, Next: Fraction-coercion, Prev: Fraction-arithmetic, Up: Fraction 1.84.5 Fraction: coercing ------------------------- ceiling Truncate the receiver towards positive infinity and return the truncated result coerce: aNumber Coerce aNumber to the receiver's class floor Truncate the receiver towards negative infinity and return the truncated result generality Return the receiver's generality truncated Truncate the receiver and return the truncated result unity Coerce 1 to the receiver's class zero Coerce 0 to the receiver's class  File: gst-base.info, Node: Fraction-coercion, Next: Fraction-comparing, Prev: Fraction-coercing, Up: Fraction 1.84.6 Fraction: coercion ------------------------- asCNumber Convert the receiver to a kind of number that is understood by the C call-out mechanism.  File: gst-base.info, Node: Fraction-comparing, Next: Fraction-converting, Prev: Fraction-coercion, Up: Fraction 1.84.7 Fraction: comparing -------------------------- < arg Test if the receiver is less than arg. <= arg Test if the receiver is less than or equal to arg. = arg Test if the receiver equals arg. > arg Test if the receiver is more than arg. >= arg Test if the receiver is greater than or equal to arg. hash Answer an hash value for the receiver  File: gst-base.info, Node: Fraction-converting, Next: Fraction-optimized cases, Prev: Fraction-comparing, Up: Fraction 1.84.8 Fraction: converting --------------------------- asExactFraction Answer the receiver, it is already a Fraction asFloatD Answer the receiver converted to a FloatD asFloatE Answer the receiver converted to a FloatD asFloatQ Answer the receiver converted to a FloatD asFraction Answer the receiver, it is already a Fraction integerPart Answer the integer part of the receiver, expressed as a Fraction  File: gst-base.info, Node: Fraction-optimized cases, Next: Fraction-printing, Prev: Fraction-converting, Up: Fraction 1.84.9 Fraction: optimized cases -------------------------------- negated Return the receiver, with its sign changed. raisedToInteger: anInteger Return self raised to the anInteger-th power. reciprocal Return the reciprocal of the receiver sqrt Return the square root of the receiver. squared Return the square of the receiver.  File: gst-base.info, Node: Fraction-printing, Next: Fraction-testing, Prev: Fraction-optimized cases, Up: Fraction 1.84.10 Fraction: printing -------------------------- printOn: aStream Print a representation of the receiver on aStream storeOn: aStream Store Smalltalk code compiling to the receiver on aStream  File: gst-base.info, Node: Fraction-testing, Prev: Fraction-printing, Up: Fraction 1.84.11 Fraction: testing ------------------------- isRational Answer whether the receiver is rational - true  File: gst-base.info, Node: Generator, Next: Getopt, Prev: Fraction, Up: Base classes 1.85 Generator ============== Defined in namespace Smalltalk Superclass: Stream Category: Streams-Generators A Generator object provides a way to use blocks to define a Stream of many return values. The return values are computed one at a time, as needed, and hence need not even be finite. A generator block is converted to a Generator with "Generator on: [...]". The Generator itself is passed to the block, and as soon as a message like #next, #peek, #atEnd or #peekFor: is sent to the generator, execution of the block starts/resumes and goes on until the generator's #yield: method is called: then the argument of #yield: will be the Generator's next element. If the block goes on to the end without calling #yield:, the Generator will produce no more elements and #atEnd will return true. You could achieve the effect of generators manually by writing your own class and storing all the local variables of the generator as instance variables. For example, returning a list of integers could be done by setting a variable to 0, and having the #next method increment it and return it. However, for a moderately complicated generator, writing a corresponding class would be much messier (and might lead to code duplication or inefficiency if you want to support #peek, #peekFor: and/or #atEnd): in general, providing a #do:-like interface is easy, but not providing a Stream-like one (think binary trees). The idea of generators comes from other programming languages, in particular this interface looks much like Scheme streams and Python generators. But Python in turn mutuated the idea for example from Icon, where the idea of generators is central. In Icon, every expression and function call behaves like a generator, and if a statement manages scalars, it automatically uses up all the results that the corresponding generator provides; on the other hand, Icon does not represent generators as first-class objects like Python and Smalltalk do. * Menu: * Generator class-instance creation:: (class) * Generator-stream protocol:: (instance)  File: gst-base.info, Node: Generator class-instance creation, Next: Generator-stream protocol, Up: Generator 1.85.1 Generator class: instance creation ----------------------------------------- inject: aValue into: aBlock Return an infinite generator; the first item is aValue, the following items are obtained by passing the previous value to aBlock. on: aBlock Return a generator and pass it to aBlock. When #next is sent to the generator, the block will start execution, and will be suspended again as soon as #yield: is sent from the block to the generator. on: aCollection do: aBlock Return a generator; for each item of aCollection, evaluate aBlock passing the generator and the item.  File: gst-base.info, Node: Generator-stream protocol, Prev: Generator class-instance creation, Up: Generator 1.85.2 Generator: stream protocol --------------------------------- atEnd Answer whether more data can be generated. next Evaluate the generator until it generates the next value or decides that nothing else can be generated. peek Evaluate the generator until it generates the next value or decides that nothing else can be generated, and save the value so that #peek or #next will return it again. peekFor: anObject Evaluate the generator until it generates the next value or decides that nothing else can be generated, and if it is not equal to anObject, save the value so that #peek or #next will return it again. yield: anObject When entering from the generator the code in the block is executed and control flow goes back to the consumer. When entering from the consumer, the code after the continuation is executed, which resumes execution of the generator block.  File: gst-base.info, Node: Getopt, Next: Halt, Prev: Generator, Up: Base classes 1.86 Getopt =========== Defined in namespace Smalltalk Superclass: Object Category: Language-Data types This class is usually not instantiated. Class methods provide a way to parse command lines from Smalltalk. * Menu: * Getopt class-instance creation:: (class)  File: gst-base.info, Node: Getopt class-instance creation, Up: Getopt 1.86.1 Getopt class: instance creation -------------------------------------- parse: args with: pattern do: actionBlock Parse the command-line arguments in args according to the syntax specified in pattern. For every command-line option found, the two-argument block actionBlock is evaluated passing the option name and the argument. For file names (or in general, other command-line arguments than options) the block's first argument will be nil. For options without arguments, or with unspecified optional arguments, the block's second argument will be nil. The option name will be passed as a character object for short options, and as a string for long options. If an error is found, nil is returned. For more information on the syntax of pattern, see #parse:with:do:ifError:. parse: args with: pattern do: actionBlock ifError: errorBlock Parse the command-line arguments in args according to the syntax specified in pattern. For every command-line option found, the two-argument block actionBlock is evaluated passing the option name and the argument. For file names (or in general, other command-line arguments than options) the block's first argument will be nil. For options without arguments, or with unspecified optional arguments, the block's second argument will be nil. The option name will be passed as a character object for short options, and as a string for long options. If an error is found, the parsing is interrupted, errorBlock is evaluated, and the returned value is answered. Every whitespace-separated part (`word') of pattern specifies a command-line option. If a word ends with a colon, the option will have a mandatory argument. If a word ends with two colons, the option will have an optional argument. Before the colons, multiple option names (either short names like `-l' or long names like `-long') can be specified. Before passing the option to actionBlock, the name will be canonicalized to the last one. Prefixes of long options are accepted as long as they're unique, and they are canonicalized to the full name before passing it to actionBlock. Additionally, the full name of an option is accepted even if it is the prefix of a longer option. Mandatory arguments can appear in the next argument, or in the same argument (separated by an = for arguments to long options). Optional arguments must appear in the same argument.  File: gst-base.info, Node: Halt, Next: HashedCollection, Prev: Getopt, Up: Base classes 1.87 Halt ========= Defined in namespace Smalltalk Superclass: Exception Category: Language-Exceptions Halt represents a resumable error, usually a bug. * Menu: * Halt-description:: (instance)  File: gst-base.info, Node: Halt-description, Up: Halt 1.87.1 Halt: description ------------------------ description Answer a textual description of the exception. isResumable Answer true. #halt exceptions are by default resumable.  File: gst-base.info, Node: HashedCollection, Next: HomedAssociation, Prev: Halt, Up: Base classes 1.88 HashedCollection ===================== Defined in namespace Smalltalk Superclass: Collection Category: Collections-Unordered I am an hashed collection that can store objects uniquely and give fast responses on their presence in the collection. * Menu: * HashedCollection class-instance creation:: (class) * HashedCollection-accessing:: (instance) * HashedCollection-builtins:: (instance) * HashedCollection-copying:: (instance) * HashedCollection-enumerating the elements of a collection:: (instance) * HashedCollection-rehashing:: (instance) * HashedCollection-removing:: (instance) * HashedCollection-saving and loading:: (instance) * HashedCollection-storing:: (instance) * HashedCollection-testing collections:: (instance)  File: gst-base.info, Node: HashedCollection class-instance creation, Next: HashedCollection-accessing, Up: HashedCollection 1.88.1 HashedCollection class: instance creation ------------------------------------------------ new Answer a new instance of the receiver with a default size new: anInteger Answer a new instance of the receiver with the given capacity withAll: aCollection Answer a collection whose elements are all those in aCollection  File: gst-base.info, Node: HashedCollection-accessing, Next: HashedCollection-builtins, Prev: HashedCollection class-instance creation, Up: HashedCollection 1.88.2 HashedCollection: accessing ---------------------------------- add: newObject Add newObject to the set, if and only if the set doesn't already contain an occurrence of it. Don't fail if a duplicate is found. Answer anObject at: index This method should not be called for instances of this class. at: index put: value This method should not be called for instances of this class.  File: gst-base.info, Node: HashedCollection-builtins, Next: HashedCollection-copying, Prev: HashedCollection-accessing, Up: HashedCollection 1.88.3 HashedCollection: builtins --------------------------------- primAt: anIndex Private - Answer the anIndex-th item of the hash table for the receiver. Using this instead of basicAt: allows for easier changes in the representation primAt: anIndex put: value Private - Store value in the anIndex-th item of the hash table for the receiver. Using this instead of basicAt:put: allows for easier changes in the representation primSize Private - Answer the size of the hash table for the receiver. Using this instead of basicSize allows for easier changes in the representation  File: gst-base.info, Node: HashedCollection-copying, Next: HashedCollection-enumerating the elements of a collection, Prev: HashedCollection-builtins, Up: HashedCollection 1.88.4 HashedCollection: copying -------------------------------- deepCopy Returns a deep copy of the receiver (the instance variables are copies of the receiver's instance variables) shallowCopy Returns a shallow copy of the receiver (the instance variables are not copied)  File: gst-base.info, Node: HashedCollection-enumerating the elements of a collection, Next: HashedCollection-rehashing, Prev: HashedCollection-copying, Up: HashedCollection 1.88.5 HashedCollection: enumerating the elements of a collection ----------------------------------------------------------------- do: aBlock Enumerate all the non-nil members of the set  File: gst-base.info, Node: HashedCollection-rehashing, Next: HashedCollection-removing, Prev: HashedCollection-enumerating the elements of a collection, Up: HashedCollection 1.88.6 HashedCollection: rehashing ---------------------------------- rehash Rehash the receiver  File: gst-base.info, Node: HashedCollection-removing, Next: HashedCollection-saving and loading, Prev: HashedCollection-rehashing, Up: HashedCollection 1.88.7 HashedCollection: removing --------------------------------- remove: oldObject ifAbsent: anExceptionBlock Remove oldObject from the set. If it is found, answer oldObject. Otherwise, evaluate anExceptionBlock and answer its value.  File: gst-base.info, Node: HashedCollection-saving and loading, Next: HashedCollection-storing, Prev: HashedCollection-removing, Up: HashedCollection 1.88.8 HashedCollection: saving and loading ------------------------------------------- postLoad Called after loading an object; rehash the collection because identity objects will most likely mutate their hashes. postStore Called after an object is dumped. Do nothing - necessary because by default this calls #postLoad by default  File: gst-base.info, Node: HashedCollection-storing, Next: HashedCollection-testing collections, Prev: HashedCollection-saving and loading, Up: HashedCollection 1.88.9 HashedCollection: storing -------------------------------- storeOn: aStream Store on aStream some Smalltalk code which compiles to the receiver  File: gst-base.info, Node: HashedCollection-testing collections, Prev: HashedCollection-storing, Up: HashedCollection 1.88.10 HashedCollection: testing collections --------------------------------------------- = aHashedCollection Returns true if the two sets have the same membership, false if not capacity Answer how many elements the receiver can hold before having to grow. hash Return the hash code for the members of the set. Since order is unimportant, we use a commutative operator to compute the hash value. includes: anObject Answer whether the receiver contains an instance of anObject. isEmpty Answer whether the receiver is empty. occurrencesOf: anObject Return the number of occurrences of anObject. Since we're a set, this is either 0 or 1. Nil is never directly in the set, so we special case it (the result is always 1). size Answer the receiver's size  File: gst-base.info, Node: HomedAssociation, Next: IdentityDictionary, Prev: HashedCollection, Up: Base classes 1.89 HomedAssociation ===================== Defined in namespace Smalltalk Superclass: Association Category: Language-Data types My instances represent know about their parent namespace, which is of use when implementing weak collections and finalizations. * Menu: * HomedAssociation class-basic:: (class) * HomedAssociation-accessing:: (instance) * HomedAssociation-finalization:: (instance) * HomedAssociation-storing:: (instance)  File: gst-base.info, Node: HomedAssociation class-basic, Next: HomedAssociation-accessing, Up: HomedAssociation 1.89.1 HomedAssociation class: basic ------------------------------------ key: aKey value: aValue environment: aNamespace Answer a new association with the given key and value  File: gst-base.info, Node: HomedAssociation-accessing, Next: HomedAssociation-finalization, Prev: HomedAssociation class-basic, Up: HomedAssociation 1.89.2 HomedAssociation: accessing ---------------------------------- environment Answer the namespace in which I live. environment: aNamespace Set the namespace in which I live to be aNamespace.  File: gst-base.info, Node: HomedAssociation-finalization, Next: HomedAssociation-storing, Prev: HomedAssociation-accessing, Up: HomedAssociation 1.89.3 HomedAssociation: finalization ------------------------------------- mourn This message is sent to the receiver when the object is made ephemeron (which is common when HomedAssociations are used by a WeakKeyDictionary or a WeakSet). The mourning of the object's key is first of all demanded to the environment (which will likely remove the object from itself), and then performed as usual by clearing the key and value fields.  File: gst-base.info, Node: HomedAssociation-storing, Prev: HomedAssociation-finalization, Up: HomedAssociation 1.89.4 HomedAssociation: storing -------------------------------- storeOn: aStream Put on aStream some Smalltalk code compiling to the receiver  File: gst-base.info, Node: IdentityDictionary, Next: IdentitySet, Prev: HomedAssociation, Up: Base classes 1.90 IdentityDictionary ======================= Defined in namespace Smalltalk Superclass: LookupTable Category: Collections-Keyed I am similar to LookupTable, except that I use the object identity comparision message == to determine equivalence of indices. * Menu:  File: gst-base.info, Node: IdentitySet, Next: Integer, Prev: IdentityDictionary, Up: Base classes 1.91 IdentitySet ================ Defined in namespace Smalltalk Superclass: Set Category: Collections-Unordered I am the typical set object; I can store any objects uniquely. I use the == operator to determine duplication of objects. * Menu: * IdentitySet-testing:: (instance)  File: gst-base.info, Node: IdentitySet-testing, Up: IdentitySet 1.91.1 IdentitySet: testing --------------------------- identityIncludes: anObject Answer whether we include the anObject object; for IdentitySets this is identical to #includes:  File: gst-base.info, Node: Integer, Next: Interval, Prev: IdentitySet, Up: Base classes 1.92 Integer ============ Defined in namespace Smalltalk Superclass: Number Category: Language-Data types I am the abstract integer class of the GNU Smalltalk system. My subclasses' instances can represent signed integers of various sizes (a subclass is picked according to the size), with varying efficiency. * Menu: * Integer class-converting:: (class) * Integer-accessing:: (instance) * Integer-basic:: (instance) * Integer-bit operators:: (instance) * Integer-converting:: (instance) * Integer-extension:: (instance) * Integer-iterators:: (instance) * Integer-math methods:: (instance) * Integer-printing:: (instance) * Integer-storing:: (instance) * Integer-testing functionality:: (instance)  File: gst-base.info, Node: Integer class-converting, Next: Integer-accessing, Up: Integer 1.92.1 Integer class: converting -------------------------------- coerce: aNumber Answer aNumber converted to a kind of Integer  File: gst-base.info, Node: Integer-accessing, Next: Integer-basic, Prev: Integer class-converting, Up: Integer 1.92.2 Integer: accessing ------------------------- denominator Answer `1'. numerator Answer the receiver.  File: gst-base.info, Node: Integer-basic, Next: Integer-bit operators, Prev: Integer-accessing, Up: Integer 1.92.3 Integer: basic --------------------- hash Answer an hash value for the receiver  File: gst-base.info, Node: Integer-bit operators, Next: Integer-converting, Prev: Integer-basic, Up: Integer 1.92.4 Integer: bit operators ----------------------------- allMask: anInteger True if all 1 bits in anInteger are 1 in the receiver anyMask: anInteger True if any 1 bits in anInteger are 1 in the receiver bitAt: index Answer the index-th bit of the receiver (the LSB has an index of 1) bitAt: index put: value Answer an integer which is identical to the receiver, possibly with the exception of the index-th bit of the receiver (the LSB having an index of 1), which assumes a value equal to the low-order bit of the second parameter. bitClear: aMask Answer an Integer equal to the receiver, except that all the bits that are set in aMask are cleared. bitInvert Return the 1's complement of the bits of the receiver clearBit: index Clear the index-th bit of the receiver and answer a new Integer digitAt: index Answer the index-th base-256 digit of the receiver (byte), expressed in two's complement highBit Return the index of the highest order 1 bit of the receiver. isBitSet: index Answer whether the index-th bit of the receiver is set lowBit Return the index of the lowest order 1 bit of the receiver. noMask: anInteger Answer true if no 1 bits in anInteger are 1 in the receiver. setBit: index Set the index-th bit of the receiver and answer a new Integer  File: gst-base.info, Node: Integer-converting, Next: Integer-extension, Prev: Integer-bit operators, Up: Integer 1.92.5 Integer: converting -------------------------- asCharacter Return self as a Character or UnicodeCharacter object. asFraction Return the receiver converted to a fraction asScaledDecimal: n Answer the receiver, converted to a ScaledDecimal object. The scale is forced to be 0. ceiling Return the receiver - it's already truncated coerce: aNumber Coerce aNumber to the receiver's class. floor Return the receiver - it's already truncated rounded Return the receiver - it's already truncated truncated Return the receiver - it's already truncated  File: gst-base.info, Node: Integer-extension, Next: Integer-iterators, Prev: Integer-converting, Up: Integer 1.92.6 Integer: extension ------------------------- alignTo: anInteger Answer the receiver, truncated to the first higher or equal multiple of anInteger (which must be a power of two)  File: gst-base.info, Node: Integer-iterators, Next: Integer-math methods, Prev: Integer-extension, Up: Integer 1.92.7 Integer: iterators ------------------------- timesRepeat: aBlock Evaluate aBlock a number of times equal to the receiver's value. Compiled in-line for no argument aBlocks without temporaries, and therefore not overridable.  File: gst-base.info, Node: Integer-math methods, Next: Integer-printing, Prev: Integer-iterators, Up: Integer 1.92.8 Integer: math methods ---------------------------- binomial: anInteger Compute the number of combinations of anInteger objects among a number of objects given by the receiver. ceilingLog: radix Answer (self log: radix) ceiling. Optimized to answer an integer. estimatedLog Answer an estimate of (self abs floorLog: 10) even Return whether the receiver is even factorial Return the receiver's factorial. floorLog: radix Answer (self log: radix) floor. Optimized to answer an integer. gcd: anInteger Return the greatest common divisor (Euclid's algorithm) between the receiver and anInteger lcm: anInteger Return the least common multiple between the receiver and anInteger odd Return whether the receiver is odd  File: gst-base.info, Node: Integer-printing, Next: Integer-storing, Prev: Integer-math methods, Up: Integer 1.92.9 Integer: printing ------------------------ displayOn: aStream Print on aStream the base 10 representation of the receiver displayString Return the base 10 representation of the receiver isLiteralObject Answer whether the receiver is expressible as a Smalltalk literal. printOn: aStream Print on aStream the base 10 representation of the receiver printOn: aStream base: b Print on aStream the base b representation of the receiver printOn: aStream paddedWith: padding to: size Print on aStream the base 10 representation of the receiver, padded if necessary to size characters with copies of padding. printOn: aStream paddedWith: padding to: size base: baseInteger Print on aStream the base b representation of the receiver, padded if necessary to size characters with copies of padding. printPaddedWith: padding to: size Return the base baseInteger representation of the receiver, padded if necessary to size characters with copies of padding. printPaddedWith: padding to: size base: baseInteger Return the base baseInteger representation of the receiver, padded if necessary to size characters with copies of padding. printString Return the base 10 representation of the receiver printString: baseInteger Return the base baseInteger representation of the receiver printStringRadix: baseInteger Return the base baseInteger representation of the receiver, with BBr in front of it radix: baseInteger Return the base baseInteger representation of the receiver, with BBr in front of it. This method is deprecated, use #printStringRadix: instead. storeLiteralOn: aStream Store on aStream some Smalltalk code which compiles to the receiver storeOn: aStream base: b Print on aStream Smalltalk code compiling to the receiver, represented in base b  File: gst-base.info, Node: Integer-storing, Next: Integer-testing functionality, Prev: Integer-printing, Up: Integer 1.92.10 Integer: storing ------------------------ storeOn: aStream Print on aStream the base 10 representation of the receiver storeString Return the base 10 representation of the receiver  File: gst-base.info, Node: Integer-testing functionality, Prev: Integer-storing, Up: Integer 1.92.11 Integer: testing functionality -------------------------------------- isInteger Answer `true'. isRational Answer whether the receiver is rational - true  File: gst-base.info, Node: Interval, Next: Iterable, Prev: Integer, Up: Base classes 1.93 Interval ============= Defined in namespace Smalltalk Superclass: ArrayedCollection Category: Collections-Sequenceable My instances represent ranges of objects, typically Number type objects. I provide iteration/enumeration messages for producing all the members that my instance represents. * Menu: * Interval class-instance creation:: (class) * Interval-basic:: (instance) * Interval-printing:: (instance) * Interval-storing:: (instance) * Interval-testing:: (instance)  File: gst-base.info, Node: Interval class-instance creation, Next: Interval-basic, Up: Interval 1.93.1 Interval class: instance creation ---------------------------------------- from: startInteger to: stopInteger Answer an Interval going from startInteger to the stopInteger, with a step of 1 from: startInteger to: stopInteger by: stepInteger Answer an Interval going from startInteger to the stopInteger, with a step of stepInteger withAll: aCollection Answer an Interval containing the same elements as aCollection. Fail if it is not possible to create one.  File: gst-base.info, Node: Interval-basic, Next: Interval-printing, Prev: Interval class-instance creation, Up: Interval 1.93.2 Interval: basic ---------------------- at: index Answer the index-th element of the receiver. at: index put: anObject This method should not be called for instances of this class. collect: aBlock Evaluate the receiver for each element in aBlock, collect in an array the result of the evaluations. copyFrom: startIndex to: stopIndex Not commented. do: aBlock Evaluate the receiver for each element in aBlock isEmpty Answer whether the receiver is empty. reverse Answer a copy of the receiver with all of its items reversed size Answer the number of elements in the receiver. species Answer `Array'.  File: gst-base.info, Node: Interval-printing, Next: Interval-storing, Prev: Interval-basic, Up: Interval 1.93.3 Interval: printing ------------------------- first Not commented. increment Answer `step'. last Answer the last value. printOn: aStream Print a representation for the receiver on aStream  File: gst-base.info, Node: Interval-storing, Next: Interval-testing, Prev: Interval-printing, Up: Interval 1.93.4 Interval: storing ------------------------ storeOn: aStream Store Smalltalk code compiling to the receiver on aStream  File: gst-base.info, Node: Interval-testing, Prev: Interval-storing, Up: Interval 1.93.5 Interval: testing ------------------------ = anInterval Answer whether anInterval is the same interval as the receiver hash Answer an hash value for the receiver isExact Answer whether elements of the receiver are computed using exact arithmetic. This is true as long as the start and step value are exact (i.e. not floating-point).  File: gst-base.info, Node: Iterable, Next: LargeArray, Prev: Interval, Up: Base classes 1.94 Iterable ============= Defined in namespace Smalltalk Superclass: Object Category: Collections I am an abstract class. My instances are collections of objects that can be iterated. The details on how they can be mutated (if at all possible) are left to the subclasses. * Menu: * Iterable class-multibyte encodings:: (class) * Iterable-enumeration:: (instance) * Iterable-iteration:: (instance) * Iterable-streaming:: (instance)  File: gst-base.info, Node: Iterable class-multibyte encodings, Next: Iterable-enumeration, Up: Iterable 1.94.1 Iterable class: multibyte encodings ------------------------------------------ isUnicode Answer true; the receiver is able to store arbitrary Unicode characters.  File: gst-base.info, Node: Iterable-enumeration, Next: Iterable-iteration, Prev: Iterable class-multibyte encodings, Up: Iterable 1.94.2 Iterable: enumeration ---------------------------- , anIterable Answer an iterable that enumerates first the elements of the receiver and then the elements of anIterable. allSatisfy: aBlock Search the receiver for an element for which aBlock returns false. Answer true if none does, false otherwise. anySatisfy: aBlock Search the receiver for an element for which aBlock returns true. Answer true if some does, false otherwise. collect: aBlock Answer a new instance of a Collection containing all the results of evaluating aBlock passing each of the receiver's elements conform: aBlock Search the receiver for an element for which aBlock returns false. Answer true if none does, false otherwise. contains: aBlock Search the receiver for an element for which aBlock returns true. Answer true if some does, false otherwise. count: aBlock Count the elements of the receiver for which aBlock returns true, and return their number. detect: aBlock Search the receiver for an element for which aBlock returns true. If some does, answer it. If none does, fail detect: aBlock ifNone: exceptionBlock Search the receiver for an element for which aBlock returns true. If some does, answer it. If none does, answer the result of evaluating aBlock do: aBlock Enumerate each object of the receiver, passing them to aBlock do: aBlock separatedBy: separatorBlock Enumerate each object of the receiver, passing them to aBlock. Between every two invocations of aBlock, invoke separatorBlock fold: binaryBlock First, pass to binaryBlock the first and second elements of the receiver; for each subsequent element, pass the result of the previous evaluation and an element. Answer the result of the last invocation, or the first element if the collection has size 1. Fail if the collection is empty. inject: thisValue into: binaryBlock First, pass to binaryBlock thisValue and the first element of the receiver; for each subsequent element, pass the result of the previous evaluation and an element. Answer the result of the last invocation. noneSatisfy: aBlock Search the receiver for an element for which aBlock returns true. Answer true if none does, false otherwise. reject: aBlock Answer a new instance of a Collection containing all the elements in the receiver which, when passed to aBlock, don't answer true select: aBlock Answer a new instance of a Collection containing all the elements in the receiver which, when passed to aBlock, answer true  File: gst-base.info, Node: Iterable-iteration, Next: Iterable-streaming, Prev: Iterable-enumeration, Up: Iterable 1.94.3 Iterable: iteration -------------------------- ifNil: nilBlock ifNotNilDo: iterableBlock Evaluate nilBlock if the receiver is nil, else evaluate iterableBlock with each element of the receiver (which should be an Iterable). ifNotNilDo: iterableBlock Evaluate iterableBlock with each element of the receiver (which should be an Iterable) if not nil. Else answer nil ifNotNilDo: iterableBlock ifNil: nilBlock Evaluate nilBlock if the receiver is nil, else evaluate iterableBlock, passing each element of the receiver (which should be an Iterable).  File: gst-base.info, Node: Iterable-streaming, Prev: Iterable-iteration, Up: Iterable 1.94.4 Iterable: streaming -------------------------- nextPutAllOn: aStream Write all the objects in the receiver to aStream readStream Return a stream with the same contents as the receiver.  File: gst-base.info, Node: LargeArray, Next: LargeArrayedCollection, Prev: Iterable, Up: Base classes 1.95 LargeArray =============== Defined in namespace Smalltalk Superclass: LargeArrayedCollection Category: Collections-Sequenceable I am similar to a plain array, but I'm specially designed to save memory when lots of items are nil. * Menu: * LargeArray-overridden:: (instance)  File: gst-base.info, Node: LargeArray-overridden, Up: LargeArray 1.95.1 LargeArray: overridden ----------------------------- newCollection: size Create an Array of the given size  File: gst-base.info, Node: LargeArrayedCollection, Next: LargeByteArray, Prev: LargeArray, Up: Base classes 1.96 LargeArrayedCollection =========================== Defined in namespace Smalltalk Superclass: ArrayedCollection Category: Collections-Sequenceable I am an abstract class specially designed to save memory when lots of items have the same value. * Menu: * LargeArrayedCollection class-instance creation:: (class) * LargeArrayedCollection-accessing:: (instance) * LargeArrayedCollection-basic:: (instance)  File: gst-base.info, Node: LargeArrayedCollection class-instance creation, Next: LargeArrayedCollection-accessing, Up: LargeArrayedCollection 1.96.1 LargeArrayedCollection class: instance creation ------------------------------------------------------ new: anInteger Answer a new instance of the receiver, with room for anInteger elements.  File: gst-base.info, Node: LargeArrayedCollection-accessing, Next: LargeArrayedCollection-basic, Prev: LargeArrayedCollection class-instance creation, Up: LargeArrayedCollection 1.96.2 LargeArrayedCollection: accessing ---------------------------------------- at: anIndex Answer the anIndex-th item of the receiver. at: anIndex put: anObject Replace the anIndex-th item of the receiver with anObject. compress Arrange the representation of the array for maximum memory saving.  File: gst-base.info, Node: LargeArrayedCollection-basic, Prev: LargeArrayedCollection-accessing, Up: LargeArrayedCollection 1.96.3 LargeArrayedCollection: basic ------------------------------------ = aLargeArray Answer whether the receiver and aLargeArray have the same contents hash Answer an hash value for the receiver size Answer the maximum valid index for the receiver  File: gst-base.info, Node: LargeByteArray, Next: LargeInteger, Prev: LargeArrayedCollection, Up: Base classes 1.97 LargeByteArray =================== Defined in namespace Smalltalk Superclass: LargeArrayedCollection Category: Collections-Sequenceable I am similar to a plain ByteArray, but I'm specially designed to save memory when lots of items are zero. * Menu: * LargeByteArray-overridden:: (instance)  File: gst-base.info, Node: LargeByteArray-overridden, Up: LargeByteArray 1.97.1 LargeByteArray: overridden --------------------------------- costOfNewIndex Answer the maximum number of consecutive items set to the defaultElement that can be present in a compressed array. defaultElement Answer the value which is hoped to be the most common in the array newCollection: size Create a ByteArray of the given size  File: gst-base.info, Node: LargeInteger, Next: LargeNegativeInteger, Prev: LargeByteArray, Up: Base classes 1.98 LargeInteger ================= Defined in namespace Smalltalk Superclass: Integer Category: Language-Data types I represent a large integer, which has to be stored as a long sequence of bytes. I have methods to do arithmetics and comparisons, but I need some help from my children, LargePositiveInteger and LargeNegativeInteger, to speed them up a bit. * Menu: * LargeInteger-accessing:: (instance) * LargeInteger-arithmetic:: (instance) * LargeInteger-bit operations:: (instance) * LargeInteger-built-ins:: (instance) * LargeInteger-coercion:: (instance) * LargeInteger-disabled:: (instance) * LargeInteger-primitive operations:: (instance) * LargeInteger-testing:: (instance)  File: gst-base.info, Node: LargeInteger-accessing, Next: LargeInteger-arithmetic, Up: LargeInteger 1.98.1 LargeInteger: accessing ------------------------------ raisedToInteger: n Return self raised to the anInteger-th power  File: gst-base.info, Node: LargeInteger-arithmetic, Next: LargeInteger-bit operations, Prev: LargeInteger-accessing, Up: LargeInteger 1.98.2 LargeInteger: arithmetic ------------------------------- * aNumber Multiply aNumber and the receiver, answer the result + aNumber Sum the receiver and aNumber, answer the result - aNumber Subtract aNumber from the receiver, answer the result / aNumber Divide aNumber and the receiver, answer the result (an Integer or Fraction) // aNumber Divide aNumber and the receiver, answer the result truncated towards -infinity \\ aNumber Divide aNumber and the receiver, answer the remainder truncated towards -infinity divExact: aNumber Dividing receiver by arg assuming that the remainder is zero, and answer the result estimatedLog Answer an estimate of (self abs floorLog: 10) negated Answer the receiver's negated quo: aNumber Divide aNumber and the receiver, answer the result truncated towards 0 rem: aNumber Divide aNumber and the receiver, answer the remainder truncated towards 0  File: gst-base.info, Node: LargeInteger-bit operations, Next: LargeInteger-built-ins, Prev: LargeInteger-arithmetic, Up: LargeInteger 1.98.3 LargeInteger: bit operations ----------------------------------- bitAnd: aNumber Answer the receiver ANDed with aNumber bitAt: aNumber Answer the aNumber-th bit in the receiver, where the LSB is 1 bitInvert Answer the receiver's 1's complement bitOr: aNumber Answer the receiver ORed with aNumber bitShift: aNumber Answer the receiver shifted by aNumber places bitXor: aNumber Answer the receiver XORed with aNumber lowBit Return the index of the lowest order 1 bit of the receiver.  File: gst-base.info, Node: LargeInteger-built-ins, Next: LargeInteger-coercion, Prev: LargeInteger-bit operations, Up: LargeInteger 1.98.4 LargeInteger: built-ins ------------------------------ at: anIndex Answer the anIndex-th byte in the receiver's representation at: anIndex put: aNumber Set the anIndex-th byte in the receiver's representation digitAt: anIndex Answer the index-th base-256 digit of the receiver (byte), expressed in two's complement digitAt: anIndex put: aNumber Set the anIndex-th base-256 digit in the receiver's representation digitLength Answer the number of base-256 digits in the receiver hash Answer an hash value for the receiver primReplaceFrom: start to: stop with: replacementString startingAt: replaceStart Private - Replace the characters from start to stop with new characters contained in replacementString (which, actually, can be any variable byte class), starting at the replaceStart location of replacementString size Answer the number of indexed instance variable in the receiver  File: gst-base.info, Node: LargeInteger-coercion, Next: LargeInteger-disabled, Prev: LargeInteger-built-ins, Up: LargeInteger 1.98.5 LargeInteger: coercion ----------------------------- asCNumber Convert the receiver to a kind of number that is understood by the C call-out mechanism. coerce: aNumber Truncate the number; if needed, convert it to LargeInteger representation. generality Answer the receiver's generality unity Coerce 1 to the receiver's class zero Coerce 0 to the receiver's class  File: gst-base.info, Node: LargeInteger-disabled, Next: LargeInteger-primitive operations, Prev: LargeInteger-coercion, Up: LargeInteger 1.98.6 LargeInteger: disabled ----------------------------- asObject This method always fails. The number of OOPs is far less than the minimum number represented with a LargeInteger. asObjectNoFail Answer `nil'.  File: gst-base.info, Node: LargeInteger-primitive operations, Next: LargeInteger-testing, Prev: LargeInteger-disabled, Up: LargeInteger 1.98.7 LargeInteger: primitive operations ----------------------------------------- basicLeftShift: totalShift Private - Left shift the receiver by aNumber places basicRightShift: totalShift Private - Right shift the receiver by 'shift' places largeNegated Private - Same as negated, but always answer a LargeInteger  File: gst-base.info, Node: LargeInteger-testing, Prev: LargeInteger-primitive operations, Up: LargeInteger 1.98.8 LargeInteger: testing ---------------------------- < aNumber Answer whether the receiver is smaller than aNumber <= aNumber Answer whether the receiver is smaller than aNumber or equal to it = aNumber Answer whether the receiver and aNumber identify the same number. > aNumber Answer whether the receiver is greater than aNumber >= aNumber Answer whether the receiver is greater than aNumber or equal to it ~= aNumber Answer whether the receiver and aNumber identify different numbers.  File: gst-base.info, Node: LargeNegativeInteger, Next: LargePositiveInteger, Prev: LargeInteger, Up: Base classes 1.99 LargeNegativeInteger ========================= Defined in namespace Smalltalk Superclass: LargeInteger Category: Language-Data types Just like my brother LargePositiveInteger, I provide a few methods that allow LargeInteger to determine the sign of a large integer in a fast way during its calculations. For example, I know that I am smaller than any LargePositiveInteger * Menu: * LargeNegativeInteger-converting:: (instance) * LargeNegativeInteger-numeric testing:: (instance) * LargeNegativeInteger-reverting to LargePositiveInteger:: (instance)  File: gst-base.info, Node: LargeNegativeInteger-converting, Next: LargeNegativeInteger-numeric testing, Up: LargeNegativeInteger 1.99.1 LargeNegativeInteger: converting --------------------------------------- asFloatD Answer the receiver converted to a FloatD asFloatE Answer the receiver converted to a FloatE asFloatQ Answer the receiver converted to a FloatQ  File: gst-base.info, Node: LargeNegativeInteger-numeric testing, Next: LargeNegativeInteger-reverting to LargePositiveInteger, Prev: LargeNegativeInteger-converting, Up: LargeNegativeInteger 1.99.2 LargeNegativeInteger: numeric testing -------------------------------------------- abs Answer the receiver's absolute value. negative Answer whether the receiver is < 0 positive Answer whether the receiver is >= 0 sign Answer the receiver's sign strictlyPositive Answer whether the receiver is > 0  File: gst-base.info, Node: LargeNegativeInteger-reverting to LargePositiveInteger, Prev: LargeNegativeInteger-numeric testing, Up: LargeNegativeInteger 1.99.3 LargeNegativeInteger: reverting to LargePositiveInteger -------------------------------------------------------------- + aNumber Sum the receiver and aNumber, answer the result - aNumber Subtract aNumber from the receiver, answer the result gcd: anInteger Return the greatest common divisor between the receiver and anInteger highBit Answer the receiver's highest bit's index  File: gst-base.info, Node: LargePositiveInteger, Next: LargeWordArray, Prev: LargeNegativeInteger, Up: Base classes 1.100 LargePositiveInteger ========================== Defined in namespace Smalltalk Superclass: LargeInteger Category: Language-Data types Just like my brother LargeNegativeInteger, I provide a few methods that allow LargeInteger to determine the sign of a large integer in a fast way during its calculations. For example, I know that I am larger than any LargeNegativeInteger. In addition I implement the guts of arbitrary precision arithmetic. * Menu: * LargePositiveInteger-arithmetic:: (instance) * LargePositiveInteger-converting:: (instance) * LargePositiveInteger-helper byte-level methods:: (instance) * LargePositiveInteger-numeric testing:: (instance) * LargePositiveInteger-primitive operations:: (instance)  File: gst-base.info, Node: LargePositiveInteger-arithmetic, Next: LargePositiveInteger-converting, Up: LargePositiveInteger 1.100.1 LargePositiveInteger: arithmetic ---------------------------------------- + aNumber Sum the receiver and aNumber, answer the result - aNumber Subtract aNumber from the receiver, answer the result gcd: anInteger Calculate the GCD between the receiver and anInteger highBit Answer the receiver's highest bit's index  File: gst-base.info, Node: LargePositiveInteger-converting, Next: LargePositiveInteger-helper byte-level methods, Prev: LargePositiveInteger-arithmetic, Up: LargePositiveInteger 1.100.2 LargePositiveInteger: converting ---------------------------------------- asFloatD Answer the receiver converted to a FloatD asFloatE Answer the receiver converted to a FloatE asFloatQ Answer the receiver converted to a FloatQ replace: str withStringBase: radix Return in a String str the base radix representation of the receiver.  File: gst-base.info, Node: LargePositiveInteger-helper byte-level methods, Next: LargePositiveInteger-numeric testing, Prev: LargePositiveInteger-converting, Up: LargePositiveInteger 1.100.3 LargePositiveInteger: helper byte-level methods ------------------------------------------------------- bytes: byteArray1 from: j compare: byteArray2 Private - Answer the sign of byteArray2 - byteArray1; the j-th byte of byteArray1 is compared with the first of byteArray2, the j+1-th with the second, and so on. bytes: byteArray1 from: j subtract: byteArray2 Private - Sutract the bytes in byteArray2 from those in byteArray1 bytes: bytes multiply: anInteger Private - Multiply the bytes in bytes by anInteger, which must be < 255. Put the result back in bytes. bytesLeftShift: aByteArray Private - Left shift by 1 place the bytes in aByteArray bytesLeftShift: aByteArray big: totalShift Private - Left shift the bytes in aByteArray by totalShift places bytesLeftShift: aByteArray n: shift Private - Left shift by shift places the bytes in aByteArray (shift <= 7) bytesRightShift: aByteArray big: totalShift Private - Right shift the bytes in aByteArray by totalShift places bytesRightShift: bytes n: aNumber Private - Right shift the bytes in `bytes' by 'aNumber' places (shift <= 7) bytesTrailingZeros: bytes Private - Answer the number of trailing zero bits in the receiver primDivide: rhs Private - Implements Knuth's divide and correct algorithm from `Seminumerical Algorithms' 3rd Edition, section 4.3.1 (which is basically an enhanced version of the divide `algorithm' for two-digit divisors which is taught in primary school!!!)  File: gst-base.info, Node: LargePositiveInteger-numeric testing, Next: LargePositiveInteger-primitive operations, Prev: LargePositiveInteger-helper byte-level methods, Up: LargePositiveInteger 1.100.4 LargePositiveInteger: numeric testing --------------------------------------------- abs Answer the receiver's absolute value negative Answer whether the receiver is < 0 positive Answer whether the receiver is >= 0 sign Answer the receiver's sign strictlyPositive Answer whether the receiver is > 0  File: gst-base.info, Node: LargePositiveInteger-primitive operations, Prev: LargePositiveInteger-numeric testing, Up: LargePositiveInteger 1.100.5 LargePositiveInteger: primitive operations -------------------------------------------------- divide: aNumber using: aBlock Private - Divide the receiver by aNumber (unsigned division). Evaluate aBlock passing the result ByteArray, the remainder ByteArray, and whether the division had a remainder isSmall Private - Answer whether the receiver is small enough to employ simple scalar algorithms for division and multiplication multiply: aNumber Private - Multiply the receiver by aNumber (unsigned multiply)  File: gst-base.info, Node: LargeWordArray, Next: LargeZeroInteger, Prev: LargePositiveInteger, Up: Base classes 1.101 LargeWordArray ==================== Defined in namespace Smalltalk Superclass: LargeArrayedCollection Category: Collections-Sequenceable I am similar to a plain WordArray, but I'm specially designed to save memory when lots of items are zero. * Menu: * LargeWordArray-overridden:: (instance)  File: gst-base.info, Node: LargeWordArray-overridden, Up: LargeWordArray 1.101.1 LargeWordArray: overridden ---------------------------------- defaultElement Answer the value which is hoped to be the most common in the array newCollection: size Create a WordArray of the given size  File: gst-base.info, Node: LargeZeroInteger, Next: Link, Prev: LargeWordArray, Up: Base classes 1.102 LargeZeroInteger ====================== Defined in namespace Smalltalk Superclass: LargePositiveInteger Category: Language-Data types I am quite a strange class. Indeed, the concept of a "large integer" that is zero is a weird one. Actually my only instance is zero but is represented like LargeIntegers, has the same generality as LargeIntegers, and so on. That only instance is stored in the class variable Zero, and is used in arithmetical methods, when we have to coerce a parameter that is zero. * Menu: * LargeZeroInteger-accessing:: (instance) * LargeZeroInteger-arithmetic:: (instance) * LargeZeroInteger-numeric testing:: (instance) * LargeZeroInteger-printing:: (instance)  File: gst-base.info, Node: LargeZeroInteger-accessing, Next: LargeZeroInteger-arithmetic, Up: LargeZeroInteger 1.102.1 LargeZeroInteger: accessing ----------------------------------- at: anIndex Answer `0'. hash Answer `0'. size Answer `0'.  File: gst-base.info, Node: LargeZeroInteger-arithmetic, Next: LargeZeroInteger-numeric testing, Prev: LargeZeroInteger-accessing, Up: LargeZeroInteger 1.102.2 LargeZeroInteger: arithmetic ------------------------------------ * aNumber Multiply aNumber and the receiver, answer the result + aNumber Sum the receiver and aNumber, answer the result - aNumber Subtract aNumber from the receiver, answer the result / aNumber Divide aNumber and the receiver, answer the result (an Integer or Fraction) // aNumber Divide aNumber and the receiver, answer the result truncated towards -infinity \\ aNumber Divide aNumber and the receiver, answer the remainder truncated towards -infinity quo: aNumber Divide aNumber and the receiver, answer the result truncated towards 0 rem: aNumber Divide aNumber and the receiver, answer the remainder truncated towards 0  File: gst-base.info, Node: LargeZeroInteger-numeric testing, Next: LargeZeroInteger-printing, Prev: LargeZeroInteger-arithmetic, Up: LargeZeroInteger 1.102.3 LargeZeroInteger: numeric testing ----------------------------------------- sign Answer the receiver's sign strictlyPositive Answer whether the receiver is > 0  File: gst-base.info, Node: LargeZeroInteger-printing, Prev: LargeZeroInteger-numeric testing, Up: LargeZeroInteger 1.102.4 LargeZeroInteger: printing ---------------------------------- replace: str withStringBase: radix Return in a string the base radix representation of the receiver.  File: gst-base.info, Node: Link, Next: LinkedList, Prev: LargeZeroInteger, Up: Base classes 1.103 Link ========== Defined in namespace Smalltalk Superclass: Object Category: Collections-Sequenceable I represent simple linked lists. Generally, I am not used by myself, but rather a subclass adds other instance variables that hold the information for each node, and I hold the glue that keeps them together. * Menu: * Link class-instance creation:: (class) * Link-basic:: (instance) * Link-iteration:: (instance)  File: gst-base.info, Node: Link class-instance creation, Next: Link-basic, Up: Link 1.103.1 Link class: instance creation ------------------------------------- nextLink: aLink Create an instance with the given next link  File: gst-base.info, Node: Link-basic, Next: Link-iteration, Prev: Link class-instance creation, Up: Link 1.103.2 Link: basic ------------------- nextLink Answer the next item in the list nextLink: aLink Set the next item in the list  File: gst-base.info, Node: Link-iteration, Prev: Link-basic, Up: Link 1.103.3 Link: iteration ----------------------- at: index Retrieve a node (instance of Link) that is at a distance of `index' after the receiver. at: index put: object This method should not be called for instances of this class. do: aBlock Evaluate aBlock for each element in the list size Answer the number of elements in the list. Warning: this is O(n)  File: gst-base.info, Node: LinkedList, Next: LookupKey, Prev: Link, Up: Base classes 1.104 LinkedList ================ Defined in namespace Smalltalk Superclass: SequenceableCollection Category: Collections-Sequenceable I provide methods that access and manipulate linked lists. I assume that the elements of the linked list are subclasses of Link, because I use the methods that class Link supplies to implement my methods. * Menu: * LinkedList-accessing:: (instance) * LinkedList-adding:: (instance) * LinkedList-enumerating:: (instance) * LinkedList-iteration:: (instance) * LinkedList-testing:: (instance)  File: gst-base.info, Node: LinkedList-accessing, Next: LinkedList-adding, Up: LinkedList 1.104.1 LinkedList: accessing ----------------------------- at: index Return the element that is index into the linked list. at: index put: object This method should not be called for instances of this class.  File: gst-base.info, Node: LinkedList-adding, Next: LinkedList-enumerating, Prev: LinkedList-accessing, Up: LinkedList 1.104.2 LinkedList: adding -------------------------- add: aLink Add aLink at the end of the list; return aLink. addFirst: aLink Add aLink at the head of the list; return aLink. addLast: aLink Add aLink at then end of the list; return aLink. remove: aLink ifAbsent: aBlock Remove aLink from the list and return it, or invoke aBlock if it's not found in the list. removeFirst Remove the first element from the list and return it, or error if the list is empty. removeLast Remove the final element from the list and return it, or error if the list is empty.  File: gst-base.info, Node: LinkedList-enumerating, Next: LinkedList-iteration, Prev: LinkedList-adding, Up: LinkedList 1.104.3 LinkedList: enumerating ------------------------------- do: aBlock Enumerate each object in the list, passing it to aBlock (actual behavior might depend on the subclass of Link that is being used). identityIncludes: anObject Answer whether we include the anObject object includes: anObject Answer whether we include anObject  File: gst-base.info, Node: LinkedList-iteration, Next: LinkedList-testing, Prev: LinkedList-enumerating, Up: LinkedList 1.104.4 LinkedList: iteration ----------------------------- first Retrieve the first element of the list and return it, or error if the list is empty. last Retrieve the last element of the list and return it, or error if the list is empty.  File: gst-base.info, Node: LinkedList-testing, Prev: LinkedList-iteration, Up: LinkedList 1.104.5 LinkedList: testing --------------------------- isEmpty Returns true if the list contains no members notEmpty Returns true if the list contains at least a member size Answer the number of elements in the list. Warning: this is O(n)  File: gst-base.info, Node: LookupKey, Next: LookupTable, Prev: LinkedList, Up: Base classes 1.105 LookupKey =============== Defined in namespace Smalltalk Superclass: Magnitude Category: Language-Data types I represent a key for looking up entries in a data structure. Subclasses of me, such as Association, typically represent dictionary entries. * Menu: * LookupKey class-basic:: (class) * LookupKey-accessing:: (instance) * LookupKey-printing:: (instance) * LookupKey-storing:: (instance) * LookupKey-testing:: (instance)  File: gst-base.info, Node: LookupKey class-basic, Next: LookupKey-accessing, Up: LookupKey 1.105.1 LookupKey class: basic ------------------------------ key: aKey Answer a new instance of the receiver with the given key and value  File: gst-base.info, Node: LookupKey-accessing, Next: LookupKey-printing, Prev: LookupKey class-basic, Up: LookupKey 1.105.2 LookupKey: accessing ---------------------------- key Answer the receiver's key key: aKey Set the receiver's key to aKey  File: gst-base.info, Node: LookupKey-printing, Next: LookupKey-storing, Prev: LookupKey-accessing, Up: LookupKey 1.105.3 LookupKey: printing --------------------------- printOn: aStream Put on aStream a representation of the receiver  File: gst-base.info, Node: LookupKey-storing, Next: LookupKey-testing, Prev: LookupKey-printing, Up: LookupKey 1.105.4 LookupKey: storing -------------------------- storeOn: aStream Put on aStream some Smalltalk code compiling to the receiver  File: gst-base.info, Node: LookupKey-testing, Prev: LookupKey-storing, Up: LookupKey 1.105.5 LookupKey: testing -------------------------- < aLookupKey Answer whether the receiver's key is less than aLookupKey's = aLookupKey Answer whether the receiver's key and value are the same as aLookupKey's, or false if aLookupKey is not an instance of the receiver hash Answer an hash value for the receiver  File: gst-base.info, Node: LookupTable, Next: Magnitude, Prev: LookupKey, Up: Base classes 1.106 LookupTable ================= Defined in namespace Smalltalk Superclass: Dictionary Category: Collections-Keyed I am a more efficient variant of Dictionary that cannot be used as a pool dictionary of variables, as I don't use Associations to store key-value pairs. I also cannot have nil as a key; if you need to be able to store nil as a key, use Dictionary instead. I use the object equality comparison message #= to determine equivalence of indices. * Menu: * LookupTable class-instance creation:: (class) * LookupTable-accessing:: (instance) * LookupTable-enumerating:: (instance) * LookupTable-hashing:: (instance) * LookupTable-rehashing:: (instance) * LookupTable-removing:: (instance) * LookupTable-storing:: (instance)  File: gst-base.info, Node: LookupTable class-instance creation, Next: LookupTable-accessing, Up: LookupTable 1.106.1 LookupTable class: instance creation -------------------------------------------- new Create a new LookupTable with a default size  File: gst-base.info, Node: LookupTable-accessing, Next: LookupTable-enumerating, Prev: LookupTable class-instance creation, Up: LookupTable 1.106.2 LookupTable: accessing ------------------------------ add: anAssociation Add the anAssociation key to the receiver associationAt: key ifAbsent: aBlock Answer the key/value Association for the given key. Evaluate aBlock (answering the result) if the key is not found at: key ifAbsent: aBlock Answer the value associated to the given key, or the result of evaluating aBlock if the key is not found at: aKey ifPresent: aBlock If aKey is absent, answer nil. Else, evaluate aBlock passing the associated value and answer the result of the invocation at: key put: value Store value as associated to the given key  File: gst-base.info, Node: LookupTable-enumerating, Next: LookupTable-hashing, Prev: LookupTable-accessing, Up: LookupTable 1.106.3 LookupTable: enumerating -------------------------------- associationsDo: aBlock Pass each association in the LookupTable to aBlock. do: aBlock Pass each value in the LookupTable to aBlock. keysAndValuesDo: aBlock Pass each key/value pair in the LookupTable as two distinct parameters to aBlock. keysDo: aBlock Pass each key in the LookupTable to aBlock.  File: gst-base.info, Node: LookupTable-hashing, Next: LookupTable-rehashing, Prev: LookupTable-enumerating, Up: LookupTable 1.106.4 LookupTable: hashing ---------------------------- hash Answer the hash value for the receiver  File: gst-base.info, Node: LookupTable-rehashing, Next: LookupTable-removing, Prev: LookupTable-hashing, Up: LookupTable 1.106.5 LookupTable: rehashing ------------------------------ rehash Rehash the receiver  File: gst-base.info, Node: LookupTable-removing, Next: LookupTable-storing, Prev: LookupTable-rehashing, Up: LookupTable 1.106.6 LookupTable: removing ----------------------------- remove: anAssociation Remove anAssociation's key from the dictionary remove: anAssociation ifAbsent: aBlock Remove anAssociation's key from the dictionary removeKey: key ifAbsent: aBlock Remove the passed key from the LookupTable, answer the result of evaluating aBlock if it is not found  File: gst-base.info, Node: LookupTable-storing, Prev: LookupTable-removing, Up: LookupTable 1.106.7 LookupTable: storing ---------------------------- storeOn: aStream Print Smalltalk code compiling to the receiver on aStream  File: gst-base.info, Node: Magnitude, Next: MappedCollection, Prev: LookupTable, Up: Base classes 1.107 Magnitude =============== Defined in namespace Smalltalk Superclass: Object Category: Language-Data types I am an abstract class. My objects represent things that are discrete and map to a number line. My instances can be compared with < and >. * Menu: * Magnitude-basic:: (instance) * Magnitude-misc methods:: (instance)  File: gst-base.info, Node: Magnitude-basic, Next: Magnitude-misc methods, Up: Magnitude 1.107.1 Magnitude: basic ------------------------ < aMagnitude Answer whether the receiver is less than aMagnitude <= aMagnitude Answer whether the receiver is less than or equal to aMagnitude = aMagnitude Answer whether the receiver is equal to aMagnitude > aMagnitude Answer whether the receiver is greater than aMagnitude >= aMagnitude Answer whether the receiver is greater than or equal to aMagnitude  File: gst-base.info, Node: Magnitude-misc methods, Prev: Magnitude-basic, Up: Magnitude 1.107.2 Magnitude: misc methods ------------------------------- between: min and: max Returns true if object is inclusively between min and max. max: aMagnitude Returns the greatest object between the receiver and aMagnitude min: aMagnitude Returns the least object between the receiver and aMagnitude  File: gst-base.info, Node: MappedCollection, Next: Memory, Prev: Magnitude, Up: Base classes 1.108 MappedCollection ====================== Defined in namespace Smalltalk Superclass: Collection Category: Collections-Keyed I represent collections of objects that are indirectly indexed by names. There are really two collections involved: domain and a map. The map maps between external names and indices into domain, which contains the real association. In order to work properly, the domain must be an instance of a subclass of SequenceableCollection, and the map must be an instance of Dictionary, or of a subclass of SequenceableCollection. As an example of using me, consider implenting a Dictionary whose elements are indexed. The domain would be a SequenceableCollection with n elements, the map a Dictionary associating each key to an index in the domain. To access by key, to perform enumeration, etc. you would ask an instance of me; to access by index, you would access the domain directly. Another idea could be to implement row access or column access to a matrix implemented as a single n*m Array: the Array would be the domain, while the map would be an Interval. * Menu: * MappedCollection class-instance creation:: (class) * MappedCollection-basic:: (instance)  File: gst-base.info, Node: MappedCollection class-instance creation, Next: MappedCollection-basic, Up: MappedCollection 1.108.1 MappedCollection class: instance creation ------------------------------------------------- collection: aCollection map: aMap Answer a new MappedCollection using the given domain (aCollection) and map new This method should not be used; instead, use #collection:map: to create MappedCollection.  File: gst-base.info, Node: MappedCollection-basic, Prev: MappedCollection class-instance creation, Up: MappedCollection 1.108.2 MappedCollection: basic ------------------------------- add: anObject This method should not be called for instances of this class. at: key Answer the object at the given key at: key put: value Store value at the given key atAll: keyCollection Answer a new MappedCollection that only includes the given keys. The new MappedCollection might use keyCollection or consecutive integers for the keys, depending on the map's type. Fail if any of them is not found in the map. collect: aBlock Answer a Collection with the same keys as the map, where accessing a key yields the value obtained by passing through aBlock the value accessible from the key in the receiver. The result need not be another MappedCollection contents Answer a bag with the receiver's values copyFrom: a to: b Answer a new collection containing all the items in the receiver from the a-th to the b-th. do: aBlock Evaluate aBlock for each object domain Answer the receiver's domain keys Answer the keys that can be used to access this collection. keysAndValuesDo: aBlock Evaluate aBlock passing two arguments, one being a key that can be used to access this collection, and the other one being the value. keysDo: aBlock Evaluate aBlock on the keys that can be used to access this collection. map Answer the receiver's map reject: aBlock Answer the objects in the domain for which aBlock returns false select: aBlock Answer the objects in the domain for which aBlock returns true size Answer the receiver's size  File: gst-base.info, Node: Memory, Next: Message, Prev: MappedCollection, Up: Base classes 1.109 Memory ============ Defined in namespace Smalltalk Superclass: Object Category: Language-Implementation I provide access to actual machine addresses of OOPs and objects. I have no instances; you send messages to my class to map between an object and the address of its OOP or object. In addition I provide direct memory access with different C types (ints, chars, OOPs, floats,...). * Menu: * Memory class-accessing:: (class)  File: gst-base.info, Node: Memory class-accessing, Up: Memory 1.109.1 Memory class: accessing ------------------------------- at: anAddress Access the Smalltalk object (OOP) at the given address. at: anAddress put: aValue Store a pointer (OOP) to the Smalltalk object identified by `value' at the given address. bigEndian Answer whether we're running on a big- or little-endian system. charAt: anAddress Access the C char at the given address. The value is returned as a Smalltalk Character. charAt: anAddress put: aValue Store as a C char the Smalltalk Character or Integer object identified by `value', at the given address, using sizeof(char) bytes - i.e. 1 byte. deref: anAddress Access the C int pointed by the given address doubleAt: anAddress Access the C double at the given address. doubleAt: anAddress put: aValue Store the Smalltalk Float object identified by `value', at the given address, writing it like a C double. floatAt: anAddress Access the C float at the given address. floatAt: anAddress put: aValue Store the Smalltalk Float object identified by `value', at the given address, writing it like a C float. intAt: anAddress Access the C int at the given address. intAt: anAddress put: aValue Store the Smalltalk Integer object identified by `value', at the given address, using sizeof(int) bytes. longAt: anAddress Access the C long int at the given address. longAt: anAddress put: aValue Store the Smalltalk Integer object identified by `value', at the given address, using sizeof(long) bytes. longDoubleAt: anAddress Access the C long double at the given address. longDoubleAt: anAddress put: aValue Store the Smalltalk Float object identified by `value', at the given address, writing it like a C long double. shortAt: anAddress Access the C short int at the given address. shortAt: anAddress put: aValue Store the Smalltalk Integer object identified by `value', at the given address, using sizeof(short) bytes. stringAt: anAddress Access the string pointed by the C `char *' at the given given address. stringAt: anAddress put: aValue Store the Smalltalk String object identified by `value', at the given address in memory, writing it like a *FRESHLY ALLOCATED* C string. It is the caller's responsibility to free it if necessary. ucharAt: anAddress put: aValue Store as a C char the Smalltalk Character or Integer object identified by `value', at the given address, using sizeof(char) bytes - i.e. 1 byte. uintAt: anAddress put: aValue Store the Smalltalk Integer object identified by `value', at the given address, using sizeof(int) bytes. ulongAt: anAddress put: aValue Store the Smalltalk Integer object identified by `value', at the given address, using sizeof(long) bytes. unsignedCharAt: anAddress Access the C unsigned char at the given address. The value is returned as a Smalltalk Character. unsignedCharAt: anAddress put: aValue Store as a C char the Smalltalk Character or Integer object identified by `value', at the given address, using sizeof(char) bytes - i.e. 1 byte. unsignedIntAt: anAddress Access the C unsigned int at the given address. unsignedIntAt: anAddress put: aValue Store the Smalltalk Integer object identified by `value', at the given address, using sizeof(int) bytes. unsignedLongAt: anAddress Access the C unsigned long int at the given address. unsignedLongAt: anAddress put: aValue Store the Smalltalk Integer object identified by `value', at the given address, using sizeof(long) bytes. unsignedShortAt: anAddress Access the C unsigned short int at the given address. unsignedShortAt: anAddress put: aValue Store the Smalltalk Integer object identified by `value', at the given address, using sizeof(short) bytes. ushortAt: anAddress put: aValue Store the Smalltalk Integer object identified by `value', at the given address, using sizeof(short) bytes.  File: gst-base.info, Node: Message, Next: MessageNotUnderstood, Prev: Memory, Up: Base classes 1.110 Message ============= Defined in namespace Smalltalk Superclass: Object Category: Language-Implementation I represent a message send. My instances are created to hold a message that has failed, so that error reporting methods can examine the sender and arguments, but also to represent method attributes (like since their syntax is isomorphic to that of a message send. * Menu: * Message class-creating instances:: (class) * Message-accessing:: (instance) * Message-basic:: (instance) * Message-printing:: (instance)  File: gst-base.info, Node: Message class-creating instances, Next: Message-accessing, Up: Message 1.110.1 Message class: creating instances ----------------------------------------- selector: aSymbol argument: anObject Create a new Message with the given selector and argument selector: aSymbol arguments: anArray Create a new Message with the given selector and arguments  File: gst-base.info, Node: Message-accessing, Next: Message-basic, Prev: Message class-creating instances, Up: Message 1.110.2 Message: accessing -------------------------- argument Answer the first of the receiver's arguments arguments Answer the receiver's arguments arguments: anArray Set the receiver's arguments selector Answer the receiver's selector selector: aSymbol Set the receiver's selector  File: gst-base.info, Node: Message-basic, Next: Message-printing, Prev: Message-accessing, Up: Message 1.110.3 Message: basic ---------------------- printAsAttributeOn: aStream Print a representation of the receiver on aStream, modeling it after the source code for a attribute.  File: gst-base.info, Node: Message-printing, Prev: Message-basic, Up: Message 1.110.4 Message: printing ------------------------- printOn: aStream Print a representation of the receiver on aStream reinvokeFor: aReceiver Resend to aReceiver - present for compatibility sendTo: aReceiver Resend to aReceiver  File: gst-base.info, Node: MessageNotUnderstood, Next: Metaclass, Prev: Message, Up: Base classes 1.111 MessageNotUnderstood ========================== Defined in namespace Smalltalk Superclass: Error Category: Language-Exceptions MessageNotUnderstood represents an error during message lookup. Signaling it is the default action of the #doesNotUnderstand: handler * Menu: * MessageNotUnderstood-accessing:: (instance) * MessageNotUnderstood-description:: (instance)  File: gst-base.info, Node: MessageNotUnderstood-accessing, Next: MessageNotUnderstood-description, Up: MessageNotUnderstood 1.111.1 MessageNotUnderstood: accessing --------------------------------------- message Answer the message that wasn't understood receiver Answer the object to whom the message send was directed  File: gst-base.info, Node: MessageNotUnderstood-description, Prev: MessageNotUnderstood-accessing, Up: MessageNotUnderstood 1.111.2 MessageNotUnderstood: description ----------------------------------------- description Answer a textual description of the exception. isResumable Answer true. #doesNotUnderstand: exceptions are by default resumable.  File: gst-base.info, Node: Metaclass, Next: MethodContext, Prev: MessageNotUnderstood, Up: Base classes 1.112 Metaclass =============== Defined in namespace Smalltalk Superclass: ClassDescription Category: Language-Implementation I am the root of the class hierarchy. My instances are metaclasses, one for each real class. My instances have a single instance, which they hold onto, which is the class that they are the metaclass of. I provide methods for creation of actual class objects from metaclass object, and the creation of metaclass objects, which are my instances. If this is confusing to you, it should be...the Smalltalk metaclass system is strange and complex. * Menu: * Metaclass class-instance creation:: (class) * Metaclass-accessing:: (instance) * Metaclass-basic:: (instance) * Metaclass-compiling methods:: (instance) * Metaclass-delegation:: (instance) * Metaclass-filing:: (instance) * Metaclass-printing:: (instance) * Metaclass-testing functionality:: (instance)  File: gst-base.info, Node: Metaclass class-instance creation, Next: Metaclass-accessing, Up: Metaclass 1.112.1 Metaclass class: instance creation ------------------------------------------ subclassOf: superMeta Answer a new metaclass representing a subclass of superMeta  File: gst-base.info, Node: Metaclass-accessing, Next: Metaclass-basic, Prev: Metaclass class-instance creation, Up: Metaclass 1.112.2 Metaclass: accessing ---------------------------- instanceClass Answer the only instance of the metaclass primaryInstance Answer the only instance of the metaclass - present for compatibility soleInstance Answer the only instance of the metaclass - present for compatibility  File: gst-base.info, Node: Metaclass-basic, Next: Metaclass-compiling methods, Prev: Metaclass-accessing, Up: Metaclass 1.112.3 Metaclass: basic ------------------------ name: className environment: aNamespace subclassOf: theSuperclass Private - create a full featured class and install it, or change the superclass or shape of an existing one; instance variable names, class variable names and pool dictionaries are left untouched. name: className environment: aNamespace subclassOf: newSuperclass instanceVariableArray: variableArray shape: shape classPool: classVarDict poolDictionaries: sharedPoolNames category: categoryName Private - create a full featured class and install it, or change an existing one name: newName environment: aNamespace subclassOf: theSuperclass instanceVariableNames: stringOfInstVarNames shape: shape classVariableNames: stringOfClassVarNames poolDictionaries: stringOfPoolNames category: categoryName Private - parse the instance and class variables, and the pool dictionaries, then create the class. newMeta: className environment: aNamespace subclassOf: theSuperclass instanceVariableArray: arrayOfInstVarNames shape: shape classPool: classVarDict poolDictionaries: sharedPoolNames category: categoryName Private - create a full featured class and install it  File: gst-base.info, Node: Metaclass-compiling methods, Next: Metaclass-delegation, Prev: Metaclass-basic, Up: Metaclass 1.112.4 Metaclass: compiling methods ------------------------------------ poolResolution Use my instance's poolResolution.  File: gst-base.info, Node: Metaclass-delegation, Next: Metaclass-filing, Prev: Metaclass-compiling methods, Up: Metaclass 1.112.5 Metaclass: delegation ----------------------------- addClassVarName: aString Add a class variable with the given name to the class pool dictionary addSharedPool: aDictionary Add the given shared pool to the list of the class' pool dictionaries allClassVarNames Answer the names of the variables in the receiver's class pool dictionary and in each of the superclasses' class pool dictionaries allSharedPoolDictionariesDo: aBlock Answer the shared pools visible from methods in the metaclass, in the correct search order. allSharedPools Return the names of the shared pools defined by the class and any of its superclasses category Answer the class category classPool Answer the class pool dictionary classVarNames Answer the names of the variables in the class pool dictionary comment Answer the class comment debuggerClass Answer the debugger class that was set in the instance class environment Answer the namespace in which the receiver is implemented name Answer the class name - it has none, actually pragmaHandlerFor: aSymbol Answer the (possibly inherited) registered handler for pragma aSymbol, or nil if not found. removeClassVarName: aString Removes the class variable from the class, error if not present, or still in use. removeSharedPool: aDictionary Remove the given dictionary to the list of the class' pool dictionaries sharedPools Return the names of the shared pools defined by the class  File: gst-base.info, Node: Metaclass-filing, Next: Metaclass-printing, Prev: Metaclass-delegation, Up: Metaclass 1.112.6 Metaclass: filing ------------------------- fileOutOn: aFileStream File out complete class description: class definition, class and instance methods  File: gst-base.info, Node: Metaclass-printing, Next: Metaclass-testing functionality, Prev: Metaclass-filing, Up: Metaclass 1.112.7 Metaclass: printing --------------------------- nameIn: aNamespace Answer the class name when the class is referenced from aNamespace. printOn: aStream Print a represention of the receiver on aStream printOn: aStream in: aNamespace Print on aStream the class name when the class is referenced from aNamespace. storeOn: aStream Store Smalltalk code compiling to the receiver on aStream  File: gst-base.info, Node: Metaclass-testing functionality, Prev: Metaclass-printing, Up: Metaclass 1.112.8 Metaclass: testing functionality ---------------------------------------- asClass Answer `instanceClass'. isMetaclass Answer `true'.  File: gst-base.info, Node: MethodContext, Next: MethodDictionary, Prev: Metaclass, Up: Base classes 1.113 MethodContext =================== Defined in namespace Smalltalk Superclass: ContextPart Category: Language-Implementation My instances represent an actively executing method. They record various bits of information about the execution environment, and contain the execution stack. * Menu: * MethodContext-accessing:: (instance) * MethodContext-debugging:: (instance) * MethodContext-printing:: (instance)  File: gst-base.info, Node: MethodContext-accessing, Next: MethodContext-debugging, Up: MethodContext 1.113.1 MethodContext: accessing -------------------------------- home Answer the MethodContext to which the receiver refers (i.e. the receiver itself) isBlock Answer whether the receiver is a block context isDisabled Answers whether the receiver has actually ended execution and will be skipped when doing a return. BlockContexts are removed from the chain whenever a non-local return is done, but MethodContexts need to stay there in case there is a non-local return from the #ensure: block. isEnvironment To create a valid execution environment for the interpreter even before it starts, GST creates a fake context which invokes a special "termination" method. Such a context can be used as a marker for the current execution environment. Answer whether the receiver is that kind of context. isUnwind Answers whether the context must continue execution even after a non-local return (a return from the enclosing method of a block, or a call to the #continue: method of ContextPart). Such contexts are created only by #ensure:. mark To create a valid execution environment for the interpreter even before it starts, GST creates a fake context which invokes a special "termination" method. A similar context is created by #valueWithUnwind, by using this method. sender Return the context from which the receiver was sent  File: gst-base.info, Node: MethodContext-debugging, Next: MethodContext-printing, Prev: MethodContext-accessing, Up: MethodContext 1.113.2 MethodContext: debugging -------------------------------- isInternalExceptionHandlingContext Answer whether the receiver is a context that should be hidden to the user when presenting a backtrace. Such contexts are identified through the #exceptionHandlingInternal: attribute: if there is such a context in the backtrace, all those above it are marked as internal. That is, the attribute being set to true means that the context and all those above it are to be hidden, while the attribute being set to false means that the contexts above it must be hidden, but not the context itself.  File: gst-base.info, Node: MethodContext-printing, Prev: MethodContext-debugging, Up: MethodContext 1.113.3 MethodContext: printing ------------------------------- printOn: aStream Print a representation for the receiver on aStream  File: gst-base.info, Node: MethodDictionary, Next: MethodInfo, Prev: MethodContext, Up: Base classes 1.114 MethodDictionary ====================== Defined in namespace Smalltalk Superclass: IdentityDictionary Category: Language-Implementation I am similar to an IdentityDictionary, except that removal and rehashing operations inside my instances look atomic to the interpreter. * Menu: * MethodDictionary-adding:: (instance) * MethodDictionary-rehashing:: (instance) * MethodDictionary-removing:: (instance)  File: gst-base.info, Node: MethodDictionary-adding, Next: MethodDictionary-rehashing, Up: MethodDictionary 1.114.1 MethodDictionary: adding -------------------------------- at: key put: value Store value as associated to the given key  File: gst-base.info, Node: MethodDictionary-rehashing, Next: MethodDictionary-removing, Prev: MethodDictionary-adding, Up: MethodDictionary 1.114.2 MethodDictionary: rehashing ----------------------------------- rehash Rehash the receiver  File: gst-base.info, Node: MethodDictionary-removing, Prev: MethodDictionary-rehashing, Up: MethodDictionary 1.114.3 MethodDictionary: removing ---------------------------------- remove: anAssociation Remove anAssociation's key from the dictionary removeKey: anElement ifAbsent: aBlock Remove the passed key from the dictionary, answer the result of evaluating aBlock if it is not found  File: gst-base.info, Node: MethodInfo, Next: Namespace, Prev: MethodDictionary, Up: Base classes 1.115 MethodInfo ================ Defined in namespace Smalltalk Superclass: Object Category: Language-Implementation I provide information about particular methods. I can produce the category that a method was filed under, and can be used to access the source code of the method. * Menu: * MethodInfo-accessing:: (instance) * MethodInfo-equality:: (instance)  File: gst-base.info, Node: MethodInfo-accessing, Next: MethodInfo-equality, Up: MethodInfo 1.115.1 MethodInfo: accessing ----------------------------- category Answer the method category category: aCategory Set the method category methodClass Answer the class in which the method is defined methodClass: aClass Set the class in which the method is defined selector Answer the selector through which the method is called selector: aSymbol Set the selector through which the method is called sourceCode Answer a FileSegment or String or nil containing the method source code sourceFile Answer the name of the file where the method source code is sourcePos Answer the starting position of the method source code in the sourceFile sourceString Answer a String containing the method source code stripSourceCode Remove the reference to the source code for the method  File: gst-base.info, Node: MethodInfo-equality, Prev: MethodInfo-accessing, Up: MethodInfo 1.115.2 MethodInfo: equality ---------------------------- = aMethodInfo Compare the receiver and aMethodInfo, answer whether they're equal hash Answer an hash value for the receiver  File: gst-base.info, Node: Namespace, Next: NetClients.URIResolver, Prev: MethodInfo, Up: Base classes 1.116 Namespace =============== Defined in namespace Smalltalk Superclass: AbstractNamespace Category: Language-Implementation I am a Namespace that has a super-namespace. * Menu: * Namespace class-accessing:: (class) * Namespace class-disabling instance creation:: (class) * Namespace class-initialization:: (class) * Namespace-accessing:: (instance) * Namespace-namespace hierarchy:: (instance) * Namespace-overrides for superspaces:: (instance) * Namespace-printing:: (instance)  File: gst-base.info, Node: Namespace class-accessing, Next: Namespace class-disabling instance creation, Up: Namespace 1.116.1 Namespace class: accessing ---------------------------------- current Answer the current namespace current: aNamespaceOrClass Set the current namespace to be aNamespace or, if it is a class, its class pool (the Dictionary that holds class variables).  File: gst-base.info, Node: Namespace class-disabling instance creation, Next: Namespace class-initialization, Prev: Namespace class-accessing, Up: Namespace 1.116.2 Namespace class: disabling instance creation ---------------------------------------------------- new Disabled - use #addSubspace: to create instances new: size Disabled - use #addSubspace: to create instances  File: gst-base.info, Node: Namespace class-initialization, Next: Namespace-accessing, Prev: Namespace class-disabling instance creation, Up: Namespace 1.116.3 Namespace class: initialization --------------------------------------- initialize This actually is not needed, the job could be done in dict.c (function namespace_new). But I'm lazy and I prefer to rely on the Smalltalk implementation of IdentitySet.  File: gst-base.info, Node: Namespace-accessing, Next: Namespace-namespace hierarchy, Prev: Namespace class-initialization, Up: Namespace 1.116.4 Namespace: accessing ---------------------------- inheritedKeys Answer a Set of all the keys in the receiver and its superspaces  File: gst-base.info, Node: Namespace-namespace hierarchy, Next: Namespace-overrides for superspaces, Prev: Namespace-accessing, Up: Namespace 1.116.5 Namespace: namespace hierarchy -------------------------------------- siblings Answer all the other namespaces that inherit from the receiver's superspace. siblingsDo: aBlock Evaluate aBlock once for each of the other namespaces that inherit from the receiver's superspace, passing the namespace as a parameter.  File: gst-base.info, Node: Namespace-overrides for superspaces, Next: Namespace-printing, Prev: Namespace-namespace hierarchy, Up: Namespace 1.116.6 Namespace: overrides for superspaces -------------------------------------------- associationAt: key ifAbsent: aBlock Return the key/value pair associated to the variable named as specified by `key'. If the key is not found search will be brought on in superspaces, finally evaluating aBlock if the variable cannot be found in any of the superspaces. associationsDo: aBlock Pass each association in the namespace to aBlock at: key ifAbsent: aBlock Return the value associated to the variable named as specified by `key'. If the key is not found search will be brought on in superspaces, finally evaluating aBlock if the variable cannot be found in any of the superspaces. at: key ifPresent: aBlock If aKey is absent from the receiver and all its superspaces, answer nil. Else, evaluate aBlock passing the associated value and answer the result of the invocation do: aBlock Pass each value in the namespace to aBlock includesKey: key Answer whether the receiver or any of its superspaces contain the given key keysAndValuesDo: aBlock Pass to aBlock each of the receiver's keys and values, in two separate parameters keysDo: aBlock Pass to aBlock each of the receiver's keys set: key to: newValue ifAbsent: aBlock Assign newValue to the variable named as specified by `key'. This method won't define a new variable; instead if the key is not found it will search in superspaces and evaluate aBlock if it is not found. Answer newValue. size Answer the number of keys in the receiver and each of its superspaces  File: gst-base.info, Node: Namespace-printing, Prev: Namespace-overrides for superspaces, Up: Namespace 1.116.7 Namespace: printing --------------------------- nameIn: aNamespace Answer Smalltalk code compiling to the receiver when the current namespace is aNamespace printOn: aStream in: aNamespace Print on aStream some Smalltalk code compiling to the receiver when the current namespace is aNamespace storeOn: aStream Store Smalltalk code compiling to the receiver  File: gst-base.info, Node: NetClients.URIResolver, Next: NetClients.URL, Prev: Namespace, Up: Base classes 1.117 NetClients.URIResolver ============================ Defined in namespace Smalltalk.NetClients Superclass: Object Category: NetClients-URIResolver This class publishes methods to download files from the Internet. * Menu: * NetClients.URIResolver class-api:: (class) * NetClients.URIResolver class-instance creation:: (class)  File: gst-base.info, Node: NetClients.URIResolver class-api, Next: NetClients.URIResolver class-instance creation, Up: NetClients.URIResolver 1.117.1 NetClients.URIResolver class: api ----------------------------------------- openOn: aURI Always raise an error, as this method is not supported without loading the additional NetClients package. openOn: aURI ifFail: aBlock Always evaluate aBlock and answer the result if the additional NetClients package is not loaded. If it is, instead, return a WebEntity with the contents of the resource specified by anURI, and only evaluate the block if loading the resource fails. openStreamOn: aURI Check if aURI can be fetched from the Internet or from the local system, and if so return a Stream with its contents. If this is not possible, raise an exception. openStreamOn: aURI ifFail: aBlock Check if aURI can be fetched from the Internet or from the local system, and if so return a Stream with its contents. If this is not possible, instead, evaluate the zero-argument block aBlock and answer the result of the evaluation.  File: gst-base.info, Node: NetClients.URIResolver class-instance creation, Prev: NetClients.URIResolver class-api, Up: NetClients.URIResolver 1.117.2 NetClients.URIResolver class: instance creation ------------------------------------------------------- on: anURL Answer a new URIResolver that will do its best to fetch the data for anURL from the Internet.  File: gst-base.info, Node: NetClients.URL, Next: Notification, Prev: NetClients.URIResolver, Up: Base classes 1.118 NetClients.URL ==================== Defined in namespace Smalltalk.NetClients Superclass: Object Category: NetClients-URIResolver Copyright (c) Kazuki Yasumatsu, 1995. All rights reserved. * Menu: * NetClients.URL class-encoding URLs:: (class) * NetClients.URL class-instance creation:: (class) * NetClients.URL-accessing:: (instance) * NetClients.URL-comparing:: (instance) * NetClients.URL-copying:: (instance) * NetClients.URL-initialize-release:: (instance) * NetClients.URL-printing:: (instance) * NetClients.URL-still unclassified:: (instance) * NetClients.URL-testing:: (instance) * NetClients.URL-utilities:: (instance)  File: gst-base.info, Node: NetClients.URL class-encoding URLs, Next: NetClients.URL class-instance creation, Up: NetClients.URL 1.118.1 NetClients.URL class: encoding URLs ------------------------------------------- decode: aString Decode a text/x-www-form-urlencoded String into a text/plain String. encode: anURL Encode a text/plain into a text/x-www-form-urlencoded String (those things with lots of % in them). initialize Initialize the receiver's class variables.  File: gst-base.info, Node: NetClients.URL class-instance creation, Next: NetClients.URL-accessing, Prev: NetClients.URL class-encoding URLs, Up: NetClients.URL 1.118.2 NetClients.URL class: instance creation ----------------------------------------------- fromString: aString Parse the given URL and answer an URL object based on it. new Answer a 'blank' URL. scheme: schemeString host: hostString path: pathString Answer an URL object made from all the parts passed as arguments. scheme: schemeString host: hostString port: portNumber path: pathString Answer an URL object made from all the parts passed as arguments. scheme: schemeString path: pathString Answer an URL object made from all the parts passed as arguments. scheme: schemeString username: userString password: passwordString host: hostString port: portNumber path: pathString Answer an URL object made from all the parts passed as arguments.  File: gst-base.info, Node: NetClients.URL-accessing, Next: NetClients.URL-comparing, Prev: NetClients.URL class-instance creation, Up: NetClients.URL 1.118.3 NetClients.URL: accessing --------------------------------- asString Answer the full request string corresponding to the URL. This is how the URL would be printed in the address bar of a web browser, except that the query data is printed even if it is to be sent through a POST request. decodedFields Convert the form fields to a Dictionary, answer nil if no question mark is found in the URL. decodedFile Answer the file part of the URL, decoding it from x-www-form-urlencoded format. decodedFragment Answer the fragment part of the URL, decoding it from x-www-form-urlencoded format. fragment Answer the fragment part of the URL, leaving it in x-www-form-urlencoded format. fragment: aString Set the fragment part of the URL, which should be in x-www-form-urlencoded format. fullRequestString Answer the full request string corresponding to the URL. This is how the URL would be printed in the address bar of a web browser, except that the query data is printed even if it is to be sent through a POST request. hasPostData Answer whether the URL has a query part but is actually for an HTTP POST request and not really part of the URL (as it would be for the HTTP GET request). hasPostData: aBoolean Set whether the query part of the URL is actually the data for an HTTP POST request and not really part of the URL (as it would be for the HTTP GET request). host Answer the host part of the URL. host: aString Set the host part of the URL to aString. newsGroup If the receiver is an nntp url, return the news group. password Answer the password part of the URL. password: aString Set the password part of the URL to aString. path Answer the path part of the URL. path: aString Set the path part of the URL to aString. port Answer the port number part of the URL. port: anInteger Set the port number part of the URL to anInteger. postData Answer whether the URL has a query part and it is meant for an HTTP POST request, answer it. Else answer nil. postData: aString Associate to the URL some data that is meant to be sent through an HTTP POST request, answer it. query Answer the query data associated to the URL. query: aString Set the query data associated to the URL to aString. requestString Answer the URL as it would be sent in an HTTP stream (that is, the path and the query data, the latter only if it is to be sent with an HTTP POST request). scheme Answer the URL's scheme. scheme: aString Set the URL's scheme to be aString. username Answer the username part of the URL. username: aString Set the username part of the URL to aString.  File: gst-base.info, Node: NetClients.URL-comparing, Next: NetClients.URL-copying, Prev: NetClients.URL-accessing, Up: NetClients.URL 1.118.4 NetClients.URL: comparing --------------------------------- = anURL Answer whether the two URLs are equal. The file and anchor are converted to full 8-bit ASCII (contrast with urlencoded) and the comparison is case-sensitive; on the other hand, the protocol and host are compared without regard to case. hash Answer an hash value for the receiver  File: gst-base.info, Node: NetClients.URL-copying, Next: NetClients.URL-initialize-release, Prev: NetClients.URL-comparing, Up: NetClients.URL 1.118.5 NetClients.URL: copying ------------------------------- copyWithoutAuxiliaryParts Answer a copy of the receiver where the fragment and query parts of the URL have been cleared. copyWithoutFragment Answer a copy of the receiver where the fragment parts of the URL has been cleared. postCopy All the variables are copied when an URL object is copied.  File: gst-base.info, Node: NetClients.URL-initialize-release, Next: NetClients.URL-printing, Prev: NetClients.URL-copying, Up: NetClients.URL 1.118.6 NetClients.URL: initialize-release ------------------------------------------ initialize Initialize the object to a consistent state.  File: gst-base.info, Node: NetClients.URL-printing, Next: NetClients.URL-still unclassified, Prev: NetClients.URL-initialize-release, Up: NetClients.URL 1.118.7 NetClients.URL: printing -------------------------------- printOn: stream Print a representation of the URL on the given stream.  File: gst-base.info, Node: NetClients.URL-still unclassified, Next: NetClients.URL-testing, Prev: NetClients.URL-printing, Up: NetClients.URL 1.118.8 NetClients.URL: still unclassified ------------------------------------------ contents Not commented. entity Not commented. readStream Not commented.  File: gst-base.info, Node: NetClients.URL-testing, Next: NetClients.URL-utilities, Prev: NetClients.URL-still unclassified, Up: NetClients.URL 1.118.9 NetClients.URL: testing ------------------------------- canCache Answer whether the URL is cacheable. The current implementation considers file URLs not to be cacheable, and everything else to be. hasFragment Answer whether the URL points to a particular fragment (anchor) of the resource. hasQuery Answer whether the URL includes query arguments to be submitted when retrieving the resource. isFileScheme Answer whether the URL is a file URL. isFragmentOnly Answer whether the URL only includes the name of a particular fragment (anchor) of the resource to which it refers.  File: gst-base.info, Node: NetClients.URL-utilities, Prev: NetClients.URL-testing, Up: NetClients.URL 1.118.10 NetClients.URL: utilities ---------------------------------- construct: anURL Construct an absolute URL based on the relative URL anURL and the base path represented by the receiver  File: gst-base.info, Node: Notification, Next: NullProxy, Prev: NetClients.URL, Up: Base classes 1.119 Notification ================== Defined in namespace Smalltalk Superclass: Exception Category: Language-Exceptions Notification represents a resumable, exceptional yet non-erroneous, situation. Signaling a notification in absence of an handler simply returns nil. * Menu: * Notification-exception description:: (instance)  File: gst-base.info, Node: Notification-exception description, Up: Notification 1.119.1 Notification: exception description ------------------------------------------- defaultAction Do the default action for notifications, which is to resume execution of the context which signaled the exception. description Answer a textual description of the exception. isResumable Answer true. Notification exceptions are by default resumable.  File: gst-base.info, Node: NullProxy, Next: NullValueHolder, Prev: Notification, Up: Base classes 1.120 NullProxy =============== Defined in namespace Smalltalk Superclass: AlternativeObjectProxy Category: Streams-Files I am a proxy that does no special processing on the object to be saved. I can be used to disable proxies for particular subclasses. My subclasses add to the stored information, but share the fact that the format is about the same as that of #dump: without a proxy. * Menu: * NullProxy class-instance creation:: (class) * NullProxy-accessing:: (instance)  File: gst-base.info, Node: NullProxy class-instance creation, Next: NullProxy-accessing, Up: NullProxy 1.120.1 NullProxy class: instance creation ------------------------------------------ loadFrom: anObjectDumper Reload the object stored in anObjectDumper  File: gst-base.info, Node: NullProxy-accessing, Prev: NullProxy class-instance creation, Up: NullProxy 1.120.2 NullProxy: accessing ---------------------------- dumpTo: anObjectDumper Dump the object stored in the proxy to anObjectDumper  File: gst-base.info, Node: NullValueHolder, Next: Number, Prev: NullProxy, Up: Base classes 1.121 NullValueHolder ===================== Defined in namespace Smalltalk Superclass: ValueAdaptor Category: Language-Data types I pretend to store my value in a variable, but I don't actually. You can use the only instance of my class (returned by `ValueHolder null') if you're not interested in a value that is returned as described in ValueHolder's comment. * Menu: * NullValueHolder class-creating instances:: (class) * NullValueHolder-accessing:: (instance)  File: gst-base.info, Node: NullValueHolder class-creating instances, Next: NullValueHolder-accessing, Up: NullValueHolder 1.121.1 NullValueHolder class: creating instances ------------------------------------------------- new Not used - use `ValueHolder null' instead uniqueInstance Answer the sole instance of NullValueHolder  File: gst-base.info, Node: NullValueHolder-accessing, Prev: NullValueHolder class-creating instances, Up: NullValueHolder 1.121.2 NullValueHolder: accessing ---------------------------------- value Retrive the value of the receiver. Always answer nil value: anObject Set the value of the receiver. Do nothing, discard the value  File: gst-base.info, Node: Number, Next: Object, Prev: NullValueHolder, Up: Base classes 1.122 Number ============ Defined in namespace Smalltalk Superclass: Magnitude Category: Language-Data types I am an abstract class that provides operations on numbers, both floating point and integer. I provide some generic predicates, and supply the implicit type coercing code for binary operations. * Menu: * Number class-converting:: (class) * Number class-testing:: (class) * Number-arithmetic:: (instance) * Number-coercion:: (instance) * Number-comparing:: (instance) * Number-converting:: (instance) * Number-copying:: (instance) * Number-error raising:: (instance) * Number-misc math:: (instance) * Number-point creation:: (instance) * Number-retrying:: (instance) * Number-shortcuts and iterators:: (instance) * Number-testing:: (instance) * Number-truncation and round off:: (instance)  File: gst-base.info, Node: Number class-converting, Next: Number class-testing, Up: Number 1.122.1 Number class: converting -------------------------------- coerce: aNumber Answer aNumber - whatever class it belongs to, it is good readFrom: aStream Answer the number read from the rest of aStream, converted to an instance of the receiver. If the receiver is number, the class of the result is undefined - but the result is good. readFrom: aStream radix: anInteger Answer the number read from the rest of aStream, converted to an instance of the receiver. If the receiver is number, the class of the result is undefined - but the result is good. The exponent (for example 1.2e-1) is only parsed if anInteger is 10.  File: gst-base.info, Node: Number class-testing, Next: Number-arithmetic, Prev: Number class-converting, Up: Number 1.122.2 Number class: testing ----------------------------- isImmediate Answer whether, if x is an instance of the receiver, x copy == x  File: gst-base.info, Node: Number-arithmetic, Next: Number-coercion, Prev: Number class-testing, Up: Number 1.122.3 Number: arithmetic -------------------------- * aNumber Subtract the receiver and aNumber, answer the result + aNumber Sum the receiver and aNumber, answer the result - aNumber Subtract aNumber from the receiver, answer the result / aNumber Divide the receiver by aNumber, answer the result (no loss of precision). Raise a ZeroDivide exception or return a valid (possibly infinite) continuation value if aNumber is zero. // aNumber Return the integer quotient of dividing the receiver by aNumber with truncation towards negative infinity. Raise a ZeroDivide exception if aNumber is zero \\ aNumber Return the remainder of dividing the receiver by aNumber with truncation towards negative infinity. Raise a ZeroDivide exception if aNumber is zero quo: aNumber Return the integer quotient of dividing the receiver by aNumber with truncation towards zero. Raise a ZeroDivide exception if aNumber is zero reciprocal Return the reciprocal of the receiver rem: aNumber Return the remainder of dividing the receiver by aNumber with truncation towards zero. Raise a ZeroDivide exception if aNumber is zero  File: gst-base.info, Node: Number-coercion, Next: Number-comparing, Prev: Number-arithmetic, Up: Number 1.122.4 Number: coercion ------------------------ asCNumber Convert the receiver to a kind of number that is understood by the C call-out mechanism.  File: gst-base.info, Node: Number-comparing, Next: Number-converting, Prev: Number-coercion, Up: Number 1.122.5 Number: comparing ------------------------- max: aNumber Answer the maximum between the receiver and aNumber. Redefine in subclasses if necessary to ensure that if either self or aNumber is a NaN, it is always answered. min: aNumber Answer the minimum between the receiver and aNumber. Redefine in subclasses if necessary to ensure that if either self or aNumber is a NaN, it is always answered.  File: gst-base.info, Node: Number-converting, Next: Number-copying, Prev: Number-comparing, Up: Number 1.122.6 Number: converting -------------------------- asExactFraction Return the receiver, converted to a Fraction retaining the exact value of the receiver. asFloat Convert the receiver to an arbitrary subclass of Float asFloatD This method's functionality should be implemented by subclasses of Number asFloatE This method's functionality should be implemented by subclasses of Number asFloatQ This method's functionality should be implemented by subclasses of Number asFraction This method's functionality should be implemented by subclasses of Number asNumber Answer the receiver, since it is already a number asRectangle Answer an empty rectangle whose origin is (self asPoint) asScaledDecimal: n Answer the receiver, converted to a ScaledDecimal object. asScaledDecimal: denDigits radix: base scale: n Answer the receiver, divided by base^denDigits and converted to a ScaledDecimal object. asString Answer the receiver's #displayString, which should be a good enough conversion to String for a number. coerce: aNumber Answer aNumber, converted to an integer or floating-point number. degreesToRadians Convert the receiver to radians generality Answer the receiver's generality radiansToDegrees Convert the receiver from radians to degrees unity Coerce 1 to the receiver's class. The default implementation works, but is inefficient zero Coerce 0 to the receiver's class. The default implementation works, but is inefficient  File: gst-base.info, Node: Number-copying, Next: Number-error raising, Prev: Number-converting, Up: Number 1.122.7 Number: copying ----------------------- deepCopy Return the receiver - it's an immediate (immutable) object shallowCopy Return the receiver - it's an immediate (immutable) object  File: gst-base.info, Node: Number-error raising, Next: Number-misc math, Prev: Number-copying, Up: Number 1.122.8 Number: error raising ----------------------------- arithmeticError: msg Raise an ArithmeticError exception having msg as its message text. zeroDivide Raise a division-by-zero (ZeroDivide) exception whose dividend is the receiver.  File: gst-base.info, Node: Number-misc math, Next: Number-point creation, Prev: Number-error raising, Up: Number 1.122.9 Number: misc math ------------------------- abs Answer the absolute value of the receiver arcCos Answer the arc cosine of the receiver arcCosh Answer the hyperbolic arc-cosine of the receiver. arcSin Answer the arc sine of the receiver arcSinh Answer the hyperbolic arc-sine of the receiver. arcTan Answer the arc tangent of the receiver arcTan: x Answer the angle (measured counterclockwise) between (x, self) and a ray starting in (0, 0) and moving towards (1, 0) - i.e. 3 o'clock arcTanh Answer the hyperbolic arc-tangent of the receiver. ceilingLog: radix Answer (self log: radix) ceiling. Optimized to answer an integer. cos Answer the cosine of the receiver cosh Answer the hyperbolic cosine of the receiver. estimatedLog Answer an estimate of (self abs floorLog: 10). This method should be overridden by subclasses, but Number's implementation does not raise errors - simply, it gives a correct result, so it is slow. exp Answer e raised to the receiver floorLog: radix Answer (self log: radix) floor. Optimized to answer an integer. ln Answer log base e of the receiver log Answer log base 10 of the receiver log: aNumber Answer log base aNumber of the receiver negated Answer the negated of the receiver positiveDifference: aNumber Answer the positive difference of the receiver and aNumber, that is self - aNumber if it is positive, 0 otherwise. raisedTo: aNumber Return self raised to aNumber power raisedToInteger: anInteger Return self raised to the anInteger-th power sin Answer the sine of the receiver sinh Answer the hyperbolic sine of the receiver. sqrt Answer the square root of the receiver squared Answer the square of the receiver tan Answer the tangent of the receiver tanh Answer the hyperbolic tangent of the receiver. withSignOf: aNumber Answer the receiver, with its sign possibly changed to match that of aNumber.  File: gst-base.info, Node: Number-point creation, Next: Number-retrying, Prev: Number-misc math, Up: Number 1.122.10 Number: point creation ------------------------------- @ y Answer a new point whose x is the receiver and whose y is y asPoint Answer a new point, self @ self  File: gst-base.info, Node: Number-retrying, Next: Number-shortcuts and iterators, Prev: Number-point creation, Up: Number 1.122.11 Number: retrying ------------------------- retry: aSymbol coercing: aNumber Coerce to the other number's class the one number between the receiver and aNumber which has the lowest, and retry calling aSymbol. aSymbol is supposed not to be #= or #~= (since those don't fail if aNumber is not a Number). retryDifferenceCoercing: aNumber Coerce to the other number's class the one number between the receiver and aNumber which has the lowest, and retry calling #-. retryDivisionCoercing: aNumber Coerce to the other number's class the one number between the receiver and aNumber which has the lowest, and retry calling #/. retryEqualityCoercing: aNumber Coerce to the other number's class the one number between the receiver and aNumber which has the lowest, and retry calling #=. retryError Raise an error--a retrying method was called with two arguments having the same generality. retryInequalityCoercing: aNumber Coerce to the other number's class the one number between the receiver and aNumber which has the lowest, and retry calling #~=. retryMultiplicationCoercing: aNumber Coerce to the other number's class the one number between the receiver and aNumber which has the lowest, and retry calling #*. retryRelationalOp: aSymbol coercing: aNumber Coerce to the other number's class the one number between the receiver and aNumber which has the lowest, and retry calling aSymbol (<, <=, >, >=). retrySumCoercing: aNumber Coerce to the other number's class the one number between the receiver and aNumber which has the lowest, and retry calling #+.  File: gst-base.info, Node: Number-shortcuts and iterators, Next: Number-testing, Prev: Number-retrying, Up: Number 1.122.12 Number: shortcuts and iterators ---------------------------------------- to: stop Return an interval going from the receiver to stop by 1 to: stop by: step Return an interval going from the receiver to stop with the given step to: stop by: step collect: aBlock Evaluate aBlock for each value in the interval going from the receiver to stop with the given step. The results are collected in an Array and returned. to: stop by: step do: aBlock Evaluate aBlock for each value in the interval going from the receiver to stop with the given step. Compiled in-line for integer literal steps, and for one-argument aBlocks without temporaries, and therefore not overridable. to: stop collect: aBlock Evaluate aBlock for each value in the interval going from the receiver to stop by 1. The results are collected in an Array and returned. to: stop do: aBlock Evaluate aBlock for each value in the interval going from the receiver to stop by 1. Compiled in-line for one-argument aBlocks without temporaries, and therefore not overridable.  File: gst-base.info, Node: Number-testing, Next: Number-truncation and round off, Prev: Number-shortcuts and iterators, Up: Number 1.122.13 Number: testing ------------------------ closeTo: num Answer whether the receiver can be considered sufficiently close to num (this is done by checking equality if num is not a number, and by checking with 0.01% tolerance if num is a number). even Returns true if self is divisible by 2 isExact Answer whether the receiver performs exact arithmetic. Most numeric classes do (in fact the only exceptions is Float and its descendants), so the default is to answer true rather than calling #subclassResponsibility. isFinite Answer whether the receiver represents a finite quantity. Most numeric classes are for finite quantities, so the default is to answer true rather than calling #subclassResponsibility. isInfinite Answer whether the receiver represents an infinite quantity. Most numeric classes are for finite quantities, so the default is to answer false rather than calling #subclassResponsibility. isNaN Answer whether the receiver is a Not-A-Number. Most numeric classes don't handle nans, so the default is to answer false rather than calling #subclassResponsibility. isNumber Answer `true'. isRational Answer whether the receiver is rational - false by default negative Answer whether the receiver is < 0 odd Returns true if self is not divisible by 2 positive Answer whether the receiver is >= 0 sign Returns the sign of the receiver. strictlyPositive Answer whether the receiver is > 0  File: gst-base.info, Node: Number-truncation and round off, Prev: Number-testing, Up: Number 1.122.14 Number: truncation and round off ----------------------------------------- asInteger Answer the receiver, rounded to the nearest integer floor Return the integer nearest the receiver toward negative infinity. fractionPart Answer a number which, summed to the #integerPart of the receiver, gives the receiver itself. integerPart Answer the receiver, truncated towards zero roundTo: aNumber Answer the receiver, truncated to the nearest multiple of aNumber rounded Returns the integer nearest the receiver truncateTo: aNumber Answer the receiver, truncated towards zero to a multiple of aNumber truncated Answer the receiver, truncated towards zero  File: gst-base.info, Node: Object, Next: ObjectDumper, Prev: Number, Up: Base classes 1.123 Object ============ Defined in namespace Smalltalk Superclass: none Category: Language-Implementation I am the root of the Smalltalk class system. All classes in the system are subclasses of me. * Menu: * Object class-initialization:: (class) * Object-built ins:: (instance) * Object-change and update:: (instance) * Object-class type methods:: (instance) * Object-compiler:: (instance) * Object-conversion:: (instance) * Object-copying:: (instance) * Object-debugging:: (instance) * Object-dependents access:: (instance) * Object-error raising:: (instance) * Object-finalization:: (instance) * Object-introspection:: (instance) * Object-printing:: (instance) * Object-relational operators:: (instance) * Object-saving and loading:: (instance) * Object-storing:: (instance) * Object-syntax shortcuts:: (instance) * Object-testing functionality:: (instance) * Object-VM callbacks:: (instance)  File: gst-base.info, Node: Object class-initialization, Next: Object-built ins, Up: Object 1.123.1 Object class: initialization ------------------------------------ dependencies Answer a dictionary that associates an object with its dependents. dependencies: anObject Use anObject as the dictionary that associates an object with its dependents. finalizableObjects Answer a set of finalizable objects. initialize Initialize the Dependencies dictionary to be a WeakKeyIdentityDictionary. update: aspect Do any global tasks for the ObjectMemory events.  File: gst-base.info, Node: Object-built ins, Next: Object-change and update, Prev: Object class-initialization, Up: Object 1.123.2 Object: built ins ------------------------- = arg Answer whether the receiver is equal to arg. The equality test is by default the same as that for identical objects. = must not fail; answer false if the receiver cannot be compared to arg == arg Answer whether the receiver is the same object as arg. This is a very fast test and is called 'object identity'. allOwners Return an Array of Objects that point to the receiver. asOop Answer the object index associated to the receiver. The object index doesn't change when garbage collection is performed. at: anIndex Answer the index-th indexed instance variable of the receiver at: anIndex put: value Store value in the index-th indexed instance variable of the receiver basicAt: anIndex Answer the index-th indexed instance variable of the receiver. This method must not be overridden, override at: instead basicAt: anIndex put: value Store value in the index-th indexed instance variable of the receiver This method must not be overridden, override at:put: instead basicPrint Print a basic representation of the receiver basicSize Answer the number of indexed instance variable in the receiver become: otherObject Change all references to the receiver into references to otherObject. Depending on the implementation, references to otherObject might or might not be transformed into the receiver (respectively, 'two-way become' and 'one-way become'). Implementations doing one-way become answer the receiver (so that it is not lost). Most implementations doing two-way become answer otherObject, but this is not assured - so do answer the receiver for consistency. GNU Smalltalk does two-way become and answers otherObject, but this might change in future versions: programs should not rely on the behavior and results of #become: . becomeForward: otherObject Change all references to the receiver into references to otherObject. References to otherObject are not transformed into the receiver. Answer the receiver so that it is not lost. changeClassTo: aBehavior Mutate the class of the receiver to be aBehavior. Note: Tacitly assumes that the structure is the same for the original and new class!! checkIndexableBounds: index Private - Check the reason why an access to the given indexed instance variable failed checkIndexableBounds: index ifAbsent: aBlock Private - Check the reason why an access to the given indexed instance variable failed. Evaluate aBlock for an invalid index. checkIndexableBounds: index put: object Private - Check the reason why a store to the given indexed instance variable failed class Answer the class to which the receiver belongs halt Called to enter the debugger hash Answer an hash value for the receiver. This hash value is ok for objects that do not redefine ==. identityHash Answer an hash value for the receiver. This method must not be overridden instVarAt: index Answer the index-th instance variable of the receiver. This method must not be overridden. instVarAt: index put: value Store value in the index-th instance variable of the receiver. This method must not be overridden. isReadOnly Answer whether the object's indexed instance variables can be written isUntrusted Answer whether the object is to be considered untrusted. makeEphemeron Make the object an 'ephemeron'. An ephemeron is marked after all other objects, and if no references are found to the key except from the object itself, it is sent the #mourn message. makeFixed Avoid that the receiver moves in memory across garbage collections. makeReadOnly: aBoolean Set whether the object's indexed instance variables can be written makeUntrusted: aBoolean Set whether the object is to be considered untrusted. makeWeak Make the object a 'weak' one. When an object is only referenced by weak objects, it is collected and the slots in the weak objects are changed to nils by the VM; the weak object is then sent the #mourn message. mark: aSymbol Private - use this method to mark code which needs to be reworked, removed, etc. You can then find all senders of #mark: to find all marked methods or you can look for all senders of the symbol that you sent to #mark: to find a category of marked methods. nextInstance Private - answer another instance of the receiver's class, or nil if the entire object table has been walked notYetImplemented Called when a method defined by a class is not yet implemented, but is going to be perform: selectorOrMessageOrMethod Send the unary message named selectorOrMessageOrMethod (if a Symbol) to the receiver, or the message and arguments it identifies (if a Message or DirectedMessage), or finally execute the method within the receiver (if a CompiledMethod). In the last case, the method need not reside on the hierarchy from the receiver's class to Object - it need not reside at all in a MethodDictionary, in fact - but doing bad things will compromise stability of the Smalltalk virtual machine (and don't blame anybody but yourself). This method should not be overridden perform: selectorOrMethod with: arg1 Send the message named selectorOrMethod (if a Symbol) to the receiver, passing arg1 to it, or execute the method within the receiver (if a CompiledMethod). In the latter case, the method need not reside on the hierarchy from the receiver's class to Object - it need not reside at all in a MethodDictionary, in fact - but doing bad things will compromise stability of the Smalltalk virtual machine (and don't blame anybody but yourself). This method should not be overridden perform: selectorOrMethod with: arg1 with: arg2 Send the message named selectorOrMethod (if a Symbol) to the receiver, passing arg1 and arg2 to it, or execute the method within the receiver (if a CompiledMethod). In the latter case, the method need not reside on the hierarchy from the receiver's class to Object - it need not reside at all in a MethodDictionary, in fact - but doing bad things will compromise stability of the Smalltalk virtual machine (and don't blame anybody but yourself). This method should not be overridden perform: selectorOrMethod with: arg1 with: arg2 with: arg3 Send the message named selectorOrMethod (if a Symbol) to the receiver, passing the other arguments to it, or execute the method within the receiver (if a CompiledMethod). In the latter case, the method need not reside on the hierarchy from the receiver's class to Object - it need not reside at all in a MethodDictionary, in fact - but doing bad things will compromise stability of the Smalltalk virtual machine (and don't blame anybody but yourself). This method should not be overridden perform: selectorOrMethod with: arg1 with: arg2 with: arg3 with: arg4 Send the message named selectorOrMethod (if a Symbol) to the receiver, passing the other arguments to it, or execute the method within the receiver (if a CompiledMethod). In the latter case, the method need not reside on the hierarchy from the receiver's class to Object - it need not reside at all in a MethodDictionary, in fact - but doing bad things will compromise stability of the Smalltalk virtual machine (and don't blame anybody but yourself). This method should not be overridden perform: selectorOrMethod withArguments: argumentsArray Send the message named selectorOrMethod (if a Symbol) to the receiver, passing the elements of argumentsArray as parameters, or execute the method within the receiver (if a CompiledMethod). In the latter case, the method need not reside on the hierarchy from the receiver's class to Object - it need not reside at all in a MethodDictionary, in fact - but doing bad things will compromise stability of the Smalltalk virtual machine (and don't blame anybody but yourself). This method should not be overridden primitiveFailed Called when a VM primitive fails shallowCopy Returns a shallow copy of the receiver (the instance variables are not copied) shouldNotImplement Called when objects belonging to a class should not answer a selector defined by a superclass size Answer the number of indexed instance variable in the receiver subclassResponsibility Called when a method defined by a class should be overridden in a subclass tenure Move the object to oldspace.  File: gst-base.info, Node: Object-change and update, Next: Object-class type methods, Prev: Object-built ins, Up: Object 1.123.3 Object: change and update --------------------------------- broadcast: aSymbol Send the unary message aSymbol to each of the receiver's dependents broadcast: aSymbol with: anObject Send the message aSymbol to each of the receiver's dependents, passing anObject broadcast: aSymbol with: arg1 with: arg2 Send the message aSymbol to each of the receiver's dependents, passing arg1 and arg2 as parameters broadcast: aSymbol withArguments: anArray Send the message aSymbol to each of the receiver's dependents, passing the parameters in anArray broadcast: aSymbol withBlock: aBlock Send the message aSymbol to each of the receiver's dependents, passing the result of evaluating aBlock with each dependent as the parameter changed Send update: for each of the receiver's dependents, passing them the receiver changed: aParameter Send update: for each of the receiver's dependents, passing them aParameter update: aParameter Default behavior is to do nothing. Called by #changed and #changed:  File: gst-base.info, Node: Object-class type methods, Next: Object-compiler, Prev: Object-change and update, Up: Object 1.123.4 Object: class type methods ---------------------------------- species This method has no unique definition. Generally speaking, methods which always return the same type usually don't use #class, but #species. For example, a PositionableStream's species is the class of the collection on which it is streaming (used by upTo:, upToAll:, upToEnd). Stream uses species for obtaining the class of next:'s return value, Collection uses it in its #copyEmpty: message, which in turn is used by all collection-returning methods. An Interval's species is Array (used by collect:, select:, reject:, etc.). yourself Answer the receiver  File: gst-base.info, Node: Object-compiler, Next: Object-conversion, Prev: Object-class type methods, Up: Object 1.123.5 Object: compiler ------------------------ literalEquals: anObject Not commented. literalHash Not commented.  File: gst-base.info, Node: Object-conversion, Next: Object-copying, Prev: Object-compiler, Up: Object 1.123.6 Object: conversion -------------------------- asValue Answer a ValueHolder whose initial value is the receiver.  File: gst-base.info, Node: Object-copying, Next: Object-debugging, Prev: Object-conversion, Up: Object 1.123.7 Object: copying ----------------------- copy Returns a shallow copy of the receiver (the instance variables are not copied). The shallow copy receives the message postCopy and the result of postCopy is passed back. deepCopy Returns a deep copy of the receiver (the instance variables are copies of the receiver's instance variables) postCopy Performs any changes required to do on a copied object. This is the place where one could, for example, put code to replace objects with copies of the objects  File: gst-base.info, Node: Object-debugging, Next: Object-dependents access, Prev: Object-copying, Up: Object 1.123.8 Object: debugging ------------------------- examine Print all the instance variables of the receiver on the Transcript examineOn: aStream Print all the instance variables of the receiver on aStream inspect In a GUI environment, this opens a tool to examine and modify the receiver. In the default image, it just calls #examine. validSize Answer how many elements in the receiver should be inspected  File: gst-base.info, Node: Object-dependents access, Next: Object-error raising, Prev: Object-debugging, Up: Object 1.123.9 Object: dependents access --------------------------------- addDependent: anObject Add anObject to the set of the receiver's dependents. Important: if an object has dependents, it won't be garbage collected. dependents Answer a collection of the receiver's dependents. release Remove all of the receiver's dependents from the set and allow the receiver to be garbage collected. removeDependent: anObject Remove anObject to the set of the receiver's dependents. No problem if anObject is not in the set of the receiver's dependents.  File: gst-base.info, Node: Object-error raising, Next: Object-finalization, Prev: Object-dependents access, Up: Object 1.123.10 Object: error raising ------------------------------ doesNotUnderstand: aMessage Called by the system when a selector was not found. message is a Message containing information on the receiver error: message Display a walkback for the receiver, with the given error message. Signal an `Error' exception. halt: message Display a walkback for the receiver, with the given error message. Signal an `Halt' exception.  File: gst-base.info, Node: Object-finalization, Next: Object-introspection, Prev: Object-error raising, Up: Object 1.123.11 Object: finalization ----------------------------- addToBeFinalized Arrange things so that #finalize is sent to the object when the garbage collector finds out there are only weak references to it. finalize Do nothing by default mourn This method is sent by the VM to weak and ephemeron objects when one of their fields is found out to be garbage collectable (this means, for weak objects, that there are no references to it from non-weak objects, and for ephemeron objects, that the only paths to the first instance variable pass through other instance variables of the same ephemeron). The default behavior is to do nothing. removeToBeFinalized Unregister the object, so that #finalize is no longer sent to the object when the garbage collector finds out there are only weak references to it.  File: gst-base.info, Node: Object-introspection, Next: Object-printing, Prev: Object-finalization, Up: Object 1.123.12 Object: introspection ------------------------------ instVarNamed: aString Answer the instance variable named aString in the receiver. instVarNamed: aString put: anObject Answer the instance variable named aString in the receiver.  File: gst-base.info, Node: Object-printing, Next: Object-relational operators, Prev: Object-introspection, Up: Object 1.123.13 Object: printing ------------------------- basicPrintNl Print a basic representation of the receiver, followed by a new line. basicPrintOn: aStream Print a represention of the receiver on aStream display Print a represention of the receiver on the Transcript (stdout the GUI is not active). For most objects this is simply its #print representation, but for strings and characters, superfluous dollars or extra pair of quotes are stripped. displayNl Print a represention of the receiver, then put a new line on the Transcript (stdout the GUI is not active). For most objects this is simply its #printNl representation, but for strings and characters, superfluous dollars or extra pair of quotes are stripped. displayOn: aStream Print a represention of the receiver on aStream. For most objects this is simply its #printOn: representation, but for strings and characters, superfluous dollars or extra pair of quotes are stripped. displayString Answer a String representing the receiver. For most objects this is simply its #printString, but for strings and characters, superfluous dollars or extra pair of quotes are stripped. print Print a represention of the receiver on the Transcript (stdout the GUI is not active) printNl Print a represention of the receiver on stdout, put a new line the Transcript (stdout the GUI is not active) printOn: aStream Print a represention of the receiver on aStream printString Answer a String representing the receiver  File: gst-base.info, Node: Object-relational operators, Next: Object-saving and loading, Prev: Object-printing, Up: Object 1.123.14 Object: relational operators ------------------------------------- ~= anObject Answer whether the receiver and anObject are not equal ~~ anObject Answer whether the receiver and anObject are not the same object  File: gst-base.info, Node: Object-saving and loading, Next: Object-storing, Prev: Object-relational operators, Up: Object 1.123.15 Object: saving and loading ----------------------------------- binaryRepresentationObject This method must be implemented if PluggableProxies are used with the receiver's class. The default implementation raises an exception. postLoad Called after loading an object; must restore it to the state before `preStore' was called. Do nothing by default postStore Called after an object is dumped; must restore it to the state before `preStore' was called. Call #postLoad by default preStore Called before dumping an object; it must *change* it (it must not answer a new object) if necessary. Do nothing by default reconstructOriginalObject Used if an instance of the receiver's class is returned as the #binaryRepresentationObject of another object. The default implementation raises an exception.  File: gst-base.info, Node: Object-storing, Next: Object-syntax shortcuts, Prev: Object-saving and loading, Up: Object 1.123.16 Object: storing ------------------------ store Put a String of Smalltalk code compiling to the receiver on the Transcript (stdout the GUI is not active) storeLiteralOn: aStream Put a Smalltalk literal compiling to the receiver on aStream storeNl Put a String of Smalltalk code compiling to the receiver, followed by a new line, on the Transcript (stdout the GUI is not active) storeOn: aStream Put Smalltalk code compiling to the receiver on aStream storeString Answer a String of Smalltalk code compiling to the receiver  File: gst-base.info, Node: Object-syntax shortcuts, Next: Object-testing functionality, Prev: Object-storing, Up: Object 1.123.17 Object: syntax shortcuts --------------------------------- -> anObject Creates a new instance of Association with the receiver being the key and the argument becoming the value  File: gst-base.info, Node: Object-testing functionality, Next: Object-VM callbacks, Prev: Object-syntax shortcuts, Up: Object 1.123.18 Object: testing functionality -------------------------------------- ifNil: nilBlock Evaluate nilBlock if the receiver is nil, else answer self ifNil: nilBlock ifNotNil: notNilBlock Evaluate nilBlock if the receiver is nil, else evaluate notNilBlock, passing the receiver. ifNotNil: notNilBlock Evaluate notNilBlock if the receiver is not nil, passing the receiver. Else answer nil. ifNotNil: notNilBlock ifNil: nilBlock Evaluate nilBlock if the receiver is nil, else evaluate notNilBlock, passing the receiver. isArray Answer `false'. isBehavior Answer `false'. isCObject Answer `false'. isCharacter Answer `false'. isCharacterArray Answer `false'. isClass Answer `false'. isFloat Answer `false'. isInteger Answer `false'. isKindOf: aClass Answer whether the receiver's class is aClass or a subclass of aClass isMemberOf: aClass Returns true if the receiver is an instance of the class 'aClass' isMeta Same as isMetaclass isMetaClass Same as isMetaclass isMetaclass Answer `false'. isNamespace Answer `false'. isNil Answer whether the receiver is nil isNumber Answer `false'. isSmallInteger Answer `false'. isString Answer `false'. isSymbol Answer `false'. notNil Answer whether the receiver is not nil respondsTo: aSymbol Returns true if the receiver understands the given selector  File: gst-base.info, Node: Object-VM callbacks, Prev: Object-testing functionality, Up: Object 1.123.19 Object: VM callbacks ----------------------------- badReturnError Called back when a block performs a bad return. mustBeBoolean Called by the system when ifTrue:*, ifFalse:*, and: or or: are sent to anything but a boolean noRunnableProcess Called back when all processes are suspended userInterrupt Called back when the user presses Ctrl-Break  File: gst-base.info, Node: ObjectDumper, Next: ObjectMemory, Prev: Object, Up: Base classes 1.124 ObjectDumper ================== Defined in namespace Smalltalk Superclass: Stream Category: Streams-Files I'm not part of a normal Smalltalk system, but most Smalltalks provide a similar feature: that is, support for storing objects in a binary format; there are many advantages in using me instead of #storeOn: and the Smalltalk compiler. The data is stored in a very compact format, which has the side effect of making loading much faster when compared with compiling the Smalltalk code prepared by #storeOn:. In addition, my instances support circular references between objects, while #storeOn: supports it only if you know of such references at design time and you override #storeOn: to deal with them * Menu: * ObjectDumper class-establishing proxy classes:: (class) * ObjectDumper class-instance creation:: (class) * ObjectDumper class-shortcuts:: (class) * ObjectDumper class-testing:: (class) * ObjectDumper-accessing:: (instance) * ObjectDumper-loading/dumping objects:: (instance) * ObjectDumper-stream interface:: (instance)  File: gst-base.info, Node: ObjectDumper class-establishing proxy classes, Next: ObjectDumper class-instance creation, Up: ObjectDumper 1.124.1 ObjectDumper class: establishing proxy classes ------------------------------------------------------ disableProxyFor: aClass Disable proxies for instances of aClass and its descendants hasProxyFor: aClass Answer whether a proxy class has been registered for instances of aClass. proxyClassFor: anObject Answer the class of a valid proxy for an object, or nil if none could be found proxyFor: anObject Answer a valid proxy for an object, or the object itself if none could be found registerProxyClass: aProxyClass for: aClass Register the proxy class aProxyClass - descendent of DumperProxy - to be used for instances of aClass and its descendants  File: gst-base.info, Node: ObjectDumper class-instance creation, Next: ObjectDumper class-shortcuts, Prev: ObjectDumper class-establishing proxy classes, Up: ObjectDumper 1.124.2 ObjectDumper class: instance creation --------------------------------------------- new This method should not be called for instances of this class. on: aFileStream Answer an ObjectDumper working on aFileStream.  File: gst-base.info, Node: ObjectDumper class-shortcuts, Next: ObjectDumper class-testing, Prev: ObjectDumper class-instance creation, Up: ObjectDumper 1.124.3 ObjectDumper class: shortcuts ------------------------------------- dump: anObject to: aFileStream Dump anObject to aFileStream. Answer anObject loadFrom: aFileStream Load an object from aFileStream and answer it  File: gst-base.info, Node: ObjectDumper class-testing, Next: ObjectDumper-accessing, Prev: ObjectDumper class-shortcuts, Up: ObjectDumper 1.124.4 ObjectDumper class: testing ----------------------------------- example This is a real torture test: it outputs recursive objects, identical objects multiple times, classes, metaclasses, integers, characters and proxies (which is also a test of more complex objects)!  File: gst-base.info, Node: ObjectDumper-accessing, Next: ObjectDumper-loading/dumping objects, Prev: ObjectDumper class-testing, Up: ObjectDumper 1.124.5 ObjectDumper: accessing ------------------------------- flush `Forget' any information on previously stored objects. stream Answer the ByteStream to which the ObjectDumper will write and from which it will read. stream: aByteStream Set the ByteStream to which the ObjectDumper will write and from which it will read.  File: gst-base.info, Node: ObjectDumper-loading/dumping objects, Next: ObjectDumper-stream interface, Prev: ObjectDumper-accessing, Up: ObjectDumper 1.124.6 ObjectDumper: loading/dumping objects --------------------------------------------- dump: anObject Dump anObject on the stream associated with the receiver. Answer anObject load Load an object from the stream associated with the receiver and answer it  File: gst-base.info, Node: ObjectDumper-stream interface, Prev: ObjectDumper-loading/dumping objects, Up: ObjectDumper 1.124.7 ObjectDumper: stream interface -------------------------------------- atEnd Answer whether the underlying stream is at EOF next Load an object from the underlying stream nextPut: anObject Store an object on the underlying stream  File: gst-base.info, Node: ObjectMemory, Next: OrderedCollection, Prev: ObjectDumper, Up: Base classes 1.125 ObjectMemory ================== Defined in namespace Smalltalk Superclass: Object Category: Language-Implementation I provide a few methods that enable one to tune the virtual machine's usage of memory. In addition, I can signal to my dependants some `events' that can happen during the virtual machine's life. ObjectMemory has both class-side and instance-side methods. In general, class-side methods provide means to tune the parameters of the memory manager, while instance-side methods are used together with the #current class-side method to take a look at statistics on the memory manager's state. * Menu: * ObjectMemory class-accessing:: (class) * ObjectMemory class-builtins:: (class) * ObjectMemory class-initialization:: (class) * ObjectMemory class-saving the image:: (class) * ObjectMemory-accessing:: (instance) * ObjectMemory-builtins:: (instance) * ObjectMemory-derived information:: (instance)  File: gst-base.info, Node: ObjectMemory class-accessing, Next: ObjectMemory class-builtins, Up: ObjectMemory 1.125.1 ObjectMemory class: accessing ------------------------------------- current Return a snapshot of the VM's memory management statistics.  File: gst-base.info, Node: ObjectMemory class-builtins, Next: ObjectMemory class-initialization, Prev: ObjectMemory class-accessing, Up: ObjectMemory 1.125.2 ObjectMemory class: builtins ------------------------------------ abort Quit the Smalltalk environment, dumping core. addressOf: anObject Returns the address of the actual object that anObject references. Note that, with the exception of fixed objects this address is only valid until the next garbage collection; thus it's pretty risky to count on the address returned by this method for very long. addressOfOOP: anObject Returns the address of the OOP (object table slot) for anObject. The address is an Integer and will not change over time (i.e. is immune from garbage collector action) except if the virtual machine is stopped and restarted. bigObjectThreshold Answer the smallest size for objects that are allocated outside the main heap in the hope of providing more locality of reference between small objects. bigObjectThreshold: bytes Set the smallest size for objects that are allocated outside the main heap in the hope of providing more locality of reference between small objects. bytes must be a positive SmallInteger. compact Force a full garbage collection, including compaction of oldspace finishIncrementalGC Do a step in the incremental garbage collection. gcMessage Answer whether messages indicating that garbage collection is taking place are printed on stdout gcMessage: aBoolean Set whether messages indicating that garbage collection is taking place are printed on stdout globalGarbageCollect Force a full garbage collection growThresholdPercent Answer the percentage of the amount of memory used by the system grows which has to be full for the system to allocate more memory growThresholdPercent: growPercent Set the percentage of the amount of memory used by the system grows which has to be full for the system to allocate more memory growTo: numBytes Grow the amount of memory used by the system grows to numBytes. incrementalGCStep Do a step in the incremental garbage collection. quit Quit the Smalltalk environment. Whether files are closed and other similar cleanup occurs depends on the platform quit: exitStatus Quit the Smalltalk environment, passing the exitStatus integer to the OS. Files are closed and other similar cleanups occur. scavenge Force a minor garbage collection smoothingFactor Answer the factor (between 0 and 1) used to smooth the statistics provided by the virtual machine about memory handling. 0 disables updating the averages, 1 disables the smoothing (the statistics return the last value). smoothingFactor: rate Set the factor (between 0 and 1) used to smooth the statistics provided by the virtual machine about memory handling. 0 disables updating the averages, 1 disables the smoothing (the statistics return the last value). spaceGrowRate Answer the rate with which the amount of memory used by the system grows spaceGrowRate: rate Set the rate with which the amount of memory used by the system grows  File: gst-base.info, Node: ObjectMemory class-initialization, Next: ObjectMemory class-saving the image, Prev: ObjectMemory class-builtins, Up: ObjectMemory 1.125.3 ObjectMemory class: initialization ------------------------------------------ changed: aSymbol Not commented. initialize Initialize the globals  File: gst-base.info, Node: ObjectMemory class-saving the image, Next: ObjectMemory-accessing, Prev: ObjectMemory class-initialization, Up: ObjectMemory 1.125.4 ObjectMemory class: saving the image -------------------------------------------- snapshot Save a snapshot on the image file that was loaded on startup. snapshot: aString Save an image on the aString file  File: gst-base.info, Node: ObjectMemory-accessing, Next: ObjectMemory-builtins, Prev: ObjectMemory class-saving the image, Up: ObjectMemory 1.125.5 ObjectMemory: accessing ------------------------------- allocFailures Answer the number of times that the old-space allocator found no block that was at least as big as requested, and had to ask the operating system for more memory. allocMatches Answer the number of times that the old-space allocator found a block that was exactly as big as requested. allocProbes Answer the number of free blocks that the old-space allocator had to examine so far to allocate all the objects that are in old-space allocSplits Answer the number of times that the old-space allocator could not find a block that was exactly as big as requested, and had to split a larger free block in two parts. bytesPerOOP Answer the number of bytes that is taken by an ordinary object pointer (in practice, a field such as a named instance variable). bytesPerOTE Answer the number of bytes that is taken by an object table entry (in practice, the overhead incurred by every object in the system, with the sole exception of SmallIntegers). edenSize Answer the number of bytes in the `eden' area of the young generation (in practice, the number of allocated bytes between two scavenges). edenUsedBytes Answer the number of bytes that are currently filled in the `eden' area of the young generation. fixedSpaceSize Answer the number of bytes in the special heap devoted to objects that the garbage collector cannot move around in memory. fixedSpaceUsedBytes Answer the number of bytes that are currently filled in the special heap devoted to objects that the garbage collector cannot move around in memory. numCompactions Answer the number of oldspace compactions that happened since the VM was started. numFixedOOPs Answer the number of objects that the garbage collector cannot move around in memory. numFreeOTEs Answer the number of entries that are currently free in the object table. numGlobalGCs Answer the number of global garbage collections (collection of the entire heap) that happened since the VM was started. numGrowths Answer the number of times that oldspace was grown since the VM was started. numOTEs Answer the number of entries that are currently allocated for the object table. numOldOOPs Answer the number of objects that reside in the old generation. numScavenges Answer the number of scavenges (fast collections of the young generation) that happened since the VM was started. numWeakOOPs Answer the number of weak objects that the garbage collector is currently tracking. oldSpaceSize Answer the number of bytes in the old generation. oldSpaceUsedBytes Answer the number of bytes that are currently filled in the old generation. reclaimedBytesPerGlobalGC Answer the average number of bytes that are found to be garbage during a global garbage collections. reclaimedBytesPerScavenge Answer the average number of bytes that are found to be garbage during a scavenge. reclaimedPercentPerScavenge Answer the average percentage of allocated bytes that are found to be garbage during a scavenge. If this number falls below 60-70 you should definitely increment the size of the eden, because you risk that scavenging is eating a considerable fraction of your execution time; do the measurement on a restarted image, so that the extra tenuring incurred when creating long-lived objects such as classes or methods is not considered. survSpaceSize Answer the number of bytes in the `survivor' area of the young generation (the area to which young objects are relocated during scavenges). survSpaceUsedBytes Answer the number of bytes that are currently filled in the `survivor' area of the young generation. tenuredBytesPerScavenge Answer the average number of bytes that are promoted to oldspace during a scavenge. timeBetweenGlobalGCs Answer the average number of milliseconds between two global garbage collections. timeBetweenGrowths Answer the average number of milliseconds between decisions to grow the heap. timeBetweenScavenges Answer the average number of milliseconds between two scavenges (fast collections of the young generation). timeToCollect Answer the average number of milliseconds that a global garbage collection takes. timeToCompact Answer the average number of milliseconds that compacting the heap takes. This the same time that is taken by growing the heap. timeToScavenge Answer the average number of milliseconds that a scavenge takes (fast collections of the young generation).  File: gst-base.info, Node: ObjectMemory-builtins, Next: ObjectMemory-derived information, Prev: ObjectMemory-accessing, Up: ObjectMemory 1.125.6 ObjectMemory: builtins ------------------------------ update Update the values in the object to the current state of the VM.  File: gst-base.info, Node: ObjectMemory-derived information, Prev: ObjectMemory-builtins, Up: ObjectMemory 1.125.7 ObjectMemory: derived information ----------------------------------------- scavengesBeforeTenuring Answer the number of scavenges that an object must on average survive before being promoted to oldspace; this is however only an estimate because objects that are reachable from oldspace have a higher probability to be tenured soon, while objects that are only reachable from thisContext have a lower probability to be tenured. Anyway, if this number falls below 2-3 you should definitely increment the size of eden and/or of survivor space, because you are tenuring too often and relying too much on global garbage collection to keep your heap clean; do the measurement on a restarted image, so that the extra tenuring incurred when creating long-lived objects such as classes or methods is not considered.  File: gst-base.info, Node: OrderedCollection, Next: Package, Prev: ObjectMemory, Up: Base classes 1.126 OrderedCollection ======================= Defined in namespace Smalltalk Superclass: SequenceableCollection Category: Collections-Sequenceable My instances represent ordered collections of arbitrary typed objects which are not directly accessible by an index. They can be accessed indirectly through an index, and can be manipulated by adding to the end or based on content (such as add:after:) * Menu: * OrderedCollection class-instance creation:: (class) * OrderedCollection-accessing:: (instance) * OrderedCollection-adding:: (instance) * OrderedCollection-built ins:: (instance) * OrderedCollection-enumerating:: (instance) * OrderedCollection-removing:: (instance)  File: gst-base.info, Node: OrderedCollection class-instance creation, Next: OrderedCollection-accessing, Up: OrderedCollection 1.126.1 OrderedCollection class: instance creation -------------------------------------------------- new Answer an OrderedCollection of default size new: anInteger Answer an OrderedCollection of size anInteger  File: gst-base.info, Node: OrderedCollection-accessing, Next: OrderedCollection-adding, Prev: OrderedCollection class-instance creation, Up: OrderedCollection 1.126.2 OrderedCollection: accessing ------------------------------------ at: anIndex Answer the anIndex-th item of the receiver at: anIndex put: anObject Store anObject at the anIndex-th item of the receiver, answer anObject first Answer the first item of the receiver last Answer the last item of the receiver size Return the number of objects in the receiver  File: gst-base.info, Node: OrderedCollection-adding, Next: OrderedCollection-built ins, Prev: OrderedCollection-accessing, Up: OrderedCollection 1.126.3 OrderedCollection: adding --------------------------------- add: anObject Add anObject in the receiver, answer it add: newObject after: oldObject Add newObject in the receiver just after oldObject, answer it. Fail if oldObject can't be found add: newObject afterIndex: i Add newObject in the receiver just after the i-th, answer it. Fail if i < 0 or i > self size add: newObject before: oldObject Add newObject in the receiver just before oldObject, answer it. Fail if oldObject can't be found add: newObject beforeIndex: i Add newObject in the receiver just before the i-th, answer it. Fail if i < 1 or i > self size + 1 addAll: aCollection Add every item of aCollection to the receiver, answer it addAll: newCollection after: oldObject Add every item of newCollection to the receiver just after oldObject, answer it. Fail if oldObject is not found addAll: newCollection afterIndex: i Add every item of newCollection to the receiver just after the i-th, answer it. Fail if i < 0 or i > self size addAll: newCollection before: oldObject Add every item of newCollection to the receiver just before oldObject, answer it. Fail if oldObject is not found addAll: newCollection beforeIndex: i Add every item of newCollection to the receiver just before the i-th, answer it. Fail if i < 1 or i > self size + 1 addAllFirst: aCollection Add every item of newCollection to the receiver right at the start of the receiver. Answer aCollection addAllLast: aCollection Add every item of newCollection to the receiver right at the end of the receiver. Answer aCollection addFirst: newObject Add newObject to the receiver right at the start of the receiver. Answer newObject addLast: newObject Add newObject to the receiver right at the end of the receiver. Answer newObject  File: gst-base.info, Node: OrderedCollection-built ins, Next: OrderedCollection-enumerating, Prev: OrderedCollection-adding, Up: OrderedCollection 1.126.4 OrderedCollection: built ins ------------------------------------ primReplaceFrom: start to: stop with: byteArray startingAt: replaceStart Replace the characters from start to stop with new characters whose ASCII codes are contained in byteArray, starting at the replaceStart location of byteArray  File: gst-base.info, Node: OrderedCollection-enumerating, Next: OrderedCollection-removing, Prev: OrderedCollection-built ins, Up: OrderedCollection 1.126.5 OrderedCollection: enumerating -------------------------------------- do: aBlock Evaluate aBlock for all the elements in the collection  File: gst-base.info, Node: OrderedCollection-removing, Prev: OrderedCollection-enumerating, Up: OrderedCollection 1.126.6 OrderedCollection: removing ----------------------------------- identityRemove: oldObject Remove oldObject from the receiver. If absent, fail, else answer oldObject. identityRemove: anObject ifAbsent: aBlock Remove anObject from the receiver. If it can't be found, answer the result of evaluating aBlock remove: anObject ifAbsent: aBlock Remove anObject from the receiver. If it can't be found, answer the result of evaluating aBlock removeAtIndex: anIndex Remove the object at index anIndex from the receiver. Fail if the index is out of bounds. removeFirst Remove an object from the start of the receiver. Fail if the receiver is empty removeLast Remove an object from the end of the receiver. Fail if the receiver is empty  File: gst-base.info, Node: Package, Next: PackageLoader, Prev: OrderedCollection, Up: Base classes 1.127 Package ============= Defined in namespace Smalltalk Superclass: Kernel.PackageInfo Category: Language-Packaging I am not part of a standard Smalltalk system. I store internally the information on a Smalltalk package, and can output my description in XML. * Menu: * Package class-accessing:: (class) * Package class-instance creation:: (class) * Package-accessing:: (instance) * Package-still unclassified:: (instance) * Package-version parsing:: (instance)  File: gst-base.info, Node: Package class-accessing, Next: Package class-instance creation, Up: Package 1.127.1 Package class: accessing -------------------------------- tags Not commented.  File: gst-base.info, Node: Package class-instance creation, Next: Package-accessing, Prev: Package class-accessing, Up: Package 1.127.2 Package class: instance creation ---------------------------------------- parse: file Answer a package from the XML description in file.  File: gst-base.info, Node: Package-accessing, Next: Package-still unclassified, Prev: Package class-instance creation, Up: Package 1.127.3 Package: accessing -------------------------- addBuiltFile: aString Not commented. addCallout: aString Not commented. addFeature: aString Not commented. addFile: aString Not commented. addFileIn: aString Not commented. addLibrary: aString Not commented. addModule: aString Not commented. addPrerequisite: aString Not commented. addSunitScript: aString Not commented. baseDirectories Answer `baseDirectories'. baseDirectories: aCollection Check if it's possible to resolve the names in the package according to the base directories in baseDirectories, which depend on where the packages.xml is found: the three possible places are 1) the system kernel directory's parent directory, 2) the local kernel directory's parent directory, 3) the local image directory (in order of decreasing priority). For a packages.xml found in the system kernel directory's parent directory, all three directories are searched. For a packages.xml found in the local kernel directory's parent directory, only directories 2 and 3 are searched. For a packages.xml directory in the local image directory, instead, only directory 3 is searched. builtFiles Answer a (modifiable) OrderedCollection of files that are part of the package but are not distributed. callouts Answer a (modifiable) Set of call-outs that are required to load the package. Their presence is checked after the libraries and modules are loaded so that you can do a kind of versioning. directory Answer the base directory from which to load the package. features Answer a (modifiable) Set of features provided by the package. fileIns Answer a (modifiable) OrderedCollections of files that are to be filed-in to load the package. This is usually a subset of `files' and `builtFiles'. files Answer a (modifiable) OrderedCollection of files that are part of the package. fullPathOf: fileName Try appending 'self directory' and fileName to each of the directory in baseDirectories, and return the path to the first tried filename that exists. Raise a PackageNotAvailable exception if no directory is found that contains the file. libraries Answer a (modifiable) Set of shared library names that are required to load the package. modules Answer a (modifiable) Set of modules that are required to load the package. namespace Answer the namespace in which the package is loaded. namespace: aString Set to aString the namespace in which the package is loaded. prerequisites Answer a (modifiable) Set of prerequisites. primFileIn Private - File in the given package without paying attention at dependencies and C callout availability relativeDirectory Answer the directory, relative to the packages file, from which to load the package. relativeDirectory: dir Set the directory, relative to the packages file, from which to load the package, to dir. startScript Answer the start script for the package. startScript: aString Set the start script for the package to aString. stopScript Answer the start script for the package. stopScript: aString Set the stop script for the package to aString. sunitScripts Answer a (modifiable) OrderedCollection of SUnit scripts that compose the package's test suite. test Answer the test sub-package. test: aPackage Set the test sub-package to be aPackage. url Answer the URL at which the package repository can be found. url: aString Set to aString the URL at which the package repository can be found. version Not commented. version: aVersion Not commented.  File: gst-base.info, Node: Package-still unclassified, Next: Package-version parsing, Prev: Package-accessing, Up: Package 1.127.4 Package: still unclassified ----------------------------------- checkTagIfInPath: aString Not commented. dir: file tag: aDictionary Not commented. isInPath Not commented. parseAttributes: aString Not commented. path Not commented. path: aString Not commented.  File: gst-base.info, Node: Package-version parsing, Prev: Package-still unclassified, Up: Package 1.127.5 Package: version parsing -------------------------------- parseVersion: aString Not commented.  File: gst-base.info, Node: PackageLoader, Next: Permission, Prev: Package, Up: Base classes 1.128 PackageLoader =================== Defined in namespace Smalltalk Superclass: Object Category: Language-Packaging I am not part of a standard Smalltalk system. I provide methods for retrieving package information from an XML file and to load packages into a Smalltalk image, correctly handling dependencies. * Menu: * PackageLoader class-accessing:: (class) * PackageLoader class-loading:: (class) * PackageLoader class-testing:: (class)  File: gst-base.info, Node: PackageLoader class-accessing, Next: PackageLoader class-loading, Up: PackageLoader 1.128.1 PackageLoader class: accessing -------------------------------------- builtFilesFor: package Answer a Set of Strings containing the filenames of the given package's machine-generated files (relative to the directory answered by #directoryFor:) calloutsFor: package Answer a Set of Strings containing the filenames of the given package's required callouts (relative to the directory answered by #directoryFor:) directoryFor: package Answer a Directory object to the given package's files featuresFor: package Answer a Set of Strings containing the features provided by the given package. fileInsFor: package Answer a Set of Strings containing the filenames of the given package's file-ins (relative to the directory answered by #directoryFor:) filesFor: package Answer a Set of Strings containing the filenames of the given package's files (relative to the directory answered by #directoryFor:) flush Set to reload the `packages.xml' file the next time it is needed. ignoreCallouts Answer whether unavailable C callouts must generate errors or not. ignoreCallouts: aBoolean Set whether unavailable C callouts must generate errors or not. librariesFor: package Answer a Set of Strings containing the filenames of the given package's libraries (relative to the directory answered by #directoryFor:) modulesFor: package Answer a Set of Strings containing the filenames of the given package's modules (relative to the directory answered by #directoryFor:) packageAt: package Answer a Package object for the given package packageAt: package ifAbsent: aBlock Answer a Package object for the given package prerequisitesFor: package Answer a Set of Strings containing the prerequisites for the given package refresh Reload the `packages.xml' file in the image and kernel directories. The three possible places are 1) the kernel directory's parent directory, 2) the `.st' subdirectory of the user's home directory, 3) the local image directory (in order of decreasing priority). For a packages.xml found in the kernel directory's parent directory, all three directories are searched. For a packages.xml found in the `.st' subdirectory, only directories 2 and 3 are searched. For a packages.xml directory in the local image directory, finally, only directory 3 is searched. sunitScriptFor: package Answer a Strings containing a SUnit script that describes the package's test suite.  File: gst-base.info, Node: PackageLoader class-loading, Next: PackageLoader class-testing, Prev: PackageLoader class-accessing, Up: PackageLoader 1.128.2 PackageLoader class: loading ------------------------------------ fileInPackage: package File in the given package into GNU Smalltalk. fileInPackages: packagesList File in all the packages in packagesList into GNU Smalltalk.  File: gst-base.info, Node: PackageLoader class-testing, Prev: PackageLoader class-loading, Up: PackageLoader 1.128.3 PackageLoader class: testing ------------------------------------ canLoad: package Answer whether all the needed pre-requisites for package are available.  File: gst-base.info, Node: Permission, Next: PluggableAdaptor, Prev: PackageLoader, Up: Base classes 1.129 Permission ================ Defined in namespace Smalltalk Superclass: Object Category: Language-Security I am the basic class that represents whether operations that could harm the system's security are allowed or denied. * Menu: * Permission class-testing:: (class) * Permission-accessing:: (instance) * Permission-testing:: (instance)  File: gst-base.info, Node: Permission class-testing, Next: Permission-accessing, Up: Permission 1.129.1 Permission class: testing --------------------------------- allowing: aSymbol target: aTarget action: action Not commented. allowing: aSymbol target: aTarget actions: actionsArray Not commented. denying: aSymbol target: aTarget action: action Not commented. denying: aSymbol target: aTarget actions: actionsArray Not commented. granting: aSymbol target: aTarget action: action Not commented. granting: aSymbol target: aTarget actions: actionsArray Not commented. name: aSymbol target: aTarget action: action Not commented. name: aSymbol target: aTarget actions: actionsArray Not commented.  File: gst-base.info, Node: Permission-accessing, Next: Permission-testing, Prev: Permission class-testing, Up: Permission 1.129.2 Permission: accessing ----------------------------- action: anObject Not commented. actions Answer `actions'. actions: anObject Not commented. allow Not commented. allowing Not commented. deny Not commented. denying Not commented. isAllowing Answer `positive'. name Answer `name'. name: anObject Not commented. target Answer `target'. target: anObject Not commented.  File: gst-base.info, Node: Permission-testing, Prev: Permission-accessing, Up: Permission 1.129.3 Permission: testing --------------------------- check: aPermission for: anObject Not commented. implies: aPermission Not commented.  File: gst-base.info, Node: PluggableAdaptor, Next: PluggableProxy, Prev: Permission, Up: Base classes 1.130 PluggableAdaptor ====================== Defined in namespace Smalltalk Superclass: ValueAdaptor Category: Language-Data types I mediate between complex get/set behavior and the #value/#value: protocol used by ValueAdaptors. The get/set behavior can be implemented by two blocks, or can be delegated to another object with messages such as #someProperty to get and #someProperty: to set. * Menu: * PluggableAdaptor class-creating instances:: (class) * PluggableAdaptor-accessing:: (instance)  File: gst-base.info, Node: PluggableAdaptor class-creating instances, Next: PluggableAdaptor-accessing, Up: PluggableAdaptor 1.130.1 PluggableAdaptor class: creating instances -------------------------------------------------- getBlock: getBlock putBlock: putBlock Answer a PluggableAdaptor using the given blocks to implement #value and #value: on: anObject aspect: aSymbol Answer a PluggableAdaptor using anObject's aSymbol message to implement #value, and anObject's aSymbol: message (aSymbol followed by a colon) to implement #value: on: anObject getSelector: getSelector putSelector: putSelector Answer a PluggableAdaptor using anObject's getSelector message to implement #value, and anObject's putSelector message to implement #value: on: anObject index: anIndex Answer a PluggableAdaptor using anObject's #at: and #at:put: message to implement #value and #value:; the first parameter of #at: and #at:put: is anIndex on: aDictionary key: aKey Same as #on:index:. Provided for clarity and completeness.  File: gst-base.info, Node: PluggableAdaptor-accessing, Prev: PluggableAdaptor class-creating instances, Up: PluggableAdaptor 1.130.2 PluggableAdaptor: accessing ----------------------------------- value Get the value of the receiver. value: anObject Set the value of the receiver.  File: gst-base.info, Node: PluggableProxy, Next: Point, Prev: PluggableAdaptor, Up: Base classes 1.131 PluggableProxy ==================== Defined in namespace Smalltalk Superclass: AlternativeObjectProxy Category: Streams-Files I am a proxy that stores a different object and, upon load, sends #reconstructOriginalObject to that object (which can be a DirectedMessage, in which case the message is sent). The object to be stored is retrieved by sending #binaryRepresentationObject to the object. * Menu: * PluggableProxy class-accessing:: (class) * PluggableProxy-saving and restoring:: (instance)  File: gst-base.info, Node: PluggableProxy class-accessing, Next: PluggableProxy-saving and restoring, Up: PluggableProxy 1.131.1 PluggableProxy class: accessing --------------------------------------- on: anObject Answer a proxy to be used to save anObject. The proxy stores a different object obtained by sending to anObject the #binaryRepresentationObject message (embedded between #preStore and #postStore as usual).  File: gst-base.info, Node: PluggableProxy-saving and restoring, Prev: PluggableProxy class-accessing, Up: PluggableProxy 1.131.2 PluggableProxy: saving and restoring -------------------------------------------- object Reconstruct the object stored in the proxy and answer it; the binaryRepresentationObject is sent the #reconstructOriginalObject message, and the resulting object is sent the #postLoad message.  File: gst-base.info, Node: Point, Next: PositionableStream, Prev: PluggableProxy, Up: Base classes 1.132 Point =========== Defined in namespace Smalltalk Superclass: Object Category: Language-Data types Beginning of a Point class for simple display manipulation. Has not been exhaustively tested but appears to work for the basic primitives and for the needs of the Rectangle class. * Menu: * Point class-instance creation:: (class) * Point-accessing:: (instance) * Point-arithmetic:: (instance) * Point-comparing:: (instance) * Point-converting:: (instance) * Point-point functions:: (instance) * Point-printing:: (instance) * Point-storing:: (instance) * Point-truncation and round off:: (instance)  File: gst-base.info, Node: Point class-instance creation, Next: Point-accessing, Up: Point 1.132.1 Point class: instance creation -------------------------------------- new Create a new point with both coordinates set to 0 x: xInteger y: yInteger Create a new point with the given coordinates  File: gst-base.info, Node: Point-accessing, Next: Point-arithmetic, Prev: Point class-instance creation, Up: Point 1.132.2 Point: accessing ------------------------ x Answer the x coordinate x: aNumber Set the x coordinate to aNumber x: anXNumber y: aYNumber Set the x and y coordinate to anXNumber and aYNumber, respectively y Answer the y coordinate y: aNumber Set the y coordinate to aNumber  File: gst-base.info, Node: Point-arithmetic, Next: Point-comparing, Prev: Point-accessing, Up: Point 1.132.3 Point: arithmetic ------------------------- * scale Multiply the receiver by scale, which can be a Number or a Point + delta Sum the receiver and delta, which can be a Number or a Point - delta Subtract delta, which can be a Number or a Point, from the receiver / scale Divide the receiver by scale, which can be a Number or a Point, with no loss of precision // scale Divide the receiver by scale, which can be a Number or a Point, with truncation towards -infinity abs Answer a new point whose coordinates are the absolute values of the receiver's  File: gst-base.info, Node: Point-comparing, Next: Point-converting, Prev: Point-arithmetic, Up: Point 1.132.4 Point: comparing ------------------------ < aPoint Answer whether the receiver is higher and to the left of aPoint <= aPoint Answer whether aPoint is equal to the receiver, or the receiver is higher and to the left of aPoint = aPoint Answer whether the receiver is equal to aPoint > aPoint Answer whether the receiver is lower and to the right of aPoint >= aPoint Answer whether aPoint is equal to the receiver, or the receiver is lower and to the right of aPoint max: aPoint Answer self if it is lower and to the right of aPoint, aPoint otherwise min: aPoint Answer self if it is higher and to the left of aPoint, aPoint otherwise  File: gst-base.info, Node: Point-converting, Next: Point-point functions, Prev: Point-comparing, Up: Point 1.132.5 Point: converting ------------------------- asPoint Answer the receiver. asRectangle Answer an empty rectangle whose origin is self corner: aPoint Answer a Rectangle whose origin is the receiver and whose corner is aPoint extent: aPoint Answer a Rectangle whose origin is the receiver and whose extent is aPoint hash Answer an hash value for the receiver  File: gst-base.info, Node: Point-point functions, Next: Point-printing, Prev: Point-converting, Up: Point 1.132.6 Point: point functions ------------------------------ arcTan Answer the angle (measured counterclockwise) between the receiver and a ray starting in (0, 0) and moving towards (1, 0) - i.e. 3 o'clock dist: aPoint Answer the distance between the receiver and aPoint dotProduct: aPoint Answer the dot product between the receiver and aPoint grid: aPoint Answer a new point whose coordinates are rounded towards the nearest multiple of aPoint normal Rotate the Point 90degrees clockwise and get the unit vector transpose Answer a new point whose coordinates are the receiver's coordinates exchanged (x becomes y, y becomes x) truncatedGrid: aPoint Answer a new point whose coordinates are rounded towards -infinity, to a multiple of grid (which must be a Point)  File: gst-base.info, Node: Point-printing, Next: Point-storing, Prev: Point-point functions, Up: Point 1.132.7 Point: printing ----------------------- printOn: aStream Print a representation for the receiver on aStream  File: gst-base.info, Node: Point-storing, Next: Point-truncation and round off, Prev: Point-printing, Up: Point 1.132.8 Point: storing ---------------------- storeOn: aStream Print Smalltalk code compiling to the receiver on aStream  File: gst-base.info, Node: Point-truncation and round off, Prev: Point-storing, Up: Point 1.132.9 Point: truncation and round off --------------------------------------- rounded Answer a new point whose coordinates are rounded to the nearest integer truncateTo: grid Answer a new point whose coordinates are rounded towards -infinity, to a multiple of grid (which must be a Number)  File: gst-base.info, Node: PositionableStream, Next: Process, Prev: Point, Up: Base classes 1.133 PositionableStream ======================== Defined in namespace Smalltalk Superclass: Stream Category: Streams-Collections My instances represent streams where explicit positioning is permitted. Thus, my streams act in a manner to normal disk files: you can read or write sequentially, but also position the file to a particular place whenever you choose. Generally, you'll want to use ReadStream, WriteStream or ReadWriteStream instead of me to create and use streams. * Menu: * PositionableStream class-instance creation:: (class) * PositionableStream-accessing-reading:: (instance) * PositionableStream-class type methods:: (instance) * PositionableStream-compiling:: (instance) * PositionableStream-positioning:: (instance) * PositionableStream-still unclassified:: (instance) * PositionableStream-testing:: (instance) * PositionableStream-truncating:: (instance)  File: gst-base.info, Node: PositionableStream class-instance creation, Next: PositionableStream-accessing-reading, Up: PositionableStream 1.133.1 PositionableStream class: instance creation --------------------------------------------------- on: aCollection Answer an instance of the receiver streaming on the whole contents of aCollection on: aCollection from: firstIndex to: lastIndex Answer an instance of the receiver streaming from the firstIndex-th item of aCollection to the lastIndex-th  File: gst-base.info, Node: PositionableStream-accessing-reading, Next: PositionableStream-class type methods, Prev: PositionableStream class-instance creation, Up: PositionableStream 1.133.2 PositionableStream: accessing-reading --------------------------------------------- close Disassociate a stream from its backing store. contents Returns a collection of the same type that the stream accesses, up to and including the final element. copyFrom: start to: end Answer the data on which the receiver is streaming, from the start-th item to the end-th. Note that this method is 0-based, unlike the one in Collection, because a Stream's #position method returns 0-based values. next Answer the next item of the receiver. Returns nil when at end of stream. nextAvailable: anInteger into: aCollection startingAt: pos Place up to anInteger objects from the receiver into aCollection, starting from position pos in the collection and stopping if no more data is available. nextAvailable: anInteger putAllOn: aStream Copy up to anInteger objects from the receiver into aStream, stopping if no more data is available. peek Returns the next element of the stream without moving the pointer. Returns nil when at end of stream. peekFor: anObject Returns true and gobbles the next element from the stream of it is equal to anObject, returns false and doesn't gobble the next element if the next element is not equal to anObject. readStream Answer a ReadStream on the same contents as the receiver reverseContents Returns a collection of the same type that the stream accesses, up to and including the final element, but in reverse order. upTo: anObject Returns a collection of the same type that the stream accesses, up to but not including the object anObject. Returns the entire rest of the stream's contents if anObject is not present. upToEnd Returns a collection of the same type that the stream accesses, containing the entire rest of the stream's contents.  File: gst-base.info, Node: PositionableStream-class type methods, Next: PositionableStream-compiling, Prev: PositionableStream-accessing-reading, Up: PositionableStream 1.133.3 PositionableStream: class type methods ---------------------------------------------- isExternalStream We stream on a collection residing in the image, so answer false species Return the type of the collections returned by #upTo: etc., which are the same kind as those returned by the collection with methods such as #select:.  File: gst-base.info, Node: PositionableStream-compiling, Next: PositionableStream-positioning, Prev: PositionableStream-class type methods, Up: PositionableStream 1.133.4 PositionableStream: compiling ------------------------------------- name Answer a string that represents what the receiver is streaming on segmentFrom: startPos to: endPos Answer an object that, when sent #asString, will yield the result of sending `copyFrom: startPos to: endPos' to the receiver  File: gst-base.info, Node: PositionableStream-positioning, Next: PositionableStream-still unclassified, Prev: PositionableStream-compiling, Up: PositionableStream 1.133.5 PositionableStream: positioning --------------------------------------- basicPosition: anInteger Move the stream pointer to the anInteger-th object isPositionable Answer true if the stream supports moving backwards with #skip:. position Answer the current value of the stream pointer position: anInteger Move the stream pointer to the anInteger-th object reset Move the stream back to its first element. For write-only streams, the stream is truncated there. setToEnd Move the current position to the end of the stream. size Answer the size of data on which we are streaming. skip: anInteger Move the current position by anInteger places, either forwards or backwards.  File: gst-base.info, Node: PositionableStream-still unclassified, Next: PositionableStream-testing, Prev: PositionableStream-positioning, Up: PositionableStream 1.133.6 PositionableStream: still unclassified ---------------------------------------------- nextPutAllOn: aStream Write all the objects in the receiver to aStream.  File: gst-base.info, Node: PositionableStream-testing, Next: PositionableStream-truncating, Prev: PositionableStream-still unclassified, Up: PositionableStream 1.133.7 PositionableStream: testing ----------------------------------- atEnd Answer whether the objects in the stream have reached an end basicAtEnd Answer whether the objects in the stream have reached an end. This method must NOT be overridden. isEmpty Answer whether the stream has no objects  File: gst-base.info, Node: PositionableStream-truncating, Prev: PositionableStream-testing, Up: PositionableStream 1.133.8 PositionableStream: truncating -------------------------------------- truncate Truncate the receiver to the current position - only valid for writing streams  File: gst-base.info, Node: Process, Next: ProcessEnvironment, Prev: PositionableStream, Up: Base classes 1.134 Process ============= Defined in namespace Smalltalk Superclass: Link Category: Language-Processes I represent a unit of computation. My instances are independantly executable blocks that have a priority associated with them, and they can suspend themselves and resume themselves however they wish. * Menu: * Process-accessing:: (instance) * Process-basic:: (instance) * Process-builtins:: (instance) * Process-debugging:: (instance) * Process-printing:: (instance)  File: gst-base.info, Node: Process-accessing, Next: Process-basic, Up: Process 1.134.1 Process: accessing -------------------------- externalInterruptsEnabled Answer whether the receiver is executed with interrupts enabled name Answer the user-friendly name of the process. name: aString Give the name aString to the process priority Answer the receiver's priority priority: anInteger Change the receiver's priority to anInteger queueInterrupt: aBlock Force the receiver to be interrupted and to evaluate aBlock as soon as it becomes the active process (this could mean NOW if the receiver is active). If the process is temporarily suspended or waiting on a semaphore, it is temporarily woken up so that the interrupt is processed as soon as the process priority allows to do. Answer the receiver. suspendedContext Answer the context that the process was executing at the time it was suspended. suspendedContext: aContext Modify the context that the process was executing at the time it was suspended. valueWithoutInterrupts: aBlock Evaluate aBlock and delay all interrupts that are requested during its execution to after aBlock returns.  File: gst-base.info, Node: Process-basic, Next: Process-builtins, Prev: Process-accessing, Up: Process 1.134.2 Process: basic ---------------------- context Return the execution context of the receiver. debugger Return the object in charge of debugging the receiver. This always returns nil unless the DebugTools package is loaded. finalize Terminate processes that are GCed while waiting on a dead semaphore. lowerPriority Lower a bit the priority of the receiver. A #lowerPriority will cancel a previous #raisePriority, and vice versa. makeUntrusted: aBoolean Set whether the receiver is trusted or not. primTerminate Terminate the receiver - This is nothing more than prohibiting to resume the process, then suspending it. raisePriority Raise a bit the priority of the receiver. A #lowerPriority will cancel a previous #raisePriority, and vice versa. singleStep Execute a limited amount of code (usually a bytecode, or up to the next backward jump, or up to the next message send) of the receiver, which must in a ready-to-run state (neither executing nor terminating nor suspended), then restart running the current process. The current process should have higher priority than the receiver. For better performance, use the underlying primitive, Process>>#singleStepWaitingOn:. terminate Terminate the receiver after having evaluated all the #ensure: and #ifCurtailed: blocks that are active in it. This is done by signalling a ProcessBeingTerminated notification. terminateOnQuit Mark the receiver so that it is terminated when ObjectMemory class>>#quit: is sent.  File: gst-base.info, Node: Process-builtins, Next: Process-debugging, Prev: Process-basic, Up: Process 1.134.3 Process: builtins ------------------------- resume Resume the receiver's execution singleStepWaitingOn: aSemaphore Execute a limited amount of code (usually a bytecode, or up to the next backward jump, or up to the next message send) of the receiver, which must in a ready-to-run state (neither executing nor terminating nor suspended), then restart running the current process. aSemaphore is used as a means to synchronize the execution of the current process and the receiver and should have no signals on it. The current process should have higher priority than the receiver. suspend Do nothing if we're already suspended. Note that the blue book made suspend a primitive - but the real primitive is yielding control to another process. Suspending is nothing more than taking ourselves out of every scheduling list and THEN yielding control to another process yield Yield control from the receiver to other processes  File: gst-base.info, Node: Process-debugging, Next: Process-printing, Prev: Process-builtins, Up: Process 1.134.4 Process: debugging -------------------------- detach Do nothing, instances of Process are already detached.  File: gst-base.info, Node: Process-printing, Prev: Process-debugging, Up: Process 1.134.5 Process: printing ------------------------- printOn: aStream Print a representation of the receiver on aStream  File: gst-base.info, Node: ProcessEnvironment, Next: ProcessorScheduler, Prev: Process, Up: Base classes 1.135 ProcessEnvironment ======================== Defined in namespace Smalltalk Superclass: Object Category: Language-Processes I represent a proxy for thread-local variables defined for Smalltalk processes. Associations requested to me retrieve the thread-local value for the current process. For now, I don't provide the full protocol of a Dictionary; in particular the iteration protocol is absent. * Menu: * ProcessEnvironment class-disabled:: (class) * ProcessEnvironment class-singleton:: (class) * ProcessEnvironment-accessing:: (instance) * ProcessEnvironment-dictionary removing:: (instance) * ProcessEnvironment-dictionary testing:: (instance)  File: gst-base.info, Node: ProcessEnvironment class-disabled, Next: ProcessEnvironment class-singleton, Up: ProcessEnvironment 1.135.1 ProcessEnvironment class: disabled ------------------------------------------ new This method should not be called for instances of this class.  File: gst-base.info, Node: ProcessEnvironment class-singleton, Next: ProcessEnvironment-accessing, Prev: ProcessEnvironment class-disabled, Up: ProcessEnvironment 1.135.2 ProcessEnvironment class: singleton ------------------------------------------- uniqueInstance Return the singleton instance of ProcessEnvironment.  File: gst-base.info, Node: ProcessEnvironment-accessing, Next: ProcessEnvironment-dictionary removing, Prev: ProcessEnvironment class-singleton, Up: ProcessEnvironment 1.135.3 ProcessEnvironment: accessing ------------------------------------- add: newObject Add the newObject association to the receiver associationAt: key Answer the value associated to the given key, or the result of evaluating aBlock if the key is not found associationAt: key ifAbsent: aBlock Answer the value associated to the given key, or the result of evaluating aBlock if the key is not found at: key Answer the value associated to the given key. Return nil if the key is not found at: key ifAbsent: aBlock Answer the value associated to the given key, or the result of evaluating aBlock if the key is not found at: key ifAbsentPut: aBlock Answer the value associated to the given key, setting it to the result of evaluating aBlock if the key is not found. at: key ifPresent: aBlock Answer the value associated to the given key, or the result of evaluating aBlock if the key is not found at: key put: value Store value as associated to the given key keys Answer a kind of Set containing the keys of the receiver  File: gst-base.info, Node: ProcessEnvironment-dictionary removing, Next: ProcessEnvironment-dictionary testing, Prev: ProcessEnvironment-accessing, Up: ProcessEnvironment 1.135.4 ProcessEnvironment: dictionary removing ----------------------------------------------- remove: anAssociation Remove anAssociation's key from the dictionary remove: anAssociation ifAbsent: aBlock Remove anAssociation's key from the dictionary removeAllKeys: keys Remove all the keys in keys, without raising any errors removeAllKeys: keys ifAbsent: aBlock Remove all the keys in keys, passing the missing keys as parameters to aBlock as they're encountered removeKey: aSymbol Remove the aSymbol key from the dictionary removeKey: aSymbol ifAbsent: aBlock Remove the aSymbol key from the dictionary  File: gst-base.info, Node: ProcessEnvironment-dictionary testing, Prev: ProcessEnvironment-dictionary removing, Up: ProcessEnvironment 1.135.5 ProcessEnvironment: dictionary testing ---------------------------------------------- includesKey: key Answer whether the receiver contains the given key  File: gst-base.info, Node: ProcessorScheduler, Next: ProcessVariable, Prev: ProcessEnvironment, Up: Base classes 1.136 ProcessorScheduler ======================== Defined in namespace Smalltalk Superclass: Object Category: Language-Processes I provide methods that control the execution of processes. * Menu: * ProcessorScheduler class-instance creation:: (class) * ProcessorScheduler-basic:: (instance) * ProcessorScheduler-built ins:: (instance) * ProcessorScheduler-idle tasks:: (instance) * ProcessorScheduler-printing:: (instance) * ProcessorScheduler-priorities:: (instance) * ProcessorScheduler-storing:: (instance) * ProcessorScheduler-timed invocation:: (instance)  File: gst-base.info, Node: ProcessorScheduler class-instance creation, Next: ProcessorScheduler-basic, Up: ProcessorScheduler 1.136.1 ProcessorScheduler class: instance creation --------------------------------------------------- new Error--new instances of ProcessorScheduler should not be created.  File: gst-base.info, Node: ProcessorScheduler-basic, Next: ProcessorScheduler-built ins, Prev: ProcessorScheduler class-instance creation, Up: ProcessorScheduler 1.136.2 ProcessorScheduler: basic --------------------------------- activeDebugger Answer the active process' debugger activePriority Answer the active process' priority activeProcess Answer the active process processEnvironment Answer another singleton object hosting thread-local variables for the Smalltalk processes. This acts like a normal Dictionary with a couple of differences: a) using #associationAt: will return special associations that retrieve a thread-local value; b) requesting missing keys will return nil, and removing them will be a nop. processesAt: aPriority Answer a linked list of processes at the given priority terminateActive Terminate the active process timeSlice Answer the timeslice that is assigned to each Process before it is automatically preempted by the system (in milliseconds). An answer of zero means that preemptive multitasking is disabled. Note that the system by default is compiled without preemptive multitasking, and that even if it is enabled it will work only under BSD derivatives (or, in general, systems that support ITIMER_VIRTUAL). timeSlice: milliSeconds Set the timeslice that is assigned to each Process before it is automatically preempted by the system. Setting this to zero disables preemptive multitasking. Note that the system by default is compiled with preemptive multitasking disabled, and that even if it is enabled it will surely work only under BSD derivatives (or, in general, systems that support ITIMER_VIRTUAL). yield Let the active process yield control to other processes  File: gst-base.info, Node: ProcessorScheduler-built ins, Next: ProcessorScheduler-idle tasks, Prev: ProcessorScheduler-basic, Up: ProcessorScheduler 1.136.3 ProcessorScheduler: built ins ------------------------------------- disableInterrupts Disable interrupts caused by external events while the current process is executing. Note that interrupts are disabled on a per-process basis, and that calling #disableInterrupts twice requires calling #enableInterrupts twice as well to re-enable interrupts. enableInterrupts Re-enable interrupts caused by external events while the current process is executing. By default, interrupts are enabled.  File: gst-base.info, Node: ProcessorScheduler-idle tasks, Next: ProcessorScheduler-printing, Prev: ProcessorScheduler-built ins, Up: ProcessorScheduler 1.136.4 ProcessorScheduler: idle tasks -------------------------------------- idle Private - Call the next idle task. Return whether GNU Smalltalk should pause until the next OS signal. idleAdd: aBlock Register aBlock to be executed when things are idle initialize Private - Start the finalization process. pause: aBoolean Private - Pause for some time if aBoolean is false, or until a signal if it is true. startFinalizers Private - Fire a low-priority process to finalize the objects update: aSymbol If we left some work behind when the image was saved, do it now.  File: gst-base.info, Node: ProcessorScheduler-printing, Next: ProcessorScheduler-priorities, Prev: ProcessorScheduler-idle tasks, Up: ProcessorScheduler 1.136.5 ProcessorScheduler: printing ------------------------------------ printOn: aStream Store onto aStream a printed representation of the receiver  File: gst-base.info, Node: ProcessorScheduler-priorities, Next: ProcessorScheduler-storing, Prev: ProcessorScheduler-printing, Up: ProcessorScheduler 1.136.6 ProcessorScheduler: priorities -------------------------------------- highIOPriority Answer the priority for system high-priority I/O processes, such as a process handling input from a network. highestPriority Answer the highest valid priority idlePriority Answer the priority of idle processes. lowIOPriority Answer the priority for system low-priority I/O processes. Examples are the process handling input from the user (keyboard, pointing device, etc.) and the process distributing input from a network. lowestPriority Answer the lowest valid priority priorityName: priority Private - Answer a name for the given process priority systemBackgroundPriority Answer the priority for system background-priority processes. An incremental garbage collector could run at this level but now it runs at idlePriority instead. timingPriority Answer the priority for system real-time processes. unpreemptedPriority Answer the highest priority avilable in the system; never create a process with this priority, instead use BlockClosure>>#valueWithoutPreemption. userBackgroundPriority Answer the priority for user background-priority processes userInterruptPriority Answer the priority for user interrupt-priority processes. Processes run at this level will preempt the window scheduler and should, therefore, not consume the processor forever. userSchedulingPriority Answer the priority for user standard-priority processes  File: gst-base.info, Node: ProcessorScheduler-storing, Next: ProcessorScheduler-timed invocation, Prev: ProcessorScheduler-priorities, Up: ProcessorScheduler 1.136.7 ProcessorScheduler: storing ----------------------------------- storeOn: aStream Store onto aStream a Smalltalk expression which evaluates to the receiver  File: gst-base.info, Node: ProcessorScheduler-timed invocation, Prev: ProcessorScheduler-storing, Up: ProcessorScheduler 1.136.8 ProcessorScheduler: timed invocation -------------------------------------------- isTimeoutProgrammed Private - Answer whether there is a pending call to #signal:atMilliseconds: signal: aSemaphore atNanosecondClockValue: ns Private - signal 'aSemaphore' when the nanosecond clock reaches 'ns' nanoseconds. signal: aSemaphore onInterrupt: anIntegerSignalNumber Signal 'aSemaphore' when the given C signal occurs.  File: gst-base.info, Node: ProcessVariable, Next: Promise, Prev: ProcessorScheduler, Up: Base classes 1.137 ProcessVariable ===================== Defined in namespace Smalltalk Superclass: LookupKey Category: Language-Processes I represent a proxy for a thread-local variable defined for a process. Requesting the value will return the thread-local setting for the current process. * Menu: * ProcessVariable class-accessing:: (class) * ProcessVariable-accessing:: (instance)  File: gst-base.info, Node: ProcessVariable class-accessing, Next: ProcessVariable-accessing, Up: ProcessVariable 1.137.1 ProcessVariable class: accessing ---------------------------------------- key: anObject Return a new ProcessVariable with the given key. Not that the key need not be a symbol or string, for example you could use an array #(#{class name} 'name'). Setting the variable's value will automatically create it in the current process, while removal must be done by hand through the ProcessEnvironment singleton object. new Return a new ProcessVariable with a new anonymous but unique key. It is suggested to use a descriptive name instead to ease debugging. Setting the variable's value will automatically create it in the current process, while removal must be done by hand through the ProcessEnvironment singleton object.  File: gst-base.info, Node: ProcessVariable-accessing, Prev: ProcessVariable class-accessing, Up: ProcessVariable 1.137.2 ProcessVariable: accessing ---------------------------------- environment Return the environment in which this ProcessVariable lives. This is the singleton instance of ProcessEnvironment for all variables. use: anObject during: aBlock Set the value of this variable to anObject during the execution of aBlock, then restore it. value Return the value of this variable in the current process. value: anObject Set the value of the current process's copy of the variable to be anObject. valueIfAbsent: aBlock Return the value of this variable in the current process.  File: gst-base.info, Node: Promise, Next: Random, Prev: ProcessVariable, Up: Base classes 1.138 Promise ============= Defined in namespace Smalltalk Superclass: ValueHolder Category: Language-Data types I store my value in a variable, and know whether I have been initialized or not. If you ask for my value and I have not been initialized, I suspend the process until a value has been assigned. * Menu: * Promise class-creating instances:: (class) * Promise-accessing:: (instance) * Promise-initializing:: (instance) * Promise-printing:: (instance) * Promise-still unclassified:: (instance)  File: gst-base.info, Node: Promise class-creating instances, Next: Promise-accessing, Up: Promise 1.138.1 Promise class: creating instances ----------------------------------------- for: aBlock Invoke aBlock at an indeterminate time in an indeterminate process before answering its value from #value sent to my result. null This method should not be called for instances of this class.  File: gst-base.info, Node: Promise-accessing, Next: Promise-initializing, Prev: Promise class-creating instances, Up: Promise 1.138.2 Promise: accessing -------------------------- hasError Answer whether calling #value will raise an exception. hasValue Answer whether we already have a value (or calling #value will raise an error). value Get the value of the receiver. value: anObject Set the value of the receiver.  File: gst-base.info, Node: Promise-initializing, Next: Promise-printing, Prev: Promise-accessing, Up: Promise 1.138.3 Promise: initializing ----------------------------- initialize Private - set the initial state of the receiver  File: gst-base.info, Node: Promise-printing, Next: Promise-still unclassified, Prev: Promise-initializing, Up: Promise 1.138.4 Promise: printing ------------------------- printOn: aStream Print a representation of the receiver  File: gst-base.info, Node: Promise-still unclassified, Prev: Promise-printing, Up: Promise 1.138.5 Promise: still unclassified ----------------------------------- errorValue: anException Private - Raise anException whenever #value is called.  File: gst-base.info, Node: Random, Next: ReadStream, Prev: Promise, Up: Base classes 1.139 Random ============ Defined in namespace Smalltalk Superclass: Stream Category: Streams My instances are generator streams that produce random numbers, which are floating point values between 0 and 1. * Menu: * Random class-instance creation:: (class) * Random class-shortcuts:: (class) * Random-basic:: (instance) * Random-testing:: (instance) smalltalk-3.2.5/doc/debug.texi0000644000175000017500000001052112130455700013150 00000000000000@c Define the class index, method index, and selector cross-reference @ifclear CLASS-INDICES @set CLASS-INDICES @defindex cl @defcodeindex me @defcodeindex sl @end ifclear @c These are used for both TeX and HTML @set BEFORE1 @set AFTER1 @set BEFORE2 @set AFTER2 @ifinfo @c Use asis so that leading and trailing spaces are meaningful. @c Remember we're inside a @menu command, hence the blanks are @c kept in the output. @set BEFORE1 @asis{* } @set AFTER1 @asis{::} @set BEFORE2 @asis{ (} @set AFTER2 @asis{)} @end ifinfo @macro class {a,b} @value{BEFORE1}\a\\a\@b{\b\}@value{AFTER1} @end macro @macro superclass {a,b} \a\\a\@value{BEFORE2}@i{\b\}@value{AFTER2} @end macro @ifnotinfo @macro begindetailmenu @display @end macro @macro enddetailmenu @end display @end macro @end ifnotinfo @ifinfo @macro begindetailmenu @detailmenu @end macro @macro enddetailmenu @end detailmenu @end macro @end ifinfo @iftex @macro beginmenu @end macro @macro endmenu @end macro @end iftex @ifnottex @macro beginmenu @menu @end macro @macro endmenu @end menu @end macro @end ifnottex @beginmenu @ifnottex Alphabetic list: * Debugger:: @end ifnottex @ifinfo Class tree: @end ifinfo @iftex @section Tree @end iftex @ifnotinfo Classes documented in this manual are @b{boldfaced}. @end ifnotinfo @begindetailmenu @superclass{@t{}, Object} @class{@t{ }, Debugger} @enddetailmenu @endmenu @unmacro class @unmacro superclass @unmacro endmenu @unmacro beginmenu @unmacro enddetailmenu @unmacro begindetailmenu @node Debugger @section Debugger @clindex Debugger @table @b @item Defined in namespace Smalltalk @itemx Superclass: Object @itemx Category: System-Debugging I provide debugging facilities for another inferior process. I have methods that allow the controlled process to proceed with varying granularity. In addition, I keep a cache mapping instruction pointer bytecodes to line numbers. @end table @menu * Debugger class-disabling debugging:: (class) * Debugger class-instance creation:: (class) * Debugger class-source code:: (class) * Debugger-inferior process properties:: (instance) * Debugger-stepping commands:: (instance) @end menu @node Debugger class-disabling debugging @subsection Debugger class:@- disabling debugging @table @b @meindex debuggerClass @item debuggerClass Answer `nil'. @end table @node Debugger class-instance creation @subsection Debugger class:@- instance creation @table @b @meindex on:@- @item on:@- aProcess Suspend aProcess and return a new Debugger that controls aProcess. aProcess must not be the currently running process. @end table @node Debugger class-source code @subsection Debugger class:@- source code @table @b @meindex currentLineIn:@- @item currentLineIn:@- aContext Not commented. @end table @node Debugger-inferior process properties @subsection Debugger:@- inferior process properties @table @b @meindex currentLine @item currentLine Return the line number in traced process. @meindex isActive @item isActive Answer true if the inferior process is still running. @meindex process @item process Answer the inferior process. @meindex suspendedContext @item suspendedContext Answer the suspended execution state of the inferior process. @end table @node Debugger-stepping commands @subsection Debugger:@- stepping commands @table @b @meindex continue @item continue Terminate the controlling process and continue execution of the traced process. @meindex finish @item finish Run to the next return. @meindex finish:@- @item finish:@- aContext Run up until aContext returns. @meindex next @item next Run to the end of the current line in the inferior process, skipping over message sends. @meindex slowFinish @item slowFinish Run in single-step mode up to the next return. @meindex slowFinish:@- @item slowFinish:@- aContext Run in single-step mode until aContext returns. @meindex step @item step Run to the end of the current line in the inferior process or to the next message send. @meindex stepBytecode @item stepBytecode Run a single bytecode in the inferior process. @meindex stopInferior @item stopInferior Suspend the inferior process and raise a DebuggerReentered notification in the controlling process. @meindex stopInferior:@- @item stopInferior:@- anObject Suspend the inferior process and raise a DebuggerReentered notification in the controlling process with anObject as the exception's message. @end table smalltalk-3.2.5/doc/gst.info-20000644000175000017500000013404512130455672013020 00000000000000This is gst.info, produced by makeinfo version 4.13 from /home/ich/source/smalltalk/release/smalltalk/doc/gst-fixed.texi. INFO-DIR-SECTION Software development START-INFO-DIR-ENTRY * Smalltalk: (gst). The GNU Smalltalk user's guide. END-INFO-DIR-ENTRY Permission is granted to copy, distribute and/or modify this document under the terms of the GNU Free Documentation License, Version 1.2 or any later version published by the Free Software Foundation; with no Invariant Sections, with no Front-Cover Texts, and with no Back-Cover Texts. A copy of the license is included in the section entitled "GNU Free Documentation License".  File: gst.info, Node: Creating exceptions, Next: Raising exceptions, Up: Exception handling 6.11.1 Creating exceptions -------------------------- GNU Smalltalk provides a few exceptions, all of which are subclasses of `Exception'. Most of the ones you might want to create yourself are in the `SystemExceptions' namespace. You can browse the builtin exceptions in the base library reference, and look at their names with `Exception printHierarchy'. Some useful examples from the system exceptions are `SystemExceptions.InvalidValue', whose meaning should be obvious, and `SystemExceptions.WrongMessageSent', which we will demonstrate below. Let's say that you change one of your classes to no longer support #new for creating new instances. However, because you use the first-class classes feature of Smalltalk, it is not so easy to find and change all sends. Now, you can do something like this: Object subclass: Toaster [ Toaster class >> new [ ^SystemExceptions.WrongMessageSent signalOn: #new useInstead: #toast: ] Toaster class >> toast: reason [ ^super new reason: reason; yourself ] ... ] Admittedly, this doesn't quite fit the conditions for using exceptions. However, since the exception type is already provided, it is probably easier to use it than #error: when you are doing defensive programming of this sort.  File: gst.info, Node: Raising exceptions, Next: Handling exceptions, Prev: Creating exceptions, Up: Exception handling 6.11.2 Raising exceptions ------------------------- Raising an exception is really a two-step process. First, you create the exception object; then, you send it `#signal'. If you look through the hierarchy, you'll see many class methods that combine these steps for convenience. For example, the class `Exception' provides `#new' and `#signal', where the latter is just `^self new signal'. You may be tempted to provide only a signalling variant of your own exception creation methods. However, this creates the problem that your subclasses will not be able to trivially provide new instance creation methods. Error subclass: ReadOnlyText [ ReadOnlyText class >> signalOn: aText range: anInterval [ ^self new initText: aText range: anInterval; signal ] initText: aText range: anInterval [ ... ] ] Here, if you ever want to subclass `ReadOnlyText' and add new information to the instance before signalling it, you'll have to use the private method `#initText:range:'. We recommend leaving out the signalling instance-creation variant in new code, as it saves very little work and makes signalling code less clear. Use your own judgement and evaluation of the situation to determine when to include a signalling variant.  File: gst.info, Node: Handling exceptions, Next: When an exception isn't handled, Prev: Raising exceptions, Up: Exception handling 6.11.3 Handling exceptions -------------------------- To handle an exception when it occurs in a particular block of code, use `#on:do:' like this: ^[someText add: inputChar beforeIndex: i] on: ReadOnlyText do: [:sig | sig return: nil] This code will put a handler for `ReadOnlyText' signals on the handler stack while the first block is executing. If such an exception occurs, and it is not handled by any handlers closer to the point of signalling on the stack (known as "inner handlers"), the exception object will pass itself to the handler block given as the `do:' argument. You will almost always want to use this object to handle the exception somehow. There are six basic handler actions, all sent as messages to the exception object: `return:' Exit the block that received this `#on:do:', returning the given value. You can also leave out the argument by sending `#return', in which case it will be nil. If you want this handler to also handle exceptions in whatever value you might provide, you should use `#retryUsing:' with a block instead. `retry' Acts sort of like a "goto" by restarting the first block. Obviously, this can lead to an infinite loop if you don't fix the situation that caused the exception. `#retry' is a good way to implement reinvocation upon recovery, because it does not increase the stack height. For example, this: frobnicate: n [ ^[do some stuff with n] on: SomeError do: [:sig | sig return: (self frobnicate: n + 1)] ] should be replaced with retry: frobnicate: aNumber [ | n | n := aNumber. ^[do some stuff with n] on: SomeError do: [:sig | n := 1 + n. sig retry] ] `retryUsing:' Like `#retry', except that it effectively replaces the original block with the one given as an argument. `pass' If you want to tell the exception to let an outer handler handle it, use `#pass' instead of `#signal'. This is just like rethrowing a caught exception in other languages. `resume:' This is the really interesting one. Instead of unwinding the stack, this will effectively answer the argument from the `#signal' send. Code that sends `#signal' to resumable exceptions can use this value, or ignore it, and continue executing. You can also leave out the argument, in which case the `#signal' send will answer nil. Exceptions that want to be resumable must register this capability by answering `true' from the `#isResumable' method, which is checked on every `#resume:' send. `outer' This is like `#pass', but if an outer handler uses `#resume:', this handler block will be resumed (and `#outer' will answer the argument given to `#resume:') rather than the piece of code that sent `#signal' in the first place. None of these methods return to the invoking handler block except for `#outer', and that only in certain cases described for it above. Exceptions provide several more features; see the methods on the classes `Signal' and `Exception' for the various things you can do with them. Fortunately, the above methods can do what you want in almost all cases. If you don't use one of these methods or another exception feature to exit your handler, Smalltalk will assume that you meant to `sig return:' whatever you answer from your handler block. We don't recommend relying on this; you should use an explicit `sig return:' instead. A quick shortcut to handling multiple exception types is the `ExceptionSet', which allows you to have a single handler for the exceptions of a union of classes: ^[do some stuff with n] on: SomeError, ReadOnlyError do: [:sig | ...] In this code, any `SomeError' or `ReadOnlyError' signals will be handled by the given handler block.  File: gst.info, Node: When an exception isn't handled, Next: Creating new exception classes, Prev: Handling exceptions, Up: Exception handling 6.11.4 When an exception isn't handled -------------------------------------- Every exception chooses one of the above handler actions by default when no handler is found, or they all use `#pass'. This is invoked by sending `#defaultAction' to the class. One example of a default action is presented above as part of the example of `#error:' usage; that default action prints a message, backtrace, and unwinds the stack all the way. The easiest way to choose a default action for your own exception classes is to subclass from an exception class that already chose the right one, as explained in the next section. For example, some exceptions, such as warnings, resume by default, and thus should be treated as if they will almost always resume. Selecting by superclass is by no means a requirement. Specializing your `Error' subclass to be resumable, or even to resume by default, is perfectly acceptable when it makes sense for your design.  File: gst.info, Node: Creating new exception classes, Next: Hooking into the stack unwinding, Prev: When an exception isn't handled, Up: Exception handling 6.11.5 Creating new exception classes ------------------------------------- If you want code to be able to handle your signalled exceptions, you will probably want to provide a way to pick those kinds out automatically. The easiest way to do this is to subclass `Exception'. First, you should choose an exception class to specialize. `Error' is the best choice for non-resumable exceptions, and `Notification' or its subclass `Warning' is best for exceptions that should resume with `nil' by default. Exceptions are just normal objects; include whatever information you think would be useful to handlers. Note that there are two textual description fields, a "description" and a "message text". The description, if provided, should be a more-or-less constant string answered from a override method on `#description', meant to describe all instances of your exception class. The message text is meant to be provided at the point of signalling, and should be used for any extra information that code might want to provide. Your signalling code can provide the `messageText' by using `#signal:' instead of `#signal'. This is yet another reason why signalling variants of instance creation messages can be more trouble than they're worth.  File: gst.info, Node: Hooking into the stack unwinding, Next: Handler stack unwinding caveat, Prev: Creating new exception classes, Up: Exception handling 6.11.6 Hooking into the stack unwinding --------------------------------------- More often useful than even `#on:do:' is `#ensure:', which guarantees that some code is executed when the stack unwinds, whether because of normal execution or because of a signalled exception. Here is an example of use of `#ensure:' and a situation where the stack can unwind even without a signal: Object subclass: ExecuteWithBreak [ | breakBlock | break: anObject [ breakBlock value: anObject ] valueWithBreak: aBlock [ "Sets up breakBlock before entering the block, and passes self to the block." | oldBreakBlock | oldBreakBlock := breakBlock. ^[breakBlock := [:arg | ^arg]. aBlock value] ensure: [breakBlock := oldBreakBlock] ] ] This class provides a way to stop the execution of a block without exiting the whole method as using `^' inside a block would do. The use of `#ensure:' guarantees (hence the name "ensure") that even if `breakBlock' is invoked or an error is handled by unwinding, the old "break block" will be restored. The definition of `breakBlock' is extremely simply; it is an example of the general unwinding feature of blocks, that you have probably already used: (history includesKey: num) ifTrue: [ ^self error: 'Duplicate check number' ]. You have probably been using `#ensure:' without knowing. For example, `File>>#withReadStreamDo:' uses it to ensure that the file is closed when leaving the block.  File: gst.info, Node: Handler stack unwinding caveat, Prev: Hooking into the stack unwinding, Up: Exception handling 6.11.7 Handler stack unwinding caveat ------------------------------------- One important difference between Smalltalk and other languages is that when a handler is invoked, the stack is not unwound. The Smalltalk exception system is designed this way because it's rare to write code that could break because of this difference, and the `#resume:' feature doesn't make sense if the stack is unwound. It is easy enough to unwind a stack later, and is not so easy to wind it again if done too early. For almost all applications, this will not matter, but it technically changes the semantics significantly so should be kept in mind. One important case in which it might matter is when using `#ensure:' blocks _and_ exception handlers. For comparison, this Smalltalk code: | n | n := 42. [[self error: 'error'] ensure: [n := 24]] on: Error do: [:sig | n printNl. sig return]. n printNl. will put "42" followed by "24" on the transcript, because the `n := 24' will not be executed until `sig return' is invoked, unwinding the stack. Similar Java code acts differently: int n = 42; try { try {throw new Exception ("42");} finally {n = 24;} } catch (Exception e) { System.out.println (n); } System.out.println (n); printing "24" twice, because the stack unwinds before executing the catch block.  File: gst.info, Node: Behind the scenes, Next: And now, Prev: Exception handling, Up: Tutorial 6.12 Some nice stuff from the Smalltalk innards =============================================== Just like with everything else, you'd probably end up asking yourself: how's it done? So here's this chapter, just to wheten your appetite... * Menu: * Inside Arrays:: Delving into something old * Two flavors of equality:: Delving into something new * Why is #new there?!?:: Or, the truth on metaclasses * Performance:: Hmm... they told me Smalltalk is slow...  File: gst.info, Node: Inside Arrays, Next: Two flavors of equality, Up: Behind the scenes 6.12.1 How Arrays Work ---------------------- Smalltalk provides a very adequate selection of predefined classes from which to choose. Eventually, however, you will find the need to code a new basic data structure. Because Smalltalk's most fundamental storage allocation facilities are arrays, it is important that you understand how to use them to gain efficient access to this kind of storage. The Array Class. Our examples have already shown the Array class, and its use is fairly obvious. For many applications, it will fill all your needs--when you need an array in a new class, you keep an instance variable, allocate a new Array and assign it to the variable, and then send array accesses via the instance variable. This technique even works for string-like objects, although it is wasteful of storage. An Array object uses a Smalltalk pointer for each slot in the array; its exact size is transparent to the programmer, but you can generally guess that it'll be roughly the word size of your machine. (1) For storing an array of characters, therefore, an Array works but is inefficient. Arrays at a Lower Level. So let's step down to a lower level of data structure. A ByteArray is much like an Array, but each slot holds only an integer from 0 to 255-and each slot uses only a byte of storage. If you only needed to store small quantities in each array slot, this would therefore be a much more efficient choice than an Array. As you might guess, this is the type of array which a String uses. Aha! But when you go back to chapter 9 and look at the Smalltalk hierarchy, you notice that String does not inherit from ByteArray. To see why, we must delve down yet another level, and arrive at the basic methods for setting up the structure of the instances of a class. When we implemented our NiledArray example, we used `'. The shape is exactly that: the fundamental structure of Smalltalk objects created within a given class. Let's consider the differences in the next sub-sections. Nothing The default shape specifies the simplest Smalltalk object. The object consists only of the storage needed to hold the instance variables. In C, this would be a simple structure with zero or more scalar fields.(2). `#pointer' Storage is still allocated for any instance variables, but the objects of the class must be created with a `new:' message. The number passed as an argument to `new:' causes the new object, in addition to the space for instance variables, to also have that many slots of unnamed (indexed) storage allocated. The analog in C would be to have a dynamically allocated structure with some scalar fields, followed at its end by a array of pointers. `#byte' The storage allocated as specified by new: is an array of bytes. The analog in C would be a dynamically allocated structure with scalar fields(3), followed by a array of `char'. `#word' The storage allocated as specified by new: is an array of C unsigned longs, which are represented in Smalltalk by Integer objects. The analog in C would be a dynamically allocated structure with scalar fields, followed by an array of `long'. This kind of subclass is only used in a few places in Smalltalk. `#character' The storage allocated as specified by new: is an array of characters. The analog in C would be a dynamically allocated structure with scalar fields, followed by a array of `char'. There are many more shapes for more specialized usage. All of them specify the same kind of "array-like" behavior, with different data types. How to access this new arrays? You already know how to access instance variables--by name. But there doesn't seem to be a name for this new storage. The way an object accesses it is to send itself array-type messages like `at:', `at:put:', and so forth. The problem is when an object wants to add a new level of interpretation to these messages. Consider a Dictionary--it is a pointer-holding object but its `at:' message is in terms of a key, not an integer index of its storage. Since it has redefined the `at:' message, how does it access its fundamental storage? The answer is that Smalltalk has defined `basicAt:' and `basicAt:put:', which will access the basic storage even when the `at:' and `at:put:' messages have been defined to provide a different abstraction. This can get pretty confusing in the abstract, so let's do an example to show how it's pretty simple in practice. Smalltalk arrays tend to start at 1; let's define an array type whose permissible range is arbitrary. ArrayedCollection subclass: RangedArray [ | offset | RangedArray class >> new: size [ ^self new: size base: 1 ] RangedArray class >> new: size base: b [ ^(super new: size) init: b ] init: b [ offset := (b - 1). "- 1 because basicAt: works with a 1 base" ^self ] rangeCheck: i [ (i <= offset) | (i > (offset + self basicSize)) ifTrue: [ 'Bad index value: ' printOn: stderr. i printOn: stderr. Character nl printOn: stderr. ^self error: 'illegal index' ] ] at: [ self rangeCheck: i. ^self basicAt: i - offset ] at: i put: v [ self rangeCheck: i. ^self basicAt: i - offset put: v ] ] The code has two parts; an initialization, which simply records what index you wish the array to start with, and the at: messages, which adjust the requested index so that the underlying storage receives its 1-based index instead. We've included a range check; its utility will demonstrate itself in a moment: a := RangedArray new: 10 base: 5. a at: 5 put: 0 a at: 4 put: 1 Since 4 is below our base of 5, a range check error occurs. But this check can catch more than just our own misbehavior! a do: [:x| x printNl] Our do: message handling is broken! The stack backtrace pretty much tells the story: RangedArray>>#rangeCheck: RangedArray>>#at: RangedArray>>#do: Our code received a do: message. We didn't define one, so we inherited the existing do: handling. We see that an Integer loop was constructed, that a code block was invoked, and that our own at: code was invoked. When we range checked, we trapped an illegal index. Just by coincidence, this version of our range checking code also dumps the index. We see that do: has assumed that all arrays start at 1. The immediate fix is obvious; we implement our own do: RangedArray extend [ do: aBlock [ 1 to: (self basicSize) do: [:x| aBlock value: (self basicAt: x) ] ] ] But the issues start to run deep. If our parent class believed that it knew enough to assume a starting index of 1(4), why didn't it also assume that it could call basicAt:? The answer is that of the two choices, the designer of the parent class chose the one which was less likely to cause trouble; in fact all standard Smalltalk collections do have indices starting at 1, yet not all of them are implemented so that calling basicAt: would work.(5) Object-oriented methodology says that one object should be entirely opaque to another. But what sort of privacy should there be between a higher class and its subclasses? How many assumption can a subclass make about its superclass, and how many can the superclass make before it begins infringing on the sovereignty of its subclasses? Alas, there are rarely easy answers, and this is just an example. For this particular problem, there is an easy solution. When the storage need not be accessed with peak efficiency, you can use the existing array classes. When every access counts, having the storage be an integral part of your own object allows for the quickest access--but remember that when you move into this area, inheritance and polymorphism become trickier, as each level must coordinate its use of the underlying array with other levels. ---------- Footnotes ---------- (1) For GNU Smalltalk, the size of a C `long', which is usually 32 bits. (2) C requires one or more; zero is allowed in Smalltalk (3) This is not always true for other Smalltalk implementations, who don't allow instance variables in variableByteSubclasses and variableWordSubclasses. (4) Actually, in GNU Smalltalk `do:' is not the only message assuming that. (5) Some of these classes actually redefine `do:' for performance reasons, but they would work even if the parent class' implementation of `do:' was kept.  File: gst.info, Node: Two flavors of equality, Next: Why is #new there?!?, Prev: Inside Arrays, Up: Behind the scenes 6.12.2 Two flavors of equality ------------------------------ As first seen in chapter two, Smalltalk keys its dictionary with things like #word, whereas we generally use 'word'. The former, as it turns out, is from class Symbol. The latter is from class String. What's the real difference between a Symbol and a String? To answer the question, we'll use an analogy from C. In C, if you have a function for comparing strings, you might try to write it: streq(char *p, char *q) { return (p == q); } But clearly this is wrong! The reason is that you can have two copies of a string, each with the same contents but each at its own address. A correct string compare must walk its way through the strings and compare each element. In Smalltalk, exactly the same issue exists, although the details of manipulating storage addresses are hidden. If we have two Smalltalk strings, both with the same contents, we don't necessarily know if they're at the same storage address. In Smalltalk terms, we don't know if they're the same object. The Smalltalk dictionary is searched frequently. To speed the search, it would be nice to not have to compare the characters of each element, but only compare the address itself. To do this, you need to have a guarantee that all strings with the same contents are the same object. The String class, created like: y := 'Hello' does not satisfy this. Each time you execute this line, you may well get a new object. But a very similar class, Symbol, will always return the same object: y := #Hello In general, you can use strings for almost all your tasks. If you ever get into a performance-critical function which looks up strings, you can switch to Symbol. It takes longer to create a Symbol, and the memory for a Symbol is never freed (since the class has to keep tabs on it indefinitely to guarantee it continues to return the same object). You can use it, but use it with care. This tutorial has generally used the strcmp()-ish kind of checks for equality. If you ever need to ask the question "is this the same object?", you use the `==' operator instead of `=': x := y := 'Hello' (x = y) printNl (x == y) printNl y := 'Hel', 'lo' (x = y) printNl (x == y) printNl x := #Hello y := #Hello (x = y) printNl (x == y) printNl Using C terms, `=' compares contents like `strcmp()'. `==' compares storage addresses, like a pointer comparison.  File: gst.info, Node: Why is #new there?!?, Next: Performance, Prev: Two flavors of equality, Up: Behind the scenes 6.12.3 The truth about metaclasses ---------------------------------- Everybody, sooner or later, looks for the implementation of the `#new' method in Object class. To their surprise, they don't find it; if they're really smart, they search for implementors of #new in the image and they find out it is implemented by `Behavior'... which turns out to be a subclass of Object! The truth starts showing to their eyes about that sentence that everybody says but few people understand: "classes are objects". Huh? Classes are objects?!? Let me explain. Open up an image; then type the text following the `st>' prompt. st> Set superclass! HashedCollection st> HashedCollection superclass! Collection st> Collection superclass! Object st> Object superclass! nil Nothing new for now. Let's try something else: st> #(1 2 3) class! Array st> '123' class! String st> Set class! Set class st> Set class class! Metaclass You get it, that strange `Set class' thing is something called "a meta-class"... let's go on: st> ^Set class superclass! Collection class st> ^Collection class superclass! Object class You see, there is a sort of `parallel' hierarchy between classes and metaclasses. When you create a class, Smalltalk creates a metaclass; and just like a class describes how methods for its instances work, a metaclass describes how class methods for that same class work. `Set' is an instance of the metaclass, so when you invoke the `#new' class method, you can also say you are invoking an instance method implemented by `Set class'. Simply put, class methods are a lie: they're simply instance methods that are understood by instances of metaclasses. Now you would expect that `Object class superclass' answers `nil class', that is `UndefinedObject'. Yet you saw that `#new' is not implemented there... let's try it: st> ^Object class superclass! Class Uh?!? Try to read it aloud: the `Object class' class inherits from the `Class' class. `Class' is the abstract superclass of all metaclasses, and provides the logic that allows you to create classes in the image. But it is not the termination point: st> ^Class superclass! ClassDescription st> ^ClassDescription superclass! Behavior st> ^Behavior superclass! Object Class is a subclass of other classes. `ClassDescription' is abstract; `Behavior' is concrete but lacks the methods and state that allow classes to have named instance variables, class comments and more. Its instances are called _light-weight_ classes because they don't have separate metaclasses, instead they all share `Behavior' itself as their metaclass. Evaluating `Behavior superclass' we have worked our way up to class Object again: Object is the superclass of all instances as well as all metaclasses. This complicated system is extremely powerful, and allows you to do very interesting things that you probably did without thinking about it--for example, using methods such as `#error:' or `#shouldNotImplement' in class methods. Now, one final question and one final step: what are metaclasses instances of? The question makes sense: if everything has a class, should not metaclasses have one? Evaluate the following: st> meta := Set class st> 0 to: 4 do: [ :i | st> i timesRepeat: [ Transcript space ] st> meta printNl st> meta := meta class st> ] Set class Metaclass Metaclass class Metaclass Metaclass class 0 If you send `#class' repeatedly, it seems that you end up in a loop made of class `Metaclass'(1) and its own metaclass, `Metaclass class'. It looks like class Metaclass is an instance of an instance of itself. To understand the role of `Metaclass', it can be useful to know that the class creation is implemented there. Think about it. * `Random class' implements creation and initialization of its instances' random number seed; analogously, `Metaclass class' implements creation and initialization of its instances, which are metaclasses. * And `Metaclass' implements creation and initialization of its instances, which are classes (subclasses of `Class'). The circle is closed. In the end, this mechanism implements a clean, elegant and (with some contemplation) understandable facility for self-definition of classes. In other words, it is what allows classes to talk about themselves, posing the foundation for the creation of browsers. ---------- Footnotes ---------- (1) Which turns out to be another subclass of `ClassDescription'.  File: gst.info, Node: Performance, Prev: Why is #new there?!?, Up: Behind the scenes 6.12.4 The truth of Smalltalk performance ----------------------------------------- Everybody says Smalltalk is slow, yet this is not completely true for at least three reasons. First, most of the time in graphical applications is spent waiting for the user to "do something", and most of the time in scripting applications (which GNU Smalltalk is particularly well versed in) is spent in disk I/O; implementing a travelling salesman problem in Smalltalk would indeed be slow, but for most real applications you can indeed exchange performance for Smalltalk's power and development speed. Second, Smalltalk's automatic memory management is faster than C's manual one. Most C programs are sped up if you relink them with one of the garbage collecting systems available for C or C++. Third, even though very few Smalltalk virtual machines are as optimized as, say, the Self environment (which reaches half the speed of optimized C!), they do perform some optimizations on Smalltalk code which make them run many times faster than a naive bytecode interpreter. Peter Deutsch, who among other things invented the idea of a just-in-time compiler like those you are used to seeing for Java(1), once observed that implementing a language like Smalltalk efficiently requires the implementor to cheat... but that's okay as long as you don't get caught. That is, as long as you don't break the language semantics. Let's look at some of these optimizations. For certain frequently used 'special selectors', the compiler emits a send-special-selector bytecode instead of a send-message bytecode. Special selectors have one of three behaviors: * A few selectors are assigned to special bytecode solely in order to save space. This is the case for `#do:' for example. * Three selectors (`#at:', `#at:put:', `#size') are assigned to special bytecodes because they are subject to a special caching optimization. These selectors often result in calling a virtual machine primitive, so GNU Smalltalk remembers which primitve was last called as the result of sending them. If we send `#at:' 100 times for the same class, the last 99 sends are directly mapped to the primitive, skipping the method lookup phase. * For some pairs of receiver classes and special selectors, the interpreter never looks up the method in the class; instead it swiftly executes the same code which is tied to a particular primitive. Of course a special selector whose receiver or argument is not of the right class to make a no-lookup pair is looked up normally. No-lookup methods do contain a primitive number specification, `', but it is used only when the method is reached through a `#perform:...' message send. Since the method is not normally looked up, deleting the primitive name specification cannot in general prevent this primitive from running. No-lookup pairs are listed below: `Integer'/`Integer' for `+ - * = ~= > < >= <=' `Float'/`Integer' `Float'/`Float' `Integer'/`Integer' for `// \\ bitOr: bitShift: bitAnd:' Any pair of objects for `== isNil notNil class' BlockClosure for `value value: blockCopy:'(2) Other messages are open coded by the compiler. That is, there are no message sends for these messages--if the compiler sees blocks without temporaries and with the correct number of arguments at the right places, the compiler unwinds them using jump bytecodes, producing very efficient code. These are: to:by:do: if the second argument is an integer literal to:do: timesRepeat: and:, or: ifTrue:ifFalse:, ifFalse:ifTrue:, ifTrue:, ifFalse: whileTrue:, whileFalse: Other minor optimizations are done. Some are done by a peephole optimizer which is ran on the compiled bytecodes. Or, for example, when GNU Smalltalk pushes a boolean value on the stack, it automatically checks whether the following bytecode is a jump (which is a common pattern resulting from most of the open-coded messages above) and combines the execution of the two bytecodes. All these snippets can be optimized this way: 1 to: 5 do: [ :i | ... ] a < b and: [ ... ] myObject isNil ifTrue: [ ... ] That's all. If you want to know more, look at the virtual machine's source code in `libgst/interp-bc.inl' and at the compiler in `libgst/comp.c'. ---------- Footnotes ---------- (1) And like the one that GNU Smalltalk includes as an experimental feature. (2) You won't ever send this message in Smalltalk programs. The compiler uses it when compiling blocks.  File: gst.info, Node: And now, Next: The syntax, Prev: Behind the scenes, Up: Tutorial 6.13 Some final words ===================== The question is always how far to go in one document. At this point, you know how to create classes. You know how to use inheritance, polymorphism, and the basic storage management mechanisms of Smalltalk. You've also seen a sampling of Smalltalk's powerful classes. The rest of this chapter simply points out areas for further study; perhaps a newer version of this document might cover these in further chapters. Viewing the Smalltalk Source Code Lots of experience can be gained by looking at the source code for system methods; all of them are visible: data structure classes, the innards of the magic that makes classes be themselves objects and have a class, a compiler written in Smalltalk itself, the classes that implement the Smalltalk GUI and those that wrap sockets. Other Ways to Collect Objects We've seen Array, ByteArray, Dictionary, Set, and the various streams. You'll want to look at the Bag, OrderedCollection, and SortedCollection classes. For special purposes, you'll want to examine the CObject and CType hierarchies. Flow of Control GNU Smalltalk has support for non-preemptive multiple threads of execution. The state is embodied in a Process class object; you'll also want to look at the Semaphore and ProcessorScheduler class. Smalltalk Virtual Machine GNU Smalltalk is implemented as a virtual instruction set. By invoking GNU Smalltalk with the `-D' option, you can view the byte opcodes which are generated as files on the command line are loaded. Similarly, running GNU Smalltalk with `-E' will trace the execution of instructions in your methods. You can look at the GNU Smalltalk source to gain more information on the instruction set. With a few modifications, it is based on the set described in the canonical book from two of the original designers of Smalltalk: Smalltalk-80: The Language and its Implementation, by Adele Goldberg and David Robson. Where to get Help The Usenet comp.lang.smalltalk newsgroup is read by many people with a great deal of Smalltalk experience. There are several commercial Smalltalk implementations; you can buy support for these, though it isn't cheap. For the GNU Smalltalk system in particular, you can try the mailing list at: help-smalltalk@gnu.org No guarantees, but the subscribers will surely do their best!  File: gst.info, Node: The syntax, Prev: And now, Up: Tutorial 6.14 A Simple Overview of Smalltalk Syntax ========================================== Smalltalk's power comes from its treatment of objects. In this document, we've mostly avoided the issue of syntax by using strictly parenthesized expressions as needed. When this leads to code which is hard to read due to the density of parentheses, a knowledge of Smalltalk's syntax can let you simplify expressions. In general, if it was hard for you to tell how an expression would parse, it will be hard for the next person, too. The following presentation presents the grammar a couple of related elements at a time. We use an EBNF style of grammar. The form: [ ... ] means that "..." can occur zero or one times. [ ... ]* means zero or more; [ ... ]+ means one or more. ... | ... [ | ... ]* means that one of the variants must be chosen. Characters in double quotes refer to the literal characters. Most elements may be separated by white space; where this is not legal, the elements are presented without white space between them. methods: "!" id ["class"] "methodsFor:" string "!" [method "!"]+ "!" Methods are introduced by first naming a class (the id element), specifying "class" if you're adding class methods instead of instance methods, and sending a string argument to the `methodsFor:' message. Each method is terminated with an "!"; two bangs in a row (with a space in the middle) signify the end of the new methods. method: message [pragma] [temps] exprs message: id | binsel id | [keysel id]+ pragma: "<" keymsg ">" temps: "|" [id]* "|" A method definition starts out with a kind of template. The message to be handled is specified with the message names spelled out and identifiers in the place of arguments. A special kind of definition is the pragma; it has not been covered in this tutorial and it provides a way to mark a method specially as well as the interface to the underlying Smalltalk virtual machine. temps is the declaration of local variables. Finally, exprs (covered soon) is the actual code for implementing the method. unit: id | literal | block | arrayconstructor | "(" expr ")" unaryexpr: unit [ id ]+ primary: unit | unaryexpr These are the "building blocks" of Smalltalk expressions. A unit represents a single Smalltalk value, with the highest syntactic precedence. A unaryexpr is simply a unit which receives a number of unary messages. A unaryexpr has the next highest precedence. A primary is simply a convenient left-hand-side name for one of the above. exprs: [expr "."]* [["^"] expr] expr: [id ":="]* expr2 expr2: primary | msgexpr [ ";" cascade ]* A sequence of expressions is separated by dots and can end with a returned value (`^'). There can be leading assignments; unlike C, assignments apply only to simple variable names. An expression is either a primary (with highest precedence) or a more complex message. cascade does not apply to primary constructions, as they are too simple to require the construct. Since all primary construct are unary, you can just add more unary messages: 1234 printNl printNl printNl msgexpr: unaryexpr | binexpr | keyexpr A complex message is either a unary message (which we have already covered), a binary message (`+', `-', and so forth), or a keyword message (`at:', `new:', ...) Unary has the highest precedence, followed by binary, and keyword messages have the lowest precedence. Examine the two versions of the following messages. The second have had parentheses added to show the default precedence. myvar at: 2 + 3 put: 4 mybool ifTrue: [ ^ 2 / 4 roundup ] (myvar at: (2 + 3) put: (4)) (mybool ifTrue: ([ ^ (2 / (4 roundup)) ])) cascade: id | binmsg | keymsg A cascade is used to direct further messages to the same object which was last used. The three types of messages ( id is how you send a unary message) can thus be sent. binexpr: primary binmsg [ binmsg ]* binmsg: binsel primary binsel: binchar[binchar] A binary message is sent to an object, which primary has identified. Each binary message is a binary selector, constructed from one or two characters, and an argument which is also provided by a primary. 1 + 2 - 3 / 4 which parses as: (((1 + 2) - 3) / 4) keyexpr: keyexpr2 keymsg keyexpr2: binexpr | primary keymsg: [keysel keyw2]+ keysel: id":" Keyword expressions are much like binary expressions, except that the selectors are made up of identifiers with a colon appended. Where the arguments to a binary function can only be from primary, the arguments to a keyword can be binary expressions or primary ones. This is because keywords have the lowest precedence. block: "[" [[":" id]* "|" ] [temps] exprs "]" A code block is square brackets around a collection of Smalltalk expressions. The leading ": id" part is for block arguments. Note that it is possible for a block to have temporary variables of its own. arrayconstructor: "{" exprs "}" Not covered in this tutorial, this syntax allows to create arrays whose values are not literals, but are instead evaluated at run-time. Compare `#(a b)', which results in an Array of two symbols `#a' and `#b', to `{a. b+c}' which results in an Array whose two elements are the contents of variable `a' and the result of summing `c' to `b'. literal: number | string | charconst | symconst | arrayconst | binding | eval arrayconst: "#" array | "#" bytearray bytearray: "[" [number]* "]" array: "(" [literal | array | bytearray | arraysym | ]* ")" number: [[dig]+ "r"] ["-"] [alphanum]+ ["." [alphanum]+] [exp ["-"][dig]+]. string: "'"[char]*"'" charconst: "$"char symconst: "#"symbol | "#"string arraysym: [id | ":"]* exp: "d" | "e" | "q" | "s" We have already shown the use of many of these constants. Although not covered in this tutorial, numbers can have a base specified at their front, and a trailing scientific notation. We have seen examples of character, string, and symbol constants. Array constants are simple enough; they would look like: a := #(1 2 'Hi' $x #Hello 4 16r3F) There are also ByteArray constants, whose elements are constrained to be integers between 0 and 255; they would look like: a := #[1 2 34 16r8F 26r3H 253] Finally, there are three types of floating-point constants with varying precision (the one with the `e' being the less precise, followed by `d' and `q'), and scaled-decimal constants for a special class which does exact computations but truncates comparisons to a given number of decimals. For example, `1.23s4' means "the value `1.23', with four significant decimal digits". binding: "#{" [id "."]* id "}" This syntax has not been used in the tutorial, and results in an Association literal (known as a "variable binding") tied to the class that is named between braces. For example, `#{Class} value' is the same as `Class'. The dot syntax is required for supporting namespaces: `#{Smalltalk.Class}' is the same as `Smalltalk associationAt: #Class', but is resolved at compile-time rather than at run-time. symbol: id | binsel | keysel[keysel]* Symbols are mostly used to represent the names of methods. Thus, they can hold simple identifiers, binary selectors, and keyword selectors: #hello #+ #at:put: eval: "##(" [temps] exprs ")" This syntax also has not been used in the tutorial, and results in evaluating an arbitrarily complex expression at compile-time, and substituting the result: for example `##(Object allInstances size)' is the number of instances of `Object' held in the image _at the time the method is compiled_. id: letter[alphanum]* binchar: "+" | "-" | "*" | "/" | "~" | "|" | "," | "<" | ">" | "=" | "&" | "@" | "?" | "\" | "%" alphanum: dig | letter letter: "A".."Z" dig: "0".."9" These are the categories of characters and how they are combined at the most basic level. binchar simply lists the characters which can be combined to name a binary message. smalltalk-3.2.5/doc/gst.info0000644000175000017500000001271712130455672012662 00000000000000This is gst.info, produced by makeinfo version 4.13 from /home/ich/source/smalltalk/release/smalltalk/doc/gst-fixed.texi. INFO-DIR-SECTION Software development START-INFO-DIR-ENTRY * Smalltalk: (gst). The GNU Smalltalk user's guide. END-INFO-DIR-ENTRY Permission is granted to copy, distribute and/or modify this document under the terms of the GNU Free Documentation License, Version 1.2 or any later version published by the Free Software Foundation; with no Invariant Sections, with no Front-Cover Texts, and with no Back-Cover Texts. A copy of the license is included in the section entitled "GNU Free Documentation License".  Indirect: gst.info-1: 676 gst.info-2: 299266  Tag Table: (Indirect) Node: Top676 Node: Overview5614 Node: Using GNU Smalltalk8333 Node: Invocation8901 Ref: Invocation-Footnote-115443 Ref: Invocation-Footnote-215596 Node: Operation15714 Node: Command-line processing16440 Node: Loading or creating an image17970 Ref: Loading or creating an image-Footnote-120446 Ref: Loading or creating an image-Footnote-220593 Node: Starting the system20761 Ref: Starting the system-Footnote-121524 Node: Syntax21717 Ref: Syntax-Footnote-125662 Node: Test suite26357 Node: Legal concerns26844 Node: GPL27347 Node: LGPL29306 Ref: LGPL-Footnote-131365 Node: Features31448 Node: Extended streams33066 Node: Regular expressions34769 Ref: Regular expressions-Footnote-139554 Node: Namespaces39642 Node: Disk file-IO52602 Node: Object dumping54969 Node: Dynamic loading55569 Node: Documentation56770 Node: Memory access58319 Node: GC60812 Ref: GC-Footnote-172081 Ref: GC-Footnote-272440 Ref: GC-Footnote-372830 Ref: GC-Footnote-473063 Node: Security73118 Node: Special objects73266 Node: Packages78418 Node: GUI88472 Node: Smalltalk-in-Smalltalk89866 Node: Database92203 Node: Locales94281 Ref: Locales-Footnote-1101968 Ref: Locales-Footnote-2102054 Ref: Locales-Footnote-3102122 Node: Seaside102297 Node: Swazoo104088 Node: SUnit105844 Ref: SUnit-Footnote-1113922 Node: Network support114164 Node: XML115514 Node: Other packages116173 Node: Emacs117077 Node: Editing117635 Node: Interactor118601 Node: C and Smalltalk123069 Node: External modules123948 Ref: External modules-Footnote-1129261 Node: C callout129307 Node: C data types140399 Ref: C data types-Footnote-1150175 Node: Smalltalk types150241 Node: Smalltalk callin161115 Node: Smalltalk callbacks170508 Ref: Smalltalk callbacks-Footnote-1172807 Node: Other C functions172884 Ref: Other C functions-Footnote-1182519 Node: Object representation182826 Node: Using Smalltalk189897 Node: Incubator193428 Node: Tutorial198652 Node: Getting started200479 Node: Starting Smalltalk200895 Node: Saying hello201414 Ref: Saying hello-Footnote-1201970 Node: What happened202194 Ref: What happened-Footnote-1203800 Ref: What happened-Footnote-2204099 Node: Doing math204384 Node: Math in Smalltalk206066 Node: Some classes207145 Node: Arrays207849 Ref: Arrays-Footnote-1210263 Ref: Arrays-Footnote-2210648 Node: Sets210751 Node: Dictionaries214587 Node: Closing thoughts216210 Node: The hierarchy217218 Node: Class Object218001 Node: Animals218898 Node: But why221767 Node: Creating classes222784 Node: A new class224731 Node: Documenting the class225659 Node: Defining methods227005 Ref: Defining methods-Footnote-1231247 Node: Instance methods231540 Ref: Instance methods-Footnote-1233475 Node: A look at our object233696 Node: Moving money around235888 Node: Next coming236707 Node: Creating subclasses237154 Node: The Savings class237913 Ref: The Savings class-Footnote-1241578 Ref: The Savings class-Footnote-2241896 Node: The Checking class242156 Node: Writing checks243331 Node: Code blocks (I)245289 Node: Conditions245905 Ref: Conditions-Footnote-1249061 Node: Iteration249282 Ref: Iteration-Footnote-1256759 Node: Code blocks (II)257282 Ref: Code blocks (II)-Footnote-1258137 Node: Integer loops258406 Node: Intervals258964 Node: Invoking code blocks259583 Ref: Invoking code blocks-Footnote-1262514 Node: Debugging262636 Node: Simple errors263574 Node: Nested calls264853 Node: Looking at objects267343 Ref: Looking at objects-Footnote-1268600 Node: More subclassing268685 Node: The existing hierarchy270013 Ref: The existing hierarchy-Footnote-1275661 Node: Playing with Arrays275808 Ref: Playing with Arrays-Footnote-1279869 Node: New kinds of Numbers280412 Ref: New kinds of Numbers-Footnote-1285596 Node: Inheritance and Polymorphism285698 Node: Streams287943 Node: The output stream289061 Ref: The output stream-Footnote-1289972 Node: Your own stream290065 Node: Files293471 Node: Dynamic Strings294114 Node: Exception handling295748 Node: Creating exceptions299266 Node: Raising exceptions300715 Node: Handling exceptions302191 Node: When an exception isn't handled306346 Node: Creating new exception classes307456 Node: Hooking into the stack unwinding308870 Node: Handler stack unwinding caveat310617 Node: Behind the scenes312158 Node: Inside Arrays312763 Ref: Inside Arrays-Footnote-1321570 Ref: Inside Arrays-Footnote-2321647 Ref: Inside Arrays-Footnote-3321708 Ref: Inside Arrays-Footnote-4321866 Ref: Inside Arrays-Footnote-5321946 Node: Two flavors of equality322105 Node: Why is #new there?!?324781 Ref: Why is #new there?!?-Footnote-1329723 Node: Performance329793 Ref: Performance-Footnote-1334413 Ref: Performance-Footnote-2334494 Node: And now334603 Node: The syntax337207  End Tag Table smalltalk-3.2.5/doc/using-xml.texi0000644000175000017500000003205512123404352014012 00000000000000@emph{by Thomas Gagne, edited by Paolo Bonzini} @menu * Building a DOM from XML:: * Building XML:: * Using DTDs:: * XSL Processing:: * Attributions:: @end menu @node Building a DOM from XML @section Building a DOM from XML If you're like me, the first thing you may be trying to do is build a Document Object Model (DOM) tree from some kind of XML input. Assuming you've got the XML in a String the following code will build an XML Document: @example XML.SAXParser defaultParserClass processDocumentString: theXMLString beforeScanDo: [ :p | p validate: false]. @end example Though the code above appears as though it should be easy to use, there's some hidden features you should know about. First, @code{theXMLString} can not contain any null bytes. Depending on where your XML comes from it may have a NULL byte at the end (like mine did). Many languages implement strings as an array of bytes (usually printable ones) ending with a null (a character with integer value 0). In my case, the XML was coming from a remote client written in C using middleware to send the message to my server. Since the middleware doesn't assume to know anything about the message it received, it's received into a String, null-byte and all. To remove it I used: @example XML.SAXParser defaultParserClass processDocumentString: (aString copyWithout: 0 asCharacter) beforeScanDo: [ :p | p validate: false]. @end example Starting out, I didn't know much about the value of DTDs either (Document Type Definitions), so I wasn't using them (more on why you should later). What you need to know is XML comes in two flavors, (three if you include broken as a flavor) @emph{well-formed} and @emph{valid}. @emph{Well-formed XML} is simply XML following the basic rules, like only one top-level (the document's root), no overlapping tags, and a few other contraints. Valid XML means not only is the XML well-formed, but it's also compliant with some kind of rule base about which elements are allowed to follow which other ones, whether or not attributes are permitted and what their values and defaults should be, etc. There's no way to get around well-formedness. Most XML tools complain vociferously about missing or open tags. What you may not have lying around, though, is a DTD describing how the XML should be assembled. If you need to skip validation for any reason you must include the selector: @example beforeScanDo: [ :p | p validate: false]. @end example Now that you have your XML document, you probably want to access its contents (why else would you want one, right?). Let's take the following (brief) XML as an example: @example 01/04/2000 widget 1.0000 doodad 2.0000 @end example The first thing you probably want to know is how to access the different tags, and more specifically, how to access the contents of those tags. First, by way of providing a roadmap to the elements I'll show you the Smalltalk code for getting different pieces of the document, assuming the variable you've assigned the document to is named @emph{doc}. I'll also create instance variables for the various elements as I go along: @multitable @columnfractions .5 .5 @item @emph{Element you want} @tab @emph{Code to get it} @item porder element @tab @code{doc root} @item porder_head @tab @code{doc root elementNamed: 'porder_head'} @item order_date (as a String) @tab @code{(porderHead elementNamed: 'order_date') characterData} @item order_date (as a Date) @tab @code{(Date readFrom: (porderHead elementNamed: 'order_date') characterData readStream)} @item a collection with both porder_lines @tab @code{doc root elementsNamed: 'porder_line'} @end multitable I've deliberately left-out accessing @code{porder}'s attribute because accessing them is different from accessing other nodes. You can get an OrderedCollection of attributes using: @example attributes := doc root attributes. @end example @noindent but the ordered collection isn't really useful. To access any single attribute you'd need to look for it in the collection: @example porderNum := (attributes detect: [ :each | each key type = 'porder_num' ]) value. @end example But that's not a whole lot of fun, especially if there's a lot you need to get, and if there's any possibility the attribute may not exist. Then you have to do the whole @code{detect:ifNone:} thing, and boy, does that make the code readable! What I did instead was create a method in my objects' abstract: @example dictionaryForAttributes: aCollection ^Dictionary withAll: (aCollection collect: [ :each | each key type -> each value ]) @end example Now what you have is an incrementally more useful method for getting attributes: @example attributes := self dictionaryForAttributes: doc root attributes. porderNum := attributes at: 'porder_num'. @end example At first this appears like more code, and for a single attribute it probably is. But if an element includes more than one attribute the payoff is fairly decent. Of course, you still need to handle the absence of an attribute in the dictionary but I think it reads a little better using a Dictionary than an OrderedCollection: @example porderNum := attributes at: 'porder_num' ifAbsent: []. @end example @node Building XML @section Building XML There's little reason to build an XML document if its not going to be processed by something down the road. Most XML tools require XML documents have a document root. A root is a tag inside which all other tags exist, or put another way, a single parent node from which all other nodes descend. In my case, a co-worker was attempting to use Sablot's sabcmd to transform the XML from my server into HTML. So start your document with the root ready to go: @example replyDoc := XML.Document new. replyDoc addNode: (XML.Element tag: 'response'). @end example Before doing anything more complex, we can play with our new XML document. Assuming you're going to want to send the XML text to someone or write it to a file, you may first want to capture it in a string. Even if you don't want to first capture it into a string our example is going to: @example replyStream := String new writeStream. replyDoc printOn: replyStream. @end example If we examine'd the contents of our replyStream (@code{replyStream contents}) we'd see: @example @end example Which is what an empty tag looks like. Let's add some text to our XML document now. Let's say we want it to look like: @example Hello, world! @end example Building this actually requires two nodes be added to a new XML document. The first node (or element) is named @code{response}. The second node adds text to the first: @example replyDoc := XML.Document new. replyDoc addNode: (XML.Element tag: response). "our root node" replyDoc root addNode: (XML.Text text: 'Hello, world!'). @end example Another way of writing it, and the way I've adopted in my code is to create the whole node before adding it. This is not just to reduce the appearance of assignments, but it suggests a template for cascading @code{#addNode:} messages to an element, which, if you're building any kind of nontrivial XML, you'll be doing a lot of: @example replyDoc := XML.Document new. replyDoc addNode: ( (XML.Element tag: response) addNode: (XML.Text text: 'Hello, world!') ). @end example Unless you're absolutely sure you'll never accidentally add text nodes that have an ampersand (&) in them, you'll need to escape it to get past XML parsers. The way I got around this was to escape them whenever I added text nodes. To make it easier, I (again) created a method in my objects' abstract superclass: @example asXMLElement: tag value: aValue | n | n := XML.Element tag: tag. aValue isNil ifFalse: [ n addNode: (XML.Text text: (aValue displayString copyReplaceAll: '&' with: '&'))]. ^n @end example Calls to @code{self asXMLElement: 'sometagname' value: anInstanceVariable} are littered throughout my code. Adding attributes to documents is, thankfully, easier than accessing them. If we wanted to add an attribute to our document above we can do so with a single statement: @example replyDoc root addAttribute: (XML.Attribute name: 'isExample' value: 'yes'). @end example Now, our XML looks like: @example Hello, world! @end example @node Using DTDs @section Using DTDs What I didn't appreciate in my first XML project (this one) was how much error checking I was doing just to verify the format of incoming XML. During testing I'd go looking for attributes or elements that @emph{should} have been there but for various reasons were not. Because I was coding fast and furious I overlooked some and ignored others. Testing quickly ferreted out my carelessnes and my application started throwing exceptions faster than election officials throw chads. The cure, at least for formatting, is having a DTD, or Document Type Definition describing the XML format. You can read more about the syntax of DTDs in the XML specification. There's not a lot programmers are able to do with DTDs in VisualWorks, except requiring incoming XML to include DOCTYPE statements. There is something programmers need to do to handle the exceptions the XML parser throws when it finds errors. I'm not an expert at writing Smalltalk exception handling code, and I haven't decided on what those exceptions should look like to the client who sent the poorly formatted XML in the first place. The code below does a decent job of catching the errors and putting the description of the error into an XML response. It's also a fairly decent example of XML document building as discussed earlier. @example replyDoc := XML.Document new. replyDoc addNode: (XML.Element tag: 'response'). [ doc := XML.SAXParser defaultParserClass processDocumentString: (anIsdMessage message copyWithout: 0) asString ] on: Exception do: [ :ex | replyDoc root addAttribute: (XML.Attribute name: 'type' value: 'Exception'); addNode: ((XML.Element tag: 'description') addNode: (XML.Text text: ex signal description)); addNode: ((XML.Element tag: 'message') addNode: (XML.Text text: ex messageText)) ]. @end example I said before there's not a lot programmers can do with DTDs, but there are some things I wish the XML library would do: @itemize @bullet @item I'd like to make sure the documents I build are built correctly. It would be great if a DTD could be attached to an empty XML document so that exceptions could be thrown as misplaced elements were added. @item It would be great to specify which DTD the XML parser should use when parsing incoming XML so that the incoming XML wouldn't always have to include a tag. Though it's fairly easy to add the tag at the start of XML text, it's really not that simple. You need to know the XML's root element before adding the tag but you really don't know that until after you've parsed the XML You would have to parse the XML, determine the root tag, then parse the output of the first into a new XML document with validation turned-on. @item Another reason to be able to create a DTD document to use with subsequent parsing is to avoid the overhead of parsing the same DTD over and over again. In transaction processing systems this kind of redundant task could be eliminated and the spare CPU cycles put to better use. @end itemize @node XSL Processing @section XSL Processing I spent a night the other week trying to figure out how to get the XSL libraries to do anything. I no longer need it now, but I did discover some things others with an immediate need may want to be aware of. @itemize @bullet @item Transforming an XML document requires you parse the XSL and XML documents separately first. After that, you tell the XSL.RuleDatabase to process the XML document. The result is another XML document with the transformations. A code snippet for doing just that appears below. @example | rules xmlDoc htmlDoc | rules := XSL.RuleDatabase new readFileNamed: 'paymentspending.xsl'. xmlDoc := XML.SAXParser defaultParserClass processDocumentInFilename: 'paymentspending.xml' beforeScanDo: [ :p | p validate: false ]. htmlDoc := rules process: xmlDoc. @end example There is also a @code{readString:} method which can be used instead of @code{readFileNamed:}. @item The XSL library doesn't use the W3-approved stylesheet, but instead uses the draft version (same one Microsoft uses). @code{} @item The functions @code{position()} and @code{count()} aren't implemented, or if they are, aren't implemented in the way other XSL tools implement it. @end itemize @node Attributions @section Attributions Cincom, for supporting Smalltalk and the Smalltalk community by making the library available for GNU Smalltalk under the LGPL. Thanks also to Randy Ynchausti, Bijan Parsia, Reinout Heeck, and Joseph Bacanskas for answering many questions on the XML library. smalltalk-3.2.5/doc/gst.info-10000644000175000017500000111040212130455672013007 00000000000000This is gst.info, produced by makeinfo version 4.13 from /home/ich/source/smalltalk/release/smalltalk/doc/gst-fixed.texi. INFO-DIR-SECTION Software development START-INFO-DIR-ENTRY * Smalltalk: (gst). The GNU Smalltalk user's guide. END-INFO-DIR-ENTRY Permission is granted to copy, distribute and/or modify this document under the terms of the GNU Free Documentation License, Version 1.2 or any later version published by the Free Software Foundation; with no Invariant Sections, with no Front-Cover Texts, and with no Back-Cover Texts. A copy of the license is included in the section entitled "GNU Free Documentation License".  File: gst.info, Node: Top, Up: (DIR) GNU Smalltalk User's Guide ************************** GNU Smalltalk User's Guide This document describes installing and operating the GNU Smalltalk programming environment. Permission is granted to copy, distribute and/or modify this document under the terms of the GNU Free Documentation License, Version 1.2 or any later version published by the Free Software Foundation; with no Invariant Sections, with no Front-Cover Texts, and with no Back-Cover Texts. A copy of the license is included in the section entitled "GNU Free Documentation License". * Menu: * Overview:: What GNU Smalltalk is. * Using GNU Smalltalk:: Running GNU Smalltalk. * Features:: A description of GNU Smalltalk's special features. * Packages:: An easy way to install Smalltalk code into an image. * Emacs:: GNU Smalltalk and Emacs. * C and Smalltalk:: GNU Smalltalk's C/Smalltalk interoperability features. * Tutorial:: An introduction to Smalltalk and OOP. --- The detailed node listing --- Using GNU Smalltalk: * Invocation:: What you can specify on the command line. * Operation:: A step-by-step description of the startup process and a short description of how to interact with GNU Smalltalk. * Syntax:: A description of the input file syntax * Test suite:: How to run the test suite system. * Legal concerns:: Licensing of GNU Smalltalk Operation: * Command-line processing:: Picking an image path and a kernel path. * Loading or creating an image:: Loading an image or creating a new one. * Starting the system:: After the image is created or restored. Legal concerns: * GPL:: Complying with the GNU GPL. * LGPL:: Complying with the GNU LGPL. Features: * Extended streams:: Extensions to streams, and generators * Regular expressions:: String matching extensions * Namespaces:: Avoiding clashes between class names. * Disk file-IO:: Methods for reading and writing disk files. * Object dumping:: Methods that read and write objects in binary format. * Dynamic loading:: Picking external libraries and modules at run-time. * Documentation:: Automatic documentation generation. * Memory access:: The direct memory accessing classes and methods, plus broadcasts from the virtual machine. * GC:: The GNU Smalltalk memory manager. * Security:: Sandboxing and access control. * Special objects:: Methods to assign particular properties to objects. Packages * GTK and VisualGST: GUI. * Parser, STInST, Compiler: Smalltalk-in-Smalltalk. * DBI: Database. * I18N: Locales. * Seaside: Seaside. * Swazoo: Swazoo. * SUnit: SUnit. * Sockets, WebServer, NetClients: Network support. * XML, XPath, XSL: XML. * Other packages: Other packages. Emacs * Editing:: Autoindent and more for GNU Smalltalk. * Interactor:: Smalltalk interactor mode. C and Smalltalk: * External modules:: Linking your libraries to the virtual machine * C callout:: Calls from Smalltalk to C * C data types:: Manipulating C data from Smalltalk * Smalltalk types:: Manipulating Smalltalk data from C * Smalltalk callin:: Calls from C to Smalltalk * Object representation:: Manipulating your own Smalltalk objects * Incubator:: Protecting newly created objects from garbage collections * Other C functions:: Handling and creating OOPs * Using Smalltalk:: The Smalltalk environment as an extension library Tutorial: * Getting started:: Starting to explore GNU Smalltalk * Some classes:: Using some of the Smalltalk classes * The hierarchy:: The Smalltalk class hierarchy * Creating classes:: Creating a new class of objects * Creating subclasses:: Adding subclasses to another class * Code blocks (I):: Control structures in Smalltalk * Code blocks (II):: Guess what? More control structures * Debugging:: Things go bad in Smalltalk too! * More subclassing:: Coexisting in the class hierarchy * Streams:: Something really powerful * Exception handling:: More sophisticated error handling * Behind the scenes:: Some nice stuff from the Smalltalk innards * And now:: Some final words * The syntax:: For the most die-hard computer scientists  File: gst.info, Node: Overview, Next: Using GNU Smalltalk, Prev: Top, Up: Top Introduction ************ GNU Smalltalk is an implementation that closely follows the Smalltalk-80 language as described in the book `Smalltalk-80: the Language and its Implementation' by Adele Goldberg and David Robson, which will hereinafter be referred to as `the Blue Book'. The Smalltalk programming language is an object oriented programming language. This means, for one thing, that when programming you are thinking of not only the data that an object contains, but also of the operations available on that object. The object's data representation capabilities and the operations available on the object are "inseparable"; the set of things that you can do with an object is defined precisely by the set of operations, which Smalltalk calls "methods", that are available for that object: each object belongs to a "class" (a datatype and the set of functions that operate on it) or, better, it is an "instance" of that class. You cannot even examine the contents of an object from the outside--to an outsider, the object is a black box that has some state and some operations available, but that's all you know: when you want to perform an operation on an object, you can only send it a "message", and the object picks up the method that corresponds to that message. In the Smalltalk language, everything is an object. This includes not only numbers and all data structures, but even classes, methods, pieces of code within a method ("blocks" or "closures"), stack frames ("contexts"), etc. Even `if' and `while' structures are implemented as methods sent to particular objects. Unlike other Smalltalks (including Smalltalk-80), GNU Smalltalk emphasizes Smalltalk's rapid prototyping features rather than the graphical and easy-to-use nature of the programming environment (did you know that the first GUIs ever ran under Smalltalk?). The availability of a large body of system classes, once you master them, makes it pretty easy to write complex programs which are usually a task for the so called "scripting languages". Therefore, even though we have a GUI environment based on GTK (*note GTK and VisualGST: GUI.), the goal of the GNU Smalltalk project is currently to produce a complete system to be used to write your scripts in a clear, aesthetically pleasing, and philosophically appealing programming language. An example of what can be obtained with Smalltalk in this novel way can be found in *note Class reference: (gst-libs)Top. That part of the manual is entirely generated by a Smalltalk program, starting from the source code for the class libraries distributed together with the system.  File: gst.info, Node: Using GNU Smalltalk, Next: Features, Prev: Overview, Up: Top 1 Using GNU Smalltalk ********************* * Menu: * Invocation:: What you can specify on the command line. * Operation:: A step-by-step description of the startup process and a short description of how to interact with GNU Smalltalk. * Syntax:: A description of the input file syntax * Test suite:: How to run the test suite system. * Legal concerns:: Licensing of GNU Smalltalk  File: gst.info, Node: Invocation, Next: Operation, Up: Using GNU Smalltalk 1.1 Command line arguments ========================== The GNU Smalltalk virtual machine may be invoked via the following command: gst [ flags ... ] [ file ... ] When you invoke GNU Smalltalk, it will ensure that the binary image file (called `gst.im') is up to date; if not, it will build a new one as described in *note Loading an image or creating a new one: Loading or creating an image. Your first invocation should look something like this: "Global garbage collection... done" GNU Smalltalk ready st> If you specify one or more FILEs, they will be read and executed in order, and Smalltalk will exit when end of file is reached. If you don't specify FILE, GNU Smalltalk reads standard input, issuing a `st>' prompt if the standard input is a terminal. You may specify `-' for the name of a file to invoke an explicit read from standard input. To exit while at the `st>' prompt, use `Ctrl-d', or type `ObjectMemory quit' followed by . Use `ObjectMemory snapshot' first to save a new image that you can reload later, if you wish. As is standard for GNU-style options, specifying `--' stops the interpretation of options so that every argument that follows is considered a file name even if it begins with a `-'. You can specify both short and long flags; for example, `--version' is exactly the same as `-v', but is easier to remember. Short flags may be specified one at a time, or in a group. A short flag or a group of short flags always starts off with a single dash to indicate that what follows is a flag or set of flags instead of a file name; a long flag starts off with two consecutive dashes, without spaces between them. In the current implementation the flags can be intermixed with file names, but their effect is as if they were all specified first. The various flags are interpreted as follows: `-a' `--smalltalk-args' Treat all options afterward as arguments to be given to Smalltalk code retrievable with `Smalltalk arguments', ignoring them as arguments to GNU Smalltalk itself. Examples: command line Options seen by GNU Smalltalk `Smalltalk arguments' (empty) (none) `#()' `-Via foo bar' `-Vi' `#('foo' 'bar')' `-Vai test' `-Vi' `#('test')' `-Vaq' `-Vq' `#()' `--verbose -aq -c ' `--verbose -q' `#('-c')' `-c' `--core-dump' When a fatal signal occurs, produce a core dump before terminating. Without this option, only a backtrace is provided. `-D' `--declaration-trace' Print the class name, the method name, and the byte codes that the compiler generates as it compiles methods. Only applies to files that are named explicitly on the command line, unless the flag is given multiple times on the command line. `-E' `--execution-trace' Print the byte codes being executed as the interpreter operates. Only works for statements explicitly issued by the user (either interactively or from files given on the command line), unless the flag is given multiple times on the command line. `--kernel-directory' Specify the directory from which the kernel source files will be loaded. This is used mostly while compiling GNU Smalltalk itself. Smalltalk code can retrieve this information with `Directory kernel'. `--no-user-files' Don't load any files from `~/.st/' (*note Loading an image or creating a new one: Loading or creating an image.).(1) This is used mostly while compiling GNU Smalltalk itself, to ensure that the installed image is built only from files in the source tree. `-K FILE' `--kernel-file FILE' Load FILE in the usual way, but look for it relative to the kernel directory's parent directory, which is usually `/usr/local/share/smalltalk/'. See `--kernel-dir' above. `-f' `--file' The following two command lines are equivalent: gst -f FILE `args...' gst -q FILE -a `args...' This is meant to be used in the so called "sharp-bang" sequence at the beginning of a file, as in #! /usr/bin/gst -f ... Smalltalk source code ... GNU Smalltalk treats the first line as a comment, and the `-f' option ensures that the arguments are passed properly to the script. Use this instead to avoid hard-coding the path to `gst':(2) #! /bin/sh "exec" "gst" "-f" "$0" "$@" ... Smalltalk source code ... `-g' `--no-gc-messages' Suppress garbage collection messages. `-h' `--help' Print out a brief summary of the command line syntax of GNU Smalltalk, including the definitions of all of the option flags, and then exit. `-i' `--rebuild-image' Always build and save a new image file; see *note Loading an image or creating a new one: Loading or creating an image. `--maybe-rebuild-image' Perform the image checks and rebuild as described in *note Loading an image or creating a new one: Loading or creating an image. This is the default when `-I' is not given. `-I FILE' `--image-file FILE' Use the image file named FILE as the image file to load instead of the default location, and set FILE's directory part as the image path. This option completely bypasses checking the file dates on the kernel files; use `--maybe-rebuild-image' to restore the usual behavior, writing the newly built image to FILE if needed. `-q' `--quiet' `--silent' Suppress the printing of answered values from top-level expressions while GNU Smalltalk runs. `-r' `--regression-test' This is used by the regression testing system and is probably not of interest to the general user. It controls printing of certain information. `-S' `--snapshot' Save the image after loading files from the command line. Of course this "snapshot" is not saved if you include - (stdin) on the command line and exit by typing `Ctrl-c'. `-v' `--version' Print out the GNU Smalltalk version number, then exit. `-V' `--verbose' Print various diagnostic messages while executing (the name of each file as it's loaded, plus messages about the beginning of execution or how many byte codes were executed). ---------- Footnotes ---------- (1) The directory would be called `_st/' under MS-DOS. Under OSes that don't use home directories, it would be looked for in the current directory. (2) The words in the shell command `exec' are all quoted, so GNU Smalltalk parses them as five separate comments.  File: gst.info, Node: Operation, Next: Syntax, Prev: Invocation, Up: Using GNU Smalltalk 1.2 Startup sequence ==================== *Caveat*: _The startup sequence is pretty complicated. If you are not interested in its customization, you can skip the first two sections below. These two sections also don't apply when using the command-line option `-I', unless also using `--maybe-rebuild-image'._ You can abort GNU Smalltalk at any time during this procedure with `Ctrl-c'. * Menu: * Command-line processing:: Picking an image path and a kernel path. * Loading or creating an image:: Loading an image or creating a new one. * Starting the system:: After the image is created or restored.  File: gst.info, Node: Command-line processing, Next: Loading or creating an image, Up: Operation 1.2.1 Picking an image path and a kernel path --------------------------------------------- When GNU Smalltalk is invoked, it first chooses two paths, the "image path" and the "kernel path". The image path is set by considering these paths in succession: * the directory part of the `--image-file' option if it is given; * the value of the `SMALLTALK_IMAGE' environment variable if it is defined and readable; this step will disappear in a future release; * the path compiled in the binary (usually, under Unix systems, `/usr/local/var/lib/smalltalk' or a similar path under `/var') if it exists and it is readable; * the current directory. The current directory is also used if the image has to be rebuilt but you cannot write to a directory chosen according to the previous criteria. The "kernel path" is the directory in which to look for Smalltalk code compiled into the base image. The possibilities in this case are: * the argument to the `--kernel-dir' option if it is given; * the value of the `SMALLTALK_KERNEL' environment variable if it is defined and readable; this step will disappear in a future release; * the path compiled in the binary (usually, under Unix systems, `/usr/local/share/smalltalk/kernel' or a similar data file path) if it exists and it is readable; * a subdirectory named `kernel' of the image path.  File: gst.info, Node: Loading or creating an image, Next: Starting the system, Prev: Command-line processing, Up: Operation 1.2.2 Loading an image or creating a new one -------------------------------------------- GNU Smalltalk can load images created on any system with the same pointer size as its host system by approximately the same version of GNU Smalltalk, even if they have different endianness. For example, images created on 32-bit PowerPC can be loaded with a 32-bit x86 `gst' VM, provided that the GNU Smalltalk versions are similar enough. Such images are called "compatible images". It cannot load images created on systems with different pointer sizes; for example, our x86 `gst' cannot load an image created on x86-64. Unless the `-i' flag is used, GNU Smalltalk first tries to load the file named by `--image-file', defaulting to `gst.im' in the image path. If this is found, GNU Smalltalk ensures the image is "not stale", meaning its write date is newer than the write dates of all of the kernel method definition files. It also ensures that the image is "compatible", as described above. If both tests pass, GNU Smalltalk loads the image and continues with *note After the image is created or restored: Starting the system. If that fails, a new image has to be created. The image path may now be changed to the current directory if the previous choice is not writeable. To build an image, GNU Smalltalk loads the set of files that make up the kernel, one at a time. The list can be found in `libgst/lib.c', in the `standard_files' variable. You can override kernel files by placing your own copies in `~/.st/kernel/'.(1) For example, if you create a file `~/.st/kernel/Builtins.st', it will be loaded instead of the `Builtins.st' in the kernel path. To aid with image customization and local bug fixes, GNU Smalltalk loads two more files (if present) before saving the image. The first is `site-pre.st', found in the parent directory of the kernel directory. Unless users at a site change the kernel directory when running `gst', `/usr/local/share/smalltalk/site-pre.st' provides a convenient place for site-wide customization. The second is `~/.st/pre.st', which can be different for each user's home directory.(2). Before the next steps, GNU Smalltalk takes a snapshot of the new memory image, saving it over the old image file if it can, or in the current directory otherwise. ---------- Footnotes ---------- (1) The directory is called `_st/kernel' under MS-DOS. Under OSes that don't use home directories, it is looked for in the current directory. (2) The file is looked up as `_st/pre.st' under MS-DOS and again, under OSes that don't use home directories it is looked for as `pre.st' in the current directory.  File: gst.info, Node: Starting the system, Prev: Loading or creating an image, Up: Operation 1.2.3 After the image is created or restored -------------------------------------------- Next, GNU Smalltalk sends the `returnFromSnapshot' event to the dependents of the special class `ObjectMemory' (*note Memory access::). Afterwards, it loads `~/.st/init.st' if available.(1) You can remember the difference between `pre.st' and `init.st' by remembering that `pre.st' is the _pre_-snapshot file and `init.st' is the post-image-load _init_ialization file. Finally, GNU Smalltalk loads files listed on the command line, or prompts for input at the terminal, as described in *note Command line arguments: Invocation. ---------- Footnotes ---------- (1) The same considerations made above hold here too. The file is called `_st/init.st' under MS-DOS, and is looked for in the current directory under OSes that don't use home directories.  File: gst.info, Node: Syntax, Next: Test suite, Prev: Operation, Up: Using GNU Smalltalk 1.3 Syntax of GNU Smalltalk =========================== The language that GNU Smalltalk accepts is basically the same that other Smalltalk environment accept and the same syntax used in the "Blue Book", also known as `Smalltalk-80: The Language and Its Implementation'. The return operator, which is represented in the Blue Book as an up-arrow, is mapped to the ASCII caret symbol `^'; the assignment operator (left-arrow) is usually represented as `:='(1). Actually, the grammar of GNU Smalltalk is slightly different from the grammar of other Smalltalk environments in order to simplify interaction with the system in a command-line environment as well as in full-screen editors. Statements are executed one by one; multiple statements are separated by a period. At end-of-line, if a valid statement is complete, a period is implicit. For example, 8r300. 16rFFFF prints out the decimal value of octal `300' and hex `FFFF', each followed by a newline. Multiple statements share the same local variables, which are automatically declared. To delete the local variables, terminate a statement with `!' rather than `.' or newline. Here, a := 42 a! a the first two `a's are printed as `42', but the third one is uninitialized and thus printed as `nil'. In order to evaluate multiple statements in a single block, wrap them into an "eval block" as follows: Eval [ a := 42. a printString ] This won't print the intermediate result (the integer 42), only the final result (the string `'42''). ObjectMemory quit exits from the system. You can also type a `C-d' to exit from Smalltalk if it's reading statements from standard input. GNU Smalltalk provides three extensions to the language that make it simpler to write complete programs in an editor. However, it is also compatible with the "file out" syntax as shown in the "Green Book" (also known as `Smalltalk-80: Bits of History, Words of Advice' by Glenn Krasner). A new class is created using this syntax: SUPERCLASS-NAME subclass: NEW-CLASS-NAME [ | INSTANCE VARIABLES | PRAGMAS MESSAGE-PATTERN-1 [ STATEMENTS ] MESSAGE-PATTERN-2 [ STATEMENTS ] ... CLASS-VARIABLE-1 := EXPRESSION. CLASS-VARIABLE-2 := EXPRESSION. ... ] In short: * Instance variables are defined with the same syntax as method temporary variables. * Unlike other Smalltalks, method statements are inside brackets. * Class variables are defined the same as variable assignments. * Pragmas define class comment, class category, imported namespaces, and the shape of indexed instance variables. A similar syntax is used to define new methods in an existing class. CLASS-EXPRESSION extend [ ... ] The CLASS-EXPRESSION is an expression that evaluates to a class object, which is typically just the name of a class, although it can be the name of a class followed by the word `class', which causes the method definitions that follow to apply to the named class itself, rather than to its instances. Number extend [ radiusToArea [ ^self squared * Float pi ] radiusToCircumference [ ^self * 2 * Float pi ] ] A complete treatment of the Smalltalk syntax and of the class library can be found in the included tutorial and class reference (*note Class Reference: (gst-base)Top.). More information on the implementation of the language can be found in the `Blue Book'; the relevant parts are available, scanned, at `http://stephane.ducasse.free.fr/FreeBooks/BlueBook/Bluebook.pdf'. ---------- Footnotes ---------- (1) It also bears mentioning that there are two assignment operators: `_' and `:='. Both are usable interchangeably, provided that they are surrounded by spaces. The GNU Smalltalk kernel code uses the `:=' form exclusively, but `_' is supported a) for compatibility with previous versions of GNU Smalltalk b) because this is the correct mapping between the assignment operator mentioned in the Blue Book and the current ASCII definition. In the ancient days (like the middle 70's), the ASCII underscore character was also printed as a back-arrow, and many terminals would display it that way, thus its current usage. Anyway, using `_' may lead to portability problems.  File: gst.info, Node: Test suite, Next: Legal concerns, Prev: Syntax, Up: Using GNU Smalltalk 1.4 Running the test suite ========================== GNU Smalltalk comes with a set of files that provides a simple regression test suite. To run the test suite, you should be connected to the top-level Smalltalk directory. Type make check You should see the names of the test suite files as they are processed, but that's it. Any other output indicates some problem.  File: gst.info, Node: Legal concerns, Prev: Test suite, Up: Using GNU Smalltalk 1.5 Licensing of GNU Smalltalk ============================== Different parts of GNU Smalltalk comes under two licenses: the virtual machine and the development environment (compiler and browser) come under the GNU General Public License, while the system class libraries come under the Lesser General Public License. * Menu: * GPL:: Complying with the GNU GPL. * LGPL:: Complying with the GNU LGPL.  File: gst.info, Node: GPL, Next: LGPL, Up: Legal concerns 1.5.1 Complying with the GNU GPL -------------------------------- The GPL licensing of the virtual machine means that all derivatives of the virtual machine must be put under the same license. In other words, it is strictly forbidden to distribute programs that include the GNU Smalltalk virtual machine under a license that is not the GPL. This also includes any bindings to external libraries. For example, the bindings to Gtk+ are released under the GPL. In principle, the GPL would not extend to Smalltalk programs, since these are merely input data for the virtual machine. On the other hand, using bindings that are under the GPL via dynamic linking would constitute combining two parts (the Smalltalk program and the bindings) into one program. Therefore, we added a special exception to the GPL in order to avoid gray areas that could adversely hit both the project and its users: In addition, as a special exception, the Free Software Foundation give you permission to combine GNU Smalltalk with free software programs or libraries that are released under the GNU LGPL and with independent programs running under the GNU Smalltalk virtual machine. You may copy and distribute such a system following the terms of the GNU GPL for GNU Smalltalk and the licenses of the other code concerned, provided that you include the source code of that other code when and as the GNU GPL requires distribution of source code. Note that people who make modified versions of GNU Smalltalk are not obligated to grant this special exception for their modified versions; it is their choice whether to do so. The GNU General Public License gives permission to release a modified version without this exception; this exception also makes it possible to release a modified version which carries forward this exception.  File: gst.info, Node: LGPL, Prev: GPL, Up: Legal concerns 1.5.2 Complying with the GNU LGPL --------------------------------- Smalltalk programs that run under GNU Smalltalk are linked with the system classes in GNU Smalltalk class library. Therefore, they must respect the terms of the Lesser General Public License(1). The interpretation of this license for architectures different from that of the C language is often difficult; the accepted one for Smalltalk is as follows. The image file can be considered as an object file, falling under Subsection 6a of the license, as long as it allows a user to load an image, upgrade the library or otherwise apply modifications to it, and save a modified image: this is most conveniently obtained by allowing the user to use the read-eval-print loop that is embedded in the GNU Smalltalk virtual machine. In other words, provided that you leave access to the loop in a documented way, or that you provide a way to file in arbitrary files in an image and save the result to a new image, you are obeying Subsection 6a of the Lesser General Public License, which is reported here: a) Accompany the work with the complete corresponding machine-readable source code for the Library including whatever changes were used in the work (which must be distributed under Sections 1 and 2 above); and, if the work is an executable linked with the Library, with the complete machine-readable "work that uses the Library", as object code and/or source code, so that the user can modify the Library and then relink to produce a modified executable containing the modified Library. (It is understood that the user who changes the contents of definitions files in the Library will not necessarily be able to recompile the application to use the modified definitions.) In the future, alternative mechanisms similar to shared libraries may be provided, so that it is possible to comply with the GNU LGPL in other ways. ---------- Footnotes ---------- (1) Of course, they may be more constrained by usage of GPL class libraries.  File: gst.info, Node: Features, Next: Packages, Prev: Using GNU Smalltalk, Up: Top 2 Features of GNU Smalltalk *************************** In this section, the features which are specific to GNU Smalltalk are described. These features include support for calling C functions from within Smalltalk, accessing environment variables, and controlling various aspects of compilation and execution monitoring. Note that, in general, GNU Smalltalk is much more powerful than the original Smalltalk-80, as it contains a lot of methods that are common in today's Smalltalk implementation and are present in the ANSI Standard for Smalltalk, but were absent in the Blue Book. Examples include Collection's `allSatisfy:' and `anySatisfy:' methods and many methods in SystemDictionary (the Smalltalk dictionary's class). * Menu: * Extended streams:: Extensions to streams, and generators * Regular expressions:: String matching extensions * Namespaces:: Avoiding clashes between class names. * Disk file-IO:: Methods for reading and writing disk files. * Object dumping:: Methods that read and write objects in binary format. * Dynamic loading:: Picking external libraries and modules at run-time. * Documentation:: Automatic documentation generation. * Memory access:: The direct memory accessing classes and methods, plus broadcasts from the virtual machine. * GC:: The GNU Smalltalk memory manager. * Security:: Sandboxing and access control. * Special objects:: Methods to assign particular properties to objects.  File: gst.info, Node: Extended streams, Next: Regular expressions, Up: Features 2.1 Extended streams ==================== The basic image in GNU Smalltalk includes powerful extensions to the _Stream_ hierarchy found in ANSI Smalltalk (and Smalltalk-80). In particular: * Read streams support all the iteration protocols available for collections. In some cases (like `fold:', `detect:', `inject:into:') these are completely identical. For messages that return a new stream, such as `select:' and `collect:', the blocks are evaluated lazily, as elements are requested from the stream using `next'. * Read streams can be concatenated using `,' like SequenceableCollections. * "Generators" are supported as a quick way to create a Stream. A generator is a kind of pluggable stream, in that a user-supplied blocks defines which values are in a stream. For example, here is an empty generator and two infinite generators: "Returns an empty stream" Generator on: [ :gen | ] "Return an infinite stream of 1's" Generator on: [ :gen | [ gen yield: 1 ] repeat ] "Return an infinite stream of integers counting up from 1" Generator inject: 1 into: [ :value | value + 1 ] The block is put "on hold" and starts executing as soon as `#next' or `#atEnd' are sent to the generator. When the block sends `#yield:' to the generator, it is again put on hold and the argument becomes the next object in the stream. Generators use "continuations", but they shield the users from their complexity by presenting the same simple interface as streams.  File: gst.info, Node: Regular expressions, Next: Namespaces, Prev: Extended streams, Up: Features 2.2 Regular expression matching =============================== _Regular expressions_, or "regexes", are a sophisticated way to efficiently match patterns of text. If you are unfamiliar with regular expressions in general, see *note Syntax of Regular Expressions: (emacs)Regexps, for a guide for those who have never used regular expressions. GNU Smalltalk supports regular expressions in the core image with methods on `String'. The GNU Smalltalk regular expression library is derived from GNU libc, with modifications made originally for Ruby to support Perl-like syntax. It will always use its included library, and never the ones installed on your system; this may change in the future in backwards-compatible ways. Regular expressions are currently 8-bit clean, meaning they can work with any ordinary String, but do not support full Unicode, even when package `I18N' is loaded. Broadly speaking, these regexes support Perl 5 syntax; register groups `()' and repetition `{}' must not be given with backslashes, and their counterpart literal characters should. For example, `\{{1,3}' matches `{', `{{', `{{{'; correspondingly, `(a)(\()' matches `a(', with `a' and `(' as the first and second register groups respectively. GNU Smalltalk also supports the regex modifiers `imsx', as in Perl. You can't put regex modifiers like `im' after Smalltalk strings to specify them, because they aren't part of Smalltalk syntax. Instead, use the inline modifier syntax. For example, `(?is:abc.)' is equivalent to `[Aa][Bb][Cc](?:.|\n)'. In most cases, you should specify regular expressions as ordinary strings. GNU Smalltalk always caches compiled regexes, and uses a special high-efficiency caching when looking up literal strings (i.e. most regexes), to hide the compiled `Regex' objects from most code. For special cases where this caching is not good enough, simply send `#asRegex' to a string to retrieved a compiled form, which works in all places in the public API where you would specify a regex string. You should always rely on the cache until you have demonstrated that using Regex objects makes a noticeable performance difference in your code. Smalltalk strings only have one escape, the `'' given by `''', so backslashes used in regular expression strings will be understood as backslashes, and a literal backslash can be given directly with `\\'(1). The methods on the compiled Regex object are private to this interface. As a public interface, GNU Smalltalk provides methods on String, in the category `regex'. There are several methods for matching, replacing, pattern expansion, iterating over matches, and other useful things. The fundamental operator is `#searchRegex:', usually written as `#=~', reminiscent of Perl syntax. This method will always return a `RegexResults', which you can query for whether the regex matched, the location Interval and contents of the match and any register groups as a collection, and other features. For example, here is a simple configuration file line parser: | file config | config := LookupTable new. file := (File name: 'myapp.conf') readStream. file linesDo: [:line | (line =~ '(\w+)\s*=\s*((?: ?\w+)+)') ifMatched: [:match | config at: (match at: 1) put: (match at: 2)]]. file close. config printNl. As with Perl, `=~' will scan the entire string and answer the leftmost match if any is to be found, consuming as many characters as possible from that position. You can anchor the search with variant messages like `#matchRegex:', or of course `^' and `$' with their usual semantics if you prefer. You shouldn't modify the string while you want a particular RegexResults object matched on it to remain valid, because changes to the matched text may propagate to the RegexResults object. Analogously to the Perl `s' operator, GNU Smalltalk provides `#replacingRegex:with:'. Unlike Perl, GNU Smalltalk employs the pattern expansion syntax of the `#%' message here. For example, `'The ratio is 16/9.' replacingRegex: '(\d+)/(\d+)' with: '$%1\over%2$'' answers `'The ratio is $16\over9$.''. In place of the `g' modifier, use the `#replacingAllRegex:with:' message instead. One other interesting String message is `#onOccurrencesOfRegex:do:', which invokes its second argument, a block, on every successful match found in the receiver. Internally, every search will start at the end of the previous successful match. For example, this will print all the words in a stream: stream contents onOccurrencesOfRegex: '\w+' do: [:each | each match printNl] ---------- Footnotes ---------- (1) Whereas it must be given as `\\\\' in a literal Emacs Lisp string, for example.  File: gst.info, Node: Namespaces, Next: Disk file-IO, Prev: Regular expressions, Up: Features 2.3 Namespaces ============== [This section (and the implementation of namespaces in GNU Smalltalk) is based on the paper `Structured Symbolic Name Spaces in Smalltalk', by Augustin Mrazik.] 2.3.1 Introduction ------------------ The Smalltalk-80 programming environment, upon which GNU Smalltalk is historically based, supports symbolic identification of objects in one global namespace--in the `Smalltalk' system dictionary. This means that each global variable in the system has its unique name which is used for symbolic identification of the particular object in the source code (e.g. in expressions or methods). The most important of these global variables are classes defining the behavior of objects. In development dealing with modelling of real systems, "polymorphic symbolic identification" is often needed. By this, we mean that it should be possible to use the same name for different classes or other global variables. Selection of the proper variable binding should be context-specific. By way of illustration, let us consider class `Statement' as an example which would mean totally different things in different domains: GNU Smalltalk or other programming language An expression in the top level of a code body, possibly with special syntax available such as assignment or branching. Bank A customer's trace report of recent transactions. AI, logical derivation An assertion of a truth within a logical system. This issue becomes inevitable if we start to work persistently, using `ObjectMemory snapshot' to save after each session for later resumption. For example, you might have the class `Statement' already in your image with the "Bank" meaning above (e.g. in the live bank support systems we all run in our images) and you might decide to start developing YAC [Yet Another C]. Upon starting to write parse nodes for the compiler, you would find that `#Statement' is boundk in the banking package. You could replace it with your parse node class, and the bank's `Statement' could remain in the system as an unbound class with full functionality; however, it could not be accessed anymore at the symbolic level in the source code. Whether this would be a problem or not would depend on whether any of the bank's code refers to the class `Statement', and when these references occur. Objects which have to be identified in source code by their names are included in `Smalltalk', the sole instance of `SystemDictionary'. Such objects may be identified simply by writing their names as you would any variable names. The code is compiled in the default environment, and if the variable is found in `Smalltalk', without being shadowed by a class pool or local variables, its value is retrieved and used as the value of the expression. In this way `Smalltalk' represents the sole symbolic namespace. In the following text the symbolic namespace, as a concept, will be called simply "environment" to make the text more clear. 2.3.2 Concepts -------------- To support polymorphic symbolical identification several environments will be needed. The same name may exist concurrently in several environments as a key, pointing to diverse objects in each. Symbolic navigation between these environments is needed. Before approaching the problem of the syntax and semantics to be implemented, we have to decide on structural relations to be established between environments. Since the environment must first be symbolically identified to direct access to its global variables, it must first itself be a global variable in another environment. `Smalltalk' is a great choice for the root environment, from which selection of other environments and their variables begins. From `Smalltalk' some of the existing sub-environments may be seen; from these other sub-environments may be seen, etc. This means that environments represent nodes in a graph where symbolic selections from one environment to another one represent branches. The symbolic identification should be unambiguous, although it will be polymorphic. This is why we should avoid cycles in the environment graph. Cycles in the graph could cause also other problems in the implementation, e.g. inability to use trivially recursive algorithms. Thus, in general, the environments must build a directed acyclic graph; GNU Smalltalk currently limits this to an n-ary tree, with the extra feature that environments can be used as pool dictionaries. Let us call the partial ordering relation which occurs between environments "inheritance". Sub-environments inherit from their super-environments. The feature of inheritance in the meaning of object-orientation is associated with this relation: all associations of the super-environment are valid also in its sub-environments, unless they are locally redefined in the sub-environment. A super-environment includes all its sub-enviroments as `Association's under their names. The sub-environment includes its super-environment under the symbol `#Super'. Most environments inherit from `Smalltalk', the standard root environment, but they are not required to do so; this is similar to how most classes derive from `Object', yet one can derive a class directly from `nil'. Since they all inherit `Smalltalk''s global variables, it is not necessary to define `Smalltalk' as pointing to `Smalltalk''s `Smalltalk' in each environment. The inheritance links to the super-environments are used in the lookup for a potentially inherited global variable. This includes lookups by a compiler searching for a variable binding and lookups via methods such as `#at:' and `#includesKey:'. 2.3.3 Syntax ------------ Global objects of an environment, be they local or inherited, may be referenced by their symbol variable names used in the source code, e.g. John goHome if the `#John -> aMan' association exists in the particular environment or one of its super-environments, all along the way to the root environment. If an object must be referenced from another environment (i.e. which is not one of its sub-environments) it has to be referenced either _relatively_ to the position of the current environment, using the `Super' symbol, or _absolutely_, using the "full pathname" of the object, navigating from the tree root (usually `Smalltalk') through the tree of sub-environments. For the identification of global objects in another environment, we use a "pathname" of symbols. The symbols are separated by periods; the "look" to appear is that of Smalltalk.Tasks.MyTask and of Super.Super.Peter. As is custom in Smalltalk, we are reminded by capitalization that we are accessing global objects. Another syntax returns the "variable binding", the `Association' for a particular global. The first example above is equivalently: #{Smalltalk.Tasks.MyTask} value The latter syntax, a "variable binding", is also valid inside literal arrays. 2.3.4 Implementation -------------------- A superclass of `SystemDictionary' called `RootNamespace' is defined, and many of the features of the Smalltalk-80 `SystemDictionary' will be hosted by that class. `Namespace' and `RootNamespace' are in turn subclasses of `AbstractNamespace'. To handle inheritance, the following methods have to be defined or redefined in Namespace (_not_ in RootNamespace): Accessors like `#at:ifAbsent:' and `#includesKey:' Inheritance must be implemented. When `Namespace', trying to read a variable, finds an association in its own dictionary or a super-environment dictionary, it uses that; for `Dictionary''s writes and when a new association must be created, `Namespace' creates it in its own dictionary. There are special methods like `#set:to:' for cases in which you want to modify a binding in a super-environment if that is the relevant variable's binding. Enumerators like `#do:' and `#keys' This should return *all* the objects in the namespace, including those which are inherited. Hierarchy access `AbstractNamespace' will also implement a new set of methods that allow one to navigate through the namespace hierarchy; these parallel those found in `Behavior' for the class hierarchy. The most important task of the `Namespace' class is to provide organization for the most important global objects in the Smalltalk system--for the classes. This importance becomes even more crucial in a structure of multiple environments intended to change the semantics of code compiled for those classes. In Smalltalk the classes have the instance variable `name' which holds the name of the class. Each "defined class" is included in `Smalltalk', or another environment, under this name. In a framework with several environments the class should know the environment in which it has been created and compiled. This is a new property of `Class' which must be defined and properly used in relevant methods. In the mother environment the class shall be included under its name. Any class, as with any other object, may be included concurrently in several environments, even under different symbols in the same or in diverse environments. We can consider these "alias names" of the particular class or other value. A class may be referenced under the other names or in other environments than its mother environment, e.g. for the purpose of instance creation or messages to the class, but it should not compile code in these environments, even if this compilation is requested from another environment. If the syntax is not correct in the mother environment, a compilation error occurs. This follows from the existence of class "mother environments", as a class is responsible for compiling its own methods. An important issue is also the name of the class answered by the class for the purpose of its identification in diverse tools (e.g. in a browser). This must be changed to reflect the environment in which it is shown, i.e. the method `nameIn: environment' must be implemented and used in proper places. Other changes must be made to the Smalltalk system to achieve the full functionality of structured environments. In particular, changes have to be made to the behavior classes, the user interface, the compiler, and a few classes supporting persistance. One small detail of note is that evaluation in the REPL or `Workspace', implemented by compiling methods on `UndefinedObject', make more sense if `UndefinedObject''s environment is the "current environment" as reachable by `Namespace current', even though its mother environment by any other sensibility is `Smalltalk'. 2.3.5 Using namespaces ---------------------- Using namespaces is often merely a matter of adding a `namespace' option to the GNU Smalltalk XML package description used by `PackageLoader', or wrapping your code like this: Namespace current: NewNS [ ... ] Namespaces can be imported into classes like this: Stream subclass: EncodedStream [ ] Alternatively, paths to classes (and other objects) in the namespaces will have to be specified completely. Importing a namespace into a class is similar to C++'s `using namespace' declaration within the class proper's definition. Finally, be careful when working with fundamental system classes. Although you can use code like Namespace current: NewNS [ Smalltalk.Set subclass: Set [ ... ] ] this approach won't work when applied to core classes. For example, you might be successful with a `Set' or `WriteStream' object, but subclassing `SmallInteger' this way can bite you in strange ways: integer literals will still belong to the `Smalltalk' dictionary's version of the class (this holds for `Array's, `String's, etc. too), primitive operations will still answer standard Smalltalk `SmallIntegers', and so on. Similarly, word-shaped will recognize 32-bit `Smalltalk.LargeInteger' objects, but not `LargeInteger's belonging to your own namespace. Unfortunately, this problem is not easy to solve since Smalltalk has to know the OOPs of determinate class objects for speed--it would not be feasible to lookup the environment to which sender of a message belongs every time the `+' message was sent to an Integer. So, GNU Smalltalk namespaces cannot yet solve 100% of the problem of clashes between extensions to a class--for that you'll still have to rely on prefixes to method names. But they _do_ solve the problem of clashes between class names, or between class names and pool dictionary names. Namespaces are unrelated from packages; loading a package does not import the corresponding namespace.  File: gst.info, Node: Disk file-IO, Next: Object dumping, Prev: Namespaces, Up: Features 2.4 Disk file-IO primitive messages =================================== Four classes (`FileDescriptor', `FileStream', `File', `Directory') allow you to create files and access the file system in a fully object-oriented way. `FileDescriptor' and `FileStream' are much more powerful than the corresponding C language facilities (the difference between the two is that, like the C `stdio' library, `FileStream' does buffering). For one thing, they allow you to write raw binary data in a portable endian-neutral format. But, more importantly, these classes transparently implement virtual filesystems and asynchronous I/O. Asynchronous I/O means that an input/output operation blocks the Smalltalk Process that is doing it, but not the others, which makes them very useful in the context of network programming. Virtual file systems mean that these objects can transparently extract files from archives such as `tar' and `gzip' files, through a mechanism that can be extended through either shell scripting or Smalltalk programming. For more information on these classes, look in the class reference, under the `VFS' namespace. URLs may be used as file names; though, unless you have loaded the `NetClients' package (*note Network support::), only `file' URLs will be accepted. In addition, the three files, `stdin', `stdout', and `stderr' are declared as global instances of `FileStream' that are bound to the proper values as passed to the C virtual machine. They can be accessed as either `stdout' and `FileStream stdout'--the former is easier to type, but the latter can be clearer. Finally, `Object' defines four other methods: `print' and `printNl', `store' and `storeNl'. These do a `printOn:' or `storeOn:' to the "Transcript" object; this object, which is the sole instance of class `TextCollector', normally delegates write operations to `stdout'. If you load the VisualGST GUI, instead, the Transcript Window will be attached to the Transcript object (*note GTK and VisualGST: GUI.). The `fileIn:' message sent to the FileStream class, with a file name as a string argument, will cause that file to be loaded into Smalltalk. For example, FileStream fileIn: 'foo.st' ! will cause `foo.st' to be loaded into GNU Smalltalk.  File: gst.info, Node: Object dumping, Next: Dynamic loading, Prev: Disk file-IO, Up: Features 2.5 The GNU Smalltalk ObjectDumper ================================== Another GNU Smalltalk-specific class, the `ObjectDumper' class, allows you to dump objects in a portable, endian-neutral, binary format. Note that you can use the `ObjectDumper' on ByteArrays too, thanks to another GNU Smalltalk-specific class, `ByteStream', which allows you to treat ByteArrays the same way you would treat disk files. For more information on the usage of the `ObjectDumper', look in the class reference.  File: gst.info, Node: Dynamic loading, Next: Documentation, Prev: Object dumping, Up: Features 2.6 Dynamic loading =================== The `DLD' class enhances the C callout mechanism to automatically look for unresolved functions in a series of program-specified libraries. To add a library to the list, evaluate code like the following: DLD addLibrary: 'libc' The extension (`.so', `.sl', `.a', `.dll' depending on your operating system) will be added automatically. You are advised not to specify it for portability reasons. You will then be able to use the standard C call-out mechanisms to define all the functions in the C run-time library. Note that this is a potential security problem (especially if your program is SUID root under Unix), so you might want to disable dynamic loading when using GNU Smalltalk as an extension language. To disable dynamic loading, configure GNU Smalltalk passing the `--disable-dld' switch. Note that a `DLD' class will be present even if dynamic loading is disabled (either because your system is not supported, or by the `--disable-dld' configure switch) but any attempt to perform dynamic linking will result in an error.  File: gst.info, Node: Documentation, Next: Memory access, Prev: Dynamic loading, Up: Features 2.7 Automatic documentation generator ===================================== GNU Smalltalk includes an automatic documentation generator invoked via the `gst-doc' command. The code is actually part of the `ClassPublisher' package, and `gst-doc' takes care of reading the code to be documented and firing a `ClassPublisher'. Currently, `gst-doc' can only generate output in Texinfo format, though this will change in future releases. `gst-doc' can document code that is already in the image, or it can load external files and packages. Note that the latter approach will not work for files and packages that programmatically create code or file in other files/packages. `gst-doc' is invoked as follows: gst-doc [ FLAG ... ] CLASS ... The following options are supported: `-p PACKAGE' `--package=PACKAGE' Produce documentation for the classes inside the PACKAGE package. `-f FILE' `--file=FILE' Produce documentation for the classes inside the FILE file. `-I' `--image-file' Produce documentation for the code that is already in the given image. `-o' `--output=FILE' Emit documentation in the named file. CLASS is either a class name, or a namespace name followed by `.*'. Documentation will be written for classes that are specified in the command line. CLASS can be omitted if a `-f' or `-p' option is given. In this case, documentation will be written for all the classes in the package.  File: gst.info, Node: Memory access, Next: GC, Prev: Documentation, Up: Features 2.8 Memory accessing methods ============================ GNU Smalltalk provides methods to query its own internal data structures. You may determine the real memory address of an object or the real memory address of the OOP table that points to a given object, by using messages to the `Memory' class, described below. -- Method on Object: asOop Returns the index of the OOP for anObject. This index is immume from garbage collection and is the same value used by default as an hash value for anObject (it is returned by Object's implementation of `hash' and `identityHash'). -- Method on Integer: asObject Converts the given OOP _index_ (not address) back to an object. Fails if no object is associated to the given index. -- Method on Integer: asObjectNoFail Converts the given OOP _index_ (not address) back to an object. Returns nil if no object is associated to the given index. Other methods in ByteArray and Memory allow to read various C types (`doubleAt:', `ucharAt:', etc.). These are mostly obsoleted by `CObject' which, in newer versions of GNU Smalltalk, supports manually managed heap-backed memory as well as garbage collected ByteArray-backed memory. Another interesting class is ObjectMemory. This provides a few methods that enable one to tune the virtual machine's usage of memory; many methods that in the past were instance methods of Smalltalk or class methods of Memory are now class methods of ObjectMemory. In addition, and that's what the rest of this section is about, the virtual machines signals events to its dependents exactly through this class. The events that can be received are "returnFromSnapshot" This is sent every time an image is restarted, and substitutes the concept of an "init block" that was present in previous versions. "aboutToQuit" This is sent just before the interpreter is exiting, either because `ObjectMemory quit' was sent or because the specified files were all filed in. Exiting from within this event might cause an infinite loop, so be careful. "aboutToSnapshot" This is sent just before an image file is created. Exiting from within this event will leave any preexisting image untouched. "finishedSnapshot" This is sent just after an image file is created. Exiting from within this event will not make the image unusable.  File: gst.info, Node: GC, Next: Security, Prev: Memory access, Up: Features 2.9 Memory management in GNU Smalltalk ====================================== The GNU Smalltalk virtual machine is equipped with a garbage collector, a facility that reclaims the space occupied by objects that are no longer accessible from the system roots. The collector is composed of several parts, each of which can be invoked by the virtual machine using various tunable strategies, or invoked manually by the programmer. These parts include a "generation scavenger", a "mark & sweep" collectory with an incremental sweep phase, and a "compactor". All these facilities work on different memory spaces and differs from the other in its scope, speed and disadvantages (which are hopefully balanced by the availability of different algorithms). What follows is a description of these algorithms and of the memory spaces they work in. "NewSpace" is the memory space where young objects live. It is composed of three sub-spaces: an object-creation space ("Eden") and two "SurvivorSpaces". When an object is first created, it is placed in Eden. When Eden starts to fill up (i.e., when the number of used bytes in Eden exceeds the scavenge threshold), objects that are housed in Eden or in the occupied SurvivorSpace and that are still reachable from the system roots are copied to the unoccupied SurvivorSpace. As an object survives different scavenging passes, it will be shuffled by the scavenger from the occupied SurvivorSpace to the unoccupied one. When the number of used bytes in SurvivorSpace is high enough that the scavenge pause might be excessively long, the scavenger will move some of the older surviving objects from NewSpace to "OldSpace". In the garbage collection jargon, we say that such objects are being "tenured" to OldSpace. This garbage collection algorithm is designed to reclaim short-lived objects, that is those objects that expire while residing in NewSpace, and to decide when enough data is residing in NewSpace that it is useful to move some of it in OldSpace. A "copying" garbage collector is particularly efficient in an object population whose members are more likely to die than survive, because this kind of scavenger spends most of its time copying survivors, who will be few in number in such populations, rather than tracing corpses, who will be many in number. This fact makes copying collection especially well suited to NewSpace, where a percentage of 90% or more objects often fails to survive across a single scavenge. The particular structure of NewSpace has many advantages. On one hand, having a large Eden and two small SurvivorSpaces has a smaller memory footprint than having two equally big semi-spaces and allocating new objects directly from the occupied one (by default, GNU Smalltalk uses 420=300+60*2 kilobytes of memory, while a simpler configuration would use 720=360*2 kilobytes). On the other hand, it makes tenuring decisions particularly simple: the copying order is such that short-lived objects tend to be copied last, while objects that are being referred from OldSpace tend to be copied first: this is because the tenuring strategy of the scavenger is simply to treat the destination SurvivorSpace as a circular buffer, tenuring objects with a First-In-First-Out policy. An object might become part of the scavenger root set for several reasons: objects that have been tenured are roots if their data lives in an OldSpace page that has been written to since the last scavenge (more on this later), plus all objects can be roots if they are known to be referenced from C code or from the Smalltalk stacks. In turn, some of the old objects can be made to live in a special area, called "FixedSpace". Objects that reside in FixedSpace are special in that their body is guaranteed to remain at a fixed address (in general, GNU Smalltalk only ensures that the header of the object remains at a fixed address in the Object Table). Because the garbage collector can and does move objects, passing objects to foreign code which uses the object's address as a fixed key, or which uses a ByteArray as a buffer, presents difficulties. One can use `CObject' to manipulate C data on the `malloc' heap, which indeed does not move, but this can be tedious and requires the same attentions to avoid memory leaks as coding in C. FixedSpace provides a much more convenient mechanism: once an object is deemed fixed, the object's body will never move through-out its life-time; the space it occupies will however still be returned automatically to the FixedSpace pool when the object is garbage collected. Note that because objects in FixedSpace cannot move, FixedSpace cannot be compacted and can therefore suffer from extensive fragmentation. For this reason, FixedSpace should be used carefully. FixedSpace however is rebuilt (of course) every time an image is brought up, so a kind of compaction of FixedSpace can be achieved by saving a snapshot, quitting, and then restarting the newly saved image. Memory for OldSpace and FixedSpace is allocated using a variation of the system allocator `malloc': in fact, GNU Smalltalk uses the same allocator for its own internal needs, for OldSpace and for FixedSpace, but it ensures that a given memory page never hosts objects that reside in separate spaces. New pages are mapped into the address space as needed and devoted to OldSpace or FixedSpace segments; similarly, when unused they may be subsequently unmapped, or they might be left in place waiting to be reused by `malloc' or by another Smalltalk data space. Garbage that is created among old objects is taken care of by a mark & sweep collector which, unlike the scavenger which only reclaims objects in NewSpace, can only reclaim objects in OldSpace. Note that as objects are allocated, they will not only use the space that was previously occupied in the Eden by objects that have survived, but they will also reuse the entries in the global Object Table that have been freed by object that the scavenger could reclaim. This quest for free object table entries can be combined with the sweep phase of the OldSpace collector, which can then be done incrementally, limiting the disruptive part of OldSpace garbage collection to the mark phase. Several runs of the mark & sweep collector can lead to fragmentation (where objects are allocated from several pages, and then become garbage in an order such that a bunch of objects remain in each page and the system is not able to recycle them). For this reason, the system periodically tries to compact OldSpace. It does so simply by looping through every old object and copying it into a new OldSpace. Since the OldSpace allocator does not suffer from fragmentation until objects start to be freed nor after all objects are freed, at the end of the copy all the pages in the fragmented OldSpace will have been returned to the system (some of them might already have been used by the compacted OldSpace), and the new, compacted OldSpace is ready to be used as the system OldSpace. Growing the object heap (which is done when it is found to be quite full even after a mark & sweep collection) automatically triggers a compaction. You can run the compactor without marking live objects. Since the amount of garbage in OldSpace is usually quite limited, the overhead incurred by copying potentially dead objects is small enough that the compactor still runs considerably faster than a full garbage collection, and can still give the application some breathing room. Keeping OldSpace and FixedSpace in the same heap would then make compaction of OldSpace (whereby it is rebuilt from time to time in order to limit fragmentation) much less effective. Also, the `malloc' heap is not used for FixedSpace objects because GNU Smalltalk needs to track writes to OldSpace and FixedSpace in order to support efficient scavenging of young objects. To do so, the grey page table(1) contains one entry for each page in OldSpace or FixedSpace that is thought to contain at least a reference to an object housed in NewSpace. Every page in OldSpace is created as grey, and is considered grey until a scavenging pass finds out that it actually does not contain pointers to NewSpace. Then the page is recolored black(2), and will stay black until it is written to or another object is allocated in it (either a new fixed object, or a young object being tenured). The grey page table is expanded and shrunk as needed by the virtual machine. Drawing an histogram of object sizes shows that there are only a few sources of large objects on average (i.e., objects greater than a page in size), but that enough of these objects are created dynamically that they must be handled specially. Such objects should not be allocated in NewSpace along with ordinary objects, since they would fill up NewSpace prematurely (or might not even fit in it), thus accelerating the scavenging rate, reducing performance and resulting in an increase in tenured garbage. Even though this is not an optimal solution because it effectively tenures these objects at the time they are created, a benefit can be obtained by allocating these objects directly in FixedSpace. The reason why FixedSpace is used is that these objects are big enough that they don't result in fragmentation(3); and using FixedSpace instead of OldSpace avoids that the compactor copies them because this would not provide any benefit in terms of reduced fragmentation. Smalltalk activation records are allocated from another special heap, the context pool. This is because it is often the case that they can be deallocated in a Last-In-First-Out (stack) fashion, thereby saving the work needed to allocate entries in the object table for them, and quickly reusing the memory that they use. When the activation record is accessed by Smalltalk, however, the activation record must be turned into a first-class `OOP'(4). Since even these objects are usually very short-lived, the data is however not copied to the Eden: the eviction of the object bodies from the context pool is delayed to the next scavenging, which will also empty the context pool just like it empties Eden. If few objects are allocated and the context pool turns full before the Eden, a scavenging is also triggered; this is however quite rare. Optionally, GNU Smalltalk can avoid the overhead of interpretation by executing a given Smalltalk method only after that method has been compiled into the underlying microprocessor's machine code. This machine-code generation is performed automatically, and the resulting machine code is then placed in `malloc'-managed memory. Once executed, a method's machine code is left there for subsequent execution. However, since it would require way too much memory to permanently house the machine-code version of every Smalltalk method, methods might be compiled more than once: when a translation is not used at the time that two garbage collection actions are taken (scavenges and global garbage collections count equally), the incremental sweeper discards it, so that it will be recomputed if and when necessary. ---------- Footnotes ---------- (1) The denomination "grey" comes from the lexicon of "tri-color marking", which is an abstraction of every possible garbage collection algorithm: in tri-color marking, grey objects are those that are known to be reachable or that we are not interested in reclaiming, yet have not been scanned to mark the objects that they refer to as reachable. (2) Black objects are those that are known to be reachable or that we are not interested in reclaiming, and are known to have references only to other black or grey objects (in case you're curious, the tri-color marking algorithm goes on like this: object not yet known to be reachable are white, and when all objects are either black or white, the white ones are garbage). (3) Remember that free pages are shared among the three heaps, that is, OldSpace, FixedSpace and the `malloc' heap. When a large object is freed, the memory that it used can be reused by `malloc' or by OldSpace allocation (4) This is short for "Ordinary Object Pointer".  File: gst.info, Node: Security, Next: Special objects, Prev: GC, Up: Features 2.10 Security in GNU Smalltalk ==============================  File: gst.info, Node: Special objects, Prev: Security, Up: Features 2.11 Special kinds of objects ============================= A few methods in Object support the creation of particular objects. This include: * finalizable objects * weak and ephemeron objects (i.e. objects whose contents are considered specially, during the heap scanning phase of garbage collection). * read-only objects (like literals found in methods) * fixed objects (guaranteed not to move across garbage collections) They are: -- Method on Object: makeWeak Marks the object so that it is considered weak in subsequent garbage collection passes. The garbage collector will consider dead an object which has references only inside weak objects, and will replace references to such an "almost-dead" object with nils, and then send the `mourn' message to the object. -- Method on Object: makeEphemeron Marks the object so that it is considered specially in subsequent garbage collection passes. Ephemeron objects are sent the message `mourn' when the first instance variable is not referenced or is referenced _only through another instance variable in the ephemeron_. Ephemerons provide a very versatile base on which complex interactions with the garbage collector can be programmed (for example, finalization which is described below is implemented with ephemerons). -- Method on Object: addToBeFinalized Marks the object so that, as soon as it becomes unreferenced, its `finalize' method is called. Before `finalize' is called, the VM implicitly removes the objects from the list of finalizable ones. If necessary, the `finalize' method can mark again the object as finalizable, but by default finalization will only occur once. Note that a finalizable object is kept in memory even when it has no references, because tricky finalizers might "resuscitate" the object; automatic marking of the object as not to be finalized has the nice side effect that the VM can simply delay the releasing of the memory associated to the object, instead of being forced to waste memory even after finalization happens. An object must be explicitly marked as to be finalized _every time the image is loaded_; that is, finalizability is not preserved by an image save. This was done because in most cases finalization is used together with operating system resources that would be stale when the image is loaded again. For `CObject's, in particular, freeing them would cause a segmentation violation. -- Method on Object: removeToBeFinalized Removes the to-be-finalized mark from the object. As I noted above, the finalize code for the object does not have to do this explicitly. -- Method on Object: finalize This method is called by the VM when there are no more references to the object (or, of course, if it only has references inside weak objects). -- Method on Object: isReadOnly This method answers whether the VM will refuse to make changes to the objects when methods like `become:', `basicAt:put:', and possibly `at:put:' too (depending on the implementation of the method). Note that GNU Smalltalk won't try to intercept assignments to fixed instance variables, nor assignments via `instVarAt:put:'. Many objects (Characters, `nil', `true', `false', method literals) are read-only by default. -- Method on Object: makeReadOnly: aBoolean Changes the read-only or read-write status of the receiver to that indicated by `aBoolean'. -- Method on Object: basicNewInFixedSpace Same as `#basicNew', but the object won't move across garbage collections. -- Method on Object: basicNewInFixedSpace: Same as `#basicNew:', but the object won't move across garbage collections. -- Method on Object: makeFixed Ensure that the receiver won't move across garbage collections. This can be used either if you decide after its creation that an object must be fixed, or if a class does not support using `#new' or `#new:' to create an object Note that, although particular applications will indeed have a need for fixed, read-only or finalizable objects, the `#makeWeak' primitive is seldom needed and weak objects are normally used only indirectly, through the so called "weak collections". These are easier to use because they provide additional functionality (for example, `WeakArray' is able to determine whether an item has been garbage collected, and `WeakSet' implements hash table functionality); they are: * `WeakArray' * `WeakSet' * `WeakKeyDictionary' * `WeakValueLookupTable' * `WeakIdentitySet' * `WeakKeyIdentityDictionary' * `WeakValueIdentityDictionary' Versions of GNU Smalltalk preceding 2.1 included a `WeakKeyLookupTable' class which has been replaced by `WeakKeyDictionary'; the usage is completely identical, but the implementation was changed to use a more efficient approach based on ephemeron objects.  File: gst.info, Node: Packages, Next: Emacs, Prev: Features, Up: Top 3 Packages ********** GNU Smalltalk includes a packaging system which allows one to file in components (often called "goodies" in Smalltalk lore) without caring of whether they need other goodies to be loaded first. The packaging system is implemented by a Smalltalk class, `PackageLoader', which looks for information about packages in various places: * the kernel directory's parent directory; this is where an installed `packages.xml' resides, in a system-wide data directory such as `/usr/local/share/smalltalk'; * the above directory's `site-packages' subdirectory, for example `/usr/local/share/smalltalk/site-packages'; * in the file `.st/packages.xml', hosting per-user packages; * finally, there can be a `packages.xml' in the same directory as the current image. Each of this directories can contain package descriptions in an XML file named (guess what) `packages.xml', as well as standalone packages in files named `*.star' (short for `Smalltalk archive'). Later in this section you will find information about `gst-package', a program that helps you create `.star' files. There are two ways to load something using the packaging system. The first way is to use the PackageLoader's `fileInPackage:' and `fileInPackages:' methods. For example: PackageLoader fileInPackages: #('DBD-MySQL' 'DBD-SQLite'). PackageLoader fileInPackage: 'Sockets'. The second way is to use the `gst-load' script which is installed together with the virtual machine. For example, you can do: gst-load DBD-MySQL DBD-SQLite DBI and GNU Smalltalk will automatically file in: * DBI, loaded first because it is needed by the other two packages * Sockets and Digest, not specified, but needed by DBD-MySQL * DBD-MySQL * DBD-SQLite Notice how DBI has already been loaded. Then it will save the Smalltalk image, and finally exit. `gst-load' supports several options: `-I' `--image-file' Load the packages inside the given image. `-i' `--rebuild-image' Build an image from scratch and load the package into it. Useful when the image specified with `-I' does not exist yet. `-q' `--quiet' Hide the script's output. `-v' `--verbose' Show which files are loaded, one by one. `-f' `--force' If a package given on the command-line is already present, reload it. This does not apply to automatically selected prerequisites. `-t' `--test' Run the package testsuite before installing, and exit with a failure if the tests fail. Currently, the testsuites are placed in the image together with the package, but this may change in future versions. `-n' `--dry-run' Do not save the image after loading. `--start[=ARG]' Start the services identified by the package. If an argument is given, only one package can be specified on the command-line. If at least one package specifies a startup script, `gst-load' won't exit. To provide support for this system, you have to give away with your GNU Smalltalk goodies a small file (usually called `package.xml') which looks like this: DBD-SQLite DBI.SQLite DBI dbd-sqlite3 DBI.SQLite.SQLiteTestSuite SQLiteTests.st SQLite.st Connection.st ResultSet.st Statement.st Row.st ColumnInfo.st Table.st TableColumnInfo.st SQLiteTests.st ChangeLog Other tags exist: `url' Specifies a URL at which a repository for the package can be found. The repository, when checked out, should contain a `package.xml' file at its root. The contents of this tag are not used for local packages; they are used when using the `--download' option to `gst-package'. `library' Loads a dynamic shared object and registers the functions in it so that they can all be called from Smalltalk code. The `GTK' package registers the GTK+ library in this way, so that the bindings can use them. `callout' Instructs to load the package only if the C function whose name is within the tag is available to be called from Smalltalk code. `start' Specifies a Smalltalk script that `gst-load' and `gst-remote' will execute in order to start the execution of the service implemented in the package. Before executing the script, `%1' is replaced with either `nil' or a String literal. `stop' Specifies a Smalltalk script that `gst-remote' will execute in order to shut down the service implemented in the package. Before executing the script, `%1' is replaced with either `nil' or a String literal. `dir' Should include a `name' attribute. The `file', `filein' and `built-file' tags that are nested within a `dir' tag are prepended with the directory specified by the attribute. `test' Specifies a subpackage that is only loaded by `gst-sunit' in order to test the package. The subpackage may include arbitrary tags (including `file', `filein' and `sunit') but not `name'. `provides' In some cases, a single functionality can be provided by multiple modules. For example, GNU Smalltalk includes two browsers but only one should be loaded at any time. To this end, a dummy package `Browser' is created pointing to the default browser (`VisualGST'), but both browsers use `provides' so that if the old BLOX browser is in the image, loading `Browser' will have no effect. To install your package, you only have to do gst-package path/to/package.xml `gst-package' is a Smalltalk script which will create a `.star' archive in the current image directory, with the files specified in the `file', `filein' and `built-file' tags. By default the package is placed in the system-wide package directory; you can use the option `--target-directory' to create the `.star' file elsewhere. Instead of a local `package.xml' file, you can give: * a local `.star' file or a `URL' to such a file. The file will be downloaded if necessary, and copied to the target directory; * a URL to a `package.xml' file. The `url' tag in the file will be used to find a source code repository (`git' or `svn') or as a redirect to another `package.xml' file. There is also a short form for specifying `package.xml' file on GNU Smalltalk's web site, so that the following two commands are equivalent: gst-package http://smalltalk.gnu.org/project/Iliad/package.xml gst-package --download Iliad When downloading remote `package.xml' files, `gst-package' also performs a special check to detect multiple packages in the same repository. If the following conditions are met: * a package named `PACKAGE' has a prerequisite `PACKAGE-SUBPACKAGE'; * there is a toplevel subdirectory SUBPACKAGE in the repository; * the subdirectory has a `package.xml' file in it then the `SUBPACKAGE/package.xml' will be installed as well. `gst-package' does not check if the file actually defines a package with the correct name, but this may change in future versions. Alternatively, `gst-package' can be used to create a skeleton GNU style source tree. This includes a `configure.ac' that will find the installation path of GNU Smalltalk, and a `Makefile.am' to support all the standard Makefile targets (including `make install' and `make dist'). To do so, go in the directory that is to become the top of the source tree and type. gst-package --prepare path1/package.xml path2/package.xml In this case the generated configure script and Makefile will use more features of `gst-package', which are yet to be documented. The GNU Smalltalk makefile similarly uses `gst-package' to install packages and to prepare the distribution tarballs. The rest of this chapter discusses some of the packages provided with GNU Smalltalk. * Menu: * GTK and VisualGST: GUI. * Parser, STInST, Compiler: Smalltalk-in-Smalltalk. * DBI: Database. * I18N: Locales. * Seaside: Seaside. * Swazoo: Swazoo. * SUnit: SUnit. * Sockets, WebServer, NetClients: Network support. * XML, XPath, XSL: XML. * Other packages: Other packages.  File: gst.info, Node: GUI, Next: Smalltalk-in-Smalltalk, Up: Packages 3.1 GTK and VisualGST ===================== GNU Smalltalk comes with GTK bindings and with a browser based on it. The system can be started as `gst-browser' and will allow the programmer to view the source code for existing classes, to modify existing classes and methods, to get detailed information about the classes and methods, and to evaluate code within the browser. In addition, simple debugging and unit testing tools are provided. An Inspector window allows the programmer to graphically inspect and modify the representation of an object and a walkback inspector was designed which will display a backtrace when the program encounters an error. SUnit tests (*note SUnit::) can be run from the browser in order to easily support test driven development. The Transcript global object is redirected to print to the transcript window instead of printing to stdout, and the transcript window as well as the workspaces, unlike the console read-eval-print loop, support variables that live across multiple evaluations: a := 2 "Do-it" a + 2 "Print-it: 4 will be shown" To start the browser you can simply type: gst-browser This will load any requested packages, then, if all goes well, a _launcher_ window combining all the basic tools will appear on your display.  File: gst.info, Node: Smalltalk-in-Smalltalk, Next: Database, Prev: GUI, Up: Packages 3.2 The Smalltalk-in-Smalltalk library ====================================== The Smalltalk-in-Smalltalk library is a set of classes for looking at Smalltalk code, constructing models of Smalltalk classes that can later be created for real, analyzing and performing changes to the image, finding smelly code and automatically doing repetitive changes. This package incredibly enhances the reflective capabilities of Smalltalk. A fundamental part of the system is the recursive-descent parser which creates parse nodes in the form of instances of subclasses of `RBProgramNode'. The parser's extreme flexibility can be exploited in three ways, all of which are demonstrated by source code available in the distribution: * First, actions are not hard-coded in the parser itself: the parser creates a parse tree, then hands it to methods in `RBParser' that can be overridden in different `RBParser' subclasses. This is done by the compiler itself, in which a subclass of `RBParser' (class `STFileInParser') hands the parse trees to the `STCompiler' class. * Second, an implementation of the "visitor" pattern is provided to help in dealing with parse trees created along the way; this approach is demonstrated by the Smalltalk code pretty-printer in class `RBFormatter', by the syntax highlighting engine included with the browser, and by the compiler. * The parser is able to perform complex tree searches and rewrites, through the ParseTreeSearcher and ParseTreeRewriter classes. In addition, two applications were created on top of this library which are specific to GNU Smalltalk. The first is a compiler for Smalltalk methods written in Smalltalk itself, whose source code provides good insights into the GNU Smalltalk virtual machine. The second is the automatic documentation extractor. `gst-doc' is able to create documentation even if the library cannot be loaded (for example, if loading it requires a running X server). To do so it uses `STClassLoader' from the `Parser' package to load and interpret Smalltalk source code, creating objects for the classes and methods being read in; then, polymorphism allows one to treat these exactly like usual classes.  File: gst.info, Node: Database, Next: Locales, Prev: Smalltalk-in-Smalltalk, Up: Packages 3.3 Database connectivity ========================= GNU Smalltalk includes support for connecting to databases. Currently this support is limited to retrieving result sets from SQL selection queries and executing SQL data manipulation queries; in the future however a full object model will be available that hides the usage of SQL. Classes that are independent of the database management system that is in use reside in package `DBI', while the drivers proper reside in separate packages which have `DBI' as a prerequisite; currently, drivers are supplied for _MySQL_ and _PostgreSQL_, in packages `DBD-MySQL' and `DBD-PostgreSQL' respectively. Using the library is fairly simple. To execute a query you need to create a connection to the database, create a statement on the connection, and execute your query. For example, let's say I want to connect to the `test' database on the localhost. My user name is `doe' and my password is `mypass'. | connection statement result | connection := DBI.Connection connect: 'dbi:MySQL:dbname=test;hostname=localhost' user: 'doe' password: 'mypass'). You can see that the DBMS-specific classes live in a sub-namespace of `DBI', while DBMS-independent classes live in `DBI'. Here is how I execute a query. statement := connection execute: 'insert into aTable (aField) values (123)'. The result that is returned is a `ResultSet'. For write queries the object returns the number of rows affected. For read queries (such as selection queries) the result set supports standard stream protocol (`next', `atEnd' to read rows off the result stream) and can also supply collection of column information. These are instances of `ColumnInfo') and describe the type, size, and other characteristics of the returned column. A common usage of a ResultSet would be: | resultSet values | [resultSet atEnd] whileFalse: [values add: (resultSet next at: 'columnName') ].  File: gst.info, Node: Locales, Next: Seaside, Prev: Database, Up: Packages 3.4 Internationalization and localization support ================================================= Different countries and cultures have varying conventions for how to communicate. These conventions range from very simple ones, such as the format for representing dates and times, to very complex ones, such as the language spoken. Provided the programs are written to obey the choice of conventions, they will follow the conventions preferred by the user. GNU Smalltalk provides two packages to ease you in doing so. The `I18N' package covers both "internationalization" and "multilingualization"; the lighter-weight `Iconv' package covers only the latter, as it is a prerequisite for correct internationalization. "Multilingualizing" software means programming it to be able to support languages from every part of the world. In particular, it includes understanding multi-byte character sets (such as UTF-8) and Unicode characters whose "code point" (the equivalent of the ASCII value) is above 127. To this end, GNU Smalltalk provides the `UnicodeString' class that stores its data as 32-bit Unicode values. In addition, `Character' will provide support for all the over one million available code points in Unicode. Loading the `I18N' package improves this support through the `EncodedStream' class(1), which interprets and transcodes non-ASCII Unicode characters. This support is mostly transparent, because the base classes `Character', `UnicodeCharacter' and `UnicodeString' are enhanced to use it. Sending `asString' or `printString' to an instance of `Character' and `UnicodeString' will convert Unicode characters so that they are printed correctly in the current locale. For example, `$<279> printNl' will print a small Latin letter `e' with a dot above, when the `I18N' package is loaded. Dually, you can convert `String' or `ByteArray' objects to Unicode with a single method call. If the current locale's encoding is UTF-8, `#[196 151] asUnicodeString' will return a Unicode string with the same character as above, the small Latin letter `e' with a dot above. The implementation of multilingualization support is not yet complete. For example, methods such as `asLowercase', `asUppercase', `isLetter' do not yet recognize Unicode characters. You need to exercise some care, or your program will be buggy when Unicode characters are used. In particular, Characters must *not* be compared with `=='(2) and should be printed on a Stream with `display:' rather than `nextPut:'. Also, Characters need to be created with the class method `codePoint:' if you are referring to their Unicode value; `codePoint:' is also the only method to create characters that is accepted by the ANSI Standard for Smalltalk. The method `value:', instead, should be used if you are referring to a byte in a particular encoding. This subtle difference means that, for example, the last two of the following examples will fail: "Correct. Use #value: with Strings, #codePoint: with UnicodeString." String with: (Character value: 65) String with: (Character value: 128) UnicodeString with: (Character codePoint: 65) UnicodeString with: (Character codePoint: 128) "Correct. Only works for characters in the 0-127 range, which may be considered as defensive programming." String with: (Character codePoint: 65) "Dubious, and only works for characters in the 0-127 range. With UnicodeString, probably you always want #codePoint:." UnicodeString with: (Character value: 65) "Fails, we try to use a high character in a String" String with: (Character codePoint: 128) "Fails, we try to use an encoding in a Unicode string" UnicodeString with: (Character value: 128) "Internationalizing" software, instead, means programming it to be able to adapt to the user's favorite conventions. These conventions can get pretty complex; for example, the user might specify the locale `espana-castellano' for most purposes, but specify the locale `usa-english' for currency formatting: this might make sense if the user is a Spanish-speaking American, working in Spanish, but representing monetary amounts in US dollars. You can see that this system is simple but, at the same time, very complete. This manual, however, is not the right place for a thorough discussion of how an user would set up his system for these conventions; for more information, refer to your operating system's manual or to the GNU C library's manual. GNU Smalltalk inherits from ISO C the concept of a "locale", that is, a collection of conventions, one convention for each purpose, and maps each of these purposes to a Smalltalk class defined by the `I18N' package, and these classes form a small hierarchy with class `Locale' as its roots: * `LcNumeric' formats numbers; `LcMonetary' and `LcMonetaryISO' format currency amounts. * `LcTime' formats dates and times. * `LcMessages' translates your program's output. Of course, the package can't automatically translate your program's output messages into other languages; the only way you can support output in the user's favorite language is to translate these messages by hand. The package does, though, provide methods to easily handle translations into multiple languages. Basic usage of the `I18N' package involves a single selector, the question mark (`?'), which is a rarely used yet valid character for a Smalltalk binary message. The meaning of the question mark selector is "How do you say ... under your convention?". You can send `?' to either a specific instance of a subclass of `Locale', or to the class itself; in this case, rules for the default locale (which is specified via environment variables) apply. You might say, for example, `LcTime ? Date today' or, for example, `germanMonetaryLocale ? account balance'. This syntax can be at first confusing, but turns out to be convenient because of its consistency and overall simplicity. Here is how `?' works for different classes: -- Method on LcTime: ? aString Format a date, a time or a timestamp (`DateTime' object). -- Method on LcNumber: ? aString Format a number. -- Method on LcMonetary: ? aString Format a monetary value together with its currency symbol. -- Method on LcMonetaryISO: ? aString Format a monetary value together with its ISO currency symbol. -- Method on LcMessages: ? aString Answer an `LcMessagesDomain' that retrieves translations from the specified file. -- Method on LcMessagesDomain: ? aString Retrieve the translation of the given string.(3) These two packages provides much more functionality, including more advanced formatting options support for Unicode, and conversion to and from several character sets. For more information, refer to *note Multilingual and international support with Iconv and I18N: (gst-libs)I18N. As an aside, the representation of locales that the package uses is exactly the same as the C library, which has many advantages: the burden of mantaining locale data is removed from GNU Smalltalk's mantainers; the need of having two copies of the same data is removed from GNU Smalltalk's users; and finally, uniformity of the conventions assumed by different internationalized programs is guaranteed to the end user. In addition, the representation of translated strings is the standard MO file format adopted by the GNU `gettext' library. ---------- Footnotes ---------- (1) All the classes mentioned in this section reside in the `I18N' namespace. (2) Character equality with `=' will be as fast as with `=='. (3) The `?' method does not apply to the LcMessagesDomain class itself, but only to its instances. This is because LcMessagesDomain is not a subclass of Locale.  File: gst.info, Node: Seaside, Next: Swazoo, Prev: Locales, Up: Packages 3.5 The Seaside web framework ============================= Seaside is a framework to build highly interactive web applications quickly, reusably and maintainably. Features of Seaside include callback-based request handling, hierarchical (component-based) page design, and modal session management to easily implement complex workflows. A simple Seaside component looks like this: Seaside.WAComponent subclass: MyCounter [ | count | MyCounter class >> canBeRoot [ ^true ] initialize [ super initialize. count := 0. ] states [ ^{ self } ] renderContentOn: html [ html heading: count. html anchor callback: [ count := count + 1 ]; with: '++'. html space. html anchor callback: [ count := count - 1 ]; with: '--'. ] ] MyCounter registerAsApplication: 'mycounter' Most of the time, you will run Seaside in a background virtual machine. First of all, you should load the Seaside packages into a new image like this: $ gst-load -iI seaside.im Seaside Seaside-Development Seaside-Examples Then, you can start Seaside with either of these commands $ gst-load -I seaside.im --start Seaside $ gst-remote -I seaside.im --daemon --start=Seaside which will start serving pages at `http://localhost:8080/seaside'. The former starts the server in foreground, the latter instead runs a virtual machine that you can control using further invocations of `gst-remote'. For example, you can stop serving Seaside pages, and bring down the server, respectively with these commands: $ gst-remote --stop=Seaside $ gst-remote --kill  File: gst.info, Node: Swazoo, Next: SUnit, Prev: Seaside, Up: Packages 3.6 The Swazoo web server ========================= Swazoo (Smalltalk Web Application Zoo) is a free Smalltalk HTTP server supporting both static web serving and a fully-featured web request resolution framework. The server can be started using $ gst-load --start[=ARG] Swazoo or loaded into a background GNU Smalltalk virtual machine with $ gst-remote --start=Swazoo[:ARG] Usually, the first time you start Swazoo ARG is `swazoodemo' (which starts a simple "Hello, World!" servlet) or a path to a configuration file like this one: After this initial step, ARG can take the following meanings: * if omitted altogether, all the sites registered on the server are started; * if a number, all the sites registered on the server on that port are started; * if a configuration file name, the server configuration is _replaced_ with the one loaded from that file; * if any other string, the site named ARG is started. In addition, a background server can be stopped using $ gst-remote --stop=Swazoo[:ARG] where ARG can have the same meanings, except for being a configuration file. In addition, package `WebServer' implements an older web server engine which is now superseded by Swazoo. It is based on the GPL'ed WikiWorks project. Apart from porting to GNU Smalltalk, a number of changes were made to the code, including refactoring of classes, better aesthetics, authentication support, virtual hosting, and HTTP 1.1 compliance.  File: gst.info, Node: SUnit, Next: Network support, Prev: Swazoo, Up: Packages 3.7 The SUnit testing package ============================= `SUnit' is a framework to write and perform test cases in Smalltalk, originarily written by the father of Extreme Programming(1), Kent Beck. `SUnit' allows one to write the tests and check results in Smalltalk; while this approach has the disadvantage that testers need to be able to write simple Smalltalk programs, the resulting tests are very stable. What follows is a description of the philosophy of `SUnit' and a description of its usage, excerpted from Kent Beck's paper in which he describes `SUnit'. 3.7.1 Where should you start? ----------------------------- Testing is one of those impossible tasks. You'd like to be absolutely complete, so you can be sure the software will work. On the other hand, the number of possible states of your program is so large that you can't possibly test all combinations. If you start with a vague idea of what you'll be testing, you'll never get started. Far better to _start with a single configuration whose behavior is predictable_. As you get more experience with your software, you will be able to add to the list of configurations. Such a configuration is called a "fixture". Two example fixtures for testing Floats can be `1.0' and `2.0'; two fixtures for testing Arrays can be `#()' and `#(1 2 3)'. By choosing a fixture you are saying what you will and won't test for. A complete set of tests for a community of objects will have many fixtures, each of which will be tested many ways. To design a test fixture you have to * Subclass TestCase * Add an instance variable for each known object in the fixture * Override setUp to initialize the variables 3.7.2 How do you represent a single unit of testing? ---------------------------------------------------- You can predict the results of sending a message to a fixture. You need to represent such a predictable situation somehow. The simplest way to represent this is interactively. You open an Inspector on your fixture and you start sending it messages. There are two drawbacks to this method. First, you keep sending messages to the same fixture. If a test happens to mess that object up, all subsequent tests will fail, even though the code may be correct. More importantly, though, you can't easily communicate interactive tests to others. If you give someone else your objects, the only way they have of testing them is to have you come and inspect them. By representing each predictable situation as an object, each with its own fixture, no two tests will ever interfere. Also, you can easily give tests to others to run. _Represent a predictable reaction of a fixture as a method._ Add a method to TestCase subclass, and stimulate the fixture in the method. 3.7.3 How do you test for expected results? ------------------------------------------- If you're testing interactively, you check for expected results directly, by printing and inspecting your objects. Since tests are in their own objects, you need a way to programmatically look for problems. One way to accomplish this is to use the standard error handling mechanism (`#error:') with testing logic to signal errors: 2 + 3 = 5 ifFalse: [self error: 'Wrong answer'] When you're testing, you'd like to distinguish between errors you are checking for, like getting six as the sum of two and three, and errors you didn't anticipate, like subscripts being out of bounds or messages not being understood. There's not a lot you can do about unanticipated errors (if you did something about them, they wouldn't be unanticipated any more, would they?) When a catastrophic error occurs, the framework stops running the test case, records the error, and runs the next test case. Since each test case has its own fixture, the error in the previous case will not affect the next. The testing framework makes checking for expected values simple by providing a method, `#should:', that takes a Block as an argument. If the Block evaluates to true, everything is fine. Otherwise, the test case stops running, the failure is recorded, and the next test case runs. So, you have to _turn checks into a Block evaluating to a Boolean, and send the Block as the parameter to `#should:'_. In the example, after stimulating the fixture by adding an object to an empty Set, we want to check and make sure it's in there: SetTestCase>>#testAdd empty add: 5. self should: [empty includes: 5] There is a variant on `TestCase>>#should:'. `TestCase>>#shouldnt:' causes the test case to fail if the Block argument evaluates to true. It is there so you don't have to use `(...) not'. Once you have a test case this far, you can run it. Create an instance of your TestCase subclass, giving it the selector of the testing method. Send `run' to the resulting object: (SetTestCase selector: #testAdd) run If it runs to completion, the test worked. If you get a walkback, something went wrong. 3.7.4 How do you collect and run many different test cases? ----------------------------------------------------------- As soon as you have two test cases running, you'll want to run them both one after the other without having to execute two do it's. You could just string together a bunch of expressions to create and run test cases. However, when you then wanted to run "this bunch of cases and that bunch of cases" you'd be stuck. The testing framework provides an object to represent "a bunch of tests", `TestSuite'. A `TestSuite' runs a collection of test cases and reports their results all at once. Taking advantage of polymorphism, `TestSuites' can also contain other `TestSuites', so you can put Joe's tests and Tammy's tests together by creating a higher level suite. _Combine test cases into a test suite._ (TestSuite named: 'Money') add: (MoneyTestCase selector: #testAdd); add: (MoneyTestCase selector: #testSubtract); run The result of sending `#run' to a `TestSuite' is a `TestResult' object. It records all the test cases that caused failures or errors, and the time at which the suite was run. All of these objects are suitable for being stored in the image and retrieved. You can easily store a suite, then bring it in and run it, comparing results with previous runs. 3.7.5 Running testsuites from the command line ---------------------------------------------- GNU Smalltalk includes a Smalltalk script to simplify running SUnit test suites. It is called `gst-sunit'. The command-line to `gst-sunit' specifies the packages, files and classes to test: `-I' `--image-file' Run tests inside the given image. `-q' `--quiet' Hide the program's output. The results are still communicated with the program's exit code. `-v' `--verbose' Be more verbose, in particular this will cause `gst-sunit' to write which test is currently being executed. `-f FILE' `--file=FILE' Load FILE before running the required test cases. `-p PACKAGE' `--package=PACKAGE' Load PACKAGE and its dependencies, and add PACKAGE's tests to the set of test cases to run. `CLASS' `CLASS*' Add CLASS to the set of test cases to run. An asterisk after the class name adds all the classes in CLASS's hierarchy. In particular, each selector whose name starts with `test' constitutes a separate test case. `VAR=VALUE' Associate variable VAR with a value. Variables allow customization of the testing environment. For example, the username with which to access a database can be specified with variables. From within a test, variables are accessible with code like this: TestSuitesScripter variableAt: 'mysqluser' ifAbsent: [ 'root' ] Note that a `#variableAt:' variant does _not_ exist, because the testsuite should pick default values in case the variables are not specified by the user. ---------- Footnotes ---------- (1) Extreme Programming is a software engineering technique that focuses on team work (to the point that a programmer looks in real-time at what another one is typing), frequent testing of the program, and incremental design.  File: gst.info, Node: Network support, Next: XML, Prev: SUnit, Up: Packages 3.8 Sockets, WebServer, NetClients ================================== GNU Smalltalk includes an almost complete abstraction of the TCP, UDP and IP protocols. Although based on the standard BSD sockets, this library provides facilities such as buffering and preemptive I/O which a C programmer usually has to implement manually. The distribution includes a few tests (mostly loopback tests that demonstrate both client and server connection), which are class methods in `Socket'. This code should guide you in the process of creating and using both server and client sockets; after creation, sockets behave practically the same as standard Smalltalk streams, so you should not have particular problems. For more information, refer to *note Network programming with Sockets: (gst-libs)Sockets. The library is also used by many other packages, including Swazoo and the MySQL driver. There is also code implementing the most popular Internet protocols: FTP, HTTP, NNTP, SMTP, POP3 and IMAP. These classes, loaded by the `NetClients' package, are derived from multiple public domain and free software packages available for other Smalltalk dialects and ported to GNU Smalltalk. Future version of GNU Smalltalk will include documentation for these as well.  File: gst.info, Node: XML, Next: Other packages, Prev: Network support, Up: Packages 3.9 An XML parser and object model for GNU Smalltalk ==================================================== The XML parser library for Smalltalk, loaded as package `XML' includes a validating XML parser and Document Object Model. This library is rapidly becoming a standard in the Smalltalk world and a XSLR interpreter based on it is bundled with GNU Smalltalk as well (see packages `XPath' and `XSL'). Parts of the basic XML package can be loaded independently using packages `XML-DOM', `XML-SAXParser', `XML-XMLParser', `XML-SAXDriver', `XML-XMLNodeBuilder'.  File: gst.info, Node: Other packages, Prev: XML, Up: Packages 3.10 Other packages =================== Various other "minor" packages are provided, typically as examples of writing modules for GNU Smalltalk (*note Linking your libraries to the virtual machine: External modules.). These include: Complex which adds transparent operations with complex numbers GDBM which is an interface to the GNU database manager Digest which provides two easy to use classes to quickly compute cryptographically strong hash values using the MD5 and SHA1 algorithms. NCurses which provides bindings to ncurses Continuations which provides more examples and tests for continuations (an advanced feature to support complex control flow). DebugTools which provides a way to attach to another Smalltalk process and execute it a bytecode or a method at a time.  File: gst.info, Node: Emacs, Next: C and Smalltalk, Prev: Packages, Up: Top 4 Smalltalk interface for GNU Emacs *********************************** GNU Smalltalk comes with its own Emacs mode for hacking Smalltalk code. It also provides tools for interacting with a running Smalltalk system in an Emacs subwindow. Emacs will automatically go into Smalltalk mode when you edit a Smalltalk file (one with the extension `.st'). * Menu: * Editing:: Autoindent and more for GNU Smalltalk. * Interactor:: Smalltalk interactor mode.  File: gst.info, Node: Editing, Next: Interactor, Up: Emacs 4.1 Smalltalk editing mode ========================== The GNU Smalltalk editing mode is there to assist you in editing your Smalltalk code. It tries to be smart about indentation and provides a few cooked templates to save you keystrokes. Since Smalltalk syntax is highly context sensitive, the Smalltalk editing mode will occasionally get confused when you are editing expressions instead of method definitions. In particular, using local variables, thus: | foo | foo := 3. ^foo squared ! will confuse the Smalltalk editing mode, as this might also be a definition the binary operator `|', with second argument called `foo'. If you find yourself confused when editing this type of expression, put a dummy method name before the start of the expression, and take it out when you're done editing, thus: x | foo | foo := 3. ^foo squared !  File: gst.info, Node: Interactor, Prev: Editing, Up: Emacs 4.2 Smalltalk interactor mode ============================= An interesting feature of Emacs Smalltalk is the Smalltalk interactor, which basically allows you run in GNU Emacs with Smalltalk files in one window, and Smalltalk in the other. You can, with a single command, edit and change method definitions in the live Smalltalk system, evaluate expressions, make image snapshots of the system so you can pick up where you left off, file in an entire Smalltalk file, etc. It makes a tremendous difference in the productivity and enjoyment that you'll have when using GNU Smalltalk. To start up the Smalltalk interactor, you must be running GNU Emacs and in a buffer that's in Smalltalk mode. Then, if you type `C-c m'. A second window will appear with GNU Smalltalk running in it. This window is in most respects like a Shell mode window. You can type Smalltalk expressions to it directly and re-execute previous things in the window by moving the cursor back to the line that contains the expression that you wish to re-execute and typing return. Notice the status in the mode line (e.g. `starting-up', `idle', etc). This status will change when you issue various commands from Smalltalk mode. When you first fire up the Smalltalk interactor, it puts you in the window in which Smalltalk is running. You'll want to switch back to the window with your file in it to explore the rest of the interactor mode, so do it now. To execute a range of code, mark the region around and type `C-c e'. The expression in the region is sent to Smalltalk and evaluated. The status will change to indicate that the expression is executing. This will work for any region that you create. If the region does not end with an exclamation point (which is syntactically required by Smalltalk), one will be added for you. There is also a shortcut, `C-c d' (also invokeable as `M-x smalltalk-doit'), which uses a simple heuristic to figure out the start and end of the expression: it searches forward for a line that begins with an exclamation point, and backward for a line that does not begin with space, tab, or the comment character, and sends all the text in between to Smalltalk. If you provide a prefix argument (by typing `C-u C-c d' for instance), it will bypass the heuristic and use the region instead (just like `C-c e' does). `C-c c' will compile a method; it uses a similar heuristic to determine the bounds of the method definition. Typically, you'll change a method definition, type `C-c c' and move on to whatever's next. If you want to compile a whole bunch of method definitions, you'll have to mark the entire set of method definitions (from the `methodsFor:' line to the `! !') as the region and use `C-c e'. After you've compiled and executed some expressions, you may want to take a snapshot of your work so that you don't have to re-do things next time you fire up Smalltalk. To do this, you use the `C-c s' command, which invokes `ObjectMemory snapshot'. If you invoke this command with a prefix argument, you can specify a different name for the image file, and you can have that image file loaded instead of the default one by using the `-I' flag on the command line when invoking Smalltalk. You can also evaluate an expression and have the result of the evaluation printed by using the `C-c p' command. Mark the region and use the command. To file in an entire file (perhaps the one that you currently have in the buffer that you are working on), type `C-c f'. You can type the name of a file to load at the prompt, or just type return and the file associated with the current buffer will be loaded into Smalltalk. When you're ready to quit using GNU Smalltalk, you can quit cleanly by using the `C-c q' command. If you want to fire up Smalltalk again, or if (heaven forbid) Smalltalk dies on you, you can use the `C-c m' command, and Smalltalk will be reincarnated. Even if it's running, but the Smalltalk window is not visible, `C-c m' will cause it to be displayed right away. You might notice that as you use this mode, the Smalltalk window will scroll to keep the bottom of the buffer in focus, even when the Smalltalk window is not the current window. This was a design choice that I made to see how it would work. On the whole, I guess I'm pretty happy with it, but I am interested in hearing your opinions on the subject.  File: gst.info, Node: C and Smalltalk, Next: Tutorial, Prev: Emacs, Up: Top 5 Interoperability between C and GNU Smalltalk ********************************************** * Menu: * External modules:: Linking your libraries to the virtual machine * C callout:: Calls from Smalltalk to C * C data types:: Manipulating C data from Smalltalk * Smalltalk types:: Manipulating Smalltalk data from C * Smalltalk callin:: Calls from C to Smalltalk * Smalltalk callbacks:: Smalltalk blocks as C function pointers * Object representation:: Manipulating your own Smalltalk objects * Incubator:: Protecting newly created objects from garbage collections * Other C functions:: Handling and creating OOPs * Using Smalltalk:: The Smalltalk environment as an extension library  File: gst.info, Node: External modules, Next: C callout, Up: C and Smalltalk 5.1 Linking your libraries to the virtual machine ================================================= A nice thing you can do with GNU Smalltalk is enhancing it with your own goodies. If they're written in Smalltalk only, no problem: getting them to work as packages (*note Packages::), and to fit in with the GNU Smalltalk packaging system, is likely to be a five-minutes task. If your goodie is creating a binding to an external C library and you do not need particular glue to link it to Smalltalk (for example, there are no callbacks from C code to Smalltalk code), you can use the `dynamic library linking' system. When using this system, you have to link GNU Smalltalk with the library at run-time using DLD, using either `DLD class>>#addLibrary:' or a `' tag in a `package.xml' file (*note Packages::). The following line: DLD addLibrary: 'libc' is often used to use the standard C library functions from Smalltalk. However, if you want to provide a more intimate link between C and Smalltalk, as is the case with for example the GTK bindings, you should use the `dynamic module linking' system. This section explains what to do, taking the Digest library as a guide. A module is distinguished from a standard shared library because it has a function which Smalltalk calls to initialize the module; the name of this function must be `gst_initModule'. Here is the initialization function used by Digest: void gst_initModule(proxy) VMProxy *proxy; { vmProxy = proxy; vmProxy->defineCFunc ("MD5AllocOOP", MD5AllocOOP); vmProxy->defineCFunc ("MD5Update", md5_process_bytes); vmProxy->defineCFunc ("MD5Final", md5_finish_ctx); vmProxy->defineCFunc ("SHA1AllocOOP", SHA1AllocOOP); vmProxy->defineCFunc ("SHA1Update", sha1_process_bytes); vmProxy->defineCFunc ("SHA1Final", sha1_finish_ctx); } Note that the `defineCFunc' function is called through a function pointer in `gst_initModule', and that the value of its parameter is saved in order to use it elsewhere in its code. This is not strictly necessary on many platforms, namely those where the module is effectively _linked with the Smalltalk virtual machine_ at run-time; but since some(1) cannot obtain this, for maximum portability you must always call the virtual machine through the proxy and never refer to any symbol which the virtual machine exports. For uniformity, even programs that link with `libgst.a' should not call these functions directly, but through a `VMProxy' exported by `libgst.a' and accessible through the `gst_interpreter_proxy' variable. Modules are shared libraries; the default directory in which modules are searched for is stored in a `gnu-smalltalk.pc' file that is installed by GNU Smalltalk so that it can be used with `pkg-config'. An Autoconf macro `AM_PATH_GST' is also installed that will put the directory in the `gstmoduledir' Autoconf substitution. When using GNU Automake and Libtool, you can then build modules by including something like this in `Makefile.am': gstmodule_LTLIBRARIES = libdigest.la libdigest_la_LDFLAGS = -module -no-undefined "... more flags ..." libdigest_la_SOURCES = "... your source files ..." While you can use `DLD class>>#addModule:' to link a module into the virtual machine at run time, usually bindings that require a module are complex enough to be packaged as `.star' files. In this case, you will have to add the name of the module in a package file (*note Packages::). In this case, the relevant entry in the file will be Digest digest.st md5.st sha1.st digest MD5Test SHA1Test mdtests.st There is also a third case, in which the bindings are a mixture of code written specially for GNU Smalltalk, and the normal C library. In this case, you can use a combination of dynamic shared libraries and dynamic modules. To do this, you can specify both `' and `' tags in the `package.xml' file; alternatively, the following functions allow you to call `DLD class>>#addLibrary:' from within a module. -- Function: mst_Boolean dlOpen (void *filename, int module) Open the library pointed to by with FILENAME (which need not include an extension), and invoke gst_initModule if it is found in the library. If MODULE is false, add the file to the list of libraries that Smalltalk searches for external symbols. Return true if the library was found. -- Function: void dlAddSearchDir (const char *dir) Add DIR at the beginning of the search path of `dlOpen'. -- Function: void dlPushSearchPath (void) Save the current value of the search path for `dlOpen'. This can be used to temporarily add the search path for the libraries added by a module, without affecting subsequent libraries manually opened with the `DLD' class. -- Function: void dlPopSearchPath (void) Restore the last saved value of the search path. ---------- Footnotes ---------- (1) The most notable are AIX and Windows.  File: gst.info, Node: C callout, Next: C data types, Prev: External modules, Up: C and Smalltalk 5.2 Using the C callout mechanism ================================= To use the C callout mechanism, you first need to inform Smalltalk about the C functions that you wish to call. You currently need to do this in two places: 1) you need to establish the mapping between your C function's address and the name that you wish to refer to it by, and 2) define that function along with how the argument objects should be mapped to C data types to the Smalltalk interpreter. As an example, let us use the pre-defined (to GNU Smalltalk) functions of `system' and `getenv'. First, the mapping between these functions and string names for the functions needs to be established in your module. If you are writing an external Smalltalk module (which can look at Smalltalk objects and manipulate them), see *note Linking your libraries to the virtual machine: External modules.; if you are using function from a dynamically loaded library, see *note Dynamic loading::. Second, we need to define a method that will invoke these C functions and describe its arguments to the Smalltalk runtime system. Such a method is defined with a primitive-like syntax, similar to the following example (taken from `kernel/CFuncs.st') system: aString getenv: aString These methods were defined on class `SystemDictionary', so that we would invoke it thus: Smalltalk system: 'lpr README' ! However, there is no special significance to which class receives the method; it could have just as well been Float, but it might look kind of strange to see: 1701.0 system: 'mail help-smalltalk@gnu.org' ! The various keyword arguments are described below. `cCall: 'system'' This says that we are defining the C function `system'. This name must be *exactly* the same as the string passed to `defineCFunc'. The name of the method does not have to match the name of the C function; we could have just as easily defined the selector to be `'rambo: fooFoo''; it's just good practice to define the method with a similar name and the argument names to reflect the data types that should be passed. `returning: #int' This defines the C data type that will be returned. It is converted to the corresponding Smalltalk data type. The set of valid return types is: `char' Single C character value `string' A C char *, converted to a Smalltalk string `stringOut' A C char *, converted to a Smalltalk string and then freed. `symbol' A C char *, converted to a Smalltalk symbol `symbolOut' A C char *, converted to a Smalltalk symbol and then freed. `int' A C int value `uInt' A C unsigned int value `long' A C long value `uLong' A C unsigned long value `double' A C double, converted to an instance of FloatD `longDouble' A C long double, converted to an instance of FloatQ `void' No returned value (`self' returned from Smalltalk) `wchar' Single C wide character (`wchar_t') value `wstring' Wide C string (`wchar_t *'), converted to a UnicodeString `wstringOut' Wide C string (`wchar_t *'), converted to a UnicodeString and then freed `cObject' An anonymous C pointer; useful to pass back to some C function later `smalltalk' An anonymous (to C) Smalltalk object pointer; should have been passed to C at some point in the past or created by the program by calling other public GNU Smalltalk functions (*note Smalltalk types::). `CTYPE' You can pass an instance of CType or one of its subclasses (*note C data types::). In this case the object will be sent `#narrow' before being returned: an example of this feature is given in the experimental Gtk+ bindings. `args: #(#string)' This is an array of symbols that describes the types of the arguments in order. For example, to specify a call to open(2), the arguments might look something like: args: #(#string #int #int) The following argument types are supported; see above for details. `unknown' Smalltalk will make the best conversion that it can guess for this object; see the mapping table below `boolean' passed as `char', which is promoted to `int' `char' passed as `char', which is promoted to `int' `wchar' passed as `wchar_t' `string' passed as `char *' `byteArrayOut' passed as `char *'. The contents are expected to be overwritten with a new C string, and copied back to the object that was passed on return from the C function `stringOut' passed as `char *', the contents are expected to be overwritten with a new C string, and the object that was passed becomes the new string on return `wstring' passed as `wchar_t *' `wstringOut' passed as `wchar_t *', the contents are expected to be overwritten with a new C wide string, and the object that was passed becomes the new string on return `symbol' passed as `char *' `byteArray' passed as `char *', even though may contain NUL's `int' passed as `int' `uInt' passed as `unsigned int' `long' passed as `long' `uLong' passed as `unsigned long' `double' passed as `double' `longDouble' passed as `long double' `cObject' C object value passed as `void *'. Any class with non-pointer indexed instance variables can be passed as a `#cObject', and GNU Smalltalk will pass the address of the first indexed instance variable. This however should never be done for functions that allocate objects, call back into Smalltalk code or otherwise may cause a garbage collection: after a GC, pointers passed as `#cObject' may be invalidated. In this case, it is safer to pass every object as `#smalltalk', or to only pass `CObject's that were returned by a C function previously. In addition, `#cObject' can be used for function pointers. These are instances of `CCallable' or one of its subclasses. See *note Smalltalk callbacks:: for more information on how to create function pointers for Smalltalk blocks. `cObjectPtr' Pointer to C object value passed as `void **'. The `CObject' is modified on output to reflect the value stored into the passed object. `smalltalk' Pass the object pointer to C. The C routine should treat the value as a pointer to anonymous storage. This pointer can be returned to Smalltalk at some later point in time. `variadic' `variadicSmalltalk' an Array is expected, each of the elements of the array will be converted like an `unknown' parameter if `variadic' is used, or passed as a raw object pointer for `variadicSmalltalk'. `self' `selfSmalltalk' Pass the receiver, converting it to C like an `unknown' parameter if `self' is used or passing the raw object pointer for `selfSmalltalk'. Parameters passed this way don't map to the message's arguments, instead they map to the message's receiver. Table of parameter conversions: Declared param type Object type C parameter type used boolean Boolean (True, False) int byteArray ByteArray char * cObject CObject void * cObject ByteArray, etc. void * cObjectPtr CObject void ** char Boolean (True, False) int char Character int (C promotion rule) char Integer int double Float double (C promotion) longDouble Float long double int Boolean (True, False) int int Integer int uInt Boolean (True, False) unsigned int uInt Integer unsigned int long Boolean (True, False) long long Integer long uLong Boolean (True, False) unsigned long uLong Integer unsigned long smalltalk, anything OOP selfSmalltalk string String char * string Symbol char * stringOut String char * symbol Symbol char * unknown, self Boolean (True, False) int unknown, self ByteArray char * unknown, self CObject void * unknown, self Character int unknown, self Float double unknown, self Integer long unknown, self String char * unknown, self Symbol char * unknown, self anything else OOP variadic Array each element is passed according to "unknown" variadicSmalltalk Array each element is passed as an OOP wchar Character wchar_t wstring UnicodeString wchar_t * wstringOut UnicodeString wchar_t * When your call-out returns `#void', depending on your application you might consider using "asynchronous call-outs". These are call-outs that do not suspend the process that initiated them, so the process might be scheduled again, executing the code that follows the call-out, during the execution of the call-out itself. This is particularly handy when writing event loops (the most common place where you call back into Smalltalk) because then _you can handle events that arrive during the handling of an outer event_ before the outer event's processing has ended. Depending on your application this might be correct or not, of course. In the future, asynchronous call-outs might be started into a separate thread. An asynchronous call-out is defined using an alternate primitive-like syntax, `asyncCCall:args:'. Note that the returned value parameter is missing because an asynchronous call-out always returns `nil'.  File: gst.info, Node: C data types, Next: Smalltalk types, Prev: C callout, Up: C and Smalltalk 5.3 The C data type manipulation system ======================================= `CType' is a class used to represent C data types themselves (no storage, just the type). There are subclasses called things like `CMUMBLECType'. The instances can answer their size and alignment. Their `valueType' is the underlying type of data. It's either an integer, which is interpreted by the interpreter as the scalar type, or the underlying element type, which is another `CType' subclass instance. To make life easier, there are global variables which hold onto instances of `CScalarCType': they are called `CMUMBLEType' (like `CIntType', not like `CIntCType'), and can be used wherever a C datatype is used. If you had an array of strings, the elements would be CStringType's (a specific instance of CScalarCType). `CObject' is the base class of the instances of C data. It has a subclass called `CScalar', which has subclasses called `CMUMBLE'. These subclasses can answer size and alignment information. Instances of `CObject' can hold a raw C pointer (for example in `malloc'ed heap)), or can delegate their storage to a `ByteArray'. In the latter case, the storage is automatically garbage collected when the `CObject' becomes dead, and the VM checks accesses to make sure they are in bounds. On the other hand, the storage may move, and for this reason extra care must be put when using this kind of `CObject' with C routines that call back into Smalltalk, or that store the passed pointer somewhere. Instances of `CObject' can be created in many ways: * creating an instance with `CLASS new' initializes the pointer to `NULL'; * doing `TYPE new', where TYPE is a `CType' subclass instance, allocates a new instance with `malloc'. * doing `TYPE gcNew', where TYPE is a `CType' subclass instance, allocates a new instance backed by garbage-collected storage. `CStruct' and `CUnion' subclasses are special. First, `new' allocates a new instance with `malloc' instead of initializing the pointer to `NULL'. Second, they support `gcNew' which creates a new instance backed by garbage-collected storage. `CObject's created by the C callout mechanism are never backed by garbage-collected storage. `CObject' and its subclasses represent a pointer to a C object and as such provide the full range of operations supported by C pointers. For example, `+' `anInteger' which returns a CObject which is higher in memory by `anInteger' times the size of each item. There is also `-' which acts like `+' if it is given an integer as its parameter. If a CObject is given, it returns the difference between the two pointers. `incr', `decr', `incrBy:', `decrBy:' adjust the string either forward or backward, by either 1 or `n' characters. Only the pointer to the string is changed; the actual characters in the string remain untouched. CObjects can be divided into two families, scalars and non-scalars, just like C data types. Scalars fetch a Smalltalk object when sent the `value' message, and change their value when sent the `value:' message. Non-scalars do not support these two messages. Non-scalars include instances of `CArray' and subclasses of `CStruct' and `CUnion' (but not `CPtr'). `CPtr's and `CArray's get their underlying element type through a `CType' subclass instance which is associated with the `CArray' or `CPtr' instance. `CPtr''s `value' and `value:' method get or change the underlying value that's pointed to. `value' returns another `CObject' corresponding to the pointed value. That's because, for example, a `CPtr' to `long' points to a place in memory where a pointer to long is stored. It is really a `long **' and must be dereferenced twice with `cPtr value value' to get the `long'. `CString' is a subclass of `CPtr' that answers a Smalltalk `String' when sent `value', and automatically allocates storage to copy and null-terminate a Smalltalk `String' when sent `value:'. `replaceWith:' replaces the string the instance points to with a new string or `ByteArray', passed as the argument. Actually, it copies the bytes from the Smalltalk `String' instance aString into the same buffer already pointed to by the `CString', with a null terminator. Finally, there are `CStruct' and `CUnion', which are abstract subclasses of `CObject'(1). The following will refer to CStruct, but the same considerations apply to CUnion as well, with the only difference that CUnions of course implement the semantics of a C union. These classes provide direct access to C data structures including * `long' (unsigned too) * `short' (unsigned too) * `char' (unsigned too) & byte type * `double', `long double', `float' * `string' (NUL terminated char *, with special accessors) * arrays of any type * pointers to any type * other structs containing any fixed size types Here is an example struct decl in C: struct audio_prinfo { unsigned channels; unsigned precision; unsigned encoding; unsigned gain; unsigned port; unsigned _xxx[4]; unsigned samples; unsigned eof; unsigned char pause; unsigned char error; unsigned char waiting; unsigned char _ccc[3]; unsigned char open; unsigned char active; }; struct audio_info { audio_prinfo_t play; audio_prinfo_t record; unsigned monitor_gain; unsigned _yyy[4]; }; And here is a Smalltalk equivalent decision: CStruct subclass: AudioPrinfo [ ] CStruct subclass: AudioInfo [ ] This creates two new subclasses of `CStruct' called `AudioPrinfo' and `AudioInfo', with the given fields. The syntax is the same as for creating standard subclasses, with the additional metadata `declaration:'. You can make C functions return `CObject's that are instances of these classes by passing `AudioPrinfo type' as the parameter to the `returning:' keyword. AudioPrinfo has methods defined on it like: #sampleRate #channels #precision #encoding etc. These access the various data members. The array element accessors (xxx, ccc) just return a pointer to the array itself. For simple scalar types, just list the type name after the variable. Here's the set of scalars names, as defined in `kernel/CStruct.st': #long CLong #uLong CULong #ulong CULong #byte CByte #char CChar #uChar CUChar #uchar CUChar #short CShort #uShort CUShort #ushort CUShort #int CInt #uInt CUInt #uint CUInt #float CFloat #double CDouble #longDouble CLongDouble #string CString #smalltalk CSmalltalk #{...} A given subclass of `CObject' The `#{...}' syntax is not in the Blue Book, but it is present in GNU Smalltalk and other Smalltalks; it returns an Association object corresponding to a global variable. To have a pointer to a type, use something like: (#example (#ptr #long)) To have an array pointer of size SIZE, use: (#example (#array #string SIZE)) Note that this maps to `char *example[SIZE]' in C. The objects returned by using the fields are CObjects; there is no implicit value fetching currently. For example, suppose you somehow got ahold of an instance of class AudioPrinfo as described above (the instance is a CObject subclass and points to a real C structure somewhere). Let's say you stored this object in variable `audioInfo'. To get the current gain value, do audioInfo gain value to change the gain value in the structure, do audioInfo gain value: 255 The structure member message just answers a `CObject' instance, so you can hang onto it to directly refer to that structure member, or you can use the `value' or `value:' methods to access or change the value of the member. Note that this is the same kind of access you get if you use the `addressAt:' method on CStrings or CArrays or CPtrs: they return a CObject which points to a C object of the right type and you need to use `value' and `value:' to access and modify the actual C variable. ---------- Footnotes ---------- (1) Actually they have a common superclass named `CCompound'.  File: gst.info, Node: Smalltalk types, Next: Smalltalk callin, Prev: C data types, Up: C and Smalltalk 5.4 Manipulating Smalltalk data from C ====================================== GNU Smalltalk internally maps every object except Integers to a data structure named an "OOP" (which is short for "Ordinary Object Pointer"). An OOP is a pointer to an internal data structure; this data structure basically adds a level of indirection in the representation of objects, since it contains * a pointer to the actual object data * a bunch of flags, most of which interest the garbage collection process This additional level of indirection makes garbage collection very efficient, since the collector is free to move an object in memory without updating every reference to that object in the heap, thereby keeping the heap fully compact and allowing very fast allocation of new objects. However, it makes C code that wants to deal with objects even more messy than it would be without; if you want some examples, look at the hairy code in GNU Smalltalk that deals with processes. To shield you as much as possible from the complications of doing object-oriented programming in a non-object-oriented environment like C, GNU Smalltalk provides friendly functions to map between common Smalltalk objects and C types. This way you can simply declare OOP variables and then use these functions to treat their contents like C data. These functions are passed to a module via the `VMProxy' struct, a pointer to which is passed to the module, as shown in *note Linking your libraries to the virtual machine: External modules. They can be divided in two groups, those that map _from Smalltalk objects to C data types_ and those that map _from C data types to Smalltalk objects_. Here are those in the former group (Smalltalk to C); you can see that they all begin with `OOPTo': -- Function: long OOPToInt (OOP) This function assumes that the passed OOP is an Integer and returns the C `signed long' for that integer. -- Function: long OOPToId (OOP) This function returns an unique identifier for the given OOP, valid until the OOP is garbage-collected. -- Function: double OOPToFloat (OOP) This function assumes that the passed OOP is an Integer or Float and returns the C `double' for that object. -- Function: long double OOPToLongDouble (OOP) This function assumes that the passed OOP is an Integer or Float and returns the C `long double' for that object. -- Function: int OOPToBool (OOP) This function returns a C integer which is true (i.e. `!= 0') if the given OOP is the `true' object, false (i.e. `== 0') otherwise. -- Function: char OOPToChar (OOP) This function assumes that the passed OOP is a Character and returns the C `char' for that integer. -- Function: wchar_t OOPToWChar (OOP) This function assumes that the passed OOP is a Character or UnicodeCharacter and returns the C `wchar_t' for that integer. -- Function: char *OOPToString (OOP) This function assumes that the passed OOP is a String or ByteArray and returns a C null-terminated `char *' with the same contents. It is the caller's responsibility to free the pointer and to handle possible `NUL' characters inside the Smalltalk object. -- Function: wchar_t *OOPToWString (OOP) This function assumes that the passed OOP is a UnicodeString and returns a C null-terminated `wchar_t *' with the same contents. It is the caller's responsibility to free the pointer and to handle possible `NUL' characters inside the Smalltalk object. -- Function: char *OOPToByteArray (OOP) This function assumes that the passed OOP is a String or ByteArray and returns a C `char *' with the same contents, without null-terminating it. It is the caller's responsibility to free the pointer. -- Function: PTR OOPToCObject (OOP) This functions assumes that the passed OOP is a kind of CObject and returns a C `PTR' to the C data pointed to by the object. The caller should not free the pointer, nor assume anything about its size and contents, unless it exactly knows what it's doing. A `PTR' is a `void *' if supported, or otherwise a `char *'. -- Function: long OOPToC (OOP) This functions assumes that the passed OOP is a String, a ByteArray, a CObject, or a built-in object (`nil', `true', `false', character, integer). If the OOP is `nil', it answers 0; else the mapping for each object is exactly the same as for the above functions. Note that, even though the function is declared as returning a `long', you might need to cast it to either a `char *' or `PTR'. While special care is needed to use the functions above (you will probably want to know at least the type of the Smalltalk object you're converting), the functions below, which convert C data to Smalltalk objects, are easier to use and also put objects in the incubator so that they are not swept by a garbage collection (*note Incubator::). These functions all "end" with `ToOOP', except `cObjectToTypedOOP': -- Function: OOP intToOOP (long) This object returns a Smalltalk `Integer' which contains the same value as the passed C `long'. -- Function: OOP uintToOOP (unsigned long) This object returns a Smalltalk `Integer' which contains the same value as the passed C `unsigned long'. -- Function: OOP idToOOP (OOP) This function returns an OOP from a unique identifier returned by `OOPToId'. The OOP will be the same that was passed to `OOPToId' only if the original OOP has not been garbage-collected since the call to `OOPToId'. -- Function: OOP floatToOOP (double) This object returns a Smalltalk `FloatD' which contains the same value as the passed `double'. Unlike Integers, FloatDs have exactly the same precision as C doubles. -- Function: OOP longDoubleToOOP (long double) This object returns a Smalltalk `FloatQ' which contains the same value as the passed `long double'. Unlike Integers, FloatQs have exactly the same precision as C long doubles. -- Function: OOP boolToOOP (int) This object returns a Smalltalk `Boolean' which contains the same boolean value as the passed C `int'. That is, the returned OOP is the sole instance of either `False' or `True', depending on where the parameter is zero or not. -- Function: OOP charToOOP (char) This object returns a Smalltalk `Character' which represents the same char as the passed C `char'. -- Function: OOP charToOOP (wchar_t) This object returns a Smalltalk `Character' or `UnicodeCharacter' which represents the same char as the passed C `wchar_t'. -- Function: OOP classNameToOOP (char *) This method returns the Smalltalk class (i.e. an instance of a subclass of Class) whose name is the given parameter. Namespaces are supported; the parameter must give the complete path to the class starting from the `Smalltalk' dictionary. `NULL' is returned if the class is not found. This method is slow; you can safely cache its result. -- Function: OOP stringToOOP (char *) This method returns a String which maps to the given null-terminated C string, or the builtin object `nil' if the parameter points to address 0 (zero). -- Function: OOP wstringToOOP (wchar_t *) This method returns a UnicodeString which maps to the given null-terminated C wide string, or the builtin object `nil' if the parameter points to address 0 (zero). -- Function: OOP byteArrayToOOP (char *, int) This method returns a ByteArray which maps to the bytes that the first parameters points to; the second parameter gives the size of the ByteArray. The builtin object `nil' is returned if the first parameter points to address 0 (zero). -- Function: OOP symbolToOOP (char *) This method returns a String which maps to the given null-terminated C string, or the builtin object `nil' if the parameter points to address 0 (zero). -- Function: OOP cObjectToOOP (PTR) This method returns a CObject which maps to the given C pointer, or the builtin object `nil' if the parameter points to address 0 (zero). The returned value has no precise CType assigned. To assign one, use `cObjectToTypedOOP'. -- Function: OOP cObjectToTypedOOP (PTR, OOP) This method returns a CObject which maps to the given C pointer, or the builtin object `nil' if the parameter points to address 0 (zero). The returned value has the second parameter as its type; to get possible types you can use `typeNameToOOP'. -- Function: OOP typeNameToOOP (char *) All this method actually does is evaluating its parameter as Smalltalk code; so you can, for example, use it in any of these ways: cIntType = typeNameToOOP("CIntType"); myOwnCStructType = typeNameToOOP("MyOwnCStruct type"); This method is primarily used by `msgSendf' (*note Smalltalk callin::), but it can be useful if you use lower level call-in methods. This method is slow too; you can safely cache its result. As said above, the C to Smalltalk layer automatically puts the objects it creates in the incubator which prevents objects from being collected as garbage. A plugin, however, has limited control on the incubator, and the incubator itself is not at all useful when objects should be kept registered for a relatively long time, and whose lives in the registry typically overlap. To avoid garbage collection of such object, you can use these functions, which access a separate registry: -- Function: OOP registerOOP (OOP) Puts the given OOP in the registry. If you register an object multiple times, you will need to unregister it the same number of times. You may want to register objects returned by Smalltalk call-ins. -- Function: void unregisterOOP (OOP) Removes an occurrence of the given OOP from the registry. -- Function: void registerOOPArray (OOP **, OOP **) Tells the garbage collector that an array of objects must be made part of the root set. The two parameters point indirectly to the base and the top of the array; that is, they are pointers to variables holding the base and the top of the array: having indirect pointers allows you to dynamically change the size of the array and even to relocate it in memory without having to unregister and re-register it every time you modify it. If you register an array multiple times, you will need to unregister it the same number of times. -- Function: void unregisterOOPArray (OOP **) Removes the array with the given base from the registry.  File: gst.info, Node: Smalltalk callin, Next: Smalltalk callbacks, Prev: Smalltalk types, Up: C and Smalltalk 5.5 Calls from C to Smalltalk ============================= GNU Smalltalk provides seven different function calls that allow you to call Smalltalk methods in a different execution context than the current one. The priority in which the method will execute will be the same as the one of Smalltalk process which is currently active. Four of these functions are more low level and are more suited when the Smalltalk program itself gave a receiver, a selector and maybe some parameters; the others, instead, are more versatile. One of them (`msgSendf') automatically handles most conversions between C data types and Smalltalk objects, while the others takes care of compiling full snippets of Smalltalk code. All these functions handle properly the case of specifying, say, 5 arguments for a 3-argument selector--see the description of the single functions for more information). In all cases except `msgSendf', passing NULL as the selector will expect the receiver to be a block and evaluate it. -- Function: OOP msgSend (OOP receiver, OOP selector, ...) This function sends the given selector (should be a Symbol, otherwise `nilOOP' is returned) to the given receiver. The message arguments should also be OOPs (otherwise, an access violation exception is pretty likely) and are passed in a NULL-terminated list after the selector. The value returned from the method is passed back as an OOP to the C program as the result of `msgSend', or `nilOOP' if the number of arguments is wrong. Example (same as `1 + 2'): OOP shouldBeThreeOOP = vmProxy->msgSend( intToOOP(1), symbolToOOP("+"), intToOOP(2), NULL); -- Function: OOP strMsgSend (OOP receiver, char *selector, ...) This function is the same as above, but the selector is passed as a C string and is automatically converted to a Smalltalk symbol. Theoretically, this function is a bit slower than `msgSend' if your program has some way to cache the selector and avoiding a call to `symbolToOOP' on every call-in. However, this is not so apparent in "real" code because the time spent in the Smalltalk interpreter will usually be much higher than the time spent converting the selector to a Symbol object. Example: OOP shouldBeThreeOOP = vmProxy->strMsgSend( intToOOP(1), "+", intToOOP(2), NULL); -- Function: OOP vmsgSend (OOP receiver, OOP selector, OOP *args) This function is the same as msgSend, but accepts a pointer to the NULL-terminated list of arguments, instead of being a variable-arguments functions. Example: OOP arguments[2], shouldBeThreeOOP; arguments[0] = intToOOP(2); arguments[1] = NULL; /* ... some more code here ... */ shouldBeThreeOOP = vmProxy->vmsgSend( intToOOP(1), symbolToOOP("+"), arguments); -- Function: OOP nvmsgSend (OOP receiver, OOP selector, OOP *args, int nargs) This function is the same as msgSend, but accepts an additional parameter containing the number of arguments to be passed to the Smalltalk method, instead of relying on the NULL-termination of args. Example: OOP argument, shouldBeThreeOOP; argument = intToOOP(2); /* ... some more code here ... */ shouldBeThreeOOP = vmProxy->nvmsgSend( intToOOP(1), symbolToOOP("+"), &argument, 1); -- Function: OOP perform (OOP, OOP) Shortcut function to invoke a unary selector. The first parameter is the receiver, and the second is the selector. -- Function: OOP performWith (OOP, OOP, OOP) Shortcut function to invoke a one-argument selector. The first parameter is the receiver, the second is the selector, the third is the sole argument. -- Function: OOP invokeHook (int) Calls into Smalltalk to process a `ObjectMemory' hook given by the parameter. In practice, `changed:' is sent to `ObjectMemory' with a symbol derived from the parameter. The parameter can be one of: * `GST_BEFORE_EVAL' * `GST_AFTER_EVAL' * `GST_ABOUT_TO_QUIT' * `GST_RETURN_FROM_SNAPSHOT' * `GST_ABOUT_TO_SNAPSHOT' * `GST_FINISHED_SNAPSHOT' All cases where the last three should be used should be covered in GNU Smalltalk's source code. The first three, however, can actually be useful in user code. The two functions that directly accept Smalltalk code are named `evalCode' and `evalExpr', and they're basically the same. They both accept a single parameter, a pointer to the code to be submitted to the parser. The main difference is that `evalCode' discards the result, while `evalExpr' returns it to the caller as an OOP. `msgSendf', instead, has a radically different syntax. Let's first look at some examples. /* 1 + 2 */ int shouldBeThree; vmProxy->msgSendf(&shouldBeThree, "%i %i + %i", 1, 2) /* aCollection includes: 'abc' */ OOP aCollection; int aBoolean; vmProxy->msgSendf(&aBoolean, "%b %o includes: %s", aCollection, "abc") /* 'This is a test' printNl -- in two different ways */ vmProxy->msgSendf(NULL, "%v %s printNl", "This is a test"); vmProxy->msgSendf(NULL, "%s %s printNl", "This is a test"); /* 'This is a test', ' ok?' */ char *str; vmProxy->msgSendf(&str, "%s %s , %s", "This is a test", " ok?"); As you can see, the parameters to msgSendf are, in order: * A pointer to the variable which will contain the record. If this pointer is `NULL', it is discarded. * A description of the method's interface in this format (the object types, after percent signs, will be explained later in this section) %result_type %receiver_type selector %param1_type %param2_type * A C variable or Smalltalk object (depending on the type specifier) for the receiver * If needed, the C variables and/or Smalltalk object (depending on the type specifiers) for the arguments. Note that the receiver and parameters are NOT registered in the object registry (*note Smalltalk types::). "receiver_type" and "paramX_type" can be any of these characters, with these meanings: Specifier C data type equivalent Smalltalk class i long Integer (see intToOOP) f double Float (see floatToOOP) F long double Float (see longDoubleToOOP) b int True or False (see boolToOOP) B OOP BlockClosure c char Character (see charToOOP) C PTR CObject (see cObjToOOP) s char * String (see stringToOOP) S char * Symbol (see symbolToOOP) o OOP any t char *, PTR CObject (see below) T OOP, PTR CObject (see below) w wchar_t Character (see wcharToOOP) W wchar_t * UnicodeString (see wstringToOOP) `%t' and `%T' are particular in the sense that you need to pass "two" additional arguments to `msgSendf', not one. The first will be a description of the type of the CObject to be created, the second instead will be the CObject's address. If you specify `%t', the first of the two arguments will be converted to a Smalltalk `CType' via `typeNameToOOP' (*note Smalltalk types::); instead, if you specify `%T', you will have to directly pass an OOP for the new CObject's type. For `%B' you should not pass a selector, and the block will be evaluated. The type specifiers you can pass for "result_type" are a bit different: Result Specifier if nil C data type expected result i 0L long nil or an Integer f 0.0 double nil or a Float F 0.0 long double nil or a Float b 0 int nil or a Boolean c '\0' char nil or a Character C NULL PTR nil or a CObject s NULL char * nil, a String, or a Symbol ? 0 char *, PTR See oopToC o nilOOP OOP any (result is not converted) w '\0' wchar_t nil or a Character W NULL wchar_t * nil or a UnicodeString v / any (result is discarded) Note that, if resultPtr is `NULL', the "result_type" is always treated as `%v'. If an error occurs, the value in the `result if nil' column is returned.  File: gst.info, Node: Smalltalk callbacks, Next: Object representation, Prev: Smalltalk callin, Up: C and Smalltalk 5.6 Smalltalk blocks as C function pointers =========================================== The Smalltalk callin mechanism can be used effectively to construct bindings to C libraries that require callbacks into Smalltalk. However, it is a "static" mechanism, as the callback functions passed to the libraries have to be written in C and their type signatures are fixed. If the signatures of the callbacks are not known in advance, and the only way to define callbacks is via C function pointers (as opposed to reflective mechanisms such as the ones in GTK+), then the `VMProxy' functions for Smalltalk callin are not enough. GNU Smalltalk provides a more dynamic way to convert Smalltalk blocks into C function pointers through the `CCallbackDescriptor' class. This class has a constructor method that is similar to the `cCall:' annotation used for callouts. The method is called `for:returning:withArgs:' and its parameters are: * a block, whose number of arguments is variable * a symbol representing the return type * an array representing the type of the arguments. The array passed as the third parameter represents values that are passed _from C to Smalltalk_ and, as such, should be filled with the same rules that are used by the _return type_ of a C callout. In particular, if the C callback accepts an `int *' it is possible (and indeed useful) to specify the type of the argument as `#{CInt}', so that the block will receive a `CInt' object. Here is an example of creating a callback which is passed to `glutReshapeFunc'(1). The desired signature in C is `void (*) (int, int)'. | glut | ... glut glutReshapeFunc: (CCallbackDescriptor for: [ :x :y | self reshape: x@y ] returning: #void withArgs: #(#int #int)) It is important to note that this kind of callback does not survive across an image load (this restriction may be lifted in a future version). When the image is loaded, it has to be reset by sending it the `link' message before it is passed to any C function. Sending the `link' message to an already valid callback is harmless and cheap. ---------- Footnotes ---------- (1) The GLUT bindings use a different scheme for setting up callbacks.  File: gst.info, Node: Other C functions, Next: Using Smalltalk, Prev: Incubator, Up: C and Smalltalk 5.7 Other functions available to modules ======================================== In addition to the functions described so far, the `VMProxy' that is available to modules contains entry-points for many functions that aid in developing GNU Smalltalk extensions in C. This node documents these functions and the macros that are defined by `libgst/gstpub.h'. -- Function: void asyncCall (void (*) (OOP), OOP) This functions accepts a function pointer and an OOP (or `NULL', but not an arbitrary pointer) and sets up the interpreter to call the function as soon as the next message send is executed. _Caution:_ This and the next two are the only functions in the `intepreterProxy' that are thread-safe. -- Function: void asyncSignal (OOP) This functions accepts an OOP for a `Semaphore' object and signals that object so that one of the processes waiting on that semaphore is waken up. Since a Smalltalk call-in is not an atomic operation, the correct way to signal a semaphore is not to send the `signal' method to the object but, rather, to use: asyncSignal(semaphoreOOP) The signal request will be processed as soon as the next message send is executed. -- Function: void asyncSignalAndUnregister (OOP) This functions accepts an OOP for a `Semaphore' object and signals that object so that one of the processes waiting on that semaphore is waken up; the signal request will be processed as soon as the next message send is executed. The object is then removed from the registry. -- Function: void wakeUp (void) When no Smalltalk process is running, GNU Smalltalk tries to limit CPU usage by pausing until it gets a signal from the OS. `wakeUp' is an alternative way to wake up the main Smalltalk loop. This should rarely be necessary, since the above functions already call it automatically. -- Function: void syncSignal (OOP, mst_Boolean) This functions accepts an OOP for a `Semaphore' object and signals that object so that one of the processes waiting on that semaphore is waken up. If the semaphore has no process waiting in the queue and the second argument is true, an excess signal is added to the semaphore. Since a Smalltalk call-in is not an atomic operation, the correct way to signal a semaphore is not to send the `signal' or `notify' methods to the object but, rather, to use: syncSignal(semaphoreOOP, true) The `sync' in the name of this function distinguishes it from `asyncSignal', in that it can only be called from a procedure already scheduled with `asyncCall'. It cannot be called from a call-in, or from other threads than the interpreter thread. -- Function: void syncWait (OOP) This function is present for backwards-compatibility only and should not be used. -- Function: void showBacktrace (FILE *) This functions show a backtrace on the given file. -- Function: OOP objectAlloc (OOP, int) The `objectAlloc' function allocates an OOP for a newly created instance of the class whose OOP is passed as the first parameter; if that parameter is not a class the results are undefined (for now, read as "the program will most likely core dump", but that could change in a future version). The second parameter is used only if the class is an indexable one, otherwise it is discarded: it contains the number of indexed instance variables in the object that is going to be created. Simple uses of `objectAlloc' include: OOP myClassOOP; OOP myNewObject; myNewObjectData obj; ... myNewObject = objectAlloc(myClassOOP, 0); obj = (myNewObjectData) OOP_TO_OBJ (myNewObject); obj->arguments = objectAlloc(classNameToOOP("Array"), 10); ... -- Function: size_t OOPSize (OOP) Return the number of indexed instance variables in the given object. -- Function: OOP OOPAt (OOP, size_t) Return an indexed instance variable of the given object. The index is in the second parameter and is zero-based. The function aborts if the index is out of range. -- Function: OOP OOPAtPut (OOP, size_t, OOP) Put the object given as the third parameter into an indexed instance variable of the object given as the first parameter. The index in the second parameter and is zero-based. The function aborts if the index is out of range. The function returns the old value of the indexed instance variable. -- Function: enum gst_indexed_kind OOPIndexedKind (OOP) Return the kind of indexed instance variables that the given object has. -- Function: void * OOPIndexedBase (OOP) Return a pointer to the first indexed instance variable of the given object. The program should first retrieve the kind of data using OOPIndexedKind. -- Function: OOP getObjectClass (OOP) Return the class of the Smalltalk object passed as a parameter. -- Function: OOP getSuperclass (OOP) Return the superclass of the class given by the Smalltalk object, that is passed as a parameter. -- Function: mst_Boolean classIsKindOf (OOP, OOP) Return true if the class given as the first parameter, is the same or a superclass of the class given as the second parameter. -- Function: mst_Boolean objectIsKindOf (OOP, OOP) Return true if the object given as the first parameter is an instance of the class given as the second parameter, or of any of its subclasses. -- Function: mst_Boolean classImplementsSelector (OOP, OOP) Return true if the class given as the first parameter implements or overrides the method whose selector is given as the second parameter. -- Function: mst_Boolean classCanUnderstand (OOP, OOP) Return true if instances of the class given as the first parameter respond to the message whose selector is given as the second parameter. -- Function: mst_Boolean respondsTo (OOP, OOP) Return true if the object given as the first parameter responds to the message whose selector is given as the second parameter. Finally, several slots of the interpreter proxy provide access to the system objects and to the most important classes. These are: * `nilOOP', `trueOOP', `falseOOP', `processorOOP' * `objectClass', `arrayClass', `stringClass', `characterClass', `smallIntegerClass', `floatDClass', `floatEClass', `byteArrayClass', `objectMemoryClass', `classClass', `behaviorClass', `blockClosureClass', `contextPartClass', `blockContextClass', `methodContextClass', `compiledMethodClass', `compiledBlockClass', `fileDescriptorClass', `fileStreamClass', `processClass', `semaphoreClass', `cObjectClass' More may be added in the future The macros are(1): -- Macro: gst_object OOP_TO_OBJ (OOP) Dereference a pointer to an OOP into a pointer to the actual object data (*note Object representation::). The result of `OOP_TO_OBJ' is not valid anymore if a garbage-collection happens; for this reason, you should assume that a pointer to object data is not valid after doing a call-in, calling `objectAlloc', and caling any of the "C to Smalltalk" functions (*note Smalltalk types::). -- Macro: OOP OOP_CLASS (OOP) Return the OOP for the class of the given object. For example, `OOP_CLASS(proxy->stringToOOP("Wonderful GNU Smalltalk"))' is the `String' class, as returned by `classNameToOOP("String")'. -- Macro: mst_Boolean IS_INT (OOP) Return a Boolean indicating whether or not the OOP is an Integer object; the value of SmallInteger objects is encoded directly in the OOP, not separately in a `gst_object' structure. It is not safe to use `OOP_TO_OBJ' and `OOP_CLASS' if `isInt' returns false. -- Macro: mst_Boolean IS_OOP (OOP) Return a Boolean indicating whether or not the OOP is a `real' object (and not a SmallInteger). It is safe to use `OOP_TO_OBJ' and `OOP_CLASS' only if `IS_OOP' returns true. -- Macro: mst_Boolean ARRAY_OOP_AT (gst_object, int) Access the character given in the second parameter of the given Array object. Note that this is necessary because of the way `gst_object' is defined, which prevents `indexedOOP' from working. -- Macro: mst_Boolean STRING_OOP_AT (gst_object, int) Access the character given in the second parameter of the given String or ByteArray object. Note that this is necessary because of the way `gst_object' is defined, which prevents `indexedByte' from working. -- Macro: mst_Boolean INDEXED_WORD (SOME-OBJECT-TYPE, int) Access the given indexed instance variable in a `variableWordSubclass'. The first parameter must be a structure declared as described in *note Object representation::). -- Macro: mst_Boolean INDEXED_BYTE (SOME-OBJECT-TYPE, int) Access the given indexed instance variable in a `variableByteSubclass'. The first parameter must be a structure declared as described in *note Object representation::). -- Macro: mst_Boolean INDEXED_OOP (SOME-OBJECT-TYPE, int) Access the given indexed instance variable in a `variableSubclass'. The first parameter must be a structure declared as described in *note Object representation::). ---------- Footnotes ---------- (1) IS_NIL and IS_CLASS have been removed because they are problematic in shared libraries (modules), where they caused undefined symbols to be present in the shared library. These are now private to `libgst.a'. You should use the `nilOOP' field of the interpreter proxy, or `getObjectClass'.  File: gst.info, Node: Object representation, Next: Incubator, Prev: Smalltalk callbacks, Up: C and Smalltalk 5.8 Manipulating instances of your own Smalltalk classes from C =============================================================== Although GNU Smalltalk's library exposes functions to deal with instances of the most common base class, it's likely that, sooner or later, you'll want your C code to directly deal with instances of classes defined by your program. There are three steps in doing so: * Defining the Smalltalk class * Defining a C `struct' that maps the representation of the class * Actually using the C struct In this chapter you will be taken through these steps considering the hypotetical task of defining a Smalltalk interface to an SQL server. The first part is also the simplest, since defining the Smalltalk class can be done in a single way which is also easy and very practical; just evaluate the standard Smalltalk code that does that: Object subclass: SQLAction [ | database request | ] SQLAction subclass: SQLRequest [ | returnedRows | ] To define the C `struct' for a class derived from Object, GNU Smalltalk's `gstpub.h' include file defines an `OBJ_HEADER' macro which defines the fields that constitute the header of every object. Defining a `struct' for SQLAction results then in the following code: struct st_SQLAction { OBJ_HEADER; OOP database; OOP request; } The representation of SQLRequest in memory is this: .------------------------------. | common object header | 2 longs |------------------------------| | SQLAction instance variables | | database | 2 longs | request | |------------------------------| | SQLRequest instance variable | | returnedRows | 1 long '------------------------------' A first way to define the struct would then be: typedef struct st_SQLAction { OBJ_HEADER; OOP database; OOP request; OOP returnedRows; } *SQLAction; but this results in a lot of duplicated code. Think of what would happen if you had other subclasses of `SQLAction' such as `SQLObjectCreation', `SQLUpdateQuery', and so on! The solution, which is also the one used in GNU Smalltalk's source code is to define a macro for each superclass, in this way: /* SQLAction |-- SQLRequest | `-- SQLUpdateQuery `-- SQLObjectCreation */ #define ST_SQLACTION_HEADER \ OBJ_HEADER; \ OOP database; \ OOP request /* no semicolon */ #define ST_SQLREQUEST_HEADER \ ST_SQLACTION_HEADER; \ OOP returnedRows /* no semicolon */ typedef struct st_SQLAction { ST_SQLACTION_HEADER; } *SQLAction; typedef struct st_SQLRequest { ST_SQLREQUEST_HEADER; } *SQLRequest; typedef struct st_SQLObjectCreation { ST_SQLACTION_HEADER; OOP newDBObject; } *SQLObjectCreation; typedef struct st_SQLUpdateQuery { ST_SQLREQUEST_HEADER; OOP numUpdatedRows; } *SQLUpdateQuery; Note that the macro you declare is used instead of `OBJ_HEADER' in the declaration of both the superclass and the subclasses. Although this example does not show that, please note that you should not declare anything if the class has indexed instance variables. The first step in actually using your structs is obtaining a pointer to an OOP which is an instance of your class. Ways to do so include doing a call-in, receiving the object from a call-out (using `#smalltalk', `#self' or `#selfSmalltalk' as the type specifier). Let's assume that the `oop' variable contains such an object. Then, you have to dereference the OOP (which, as you might recall from *note Smalltalk types::, point to the actual object only indirectly) and get a pointer to the actual data. You do that with the `OOP_TO_OBJ' macro (note the type casting): SQLAction action = (SQLAction) OOP_TO_OBJ(oop); Now you can use the fields in the object like in this pseudo-code: /* These are retrieved via classNameToOOP and then cached in global variables */ OOP sqlUpdateQueryClass, sqlActionClass, sqlObjectCreationClass; ... invoke_sql_query( vmProxy->oopToCObject(action->database), vmProxy->oopToString(action->request), query_completed_callback, /* Callback function */ oop); /* Passed to the callback */ ... /* Imagine that invoke_sql_query runs asynchronously and calls this when the job is done. */ void query_completed_callback(result, database, request, clientData) struct query_result *result; struct db *database; char *request; OOP clientData; { SQLUpdateQuery query; OOP rows; OOP cObject; /* Free the memory allocated by oopToString */ free(request); if (OOP_CLASS (oop) == sqlActionClass) return; if (OOP_CLASS (oop) == sqlObjectCreationClass) { SQLObjectCreation oc; oc = (SQLObjectCreation) OOP_TO_OBJ (clientData); cObject = vmProxy->cObjectToOOP (result->dbObject) oc->newDBObject = cObject; } else { /* SQLRequest or SQLUpdateQuery */ cObject = vmProxy->cObjectToOOP (result->rows); query = (SQLUpdateQuery) OOP_TO_OBJ (clientData); query->returnedRows = cObject; if (OOP_CLASS (oop) == sqlUpdateQueryClass) query->numReturnedRows = vmProxy->intToOOP (result->count); } } Note that the result of `OOP_TO_OBJ' is not valid anymore if a garbage-collection happens; for this reason, you should assume that a pointer to object data is not valid after doing a call-in, calling `objectAlloc', and using any of the "C to Smalltalk" functions except `intToOOP' (*note Smalltalk types::). That's why I passed the OOP to the callback, not the object pointer itself. If your class has indexed instance variables, you can use the `INDEXED_WORD', `INDEXED_OOP' and `INDEXED_BYTE' macros declared in `gstpub.h', which return an lvalue for the given indexed instance variable--for more information, *note Other C functions::.  File: gst.info, Node: Using Smalltalk, Prev: Other C functions, Up: C and Smalltalk 5.9 Using the Smalltalk environment as an extension library =========================================================== If you are reading this chapter because you are going to write extensions to GNU Smalltalk, this section won't probably interest you. But if you intend to use GNU Smalltalk as a scripting language or an extension language for your future marvellous software projects, you might be interest. How to initialize GNU Smalltalk is most briefly and easily explained by looking at GNU Smalltalk's own source code. For this reason, here is a simplified snippet from `gst-tool.c'. int main(argc, argv) int argc; char **argv; { gst_set_var (GST_VERBOSITY, 1); gst_smalltalk_args (argc - 1, argv + 1); gst_set_executable_path (argv[0]); result = gst_initialize ("KERNEL-DIR", "IMAGE-FILE", GST_NO_TTY); if (result != 0) exit (result < 0 ? 1 : result); if (!gst_process_file ("SOURCE-FILE", GST_DIR_KERNEL_SYSTEM)) perror ("gst: couldn't load `SOURCE-FILE'"); gst_invoke_hook (GST_ABOUT_TO_QUIT); exit (0); } Your initialization code will be almost the same as that in GNU Smalltalk's `main()', with the exception of the call to `gst_process_file'. All you'll have to do is to pass some arguments to the GNU Smalltalk library via `gst_smalltalk_args', possibly modify some defaults using `gst_get_var' and `gst_set_var', and then call `gst_initialize'. Variable indices that can be passed to `gst_get_var' and `gst_set_var' include: `GST_DECLARE_TRACING' `GST_EXECUTION_TRACING' `GST_EXECUTION_TRACING_VERBOSE' `GST_GC_MESSAGE' `GST_VERBOSITY' `GST_MAKE_CORE_FILE' `GST_REGRESSION_TESTING' While the flags that can be passed as the last parameter to `gst_initialize' are any combination of these: `GST_REBUILD_IMAGE' `GST_MAYBE_REBUILD_IMAGE' `GST_IGNORE_USER_FILES' `GST_IGNORE_BAD_IMAGE_NAME' `GST_IGNORE_BAD_IMAGE_PATH' `GST_IGNORE_BAD_KERNEL_PATH' `GST_NO_TTY' Note that `gst_initialize' will likely take some time (from a tenth of a second to 3-4 seconds), because it has to check if the image file must be be rebuilt and, if so, it reloads and recompiles the over 50,000 lines of Smalltalk code that form a basic image. To avoid this check, pass a valid image file as the second argument to `gst_initialize'. The result of `gst_init_smalltalk' is `0' for success, while anything else is an error code. If you're using GNU Smalltalk as an extension library, you might also want to disable the two `ObjectMemory' class methods, `quit' and `quit:' method. I advice you not to change the Smalltalk kernel code. Instead, in the script that loads your extension classes add these two lines: ObjectMemory class compile: 'quit self shouldNotImplement'! ObjectMemory class compile: 'quit: n self shouldNotImplement'! which will effectively disable the two offending methods. Other possibilities include using `atexit' (from the C library) to exit your program in a less traumatic way, or redefining these two methods to exit through a call out to a C routine in your program. Also, note that it is not a problem if you develop the class libraries for your programs within GNU Smalltalk's environment (which will not call `defineCFunc' for your own C call-outs), since the addresses of the C call-outs are looked up again when an image is restored.  File: gst.info, Node: Incubator, Next: Other C functions, Prev: Object representation, Up: C and Smalltalk 5.10 Incubator support ====================== The incubator concept provides a mechanism to protect newly created objects from being accidentally garbage collected before they can be attached to some object which is reachable from the root set. If you are creating some set of objects which will not be immediately (that means, before the next object is allocated from the Smalltalk memory system) be attached to an object which is still "live" (reachable from the root set of objects), you'll need to use this interface. If you are writing a C call-out from Smalltalk (for example, inside a module), you will not have direct access to the incubator; instead the functions described in *note Smalltalk types:: automatically put the objects that they create in the incubator, and the virtual machine takes care of wrapping C call-outs so that the incubator state is restored at the end of the call. This section describes its usage from the point of view of a program that is linking with `libgst.a'. Such a program has much finer control to the incubator. The interface provides the following operations: -- Macro: void INC_ADD_OOP (OOP anOOP) Adds a new object to the protected set. -- Macro: inc_ptr INC_SAVE_POINTER () Retrieves the current incubator pointer. Think of the incubator as a stack, and this operation returns the current stack pointer for later use (restoration) with the incRestorePointer function. -- Macro: void INC_RESTORE_POINTER (inc_ptr ptr) Sets (restores) the incubator pointer to the given pointer value. Typically, when you are within a function which allocates more than one object at a time, either directly or indirectly, you'd want to use the incubator mechanism. First you'd save a copy of the current pointer in a local variable. Then, for each object you allocate (except the last, if you want to be optimal), after you create the object you add it to the incubator's list. When you return, you need to restore the incubator's pointer to the value you got with `INC_SAVE_POINTER' using the `INC_RESTORE_POINTER' macro. Here's an example from cint.c: The old code was (the comments are added for this example): desc = (_gst_cfunc_descriptor) new_instance_with (cFuncDescriptorClass, numArgs); desc->cFunction = _gst_cobject_new (funcAddr); // 1 desc->cFunctionName = _gst_string_new (funcName); // 2 desc->numFixedArgs = FROM_INT (numArgs); desc->returnType = _gst_classify_type_symbol (returnTypeOOP, true); for (i = 1; i <= numArgs; i++) { desc->argTypes[i - 1] = _gst_classify_type_symbol(ARRAY_AT(argsOOP, i), false); } return (_gst_alloc_oop(desc)); `desc' is originally allocated via `newInstanceWith' and `allocOOP', two private routines which are encapsulated by the public routine `objectAlloc'. At "1", more storage is allocated, and the garbage collector has the potential to run and free (since no live object is referring to it) desc's storage. At "2" another object is allocated, and again the potential for losing both `desc' and `desc->cFunction' is there if the GC runs (this actually happened!). To fix this code to use the incubator, modify it like this: OOP descOOP; IncPtr ptr; incPtr = INC_SAVE_POINTER(); desc = (_gst_cfunc_descriptor) new_instance_with (cFuncDescriptorClass, numArgs); descOOP = _gst_alloc_oop(desc); INC_ADD_OOP (descOOP); desc->cFunction = _gst_cobject_new (funcAddr); // 1 INC_ADD_OOP (desc->cFunction); desc->cFunctionName = _gst_string_new (funcName); // 2 /* since none of the rest of the function (or the functions it calls) * allocates any storage, we don't have to add desc->cFunctionName * to the incubator's set of objects, although we could if we wanted * to be completely safe against changes to the implementations of * the functions called from this function. */ desc->numFixedArgs = FROM_INT (numArgs); desc->returnType = _gst_classify_type_symbol (returnTypeOOP, true); for (i = 1; i <= numArgs; i++) { desc->argTypes[i - 1] = _gst_classify_type_symbol(ARRAY_AT(argsOOP, i), false); } return (_gst_alloc_oop(desc)); Note that it is permissible for two or more functions to cooperate with their use of the incubator. For example, say function A allocates some objects, then calls function B which allocates some more objects, and then control returns to A where it does some more execution with the allocated objects. If B is only called by A, B can leave the management of the incubator pointer up to A, and just register the objects it allocates with the incubator. When A does a `INC_RESTORE_POINTER', it automatically clears out the objects that B has registered from the incubator's set of objects as well; the incubator doesn't know about functions A & B, so as far as it is concerned, all of the registered objects were registered from the same function.  File: gst.info, Node: Tutorial, Prev: C and Smalltalk, Up: Top 6 Tutorial ********** What this manual presents This document provides a tutorial introduction to the Smalltalk language in general, and the GNU Smalltalk implementation in particular. It does not provide exhaustive coverage of every feature of the language and its libraries; instead, it attempts to introduce a critical mass of ideas and techniques to get the Smalltalk novice moving in the right direction. Who this manual is written for This manual assumes that the reader is acquainted with the basics of computer science, and has reasonable proficiency with a procedural language such as C. It also assumes that the reader is already familiar with the usual janitorial tasks associated with programming: editing, moving files, and so forth. * Menu: * Getting started:: Starting to explore GNU Smalltalk * Some classes:: Using some of the Smalltalk classes * The hierarchy:: The Smalltalk class hierarchy * Creating classes:: Creating a new class of objects * Creating subclasses:: Adding subclasses to another class * Code blocks (I):: Control structures in Smalltalk * Code blocks (II):: Guess what? More control structures * Debugging:: Things go bad in Smalltalk too! * More subclassing:: Coexisting in the class hierarchy * Streams:: A powerful abstraction useful in scripts * Exception handling:: More sophisticated error handling * Behind the scenes:: Some nice stuff from the Smalltalk innards * And now:: Some final words * The syntax:: For the most die-hard computer scientists  File: gst.info, Node: Getting started, Next: Some classes, Up: Tutorial 6.1 Getting started =================== * Menu: * Starting Smalltalk:: Starting up Smalltalk * Saying hello:: Saying hello * What happened:: But how does it say hello? * Doing math:: Smalltalk too can do it! * Math in Smalltalk:: But in a peculiar way of course...  File: gst.info, Node: Starting Smalltalk, Next: Saying hello, Up: Getting started 6.1.1 Starting up Smalltalk --------------------------- Assuming that GNU Smalltalk has been installed on your system, starting it is as simple as: $ gst the system loads in Smalltalk, and displays a startup banner like: GNU Smalltalk ready st> You are now ready to try your hand at Smalltalk! By the way, when you're ready to quit, you exit Smalltalk by typing `control-D' on an empty line.  File: gst.info, Node: Saying hello, Next: What happened, Prev: Starting Smalltalk, Up: Getting started 6.1.2 Saying hello ------------------ An initial exercise is to make Smalltalk say "hello" to you. Type in the following line (`printNl' is a upper case N and a lower case L): 'Hello, world' printNl The system then prints back 'Hello, world' to you. It prints it twice, the first time because you asked to print and the second time because the snipped evaluated to the 'Hello, world' string.(1) ---------- Footnotes ---------- (1) You can also have the system print out a lot of statistics which provide information on the performance of the underlying Smalltalk engine. You can enable them by starting Smalltalk as: $ gst -V  File: gst.info, Node: What happened, Next: Doing math, Prev: Saying hello, Up: Getting started 6.1.3 What actually happened ---------------------------- The front-line Smalltalk interpreter gathers all text until a '!' character and executes it. So the actual Smalltalk code executed was: 'Hello, world' printNl This code does two things. First, it creates an object of type `String' which contains the characters "Hello, world". Second, it sends the message named `printNl' to the object. When the object is done processing the message, the code is done and we get our prompt back. You'll notice that we didn't say anything about printing ing the string, even though that's in fact what happened. This was very much on purpose: the code we typed in doesn't know anything about printing strings. It knew how to get a string object, and it knew how to send a message to that object. That's the end of the story for the code we wrote. But for fun, let's take a look at what happened when the string object received the `printNl' message. The string object then went to a table (1) which lists the messages which strings can receive, and what code to execute. It found that there is indeed an entry for `printNl' in that table and ran this code. This code then walked through its characters, printing each of them out to the terminal. (2) The central point is that an object is entirely self-contained; only the object knew how to print itself out. When we want an object to print out, we ask the object itself to do the printing. ---------- Footnotes ---------- (1) Which table? This is determined by the type of the object. An object has a type, known as the class to which it belongs. Each class has a table of methods. For the object we created, it is known as a member of the `String' class. So we go to the table associated with the String class. (2) Actually, the message `printNl' was inherited from Object. It sent a `print' message, also inherited by Object, which then sent `printOn:' to the object, specifying that it print to the `Transcript' object. The String class then prints its characters to the standard output.  File: gst.info, Node: Doing math, Next: Math in Smalltalk, Prev: What happened, Up: Getting started 6.1.4 Doing math ---------------- A similar piece of code prints numbers: 1234 printNl Notice how we used the same message, but have sent it to a new type of object--an integer (from class `Integer'). The way in which an integer is printed is much different from the way a string is printed on the inside, but because we are just sending a message, we do not have to be aware of this. We tell it to `printNl', and it prints itself out. As a user of an object, we can thus usually send a particular message and expect basically the same kind of behavior, regardless of object's internal structure (for instance, we have seen that sending `printNl' to an object makes the object print itself). In later chapters we will see a wide range of types of objects. Yet all of them can be printed out the same way--with `printNl'. White space is ignored, except as it separates words. This example could also have looked like: 1234 printNl However, GNU Smalltalk tries to execute each line by itself if possible. If you wanted to write the code on two lines, you might have written something like: (1234 printNl) From now on, we'll omit `printNl' since GNU Smalltalk does the service of printing the answer for us. An integer can be sent a number of messages in addition to just printing itself. An important set of messages for integers are the ones which do math: 9 + 7 Answers (correctly!) the value 16. The way that it does this, however, is a significant departure from a procedural language.  File: gst.info, Node: Math in Smalltalk, Prev: Doing math, Up: Getting started 6.1.5 Math in Smalltalk ----------------------- In this case, what happened was that the object `9' (an Integer), received a `+' message with an argument of `7' (also an Integer). The `+' message for integers then caused Smalltalk to create a new object `16' and return it as the resultant object. This `16' object was then given the `printNl' message, and printed `16' on the terminal. Thus, math is not a special case in Smalltalk; it is done, exactly like everything else, by creating objects, and sending them messages. This may seem odd to the Smalltalk novice, but this regularity turns out to be quite a boon: once you've mastered just a few paradigms, all of the language "falls into place". Before you go on to the next chapter, make sure you try math involving `*' (multiplication), `-' (subtraction), and `/' (division) also. These examples should get you started: 8 * (4 / 2) 8 - (4 + 1) 5 + 4 2/3 + 7 2 + 3 * 4 2 + (3 * 4)  File: gst.info, Node: Some classes, Next: The hierarchy, Prev: Getting started, Up: Tutorial 6.2 Using some of the Smalltalk classes ======================================= This chapter has examples which need a place to hold the objects they create. Such place is created automatically as necessary; when you want to discard all the objects you stored, write an exclamation mark at the end of the statement. Now let's create some new objects. * Menu: * Arrays:: An array in Smalltalk * Sets:: A set in Smalltalk * Dictionaries:: Getting more sophisticated, eh? * Closing thoughts:: There always ought to be some closing thoughts  File: gst.info, Node: Arrays, Next: Sets, Up: Some classes 6.2.1 An array in Smalltalk --------------------------- An array in Smalltalk is similar to an array in any other language, although the syntax may seem peculiar at first. To create an array with room for 20 elements, do(1): x := Array new: 20 The `Array new: 20' creates the array; the `x :=' part connects the name `x' with the object. Until you assign something else to `x', you can refer to this array by the name `x'. Changing elements of the array is not done using the `:=' operator; this operator is used only to bind names to objects. In fact, you never modify data structures; instead, you send a message to the object, and it will modify itself. For instance: x at: 1 which prints: nil The slots of an array are initially set to "nothing" (which Smalltalk calls `nil'). Let's set the first slot to the number 99: x at: 1 put: 99 and now make sure the 99 is actually there: x at: 1 which then prints out: 99 These examples show how to manipulate an array. They also show the standard way in which messages are passed arguments ments. In most cases, if a message takes an argument, its name will end with `:'.(2) So when we said `x at: 1' we were sending a message to whatever object was currently bound to `x' with an argument of 1. For an array, this results in the first slot of the array being returned. The second operation, `x at: 1 put: 99' is a message with two arguments. It tells the array to place the second argument (99) in the slot specified by the first (1). Thus, when we re-examine the first slot, it does indeed now contain 99. There is a shorthand for describing the messages you send to objects. You just run the message names together. So we would say that our array accepts both the `at:' and `at:put:' messages. There is quite a bit of sanity checking built into an array. The request 6 at: 1 fails with an error; 6 is an integer, and can't be indexed. Further, x at: 21 fails with an error, because the array we created only has room for 20 objects. Finally, note that the object stored in an array is just like any other object, so we can do things like: (x at: 1) + 1 which (assuming you've been typing in the examples) will print 100. ---------- Footnotes ---------- (1) GNU Smalltalk supports completion in the same way as Bash or GDB. To enter the following line, you can for example type `x := Arr new: 20'. This can come in handy when you have to type long names such as `IdentityDictionary', which becomes `IdeD'. Everything starting with a capital letter or ending with a colon can be completed. (2) Alert readers will remember that the math examples of the previous chapter deviated from this.  File: gst.info, Node: Sets, Next: Dictionaries, Prev: Arrays, Up: Some classes 6.2.2 A set in Smalltalk ------------------------ We're done with the array we've been using, so we'll assign something new to our `x' variable. Note that we don't need to do anything special about the old array: the fact that nobody is using it any more will be automatically detected, and the memory reclaimed. This is known as garbage collection and it is generally done when Smalltalk finds that it is running low on memory. So, to get our new object, simply do: x := Set new which creates an empty set. To view its contents, do: x The kind of object is printed out (i.e., `Set'), and then the members are listed within parenthesis. Since it's empty, we see: Set () Now let's toss some stuff into it. We'll add the numbers 5 and 7, plus the string 'foo'. This is also the first example where we're using more than one statement, and thus a good place to present the statement separator--the `.' period: x add: 5. x add: 7. x add: 'foo' Like Pascal, and unlike C, statements are separated rather than terminated. Thus you need only use a `.' when you have finished one statement and are starting another. This is why our last statement, `^r', does not have a `.' following. Once again like Pascal, however, Smalltalk won't complain if your enter a spurious statement separator after the last statement. However, we can save a little typing by using a Smalltalk shorthand: x add: 5; add: 7; add: 'foo' This line does exactly what the previous one did. The trick is that the semicolon operator causes the message to be sent to the same object as the last message sent. So saying `; add: 7' is the same as saying `x add: 7', because `x' was the last thing a message was sent to. This may not seem like such a big savings, but compare the ease when your variable is named `aVeryLongVariableName' instead of just `x'! We'll revisit some other occasions where `;' saves you trouble, but for now let's continue with our set. Type either version of the example, and make sure that we've added 5, 7, and "foo": x we'll see that it now contains our data: Set ('foo' 5 7) What if we add something twice? No problem--it just stays in the set. So a set is like a big checklist--either it's in there, or it isn't. To wit: x add:5; add: 5; add: 5; add: 5; yourself We've added 5 several times, but when we printed our set back out, we just see: Set ('foo' 5 7) `yourself' is commonly sent at the end of the cascade, if what you are interested in is the object itself--in this case, we were not interested in the return value of `add: 5', which happens to be `5' simply. There's nothing magic in `yourself'; it is a unary message like `printNl', which does nothing but returning the object itself. So you can do this too: x yourself What you put into a set with `add:', you can take out with `remove:'. Try: x remove: 5 x printNl The set now prints as: Set ('foo' 7) The "5" is indeed gone from the set. We'll finish up with one more of the many things you can do with a set--checking for membership. Try: x includes: 7 x includes: 5 From which we see that x does indeed contain 7, but not 5. Notice that the answer is printed as `true' or `false'. Once again, the thing returned is an object--in this case, an object known as a boolean. We'll look at the use of booleans later, but for now we'll just say that booleans are nothing more than objects which can only either be true or false--nothing else. So they're very useful for answers to yes or no questions, like the ones we just posed. Let's take a look at just one more kind of data structure:  File: gst.info, Node: Dictionaries, Next: Closing thoughts, Prev: Sets, Up: Some classes 6.2.3 Dictionaries ------------------ A dictionary is a special kind of collection. With a regular array, you must index it with integers. With dictionaries, you can index it with any object at all. Dictionaries thus provide a very powerful way of correlating one piece of information to another. Their only downside is that they are somewhat less efficient than simple arrays. Try the following: y := Dictionary new y at: 'One' put: 1 y at: 'Two' put: 2 y at: 1 put: 'One' y at: 2 put: 'Two' This fills our dictionary in with some data. The data is actually stored in pairs of key and value (the key is what you give to `at:'--it specifies a slot; the value is what is actually stored at that slot). Notice how we were able to specify not only integers but also strings as both the key and the value. In fact, we can use any kind of object we want as either--the dictionary doesn't care. Now we can map each key to a value: y at: 1 y at: 'Two' which prints respectively: 'One' 2 We can also ask a dictionary to print itself: y which prints: Dictionary (1->'One' 2->'Two' 'One'->1 'Two'->2 ) where the first member of each pair is the key, and the second the value. It is now time to take a final look at the objects we have created, and send them to oblivion: y x! The exclamation mark deleted GNU Smalltalk's knowledge of both variables. Asking for them again will return just `nil'.  File: gst.info, Node: Closing thoughts, Prev: Dictionaries, Up: Some classes 6.2.4 Closing thoughts ---------------------- You've seen how Smalltalk provides you with some very powerful data structures. You've also seen how Smalltalk itself uses these same facilities to implement the language. But this is only the tip of the iceberg--Smalltalk is much more than a collection of "neat" facilities to use. The objects and methods which are automatically available are only the beginning of the foundation on which you build your programs--Smalltalk allows you to add your own objects and methods into the system, and then use them along with everything else. The art of programming in Smalltalk is the art of looking at your problems in terms of objects, using the existing object types to good effect, and enhancing Smalltalk with new types of objects. Now that you've been exposed to the basics of Smalltalk manipulation, we can begin to look at this object-oriented technique of programming.  File: gst.info, Node: The hierarchy, Next: Creating classes, Prev: Some classes, Up: Tutorial 6.3 The Smalltalk class hierarchy ================================= When programming in Smalltalk, you sometimes need to create new kinds of objects, and define what various messages will do to these objects. In the next chapter we will create some new classes, but first we need to understand how Smalltalk organizes the types and objects it contains. Because this is a pure "concept" chapter, without any actual Smalltalk code to run, we will keep it short and to the point. * Menu: * Class Object:: The grandfather of every class * Animals:: A classic in learning OOP! * But why:: The bottom line of the class hierarchy  File: gst.info, Node: Class Object, Next: Animals, Up: The hierarchy 6.3.1 Class `Object' -------------------- Smalltalk organizes all of its classes as a tree hierarchy. At the very top of this hierarchy is class Object. Following somewhere below it are more specific classes, such as the ones we've worked with--strings, integers, arrays, and so forth. They are grouped together based on their similarities; for instance, types of objects which may be compared as greater or less than each other fall under a class known as Magnitude. One of the first tasks when creating a new object is to figure out where within this hierarchy your object falls. Coming up with an answer to this problem is at least as much art as science, and there are no hard-and-fast rules to nail it down. We'll take a look at three kinds of objects to give you a feel for how this organization matters.  File: gst.info, Node: Animals, Next: But why, Prev: Class Object, Up: The hierarchy 6.3.2 Animals ------------- Imagine that we have three kinds of objects, representing Animals, Parrots, and Pigs. Our messages will be eat, sing, and snort. Our first pass at inserting these objects into the Smalltalk hierarchy would organize them like: Object Animals Parrots Pigs This means that Animals, Parrots, and Pigs are all direct descendants of Object, and are not descendants of each other. Now we must define how each animal responds to each kind of message. Animals eat -> Say "I have now eaten" sing -> Error snort -> Error Parrots eat -> Say "I have now eaten" sing -> Say "Tweet" snort -> Error Pigs eat -> Say "I have now eaten"" sing -> Error snort -> Say "Oink" Notice how we kept having to indicate an action for eat. An experienced object designer would immediately recognize this as a clue that we haven't set up our hierarchy correctly. Let's try a different organization: Object Animals Parrots Pigs That is, Parrots inherit from Animals, and Pigs from Parrots. Now Parrots inherit all of the actions from Animals, and Pigs from both Parrots and Animals. Because of this inheritance, we may now define a new set of actions which spares us the redundancy of the previous set: Animals eat -> Say "I have now eaten" sing -> Error snort -> Error Parrots sing -> Say "Tweet" Pigs snort -> Say "Oink" Because Parrots and Pigs both inherit from Animals, we have only had to define the eat action once. However, we have made one mistake in our class setup--what happens when we tell a Pig to sing? It says "Tweet", because we have put Pigs as an inheritor of Parrots. Let's try one final organization: Object Animals Parrots Pigs Now Parrots and Pigs inherit from Animals, but not from each other. Let's also define one final pithy set of actions: Animals eat -> Say "I have eaten" Parrots sing -> Say "Tweet" Pigs snort -> Say "Oink" The change is just to leave out messages which are inappropriate. If Smalltalk detects that a message is not known by an object or any of its ancestors, it will automatically give an error--so you don't have to do this sort of thing yourself. Notice that now sending sing to a Pig does indeed not say "Tweet"--it will cause a Smalltalk error instead.  File: gst.info, Node: But why, Prev: Animals, Up: The hierarchy 6.3.3 The bottom line of the class hierarchy -------------------------------------------- The goal of the class hierarchy is to allow you to organize objects into a relationship which allows a particular object to inherit the code of its ancestors. Once you have identified an effective organization of types, you should find that a particular technique need only be implemented once, then inherited by the children below. This keeps your code smaller, and allows you to fix a bug in a particular algorithm in only once place--then have all users of it just inherit the fix. You will find your decisions for adding objects change as you gain experience. As you become more familiar with the existing set of objects and messages, your selections will increasingly "fit in" with the existing ones. But even a Smalltalk pro stops and thinks carefully at this stage, so don't be daunted if your first choices seem difficult and error-prone.  File: gst.info, Node: Creating classes, Next: Creating subclasses, Prev: The hierarchy, Up: Tutorial 6.4 Creating a new class of objects =================================== With the basic techniques presented in the preceding chapters, we're ready do our first real Smalltalk program. In this chapter we will construct three new types of objects (known as classes), using the Smalltalk technique of inheritance to tie the classes together, create new objects belonging to these classes (known as creating instances of the class), and send messages to these objects. We'll exercise all this by implementing a toy home-finance accounting system. We will keep track of our overall cash, and will have special handling for our checking and savings accounts. From this point on, we will be defining classes which will be used in future chapters. Since you will probably not be running this whole tutorial in one Smalltalk session, it would be nice to save off the state of Smalltalk and resume it without having to retype all the previous examples. To save the current state of GNU Smalltalk, type: ObjectMemory snapshot: 'myimage.im' and from your shell, to later restart Smalltalk from this "snapshot": $ gst -I myimage.im Such a snapshot currently takes a little more than a megabyte, and contains all variables, classes, and definitions you have added. * Menu: * A new class:: Creating a new class * Documenting the class:: So anybody will know what it's about * Defining methods:: So it will be useful * Instance methods:: One of two kind of methods (the others, class methods, are above) * A look at our object:: which will sorely show that something is still missing. * Moving money around:: Let's make it more fun! * Next coming:: Yeah, what's next?!?  File: gst.info, Node: A new class, Next: Documenting the class, Up: Creating classes 6.4.1 Creating a new class -------------------------- Guess how you create a new class? This should be getting monotonous by now--by sending a message to an object. The way we create our first "custom" class is by sending the following message: Object subclass: #Account. Account instanceVariableNames: 'balance'. Quite a mouthful, isn't it? GNU Smalltalk provides a simpler way to write this, but for now let's stick with this. Conceptually, it isn't really that bad. The Smalltalk variable Object is bound to the grand-daddy of all classes on the system. What we're doing here is telling the Object class that we want to add to it a subclass known as Account. Then, `instanceVariableNames: 'balance'' tells the new class that each of its objects ("instances") will have a hidden variable named `balance'.  File: gst.info, Node: Documenting the class, Next: Defining methods, Prev: A new class, Up: Creating classes 6.4.2 Documenting the class --------------------------- The next step is to associate a description with the class. You do this by sending a message to the new class: Account comment: 'I represent a place to deposit and withdraw money' A description is associated with every Smalltalk class, and it's considered good form to add a description to each new class you define. To get the description for a given class: Account comment And your string is printed back to you. Try this with class Integer, too: Integer comment However, there is another way to define classes. This still translates to sending objects, but looks more like a traditional programming language or scripting language: Object subclass: Account [ | balance | ] This has created a class. If we want to access it again, for example to modify the comment, we can do so like this: Account extend [ ] This instructs Smalltalk to pick an existing class, rather than trying to create a subclass.  File: gst.info, Node: Defining methods, Next: Instance methods, Prev: Documenting the class, Up: Creating classes 6.4.3 Defining a method for the class ------------------------------------- We have created a class, but it isn't ready to do any work for us--we have to define some messages which the class can process first. We'll start at the beginning by defining methods for instance creation: Account class extend [ new [ | r | r := super new. r init. ^r ] ] The important points about this are: * `Account class' means that we are defining messages which are to be sent to the Account class itself. * `' is more documentation support; it says that the methods we are defining supports creating objects of type Account. * The text starting with `new [' and ending with `]' defined what action to take for the message `new'. When you enter this definition, GNU Smalltalk will simply give you another prompt, but your method has been compiled in and is ready for use. GNU Smalltalk is pretty quiet on successful method definitions--but you'll get plenty of error messages if there's a problem! If you're familiar with other Smalltalks, note that the body of the method is always in brackets. The best way to describe how this method works is to step through it. Imagine we sent a message to the new class Account with the command line: Account new `Account' receives the message `new' and looks up how to process this message. It finds our new definition, and starts running it. The first line, `| r |', creates a local variable named `r' which can be used as a placeholder for the objects we create. `r' will go away as soon as the message is done being processed; note the parallel with `balance', which goes away as soon as the object is not used anymore. And note that here you have to declare local variables explicitly, unlike what you did in previous examples. The first real step is to actually create the object. The line `r := super new' does this using a fancy trick. The word `super' stands for the same object that the message `new' was originally sent to (remember? it's `Account'), except that when Smalltalk goes to search for the methods, it starts one level higher up in the hierarchy than the current level. So for a method in the Account class, this is the Object class (because the class Account inherits from is Object--go back and look at how we created the Account class), and the Object class' methods then execute some code in response to the `#new' message. As it turns out, Object will do the actual creation of the object when sent a `#new' message. One more time in slow motion: the Account method `#new' wants to do some fiddling about when new objects are created, but he also wants to let his parent do some work with a method of the same name. By saying `r := super new' he is letting his parent create the object, and then he is attaching it to the variable `r'. So after this line of code executes, we have a brand new object of type Account, and `r' is bound to it. You will understand this better as time goes on, but for now scratch your head once, accept it as a recipe, and keep going. We have the new object, but we haven't set it up correctly. Remember the hidden variable `balance' which we saw in the beginning of this chapter? `super new' gives us the object with the `balance' field containing nothing, but we want our balance field to start at 0. (1) So what we need to do is ask the object to set itself up. By saying `r init', we are sending the `init' message to our new Account. We'll define this method in the next section--for now just assume that sending the `init' message will get our Account set up. Finally, we say `^r'. In English, this is return what r is attached to. This means that whoever sent to Account the `new' message will get back this brand new account. At the same time, our temporary variable `r' ceases to exist. ---------- Footnotes ---------- (1) And unlike C, Smalltalk draws a distinction between `0' and `nil'. `nil' is the nothing object, and you will receive an error if you try to do, say, math on it. It really does matter that we initialize our instance variable to the number 0 if we wish to do math on it in the future.  File: gst.info, Node: Instance methods, Next: A look at our object, Prev: Defining methods, Up: Creating classes 6.4.4 Defining an instance method --------------------------------- We need to define the `init' method for our Account objects, so that our `new' method defined above will work. Here's the Smalltalk code: Account extend [ init [ balance := 0 ] ] It looks quite a bit like the previous method definition, except that the first one said `Account class extend', and ours says `Account extend'. The difference is that the first one defined a method for messages sent directly to `Account', but the second one is for messages which are sent to Account objects once they are created. The method named `init' has only one line, `balance := 0'. This initializes the hidden variable `balance' (actually called an instance variable) to zero, which makes sense for an account balance. Notice that the method doesn't end with `^r' or anything like it: this method doesn't return a value to the message sender. When you do not specify a return value, Smalltalk defaults the return value to the object currently executing. For clarity of programming, you might consider explicitly returning `self' in cases where you intend the return value to be used.(1) Before going on, ere is how you could have written this code in a single declaration (i.e. without using `extend'): Object subclass: Account [ | balance | Account class >> new [ | r | r := super new. r init. ^r ] init [ balance := 0 ] ] ---------- Footnotes ---------- (1) And why didn't the designers default the return value to nil? Perhaps they didn't appreciate the value of void functions. After all, at the time Smalltalk was being designed, C didn't even have a void data type.  File: gst.info, Node: A look at our object, Next: Moving money around, Prev: Instance methods, Up: Creating classes 6.4.5 Looking at our Account ---------------------------- Let's create an instance of class Account: a := Account new Can you guess what this does? The `Smalltalk at: #a put: ' creates a Smalltalk variable. And the `Account new' creates a new Account, and returns it. So this line creates a Smalltalk variable named `a', and attaches it to a new Account--all in one line. It also prints the Account object we just created: an Account Hmmm... not very informative. The problem is that we didn't tell our Account how to print itself, so we're just getting the default system `printNl' method--which tells what the object is, but not what it contains. So clearly we must add such a method: Account extend [ printOn: stream [ super printOn: stream. stream nextPutAll: ' with balance: '. balance printOn: stream ] ] Now give it a try again: a which prints: an Account with balance: 0 This may seem a little strange. We added a new method, printOn:, and our printNl message starts behaving differently. It turns out that the printOn: message is the central printing function--once you've defined it, all of the other printing methods end up calling it. Its argument is a place to print to--quite often it is the variable `Transcript'. This variable is usually hooked to your terminal, and thus you get the printout to your screen. The `super printOn: stream' lets our parent do what it did before--print out what our type is. The `an Account' part of the printout came from this. `stream nextPutAll: ' with balance: '' creates the string ` with balance: ', and prints it out to the stream, too; note that we don't use `printOn:' here because that would enclose our string within quotes. Finally, `balance printOn: stream' asks whatever object is hooked to the `balance' variable to print itself to the stream. We set `balance' to 0, so the 0 gets printed out.  File: gst.info, Node: Moving money around, Next: Next coming, Prev: A look at our object, Up: Creating classes 6.4.6 Moving money around ------------------------- We can now create accounts, and look at them. As it stands, though, our balance will always be 0--what a tragedy! Our final methods will let us deposit and spend money. They're very simple: Account extend [ spend: amount [ balance := balance - amount ] deposit: amount [ balance := balance + amount ] ] With these methods you can now deposit and spend amounts of money. Try these operations: a deposit: 125 a deposit: 20 a spend: 10  File: gst.info, Node: Next coming, Prev: Moving money around, Up: Creating classes 6.4.7 What's next? ------------------ We now have a generic concept, an "Account". We can create them, check their balance, and move money in and out of them. They provide a good foundation, but leave out important information that particular types of accounts might want. In the next chapter, we'll take a look at fixing this problem using subclasses.  File: gst.info, Node: Creating subclasses, Next: Code blocks (I), Prev: Creating classes, Up: Tutorial 6.5 Two Subclasses for the Account Class ======================================== This chapter continues from the previous chapter in demonstrating how one creates classes and subclasses in Smalltalk. In this chapter we will create two special subclasses of Account, known as Checking and Savings. We will continue to inherit the capabilities of Account, but will tailor the two kinds of objects to better manage particular kinds of accounts. * Menu: * The Savings class:: One of the two subclasses we'll put together * The Checking class:: And here is the other * Writing checks:: Only in Smalltalk, of course  File: gst.info, Node: The Savings class, Next: The Checking class, Up: Creating subclasses 6.5.1 The Savings class ----------------------- We create the Savings class as a subclass of Account. It holds money, just like an Account, but has an additional property that we will model: it is paid interest based on its balance. We create the class Savings as a subclass of Account. Account subclass: Savings [ | interest | This is already telling something: the instance variable `interest' will accumulate interest paid. Thus, in addition to the `spend:' and `deposit:' messages which we inherit from our parent, Account, we will need to define a method to add in interest deposits, and a way to clear the interest variable (which we would do yearly, after we have paid taxes). We first define a method for allocating a new account--we need to make sure that the interest field starts at 0. We can do so within the `Account subclass: Savings' scope, which we have not closed above. init [ interest := 0. ^super init ] Recall that the parent took care of the `new' message, and created a new object of the appropriate size. After creation, the parent also sent an `init' message to the new object. As a subclass of Account, the new object will receive the `init' message first; it sets up its own instance variable, and then passes the `init' message up the chain to let its parent take care of its part of the initialization. With our new `Savings' account created, we can define two methods for dealing specially with such an account: interest: amount [ interest := interest + amount. self deposit: amount ] clearInterest [ | oldinterest | oldinterest := interest. interest := 0. ^oldinterest ] We are now finished, and close the class scope: ] The first method says that we add the `amount' to our running total of interest. The line `self deposit: amount' tells Smalltalk to send ourselves a message, in this case `deposit: amount'. This then causes Smalltalk to look up the method for `deposit:', which it finds in our parent, Account. Executing this method then updates our overall balance.(1) One may wonder why we don't just replace this with the simpler `balance := balance + amount'. The answer lies in one of the philosophies of object-oriented languages in general, and Smalltalk in particular. Our goal is to encode a technique for doing something once only, and then re-using that technique when needed. If we had directly encoded `balance := balance + amount' here, there would have been two places that knew how to update the balance from a deposit. This may seem like a useless difference. But consider if later we decided to start counting the number of deposits made. If we had encoded `balance := balance + amount' in each place that needed to update the balance, we would have to hunt each of them down in order to update the count of deposits. By sending `self' the message `deposit:', we need only update this method once; each sender of this message would then automatically get the correct up-to-date technique for updating the balance. The second method, `clearInterest', is simpler. We create a temporary variable `oldinterest' to hold the current amount of interest. We then zero out our interest to start the year afresh. Finally, we return the old interest as our result, so that our year-end accountant can see how much we made.(2) ---------- Footnotes ---------- (1) `self' is much like `super', except that `self' will start looking for a method at the bottom of the type hierarchy for the object, while `super' starts looking one level up from the current level. Thus, using `super' forces inheritance, but `self' will find the first definition of the message which it can. (2) Of course, in a real accounting system we would never discard such information--we'd probably throw it into a Dictionary object, indexed by the year that we're finishing. The ambitious might want to try their hand at implementing such an enhancement.  File: gst.info, Node: The Checking class, Next: Writing checks, Prev: The Savings class, Up: Creating subclasses 6.5.2 The Checking class ------------------------ Our second subclass of Account represents a checking account. We will keep track of two facets: * What check number we are on * How many checks we have left in our checkbook We will define this as another subclass of Account: Account subclass: Checking [ | checknum checksleft | We have two instance variables, but we really only need to initialize one of them--if there are no checks left, the current check number can't matter. Remember, our parent class Account will send us the `init' message. We don't need our own class-specific `new' function, since our parent's will provide everything we need. init [ checksleft := 0. ^super init ] As in Savings, we inherit most of abilities from our superclass, Account. For initialization, we leave `checknum' alone, but set the number of checks in our checkbook to zero. We finish by letting our parent class do its own initialization.  File: gst.info, Node: Writing checks, Prev: The Checking class, Up: Creating subclasses 6.5.3 Writing checks -------------------- We will finish this chapter by adding a method for spending money through our checkbook. The mechanics of taking a message and updating variables should be familiar: newChecks: number count: checkcount [ checknum := number. checksleft := checkcount ] writeCheck: amount [ | num | num := checknum. checknum := checknum + 1. checksleft := checksleft - 1. self spend: amount. ^ num ] ] `newChecks:' fills our checkbook with checks. We record what check number we're starting with, and update the count of the number of checks in the checkbook. `writeCheck:' merely notes the next check number, then bumps up the check number, and down the check count. The message `self spend: amount' resends the message `spend:' to our own object. This causes its method to be looked up by Smalltalk. The method is then found in our parent class, Account, and our balance is then updated to reflect our spending. You can try the following examples: c := Checking new c deposit: 250 c newChecks: 100 count: 50 c writeCheck: 32 c For amusement, you might want to add a printOn: message to the checking class so you can see the checking-specific information. In this chapter, you have seen how to create subclasses of your own classes. You have added new methods, and inherited methods from the parent classes. These techniques provide the majority of the structure for building solutions to problems. In the following chapters we will be filling in details on further language mechanisms and types, and providing details on how to debug software written in Smalltalk.  File: gst.info, Node: Code blocks (I), Next: Code blocks (II), Prev: Creating subclasses, Up: Tutorial 6.6 Code blocks =============== The Account/Saving/Checking example from the last chapter has several deficiencies. It has no record of the checks and their values. Worse, it allows you to write a check when there are no more checks--the Integer value for the number of checks will just calmly go negative! To fix these problems we will need to introduce more sophisticated control structures. * Menu: * Conditions:: Making some decisions * Iteration:: Making some loops  File: gst.info, Node: Conditions, Next: Iteration, Up: Code blocks (I) 6.6.1 Conditions and decision making ------------------------------------ Let's first add some code to keep you from writing too many checks. We will simply update our current method for the Checking class; if you have entered the methods from the previous chapters, the old definition will be overridden by this new one. Checking extend [ writeCheck: amount [ | num | (checksleft < 1) ifTrue: [ ^self error: 'Out of checks' ]. num := checknum. checknum := checknum + 1. checksleft := checksleft - 1. self spend: amount ^ num ] ] The two new lines are: (checksleft < 1) ifTrue: [ ^self error: 'Out of checks' ]. At first glance, this appears to be a completely new structure. But, look again! The only new construct is the square brackets, which appear within a method and not only surround it. The first line is a simple boolean expression. `checksleft' is our integer, as initialized by our Checking class. It is sent the message `<', and the argument 1. The current number bound to `checksleft' compares itself against 1, and returns a boolean object telling whether it is less than 1. Now this boolean, which is either true or false, is sent the message `ifTrue:', with an argument which is called a code block. A code block is an object, just like any other. But instead of holding a number, or a Set, it holds executable statements. So what does a boolean do with a code block which is an argument to a `ifTrue:' message? It depends on which boolean! If the object is the `true' object, it executes the code block it has been handed. If it is the `false' object, it returns without executing the code block. So the traditional conditional construct has been replaced in Smalltalk with boolean objects which execute the indicated code block or not, depending on their truth-value. (1) In the case of our example, the actual code within the block sends an error message to the current object. `error:' is handled by the parent class Object, and will pop up an appropriate complaint when the user tries to write too many checks. In general, the way you handle a fatal error in Smalltalk is to send an error message to yourself (through the `self' pseudo-variable), and let the error handling mechanisms inherited from the Object class take over. As you might guess, there is also an `ifFalse:' message which booleans accept. It works exactly like `ifTrue:', except that the logic has been reversed; a boolean `false' will execute the code block, and a boolean `true' will not. You should take a little time to play with this method of representing conditionals. You can run your checkbook, but can also invoke the conditional functions directly: true ifTrue: [ 'Hello, world!' printNl ] false ifTrue: [ 'Hello, world!' printNl ] true ifFalse: [ 'Hello, world!' printNl ] false ifFalse: [ 'Hello, world!' printNl ] ---------- Footnotes ---------- (1) It is interesting to note that because of the way conditionals are done, conditional constructs are not part of the Smalltalk language, instead they are merely a defined behavior for the Boolean class of objects.  File: gst.info, Node: Iteration, Prev: Conditions, Up: Code blocks (I) 6.6.2 Iteration and collections ------------------------------- Now that we have some sanity checking in place, it remains for us to keep a log of the checks we write. We will do so by adding a Dictionary object to our Checking class, logging checks into it, and providing some messages for querying our check-writing history. But this enhancement brings up a very interesting question--when we change the "shape" of an object (in this case, by adding our dictionary as a new instance variable to the Checking class), what happens to the existing class, and its objects? The answer is that the old objects are mutated to keep their new shape, and all methods are recompiled so that they work with the new shape. New objects will have exactly the same shape as old ones, but old objects might happen to be initialized incorrectly (since the newly added variables will be simply put to nil). As this can lead to very puzzling behavior, it is usually best to eradicate all of the old objects, and then implement your changes. If this were more than a toy object accounting system, this would probably entail saving the objects off, converting to the new class, and reading the objects back into the new format. For now, we'll just ignore what's currently there, and define our latest Checking class. Checking extend [ | history | This is the same syntax as the last time we defined a checking account, except that we start with `extend' (since the class is already there). Then, the two instance variables we had defined remain, and we add a new `history' variable; the old methods will be recompiled without errors. We must now feed in our definitions for each of the messages our object can handle, since we are basically defining a new class under an old name. With our new Checking instance variable, we are all set to start recording our checking history. Our first change will be in the handling of the `init' message: init [ checksleft := 0. history := Dictionary new. ^ super init ] This provides us with a Dictionary, and hooks it to our new `history' variable. Our next method records each check as it's written. The method is a little more involved, as we've added some more sanity checks to the writing of checks. writeCheck: amount [ | num | "Sanity check that we have checks left in our checkbook" (checksleft < 1) ifTrue: [ ^self error: 'Out of checks' ]. "Make sure we've never used this check number before" num := checknum. (history includesKey: num) ifTrue: [ ^self error: 'Duplicate check number' ]. "Record the check number and amount" history at: num put: amount. "Update our next checknumber, checks left, and balance" checknum := checknum + 1. checksleft := checksleft - 1. self spend: amount. ^ num ] We have added three things to our latest version of `writeCheck:'. First, since our routine has become somewhat involved, we have added comments. In Smalltalk, single quotes are used for strings; double quotes enclose comments. We have added comments before each section of code. Second, we have added a sanity check on the check number we propose to use. Dictionary objects respond to the `includesKey:' message with a boolean, depending on whether something is currently stored under the given key in the dictionary. If the check number is already used, the `error:' message is sent to our object, aborting the operation. Finally, we add a new entry to the dictionary. We have already seen the `at:put:' message (often found written as `#at:put:', with a sharp in front of it) at the start of this tutorial. Our use here simply associates a check number with an amount of money spent.(1) With this, we now have a working Checking class, with reasonable sanity checks and per-check information. Let us finish the chapter by enhancing our ability to get access to all this information. We will start with some simple print-out functions. printOn: stream [ super printOn: stream. ', checks left: ' printOn: stream. checksleft printOn: stream. ', checks written: ' printOn: stream. (history size) printOn: stream. ] check: num [ | c | c := history at: num ifAbsent: [ ^self error: 'No such check #' ]. ^c ] There should be very few surprises here. We format and print our information, while letting our parent classes handle their own share of the work. When looking up a check number, we once again take advantage of the fact that blocks of executable statements are an object; in this case, we are using the `at:ifAbsent:' message supported by the Dictionary class. As you can probably anticipate, if the requested key value is not found in the dictionary, the code block is executed. This allows us to customize our error handling, as the generic error would only tell the user "key not found". While we can look up a check if we know its number, we have not yet written a way to "riffle through" our collection of checks. The following function loops over the checks, printing them out one per line. Because there is currently only a single numeric value under each key, this might seem wasteful. But we have already considered storing multiple values under each check number, so it is best to leave some room for each item. And, of course, because we are simply sending a printing message to an object, we will not have to come back and re-write this code so long as the object in the dictionary honors our `printNl'/`printOn:' messages sages. printChecks [ history keysAndValuesDo: [ :key :value | key print. ' - ' print. value printNl. ] ] ] We still see a code block object being passed to the dictionary, but `:key :value |' is something new. A code block can optionally receive arguments. In this case, the two arguments represent a key/value pair. If you only wanted the value portion, you could call history with a `do:' message instead; if you only wanted the key portion, you could call history with a `keysDo:' message instead. We then invoke our printing interface upon them. We don't want a newline until the end, so the `print' message is used instead. It is pretty much the same as `printNl', since both implicitly use `Transcript', except it doesn't add a newline. It is important that you be clear that in principle there is no relationship between the code block and the dictionary you passed it to. The dictionary just invokes the passed code block with a key/value pair when processing a keysAndValuesDo: message. But the same two-parameter code block can be passed to any message that wishes to evaluate it (and passes the exact number of parameters to it). In the next chapter we'll see more on how code blocks are used; we'll also look at how you can invoke code blocks in your own code. ---------- Footnotes ---------- (1) You might start to wonder what one would do if you wished to associate two pieces of information under one key. Say, the value and who the check was written to. There are several ways; the best would probably be to create a new, custom object which contained this information, and then store this object under the check number key in the dictionary. It would also be valid (though probably overkill) to store a dictionary as the value--and then store as many pieces of information as you'd like under each slot!  File: gst.info, Node: Code blocks (II), Next: Debugging, Prev: Code blocks (I), Up: Tutorial 6.7 Code blocks, part two ========================= In the last chapter, we looked at how code blocks could be used to build conditional expressions, and how you could iterate across all entries in a collection.(1) We built our own code blocks, and handed them off for use by system objects. But there is nothing magic about invoking code blocks; your own code will often need to do so. This chapter will shows some examples of loop construction in Smalltalk, and then demonstrate how you invoke code blocks for yourself. * Menu: * Integer loops:: Well, Smalltalk too has them * Intervals:: And of course here's a peculiar way to use them * Invoking code blocks:: You can do it, too ---------- Footnotes ---------- (1) The `do:' message is understood by most types of Smalltalk collections. It works for the Dictionary class, as well as sets, arrays, strings, intervals, linked lists, bags, and streams. The `keysDo:' message, for example, works only with dictionaries.  File: gst.info, Node: Integer loops, Next: Intervals, Up: Code blocks (II) 6.7.1 Integer loops ------------------- Integer loops are constructed by telling a number to drive the loop. Try this example to count from 1 to 20: 1 to: 20 do: [:x | x printNl ] There's also a way to count up by more than one: 1 to: 20 by: 2 do: [:x | x printNl ] Finally, counting down is done with a negative step: 20 to: 1 by: -1 do: [:x | x printNl ] Note that the `x' variable is local to the block. x just prints `nil'.  File: gst.info, Node: Intervals, Next: Invoking code blocks, Prev: Integer loops, Up: Code blocks (II) 6.7.2 Intervals --------------- It is also possible to represent a range of numbers as a standalone object. This allows you to represent a range of numbers as a single object, which can be passed around the system. i := Interval from: 5 to: 10 i do: [:x | x printNl] As with the integer loops, the Interval class can also represent steps greater than 1. It is done much like it was for our numeric loop above: i := (Interval from: 5 to: 10 by: 2) i do: [:x| x printNl]  File: gst.info, Node: Invoking code blocks, Prev: Intervals, Up: Code blocks (II) 6.7.3 Invoking code blocks -------------------------- Let us revisit the checking example and add a method for scanning only checks over a certain amount. This would allow our user to find "big" checks, by passing in a value below which we will not invoke their function. We will invoke their code block with the check number as an argument ment; they can use our existing check: message to get the amount. Checking extend [ checksOver: amount do: aBlock history keysAndValuesDo: [:key :value | (value > amount) ifTrue: [aBlock value: key] ] ] The structure of this loop is much like our printChecks message sage from chapter 6. However, in this case we consider each entry, and only invoke the supplied block if the check's value is greater than the specified amount. The line: ifTrue: [aBlock value: key] invokes the user-supplied block, passing as an argument the key, which is the check number. The `value:' message, when received by a code block, causes the code block to execute. Code blocks take `value', `value:', `value:value:', and `value:value:value:' messages, so you can pass from 0 to 3 arguments to a code block.(1) You might find it puzzling that an association takes a `value' message, and so does a code block. Remember, each object can do its own thing with a message. A code block gets run when it receives a `value' message. An association merely returns the value part of its key/value pair. The fact that both take the same message is, in this case, coincidence. Let's quickly set up a new checking account with $250 (wouldn't this be nice in real life?) and write a couple checks. Then we'll see if our new method does the job correctly: mycheck := Checking new. mycheck deposit: 250 mycheck newChecks: 100 count: 40 mycheck writeCheck: 10 mycheck writeCheck: 52 mycheck writeCheck: 15 mycheck checksOver: 1 do: [:x | x printNl] mycheck checksOver: 17 do: [:x | x printNl] mycheck checksOver: 200 do: [:x | x printNl] We will finish this chapter with an alternative way of writing our `checksOver:' code. In this example, we will use the message `select:' to pick the checks which exceed our value, instead of doing the comparison ourselves. We can then invoke the new resulting collection against the user's code block. Checking extend [ checksOver: amount do: aBlock [ | chosen | chosen := history select: [:amt| amt > amount]. chosen keysDo: aBlock ] ] Note that `extend' will also overwrite methods. Try the same tests as above, they should yield the same result! ---------- Footnotes ---------- (1) There is also a `valueWithArguments:' message which accepts an array holding as many arguments as you would like.  File: gst.info, Node: Debugging, Next: More subclassing, Prev: Code blocks (II), Up: Tutorial 6.8 When Things Go Bad ====================== So far we've been working with examples which work the first time. If you didn't type them in correctly, you probably received a flood of unintelligible complaints. You probably ignored the complaints, and typed the example again. When developing your own Smalltalk code, however, these messages are the way you find out what went wrong. Because your objects, their methods, the error printout, and your interactive environment are all contained within the same Smalltalk session, you can use these error messages to debug your code using very powerful techniques. * Menu: * Simple errors:: Those that only happen in examples * Nested calls:: Those that actually happen in real life * Looking at objects:: Trying to figure it out  File: gst.info, Node: Simple errors, Next: Nested calls, Up: Debugging 6.8.1 A Simple Error -------------------- First, let's take a look at a typical error. Type: 7 plus: 1 This will print out: 7 did not understand selector 'plus:' UndefinedObject>>#executeStatements The first line is pretty simple; we sent a message to the `7' object which was not understood; not surprising since the `plus:' operation should have been `+'. Then there are a few lines of gobbledegook: just ignore them, they reflect the fact that the error passed throgh GNU Smalltalk's exception handling system. The remaining line reflect the way the GNU Smalltalk invokes code which we type to our command prompt; it generates a block of code which is invoked via an internal method `executeStatements' defined in class Object and evaluated like `nil executeStatements' (nil is an instance of UndefinedObject). Thus, this output tells you that you directly typed a line which sent an invalid message to the `7' object. All the error output but the first line is actually a stack backtrace. The most recent call is the one nearer the top of the screen. In the next example, we will cause an error which happens deeper within an object.  File: gst.info, Node: Nested calls, Next: Looking at objects, Prev: Simple errors, Up: Debugging 6.8.2 Nested Calls ------------------ Type the following lines: x := Dictionary new x at: 1 The error you receive will look like: Dictionary new: 31 "<0x33788>" error: key not found ...blah blah... Dictionary>>#error: [] in Dictionary>>#at: [] in Dictionary>>#at:ifAbsent: Dictionary(HashedCollection)>>#findIndex:ifAbsent: Dictionary>>#at:ifAbsent: Dictionary>>#at: UndefinedObject(Object)>>#executeStatements The error itself is pretty clear; we asked for something within the Dictionary which wasn't there. The object which had the error is identified as `Dictionary new: 31'. A Dictionary's default size is 31; thus, this is the object we created with `Dictionary new'. The stack backtrace shows us the inner structure of how a Dictionary responds to the `#at:' message. Our hand-entered command causes the usual entry for `UndefinedObject(Object)'. Then we see a Dictionary object responding to an `#at:' message (the "Dictionary>>#at:" line). This code called the object with an `#at:ifAbsent:' message. All of a sudden, Dictionary calls that strange method `#findIndex:ifAbsent:', which evaluates two blocks, and then the error happens. To understand this better, it is necessary to know that a very common way to handle errors in Smalltalk is to hand down a block of code which will be called when an error occurs. For the Dictionary code, the `at:' message passes in a block of code to the at:ifAbsent: code to be called when `at:ifAbsent:' can't find the given key, and `at:ifAbsent:' does the same with `findIndex:ifAbsent:'. Thus, without even looking at the code for Dictionary itself, we can guess something of the code for Dictionary's implementation: findIndex: key ifAbsent: errCodeBlock [ ...look for key... (keyNotFound) ifTrue: [ ^(errCodeBlock value) ] ... ] at: key [ ^self at: key ifAbsent: [^self error: 'key not found'] ] Actually, `findIndex:ifAbsent:' lies in class `HashedCollection', as that `Dictionary(HashedCollection)' in the backtrace says. It would be nice if each entry on the stack backtrace included source line numbers. Unfortunately, at this point GNU Smalltalk doesn't provide this feature. Of course, you have the source code available...  File: gst.info, Node: Looking at objects, Prev: Nested calls, Up: Debugging 6.8.3 Looking at Objects ------------------------ When you are chasing an error, it is often helpful to examine the instance variables of your objects. While strategic calls to `printNl' will no doubt help, you can look at an object without having to write all the code yourself. The `inspect' message works on any object, and dumps out the values of each instance variable within the object.(1) Thus: x := Interval from: 1 to: 5. x inspect displays: An instance of Interval start: 1 stop: 5 step: 1 contents: [ [1]: 1 [2]: 2 [3]: 3 [4]: 4 [5]: 5 ] We'll finish this chapter by emphasizing a technique which has already been covered: the use of the `error:' message in your own objects. As you saw in the case of Dictionary, an object can send itself an `error:' message with a descriptive string to abort execution and dump a stack backtrace. You should plan on using this technique in your own objects. It can be used both for explicit user-caused errors, as well as in internal sanity checks. ---------- Footnotes ---------- (1) When using the Blox GUI, it actually pops up a so-called "Inspector window".  File: gst.info, Node: More subclassing, Next: Streams, Prev: Debugging, Up: Tutorial 6.9 Coexisting in the Class Hierarchy ===================================== The early chapters of this tutorial discussed classes in one of two ways. The "toy" classes we developed were rooted at Object; the system-provided classes were treated as immutable entities. While one shouldn't modify the behavior of the standard classes lightly, "plugging in" your own classes in the right place among their system-provided brethren can provide you powerful new classes with very little effort. This chapter will create two complete classes which enhance the existing Smalltalk hierarchy. The discussion will start with the issue of where to connect our new classes, and then continue onto implementation. Like most programming efforts, the result will leave many possibilities for improvements. The framework, however, should begin to give you an intuition of how to develop your own Smalltalk classes. * Menu: * The existing hierarchy:: We've been talking about it for a while, so here it is at last * Playing with Arrays:: Again. * New kinds of Numbers:: Sounds interesting, doesn't it? * Inheritance and Polymorphism:: Sounds daunting, doesn't it?  File: gst.info, Node: The existing hierarchy, Next: Playing with Arrays, Up: More subclassing 6.9.1 The Existing Class Hierarchy ---------------------------------- To discuss where a new class might go, it is helpful to have a map of the current classes. The following is the basic class hierarchy of GNU Smalltalk. Indentation means that the line inherits from the earlier line with one less level of indentation.(1). Object Behavior ClassDescription Class Metaclass BlockClosure Boolean False True Browser CFunctionDescriptor CObject CAggregate CArray CPtr CCompound CStruct CUnion CScalar CChar CDouble CFloat CInt CLong CShort CSmalltalk CString CUChar CByte CBoolean CUInt CULong CUShort Collection Bag MappedCollection SequenceableCollection ArrayedCollection Array ByteArray WordArray LargeArrayedCollection LargeArray LargeByteArray LargeWordArray CompiledCode CompiledMethod CompiledBlock Interval CharacterArray String Symbol LinkedList Semaphore OrderedCollection RunArray SortedCollection HashedCollection Dictionary IdentityDictionary MethodDictionary RootNamespace Namespace SystemDictionary Set IdentitySet ContextPart BlockContext MethodContext CType CArrayCType CPtrCType CScalarCType Delay DLD DumperProxy AlternativeObjectProxy NullProxy VersionableObjectProxy PluggableProxy File Directory FileSegment Link Process SymLink Magnitude Association Character Date LargeArraySubpart Number Float Fraction Integer LargeInteger LargeNegativeInteger LargePositiveInteger LargeZeroInteger SmallInteger Time Memory Message DirectedMessage MethodInfo NullProxy PackageLoader Point ProcessorScheduler Rectangle SharedQueue Signal Exception Error Halt ArithmeticError ZeroDivide MessageNotUnderstood UserBreak Notification Warning Stream ObjectDumper PositionableStream ReadStream WriteStream ReadWriteStream ByteStream FileStream Random TextCollector TokenStream TrappableEvent CoreException ExceptionCollection UndefinedObject ValueAdaptor NullValueHolder PluggableAdaptor DelayedAdaptor ValueHolder While initially a daunting list, you should take the time to hunt down the classes we've examined in this tutorial so far. Notice, for instance, how an Array is a subclass below the SequenceableCollection class. This makes sense; you can walk an Array from one end to the other. By contrast, notice how this is not true for Sets: it doesn't make sense to walk a Set from one end to the other. A little puzzling is the relationship of a Bag to a Set, since a Bag is actually a Set supporting multiple occurrences of its elements. The answer lies in the purpose of both a Set and a Bag. Both hold an unordered collection of objects; but a Bag needs to be optimized for the case when an object has possibly thousands of occurrences, while a Set is optimized for checking object uniqueness. That's why Set being a subclass or Bag, or the other way round, would be a source of problems in the actual implementation of the class. Currently a Bag holds a Dictionary associating each object to each count; it would be feasible however to have Bag as a subclass of HashedCollection and a sibling of Set. Look at the treatment of numbers--starting with the class Magnitude. While numbers can indeed be ordered by _less than_, _greater than_, and so forth, so can a number of other objects. Each subclass of Magnitude is such an object. So we can compare characters with other characters, dates with other dates, and times with other times, as well as numbers with numbers. Finally, you will have probably noted some pretty strange classes, representing language entities that you might have never thought of as objects themselves: Namespace, Class and even CompiledMethod. They are the base of Smalltalk's "reflection" mechanism which will be discussed later, in *note The truth on metaclasses: Why is #new there?!?. ---------- Footnotes ---------- (1) This listing is courtesy of the printHierarchy method supplied by GNU Smalltalk author Steve Byrne. It's in the `kernel/Browser.st' file.  File: gst.info, Node: Playing with Arrays, Next: New kinds of Numbers, Prev: The existing hierarchy, Up: More subclassing 6.9.2 Playing with Arrays ------------------------- Imagine that you need an array, but alas you need that if an index is out of bounds, it returns nil. You could modify the Smalltalk implementation, but that might break some code in the image, so it is not practical. Why not add a subclass? "We could subclass from Array, but that class is specifically optimized by the VM (which assumes, among other things, that it does not have any instance variables). So we use its abstract superclass instead. The discussion below holds equally well." ArrayedCollection subclass: NiledArray [ boundsCheck: index [ ^(index < 1) | (index > (self basicSize)) ] at: index [ ^(self boundsCheck: index) ifTrue: [ nil ] ifFalse: [ super at: index ] ] at: index put: val [ ^(self boundsCheck: index) ifTrue: [ val ] ifFalse: [ super at: index put: val ] ] ] Much of the machinery of adding a class should be familiar. We see another declaration like `comment:', that is `shape:' message. This sets up `NiledArray' to have the same underlying structure of an `Array' object; we'll delay discussing this until the chapter on the nuts and bolts of arrays. In any case, we inherit all of the actual knowledge of how to create arrays, reference them, and so forth. All that we do is intercept `at:' and `at:put:' messages, call our common function to validate the array index, and do something special if the index is not valid. The way that we coded the bounds check bears a little examination. Making a first cut at coding the bounds check, you might have coded the bounds check in NiledArray's methods twice (once for `at:', and again for `at:put:'. As always, it's preferable to code things once, and then re-use them. So we instead add a method for bounds checking `boundsCheck:', and use it for both cases. If we ever wanted to enhance the bounds checking (perhaps emit an error if the index is < 1 and answer nil only for indices greater than the array size?), we only have to change it in one place. The actual math for calculating whether the bounds have been violated is a little interesting. The first part of the expression returned by the method: (index < 1) | (index > (self basicSize)) is true if the index is less than 1, otherwise it's false. This part of the expression thus becomes the boolean object true or false. The boolean object then receives the message `|', and the argument `(index > (self basicSize))'. `|' means "or"--we want to OR together the two possible out-of-range checks. What is the second part of the expression? (1) `index' is our argument, an integer; it receives the message `>', and thus will compare itself to the value `self basicSize' returns. While we haven't covered the underlying structures Smalltalk uses to build arrays, we can briefly say that the `#basicSize' message returns the number of elements the Array object can contain. So the index is checked to see if it's less than 1 (the lowest legal Array index) or greater than the highest allocated slot in the Array. If it is either (the `|' operator!), the expression is true, otherwise false. From there it's downhill; our boolean object, returned by `boundsCheck:', receives the `ifTrue:ifFalse:' message, and a code block which will do the appropriate thing. Why do we have `at:put:' return val? Well, because that's what it's supposed to do: look at every implementor of `at:put' or `at:' and you'll find that it returns its second parameter. In general, the result is discarded; but one could write a program which uses it, so we'll write it this way anyway. ---------- Footnotes ---------- (1) Smalltalk also offers an `or:' message, which is different in a subtle way from `|'. or: takes a code block, and only invokes the code block if it's necessary to determine the value of the expression. This is analogous to the guaranteed C semantic that `||' evaluates left-to-right only as far as needed. We could have written the expressions as `((index < 1) or: [index > (self basicSize)])'. Since we expect both sides of or: to be false most of the time, there isn't much reason to delay evaluation of either side in this case.  File: gst.info, Node: New kinds of Numbers, Next: Inheritance and Polymorphism, Prev: Playing with Arrays, Up: More subclassing 6.9.3 Adding a New Kind of Number --------------------------------- If we were programming an application which did a large amount of complex math, we could probably manage it with a number of two-element arrays. But we'd forever be writing in-line code for the math and comparisons; it would be much easier to just implement an object class to support the complex numeric type. Where in the class hierarchy would it be placed? You've probably already guessed--but let's step down the hierarchy anyway. Everything inherits from Object, so that's a safe starting point. Complex numbers can not be compared with `<' and `>', and yet we strongly suspect that, since they are numbers, we should place them under the Number class. But Number inherits from Magnitude--how do we resolve this conflict? A subclass can place itself under a superclass which allows some operations the subclass doesn't wish to allow. All that you must do is make sure you intercept these messages and return an error. So we will place our new Complex class under Number, and make sure to disallow comparisons. One can reasonably ask whether the real and imaginary parts of our complex number will be integer or floating point. In the grand Smalltalk tradition, we'll just leave them as objects, and hope that they respond to numeric messages reasonably. If they don't, the user will doubtless receive errors and be able to track back their mistake with little fuss. We'll define the four basic math operators, as well as the (illegal) relationals. We'll add `printOn:' so that the printing methods work, and that should give us our Complex class. The class as presented suffers some limitations, which we'll cover later in the chapter. Number subclass: Complex [ | realpart imagpart | "This is a quick way to define class-side methods." Complex class >> new [ ^self error: 'use real:imaginary:' ] Complex class >> new: ignore [ ^self new ] Complex class >> real: r imaginary: i [ ^(super new) setReal: r setImag: i ] setReal: r setImag: i [ realpart := r. imagpart := i. ^self ] real [ ^realpart ] imaginary [ ^imagpart ] + val [ ^Complex real: (realpart + val real) imaginary: (imagpart + val imaginary) ] - val [ ^Complex real: (realpart - val real) imaginary: (imagpart - val imaginary) ] * val [ ^Complex real: (realpart * val real) - (imagpart * val imaginary) imaginary: (imagpart * val real) + (realpart * val imaginary) ] / val [ | d r i | d := (val real * val real) + (val imaginary * val imaginary). r := ((realpart * val real) + (imagpart * val imaginary)). i := ((imagpart * val real) - (realpart * val imaginary)). ^Complex real: r / d imaginary: i / d ] = val [ ^(realpart = val real) & (imagpart = val imaginary) ] "All other comparison methods are based on <" < val [ ^self shouldNotImplement ] printOn: aStream [ realpart printOn: aStream. aStream nextPut: $+. imagpart printOn: aStream. aStream nextPut: $i ] ] There should be surprisingly little which is actually new in this example. The printing method uses both `printOn:' as well as `nextPut:' to do its printing. While we haven't covered it, it's pretty clear that `$+' generates the ASCII character `+' as an object(1), and `nextPut:' puts its argument as the next thing on the stream. The math operations all generate a new object, calculating the real and imaginary parts, and invoking the Complex class to create the new object. Our creation code is a little more compact than earlier examples; instead of using a local variable to name the newly-created object, we just use the return value and send a message directly to the new object. Our initialization code explicitly returns self; what would happen if we left this off? ---------- Footnotes ---------- (1) A GNU Smalltalk extension allows you to type characters by ASCII code too, as in `$<43>'.  File: gst.info, Node: Inheritance and Polymorphism, Prev: New kinds of Numbers, Up: More subclassing 6.9.4 Inheritance and Polymorphism ---------------------------------- This is a good time to look at what we've done with the two previous examples at a higher level. With the NiledArray class, we inherited almost all of the functionality ality of arrays, with only a little bit of code added to address our specific needs. While you may have not thought to try it, all the existing methods for an Array continue to work without further effort-you might find it interesting to ponder why the following still works: a := NiledArray new: 10 a at: 5 put: 1234 a do: [:i| i printNl ] The strength of inheritance is that you focus on the incremental changes you make; the things you don't change will generally continue to work. In the Complex class, the value of polymorphism was exercised. A Complex number responds to exactly the same set of messages as any other number. If you had handed this code to someone, they would know how to do math with Complex numbers without further instruction. Compare this with C, where a complex number package would require the user to first find out if the complex-add function was complex_plus(), or perhaps complex_add(), or add_complex(), or... However, one glaring deficiency is present in the Complex class: what happens if you mix normal numbers with Complex numbers? Currently, the Complex class assumes that it will only interact with other Complex numbers. But this is unrealistic: mathematically, a "normal" number is simply one with an imaginary part of 0. Smalltalk was designed to allow numbers to coerce themselves into a form which will work with other numbers. The system is clever and requires very little additional code. Unfortunately, it would have tripled the amount of explanation required. If you're interested in how coercion works in GNU Smalltalk, you should find the Smalltalk library source, and trace back the execution of the `retry:coercing:' messages. You want to consider the value which the `generality' message returns for each type of number. Finally, you need to examine the `coerce:' handling in each numeric class.  File: gst.info, Node: Streams, Next: Exception handling, Prev: More subclassing, Up: Tutorial 6.10 Smalltalk Streams ====================== Our examples have used a mechanism extensively, even though we haven't discussed it yet. The Stream class provides a framework for a number of data structures, including input and output functionality, queues, and endless sources of dynamically-generated data. A Smalltalk stream is quite similar to the UNIX streams you've used from C. A stream provides a sequential view to an underlying resource; as you read or write elements, the stream position advances until you finally reach the end of the underlying medium. Most streams also allow you to set the current position, providing random access to the medium. * Menu: * The output stream:: Which, even though you maybe didn't know it, we've used all the time * Your own stream:: Which, instead, is something new * Files:: Which are streams too * Dynamic Strings:: A useful application of Streams  File: gst.info, Node: The output stream, Next: Your own stream, Up: Streams 6.10.1 The Output Stream ------------------------ The examples in this book all work because they write their output to the `Transcript' stream. Each class implements the `printOn:' method, and writes its output to the supplied stream. The `printNl' method all objects use is simply to send the current object a `printOn:' message whose argument is `Transcript' (by default attached to the standard output stream found in the `stdout' global). You can invoke the standard output stream directly: 'Hello, world' printOn: stdout stdout inspect or you can do the same for the Transcript, which is yet another stream: 'Hello, world' printOn: stdout Transcript inspect the last `inspect' statement will show you how the `Transcript' is linked to `stdout'(1). ---------- Footnotes ---------- (1) Try executing it under Blox, where the Transcript is linked to the omonymous window!  File: gst.info, Node: Your own stream, Next: Files, Prev: The output stream, Up: Streams 6.10.2 Your Own Stream ---------------------- Unlike a pipe you might create in C, the underlying storage of a Stream is under your control. Thus, a Stream can provide an anonymous buffer of data, but it can also provide a stream-like interpretation to an existing array of data. Consider this example: a := Array new: 10 a at: 4 put: 1234 a at: 9 put: 5678 s := ReadWriteStream on: a. s inspect s position: 1 s inspect s nextPut: 11; nextPut: 22 (a at: 1) printNl a do: [:x| x printNl] s position: 2 s do: [:x| x printNl] s position: 5 s do: [:x| x printNl] s inspect The key is the `on:' message; it tells a stream class to create itself in terms of the existing storage. Because of polymorphism, the object specified by on: does not have to be an Array; any object which responds to numeric at: messages can be used. If you happen to have the NiledArray class still loaded from the previous chapter, you might try streaming over that kind of array instead. You're wondering if you're stuck with having to know how much data will be queued in a Stream at the time you create the stream. If you use the right class of stream, the answer is no. A ReadStream provides read-only access to an existing collection. You will receive an error if you try to write to it. If you try to read off the end of the stream, you will also get an error. By contrast, WriteStream and ReadWriteStream (used in our example) will tell the underlying collection to grow when you write off the end of the existing collection. Thus, if you want to write several strings, and don't want to add up their lengths yourself: s := ReadWriteStream on: String new s inspect s nextPutAll: 'Hello, ' s inspect s nextPutAll: 'world' s inspect s position: 1 s inspect s do: [:c | stdout nextPut: c ] s contents In this case, we have used a String as the collection for the Stream. The `printOn:' messages add bytes to the initially empty string. Once we've added the data, you can continue to treat the data as a stream. Alternatively, you can ask the stream to return to you the underlying object. After that, you can use the object (a String, in this example) using its own access methods. There are many amenities available on a stream object. You can ask if there's more to read with `atEnd'. You can query the position with `position', and set it with `position:'. You can see what will be read next with `peek', and you can read the next element with `next'. In the writing direction, you can write an element with `nextPut:'. You don't need to worry about objects doing a `printOn:' with your stream as a destination; this operation ends up as a sequence of `nextPut:' operations to your stream. If you have a collection of things to write, you can use `nextPutAll:' with the collection as an argument; each member of the collection will be written onto the stream. If you want to write an object to the stream several times, you can use `next:put:', like this: s := ReadWriteStream on: (Array new: 0) s next: 4 put: 'Hi!' s position: 1 s do: [:x | x printNl]  File: gst.info, Node: Files, Next: Dynamic Strings, Prev: Your own stream, Up: Streams 6.10.3 Files ------------ Streams can also operate on files. If you wanted to dump the file `/etc/passwd' to your terminal, you could create a stream on the file, and then stream over its contents: f := FileStream open: '/etc/passwd' mode: FileStream read f linesDo: [ :c | Transcript nextPutAll: c; nl ] f position: 30 25 timesRepeat: [ Transcript nextPut: (f next) ] f close and, of course, you can load Smalltalk source code into your image: FileStream fileIn: '/Users/myself/src/source.st'  File: gst.info, Node: Dynamic Strings, Prev: Files, Up: Streams 6.10.4 Dynamic Strings ---------------------- Streams provide a powerful abstraction for a number of data structures. Concepts like current position, writing the next position, and changing the way you view a data structure when convenient combine to let you write compact, powerful code. The last example is taken from the actual Smalltalk source code--it shows a general method for making an object print itself onto a string. printString [ | stream | stream := WriteStream on: (String new). self printOn: stream. ^stream contents ] This method, residing in Object, is inherited by every class in Smalltalk. The first line creates a WriteStream which stores on a String whose length is currently 0 (`String new' simply creates an empty string. It then invokes the current object with `printOn:'. As the object prints itself to "stream", the String grows to accommodate new characters. When the object is done printing, the method simply returns the underlying string. As we've written code, the assumption has been that printOn: would go to the terminal. But replacing a stream to a file like `/dev/tty' with a stream to a data structure (`String new') works just as well. The last line tells the Stream to return its underlying collection, which will be the string which has had all the printing added to it. The result is that the `printString' message returns an object of the String class whose contents are the printed representation of the very object receiving the message.  File: gst.info, Node: Exception handling, Next: Behind the scenes, Prev: Streams, Up: Tutorial 6.11 Exception handling in Smalltalk ==================================== Up to this point of the tutorial, you used the original Smalltalk-80 error signalling mechanism: check: num [ | c | c := history at: num ifAbsent: [ ^self error: 'No such check #' ]. ^c ] In the above code, if a matching check number is found, the method will answer the object associated to it. If no prefix is found, Smalltalk will unwind the stack and print an error message including the message you gave and stack information. CheckingAccount new: 31 "<0x33788>" error: No such check # ...blah blah... CheckingAccount>>#error: [] in Dictionary>>#at:ifAbsent: Dictionary(HashedCollection)>>#findIndex:ifAbsent: Dictionary>>#at:ifAbsent: [] in CheckingAccount>>#check: CheckingAccount>>#check: UndefinedObject(Object)>>#executeStatements Above we see the object that received the #error: message, the message text itself, and the frames (innermost-first) running when the error was captured by the system. In addition, the rest of the code in methods like `CheckingAccount>>#check:' was not executed. So simple error reporting gives us most of the features we want: * Execution stops immediately, preventing programs from continuing as if nothing is wrong. * The failing code provides a more-or-less useful error message. * Basic system state information is provided for diagnosis. * A debugger can drill further into the state, providing information like details of the receivers and arguments on the stack. However, there is a more powerful and complex error handling mechanism, that is "exception". They are like "exceptions" in other programming languages, but are more powerful and do not always indicate error conditions. Even though we use the term "signal" often with regard to them, do not confuse them with the signals like `SIGTERM' and `SIGINT' provided by some operating systems; they are a different concept altogether. Deciding to use exceptions instead of `#error:' is a matter of aesthetics, but you can use a simple rule: use exceptions only if you want to provide callers with a way to recover sensibly from certain errors, and then only for signalling those particular errors. For example, if you are writing a word processor, you might provide the user with a way to make regions of text read-only. Then, if the user tries to edit the text, the objects that model the read-only text can signal a `ReadOnlyText' or other kind of exception, whereupon the user interface code can stop the exception from unwinding and report the error to the user. When in doubt about whether exceptions would be useful, err on the side of simplicity; use `#error:' instead. It is much easier to convert an #error: to an explicit exception than to do the opposite. * Menu: * Creating exceptions:: Starting to use the mechanism * Raising exceptions:: What to do when exceptional events happen * Handling exceptions:: The other side * When an exception isn't handled:: Default actions * Creating new exception classes:: Your own exceptions * Hooking into the stack unwinding:: An alternative exception handling system * Handler stack unwinding caveat:: Differences with other languages smalltalk-3.2.5/doc/gst-doc.10000644000175000017500000000240412130455703012615 00000000000000.\" DO NOT MODIFY THIS FILE! It was generated by help2man 1.28. .TH GST-DOC "1" "April 2013" "gst-doc version 3.2.5-4dc033e" "User Commands" .SH NAME gst-doc \- GNU Smalltalk documentation generator .SH DESCRIPTION .SS "Usage:" .IP gst-doc [ flag ... ] class ... .SH OPTIONS .TP \fB\-I\fR \fB\-\-image\-file\fR=\fIFILE\fR look for classes in the given image .TP \fB\-p\fR \fB\-\-package\fR=\fIPKG\fR look for classes in the given package .TP \fB\-f\fR \fB\-\-file\fR=\fIFILE\fR look for classes in the given file .HP \fB\-n\fR \fB\-\-namespace\fR=\fINAMESP\fR load files in the given namespace .TP \fB\-o\fR \fB\-\-output\fR=\fIFILE\fR emit documentation in the given file (default=stdout) .TP \fB\-\-kernel\-dir\fR=\fIPATH\fR use the specified kernel directory .TP \fB\-F\fR \fB\-\-output\-format\fR=\fIKIND\fR use the given publisher (HTML or default=Texinfo) .TP \fB\-h\fR \fB\-\-help\fR show this message .TP \fB\-v\fR \fB\-\-verbose\fR print extra information while processing .TP \fB\-\-version\fR print version information and exit .SH "SEE ALSO" The full documentation for .B gst-doc is maintained as a Texinfo manual. If the .B info and .B gst-doc programs are properly installed at your site, the command .IP .B info gst .PP should give you access to the complete manual. smalltalk-3.2.5/doc/gst-convert.10000644000175000017500000000344312130455702013533 00000000000000.\" DO NOT MODIFY THIS FILE! It was generated by help2man 1.28. .TH GST-CONVERT "1" "April 2013" "gst-convert version 3.2.5-4dc033e" "User Commands" .SH NAME gst-convert \- Smalltalk syntax converter and beautifier .SH DESCRIPTION .SS "Usage:" .IP gst-convert [OPTION]... [INFILE [OUTFILE]] gst-convert [OPTION]... \fB\-o\fR|--output OUTFILE INFILES .SH OPTIONS .TP \fB\-q\fR, \fB\-\-quiet\fR don't show any message .TP \fB\-v\fR, \fB\-\-verbose\fR print extra information while processing .TP \fB\-f\fR, \fB\-\-format\fR=\fIFORMAT\fR convert from given input format (supported formats are gst, gst2, sif, squeak) .TP \fB\-F\fR, \fB\-\-output\-format\fR=\fIFORMAT\fR convert to given output format (supported formats are gst, gst2, squeak) .TP \fB\-C\fR, \fB\-\-class\fR=\fIREGEX\fR convert only classes matching REGEX .TP \fB\-C\fR, \fB\-\-class=\fR+REGEX in addition, convert classes matching REGEX .TP \fB\-C\fR, \fB\-\-class\fR=\fI\-REGEX\fR do not convert classes matching REGEX .TP \fB\-c\fR, \fB\-\-category\fR=\fIREGEX\fR convert only classes whose category matches REGEX .TP \fB\-c\fR, \fB\-\-category=\fR+REGEX in addition, convert those whose category matches REGEX .TP \fB\-c\fR, \fB\-\-category\fR=\fI\-REGEX\fR do not convert classes whose category matches REGEX .TP \fB\-r\fR, \fB\-\-rule=\fR'CODE->REPL' look for CODE and replace it with REPL .TP \fB\-o\fR, \fB\-\-output\fR OUTFILE concatenate multiple input files into a single converted output file .TP \fB\-\-help\fR display this message and exit .TP \fB\-\-version\fR print version information and exit .SH "SEE ALSO" The full documentation for .B gst-convert is maintained as a Texinfo manual. If the .B info and .B gst-convert programs are properly installed at your site, the command .IP .B info gst .PP should give you access to the complete manual. smalltalk-3.2.5/doc/gst-profile.10000644000175000017500000000236512130455703013516 00000000000000.\" DO NOT MODIFY THIS FILE! It was generated by help2man 1.28. .TH GST-DOC "1" "April 2013" "gst-doc version 3.2.5-4dc033e" "User Commands" .SH NAME gst-doc \- GNU Smalltalk profiler .SH DESCRIPTION .SS "Usage:" .IP gst-doc [ flag ... ] class ... .SH OPTIONS .TP \fB\-I\fR \fB\-\-image\-file\fR=\fIFILE\fR look for classes in the given image .TP \fB\-p\fR \fB\-\-package\fR=\fIPKG\fR look for classes in the given package .TP \fB\-f\fR \fB\-\-file\fR=\fIFILE\fR look for classes in the given file .HP \fB\-n\fR \fB\-\-namespace\fR=\fINAMESP\fR load files in the given namespace .TP \fB\-o\fR \fB\-\-output\fR=\fIFILE\fR emit documentation in the given file (default=stdout) .TP \fB\-\-kernel\-dir\fR=\fIPATH\fR use the specified kernel directory .TP \fB\-F\fR \fB\-\-output\-format\fR=\fIKIND\fR use the given publisher (HTML or default=Texinfo) .TP \fB\-h\fR \fB\-\-help\fR show this message .TP \fB\-v\fR \fB\-\-verbose\fR print extra information while processing .TP \fB\-\-version\fR print version information and exit .SH "SEE ALSO" The full documentation for .B gst-doc is maintained as a Texinfo manual. If the .B info and .B gst-doc programs are properly installed at your site, the command .IP .B info gst .PP should give you access to the complete manual. smalltalk-3.2.5/doc/Makefile.am0000644000175000017500000002073512123404352013232 00000000000000EXTRA_DIST = $(HTML_IMAGES) categories HTML_IMAGES = images/backon.png images/back.png images/blankon.png \ images/blank.png images/forwardon.png images/forward.png \ images/helpon.png images/help.png images/homeon.png \ images/home.png images/inactive.png images/indexon.png \ images/index.png images/nexton.png images/next.png \ images/prevon.png images/prev.png images/tocon.png \ images/toc.png images/upon.png images/up.png dist_man_MANS = gst.1 gst-load.1 gst-package.1 gst-sunit.1 gst-config.1 \ gst-convert.1 gst-doc.1 gst-profile.1 HELP2MAN = $(top_srcdir)/build-aux/help2man -p gst info_TEXINFOS = gst.texi gst-base.texi gst-libs.texi gst_TEXINFOS = tutorial.texi vers-gst.texi gst_libs_TEXINFOS = blox.texi sockets.texi i18n.texi complex.texi debug.texi \ dbi.texi zlib.texi using-xml.texi vers-libs.texi gst_base_TEXINFOS = classes.texi vers-base.texi TEXI2DVI=pool_size=750000 $(top_srcdir)/build-aux/texi2dvi --expand MOSTLYCLEANFILES = gst-libs.me gst-libs.mes gst-base.me gst-base.mes \ gst-libs.cl gst-libs.cls gst-base.cl gst-base.cls \ gst-libs.sl gst-libs.sls gst-base.sl gst-base.sls GST_TOOL = $(top_builddir)/gst-tool$(EXEEXT) GST_TOOL_ARGS = -I $(top_builddir)/gst.im --kernel-dir $(top_srcdir)/kernel GST_DOC = $(GST_TOOL) gst-doc $(GST_TOOL_ARGS) GST_PACKAGE = $(GST_TOOL) gst-package $(GST_TOOL_ARGS) #################################################### ## ## Rule to build the man page ## #################################################### $(srcdir)/gst-package.1: $(top_srcdir)/scripts/Package.st $(top_srcdir)/configure.ac $(HELP2MAN) \ --name "create and install GNU Smalltalk .star package files" \ "$(GST_TOOL) gst-package $(GST_TOOL_ARGS)" >$@ $(srcdir)/gst-convert.1: $(top_srcdir)/scripts/Load.st $(top_srcdir)/configure.ac $(HELP2MAN) \ --name "Smalltalk syntax converter and beautifier" \ "$(GST_TOOL) gst-convert $(GST_TOOL_ARGS)" >$@ $(srcdir)/gst-load.1: $(top_srcdir)/scripts/Load.st $(top_srcdir)/configure.ac $(HELP2MAN) \ --name "test and load packages into a GNU Smalltalk image" \ "$(GST_TOOL) gst-load $(GST_TOOL_ARGS)" >$@ $(srcdir)/gst-sunit.1: $(top_srcdir)/scripts/Test.st $(top_srcdir)/configure.ac $(HELP2MAN) \ --name "unit testing tool for GNU Smalltalk" \ "$(GST_TOOL) gst-sunit $(GST_TOOL_ARGS)" >$@ $(srcdir)/gst-doc.1: $(top_srcdir)/scripts/GenDoc.st $(top_srcdir)/configure.ac $(HELP2MAN) \ --name "GNU Smalltalk documentation generator" \ "$(GST_TOOL) gst-doc $(GST_TOOL_ARGS)" >$@ $(srcdir)/gst-profile.1: $(top_srcdir)/scripts/Profile.st $(top_srcdir)/configure.ac $(HELP2MAN) \ --name "GNU Smalltalk profiler" \ "$(GST_TOOL) gst-doc $(GST_TOOL_ARGS)" >$@ $(srcdir)/gst.1: $(top_srcdir)/main.c $(top_srcdir)/configure.ac $(HELP2MAN) \ --name "the GNU Smalltalk virtual machine" $(top_builddir)/gst$(EXEEXT) >$@ $(srcdir)/gst-config.1: $(top_srcdir)/gst-config.in $(HELP2MAN) \ --name "configuration for libgst" $(top_builddir)/gst-config >$@ uninstall-local: rm -f $(DESTDIR)$(man1dir)/gst-reload.1 install-data-local: install-man rm -f $(DESTDIR)$(man1dir)/gst-reload.1 $(LN_S) $(DESTDIR)$(man1dir)/gst-load.1 $(DESTDIR)$(man1dir)/gst-reload.1 #################################################### ## ## Rules to build the generated documentation ## #################################################### PUBLISHED_CLASSES = Smalltalk.* SystemExceptions.* NetClients.* VFS.* $(srcdir)/blox.texi: $(top_srcdir)/packages/blox/tk/stamp-classes files=`$(GST_PACKAGE) $(patsubst %, %/package.xml, $(^D)) \ --load --list-files=BloxTK | \ sed s,^,-f,`; \ IFS=`printf '\n\t'`; \ $(GST_DOC) -n BLOX -o $(srcdir)/blox.texi $$files BLOX.* || \ rm -f $(srcdir)/blox.texi test -f $(srcdir)/blox.texi && touch $(srcdir)/gst-libs.texi $(srcdir)/sockets.texi: $(top_srcdir)/packages/sockets/stamp-classes files=`$(GST_PACKAGE) $(patsubst %, %/package.xml, $(^D)) \ --load --list-files=Sockets | \ sed s,^,-f,`; \ IFS=`printf '\n\t'`; \ $(GST_DOC) -n Sockets -o $(srcdir)/sockets.texi $$files Sockets.* || \ rm -f $(srcdir)/sockets.texi test -f $(srcdir)/sockets.texi && touch $(srcdir)/gst-libs.texi $(srcdir)/complex.texi: $(top_srcdir)/packages/complex/stamp-classes files=`$(GST_PACKAGE) $(patsubst %, %/package.xml, $(^D)) \ --load --list-files=Complex | \ sed s,^,-f,`; \ IFS=`printf '\n\t'`; \ $(GST_DOC) -o $(srcdir)/complex.texi $$files Complex || \ rm -f $(srcdir)/complex.texi test -f $(srcdir)/complex.texi && touch $(srcdir)/gst-libs.texi $(srcdir)/debug.texi: $(top_srcdir)/packages/debug/stamp-classes files=`$(GST_PACKAGE) $(patsubst %, %/package.xml, $(^D)) \ --load --list-files=DebugTools | \ sed s,^,-f,`; \ IFS=`printf '\n\t'`; \ $(GST_DOC) -o $(srcdir)/debug.texi $$files Debugger* || \ rm -f $(srcdir)/debug.texi test -f $(srcdir)/debug.texi && touch $(srcdir)/gst-libs.texi $(srcdir)/zlib.texi: $(top_srcdir)/packages/zlib/stamp-classes files=`$(GST_PACKAGE) $(patsubst %, %/package.xml, $(^D)) \ --load --list-files=ZLib | \ sed s,^,-f,`; \ IFS=`printf '\n\t'`; \ $(GST_DOC) -n ZLib -o $(srcdir)/zlib.texi $$files ZLib.* || \ rm -f $(srcdir)/zlib.texi test -f $(srcdir)/zlib.texi && touch $(srcdir)/gst-libs.texi $(srcdir)/dbi.texi: $(top_srcdir)/packages/dbi/stamp-classes files=`$(GST_PACKAGE) $(patsubst %, %/package.xml, $(^D)) \ --load --list-files=DBI | \ sed s,^,-f,`; \ IFS=`printf '\n\t'`; \ $(GST_DOC) -n DBI -o $(srcdir)/dbi.texi $$files DBI.* || \ rm -f $(srcdir)/dbi.texi test -f $(srcdir)/dbi.texi && touch $(srcdir)/gst-libs.texi $(srcdir)/i18n.texi: $(top_srcdir)/packages/iconv/stamp-classes $(top_srcdir)/packages/i18n/stamp-classes files=`$(GST_PACKAGE) $(patsubst %, %/package.xml, $(^D)) \ --load --list-files=Iconv --list-files=I18N | \ sed s,^,-f,`; \ IFS=`printf '\n\t'`; \ $(GST_DOC) -n I18N -o $(srcdir)/i18n.texi $$files I18N.* || \ rm -f $(srcdir)/i18n.texi test -f $(srcdir)/i18n.texi && touch $(srcdir)/gst-libs.texi $(srcdir)/classes.texi: $(top_srcdir)/kernel/stamp-classes $(GST_DOC) -o $(srcdir)/classes.texi $(PUBLISHED_CLASSES) || \ rm -f $(srcdir)/classes.texi test -f $(srcdir)/classes.texi && touch $(srcdir)/gst-base.texi # In TeX output, having colons in index entries looks pretty, but # this is impossible in info output!!! So we hack by replacing # colons with underscores in the info file. %.info: %.texi @cd $(srcdir) && rm -f $@ $@-[0-9] $@-[0-9][0-9] fixed=`pwd`/`echo $< | $(SED) 's/\.texi/-fixed&/' `; \ cd $(srcdir) && \ $(MAKEINFO) `echo $< | $(SED) 's,.*/,,'` -E - -o /dev/null | \ $(SED) '/^@..index/ s/:/_/g' > $$fixed && \ $(MAKEINFO) $$fixed > /dev/null 2>&1 && \ rm -f $$fixed #################################################### ## ## Rules to build the HTML documentation ## #################################################### # We want the HTML doc to look professional, so we use makeinfo first. # This rule is pretty complex. What it does is: # - check whether /usr/bin/env perl works # - check whether we have makeinfo (it could be faked by the missing script) # - check whether we have makeinfo 4.0 # - resolve macros in gst.texi using makeinfo # - finally invoke texi2html # - remove the temporary file with resolved macros html: $(srcdir)/gst.texi $(srcdir)/gst-base.texi $(srcdir)/gst-libs.texi @(echo 'print "ohyeah"' | perl | grep ohyeah) > /dev/null 2>&1 || \ (echo "You need Perl to make HTML documentation"; exit 1) @($(MAKEINFO) --version 2>&1 | grep missing:) > /dev/null 2>&1 || exit 0; \ (echo "You need Makeinfo to make HTML documentation"; exit 1) rm -rf html mkdir html @echo "Building HTML documentation may be a long task... please wait" ($(MAKEINFO) --help | grep ifhtml) > /dev/null 2>&1 && makeinfo4=yes; \ htmldir=`pwd`/html && \ cd $(srcdir) && \ srcdir=`pwd` && \ $(MAKEINFO) gst.texi -E $$htmldir/gst.texi \ $${makeinfo4+--no-iftex --no-ifinfo --ifhtml} -o /dev/null && \ $(MAKEINFO) gst-libs.texi -E $$htmldir/gst-libs.texi \ $${makeinfo4+--no-iftex --no-ifinfo --ifhtml} -o /dev/null && \ $(MAKEINFO) gst-base.texi -E $$htmldir/gst-base.texi \ $${makeinfo4+--no-iftex --no-ifinfo --ifhtml} -o /dev/null && \ cd $$htmldir && \ $$srcdir/../build-aux/texi2html -Verbose -split section gst.texi && \ $$srcdir/../build-aux/texi2html -Verbose -split section gst-libs.texi && \ $$srcdir/../build-aux/texi2html -Verbose -split section gst-base.texi && \ ln -sf $$srcdir/images $$htmldir/images && \ $(RM) $$htmldir/gst.texi $$htmldir/gst-libs.texi $$htmldir/gst-base.texi clean-local: $(RM) -r html .PHONY: clean-html smalltalk-3.2.5/doc/vers-libs.texi0000644000175000017500000000013612130456006013771 00000000000000@set UPDATED 8 April 2013 @set UPDATED-MONTH April 2013 @set EDITION 3.2.5 @set VERSION 3.2.5 smalltalk-3.2.5/doc/images/0000755000175000017500000000000012130456006012515 500000000000000smalltalk-3.2.5/doc/images/backon.png0000644000175000017500000000304712123404352014403 00000000000000‰PNG  IHDR((œ/:bKGDùC» pHYs  d_‘ÇIDATxœÅ˜!t9†ÿÜ;0fZ¶bQÙ†Ù,f t™Ë’²–õXÂÎÐaÖ°†5a1»…f3/«Ø)¨Zf1ËñÊŠí&é+¨^^ÞîZ«Oókf4Ú½ïß¿ãw´?~ ÀŸ?Õ;<”™ ä¼:e-€ (¨oFk£Ôþà•Cí½FjáåŸ+Û8r@ÎA Øð€E®Ìqou¡U~ôKàÐÜgÖ矫ºž+æø¼H©L´h;°ÑÝñ§çñÏÃC©ofjî°sêÆÍ[RÚ:Dé´¤ƒô_¾þ4xovK•Un)·3[WÞ;rІÓO§Å9 .GÅÑÉvÏ^šû½Ù-YOPèöáÒή•…*R§¼HÕímM(ÏÆöþöUàÌyª¬Zj*ŠY=½®gÖ9"f Ú6Ú'ì8éÃ;Ù›àðPRe À¬,oªªq‘ON×25OEΈ„Í„ý84÷âM¤ô¬žÞTs*søÙ¦n˜›X0gDDònhÂäãûÐÜïgÖÓÝ™rv~SUò0R‘(Ü!2]uPê*áÉRðÄLÌÇÌ9ˆHÕeåíZ”uæ Í=F× À"L+¶bµ´ë=þ»{<žb«MÞ¼ñÎgDb+13bÖ@Ã@5ºÒw«à^ƒ3ë—Î#׳ÆY爔bmeuMW}˜oÇðª ÿûÀÕ^G`f"j½A”ãÐ8ç­WùS©óÏ+m+ï0‡¨Þ‹ÔØ>=.™(¥ X1)ö¦”‡+px(ëz nÜ²í¤˜eQQJ½îEGÞѺgïRª!å^n>圹 ?Ì‘Ò>/)µ±›¾¶bü…[© )ÇA¦Ù!šà]åjÉùeò²,êö BUÌõèÝö¯„L.ò„Új R‰TÁÁD Ϋ£“ØN]È6·4]©\¹™^”iŸ¬51Šm•hŒ1ÂðÍ"zµìê;› €Úú5kc&}˜ÚÊ„mH"UÍl‘zõvVŠíöà­w¤<ÝZ­7RaÉ?b4s0Ë%R°ßµÑÊÐ'ß¾åÅzè˜%bØÈÿh¢I[sã‹rÝɲ58ÅÎñ@3 >Ì}qró°Þ’IAB[æJJyS ®q>4u¹2Ñ·¶Êâ,¬“>Ç7ÿV§o1™sÿn ÃpDJ@–EüáBÍ.¯P–1ÃPÌuëhÔ7k°“LG„V4èÖ¦zô®;¾‹ìf2͇gÐÝ!;‹²Œ[YŒLßê¯~©ÃC©‚Ñ‹§y.¦ÌéEÙÔÑî|Øßµ,>žH! cFAÀj öT˜ˆô­>qȪÿO3¹Œì€{wÚL&ÂÛ¨JE€¢0R{¯s5®kñ=ñáûtlG€;+Ô´õæ‘ÊA½–²«ý.4-A'+‘ãµ¾¼«z=w}ê Ñ6Ô;úhŽ…ºjp f™Ñ‹6zÖåmx(½ ÕéHnc“nì›O .BÝ6÷–à8©Ñõè±-u× DŒ6ƒ•ãøÖÊ8tº±o\ºqýñî4þx”oƒõ–òcë%çüXDÀèÜèÆ\ âÙtþùóóÀÒQ^«„ÄrX!ê¢(3z2= =—÷+:ކ®;À­¼éN°8ˆXž¥¤(ÖhKõyŒ6wÉîXNà«I]'Éiªã[6É»•ØUVÛcˆk¸ÚH…Ç“4K“$!žq}¾Ê©ëFf¼ü°ÿÇ ‘Ùê 4ÀÝçNêÇoONØ_£+¤V.v4‰çŸÞ£à=©!´$-(}UW* }T°ÛoOð‹úƒMu£ÊË*ëÂÒÁ]X¯”1Ròd“ï²…kf¶Üþ,0¸ [,ÖüXñ³„ËØaó»6¾¢Ó/ÑÝè!U;SæÉaeK+­n=ú‡zS ÁU°óõµ´ô!!/v’êrWå0¦•Ì›ÑÕPaE ÇÖcØí…!5œ9ªq ¶X¯Q?†l§fâ±êÀpÒ‘öÌqPŽva;‡„C¬ùéþeÙ‚e>§»c#ÂÄŠ$æAFiÅ8Õ1f&zÏÅc †PËSP¡{”¹ðí…HUÈÅ9ª¬ ú2lÓ‚`VS™É´î+ìÛ}iì¤ÒI5åC3¡[0.µ^E&oHuf$ö0®ªÁóÛí§™<%uV‡ÑÐWŸÂg©¤‰« -R1ÒA£ºÏb¢×Ò³|%ƒF˜å(.T6w`?üÈ~©xV Y£L:¥“ëuçÏ _Õy·ÑIäôÕR ÏGÅÒ‡••©“i¤¥ö *›´CÑÅÍ‘E,­Ár2USj=†4‹UÙ¬0´ª7hgεkú*tùM6[5?7XÎhS t7 T[eõå©„TK^|wUÞÀ%ÆL½av„*Ù•kvÚjf“0ÜïWXútËWSRΦ$Í{ÚàùŠ ×—Jñ¸ÕîÞÀífÜ騫¹€=[-ñ1PþھFË5b7ýðÎ,­íº:øå Ôþ>¶)/Ñç5Õ 'DàŸÏïïžâs=2×ÁF¶U ˜WÅ!² »½¿ƒœ²zzïNPû?üÑáUž›¡uú È¢¿÷)êEw'Ó’·oËÔÔÛžòþ0ˆ in‹¿ý¹¨Ù•ó²zî~üï×jÇ¡&Ï4Ÿ£—‚Qy¨‡¡2­pKòÜSn–¿;ï¥ßF¼Ü¡X+ë‚c@ÒW×,Žãÿÿ Þy4v!ɲÿ½óš—±ÎIEND®B`‚smalltalk-3.2.5/doc/images/homeon.png0000644000175000017500000000252412123404352014432 00000000000000‰PNG  IHDR((œ/:gAMA± üabKGDùC»ùIDATxœÅ˜-tã8ÇÿÝw`Â$fAK˜ËÖ¬- \še[Ö…[¶ÇZØcVC—%,f6«ØÊÌbv˲óÑî»}oçõõùû§ÿh43ÊÅ?ð;ìÃo¡øãýÚú *ͨҦ¨Pj® "E“ÉXŒcž(Dtõž¯]¼ÇÕ¶~‘k½{zƦÀþ:€45MäìF¤ñ›ø7À-ÿakfvÈÀD˜¹Ù‰tq{ÌE¦žr*jh¶&f 4-CdÿE¯>½›GÉõO€mý¢ªF<æ b²ØTÅÚÍ>&úoy¼€ÙÃR]ªCéG¢º£ŽÇHÓ‚ñ¨‹'­ÏPŠep÷ïÏ_õZÛúåm0mÍžªÔf»~Îó¢ÒƒgZ›Ól­nfkÞs‘Å÷™£æÛõÓje­û÷¨ÏRÍÿÝQ«H1w‘á¨^Vº›¢ªÁhCq`’ˆ0:OuvýZÂ;¹?e>ÖÖŶ£ÔdÁ¾æô–¬ 0šÎÛGóê©#/$Ûqp©á;ª‹ž¼I–ÿRJEŸ¶oˆÎF’™C;ª ë!šÚvŠm$wÀîT¥cæz˜åÚ!5d»c©L“m;ÑCzë'¦S&†§$Ú”°s#§“¸#33‡Å¼Wsú‘`u1z¼­.Úzójƒ<@HÆXŒc×O9e‡•ÎA÷BÞ%E:á‰`^»ç=«óD¹{=eDžz¨ØŒû×G‘:J¥65‰–õÁßQÓÄ9ÄkÌ{63€]¿#8ªÕ] ©PÑÞÕé4qwZWGWrvÓ}˜È bPsBsépM\›0 ¼Uû¾˜/g7®ñëv" Ô¶äÁ%ÀBøP"êªÖ¦½8@ú# v~žŠ¨Ic÷bWEt•.n]4ý¤íjY‹ ¼ÓÈÛãéòÖ÷¹½ÖG¤±š&°IÛW:MƒŒèä†ZýIÖ¦áù4mRßÀÑUz7wÇÖ-¡`jÃú:u8©ÎòÖÉ1€»Oa[?lo£äzö°tfÖ­ôÃúê³Ä€êNX‹öâìa9ØËièÕ¥š}_zÝ…gŸÈþ‡T ~jµ¸{Xò¥PNîÌÖ¬>/ü•˜H´L˜$ÃõêEÐÆ`þ°äc{§s»ÅºÈ²ûG“{‡A’H fÉû,a°ß?êþZ¸ž&ã»9ýÔn1”®×:[|sÍý;Mq³üûã¾X=;õ ¦a¬¦Éô—ü"0ÀƒaJSW•.ʦÔ\[Š„œÄq2‰ÆcõË95Çð?eÿ¶ŠG%Yý’IEND®B`‚smalltalk-3.2.5/doc/images/upon.png0000644000175000017500000000257112123404352014130 00000000000000‰PNG  IHDR((Œþ¸mgAMA± üabKGDùC» pHYs  d_‘ IDATxœÍ˜OˆUÇ?+‚¯ 0EÐ<±è§ÔÚ݃’€e7RЭ"nÁÃÚ[¤—î­Ç]°Hðæm/…]OÍžl@Ä/É-™Ûææó´“[æÖw[“7óæ_fv­âB&oÞÌûäû~¿÷oåôôôŒÿ±^¼èƒálĉB«1˜0›…¥Ð®‹hHDÛ‹®¯Ià46ÎÝÎÊy gCäH1ïýãi\®D ˜YÏ9íUÄÖdË=hm@&öÂyr°À²pu½º¿W´àÊø§wŒPa\¦•B…s|4 2ϸKÞ§¯ÝbëÉ“ΆH5ÇéöÁ‹šÔzŽïO)•ƒ²á”u]hÔ9è"Öd©›¥€q—&h×Ñ.ãÑ|Ÿž*CK઴µµ¤Ë_({‰Tó\¯ß¯ W^+ßßé¢'AaÝBWÆÇ4ºGQ·®5Œôûý%MÖs@Zף̽ÝÓ?sõs†³!Nïí:„²Q .«2÷$élneîÿt÷N4¾.”#!.3T-¸¬{E.ÊÌwd0žŒÒ/ÕÅálˆÛÞC¸Q?ú£Z±´¬k PP‡uÏnçÁä0N˜”ƒr¤Â9Z)ÆaP W6”<<{†l~7nƒÚj,>«Y`ËÅ0œ qñQl5²¯¿þÀÇ?|$w6ÜŒdƱ»zÜ{Çbâ åO"¸%îÙñ–¹Û÷¹²~ €+ë·¸þxÈ»gàŒƒXßÅ¢™5c@q’ eçÑ"¸¢?põ‹ÍÔïw3¿³Eï7Ò'AP«¨ Z•”ý "÷^–i¯.Iɇ  T˜D,>‰‚é4 gCÄ`B¸ðÕ€xM‘‚±»5«÷;…åïÜïðÆçŸ‚Å0Ö*(–’:h±‰@[•§c]9mA”µË´þkùX*ñµý'Ž~ Y;·*Õ™[MÖVéúÏG…p¢éÅ6¬é©$]7euÙˆ³¶J¯ÝýŠWï|ƒ5ö ë˶LŠF¢uW%_Z PGW»€(挶k¶A΢ÃÀ¶$CL•s’(ΣWn~À[⦅3²‡7·¹–Ô®›ªP•ŸÔŒ½¬Þü’+Óè®^¬¯¥Ç°eÎÝþn—×kÆ^V/IIËÿ£ðž½>4<ÉT'¢­a”ý}ãÑÞ…àâ¦nFÝ,¶7 ]‰ƒ@Yñ×i¶0–Æw§±Ü˜òYeÏ,Ûc^]ygsÔÊåxì³[u:mDÑrËîfƒÒúØfî^Zz Wÿ|ð¯!ÁDÑßéVW®P•k4 gC‚‘bÜ{í¾jJ6=6;ß,=j{.€6(:Ú}M§Sæ¾J…€×nqyÕÅó¼ÿöŒºz¡‹Àé¹þú!gû¤®¥IEND®B`‚smalltalk-3.2.5/doc/images/index.png0000644000175000017500000000230112123404352014245 00000000000000‰PNG  IHDR((œ/:bKGDùC» pHYs  d_‘aIDATxœÅ˜?lÛFÆ?©q‚ô´ñ²¨Ú¬M-£³UÞâÍîT ºØ[ t°»Ù[¼U£¸É›¸‰ã(êcÿ÷‚ÂÐ!•Å”(ê/i'h>h(òýî½{÷‘Gëîî_C[_… àYñS)ò™Ai J„HŠ·*Žñ\¸« Ü®‰f)µ¹õKÅ.Þ››€†@9Mð<§ùRÔœ\|ØÜú¥¾´Û—Æ" @Âð%ªš¿Š8÷Ú‡›ñ›ÀVÐá& ”JØ8×Dé™)8š~Ñ@µQsömoï`Šü²Ú­+8Îä”DJ) € ­K7šR'q`ÞœŸ°ªXN}EWS䋾²O;¨í¢êMØe>ù×ÞHÅpvp¬z’"?\î+~ÕƒW…³£šÔÐ$ÔTÙ g‹¼ «Ã–é/´ÁØ :öY®‹2/€‚4‘¢hîâåyM©“¤›êìà8 :kÁùü¢ƒ2+i(A)¥48_®ð2uº§WÙ‚ÏH¹'Y/DÅ…Bf!„:’™j3¦¾µJÙ†Z »]··ë½ª/fln}Þº˜ÆŽ %Âá ”RfЬ€­íoü£fs©‰:­³4éYÆ¥¾$Ò¶-  š$ëG*OC'¨ñhϳ­W€ À™¾Â^L‘/.5Õ¢ÔЀ†Ù%›&ø‡eñOÛÏ穉äRõÏÞת‚Ûõ ˜$>lH‡Œ!"ZöaI7=ŒŒÿýþ×ߢ¸ nj8œe\¨ÔúµYŒ²¸äõð%ÕžÎq(Ë`zÕÀ—½éÇL?':°¬GC‰½iWë Ô0€ó2çN£¶ŽÊ¿s°$këabÖÕ9i" èno%Àowê‡g;Û;;o?þY–•ê®ã‰®ò&Ìûðhhâ‡ñ§ûû§Q"Šü ˜ÛBé-v5ÕGëS6VÇÅÁŽ-¸]ß@‘Êlær©³Hz Ø®8HJÍíºñÜâÔ⌕*{.fÍå:¹ÔÏG&®§ÍŪâÿ¡:`Ê@öî$v½"Ôo_¼ØÞÙy2ØÛõ ÒRs».šJݹ¹Þøðó’§žÇ1 øãÜ}ý’Ùud3fUAœo¦xÖÅÍõ¯+£:Y>s·áõ/7‡íüyµ,kUrñx¼Ê8?j³Wß'?çÆ(jNêÒ›º)Žãñxù³ àUµjj3·˜s»îíçPŸ$Ìi7³õ‹³b{{¯ÏÛ_–ÊÁšçí¤™×‚°ªØ÷ÅØìÍ»–^ÚŬs».jNóüòó©ØñyÛ¬Ú6nÚ-FA§{zv»O£6 契5[õœý1E¾êÉëÖ‰ÉlJsår»qrÌ+°µ/òÁÉÕÕAç:7{·Ñhìïy'QèUDvª«#%U()IJî8Âq„繮؜âÓÁ+Ç‘(Q䤸­Fp®ÁÈÏIEND®B`‚smalltalk-3.2.5/doc/images/back.png0000644000175000017500000000254712123404352014052 00000000000000‰PNG  IHDR((œ/:bKGDÿÿÿ ½§“ pHYs  ÒÝ~üIDATxœÅ˜/tã8Æ¿öÐ2…Ùì æ°3«—åX¥ìR–²”Õ0e kY|,e Û°sX–Å,‚b+3‹UìÈVä?I»oïÞ ¤ãZ™ß|£ñHÎÅ·oßð3ÆåO¡øåãSe¾…9ˆOŒ¿e,?päŽKúŸúžê»  ÎÕG¼]|$Õ2ßövœ¬¾¨¯ @@ =¡²ý Pãß½Ð{ÿX#ÙJÊ€Rª€’Ö„¸”z³»óøsà‹lC“ aB_*‘s)´_©±¨,ªK7 ÃéÈ †ß–ùÖeMR8.ÈJɪ²”¢º(ê_U@ j¼œÓÛ–ÞQÕGªïÃuẠ={B¡I&„:’r($¹½ç;.óíû`²4I àºèÑÊ¥ÐrOeØ¥€Hé ds7“{³'ÀÙÆ[¼Â±ê ¹…ÔŒžE-¬u5Žu†Ë¯BéÏÕmœg›“`™oi²çÁu+9œk¹\–ìv†]ã¡R Ë *]¼Ø ¯{;Nv¬TYHvçLp^-hù‡R…nö_XÕ„–\KS¾ãæ?Ǫ–ùÖ‹bBÐr!T:â9(±¥²×õæy.2ÖÊ”I€É>Ñ~TÜÛñ²t8‡RÈöòÀ4U¯+ ‚á~ÌŸjT”ãÑÃ~=Ÿ·åÚTFô¥‘KV_(¥d!5Ò<µ A¥) |-±­ @4L–«6ÏŽ†­S½Ò—Ç›_.…ÊË'§Ê(¥Qš–B¥zŽÂN0€`<Îâ†n»ÖXšê›%˜ªîÏ¡ìÞ w¾¨Q»ÖÒŒádÚ¨jÔ3/f[üĸ¦‚RÔ»¥4lªÒÇGÝÜÀ7…¦‹KGPÚŒcXß2¦[?êZ`Ð 3¶ßwëxfµ?ÛH#WAñŒ9:Õ2ߪýáØýµn3;ŠdÆVQTTTY_¼ög#Ïv¶ Èîp€S窶精í¤÷wBJ»K´]­£ÑC´áåǪv\´öMíâúõ‹øhõ&ã®]½í»GƒR™o«ªî{¥Ö:Ï(™ì÷ýñMÃog—8ÓC´á úÔ¹ª{t×¹Ó±tw-(-—o@–¬ÔÃß;œëǘ§»F4F½N^ ¦¾gžÍöþš>/¢‡ãå2²dåE¿¢ÊŒñt×àÙ¢©ïÁ¬±ê»Tx‰cY•ôx¹ ªœwŽäþÎØí5¦ëÒL¡QX4k8 löIêí­-ׯk# }U‚©s…ëÈhµŸ3âÁ ]<ŸBÊŒ->Î’UC®„‚ò&4·E/ô@©aÔŸëûûÇÁ K^ŒzH•­7Éííl­hÕ¶" Ž”kZ;Þfë¿øÝL´´66sãëÔ¦{jÄOñ?×j»vôñBQh¨§üš¬ÎÖØ6†QX„ž™VSç*œŽÐêDîÚãLÿ¢€?ÙÇúæñÖ †7ËÙ™ÞÔÝësÚwÇË©¿ËtèéÀ>ÅvøïvÁ3GÓåÌÔÔY°så…Þx9oKù`æ­¨íw§so‹y¶I/,MíóéÉv7ÖF…Þ÷¾-š!ó-ßñÍÝì  qhÿÀûqŸ%¯Gv;&/¢É í»ô×ûE ‡‚<Θȸ8T.‰CÝ~ß <Ï÷éþÈÿ1þ($/¦bðIEND®B`‚smalltalk-3.2.5/doc/images/inactive.png0000644000175000017500000000207712123404352014752 00000000000000‰PNG  IHDR((œ/:IDATxÚŘ;K+QÇɽ|†ø ÑÊJôØiÒA‹€_ÊÂFð{hZZˆ‚׉‰&¾ 1A¹vâìx^»©œBΞìîïügæÌ™µ¯R©¨ß°Ä¯PaâßúöööùùÙh4®¯¯ŸK§ÓÃÃó³³£££“““Édrhh(ÎÛú*1\ äÝÝÝññq¹\¦™¯¯¯v»J¥ð—N‡æçææ°ŽH|˜¿¾¾Ò$0PFHI…ñd>Ÿ÷ã}àZ­vvvöòòB—ððóóóûû;ÞþññÁ·õ÷÷›ÏâHߨØè ¡Ífóèèh||œt\\\ ®’ÇTšÔð|g¡P˜šš2¥[Àä^`ÒžžV«Õóóss}Du)æñúúºévËv‚VI-‹~ªéÍ{{{···Ú :q…‡‘® žœœ€jÔj*N†mÆ3;;;>0œŒlµT*©(3åòƒIööö6Þo#´———xòññÑCõÈųüWcÿ ÌÆr°_3™L½^ßßßw!] Eîe­ÚS4@°Yt†\”lV€]ùbÝ9d„”Zaä`¹*‘Òª+®¦\ ;I‡’èî!êuu…Áýý½«J°P3®T·¥\¢â/_²b°BÅ8sh ¯Fu 5=¬Á´å"¦!¡UßgŽËÃÖÐ*q0ȸšëãÅQ­LP€WÒjVÊd“ÇAÕ<¹2à.UG:N:ò¾©ÕJU¶vÝ)Źº`¤Xd\ÕÏÚI¥¼“+Àkáã.•™ßY‡•#›Ì¸ZšŸŸë‚yŸEj5cf•ÛL.‘Ÿ¢›»`œ—ê{/ùµÆ ­Õ+²/ ÁèùONÅ13:‰DX›ÁR\¹Ð™ò­œ)­Ö¢­D¯H¬îB°—È.ÅÙ²V*´âÎV«E—KKK`…`leLi.’—qÒØJ¥zS,//#¥•ü’`oSV»HZõ—Tí¦B.å öS˜Ãè™ÍûÁÊöSe6¡þ³Üµµ5’û ocSq¤Ávmοgƒ¡‹"¹‹‹‹h°CÈÀÎår|Éy¨y˜ßëJ`ùnZ²Ù,ËUf{‹M†ÞßÅ–îUŽºHN†‡qÆóã›››?n3— ‡ ÷רZƒ ?M*²‰= ÛÚÚ’u‚Ìùí„Þ_vá”ç$ÚšÃD©$kQ¥“}`¶ÝÝ]|ÅÈm¤žü!ãÃ×âêê*ZL“ Æw)šôêGs fÏ£;Dg*?¬† ¹²²‚,ñ {3•=âÍÍM¹\æÀ¥ÓÓÓ333ô?HdÏ`s4ˆIÒì?æ“Æ¥´iõ@IEND®B`‚smalltalk-3.2.5/doc/images/prevon.png0000644000175000017500000000262312123404352014456 00000000000000‰PNG  IHDR((Œþ¸mgAMA± üabKGDùC» pHYs  d_‘#IDATxœÍ˜AˆUÇ‘ÞÞfÁÃŒ t¤¦‚°{Kb½´ˆ°Áµ qÝ[]¨Âzì­=´l<5½5âÁ€ˆII@0*é+vrË\dßm=LÞÌ›ÉÌdv»ÿ2yófÞ/ß÷¾÷}ïÕŽŽŽNøëÂY gCP %JˆÁ„Ù,DH‰r]„í Z^t}Å–Ý<õ8µÓZ0œ qF’y÷;Oãv( €™ñœÕÚ@l]Çi¸§­ ¨ÁÄ^€ œ'÷P, ×÷÷*ƒV¬ûXÝ>B†q›’ÎñQ€Ì<ã–¼O^«ÁÖãÇ/Ά8r޵ß/R©9¾?e$å” 'ë<@­öÁ>bÓ)´f!`ìÒÁåzXŽËx4ß§+‹Ð¸U4µUâò׊^âÈù\·×« WÜk¾·»š¹}s-X÷±÷ŸDnݬ3 èõz%CV³€c\2÷î=_ê¿dÁp6ÄêöQ®EèØ•à²*²žC:š™û_߸­¯e€ÎHÂÀGˆu欗µ^žë7?Š!M™ÁxJ0Jÿ½”‹ÃÙ·µ‡p£!îù£Js©Ìµhûä˜'µµÜ>ÙeêÖ¤LÊ‚ÎH„s””ŒÃ`%\ÙR¢uñî¶OŽsïÙ‹ÏFذbœ‹ÃÙ§3@ç‡Q…hÕʳàúåK|úçï…ï°I²Mäj4ãîÓxÙIŠÒŸDp%ÖË‹Vózýò%®>|À›ï½»Îδiã):kÆ€â0AÊæÑ<¸<«}8ü¾, Yô~uÀEc*-QURþ°þ­uõá}vŽž¯„Ós.+±ø$ ¦Q¥t¢ù'“¸*Ñ ^]0«ÂåãêÃû¼óy»ªŠt™–’,,hÙͨØD Œ’IÃåÍÇOþøõ\àL0ÓºýŸˆEÔÎNy¹µ~÷·OŽyýí+ç'ê^ iÂjoÅA¢\—¹±´äe‡ÛëÙYÀ´äØ_v/à´¢™XÐN¦hQUr¯¶Æo:/  âêÛ„3+rkáð°åÉS?ììr¯¶Æq_­Rž;µÌåÍ­o¦•ë¦:”¥9€oÞx‹¿uNêdö-ñب%\µ¨ ^I×eÉ_÷üvg7­¢<·š2ëCÍ“ "ÚA™ßAæ÷/;»…•JVn=Cl_#t,Ò°l»Þ@ÿ‡в›8Û7r³H¶-[Ói jk<ÿb¿ÎA Œ½4OúØ‹ æý¬v+¿Ü2ݬç CÚ­YÙ™ï_~Å ¶ÆüÙO… @ÊÉ×Ôf2ÁÒµˆ6Õ&d@~n΃45k~À ¶Æ?Ï~NµgB‘¶žw°ŸÚÝ¥-»‰Óp­¤—ä[Ï„2£_€Î¯7ßgZ[OÆÈHß°ÞµÖb3=Zî®.|1äA#gͽC^=—UQ¤š­cT¹.Ðþ±Ã±—Þçî‹­‹MÚéÉžÝ"fáÌxœzÀÖÁÞ\! €ØtØ2æ£ ™WÐfO¶Šà$*åV€Û{©À0µòlFM:Ÿ¥A]¢y©­¨ÁÊ,'Qø,g( wê³™¬z7o2d ‘Eµ¥—ŸŠN·nÜÚfÃU?|1$˜Hz»Å qU­²Ú™µÂÙ`$wŸF»¯Šrê×Ú—µ   ŠŠv_Ó锹/SSÀk5Xßpñ<ï¿=£^ ½ÐY`òt®€¯Bÿ,Ž:Ù¢7[IEND®B`‚smalltalk-3.2.5/doc/images/indexon.png0000644000175000017500000000225712123404352014614 00000000000000‰PNG  IHDR((œ/:bKGDùC» pHYs  ­#½uOIDATxœÅ˜!”Û8†ÿôh™Ë,v‚.KXÌb¸e[¶W–cVØÀв…»‡še5»@‡Ù,f1;Z™ÙlÅö€,Y‘ålÚwïu@^dô韌FR&OOOøöæ—P¼½Üµ­÷ G.¹ Ù¡®[¹dŒ„”$‘dŒ¼§ ÂÅ%£M. u[ïiΛíß(*õD’‚Hµö ’)¹ù@cö*þ°B’õÑ6ÝCH¢‘6€Ð_¦wëóøsàI± ¶;Â[Õ”œó¶)!À-7æëË(‰o¾}û1p[ï)o‚MŠˆ²)Ë*çœ<™ž„ƒ7žËû ™Ñ¡t¸ ov, (+ò e¹õ@;ê˜bc7¾°{–åMݦéyªçÝélÒÕF„ãà*ž»póˆˆa6Ïò,MSß°ç´ úKn=üòôís¢¸­÷Áv'YÐÒð Õ¶¡\jåvl=ÿëㇶÞûÁ4çÈJBÞ5‚Ÿ¡*¹w/ÏŸ_žÕ§M…¥Øf‹¢y?ÏÜÖ{²~ Œ¡âéãh„Ç‚LOµ:½”¥«݃iÎEÛH΋VŒå‹wåt‚4Þ¶©í¦Ewµº­÷ô!S•)ÏaeJñ×ÉU?iͶÁ¡.j!ëD+¶ßÕÒÒ›„/rŸ\'¼Žbª‘Cjh5;ÅE¥Jmjrìpváu¨Þf“ÍvÆQ&&Ô’ Òí9ªÓÓNceVØ  †TC‰ª ¯ñ*Ÿ³C ‰æÄØx¡Ú Àìc•G¨P᢮["µGUȱZàëäÊ–xžªäÚowY‰þ7æ@£ß¯ÃÞõ:F%óH±Í ÐÖû,3±sØ[(0’MR‘xQº¯„ ­8¤uL+.“+ •#Ô ¢uA¯¥óZq™\©Ì,T6Ÿõ`ɘy1–SµŽcÝàö$c=˜¼ïeŒmÙ¼TG.¬½Y±ô&A$SÇÕÎ#ï0Feón(r{Ý2€pƒåU™ow¤ŠG~Ú7JâÞ6ìÊ{Y}í~üï^xºÚœññÚ˜ÐKÁ¾Þ‹œÛ£óèzù»÷^ú3`ƒ‡„<Šªªš’›Ÿ JâwSEÑÿÿÈè<àR’cÿÂ>™ÌÎÝæIEND®B`‚smalltalk-3.2.5/doc/images/nexton.png0000644000175000017500000000260612123404352014461 00000000000000‰PNG  IHDR((Œþ¸mgAMA± üabKGDùC» pHYs  d_‘IDATxœÍ˜½‹G‡™sb¯ŠÖȲNu1H…ñ© œ»3r9XÁä:—'° ý רܙ@¬ë¬.7’1Xª"NN¸ñ¤±V©´&•R¬v5³_’.Gð„V³3;~ï¼;`6øPuåC†øè¢ ýqˆs‰’¢Ýg<öR¢Q´7¸¾aƒ«¸³v?…Ñh4[ÌîJ&ß 7ŒÊà¡°x(ÆZ;«²…Ø»ƒ]vÖ]0µS<²¸‡Bh`q8O»Þ:®­ º`¡×Âj´ÒÊ””HÂ…ÈX'çyp+eöž=ûo€þ¸ƒ-'Xõ&¸A—JM †t¥L@épR»N U=©#¶íL73£¶û(ÇŲzÝ6 4dÚn™ƒºörB~%ë!¶œ$àÍæÊpÙµ’ðÍÃ:ªï¥ÖMu°ÐkQ¬ŸaÝ.Ñî¶i6›9]®æ€­]wc÷ŽFïõúãV£…r,|»˜ ÷ÕÁ·©åYîÙ˜Ù\ŽÝz÷Nð~Í´»Ú„ØdâÉ\ç¾ÿõ)t/ÍE;öéõ†x]óï€þ¸ƒ¨"†’æY~XŽgS¾xx”Z›¤sqém›‡uÃEÐîJ<‚’’žï­<Ðï<ªñ`6eóóë‰z!XÜ9€âü³o£¹úãÖi;ºÑ]![ãº÷ö ßt^D yî f›pÆÑCÝk<\\8¨@ú\Ž{˲õÓÛ·¸÷ö ™î…p¡ƒhߌÅpÖŒÅù)>¦Áå…à“Û·øiôŽ›SïSÊô?­Î=PÉ  X•dÃ¥=,K¶ÍõûUögSn>>6Óe#柅¼áÐí>þÜ×Ä- ÆY,M×ïW¹ùÇï©÷ôUP¤Á¹ 8ûJ«<쩕¹ª>þò•Ù”ÏEe6"ºÖÝmµ& ˜gíD«´Î˜[G×ը̦ØDÉ uØ0R‹1è8†Õ«ÌÕäÉ/ ›ÈÞ µŽ] Fd´'E›éÜŸs—÷çñúêµÄ<9BéYó€/B\qÅ+f™si3CØû'§¼¾z-5œ¡ô×›SÚ4•ã.˹÷ONyûãa•–± …VŽcЦ'—á\»°¡µ[À¥¹æú0äYLu"ØæA…ßy+€wê™pNiчØßÅwl,Rs¶Z*þ‡ÈA«¸ƒ½ï1l'³*”åâäå+;_ÇêšÎ)m/ÍY+z÷é½ZÕ b¾?1–[ÅÝýè:|ïÙÚ'K¿|E»°‘ ÏVÀø%QQe@m/XbE½u\3 =òCÚ.lðg ,§K¡Œ…éž{R7vwÉ%ÙAT«3Iöból>ÎôìÒà€D¶¶4÷v+[ˆm³· UÜ¡R¯eñÝ—¾žƒØZnI¦êêipP>:LìS÷ÅÖg;TOêK!ué/à,¸°TM”ñ̽“Sw»Ø¶ÙÓÆ£™¶ ŸleÁI”V€'5#1t-=›Q}ÓLP‡`\†.f%„'Q H®ŠB¸µÏfâj0lÇ £¡ÓÉVÁéÖÝŸ÷™8¹Çp«ŸþÕÁëKš‡õå•—h™k å;x]I¯ñ<Ø}­(»ä²[ý.÷¨íRuPT°û‡LÒn¥Ìæ–ƒëºÿïõRè¹.“¦,^7¶H-þIEND®B`‚smalltalk-3.2.5/doc/images/blankon.png0000644000175000017500000000220012123404352014560 00000000000000‰PNG  IHDR((œ/:bKGDkzu pHYs  d_‘ IDATxœÅ˜!”ã6†ÿ½W 2³X},a1‹áË²í±”Ý²Â -;˜-º;³ÆÌf1[³ªhef³ È’Yvܾ¾wöEöXŸþÑh$íÝëë+¾‡½ù.T?Ìwmë ä…K.ÈùR×-á\2FBJ’H2FÞQázNowsBÝÖÍysüE¥žH@@R  ÖžA² ›÷4f7ñ7À IvÏDÛt!‰FÚTBÿX|ÞMã§ÀwÅ)8žoUSrÎÛ¦„·Ü˜ï[DI¼ùòåßÛ:£¼ ö)"@ʦ,«œs>ðdzÞxn{²¤CépÞóE²( ¬ÈÏ(Ë£ÚQÇÛøÂîYN”76õ˜¦ÓTÏ»ëѤO{yŽƒ«ø®8…û¯ˆ–«s~NÓÔ×í”VTÿÈ­‡Ÿ^ÿ´}®·uO’- '¨¶ åR+·cëùïïÛ:óƒiÎq. yÛ>Aµå:¢©õ×a‹¢y?Î>Ôm±dGð[™OÌœ7È &®©ÐMo/Ï*ËzÅ4ç¢m$çE+ƨޕczÇ€!°°Ý´¢ÜÖYð|V¿óñVæW{j µÖuͼ8~S3­7 ^^ä>¹NçUh¶C ­¦2QTªÔvŠÉK‡³ ¯C ß¼Ú0g¸òEô`ɺ=ÇCu¾tlaIA(ˆœ¨ªÜÖ9_ZHhL´"°ŒI} ú<Í>ÖYùÒƒp]×-‘Ú£*äX-4TørØçIœ·§s‰~Ž9ÐèwÓux˜ÀT²ŠÛŒ€mé9fÌd¢0a2›¤"ñ¢t_%4×ZqHê˜VÌ“+ •#Ô ¢uA¯¥i­˜1µNl•™…ÊVË,3/&rjŽQë8ÖuiA2S¹È»^Æ„Vqkñª#ÖÞ¬Xz“ ’…ãjçÑœ%k¨lÕuEï[F®c°]ÅjH8×ôñÁÉ»9'V©ßøz ¹`2;Ø&j[ìo&Ú*«ÇHNõ·©NxMƒCª¼‰¹dêùÛqñygØÂ·l {šjg“´äF‡½9köà \Ó˜‘$6ì±ecò_Á†Z«yÒrï“Yö]^¹‚pì·¦iŸí÷›ëH+4•ñ§'ûhíž«ƒŸÖÛÃ~ŒmÌ”ˆ!Uµ%BšÏ7‡ÝßÑ­=YÒžlÃvöUqHå&Â~=ìäÒ­£w'yÏ¿ôx•çJ´7‡•C–×µOQgÝlK?|¨Îv¼Ý*ùõ·Q?||lØÞËê­ûñ_™¸ðôi?áãµ1¡sÁ¾ÎD΋ã7aJÒˆÑUt¿ýÙ{/ý/`ƒ‡„|UU5%7S%ñÛ‹¢èÿÿÈè8`.ɱ6Wõ ìÕIEND®B`‚smalltalk-3.2.5/doc/images/home.png0000644000175000017500000000214712123404352014076 00000000000000‰PNG  IHDR((œ/:bKGDÿÿÿ ½§“ pHYs  ÒÝ~üIDATxœÅ˜/xâJÅû=1¸ÁeÜŽG\q »®’Ê­+®u[És¬«leq[‰$®uàˆœªÎ¸\—ëxbHH!@xKwχ LÈ/÷Ι;jïïïøúòW¨þ©~+¹H0xa±Iç1/ 9‹@‰–F»)š-t«<­V%Õü5¿ø5NÀ öM)Àewг¶¾ü&:ú þ˜ß¢ÆÌˆá(!f ˜²Ö j 0@€”Rz/~˜çõ4±JØZ#¢"Øà2*ßšª×éÝôƒöù`r‘Šy?R̰–1œ ¢4»ÓbÍ© €Àý‡‘ Õvè%®&©™•S„mh½bçΨNÊRj’Q½ÆW·æÅ‹ƒUœÈñ Ú!”‚ÖÀ f ^S•ÆŠ,VÊ ø<¸³3{Ìó‰=Ck4$d”€SPBÖ’[ýÙ÷+2s튵¨ñÕ­›Ov‚ù-R“%°Ö±µœH.ûÎ{c-jús\LøÇˆgFÌ pŠ„` ¬ãxa¬±Îb«_yËM{O§æÅ”€ù-R·÷« ë` ŒñT?‚dýêu½L7¨¥±æšÜò ×àÆÂ3§Œ„`-Œ¡El¬±On.Oý±L+R0Qî²U­&Õ%>‡ Nm«WîáËüe0Z¦·µúAª×ëã“Ö+°`ðk ÀÀTHiNõº^n´`´L¯jµ*`ó:÷o¸J5/,€ì+bnW—Q½–Ë*`XØ5¸›Œ¬Ä§[á&{©G±mlÖàt€”l6 ä±zûì§ÁžÇ(¤ÚPYõGzjEöt¶@ÁÕëZZìÔl’Á¿µ:>š¹TU,V'"eã8PÈûUÊ jñò÷¥¥„O5¹(méâ´Sj®S)[2è~ ƒn£ÝÄÖȡ´³­«ZÍŽ{VV@šzÃÃÛ®X›J45Öµº¥þ UCˆ–*€ÄY{W¿žŠ à¬×a5X]}ù­´_OHRꋞ_ø­w¢£!¥_Ií¢–Z©º¿:µÿ¾žeÐí ÉçÄ @Hy6ˆ¯ÝM0ÑѪ×ù *€‹0äŽÎ/?€eÐíÝô?ƒª!ôM¿¸¬ß\Þíóó‡ái© ®ŸF¬êÅËô¡º¸?[B|l³±±‹)Ë «;ºÿ0ú}ª†øþ0ä²mãÎÝ"¹ˆm:ý9ާÓÿGí÷zú¦Ïª^ºYÝ·Mõk`ób&w#&ÚuÛ¶\Žn*`çÁá?OFßìõÎû碥øÐ™D¥£ˆõž‡aÖű3›1‘R‡a»ÝTM]…w¸ü%>J]rQE*€ÿo“b«%„hkIEND®B`‚smalltalk-3.2.5/doc/images/tocon.png0000644000175000017500000000265212123404352014271 00000000000000‰PNG  IHDR((œ/:bKGDùC» pHYs  ÒÝ~üJIDATxœÅ˜-pã8ÇÿÝ9 2‡YlµÌËf³º¬ËÖ=tYÖ²”m`ʶ¬Ë’C벚]Xf³˜Õìt¨2³YÈ–ÛI»77³o2‰e?ë§÷¡')GÏÏÏøòî—PüövÕªØ@‚äöéDyiRÃ(:Lx¶;šèj!·¢£Ðµø(]Û‹{8 c/Nâ(Іº=d+Ú\$ÆÍ¯Ï›:;WÅÆ ×’YµPMé›KÜöûN>UÅfLŽ8#dT ~€jšÛ1šß¶Hs‘´ãl]]Ì cn³ä@ä¬`b—Šæ¦îír»RYÖZL.ªRržVbupæèÞÑ£Ú€ ¸¦ZcQ ®ŠµŠÕu²?‡• ÆÕ ­¦M]ÓOÃéf‘àÙ@2dn'‡ûq »Cµ¦‘æªÔÖ`òTãÌÂÛ¡šl⊙ ÅU®ór, ñÒøOûL> ¼oÀ’ R¯9àxä2);}¥s?¹Éh@/wfd~;ɮ׺é~:‹;T1¬@­ÊÉ5€REžÛgx *6$ÞVØS†´8¬CàÌζ3âQÁòÒ¤ Ö±^ÇjÉž ’˲OŠ¢" ²ÑÈSùÝ­?¬›+ÿþôÃ6ÎÏÂ'u§â_Ö§~6ÿ¤š–»`ãx¾=ýVϯ2ÿ´ˆV§Ã¼Ž3´1æ Ú¹ ÈS9:– "þ…¯©«!ª’Ÿzá#69/Y¡lå«q³PNæ¹… &P›z:IÆ´CöÖaö¢~ùJèlâ÷ T±åNG#Ky¸ZÅD}xšuº¡µì“LlÚ¡šÁ&?®u&mI°Wý Re `1[@*K”¹´alèBÍ\êa‰/êÁXîÂýö€ãùþ·imúCš$™*S, GžOAèì’=Ö ¯'*óÆÐ1–Œé}?×Ç"¿8³ÎléÌ–­F7!ãB~¾ nÀMëžãTBZÝŠeXü±­ƒ¥X=ή×ùí—Î#™Åéøê…sÉǧC´k³b5%“À Ü*ÞM„XDþò¸]v²ë°úžÀ£sÈ8/Ó¤â4`ž+ƒ1•V)x‘f6o<õ|e|»,ëûøË|Ÿ­}±w›ŠJ —m#jÊÖl9'gÀ\µ·yãCTû穼¡ú€ב|g*ºwsͽe®Ã>@•¤½†ŽŸ³\è½f ¶ìê3øšÝ_Õ•èüW°¾­f¯sÏ—ŒÛ.wö\–},¦ºiîÍõµ]\wKD_Ò†Êÿ땹µîî«­÷'Óåb[‹.¿}ªjK ‚Ô¯Ÿ/ç/Îkz2¦çwmz«—;󍨧rHía³å\ç”–½g'¹+cv1€6Fæ°¢rÈl·Î+ê›ÎN¦D¿ÿžÇ¦¿»# •?’ÝwÀŸ\^”ìxð°úÚùøŸØòèjq@gPöúVp/6"áiø šö õœ³éçÁsék<$ä“Èó¼Ì¸ø#—9Žóÿÿ²wðVRGþ £àÉt ¸IEND®B`‚smalltalk-3.2.5/doc/images/prev.png0000644000175000017500000000230512123404352014116 00000000000000‰PNG  IHDR((œ/:gAMA± üabKGDùC» pHYs  d_‘UIDATxœÅØ=lÛFà—A‡Ðᘉ—¥e¥:Q@«@Qi´Ñ%âx“P£ˆ§Æ[$)Ô©Îf1¤-ì-T@1è w©…ˆLçÉÇí>tÑmî@‰¤õoE@ÞIH>úî<àyaØÌ‹áøƒjë^ëÕÂê½r¹¼³µÌ;‰¥^Edÿ„jëHIÕë))IJîºÂu…ï{ž˜_âêðÔÿ'Æ( –Tü6–D»×?>XIEND®B`‚smalltalk-3.2.5/doc/images/up.png0000644000175000017500000000252312123404352013570 00000000000000‰PNG  IHDR((Œþ¸mgAMA± üabKGDùC» pHYs  d_‘ãIDATxœÍ˜?lÛF‡?ÛM@hsZ€\ÚŠÒ@ÑPCklmI¦&EŠ:Ýœ¡@ tˆ·™4Ê[<°ÇhJ2µÚAÚl ƒµ‰[.“/YtЏ%Š”DIT›´¿‰ïxÞÝûsoéìììœÿ±–ÿk€Yú`щ:lcXí*$Q'€®D‡ a;°æb|<«ì ìÍÂë,Ýbó²ÍjWa=ÅœD˜º?&™£|wûNÅ-:7 yÙfõTb×cŒAëCb9pjÂw´øµ¹Aç\ê4GM,ÙÇP*”}ë!‘Ö™yiÀ0õåjïþ¶}q@¶)©ö^\wøBJ´V(ÛK,< . ˜£1Ü;¬c•\kæz±Û8§ {¿ •u(ûCÈ’Ž3šhN¸Ì÷û–?¸»‹:–è°] °tªcðËà8Ù—‘FõL—Öè¶Žní$5vö0§“NlàR§‰}ÐÏ‹­%Jñ Ó¡µB‡ãÌ;si8I¬—ÖÁÝ]ÂNs6 Ûˆ£f f­öÿŒ@)P!¨þÙ"w[óàf©µßÛê1ÀÒ±Ä:Žã¦‘Â]‚(DñØ4Üí³|øé'á&Y.­ ÕBwóÍË6bïhø‡ AJ‚NJäÈÖ¦Už4øÈqøñÏß Ã ÔÜ;ÈX1¸z*“L¤c8)Ñ2ˆáŒ¦”Þ­ï°¯|ÃÊ—— í3“ê°õø÷øÙP ­’(źQ¸ŸÚdúþ׃ÂpÏÐIµDÝC:¿·^V+öÓ¤ˆüP¸>l‚ÕXuüŽ}8ºTÑâiœ}ð†¼ÁÕš^\k¥+Ñ/­Ü`õ P2­ò¢1‘@iœ9yˆ’EÖEÖ˜h1yžSvYû§«'³Ó•â&k”ÖeŒVi}ä½BM{Ž|2N "À 5rvÚL{û£ÿ‹J«ñ&3Zתób=Š-{¸œµä²J€u.- ³@÷Þ$´bðÊt~œ×;@ú ç€r'žãÁ8Û§v³%i*¦ Û¨ÊD'G0åB;Ai#ÕÓ:¿³¢p® ¾Î‹çx<>zÑÇ™n™`Öò^^ v®}QÍzć2ê»¶eNŠh´¼Hã¤Ìwlœt_1í9Û×`R²â ”vKºÙ‘5cT‚¬&1›ÿ,ºrÔ‹dZkµ©¾¬zݤxjÕ-­èêÀ`¾×ݦê¥2¢Z1!ªBÂxrï1 {ÍKÀ¸R8DYN‘€àYr(¸ªRfÄ‘ô[W„C>ZŒ*mÇæ9kؾ™*X»Ò:è©©Á8l8+l¶b'&ɹ8f.Uý}×¥ÚùçÿXS—ƒÚÆ€ôÍ›3\j™ïäla©ºé+Þaà£Þc­üîR% Òmz}{ ìP…ßÂjnD•‰ÃáÑyêÓ‰Ý^wƒ„9Wµ^çqÜ|^8÷Z=~ã·Æ5Jwk­£é­9«=®0‚P©jÏb7¹/^…Ó‰?Ów@ Ìw:Ëä×µu¨–7Y¹ eÌ̳FÍ•¯?‹÷ [Ru·Ý/»ø|õTìvçGò$™ÜŒ/ùOâ"°a@ ¹—J™2Ûk­ˆX&<: üÿù?žtÚ…<ÛþÌÊ’ù>0IEND®B`‚smalltalk-3.2.5/doc/images/help.png0000644000175000017500000000237212123404352014076 00000000000000‰PNG  IHDR((œ/:ÁIDATxÚŘOhÛVÇ_Ò°)°±§±Q +ÛÄNöèAîaÈ—³]èa‡RØÅ; vÈBÃÇÐCqsj`‡øèÀRÚ[|)8ìbe0ì›uÚ^Gd?AǤ­Ð<tû=I–e[ÿšúÃ1òó‹>úþÞï÷{¿ç…Ñh„^‡-¾*ØRþ©®}"0´< È$NßDâÚK2*©L+¢¢*”e˜†¥Õì"­Œdy2ê¸ôœùÔXGS=ôþjµâ×ˤu½pp}Y.³ŠnD³ ½Ýo·Ö·.1š|ƒ`Þè6C¹h¾¯†ôÖÁîåR¡i­ì²é]7¦¡‡(Û¸il nÞ¯;s§˜0O­ŠZ;h½:<¼ZãŽi§EXo衾µZ­jJ8ªgœaã‚#×£zƒE¥™VÄRµ±ƒK2¬kÒ9ì_ÐŽÓo?ÊT_™ky~“ÈõSDô!à lJh¿OyÇO°ªÊðÒ´bQN—xqp’3Bq0’“ ö?mU])»Ð'IEND®B`‚smalltalk-3.2.5/doc/images/next.png0000644000175000017500000000232112123404352014116 00000000000000‰PNG  IHDR((œ/:gAMA± üabKGDùC» pHYs  d_‘aIDATxœÅ˜?lÛFÆ?-pZŠS'ÒKK´iA(@nVÃ:9@†¢Cá]d8(ìÍÞbÔA¡­öP ,ÈZØS“¡@dò&A Âípž|Üîuòmê@š¢õ‡¢Õù&Š|ºß»{ïÞ±pyy‰w¡;ï„ à½ü¦zL£Ø—„òô…’&Ê–vlØsMܨæ­'ÔúÂ+ö%;z¦Ï TÊLp«~߬X3ñ3ÀúÂ+ö„Ñ8ÖZ)šQåÍçNc3Ÿ.øm~Ôf‚@ʈ- €sE”X&àðúBn­bo­ÎÊ-Àz%yeìœÀ²â[BI)Ò4ÍÝðš½ÑÚc®9îú„UM¡gö¤±ßFe®³K<~ªIeR‡ã@8XÛ–]A¡7\êI~Ò…ãÂ4‡wÉ+Q¥#œòˆN6wtodŒ ~Û8höQâà%ÐW E$ßÿj9m9>¯ • #w¬m‡~{*˜BµQâ`E )!CH)¥úô÷_Ç#yr[ªvU6‘î«ÍEGžù9©ç/_þ\ÍÕ?ÈYt4KÀܨšu)Ïü™Ô¹‘çöÃų̂"í1sMâ<ʨiÔÛvDV‚§Ïp?æFÕil¾=*ã|q§Î>®Ž‚˜+©Ò9÷×üúÚuueX-n€¹Qµ·VßÕ³õt[?ÚÞÎÊÃVãÍR9X½ÕÐ7wÝ =sÍÕ§oŒÍÁ6žî¨±SÌ07ªfŪ·Žÿ?ÕÛn5ô¤ccÖi1ôÛý“ Ó™Z«Õœ½:¦Õgœ)ôdW<ßÙÓ©CéLÙܨímó²©ÙÔ³ÁÑ…ì(¿ý|¦÷v­V[]ÉóM"×§ˆôKÈŽ ¥¾/… !¸e™–e:Žm›Ù.Ξø‘"…^N*€ÿ×SþÑFá IEND®B`‚smalltalk-3.2.5/doc/images/blank.png0000644000175000017500000000177312123404352014241 00000000000000‰PNG  IHDR((œ/:bKGDÿÿÿ ½§“ pHYs  ÒÝ~ü›IDATxœÅØ-xÛ:à¯{.P˜Ì$vf³†%°c»¬ƒ[Ù [¶°6lc3ŒYÊbCUb:¬b»À®íügK²”GoŽ|tlùâåå#ÞýÀ?‡J6e­…A®]–c¡É.$ÚÊG!BÅb €‹î!£]2Õþ9m- {øæŸr\ã0 ŠTÿ½ì¨½üØ?§­¹ÃGï=‘ áùšj–EœGÛÝü.ø"KøCÂ4€1…­á€sGTYÁöí…â^'ür-¢«_€É¦yƒ ”*?ÒšÈã§méÚ7µþóøŽÅr=õ UM6•s#ît.G¥ðò[On§Z`ôéÖÌ4Ùt?Ì ŸÌŲþÔ‘yõ…ZEs†›“¼“›Ÿ¯”Á|‘%b” pðü+ȲK?^?¯•JðEºUŒ>ÝÚ,Ù “MùC‚€ƒµ€Œ±0ÆÎ×gx]ÝÓûIs—à`¦Ù,/³tTªù"wV{ªÊx·º’kùtªg‹êmݹüs*` ŒÊŒs­µßµrQ‹H#Õi^í¹&rBH8‚#ÅúÑž‚·¡Qx"?7¸ª©&›²ÇÈ{Cdr£qÍ%{¤ZÄ|ô­8ÓeÆÌ£èÞ\Î,Ñz>Zð”=upSí…©Z¿ó«£¬®ÁeõW£˜í·ªÎu¶ñ¸½©©žne¡:Ç.Ë<à<à\õ:çR<ËQWõB—+†Èn:;“ ÀÌhTµ°±7Và‰È¦%Ì…tÀzo:¹ @ ÉE÷²)Úªúâ¬*ÑV(¦š‹®Â?£¢uq…j¯z•q~9è³»«0ÙQU—>­ àCûNÝ-–`.ºá—ës¨ L ûÍÛúÕÛ[]}O«r°þxè—¯ºnèY,¯¿žÌæ`Ÿ¿ÜÚ.fÌEWvTüx¼ªÀnÇC¿iÛ¸k·h³dz?ɧÓßS{½^t×Ç–­úžý1ÙÔÌô÷ÁolJ÷FÈEïî–·¥g[쇋fê²äûÞìÃ^¯w}uÈ3‰ƒE4ÿ„™:k´É2£5iÍ•’JÉ( C¹;Å߇7þ" Œlz  àuœ$µqõ¤/IEND®B`‚smalltalk-3.2.5/doc/images/toc.png0000644000175000017500000000255412123404352013735 00000000000000‰PNG  IHDR((œ/:bKGDÿÿÿ ½§“ pHYs  ÒÝ~ü IDATxœÅ˜!xâJÇÿ½ï‰Å-.q·2u‰#ŽÔõ\ÏQɹֻHêÀ²¸â.ŽàÀG䞺Ûq·îžØ(PÊ{wýÍf~;“ÙÙÝ\üøñCþ À?çw¥bÎ jk…\ê,ÇZR¡¸ãâR߃'XààNókç„Ú|Ÿ×ÖŠŸÍ2 a@ïtS|_´?¹¡xÿØ|Ÿ×VÒé=cˆ4 èêå[Ĺ߻??¾È>N˜$Pʲ% p®‰ªž¸Ø\h ˆB¯Órüëÿ¦b^W?x!Ê&)‰”RzÍÝbC-íÀÜú,p]?’ÕTÌÝ•r ¿d×yùÔ>IÝÚ0üÒU IÅümp}¥ød?€ën[5©ŸÆR+íF¸òu·ƒÕä>6«½48_d‰3Lày¨sð:˜Ÿ M¤¨xñò¾¥Œu·ÒðK·È’WÁTÌù8AƒÕ€4”‚* ”RœFø´¯»J“Ý€¿×’-òÒKM%5_纆ª4>á+6ŸöPyšÊźºÝV.ó}îÆc0ªJs)¥95sð2OŒ)‰‡"¼´¾×V’H;Ž MÐÀÎi¨¾1}Ô×3© ‘Y)\U¨©˜³§oÈ(E¤r%•Ò»SöèÌ9Ÿjµ>Û/]zÌ l6¤sÆPÖá R8®¸Véâ(Õ‹"JJ’r¼Ì–!î·àÚZU¥Ÿ‡7›í½=<¬â^- ;ÏÏŒ—Ť¤ƒá´ƒJp«ÿ¶o«Ù4~þ´gÊF{“Õ¹¬ƒŽRÐi·f³Ê¨UÔ¹‹Ó…mlž¢ÎÝnn+Ážr‰êë,×0€sZ­ó««¬{oÉñ$ ÃÕó7/î•-érüùsòð`ˆ8¾wÝízQÔh·l‡äáapu•MSžåØfõZ–3†H:]TîS!Õ2s;e Ñð*°œN•”íÑ@p}SwÊåd9žLã@ž¦ ¿qV«5v²ZÙЭ>àÖK»épXUÄåxlßs6ëØb2®^\fËCk†ˆŠy 掫µ)×å¼FT5Úì-mm–^­¤¯H8.wšP1Çå¶÷ÕÞªñSùZÔ¸éõç^Ýömcöœä‹Ô^ßöûv@Q§óu¶8;—6ÔÜißÛ£V%Â4 ˆÒÁж\ýú¨ug6s|Ϻûü§ƒA‘åçÙlôëW«ß?êqÝ÷°]$6·`y÷¨–~£Ÿ£›FC ïËäÀ¦ÛþüÞTƹwûÉ.‹Û \ÚT»÷ YA9}¶`î4ýÞýûQç¸Í>6÷ÁÜPˆ(|*€› 0á¶Z¼s§éuZïA`¢×ÞÝÖïooÿúvÔû³TÖõÌËU÷Ȇžnëñ±9ØÝc¬N1GÀÜiº¡hž~Ÿ*Àº£ž9vlÖ²–­lKXÍb¨¡IÌElü'Nc»Ý]÷ÙC‰¤¾ú====ùèû÷ïøöæ·P¼}ùP2KX8Lé4³£ázl }æ <0pwø’ÙŽ^âjú¶t6šÅwvÈaËv` 0ÕÈí±œà¡xÿ ˜ÌÒY)>»ådmA¥ƒr EK^µ[ÎÃÙe?¾|”>¸q‚L•Ó)¥@D5•óúo¬^WgïåÉO€É,½,çqΪ&k•R¹@D]ZkjÕkÏs/ð¥·D5™¥ó¨yœÀ÷!²ck‰¨ ¢AmZ“ZØíx¢VŠÌòy°—åîí 2€ð\äZ+›£Ž&λ<\­ÉRµ€ûË©~lv¶Ò>»ïÃáe“ݰÖÖT €¨@沞آÅnÇ“>0™¥'ð<` ÖBheÓLåZYÎm›‡½ i÷µî±?}j:|/8+eÓŒI´ÝB+dª¤¢ iWJ' xxòŽ;tú¨²TÅ7mRw–%‰ÿÉ?Ë(ÛE5™¥¯àyLˆ2˜ÉBëL+MT"ÎýùµÎkÉÞL.×qÜÃfœ_$Ÿ‹ß¹ÚyÔd-¶Zƒ,2e•ª©`Rž*ÕJÀ8-£EŸnKD«2+¼©å²ø(·9ÙM–é‡-àJ& «õ¾­ãÛâÇñ謟ÄwÅNWŠ-Š<ñø¼PìJ_H©Ò´œëÌ­ë4À9/nº-ÐÌþµf‰'G6ŸßN&Ü èTœ>îû¨<Ü̇±¾ZçM®¯·Dž]àd£d­85ÕÝ·Ÿ›Z©]¹©¶ÁqÔÓ+ ‘YVQíz‡îÒÚcŒó¿î¾β$éãpŽÂÕd–l ¶F·j-†²`P³½ƒ¹ ã|š¬\é°y~0ª4îßàîÐÈ•MV]Zàâëס㣣&Õ$ë®àÉõ3_ôxXÁ¦Õmµ&@<¹èì‹Æ¼.ªÙxraÒ¬k®=êxÜ#×ç.w‡˜Gòp[ê“c‰fQh’uëtå¾’Çãþ J Ô®æîÐ9ýPüÖ[¹¢éa<·JW÷S_ôS9˜wñ±¸w……å<¯NSW–XÇñ:Ž…”"ЏãPI¢62ÏYÀ9‚rO÷ÊÛo÷ÿ|¹œõPÿ1Î/æS~R^ç{5……¿‚ àTøu€Ýapuö+¨Ìû|ÉßïÊú§åí{yr²˜½.Õ‹3ì—m}àþýjlìã|ŽƒWL ˜»CгÅüU¨“›9‹œÃ·Sçk‘Ì’ôvu}ÛsÏôÛit\~üÔk±fP+õ0Û–z¤Ó|îFÓ)‹ óÁó_j|vŸ<«^FQxrZø–Ìò?>ÌŸ°ÀBo´É´NS½Ù1ÜuÅ`àHé{‚…Î+y²ˆBM³ñ…°¦ý "ÄÏÏŽ[bªIEND®B`‚smalltalk-3.2.5/doc/tutorial.texi0000644000175000017500000042533212123404352013736 00000000000000 @table @b @item What this manual presents This document provides a tutorial introduction to the Smalltalk language in general, and the @gst{} implementation in particular. It does not provide exhaustive coverage of every feature of the language and its libraries; instead, it attempts to introduce a critical mass of ideas and techniques to get the Smalltalk novice moving in the right direction. @item Who this manual is written for This manual assumes that the reader is acquainted with the basics of computer science, and has reasonable proficiency with a procedural language such as C. It also assumes that the reader is already familiar with the usual janitorial tasks associated with programming: editing, moving files, and so forth. @end table @menu * Getting started:: Starting to explore @gst{} * Some classes:: Using some of the Smalltalk classes * The hierarchy:: The Smalltalk class hierarchy * Creating classes:: Creating a new class of objects * Creating subclasses:: Adding subclasses to another class * Code blocks (I):: Control structures in Smalltalk * Code blocks (II):: Guess what? More control structures * Debugging:: Things go bad in Smalltalk too! * More subclassing:: Coexisting in the class hierarchy * Streams:: A powerful abstraction useful in scripts * Exception handling:: More sophisticated error handling * Behind the scenes:: Some nice stuff from the Smalltalk innards * And now:: Some final words * The syntax:: For the most die-hard computer scientists @end menu @node Getting started @section Getting started @menu * Starting Smalltalk:: Starting up Smalltalk * Saying hello:: Saying hello * What happened:: But how does it say hello? * Doing math:: Smalltalk too can do it! * Math in Smalltalk:: But in a peculiar way of course... @end menu @node Starting Smalltalk @subsection Starting up Smalltalk Assuming that @gst{} has been installed on your system, starting it is as simple as: @example @b{$} gst @end example the system loads in Smalltalk, and displays a startup banner like: @display GNU Smalltalk ready st> @end display You are now ready to try your hand at Smalltalk! By the way, when you're ready to quit, you exit Smalltalk by typing @kbd{control-D} on an empty line. @node Saying hello @subsection Saying hello An initial exercise is to make Smalltalk say ``hello'' to you. Type in the following line (@code{printNl} is a upper case N and a lower case L): @example 'Hello, world' printNl @end example The system then prints back 'Hello, world' to you. It prints it twice, the first time because you asked to print and the second time because the snipped evaluated to the 'Hello, world' string.@footnote{ You can also have the system print out a lot of statistics which provide information on the performance of the underlying Smalltalk engine. You can enable them by starting Smalltalk as: @example @b{$} gst -V @end example } @node What happened @subsection What actually happened The front-line Smalltalk interpreter gathers all text until a '!' character and executes it. So the actual Smalltalk code executed was: @example 'Hello, world' printNl @end example This code does two things. First, it creates an object of type @code{String} which contains the characters ``Hello, world''. Second, it sends the message named @code{printNl} to the object. When the object is done processing the message, the code is done and we get our prompt back. You'll notice that we didn't say anything about printing ing the string, even though that's in fact what happened. This was very much on purpose: the code we typed in doesn't know anything about printing strings. It knew how to get a string object, and it knew how to send a message to that object. That's the end of the story for the code we wrote. But for fun, let's take a look at what happened when the string object received the @code{printNl} message. The string object then went to a table @footnote{Which table? This is determined by the type of the object. An object has a type, known as the class to which it belongs. Each class has a table of methods. For the object we created, it is known as a member of the @code{String} class. So we go to the table associated with the String class.} which lists the messages which strings can receive, and what code to execute. It found that there is indeed an entry for @code{printNl} in that table and ran this code. This code then walked through its characters, printing each of them out to the terminal. @footnote{ Actually, the message @code{printNl} was inherited from Object. It sent a @code{print} message, also inherited by Object, which then sent @code{printOn:} to the object, specifying that it print to the @code{Transcript} object. The String class then prints its characters to the standard output.} The central point is that an object is entirely self-contained; only the object knew how to print itself out. When we want an object to print out, we ask the object itself to do the printing. @node Doing math @subsection Doing math A similar piece of code prints numbers: @example 1234 printNl @end example Notice how we used the same message, but have sent it to a new type of object---an integer (from class @code{Integer}). The way in which an integer is printed is much different from the way a string is printed on the inside, but because we are just sending a message, we do not have to be aware of this. We tell it to @code{printNl}, and it prints itself out. As a user of an object, we can thus usually send a particular message and expect basically the same kind of behavior, regardless of object's internal structure (for instance, we have seen that sending @code{printNl} to an object makes the object print itself). In later chapters we will see a wide range of types of objects. Yet all of them can be printed out the same way---with @code{printNl}. White space is ignored, except as it separates words. This example could also have looked like: @example 1234 printNl @end example However, @gst{} tries to execute each line by itself if possible. If you wanted to write the code on two lines, you might have written something like: @example (1234 printNl) @end example From now on, we'll omit @code{printNl} since @gst{} does the service of printing the answer for us. An integer can be sent a number of messages in addition to just printing itself. An important set of messages for integers are the ones which do math: @example 9 + 7 @end example Answers (correctly!) the value 16. The way that it does this, however, is a significant departure from a procedural language. @node Math in Smalltalk @subsection Math in Smalltalk In this case, what happened was that the object @code{9} (an Integer), received a @code{+} message with an argument of @code{7} (also an Integer). The @code{+} message for integers then caused Smalltalk to create a new object @code{16} and return it as the resultant object. This @code{16} object was then given the @code{printNl} message, and printed @code{16} on the terminal. Thus, math is not a special case in Smalltalk; it is done, exactly like everything else, by creating objects, and sending them messages. This may seem odd to the Smalltalk novice, but this regularity turns out to be quite a boon: once you've mastered just a few paradigms, all of the language ``falls into place''. Before you go on to the next chapter, make sure you try math involving @code{*} (multiplication), @code{-} (subtraction), and @code{/} (division) also. These examples should get you started: @example 8 * (4 / 2) 8 - (4 + 1) 5 + 4 2/3 + 7 2 + 3 * 4 2 + (3 * 4) @end example @node Some classes @section Using some of the Smalltalk classes This chapter has examples which need a place to hold the objects they create. Such place is created automatically as necessary; when you want to discard all the objects you stored, write an exclamation mark at the end of the statement. Now let's create some new objects. @menu * Arrays:: An array in Smalltalk * Sets:: A set in Smalltalk * Dictionaries:: Getting more sophisticated, eh? * Closing thoughts:: There always ought to be some closing thoughts @end menu @node Arrays @subsection An array in Smalltalk An array in Smalltalk is similar to an array in any other language, although the syntax may seem peculiar at first. To create an array with room for 20 elements, do@footnote{ @gst{} supports completion in the same way as Bash or @sc{gdb}. To enter the following line, you can for example type @samp{x := Arr@kbd{} new: 20}. This can come in handy when you have to type long names such as @code{IdentityDictionary}, which becomes @samp{Ide@kbd{}D@kbd{}}. Everything starting with a capital letter or ending with a colon can be completed.}: @example x := Array new: 20 @end example The @code{Array new: 20} creates the array; the @code{x :=} part connects the name @code{x} with the object. Until you assign something else to @code{x}, you can refer to this array by the name @code{x}. Changing elements of the array is not done using the @code{:=} operator; this operator is used only to bind names to objects. In fact, you never modify data structures; instead, you send a message to the object, and it will modify itself. For instance: @example x at: 1 @end example @noindent which prints: @example nil @end example The slots of an array are initially set to ``nothing'' (which Smalltalk calls @code{nil}). Let's set the first slot to the number 99: @example x at: 1 put: 99 @end example @noindent and now make sure the 99 is actually there: @example x at: 1 @end example @noindent which then prints out: @example 99 @end example These examples show how to manipulate an array. They also show the standard way in which messages are passed arguments ments. In most cases, if a message takes an argument, its name will end with `:'.@footnote{Alert readers will remember that the math examples of the previous chapter deviated from this.} So when we said @code{x at: 1} we were sending a message to whatever object was currently bound to @code{x} with an argument of 1. For an array, this results in the first slot of the array being returned. The second operation, @code{x at: 1 put: 99} is a message with two arguments. It tells the array to place the second argument (99) in the slot specified by the first (1). Thus, when we re-examine the first slot, it does indeed now contain 99. There is a shorthand for describing the messages you send to objects. You just run the message names together. So we would say that our array accepts both the @code{at:} and @code{at:put:} messages. There is quite a bit of sanity checking built into an array. The request @example 6 at: 1 @end example @noindent fails with an error; 6 is an integer, and can't be indexed. Further, @example x at: 21 @end example @noindent fails with an error, because the array we created only has room for 20 objects. Finally, note that the object stored in an array is just like any other object, so we can do things like: @example (x at: 1) + 1 @end example @noindent which (assuming you've been typing in the examples) will print 100. @node Sets @subsection A set in Smalltalk We're done with the array we've been using, so we'll assign something new to our @code{x} variable. Note that we don't need to do anything special about the old array: the fact that nobody is using it any more will be automatically detected, and the memory reclaimed. This is known as @i{garbage collection} and it is generally done when Smalltalk finds that it is running low on memory. So, to get our new object, simply do: @example x := Set new @end example @noindent which creates an empty set. To view its contents, do: @example x @end example The kind of object is printed out (i.e., @code{Set}), and then the members are listed within parenthesis. Since it's empty, we see: @example Set () @end example Now let's toss some stuff into it. We'll add the numbers 5 and 7, plus the string 'foo'. This is also the first example where we're using more than one statement, and thus a good place to present the statement separator---the @code{.} period: @example x add: 5. x add: 7. x add: 'foo' @end example Like Pascal, and unlike C, statements are separated rather than terminated. Thus you need only use a @code{.} when you have finished one statement and are starting another. This is why our last statement, @code{^r}, does not have a @code{.} following. Once again like Pascal, however, Smalltalk won't complain if your enter a spurious statement separator after @i{the last} statement. However, we can save a little typing by using a Smalltalk shorthand: @example x add: 5; add: 7; add: 'foo' @end example This line does exactly what the previous one did. The trick is that the semicolon operator causes the message to be sent to the same object as the last message sent. So saying @code{; add: 7} is the same as saying @code{x add: 7}, because @code{x} was the last thing a message was sent to. This may not seem like such a big savings, but compare the ease when your variable is named @code{aVeryLongVariableName} instead of just @code{x}! We'll revisit some other occasions where @code{;} saves you trouble, but for now let's continue with our set. Type either version of the example, and make sure that we've added 5, 7, and ``foo'': @example x @end example @noindent we'll see that it now contains our data: @example Set ('foo' 5 7) @end example What if we add something twice? No problem---it just stays in the set. So a set is like a big checklist---either it's in there, or it isn't. To wit: @example x add:5; add: 5; add: 5; add: 5; yourself @end example We've added @i{5} several times, but when we printed our set back out, we just see: @example Set ('foo' 5 7) @end example @code{yourself} is commonly sent at the end of the cascade, if what you are interested in is the object itself---in this case, we were not interested in the return value of @code{add: 5}, which happens to be @code{5} simply. There's nothing magic in @code{yourself}; it is a unary message like @code{printNl}, which does nothing but returning the object itself. So you can do this too: @example x yourself @end example What you put into a set with @code{add:}, you can take out with @code{remove:}. Try: @example x remove: 5 x printNl @end example The set now prints as: @example Set ('foo' 7) @end example The ``5'' is indeed gone from the set. We'll finish up with one more of the many things you can do with a set---checking for membership. Try: @example x includes: 7 x includes: 5 @end example From which we see that x does indeed contain 7, but not 5. Notice that the answer is printed as @code{true} or @code{false}. Once again, the thing returned is an object---in this case, an object known as a boolean. We'll look at the use of booleans later, but for now we'll just say that booleans are nothing more than objects which can only either be true or false---nothing else. So they're very useful for answers to yes or no questions, like the ones we just posed. Let's take a look at just one more kind of data structure: @node Dictionaries @subsection Dictionaries A dictionary is a special kind of collection. With a regular array, you must index it with integers. With dictionaries, you can index it with any object at all. Dictionaries thus provide a very powerful way of correlating one piece of information to another. Their only downside is that they are somewhat less efficient than simple arrays. Try the following: @example y := Dictionary new y at: 'One' put: 1 y at: 'Two' put: 2 y at: 1 put: 'One' y at: 2 put: 'Two' @end example This fills our dictionary in with some data. The data is actually stored in pairs of key and value (the key is what you give to @code{at:}---it specifies a slot; the value is what is actually stored at that slot). Notice how we were able to specify not only integers but also strings as both the key and the value. In fact, we can use any kind of object we want as either---the dictionary doesn't care. Now we can map each key to a value: @example y at: 1 y at: 'Two' @end example which prints respectively: @example 'One' 2 @end example We can also ask a dictionary to print itself: @example y @end example @noindent which prints: @example Dictionary (1->'One' 2->'Two' 'One'->1 'Two'->2 ) @end example @noindent where the first member of each pair is the key, and the second the value. It is now time to take a final look at the objects we have created, and send them to oblivion: @example y x! @end example The exclamation mark deleted @gst{}'s knowledge of both variables. Asking for them again will return just @code{nil}. @node Closing thoughts @subsection Closing thoughts You've seen how Smalltalk provides you with some very powerful data structures. You've also seen how Smalltalk itself uses these same facilities to implement the language. But this is only the tip of the iceberg---Smalltalk is much more than a collection of ``neat'' facilities to use. The objects and methods which are automatically available are only the beginning of the foundation on which you build your programs---Smalltalk allows you to add your own objects and methods into the system, and then use them along with everything else. The art of programming in Smalltalk is the art of looking at your problems in terms of objects, using the existing object types to good effect, and enhancing Smalltalk with new types of objects. Now that you've been exposed to the basics of Smalltalk manipulation, we can begin to look at this object-oriented technique of programming. @node The hierarchy @section The Smalltalk class hierarchy When programming in Smalltalk, you sometimes need to create new kinds of objects, and define what various messages will do to these objects. In the next chapter we will create some new classes, but first we need to understand how Smalltalk organizes the types and objects it contains. Because this is a pure ``concept'' chapter, without any actual Smalltalk code to run, we will keep it short and to the point. @menu * Class Object:: The grandfather of every class * Animals:: A classic in learning OOP! * But why:: The bottom line of the class hierarchy @end menu @node Class Object @subsection Class @code{Object} Smalltalk organizes all of its classes as a tree hierarchy. At the very top of this hierarchy is class @i{Object}. Following somewhere below it are more specific classes, such as the ones we've worked with---strings, integers, arrays, and so forth. They are grouped together based on their similarities; for instance, types of objects which may be compared as greater or less than each other fall under a class known as @i{Magnitude}. One of the first tasks when creating a new object is to figure out where within this hierarchy your object falls. Coming up with an answer to this problem is at least as much art as science, and there are no hard-and-fast rules to nail it down. We'll take a look at three kinds of objects to give you a feel for how this organization matters. @node Animals @subsection Animals Imagine that we have three kinds of objects, representing @i{Animals}, @i{Parrots}, and @i{Pigs}. Our messages will be @i{eat}, @i{sing}, and @i{snort}. Our first pass at inserting these objects into the Smalltalk hierarchy would organize them like: @example @r{Object} @r{Animals} @r{Parrots} @r{Pigs} @end example This means that Animals, Parrots, and Pigs are all direct descendants of @i{Object}, and are not descendants of each other. Now we must define how each animal responds to each kind of message. @example @r{Animals} @r{eat --> Say ``I have now eaten''} @r{sing --> Error} @r{snort --> Error} @r{Parrots} @r{eat --> Say ``I have now eaten''} @r{sing --> Say ``Tweet''} @r{snort --> Error} @r{Pigs} @r{eat --> Say ``I have now eaten"''} @r{sing --> Error} @r{snort --> Say ``Oink''} @end example Notice how we kept having to indicate an action for @i{eat}. An experienced object designer would immediately recognize this as a clue that we haven't set up our hierarchy correctly. Let's try a different organization: @example @r{Object} @r{Animals} @r{Parrots} @r{Pigs} @end example That is, Parrots inherit from Animals, and Pigs from Parrots. Now Parrots inherit all of the actions from Animals, and Pigs from both Parrots and Animals. Because of this inheritance, we may now define a new set of actions which spares us the redundancy of the previous set: @example @r{Animals} @r{eat --> Say ``I have now eaten''} @r{sing --> Error} @r{snort --> Error} @r{Parrots} @r{sing --> Say ``Tweet''} @r{Pigs} @r{snort --> Say ``Oink''} @end example Because Parrots and Pigs both inherit from Animals, we have only had to define the @i{eat} action once. However, we have made one mistake in our class setup---what happens when we tell a Pig to @i{sing}? It says ``Tweet'', because we have put Pigs as an inheritor of Parrots. Let's try one final organization: @example @r{Object} @r{Animals} @r{Parrots} @r{Pigs} @end example Now Parrots and Pigs inherit from Animals, but not from each other. Let's also define one final pithy set of actions: @example @r{Animals} @r{eat --> Say ``I have eaten''} @r{Parrots} @r{sing --> Say ``Tweet''} @r{Pigs} @r{snort --> Say ``Oink''} @end example The change is just to leave out messages which are inappropriate. If Smalltalk detects that a message is not known by an object or any of its ancestors, it will automatically give an error---so you don't have to do this sort of thing yourself. Notice that now sending @i{sing} to a Pig does indeed not say ``Tweet''---it will cause a Smalltalk error instead. @node But why @subsection The bottom line of the class hierarchy The goal of the class hierarchy is to allow you to organize objects into a relationship which allows a particular object to inherit the code of its ancestors. Once you have identified an effective organization of types, you should find that a particular technique need only be implemented once, then inherited by the children below. This keeps your code smaller, and allows you to fix a bug in a particular algorithm in only once place---then have all users of it just inherit the fix. You will find your decisions for adding objects change as you gain experience. As you become more familiar with the existing set of objects and messages, your selections will increasingly ``fit in'' with the existing ones. But even a Smalltalk @i{pro} stops and thinks carefully at this stage, so don't be daunted if your first choices seem difficult and error-prone. @node Creating classes @section Creating a new class of objects With the basic techniques presented in the preceding chapters, we're ready do our first real Smalltalk program. In this chapter we will construct three new types of objects (known as @i{classes}), using the Smalltalk technique of inheritance to tie the classes together, create new objects belonging to these classes (known as creating instances of the class), and send messages to these objects. We'll exercise all this by implementing a toy home-finance accounting system. We will keep track of our overall cash, and will have special handling for our checking and savings accounts. From this point on, we will be defining classes which will be used in future chapters. Since you will probably not be running this whole tutorial in one Smalltalk session, it would be nice to save off the state of Smalltalk and resume it without having to retype all the previous examples. To save the current state of @gst{}, type: @example ObjectMemory snapshot: 'myimage.im' @end example @noindent and from your shell, to later restart Smalltalk from this ``snapshot'': @example @b{$} gst -I myimage.im @end example Such a snapshot currently takes a little more than a megabyte, and contains all variables, classes, and definitions you have added. @menu * A new class:: Creating a new class * Documenting the class:: So anybody will know what it's about * Defining methods:: So it will be useful * Instance methods:: One of two kind of methods (the others, class methods, are above) * A look at our object:: which will sorely show that something is still missing. * Moving money around:: Let's make it more fun! * Next coming:: Yeah, what's next?!? @end menu @node A new class @subsection Creating a new class Guess how you create a new class? This should be getting monotonous by now---by sending a message to an object. The way we create our first ``custom'' class is by sending the following message: @example Object subclass: #Account. Account instanceVariableNames: 'balance'. @end example Quite a mouthful, isn't it? @gst{} provides a simpler way to write this, but for now let's stick with this. Conceptually, it isn't really that bad. The Smalltalk variable @i{Object} is bound to the grand-daddy of all classes on the system. What we're doing here is telling the @i{Object} class that we want to add to it a subclass known as @i{Account}. Then, @code{instanceVariableNames: 'balance'} tells the new class that each of its objects (@dfn{instances}) will have a hidden variable named @code{balance}. @node Documenting the class @subsection Documenting the class The next step is to associate a description with the class. You do this by sending a message to the new class: @example Account comment: 'I represent a place to deposit and withdraw money' @end example A description is associated with every Smalltalk class, and it's considered good form to add a description to each new class you define. To get the description for a given class: @example Account comment @end example And your string is printed back to you. Try this with class Integer, too: @example Integer comment @end example However, there is another way to define classes. This still translates to sending objects, but looks more like a traditional programming language or scripting language: @example Object subclass: Account [ | balance | ] @end example This has created a class. If we want to access it again, for example to modify the comment, we can do so like this: @example Account extend [ ] @end example This instructs Smalltalk to pick an existing class, rather than trying to create a subclass. @node Defining methods @subsection Defining a method for the class We have created a class, but it isn't ready to do any work for us---we have to define some messages which the class can process first. We'll start at the beginning by defining methods for instance creation: @example Account class extend [ new [ | r | r := super new. r init. ^r ] ] @end example The important points about this are: @itemize @bullet @item @code{Account class} means that we are defining messages which are to be sent to the Account class itself. @item @code{} is more documentation support; it says that the methods we are defining supports creating objects of type Account. @item The text starting with @code{new [} and ending with @code{]} defined what action to take for the message @code{new}. When you enter this definition, @gst{} will simply give you another prompt, but your method has been compiled in and is ready for use. @gst{} is pretty quiet on successful method definitions---but you'll get plenty of error messages if there's a problem! If you're familiar with other Smalltalks, note that the body of the method is always in brackets. @end itemize The best way to describe how this method works is to step through it. Imagine we sent a message to the new class Account with the command line: @example Account new @end example @code{Account} receives the message @code{new} and looks up how to process this message. It finds our new definition, and starts running it. The first line, @code{| r |}, creates a local variable named @code{r} which can be used as a placeholder for the objects we create. @code{r} will go away as soon as the message is done being processed; note the parallel with @code{balance}, which goes away as soon as the object is not used anymore. And note that here you have to declare local variables explicitly, unlike what you did in previous examples. The first real step is to actually create the object. The line @code{r := super new} does this using a fancy trick. The word @code{super} stands for the same object that the message @code{new} was originally sent to (remember? it's @code{Account}), except that when Smalltalk goes to search for the methods, it starts one level higher up in the hierarchy than the current level. So for a method in the Account class, this is the Object class (because the class Account inherits from is Object---go back and look at how we created the Account class), and the Object class' methods then execute some code in response to the @code{#new} message. As it turns out, Object will do the actual creation of the object when sent a @code{#new} message. One more time in slow motion: the Account method @code{#new} wants to do some fiddling about when new objects are created, but he also wants to let his parent do some work with a method of the same name. By saying @code{r := super new} he is letting his parent create the object, and then he is attaching it to the variable @code{r}. So after this line of code executes, we have a brand new object of type Account, and @code{r} is bound to it. You will understand this better as time goes on, but for now scratch your head once, accept it as a recipe, and keep going. We have the new object, but we haven't set it up correctly. Remember the hidden variable @code{balance} which we saw in the beginning of this chapter? @code{super new} gives us the object with the @code{balance} field containing nothing, but we want our balance field to start at 0. @footnote{And unlike C, Smalltalk draws a distinction between @code{0} and @code{nil}. @code{nil} is the @i{nothing} object, and you will receive an error if you try to do, say, math on it. It really does matter that we initialize our instance variable to the number 0 if we wish to do math on it in the future.} So what we need to do is ask the object to set itself up. By saying @code{r init}, we are sending the @code{init} message to our new Account. We'll define this method in the next section---for now just assume that sending the @code{init} message will get our Account set up. Finally, we say @code{^r}. In English, this is @i{return what r is attached to}. This means that whoever sent to Account the @code{new} message will get back this brand new account. At the same time, our temporary variable @code{r} ceases to exist. @node Instance methods @subsection Defining an instance method We need to define the @code{init} method for our Account objects, so that our @code{new} method defined above will work. Here's the Smalltalk code: @example Account extend [ init [ balance := 0 ] ] @end example It looks quite a bit like the previous method definition, except that the first one said @code{Account class extend}, and ours says @code{Account extend}. The difference is that the first one defined a method for messages sent directly to @code{Account}, but the second one is for messages which are sent to Account objects once they are created. The method named @code{init} has only one line, @code{balance := 0}. This initializes the hidden variable @code{balance} (actually called an instance variable) to zero, which makes sense for an account balance. Notice that the method doesn't end with @code{^r} or anything like it: this method doesn't return a value to the message sender. When you do not specify a return value, Smalltalk defaults the return value to the object currently executing. For clarity of programming, you might consider explicitly returning @code{self} in cases where you intend the return value to be used.@footnote{ And why didn't the designers default the return value to nil? Perhaps they didn't appreciate the value of void functions. After all, at the time Smalltalk was being designed, C didn't even have a void data type.} Before going on, ere is how you could have written this code in a single declaration (i.e.@: without using @code{extend}): @example Object subclass: Account [ | balance | Account class >> new [ | r | r := super new. r init. ^r ] init [ balance := 0 ] ] @end example @node A look at our object @subsection Looking at our Account Let's create an instance of class Account: @example a := Account new @end example Can you guess what this does? The @code{Smalltalk at: #a put: } creates a Smalltalk variable. And the @code{Account new} creates a new Account, and returns it. So this line creates a Smalltalk variable named @code{a}, and attaches it to a new Account---all in one line. It also prints the Account object we just created: @example an Account @end example Hmmm... not very informative. The problem is that we didn't tell our Account how to print itself, so we're just getting the default system @code{printNl} method---which tells what the object is, but not what it contains. So clearly we must add such a method: @example Account extend [ printOn: stream [ super printOn: stream. stream nextPutAll: ' with balance: '. balance printOn: stream ] ] @end example Now give it a try again: @example a @end example @noindent which prints: @example an Account with balance: 0 @end example This may seem a little strange. We added a new method, printOn:, and our printNl message starts behaving differently. It turns out that the printOn: message is the central printing function---once you've defined it, all of the other printing methods end up calling it. Its argument is a place to print to---quite often it is the variable @code{Transcript}. This variable is usually hooked to your terminal, and thus you get the printout to your screen. The @code{super printOn: stream} lets our parent do what it did before---print out what our type is. The @code{an Account} part of the printout came from this. @code{stream nextPutAll: ' with balance: '} creates the string @code{ with balance: }, and prints it out to the stream, too; note that we don't use @code{printOn:} here because that would enclose our string within quotes. Finally, @code{balance printOn: stream} asks whatever object is hooked to the @code{balance} variable to print itself to the stream. We set @code{balance} to 0, so the 0 gets printed out. @node Moving money around @subsection Moving money around We can now create accounts, and look at them. As it stands, though, our balance will always be 0---what a tragedy! Our final methods will let us deposit and spend money. They're very simple: @example Account extend [ spend: amount [ balance := balance - amount ] deposit: amount [ balance := balance + amount ] ] @end example With these methods you can now deposit and spend amounts of money. Try these operations: @example a deposit: 125 a deposit: 20 a spend: 10 @end example @node Next coming @subsection What's next? We now have a generic concept, an ``Account''. We can create them, check their balance, and move money in and out of them. They provide a good foundation, but leave out important information that particular types of accounts might want. In the next chapter, we'll take a look at fixing this problem using subclasses. @node Creating subclasses @section Two Subclasses for the Account Class This chapter continues from the previous chapter in demonstrating how one creates classes and subclasses in Smalltalk. In this chapter we will create two special subclasses of Account, known as Checking and Savings. We will continue to inherit the capabilities of Account, but will tailor the two kinds of objects to better manage particular kinds of accounts. @menu * The Savings class:: One of the two subclasses we'll put together * The Checking class:: And here is the other * Writing checks:: Only in Smalltalk, of course @end menu @node The Savings class @subsection The Savings class We create the Savings class as a subclass of Account. It holds money, just like an Account, but has an additional property that we will model: it is paid interest based on its balance. We create the class Savings as a subclass of Account. @example Account subclass: Savings [ | interest | @end example This is already telling something: the instance variable @code{interest} will accumulate interest paid. Thus, in addition to the @code{spend:} and @code{deposit:} messages which we inherit from our parent, Account, we will need to define a method to add in interest deposits, and a way to clear the interest variable (which we would do yearly, after we have paid taxes). We first define a method for allocating a new account---we need to make sure that the interest field starts at 0. We can do so within the @code{Account subclass: Savings} scope, which we have not closed above. @example init [ interest := 0. ^super init ] @end example Recall that the parent took care of the @code{new} message, and created a new object of the appropriate size. After creation, the parent also sent an @code{init} message to the new object. As a subclass of Account, the new object will receive the @code{init} message first; it sets up its own instance variable, and then passes the @code{init} message up the chain to let its parent take care of its part of the initialization. With our new @code{Savings} account created, we can define two methods for dealing specially with such an account: @example interest: amount [ interest := interest + amount. self deposit: amount ] clearInterest [ | oldinterest | oldinterest := interest. interest := 0. ^oldinterest ] @end example We are now finished, and close the class scope: @example ] @end example The first method says that we add the @code{amount} to our running total of interest. The line @code{self deposit: amount} tells Smalltalk to send ourselves a message, in this case @code{deposit: amount}. This then causes Smalltalk to look up the method for @code{deposit:}, which it finds in our parent, Account. Executing this method then updates our overall balance.@footnote{@code{self} is much like @code{super}, except that @code{self} will start looking for a method at the bottom of the type hierarchy for the object, while @code{super} starts looking one level up from the current level. Thus, using @code{super} forces inheritance, but @code{self} will find the first definition of the message which it can.} One may wonder why we don't just replace this with the simpler @code{balance := balance + amount}. The answer lies in one of the philosophies of object-oriented languages in general, and Smalltalk in particular. Our goal is to encode a technique for doing something once only, and then re-using that technique when needed. If we had directly encoded @code{balance := balance + amount} here, there would have been two places that knew how to update the balance from a deposit. This may seem like a useless difference. But consider if later we decided to start counting the number of deposits made. If we had encoded @code{balance := balance + amount} in each place that needed to update the balance, we would have to hunt each of them down in order to update the count of deposits. By sending @code{self} the message @code{deposit:}, we need only update this method once; each sender of this message would then automatically get the correct up-to-date technique for updating the balance. The second method, @code{clearInterest}, is simpler. We create a temporary variable @code{oldinterest} to hold the current amount of interest. We then zero out our interest to start the year afresh. Finally, we return the old interest as our result, so that our year-end accountant can see how much we made.@footnote{Of course, in a real accounting system we would never discard such information---we'd probably throw it into a Dictionary object, indexed by the year that we're finishing. The ambitious might want to try their hand at implementing such an enhancement.} @node The Checking class @subsection The Checking class Our second subclass of Account represents a checking account. We will keep track of two facets: @itemize @bullet @item What check number we are on @item How many checks we have left in our checkbook @end itemize We will define this as another subclass of Account: @example Account subclass: Checking [ | checknum checksleft | @end example We have two instance variables, but we really only need to initialize one of them---if there are no checks left, the current check number can't matter. Remember, our parent class Account will send us the @code{init} message. We don't need our own class-specific @code{new} function, since our parent's will provide everything we need. @example init [ checksleft := 0. ^super init ] @end example As in Savings, we inherit most of abilities from our superclass, Account. For initialization, we leave @code{checknum} alone, but set the number of checks in our checkbook to zero. We finish by letting our parent class do its own initialization. @node Writing checks @subsection Writing checks We will finish this chapter by adding a method for spending money through our checkbook. The mechanics of taking a message and updating variables should be familiar: @example newChecks: number count: checkcount [ checknum := number. checksleft := checkcount ] writeCheck: amount [ | num | num := checknum. checknum := checknum + 1. checksleft := checksleft - 1. self spend: amount. ^ num ] ] @end example @code{newChecks:} fills our checkbook with checks. We record what check number we're starting with, and update the count of the number of checks in the checkbook. @code{writeCheck:} merely notes the next check number, then bumps up the check number, and down the check count. The message @code{self spend: amount} resends the message @code{spend:} to our own object. This causes its method to be looked up by Smalltalk. The method is then found in our parent class, Account, and our balance is then updated to reflect our spending. You can try the following examples: @example c := Checking new c deposit: 250 c newChecks: 100 count: 50 c writeCheck: 32 c @end example For amusement, you might want to add a printOn: message to the checking class so you can see the checking-specific information. In this chapter, you have seen how to create subclasses of your own classes. You have added new methods, and inherited methods from the parent classes. These techniques provide the majority of the structure for building solutions to problems. In the following chapters we will be filling in details on further language mechanisms and types, and providing details on how to debug software written in Smalltalk. @node Code blocks (I) @section Code blocks The Account/Saving/Checking example from the last chapter has several deficiencies. It has no record of the checks and their values. Worse, it allows you to write a check when there are no more checks---the Integer value for the number of checks will just calmly go negative! To fix these problems we will need to introduce more sophisticated control structures. @menu * Conditions:: Making some decisions * Iteration:: Making some loops @end menu @node Conditions @subsection Conditions and decision making Let's first add some code to keep you from writing too many checks. We will simply update our current method for the Checking class; if you have entered the methods from the previous chapters, the old definition will be overridden by this new one. @example Checking extend [ writeCheck: amount [ | num | (checksleft < 1) ifTrue: [ ^self error: 'Out of checks' ]. num := checknum. checknum := checknum + 1. checksleft := checksleft - 1. self spend: amount ^ num ] ] @end example The two new lines are: @example (checksleft < 1) ifTrue: [ ^self error: 'Out of checks' ]. @end example At first glance, this appears to be a completely new structure. But, look again! The only new construct is the square brackets, which appear within a method and not only surround it. The first line is a simple boolean expression. @code{checksleft} is our integer, as initialized by our Checking class. It is sent the message @code{<}, and the argument 1. The current number bound to @code{checksleft} compares itself against 1, and returns a boolean object telling whether it is less than 1. Now this boolean, which is either true or false, is sent the message @code{ifTrue:}, with an argument which is called a code block. A code block is an object, just like any other. But instead of holding a number, or a Set, it holds executable statements. So what does a boolean do with a code block which is an argument to a @code{ifTrue:} message? It depends on which boolean! If the object is the @code{true} object, it executes the code block it has been handed. If it is the @code{false} object, it returns without executing the code block. So the traditional @i{conditional construct} has been replaced in Smalltalk with boolean objects which execute the indicated code block or not, depending on their truth-value. @footnote{It is interesting to note that because of the way conditionals are done, conditional constructs are not part of the Smalltalk language, instead they are merely a defined behavior for the Boolean class of objects.} In the case of our example, the actual code within the block sends an error message to the current object. @code{error:} is handled by the parent class Object, and will pop up an appropriate complaint when the user tries to write too many checks. In general, the way you handle a fatal error in Smalltalk is to send an error message to yourself (through the @code{self} pseudo-variable), and let the error handling mechanisms inherited from the Object class take over. As you might guess, there is also an @code{ifFalse:} message which booleans accept. It works exactly like @code{ifTrue:}, except that the logic has been reversed; a boolean @code{false} will execute the code block, and a boolean @code{true} will not. You should take a little time to play with this method of representing conditionals. You can run your checkbook, but can also invoke the conditional functions directly: @example true ifTrue: [ 'Hello, world!' printNl ] false ifTrue: [ 'Hello, world!' printNl ] true ifFalse: [ 'Hello, world!' printNl ] false ifFalse: [ 'Hello, world!' printNl ] @end example @node Iteration @subsection Iteration and collections Now that we have some sanity checking in place, it remains for us to keep a log of the checks we write. We will do so by adding a Dictionary object to our Checking class, logging checks into it, and providing some messages for querying our check-writing history. But this enhancement brings up a very interesting question---when we change the ``shape'' of an object (in this case, by adding our dictionary as a new instance variable to the Checking class), what happens to the existing class, and its objects? The answer is that the old objects are mutated to keep their new shape, and all methods are recompiled so that they work with the new shape. New objects will have exactly the same shape as old ones, but old objects might happen to be initialized incorrectly (since the newly added variables will be simply put to nil). As this can lead to very puzzling behavior, it is usually best to eradicate all of the old objects, and then implement your changes. If this were more than a toy object accounting system, this would probably entail saving the objects off, converting to the new class, and reading the objects back into the new format. For now, we'll just ignore what's currently there, and define our latest Checking class. @example Checking extend [ | history | @end example This is the same syntax as the last time we defined a checking account, except that we start with @code{extend} (since the class is already there). Then, the two instance variables we had defined remain, and we add a new @code{history} variable; the old methods will be recompiled without errors. We must now feed in our definitions for each of the messages our object can handle, since we are basically defining a new class under an old name. With our new Checking instance variable, we are all set to start recording our checking history. Our first change will be in the handling of the @code{init} message: @example init [ checksleft := 0. history := Dictionary new. ^ super init ] @end example This provides us with a Dictionary, and hooks it to our new @code{history} variable. Our next method records each check as it's written. The method is a little more involved, as we've added some more sanity checks to the writing of checks. @example writeCheck: amount [ | num | "Sanity check that we have checks left in our checkbook" (checksleft < 1) ifTrue: [ ^self error: 'Out of checks' ]. "Make sure we've never used this check number before" num := checknum. (history includesKey: num) ifTrue: [ ^self error: 'Duplicate check number' ]. "Record the check number and amount" history at: num put: amount. "Update our next checknumber, checks left, and balance" checknum := checknum + 1. checksleft := checksleft - 1. self spend: amount. ^ num ] @end example We have added three things to our latest version of @code{writeCheck:}. First, since our routine has become somewhat involved, we have added comments. In Smalltalk, single quotes are used for strings; double quotes enclose comments. We have added comments before each section of code. Second, we have added a sanity check on the check number we propose to use. Dictionary objects respond to the @code{includesKey:} message with a boolean, depending on whether something is currently stored under the given key in the dictionary. If the check number is already used, the @code{error:} message is sent to our object, aborting the operation. Finally, we add a new entry to the dictionary. We have already seen the @code{at:put:} message (often found written as @code{#at:put:}, with a sharp in front of it) at the start of this tutorial. Our use here simply associates a check number with an amount of money spent.@footnote{You might start to wonder what one would do if you wished to associate two pieces of information under one key. Say, the value and who the check was written to. There are several ways; the best would probably be to create a new, custom object which contained this information, and then store this object under the check number key in the dictionary. It would also be valid (though probably overkill) to store a dictionary as the value---and then store as many pieces of information as you'd like under each slot!} With this, we now have a working Checking class, with reasonable sanity checks and per-check information. Let us finish the chapter by enhancing our ability to get access to all this information. We will start with some simple print-out functions. @example printOn: stream [ super printOn: stream. ', checks left: ' printOn: stream. checksleft printOn: stream. ', checks written: ' printOn: stream. (history size) printOn: stream. ] check: num [ | c | c := history at: num ifAbsent: [ ^self error: 'No such check #' ]. ^c ] @end example There should be very few surprises here. We format and print our information, while letting our parent classes handle their own share of the work. When looking up a check number, we once again take advantage of the fact that blocks of executable statements are an object; in this case, we are using the @code{at:ifAbsent:} message supported by the Dictionary class. As you can probably anticipate, if the requested key value is not found in the dictionary, the code block is executed. This allows us to customize our error handling, as the generic error would only tell the user ``key not found''. While we can look up a check if we know its number, we have not yet written a way to ``riffle through'' our collection of checks. The following function loops over the checks, printing them out one per line. Because there is currently only a single numeric value under each key, this might seem wasteful. But we have already considered storing multiple values under each check number, so it is best to leave some room for each item. And, of course, because we are simply sending a printing message to an object, we will not have to come back and re-write this code so long as the object in the dictionary honors our @code{printNl}/@code{printOn:} messages sages. @example printChecks [ history keysAndValuesDo: [ :key :value | key print. ' - ' print. value printNl. ] ] ] @end example We still see a code block object being passed to the dictionary, but @code{:key :value |} is something new. A code block can optionally receive arguments. In this case, the two arguments represent a key/value pair. If you only wanted the value portion, you could call history with a @code{do:} message instead; if you only wanted the key portion, you could call history with a @code{keysDo:} message instead. We then invoke our printing interface upon them. We don't want a newline until the end, so the @code{print} message is used instead. It is pretty much the same as @code{printNl}, since both implicitly use @code{Transcript}, except it doesn't add a newline. It is important that you be clear that in principle there is no relationship between the code block and the dictionary you passed it to. The dictionary just invokes the passed code block with a key/value pair when processing a keysAndValuesDo: message. But the same two-parameter code block can be passed to any message that wishes to evaluate it (and passes the exact number of parameters to it). In the next chapter we'll see more on how code blocks are used; we'll also look at how you can invoke code blocks in your own code. @node Code blocks (II) @section Code blocks, part two In the last chapter, we looked at how code blocks could be used to build conditional expressions, and how you could iterate across all entries in a collection.@footnote{The @code{do:} message is understood by most types of Smalltalk collections. It works for the Dictionary class, as well as sets, arrays, strings, intervals, linked lists, bags, and streams. The @code{keysDo:} message, for example, works only with dictionaries.} We built our own code blocks, and handed them off for use by system objects. But there is nothing magic about invoking code blocks; your own code will often need to do so. This chapter will shows some examples of loop construction in Smalltalk, and then demonstrate how you invoke code blocks for yourself. @menu * Integer loops:: Well, Smalltalk too has them * Intervals:: And of course here's a peculiar way to use them * Invoking code blocks:: You can do it, too @end menu @node Integer loops @subsection Integer loops Integer loops are constructed by telling a number to drive the loop. Try this example to count from 1 to 20: @example 1 to: 20 do: [:x | x printNl ] @end example There's also a way to count up by more than one: @example 1 to: 20 by: 2 do: [:x | x printNl ] @end example Finally, counting down is done with a negative step: @example 20 to: 1 by: -1 do: [:x | x printNl ] @end example Note that the @code{x} variable is local to the block. @example x @end example @noindent just prints @code{nil}. @node Intervals @subsection Intervals It is also possible to represent a range of numbers as a standalone object. This allows you to represent a range of numbers as a single object, which can be passed around the system. @example i := Interval from: 5 to: 10 i do: [:x | x printNl] @end example As with the integer loops, the Interval class can also represent steps greater than 1. It is done much like it was for our numeric loop above: @example i := (Interval from: 5 to: 10 by: 2) i do: [:x| x printNl] @end example @node Invoking code blocks @subsection Invoking code blocks Let us revisit the checking example and add a method for scanning only checks over a certain amount. This would allow our user to find ``big'' checks, by passing in a value below which we will not invoke their function. We will invoke their code block with the check number as an argument ment; they can use our existing check: message to get the amount. @example Checking extend [ checksOver: amount do: aBlock history keysAndValuesDo: [:key :value | (value > amount) ifTrue: [aBlock value: key] ] ] @end example The structure of this loop is much like our printChecks message sage from chapter 6. However, in this case we consider each entry, and only invoke the supplied block if the check's value is greater than the specified amount. The line: @example ifTrue: [aBlock value: key] @end example @noindent invokes the user-supplied block, passing as an argument the key, which is the check number. The @code{value:} message, when received by a code block, causes the code block to execute. Code blocks take @code{value}, @code{value:}, @code{value:value:}, and @code{value:value:value:} messages, so you can pass from 0 to 3 arguments to a code block.@footnote{ There is also a @code{valueWithArguments:} message which accepts an array holding as many arguments as you would like.} You might find it puzzling that an association takes a @code{value} message, and so does a code block. Remember, each object can do its own thing with a message. A code block gets run when it receives a @code{value} message. An association merely returns the value part of its key/value pair. The fact that both take the same message is, in this case, coincidence. Let's quickly set up a new checking account with $250 (wouldn't this be nice in real life?) and write a couple checks. Then we'll see if our new method does the job correctly: @example mycheck := Checking new. mycheck deposit: 250 mycheck newChecks: 100 count: 40 mycheck writeCheck: 10 mycheck writeCheck: 52 mycheck writeCheck: 15 mycheck checksOver: 1 do: [:x | x printNl] mycheck checksOver: 17 do: [:x | x printNl] mycheck checksOver: 200 do: [:x | x printNl] @end example We will finish this chapter with an alternative way of writing our @code{checksOver:} code. In this example, we will use the message @code{select:} to pick the checks which exceed our value, instead of doing the comparison ourselves. We can then invoke the new resulting collection against the user's code block. @example Checking extend [ checksOver: amount do: aBlock [ | chosen | chosen := history select: [:amt| amt > amount]. chosen keysDo: aBlock ] ] @end example Note that @code{extend} will also overwrite methods. Try the same tests as above, they should yield the same result! @node Debugging @section When Things Go Bad So far we've been working with examples which work the first time. If you didn't type them in correctly, you probably received a flood of unintelligible complaints. You probably ignored the complaints, and typed the example again. When developing your own Smalltalk code, however, these messages are the way you find out what went wrong. Because your objects, their methods, the error printout, and your interactive environment are all contained within the same Smalltalk session, you can use these error messages to debug your code using very powerful techniques. @menu * Simple errors:: Those that only happen in examples * Nested calls:: Those that actually happen in real life * Looking at objects:: Trying to figure it out @end menu @node Simple errors @subsection A Simple Error First, let's take a look at a typical error. Type: @example 7 plus: 1 @end example This will print out: @example 7 did not understand selector 'plus:' UndefinedObject>>#executeStatements @end example The first line is pretty simple; we sent a message to the @code{7} object which was not understood; not surprising since the @code{plus:} operation should have been @code{+}. Then there are a few lines of gobbledegook: just ignore them, they reflect the fact that the error passed throgh @gst{}'s exception handling system. The remaining line reflect the way the @gst{} invokes code which we type to our command prompt; it generates a block of code which is invoked via an internal method @code{executeStatements} defined in class Object and evaluated like @code{nil executeStatements} (nil is an instance of @i{UndefinedObject}). Thus, this output tells you that you directly typed a line which sent an invalid message to the @code{7} object. All the error output but the first line is actually a stack backtrace. The most recent call is the one nearer the top of the screen. In the next example, we will cause an error which happens deeper within an object. @node Nested calls @subsection Nested Calls Type the following lines: @example x := Dictionary new x at: 1 @end example The error you receive will look like: @example Dictionary new: 31 "<0x33788>" error: key not found @i{@r{@dots{}blah blah@dots{}}} Dictionary>>#error: [] in Dictionary>>#at: [] in Dictionary>>#at:ifAbsent: Dictionary(HashedCollection)>>#findIndex:ifAbsent: Dictionary>>#at:ifAbsent: Dictionary>>#at: UndefinedObject(Object)>>#executeStatements @end example The error itself is pretty clear; we asked for something within the Dictionary which wasn't there. The object which had the error is identified as @code{Dictionary new: 31}. A Dictionary's default size is 31; thus, this is the object we created with @code{Dictionary new}. The stack backtrace shows us the inner structure of how a Dictionary responds to the @code{#at:} message. Our hand-entered command causes the usual entry for @code{UndefinedObject(Object)}. Then we see a Dictionary object responding to an @code{#at:} message (the ``Dictionary>>#at:'' line). This code called the object with an @code{#at:ifAbsent:} message. All of a sudden, Dictionary calls that strange method @code{#findIndex:ifAbsent:}, which evaluates two blocks, and then the error happens. To understand this better, it is necessary to know that a very common way to handle errors in Smalltalk is to hand down a block of code which will be called when an error occurs. For the Dictionary code, the @code{at:} message passes in a block of code to the at:ifAbsent: code to be called when @code{at:ifAbsent:} can't find the given key, and @code{at:ifAbsent:} does the same with @code{findIndex:ifAbsent:}. Thus, without even looking at the code for Dictionary itself, we can guess something of the code for Dictionary's implementation: @example findIndex: key ifAbsent: errCodeBlock [ @i{@r{@dots{}look for key@dots{}}} (keyNotFound) ifTrue: [ ^(errCodeBlock value) ] @i{@r{@dots{}}} ] at: key [ ^self at: key ifAbsent: [^self error: 'key not found'] ] @end example Actually, @code{findIndex:ifAbsent:} lies in class @code{HashedCollection}, as that @code{Dictionary(HashedCollection)} in the backtrace says. It would be nice if each entry on the stack backtrace included source line numbers. Unfortunately, at this point @gst{} doesn't provide this feature. Of course, you have the source code available... @node Looking at objects @subsection Looking at Objects When you are chasing an error, it is often helpful to examine the instance variables of your objects. While strategic calls to @code{printNl} will no doubt help, you can look at an object without having to write all the code yourself. The @code{inspect} message works on any object, and dumps out the values of each instance variable within the object.@footnote{When using the Blox GUI, it actually pops up a so-called @dfn{Inspector window}.} Thus: @example x := Interval from: 1 to: 5. x inspect @end example displays: @example An instance of Interval start: 1 stop: 5 step: 1 contents: [ [1]: 1 [2]: 2 [3]: 3 [4]: 4 [5]: 5 ] @end example We'll finish this chapter by emphasizing a technique which has already been covered: the use of the @code{error:} message in your own objects. As you saw in the case of Dictionary, an object can send itself an @code{error:} message with a descriptive string to abort execution and dump a stack backtrace. You should plan on using this technique in your own objects. It can be used both for explicit user-caused errors, as well as in internal sanity checks. @node More subclassing @section Coexisting in the Class Hierarchy The early chapters of this tutorial discussed classes in one of two ways. The ``toy'' classes we developed were rooted at Object; the system-provided classes were treated as immutable entities. While one shouldn't modify the behavior of the standard classes lightly, ``plugging in'' your own classes in the right place among their system-provided brethren can provide you powerful new classes with very little effort. This chapter will create two complete classes which enhance the existing Smalltalk hierarchy. The discussion will start with the issue of where to connect our new classes, and then continue onto implementation. Like most programming efforts, the result will leave many possibilities for improvements. The framework, however, should begin to give you an intuition of how to develop your own Smalltalk classes. @menu * The existing hierarchy:: We've been talking about it for a while, so here it is at last * Playing with Arrays:: Again. * New kinds of Numbers:: Sounds interesting, doesn't it? * Inheritance and Polymorphism:: Sounds daunting, doesn't it? @end menu @node The existing hierarchy @subsection The Existing Class Hierarchy To discuss where a new class might go, it is helpful to have a map of the current classes. The following is the basic class hierarchy of @gst{}. Indentation means that the line inherits from the earlier line with one less level of indentation.@footnote{This listing is courtesy of the printHierarchy method supplied by @gst{} author Steve Byrne. It's in the @file{kernel/Browser.st} file.}. @display @t{ }Object @t{ }Behavior @t{ }ClassDescription @t{ }Class @t{ }Metaclass @t{ }BlockClosure @t{ }Boolean @t{ }False @t{ }True @t{ }Browser @t{ }CFunctionDescriptor @t{ }CObject @t{ }CAggregate @t{ }CArray @t{ }CPtr @t{ }CCompound @t{ }CStruct @t{ }CUnion @t{ }CScalar @t{ }CChar @t{ }CDouble @t{ }CFloat @t{ }CInt @t{ }CLong @t{ }CShort @t{ }CSmalltalk @t{ }CString @t{ }CUChar @t{ }CByte @t{ }CBoolean @t{ }CUInt @t{ }CULong @t{ }CUShort @t{ }Collection @t{ }Bag @t{ }MappedCollection @t{ }SequenceableCollection @t{ }ArrayedCollection @t{ }Array @t{ }ByteArray @t{ }WordArray @t{ }LargeArrayedCollection @t{ }LargeArray @t{ }LargeByteArray @t{ }LargeWordArray @t{ }CompiledCode @t{ }CompiledMethod @t{ }CompiledBlock @t{ }Interval @t{ }CharacterArray @t{ }String @t{ }Symbol @t{ }LinkedList @t{ }Semaphore @t{ }OrderedCollection @t{ }RunArray @t{ }SortedCollection @t{ }HashedCollection @t{ }Dictionary @t{ }IdentityDictionary @t{ }MethodDictionary @t{ }RootNamespace @t{ }Namespace @t{ }SystemDictionary @t{ }Set @t{ }IdentitySet @t{ }ContextPart @t{ }BlockContext @t{ }MethodContext @t{ }CType @t{ }CArrayCType @t{ }CPtrCType @t{ }CScalarCType @t{ }Delay @t{ }DLD @t{ }DumperProxy @t{ }AlternativeObjectProxy @t{ }NullProxy @t{ }VersionableObjectProxy @t{ }PluggableProxy @t{ }File @t{ }Directory @t{ }FileSegment @t{ }Link @t{ }Process @t{ }SymLink @t{ }Magnitude @t{ }Association @t{ }Character @t{ }Date @t{ }LargeArraySubpart @t{ }Number @t{ }Float @t{ }Fraction @t{ }Integer @t{ }LargeInteger @t{ }LargeNegativeInteger @t{ }LargePositiveInteger @t{ }LargeZeroInteger @t{ }SmallInteger @t{ }Time @t{ }Memory @t{ }Message @t{ }DirectedMessage @t{ }MethodInfo @t{ }NullProxy @t{ }PackageLoader @t{ }Point @t{ }ProcessorScheduler @t{ }Rectangle @t{ }SharedQueue @t{ }Signal @t{ }Exception @t{ }Error @t{ }Halt @t{ }ArithmeticError @t{ }ZeroDivide @t{ }MessageNotUnderstood @t{ }UserBreak @t{ }Notification @t{ }Warning @t{ }Stream @t{ }ObjectDumper @t{ }PositionableStream @t{ }ReadStream @t{ }WriteStream @t{ }ReadWriteStream @t{ }ByteStream @t{ }FileStream @t{ }Random @t{ }TextCollector @t{ }TokenStream @t{ }TrappableEvent @t{ }CoreException @t{ }ExceptionCollection @t{ }UndefinedObject @t{ }ValueAdaptor @t{ }NullValueHolder @t{ }PluggableAdaptor @t{ }DelayedAdaptor @t{ }ValueHolder @end display While initially a daunting list, you should take the time to hunt down the classes we've examined in this tutorial so far. Notice, for instance, how an Array is a subclass below the @i{SequenceableCollection} class. This makes sense; you can walk an Array from one end to the other. By contrast, notice how this is not true for Sets: it doesn't make sense to walk a Set from one end to the other. A little puzzling is the relationship of a Bag to a Set, since a Bag is actually a Set supporting multiple occurrences of its elements. The answer lies in the purpose of both a Set and a Bag. Both hold an unordered collection of objects; but a Bag needs to be optimized for the case when an object has possibly thousands of occurrences, while a Set is optimized for checking object uniqueness. That's why Set being a subclass or Bag, or the other way round, would be a source of problems in the actual implementation of the class. Currently a Bag holds a Dictionary associating each object to each count; it would be feasible however to have Bag as a subclass of HashedCollection and a sibling of Set. Look at the treatment of numbers---starting with the class @i{Magnitude}. While numbers can indeed be ordered by @emph{less than}, @emph{greater than}, and so forth, so can a number of other objects. Each subclass of Magnitude is such an object. So we can compare characters with other characters, dates with other dates, and times with other times, as well as numbers with numbers. Finally, you will have probably noted some pretty strange classes, representing language entities that you might have never thought of as objects themselves: @i{Namespace}, @i{Class} and even @i{CompiledMethod}. They are the base of Smalltalk's ``reflection'' mechanism which will be discussed later, in @ref{Why is #new there?!?, , The truth on metaclasses}. @node Playing with Arrays @subsection Playing with Arrays Imagine that you need an array, but alas you need that if an index is out of bounds, it returns nil. You could modify the Smalltalk implementation, but that might break some code in the image, so it is not practical. Why not add a subclass? @example "We could subclass from Array, but that class is specifically optimized by the VM (which assumes, among other things, that it does not have any instance variables). So we use its abstract superclass instead. The discussion below holds equally well." ArrayedCollection subclass: NiledArray [ boundsCheck: index [ ^(index < 1) | (index > (self basicSize)) ] at: index [ ^(self boundsCheck: index) ifTrue: [ nil ] ifFalse: [ super at: index ] ] at: index put: val [ ^(self boundsCheck: index) ifTrue: [ val ] ifFalse: [ super at: index put: val ] ] ] @end example Much of the machinery of adding a class should be familiar. We see another declaration like @code{comment:}, that is @code{shape:} message. This sets up @code{NiledArray} to have the same underlying structure of an @code{Array} object; we'll delay discussing this until the chapter on the nuts and bolts of arrays. In any case, we inherit all of the actual knowledge of how to create arrays, reference them, and so forth. All that we do is intercept @code{at:} and @code{at:put:} messages, call our common function to validate the array index, and do something special if the index is not valid. The way that we coded the bounds check bears a little examination. Making a first cut at coding the bounds check, you might have coded the bounds check in NiledArray's methods twice (once for @code{at:}, and again for @code{at:put:}. As always, it's preferable to code things once, and then re-use them. So we instead add a method for bounds checking @code{boundsCheck:}, and use it for both cases. If we ever wanted to enhance the bounds checking (perhaps emit an error if the index is < 1 and answer nil only for indices greater than the array size?), we only have to change it in one place. The actual math for calculating whether the bounds have been violated is a little interesting. The first part of the expression returned by the method: @example (index < 1) | (index > (self basicSize)) @end example @noindent is true if the index is less than 1, otherwise it's false. This part of the expression thus becomes the boolean object true or false. The boolean object then receives the message @code{|}, and the argument @code{(index > (self basicSize))}. @code{|} means ``or''---we want to OR together the two possible out-of-range checks. What is the second part of the expression? @footnote{Smalltalk also offers an @code{or:} message, which is different in a subtle way from @code{|}. or: takes a code block, and only invokes the code block if it's necessary to determine the value of the expression. This is analogous to the guaranteed C semantic that @code{||} evaluates left-to-right only as far as needed. We could have written the expressions as @code{((index < 1) or: [index > (self basicSize)])}. Since we expect both sides of or: to be false most of the time, there isn't much reason to delay evaluation of either side in this case.} @code{index} is our argument, an integer; it receives the message @code{>}, and thus will compare itself to the value @code{self basicSize} returns. While we haven't covered the underlying structures Smalltalk uses to build arrays, we can briefly say that the @code{#basicSize} message returns the number of elements the Array object can contain. So the index is checked to see if it's less than 1 (the lowest legal Array index) or greater than the highest allocated slot in the Array. If it is either (the @code{|} operator!), the expression is true, otherwise false. From there it's downhill; our boolean object, returned by @code{boundsCheck:}, receives the @code{ifTrue:ifFalse:} message, and a code block which will do the appropriate thing. Why do we have @code{at:put:} return val? Well, because that's what it's supposed to do: look at every implementor of @code{at:put} or @code{at:} and you'll find that it returns its second parameter. In general, the result is discarded; but one could write a program which uses it, so we'll write it this way anyway. @node New kinds of Numbers @subsection Adding a New Kind of Number If we were programming an application which did a large amount of complex math, we could probably manage it with a number of two-element arrays. But we'd forever be writing in-line code for the math and comparisons; it would be much easier to just implement an object class to support the complex numeric type. Where in the class hierarchy would it be placed? You've probably already guessed---but let's step down the hierarchy anyway. Everything inherits from Object, so that's a safe starting point. Complex numbers can not be compared with @code{<} and @code{>}, and yet we strongly suspect that, since they are numbers, we should place them under the Number class. But Number inherits from Magnitude---how do we resolve this conflict? A subclass can place itself under a superclass which allows some operations the subclass doesn't wish to allow. All that you must do is make sure you intercept these messages and return an error. So we will place our new Complex class under Number, and make sure to disallow comparisons. One can reasonably ask whether the real and imaginary parts of our complex number will be integer or floating point. In the grand Smalltalk tradition, we'll just leave them as objects, and hope that they respond to numeric messages reasonably. If they don't, the user will doubtless receive errors and be able to track back their mistake with little fuss. We'll define the four basic math operators, as well as the (illegal) relationals. We'll add @code{printOn:} so that the printing methods work, and that should give us our Complex class. The class as presented suffers some limitations, which we'll cover later in the chapter. @example Number subclass: Complex [ | realpart imagpart | "This is a quick way to define class-side methods." Complex class >> new [ ^self error: 'use real:imaginary:' ] Complex class >> new: ignore [ ^self new ] Complex class >> real: r imaginary: i [ ^(super new) setReal: r setImag: i ] setReal: r setImag: i [ realpart := r. imagpart := i. ^self ] real [ ^realpart ] imaginary [ ^imagpart ] + val [ ^Complex real: (realpart + val real) imaginary: (imagpart + val imaginary) ] - val [ ^Complex real: (realpart - val real) imaginary: (imagpart - val imaginary) ] * val [ ^Complex real: (realpart * val real) - (imagpart * val imaginary) imaginary: (imagpart * val real) + (realpart * val imaginary) ] / val [ | d r i | d := (val real * val real) + (val imaginary * val imaginary). r := ((realpart * val real) + (imagpart * val imaginary)). i := ((imagpart * val real) - (realpart * val imaginary)). ^Complex real: r / d imaginary: i / d ] = val [ ^(realpart = val real) & (imagpart = val imaginary) ] "All other comparison methods are based on <" < val [ ^self shouldNotImplement ] printOn: aStream [ realpart printOn: aStream. aStream nextPut: $+. imagpart printOn: aStream. aStream nextPut: $i ] ] @end example There should be surprisingly little which is actually new in this example. The printing method uses both @code{printOn:} as well as @code{nextPut:} to do its printing. While we haven't covered it, it's pretty clear that @code{$+} generates the ASCII character @code{+} as an object@footnote{A @gst{} extension allows you to type characters by ASCII code too, as in @code{$<43>}.}, and @code{nextPut:} puts its argument as the next thing on the stream. The math operations all generate a new object, calculating the real and imaginary parts, and invoking the Complex class to create the new object. Our creation code is a little more compact than earlier examples; instead of using a local variable to name the newly-created object, we just use the return value and send a message directly to the new object. Our initialization code explicitly returns self; what would happen if we left this off? @node Inheritance and Polymorphism @subsection Inheritance and Polymorphism This is a good time to look at what we've done with the two previous examples at a higher level. With the NiledArray class, we inherited almost all of the functionality ality of arrays, with only a little bit of code added to address our specific needs. While you may have not thought to try it, all the existing methods for an Array continue to work without further effort-you might find it interesting to ponder why the following still works: @example a := NiledArray new: 10 a at: 5 put: 1234 a do: [:i| i printNl ] @end example The strength of inheritance is that you focus on the incremental changes you make; the things you don't change will generally continue to work. In the Complex class, the value of polymorphism was exercised. A Complex number responds to exactly the same set of messages as any other number. If you had handed this code to someone, they would know how to do math with Complex numbers without further instruction. Compare this with C, where a complex number package would require the user to first find out if the complex-add function was complex_plus(), or perhaps complex_add(), or add_complex(), or@dots{} However, one glaring deficiency is present in the Complex class: what happens if you mix normal numbers with Complex numbers? Currently, the Complex class assumes that it will only interact with other Complex numbers. But this is unrealistic: mathematically, a ``normal'' number is simply one with an imaginary part of 0. Smalltalk was designed to allow numbers to coerce themselves into a form which will work with other numbers. The system is clever and requires very little additional code. Unfortunately, it would have tripled the amount of explanation required. If you're interested in how coercion works in @gst{}, you should find the Smalltalk library source, and trace back the execution of the @code{retry:coercing:} messages. You want to consider the value which the @code{generality} message returns for each type of number. Finally, you need to examine the @code{coerce:} handling in each numeric class. @node Streams @section Smalltalk Streams Our examples have used a mechanism extensively, even though we haven't discussed it yet. The Stream class provides a framework for a number of data structures, including input and output functionality, queues, and endless sources of dynamically-generated data. A Smalltalk stream is quite similar to the UNIX streams you've used from C. A stream provides a sequential view to an underlying resource; as you read or write elements, the stream position advances until you finally reach the end of the underlying medium. Most streams also allow you to set the current position, providing random access to the medium. @menu * The output stream:: Which, even though you maybe didn't know it, we've used all the time * Your own stream:: Which, instead, is something new * Files:: Which are streams too * Dynamic Strings:: A useful application of Streams @end menu @node The output stream @subsection The Output Stream The examples in this book all work because they write their output to the @code{Transcript} stream. Each class implements the @code{printOn:} method, and writes its output to the supplied stream. The @code{printNl} method all objects use is simply to send the current object a @code{printOn:} message whose argument is @code{Transcript} (by default attached to the standard output stream found in the @code{stdout} global). You can invoke the standard output stream directly: @example 'Hello, world' printOn: stdout stdout inspect @end example @noindent or you can do the same for the Transcript, which is yet another stream: @example 'Hello, world' printOn: stdout Transcript inspect @end example @noindent the last @code{inspect} statement will show you how the @code{Transcript} is linked to @code{stdout}@footnote{Try executing it under Blox, where the Transcript is linked to the omonymous window!}. @node Your own stream @subsection Your Own Stream Unlike a pipe you might create in C, the underlying storage of a Stream is under your control. Thus, a Stream can provide an anonymous buffer of data, but it can also provide a stream-like interpretation to an existing array of data. Consider this example: @example a := Array new: 10 a at: 4 put: 1234 a at: 9 put: 5678 s := ReadWriteStream on: a. s inspect s position: 1 s inspect s nextPut: 11; nextPut: 22 (a at: 1) printNl a do: [:x| x printNl] s position: 2 s do: [:x| x printNl] s position: 5 s do: [:x| x printNl] s inspect @end example The key is the @code{on:} message; it tells a stream class to create itself in terms of the existing storage. Because of polymorphism, the object specified by on: does not have to be an Array; any object which responds to numeric at: messages can be used. If you happen to have the NiledArray class still loaded from the previous chapter, you might try streaming over that kind of array instead. You're wondering if you're stuck with having to know how much data will be queued in a Stream at the time you create the stream. If you use the right class of stream, the answer is no. A ReadStream provides read-only access to an existing collection. You will receive an error if you try to write to it. If you try to read off the end of the stream, you will also get an error. By contrast, WriteStream and ReadWriteStream (used in our example) will tell the underlying collection to grow when you write off the end of the existing collection. Thus, if you want to write several strings, and don't want to add up their lengths yourself: @example s := ReadWriteStream on: String new s inspect s nextPutAll: 'Hello, ' s inspect s nextPutAll: 'world' s inspect s position: 1 s inspect s do: [:c | stdout nextPut: c ] s contents @end example In this case, we have used a String as the collection for the Stream. The @code{printOn:} messages add bytes to the initially empty string. Once we've added the data, you can continue to treat the data as a stream. Alternatively, you can ask the stream to return to you the underlying object. After that, you can use the object (a String, in this example) using its own access methods. There are many amenities available on a stream object. You can ask if there's more to read with @code{atEnd}. You can query the position with @code{position}, and set it with @code{position:}. You can see what will be read next with @code{peek}, and you can read the next element with @code{next}. In the writing direction, you can write an element with @code{nextPut:}. You don't need to worry about objects doing a @code{printOn:} with your stream as a destination; this operation ends up as a sequence of @code{nextPut:} operations to your stream. If you have a collection of things to write, you can use @code{nextPutAll:} with the collection as an argument; each member of the collection will be written onto the stream. If you want to write an object to the stream several times, you can use @code{next:put:}, like this: @example s := ReadWriteStream on: (Array new: 0) s next: 4 put: 'Hi!' s position: 1 s do: [:x | x printNl] @end example @node Files @subsection Files Streams can also operate on files. If you wanted to dump the file @file{/etc/passwd} to your terminal, you could create a stream on the file, and then stream over its contents: @example f := FileStream open: '/etc/passwd' mode: FileStream read f linesDo: [ :c | Transcript nextPutAll: c; nl ] f position: 30 25 timesRepeat: [ Transcript nextPut: (f next) ] f close @end example and, of course, you can load Smalltalk source code into your image: @example FileStream fileIn: '/Users/myself/src/source.st' @end example @node Dynamic Strings @subsection Dynamic Strings Streams provide a powerful abstraction for a number of data structures. Concepts like current position, writing the next position, and changing the way you view a data structure when convenient combine to let you write compact, powerful code. The last example is taken from the actual Smalltalk source code---it shows a general method for making an object print itself onto a string. @example printString [ | stream | stream := WriteStream on: (String new). self printOn: stream. ^stream contents ] @end example This method, residing in Object, is inherited by every class in Smalltalk. The first line creates a WriteStream which stores on a String whose length is currently 0 (@code{String new} simply creates an empty string. It then invokes the current object with @code{printOn:}. As the object prints itself to ``stream'', the String grows to accommodate new characters. When the object is done printing, the method simply returns the underlying string. As we've written code, the assumption has been that printOn: would go to the terminal. But replacing a stream to a file like @file{/dev/tty} with a stream to a data structure (@code{String new}) works just as well. The last line tells the Stream to return its underlying collection, which will be the string which has had all the printing added to it. The result is that the @code{printString} message returns an object of the String class whose contents are the printed representation of the very object receiving the message. @node Exception handling @section Exception handling in Smalltalk Up to this point of the tutorial, you used the original Smalltalk-80 error signalling mechanism: @example check: num [ | c | c := history at: num ifAbsent: [ ^self error: 'No such check #' ]. ^c ] @end example In the above code, if a matching check number is found, the method will answer the object associated to it. If no prefix is found, Smalltalk will unwind the stack and print an error message including the message you gave and stack information. @example CheckingAccount new: 31 "<0x33788>" error: No such check # @i{@r{@dots{}blah blah@dots{}}} CheckingAccount>>#error: [] in Dictionary>>#at:ifAbsent: Dictionary(HashedCollection)>>#findIndex:ifAbsent: Dictionary>>#at:ifAbsent: [] in CheckingAccount>>#check: CheckingAccount>>#check: UndefinedObject(Object)>>#executeStatements @end example Above we see the object that received the #error: message, the message text itself, and the frames (innermost-first) running when the error was captured by the system. In addition, the rest of the code in methods like @code{CheckingAccount>>#check:} was not executed. So simple error reporting gives us most of the features we want: @itemize @bullet @item Execution stops immediately, preventing programs from continuing as if nothing is wrong. @item The failing code provides a more-or-less useful error message. @item Basic system state information is provided for diagnosis. @item A debugger can drill further into the state, providing information like details of the receivers and arguments on the stack. @end itemize However, there is a more powerful and complex error handling mechanism, that is @dfn{exception}. They are like "exceptions" in other programming languages, but are more powerful and do not always indicate error conditions. Even though we use the term "signal" often with regard to them, do not confuse them with the signals like @code{SIGTERM} and @code{SIGINT} provided by some operating systems; they are a different concept altogether. Deciding to use exceptions instead of @code{#error:} is a matter of aesthetics, but you can use a simple rule: use exceptions only if you want to provide callers with a way to recover sensibly from certain errors, and then only for signalling those particular errors. For example, if you are writing a word processor, you might provide the user with a way to make regions of text read-only. Then, if the user tries to edit the text, the objects that model the read-only text can signal a @code{ReadOnlyText} or other kind of exception, whereupon the user interface code can stop the exception from unwinding and report the error to the user. When in doubt about whether exceptions would be useful, err on the side of simplicity; use @code{#error:} instead. It is much easier to convert an #error: to an explicit exception than to do the opposite. @menu * Creating exceptions:: Starting to use the mechanism * Raising exceptions:: What to do when exceptional events happen * Handling exceptions:: The other side * When an exception isn't handled:: Default actions * Creating new exception classes:: Your own exceptions * Hooking into the stack unwinding:: An alternative exception handling system * Handler stack unwinding caveat:: Differences with other languages @end menu @node Creating exceptions @subsection Creating exceptions @gst{} provides a few exceptions, all of which are subclasses of @code{Exception}. Most of the ones you might want to create yourself are in the @code{SystemExceptions} namespace. You can browse the builtin exceptions in the base library reference, and look at their names with @code{Exception printHierarchy}. Some useful examples from the system exceptions are @code{SystemExceptions.InvalidValue}, whose meaning should be obvious, and @code{SystemExceptions.WrongMessageSent}, which we will demonstrate below. Let's say that you change one of your classes to no longer support #new for creating new instances. However, because you use the first-class classes feature of Smalltalk, it is not so easy to find and change all sends. Now, you can do something like this: @example Object subclass: Toaster [ Toaster class >> new [ ^SystemExceptions.WrongMessageSent signalOn: #new useInstead: #toast: ] Toaster class >> toast: reason [ ^super new reason: reason; yourself ] ... ] @end example Admittedly, this doesn't quite fit the conditions for using exceptions. However, since the exception type is already provided, it is probably easier to use it than #error: when you are doing defensive programming of this sort. @node Raising exceptions @subsection Raising exceptions Raising an exception is really a two-step process. First, you create the exception object; then, you send it @code{#signal}. If you look through the hierarchy, you'll see many class methods that combine these steps for convenience. For example, the class @code{Exception} provides @code{#new} and @code{#signal}, where the latter is just @code{^self new signal}. You may be tempted to provide only a signalling variant of your own exception creation methods. However, this creates the problem that your subclasses will not be able to trivially provide new instance creation methods. @example Error subclass: ReadOnlyText [ ReadOnlyText class >> signalOn: aText range: anInterval [ ^self new initText: aText range: anInterval; signal ] initText: aText range: anInterval [ ... ] ] @end example Here, if you ever want to subclass @code{ReadOnlyText} and add new information to the instance before signalling it, you'll have to use the private method @code{#initText:range:}. We recommend leaving out the signalling instance-creation variant in new code, as it saves very little work and makes signalling code less clear. Use your own judgement and evaluation of the situation to determine when to include a signalling variant. @node Handling exceptions @subsection Handling exceptions To handle an exception when it occurs in a particular block of code, use @code{#on:do:} like this: @example ^[someText add: inputChar beforeIndex: i] on: ReadOnlyText do: [:sig | sig return: nil] @end example This code will put a handler for @code{ReadOnlyText} signals on the handler stack while the first block is executing. If such an exception occurs, and it is not handled by any handlers closer to the point of signalling on the stack (known as "inner handlers"), the exception object will pass itself to the handler block given as the @code{do:} argument. You will almost always want to use this object to handle the exception somehow. There are six basic handler actions, all sent as messages to the exception object: @table @code @item return: Exit the block that received this @code{#on:do:}, returning the given value. You can also leave out the argument by sending @code{#return}, in which case it will be nil. If you want this handler to also handle exceptions in whatever value you might provide, you should use @code{#retryUsing:} with a block instead. @item retry Acts sort of like a "goto" by restarting the first block. Obviously, this can lead to an infinite loop if you don't fix the situation that caused the exception. @code{#retry} is a good way to implement reinvocation upon recovery, because it does not increase the stack height. For example, this: @example frobnicate: n [ ^[do some stuff with n] on: SomeError do: [:sig | sig return: (self frobnicate: n + 1)] ] @end example @noindent should be replaced with retry: @example frobnicate: aNumber [ | n | n := aNumber. ^[do some stuff with n] on: SomeError do: [:sig | n := 1 + n. sig retry] ] @end example @item retryUsing: Like @code{#retry}, except that it effectively replaces the original block with the one given as an argument. @item pass If you want to tell the exception to let an outer handler handle it, use @code{#pass} instead of @code{#signal}. This is just like rethrowing a caught exception in other languages. @item resume: This is the really interesting one. Instead of unwinding the stack, this will effectively answer the argument from the @code{#signal} send. Code that sends @code{#signal} to resumable exceptions can use this value, or ignore it, and continue executing. You can also leave out the argument, in which case the @code{#signal} send will answer nil. Exceptions that want to be resumable must register this capability by answering @code{true} from the @code{#isResumable} method, which is checked on every @code{#resume:} send. @item outer This is like @code{#pass}, but if an outer handler uses @code{#resume:}, this handler block will be resumed (and @code{#outer} will answer the argument given to @code{#resume:}) rather than the piece of code that sent @code{#signal} in the first place. @end table None of these methods return to the invoking handler block except for @code{#outer}, and that only in certain cases described for it above. Exceptions provide several more features; see the methods on the classes @code{Signal} and @code{Exception} for the various things you can do with them. Fortunately, the above methods can do what you want in almost all cases. If you don't use one of these methods or another exception feature to exit your handler, Smalltalk will assume that you meant to @code{sig return:} whatever you answer from your handler block. We don't recommend relying on this; you should use an explicit @code{sig return:} instead. A quick shortcut to handling multiple exception types is the @code{ExceptionSet}, which allows you to have a single handler for the exceptions of a union of classes: @example ^[do some stuff with n] on: SomeError, ReadOnlyError do: [:sig | ...] @end example In this code, any @code{SomeError} or @code{ReadOnlyError} signals will be handled by the given handler block. @node When an exception isn't handled @subsection When an exception isn't handled Every exception chooses one of the above handler actions by default when no handler is found, or they all use @code{#pass}. This is invoked by sending @code{#defaultAction} to the class. One example of a default action is presented above as part of the example of @code{#error:} usage; that default action prints a message, backtrace, and unwinds the stack all the way. The easiest way to choose a default action for your own exception classes is to subclass from an exception class that already chose the right one, as explained in the next section. For example, some exceptions, such as warnings, resume by default, and thus should be treated as if they will almost always resume. Selecting by superclass is by no means a requirement. Specializing your @code{Error} subclass to be resumable, or even to resume by default, is perfectly acceptable when it makes sense for your design. @node Creating new exception classes @subsection Creating new exception classes If you want code to be able to handle your signalled exceptions, you will probably want to provide a way to pick those kinds out automatically. The easiest way to do this is to subclass @code{Exception}. First, you should choose an exception class to specialize. @code{Error} is the best choice for non-resumable exceptions, and @code{Notification} or its subclass @code{Warning} is best for exceptions that should resume with @code{nil} by default. Exceptions are just normal objects; include whatever information you think would be useful to handlers. Note that there are two textual description fields, a @dfn{description} and a @dfn{message text}. The description, if provided, should be a more-or-less constant string answered from a override method on @code{#description}, meant to describe all instances of your exception class. The message text is meant to be provided at the point of signalling, and should be used for any extra information that code might want to provide. Your signalling code can provide the @code{messageText} by using @code{#signal:} instead of @code{#signal}. This is yet another reason why signalling variants of instance creation messages can be more trouble than they're worth. @node Hooking into the stack unwinding @subsection Hooking into the stack unwinding More often useful than even @code{#on:do:} is @code{#ensure:}, which guarantees that some code is executed when the stack unwinds, whether because of normal execution or because of a signalled exception. Here is an example of use of @code{#ensure:} and a situation where the stack can unwind even without a signal: @example Object subclass: ExecuteWithBreak [ | breakBlock | break: anObject [ breakBlock value: anObject ] valueWithBreak: aBlock [ "Sets up breakBlock before entering the block, and passes self to the block." | oldBreakBlock | oldBreakBlock := breakBlock. ^[breakBlock := [:arg | ^arg]. aBlock value] ensure: [breakBlock := oldBreakBlock] ] ] @end example This class provides a way to stop the execution of a block without exiting the whole method as using @code{^} inside a block would do. The use of @code{#ensure:} guarantees (hence the name "ensure") that even if @code{breakBlock} is invoked or an error is handled by unwinding, the old ``break block'' will be restored. The definition of @code{breakBlock} is extremely simply; it is an example of the general unwinding feature of blocks, that you have probably already used: @example (history includesKey: num) ifTrue: [ ^self error: 'Duplicate check number' ]. @end example You have probably been using @code{#ensure:} without knowing. For example, @code{File>>#withReadStreamDo:} uses it to ensure that the file is closed when leaving the block. @node Handler stack unwinding caveat @subsection Handler stack unwinding caveat One important difference between Smalltalk and other languages is that when a handler is invoked, the stack is not unwound. The Smalltalk exception system is designed this way because it's rare to write code that could break because of this difference, and the @code{#resume:} feature doesn't make sense if the stack is unwound. It is easy enough to unwind a stack later, and is not so easy to wind it again if done too early. For almost all applications, this will not matter, but it technically changes the semantics significantly so should be kept in mind. One important case in which it might matter is when using @code{#ensure:} blocks @emph{and} exception handlers. For comparison, this Smalltalk code: @example | n | n := 42. [[self error: 'error'] ensure: [n := 24]] on: Error do: [:sig | n printNl. sig return]. n printNl. @end example @noindent will put "42" followed by "24" on the transcript, because the @code{n := 24} will not be executed until @code{sig return} is invoked, unwinding the stack. Similar Java code acts differently: @example int n = 42; try @{ try @{throw new Exception ("42");@} finally @{n = 24;@} @} catch (Exception e) @{ System.out.println (n); @} System.out.println (n); @end example @noindent printing "24" twice, because the stack unwinds before executing the catch block. @node Behind the scenes @section Some nice stuff from the Smalltalk innards Just like with everything else, you'd probably end up asking yourself: how's it done? So here's this chapter, just to wheten your appetite... @menu * Inside Arrays:: Delving into something old * Two flavors of equality:: Delving into something new * Why is #new there?!?:: Or, the truth on metaclasses * Performance:: Hmm... they told me Smalltalk is slow... @end menu @node Inside Arrays @subsection How Arrays Work Smalltalk provides a very adequate selection of predefined classes from which to choose. Eventually, however, you will find the need to code a new basic data structure. Because Smalltalk's most fundamental storage allocation facilities are arrays, it is important that you understand how to use them to gain efficient access to this kind of storage. @b{The Array Class.} Our examples have already shown the Array class, and its use is fairly obvious. For many applications, it will fill all your needs---when you need an array in a new class, you keep an instance variable, allocate a new Array and assign it to the variable, and then send array accesses via the instance variable. This technique even works for string-like objects, although it is wasteful of storage. An Array object uses a Smalltalk pointer for each slot in the array; its exact size is transparent to the programmer, but you can generally guess that it'll be roughly the word size of your machine. @footnote{For @gst{}, the size of a C @code{long}, which is usually 32 bits.} For storing an array of characters, therefore, an Array works but is inefficient. @b{Arrays at a Lower Level.} So let's step down to a lower level of data structure. A ByteArray is much like an Array, but each slot holds only an integer from 0 to 255-and each slot uses only a byte of storage. If you only needed to store small quantities in each array slot, this would therefore be a much more efficient choice than an Array. As you might guess, this is the type of array which a String uses. Aha! But when you go back to chapter 9 and look at the Smalltalk hierarchy, you notice that String does not inherit from ByteArray. To see why, we must delve down yet another level, and arrive at the basic methods for setting up the structure of the instances of a class. When we implemented our NiledArray example, we used @code{}. The shape is exactly that: the fundamental structure of Smalltalk objects created within a given class. Let's consider the differences in the next sub-sections. @table @asis @item Nothing The default shape specifies the simplest Smalltalk object. The object consists only of the storage needed to hold the instance variables. In C, this would be a simple structure with zero or more scalar fields.@footnote{C requires one or more; zero is allowed in Smalltalk}. @item @code{#pointer} Storage is still allocated for any instance variables, but the objects of the class must be created with a @code{new:} message. The number passed as an argument to @code{new:} causes the new object, in addition to the space for instance variables, to also have that many slots of unnamed (indexed) storage allocated. The analog in C would be to have a dynamically allocated structure with some scalar fields, followed at its end by a array of pointers. @item @code{#byte} The storage allocated as specified by new: is an array of bytes. The analog in C would be a dynamically allocated structure with scalar fields@footnote{This is not always true for other Smalltalk implementations, who don't allow instance variables in variableByteSubclasses and variableWordSubclasses.}, followed by a array of @code{char}. @item @code{#word} The storage allocated as specified by new: is an array of C unsigned longs, which are represented in Smalltalk by Integer objects. The analog in C would be a dynamically allocated structure with scalar fields, followed by an array of @code{long}. This kind of subclass is only used in a few places in Smalltalk. @item @code{#character} The storage allocated as specified by new: is an array of characters. The analog in C would be a dynamically allocated structure with scalar fields, followed by a array of @code{char}. @end table There are many more shapes for more specialized usage. All of them specify the same kind of ``array-like'' behavior, with different data types. How to access this new arrays? You already know how to access instance variables---by name. But there doesn't seem to be a name for this new storage. The way an object accesses it is to send itself array-type messages like @code{at:}, @code{at:put:}, and so forth. The problem is when an object wants to add a new level of interpretation to these messages. Consider a Dictionary---it is a pointer-holding object but its @code{at:} message is in terms of a key, not an integer index of its storage. Since it has redefined the @code{at:} message, how does it access its fundamental storage? The answer is that Smalltalk has defined @code{basicAt:} and @code{basicAt:put:}, which will access the basic storage even when the @code{at:} and @code{at:put:} messages have been defined to provide a different abstraction. This can get pretty confusing in the abstract, so let's do an example to show how it's pretty simple in practice. Smalltalk arrays tend to start at 1; let's define an array type whose permissible range is arbitrary. @example ArrayedCollection subclass: RangedArray [ | offset | RangedArray class >> new: size [ ^self new: size base: 1 ] RangedArray class >> new: size base: b [ ^(super new: size) init: b ] init: b [ offset := (b - 1). "- 1 because basicAt: works with a 1 base" ^self ] rangeCheck: i [ (i <= offset) | (i > (offset + self basicSize)) ifTrue: [ 'Bad index value: ' printOn: stderr. i printOn: stderr. Character nl printOn: stderr. ^self error: 'illegal index' ] ] at: [ self rangeCheck: i. ^self basicAt: i - offset ] at: i put: v [ self rangeCheck: i. ^self basicAt: i - offset put: v ] ] @end example The code has two parts; an initialization, which simply records what index you wish the array to start with, and the at: messages, which adjust the requested index so that the underlying storage receives its 1-based index instead. We've included a range check; its utility will demonstrate itself in a moment: @example a := RangedArray new: 10 base: 5. a at: 5 put: 0 a at: 4 put: 1 @end example Since 4 is below our base of 5, a range check error occurs. But this check can catch more than just our own misbehavior! @example a do: [:x| x printNl] @end example Our do: message handling is broken! The stack backtrace pretty much tells the story: @example RangedArray>>#rangeCheck: RangedArray>>#at: RangedArray>>#do: @end example Our code received a do: message. We didn't define one, so we inherited the existing do: handling. We see that an Integer loop was constructed, that a code block was invoked, and that our own at: code was invoked. When we range checked, we trapped an illegal index. Just by coincidence, this version of our range checking code also dumps the index. We see that do: has assumed that all arrays start at 1. The immediate fix is obvious; we implement our own do: @example RangedArray extend [ do: aBlock [ 1 to: (self basicSize) do: [:x| aBlock value: (self basicAt: x) ] ] ] @end example But the issues start to run deep. If our parent class believed that it knew enough to assume a starting index of 1@footnote{Actually, in @gst{} @code{do:} is not the only message assuming that.}, why didn't it also assume that it could call basicAt:? The answer is that of the two choices, the designer of the parent class chose the one which was less likely to cause trouble; in fact all standard Smalltalk collections do have indices starting at 1, yet not all of them are implemented so that calling basicAt: would work.@footnote{Some of these classes actually redefine @code{do:} for performance reasons, but they would work even if the parent class' implementation of @code{do:} was kept.} Object-oriented methodology says that one object should be entirely opaque to another. But what sort of privacy should there be between a higher class and its subclasses? How many assumption can a subclass make about its superclass, and how many can the superclass make before it begins infringing on the sovereignty of its subclasses? Alas, there are rarely easy answers, and this is just an example. For this particular problem, there is an easy solution. When the storage need not be accessed with peak efficiency, you can use the existing array classes. When every access counts, having the storage be an integral part of your own object allows for the quickest access---but remember that when you move into this area, inheritance and polymorphism become trickier, as each level must coordinate its use of the underlying array with other levels. @node Two flavors of equality @subsection Two flavors of equality As first seen in chapter two, Smalltalk keys its dictionary with things like @i{#word}, whereas we generally use @i{'word'}. The former, as it turns out, is from class Symbol. The latter is from class String. What's the real difference between a Symbol and a String? To answer the question, we'll use an analogy from C. In C, if you have a function for comparing strings, you might try to write it: @example streq(char *p, char *q) @{ return (p == q); @} @end example But clearly this is wrong! The reason is that you can have two copies of a string, each with the same contents but each at its own address. A correct string compare must walk its way through the strings and compare each element. In Smalltalk, exactly the same issue exists, although the details of manipulating storage addresses are hidden. If we have two Smalltalk strings, both with the same contents, we don't necessarily know if they're at the same storage address. In Smalltalk terms, we don't know if they're the same object. The Smalltalk dictionary is searched frequently. To speed the search, it would be nice to not have to compare the characters of each element, but only compare the address itself. To do this, you need to have a guarantee that all strings with the same contents are the same object. The String class, created like: @example y := 'Hello' @end example @noindent does not satisfy this. Each time you execute this line, you may well get a new object. But a very similar class, Symbol, will always return the same object: @example y := #Hello @end example In general, you can use strings for almost all your tasks. If you ever get into a performance-critical function which looks up strings, you can switch to Symbol. It takes longer to create a Symbol, and the memory for a Symbol is never freed (since the class has to keep tabs on it indefinitely to guarantee it continues to return the same object). You can use it, but use it with care. This tutorial has generally used the strcmp()-ish kind of checks for equality. If you ever need to ask the question ``is this the same object?'', you use the @code{==} operator instead of @code{=}: @example x := y := 'Hello' (x = y) printNl (x == y) printNl y := 'Hel', 'lo' (x = y) printNl (x == y) printNl x := #Hello y := #Hello (x = y) printNl (x == y) printNl @end example Using C terms, @code{=} compares contents like @code{strcmp()}. @code{==} compares storage addresses, like a pointer comparison. @node Why is #new there?!? @subsection The truth about metaclasses Everybody, sooner or later, looks for the implementation of the @code{#new} method in Object class. To their surprise, they don't find it; if they're really smart, they search for implementors of #new in the image and they find out it is implemented by @code{Behavior}... which turns out to be a subclass of Object! The truth starts showing to their eyes about that sentence that everybody says but few people understand: ``classes are objects''. Huh? Classes are objects?!? Let me explain. @ifinfo Open up an image; then type the text following the @code{st>} prompt. @end ifinfo @ifhtml Open up an image; then type the text following the @code{st>} prompt. @end ifhtml @iftex Open up an image; then type the text printed in @t{mono-spaced} font. @end iftex @display st> @t{Set superclass!} HashedCollection st> @t{HashedCollection superclass!} Collection st> @t{Collection superclass!} Object st> @t{Object superclass!} nil @end display Nothing new for now. Let's try something else: @display st> @t{#(1 2 3) class!} Array st> @t{'123' class!} String st> @t{Set class!} Set class st> @t{Set class class!} Metaclass @end display You get it, that strange @code{Set class} thing is something called ``a meta-class''... let's go on: @display st> @t{^Set class superclass!} Collection class st> @t{^Collection class superclass!} Object class @end display You see, there is a sort of `parallel' hierarchy between classes and metaclasses. When you create a class, Smalltalk creates a metaclass; and just like a class describes how methods for its instances work, a metaclass describes how class methods for that same class work. @code{Set} is an instance of the metaclass, so when you invoke the @code{#new} class method, you can also say you are invoking an instance method implemented by @code{Set class}. Simply put, class methods are a lie: they're simply instance methods that are understood by instances of metaclasses. Now you would expect that @code{Object class superclass} answers @code{nil class}, that is @code{UndefinedObject}. Yet you saw that @code{#new} is not implemented there... let's try it: @display st> @t{^Object class superclass!} Class @end display Uh?!? Try to read it aloud: the @code{Object class} class inherits from the @code{Class} class. @code{Class} is the abstract superclass of all metaclasses, and provides the logic that allows you to create classes in the image. But it is not the termination point: @display st> @t{^Class superclass!} ClassDescription st> @t{^ClassDescription superclass!} Behavior st> @t{^Behavior superclass!} Object @end display Class is a subclass of other classes. @code{ClassDescription} is abstract; @code{Behavior} is concrete but lacks the methods and state that allow classes to have named instance variables, class comments and more. Its instances are called @emph{light-weight} classes because they don't have separate metaclasses, instead they all share @code{Behavior} itself as their metaclass. Evaluating @code{Behavior superclass} we have worked our way up to class Object again: Object is the superclass of all instances as well as all metaclasses. This complicated system is extremely powerful, and allows you to do very interesting things that you probably did without thinking about it---for example, using methods such as @code{#error:} or @code{#shouldNotImplement} in class methods. Now, one final question and one final step: what are metaclasses instances of? The question makes sense: if everything has a class, should not metaclasses have one? Evaluate the following: @display st> @t{meta := Set class} st> @t{0 to: 4 do: [ :i |} st> @t{ i timesRepeat: [ Transcript space ]} st> @t{ meta printNl} st> @t{ meta := meta class} st> @t{]} Set class Metaclass Metaclass class Metaclass Metaclass class 0 @end display If you send @code{#class} repeatedly, it seems that you end up in a loop made of class @code{Metaclass}@footnote{Which turns out to be another subclass of @code{ClassDescription}.} and its own metaclass, @code{Metaclass class}. It looks like class Metaclass is @i{an instance of an instance of itself}. To understand the role of @code{Metaclass}, it can be useful to know that the class creation is implemented there. Think about it. @itemize @bullet @item @code{Random class} implements creation and initialization of its instances' random number seed; analogously, @code{Metaclass class} implements creation and initialization of its instances, which are metaclasses. @item And @code{Metaclass} implements creation and initialization of its instances, which are classes (subclasses of @code{Class}). @end itemize The circle is closed. In the end, this mechanism implements a clean, elegant and (with some contemplation) understandable facility for self-definition of classes. In other words, it is what allows classes to talk about themselves, posing the foundation for the creation of browsers. @node Performance @subsection The truth of Smalltalk performance Everybody says Smalltalk is slow, yet this is not completely true for at least three reasons. First, most of the time in graphical applications is spent waiting for the user to ``do something'', and most of the time in scripting applications (which @gst{} is particularly well versed in) is spent in disk I/O; implementing a travelling salesman problem in Smalltalk would indeed be slow, but for most real applications you can indeed exchange performance for Smalltalk's power and development speed. Second, Smalltalk's automatic memory management is faster than C's manual one. Most C programs are sped up if you relink them with one of the garbage collecting systems available for C or C++. Third, even though very few Smalltalk virtual machines are as optimized as, say, the Self environment (which reaches half the speed of optimized C!), they do perform some optimizations on Smalltalk code which make them run many times faster than a naive bytecode interpreter. Peter Deutsch, who among other things invented the idea of a just-in-time compiler like those you are used to seeing for Java@footnote{And like the one that @gst{} includes as an experimental feature.}, once observed that implementing a language like Smalltalk efficiently requires the implementor to cheat... but that's okay as long as you don't get caught. That is, as long as you don't break the language semantics. Let's look at some of these optimizations. For certain frequently used 'special selectors', the compiler emits a send-special-selector bytecode instead of a send-message bytecode. Special selectors have one of three behaviors: @itemize @bullet @item A few selectors are assigned to special bytecode solely in order to save space. This is the case for @code{#do:} for example. @item Three selectors (@code{#at:}, @code{#at:put:}, @code{#size}) are assigned to special bytecodes because they are subject to a special caching optimization. These selectors often result in calling a virtual machine primitive, so @gst{} remembers which primitve was last called as the result of sending them. If we send @code{#at:} 100 times for the same class, the last 99 sends are directly mapped to the primitive, skipping the method lookup phase. @item For some pairs of receiver classes and special selectors, the interpreter never looks up the method in the class; instead it swiftly executes the same code which is tied to a particular primitive. Of course a special selector whose receiver or argument is not of the right class to make a no-lookup pair is looked up normally. @end itemize No-lookup methods do contain a primitive number specification, @code{}, but it is used only when the method is reached through a @code{#perform:@dots{}} message send. Since the method is not normally looked up, deleting the primitive name specification cannot in general prevent this primitive from running. No-lookup pairs are listed below: @multitable @columnfractions .35 .1 .55 @item @code{Integer}/@code{Integer} @* @code{Float}/@code{Integer} @* @code{Float}/@code{Float} @tab @ @* for @tab @ @* @code{+ - * = ~= > < >= <=} @item @code{Integer}/@code{Integer} @tab for @tab @code{// \\ bitOr: bitShift: bitAnd:} @item Any pair of objects @tab for @tab @code{== isNil notNil class} @item BlockClosure @tab for @tab @code{value value: blockCopy:}@footnote{You won't ever send this message in Smalltalk programs. The compiler uses it when compiling blocks.} @end multitable Other messages are open coded by the compiler. That is, there are no message sends for these messages---if the compiler sees blocks without temporaries and with the correct number of arguments at the right places, the compiler unwinds them using jump bytecodes, producing very efficient code. These are: @example to:by:do: if the second argument is an integer literal to:do: timesRepeat: and:, or: ifTrue:ifFalse:, ifFalse:ifTrue:, ifTrue:, ifFalse: whileTrue:, whileFalse: @end example Other minor optimizations are done. Some are done by a peephole optimizer which is ran on the compiled bytecodes. Or, for example, when @gst{} pushes a boolean value on the stack, it automatically checks whether the following bytecode is a jump (which is a common pattern resulting from most of the open-coded messages above) and combines the execution of the two bytecodes. All these snippets can be optimized this way: @example 1 to: 5 do: [ :i | @dots{} ] a < b and: [ @dots{} ] myObject isNil ifTrue: [ @dots{} ] @end example That's all. If you want to know more, look at the virtual machine's source code in @file{libgst/interp-bc.inl} and at the compiler in @file{libgst/comp.c}. @node And now @section Some final words The question is always how far to go in one document. At this point, you know how to create classes. You know how to use inheritance, polymorphism, and the basic storage management mechanisms of Smalltalk. You've also seen a sampling of Smalltalk's powerful classes. The rest of this chapter simply points out areas for further study; perhaps a newer version of this document might cover these in further chapters. @table @b @item Viewing the Smalltalk Source Code Lots of experience can be gained by looking at the source code for system methods; all of them are visible: data structure classes, the innards of the magic that makes classes be themselves objects and have a class, a compiler written in Smalltalk itself, the classes that implement the Smalltalk GUI and those that wrap sockets. @item Other Ways to Collect Objects We've seen Array, ByteArray, Dictionary, Set, and the various streams. You'll want to look at the Bag, OrderedCollection, and SortedCollection classes. For special purposes, you'll want to examine the CObject and CType hierarchies. @item Flow of Control @gst{} has support for non-preemptive multiple threads of execution. The state is embodied in a Process class object; you'll also want to look at the Semaphore and ProcessorScheduler class. @item Smalltalk Virtual Machine @gst{} is implemented as a virtual instruction set. By invoking @gst{} with the @code{-D} option, you can view the byte opcodes which are generated as files on the command line are loaded. Similarly, running @gst{} with @code{-E} will trace the execution of instructions in your methods. You can look at the @gst{} source to gain more information on the instruction set. With a few modifications, it is based on the set described in the canonical book from two of the original designers of Smalltalk: @i{Smalltalk-80: The Language and its Implementation}, by Adele Goldberg and David Robson. @item Where to get Help The Usenet @t{comp.lang.smalltalk} newsgroup is read by many people with a great deal of Smalltalk experience. There are several commercial Smalltalk implementations; you can buy support for these, though it isn't cheap. For the @gst{} system in particular, you can try the mailing list at: @example @mailto{help-smalltalk@@gnu.org} @end example No guarantees, but the subscribers will surely do their best! @end table @node The syntax @section A Simple Overview of Smalltalk Syntax Smalltalk's power comes from its treatment of objects. In this document, we've mostly avoided the issue of syntax by using strictly parenthesized expressions as needed. When this leads to code which is hard to read due to the density of parentheses, a knowledge of Smalltalk's syntax can let you simplify expressions. In general, if it was hard for you to tell how an expression would parse, it will be hard for the next person, too. The following presentation presents the grammar a couple of related elements at a time. We use an EBNF style of grammar. The form: @example [ @dots{} ] @end example @noindent means that ``@dots{}'' can occur zero or one times. @example [ @dots{} ]* @end example @noindent means zero or more; @example [ @dots{} ]+ @end example @noindent means one or more. @example @dots{} | @dots{} [ | @dots{} ]* @end example @noindent means that one of the variants must be chosen. Characters in double quotes refer to the literal characters. Most elements may be separated by white space; where this is not legal, the elements are presented without white space between them. @table @b @item @t{methods: ``!'' id [``class''] ``methodsFor:'' string ``!'' [method ``!'']+ ``!''} Methods are introduced by first naming a class (the id element), specifying ``class'' if you're adding class methods instead of instance methods, and sending a string argument to the @code{methodsFor:} message. Each method is terminated with an ``!''; two bangs in a row (with a space in the middle) signify the end of the new methods. @item @t{method: message [pragma] [temps] exprs} @itemx @t{message: id | binsel id | [keysel id]+} @itemx @t{pragma: ``<'' keymsg ``>''} @itemx @t{temps: ``|'' [id]* ``|''} A method definition starts out with a kind of template. The message to be handled is specified with the message names spelled out and identifiers in the place of arguments. A special kind of definition is the pragma; it has not been covered in this tutorial and it provides a way to mark a method specially as well as the interface to the underlying Smalltalk virtual machine. temps is the declaration of local variables. Finally, exprs (covered soon) is the actual code for implementing the method. @item @t{unit: id | literal | block | arrayconstructor | ``('' expr ``)''} @itemx @t{unaryexpr: unit [ id ]+} @itemx @t{primary: unit | unaryexpr} These are the ``building blocks'' of Smalltalk expressions. A unit represents a single Smalltalk value, with the highest syntactic precedence. A unaryexpr is simply a unit which receives a number of unary messages. A unaryexpr has the next highest precedence. A primary is simply a convenient left-hand-side name for one of the above. @item @t{exprs: [expr ``.'']* [[``^''] expr]} @itemx @t{expr: [id ``:='']* expr2} @* @itemx @t{expr2: primary | msgexpr [ ``;'' cascade ]*} A sequence of expressions is separated by dots and can end with a returned value (@code{^}). There can be leading assignments; unlike C, assignments apply only to simple variable names. An expression is either a primary (with highest precedence) or a more complex message. cascade does not apply to primary constructions, as they are too simple to require the construct. Since all primary construct are unary, you can just add more unary messages: @example 1234 printNl printNl printNl @end example @item @t{msgexpr: unaryexpr | binexpr | keyexpr} A complex message is either a unary message (which we have already covered), a binary message (@code{+}, @code{-}, and so forth), or a keyword message (@code{at:}, @code{new:}, @dots{}) Unary has the highest precedence, followed by binary, and keyword messages have the lowest precedence. Examine the two versions of the following messages. The second have had parentheses added to show the default precedence. @example myvar at: 2 + 3 put: 4 mybool ifTrue: [ ^ 2 / 4 roundup ] (myvar at: (2 + 3) put: (4)) (mybool ifTrue: ([ ^ (2 / (4 roundup)) ])) @end example @item @t{cascade: id | binmsg | keymsg} A cascade is used to direct further messages to the same object which was last used. The three types of messages ( id is how you send a unary message) can thus be sent. @item @t{binexpr: primary binmsg [ binmsg ]*} @itemx @t{binmsg: binsel primary} @itemx @t{binsel: binchar[binchar]} A binary message is sent to an object, which primary has identified. Each binary message is a binary selector, constructed from one or two characters, and an argument which is also provided by a primary. @example 1 + 2 - 3 / 4 @end example @noindent which parses as: @example (((1 + 2) - 3) / 4) @end example @item @t{keyexpr: keyexpr2 keymsg} @itemx @t{keyexpr2: binexpr | primary} @itemx @t{keymsg: [keysel keyw2]+} @itemx @t{keysel: id``:''} Keyword expressions are much like binary expressions, except that the selectors are made up of identifiers with a colon appended. Where the arguments to a binary function can only be from primary, the arguments to a keyword can be binary expressions or primary ones. This is because keywords have the lowest precedence. @item @t{block: ``['' [[``:'' id]* ``|'' ] [temps] exprs ``]''} A code block is square brackets around a collection of Smalltalk expressions. The leading ``: id'' part is for block arguments. Note that it is possible for a block to have temporary variables of its own. @item @t{arrayconstructor: ``@{'' exprs ``@}''} Not covered in this tutorial, this syntax allows to create arrays whose values are not literals, but are instead evaluated at run-time. Compare @code{#(a b)}, which results in an Array of two symbols @code{#a} and @code{#b}, to @code{@{a. b+c@}} which results in an Array whose two elements are the contents of variable @code{a} and the result of summing @code{c} to @code{b}. @item @t{literal: number | string | charconst | symconst | arrayconst | binding | eval} @itemx @t{arrayconst: ``#'' array | ``#'' bytearray} @itemx @t{bytearray: ``['' [number]* ``]''} @itemx @t{array: ``('' [literal | array | bytearray | arraysym | ]* ``)''} @itemx @t{number: [[dig]+ ``r''] [``-''] [alphanum]+ [``.'' [alphanum]+] [exp [``-''][dig]+].} @itemx @t{string: "'"[char]*"'"} @itemx @t{charconst: ``$''char} @itemx @t{symconst: ``#''symbol | ``#''string } @itemx @t{arraysym: [id | ``:'']*} @itemx @t{exp: ``d'' | ``e'' | ``q'' | ``s''} We have already shown the use of many of these constants. Although not covered in this tutorial, numbers can have a base specified at their front, and a trailing scientific notation. We have seen examples of character, string, and symbol constants. Array constants are simple enough; they would look like: @example a := #(1 2 'Hi' $x #Hello 4 16r3F) @end example There are also ByteArray constants, whose elements are constrained to be integers between 0 and 255; they would look like: @example a := #[1 2 34 16r8F 26r3H 253] @end example Finally, there are three types of floating-point constants with varying precision (the one with the @code{e} being the less precise, followed by @code{d} and @code{q}), and scaled-decimal constants for a special class which does exact computations but truncates comparisons to a given number of decimals. For example, @code{1.23s4} means ``the value @code{1.23}, with four significant decimal digits''. @item @t{binding: ``#@{'' [id ``.'']* id ``@}''} This syntax has not been used in the tutorial, and results in an Association literal (known as a @dfn{variable binding}) tied to the class that is named between braces. For example, @code{#@{Class@} value} is the same as @code{Class}. The dot syntax is required for supporting namespaces: @code{#@{Smalltalk.Class@}} is the same as @code{Smalltalk associationAt: #Class}, but is resolved at compile-time rather than at run-time. @item @t{symbol: id | binsel | keysel[keysel]*} Symbols are mostly used to represent the names of methods. Thus, they can hold simple identifiers, binary selectors, and keyword selectors: @example #hello #+ #at:put: @end example @itemx @t{eval: ``##('' [temps] exprs ``)''} This syntax also has not been used in the tutorial, and results in evaluating an arbitrarily complex expression at compile-time, and substituting the result: for example @code{##(Object allInstances size)} is the number of instances of @code{Object} held in the image @emph{at the time the method is compiled}. @item @t{id: letter[alphanum]*} @itemx @t{binchar: ``+'' | ``-'' | ``*'' | ``/'' | ``~'' | ``|'' | ``,'' |} @itemx @t{``<'' | ``>'' | ``='' | ``&'' | ``@@'' | ``?'' | ``\'' | ``%''} @itemx @t{alphanum: dig | letter} @itemx @t{letter: ``A''..``Z''} @itemx @t{dig: ``0''..``9''} These are the categories of characters and how they are combined at the most basic level. binchar simply lists the characters which can be combined to name a binary message. @end table smalltalk-3.2.5/doc/stamp-20000644000175000017500000000013612130456006012376 00000000000000@set UPDATED 8 April 2013 @set UPDATED-MONTH April 2013 @set EDITION 3.2.5 @set VERSION 3.2.5 smalltalk-3.2.5/doc/vers-gst.texi0000644000175000017500000000013712130455672013646 00000000000000@set UPDATED 23 March 2013 @set UPDATED-MONTH March 2013 @set EDITION 3.2.5 @set VERSION 3.2.5 smalltalk-3.2.5/doc/Makefile.in0000644000175000017500000011626412130455425013253 00000000000000# Makefile.in generated by automake 1.11.6 from Makefile.am. # @configure_input@ # Copyright (C) 1994, 1995, 1996, 1997, 1998, 1999, 2000, 2001, 2002, # 2003, 2004, 2005, 2006, 2007, 2008, 2009, 2010, 2011 Free Software # Foundation, Inc. # This Makefile.in is free software; the Free Software Foundation # gives unlimited permission to copy and/or distribute it, # with or without modifications, as long as this notice is preserved. # This program is distributed in the hope that it will be useful, # but WITHOUT ANY WARRANTY, to the extent permitted by law; without # even the implied warranty of MERCHANTABILITY or FITNESS FOR A # PARTICULAR PURPOSE. @SET_MAKE@ VPATH = @srcdir@ am__make_dryrun = \ { \ am__dry=no; \ case $$MAKEFLAGS in \ *\\[\ \ ]*) \ echo 'am--echo: ; @echo "AM" OK' | $(MAKE) -f - 2>/dev/null \ | grep '^AM OK$$' >/dev/null || am__dry=yes;; \ *) \ for am__flg in $$MAKEFLAGS; do \ case $$am__flg in \ *=*|--*) ;; \ *n*) am__dry=yes; break;; \ esac; \ done;; \ esac; \ test $$am__dry = yes; \ } pkgdatadir = $(datadir)/@PACKAGE@ pkgincludedir = $(includedir)/@PACKAGE@ pkglibdir = $(libdir)/@PACKAGE@ pkglibexecdir = $(libexecdir)/@PACKAGE@ am__cd = CDPATH="$${ZSH_VERSION+.}$(PATH_SEPARATOR)" && cd install_sh_DATA = $(install_sh) -c -m 644 install_sh_PROGRAM = $(install_sh) -c install_sh_SCRIPT = $(install_sh) -c INSTALL_HEADER = $(INSTALL_DATA) transform = $(program_transform_name) NORMAL_INSTALL = : PRE_INSTALL = : POST_INSTALL = : NORMAL_UNINSTALL = : PRE_UNINSTALL = : POST_UNINSTALL = : build_triplet = @build@ host_triplet = @host@ subdir = doc DIST_COMMON = $(dist_man_MANS) $(gst_TEXINFOS) $(gst_base_TEXINFOS) \ $(gst_libs_TEXINFOS) $(srcdir)/Makefile.am \ $(srcdir)/Makefile.in $(srcdir)/stamp-1 $(srcdir)/stamp-2 \ $(srcdir)/stamp-vti $(srcdir)/vers-base.texi \ $(srcdir)/vers-gst.texi $(srcdir)/vers-libs.texi ACLOCAL_M4 = $(top_srcdir)/aclocal.m4 am__aclocal_m4_deps = $(top_srcdir)/build-aux/bold.m4 \ $(top_srcdir)/build-aux/codeset.m4 \ $(top_srcdir)/build-aux/emacs-pkg.m4 \ $(top_srcdir)/build-aux/emacs-site-start.m4 \ $(top_srcdir)/build-aux/ext_goto.m4 \ $(top_srcdir)/build-aux/gawk.m4 $(top_srcdir)/build-aux/gcc.m4 \ $(top_srcdir)/build-aux/gl.m4 \ $(top_srcdir)/build-aux/glib-2.0.m4 \ $(top_srcdir)/build-aux/glut.m4 $(top_srcdir)/build-aux/gmp.m4 \ $(top_srcdir)/build-aux/gst-package.m4 \ $(top_srcdir)/build-aux/gtk-2.0.m4 \ $(top_srcdir)/build-aux/iconv.m4 \ $(top_srcdir)/build-aux/lib-ld.m4 \ $(top_srcdir)/build-aux/lib-link.m4 \ $(top_srcdir)/build-aux/lib-prefix.m4 \ $(top_srcdir)/build-aux/lib.m4 \ $(top_srcdir)/build-aux/libc-so-name.m4 \ $(top_srcdir)/build-aux/libtool.m4 \ $(top_srcdir)/build-aux/lightning.m4 \ $(top_srcdir)/build-aux/ln.m4 \ $(top_srcdir)/build-aux/localtime.m4 \ $(top_srcdir)/build-aux/lock.m4 \ $(top_srcdir)/build-aux/long-double.m4 \ $(top_srcdir)/build-aux/lrint.m4 \ $(top_srcdir)/build-aux/ltdl-gst.m4 \ $(top_srcdir)/build-aux/ltoptions.m4 \ $(top_srcdir)/build-aux/ltsugar.m4 \ $(top_srcdir)/build-aux/ltversion.m4 \ $(top_srcdir)/build-aux/lt~obsolete.m4 \ $(top_srcdir)/build-aux/modules.m4 \ $(top_srcdir)/build-aux/pkg.m4 $(top_srcdir)/build-aux/poll.m4 \ $(top_srcdir)/build-aux/readline.m4 \ $(top_srcdir)/build-aux/relocatable.m4 \ $(top_srcdir)/build-aux/setenv.m4 \ $(top_srcdir)/build-aux/snprintfv.m4 \ $(top_srcdir)/build-aux/sockets.m4 \ $(top_srcdir)/build-aux/sockpfaf.m4 \ $(top_srcdir)/build-aux/strtoul.m4 \ $(top_srcdir)/build-aux/sync-builtins.m4 \ $(top_srcdir)/build-aux/tcltk.m4 \ $(top_srcdir)/build-aux/version.m4 \ $(top_srcdir)/build-aux/vis-hidden.m4 \ $(top_srcdir)/build-aux/wine.m4 $(top_srcdir)/configure.ac am__configure_deps = $(am__aclocal_m4_deps) $(CONFIGURE_DEPENDENCIES) \ $(ACLOCAL_M4) mkinstalldirs = $(install_sh) -d CONFIG_HEADER = $(top_builddir)/config.h CONFIG_CLEAN_FILES = CONFIG_CLEAN_VPATH_FILES = SOURCES = DIST_SOURCES = INFO_DEPS = $(srcdir)/gst.info $(srcdir)/gst-base.info \ $(srcdir)/gst-libs.info TEXINFO_TEX = $(top_srcdir)/build-aux/texinfo.tex am__TEXINFO_TEX_DIR = $(top_srcdir)/build-aux DVIS = gst.dvi gst-base.dvi gst-libs.dvi PDFS = gst.pdf gst-base.pdf gst-libs.pdf PSS = gst.ps gst-base.ps gst-libs.ps HTMLS = gst.html gst-base.html gst-libs.html TEXINFOS = gst.texi gst-base.texi gst-libs.texi TEXI2PDF = $(TEXI2DVI) --pdf --batch MAKEINFOHTML = $(MAKEINFO) --html AM_MAKEINFOHTMLFLAGS = $(AM_MAKEINFOFLAGS) DVIPS = dvips am__can_run_installinfo = \ case $$AM_UPDATE_INFO_DIR in \ n|no|NO) false;; \ *) (install-info --version) >/dev/null 2>&1;; \ esac am__installdirs = "$(DESTDIR)$(infodir)" "$(DESTDIR)$(man1dir)" am__vpath_adj_setup = srcdirstrip=`echo "$(srcdir)" | sed 's|.|.|g'`; am__vpath_adj = case $$p in \ $(srcdir)/*) f=`echo "$$p" | sed "s|^$$srcdirstrip/||"`;; \ *) f=$$p;; \ esac; am__strip_dir = f=`echo $$p | sed -e 's|^.*/||'`; am__install_max = 40 am__nobase_strip_setup = \ srcdirstrip=`echo "$(srcdir)" | sed 's/[].[^$$\\*|]/\\\\&/g'` am__nobase_strip = \ for p in $$list; do echo "$$p"; done | sed -e "s|$$srcdirstrip/||" am__nobase_list = $(am__nobase_strip_setup); \ for p in $$list; do echo "$$p $$p"; done | \ sed "s| $$srcdirstrip/| |;"' / .*\//!s/ .*/ ./; s,\( .*\)/[^/]*$$,\1,' | \ $(AWK) 'BEGIN { files["."] = "" } { files[$$2] = files[$$2] " " $$1; \ if (++n[$$2] == $(am__install_max)) \ { print $$2, files[$$2]; n[$$2] = 0; files[$$2] = "" } } \ END { for (dir in files) print dir, files[dir] }' am__base_list = \ sed '$$!N;$$!N;$$!N;$$!N;$$!N;$$!N;$$!N;s/\n/ /g' | \ sed '$$!N;$$!N;$$!N;$$!N;s/\n/ /g' am__uninstall_files_from_dir = { \ test -z "$$files" \ || { test ! -d "$$dir" && test ! -f "$$dir" && test ! -r "$$dir"; } \ || { echo " ( cd '$$dir' && rm -f" $$files ")"; \ $(am__cd) "$$dir" && rm -f $$files; }; \ } man1dir = $(mandir)/man1 NROFF = nroff MANS = $(dist_man_MANS) DISTFILES = $(DIST_COMMON) $(DIST_SOURCES) $(TEXINFOS) $(EXTRA_DIST) ACLOCAL = @ACLOCAL@ ALLOCA = @ALLOCA@ ALL_PACKAGES = @ALL_PACKAGES@ AMTAR = @AMTAR@ AR = @AR@ AS = @AS@ ATK_CFLAGS = @ATK_CFLAGS@ ATK_LIBS = @ATK_LIBS@ AUTOCONF = @AUTOCONF@ AUTOHEADER = @AUTOHEADER@ AUTOM4TE = @AUTOM4TE@ AUTOMAKE = @AUTOMAKE@ AWK = @AWK@ BLOX_IMPLEMENTATION = @BLOX_IMPLEMENTATION@ BUILT_PACKAGES = @BUILT_PACKAGES@ CAIRO_CFLAGS = @CAIRO_CFLAGS@ CAIRO_LIBS = @CAIRO_LIBS@ CC = @CC@ CCDEPMODE = @CCDEPMODE@ CFLAGS = @CFLAGS@ CPP = @CPP@ CPPFLAGS = @CPPFLAGS@ CYGPATH_W = @CYGPATH_W@ DEFS = @DEFS@ DEPDIR = @DEPDIR@ DLLTOOL = @DLLTOOL@ DSYMUTIL = @DSYMUTIL@ DUMPBIN = @DUMPBIN@ ECHO_C = @ECHO_C@ ECHO_N = @ECHO_N@ ECHO_T = @ECHO_T@ EGREP = @EGREP@ EMACS = @EMACS@ EMACSLOADPATH = @EMACSLOADPATH@ EXEEXT = @EXEEXT@ FGREP = @FGREP@ GLIB_CFLAGS = @GLIB_CFLAGS@ GLIB_GENMARSHAL = @GLIB_GENMARSHAL@ GLIB_LIBS = @GLIB_LIBS@ GLIB_MKENUMS = @GLIB_MKENUMS@ GNUTLS_CFLAGS = @GNUTLS_CFLAGS@ GNUTLS_LIBS = @GNUTLS_LIBS@ GOBJECT_QUERY = @GOBJECT_QUERY@ GPERF = @GPERF@ GREP = @GREP@ GST_RUN = @GST_RUN@ GTHREAD_CFLAGS = @GTHREAD_CFLAGS@ GTHREAD_LIBS = @GTHREAD_LIBS@ GTK_CFLAGS = @GTK_CFLAGS@ GTK_LIBS = @GTK_LIBS@ ICON = @ICON@ INCFFI = @INCFFI@ INCLTDL = @INCLTDL@ INCSIGSEGV = @INCSIGSEGV@ INCSNPRINTFV = @INCSNPRINTFV@ INCTCLTK = @INCTCLTK@ INSTALL = @INSTALL@ INSTALL_DATA = @INSTALL_DATA@ INSTALL_INFO = @INSTALL_INFO@ INSTALL_PROGRAM = @INSTALL_PROGRAM@ INSTALL_SCRIPT = @INSTALL_SCRIPT@ INSTALL_STRIP_PROGRAM = @INSTALL_STRIP_PROGRAM@ LD = @LD@ LDFLAGS = @LDFLAGS@ LEX = @LEX@ LIBADD_DL = @LIBADD_DL@ LIBC_SO_DIR = @LIBC_SO_DIR@ LIBC_SO_NAME = @LIBC_SO_NAME@ LIBFFI = @LIBFFI@ LIBFFI_CFLAGS = @LIBFFI_CFLAGS@ LIBFFI_EXECUTABLE_LDFLAGS = @LIBFFI_EXECUTABLE_LDFLAGS@ LIBFFI_LIBS = @LIBFFI_LIBS@ LIBGLUT = @LIBGLUT@ LIBGMP = @LIBGMP@ LIBGST_CFLAGS = @LIBGST_CFLAGS@ LIBICONV = @LIBICONV@ LIBLTDL = @LIBLTDL@ LIBOBJS = @LIBOBJS@ LIBOPENGL = @LIBOPENGL@ LIBREADLINE = @LIBREADLINE@ LIBS = @LIBS@ LIBSIGSEGV = @LIBSIGSEGV@ LIBSNPRINTFV = @LIBSNPRINTFV@ LIBTCLTK = @LIBTCLTK@ LIBTHREAD = @LIBTHREAD@ LIBTOOL = @LIBTOOL@ LIPO = @LIPO@ LN = @LN@ LN_S = @LN_S@ LTALLOCA = @LTALLOCA@ LTLIBICONV = @LTLIBICONV@ LTLIBOBJS = @LTLIBOBJS@ MAINTAINER = @MAINTAINER@ MAKEINFO = @MAKEINFO@ MANIFEST_TOOL = @MANIFEST_TOOL@ MKDIR_P = @MKDIR_P@ MODULES = @MODULES@ NM = @NM@ NMEDIT = @NMEDIT@ OBJC = @OBJC@ OBJCDEPMODE = @OBJCDEPMODE@ OBJCFLAGS = @OBJCFLAGS@ OBJDUMP = @OBJDUMP@ OBJEXT = @OBJEXT@ OTOOL = @OTOOL@ OTOOL64 = @OTOOL64@ PACKAGE = @PACKAGE@ PACKAGE_BUGREPORT = @PACKAGE_BUGREPORT@ PACKAGE_DLOPEN_FLAGS = @PACKAGE_DLOPEN_FLAGS@ PACKAGE_NAME = @PACKAGE_NAME@ PACKAGE_STRING = @PACKAGE_STRING@ PACKAGE_TARNAME = @PACKAGE_TARNAME@ PACKAGE_URL = @PACKAGE_URL@ PACKAGE_VERSION = @PACKAGE_VERSION@ PANGO_CFLAGS = @PANGO_CFLAGS@ PANGO_LIBS = @PANGO_LIBS@ PATH_SEPARATOR = @PATH_SEPARATOR@ PKG_CONFIG = @PKG_CONFIG@ RANLIB = @RANLIB@ RELOCATABLE = @RELOCATABLE@ RELOC_CPPFLAGS = @RELOC_CPPFLAGS@ RELOC_LDFLAGS = @RELOC_LDFLAGS@ SDL_CFLAGS = @SDL_CFLAGS@ SDL_LIBS = @SDL_LIBS@ SED = @SED@ SET_MAKE = @SET_MAKE@ SHELL = @SHELL@ SOCKET_LIBS = @SOCKET_LIBS@ STRIP = @STRIP@ SYNC_CFLAGS = @SYNC_CFLAGS@ TCLSH = @TCLSH@ TIMEOUT = @TIMEOUT@ VERSION = @VERSION@ VERSION_INFO = @VERSION_INFO@ WINDRES = @WINDRES@ WINEWRAPPER = @WINEWRAPPER@ WINEWRAPPERDEP = @WINEWRAPPERDEP@ XMKMF = @XMKMF@ XZIP = @XZIP@ X_CFLAGS = @X_CFLAGS@ X_EXTRA_LIBS = @X_EXTRA_LIBS@ X_LIBS = @X_LIBS@ X_PRE_LIBS = @X_PRE_LIBS@ YACC = @YACC@ ZIP = @ZIP@ abs_builddir = @abs_builddir@ abs_srcdir = @abs_srcdir@ abs_top_builddir = @abs_top_builddir@ abs_top_srcdir = @abs_top_srcdir@ ac_ct_AR = @ac_ct_AR@ ac_ct_CC = @ac_ct_CC@ ac_ct_DUMPBIN = @ac_ct_DUMPBIN@ am__include = @am__include@ am__leading_dot = @am__leading_dot@ am__quote = @am__quote@ am__tar = @am__tar@ am__untar = @am__untar@ bindir = @bindir@ build = @build@ build_alias = @build_alias@ build_cpu = @build_cpu@ build_os = @build_os@ build_vendor = @build_vendor@ builddir = @builddir@ datadir = @datadir@ datarootdir = @datarootdir@ docdir = @docdir@ dvidir = @dvidir@ enable_mysql_tests = @enable_mysql_tests@ exec_prefix = @exec_prefix@ host = @host@ host_alias = @host_alias@ host_cpu = @host_cpu@ host_os = @host_os@ host_vendor = @host_vendor@ htmldir = @htmldir@ imagedir = @imagedir@ includedir = @includedir@ infodir = @infodir@ install_sh = @install_sh@ libdir = @libdir@ libexecdir = @libexecdir@ lispdir = @lispdir@ lispstartdir = @lispstartdir@ localedir = @localedir@ localstatedir = @localstatedir@ mandir = @mandir@ mkdir_p = @mkdir_p@ moduledir = @moduledir@ moduleexecdir = @moduleexecdir@ oldincludedir = @oldincludedir@ pdfdir = @pdfdir@ prefix = @prefix@ program_transform_name = @program_transform_name@ psdir = @psdir@ sbindir = @sbindir@ sharedstatedir = @sharedstatedir@ srcdir = @srcdir@ subdirs = @subdirs@ sysconfdir = @sysconfdir@ target_alias = @target_alias@ top_build_prefix = @top_build_prefix@ top_builddir = @top_builddir@ top_srcdir = @top_srcdir@ EXTRA_DIST = $(HTML_IMAGES) categories HTML_IMAGES = images/backon.png images/back.png images/blankon.png \ images/blank.png images/forwardon.png images/forward.png \ images/helpon.png images/help.png images/homeon.png \ images/home.png images/inactive.png images/indexon.png \ images/index.png images/nexton.png images/next.png \ images/prevon.png images/prev.png images/tocon.png \ images/toc.png images/upon.png images/up.png dist_man_MANS = gst.1 gst-load.1 gst-package.1 gst-sunit.1 gst-config.1 \ gst-convert.1 gst-doc.1 gst-profile.1 HELP2MAN = $(top_srcdir)/build-aux/help2man -p gst info_TEXINFOS = gst.texi gst-base.texi gst-libs.texi gst_TEXINFOS = tutorial.texi vers-gst.texi gst_libs_TEXINFOS = blox.texi sockets.texi i18n.texi complex.texi debug.texi \ dbi.texi zlib.texi using-xml.texi vers-libs.texi gst_base_TEXINFOS = classes.texi vers-base.texi TEXI2DVI = pool_size=750000 $(top_srcdir)/build-aux/texi2dvi --expand MOSTLYCLEANFILES = gst-libs.me gst-libs.mes gst-base.me gst-base.mes \ gst-libs.cl gst-libs.cls gst-base.cl gst-base.cls \ gst-libs.sl gst-libs.sls gst-base.sl gst-base.sls GST_TOOL = $(top_builddir)/gst-tool$(EXEEXT) GST_TOOL_ARGS = -I $(top_builddir)/gst.im --kernel-dir $(top_srcdir)/kernel GST_DOC = $(GST_TOOL) gst-doc $(GST_TOOL_ARGS) GST_PACKAGE = $(GST_TOOL) gst-package $(GST_TOOL_ARGS) #################################################### #################################################### PUBLISHED_CLASSES = Smalltalk.* SystemExceptions.* NetClients.* VFS.* all: all-am .SUFFIXES: .SUFFIXES: .dvi .html .info .pdf .ps .texi $(srcdir)/Makefile.in: $(srcdir)/Makefile.am $(am__configure_deps) @for dep in $?; do \ case '$(am__configure_deps)' in \ *$$dep*) \ ( cd $(top_builddir) && $(MAKE) $(AM_MAKEFLAGS) am--refresh ) \ && { if test -f $@; then exit 0; else break; fi; }; \ exit 1;; \ esac; \ done; \ echo ' cd $(top_srcdir) && $(AUTOMAKE) --gnu doc/Makefile'; \ $(am__cd) $(top_srcdir) && \ $(AUTOMAKE) --gnu doc/Makefile .PRECIOUS: Makefile Makefile: $(srcdir)/Makefile.in $(top_builddir)/config.status @case '$?' in \ *config.status*) \ cd $(top_builddir) && $(MAKE) $(AM_MAKEFLAGS) am--refresh;; \ *) \ echo ' cd $(top_builddir) && $(SHELL) ./config.status $(subdir)/$@ $(am__depfiles_maybe)'; \ cd $(top_builddir) && $(SHELL) ./config.status $(subdir)/$@ $(am__depfiles_maybe);; \ esac; $(top_builddir)/config.status: $(top_srcdir)/configure $(CONFIG_STATUS_DEPENDENCIES) cd $(top_builddir) && $(MAKE) $(AM_MAKEFLAGS) am--refresh $(top_srcdir)/configure: $(am__configure_deps) cd $(top_builddir) && $(MAKE) $(AM_MAKEFLAGS) am--refresh $(ACLOCAL_M4): $(am__aclocal_m4_deps) cd $(top_builddir) && $(MAKE) $(AM_MAKEFLAGS) am--refresh $(am__aclocal_m4_deps): mostlyclean-libtool: -rm -f *.lo clean-libtool: -rm -rf .libs _libs .texi.info: restore=: && backupdir="$(am__leading_dot)am$$$$" && \ am__cwd=`pwd` && $(am__cd) $(srcdir) && \ rm -rf $$backupdir && mkdir $$backupdir && \ if ($(MAKEINFO) --version) >/dev/null 2>&1; then \ for f in $@ $@-[0-9] $@-[0-9][0-9] $(@:.info=).i[0-9] $(@:.info=).i[0-9][0-9]; do \ if test -f $$f; then mv $$f $$backupdir; restore=mv; else :; fi; \ done; \ else :; fi && \ cd "$$am__cwd"; \ if $(MAKEINFO) $(AM_MAKEINFOFLAGS) $(MAKEINFOFLAGS) -I $(srcdir) \ -o $@ $<; \ then \ rc=0; \ $(am__cd) $(srcdir); \ else \ rc=$$?; \ $(am__cd) $(srcdir) && \ $$restore $$backupdir/* `echo "./$@" | sed 's|[^/]*$$||'`; \ fi; \ rm -rf $$backupdir; exit $$rc .texi.dvi: TEXINPUTS="$(am__TEXINFO_TEX_DIR)$(PATH_SEPARATOR)$$TEXINPUTS" \ MAKEINFO='$(MAKEINFO) $(AM_MAKEINFOFLAGS) $(MAKEINFOFLAGS) -I $(srcdir)' \ $(TEXI2DVI) $< .texi.pdf: TEXINPUTS="$(am__TEXINFO_TEX_DIR)$(PATH_SEPARATOR)$$TEXINPUTS" \ MAKEINFO='$(MAKEINFO) $(AM_MAKEINFOFLAGS) $(MAKEINFOFLAGS) -I $(srcdir)' \ $(TEXI2PDF) $< .texi.html: rm -rf $(@:.html=.htp) if $(MAKEINFOHTML) $(AM_MAKEINFOHTMLFLAGS) $(MAKEINFOFLAGS) -I $(srcdir) \ -o $(@:.html=.htp) $<; \ then \ rm -rf $@; \ if test ! -d $(@:.html=.htp) && test -d $(@:.html=); then \ mv $(@:.html=) $@; else mv $(@:.html=.htp) $@; fi; \ else \ if test ! -d $(@:.html=.htp) && test -d $(@:.html=); then \ rm -rf $(@:.html=); else rm -Rf $(@:.html=.htp) $@; fi; \ exit 1; \ fi $(srcdir)/gst.info: gst.texi $(srcdir)/vers-gst.texi $(gst_TEXINFOS) gst.dvi: gst.texi $(srcdir)/vers-gst.texi $(gst_TEXINFOS) gst.pdf: gst.texi $(srcdir)/vers-gst.texi $(gst_TEXINFOS) gst.html: gst.texi $(srcdir)/vers-gst.texi $(gst_TEXINFOS) $(srcdir)/vers-gst.texi: $(srcdir)/stamp-vti $(srcdir)/stamp-vti: gst.texi $(top_srcdir)/configure @(dir=.; test -f ./gst.texi || dir=$(srcdir); \ set `$(SHELL) $(top_srcdir)/build-aux/mdate-sh $$dir/gst.texi`; \ echo "@set UPDATED $$1 $$2 $$3"; \ echo "@set UPDATED-MONTH $$2 $$3"; \ echo "@set EDITION $(VERSION)"; \ echo "@set VERSION $(VERSION)") > vti.tmp @cmp -s vti.tmp $(srcdir)/vers-gst.texi \ || (echo "Updating $(srcdir)/vers-gst.texi"; \ cp vti.tmp $(srcdir)/vers-gst.texi) -@rm -f vti.tmp @cp $(srcdir)/vers-gst.texi $@ mostlyclean-vti: -rm -f vti.tmp maintainer-clean-vti: -rm -f $(srcdir)/stamp-vti $(srcdir)/vers-gst.texi $(srcdir)/gst-base.info: gst-base.texi $(srcdir)/vers-base.texi $(gst_base_TEXINFOS) gst-base.dvi: gst-base.texi $(srcdir)/vers-base.texi $(gst_base_TEXINFOS) gst-base.pdf: gst-base.texi $(srcdir)/vers-base.texi $(gst_base_TEXINFOS) gst-base.html: gst-base.texi $(srcdir)/vers-base.texi $(gst_base_TEXINFOS) $(srcdir)/vers-base.texi: $(srcdir)/stamp-1 $(srcdir)/stamp-1: gst-base.texi $(top_srcdir)/configure @(dir=.; test -f ./gst-base.texi || dir=$(srcdir); \ set `$(SHELL) $(top_srcdir)/build-aux/mdate-sh $$dir/gst-base.texi`; \ echo "@set UPDATED $$1 $$2 $$3"; \ echo "@set UPDATED-MONTH $$2 $$3"; \ echo "@set EDITION $(VERSION)"; \ echo "@set VERSION $(VERSION)") > 1.tmp @cmp -s 1.tmp $(srcdir)/vers-base.texi \ || (echo "Updating $(srcdir)/vers-base.texi"; \ cp 1.tmp $(srcdir)/vers-base.texi) -@rm -f 1.tmp @cp $(srcdir)/vers-base.texi $@ mostlyclean-1: -rm -f 1.tmp maintainer-clean-1: -rm -f $(srcdir)/stamp-1 $(srcdir)/vers-base.texi $(srcdir)/gst-libs.info: gst-libs.texi $(srcdir)/vers-libs.texi $(gst_libs_TEXINFOS) gst-libs.dvi: gst-libs.texi $(srcdir)/vers-libs.texi $(gst_libs_TEXINFOS) gst-libs.pdf: gst-libs.texi $(srcdir)/vers-libs.texi $(gst_libs_TEXINFOS) gst-libs.html: gst-libs.texi $(srcdir)/vers-libs.texi $(gst_libs_TEXINFOS) $(srcdir)/vers-libs.texi: $(srcdir)/stamp-2 $(srcdir)/stamp-2: gst-libs.texi $(top_srcdir)/configure @(dir=.; test -f ./gst-libs.texi || dir=$(srcdir); \ set `$(SHELL) $(top_srcdir)/build-aux/mdate-sh $$dir/gst-libs.texi`; \ echo "@set UPDATED $$1 $$2 $$3"; \ echo "@set UPDATED-MONTH $$2 $$3"; \ echo "@set EDITION $(VERSION)"; \ echo "@set VERSION $(VERSION)") > 2.tmp @cmp -s 2.tmp $(srcdir)/vers-libs.texi \ || (echo "Updating $(srcdir)/vers-libs.texi"; \ cp 2.tmp $(srcdir)/vers-libs.texi) -@rm -f 2.tmp @cp $(srcdir)/vers-libs.texi $@ mostlyclean-2: -rm -f 2.tmp maintainer-clean-2: -rm -f $(srcdir)/stamp-2 $(srcdir)/vers-libs.texi .dvi.ps: TEXINPUTS="$(am__TEXINFO_TEX_DIR)$(PATH_SEPARATOR)$$TEXINPUTS" \ $(DVIPS) -o $@ $< uninstall-dvi-am: @$(NORMAL_UNINSTALL) @list='$(DVIS)'; test -n "$(dvidir)" || list=; \ for p in $$list; do \ $(am__strip_dir) \ echo " rm -f '$(DESTDIR)$(dvidir)/$$f'"; \ rm -f "$(DESTDIR)$(dvidir)/$$f"; \ done uninstall-html-am: @$(NORMAL_UNINSTALL) @list='$(HTMLS)'; test -n "$(htmldir)" || list=; \ for p in $$list; do \ $(am__strip_dir) \ echo " rm -rf '$(DESTDIR)$(htmldir)/$$f'"; \ rm -rf "$(DESTDIR)$(htmldir)/$$f"; \ done uninstall-info-am: @$(PRE_UNINSTALL) @if test -d '$(DESTDIR)$(infodir)' && $(am__can_run_installinfo); then \ list='$(INFO_DEPS)'; \ for file in $$list; do \ relfile=`echo "$$file" | sed 's|^.*/||'`; \ echo " install-info --info-dir='$(DESTDIR)$(infodir)' --remove '$(DESTDIR)$(infodir)/$$relfile'"; \ if install-info --info-dir="$(DESTDIR)$(infodir)" --remove "$(DESTDIR)$(infodir)/$$relfile"; \ then :; else test ! -f "$(DESTDIR)$(infodir)/$$relfile" || exit 1; fi; \ done; \ else :; fi @$(NORMAL_UNINSTALL) @list='$(INFO_DEPS)'; \ for file in $$list; do \ relfile=`echo "$$file" | sed 's|^.*/||'`; \ relfile_i=`echo "$$relfile" | sed 's|\.info$$||;s|$$|.i|'`; \ (if test -d "$(DESTDIR)$(infodir)" && cd "$(DESTDIR)$(infodir)"; then \ echo " cd '$(DESTDIR)$(infodir)' && rm -f $$relfile $$relfile-[0-9] $$relfile-[0-9][0-9] $$relfile_i[0-9] $$relfile_i[0-9][0-9]"; \ rm -f $$relfile $$relfile-[0-9] $$relfile-[0-9][0-9] $$relfile_i[0-9] $$relfile_i[0-9][0-9]; \ else :; fi); \ done uninstall-pdf-am: @$(NORMAL_UNINSTALL) @list='$(PDFS)'; test -n "$(pdfdir)" || list=; \ for p in $$list; do \ $(am__strip_dir) \ echo " rm -f '$(DESTDIR)$(pdfdir)/$$f'"; \ rm -f "$(DESTDIR)$(pdfdir)/$$f"; \ done uninstall-ps-am: @$(NORMAL_UNINSTALL) @list='$(PSS)'; test -n "$(psdir)" || list=; \ for p in $$list; do \ $(am__strip_dir) \ echo " rm -f '$(DESTDIR)$(psdir)/$$f'"; \ rm -f "$(DESTDIR)$(psdir)/$$f"; \ done dist-info: $(INFO_DEPS) @srcdirstrip=`echo "$(srcdir)" | sed 's|.|.|g'`; \ list='$(INFO_DEPS)'; \ for base in $$list; do \ case $$base in \ $(srcdir)/*) base=`echo "$$base" | sed "s|^$$srcdirstrip/||"`;; \ esac; \ if test -f $$base; then d=.; else d=$(srcdir); fi; \ base_i=`echo "$$base" | sed 's|\.info$$||;s|$$|.i|'`; \ for file in $$d/$$base $$d/$$base-[0-9] $$d/$$base-[0-9][0-9] $$d/$$base_i[0-9] $$d/$$base_i[0-9][0-9]; do \ if test -f $$file; then \ relfile=`expr "$$file" : "$$d/\(.*\)"`; \ test -f "$(distdir)/$$relfile" || \ cp -p $$file "$(distdir)/$$relfile"; \ else :; fi; \ done; \ done mostlyclean-aminfo: -rm -rf gst.aux gst.cp gst.cps gst.fn gst.fns gst.ky gst.kys gst.log gst.pg \ gst.pgs gst.tmp gst.toc gst.tp gst.tps gst.vr gst.vrs \ gst-base.aux gst-base.cp gst-base.cps gst-base.fn \ gst-base.fns gst-base.ky gst-base.kys gst-base.log \ gst-base.pg gst-base.pgs gst-base.tmp gst-base.toc \ gst-base.tp gst-base.tps gst-base.vr gst-base.vrs \ gst-libs.aux gst-libs.cp gst-libs.cps gst-libs.fn \ gst-libs.fns gst-libs.ky gst-libs.kys gst-libs.log \ gst-libs.pg gst-libs.pgs gst-libs.tmp gst-libs.toc \ gst-libs.tp gst-libs.tps gst-libs.vr gst-libs.vrs clean-aminfo: -test -z "gst.dvi gst.pdf gst.ps gst.html gst-base.dvi gst-base.pdf gst-base.ps \ gst-base.html gst-libs.dvi gst-libs.pdf gst-libs.ps \ gst-libs.html" \ || rm -rf gst.dvi gst.pdf gst.ps gst.html gst-base.dvi gst-base.pdf gst-base.ps \ gst-base.html gst-libs.dvi gst-libs.pdf gst-libs.ps \ gst-libs.html maintainer-clean-aminfo: @list='$(INFO_DEPS)'; for i in $$list; do \ i_i=`echo "$$i" | sed 's|\.info$$||;s|$$|.i|'`; \ echo " rm -f $$i $$i-[0-9] $$i-[0-9][0-9] $$i_i[0-9] $$i_i[0-9][0-9]"; \ rm -f $$i $$i-[0-9] $$i-[0-9][0-9] $$i_i[0-9] $$i_i[0-9][0-9]; \ done install-man1: $(dist_man_MANS) @$(NORMAL_INSTALL) @list1=''; \ list2='$(dist_man_MANS)'; \ test -n "$(man1dir)" \ && test -n "`echo $$list1$$list2`" \ || exit 0; \ echo " $(MKDIR_P) '$(DESTDIR)$(man1dir)'"; \ $(MKDIR_P) "$(DESTDIR)$(man1dir)" || exit 1; \ { for i in $$list1; do echo "$$i"; done; \ if test -n "$$list2"; then \ for i in $$list2; do echo "$$i"; done \ | sed -n '/\.1[a-z]*$$/p'; \ fi; \ } | while read p; do \ if test -f $$p; then d=; else d="$(srcdir)/"; fi; \ echo "$$d$$p"; echo "$$p"; \ done | \ sed -e 'n;s,.*/,,;p;h;s,.*\.,,;s,^[^1][0-9a-z]*$$,1,;x' \ -e 's,\.[0-9a-z]*$$,,;$(transform);G;s,\n,.,' | \ sed 'N;N;s,\n, ,g' | { \ list=; while read file base inst; do \ if test "$$base" = "$$inst"; then list="$$list $$file"; else \ echo " $(INSTALL_DATA) '$$file' '$(DESTDIR)$(man1dir)/$$inst'"; \ $(INSTALL_DATA) "$$file" "$(DESTDIR)$(man1dir)/$$inst" || exit $$?; \ fi; \ done; \ for i in $$list; do echo "$$i"; done | $(am__base_list) | \ while read files; do \ test -z "$$files" || { \ echo " $(INSTALL_DATA) $$files '$(DESTDIR)$(man1dir)'"; \ $(INSTALL_DATA) $$files "$(DESTDIR)$(man1dir)" || exit $$?; }; \ done; } uninstall-man1: @$(NORMAL_UNINSTALL) @list=''; test -n "$(man1dir)" || exit 0; \ files=`{ for i in $$list; do echo "$$i"; done; \ l2='$(dist_man_MANS)'; for i in $$l2; do echo "$$i"; done | \ sed -n '/\.1[a-z]*$$/p'; \ } | sed -e 's,.*/,,;h;s,.*\.,,;s,^[^1][0-9a-z]*$$,1,;x' \ -e 's,\.[0-9a-z]*$$,,;$(transform);G;s,\n,.,'`; \ dir='$(DESTDIR)$(man1dir)'; $(am__uninstall_files_from_dir) tags: TAGS TAGS: ctags: CTAGS CTAGS: distdir: $(DISTFILES) @list='$(MANS)'; if test -n "$$list"; then \ list=`for p in $$list; do \ if test -f $$p; then d=; else d="$(srcdir)/"; fi; \ if test -f "$$d$$p"; then echo "$$d$$p"; else :; fi; done`; \ if test -n "$$list" && \ grep 'ab help2man is required to generate this page' $$list >/dev/null; then \ echo "error: found man pages containing the \`missing help2man' replacement text:" >&2; \ grep -l 'ab help2man is required to generate this page' $$list | sed 's/^/ /' >&2; \ echo " to fix them, install help2man, remove and regenerate the man pages;" >&2; \ echo " typically \`make maintainer-clean' will remove them" >&2; \ exit 1; \ else :; fi; \ else :; fi @srcdirstrip=`echo "$(srcdir)" | sed 's/[].[^$$\\*]/\\\\&/g'`; \ topsrcdirstrip=`echo "$(top_srcdir)" | sed 's/[].[^$$\\*]/\\\\&/g'`; \ list='$(DISTFILES)'; \ dist_files=`for file in $$list; do echo $$file; done | \ sed -e "s|^$$srcdirstrip/||;t" \ -e "s|^$$topsrcdirstrip/|$(top_builddir)/|;t"`; \ case $$dist_files in \ */*) $(MKDIR_P) `echo "$$dist_files" | \ sed '/\//!d;s|^|$(distdir)/|;s,/[^/]*$$,,' | \ sort -u` ;; \ esac; \ for file in $$dist_files; do \ if test -f $$file || test -d $$file; then d=.; else d=$(srcdir); fi; \ if test -d $$d/$$file; then \ dir=`echo "/$$file" | sed -e 's,/[^/]*$$,,'`; \ if test -d "$(distdir)/$$file"; then \ find "$(distdir)/$$file" -type d ! -perm -700 -exec chmod u+rwx {} \;; \ fi; \ if test -d $(srcdir)/$$file && test $$d != $(srcdir); then \ cp -fpR $(srcdir)/$$file "$(distdir)$$dir" || exit 1; \ find "$(distdir)/$$file" -type d ! -perm -700 -exec chmod u+rwx {} \;; \ fi; \ cp -fpR $$d/$$file "$(distdir)$$dir" || exit 1; \ else \ test -f "$(distdir)/$$file" \ || cp -p $$d/$$file "$(distdir)/$$file" \ || exit 1; \ fi; \ done $(MAKE) $(AM_MAKEFLAGS) \ top_distdir="$(top_distdir)" distdir="$(distdir)" \ dist-info check-am: all-am check: check-am all-am: Makefile $(INFO_DEPS) $(MANS) installdirs: for dir in "$(DESTDIR)$(infodir)" "$(DESTDIR)$(man1dir)"; do \ test -z "$$dir" || $(MKDIR_P) "$$dir"; \ done install: install-am install-exec: install-exec-am install-data: install-data-am uninstall: uninstall-am install-am: all-am @$(MAKE) $(AM_MAKEFLAGS) install-exec-am install-data-am installcheck: installcheck-am install-strip: if test -z '$(STRIP)'; then \ $(MAKE) $(AM_MAKEFLAGS) INSTALL_PROGRAM="$(INSTALL_STRIP_PROGRAM)" \ install_sh_PROGRAM="$(INSTALL_STRIP_PROGRAM)" INSTALL_STRIP_FLAG=-s \ install; \ else \ $(MAKE) $(AM_MAKEFLAGS) INSTALL_PROGRAM="$(INSTALL_STRIP_PROGRAM)" \ install_sh_PROGRAM="$(INSTALL_STRIP_PROGRAM)" INSTALL_STRIP_FLAG=-s \ "INSTALL_PROGRAM_ENV=STRIPPROG='$(STRIP)'" install; \ fi mostlyclean-generic: -test -z "$(MOSTLYCLEANFILES)" || rm -f $(MOSTLYCLEANFILES) clean-generic: distclean-generic: -test -z "$(CONFIG_CLEAN_FILES)" || rm -f $(CONFIG_CLEAN_FILES) -test . = "$(srcdir)" || test -z "$(CONFIG_CLEAN_VPATH_FILES)" || rm -f $(CONFIG_CLEAN_VPATH_FILES) maintainer-clean-generic: @echo "This command is intended for maintainers to use" @echo "it deletes files that may require special tools to rebuild." clean: clean-am clean-am: clean-aminfo clean-generic clean-libtool clean-local \ mostlyclean-am distclean: distclean-am -rm -f Makefile distclean-am: clean-am distclean-generic dvi: dvi-am dvi-am: $(DVIS) html-am: $(HTMLS) info: info-am info-am: $(INFO_DEPS) install-data-am: install-data-local install-info-am install-man install-dvi: install-dvi-am install-dvi-am: $(DVIS) @$(NORMAL_INSTALL) @list='$(DVIS)'; test -n "$(dvidir)" || list=; \ if test -n "$$list"; then \ echo " $(MKDIR_P) '$(DESTDIR)$(dvidir)'"; \ $(MKDIR_P) "$(DESTDIR)$(dvidir)" || exit 1; \ fi; \ for p in $$list; do \ if test -f "$$p"; then d=; else d="$(srcdir)/"; fi; \ echo "$$d$$p"; \ done | $(am__base_list) | \ while read files; do \ echo " $(INSTALL_DATA) $$files '$(DESTDIR)$(dvidir)'"; \ $(INSTALL_DATA) $$files "$(DESTDIR)$(dvidir)" || exit $$?; \ done install-exec-am: install-html: install-html-am install-html-am: $(HTMLS) @$(NORMAL_INSTALL) @list='$(HTMLS)'; list2=; test -n "$(htmldir)" || list=; \ if test -n "$$list"; then \ echo " $(MKDIR_P) '$(DESTDIR)$(htmldir)'"; \ $(MKDIR_P) "$(DESTDIR)$(htmldir)" || exit 1; \ fi; \ for p in $$list; do \ if test -f "$$p" || test -d "$$p"; then d=; else d="$(srcdir)/"; fi; \ $(am__strip_dir) \ d2=$$d$$p; \ if test -d "$$d2"; then \ echo " $(MKDIR_P) '$(DESTDIR)$(htmldir)/$$f'"; \ $(MKDIR_P) "$(DESTDIR)$(htmldir)/$$f" || exit 1; \ echo " $(INSTALL_DATA) '$$d2'/* '$(DESTDIR)$(htmldir)/$$f'"; \ $(INSTALL_DATA) "$$d2"/* "$(DESTDIR)$(htmldir)/$$f" || exit $$?; \ else \ list2="$$list2 $$d2"; \ fi; \ done; \ test -z "$$list2" || { echo "$$list2" | $(am__base_list) | \ while read files; do \ echo " $(INSTALL_DATA) $$files '$(DESTDIR)$(htmldir)'"; \ $(INSTALL_DATA) $$files "$(DESTDIR)$(htmldir)" || exit $$?; \ done; } install-info: install-info-am install-info-am: $(INFO_DEPS) @$(NORMAL_INSTALL) @srcdirstrip=`echo "$(srcdir)" | sed 's|.|.|g'`; \ list='$(INFO_DEPS)'; test -n "$(infodir)" || list=; \ if test -n "$$list"; then \ echo " $(MKDIR_P) '$(DESTDIR)$(infodir)'"; \ $(MKDIR_P) "$(DESTDIR)$(infodir)" || exit 1; \ fi; \ for file in $$list; do \ case $$file in \ $(srcdir)/*) file=`echo "$$file" | sed "s|^$$srcdirstrip/||"`;; \ esac; \ if test -f $$file; then d=.; else d=$(srcdir); fi; \ file_i=`echo "$$file" | sed 's|\.info$$||;s|$$|.i|'`; \ for ifile in $$d/$$file $$d/$$file-[0-9] $$d/$$file-[0-9][0-9] \ $$d/$$file_i[0-9] $$d/$$file_i[0-9][0-9] ; do \ if test -f $$ifile; then \ echo "$$ifile"; \ else : ; fi; \ done; \ done | $(am__base_list) | \ while read files; do \ echo " $(INSTALL_DATA) $$files '$(DESTDIR)$(infodir)'"; \ $(INSTALL_DATA) $$files "$(DESTDIR)$(infodir)" || exit $$?; done @$(POST_INSTALL) @if $(am__can_run_installinfo); then \ list='$(INFO_DEPS)'; test -n "$(infodir)" || list=; \ for file in $$list; do \ relfile=`echo "$$file" | sed 's|^.*/||'`; \ echo " install-info --info-dir='$(DESTDIR)$(infodir)' '$(DESTDIR)$(infodir)/$$relfile'";\ install-info --info-dir="$(DESTDIR)$(infodir)" "$(DESTDIR)$(infodir)/$$relfile" || :;\ done; \ else : ; fi install-man: install-man1 install-pdf: install-pdf-am install-pdf-am: $(PDFS) @$(NORMAL_INSTALL) @list='$(PDFS)'; test -n "$(pdfdir)" || list=; \ if test -n "$$list"; then \ echo " $(MKDIR_P) '$(DESTDIR)$(pdfdir)'"; \ $(MKDIR_P) "$(DESTDIR)$(pdfdir)" || exit 1; \ fi; \ for p in $$list; do \ if test -f "$$p"; then d=; else d="$(srcdir)/"; fi; \ echo "$$d$$p"; \ done | $(am__base_list) | \ while read files; do \ echo " $(INSTALL_DATA) $$files '$(DESTDIR)$(pdfdir)'"; \ $(INSTALL_DATA) $$files "$(DESTDIR)$(pdfdir)" || exit $$?; done install-ps: install-ps-am install-ps-am: $(PSS) @$(NORMAL_INSTALL) @list='$(PSS)'; test -n "$(psdir)" || list=; \ if test -n "$$list"; then \ echo " $(MKDIR_P) '$(DESTDIR)$(psdir)'"; \ $(MKDIR_P) "$(DESTDIR)$(psdir)" || exit 1; \ fi; \ for p in $$list; do \ if test -f "$$p"; then d=; else d="$(srcdir)/"; fi; \ echo "$$d$$p"; \ done | $(am__base_list) | \ while read files; do \ echo " $(INSTALL_DATA) $$files '$(DESTDIR)$(psdir)'"; \ $(INSTALL_DATA) $$files "$(DESTDIR)$(psdir)" || exit $$?; done installcheck-am: maintainer-clean: maintainer-clean-am -rm -f Makefile maintainer-clean-am: distclean-am maintainer-clean-1 \ maintainer-clean-2 maintainer-clean-aminfo \ maintainer-clean-generic maintainer-clean-vti mostlyclean: mostlyclean-am mostlyclean-am: mostlyclean-1 mostlyclean-2 mostlyclean-aminfo \ mostlyclean-generic mostlyclean-libtool mostlyclean-vti pdf: pdf-am pdf-am: $(PDFS) ps: ps-am ps-am: $(PSS) uninstall-am: uninstall-dvi-am uninstall-html-am uninstall-info-am \ uninstall-local uninstall-man uninstall-pdf-am uninstall-ps-am uninstall-man: uninstall-man1 .MAKE: install-am install-strip .PHONY: all all-am check check-am clean clean-aminfo clean-generic \ clean-libtool clean-local dist-info distclean \ distclean-generic distclean-libtool distdir dvi dvi-am html \ html-am info info-am install install-am install-data \ install-data-am install-data-local install-dvi install-dvi-am \ install-exec install-exec-am install-html install-html-am \ install-info install-info-am install-man install-man1 \ install-pdf install-pdf-am install-ps install-ps-am \ install-strip installcheck installcheck-am installdirs \ maintainer-clean maintainer-clean-1 maintainer-clean-2 \ maintainer-clean-aminfo maintainer-clean-generic \ maintainer-clean-vti mostlyclean mostlyclean-1 mostlyclean-2 \ mostlyclean-aminfo mostlyclean-generic mostlyclean-libtool \ mostlyclean-vti pdf pdf-am ps ps-am uninstall uninstall-am \ uninstall-dvi-am uninstall-html-am uninstall-info-am \ uninstall-local uninstall-man uninstall-man1 uninstall-pdf-am \ uninstall-ps-am #################################################### #################################################### $(srcdir)/gst-package.1: $(top_srcdir)/scripts/Package.st $(top_srcdir)/configure.ac $(HELP2MAN) \ --name "create and install GNU Smalltalk .star package files" \ "$(GST_TOOL) gst-package $(GST_TOOL_ARGS)" >$@ $(srcdir)/gst-convert.1: $(top_srcdir)/scripts/Load.st $(top_srcdir)/configure.ac $(HELP2MAN) \ --name "Smalltalk syntax converter and beautifier" \ "$(GST_TOOL) gst-convert $(GST_TOOL_ARGS)" >$@ $(srcdir)/gst-load.1: $(top_srcdir)/scripts/Load.st $(top_srcdir)/configure.ac $(HELP2MAN) \ --name "test and load packages into a GNU Smalltalk image" \ "$(GST_TOOL) gst-load $(GST_TOOL_ARGS)" >$@ $(srcdir)/gst-sunit.1: $(top_srcdir)/scripts/Test.st $(top_srcdir)/configure.ac $(HELP2MAN) \ --name "unit testing tool for GNU Smalltalk" \ "$(GST_TOOL) gst-sunit $(GST_TOOL_ARGS)" >$@ $(srcdir)/gst-doc.1: $(top_srcdir)/scripts/GenDoc.st $(top_srcdir)/configure.ac $(HELP2MAN) \ --name "GNU Smalltalk documentation generator" \ "$(GST_TOOL) gst-doc $(GST_TOOL_ARGS)" >$@ $(srcdir)/gst-profile.1: $(top_srcdir)/scripts/Profile.st $(top_srcdir)/configure.ac $(HELP2MAN) \ --name "GNU Smalltalk profiler" \ "$(GST_TOOL) gst-doc $(GST_TOOL_ARGS)" >$@ $(srcdir)/gst.1: $(top_srcdir)/main.c $(top_srcdir)/configure.ac $(HELP2MAN) \ --name "the GNU Smalltalk virtual machine" $(top_builddir)/gst$(EXEEXT) >$@ $(srcdir)/gst-config.1: $(top_srcdir)/gst-config.in $(HELP2MAN) \ --name "configuration for libgst" $(top_builddir)/gst-config >$@ uninstall-local: rm -f $(DESTDIR)$(man1dir)/gst-reload.1 install-data-local: install-man rm -f $(DESTDIR)$(man1dir)/gst-reload.1 $(LN_S) $(DESTDIR)$(man1dir)/gst-load.1 $(DESTDIR)$(man1dir)/gst-reload.1 $(srcdir)/blox.texi: $(top_srcdir)/packages/blox/tk/stamp-classes files=`$(GST_PACKAGE) $(patsubst %, %/package.xml, $(^D)) \ --load --list-files=BloxTK | \ sed s,^,-f,`; \ IFS=`printf '\n\t'`; \ $(GST_DOC) -n BLOX -o $(srcdir)/blox.texi $$files BLOX.* || \ rm -f $(srcdir)/blox.texi test -f $(srcdir)/blox.texi && touch $(srcdir)/gst-libs.texi $(srcdir)/sockets.texi: $(top_srcdir)/packages/sockets/stamp-classes files=`$(GST_PACKAGE) $(patsubst %, %/package.xml, $(^D)) \ --load --list-files=Sockets | \ sed s,^,-f,`; \ IFS=`printf '\n\t'`; \ $(GST_DOC) -n Sockets -o $(srcdir)/sockets.texi $$files Sockets.* || \ rm -f $(srcdir)/sockets.texi test -f $(srcdir)/sockets.texi && touch $(srcdir)/gst-libs.texi $(srcdir)/complex.texi: $(top_srcdir)/packages/complex/stamp-classes files=`$(GST_PACKAGE) $(patsubst %, %/package.xml, $(^D)) \ --load --list-files=Complex | \ sed s,^,-f,`; \ IFS=`printf '\n\t'`; \ $(GST_DOC) -o $(srcdir)/complex.texi $$files Complex || \ rm -f $(srcdir)/complex.texi test -f $(srcdir)/complex.texi && touch $(srcdir)/gst-libs.texi $(srcdir)/debug.texi: $(top_srcdir)/packages/debug/stamp-classes files=`$(GST_PACKAGE) $(patsubst %, %/package.xml, $(^D)) \ --load --list-files=DebugTools | \ sed s,^,-f,`; \ IFS=`printf '\n\t'`; \ $(GST_DOC) -o $(srcdir)/debug.texi $$files Debugger* || \ rm -f $(srcdir)/debug.texi test -f $(srcdir)/debug.texi && touch $(srcdir)/gst-libs.texi $(srcdir)/zlib.texi: $(top_srcdir)/packages/zlib/stamp-classes files=`$(GST_PACKAGE) $(patsubst %, %/package.xml, $(^D)) \ --load --list-files=ZLib | \ sed s,^,-f,`; \ IFS=`printf '\n\t'`; \ $(GST_DOC) -n ZLib -o $(srcdir)/zlib.texi $$files ZLib.* || \ rm -f $(srcdir)/zlib.texi test -f $(srcdir)/zlib.texi && touch $(srcdir)/gst-libs.texi $(srcdir)/dbi.texi: $(top_srcdir)/packages/dbi/stamp-classes files=`$(GST_PACKAGE) $(patsubst %, %/package.xml, $(^D)) \ --load --list-files=DBI | \ sed s,^,-f,`; \ IFS=`printf '\n\t'`; \ $(GST_DOC) -n DBI -o $(srcdir)/dbi.texi $$files DBI.* || \ rm -f $(srcdir)/dbi.texi test -f $(srcdir)/dbi.texi && touch $(srcdir)/gst-libs.texi $(srcdir)/i18n.texi: $(top_srcdir)/packages/iconv/stamp-classes $(top_srcdir)/packages/i18n/stamp-classes files=`$(GST_PACKAGE) $(patsubst %, %/package.xml, $(^D)) \ --load --list-files=Iconv --list-files=I18N | \ sed s,^,-f,`; \ IFS=`printf '\n\t'`; \ $(GST_DOC) -n I18N -o $(srcdir)/i18n.texi $$files I18N.* || \ rm -f $(srcdir)/i18n.texi test -f $(srcdir)/i18n.texi && touch $(srcdir)/gst-libs.texi $(srcdir)/classes.texi: $(top_srcdir)/kernel/stamp-classes $(GST_DOC) -o $(srcdir)/classes.texi $(PUBLISHED_CLASSES) || \ rm -f $(srcdir)/classes.texi test -f $(srcdir)/classes.texi && touch $(srcdir)/gst-base.texi # In TeX output, having colons in index entries looks pretty, but # this is impossible in info output!!! So we hack by replacing # colons with underscores in the info file. %.info: %.texi @cd $(srcdir) && rm -f $@ $@-[0-9] $@-[0-9][0-9] fixed=`pwd`/`echo $< | $(SED) 's/\.texi/-fixed&/' `; \ cd $(srcdir) && \ $(MAKEINFO) `echo $< | $(SED) 's,.*/,,'` -E - -o /dev/null | \ $(SED) '/^@..index/ s/:/_/g' > $$fixed && \ $(MAKEINFO) $$fixed > /dev/null 2>&1 && \ rm -f $$fixed #################################################### #################################################### # We want the HTML doc to look professional, so we use makeinfo first. # This rule is pretty complex. What it does is: # - check whether /usr/bin/env perl works # - check whether we have makeinfo (it could be faked by the missing script) # - check whether we have makeinfo 4.0 # - resolve macros in gst.texi using makeinfo # - finally invoke texi2html # - remove the temporary file with resolved macros html: $(srcdir)/gst.texi $(srcdir)/gst-base.texi $(srcdir)/gst-libs.texi @(echo 'print "ohyeah"' | perl | grep ohyeah) > /dev/null 2>&1 || \ (echo "You need Perl to make HTML documentation"; exit 1) @($(MAKEINFO) --version 2>&1 | grep missing:) > /dev/null 2>&1 || exit 0; \ (echo "You need Makeinfo to make HTML documentation"; exit 1) rm -rf html mkdir html @echo "Building HTML documentation may be a long task... please wait" ($(MAKEINFO) --help | grep ifhtml) > /dev/null 2>&1 && makeinfo4=yes; \ htmldir=`pwd`/html && \ cd $(srcdir) && \ srcdir=`pwd` && \ $(MAKEINFO) gst.texi -E $$htmldir/gst.texi \ $${makeinfo4+--no-iftex --no-ifinfo --ifhtml} -o /dev/null && \ $(MAKEINFO) gst-libs.texi -E $$htmldir/gst-libs.texi \ $${makeinfo4+--no-iftex --no-ifinfo --ifhtml} -o /dev/null && \ $(MAKEINFO) gst-base.texi -E $$htmldir/gst-base.texi \ $${makeinfo4+--no-iftex --no-ifinfo --ifhtml} -o /dev/null && \ cd $$htmldir && \ $$srcdir/../build-aux/texi2html -Verbose -split section gst.texi && \ $$srcdir/../build-aux/texi2html -Verbose -split section gst-libs.texi && \ $$srcdir/../build-aux/texi2html -Verbose -split section gst-base.texi && \ ln -sf $$srcdir/images $$htmldir/images && \ $(RM) $$htmldir/gst.texi $$htmldir/gst-libs.texi $$htmldir/gst-base.texi clean-local: $(RM) -r html .PHONY: clean-html # Tell versions [3.59,3.63) of GNU make to not export all variables. # Otherwise a system limit (for SysV at least) may be exceeded. .NOEXPORT: smalltalk-3.2.5/doc/gst-base.texi0000644000175000017500000000462512130455674013611 00000000000000\input texinfo.tex @c -*- texinfo -*- @c %**start of header (This is for running Texinfo on a region.) @setfilename gst-base.info @settitle GNU Smalltalk Library Reference @setchapternewpage odd @c %**end of header (This is for running Texinfo on a region.) @c ******************************************* Values and macros ********* @include vers-base.texi @ifclear UPDATE-MONTH @set UPDATE-MONTH @value{UPDATED} @end ifclear @macro bulletize{a} @item \a\ @end macro @c ********************************************** Texinfo 4.0 macros ***** @c Emulate the `@ifnottex' command which is found in Texinfo 4.0 @iftex @set IS_TEX @end iftex @c *********************************************************************** @macro gst{} @sc{gnu} Smalltalk @end macro @macro gnu{} @sc{gnu} @end macro @dircategory Software development @direntry * Smalltalk base classes: (gst-base). The GNU Smalltalk base classes. @end direntry @copying @quotation Permission is granted to copy, distribute and/or modify this document under the terms of the GNU Free Documentation License, Version 1.2 or any later version published by the Free Software Foundation; with no Invariant Sections, with no Front-Cover Texts, and with no Back-Cover Texts. A copy of the license is included in the section entitled ``GNU Free Documentation License''. @end quotation @end copying @titlepage @title @sc{gnu} Smalltalk Library Reference @subtitle Version @value{VERSION} @subtitle @value{UPDATE-MONTH} @author by Paolo Bonzini @comment The following two commands start the copyright page. @page @vskip 0pt plus 1filll @insertcopying @end titlepage @node Top, , , (DIR) @top @ifnottex This document describes the class libraries that are distributed together with the @gst{} programming language. @insertcopying @end ifnottex @menu * Base classes:: The class reference * Class index:: Index to the classes in the class reference * Method index:: Index to the method selectors in the class reference * Cross-reference:: Cross-reference between selectors @end menu @node Base classes @chapter Base classes @include classes.texi @node Class index @unnumbered Class index @printindex cl @node Method index @unnumbered Method index @printindex me @node Cross-reference @unnumbered Selector cross-reference @printindex sl @iftex @contents @end iftex @bye Local Variables: compile-command: "makeinfo -fc 72 gst-base.texi" fill-column: 72 End: smalltalk-3.2.5/doc/vers-base.texi0000644000175000017500000000013612130456006013752 00000000000000@set UPDATED 8 April 2013 @set UPDATED-MONTH April 2013 @set EDITION 3.2.5 @set VERSION 3.2.5 smalltalk-3.2.5/doc/gst-config.10000644000175000017500000000116212130455702013314 00000000000000.\" DO NOT MODIFY THIS FILE! It was generated by help2man 1.28. .TH GST-CONFIG "1" "April 2013" "gst-config 3.2.5" "User Commands" .SH NAME gst-config \- configuration for libgst .SH SYNOPSIS .B gst-config [\fIOPTIONS\fR] [\fILIBRARIES\fR] .SH OPTIONS .IP [--prefix[=DIR]] [--exec-prefix[=DIR]] [--version] [--libdir] [--datadir] [--libs] [--cflags] .SS "Libraries:" .IP gst .SH "SEE ALSO" The full documentation for .B gst-config is maintained as a Texinfo manual. If the .B info and .B gst-config programs are properly installed at your site, the command .IP .B info gst .PP should give you access to the complete manual. smalltalk-3.2.5/doc/gst-libs.info-20000644000175000017500000037071612130456010013741 00000000000000This is gst-libs.info, produced by makeinfo version 4.13 from /home/ich/source/smalltalk/release/smalltalk/doc/gst-libs-fixed.texi. INFO-DIR-SECTION Software development START-INFO-DIR-ENTRY * Smalltalk libraries: (gst-libs). The GNU Smalltalk class libraries. END-INFO-DIR-ENTRY Permission is granted to copy, distribute and/or modify this document under the terms of the GNU Free Documentation License, Version 1.2 or any later version published by the Free Software Foundation; with no Invariant Sections, with no Front-Cover Texts, and with no Back-Cover Texts. A copy of the license is included in the section entitled "GNU Free Documentation License".  File: gst-libs.info, Node: Sockets.AbstractSocket class-well known ports, Next: Sockets.AbstractSocket-accessing, Prev: Sockets.AbstractSocket class-timed-out operations, Up: Sockets.AbstractSocket 6.1.4 Sockets.AbstractSocket class: well known ports ---------------------------------------------------- defaultPortAt: protocol Answer the port that is used (by default) for the given service (high level protocol) defaultPortAt: protocol ifAbsent: port Answer the port that is used (by default) for the given service (high level protocol), or the specified port if none is registered. defaultPortAt: protocol put: port Associate the given port to the service specified by `protocol'. portCmdServer Answer the port on which the rsh daemon listens portDNS Answer the port on which the DNS listens portDayTime Answer the port on which the TOD service listens portDiscard Answer the port on which the DISCARD service listens portEcho Answer the port on which the ECHO service listens portExecServer Answer the port on which the exec server listens portFTP Answer the port on which the FTP daemon listens portFinger Answer the port on which the finger daemon listens portGopher Answer the port on which the Gopher daemon listens portHTTP Answer the port on which the http daemon listens portLoginServer Answer the port on which the rlogin daemon listens portNNTP Answer the port on which the nntp daemon listens portNetStat Answer the port on which the NETSTAT service listens portPOP3 Answer the port on which the pop3 daemon listens portReserved Answer the last port reserved to privileged processes portSMTP Answer the port on which the SMTP daemon listens portSSH Answer the port on which the SSH daemon listens portSystat Answer the port on which the SYSTAT service listens portTelnet Answer the port on which the TELNET daemon listens portTimeServer Answer the port on which the time server listens portWhois Answer the port on which the WHOIS daemon listens  File: gst-libs.info, Node: Sockets.AbstractSocket-accessing, Next: Sockets.AbstractSocket-printing, Prev: Sockets.AbstractSocket class-well known ports, Up: Sockets.AbstractSocket 6.1.5 Sockets.AbstractSocket: accessing --------------------------------------- address Answer an IP address that is of common interest (this can be either the local or the remote address, according to the definition in the subclass). available Answer whether there is data available on the socket. Same as #canRead, present for backwards compatibility. canRead Answer whether there is data available on the socket. canWrite Answer whether there is free space in the socket's write buffer. close Close the socket represented by the receiver. flush Flush any buffers used by the receiver. isOpen Answer whether the connection between the receiver and the remote endpoint is still alive. isPeerAlive Answer whether the connection with the peer remote machine is still valid. localAddress Answer the local IP address of the socket. localPort Answer the local IP port of the socket. port Answer an IP port that is of common interest (this can be the port for either the local or remote endpoint, according to the definitions in the subclass remoteAddress Answer the IP address of the socket's remote endpoint. remotePort Answer the IP port of the socket's remote endpoint.  File: gst-libs.info, Node: Sockets.AbstractSocket-printing, Next: Sockets.AbstractSocket-socket options, Prev: Sockets.AbstractSocket-accessing, Up: Sockets.AbstractSocket 6.1.6 Sockets.AbstractSocket: printing -------------------------------------- printOn: aStream Print a representation of the receiver on aStream  File: gst-libs.info, Node: Sockets.AbstractSocket-socket options, Next: Sockets.AbstractSocket-stream protocol, Prev: Sockets.AbstractSocket-printing, Up: Sockets.AbstractSocket 6.1.7 Sockets.AbstractSocket: socket options -------------------------------------------- soLinger Answer the number of seconds that the socket is allowed to wait if it promises reliable delivery but has unacknowledged/untransmitted packets when it is closed, or nil if those packets are left to their destiny or discarded. soLinger: linger Set the number of seconds that the socket is allowed to wait if it promises reliable delivery but has unacknowledged/untransmitted packets when it is closed. soLingerOff Specify that, even if the socket promises reliable delivery, any packets that are unacknowledged/untransmitted when it is closed are to be left to their destiny or discarded. species Answer `String'.  File: gst-libs.info, Node: Sockets.AbstractSocket-stream protocol, Next: Sockets.AbstractSocket-testing, Prev: Sockets.AbstractSocket-socket options, Up: Sockets.AbstractSocket 6.1.8 Sockets.AbstractSocket: stream protocol --------------------------------------------- atEnd By default, answer whether the connection is still open. next Read another character from the socket, failing if the connection is dead. next: n putAll: aCollection startingAt: pos Write `char' to the socket, failing if the connection is dead. The SIGPIPE signal is automatically caught and ignored by the system. nextPut: char Write `char' to the socket, failing if the connection is dead. The SIGPIPE signal is automatically caught and ignored by the system.  File: gst-libs.info, Node: Sockets.AbstractSocket-testing, Prev: Sockets.AbstractSocket-stream protocol, Up: Sockets.AbstractSocket 6.1.9 Sockets.AbstractSocket: testing ------------------------------------- isExternalStream Answer whether the receiver streams on a file or socket.  File: gst-libs.info, Node: Sockets.AbstractSocketImpl, Next: Sockets.CAddrInfoStruct, Prev: Sockets.AbstractSocket, Up: Sockets package 6.2 Sockets.AbstractSocketImpl ============================== Defined in namespace Sockets Superclass: FileDescriptor Category: Sockets-Protocols This abstract class serves as the parent class for socket implementations. The implementation class serves an intermediary to routines that perform the actual socket operations. It hides the buffering and blocking behavior of the Socket classes. A default implementation is provided by each address family, but this can be changed by class methods on SocketAddress sublcasses. * Menu: * Sockets.AbstractSocketImpl class-abstract:: (class) * Sockets.AbstractSocketImpl class-C call-outs:: (class) * Sockets.AbstractSocketImpl class-C constants:: (class) * Sockets.AbstractSocketImpl class-socket creation:: (class) * Sockets.AbstractSocketImpl-accessing:: (instance) * Sockets.AbstractSocketImpl-asynchronous operations:: (instance) * Sockets.AbstractSocketImpl-C call-outs:: (instance) * Sockets.AbstractSocketImpl-C constants:: (instance) * Sockets.AbstractSocketImpl-socket operations:: (instance) * Sockets.AbstractSocketImpl-socket options:: (instance)  File: gst-libs.info, Node: Sockets.AbstractSocketImpl class-abstract, Next: Sockets.AbstractSocketImpl class-C call-outs, Up: Sockets.AbstractSocketImpl 6.2.1 Sockets.AbstractSocketImpl class: abstract ------------------------------------------------ addressClass Answer the class responsible for handling addresses for the receiver protocol Answer the protocol parameter for `create' socketType Answer the socket type parameter for `create'.  File: gst-libs.info, Node: Sockets.AbstractSocketImpl class-C call-outs, Next: Sockets.AbstractSocketImpl class-C constants, Prev: Sockets.AbstractSocketImpl class-abstract, Up: Sockets.AbstractSocketImpl 6.2.2 Sockets.AbstractSocketImpl class: C call-outs --------------------------------------------------- accept: socket peer: peer addrLen: len Not commented. bind: socket to: addr addrLen: len Not commented. connect: socket to: addr addrLen: len Not commented. create: family type: type protocol: protocol Not commented. getPeerName: socket addr: addr addrLen: len Not commented. getSockName: socket addr: addr addrLen: len Not commented. listen: socket log: len Not commented. option: socket level: level at: name get: value size: len Not commented. option: socket level: level at: name put: value size: len Not commented. receive: socket buffer: buf size: len flags: flags from: addr size: addrLen Not commented. send: socket buffer: buf size: len flags: flags to: addr size: addrLen Not commented.  File: gst-libs.info, Node: Sockets.AbstractSocketImpl class-C constants, Next: Sockets.AbstractSocketImpl class-socket creation, Prev: Sockets.AbstractSocketImpl class-C call-outs, Up: Sockets.AbstractSocketImpl 6.2.3 Sockets.AbstractSocketImpl class: C constants --------------------------------------------------- soLinger Not commented. soReuseAddr Not commented. sockDgram Not commented. sockRDM Not commented. sockRaw Not commented. sockStream Not commented. solSocket Not commented.  File: gst-libs.info, Node: Sockets.AbstractSocketImpl class-socket creation, Next: Sockets.AbstractSocketImpl-accessing, Prev: Sockets.AbstractSocketImpl class-C constants, Up: Sockets.AbstractSocketImpl 6.2.4 Sockets.AbstractSocketImpl class: socket creation ------------------------------------------------------- newFor: addressClass Create a socket for the receiver.  File: gst-libs.info, Node: Sockets.AbstractSocketImpl-accessing, Next: Sockets.AbstractSocketImpl-asynchronous operations, Prev: Sockets.AbstractSocketImpl class-socket creation, Up: Sockets.AbstractSocketImpl 6.2.5 Sockets.AbstractSocketImpl: accessing ------------------------------------------- connectTo: ipAddress port: port Connect the receiver to the given IP address and port. `Connecting' means attaching the remote endpoint of the socket. localAddress Answer the address of the local endpoint of the socket (even if IP is not being used, this identifies the machine that is bound to the socket). localPort Answer the port of the local endpoint of the socket (even if IP is not being used, this identifies the service or process that is bound to the socket). remoteAddress Answer the address of the remote endpoint of the socket (even if IP is not being used, this identifies the machine to which the socket is connected). remotePort Answer the port of the remote endpoint of the socket (even if IP is not being used, this identifies the service or process to which the socket is connected).  File: gst-libs.info, Node: Sockets.AbstractSocketImpl-asynchronous operations, Next: Sockets.AbstractSocketImpl-C call-outs, Prev: Sockets.AbstractSocketImpl-accessing, Up: Sockets.AbstractSocketImpl 6.2.6 Sockets.AbstractSocketImpl: asynchronous operations --------------------------------------------------------- ensureReadable If the file is open, wait until data can be read from it. The wait allows other Processes to run. ensureWriteable If the file is open, wait until we can write to it. The wait allows other Processes to run. waitForException If the file is open, wait until an exceptional condition (such as presence of out of band data) has occurred on it. The wait allows other Processes to run.  File: gst-libs.info, Node: Sockets.AbstractSocketImpl-C call-outs, Next: Sockets.AbstractSocketImpl-C constants, Prev: Sockets.AbstractSocketImpl-asynchronous operations, Up: Sockets.AbstractSocketImpl 6.2.7 Sockets.AbstractSocketImpl: C call-outs --------------------------------------------- accept: socket peer: peer addrLen: len Not commented. bind: socket to: addr addrLen: len Not commented. connect: socket to: addr addrLen: len Not commented. create: family type: type protocol: protocol Not commented. getPeerName: socket addr: addr addrLen: len Not commented. getSockName: socket addr: addr addrLen: len Not commented. listen: socket log: len Not commented. option: socket level: level at: name get: value size: len Not commented. option: socket level: level at: name put: value size: len Not commented. receive: socket buffer: buf size: len flags: flags from: addr size: addrLen Not commented. send: socket buffer: buf size: len flags: flags to: addr size: addrLen Not commented.  File: gst-libs.info, Node: Sockets.AbstractSocketImpl-C constants, Next: Sockets.AbstractSocketImpl-socket operations, Prev: Sockets.AbstractSocketImpl-C call-outs, Up: Sockets.AbstractSocketImpl 6.2.8 Sockets.AbstractSocketImpl: C constants --------------------------------------------- soError: socket Not commented.  File: gst-libs.info, Node: Sockets.AbstractSocketImpl-socket operations, Next: Sockets.AbstractSocketImpl-socket options, Prev: Sockets.AbstractSocketImpl-C constants, Up: Sockets.AbstractSocketImpl 6.2.9 Sockets.AbstractSocketImpl: socket operations --------------------------------------------------- accept: implementationClass Accept a connection on the receiver, and create a new instance of implementationClass that will deal with the newly created active server socket. bindTo: ipAddress port: port Bind the receiver to the given IP address and port. `Binding' means attaching the local endpoint of the socket. fileOp: ioFuncIndex Private - Used to limit the number of primitives used by FileStreams fileOp: ioFuncIndex ifFail: aBlock Private - Used to limit the number of primitives used by FileStreams. fileOp: ioFuncIndex with: arg1 Private - Used to limit the number of primitives used by FileStreams fileOp: ioFuncIndex with: arg1 ifFail: aBlock Private - Used to limit the number of primitives used by FileStreams. fileOp: ioFuncIndex with: arg1 with: arg2 Private - Used to limit the number of primitives used by FileStreams fileOp: ioFuncIndex with: arg1 with: arg2 ifFail: aBlock Private - Used to limit the number of primitives used by FileStreams. fileOp: ioFuncIndex with: arg1 with: arg2 with: arg3 Private - Used to limit the number of primitives used by FileStreams fileOp: ioFuncIndex with: arg1 with: arg2 with: arg3 ifFail: aBlock Private - Used to limit the number of primitives used by FileStreams. getSockName Retrieve a ByteArray containing a sockaddr_in struct for the local endpoint of the socket. listen: backlog Make the receiver a passive server socket with a pending connections queue of the given size.  File: gst-libs.info, Node: Sockets.AbstractSocketImpl-socket options, Prev: Sockets.AbstractSocketImpl-socket operations, Up: Sockets.AbstractSocketImpl 6.2.10 Sockets.AbstractSocketImpl: socket options ------------------------------------------------- optionAt: opt level: level put: anObject Modify the value of a socket option. The option identifier is in `opt' and the level is in `level'. anObject can be a boolean, integer, socket address or ByteArray. A layer over this method is provided for the most common socket options, so this will be rarely used. optionAt: opt level: level size: size Answer in a ByteArray of the given size the value of a socket option. The option identifier is in `opt' and the level is in `level'. A layer over this method is provided for the most common socket options, so this will be rarely used. soLinger Answer the number of seconds by which a `close' operation can block to ensure that all the packets have reliably reached the destination, or nil if those packets are left to their destiny. soLinger: linger Set the number of seconds by which a `close' operation can block to ensure that all the packets have reliably reached the destination. If linger is nil, those packets are left to their destiny. soReuseAddr Answer whether another socket can be bound the same local address as this one. If you enable this option, you can actually have two sockets with the same Internet port number; but the system won't allow you to use the two identically-named sockets in a way that would confuse the Internet. The reason for this option is that some higher-level Internet protocols, including FTP, require you to keep reusing the same socket number. soReuseAddr: aBoolean Set whether another socket can be bound the same local address as this one. valueWithoutBuffering: aBlock Evaluate aBlock, ensuring that any data that it writes to the socket is sent immediately to the network.  File: gst-libs.info, Node: Sockets.CAddrInfoStruct, Next: Sockets.CSockAddrIn6Struct, Prev: Sockets.AbstractSocketImpl, Up: Sockets package 6.3 Sockets.CAddrInfoStruct =========================== Defined in namespace Sockets Superclass: CStruct Category: * Menu: * Sockets.CAddrInfoStruct class-C call-outs:: (class) * Sockets.CAddrInfoStruct-C call-outs:: (instance) * Sockets.CAddrInfoStruct-C function wrappers:: (instance)  File: gst-libs.info, Node: Sockets.CAddrInfoStruct class-C call-outs, Next: Sockets.CAddrInfoStruct-C call-outs, Up: Sockets.CAddrInfoStruct 6.3.1 Sockets.CAddrInfoStruct class: C call-outs ------------------------------------------------ getaddrinfo: name service: servname hints: hints result: res Not commented.  File: gst-libs.info, Node: Sockets.CAddrInfoStruct-C call-outs, Next: Sockets.CAddrInfoStruct-C function wrappers, Prev: Sockets.CAddrInfoStruct class-C call-outs, Up: Sockets.CAddrInfoStruct 6.3.2 Sockets.CAddrInfoStruct: C call-outs ------------------------------------------ aiAddr Not commented. aiCanonname Not commented. free Not commented.  File: gst-libs.info, Node: Sockets.CAddrInfoStruct-C function wrappers, Prev: Sockets.CAddrInfoStruct-C call-outs, Up: Sockets.CAddrInfoStruct 6.3.3 Sockets.CAddrInfoStruct: C function wrappers -------------------------------------------------- getaddrinfo: name Not commented. getaddrinfo: name service: service Not commented.  File: gst-libs.info, Node: Sockets.CSockAddrIn6Struct, Next: Sockets.Datagram, Prev: Sockets.CAddrInfoStruct, Up: Sockets package 6.4 Sockets.CSockAddrIn6Struct ============================== Defined in namespace Sockets Superclass: CStruct Category: * Menu:  File: gst-libs.info, Node: Sockets.Datagram, Next: Sockets.DatagramSocket, Prev: Sockets.CSockAddrIn6Struct, Up: Sockets package 6.5 Sockets.Datagram ==================== Defined in namespace Sockets Superclass: Object Category: Sockets-Protocols This class models a packet of data that is to be sent across the network using a connectionless protocol such as UDP. It contains the data to be send, as well as the destination address and port. Note that datagram packets can arrive in any order and are not guaranteed to be delivered at all. This class can also be used for receiving data from the network. * Menu: * Sockets.Datagram class-instance creation:: (class) * Sockets.Datagram-accessing:: (instance)  File: gst-libs.info, Node: Sockets.Datagram class-instance creation, Next: Sockets.Datagram-accessing, Up: Sockets.Datagram 6.5.1 Sockets.Datagram class: instance creation ----------------------------------------------- data: aByteArray Answer a new datagram with the specified data. data: aByteArray address: ipAddress port: port Answer a new datagram with the specified target socket, and aByteArray as its data. object: object address: ipAddress port: port Serialize the object onto a ByteArray, and create a Datagram with the object as its contents, and the specified receiver. Note that each invocation of this method creates a separate ObjectDumper; if different objects that you're sending are likely to contain references to the same objects, you should use #object:objectDumper:address:port:. object: object objectDumper: od address: ipAddress port: port Serialize the object onto a ByteArray, and create a Datagram with the object as its contents, and the specified receiver. Serialization takes place through ObjectDumper passed as `od', and the stream attached to the ObjectDumper is resetted every time. Using this method is indicated if different objects that you're sending are likely to contain references to the same objects.  File: gst-libs.info, Node: Sockets.Datagram-accessing, Prev: Sockets.Datagram class-instance creation, Up: Sockets.Datagram 6.5.2 Sockets.Datagram: accessing --------------------------------- address Answer the address of the target socket address: ipAddress Set the address of the target socket data Answer the data attached to the datagram data: aByteArray Set the data attached to the datagram dataSize Answer the size of the message. dataSize: aSize I am called to update the size... get Parse the data attached to the datagram through a newly created ObjectDumper, and answer the resulting object. This method is complementary to #object:address:port:. getThrough: objectDumper Parse the data attached to the datagram through the given ObjectDumper without touching the stream to which it is attached, and answer the resulting object. The state of the ObjectDumper, though, is updated. This method is complementary to #object:objectDumper:address:port:. port Answer the IP port of the target socket port: thePort Set the IP port of the target socket size I determine the size of the datagram. It is either an explicitly specified dataSize, or the size of the whole collection.  File: gst-libs.info, Node: Sockets.DatagramSocket, Next: Sockets.DatagramSocketImpl, Prev: Sockets.Datagram, Up: Sockets package 6.6 Sockets.DatagramSocket ========================== Defined in namespace Sockets Superclass: Sockets.AbstractSocket Category: Sockets-Streams This class models a connectionless datagram socket that sends individual packets of data across the network. In the TCP/IP world, this means UDP. Datagram packets do not have guaranteed delivery, or any guarantee about the order the data will be received on the remote host. This class uses an underlying socket implementation object which is a subclass of DatagramSocketImpl. This is less necessary for datagram sockets than for stream sockets (except for hiding some methods in FileDescriptor that are not relevant to sockets), but it is done for cleanliness and symmetry. * Menu: * Sockets.DatagramSocket class-accessing:: (class) * Sockets.DatagramSocket class-initialization:: (class) * Sockets.DatagramSocket class-instance creation:: (class) * Sockets.DatagramSocket-accessing:: (instance) * Sockets.DatagramSocket-direct operations:: (instance)  File: gst-libs.info, Node: Sockets.DatagramSocket class-accessing, Next: Sockets.DatagramSocket class-initialization, Up: Sockets.DatagramSocket 6.6.1 Sockets.DatagramSocket class: accessing --------------------------------------------- defaultBufferSize Answer the default maximum size for input datagrams. defaultBufferSize: size Set the default maximum size for input datagrams. defaultImplementationClassFor: aSocketAddressClass Answer the default implementation class. Depending on the subclass, this might be the default stream socket implementation class of the given address class, or rather its default datagram socket implementation class.  File: gst-libs.info, Node: Sockets.DatagramSocket class-initialization, Next: Sockets.DatagramSocket class-instance creation, Prev: Sockets.DatagramSocket class-accessing, Up: Sockets.DatagramSocket 6.6.2 Sockets.DatagramSocket class: initialization -------------------------------------------------- initialize Initialize the class to use an input datagram size of 128.  File: gst-libs.info, Node: Sockets.DatagramSocket class-instance creation, Next: Sockets.DatagramSocket-accessing, Prev: Sockets.DatagramSocket class-initialization, Up: Sockets.DatagramSocket 6.6.3 Sockets.DatagramSocket class: instance creation ----------------------------------------------------- local: ipAddressOrString port: remotePort Create a new socket and bind it to the given host (passed as a String to be resolved or as an IPAddress), on the given port. new Answer a new datagram socket (by default an UDP socket), without a specified local address and port. port: localPort Create a new socket and bind it to the local host on the given port. remote: ipAddressOrString port: remotePort local: ipAddress port: localPort Create a new socket and bind it to the given host (passed as a String to be resolved or as a SocketAddress), and to the given remotePort. The default destination for the datagrams will be ipAddressOrString (if not nil), on the remotePort port.  File: gst-libs.info, Node: Sockets.DatagramSocket-accessing, Next: Sockets.DatagramSocket-direct operations, Prev: Sockets.DatagramSocket class-instance creation, Up: Sockets.DatagramSocket 6.6.4 Sockets.DatagramSocket: accessing --------------------------------------- address Answer the local address. bufferSize Answer the size of the buffer in which datagrams are stored. bufferSize: size Set the size of the buffer in which datagrams are stored. datagramClass Answer the class used by the socket to return datagrams. next Read a datagram on the socket and answer it. nextPut: aDatagram Send the given datagram on the socket. peek Peek for a datagram on the socket and answer it. peek: datagram Peek for a datagram on the socket, store it in `datagram', and answer the datagram itself. port Answer the local port. receive: datagram Read a datagram from the socket, store it in `datagram', and answer the datagram itself.  File: gst-libs.info, Node: Sockets.DatagramSocket-direct operations, Prev: Sockets.DatagramSocket-accessing, Up: Sockets.DatagramSocket 6.6.5 Sockets.DatagramSocket: direct operations ----------------------------------------------- nextFrom: ipAddress port: port Answer the next datagram from the given address and port.  File: gst-libs.info, Node: Sockets.DatagramSocketImpl, Next: Sockets.DummyStream, Prev: Sockets.DatagramSocket, Up: Sockets package 6.7 Sockets.DatagramSocketImpl ============================== Defined in namespace Sockets Superclass: Sockets.AbstractSocketImpl Category: Sockets-Protocols This abstract class serves as the parent class for datagram socket implementations. * Menu: * Sockets.DatagramSocketImpl class-parameters:: (class) * Sockets.DatagramSocketImpl-accessing:: (instance) * Sockets.DatagramSocketImpl-C constants:: (instance) * Sockets.DatagramSocketImpl-socket operations:: (instance)  File: gst-libs.info, Node: Sockets.DatagramSocketImpl class-parameters, Next: Sockets.DatagramSocketImpl-accessing, Up: Sockets.DatagramSocketImpl 6.7.1 Sockets.DatagramSocketImpl class: parameters -------------------------------------------------- datagramClass Answer the datagram class returned by default by instances of this class. socketType Answer the socket type parameter for `create'.  File: gst-libs.info, Node: Sockets.DatagramSocketImpl-accessing, Next: Sockets.DatagramSocketImpl-C constants, Prev: Sockets.DatagramSocketImpl class-parameters, Up: Sockets.DatagramSocketImpl 6.7.2 Sockets.DatagramSocketImpl: accessing ------------------------------------------- bufferSize Answer the size of the buffer in which datagrams are stored. bufferSize: size Set the size of the buffer in which datagrams are stored.  File: gst-libs.info, Node: Sockets.DatagramSocketImpl-C constants, Next: Sockets.DatagramSocketImpl-socket operations, Prev: Sockets.DatagramSocketImpl-accessing, Up: Sockets.DatagramSocketImpl 6.7.3 Sockets.DatagramSocketImpl: C constants --------------------------------------------- ipAddMembership Not commented. ipDropMembership Not commented. ipMulticastIf Not commented. ipMulticastTtl Not commented. msgPeek Not commented.  File: gst-libs.info, Node: Sockets.DatagramSocketImpl-socket operations, Prev: Sockets.DatagramSocketImpl-C constants, Up: Sockets.DatagramSocketImpl 6.7.4 Sockets.DatagramSocketImpl: socket operations --------------------------------------------------- next Retrieve a datagram from the receiver, answer a new object of the receiver's datagram class. nextPut: aDatagram Send aDatagram on the socket peek Peek for a datagram on the receiver, answer a new object of the receiver's datagram class. peek: aDatagram Peek for a datagram on the receiver, answer aDatagram modified to contain information on the newly received datagram. receive: aDatagram Retrieve a datagram from the receiver, answer aDatagram modified to contain information on the newly received datagram. receive: flags datagram: aDatagram Receive a new datagram into `datagram', with the given flags, and answer `datagram' itself; this is an abstract method. The flags can be zero to receive the datagram, or `self msgPeek' to only peek for it without removing it from the queue. send: aDatagram to: theReceiver port: port Send aDatagram on the socket to the given receiver and port  File: gst-libs.info, Node: Sockets.DummyStream, Next: Sockets.ICMP6SocketImpl, Prev: Sockets.DatagramSocketImpl, Up: Sockets package 6.8 Sockets.DummyStream ======================= Defined in namespace Sockets Superclass: Stream Category: Sockets-Tests * Menu:  File: gst-libs.info, Node: Sockets.ICMP6SocketImpl, Next: Sockets.ICMPSocketImpl, Prev: Sockets.DummyStream, Up: Sockets package 6.9 Sockets.ICMP6SocketImpl =========================== Defined in namespace Sockets Superclass: Sockets.RawSocketImpl Category: Sockets-Protocols Unless the application installs its own implementation, this is the default socket implementation that will be used for IPv6 raw sockets. It uses C call-outs to implement standard BSD style sockets of family AF_INET, type SOCK_RAW, protocol IPPROTO_ICMPV6. * Menu: * Sockets.ICMP6SocketImpl class-C constants:: (class)  File: gst-libs.info, Node: Sockets.ICMP6SocketImpl class-C constants, Up: Sockets.ICMP6SocketImpl 6.9.1 Sockets.ICMP6SocketImpl class: C constants ------------------------------------------------ protocol Not commented.  File: gst-libs.info, Node: Sockets.ICMPSocketImpl, Next: Sockets.IP6Address, Prev: Sockets.ICMP6SocketImpl, Up: Sockets package 6.10 Sockets.ICMPSocketImpl =========================== Defined in namespace Sockets Superclass: Sockets.RawSocketImpl Category: Sockets-Protocols Unless the application installs its own implementation, this is the default socket implementation that will be used for IPv4 raw sockets. It uses C call-outs to implement standard BSD style sockets of family AF_INET, type SOCK_RAW, protocol IPPROTO_ICMP. * Menu: * Sockets.ICMPSocketImpl class-C constants:: (class)  File: gst-libs.info, Node: Sockets.ICMPSocketImpl class-C constants, Up: Sockets.ICMPSocketImpl 6.10.1 Sockets.ICMPSocketImpl class: C constants ------------------------------------------------ protocol Not commented.  File: gst-libs.info, Node: Sockets.IP6Address, Next: Sockets.IPAddress, Prev: Sockets.ICMPSocketImpl, Up: Sockets package 6.11 Sockets.IP6Address ======================= Defined in namespace Sockets Superclass: Sockets.SocketAddress Category: Sockets-Protocols This class models an IPv6 address. It also acts as a factory for IPv6 stream (TCP), datagram (UDP) and raw sockets. * Menu: * Sockets.IP6Address class-C constants:: (class) * Sockets.IP6Address class-constants:: (class) * Sockets.IP6Address class-initialization:: (class) * Sockets.IP6Address class-instance creation:: (class) * Sockets.IP6Address-accessing:: (instance) * Sockets.IP6Address-printing:: (instance)  File: gst-libs.info, Node: Sockets.IP6Address class-C constants, Next: Sockets.IP6Address class-constants, Up: Sockets.IP6Address 6.11.1 Sockets.IP6Address class: C constants -------------------------------------------- addressFamily Not commented. aiAll Not commented. aiV4mapped Not commented. protocolFamily Not commented.  File: gst-libs.info, Node: Sockets.IP6Address class-constants, Next: Sockets.IP6Address class-initialization, Prev: Sockets.IP6Address class-C constants, Up: Sockets.IP6Address 6.11.2 Sockets.IP6Address class: constants ------------------------------------------ addressSize Answer the size of an IPv4 address. version Answer the version of IP that the receiver implements.  File: gst-libs.info, Node: Sockets.IP6Address class-initialization, Next: Sockets.IP6Address class-instance creation, Prev: Sockets.IP6Address class-constants, Up: Sockets.IP6Address 6.11.3 Sockets.IP6Address class: initialization ----------------------------------------------- createLoopbackHost Answer an object representing the loopback host in the address family for the receiver. This is ::1 for IPv4. createUnknownAddress Answer an object representing an unkown address in the address family for the receiver initialize Set up the default implementation classes for the receiver  File: gst-libs.info, Node: Sockets.IP6Address class-instance creation, Next: Sockets.IP6Address-accessing, Prev: Sockets.IP6Address class-initialization, Up: Sockets.IP6Address 6.11.4 Sockets.IP6Address class: instance creation -------------------------------------------------- fromArray: parts Answer a new IP6Address from an array of numbers; the numbers are to be thought as the colon-separated numbers in the standard numbers-and-colons notation for IPv4 addresses. fromBytes: aByteArray Answer a new IP6Address from a ByteArray containing the bytes in the same order as the digit form: 131.175.6.2 would be represented as #[131 175 6 2]. fromSockAddr: aByteArray port: portAdaptor Private - Answer a new IP6Address from a ByteArray containing a C sockaddr_in structure. The portAdaptor's value is changed to contain the port that the structure refers to. fromString: aString Answer a new IP6Address from a String containing the requested address in digit form. new This method should not be called for instances of this class.  File: gst-libs.info, Node: Sockets.IP6Address-accessing, Next: Sockets.IP6Address-printing, Prev: Sockets.IP6Address class-instance creation, Up: Sockets.IP6Address 6.11.5 Sockets.IP6Address: accessing ------------------------------------ asByteArray Answer a read-only ByteArray of size four containing the receiver's bytes in network order (big-endian) isMulticast Answer whether the receiver reprensents an address reserved for multicast datagram connections  File: gst-libs.info, Node: Sockets.IP6Address-printing, Prev: Sockets.IP6Address-accessing, Up: Sockets.IP6Address 6.11.6 Sockets.IP6Address: printing ----------------------------------- printOn: aStream Print the receiver in dot notation.  File: gst-libs.info, Node: Sockets.IPAddress, Next: Sockets.MulticastSocket, Prev: Sockets.IP6Address, Up: Sockets package 6.12 Sockets.IPAddress ====================== Defined in namespace Sockets Superclass: Sockets.SocketAddress Category: Sockets-Protocols This class models an IPv4 address. It also acts as a factory for IPv4 stream (TCP), datagram (UDP) and raw sockets. * Menu: * Sockets.IPAddress class-C constants:: (class) * Sockets.IPAddress class-constants:: (class) * Sockets.IPAddress class-initialization:: (class) * Sockets.IPAddress class-instance creation:: (class) * Sockets.IPAddress-accessing:: (instance) * Sockets.IPAddress-printing:: (instance)  File: gst-libs.info, Node: Sockets.IPAddress class-C constants, Next: Sockets.IPAddress class-constants, Up: Sockets.IPAddress 6.12.1 Sockets.IPAddress class: C constants ------------------------------------------- addressFamily Not commented. protocolFamily Not commented.  File: gst-libs.info, Node: Sockets.IPAddress class-constants, Next: Sockets.IPAddress class-initialization, Prev: Sockets.IPAddress class-C constants, Up: Sockets.IPAddress 6.12.2 Sockets.IPAddress class: constants ----------------------------------------- addressSize Answer the size of an IPv4 address. version Answer the version of IP that the receiver implements.  File: gst-libs.info, Node: Sockets.IPAddress class-initialization, Next: Sockets.IPAddress class-instance creation, Prev: Sockets.IPAddress class-constants, Up: Sockets.IPAddress 6.12.3 Sockets.IPAddress class: initialization ---------------------------------------------- createLoopbackHost Answer an object representing the loopback host in the address family for the receiver. This is 127.0.0.1 for IPv4. createUnknownAddress Answer an object representing an unkown address in the address family for the receiver initialize Set up the default implementation classes for the receiver  File: gst-libs.info, Node: Sockets.IPAddress class-instance creation, Next: Sockets.IPAddress-accessing, Prev: Sockets.IPAddress class-initialization, Up: Sockets.IPAddress 6.12.4 Sockets.IPAddress class: instance creation ------------------------------------------------- fromArray: parts Answer a new IPAddress from an array of numbers; the numbers are to be thought as the dot-separated numbers in the standard numbers-and-dots notation for IPv4 addresses. fromBytes: aByteArray Answer a new IPAddress from a ByteArray containing the bytes in the same order as the digit form: 131.175.6.2 would be represented as #[131 175 6 2]. fromSockAddr: aByteArray port: portAdaptor Private - Answer a new IPAddress from a ByteArray containing a C sockaddr_in structure. The portAdaptor's value is changed to contain the port that the structure refers to. fromString: aString Answer a new IPAddress from a String containing the requested address in digit form. Hexadecimal forms are not allowed. An Internet host address is a number containing four bytes of data. These are divided into two parts, a network number and a local network address number within that network. The network number consists of the first one, two or three bytes; the rest of the bytes are the local address. Network numbers are registered with the Network Information Center (NIC), and are divided into three classes-A, B, and C. The local network address numbers of individual machines are registered with the administrator of the particular network. Class A networks have single-byte numbers in the range 0 to 127. There are only a small number of Class A networks, but they can each support a very large number of hosts (several millions). Medium-sized Class B networks have two-byte network numbers, with the first byte in the range 128 to 191; they support several thousands of host, but are almost exhausted. Class C networks are the smallest and the most commonly available; they have three-byte network numbers, with the first byte in the range 192-223. Class D (multicast, 224.0.0.0 to 239.255.255.255) and E (research, 240.0.0.0 to 255.255.255.255) also have three-byte network numbers. Thus, the first 1, 2, or 3 bytes of an Internet address specifies a network. The remaining bytes of the Internet address specify the address within that network. The Class A network 0 is reserved for broadcast to all networks. In addition, the host number 0 within each network is reserved for broadcast to all hosts in that network. The Class A network 127 is reserved for loopback; you can always use the Internet address `127.0.0.1' to refer to the host machine (this is answered by the #loopbackHost class method). Since a single machine can be a member of multiple networks, it can have multiple Internet host addresses. However, there is never supposed to be more than one machine with the same host address. There are four forms of the standard numbers-and-dots notation for Internet addresses: a.b.c.d specifies all four bytes of the address individually; a.b.c interprets as a 2-byte quantity, which is useful for specifying host addresses in a Class B network with network address number a.b; a.b intrprets the last part of the address as a 3-byte quantity, which is useful for specifying host addresses in a Class A network with network address number a. If only one part is given, this corresponds directly to the host address number. new This method should not be called for instances of this class. with: b1 with: b2 with: b3 with: b4 Answer a new IPAddress whose bytes (from most-significant to least-significant) are in the parameters.  File: gst-libs.info, Node: Sockets.IPAddress-accessing, Next: Sockets.IPAddress-printing, Prev: Sockets.IPAddress class-instance creation, Up: Sockets.IPAddress 6.12.5 Sockets.IPAddress: accessing ----------------------------------- addressClass Answer the `address class' of the receiver (see IPAddress class>>#fromString:) asByteArray Answer a read-only ByteArray of size four containing the receiver's bytes in network order (big-endian) host Answer an host number for the receiver; this is given by the last three bytes for class A addresses, by the last two bytes for class B addresses, else by the last byte. isMulticast Answer whether the receiver reprensents an address reserved for multicast datagram connections network Answer a network number for the receiver; this is given by the first three bytes for class C/D/E addresses, by the first two bytes for class B addresses, else by the first byte. subnet Answer an host number for the receiver; this is 0 for class A addresses, while it is given by the last byte of the network number for class B/C/D/E addresses.  File: gst-libs.info, Node: Sockets.IPAddress-printing, Prev: Sockets.IPAddress-accessing, Up: Sockets.IPAddress 6.12.6 Sockets.IPAddress: printing ---------------------------------- printOn: aStream Print the receiver in dot notation.  File: gst-libs.info, Node: Sockets.MulticastSocket, Next: Sockets.MulticastSocketImpl, Prev: Sockets.IPAddress, Up: Sockets package 6.13 Sockets.MulticastSocket ============================ Defined in namespace Sockets Superclass: Sockets.DatagramSocket Category: Sockets-Streams This class models a multicast socket that sends packets to a multicast group. All members of the group listening on that address and port will receive all the messages sent to the group. In the TCP/IP world, these sockets are UDP-based and a multicast group consists of a multicast address (a class D internet address, i.e. one whose most significant bits are 1110), and a well known port number. * Menu: * Sockets.MulticastSocket-instance creation:: (instance)  File: gst-libs.info, Node: Sockets.MulticastSocket-instance creation, Up: Sockets.MulticastSocket 6.13.1 Sockets.MulticastSocket: instance creation ------------------------------------------------- interface Answer the local device supporting the multicast socket. This is usually set to any local address. interface: ipAddress Set the local device supporting the multicast socket. This is usually set to any local address. join: ipAddress Join the multicast socket at the given IP address leave: ipAddress Leave the multicast socket at the given IP address nextPut: packet timeToLive: timeToLive Send the datagram with a specific TTL (time-to-live) timeToLive Answer the socket's datagrams' default time-to-live timeToLive: newTTL Set the default time-to-live for the socket's datagrams  File: gst-libs.info, Node: Sockets.MulticastSocketImpl, Next: Sockets.OOBSocketImpl, Prev: Sockets.MulticastSocket, Up: Sockets package 6.14 Sockets.MulticastSocketImpl ================================ Defined in namespace Sockets Superclass: Sockets.DatagramSocketImpl Category: Sockets-Protocols This abstract class serves as the parent class for datagram socket implementations that support multicast. * Menu: * Sockets.MulticastSocketImpl-multicasting:: (instance)  File: gst-libs.info, Node: Sockets.MulticastSocketImpl-multicasting, Up: Sockets.MulticastSocketImpl 6.14.1 Sockets.MulticastSocketImpl: multicasting ------------------------------------------------ ipMulticastIf Answer the local device for a multicast socket (in the form of an address) ipMulticastIf: interface Set the local device for a multicast socket (in the form of an address, usually anyLocalAddress) join: ipAddress Join the multicast socket at the given address leave: ipAddress Leave the multicast socket at the given address timeToLive Answer the time to live of the datagrams sent through the receiver to a multicast socket. timeToLive: ttl Set the time to live of the datagrams sent through the receiver to a multicast socket.  File: gst-libs.info, Node: Sockets.OOBSocketImpl, Next: Sockets.RawSocketImpl, Prev: Sockets.MulticastSocketImpl, Up: Sockets package 6.15 Sockets.OOBSocketImpl ========================== Defined in namespace Sockets Superclass: Sockets.DatagramSocketImpl Category: Sockets-Protocols This abstract class serves as the parent class for socket implementations that send out-of-band data over a stream socket. * Menu: * Sockets.OOBSocketImpl-C constants:: (instance) * Sockets.OOBSocketImpl-implementation:: (instance)  File: gst-libs.info, Node: Sockets.OOBSocketImpl-C constants, Next: Sockets.OOBSocketImpl-implementation, Up: Sockets.OOBSocketImpl 6.15.1 Sockets.OOBSocketImpl: C constants ----------------------------------------- msgOOB Not commented.  File: gst-libs.info, Node: Sockets.OOBSocketImpl-implementation, Prev: Sockets.OOBSocketImpl-C constants, Up: Sockets.OOBSocketImpl 6.15.2 Sockets.OOBSocketImpl: implementation -------------------------------------------- canRead Answer whether out-of-band data is available on the socket ensureReadable Stop the process until an error occurs or out-of-band data becomes available on the socket  File: gst-libs.info, Node: Sockets.RawSocketImpl, Next: Sockets.ReadBuffer, Prev: Sockets.OOBSocketImpl, Up: Sockets package 6.16 Sockets.RawSocketImpl ========================== Defined in namespace Sockets Superclass: Sockets.DatagramSocketImpl Category: Sockets-Protocols This abstract class serves as the parent class for raw socket implementations. Raw socket packets are modeled as datagrams. * Menu: * Sockets.RawSocketImpl class-parameters:: (class)  File: gst-libs.info, Node: Sockets.RawSocketImpl class-parameters, Up: Sockets.RawSocketImpl 6.16.1 Sockets.RawSocketImpl class: parameters ---------------------------------------------- socketType Answer the socket type parameter for `create'.  File: gst-libs.info, Node: Sockets.ReadBuffer, Next: Sockets.ServerSocket, Prev: Sockets.RawSocketImpl, Up: Sockets package 6.17 Sockets.ReadBuffer ======================= Defined in namespace Sockets Superclass: ReadStream Category: Examples-Useful tools I'm a ReadStream that, when the end of the stream is reached, evaluates an user defined block to try to get some more data. * Menu: * Sockets.ReadBuffer class-instance creation:: (class) * Sockets.ReadBuffer-accessing-reading:: (instance) * Sockets.ReadBuffer-buffer handling:: (instance)  File: gst-libs.info, Node: Sockets.ReadBuffer class-instance creation, Next: Sockets.ReadBuffer-accessing-reading, Up: Sockets.ReadBuffer 6.17.1 Sockets.ReadBuffer class: instance creation -------------------------------------------------- on: aCollection Answer a Stream that uses aCollection as a buffer. You should ensure that the fillBlock is set before the first operation, because the buffer will report that the data has ended until you set the fillBlock.  File: gst-libs.info, Node: Sockets.ReadBuffer-accessing-reading, Next: Sockets.ReadBuffer-buffer handling, Prev: Sockets.ReadBuffer class-instance creation, Up: Sockets.ReadBuffer 6.17.2 Sockets.ReadBuffer: accessing-reading -------------------------------------------- nextAvailable: anInteger into: aCollection startingAt: pos Place the next anInteger objects from the receiver into aCollection, starting at position pos. Return the number of items stored. nextAvailable: anInteger putAllOn: aStream Copy the next anInteger objects from the receiver to aStream. Return the number of items stored. upTo: anObject Returns a collection of the same type that the stream accesses, up to but not including the object anObject. Returns the entire rest of the stream's contents if anObject is not present. upToEnd Returns a collection of the same type that the stream accesses, up to but not including the object anObject. Returns the entire rest of the stream's contents if anObject is not present.  File: gst-libs.info, Node: Sockets.ReadBuffer-buffer handling, Prev: Sockets.ReadBuffer-accessing-reading, Up: Sockets.ReadBuffer 6.17.3 Sockets.ReadBuffer: buffer handling ------------------------------------------ atEnd Answer whether the data stream has ended. availableBytes Answer how many bytes are available in the buffer. bufferContents Answer the data that is in the buffer, and empty it. close Not commented. fill Fill the buffer with more data if it is empty, and answer true if the fill block was able to read more data. fillBlock: block Set the block that fills the buffer. It receives a collection and the number of bytes to fill in it, and must return the number of bytes actually read isEmpty Answer whether the next input operation will force a buffer fill isFull Answer whether the buffer has been just filled notEmpty Check whether the next input operation will force a buffer fill and answer true if it will not. pastEnd Try to fill the buffer if the data stream has ended.  File: gst-libs.info, Node: Sockets.ServerSocket, Next: Sockets.Socket, Prev: Sockets.ReadBuffer, Up: Sockets package 6.18 Sockets.ServerSocket ========================= Defined in namespace Sockets Superclass: Sockets.AbstractSocket Category: Sockets-Streams This class models server side sockets. The basic model is that the server socket is created and bound to some well known port. It then listens for and accepts connections. At that point the client and server sockets are ready to communicate with one another utilizing whatever application layer protocol they desire. As with the other AbstractSocket subclasses, most instance methods of this class simply redirect their calls to an implementation class. * Menu: * Sockets.ServerSocket class-accessing:: (class) * Sockets.ServerSocket class-instance creation:: (class) * Sockets.ServerSocket-accessing:: (instance) * Sockets.ServerSocket-initializing:: (instance)  File: gst-libs.info, Node: Sockets.ServerSocket class-accessing, Next: Sockets.ServerSocket class-instance creation, Up: Sockets.ServerSocket 6.18.1 Sockets.ServerSocket class: accessing -------------------------------------------- defaultImplementationClassFor: aSocketAddressClass Answer the default implementation class.  File: gst-libs.info, Node: Sockets.ServerSocket class-instance creation, Next: Sockets.ServerSocket-accessing, Prev: Sockets.ServerSocket class-accessing, Up: Sockets.ServerSocket 6.18.2 Sockets.ServerSocket class: instance creation ---------------------------------------------------- defaultQueueSize Answer the default length of the queue for pending connections. When the queue fills, new clients attempting to connect fail until the server has sent #accept to accept a connection from the queue. port: anInteger Answer a new ServerSocket serving on any local address, on the given port, with a pending connections queue of the default length. port: anInteger bindTo: ipAddress Answer a new ServerSocket serving on the given address and port, with a pending connections queue of the default length. port: anInteger queueSize: backlog Answer a new ServerSocket serving on any local address, on the given port, with a pending connections queue of the given length. port: anInteger queueSize: backlog bindTo: ipAddress Answer a new ServerSocket serving on the given address and port, and with a pending connections queue of the given length. queueSize: backlog Answer a new ServerSocket serving on any local address and port, with a pending connections queue of the given length. queueSize: backlog bindTo: ipAddress Answer a new ServerSocket serving on the given local address, and on any port, with a pending connections queue of the given length.  File: gst-libs.info, Node: Sockets.ServerSocket-accessing, Next: Sockets.ServerSocket-initializing, Prev: Sockets.ServerSocket class-instance creation, Up: Sockets.ServerSocket 6.18.3 Sockets.ServerSocket: accessing -------------------------------------- accept Accept a new connection and create a new instance of Socket if there is one, else answer nil. accept: socketClass Accept a new connection and create a new instance of socketClass if there is one, else answer nil. This is usually needed only to create DatagramSockets. address Answer the local address port Answer the local port (the port that the passive socket is listening on). primAccept: socketClass Accept a new connection and create a new instance of Socket if there is one, else fail. waitForConnection Wait for a connection to be available, and suspend the currently executing process in the meanwhile.  File: gst-libs.info, Node: Sockets.ServerSocket-initializing, Prev: Sockets.ServerSocket-accessing, Up: Sockets.ServerSocket 6.18.4 Sockets.ServerSocket: initializing ----------------------------------------- port: anInteger queueSize: backlog bindTo: localAddr Initialize the ServerSocket so that it serves on the given address and port, and has a pending connections queue of the given length.  File: gst-libs.info, Node: Sockets.Socket, Next: Sockets.SocketAddress, Prev: Sockets.ServerSocket, Up: Sockets package 6.19 Sockets.Socket =================== Defined in namespace Sockets Superclass: Sockets.StreamSocket Category: Sockets-Streams This class adds read and write buffers to the basic model of AbstractSocket. * Menu: * Sockets.Socket class-accessing:: (class) * Sockets.Socket class-tests:: (class) * Sockets.Socket class-well known ports:: (class) * Sockets.Socket-stream protocol:: (instance)  File: gst-libs.info, Node: Sockets.Socket class-accessing, Next: Sockets.Socket class-tests, Up: Sockets.Socket 6.19.1 Sockets.Socket class: accessing -------------------------------------- writeBufferSize Answer the size of the write buffer for newly-created sockets writeBufferSize: anInteger Set the size of the write buffer for newly-created sockets  File: gst-libs.info, Node: Sockets.Socket class-tests, Next: Sockets.Socket class-well known ports, Prev: Sockets.Socket class-accessing, Up: Sockets.Socket 6.19.2 Sockets.Socket class: tests ---------------------------------- datagramLoopbackTest Send data from one datagram socket to another on the local machine. Tests most of the socket primitives and works with different processes. datagramLoopbackTestOn: addressClass Send data from one datagram socket to another on the local machine. Tests most of the socket primitives and works with different processes. loopbackTest Send data from one socket to another on the local machine. Tests most of the socket primitives. loopbackTest: bufferSizes Send data from one socket to another on the local machine. Tests most of the socket primitives. The parameter is the size of the input and output buffer sizes. loopbackTest: bufferSizes addressClass: addressClass Send data from one socket to another on the local machine. Tests most of the socket primitives. The parameters are the size of the input and output buffer sizes, and the address class (family) to use. loopbackTestOn: addressClass Send data from one socket to another on the local machine. Tests most of the socket primitives. The parameter is the address class (family) to use. microTest Extremely small test (try to receive SMTP header) producerConsumerTest Send data from one datagram socket to another on the local machine. Tests most of the socket primitives and works with different processes. producerConsumerTestOn: addressClass Send data from one socket to another on the local machine. Tests most of the socket primitives and works with different processes. sendTest Send data to the 'discard' socket of localhost. sendTest: host Send data to the 'discard' socket of the given host. Tests the speed of one-way data transfers across the network to the given host. Note that many hosts do not run a discard server. testPort2For: anAddressClass Not commented. testPortFor: anAddressClass Not commented. tweakedLoopbackTest Send data from one socket to another on the local machine, trying to avoid buffering overhead. Tests most of the socket primitives. Comparison of the results of loopbackTest and tweakedLoopbackTest should give a measure of the overhead of buffering when sending/receiving large quantities of data.  File: gst-libs.info, Node: Sockets.Socket class-well known ports, Next: Sockets.Socket-stream protocol, Prev: Sockets.Socket class-tests, Up: Sockets.Socket 6.19.3 Sockets.Socket class: well known ports --------------------------------------------- initialize Initialize the receiver's defaults  File: gst-libs.info, Node: Sockets.Socket-stream protocol, Prev: Sockets.Socket class-well known ports, Up: Sockets.Socket 6.19.4 Sockets.Socket: stream protocol -------------------------------------- canWrite Answer whether more data is available in the socket's read buffer or from the operating system. ensureWriteable Answer whether more data is available in the socket's read buffer or from the operating system. flush Flush the write buffer to the operating system next: n putAll: aCollection startingAt: pos Write aString to the socket; this acts as a bit-bucket when the socket is closed. This might yield control to other Smalltalk Processes. nextPut: char Write a character to the socket; this acts as a bit-bucket when the socket is closed. This might yield control to other Smalltalk Processes. writeBufferSize: size Create a new write buffer of the given size, flushing the old one is needed. This might yield control to other Smalltalk Processes.  File: gst-libs.info, Node: Sockets.SocketAddress, Next: Sockets.SocketImpl, Prev: Sockets.Socket, Up: Sockets package 6.20 Sockets.SocketAddress ========================== Defined in namespace Sockets Superclass: Object Category: Sockets-Protocols This class is the abstract class for machine addresses over a network. It also fulfills the function of the C style functions gethostname(), gethostbyname(), and gethostbyaddr(), resolves machine names into their corresponding numeric addresses (via DNS, /etc/hosts, or other mechanisms) and vice versa. * Menu: * Sockets.SocketAddress class-abstract:: (class) * Sockets.SocketAddress class-accessing:: (class) * Sockets.SocketAddress class-C call-outs:: (class) * Sockets.SocketAddress class-C constants:: (class) * Sockets.SocketAddress class-creating sockets:: (class) * Sockets.SocketAddress class-host name lookup:: (class) * Sockets.SocketAddress class-initialization:: (class) * Sockets.SocketAddress-accessing:: (instance) * Sockets.SocketAddress-testing:: (instance)  File: gst-libs.info, Node: Sockets.SocketAddress class-abstract, Next: Sockets.SocketAddress class-accessing, Up: Sockets.SocketAddress 6.20.1 Sockets.SocketAddress class: abstract -------------------------------------------- extractFromSockAddr: aByteArray port: portAdaptor Private - Answer a new SocketAddress from a ByteArray containing a C sockaddr structure. The portAdaptor's value is changed to contain the port that the structure refers to. fromSockAddr: aByteArray port: portAdaptor Private - Answer a new IPAddress from a ByteArray containing a C sockaddr structure. The portAdaptor's value is changed to contain the port that the structure refers to. Raise an error if the address family is unknown.  File: gst-libs.info, Node: Sockets.SocketAddress class-accessing, Next: Sockets.SocketAddress class-C call-outs, Prev: Sockets.SocketAddress class-abstract, Up: Sockets.SocketAddress 6.20.2 Sockets.SocketAddress class: accessing --------------------------------------------- anyLocalAddress Answer an IPAddress representing a local address. at: host cache: aBlock Private - Answer the list of addresses associated to the given host in the cache. If the host is not cached yet, evaluate aBlock and cache and answer the result. defaultDatagramSocketImplClass Answer the class that, by default, is used to map between the Socket's protocol and a low-level C interface. defaultDatagramSocketImplClass: aClass Set which class will be used by default to map between the receiver's protocol and a low-level C interface. defaultRawSocketImplClass Answer the class that, by default, is used to map between the Socket's protocol and a low-level C interface. defaultRawSocketImplClass: aClass Set which class will be used by default to map between the receiver's protocol and a low-level C interface. defaultStreamSocketImplClass Answer the class that, by default, is used to map between the Socket's protocol and a low-level C interface. defaultStreamSocketImplClass: aClass Set which class will be used by default to map between the receiver's protocol and a low-level C interface. isDigitAddress: aString Answer whether the receiver can interpret aString as a valid address without going through a resolver. localHostName Answer the name of the local machine. loopbackHost Answer an instance of the receiver representing the local machine (127.0.0.1 in the IPv4 family). unknownAddress Answer an instance of the receiver representing an unknown machine (0.0.0.0 in the IPv4 family).  File: gst-libs.info, Node: Sockets.SocketAddress class-C call-outs, Next: Sockets.SocketAddress class-C constants, Prev: Sockets.SocketAddress class-accessing, Up: Sockets.SocketAddress 6.20.3 Sockets.SocketAddress class: C call-outs ----------------------------------------------- primLocalName Not commented. primName: address len: len type: addressFamily Not commented.  File: gst-libs.info, Node: Sockets.SocketAddress class-C constants, Next: Sockets.SocketAddress class-creating sockets, Prev: Sockets.SocketAddress class-C call-outs, Up: Sockets.SocketAddress 6.20.4 Sockets.SocketAddress class: C constants ----------------------------------------------- addressFamily Not commented. aiAddrconfig Not commented. aiCanonname Not commented. protocolFamily Not commented.  File: gst-libs.info, Node: Sockets.SocketAddress class-creating sockets, Next: Sockets.SocketAddress class-host name lookup, Prev: Sockets.SocketAddress class-C constants, Up: Sockets.SocketAddress 6.20.5 Sockets.SocketAddress class: creating sockets ---------------------------------------------------- newRawSocket Create a new raw socket, providing access to low-level network protocols and interfaces for the protocol family represented by the receiver (for example, the C protocol family PF_INET for the IPAddress class) Ordinary user programs usually have no need to use this method.  File: gst-libs.info, Node: Sockets.SocketAddress class-host name lookup, Next: Sockets.SocketAddress class-initialization, Prev: Sockets.SocketAddress class-creating sockets, Up: Sockets.SocketAddress 6.20.6 Sockets.SocketAddress class: host name lookup ---------------------------------------------------- allByName: aString Answer all the IP addresses that refer to the the given host. If a digit address is passed in aString, the result is an array containing the single passed address. If the host could not be resolved to an IP address, answer nil. byName: aString Answer a single IP address that refer to the the given host. If a digit address is passed in aString, the result is the same as using #fromString:. If the host could not be resolved to an IP address, answer nil.  File: gst-libs.info, Node: Sockets.SocketAddress class-initialization, Next: Sockets.SocketAddress-accessing, Prev: Sockets.SocketAddress class-host name lookup, Up: Sockets.SocketAddress 6.20.7 Sockets.SocketAddress class: initialization -------------------------------------------------- anyLocalAddress: anObject Private - Store an object representing a local address in the address family for the receiver createLoopbackHost Answer an object representing the loopback host in the address family for the receiver. createUnknownAddress Answer an object representing an unkown address in the address family for the receiver flush Flush the cached IP addresses. initLocalAddresses Private - Initialize the anyLocalAddress class-instance variable for the entire hierarchy. update: aspect Flush all the caches for IPAddress subclasses  File: gst-libs.info, Node: Sockets.SocketAddress-accessing, Next: Sockets.SocketAddress-testing, Prev: Sockets.SocketAddress class-initialization, Up: Sockets.SocketAddress 6.20.8 Sockets.SocketAddress: accessing --------------------------------------- = aSocketAddress Answer whether the receiver and aSocketAddress represent the same machine. The host name is not checked because an IPAddress created before a DNS is activated is named after its numbers-and-dots notation, while the same IPAddress, created when a DNS is active, is named after its resolved name. asByteArray Convert the receiver to a ByteArray passed to the operating system's socket functions) hash Answer an hash value for the receiver name Answer the host name (or the digit notation if the DNS could not resolve the address). If the DNS answers a different IP address for the same name, the second response is not cached and the digit notation is also returned (somebody's likely playing strange jokes with your DNS).  File: gst-libs.info, Node: Sockets.SocketAddress-testing, Prev: Sockets.SocketAddress-accessing, Up: Sockets.SocketAddress 6.20.9 Sockets.SocketAddress: testing ------------------------------------- isMulticast Answer whether an address is reserved for multicast connections.  File: gst-libs.info, Node: Sockets.SocketImpl, Next: Sockets.StreamSocket, Prev: Sockets.SocketAddress, Up: Sockets package 6.21 Sockets.SocketImpl ======================= Defined in namespace Sockets Superclass: Sockets.AbstractSocketImpl Category: Sockets-Protocols This abstract class serves as the parent class for stream socket implementations. * Menu: * Sockets.SocketImpl class-parameters:: (class) * Sockets.SocketImpl-abstract:: (instance) * Sockets.SocketImpl-socket operations:: (instance)  File: gst-libs.info, Node: Sockets.SocketImpl class-parameters, Next: Sockets.SocketImpl-abstract, Up: Sockets.SocketImpl 6.21.1 Sockets.SocketImpl class: parameters ------------------------------------------- socketType Answer the socket type parameter for `create'.  File: gst-libs.info, Node: Sockets.SocketImpl-abstract, Next: Sockets.SocketImpl-socket operations, Prev: Sockets.SocketImpl class-parameters, Up: Sockets.SocketImpl 6.21.2 Sockets.SocketImpl: abstract ----------------------------------- outOfBandImplClass Return an implementation class to be used for out-of-band data on the receiver.  File: gst-libs.info, Node: Sockets.SocketImpl-socket operations, Prev: Sockets.SocketImpl-abstract, Up: Sockets.SocketImpl 6.21.3 Sockets.SocketImpl: socket operations -------------------------------------------- connectTo: ipAddress port: port Try to connect the socket represented by the receiver to the given remote machine. getPeerName Retrieve a ByteArray containing a sockaddr_in struct for the remote endpoint of the socket.  File: gst-libs.info, Node: Sockets.StreamSocket, Next: Sockets.TCPSocketImpl, Prev: Sockets.SocketImpl, Up: Sockets package 6.22 Sockets.StreamSocket ========================= Defined in namespace Sockets Superclass: Sockets.AbstractSocket Category: Sockets-Streams This class adds a read buffer to the basic model of AbstractSocket. * Menu: * Sockets.StreamSocket class-accessing:: (class) * Sockets.StreamSocket class-initialize:: (class) * Sockets.StreamSocket class-instance creation:: (class) * Sockets.StreamSocket-accessing:: (instance) * Sockets.StreamSocket-accessing-reading:: (instance) * Sockets.StreamSocket-out-of-band data:: (instance) * Sockets.StreamSocket-printing:: (instance) * Sockets.StreamSocket-stream protocol:: (instance)  File: gst-libs.info, Node: Sockets.StreamSocket class-accessing, Next: Sockets.StreamSocket class-initialize, Up: Sockets.StreamSocket 6.22.1 Sockets.StreamSocket class: accessing -------------------------------------------- defaultImplementationClassFor: aSocketAddressClass Answer the default implementation class. Depending on the subclass, this might be the default stream socket implementation class of the given address class, or rather its default datagram socket implementation class. readBufferSize Answer the size of the read buffer for newly-created sockets readBufferSize: anInteger Set the size of the read buffer for newly-created sockets  File: gst-libs.info, Node: Sockets.StreamSocket class-initialize, Next: Sockets.StreamSocket class-instance creation, Prev: Sockets.StreamSocket class-accessing, Up: Sockets.StreamSocket 6.22.2 Sockets.StreamSocket class: initialize --------------------------------------------- initialize Initialize the receiver's defaults  File: gst-libs.info, Node: Sockets.StreamSocket class-instance creation, Next: Sockets.StreamSocket-accessing, Prev: Sockets.StreamSocket class-initialize, Up: Sockets.StreamSocket 6.22.3 Sockets.StreamSocket class: instance creation ---------------------------------------------------- remote: ipAddressOrString port: remotePort Create a new socket and connect to the given host (passed as a String to be resolved or as a SocketAddress), and to the given port. remote: ipAddressOrString port: remotePort local: ipAddress port: localPort Create a new socket and connect to the given host (passed as a String to be resolved or as a SocketAddress), and to the given remotePort. Then bind it to the local address passed in ipAddress, on the localPort port; if the former is nil, any local address will do, and if the latter is 0, any local port will do.  File: gst-libs.info, Node: Sockets.StreamSocket-accessing, Next: Sockets.StreamSocket-accessing-reading, Prev: Sockets.StreamSocket class-instance creation, Up: Sockets.StreamSocket 6.22.4 Sockets.StreamSocket: accessing -------------------------------------- address Answer the address of the remote endpoint port Answer the port of the remote endpoint  File: gst-libs.info, Node: Sockets.StreamSocket-accessing-reading, Next: Sockets.StreamSocket-out-of-band data, Prev: Sockets.StreamSocket-accessing, Up: Sockets.StreamSocket 6.22.5 Sockets.StreamSocket: accessing-reading ---------------------------------------------- nextAvailable: anInteger into: aCollection startingAt: pos Place up to anInteger objects from the receiver into aCollection, starting from position pos and stopping if no more data is available. nextAvailable: anInteger putAllOn: aStream Copy up to anInteger objects from the receiver to aStream, stopping if no more data is available.  File: gst-libs.info, Node: Sockets.StreamSocket-out-of-band data, Next: Sockets.StreamSocket-printing, Prev: Sockets.StreamSocket-accessing-reading, Up: Sockets.StreamSocket 6.22.6 Sockets.StreamSocket: out-of-band data --------------------------------------------- outOfBand Return a datagram socket to be used for receiving out-of-band data on the receiver.  File: gst-libs.info, Node: Sockets.StreamSocket-printing, Next: Sockets.StreamSocket-stream protocol, Prev: Sockets.StreamSocket-out-of-band data, Up: Sockets.StreamSocket 6.22.7 Sockets.StreamSocket: printing ------------------------------------- printOn: aStream Print a representation of the receiver on aStream  File: gst-libs.info, Node: Sockets.StreamSocket-stream protocol, Prev: Sockets.StreamSocket-printing, Up: Sockets.StreamSocket 6.22.8 Sockets.StreamSocket: stream protocol -------------------------------------------- atEnd Answer whether more data is available on the socket availableBytes Answer how many bytes are available in the socket's read buffer or from the operating system. bufferContents Answer the current contents of the read buffer canRead Answer whether more data is available in the socket's read buffer or from the operating system. close Flush and close the socket. fill Fill the read buffer with data read from the socket isPeerAlive Answer whether the connection with the peer remote machine is still valid. next Read a byte from the socket. This might yield control to other Smalltalk Processes. peek Read a byte from the socket, without advancing the buffer; answer nil if no more data is available. This might yield control to other Smalltalk Processes. peekFor: anObject Read a byte from the socket, advancing the buffer only if it matches anObject; answer whether they did match or not. This might yield control to other Smalltalk Processes. readBufferSize: size Create a new read buffer of the given size (which is only possible before the first read or if the current buffer is empty).  File: gst-libs.info, Node: Sockets.TCPSocketImpl, Next: Sockets.UDPSocketImpl, Prev: Sockets.StreamSocket, Up: Sockets package 6.23 Sockets.TCPSocketImpl ========================== Defined in namespace Sockets Superclass: Sockets.SocketImpl Category: Sockets-Protocols Unless the application installs its own implementation, this is the default socket implementation that will be used for IPv4 stream sockets. It uses C call-outs to implement standard BSD style sockets of family AF_INET and type SOCK_STREAM. * Menu: * Sockets.TCPSocketImpl class-C constants:: (class) * Sockets.TCPSocketImpl-socket options:: (instance)  File: gst-libs.info, Node: Sockets.TCPSocketImpl class-C constants, Next: Sockets.TCPSocketImpl-socket options, Up: Sockets.TCPSocketImpl 6.23.1 Sockets.TCPSocketImpl class: C constants ----------------------------------------------- ipprotoTcp Not commented. protocol Not commented. tcpNodelay Not commented.  File: gst-libs.info, Node: Sockets.TCPSocketImpl-socket options, Prev: Sockets.TCPSocketImpl class-C constants, Up: Sockets.TCPSocketImpl 6.23.2 Sockets.TCPSocketImpl: socket options -------------------------------------------- valueWithoutBuffering: aBlock Evaluate aBlock, ensuring that any data that it writes to the socket is sent immediately to the network.  File: gst-libs.info, Node: Sockets.UDPSocketImpl, Next: Sockets.UnixAddress, Prev: Sockets.TCPSocketImpl, Up: Sockets package 6.24 Sockets.UDPSocketImpl ========================== Defined in namespace Sockets Superclass: Sockets.MulticastSocketImpl Category: Sockets-Protocols Unless the application installs its own implementation, this is the default socket implementation that will be used for IPv4 datagram sockets. It uses C call-outs to implement standard BSD style sockets of family AF_INET and type SOCK_DGRAM. * Menu: * Sockets.UDPSocketImpl class-C constants:: (class) * Sockets.UDPSocketImpl-multicasting:: (instance)  File: gst-libs.info, Node: Sockets.UDPSocketImpl class-C constants, Next: Sockets.UDPSocketImpl-multicasting, Up: Sockets.UDPSocketImpl 6.24.1 Sockets.UDPSocketImpl class: C constants ----------------------------------------------- ipprotoIp Not commented. protocol Not commented.  File: gst-libs.info, Node: Sockets.UDPSocketImpl-multicasting, Prev: Sockets.UDPSocketImpl class-C constants, Up: Sockets.UDPSocketImpl 6.24.2 Sockets.UDPSocketImpl: multicasting ------------------------------------------ ipMulticastIf Answer the local device for a multicast socket (in the form of an address) ipMulticastIf: interface Set the local device for a multicast socket (in the form of an address, usually anyLocalAddress) join: ipAddress Join the multicast socket at the given address leave: ipAddress Leave the multicast socket at the given address primJoinLeave: ipAddress option: opt Private - Used to join or leave a multicast service. timeToLive Answer the time to live of the datagrams sent through the receiver to a multicast socket. timeToLive: ttl Set the time to live of the datagrams sent through the receiver to a multicast socket.  File: gst-libs.info, Node: Sockets.UnixAddress, Next: Sockets.UnixDatagramSocketImpl, Prev: Sockets.UDPSocketImpl, Up: Sockets package 6.25 Sockets.UnixAddress ======================== Defined in namespace Sockets Superclass: Sockets.SocketAddress Category: Sockets-Protocols This class represents an address for a machine using the AF_UNIX address family. Since this address family is only used for local sockets, the class is a singleton; the filesystem path to the socket is represented using the port argument to socket functions, as either a String or a File object. * Menu: * Sockets.UnixAddress class-C constants:: (class) * Sockets.UnixAddress class-initialization:: (class) * Sockets.UnixAddress class-instance creation:: (class) * Sockets.UnixAddress-accessing:: (instance) * Sockets.UnixAddress-printing:: (instance) * Sockets.UnixAddress-testing:: (instance)  File: gst-libs.info, Node: Sockets.UnixAddress class-C constants, Next: Sockets.UnixAddress class-initialization, Up: Sockets.UnixAddress 6.25.1 Sockets.UnixAddress class: C constants --------------------------------------------- addressFamily Not commented. protocolFamily Not commented.  File: gst-libs.info, Node: Sockets.UnixAddress class-initialization, Next: Sockets.UnixAddress class-instance creation, Prev: Sockets.UnixAddress class-C constants, Up: Sockets.UnixAddress 6.25.2 Sockets.UnixAddress class: initialization ------------------------------------------------ createLoopbackHost Answer an object representing the loopback host in the address family for the receiver. This is 127.0.0.1 for IPv4. createUnknownAddress Answer an object representing an unkown address in the address family for the receiver initialize Set up the default implementation classes for the receiver  File: gst-libs.info, Node: Sockets.UnixAddress class-instance creation, Next: Sockets.UnixAddress-accessing, Prev: Sockets.UnixAddress class-initialization, Up: Sockets.UnixAddress 6.25.3 Sockets.UnixAddress class: instance creation --------------------------------------------------- fromSockAddr: aByteArray port: portAdaptor Private - Answer the unique UnixAddress instance, filling in the portAdaptor's value from a ByteArray containing a C sockaddr_in structure. uniqueInstance Not commented.  File: gst-libs.info, Node: Sockets.UnixAddress-accessing, Next: Sockets.UnixAddress-printing, Prev: Sockets.UnixAddress class-instance creation, Up: Sockets.UnixAddress 6.25.4 Sockets.UnixAddress: accessing ------------------------------------- = aSocketAddress Answer whether the receiver and aSocketAddress represent the same socket on the same machine. hash Answer an hash value for the receiver  File: gst-libs.info, Node: Sockets.UnixAddress-printing, Next: Sockets.UnixAddress-testing, Prev: Sockets.UnixAddress-accessing, Up: Sockets.UnixAddress 6.25.5 Sockets.UnixAddress: printing ------------------------------------ printOn: aStream Print the receiver in dot notation.  File: gst-libs.info, Node: Sockets.UnixAddress-testing, Prev: Sockets.UnixAddress-printing, Up: Sockets.UnixAddress 6.25.6 Sockets.UnixAddress: testing ----------------------------------- isMulticast Answer whether an address is reserved for multicast connections.  File: gst-libs.info, Node: Sockets.UnixDatagramSocketImpl, Next: Sockets.UnixSocketImpl, Prev: Sockets.UnixAddress, Up: Sockets package 6.26 Sockets.UnixDatagramSocketImpl =================================== Defined in namespace Sockets Superclass: Sockets.DatagramSocketImpl Category: Sockets-Protocols This class represents a datagram socket using the AF_UNIX address family. It unlinks the filesystem path when the socket is closed. * Menu: * Sockets.UnixDatagramSocketImpl-socket operations:: (instance)  File: gst-libs.info, Node: Sockets.UnixDatagramSocketImpl-socket operations, Up: Sockets.UnixDatagramSocketImpl 6.26.1 Sockets.UnixDatagramSocketImpl: socket operations -------------------------------------------------------- close Not commented.  File: gst-libs.info, Node: Sockets.UnixSocketImpl, Next: Sockets.WriteBuffer, Prev: Sockets.UnixDatagramSocketImpl, Up: Sockets package 6.27 Sockets.UnixSocketImpl =========================== Defined in namespace Sockets Superclass: Sockets.SocketImpl Category: Sockets-Protocols This class represents a stream socket using the AF_UNIX address family. It unlinks the filesystem path when the socket is closed. * Menu: * Sockets.UnixSocketImpl-socket operations:: (instance)  File: gst-libs.info, Node: Sockets.UnixSocketImpl-socket operations, Up: Sockets.UnixSocketImpl 6.27.1 Sockets.UnixSocketImpl: socket operations ------------------------------------------------ close Not commented.  File: gst-libs.info, Node: Sockets.WriteBuffer, Prev: Sockets.UnixSocketImpl, Up: Sockets package 6.28 Sockets.WriteBuffer ======================== Defined in namespace Sockets Superclass: WriteStream Category: Examples-Useful tools I'm a WriteStream that, instead of growing the collection, evaluates an user defined block and starts over with the same collection. * Menu: * Sockets.WriteBuffer-accessing-writing:: (instance) * Sockets.WriteBuffer-buffer handling:: (instance) * Sockets.WriteBuffer-testing:: (instance)  File: gst-libs.info, Node: Sockets.WriteBuffer-accessing-writing, Next: Sockets.WriteBuffer-buffer handling, Up: Sockets.WriteBuffer 6.28.1 Sockets.WriteBuffer: accessing-writing --------------------------------------------- next: n putAll: aCollection startingAt: pos Put n characters or bytes of aCollection, starting at the pos-th, in the collection buffer.  File: gst-libs.info, Node: Sockets.WriteBuffer-buffer handling, Next: Sockets.WriteBuffer-testing, Prev: Sockets.WriteBuffer-accessing-writing, Up: Sockets.WriteBuffer 6.28.2 Sockets.WriteBuffer: buffer handling ------------------------------------------- close Not commented. flush Evaluate the flushing block and reset the stream flushBlock: block Set which block will be used to flush the buffer. The block will be evaluated with a collection and an Integer n as parameters, and will have to write the first n elements of the collection.  File: gst-libs.info, Node: Sockets.WriteBuffer-testing, Prev: Sockets.WriteBuffer-buffer handling, Up: Sockets.WriteBuffer 6.28.3 Sockets.WriteBuffer: testing ----------------------------------- isFull Not commented.  File: gst-libs.info, Node: ZLib package, Next: Class index, Prev: XML/XPath/XSL packages, Up: Top 7 Compressing and decompressing data with ZLib ********************************************** * Menu: Alphabetic list: * ZLib.DeflateStream:: * ZLib.DeflateWriteStream:: * ZLib.GZipDeflateStream:: * ZLib.GZipDeflateWriteStream:: * ZLib.GZipInflateStream:: * ZLib.InflateStream:: * ZLib.RawDeflateStream:: * ZLib.RawDeflateWriteStream:: * ZLib.RawInflateStream:: * ZLib.ZlibError:: * ZLib.ZlibReadStream:: * ZLib.ZlibStream:: * ZLib.ZlibWriteStream:: Class tree: (Object) (Exception) (Error) * ZLib.ZlibError:: (Iterable) (Stream) * ZLib.ZlibStream:: * ZLib.ZlibReadStream:: * ZLib.RawDeflateStream:: * ZLib.DeflateStream:: * ZLib.GZipDeflateStream:: * ZLib.RawInflateStream:: * ZLib.GZipInflateStream:: * ZLib.InflateStream:: * ZLib.ZlibWriteStream:: * ZLib.RawDeflateWriteStream:: * ZLib.DeflateWriteStream:: * ZLib.GZipDeflateWriteStream::  File: gst-libs.info, Node: ZLib.DeflateStream, Next: ZLib.DeflateWriteStream, Up: ZLib package 7.1 ZLib.DeflateStream ====================== Defined in namespace ZLib Superclass: ZLib.RawDeflateStream Category: Examples-Useful Instances of this class produce "standard" (zlib, RFC1950) deflated data. * Menu: * ZLib.DeflateStream class-instance creation:: (class)  File: gst-libs.info, Node: ZLib.DeflateStream class-instance creation, Up: ZLib.DeflateStream 7.1.1 ZLib.DeflateStream class: instance creation ------------------------------------------------- compressingTo: aStream Answer a stream that receives data via #nextPut: and compresses it onto aStream. compressingTo: aStream level: level Answer a stream that receives data via #nextPut: and compresses it onto aStream with the given compression level.  File: gst-libs.info, Node: ZLib.DeflateWriteStream, Next: ZLib.GZipDeflateStream, Prev: ZLib.DeflateStream, Up: ZLib package 7.2 ZLib.DeflateWriteStream =========================== Defined in namespace ZLib Superclass: ZLib.RawDeflateWriteStream Category: Examples-Useful Instances of this class produce "standard" (zlib, RFC1950) deflated data. * Menu:  File: gst-libs.info, Node: ZLib.GZipDeflateStream, Next: ZLib.GZipDeflateWriteStream, Prev: ZLib.DeflateWriteStream, Up: ZLib package 7.3 ZLib.GZipDeflateStream ========================== Defined in namespace ZLib Superclass: ZLib.RawDeflateStream Category: Examples-Useful Instances of this class produce GZip (RFC1952) deflated data. * Menu: * ZLib.GZipDeflateStream class-instance creation:: (class)  File: gst-libs.info, Node: ZLib.GZipDeflateStream class-instance creation, Up: ZLib.GZipDeflateStream 7.3.1 ZLib.GZipDeflateStream class: instance creation ----------------------------------------------------- compressingTo: aStream Answer a stream that receives data via #nextPut: and compresses it onto aStream. compressingTo: aStream level: level Answer a stream that receives data via #nextPut: and compresses it onto aStream with the given compression level.  File: gst-libs.info, Node: ZLib.GZipDeflateWriteStream, Next: ZLib.GZipInflateStream, Prev: ZLib.GZipDeflateStream, Up: ZLib package 7.4 ZLib.GZipDeflateWriteStream =============================== Defined in namespace ZLib Superclass: ZLib.RawDeflateWriteStream Category: Examples-Useful Instances of this class produce GZip (RFC1952) deflated data. * Menu:  File: gst-libs.info, Node: ZLib.GZipInflateStream, Next: ZLib.InflateStream, Prev: ZLib.GZipDeflateWriteStream, Up: ZLib package 7.5 ZLib.GZipInflateStream ========================== Defined in namespace ZLib Superclass: ZLib.RawInflateStream Category: Examples-Useful Instances of this class reinflate GZip (RFC1952) deflated data. * Menu:  File: gst-libs.info, Node: ZLib.InflateStream, Next: ZLib.RawDeflateStream, Prev: ZLib.GZipInflateStream, Up: ZLib package 7.6 ZLib.InflateStream ====================== Defined in namespace ZLib Superclass: ZLib.RawInflateStream Category: Examples-Useful Instances of this class reinflate "standard" (zlib, RFC1950) deflated data. * Menu:  File: gst-libs.info, Node: ZLib.RawDeflateStream, Next: ZLib.RawDeflateWriteStream, Prev: ZLib.InflateStream, Up: ZLib package 7.7 ZLib.RawDeflateStream ========================= Defined in namespace ZLib Superclass: ZLib.ZlibReadStream Category: Examples-Useful Instances of this class produce "raw" (PKZIP) deflated data. * Menu: * ZLib.RawDeflateStream class-instance creation:: (class)  File: gst-libs.info, Node: ZLib.RawDeflateStream class-instance creation, Up: ZLib.RawDeflateStream 7.7.1 ZLib.RawDeflateStream class: instance creation ---------------------------------------------------- compressingTo: aStream Answer a stream that receives data via #nextPut: and compresses it onto aStream. compressingTo: aStream level: level Answer a stream that receives data via #nextPut: and compresses it onto aStream with the given compression level. on: aStream Answer a stream that compresses the data in aStream with the default compression level. on: aStream level: compressionLevel Answer a stream that compresses the data in aStream with the given compression level.  File: gst-libs.info, Node: ZLib.RawDeflateWriteStream, Next: ZLib.RawInflateStream, Prev: ZLib.RawDeflateStream, Up: ZLib package 7.8 ZLib.RawDeflateWriteStream ============================== Defined in namespace ZLib Superclass: ZLib.ZlibWriteStream Category: Examples-Useful Instances of this class produce "raw" (PKZIP) deflated data. * Menu: * ZLib.RawDeflateWriteStream class-instance creation:: (class)  File: gst-libs.info, Node: ZLib.RawDeflateWriteStream class-instance creation, Up: ZLib.RawDeflateWriteStream 7.8.1 ZLib.RawDeflateWriteStream class: instance creation --------------------------------------------------------- on: aWriteStream Answer a stream that compresses the data in aStream with the default compression level. on: aWriteStream level: compressionLevel Answer a stream that compresses the data in aStream with the given compression level.  File: gst-libs.info, Node: ZLib.RawInflateStream, Next: ZLib.ZlibError, Prev: ZLib.RawDeflateWriteStream, Up: ZLib package 7.9 ZLib.RawInflateStream ========================= Defined in namespace ZLib Superclass: ZLib.ZlibReadStream Category: Examples-Useful Instances of this class reinflate "raw" (PKZIP) deflated data. * Menu: * ZLib.RawInflateStream-positioning:: (instance)  File: gst-libs.info, Node: ZLib.RawInflateStream-positioning, Up: ZLib.RawInflateStream 7.9.1 ZLib.RawInflateStream: positioning ---------------------------------------- copyFrom: start to: end Answer the data on which the receiver is streaming, from the start-th item to the end-th. Note that this method is 0-based, unlike the one in Collection, because a Stream's #position method returns 0-based values. Notice that this class can only provide the illusion of random access, by appropriately rewinding the input stream or skipping compressed data. isPositionable Answer true if the stream supports moving backwards with #skip:. position: anInteger Set the current position in the stream to anInteger. Notice that this class can only provide the illusion of random access, by appropriately rewinding the input stream or skipping compressed data. reset Reset the stream to the beginning of the compressed data. skip: anInteger Move the current position by anInteger places, either forwards or backwards.  File: gst-libs.info, Node: ZLib.ZlibError, Next: ZLib.ZlibReadStream, Prev: ZLib.RawInflateStream, Up: ZLib package 7.10 ZLib.ZlibError =================== Defined in namespace ZLib Superclass: Error Category: Examples-Useful This exception is raised whenever there is an error in a compressed stream. * Menu: * ZLib.ZlibError-accessing:: (instance)  File: gst-libs.info, Node: ZLib.ZlibError-accessing, Up: ZLib.ZlibError 7.10.1 ZLib.ZlibError: accessing -------------------------------- stream Answer the ZlibStream that caused the error. stream: anObject Set the ZlibStream that caused the error.  File: gst-libs.info, Node: ZLib.ZlibReadStream, Next: ZLib.ZlibStream, Prev: ZLib.ZlibError, Up: ZLib package 7.11 ZLib.ZlibReadStream ======================== Defined in namespace ZLib Superclass: ZLib.ZlibStream Category: Examples-Useful This abstract class implements the basic buffering that is used for communication with zlib. * Menu: * ZLib.ZlibReadStream-accessing-reading:: (instance) * ZLib.ZlibReadStream-streaming:: (instance)  File: gst-libs.info, Node: ZLib.ZlibReadStream-accessing-reading, Next: ZLib.ZlibReadStream-streaming, Up: ZLib.ZlibReadStream 7.11.1 ZLib.ZlibReadStream: accessing-reading --------------------------------------------- nextAvailable: anInteger into: aCollection startingAt: pos Place up to anInteger objects from the receiver into aCollection, starting from position pos and stopping if no more data is available. nextAvailable: anInteger putAllOn: aStream Copy up to anInteger objects from the receiver to aStream, stopping if no more data is available.  File: gst-libs.info, Node: ZLib.ZlibReadStream-streaming, Prev: ZLib.ZlibReadStream-accessing-reading, Up: ZLib.ZlibReadStream 7.11.2 ZLib.ZlibReadStream: streaming ------------------------------------- atEnd Answer whether the stream has got to an end next Return the next object (character or byte) in the receiver. peek Returns the next element of the stream without moving the pointer. Returns nil when at end of stream. peekFor: anObject Returns true and gobbles the next element from the stream of it is equal to anObject, returns false and doesn't gobble the next element if the next element is not equal to anObject. position Answer the current value of the stream pointer. Note that only inflating streams support random access to the stream data.  File: gst-libs.info, Node: ZLib.ZlibStream, Next: ZLib.ZlibWriteStream, Prev: ZLib.ZlibReadStream, Up: ZLib package 7.12 ZLib.ZlibStream ==================== Defined in namespace ZLib Superclass: Stream Category: Examples-Useful This abstract class implements the basic interface to the zlib module. Its layout matches what is expected by the C code. * Menu: * ZLib.ZlibStream class-accessing:: (class) * ZLib.ZlibStream class-instance creation:: (class) * ZLib.ZlibStream-streaming:: (instance)  File: gst-libs.info, Node: ZLib.ZlibStream class-accessing, Next: ZLib.ZlibStream class-instance creation, Up: ZLib.ZlibStream 7.12.1 ZLib.ZlibStream class: accessing --------------------------------------- bufferSize Answer the size of the output buffers that are passed to zlib. Each zlib stream uses a buffer of this size. bufferSize: anInteger Set the size of the output buffers that are passed to zlib. Each zlib stream uses a buffer of this size. defaultCompressionLevel Return the default compression level used by deflating streams. defaultCompressionLevel: anInteger Set the default compression level used by deflating streams. It should be a number between 1 and 9.  File: gst-libs.info, Node: ZLib.ZlibStream class-instance creation, Next: ZLib.ZlibStream-streaming, Prev: ZLib.ZlibStream class-accessing, Up: ZLib.ZlibStream 7.12.2 ZLib.ZlibStream class: instance creation ----------------------------------------------- new This method should not be called for instances of this class. on: aStream Answer an instance of the receiver that decorates aStream.  File: gst-libs.info, Node: ZLib.ZlibStream-streaming, Prev: ZLib.ZlibStream class-instance creation, Up: ZLib.ZlibStream 7.12.3 ZLib.ZlibStream: streaming --------------------------------- isExternalStream Answer whether the receiver streams on a file or socket. name Return the name of the underlying stream. species Return the type of the collections returned by #upTo: etc. stream Answer the wrapped stream.  File: gst-libs.info, Node: ZLib.ZlibWriteStream, Prev: ZLib.ZlibStream, Up: ZLib package 7.13 ZLib.ZlibWriteStream ========================= Defined in namespace ZLib Superclass: ZLib.ZlibStream Category: Examples-Useful This abstract class implements the basic buffering that is used for communication with zlib in a WriteStream decorator. * Menu: * ZLib.ZlibWriteStream-streaming:: (instance)  File: gst-libs.info, Node: ZLib.ZlibWriteStream-streaming, Up: ZLib.ZlibWriteStream 7.13.1 ZLib.ZlibWriteStream: streaming -------------------------------------- close Finish the deflated output to the destination stream using Z_FINISH. The destination stream is closed, which implies flushing. contents Finish the deflated output to the destination stream using Z_FINISH and return the deflated data (requires the destination stream to support #contents). finish Finish the deflated output to the destination stream using Z_FINISH. The destination stream is not flushed. flush Flush the deflated output to the destination stream, and flush the destination stream. flushBuffer Flush the deflated output to the destination stream. flushDictionary Flush the deflated output to the destination stream using Z_FULL_FLUSH, and flush the destination stream. next: n putAll: aCollection startingAt: pos Put n characters or bytes of aCollection, starting at the pos-th, in the deflation buffer. nextPut: aByte Append a character or byte (depending on whether the destination stream works on a ByteArray or String) to the deflation buffer. partialFlush Flush the deflated output to the destination stream using Z_PARTIAL_FLUSH, and flush the destination stream. position Answer the number of compressed bytes written. readStream Finish the deflated output to the destination stream using Z_FINISH and return a ReadStream on the deflated data (requires the destination stream to support #readStream). syncFlush Flush the deflated output to the destination stream using Z_SYNC_FLUSH, and flush the destination stream. Note that this includes the four bytes 0/0/255/255 at the end of the flush.  File: gst-libs.info, Node: XML/XPath/XSL packages, Next: ZLib package, Prev: Iconv/I18N packages, Up: Top 8 Libraries for the SAX, DOM, XPath and XSLT standards ****************************************************** _by Thomas Gagne, edited by Paolo Bonzini_ * Menu: * Building a DOM from XML:: * Building XML:: * Using DTDs:: * XSL Processing:: * Attributions::  File: gst-libs.info, Node: Building a DOM from XML, Next: Building XML, Up: XML/XPath/XSL packages 8.1 Building a DOM from XML =========================== If you're like me, the first thing you may be trying to do is build a Document Object Model (DOM) tree from some kind of XML input. Assuming you've got the XML in a String the following code will build an XML Document: XML.SAXParser defaultParserClass processDocumentString: theXMLString beforeScanDo: [ :p | p validate: false]. Though the code above appears as though it should be easy to use, there's some hidden features you should know about. First, `theXMLString' can not contain any null bytes. Depending on where your XML comes from it may have a NULL byte at the end (like mine did). Many languages implement strings as an array of bytes (usually printable ones) ending with a null (a character with integer value 0). In my case, the XML was coming from a remote client written in C using middleware to send the message to my server. Since the middleware doesn't assume to know anything about the message it received, it's received into a String, null-byte and all. To remove it I used: XML.SAXParser defaultParserClass processDocumentString: (aString copyWithout: 0 asCharacter) beforeScanDo: [ :p | p validate: false]. Starting out, I didn't know much about the value of DTDs either (Document Type Definitions), so I wasn't using them (more on why you should later). What you need to know is XML comes in two flavors, (three if you include broken as a flavor) _well-formed_ and _valid_. _Well-formed XML_ is simply XML following the basic rules, like only one top-level (the document's root), no overlapping tags, and a few other contraints. Valid XML means not only is the XML well-formed, but it's also compliant with some kind of rule base about which elements are allowed to follow which other ones, whether or not attributes are permitted and what their values and defaults should be, etc. There's no way to get around well-formedness. Most XML tools complain vociferously about missing or open tags. What you may not have lying around, though, is a DTD describing how the XML should be assembled. If you need to skip validation for any reason you must include the selector: beforeScanDo: [ :p | p validate: false]. Now that you have your XML document, you probably want to access its contents (why else would you want one, right?). Let's take the following (brief) XML as an example: 01/04/2000 widget 1.0000 doodad 2.0000 The first thing you probably want to know is how to access the different tags, and more specifically, how to access the contents of those tags. First, by way of providing a roadmap to the elements I'll show you the Smalltalk code for getting different pieces of the document, assuming the variable you've assigned the document to is named _doc_. I'll also create instance variables for the various elements as I go along: _Element you want_ _Code to get it_ porder element `doc root' porder_head `doc root elementNamed: 'porder_head'' order_date (as a String) `(porderHead elementNamed: 'order_date') characterData' order_date (as a Date) `(Date readFrom: (porderHead elementNamed: 'order_date') characterData readStream)' a collection with both porder_lines `doc root elementsNamed: 'porder_line'' I've deliberately left-out accessing `porder''s attribute because accessing them is different from accessing other nodes. You can get an OrderedCollection of attributes using: attributes := doc root attributes. but the ordered collection isn't really useful. To access any single attribute you'd need to look for it in the collection: porderNum := (attributes detect: [ :each | each key type = 'porder_num' ]) value. But that's not a whole lot of fun, especially if there's a lot you need to get, and if there's any possibility the attribute may not exist. Then you have to do the whole `detect:ifNone:' thing, and boy, does that make the code readable! What I did instead was create a method in my objects' abstract: dictionaryForAttributes: aCollection ^Dictionary withAll: (aCollection collect: [ :each | each key type -> each value ]) Now what you have is an incrementally more useful method for getting attributes: attributes := self dictionaryForAttributes: doc root attributes. porderNum := attributes at: 'porder_num'. At first this appears like more code, and for a single attribute it probably is. But if an element includes more than one attribute the payoff is fairly decent. Of course, you still need to handle the absence of an attribute in the dictionary but I think it reads a little better using a Dictionary than an OrderedCollection: porderNum := attributes at: 'porder_num' ifAbsent: [].  File: gst-libs.info, Node: Building XML, Next: Using DTDs, Prev: Building a DOM from XML, Up: XML/XPath/XSL packages 8.2 Building XML ================ There's little reason to build an XML document if its not going to be processed by something down the road. Most XML tools require XML documents have a document root. A root is a tag inside which all other tags exist, or put another way, a single parent node from which all other nodes descend. In my case, a co-worker was attempting to use Sablot's sabcmd to transform the XML from my server into HTML. So start your document with the root ready to go: replyDoc := XML.Document new. replyDoc addNode: (XML.Element tag: 'response'). Before doing anything more complex, we can play with our new XML document. Assuming you're going to want to send the XML text to someone or write it to a file, you may first want to capture it in a string. Even if you don't want to first capture it into a string our example is going to: replyStream := String new writeStream. replyDoc printOn: replyStream. If we examine'd the contents of our replyStream (`replyStream contents') we'd see: Which is what an empty tag looks like. Let's add some text to our XML document now. Let's say we want it to look like: Hello, world! Building this actually requires two nodes be added to a new XML document. The first node (or element) is named `response'. The second node adds text to the first: replyDoc := XML.Document new. replyDoc addNode: (XML.Element tag: response). "our root node" replyDoc root addNode: (XML.Text text: 'Hello, world!'). Another way of writing it, and the way I've adopted in my code is to create the whole node before adding it. This is not just to reduce the appearance of assignments, but it suggests a template for cascading `#addNode:' messages to an element, which, if you're building any kind of nontrivial XML, you'll be doing a lot of: replyDoc := XML.Document new. replyDoc addNode: ( (XML.Element tag: response) addNode: (XML.Text text: 'Hello, world!') ). Unless you're absolutely sure you'll never accidentally add text nodes that have an ampersand (&) in them, you'll need to escape it to get past XML parsers. The way I got around this was to escape them whenever I added text nodes. To make it easier, I (again) created a method in my objects' abstract superclass: asXMLElement: tag value: aValue | n | n := XML.Element tag: tag. aValue isNil ifFalse: [ n addNode: (XML.Text text: (aValue displayString copyReplaceAll: '&' with: '&'))]. ^n Calls to `self asXMLElement: 'sometagname' value: anInstanceVariable' are littered throughout my code. Adding attributes to documents is, thankfully, easier than accessing them. If we wanted to add an attribute to our document above we can do so with a single statement: replyDoc root addAttribute: (XML.Attribute name: 'isExample' value: 'yes'). Now, our XML looks like: Hello, world!  File: gst-libs.info, Node: Using DTDs, Next: XSL Processing, Prev: Building XML, Up: XML/XPath/XSL packages 8.3 Using DTDs ============== What I didn't appreciate in my first XML project (this one) was how much error checking I was doing just to verify the format of incoming XML. During testing I'd go looking for attributes or elements that _should_ have been there but for various reasons were not. Because I was coding fast and furious I overlooked some and ignored others. Testing quickly ferreted out my carelessnes and my application started throwing exceptions faster than election officials throw chads. The cure, at least for formatting, is having a DTD, or Document Type Definition describing the XML format. You can read more about the syntax of DTDs in the XML specification. There's not a lot programmers are able to do with DTDs in VisualWorks, except requiring incoming XML to include DOCTYPE statements. There is something programmers need to do to handle the exceptions the XML parser throws when it finds errors. I'm not an expert at writing Smalltalk exception handling code, and I haven't decided on what those exceptions should look like to the client who sent the poorly formatted XML in the first place. The code below does a decent job of catching the errors and putting the description of the error into an XML response. It's also a fairly decent example of XML document building as discussed earlier. replyDoc := XML.Document new. replyDoc addNode: (XML.Element tag: 'response'). [ doc := XML.SAXParser defaultParserClass processDocumentString: (anIsdMessage message copyWithout: 0) asString ] on: Exception do: [ :ex | replyDoc root addAttribute: (XML.Attribute name: 'type' value: 'Exception'); addNode: ((XML.Element tag: 'description') addNode: (XML.Text text: ex signal description)); addNode: ((XML.Element tag: 'message') addNode: (XML.Text text: ex messageText)) ]. I said before there's not a lot programmers can do with DTDs, but there are some things I wish the XML library would do: * I'd like to make sure the documents I build are built correctly. It would be great if a DTD could be attached to an empty XML document so that exceptions could be thrown as misplaced elements were added. * It would be great to specify which DTD the XML parser should use when parsing incoming XML so that the incoming XML wouldn't always have to include a tag. Though it's fairly easy to add the tag at the start of XML text, it's really not that simple. You need to know the XML's root element before adding the tag but you really don't know that until after you've parsed the XML You would have to parse the XML, determine the root tag, then parse the output of the first into a new XML document with validation turned-on. * Another reason to be able to create a DTD document to use with subsequent parsing is to avoid the overhead of parsing the same DTD over and over again. In transaction processing systems this kind of redundant task could be eliminated and the spare CPU cycles put to better use.  File: gst-libs.info, Node: XSL Processing, Next: Attributions, Prev: Using DTDs, Up: XML/XPath/XSL packages 8.4 XSL Processing ================== I spent a night the other week trying to figure out how to get the XSL libraries to do anything. I no longer need it now, but I did discover some things others with an immediate need may want to be aware of. * Transforming an XML document requires you parse the XSL and XML documents separately first. After that, you tell the XSL.RuleDatabase to process the XML document. The result is another XML document with the transformations. A code snippet for doing just that appears below. | rules xmlDoc htmlDoc | rules := XSL.RuleDatabase new readFileNamed: 'paymentspending.xsl'. xmlDoc := XML.SAXParser defaultParserClass processDocumentInFilename: 'paymentspending.xml' beforeScanDo: [ :p | p validate: false ]. htmlDoc := rules process: xmlDoc. There is also a `readString:' method which can be used instead of `readFileNamed:'. * The XSL library doesn't use the W3-approved stylesheet, but instead uses the draft version (same one Microsoft uses). `' * The functions `position()' and `count()' aren't implemented, or if they are, aren't implemented in the way other XSL tools implement it.  File: gst-libs.info, Node: Attributions, Prev: XSL Processing, Up: XML/XPath/XSL packages 8.5 Attributions ================ Cincom, for supporting Smalltalk and the Smalltalk community by making the library available for GNU Smalltalk under the LGPL. Thanks also to Randy Ynchausti, Bijan Parsia, Reinout Heeck, and Joseph Bacanskas for answering many questions on the XML library.  File: gst-libs.info, Node: Class index, Next: Method index, Prev: ZLib package, Up: Top Class index *********** [index] * Menu: * BLOX.BArc: BLOX.BArc. (line 6) * BLOX.BBalloon: BLOX.BBalloon. (line 6) * BLOX.BBoundingBox: BLOX.BBoundingBox. (line 6) * BLOX.BButton: BLOX.BButton. (line 6) * BLOX.BButtonLike: BLOX.BButtonLike. (line 6) * BLOX.BCanvas: BLOX.BCanvas. (line 6) * BLOX.BCanvasObject: BLOX.BCanvasObject. (line 6) * BLOX.BCheckMenuItem: BLOX.BCheckMenuItem. (line 6) * BLOX.BColorButton: BLOX.BColorButton. (line 6) * BLOX.BContainer: BLOX.BContainer. (line 6) * BLOX.BDialog: BLOX.BDialog. (line 6) * BLOX.BDropDown: BLOX.BDropDown. (line 6) * BLOX.BDropDownEdit: BLOX.BDropDownEdit. (line 6) * BLOX.BDropDownList: BLOX.BDropDownList. (line 6) * BLOX.BEdit: BLOX.BEdit. (line 6) * BLOX.BEmbeddedImage: BLOX.BEmbeddedImage. (line 6) * BLOX.BEmbeddedText: BLOX.BEmbeddedText. (line 6) * BLOX.BEventSet: BLOX.BEventSet. (line 6) * BLOX.BEventTarget: BLOX.BEventTarget. (line 6) * BLOX.BExtended: BLOX.BExtended. (line 6) * BLOX.BForm: BLOX.BForm. (line 6) * BLOX.BImage: BLOX.BImage. (line 6) * BLOX.BLabel: BLOX.BLabel. (line 6) * BLOX.BLine: BLOX.BLine. (line 6) * BLOX.BList: BLOX.BList. (line 6) * BLOX.Blox: BLOX.Blox. (line 6) * BLOX.BMenu: BLOX.BMenu. (line 6) * BLOX.BMenuBar: BLOX.BMenuBar. (line 6) * BLOX.BMenuItem: BLOX.BMenuItem. (line 6) * BLOX.BMenuObject: BLOX.BMenuObject. (line 6) * BLOX.BOval: BLOX.BOval. (line 6) * BLOX.BPolyline: BLOX.BPolyline. (line 6) * BLOX.BPopupMenu: BLOX.BPopupMenu. (line 6) * BLOX.BPopupWindow: BLOX.BPopupWindow. (line 6) * BLOX.BPrimitive: BLOX.BPrimitive. (line 6) * BLOX.BProgress: BLOX.BProgress. (line 6) * BLOX.BRadioButton: BLOX.BRadioButton. (line 6) * BLOX.BRadioGroup: BLOX.BRadioGroup. (line 6) * BLOX.BRectangle: BLOX.BRectangle. (line 6) * BLOX.BScrolledCanvas: BLOX.BScrolledCanvas. (line 6) * BLOX.BSpline: BLOX.BSpline. (line 6) * BLOX.BText: BLOX.BText. (line 6) * BLOX.BTextAttributes: BLOX.BTextAttributes. (line 6) * BLOX.BTextBindings: BLOX.BTextBindings. (line 6) * BLOX.BTextTags: BLOX.BTextTags. (line 6) * BLOX.BToggle: BLOX.BToggle. (line 6) * BLOX.BTransientWindow: BLOX.BTransientWindow. (line 6) * BLOX.BViewport: BLOX.BViewport. (line 6) * BLOX.BWidget: BLOX.BWidget. (line 6) * BLOX.BWindow: BLOX.BWindow. (line 6) * BLOX.Gui: BLOX.Gui. (line 6) * Complex: Complex. (line 6) * DBI.ColumnInfo: DBI.ColumnInfo. (line 6) * DBI.Connection: DBI.Connection. (line 6) * DBI.ConnectionInfo: DBI.ConnectionInfo. (line 6) * DBI.FieldConverter: DBI.FieldConverter. (line 6) * DBI.ResultSet: DBI.ResultSet. (line 6) * DBI.Row: DBI.Row. (line 6) * DBI.Statement: DBI.Statement. (line 6) * DBI.Table: DBI.Table. (line 6) * Debugger: Debugger. (line 6) * I18N.BigEndianFileStream: I18N.BigEndianFileStream. (line 6) * I18N.EncodedStream: I18N.EncodedStream. (line 6) * I18N.EncodedString: I18N.EncodedString. (line 6) * I18N.EncodedStringFactory: I18N.EncodedStringFactory. (line 6) * I18N.Encoder: I18N.Encoder. (line 6) * I18N.FileStreamSegment: I18N.FileStreamSegment. (line 6) * I18N.IncompleteSequenceError: I18N.IncompleteSequenceError. (line 6) * I18N.InvalidCharsetError: I18N.InvalidCharsetError. (line 6) * I18N.InvalidSequenceError: I18N.InvalidSequenceError. (line 6) * I18N.LcMessages: I18N.LcMessages. (line 6) * I18N.LcMessagesCatalog: I18N.LcMessagesCatalog. (line 6) * I18N.LcMessagesDomain: I18N.LcMessagesDomain. (line 6) * I18N.LcMessagesDummyDomain: I18N.LcMessagesDummyDomain. (line 6) * I18N.LcMessagesMoFileVersion0: I18N.LcMessagesMoFileVersion0. (line 6) * I18N.LcMessagesTerritoryDomain: I18N.LcMessagesTerritoryDomain. (line 6) * I18N.LcMonetary: I18N.LcMonetary. (line 6) * I18N.LcMonetaryISO: I18N.LcMonetaryISO. (line 6) * I18N.LcNumeric: I18N.LcNumeric. (line 6) * I18N.LcPrintFormats: I18N.LcPrintFormats. (line 6) * I18N.LcTime: I18N.LcTime. (line 6) * I18N.Locale: I18N.Locale. (line 6) * I18N.LocaleConventions: I18N.LocaleConventions. (line 6) * I18N.LocaleData: I18N.LocaleData. (line 6) * I18N.RTEAlternativeNode: I18N.RTEAlternativeNode. (line 6) * I18N.RTEBinaryNode: I18N.RTEBinaryNode. (line 6) * I18N.RTELiteralNode: I18N.RTELiteralNode. (line 6) * I18N.RTENegationNode: I18N.RTENegationNode. (line 6) * I18N.RTEParameterNode: I18N.RTEParameterNode. (line 6) * I18N.RunTimeExpression: I18N.RunTimeExpression. (line 6) * Sockets.AbstractSocket: Sockets.AbstractSocket. (line 6) * Sockets.AbstractSocketImpl: Sockets.AbstractSocketImpl. (line 6) * Sockets.CAddrInfoStruct: Sockets.CAddrInfoStruct. (line 6) * Sockets.CSockAddrIn6Struct: Sockets.CSockAddrIn6Struct. (line 6) * Sockets.Datagram: Sockets.Datagram. (line 6) * Sockets.DatagramSocket: Sockets.DatagramSocket. (line 6) * Sockets.DatagramSocketImpl: Sockets.DatagramSocketImpl. (line 6) * Sockets.DummyStream: Sockets.DummyStream. (line 6) * Sockets.ICMP6SocketImpl: Sockets.ICMP6SocketImpl. (line 6) * Sockets.ICMPSocketImpl: Sockets.ICMPSocketImpl. (line 6) * Sockets.IP6Address: Sockets.IP6Address. (line 6) * Sockets.IPAddress: Sockets.IPAddress. (line 6) * Sockets.MulticastSocket: Sockets.MulticastSocket. (line 6) * Sockets.MulticastSocketImpl: Sockets.MulticastSocketImpl. (line 6) * Sockets.OOBSocketImpl: Sockets.OOBSocketImpl. (line 6) * Sockets.RawSocketImpl: Sockets.RawSocketImpl. (line 6) * Sockets.ReadBuffer: Sockets.ReadBuffer. (line 6) * Sockets.ServerSocket: Sockets.ServerSocket. (line 6) * Sockets.Socket: Sockets.Socket. (line 6) * Sockets.SocketAddress: Sockets.SocketAddress. (line 6) * Sockets.SocketImpl: Sockets.SocketImpl. (line 6) * Sockets.StreamSocket: Sockets.StreamSocket. (line 6) * Sockets.TCPSocketImpl: Sockets.TCPSocketImpl. (line 6) * Sockets.UDPSocketImpl: Sockets.UDPSocketImpl. (line 6) * Sockets.UnixAddress: Sockets.UnixAddress. (line 6) * Sockets.UnixDatagramSocketImpl: Sockets.UnixDatagramSocketImpl. (line 6) * Sockets.UnixSocketImpl: Sockets.UnixSocketImpl. (line 6) * Sockets.WriteBuffer: Sockets.WriteBuffer. (line 6) * ZLib.DeflateStream: ZLib.DeflateStream. (line 6) * ZLib.DeflateWriteStream: ZLib.DeflateWriteStream. (line 6) * ZLib.GZipDeflateStream: ZLib.GZipDeflateStream. (line 6) * ZLib.GZipDeflateWriteStream: ZLib.GZipDeflateWriteStream. (line 6) * ZLib.GZipInflateStream: ZLib.GZipInflateStream. (line 6) * ZLib.InflateStream: ZLib.InflateStream. (line 6) * ZLib.RawDeflateStream: ZLib.RawDeflateStream. (line 6) * ZLib.RawDeflateWriteStream: ZLib.RawDeflateWriteStream. (line 6) * ZLib.RawInflateStream: ZLib.RawInflateStream. (line 6) * ZLib.ZlibError: ZLib.ZlibError. (line 6) * ZLib.ZlibReadStream: ZLib.ZlibReadStream. (line 6) * ZLib.ZlibStream: ZLib.ZlibStream. (line 6) * ZLib.ZlibWriteStream: ZLib.ZlibWriteStream. (line 6) smalltalk-3.2.5/doc/gst-base.info-10000644000175000017500000111244412130456007013720 00000000000000This is gst-base.info, produced by makeinfo version 4.13 from /home/ich/source/smalltalk/release/smalltalk/doc/gst-base-fixed.texi. INFO-DIR-SECTION Software development START-INFO-DIR-ENTRY * Smalltalk base classes: (gst-base). The GNU Smalltalk base classes. END-INFO-DIR-ENTRY Permission is granted to copy, distribute and/or modify this document under the terms of the GNU Free Documentation License, Version 1.2 or any later version published by the Free Software Foundation; with no Invariant Sections, with no Front-Cover Texts, and with no Back-Cover Texts. A copy of the license is included in the section entitled "GNU Free Documentation License".  File: gst-base.info, Node: Top, Up: (DIR) GNU Smalltalk Library Reference ******************************* GNU Smalltalk Library Reference This document describes the class libraries that are distributed together with the GNU Smalltalk programming language. Permission is granted to copy, distribute and/or modify this document under the terms of the GNU Free Documentation License, Version 1.2 or any later version published by the Free Software Foundation; with no Invariant Sections, with no Front-Cover Texts, and with no Back-Cover Texts. A copy of the license is included in the section entitled "GNU Free Documentation License". * Menu: * Base classes:: The class reference * Class index:: Index to the classes in the class reference * Method index:: Index to the method selectors in the class reference * Cross-reference:: Cross-reference between selectors  File: gst-base.info, Node: Base classes, Next: Class index, Prev: Top, Up: Top 1 Base classes ************** * Menu: Alphabetic list: * AbstractNamespace:: * AlternativeObjectProxy:: * ArithmeticError:: * Array:: * ArrayedCollection:: * Association:: * Autoload:: * Bag:: * Behavior:: * BindingDictionary:: * BlockClosure:: * BlockContext:: * Boolean:: * ByteArray:: * CAggregate:: * CallinProcess:: * CArray:: * CArrayCType:: * CBoolean:: * CByte:: * CCallable:: * CCallbackDescriptor:: * CChar:: * CCompound:: * CDouble:: * CFloat:: * CFunctionDescriptor:: * Character:: * CharacterArray:: * CInt:: * Class:: * ClassDescription:: * CLong:: * CLongDouble:: * CLongLong:: * CObject:: * Collection:: * CompiledBlock:: * CompiledCode:: * CompiledMethod:: * ContextPart:: * Continuation:: * CPtr:: * CPtrCType:: * CScalar:: * CScalarCType:: * CShort:: * CSmalltalk:: * CString:: * CStringCType:: * CStruct:: * CType:: * CUChar:: * CUInt:: * CULong:: * CULongLong:: * CUnion:: * CUShort:: * Date:: * DateTime:: * DeferredVariableBinding:: * Delay:: * DelayedAdaptor:: * Dictionary:: * DirectedMessage:: * Directory:: * DLD:: * DumperProxy:: * Duration:: * DynamicVariable:: * Error:: * Exception:: * ExceptionSet:: * False:: * File:: * FileDescriptor:: * FilePath:: * FileSegment:: * FileStream:: * Float:: * FloatD:: * FloatE:: * FloatQ:: * Fraction:: * Generator:: * Getopt:: * Halt:: * HashedCollection:: * HomedAssociation:: * IdentityDictionary:: * IdentitySet:: * Integer:: * Interval:: * Iterable:: * LargeArray:: * LargeArrayedCollection:: * LargeByteArray:: * LargeInteger:: * LargeNegativeInteger:: * LargePositiveInteger:: * LargeWordArray:: * LargeZeroInteger:: * Link:: * LinkedList:: * LookupKey:: * LookupTable:: * Magnitude:: * MappedCollection:: * Memory:: * Message:: * MessageNotUnderstood:: * Metaclass:: * MethodContext:: * MethodDictionary:: * MethodInfo:: * Namespace:: * NetClients.URIResolver:: * NetClients.URL:: * Notification:: * NullProxy:: * NullValueHolder:: * Number:: * Object:: * ObjectDumper:: * ObjectMemory:: * OrderedCollection:: * Package:: * PackageLoader:: * Permission:: * PluggableAdaptor:: * PluggableProxy:: * Point:: * PositionableStream:: * Process:: * ProcessEnvironment:: * ProcessorScheduler:: * ProcessVariable:: * Promise:: * Random:: * ReadStream:: * ReadWriteStream:: * Rectangle:: * RecursionLock:: * Regex:: * RegexResults:: * RootNamespace:: * RunArray:: * ScaledDecimal:: * SecurityPolicy:: * Semaphore:: * SequenceableCollection:: * Set:: * SharedQueue:: * SingletonProxy:: * SmallInteger:: * SortedCollection:: * Stream:: * String:: * Symbol:: * SymLink:: * SystemDictionary:: * SystemExceptions.AlreadyDefined:: * SystemExceptions.ArgumentOutOfRange:: * SystemExceptions.BadReturn:: * SystemExceptions.CInterfaceError:: * SystemExceptions.EmptyCollection:: * SystemExceptions.EndOfStream:: * SystemExceptions.FileError:: * SystemExceptions.IndexOutOfRange:: * SystemExceptions.InvalidArgument:: * SystemExceptions.InvalidProcessState:: * SystemExceptions.InvalidSize:: * SystemExceptions.InvalidState:: * SystemExceptions.InvalidValue:: * SystemExceptions.MustBeBoolean:: * SystemExceptions.MutationError:: * SystemExceptions.NoRunnableProcess:: * SystemExceptions.NotEnoughElements:: * SystemExceptions.NotFound:: * SystemExceptions.NotImplemented:: * SystemExceptions.NotIndexable:: * SystemExceptions.NotYetImplemented:: * SystemExceptions.PackageNotAvailable:: * SystemExceptions.PrimitiveFailed:: * SystemExceptions.ProcessBeingTerminated:: * SystemExceptions.ProcessTerminated:: * SystemExceptions.ReadOnlyObject:: * SystemExceptions.SecurityError:: * SystemExceptions.ShouldNotImplement:: * SystemExceptions.SubclassResponsibility:: * SystemExceptions.UnhandledException:: * SystemExceptions.UserInterrupt:: * SystemExceptions.VerificationError:: * SystemExceptions.VMError:: * SystemExceptions.WrongArgumentCount:: * SystemExceptions.WrongClass:: * SystemExceptions.WrongMessageSent:: * TextCollector:: * Time:: * True:: * UndefinedObject:: * UnicodeCharacter:: * UnicodeString:: * ValueAdaptor:: * ValueHolder:: * VariableBinding:: * VersionableObjectProxy:: * VFS.ArchiveFile:: * VFS.ArchiveMember:: * VFS.FileWrapper:: * VFS.StoredZipMember:: * VFS.TmpFileArchiveMember:: * VFS.ZipFile:: * Warning:: * WeakArray:: * WeakIdentitySet:: * WeakKeyDictionary:: * WeakKeyIdentityDictionary:: * WeakSet:: * WeakValueIdentityDictionary:: * WeakValueLookupTable:: * WordArray:: * WriteStream:: * ZeroDivide:: Class tree: * Autoload:: * Object:: * Behavior:: * ClassDescription:: * Class:: * Metaclass:: * BlockClosure:: * Boolean:: * False:: * True:: * CObject:: * CAggregate:: * CArray:: * CPtr:: * CString:: * CCallable:: * CCallbackDescriptor:: * CFunctionDescriptor:: * CCompound:: * CStruct:: * CUnion:: * CScalar:: * CChar:: * CDouble:: * CFloat:: * CInt:: * CLong:: * CLongDouble:: * CLongLong:: * CShort:: * CSmalltalk:: * CUChar:: * CByte:: * CBoolean:: * CUInt:: * CULong:: * CULongLong:: * CUShort:: * ContextPart:: * BlockContext:: * MethodContext:: * Continuation:: * CType:: * CPtrCType:: * CArrayCType:: * CScalarCType:: * CStringCType:: * Delay:: * Directory:: * DLD:: * DumperProxy:: * AlternativeObjectProxy:: * NullProxy:: * VersionableObjectProxy:: * PluggableProxy:: * SingletonProxy:: * DynamicVariable:: * Exception:: * Error:: * ArithmeticError:: * ZeroDivide:: * MessageNotUnderstood:: * SystemExceptions.InvalidValue:: * SystemExceptions.EmptyCollection:: * SystemExceptions.InvalidArgument:: * SystemExceptions.AlreadyDefined:: * SystemExceptions.ArgumentOutOfRange:: * SystemExceptions.IndexOutOfRange:: * SystemExceptions.InvalidSize:: * SystemExceptions.NotFound:: * SystemExceptions.PackageNotAvailable:: * SystemExceptions.InvalidProcessState:: * SystemExceptions.InvalidState:: * SystemExceptions.NotIndexable:: * SystemExceptions.ProcessTerminated:: * SystemExceptions.ReadOnlyObject:: * SystemExceptions.WrongClass:: * SystemExceptions.MustBeBoolean:: * SystemExceptions.MutationError:: * SystemExceptions.NotEnoughElements:: * SystemExceptions.NotImplemented:: * SystemExceptions.NotYetImplemented:: * SystemExceptions.ShouldNotImplement:: * SystemExceptions.SubclassResponsibility:: * SystemExceptions.WrongMessageSent:: * SystemExceptions.VMError:: * SystemExceptions.BadReturn:: * SystemExceptions.NoRunnableProcess:: * SystemExceptions.PrimitiveFailed:: * SystemExceptions.CInterfaceError:: * SystemExceptions.FileError:: * SystemExceptions.WrongArgumentCount:: * SystemExceptions.SecurityError:: * SystemExceptions.UserInterrupt:: * SystemExceptions.VerificationError:: * Halt:: * Notification:: * SystemExceptions.EndOfStream:: * SystemExceptions.ProcessBeingTerminated:: * Warning:: * SystemExceptions.UnhandledException:: * ExceptionSet:: * FilePath:: * File:: * VFS.ArchiveMember:: * VFS.TmpFileArchiveMember:: * VFS.StoredZipMember:: * VFS.FileWrapper:: * VFS.ArchiveFile:: * VFS.ZipFile:: * FileSegment:: * Getopt:: * Iterable:: * Collection:: * Bag:: * HashedCollection:: * Dictionary:: * BindingDictionary:: * AbstractNamespace:: * Namespace:: * RootNamespace:: * SystemDictionary:: * LookupTable:: * IdentityDictionary:: * MethodDictionary:: * WeakValueLookupTable:: * WeakValueIdentityDictionary:: * WeakKeyDictionary:: * WeakKeyIdentityDictionary:: * Set:: * IdentitySet:: * WeakSet:: * WeakIdentitySet:: * MappedCollection:: * SequenceableCollection:: * ArrayedCollection:: * Array:: * WeakArray:: * ByteArray:: * CharacterArray:: * String:: * Symbol:: * UnicodeString:: * CompiledCode:: * CompiledBlock:: * CompiledMethod:: * Interval:: * LargeArrayedCollection:: * LargeArray:: * LargeByteArray:: * LargeWordArray:: * WordArray:: * LinkedList:: * Semaphore:: * OrderedCollection:: * RunArray:: * SortedCollection:: * Stream:: * FileDescriptor:: * FileStream:: * Generator:: * ObjectDumper:: * PositionableStream:: * ReadStream:: * WriteStream:: * ReadWriteStream:: * Random:: * TextCollector:: (Kernel.PackageInfo) * Package:: * Link:: * Process:: * CallinProcess:: * SymLink:: * Magnitude:: * Character:: * UnicodeCharacter:: * Date:: * DateTime:: * LookupKey:: * Association:: * HomedAssociation:: * VariableBinding:: * DeferredVariableBinding:: * ProcessVariable:: * Number:: * Float:: * FloatD:: * FloatE:: * FloatQ:: * Fraction:: * Integer:: * LargeInteger:: * LargeNegativeInteger:: * LargePositiveInteger:: * LargeZeroInteger:: * SmallInteger:: * ScaledDecimal:: * Time:: * Duration:: * Memory:: * Message:: * DirectedMessage:: * MethodInfo:: * NetClients.URIResolver:: * NetClients.URL:: * ObjectMemory:: * PackageLoader:: * Permission:: * Point:: * ProcessEnvironment:: * ProcessorScheduler:: * Rectangle:: * RecursionLock:: * Regex:: * RegexResults:: * SecurityPolicy:: * SharedQueue:: * UndefinedObject:: * ValueAdaptor:: * NullValueHolder:: * PluggableAdaptor:: * DelayedAdaptor:: * ValueHolder:: * Promise::  File: gst-base.info, Node: AbstractNamespace, Next: AlternativeObjectProxy, Up: Base classes 1.1 AbstractNamespace ===================== Defined in namespace Smalltalk Superclass: BindingDictionary Category: Language-Implementation I am a special form of dictionary. Classes hold on an instance of me; it is called their `environment'. * Menu: * AbstractNamespace class-instance creation:: (class) * AbstractNamespace-accessing:: (instance) * AbstractNamespace-compiling:: (instance) * AbstractNamespace-copying:: (instance) * AbstractNamespace-namespace hierarchy:: (instance) * AbstractNamespace-overrides for superspaces:: (instance) * AbstractNamespace-printing:: (instance) * AbstractNamespace-testing:: (instance)  File: gst-base.info, Node: AbstractNamespace class-instance creation, Next: AbstractNamespace-accessing, Up: AbstractNamespace 1.1.1 AbstractNamespace class: instance creation ------------------------------------------------ new Disabled - use #new to create instances primNew: parent name: spaceName Private - Create a new namespace with the given name and parent, and add to the parent a key that references it.  File: gst-base.info, Node: AbstractNamespace-accessing, Next: AbstractNamespace-compiling, Prev: AbstractNamespace class-instance creation, Up: AbstractNamespace 1.1.2 AbstractNamespace: accessing ---------------------------------- allAssociations Answer a Dictionary with all of the associations in the receiver and each of its superspaces (duplicate keys are associated to the associations that are deeper in the namespace hierarchy) allBehaviorsDo: aBlock Evaluate aBlock once for each class and metaclass in the namespace. allClassObjectsDo: aBlock Evaluate aBlock once for each class and metaclass in the namespace. allClassesDo: aBlock Evaluate aBlock once for each class in the namespace. allMetaclassesDo: aBlock Evaluate aBlock once for each metaclass in the namespace. classAt: aKey Answer the value corrisponding to aKey if it is a class. Fail if either aKey is not found or it is associated to something different from a class. classAt: aKey ifAbsent: aBlock Answer the value corrisponding to aKey if it is a class. Evaluate aBlock and answer its result if either aKey is not found or it is associated to something different from a class.  File: gst-base.info, Node: AbstractNamespace-compiling, Next: AbstractNamespace-copying, Prev: AbstractNamespace-accessing, Up: AbstractNamespace 1.1.3 AbstractNamespace: compiling ---------------------------------- addSharedPool: aDictionary Import the given bindings for classes compiled with me as environment. import: aDictionary Import the given bindings for classes compiled with me as environment. removeSharedPool: aDictionary Remove aDictionary from my list of direct pools. sharedPoolDictionaries Answer the shared pools (not names) imported for my classes.  File: gst-base.info, Node: AbstractNamespace-copying, Next: AbstractNamespace-namespace hierarchy, Prev: AbstractNamespace-compiling, Up: AbstractNamespace 1.1.4 AbstractNamespace: copying -------------------------------- copyEmpty: newSize Answer an empty copy of the receiver whose size is newSize whileCurrentDo: aBlock Evaluate aBlock with the current namespace set to the receiver. Answer the result of the evaluation.  File: gst-base.info, Node: AbstractNamespace-namespace hierarchy, Next: AbstractNamespace-overrides for superspaces, Prev: AbstractNamespace-copying, Up: AbstractNamespace 1.1.5 AbstractNamespace: namespace hierarchy -------------------------------------------- addSubspace: aSymbol Create a namespace named aSymbol, add it to the receiver's subspaces, and answer it. allSubassociationsDo: aBlock Invokes aBlock once for every association in each of the receiver's subspaces. allSubspaces Answer the direct and indirect subspaces of the receiver in a Set allSubspacesDo: aBlock Invokes aBlock for all subspaces, both direct and indirect. allSuperspacesDo: aBlock Evaluate aBlock once for each of the receiver's superspaces includesClassNamed: aString Answer whether the receiver or any of its superspaces include the given class - note that this method (unlike #includesKey:) does not require aString to be interned and (unlike #includesGlobalNamed:) only returns true if the global is a class object. includesGlobalNamed: aString Answer whether the receiver or any of its superspaces include the given key - note that this method (unlike #includesKey:) does not require aString to be interned but (unlike #includesClassNamed:) returns true even if the global is not a class object. removeSubspace: aSymbol Remove my subspace named aSymbol from the hierarchy. selectSubspaces: aBlock Return a Set of subspaces of the receiver satisfying aBlock. selectSuperspaces: aBlock Return a Set of superspaces of the receiver satisfying aBlock. siblings Answer all the other children of the same namespace as the receiver. siblingsDo: aBlock Evaluate aBlock once for each of the other root namespaces, passing the namespace as a parameter. subspaces Answer the receiver's direct subspaces subspacesDo: aBlock Invokes aBlock for all direct subspaces. superspace Answer the receiver's superspace. superspace: aNamespace Set the superspace of the receiver to be 'aNamespace'. Also adds the receiver as a subspace of it. withAllSubspaces Answer a Set containing the receiver together with its direct and indirect subspaces withAllSubspacesDo: aBlock Invokes aBlock for the receiver and all subclasses, both direct and indirect.  File: gst-base.info, Node: AbstractNamespace-overrides for superspaces, Next: AbstractNamespace-printing, Prev: AbstractNamespace-namespace hierarchy, Up: AbstractNamespace 1.1.6 AbstractNamespace: overrides for superspaces -------------------------------------------------- inheritedKeys Answer a Set of all the keys in the receiver and its superspaces set: key to: newValue Assign newValue to the variable named as specified by `key'. This method won't define a new variable; instead if the key is not found it will search in superspaces and raising an error if the variable cannot be found in any of the superspaces. Answer newValue. set: key to: newValue ifAbsent: aBlock Assign newValue to the variable named as specified by `key'. This method won't define a new variable; instead if the key is not found it will search in superspaces and evaluate aBlock if it is not found. Answer newValue. values Answer a Bag containing the values of the receiver  File: gst-base.info, Node: AbstractNamespace-printing, Next: AbstractNamespace-testing, Prev: AbstractNamespace-overrides for superspaces, Up: AbstractNamespace 1.1.7 AbstractNamespace: printing --------------------------------- name Answer the receiver's name name: aSymbol Change the receiver's name to aSymbol nameIn: aNamespace Answer Smalltalk code compiling to the receiver when the current namespace is aNamespace printOn: aStream Print a representation of the receiver storeOn: aStream Store Smalltalk code compiling to the receiver  File: gst-base.info, Node: AbstractNamespace-testing, Prev: AbstractNamespace-printing, Up: AbstractNamespace 1.1.8 AbstractNamespace: testing -------------------------------- isNamespace Answer `true'. isSmalltalk Answer `false'.  File: gst-base.info, Node: AlternativeObjectProxy, Next: ArithmeticError, Prev: AbstractNamespace, Up: Base classes 1.2 AlternativeObjectProxy ========================== Defined in namespace Smalltalk Superclass: DumperProxy Category: Streams-Files I am a proxy that uses the same ObjectDumper to store an object which is not the object to be dumped, but from which the dumped object can be reconstructed. I am an abstract class, using me would result in infinite loops because by default I try to store the same object again and again. See the method comments for more information * Menu: * AlternativeObjectProxy class-instance creation:: (class) * AlternativeObjectProxy-accessing:: (instance)  File: gst-base.info, Node: AlternativeObjectProxy class-instance creation, Next: AlternativeObjectProxy-accessing, Up: AlternativeObjectProxy 1.2.1 AlternativeObjectProxy class: instance creation ----------------------------------------------------- acceptUsageForClass: aClass The receiver was asked to be used as a proxy for the class aClass. Answer whether the registration is fine. By default, answer true except if AlternativeObjectProxy itself is being used. on: anObject Answer a proxy to be used to save anObject. IMPORTANT: this method MUST be overridden so that the overridden version sends #on: to super passing an object that is NOT the same as anObject (alternatively, you can override #dumpTo:, which is what NullProxy does), because that would result in an infinite loop! This also means that AlternativeObjectProxy must never be used directly - only as a superclass.  File: gst-base.info, Node: AlternativeObjectProxy-accessing, Prev: AlternativeObjectProxy class-instance creation, Up: AlternativeObjectProxy 1.2.2 AlternativeObjectProxy: accessing --------------------------------------- object Reconstruct the object stored in the proxy and answer it. A subclass will usually override this object: theObject Set the object to be dumped to theObject. This should not be overridden. primObject Reconstruct the object stored in the proxy and answer it. This method must not be overridden  File: gst-base.info, Node: ArithmeticError, Next: Array, Prev: AlternativeObjectProxy, Up: Base classes 1.3 ArithmeticError =================== Defined in namespace Smalltalk Superclass: Error Category: Language-Exceptions An ArithmeticError exception is raised by numeric classes when a program tries to do something wrong, such as extracting the square root of a negative number. * Menu: * ArithmeticError-description:: (instance)  File: gst-base.info, Node: ArithmeticError-description, Up: ArithmeticError 1.3.1 ArithmeticError: description ---------------------------------- description Answer a textual description of the exception. isResumable Answer true. Arithmetic exceptions are by default resumable.  File: gst-base.info, Node: Array, Next: ArrayedCollection, Prev: ArithmeticError, Up: Base classes 1.4 Array ========= Defined in namespace Smalltalk Superclass: ArrayedCollection Category: Collections-Sequenceable My instances are objects that have array-like properties: they are directly indexable by integers starting at 1, and they are fixed in size. I inherit object creation behavior messages such as #with:, as well as iteration and general access behavior from SequenceableCollection. * Menu: * Array class-instance creation:: (class) * Array-built ins:: (instance) * Array-mutating objects:: (instance) * Array-printing:: (instance) * Array-testing:: (instance)  File: gst-base.info, Node: Array class-instance creation, Next: Array-built ins, Up: Array 1.4.1 Array class: instance creation ------------------------------------ from: anArray Answer anArray, which is expected to be an array specified with a brace-syntax expression per my inherited protocol.  File: gst-base.info, Node: Array-built ins, Next: Array-mutating objects, Prev: Array class-instance creation, Up: Array 1.4.2 Array: built ins ---------------------- at: anIndex ifAbsent: aBlock Answer the index-th indexed instance variable of the receiver replaceFrom: start to: stop with: byteArray startingAt: replaceStart Replace the characters from start to stop with new characters whose ASCII codes are contained in byteArray, starting at the replaceStart location of byteArray  File: gst-base.info, Node: Array-mutating objects, Next: Array-printing, Prev: Array-built ins, Up: Array 1.4.3 Array: mutating objects ----------------------------- multiBecome: anArray Transform every object in the receiver in each corresponding object in anArray. anArray and the receiver must have the same size  File: gst-base.info, Node: Array-printing, Next: Array-testing, Prev: Array-mutating objects, Up: Array 1.4.4 Array: printing --------------------- isLiteralObject Answer whether the receiver is expressible as a Smalltalk literal. printOn: aStream Print a representation for the receiver on aStream storeLiteralOn: aStream Store a Smalltalk literal compiling to the receiver on aStream storeOn: aStream Store Smalltalk code compiling to the receiver on aStream  File: gst-base.info, Node: Array-testing, Prev: Array-printing, Up: Array 1.4.5 Array: testing -------------------- isArray Answer `true'.  File: gst-base.info, Node: ArrayedCollection, Next: Association, Prev: Array, Up: Base classes 1.5 ArrayedCollection ===================== Defined in namespace Smalltalk Superclass: SequenceableCollection Category: Collections-Sequenceable My instances are objects that are generally fixed size, and are accessed by an integer index. The ordering of my instance's elements is determined externally; I will not rearrange the order of the elements. * Menu: * ArrayedCollection class-instance creation:: (class) * ArrayedCollection-basic:: (instance) * ArrayedCollection-built ins:: (instance) * ArrayedCollection-compiler:: (instance) * ArrayedCollection-copying Collections:: (instance) * ArrayedCollection-enumerating the elements of a collection:: (instance) * ArrayedCollection-sorting:: (instance) * ArrayedCollection-storing:: (instance) * ArrayedCollection-streams:: (instance)  File: gst-base.info, Node: ArrayedCollection class-instance creation, Next: ArrayedCollection-basic, Up: ArrayedCollection 1.5.1 ArrayedCollection class: instance creation ------------------------------------------------ join: aCollection Where aCollection is a collection of SequenceableCollections, answer a new instance with all the elements therein, in order. join: aCollection separatedBy: sepCollection Where aCollection is a collection of SequenceableCollections, answer a new instance with all the elements therein, in order, each separated by an occurrence of sepCollection. new: size withAll: anObject Answer a collection with the given size, whose elements are all set to anObject streamContents: aBlock Create a ReadWriteStream on an empty instance of the receiver; pass the stream to aBlock, then retrieve its contents and answer them. with: element1 Answer a collection whose only element is element1 with: element1 with: element2 Answer a collection whose only elements are the parameters in the order they were passed with: element1 with: element2 with: element3 Answer a collection whose only elements are the parameters in the order they were passed with: element1 with: element2 with: element3 with: element4 Answer a collection whose only elements are the parameters in the order they were passed with: element1 with: element2 with: element3 with: element4 with: element5 Answer a collection whose only elements are the parameters in the order they were passed withAll: aCollection Answer a collection whose elements are the same as those in aCollection  File: gst-base.info, Node: ArrayedCollection-basic, Next: ArrayedCollection-built ins, Prev: ArrayedCollection class-instance creation, Up: ArrayedCollection 1.5.2 ArrayedCollection: basic ------------------------------ , aSequenceableCollection Answer a new instance of an ArrayedCollection containing all the elements in the receiver, followed by all the elements in aSequenceableCollection add: value This method should not be called for instances of this class. atAll: keyCollection Answer a collection of the same kind returned by #collect:, that only includes the values at the given indices. Fail if any of the values in keyCollection is out of bounds for the receiver. copyFrom: start to: stop Answer a new collection containing all the items in the receiver from the start-th and to the stop-th copyWith: anElement Answer a new instance of an ArrayedCollection containing all the elements in the receiver, followed by the single item anElement copyWithout: oldElement Answer a copy of the receiver to which all occurrences of oldElement are removed  File: gst-base.info, Node: ArrayedCollection-built ins, Next: ArrayedCollection-compiler, Prev: ArrayedCollection-basic, Up: ArrayedCollection 1.5.3 ArrayedCollection: built ins ---------------------------------- size Answer the size of the receiver  File: gst-base.info, Node: ArrayedCollection-compiler, Next: ArrayedCollection-copying Collections, Prev: ArrayedCollection-built ins, Up: ArrayedCollection 1.5.4 ArrayedCollection: compiler --------------------------------- literalEquals: anObject Not commented. literalHash Not commented.  File: gst-base.info, Node: ArrayedCollection-copying Collections, Next: ArrayedCollection-enumerating the elements of a collection, Prev: ArrayedCollection-compiler, Up: ArrayedCollection 1.5.5 ArrayedCollection: copying Collections -------------------------------------------- copyReplaceAll: oldSubCollection with: newSubCollection Answer a new collection in which all the sequences matching oldSubCollection are replaced with newSubCollection copyReplaceFrom: start to: stop with: replacementCollection Answer a new collection of the same class as the receiver that contains the same elements as the receiver, in the same order, except for elements from index `start' to index `stop'. If start < stop, these are replaced by the contents of the replacementCollection. Instead, If start = (stop + 1), like in `copyReplaceFrom: 4 to: 3 with: anArray', then every element of the receiver will be present in the answered copy; the operation will be an append if stop is equal to the size of the receiver or, if it is not, an insert before index `start'. copyReplaceFrom: start to: stop withObject: anObject Answer a new collection of the same class as the receiver that contains the same elements as the receiver, in the same order, except for elements from index `start' to index `stop'. If start < stop, these are replaced by stop-start+1 copies of anObject. Instead, If start = (stop + 1), then every element of the receiver will be present in the answered copy; the operation will be an append if stop is equal to the size of the receiver or, if it is not, an insert before index `start'. reverse Answer the receivers' contents in reverse order  File: gst-base.info, Node: ArrayedCollection-enumerating the elements of a collection, Next: ArrayedCollection-sorting, Prev: ArrayedCollection-copying Collections, Up: ArrayedCollection 1.5.6 ArrayedCollection: enumerating the elements of a collection ----------------------------------------------------------------- collect: aBlock Answer a new instance of an ArrayedCollection containing all the results of evaluating aBlock passing each of the receiver's elements reject: aBlock Answer a new instance of an ArrayedCollection containing all the elements in the receiver which, when passed to aBlock, answer false select: aBlock Answer a new instance of an ArrayedCollection containing all the elements in the receiver which, when passed to aBlock, answer true with: aSequenceableCollection collect: aBlock Evaluate aBlock for each pair of elements took respectively from the receiver and from aSequenceableCollection; answer a collection of the same kind of the receiver, made with the block's return values. Fail if the receiver has not the same size as aSequenceableCollection.  File: gst-base.info, Node: ArrayedCollection-sorting, Next: ArrayedCollection-storing, Prev: ArrayedCollection-enumerating the elements of a collection, Up: ArrayedCollection 1.5.7 ArrayedCollection: sorting -------------------------------- sorted Return a copy of the receiver sorted according to the default sort block, which uses #<= to compare items. sorted: sortBlock Return a copy of the receiver sorted according to the given sort block, which accepts pair of items and returns true if the first item is less than the second one.  File: gst-base.info, Node: ArrayedCollection-storing, Next: ArrayedCollection-streams, Prev: ArrayedCollection-sorting, Up: ArrayedCollection 1.5.8 ArrayedCollection: storing -------------------------------- storeOn: aStream Store Smalltalk code compiling to the receiver on aStream  File: gst-base.info, Node: ArrayedCollection-streams, Prev: ArrayedCollection-storing, Up: ArrayedCollection 1.5.9 ArrayedCollection: streams -------------------------------- writeStream Answer a WriteStream streaming on the receiver  File: gst-base.info, Node: Association, Next: Autoload, Prev: ArrayedCollection, Up: Base classes 1.6 Association =============== Defined in namespace Smalltalk Superclass: LookupKey Category: Language-Data types My instances represent a mapping between two objects. Typically, my "key" object is a symbol, but I don't require this. My "value" object has no conventions associated with it; it can be any object at all. * Menu: * Association class-basic:: (class) * Association-accessing:: (instance) * Association-finalization:: (instance) * Association-printing:: (instance) * Association-storing:: (instance) * Association-testing:: (instance)  File: gst-base.info, Node: Association class-basic, Next: Association-accessing, Up: Association 1.6.1 Association class: basic ------------------------------ key: aKey value: aValue Answer a new association with the given key and value  File: gst-base.info, Node: Association-accessing, Next: Association-finalization, Prev: Association class-basic, Up: Association 1.6.2 Association: accessing ---------------------------- environment Answer nil. This is present to achieve polymorphism with instances of VariableBinding. environment: aNamespace Do nothing. This is present to achieve polymorphism with instances of VariableBinding. key: aKey value: aValue Set the association's key to aKey, and its value to aValue value Answer the association's value value: aValue Set the association's value to aValue  File: gst-base.info, Node: Association-finalization, Next: Association-printing, Prev: Association-accessing, Up: Association 1.6.3 Association: finalization ------------------------------- mourn Finalize the receiver  File: gst-base.info, Node: Association-printing, Next: Association-storing, Prev: Association-finalization, Up: Association 1.6.4 Association: printing --------------------------- printOn: aStream Put on aStream a representation of the receiver  File: gst-base.info, Node: Association-storing, Next: Association-testing, Prev: Association-printing, Up: Association 1.6.5 Association: storing -------------------------- storeOn: aStream Put on aStream some Smalltalk code compiling to the receiver  File: gst-base.info, Node: Association-testing, Prev: Association-storing, Up: Association 1.6.6 Association: testing -------------------------- = anAssociation Answer whether the association's key and value are the same as anAssociation's, or false if anAssociation is not an Association. As a special case, identical values are considered equal even if #= returns false (as is the case for NaN floating-point values). hash Answer an hash value for the receiver  File: gst-base.info, Node: Autoload, Next: Bag, Prev: Association, Up: Base classes 1.7 Autoload ============ Defined in namespace Smalltalk Superclass: none Category: Examples-Useful tools I am not a part of the normal Smalltalk kernel class system. I provide the ability to do late ("on-demand") loading of class definitions. Through me, you can define any class to be loaded when any message is sent to the class itself (such as to create an instance) or to its metaclass (such as #methodsFor: to extend it with class-side methods). * Menu: * Autoload class-instance creation:: (class) * Autoload-accessing:: (instance)  File: gst-base.info, Node: Autoload class-instance creation, Next: Autoload-accessing, Up: Autoload 1.7.1 Autoload class: instance creation --------------------------------------- class: nameSymbol from: fileNameString Make Smalltalk automatically load the class named nameSymbol from fileNameString when needed class: nameSymbol in: aNamespace from: fileNameString Make Smalltalk automatically load the class named nameSymbol and residing in aNamespace from fileNameString when needed class: nameSymbol in: aNamespace loader: anObject Make Smalltalk automatically load the class named nameSymbol and residing in aNamespace. When the class is needed, anObject will be sent #autoload. By default, instances of FilePath and Package can be used. class: nameSymbol loader: anObject Make Smalltalk automatically load the class named nameSymbol. When the class is needed, anObject will be sent #autoload. By default, instances of FilePath and Package can be used.  File: gst-base.info, Node: Autoload-accessing, Prev: Autoload class-instance creation, Up: Autoload 1.7.2 Autoload: accessing ------------------------- class We need it to access the metaclass instance, because that's what will load the file. doesNotUnderstand: aMessage Load the class and resend the message to it  File: gst-base.info, Node: Bag, Next: Behavior, Prev: Autoload, Up: Base classes 1.8 Bag ======= Defined in namespace Smalltalk Superclass: Collection Category: Collections-Unordered My instances are unordered collections of objects. You can think of me as a set with a memory; that is, if the same object is added to me twice, then I will report that that element has been stored twice. * Menu: * Bag class-basic:: (class) * Bag-adding:: (instance) * Bag-enumerating the elements of a collection:: (instance) * Bag-extracting items:: (instance) * Bag-printing:: (instance) * Bag-removing:: (instance) * Bag-storing:: (instance) * Bag-testing collections:: (instance)  File: gst-base.info, Node: Bag class-basic, Next: Bag-adding, Up: Bag 1.8.1 Bag class: basic ---------------------- new Answer a new instance of the receiver new: size Answer a new instance of the receiver, with space for size distinct objects  File: gst-base.info, Node: Bag-adding, Next: Bag-enumerating the elements of a collection, Prev: Bag class-basic, Up: Bag 1.8.2 Bag: adding ----------------- add: newObject Add an occurrence of newObject to the receiver. Answer newObject. Fail if newObject is nil. add: newObject withOccurrences: anInteger If anInteger > 0, add anInteger occurrences of newObject to the receiver. If anInteger < 0, remove them. Answer newObject. Fail if newObject is nil.  File: gst-base.info, Node: Bag-enumerating the elements of a collection, Next: Bag-extracting items, Prev: Bag-adding, Up: Bag 1.8.3 Bag: enumerating the elements of a collection --------------------------------------------------- asSet Answer a set with the elements of the receiver do: aBlock Evaluate the block for all members in the collection.  File: gst-base.info, Node: Bag-extracting items, Next: Bag-printing, Prev: Bag-enumerating the elements of a collection, Up: Bag 1.8.4 Bag: extracting items --------------------------- sortedByCount Answer a collection of counts with elements, sorted by decreasing count.  File: gst-base.info, Node: Bag-printing, Next: Bag-removing, Prev: Bag-extracting items, Up: Bag 1.8.5 Bag: printing ------------------- printOn: aStream Put on aStream a representation of the receiver  File: gst-base.info, Node: Bag-removing, Next: Bag-storing, Prev: Bag-printing, Up: Bag 1.8.6 Bag: removing ------------------- remove: oldObject ifAbsent: anExceptionBlock Remove oldObject from the collection and return it. If can't be found, answer instead the result of evaluationg anExceptionBlock  File: gst-base.info, Node: Bag-storing, Next: Bag-testing collections, Prev: Bag-removing, Up: Bag 1.8.7 Bag: storing ------------------ storeOn: aStream Put on aStream some Smalltalk code compiling to the receiver  File: gst-base.info, Node: Bag-testing collections, Prev: Bag-storing, Up: Bag 1.8.8 Bag: testing collections ------------------------------ = aBag Answer whether the receiver and aBag contain the same objects hash Answer an hash value for the receiver includes: anObject Answer whether we include anObject occurrencesOf: anObject Answer the number of occurrences of anObject found in the receiver size Answer the total number of objects found in the receiver  File: gst-base.info, Node: Behavior, Next: BindingDictionary, Prev: Bag, Up: Base classes 1.9 Behavior ============ Defined in namespace Smalltalk Superclass: Object Category: Language-Implementation I am the parent class of all "class" type methods. My instances know about the subclass/superclass relationships between classes, contain the description that instances are created from, and hold the method dictionary that's associated with each class. I provide methods for compiling methods, modifying the class inheritance hierarchy, examining the method dictionary, and iterating over the class hierarchy. * Menu: * Behavior-accessing class hierarchy:: (instance) * Behavior-accessing instances and variables:: (instance) * Behavior-accessing the method dictionary:: (instance) * Behavior-built ins:: (instance) * Behavior-builtin:: (instance) * Behavior-compilation:: (instance) * Behavior-compilation (alternative):: (instance) * Behavior-compiling:: (instance) * Behavior-compiling methods:: (instance) * Behavior-creating a class hierarchy:: (instance) * Behavior-enumerating:: (instance) * Behavior-evaluating:: (instance) * Behavior-instance creation:: (instance) * Behavior-instance variables:: (instance) * Behavior-method dictionary:: (instance) * Behavior-parsing class declarations:: (instance) * Behavior-pluggable behavior (not yet implemented):: (instance) * Behavior-printing hierarchy:: (instance) * Behavior-source code:: (instance) * Behavior-still unclassified:: (instance) * Behavior-support for lightweight classes:: (instance) * Behavior-testing functionality:: (instance) * Behavior-testing the class hierarchy:: (instance) * Behavior-testing the form of the instances:: (instance) * Behavior-testing the method dictionary:: (instance)  File: gst-base.info, Node: Behavior-accessing class hierarchy, Next: Behavior-accessing instances and variables, Up: Behavior 1.9.1 Behavior: accessing class hierarchy ----------------------------------------- allSubclasses Answer the direct and indirect subclasses of the receiver in a Set allSuperclasses Answer all the receiver's superclasses in a collection subclasses Answer the direct subclasses of the receiver in a Set superclass Answer the receiver's superclass (if any, otherwise answer nil) withAllSubclasses Answer a Set containing the receiver together with its direct and indirect subclasses withAllSuperclasses Answer the receiver and all of its superclasses in a collection  File: gst-base.info, Node: Behavior-accessing instances and variables, Next: Behavior-accessing the method dictionary, Prev: Behavior-accessing class hierarchy, Up: Behavior 1.9.2 Behavior: accessing instances and variables ------------------------------------------------- allClassVarNames Return all the class variables understood by the receiver allInstVarNames Answer the names of every instance variables the receiver contained in the receiver's instances allInstances Returns a set of all instances of the receiver allSharedPoolDictionaries Return the shared pools defined by the class and any of its superclasses, in the correct search order. allSharedPools Return the names of the shared pools defined by the class and any of its superclasses, in the correct search order. classPool Answer the class pool dictionary. Since Behavior does not support classes with class variables, we answer an empty one; adding variables to it results in an error. classVarNames Answer all the class variables for instances of the receiver indexOfInstVar: aString Answer the index of aString in the fixed instance variables of the instances of the receiver, or 0 if the variable is missing. indexOfInstVar: aString ifAbsent: aBlock Answer the index of aString in the fixed instance variables of the instances of the receiver, or 0 if the variable is missing. instVarNames Answer an Array containing the instance variables defined by the receiver instanceCount Return a count of all the instances of the receiver sharedPools Return the names of the shared pools defined by the class subclassInstVarNames Answer the names of the instance variables the receiver inherited from its superclass  File: gst-base.info, Node: Behavior-accessing the method dictionary, Next: Behavior-built ins, Prev: Behavior-accessing instances and variables, Up: Behavior 1.9.3 Behavior: accessing the method dictionary ----------------------------------------------- >> selector Return the compiled method associated with selector, from the local method dictionary. Error if not found. allSelectors Answer a Set of all the selectors understood by the receiver compiledMethodAt: selector Return the compiled method associated with selector, from the local method dictionary. Error if not found. compiledMethodAt: selector ifAbsent: aBlock Return the compiled method associated with selector, from the local method dictionary. Evaluate aBlock if not found. formattedSourceStringAt: selector Answer the method source code as a formatted string (if available) for the given selector. Requires package Parser. lookupAllSelectors: aSelector Answer a Set of all the compiled method associated with selector. from the local method dictionary and all of the superclasses. lookupSelector: aSelector Return the compiled method associated with selector, from the local method dictionary or one of a superclass; return nil if not found. parseTreeFor: selector Answer the parse tree for the given selector, or nil if there was an error. Requires the Parser package to be loaded. selectorAt: method Return selector for the given CompiledMethod selectors Answer a Set of the receiver's selectors sourceCodeAt: selector Answer source code (if available) for the given selector. sourceCodeAt: selector ifAbsent: aBlock Answer source code (if available) for the given selector. sourceMethodAt: selector This is too dependent on the original implementation  File: gst-base.info, Node: Behavior-built ins, Next: Behavior-builtin, Prev: Behavior-accessing the method dictionary, Up: Behavior 1.9.4 Behavior: built ins ------------------------- basicNewInFixedSpace Create a new instance of a class with no indexed instance variables. The instance is guaranteed not to move across garbage collections. Like #basicNew, this method should not be overridden. basicNewInFixedSpace: numInstanceVariables Create a new instance of a class with indexed instance variables. The instance has numInstanceVariables indexed instance variables. The instance is guaranteed not to move across garbage collections. Like #basicNew:, this method should not be overridden. flushCache Invalidate the method cache kept by the virtual machine. This message should not need to be called by user programs. methodsFor: category ifTrue: condition Compile the following code inside the receiver, with the given category, if condition is true; else ignore it primCompile: code Compile the code, a string or readable stream, with no category. Fail if the code does not obey Smalltalk syntax. Answer the generated CompiledMethod if it does. Do not send this in user code; use #compile: or related methods instead. primCompile: code ifError: aBlock As with #primCompile:, but evaluate aBlock (passing the file name, line number and description of the error) if the code does not obey Smalltalk syntax. Do not send this in user code; use #compile:ifError: or related methods instead. someInstance Private - Answer the first instance of the receiver in the object table  File: gst-base.info, Node: Behavior-builtin, Next: Behavior-compilation, Prev: Behavior-built ins, Up: Behavior 1.9.5 Behavior: builtin ----------------------- basicNew Create a new instance of a class with no indexed instance variables; this method must not be overridden. basicNew: numInstanceVariables Create a new instance of a class with indexed instance variables. The instance has numInstanceVariables indexed instance variables; this method must not be overridden. new Create a new instance of a class with no indexed instance variables new: numInstanceVariables Create a new instance of a class with indexed instance variables. The instance has numInstanceVariables indexed instance variables.  File: gst-base.info, Node: Behavior-compilation, Next: Behavior-compilation (alternative), Prev: Behavior-builtin, Up: Behavior 1.9.6 Behavior: compilation --------------------------- scopeDictionary Answer the dictionary that is used when the receiver is before a period in Smalltalk source code.  File: gst-base.info, Node: Behavior-compilation (alternative), Next: Behavior-compiling, Prev: Behavior-compilation, Up: Behavior 1.9.7 Behavior: compilation (alternative) ----------------------------------------- methods Don't use this, it's only present to file in from Smalltalk/V methodsFor Don't use this, it's only present to file in from Dolphin Smalltalk methodsFor: category ifFeatures: features Start compiling methods in the receiver if this implementation of Smalltalk has the given features, else skip the section methodsFor: category stamp: notUsed Don't use this, it's only present to file in from Squeak privateMethods Don't use this, it's only present to file in from IBM Smalltalk publicMethods Don't use this, it's only present to file in from IBM Smalltalk  File: gst-base.info, Node: Behavior-compiling, Next: Behavior-compiling methods, Prev: Behavior-compilation (alternative), Up: Behavior 1.9.8 Behavior: compiling ------------------------- compilerClass Return the class that will be used to compile the parse nodes into bytecodes.  File: gst-base.info, Node: Behavior-compiling methods, Next: Behavior-creating a class hierarchy, Prev: Behavior-compiling, Up: Behavior 1.9.9 Behavior: compiling methods --------------------------------- methodsFor: aCategoryString Calling this method prepares the parser to receive methods to be compiled and installed in the receiver's method dictionary. The methods are put in the category identified by the parameter. poolResolution Answer a PoolResolution class to be used for resolving pool variables while compiling methods on this class.  File: gst-base.info, Node: Behavior-creating a class hierarchy, Next: Behavior-enumerating, Prev: Behavior-compiling methods, Up: Behavior 1.9.10 Behavior: creating a class hierarchy ------------------------------------------- addSubclass: aClass Add aClass asone of the receiver's subclasses. removeSubclass: aClass Remove aClass from the list of the receiver's subclasses superclass: aClass Set the receiver's superclass.  File: gst-base.info, Node: Behavior-enumerating, Next: Behavior-evaluating, Prev: Behavior-creating a class hierarchy, Up: Behavior 1.9.11 Behavior: enumerating ---------------------------- allInstancesDo: aBlock Invokes aBlock for all instances of the receiver allSubclassesDo: aBlock Invokes aBlock for all subclasses, both direct and indirect. allSubinstancesDo: aBlock Invokes aBlock for all instances of each of the receiver's subclasses. allSuperclassesDo: aBlock Invokes aBlock for all superclasses, both direct and indirect. selectSubclasses: aBlock Return a Set of subclasses of the receiver satisfying aBlock. selectSuperclasses: aBlock Return a Set of superclasses of the receiver satisfying aBlock. subclassesDo: aBlock Invokes aBlock for all direct subclasses. withAllSubclassesDo: aBlock Invokes aBlock for the receiver and all subclasses, both direct and indirect. withAllSuperclassesDo: aBlock Invokes aBlock for the receiver and all superclasses, both direct and indirect.  File: gst-base.info, Node: Behavior-evaluating, Next: Behavior-instance creation, Prev: Behavior-enumerating, Up: Behavior 1.9.12 Behavior: evaluating --------------------------- evalString: aString to: anObject Answer the stack top at the end of the evaluation of the code in aString. The code is executed as part of anObject evalString: aString to: anObject ifError: aBlock Answer the stack top at the end of the evaluation of the code in aString. If aString cannot be parsed, evaluate aBlock (see compile:ifError:). The code is executed as part of anObject evaluate: code Evaluate Smalltalk expression in 'code' and return result. evaluate: code ifError: block Evaluate 'code'. If a parsing error is detected, invoke 'block' evaluate: code notifying: requestor Evaluate Smalltalk expression in 'code'. If a parsing error is encountered, send #error: to requestor evaluate: code to: anObject Evaluate Smalltalk expression as part of anObject's method definition evaluate: code to: anObject ifError: block Evaluate Smalltalk expression as part of anObject's method definition. This method is used to support Inspector expression evaluation. If a parsing error is encountered, invoke error block, 'block'  File: gst-base.info, Node: Behavior-instance creation, Next: Behavior-instance variables, Prev: Behavior-evaluating, Up: Behavior 1.9.13 Behavior: instance creation ---------------------------------- newInFixedSpace Create a new instance of a class without indexed instance variables. The instance is guaranteed not to move across garbage collections. If a subclass overrides #new, the changes will apply to this method too. newInFixedSpace: numInstanceVariables Create a new instance of a class with indexed instance variables. The instance has numInstanceVariables indexed instance variables. The instance is guaranteed not to move across garbage collections. If a subclass overrides #new:, the changes will apply to this method too.  File: gst-base.info, Node: Behavior-instance variables, Next: Behavior-method dictionary, Prev: Behavior-instance creation, Up: Behavior 1.9.14 Behavior: instance variables ----------------------------------- addInstVarName: aString Add the given instance variable to instance of the receiver instanceVariableNames: instVarNames Set the instance variables for the receiver to be those in instVarNames removeInstVarName: aString Remove the given instance variable from the receiver and recompile all of the receiver's subclasses  File: gst-base.info, Node: Behavior-method dictionary, Next: Behavior-parsing class declarations, Prev: Behavior-instance variables, Up: Behavior 1.9.15 Behavior: method dictionary ---------------------------------- addSelector: selector withMethod: compiledMethod Add the given compiledMethod to the method dictionary, giving it the passed selector. Answer compiledMethod compile: code Compile method source. If there are parsing errors, answer nil. Else, return a CompiledMethod result of compilation compile: code ifError: block Compile method source. If there are parsing errors, invoke exception block, 'block' passing file name, line number and error. Return a CompiledMethod result of compilation compile: code notifying: requestor Compile method source. If there are parsing errors, send #error: to the requestor object, else return a CompiledMethod result of compilation compileAll Recompile all selectors in the receiver. Ignore errors. compileAll: aNotifier Recompile all selectors in the receiver. Notify aNotifier by sending #error: messages if something goes wrong. compileAllSubclasses Recompile all selector of all subclasses. Notify aNotifier by sending #error: messages if something goes wrong. compileAllSubclasses: aNotifier Recompile all selector of all subclasses. Notify aNotifier by sending #error: messages if something goes wrong. createGetMethod: what Create a method accessing the variable `what'. createGetMethod: what default: value Create a method accessing the variable `what', with a default value of `value', using lazy initialization createSetMethod: what Create a method which sets the variable `what'. decompile: selector Decompile the bytecodes for the given selector. defineAsyncCFunc: cFuncNameString withSelectorArgs: selectorAndArgs args: argsArray Please lookup the part on the C interface in the manual. This method is deprecated, you should use the asyncCCall:args: attribute. defineCFunc: cFuncNameString withSelectorArgs: selectorAndArgs returning: returnTypeSymbol args: argsArray Please lookup the part on the C interface in the manual. This method is deprecated, you should use the cCall:returning:args: attribute. edit: selector Open Emacs to edit the method with the passed selector, then compile it methodDictionary Answer the receiver's method dictionary. Don't modify the method dictionary unless you exactly know what you're doing methodDictionary: aDictionary Set the receiver's method dictionary to aDictionary recompile: selector Recompile the given selector, answer nil if something goes wrong or the new CompiledMethod if everything's ok. recompile: selector notifying: aNotifier Recompile the given selector. If there are parsing errors, send #error: to the aNotifier object, else return a CompiledMethod result of compilation removeSelector: selector Remove the given selector from the method dictionary, answer the CompiledMethod attached to that selector removeSelector: selector ifAbsent: aBlock Remove the given selector from the method dictionary, answer the CompiledMethod attached to that selector. If the selector cannot be found, answer the result of evaluating aBlock. selectorsAndMethodsDo: aBlock Evaluate aBlock, passing for each evaluation a selector that's defined in the receiver and the corresponding method.  File: gst-base.info, Node: Behavior-parsing class declarations, Next: Behavior-pluggable behavior (not yet implemented), Prev: Behavior-method dictionary, Up: Behavior 1.9.16 Behavior: parsing class declarations ------------------------------------------- parseInstanceVariableString: variableString As with #parseVariableString:, but answer symbols that name the variables instead of strings. parseVariableString: aString Answer an array of instance variable names. aString should specify these in traditional file-in `instanceVariableNames' format. Signal an error if aString contains something other than valid Smalltalk variables.  File: gst-base.info, Node: Behavior-pluggable behavior (not yet implemented), Next: Behavior-printing hierarchy, Prev: Behavior-parsing class declarations, Up: Behavior 1.9.17 Behavior: pluggable behavior (not yet implemented) --------------------------------------------------------- debuggerClass Answer which class is to be used to debug a chain of contexts which includes the receiver. nil means 'do not debug'; other classes are sent #debuggingPriority and the one with the highest priority is picked. decompilerClass Answer the class that can be used to decompile methods, or nil if there is none (as is the case now). evaluatorClass Answer the class that can be used to evaluate doits, or nil if there is none (as is the case now). parserClass Answer the class that can be used to parse methods, or nil if there is none (as is the case now).  File: gst-base.info, Node: Behavior-printing hierarchy, Next: Behavior-source code, Prev: Behavior-pluggable behavior (not yet implemented), Up: Behavior 1.9.18 Behavior: printing hierarchy ----------------------------------- hierarchyIndent Answer the indent to be used by #printHierarchy - 4 by default printFullHierarchy Print my full hierarchy (i.e. all my superclasses and subclasses) on the terminal. printHierarchy Print my entire subclass hierarchy on the terminal.  File: gst-base.info, Node: Behavior-source code, Next: Behavior-still unclassified, Prev: Behavior-printing hierarchy, Up: Behavior 1.9.19 Behavior: source code ---------------------------- formattedSourceStringAt: aSelector ifAbsent: aBlock Answer the method source code as a formatted string. Requires package Parser.  File: gst-base.info, Node: Behavior-still unclassified, Next: Behavior-support for lightweight classes, Prev: Behavior-source code, Up: Behavior 1.9.20 Behavior: still unclassified ----------------------------------- allSharedPoolDictionariesDo: aBlock Answer the shared pools visible from methods in the metaclass, in the correct search order. parseNodeAt: selector Available only when the Parser package is loaded-Answer an RBMethodNode that compiles to my method named by selector. updateInstanceVars: variableArray shape: shape Update instance variables and instance spec of the class and all its subclasses. variableArray lists the new variables, including inherited ones.  File: gst-base.info, Node: Behavior-support for lightweight classes, Next: Behavior-testing functionality, Prev: Behavior-still unclassified, Up: Behavior 1.9.21 Behavior: support for lightweight classes ------------------------------------------------ article Answer an article (`a' or `an') which is ok for the receiver's name asClass Answer the first superclass that is a full-fledged Class object environment Answer the namespace that this class belongs to - the same as the superclass, since Behavior does not support namespaces yet. name Answer the class name; this prints to the name of the superclass enclosed in braces. This class name is used, for example, to print the receiver. nameIn: aNamespace Answer the class name when the class is referenced from aNamespace - a dummy one, since Behavior does not support names. printOn: aStream in: aNamespace Answer the class name when the class is referenced from aNamespace - a dummy one, since Behavior does not support names. securityPolicy Not commented. securityPolicy: aSecurityPolicy This method should not be called for instances of this class.  File: gst-base.info, Node: Behavior-testing functionality, Next: Behavior-testing the class hierarchy, Prev: Behavior-support for lightweight classes, Up: Behavior 1.9.22 Behavior: testing functionality -------------------------------------- isBehavior Answer `true'.  File: gst-base.info, Node: Behavior-testing the class hierarchy, Next: Behavior-testing the form of the instances, Prev: Behavior-testing functionality, Up: Behavior 1.9.23 Behavior: testing the class hierarchy -------------------------------------------- includesBehavior: aClass Returns true if aClass is the receiver or a superclass of the receiver. inheritsFrom: aClass Returns true if aClass is a superclass of the receiver kindOfSubclass Return a string indicating the type of class the receiver is shape Answer the symbolic shape of my instances. shape: shape Give the provided shape to the receiver's instances. The shape can be nil, or one of #byte #int8 #character #short #word #ushort #int #uint #int64 #uint64 #utf32 #float #double or #pointer. In addition, the special value #inherit means to use the shape of the superclass; note however that this is a static setting, and subclasses that used #inherit are not mutated when the superclass adopts a different shape.  File: gst-base.info, Node: Behavior-testing the form of the instances, Next: Behavior-testing the method dictionary, Prev: Behavior-testing the class hierarchy, Up: Behavior 1.9.24 Behavior: testing the form of the instances -------------------------------------------------- instSize Answer how many fixed instance variables are reserved to each of the receiver's instances isBits Answer whether my instances' variables are immediate, non-OOP values. isFixed Answer whether the receiver's instances have no indexed instance variables isIdentity Answer whether x = y implies x == y for instances of the receiver isImmediate Answer whether, if x is an instance of the receiver, x copy == x isPointers Answer whether the instance variables of the receiver's instances are objects isVariable Answer whether the receiver's instances have indexed instance variables  File: gst-base.info, Node: Behavior-testing the method dictionary, Prev: Behavior-testing the form of the instances, Up: Behavior 1.9.25 Behavior: testing the method dictionary ---------------------------------------------- canUnderstand: selector Returns true if the instances of the receiver understand the given selector hasMethods Return whether the receiver has any methods defined includesSelector: selector Returns true if the local method dictionary contains the given selector scopeHas: name ifTrue: aBlock If methods understood by the receiver's instances have access to a symbol named 'name', evaluate aBlock whichClassIncludesSelector: selector Answer which class in the receiver's hierarchy contains the implementation of selector used by instances of the class (nil if none does) whichSelectorsAccess: instVarName Answer a Set of selectors which access the given instance variable whichSelectorsAssign: instVarName Answer a Set of selectors which read the given instance variable whichSelectorsRead: instVarName Answer a Set of selectors which read the given instance variable whichSelectorsReferTo: anObject Returns a Set of selectors that refer to anObject whichSelectorsReferToByteCode: aByteCode Return the collection of selectors in the class which reference the byte code, aByteCode  File: gst-base.info, Node: BindingDictionary, Next: BlockClosure, Prev: Behavior, Up: Base classes 1.10 BindingDictionary ====================== Defined in namespace Smalltalk Superclass: Dictionary Category: Language-Implementation I am a special form of dictionary that provides special ways to access my keys, which typically begin with an uppercase letter; also, my associations are actually VariableBinding instances. My keys are (expected to be) symbols, so I use == to match searched keys to those in the dictionary - this is done expecting that it brings a bit more speed. * Menu: * BindingDictionary-accessing:: (instance) * BindingDictionary-basic & copying:: (instance) * BindingDictionary-copying:: (instance) * BindingDictionary-forward declarations:: (instance) * BindingDictionary-printing:: (instance) * BindingDictionary-testing:: (instance)  File: gst-base.info, Node: BindingDictionary-accessing, Next: BindingDictionary-basic & copying, Up: BindingDictionary 1.10.1 BindingDictionary: accessing ----------------------------------- define: aSymbol Define aSymbol as equal to nil inside the receiver. Fail if such a variable already exists (use #at:put: if you don't want to fail) doesNotUnderstand: aMessage Try to map unary selectors to read accesses to the Namespace, and one-argument keyword selectors to write accesses. Note that: a) this works only if the selector has an uppercase first letter; and b) `aNamespace Variable: value' is the same as `aNamespace set: #Variable to: value', not the same as `aNamespace at: #Variable put: value' -- the latter always refers to the current namespace, while the former won't define a new variable, instead searching in superspaces (and raising an error if the variable cannot be found). environment Answer the environment to which the receiver is connected. This can be the class for a dictionary that holds class variables, or the super-namespace. In general it is used to compute the receiver's name. environment: anObject Set the environment to which the receiver is connected. This can be the class for a dictionary that holds class variables, or the super-namespace. In general it is used to compute the receiver's name. import: aSymbol from: aNamespace Add to the receiver the symbol aSymbol, associated to the same value as in aNamespace. Fail if aNamespace does not contain the given key. name Answer the receiver's name, which by default is the same as the name of the receiver's environment. nameIn: aNamespace Answer the receiver's name when referred to from aNamespace; by default the computation is deferred to the receiver's environment.  File: gst-base.info, Node: BindingDictionary-basic & copying, Next: BindingDictionary-copying, Prev: BindingDictionary-accessing, Up: BindingDictionary 1.10.2 BindingDictionary: basic & copying ----------------------------------------- = arg Answer whether the receiver is equal to arg. The equality test is by default the same as that for equal objects. = must not fail; answer false if the receiver cannot be compared to arg hash Answer an hash value for the receiver. This is the same as the object's #identityHash.  File: gst-base.info, Node: BindingDictionary-copying, Next: BindingDictionary-forward declarations, Prev: BindingDictionary-basic & copying, Up: BindingDictionary 1.10.3 BindingDictionary: copying --------------------------------- copy Answer the receiver. copyEmpty: newSize Answer an empty copy of the receiver whose size is newSize copyEmptyForCollect Answer an empty copy of the receiver which is filled in to compute the result of #collect: copyEmptyForCollect: size Answer an empty copy of the receiver which is filled in to compute the result of #collect: deepCopy Answer the receiver. shallowCopy Answer the receiver.  File: gst-base.info, Node: BindingDictionary-forward declarations, Next: BindingDictionary-printing, Prev: BindingDictionary-copying, Up: BindingDictionary 1.10.4 BindingDictionary: forward declarations ---------------------------------------------- at: key put: value Store value as associated to the given key. If any, recycle Associations temporarily stored by the compiler inside the `Undeclared' dictionary.  File: gst-base.info, Node: BindingDictionary-printing, Next: BindingDictionary-testing, Prev: BindingDictionary-forward declarations, Up: BindingDictionary 1.10.5 BindingDictionary: printing ---------------------------------- printOn: aStream in: aNamespace Print the receiver's name when referred to from aNamespace; by default the computation is deferred to the receiver's environment.  File: gst-base.info, Node: BindingDictionary-testing, Prev: BindingDictionary-printing, Up: BindingDictionary 1.10.6 BindingDictionary: testing --------------------------------- species Answer `IdentityDictionary'.  File: gst-base.info, Node: BlockClosure, Next: BlockContext, Prev: BindingDictionary, Up: Base classes 1.11 BlockClosure ================= Defined in namespace Smalltalk Superclass: Object Category: Language-Implementation I am a factotum class. My instances represent Smalltalk blocks, portions of executeable code that have access to the environment that they were declared in, take parameters, and can be passed around as objects to be executed by methods outside the current class. Block closures are sent a message to compute their value and create a new execution context; this property can be used in the construction of control flow methods. They also provide some methods that are used in the creation of Processes from blocks. * Menu: * BlockClosure class-instance creation:: (class) * BlockClosure class-testing:: (class) * BlockClosure-accessing:: (instance) * BlockClosure-built ins:: (instance) * BlockClosure-control structures:: (instance) * BlockClosure-exception handling:: (instance) * BlockClosure-multiple process:: (instance) * BlockClosure-overriding:: (instance) * BlockClosure-testing:: (instance) * BlockClosure-unwind protection:: (instance)  File: gst-base.info, Node: BlockClosure class-instance creation, Next: BlockClosure class-testing, Up: BlockClosure 1.11.1 BlockClosure class: instance creation -------------------------------------------- block: aCompiledBlock Answer a BlockClosure that activates the passed CompiledBlock. block: aCompiledBlock receiver: anObject Answer a BlockClosure that activates the passed CompiledBlock with the given receiver. block: aCompiledBlock receiver: anObject outerContext: aContext Answer a BlockClosure that activates the passed CompiledBlock with the given receiver. numArgs: args numTemps: temps bytecodes: bytecodes depth: depth literals: literalArray Answer a BlockClosure for a new CompiledBlock that is created using the passed parameters. To make it work, you must put the BlockClosure into a CompiledMethod's literals.  File: gst-base.info, Node: BlockClosure class-testing, Next: BlockClosure-accessing, Prev: BlockClosure class-instance creation, Up: BlockClosure 1.11.2 BlockClosure class: testing ---------------------------------- isImmediate Answer whether, if x is an instance of the receiver, x copy == x  File: gst-base.info, Node: BlockClosure-accessing, Next: BlockClosure-built ins, Prev: BlockClosure class-testing, Up: BlockClosure 1.11.3 BlockClosure: accessing ------------------------------ argumentCount Answer the number of arguments passed to the receiver block Answer the CompiledBlock which contains the receiver's bytecodes block: aCompiledBlock Set the CompiledBlock which contains the receiver's bytecodes finalIP Answer the last instruction that can be executed by the receiver fixTemps This should fix the values of the temporary variables used in the block that are ordinarily shared with the method in which the block is defined. Not defined yet, but it is not harmful that it isn't. Answer the receiver. initialIP Answer the initial instruction pointer into the receiver. method Answer the CompiledMethod in which the receiver lies numArgs Answer the number of arguments passed to the receiver numTemps Answer the number of temporary variables used by the receiver outerContext Answer the method/block context which is the immediate outer of the receiver outerContext: containingContext Set the method/block context which is the immediate outer of the receiver receiver Answer the object that is used as `self' when executing the receiver (if nil, it might mean that the receiver is not valid though...) receiver: anObject Set the object that is used as `self' when executing the receiver stackDepth Answer the number of stack slots needed for the receiver  File: gst-base.info, Node: BlockClosure-built ins, Next: BlockClosure-control structures, Prev: BlockClosure-accessing, Up: BlockClosure 1.11.4 BlockClosure: built ins ------------------------------ cull: arg1 Evaluate the receiver, passing arg1 as the only parameter if the receiver has parameters. cull: arg1 cull: arg2 Evaluate the receiver, passing arg1 and arg2 as parameters if the receiver accepts them. cull: arg1 cull: arg2 cull: arg3 Evaluate the receiver, passing arg1, arg2 and arg3 as parameters if the receiver accepts them. value Evaluate the receiver passing no parameters value: arg1 Evaluate the receiver passing arg1 as the only parameter value: arg1 value: arg2 Evaluate the receiver passing arg1 and arg2 as the parameters value: arg1 value: arg2 value: arg3 Evaluate the receiver passing arg1, arg2 and arg3 as the parameters valueWithArguments: argumentsArray Evaluate the receiver passing argArray's elements as the parameters  File: gst-base.info, Node: BlockClosure-control structures, Next: BlockClosure-exception handling, Prev: BlockClosure-built ins, Up: BlockClosure 1.11.5 BlockClosure: control structures --------------------------------------- repeat Evaluate the receiver 'forever' (actually until a return is executed or the process is terminated). whileFalse Evaluate the receiver until it returns true whileFalse: aBlock Evaluate the receiver. If it returns false, evaluate aBlock and restart whileTrue Evaluate the receiver until it returns false whileTrue: aBlock Evaluate the receiver. If it returns true, evaluate aBlock and restart  File: gst-base.info, Node: BlockClosure-exception handling, Next: BlockClosure-multiple process, Prev: BlockClosure-control structures, Up: BlockClosure 1.11.6 BlockClosure: exception handling --------------------------------------- ifError: aBlock Evaluate the receiver; when #error: is called, pass to aBlock the receiver and the parameter, and answer the result of evaluating aBlock. If another exception is raised, it is passed to an outer handler; if no exception is raised, the result of evaluating the receiver is returned. on: anException do: aBlock Evaluate the receiver; when anException is signaled, evaluate aBlock passing a Signal describing the exception. Answer either the result of evaluating the receiver or the parameter of a Signal>>#return: on: e1 do: b1 on: e2 do: b2 Evaluate the receiver; when e1 or e2 are signaled, evaluate respectively b1 or b2, passing a Signal describing the exception. Answer either the result of evaluating the receiver or the argument of a Signal>>#return: on: e1 do: b1 on: e2 do: b2 on: e3 do: b3 Evaluate the receiver; when e1, e2 or e3 are signaled, evaluate respectively b1, b2 or b3, passing a Signal describing the exception. Answer either the result of evaluating the receiver or the parameter of a Signal>>#return: on: e1 do: b1 on: e2 do: b2 on: e3 do: b3 on: e4 do: b4 Evaluate the receiver; when e1, e2, e3 or e4 are signaled, evaluate respectively b1, b2, b3 or b4, passing a Signal describing the exception. Answer either the result of evaluating the receiver or the parameter of a Signal>>#return: on: e1 do: b1 on: e2 do: b2 on: e3 do: b3 on: e4 do: b4 on: e5 do: b5 Evaluate the receiver; when e1, e2, e3, e4 or e5 are signaled, evaluate respectively b1, b2, b3, b4 or b5, passing a Signal describing the exception. Answer either the result of evaluating the receiver or the parameter of a Signal>>#return:  File: gst-base.info, Node: BlockClosure-multiple process, Next: BlockClosure-overriding, Prev: BlockClosure-exception handling, Up: BlockClosure 1.11.7 BlockClosure: multiple process ------------------------------------- fork Create a new process executing the receiver and start it forkAt: priority Create a new process executing the receiver with given priority and start it forkWithoutPreemption Evaluate the receiver in a process that cannot be preempted. If the receiver expect a parameter, pass the current process. newProcess Create a new process executing the receiver in suspended state. The priority is the same as for the calling process. The receiver must not contain returns newProcessWith: anArray Create a new process executing the receiver with the passed arguments, and leave it in suspended state. The priority is the same as for the calling process. The receiver must not contain returns valueWithoutInterrupts Evaluate aBlock and delay all interrupts that are requested to the active process during its execution to after aBlock returns. valueWithoutPreemption Evaluate the receiver with external interrupts disabled. This effectively disables preemption as long as the block does not explicitly yield control, wait on semaphores, and the like.  File: gst-base.info, Node: BlockClosure-overriding, Next: BlockClosure-testing, Prev: BlockClosure-multiple process, Up: BlockClosure 1.11.8 BlockClosure: overriding ------------------------------- copy Answer the receiver. deepCopy Answer a shallow copy.  File: gst-base.info, Node: BlockClosure-testing, Next: BlockClosure-unwind protection, Prev: BlockClosure-overriding, Up: BlockClosure 1.11.9 BlockClosure: testing ---------------------------- hasMethodReturn Answer whether the block contains a method return  File: gst-base.info, Node: BlockClosure-unwind protection, Prev: BlockClosure-testing, Up: BlockClosure 1.11.10 BlockClosure: unwind protection --------------------------------------- ensure: aBlock Evaluate the receiver; when any exception is signaled exit returning the result of evaluating aBlock; if no exception is raised, return the result of evaluating aBlock when the receiver has ended ifCurtailed: aBlock Evaluate the receiver; if its execution triggers an unwind which truncates the execution of the block (`curtails' the block), evaluate aBlock. The three cases which can curtail the execution of the receiver are: a non-local return in the receiver, a non-local return in a block evaluated by the receiver which returns past the receiver itself, and an exception raised and not resumed during the execution of the receiver. valueWithUnwind Evaluate the receiver. Any errors caused by the block will cause a backtrace, but execution will continue in the method that sent #valueWithUnwind, after that call. Example: [ 1 / 0 ] valueWithUnwind. 'unwind works!' printNl. Important: this method is public, but it is intended to be used in very special cases (as a rule of thumb, use it only when the corresponding C code uses the _gst_prepare_execution_environment and _gst_finish_execution_environment functions). You should usually rely on #ensure: and #on:do:.  File: gst-base.info, Node: BlockContext, Next: Boolean, Prev: BlockClosure, Up: Base classes 1.12 BlockContext ================= Defined in namespace Smalltalk Superclass: ContextPart Category: Language-Implementation My instances represent executing Smalltalk blocks, which are portions of executeable code that have access to the environment that they were declared in, take parameters, and result from BlockClosure objects created to be executed by methods outside the current class. Block contexts are created by messages sent to compute a closure's value. They contain a stack and also provide some methods that can be used in inspection or debugging. * Menu: * BlockContext-accessing:: (instance) * BlockContext-debugging:: (instance) * BlockContext-printing:: (instance)  File: gst-base.info, Node: BlockContext-accessing, Next: BlockContext-debugging, Up: BlockContext 1.12.1 BlockContext: accessing ------------------------------ caller Answer the context that called the receiver home Answer the MethodContext to which the receiver refers, or nil if it has been optimized away isBlock Answer whether the receiver is a block context isDisabled Answers false, because contexts that are skipped when doing a return are always MethodContexts. BlockContexts are removed from the chain whenever a non-local return is done, while MethodContexts need to stay there in case there is a non-local return from the #ensure: block. isEnvironment To create a valid execution environment for the interpreter even before it starts, GST creates a fake context whose selector is nil and which can be used as a marker for the current execution environment. Answer whether the receiver is that kind of context (always false, since those contexts are always MethodContexts). isUnwind Answers whether the context must continue execution even after a non-local return (a return from the enclosing method of a block, or a call to the #continue: method of ContextPart). Such contexts are created only by #ensure: and are always MethodContexts. nthOuterContext: n Answer the n-th outer block/method context for the receiver outerContext Answer the outer block/method context for the receiver  File: gst-base.info, Node: BlockContext-debugging, Next: BlockContext-printing, Prev: BlockContext-accessing, Up: BlockContext 1.12.2 BlockContext: debugging ------------------------------ isInternalExceptionHandlingContext Answer whether the receiver is a context that should be hidden to the user when presenting a backtrace. Such contexts are never blocks, but check the rest of the chain.  File: gst-base.info, Node: BlockContext-printing, Prev: BlockContext-debugging, Up: BlockContext 1.12.3 BlockContext: printing ----------------------------- printOn: aStream Print a representation for the receiver on aStream  File: gst-base.info, Node: Boolean, Next: ByteArray, Prev: BlockContext, Up: Base classes 1.13 Boolean ============ Defined in namespace Smalltalk Superclass: Object Category: Language-Data types I have two instances in the Smalltalk system: true and false. I provide methods that are conditional on boolean values, such as conditional execution and loops, and conditional testing, such as conditional and and conditional or. I should say that I appear to provide those operations; my subclasses True and False actually provide those operations. * Menu: * Boolean class-testing:: (class) * Boolean-basic:: (instance) * Boolean-C hacks:: (instance) * Boolean-overriding:: (instance) * Boolean-storing:: (instance)  File: gst-base.info, Node: Boolean class-testing, Next: Boolean-basic, Up: Boolean 1.13.1 Boolean class: testing ----------------------------- isIdentity Answer whether x = y implies x == y for instances of the receiver isImmediate Answer whether, if x is an instance of the receiver, x copy == x  File: gst-base.info, Node: Boolean-basic, Next: Boolean-C hacks, Prev: Boolean class-testing, Up: Boolean 1.13.2 Boolean: basic --------------------- & aBoolean This method's functionality should be implemented by subclasses of Boolean and: aBlock This method's functionality should be implemented by subclasses of Boolean eqv: aBoolean This method's functionality should be implemented by subclasses of Boolean ifFalse: falseBlock This method's functionality should be implemented by subclasses of Boolean ifFalse: falseBlock ifTrue: trueBlock This method's functionality should be implemented by subclasses of Boolean ifTrue: trueBlock This method's functionality should be implemented by subclasses of Boolean ifTrue: trueBlock ifFalse: falseBlock This method's functionality should be implemented by subclasses of Boolean not This method's functionality should be implemented by subclasses of Boolean or: aBlock This method's functionality should be implemented by subclasses of Boolean xor: aBoolean This method's functionality should be implemented by subclasses of Boolean | aBoolean This method's functionality should be implemented by subclasses of Boolean  File: gst-base.info, Node: Boolean-C hacks, Next: Boolean-overriding, Prev: Boolean-basic, Up: Boolean 1.13.3 Boolean: C hacks ----------------------- asCBooleanValue This method's functionality should be implemented by subclasses of Boolean  File: gst-base.info, Node: Boolean-overriding, Next: Boolean-storing, Prev: Boolean-C hacks, Up: Boolean 1.13.4 Boolean: overriding -------------------------- deepCopy Answer the receiver. shallowCopy Answer the receiver.  File: gst-base.info, Node: Boolean-storing, Prev: Boolean-overriding, Up: Boolean 1.13.5 Boolean: storing ----------------------- isLiteralObject Answer whether the receiver is expressible as a Smalltalk literal. storeLiteralOn: aStream Store on aStream some Smalltalk code which compiles to the receiver storeOn: aStream Store on aStream some Smalltalk code which compiles to the receiver  File: gst-base.info, Node: ByteArray, Next: CAggregate, Prev: Boolean, Up: Base classes 1.14 ByteArray ============== Defined in namespace Smalltalk Superclass: ArrayedCollection Category: Collections-Sequenceable My instances are similar to strings in that they are both represented as a sequence of bytes, but my individual elements are integers, where as a String's elements are characters. * Menu: * ByteArray class-instance creation:: (class) * ByteArray-basic:: (instance) * ByteArray-built ins:: (instance) * ByteArray-CObject:: (instance) * ByteArray-converting:: (instance) * ByteArray-more advanced accessing:: (instance) * ByteArray-storing:: (instance)  File: gst-base.info, Node: ByteArray class-instance creation, Next: ByteArray-basic, Up: ByteArray 1.14.1 ByteArray class: instance creation ----------------------------------------- fromCData: aCObject size: anInteger Answer a ByteArray containing anInteger bytes starting at the location pointed to by aCObject  File: gst-base.info, Node: ByteArray-basic, Next: ByteArray-built ins, Prev: ByteArray class-instance creation, Up: ByteArray 1.14.2 ByteArray: basic ----------------------- = aCollection Answer whether the receiver's items match those in aCollection indexOf: anElement startingAt: anIndex Answer the first index > anIndex which contains anElement. Invoke exceptionBlock and answer its result if no item is found indexOf: anElement startingAt: anIndex ifAbsent: exceptionBlock Answer the first index > anIndex which contains anElement. Invoke exceptionBlock and answer its result if no item is found  File: gst-base.info, Node: ByteArray-built ins, Next: ByteArray-CObject, Prev: ByteArray-basic, Up: ByteArray 1.14.3 ByteArray: built ins --------------------------- asCData: aCType Allocate memory with malloc for a copy of the receiver, and return it converted to a CObject with the given type at: anIndex ifAbsent: aBlock Answer the index-th indexed instance variable of the receiver byteAt: index Answer the index-th indexed instance variable of the receiver byteAt: index put: value Store the `value' byte in the index-th indexed instance variable of the receiver hash Answer an hash value for the receiver replaceFrom: start to: stop with: aByteArray startingAt: replaceStart Replace the characters from start to stop with the bytes contained in aByteArray (which, actually, can be any variable byte class), starting at the replaceStart location of aByteArray replaceFrom: start to: stop withString: aString startingAt: replaceStart Replace the characters from start to stop with the ASCII codes contained in aString (which, actually, can be any variable byte class), starting at the replaceStart location of aString  File: gst-base.info, Node: ByteArray-CObject, Next: ByteArray-converting, Prev: ByteArray-built ins, Up: ByteArray 1.14.4 ByteArray: CObject ------------------------- asCData Allocate memory with malloc for a copy of the receiver, and return a pointer to it as a CByte. castTo: type Give access to the receiver as a value with the given CType.  File: gst-base.info, Node: ByteArray-converting, Next: ByteArray-more advanced accessing, Prev: ByteArray-CObject, Up: ByteArray 1.14.5 ByteArray: converting ---------------------------- asString Answer a String whose character's ASCII codes are the receiver's contents asUnicodeString Answer a UnicodeString whose character's codes are the receiver's contents. This is not implemented unless you load the I18N package.  File: gst-base.info, Node: ByteArray-more advanced accessing, Next: ByteArray-storing, Prev: ByteArray-converting, Up: ByteArray 1.14.6 ByteArray: more advanced accessing ----------------------------------------- charAt: index Access the C char at the given index in the receiver. The value is returned as a Smalltalk Character. Indices are 1-based just like for other Smalltalk access. charAt: index put: value Store as a C char the Smalltalk Character or Integer object identified by `value', at the given index in the receiver, using sizeof(char) bytes - i.e. 1 byte. Indices are 1-based just like for other Smalltalk access. doubleAt: index Access the C double at the given index in the receiver. Indices are 1-based just like for other Smalltalk access. doubleAt: index put: value Store the Smalltalk Float object identified by `value', at the given index in the receiver, writing it like a C double. Indices are 1-based just like for other Smalltalk access. floatAt: index Access the C float at the given index in the receiver. Indices are 1-based just like for other Smalltalk access. floatAt: index put: value Store the Smalltalk Float object identified by `value', at the given index in the receiver, writing it like a C float. Indices are 1-based just like for other Smalltalk access. intAt: index Access the C int at the given index in the receiver. Indices are 1-based just like for other Smalltalk access. intAt: index put: value Store the Smalltalk Integer object identified by `value', at the given index in the receiver, using sizeof(int) bytes. Indices are 1-based just like for other Smalltalk access. longAt: index Access the C long int at the given index in the receiver. Indices are 1-based just like for other Smalltalk access. longAt: index put: value Store the Smalltalk Integer object identified by `value', at the given index in the receiver, using sizeof(long) bytes. Indices are 1-based just like for other Smalltalk access. longDoubleAt: index Access the C long double at the given index in the receiver. Indices are 1-based just like for other Smalltalk access. longDoubleAt: index put: value Store the Smalltalk Float object identified by `value', at the given index in the receiver, writing it like a C double. Indices are 1-based just like for other Smalltalk access. objectAt: index Access the Smalltalk object (OOP) at the given index in the receiver. Indices are 1-based just like for other Smalltalk access. objectAt: index put: value Store a pointer (OOP) to the Smalltalk object identified by `value', at the given index in the receiver. Indices are 1-based just like for other Smalltalk access. shortAt: index Access the C short int at the given index in the receiver. Indices are 1-based just like for other Smalltalk access. shortAt: index put: value Store the Smalltalk Integer object identified by `value', at the given index in the receiver, using sizeof(short) bytes. Indices are 1-based just like for other Smalltalk access. stringAt: index Access the string pointed by the C `char *' at the given index in the receiver. Indices are 1-based just like for other Smalltalk access. stringAt: index put: value Store the Smalltalk String object identified by `value', at the given index in the receiver, writing it like a *FRESHLY ALLOCATED* C string. It is the caller's responsibility to free it if necessary. Indices are 1-based just like for other Smalltalk access. ucharAt: index Access the C unsigned char at the given index in the receiver. The value is returned as a Smalltalk Character. Indices are 1-based just like for other Smalltalk access. ucharAt: index put: value Store as a C char the Smalltalk Character or Integer object identified by `value', at the given index in the receiver, using sizeof(char) bytes - i.e. 1 byte. Indices are 1-based just like for other Smalltalk access. uintAt: index Access the C unsigned int at the given index in the receiver. Indices are 1-based just like for other Smalltalk access. uintAt: index put: value Store the Smalltalk Integer object identified by `value', at the given index in the receiver, using sizeof(int) bytes. Indices are 1-based just like for other Smalltalk access. ulongAt: index Access the C unsigned long int at the given index in the receiver. Indices are 1-based just like for other Smalltalk access. ulongAt: index put: value Store the Smalltalk Integer object identified by `value', at the given index in the receiver, using sizeof(long) bytes. Indices are 1-based just like for other Smalltalk access. unsignedCharAt: index Access the C unsigned char at the given index in the receiver. The value is returned as a Smalltalk Character. Indices are 1-based just like for other Smalltalk access. unsignedCharAt: index put: value Store as a C char the Smalltalk Character or Integer object identified by `value', at the given index in the receiver, using sizeof(char) bytes - i.e. 1 byte. Indices are 1-based just like for other Smalltalk access. unsignedIntAt: index Access the C unsigned int at the given index in the receiver. Indices are 1-based just like for other Smalltalk access. unsignedIntAt: index put: value Store the Smalltalk Integer object identified by `value', at the given index in the receiver, using sizeof(int) bytes. Indices are 1-based just like for other Smalltalk access. unsignedLongAt: index Access the C unsigned long int at the given index in the receiver. Indices are 1-based just like for other Smalltalk access. unsignedLongAt: index put: value Store the Smalltalk Integer object identified by `value', at the given index in the receiver, using sizeof(long) bytes. Indices are 1-based just like for other Smalltalk access. unsignedShortAt: index Access the C unsigned short int at the given index in the receiver. Indices are 1-based just like for other Smalltalk access. unsignedShortAt: index put: value Store the Smalltalk Integer object identified by `value', at the given index in the receiver, using sizeof(short) bytes. Indices are 1-based just like for other Smalltalk access. ushortAt: index Access the C unsigned short int at the given index in the receiver. Indices are 1-based just like for other Smalltalk access. ushortAt: index put: value Store the Smalltalk Integer object identified by `value', at the given index in the receiver, using sizeof(short) bytes. Indices are 1-based just like for other Smalltalk access.  File: gst-base.info, Node: ByteArray-storing, Prev: ByteArray-more advanced accessing, Up: ByteArray 1.14.7 ByteArray: storing ------------------------- isLiteralObject Answer whether the receiver is expressible as a Smalltalk literal. storeLiteralOn: aStream Put a Smalltalk literal evaluating to the receiver on aStream. storeOn: aStream Put Smalltalk code evaluating to the receiver on aStream.  File: gst-base.info, Node: CAggregate, Next: CallinProcess, Prev: ByteArray, Up: Base classes 1.15 CAggregate =============== Defined in namespace Smalltalk Superclass: CObject Category: Language-C interface * Menu: * CAggregate class-accessing:: (class) * CAggregate-accessing:: (instance)  File: gst-base.info, Node: CAggregate class-accessing, Next: CAggregate-accessing, Up: CAggregate 1.15.1 CAggregate class: accessing ---------------------------------- alignof Answer the receiver's instances required aligment sizeof Answer the receiver's instances size  File: gst-base.info, Node: CAggregate-accessing, Prev: CAggregate class-accessing, Up: CAggregate 1.15.2 CAggregate: accessing ---------------------------- elementType Answer the type over which the receiver is constructed.  File: gst-base.info, Node: CallinProcess, Next: CArray, Prev: CAggregate, Up: Base classes 1.16 CallinProcess ================== Defined in namespace Smalltalk Superclass: Process Category: Language-Processes I represent a unit of computation for which external C code requested execution, so I must store the returned value once my computation terminates and I must not survive across image saves (since those who invoked me no longer exist). I am otherwise equivalent to a Process. * Menu: * CallinProcess-debugging:: (instance)  File: gst-base.info, Node: CallinProcess-debugging, Up: CallinProcess 1.16.1 CallinProcess: debugging ------------------------------- detach Continue running the receiver as a normal Process, and return nil from the callin.  File: gst-base.info, Node: CArray, Next: CArrayCType, Prev: CallinProcess, Up: Base classes 1.17 CArray =========== Defined in namespace Smalltalk Superclass: CAggregate Category: Language-C interface * Menu: * CArray-accessing:: (instance)  File: gst-base.info, Node: CArray-accessing, Up: CArray 1.17.1 CArray: accessing ------------------------ alignof Answer the receiver's required aligment sizeof Answer the receiver's size  File: gst-base.info, Node: CArrayCType, Next: CBoolean, Prev: CArray, Up: Base classes 1.18 CArrayCType ================ Defined in namespace Smalltalk Superclass: CPtrCType Category: Language-C interface * Menu: * CArrayCType class-instance creation:: (class) * CArrayCType-accessing:: (instance) * CArrayCType-basic:: (instance) * CArrayCType-storing:: (instance)  File: gst-base.info, Node: CArrayCType class-instance creation, Next: CArrayCType-accessing, Up: CArrayCType 1.18.1 CArrayCType class: instance creation ------------------------------------------- elementType: aCType This method should not be called for instances of this class. elementType: aCType numberOfElements: anInteger Answer a new instance of CPtrCType that maps an array whose elements are of the given CType, and whose size is exactly anInteger elements (of course, anInteger only matters for allocation, not for access, since no out-of-bounds protection is provided for C objects). from: type Private - Called by CType>>from: for arrays  File: gst-base.info, Node: CArrayCType-accessing, Next: CArrayCType-basic, Prev: CArrayCType class-instance creation, Up: CArrayCType 1.18.2 CArrayCType: accessing ----------------------------- alignof Answer the alignment of the receiver's instances numberOfElements Answer the number of elements in the receiver's instances sizeof Answer the size of the receiver's instances  File: gst-base.info, Node: CArrayCType-basic, Next: CArrayCType-storing, Prev: CArrayCType-accessing, Up: CArrayCType 1.18.3 CArrayCType: basic ------------------------- = anObject Return whether the receiver and anObject are equal. hash Return a hash code for the receiver.  File: gst-base.info, Node: CArrayCType-storing, Prev: CArrayCType-basic, Up: CArrayCType 1.18.4 CArrayCType: storing --------------------------- storeOn: aStream As with super.  File: gst-base.info, Node: CBoolean, Next: CByte, Prev: CArrayCType, Up: Base classes 1.19 CBoolean ============= Defined in namespace Smalltalk Superclass: CByte Category: Language-C interface I return true if a byte is not zero, false otherwise. * Menu: * CBoolean class-conversion:: (class) * CBoolean-accessing:: (instance)  File: gst-base.info, Node: CBoolean class-conversion, Next: CBoolean-accessing, Up: CBoolean 1.19.1 CBoolean class: conversion --------------------------------- type Answer a CType for the receiver  File: gst-base.info, Node: CBoolean-accessing, Prev: CBoolean class-conversion, Up: CBoolean 1.19.2 CBoolean: accessing -------------------------- value Get the receiver's value - answer true if it is != 0, false if it is 0. value: aBoolean Set the receiver's value - it's the same as for CBytes, but we get a Boolean, not a Character  File: gst-base.info, Node: CByte, Next: CCallable, Prev: CBoolean, Up: Base classes 1.20 CByte ========== Defined in namespace Smalltalk Superclass: CUChar Category: Language-C interface You know what a byte is, don't you?!? * Menu: * CByte class-conversion:: (class) * CByte-accessing:: (instance)  File: gst-base.info, Node: CByte class-conversion, Next: CByte-accessing, Up: CByte 1.20.1 CByte class: conversion ------------------------------ cObjStoredType Nothing special in the default case - answer a CType for the receiver type Answer a CType for the receiver  File: gst-base.info, Node: CByte-accessing, Prev: CByte class-conversion, Up: CByte 1.20.2 CByte: accessing ----------------------- cObjStoredType Nothing special in the default case - answer the receiver's CType value Answer the value the receiver is pointing to. The returned value is a SmallInteger value: aValue Set the receiver to point to the value, aValue (a SmallInteger).  File: gst-base.info, Node: CCallable, Next: CCallbackDescriptor, Prev: CByte, Up: Base classes 1.21 CCallable ============== Defined in namespace Smalltalk Superclass: CObject Category: Language-C interface I am not part of the Smalltalk definition. My instances contain information about C functions that can be called from within Smalltalk, such as number and type of parameters. This information is used by the C callout mechanism to perform the actual call-out to C routines. * Menu: * CCallable class-instance creation:: (class) * CCallable-accessing:: (instance) * CCallable-calling:: (instance) * CCallable-restoring:: (instance)  File: gst-base.info, Node: CCallable class-instance creation, Next: CCallable-accessing, Up: CCallable 1.21.1 CCallable class: instance creation ----------------------------------------- for: aCObject returning: returnTypeSymbol withArgs: argsArray Answer a CFunctionDescriptor with the given address, return type and arguments. The address will be reset to NULL upon image save (and it's the user's task to figure out a way to reinitialize it!)  File: gst-base.info, Node: CCallable-accessing, Next: CCallable-calling, Prev: CCallable class-instance creation, Up: CCallable 1.21.2 CCallable: accessing --------------------------- isValid Answer whether the object represents a valid function. returnType Not commented.  File: gst-base.info, Node: CCallable-calling, Next: CCallable-restoring, Prev: CCallable-accessing, Up: CCallable 1.21.3 CCallable: calling ------------------------- asyncCall Perform the call-out for the function represented by the receiver. The arguments (and the receiver if one of the arguments has type #self or #selfSmalltalk) are taken from the parent context. Asynchronous call-outs don't return a value, but if the function calls back into Smalltalk the process that started the call-out is not suspended. asyncCallNoRetryFrom: aContext Perform the call-out for the function represented by the receiver. The arguments (and the receiver if one of the arguments has type #self or #selfSmalltalk) are taken from the base of the stack of aContext. Asynchronous call-outs don't return a value, but if the function calls back into Smalltalk the process that started the call-out is not suspended. Unlike #asyncCallFrom:, this method does not attempt to find functions in shared objects. callInto: aValueHolder Perform the call-out for the function represented by the receiver. The arguments (and the receiver if one of the arguments has type #self or #selfSmalltalk) are taken from the parent context, and the the result is stored into aValueHolder. aValueHolder is also returned. callNoRetryFrom: aContext into: aValueHolder Perform the call-out for the function represented by the receiver. The arguments (and the receiver if one of the arguments has type #self or #selfSmalltalk) are taken from the base of the stack of aContext, and the result is stored into aValueHolder. aValueHolder is also returned. Unlike #callFrom:into:, this method does not attempt to find functions in shared objects.  File: gst-base.info, Node: CCallable-restoring, Prev: CCallable-calling, Up: CCallable 1.21.4 CCallable: restoring --------------------------- link Rebuild the object after the image is restarted.  File: gst-base.info, Node: CCallbackDescriptor, Next: CChar, Prev: CCallable, Up: Base classes 1.22 CCallbackDescriptor ======================== Defined in namespace Smalltalk Superclass: CCallable Category: Language-C interface I am not part of the Smalltalk definition. My instances are able to convert blocks into C functions that can be passed to C. * Menu: * CCallbackDescriptor class-instance creation:: (class) * CCallbackDescriptor-accessing:: (instance) * CCallbackDescriptor-restoring:: (instance)  File: gst-base.info, Node: CCallbackDescriptor class-instance creation, Next: CCallbackDescriptor-accessing, Up: CCallbackDescriptor 1.22.1 CCallbackDescriptor class: instance creation --------------------------------------------------- for: aBlock returning: returnTypeSymbol withArgs: argsArray Answer a CCallbackDescriptor with the given block, return type and arguments.  File: gst-base.info, Node: CCallbackDescriptor-accessing, Next: CCallbackDescriptor-restoring, Prev: CCallbackDescriptor class-instance creation, Up: CCallbackDescriptor 1.22.2 CCallbackDescriptor: accessing ------------------------------------- block Answer the block of the function represented by the receiver. block: aBlock Set the block of the function represented by the receiver.  File: gst-base.info, Node: CCallbackDescriptor-restoring, Prev: CCallbackDescriptor-accessing, Up: CCallbackDescriptor 1.22.3 CCallbackDescriptor: restoring ------------------------------------- link Make the address of the function point to the registered address.  File: gst-base.info, Node: CChar, Next: CCompound, Prev: CCallbackDescriptor, Up: Base classes 1.23 CChar ========== Defined in namespace Smalltalk Superclass: CScalar Category: Language-C interface * Menu: * CChar class-accessing:: (class) * CChar-accessing:: (instance) * CChar-conversion:: (instance)  File: gst-base.info, Node: CChar class-accessing, Next: CChar-accessing, Up: CChar 1.23.1 CChar class: accessing ----------------------------- alignof Answer the receiver's instances required aligment cObjStoredType Private - Answer an index referring to the receiver's instances scalar type sizeof Answer the receiver's instances size  File: gst-base.info, Node: CChar-accessing, Next: CChar-conversion, Prev: CChar class-accessing, Up: CChar 1.23.2 CChar: accessing ----------------------- alignof Answer the receiver's required aligment cObjStoredType Private - Answer an index referring to the receiver's scalar type sizeof Answer the receiver's size  File: gst-base.info, Node: CChar-conversion, Prev: CChar-accessing, Up: CChar 1.23.3 CChar: conversion ------------------------ asByteArray: size Convert size bytes pointed to by the receiver to a String asString Convert the data pointed to by the receiver, up to the first NULL byte, to a String asString: size Convert size bytes pointed to by the receiver to a String  File: gst-base.info, Node: CCompound, Next: CDouble, Prev: CChar, Up: Base classes 1.24 CCompound ============== Defined in namespace Smalltalk Superclass: CObject Category: Language-C interface * Menu: * CCompound class-instance creation:: (class) * CCompound class-subclass creation:: (class) * CCompound-debugging:: (instance)  File: gst-base.info, Node: CCompound class-instance creation, Next: CCompound class-subclass creation, Up: CCompound 1.24.1 CCompound class: instance creation ----------------------------------------- gcNew Allocate a new instance of the receiver, backed by garbage-collected storage. new Allocate a new instance of the receiver. To free the memory after GC, remember to call #addToBeFinalized.  File: gst-base.info, Node: CCompound class-subclass creation, Next: CCompound-debugging, Prev: CCompound class-instance creation, Up: CCompound 1.24.2 CCompound class: subclass creation ----------------------------------------- alignof Answer 1, the alignment of an empty struct classPragmas Return the pragmas that are written in the file-out of this class. compileSize: size align: alignment Private - Compile sizeof and alignof methods declaration Return the description of the fields in the receiver class. declaration: array This method's functionality should be implemented by subclasses of CCompound declaration: array inject: startOffset into: aBlock Compile methods that implement the declaration in array. To compute the offset after each field, the value of the old offset plus the new field's size is passed to aBlock, together with the new field's alignment requirements. emitFieldNameTo: str for: name Private - Emit onto the given stream the code for adding the given selector to the CCompound's #examineOn: method. newStruct: structName declaration: array The old way to create a CStruct. Superseded by #subclass:declaration:... sizeof Answer 0, the size of an empty struct subclass: structName declaration: array classVariableNames: cvn poolDictionaries: pd category: category Create a new class with the given name that contains code to implement the given C struct. All the parameters except `array' are the same as for a standard class creation message; see documentation for more information  File: gst-base.info, Node: CCompound-debugging, Prev: CCompound class-subclass creation, Up: CCompound 1.24.3 CCompound: debugging --------------------------- examineOn: aStream Print the contents of the receiver's fields on aStream fieldSelectorList Answer a list of selectors whose return values should be printed by #examineOn:.  File: gst-base.info, Node: CDouble, Next: CFloat, Prev: CCompound, Up: Base classes 1.25 CDouble ============ Defined in namespace Smalltalk Superclass: CScalar Category: Language-C interface * Menu: * CDouble class-accessing:: (class) * CDouble-accessing:: (instance)  File: gst-base.info, Node: CDouble class-accessing, Next: CDouble-accessing, Up: CDouble 1.25.1 CDouble class: accessing ------------------------------- alignof Answer the receiver's instances required aligment cObjStoredType Private - Answer an index referring to the receiver's instances scalar type sizeof Answer the receiver's instances size  File: gst-base.info, Node: CDouble-accessing, Prev: CDouble class-accessing, Up: CDouble 1.25.2 CDouble: accessing ------------------------- alignof Answer the receiver's required aligment cObjStoredType Private - Answer an index referring to the receiver's scalar type sizeof Answer the receiver's size  File: gst-base.info, Node: CFloat, Next: CFunctionDescriptor, Prev: CDouble, Up: Base classes 1.26 CFloat =========== Defined in namespace Smalltalk Superclass: CScalar Category: Language-C interface * Menu: * CFloat class-accessing:: (class) * CFloat-accessing:: (instance)  File: gst-base.info, Node: CFloat class-accessing, Next: CFloat-accessing, Up: CFloat 1.26.1 CFloat class: accessing ------------------------------ alignof Answer the receiver's instances required aligment cObjStoredType Private - Answer an index referring to the receiver's instances scalar type sizeof Answer the receiver's instances size  File: gst-base.info, Node: CFloat-accessing, Prev: CFloat class-accessing, Up: CFloat 1.26.2 CFloat: accessing ------------------------ alignof Answer the receiver's required aligment cObjStoredType Private - Answer an index referring to the receiver's scalar type sizeof Answer the receiver's size  File: gst-base.info, Node: CFunctionDescriptor, Next: Character, Prev: CFloat, Up: Base classes 1.27 CFunctionDescriptor ======================== Defined in namespace Smalltalk Superclass: CCallable Category: Language-C interface I am not part of the Smalltalk definition. My instances contain information about C functions that can be called from within Smalltalk, such as number and type of parameters. This information is used by the C callout mechanism to perform the actual call-out to C routines. * Menu: * CFunctionDescriptor class-instance creation:: (class) * CFunctionDescriptor class-testing:: (class) * CFunctionDescriptor-accessing:: (instance) * CFunctionDescriptor-printing:: (instance) * CFunctionDescriptor-restoring:: (instance)  File: gst-base.info, Node: CFunctionDescriptor class-instance creation, Next: CFunctionDescriptor class-testing, Up: CFunctionDescriptor 1.27.1 CFunctionDescriptor class: instance creation --------------------------------------------------- for: funcName returning: returnTypeSymbol withArgs: argsArray Answer a CFunctionDescriptor with the given function name, return type and arguments. funcName must be a String.  File: gst-base.info, Node: CFunctionDescriptor class-testing, Next: CFunctionDescriptor-accessing, Prev: CFunctionDescriptor class-instance creation, Up: CFunctionDescriptor 1.27.2 CFunctionDescriptor class: testing ----------------------------------------- addressOf: function Answer whether a function is registered (on the C side) with the given name or is dynamically loadable. isFunction: function Answer whether a function is registered (on the C side) with the given name.  File: gst-base.info, Node: CFunctionDescriptor-accessing, Next: CFunctionDescriptor-printing, Prev: CFunctionDescriptor class-testing, Up: CFunctionDescriptor 1.27.3 CFunctionDescriptor: accessing ------------------------------------- name Answer the name of the function (on the C side) represented by the receiver name: aString Set the name of the function (on the C side) represented by the receiver  File: gst-base.info, Node: CFunctionDescriptor-printing, Next: CFunctionDescriptor-restoring, Prev: CFunctionDescriptor-accessing, Up: CFunctionDescriptor 1.27.4 CFunctionDescriptor: printing ------------------------------------ printOn: aStream Print a representation of the receiver onto aStream  File: gst-base.info, Node: CFunctionDescriptor-restoring, Prev: CFunctionDescriptor-printing, Up: CFunctionDescriptor 1.27.5 CFunctionDescriptor: restoring ------------------------------------- link Make the address of the function point to the registered address.  File: gst-base.info, Node: Character, Next: CharacterArray, Prev: CFunctionDescriptor, Up: Base classes 1.28 Character ============== Defined in namespace Smalltalk Superclass: Magnitude Category: Language-Data types My instances represent the 256 characters of the character set. I provide messages to translate between integers and character objects, and provide names for some of the common unprintable characters. Character is always used (mostly for performance reasons) when referring to characters whose code point is between 0 and 127. Above 127, instead, more care is needed: Character refers to bytes that are used as part of encoding of a character, while UnicodeCharacter refers to the character itself. * Menu: * Character class-built ins:: (class) * Character class-constants:: (class) * Character class-initializing lookup tables:: (class) * Character class-instance creation:: (class) * Character class-testing:: (class) * Character-built ins:: (instance) * Character-coercion methods:: (instance) * Character-comparing:: (instance) * Character-converting:: (instance) * Character-printing:: (instance) * Character-storing:: (instance) * Character-testing:: (instance) * Character-testing functionality:: (instance)  File: gst-base.info, Node: Character class-built ins, Next: Character class-constants, Up: Character 1.28.1 Character class: built ins --------------------------------- asciiValue: anInteger Returns the character object corresponding to anInteger. Error if anInteger is not an integer, or not in 0..127. codePoint: anInteger Returns the character object, possibly an UnicodeCharacter, corresponding to anInteger. Error if anInteger is not an integer, or not in 0..16r10FFFF. value: anInteger Returns the character object corresponding to anInteger. Error if anInteger is not an integer, or not in 0..255.  File: gst-base.info, Node: Character class-constants, Next: Character class-initializing lookup tables, Prev: Character class-built ins, Up: Character 1.28.2 Character class: constants --------------------------------- backspace Returns the character 'backspace' bell Returns the character 'bel' cr Returns the character 'cr' eof Returns the character 'eof', also known as 'sub' eot Returns the character 'eot', also known as 'Ctrl-D' esc Returns the character 'esc' ff Returns the character 'ff', also known as 'newPage' lf Returns the character 'lf', also known as 'nl' newPage Returns the character 'newPage', also known as 'ff' nl Returns the character 'nl', also known as 'lf' nul Returns the character 'nul' space Returns the character 'space' tab Returns the character 'tab'  File: gst-base.info, Node: Character class-initializing lookup tables, Next: Character class-instance creation, Prev: Character class-constants, Up: Character 1.28.3 Character class: initializing lookup tables -------------------------------------------------- initialize Initialize the lookup table which is used to make case and digit-to-char conversions faster. Indices in Table are ASCII values incremented by one. Indices 1-256 classify chars (0 = nothing special, 2 = separator, 48 = digit, 55 = uppercase, 3 = lowercase), indices 257-512 map to lowercase chars, indices 513-768 map to uppercase chars.  File: gst-base.info, Node: Character class-instance creation, Next: Character class-testing, Prev: Character class-initializing lookup tables, Up: Character 1.28.4 Character class: instance creation ----------------------------------------- digitValue: anInteger Returns a character that corresponds to anInteger. 0-9 map to $0-$9, 10-35 map to $A-$Z  File: gst-base.info, Node: Character class-testing, Next: Character-built ins, Prev: Character class-instance creation, Up: Character 1.28.5 Character class: testing ------------------------------- isImmediate Answer whether, if x is an instance of the receiver, x copy == x  File: gst-base.info, Node: Character-built ins, Next: Character-coercion methods, Prev: Character class-testing, Up: Character 1.28.6 Character: built ins --------------------------- = char Boolean return value; true if the characters are equal asInteger Returns the integer value corresponding to self. #codePoint, #asciiValue, #value, and #asInteger are synonyms. asciiValue Returns the integer value corresponding to self. #codePoint, #asciiValue, #value, and #asInteger are synonyms. codePoint Returns the integer value corresponding to self. #codePoint, #asciiValue, #value, and #asInteger are synonyms. value Returns the integer value corresponding to self. #codePoint, #asciiValue, #value, and #asInteger are synonyms.  File: gst-base.info, Node: Character-coercion methods, Next: Character-comparing, Prev: Character-built ins, Up: Character 1.28.7 Character: coercion methods ---------------------------------- * aNumber Returns a String with aNumber occurrences of the receiver. asLowercase Returns self as a lowercase character if it's an uppercase letter, otherwise returns the character unchanged. asString Returns the character self as a string. Only valid if the character is between 0 and 255. asSymbol Returns the character self as a symbol. asUnicodeString Returns the character self as a Unicode string. asUppercase Returns self as a uppercase character if it's an lowercase letter, otherwise returns the character unchanged.  File: gst-base.info, Node: Character-comparing, Next: Character-converting, Prev: Character-coercion methods, Up: Character 1.28.8 Character: comparing --------------------------- < aCharacter Compare the character's ASCII value. Answer whether the receiver's is the least. <= aCharacter Compare the character's ASCII value. Answer whether the receiver's is the least or their equal. > aCharacter Compare the character's ASCII value. Answer whether the receiver's is the greatest. >= aCharacter Compare the character's ASCII value. Answer whether the receiver's is the greatest or their equal.  File: gst-base.info, Node: Character-converting, Next: Character-printing, Prev: Character-comparing, Up: Character 1.28.9 Character: converting ---------------------------- asCharacter Return the receiver, since it is already a character. digitValue Returns the value of self interpreted as a digit. Here, 'digit' means either 0-9, or A-Z, which maps to 10-35.  File: gst-base.info, Node: Character-printing, Next: Character-storing, Prev: Character-converting, Up: Character 1.28.10 Character: printing --------------------------- displayOn: aStream Print a representation of the receiver on aStream. Unlike #printOn:, this method strips the leading dollar. printOn: aStream Print a representation of the receiver on aStream storeLiteralOn: aStream Store on aStream some Smalltalk code which compiles to the receiver  File: gst-base.info, Node: Character-storing, Next: Character-testing, Prev: Character-printing, Up: Character 1.28.11 Character: storing -------------------------- isLiteralObject Answer whether the receiver is expressible as a Smalltalk literal. storeOn: aStream Store Smalltalk code compiling to the receiver on aStream  File: gst-base.info, Node: Character-testing, Next: Character-testing functionality, Prev: Character-storing, Up: Character 1.28.12 Character: testing -------------------------- isAlphaNumeric True if self is a letter or a digit isDigit True if self is a 0-9 digit isDigit: radix Answer whether the receiver is a valid character in the given radix. isLetter True if self is an upper- or lowercase letter isLowercase True if self is a lowercase letter isPathSeparator Returns true if self is a path separator ($/ or $\ under Windows, $/ only under Unix systems including Mac OS X). isPunctuation Returns true if self is one of '.,:;!?' isSeparator Returns true if self is a space, cr, tab, nl, or newPage isUppercase True if self is uppercase isVowel Returns true if self is a, e, i, o, or u; case insensitive  File: gst-base.info, Node: Character-testing functionality, Prev: Character-testing, Up: Character 1.28.13 Character: testing functionality ---------------------------------------- isCharacter Answer True. We're definitely characters  File: gst-base.info, Node: CharacterArray, Next: CInt, Prev: Character, Up: Base classes 1.29 CharacterArray =================== Defined in namespace Smalltalk Superclass: ArrayedCollection Category: Collections-Text My instances represent a generic textual (string) data type. I provide accessing and manipulation methods for strings. * Menu: * CharacterArray class-basic:: (class) * CharacterArray class-multibyte encodings:: (class) * CharacterArray-basic:: (instance) * CharacterArray-built ins:: (instance) * CharacterArray-comparing:: (instance) * CharacterArray-converting:: (instance) * CharacterArray-multibyte encodings:: (instance) * CharacterArray-still unclassified:: (instance) * CharacterArray-string processing:: (instance) * CharacterArray-testing functionality:: (instance)  File: gst-base.info, Node: CharacterArray class-basic, Next: CharacterArray class-multibyte encodings, Up: CharacterArray 1.29.1 CharacterArray class: basic ---------------------------------- fromString: aCharacterArray Make up an instance of the receiver containing the same characters as aCharacterArray, and answer it. lineDelimiter Answer a CharacterArray which one can use as a line delimiter. This is meant to be used on subclasses of CharacterArray.  File: gst-base.info, Node: CharacterArray class-multibyte encodings, Next: CharacterArray-basic, Prev: CharacterArray class-basic, Up: CharacterArray 1.29.2 CharacterArray class: multibyte encodings ------------------------------------------------ isUnicode Answer whether the receiver stores bytes (i.e. an encoded form) or characters (if true is returned).  File: gst-base.info, Node: CharacterArray-basic, Next: CharacterArray-built ins, Prev: CharacterArray class-multibyte encodings, Up: CharacterArray 1.29.3 CharacterArray: basic ---------------------------- valueAt: anIndex ifAbsent: aBlock Answer the ascii value of the anIndex-th character of the receiver, or evaluate aBlock and answer the result if the index is out of range.  File: gst-base.info, Node: CharacterArray-built ins, Next: CharacterArray-comparing, Prev: CharacterArray-basic, Up: CharacterArray 1.29.4 CharacterArray: built ins -------------------------------- valueAt: index Answer the ascii value of index-th character variable of the receiver valueAt: index put: value Store (Character value: value) in the index-th indexed instance variable of the receiver  File: gst-base.info, Node: CharacterArray-comparing, Next: CharacterArray-converting, Prev: CharacterArray-built ins, Up: CharacterArray 1.29.5 CharacterArray: comparing -------------------------------- < aCharacterArray Return true if the receiver is less than aCharacterArray, ignoring case differences. <= aCharacterArray Returns true if the receiver is less than or equal to aCharacterArray, ignoring case differences. If is receiver is an initial substring of aCharacterArray, it is considered to be less than aCharacterArray. = aString Answer whether the receiver's items match those in aCollection > aCharacterArray Return true if the receiver is greater than aCharacterArray, ignoring case differences. >= aCharacterArray Returns true if the receiver is greater than or equal to aCharacterArray, ignoring case differences. If is aCharacterArray is an initial substring of the receiver, it is considered to be less than the receiver. indexOf: aCharacterArray matchCase: aBoolean startingAt: anIndex Answer an Interval of indices in the receiver which match the aCharacterArray pattern. # in aCharacterArray means 'match any character', * in aCharacterArray means 'match any sequence of characters'. The first item of the returned interval is >= anIndex. If aBoolean is false, the search is case-insensitive, else it is case-sensitive. If no Interval matches the pattern, answer nil. match: aCharacterArray Answer whether aCharacterArray matches the pattern contained in the receiver. # in the receiver means 'match any character', * in receiver means 'match any sequence of characters'. match: aCharacterArray ignoreCase: aBoolean Answer whether aCharacterArray matches the pattern contained in the receiver. # in the receiver means 'match any character', * in receiver means 'match any sequence of characters'. The case of alphabetic characters is ignored if aBoolean is true. sameAs: aCharacterArray Returns true if the receiver is the same CharacterArray as aCharacterArray, ignoring case differences.  File: gst-base.info, Node: CharacterArray-converting, Next: CharacterArray-multibyte encodings, Prev: CharacterArray-comparing, Up: CharacterArray 1.29.6 CharacterArray: converting --------------------------------- asByteArray Return the receiver, converted to a ByteArray of ASCII values asClassPoolKey Return the receiver, ready to be put in a class pool dictionary asGlobalKey Return the receiver, ready to be put in the Smalltalk dictionary asInteger Parse an Integer number from the receiver until the input character is invalid and answer the result at this point asLowercase Returns a copy of self as a lowercase CharacterArray asNumber Parse a Number from the receiver until the input character is invalid and answer the result at this point asPoolKey Return the receiver, ready to be put in a pool dictionary asString But I already am a String! Really! asSymbol Returns the symbol corresponding to the CharacterArray asUnicodeString Answer a UnicodeString whose character's codes are the receiver's contents This is not implemented unless you load the I18N package. asUppercase Returns a copy of self as an uppercase CharacterArray fileName But I don't HAVE a file name! filePos But I don't HAVE a file position! isNumeric Answer whether the receiver denotes a number trimSeparators Return a copy of the reciever without any spaces on front or back. The implementation is protected against the `all blanks' case.  File: gst-base.info, Node: CharacterArray-multibyte encodings, Next: CharacterArray-still unclassified, Prev: CharacterArray-converting, Up: CharacterArray 1.29.7 CharacterArray: multibyte encodings ------------------------------------------ encoding Answer the encoding used by the receiver. isUnicode Answer whether the receiver stores bytes (i.e. an encoded form) or characters (if true is returned). numberOfCharacters Answer the number of Unicode characters in the receiver. This is not implemented unless you load the I18N package.  File: gst-base.info, Node: CharacterArray-still unclassified, Next: CharacterArray-string processing, Prev: CharacterArray-multibyte encodings, Up: CharacterArray 1.29.8 CharacterArray: still unclassified ----------------------------------------- withUnixShellEscapes Answer the receiver with special shell characters converted to a backslash sequence. withWindowsShellEscapes Answer the receiver with Windows shell characters escaped properly.  File: gst-base.info, Node: CharacterArray-string processing, Next: CharacterArray-testing functionality, Prev: CharacterArray-still unclassified, Up: CharacterArray 1.29.9 CharacterArray: string processing ---------------------------------------- % aCollection Answer the receiver with special escape sequences replaced by elements of aCollection. %n (1<=n<=9, A<=n<=Z) are replaced by the n-th element of aCollection (A being the 10-th element and so on until the 35th). %(string) sequences are accessed as strings, which makes sense only if aCollection is a Dictionary or LookupTable. In addition, the special pattern %n or %(string) is replaced with one of the two strings depending on the element of aCollection being true or false. The replaced elements are `displayed' (i.e. their displayString is used). bindWith: s1 Answer the receiver with every %1 replaced by the displayString of s1 bindWith: s1 with: s2 Answer the receiver with every %1 or %2 replaced by s1 or s2, respectively. s1 and s2 are `displayed' (i.e. their displayString is used) upon replacement. bindWith: s1 with: s2 with: s3 Answer the receiver with every %1, %2 or %3 replaced by s1, s2 or s3, respectively. s1, s2 and s3 are `displayed' (i.e. their displayString is used) upon replacement. bindWith: s1 with: s2 with: s3 with: s4 Answer the receiver with every %1, %2, %3 or %4 replaced by s1, s2, s3 or s4, respectively. s1, s2, s3 and s4 are `displayed' (i.e. their displayString is used) upon replacement. bindWithArguments: aCollection Answer the receiver with special escape sequences replaced by elements of aCollection. %n (1<=n<=9, A<=n<=Z) are replaced by the n-th element of aCollection (A being the 10-th element and so on until the 35th). %(string) sequences are accessed as strings, which makes sense only if aCollection is a Dictionary or LookupTable. In addition, the special pattern %n or %(string) is replaced with one of the two strings depending on the element of aCollection being true or false. The replaced elements are `displayed' (i.e. their displayString is used). contractTo: smallSize Either return myself, or a copy shortened to smallSize characters by inserting an ellipsis (three dots: ...) lines Answer an Array of Strings each representing one line in the receiver. linesDo: aBlock Evaluate aBlock once for every newline delimited line in the receiver, passing the line to the block. subStrings Answer an OrderedCollection of substrings of the receiver. A new substring start at the start of the receiver, or after every sequence of white space characters subStrings: sep Answer an OrderedCollection of substrings of the receiver. A new substring start at the start of the receiver, or after every occurrence of one of the characters in sep substrings Answer an OrderedCollection of substrings of the receiver. A new substring start at the start of the receiver, or after every sequence of white space characters. This message is preserved for backwards compatibility; the ANSI standard mandates `subStrings', with an uppercase s. substrings: sep Answer an OrderedCollection of substrings of the receiver. A new substring start at the start of the receiver, or after every occurrence of one of the characters in sep. This message is preserved for backwards compatibility; the ANSI standard mandates `subStrings:', with an uppercase s. withShellEscapes Answer the receiver with special shell characters converted to a backslash sequence.  File: gst-base.info, Node: CharacterArray-testing functionality, Prev: CharacterArray-string processing, Up: CharacterArray 1.29.10 CharacterArray: testing functionality --------------------------------------------- isCharacterArray Answer `true'.  File: gst-base.info, Node: CInt, Next: Class, Prev: CharacterArray, Up: Base classes 1.30 CInt ========= Defined in namespace Smalltalk Superclass: CScalar Category: Language-C interface * Menu: * CInt class-accessing:: (class) * CInt-accessing:: (instance)  File: gst-base.info, Node: CInt class-accessing, Next: CInt-accessing, Up: CInt 1.30.1 CInt class: accessing ---------------------------- alignof Answer the receiver's required aligment cObjStoredType Private - Answer an index referring to the receiver's instances scalar type sizeof Answer the receiver's size  File: gst-base.info, Node: CInt-accessing, Prev: CInt class-accessing, Up: CInt 1.30.2 CInt: accessing ---------------------- alignof Answer the receiver's instances required aligment cObjStoredType Private - Answer an index referring to the receiver's scalar type sizeof Answer the receiver's instances size  File: gst-base.info, Node: Class, Next: ClassDescription, Prev: CInt, Up: Base classes 1.31 Class ========== Defined in namespace Smalltalk Superclass: ClassDescription Category: Language-Implementation I am THE class object. My instances are the classes of the system. I provide information commonly attributed to classes: namely, the class name, class comment (you wouldn't be reading this if it weren't for me), a list of the instance variables of the class, and the class category. * Menu: * Class class-initialize:: (class) * Class-accessing instances and variables:: (instance) * Class-filing:: (instance) * Class-instance creation:: (instance) * Class-instance creation - alternative:: (instance) * Class-pragmas:: (instance) * Class-printing:: (instance) * Class-saving and loading:: (instance) * Class-security:: (instance) * Class-still unclassified:: (instance) * Class-testing:: (instance) * Class-testing functionality:: (instance)  File: gst-base.info, Node: Class class-initialize, Next: Class-accessing instances and variables, Up: Class 1.31.1 Class class: initialize ------------------------------ initialize Perform the special initialization of root classes.  File: gst-base.info, Node: Class-accessing instances and variables, Next: Class-filing, Prev: Class class-initialize, Up: Class 1.31.2 Class: accessing instances and variables ----------------------------------------------- addClassVarName: aString Add a class variable with the given name to the class pool dictionary. addClassVarName: aString value: valueBlock Add a class variable with the given name to the class pool dictionary, and evaluate valueBlock as its initializer. addSharedPool: aDictionary Add the given shared pool to the list of the class' pool dictionaries allClassVarNames Answer the names of the variables in the receiver's class pool dictionary and in each of the superclasses' class pool dictionaries bindingFor: aString Answer the variable binding for the class variable with the given name category Answer the class category category: aString Change the class category to aString classPool Answer the class pool dictionary classPragmas Return the pragmas that are written in the file-out of this class. classVarNames Answer the names of the variables in the class pool dictionary comment Answer the class comment comment: aString Change the class name environment Answer `environment'. environment: aNamespace Set the receiver's environment to aNamespace and recompile everything initialize redefined in children (?) initializeAsRootClass Perform special initialization reserved to root classes. name Answer the class name removeClassVarName: aString Removes the class variable from the class, error if not present, or still in use. removeSharedPool: aDictionary Remove the given dictionary to the list of the class' pool dictionaries sharedPools Return the names of the shared pools defined by the class superclass: aClass Set the receiver's superclass.  File: gst-base.info, Node: Class-filing, Next: Class-instance creation, Prev: Class-accessing instances and variables, Up: Class 1.31.3 Class: filing -------------------- fileOutDeclarationOn: aFileStream File out class definition to aFileStream. Requires package Parser. fileOutOn: aFileStream File out complete class description: class definition, class and instance methods. Requires package Parser.  File: gst-base.info, Node: Class-instance creation, Next: Class-instance creation - alternative, Prev: Class-filing, Up: Class 1.31.4 Class: instance creation ------------------------------- extend Redefine a version of the receiver in the current namespace. Note: this method can bite you in various ways when sent to system classes; read the section on namespaces in the manual for some examples of the problems you can encounter. inheritShape Answer whether subclasses will have by default the same shape as this class. The default is false. subclass: classNameString Define a subclass of the receiver with the given name. If the class is already defined, don't modify its instance or class variables but still, if necessary, recompile everything needed. subclass: classNameString instanceVariableNames: stringInstVarNames classVariableNames: stringOfClassVarNames poolDictionaries: stringOfPoolNames category: categoryNameString Define a fixed subclass of the receiver with the given name, instance variables, class variables, pool dictionaries and category. If the class is already defined, if necessary, recompile everything needed. variable: shape subclass: classNameString instanceVariableNames: stringInstVarNames classVariableNames: stringOfClassVarNames poolDictionaries: stringOfPoolNames category: categoryNameString Define a variable subclass of the receiver with the given name, shape, instance variables, class variables, pool dictionaries and category. If the class is already defined, if necessary, recompile everything needed. The shape can be one of #byte #int8 #character #short #ushort #int #uint #int64 #uint64 #utf32 #float #double or #pointer. variableByteSubclass: classNameString instanceVariableNames: stringInstVarNames classVariableNames: stringOfClassVarNames poolDictionaries: stringOfPoolNames category: categoryNameString Define a byte variable subclass of the receiver with the given name, instance variables (must be "), class variables, pool dictionaries and category. If the class is already defined, if necessary, recompile everything needed. variableSubclass: classNameString instanceVariableNames: stringInstVarNames classVariableNames: stringOfClassVarNames poolDictionaries: stringOfPoolNames category: categoryNameString Define a variable pointer subclass of the receiver with the given name, instance variables, class variables, pool dictionaries and category. If the class is already defined, if necessary, recompile everything needed. variableWordSubclass: classNameString instanceVariableNames: stringInstVarNames classVariableNames: stringOfClassVarNames poolDictionaries: stringOfPoolNames category: categoryNameString Define a word variable subclass of the receiver with the given name, instance variables (must be "), class variables, pool dictionaries and category. If the class is already defined, if necessary, recompile everything needed.  File: gst-base.info, Node: Class-instance creation - alternative, Next: Class-pragmas, Prev: Class-instance creation, Up: Class 1.31.5 Class: instance creation - alternative --------------------------------------------- categoriesFor: method are: categories Don't use this, it is only present to file in from IBM Smalltalk subclass: classNameString classInstanceVariableNames: stringClassInstVarNames instanceVariableNames: stringInstVarNames classVariableNames: stringOfClassVarNames poolDictionaries: stringOfPoolNames Don't use this, it is only present to file in from IBM Smalltalk subclass: classNameString instanceVariableNames: stringInstVarNames classVariableNames: stringOfClassVarNames poolDictionaries: stringOfPoolNames Don't use this, it is only present to file in from IBM Smalltalk variableByteSubclass: classNameString classInstanceVariableNames: stringClassInstVarNames classVariableNames: stringOfClassVarNames poolDictionaries: stringOfPoolNames Don't use this, it is only present to file in from IBM Smalltalk variableByteSubclass: classNameString classVariableNames: stringOfClassVarNames poolDictionaries: stringOfPoolNames Don't use this, it is only present to file in from IBM Smalltalk variableLongSubclass: classNameString classInstanceVariableNames: stringClassInstVarNames classVariableNames: stringOfClassVarNames poolDictionaries: stringOfPoolNames Don't use this, it is only present to file in from IBM Smalltalk variableLongSubclass: classNameString classVariableNames: stringOfClassVarNames poolDictionaries: stringOfPoolNames Don't use this, it is only present to file in from IBM Smalltalk variableSubclass: classNameString classInstanceVariableNames: stringClassInstVarNames instanceVariableNames: stringInstVarNames classVariableNames: stringOfClassVarNames poolDictionaries: stringOfPoolNames Don't use this, it is only present to file in from IBM Smalltalk variableSubclass: classNameString instanceVariableNames: stringInstVarNames classVariableNames: stringOfClassVarNames poolDictionaries: stringOfPoolNames Don't use this, it is only present to file in from IBM Smalltalk  File: gst-base.info, Node: Class-pragmas, Next: Class-printing, Prev: Class-instance creation - alternative, Up: Class 1.31.6 Class: pragmas --------------------- pragmaHandlerFor: aSymbol Answer the (possibly inherited) registered handler for pragma aSymbol, or nil if not found. registerHandler: aBlock forPragma: pragma While compiling methods, on every encounter of the pragma with the given name, call aBlock with the CompiledMethod and an array of pragma argument values.  File: gst-base.info, Node: Class-printing, Next: Class-saving and loading, Prev: Class-pragmas, Up: Class 1.31.7 Class: printing ---------------------- article Answer an article (`a' or `an') which is ok for the receiver's name printOn: aStream Print a representation of the receiver on aStream storeOn: aStream Store Smalltalk code compiling to the receiver on aStream  File: gst-base.info, Node: Class-saving and loading, Next: Class-security, Prev: Class-printing, Up: Class 1.31.8 Class: saving and loading -------------------------------- binaryRepresentationVersion Answer a number >= 0 which represents the current version of the object's representation. The default implementation answers zero. convertFromVersion: version withFixedVariables: fixed indexedVariables: indexed for: anObjectDumper This method is called if a VersionableObjectProxy is attached to a class. It receives the version number that was stored for the object (or nil if the object did not use a VersionableObjectProxy), the fixed instance variables, the indexed instance variables, and the ObjectDumper that has read the object. The default implementation ignores the version and simply fills in an instance of the receiver with the given fixed and indexed instance variables (nil if the class instances are of fixed size). If instance variables were removed from the class, extras are ignored; if the class is now fixed and used to be indexed, indexed is not used. nonVersionedInstSize Answer the number of instance variables that the class used to have when objects were stored without using a VersionableObjectProxy. The default implementation answers the current instSize.  File: gst-base.info, Node: Class-security, Next: Class-still unclassified, Prev: Class-saving and loading, Up: Class 1.31.9 Class: security ---------------------- check: aPermission Not commented. securityPolicy Answer `securityPolicy'. securityPolicy: aSecurityPolicy Not commented.  File: gst-base.info, Node: Class-still unclassified, Next: Class-testing, Prev: Class-security, Up: Class 1.31.10 Class: still unclassified --------------------------------- allSharedPoolDictionariesDo: aBlock Answer the shared pools visible from methods in the metaclass, in the correct search order. fileOutHeaderOn: aFileStream Not commented.  File: gst-base.info, Node: Class-testing, Next: Class-testing functionality, Prev: Class-still unclassified, Up: Class 1.31.11 Class: testing ---------------------- = aClass Returns true if the two class objects are to be considered equal.  File: gst-base.info, Node: Class-testing functionality, Prev: Class-testing, Up: Class 1.31.12 Class: testing functionality ------------------------------------ asClass Answer the receiver. isClass Answer `true'.  File: gst-base.info, Node: ClassDescription, Next: CLong, Prev: Class, Up: Base classes 1.32 ClassDescription ===================== Defined in namespace Smalltalk Superclass: Behavior Category: Language-Implementation My instances provide methods that access classes by category, and allow whole categories of classes to be filed out to external disk files. * Menu: * ClassDescription-compiling:: (instance) * ClassDescription-conversion:: (instance) * ClassDescription-copying:: (instance) * ClassDescription-filing:: (instance) * ClassDescription-organization of messages and classes:: (instance) * ClassDescription-parsing class declarations:: (instance) * ClassDescription-printing:: (instance) * ClassDescription-still unclassified:: (instance)  File: gst-base.info, Node: ClassDescription-compiling, Next: ClassDescription-conversion, Up: ClassDescription 1.32.1 ClassDescription: compiling ---------------------------------- compile: code classified: categoryName Compile code in the receiver, assigning the method to the given category. Answer the newly created CompiledMethod, or nil if an error was found. compile: code classified: categoryName ifError: block Compile method source and install in method category, categoryName. If there are parsing errors, invoke exception block, 'block' (see compile:ifError:). Return the method compile: code classified: categoryName notifying: requestor Compile method source and install in method category, categoryName. If there are parsing errors, send an error message to requestor  File: gst-base.info, Node: ClassDescription-conversion, Next: ClassDescription-copying, Prev: ClassDescription-compiling, Up: ClassDescription 1.32.2 ClassDescription: conversion ----------------------------------- asClass This method's functionality should be implemented by subclasses of ClassDescription asMetaclass Answer the metaclass associated to the receiver binding Answer a VariableBinding object whose value is the receiver  File: gst-base.info, Node: ClassDescription-copying, Next: ClassDescription-filing, Prev: ClassDescription-conversion, Up: ClassDescription 1.32.3 ClassDescription: copying -------------------------------- copy: selector from: aClass Copy the given selector from aClass, assigning it the same category copy: selector from: aClass classified: categoryName Copy the given selector from aClass, assigning it the given category copyAll: arrayOfSelectors from: class Copy all the selectors in arrayOfSelectors from class, assigning them the same category they have in class copyAll: arrayOfSelectors from: class classified: categoryName Copy all the selectors in arrayOfSelectors from aClass, assigning them the given category copyAllCategoriesFrom: aClass Copy all the selectors in aClass, assigning them the original category copyCategory: categoryName from: aClass Copy all the selectors in from aClass that belong to the given category copyCategory: categoryName from: aClass classified: newCategoryName Copy all the selectors in from aClass that belong to the given category, reclassifying them as belonging to the given category  File: gst-base.info, Node: ClassDescription-filing, Next: ClassDescription-organization of messages and classes, Prev: ClassDescription-copying, Up: ClassDescription 1.32.4 ClassDescription: filing ------------------------------- fileOut: fileName Open the given file and to file out a complete class description to it. Requires package Parser. fileOutCategory: categoryName to: fileName File out all the methods belonging to the method category, categoryName, to the fileName file. Requires package Parser. fileOutOn: aFileStream File out complete class description: class definition, class and instance methods. Requires package Parser. fileOutSelector: selector to: fileName File out the given selector to fileName. Requires package Parser.  File: gst-base.info, Node: ClassDescription-organization of messages and classes, Next: ClassDescription-parsing class declarations, Prev: ClassDescription-filing, Up: ClassDescription 1.32.5 ClassDescription: organization of messages and classes ------------------------------------------------------------- classify: aSelector under: aString Put the method identified by the selector aSelector under the category given by aString. createGetMethod: what Create a method accessing the variable `what'. createGetMethod: what default: value Create a method accessing the variable `what', with a default value of `value', using lazy initialization createSetMethod: what Create a method which sets the variable `what'. defineAsyncCFunc: cFuncNameString withSelectorArgs: selectorAndArgs args: argsArray See documentation. This function is deprecated, you should use the special syntax instead. defineCFunc: cFuncNameString withSelectorArgs: selectorAndArgs returning: returnTypeSymbol args: argsArray See documentation. This function is deprecated, you should use the special syntax instead. removeCategory: aString Remove from the receiver every method belonging to the given category whichCategoryIncludesSelector: selector Answer the category for the given selector, or nil if the selector is not found  File: gst-base.info, Node: ClassDescription-parsing class declarations, Next: ClassDescription-printing, Prev: ClassDescription-organization of messages and classes, Up: ClassDescription 1.32.6 ClassDescription: parsing class declarations --------------------------------------------------- addSharedPool: aDictionary Add the given shared pool to the list of the class' pool dictionaries import: aDictionary Add the given shared pool to the list of the class' pool dictionaries  File: gst-base.info, Node: ClassDescription-printing, Next: ClassDescription-still unclassified, Prev: ClassDescription-parsing class declarations, Up: ClassDescription 1.32.7 ClassDescription: printing --------------------------------- classVariableString This method's functionality should be implemented by subclasses of ClassDescription instanceVariableString Answer a string containing the name of the receiver's instance variables. nameIn: aNamespace Answer the class name when the class is referenced from aNamespace printOn: aStream in: aNamespace Print on aStream the class name when the class is referenced from aNamespace sharedVariableString This method's functionality should be implemented by subclasses of ClassDescription  File: gst-base.info, Node: ClassDescription-still unclassified, Prev: ClassDescription-printing, Up: ClassDescription 1.32.8 ClassDescription: still unclassified ------------------------------------------- fileOutCategory: category toStream: aFileStream File out all the methods belonging to the method category, category, to aFileStream. Requires package Parser. fileOutSelector: aSymbol toStream: aFileStream File out all the methods belonging to the method category, category, to aFileStream. Requires package Parser.  File: gst-base.info, Node: CLong, Next: CLongDouble, Prev: ClassDescription, Up: Base classes 1.33 CLong ========== Defined in namespace Smalltalk Superclass: CScalar Category: Language-C interface * Menu: * CLong class-accessing:: (class) * CLong-accessing:: (instance)  File: gst-base.info, Node: CLong class-accessing, Next: CLong-accessing, Up: CLong 1.33.1 CLong class: accessing ----------------------------- alignof Answer the receiver's instances required aligment cObjStoredType Private - Answer an index referring to the receiver's instances scalar type sizeof Answer the receiver's instances size  File: gst-base.info, Node: CLong-accessing, Prev: CLong class-accessing, Up: CLong 1.33.2 CLong: accessing ----------------------- alignof Answer the receiver's required aligment cObjStoredType Private - Answer an index referring to the receiver's scalar type sizeof Answer the receiver's size  File: gst-base.info, Node: CLongDouble, Next: CLongLong, Prev: CLong, Up: Base classes 1.34 CLongDouble ================ Defined in namespace Smalltalk Superclass: CScalar Category: Language-C interface * Menu: * CLongDouble class-accessing:: (class) * CLongDouble-accessing:: (instance)  File: gst-base.info, Node: CLongDouble class-accessing, Next: CLongDouble-accessing, Up: CLongDouble 1.34.1 CLongDouble class: accessing ----------------------------------- alignof Answer the receiver's instances required aligment cObjStoredType Private - Answer an index referring to the receiver's instances scalar type sizeof Answer the receiver's instances size  File: gst-base.info, Node: CLongDouble-accessing, Prev: CLongDouble class-accessing, Up: CLongDouble 1.34.2 CLongDouble: accessing ----------------------------- alignof Answer the receiver's required aligment cObjStoredType Private - Answer an index referring to the receiver's scalar type sizeof Answer the receiver's size  File: gst-base.info, Node: CLongLong, Next: CObject, Prev: CLongDouble, Up: Base classes 1.35 CLongLong ============== Defined in namespace Smalltalk Superclass: CScalar Category: Language-C interface * Menu: * CLongLong class-accessing:: (class) * CLongLong-accessing:: (instance)  File: gst-base.info, Node: CLongLong class-accessing, Next: CLongLong-accessing, Up: CLongLong 1.35.1 CLongLong class: accessing --------------------------------- alignof Answer the receiver's instances required aligment cObjStoredType Private - Answer an index referring to the receiver's instances scalar type sizeof Answer the receiver's instances size  File: gst-base.info, Node: CLongLong-accessing, Prev: CLongLong class-accessing, Up: CLongLong 1.35.2 CLongLong: accessing --------------------------- alignof Answer the receiver's required aligment cObjStoredType Private - Answer an index referring to the receiver's scalar type sizeof Answer the receiver's size  File: gst-base.info, Node: CObject, Next: Collection, Prev: CLongLong, Up: Base classes 1.36 CObject ============ Defined in namespace Smalltalk Superclass: Object Category: Language-C interface I am not part of the standard Smalltalk kernel class hierarchy. My instances contain values that are not interpreted by the Smalltalk system; they frequently hold "pointers" to data outside of the Smalltalk environment. The C callout mechanism allows my instances to be transformed into their corresponding C values for use in external routines. * Menu: * CObject class-conversion:: (class) * CObject class-instance creation:: (class) * CObject class-primitive allocation:: (class) * CObject class-subclass creation:: (class) * CObject-accessing:: (instance) * CObject-basic:: (instance) * CObject-C data access:: (instance) * CObject-conversion:: (instance) * CObject-finalization:: (instance) * CObject-pointer-like behavior:: (instance) * CObject-testing:: (instance) * CObject-testing functionality:: (instance)  File: gst-base.info, Node: CObject class-conversion, Next: CObject class-instance creation, Up: CObject 1.36.1 CObject class: conversion -------------------------------- type Nothing special in the default case - answer a CType for the receiver  File: gst-base.info, Node: CObject class-instance creation, Next: CObject class-primitive allocation, Prev: CObject class-conversion, Up: CObject 1.36.2 CObject class: instance creation --------------------------------------- address: anInteger Answer a new object pointing to the passed address, anInteger alloc: nBytes Allocate nBytes bytes and return an instance of the receiver gcAlloc: nBytes Allocate nBytes bytes and return an instance of the receiver gcNew: nBytes Allocate nBytes bytes and return an instance of the receiver new Answer a new object pointing to NULL. new: nBytes Allocate nBytes bytes and return an instance of the receiver  File: gst-base.info, Node: CObject class-primitive allocation, Next: CObject class-subclass creation, Prev: CObject class-instance creation, Up: CObject 1.36.3 CObject class: primitive allocation ------------------------------------------ alloc: nBytes type: cTypeObject Allocate nBytes bytes and return a CObject of the given type gcAlloc: nBytes type: cTypeObject Allocate nBytes bytes and return a CObject of the given type  File: gst-base.info, Node: CObject class-subclass creation, Next: CObject-accessing, Prev: CObject class-primitive allocation, Up: CObject 1.36.4 CObject class: subclass creation --------------------------------------- inheritShape Answer whether subclasses will have by default the same shape as this class. The default is true for the CObject hierarchy.  File: gst-base.info, Node: CObject-accessing, Next: CObject-basic, Prev: CObject class-subclass creation, Up: CObject 1.36.5 CObject: accessing ------------------------- address Answer the address the receiver is pointing to. The address can be absolute if the storage is nil, or relative to the Smalltalk object in #storage. In this case, an address of 0 corresponds to the first instance variable. address: anInteger Set the receiver to point to the passed address, anInteger isAbsolute Answer whether the object points into a garbage-collected Smalltalk storage, or it is an absolute address. printOn: aStream Print a representation of the receiver storage Answer the storage that the receiver is pointing into, or nil if the address is absolute. storage: anObject Change the receiver to point to the storage of anObject. type: aCType Set the receiver's type to aCType.  File: gst-base.info, Node: CObject-basic, Next: CObject-C data access, Prev: CObject-accessing, Up: CObject 1.36.6 CObject: basic --------------------- = anObject Return true if the receiver and aCObject are equal. hash Return a hash value for anObject.  File: gst-base.info, Node: CObject-C data access, Next: CObject-conversion, Prev: CObject-basic, Up: CObject 1.36.7 CObject: C data access ----------------------------- at: byteOffset put: aValue type: aType Store aValue as data of the given type from byteOffset bytes after the pointer stored in the receiver at: byteOffset type: aType Answer some data of the given type from byteOffset bytes after the pointer stored in the receiver free Free the receiver's pointer and set it to null. Big trouble hits you if the receiver doesn't point to the base of a malloc-ed area.  File: gst-base.info, Node: CObject-conversion, Next: CObject-finalization, Prev: CObject-C data access, Up: CObject 1.36.8 CObject: conversion -------------------------- castTo: aType Answer another CObject, pointing to the same address as the receiver, but belonging to the aType CType. narrow This method is called on CObjects returned by a C call-out whose return type is specified as a CType; it mostly allows one to change the class of the returned CObject. By default it does nothing, and that's why it is not called when #cObject is used to specify the return type. type Answer a CType for the receiver  File: gst-base.info, Node: CObject-finalization, Next: CObject-pointer-like behavior, Prev: CObject-conversion, Up: CObject 1.36.9 CObject: finalization ---------------------------- finalize To make the VM call this, use #addToBeFinalized. It frees automatically any memory pointed to by the CObject. It is not automatically enabled because big trouble hits you if you use #free and the receiver doesn't point to the base of a malloc-ed area.  File: gst-base.info, Node: CObject-pointer-like behavior, Next: CObject-testing, Prev: CObject-finalization, Up: CObject 1.36.10 CObject: pointer-like behavior -------------------------------------- + anInteger Return another instance of the receiver's class which points at &receiver[anInteger] (or, if you prefer, what `receiver + anInteger' does in C). - intOrPtr If intOrPtr is an integer, return another instance of the receiver's class pointing at &receiver[-anInteger] (or, if you prefer, what `receiver - anInteger' does in C). If it is the same class as the receiver, return the difference in chars, i.e. in bytes, between the two pointed addresses (or, if you prefer, what `receiver - anotherCharPtr' does in C) addressAt: anIndex Return a new CObject of the element type, corresponding to an object that is anIndex places past the receiver (remember that CObjects represent pointers and that C pointers behave like arrays). anIndex is zero-based, just like with all other C-style accessing. at: anIndex Dereference a pointer that is anIndex places past the receiver (remember that CObjects represent pointers and that C pointers behave like arrays). anIndex is zero-based, just like with all other C-style accessing. at: anIndex put: aValue Store anIndex places past the receiver the passed Smalltalk object or CObject `aValue'; if it is a CObject is dereferenced: that is, this method is equivalent either to cobj[anIndex]=aValue or cobj[anIndex]=*aValue. anIndex is zero-based, just like with all other C-style accessing. In both cases, aValue should be of the element type or of the corresponding Smalltalk type (that is, a String is ok for an array of CStrings) to avoid typing problems which however will not be signaled because C is untyped. decr Adjust the pointer by sizeof(dereferencedType) bytes down (i.e. -receiver) decrBy: anInteger Adjust the pointer by anInteger elements down (i.e. receiver -= anInteger) incr Adjust the pointer by sizeof(dereferencedType) bytes up (i.e. ++receiver) incrBy: anInteger Adjust the pointer by anInteger elements up (i.e. receiver += anInteger)  File: gst-base.info, Node: CObject-testing, Next: CObject-testing functionality, Prev: CObject-pointer-like behavior, Up: CObject 1.36.11 CObject: testing ------------------------ isNull Return true if the receiver points to NULL.  File: gst-base.info, Node: CObject-testing functionality, Prev: CObject-testing, Up: CObject 1.36.12 CObject: testing functionality -------------------------------------- isCObject Answer `true'.  File: gst-base.info, Node: Collection, Next: CompiledBlock, Prev: CObject, Up: Base classes 1.37 Collection =============== Defined in namespace Smalltalk Superclass: Iterable Category: Collections I am an abstract class. My instances are collections of objects. My subclasses may place some restrictions or add some definitions to how the objects are stored or organized; I say nothing about this. I merely provide some object creation and access routines for general collections of objects. * Menu: * Collection class-instance creation:: (class) * Collection class-multibyte encodings:: (class) * Collection-adding:: (instance) * Collection-compiler:: (instance) * Collection-concatenating:: (instance) * Collection-converting:: (instance) * Collection-copying Collections:: (instance) * Collection-copying SequenceableCollections:: (instance) * Collection-enumeration:: (instance) * Collection-finalization:: (instance) * Collection-printing:: (instance) * Collection-removing:: (instance) * Collection-sorting:: (instance) * Collection-storing:: (instance) * Collection-testing collections:: (instance)  File: gst-base.info, Node: Collection class-instance creation, Next: Collection class-multibyte encodings, Up: Collection 1.37.1 Collection class: instance creation ------------------------------------------ from: anArray Convert anArray to an instance of the receiver. anArray is structured such that the instance can be conveniently and fully specified using brace-syntax, possibly by imposing some additional structure on anArray. join: aCollection Answer a collection formed by treating each element in aCollection as a `withAll:' argument collection to be added to a new instance. with: anObject Answer a collection whose only element is anObject with: firstObject with: secondObject Answer a collection whose only elements are the parameters in the order they were passed with: firstObject with: secondObject with: thirdObject Answer a collection whose only elements are the parameters in the order they were passed with: firstObject with: secondObject with: thirdObject with: fourthObject Answer a collection whose only elements are the parameters in the order they were passed with: firstObject with: secondObject with: thirdObject with: fourthObject with: fifthObject Answer a collection whose only elements are the parameters in the order they were passed withAll: aCollection Answer a collection whose elements are all those in aCollection  File: gst-base.info, Node: Collection class-multibyte encodings, Next: Collection-adding, Prev: Collection class-instance creation, Up: Collection 1.37.2 Collection class: multibyte encodings -------------------------------------------- isUnicode Answer true; the receiver is able to store arbitrary Unicode characters.  File: gst-base.info, Node: Collection-adding, Next: Collection-compiler, Prev: Collection class-multibyte encodings, Up: Collection 1.37.3 Collection: adding ------------------------- add: newObject Add newObject to the receiver, answer it addAll: aCollection Adds all the elements of 'aCollection' to the receiver, answer aCollection  File: gst-base.info, Node: Collection-compiler, Next: Collection-concatenating, Prev: Collection-adding, Up: Collection 1.37.4 Collection: compiler --------------------------- literalEquals: anObject Not commented. literalHash Not commented.  File: gst-base.info, Node: Collection-concatenating, Next: Collection-converting, Prev: Collection-compiler, Up: Collection 1.37.5 Collection: concatenating -------------------------------- join Answer a new collection like my first element, with all the elements (in order) of all my elements, which should be collections. I use my first element instead of myself as a prototype because my elements are more likely to share the desired properties than I am, such as in: #('hello, ' 'world') join => 'hello, world'  File: gst-base.info, Node: Collection-converting, Next: Collection-copying Collections, Prev: Collection-concatenating, Up: Collection 1.37.6 Collection: converting ----------------------------- asArray Answer an Array containing all the elements in the receiver asBag Answer a Bag containing all the elements in the receiver asByteArray Answer a ByteArray containing all the elements in the receiver asOrderedCollection Answer an OrderedCollection containing all the elements in the receiver asRunArray Answer the receiver converted to a RunArray. If the receiver is not ordered the order of the elements in the RunArray might not be the #do: order. asSet Answer a Set containing all the elements in the receiver with no duplicates asSortedCollection Answer a SortedCollection containing all the elements in the receiver with the default sort block - [ :a :b | a <= b ] asSortedCollection: aBlock Answer a SortedCollection whose elements are the elements of the receiver, sorted according to the sort block aBlock asString Answer a String containing all the elements in the receiver asUnicodeString Answer a UnicodeString containing all the elements in the receiver  File: gst-base.info, Node: Collection-copying Collections, Next: Collection-copying SequenceableCollections, Prev: Collection-converting, Up: Collection 1.37.7 Collection: copying Collections -------------------------------------- copyReplacing: targetObject withObject: newObject Copy replacing each object which is = to targetObject with newObject copyWith: newElement Answer a copy of the receiver to which newElement is added copyWithout: oldElement Answer a copy of the receiver to which all occurrences of oldElement are removed  File: gst-base.info, Node: Collection-copying SequenceableCollections, Next: Collection-enumeration, Prev: Collection-copying Collections, Up: Collection 1.37.8 Collection: copying SequenceableCollections -------------------------------------------------- , anIterable Append anIterable at the end of a copy of the receiver (using #add:), and answer a new collection  File: gst-base.info, Node: Collection-enumeration, Next: Collection-finalization, Prev: Collection-copying SequenceableCollections, Up: Collection 1.37.9 Collection: enumeration ------------------------------ anyOne Answer an unspecified element of the collection. beConsistent This method is private, but it is quite interesting so it is documented. It ensures that a collection is in a consistent state before attempting to iterate on it; its presence reduces the number of overrides needed by collections who try to amortize their execution times. The default implementation does nothing, so it is optimized out by the virtual machine and so it loses very little on the performance side. Note that descendants of Collection have to call it explicitly since #do: is abstract in Collection. collect: aBlock Answer a new instance of a Collection containing all the results of evaluating aBlock passing each of the receiver's elements gather: aBlock Answer a new instance of a Collection containing all the results of evaluating aBlock, joined together. aBlock should return collections. The result is the same kind as the first collection, returned by aBlock (as for #join). readStream Answer a stream that gives elements of the receiver reject: aBlock Answer a new instance of a Collection containing all the elements in the receiver which, when passed to aBlock, don't answer true select: aBlock Answer a new instance of a Collection containing all the elements in the receiver which, when passed to aBlock, answer true  File: gst-base.info, Node: Collection-finalization, Next: Collection-printing, Prev: Collection-enumeration, Up: Collection 1.37.10 Collection: finalization -------------------------------- mourn: anObject Private - anObject has been found to have a weak key, remove it and possibly finalize the key.  File: gst-base.info, Node: Collection-printing, Next: Collection-removing, Prev: Collection-finalization, Up: Collection 1.37.11 Collection: printing ---------------------------- displayLines Print each element of the receiver to a line on standard output. examineOn: aStream Print all the instance variables and objects in the receiver on aStream printOn: aStream Print a representation of the receiver on aStream  File: gst-base.info, Node: Collection-removing, Next: Collection-sorting, Prev: Collection-printing, Up: Collection 1.37.12 Collection: removing ---------------------------- empty Remove everything from the receiver. remove: oldObject Remove oldObject from the receiver. If absent, fail, else answer oldObject. remove: oldObject ifAbsent: anExceptionBlock Remove oldObject from the receiver. If absent, evaluate anExceptionBlock and answer the result, else answer oldObject. removeAll: aCollection Remove each object in aCollection, answer aCollection, fail if some of them is absent. Warning: this could leave the collection in a semi-updated state. removeAll: aCollection ifAbsent: aBlock Remove each object in aCollection, answer aCollection; if some element is absent, pass it to aBlock. removeAllSuchThat: aBlock Remove from the receiver all objects for which aBlock returns true.  File: gst-base.info, Node: Collection-sorting, Next: Collection-storing, Prev: Collection-removing, Up: Collection 1.37.13 Collection: sorting --------------------------- sorted Return a sequenceable collection with the contents of the receiver sorted according to the default sort block, which uses #<= to compare items. sorted: sortBlock Return a sequenceable collection with the contents of the receiver sorted according to the given sort block, which accepts pair of items and returns true if the first item is less than the second one.  File: gst-base.info, Node: Collection-storing, Next: Collection-testing collections, Prev: Collection-sorting, Up: Collection 1.37.14 Collection: storing --------------------------- storeOn: aStream Store Smalltalk code compiling to the receiver on aStream  File: gst-base.info, Node: Collection-testing collections, Prev: Collection-storing, Up: Collection 1.37.15 Collection: testing collections --------------------------------------- capacity Answer how many elements the receiver can hold before having to grow. identityIncludes: anObject Answer whether we include the anObject object includes: anObject Answer whether we include anObject includesAllOf: aCollection Answer whether we include all of the objects in aCollection includesAnyOf: aCollection Answer whether we include any of the objects in aCollection isEmpty Answer whether we are (still) empty isSequenceable Answer whether the receiver can be accessed by a numeric index with #at:/#at:put:. notEmpty Answer whether we include at least one object occurrencesOf: anObject Answer how many occurrences of anObject we include size Answer how many objects we include  File: gst-base.info, Node: CompiledBlock, Next: CompiledCode, Prev: Collection, Up: Base classes 1.38 CompiledBlock ================== Defined in namespace Smalltalk Superclass: CompiledCode Category: Language-Implementation I represent a block that has been compiled. * Menu: * CompiledBlock class-instance creation:: (class) * CompiledBlock-accessing:: (instance) * CompiledBlock-basic:: (instance) * CompiledBlock-printing:: (instance) * CompiledBlock-saving and loading:: (instance)  File: gst-base.info, Node: CompiledBlock class-instance creation, Next: CompiledBlock-accessing, Up: CompiledBlock 1.38.1 CompiledBlock class: instance creation --------------------------------------------- new: numBytecodes header: anInteger method: outerMethod Answer a new instance of the receiver with room for the given number of bytecodes and the given header. numArgs: args numTemps: temps bytecodes: bytecodes depth: depth literals: literalArray Answer an (almost) full fledged CompiledBlock. To make it complete, you must either set the new object's `method' variable, or put it into a BlockClosure and put the BlockClosure into a CompiledMethod's literals. The clean-ness of the block is automatically computed.  File: gst-base.info, Node: CompiledBlock-accessing, Next: CompiledBlock-basic, Prev: CompiledBlock class-instance creation, Up: CompiledBlock 1.38.2 CompiledBlock: accessing ------------------------------- flags Answer the `cleanness' of the block. 0 = clean; 1 = access to receiver variables and/or self; 2-30 = access to variables that are 1-29 contexts away; 31 = return from method or push thisContext method Answer the CompiledMethod in which the receiver lies methodClass Answer the class in which the receiver is installed. methodClass: methodClass Set the receiver's class instance variable numArgs Answer the number of arguments passed to the receiver numLiterals Answer the number of literals for the receiver numTemps Answer the number of temporary variables used by the receiver selector Answer the selector through which the method is called selector: aSymbol Set the selector through which the method is called sourceCodeLinesDelta Answer the delta from the numbers in LINE_NUMBER bytecodes to source code line numbers. sourceCodeMap Answer an array which maps bytecode indices to source code line numbers. 0 values represent invalid instruction pointer indices. stackDepth Answer the number of stack slots needed for the receiver  File: gst-base.info, Node: CompiledBlock-basic, Next: CompiledBlock-printing, Prev: CompiledBlock-accessing, Up: CompiledBlock 1.38.3 CompiledBlock: basic --------------------------- = aMethod Answer whether the receiver and aMethod are equal methodCategory Answer the method category methodCategory: aCategory Set the method category to the given string methodSourceCode Answer the method source code (a FileSegment or String or nil) methodSourceFile Answer the file where the method source code is stored methodSourcePos Answer the location where the method source code is stored in the methodSourceFile methodSourceString Answer the method source code as a string  File: gst-base.info, Node: CompiledBlock-printing, Next: CompiledBlock-saving and loading, Prev: CompiledBlock-basic, Up: CompiledBlock 1.38.4 CompiledBlock: printing ------------------------------ printOn: aStream Print the receiver's class and selector on aStream  File: gst-base.info, Node: CompiledBlock-saving and loading, Prev: CompiledBlock-printing, Up: CompiledBlock 1.38.5 CompiledBlock: saving and loading ---------------------------------------- binaryRepresentationObject This method is implemented to allow for a PluggableProxy to be used with CompiledBlocks. Answer a DirectedMessage which sends #blockAt: to the CompiledMethod containing the receiver.  File: gst-base.info, Node: CompiledCode, Next: CompiledMethod, Prev: CompiledBlock, Up: Base classes 1.39 CompiledCode ================= Defined in namespace Smalltalk Superclass: ArrayedCollection Category: Language-Implementation I represent code that has been compiled. I am an abstract superclass for blocks and methods * Menu: * CompiledCode class-cache flushing:: (class) * CompiledCode class-instance creation:: (class) * CompiledCode class-tables:: (class) * CompiledCode-accessing:: (instance) * CompiledCode-basic:: (instance) * CompiledCode-copying:: (instance) * CompiledCode-debugging:: (instance) * CompiledCode-decoding bytecodes:: (instance) * CompiledCode-literals - iteration:: (instance) * CompiledCode-security:: (instance) * CompiledCode-testing accesses:: (instance) * CompiledCode-translation:: (instance)  File: gst-base.info, Node: CompiledCode class-cache flushing, Next: CompiledCode class-instance creation, Up: CompiledCode 1.39.1 CompiledCode class: cache flushing ----------------------------------------- flushTranslatorCache Answer any kind of cache mantained by a just-in-time code translator in the virtual machine (if any). Do nothing for now.  File: gst-base.info, Node: CompiledCode class-instance creation, Next: CompiledCode class-tables, Prev: CompiledCode class-cache flushing, Up: CompiledCode 1.39.2 CompiledCode class: instance creation -------------------------------------------- new: numBytecodes header: anInteger literals: literals Answer a new instance of the receiver with room for the given number of bytecodes and the given header new: numBytecodes header: anInteger numLiterals: numLiterals Answer a new instance of the receiver with room for the given number of bytecodes and the given header  File: gst-base.info, Node: CompiledCode class-tables, Next: CompiledCode-accessing, Prev: CompiledCode class-instance creation, Up: CompiledCode 1.39.3 CompiledCode class: tables --------------------------------- bytecodeInfoTable Return a ByteArray which defines some properties of the bytecodes. For each bytecode, 4 bytes are reserved. The fourth byte is a flag byte: bit 7 means that the argument is a line number to be used in creating the bytecode->line number map. The first three have a meaning only for those bytecodes that represent a combination of operations: the combination can be BC1 ARG BC2 OPERAND if the fourth byte's bit 0 = 0 or BC1 OPERAND BC2 ARG if the fourth byte's bit 0 = 1 where BC1 is the first byte, BC2 is the second, ARG is the third and OPERAND is the bytecode argument as it appears in the bytecode stream. specialSelectors Answer an array of message names that don't need to be in literals to be sent in a method. Their position here reflects their integer code in bytecode. specialSelectorsNumArgs Answer a harmoniously-indexed array of arities for the messages answered by #specialSelectors.  File: gst-base.info, Node: CompiledCode-accessing, Next: CompiledCode-basic, Prev: CompiledCode class-tables, Up: CompiledCode 1.39.4 CompiledCode: accessing ------------------------------ at: anIndex put: aBytecode Store aBytecode as the anIndex-th bytecode blockAt: anIndex Answer the CompiledBlock attached to the anIndex-th literal, assuming that the literal is a CompiledBlock or a BlockClosure. bytecodeAt: anIndex Answer the anIndex-th bytecode bytecodeAt: anIndex put: aBytecode Store aBytecode as the anIndex-th bytecode flags Private - Answer the optimization flags for the receiver isAnnotated Answer `false'. literalAt: anIndex Answer the anIndex-th literal literalAt: anInteger put: aValue Store aValue as the anIndex-th literal literals Answer the literals referenced by my code or any CompiledCode instances I own. method Answer the parent method for the receiver, or self if it is a method. methodClass Answer the class in which the receiver is installed. methodClass: methodClass Set the receiver's class instance variable numArgs Answer the number of arguments for the receiver numLiterals Answer the number of literals for the receiver numTemps Answer the number of temporaries for the receiver primitive Answer the primitive called by the receiver selector Answer the selector through which the method is called selector: aSymbol Set the selector through which the method is called sourceCodeLinesDelta Answer the delta from the numbers in LINE_NUMBER bytecodes to source code line numbers. stackDepth Answer the number of stack slots needed for the receiver  File: gst-base.info, Node: CompiledCode-basic, Next: CompiledCode-copying, Prev: CompiledCode-accessing, Up: CompiledCode 1.39.5 CompiledCode: basic -------------------------- = aMethod Answer whether the receiver is the same object as arg. Testing for equality could break the browser, since it's possible to put arbitrary objects via ##(...), so this is safer. hash Answer an hash value for the receiver methodCategory Answer the method category methodCategory: aCategory Set the method category to the given string methodSourceCode Answer the method source code (a FileSegment or String or nil) methodSourceFile Answer the file where the method source code is stored methodSourcePos Answer the location where the method source code is stored in the methodSourceFile methodSourceString Answer the method source code as a string  File: gst-base.info, Node: CompiledCode-copying, Next: CompiledCode-debugging, Prev: CompiledCode-basic, Up: CompiledCode 1.39.6 CompiledCode: copying ---------------------------- deepCopy Answer a deep copy of the receiver  File: gst-base.info, Node: CompiledCode-debugging, Next: CompiledCode-decoding bytecodes, Prev: CompiledCode-copying, Up: CompiledCode 1.39.7 CompiledCode: debugging ------------------------------ examineOn: aStream Print the contents of the receiver in a verbose way.  File: gst-base.info, Node: CompiledCode-decoding bytecodes, Next: CompiledCode-literals - iteration, Prev: CompiledCode-debugging, Up: CompiledCode 1.39.8 CompiledCode: decoding bytecodes --------------------------------------- dispatchTo: anObject with: param Disassemble the bytecodes and tell anObject about them in the form of message sends. param is given as an argument to every message send.  File: gst-base.info, Node: CompiledCode-literals - iteration, Next: CompiledCode-security, Prev: CompiledCode-decoding bytecodes, Up: CompiledCode 1.39.9 CompiledCode: literals - iteration ----------------------------------------- allLiteralSymbolsDo: aBlock As with #allLiteralsDo:, but only call aBlock with found Symbols. allLiteralsDo: aBlock Walk my literals, descending into Arrays and Messages, invoking aBlock with each touched object. literalsDo: aBlock Invoke aBlock with each object immediately in my list of literals.  File: gst-base.info, Node: CompiledCode-security, Next: CompiledCode-testing accesses, Prev: CompiledCode-literals - iteration, Up: CompiledCode 1.39.10 CompiledCode: security ------------------------------ verify Verify the bytecodes for the receiver, and raise an exception if the verification process failed.  File: gst-base.info, Node: CompiledCode-testing accesses, Next: CompiledCode-translation, Prev: CompiledCode-security, Up: CompiledCode 1.39.11 CompiledCode: testing accesses -------------------------------------- accesses: instVarIndex Answer whether the receiver accesses the instance variable with the given index assigns: instVarIndex Answer whether the receiver writes to the instance variable with the given index containsLiteral: anObject Answer if the receiver contains a literal which is equal to anObject. hasBytecode: byte between: firstIndex and: lastIndex Answer whether the receiver includes the `byte' bytecode in any of the indices between firstIndex and lastIndex. jumpDestinationAt: anIndex forward: aBoolean Answer where the jump at bytecode index `anIndex' lands reads: instVarIndex Answer whether the receiver reads the instance variable with the given index refersTo: anObject Answer whether the receiver refers to the given object sendsToSuper Answer whether the receiver includes a send to super. sourceCodeMap Answer an array which maps bytecode indices to source code line numbers. 0 values represent invalid instruction pointer indices.  File: gst-base.info, Node: CompiledCode-translation, Prev: CompiledCode-testing accesses, Up: CompiledCode 1.39.12 CompiledCode: translation --------------------------------- discardTranslation Flush the just-in-time translated code for the receiver (if any).  File: gst-base.info, Node: CompiledMethod, Next: ContextPart, Prev: CompiledCode, Up: Base classes 1.40 CompiledMethod =================== Defined in namespace Smalltalk Superclass: CompiledCode Category: Language-Implementation I represent methods that have been compiled. I can recompile methods from their source code, I can invoke Emacs to edit the source code for one of my instances, and I know how to access components of my instances. * Menu: * CompiledMethod class-c call-outs:: (class) * CompiledMethod class-instance creation:: (class) * CompiledMethod class-lean images:: (class) * CompiledMethod-accessing:: (instance) * CompiledMethod-attributes:: (instance) * CompiledMethod-basic:: (instance) * CompiledMethod-c call-outs:: (instance) * CompiledMethod-compiling:: (instance) * CompiledMethod-invoking:: (instance) * CompiledMethod-printing:: (instance) * CompiledMethod-saving and loading:: (instance) * CompiledMethod-source code:: (instance) * CompiledMethod-testing:: (instance)  File: gst-base.info, Node: CompiledMethod class-c call-outs, Next: CompiledMethod class-instance creation, Up: CompiledMethod 1.40.1 CompiledMethod class: c call-outs ---------------------------------------- asyncCCall: descr numArgs: numArgs attributes: attributesArray Return a CompiledMethod corresponding to a #asyncCCall:args: pragma with the given arguments. cCall: descr numArgs: numArgs attributes: attributesArray Return a CompiledMethod corresponding to a #cCall:returning:args: pragma with the given arguments.  File: gst-base.info, Node: CompiledMethod class-instance creation, Next: CompiledMethod class-lean images, Prev: CompiledMethod class-c call-outs, Up: CompiledMethod 1.40.2 CompiledMethod class: instance creation ---------------------------------------------- literals: lits numArgs: numArg numTemps: numTemp attributes: attrArray bytecodes: bytecodes depth: depth Answer a full fledged CompiledMethod. Construct the method header from the parameters, and set the literals and bytecodes to the provided ones. Also, the bytecodes are optimized and any embedded CompiledBlocks modified to refer to these literals and to the newly created CompiledMethod. numArgs: args Create a user-defined method (one that is sent #valueWithReceiver:withArguments: when it is invoked) with numArgs arguments. This only makes sense when called for a subclass of CompiledMethod.  File: gst-base.info, Node: CompiledMethod class-lean images, Next: CompiledMethod-accessing, Prev: CompiledMethod class-instance creation, Up: CompiledMethod 1.40.3 CompiledMethod class: lean images ---------------------------------------- stripSourceCode Remove all the references to method source code from the system  File: gst-base.info, Node: CompiledMethod-accessing, Next: CompiledMethod-attributes, Prev: CompiledMethod class-lean images, Up: CompiledMethod 1.40.4 CompiledMethod: accessing -------------------------------- allBlocksDo: aBlock Evaluate aBlock, passing to it all the CompiledBlocks it holds allLiterals Answer the literals referred to by the receiver and all the blocks in it flags Private - Answer the optimization flags for the receiver isOldSyntax Answer whether the method was written with the old (chunk-format) syntax method Answer the receiver, since it is already a method. methodCategory Answer the method category methodCategory: aCategory Set the method category to the given string methodClass Answer the class in which the receiver is installed. methodClass: methodClass Set the receiver's class instance variable noteOldSyntax Remember that the method is written with the old (chunk-format) syntax numArgs Answer the number of arguments for the receiver numTemps Answer the number of temporaries for the receiver primitive Answer the primitive called by the receiver selector Answer the selector through which the method is called selector: aSymbol Set the selector through which the method is called sourceCodeLinesDelta Answer the delta from the numbers in LINE_NUMBER bytecodes to source code line numbers. stackDepth Answer the number of stack slots needed for the receiver withAllBlocksDo: aBlock Evaluate aBlock, passing the receiver and all the CompiledBlocks it holds withNewMethodClass: class Answer either the receiver or a copy of it, with the method class set to class withNewMethodClass: class selector: selector Answer either the receiver or a copy of it, with the method class set to class  File: gst-base.info, Node: CompiledMethod-attributes, Next: CompiledMethod-basic, Prev: CompiledMethod-accessing, Up: CompiledMethod 1.40.5 CompiledMethod: attributes --------------------------------- attributeAt: aSymbol Return a Message for the first attribute named aSymbol defined by the receiver, or answer an error if none was found. attributeAt: aSymbol ifAbsent: aBlock Return a Message for the first attribute named aSymbol defined by the receiver, or evaluate aBlock is none was found. attributes Return an Array of Messages, one for each attribute defined by the receiver. attributesDo: aBlock Evaluate aBlock once for each attribute defined by the receiver, passing a Message each time. isAnnotated If the receiver has any attributes, answer true. primitiveAttribute If the receiver defines a primitive, return a Message resembling the attribute that was used to define it.  File: gst-base.info, Node: CompiledMethod-basic, Next: CompiledMethod-c call-outs, Prev: CompiledMethod-attributes, Up: CompiledMethod 1.40.6 CompiledMethod: basic ---------------------------- = aMethod Answer whether the receiver and aMethod are equal hash Answer an hash value for the receiver  File: gst-base.info, Node: CompiledMethod-c call-outs, Next: CompiledMethod-compiling, Prev: CompiledMethod-basic, Up: CompiledMethod 1.40.7 CompiledMethod: c call-outs ---------------------------------- isValidCCall Answer whether I appear to have the valid flags, information, and ops to invoke a C function and answer its result. rewriteAsAsyncCCall: func args: argsArray Not commented. rewriteAsCCall: funcOrDescr for: aClass Not commented. rewriteAsCCall: func returning: returnType args: argsArray Not commented.  File: gst-base.info, Node: CompiledMethod-compiling, Next: CompiledMethod-invoking, Prev: CompiledMethod-c call-outs, Up: CompiledMethod 1.40.8 CompiledMethod: compiling -------------------------------- methodFormattedSourceString Answer the method source code as a string, formatted using the RBFormatter. Requires package Parser. methodParseNode Answer the parse tree for the receiver, or nil if there is an error. Requires package Parser. parserClass Answer a parser class, similar to Behavior>>parserClass, that can parse my source code. Requires package Parser. recompile Recompile the method in the scope of the class where it leaves. recompileNotifying: aNotifier Recompile the method in the scope of the class where it leaves, notifying errors to aNotifier by sending it #error:.  File: gst-base.info, Node: CompiledMethod-invoking, Next: CompiledMethod-printing, Prev: CompiledMethod-compiling, Up: CompiledMethod 1.40.9 CompiledMethod: invoking ------------------------------- valueWithReceiver: anObject withArguments: args Execute the method within anObject, passing the elements of the args Array as parameters. The method need not reside on the hierarchy from the receiver's class to Object - it need not reside at all in a MethodDictionary, in fact - but doing bad things will compromise stability of the Smalltalk virtual machine (and don't blame anybody but yourself). If the flags field of the method header is 6, this method instead provides a hook from which the virtual machine can call back whenever execution of the method is requested. In this case, invoking the method would cause an infinite loop (the VM asks the method to run, the method asks the VM to invoke it, and so on), so this method fails with a #subclassResponsibility error.  File: gst-base.info, Node: CompiledMethod-printing, Next: CompiledMethod-saving and loading, Prev: CompiledMethod-invoking, Up: CompiledMethod 1.40.10 CompiledMethod: printing -------------------------------- printOn: aStream Print the receiver's class and selector on aStream storeOn: aStream Print code to create the receiver on aStream  File: gst-base.info, Node: CompiledMethod-saving and loading, Next: CompiledMethod-source code, Prev: CompiledMethod-printing, Up: CompiledMethod 1.40.11 CompiledMethod: saving and loading ------------------------------------------ binaryRepresentationObject This method is implemented to allow for a PluggableProxy to be used with CompiledMethods. Answer a DirectedMessage which sends #>> to the class object containing the receiver.  File: gst-base.info, Node: CompiledMethod-source code, Next: CompiledMethod-testing, Prev: CompiledMethod-saving and loading, Up: CompiledMethod 1.40.12 CompiledMethod: source code ----------------------------------- methodRecompilationSourceString Answer the method source code as a string, ensuring that it is in new syntax (it has brackets). methodSourceCode Answer the method source code (a FileSegment or String or nil) methodSourceFile Answer the file where the method source code is stored methodSourcePos Answer the location where the method source code is stored in the methodSourceFile methodSourceString Answer the method source code as a string  File: gst-base.info, Node: CompiledMethod-testing, Prev: CompiledMethod-source code, Up: CompiledMethod 1.40.13 CompiledMethod: testing ------------------------------- accesses: instVarIndex Answer whether the receiver or the blocks it contains accesses the instance variable with the given index assigns: instVarIndex Answer whether the receiver or the blocks it contains writes to the instance variable with the given index isAbstract Answer whether the receiver is abstract. reads: instVarIndex Answer whether the receiver or the blocks it contains reads to the instance variable with the given index sendsToSuper Answer whether the receiver or the blocks it contains have sends to super  File: gst-base.info, Node: ContextPart, Next: Continuation, Prev: CompiledMethod, Up: Base classes 1.41 ContextPart ================ Defined in namespace Smalltalk Superclass: Object Category: Language-Implementation My instances represent executing Smalltalk code, which represent the local environment of executable code. They contain a stack and also provide some methods that can be used in inspection or debugging. * Menu: * ContextPart class-built ins:: (class) * ContextPart class-exception handling:: (class) * ContextPart-accessing:: (instance) * ContextPart-built ins:: (instance) * ContextPart-copying:: (instance) * ContextPart-debugging:: (instance) * ContextPart-enumerating:: (instance) * ContextPart-printing:: (instance) * ContextPart-security checks:: (instance)  File: gst-base.info, Node: ContextPart class-built ins, Next: ContextPart class-exception handling, Up: ContextPart 1.41.1 ContextPart class: built ins ----------------------------------- thisContext Return the value of the thisContext variable. Called internally when the variable is accessed.  File: gst-base.info, Node: ContextPart class-exception handling, Next: ContextPart-accessing, Prev: ContextPart class-built ins, Up: ContextPart 1.41.2 ContextPart class: exception handling -------------------------------------------- backtrace Print a backtrace from the caller to the bottom of the stack on the Transcript backtraceOn: aStream Print a backtrace from the caller to the bottom of the stack on aStream  File: gst-base.info, Node: ContextPart-accessing, Next: ContextPart-built ins, Prev: ContextPart class-exception handling, Up: ContextPart 1.41.3 ContextPart: accessing ----------------------------- at: index Answer the index-th slot in the receiver. Any read access from (self size + 1) to (self basicSize) will give nil. at: index put: anObject Answer the index-th slot in the receiver. Any write access from (self size + 1) to (self basicSize) will give an error unless nil is being written. This is because doing such an access first, and then updating sp, is racy: the garbage collector may trigger in the middle and move anObject, but the slot in the context won't be adjusted. client Answer the client of this context, that is, the object that sent the message that created this context. Fail if the receiver has no parent currentFileName Answer the name of the file where the method source code is environment To create a valid execution environment for the interpreter even before it starts, GST creates a fake context whose selector is nil and which can be used as a marker for the current execution environment. This method answers that context. For processes, it answers the process block itself home Answer the MethodContext to which the receiver refers initialIP Answer the value of the instruction pointer when execution starts in the current context ip Answer the current instruction pointer into the receiver ip: newIP Set the instruction pointer for the receiver isBlock Answer whether the receiver is a block context isDisabled Answers whether the context is skipped when doing a return. Contexts are marked as disabled whenever a non-local return is done (either by returning from the enclosing method of a block, or with the #continue: method of ContextPart) and there are unwind contexts such as those created by #ensure:. All non-unwind contexts are then marked as disabled. isEnvironment To create a valid execution environment for the interpreter even before it starts, GST creates a fake context which invokes a special "termination" method. Such a context can be used as a marker for the current execution environment. Answer whether the receiver is that kind of context. isProcess Answer whether the receiver represents a process context, i.e. a context created by BlockClosure>>#newProcess. Such a context can be recognized because it has no parent but its flags are different from those of the contexts created by the VM's prepareExecutionEnvironment function. isUnwind Answers whether the context must continue execution even after a non-local return (a return from the enclosing method of a block, or a call to the #continue: method of ContextPart). Such contexts are created by #ensure:. method Return the CompiledMethod being executed methodClass Return the class in which the CompiledMethod being executed is defined numArgs Answer the number of arguments passed to the receiver numTemps Answer the number of temporaries used by the receiver parentContext Answer the context that called the receiver parentContext: aContext Set the context to which the receiver will return push: anObject Push an object on the receiver's stack. receiver Return the receiver (self) for the method being executed selector Return the selector for the method being executed size Answer the number of valid fields for the receiver. Any read access from (self size + 1) to (self basicSize) will give nil. sp Answer the current stack pointer into the receiver sp: newSP Set the stack pointer for the receiver. validSize Answer how many elements in the receiver should be inspected  File: gst-base.info, Node: ContextPart-built ins, Next: ContextPart-copying, Prev: ContextPart-accessing, Up: ContextPart 1.41.4 ContextPart: built ins ----------------------------- continue: anObject Resume execution from the receiver, faking that the context on top of it in the execution chain has returned anObject. The receiver must belong to the same process as the executing context, otherwise the results are not predictable. All #ensure: (and possibly #ifCurtailed:) blocks between the currently executing context and the receiver are evaluated (which is not what would happen if you directly bashed at the parent context of thisContext).  File: gst-base.info, Node: ContextPart-copying, Next: ContextPart-debugging, Prev: ContextPart-built ins, Up: ContextPart 1.41.5 ContextPart: copying --------------------------- copyStack Answer a copy of the entire stack. deepCopy Answer a copy of the entire stack, but don't copy any of the other instance variables of the context.  File: gst-base.info, Node: ContextPart-debugging, Next: ContextPart-enumerating, Prev: ContextPart-copying, Up: ContextPart 1.41.6 ContextPart: debugging ----------------------------- currentLine Answer the 1-based number of the line that is pointed to by the receiver's instruction pointer. The DebugTools package caches information, thus making the implementation faster. currentLineInFile Answer the 1-based number of the line that is pointed to by the receiver's instruction pointer, relative to the method's file. The implementation is slow unless the DebugTools package is loaded. debugger Answer the debugger that is attached to the given context. It is always nil unless the DebugTools package is loaded. debuggerClass Answer which debugger should be used to debug the current context chain. The class with the highest debugging priority is picked among those mentioned in the chain. isInternalExceptionHandlingContext Answer whether the receiver is a context that should be hidden to the user when presenting a backtrace.  File: gst-base.info, Node: ContextPart-enumerating, Next: ContextPart-printing, Prev: ContextPart-debugging, Up: ContextPart 1.41.7 ContextPart: enumerating ------------------------------- scanBacktraceFor: selectors do: aBlock Scan the backtrace for contexts whose selector is among those listed in selectors; if one is found, invoke aBlock passing the context. scanBacktraceForAttribute: selector do: aBlock Scan the backtrace for contexts which have the attribute selector listed in selectors; if one is found, invoke aBlock passing the context and the attribute.  File: gst-base.info, Node: ContextPart-printing, Next: ContextPart-security checks, Prev: ContextPart-enumerating, Up: ContextPart 1.41.8 ContextPart: printing ---------------------------- backtrace Print a backtrace from the receiver to the bottom of the stack on the Transcript. backtraceOn: aStream Print a backtrace from the caller to the bottom of the stack on aStream.  File: gst-base.info, Node: ContextPart-security checks, Prev: ContextPart-printing, Up: ContextPart 1.41.9 ContextPart: security checks ----------------------------------- checkSecurityFor: perm Answer the receiver. doSecurityCheckForName: name actions: actions target: target Not commented. securityCheckForName: name Not commented. securityCheckForName: name action: action Not commented. securityCheckForName: name actions: actions target: target Not commented. securityCheckForName: name target: target Not commented.  File: gst-base.info, Node: Continuation, Next: CPtr, Prev: ContextPart, Up: Base classes 1.42 Continuation ================= Defined in namespace Smalltalk Superclass: Object Category: Language-Implementation At my heart, I am something like the goto instruction; my creation sets the label, and my methods do the jump. However, this is a really powerful kind of goto instruction. If your hair is turning green at this point, don't worry as you will probably only deal with users of continuations, rather than with the concept itself. * Menu: * Continuation class-instance creation:: (class) * Continuation-invocation:: (instance)  File: gst-base.info, Node: Continuation class-instance creation, Next: Continuation-invocation, Up: Continuation 1.42.1 Continuation class: instance creation -------------------------------------------- current Return a continuation. currentDo: aBlock Pass a continuation to the one-argument block, aBlock and return the result of evaluating it. escapeDo: aBlock Pass a continuation to the one-argument block, knowing that aBlock does not fall off (either because it includes a method return, or because it yields control to another continuation). If it does, an exception will be signalled and the current process terminated.  File: gst-base.info, Node: Continuation-invocation, Prev: Continuation class-instance creation, Up: Continuation 1.42.2 Continuation: invocation ------------------------------- callCC Activate the original continuation, passing back in turn a continuation for the caller. The called continuation becomes unusable, and any attempt to reactivate it will cause an exception. This is not a limitation, in general, because this method is used to replace a continuation with another (see the implementation of the Generator class). oneShotValue Return nil to the original continuation, which becomes unusable. Attempting to reactivate it will cause an exception. This is an optimization over #value. oneShotValue: v Return anObject to the original continuation, which becomes unusable. Attempting to reactivate it will cause an exception. This is an optimization over #value:. value Return nil to the original continuation, copying the stack to allow another activation. value: anObject Return anObject to the original continuation, copying the stack to allow another activation. valueWithArguments: aCollection Return the sole element of aCollection to the original continuation (or nil if aCollection is empty), copying the stack to allow another activation  File: gst-base.info, Node: CPtr, Next: CPtrCType, Prev: Continuation, Up: Base classes 1.43 CPtr ========= Defined in namespace Smalltalk Superclass: CAggregate Category: Language-C interface * Menu: * CPtr-accessing:: (instance)  File: gst-base.info, Node: CPtr-accessing, Up: CPtr 1.43.1 CPtr: accessing ---------------------- alignof Answer the receiver's required aligment sizeof Answer the receiver's size value Answer the address of the location pointed to by the receiver. value: anObject Set the address of the location pointed to by the receiver to anObject, which can be either an Integer or a CObject. if anObject is an Integer, it is interpreted as a 32-bit or 64-bit address. If it is a CObject, its address is stored.  File: gst-base.info, Node: CPtrCType, Next: CScalar, Prev: CPtr, Up: Base classes 1.44 CPtrCType ============== Defined in namespace Smalltalk Superclass: CType Category: Language-C interface * Menu: * CPtrCType class-instance creation:: (class) * CPtrCType-accessing:: (instance) * CPtrCType-basic:: (instance) * CPtrCType-storing:: (instance)  File: gst-base.info, Node: CPtrCType class-instance creation, Next: CPtrCType-accessing, Up: CPtrCType 1.44.1 CPtrCType class: instance creation ----------------------------------------- elementType: aCType Answer a new instance of CPtrCType that maps pointers to the given CType from: type Private - Called by computeAggregateType: for pointers  File: gst-base.info, Node: CPtrCType-accessing, Next: CPtrCType-basic, Prev: CPtrCType class-instance creation, Up: CPtrCType 1.44.2 CPtrCType: accessing --------------------------- elementType Answer the type of the elements in the receiver's instances  File: gst-base.info, Node: CPtrCType-basic, Next: CPtrCType-storing, Prev: CPtrCType-accessing, Up: CPtrCType 1.44.3 CPtrCType: basic ----------------------- = anObject Return whether the receiver and anObject are equal. hash Return a hash code for the receiver.  File: gst-base.info, Node: CPtrCType-storing, Prev: CPtrCType-basic, Up: CPtrCType 1.44.4 CPtrCType: storing ------------------------- storeOn: aStream Not commented.  File: gst-base.info, Node: CScalar, Next: CScalarCType, Prev: CPtrCType, Up: Base classes 1.45 CScalar ============ Defined in namespace Smalltalk Superclass: CObject Category: Language-C interface * Menu: * CScalar class-instance creation:: (class) * CScalar-accessing:: (instance)  File: gst-base.info, Node: CScalar class-instance creation, Next: CScalar-accessing, Up: CScalar 1.45.1 CScalar class: instance creation --------------------------------------- gcValue: anObject Answer a newly allocated CObject containing the passed value, anObject, in garbage-collected storage. type Answer a CType for the receiver--for example, CByteType if the receiver is CByte. value: anObject Answer a newly allocated CObject containing the passed value, anObject. Remember to call #addToBeFinalized if you want the CObject to be automatically freed  File: gst-base.info, Node: CScalar-accessing, Prev: CScalar class-instance creation, Up: CScalar 1.45.2 CScalar: accessing ------------------------- cObjStoredType Private - Provide a conversion from a CObject to a Smalltalk object to be stored by #at:put: value Answer the value the receiver is pointing to. The exact returned value depends on the receiver's class value: aValue Set the receiver to point to the value, aValue. The exact meaning of aValue depends on the receiver's class  File: gst-base.info, Node: CScalarCType, Next: CShort, Prev: CScalar, Up: Base classes 1.46 CScalarCType ================= Defined in namespace Smalltalk Superclass: CType Category: Language-C interface * Menu: * CScalarCType-accessing:: (instance) * CScalarCType-storing:: (instance)  File: gst-base.info, Node: CScalarCType-accessing, Next: CScalarCType-storing, Up: CScalarCType 1.46.1 CScalarCType: accessing ------------------------------ valueType valueType is used as a means to communicate to the interpreter the underlying type of the data. For scalars, it is supplied by the CObject subclass.  File: gst-base.info, Node: CScalarCType-storing, Prev: CScalarCType-accessing, Up: CScalarCType 1.46.2 CScalarCType: storing ---------------------------- storeOn: aStream Store Smalltalk code that compiles to the receiver  File: gst-base.info, Node: CShort, Next: CSmalltalk, Prev: CScalarCType, Up: Base classes 1.47 CShort =========== Defined in namespace Smalltalk Superclass: CScalar Category: Language-C interface * Menu: * CShort class-accessing:: (class) * CShort-accessing:: (instance)  File: gst-base.info, Node: CShort class-accessing, Next: CShort-accessing, Up: CShort 1.47.1 CShort class: accessing ------------------------------ alignof Answer the receiver's instances required aligment cObjStoredType Private - Answer an index referring to the receiver's instances scalar type sizeof Answer the receiver's instances size  File: gst-base.info, Node: CShort-accessing, Prev: CShort class-accessing, Up: CShort 1.47.2 CShort: accessing ------------------------ alignof Answer the receiver's required aligment cObjStoredType Private - Answer an index referring to the receiver's scalar type sizeof Answer the receiver's size  File: gst-base.info, Node: CSmalltalk, Next: CString, Prev: CShort, Up: Base classes 1.48 CSmalltalk =============== Defined in namespace Smalltalk Superclass: CScalar Category: Language-C interface * Menu: * CSmalltalk class-accessing:: (class) * CSmalltalk-accessing:: (instance)  File: gst-base.info, Node: CSmalltalk class-accessing, Next: CSmalltalk-accessing, Up: CSmalltalk 1.48.1 CSmalltalk class: accessing ---------------------------------- alignof Answer the receiver's instances required aligment cObjStoredType Private - Answer an index referring to the receiver's instances scalar type sizeof Answer the receiver's instances size  File: gst-base.info, Node: CSmalltalk-accessing, Prev: CSmalltalk class-accessing, Up: CSmalltalk 1.48.2 CSmalltalk: accessing ---------------------------- alignof Answer the receiver's required aligment cObjStoredType Private - Answer an index referring to the receiver's scalar type sizeof Answer the receiver's size  File: gst-base.info, Node: CString, Next: CStringCType, Prev: CSmalltalk, Up: Base classes 1.49 CString ============ Defined in namespace Smalltalk Superclass: CPtr Category: Language-C interface Technically, CString is really a pointer to CChar. However, it can be very useful as a distinct datatype because it is a separate datatype in Smalltalk, so we allow developers to express their semantics more precisely by using a more descriptive type. Note that like CChar is a pointer to char, CString is actually a *pointer* to string: a char ** in C terms. If you need to take a String out of a char *, use CChar>>#asString. In general, I behave like a cross between an array of characters and a pointer to a character. I provide the protocol for both data types. My #value method returns a Smalltalk String, as you would expect for a scalar datatype. * Menu: * CString class-accessing:: (class) * CString class-instance creation:: (class) * CString-accessing:: (instance)  File: gst-base.info, Node: CString class-accessing, Next: CString class-instance creation, Up: CString 1.49.1 CString class: accessing ------------------------------- cObjStoredType Private - Provide a conversion from a CObject to a Smalltalk object to be stored by #at:put:  File: gst-base.info, Node: CString class-instance creation, Next: CString-accessing, Prev: CString class-accessing, Up: CString 1.49.2 CString class: instance creation --------------------------------------- type Answer a CType for the receiver--for example, CByteType if the receiver is CByte. value: anObject Answer a newly allocated CObject containing the passed value, anObject. Remember to call #addToBeFinalized if you want the CObject to be automatically freed  File: gst-base.info, Node: CString-accessing, Prev: CString class-instance creation, Up: CString 1.49.3 CString: accessing ------------------------- cObjStoredType Private - Provide a conversion from a CObject to a Smalltalk object to be stored by #at:put: value Answer the value the receiver is pointing to. The exact returned value depends on the receiver's class value: aValue Set the receiver to point to the value, aValue. The exact meaning of aValue depends on the receiver's class  File: gst-base.info, Node: CStringCType, Next: CStruct, Prev: CString, Up: Base classes 1.50 CStringCType ================= Defined in namespace Smalltalk Superclass: CScalarCType Category: Language-C interface * Menu: * CStringCType-accessing:: (instance)  File: gst-base.info, Node: CStringCType-accessing, Up: CStringCType 1.50.1 CStringCType: accessing ------------------------------ elementType Answer the type of the elements in the receiver's instances  File: gst-base.info, Node: CStruct, Next: CType, Prev: CStringCType, Up: Base classes 1.51 CStruct ============ Defined in namespace Smalltalk Superclass: CCompound Category: Language-C interface * Menu: * CStruct class-subclass creation:: (class)  File: gst-base.info, Node: CStruct class-subclass creation, Up: CStruct 1.51.1 CStruct class: subclass creation --------------------------------------- declaration: array Compile methods that implement the declaration in array.  File: gst-base.info, Node: CType, Next: CUChar, Prev: CStruct, Up: Base classes 1.52 CType ========== Defined in namespace Smalltalk Superclass: Object Category: Language-C interface I am not part of the standard Smalltalk kernel class hierarchy. I contain type information used by subclasses of CObject, which represents external C data items. My only instance variable, cObjectType, is used to hold onto the CObject subclass that gets created for a given CType. Used primarily in the C part of the interpreter because internally it cannot execute methods to get values, so it has a simple way to access instance variable which holds the desired subclass. My subclasses have instances which represent the actual data types; for the scalar types, there is only one instance created of each, but for the aggregate types, there is at least one instance per base type and/or number of elements. * Menu: * CType class-C instance creation:: (class) * CType class-initialization:: (class) * CType-accessing:: (instance) * CType-basic:: (instance) * CType-C instance creation:: (instance) * CType-storing:: (instance)  File: gst-base.info, Node: CType class-C instance creation, Next: CType class-initialization, Up: CType 1.52.1 CType class: C instance creation --------------------------------------- cObjectBinding: aCObjectSubclassBinding Create a new CType for the given subclass of CObject cObjectType: aCObjectSubclass Create a new CType for the given subclass of CObject computeAggregateType: type Private - Called by from: for pointers/arrays. Format of type: (#array #int 3) or (#ptr #{FooStruct}) from: type Private - Pass the size, alignment, and description of CType for aBlock, given the field description in `type' (the second element of each pair).  File: gst-base.info, Node: CType class-initialization, Next: CType-accessing, Prev: CType class-C instance creation, Up: CType 1.52.2 CType class: initialization ---------------------------------- initialize Initialize the receiver's TypeMap  File: gst-base.info, Node: CType-accessing, Next: CType-basic, Prev: CType class-initialization, Up: CType 1.52.3 CType: accessing ----------------------- alignof Answer the size of the receiver's instances arrayType: size Answer a CArrayCType which represents an array with the given size of CObjects whose type is in turn represented by the receiver cObjectType Answer the CObject subclass whose instance is created when new is sent to the receiver new: anInteger Allocate a new CObject with room for anInteger C objects of the type (class) identified by the receiver. It is the caller's responsibility to free the memory allocated for it. ptrType Answer a CPtrCType which represents a pointer to CObjects whose type is in turn represented by the receiver sizeof Answer the size of the receiver's instances valueType valueType is used as a means to communicate to the interpreter the underlying type of the data. For anything but scalars, it's just 'self'  File: gst-base.info, Node: CType-basic, Next: CType-C instance creation, Prev: CType-accessing, Up: CType 1.52.4 CType: basic ------------------- = anObject Return whether the receiver and anObject are equal. hash Return a hash code for the receiver.  File: gst-base.info, Node: CType-C instance creation, Next: CType-storing, Prev: CType-basic, Up: CType 1.52.5 CType: C instance creation --------------------------------- address: cObjOrInt Create a new CObject with the type (class) identified by the receiver, pointing to the given address (identified by an Integer or CObject). gcNew Allocate a new CObject with the type (class) identified by the receiver. The object is movable in memory, but on the other hand it is garbage-collected automatically. gcNew: anInteger Allocate a new CObject with room for anInteger C object of the type (class) identified by the receiver. The object is movable in memory, but on the other hand it is garbage-collected automatically. new Allocate a new CObject with the type (class) identified by the receiver. It is the caller's responsibility to free the memory allocated for it.  File: gst-base.info, Node: CType-storing, Prev: CType-C instance creation, Up: CType 1.52.6 CType: storing --------------------- storeOn: aStream Store Smalltalk code that compiles to the receiver  File: gst-base.info, Node: CUChar, Next: CUInt, Prev: CType, Up: Base classes 1.53 CUChar =========== Defined in namespace Smalltalk Superclass: CScalar Category: Language-C interface * Menu: * CUChar class-getting info:: (class) * CUChar-accessing:: (instance)  File: gst-base.info, Node: CUChar class-getting info, Next: CUChar-accessing, Up: CUChar 1.53.1 CUChar class: getting info --------------------------------- alignof Answer the receiver's instances required aligment cObjStoredType Private - Answer an index referring to the receiver's instances scalar type sizeof Answer the receiver's instances size  File: gst-base.info, Node: CUChar-accessing, Prev: CUChar class-getting info, Up: CUChar 1.53.2 CUChar: accessing ------------------------ alignof Answer the receiver's required aligment cObjStoredType Private - Answer an index referring to the receiver's scalar type sizeof Answer the receiver's size  File: gst-base.info, Node: CUInt, Next: CULong, Prev: CUChar, Up: Base classes 1.54 CUInt ========== Defined in namespace Smalltalk Superclass: CScalar Category: Language-C interface * Menu: * CUInt class-accessing:: (class) * CUInt-accessing:: (instance)  File: gst-base.info, Node: CUInt class-accessing, Next: CUInt-accessing, Up: CUInt 1.54.1 CUInt class: accessing ----------------------------- alignof Answer the receiver's instances required aligment cObjStoredType Private - Answer an index referring to the receiver's instances scalar type sizeof Answer the receiver's instances size  File: gst-base.info, Node: CUInt-accessing, Prev: CUInt class-accessing, Up: CUInt 1.54.2 CUInt: accessing ----------------------- alignof Answer the receiver's required aligment cObjStoredType Private - Answer an index referring to the receiver's scalar type sizeof Answer the receiver's size  File: gst-base.info, Node: CULong, Next: CULongLong, Prev: CUInt, Up: Base classes 1.55 CULong =========== Defined in namespace Smalltalk Superclass: CScalar Category: Language-C interface * Menu: * CULong class-accessing:: (class) * CULong-accessing:: (instance)  File: gst-base.info, Node: CULong class-accessing, Next: CULong-accessing, Up: CULong 1.55.1 CULong class: accessing ------------------------------ alignof Answer the receiver's instances required aligment cObjStoredType Private - Answer an index referring to the receiver's instances scalar type sizeof Answer the receiver's instances size  File: gst-base.info, Node: CULong-accessing, Prev: CULong class-accessing, Up: CULong 1.55.2 CULong: accessing ------------------------ alignof Answer the receiver's required aligment cObjStoredType Private - Answer an index referring to the receiver's scalar type sizeof Answer the receiver's size  File: gst-base.info, Node: CULongLong, Next: CUnion, Prev: CULong, Up: Base classes 1.56 CULongLong =============== Defined in namespace Smalltalk Superclass: CScalar Category: Language-C interface * Menu: * CULongLong class-accessing:: (class) * CULongLong-accessing:: (instance)  File: gst-base.info, Node: CULongLong class-accessing, Next: CULongLong-accessing, Up: CULongLong 1.56.1 CULongLong class: accessing ---------------------------------- alignof Answer the receiver's instances required aligment cObjStoredType Private - Answer an index referring to the receiver's instances scalar type sizeof Answer the receiver's instances size  File: gst-base.info, Node: CULongLong-accessing, Prev: CULongLong class-accessing, Up: CULongLong 1.56.2 CULongLong: accessing ---------------------------- alignof Answer the receiver's required aligment cObjStoredType Private - Answer an index referring to the receiver's scalar type sizeof Answer the receiver's size  File: gst-base.info, Node: CUnion, Next: CUShort, Prev: CULongLong, Up: Base classes 1.57 CUnion =========== Defined in namespace Smalltalk Superclass: CCompound Category: Language-C interface * Menu: * CUnion class-subclass creation:: (class)  File: gst-base.info, Node: CUnion class-subclass creation, Up: CUnion 1.57.1 CUnion class: subclass creation -------------------------------------- declaration: array Compile methods that implement the declaration in array.  File: gst-base.info, Node: CUShort, Next: Date, Prev: CUnion, Up: Base classes 1.58 CUShort ============ Defined in namespace Smalltalk Superclass: CScalar Category: Language-C interface * Menu: * CUShort class-accessing:: (class) * CUShort-accessing:: (instance)  File: gst-base.info, Node: CUShort class-accessing, Next: CUShort-accessing, Up: CUShort 1.58.1 CUShort class: accessing ------------------------------- alignof Answer the receiver's instances required aligment cObjStoredType Private - Answer an index referring to the receiver's instances scalar type sizeof Answer the receiver's instances size  File: gst-base.info, Node: CUShort-accessing, Prev: CUShort class-accessing, Up: CUShort 1.58.2 CUShort: accessing ------------------------- alignof Answer the receiver's required aligment cObjStoredType Private - Answer an index referring to the receiver's scalar type sizeof Answer the receiver's size  File: gst-base.info, Node: Date, Next: DateTime, Prev: CUShort, Up: Base classes 1.59 Date ========= Defined in namespace Smalltalk Superclass: Magnitude Category: Language-Data types My instances represent dates. My base date is defined to be Jan 1, 1901. I provide methods for instance creation (including via "symbolic" dates, such as "Date newDay: 14 month: #Feb year: 1990". PLEASE BE WARNED - use this class only for dates after 1582 AD; that's the beginning of the epoch. Dates before 1582 will not be correctly printed. In addition, since ten days were lost from October 5 through October 15, operations between a Gregorian date (after 15-Oct-1582) and a Julian date (before 5-Oct-1582) will give incorrect results; or, 4-Oct-1582 + 2 days will yield 6-Oct-1582 (a non-existent day!), not 16-Oct-1582. In fact, if you pass a year < 1582 to a method like #newDay:month:year: it will assume that it is a two-digit year (e.g. 90=1990, 1000=2900). The only way to create Julian calendar dates is with the #fromDays: instance creation method. * Menu: * Date class-basic:: (class) * Date class-instance creation (ANSI):: (class) * Date class-instance creation (Blue Book):: (class) * Date-basic:: (instance) * Date-compatibility (non-ANSI):: (instance) * Date-date computations:: (instance) * Date-printing:: (instance) * Date-still unclassified:: (instance) * Date-storing:: (instance) * Date-testing:: (instance)  File: gst-base.info, Node: Date class-basic, Next: Date class-instance creation (ANSI), Up: Date 1.59.1 Date class: basic ------------------------ abbreviationOfDay: dayIndex Answer the abbreviated name of the day of week corresponding to the given index dayOfWeek: dayName Answer the index of the day of week corresponding to the given name daysInMonth: monthName forYear: yearInteger Answer the number of days in the given (named) month for the given year daysInYear: i Answer the number of days in the given year indexOfMonth: monthName Answer the index of the month corresponding to the given name initDayNameDict Initialize the DayNameDict to the names of the days initMonthNameDict Initialize the MonthNameDict to the names of the months initialize Initialize the receiver nameOfDay: dayIndex Answer the name of the day of week corresponding to the given index nameOfMonth: monthIndex Answer the name of the month corresponding to the given index shortNameOfMonth: monthIndex Answer the name of the month corresponding to the given index  File: gst-base.info, Node: Date class-instance creation (ANSI), Next: Date class-instance creation (Blue Book), Prev: Date class-basic, Up: Date 1.59.2 Date class: instance creation (ANSI) ------------------------------------------- year: y day: d hour: h minute: min second: s Answer a Date denoting the d-th day of the given year year: y month: m day: d hour: h minute: min second: s Answer a Date denoting the d-th day of the given (as a number) month and year  File: gst-base.info, Node: Date class-instance creation (Blue Book), Next: Date-basic, Prev: Date class-instance creation (ANSI), Up: Date 1.59.3 Date class: instance creation (Blue Book) ------------------------------------------------ dateAndTimeNow Answer an array containing the current date and time fromDays: dayCount Answer a Date denoting dayCount days past 1/1/1901 fromJulian: jd Answer a Date denoting the jd-th day in the astronomical Julian calendar. fromSeconds: time Answer a Date denoting the date time seconds past Jan 1st, 1901 newDay: day month: monthName year: yearInteger Answer a Date denoting the dayCount day of the given (named) month and year newDay: day monthIndex: monthIndex year: yearInteger Answer a Date denoting the dayCount day of the given (as a number) month and year newDay: dayCount year: yearInteger Answer a Date denoting the dayCount day of the yearInteger year readFrom: aStream Parse an instance of the receiver from aStream today Answer a Date denoting the current date in local time utcDateAndTimeNow Answer an array containing the current date and time in Coordinated Universal Time (UTC) utcToday Answer a Date denoting the current date in Coordinated Universal Time (UTC)  File: gst-base.info, Node: Date-basic, Next: Date-compatibility (non-ANSI), Prev: Date class-instance creation (Blue Book), Up: Date 1.59.4 Date: basic ------------------ - aDate Answer a new Duration counting the number of days between the receiver and aDate. addDays: dayCount Answer a new Date pointing dayCount past the receiver subtractDate: aDate Answer the number of days between aDate and the receiver (negative if the receiver is before aDate) subtractDays: dayCount Answer a new Date pointing dayCount before the receiver  File: gst-base.info, Node: Date-compatibility (non-ANSI), Next: Date-date computations, Prev: Date-basic, Up: Date 1.59.5 Date: compatibility (non-ANSI) ------------------------------------- day Answer the day represented by the receiver dayName Answer the day of week of the receiver as a Symbol shortMonthName Answer the abbreviated name of the month represented by the receiver  File: gst-base.info, Node: Date-date computations, Next: Date-printing, Prev: Date-compatibility (non-ANSI), Up: Date 1.59.6 Date: date computations ------------------------------ asSeconds Answer the date as the number of seconds from 1/1/1901. dayOfMonth Answer the day represented by the receiver (same as #day) dayOfWeek Answer the day of week of the receiver. 1 = Monday, 7 = Sunday dayOfWeekAbbreviation Answer the day of week of the receiver as a Symbol dayOfWeekName Answer the day of week of the receiver as a Symbol dayOfYear Answer the days passed since 31/12 of last year; e.g. New Year's Day is 1 daysFromBaseDay Answer the days passed since 1/1/1901 daysInMonth Answer the days in the month represented by the receiver daysInYear Answer the days in the year represented by the receiver daysLeftInMonth Answer the days to the end of the month represented by the receiver daysLeftInYear Answer the days to the end of the year represented by the receiver firstDayOfMonth Answer a Date representing the first day of the month represented by the receiver isLeapYear Answer whether the receiver refers to a date in a leap year. lastDayOfMonth Answer a Date representing the last day of the month represented by the receiver month Answer the index of the month represented by the receiver monthAbbreviation Answer the abbreviated name of the month represented by the receiver monthIndex Answer the index of the month represented by the receiver monthName Answer the name of the month represented by the receiver year Answer the year represented by the receiver  File: gst-base.info, Node: Date-printing, Next: Date-still unclassified, Prev: Date-date computations, Up: Date 1.59.7 Date: printing --------------------- printOn: aStream Print a representation for the receiver on aStream  File: gst-base.info, Node: Date-still unclassified, Next: Date-storing, Prev: Date-printing, Up: Date 1.59.8 Date: still unclassified ------------------------------- + aDuration Answer a new Date or DateTime pointing aDuration time past the receiver.  File: gst-base.info, Node: Date-storing, Next: Date-testing, Prev: Date-still unclassified, Up: Date 1.59.9 Date: storing -------------------- storeOn: aStream Store on aStream Smalltalk code compiling to the receiver  File: gst-base.info, Node: Date-testing, Prev: Date-storing, Up: Date 1.59.10 Date: testing --------------------- < aDate Answer whether the receiver indicates a date preceding aDate = aDate Answer whether the receiver indicates the same date as aDate hash Answer an hash value for the receievr  File: gst-base.info, Node: DateTime, Next: DeferredVariableBinding, Prev: Date, Up: Base classes 1.60 DateTime ============= Defined in namespace Smalltalk Superclass: Date Category: Language-Data types My instances represent timestamps. * Menu: * DateTime class-information:: (class) * DateTime class-instance creation:: (class) * DateTime class-instance creation (non-ANSI):: (class) * DateTime-basic:: (instance) * DateTime-computations:: (instance) * DateTime-printing:: (instance) * DateTime-splitting in dates & times:: (instance) * DateTime-storing:: (instance) * DateTime-testing:: (instance) * DateTime-time zones:: (instance)  File: gst-base.info, Node: DateTime class-information, Next: DateTime class-instance creation, Up: DateTime 1.60.1 DateTime class: information ---------------------------------- clockPrecision Answer `ClockPrecision'. initialize Initialize the receiver's class variables  File: gst-base.info, Node: DateTime class-instance creation, Next: DateTime class-instance creation (non-ANSI), Prev: DateTime class-information, Up: DateTime 1.60.2 DateTime class: instance creation ---------------------------------------- now Answer an instance of the receiver referring to the current date and time. readFrom: aStream Parse an instance of the receiver from aStream today Answer an instance of the receiver referring to midnight of today in local time. year: y day: d hour: h minute: min second: s Answer a DateTime denoting the d-th day of the given year, and setting the time part to the given hour, minute, and second year: y day: d hour: h minute: min second: s offset: ofs Answer a DateTime denoting the d-th day of the given year. Set the offset field to ofs (a Duration), and the time part to the given hour, minute, and second year: y month: m day: d hour: h minute: min second: s Answer a DateTime denoting the d-th day of the given (as a number) month and year, setting the time part to the given hour, minute, and second year: y month: m day: d hour: h minute: min second: s offset: ofs Answer a DateTime denoting the d-th day of the given (as a number) month and year. Set the offset field to ofs (a Duration), and the the time part to the given hour, minute, and second  File: gst-base.info, Node: DateTime class-instance creation (non-ANSI), Next: DateTime-basic, Prev: DateTime class-instance creation, Up: DateTime 1.60.3 DateTime class: instance creation (non-ANSI) --------------------------------------------------- date: aDate time: aTime Answer a DateTime denoting the given date and time. Set the offset field to ofs (a Duration). date: aDate time: aTime offset: ofs Answer a DateTime denoting the given date and time. Set the offset field to ofs (a Duration). fromDays: days seconds: secs Answer a DateTime denoting the given date (as days since January 1, 1901) and time (as seconds since UTC midnight). fromDays: days seconds: secs offset: ofs Answer a DateTime denoting the given date (as days since January 1, 1901) and time (as seconds since midnight). Set the offset field to ofs (a Duration). fromSeconds: secs Answer a DateTime denoting the given date and time (as seconds since January 1, 1901 midnight UTC). fromSeconds: secs offset: ofs Answer a DateTime denoting the given date and time (as seconds since January 1, 1901 midnight). Set the offset field to ofs (a Duration).  File: gst-base.info, Node: DateTime-basic, Next: DateTime-computations, Prev: DateTime class-instance creation (non-ANSI), Up: DateTime 1.60.4 DateTime: basic ---------------------- + aDuration Answer a new Date pointing aDuration time past the receiver - aDateTimeOrDuration Answer a new Date pointing dayCount before the receiver  File: gst-base.info, Node: DateTime-computations, Next: DateTime-printing, Prev: DateTime-basic, Up: DateTime 1.60.5 DateTime: computations ----------------------------- asSeconds Answer the date as the number of seconds from 1/1/1901. dayOfWeek Answer the day of week of the receiver. Unlike Dates, DateAndTimes have 1 = Sunday, 7 = Saturday hour Answer the hour in a 24-hour clock hour12 Answer the hour in a 12-hour clock hour24 Answer the hour in a 24-hour clock meridianAbbreviation Answer either #AM (for anti-meridian) or #PM (for post-meridian) minute Answer the minute second Answer the month represented by the receiver  File: gst-base.info, Node: DateTime-printing, Next: DateTime-splitting in dates & times, Prev: DateTime-computations, Up: DateTime 1.60.6 DateTime: printing ------------------------- printOn: aStream Print a representation for the receiver on aStream  File: gst-base.info, Node: DateTime-splitting in dates & times, Next: DateTime-storing, Prev: DateTime-printing, Up: DateTime 1.60.7 DateTime: splitting in dates & times ------------------------------------------- asDate Answer a Date referring to the same day as the receiver asTime Answer a Time referring to the same time (from midnight) as the receiver at: anIndex Since in the past timestamps were referred to as Arrays containing a Date and a Time (in this order), this method provides access to DateTime objects like if they were two-element Arrays.  File: gst-base.info, Node: DateTime-storing, Next: DateTime-testing, Prev: DateTime-splitting in dates & times, Up: DateTime 1.60.8 DateTime: storing ------------------------ storeOn: aStream Store on aStream Smalltalk code compiling to the receiver  File: gst-base.info, Node: DateTime-testing, Next: DateTime-time zones, Prev: DateTime-storing, Up: DateTime 1.60.9 DateTime: testing ------------------------ < aDateTime Answer whether the receiver indicates a date preceding aDate = aDateTime Answer whether the receiver indicates the same date as aDate hash Answer an hash value for the receievr  File: gst-base.info, Node: DateTime-time zones, Prev: DateTime-testing, Up: DateTime 1.60.10 DateTime: time zones ---------------------------- asLocal Answer the receiver, since DateTime objects store themselves in Local time asUTC Convert the receiver to UTC time, and answer a new DateTime object. offset Answer the receiver's offset from UTC to local time (e.g. +3600 seconds for Central Europe Time, -3600*6 seconds for Eastern Standard Time). The offset is expressed as a Duration offset: anOffset Answer a copy of the receiver with the offset from UTC to local time changed to anOffset (a Duration). timeZoneAbbreviation Answer an abbreviated indication of the receiver's offset, expressed as `shhmm', where `hh' is the number of hours and `mm' is the number of minutes between UTC and local time, and `s' can be `+' for the Eastern hemisphere and `-' for the Western hemisphere. timeZoneName Answer the time zone name for the receiver (currently, it is simply `GMT +xxxx', where `xxxx' is the receiver's #timeZoneAbbreviation).  File: gst-base.info, Node: DeferredVariableBinding, Next: Delay, Prev: DateTime, Up: Base classes 1.61 DeferredVariableBinding ============================ Defined in namespace Smalltalk Superclass: LookupKey Category: Language-Data types I represent a binding to a variable that is not tied to a particular dictionary until the first access. Then, lookup rules for global variables in the scope of a given class are used. * Menu: * DeferredVariableBinding class-basic:: (class) * DeferredVariableBinding-basic:: (instance) * DeferredVariableBinding-storing:: (instance)  File: gst-base.info, Node: DeferredVariableBinding class-basic, Next: DeferredVariableBinding-basic, Up: DeferredVariableBinding 1.61.1 DeferredVariableBinding class: basic ------------------------------------------- key: aSymbol class: aClass defaultDictionary: aDictionary Answer a binding that will look up aSymbol as a variable in aClass's environment at first access. See #resolveBinding's comment for aDictionary's meaning. path: anArray class: aClass defaultDictionary: aDictionary As with #key:class:defaultDictionary:, but accepting an array of symbols, representing a namespace path, instead.  File: gst-base.info, Node: DeferredVariableBinding-basic, Next: DeferredVariableBinding-storing, Prev: DeferredVariableBinding class-basic, Up: DeferredVariableBinding 1.61.2 DeferredVariableBinding: basic ------------------------------------- path Answer the path followed after resolving the first key. value Answer a new instance of the receiver with the given key and value value: anObject Answer a new instance of the receiver with the given key and value  File: gst-base.info, Node: DeferredVariableBinding-storing, Prev: DeferredVariableBinding-basic, Up: DeferredVariableBinding 1.61.3 DeferredVariableBinding: storing --------------------------------------- printOn: aStream Put on aStream some Smalltalk code compiling to the receiver storeOn: aStream Put on aStream some Smalltalk code compiling to the receiver  File: gst-base.info, Node: Delay, Next: DelayedAdaptor, Prev: DeferredVariableBinding, Up: Base classes 1.62 Delay ========== Defined in namespace Smalltalk Superclass: Object Category: Kernel-Processes I am the ultimate agent for frustration in the world. I cause things to wait (sometimes much more than is appropriate, but it is those losing operating systems' fault). When a process sends one of my instances a wait message, that process goes to sleep for the interval specified when the instance was created. * Menu: * Delay class-instance creation:: (class) * Delay class-still unclassified:: (class) * Delay class-timer process:: (class) * Delay-accessing:: (instance) * Delay-comparing:: (instance) * Delay-copying:: (instance) * Delay-delaying:: (instance) * Delay-initialization:: (instance) * Delay-instance creation:: (instance) * Delay-testing:: (instance) * Delay-timeout:: (instance)  File: gst-base.info, Node: Delay class-instance creation, Next: Delay class-still unclassified, Up: Delay 1.62.1 Delay class: instance creation ------------------------------------- forMilliseconds: millisecondCount Answer a Delay waiting for millisecondCount milliseconds forNanoseconds: nanosecondCount Answer a Delay waiting for nanosecondCount nanoseconds forSeconds: secondCount Answer a Delay waiting for secondCount seconds untilMilliseconds: millisecondCount Answer a Delay waiting until millisecondCount milliseconds after startup untilNanoseconds: nanosecondCount Answer a Delay waiting until nanosecondCount nanoseconds after startup  File: gst-base.info, Node: Delay class-still unclassified, Next: Delay class-timer process, Prev: Delay class-instance creation, Up: Delay 1.62.2 Delay class: still unclassified -------------------------------------- update: aspect Prime the timer event loop when the image starts running.  File: gst-base.info, Node: Delay class-timer process, Next: Delay-accessing, Prev: Delay class-still unclassified, Up: Delay 1.62.3 Delay class: timer process --------------------------------- activeDelay Return the delay at the head of the queue. handleDelayRequestor Handle a timer event; which can be either: - a schedule or unschedule request (DelayRequestor notNil) - a timer signal (not explicitly specified) We check for timer expiry every time we get a signal. runDelayProcess Run the timer event loop. scheduleDelay: aDelay Private - Schedule this Delay. Run in the timer process, which is the only one that manipulates Queue. startDelayLoop Start the timer event loop. unscheduleDelay: aDelay Private - Unschedule this Delay. Run in the timer process, which is the only one that manipulates Queue.  File: gst-base.info, Node: Delay-accessing, Next: Delay-comparing, Prev: Delay class-timer process, Up: Delay 1.62.4 Delay: accessing ----------------------- asAbsolute Answer a delay that waits until the current delay's resumptionTime, or delayDuration milliseconds from now if that would be nil. May answer the receiver if it is already waiting until an absolute time. delayDuration Answer the time I have left to wait, in milliseconds. isAbsolute Answer whether the receiver waits until an absolute time on the millisecond clock. resumptionTime Answer `resumptionTime'.  File: gst-base.info, Node: Delay-comparing, Next: Delay-copying, Prev: Delay-accessing, Up: Delay 1.62.5 Delay: comparing ----------------------- = aDelay Answer whether the receiver and aDelay denote the same delay hash Answer an hash value for the receiver  File: gst-base.info, Node: Delay-copying, Next: Delay-delaying, Prev: Delay-comparing, Up: Delay 1.62.6 Delay: copying --------------------- postCopy Adjust the current delay so that it behaves as if it had just been created.  File: gst-base.info, Node: Delay-delaying, Next: Delay-initialization, Prev: Delay-copying, Up: Delay 1.62.7 Delay: delaying ---------------------- timedWaitOn: aSemaphore Schedule this Delay and wait on it. The current process will be suspended for the amount of time specified when this Delay was created, or until aSemaphore is signaled. wait Schedule this Delay and wait on it. The current process will be suspended for the amount of time specified when this Delay was created.  File: gst-base.info, Node: Delay-initialization, Next: Delay-instance creation, Prev: Delay-delaying, Up: Delay 1.62.8 Delay: initialization ---------------------------- initForNanoseconds: value Initialize a Delay waiting for millisecondCount milliseconds  File: gst-base.info, Node: Delay-instance creation, Next: Delay-testing, Prev: Delay-initialization, Up: Delay 1.62.9 Delay: instance creation ------------------------------- initUntilNanoseconds: value Initialize a Delay waiting for millisecondCount milliseconds after startup  File: gst-base.info, Node: Delay-testing, Next: Delay-timeout, Prev: Delay-instance creation, Up: Delay 1.62.10 Delay: testing ---------------------- isActive Answer whether this Delay is being waited on.  File: gst-base.info, Node: Delay-timeout, Prev: Delay-testing, Up: Delay 1.62.11 Delay: timeout ---------------------- value: aBlock onTimeoutDo: aTimeoutBlock Execute aBlock for up to the time of my own delay; in case the code did not finish abort the execution, unwind the block and then evaluate aTimeoutBlock.  File: gst-base.info, Node: DelayedAdaptor, Next: Dictionary, Prev: Delay, Up: Base classes 1.63 DelayedAdaptor =================== Defined in namespace Smalltalk Superclass: PluggableAdaptor Category: Language-Data types I can be used where many expensive updates must be performed. My instances buffer the last value that was set, and only actually set the value when the #trigger message is sent. Apart from this, I'm equivalent to PluggableAdaptor. * Menu: * DelayedAdaptor-accessing:: (instance)  File: gst-base.info, Node: DelayedAdaptor-accessing, Up: DelayedAdaptor 1.63.1 DelayedAdaptor: accessing -------------------------------- trigger Really set the value of the receiver. value Get the value of the receiver. value: anObject Set the value of the receiver - actually, the value is cached and is not set until the #trigger method is sent.  File: gst-base.info, Node: Dictionary, Next: DirectedMessage, Prev: DelayedAdaptor, Up: Base classes 1.64 Dictionary =============== Defined in namespace Smalltalk Superclass: HashedCollection Category: Collections-Keyed I implement a dictionary, which is an object that is indexed by unique objects (typcially instances of Symbol), and associates another object with that index. I use the equality operator = to determine equality of indices. In almost all places where you would use a plain Dictionary, a LookupTable would be more efficient; see LookupTable's comment before you use it. I do have a couple of special features that are useful in certain special cases. * Menu: * Dictionary class-instance creation:: (class) * Dictionary-accessing:: (instance) * Dictionary-awful ST-80 compatibility hacks:: (instance) * Dictionary-compilation:: (instance) * Dictionary-dictionary enumerating:: (instance) * Dictionary-dictionary removing:: (instance) * Dictionary-dictionary testing:: (instance) * Dictionary-namespace protocol:: (instance) * Dictionary-printing:: (instance) * Dictionary-rehashing:: (instance) * Dictionary-removing:: (instance) * Dictionary-storing:: (instance) * Dictionary-testing:: (instance)  File: gst-base.info, Node: Dictionary class-instance creation, Next: Dictionary-accessing, Up: Dictionary 1.64.1 Dictionary class: instance creation ------------------------------------------ from: anArray Answer a new dictionary created from the keys and values of Associations in anArray, such as {1 -> 2. 3 -> 4}. anArray should be specified using brace-syntax. new Create a new dictionary with a default size  File: gst-base.info, Node: Dictionary-accessing, Next: Dictionary-awful ST-80 compatibility hacks, Prev: Dictionary class-instance creation, Up: Dictionary 1.64.2 Dictionary: accessing ---------------------------- add: newObject Add the newObject association to the receiver addAll: aCollection Adds all the elements of 'aCollection' to the receiver, answer aCollection associationAt: key Answer the key/value Association for the given key. Fail if the key is not found associationAt: key ifAbsent: aBlock Answer the key/value Association for the given key. Evaluate aBlock (answering the result) if the key is not found associations Returns the content of a Dictionary as a Set of Associations. at: key Answer the value associated to the given key. Fail if the key is not found at: key ifAbsent: aBlock Answer the value associated to the given key, or the result of evaluating aBlock if the key is not found at: aKey ifAbsentPut: aBlock Answer the value associated to the given key. If the key is not found, evaluate aBlock and associate the result to aKey before returning. at: aKey ifPresent: aBlock If aKey is absent, answer nil. Else, evaluate aBlock passing the associated value and answer the result of the invocation at: key put: value Store value as associated to the given key atAll: keyCollection Answer a Dictionary that only includes the given keys. Fail if any of them is not found keyAtValue: value Answer the key associated to the given value, or nil if the value is not found keyAtValue: value ifAbsent: exceptionBlock Answer the key associated to the given value. Evaluate exceptionBlock (answering the result) if the value is not found. IMPORTANT: == is used to compare values keys Answer a kind of Set containing the keys of the receiver values Answer an Array containing the values of the receiver  File: gst-base.info, Node: Dictionary-awful ST-80 compatibility hacks, Next: Dictionary-compilation, Prev: Dictionary-accessing, Up: Dictionary 1.64.3 Dictionary: awful ST-80 compatibility hacks -------------------------------------------------- findKeyIndex: key Tries to see if key exists as a the key of an indexed variable. As soon as nil or an association with the correct key is found, the index of that slot is answered  File: gst-base.info, Node: Dictionary-compilation, Next: Dictionary-dictionary enumerating, Prev: Dictionary-awful ST-80 compatibility hacks, Up: Dictionary 1.64.4 Dictionary: compilation ------------------------------ scopeDictionary Answer the dictionary that is used when the receiver is before a period in Smalltalk source code.  File: gst-base.info, Node: Dictionary-dictionary enumerating, Next: Dictionary-dictionary removing, Prev: Dictionary-compilation, Up: Dictionary 1.64.5 Dictionary: dictionary enumerating ----------------------------------------- associationsDo: aBlock Pass each association in the dictionary to aBlock collect: aBlock Answer a new dictionary where the keys are the same and the values are obtained by passing each value to aBlock and collecting the return values do: aBlock Pass each value in the dictionary to aBlock keysAndValuesDo: aBlock Pass each key/value pair in the dictionary as two distinct parameters to aBlock keysDo: aBlock Pass each key in the dictionary to aBlock reject: aBlock Answer a new dictionary containing the key/value pairs for which aBlock returns false. aBlock only receives the value part of the pairs. select: aBlock Answer a new dictionary containing the key/value pairs for which aBlock returns true. aBlock only receives the value part of the pairs.  File: gst-base.info, Node: Dictionary-dictionary removing, Next: Dictionary-dictionary testing, Prev: Dictionary-dictionary enumerating, Up: Dictionary 1.64.6 Dictionary: dictionary removing -------------------------------------- remove: anAssociation Remove anAssociation's key from the dictionary remove: anAssociation ifAbsent: aBlock Remove anAssociation's key from the dictionary removeAllKeys: keys Remove all the keys in keys, without raising any errors removeAllKeys: keys ifAbsent: aBlock Remove all the keys in keys, passing the missing keys as parameters to aBlock as they're encountered removeKey: key Remove the passed key from the dictionary, fail if it is not found removeKey: key ifAbsent: aBlock Remove the passed key from the dictionary, answer the result of evaluating aBlock if it is not found  File: gst-base.info, Node: Dictionary-dictionary testing, Next: Dictionary-namespace protocol, Prev: Dictionary-dictionary removing, Up: Dictionary 1.64.7 Dictionary: dictionary testing ------------------------------------- includes: anObject Answer whether the receiver contains anObject as one of its values includesAssociation: anAssociation Answer whether the receiver contains the key which is anAssociation's key and its value is anAssociation's value includesKey: key Answer whether the receiver contains the given key occurrencesOf: aValue Answer whether the number of occurrences of aValue as one of the receiver's values  File: gst-base.info, Node: Dictionary-namespace protocol, Next: Dictionary-printing, Prev: Dictionary-dictionary testing, Up: Dictionary 1.64.8 Dictionary: namespace protocol ------------------------------------- allSuperspaces Answer all the receiver's superspaces in a collection allSuperspacesDo: aBlock Evaluate aBlock once for each of the receiver's superspaces (which is none for BindingDictionary). definedKeys Answer a kind of Set containing the keys of the receiver definesKey: key Answer whether the receiver defines the given key. `Defines' means that the receiver's superspaces, if any, are not considered. hereAssociationAt: key Return the association for the variable named as specified by `key' *in this namespace*. If the key is not found search will *not* be carried on in superspaces and the method will fail. hereAssociationAt: key ifAbsent: aBlock Return the association for the variable named as specified by `key' *in this namespace*. If the key is not found search will *not* be carried on in superspaces and aBlock will be immediately evaluated. hereAt: key Return the value associated to the variable named as specified by `key' *in this namespace*. If the key is not found search will *not* be carried on in superspaces and the method will fail. hereAt: key ifAbsent: aBlock Return the value associated to the variable named as specified by `key' *in this namespace*. If the key is not found search will *not* be carried on in superspaces and aBlock will be immediately evaluated. inheritsFrom: aNamespace Answer whether aNamespace is one of the receiver's direct and indirect superspaces superspace Answer the receiver's superspace, which is nil for BindingDictionary. withAllSuperspaces Answer the receiver and all of its superspaces in a collection, which is none for BindingDictionary withAllSuperspacesDo: aBlock Invokes aBlock for the receiver and all superspaces, both direct and indirect (though a BindingDictionary does not have any).  File: gst-base.info, Node: Dictionary-printing, Next: Dictionary-rehashing, Prev: Dictionary-namespace protocol, Up: Dictionary 1.64.9 Dictionary: printing --------------------------- examineOn: aStream Print all the instance variables and objects in the receiver on aStream printOn: aStream Print a representation of the receiver on aStream  File: gst-base.info, Node: Dictionary-rehashing, Next: Dictionary-removing, Prev: Dictionary-printing, Up: Dictionary 1.64.10 Dictionary: rehashing ----------------------------- rehash Rehash the receiver  File: gst-base.info, Node: Dictionary-removing, Next: Dictionary-storing, Prev: Dictionary-rehashing, Up: Dictionary 1.64.11 Dictionary: removing ---------------------------- removeAllKeysSuchThat: aBlock Remove from the receiver all keys for which aBlock returns true.  File: gst-base.info, Node: Dictionary-storing, Next: Dictionary-testing, Prev: Dictionary-removing, Up: Dictionary 1.64.12 Dictionary: storing --------------------------- storeOn: aStream Print Smalltalk code compiling to the receiver on aStream  File: gst-base.info, Node: Dictionary-testing, Prev: Dictionary-storing, Up: Dictionary 1.64.13 Dictionary: testing --------------------------- = aDictionary Answer whether the receiver and aDictionary are equal hash Answer the hash value for the receiver  File: gst-base.info, Node: DirectedMessage, Next: Directory, Prev: Dictionary, Up: Base classes 1.65 DirectedMessage ==================== Defined in namespace Smalltalk Superclass: Message Category: Language-Implementation I represent a message send: I contain the receiver, selector and arguments for a message. * Menu: * DirectedMessage class-creating instances:: (class) * DirectedMessage-accessing:: (instance) * DirectedMessage-basic:: (instance) * DirectedMessage-multiple process:: (instance) * DirectedMessage-saving and loading:: (instance)  File: gst-base.info, Node: DirectedMessage class-creating instances, Next: DirectedMessage-accessing, Up: DirectedMessage 1.65.1 DirectedMessage class: creating instances ------------------------------------------------ receiver: anObject selector: aSymbol Create a new instance of the receiver receiver: receiverObject selector: aSymbol argument: argumentObject Create a new instance of the receiver receiver: anObject selector: aSymbol arguments: anArray Create a new instance of the receiver selector: aSymbol arguments: anArray This method should not be called for instances of this class. selector: aSymbol arguments: anArray receiver: anObject Create a new instance of the receiver  File: gst-base.info, Node: DirectedMessage-accessing, Next: DirectedMessage-basic, Prev: DirectedMessage class-creating instances, Up: DirectedMessage 1.65.2 DirectedMessage: accessing --------------------------------- receiver Answer the receiver receiver: anObject Change the receiver  File: gst-base.info, Node: DirectedMessage-basic, Next: DirectedMessage-multiple process, Prev: DirectedMessage-accessing, Up: DirectedMessage 1.65.3 DirectedMessage: basic ----------------------------- printOn: aStream Print a representation of the receiver on aStream send Send the message value Send the message (this message provides interoperability between DirectedMessages and blocks) value: anObject Send the message with the sole argument anObject (this message provides interoperability between DirectedMessages and blocks) value: obj1 value: obj2 Send the message with the arguments obj1 and obj2 (this message provides interoperability between DirectedMessages and blocks) valueWithArguments: anArray Send the message with the arguments replaced by anArray (this message provides interoperability between DirectedMessages and blocks)  File: gst-base.info, Node: DirectedMessage-multiple process, Next: DirectedMessage-saving and loading, Prev: DirectedMessage-basic, Up: DirectedMessage 1.65.4 DirectedMessage: multiple process ---------------------------------------- fork Create a new process executing the receiver and start it forkAt: priority Create a new process executing the receiver with given priority and start it newProcess Create a new process executing the receiver in suspended state. The priority is the same as for the calling process. The receiver must not contain returns  File: gst-base.info, Node: DirectedMessage-saving and loading, Prev: DirectedMessage-multiple process, Up: DirectedMessage 1.65.5 DirectedMessage: saving and loading ------------------------------------------ reconstructOriginalObject This method is used when DirectedMessages are used together with PluggableProxies (see ObjectDumper). It sends the receiver to reconstruct the object that was originally stored.  File: gst-base.info, Node: Directory, Next: DLD, Prev: DirectedMessage, Up: Base classes 1.66 Directory ============== Defined in namespace Smalltalk Superclass: Object Category: Streams-Files I am the counterpart of File in a tree-structured file system. I provide the notion of a current working directory and know several well-known places in the file system. However, all navigation methods for directories are under FilePath or File for efficiency reasons. Refer to the manual of FilePath for information on how to use the instances returned by my class methods. * Menu: * Directory class-file name management:: (class) * Directory class-file operations:: (class) * Directory class-reading system defaults:: (class)  File: gst-base.info, Node: Directory class-file name management, Next: Directory class-file operations, Up: Directory 1.66.1 Directory class: file name management -------------------------------------------- append: fileName to: directory Answer the name of a file named `fileName' which resides in a directory named `directory'. pathSeparator Answer (as a Character) the character used to separate directory names pathSeparatorString Answer (in a String) the character used to separate directory names  File: gst-base.info, Node: Directory class-file operations, Next: Directory class-reading system defaults, Prev: Directory class-file name management, Up: Directory 1.66.2 Directory class: file operations --------------------------------------- allFilesMatching: aPattern do: aBlock Invoke #allFilesMatching:do: on the current working directory. create: dirName Create a directory named dirName and answer it. createTemporary: prefix Create an empty directory whose name starts with prefix and answer it. working Answer the current working directory, not following symlinks. working: dirName Change the current working directory to dirName.  File: gst-base.info, Node: Directory class-reading system defaults, Prev: Directory class-file operations, Up: Directory 1.66.3 Directory class: reading system defaults ----------------------------------------------- execPrefix Answer the path to GNU Smalltalk's executable installation prefix home Answer the path to the user's home directory image Answer the path to GNU Smalltalk's image file kernel Answer the path in which a local version of the GNU Smalltalk kernel's Smalltalk source files were searched when the image was created. libexec Answer the path to GNU Smalltalk's auxiliary executables localKernel Answer the path to the GNU Smalltalk kernel's Smalltalk source files. Same as `Directory kernel' since GNU Smalltalk 3.0. module Answer the path to GNU Smalltalk's dynamically loaded modules prefix Answer the path to GNU Smalltalk's installation prefix systemKernel Answer the path to the installed Smalltalk kernel source files. temporary Answer the path in which temporary files can be created. This is read from the environment, and guessed if that fails. userBase Answer the base path under which file for user customization of GNU Smalltalk are stored.  File: gst-base.info, Node: DLD, Next: DumperProxy, Prev: Directory, Up: Base classes 1.67 DLD ======== Defined in namespace Smalltalk Superclass: Object Category: Language-C interface ...and Gandalf said: "Many folk like to know beforehand what is to be set on the table; but those who have laboured to prepare the feast like to keep their secret; for wonder makes the words of praise louder." I am just an ancillary class used to reference some C functions. Most of my actual functionality is used by redefinitions of methods in CFunctionDescriptor. * Menu: * DLD class-C call-outs:: (class) * DLD class-dynamic linking:: (class)  File: gst-base.info, Node: DLD class-C call-outs, Next: DLD class-dynamic linking, Up: DLD 1.67.1 DLD class: C call-outs ----------------------------- defineCFunc: aName as: aFuncAddr Register aFuncAddr as the target for cCalls to aName.  File: gst-base.info, Node: DLD class-dynamic linking, Prev: DLD class-C call-outs, Up: DLD 1.67.2 DLD class: dynamic linking --------------------------------- addLibrary: library Add library to the search path of libraries to be used by DLD. addLibraryHandle: libraryHandle This is called internally by gst_dlopen. The library will be open and put in the search path. addModule: library Add library to the list of modules to be loaded when the image is started. The gst_initModule function in the library is called, but the library will not be put in the search path used whenever a C function is requested but not registered. defineExternFunc: aFuncName This method calls #primDefineExternFunc: to try to link to a function with the given name, and answers whether the linkage was successful. You can redefine this method to restrict the ability to do dynamic linking. initialize Private - Initialize the receiver's class variables libraryList Answer a copy of the search path of libraries to be used by DLD moduleList Answer a copy of the modules reloaded when the image is started primDefineExternFunc: aFuncName This method tries to link to a function with the given name, and answers whether the linkage was successful. It should not be overridden. update: aspect Called on startup - Make DLD re-link and reset the addresses of all the externally defined functions  File: gst-base.info, Node: DumperProxy, Next: Duration, Prev: DLD, Up: Base classes 1.68 DumperProxy ================ Defined in namespace Smalltalk Superclass: Object Category: Streams-Files I am an helper class for ObjectDumper. When an object cannot be saved in the standard way, you can register a subclass of me to provide special means to save that object. * Menu: * DumperProxy class-accessing:: (class) * DumperProxy class-instance creation:: (class) * DumperProxy-saving and restoring:: (instance)  File: gst-base.info, Node: DumperProxy class-accessing, Next: DumperProxy class-instance creation, Up: DumperProxy 1.68.1 DumperProxy class: accessing ----------------------------------- acceptUsageForClass: aClass The receiver was asked to be used as a proxy for the class aClass. Answer whether the registration is fine. By default, answer true loadFrom: anObjectDumper Reload a proxy stored in anObjectDumper and reconstruct the object  File: gst-base.info, Node: DumperProxy class-instance creation, Next: DumperProxy-saving and restoring, Prev: DumperProxy class-accessing, Up: DumperProxy 1.68.2 DumperProxy class: instance creation ------------------------------------------- on: anObject Answer a proxy to be used to save anObject. This method MUST be overridden and anObject must NOT be stored in the object's instance variables unless you override #dumpTo:, because that would result in an infinite loop!  File: gst-base.info, Node: DumperProxy-saving and restoring, Prev: DumperProxy class-instance creation, Up: DumperProxy 1.68.3 DumperProxy: saving and restoring ---------------------------------------- dumpTo: anObjectDumper Dump the proxy to anObjectDumper - the #loadFrom: class method will reconstruct the original object. object Reconstruct the object stored in the proxy and answer it  File: gst-base.info, Node: Duration, Next: DynamicVariable, Prev: DumperProxy, Up: Base classes 1.69 Duration ============= Defined in namespace Smalltalk Superclass: Time Category: Language-Data types My instances represent differences between timestamps. * Menu: * Duration class-instance creation:: (class) * Duration class-instance creation (non ANSI):: (class) * Duration-arithmetics:: (instance) * Duration-processes:: (instance) * Duration-storing:: (instance)  File: gst-base.info, Node: Duration class-instance creation, Next: Duration class-instance creation (non ANSI), Up: Duration 1.69.1 Duration class: instance creation ---------------------------------------- days: d Answer a duration of `d' days days: d hours: h minutes: m seconds: s Answer a duration of `d' days and the given number of hours, minutes, and seconds. initialize Initialize the receiver's instance variables milliseconds: msec Answer a duration of `msec' milliseconds readFrom: aStream Parse an instance of the receiver (hours/minutes/seconds) from aStream weeks: w Answer a duration of `w' weeks zero Answer a duration of zero seconds.  File: gst-base.info, Node: Duration class-instance creation (non ANSI), Next: Duration-arithmetics, Prev: Duration class-instance creation, Up: Duration 1.69.2 Duration class: instance creation (non ANSI) --------------------------------------------------- fromDays: days seconds: secs offset: unused Answer a duration of `d' days and `secs' seconds. The last parameter is unused; this message is available for interoperability with the DateTime class.  File: gst-base.info, Node: Duration-arithmetics, Next: Duration-processes, Prev: Duration class-instance creation (non ANSI), Up: Duration 1.69.3 Duration: arithmetics ---------------------------- * factor Answer a Duration that is `factor' times longer than the receiver + aDuration Answer a Duration that is the sum of the receiver and aDuration's lengths. - aDuration Answer a Duration that is the difference of the receiver and aDuration's lengths. / factorOrDuration If the parameter is a Duration, answer the ratio between the receiver and factorOrDuration. Else divide the receiver by factorOrDuration (a Number) and answer a new Duration that is correspondingly shorter. abs Answer a Duration that is as long as the receiver, but always in the future. days Answer the number of days in the receiver isZero Answer whether the receiver correspond to a duration of zero seconds. negated Answer a Duration that is as long as the receiver, but with past and future exchanged. negative Answer whether the receiver is in the past. positive Answer whether the receiver is a zero-second duration or is in the future. printOn: aStream Print a represention of the receiver on aStream.  File: gst-base.info, Node: Duration-processes, Next: Duration-storing, Prev: Duration-arithmetics, Up: Duration 1.69.4 Duration: processes -------------------------- wait Answer a Delay waiting for the amount of time represented by the receiver and start waiting on it.  File: gst-base.info, Node: Duration-storing, Prev: Duration-processes, Up: Duration 1.69.5 Duration: storing ------------------------ storeOn: aStream Store on aStream Smalltalk code compiling to the receiver  File: gst-base.info, Node: DynamicVariable, Next: Error, Prev: Duration, Up: Base classes 1.70 DynamicVariable ==================== Defined in namespace Smalltalk Superclass: Object Category: Language-Utilities I am a variable that is visible only in the stackframes outgoing from this one. Do not use DynamicVariable directly, instead create a subclass for each variable you want to use. You can override the #value class method, and call #valueIfAbsent: from there if you want the default value to be something else than nil. * Menu: * DynamicVariable class-evaluating:: (class)  File: gst-base.info, Node: DynamicVariable class-evaluating, Up: DynamicVariable 1.70.1 DynamicVariable class: evaluating ---------------------------------------- use: anObject during: aBlock Not commented. value Not commented. valueIfAbsent: aBlock Not commented.  File: gst-base.info, Node: Error, Next: Exception, Prev: DynamicVariable, Up: Base classes 1.71 Error ========== Defined in namespace Smalltalk Superclass: Exception Category: Language-Exceptions Error represents a fatal error. Instances of it are not resumable. * Menu: * Error-exception description:: (instance)  File: gst-base.info, Node: Error-exception description, Up: Error 1.71.1 Error: exception description ----------------------------------- description Answer a textual description of the exception. isResumable Answer false. Error exceptions are by default unresumable; subclasses can override this method if desired.  File: gst-base.info, Node: Exception, Next: ExceptionSet, Prev: Error, Up: Base classes 1.72 Exception ============== Defined in namespace Smalltalk Superclass: Object Category: Language-Exceptions My instances describe an exception that has happened, and are passed to exception handlers. Classes describe the kind of exception. Apart from containing information on the generated exception, my instances contain methods that allow you to resume execution, leave the #on:do:... block, and pass the exception to an handler with a lower priority. * Menu: * Exception class-comparison:: (class) * Exception class-creating ExceptionCollections:: (class) * Exception class-instance creation:: (class) * Exception class-interoperability with TrappableEvents:: (class) * Exception-accessing:: (instance) * Exception-built ins:: (instance) * Exception-comparison:: (instance) * Exception-copying:: (instance) * Exception-exception description:: (instance) * Exception-exception handling:: (instance) * Exception-exception signaling:: (instance) * Exception-still unclassified:: (instance)  File: gst-base.info, Node: Exception class-comparison, Next: Exception class-creating ExceptionCollections, Up: Exception 1.72.1 Exception class: comparison ---------------------------------- goodness: anExceptionClass Answer how good the receiver is at handling the given exception. A negative value indicates that the receiver is not able to handle the exception. handles: anException Answer whether the receiver handles `anException'.  File: gst-base.info, Node: Exception class-creating ExceptionCollections, Next: Exception class-instance creation, Prev: Exception class-comparison, Up: Exception 1.72.2 Exception class: creating ExceptionCollections ----------------------------------------------------- , aTrappableEvent Answer an ExceptionCollection containing all the exceptions in the receiver and all the exceptions in aTrappableEvent  File: gst-base.info, Node: Exception class-instance creation, Next: Exception class-interoperability with TrappableEvents, Prev: Exception class-creating ExceptionCollections, Up: Exception 1.72.3 Exception class: instance creation ----------------------------------------- new Create an instance of the receiver, which you will be able to signal later. signal Create an instance of the receiver, give it default attributes, and signal it immediately. signal: messageText Create an instance of the receiver, set its message text, and signal it immediately.  File: gst-base.info, Node: Exception class-interoperability with TrappableEvents, Next: Exception-accessing, Prev: Exception class-instance creation, Up: Exception 1.72.4 Exception class: interoperability with TrappableEvents ------------------------------------------------------------- allExceptionsDo: aBlock Private - Pass ourselves to aBlock  File: gst-base.info, Node: Exception-accessing, Next: Exception-built ins, Prev: Exception class-interoperability with TrappableEvents, Up: Exception 1.72.5 Exception: accessing --------------------------- basicMessageText Answer an exception's message text. Do not override this method. messageText Answer an exception's message text. messageText: aString Set an exception's message text. tag Answer an exception's tag value. If not specified, it is the same as the message text. tag: anObject Set an exception's tag value. If nil, the tag value will be the same as the message text.  File: gst-base.info, Node: Exception-built ins, Next: Exception-comparison, Prev: Exception-accessing, Up: Exception 1.72.6 Exception: built ins --------------------------- resignalAsUnhandled: message This might start the debugger... Note that we use #basicPrint 'cause #printOn: might invoke an error.  File: gst-base.info, Node: Exception-comparison, Next: Exception-copying, Prev: Exception-built ins, Up: Exception 1.72.7 Exception: comparison ---------------------------- = anObject Answer whether the receiver is equal to anObject. This is true if either the receiver or its class are the same object as anObject.  File: gst-base.info, Node: Exception-copying, Next: Exception-exception description, Prev: Exception-comparison, Up: Exception 1.72.8 Exception: copying ------------------------- postCopy Modify the receiver so that it does not refer to any instantiated exception handler.  File: gst-base.info, Node: Exception-exception description, Next: Exception-exception handling, Prev: Exception-copying, Up: Exception 1.72.9 Exception: exception description --------------------------------------- defaultAction Execute the default action that is attached to the receiver. description Answer a textual description of the exception. isResumable Answer true. Exceptions are by default resumable.  File: gst-base.info, Node: Exception-exception handling, Next: Exception-exception signaling, Prev: Exception-exception description, Up: Exception 1.72.10 Exception: exception handling ------------------------------------- context Return the execution context for the #on:do: snippet isNested Answer whether the current exception handler is within the scope of another handler for the same exception. outer Raise the exception that instantiated the receiver, passing the same parameters. If the receiver is resumable and the evaluated exception action resumes then the result returned from #outer will be the resumption value of the evaluated exception action. If the receiver is not resumable or if the exception action does not resume then this message will not return, and #outer will be equivalent to #pass. pass Yield control to the enclosing exception action for the receiver. Similar to #outer, but control does not return to the currently active exception handler. resignalAs: replacementException Reinstate all handlers and execute the handler for `replacementException'; control does not return to the currently active exception handler. The new Signal object that is created has the same contents as the receiver (this might or not be correct - if it isn't you can use an idiom such as `sig retryUsing: [ replacementException signal ]) resume If the exception is resumable, resume the execution of the block that raised the exception; the method that was used to signal the exception will answer the receiver. Use this method IF AND ONLY IF you know who caused the exception and if it is possible to resume it in that particular case resume: anObject If the exception is resumable, resume the execution of the block that raised the exception; the method that was used to signal the exception will answer anObject. Use this method IF AND ONLY IF you know who caused the exception and if it is possible to resume it in that particular case retry Re-execute the receiver of the #on:do: message. All handlers are reinstated: watch out, this can easily cause an infinite loop. retryUsing: aBlock Execute aBlock reinstating all handlers, and return its result from the #signal method. return Exit the #on:do: snippet, answering nil to its caller. return: anObject Exit the #on:do: snippet, answering anObject to its caller. smalltalk-3.2.5/doc/stamp-vti0000644000175000017500000000013712130455672013050 00000000000000@set UPDATED 23 March 2013 @set UPDATED-MONTH March 2013 @set EDITION 3.2.5 @set VERSION 3.2.5 smalltalk-3.2.5/doc/gst-base.info-40000644000175000017500000167642112130456007013735 00000000000000This is gst-base.info, produced by makeinfo version 4.13 from /home/ich/source/smalltalk/release/smalltalk/doc/gst-base-fixed.texi. INFO-DIR-SECTION Software development START-INFO-DIR-ENTRY * Smalltalk base classes: (gst-base). The GNU Smalltalk base classes. END-INFO-DIR-ENTRY Permission is granted to copy, distribute and/or modify this document under the terms of the GNU Free Documentation License, Version 1.2 or any later version published by the Free Software Foundation; with no Invariant Sections, with no Front-Cover Texts, and with no Back-Cover Texts. A copy of the license is included in the section entitled "GNU Free Documentation License".  File: gst-base.info, Node: Method index, Next: Cross-reference, Prev: Class index, Up: Top Method index ************ [index] * Menu: * %: CharacterArray-string processing. (line 6) * & <1>: True-basic. (line 6) * & <2>: Set-arithmetic. (line 6) * & <3>: False-basic. (line 6) * &: Boolean-basic. (line 6) * * <1>: UnicodeCharacter-coercion methods. (line 6) * * <2>: SmallInteger-built ins. (line 6) * * <3>: ScaledDecimal-arithmetic. (line 6) * * <4>: Point-arithmetic. (line 6) * * <5>: Number-arithmetic. (line 6) * * <6>: LargeZeroInteger-arithmetic. (line 6) * * <7>: LargeInteger-arithmetic. (line 6) * * <8>: Fraction-arithmetic. (line 6) * * <9>: FloatQ-built ins. (line 6) * * <10>: FloatE-built ins. (line 6) * * <11>: FloatD-built ins. (line 6) * * <12>: Duration-arithmetics. (line 6) * *: Character-coercion methods. (line 6) * + <1>: SmallInteger-built ins. (line 9) * + <2>: Set-arithmetic. (line 9) * + <3>: ScaledDecimal-arithmetic. (line 9) * + <4>: Point-arithmetic. (line 9) * + <5>: Number-arithmetic. (line 9) * + <6>: LargeZeroInteger-arithmetic. (line 9) * + <7>: LargePositiveInteger-arithmetic. (line 6) * + <8>: LargeNegativeInteger-reverting to LargePositiveInteger. (line 6) * + <9>: LargeInteger-arithmetic. (line 9) * + <10>: Fraction-arithmetic. (line 9) * + <11>: FloatQ-built ins. (line 9) * + <12>: FloatE-built ins. (line 9) * + <13>: FloatD-built ins. (line 9) * + <14>: Duration-arithmetics. (line 9) * + <15>: DateTime-basic. (line 6) * + <16>: Date-still unclassified. (line 6) * +: CObject-pointer-like behavior. (line 6) * , <1>: VFS.ArchiveMember-still unclassified. (line 6) * , <2>: String-basic. (line 6) * , <3>: Stream-filtering. (line 6) * , <4>: Iterable-enumeration. (line 6) * , <5>: File-still unclassified. (line 6) * , <6>: ExceptionSet-instance creation. (line 6) * , <7>: Exception class-creating ExceptionCollections. (line 6) * , <8>: Collection-copying SequenceableCollections. (line 6) * ,: ArrayedCollection-basic. (line 6) * - <1>: SmallInteger-built ins. (line 12) * - <2>: Set-arithmetic. (line 12) * - <3>: ScaledDecimal-arithmetic. (line 12) * - <4>: Point-arithmetic. (line 12) * - <5>: Number-arithmetic. (line 12) * - <6>: LargeZeroInteger-arithmetic. (line 12) * - <7>: LargePositiveInteger-arithmetic. (line 9) * - <8>: LargeNegativeInteger-reverting to LargePositiveInteger. (line 9) * - <9>: LargeInteger-arithmetic. (line 12) * - <10>: Fraction-arithmetic. (line 12) * - <11>: FloatQ-built ins. (line 12) * - <12>: FloatE-built ins. (line 12) * - <13>: FloatD-built ins. (line 12) * - <14>: Duration-arithmetics. (line 13) * - <15>: DateTime-basic. (line 9) * - <16>: Date-basic. (line 6) * -: CObject-pointer-like behavior. (line 11) * ->: Object-syntax shortcuts. (line 6) * / <1>: String-filesystem. (line 6) * / <2>: SmallInteger-built ins. (line 15) * / <3>: ScaledDecimal-arithmetic. (line 15) * / <4>: Point-arithmetic. (line 15) * / <5>: Number-arithmetic. (line 15) * / <6>: LargeZeroInteger-arithmetic. (line 15) * / <7>: LargeInteger-arithmetic. (line 15) * / <8>: Fraction-arithmetic. (line 15) * / <9>: FloatQ-built ins. (line 15) * / <10>: FloatE-built ins. (line 15) * / <11>: FloatD-built ins. (line 15) * / <12>: FilePath-still unclassified. (line 6) * /: Duration-arithmetics. (line 17) * // <1>: SmallInteger-built ins. (line 18) * // <2>: ScaledDecimal-arithmetic. (line 18) * // <3>: Point-arithmetic. (line 19) * // <4>: Number-arithmetic. (line 20) * // <5>: LargeZeroInteger-arithmetic. (line 19) * // <6>: LargeInteger-arithmetic. (line 19) * //: Fraction-arithmetic. (line 18) * < <1>: Time-comparing. (line 6) * < <2>: SmallInteger-built ins. (line 22) * < <3>: Set-comparing. (line 6) * < <4>: ScaledDecimal-comparing. (line 6) * < <5>: Point-comparing. (line 6) * < <6>: Magnitude-basic. (line 6) * < <7>: LookupKey-testing. (line 6) * < <8>: LargeInteger-testing. (line 6) * < <9>: Fraction-comparing. (line 6) * < <10>: FloatQ-built ins. (line 18) * < <11>: FloatE-built ins. (line 18) * < <12>: FloatD-built ins. (line 18) * < <13>: DateTime-testing. (line 6) * < <14>: Date-testing. (line 6) * < <15>: CharacterArray-comparing. (line 6) * <: Character-comparing. (line 6) * <<: Stream-printing. (line 6) * <= <1>: SmallInteger-built ins. (line 25) * <= <2>: Set-comparing. (line 9) * <= <3>: ScaledDecimal-comparing. (line 9) * <= <4>: Point-comparing. (line 9) * <= <5>: Magnitude-basic. (line 9) * <= <6>: LargeInteger-testing. (line 9) * <= <7>: Fraction-comparing. (line 9) * <= <8>: FloatQ-built ins. (line 21) * <= <9>: FloatE-built ins. (line 21) * <= <10>: FloatD-built ins. (line 21) * <= <11>: CharacterArray-comparing. (line 10) * <=: Character-comparing. (line 10) * = <1>: VFS.FileWrapper-basic. (line 6) * = <2>: VFS.ArchiveMember-basic. (line 6) * = <3>: Time-comparing. (line 9) * = <4>: Symbol-built ins. (line 6) * = <5>: String-basic. (line 11) * = <6>: SmallInteger-built ins. (line 28) * = <7>: SequenceableCollection-testing. (line 6) * = <8>: ScaledDecimal-comparing. (line 12) * = <9>: RunArray-testing. (line 6) * = <10>: Rectangle-testing. (line 6) * = <11>: Point-comparing. (line 13) * = <12>: Object-built ins. (line 6) * = <13>: NetClients.URL-comparing. (line 6) * = <14>: MethodInfo-equality. (line 6) * = <15>: Magnitude-basic. (line 12) * = <16>: LookupKey-testing. (line 9) * = <17>: LargeInteger-testing. (line 12) * = <18>: LargeArrayedCollection-basic. (line 6) * = <19>: Interval-testing. (line 6) * = <20>: HashedCollection-testing collections. (line 6) * = <21>: Fraction-comparing. (line 12) * = <22>: FloatQ-built ins. (line 24) * = <23>: FloatE-built ins. (line 24) * = <24>: FloatD-built ins. (line 24) * = <25>: FileSegment-equality. (line 6) * = <26>: File-basic. (line 6) * = <27>: Exception-comparison. (line 6) * = <28>: Dictionary-testing. (line 6) * = <29>: Delay-comparing. (line 6) * = <30>: DateTime-testing. (line 9) * = <31>: Date-testing. (line 9) * = <32>: CType-basic. (line 6) * = <33>: CPtrCType-basic. (line 6) * = <34>: CompiledMethod-basic. (line 6) * = <35>: CompiledCode-basic. (line 6) * = <36>: CompiledBlock-basic. (line 6) * = <37>: CObject-basic. (line 6) * = <38>: Class-testing. (line 6) * = <39>: CharacterArray-comparing. (line 16) * = <40>: Character-built ins. (line 6) * = <41>: CArrayCType-basic. (line 6) * = <42>: ByteArray-basic. (line 6) * = <43>: BindingDictionary-basic & copying. (line 6) * = <44>: Bag-testing collections. (line 6) * =: Association-testing. (line 6) * == <1>: SmallInteger-built ins. (line 31) * ==: Object-built ins. (line 11) * =~: String-regex. (line 6) * > <1>: SmallInteger-built ins. (line 34) * > <2>: Set-comparing. (line 12) * > <3>: ScaledDecimal-comparing. (line 15) * > <4>: Point-comparing. (line 16) * > <5>: Magnitude-basic. (line 15) * > <6>: LargeInteger-testing. (line 15) * > <7>: Fraction-comparing. (line 15) * > <8>: FloatQ-built ins. (line 27) * > <9>: FloatE-built ins. (line 27) * > <10>: FloatD-built ins. (line 27) * > <11>: CharacterArray-comparing. (line 19) * >: Character-comparing. (line 14) * >= <1>: SmallInteger-built ins. (line 37) * >= <2>: Set-comparing. (line 15) * >= <3>: ScaledDecimal-comparing. (line 18) * >= <4>: Point-comparing. (line 19) * >= <5>: Magnitude-basic. (line 18) * >= <6>: LargeInteger-testing. (line 18) * >= <7>: Fraction-comparing. (line 18) * >= <8>: FloatQ-built ins. (line 30) * >= <9>: FloatE-built ins. (line 30) * >= <10>: FloatD-built ins. (line 30) * >= <11>: CharacterArray-comparing. (line 23) * >=: Character-comparing. (line 18) * >>: Behavior-accessing the method dictionary. (line 6) * @: Number-point creation. (line 6) * \\ <1>: SmallInteger-built ins. (line 40) * \\ <2>: ScaledDecimal-arithmetic. (line 22) * \\ <3>: Number-arithmetic. (line 25) * \\ <4>: LargeZeroInteger-arithmetic. (line 23) * \\ <5>: LargeInteger-arithmetic. (line 23) * \\: Fraction-arithmetic. (line 22) * abbreviationOfDay_: Date class-basic. (line 6) * abort: ObjectMemory class-builtins. (line 6) * abs <1>: Point-arithmetic. (line 23) * abs <2>: Number-misc math. (line 6) * abs <3>: LargePositiveInteger-numeric testing. (line 6) * abs <4>: LargeNegativeInteger-numeric testing. (line 6) * abs: Duration-arithmetics. (line 23) * acceptUsageForClass_ <1>: SingletonProxy class-accessing. (line 6) * acceptUsageForClass_ <2>: DumperProxy class-accessing. (line 6) * acceptUsageForClass_: AlternativeObjectProxy class-instance creation. (line 6) * accesses_ <1>: CompiledMethod-testing. (line 6) * accesses_: CompiledCode-testing accesses. (line 6) * action_: Permission-accessing. (line 6) * actions: Permission-accessing. (line 9) * actions_: Permission-accessing. (line 12) * activeDebugger: ProcessorScheduler-basic. (line 6) * activeDelay: Delay class-timer process. (line 6) * activePriority: ProcessorScheduler-basic. (line 9) * activeProcess: ProcessorScheduler-basic. (line 12) * add_ <1>: WeakSet-accessing. (line 6) * add_ <2>: WeakKeyDictionary-accessing. (line 6) * add_ <3>: ProcessEnvironment-accessing. (line 6) * add_ <4>: OrderedCollection-adding. (line 6) * add_ <5>: MappedCollection-basic. (line 6) * add_ <6>: LookupTable-accessing. (line 6) * add_ <7>: LinkedList-adding. (line 6) * add_ <8>: HashedCollection-accessing. (line 6) * add_ <9>: Dictionary-accessing. (line 6) * add_ <10>: Collection-adding. (line 6) * add_ <11>: Bag-adding. (line 6) * add_: ArrayedCollection-basic. (line 11) * add_after_: OrderedCollection-adding. (line 9) * add_afterIndex_ <1>: SortedCollection-disabled. (line 6) * add_afterIndex_ <2>: RunArray-adding. (line 6) * add_afterIndex_: OrderedCollection-adding. (line 13) * add_before_: OrderedCollection-adding. (line 17) * add_beforeIndex_: OrderedCollection-adding. (line 21) * add_withOccurrences_: Bag-adding. (line 10) * addAll_ <1>: OrderedCollection-adding. (line 25) * addAll_ <2>: Dictionary-accessing. (line 9) * addAll_: Collection-adding. (line 9) * addAll_after_: OrderedCollection-adding. (line 28) * addAll_afterIndex_ <1>: SortedCollection-disabled. (line 9) * addAll_afterIndex_ <2>: RunArray-adding. (line 9) * addAll_afterIndex_: OrderedCollection-adding. (line 32) * addAll_before_: OrderedCollection-adding. (line 36) * addAll_beforeIndex_: OrderedCollection-adding. (line 40) * addAllFirst_ <1>: SortedCollection-disabled. (line 12) * addAllFirst_ <2>: RunArray-adding. (line 14) * addAllFirst_: OrderedCollection-adding. (line 44) * addAllLast_ <1>: SortedCollection-disabled. (line 15) * addAllLast_ <2>: RunArray-adding. (line 19) * addAllLast_: OrderedCollection-adding. (line 48) * addBuiltFile_: Package-accessing. (line 6) * addCallout_: Package-accessing. (line 9) * addClassVarName_ <1>: Metaclass-delegation. (line 6) * addClassVarName_: Class-accessing instances and variables. (line 6) * addClassVarName_value_: Class-accessing instances and variables. (line 10) * addDays_: Date-basic. (line 10) * addDependent_ <1>: UndefinedObject-dependents access. (line 6) * addDependent_: Object-dependents access. (line 6) * addFeature_ <1>: SystemDictionary-special accessing. (line 6) * addFeature_: Package-accessing. (line 12) * addFile_: Package-accessing. (line 15) * addFileIn_: Package-accessing. (line 18) * addFirst_ <1>: SortedCollection-disabled. (line 18) * addFirst_ <2>: RunArray-adding. (line 24) * addFirst_ <3>: OrderedCollection-adding. (line 52) * addFirst_: LinkedList-adding. (line 9) * addInstVarName_: Behavior-instance variables. (line 6) * addLast_ <1>: SortedCollection-disabled. (line 21) * addLast_ <2>: RunArray-adding. (line 28) * addLast_ <3>: OrderedCollection-adding. (line 56) * addLast_: LinkedList-adding. (line 12) * addLibrary_ <1>: Package-accessing. (line 21) * addLibrary_: DLD class-dynamic linking. (line 6) * addLibraryHandle_: DLD class-dynamic linking. (line 9) * addModule_ <1>: Package-accessing. (line 24) * addModule_: DLD class-dynamic linking. (line 13) * addPermission_: SecurityPolicy-modifying. (line 6) * addPrerequisite_: Package-accessing. (line 27) * address: CObject-accessing. (line 6) * address_ <1>: CType-C instance creation. (line 6) * address_ <2>: CObject-accessing. (line 12) * address_: CObject class-instance creation. (line 6) * addressAt_: CObject-pointer-like behavior. (line 19) * addressOf_ <1>: ObjectMemory class-builtins. (line 9) * addressOf_: CFunctionDescriptor class-testing. (line 6) * addressOfOOP_: ObjectMemory class-builtins. (line 16) * addSeconds_: Time-arithmetic. (line 6) * addSelector_withMethod_: Behavior-method dictionary. (line 6) * addSharedPool_ <1>: Metaclass-delegation. (line 10) * addSharedPool_ <2>: ClassDescription-parsing class declarations. (line 6) * addSharedPool_ <3>: Class-accessing instances and variables. (line 14) * addSharedPool_: AbstractNamespace-compiling. (line 6) * addSubclass_: Behavior-creating a class hierarchy. (line 6) * addSubspace_: AbstractNamespace-namespace hierarchy. (line 6) * addSunitScript_: Package-accessing. (line 30) * addTime_: Time-arithmetic. (line 9) * addToBeFinalized <1>: Object-finalization. (line 6) * addToBeFinalized: FileDescriptor-initialize-release. (line 6) * after_: SequenceableCollection-basic. (line 6) * alignof <1>: CUShort-accessing. (line 6) * alignof <2>: CUShort class-accessing. (line 6) * alignof <3>: CULongLong-accessing. (line 6) * alignof <4>: CULongLong class-accessing. (line 6) * alignof <5>: CULong-accessing. (line 6) * alignof <6>: CULong class-accessing. (line 6) * alignof <7>: CUInt-accessing. (line 6) * alignof <8>: CUInt class-accessing. (line 6) * alignof <9>: CUChar-accessing. (line 6) * alignof <10>: CUChar class-getting info. (line 6) * alignof <11>: CType-accessing. (line 6) * alignof <12>: CSmalltalk-accessing. (line 6) * alignof <13>: CSmalltalk class-accessing. (line 6) * alignof <14>: CShort-accessing. (line 6) * alignof <15>: CShort class-accessing. (line 6) * alignof <16>: CPtr-accessing. (line 6) * alignof <17>: CLongLong-accessing. (line 6) * alignof <18>: CLongLong class-accessing. (line 6) * alignof <19>: CLongDouble-accessing. (line 6) * alignof <20>: CLongDouble class-accessing. (line 6) * alignof <21>: CLong-accessing. (line 6) * alignof <22>: CLong class-accessing. (line 6) * alignof <23>: CInt-accessing. (line 6) * alignof <24>: CInt class-accessing. (line 6) * alignof <25>: CFloat-accessing. (line 6) * alignof <26>: CFloat class-accessing. (line 6) * alignof <27>: CDouble-accessing. (line 6) * alignof <28>: CDouble class-accessing. (line 6) * alignof <29>: CCompound class-subclass creation. (line 6) * alignof <30>: CChar-accessing. (line 6) * alignof <31>: CChar class-accessing. (line 6) * alignof <32>: CArrayCType-accessing. (line 6) * alignof <33>: CArray-accessing. (line 6) * alignof: CAggregate class-accessing. (line 6) * alignTo_: Integer-extension. (line 6) * aliveObjectsDo_: WeakArray-accessing. (line 6) * all: FilePath-decoration. (line 6) * allAssociations: AbstractNamespace-accessing. (line 6) * allBehaviorsDo_: AbstractNamespace-accessing. (line 11) * allBlocksDo_: CompiledMethod-accessing. (line 6) * allButFirst: SequenceableCollection-basic. (line 10) * allButFirst_: SequenceableCollection-basic. (line 13) * allButLast: SequenceableCollection-basic. (line 16) * allButLast_: SequenceableCollection-basic. (line 19) * allClassesDo_: AbstractNamespace-accessing. (line 17) * allClassObjectsDo_: AbstractNamespace-accessing. (line 14) * allClassVarNames <1>: Metaclass-delegation. (line 14) * allClassVarNames <2>: Class-accessing instances and variables. (line 18) * allClassVarNames: Behavior-accessing instances and variables. (line 6) * allExceptionsDo_ <1>: ExceptionSet-enumerating. (line 6) * allExceptionsDo_: Exception class-interoperability with TrappableEvents. (line 6) * allFilesMatching_do_ <1>: FilePath-enumerating. (line 6) * allFilesMatching_do_: Directory class-file operations. (line 6) * allInstances: Behavior-accessing instances and variables. (line 13) * allInstancesDo_: Behavior-enumerating. (line 6) * allInstVarNames: Behavior-accessing instances and variables. (line 9) * allLiterals: CompiledMethod-accessing. (line 9) * allLiteralsDo_: CompiledCode-literals - iteration. (line 9) * allLiteralSymbolsDo_: CompiledCode-literals - iteration. (line 6) * allMask_: Integer-bit operators. (line 6) * allMetaclassesDo_: AbstractNamespace-accessing. (line 20) * alloc_: CObject class-instance creation. (line 9) * alloc_type_: CObject class-primitive allocation. (line 6) * allOccurrencesOfRegex_: String-regex. (line 10) * allOccurrencesOfRegex_do_: String-regex. (line 14) * allOccurrencesOfRegex_from_to_: String-regex. (line 18) * allOccurrencesOfRegex_from_to_do_: String-regex. (line 23) * allocFailures: ObjectMemory-accessing. (line 6) * allocMatches: ObjectMemory-accessing. (line 11) * allocProbes: ObjectMemory-accessing. (line 15) * allocSplits: ObjectMemory-accessing. (line 19) * allow: Permission-accessing. (line 15) * allowing: Permission-accessing. (line 18) * allowing_target_action_: Permission class-testing. (line 6) * allowing_target_actions_: Permission class-testing. (line 9) * allOwners: Object-built ins. (line 15) * allSatisfy_: Iterable-enumeration. (line 10) * allSelectors: Behavior-accessing the method dictionary. (line 10) * allSharedPoolDictionaries: Behavior-accessing instances and variables. (line 16) * allSharedPoolDictionariesDo_ <1>: Metaclass-delegation. (line 18) * allSharedPoolDictionariesDo_ <2>: Class-still unclassified. (line 6) * allSharedPoolDictionariesDo_: Behavior-still unclassified. (line 6) * allSharedPools <1>: Metaclass-delegation. (line 22) * allSharedPools: Behavior-accessing instances and variables. (line 20) * allSubassociationsDo_: AbstractNamespace-namespace hierarchy. (line 10) * allSubclasses <1>: UndefinedObject-class polymorphism. (line 6) * allSubclasses: Behavior-accessing class hierarchy. (line 6) * allSubclassesDo_: Behavior-enumerating. (line 9) * allSubinstancesDo_: Behavior-enumerating. (line 12) * allSubspaces: AbstractNamespace-namespace hierarchy. (line 14) * allSubspacesDo_: AbstractNamespace-namespace hierarchy. (line 17) * allSuperclasses: Behavior-accessing class hierarchy. (line 9) * allSuperclassesDo_: Behavior-enumerating. (line 16) * allSuperspaces: Dictionary-namespace protocol. (line 6) * allSuperspacesDo_ <1>: Dictionary-namespace protocol. (line 9) * allSuperspacesDo_: AbstractNamespace-namespace hierarchy. (line 20) * amountToTranslateWithin_: Rectangle-rectangle functions. (line 6) * and_ <1>: True-basic. (line 10) * and_ <2>: False-basic. (line 9) * and_: Boolean-basic. (line 10) * anyMask_: Integer-bit operators. (line 9) * anyOne <1>: SequenceableCollection-enumerating. (line 6) * anyOne: Collection-enumeration. (line 6) * anySatisfy_: Iterable-enumeration. (line 14) * append: FileDescriptor class-instance creation. (line 6) * append_to_ <1>: FilePath class-file name management. (line 6) * append_to_: Directory class-file name management. (line 6) * arcCos <1>: Number-misc math. (line 9) * arcCos: Float-built ins. (line 6) * arcCosh: Number-misc math. (line 12) * archive: VFS.ArchiveMember-accessing. (line 6) * archive_: VFS.ArchiveMember-initializing. (line 6) * arcSin <1>: Number-misc math. (line 15) * arcSin: Float-built ins. (line 9) * arcSinh: Number-misc math. (line 18) * arcTan <1>: Point-point functions. (line 6) * arcTan <2>: Number-misc math. (line 21) * arcTan: Float-built ins. (line 12) * arcTan_: Number-misc math. (line 24) * arcTanh: Number-misc math. (line 28) * area: Rectangle-rectangle functions. (line 10) * areasOutside_: Rectangle-rectangle functions. (line 15) * argument: Message-accessing. (line 6) * argumentCount: BlockClosure-accessing. (line 6) * arguments <1>: SystemDictionary-miscellaneous. (line 6) * arguments: Message-accessing. (line 9) * arguments_: Message-accessing. (line 12) * arguments_do_: SystemDictionary-command-line. (line 6) * arguments_do_ifError_: SystemDictionary-command-line. (line 20) * arithmeticError_: Number-error raising. (line 6) * arrayType_: CType-accessing. (line 9) * article <1>: Class-printing. (line 6) * article: Behavior-support for lightweight classes. (line 6) * asAbsolute: Delay-accessing. (line 6) * asArray <1>: WeakArray-conversion. (line 6) * asArray <2>: RegexResults-accessing. (line 6) * asArray: Collection-converting. (line 6) * asBag: Collection-converting. (line 9) * asByteArray <1>: String-converting. (line 6) * asByteArray <2>: Collection-converting. (line 12) * asByteArray: CharacterArray-converting. (line 6) * asByteArray_: CChar-conversion. (line 6) * asCBooleanValue <1>: True-C hacks. (line 6) * asCBooleanValue <2>: False-C hacks. (line 6) * asCBooleanValue: Boolean-C hacks. (line 6) * asCData <1>: String-CObject. (line 6) * asCData: ByteArray-CObject. (line 6) * asCData_ <1>: String-built ins. (line 6) * asCData_: ByteArray-built ins. (line 6) * asCharacter <1>: Integer-converting. (line 6) * asCharacter: Character-converting. (line 6) * asciiValue: Character-built ins. (line 13) * asciiValue_: Character class-built ins. (line 6) * asClass <1>: Metaclass-testing functionality. (line 6) * asClass <2>: ClassDescription-conversion. (line 6) * asClass <3>: Class-testing functionality. (line 6) * asClass: Behavior-support for lightweight classes. (line 9) * asClassPoolKey: CharacterArray-converting. (line 9) * asCNumber <1>: SmallInteger-coercion. (line 6) * asCNumber <2>: ScaledDecimal-coercion. (line 6) * asCNumber <3>: Number-coercion. (line 6) * asCNumber <4>: LargeInteger-coercion. (line 6) * asCNumber <5>: Fraction-coercion. (line 6) * asCNumber: Float-coercion. (line 6) * asDate: DateTime-splitting in dates & times. (line 6) * asExactFraction <1>: Number-converting. (line 6) * asExactFraction <2>: Fraction-converting. (line 6) * asExactFraction: Float-coercing. (line 6) * asFile <1>: String-filesystem. (line 10) * asFile: FilePath-converting. (line 6) * asFloat <1>: Number-converting. (line 10) * asFloat: Float-transcendental operations. (line 6) * asFloatD <1>: SmallInteger-built ins. (line 44) * asFloatD <2>: ScaledDecimal-coercion. (line 10) * asFloatD <3>: Number-converting. (line 13) * asFloatD <4>: LargePositiveInteger-converting. (line 6) * asFloatD <5>: LargeNegativeInteger-converting. (line 6) * asFloatD <6>: Fraction-converting. (line 9) * asFloatD <7>: FloatQ-built ins. (line 33) * asFloatD <8>: FloatE-built ins. (line 33) * asFloatD: FloatD-coercing. (line 6) * asFloatE <1>: SmallInteger-built ins. (line 47) * asFloatE <2>: ScaledDecimal-coercion. (line 13) * asFloatE <3>: Number-converting. (line 17) * asFloatE <4>: LargePositiveInteger-converting. (line 9) * asFloatE <5>: LargeNegativeInteger-converting. (line 9) * asFloatE <6>: Fraction-converting. (line 12) * asFloatE <7>: FloatQ-built ins. (line 36) * asFloatE <8>: FloatE-coercing. (line 6) * asFloatE: FloatD-built ins. (line 33) * asFloatQ <1>: SmallInteger-built ins. (line 50) * asFloatQ <2>: ScaledDecimal-coercion. (line 16) * asFloatQ <3>: Number-converting. (line 21) * asFloatQ <4>: LargePositiveInteger-converting. (line 12) * asFloatQ <5>: LargeNegativeInteger-converting. (line 12) * asFloatQ <6>: Fraction-converting. (line 15) * asFloatQ <7>: FloatQ-coercing. (line 6) * asFloatQ <8>: FloatE-built ins. (line 36) * asFloatQ: FloatD-built ins. (line 36) * asFraction <1>: ScaledDecimal-coercion. (line 19) * asFraction <2>: Number-converting. (line 25) * asFraction <3>: Integer-converting. (line 9) * asFraction <4>: Fraction-converting. (line 18) * asFraction: Float-coercing. (line 10) * asGlobalKey: CharacterArray-converting. (line 12) * asInteger <1>: Number-truncation and round off. (line 6) * asInteger <2>: CharacterArray-converting. (line 15) * asInteger: Character-built ins. (line 9) * asLocal: DateTime-time zones. (line 6) * asLowercase <1>: CharacterArray-converting. (line 19) * asLowercase: Character-coercion methods. (line 9) * asMetaclass: ClassDescription-conversion. (line 10) * asMilliseconds: Time-accessing (non ANSI & for Durations). (line 6) * asNanoseconds: Time-accessing (non ANSI & for Durations). (line 9) * asNumber <1>: Number-converting. (line 29) * asNumber: CharacterArray-converting. (line 22) * asObject <1>: SmallInteger-built ins. (line 53) * asObject: LargeInteger-disabled. (line 6) * asObjectNoFail <1>: SmallInteger-built ins. (line 57) * asObjectNoFail: LargeInteger-disabled. (line 10) * asOop: Object-built ins. (line 18) * asOrderedCollection: Collection-converting. (line 15) * asPoint <1>: Point-converting. (line 6) * asPoint: Number-point creation. (line 9) * asPoolKey: CharacterArray-converting. (line 26) * asRectangle <1>: Point-converting. (line 9) * asRectangle: Number-converting. (line 32) * asRegex <1>: String-regex. (line 28) * asRegex: Regex-conversion. (line 6) * asRunArray: Collection-converting. (line 19) * asScaledDecimal_ <1>: Number-converting. (line 35) * asScaledDecimal_: Integer-converting. (line 12) * asScaledDecimal_radix_scale_: Number-converting. (line 38) * asSeconds <1>: Time-accessing (non ANSI & for Durations). (line 12) * asSeconds <2>: DateTime-computations. (line 6) * asSeconds: Date-date computations. (line 6) * asSet <1>: Collection-converting. (line 24) * asSet: Bag-enumerating the elements of a collection. (line 6) * assigns_ <1>: CompiledMethod-testing. (line 10) * assigns_: CompiledCode-testing accesses. (line 10) * associationAt_ <1>: ProcessEnvironment-accessing. (line 9) * associationAt_: Dictionary-accessing. (line 13) * associationAt_ifAbsent_ <1>: ProcessEnvironment-accessing. (line 13) * associationAt_ifAbsent_ <2>: Namespace-overrides for superspaces. (line 6) * associationAt_ifAbsent_ <3>: LookupTable-accessing. (line 9) * associationAt_ifAbsent_: Dictionary-accessing. (line 17) * associations: Dictionary-accessing. (line 21) * associationsDo_ <1>: Namespace-overrides for superspaces. (line 12) * associationsDo_ <2>: LookupTable-enumerating. (line 6) * associationsDo_: Dictionary-dictionary enumerating. (line 6) * asSortedCollection: Collection-converting. (line 28) * asSortedCollection_: Collection-converting. (line 32) * asString <1>: VFS.FileWrapper-accessing. (line 6) * asString <2>: VFS.ArchiveMember-accessing. (line 9) * asString <3>: UnicodeString-converting. (line 6) * asString <4>: Symbol-converting. (line 6) * asString <5>: String-converting. (line 9) * asString <6>: Regex-conversion. (line 9) * asString <7>: Number-converting. (line 42) * asString <8>: NetClients.URL-accessing. (line 6) * asString <9>: FileSegment-basic. (line 6) * asString <10>: FilePath-printing. (line 6) * asString <11>: File-accessing. (line 6) * asString <12>: Collection-converting. (line 36) * asString <13>: CharacterArray-converting. (line 29) * asString <14>: Character-coercion methods. (line 13) * asString <15>: CChar-conversion. (line 9) * asString: ByteArray-converting. (line 6) * asString_: CChar-conversion. (line 13) * asSymbol <1>: UnicodeString-converting. (line 12) * asSymbol <2>: Symbol-converting. (line 9) * asSymbol <3>: String-converting. (line 12) * asSymbol <4>: CharacterArray-converting. (line 32) * asSymbol: Character-coercion methods. (line 17) * asTime: DateTime-splitting in dates & times. (line 9) * asUnicodeString <1>: UnicodeString-converting. (line 15) * asUnicodeString <2>: Collection-converting. (line 39) * asUnicodeString <3>: CharacterArray-converting. (line 35) * asUnicodeString <4>: Character-coercion methods. (line 20) * asUnicodeString: ByteArray-converting. (line 10) * asUppercase <1>: CharacterArray-converting. (line 39) * asUppercase: Character-coercion methods. (line 23) * asUTC: DateTime-time zones. (line 10) * asValue: Object-conversion. (line 6) * asyncCall: CCallable-calling. (line 6) * asyncCallNoRetryFrom_: CCallable-calling. (line 14) * asyncCCall_numArgs_attributes_: CompiledMethod class-c call-outs. (line 6) * at_ <1>: WeakArray-accessing. (line 13) * at_ <2>: VFS.FileWrapper-accessing. (line 9) * at_ <3>: VFS.ArchiveMember-directory operations. (line 6) * at_ <4>: VFS.ArchiveFile-directory operations. (line 6) * at_ <5>: String-built ins. (line 11) * at_ <6>: SmallInteger-builtins. (line 6) * at_ <7>: RunArray-accessing. (line 6) * at_ <8>: RegexResults-accessing. (line 10) * at_ <9>: ProcessEnvironment-accessing. (line 17) * at_ <10>: OrderedCollection-accessing. (line 6) * at_ <11>: Object-built ins. (line 22) * at_ <12>: Memory class-accessing. (line 6) * at_ <13>: MappedCollection-basic. (line 9) * at_ <14>: LinkedList-accessing. (line 6) * at_ <15>: Link-iteration. (line 6) * at_ <16>: LargeZeroInteger-accessing. (line 6) * at_ <17>: LargeInteger-built-ins. (line 6) * at_ <18>: LargeArrayedCollection-accessing. (line 6) * at_ <19>: Interval-basic. (line 6) * at_ <20>: HashedCollection-accessing. (line 11) * at_ <21>: FilePath-accessing. (line 6) * at_ <22>: File-accessing. (line 9) * at_ <23>: Dictionary-accessing. (line 24) * at_ <24>: DateTime-splitting in dates & times. (line 13) * at_ <25>: ContextPart-accessing. (line 6) * at_: CObject-pointer-like behavior. (line 26) * at_ifAbsent_ <1>: WordArray-built ins. (line 6) * at_ifAbsent_ <2>: WeakValueLookupTable-hacks. (line 6) * at_ifAbsent_ <3>: UnicodeString-built ins. (line 6) * at_ifAbsent_ <4>: String-built ins. (line 14) * at_ifAbsent_ <5>: SequenceableCollection-basic. (line 22) * at_ifAbsent_ <6>: ProcessEnvironment-accessing. (line 21) * at_ifAbsent_ <7>: Namespace-overrides for superspaces. (line 15) * at_ifAbsent_ <8>: LookupTable-accessing. (line 13) * at_ifAbsent_ <9>: Dictionary-accessing. (line 28) * at_ifAbsent_ <10>: ByteArray-built ins. (line 10) * at_ifAbsent_: Array-built ins. (line 6) * at_ifAbsentPut_ <1>: ProcessEnvironment-accessing. (line 25) * at_ifAbsentPut_: Dictionary-accessing. (line 32) * at_ifPresent_ <1>: WeakValueLookupTable-hacks. (line 10) * at_ifPresent_ <2>: ProcessEnvironment-accessing. (line 29) * at_ifPresent_ <3>: Namespace-overrides for superspaces. (line 21) * at_ifPresent_ <4>: LookupTable-accessing. (line 17) * at_ifPresent_: Dictionary-accessing. (line 37) * at_put_ <1>: WeakKeyDictionary-accessing. (line 9) * at_put_ <2>: WeakArray-accessing. (line 17) * at_put_ <3>: String-built ins. (line 17) * at_put_ <4>: SortedCollection-disabled. (line 24) * at_put_ <5>: SmallInteger-builtins. (line 10) * at_put_ <6>: RunArray-accessing. (line 9) * at_put_ <7>: Regex-basic. (line 6) * at_put_ <8>: ProcessEnvironment-accessing. (line 33) * at_put_ <9>: OrderedCollection-accessing. (line 9) * at_put_ <10>: Object-built ins. (line 25) * at_put_ <11>: MethodDictionary-adding. (line 6) * at_put_ <12>: Memory class-accessing. (line 9) * at_put_ <13>: MappedCollection-basic. (line 12) * at_put_ <14>: LookupTable-accessing. (line 21) * at_put_ <15>: LinkedList-accessing. (line 9) * at_put_ <16>: Link-iteration. (line 10) * at_put_ <17>: LargeInteger-built-ins. (line 9) * at_put_ <18>: LargeArrayedCollection-accessing. (line 9) * at_put_ <19>: Interval-basic. (line 9) * at_put_ <20>: HashedCollection-accessing. (line 14) * at_put_ <21>: Dictionary-accessing. (line 41) * at_put_ <22>: ContextPart-accessing. (line 10) * at_put_ <23>: CompiledCode-accessing. (line 6) * at_put_ <24>: CObject-pointer-like behavior. (line 32) * at_put_: BindingDictionary-forward declarations. (line 6) * at_put_type_: CObject-C data access. (line 6) * at_type_: CObject-C data access. (line 10) * atAll_ <1>: SequenceableCollection-basic. (line 26) * atAll_ <2>: MappedCollection-basic. (line 15) * atAll_ <3>: Dictionary-accessing. (line 44) * atAll_: ArrayedCollection-basic. (line 14) * atAll_put_ <1>: WeakArray-accessing. (line 22) * atAll_put_: SequenceableCollection-basic. (line 31) * atAllPut_ <1>: WeakArray-accessing. (line 25) * atAllPut_: SequenceableCollection-basic. (line 34) * atEnd <1>: Stream-testing. (line 6) * atEnd <2>: Random-basic. (line 6) * atEnd <3>: PositionableStream-testing. (line 6) * atEnd <4>: ObjectDumper-stream interface. (line 6) * atEnd <5>: Generator-stream protocol. (line 6) * atEnd <6>: FileStream-testing. (line 6) * atEnd: FileDescriptor-testing. (line 6) * atRandom: SequenceableCollection-basic. (line 37) * attributeAt_: CompiledMethod-attributes. (line 6) * attributeAt_ifAbsent_: CompiledMethod-attributes. (line 10) * attributes: CompiledMethod-attributes. (line 14) * attributesDo_: CompiledMethod-attributes. (line 18) * backspace: Character class-constants. (line 6) * backtrace <1>: SystemDictionary-miscellaneous. (line 9) * backtrace <2>: ContextPart-printing. (line 6) * backtrace: ContextPart class-exception handling. (line 6) * backtraceOn_ <1>: ContextPart-printing. (line 10) * backtraceOn_: ContextPart class-exception handling. (line 10) * badReturnError: Object-VM callbacks. (line 6) * baseDirectories: Package-accessing. (line 33) * baseDirectories_: Package-accessing. (line 36) * basicAt_ <1>: String-built ins. (line 21) * basicAt_ <2>: SmallInteger-builtins. (line 14) * basicAt_: Object-built ins. (line 29) * basicAt_put_ <1>: String-built ins. (line 25) * basicAt_put_ <2>: SmallInteger-builtins. (line 18) * basicAt_put_: Object-built ins. (line 33) * basicAtEnd: PositionableStream-testing. (line 9) * basicBacktrace: SystemDictionary-builtins. (line 6) * basicLeftShift_: LargeInteger-primitive operations. (line 6) * basicMessageText: Exception-accessing. (line 6) * basicNew: Behavior-builtin. (line 6) * basicNew_: Behavior-builtin. (line 10) * basicNewInFixedSpace: Behavior-built ins. (line 6) * basicNewInFixedSpace_: Behavior-built ins. (line 11) * basicPosition_: PositionableStream-positioning. (line 6) * basicPrint: Object-built ins. (line 38) * basicPrintNl: Object-printing. (line 6) * basicPrintOn_: Object-printing. (line 10) * basicRightShift_: LargeInteger-primitive operations. (line 9) * basicSize: Object-built ins. (line 41) * become_: Object-built ins. (line 44) * becomeForward_: Object-built ins. (line 56) * beConsistent <1>: SortedCollection-enumerating. (line 6) * beConsistent: Collection-enumeration. (line 9) * before_: SequenceableCollection-basic. (line 40) * bell: Character class-constants. (line 9) * between_and_ <1>: Random-basic. (line 9) * between_and_ <2>: Random class-shortcuts. (line 6) * between_and_: Magnitude-misc methods. (line 6) * bigEndian: Memory class-accessing. (line 13) * bigObjectThreshold: ObjectMemory class-builtins. (line 22) * bigObjectThreshold_: ObjectMemory class-builtins. (line 27) * binaryRepresentationObject <1>: VariableBinding-saving and loading. (line 6) * binaryRepresentationObject <2>: Object-saving and loading. (line 6) * binaryRepresentationObject <3>: CompiledMethod-saving and loading. (line 6) * binaryRepresentationObject: CompiledBlock-saving and loading. (line 6) * binaryRepresentationVersion: Class-saving and loading. (line 6) * binding: ClassDescription-conversion. (line 13) * bindingFor_: Class-accessing instances and variables. (line 22) * bindWith_: CharacterArray-string processing. (line 18) * bindWith_with_: CharacterArray-string processing. (line 22) * bindWith_with_with_: CharacterArray-string processing. (line 27) * bindWith_with_with_with_: CharacterArray-string processing. (line 32) * bindWithArguments_: CharacterArray-string processing. (line 37) * binomial_: Integer-math methods. (line 6) * bitAnd_ <1>: SmallInteger-built ins. (line 61) * bitAnd_: LargeInteger-bit operations. (line 6) * bitAt_ <1>: LargeInteger-bit operations. (line 9) * bitAt_: Integer-bit operators. (line 12) * bitAt_put_: Integer-bit operators. (line 15) * bitClear_: Integer-bit operators. (line 21) * bitInvert <1>: LargeInteger-bit operations. (line 12) * bitInvert: Integer-bit operators. (line 25) * bitOr_ <1>: SmallInteger-built ins. (line 64) * bitOr_: LargeInteger-bit operations. (line 15) * bits: SmallInteger class-getting limits. (line 6) * bitShift_ <1>: SmallInteger-built ins. (line 67) * bitShift_: LargeInteger-bit operations. (line 18) * bitXor_ <1>: SmallInteger-built ins. (line 71) * bitXor_: LargeInteger-bit operations. (line 21) * block <1>: CCallbackDescriptor-accessing. (line 6) * block: BlockClosure-accessing. (line 9) * block_ <1>: CCallbackDescriptor-accessing. (line 9) * block_ <2>: BlockClosure-accessing. (line 12) * block_: BlockClosure class-instance creation. (line 6) * block_receiver_: BlockClosure class-instance creation. (line 9) * block_receiver_outerContext_: BlockClosure class-instance creation. (line 13) * blockAt_: CompiledCode-accessing. (line 9) * bottom: Rectangle-accessing. (line 6) * bottom_: Rectangle-accessing. (line 9) * bottomCenter: Rectangle-accessing. (line 12) * bottomLeft: Rectangle-accessing. (line 15) * bottomLeft_: Rectangle-accessing. (line 18) * bottomRight: Rectangle-accessing. (line 21) * bottomRight_: Rectangle-accessing. (line 24) * broadcast_: Object-change and update. (line 6) * broadcast_with_: Object-change and update. (line 9) * broadcast_with_with_: Object-change and update. (line 13) * broadcast_withArguments_: Object-change and update. (line 17) * broadcast_withBlock_: Object-change and update. (line 21) * bufferSize: FileStream-buffering. (line 6) * bufferSize_: FileStream-buffering. (line 9) * bufferStart: FileStream-basic. (line 6) * builtFiles: Package-accessing. (line 50) * builtFilesFor_: PackageLoader class-accessing. (line 6) * byteAt_ <1>: String-accessing. (line 6) * byteAt_: ByteArray-built ins. (line 13) * byteAt_put_ <1>: String-accessing. (line 10) * byteAt_put_: ByteArray-built ins. (line 16) * bytecodeAt_: CompiledCode-accessing. (line 13) * bytecodeAt_put_: CompiledCode-accessing. (line 16) * byteCodeCounter: SystemDictionary-builtins. (line 10) * bytecodeInfoTable: CompiledCode class-tables. (line 6) * bytes_from_compare_: LargePositiveInteger-helper byte-level methods. (line 6) * bytes_from_subtract_: LargePositiveInteger-helper byte-level methods. (line 11) * bytes_multiply_: LargePositiveInteger-helper byte-level methods. (line 14) * bytesLeftShift_: LargePositiveInteger-helper byte-level methods. (line 18) * bytesLeftShift_big_: LargePositiveInteger-helper byte-level methods. (line 21) * bytesLeftShift_n_: LargePositiveInteger-helper byte-level methods. (line 24) * bytesPerOOP: ObjectMemory-accessing. (line 24) * bytesPerOTE: ObjectMemory-accessing. (line 28) * bytesRightShift_big_: LargePositiveInteger-helper byte-level methods. (line 28) * bytesRightShift_n_: LargePositiveInteger-helper byte-level methods. (line 31) * bytesTrailingZeros_: LargePositiveInteger-helper byte-level methods. (line 35) * callCC: Continuation-invocation. (line 6) * caller: BlockContext-accessing. (line 6) * callInto_: CCallable-calling. (line 23) * callNoRetryFrom_into_: CCallable-calling. (line 30) * callouts: Package-accessing. (line 54) * calloutsFor_: PackageLoader class-accessing. (line 11) * canCache: NetClients.URL-testing. (line 6) * canLoad_: PackageLoader class-testing. (line 6) * canRead: FileDescriptor-accessing. (line 6) * canUnderstand_: Behavior-testing the method dictionary. (line 6) * canWrite: FileDescriptor-accessing. (line 9) * capacity <1>: HashedCollection-testing collections. (line 9) * capacity: Collection-testing collections. (line 6) * castTo_ <1>: CObject-conversion. (line 6) * castTo_: ByteArray-CObject. (line 10) * categoriesFor_are_: Class-instance creation - alternative. (line 6) * category <1>: MethodInfo-accessing. (line 6) * category <2>: Metaclass-delegation. (line 26) * category: Class-accessing instances and variables. (line 26) * category_ <1>: MethodInfo-accessing. (line 9) * category_: Class-accessing instances and variables. (line 29) * cCall_numArgs_attributes_: CompiledMethod class-c call-outs. (line 10) * ceiling <1>: ScaledDecimal-coercion. (line 22) * ceiling <2>: Integer-converting. (line 16) * ceiling <3>: Fraction-coercing. (line 6) * ceiling: Float-built ins. (line 15) * ceilingLog_ <1>: Number-misc math. (line 31) * ceilingLog_ <2>: Integer-math methods. (line 10) * ceilingLog_: Float-transcendental operations. (line 9) * center: Rectangle-accessing. (line 27) * centralDirectoryRangeIn_: VFS.ZipFile-members. (line 6) * changeClassTo_: Object-built ins. (line 61) * changed: Object-change and update. (line 26) * changed_ <1>: ObjectMemory class-initialization. (line 6) * changed_: Object-change and update. (line 30) * charAt_ <1>: Memory class-accessing. (line 16) * charAt_: ByteArray-more advanced accessing. (line 6) * charAt_put_ <1>: Memory class-accessing. (line 20) * charAt_put_: ByteArray-more advanced accessing. (line 11) * check_ <1>: SecurityPolicy-querying. (line 6) * check_: Class-security. (line 6) * check_for_: Permission-testing. (line 6) * checkError <1>: FileDescriptor-basic. (line 6) * checkError: File class-file operations. (line 6) * checkError_: File class-file operations. (line 10) * checkIndexableBounds_: Object-built ins. (line 66) * checkIndexableBounds_ifAbsent_: Object-built ins. (line 70) * checkIndexableBounds_put_: Object-built ins. (line 74) * checkSecurityFor_: ContextPart-security checks. (line 6) * checkTagIfInPath_: Package-still unclassified. (line 6) * chiSquare: Random-testing. (line 6) * chiSquare_range_: Random-testing. (line 9) * class <1>: Object-built ins. (line 78) * class: Autoload-accessing. (line 6) * class_from_: Autoload class-instance creation. (line 6) * class_in_from_: Autoload class-instance creation. (line 10) * class_in_loader_: Autoload class-instance creation. (line 14) * class_loader_: Autoload class-instance creation. (line 20) * classAt_: AbstractNamespace-accessing. (line 23) * classAt_ifAbsent_: AbstractNamespace-accessing. (line 28) * classify_under_: ClassDescription-organization of messages and classes. (line 6) * classPool <1>: Metaclass-delegation. (line 29) * classPool <2>: Class-accessing instances and variables. (line 32) * classPool: Behavior-accessing instances and variables. (line 24) * classPragmas <1>: Class-accessing instances and variables. (line 35) * classPragmas: CCompound class-subclass creation. (line 9) * classVariableString: ClassDescription-printing. (line 6) * classVarNames <1>: Metaclass-delegation. (line 32) * classVarNames <2>: Class-accessing instances and variables. (line 38) * classVarNames: Behavior-accessing instances and variables. (line 29) * clean: FileStream-buffering. (line 12) * clearBit_: Integer-bit operators. (line 28) * clearGCFlag_: WeakArray-accessing. (line 28) * client: ContextPart-accessing. (line 18) * clockPrecision: DateTime class-information. (line 6) * close <1>: Stream-polymorphism. (line 6) * close <2>: PositionableStream-accessing-reading. (line 6) * close: FileDescriptor-basic. (line 10) * closeTo_: Number-testing. (line 6) * cObjectBinding_: CType class-C instance creation. (line 6) * cObjectType: CType-accessing. (line 13) * cObjectType_: CType class-C instance creation. (line 9) * cObjStoredType <1>: CUShort-accessing. (line 9) * cObjStoredType <2>: CUShort class-accessing. (line 9) * cObjStoredType <3>: CULongLong-accessing. (line 9) * cObjStoredType <4>: CULongLong class-accessing. (line 9) * cObjStoredType <5>: CULong-accessing. (line 9) * cObjStoredType <6>: CULong class-accessing. (line 9) * cObjStoredType <7>: CUInt-accessing. (line 9) * cObjStoredType <8>: CUInt class-accessing. (line 9) * cObjStoredType <9>: CUChar-accessing. (line 9) * cObjStoredType <10>: CUChar class-getting info. (line 9) * cObjStoredType <11>: CString-accessing. (line 6) * cObjStoredType <12>: CString class-accessing. (line 6) * cObjStoredType <13>: CSmalltalk-accessing. (line 9) * cObjStoredType <14>: CSmalltalk class-accessing. (line 9) * cObjStoredType <15>: CShort-accessing. (line 9) * cObjStoredType <16>: CShort class-accessing. (line 9) * cObjStoredType <17>: CScalar-accessing. (line 6) * cObjStoredType <18>: CLongLong-accessing. (line 9) * cObjStoredType <19>: CLongLong class-accessing. (line 9) * cObjStoredType <20>: CLongDouble-accessing. (line 9) * cObjStoredType <21>: CLongDouble class-accessing. (line 9) * cObjStoredType <22>: CLong-accessing. (line 9) * cObjStoredType <23>: CLong class-accessing. (line 9) * cObjStoredType <24>: CInt-accessing. (line 9) * cObjStoredType <25>: CInt class-accessing. (line 9) * cObjStoredType <26>: CFloat-accessing. (line 9) * cObjStoredType <27>: CFloat class-accessing. (line 9) * cObjStoredType <28>: CDouble-accessing. (line 9) * cObjStoredType <29>: CDouble class-accessing. (line 9) * cObjStoredType <30>: CChar-accessing. (line 9) * cObjStoredType <31>: CChar class-accessing. (line 9) * cObjStoredType <32>: CByte-accessing. (line 6) * cObjStoredType: CByte class-conversion. (line 6) * codePoint: Character-built ins. (line 17) * codePoint_: Character class-built ins. (line 10) * coerce_ <1>: ScaledDecimal-coercion. (line 26) * coerce_ <2>: Number-converting. (line 46) * coerce_ <3>: Number class-converting. (line 6) * coerce_ <4>: LargeInteger-coercion. (line 10) * coerce_ <5>: Integer-converting. (line 19) * coerce_ <6>: Integer class-converting. (line 6) * coerce_ <7>: Fraction-coercing. (line 10) * coerce_ <8>: Fraction class-converting. (line 6) * coerce_ <9>: FloatQ-coercing. (line 9) * coerce_ <10>: FloatQ class-converting. (line 6) * coerce_ <11>: FloatE-coercing. (line 9) * coerce_ <12>: FloatE class-converting. (line 6) * coerce_ <13>: FloatD-coercing. (line 9) * coerce_: FloatD class-converting. (line 6) * collect_ <1>: Stream-filtering. (line 11) * collect_ <2>: MappedCollection-basic. (line 21) * collect_ <3>: Iterable-enumeration. (line 18) * collect_ <4>: Interval-basic. (line 12) * collect_ <5>: Dictionary-dictionary enumerating. (line 9) * collect_ <6>: Collection-enumeration. (line 20) * collect_: ArrayedCollection-enumerating the elements of a collection. (line 6) * collection: SystemExceptions.IndexOutOfRange-accessing. (line 6) * collection_: SystemExceptions.IndexOutOfRange-accessing. (line 9) * collection_map_: MappedCollection class-instance creation. (line 6) * comment <1>: Metaclass-delegation. (line 35) * comment: Class-accessing instances and variables. (line 41) * comment_: Class-accessing instances and variables. (line 44) * compact: ObjectMemory class-builtins. (line 32) * compile_: Behavior-method dictionary. (line 10) * compile_classified_: ClassDescription-compiling. (line 6) * compile_classified_ifError_: ClassDescription-compiling. (line 11) * compile_classified_notifying_: ClassDescription-compiling. (line 16) * compile_ifError_: Behavior-method dictionary. (line 14) * compile_notifying_: Behavior-method dictionary. (line 19) * compileAll: Behavior-method dictionary. (line 24) * compileAll_: Behavior-method dictionary. (line 27) * compileAllSubclasses: Behavior-method dictionary. (line 31) * compileAllSubclasses_: Behavior-method dictionary. (line 35) * compiledMethodAt_: Behavior-accessing the method dictionary. (line 13) * compiledMethodAt_ifAbsent_: Behavior-accessing the method dictionary. (line 17) * compilerClass: Behavior-compiling. (line 6) * compileSize_align_: CCompound class-subclass creation. (line 12) * compress: LargeArrayedCollection-accessing. (line 12) * computeAggregateType_: CType class-C instance creation. (line 12) * conform_: Iterable-enumeration. (line 22) * construct_: NetClients.URL-utilities. (line 6) * contains_ <1>: Rectangle-testing. (line 9) * contains_: Iterable-enumeration. (line 26) * containsLiteral_: CompiledCode-testing accesses. (line 14) * containsPoint_: Rectangle-testing. (line 13) * contents <1>: WriteStream-accessing-writing. (line 6) * contents <2>: Stream-accessing-reading. (line 6) * contents <3>: ReadWriteStream-positioning. (line 6) * contents <4>: PositionableStream-accessing-reading. (line 9) * contents <5>: NetClients.URL-still unclassified. (line 6) * contents <6>: MappedCollection-basic. (line 27) * contents <7>: FilePath-file operations. (line 6) * contents: FileDescriptor-basic. (line 13) * context <1>: Process-basic. (line 6) * context: Exception-exception handling. (line 6) * continue_: ContextPart-built ins. (line 6) * contractTo_: CharacterArray-string processing. (line 49) * convertFromVersion_withFixedVariables_indexedVariables_for_: Class-saving and loading. (line 10) * copy <1>: UndefinedObject-basic. (line 6) * copy <2>: Regex-basic. (line 9) * copy <3>: Rectangle-copying. (line 6) * copy <4>: Object-copying. (line 6) * copy <5>: BlockClosure-overriding. (line 6) * copy: BindingDictionary-copying. (line 6) * copy_from_: ClassDescription-copying. (line 6) * copy_from_classified_: ClassDescription-copying. (line 9) * copyAfter_: SequenceableCollection-copying SequenceableCollections. (line 6) * copyAfterLast_: SequenceableCollection-copying SequenceableCollections. (line 10) * copyAll_from_: ClassDescription-copying. (line 13) * copyAll_from_classified_: ClassDescription-copying. (line 17) * copyAllCategoriesFrom_: ClassDescription-copying. (line 21) * copyCategory_from_: ClassDescription-copying. (line 25) * copyCategory_from_classified_: ClassDescription-copying. (line 29) * copyEmpty_ <1>: SortedCollection-copying. (line 6) * copyEmpty_ <2>: BindingDictionary-copying. (line 9) * copyEmpty_: AbstractNamespace-copying. (line 6) * copyEmptyForCollect: BindingDictionary-copying. (line 12) * copyEmptyForCollect_: BindingDictionary-copying. (line 16) * copyFrom_: SequenceableCollection-copying SequenceableCollections. (line 14) * copyFrom_to_ <1>: SequenceableCollection-copying SequenceableCollections. (line 18) * copyFrom_to_ <2>: PositionableStream-accessing-reading. (line 13) * copyFrom_to_ <3>: MappedCollection-basic. (line 30) * copyFrom_to_ <4>: Interval-basic. (line 16) * copyFrom_to_ <5>: FileStream-basic. (line 10) * copyFrom_to_ <6>: FileSegment-basic. (line 9) * copyFrom_to_ <7>: FileDescriptor-basic. (line 16) * copyFrom_to_: ArrayedCollection-basic. (line 19) * copyFrom_to_replacingAllRegex_with_: String-regex. (line 31) * copyFrom_to_replacingRegex_with_: String-regex. (line 38) * copyReplaceAll_with_ <1>: SequenceableCollection-copying SequenceableCollections. (line 22) * copyReplaceAll_with_: ArrayedCollection-copying Collections. (line 6) * copyReplaceFrom_to_with_ <1>: SequenceableCollection-copying SequenceableCollections. (line 26) * copyReplaceFrom_to_with_: ArrayedCollection-copying Collections. (line 10) * copyReplaceFrom_to_withObject_ <1>: SequenceableCollection-copying SequenceableCollections. (line 38) * copyReplaceFrom_to_withObject_: ArrayedCollection-copying Collections. (line 22) * copyReplacing_withObject_: Collection-copying Collections. (line 6) * copyReplacingAllRegex_with_: String-regex. (line 46) * copyReplacingRegex_with_: String-regex. (line 53) * copyStack: ContextPart-copying. (line 6) * copyUpTo_: SequenceableCollection-copying SequenceableCollections. (line 49) * copyUpToLast_: SequenceableCollection-copying SequenceableCollections. (line 53) * copyWith_ <1>: Collection-copying Collections. (line 10) * copyWith_: ArrayedCollection-basic. (line 23) * copyWithFirst_: SequenceableCollection-copying SequenceableCollections. (line 57) * copyWithout_ <1>: Collection-copying Collections. (line 13) * copyWithout_: ArrayedCollection-basic. (line 27) * copyWithoutAuxiliaryParts: NetClients.URL-copying. (line 6) * copyWithoutFragment: NetClients.URL-copying. (line 10) * corner: Rectangle-accessing. (line 30) * corner_ <1>: Rectangle-accessing. (line 33) * corner_: Point-converting. (line 12) * cos <1>: Number-misc math. (line 34) * cos: Float-built ins. (line 19) * cosh: Number-misc math. (line 37) * costOfNewIndex: LargeByteArray-overridden. (line 6) * count_: Iterable-enumeration. (line 30) * cr <1>: TextCollector-accessing. (line 6) * cr <2>: Stream-character writing. (line 6) * cr: Character class-constants. (line 12) * create: FileDescriptor class-instance creation. (line 10) * create_: Directory class-file operations. (line 9) * createDirectories: FilePath-directory operations. (line 6) * createDirectory <1>: FilePath-directory operations. (line 9) * createDirectory: File-directory operations. (line 6) * createDirectory_ <1>: VFS.ZipFile-members. (line 9) * createDirectory_: VFS.ArchiveMember-directory operations. (line 10) * createGetMethod_ <1>: ClassDescription-organization of messages and classes. (line 10) * createGetMethod_: Behavior-method dictionary. (line 39) * createGetMethod_default_ <1>: ClassDescription-organization of messages and classes. (line 13) * createGetMethod_default_: Behavior-method dictionary. (line 42) * createSetMethod_ <1>: ClassDescription-organization of messages and classes. (line 17) * createSetMethod_: Behavior-method dictionary. (line 46) * createTemporary_: Directory class-file operations. (line 12) * creationTime <1>: VFS.FileWrapper-delegation. (line 6) * creationTime <2>: VFS.ArchiveMember-accessing. (line 13) * creationTime <3>: FilePath-accessing. (line 10) * creationTime: File-accessing. (line 13) * critical_ <1>: TextCollector-accessing. (line 9) * critical_ <2>: Semaphore-mutual exclusion. (line 6) * critical_: RecursionLock-mutual exclusion. (line 6) * crTab: Stream-character writing. (line 9) * cull_: BlockClosure-built ins. (line 6) * cull_cull_: BlockClosure-built ins. (line 10) * cull_cull_cull_: BlockClosure-built ins. (line 14) * current <1>: ObjectMemory class-accessing. (line 6) * current <2>: Namespace class-accessing. (line 6) * current: Continuation class-instance creation. (line 6) * current_: Namespace class-accessing. (line 9) * currentDo_: Continuation class-instance creation. (line 9) * currentFileName: ContextPart-accessing. (line 23) * currentLine: ContextPart-debugging. (line 6) * currentLineInFile: ContextPart-debugging. (line 11) * date_time_: DateTime class-instance creation (non-ANSI). (line 6) * date_time_offset_: DateTime class-instance creation (non-ANSI). (line 10) * dateAndTimeNow: Date class-instance creation (Blue Book). (line 6) * day: Date-compatibility (non-ANSI). (line 6) * dayName: Date-compatibility (non-ANSI). (line 9) * dayOfMonth: Date-date computations. (line 9) * dayOfWeek <1>: DateTime-computations. (line 9) * dayOfWeek: Date-date computations. (line 12) * dayOfWeek_: Date class-basic. (line 10) * dayOfWeekAbbreviation: Date-date computations. (line 15) * dayOfWeekName: Date-date computations. (line 18) * dayOfYear: Date-date computations. (line 21) * days: Duration-arithmetics. (line 27) * days_: Duration class-instance creation. (line 6) * days_hours_minutes_seconds_: Duration class-instance creation. (line 9) * daysFromBaseDay: Date-date computations. (line 25) * daysInMonth: Date-date computations. (line 28) * daysInMonth_forYear_: Date class-basic. (line 13) * daysInYear: Date-date computations. (line 31) * daysInYear_: Date class-basic. (line 17) * daysLeftInMonth: Date-date computations. (line 34) * daysLeftInYear: Date-date computations. (line 37) * debug: SystemDictionary-builtins. (line 13) * debugger <1>: Process-basic. (line 9) * debugger: ContextPart-debugging. (line 16) * debuggerClass <1>: Metaclass-delegation. (line 38) * debuggerClass <2>: ContextPart-debugging. (line 20) * debuggerClass: Behavior-pluggable behavior (not yet implemented). (line 6) * decimalDigits <1>: FloatQ class-characterization. (line 6) * decimalDigits <2>: FloatE class-characterization. (line 6) * decimalDigits: FloatD class-characterization. (line 6) * declaration: CCompound class-subclass creation. (line 15) * declaration_ <1>: CUnion class-subclass creation. (line 6) * declaration_ <2>: CStruct class-subclass creation. (line 6) * declaration_: CCompound class-subclass creation. (line 18) * declaration_inject_into_: CCompound class-subclass creation. (line 22) * declarationTrace: SystemDictionary-builtins. (line 18) * declarationTrace_: SystemDictionary-builtins. (line 21) * decode_: NetClients.URL class-encoding URLs. (line 6) * decodedFields: NetClients.URL-accessing. (line 12) * decodedFile: NetClients.URL-accessing. (line 16) * decodedFragment: NetClients.URL-accessing. (line 20) * decompile_: Behavior-method dictionary. (line 49) * decompilerClass: Behavior-pluggable behavior (not yet implemented). (line 12) * decr: CObject-pointer-like behavior. (line 44) * decrBy_: CObject-pointer-like behavior. (line 48) * deepCopy <1>: WeakSet-copying. (line 6) * deepCopy <2>: WeakArray-conversion. (line 9) * deepCopy <3>: UndefinedObject-basic. (line 9) * deepCopy <4>: Symbol-basic. (line 6) * deepCopy <5>: RunArray-copying. (line 6) * deepCopy <6>: Object-copying. (line 11) * deepCopy <7>: Number-copying. (line 6) * deepCopy <8>: HashedCollection-copying. (line 6) * deepCopy <9>: ContextPart-copying. (line 9) * deepCopy <10>: CompiledCode-copying. (line 6) * deepCopy <11>: Boolean-overriding. (line 6) * deepCopy <12>: BlockClosure-overriding. (line 9) * deepCopy: BindingDictionary-copying. (line 20) * defaultAction <1>: SystemExceptions.UnhandledException-accessing. (line 6) * defaultAction <2>: Notification-exception description. (line 6) * defaultAction: Exception-exception description. (line 6) * defaultElement <1>: LargeWordArray-overridden. (line 6) * defaultElement: LargeByteArray-overridden. (line 10) * defaultEncoding: UnicodeString class-multibyte encodings. (line 6) * defaultSortBlock: SortedCollection class-hacking. (line 6) * define_: BindingDictionary-accessing. (line 6) * defineAsyncCFunc_withSelectorArgs_args_ <1>: ClassDescription-organization of messages and classes. (line 20) * defineAsyncCFunc_withSelectorArgs_args_: Behavior-method dictionary. (line 52) * defineCFunc_as_: DLD class-C call-outs. (line 6) * defineCFunc_withSelectorArgs_returning_args_ <1>: ClassDescription-organization of messages and classes. (line 24) * defineCFunc_withSelectorArgs_returning_args_: Behavior-method dictionary. (line 57) * definedKeys: Dictionary-namespace protocol. (line 13) * defineExternFunc_: DLD class-dynamic linking. (line 19) * definesKey_: Dictionary-namespace protocol. (line 16) * degreesToRadians: Number-converting. (line 49) * delayDuration: Delay-accessing. (line 12) * denominator <1>: Integer-accessing. (line 6) * denominator: Fraction-accessing. (line 6) * denormalized: Float class-characterization. (line 6) * deny: Permission-accessing. (line 21) * denying: Permission-accessing. (line 24) * denying_target_action_: Permission class-testing. (line 12) * denying_target_actions_: Permission class-testing. (line 15) * dependencies: Object class-initialization. (line 6) * dependencies_: Object class-initialization. (line 9) * dependents: Object-dependents access. (line 10) * deref_: Memory class-accessing. (line 25) * description <1>: ZeroDivide-description. (line 6) * description <2>: Warning-exception description. (line 6) * description <3>: SystemExceptions.WrongClass-accessing. (line 6) * description <4>: SystemExceptions.WrongArgumentCount-accessing. (line 6) * description <5>: SystemExceptions.VMError-accessing. (line 6) * description <6>: SystemExceptions.VerificationError-accessing. (line 6) * description <7>: SystemExceptions.UserInterrupt-accessing. (line 6) * description <8>: SystemExceptions.UnhandledException-accessing. (line 9) * description <9>: SystemExceptions.SubclassResponsibility-accessing. (line 6) * description <10>: SystemExceptions.ShouldNotImplement-accessing. (line 6) * description <11>: SystemExceptions.SecurityError-accessing. (line 6) * description <12>: SystemExceptions.ReadOnlyObject-accessing. (line 6) * description <13>: SystemExceptions.ProcessTerminated-accessing. (line 6) * description <14>: SystemExceptions.ProcessBeingTerminated-accessing. (line 6) * description <15>: SystemExceptions.PrimitiveFailed-accessing. (line 6) * description <16>: SystemExceptions.NotYetImplemented-accessing. (line 6) * description <17>: SystemExceptions.NotIndexable-accessing. (line 6) * description <18>: SystemExceptions.NotImplemented-accessing. (line 6) * description <19>: SystemExceptions.NotFound-accessing. (line 6) * description <20>: SystemExceptions.NotEnoughElements-accessing. (line 6) * description <21>: SystemExceptions.NoRunnableProcess-accessing. (line 6) * description <22>: SystemExceptions.MutationError-accessing. (line 6) * description <23>: SystemExceptions.InvalidValue-accessing. (line 6) * description <24>: SystemExceptions.InvalidSize-accessing. (line 6) * description <25>: SystemExceptions.InvalidProcessState-accessing. (line 6) * description <26>: SystemExceptions.IndexOutOfRange-accessing. (line 12) * description <27>: SystemExceptions.FileError-accessing. (line 6) * description <28>: SystemExceptions.EndOfStream-accessing. (line 6) * description <29>: SystemExceptions.EmptyCollection-accessing. (line 6) * description <30>: SystemExceptions.CInterfaceError-accessing. (line 6) * description <31>: SystemExceptions.BadReturn-accessing. (line 6) * description <32>: SystemExceptions.ArgumentOutOfRange-accessing. (line 6) * description <33>: SystemExceptions.AlreadyDefined-accessing. (line 6) * description <34>: Notification-exception description. (line 10) * description <35>: MessageNotUnderstood-description. (line 6) * description <36>: Halt-description. (line 6) * description <37>: Exception-exception description. (line 9) * description <38>: Error-exception description. (line 6) * description: ArithmeticError-description. (line 6) * detach <1>: Process-debugging. (line 6) * detach: CallinProcess-debugging. (line 6) * detect_: Iterable-enumeration. (line 34) * detect_ifNone_: Iterable-enumeration. (line 38) * digitAt_ <1>: LargeInteger-built-ins. (line 12) * digitAt_: Integer-bit operators. (line 31) * digitAt_put_: LargeInteger-built-ins. (line 16) * digitLength: LargeInteger-built-ins. (line 19) * digitValue: Character-converting. (line 9) * digitValue_: Character class-instance creation. (line 6) * dir_tag_: Package-still unclassified. (line 9) * directories: FilePath-enumerating. (line 11) * directory <1>: Package-accessing. (line 59) * directory: FilePath-file name management. (line 6) * directoryFor_: PackageLoader class-accessing. (line 16) * disableInterrupts: ProcessorScheduler-built ins. (line 6) * disableProxyFor_: ObjectDumper class-establishing proxy classes. (line 6) * discardTranslation: CompiledCode-translation. (line 6) * dispatchTo_with_: CompiledCode-decoding bytecodes. (line 6) * display: Object-printing. (line 13) * display_: Stream-printing. (line 11) * displayLines: Collection-printing. (line 6) * displayNl: Object-printing. (line 19) * displayOn_ <1>: VFS.ArchiveMember-still unclassified. (line 10) * displayOn_ <2>: VFS.ArchiveFile-still unclassified. (line 6) * displayOn_ <3>: UnicodeString-converting. (line 18) * displayOn_ <4>: Symbol-storing. (line 6) * displayOn_ <5>: String-printing. (line 6) * displayOn_ <6>: ScaledDecimal-printing. (line 6) * displayOn_ <7>: Regex-printing. (line 6) * displayOn_ <8>: Object-printing. (line 26) * displayOn_ <9>: Integer-printing. (line 6) * displayOn_ <10>: FilePath-printing. (line 9) * displayOn_: Character-printing. (line 6) * displayString <1>: Symbol-storing. (line 12) * displayString <2>: String-printing. (line 10) * displayString <3>: Regex-printing. (line 12) * displayString <4>: Object-printing. (line 32) * displayString: Integer-printing. (line 9) * dist_: Point-point functions. (line 11) * divExact_ <1>: SmallInteger-built ins. (line 74) * divExact_: LargeInteger-arithmetic. (line 27) * divide_using_: LargePositiveInteger-primitive operations. (line 6) * dividend: ZeroDivide-accessing. (line 6) * dividend_: ZeroDivide class-instance creation. (line 6) * do_ <1>: WeakSet-accessing. (line 11) * do_ <2>: WeakArray-accessing. (line 32) * do_ <3>: SymLink-iteration. (line 6) * do_ <4>: Stream-enumerating. (line 6) * do_ <5>: SequenceableCollection-enumerating. (line 9) * do_ <6>: RunArray-enumerating. (line 6) * do_ <7>: OrderedCollection-enumerating. (line 6) * do_ <8>: Namespace-overrides for superspaces. (line 26) * do_ <9>: MappedCollection-basic. (line 34) * do_ <10>: LookupTable-enumerating. (line 9) * do_ <11>: LinkedList-enumerating. (line 6) * do_ <12>: Link-iteration. (line 13) * do_ <13>: Iterable-enumeration. (line 43) * do_ <14>: Interval-basic. (line 19) * do_ <15>: HashedCollection-enumerating the elements of a collection. (line 6) * do_ <16>: FilePath-enumerating. (line 15) * do_ <17>: Dictionary-dictionary enumerating. (line 14) * do_: Bag-enumerating the elements of a collection. (line 9) * do_separatedBy_ <1>: SequenceableCollection-enumerating. (line 12) * do_separatedBy_: Iterable-enumeration. (line 46) * doesNotUnderstand_ <1>: Object-error raising. (line 6) * doesNotUnderstand_ <2>: BindingDictionary-accessing. (line 10) * doesNotUnderstand_: Autoload-accessing. (line 10) * domain: MappedCollection-basic. (line 37) * doSecurityCheckForName_actions_target_: ContextPart-security checks. (line 9) * dotProduct_: Point-point functions. (line 14) * doubleAt_ <1>: Memory class-accessing. (line 28) * doubleAt_: ByteArray-more advanced accessing. (line 17) * doubleAt_put_ <1>: Memory class-accessing. (line 31) * doubleAt_put_: ByteArray-more advanced accessing. (line 21) * doWithIndex_: SequenceableCollection-enumerating. (line 17) * dump_: ObjectDumper-loading/dumping objects. (line 6) * dump_to_: ObjectDumper class-shortcuts. (line 6) * dumpTo_ <1>: VersionableObjectProxy-saving and restoring. (line 6) * dumpTo_ <2>: NullProxy-accessing. (line 6) * dumpTo_: DumperProxy-saving and restoring. (line 6) * e <1>: FloatQ class-characterization. (line 14) * e <2>: FloatE class-characterization. (line 14) * e: Float class-characterization. (line 10) * edenSize: ObjectMemory-accessing. (line 33) * edenUsedBytes: ObjectMemory-accessing. (line 38) * edit_: Behavior-method dictionary. (line 62) * elementType <1>: CStringCType-accessing. (line 6) * elementType <2>: CPtrCType-accessing. (line 6) * elementType: CAggregate-accessing. (line 6) * elementType_ <1>: CPtrCType class-instance creation. (line 6) * elementType_: CArrayCType class-instance creation. (line 6) * elementType_numberOfElements_: CArrayCType class-instance creation. (line 9) * emax <1>: FloatQ class-characterization. (line 17) * emax <2>: FloatE class-characterization. (line 17) * emax: FloatD class-characterization. (line 14) * emin <1>: FloatQ class-characterization. (line 20) * emin <2>: FloatE class-characterization. (line 20) * emin: FloatD class-characterization. (line 17) * emitFieldNameTo_for_: CCompound class-subclass creation. (line 28) * empty: Collection-removing. (line 6) * emptyStream: WriteStream-positioning. (line 6) * enableInterrupts: ProcessorScheduler-built ins. (line 13) * encode_: NetClients.URL class-encoding URLs. (line 10) * encoding <1>: UnicodeString-multibyte encodings. (line 6) * encoding <2>: String-converting. (line 15) * encoding <3>: Stream-character writing. (line 12) * encoding: CharacterArray-multibyte encodings. (line 6) * endEntry: TextCollector-accessing. (line 12) * endsWith_: SequenceableCollection-comparing. (line 6) * ensure_: BlockClosure-unwind protection. (line 6) * ensureReadable: FileDescriptor-accessing. (line 12) * ensureWriteable: FileDescriptor-accessing. (line 16) * entity: NetClients.URL-still unclassified. (line 9) * entries: FilePath-enumerating. (line 21) * entryNames: FilePath-enumerating. (line 25) * environ: SystemDictionary-c call-outs. (line 6) * environment <1>: ProcessVariable-accessing. (line 6) * environment <2>: Metaclass-delegation. (line 41) * environment <3>: HomedAssociation-accessing. (line 6) * environment <4>: ContextPart-accessing. (line 26) * environment <5>: Class-accessing instances and variables. (line 47) * environment <6>: BindingDictionary-accessing. (line 20) * environment <7>: Behavior-support for lightweight classes. (line 12) * environment: Association-accessing. (line 6) * environment_ <1>: HomedAssociation-accessing. (line 9) * environment_ <2>: Class-accessing instances and variables. (line 50) * environment_ <3>: BindingDictionary-accessing. (line 26) * environment_: Association-accessing. (line 10) * eof: Character class-constants. (line 15) * eot: Character class-constants. (line 18) * epsilon: Float class-characterization. (line 13) * eqv_ <1>: True-basic. (line 14) * eqv_ <2>: False-basic. (line 12) * eqv_: Boolean-basic. (line 14) * errno: File class-C functions. (line 6) * error_: Object-error raising. (line 10) * errorValue_: Promise-still unclassified. (line 6) * esc: Character class-constants. (line 21) * escapeDo_: Continuation class-instance creation. (line 13) * escapeRegex: String-still unclassified. (line 6) * estimatedLog <1>: Number-misc math. (line 40) * estimatedLog <2>: LargeInteger-arithmetic. (line 31) * estimatedLog <3>: Integer-math methods. (line 13) * estimatedLog <4>: Fraction-arithmetic. (line 26) * estimatedLog: Float-transcendental operations. (line 13) * evalString_to_: Behavior-evaluating. (line 6) * evalString_to_ifError_: Behavior-evaluating. (line 10) * evaluate_: Behavior-evaluating. (line 15) * evaluate_ifError_: Behavior-evaluating. (line 18) * evaluate_notifying_: Behavior-evaluating. (line 21) * evaluate_to_: Behavior-evaluating. (line 25) * evaluate_to_ifError_: Behavior-evaluating. (line 29) * evaluatorClass: Behavior-pluggable behavior (not yet implemented). (line 16) * even <1>: Number-testing. (line 11) * even: Integer-math methods. (line 16) * examine: Object-debugging. (line 6) * examineOn_ <1>: SequenceableCollection-testing. (line 9) * examineOn_ <2>: Object-debugging. (line 9) * examineOn_ <3>: Dictionary-printing. (line 6) * examineOn_ <4>: CompiledCode-debugging. (line 6) * examineOn_ <5>: Collection-printing. (line 9) * examineOn_: CCompound-debugging. (line 6) * example: ObjectDumper class-testing. (line 6) * exceptionalCondition: FileDescriptor-accessing. (line 20) * execPrefix: Directory class-reading system defaults. (line 6) * executable: File class-reading system defaults. (line 6) * executionTrace: SystemDictionary-builtins. (line 24) * executionTrace_: SystemDictionary-builtins. (line 27) * exists <1>: VFS.FileWrapper-testing. (line 6) * exists <2>: VFS.ArchiveMember-testing. (line 6) * exists <3>: FilePath-testing. (line 6) * exists: File-testing. (line 6) * exists_: File class-testing. (line 6) * exp <1>: Number-misc math. (line 45) * exp: Float-built ins. (line 22) * expandBy_: Rectangle-rectangle functions. (line 21) * exponent <1>: FloatQ-built ins. (line 39) * exponent <2>: FloatE-built ins. (line 39) * exponent: FloatD-built ins. (line 39) * extend: Class-instance creation. (line 6) * extension: FilePath-file name management. (line 9) * extensionFor_: FilePath class-file name management. (line 10) * extent: Rectangle-accessing. (line 36) * extent_ <1>: Rectangle-accessing. (line 39) * extent_: Point-converting. (line 16) * externalInterruptsEnabled: Process-accessing. (line 6) * extracted: VFS.TmpFileArchiveMember-still unclassified. (line 6) * extractMember_: VFS.ArchiveFile-TmpFileArchiveMember protocol. (line 6) * extractMember_into_ <1>: VFS.ZipFile-members. (line 12) * extractMember_into_: VFS.ArchiveFile-TmpFileArchiveMember protocol. (line 10) * factorial: Integer-math methods. (line 19) * failedPermission: SystemExceptions.SecurityError-accessing. (line 9) * failedPermission_: SystemExceptions.SecurityError-accessing. (line 12) * fd: FileDescriptor-accessing. (line 24) * features: Package-accessing. (line 62) * featuresFor_: PackageLoader class-accessing. (line 19) * ff: Character class-constants. (line 24) * fieldSelectorList: CCompound-debugging. (line 9) * file <1>: VFS.TmpFileArchiveMember-directory operations. (line 6) * file <2>: Stream-accessing-reading. (line 10) * file <3>: FileSegment-basic. (line 13) * file: FileDescriptor-accessing. (line 27) * fileData: VFS.ZipFile-members. (line 16) * fileIn <1>: Stream-built ins. (line 6) * fileIn <2>: FilePath-file operations. (line 10) * fileIn: FileDescriptor-built ins. (line 6) * fileIn_: FileStream class-file-in. (line 6) * fileIn_ifMissing_: FileStream class-file-in. (line 16) * fileIn_ifTrue_: FileStream class-file-in. (line 28) * fileIn_line_from_at_: FileStream class-file-in. (line 39) * fileInLine_file_at_: Stream-built ins. (line 16) * fileInLine_fileName_at_: Stream-built ins. (line 20) * fileInPackage_: PackageLoader class-loading. (line 6) * fileInPackages_: PackageLoader class-loading. (line 9) * fileIns: Package-accessing. (line 65) * fileInsFor_: PackageLoader class-accessing. (line 23) * fileName <1>: FileSegment-basic. (line 16) * fileName: CharacterArray-converting. (line 42) * fileOp_: FileDescriptor-built ins. (line 16) * fileOp_ifFail_: FileDescriptor-built ins. (line 20) * fileOp_with_: FileDescriptor-built ins. (line 24) * fileOp_with_ifFail_: FileDescriptor-built ins. (line 28) * fileOp_with_with_: FileDescriptor-built ins. (line 32) * fileOp_with_with_ifFail_: FileDescriptor-built ins. (line 36) * fileOp_with_with_with_: FileDescriptor-built ins. (line 40) * fileOp_with_with_with_ifFail_: FileDescriptor-built ins. (line 44) * fileOp_with_with_with_with_: FileDescriptor-built ins. (line 48) * fileOp_with_with_with_with_ifFail_: FileDescriptor-built ins. (line 52) * fileOut_ <1>: Stream-filing out. (line 6) * fileOut_: ClassDescription-filing. (line 6) * fileOutCategory_to_: ClassDescription-filing. (line 10) * fileOutCategory_toStream_: ClassDescription-still unclassified. (line 6) * fileOutDeclarationOn_: Class-filing. (line 6) * fileOutHeaderOn_: Class-still unclassified. (line 10) * fileOutOn_ <1>: Metaclass-filing. (line 6) * fileOutOn_ <2>: ClassDescription-filing. (line 14) * fileOutOn_: Class-filing. (line 9) * fileOutSelector_to_: ClassDescription-filing. (line 18) * fileOutSelector_toStream_: ClassDescription-still unclassified. (line 10) * filePos <1>: FileSegment-basic. (line 19) * filePos: CharacterArray-converting. (line 45) * files <1>: Package-accessing. (line 70) * files: FilePath-enumerating. (line 29) * filesFor_: PackageLoader class-accessing. (line 28) * filesMatching_: FilePath-enumerating. (line 33) * filesMatching_do_: FilePath-enumerating. (line 38) * fill: FileStream-buffering. (line 15) * fillFrom_: VFS.ArchiveMember-initializing. (line 9) * fillMember_: VFS.ArchiveFile-ArchiveMember protocol. (line 6) * finalIP: BlockClosure-accessing. (line 15) * finalizableObjects: Object class-initialization. (line 13) * finalize <1>: Process-basic. (line 13) * finalize <2>: Object-finalization. (line 10) * finalize <3>: FileDescriptor-basic. (line 19) * finalize: CObject-finalization. (line 6) * findFirst_: SequenceableCollection-enumerating. (line 23) * findKeyIndex_: Dictionary-awful ST-80 compatibility hacks. (line 6) * findLast_: SequenceableCollection-enumerating. (line 27) * findObjectIndex_: Set-awful ST-80 compatibility hacks. (line 6) * finishIncrementalGC: ObjectMemory class-builtins. (line 35) * first <1>: SequenceableCollection-basic. (line 44) * first <2>: RunArray-basic. (line 6) * first <3>: OrderedCollection-accessing. (line 13) * first <4>: LinkedList-iteration. (line 6) * first: Interval-printing. (line 6) * first_: SequenceableCollection-basic. (line 47) * firstDayOfMonth: Date-date computations. (line 40) * fixedSpaceSize: ObjectMemory-accessing. (line 42) * fixedSpaceUsedBytes: ObjectMemory-accessing. (line 46) * fixTemps: BlockClosure-accessing. (line 18) * flags <1>: CompiledMethod-accessing. (line 13) * flags <2>: CompiledCode-accessing. (line 19) * flags: CompiledBlock-accessing. (line 6) * floatAt_ <1>: Memory class-accessing. (line 35) * floatAt_: ByteArray-more advanced accessing. (line 26) * floatAt_put_ <1>: Memory class-accessing. (line 38) * floatAt_put_: ByteArray-more advanced accessing. (line 30) * floor <1>: Number-truncation and round off. (line 9) * floor <2>: Integer-converting. (line 22) * floor <3>: Fraction-coercing. (line 13) * floor: Float-built ins. (line 25) * floorLog_ <1>: Number-misc math. (line 48) * floorLog_ <2>: Integer-math methods. (line 22) * floorLog_: Float-transcendental operations. (line 16) * flush <1>: Stream-polymorphism. (line 9) * flush <2>: PackageLoader class-accessing. (line 33) * flush <3>: ObjectDumper-accessing. (line 6) * flush: FileStream-buffering. (line 18) * flushCache: Behavior-built ins. (line 17) * flushTranslatorCache: CompiledCode class-cache flushing. (line 6) * fmax <1>: FloatQ class-characterization. (line 23) * fmax <2>: FloatE class-characterization. (line 23) * fmax: FloatD class-characterization. (line 20) * fmin: Float class-characterization. (line 16) * fminDenormalized: Float class-characterization. (line 19) * fminNormalized <1>: FloatQ class-characterization. (line 26) * fminNormalized <2>: FloatE class-characterization. (line 26) * fminNormalized: FloatD class-characterization. (line 23) * fold_ <1>: SequenceableCollection-enumerating. (line 31) * fold_: Iterable-enumeration. (line 50) * fopen_mode_: FileDescriptor class-instance creation. (line 15) * fopen_mode_ifFail_: FileDescriptor class-instance creation. (line 25) * for_: Promise class-creating instances. (line 6) * for_returning_withArgs_ <1>: CFunctionDescriptor class-instance creation. (line 6) * for_returning_withArgs_ <2>: CCallbackDescriptor class-instance creation. (line 6) * for_returning_withArgs_: CCallable class-instance creation. (line 6) * fork <1>: DirectedMessage-multiple process. (line 6) * fork: BlockClosure-multiple process. (line 6) * forkAt_ <1>: DirectedMessage-multiple process. (line 9) * forkAt_: BlockClosure-multiple process. (line 9) * forkWithoutPreemption: BlockClosure-multiple process. (line 13) * formattedSourceStringAt_: Behavior-accessing the method dictionary. (line 21) * formattedSourceStringAt_ifAbsent_: Behavior-source code. (line 6) * forMilliseconds_: Delay class-instance creation. (line 6) * forMutualExclusion: Semaphore class-instance creation. (line 6) * forNanoseconds_: Delay class-instance creation. (line 9) * forSeconds_: Delay class-instance creation. (line 12) * fourth: SequenceableCollection-basic. (line 50) * fractionPart <1>: ScaledDecimal-coercion. (line 30) * fractionPart <2>: Number-truncation and round off. (line 12) * fractionPart <3>: FloatQ-built ins. (line 43) * fractionPart <4>: FloatE-built ins. (line 43) * fractionPart: FloatD-built ins. (line 43) * fragment: NetClients.URL-accessing. (line 24) * fragment_: NetClients.URL-accessing. (line 28) * free <1>: UndefinedObject-CObject interoperability. (line 6) * free: CObject-C data access. (line 14) * from: RegexResults-accessing. (line 14) * from_ <1>: Dictionary class-instance creation. (line 6) * from_ <2>: CType class-C instance creation. (line 16) * from_ <3>: CPtrCType class-instance creation. (line 10) * from_ <4>: Collection class-instance creation. (line 6) * from_ <5>: CArrayCType class-instance creation. (line 16) * from_: Array class-instance creation. (line 6) * from_to_: Interval class-instance creation. (line 6) * from_to_by_: Interval class-instance creation. (line 10) * from_to_do_: SequenceableCollection-enumerating. (line 38) * from_to_doWithIndex_: SequenceableCollection-enumerating. (line 42) * from_to_keysAndValuesDo_: SequenceableCollection-enumerating. (line 49) * fromAt_: RegexResults-accessing. (line 18) * fromBytes_ <1>: FloatE class-byte-order dependencies. (line 6) * fromBytes_: FloatD class-byte-order dependencies. (line 6) * fromCData_: String class-instance creation. (line 6) * fromCData_size_ <1>: String class-instance creation. (line 10) * fromCData_size_: ByteArray class-instance creation. (line 6) * fromDays_: Date class-instance creation (Blue Book). (line 9) * fromDays_seconds_: DateTime class-instance creation (non-ANSI). (line 14) * fromDays_seconds_offset_ <1>: Duration class-instance creation (non ANSI). (line 6) * fromDays_seconds_offset_: DateTime class-instance creation (non-ANSI). (line 18) * fromJulian_: Date class-instance creation (Blue Book). (line 12) * fromSeconds_ <1>: Time class-instance creation. (line 6) * fromSeconds_ <2>: DateTime class-instance creation (non-ANSI). (line 23) * fromSeconds_: Date class-instance creation (Blue Book). (line 16) * fromSeconds_offset_: DateTime class-instance creation (non-ANSI). (line 27) * fromString_ <1>: UnicodeString class-converting. (line 6) * fromString_ <2>: Regex class-instance creation. (line 6) * fromString_ <3>: NetClients.URL class-instance creation. (line 6) * fromString_: CharacterArray class-basic. (line 6) * full <1>: VFS.FileWrapper-delegation. (line 12) * full <2>: VFS.ArchiveMember-delegation. (line 6) * full <3>: FilePath-file name management. (line 12) * full: File-file name management. (line 6) * fullName: FilePath-file name management. (line 17) * fullNameFor_: FilePath class-file name management. (line 14) * fullPathOf_: Package-accessing. (line 74) * fullRequestString: NetClients.URL-accessing. (line 32) * gather_: Collection-enumeration. (line 24) * gcAlloc_: CObject class-instance creation. (line 12) * gcAlloc_type_: CObject class-primitive allocation. (line 9) * gcd_ <1>: LargePositiveInteger-arithmetic. (line 12) * gcd_ <2>: LargeNegativeInteger-reverting to LargePositiveInteger. (line 12) * gcd_: Integer-math methods. (line 25) * gcMessage: ObjectMemory class-builtins. (line 38) * gcMessage_: ObjectMemory class-builtins. (line 42) * gcNew <1>: CType-C instance creation. (line 11) * gcNew: CCompound class-instance creation. (line 6) * gcNew_ <1>: CType-C instance creation. (line 16) * gcNew_: CObject class-instance creation. (line 15) * gcValue_: CScalar class-instance creation. (line 6) * generality <1>: SmallInteger-coercion methods. (line 6) * generality <2>: ScaledDecimal-coercion. (line 33) * generality <3>: Number-converting. (line 52) * generality <4>: LargeInteger-coercion. (line 14) * generality <5>: Fraction-coercing. (line 17) * generality <6>: FloatQ-coercing. (line 12) * generality <7>: FloatE-coercing. (line 12) * generality: FloatD-coercing. (line 12) * generateMakefileOnto_: FileStream class-file-in. (line 44) * getArgc: SystemDictionary-c call-outs. (line 9) * getArgv_: SystemDictionary-c call-outs. (line 12) * getBlock_putBlock_: PluggableAdaptor class-creating instances. (line 6) * getenv_: SystemDictionary-c call-outs. (line 15) * getTraceFlag_: SystemDictionary-builtins. (line 30) * globalGarbageCollect: ObjectMemory class-builtins. (line 46) * goodness_ <1>: ExceptionSet-enumerating. (line 10) * goodness_: Exception class-comparison. (line 6) * granting_target_action_: Permission class-testing. (line 18) * granting_target_actions_: Permission class-testing. (line 21) * grid_: Point-point functions. (line 17) * group_: FilePath-accessing. (line 16) * growThresholdPercent: ObjectMemory class-builtins. (line 49) * growThresholdPercent_: ObjectMemory class-builtins. (line 53) * growTo_: ObjectMemory class-builtins. (line 57) * half <1>: FloatQ-converting. (line 6) * half <2>: FloatE-converting. (line 6) * half <3>: FloatD-converting. (line 6) * half: Float-converting. (line 6) * halt <1>: SystemDictionary-basic. (line 6) * halt: Object-built ins. (line 81) * halt_: Object-error raising. (line 14) * handleDelayRequestor: Delay class-timer process. (line 9) * handles_ <1>: ExceptionSet-enumerating. (line 15) * handles_: Exception class-comparison. (line 11) * hasBytecode_between_and_: CompiledCode-testing accesses. (line 18) * hasError: Promise-accessing. (line 6) * hasFeatures_: SystemDictionary-special accessing. (line 9) * hasFragment: NetClients.URL-testing. (line 10) * hash <1>: VFS.FileWrapper-basic. (line 10) * hash <2>: VFS.ArchiveMember-basic. (line 10) * hash <3>: UnicodeString-built-ins. (line 6) * hash <4>: Time-comparing. (line 12) * hash <5>: SystemDictionary-basic. (line 9) * hash <6>: Symbol-built ins. (line 9) * hash <7>: String-built ins. (line 30) * hash <8>: SequenceableCollection-testing. (line 13) * hash <9>: ScaledDecimal-comparing. (line 21) * hash <10>: RunArray-testing. (line 9) * hash <11>: Rectangle-testing. (line 18) * hash <12>: Point-converting. (line 20) * hash <13>: Object-built ins. (line 84) * hash <14>: NetClients.URL-comparing. (line 12) * hash <15>: MethodInfo-equality. (line 9) * hash <16>: LookupTable-hashing. (line 6) * hash <17>: LookupKey-testing. (line 14) * hash <18>: LargeZeroInteger-accessing. (line 9) * hash <19>: LargeInteger-built-ins. (line 22) * hash <20>: LargeArrayedCollection-basic. (line 9) * hash <21>: Interval-testing. (line 9) * hash <22>: Integer-basic. (line 6) * hash <23>: HashedCollection-testing collections. (line 13) * hash <24>: Fraction-comparing. (line 21) * hash <25>: Float-basic. (line 6) * hash <26>: FileSegment-equality. (line 9) * hash <27>: File-basic. (line 10) * hash <28>: Dictionary-testing. (line 9) * hash <29>: Delay-comparing. (line 9) * hash <30>: DateTime-testing. (line 12) * hash <31>: Date-testing. (line 12) * hash <32>: CType-basic. (line 9) * hash <33>: CPtrCType-basic. (line 9) * hash <34>: CompiledMethod-basic. (line 9) * hash <35>: CompiledCode-basic. (line 11) * hash <36>: CObject-basic. (line 9) * hash <37>: CArrayCType-basic. (line 9) * hash <38>: ByteArray-built ins. (line 20) * hash <39>: BindingDictionary-basic & copying. (line 11) * hash <40>: Bag-testing collections. (line 9) * hash: Association-testing. (line 12) * hasInterned_ifTrue_: Symbol class-symbol table. (line 6) * hasMethodReturn: BlockClosure-testing. (line 6) * hasMethods: Behavior-testing the method dictionary. (line 10) * hasPostData: NetClients.URL-accessing. (line 38) * hasPostData_: NetClients.URL-accessing. (line 43) * hasProxyFor_: ObjectDumper class-establishing proxy classes. (line 9) * hasQuery: NetClients.URL-testing. (line 14) * hasValue: Promise-accessing. (line 9) * height: Rectangle-accessing. (line 42) * height_: Rectangle-accessing. (line 45) * hereAssociationAt_: Dictionary-namespace protocol. (line 20) * hereAssociationAt_ifAbsent_: Dictionary-namespace protocol. (line 25) * hereAt_: Dictionary-namespace protocol. (line 31) * hereAt_ifAbsent_: Dictionary-namespace protocol. (line 36) * hierarchyIndent: Behavior-printing hierarchy. (line 6) * high: SystemExceptions.ArgumentOutOfRange-accessing. (line 9) * high_: SystemExceptions.ArgumentOutOfRange-accessing. (line 12) * highBit <1>: SmallInteger-bit arithmetic. (line 6) * highBit <2>: LargePositiveInteger-arithmetic. (line 15) * highBit <3>: LargeNegativeInteger-reverting to LargePositiveInteger. (line 16) * highBit: Integer-bit operators. (line 35) * highestPriority: ProcessorScheduler-priorities. (line 10) * highIOPriority: ProcessorScheduler-priorities. (line 6) * home <1>: MethodContext-accessing. (line 6) * home <2>: Directory class-reading system defaults. (line 9) * home <3>: ContextPart-accessing. (line 33) * home: BlockContext-accessing. (line 9) * host: NetClients.URL-accessing. (line 48) * host_: NetClients.URL-accessing. (line 51) * hostSystem: SystemDictionary-miscellaneous. (line 12) * hour <1>: Time-accessing (ANSI for DateAndTimes). (line 6) * hour: DateTime-computations. (line 13) * hour12 <1>: Time-accessing (ANSI for DateAndTimes). (line 9) * hour12: DateTime-computations. (line 16) * hour24 <1>: Time-accessing (ANSI for DateAndTimes). (line 12) * hour24: DateTime-computations. (line 19) * hour_: Time class-instance creation. (line 9) * hour_minute_second_: Time class-instance creation. (line 12) * hours: Time-accessing (non ANSI & for Durations). (line 15) * hours_: Time class-instance creation. (line 16) * hours_minutes_seconds_: Time class-instance creation. (line 19) * identityHash: Object-built ins. (line 88) * identityIncludes_ <1>: WeakIdentitySet-accessing. (line 6) * identityIncludes_ <2>: SequenceableCollection-basic. (line 53) * identityIncludes_ <3>: LinkedList-enumerating. (line 10) * identityIncludes_ <4>: IdentitySet-testing. (line 6) * identityIncludes_: Collection-testing collections. (line 10) * identityIndexOf_: SequenceableCollection-basic. (line 56) * identityIndexOf_ifAbsent_: SequenceableCollection-basic. (line 60) * identityIndexOf_startingAt_: SequenceableCollection-basic. (line 65) * identityIndexOf_startingAt_ifAbsent_: SequenceableCollection-basic. (line 69) * identityIndexOfLast_ifAbsent_: SequenceableCollection-basic. (line 74) * identityRemove_: OrderedCollection-removing. (line 6) * identityRemove_ifAbsent_: OrderedCollection-removing. (line 10) * idle: ProcessorScheduler-idle tasks. (line 6) * idleAdd_: ProcessorScheduler-idle tasks. (line 10) * idlePriority: ProcessorScheduler-priorities. (line 13) * ifCurtailed_: BlockClosure-unwind protection. (line 12) * ifError_: BlockClosure-exception handling. (line 6) * ifFalse_ <1>: True-basic. (line 18) * ifFalse_ <2>: False-basic. (line 16) * ifFalse_: Boolean-basic. (line 18) * ifFalse_ifTrue_ <1>: True-basic. (line 21) * ifFalse_ifTrue_ <2>: False-basic. (line 19) * ifFalse_ifTrue_: Boolean-basic. (line 22) * ifMatched_: RegexResults-testing. (line 6) * ifMatched_ifNotMatched_: RegexResults-testing. (line 10) * ifNil_ <1>: UndefinedObject-testing. (line 6) * ifNil_: Object-testing functionality. (line 6) * ifNil_ifNotNil_ <1>: UndefinedObject-testing. (line 9) * ifNil_ifNotNil_: Object-testing functionality. (line 9) * ifNil_ifNotNilDo_ <1>: UndefinedObject-iteration. (line 6) * ifNil_ifNotNilDo_: Iterable-iteration. (line 6) * ifNotMatched_: RegexResults-testing. (line 15) * ifNotMatched_ifMatched_: RegexResults-testing. (line 19) * ifNotNil_ <1>: UndefinedObject-testing. (line 13) * ifNotNil_: Object-testing functionality. (line 13) * ifNotNil_ifNil_ <1>: UndefinedObject-testing. (line 17) * ifNotNil_ifNil_: Object-testing functionality. (line 17) * ifNotNilDo_ <1>: UndefinedObject-iteration. (line 11) * ifNotNilDo_: Iterable-iteration. (line 11) * ifNotNilDo_ifNil_ <1>: UndefinedObject-iteration. (line 15) * ifNotNilDo_ifNil_: Iterable-iteration. (line 15) * ifTrue_ <1>: True-basic. (line 24) * ifTrue_ <2>: False-basic. (line 22) * ifTrue_: Boolean-basic. (line 26) * ifTrue_ifFalse_ <1>: True-basic. (line 27) * ifTrue_ifFalse_ <2>: False-basic. (line 25) * ifTrue_ifFalse_: Boolean-basic. (line 30) * ignoreCallouts: PackageLoader class-accessing. (line 36) * ignoreCallouts_: PackageLoader class-accessing. (line 39) * image <1>: File class-reading system defaults. (line 9) * image: Directory class-reading system defaults. (line 12) * imageLocal: SystemDictionary-testing. (line 6) * implementors: Symbol-accessing the method dictionary. (line 6) * implies_ <1>: SecurityPolicy-querying. (line 9) * implies_: Permission-testing. (line 9) * import_ <1>: ClassDescription-parsing class declarations. (line 10) * import_: AbstractNamespace-compiling. (line 10) * import_from_: BindingDictionary-accessing. (line 32) * includes_ <1>: SortedCollection-searching. (line 6) * includes_ <2>: SequenceableCollection-basic. (line 79) * includes_ <3>: LinkedList-enumerating. (line 13) * includes_ <4>: HashedCollection-testing collections. (line 18) * includes_ <5>: FilePath-accessing. (line 19) * includes_ <6>: Dictionary-dictionary testing. (line 6) * includes_ <7>: Collection-testing collections. (line 13) * includes_: Bag-testing collections. (line 12) * includesAllOf_: Collection-testing collections. (line 16) * includesAnyOf_: Collection-testing collections. (line 19) * includesAssociation_: Dictionary-dictionary testing. (line 9) * includesBehavior_: Behavior-testing the class hierarchy. (line 6) * includesClassNamed_: AbstractNamespace-namespace hierarchy. (line 23) * includesGlobalNamed_: AbstractNamespace-namespace hierarchy. (line 29) * includesKey_ <1>: WeakValueLookupTable-hacks. (line 14) * includesKey_ <2>: ProcessEnvironment-dictionary testing. (line 6) * includesKey_ <3>: Namespace-overrides for superspaces. (line 29) * includesKey_: Dictionary-dictionary testing. (line 13) * includesSelector_: Behavior-testing the method dictionary. (line 13) * incr: CObject-pointer-like behavior. (line 52) * incrBy_: CObject-pointer-like behavior. (line 56) * increment: Interval-printing. (line 9) * incrementalGCStep: ObjectMemory class-builtins. (line 60) * indexOf_: SequenceableCollection-basic. (line 82) * indexOf_ifAbsent_: SequenceableCollection-basic. (line 86) * indexOf_matchCase_startingAt_: CharacterArray-comparing. (line 29) * indexOf_startingAt_ <1>: String-basic. (line 14) * indexOf_startingAt_ <2>: SequenceableCollection-basic. (line 91) * indexOf_startingAt_: ByteArray-basic. (line 9) * indexOf_startingAt_ifAbsent_ <1>: String-basic. (line 18) * indexOf_startingAt_ifAbsent_ <2>: SortedCollection-searching. (line 10) * indexOf_startingAt_ifAbsent_ <3>: SequenceableCollection-basic. (line 95) * indexOf_startingAt_ifAbsent_ <4>: RunArray-searching. (line 6) * indexOf_startingAt_ifAbsent_: ByteArray-basic. (line 13) * indexOfInstVar_: Behavior-accessing instances and variables. (line 32) * indexOfInstVar_ifAbsent_: Behavior-accessing instances and variables. (line 36) * indexOfLast_ifAbsent_: SequenceableCollection-basic. (line 99) * indexOfMonth_: Date class-basic. (line 20) * indexOfRegex_: String-regex. (line 60) * indexOfRegex_from_to_: String-regex. (line 65) * indexOfRegex_from_to_ifAbsent_: String-regex. (line 70) * indexOfRegex_ifAbsent_: String-regex. (line 76) * indexOfRegex_startingAt_: String-regex. (line 81) * indexOfRegex_startingAt_ifAbsent_: String-regex. (line 86) * indexOfSubCollection_: SequenceableCollection-basic. (line 103) * indexOfSubCollection_ifAbsent_: SequenceableCollection-basic. (line 108) * indexOfSubCollection_startingAt_: SequenceableCollection-basic. (line 113) * indexOfSubCollection_startingAt_ifAbsent_: SequenceableCollection-basic. (line 118) * infinity <1>: FloatQ class-characterization. (line 29) * infinity <2>: FloatE class-characterization. (line 29) * infinity: FloatD class-characterization. (line 26) * inheritedKeys <1>: RootNamespace-overrides for superspaces. (line 6) * inheritedKeys <2>: Namespace-accessing. (line 6) * inheritedKeys: AbstractNamespace-overrides for superspaces. (line 6) * inheritsFrom_ <1>: UndefinedObject-still unclassified. (line 6) * inheritsFrom_ <2>: Dictionary-namespace protocol. (line 42) * inheritsFrom_: Behavior-testing the class hierarchy. (line 10) * inheritShape <1>: CObject class-subclass creation. (line 6) * inheritShape: Class-instance creation. (line 12) * initDayNameDict: Date class-basic. (line 23) * initForNanoseconds_: Delay-initialization. (line 6) * initialIP <1>: ContextPart-accessing. (line 36) * initialIP: BlockClosure-accessing. (line 24) * initialize <1>: VFS.FileWrapper class-initializing. (line 6) * initialize <2>: ValueHolder-initializing. (line 6) * initialize <3>: Time class-initialization. (line 6) * initialize <4>: SystemExceptions.ProcessBeingTerminated class-still unclassified. (line 6) * initialize <5>: SystemDictionary class-initialization. (line 6) * initialize <6>: Promise-initializing. (line 6) * initialize <7>: ProcessorScheduler-idle tasks. (line 13) * initialize <8>: ObjectMemory class-initialization. (line 9) * initialize <9>: Object class-initialization. (line 16) * initialize <10>: NetClients.URL-initialize-release. (line 6) * initialize <11>: NetClients.URL class-encoding URLs. (line 14) * initialize <12>: Namespace class-initialization. (line 6) * initialize <13>: Fraction class-instance creation. (line 6) * initialize <14>: FileStream-initialize-release. (line 6) * initialize <15>: FileStream class-file-in. (line 48) * initialize <16>: FileDescriptor-initialize-release. (line 9) * initialize <17>: FileDescriptor class-initialization. (line 6) * initialize <18>: File class-initialization. (line 6) * initialize <19>: Duration class-instance creation. (line 13) * initialize <20>: DLD class-dynamic linking. (line 25) * initialize <21>: DateTime class-information. (line 9) * initialize <22>: Date class-basic. (line 29) * initialize <23>: CType class-initialization. (line 6) * initialize <24>: Class-accessing instances and variables. (line 54) * initialize <25>: Class class-initialize. (line 6) * initialize: Character class-initializing lookup tables. (line 6) * initializeAsRootClass: Class-accessing instances and variables. (line 57) * initMonthNameDict: Date class-basic. (line 26) * initUntilNanoseconds_: Delay-instance creation. (line 6) * inject_into_ <1>: Iterable-enumeration. (line 57) * inject_into_: Generator class-instance creation. (line 6) * insetBy_: Rectangle-rectangle functions. (line 27) * insetOriginBy_corner_: Rectangle-rectangle functions. (line 33) * inspect: Object-debugging. (line 12) * instanceClass: Metaclass-accessing. (line 6) * instanceCount: Behavior-accessing instances and variables. (line 44) * instanceVariableNames_: Behavior-instance variables. (line 9) * instanceVariableString: ClassDescription-printing. (line 10) * instSize <1>: UndefinedObject-class polymorphism. (line 9) * instSize: Behavior-testing the form of the instances. (line 6) * instVarAt_: Object-built ins. (line 92) * instVarAt_put_: Object-built ins. (line 96) * instVarNamed_: Object-introspection. (line 6) * instVarNamed_put_: Object-introspection. (line 9) * instVarNames: Behavior-accessing instances and variables. (line 40) * intAt_ <1>: Memory class-accessing. (line 42) * intAt_: ByteArray-more advanced accessing. (line 35) * intAt_put_ <1>: Memory class-accessing. (line 45) * intAt_put_: ByteArray-more advanced accessing. (line 39) * integerPart <1>: ScaledDecimal-coercion. (line 36) * integerPart <2>: Number-truncation and round off. (line 16) * integerPart <3>: Fraction-converting. (line 21) * integerPart: Float-arithmetic. (line 6) * intern_: Symbol class-built ins. (line 6) * internCharacter_: Symbol class-instance creation. (line 6) * intersect_: Rectangle-rectangle functions. (line 38) * intersects_: Rectangle-testing. (line 21) * intervalAt_: RegexResults-accessing. (line 23) * invalidate: FileDescriptor-basic. (line 23) * ip: ContextPart-accessing. (line 40) * ip_: ContextPart-accessing. (line 43) * isAbsolute <1>: VFS.FileWrapper-testing. (line 10) * isAbsolute <2>: VFS.ArchiveMember-still unclassified. (line 13) * isAbsolute <3>: FilePath-testing. (line 10) * isAbsolute <4>: File-testing. (line 10) * isAbsolute <5>: Delay-accessing. (line 15) * isAbsolute: CObject-accessing. (line 15) * isAbsolute_: FilePath class-still unclassified. (line 6) * isAbstract: CompiledMethod-testing. (line 14) * isAccessible <1>: VFS.FileWrapper-testing. (line 13) * isAccessible <2>: VFS.ArchiveMember-testing. (line 10) * isAccessible <3>: VFS.ArchiveFile-querying. (line 6) * isAccessible <4>: FilePath-testing. (line 13) * isAccessible: File-testing. (line 13) * isAccessible_: File class-testing. (line 9) * isActive: Delay-testing. (line 6) * isAlive_: WeakArray-accessing. (line 36) * isAllowing: Permission-accessing. (line 27) * isAlphaNumeric: Character-testing. (line 6) * isAnnotated <1>: CompiledMethod-attributes. (line 22) * isAnnotated: CompiledCode-accessing. (line 22) * isArray <1>: Object-testing functionality. (line 21) * isArray: Array-testing. (line 6) * isBehavior <1>: Object-testing functionality. (line 24) * isBehavior: Behavior-testing functionality. (line 6) * isBinary: FileDescriptor-class type methods. (line 6) * isBits: Behavior-testing the form of the instances. (line 10) * isBitSet_: Integer-bit operators. (line 38) * isBlock <1>: MethodContext-accessing. (line 10) * isBlock <2>: ContextPart-accessing. (line 46) * isBlock: BlockContext-accessing. (line 13) * isCharacter <1>: Object-testing functionality. (line 30) * isCharacter: Character-testing functionality. (line 6) * isCharacterArray <1>: Object-testing functionality. (line 33) * isCharacterArray: CharacterArray-testing functionality. (line 6) * isClass <1>: Object-testing functionality. (line 36) * isClass: Class-testing functionality. (line 9) * isCObject <1>: Object-testing functionality. (line 27) * isCObject: CObject-testing functionality. (line 6) * isDefined: VariableBinding-testing. (line 6) * isDigit: Character-testing. (line 9) * isDigit_: Character-testing. (line 12) * isDirectory <1>: VFS.FileWrapper-testing. (line 17) * isDirectory <2>: VFS.ArchiveMember-testing. (line 14) * isDirectory <3>: VFS.ArchiveFile-querying. (line 10) * isDirectory <4>: FilePath-testing. (line 17) * isDirectory: File-accessing. (line 19) * isDisabled <1>: MethodContext-accessing. (line 13) * isDisabled <2>: ContextPart-accessing. (line 49) * isDisabled: BlockContext-accessing. (line 16) * isEmpty <1>: SharedQueue-accessing. (line 6) * isEmpty <2>: PositionableStream-testing. (line 13) * isEmpty <3>: LinkedList-testing. (line 6) * isEmpty <4>: Interval-basic. (line 22) * isEmpty <5>: HashedCollection-testing collections. (line 21) * isEmpty <6>: FileDescriptor-overriding inherited methods. (line 6) * isEmpty: Collection-testing collections. (line 22) * isEnvironment <1>: MethodContext-accessing. (line 20) * isEnvironment <2>: ContextPart-accessing. (line 57) * isEnvironment: BlockContext-accessing. (line 23) * isExact <1>: Number-testing. (line 14) * isExact <2>: Interval-testing. (line 12) * isExact: Float-testing. (line 6) * isExecutable <1>: VFS.FileWrapper-delegation. (line 15) * isExecutable <2>: VFS.ArchiveMember-testing. (line 18) * isExecutable <3>: FilePath-testing. (line 21) * isExecutable: File-testing. (line 17) * isExecutable_: File class-testing. (line 13) * isExternalStream <1>: Stream-testing. (line 9) * isExternalStream <2>: PositionableStream-class type methods. (line 6) * isExternalStream: FileDescriptor-class type methods. (line 9) * isFile: FilePath-testing. (line 25) * isFileScheme: NetClients.URL-testing. (line 18) * isFileSystemPath <1>: FilePath-testing. (line 29) * isFileSystemPath: File-testing. (line 21) * isFinite <1>: Number-testing. (line 20) * isFinite: Float-testing. (line 10) * isFixed: Behavior-testing the form of the instances. (line 14) * isFloat <1>: Object-testing functionality. (line 39) * isFloat: Float-testing functionality. (line 6) * isFragmentOnly: NetClients.URL-testing. (line 21) * isFunction_: CFunctionDescriptor class-testing. (line 10) * isIdentity <1>: SmallInteger class-testing. (line 6) * isIdentity <2>: Boolean class-testing. (line 6) * isIdentity: Behavior-testing the form of the instances. (line 18) * isImmediate <1>: Number class-testing. (line 6) * isImmediate <2>: Character class-testing. (line 6) * isImmediate <3>: Boolean class-testing. (line 9) * isImmediate <4>: BlockClosure class-testing. (line 6) * isImmediate: Behavior-testing the form of the instances. (line 21) * isInfinite <1>: Number-testing. (line 25) * isInfinite: Float-testing. (line 13) * isInPath: Package-still unclassified. (line 12) * isInteger <1>: Object-testing functionality. (line 42) * isInteger: Integer-testing functionality. (line 6) * isInternalExceptionHandlingContext <1>: MethodContext-debugging. (line 6) * isInternalExceptionHandlingContext <2>: ContextPart-debugging. (line 25) * isInternalExceptionHandlingContext: BlockContext-debugging. (line 6) * isKindOf_: Object-testing functionality. (line 45) * isLeapYear: Date-date computations. (line 44) * isLetter: Character-testing. (line 16) * isLiteralObject <1>: VariableBinding-storing. (line 6) * isLiteralObject <2>: UndefinedObject-storing. (line 6) * isLiteralObject <3>: String-printing. (line 15) * isLiteralObject <4>: ScaledDecimal-storing. (line 6) * isLiteralObject <5>: Integer-printing. (line 12) * isLiteralObject <6>: Float-storing. (line 6) * isLiteralObject <7>: Character-storing. (line 6) * isLiteralObject <8>: ByteArray-storing. (line 6) * isLiteralObject <9>: Boolean-storing. (line 6) * isLiteralObject: Array-printing. (line 6) * isLowercase: Character-testing. (line 19) * isMemberOf_: Object-testing functionality. (line 49) * isMeta: Object-testing functionality. (line 52) * isMetaclass: Object-testing functionality. (line 58) * isMetaClass: Object-testing functionality. (line 55) * isMetaclass: Metaclass-testing functionality. (line 9) * isNamespace <1>: Object-testing functionality. (line 61) * isNamespace: AbstractNamespace-testing. (line 6) * isNaN <1>: Number-testing. (line 30) * isNaN: Float-testing. (line 17) * isNested: Exception-exception handling. (line 9) * isNil <1>: UndefinedObject-testing. (line 21) * isNil: Object-testing functionality. (line 64) * isNull <1>: UndefinedObject-testing. (line 25) * isNull: CObject-testing. (line 6) * isNumber <1>: Object-testing functionality. (line 67) * isNumber: Number-testing. (line 35) * isNumeric: CharacterArray-converting. (line 48) * isOldSyntax: CompiledMethod-accessing. (line 16) * isOpen: FileDescriptor-accessing. (line 30) * isOwnerProcess: RecursionLock-accessing. (line 6) * isPathSeparator: Character-testing. (line 22) * isPeerAlive: FileDescriptor-accessing. (line 33) * isPipe: FileDescriptor-accessing. (line 37) * isPointers: Behavior-testing the form of the instances. (line 24) * isPositionable <1>: Stream-positioning. (line 6) * isPositionable <2>: PositionableStream-positioning. (line 9) * isPositionable: FileDescriptor-positioning. (line 6) * isProcess: ContextPart-accessing. (line 64) * isPunctuation: Character-testing. (line 26) * isRational <1>: Number-testing. (line 38) * isRational <2>: Integer-testing functionality. (line 9) * isRational: Fraction-testing. (line 6) * isReadable <1>: VFS.FileWrapper-delegation. (line 19) * isReadable <2>: VFS.ArchiveMember-testing. (line 22) * isReadable <3>: FilePath-testing. (line 32) * isReadable: File-testing. (line 24) * isReadable_: File class-testing. (line 17) * isReadOnly: Object-built ins. (line 100) * isRelative: FilePath-testing. (line 36) * isResumable <1>: SystemExceptions.PackageNotAvailable-description. (line 6) * isResumable <2>: Notification-exception description. (line 13) * isResumable <3>: MessageNotUnderstood-description. (line 9) * isResumable <4>: Halt-description. (line 9) * isResumable <5>: Exception-exception description. (line 12) * isResumable <6>: Error-exception description. (line 9) * isResumable: ArithmeticError-description. (line 9) * isSeparator: Character-testing. (line 29) * isSequenceable <1>: Stream-testing. (line 13) * isSequenceable <2>: SequenceableCollection-testing. (line 16) * isSequenceable: Collection-testing collections. (line 25) * isSimpleSymbol: Symbol-testing. (line 6) * isSmall: LargePositiveInteger-primitive operations. (line 11) * isSmallInteger <1>: SmallInteger-testing functionality. (line 6) * isSmallInteger: Object-testing functionality. (line 70) * isSmalltalk <1>: SystemDictionary-testing. (line 10) * isSmalltalk: AbstractNamespace-testing. (line 9) * isSocket: File-accessing. (line 22) * isString <1>: Symbol-testing functionality. (line 6) * isString <2>: String-testing functionality. (line 6) * isString: Object-testing functionality. (line 73) * isSymbol <1>: Symbol-testing functionality. (line 9) * isSymbol: Object-testing functionality. (line 76) * isSymbolicLink <1>: VFS.FileWrapper-testing. (line 21) * isSymbolicLink <2>: VFS.ArchiveMember-testing. (line 26) * isSymbolicLink <3>: FilePath-testing. (line 39) * isSymbolicLink: File-accessing. (line 25) * isSymbolString_: Symbol class-symbol table. (line 14) * isText: FileDescriptor-class type methods. (line 12) * isTimeoutProgrammed: ProcessorScheduler-timed invocation. (line 6) * isUnicode <1>: UnicodeString class-multibyte encodings. (line 11) * isUnicode <2>: String class-multibyte encodings. (line 6) * isUnicode <3>: Stream-character writing. (line 15) * isUnicode <4>: Iterable class-multibyte encodings. (line 6) * isUnicode <5>: Collection class-multibyte encodings. (line 6) * isUnicode <6>: CharacterArray-multibyte encodings. (line 9) * isUnicode: CharacterArray class-multibyte encodings. (line 6) * isUntrusted: Object-built ins. (line 104) * isUnwind <1>: MethodContext-accessing. (line 27) * isUnwind <2>: ContextPart-accessing. (line 71) * isUnwind: BlockContext-accessing. (line 30) * isUppercase: Character-testing. (line 32) * isValid: CCallable-accessing. (line 6) * isValidCCall: CompiledMethod-c call-outs. (line 6) * isVariable: Behavior-testing the form of the instances. (line 28) * isVowel: Character-testing. (line 35) * isWriteable <1>: VFS.FileWrapper-delegation. (line 23) * isWriteable <2>: VFS.ArchiveMember-testing. (line 30) * isWriteable <3>: FilePath-testing. (line 43) * isWriteable: File-testing. (line 28) * isWriteable_: File class-testing. (line 20) * isZero: Duration-arithmetics. (line 30) * join: Collection-concatenating. (line 6) * join_ <1>: SequenceableCollection-concatenating. (line 6) * join_ <2>: Collection class-instance creation. (line 12) * join_: ArrayedCollection class-instance creation. (line 6) * join_separatedBy_ <1>: SequenceableCollection class-instance creation. (line 6) * join_separatedBy_: ArrayedCollection class-instance creation. (line 10) * jumpDestinationAt_forward_: CompiledCode-testing accesses. (line 22) * kernel: Directory class-reading system defaults. (line 15) * key: LookupKey-accessing. (line 6) * key_ <1>: ProcessVariable class-accessing. (line 6) * key_ <2>: LookupKey-accessing. (line 9) * key_: LookupKey class-basic. (line 6) * key_class_defaultDictionary_: DeferredVariableBinding class-basic. (line 6) * key_value_ <1>: Association-accessing. (line 14) * key_value_: Association class-basic. (line 6) * key_value_environment_: HomedAssociation class-basic. (line 6) * keyAtValue_: Dictionary-accessing. (line 48) * keyAtValue_ifAbsent_: Dictionary-accessing. (line 52) * keys <1>: SequenceableCollection-enumerating. (line 55) * keys <2>: ProcessEnvironment-accessing. (line 36) * keys <3>: MappedCollection-basic. (line 40) * keys: Dictionary-accessing. (line 57) * keysAndValuesDo_ <1>: SequenceableCollection-enumerating. (line 59) * keysAndValuesDo_ <2>: Namespace-overrides for superspaces. (line 33) * keysAndValuesDo_ <3>: MappedCollection-basic. (line 43) * keysAndValuesDo_ <4>: LookupTable-enumerating. (line 12) * keysAndValuesDo_: Dictionary-dictionary enumerating. (line 17) * keysDo_ <1>: Namespace-overrides for superspaces. (line 37) * keysDo_ <2>: MappedCollection-basic. (line 47) * keysDo_ <3>: LookupTable-enumerating. (line 16) * keysDo_: Dictionary-dictionary enumerating. (line 21) * keywords: Symbol-basic. (line 10) * kindOfSubclass: Behavior-testing the class hierarchy. (line 13) * largeNegated: LargeInteger-primitive operations. (line 12) * largest: SmallInteger class-getting limits. (line 10) * last <1>: SortedCollection-basic. (line 6) * last <2>: SequenceableCollection-basic. (line 123) * last <3>: RunArray-basic. (line 9) * last <4>: OrderedCollection-accessing. (line 16) * last <5>: LinkedList-iteration. (line 10) * last: Interval-printing. (line 12) * last_: SequenceableCollection-basic. (line 126) * lastAccessTime <1>: VFS.FileWrapper-delegation. (line 27) * lastAccessTime <2>: VFS.ArchiveMember-accessing. (line 19) * lastAccessTime <3>: FilePath-accessing. (line 23) * lastAccessTime: File-accessing. (line 28) * lastAccessTime_: FilePath-accessing. (line 26) * lastAccessTime_lastModifyTime_ <1>: VFS.FileWrapper-accessing. (line 13) * lastAccessTime_lastModifyTime_ <2>: FilePath-accessing. (line 30) * lastAccessTime_lastModifyTime_: File-file operations. (line 6) * lastChangeTime <1>: VFS.FileWrapper-delegation. (line 30) * lastChangeTime <2>: VFS.ArchiveMember-accessing. (line 22) * lastChangeTime <3>: FilePath-accessing. (line 34) * lastChangeTime: File-accessing. (line 31) * lastDayOfMonth: Date-date computations. (line 47) * lastModifyTime <1>: VFS.FileWrapper-delegation. (line 36) * lastModifyTime <2>: VFS.ArchiveMember-accessing. (line 28) * lastModifyTime <3>: FilePath-accessing. (line 40) * lastModifyTime: File-accessing. (line 37) * lastModifyTime_: FilePath-accessing. (line 44) * lcm_: Integer-math methods. (line 29) * left: Rectangle-accessing. (line 48) * left_: Rectangle-accessing. (line 51) * left_right_top_bottom_: Rectangle class-instance creation. (line 6) * left_top_right_bottom_ <1>: Rectangle-accessing. (line 54) * left_top_right_bottom_: Rectangle class-instance creation. (line 9) * leftCenter: Rectangle-accessing. (line 57) * lf: Character class-constants. (line 27) * libexec: Directory class-reading system defaults. (line 20) * libraries: Package-accessing. (line 80) * librariesFor_: PackageLoader class-accessing. (line 42) * libraryList: DLD class-dynamic linking. (line 28) * lineDelimiter: CharacterArray class-basic. (line 10) * lines <1>: Stream-filtering. (line 17) * lines: CharacterArray-string processing. (line 53) * linesDo_ <1>: Stream-enumerating. (line 9) * linesDo_: CharacterArray-string processing. (line 57) * link <1>: CFunctionDescriptor-restoring. (line 6) * link <2>: CCallbackDescriptor-restoring. (line 6) * link: CCallable-restoring. (line 6) * literalAt_: CompiledCode-accessing. (line 25) * literalAt_put_: CompiledCode-accessing. (line 28) * literalEquals_ <1>: VariableBinding-compiler. (line 6) * literalEquals_ <2>: Object-compiler. (line 6) * literalEquals_ <3>: Float-compiler. (line 6) * literalEquals_ <4>: Collection-compiler. (line 6) * literalEquals_: ArrayedCollection-compiler. (line 6) * literalHash <1>: VariableBinding-compiler. (line 9) * literalHash <2>: Object-compiler. (line 9) * literalHash <3>: Float-compiler. (line 9) * literalHash <4>: Collection-compiler. (line 9) * literalHash: ArrayedCollection-compiler. (line 9) * literals: CompiledCode-accessing. (line 31) * literals_numArgs_numTemps_attributes_bytecodes_depth_: CompiledMethod class-instance creation. (line 6) * literalsDo_: CompiledCode-literals - iteration. (line 13) * ln <1>: Number-misc math. (line 51) * ln: Float-built ins. (line 29) * ln10 <1>: FloatQ class-characterization. (line 32) * ln10 <2>: FloatE class-characterization. (line 32) * ln10: Float class-characterization. (line 23) * load: ObjectDumper-loading/dumping objects. (line 10) * loadFrom_ <1>: VersionableObjectProxy class-saving and restoring. (line 6) * loadFrom_ <2>: ObjectDumper class-shortcuts. (line 9) * loadFrom_ <3>: NullProxy class-instance creation. (line 6) * loadFrom_: DumperProxy class-accessing. (line 10) * localKernel: Directory class-reading system defaults. (line 23) * lock: Semaphore-builtins. (line 6) * log <1>: Number-misc math. (line 54) * log: Float-transcendental operations. (line 20) * log10Base2 <1>: FloatQ class-characterization. (line 35) * log10Base2 <2>: FloatE class-characterization. (line 35) * log10Base2: Float class-characterization. (line 26) * log_ <1>: Number-misc math. (line 57) * log_: Float-misc math. (line 6) * longAt_ <1>: Memory class-accessing. (line 49) * longAt_: ByteArray-more advanced accessing. (line 44) * longAt_put_ <1>: Memory class-accessing. (line 52) * longAt_put_: ByteArray-more advanced accessing. (line 48) * longDoubleAt_ <1>: Memory class-accessing. (line 56) * longDoubleAt_: ByteArray-more advanced accessing. (line 53) * longDoubleAt_put_ <1>: Memory class-accessing. (line 59) * longDoubleAt_put_: ByteArray-more advanced accessing. (line 57) * lookupAllSelectors_: Behavior-accessing the method dictionary. (line 25) * lookupSelector_: Behavior-accessing the method dictionary. (line 29) * low: SystemExceptions.ArgumentOutOfRange-accessing. (line 15) * low_: SystemExceptions.ArgumentOutOfRange-accessing. (line 18) * lowBit <1>: SmallInteger-bit arithmetic. (line 9) * lowBit <2>: LargeInteger-bit operations. (line 24) * lowBit: Integer-bit operators. (line 41) * lowerPriority: Process-basic. (line 17) * lowestPriority: ProcessorScheduler-priorities. (line 22) * lowIOPriority: ProcessorScheduler-priorities. (line 16) * makeEphemeron: Object-built ins. (line 107) * makeFixed: Object-built ins. (line 112) * makeReadOnly_: Object-built ins. (line 115) * makeUntrusted_ <1>: Process-basic. (line 21) * makeUntrusted_: Object-built ins. (line 118) * makeWeak: Object-built ins. (line 121) * map: MappedCollection-basic. (line 51) * mark: MethodContext-accessing. (line 33) * mark_: Object-built ins. (line 127) * match: RegexResults-accessing. (line 28) * match_: CharacterArray-comparing. (line 38) * match_ignoreCase_: CharacterArray-comparing. (line 43) * matched: RegexResults-testing. (line 24) * matchInterval: RegexResults-accessing. (line 32) * matchRegex_: String-regex. (line 92) * matchRegex_from_to_: String-regex. (line 97) * max_ <1>: Point-comparing. (line 23) * max_ <2>: Number-comparing. (line 6) * max_ <3>: Magnitude-misc methods. (line 9) * max_: Float-comparing. (line 6) * member_do_: VFS.ArchiveFile-ArchiveMember protocol. (line 12) * member_mode_ <1>: VFS.ZipFile-members. (line 19) * member_mode_: VFS.ArchiveFile-ArchiveMember protocol. (line 16) * merge_: Rectangle-rectangle functions. (line 42) * meridianAbbreviation: DateTime-computations. (line 22) * message <1>: TextCollector-set up. (line 6) * message: MessageNotUnderstood-accessing. (line 6) * message_ <1>: TextCollector-set up. (line 11) * message_: TextCollector class-accessing. (line 6) * messageText <1>: SystemExceptions.WrongMessageSent-accessing. (line 6) * messageText <2>: SystemExceptions.WrongClass-accessing. (line 9) * messageText <3>: SystemExceptions.NotEnoughElements-accessing. (line 9) * messageText <4>: SystemExceptions.InvalidValue-accessing. (line 9) * messageText <5>: SystemExceptions.InvalidState-accessing. (line 6) * messageText <6>: SystemExceptions.InvalidArgument-accessing. (line 6) * messageText <7>: SystemExceptions.IndexOutOfRange-accessing. (line 15) * messageText: Exception-accessing. (line 9) * messageText_: Exception-accessing. (line 12) * metaclassFor_: UndefinedObject-class polymorphism. (line 12) * method <1>: ContextPart-accessing. (line 77) * method <2>: CompiledMethod-accessing. (line 20) * method <3>: CompiledCode-accessing. (line 35) * method <4>: CompiledBlock-accessing. (line 11) * method: BlockClosure-accessing. (line 27) * methodCategory <1>: CompiledMethod-accessing. (line 23) * methodCategory <2>: CompiledCode-basic. (line 14) * methodCategory: CompiledBlock-basic. (line 9) * methodCategory_ <1>: CompiledMethod-accessing. (line 26) * methodCategory_ <2>: CompiledCode-basic. (line 17) * methodCategory_: CompiledBlock-basic. (line 12) * methodClass <1>: MethodInfo-accessing. (line 12) * methodClass <2>: ContextPart-accessing. (line 80) * methodClass <3>: CompiledMethod-accessing. (line 29) * methodClass <4>: CompiledCode-accessing. (line 39) * methodClass: CompiledBlock-accessing. (line 14) * methodClass_ <1>: MethodInfo-accessing. (line 15) * methodClass_ <2>: CompiledMethod-accessing. (line 32) * methodClass_ <3>: CompiledCode-accessing. (line 42) * methodClass_: CompiledBlock-accessing. (line 17) * methodDictionary <1>: UndefinedObject-class polymorphism. (line 16) * methodDictionary: Behavior-method dictionary. (line 66) * methodDictionary_: Behavior-method dictionary. (line 70) * methodFormattedSourceString: CompiledMethod-compiling. (line 6) * methodParseNode: CompiledMethod-compiling. (line 10) * methodRecompilationSourceString: CompiledMethod-source code. (line 6) * methods: Behavior-compilation (alternative). (line 6) * methodsFor: Behavior-compilation (alternative). (line 9) * methodsFor_: Behavior-compiling methods. (line 6) * methodsFor_ifFeatures_: Behavior-compilation (alternative). (line 12) * methodsFor_ifTrue_: Behavior-built ins. (line 21) * methodsFor_stamp_: Behavior-compilation (alternative). (line 16) * methodSourceCode <1>: CompiledMethod-source code. (line 10) * methodSourceCode <2>: CompiledCode-basic. (line 20) * methodSourceCode: CompiledBlock-basic. (line 15) * methodSourceFile <1>: CompiledMethod-source code. (line 13) * methodSourceFile <2>: CompiledCode-basic. (line 23) * methodSourceFile: CompiledBlock-basic. (line 18) * methodSourcePos <1>: CompiledMethod-source code. (line 16) * methodSourcePos <2>: CompiledCode-basic. (line 26) * methodSourcePos: CompiledBlock-basic. (line 21) * methodSourceString <1>: CompiledMethod-source code. (line 20) * methodSourceString <2>: CompiledCode-basic. (line 30) * methodSourceString: CompiledBlock-basic. (line 25) * midnight: Time class-basic (UTC). (line 6) * millisecondClock: Time class-clocks. (line 6) * millisecondClockValue: Time class-clocks. (line 9) * milliseconds_: Duration class-instance creation. (line 16) * millisecondsPerDay: Time class-clocks. (line 12) * millisecondsToRun_: Time class-clocks. (line 15) * min_ <1>: Point-comparing. (line 27) * min_ <2>: Number-comparing. (line 11) * min_ <3>: Magnitude-misc methods. (line 12) * min_: Float-comparing. (line 11) * minute <1>: Time-accessing (ANSI for DateAndTimes). (line 15) * minute: DateTime-computations. (line 25) * minute_: Time class-instance creation. (line 23) * minutes: Time-accessing (non ANSI & for Durations). (line 18) * minutes_: Time class-instance creation. (line 26) * mode <1>: VFS.FileWrapper-delegation. (line 40) * mode <2>: VFS.ArchiveMember-testing. (line 34) * mode <3>: FilePath-accessing. (line 48) * mode: File-accessing. (line 41) * mode_ <1>: VFS.FileWrapper-delegation. (line 43) * mode_ <2>: VFS.ArchiveMember-testing. (line 37) * mode_ <3>: FilePath-accessing. (line 51) * mode_: File-accessing. (line 44) * module: Directory class-reading system defaults. (line 27) * moduleList: DLD class-dynamic linking. (line 31) * modules: Package-accessing. (line 84) * modulesFor_: PackageLoader class-accessing. (line 47) * month: Date-date computations. (line 51) * monthAbbreviation: Date-date computations. (line 54) * monthIndex: Date-date computations. (line 58) * monthName: Date-date computations. (line 61) * mourn <1>: Object-finalization. (line 13) * mourn <2>: HomedAssociation-finalization. (line 6) * mourn: Association-finalization. (line 6) * mourn_: Collection-finalization. (line 6) * moveBy_: Rectangle-transforming. (line 6) * moveTo_: Rectangle-transforming. (line 10) * multiBecome_: Array-mutating objects. (line 6) * multiply_: LargePositiveInteger-primitive operations. (line 15) * mustBeBoolean: Object-VM callbacks. (line 9) * name <1>: VFS.FileWrapper-accessing. (line 17) * name <2>: VFS.ArchiveMember-accessing. (line 32) * name <3>: Stream-accessing-reading. (line 13) * name <4>: Semaphore-accessing. (line 6) * name <5>: RecursionLock-accessing. (line 9) * name <6>: Process-accessing. (line 9) * name <7>: PositionableStream-compiling. (line 6) * name <8>: Permission-accessing. (line 30) * name <9>: Metaclass-delegation. (line 44) * name <10>: FilePath-file name management. (line 21) * name <11>: FileDescriptor-accessing. (line 40) * name <12>: File-accessing. (line 48) * name <13>: Class-accessing instances and variables. (line 60) * name <14>: CFunctionDescriptor-accessing. (line 6) * name <15>: BindingDictionary-accessing. (line 37) * name <16>: Behavior-support for lightweight classes. (line 16) * name: AbstractNamespace-printing. (line 6) * name_ <1>: VFS.ArchiveMember-accessing. (line 35) * name_ <2>: Semaphore-accessing. (line 9) * name_ <3>: RecursionLock-accessing. (line 12) * name_ <4>: Process-accessing. (line 12) * name_ <5>: Permission-accessing. (line 33) * name_ <6>: File class-instance creation. (line 6) * name_ <7>: CFunctionDescriptor-accessing. (line 10) * name_: AbstractNamespace-printing. (line 9) * name_environment_subclassOf_: Metaclass-basic. (line 6) * name_environment_subclassOf_instanceVariableArray_shape_classPool_poolDictionaries_category_: Metaclass-basic. (line 12) * name_environment_subclassOf_instanceVariableNames_shape_classVariableNames_poolDictionaries_category_: Metaclass-basic. (line 16) * name_target_action_: Permission class-testing. (line 24) * name_target_actions_: Permission class-testing. (line 27) * nameAt_ <1>: VFS.ArchiveFile-directory operations. (line 10) * nameAt_: FilePath-directory operations. (line 12) * nameIn_ <1>: SystemDictionary-printing. (line 6) * nameIn_ <2>: RootNamespace-printing. (line 6) * nameIn_ <3>: Namespace-printing. (line 6) * nameIn_ <4>: Metaclass-printing. (line 6) * nameIn_ <5>: ClassDescription-printing. (line 14) * nameIn_ <6>: BindingDictionary-accessing. (line 41) * nameIn_ <7>: Behavior-support for lightweight classes. (line 21) * nameIn_: AbstractNamespace-printing. (line 12) * nameOfDay_: Date class-basic. (line 32) * nameOfMonth_: Date class-basic. (line 35) * namesDo_ <1>: VFS.FileWrapper-enumerating. (line 6) * namesDo_ <2>: VFS.ArchiveMember-directory operations. (line 13) * namesDo_ <3>: VFS.ArchiveFile-directory operations. (line 14) * namesDo_ <4>: FilePath-enumerating. (line 42) * namesDo_: File-directory operations. (line 9) * namesMatching_do_: FilePath-enumerating. (line 47) * namespace: Package-accessing. (line 88) * namespace_: Package-accessing. (line 91) * nan <1>: FloatQ class-characterization. (line 38) * nan <2>: FloatE class-characterization. (line 38) * nan: FloatD class-characterization. (line 29) * nanosecondClock: Time class-clocks. (line 18) * nanosecondClockValue: Time class-clocks. (line 21) * narrow <1>: UndefinedObject-CObject interoperability. (line 9) * narrow: CObject-conversion. (line 10) * negated <1>: Number-misc math. (line 60) * negated <2>: LargeInteger-arithmetic. (line 34) * negated <3>: Fraction-optimized cases. (line 6) * negated <4>: Float-arithmetic. (line 9) * negated: Duration-arithmetics. (line 34) * negative <1>: Number-testing. (line 41) * negative <2>: LargePositiveInteger-numeric testing. (line 9) * negative <3>: LargeNegativeInteger-numeric testing. (line 9) * negative <4>: Float-testing. (line 20) * negative: Duration-arithmetics. (line 38) * negativeInfinity <1>: FloatQ class-characterization. (line 42) * negativeInfinity <2>: FloatE class-characterization. (line 42) * negativeInfinity: FloatD class-characterization. (line 33) * new <1>: ZeroDivide class-instance creation. (line 10) * new <2>: WeakArray class-instance creation. (line 6) * new <3>: ValueHolder class-creating instances. (line 6) * new <4>: ValueAdaptor class-creating instances. (line 6) * new <5>: Time class-instance creation. (line 29) * new <6>: TextCollector class-accessing. (line 12) * new <7>: SystemExceptions.MutationError class-instance creation. (line 6) * new <8>: Symbol class-instance creation. (line 9) * new <9>: SortedCollection class-instance creation. (line 6) * new <10>: SharedQueue class-instance creation. (line 6) * new <11>: Semaphore class-instance creation. (line 10) * new <12>: RunArray class-instance creation. (line 6) * new <13>: Regex class-instance creation. (line 9) * new <14>: RecursionLock class-instance creation. (line 6) * new <15>: Rectangle class-instance creation. (line 12) * new <16>: Random class-instance creation. (line 6) * new <17>: ProcessVariable class-accessing. (line 13) * new <18>: ProcessorScheduler class-instance creation. (line 6) * new <19>: ProcessEnvironment class-disabled. (line 6) * new <20>: Point class-instance creation. (line 6) * new <21>: OrderedCollection class-instance creation. (line 6) * new <22>: ObjectDumper class-instance creation. (line 6) * new <23>: NullValueHolder class-creating instances. (line 6) * new <24>: NetClients.URL class-instance creation. (line 9) * new <25>: Namespace class-disabling instance creation. (line 6) * new <26>: MappedCollection class-instance creation. (line 10) * new <27>: LookupTable class-instance creation. (line 6) * new <28>: HashedCollection class-instance creation. (line 6) * new <29>: ExceptionSet class-instance creation. (line 6) * new <30>: Exception class-instance creation. (line 6) * new <31>: Dictionary class-instance creation. (line 11) * new <32>: CType-C instance creation. (line 22) * new <33>: CObject class-instance creation. (line 18) * new <34>: CCompound class-instance creation. (line 10) * new <35>: Behavior-builtin. (line 15) * new <36>: Bag class-basic. (line 6) * new: AbstractNamespace class-instance creation. (line 6) * new_ <1>: WeakArray class-instance creation. (line 9) * new_ <2>: Symbol class-instance creation. (line 12) * new_ <3>: SortedCollection class-instance creation. (line 9) * new_ <4>: RunArray class-instance creation. (line 9) * new_ <5>: RootNamespace class-instance creation. (line 6) * new_ <6>: OrderedCollection class-instance creation. (line 9) * new_ <7>: Namespace class-disabling instance creation. (line 9) * new_ <8>: LargeArrayedCollection class-instance creation. (line 6) * new_ <9>: HashedCollection class-instance creation. (line 9) * new_ <10>: CType-accessing. (line 17) * new_ <11>: CObject class-instance creation. (line 21) * new_ <12>: Behavior-builtin. (line 18) * new_: Bag class-basic. (line 9) * new_header_literals_: CompiledCode class-instance creation. (line 6) * new_header_method_: CompiledBlock class-instance creation. (line 6) * new_header_numLiterals_: CompiledCode class-instance creation. (line 10) * new_withAll_: ArrayedCollection class-instance creation. (line 15) * newBuffer: FileStream-buffering. (line 21) * newCollection_ <1>: LargeWordArray-overridden. (line 9) * newCollection_ <2>: LargeByteArray-overridden. (line 13) * newCollection_: LargeArray-overridden. (line 6) * newDay_month_year_: Date class-instance creation (Blue Book). (line 19) * newDay_monthIndex_year_: Date class-instance creation (Blue Book). (line 23) * newDay_year_: Date class-instance creation (Blue Book). (line 27) * newFromNumber_scale_: ScaledDecimal class-instance creation. (line 6) * newInFixedSpace: Behavior-instance creation. (line 6) * newInFixedSpace_: Behavior-instance creation. (line 12) * newMeta_environment_subclassOf_instanceVariableArray_shape_classPool_poolDictionaries_category_: Metaclass-basic. (line 20) * newPage: Character class-constants. (line 30) * newProcess <1>: DirectedMessage-multiple process. (line 13) * newProcess: BlockClosure-multiple process. (line 17) * newProcessWith_: BlockClosure-multiple process. (line 22) * newsGroup: NetClients.URL-accessing. (line 54) * newStruct_declaration_: CCompound class-subclass creation. (line 32) * next <1>: Stream-accessing-reading. (line 16) * next <2>: SharedQueue-accessing. (line 9) * next <3>: Random-basic. (line 12) * next <4>: Random class-shortcuts. (line 9) * next <5>: PositionableStream-accessing-reading. (line 19) * next <6>: ObjectDumper-stream interface. (line 9) * next <7>: Generator-stream protocol. (line 9) * next <8>: FileStream-basic. (line 13) * next: FileDescriptor-basic. (line 26) * next_: Stream-accessing-reading. (line 19) * next_bufferAll_startingAt_: FileStream-buffering. (line 24) * next_into_startingAt_: Stream-buffering. (line 6) * next_put_ <1>: TextCollector-accessing. (line 16) * next_put_: Stream-accessing-writing. (line 6) * next_putAll_startingAt_ <1>: WriteStream-accessing-writing. (line 10) * next_putAll_startingAt_ <2>: TextCollector-accessing. (line 19) * next_putAll_startingAt_ <3>: Stream-accessing-writing. (line 9) * next_putAll_startingAt_ <4>: FileStream-overriding inherited methods. (line 6) * next_putAll_startingAt_: FileDescriptor-low-level access. (line 6) * next_putAllOn_: Stream-buffering. (line 11) * nextAvailable_: Stream-accessing-reading. (line 22) * nextAvailable_into_startingAt_ <1>: Stream-accessing-reading. (line 29) * nextAvailable_into_startingAt_ <2>: PositionableStream-accessing-reading. (line 23) * nextAvailable_into_startingAt_ <3>: FileStream-buffering. (line 29) * nextAvailable_into_startingAt_: FileDescriptor-low-level access. (line 9) * nextAvailable_putAllOn_ <1>: Stream-accessing-reading. (line 37) * nextAvailable_putAllOn_ <2>: PositionableStream-accessing-reading. (line 28) * nextAvailable_putAllOn_: FileStream-buffering. (line 33) * nextAvailablePutAllOn_: Stream-streaming protocol. (line 6) * nextByte: FileDescriptor-basic. (line 29) * nextByteArray_: FileDescriptor-binary I/O. (line 6) * nextDouble: FileDescriptor-binary I/O. (line 9) * nextFloat: FileDescriptor-binary I/O. (line 12) * nextInstance: Object-built ins. (line 133) * nextLine <1>: Stream-accessing-reading. (line 44) * nextLine: FileStream-overriding inherited methods. (line 9) * nextLink: Link-basic. (line 6) * nextLink_ <1>: Link-basic. (line 9) * nextLink_: Link class-instance creation. (line 6) * nextLong: FileDescriptor-binary I/O. (line 15) * nextLongLong: FileDescriptor-binary I/O. (line 19) * nextMatchFor_: Stream-accessing-reading. (line 50) * nextPut_ <1>: WriteStream-accessing-writing. (line 14) * nextPut_ <2>: TextCollector-accessing. (line 22) * nextPut_ <3>: Stream-accessing-writing. (line 13) * nextPut_ <4>: SharedQueue-accessing. (line 12) * nextPut_ <5>: Random-basic. (line 15) * nextPut_ <6>: ObjectDumper-stream interface. (line 12) * nextPut_ <7>: FileStream-basic. (line 16) * nextPut_: FileDescriptor-basic. (line 32) * nextPutAll_: Stream-accessing-writing. (line 16) * nextPutAllFlush_: Stream-accessing-writing. (line 19) * nextPutAllOn_ <1>: Stream-still unclassified. (line 6) * nextPutAllOn_ <2>: SequenceableCollection-still unclassified. (line 6) * nextPutAllOn_ <3>: PositionableStream-still unclassified. (line 6) * nextPutAllOn_ <4>: Iterable-streaming. (line 6) * nextPutAllOn_ <5>: FileStream-overriding inherited methods. (line 15) * nextPutAllOn_: FileDescriptor-overriding inherited methods. (line 9) * nextPutByte_: FileDescriptor-basic. (line 35) * nextPutByteArray_: FileDescriptor-basic. (line 38) * nextPutDouble_: FileDescriptor-binary I/O. (line 23) * nextPutFloat_: FileDescriptor-binary I/O. (line 26) * nextPutInt64_: FileDescriptor-binary I/O. (line 29) * nextPutLong_: FileDescriptor-binary I/O. (line 32) * nextPutShort_: FileDescriptor-binary I/O. (line 35) * nextShort: FileDescriptor-binary I/O. (line 38) * nextSignedByte: FileDescriptor-binary I/O. (line 42) * nextUint64: FileDescriptor-binary I/O. (line 46) * nextUlong: FileDescriptor-binary I/O. (line 50) * nextUshort: FileDescriptor-binary I/O. (line 54) * nextValidOop: SmallInteger-built ins. (line 78) * nl <1>: Stream-character writing. (line 21) * nl: Character class-constants. (line 33) * nlTab: Stream-character writing. (line 24) * noMask_: Integer-bit operators. (line 44) * noneSatisfy_: Iterable-enumeration. (line 63) * nonVersionedInstSize: Class-saving and loading. (line 23) * normal: Point-point functions. (line 21) * noRunnableProcess: Object-VM callbacks. (line 13) * not <1>: True-basic. (line 30) * not <2>: False-basic. (line 28) * not: Boolean-basic. (line 34) * notEmpty <1>: LinkedList-testing. (line 9) * notEmpty: Collection-testing collections. (line 29) * noteOldSyntax: CompiledMethod-accessing. (line 35) * notify: Semaphore-builtins. (line 11) * notifyAll: Semaphore-builtins. (line 16) * notNil <1>: UndefinedObject-testing. (line 29) * notNil: Object-testing functionality. (line 79) * notYetImplemented: Object-built ins. (line 137) * now <1>: Time class-instance creation. (line 32) * now: DateTime class-instance creation. (line 6) * nthOuterContext_: BlockContext-accessing. (line 36) * nul: Character class-constants. (line 36) * null <1>: ValueHolder class-creating instances. (line 9) * null: Promise class-creating instances. (line 10) * numArgs <1>: Symbol-basic. (line 15) * numArgs <2>: ContextPart-accessing. (line 84) * numArgs <3>: CompiledMethod-accessing. (line 39) * numArgs <4>: CompiledCode-accessing. (line 45) * numArgs <5>: CompiledBlock-accessing. (line 20) * numArgs: BlockClosure-accessing. (line 30) * numArgs_: CompiledMethod class-instance creation. (line 13) * numArgs_numTemps_bytecodes_depth_literals_ <1>: CompiledBlock class-instance creation. (line 10) * numArgs_numTemps_bytecodes_depth_literals_: BlockClosure class-instance creation. (line 17) * numberOfCharacters <1>: UnicodeString-multibyte encodings. (line 11) * numberOfCharacters: CharacterArray-multibyte encodings. (line 13) * numberOfElements: CArrayCType-accessing. (line 9) * numCompactions: ObjectMemory-accessing. (line 51) * numerator <1>: Integer-accessing. (line 9) * numerator: Fraction-accessing. (line 9) * numerator_denominator_: Fraction class-instance creation. (line 9) * numFixedOOPs: ObjectMemory-accessing. (line 55) * numFreeOTEs: ObjectMemory-accessing. (line 59) * numGlobalGCs: ObjectMemory-accessing. (line 63) * numGrowths: ObjectMemory-accessing. (line 67) * numLiterals <1>: CompiledCode-accessing. (line 48) * numLiterals: CompiledBlock-accessing. (line 23) * numOldOOPs: ObjectMemory-accessing. (line 75) * numOTEs: ObjectMemory-accessing. (line 71) * numScavenges: ObjectMemory-accessing. (line 78) * numTemps <1>: ContextPart-accessing. (line 87) * numTemps <2>: CompiledMethod-accessing. (line 42) * numTemps <3>: CompiledCode-accessing. (line 51) * numTemps <4>: CompiledBlock-accessing. (line 26) * numTemps: BlockClosure-accessing. (line 33) * numWeakOOPs: ObjectMemory-accessing. (line 82) * object <1>: SingletonProxy-saving and restoring. (line 6) * object <2>: PluggableProxy-saving and restoring. (line 6) * object <3>: DumperProxy-saving and restoring. (line 10) * object: AlternativeObjectProxy-accessing. (line 6) * object_: AlternativeObjectProxy-accessing. (line 10) * objectAt_: ByteArray-more advanced accessing. (line 62) * objectAt_put_: ByteArray-more advanced accessing. (line 67) * objectsAndRunLengthsDo_: RunArray-enumerating. (line 10) * occurrencesOf_ <1>: SortedCollection-searching. (line 14) * occurrencesOf_ <2>: HashedCollection-testing collections. (line 24) * occurrencesOf_ <3>: Dictionary-dictionary testing. (line 16) * occurrencesOf_ <4>: Collection-testing collections. (line 32) * occurrencesOf_: Bag-testing collections. (line 15) * occurrencesOfRegex_: String-regex. (line 103) * occurrencesOfRegex_from_to_: String-regex. (line 106) * occurrencesOfRegex_startingAt_: String-regex. (line 110) * odd <1>: Number-testing. (line 44) * odd: Integer-math methods. (line 32) * offset <1>: VFS.StoredZipMember-accessing. (line 6) * offset: DateTime-time zones. (line 13) * offset_ <1>: VFS.StoredZipMember-accessing. (line 9) * offset_: DateTime-time zones. (line 18) * oldSpaceSize: ObjectMemory-accessing. (line 86) * oldSpaceUsedBytes: ObjectMemory-accessing. (line 89) * on_ <1>: WriteStream class-instance creation. (line 6) * on_ <2>: VFS.FileWrapper class-instance creation. (line 6) * on_ <3>: SingletonProxy class-instance creation. (line 6) * on_ <4>: ReadWriteStream class-instance creation. (line 6) * on_ <5>: ReadStream class-instance creation. (line 6) * on_ <6>: PositionableStream class-instance creation. (line 6) * on_ <7>: PluggableProxy class-accessing. (line 6) * on_ <8>: ObjectDumper class-instance creation. (line 9) * on_ <9>: NetClients.URIResolver class-instance creation. (line 6) * on_ <10>: Generator class-instance creation. (line 11) * on_ <11>: FileDescriptor class-instance creation. (line 35) * on_ <12>: DumperProxy class-instance creation. (line 6) * on_: AlternativeObjectProxy class-instance creation. (line 11) * on_aspect_: PluggableAdaptor class-creating instances. (line 10) * on_do_ <1>: Generator class-instance creation. (line 17) * on_do_: BlockClosure-exception handling. (line 13) * on_do_on_do_: BlockClosure-exception handling. (line 19) * on_do_on_do_on_do_: BlockClosure-exception handling. (line 25) * on_do_on_do_on_do_on_do_: BlockClosure-exception handling. (line 31) * on_do_on_do_on_do_on_do_on_do_: BlockClosure-exception handling. (line 37) * on_from_to_ <1>: ReadWriteStream class-instance creation. (line 10) * on_from_to_ <2>: ReadStream class-instance creation. (line 9) * on_from_to_: PositionableStream class-instance creation. (line 10) * on_getSelector_putSelector_: PluggableAdaptor class-creating instances. (line 15) * on_index_: PluggableAdaptor class-creating instances. (line 20) * on_key_: PluggableAdaptor class-creating instances. (line 25) * on_startingAt_for_: FileSegment class-basic. (line 6) * one: ScaledDecimal-constants. (line 6) * oneShotValue: Continuation-invocation. (line 14) * oneShotValue_: Continuation-invocation. (line 19) * onOccurrencesOfRegex_do_: String-regex. (line 114) * onOccurrencesOfRegex_from_to_do_: String-regex. (line 118) * open_ <1>: FilePath-file operations. (line 13) * open_: FileDescriptor class-instance creation. (line 39) * open_ifFail_: FilePath-file operations. (line 17) * open_mode_: FileDescriptor class-still unclassified. (line 6) * open_mode_ifFail_ <1>: VFS.TmpFileArchiveMember-directory operations. (line 10) * open_mode_ifFail_ <2>: VFS.StoredZipMember-opening. (line 6) * open_mode_ifFail_ <3>: VFS.FileWrapper-delegation. (line 46) * open_mode_ifFail_ <4>: VFS.ArchiveMember-file operations. (line 6) * open_mode_ifFail_ <5>: FilePath-file operations. (line 21) * open_mode_ifFail_ <6>: FileDescriptor class-instance creation. (line 46) * open_mode_ifFail_: File-file operations. (line 10) * openDescriptor_: FilePath-file operations. (line 25) * openDescriptor_ifFail_: FilePath-file operations. (line 29) * openOn_: NetClients.URIResolver class-api. (line 6) * openOn_ifFail_: NetClients.URIResolver class-api. (line 10) * openStreamOn_: NetClients.URIResolver class-api. (line 16) * openStreamOn_ifFail_: NetClients.URIResolver class-api. (line 21) * openTemporaryFile_: FileDescriptor class-instance creation. (line 61) * or_ <1>: True-basic. (line 33) * or_ <2>: False-basic. (line 31) * or_: Boolean-basic. (line 38) * origin: Rectangle-accessing. (line 60) * origin_: Rectangle-accessing. (line 63) * origin_corner_ <1>: Rectangle-accessing. (line 66) * origin_corner_: Rectangle class-instance creation. (line 15) * origin_extent_ <1>: Rectangle-accessing. (line 70) * origin_extent_: Rectangle class-instance creation. (line 18) * originalException: SystemExceptions.UnhandledException-accessing. (line 12) * originalException_: SystemExceptions.UnhandledException-accessing. (line 15) * outer: Exception-exception handling. (line 13) * outerContext <1>: BlockContext-accessing. (line 39) * outerContext: BlockClosure-accessing. (line 36) * outerContext_: BlockClosure-accessing. (line 40) * owner_ <1>: SecurityPolicy-modifying. (line 9) * owner_: FilePath-accessing. (line 55) * owner_group_ <1>: VFS.FileWrapper-accessing. (line 20) * owner_group_ <2>: FilePath-accessing. (line 58) * owner_group_: File-file operations. (line 14) * packageAt_: PackageLoader class-accessing. (line 52) * packageAt_ifAbsent_: PackageLoader class-accessing. (line 55) * parent: FilePath-file name management. (line 25) * parentContext: ContextPart-accessing. (line 90) * parentContext_: ContextPart-accessing. (line 93) * parse_: Package class-instance creation. (line 6) * parse_with_do_: Getopt class-instance creation. (line 6) * parse_with_do_ifError_: Getopt class-instance creation. (line 20) * parseAttributes_: Package-still unclassified. (line 15) * parseInstanceVariableString_: Behavior-parsing class declarations. (line 6) * parseNodeAt_: Behavior-still unclassified. (line 10) * parserClass <1>: CompiledMethod-compiling. (line 14) * parserClass: Behavior-pluggable behavior (not yet implemented). (line 20) * parseTreeFor_: Behavior-accessing the method dictionary. (line 33) * parseVariableString_: Behavior-parsing class declarations. (line 10) * parseVersion_: Package-version parsing. (line 6) * pass: Exception-exception handling. (line 22) * password: NetClients.URL-accessing. (line 57) * password_: NetClients.URL-accessing. (line 60) * pastEnd <1>: Stream-polymorphism. (line 12) * pastEnd: FileDescriptor-polymorphism. (line 6) * path <1>: VariableBinding-printing. (line 6) * path <2>: Package-still unclassified. (line 18) * path <3>: NetClients.URL-accessing. (line 63) * path <4>: FilePath-file name management. (line 28) * path: DeferredVariableBinding-basic. (line 6) * path_ <1>: Package-still unclassified. (line 21) * path_ <2>: NetClients.URL-accessing. (line 66) * path_: File class-instance creation. (line 10) * path_class_defaultDictionary_: DeferredVariableBinding class-basic. (line 11) * pathFor_: FilePath class-file name management. (line 19) * pathFor_ifNone_: FilePath class-file name management. (line 24) * pathFrom_ <1>: VFS.FileWrapper-file operations. (line 6) * pathFrom_ <2>: FilePath-file operations. (line 33) * pathFrom_: File-file operations. (line 18) * pathFrom_to_: FilePath class-file name management. (line 30) * pathSeparator: Directory class-file name management. (line 10) * pathSeparatorString: Directory class-file name management. (line 14) * pathTo_ <1>: VFS.FileWrapper-accessing. (line 24) * pathTo_ <2>: FilePath-accessing. (line 62) * pathTo_: File-accessing. (line 51) * pause_: ProcessorScheduler-idle tasks. (line 16) * peek <1>: Stream-filtering. (line 20) * peek <2>: SharedQueue-accessing. (line 15) * peek <3>: PositionableStream-accessing-reading. (line 32) * peek <4>: Generator-stream protocol. (line 13) * peek <5>: FileStream-basic. (line 19) * peek: FileDescriptor-basic. (line 41) * peekFor_ <1>: Stream-filtering. (line 26) * peekFor_ <2>: PositionableStream-accessing-reading. (line 36) * peekFor_ <3>: Generator-stream protocol. (line 18) * peekFor_: FileDescriptor-basic. (line 45) * pendingWrite: FileStream-buffering. (line 37) * perform_: Object-built ins. (line 141) * perform_with_: Object-built ins. (line 154) * perform_with_with_: Object-built ins. (line 165) * perform_with_with_with_: Object-built ins. (line 176) * perform_with_with_with_with_: Object-built ins. (line 187) * perform_withArguments_: Object-built ins. (line 198) * pi <1>: FloatQ class-characterization. (line 45) * pi <2>: FloatE class-characterization. (line 45) * pi: Float class-characterization. (line 29) * poolResolution <1>: Metaclass-compiling methods. (line 6) * poolResolution: Behavior-compiling methods. (line 11) * popen_dir_: FileDescriptor class-instance creation. (line 70) * popen_dir_ifFail_: FileDescriptor class-instance creation. (line 82) * port: NetClients.URL-accessing. (line 69) * port_: NetClients.URL-accessing. (line 72) * position <1>: PositionableStream-positioning. (line 12) * position <2>: FileStream-basic. (line 23) * position: FileDescriptor-basic. (line 49) * position_ <1>: PositionableStream-positioning. (line 15) * position_ <2>: FileStream-basic. (line 26) * position_: FileDescriptor-basic. (line 52) * positive <1>: Number-testing. (line 47) * positive <2>: LargePositiveInteger-numeric testing. (line 12) * positive <3>: LargeNegativeInteger-numeric testing. (line 12) * positive <4>: Float-testing. (line 23) * positive: Duration-arithmetics. (line 41) * positiveDifference_: Number-misc math. (line 63) * postCopy <1>: Object-copying. (line 15) * postCopy <2>: NetClients.URL-copying. (line 14) * postCopy <3>: Exception-copying. (line 6) * postCopy: Delay-copying. (line 6) * postData: NetClients.URL-accessing. (line 75) * postData_: NetClients.URL-accessing. (line 79) * postLoad <1>: WeakSet-loading. (line 6) * postLoad <2>: WeakKeyDictionary class-hacks. (line 6) * postLoad <3>: WeakArray-loading. (line 6) * postLoad <4>: SortedCollection-saving and loading. (line 6) * postLoad <5>: Object-saving and loading. (line 11) * postLoad: HashedCollection-saving and loading. (line 6) * postStore <1>: Object-saving and loading. (line 15) * postStore: HashedCollection-saving and loading. (line 10) * pragmaHandlerFor_ <1>: Metaclass-delegation. (line 47) * pragmaHandlerFor_: Class-pragmas. (line 6) * precision <1>: FloatQ class-characterization. (line 48) * precision <2>: FloatE class-characterization. (line 48) * precision: FloatD class-characterization. (line 36) * predecessor: Float-floating point. (line 6) * prefix: Directory class-reading system defaults. (line 30) * prerequisites: Package-accessing. (line 94) * prerequisitesFor_: PackageLoader class-accessing. (line 58) * preStore <1>: SortedCollection-saving and loading. (line 9) * preStore: Object-saving and loading. (line 19) * primaryInstance: Metaclass-accessing. (line 9) * primAt_: HashedCollection-builtins. (line 6) * primAt_put_: HashedCollection-builtins. (line 11) * primCompile_: Behavior-built ins. (line 25) * primCompile_ifError_: Behavior-built ins. (line 33) * primDefineExternFunc_: DLD class-dynamic linking. (line 34) * primDivide_: LargePositiveInteger-helper byte-level methods. (line 38) * primFileIn: Package-accessing. (line 97) * primHash: Float-built ins. (line 33) * primitive <1>: CompiledMethod-accessing. (line 45) * primitive: CompiledCode-accessing. (line 54) * primitiveAttribute: CompiledMethod-attributes. (line 25) * primitiveFailed: Object-built ins. (line 210) * primNanosecondClock: Time class-builtins. (line 6) * primNew_: WeakValueLookupTable class-hacks. (line 6) * primNew_name_: AbstractNamespace class-instance creation. (line 9) * primObject: AlternativeObjectProxy-accessing. (line 14) * primReplaceFrom_to_with_startingAt_ <1>: OrderedCollection-built ins. (line 6) * primReplaceFrom_to_with_startingAt_: LargeInteger-built-ins. (line 25) * primSecondClock: Time class-builtins. (line 9) * primSize: HashedCollection-builtins. (line 16) * primTerminate: Process-basic. (line 24) * print: Object-printing. (line 37) * print_ <1>: TextCollector-printing. (line 6) * print_: Stream-printing. (line 16) * printAsAttributeOn_: Message-basic. (line 6) * printedFileName: FileSegment-printing. (line 6) * printFullHierarchy: Behavior-printing hierarchy. (line 9) * printHierarchy: Behavior-printing hierarchy. (line 13) * printNl: Object-printing. (line 41) * printOn_ <1>: VariableBinding-printing. (line 9) * printOn_ <2>: ValueAdaptor-printing. (line 6) * printOn_ <3>: UnicodeString-converting. (line 21) * printOn_ <4>: UndefinedObject-printing. (line 6) * printOn_ <5>: True-printing. (line 6) * printOn_ <6>: Time-arithmetic. (line 13) * printOn_ <7>: TextCollector-printing. (line 9) * printOn_ <8>: SymLink-printing. (line 6) * printOn_ <9>: Symbol-storing. (line 17) * printOn_ <10>: String-printing. (line 18) * printOn_ <11>: Semaphore-printing. (line 6) * printOn_ <12>: ScaledDecimal-printing. (line 11) * printOn_ <13>: Regex-printing. (line 17) * printOn_ <14>: RecursionLock-printing. (line 6) * printOn_ <15>: Rectangle-printing. (line 6) * printOn_ <16>: Promise-printing. (line 6) * printOn_ <17>: ProcessorScheduler-printing. (line 6) * printOn_ <18>: Process-printing. (line 6) * printOn_ <19>: Point-printing. (line 6) * printOn_ <20>: Object-printing. (line 45) * printOn_ <21>: NetClients.URL-printing. (line 6) * printOn_ <22>: MethodContext-printing. (line 6) * printOn_ <23>: Metaclass-printing. (line 9) * printOn_ <24>: Message-printing. (line 6) * printOn_ <25>: LookupKey-printing. (line 6) * printOn_ <26>: Interval-printing. (line 15) * printOn_ <27>: Integer-printing. (line 15) * printOn_ <28>: Fraction-printing. (line 6) * printOn_ <29>: Float-printing. (line 6) * printOn_ <30>: FilePath-printing. (line 12) * printOn_ <31>: FileDescriptor-printing. (line 6) * printOn_ <32>: False-printing. (line 6) * printOn_ <33>: Duration-arithmetics. (line 45) * printOn_ <34>: DirectedMessage-basic. (line 6) * printOn_ <35>: Dictionary-printing. (line 10) * printOn_ <36>: DeferredVariableBinding-storing. (line 6) * printOn_ <37>: DateTime-printing. (line 6) * printOn_ <38>: Date-printing. (line 6) * printOn_ <39>: CompiledMethod-printing. (line 6) * printOn_ <40>: CompiledBlock-printing. (line 6) * printOn_ <41>: Collection-printing. (line 13) * printOn_ <42>: CObject-accessing. (line 19) * printOn_ <43>: Class-printing. (line 9) * printOn_ <44>: Character-printing. (line 10) * printOn_ <45>: CFunctionDescriptor-printing. (line 6) * printOn_ <46>: BlockContext-printing. (line 6) * printOn_ <47>: Bag-printing. (line 6) * printOn_ <48>: Association-printing. (line 6) * printOn_ <49>: Array-printing. (line 9) * printOn_: AbstractNamespace-printing. (line 16) * printOn_base_: Integer-printing. (line 18) * printOn_in_ <1>: UndefinedObject-printing. (line 9) * printOn_in_ <2>: SystemDictionary-printing. (line 9) * printOn_in_ <3>: RootNamespace-printing. (line 10) * printOn_in_ <4>: Namespace-printing. (line 10) * printOn_in_ <5>: Metaclass-printing. (line 12) * printOn_in_ <6>: ClassDescription-printing. (line 17) * printOn_in_ <7>: BindingDictionary-printing. (line 6) * printOn_in_: Behavior-support for lightweight classes. (line 25) * printOn_paddedWith_to_: Integer-printing. (line 21) * printOn_paddedWith_to_base_: Integer-printing. (line 25) * printPaddedWith_to_: Integer-printing. (line 29) * printPaddedWith_to_base_: Integer-printing. (line 33) * printString <1>: Object-printing. (line 48) * printString: Integer-printing. (line 37) * printString_: Integer-printing. (line 40) * printStringRadix_: Integer-printing. (line 43) * priority: Process-accessing. (line 15) * priority_: Process-accessing. (line 18) * priorityName_: ProcessorScheduler-priorities. (line 25) * privateMethods: Behavior-compilation (alternative). (line 19) * processEnvironment: ProcessorScheduler-basic. (line 15) * processesAt_: ProcessorScheduler-basic. (line 23) * proxyClassFor_: ObjectDumper class-establishing proxy classes. (line 13) * proxyFor_: ObjectDumper class-establishing proxy classes. (line 17) * ptrType: CType-accessing. (line 22) * publicMethods: Behavior-compilation (alternative). (line 22) * push_: ContextPart-accessing. (line 96) * putenv_: SystemDictionary-c call-outs. (line 18) * query: NetClients.URL-accessing. (line 83) * query_: NetClients.URL-accessing. (line 86) * queueInterrupt_: Process-accessing. (line 21) * quit: ObjectMemory class-builtins. (line 63) * quit_: ObjectMemory class-builtins. (line 67) * quo_ <1>: SmallInteger-built ins. (line 83) * quo_ <2>: Number-arithmetic. (line 30) * quo_ <3>: LargeZeroInteger-arithmetic. (line 27) * quo_: LargeInteger-arithmetic. (line 37) * radiansToDegrees: Number-converting. (line 55) * radix: Float class-characterization. (line 32) * radix_: Integer-printing. (line 47) * raisedTo_ <1>: Number-misc math. (line 67) * raisedTo_: Float-built ins. (line 36) * raisedToInteger_ <1>: Number-misc math. (line 70) * raisedToInteger_ <2>: LargeInteger-accessing. (line 6) * raisedToInteger_ <3>: Fraction-optimized cases. (line 9) * raisedToInteger_: Float-arithmetic. (line 13) * raisePriority: Process-basic. (line 28) * rawProfile_: SystemDictionary-profiling. (line 6) * read: FileDescriptor class-instance creation. (line 92) * readFrom_ <1>: Time class-instance creation. (line 35) * readFrom_ <2>: Number class-converting. (line 9) * readFrom_ <3>: Duration class-instance creation. (line 19) * readFrom_ <4>: DateTime class-instance creation. (line 10) * readFrom_: Date class-instance creation (Blue Book). (line 30) * readFrom_radix_: Number class-converting. (line 14) * reads_ <1>: CompiledMethod-testing. (line 17) * reads_: CompiledCode-testing accesses. (line 25) * readStream <1>: WriteStream-accessing-writing. (line 18) * readStream <2>: Stream-testing. (line 17) * readStream <3>: SequenceableCollection-enumerating. (line 64) * readStream <4>: PositionableStream-accessing-reading. (line 41) * readStream <5>: NetClients.URL-still unclassified. (line 12) * readStream <6>: Iterable-streaming. (line 9) * readStream <7>: FilePath-file operations. (line 37) * readStream <8>: FileDescriptor-initialize-release. (line 12) * readStream: Collection-enumeration. (line 30) * readWrite: FileDescriptor class-instance creation. (line 96) * readWriteStream: SequenceableCollection-enumerating. (line 67) * rebuildTable: Symbol class-symbol table. (line 21) * receiver <1>: MessageNotUnderstood-accessing. (line 9) * receiver <2>: DirectedMessage-accessing. (line 6) * receiver <3>: ContextPart-accessing. (line 99) * receiver: BlockClosure-accessing. (line 44) * receiver_ <1>: DirectedMessage-accessing. (line 9) * receiver_: BlockClosure-accessing. (line 49) * receiver_selector_: DirectedMessage class-creating instances. (line 6) * receiver_selector_argument_: DirectedMessage class-creating instances. (line 9) * receiver_selector_arguments_: DirectedMessage class-creating instances. (line 12) * reciprocal <1>: Number-arithmetic. (line 35) * reciprocal: Fraction-optimized cases. (line 12) * reclaimedBytesPerGlobalGC: ObjectMemory-accessing. (line 93) * reclaimedBytesPerScavenge: ObjectMemory-accessing. (line 97) * reclaimedPercentPerScavenge: ObjectMemory-accessing. (line 101) * recompile: CompiledMethod-compiling. (line 18) * recompile_: Behavior-method dictionary. (line 73) * recompile_notifying_: Behavior-method dictionary. (line 77) * recompileNotifying_: CompiledMethod-compiling. (line 21) * reconstructOriginalObject <1>: Object-saving and loading. (line 23) * reconstructOriginalObject: DirectedMessage-saving and loading. (line 6) * record_: FileStream class-file-in. (line 51) * refersTo_: CompiledCode-testing accesses. (line 29) * refresh <1>: VFS.ArchiveMember-accessing. (line 38) * refresh <2>: VFS.ArchiveFile-ArchiveMember protocol. (line 19) * refresh <3>: PackageLoader class-accessing. (line 62) * refresh <4>: FilePath-accessing. (line 65) * refresh: File-accessing. (line 54) * registerHandler_forPragma_: Class-pragmas. (line 10) * registerProxyClass_for_: ObjectDumper class-establishing proxy classes. (line 21) * rehash <1>: WeakValueLookupTable-rehashing. (line 6) * rehash <2>: MethodDictionary-rehashing. (line 6) * rehash <3>: LookupTable-rehashing. (line 6) * rehash <4>: HashedCollection-rehashing. (line 6) * rehash: Dictionary-rehashing. (line 6) * reinvokeFor_: Message-printing. (line 9) * reject_ <1>: Stream-filtering. (line 33) * reject_ <2>: MappedCollection-basic. (line 54) * reject_ <3>: Iterable-enumeration. (line 67) * reject_ <4>: FilePath-enumerating. (line 51) * reject_ <5>: Dictionary-dictionary enumerating. (line 24) * reject_ <6>: Collection-enumeration. (line 33) * reject_: ArrayedCollection-enumerating the elements of a collection. (line 11) * relativeDirectory: Package-accessing. (line 101) * relativeDirectory_: Package-accessing. (line 105) * release <1>: VFS.TmpFileArchiveMember-finalization. (line 6) * release <2>: VFS.ArchiveFile-directory operations. (line 18) * release <3>: UndefinedObject-dependents access. (line 9) * release: Object-dependents access. (line 13) * relocate: FileSegment class-installing. (line 6) * relocateFrom_map_: FileSegment-basic. (line 22) * rem_ <1>: Number-arithmetic. (line 38) * rem_ <2>: LargeZeroInteger-arithmetic. (line 31) * rem_: LargeInteger-arithmetic. (line 41) * remainingCount: SystemExceptions.NotEnoughElements-accessing. (line 12) * remainingCount_: SystemExceptions.NotEnoughElements-accessing. (line 15) * remove <1>: VFS.FileWrapper-delegation. (line 50) * remove <2>: VFS.ArchiveMember-file operations. (line 10) * remove <3>: FilePath-file operations. (line 40) * remove: File-file operations. (line 22) * remove_ <1>: ProcessEnvironment-dictionary removing. (line 6) * remove_ <2>: MethodDictionary-removing. (line 6) * remove_ <3>: LookupTable-removing. (line 6) * remove_ <4>: File class-file operations. (line 14) * remove_ <5>: Dictionary-dictionary removing. (line 6) * remove_: Collection-removing. (line 9) * remove_ifAbsent_ <1>: ProcessEnvironment-dictionary removing. (line 9) * remove_ifAbsent_ <2>: OrderedCollection-removing. (line 14) * remove_ifAbsent_ <3>: LookupTable-removing. (line 9) * remove_ifAbsent_ <4>: LinkedList-adding. (line 15) * remove_ifAbsent_ <5>: HashedCollection-removing. (line 6) * remove_ifAbsent_ <6>: Dictionary-dictionary removing. (line 9) * remove_ifAbsent_ <7>: Collection-removing. (line 13) * remove_ifAbsent_: Bag-removing. (line 6) * removeAll_: Collection-removing. (line 17) * removeAll_ifAbsent_: Collection-removing. (line 22) * removeAllKeys_ <1>: ProcessEnvironment-dictionary removing. (line 12) * removeAllKeys_: Dictionary-dictionary removing. (line 12) * removeAllKeys_ifAbsent_ <1>: ProcessEnvironment-dictionary removing. (line 15) * removeAllKeys_ifAbsent_: Dictionary-dictionary removing. (line 15) * removeAllKeysSuchThat_: Dictionary-removing. (line 6) * removeAllSuchThat_: Collection-removing. (line 26) * removeAtIndex_ <1>: RunArray-removing. (line 6) * removeAtIndex_: OrderedCollection-removing. (line 18) * removeCategory_: ClassDescription-organization of messages and classes. (line 28) * removeClassVarName_ <1>: Metaclass-delegation. (line 51) * removeClassVarName_: Class-accessing instances and variables. (line 63) * removeDependent_: Object-dependents access. (line 17) * removeFeature_: SystemDictionary-special accessing. (line 13) * removeFirst <1>: RunArray-removing. (line 10) * removeFirst <2>: OrderedCollection-removing. (line 22) * removeFirst: LinkedList-adding. (line 19) * removeInstVarName_: Behavior-instance variables. (line 13) * removeKey_ <1>: ProcessEnvironment-dictionary removing. (line 19) * removeKey_: Dictionary-dictionary removing. (line 19) * removeKey_ifAbsent_ <1>: ProcessEnvironment-dictionary removing. (line 22) * removeKey_ifAbsent_ <2>: MethodDictionary-removing. (line 9) * removeKey_ifAbsent_ <3>: LookupTable-removing. (line 12) * removeKey_ifAbsent_: Dictionary-dictionary removing. (line 22) * removeLast <1>: SortedCollection-basic. (line 9) * removeLast <2>: RunArray-removing. (line 14) * removeLast <3>: OrderedCollection-removing. (line 26) * removeLast: LinkedList-adding. (line 23) * removeMember_ <1>: VFS.ZipFile-members. (line 22) * removeMember_: VFS.ArchiveFile-ArchiveMember protocol. (line 22) * removePermission_: SecurityPolicy-modifying. (line 12) * removeSelector_: Behavior-method dictionary. (line 82) * removeSelector_ifAbsent_: Behavior-method dictionary. (line 86) * removeSharedPool_ <1>: Metaclass-delegation. (line 55) * removeSharedPool_ <2>: Class-accessing instances and variables. (line 67) * removeSharedPool_: AbstractNamespace-compiling. (line 14) * removeSubclass_ <1>: UndefinedObject-class polymorphism. (line 19) * removeSubclass_: Behavior-creating a class hierarchy. (line 9) * removeSubspace_: AbstractNamespace-namespace hierarchy. (line 35) * removeToBeFinalized <1>: Object-finalization. (line 22) * removeToBeFinalized: FileDescriptor-initialize-release. (line 15) * rename_to_: File class-file operations. (line 17) * renameTo_ <1>: VFS.FileWrapper-file operations. (line 10) * renameTo_ <2>: VFS.ArchiveMember-file operations. (line 13) * renameTo_ <3>: FilePath-file operations. (line 43) * renameTo_: File-file operations. (line 25) * repeat: BlockClosure-control structures. (line 6) * replace_withStringBase_ <1>: LargeZeroInteger-printing. (line 6) * replace_withStringBase_: LargePositiveInteger-converting. (line 15) * replaceAll_with_: SequenceableCollection-replacing items. (line 6) * replaceFrom_to_with_: SequenceableCollection-replacing items. (line 10) * replaceFrom_to_with_startingAt_ <1>: String-built ins. (line 33) * replaceFrom_to_with_startingAt_ <2>: SequenceableCollection-replacing items. (line 15) * replaceFrom_to_with_startingAt_ <3>: ByteArray-built ins. (line 23) * replaceFrom_to_with_startingAt_: Array-built ins. (line 9) * replaceFrom_to_withByteArray_startingAt_: String-built ins. (line 38) * replaceFrom_to_withObject_: SequenceableCollection-replacing items. (line 19) * replaceFrom_to_withString_startingAt_: ByteArray-built ins. (line 28) * replacingAllRegex_with_: String-regex. (line 123) * replacingRegex_with_: String-regex. (line 130) * requestString: NetClients.URL-accessing. (line 89) * require_: FileStream class-file-in. (line 57) * reset <1>: PositionableStream-positioning. (line 18) * reset: FileDescriptor-basic. (line 55) * resignalAs_: Exception-exception handling. (line 27) * resignalAsUnhandled_: Exception-built ins. (line 6) * respondsTo_: Object-testing functionality. (line 82) * resume <1>: Process-builtins. (line 6) * resume: Exception-exception handling. (line 35) * resume_: Exception-exception handling. (line 42) * resumptionTime: Delay-accessing. (line 19) * retry: Exception-exception handling. (line 49) * retry_coercing_: Number-retrying. (line 6) * retryDifferenceCoercing_: Number-retrying. (line 12) * retryDivisionCoercing_: Number-retrying. (line 16) * retryEqualityCoercing_: Number-retrying. (line 20) * retryError: Number-retrying. (line 24) * retryInequalityCoercing_: Number-retrying. (line 28) * retryMultiplicationCoercing_: Number-retrying. (line 32) * retryRelationalOp_coercing_: Number-retrying. (line 36) * retrySumCoercing_: Number-retrying. (line 41) * retryUsing_: Exception-exception handling. (line 53) * return: Exception-exception handling. (line 57) * return_: Exception-exception handling. (line 60) * returnType: CCallable-accessing. (line 9) * reverse <1>: SequenceableCollection-enumerating. (line 70) * reverse <2>: Interval-basic. (line 25) * reverse: ArrayedCollection-copying Collections. (line 33) * reverseContents <1>: WriteStream-accessing-writing. (line 21) * reverseContents <2>: PositionableStream-accessing-reading. (line 44) * reverseContents: FileDescriptor-overriding inherited methods. (line 12) * reverseDo_: SequenceableCollection-enumerating. (line 73) * rewriteAsAsyncCCall_args_: CompiledMethod-c call-outs. (line 10) * rewriteAsCCall_for_: CompiledMethod-c call-outs. (line 13) * rewriteAsCCall_returning_args_: CompiledMethod-c call-outs. (line 16) * right: Rectangle-accessing. (line 73) * right_: Rectangle-accessing. (line 76) * rightCenter: Rectangle-accessing. (line 79) * rounded <1>: Rectangle-truncation and round off. (line 6) * rounded <2>: Point-truncation and round off. (line 6) * rounded <3>: Number-truncation and round off. (line 22) * rounded <4>: Integer-converting. (line 25) * rounded: Float-truncation and round off. (line 6) * roundTo_: Number-truncation and round off. (line 19) * runDelayProcess: Delay class-timer process. (line 15) * sameAs_: CharacterArray-comparing. (line 49) * scaleBy_: Rectangle-transforming. (line 14) * scanBacktraceFor_do_: ContextPart-enumerating. (line 6) * scanBacktraceForAttribute_do_: ContextPart-enumerating. (line 11) * scavenge: ObjectMemory class-builtins. (line 71) * scavengesBeforeTenuring: ObjectMemory-derived information. (line 6) * scheduleDelay_: Delay class-timer process. (line 18) * scheme: NetClients.URL-accessing. (line 94) * scheme_: NetClients.URL-accessing. (line 97) * scheme_host_path_: NetClients.URL class-instance creation. (line 12) * scheme_host_port_path_: NetClients.URL class-instance creation. (line 15) * scheme_path_: NetClients.URL class-instance creation. (line 18) * scheme_username_password_host_port_path_: NetClients.URL class-instance creation. (line 21) * scopeDictionary <1>: Dictionary-compilation. (line 6) * scopeDictionary: Behavior-compilation. (line 6) * scopeHas_ifTrue_: Behavior-testing the method dictionary. (line 17) * scramble: SmallInteger-builtins. (line 22) * searchRegex_: String-regex. (line 137) * searchRegex_from_to_: String-regex. (line 141) * searchRegex_startingAt_: String-regex. (line 146) * second <1>: Time-accessing (ANSI for DateAndTimes). (line 18) * second <2>: SequenceableCollection-basic. (line 129) * second: DateTime-computations. (line 28) * second_: Time class-instance creation. (line 39) * secondClock: Time class-clocks. (line 24) * seconds: Time-accessing (non ANSI & for Durations). (line 21) * seconds_: Time class-instance creation. (line 42) * securityCheckForName_: ContextPart-security checks. (line 12) * securityCheckForName_action_: ContextPart-security checks. (line 15) * securityCheckForName_actions_target_: ContextPart-security checks. (line 18) * securityCheckForName_target_: ContextPart-security checks. (line 21) * securityPolicy <1>: Class-security. (line 9) * securityPolicy: Behavior-support for lightweight classes. (line 29) * securityPolicy_ <1>: Class-security. (line 12) * securityPolicy_: Behavior-support for lightweight classes. (line 32) * seed_: Random class-instance creation. (line 10) * segmentFrom_to_ <1>: Stream-compiling. (line 6) * segmentFrom_to_ <2>: PositionableStream-compiling. (line 9) * segmentFrom_to_: FileStream-compiling. (line 6) * select_ <1>: Stream-filtering. (line 38) * select_ <2>: MappedCollection-basic. (line 57) * select_ <3>: Iterable-enumeration. (line 71) * select_ <4>: FilePath-enumerating. (line 56) * select_ <5>: Dictionary-dictionary enumerating. (line 29) * select_ <6>: Collection-enumeration. (line 37) * select_: ArrayedCollection-enumerating the elements of a collection. (line 15) * selector <1>: SystemExceptions.WrongMessageSent-accessing. (line 9) * selector <2>: MethodInfo-accessing. (line 18) * selector <3>: Message-accessing. (line 15) * selector <4>: ContextPart-accessing. (line 102) * selector <5>: CompiledMethod-accessing. (line 48) * selector <6>: CompiledCode-accessing. (line 57) * selector: CompiledBlock-accessing. (line 29) * selector_ <1>: SystemExceptions.WrongMessageSent-accessing. (line 12) * selector_ <2>: MethodInfo-accessing. (line 21) * selector_ <3>: Message-accessing. (line 18) * selector_ <4>: CompiledMethod-accessing. (line 51) * selector_ <5>: CompiledCode-accessing. (line 60) * selector_: CompiledBlock-accessing. (line 32) * selector_argument_: Message class-creating instances. (line 6) * selector_arguments_ <1>: Message class-creating instances. (line 9) * selector_arguments_: DirectedMessage class-creating instances. (line 15) * selector_arguments_receiver_: DirectedMessage class-creating instances. (line 18) * selectorAt_: Behavior-accessing the method dictionary. (line 37) * selectors: Behavior-accessing the method dictionary. (line 40) * selectorsAndMethodsDo_: Behavior-method dictionary. (line 91) * selectSubclasses_: Behavior-enumerating. (line 19) * selectSubspaces_: AbstractNamespace-namespace hierarchy. (line 38) * selectSuperclasses_: Behavior-enumerating. (line 22) * selectSuperspaces_: AbstractNamespace-namespace hierarchy. (line 41) * semaphore: SystemExceptions.ProcessBeingTerminated-accessing. (line 9) * semaphore_: SystemExceptions.ProcessBeingTerminated-accessing. (line 12) * send: DirectedMessage-basic. (line 9) * sender: MethodContext-accessing. (line 39) * sendsToSuper <1>: CompiledMethod-testing. (line 21) * sendsToSuper: CompiledCode-testing accesses. (line 32) * sendTo_: Message-printing. (line 12) * set_to_: AbstractNamespace-overrides for superspaces. (line 9) * set_to_ifAbsent_ <1>: RootNamespace-overrides for superspaces. (line 9) * set_to_ifAbsent_ <2>: Namespace-overrides for superspaces. (line 40) * set_to_ifAbsent_: AbstractNamespace-overrides for superspaces. (line 16) * setBit_: Integer-bit operators. (line 47) * setToEnd <1>: PositionableStream-positioning. (line 22) * setToEnd: FileDescriptor-overriding inherited methods. (line 15) * setTraceFlag_to_: SystemDictionary-builtins. (line 34) * shallowCopy <1>: WeakSet-copying. (line 10) * shallowCopy <2>: WeakArray-conversion. (line 13) * shallowCopy <3>: UndefinedObject-basic. (line 12) * shallowCopy <4>: Symbol-basic. (line 20) * shallowCopy <5>: RunArray-copying. (line 10) * shallowCopy <6>: Object-built ins. (line 213) * shallowCopy <7>: Number-copying. (line 9) * shallowCopy <8>: HashedCollection-copying. (line 10) * shallowCopy <9>: Boolean-overriding. (line 9) * shallowCopy: BindingDictionary-copying. (line 23) * shape: Behavior-testing the class hierarchy. (line 16) * shape_: Behavior-testing the class hierarchy. (line 19) * sharedPoolDictionaries: AbstractNamespace-compiling. (line 17) * sharedPools <1>: Metaclass-delegation. (line 59) * sharedPools <2>: Class-accessing instances and variables. (line 71) * sharedPools: Behavior-accessing instances and variables. (line 47) * sharedVariableString: ClassDescription-printing. (line 21) * shortAt_ <1>: Memory class-accessing. (line 63) * shortAt_: ByteArray-more advanced accessing. (line 72) * shortAt_put_ <1>: Memory class-accessing. (line 66) * shortAt_put_: ByteArray-more advanced accessing. (line 76) * shortMonthName: Date-compatibility (non-ANSI). (line 12) * shortNameOfMonth_: Date class-basic. (line 38) * shouldNotImplement: Object-built ins. (line 217) * show_: TextCollector-accessing. (line 25) * showCr_: TextCollector-accessing. (line 28) * showOnNewLine_: TextCollector-accessing. (line 31) * shutdown: FileDescriptor-basic. (line 58) * siblings <1>: RootNamespace-namespace hierarchy. (line 6) * siblings <2>: Namespace-namespace hierarchy. (line 6) * siblings: AbstractNamespace-namespace hierarchy. (line 44) * siblingsDo_ <1>: RootNamespace-namespace hierarchy. (line 9) * siblingsDo_ <2>: Namespace-namespace hierarchy. (line 10) * siblingsDo_: AbstractNamespace-namespace hierarchy. (line 48) * sign <1>: Number-testing. (line 50) * sign <2>: LargeZeroInteger-numeric testing. (line 6) * sign <3>: LargePositiveInteger-numeric testing. (line 15) * sign <4>: LargeNegativeInteger-numeric testing. (line 15) * sign: Float-testing. (line 27) * signal <1>: Semaphore-builtins. (line 21) * signal <2>: Exception-exception signaling. (line 6) * signal: Exception class-instance creation. (line 10) * signal_ <1>: SystemExceptions.SecurityError class-accessing. (line 6) * signal_ <2>: SystemExceptions.PackageNotAvailable class-still unclassified. (line 6) * signal_ <3>: Exception-exception signaling. (line 9) * signal_: Exception class-instance creation. (line 14) * signal_atNanosecondClockValue_: ProcessorScheduler-timed invocation. (line 10) * signal_onInterrupt_: ProcessorScheduler-timed invocation. (line 14) * signal_reason_: SystemExceptions.PackageNotAvailable class-still unclassified. (line 10) * signalingContext: Exception-still unclassified. (line 6) * signalOn_ <1>: SystemExceptions.NotEnoughElements class-signaling. (line 6) * signalOn_ <2>: SystemExceptions.MustBeBoolean class-signaling. (line 6) * signalOn_ <3>: SystemExceptions.InvalidValue class-signaling. (line 6) * signalOn_: SystemExceptions.EndOfStream class-signaling. (line 6) * signalOn_mustBe_: SystemExceptions.WrongClass class-signaling. (line 6) * signalOn_mustBeBetween_and_: SystemExceptions.ArgumentOutOfRange class-signaling. (line 6) * signalOn_reason_ <1>: SystemExceptions.NotFound class-accessing. (line 6) * signalOn_reason_: SystemExceptions.InvalidValue class-signaling. (line 9) * signalOn_useInstead_: SystemExceptions.WrongMessageSent class-signaling. (line 6) * signalOn_what_: SystemExceptions.NotFound class-accessing. (line 9) * signalOn_withIndex_: SystemExceptions.IndexOutOfRange class-signaling. (line 6) * signByte <1>: FloatQ class-byte-order dependancies. (line 6) * signByte <2>: FloatE class-byte-order dependancies. (line 6) * signByte <3>: FloatD class-byte-order dependencies. (line 10) * signByte: Float class-byte-order dependancies. (line 6) * similarityTo_: String-built ins. (line 43) * sin <1>: Number-misc math. (line 73) * sin: Float-built ins. (line 39) * singleStep: Process-basic. (line 32) * singleStepWaitingOn_: Process-builtins. (line 9) * sinh: Number-misc math. (line 76) * size <1>: WeakArray-accessing. (line 43) * size <2>: VFS.FileWrapper-delegation. (line 53) * size <3>: VFS.ArchiveMember-accessing. (line 41) * size <4>: String-built ins. (line 48) * size <5>: SequenceableCollection-testing collections. (line 6) * size <6>: RunArray-basic. (line 12) * size <7>: RegexResults-accessing. (line 36) * size <8>: PositionableStream-positioning. (line 25) * size <9>: OrderedCollection-accessing. (line 19) * size <10>: Object-built ins. (line 221) * size <11>: Namespace-overrides for superspaces. (line 46) * size <12>: MappedCollection-basic. (line 60) * size <13>: LinkedList-testing. (line 12) * size <14>: Link-iteration. (line 16) * size <15>: LargeZeroInteger-accessing. (line 12) * size <16>: LargeInteger-built-ins. (line 31) * size <17>: LargeArrayedCollection-basic. (line 12) * size <18>: Interval-basic. (line 28) * size <19>: HashedCollection-testing collections. (line 29) * size <20>: FileStream-basic. (line 29) * size <21>: FileSegment-basic. (line 27) * size <22>: FilePath-accessing. (line 68) * size <23>: FileDescriptor-basic. (line 62) * size <24>: File-accessing. (line 57) * size <25>: ContextPart-accessing. (line 105) * size <26>: Collection-testing collections. (line 35) * size <27>: Bag-testing collections. (line 18) * size: ArrayedCollection-built ins. (line 6) * size_stCtime_stMtime_stAtime_mode_: VFS.ArchiveMember-initializing. (line 13) * size_stMtime_mode_: VFS.ArchiveMember-initializing. (line 16) * sizeof <1>: CUShort-accessing. (line 12) * sizeof <2>: CUShort class-accessing. (line 13) * sizeof <3>: CULongLong-accessing. (line 12) * sizeof <4>: CULongLong class-accessing. (line 13) * sizeof <5>: CULong-accessing. (line 12) * sizeof <6>: CULong class-accessing. (line 13) * sizeof <7>: CUInt-accessing. (line 12) * sizeof <8>: CUInt class-accessing. (line 13) * sizeof <9>: CUChar-accessing. (line 12) * sizeof <10>: CUChar class-getting info. (line 13) * sizeof <11>: CType-accessing. (line 26) * sizeof <12>: CSmalltalk-accessing. (line 12) * sizeof <13>: CSmalltalk class-accessing. (line 13) * sizeof <14>: CShort-accessing. (line 12) * sizeof <15>: CShort class-accessing. (line 13) * sizeof <16>: CPtr-accessing. (line 9) * sizeof <17>: CLongLong-accessing. (line 12) * sizeof <18>: CLongLong class-accessing. (line 13) * sizeof <19>: CLongDouble-accessing. (line 12) * sizeof <20>: CLongDouble class-accessing. (line 13) * sizeof <21>: CLong-accessing. (line 12) * sizeof <22>: CLong class-accessing. (line 13) * sizeof <23>: CInt-accessing. (line 12) * sizeof <24>: CInt class-accessing. (line 13) * sizeof <25>: CFloat-accessing. (line 12) * sizeof <26>: CFloat class-accessing. (line 13) * sizeof <27>: CDouble-accessing. (line 12) * sizeof <28>: CDouble class-accessing. (line 13) * sizeof <29>: CCompound class-subclass creation. (line 36) * sizeof <30>: CChar-accessing. (line 12) * sizeof <31>: CChar class-accessing. (line 13) * sizeof <32>: CArrayCType-accessing. (line 12) * sizeof <33>: CArray-accessing. (line 9) * sizeof: CAggregate class-accessing. (line 9) * skip_ <1>: Stream-positioning. (line 9) * skip_ <2>: PositionableStream-positioning. (line 28) * skip_: FileDescriptor-overriding inherited methods. (line 18) * skipSeparators: Stream-positioning. (line 12) * skipTo_: Stream-positioning. (line 19) * skipToAll_: Stream-positioning. (line 24) * smallest: SmallInteger class-getting limits. (line 14) * smoothingFactor: ObjectMemory class-builtins. (line 74) * smoothingFactor_: ObjectMemory class-builtins. (line 80) * snapshot: ObjectMemory class-saving the image. (line 6) * snapshot_: ObjectMemory class-saving the image. (line 9) * soleInstance: Metaclass-accessing. (line 13) * someInstance: Behavior-built ins. (line 41) * sort <1>: SortedCollection-sorting. (line 6) * sort: SequenceableCollection-sorting. (line 6) * sort_ <1>: SortedCollection-sorting. (line 12) * sort_: SequenceableCollection-sorting. (line 10) * sortBlock: SortedCollection-basic. (line 13) * sortBlock_ <1>: SortedCollection-basic. (line 16) * sortBlock_ <2>: SortedCollection class-instance creation. (line 13) * sortBlock_: SharedQueue class-instance creation. (line 9) * sorted <1>: SequenceableCollection-sorting. (line 15) * sorted <2>: Collection-sorting. (line 6) * sorted: ArrayedCollection-sorting. (line 6) * sorted_ <1>: SequenceableCollection-sorting. (line 19) * sorted_ <2>: Collection-sorting. (line 11) * sorted_: ArrayedCollection-sorting. (line 10) * sortedByCount: Bag-extracting items. (line 6) * source: Random class-shortcuts. (line 12) * sourceCode: MethodInfo-accessing. (line 24) * sourceCodeAt_: Behavior-accessing the method dictionary. (line 43) * sourceCodeAt_ifAbsent_: Behavior-accessing the method dictionary. (line 46) * sourceCodeLinesDelta <1>: CompiledMethod-accessing. (line 54) * sourceCodeLinesDelta <2>: CompiledCode-accessing. (line 63) * sourceCodeLinesDelta: CompiledBlock-accessing. (line 35) * sourceCodeMap <1>: CompiledCode-testing accesses. (line 35) * sourceCodeMap: CompiledBlock-accessing. (line 39) * sourceFile: MethodInfo-accessing. (line 28) * sourceMethodAt_: Behavior-accessing the method dictionary. (line 49) * sourcePos: MethodInfo-accessing. (line 31) * sourceString: MethodInfo-accessing. (line 35) * sp: ContextPart-accessing. (line 109) * sp_: ContextPart-accessing. (line 112) * space <1>: Stream-character writing. (line 27) * space: Character class-constants. (line 39) * space_: Stream-character writing. (line 30) * spaceGrowRate: ObjectMemory class-builtins. (line 86) * spaceGrowRate_: ObjectMemory class-builtins. (line 90) * specialSelectors: CompiledCode class-tables. (line 21) * specialSelectorsNumArgs: CompiledCode class-tables. (line 26) * species <1>: WeakArray-conversion. (line 17) * species <2>: Symbol-misc. (line 6) * species <3>: Stream-basic. (line 6) * species <4>: Regex-conversion. (line 12) * species <5>: PositionableStream-class type methods. (line 9) * species <6>: Object-class type methods. (line 6) * species <7>: Interval-basic. (line 31) * species: BindingDictionary-testing. (line 6) * splitAt_: Stream-accessing-reading. (line 54) * sqrt <1>: Number-misc math. (line 79) * sqrt <2>: Fraction-optimized cases. (line 15) * sqrt: Float-built ins. (line 42) * squared <1>: Number-misc math. (line 82) * squared: Fraction-optimized cases. (line 18) * stackDepth <1>: CompiledMethod-accessing. (line 58) * stackDepth <2>: CompiledCode-accessing. (line 67) * stackDepth <3>: CompiledBlock-accessing. (line 43) * stackDepth: BlockClosure-accessing. (line 52) * startDelayLoop: Delay class-timer process. (line 22) * startFinalizers: ProcessorScheduler-idle tasks. (line 20) * startScript: Package-accessing. (line 109) * startScript_: Package-accessing. (line 112) * startsWith_: SequenceableCollection-comparing. (line 10) * stderr: FileStream class-standard streams. (line 6) * stdin: FileStream class-standard streams. (line 11) * stdout: FileStream class-standard streams. (line 16) * stopScript: Package-accessing. (line 115) * stopScript_: Package-accessing. (line 118) * storage: CObject-accessing. (line 22) * storage_: CObject-accessing. (line 26) * store: Object-storing. (line 6) * store_ <1>: TextCollector-storing. (line 6) * store_: Stream-storing. (line 6) * storeLiteralOn_ <1>: VariableBinding-storing. (line 9) * storeLiteralOn_ <2>: UndefinedObject-storing. (line 9) * storeLiteralOn_ <3>: Symbol-storing. (line 20) * storeLiteralOn_ <4>: String-printing. (line 21) * storeLiteralOn_ <5>: ScaledDecimal-storing. (line 9) * storeLiteralOn_ <6>: Object-storing. (line 10) * storeLiteralOn_ <7>: Integer-printing. (line 52) * storeLiteralOn_ <8>: Float-storing. (line 9) * storeLiteralOn_ <9>: Character-printing. (line 13) * storeLiteralOn_ <10>: ByteArray-storing. (line 9) * storeLiteralOn_ <11>: Boolean-storing. (line 9) * storeLiteralOn_: Array-printing. (line 12) * storeNl: Object-storing. (line 13) * storeOn_ <1>: VariableBinding-storing. (line 12) * storeOn_ <2>: UndefinedObject-storing. (line 12) * storeOn_ <3>: TextCollector-storing. (line 9) * storeOn_ <4>: SystemDictionary-printing. (line 12) * storeOn_ <5>: Symbol-storing. (line 24) * storeOn_ <6>: String-printing. (line 24) * storeOn_ <7>: ScaledDecimal-storing. (line 12) * storeOn_ <8>: RootNamespace-printing. (line 14) * storeOn_ <9>: Rectangle-printing. (line 9) * storeOn_ <10>: ProcessorScheduler-storing. (line 6) * storeOn_ <11>: Point-storing. (line 6) * storeOn_ <12>: Object-storing. (line 17) * storeOn_ <13>: Namespace-printing. (line 14) * storeOn_ <14>: Metaclass-printing. (line 16) * storeOn_ <15>: LookupTable-storing. (line 6) * storeOn_ <16>: LookupKey-storing. (line 6) * storeOn_ <17>: Interval-storing. (line 6) * storeOn_ <18>: Integer-storing. (line 6) * storeOn_ <19>: HomedAssociation-storing. (line 6) * storeOn_ <20>: HashedCollection-storing. (line 6) * storeOn_ <21>: Fraction-printing. (line 9) * storeOn_ <22>: Float-storing. (line 12) * storeOn_ <23>: Duration-storing. (line 6) * storeOn_ <24>: Dictionary-storing. (line 6) * storeOn_ <25>: DeferredVariableBinding-storing. (line 9) * storeOn_ <26>: DateTime-storing. (line 6) * storeOn_ <27>: Date-storing. (line 6) * storeOn_ <28>: CType-storing. (line 6) * storeOn_ <29>: CScalarCType-storing. (line 6) * storeOn_ <30>: CPtrCType-storing. (line 6) * storeOn_ <31>: CompiledMethod-printing. (line 9) * storeOn_ <32>: Collection-storing. (line 6) * storeOn_ <33>: Class-printing. (line 12) * storeOn_ <34>: Character-storing. (line 9) * storeOn_ <35>: CArrayCType-storing. (line 6) * storeOn_ <36>: ByteArray-storing. (line 12) * storeOn_ <37>: Boolean-storing. (line 12) * storeOn_ <38>: Bag-storing. (line 6) * storeOn_ <39>: Association-storing. (line 6) * storeOn_ <40>: ArrayedCollection-storing. (line 6) * storeOn_ <41>: Array-printing. (line 15) * storeOn_: AbstractNamespace-printing. (line 19) * storeOn_base_: Integer-printing. (line 55) * storeString <1>: Object-storing. (line 20) * storeString: Integer-storing. (line 9) * stream <1>: SystemExceptions.EndOfStream-accessing. (line 9) * stream: ObjectDumper-accessing. (line 9) * stream_ <1>: SystemExceptions.EndOfStream-accessing. (line 12) * stream_: ObjectDumper-accessing. (line 13) * streamContents_: ArrayedCollection class-instance creation. (line 19) * strictlyPositive <1>: Number-testing. (line 53) * strictlyPositive <2>: LargeZeroInteger-numeric testing. (line 9) * strictlyPositive <3>: LargePositiveInteger-numeric testing. (line 18) * strictlyPositive <4>: LargeNegativeInteger-numeric testing. (line 18) * strictlyPositive: Float-testing. (line 31) * stringAt_ <1>: Memory class-accessing. (line 70) * stringAt_: ByteArray-more advanced accessing. (line 81) * stringAt_put_ <1>: Memory class-accessing. (line 74) * stringAt_put_: ByteArray-more advanced accessing. (line 86) * stringError_: File class-C functions. (line 9) * stripExtension: FilePath-file name management. (line 31) * stripExtensionFrom_: FilePath class-file name management. (line 34) * stripFileName: FilePath-file name management. (line 34) * stripFileNameFor_: FilePath class-file name management. (line 38) * stripPath: FilePath-file name management. (line 38) * stripPathFrom_: FilePath class-file name management. (line 42) * stripSourceCode <1>: MethodInfo-accessing. (line 38) * stripSourceCode: CompiledMethod class-lean images. (line 6) * subclass_ <1>: UndefinedObject-class polymorphism. (line 22) * subclass_: Class-instance creation. (line 16) * subclass_classInstanceVariableNames_instanceVariableNames_classVariableNames_poolDictionaries_ <1>: UndefinedObject-class creation - alternative. (line 6) * subclass_classInstanceVariableNames_instanceVariableNames_classVariableNames_poolDictionaries_: Class-instance creation - alternative. (line 9) * subclass_declaration_classVariableNames_poolDictionaries_category_: CCompound class-subclass creation. (line 39) * subclass_instanceVariableNames_classVariableNames_poolDictionaries_ <1>: UndefinedObject-class creation - alternative. (line 9) * subclass_instanceVariableNames_classVariableNames_poolDictionaries_: Class-instance creation - alternative. (line 12) * subclass_instanceVariableNames_classVariableNames_poolDictionaries_category_ <1>: UndefinedObject-class polymorphism. (line 27) * subclass_instanceVariableNames_classVariableNames_poolDictionaries_category_: Class-instance creation. (line 21) * subclasses: Behavior-accessing class hierarchy. (line 12) * subclassesDo_: Behavior-enumerating. (line 25) * subclassInstVarNames: Behavior-accessing instances and variables. (line 50) * subclassOf_: Metaclass class-instance creation. (line 6) * subclassResponsibility: Object-built ins. (line 224) * subject: RegexResults-accessing. (line 40) * subspaces: AbstractNamespace-namespace hierarchy. (line 52) * subspacesDo_: AbstractNamespace-namespace hierarchy. (line 55) * substrings: CharacterArray-string processing. (line 71) * subStrings: CharacterArray-string processing. (line 61) * substrings_: CharacterArray-string processing. (line 78) * subStrings_: CharacterArray-string processing. (line 66) * subtractDate_: Date-basic. (line 13) * subtractDays_: Date-basic. (line 17) * subtractTime_: Time-arithmetic. (line 16) * successor: Float-floating point. (line 9) * suggestedSelector: SystemExceptions.WrongMessageSent-accessing. (line 15) * suggestedSelector_: SystemExceptions.WrongMessageSent-accessing. (line 18) * sunitScriptFor_: PackageLoader class-accessing. (line 74) * sunitScripts: Package-accessing. (line 121) * superclass: Behavior-accessing class hierarchy. (line 15) * superclass_ <1>: Class-accessing instances and variables. (line 74) * superclass_: Behavior-creating a class hierarchy. (line 12) * superspace <1>: Dictionary-namespace protocol. (line 46) * superspace: AbstractNamespace-namespace hierarchy. (line 58) * superspace_: AbstractNamespace-namespace hierarchy. (line 61) * survSpaceSize: ObjectMemory-accessing. (line 110) * survSpaceUsedBytes: ObjectMemory-accessing. (line 115) * suspend: Process-builtins. (line 19) * suspendedContext: Process-accessing. (line 29) * suspendedContext_: Process-accessing. (line 33) * swap_with_: SequenceableCollection-manipulation. (line 6) * symbol: SymLink-accessing. (line 6) * symbol_: SymLink-accessing. (line 9) * symbol_nextLink_: SymLink class-instance creation. (line 6) * symlink_as_: File class-file operations. (line 20) * symlink_from_: File class-file operations. (line 23) * symlinkAs_ <1>: VFS.FileWrapper-file operations. (line 13) * symlinkAs_ <2>: FilePath-file operations. (line 46) * symlinkAs_: File-file operations. (line 28) * symlinkFrom_ <1>: VFS.FileWrapper-file operations. (line 17) * symlinkFrom_ <2>: FilePath-file operations. (line 50) * symlinkFrom_: File-file operations. (line 32) * system_: SystemDictionary-c call-outs. (line 21) * system_withArguments_: SystemDictionary-c call-outs. (line 24) * systemBackgroundPriority: ProcessorScheduler-priorities. (line 28) * systemKernel: Directory class-reading system defaults. (line 33) * tab <1>: Stream-character writing. (line 33) * tab: Character class-constants. (line 42) * tab_: Stream-character writing. (line 36) * tag: Exception-accessing. (line 15) * tag_: Exception-accessing. (line 19) * tags: Package class-accessing. (line 6) * tan <1>: Number-misc math. (line 85) * tan: Float-built ins. (line 45) * tanh: Number-misc math. (line 88) * target: Permission-accessing. (line 36) * target_: Permission-accessing. (line 39) * temporary: Directory class-reading system defaults. (line 36) * tenure: Object-built ins. (line 228) * tenuredBytesPerScavenge: ObjectMemory-accessing. (line 119) * terminate: Process-basic. (line 41) * terminateActive: ProcessorScheduler-basic. (line 26) * terminateOnQuit: Process-basic. (line 46) * test: Package-accessing. (line 125) * test_: Package-accessing. (line 128) * third: SequenceableCollection-basic. (line 132) * thisContext: ContextPart class-built ins. (line 6) * timeBetweenGlobalGCs: ObjectMemory-accessing. (line 123) * timeBetweenGrowths: ObjectMemory-accessing. (line 127) * timeBetweenScavenges: ObjectMemory-accessing. (line 131) * timedWaitOn_: Delay-delaying. (line 6) * timeSlice: ProcessorScheduler-basic. (line 29) * timeSlice_: ProcessorScheduler-basic. (line 38) * timesRepeat_: Integer-iterators. (line 6) * timesTwoPower_ <1>: FloatQ-built ins. (line 46) * timesTwoPower_ <2>: FloatE-built ins. (line 46) * timesTwoPower_: FloatD-built ins. (line 46) * timeToCollect: ObjectMemory-accessing. (line 135) * timeToCompact: ObjectMemory-accessing. (line 139) * timeToScavenge: ObjectMemory-accessing. (line 143) * timezone: Time class-builtins. (line 12) * timeZoneAbbreviation: DateTime-time zones. (line 22) * timezoneBias: Time class-builtins. (line 19) * timezoneBias_: Time class-builtins. (line 27) * timeZoneName: DateTime-time zones. (line 29) * timingPriority: ProcessorScheduler-priorities. (line 33) * to: RegexResults-accessing. (line 44) * to_: Number-shortcuts and iterators. (line 6) * to_by_: Number-shortcuts and iterators. (line 9) * to_by_collect_: Number-shortcuts and iterators. (line 13) * to_by_do_: Number-shortcuts and iterators. (line 18) * to_collect_: Number-shortcuts and iterators. (line 24) * to_do_: Number-shortcuts and iterators. (line 29) * toAt_: RegexResults-accessing. (line 48) * today <1>: DateTime class-instance creation. (line 13) * today: Date class-instance creation (Blue Book). (line 33) * tokenize_: String-regex. (line 151) * tokenize_from_to_: String-regex. (line 156) * top: Rectangle-accessing. (line 82) * top_: Rectangle-accessing. (line 85) * topCenter: Rectangle-accessing. (line 88) * topLeft: Rectangle-accessing. (line 91) * topLeft_: Rectangle-accessing. (line 94) * topRight: Rectangle-accessing. (line 97) * topRight_: Rectangle-accessing. (line 100) * touch: FilePath-file operations. (line 54) * touch_: File class-file operations. (line 27) * translateBy_: Rectangle-transforming. (line 18) * translatedToBeWithin_: Rectangle-rectangle functions. (line 46) * transpose: Point-point functions. (line 24) * trigger: DelayedAdaptor-accessing. (line 6) * trimSeparators: CharacterArray-converting. (line 51) * truncate <1>: PositionableStream-truncating. (line 6) * truncate <2>: FileStream-basic. (line 32) * truncate: FileDescriptor-basic. (line 65) * truncated <1>: ScaledDecimal-coercion. (line 39) * truncated <2>: Number-truncation and round off. (line 29) * truncated <3>: Integer-converting. (line 28) * truncated <4>: Fraction-coercing. (line 20) * truncated <5>: FloatQ-built ins. (line 49) * truncated <6>: FloatE-built ins. (line 49) * truncated <7>: FloatD-built ins. (line 49) * truncated: Float-coercing. (line 14) * truncatedGrid_: Point-point functions. (line 28) * truncateTo_ <1>: Point-truncation and round off. (line 10) * truncateTo_: Number-truncation and round off. (line 25) * type <1>: CString class-instance creation. (line 6) * type <2>: CScalar class-instance creation. (line 10) * type <3>: CObject-conversion. (line 17) * type <4>: CObject class-conversion. (line 6) * type <5>: CByte class-conversion. (line 10) * type: CBoolean class-conversion. (line 6) * type_: CObject-accessing. (line 29) * ucharAt_: ByteArray-more advanced accessing. (line 93) * ucharAt_put_ <1>: Memory class-accessing. (line 79) * ucharAt_put_: ByteArray-more advanced accessing. (line 98) * uintAt_: ByteArray-more advanced accessing. (line 104) * uintAt_put_ <1>: Memory class-accessing. (line 84) * uintAt_put_: ByteArray-more advanced accessing. (line 108) * ulongAt_: ByteArray-more advanced accessing. (line 113) * ulongAt_put_ <1>: Memory class-accessing. (line 88) * ulongAt_put_: ByteArray-more advanced accessing. (line 117) * uniqueInstance <1>: ProcessEnvironment class-singleton. (line 6) * uniqueInstance: NullValueHolder class-creating instances. (line 9) * unity <1>: SmallInteger-coercion methods. (line 9) * unity <2>: Number-converting. (line 58) * unity <3>: LargeInteger-coercion. (line 17) * unity <4>: Fraction-coercing. (line 23) * unity <5>: FloatQ-coercing. (line 15) * unity <6>: FloatE-coercing. (line 15) * unity: FloatD-coercing. (line 15) * unpreemptedPriority: ProcessorScheduler-priorities. (line 36) * unscheduleDelay_: Delay class-timer process. (line 25) * unsignedCharAt_ <1>: Memory class-accessing. (line 92) * unsignedCharAt_: ByteArray-more advanced accessing. (line 122) * unsignedCharAt_put_ <1>: Memory class-accessing. (line 96) * unsignedCharAt_put_: ByteArray-more advanced accessing. (line 127) * unsignedIntAt_ <1>: Memory class-accessing. (line 101) * unsignedIntAt_: ByteArray-more advanced accessing. (line 133) * unsignedIntAt_put_ <1>: Memory class-accessing. (line 104) * unsignedIntAt_put_: ByteArray-more advanced accessing. (line 137) * unsignedLongAt_ <1>: Memory class-accessing. (line 108) * unsignedLongAt_: ByteArray-more advanced accessing. (line 142) * unsignedLongAt_put_ <1>: Memory class-accessing. (line 111) * unsignedLongAt_put_: ByteArray-more advanced accessing. (line 146) * unsignedShortAt_ <1>: Memory class-accessing. (line 115) * unsignedShortAt_: ByteArray-more advanced accessing. (line 151) * unsignedShortAt_put_ <1>: Memory class-accessing. (line 118) * unsignedShortAt_put_: ByteArray-more advanced accessing. (line 155) * untilMilliseconds_: Delay class-instance creation. (line 15) * untilNanoseconds_: Delay class-instance creation. (line 19) * update: ObjectMemory-builtins. (line 6) * update_ <1>: VFS.FileWrapper class-initializing. (line 9) * update_ <2>: VFS.ArchiveMember-file operations. (line 16) * update_ <3>: Time class-initialization. (line 9) * update_ <4>: ProcessorScheduler-idle tasks. (line 23) * update_ <5>: Object-change and update. (line 34) * update_ <6>: Object class-initialization. (line 20) * update_ <7>: FileDescriptor class-initialization. (line 9) * update_ <8>: DLD class-dynamic linking. (line 39) * update_: Delay class-still unclassified. (line 6) * updateInstanceVars_shape_: Behavior-still unclassified. (line 14) * updateMember_ <1>: VFS.ZipFile-members. (line 25) * updateMember_: VFS.ArchiveFile-ArchiveMember protocol. (line 25) * upTo_ <1>: Stream-accessing-reading. (line 60) * upTo_ <2>: PositionableStream-accessing-reading. (line 48) * upTo_: FileStream-overriding inherited methods. (line 18) * upToAll_: Stream-accessing-reading. (line 65) * upToEnd <1>: Stream-accessing-reading. (line 72) * upToEnd: PositionableStream-accessing-reading. (line 53) * url: Package-accessing. (line 131) * url_: Package-accessing. (line 134) * use_during_ <1>: ProcessVariable-accessing. (line 10) * use_during_: DynamicVariable class-evaluating. (line 6) * userBackgroundPriority: ProcessorScheduler-priorities. (line 41) * userBase: Directory class-reading system defaults. (line 40) * userInterrupt: Object-VM callbacks. (line 16) * userInterruptPriority: ProcessorScheduler-priorities. (line 44) * username: NetClients.URL-accessing. (line 100) * username_: NetClients.URL-accessing. (line 103) * userSchedulingPriority: ProcessorScheduler-priorities. (line 49) * ushortAt_: ByteArray-more advanced accessing. (line 160) * ushortAt_put_ <1>: Memory class-accessing. (line 122) * ushortAt_put_: ByteArray-more advanced accessing. (line 164) * utcDateAndTimeNow: Date class-instance creation (Blue Book). (line 36) * utcNow: Time class-basic (UTC). (line 10) * utcSecondClock: Time class-basic (UTC). (line 14) * utcToday: Date class-instance creation (Blue Book). (line 40) * validClasses: SystemExceptions.WrongClass-accessing. (line 12) * validClasses_: SystemExceptions.WrongClass-accessing. (line 15) * validClassesString: SystemExceptions.WrongClass-accessing. (line 18) * validSize <1>: Object-debugging. (line 16) * validSize: ContextPart-accessing. (line 115) * value <1>: ValueHolder-accessing. (line 6) * value <2>: ValueAdaptor-accessing. (line 6) * value <3>: SystemExceptions.InvalidValue-accessing. (line 12) * value <4>: Promise-accessing. (line 13) * value <5>: ProcessVariable-accessing. (line 14) * value <6>: PluggableAdaptor-accessing. (line 6) * value <7>: NullValueHolder-accessing. (line 6) * value <8>: DynamicVariable class-evaluating. (line 9) * value <9>: DirectedMessage-basic. (line 12) * value <10>: DelayedAdaptor-accessing. (line 9) * value <11>: DeferredVariableBinding-basic. (line 9) * value <12>: CString-accessing. (line 10) * value <13>: CScalar-accessing. (line 10) * value <14>: CPtr-accessing. (line 12) * value <15>: Continuation-invocation. (line 24) * value <16>: Character-built ins. (line 21) * value <17>: CByte-accessing. (line 9) * value <18>: CBoolean-accessing. (line 6) * value <19>: BlockClosure-built ins. (line 18) * value: Association-accessing. (line 17) * value_ <1>: ValueHolder-accessing. (line 9) * value_ <2>: ValueAdaptor-accessing. (line 10) * value_ <3>: UnicodeCharacter class-built ins. (line 6) * value_ <4>: SystemExceptions.InvalidValue-accessing. (line 15) * value_ <5>: Promise-accessing. (line 16) * value_ <6>: ProcessVariable-accessing. (line 17) * value_ <7>: PluggableAdaptor-accessing. (line 9) * value_ <8>: NullValueHolder-accessing. (line 9) * value_ <9>: DirectedMessage-basic. (line 16) * value_ <10>: DelayedAdaptor-accessing. (line 12) * value_ <11>: DeferredVariableBinding-basic. (line 12) * value_ <12>: CString-accessing. (line 14) * value_ <13>: CString class-instance creation. (line 10) * value_ <14>: CScalar-accessing. (line 14) * value_ <15>: CScalar class-instance creation. (line 14) * value_ <16>: CPtr-accessing. (line 15) * value_ <17>: Continuation-invocation. (line 28) * value_ <18>: Character class-built ins. (line 15) * value_ <19>: CByte-accessing. (line 13) * value_ <20>: CBoolean-accessing. (line 10) * value_ <21>: BlockClosure-built ins. (line 21) * value_: Association-accessing. (line 20) * value_onTimeoutDo_: Delay-timeout. (line 6) * value_value_ <1>: DirectedMessage-basic. (line 20) * value_value_: BlockClosure-built ins. (line 24) * value_value_value_: BlockClosure-built ins. (line 27) * valueAt_: CharacterArray-built ins. (line 6) * valueAt_ifAbsent_: CharacterArray-basic. (line 6) * valueAt_put_: CharacterArray-built ins. (line 10) * valueIfAbsent_ <1>: ProcessVariable-accessing. (line 21) * valueIfAbsent_: DynamicVariable class-evaluating. (line 12) * values <1>: Dictionary-accessing. (line 60) * values: AbstractNamespace-overrides for superspaces. (line 22) * valueType <1>: CType-accessing. (line 29) * valueType: CScalarCType-accessing. (line 6) * valueWithArguments_ <1>: DirectedMessage-basic. (line 24) * valueWithArguments_ <2>: Continuation-invocation. (line 32) * valueWithArguments_: BlockClosure-built ins. (line 30) * valueWithoutInterrupts: BlockClosure-multiple process. (line 28) * valueWithoutInterrupts_: Process-accessing. (line 37) * valueWithoutPreemption: BlockClosure-multiple process. (line 32) * valueWithReceiver_withArguments_: CompiledMethod-invoking. (line 6) * valueWithUnwind: BlockClosure-unwind protection. (line 21) * variable_subclass_instanceVariableNames_classVariableNames_poolDictionaries_category_ <1>: UndefinedObject-class polymorphism. (line 33) * variable_subclass_instanceVariableNames_classVariableNames_poolDictionaries_category_: Class-instance creation. (line 27) * variableByteSubclass_classInstanceVariableNames_classVariableNames_poolDictionaries_: Class-instance creation - alternative. (line 15) * variableByteSubclass_classInstanceVariableNames_instanceVariableNames_classVariableNames_poolDictionaries_: UndefinedObject-class creation - alternative. (line 12) * variableByteSubclass_classVariableNames_poolDictionaries_: Class-instance creation - alternative. (line 18) * variableByteSubclass_instanceVariableNames_classVariableNames_poolDictionaries_: UndefinedObject-class creation - alternative. (line 15) * variableByteSubclass_instanceVariableNames_classVariableNames_poolDictionaries_category_ <1>: UndefinedObject-class polymorphism. (line 41) * variableByteSubclass_instanceVariableNames_classVariableNames_poolDictionaries_category_: Class-instance creation. (line 35) * variableLongSubclass_classInstanceVariableNames_classVariableNames_poolDictionaries_: Class-instance creation - alternative. (line 21) * variableLongSubclass_classInstanceVariableNames_instanceVariableNames_classVariableNames_poolDictionaries_: UndefinedObject-class creation - alternative. (line 18) * variableLongSubclass_classVariableNames_poolDictionaries_: Class-instance creation - alternative. (line 24) * variableLongSubclass_instanceVariableNames_classVariableNames_poolDictionaries_: UndefinedObject-class creation - alternative. (line 21) * variableSubclass_classInstanceVariableNames_instanceVariableNames_classVariableNames_poolDictionaries_ <1>: UndefinedObject-class creation - alternative. (line 24) * variableSubclass_classInstanceVariableNames_instanceVariableNames_classVariableNames_poolDictionaries_: Class-instance creation - alternative. (line 27) * variableSubclass_instanceVariableNames_classVariableNames_poolDictionaries_ <1>: UndefinedObject-class creation - alternative. (line 27) * variableSubclass_instanceVariableNames_classVariableNames_poolDictionaries_: Class-instance creation - alternative. (line 30) * variableSubclass_instanceVariableNames_classVariableNames_poolDictionaries_category_ <1>: UndefinedObject-class polymorphism. (line 47) * variableSubclass_instanceVariableNames_classVariableNames_poolDictionaries_category_: Class-instance creation. (line 41) * variableWordSubclass_instanceVariableNames_classVariableNames_poolDictionaries_category_ <1>: UndefinedObject-class polymorphism. (line 53) * variableWordSubclass_instanceVariableNames_classVariableNames_poolDictionaries_category_: Class-instance creation. (line 47) * verbose_: FileStream class-file-in. (line 69) * verboseTrace: SystemDictionary-builtins. (line 38) * verboseTrace_: SystemDictionary-builtins. (line 41) * verify: CompiledCode-security. (line 6) * version <1>: SystemDictionary-special accessing. (line 16) * version: Package-accessing. (line 138) * version_: Package-accessing. (line 141) * wait <1>: Semaphore-builtins. (line 24) * wait <2>: Duration-processes. (line 6) * wait: Delay-delaying. (line 11) * waitAfterSignalling_: Semaphore-builtins. (line 29) * waitForException: FileDescriptor-accessing. (line 43) * waitingProcesses <1>: Semaphore-accessing. (line 12) * waitingProcesses: RecursionLock-accessing. (line 15) * weeks_: Duration class-instance creation. (line 23) * whichCategoryIncludesSelector_: ClassDescription-organization of messages and classes. (line 32) * whichClassIncludesSelector_: Behavior-testing the method dictionary. (line 21) * whichSelectorsAccess_: Behavior-testing the method dictionary. (line 26) * whichSelectorsAssign_: Behavior-testing the method dictionary. (line 29) * whichSelectorsRead_: Behavior-testing the method dictionary. (line 32) * whichSelectorsReferTo_: Behavior-testing the method dictionary. (line 35) * whichSelectorsReferToByteCode_: Behavior-testing the method dictionary. (line 38) * whileCurrentDo_: AbstractNamespace-copying. (line 9) * whileFalse: BlockClosure-control structures. (line 10) * whileFalse_: BlockClosure-control structures. (line 13) * whileTrue: BlockClosure-control structures. (line 17) * whileTrue_: BlockClosure-control structures. (line 20) * width: Rectangle-accessing. (line 103) * width_: Rectangle-accessing. (line 106) * with_ <1>: WriteStream class-instance creation. (line 10) * with_ <2>: ValueHolder class-creating instances. (line 12) * with_ <3>: Symbol class-instance creation. (line 15) * with_ <4>: Stream-concatenating. (line 6) * with_ <5>: SequenceableCollection-concatenating. (line 17) * with_ <6>: ReadWriteStream class-instance creation. (line 14) * with_ <7>: Collection class-instance creation. (line 16) * with_: ArrayedCollection class-instance creation. (line 24) * with_collect_ <1>: SequenceableCollection-enumerating. (line 77) * with_collect_: ArrayedCollection-enumerating the elements of a collection. (line 19) * with_do_: SequenceableCollection-enumerating. (line 84) * with_from_to_: WriteStream class-instance creation. (line 14) * with_with_ <1>: Symbol class-instance creation. (line 18) * with_with_ <2>: Stream-concatenating. (line 10) * with_with_ <3>: SequenceableCollection-concatenating. (line 23) * with_with_ <4>: Collection class-instance creation. (line 19) * with_with_: ArrayedCollection class-instance creation. (line 27) * with_with_with_ <1>: Symbol class-instance creation. (line 22) * with_with_with_ <2>: Stream-concatenating. (line 14) * with_with_with_ <3>: SequenceableCollection-concatenating. (line 28) * with_with_with_ <4>: Collection class-instance creation. (line 23) * with_with_with_: ArrayedCollection class-instance creation. (line 31) * with_with_with_with_ <1>: Symbol class-instance creation. (line 26) * with_with_with_with_ <2>: Collection class-instance creation. (line 27) * with_with_with_with_: ArrayedCollection class-instance creation. (line 35) * with_with_with_with_with_ <1>: Symbol class-instance creation. (line 30) * with_with_with_with_with_ <2>: Collection class-instance creation. (line 31) * with_with_with_with_with_: ArrayedCollection class-instance creation. (line 39) * withAll_ <1>: Interval class-instance creation. (line 14) * withAll_ <2>: HashedCollection class-instance creation. (line 12) * withAll_ <3>: Collection class-instance creation. (line 35) * withAll_: ArrayedCollection class-instance creation. (line 43) * withAllBlocksDo_: CompiledMethod-accessing. (line 61) * withAllSubclasses: Behavior-accessing class hierarchy. (line 18) * withAllSubclassesDo_: Behavior-enumerating. (line 28) * withAllSubspaces: AbstractNamespace-namespace hierarchy. (line 65) * withAllSubspacesDo_: AbstractNamespace-namespace hierarchy. (line 69) * withAllSuperclasses: Behavior-accessing class hierarchy. (line 22) * withAllSuperclassesDo_: Behavior-enumerating. (line 32) * withAllSuperspaces: Dictionary-namespace protocol. (line 50) * withAllSuperspacesDo_: Dictionary-namespace protocol. (line 54) * withFileDo_: FileSegment-basic. (line 30) * withNewMethodClass_: CompiledMethod-accessing. (line 65) * withNewMethodClass_selector_: CompiledMethod-accessing. (line 69) * withOwner_: SecurityPolicy-modifying. (line 15) * withReadStreamDo_: FilePath-file operations. (line 57) * withShellEscapes <1>: FilePath-printing. (line 15) * withShellEscapes: CharacterArray-string processing. (line 85) * withSignOf_ <1>: Number-misc math. (line 91) * withSignOf_: Float-comparing. (line 16) * withUnixShellEscapes: CharacterArray-still unclassified. (line 6) * withWindowsShellEscapes: CharacterArray-still unclassified. (line 10) * withWriteStreamDo_: FilePath-file operations. (line 61) * working: Directory class-file operations. (line 16) * working_: Directory class-file operations. (line 19) * wouldBlock <1>: Semaphore-accessing. (line 15) * wouldBlock: RecursionLock-accessing. (line 18) * write: FileDescriptor class-instance creation. (line 100) * writeStream <1>: FilePath-file operations. (line 65) * writeStream: ArrayedCollection-streams. (line 6) * x: Point-accessing. (line 6) * x_: Point-accessing. (line 9) * x_y_ <1>: Point-accessing. (line 12) * x_y_: Point class-instance creation. (line 9) * xor_ <1>: True-basic. (line 36) * xor_ <2>: False-basic. (line 35) * xor_: Boolean-basic. (line 42) * y: Point-accessing. (line 15) * y_: Point-accessing. (line 18) * year: Date-date computations. (line 64) * year_day_hour_minute_second_ <1>: DateTime class-instance creation. (line 17) * year_day_hour_minute_second_: Date class-instance creation (ANSI). (line 6) * year_day_hour_minute_second_offset_: DateTime class-instance creation. (line 21) * year_month_day_hour_minute_second_ <1>: DateTime class-instance creation. (line 26) * year_month_day_hour_minute_second_: Date class-instance creation (ANSI). (line 9) * year_month_day_hour_minute_second_offset_: DateTime class-instance creation. (line 31) * yield <1>: ProcessorScheduler-basic. (line 46) * yield: Process-builtins. (line 26) * yield_: Generator-stream protocol. (line 24) * yourself: Object-class type methods. (line 17) * zero <1>: SmallInteger-coercion methods. (line 12) * zero <2>: ScaledDecimal-constants. (line 9) * zero <3>: Number-converting. (line 62) * zero <4>: LargeInteger-coercion. (line 20) * zero <5>: Fraction-coercing. (line 26) * zero <6>: FloatQ-coercing. (line 18) * zero <7>: FloatE-coercing. (line 18) * zero <8>: FloatD-coercing. (line 18) * zero: Duration class-instance creation. (line 26) * zeroDivide: Number-error raising. (line 9) * zip: FilePath-virtual filesystems. (line 6) * | <1>: True-basic. (line 40) * | <2>: False-basic. (line 39) * |: Boolean-basic. (line 46) * ~: String-regex. (line 162) * ~= <1>: SmallInteger-built ins. (line 87) * ~= <2>: ScaledDecimal-comparing. (line 24) * ~= <3>: Object-relational operators. (line 6) * ~= <4>: LargeInteger-testing. (line 21) * ~= <5>: FloatQ-built ins. (line 52) * ~= <6>: FloatE-built ins. (line 52) * ~=: FloatD-built ins. (line 52) * ~~ <1>: SmallInteger-built ins. (line 90) * ~~: Object-relational operators. (line 9) smalltalk-3.2.5/doc/sockets.texi0000644000175000017500000025325412130455677013566 00000000000000@c Define the class index, method index, and selector cross-reference @ifclear CLASS-INDICES @set CLASS-INDICES @defindex cl @defcodeindex me @defcodeindex sl @end ifclear @c These are used for both TeX and HTML @set BEFORE1 @set AFTER1 @set BEFORE2 @set AFTER2 @ifinfo @c Use asis so that leading and trailing spaces are meaningful. @c Remember we're inside a @menu command, hence the blanks are @c kept in the output. @set BEFORE1 @asis{* } @set AFTER1 @asis{::} @set BEFORE2 @asis{ (} @set AFTER2 @asis{)} @end ifinfo @macro class {a,b} @value{BEFORE1}\a\\a\@b{\b\}@value{AFTER1} @end macro @macro superclass {a,b} \a\\a\@value{BEFORE2}@i{\b\}@value{AFTER2} @end macro @ifnotinfo @macro begindetailmenu @display @end macro @macro enddetailmenu @end display @end macro @end ifnotinfo @ifinfo @macro begindetailmenu @detailmenu @end macro @macro enddetailmenu @end detailmenu @end macro @end ifinfo @iftex @macro beginmenu @end macro @macro endmenu @end macro @end iftex @ifnottex @macro beginmenu @menu @end macro @macro endmenu @end menu @end macro @end ifnottex @beginmenu @ifnottex Alphabetic list: * Sockets.AbstractSocket:: * Sockets.AbstractSocketImpl:: * Sockets.CAddrInfoStruct:: * Sockets.CSockAddrIn6Struct:: * Sockets.Datagram:: * Sockets.DatagramSocket:: * Sockets.DatagramSocketImpl:: * Sockets.DummyStream:: * Sockets.ICMP6SocketImpl:: * Sockets.ICMPSocketImpl:: * Sockets.IP6Address:: * Sockets.IPAddress:: * Sockets.MulticastSocket:: * Sockets.MulticastSocketImpl:: * Sockets.OOBSocketImpl:: * Sockets.RawSocketImpl:: * Sockets.ReadBuffer:: * Sockets.ServerSocket:: * Sockets.Socket:: * Sockets.SocketAddress:: * Sockets.SocketImpl:: * Sockets.StreamSocket:: * Sockets.TCPSocketImpl:: * Sockets.UDPSocketImpl:: * Sockets.UnixAddress:: * Sockets.UnixDatagramSocketImpl:: * Sockets.UnixSocketImpl:: * Sockets.WriteBuffer:: @end ifnottex @ifinfo Class tree: @end ifinfo @iftex @section Tree @end iftex @ifnotinfo Classes documented in this manual are @b{boldfaced}. @end ifnotinfo @begindetailmenu @superclass{@t{}, Object} @superclass{@t{ }, CObject} @superclass{@t{ }, CCompound} @superclass{@t{ }, CStruct} @class{@t{ }, Sockets.CAddrInfoStruct} @class{@t{ }, Sockets.CSockAddrIn6Struct} @superclass{@t{ }, Iterable} @superclass{@t{ }, Stream} @superclass{@t{ }, FileDescriptor} @class{@t{ }, Sockets.AbstractSocketImpl} @class{@t{ }, Sockets.DatagramSocketImpl} @class{@t{ }, Sockets.MulticastSocketImpl} @class{@t{ }, Sockets.UDPSocketImpl} @class{@t{ }, Sockets.OOBSocketImpl} @class{@t{ }, Sockets.RawSocketImpl} @class{@t{ }, Sockets.ICMP6SocketImpl} @class{@t{ }, Sockets.ICMPSocketImpl} @class{@t{ }, Sockets.UnixDatagramSocketImpl} @class{@t{ }, Sockets.SocketImpl} @class{@t{ }, Sockets.TCPSocketImpl} @class{@t{ }, Sockets.UnixSocketImpl} @superclass{@t{ }, PositionableStream} @superclass{@t{ }, ReadStream} @class{@t{ }, Sockets.ReadBuffer} @superclass{@t{ }, WriteStream} @class{@t{ }, Sockets.WriteBuffer} @class{@t{ }, Sockets.AbstractSocket} @class{@t{ }, Sockets.DatagramSocket} @class{@t{ }, Sockets.MulticastSocket} @class{@t{ }, Sockets.ServerSocket} @class{@t{ }, Sockets.StreamSocket} @class{@t{ }, Sockets.Socket} @class{@t{ }, Sockets.DummyStream} @class{@t{ }, Sockets.Datagram} @class{@t{ }, Sockets.SocketAddress} @class{@t{ }, Sockets.IP6Address} @class{@t{ }, Sockets.IPAddress} @class{@t{ }, Sockets.UnixAddress} @enddetailmenu @endmenu @unmacro class @unmacro superclass @unmacro endmenu @unmacro beginmenu @unmacro enddetailmenu @unmacro begindetailmenu @node Sockets.AbstractSocket @section Sockets.AbstractSocket @clindex Sockets.AbstractSocket @table @b @item Defined in namespace Sockets @itemx Superclass: Stream @itemx Category: Sockets-Streams This class models a client site socket. A socket is a TCP/IP endpoint for network communications conceptually similar to a file handle. This class only takes care of buffering and blocking if requested. It uses an underlying socket implementation object which is a subclass of AbstractSocketImpl. This is necessary to hide some methods in FileDescriptor that are not relevant to sockets, as well as to implement buffering independently of the implementation nuances required by the different address families. The address family class (a subclass of SocketAddress) acts as a factory for socket implementation objects. @end table @menu * Sockets.AbstractSocket class-defaults:: (class) * Sockets.AbstractSocket class-instance creation:: (class) * Sockets.AbstractSocket class-timed-out operations:: (class) * Sockets.AbstractSocket class-well known ports:: (class) * Sockets.AbstractSocket-accessing:: (instance) * Sockets.AbstractSocket-printing:: (instance) * Sockets.AbstractSocket-socket options:: (instance) * Sockets.AbstractSocket-stream protocol:: (instance) * Sockets.AbstractSocket-testing:: (instance) @end menu @node Sockets.AbstractSocket class-defaults @subsection Sockets.AbstractSocket class:@- defaults @table @b @meindex defaultAddressClass @item defaultAddressClass Answer the default address family to be used. In the library, the address family is represented by a subclass of SocketAddress which is by default IPAddress. @meindex defaultAddressClass:@- @item defaultAddressClass:@- class Set the default address family to be used. In the library, the address family is represented by a subclass of SocketAddress which is by default IPAddress. @meindex defaultImplementationClassFor:@- @item defaultImplementationClassFor:@- aSocketAddressClass Answer the default implementation class. Depending on the subclass, this might be the default stream socket implementation class of the given address class, or rather its default datagram socket implementation class. @end table @node Sockets.AbstractSocket class-instance creation @subsection Sockets.AbstractSocket class:@- instance creation @table @b @meindex new @item new This method should not be called for instances of this class. @meindex new:@- @item new:@- implementation Answer a new instance of the receiver, using as the underlying layer the object passed as the `implementation' parameter; the object is probably going to be some kind of AbstractSocketImpl. @meindex new:@-addressClass:@- @item new:@- implClass addressClass:@- addressClass Answer a new instance of the receiver, using as the underlying layer a new instance of `implementationClass' and using the protocol family of `addressClass'. @end table @node Sockets.AbstractSocket class-timed-out operations @subsection Sockets.AbstractSocket class:@- timed-out operations @table @b @meindex checkPeriod @item checkPeriod Answer the period that is to elapse between socket polls if data data is not ready and the connection is still open (in milliseconds) @meindex checkPeriod:@- @item checkPeriod:@- anInteger Set the period that is to elapse between socket polls if data data is not ready and the connection is still open (in milliseconds) @meindex timeout @item timeout Answer the period that is to elapse between the request for (yet unavailable) data and the moment when the connection is considered dead (in milliseconds) @meindex timeout:@- @item timeout:@- anInteger Set the period that is to elapse between the request for (yet unavailable) data and the moment when the connection is considered dead (in milliseconds) @end table @node Sockets.AbstractSocket class-well known ports @subsection Sockets.AbstractSocket class:@- well known ports @table @b @meindex defaultPortAt:@- @item defaultPortAt:@- protocol Answer the port that is used (by default) for the given service (high level protocol) @meindex defaultPortAt:@-ifAbsent:@- @item defaultPortAt:@- protocol ifAbsent:@- port Answer the port that is used (by default) for the given service (high level protocol), or the specified port if none is registered. @meindex defaultPortAt:@-put:@- @item defaultPortAt:@- protocol put:@- port Associate the given port to the service specified by `protocol'. @meindex portCmdServer @item portCmdServer Answer the port on which the rsh daemon listens @meindex portDNS @item portDNS Answer the port on which the DNS listens @meindex portDayTime @item portDayTime Answer the port on which the TOD service listens @meindex portDiscard @item portDiscard Answer the port on which the DISCARD service listens @meindex portEcho @item portEcho Answer the port on which the ECHO service listens @meindex portExecServer @item portExecServer Answer the port on which the exec server listens @meindex portFTP @item portFTP Answer the port on which the FTP daemon listens @meindex portFinger @item portFinger Answer the port on which the finger daemon listens @meindex portGopher @item portGopher Answer the port on which the Gopher daemon listens @meindex portHTTP @item portHTTP Answer the port on which the http daemon listens @meindex portLoginServer @item portLoginServer Answer the port on which the rlogin daemon listens @meindex portNNTP @item portNNTP Answer the port on which the nntp daemon listens @meindex portNetStat @item portNetStat Answer the port on which the NETSTAT service listens @meindex portPOP3 @item portPOP3 Answer the port on which the pop3 daemon listens @meindex portReserved @item portReserved Answer the last port reserved to privileged processes @meindex portSMTP @item portSMTP Answer the port on which the SMTP daemon listens @meindex portSSH @item portSSH Answer the port on which the SSH daemon listens @meindex portSystat @item portSystat Answer the port on which the SYSTAT service listens @meindex portTelnet @item portTelnet Answer the port on which the TELNET daemon listens @meindex portTimeServer @item portTimeServer Answer the port on which the time server listens @meindex portWhois @item portWhois Answer the port on which the WHOIS daemon listens @end table @node Sockets.AbstractSocket-accessing @subsection Sockets.AbstractSocket:@- accessing @table @b @meindex address @item address Answer an IP address that is of common interest (this can be either the local or the remote address, according to the definition in the subclass). @meindex available @slindex canRead @item available Answer whether there is data available on the socket. Same as #canRead, present for backwards compatibility. @meindex canRead @item canRead Answer whether there is data available on the socket. @meindex canWrite @item canWrite Answer whether there is free space in the socket's write buffer. @meindex close @item close Close the socket represented by the receiver. @meindex flush @item flush Flush any buffers used by the receiver. @meindex isOpen @item isOpen Answer whether the connection between the receiver and the remote endpoint is still alive. @meindex isPeerAlive @item isPeerAlive Answer whether the connection with the peer remote machine is still valid. @meindex localAddress @item localAddress Answer the local IP address of the socket. @meindex localPort @item localPort Answer the local IP port of the socket. @meindex port @item port Answer an IP port that is of common interest (this can be the port for either the local or remote endpoint, according to the definitions in the subclass @meindex remoteAddress @item remoteAddress Answer the IP address of the socket's remote endpoint. @meindex remotePort @item remotePort Answer the IP port of the socket's remote endpoint. @end table @node Sockets.AbstractSocket-printing @subsection Sockets.AbstractSocket:@- printing @table @b @meindex printOn:@- @item printOn:@- aStream Print a representation of the receiver on aStream @end table @node Sockets.AbstractSocket-socket options @subsection Sockets.AbstractSocket:@- socket options @table @b @meindex soLinger @item soLinger Answer the number of seconds that the socket is allowed to wait if it promises reliable delivery but has unacknowledged/untransmitted packets when it is closed, or nil if those packets are left to their destiny or discarded. @meindex soLinger:@- @item soLinger:@- linger Set the number of seconds that the socket is allowed to wait if it promises reliable delivery but has unacknowledged/untransmitted packets when it is closed. @meindex soLingerOff @item soLingerOff Specify that, even if the socket promises reliable delivery, any packets that are unacknowledged/untransmitted when it is closed are to be left to their destiny or discarded. @meindex species @item species Answer `String'. @end table @node Sockets.AbstractSocket-stream protocol @subsection Sockets.AbstractSocket:@- stream protocol @table @b @meindex atEnd @item atEnd By default, answer whether the connection is still open. @meindex next @item next Read another character from the socket, failing if the connection is dead. @meindex next:@-putAll:@-startingAt:@- @item next:@- n putAll:@- aCollection startingAt:@- pos Write `char' to the socket, failing if the connection is dead. The SIGPIPE signal is automatically caught and ignored by the system. @meindex nextPut:@- @item nextPut:@- char Write `char' to the socket, failing if the connection is dead. The SIGPIPE signal is automatically caught and ignored by the system. @end table @node Sockets.AbstractSocket-testing @subsection Sockets.AbstractSocket:@- testing @table @b @meindex isExternalStream @item isExternalStream Answer whether the receiver streams on a file or socket. @end table @node Sockets.AbstractSocketImpl @section Sockets.AbstractSocketImpl @clindex Sockets.AbstractSocketImpl @table @b @item Defined in namespace Sockets @itemx Superclass: FileDescriptor @itemx Category: Sockets-Protocols This abstract class serves as the parent class for socket implementations. The implementation class serves an intermediary to routines that perform the actual socket operations. It hides the buffering and blocking behavior of the Socket classes. A default implementation is provided by each address family, but this can be changed by class methods on SocketAddress sublcasses. @end table @menu * Sockets.AbstractSocketImpl class-abstract:: (class) * Sockets.AbstractSocketImpl class-C call-outs:: (class) * Sockets.AbstractSocketImpl class-C constants:: (class) * Sockets.AbstractSocketImpl class-socket creation:: (class) * Sockets.AbstractSocketImpl-accessing:: (instance) * Sockets.AbstractSocketImpl-asynchronous operations:: (instance) * Sockets.AbstractSocketImpl-C call-outs:: (instance) * Sockets.AbstractSocketImpl-C constants:: (instance) * Sockets.AbstractSocketImpl-socket operations:: (instance) * Sockets.AbstractSocketImpl-socket options:: (instance) @end menu @node Sockets.AbstractSocketImpl class-abstract @subsection Sockets.AbstractSocketImpl class:@- abstract @table @b @meindex addressClass @item addressClass Answer the class responsible for handling addresses for the receiver @meindex protocol @item protocol Answer the protocol parameter for `create' @meindex socketType @item socketType Answer the socket type parameter for `create'. @end table @node Sockets.AbstractSocketImpl class-C call-outs @subsection Sockets.AbstractSocketImpl class:@- C call-outs @table @b @meindex accept:@-peer:@-addrLen:@- @item accept:@- socket peer:@- peer addrLen:@- len Not commented. @meindex bind:@-to:@-addrLen:@- @item bind:@- socket to:@- addr addrLen:@- len Not commented. @meindex connect:@-to:@-addrLen:@- @item connect:@- socket to:@- addr addrLen:@- len Not commented. @meindex create:@-type:@-protocol:@- @item create:@- family type:@- type protocol:@- protocol Not commented. @meindex getPeerName:@-addr:@-addrLen:@- @item getPeerName:@- socket addr:@- addr addrLen:@- len Not commented. @meindex getSockName:@-addr:@-addrLen:@- @item getSockName:@- socket addr:@- addr addrLen:@- len Not commented. @meindex listen:@-log:@- @item listen:@- socket log:@- len Not commented. @meindex option:@-level:@-at:@-get:@-size:@- @item option:@- socket level:@- level at:@- name get:@- value size:@- len Not commented. @meindex option:@-level:@-at:@-put:@-size:@- @item option:@- socket level:@- level at:@- name put:@- value size:@- len Not commented. @meindex receive:@-buffer:@-size:@-flags:@-from:@-size:@- @item receive:@- socket buffer:@- buf size:@- len flags:@- flags from:@- addr size:@- addrLen Not commented. @meindex send:@-buffer:@-size:@-flags:@-to:@-size:@- @item send:@- socket buffer:@- buf size:@- len flags:@- flags to:@- addr size:@- addrLen Not commented. @end table @node Sockets.AbstractSocketImpl class-C constants @subsection Sockets.AbstractSocketImpl class:@- C constants @table @b @meindex soLinger @item soLinger Not commented. @meindex soReuseAddr @item soReuseAddr Not commented. @meindex sockDgram @item sockDgram Not commented. @meindex sockRDM @item sockRDM Not commented. @meindex sockRaw @item sockRaw Not commented. @meindex sockStream @item sockStream Not commented. @meindex solSocket @item solSocket Not commented. @end table @node Sockets.AbstractSocketImpl class-socket creation @subsection Sockets.AbstractSocketImpl class:@- socket creation @table @b @meindex newFor:@- @item newFor:@- addressClass Create a socket for the receiver. @end table @node Sockets.AbstractSocketImpl-accessing @subsection Sockets.AbstractSocketImpl:@- accessing @table @b @meindex connectTo:@-port:@- @item connectTo:@- ipAddress port:@- port Connect the receiver to the given IP address and port. `Connecting' means attaching the remote endpoint of the socket. @meindex localAddress @item localAddress Answer the address of the local endpoint of the socket (even if IP is not being used, this identifies the machine that is bound to the socket). @meindex localPort @item localPort Answer the port of the local endpoint of the socket (even if IP is not being used, this identifies the service or process that is bound to the socket). @meindex remoteAddress @item remoteAddress Answer the address of the remote endpoint of the socket (even if IP is not being used, this identifies the machine to which the socket is connected). @meindex remotePort @item remotePort Answer the port of the remote endpoint of the socket (even if IP is not being used, this identifies the service or process to which the socket is connected). @end table @node Sockets.AbstractSocketImpl-asynchronous operations @subsection Sockets.AbstractSocketImpl:@- asynchronous operations @table @b @meindex ensureReadable @item ensureReadable If the file is open, wait until data can be read from it. The wait allows other Processes to run. @meindex ensureWriteable @item ensureWriteable If the file is open, wait until we can write to it. The wait allows other Processes to run. @meindex waitForException @item waitForException If the file is open, wait until an exceptional condition (such as presence of out of band data) has occurred on it. The wait allows other Processes to run. @end table @node Sockets.AbstractSocketImpl-C call-outs @subsection Sockets.AbstractSocketImpl:@- C call-outs @table @b @meindex accept:@-peer:@-addrLen:@- @item accept:@- socket peer:@- peer addrLen:@- len Not commented. @meindex bind:@-to:@-addrLen:@- @item bind:@- socket to:@- addr addrLen:@- len Not commented. @meindex connect:@-to:@-addrLen:@- @item connect:@- socket to:@- addr addrLen:@- len Not commented. @meindex create:@-type:@-protocol:@- @item create:@- family type:@- type protocol:@- protocol Not commented. @meindex getPeerName:@-addr:@-addrLen:@- @item getPeerName:@- socket addr:@- addr addrLen:@- len Not commented. @meindex getSockName:@-addr:@-addrLen:@- @item getSockName:@- socket addr:@- addr addrLen:@- len Not commented. @meindex listen:@-log:@- @item listen:@- socket log:@- len Not commented. @meindex option:@-level:@-at:@-get:@-size:@- @item option:@- socket level:@- level at:@- name get:@- value size:@- len Not commented. @meindex option:@-level:@-at:@-put:@-size:@- @item option:@- socket level:@- level at:@- name put:@- value size:@- len Not commented. @meindex receive:@-buffer:@-size:@-flags:@-from:@-size:@- @item receive:@- socket buffer:@- buf size:@- len flags:@- flags from:@- addr size:@- addrLen Not commented. @meindex send:@-buffer:@-size:@-flags:@-to:@-size:@- @item send:@- socket buffer:@- buf size:@- len flags:@- flags to:@- addr size:@- addrLen Not commented. @end table @node Sockets.AbstractSocketImpl-C constants @subsection Sockets.AbstractSocketImpl:@- C constants @table @b @meindex soError:@- @item soError:@- socket Not commented. @end table @node Sockets.AbstractSocketImpl-socket operations @subsection Sockets.AbstractSocketImpl:@- socket operations @table @b @meindex accept:@- @item accept:@- implementationClass Accept a connection on the receiver, and create a new instance of implementationClass that will deal with the newly created active server socket. @meindex bindTo:@-port:@- @item bindTo:@- ipAddress port:@- port Bind the receiver to the given IP address and port. `Binding' means attaching the local endpoint of the socket. @meindex fileOp:@- @item fileOp:@- ioFuncIndex Private - Used to limit the number of primitives used by FileStreams @meindex fileOp:@-ifFail:@- @item fileOp:@- ioFuncIndex ifFail:@- aBlock Private - Used to limit the number of primitives used by FileStreams. @meindex fileOp:@-with:@- @item fileOp:@- ioFuncIndex with:@- arg1 Private - Used to limit the number of primitives used by FileStreams @meindex fileOp:@-with:@-ifFail:@- @item fileOp:@- ioFuncIndex with:@- arg1 ifFail:@- aBlock Private - Used to limit the number of primitives used by FileStreams. @meindex fileOp:@-with:@-with:@- @item fileOp:@- ioFuncIndex with:@- arg1 with:@- arg2 Private - Used to limit the number of primitives used by FileStreams @meindex fileOp:@-with:@-with:@-ifFail:@- @item fileOp:@- ioFuncIndex with:@- arg1 with:@- arg2 ifFail:@- aBlock Private - Used to limit the number of primitives used by FileStreams. @meindex fileOp:@-with:@-with:@-with:@- @item fileOp:@- ioFuncIndex with:@- arg1 with:@- arg2 with:@- arg3 Private - Used to limit the number of primitives used by FileStreams @meindex fileOp:@-with:@-with:@-with:@-ifFail:@- @item fileOp:@- ioFuncIndex with:@- arg1 with:@- arg2 with:@- arg3 ifFail:@- aBlock Private - Used to limit the number of primitives used by FileStreams. @meindex getSockName @item getSockName Retrieve a ByteArray containing a sockaddr_in struct for the local endpoint of the socket. @meindex listen:@- @item listen:@- backlog Make the receiver a passive server socket with a pending connections queue of the given size. @end table @node Sockets.AbstractSocketImpl-socket options @subsection Sockets.AbstractSocketImpl:@- socket options @table @b @meindex optionAt:@-level:@-put:@- @item optionAt:@- opt level:@- level put:@- anObject Modify the value of a socket option. The option identifier is in `opt' and the level is in `level'. anObject can be a boolean, integer, socket address or ByteArray. A layer over this method is provided for the most common socket options, so this will be rarely used. @meindex optionAt:@-level:@-size:@- @item optionAt:@- opt level:@- level size:@- size Answer in a ByteArray of the given size the value of a socket option. The option identifier is in `opt' and the level is in `level'. A layer over this method is provided for the most common socket options, so this will be rarely used. @meindex soLinger @item soLinger Answer the number of seconds by which a `close' operation can block to ensure that all the packets have reliably reached the destination, or nil if those packets are left to their destiny. @meindex soLinger:@- @item soLinger:@- linger Set the number of seconds by which a `close' operation can block to ensure that all the packets have reliably reached the destination. If linger is nil, those packets are left to their destiny. @meindex soReuseAddr @item soReuseAddr Answer whether another socket can be bound the same local address as this one. If you enable this option, you can actually have two sockets with the same Internet port number; but the system won't allow you to use the two identically-named sockets in a way that would confuse the Internet. The reason for this option is that some higher-level Internet protocols, including FTP, require you to keep reusing the same socket number. @meindex soReuseAddr:@- @item soReuseAddr:@- aBoolean Set whether another socket can be bound the same local address as this one. @meindex valueWithoutBuffering:@- @item valueWithoutBuffering:@- aBlock Evaluate aBlock, ensuring that any data that it writes to the socket is sent immediately to the network. @end table @node Sockets.CAddrInfoStruct @section Sockets.CAddrInfoStruct @clindex Sockets.CAddrInfoStruct @table @b @item Defined in namespace Sockets @itemx Superclass: CStruct @itemx Category: @end table @menu * Sockets.CAddrInfoStruct class-C call-outs:: (class) * Sockets.CAddrInfoStruct-C call-outs:: (instance) * Sockets.CAddrInfoStruct-C function wrappers:: (instance) @end menu @node Sockets.CAddrInfoStruct class-C call-outs @subsection Sockets.CAddrInfoStruct class:@- C call-outs @table @b @meindex getaddrinfo:@-service:@-hints:@-result:@- @item getaddrinfo:@- name service:@- servname hints:@- hints result:@- res Not commented. @end table @node Sockets.CAddrInfoStruct-C call-outs @subsection Sockets.CAddrInfoStruct:@- C call-outs @table @b @meindex aiAddr @item aiAddr Not commented. @meindex aiCanonname @item aiCanonname Not commented. @meindex free @item free Not commented. @end table @node Sockets.CAddrInfoStruct-C function wrappers @subsection Sockets.CAddrInfoStruct:@- C function wrappers @table @b @meindex getaddrinfo:@- @item getaddrinfo:@- name Not commented. @meindex getaddrinfo:@-service:@- @item getaddrinfo:@- name service:@- service Not commented. @end table @node Sockets.CSockAddrIn6Struct @section Sockets.CSockAddrIn6Struct @clindex Sockets.CSockAddrIn6Struct @table @b @item Defined in namespace Sockets @itemx Superclass: CStruct @itemx Category: @end table @menu @end menu @node Sockets.Datagram @section Sockets.Datagram @clindex Sockets.Datagram @table @b @item Defined in namespace Sockets @itemx Superclass: Object @itemx Category: Sockets-Protocols This class models a packet of data that is to be sent across the network using a connectionless protocol such as UDP. It contains the data to be send, as well as the destination address and port. Note that datagram packets can arrive in any order and are not guaranteed to be delivered at all. This class can also be used for receiving data from the network. @end table @menu * Sockets.Datagram class-instance creation:: (class) * Sockets.Datagram-accessing:: (instance) @end menu @node Sockets.Datagram class-instance creation @subsection Sockets.Datagram class:@- instance creation @table @b @meindex data:@- @item data:@- aByteArray Answer a new datagram with the specified data. @meindex data:@-address:@-port:@- @item data:@- aByteArray address:@- ipAddress port:@- port Answer a new datagram with the specified target socket, and aByteArray as its data. @meindex object:@-address:@-port:@- @slindex object:@-objectDumper:@-address:@-port:@- @item object:@- object address:@- ipAddress port:@- port Serialize the object onto a ByteArray, and create a Datagram with the object as its contents, and the specified receiver. Note that each invocation of this method creates a separate ObjectDumper; if different objects that you're sending are likely to contain references to the same objects, you should use #object:@-objectDumper:@-address:@-port:@-. @meindex object:@-objectDumper:@-address:@-port:@- @item object:@- object objectDumper:@- od address:@- ipAddress port:@- port Serialize the object onto a ByteArray, and create a Datagram with the object as its contents, and the specified receiver. Serialization takes place through ObjectDumper passed as `od', and the stream attached to the ObjectDumper is resetted every time. Using this method is indicated if different objects that you're sending are likely to contain references to the same objects. @end table @node Sockets.Datagram-accessing @subsection Sockets.Datagram:@- accessing @table @b @meindex address @item address Answer the address of the target socket @meindex address:@- @item address:@- ipAddress Set the address of the target socket @meindex data @item data Answer the data attached to the datagram @meindex data:@- @item data:@- aByteArray Set the data attached to the datagram @meindex dataSize @item dataSize Answer the size of the message. @meindex dataSize:@- @item dataSize:@- aSize I am called to update the size... @meindex get @slindex object:@-address:@-port:@- @item get Parse the data attached to the datagram through a newly created ObjectDumper, and answer the resulting object. This method is complementary to #object:@-address:@-port:@-. @meindex getThrough:@- @slindex object:@-objectDumper:@-address:@-port:@- @item getThrough:@- objectDumper Parse the data attached to the datagram through the given ObjectDumper without touching the stream to which it is attached, and answer the resulting object. The state of the ObjectDumper, though, is updated. This method is complementary to #object:@-objectDumper:@-address:@-port:@-. @meindex port @item port Answer the IP port of the target socket @meindex port:@- @item port:@- thePort Set the IP port of the target socket @meindex size @item size I determine the size of the datagram. It is either an explicitly specified dataSize, or the size of the whole collection. @end table @node Sockets.DatagramSocket @section Sockets.DatagramSocket @clindex Sockets.DatagramSocket @table @b @item Defined in namespace Sockets @itemx Superclass: Sockets.AbstractSocket @itemx Category: Sockets-Streams This class models a connectionless datagram socket that sends individual packets of data across the network. In the TCP/IP world, this means UDP. Datagram packets do not have guaranteed delivery, or any guarantee about the order the data will be received on the remote host. This class uses an underlying socket implementation object which is a subclass of DatagramSocketImpl. This is less necessary for datagram sockets than for stream sockets (except for hiding some methods in FileDescriptor that are not relevant to sockets), but it is done for cleanliness and symmetry. @end table @menu * Sockets.DatagramSocket class-accessing:: (class) * Sockets.DatagramSocket class-initialization:: (class) * Sockets.DatagramSocket class-instance creation:: (class) * Sockets.DatagramSocket-accessing:: (instance) * Sockets.DatagramSocket-direct operations:: (instance) @end menu @node Sockets.DatagramSocket class-accessing @subsection Sockets.DatagramSocket class:@- accessing @table @b @meindex defaultBufferSize @item defaultBufferSize Answer the default maximum size for input datagrams. @meindex defaultBufferSize:@- @item defaultBufferSize:@- size Set the default maximum size for input datagrams. @meindex defaultImplementationClassFor:@- @item defaultImplementationClassFor:@- aSocketAddressClass Answer the default implementation class. Depending on the subclass, this might be the default stream socket implementation class of the given address class, or rather its default datagram socket implementation class. @end table @node Sockets.DatagramSocket class-initialization @subsection Sockets.DatagramSocket class:@- initialization @table @b @meindex initialize @item initialize Initialize the class to use an input datagram size of 128. @end table @node Sockets.DatagramSocket class-instance creation @subsection Sockets.DatagramSocket class:@- instance creation @table @b @meindex local:@-port:@- @item local:@- ipAddressOrString port:@- remotePort Create a new socket and bind it to the given host (passed as a String to be resolved or as an IPAddress), on the given port. @meindex new @item new Answer a new datagram socket (by default an UDP socket), without a specified local address and port. @meindex port:@- @item port:@- localPort Create a new socket and bind it to the local host on the given port. @meindex remote:@-port:@-local:@-port:@- @item remote:@- ipAddressOrString port:@- remotePort local:@- ipAddress port:@- localPort Create a new socket and bind it to the given host (passed as a String to be resolved or as a SocketAddress), and to the given remotePort. The default destination for the datagrams will be ipAddressOrString (if not nil), on the remotePort port. @end table @node Sockets.DatagramSocket-accessing @subsection Sockets.DatagramSocket:@- accessing @table @b @meindex address @item address Answer the local address. @meindex bufferSize @item bufferSize Answer the size of the buffer in which datagrams are stored. @meindex bufferSize:@- @item bufferSize:@- size Set the size of the buffer in which datagrams are stored. @meindex datagramClass @item datagramClass Answer the class used by the socket to return datagrams. @meindex next @item next Read a datagram on the socket and answer it. @meindex nextPut:@- @item nextPut:@- aDatagram Send the given datagram on the socket. @meindex peek @item peek Peek for a datagram on the socket and answer it. @meindex peek:@- @item peek:@- datagram Peek for a datagram on the socket, store it in `datagram', and answer the datagram itself. @meindex port @item port Answer the local port. @meindex receive:@- @item receive:@- datagram Read a datagram from the socket, store it in `datagram', and answer the datagram itself. @end table @node Sockets.DatagramSocket-direct operations @subsection Sockets.DatagramSocket:@- direct operations @table @b @meindex nextFrom:@-port:@- @item nextFrom:@- ipAddress port:@- port Answer the next datagram from the given address and port. @end table @node Sockets.DatagramSocketImpl @section Sockets.DatagramSocketImpl @clindex Sockets.DatagramSocketImpl @table @b @item Defined in namespace Sockets @itemx Superclass: Sockets.AbstractSocketImpl @itemx Category: Sockets-Protocols This abstract class serves as the parent class for datagram socket implementations. @end table @menu * Sockets.DatagramSocketImpl class-parameters:: (class) * Sockets.DatagramSocketImpl-accessing:: (instance) * Sockets.DatagramSocketImpl-C constants:: (instance) * Sockets.DatagramSocketImpl-socket operations:: (instance) @end menu @node Sockets.DatagramSocketImpl class-parameters @subsection Sockets.DatagramSocketImpl class:@- parameters @table @b @meindex datagramClass @item datagramClass Answer the datagram class returned by default by instances of this class. @meindex socketType @item socketType Answer the socket type parameter for `create'. @end table @node Sockets.DatagramSocketImpl-accessing @subsection Sockets.DatagramSocketImpl:@- accessing @table @b @meindex bufferSize @item bufferSize Answer the size of the buffer in which datagrams are stored. @meindex bufferSize:@- @item bufferSize:@- size Set the size of the buffer in which datagrams are stored. @end table @node Sockets.DatagramSocketImpl-C constants @subsection Sockets.DatagramSocketImpl:@- C constants @table @b @meindex ipAddMembership @item ipAddMembership Not commented. @meindex ipDropMembership @item ipDropMembership Not commented. @meindex ipMulticastIf @item ipMulticastIf Not commented. @meindex ipMulticastTtl @item ipMulticastTtl Not commented. @meindex msgPeek @item msgPeek Not commented. @end table @node Sockets.DatagramSocketImpl-socket operations @subsection Sockets.DatagramSocketImpl:@- socket operations @table @b @meindex next @item next Retrieve a datagram from the receiver, answer a new object of the receiver's datagram class. @meindex nextPut:@- @item nextPut:@- aDatagram Send aDatagram on the socket @meindex peek @item peek Peek for a datagram on the receiver, answer a new object of the receiver's datagram class. @meindex peek:@- @item peek:@- aDatagram Peek for a datagram on the receiver, answer aDatagram modified to contain information on the newly received datagram. @meindex receive:@- @item receive:@- aDatagram Retrieve a datagram from the receiver, answer aDatagram modified to contain information on the newly received datagram. @meindex receive:@-datagram:@- @item receive:@- flags datagram:@- aDatagram Receive a new datagram into `datagram', with the given flags, and answer `datagram' itself; this is an abstract method. The flags can be zero to receive the datagram, or `self msgPeek' to only peek for it without removing it from the queue. @meindex send:@-to:@-port:@- @item send:@- aDatagram to:@- theReceiver port:@- port Send aDatagram on the socket to the given receiver and port @end table @node Sockets.DummyStream @section Sockets.DummyStream @clindex Sockets.DummyStream @table @b @item Defined in namespace Sockets @itemx Superclass: Stream @itemx Category: Sockets-Tests @end table @menu @end menu @node Sockets.ICMP6SocketImpl @section Sockets.ICMP6SocketImpl @clindex Sockets.ICMP6SocketImpl @table @b @item Defined in namespace Sockets @itemx Superclass: Sockets.RawSocketImpl @itemx Category: Sockets-Protocols Unless the application installs its own implementation, this is the default socket implementation that will be used for IPv6 raw sockets. It uses C call-outs to implement standard BSD style sockets of family AF_INET, type SOCK_RAW, protocol IPPROTO_ICMPV6. @end table @menu * Sockets.ICMP6SocketImpl class-C constants:: (class) @end menu @node Sockets.ICMP6SocketImpl class-C constants @subsection Sockets.ICMP6SocketImpl class:@- C constants @table @b @meindex protocol @item protocol Not commented. @end table @node Sockets.ICMPSocketImpl @section Sockets.ICMPSocketImpl @clindex Sockets.ICMPSocketImpl @table @b @item Defined in namespace Sockets @itemx Superclass: Sockets.RawSocketImpl @itemx Category: Sockets-Protocols Unless the application installs its own implementation, this is the default socket implementation that will be used for IPv4 raw sockets. It uses C call-outs to implement standard BSD style sockets of family AF_INET, type SOCK_RAW, protocol IPPROTO_ICMP. @end table @menu * Sockets.ICMPSocketImpl class-C constants:: (class) @end menu @node Sockets.ICMPSocketImpl class-C constants @subsection Sockets.ICMPSocketImpl class:@- C constants @table @b @meindex protocol @item protocol Not commented. @end table @node Sockets.IP6Address @section Sockets.IP6Address @clindex Sockets.IP6Address @table @b @item Defined in namespace Sockets @itemx Superclass: Sockets.SocketAddress @itemx Category: Sockets-Protocols This class models an IPv6 address. It also acts as a factory for IPv6 stream (TCP), datagram (UDP) and raw sockets. @end table @menu * Sockets.IP6Address class-C constants:: (class) * Sockets.IP6Address class-constants:: (class) * Sockets.IP6Address class-initialization:: (class) * Sockets.IP6Address class-instance creation:: (class) * Sockets.IP6Address-accessing:: (instance) * Sockets.IP6Address-printing:: (instance) @end menu @node Sockets.IP6Address class-C constants @subsection Sockets.IP6Address class:@- C constants @table @b @meindex addressFamily @item addressFamily Not commented. @meindex aiAll @item aiAll Not commented. @meindex aiV4mapped @item aiV4mapped Not commented. @meindex protocolFamily @item protocolFamily Not commented. @end table @node Sockets.IP6Address class-constants @subsection Sockets.IP6Address class:@- constants @table @b @meindex addressSize @item addressSize Answer the size of an IPv4 address. @meindex version @item version Answer the version of IP that the receiver implements. @end table @node Sockets.IP6Address class-initialization @subsection Sockets.IP6Address class:@- initialization @table @b @meindex createLoopbackHost @item createLoopbackHost Answer an object representing the loopback host in the address family for the receiver. This is ::@-1 for IPv4. @meindex createUnknownAddress @item createUnknownAddress Answer an object representing an unkown address in the address family for the receiver @meindex initialize @item initialize Set up the default implementation classes for the receiver @end table @node Sockets.IP6Address class-instance creation @subsection Sockets.IP6Address class:@- instance creation @table @b @meindex fromArray:@- @item fromArray:@- parts Answer a new IP6Address from an array of numbers; the numbers are to be thought as the colon-separated numbers in the standard numbers-and-colons notation for IPv4 addresses. @meindex fromBytes:@- @item fromBytes:@- aByteArray Answer a new IP6Address from a ByteArray containing the bytes in the same order as the digit form:@- 131.175.6.2 would be represented as #[131 175 6 2]. @meindex fromSockAddr:@-port:@- @item fromSockAddr:@- aByteArray port:@- portAdaptor Private - Answer a new IP6Address from a ByteArray containing a C sockaddr_in structure. The portAdaptor's value is changed to contain the port that the structure refers to. @meindex fromString:@- @item fromString:@- aString Answer a new IP6Address from a String containing the requested address in digit form. @meindex new @item new This method should not be called for instances of this class. @end table @node Sockets.IP6Address-accessing @subsection Sockets.IP6Address:@- accessing @table @b @meindex asByteArray @item asByteArray Answer a read-only ByteArray of size four containing the receiver's bytes in network order (big-endian) @meindex isMulticast @item isMulticast Answer whether the receiver reprensents an address reserved for multicast datagram connections @end table @node Sockets.IP6Address-printing @subsection Sockets.IP6Address:@- printing @table @b @meindex printOn:@- @item printOn:@- aStream Print the receiver in dot notation. @end table @node Sockets.IPAddress @section Sockets.IPAddress @clindex Sockets.IPAddress @table @b @item Defined in namespace Sockets @itemx Superclass: Sockets.SocketAddress @itemx Category: Sockets-Protocols This class models an IPv4 address. It also acts as a factory for IPv4 stream (TCP), datagram (UDP) and raw sockets. @end table @menu * Sockets.IPAddress class-C constants:: (class) * Sockets.IPAddress class-constants:: (class) * Sockets.IPAddress class-initialization:: (class) * Sockets.IPAddress class-instance creation:: (class) * Sockets.IPAddress-accessing:: (instance) * Sockets.IPAddress-printing:: (instance) @end menu @node Sockets.IPAddress class-C constants @subsection Sockets.IPAddress class:@- C constants @table @b @meindex addressFamily @item addressFamily Not commented. @meindex protocolFamily @item protocolFamily Not commented. @end table @node Sockets.IPAddress class-constants @subsection Sockets.IPAddress class:@- constants @table @b @meindex addressSize @item addressSize Answer the size of an IPv4 address. @meindex version @item version Answer the version of IP that the receiver implements. @end table @node Sockets.IPAddress class-initialization @subsection Sockets.IPAddress class:@- initialization @table @b @meindex createLoopbackHost @item createLoopbackHost Answer an object representing the loopback host in the address family for the receiver. This is 127.0.0.1 for IPv4. @meindex createUnknownAddress @item createUnknownAddress Answer an object representing an unkown address in the address family for the receiver @meindex initialize @item initialize Set up the default implementation classes for the receiver @end table @node Sockets.IPAddress class-instance creation @subsection Sockets.IPAddress class:@- instance creation @table @b @meindex fromArray:@- @item fromArray:@- parts Answer a new IPAddress from an array of numbers; the numbers are to be thought as the dot-separated numbers in the standard numbers-and-dots notation for IPv4 addresses. @meindex fromBytes:@- @item fromBytes:@- aByteArray Answer a new IPAddress from a ByteArray containing the bytes in the same order as the digit form:@- 131.175.6.2 would be represented as #[131 175 6 2]. @meindex fromSockAddr:@-port:@- @item fromSockAddr:@- aByteArray port:@- portAdaptor Private - Answer a new IPAddress from a ByteArray containing a C sockaddr_in structure. The portAdaptor's value is changed to contain the port that the structure refers to. @meindex fromString:@- @slindex loopbackHost @item fromString:@- aString Answer a new IPAddress from a String containing the requested address in digit form. Hexadecimal forms are not allowed. An Internet host address is a number containing four bytes of data. These are divided into two parts, a network number and a local network address number within that network. The network number consists of the first one, two or three bytes; the rest of the bytes are the local address. Network numbers are registered with the Network Information Center (NIC), and are divided into three classes--A, B, and C. The local network address numbers of individual machines are registered with the administrator of the particular network. Class A networks have single-byte numbers in the range 0 to 127. There are only a small number of Class A networks, but they can each support a very large number of hosts (several millions). Medium-sized Class B networks have two-byte network numbers, with the first byte in the range 128 to 191; they support several thousands of host, but are almost exhausted. Class C networks are the smallest and the most commonly available; they have three-byte network numbers, with the first byte in the range 192-223. Class D (multicast, 224.0.0.0 to 239.255.255.255) and E (research, 240.0.0.0 to 255.255.255.255) also have three-byte network numbers. Thus, the first 1, 2, or 3 bytes of an Internet address specifies a network. The remaining bytes of the Internet address specify the address within that network. The Class A network 0 is reserved for broadcast to all networks. In addition, the host number 0 within each network is reserved for broadcast to all hosts in that network. The Class A network 127 is reserved for loopback; you can always use the Internet address `127.0.0.1' to refer to the host machine (this is answered by the #loopbackHost class method). Since a single machine can be a member of multiple networks, it can have multiple Internet host addresses. However, there is never supposed to be more than one machine with the same host address. There are four forms of the standard numbers-and-dots notation for Internet addresses:@- a.b.c.d specifies all four bytes of the address individually; a.b.c interprets as a 2-byte quantity, which is useful for specifying host addresses in a Class B network with network address number a.b; a.b intrprets the last part of the address as a 3-byte quantity, which is useful for specifying host addresses in a Class A network with network address number a. If only one part is given, this corresponds directly to the host address number. @meindex new @item new This method should not be called for instances of this class. @meindex with:@-with:@-with:@-with:@- @item with:@- b1 with:@- b2 with:@- b3 with:@- b4 Answer a new IPAddress whose bytes (from most-significant to least-significant) are in the parameters. @end table @node Sockets.IPAddress-accessing @subsection Sockets.IPAddress:@- accessing @table @b @meindex addressClass @slindex fromString:@- @item addressClass Answer the `address class' of the receiver (see IPAddress class>>@-#fromString:@-) @meindex asByteArray @item asByteArray Answer a read-only ByteArray of size four containing the receiver's bytes in network order (big-endian) @meindex host @item host Answer an host number for the receiver; this is given by the last three bytes for class A addresses, by the last two bytes for class B addresses, else by the last byte. @meindex isMulticast @item isMulticast Answer whether the receiver reprensents an address reserved for multicast datagram connections @meindex network @item network Answer a network number for the receiver; this is given by the first three bytes for class C/D/E addresses, by the first two bytes for class B addresses, else by the first byte. @meindex subnet @item subnet Answer an host number for the receiver; this is 0 for class A addresses, while it is given by the last byte of the network number for class B/C/D/E addresses. @end table @node Sockets.IPAddress-printing @subsection Sockets.IPAddress:@- printing @table @b @meindex printOn:@- @item printOn:@- aStream Print the receiver in dot notation. @end table @node Sockets.MulticastSocket @section Sockets.MulticastSocket @clindex Sockets.MulticastSocket @table @b @item Defined in namespace Sockets @itemx Superclass: Sockets.DatagramSocket @itemx Category: Sockets-Streams This class models a multicast socket that sends packets to a multicast group. All members of the group listening on that address and port will receive all the messages sent to the group. In the TCP/IP world, these sockets are UDP-based and a multicast group consists of a multicast address (a class D internet address, i.e. one whose most significant bits are 1110), and a well known port number. @end table @menu * Sockets.MulticastSocket-instance creation:: (instance) @end menu @node Sockets.MulticastSocket-instance creation @subsection Sockets.MulticastSocket:@- instance creation @table @b @meindex interface @item interface Answer the local device supporting the multicast socket. This is usually set to any local address. @meindex interface:@- @item interface:@- ipAddress Set the local device supporting the multicast socket. This is usually set to any local address. @meindex join:@- @item join:@- ipAddress Join the multicast socket at the given IP address @meindex leave:@- @item leave:@- ipAddress Leave the multicast socket at the given IP address @meindex nextPut:@-timeToLive:@- @item nextPut:@- packet timeToLive:@- timeToLive Send the datagram with a specific TTL (time-to-live) @meindex timeToLive @item timeToLive Answer the socket's datagrams' default time-to-live @meindex timeToLive:@- @item timeToLive:@- newTTL Set the default time-to-live for the socket's datagrams @end table @node Sockets.MulticastSocketImpl @section Sockets.MulticastSocketImpl @clindex Sockets.MulticastSocketImpl @table @b @item Defined in namespace Sockets @itemx Superclass: Sockets.DatagramSocketImpl @itemx Category: Sockets-Protocols This abstract class serves as the parent class for datagram socket implementations that support multicast. @end table @menu * Sockets.MulticastSocketImpl-multicasting:: (instance) @end menu @node Sockets.MulticastSocketImpl-multicasting @subsection Sockets.MulticastSocketImpl:@- multicasting @table @b @meindex ipMulticastIf @item ipMulticastIf Answer the local device for a multicast socket (in the form of an address) @meindex ipMulticastIf:@- @item ipMulticastIf:@- interface Set the local device for a multicast socket (in the form of an address, usually anyLocalAddress) @meindex join:@- @item join:@- ipAddress Join the multicast socket at the given address @meindex leave:@- @item leave:@- ipAddress Leave the multicast socket at the given address @meindex timeToLive @item timeToLive Answer the time to live of the datagrams sent through the receiver to a multicast socket. @meindex timeToLive:@- @item timeToLive:@- ttl Set the time to live of the datagrams sent through the receiver to a multicast socket. @end table @node Sockets.OOBSocketImpl @section Sockets.OOBSocketImpl @clindex Sockets.OOBSocketImpl @table @b @item Defined in namespace Sockets @itemx Superclass: Sockets.DatagramSocketImpl @itemx Category: Sockets-Protocols This abstract class serves as the parent class for socket implementations that send out-of-band data over a stream socket. @end table @menu * Sockets.OOBSocketImpl-C constants:: (instance) * Sockets.OOBSocketImpl-implementation:: (instance) @end menu @node Sockets.OOBSocketImpl-C constants @subsection Sockets.OOBSocketImpl:@- C constants @table @b @meindex msgOOB @item msgOOB Not commented. @end table @node Sockets.OOBSocketImpl-implementation @subsection Sockets.OOBSocketImpl:@- implementation @table @b @meindex canRead @item canRead Answer whether out-of-band data is available on the socket @meindex ensureReadable @item ensureReadable Stop the process until an error occurs or out-of-band data becomes available on the socket @end table @node Sockets.RawSocketImpl @section Sockets.RawSocketImpl @clindex Sockets.RawSocketImpl @table @b @item Defined in namespace Sockets @itemx Superclass: Sockets.DatagramSocketImpl @itemx Category: Sockets-Protocols This abstract class serves as the parent class for raw socket implementations. Raw socket packets are modeled as datagrams. @end table @menu * Sockets.RawSocketImpl class-parameters:: (class) @end menu @node Sockets.RawSocketImpl class-parameters @subsection Sockets.RawSocketImpl class:@- parameters @table @b @meindex socketType @item socketType Answer the socket type parameter for `create'. @end table @node Sockets.ReadBuffer @section Sockets.ReadBuffer @clindex Sockets.ReadBuffer @table @b @item Defined in namespace Sockets @itemx Superclass: ReadStream @itemx Category: Examples-Useful tools I'm a ReadStream that, when the end of the stream is reached, evaluates an user defined block to try to get some more data. @end table @menu * Sockets.ReadBuffer class-instance creation:: (class) * Sockets.ReadBuffer-accessing-reading:: (instance) * Sockets.ReadBuffer-buffer handling:: (instance) @end menu @node Sockets.ReadBuffer class-instance creation @subsection Sockets.ReadBuffer class:@- instance creation @table @b @meindex on:@- @item on:@- aCollection Answer a Stream that uses aCollection as a buffer. You should ensure that the fillBlock is set before the first operation, because the buffer will report that the data has ended until you set the fillBlock. @end table @node Sockets.ReadBuffer-accessing-reading @subsection Sockets.ReadBuffer:@- accessing-reading @table @b @meindex nextAvailable:@-into:@-startingAt:@- @item nextAvailable:@- anInteger into:@- aCollection startingAt:@- pos Place the next anInteger objects from the receiver into aCollection, starting at position pos. Return the number of items stored. @meindex nextAvailable:@-putAllOn:@- @item nextAvailable:@- anInteger putAllOn:@- aStream Copy the next anInteger objects from the receiver to aStream. Return the number of items stored. @meindex upTo:@- @item upTo:@- anObject Returns a collection of the same type that the stream accesses, up to but not including the object anObject. Returns the entire rest of the stream's contents if anObject is not present. @meindex upToEnd @item upToEnd Returns a collection of the same type that the stream accesses, up to but not including the object anObject. Returns the entire rest of the stream's contents if anObject is not present. @end table @node Sockets.ReadBuffer-buffer handling @subsection Sockets.ReadBuffer:@- buffer handling @table @b @meindex atEnd @item atEnd Answer whether the data stream has ended. @meindex availableBytes @item availableBytes Answer how many bytes are available in the buffer. @meindex bufferContents @item bufferContents Answer the data that is in the buffer, and empty it. @meindex close @item close Not commented. @meindex fill @item fill Fill the buffer with more data if it is empty, and answer true if the fill block was able to read more data. @meindex fillBlock:@- @item fillBlock:@- block Set the block that fills the buffer. It receives a collection and the number of bytes to fill in it, and must return the number of bytes actually read @meindex isEmpty @item isEmpty Answer whether the next input operation will force a buffer fill @meindex isFull @item isFull Answer whether the buffer has been just filled @meindex notEmpty @item notEmpty Check whether the next input operation will force a buffer fill and answer true if it will not. @meindex pastEnd @item pastEnd Try to fill the buffer if the data stream has ended. @end table @node Sockets.ServerSocket @section Sockets.ServerSocket @clindex Sockets.ServerSocket @table @b @item Defined in namespace Sockets @itemx Superclass: Sockets.AbstractSocket @itemx Category: Sockets-Streams This class models server side sockets. The basic model is that the server socket is created and bound to some well known port. It then listens for and accepts connections. At that point the client and server sockets are ready to communicate with one another utilizing whatever application layer protocol they desire. As with the other AbstractSocket subclasses, most instance methods of this class simply redirect their calls to an implementation class. @end table @menu * Sockets.ServerSocket class-accessing:: (class) * Sockets.ServerSocket class-instance creation:: (class) * Sockets.ServerSocket-accessing:: (instance) * Sockets.ServerSocket-initializing:: (instance) @end menu @node Sockets.ServerSocket class-accessing @subsection Sockets.ServerSocket class:@- accessing @table @b @meindex defaultImplementationClassFor:@- @item defaultImplementationClassFor:@- aSocketAddressClass Answer the default implementation class. @end table @node Sockets.ServerSocket class-instance creation @subsection Sockets.ServerSocket class:@- instance creation @table @b @meindex defaultQueueSize @slindex accept @item defaultQueueSize Answer the default length of the queue for pending connections. When the queue fills, new clients attempting to connect fail until the server has sent #accept to accept a connection from the queue. @meindex port:@- @item port:@- anInteger Answer a new ServerSocket serving on any local address, on the given port, with a pending connections queue of the default length. @meindex port:@-bindTo:@- @item port:@- anInteger bindTo:@- ipAddress Answer a new ServerSocket serving on the given address and port, with a pending connections queue of the default length. @meindex port:@-queueSize:@- @item port:@- anInteger queueSize:@- backlog Answer a new ServerSocket serving on any local address, on the given port, with a pending connections queue of the given length. @meindex port:@-queueSize:@-bindTo:@- @item port:@- anInteger queueSize:@- backlog bindTo:@- ipAddress Answer a new ServerSocket serving on the given address and port, and with a pending connections queue of the given length. @meindex queueSize:@- @item queueSize:@- backlog Answer a new ServerSocket serving on any local address and port, with a pending connections queue of the given length. @meindex queueSize:@-bindTo:@- @item queueSize:@- backlog bindTo:@- ipAddress Answer a new ServerSocket serving on the given local address, and on any port, with a pending connections queue of the given length. @end table @node Sockets.ServerSocket-accessing @subsection Sockets.ServerSocket:@- accessing @table @b @meindex accept @item accept Accept a new connection and create a new instance of Socket if there is one, else answer nil. @meindex accept:@- @item accept:@- socketClass Accept a new connection and create a new instance of socketClass if there is one, else answer nil. This is usually needed only to create DatagramSockets. @meindex address @item address Answer the local address @meindex port @item port Answer the local port (the port that the passive socket is listening on). @meindex primAccept:@- @item primAccept:@- socketClass Accept a new connection and create a new instance of Socket if there is one, else fail. @meindex waitForConnection @item waitForConnection Wait for a connection to be available, and suspend the currently executing process in the meanwhile. @end table @node Sockets.ServerSocket-initializing @subsection Sockets.ServerSocket:@- initializing @table @b @meindex port:@-queueSize:@-bindTo:@- @item port:@- anInteger queueSize:@- backlog bindTo:@- localAddr Initialize the ServerSocket so that it serves on the given address and port, and has a pending connections queue of the given length. @end table @node Sockets.Socket @section Sockets.Socket @clindex Sockets.Socket @table @b @item Defined in namespace Sockets @itemx Superclass: Sockets.StreamSocket @itemx Category: Sockets-Streams This class adds read and write buffers to the basic model of AbstractSocket. @end table @menu * Sockets.Socket class-accessing:: (class) * Sockets.Socket class-tests:: (class) * Sockets.Socket class-well known ports:: (class) * Sockets.Socket-stream protocol:: (instance) @end menu @node Sockets.Socket class-accessing @subsection Sockets.Socket class:@- accessing @table @b @meindex writeBufferSize @item writeBufferSize Answer the size of the write buffer for newly-created sockets @meindex writeBufferSize:@- @item writeBufferSize:@- anInteger Set the size of the write buffer for newly-created sockets @end table @node Sockets.Socket class-tests @subsection Sockets.Socket class:@- tests @table @b @meindex datagramLoopbackTest @item datagramLoopbackTest Send data from one datagram socket to another on the local machine. Tests most of the socket primitives and works with different processes. @meindex datagramLoopbackTestOn:@- @item datagramLoopbackTestOn:@- addressClass Send data from one datagram socket to another on the local machine. Tests most of the socket primitives and works with different processes. @meindex loopbackTest @item loopbackTest Send data from one socket to another on the local machine. Tests most of the socket primitives. @meindex loopbackTest:@- @item loopbackTest:@- bufferSizes Send data from one socket to another on the local machine. Tests most of the socket primitives. The parameter is the size of the input and output buffer sizes. @meindex loopbackTest:@-addressClass:@- @item loopbackTest:@- bufferSizes addressClass:@- addressClass Send data from one socket to another on the local machine. Tests most of the socket primitives. The parameters are the size of the input and output buffer sizes, and the address class (family) to use. @meindex loopbackTestOn:@- @item loopbackTestOn:@- addressClass Send data from one socket to another on the local machine. Tests most of the socket primitives. The parameter is the address class (family) to use. @meindex microTest @item microTest Extremely small test (try to receive SMTP header) @meindex producerConsumerTest @item producerConsumerTest Send data from one datagram socket to another on the local machine. Tests most of the socket primitives and works with different processes. @meindex producerConsumerTestOn:@- @item producerConsumerTestOn:@- addressClass Send data from one socket to another on the local machine. Tests most of the socket primitives and works with different processes. @meindex sendTest @item sendTest Send data to the 'discard' socket of localhost. @meindex sendTest:@- @item sendTest:@- host Send data to the 'discard' socket of the given host. Tests the speed of one-way data transfers across the network to the given host. Note that many hosts do not run a discard server. @meindex testPort2For:@- @item testPort2For:@- anAddressClass Not commented. @meindex testPortFor:@- @item testPortFor:@- anAddressClass Not commented. @meindex tweakedLoopbackTest @item tweakedLoopbackTest Send data from one socket to another on the local machine, trying to avoid buffering overhead. Tests most of the socket primitives. Comparison of the results of loopbackTest and tweakedLoopbackTest should give a measure of the overhead of buffering when sending/receiving large quantities of data. @end table @node Sockets.Socket class-well known ports @subsection Sockets.Socket class:@- well known ports @table @b @meindex initialize @item initialize Initialize the receiver's defaults @end table @node Sockets.Socket-stream protocol @subsection Sockets.Socket:@- stream protocol @table @b @meindex canWrite @item canWrite Answer whether more data is available in the socket's read buffer or from the operating system. @meindex ensureWriteable @item ensureWriteable Answer whether more data is available in the socket's read buffer or from the operating system. @meindex flush @item flush Flush the write buffer to the operating system @meindex next:@-putAll:@-startingAt:@- @item next:@- n putAll:@- aCollection startingAt:@- pos Write aString to the socket; this acts as a bit-bucket when the socket is closed. This might yield control to other Smalltalk Processes. @meindex nextPut:@- @item nextPut:@- char Write a character to the socket; this acts as a bit-bucket when the socket is closed. This might yield control to other Smalltalk Processes. @meindex writeBufferSize:@- @item writeBufferSize:@- size Create a new write buffer of the given size, flushing the old one is needed. This might yield control to other Smalltalk Processes. @end table @node Sockets.SocketAddress @section Sockets.SocketAddress @clindex Sockets.SocketAddress @table @b @item Defined in namespace Sockets @itemx Superclass: Object @itemx Category: Sockets-Protocols This class is the abstract class for machine addresses over a network. It also fulfills the function of the C style functions gethostname(), gethostbyname(), and gethostbyaddr(), resolves machine names into their corresponding numeric addresses (via DNS, /etc/hosts, or other mechanisms) and vice versa. @end table @menu * Sockets.SocketAddress class-abstract:: (class) * Sockets.SocketAddress class-accessing:: (class) * Sockets.SocketAddress class-C call-outs:: (class) * Sockets.SocketAddress class-C constants:: (class) * Sockets.SocketAddress class-creating sockets:: (class) * Sockets.SocketAddress class-host name lookup:: (class) * Sockets.SocketAddress class-initialization:: (class) * Sockets.SocketAddress-accessing:: (instance) * Sockets.SocketAddress-testing:: (instance) @end menu @node Sockets.SocketAddress class-abstract @subsection Sockets.SocketAddress class:@- abstract @table @b @meindex extractFromSockAddr:@-port:@- @item extractFromSockAddr:@- aByteArray port:@- portAdaptor Private - Answer a new SocketAddress from a ByteArray containing a C sockaddr structure. The portAdaptor's value is changed to contain the port that the structure refers to. @meindex fromSockAddr:@-port:@- @item fromSockAddr:@- aByteArray port:@- portAdaptor Private - Answer a new IPAddress from a ByteArray containing a C sockaddr structure. The portAdaptor's value is changed to contain the port that the structure refers to. Raise an error if the address family is unknown. @end table @node Sockets.SocketAddress class-accessing @subsection Sockets.SocketAddress class:@- accessing @table @b @meindex anyLocalAddress @item anyLocalAddress Answer an IPAddress representing a local address. @meindex at:@-cache:@- @item at:@- host cache:@- aBlock Private - Answer the list of addresses associated to the given host in the cache. If the host is not cached yet, evaluate aBlock and cache and answer the result. @meindex defaultDatagramSocketImplClass @item defaultDatagramSocketImplClass Answer the class that, by default, is used to map between the Socket's protocol and a low-level C interface. @meindex defaultDatagramSocketImplClass:@- @item defaultDatagramSocketImplClass:@- aClass Set which class will be used by default to map between the receiver's protocol and a low-level C interface. @meindex defaultRawSocketImplClass @item defaultRawSocketImplClass Answer the class that, by default, is used to map between the Socket's protocol and a low-level C interface. @meindex defaultRawSocketImplClass:@- @item defaultRawSocketImplClass:@- aClass Set which class will be used by default to map between the receiver's protocol and a low-level C interface. @meindex defaultStreamSocketImplClass @item defaultStreamSocketImplClass Answer the class that, by default, is used to map between the Socket's protocol and a low-level C interface. @meindex defaultStreamSocketImplClass:@- @item defaultStreamSocketImplClass:@- aClass Set which class will be used by default to map between the receiver's protocol and a low-level C interface. @meindex isDigitAddress:@- @item isDigitAddress:@- aString Answer whether the receiver can interpret aString as a valid address without going through a resolver. @meindex localHostName @item localHostName Answer the name of the local machine. @meindex loopbackHost @item loopbackHost Answer an instance of the receiver representing the local machine (127.0.0.1 in the IPv4 family). @meindex unknownAddress @item unknownAddress Answer an instance of the receiver representing an unknown machine (0.0.0.0 in the IPv4 family). @end table @node Sockets.SocketAddress class-C call-outs @subsection Sockets.SocketAddress class:@- C call-outs @table @b @meindex primLocalName @item primLocalName Not commented. @meindex primName:@-len:@-type:@- @item primName:@- address len:@- len type:@- addressFamily Not commented. @end table @node Sockets.SocketAddress class-C constants @subsection Sockets.SocketAddress class:@- C constants @table @b @meindex addressFamily @item addressFamily Not commented. @meindex aiAddrconfig @item aiAddrconfig Not commented. @meindex aiCanonname @item aiCanonname Not commented. @meindex protocolFamily @item protocolFamily Not commented. @end table @node Sockets.SocketAddress class-creating sockets @subsection Sockets.SocketAddress class:@- creating sockets @table @b @meindex newRawSocket @item newRawSocket Create a new raw socket, providing access to low-level network protocols and interfaces for the protocol family represented by the receiver (for example, the C protocol family PF_INET for the IPAddress class) Ordinary user programs usually have no need to use this method. @end table @node Sockets.SocketAddress class-host name lookup @subsection Sockets.SocketAddress class:@- host name lookup @table @b @meindex allByName:@- @item allByName:@- aString Answer all the IP addresses that refer to the the given host. If a digit address is passed in aString, the result is an array containing the single passed address. If the host could not be resolved to an IP address, answer nil. @meindex byName:@- @slindex fromString:@- @item byName:@- aString Answer a single IP address that refer to the the given host. If a digit address is passed in aString, the result is the same as using #fromString:@-. If the host could not be resolved to an IP address, answer nil. @end table @node Sockets.SocketAddress class-initialization @subsection Sockets.SocketAddress class:@- initialization @table @b @meindex anyLocalAddress:@- @item anyLocalAddress:@- anObject Private - Store an object representing a local address in the address family for the receiver @meindex createLoopbackHost @item createLoopbackHost Answer an object representing the loopback host in the address family for the receiver. @meindex createUnknownAddress @item createUnknownAddress Answer an object representing an unkown address in the address family for the receiver @meindex flush @item flush Flush the cached IP addresses. @meindex initLocalAddresses @item initLocalAddresses Private - Initialize the anyLocalAddress class-instance variable for the entire hierarchy. @meindex update:@- @item update:@- aspect Flush all the caches for IPAddress subclasses @end table @node Sockets.SocketAddress-accessing @subsection Sockets.SocketAddress:@- accessing @table @b @meindex = @item = aSocketAddress Answer whether the receiver and aSocketAddress represent the same machine. The host name is not checked because an IPAddress created before a DNS is activated is named after its numbers-and-dots notation, while the same IPAddress, created when a DNS is active, is named after its resolved name. @meindex asByteArray @item asByteArray Convert the receiver to a ByteArray passed to the operating system's socket functions) @meindex hash @item hash Answer an hash value for the receiver @meindex name @item name Answer the host name (or the digit notation if the DNS could not resolve the address). If the DNS answers a different IP address for the same name, the second response is not cached and the digit notation is also returned (somebody's likely playing strange jokes with your DNS). @end table @node Sockets.SocketAddress-testing @subsection Sockets.SocketAddress:@- testing @table @b @meindex isMulticast @item isMulticast Answer whether an address is reserved for multicast connections. @end table @node Sockets.SocketImpl @section Sockets.SocketImpl @clindex Sockets.SocketImpl @table @b @item Defined in namespace Sockets @itemx Superclass: Sockets.AbstractSocketImpl @itemx Category: Sockets-Protocols This abstract class serves as the parent class for stream socket implementations. @end table @menu * Sockets.SocketImpl class-parameters:: (class) * Sockets.SocketImpl-abstract:: (instance) * Sockets.SocketImpl-socket operations:: (instance) @end menu @node Sockets.SocketImpl class-parameters @subsection Sockets.SocketImpl class:@- parameters @table @b @meindex socketType @item socketType Answer the socket type parameter for `create'. @end table @node Sockets.SocketImpl-abstract @subsection Sockets.SocketImpl:@- abstract @table @b @meindex outOfBandImplClass @item outOfBandImplClass Return an implementation class to be used for out-of-band data on the receiver. @end table @node Sockets.SocketImpl-socket operations @subsection Sockets.SocketImpl:@- socket operations @table @b @meindex connectTo:@-port:@- @item connectTo:@- ipAddress port:@- port Try to connect the socket represented by the receiver to the given remote machine. @meindex getPeerName @item getPeerName Retrieve a ByteArray containing a sockaddr_in struct for the remote endpoint of the socket. @end table @node Sockets.StreamSocket @section Sockets.StreamSocket @clindex Sockets.StreamSocket @table @b @item Defined in namespace Sockets @itemx Superclass: Sockets.AbstractSocket @itemx Category: Sockets-Streams This class adds a read buffer to the basic model of AbstractSocket. @end table @menu * Sockets.StreamSocket class-accessing:: (class) * Sockets.StreamSocket class-initialize:: (class) * Sockets.StreamSocket class-instance creation:: (class) * Sockets.StreamSocket-accessing:: (instance) * Sockets.StreamSocket-accessing-reading:: (instance) * Sockets.StreamSocket-out-of-band data:: (instance) * Sockets.StreamSocket-printing:: (instance) * Sockets.StreamSocket-stream protocol:: (instance) @end menu @node Sockets.StreamSocket class-accessing @subsection Sockets.StreamSocket class:@- accessing @table @b @meindex defaultImplementationClassFor:@- @item defaultImplementationClassFor:@- aSocketAddressClass Answer the default implementation class. Depending on the subclass, this might be the default stream socket implementation class of the given address class, or rather its default datagram socket implementation class. @meindex readBufferSize @item readBufferSize Answer the size of the read buffer for newly-created sockets @meindex readBufferSize:@- @item readBufferSize:@- anInteger Set the size of the read buffer for newly-created sockets @end table @node Sockets.StreamSocket class-initialize @subsection Sockets.StreamSocket class:@- initialize @table @b @meindex initialize @item initialize Initialize the receiver's defaults @end table @node Sockets.StreamSocket class-instance creation @subsection Sockets.StreamSocket class:@- instance creation @table @b @meindex remote:@-port:@- @item remote:@- ipAddressOrString port:@- remotePort Create a new socket and connect to the given host (passed as a String to be resolved or as a SocketAddress), and to the given port. @meindex remote:@-port:@-local:@-port:@- @item remote:@- ipAddressOrString port:@- remotePort local:@- ipAddress port:@- localPort Create a new socket and connect to the given host (passed as a String to be resolved or as a SocketAddress), and to the given remotePort. Then bind it to the local address passed in ipAddress, on the localPort port; if the former is nil, any local address will do, and if the latter is 0, any local port will do. @end table @node Sockets.StreamSocket-accessing @subsection Sockets.StreamSocket:@- accessing @table @b @meindex address @item address Answer the address of the remote endpoint @meindex port @item port Answer the port of the remote endpoint @end table @node Sockets.StreamSocket-accessing-reading @subsection Sockets.StreamSocket:@- accessing-reading @table @b @meindex nextAvailable:@-into:@-startingAt:@- @item nextAvailable:@- anInteger into:@- aCollection startingAt:@- pos Place up to anInteger objects from the receiver into aCollection, starting from position pos and stopping if no more data is available. @meindex nextAvailable:@-putAllOn:@- @item nextAvailable:@- anInteger putAllOn:@- aStream Copy up to anInteger objects from the receiver to aStream, stopping if no more data is available. @end table @node Sockets.StreamSocket-out-of-band data @subsection Sockets.StreamSocket:@- out-of-band data @table @b @meindex outOfBand @item outOfBand Return a datagram socket to be used for receiving out-of-band data on the receiver. @end table @node Sockets.StreamSocket-printing @subsection Sockets.StreamSocket:@- printing @table @b @meindex printOn:@- @item printOn:@- aStream Print a representation of the receiver on aStream @end table @node Sockets.StreamSocket-stream protocol @subsection Sockets.StreamSocket:@- stream protocol @table @b @meindex atEnd @item atEnd Answer whether more data is available on the socket @meindex availableBytes @item availableBytes Answer how many bytes are available in the socket's read buffer or from the operating system. @meindex bufferContents @item bufferContents Answer the current contents of the read buffer @meindex canRead @item canRead Answer whether more data is available in the socket's read buffer or from the operating system. @meindex close @item close Flush and close the socket. @meindex fill @item fill Fill the read buffer with data read from the socket @meindex isPeerAlive @item isPeerAlive Answer whether the connection with the peer remote machine is still valid. @meindex next @item next Read a byte from the socket. This might yield control to other Smalltalk Processes. @meindex peek @item peek Read a byte from the socket, without advancing the buffer; answer nil if no more data is available. This might yield control to other Smalltalk Processes. @meindex peekFor:@- @item peekFor:@- anObject Read a byte from the socket, advancing the buffer only if it matches anObject; answer whether they did match or not. This might yield control to other Smalltalk Processes. @meindex readBufferSize:@- @item readBufferSize:@- size Create a new read buffer of the given size (which is only possible before the first read or if the current buffer is empty). @end table @node Sockets.TCPSocketImpl @section Sockets.TCPSocketImpl @clindex Sockets.TCPSocketImpl @table @b @item Defined in namespace Sockets @itemx Superclass: Sockets.SocketImpl @itemx Category: Sockets-Protocols Unless the application installs its own implementation, this is the default socket implementation that will be used for IPv4 stream sockets. It uses C call-outs to implement standard BSD style sockets of family AF_INET and type SOCK_STREAM. @end table @menu * Sockets.TCPSocketImpl class-C constants:: (class) * Sockets.TCPSocketImpl-socket options:: (instance) @end menu @node Sockets.TCPSocketImpl class-C constants @subsection Sockets.TCPSocketImpl class:@- C constants @table @b @meindex ipprotoTcp @item ipprotoTcp Not commented. @meindex protocol @item protocol Not commented. @meindex tcpNodelay @item tcpNodelay Not commented. @end table @node Sockets.TCPSocketImpl-socket options @subsection Sockets.TCPSocketImpl:@- socket options @table @b @meindex valueWithoutBuffering:@- @item valueWithoutBuffering:@- aBlock Evaluate aBlock, ensuring that any data that it writes to the socket is sent immediately to the network. @end table @node Sockets.UDPSocketImpl @section Sockets.UDPSocketImpl @clindex Sockets.UDPSocketImpl @table @b @item Defined in namespace Sockets @itemx Superclass: Sockets.MulticastSocketImpl @itemx Category: Sockets-Protocols Unless the application installs its own implementation, this is the default socket implementation that will be used for IPv4 datagram sockets. It uses C call-outs to implement standard BSD style sockets of family AF_INET and type SOCK_DGRAM. @end table @menu * Sockets.UDPSocketImpl class-C constants:: (class) * Sockets.UDPSocketImpl-multicasting:: (instance) @end menu @node Sockets.UDPSocketImpl class-C constants @subsection Sockets.UDPSocketImpl class:@- C constants @table @b @meindex ipprotoIp @item ipprotoIp Not commented. @meindex protocol @item protocol Not commented. @end table @node Sockets.UDPSocketImpl-multicasting @subsection Sockets.UDPSocketImpl:@- multicasting @table @b @meindex ipMulticastIf @item ipMulticastIf Answer the local device for a multicast socket (in the form of an address) @meindex ipMulticastIf:@- @item ipMulticastIf:@- interface Set the local device for a multicast socket (in the form of an address, usually anyLocalAddress) @meindex join:@- @item join:@- ipAddress Join the multicast socket at the given address @meindex leave:@- @item leave:@- ipAddress Leave the multicast socket at the given address @meindex primJoinLeave:@-option:@- @item primJoinLeave:@- ipAddress option:@- opt Private - Used to join or leave a multicast service. @meindex timeToLive @item timeToLive Answer the time to live of the datagrams sent through the receiver to a multicast socket. @meindex timeToLive:@- @item timeToLive:@- ttl Set the time to live of the datagrams sent through the receiver to a multicast socket. @end table @node Sockets.UnixAddress @section Sockets.UnixAddress @clindex Sockets.UnixAddress @table @b @item Defined in namespace Sockets @itemx Superclass: Sockets.SocketAddress @itemx Category: Sockets-Protocols This class represents an address for a machine using the AF_UNIX address family. Since this address family is only used for local sockets, the class is a singleton; the filesystem path to the socket is represented using the port argument to socket functions, as either a String or a File object. @end table @menu * Sockets.UnixAddress class-C constants:: (class) * Sockets.UnixAddress class-initialization:: (class) * Sockets.UnixAddress class-instance creation:: (class) * Sockets.UnixAddress-accessing:: (instance) * Sockets.UnixAddress-printing:: (instance) * Sockets.UnixAddress-testing:: (instance) @end menu @node Sockets.UnixAddress class-C constants @subsection Sockets.UnixAddress class:@- C constants @table @b @meindex addressFamily @item addressFamily Not commented. @meindex protocolFamily @item protocolFamily Not commented. @end table @node Sockets.UnixAddress class-initialization @subsection Sockets.UnixAddress class:@- initialization @table @b @meindex createLoopbackHost @item createLoopbackHost Answer an object representing the loopback host in the address family for the receiver. This is 127.0.0.1 for IPv4. @meindex createUnknownAddress @item createUnknownAddress Answer an object representing an unkown address in the address family for the receiver @meindex initialize @item initialize Set up the default implementation classes for the receiver @end table @node Sockets.UnixAddress class-instance creation @subsection Sockets.UnixAddress class:@- instance creation @table @b @meindex fromSockAddr:@-port:@- @item fromSockAddr:@- aByteArray port:@- portAdaptor Private - Answer the unique UnixAddress instance, filling in the portAdaptor's value from a ByteArray containing a C sockaddr_in structure. @meindex uniqueInstance @item uniqueInstance Not commented. @end table @node Sockets.UnixAddress-accessing @subsection Sockets.UnixAddress:@- accessing @table @b @meindex = @item = aSocketAddress Answer whether the receiver and aSocketAddress represent the same socket on the same machine. @meindex hash @item hash Answer an hash value for the receiver @end table @node Sockets.UnixAddress-printing @subsection Sockets.UnixAddress:@- printing @table @b @meindex printOn:@- @item printOn:@- aStream Print the receiver in dot notation. @end table @node Sockets.UnixAddress-testing @subsection Sockets.UnixAddress:@- testing @table @b @meindex isMulticast @item isMulticast Answer whether an address is reserved for multicast connections. @end table @node Sockets.UnixDatagramSocketImpl @section Sockets.UnixDatagramSocketImpl @clindex Sockets.UnixDatagramSocketImpl @table @b @item Defined in namespace Sockets @itemx Superclass: Sockets.DatagramSocketImpl @itemx Category: Sockets-Protocols This class represents a datagram socket using the AF_UNIX address family. It unlinks the filesystem path when the socket is closed. @end table @menu * Sockets.UnixDatagramSocketImpl-socket operations:: (instance) @end menu @node Sockets.UnixDatagramSocketImpl-socket operations @subsection Sockets.UnixDatagramSocketImpl:@- socket operations @table @b @meindex close @item close Not commented. @end table @node Sockets.UnixSocketImpl @section Sockets.UnixSocketImpl @clindex Sockets.UnixSocketImpl @table @b @item Defined in namespace Sockets @itemx Superclass: Sockets.SocketImpl @itemx Category: Sockets-Protocols This class represents a stream socket using the AF_UNIX address family. It unlinks the filesystem path when the socket is closed. @end table @menu * Sockets.UnixSocketImpl-socket operations:: (instance) @end menu @node Sockets.UnixSocketImpl-socket operations @subsection Sockets.UnixSocketImpl:@- socket operations @table @b @meindex close @item close Not commented. @end table @node Sockets.WriteBuffer @section Sockets.WriteBuffer @clindex Sockets.WriteBuffer @table @b @item Defined in namespace Sockets @itemx Superclass: WriteStream @itemx Category: Examples-Useful tools I'm a WriteStream that, instead of growing the collection, evaluates an user defined block and starts over with the same collection. @end table @menu * Sockets.WriteBuffer-accessing-writing:: (instance) * Sockets.WriteBuffer-buffer handling:: (instance) * Sockets.WriteBuffer-testing:: (instance) @end menu @node Sockets.WriteBuffer-accessing-writing @subsection Sockets.WriteBuffer:@- accessing-writing @table @b @meindex next:@-putAll:@-startingAt:@- @item next:@- n putAll:@- aCollection startingAt:@- pos Put n characters or bytes of aCollection, starting at the pos-th, in the collection buffer. @end table @node Sockets.WriteBuffer-buffer handling @subsection Sockets.WriteBuffer:@- buffer handling @table @b @meindex close @item close Not commented. @meindex flush @item flush Evaluate the flushing block and reset the stream @meindex flushBlock:@- @item flushBlock:@- block Set which block will be used to flush the buffer. The block will be evaluated with a collection and an Integer n as parameters, and will have to write the first n elements of the collection. @end table @node Sockets.WriteBuffer-testing @subsection Sockets.WriteBuffer:@- testing @table @b @meindex isFull @item isFull Not commented. @end table smalltalk-3.2.5/doc/gst-base.info-30000644000175000017500000074244712130456007013735 00000000000000This is gst-base.info, produced by makeinfo version 4.13 from /home/ich/source/smalltalk/release/smalltalk/doc/gst-base-fixed.texi. INFO-DIR-SECTION Software development START-INFO-DIR-ENTRY * Smalltalk base classes: (gst-base). The GNU Smalltalk base classes. END-INFO-DIR-ENTRY Permission is granted to copy, distribute and/or modify this document under the terms of the GNU Free Documentation License, Version 1.2 or any later version published by the Free Software Foundation; with no Invariant Sections, with no Front-Cover Texts, and with no Back-Cover Texts. A copy of the license is included in the section entitled "GNU Free Documentation License".  File: gst-base.info, Node: Random class-instance creation, Next: Random class-shortcuts, Up: Random 1.139.1 Random class: instance creation --------------------------------------- new Create a new random number generator whose seed is given by the current time on the millisecond clock seed: aFloat Create a new random number generator whose seed is aFloat  File: gst-base.info, Node: Random class-shortcuts, Next: Random-basic, Prev: Random class-instance creation, Up: Random 1.139.2 Random class: shortcuts ------------------------------- between: low and: high Return a random integer between the given extrema next Return a random number between 0 and 1 (excluded) source Return a standard source of random numbers.  File: gst-base.info, Node: Random-basic, Next: Random-testing, Prev: Random class-shortcuts, Up: Random 1.139.3 Random: basic --------------------- atEnd This stream never ends. Always answer false. between: low and: high Return a random integer between low and high. next Return the next random number in the sequence. nextPut: value This method should not be called for instances of this class.  File: gst-base.info, Node: Random-testing, Prev: Random-basic, Up: Random 1.139.4 Random: testing ----------------------- chiSquare Compute the chi-square of the random that this class generates. chiSquare: n range: r Return the chi-square deduced from calculating n random numbers in the 0..r range.  File: gst-base.info, Node: ReadStream, Next: ReadWriteStream, Prev: Random, Up: Base classes 1.140 ReadStream ================ Defined in namespace Smalltalk Superclass: PositionableStream Category: Streams-Collections I implement the set of read-only stream objects. You may read from my objects, but you may not write to them. * Menu: * ReadStream class-instance creation:: (class)  File: gst-base.info, Node: ReadStream class-instance creation, Up: ReadStream 1.140.1 ReadStream class: instance creation ------------------------------------------- on: aCollection Answer a new stream working on aCollection from its start. on: aCollection from: firstIndex to: lastIndex Answer an instance of the receiver streaming from the firstIndex-th item of aCollection to the lastIndex-th  File: gst-base.info, Node: ReadWriteStream, Next: Rectangle, Prev: ReadStream, Up: Base classes 1.141 ReadWriteStream ===================== Defined in namespace Smalltalk Superclass: WriteStream Category: Streams-Collections I am the class of streams that may be read and written from simultaneously. In some sense, I am the best of both ReadStream and WriteStream. * Menu: * ReadWriteStream class-instance creation:: (class) * ReadWriteStream-positioning:: (instance)  File: gst-base.info, Node: ReadWriteStream class-instance creation, Next: ReadWriteStream-positioning, Up: ReadWriteStream 1.141.1 ReadWriteStream class: instance creation ------------------------------------------------ on: aCollection Answer a new stream working on aCollection from its start. The stream starts at the front of aCollection. on: aCollection from: firstIndex to: lastIndex Answer an instance of the receiver streaming from the firstIndex-th item of aCollection to the lastIndex-th with: aCollection Answer a new instance of the receiver which streams from the end of aCollection.  File: gst-base.info, Node: ReadWriteStream-positioning, Prev: ReadWriteStream class-instance creation, Up: ReadWriteStream 1.141.2 ReadWriteStream: positioning ------------------------------------ contents Unlike WriteStreams, ReadWriteStreams return the whole contents of the underlying collection.  File: gst-base.info, Node: Rectangle, Next: RecursionLock, Prev: ReadWriteStream, Up: Base classes 1.142 Rectangle =============== Defined in namespace Smalltalk Superclass: Object Category: Language-Data types Beginning of the Rectangle class for simple display manipulation. Rectangles require the Point class to be available. An extension to the Point class is made here that since it requires Rectangles to be defined (see converting) * Menu: * Rectangle class-instance creation:: (class) * Rectangle-accessing:: (instance) * Rectangle-copying:: (instance) * Rectangle-printing:: (instance) * Rectangle-rectangle functions:: (instance) * Rectangle-testing:: (instance) * Rectangle-transforming:: (instance) * Rectangle-truncation and round off:: (instance)  File: gst-base.info, Node: Rectangle class-instance creation, Next: Rectangle-accessing, Up: Rectangle 1.142.1 Rectangle class: instance creation ------------------------------------------ left: leftNumber right: rightNumber top: topNumber bottom: bottomNumber Answer a rectangle with the given coordinates left: leftNumber top: topNumber right: rightNumber bottom: bottomNumber Answer a rectangle with the given coordinates new Answer the (0 @ 0 corner: 0 @ 0) rectangle origin: originPoint corner: cornerPoint Answer a rectangle with the given corners origin: originPoint extent: extentPoint Answer a rectangle with the given origin and size  File: gst-base.info, Node: Rectangle-accessing, Next: Rectangle-copying, Prev: Rectangle class-instance creation, Up: Rectangle 1.142.2 Rectangle: accessing ---------------------------- bottom Answer the corner's y of the receiver bottom: aNumber Set the corner's y of the receiver bottomCenter Answer the center of the receiver's bottom side bottomLeft Answer the bottom-left corner of the receiver bottomLeft: aPoint Answer the receiver with the bottom-left changed to aPoint bottomRight Answer the bottom-right corner of the receiver bottomRight: aPoint Change the bottom-right corner of the receiver center Answer the center of the receiver corner Answer the corner of the receiver corner: aPoint Set the corner of the receiver extent Answer the extent of the receiver extent: aPoint Change the size of the receiver, keeping the origin the same height Answer the height of the receiver height: aNumber Set the height of the receiver left Answer the x of the left edge of the receiver left: aValue Set the x of the left edge of the receiver left: l top: t right: r bottom: b Change all four the coordinates of the receiver's corners leftCenter Answer the center of the receiver's left side origin Answer the top-left corner of the receiver origin: aPoint Change the top-left corner of the receiver to aPoint origin: pnt1 corner: pnt2 Change both the origin (top-left corner) and the corner (bottom-right corner) of the receiver origin: pnt1 extent: pnt2 Change the top-left corner and the size of the receiver right Answer the x of the bottom-right corner of the receiver right: aNumber Change the x of the bottom-right corner of the receiver rightCenter Answer the center of the receiver's right side top Answer the y of the receiver's top-left corner top: aValue Change the y of the receiver's top-left corner topCenter Answer the center of the receiver's top side topLeft Answer the receiver's top-left corner topLeft: aPoint Change the receiver's top-left corner's coordinates to aPoint topRight Answer the receiver's top-right corner topRight: aPoint Change the receiver's top-right corner to aPoint width Answer the receiver's width width: aNumber Change the receiver's width to aNumber  File: gst-base.info, Node: Rectangle-copying, Next: Rectangle-printing, Prev: Rectangle-accessing, Up: Rectangle 1.142.3 Rectangle: copying -------------------------- copy Return a deep copy of the receiver for safety.  File: gst-base.info, Node: Rectangle-printing, Next: Rectangle-rectangle functions, Prev: Rectangle-copying, Up: Rectangle 1.142.4 Rectangle: printing --------------------------- printOn: aStream Print a representation of the receiver on aStream storeOn: aStream Store Smalltalk code compiling to the receiver on aStream  File: gst-base.info, Node: Rectangle-rectangle functions, Next: Rectangle-testing, Prev: Rectangle-printing, Up: Rectangle 1.142.5 Rectangle: rectangle functions -------------------------------------- amountToTranslateWithin: aRectangle Answer a Point so that if aRectangle is translated by that point, its origin lies within the receiver's. area Answer the receiver's area. The area is the width times the height, so it is possible for it to be negative if the rectangle is not normalized. areasOutside: aRectangle Answer a collection of rectangles containing the parts of the receiver outside of aRectangle. For all points in the receiver, but outside aRectangle, exactly one rectangle in the collection will contain that point. expandBy: delta Answer a new rectangle that is the receiver expanded by aValue: if aValue is a rectangle, calculate origin=origin-aValue origin, corner=corner+aValue corner; else calculate origin=origin-aValue, corner=corner+aValue. insetBy: delta Answer a new rectangle that is the receiver inset by aValue: if aValue is a rectangle, calculate origin=origin+aValue origin, corner=corner-aValue corner; else calculate origin=origin+aValue, corner=corner-aValue. insetOriginBy: originDelta corner: cornerDelta Answer a new rectangle that is the receiver inset so that origin=origin+originDelta, corner=corner-cornerDelta. The deltas can be points or numbers intersect: aRectangle Answers the rectangle (if any) created by the overlap of rectangles A and B. Answers nil if the rectangles do not overlap merge: aRectangle Answer a new rectangle which is the smallest rectangle containing both the receiver and aRectangle. translatedToBeWithin: aRectangle Answer a copy of the receiver that does not extend beyond aRectangle.  File: gst-base.info, Node: Rectangle-testing, Next: Rectangle-transforming, Prev: Rectangle-rectangle functions, Up: Rectangle 1.142.6 Rectangle: testing -------------------------- = aRectangle Answer whether the receiver is equal to aRectangle contains: aRectangle Answer true if the receiver contains (see containsPoint:) both aRectangle's origin and aRectangle's corner containsPoint: aPoint Answer true if aPoint is equal to, or below and to the right of, the receiver's origin; and aPoint is above and to the left of the receiver's corner hash Answer an hash value for the receiver intersects: aRectangle Answer true if the receiver intersect aRectangle, i.e. if it contains (see containsPoint:) any of aRectangle corners or if aRectangle contains the receiver  File: gst-base.info, Node: Rectangle-transforming, Next: Rectangle-truncation and round off, Prev: Rectangle-testing, Up: Rectangle 1.142.7 Rectangle: transforming ------------------------------- moveBy: aPoint Change the receiver so that the origin and corner are shifted by aPoint moveTo: aPoint Change the receiver so that the origin moves to aPoint and the size remains unchanged scaleBy: scale Answer a copy of the receiver in which the origin and corner are multiplied by scale translateBy: factor Answer a copy of the receiver in which the origin and corner are shifted by aPoint  File: gst-base.info, Node: Rectangle-truncation and round off, Prev: Rectangle-transforming, Up: Rectangle 1.142.8 Rectangle: truncation and round off ------------------------------------------- rounded Answer a copy of the receiver with the coordinates rounded to the nearest integers  File: gst-base.info, Node: RecursionLock, Next: Regex, Prev: Rectangle, Up: Base classes 1.143 RecursionLock =================== Defined in namespace Smalltalk Superclass: Object Category: Language-Processes * Menu: * RecursionLock class-instance creation:: (class) * RecursionLock-accessing:: (instance) * RecursionLock-mutual exclusion:: (instance) * RecursionLock-printing:: (instance)  File: gst-base.info, Node: RecursionLock class-instance creation, Next: RecursionLock-accessing, Up: RecursionLock 1.143.1 RecursionLock class: instance creation ---------------------------------------------- new Answer a new semaphore  File: gst-base.info, Node: RecursionLock-accessing, Next: RecursionLock-mutual exclusion, Prev: RecursionLock class-instance creation, Up: RecursionLock 1.143.2 RecursionLock: accessing -------------------------------- isOwnerProcess Answer whether the receiver is the owner of the lock. name Answer a user-defined name for the lock. name: aString Set to aString the user-defined name for the lock. waitingProcesses Answer the set of processes that are waiting on the semaphore. wouldBlock Answer whether sending #wait to the receiver would suspend the active process.  File: gst-base.info, Node: RecursionLock-mutual exclusion, Next: RecursionLock-printing, Prev: RecursionLock-accessing, Up: RecursionLock 1.143.3 RecursionLock: mutual exclusion --------------------------------------- critical: aBlock Wait for the receiver to be free, execute aBlock and signal the receiver again. Return the result of evaluating aBlock.  File: gst-base.info, Node: RecursionLock-printing, Prev: RecursionLock-mutual exclusion, Up: RecursionLock 1.143.4 RecursionLock: printing ------------------------------- printOn: aStream Print a human-readable represention of the receiver on aStream.  File: gst-base.info, Node: Regex, Next: RegexResults, Prev: RecursionLock, Up: Base classes 1.144 Regex =========== Defined in namespace Smalltalk Superclass: Object Category: Collections-Text A Regex is a read-only string for which the regular expression matcher can cache a compiled representation, thus speeding up matching. Regex objects are constructed automatically by methods that expect to match many times the same regular expression, but can also be constructed explicitly sending #asRegex to a String or Symbol. Creation of Regex objects inside a loop is of course slower than creating them outside the loop, but special care is taken so that the same Regex object is used whenever possible (when converting Strings to Regex, the cache is sought for an equivalent, already constructed Regex). * Menu: * Regex class-instance creation:: (class) * Regex-basic:: (instance) * Regex-conversion:: (instance) * Regex-printing:: (instance)  File: gst-base.info, Node: Regex class-instance creation, Next: Regex-basic, Up: Regex 1.144.1 Regex class: instance creation -------------------------------------- fromString: aString Like `aString asRegex'. new Do not send this message.  File: gst-base.info, Node: Regex-basic, Next: Regex-conversion, Prev: Regex class-instance creation, Up: Regex 1.144.2 Regex: basic -------------------- at: anIndex put: anObject Fail. Regex objects are read-only. copy Answer the receiver; instances of Regex are identity objects because their only purpose is to ease caching, and we obtain better caching if we avoid copying Regex objects  File: gst-base.info, Node: Regex-conversion, Next: Regex-printing, Prev: Regex-basic, Up: Regex 1.144.3 Regex: conversion ------------------------- asRegex Answer the receiver, which *is* a Regex! asString Answer the receiver, converted back to a String species Answer `String'.  File: gst-base.info, Node: Regex-printing, Prev: Regex-conversion, Up: Regex 1.144.4 Regex: printing ----------------------- displayOn: aStream Print a represention of the receiver on aStream. For most objects this is simply its #printOn: representation, but for strings and characters, superfluous dollars or extra pairs of quotes are stripped. displayString Answer a String representing the receiver. For most objects this is simply its #printString, but for strings and characters, superfluous dollars or extra pair of quotes are stripped. printOn: aStream Print a represention of the receiver on aStream.  File: gst-base.info, Node: RegexResults, Next: RootNamespace, Prev: Regex, Up: Base classes 1.145 RegexResults ================== Defined in namespace Smalltalk Superclass: Object Category: Collections-Text I hold the results of a regular expression match, and I can reconstruct which parts of the matched string were assigned to each subexpression. Methods such as #=~ return RegexResults objects, while others transform the string directly without passing the results object back to the caller. * Menu: * RegexResults-accessing:: (instance) * RegexResults-testing:: (instance)  File: gst-base.info, Node: RegexResults-accessing, Next: RegexResults-testing, Up: RegexResults 1.145.1 RegexResults: accessing ------------------------------- asArray If the regular expression was matched, return an Array with the subexpressions that were present in the regular expression. at: anIndex If the regular expression was matched, return the text of the anIndex-th subexpression in the successful match. from If the regular expression was matched, return the index of the first character in the successful match. fromAt: anIndex If the regular expression was matched, return the index of the first character of the anIndex-th subexpression in the successful match. intervalAt: anIndex If the regular expression was matched, return an Interval for the range of indices in the anIndex-th subexpression of the successful match. match If the regular expression was matched, return the text of the successful match. matchInterval If the regular expression was matched, return an Interval for the range of indices of the successful match. size If the regular expression was matched, return the number of subexpressions that were present in the regular expression. subject If the regular expression was matched, return the text that was matched against it. to If the regular expression was matched, return the index of the last character in the successful match. toAt: anIndex If the regular expression was matched, return the index of the last character of the anIndex-th subexpression in the successful match.  File: gst-base.info, Node: RegexResults-testing, Prev: RegexResults-accessing, Up: RegexResults 1.145.2 RegexResults: testing ----------------------------- ifMatched: oneArgBlock If the regular expression was matched, pass the receiver to oneArgBlock and return its result. Otherwise, return nil. ifMatched: oneArgBlock ifNotMatched: zeroArgBlock If the regular expression was matched, evaluate oneArgBlock with the receiver as the argument. If it was not, evaluate zeroArgBlock. Answer the result of the block's evaluation. ifNotMatched: zeroArgBlock If the regular expression was matched, return the receiver. If it was not, evaluate zeroArgBlock and return its result. ifNotMatched: zeroArgBlock ifMatched: oneArgBlock If the regular expression was matched, evaluate oneArgBlock with the receiver as the argument. If it was not, evaluate zeroArgBlock. Answer the result of the block's evaluation. matched Answer whether the regular expression was matched  File: gst-base.info, Node: RootNamespace, Next: RunArray, Prev: RegexResults, Up: Base classes 1.146 RootNamespace =================== Defined in namespace Smalltalk Superclass: AbstractNamespace Category: Language-Implementation I am a special form of dictionary. Classes hold on an instance of me; it is called their `environment'. * Menu: * RootNamespace class-instance creation:: (class) * RootNamespace-namespace hierarchy:: (instance) * RootNamespace-overrides for superspaces:: (instance) * RootNamespace-printing:: (instance)  File: gst-base.info, Node: RootNamespace class-instance creation, Next: RootNamespace-namespace hierarchy, Up: RootNamespace 1.146.1 RootNamespace class: instance creation ---------------------------------------------- new: spaceName Create a new root namespace with the given name, and add to Smalltalk a key that references it.  File: gst-base.info, Node: RootNamespace-namespace hierarchy, Next: RootNamespace-overrides for superspaces, Prev: RootNamespace class-instance creation, Up: RootNamespace 1.146.2 RootNamespace: namespace hierarchy ------------------------------------------ siblings Answer all the other root namespaces siblingsDo: aBlock Evaluate aBlock once for each of the other root namespaces, passing the namespace as a parameter.  File: gst-base.info, Node: RootNamespace-overrides for superspaces, Next: RootNamespace-printing, Prev: RootNamespace-namespace hierarchy, Up: RootNamespace 1.146.3 RootNamespace: overrides for superspaces ------------------------------------------------ inheritedKeys Answer a Set of all the keys in the receiver and its superspaces set: key to: newValue ifAbsent: aBlock Assign newValue to the variable named as specified by `key'. This method won't define a new variable; instead if the key is not found it will search in superspaces and evaluate aBlock if it is not found. Answer newValue.  File: gst-base.info, Node: RootNamespace-printing, Prev: RootNamespace-overrides for superspaces, Up: RootNamespace 1.146.4 RootNamespace: printing ------------------------------- nameIn: aNamespace Answer Smalltalk code compiling to the receiver when the current namespace is aNamespace printOn: aStream in: aNamespace Print on aStream some Smalltalk code compiling to the receiver when the current namespace is aNamespace storeOn: aStream Store Smalltalk code compiling to the receiver  File: gst-base.info, Node: RunArray, Next: ScaledDecimal, Prev: RootNamespace, Up: Base classes 1.147 RunArray ============== Defined in namespace Smalltalk Superclass: OrderedCollection Category: Collections-Sequenceable My instances are OrderedCollections that automatically apply Run Length Encoding compression to the things they store. Be careful when using me: I can provide great space savings, but my instances don't grant linear access time. RunArray's behavior currently is similar to that of OrderedCollection (you can add elements to RunArrays); maybe it should behave like an ArrayedCollection. * Menu: * RunArray class-instance creation:: (class) * RunArray-accessing:: (instance) * RunArray-adding:: (instance) * RunArray-basic:: (instance) * RunArray-copying:: (instance) * RunArray-enumerating:: (instance) * RunArray-removing:: (instance) * RunArray-searching:: (instance) * RunArray-testing:: (instance)  File: gst-base.info, Node: RunArray class-instance creation, Next: RunArray-accessing, Up: RunArray 1.147.1 RunArray class: instance creation ----------------------------------------- new Answer an empty RunArray new: aSize Answer a RunArray with space for aSize runs  File: gst-base.info, Node: RunArray-accessing, Next: RunArray-adding, Prev: RunArray class-instance creation, Up: RunArray 1.147.2 RunArray: accessing --------------------------- at: anIndex Answer the element at index anIndex at: anIndex put: anObject Replace the element at index anIndex with anObject and answer anObject  File: gst-base.info, Node: RunArray-adding, Next: RunArray-basic, Prev: RunArray-accessing, Up: RunArray 1.147.3 RunArray: adding ------------------------ add: anObject afterIndex: anIndex Add anObject after the element at index anIndex addAll: aCollection afterIndex: anIndex Add all the elements of aCollection after the one at index anIndex. If aCollection is unordered, its elements could be added in an order which is not the #do: order addAllFirst: aCollection Add all the elements of aCollection at the beginning of the receiver. If aCollection is unordered, its elements could be added in an order which is not the #do: order addAllLast: aCollection Add all the elements of aCollection at the end of the receiver. If aCollection is unordered, its elements could be added in an order which is not the #do: order addFirst: anObject Add anObject at the beginning of the receiver. Watch out: this operation can cause serious performance pitfalls addLast: anObject Add anObject at the end of the receiver  File: gst-base.info, Node: RunArray-basic, Next: RunArray-copying, Prev: RunArray-adding, Up: RunArray 1.147.4 RunArray: basic ----------------------- first Answer the first element in the receiver last Answer the last element of the receiver size Answer the number of elements in the receiver  File: gst-base.info, Node: RunArray-copying, Next: RunArray-enumerating, Prev: RunArray-basic, Up: RunArray 1.147.5 RunArray: copying ------------------------- deepCopy Answer a copy of the receiver containing copies of the receiver's elements (#copy is used to obtain them) shallowCopy Answer a copy of the receiver. The elements are not copied  File: gst-base.info, Node: RunArray-enumerating, Next: RunArray-removing, Prev: RunArray-copying, Up: RunArray 1.147.6 RunArray: enumerating ----------------------------- do: aBlock Enumerate all the objects in the receiver, passing each one to aBlock objectsAndRunLengthsDo: aBlock Enumerate all the runs in the receiver, passing to aBlock two parameters for every run: the first is the repeated object, the second is the number of copies  File: gst-base.info, Node: RunArray-removing, Next: RunArray-searching, Prev: RunArray-enumerating, Up: RunArray 1.147.7 RunArray: removing -------------------------- removeAtIndex: anIndex Remove the object at index anIndex from the receiver and answer the removed object removeFirst Remove the first object from the receiver and answer the removed object removeLast Remove the last object from the receiver and answer the removed object  File: gst-base.info, Node: RunArray-searching, Next: RunArray-testing, Prev: RunArray-removing, Up: RunArray 1.147.8 RunArray: searching --------------------------- indexOf: anObject startingAt: anIndex ifAbsent: aBlock Answer the index of the first copy of anObject in the receiver, starting the search at the element at index anIndex. If no equal object is found, answer the result of evaluating aBlock  File: gst-base.info, Node: RunArray-testing, Prev: RunArray-searching, Up: RunArray 1.147.9 RunArray: testing ------------------------- = anObject Answer true if the receiver is equal to anObject hash Answer an hash value for the receiver  File: gst-base.info, Node: ScaledDecimal, Next: SecurityPolicy, Prev: RunArray, Up: Base classes 1.148 ScaledDecimal =================== Defined in namespace Smalltalk Superclass: Number Category: Language-Data types ScaledDecimal provides a numeric representation of fixed point decimal numbers able to accurately represent decimal fractions. It supports unbounded precision, with no limit to the number of digits before and after the decimal point. * Menu: * ScaledDecimal class-instance creation:: (class) * ScaledDecimal-arithmetic:: (instance) * ScaledDecimal-coercion:: (instance) * ScaledDecimal-comparing:: (instance) * ScaledDecimal-constants:: (instance) * ScaledDecimal-printing:: (instance) * ScaledDecimal-storing:: (instance)  File: gst-base.info, Node: ScaledDecimal class-instance creation, Next: ScaledDecimal-arithmetic, Up: ScaledDecimal 1.148.1 ScaledDecimal class: instance creation ---------------------------------------------- newFromNumber: aNumber scale: scale Answer a new instance of ScaledDecimal, representing a decimal fraction with a decimal representation considered valid up to the scale-th digit.  File: gst-base.info, Node: ScaledDecimal-arithmetic, Next: ScaledDecimal-coercion, Prev: ScaledDecimal class-instance creation, Up: ScaledDecimal 1.148.2 ScaledDecimal: arithmetic --------------------------------- * aNumber Multiply two numbers and answer the result. + aNumber Sum two numbers and answer the result. - aNumber Subtract aNumber from the receiver and answer the result. / aNumber Divide two numbers and answer the result. // aNumber Answer the integer quotient after dividing the receiver by aNumber with truncation towards negative infinity. \\ aNumber Answer the remainder after integer division the receiver by aNumber with truncation towards negative infinity.  File: gst-base.info, Node: ScaledDecimal-coercion, Next: ScaledDecimal-comparing, Prev: ScaledDecimal-arithmetic, Up: ScaledDecimal 1.148.3 ScaledDecimal: coercion ------------------------------- asCNumber Convert the receiver to a kind of number that is understood by the C call-out mechanism. asFloatD Answer the receiver, converted to a FloatD asFloatE Answer the receiver, converted to a FloatE asFloatQ Answer the receiver, converted to a FloatQ asFraction Answer the receiver, converted to a Fraction ceiling Answer the receiver, converted to an Integer and truncated towards +infinity. coerce: aNumber Answer aNumber, converted to a ScaledDecimal with the same scale as the receiver. fractionPart Answer the fractional part of the receiver. generality Return the receiver's generality integerPart Answer the fractional part of the receiver. truncated Answer the receiver, converted to an Integer and truncated towards -infinity.  File: gst-base.info, Node: ScaledDecimal-comparing, Next: ScaledDecimal-constants, Prev: ScaledDecimal-coercion, Up: ScaledDecimal 1.148.4 ScaledDecimal: comparing -------------------------------- < aNumber Answer whether the receiver is less than arg. <= aNumber Answer whether the receiver is less than or equal to arg. = arg Answer whether the receiver is equal to arg. > aNumber Answer whether the receiver is greater than arg. >= aNumber Answer whether the receiver is greater than or equal to arg. hash Answer an hash value for the receiver. ~= arg Answer whether the receiver is not equal arg.  File: gst-base.info, Node: ScaledDecimal-constants, Next: ScaledDecimal-printing, Prev: ScaledDecimal-comparing, Up: ScaledDecimal 1.148.5 ScaledDecimal: constants -------------------------------- one Answer the receiver's representation of one. zero Answer the receiver's representation of zero.  File: gst-base.info, Node: ScaledDecimal-printing, Next: ScaledDecimal-storing, Prev: ScaledDecimal-constants, Up: ScaledDecimal 1.148.6 ScaledDecimal: printing ------------------------------- displayOn: aStream Print a representation of the receiver on aStream, intended to be directed to a user. In this particular case, the `scale' part of the #printString is not emitted. printOn: aStream Print a representation of the receiver on aStream.  File: gst-base.info, Node: ScaledDecimal-storing, Prev: ScaledDecimal-printing, Up: ScaledDecimal 1.148.7 ScaledDecimal: storing ------------------------------ isLiteralObject Answer whether the receiver is expressible as a Smalltalk literal. storeLiteralOn: aStream Store on aStream some Smalltalk code which compiles to the receiver storeOn: aStream Print Smalltalk code that compiles to the receiver on aStream.  File: gst-base.info, Node: SecurityPolicy, Next: Semaphore, Prev: ScaledDecimal, Up: Base classes 1.149 SecurityPolicy ==================== Defined in namespace Smalltalk Superclass: Object Category: Language-Security I am the class that represents which operations that could harm the system's security are allowed or denied to a particular class. If a class does not have a policy, it is allowed everything if it is trusted, and denied everything if it is untrusted * Menu: * SecurityPolicy-modifying:: (instance) * SecurityPolicy-querying:: (instance)  File: gst-base.info, Node: SecurityPolicy-modifying, Next: SecurityPolicy-querying, Up: SecurityPolicy 1.149.1 SecurityPolicy: modifying --------------------------------- addPermission: aPermission Not commented. owner: aClass Not commented. removePermission: aPermission Not commented. withOwner: aClass Not commented.  File: gst-base.info, Node: SecurityPolicy-querying, Prev: SecurityPolicy-modifying, Up: SecurityPolicy 1.149.2 SecurityPolicy: querying -------------------------------- check: aPermission Not commented. implies: aPermission Not commented.  File: gst-base.info, Node: Semaphore, Next: SequenceableCollection, Prev: SecurityPolicy, Up: Base classes 1.150 Semaphore =============== Defined in namespace Smalltalk Superclass: LinkedList Category: Language-Processes My instances represent counting semaphores. I provide methods for signalling the semaphore's availability, and methods for waiting for its availability. I also provide some methods for implementing critical sections. * Menu: * Semaphore class-instance creation:: (class) * Semaphore-accessing:: (instance) * Semaphore-builtins:: (instance) * Semaphore-mutual exclusion:: (instance) * Semaphore-printing:: (instance)  File: gst-base.info, Node: Semaphore class-instance creation, Next: Semaphore-accessing, Up: Semaphore 1.150.1 Semaphore class: instance creation ------------------------------------------ forMutualExclusion Answer a new semaphore with a signal on it. These semaphores are a useful shortcut when you use semaphores as critical sections. new Answer a new semaphore  File: gst-base.info, Node: Semaphore-accessing, Next: Semaphore-builtins, Prev: Semaphore class-instance creation, Up: Semaphore 1.150.2 Semaphore: accessing ---------------------------- name Answer a user-friendly name for the receiver name: aString Answer a user-friendly name for the receiver waitingProcesses Answer an Array of processes currently waiting on the receiver. wouldBlock Answer whether waiting on the receiver would suspend the current process.  File: gst-base.info, Node: Semaphore-builtins, Next: Semaphore-mutual exclusion, Prev: Semaphore-accessing, Up: Semaphore 1.150.3 Semaphore: builtins --------------------------- lock Without putting the receiver to sleep, force processes that try to wait on the semaphore to block. Answer whether this was the case even before. notify Resume one of the processes that were waiting on the semaphore if there were any. Do not leave a signal on the semaphore if no process is waiting. notifyAll Resume all the processes that were waiting on the semaphore if there were any. Do not leave a signal on the semaphore if no process is waiting. signal Signal the receiver, resuming a waiting process' if there is one wait Wait for the receiver to be signalled, suspending the executing process if it is not yet. Return nil if the wait was interrupted, the receiver otherwise. waitAfterSignalling: aSemaphore Signal aSemaphore then, atomically, wait for the receiver to be signalled, suspending the executing process if it is not yet. This is needed to avoid race conditions when the #notify and #notifyAll are used before waiting on receiver: otherwise, if a process sends any of the two between the time aSemaphore is signaled and the time the process starts waiting on the receiver, the notification is lost.  File: gst-base.info, Node: Semaphore-mutual exclusion, Next: Semaphore-printing, Prev: Semaphore-builtins, Up: Semaphore 1.150.4 Semaphore: mutual exclusion ----------------------------------- critical: aBlock Wait for the receiver to be free, execute aBlock and signal the receiver again. Return the result of evaluating aBlock.  File: gst-base.info, Node: Semaphore-printing, Prev: Semaphore-mutual exclusion, Up: Semaphore 1.150.5 Semaphore: printing --------------------------- printOn: aStream Print a human-readable represention of the receiver on aStream.  File: gst-base.info, Node: SequenceableCollection, Next: Set, Prev: Semaphore, Up: Base classes 1.151 SequenceableCollection ============================ Defined in namespace Smalltalk Superclass: Collection Category: Collections-Sequenceable My instances represent collections of objects that are ordered. I provide some access and manipulation methods. * Menu: * SequenceableCollection class-instance creation:: (class) * SequenceableCollection-basic:: (instance) * SequenceableCollection-comparing:: (instance) * SequenceableCollection-concatenating:: (instance) * SequenceableCollection-copying SequenceableCollections:: (instance) * SequenceableCollection-enumerating:: (instance) * SequenceableCollection-manipulation:: (instance) * SequenceableCollection-replacing items:: (instance) * SequenceableCollection-sorting:: (instance) * SequenceableCollection-still unclassified:: (instance) * SequenceableCollection-testing:: (instance) * SequenceableCollection-testing collections:: (instance)  File: gst-base.info, Node: SequenceableCollection class-instance creation, Next: SequenceableCollection-basic, Up: SequenceableCollection 1.151.1 SequenceableCollection class: instance creation ------------------------------------------------------- join: aCollection separatedBy: sepCollection Where aCollection is a collection of SequenceableCollections, answer a new instance with all the elements therein, in order, each separated by an occurrence of sepCollection.  File: gst-base.info, Node: SequenceableCollection-basic, Next: SequenceableCollection-comparing, Prev: SequenceableCollection class-instance creation, Up: SequenceableCollection 1.151.2 SequenceableCollection: basic ------------------------------------- after: oldObject Return the element after oldObject. Error if oldObject not found or if no following object is available allButFirst Answer a copy of the receiver without the first object. allButFirst: n Answer a copy of the receiver without the first n objects. allButLast Answer a copy of the receiver without the last object. allButLast: n Answer a copy of the receiver without the last n objects. at: anIndex ifAbsent: aBlock Answer the anIndex-th item of the collection, or evaluate aBlock and answer the result if the index is out of range atAll: keyCollection Answer a collection of the same kind returned by #collect:, that only includes the values at the given indices. Fail if any of the values in keyCollection is out of bounds for the receiver. atAll: aCollection put: anObject Put anObject at every index contained in aCollection atAllPut: anObject Put anObject at every index in the receiver atRandom Return a random item of the receiver. before: oldObject Return the element before oldObject. Error if oldObject not found or if no preceding object is available first Answer the first item in the receiver first: n Answer the first n items in the receiver fourth Answer the fourth item in the receiver identityIncludes: anObject Answer whether we include the anObject object identityIndexOf: anElement Answer the index of the first occurrence of an object identical to anElement in the receiver. Answer 0 if no item is found identityIndexOf: anElement ifAbsent: exceptionBlock Answer the index of the first occurrence of an object identical to anElement in the receiver. Invoke exceptionBlock and answer its result if no item is found identityIndexOf: anElement startingAt: anIndex Answer the first index > anIndex which contains an object identical to anElement. Answer 0 if no item is found identityIndexOf: anObject startingAt: anIndex ifAbsent: exceptionBlock Answer the first index > anIndex which contains an object exactly identical to anObject. Invoke exceptionBlock and answer its result if no item is found identityIndexOfLast: anElement ifAbsent: exceptionBlock Answer the last index which contains an object identical to anElement. Invoke exceptionBlock and answer its result if no item is found includes: anObject Answer whether we include anObject indexOf: anElement Answer the index of the first occurrence of anElement in the receiver. Answer 0 if no item is found indexOf: anElement ifAbsent: exceptionBlock Answer the index of the first occurrence of anElement in the receiver. Invoke exceptionBlock and answer its result if no item is found indexOf: anElement startingAt: anIndex Answer the first index > anIndex which contains anElement. Answer 0 if no item is found indexOf: anElement startingAt: anIndex ifAbsent: exceptionBlock Answer the first index > anIndex which contains anElement. Invoke exceptionBlock and answer its result if no item is found indexOfLast: anElement ifAbsent: exceptionBlock Answer the last index which contains anElement. Invoke exceptionBlock and answer its result if no item is found indexOfSubCollection: aSubCollection Answer the first index > anIndex at which starts a sequence of items matching aSubCollection. Answer 0 if no such sequence is found. indexOfSubCollection: aSubCollection ifAbsent: exceptionBlock Answer the first index > anIndex at which starts a sequence of items matching aSubCollection. Answer 0 if no such sequence is found. indexOfSubCollection: aSubCollection startingAt: anIndex Answer the first index > anIndex at which starts a sequence of items matching aSubCollection. Answer 0 if no such sequence is found. indexOfSubCollection: aSubCollection startingAt: anIndex ifAbsent: exceptionBlock Answer the first index > anIndex at which starts a sequence of items matching aSubCollection. Invoke exceptionBlock and answer its result if no such sequence is found last Answer the last item in the receiver last: n Answer the last n items in the receiver second Answer the second item in the receiver third Answer the third item in the receiver  File: gst-base.info, Node: SequenceableCollection-comparing, Next: SequenceableCollection-concatenating, Prev: SequenceableCollection-basic, Up: SequenceableCollection 1.151.3 SequenceableCollection: comparing ----------------------------------------- endsWith: aSequenceableCollection Returns true if the receiver ends with the same characters as aSequenceableCollection. startsWith: aSequenceableCollection Returns true if the receiver starts with the same characters as aSequenceableCollection.  File: gst-base.info, Node: SequenceableCollection-concatenating, Next: SequenceableCollection-copying SequenceableCollections, Prev: SequenceableCollection-comparing, Up: SequenceableCollection 1.151.4 SequenceableCollection: concatenating --------------------------------------------- join: sepCollection Answer a new collection like my first element, with all the elements (in order) of all my elements (which should be collections) separated by sepCollection. I use my first element instead of myself as a prototype because my elements are more likely to share the desired properties than I am, such as in: #('hello,' 'world') join: ' ' => 'hello, world' with: aSequenceableCollection Return an Array with the same size as the receiver and aSequenceableCollection, each element of which is a 2-element Arrays including one element from the receiver and one from aSequenceableCollection. with: seqColl1 with: seqColl2 Return an Array with the same size as the receiver and the arguments, each element of which is a 3-element Arrays including one element from the receiver and one from each argument. with: seqColl1 with: seqColl2 with: seqColl3 Return an Array with the same size as the receiver and the arguments, each element of which is a 4-element Arrays including one element from the receiver and one from each argument.  File: gst-base.info, Node: SequenceableCollection-copying SequenceableCollections, Next: SequenceableCollection-enumerating, Prev: SequenceableCollection-concatenating, Up: SequenceableCollection 1.151.5 SequenceableCollection: copying SequenceableCollections --------------------------------------------------------------- copyAfter: anObject Answer a new collection holding all the elements of the receiver after the first occurrence of anObject, up to the last. copyAfterLast: anObject Answer a new collection holding all the elements of the receiver after the last occurrence of anObject, up to the last. copyFrom: start Answer a new collection containing all the items in the receiver from the start-th. copyFrom: start to: stop Answer a new collection containing all the items in the receiver from the start-th and to the stop-th copyReplaceAll: oldSubCollection with: newSubCollection Answer a new collection in which all the sequences matching oldSubCollection are replaced with newSubCollection copyReplaceFrom: start to: stop with: replacementCollection Answer a new collection of the same class as the receiver that contains the same elements as the receiver, in the same order, except for elements from index `start' to index `stop'. If start < stop, these are replaced by the contents of the replacementCollection. Instead, If start = (stop + 1), like in `copyReplaceFrom: 4 to: 3 with: anArray', then every element of the receiver will be present in the answered copy; the operation will be an append if stop is equal to the size of the receiver or, if it is not, an insert before index `start'. copyReplaceFrom: start to: stop withObject: anObject Answer a new collection of the same class as the receiver that contains the same elements as the receiver, in the same order, except for elements from index `start' to index `stop'. If start < stop, these are replaced by stop-start+1 copies of anObject. Instead, If start = (stop + 1), then every element of the receiver will be present in the answered copy; the operation will be an append if stop is equal to the size of the receiver or, if it is not, an insert before index `start'. copyUpTo: anObject Answer a new collection holding all the elements of the receiver from the first up to the first occurrence of anObject, excluded. copyUpToLast: anObject Answer a new collection holding all the elements of the receiver from the first up to the last occurrence of anObject, excluded. copyWithFirst: anObject Answer a new collection holding all the elements of the receiver after the first occurrence of anObject, up to the last.  File: gst-base.info, Node: SequenceableCollection-enumerating, Next: SequenceableCollection-manipulation, Prev: SequenceableCollection-copying SequenceableCollections, Up: SequenceableCollection 1.151.6 SequenceableCollection: enumerating ------------------------------------------- anyOne Answer an unspecified element of the collection. do: aBlock Evaluate aBlock for all the elements in the sequenceable collection do: aBlock separatedBy: sepBlock Evaluate aBlock for all the elements in the sequenceable collection. Between each element, evaluate sepBlock without parameters. doWithIndex: aBlock Evaluate aBlock for all the elements in the sequenceable collection, passing the index of each element as the second parameter. This method is mantained for backwards compatibility and is not mandated by the ANSI standard; use #keysAndValuesDo: findFirst: aBlock Returns the index of the first element of the sequenceable collection for which aBlock returns true, or 0 if none findLast: aBlock Returns the index of the last element of the sequenceable collection for which aBlock returns true, or 0 if none does fold: binaryBlock First, pass to binaryBlock the first and second elements of the receiver; for each subsequent element, pass the result of the previous evaluation and an element. Answer the result of the last invocation, or the first element if the collection has size 1. Fail if the collection is empty. from: startIndex to: stopIndex do: aBlock Evaluate aBlock for all the elements in the sequenceable collection whose indices are in the range index to stopIndex from: startIndex to: stopIndex doWithIndex: aBlock Evaluate aBlock for all the elements in the sequenceable collection whose indices are in the range index to stopIndex, passing the index of each element as the second parameter. This method is mantained for backwards compatibility and is not mandated by the ANSI standard; use #from:to:keysAndValuesDo: from: startIndex to: stopIndex keysAndValuesDo: aBlock Evaluate aBlock for all the elements in the sequenceable collection whose indices are in the range index to stopIndex, passing the index of each element as the first parameter and the element as the second. keys Return an Interval corresponding to the valid indices in the receiver. keysAndValuesDo: aBlock Evaluate aBlock for all the elements in the sequenceable collection, passing the index of each element as the first parameter and the element as the second. readStream Answer a ReadStream streaming on the receiver readWriteStream Answer a ReadWriteStream which streams on the receiver reverse Answer the receivers' contents in reverse order reverseDo: aBlock Evaluate aBlock for all elements in the sequenceable collection, from the last to the first. with: aSequenceableCollection collect: aBlock Evaluate aBlock for each pair of elements took respectively from the receiver and from aSequenceableCollection; answer a collection of the same kind of the receiver, made with the block's return values. Fail if the receiver has not the same size as aSequenceableCollection. with: aSequenceableCollection do: aBlock Evaluate aBlock for each pair of elements took respectively from the receiver and from aSequenceableCollection. Fail if the receiver has not the same size as aSequenceableCollection.  File: gst-base.info, Node: SequenceableCollection-manipulation, Next: SequenceableCollection-replacing items, Prev: SequenceableCollection-enumerating, Up: SequenceableCollection 1.151.7 SequenceableCollection: manipulation -------------------------------------------- swap: anIndex with: anotherIndex Swap the item at index anIndex with the item at index another index  File: gst-base.info, Node: SequenceableCollection-replacing items, Next: SequenceableCollection-sorting, Prev: SequenceableCollection-manipulation, Up: SequenceableCollection 1.151.8 SequenceableCollection: replacing items ----------------------------------------------- replaceAll: anObject with: anotherObject In the receiver, replace every occurrence of anObject with anotherObject. replaceFrom: start to: stop with: replacementCollection Replace the items from start to stop with replacementCollection's items from 1 to stop-start+1 (in unexpected order if the collection is not sequenceable). replaceFrom: start to: stop with: replacementCollection startingAt: repStart Replace the items from start to stop with replacementCollection's items from repStart to repStart+stop-start replaceFrom: anIndex to: stopIndex withObject: replacementObject Replace every item from start to stop with replacementObject.  File: gst-base.info, Node: SequenceableCollection-sorting, Next: SequenceableCollection-still unclassified, Prev: SequenceableCollection-replacing items, Up: SequenceableCollection 1.151.9 SequenceableCollection: sorting --------------------------------------- sort Sort the contents of the receiver according to the default sort block, which uses #<= to compare items. sort: sortBlock Sort the contents of the receiver according to the given sort block, which accepts pair of items and returns true if the first item is less than the second one. sorted Return a copy of the receiver sorted according to the default sort block, which uses #<= to compare items. sorted: sortBlock Return a copy of the receiver sorted according to the given sort block, which accepts pair of items and returns true if the first item is less than the second one.  File: gst-base.info, Node: SequenceableCollection-still unclassified, Next: SequenceableCollection-testing, Prev: SequenceableCollection-sorting, Up: SequenceableCollection 1.151.10 SequenceableCollection: still unclassified --------------------------------------------------- nextPutAllOn: aStream Write all the objects in the receiver to aStream  File: gst-base.info, Node: SequenceableCollection-testing, Next: SequenceableCollection-testing collections, Prev: SequenceableCollection-still unclassified, Up: SequenceableCollection 1.151.11 SequenceableCollection: testing ---------------------------------------- = aCollection Answer whether the receiver's items match those in aCollection examineOn: aStream Print all the instance variables and context of the receiver on aStream hash Answer an hash value for the receiver isSequenceable Answer whether the receiver can be accessed by a numeric index with #at:/#at:put:.  File: gst-base.info, Node: SequenceableCollection-testing collections, Prev: SequenceableCollection-testing, Up: SequenceableCollection 1.151.12 SequenceableCollection: testing collections ---------------------------------------------------- size Answer a dummy size of 0, so that SequenceableCollection>>#do: works.  File: gst-base.info, Node: Set, Next: SharedQueue, Prev: SequenceableCollection, Up: Base classes 1.152 Set ========= Defined in namespace Smalltalk Superclass: HashedCollection Category: Collections-Unordered I am the typical set object; I also known how to do arithmetic on my instances. * Menu: * Set-arithmetic:: (instance) * Set-awful ST-80 compatibility hacks:: (instance) * Set-comparing:: (instance)  File: gst-base.info, Node: Set-arithmetic, Next: Set-awful ST-80 compatibility hacks, Up: Set 1.152.1 Set: arithmetic ----------------------- & aSet Compute the set intersection of the receiver and aSet. + aSet Compute the set union of the receiver and aSet. - aSet Compute the set difference of the receiver and aSet.  File: gst-base.info, Node: Set-awful ST-80 compatibility hacks, Next: Set-comparing, Prev: Set-arithmetic, Up: Set 1.152.2 Set: awful ST-80 compatibility hacks -------------------------------------------- findObjectIndex: object Tries to see if anObject exists as an indexed variable. As soon as nil or anObject is found, the index of that slot is answered  File: gst-base.info, Node: Set-comparing, Prev: Set-awful ST-80 compatibility hacks, Up: Set 1.152.3 Set: comparing ---------------------- < aSet Answer whether the receiver is a strict subset of aSet <= aSet Answer whether the receiver is a subset of aSet > aSet Answer whether the receiver is a strict superset of aSet >= aSet Answer whether the receiver is a superset of aSet  File: gst-base.info, Node: SharedQueue, Next: SingletonProxy, Prev: Set, Up: Base classes 1.153 SharedQueue ================= Defined in namespace Smalltalk Superclass: Object Category: Language-Processes My instances provide a guaranteed safe mechanism to allow for communication between processes. All access to the underlying data structures is controlled with critical sections so that things proceed smoothly. * Menu: * SharedQueue class-instance creation:: (class) * SharedQueue-accessing:: (instance)  File: gst-base.info, Node: SharedQueue class-instance creation, Next: SharedQueue-accessing, Up: SharedQueue 1.153.1 SharedQueue class: instance creation -------------------------------------------- new Create a new instance of the receiver sortBlock: sortBlock Create a new instance of the receiver which implements a priority queue with the given sort block  File: gst-base.info, Node: SharedQueue-accessing, Prev: SharedQueue class-instance creation, Up: SharedQueue 1.153.2 SharedQueue: accessing ------------------------------ isEmpty Answer whether there is an object on the queue next Wait for an object to be on the queue, then remove it and answer it nextPut: value Put value on the queue and answer it peek Wait for an object to be on the queue if necessary, then answer the same object that #next would answer without removing it.  File: gst-base.info, Node: SingletonProxy, Next: SmallInteger, Prev: SharedQueue, Up: Base classes 1.154 SingletonProxy ==================== Defined in namespace Smalltalk Superclass: AlternativeObjectProxy Category: Streams-Files I am a proxy that stores the class of an object rather than the object itself, and pretends that a registered instance (which most likely is a singleton instance of the stored class) was stored instead. * Menu: * SingletonProxy class-accessing:: (class) * SingletonProxy class-instance creation:: (class) * SingletonProxy-saving and restoring:: (instance)  File: gst-base.info, Node: SingletonProxy class-accessing, Next: SingletonProxy class-instance creation, Up: SingletonProxy 1.154.1 SingletonProxy class: accessing --------------------------------------- acceptUsageForClass: aClass The receiver was asked to be used as a proxy for the class aClass. The registration is fine if the class is actually a singleton.  File: gst-base.info, Node: SingletonProxy class-instance creation, Next: SingletonProxy-saving and restoring, Prev: SingletonProxy class-accessing, Up: SingletonProxy 1.154.2 SingletonProxy class: instance creation ----------------------------------------------- on: anObject Answer a proxy to be used to save anObject. The proxy stores the class and restores the object by looking into a dictionary of class -> singleton objects.  File: gst-base.info, Node: SingletonProxy-saving and restoring, Prev: SingletonProxy class-instance creation, Up: SingletonProxy 1.154.3 SingletonProxy: saving and restoring -------------------------------------------- object Reconstruct the object stored in the proxy and answer it; the binaryRepresentationObject is sent the #reconstructOriginalObject message, and the resulting object is sent the #postLoad message.  File: gst-base.info, Node: SmallInteger, Next: SortedCollection, Prev: SingletonProxy, Up: Base classes 1.155 SmallInteger ================== Defined in namespace Smalltalk Superclass: Integer Category: Language-Data types I am the integer class of the GNU Smalltalk system. My instances can represent signed 30 bit integers and are as efficient as possible. * Menu: * SmallInteger class-getting limits:: (class) * SmallInteger class-testing:: (class) * SmallInteger-bit arithmetic:: (instance) * SmallInteger-built ins:: (instance) * SmallInteger-builtins:: (instance) * SmallInteger-coercion:: (instance) * SmallInteger-coercion methods:: (instance) * SmallInteger-testing functionality:: (instance)  File: gst-base.info, Node: SmallInteger class-getting limits, Next: SmallInteger class-testing, Up: SmallInteger 1.155.1 SmallInteger class: getting limits ------------------------------------------ bits Answer the number of bits (excluding the sign) that can be represented directly in an object pointer largest Answer the largest integer represented directly in an object pointer smallest Answer the smallest integer represented directly in an object pointer  File: gst-base.info, Node: SmallInteger class-testing, Next: SmallInteger-bit arithmetic, Prev: SmallInteger class-getting limits, Up: SmallInteger 1.155.2 SmallInteger class: testing ----------------------------------- isIdentity Answer whether x = y implies x == y for instances of the receiver  File: gst-base.info, Node: SmallInteger-bit arithmetic, Next: SmallInteger-built ins, Prev: SmallInteger class-testing, Up: SmallInteger 1.155.3 SmallInteger: bit arithmetic ------------------------------------ highBit Return the index of the highest order 1 bit of the receiver lowBit Return the index of the lowest order 1 bit of the receiver.  File: gst-base.info, Node: SmallInteger-built ins, Next: SmallInteger-builtins, Prev: SmallInteger-bit arithmetic, Up: SmallInteger 1.155.4 SmallInteger: built ins ------------------------------- * arg Multiply the receiver and arg and answer another Number + arg Sum the receiver and arg and answer another Number - arg Subtract arg from the receiver and answer another Number / arg Divide the receiver by arg and answer another Integer or Fraction // arg Dividing receiver by arg (with truncation towards -infinity) and answer the result < arg Answer whether the receiver is less than arg <= arg Answer whether the receiver is less than or equal to arg = arg Answer whether the receiver is equal to arg == arg Answer whether the receiver is the same object as arg > arg Answer whether the receiver is greater than arg >= arg Answer whether the receiver is greater than or equal to arg \\ arg Calculate the remainder of dividing receiver by arg (with truncation towards -infinity) and answer it asFloatD Convert the receiver to a FloatD, answer the result asFloatE Convert the receiver to a FloatE, answer the result asFloatQ Convert the receiver to a FloatQ, answer the result asObject Answer the object whose index is in the receiver, nil if there is a free object, fail if index is out of bounds asObjectNoFail Answer the object whose index is in the receiver, or nil if no object is found at that index bitAnd: arg Do a bitwise AND between the receiver and arg, answer the result bitOr: arg Do a bitwise OR between the receiver and arg, answer the result bitShift: arg Shift the receiver by arg places to the left if arg > 0, by arg places to the right if arg < 0, answer another Number bitXor: arg Do a bitwise XOR between the receiver and arg, answer the result divExact: arg Dividing receiver by arg assuming that the remainder is zero, and answer the result nextValidOop Answer the index of the first non-free OOP after the receiver. This is used internally; it is placed here to avoid polluting Object. quo: arg Dividing receiver by arg (with truncation towards zero) and answer the result ~= arg Answer whether the receiver is not equal to arg ~~ arg Answer whether the receiver is not the same object as arg  File: gst-base.info, Node: SmallInteger-builtins, Next: SmallInteger-coercion, Prev: SmallInteger-built ins, Up: SmallInteger 1.155.5 SmallInteger: builtins ------------------------------ at: anIndex Answer the index-th indexed instance variable of the receiver. This method always fails. at: anIndex put: value Store value in the index-th indexed instance variable of the receiver This method always fails. basicAt: anIndex Answer the index-th indexed instance variable of the receiver. This method always fails. basicAt: anIndex put: value Store value in the index-th indexed instance variable of the receiver This method always fails. scramble Answer the receiver with its bits mixed and matched.  File: gst-base.info, Node: SmallInteger-coercion, Next: SmallInteger-coercion methods, Prev: SmallInteger-builtins, Up: SmallInteger 1.155.6 SmallInteger: coercion ------------------------------ asCNumber Convert the receiver to a kind of number that is understood by the C call-out mechanism.  File: gst-base.info, Node: SmallInteger-coercion methods, Next: SmallInteger-testing functionality, Prev: SmallInteger-coercion, Up: SmallInteger 1.155.7 SmallInteger: coercion methods -------------------------------------- generality Return the receiver's generality unity Coerce 1 to the receiver's class zero Coerce 0 to the receiver's class  File: gst-base.info, Node: SmallInteger-testing functionality, Prev: SmallInteger-coercion methods, Up: SmallInteger 1.155.8 SmallInteger: testing functionality ------------------------------------------- isSmallInteger Answer `true'.  File: gst-base.info, Node: SortedCollection, Next: Stream, Prev: SmallInteger, Up: Base classes 1.156 SortedCollection ====================== Defined in namespace Smalltalk Superclass: OrderedCollection Category: Collections-Sequenceable I am a collection of objects, stored and accessed according to some sorting criteria. I store things using heap sort and quick sort. My instances have a comparison block associated with them; this block takes two arguments and is a predicate which returns true if the first argument should be sorted earlier than the second. The default block is [ :a :b | a <= b ], but I will accept any block that conforms to the above criteria - actually any object which responds to #value:value:. * Menu: * SortedCollection class-hacking:: (class) * SortedCollection class-instance creation:: (class) * SortedCollection-basic:: (instance) * SortedCollection-copying:: (instance) * SortedCollection-disabled:: (instance) * SortedCollection-enumerating:: (instance) * SortedCollection-saving and loading:: (instance) * SortedCollection-searching:: (instance) * SortedCollection-sorting:: (instance)  File: gst-base.info, Node: SortedCollection class-hacking, Next: SortedCollection class-instance creation, Up: SortedCollection 1.156.1 SortedCollection class: hacking --------------------------------------- defaultSortBlock Answer a default sort block for the receiver.  File: gst-base.info, Node: SortedCollection class-instance creation, Next: SortedCollection-basic, Prev: SortedCollection class-hacking, Up: SortedCollection 1.156.2 SortedCollection class: instance creation ------------------------------------------------- new Answer a new collection with a default size and sort block new: aSize Answer a new collection with a default sort block and the given size sortBlock: aSortBlock Answer a new collection with a default size and the given sort block  File: gst-base.info, Node: SortedCollection-basic, Next: SortedCollection-copying, Prev: SortedCollection class-instance creation, Up: SortedCollection 1.156.3 SortedCollection: basic ------------------------------- last Answer the last item of the receiver removeLast Remove an object from the end of the receiver. Fail if the receiver is empty sortBlock Answer the receiver's sort criteria sortBlock: aSortBlock Change the sort criteria for a sorted collection, resort the elements of the collection, and return it.  File: gst-base.info, Node: SortedCollection-copying, Next: SortedCollection-disabled, Prev: SortedCollection-basic, Up: SortedCollection 1.156.4 SortedCollection: copying --------------------------------- copyEmpty: newSize Answer an empty copy of the receiver, with the same sort block as the receiver  File: gst-base.info, Node: SortedCollection-disabled, Next: SortedCollection-enumerating, Prev: SortedCollection-copying, Up: SortedCollection 1.156.5 SortedCollection: disabled ---------------------------------- add: anObject afterIndex: i This method should not be called for instances of this class. addAll: aCollection afterIndex: i This method should not be called for instances of this class. addAllFirst: aCollection This method should not be called for instances of this class. addAllLast: aCollection This method should not be called for instances of this class. addFirst: anObject This method should not be called for instances of this class. addLast: anObject This method should not be called for instances of this class. at: index put: anObject This method should not be called for instances of this class.  File: gst-base.info, Node: SortedCollection-enumerating, Next: SortedCollection-saving and loading, Prev: SortedCollection-disabled, Up: SortedCollection 1.156.6 SortedCollection: enumerating ------------------------------------- beConsistent Prepare the receiver to be walked through with #do: or another enumeration method.  File: gst-base.info, Node: SortedCollection-saving and loading, Next: SortedCollection-searching, Prev: SortedCollection-enumerating, Up: SortedCollection 1.156.7 SortedCollection: saving and loading -------------------------------------------- postLoad Restore the default sortBlock if it is nil preStore Store the default sortBlock as nil  File: gst-base.info, Node: SortedCollection-searching, Next: SortedCollection-sorting, Prev: SortedCollection-saving and loading, Up: SortedCollection 1.156.8 SortedCollection: searching ----------------------------------- includes: anObject Private - Answer whether the receiver includes an item which is equal to anObject indexOf: anObject startingAt: index ifAbsent: aBlock Answer the first index > anIndex which contains anElement. Invoke exceptionBlock and answer its result if no item is found occurrencesOf: anObject Answer how many occurrences of anObject can be found in the receiver  File: gst-base.info, Node: SortedCollection-sorting, Prev: SortedCollection-searching, Up: SortedCollection 1.156.9 SortedCollection: sorting --------------------------------- sort Sort the contents of the receiver according to the given sort block, which accepts pair of items and returns true if the first item is less than the second one. Fails if the collections's sort block is not the same as the default sort block. sort: sortBlock Sort the contents of the receiver according to the given sort block, which accepts pair of items and returns true if the first item is less than the second one. Fails if the sort block is not the same as the collection's sort block.  File: gst-base.info, Node: Stream, Next: String, Prev: SortedCollection, Up: Base classes 1.157 Stream ============ Defined in namespace Smalltalk Superclass: Iterable Category: Streams I am an abstract class that provides interruptable sequential access to objects. I can return successive objects from a source, or accept successive objects and store them sequentially on a sink. I provide some simple iteration over the contents of one of my instances, and provide for writing collections sequentially. * Menu: * Stream-accessing-reading:: (instance) * Stream-accessing-writing:: (instance) * Stream-basic:: (instance) * Stream-buffering:: (instance) * Stream-built ins:: (instance) * Stream-character writing:: (instance) * Stream-compiling:: (instance) * Stream-concatenating:: (instance) * Stream-enumerating:: (instance) * Stream-filing out:: (instance) * Stream-filtering:: (instance) * Stream-polymorphism:: (instance) * Stream-positioning:: (instance) * Stream-printing:: (instance) * Stream-still unclassified:: (instance) * Stream-storing:: (instance) * Stream-streaming protocol:: (instance) * Stream-testing:: (instance)  File: gst-base.info, Node: Stream-accessing-reading, Next: Stream-accessing-writing, Up: Stream 1.157.1 Stream: accessing-reading --------------------------------- contents Answer the whole contents of the receiver, from the next object to the last file Return nil by default; not all streams have a file. name Return nil by default; not all streams have a name. next Return the next object in the receiver next: anInteger Return the next anInteger objects in the receiver nextAvailable: anInteger Return up to anInteger objects in the receiver. Besides stopping if the end of the stream is reached, this may return less than this number of bytes for various reasons. For example, on files and sockets this operation could be non-blocking, or could do at most one I/O operation. nextAvailable: anInteger into: aCollection startingAt: pos Place the next anInteger objects from the receiver into aCollection, starting at position pos. Return the number of items stored. Besides stopping if the end of the stream is reached, this may return less than this number of bytes for various reasons. For example, on files and sockets this operation could be non-blocking, or could do at most one I/O operation. nextAvailable: anInteger putAllOn: aStream Copy up to anInteger objects in the receiver to aStream. Besides stopping if the end of the stream is reached, this may return less than this number of bytes for various reasons. For example, on files and sockets this operation could be non-blocking, or could do at most one I/O operation. nextLine Returns a collection of the same type that the stream accesses, containing the next line up to the next new-line character. Returns the entire rest of the stream's contents if no new-line character is found. nextMatchFor: anObject Answer whether the next object is equal to anObject. Even if it does not, anObject is lost splitAt: anObject Answer an OrderedCollection of parts of the receiver. A new (possibly empty) part starts at the start of the receiver, or after every occurrence of an object which is equal to anObject (as compared by #=). upTo: anObject Returns a collection of the same type that the stream accesses, up to but not including the object anObject. Returns the entire rest of the stream's contents if anObject is not present. upToAll: aCollection If there is a sequence of objects remaining in the stream that is equal to the sequence in aCollection, set the stream position just past that sequence and answer the elements up to, but not including, the sequence. Else, set the stream position to its end and answer all the remaining elements. upToEnd Answer every item in the collection on which the receiver is streaming, from the next one to the last  File: gst-base.info, Node: Stream-accessing-writing, Next: Stream-basic, Prev: Stream-accessing-reading, Up: Stream 1.157.2 Stream: accessing-writing --------------------------------- next: anInteger put: anObject Write anInteger copies of anObject to the receiver next: n putAll: aCollection startingAt: start Write n objects to the stream, reading them from aCollection and starting at the start-th item. nextPut: anObject Write anObject to the receiver nextPutAll: aCollection Write all the objects in aCollection to the receiver nextPutAllFlush: aCollection Put all the elements of aCollection in the stream, then flush the buffers if supported by the stream.  File: gst-base.info, Node: Stream-basic, Next: Stream-buffering, Prev: Stream-accessing-writing, Up: Stream 1.157.3 Stream: basic --------------------- species Answer `Array'.  File: gst-base.info, Node: Stream-buffering, Next: Stream-built ins, Prev: Stream-basic, Up: Stream 1.157.4 Stream: buffering ------------------------- next: anInteger into: answer startingAt: pos Read up to anInteger bytes from the stream and store them into answer. Return the number of bytes that were read, raising an exception if we could not read the full amount of data. next: anInteger putAllOn: aStream Read up to anInteger bytes from the stream and store them into aStream. Return the number of bytes that were read, raising an exception if we could not read the full amount of data.  File: gst-base.info, Node: Stream-built ins, Next: Stream-character writing, Prev: Stream-buffering, Up: Stream 1.157.5 Stream: built ins ------------------------- fileIn File in the contents of the receiver. During a file in operation, global variables (starting with an uppercase letter) that are not declared don't yield an `unknown variable' error. Instead, they are defined as nil in the `Undeclared' dictionary (a global variable residing in Smalltalk). As soon as you add the variable to a namespace (for example by creating a class) the Association will be removed from Undeclared and reused in the namespace, so that the old references will automagically point to the new value. fileInLine: lineNum file: aFile at: charPosInt Private - Much like a preprocessor #line directive; it is used internally by #fileIn, and explicitly by the Emacs Smalltalk mode. fileInLine: lineNum fileName: aString at: charPosInt Private - Much like a preprocessor #line directive; it is used internally by #fileIn, and explicitly by the Emacs Smalltalk mode.  File: gst-base.info, Node: Stream-character writing, Next: Stream-compiling, Prev: Stream-built ins, Up: Stream 1.157.6 Stream: character writing --------------------------------- cr Store a cr on the receiver crTab Store a cr and a tab on the receiver encoding Answer the encoding to be used when storing Unicode characters. isUnicode Answer whether the receiver is able to store Unicode characters. Note that if this method returns true, the stream may or may not be able to store Characters (as opposed to UnicodeCharacters) whose value is above 127. nl Store a new line on the receiver nlTab Store a new line and a tab on the receiver space Store a space on the receiver space: n Store n spaces on the receiver tab Store a tab on the receiver tab: n Store n tabs on the receiver  File: gst-base.info, Node: Stream-compiling, Next: Stream-concatenating, Prev: Stream-character writing, Up: Stream 1.157.7 Stream: compiling ------------------------- segmentFrom: startPos to: endPos Answer an object that, when sent #asString, will yield the result of sending `copyFrom: startPos to: endPos' to the receiver  File: gst-base.info, Node: Stream-concatenating, Next: Stream-enumerating, Prev: Stream-compiling, Up: Stream 1.157.8 Stream: concatenating ----------------------------- with: aStream Return a new Stream whose elements are 2-element Arrays, including one element from the receiver and one from aStream. with: stream1 with: stream2 Return a new Stream whose elements are 3-element Arrays, including one element from the receiver and one from each argument. with: stream1 with: stream2 with: stream3 Return a new Stream whose elements are 3-element Arrays, including one element from the receiver and one from each argument.  File: gst-base.info, Node: Stream-enumerating, Next: Stream-filing out, Prev: Stream-concatenating, Up: Stream 1.157.9 Stream: enumerating --------------------------- do: aBlock Evaluate aBlock once for every object in the receiver linesDo: aBlock Evaluate aBlock once for every line in the receiver (assuming the receiver is streaming on Characters).  File: gst-base.info, Node: Stream-filing out, Next: Stream-filtering, Prev: Stream-enumerating, Up: Stream 1.157.10 Stream: filing out --------------------------- fileOut: aClass File out aClass on the receiver. If aClass is not a metaclass, file out class and instance methods; if aClass is a metaclass, file out only the class methods  File: gst-base.info, Node: Stream-filtering, Next: Stream-polymorphism, Prev: Stream-filing out, Up: Stream 1.157.11 Stream: filtering -------------------------- , anIterable Answer a new stream that concatenates the data in the receiver with the data in aStream. Both the receiver and aStream should be readable. collect: aBlock Answer a new stream that will pass the returned objects through aBlock, and return whatever object is returned by aBlock instead. Note that when peeking in the returned stream, the block will be invoked multiple times, with possibly surprising results. lines Answer a new stream that answers lines from the receiver. peek Returns the next element of the stream without moving the pointer. Returns nil when at end of stream. Lookahead is implemented automatically for streams that are not positionable but can be copied. peekFor: aCharacter Returns true and gobbles the next element from the stream of it is equal to anObject, returns false and doesn't gobble the next element if the next element is not equal to anObject. Lookahead is implemented automatically for streams that are not positionable but can be copied. reject: aBlock Answer a new stream that only returns those objects for which aBlock returns false. Note that the returned stream will not be positionable. select: aBlock Answer a new stream that only returns those objects for which aBlock returns true. Note that the returned stream will not be positionable.  File: gst-base.info, Node: Stream-polymorphism, Next: Stream-positioning, Prev: Stream-filtering, Up: Stream 1.157.12 Stream: polymorphism ----------------------------- close Do nothing. This is provided for consistency with file streams flush Do nothing. This is provided for consistency with file streams pastEnd The end of the stream has been reached. Signal a Notification.  File: gst-base.info, Node: Stream-positioning, Next: Stream-printing, Prev: Stream-polymorphism, Up: Stream 1.157.13 Stream: positioning ---------------------------- isPositionable Answer true if the stream supports moving backwards with #skip:. skip: anInteger Move the position forwards by anInteger places skipSeparators Advance the receiver until we find a character that is not a separator. Answer false if we reach the end of the stream, else answer true; in this case, sending #next will return the first non-separator character (possibly the same to which the stream pointed before #skipSeparators was sent). skipTo: anObject Move the current position to after the next occurrence of anObject and return true if anObject was found. If anObject doesn't exist, the pointer is atEnd, and false is returned. skipToAll: aCollection If there is a sequence of objects remaining in the stream that is equal to the sequence in aCollection, set the stream position just past that sequence and answer true. Else, set the stream position to its end and answer false.  File: gst-base.info, Node: Stream-printing, Next: Stream-still unclassified, Prev: Stream-positioning, Up: Stream 1.157.14 Stream: printing ------------------------- << anObject This method is a short-cut for #display:; it prints anObject on the receiver by sending displayOn: to anObject. This method is provided so that you can use cascading and obtain better-looking code display: anObject Print anObject on the receiver by sending displayOn: to anObject. This method is provided so that you can use cascading and obtain better-looking code print: anObject Print anObject on the receiver by sending printOn: to anObject. This method is provided so that you can use cascading and obtain better-looking code  File: gst-base.info, Node: Stream-still unclassified, Next: Stream-storing, Prev: Stream-printing, Up: Stream 1.157.15 Stream: still unclassified ----------------------------------- nextPutAllOn: aStream Write all the objects in the receiver to aStream  File: gst-base.info, Node: Stream-storing, Next: Stream-streaming protocol, Prev: Stream-still unclassified, Up: Stream 1.157.16 Stream: storing ------------------------ store: anObject Print Smalltalk code compiling to anObject on the receiver, by sending storeOn: to anObject. This method is provided so that you can use cascading and obtain better-looking code  File: gst-base.info, Node: Stream-streaming protocol, Next: Stream-testing, Prev: Stream-storing, Up: Stream 1.157.17 Stream: streaming protocol ----------------------------------- nextAvailablePutAllOn: aStream Copy to aStream a more-or-less arbitrary amount of data. When used on files, this does at most one I/O operation. For other kinds of stream, the definition may vary. This method is used to do stream-to-stream copies.  File: gst-base.info, Node: Stream-testing, Prev: Stream-streaming protocol, Up: Stream 1.157.18 Stream: testing ------------------------ atEnd Answer whether the stream has got to an end isExternalStream Answer whether the receiver streams on a file or socket. By default, answer false. isSequenceable Answer whether the receiver can be accessed by a numeric index with #at:/#at:put:. readStream As a wild guess, return the receiver. WriteStreams should override this method.  File: gst-base.info, Node: String, Next: Symbol, Prev: Stream, Up: Base classes 1.158 String ============ Defined in namespace Smalltalk Superclass: CharacterArray Category: Collections-Text My instances represent 8-bit character strings. Being a very common case, they are particularly optimized. Note that, if you care about multilingualization, you should treat String only as an encoded representation of a UnicodeString. The I18N package adds more Unicode-friendliness to the system so that encoding and decoding is performed automatically in more cases. In that case, String represents a case when the encoding is either unknown, irrelevant, or assumed to be the system default. * Menu: * String class-instance creation:: (class) * String class-multibyte encodings:: (class) * String-accessing:: (instance) * String-basic:: (instance) * String-built ins:: (instance) * String-CObject:: (instance) * String-converting:: (instance) * String-filesystem:: (instance) * String-printing:: (instance) * String-regex:: (instance) * String-still unclassified:: (instance) * String-testing functionality:: (instance)  File: gst-base.info, Node: String class-instance creation, Next: String class-multibyte encodings, Up: String 1.158.1 String class: instance creation --------------------------------------- fromCData: aCObject Answer a String containing the bytes starting at the location pointed to by aCObject, up to the first NUL character. fromCData: aCObject size: anInteger Answer a String containing anInteger bytes starting at the location pointed to by aCObject  File: gst-base.info, Node: String class-multibyte encodings, Next: String-accessing, Prev: String class-instance creation, Up: String 1.158.2 String class: multibyte encodings ----------------------------------------- isUnicode Answer false; the receiver stores bytes (i.e. an encoded form), not characters.  File: gst-base.info, Node: String-accessing, Next: String-basic, Prev: String class-multibyte encodings, Up: String 1.158.3 String: accessing ------------------------- byteAt: index Answer the ascii value of index-th character variable of the receiver byteAt: index put: value Store (Character value: value) in the index-th indexed instance variable of the receiver  File: gst-base.info, Node: String-basic, Next: String-built ins, Prev: String-accessing, Up: String 1.158.4 String: basic --------------------- , aString Answer a new instance of an ArrayedCollection containing all the elements in the receiver, followed by all the elements in aSequenceableCollection = aCollection Answer whether the receiver's items match those in aCollection indexOf: anElement startingAt: anIndex Answer the first index > anIndex which contains anElement. Invoke exceptionBlock and answer its result if no item is found indexOf: anElement startingAt: anIndex ifAbsent: exceptionBlock Answer the first index > anIndex which contains anElement. Invoke exceptionBlock and answer its result if no item is found  File: gst-base.info, Node: String-built ins, Next: String-CObject, Prev: String-basic, Up: String 1.158.5 String: built ins ------------------------- asCData: aCType Allocate memory with malloc for a NULL-terminated copy of the receiver, and return a pointer to it as a CObject of the given type. at: anIndex Answer the index-th indexed instance variable of the receiver at: anIndex ifAbsent: aBlock Answer the index-th indexed instance variable of the receiver at: anIndex put: value Store value in the index-th indexed instance variable of the receiver basicAt: anIndex Answer the index-th indexed instance variable of the receiver. This method must not be overridden, override at: instead basicAt: anIndex put: value Store value in the index-th indexed instance variable of the receiver This method must not be overridden, override at:put: instead hash Answer an hash value for the receiver replaceFrom: start to: stop with: aString startingAt: replaceStart Replace the characters from start to stop with new characters whose ASCII codes are contained in aString, starting at the replaceStart location of aString replaceFrom: start to: stop withByteArray: byteArray startingAt: replaceStart Replace the characters from start to stop with new characters whose ASCII codes are contained in byteArray, starting at the replaceStart location of byteArray similarityTo: aString Answer a number that denotes the similarity between aString and the receiver. 0 indicates equality, negative numbers indicate some difference. Implemented as a primitive for speed. size Answer the size of the receiver  File: gst-base.info, Node: String-CObject, Next: String-converting, Prev: String-built ins, Up: String 1.158.6 String: CObject ----------------------- asCData Allocate memory with malloc for a NULL-terminated copy of the receiver, and return a pointer to it as a CChar.  File: gst-base.info, Node: String-converting, Next: String-filesystem, Prev: String-CObject, Up: String 1.158.7 String: converting -------------------------- asByteArray Return the receiver, converted to a ByteArray of ASCII values asString But I already am a String! Really! asSymbol Returns the symbol corresponding to the receiver encoding Answer the encoding of the receiver. This is not implemented unless you load the Iconv package.  File: gst-base.info, Node: String-filesystem, Next: String-printing, Prev: String-converting, Up: String 1.158.8 String: filesystem -------------------------- / aName Answer a File object as appropriate for a file named 'aName' in the directory represented by the receiver. asFile Answer a File object for the file whose name is in the receiver.  File: gst-base.info, Node: String-printing, Next: String-regex, Prev: String-filesystem, Up: String 1.158.9 String: printing ------------------------ displayOn: aStream Print a representation of the receiver on aStream. Unlike #printOn:, this method strips extra quotes. displayString Answer a String representing the receiver. For most objects this is simply its #printString, but for CharacterArrays and characters, superfluous dollars or extra pair of quotes are stripped. isLiteralObject Answer whether the receiver is expressible as a Smalltalk literal. printOn: aStream Print a representation of the receiver on aStream storeLiteralOn: aStream Store a Smalltalk literal compiling to the receiver on aStream storeOn: aStream Store Smalltalk code compiling to the receiver on aStream  File: gst-base.info, Node: String-regex, Next: String-still unclassified, Prev: String-printing, Up: String 1.158.10 String: regex ---------------------- =~ pattern Answer a RegexResults object for matching the receiver against the Regex or String object pattern. allOccurrencesOfRegex: pattern Find all the matches of pattern within the receiver and collect them into an OrderedCollection. allOccurrencesOfRegex: pattern do: aBlock Find all the matches of pattern within the receiver and pass the RegexResults objects to aBlock. allOccurrencesOfRegex: pattern from: from to: to Find all the matches of pattern within the receiver and within the given range of indices. Collect them into an OrderedCollection, which is then returned. allOccurrencesOfRegex: pattern from: from to: to do: aBlock Find all the matches of pattern within the receiver and within the given range of indices. For each match, pass the RegexResults object to aBlock. asRegex Answer the receiver, converted to a Regex object. copyFrom: from to: to replacingAllRegex: pattern with: aStringOrBlock Returns the substring of the receiver between from and to. Any match of pattern in that part of the string is replaced using aStringOrBlock as follows: if it is a block, a RegexResults object is passed, while if it is a string, %n sequences are replaced with the captured subexpressions of the match (as in #%). copyFrom: from to: to replacingRegex: pattern with: aStringOrBlock Returns the substring of the receiver between from and to. If pattern has a match in that part of the string, the match is replaced using aStringOrBlock as follows: if it is a block, a RegexResults object is passed, while if it is a string, %n sequences are replaced with the captured subexpressions of the match (as in #%). copyReplacingAllRegex: pattern with: aStringOrBlock Returns the receiver after replacing all the matches of pattern (if any) using aStringOrBlock as follows: if it is a block, a RegexResults object is passed, while if it is a string, %n sequences are replaced with the captured subexpressions of the match (as in #%). copyReplacingRegex: pattern with: aStringOrBlock Returns the receiver after replacing the first match of pattern (if any) using aStringOrBlock as follows: if it is a block, a RegexResults object is passed, while if it is a string, %n sequences are replaced with the captured subexpressions of the match (as in #%). indexOfRegex: regexString If an occurrence of the regex is present in the receiver, return the Interval corresponding to the leftmost-longest match. Otherwise return nil. indexOfRegex: regexString from: from to: to If an occurrence of the regex is present in the receiver, return the Interval corresponding to the leftmost-longest match occurring within the given range of indices. Otherwise return nil. indexOfRegex: regexString from: from to: to ifAbsent: excBlock If an occurrence of the regex is present in the receiver, return the Interval corresponding to the leftmost-longest match occurring within the given indices. Otherwise, evaluate excBlock and return the result. indexOfRegex: regexString ifAbsent: excBlock If an occurrence of the regex is present in the receiver, return the Interval corresponding to the leftmost-longest match. Otherwise, evaluate excBlock and return the result. indexOfRegex: regexString startingAt: index If an occurrence of the regex is present in the receiver, return the Interval corresponding to the leftmost-longest match starting after the given index. Otherwise return nil. indexOfRegex: regexString startingAt: index ifAbsent: excBlock If an occurrence of the regex is present in the receiver, return the Interval corresponding to the leftmost-longest match starting after the given index. Otherwise, evaluate excBlock and return the result. matchRegex: pattern Answer whether the receiver is an exact match for the pattern. This means that the pattern is implicitly anchored at the beginning and the end. matchRegex: pattern from: from to: to Answer whether the given range of indices is an exact match for the pattern. This means that there is a match starting at from and ending at to (which is not necessarily the longest match starting at from). occurrencesOfRegex: pattern Returns count of how many times pattern repeats in the receiver. occurrencesOfRegex: pattern from: from to: to Return a count of how many times pattern repeats in the receiver within the given range of index. occurrencesOfRegex: pattern startingAt: index Returns count of how many times pattern repeats in the receiver, starting the search at the given index. onOccurrencesOfRegex: pattern do: body Find all the matches of pattern within the receiver and, for each match, pass the RegexResults object to aBlock. onOccurrencesOfRegex: pattern from: from to: to do: aBlock Find all the matches of pattern within the receiver and within the given range of indices. For each match, pass the RegexResults object to aBlock. replacingAllRegex: pattern with: aStringOrBlock Returns the receiver if the pattern has no match in it. Otherwise, any match of pattern in that part of the string is replaced using aStringOrBlock as follows: if it is a block, a RegexResults object is passed, while if it is a string, %n sequences are replaced with the captured subexpressions of the match (as in #%). replacingRegex: pattern with: aStringOrBlock Returns the receiver if the pattern has no match in it. If it has a match, it is replaced using aStringOrBlock as follows: if it is a block, a RegexResults object is passed, while if it is a string, %n sequences are replaced with the captured subexpressions of the match (as in #%). searchRegex: pattern A synonym for #=~. Answer a RegexResults object for matching the receiver against the Regex or String object pattern. searchRegex: pattern from: from to: to Answer a RegexResults object for matching the receiver against the Regex or String object pattern, restricting the match to the specified range of indices. searchRegex: pattern startingAt: anIndex Answer a RegexResults object for matching the receiver against the Regex or String object pattern, starting the match at index anIndex. tokenize: pattern Split the receiver at every occurrence of pattern. All parts that do not match pattern are separated and stored into an Array of Strings that is returned. tokenize: pattern from: from to: to Split the receiver at every occurrence of pattern (considering only the indices between from and to). All parts that do not match pattern are separated and stored into an Array of Strings that is returned. ~ pattern Answer whether the receiver matched against the Regex or String object pattern.  File: gst-base.info, Node: String-still unclassified, Next: String-testing functionality, Prev: String-regex, Up: String 1.158.11 String: still unclassified ----------------------------------- escapeRegex Answer the receiver with all regex special characters escaped by a backslash.  File: gst-base.info, Node: String-testing functionality, Prev: String-still unclassified, Up: String 1.158.12 String: testing functionality -------------------------------------- isString Answer `true'.  File: gst-base.info, Node: Symbol, Next: SymLink, Prev: String, Up: Base classes 1.159 Symbol ============ Defined in namespace Smalltalk Superclass: String Category: Language-Implementation My instances are unique throughout the Smalltalk system. My instances behave for the most part like strings, except that they print differently, and I guarantee that any two instances that have the same printed representation are in fact the same instance. * Menu: * Symbol class-built ins:: (class) * Symbol class-instance creation:: (class) * Symbol class-symbol table:: (class) * Symbol-accessing the method dictionary:: (instance) * Symbol-basic:: (instance) * Symbol-built ins:: (instance) * Symbol-converting:: (instance) * Symbol-misc:: (instance) * Symbol-storing:: (instance) * Symbol-testing:: (instance) * Symbol-testing functionality:: (instance)  File: gst-base.info, Node: Symbol class-built ins, Next: Symbol class-instance creation, Up: Symbol 1.159.1 Symbol class: built ins ------------------------------- intern: aString Private - Same as 'aString asSymbol'  File: gst-base.info, Node: Symbol class-instance creation, Next: Symbol class-symbol table, Prev: Symbol class-built ins, Up: Symbol 1.159.2 Symbol class: instance creation --------------------------------------- internCharacter: aCharacter Answer the one-character symbol associated to the given character. new This method should not be called for instances of this class. new: size This method should not be called for instances of this class. with: element1 Answer a collection whose only element is element1 with: element1 with: element2 Answer a collection whose only elements are the parameters in the order they were passed with: element1 with: element2 with: element3 Answer a collection whose only elements are the parameters in the order they were passed with: element1 with: element2 with: element3 with: element4 Answer a collection whose only elements are the parameters in the order they were passed with: element1 with: element2 with: element3 with: element4 with: element5 Answer a collection whose only elements are the parameters in the order they were passed  File: gst-base.info, Node: Symbol class-symbol table, Next: Symbol-accessing the method dictionary, Prev: Symbol class-instance creation, Up: Symbol 1.159.3 Symbol class: symbol table ---------------------------------- hasInterned: aString ifTrue: aBlock If aString has not been interned yet, answer false. Else, pass the interned version to aBlock and answer true. Note that this works because String>>#hash calculates the same hash value used by the VM when interning strings into the SymbolTable. Changing one of the hashing methods without changing the other will break this method. isSymbolString: aString Answer whether aString has already been interned. Note that this works because String>>#hash calculates the same hash value used by the VM when interning strings into the SymbolTable. Changing one of the hashing methods without changing the other will break this method. rebuildTable Rebuild the SymbolTable, thereby garbage-collecting unreferenced Symbols. While this process is done, preemption is disabled because it is not acceptable to leave the SymbolTable in a partially updated state. Note that this works because String>>#hash calculates the same hash value used by the VM when interning strings into the SymbolTable. Changing one of the hashing methods without changing the other will break this method.  File: gst-base.info, Node: Symbol-accessing the method dictionary, Next: Symbol-basic, Prev: Symbol class-symbol table, Up: Symbol 1.159.4 Symbol: accessing the method dictionary ----------------------------------------------- implementors Answer a Set of all the compiled method associated with selector named by the receiver, which is supposed to be a valid message name.  File: gst-base.info, Node: Symbol-basic, Next: Symbol-built ins, Prev: Symbol-accessing the method dictionary, Up: Symbol 1.159.5 Symbol: basic --------------------- deepCopy Returns a deep copy of the receiver. As Symbols are identity objects, we actually return the receiver itself. keywords Answer an array of keywords that compose the receiver, which is supposed to be a valid message name (#+, #not, #printOn:, #ifTrue:ifFalse:, etc.) numArgs Answer the number of arguments supported by the receiver, which is supposed to be a valid message name (#+, #not, #printOn:, #ifTrue:ifFalse:, etc.) shallowCopy Returns a deep copy of the receiver. As Symbols are identity objects, we actually return the receiver itself.  File: gst-base.info, Node: Symbol-built ins, Next: Symbol-converting, Prev: Symbol-basic, Up: Symbol 1.159.6 Symbol: built ins ------------------------- = aSymbol Answer whether the receiver and aSymbol are the same object hash Answer an hash value for the receiver. Symbols are optimized for speed  File: gst-base.info, Node: Symbol-converting, Next: Symbol-misc, Prev: Symbol-built ins, Up: Symbol 1.159.7 Symbol: converting -------------------------- asString Answer a String with the same characters as the receiver asSymbol But we are already a Symbol, and furthermore, Symbols are identity objects! So answer the receiver.  File: gst-base.info, Node: Symbol-misc, Next: Symbol-storing, Prev: Symbol-converting, Up: Symbol 1.159.8 Symbol: misc -------------------- species Answer `String'.  File: gst-base.info, Node: Symbol-storing, Next: Symbol-testing, Prev: Symbol-misc, Up: Symbol 1.159.9 Symbol: storing ----------------------- displayOn: aStream Print a represention of the receiver on aStream. For most objects this is simply its #printOn: representation, but for strings and characters, superfluous dollars or extra pairs of quotes are stripped. displayString Answer a String representing the receiver. For most objects this is simply its #printString, but for strings and characters, superfluous dollars or extra pair of quotes are stripped. printOn: aStream Print a represention of the receiver on aStream. storeLiteralOn: aStream Print Smalltalk code on aStream that compiles to the same symbol as the receiver. storeOn: aStream Print Smalltalk code on aStream that compiles to the same symbol as the receiver.  File: gst-base.info, Node: Symbol-testing, Next: Symbol-testing functionality, Prev: Symbol-storing, Up: Symbol 1.159.10 Symbol: testing ------------------------ isSimpleSymbol Answer whether the receiver must be represented in quoted-string (e.g. #'abc-def') form.  File: gst-base.info, Node: Symbol-testing functionality, Prev: Symbol-testing, Up: Symbol 1.159.11 Symbol: testing functionality -------------------------------------- isString Answer `false'. isSymbol Answer `true'.  File: gst-base.info, Node: SymLink, Next: SystemDictionary, Prev: Symbol, Up: Base classes 1.160 SymLink ============= Defined in namespace Smalltalk Superclass: Link Category: Language-Implementation I am used to implement the Smalltalk symbol table. My instances are links that contain symbols, and the symbol table basically a hash table that points to chains of my instances. * Menu: * SymLink class-instance creation:: (class) * SymLink-accessing:: (instance) * SymLink-iteration:: (instance) * SymLink-printing:: (instance)  File: gst-base.info, Node: SymLink class-instance creation, Next: SymLink-accessing, Up: SymLink 1.160.1 SymLink class: instance creation ---------------------------------------- symbol: aSymbol nextLink: aSymLink Answer a new SymLink, which refers to aSymbol and points to aSymLink as the next SymLink in the chain.  File: gst-base.info, Node: SymLink-accessing, Next: SymLink-iteration, Prev: SymLink class-instance creation, Up: SymLink 1.160.2 SymLink: accessing -------------------------- symbol Answer the Symbol that the receiver refers to in the symbol table. symbol: aSymbol Set the Symbol that the receiver refers to in the symbol table.  File: gst-base.info, Node: SymLink-iteration, Next: SymLink-printing, Prev: SymLink-accessing, Up: SymLink 1.160.3 SymLink: iteration -------------------------- do: aBlock Evaluate aBlock for each symbol in the list  File: gst-base.info, Node: SymLink-printing, Prev: SymLink-iteration, Up: SymLink 1.160.4 SymLink: printing ------------------------- printOn: aStream Print a representation of the receiver on aStream.  File: gst-base.info, Node: SystemDictionary, Next: SystemExceptions.AlreadyDefined, Prev: SymLink, Up: Base classes 1.161 SystemDictionary ====================== Defined in namespace Smalltalk Superclass: RootNamespace Category: Language-Implementation I am a special namespace. I only have one instance, called "Smalltalk", which is known to the Smalltalk interpreter. I define several methods that are "system" related, such as #quitPrimitive. My instance also helps keep track of dependencies between objects. * Menu: * SystemDictionary class-initialization:: (class) * SystemDictionary-basic:: (instance) * SystemDictionary-builtins:: (instance) * SystemDictionary-c call-outs:: (instance) * SystemDictionary-command-line:: (instance) * SystemDictionary-miscellaneous:: (instance) * SystemDictionary-printing:: (instance) * SystemDictionary-profiling:: (instance) * SystemDictionary-special accessing:: (instance) * SystemDictionary-testing:: (instance)  File: gst-base.info, Node: SystemDictionary class-initialization, Next: SystemDictionary-basic, Up: SystemDictionary 1.161.1 SystemDictionary class: initialization ---------------------------------------------- initialize Create the kernel's private namespace.  File: gst-base.info, Node: SystemDictionary-basic, Next: SystemDictionary-builtins, Prev: SystemDictionary class-initialization, Up: SystemDictionary 1.161.2 SystemDictionary: basic ------------------------------- halt Interrupt interpreter hash Smalltalk usually contains a reference to itself, avoid infinite loops  File: gst-base.info, Node: SystemDictionary-builtins, Next: SystemDictionary-c call-outs, Prev: SystemDictionary-basic, Up: SystemDictionary 1.161.3 SystemDictionary: builtins ---------------------------------- basicBacktrace Prints the method invocation stack backtrace, as an aid to debugging byteCodeCounter Answer the number of bytecodes executed by the VM debug This methods provides a way to break in the VM code. Set a breakpoint in _gst_debug and call this method near the point where you think the bug happens. declarationTrace Answer whether compiled bytecodes are printed on stdout declarationTrace: aBoolean Set whether compiled bytecodes are printed on stdout executionTrace Answer whether executed bytecodes are printed on stdout executionTrace: aBoolean Set whether executed bytecodes are printed on stdout getTraceFlag: anIndex Private - Returns a boolean value which is one of the interpreter's tracing flags setTraceFlag: anIndex to: aBoolean Private - Sets the value of one of the interpreter's tracing flags (indicated by 'anIndex') to the value aBoolean. verboseTrace Answer whether execution tracing prints the object on the stack top verboseTrace: aBoolean Set whether execution tracing prints the object on the stack top  File: gst-base.info, Node: SystemDictionary-c call-outs, Next: SystemDictionary-command-line, Prev: SystemDictionary-builtins, Up: SystemDictionary 1.161.4 SystemDictionary: c call-outs ------------------------------------- environ Not commented. getArgc Not commented. getArgv: index Not commented. getenv: aString Not commented. putenv: aString Not commented. system: aString Not commented. system: aString withArguments: args Not commented.  File: gst-base.info, Node: SystemDictionary-command-line, Next: SystemDictionary-miscellaneous, Prev: SystemDictionary-c call-outs, Up: SystemDictionary 1.161.5 SystemDictionary: command-line -------------------------------------- arguments: pattern do: actionBlock Parse the command-line arguments according to the syntax specified in pattern. For every command-line option found, the two-argument block actionBlock is evaluated passing the option name and the argument. For file names (or in general, other command-line arguments than options) the block's first argument will be nil. For options without arguments, or with unspecified optional arguments, the block's second argument will be nil. The option name will be passed as a character object for short options, and as a string for long options. If an error is found, nil is returned. For more information on the syntax of pattern, see #arguments:do:ifError:. arguments: pattern do: actionBlock ifError: errorBlock Parse the command-line arguments according to the syntax specified in pattern. For every command-line option found, the two-argument block actionBlock is evaluated passing the option name and the argument. For file names (or in general, other command-line arguments than options) the block's first argument will be nil. For options without arguments, or with unspecified optional arguments, the block's second argument will be nil. The option name will be passed as a character object for short options, and as a string for long options. If an error is found, the parsing is interrupted, errorBlock is evaluated, and the returned value is answered. Every whitespace-separated part (`word') of pattern specifies a command-line option. If a word ends with a colon, the option will have a mandatory argument. If a word ends with two colons, the option will have an optional argument. Before the colons, multiple option names (either short names like `-l' or long names like `-long') can be specified. Before passing the option to actionBlock, the name will be canonicalized to the last one. Prefixes of long options are accepted as long as they're unique, and they are canonicalized to the full name before passing it to actionBlock. Additionally, the full name of an option is accepted even if it is the prefix of a longer option. Mandatory arguments can appear in the next argument, or in the same argument (separated by an = for arguments to long options). Optional arguments must appear in the same argument.  File: gst-base.info, Node: SystemDictionary-miscellaneous, Next: SystemDictionary-printing, Prev: SystemDictionary-command-line, Up: SystemDictionary 1.161.6 SystemDictionary: miscellaneous --------------------------------------- arguments Return the command line arguments after the -a switch backtrace Print a backtrace on the Transcript. hostSystem Answer the triplet corresponding to the system for which GNU Smalltalk was built.  File: gst-base.info, Node: SystemDictionary-printing, Next: SystemDictionary-profiling, Prev: SystemDictionary-miscellaneous, Up: SystemDictionary 1.161.7 SystemDictionary: printing ---------------------------------- nameIn: aNamespace Answer `'Smalltalk". printOn: aStream in: aNamespace Store Smalltalk code compiling to the receiver storeOn: aStream Store Smalltalk code compiling to the receiver  File: gst-base.info, Node: SystemDictionary-profiling, Next: SystemDictionary-special accessing, Prev: SystemDictionary-printing, Up: SystemDictionary 1.161.8 SystemDictionary: profiling ----------------------------------- rawProfile: anIdentityDictionary Set the raw profile to be anIdentityDictionary and return the old one.  File: gst-base.info, Node: SystemDictionary-special accessing, Next: SystemDictionary-testing, Prev: SystemDictionary-profiling, Up: SystemDictionary 1.161.9 SystemDictionary: special accessing ------------------------------------------- addFeature: aFeature Add the aFeature feature to the Features set hasFeatures: features Returns true if the feature or features in 'features' is one of the implementation dependent features present removeFeature: aFeature Remove the aFeature feature to the Features set version Answer the current version of the GNU Smalltalk environment  File: gst-base.info, Node: SystemDictionary-testing, Prev: SystemDictionary-special accessing, Up: SystemDictionary 1.161.10 SystemDictionary: testing ---------------------------------- imageLocal Answer whether the kernel directory is a subdirectory of the image directory (non-local image) or not. isSmalltalk Answer `true'.  File: gst-base.info, Node: SystemExceptions.AlreadyDefined, Next: SystemExceptions.ArgumentOutOfRange, Prev: SystemDictionary, Up: Base classes 1.162 SystemExceptions.AlreadyDefined ===================================== Defined in namespace Smalltalk.SystemExceptions Superclass: SystemExceptions.InvalidArgument Category: Language-Exceptions I am raised when one tries to define a symbol (class or pool variable) that is already defined. * Menu: * SystemExceptions.AlreadyDefined-accessing:: (instance)  File: gst-base.info, Node: SystemExceptions.AlreadyDefined-accessing, Up: SystemExceptions.AlreadyDefined 1.162.1 SystemExceptions.AlreadyDefined: accessing -------------------------------------------------- description Answer a description for the error  File: gst-base.info, Node: SystemExceptions.ArgumentOutOfRange, Next: SystemExceptions.BadReturn, Prev: SystemExceptions.AlreadyDefined, Up: Base classes 1.163 SystemExceptions.ArgumentOutOfRange ========================================= Defined in namespace Smalltalk.SystemExceptions Superclass: SystemExceptions.InvalidArgument Category: Language-Exceptions I am raised when one invokes a method with an argument outside of its valid range. * Menu: * SystemExceptions.ArgumentOutOfRange class-signaling:: (class) * SystemExceptions.ArgumentOutOfRange-accessing:: (instance)  File: gst-base.info, Node: SystemExceptions.ArgumentOutOfRange class-signaling, Next: SystemExceptions.ArgumentOutOfRange-accessing, Up: SystemExceptions.ArgumentOutOfRange 1.163.1 SystemExceptions.ArgumentOutOfRange class: signaling ------------------------------------------------------------ signalOn: value mustBeBetween: low and: high Raise the exception. The given value was not between low and high.  File: gst-base.info, Node: SystemExceptions.ArgumentOutOfRange-accessing, Prev: SystemExceptions.ArgumentOutOfRange class-signaling, Up: SystemExceptions.ArgumentOutOfRange 1.163.2 SystemExceptions.ArgumentOutOfRange: accessing ------------------------------------------------------ description Answer a textual description of the exception. high Answer the highest value that was permitted. high: aMagnitude Set the highest value that was permitted. low Answer the lowest value that was permitted. low: aMagnitude Set the lowest value that was permitted.  File: gst-base.info, Node: SystemExceptions.BadReturn, Next: SystemExceptions.CInterfaceError, Prev: SystemExceptions.ArgumentOutOfRange, Up: Base classes 1.164 SystemExceptions.BadReturn ================================ Defined in namespace Smalltalk.SystemExceptions Superclass: SystemExceptions.VMError Category: Language-Exceptions I am raised when one tries to return from an already-terminated method. * Menu: * SystemExceptions.BadReturn-accessing:: (instance)  File: gst-base.info, Node: SystemExceptions.BadReturn-accessing, Up: SystemExceptions.BadReturn 1.164.1 SystemExceptions.BadReturn: accessing --------------------------------------------- description Answer a textual description of the exception.  File: gst-base.info, Node: SystemExceptions.CInterfaceError, Next: SystemExceptions.EmptyCollection, Prev: SystemExceptions.BadReturn, Up: Base classes 1.165 SystemExceptions.CInterfaceError ====================================== Defined in namespace Smalltalk.SystemExceptions Superclass: SystemExceptions.PrimitiveFailed Category: Language-Exceptions I am raised when an error happens that is related to the C interface. * Menu: * SystemExceptions.CInterfaceError-accessing:: (instance)  File: gst-base.info, Node: SystemExceptions.CInterfaceError-accessing, Up: SystemExceptions.CInterfaceError 1.165.1 SystemExceptions.CInterfaceError: accessing --------------------------------------------------- description Answer a textual description of the exception.  File: gst-base.info, Node: SystemExceptions.EmptyCollection, Next: SystemExceptions.EndOfStream, Prev: SystemExceptions.CInterfaceError, Up: Base classes 1.166 SystemExceptions.EmptyCollection ====================================== Defined in namespace Smalltalk.SystemExceptions Superclass: SystemExceptions.InvalidValue Category: Language-Exceptions I am raised when one invokes a method on an empty collection. * Menu: * SystemExceptions.EmptyCollection-accessing:: (instance)  File: gst-base.info, Node: SystemExceptions.EmptyCollection-accessing, Up: SystemExceptions.EmptyCollection 1.166.1 SystemExceptions.EmptyCollection: accessing --------------------------------------------------- description Answer a textual description of the exception.  File: gst-base.info, Node: SystemExceptions.EndOfStream, Next: SystemExceptions.FileError, Prev: SystemExceptions.EmptyCollection, Up: Base classes 1.167 SystemExceptions.EndOfStream ================================== Defined in namespace Smalltalk.SystemExceptions Superclass: Notification Category: Language-Exceptions I am raised when a stream reaches its end. * Menu: * SystemExceptions.EndOfStream class-signaling:: (class) * SystemExceptions.EndOfStream-accessing:: (instance)  File: gst-base.info, Node: SystemExceptions.EndOfStream class-signaling, Next: SystemExceptions.EndOfStream-accessing, Up: SystemExceptions.EndOfStream 1.167.1 SystemExceptions.EndOfStream class: signaling ----------------------------------------------------- signalOn: stream Answer an exception reporting the parameter has reached its end.  File: gst-base.info, Node: SystemExceptions.EndOfStream-accessing, Prev: SystemExceptions.EndOfStream class-signaling, Up: SystemExceptions.EndOfStream 1.167.2 SystemExceptions.EndOfStream: accessing ----------------------------------------------- description Answer a textual description of the exception. stream Answer the stream whose end was reached. stream: anObject Set the stream whose end was reached.  File: gst-base.info, Node: SystemExceptions.FileError, Next: SystemExceptions.IndexOutOfRange, Prev: SystemExceptions.EndOfStream, Up: Base classes 1.168 SystemExceptions.FileError ================================ Defined in namespace Smalltalk.SystemExceptions Superclass: SystemExceptions.PrimitiveFailed Category: Language-Exceptions I am raised when an error happens that is related to the file system. * Menu: * SystemExceptions.FileError-accessing:: (instance)  File: gst-base.info, Node: SystemExceptions.FileError-accessing, Up: SystemExceptions.FileError 1.168.1 SystemExceptions.FileError: accessing --------------------------------------------- description Answer a textual description of the exception.  File: gst-base.info, Node: SystemExceptions.IndexOutOfRange, Next: SystemExceptions.InvalidArgument, Prev: SystemExceptions.FileError, Up: Base classes 1.169 SystemExceptions.IndexOutOfRange ====================================== Defined in namespace Smalltalk.SystemExceptions Superclass: SystemExceptions.ArgumentOutOfRange Category: Language-Exceptions I am raised when one invokes am accessor method with an index outside of its valid range. * Menu: * SystemExceptions.IndexOutOfRange class-signaling:: (class) * SystemExceptions.IndexOutOfRange-accessing:: (instance)  File: gst-base.info, Node: SystemExceptions.IndexOutOfRange class-signaling, Next: SystemExceptions.IndexOutOfRange-accessing, Up: SystemExceptions.IndexOutOfRange 1.169.1 SystemExceptions.IndexOutOfRange class: signaling --------------------------------------------------------- signalOn: aCollection withIndex: value The given index was out of range in aCollection.  File: gst-base.info, Node: SystemExceptions.IndexOutOfRange-accessing, Prev: SystemExceptions.IndexOutOfRange class-signaling, Up: SystemExceptions.IndexOutOfRange 1.169.2 SystemExceptions.IndexOutOfRange: accessing --------------------------------------------------- collection Answer the collection that triggered the error collection: anObject Set the collection that triggered the error description Answer a textual description of the exception. messageText Answer an exception's message text.  File: gst-base.info, Node: SystemExceptions.InvalidArgument, Next: SystemExceptions.InvalidProcessState, Prev: SystemExceptions.IndexOutOfRange, Up: Base classes 1.170 SystemExceptions.InvalidArgument ====================================== Defined in namespace Smalltalk.SystemExceptions Superclass: SystemExceptions.InvalidValue Category: Language-Exceptions I am raised when one invokes a method with an invalid argument. * Menu: * SystemExceptions.InvalidArgument-accessing:: (instance)  File: gst-base.info, Node: SystemExceptions.InvalidArgument-accessing, Up: SystemExceptions.InvalidArgument 1.170.1 SystemExceptions.InvalidArgument: accessing --------------------------------------------------- messageText Answer an exception's message text.  File: gst-base.info, Node: SystemExceptions.InvalidProcessState, Next: SystemExceptions.InvalidSize, Prev: SystemExceptions.InvalidArgument, Up: Base classes 1.171 SystemExceptions.InvalidProcessState ========================================== Defined in namespace Smalltalk.SystemExceptions Superclass: SystemExceptions.InvalidValue Category: Language-Exceptions I am an error raised when trying to resume a terminated process, or stuff like that. * Menu: * SystemExceptions.InvalidProcessState-accessing:: (instance)  File: gst-base.info, Node: SystemExceptions.InvalidProcessState-accessing, Up: SystemExceptions.InvalidProcessState 1.171.1 SystemExceptions.InvalidProcessState: accessing ------------------------------------------------------- description Answer a textual description of the exception.  File: gst-base.info, Node: SystemExceptions.InvalidSize, Next: SystemExceptions.InvalidState, Prev: SystemExceptions.InvalidProcessState, Up: Base classes 1.172 SystemExceptions.InvalidSize ================================== Defined in namespace Smalltalk.SystemExceptions Superclass: SystemExceptions.InvalidArgument Category: Language-Exceptions I am raised when an argument has an invalid size. * Menu: * SystemExceptions.InvalidSize-accessing:: (instance)  File: gst-base.info, Node: SystemExceptions.InvalidSize-accessing, Up: SystemExceptions.InvalidSize 1.172.1 SystemExceptions.InvalidSize: accessing ----------------------------------------------- description Answer a textual description of the exception.  File: gst-base.info, Node: SystemExceptions.InvalidState, Next: SystemExceptions.InvalidValue, Prev: SystemExceptions.InvalidSize, Up: Base classes 1.173 SystemExceptions.InvalidState =================================== Defined in namespace Smalltalk.SystemExceptions Superclass: SystemExceptions.InvalidValue Category: Language-Exceptions I am raised when one invokes a method and the receiver or an argument are in an invalid state for the method. * Menu: * SystemExceptions.InvalidState-accessing:: (instance)  File: gst-base.info, Node: SystemExceptions.InvalidState-accessing, Up: SystemExceptions.InvalidState 1.173.1 SystemExceptions.InvalidState: accessing ------------------------------------------------ messageText Answer an exception's message text.  File: gst-base.info, Node: SystemExceptions.InvalidValue, Next: SystemExceptions.MustBeBoolean, Prev: SystemExceptions.InvalidState, Up: Base classes 1.174 SystemExceptions.InvalidValue =================================== Defined in namespace Smalltalk.SystemExceptions Superclass: Error Category: Language-Exceptions I am raised when one invokes a method with an invalid receiver or argument. * Menu: * SystemExceptions.InvalidValue class-signaling:: (class) * SystemExceptions.InvalidValue-accessing:: (instance)  File: gst-base.info, Node: SystemExceptions.InvalidValue class-signaling, Next: SystemExceptions.InvalidValue-accessing, Up: SystemExceptions.InvalidValue 1.174.1 SystemExceptions.InvalidValue class: signaling ------------------------------------------------------ signalOn: value Answer an exception reporting the parameter as invalid. signalOn: value reason: reason Answer an exception reporting `value' as invalid, for the given reason.  File: gst-base.info, Node: SystemExceptions.InvalidValue-accessing, Prev: SystemExceptions.InvalidValue class-signaling, Up: SystemExceptions.InvalidValue 1.174.2 SystemExceptions.InvalidValue: accessing ------------------------------------------------ description Answer a textual description of the exception. messageText Answer an exception's message text. value Answer the object that was found to be invalid. value: anObject Set the object that was found to be invalid.  File: gst-base.info, Node: SystemExceptions.MustBeBoolean, Next: SystemExceptions.MutationError, Prev: SystemExceptions.InvalidValue, Up: Base classes 1.175 SystemExceptions.MustBeBoolean ==================================== Defined in namespace Smalltalk.SystemExceptions Superclass: SystemExceptions.WrongClass Category: Language-Exceptions I am raised when one invokes a boolean method on a non-boolean. * Menu: * SystemExceptions.MustBeBoolean class-signaling:: (class)  File: gst-base.info, Node: SystemExceptions.MustBeBoolean class-signaling, Up: SystemExceptions.MustBeBoolean 1.175.1 SystemExceptions.MustBeBoolean class: signaling ------------------------------------------------------- signalOn: anObject Signal a new exception, with the bad value in question being anObject.  File: gst-base.info, Node: SystemExceptions.MutationError, Next: SystemExceptions.NoRunnableProcess, Prev: SystemExceptions.MustBeBoolean, Up: Base classes 1.176 SystemExceptions.MutationError ==================================== Defined in namespace Smalltalk.SystemExceptions Superclass: Error Category: Language-Exceptions I am an error raised when a class is mutated in an invalid way. * Menu: * SystemExceptions.MutationError class-instance creation:: (class) * SystemExceptions.MutationError-accessing:: (instance)  File: gst-base.info, Node: SystemExceptions.MutationError class-instance creation, Next: SystemExceptions.MutationError-accessing, Up: SystemExceptions.MutationError 1.176.1 SystemExceptions.MutationError class: instance creation --------------------------------------------------------------- new Create an instance of the receiver, which you will be able to signal later.  File: gst-base.info, Node: SystemExceptions.MutationError-accessing, Prev: SystemExceptions.MutationError class-instance creation, Up: SystemExceptions.MutationError 1.176.2 SystemExceptions.MutationError: accessing ------------------------------------------------- description Answer a textual description of the exception.  File: gst-base.info, Node: SystemExceptions.NoRunnableProcess, Next: SystemExceptions.NotEnoughElements, Prev: SystemExceptions.MutationError, Up: Base classes 1.177 SystemExceptions.NoRunnableProcess ======================================== Defined in namespace Smalltalk.SystemExceptions Superclass: SystemExceptions.VMError Category: Language-Exceptions I am raised when no runnable process can be found in the image. * Menu: * SystemExceptions.NoRunnableProcess-accessing:: (instance)  File: gst-base.info, Node: SystemExceptions.NoRunnableProcess-accessing, Up: SystemExceptions.NoRunnableProcess 1.177.1 SystemExceptions.NoRunnableProcess: accessing ----------------------------------------------------- description Answer a textual description of the exception.  File: gst-base.info, Node: SystemExceptions.NotEnoughElements, Next: SystemExceptions.NotFound, Prev: SystemExceptions.NoRunnableProcess, Up: Base classes 1.178 SystemExceptions.NotEnoughElements ======================================== Defined in namespace Smalltalk.SystemExceptions Superclass: Error Category: Language-Exceptions I am raised when one invokes #next: but not enough items remain in the stream. * Menu: * SystemExceptions.NotEnoughElements class-signaling:: (class) * SystemExceptions.NotEnoughElements-accessing:: (instance)  File: gst-base.info, Node: SystemExceptions.NotEnoughElements class-signaling, Next: SystemExceptions.NotEnoughElements-accessing, Up: SystemExceptions.NotEnoughElements 1.178.1 SystemExceptions.NotEnoughElements class: signaling ----------------------------------------------------------- signalOn: remainingCount Answer an exception reporting the parameter as invalid.  File: gst-base.info, Node: SystemExceptions.NotEnoughElements-accessing, Prev: SystemExceptions.NotEnoughElements class-signaling, Up: SystemExceptions.NotEnoughElements 1.178.2 SystemExceptions.NotEnoughElements: accessing ----------------------------------------------------- description Answer a textual description of the exception. messageText Answer an exception's message text. remainingCount Answer the number of items that were to be read. remainingCount: anObject Set the number of items that were to be read.  File: gst-base.info, Node: SystemExceptions.NotFound, Next: SystemExceptions.NotImplemented, Prev: SystemExceptions.NotEnoughElements, Up: Base classes 1.179 SystemExceptions.NotFound =============================== Defined in namespace Smalltalk.SystemExceptions Superclass: SystemExceptions.InvalidArgument Category: Language-Exceptions I am raised when something is searched without success. * Menu: * SystemExceptions.NotFound class-accessing:: (class) * SystemExceptions.NotFound-accessing:: (instance)  File: gst-base.info, Node: SystemExceptions.NotFound class-accessing, Next: SystemExceptions.NotFound-accessing, Up: SystemExceptions.NotFound 1.179.1 SystemExceptions.NotFound class: accessing -------------------------------------------------- signalOn: value reason: aString Raise an exception: reason specifies the reason of the exception. signalOn: value what: aString Raise an exception; aString specifies what was not found (a key, an object, a class, and so on).  File: gst-base.info, Node: SystemExceptions.NotFound-accessing, Prev: SystemExceptions.NotFound class-accessing, Up: SystemExceptions.NotFound 1.179.2 SystemExceptions.NotFound: accessing -------------------------------------------- description Answer a textual description of the exception.  File: gst-base.info, Node: SystemExceptions.NotImplemented, Next: SystemExceptions.NotIndexable, Prev: SystemExceptions.NotFound, Up: Base classes 1.180 SystemExceptions.NotImplemented ===================================== Defined in namespace Smalltalk.SystemExceptions Superclass: Error Category: Language-Exceptions I am raised when a method is called that has not been implemented. * Menu: * SystemExceptions.NotImplemented-accessing:: (instance)  File: gst-base.info, Node: SystemExceptions.NotImplemented-accessing, Up: SystemExceptions.NotImplemented 1.180.1 SystemExceptions.NotImplemented: accessing -------------------------------------------------- description Answer a textual description of the exception.  File: gst-base.info, Node: SystemExceptions.NotIndexable, Next: SystemExceptions.NotYetImplemented, Prev: SystemExceptions.NotImplemented, Up: Base classes 1.181 SystemExceptions.NotIndexable =================================== Defined in namespace Smalltalk.SystemExceptions Superclass: SystemExceptions.InvalidValue Category: Language-Exceptions I am raised when an object is not indexable. * Menu: * SystemExceptions.NotIndexable-accessing:: (instance)  File: gst-base.info, Node: SystemExceptions.NotIndexable-accessing, Up: SystemExceptions.NotIndexable 1.181.1 SystemExceptions.NotIndexable: accessing ------------------------------------------------ description Answer a textual description of the exception.  File: gst-base.info, Node: SystemExceptions.NotYetImplemented, Next: SystemExceptions.PackageNotAvailable, Prev: SystemExceptions.NotIndexable, Up: Base classes 1.182 SystemExceptions.NotYetImplemented ======================================== Defined in namespace Smalltalk.SystemExceptions Superclass: SystemExceptions.NotImplemented Category: Language-Exceptions I am raised when a method is called that has not been implemented yet. * Menu: * SystemExceptions.NotYetImplemented-accessing:: (instance)  File: gst-base.info, Node: SystemExceptions.NotYetImplemented-accessing, Up: SystemExceptions.NotYetImplemented 1.182.1 SystemExceptions.NotYetImplemented: accessing ----------------------------------------------------- description Answer a textual description of the exception.  File: gst-base.info, Node: SystemExceptions.PackageNotAvailable, Next: SystemExceptions.PrimitiveFailed, Prev: SystemExceptions.NotYetImplemented, Up: Base classes 1.183 SystemExceptions.PackageNotAvailable ========================================== Defined in namespace Smalltalk.SystemExceptions Superclass: SystemExceptions.NotFound Category: Language-Packaging * Menu: * SystemExceptions.PackageNotAvailable class-still unclassified:: (class) * SystemExceptions.PackageNotAvailable-description:: (instance)  File: gst-base.info, Node: SystemExceptions.PackageNotAvailable class-still unclassified, Next: SystemExceptions.PackageNotAvailable-description, Up: SystemExceptions.PackageNotAvailable 1.183.1 SystemExceptions.PackageNotAvailable class: still unclassified ---------------------------------------------------------------------- signal: aString Signal an exception saying that the package named aString can't be found. signal: package reason: reason Signal an exception saying that be package named package can't be found because the reason named reason.  File: gst-base.info, Node: SystemExceptions.PackageNotAvailable-description, Prev: SystemExceptions.PackageNotAvailable class-still unclassified, Up: SystemExceptions.PackageNotAvailable 1.183.2 SystemExceptions.PackageNotAvailable: description --------------------------------------------------------- isResumable Answer true. Package unavailability is resumable, because the package files might just lie elsewhere.  File: gst-base.info, Node: SystemExceptions.PrimitiveFailed, Next: SystemExceptions.ProcessBeingTerminated, Prev: SystemExceptions.PackageNotAvailable, Up: Base classes 1.184 SystemExceptions.PrimitiveFailed ====================================== Defined in namespace Smalltalk.SystemExceptions Superclass: SystemExceptions.VMError Category: Language-Exceptions I am raised when a primitive fails for some reason. * Menu: * SystemExceptions.PrimitiveFailed-accessing:: (instance)  File: gst-base.info, Node: SystemExceptions.PrimitiveFailed-accessing, Up: SystemExceptions.PrimitiveFailed 1.184.1 SystemExceptions.PrimitiveFailed: accessing --------------------------------------------------- description Answer a textual description of the exception.  File: gst-base.info, Node: SystemExceptions.ProcessBeingTerminated, Next: SystemExceptions.ProcessTerminated, Prev: SystemExceptions.PrimitiveFailed, Up: Base classes 1.185 SystemExceptions.ProcessBeingTerminated ============================================= Defined in namespace Smalltalk.SystemExceptions Superclass: Notification Category: Language-Exceptions I am raised when a process is terminated. * Menu: * SystemExceptions.ProcessBeingTerminated class-still unclassified:: (class) * SystemExceptions.ProcessBeingTerminated-accessing:: (instance)  File: gst-base.info, Node: SystemExceptions.ProcessBeingTerminated class-still unclassified, Next: SystemExceptions.ProcessBeingTerminated-accessing, Up: SystemExceptions.ProcessBeingTerminated 1.185.1 SystemExceptions.ProcessBeingTerminated class: still unclassified ------------------------------------------------------------------------- initialize Not commented.  File: gst-base.info, Node: SystemExceptions.ProcessBeingTerminated-accessing, Prev: SystemExceptions.ProcessBeingTerminated class-still unclassified, Up: SystemExceptions.ProcessBeingTerminated 1.185.2 SystemExceptions.ProcessBeingTerminated: accessing ---------------------------------------------------------- description Answer a textual description of the exception. semaphore If the process was waiting on a semaphore, answer it. semaphore: aSemaphore If the process was waiting on a semaphore, answer it.  File: gst-base.info, Node: SystemExceptions.ProcessTerminated, Next: SystemExceptions.ReadOnlyObject, Prev: SystemExceptions.ProcessBeingTerminated, Up: Base classes 1.186 SystemExceptions.ProcessTerminated ======================================== Defined in namespace Smalltalk.SystemExceptions Superclass: SystemExceptions.InvalidValue Category: Language-Exceptions I am raised when somebody tries to resume or interrupt a terminated process. * Menu: * SystemExceptions.ProcessTerminated-accessing:: (instance)  File: gst-base.info, Node: SystemExceptions.ProcessTerminated-accessing, Up: SystemExceptions.ProcessTerminated 1.186.1 SystemExceptions.ProcessTerminated: accessing ----------------------------------------------------- description Answer a textual description of the exception.  File: gst-base.info, Node: SystemExceptions.ReadOnlyObject, Next: SystemExceptions.SecurityError, Prev: SystemExceptions.ProcessTerminated, Up: Base classes 1.187 SystemExceptions.ReadOnlyObject ===================================== Defined in namespace Smalltalk.SystemExceptions Superclass: SystemExceptions.InvalidValue Category: Language-Exceptions I am raised when one writes to a read-only object. * Menu: * SystemExceptions.ReadOnlyObject-accessing:: (instance)  File: gst-base.info, Node: SystemExceptions.ReadOnlyObject-accessing, Up: SystemExceptions.ReadOnlyObject 1.187.1 SystemExceptions.ReadOnlyObject: accessing -------------------------------------------------- description Answer a textual description of the exception.  File: gst-base.info, Node: SystemExceptions.SecurityError, Next: SystemExceptions.ShouldNotImplement, Prev: SystemExceptions.ReadOnlyObject, Up: Base classes 1.188 SystemExceptions.SecurityError ==================================== Defined in namespace Smalltalk.SystemExceptions Superclass: SystemExceptions.VMError Category: Language-Exceptions I am an error raised when an untrusted object tries to do an insecure operation. * Menu: * SystemExceptions.SecurityError class-accessing:: (class) * SystemExceptions.SecurityError-accessing:: (instance)  File: gst-base.info, Node: SystemExceptions.SecurityError class-accessing, Next: SystemExceptions.SecurityError-accessing, Up: SystemExceptions.SecurityError 1.188.1 SystemExceptions.SecurityError class: accessing ------------------------------------------------------- signal: aPermission Raise the exception, setting to aPermission the permission that was tested and failed.  File: gst-base.info, Node: SystemExceptions.SecurityError-accessing, Prev: SystemExceptions.SecurityError class-accessing, Up: SystemExceptions.SecurityError 1.188.2 SystemExceptions.SecurityError: accessing ------------------------------------------------- description Answer a textual description of the exception. failedPermission Answer the permission that was tested and that failed. failedPermission: anObject Set which permission was tested and failed.  File: gst-base.info, Node: SystemExceptions.ShouldNotImplement, Next: SystemExceptions.SubclassResponsibility, Prev: SystemExceptions.SecurityError, Up: Base classes 1.189 SystemExceptions.ShouldNotImplement ========================================= Defined in namespace Smalltalk.SystemExceptions Superclass: SystemExceptions.NotImplemented Category: Language-Exceptions I am raised when a method is called that a class wishes that is not called. * Menu: * SystemExceptions.ShouldNotImplement-accessing:: (instance)  File: gst-base.info, Node: SystemExceptions.ShouldNotImplement-accessing, Up: SystemExceptions.ShouldNotImplement 1.189.1 SystemExceptions.ShouldNotImplement: accessing ------------------------------------------------------ description Answer a textual description of the exception.  File: gst-base.info, Node: SystemExceptions.SubclassResponsibility, Next: SystemExceptions.UnhandledException, Prev: SystemExceptions.ShouldNotImplement, Up: Base classes 1.190 SystemExceptions.SubclassResponsibility ============================================= Defined in namespace Smalltalk.SystemExceptions Superclass: SystemExceptions.ShouldNotImplement Category: Language-Exceptions I am raised when a method is called whose implementation is the responsibility of concrete subclass. * Menu: * SystemExceptions.SubclassResponsibility-accessing:: (instance)  File: gst-base.info, Node: SystemExceptions.SubclassResponsibility-accessing, Up: SystemExceptions.SubclassResponsibility 1.190.1 SystemExceptions.SubclassResponsibility: accessing ---------------------------------------------------------- description Answer a textual description of the exception.  File: gst-base.info, Node: SystemExceptions.UnhandledException, Next: SystemExceptions.UserInterrupt, Prev: SystemExceptions.SubclassResponsibility, Up: Base classes 1.191 SystemExceptions.UnhandledException ========================================= Defined in namespace Smalltalk.SystemExceptions Superclass: Exception Category: Language-Exception I am raised when a backtrace is shown to terminate the current process. * Menu: * SystemExceptions.UnhandledException-accessing:: (instance)  File: gst-base.info, Node: SystemExceptions.UnhandledException-accessing, Up: SystemExceptions.UnhandledException 1.191.1 SystemExceptions.UnhandledException: accessing ------------------------------------------------------ defaultAction Terminate the current process. description Answer a textual description of the exception. originalException Answer the uncaught exception. originalException: anObject Set the uncaught exception to anObject.  File: gst-base.info, Node: SystemExceptions.UserInterrupt, Next: SystemExceptions.VerificationError, Prev: SystemExceptions.UnhandledException, Up: Base classes 1.192 SystemExceptions.UserInterrupt ==================================== Defined in namespace Smalltalk.SystemExceptions Superclass: SystemExceptions.VMError Category: Language-Exceptions I am raised when one presses Ctrl-C. * Menu: * SystemExceptions.UserInterrupt-accessing:: (instance)  File: gst-base.info, Node: SystemExceptions.UserInterrupt-accessing, Up: SystemExceptions.UserInterrupt 1.192.1 SystemExceptions.UserInterrupt: accessing ------------------------------------------------- description Answer a textual description of the exception.  File: gst-base.info, Node: SystemExceptions.VerificationError, Next: SystemExceptions.VMError, Prev: SystemExceptions.UserInterrupt, Up: Base classes 1.193 SystemExceptions.VerificationError ======================================== Defined in namespace Smalltalk.SystemExceptions Superclass: SystemExceptions.VMError Category: Language-Exceptions I am raised when the verification of a method fails. * Menu: * SystemExceptions.VerificationError-accessing:: (instance)  File: gst-base.info, Node: SystemExceptions.VerificationError-accessing, Up: SystemExceptions.VerificationError 1.193.1 SystemExceptions.VerificationError: accessing ----------------------------------------------------- description Answer a textual description of the exception.  File: gst-base.info, Node: SystemExceptions.VMError, Next: SystemExceptions.WrongArgumentCount, Prev: SystemExceptions.VerificationError, Up: Base classes 1.194 SystemExceptions.VMError ============================== Defined in namespace Smalltalk.SystemExceptions Superclass: Error Category: Language-Exceptions I am an error related to the innards of the system. * Menu: * SystemExceptions.VMError-accessing:: (instance)  File: gst-base.info, Node: SystemExceptions.VMError-accessing, Up: SystemExceptions.VMError 1.194.1 SystemExceptions.VMError: accessing ------------------------------------------- description Answer a textual description of the exception.  File: gst-base.info, Node: SystemExceptions.WrongArgumentCount, Next: SystemExceptions.WrongClass, Prev: SystemExceptions.VMError, Up: Base classes 1.195 SystemExceptions.WrongArgumentCount ========================================= Defined in namespace Smalltalk.SystemExceptions Superclass: SystemExceptions.PrimitiveFailed Category: Language-Exceptions I am raised when one tries to evaluate a method (via #perform:...) or a block but passes the wrong number of arguments. * Menu: * SystemExceptions.WrongArgumentCount-accessing:: (instance)  File: gst-base.info, Node: SystemExceptions.WrongArgumentCount-accessing, Up: SystemExceptions.WrongArgumentCount 1.195.1 SystemExceptions.WrongArgumentCount: accessing ------------------------------------------------------ description Answer a textual description of the exception.  File: gst-base.info, Node: SystemExceptions.WrongClass, Next: SystemExceptions.WrongMessageSent, Prev: SystemExceptions.WrongArgumentCount, Up: Base classes 1.196 SystemExceptions.WrongClass ================================= Defined in namespace Smalltalk.SystemExceptions Superclass: SystemExceptions.InvalidValue Category: Language-Exceptions I am raised when an argument is constrained to be an instance of a determinate class, and this constraint is not respected by the caller. * Menu: * SystemExceptions.WrongClass class-signaling:: (class) * SystemExceptions.WrongClass-accessing:: (instance)  File: gst-base.info, Node: SystemExceptions.WrongClass class-signaling, Next: SystemExceptions.WrongClass-accessing, Up: SystemExceptions.WrongClass 1.196.1 SystemExceptions.WrongClass class: signaling ---------------------------------------------------- signalOn: anObject mustBe: aClassOrArray Raise an exception. The given object should have been an instance of one of the classes indicated by aClassOrArray (which should be a single class or an array of classes). Whether instances of subclasses are allowed should be clear from the context, though in general (i.e. with the exception of a few system messages) they should be.  File: gst-base.info, Node: SystemExceptions.WrongClass-accessing, Prev: SystemExceptions.WrongClass class-signaling, Up: SystemExceptions.WrongClass 1.196.2 SystemExceptions.WrongClass: accessing ---------------------------------------------- description Answer a textual description of the exception. messageText Answer an exception's message text. validClasses Answer the list of classes whose instances would have been valid. validClasses: aCollection Set the list of classes whose instances would have been valid. validClassesString Answer the list of classes whose instances would have been valid, formatted as a string.  File: gst-base.info, Node: SystemExceptions.WrongMessageSent, Next: TextCollector, Prev: SystemExceptions.WrongClass, Up: Base classes 1.197 SystemExceptions.WrongMessageSent ======================================= Defined in namespace Smalltalk.SystemExceptions Superclass: SystemExceptions.ShouldNotImplement Category: Language-Exceptions I am raised when a method is called that a class wishes that is not called. This exception also includes a suggestion on which message should be sent instead * Menu: * SystemExceptions.WrongMessageSent class-signaling:: (class) * SystemExceptions.WrongMessageSent-accessing:: (instance)  File: gst-base.info, Node: SystemExceptions.WrongMessageSent class-signaling, Next: SystemExceptions.WrongMessageSent-accessing, Up: SystemExceptions.WrongMessageSent 1.197.1 SystemExceptions.WrongMessageSent class: signaling ---------------------------------------------------------- signalOn: selector useInstead: aSymbol Raise an exception, signaling which selector was sent and suggesting a valid alternative.  File: gst-base.info, Node: SystemExceptions.WrongMessageSent-accessing, Prev: SystemExceptions.WrongMessageSent class-signaling, Up: SystemExceptions.WrongMessageSent 1.197.2 SystemExceptions.WrongMessageSent: accessing ---------------------------------------------------- messageText Answer an exception's message text. selector Answer which selector was sent. selector: aSymbol Set which selector was sent. suggestedSelector Answer a valid alternative to the selector that was used. suggestedSelector: aSymbol Set a valid alternative to the selector that was used.  File: gst-base.info, Node: TextCollector, Next: Time, Prev: SystemExceptions.WrongMessageSent, Up: Base classes 1.198 TextCollector =================== Defined in namespace Smalltalk Superclass: Stream Category: Streams I am a thread-safe class that maps between standard Stream protocol and a single message to another object (its selector is pluggable and should roughly correspond to #nextPutAll:). I am, in fact, the class that implements the global Transcript object. * Menu: * TextCollector class-accessing:: (class) * TextCollector-accessing:: (instance) * TextCollector-printing:: (instance) * TextCollector-set up:: (instance) * TextCollector-storing:: (instance)  File: gst-base.info, Node: TextCollector class-accessing, Next: TextCollector-accessing, Up: TextCollector 1.198.1 TextCollector class: accessing -------------------------------------- message: receiverToSelectorAssociation Answer a new instance of the receiver, that uses the message identified by anAssociation to perform write operations. anAssociation's key is the receiver, while its value is the selector. new This method should not be called for instances of this class.  File: gst-base.info, Node: TextCollector-accessing, Next: TextCollector-printing, Prev: TextCollector class-accessing, Up: TextCollector 1.198.2 TextCollector: accessing -------------------------------- cr Emit a new-line (carriage return) to the Transcript critical: aBlock Evaluate aBlock while holding the Transcript lock endEntry Emit two new-lines. This method is present for compatibility with VisualWorks. next: anInteger put: anObject Write anInteger copies of anObject to the Transcript next: n putAll: aString startingAt: pos Write aString to the Transcript nextPut: aCharacter Emit aCharacter to the Transcript show: aString Write aString to the Transcript showCr: aString Write aString to the Transcript, followed by a new-line character showOnNewLine: aString Write aString to the Transcript, preceded by a new-line character  File: gst-base.info, Node: TextCollector-printing, Next: TextCollector-set up, Prev: TextCollector-accessing, Up: TextCollector 1.198.3 TextCollector: printing ------------------------------- print: anObject Print anObject's representation to the Transcript printOn: aStream Print a representation of the receiver onto aStream  File: gst-base.info, Node: TextCollector-set up, Next: TextCollector-storing, Prev: TextCollector-printing, Up: TextCollector 1.198.4 TextCollector: set up ----------------------------- message Answer an association representing the message to be sent to perform write operations. The key is the receiver, the value is the selector message: receiverToSelectorAssociation Set the message to be sent to perform write operations to the one represented by anAssociation. anAssociation's key is the receiver, while its value is the selector  File: gst-base.info, Node: TextCollector-storing, Prev: TextCollector-set up, Up: TextCollector 1.198.5 TextCollector: storing ------------------------------ store: anObject Print Smalltalk code which evaluates to anObject on the Transcript storeOn: aStream Print Smalltalk code which evaluates to the receiver onto aStream  File: gst-base.info, Node: Time, Next: True, Prev: TextCollector, Up: Base classes 1.199 Time ========== Defined in namespace Smalltalk Superclass: Magnitude Category: Language-Data types My instances represent times of the day. I provide methods for instance creation, methods that access components (hours, minutes, and seconds) of a time value, and a block execution timing facility. * Menu: * Time class-basic (UTC):: (class) * Time class-builtins:: (class) * Time class-clocks:: (class) * Time class-initialization:: (class) * Time class-instance creation:: (class) * Time-accessing (ANSI for DateAndTimes):: (instance) * Time-accessing (non ANSI & for Durations):: (instance) * Time-arithmetic:: (instance) * Time-comparing:: (instance)  File: gst-base.info, Node: Time class-basic (UTC), Next: Time class-builtins, Up: Time 1.199.1 Time class: basic (UTC) ------------------------------- midnight Answer a time representing midnight in Coordinated Universal Time (UTC) utcNow Answer a time representing the current time of day in Coordinated Universal Time (UTC) utcSecondClock Answer the number of seconds since the midnight of 1/1/1901 (unlike #secondClock, the reference time is here expressed as UTC, that is as Coordinated Universal Time).  File: gst-base.info, Node: Time class-builtins, Next: Time class-clocks, Prev: Time class-basic (UTC), Up: Time 1.199.2 Time class: builtins ---------------------------- primNanosecondClock Returns the number of milliseconds since midnight. primSecondClock Returns the number of seconds to/from 1/1/2000. timezone Answer a String associated with the current timezone (either standard or daylight-saving) on this operating system. For example, the answer could be `EST' to indicate Eastern Standard Time; the answer can be empty and can't be assumed to be a three-character code such as `EST'. timezoneBias Specifies the current bias, in seconds, for local time translation for the current time. The bias is the difference, in seconds, between Coordinated Universal Time (UTC) and local time; a positive bias indicates that the local timezone is to the east of Greenwich (e.g. Europe, Asia), while a negative bias indicates that it is to the west (e.g. America) timezoneBias: seconds Specifies the bias, in seconds, for local time translation for the given second clock value (0 being midnight of 1/1/1901). The bias is the difference, in seconds, between Coordinated Universal Time (UTC) and local time; a positive bias indicates that the local timezone is to the east of Greenwich (e.g. Europe, Asia), while a negative bias indicates that it is to the west (e.g. America)  File: gst-base.info, Node: Time class-clocks, Next: Time class-initialization, Prev: Time class-builtins, Up: Time 1.199.3 Time class: clocks -------------------------- millisecondClock Answer the number of milliseconds since startup. millisecondClockValue Answer the number of milliseconds since startup millisecondsPerDay Answer the number of milliseconds in a day millisecondsToRun: timedBlock Answer the number of milliseconds which timedBlock took to run nanosecondClock Answer the number of nanoseconds since startup. nanosecondClockValue Answer the number of milliseconds since startup secondClock Answer the number of seconds since the midnight of 1/1/1901  File: gst-base.info, Node: Time class-initialization, Next: Time class-instance creation, Prev: Time class-clocks, Up: Time 1.199.4 Time class: initialization ---------------------------------- initialize Initialize the Time class after the image has been bootstrapped update: aspect Private - Initialize the receiver's instance variables  File: gst-base.info, Node: Time class-instance creation, Next: Time-accessing (ANSI for DateAndTimes), Prev: Time class-initialization, Up: Time 1.199.5 Time class: instance creation ------------------------------------- fromSeconds: secondCount Answer a Time representing secondCount seconds past midnight hour: h Answer a Time that is the given number of hours past midnight hour: h minute: m second: s Answer a Time that is the given number of hours, minutes and seconds past midnight hours: h Answer a Time that is the given number of hours past midnight hours: h minutes: m seconds: s Answer a Time that is the given number of hours, minutes and seconds past midnight minute: m Answer a Time that is the given number of minutes past midnight minutes: m Answer a Time that is the given number of minutes past midnight new Answer a Time representing midnight now Answer a time representing the current time of day readFrom: aStream Parse an instance of the receiver (hours/minutes/seconds) from aStream second: s Answer a Time that is the given number of seconds past midnight seconds: s Answer a Time that is the given number of seconds past midnight  File: gst-base.info, Node: Time-accessing (ANSI for DateAndTimes), Next: Time-accessing (non ANSI & for Durations), Prev: Time class-instance creation, Up: Time 1.199.6 Time: accessing (ANSI for DateAndTimes) ----------------------------------------------- hour Answer the number of hours in the receiver hour12 Answer the hour in a 12-hour clock hour24 Answer the hour in a 24-hour clock minute Answer the number of minutes in the receiver second Answer the number of seconds in the receiver  File: gst-base.info, Node: Time-accessing (non ANSI & for Durations), Next: Time-arithmetic, Prev: Time-accessing (ANSI for DateAndTimes), Up: Time 1.199.7 Time: accessing (non ANSI & for Durations) -------------------------------------------------- asMilliseconds Not commented. asNanoseconds Not commented. asSeconds Answer `seconds'. hours Answer the number of hours in the receiver minutes Answer the number of minutes in the receiver seconds Answer the number of seconds in the receiver  File: gst-base.info, Node: Time-arithmetic, Next: Time-comparing, Prev: Time-accessing (non ANSI & for Durations), Up: Time 1.199.8 Time: arithmetic ------------------------ addSeconds: timeAmount Answer a new Time that is timeAmount seconds after the receiver addTime: timeAmount Answer a new Time that is timeAmount seconds after the receiver; timeAmount is a Time. printOn: aStream Print a representation of the receiver on aStream subtractTime: timeAmount Answer a new Time that is timeAmount seconds before the receiver; timeAmount is a Time.  File: gst-base.info, Node: Time-comparing, Prev: Time-arithmetic, Up: Time 1.199.9 Time: comparing ----------------------- < aTime Answer whether the receiver is less than aTime = aTime Answer whether the receiver is equal to aTime hash Answer an hash value for the receiver  File: gst-base.info, Node: True, Next: UndefinedObject, Prev: Time, Up: Base classes 1.200 True ========== Defined in namespace Smalltalk Superclass: Boolean Category: Language-Data types I represent truth and justice in the world. My motto is "semper veritatis". * Menu: * True-basic:: (instance) * True-C hacks:: (instance) * True-printing:: (instance)  File: gst-base.info, Node: True-basic, Next: True-C hacks, Up: True 1.200.1 True: basic ------------------- & aBoolean We are true - anded with anything, we always answer the other operand and: aBlock We are true - anded with anything, we always answer the other operand, so evaluate aBlock eqv: aBoolean Answer whether the receiver and aBoolean represent the same boolean value ifFalse: falseBlock We are true - answer nil ifFalse: falseBlock ifTrue: trueBlock We are true - evaluate trueBlock ifTrue: trueBlock We are true - evaluate trueBlock ifTrue: trueBlock ifFalse: falseBlock We are true - evaluate trueBlock not We are true - answer false or: aBlock We are true - ored with anything, we always answer true xor: aBoolean Answer whether the receiver and aBoolean represent different boolean values | aBoolean We are true - ored with anything, we always answer true  File: gst-base.info, Node: True-C hacks, Next: True-printing, Prev: True-basic, Up: True 1.200.2 True: C hacks --------------------- asCBooleanValue Answer `1'.  File: gst-base.info, Node: True-printing, Prev: True-C hacks, Up: True 1.200.3 True: printing ---------------------- printOn: aStream Print a representation of the receiver on aStream  File: gst-base.info, Node: UndefinedObject, Next: UnicodeCharacter, Prev: True, Up: Base classes 1.201 UndefinedObject ===================== Defined in namespace Smalltalk Superclass: Object Category: Language-Implementation I have the questionable distinction of being a class with only one instance, which is the object "nil". * Menu: * UndefinedObject-basic:: (instance) * UndefinedObject-class creation - alternative:: (instance) * UndefinedObject-class polymorphism:: (instance) * UndefinedObject-CObject interoperability:: (instance) * UndefinedObject-dependents access:: (instance) * UndefinedObject-iteration:: (instance) * UndefinedObject-printing:: (instance) * UndefinedObject-still unclassified:: (instance) * UndefinedObject-storing:: (instance) * UndefinedObject-testing:: (instance)  File: gst-base.info, Node: UndefinedObject-basic, Next: UndefinedObject-class creation - alternative, Up: UndefinedObject 1.201.1 UndefinedObject: basic ------------------------------ copy Answer the receiver. deepCopy Answer the receiver. shallowCopy Answer the receiver.  File: gst-base.info, Node: UndefinedObject-class creation - alternative, Next: UndefinedObject-class polymorphism, Prev: UndefinedObject-basic, Up: UndefinedObject 1.201.2 UndefinedObject: class creation - alternative ----------------------------------------------------- subclass: classNameString classInstanceVariableNames: stringClassInstVarNames instanceVariableNames: stringInstVarNames classVariableNames: stringOfClassVarNames poolDictionaries: stringOfPoolNames Don't use this, it is only present to file in from IBM Smalltalk subclass: classNameString instanceVariableNames: stringInstVarNames classVariableNames: stringOfClassVarNames poolDictionaries: stringOfPoolNames Don't use this, it is only present to file in from IBM Smalltalk variableByteSubclass: classNameString classInstanceVariableNames: stringClassInstVarNames instanceVariableNames: stringInstVarNames classVariableNames: stringOfClassVarNames poolDictionaries: stringOfPoolNames Don't use this, it is only present to file in from IBM Smalltalk variableByteSubclass: classNameString instanceVariableNames: stringInstVarNames classVariableNames: stringOfClassVarNames poolDictionaries: stringOfPoolNames Don't use this, it is only present to file in from IBM Smalltalk variableLongSubclass: classNameString classInstanceVariableNames: stringClassInstVarNames instanceVariableNames: stringInstVarNames classVariableNames: stringOfClassVarNames poolDictionaries: stringOfPoolNames Don't use this, it is only present to file in from IBM Smalltalk variableLongSubclass: classNameString instanceVariableNames: stringInstVarNames classVariableNames: stringOfClassVarNames poolDictionaries: stringOfPoolNames Don't use this, it is only present to file in from IBM Smalltalk variableSubclass: classNameString classInstanceVariableNames: stringClassInstVarNames instanceVariableNames: stringInstVarNames classVariableNames: stringOfClassVarNames poolDictionaries: stringOfPoolNames Don't use this, it is only present to file in from IBM Smalltalk variableSubclass: classNameString instanceVariableNames: stringInstVarNames classVariableNames: stringOfClassVarNames poolDictionaries: stringOfPoolNames Don't use this, it is only present to file in from IBM Smalltalk  File: gst-base.info, Node: UndefinedObject-class polymorphism, Next: UndefinedObject-CObject interoperability, Prev: UndefinedObject-class creation - alternative, Up: UndefinedObject 1.201.3 UndefinedObject: class polymorphism ------------------------------------------- allSubclasses Return all the classes in the system. instSize Answer `0'. metaclassFor: classNameString Create a Metaclass object for the given class name. The metaclass is a subclass of Class methodDictionary Answer `nil'. removeSubclass: aClass Ignored - necessary to support disjoint class hierarchies subclass: classNameString Define a subclass of the receiver with the given name. If the class is already defined, don't modify its instance or class variables but still, if necessary, recompile everything needed. subclass: classNameString instanceVariableNames: stringInstVarNames classVariableNames: stringOfClassVarNames poolDictionaries: stringOfPoolNames category: categoryNameString Define a fixed subclass of the receiver with the given name, instance variables, class variables, pool dictionaries and category. If the class is already defined, if necessary, recompile everything needed. variable: shape subclass: classNameString instanceVariableNames: stringInstVarNames classVariableNames: stringOfClassVarNames poolDictionaries: stringOfPoolNames category: categoryNameString Define a variable subclass of the receiver with the given name, shape, instance variables, class variables, pool dictionaries and category. If the class is already defined, if necessary, recompile everything needed. The shape can be one of #byte #int8 #character #short #ushort #int #uint #int64 #uint64 #utf32 #float #double or #pointer. variableByteSubclass: classNameString instanceVariableNames: stringInstVarNames classVariableNames: stringOfClassVarNames poolDictionaries: stringOfPoolNames category: categoryNameString Define a byte variable subclass of the receiver with the given name, instance variables, class variables, pool dictionaries and category. If the class is already defined, if necessary, recompile everything needed. variableSubclass: classNameString instanceVariableNames: stringInstVarNames classVariableNames: stringOfClassVarNames poolDictionaries: stringOfPoolNames category: categoryNameString Define a variable pointer subclass of the receiver with the given name, instance variables, class variables, pool dictionaries and category. If the class is already defined, if necessary, recompile everything needed. variableWordSubclass: classNameString instanceVariableNames: stringInstVarNames classVariableNames: stringOfClassVarNames poolDictionaries: stringOfPoolNames category: categoryNameString Define a word variable subclass of the receiver with the given name, instance variables, class variables, pool dictionaries and category. If the class is already defined, if necessary, recompile everything needed.  File: gst-base.info, Node: UndefinedObject-CObject interoperability, Next: UndefinedObject-dependents access, Prev: UndefinedObject-class polymorphism, Up: UndefinedObject 1.201.4 UndefinedObject: CObject interoperability ------------------------------------------------- free Do nothing, a NULL pointer can be safely freed. narrow Return the receiver: a NULL pointer is always nil, whatever its type.  File: gst-base.info, Node: UndefinedObject-dependents access, Next: UndefinedObject-iteration, Prev: UndefinedObject-CObject interoperability, Up: UndefinedObject 1.201.5 UndefinedObject: dependents access ------------------------------------------ addDependent: ignored Fail, nil does not support dependents. release Ignore this call, nil does not support dependents.  File: gst-base.info, Node: UndefinedObject-iteration, Next: UndefinedObject-printing, Prev: UndefinedObject-dependents access, Up: UndefinedObject 1.201.6 UndefinedObject: iteration ---------------------------------- ifNil: nilBlock ifNotNilDo: iterableBlock Evaluate nilBlock if the receiver is nil, else evaluate iterableBlock with each element of the receiver (which should be an Iterable). ifNotNilDo: iterableBlock Evaluate iterableBlock with each element of the receiver (which should be an Iterable) if not nil. Else answer nil ifNotNilDo: iterableBlock ifNil: nilBlock Evaluate nilBlock if the receiver is nil, else evaluate iterableBlock, passing each element of the receiver (which should be an Iterable).  File: gst-base.info, Node: UndefinedObject-printing, Next: UndefinedObject-still unclassified, Prev: UndefinedObject-iteration, Up: UndefinedObject 1.201.7 UndefinedObject: printing --------------------------------- printOn: aStream Print a representation of the receiver on aStream. printOn: aStream in: aNamespace Print on aStream a representation of the receiver as it would be accessed from aNamespace: nil is the same everywhere, so print the same as #printOn:  File: gst-base.info, Node: UndefinedObject-still unclassified, Next: UndefinedObject-storing, Prev: UndefinedObject-printing, Up: UndefinedObject 1.201.8 UndefinedObject: still unclassified ------------------------------------------- inheritsFrom: aClass Always return false, as nil inherits from nothing.  File: gst-base.info, Node: UndefinedObject-storing, Next: UndefinedObject-testing, Prev: UndefinedObject-still unclassified, Up: UndefinedObject 1.201.9 UndefinedObject: storing -------------------------------- isLiteralObject Answer whether the receiver is expressible as a Smalltalk literal. storeLiteralOn: aStream Store on aStream some Smalltalk code which compiles to the receiver storeOn: aStream Store Smalltalk code compiling to the receiver on aStream.  File: gst-base.info, Node: UndefinedObject-testing, Prev: UndefinedObject-storing, Up: UndefinedObject 1.201.10 UndefinedObject: testing --------------------------------- ifNil: nilBlock Evaluate nilBlock if the receiver is nil, else answer nil ifNil: nilBlock ifNotNil: notNilBlock Evaluate nilBlock if the receiver is nil, else evaluate notNilBlock, passing the receiver. ifNotNil: notNilBlock Evaluate notNilBlock if the receiver is not nil, passing the receiver. Else answer nil ifNotNil: notNilBlock ifNil: nilBlock Evaluate nilBlock if the receiver is nil, else evaluate notNilBlock, passing the receiver. isNil Answer whether the receiver is the undefined object nil. Always answer true. isNull Answer whether the receiver represents a NULL C pointer. Always answer true. notNil Answer whether the receiver is not the undefined object nil. Always answer false.  File: gst-base.info, Node: UnicodeCharacter, Next: UnicodeString, Prev: UndefinedObject, Up: Base classes 1.202 UnicodeCharacter ====================== Defined in namespace Smalltalk Superclass: Character Category: Language-Data types My instances represent the over one million characters of the Unicode character set. It provides messages to translate between integers and character objects. UnicodeCharacter objects are created when accessing UnicodeStrings, or with Character class>>#codePoint:. * Menu: * UnicodeCharacter class-built ins:: (class) * UnicodeCharacter-coercion methods:: (instance)  File: gst-base.info, Node: UnicodeCharacter class-built ins, Next: UnicodeCharacter-coercion methods, Up: UnicodeCharacter 1.202.1 UnicodeCharacter class: built ins ----------------------------------------- value: anInteger Returns the character object, possibly a Character, corresponding to anInteger. Error if anInteger is not an integer, or not in 0..16r10FFFF. This is only a primitive for speed. UnicodeCharacter's #value: method is equivalent to #codePoint: (which is the same for Character and UnicodeCharacter).  File: gst-base.info, Node: UnicodeCharacter-coercion methods, Prev: UnicodeCharacter class-built ins, Up: UnicodeCharacter 1.202.2 UnicodeCharacter: coercion methods ------------------------------------------ * aNumber Returns a String with aNumber occurrences of the receiver.  File: gst-base.info, Node: UnicodeString, Next: ValueAdaptor, Prev: UnicodeCharacter, Up: Base classes 1.203 UnicodeString =================== Defined in namespace Smalltalk Superclass: CharacterArray Category: Collections-Text My instances represent Unicode string data types. Data is stored as 4-byte UTF-32 characters * Menu: * UnicodeString class-converting:: (class) * UnicodeString class-multibyte encodings:: (class) * UnicodeString-built ins:: (instance) * UnicodeString-built-ins:: (instance) * UnicodeString-converting:: (instance) * UnicodeString-multibyte encodings:: (instance)  File: gst-base.info, Node: UnicodeString class-converting, Next: UnicodeString class-multibyte encodings, Up: UnicodeString 1.203.1 UnicodeString class: converting --------------------------------------- fromString: aString Return the String, aString, converted to its Unicode representation. Unless the I18N package is loaded, this is not implemented.  File: gst-base.info, Node: UnicodeString class-multibyte encodings, Next: UnicodeString-built ins, Prev: UnicodeString class-converting, Up: UnicodeString 1.203.2 UnicodeString class: multibyte encodings ------------------------------------------------ defaultEncoding Answer the encoding used by the receiver. Conventionally, we answer 'Unicode' to ensure that two UnicodeStrings always have the same encoding. isUnicode Answer true; the receiver stores characters.  File: gst-base.info, Node: UnicodeString-built ins, Next: UnicodeString-built-ins, Prev: UnicodeString class-multibyte encodings, Up: UnicodeString 1.203.3 UnicodeString: built ins -------------------------------- at: anIndex ifAbsent: aBlock Answer the index-th indexed instance variable of the receiver  File: gst-base.info, Node: UnicodeString-built-ins, Next: UnicodeString-converting, Prev: UnicodeString-built ins, Up: UnicodeString 1.203.4 UnicodeString: built-ins -------------------------------- hash Answer an hash value for the receiver  File: gst-base.info, Node: UnicodeString-converting, Next: UnicodeString-multibyte encodings, Prev: UnicodeString-built-ins, Up: UnicodeString 1.203.5 UnicodeString: converting --------------------------------- asString Returns the string corresponding to the receiver. Without the Iconv package, unrecognized Unicode characters become $? characters. When it is loaded, an appropriate single- or multi-byte encoding could be used. asSymbol Returns the symbol corresponding to the receiver asUnicodeString But I already am a UnicodeString! Really! displayOn: aStream Print a representation of the receiver on aStream printOn: aStream Print a representation of the receiver on aStream  File: gst-base.info, Node: UnicodeString-multibyte encodings, Prev: UnicodeString-converting, Up: UnicodeString 1.203.6 UnicodeString: multibyte encodings ------------------------------------------ encoding Answer the encoding used by the receiver. Conventionally, we answer 'Unicode' to ensure that two UnicodeStrings always have the same encoding. numberOfCharacters Answer the number of Unicode characters in the receiver. This is the same as #size for UnicodeString.  File: gst-base.info, Node: ValueAdaptor, Next: ValueHolder, Prev: UnicodeString, Up: Base classes 1.204 ValueAdaptor ================== Defined in namespace Smalltalk Superclass: Object Category: Language-Data types My subclasses are used to access data from different objects with a consistent protocol. However, I'm an abstract class. * Menu: * ValueAdaptor class-creating instances:: (class) * ValueAdaptor-accessing:: (instance) * ValueAdaptor-printing:: (instance)  File: gst-base.info, Node: ValueAdaptor class-creating instances, Next: ValueAdaptor-accessing, Up: ValueAdaptor 1.204.1 ValueAdaptor class: creating instances ---------------------------------------------- new We don't know enough of subclasses to have a shared implementation of new  File: gst-base.info, Node: ValueAdaptor-accessing, Next: ValueAdaptor-printing, Prev: ValueAdaptor class-creating instances, Up: ValueAdaptor 1.204.2 ValueAdaptor: accessing ------------------------------- value Retrive the value of the receiver. Must be implemented by ValueAdaptor's subclasses value: anObject Set the value of the receiver. Must be implemented by ValueAdaptor's subclasses  File: gst-base.info, Node: ValueAdaptor-printing, Prev: ValueAdaptor-accessing, Up: ValueAdaptor 1.204.3 ValueAdaptor: printing ------------------------------ printOn: aStream Print a representation of the receiver  File: gst-base.info, Node: ValueHolder, Next: VariableBinding, Prev: ValueAdaptor, Up: Base classes 1.205 ValueHolder ================= Defined in namespace Smalltalk Superclass: ValueAdaptor Category: Language-Data types I store my value in a variable. For example, you can use me to pass numbers by reference. Just instance me before calling a method and ask for my value after that method. There are a lot of other creative uses for my intances, though. * Menu: * ValueHolder class-creating instances:: (class) * ValueHolder-accessing:: (instance) * ValueHolder-initializing:: (instance)  File: gst-base.info, Node: ValueHolder class-creating instances, Next: ValueHolder-accessing, Up: ValueHolder 1.205.1 ValueHolder class: creating instances --------------------------------------------- new Create a ValueHolder whose starting value is nil null Answer the sole instance of NullValueHolder with: anObject Create a ValueHolder whose starting value is anObject  File: gst-base.info, Node: ValueHolder-accessing, Next: ValueHolder-initializing, Prev: ValueHolder class-creating instances, Up: ValueHolder 1.205.2 ValueHolder: accessing ------------------------------ value Get the value of the receiver. value: anObject Set the value of the receiver.  File: gst-base.info, Node: ValueHolder-initializing, Prev: ValueHolder-accessing, Up: ValueHolder 1.205.3 ValueHolder: initializing --------------------------------- initialize Private - set the initial value of the receiver  File: gst-base.info, Node: VariableBinding, Next: VersionableObjectProxy, Prev: ValueHolder, Up: Base classes 1.206 VariableBinding ===================== Defined in namespace Smalltalk Superclass: HomedAssociation Category: Language-Data types My instances represent a mapping between a key in a namespace and its value. I print different than a normal Association, and know about my parent namespace, otherwise my behavior is the same. * Menu: * VariableBinding-compiler:: (instance) * VariableBinding-printing:: (instance) * VariableBinding-saving and loading:: (instance) * VariableBinding-storing:: (instance) * VariableBinding-testing:: (instance)  File: gst-base.info, Node: VariableBinding-compiler, Next: VariableBinding-printing, Up: VariableBinding 1.206.1 VariableBinding: compiler --------------------------------- literalEquals: anObject Not commented. literalHash Not commented.  File: gst-base.info, Node: VariableBinding-printing, Next: VariableBinding-saving and loading, Prev: VariableBinding-compiler, Up: VariableBinding 1.206.2 VariableBinding: printing --------------------------------- path Print a dotted path that compiles to the receiver's value printOn: aStream Put on aStream a representation of the receiver  File: gst-base.info, Node: VariableBinding-saving and loading, Next: VariableBinding-storing, Prev: VariableBinding-printing, Up: VariableBinding 1.206.3 VariableBinding: saving and loading ------------------------------------------- binaryRepresentationObject This method is implemented to allow for a PluggableProxy to be used with VariableBindings. Answer a DirectedMessage which sends #at: to the environment that holds the receiver.  File: gst-base.info, Node: VariableBinding-storing, Next: VariableBinding-testing, Prev: VariableBinding-saving and loading, Up: VariableBinding 1.206.4 VariableBinding: storing -------------------------------- isLiteralObject Answer whether the receiver is expressible as a Smalltalk literal. storeLiteralOn: aStream Store on aStream some Smalltalk code which compiles to the receiver storeOn: aStream Put on aStream some Smalltalk code compiling to the receiver  File: gst-base.info, Node: VariableBinding-testing, Prev: VariableBinding-storing, Up: VariableBinding 1.206.5 VariableBinding: testing -------------------------------- isDefined Answer true if this VariableBinding lives outside the Undeclared dictionary  File: gst-base.info, Node: VersionableObjectProxy, Next: VFS.ArchiveFile, Prev: VariableBinding, Up: Base classes 1.207 VersionableObjectProxy ============================ Defined in namespace Smalltalk Superclass: NullProxy Category: Streams-Files I am a proxy that stores additional information to allow different versions of an object's representations to be handled by the program. VersionableObjectProxies are backwards compatible, that is you can support versioning even if you did not use a VersionableObjectProxy for that class when the object was originarily dumped. VersionableObjectProxy does not support classes that changed shape across different versions. See the method comments for more information. * Menu: * VersionableObjectProxy class-saving and restoring:: (class) * VersionableObjectProxy-saving and restoring:: (instance)  File: gst-base.info, Node: VersionableObjectProxy class-saving and restoring, Next: VersionableObjectProxy-saving and restoring, Up: VersionableObjectProxy 1.207.1 VersionableObjectProxy class: saving and restoring ---------------------------------------------------------- loadFrom: anObjectDumper Retrieve the object. If the version number doesn't match the #binaryRepresentationVersion answered by the class, call the class' #convertFromVersion:withFixedVariables:instanceVariables:for: method. The stored version number will be the first parameter to that method (or nil if the stored object did not employ a VersionableObjectProxy), the remaining parameters will be respectively the fixed instance variables, the indexed instance variables (or nil if the class is fixed), and the ObjectDumper itself. If no VersionableObjectProxy, the class is sent #nonVersionedInstSize to retrieve the number of fixed instance variables stored for the non-versioned object.  File: gst-base.info, Node: VersionableObjectProxy-saving and restoring, Prev: VersionableObjectProxy class-saving and restoring, Up: VersionableObjectProxy 1.207.2 VersionableObjectProxy: saving and restoring ---------------------------------------------------- dumpTo: anObjectDumper Save the object with extra versioning information.  File: gst-base.info, Node: VFS.ArchiveFile, Next: VFS.ArchiveMember, Prev: VersionableObjectProxy, Up: Base classes 1.208 VFS.ArchiveFile ===================== Defined in namespace Smalltalk.VFS Superclass: VFS.FileWrapper Category: Streams-Files ArchiveFile handles virtual filesystems that have a directory structure of their own. The directories and files in the archive are instances of ArchiveMember, but the functionality resides entirely in ArchiveFile because the members will still ask the archive to get directory information on them, to extract them to a real file, and so on. * Menu: * VFS.ArchiveFile-ArchiveMember protocol:: (instance) * VFS.ArchiveFile-directory operations:: (instance) * VFS.ArchiveFile-querying:: (instance) * VFS.ArchiveFile-still unclassified:: (instance) * VFS.ArchiveFile-TmpFileArchiveMember protocol:: (instance)  File: gst-base.info, Node: VFS.ArchiveFile-ArchiveMember protocol, Next: VFS.ArchiveFile-directory operations, Up: VFS.ArchiveFile 1.208.1 VFS.ArchiveFile: ArchiveMember protocol ----------------------------------------------- fillMember: anArchiveMember Extract the information on anArchiveMember. Answer false if it actually does not exist in the archive; otherwise, answer true after having told anArchiveMember about them by sending #size:stCtime:stMtime:stAtime:isDirectory: to it. member: anArchiveMember do: aBlock Evaluate aBlock once for each file in the directory represented by anArchiveMember, passing its name. member: anArchiveMember mode: bits Set the permission bits for the file in anArchiveMember. refresh Extract the directory listing from the archive removeMember: anArchiveMember Remove the member represented by anArchiveMember. updateMember: anArchiveMember Update the member represented by anArchiveMember by copying the file into which it was extracted back to the archive.  File: gst-base.info, Node: VFS.ArchiveFile-directory operations, Next: VFS.ArchiveFile-querying, Prev: VFS.ArchiveFile-ArchiveMember protocol, Up: VFS.ArchiveFile 1.208.2 VFS.ArchiveFile: directory operations --------------------------------------------- at: aName Answer a FilePath for a file named `aName' residing in the directory represented by the receiver. nameAt: aString Answer a FilePath for a file named `aName' residing in the directory represented by the receiver. namesDo: aBlock Evaluate aBlock once for each file in the directory represented by the receiver, passing its name. release Release the resources used by the receiver that don't survive when reloading a snapshot.  File: gst-base.info, Node: VFS.ArchiveFile-querying, Next: VFS.ArchiveFile-still unclassified, Prev: VFS.ArchiveFile-directory operations, Up: VFS.ArchiveFile 1.208.3 VFS.ArchiveFile: querying --------------------------------- isAccessible Answer whether a directory with the name contained in the receiver does exist and can be accessed isDirectory Answer true. The archive can always be considered as a directory.  File: gst-base.info, Node: VFS.ArchiveFile-still unclassified, Next: VFS.ArchiveFile-TmpFileArchiveMember protocol, Prev: VFS.ArchiveFile-querying, Up: VFS.ArchiveFile 1.208.4 VFS.ArchiveFile: still unclassified ------------------------------------------- displayOn: aStream Print a representation of the file identified by the receiver.  File: gst-base.info, Node: VFS.ArchiveFile-TmpFileArchiveMember protocol, Prev: VFS.ArchiveFile-still unclassified, Up: VFS.ArchiveFile 1.208.5 VFS.ArchiveFile: TmpFileArchiveMember protocol ------------------------------------------------------ extractMember: anArchiveMember Extract the contents of anArchiveMember into a file that resides on disk, and answer the name of the file. extractMember: anArchiveMember into: file Extract the contents of anArchiveMember into a file that resides on disk, and answer the name of the file.  File: gst-base.info, Node: VFS.ArchiveMember, Next: VFS.FileWrapper, Prev: VFS.ArchiveFile, Up: Base classes 1.209 VFS.ArchiveMember ======================= Defined in namespace Smalltalk.VFS Superclass: FilePath Category: Streams-Files TmpFileArchiveMember is a handler class for members of archive files that creates temporary files when extracting files from an archive. * Menu: * VFS.ArchiveMember-accessing:: (instance) * VFS.ArchiveMember-basic:: (instance) * VFS.ArchiveMember-delegation:: (instance) * VFS.ArchiveMember-directory operations:: (instance) * VFS.ArchiveMember-file operations:: (instance) * VFS.ArchiveMember-initializing:: (instance) * VFS.ArchiveMember-still unclassified:: (instance) * VFS.ArchiveMember-testing:: (instance)  File: gst-base.info, Node: VFS.ArchiveMember-accessing, Next: VFS.ArchiveMember-basic, Up: VFS.ArchiveMember 1.209.1 VFS.ArchiveMember: accessing ------------------------------------ archive Answer the archive of which the receiver is a member. asString Answer the name of the file identified by the receiver as answered by File>>#name. creationTime Answer the creation time of the file identified by the receiver. On some operating systems, this could actually be the last change time (the `last change time' has to do with permissions, ownership and the like). lastAccessTime Answer the last access time of the file identified by the receiver lastChangeTime Answer the last change time of the file identified by the receiver (the `last change time' has to do with permissions, ownership and the like). On some operating systems, this could actually be the file creation time. lastModifyTime Answer the last modify time of the file identified by the receiver (the `last modify time' has to do with the actual file contents). name Answer the receiver's file name. name: aName Set the receiver's file name to aName. refresh Refresh the statistics for the receiver size Answer the size of the file identified by the receiver  File: gst-base.info, Node: VFS.ArchiveMember-basic, Next: VFS.ArchiveMember-delegation, Prev: VFS.ArchiveMember-accessing, Up: VFS.ArchiveMember 1.209.2 VFS.ArchiveMember: basic -------------------------------- = aFile Answer whether the receiver represents the same file as the receiver. hash Answer a hash value for the receiver.  File: gst-base.info, Node: VFS.ArchiveMember-delegation, Next: VFS.ArchiveMember-directory operations, Prev: VFS.ArchiveMember-basic, Up: VFS.ArchiveMember 1.209.3 VFS.ArchiveMember: delegation ------------------------------------- full Answer the size of the file identified by the receiver  File: gst-base.info, Node: VFS.ArchiveMember-directory operations, Next: VFS.ArchiveMember-file operations, Prev: VFS.ArchiveMember-delegation, Up: VFS.ArchiveMember 1.209.4 VFS.ArchiveMember: directory operations ----------------------------------------------- at: aName Answer a FilePath for a file named `aName' residing in the directory represented by the receiver. createDirectory: dirName Create a subdirectory of the receiver, naming it dirName. namesDo: aBlock Evaluate aBlock once for each file in the directory represented by the receiver, passing its name.  File: gst-base.info, Node: VFS.ArchiveMember-file operations, Next: VFS.ArchiveMember-initializing, Prev: VFS.ArchiveMember-directory operations, Up: VFS.ArchiveMember 1.209.5 VFS.ArchiveMember: file operations ------------------------------------------ open: class mode: mode ifFail: aBlock Open the receiver in the given mode (as answered by FileStream's class constant methods) remove Remove the file with the given path name renameTo: newFileName Rename the file with the given path name oldFileName to newFileName update: aspect Private - Update the in-archive version of the file before closing.  File: gst-base.info, Node: VFS.ArchiveMember-initializing, Next: VFS.ArchiveMember-still unclassified, Prev: VFS.ArchiveMember-file operations, Up: VFS.ArchiveMember 1.209.6 VFS.ArchiveMember: initializing --------------------------------------- archive: anArchiveFile Set the archive of which the receiver is a member. fillFrom: data Called back by the receiver's archive when the ArchiveMember asks for file information. size: bytes stCtime: ctime stMtime: mtime stAtime: atime mode: modeBits Set the file information for the receiver. size: bytes stMtime: mtime mode: modeBits Set the file information for the receiver.  File: gst-base.info, Node: VFS.ArchiveMember-still unclassified, Next: VFS.ArchiveMember-testing, Prev: VFS.ArchiveMember-initializing, Up: VFS.ArchiveMember 1.209.7 VFS.ArchiveMember: still unclassified --------------------------------------------- , aName Answer an object of the same kind as the receiver, whose name is suffixed with aName. displayOn: aStream Print a representation of the file identified by the receiver. isAbsolute Answer whether the receiver identifies an absolute path.  File: gst-base.info, Node: VFS.ArchiveMember-testing, Prev: VFS.ArchiveMember-still unclassified, Up: VFS.ArchiveMember 1.209.8 VFS.ArchiveMember: testing ---------------------------------- exists Answer whether a file with the name contained in the receiver does exist. isAccessible Answer whether a directory with the name contained in the receiver does exist and is accessible isDirectory Answer whether a file with the name contained in the receiver does exist and identifies a directory. isExecutable Answer whether a file with the name contained in the receiver does exist and is executable isReadable Answer whether a file with the name contained in the receiver does exist and is readable isSymbolicLink Answer whether a file with the name contained in the receiver does exist and identifies a symbolic link. isWriteable Answer whether a file with the name contained in the receiver does exist and is writeable mode Answer the octal permissions for the file. mode: mode Set the octal permissions for the file to be `mode'.  File: gst-base.info, Node: VFS.FileWrapper, Next: VFS.StoredZipMember, Prev: VFS.ArchiveMember, Up: Base classes 1.210 VFS.FileWrapper ===================== Defined in namespace Smalltalk.VFS Superclass: FilePath Category: Streams-Files FileWrapper gives information for virtual files that refer to a real file on disk. * Menu: * VFS.FileWrapper class-initializing:: (class) * VFS.FileWrapper class-instance creation:: (class) * VFS.FileWrapper-accessing:: (instance) * VFS.FileWrapper-basic:: (instance) * VFS.FileWrapper-delegation:: (instance) * VFS.FileWrapper-enumerating:: (instance) * VFS.FileWrapper-file operations:: (instance) * VFS.FileWrapper-testing:: (instance)  File: gst-base.info, Node: VFS.FileWrapper class-initializing, Next: VFS.FileWrapper class-instance creation, Up: VFS.FileWrapper 1.210.1 VFS.FileWrapper class: initializing ------------------------------------------- initialize Register the receiver with ObjectMemory update: aspect Private - Remove the files before quitting, and register the virtual filesystems specified by the subclasses upon image load.  File: gst-base.info, Node: VFS.FileWrapper class-instance creation, Next: VFS.FileWrapper-accessing, Prev: VFS.FileWrapper class-initializing, Up: VFS.FileWrapper 1.210.2 VFS.FileWrapper class: instance creation ------------------------------------------------ on: file Create an instance of this class representing the contents of the given file, under the virtual filesystem fsName.  File: gst-base.info, Node: VFS.FileWrapper-accessing, Next: VFS.FileWrapper-basic, Prev: VFS.FileWrapper class-instance creation, Up: VFS.FileWrapper 1.210.3 VFS.FileWrapper: accessing ---------------------------------- asString Answer the string representation of the receiver's path. at: aName Answer a File or Directory object as appropriate for a file named 'aName' in the directory represented by the receiver. lastAccessTime: accessDateTime lastModifyTime: modifyDateTime Update the timestamps of the file corresponding to the receiver, to be accessDateTime and modifyDateTime. name Answer the full path to the receiver. owner: ownerString group: groupString Set the receiver's owner and group to be ownerString and groupString. pathTo: destName Compute the relative path from the receiver to destName.  File: gst-base.info, Node: VFS.FileWrapper-basic, Next: VFS.FileWrapper-delegation, Prev: VFS.FileWrapper-accessing, Up: VFS.FileWrapper 1.210.4 VFS.FileWrapper: basic ------------------------------ = aFile Answer whether the receiver represents the same file as the receiver. hash Answer a hash value for the receiver.  File: gst-base.info, Node: VFS.FileWrapper-delegation, Next: VFS.FileWrapper-enumerating, Prev: VFS.FileWrapper-basic, Up: VFS.FileWrapper 1.210.5 VFS.FileWrapper: delegation ----------------------------------- creationTime Answer the creation time of the file identified by the receiver. On some operating systems, this could actually be the last change time (the `last change time' has to do with permissions, ownership and the like). full Answer the size of the file identified by the receiver isExecutable Answer whether a file with the name contained in the receiver does exist and is executable isReadable Answer whether a file with the name contained in the receiver does exist and is readable isWriteable Answer whether a file with the name contained in the receiver does exist and is writeable lastAccessTime Answer the last access time of the file identified by the receiver lastChangeTime Answer the last change time of the file identified by the receiver (the `last change time' has to do with permissions, ownership and the like). On some operating systems, this could actually be the file creation time. lastModifyTime Answer the last modify time of the file identified by the receiver (the `last modify time' has to do with the actual file contents). mode Answer the permission bits for the file identified by the receiver mode: anInteger Answer the permission bits for the file identified by the receiver open: class mode: mode ifFail: aBlock Open the receiver in the given mode (as answered by FileStream's class constant methods) remove Remove the file with the given path name size Answer the size of the file identified by the receiver  File: gst-base.info, Node: VFS.FileWrapper-enumerating, Next: VFS.FileWrapper-file operations, Prev: VFS.FileWrapper-delegation, Up: VFS.FileWrapper 1.210.6 VFS.FileWrapper: enumerating ------------------------------------ namesDo: aBlock Evaluate aBlock once for each file in the directory represented by the receiver, passing its name.  File: gst-base.info, Node: VFS.FileWrapper-file operations, Next: VFS.FileWrapper-testing, Prev: VFS.FileWrapper-enumerating, Up: VFS.FileWrapper 1.210.7 VFS.FileWrapper: file operations ---------------------------------------- pathFrom: dirName Compute the relative path from the directory dirName to the receiver renameTo: newName Rename the file identified by the receiver to newName symlinkAs: destName Create destName as a symbolic link of the receiver. The appropriate relative path is computed automatically. symlinkFrom: srcName Create the receiver as a symbolic link from srcName (relative to the path of the receiver).  File: gst-base.info, Node: VFS.FileWrapper-testing, Prev: VFS.FileWrapper-file operations, Up: VFS.FileWrapper 1.210.8 VFS.FileWrapper: testing -------------------------------- exists Answer whether a file with the name contained in the receiver does exist. isAbsolute Answer whether the receiver identifies an absolute path. isAccessible Answer whether a directory with the name contained in the receiver does exist and can be accessed isDirectory Answer whether a file with the name contained in the receiver does exist identifies a directory. isSymbolicLink Answer whether a file with the name contained in the receiver does exist and identifies a symbolic link.  File: gst-base.info, Node: VFS.StoredZipMember, Next: VFS.TmpFileArchiveMember, Prev: VFS.FileWrapper, Up: Base classes 1.211 VFS.StoredZipMember ========================= Defined in namespace Smalltalk.VFS Superclass: VFS.TmpFileArchiveMember Category: Streams-Files ArchiveMember is the handler class for stored ZIP archive members, which are optimized. * Menu: * VFS.StoredZipMember-accessing:: (instance) * VFS.StoredZipMember-opening:: (instance)  File: gst-base.info, Node: VFS.StoredZipMember-accessing, Next: VFS.StoredZipMember-opening, Up: VFS.StoredZipMember 1.211.1 VFS.StoredZipMember: accessing -------------------------------------- offset Answer `offset'. offset: anInteger Not commented.  File: gst-base.info, Node: VFS.StoredZipMember-opening, Prev: VFS.StoredZipMember-accessing, Up: VFS.StoredZipMember 1.211.2 VFS.StoredZipMember: opening ------------------------------------ open: class mode: mode ifFail: aBlock Not commented.  File: gst-base.info, Node: VFS.TmpFileArchiveMember, Next: VFS.ZipFile, Prev: VFS.StoredZipMember, Up: Base classes 1.212 VFS.TmpFileArchiveMember ============================== Defined in namespace Smalltalk.VFS Superclass: VFS.ArchiveMember Category: Streams-Files * Menu: * VFS.TmpFileArchiveMember-directory operations:: (instance) * VFS.TmpFileArchiveMember-finalization:: (instance) * VFS.TmpFileArchiveMember-still unclassified:: (instance)  File: gst-base.info, Node: VFS.TmpFileArchiveMember-directory operations, Next: VFS.TmpFileArchiveMember-finalization, Up: VFS.TmpFileArchiveMember 1.212.1 VFS.TmpFileArchiveMember: directory operations ------------------------------------------------------ file Answer the real file name which holds the file contents, or nil if it does not apply. open: class mode: mode ifFail: aBlock Open the receiver in the given mode (as answered by FileStream's class constant methods)  File: gst-base.info, Node: VFS.TmpFileArchiveMember-finalization, Next: VFS.TmpFileArchiveMember-still unclassified, Prev: VFS.TmpFileArchiveMember-directory operations, Up: VFS.TmpFileArchiveMember 1.212.2 VFS.TmpFileArchiveMember: finalization ---------------------------------------------- release Release the resources used by the receiver that don't survive when reloading a snapshot.  File: gst-base.info, Node: VFS.TmpFileArchiveMember-still unclassified, Prev: VFS.TmpFileArchiveMember-finalization, Up: VFS.TmpFileArchiveMember 1.212.3 VFS.TmpFileArchiveMember: still unclassified ---------------------------------------------------- extracted Answer whether the file has already been extracted to disk.  File: gst-base.info, Node: VFS.ZipFile, Next: Warning, Prev: VFS.TmpFileArchiveMember, Up: Base classes 1.213 VFS.ZipFile ================= Defined in namespace Smalltalk.VFS Superclass: VFS.ArchiveFile Category: Streams-Files ZipFile transparently extracts files from a ZIP archive. * Menu: * VFS.ZipFile-members:: (instance)  File: gst-base.info, Node: VFS.ZipFile-members, Up: VFS.ZipFile 1.213.1 VFS.ZipFile: members ---------------------------- centralDirectoryRangeIn: f Not commented. createDirectory: dirName Create a subdirectory of the receiver, naming it dirName. extractMember: anArchiveMember into: temp Extract the contents of anArchiveMember into a file that resides on disk, and answer the name of the file. fileData Extract the directory listing from the archive member: anArchiveMember mode: bits Set the permission bits for the file in anArchiveMember. removeMember: anArchiveMember Remove the member represented by anArchiveMember. updateMember: anArchiveMember Update the member represented by anArchiveMember by copying the file into which it was extracted back to the archive.  File: gst-base.info, Node: Warning, Next: WeakArray, Prev: VFS.ZipFile, Up: Base classes 1.214 Warning ============= Defined in namespace Smalltalk Superclass: Notification Category: Language-Exceptions Warning represents an `important' but resumable error. * Menu: * Warning-exception description:: (instance)  File: gst-base.info, Node: Warning-exception description, Up: Warning 1.214.1 Warning: exception description -------------------------------------- description Answer a textual description of the exception.  File: gst-base.info, Node: WeakArray, Next: WeakIdentitySet, Prev: Warning, Up: Base classes 1.215 WeakArray =============== Defined in namespace Smalltalk Superclass: Array Category: Collections-Weak I am similar to a plain array, but my items are stored in a weak object, so I track which of them are garbage collected. * Menu: * WeakArray class-instance creation:: (class) * WeakArray-accessing:: (instance) * WeakArray-conversion:: (instance) * WeakArray-loading:: (instance)  File: gst-base.info, Node: WeakArray class-instance creation, Next: WeakArray-accessing, Up: WeakArray 1.215.1 WeakArray class: instance creation ------------------------------------------ new Create a new WeakArray of size 0. new: size Create a new WeakArray of the given size.  File: gst-base.info, Node: WeakArray-accessing, Next: WeakArray-conversion, Prev: WeakArray class-instance creation, Up: WeakArray 1.215.2 WeakArray: accessing ---------------------------- aliveObjectsDo: aBlock Evaluate aBlock for all the elements in the array, excluding the garbage collected ones. Note: a finalized object stays alive until the next collection (the collector has no means to see whether it was resuscitated by the finalizer), so an object being alive does not mean that it is usable. at: index Answer the index-th item of the receiver, or nil if it has been garbage collected. at: index put: object Store the value associated to the given index; plus, store in nilValues whether the object is nil. nil objects whose associated item of nilValues is 1 were touched by the garbage collector. atAll: indices put: object Put object at every index contained in the indices collection atAllPut: object Put object at every index in the receiver clearGCFlag: index Clear the `object has been garbage collected' flag for the item at the given index do: aBlock Evaluate aBlock for all the elements in the array, including the garbage collected ones (pass nil for those). isAlive: index Answer whether the item at the given index is still alive or has been garbage collected. Note: a finalized object stays alive until the next collection (the collector has no means to see whether it was resuscitated by the finalizer), so an object being alive does not mean that it is usable. size Answer the number of items in the receiver  File: gst-base.info, Node: WeakArray-conversion, Next: WeakArray-loading, Prev: WeakArray-accessing, Up: WeakArray 1.215.3 WeakArray: conversion ----------------------------- asArray Answer a non-weak version of the receiver deepCopy Returns a deep copy of the receiver (the instance variables are copies of the receiver's instance variables) shallowCopy Returns a shallow copy of the receiver (the instance variables are not copied) species Answer Array; this method is used in the #copyEmpty: message, which in turn is used by all collection-returning methods (collect:, select:, reject:, etc.).  File: gst-base.info, Node: WeakArray-loading, Prev: WeakArray-conversion, Up: WeakArray 1.215.4 WeakArray: loading -------------------------- postLoad Called after loading an object; must restore it to the state before `preStore' was called. Make it weak again  File: gst-base.info, Node: WeakIdentitySet, Next: WeakKeyDictionary, Prev: WeakArray, Up: Base classes 1.216 WeakIdentitySet ===================== Defined in namespace Smalltalk Superclass: WeakSet Category: Collections-Weak I am similar to a plain identity set, but my keys are stored in a weak array; I track which of them are garbage collected and, as soon as I encounter one of them, I swiftly remove all the garbage collected keys * Menu: * WeakIdentitySet-accessing:: (instance)  File: gst-base.info, Node: WeakIdentitySet-accessing, Up: WeakIdentitySet 1.216.1 WeakIdentitySet: accessing ---------------------------------- identityIncludes: anObject Answer whether I include anObject exactly. As I am an identity-set, this is the same as #includes:.  File: gst-base.info, Node: WeakKeyDictionary, Next: WeakKeyIdentityDictionary, Prev: WeakIdentitySet, Up: Base classes 1.217 WeakKeyDictionary ======================= Defined in namespace Smalltalk Superclass: Dictionary Category: Collections-Weak I am similar to a plain Dictionary, but my keys are stored in a weak array; I track which of them are garbage collected and, as soon as I encounter one of them, I swiftly remove all the associations for the garbage collected keys * Menu: * WeakKeyDictionary class-hacks:: (class) * WeakKeyDictionary-accessing:: (instance)  File: gst-base.info, Node: WeakKeyDictionary class-hacks, Next: WeakKeyDictionary-accessing, Up: WeakKeyDictionary 1.217.1 WeakKeyDictionary class: hacks -------------------------------------- postLoad Called after loading an object; must restore it to the state before `preStore' was called. Make it weak again  File: gst-base.info, Node: WeakKeyDictionary-accessing, Prev: WeakKeyDictionary class-hacks, Up: WeakKeyDictionary 1.217.2 WeakKeyDictionary: accessing ------------------------------------ add: anAssociation Store value as associated to the given key. at: key put: value Store value as associated to the given key.  File: gst-base.info, Node: WeakKeyIdentityDictionary, Next: WeakSet, Prev: WeakKeyDictionary, Up: Base classes 1.218 WeakKeyIdentityDictionary =============================== Defined in namespace Smalltalk Superclass: WeakKeyDictionary Category: Collections-Weak I am similar to a plain identity dictionary, but my keys are stored in a weak array; I track which of them are garbage collected and, as soon as I encounter one of them, I swiftly remove all the associations for the garbage collected keys * Menu:  File: gst-base.info, Node: WeakSet, Next: WeakValueIdentityDictionary, Prev: WeakKeyIdentityDictionary, Up: Base classes 1.219 WeakSet ============= Defined in namespace Smalltalk Superclass: Set Category: Collections-Weak I am similar to a plain set, but my items are stored in a weak array; I track which of them are garbage collected and, as soon as I encounter one of them, I swiftly remove all. * Menu: * WeakSet-accessing:: (instance) * WeakSet-copying:: (instance) * WeakSet-loading:: (instance)  File: gst-base.info, Node: WeakSet-accessing, Next: WeakSet-copying, Up: WeakSet 1.219.1 WeakSet: accessing -------------------------- add: newObject Add newObject to the set, if and only if the set doesn't already contain an occurrence of it. Don't fail if a duplicate is found. Answer newObject do: aBlock Enumerate all the non-nil members of the set  File: gst-base.info, Node: WeakSet-copying, Next: WeakSet-loading, Prev: WeakSet-accessing, Up: WeakSet 1.219.2 WeakSet: copying ------------------------ deepCopy Returns a deep copy of the receiver (the instance variables are copies of the receiver's instance variables) shallowCopy Returns a shallow copy of the receiver (the instance variables are not copied)  File: gst-base.info, Node: WeakSet-loading, Prev: WeakSet-copying, Up: WeakSet 1.219.3 WeakSet: loading ------------------------ postLoad Called after loading an object; must restore it to the state before `preStore' was called. Make it weak again  File: gst-base.info, Node: WeakValueIdentityDictionary, Next: WeakValueLookupTable, Prev: WeakSet, Up: Base classes 1.220 WeakValueIdentityDictionary ================================= Defined in namespace Smalltalk Superclass: WeakValueLookupTable Category: Collections-Weak I am similar to a plain identity dictionary, but my values are stored in a weak array; I track which of the values are garbage collected and, as soon as one of them is accessed, I swiftly remove the associations for the garbage collected values * Menu:  File: gst-base.info, Node: WeakValueLookupTable, Next: WordArray, Prev: WeakValueIdentityDictionary, Up: Base classes 1.221 WeakValueLookupTable ========================== Defined in namespace Smalltalk Superclass: LookupTable Category: Collections-Weak I am similar to a plain LookupTable, but my values are stored in a weak array; I track which of the values are garbage collected and, as soon as one of them is accessed, I swiftly remove the associations for the garbage collected values * Menu: * WeakValueLookupTable class-hacks:: (class) * WeakValueLookupTable-hacks:: (instance) * WeakValueLookupTable-rehashing:: (instance)  File: gst-base.info, Node: WeakValueLookupTable class-hacks, Next: WeakValueLookupTable-hacks, Up: WeakValueLookupTable 1.221.1 WeakValueLookupTable class: hacks ----------------------------------------- primNew: realSize Answer a new, uninitialized instance of the receiver with the given size  File: gst-base.info, Node: WeakValueLookupTable-hacks, Next: WeakValueLookupTable-rehashing, Prev: WeakValueLookupTable class-hacks, Up: WeakValueLookupTable 1.221.2 WeakValueLookupTable: hacks ----------------------------------- at: key ifAbsent: aBlock Answer the value associated to the given key, or the result of evaluating aBlock if the key is not found at: key ifPresent: aBlock If aKey is absent, answer nil. Else, evaluate aBlock passing the associated value and answer the result of the invocation includesKey: key Answer whether the receiver contains the given key.  File: gst-base.info, Node: WeakValueLookupTable-rehashing, Prev: WeakValueLookupTable-hacks, Up: WeakValueLookupTable 1.221.3 WeakValueLookupTable: rehashing --------------------------------------- rehash Rehash the receiver  File: gst-base.info, Node: WordArray, Next: WriteStream, Prev: WeakValueLookupTable, Up: Base classes 1.222 WordArray =============== Defined in namespace Smalltalk Superclass: ArrayedCollection Category: Collections-Sequenceable I am similar to a plain array, but my items are 32-bit integers. * Menu: * WordArray-built ins:: (instance)  File: gst-base.info, Node: WordArray-built ins, Up: WordArray 1.222.1 WordArray: built ins ---------------------------- at: anIndex ifAbsent: aBlock Answer the index-th indexed instance variable of the receiver  File: gst-base.info, Node: WriteStream, Next: ZeroDivide, Prev: WordArray, Up: Base classes 1.223 WriteStream ================= Defined in namespace Smalltalk Superclass: PositionableStream Category: Streams-Collections I am the class of writeable streams. I only allow write operations to my instances; reading is strictly forbidden. * Menu: * WriteStream class-instance creation:: (class) * WriteStream-accessing-writing:: (instance) * WriteStream-positioning:: (instance)  File: gst-base.info, Node: WriteStream class-instance creation, Next: WriteStream-accessing-writing, Up: WriteStream 1.223.1 WriteStream class: instance creation -------------------------------------------- on: aCollection Answer a new instance of the receiver which streams on aCollection. Every item of aCollection is discarded. with: aCollection Answer a new instance of the receiver which streams from the end of aCollection. with: aCollection from: firstIndex to: lastIndex Answer a new instance of the receiver which streams from the firstIndex-th item of aCollection to the lastIndex-th. The pointer is moved to the last item in that range.  File: gst-base.info, Node: WriteStream-accessing-writing, Next: WriteStream-positioning, Prev: WriteStream class-instance creation, Up: WriteStream 1.223.2 WriteStream: accessing-writing -------------------------------------- contents Returns a collection of the same type that the stream accesses, up to and including the final element. next: n putAll: aCollection startingAt: pos Put n characters or bytes of aCollection, starting at the pos-th, in the collection buffer. nextPut: anObject Store anObject as the next item in the receiver. Grow the collection if necessary readStream Answer a ReadStream on the same contents as the receiver reverseContents Returns a collection of the same type that the stream accesses, up to and including the final element, but in reverse order.  File: gst-base.info, Node: WriteStream-positioning, Prev: WriteStream-accessing-writing, Up: WriteStream 1.223.3 WriteStream: positioning -------------------------------- emptyStream Extension - Reset the stream  File: gst-base.info, Node: ZeroDivide, Prev: WriteStream, Up: Base classes 1.224 ZeroDivide ================ Defined in namespace Smalltalk Superclass: ArithmeticError Category: Language-Exceptions A ZeroDivide exception is raised by numeric classes when a program tries to divide by zero. Information on the dividend is available to the handler. * Menu: * ZeroDivide class-instance creation:: (class) * ZeroDivide-accessing:: (instance) * ZeroDivide-description:: (instance)  File: gst-base.info, Node: ZeroDivide class-instance creation, Next: ZeroDivide-accessing, Up: ZeroDivide 1.224.1 ZeroDivide class: instance creation ------------------------------------------- dividend: aNumber Create a new ZeroDivide object remembering that the dividend was aNumber. new Create a new ZeroDivide object; the dividend is conventionally set to zero.  File: gst-base.info, Node: ZeroDivide-accessing, Next: ZeroDivide-description, Prev: ZeroDivide class-instance creation, Up: ZeroDivide 1.224.2 ZeroDivide: accessing ----------------------------- dividend Answer the number that was being divided by zero  File: gst-base.info, Node: ZeroDivide-description, Prev: ZeroDivide-accessing, Up: ZeroDivide 1.224.3 ZeroDivide: description ------------------------------- description Answer a textual description of the exception.  File: gst-base.info, Node: Class index, Next: Method index, Prev: Base classes, Up: Top Class index *********** [index] * Menu: * AbstractNamespace: AbstractNamespace. (line 6) * AlternativeObjectProxy: AlternativeObjectProxy. (line 6) * ArithmeticError: ArithmeticError. (line 6) * Array: Array. (line 6) * ArrayedCollection: ArrayedCollection. (line 6) * Association: Association. (line 6) * Autoload: Autoload. (line 6) * Bag: Bag. (line 6) * Behavior: Behavior. (line 6) * BindingDictionary: BindingDictionary. (line 6) * BlockClosure: BlockClosure. (line 6) * BlockContext: BlockContext. (line 6) * Boolean: Boolean. (line 6) * ByteArray: ByteArray. (line 6) * CAggregate: CAggregate. (line 6) * CallinProcess: CallinProcess. (line 6) * CArray: CArray. (line 6) * CArrayCType: CArrayCType. (line 6) * CBoolean: CBoolean. (line 6) * CByte: CByte. (line 6) * CCallable: CCallable. (line 6) * CCallbackDescriptor: CCallbackDescriptor. (line 6) * CChar: CChar. (line 6) * CCompound: CCompound. (line 6) * CDouble: CDouble. (line 6) * CFloat: CFloat. (line 6) * CFunctionDescriptor: CFunctionDescriptor. (line 6) * Character: Character. (line 6) * CharacterArray: CharacterArray. (line 6) * CInt: CInt. (line 6) * Class: Class. (line 6) * ClassDescription: ClassDescription. (line 6) * CLong: CLong. (line 6) * CLongDouble: CLongDouble. (line 6) * CLongLong: CLongLong. (line 6) * CObject: CObject. (line 6) * Collection: Collection. (line 6) * CompiledBlock: CompiledBlock. (line 6) * CompiledCode: CompiledCode. (line 6) * CompiledMethod: CompiledMethod. (line 6) * ContextPart: ContextPart. (line 6) * Continuation: Continuation. (line 6) * CPtr: CPtr. (line 6) * CPtrCType: CPtrCType. (line 6) * CScalar: CScalar. (line 6) * CScalarCType: CScalarCType. (line 6) * CShort: CShort. (line 6) * CSmalltalk: CSmalltalk. (line 6) * CString: CString. (line 6) * CStringCType: CStringCType. (line 6) * CStruct: CStruct. (line 6) * CType: CType. (line 6) * CUChar: CUChar. (line 6) * CUInt: CUInt. (line 6) * CULong: CULong. (line 6) * CULongLong: CULongLong. (line 6) * CUnion: CUnion. (line 6) * CUShort: CUShort. (line 6) * Date: Date. (line 6) * DateTime: DateTime. (line 6) * DeferredVariableBinding: DeferredVariableBinding. (line 6) * Delay: Delay. (line 6) * DelayedAdaptor: DelayedAdaptor. (line 6) * Dictionary: Dictionary. (line 6) * DirectedMessage: DirectedMessage. (line 6) * Directory: Directory. (line 6) * DLD: DLD. (line 6) * DumperProxy: DumperProxy. (line 6) * Duration: Duration. (line 6) * DynamicVariable: DynamicVariable. (line 6) * Error: Error. (line 6) * Exception: Exception. (line 6) * ExceptionSet: ExceptionSet. (line 6) * False: False. (line 6) * File: File. (line 6) * FileDescriptor: FileDescriptor. (line 6) * FilePath: FilePath. (line 6) * FileSegment: FileSegment. (line 6) * FileStream: FileStream. (line 6) * Float: Float. (line 6) * FloatD: FloatD. (line 6) * FloatE: FloatE. (line 6) * FloatQ: FloatQ. (line 6) * Fraction: Fraction. (line 6) * Generator: Generator. (line 6) * Getopt: Getopt. (line 6) * Halt: Halt. (line 6) * HashedCollection: HashedCollection. (line 6) * HomedAssociation: HomedAssociation. (line 6) * IdentityDictionary: IdentityDictionary. (line 6) * IdentitySet: IdentitySet. (line 6) * Integer: Integer. (line 6) * Interval: Interval. (line 6) * Iterable: Iterable. (line 6) * LargeArray: LargeArray. (line 6) * LargeArrayedCollection: LargeArrayedCollection. (line 6) * LargeByteArray: LargeByteArray. (line 6) * LargeInteger: LargeInteger. (line 6) * LargeNegativeInteger: LargeNegativeInteger. (line 6) * LargePositiveInteger: LargePositiveInteger. (line 6) * LargeWordArray: LargeWordArray. (line 6) * LargeZeroInteger: LargeZeroInteger. (line 6) * Link: Link. (line 6) * LinkedList: LinkedList. (line 6) * LookupKey: LookupKey. (line 6) * LookupTable: LookupTable. (line 6) * Magnitude: Magnitude. (line 6) * MappedCollection: MappedCollection. (line 6) * Memory: Memory. (line 6) * Message: Message. (line 6) * MessageNotUnderstood: MessageNotUnderstood. (line 6) * Metaclass: Metaclass. (line 6) * MethodContext: MethodContext. (line 6) * MethodDictionary: MethodDictionary. (line 6) * MethodInfo: MethodInfo. (line 6) * Namespace: Namespace. (line 6) * NetClients.URIResolver: NetClients.URIResolver. (line 6) * NetClients.URL: NetClients.URL. (line 6) * Notification: Notification. (line 6) * NullProxy: NullProxy. (line 6) * NullValueHolder: NullValueHolder. (line 6) * Number: Number. (line 6) * Object: Object. (line 6) * ObjectDumper: ObjectDumper. (line 6) * ObjectMemory: ObjectMemory. (line 6) * OrderedCollection: OrderedCollection. (line 6) * Package: Package. (line 6) * PackageLoader: PackageLoader. (line 6) * Permission: Permission. (line 6) * PluggableAdaptor: PluggableAdaptor. (line 6) * PluggableProxy: PluggableProxy. (line 6) * Point: Point. (line 6) * PositionableStream: PositionableStream. (line 6) * Process: Process. (line 6) * ProcessEnvironment: ProcessEnvironment. (line 6) * ProcessorScheduler: ProcessorScheduler. (line 6) * ProcessVariable: ProcessVariable. (line 6) * Promise: Promise. (line 6) * Random: Random. (line 6) * ReadStream: ReadStream. (line 6) * ReadWriteStream: ReadWriteStream. (line 6) * Rectangle: Rectangle. (line 6) * RecursionLock: RecursionLock. (line 6) * Regex: Regex. (line 6) * RegexResults: RegexResults. (line 6) * RootNamespace: RootNamespace. (line 6) * RunArray: RunArray. (line 6) * ScaledDecimal: ScaledDecimal. (line 6) * SecurityPolicy: SecurityPolicy. (line 6) * Semaphore: Semaphore. (line 6) * SequenceableCollection: SequenceableCollection. (line 6) * Set: Set. (line 6) * SharedQueue: SharedQueue. (line 6) * SingletonProxy: SingletonProxy. (line 6) * SmallInteger: SmallInteger. (line 6) * SortedCollection: SortedCollection. (line 6) * Stream: Stream. (line 6) * String: String. (line 6) * Symbol: Symbol. (line 6) * SymLink: SymLink. (line 6) * SystemDictionary: SystemDictionary. (line 6) * SystemExceptions.AlreadyDefined: SystemExceptions.AlreadyDefined. (line 6) * SystemExceptions.ArgumentOutOfRange: SystemExceptions.ArgumentOutOfRange. (line 6) * SystemExceptions.BadReturn: SystemExceptions.BadReturn. (line 6) * SystemExceptions.CInterfaceError: SystemExceptions.CInterfaceError. (line 6) * SystemExceptions.EmptyCollection: SystemExceptions.EmptyCollection. (line 6) * SystemExceptions.EndOfStream: SystemExceptions.EndOfStream. (line 6) * SystemExceptions.FileError: SystemExceptions.FileError. (line 6) * SystemExceptions.IndexOutOfRange: SystemExceptions.IndexOutOfRange. (line 6) * SystemExceptions.InvalidArgument: SystemExceptions.InvalidArgument. (line 6) * SystemExceptions.InvalidProcessState: SystemExceptions.InvalidProcessState. (line 6) * SystemExceptions.InvalidSize: SystemExceptions.InvalidSize. (line 6) * SystemExceptions.InvalidState: SystemExceptions.InvalidState. (line 6) * SystemExceptions.InvalidValue: SystemExceptions.InvalidValue. (line 6) * SystemExceptions.MustBeBoolean: SystemExceptions.MustBeBoolean. (line 6) * SystemExceptions.MutationError: SystemExceptions.MutationError. (line 6) * SystemExceptions.NoRunnableProcess: SystemExceptions.NoRunnableProcess. (line 6) * SystemExceptions.NotEnoughElements: SystemExceptions.NotEnoughElements. (line 6) * SystemExceptions.NotFound: SystemExceptions.NotFound. (line 6) * SystemExceptions.NotImplemented: SystemExceptions.NotImplemented. (line 6) * SystemExceptions.NotIndexable: SystemExceptions.NotIndexable. (line 6) * SystemExceptions.NotYetImplemented: SystemExceptions.NotYetImplemented. (line 6) * SystemExceptions.PackageNotAvailable: SystemExceptions.PackageNotAvailable. (line 6) * SystemExceptions.PrimitiveFailed: SystemExceptions.PrimitiveFailed. (line 6) * SystemExceptions.ProcessBeingTerminated: SystemExceptions.ProcessBeingTerminated. (line 6) * SystemExceptions.ProcessTerminated: SystemExceptions.ProcessTerminated. (line 6) * SystemExceptions.ReadOnlyObject: SystemExceptions.ReadOnlyObject. (line 6) * SystemExceptions.SecurityError: SystemExceptions.SecurityError. (line 6) * SystemExceptions.ShouldNotImplement: SystemExceptions.ShouldNotImplement. (line 6) * SystemExceptions.SubclassResponsibility: SystemExceptions.SubclassResponsibility. (line 6) * SystemExceptions.UnhandledException: SystemExceptions.UnhandledException. (line 6) * SystemExceptions.UserInterrupt: SystemExceptions.UserInterrupt. (line 6) * SystemExceptions.VerificationError: SystemExceptions.VerificationError. (line 6) * SystemExceptions.VMError: SystemExceptions.VMError. (line 6) * SystemExceptions.WrongArgumentCount: SystemExceptions.WrongArgumentCount. (line 6) * SystemExceptions.WrongClass: SystemExceptions.WrongClass. (line 6) * SystemExceptions.WrongMessageSent: SystemExceptions.WrongMessageSent. (line 6) * TextCollector: TextCollector. (line 6) * Time: Time. (line 6) * True: True. (line 6) * UndefinedObject: UndefinedObject. (line 6) * UnicodeCharacter: UnicodeCharacter. (line 6) * UnicodeString: UnicodeString. (line 6) * ValueAdaptor: ValueAdaptor. (line 6) * ValueHolder: ValueHolder. (line 6) * VariableBinding: VariableBinding. (line 6) * VersionableObjectProxy: VersionableObjectProxy. (line 6) * VFS.ArchiveFile: VFS.ArchiveFile. (line 6) * VFS.ArchiveMember: VFS.ArchiveMember. (line 6) * VFS.FileWrapper: VFS.FileWrapper. (line 6) * VFS.StoredZipMember: VFS.StoredZipMember. (line 6) * VFS.TmpFileArchiveMember: VFS.TmpFileArchiveMember. (line 6) * VFS.ZipFile: VFS.ZipFile. (line 6) * Warning: Warning. (line 6) * WeakArray: WeakArray. (line 6) * WeakIdentitySet: WeakIdentitySet. (line 6) * WeakKeyDictionary: WeakKeyDictionary. (line 6) * WeakKeyIdentityDictionary: WeakKeyIdentityDictionary. (line 6) * WeakSet: WeakSet. (line 6) * WeakValueIdentityDictionary: WeakValueIdentityDictionary. (line 6) * WeakValueLookupTable: WeakValueLookupTable. (line 6) * WordArray: WordArray. (line 6) * WriteStream: WriteStream. (line 6) * ZeroDivide: ZeroDivide. (line 6) smalltalk-3.2.5/doc/gst-sunit.10000644000175000017500000000204512130455702013212 00000000000000.\" DO NOT MODIFY THIS FILE! It was generated by help2man 1.28. .TH GST-SUNIT "1" "April 2013" "gst-sunit version 3.2.5-4dc033e" "User Commands" .SH NAME gst-sunit \- unit testing tool for GNU Smalltalk .SH DESCRIPTION .SS "Usage:" .IP gst-sunit [ flag ... ] class.tests ... .SH OPTIONS .TP \fB\-q\fR \fB\-\-quiet\fR hide the output .TP \fB\-v\fR \fB\-\-verbose\fR show passed tests .TP \fB\-f\fR \fB\-\-file\fR=\fIFILE\fR load file before running subsequent tests .TP \fB\-p\fR \fB\-\-package\fR=\fIPACKAGE\fR load package and run its tests .TP \fB\-I\fR \fB\-\-image\-file\fR=\fIFILE\fR run tests on the specified image file .TP \fB\-\-kernel\-dir\fR=\fIPATH\fR use the specified kernel directory .TP \fB\-h\fR \fB\-\-help\fR show this message and exit .TP \fB\-\-version\fR print version information and exit .SH "SEE ALSO" The full documentation for .B gst-sunit is maintained as a Texinfo manual. If the .B info and .B gst-sunit programs are properly installed at your site, the command .IP .B info gst .PP should give you access to the complete manual. smalltalk-3.2.5/doc/complex.texi0000644000175000017500000001524212130455700013536 00000000000000@c Define the class index, method index, and selector cross-reference @ifclear CLASS-INDICES @set CLASS-INDICES @defindex cl @defcodeindex me @defcodeindex sl @end ifclear @c These are used for both TeX and HTML @set BEFORE1 @set AFTER1 @set BEFORE2 @set AFTER2 @ifinfo @c Use asis so that leading and trailing spaces are meaningful. @c Remember we're inside a @menu command, hence the blanks are @c kept in the output. @set BEFORE1 @asis{* } @set AFTER1 @asis{::} @set BEFORE2 @asis{ (} @set AFTER2 @asis{)} @end ifinfo @macro class {a,b} @value{BEFORE1}\a\\a\@b{\b\}@value{AFTER1} @end macro @macro superclass {a,b} \a\\a\@value{BEFORE2}@i{\b\}@value{AFTER2} @end macro @ifnotinfo @macro begindetailmenu @display @end macro @macro enddetailmenu @end display @end macro @end ifnotinfo @ifinfo @macro begindetailmenu @detailmenu @end macro @macro enddetailmenu @end detailmenu @end macro @end ifinfo @iftex @macro beginmenu @end macro @macro endmenu @end macro @end iftex @ifnottex @macro beginmenu @menu @end macro @macro endmenu @end menu @end macro @end ifnottex @beginmenu @ifnottex Alphabetic list: * Complex:: @end ifnottex @ifinfo Class tree: @end ifinfo @iftex @section Tree @end iftex @ifnotinfo Classes documented in this manual are @b{boldfaced}. @end ifnotinfo @begindetailmenu @superclass{@t{}, Object} @superclass{@t{ }, Magnitude} @superclass{@t{ }, Number} @class{@t{ }, Complex} @enddetailmenu @endmenu @unmacro class @unmacro superclass @unmacro endmenu @unmacro beginmenu @unmacro enddetailmenu @unmacro begindetailmenu @node Complex @section Complex @clindex Complex @table @b @item Defined in namespace Smalltalk @itemx Superclass: Number @itemx Category: Examples-Useful I provide complex numbers, with full interoperability with other kinds of numbers. Complex numbers can be created from imaginary numbers, which in turn are created with `Complex i' or the #i method (e.g. `3 i'). Alternatively, they can be created from polar numbers. @end table @menu * Complex class-instance creation:: (class) * Complex-comparing:: (instance) * Complex-converting:: (instance) * Complex-creation/coercion:: (instance) * Complex-math:: (instance) * Complex-printing:: (instance) * Complex-testing:: (instance) * Complex-transcendental functions:: (instance) @end menu @node Complex class-instance creation @subsection Complex class:@- instance creation @table @b @meindex i @item i Return the imaginary unit, -1 sqrt. @meindex initialize @item initialize Initialize some common complex numbers. @meindex new @item new This method should not be called for instances of this class. @meindex real:@-imaginary:@- @item real:@- re imaginary:@- im Return a complex number with the given real and imaginary parts. @meindex realResult:@-imaginary:@- @item realResult:@- re imaginary:@- im Private - Return a new complex number knowing that re and im have the same generality. @meindex rho:@-theta:@- @item rho:@- dist theta:@- angle Return a complex number whose absolute value is dist and whose argument is angle. @end table @node Complex-comparing @subsection Complex:@- comparing @table @b @meindex < @item < aNumber Not commented. @meindex <= @item <= aNumber Not commented. @meindex = @item = aNumber Not commented. @meindex > @item > aNumber Not commented. @meindex >= @item >= aNumber Not commented. @meindex hash @item hash Not commented. @meindex ~= @item ~= aNumber Not commented. @end table @node Complex-converting @subsection Complex:@- converting @table @b @meindex asExactFraction @item asExactFraction Not commented. @meindex asFloat @item asFloat Not commented. @meindex asFloatD @item asFloatD Not commented. @meindex asFloatE @item asFloatE Not commented. @meindex asFloatQ @item asFloatQ Not commented. @meindex asFraction @item asFraction Not commented. @meindex ceiling @item ceiling Not commented. @meindex floor @item floor Not commented. @meindex rounded @item rounded Not commented. @meindex truncated @item truncated Not commented. @end table @node Complex-creation/coercion @subsection Complex:@- creation/coercion @table @b @meindex coerce:@- @item coerce:@- aNumber Not commented. @meindex generality @item generality Not commented. @meindex i @item i Return the receiver multiplied by the imaginary unit. @meindex imaginary @item imaginary Answer `im'. @meindex isComplex @item isComplex Answer `true'. @meindex one @item one Answer `One'. @meindex real @item real Answer `re'. @meindex setReal:@-imaginary:@- @item setReal:@- real imaginary:@- imag Not commented. @meindex zero @item zero Answer `Zero'. @end table @node Complex-math @subsection Complex:@- math @table @b @meindex * @item * z Multiply the receiver by the (real or complex) number z. @meindex + @item + z Sum the receiver with the (real or complex) number z. @meindex - @item - z Subtract the (real or complex) number z from the receiver. @meindex / @item / z Divide the receiver by the (real or complex) number z. @meindex abs @item abs Return the absolute value of the receiver. @meindex absSquared @item absSquared Return the squared absolute value of the receiver. @meindex conjugate @item conjugate Return the complex conjugate of the receiver. @meindex reciprocal @item reciprocal Return the reciprocal of the receiver. @end table @node Complex-printing @subsection Complex:@- printing @table @b @meindex printOn:@- @item printOn:@- aStream Not commented. @meindex storeOn:@- @item storeOn:@- aStream Not commented. @end table @node Complex-testing @subsection Complex:@- testing @table @b @meindex isExact @item isExact Answer whether the receiver performs exact arithmetic. Complex numbers do so as long as both parts, real and imaginary, are exact. @end table @node Complex-transcendental functions @subsection Complex:@- transcendental functions @table @b @meindex arcTan @item arcTan Return the arc-tangent of the receiver. @meindex arcTan:@- @item arcTan:@- aNumber Return the arc-tangent of aNumber divided by the receiver. @meindex arg @item arg Return the argument of the receiver. @meindex cos @item cos Return the cosine of the receiver. @meindex cosh @item cosh Return the hyperbolic cosine of the receiver. @meindex exp @item exp Return e raised to the receiver. @meindex ln @item ln Return the natural logarithm of the receiver. @meindex log @item log Return the base-10 logarithm of the receiver. @meindex sin @item sin Return the sine of the receiver. @meindex sinh @item sinh Return the hyperbolic sine of the receiver. @meindex sqrt @item sqrt Return the square root of the receiver. Can be improved! @meindex tan @item tan Return the tangent of the receiver. @meindex tanh @item tanh Return the hyperbolic tangent of the receiver. @end table smalltalk-3.2.5/doc/classes.texi0000644000175000017500000305135312130455674013544 00000000000000@c Define the class index, method index, and selector cross-reference @ifclear CLASS-INDICES @set CLASS-INDICES @defindex cl @defcodeindex me @defcodeindex sl @end ifclear @c These are used for both TeX and HTML @set BEFORE1 @set AFTER1 @set BEFORE2 @set AFTER2 @ifinfo @c Use asis so that leading and trailing spaces are meaningful. @c Remember we're inside a @menu command, hence the blanks are @c kept in the output. @set BEFORE1 @asis{* } @set AFTER1 @asis{::} @set BEFORE2 @asis{ (} @set AFTER2 @asis{)} @end ifinfo @macro class {a,b} @value{BEFORE1}\a\\a\@b{\b\}@value{AFTER1} @end macro @macro superclass {a,b} \a\\a\@value{BEFORE2}@i{\b\}@value{AFTER2} @end macro @ifnotinfo @macro begindetailmenu @display @end macro @macro enddetailmenu @end display @end macro @end ifnotinfo @ifinfo @macro begindetailmenu @detailmenu @end macro @macro enddetailmenu @end detailmenu @end macro @end ifinfo @iftex @macro beginmenu @end macro @macro endmenu @end macro @end iftex @ifnottex @macro beginmenu @menu @end macro @macro endmenu @end menu @end macro @end ifnottex @beginmenu @ifnottex Alphabetic list: * AbstractNamespace:: * AlternativeObjectProxy:: * ArithmeticError:: * Array:: * ArrayedCollection:: * Association:: * Autoload:: * Bag:: * Behavior:: * BindingDictionary:: * BlockClosure:: * BlockContext:: * Boolean:: * ByteArray:: * CAggregate:: * CallinProcess:: * CArray:: * CArrayCType:: * CBoolean:: * CByte:: * CCallable:: * CCallbackDescriptor:: * CChar:: * CCompound:: * CDouble:: * CFloat:: * CFunctionDescriptor:: * Character:: * CharacterArray:: * CInt:: * Class:: * ClassDescription:: * CLong:: * CLongDouble:: * CLongLong:: * CObject:: * Collection:: * CompiledBlock:: * CompiledCode:: * CompiledMethod:: * ContextPart:: * Continuation:: * CPtr:: * CPtrCType:: * CScalar:: * CScalarCType:: * CShort:: * CSmalltalk:: * CString:: * CStringCType:: * CStruct:: * CType:: * CUChar:: * CUInt:: * CULong:: * CULongLong:: * CUnion:: * CUShort:: * Date:: * DateTime:: * DeferredVariableBinding:: * Delay:: * DelayedAdaptor:: * Dictionary:: * DirectedMessage:: * Directory:: * DLD:: * DumperProxy:: * Duration:: * DynamicVariable:: * Error:: * Exception:: * ExceptionSet:: * False:: * File:: * FileDescriptor:: * FilePath:: * FileSegment:: * FileStream:: * Float:: * FloatD:: * FloatE:: * FloatQ:: * Fraction:: * Generator:: * Getopt:: * Halt:: * HashedCollection:: * HomedAssociation:: * IdentityDictionary:: * IdentitySet:: * Integer:: * Interval:: * Iterable:: * LargeArray:: * LargeArrayedCollection:: * LargeByteArray:: * LargeInteger:: * LargeNegativeInteger:: * LargePositiveInteger:: * LargeWordArray:: * LargeZeroInteger:: * Link:: * LinkedList:: * LookupKey:: * LookupTable:: * Magnitude:: * MappedCollection:: * Memory:: * Message:: * MessageNotUnderstood:: * Metaclass:: * MethodContext:: * MethodDictionary:: * MethodInfo:: * Namespace:: * NetClients.URIResolver:: * NetClients.URL:: * Notification:: * NullProxy:: * NullValueHolder:: * Number:: * Object:: * ObjectDumper:: * ObjectMemory:: * OrderedCollection:: * Package:: * PackageLoader:: * Permission:: * PluggableAdaptor:: * PluggableProxy:: * Point:: * PositionableStream:: * Process:: * ProcessEnvironment:: * ProcessorScheduler:: * ProcessVariable:: * Promise:: * Random:: * ReadStream:: * ReadWriteStream:: * Rectangle:: * RecursionLock:: * Regex:: * RegexResults:: * RootNamespace:: * RunArray:: * ScaledDecimal:: * SecurityPolicy:: * Semaphore:: * SequenceableCollection:: * Set:: * SharedQueue:: * SingletonProxy:: * SmallInteger:: * SortedCollection:: * Stream:: * String:: * Symbol:: * SymLink:: * SystemDictionary:: * SystemExceptions.AlreadyDefined:: * SystemExceptions.ArgumentOutOfRange:: * SystemExceptions.BadReturn:: * SystemExceptions.CInterfaceError:: * SystemExceptions.EmptyCollection:: * SystemExceptions.EndOfStream:: * SystemExceptions.FileError:: * SystemExceptions.IndexOutOfRange:: * SystemExceptions.InvalidArgument:: * SystemExceptions.InvalidProcessState:: * SystemExceptions.InvalidSize:: * SystemExceptions.InvalidState:: * SystemExceptions.InvalidValue:: * SystemExceptions.MustBeBoolean:: * SystemExceptions.MutationError:: * SystemExceptions.NoRunnableProcess:: * SystemExceptions.NotEnoughElements:: * SystemExceptions.NotFound:: * SystemExceptions.NotImplemented:: * SystemExceptions.NotIndexable:: * SystemExceptions.NotYetImplemented:: * SystemExceptions.PackageNotAvailable:: * SystemExceptions.PrimitiveFailed:: * SystemExceptions.ProcessBeingTerminated:: * SystemExceptions.ProcessTerminated:: * SystemExceptions.ReadOnlyObject:: * SystemExceptions.SecurityError:: * SystemExceptions.ShouldNotImplement:: * SystemExceptions.SubclassResponsibility:: * SystemExceptions.UnhandledException:: * SystemExceptions.UserInterrupt:: * SystemExceptions.VerificationError:: * SystemExceptions.VMError:: * SystemExceptions.WrongArgumentCount:: * SystemExceptions.WrongClass:: * SystemExceptions.WrongMessageSent:: * TextCollector:: * Time:: * True:: * UndefinedObject:: * UnicodeCharacter:: * UnicodeString:: * ValueAdaptor:: * ValueHolder:: * VariableBinding:: * VersionableObjectProxy:: * VFS.ArchiveFile:: * VFS.ArchiveMember:: * VFS.FileWrapper:: * VFS.StoredZipMember:: * VFS.TmpFileArchiveMember:: * VFS.ZipFile:: * Warning:: * WeakArray:: * WeakIdentitySet:: * WeakKeyDictionary:: * WeakKeyIdentityDictionary:: * WeakSet:: * WeakValueIdentityDictionary:: * WeakValueLookupTable:: * WordArray:: * WriteStream:: * ZeroDivide:: @end ifnottex @ifinfo Class tree: @end ifinfo @iftex @section Tree @end iftex @ifnotinfo Classes documented in this manual are @b{boldfaced}. @end ifnotinfo @begindetailmenu @class{@t{}, Autoload} @class{@t{}, Object} @class{@t{ }, Behavior} @class{@t{ }, ClassDescription} @class{@t{ }, Class} @class{@t{ }, Metaclass} @class{@t{ }, BlockClosure} @class{@t{ }, Boolean} @class{@t{ }, False} @class{@t{ }, True} @class{@t{ }, CObject} @class{@t{ }, CAggregate} @class{@t{ }, CArray} @class{@t{ }, CPtr} @class{@t{ }, CString} @class{@t{ }, CCallable} @class{@t{ }, CCallbackDescriptor} @class{@t{ }, CFunctionDescriptor} @class{@t{ }, CCompound} @class{@t{ }, CStruct} @class{@t{ }, CUnion} @class{@t{ }, CScalar} @class{@t{ }, CChar} @class{@t{ }, CDouble} @class{@t{ }, CFloat} @class{@t{ }, CInt} @class{@t{ }, CLong} @class{@t{ }, CLongDouble} @class{@t{ }, CLongLong} @class{@t{ }, CShort} @class{@t{ }, CSmalltalk} @class{@t{ }, CUChar} @class{@t{ }, CByte} @class{@t{ }, CBoolean} @class{@t{ }, CUInt} @class{@t{ }, CULong} @class{@t{ }, CULongLong} @class{@t{ }, CUShort} @class{@t{ }, ContextPart} @class{@t{ }, BlockContext} @class{@t{ }, MethodContext} @class{@t{ }, Continuation} @class{@t{ }, CType} @class{@t{ }, CPtrCType} @class{@t{ }, CArrayCType} @class{@t{ }, CScalarCType} @class{@t{ }, CStringCType} @class{@t{ }, Delay} @class{@t{ }, Directory} @class{@t{ }, DLD} @class{@t{ }, DumperProxy} @class{@t{ }, AlternativeObjectProxy} @class{@t{ }, NullProxy} @class{@t{ }, VersionableObjectProxy} @class{@t{ }, PluggableProxy} @class{@t{ }, SingletonProxy} @class{@t{ }, DynamicVariable} @class{@t{ }, Exception} @class{@t{ }, Error} @class{@t{ }, ArithmeticError} @class{@t{ }, ZeroDivide} @class{@t{ }, MessageNotUnderstood} @class{@t{ }, SystemExceptions.InvalidValue} @class{@t{ }, SystemExceptions.EmptyCollection} @class{@t{ }, SystemExceptions.InvalidArgument} @class{@t{ }, SystemExceptions.AlreadyDefined} @class{@t{ }, SystemExceptions.ArgumentOutOfRange} @class{@t{ }, SystemExceptions.IndexOutOfRange} @class{@t{ }, SystemExceptions.InvalidSize} @class{@t{ }, SystemExceptions.NotFound} @class{@t{ }, SystemExceptions.PackageNotAvailable} @class{@t{ }, SystemExceptions.InvalidProcessState} @class{@t{ }, SystemExceptions.InvalidState} @class{@t{ }, SystemExceptions.NotIndexable} @class{@t{ }, SystemExceptions.ProcessTerminated} @class{@t{ }, SystemExceptions.ReadOnlyObject} @class{@t{ }, SystemExceptions.WrongClass} @class{@t{ }, SystemExceptions.MustBeBoolean} @class{@t{ }, SystemExceptions.MutationError} @class{@t{ }, SystemExceptions.NotEnoughElements} @class{@t{ }, SystemExceptions.NotImplemented} @class{@t{ }, SystemExceptions.NotYetImplemented} @class{@t{ }, SystemExceptions.ShouldNotImplement} @class{@t{ }, SystemExceptions.SubclassResponsibility} @class{@t{ }, SystemExceptions.WrongMessageSent} @class{@t{ }, SystemExceptions.VMError} @class{@t{ }, SystemExceptions.BadReturn} @class{@t{ }, SystemExceptions.NoRunnableProcess} @class{@t{ }, SystemExceptions.PrimitiveFailed} @class{@t{ }, SystemExceptions.CInterfaceError} @class{@t{ }, SystemExceptions.FileError} @class{@t{ }, SystemExceptions.WrongArgumentCount} @class{@t{ }, SystemExceptions.SecurityError} @class{@t{ }, SystemExceptions.UserInterrupt} @class{@t{ }, SystemExceptions.VerificationError} @class{@t{ }, Halt} @class{@t{ }, Notification} @class{@t{ }, SystemExceptions.EndOfStream} @class{@t{ }, SystemExceptions.ProcessBeingTerminated} @class{@t{ }, Warning} @class{@t{ }, SystemExceptions.UnhandledException} @class{@t{ }, ExceptionSet} @class{@t{ }, FilePath} @class{@t{ }, File} @class{@t{ }, VFS.ArchiveMember} @class{@t{ }, VFS.TmpFileArchiveMember} @class{@t{ }, VFS.StoredZipMember} @class{@t{ }, VFS.FileWrapper} @class{@t{ }, VFS.ArchiveFile} @class{@t{ }, VFS.ZipFile} @class{@t{ }, FileSegment} @class{@t{ }, Getopt} @class{@t{ }, Iterable} @class{@t{ }, Collection} @class{@t{ }, Bag} @class{@t{ }, HashedCollection} @class{@t{ }, Dictionary} @class{@t{ }, BindingDictionary} @class{@t{ }, AbstractNamespace} @class{@t{ }, Namespace} @class{@t{ }, RootNamespace} @class{@t{ }, SystemDictionary} @class{@t{ }, LookupTable} @class{@t{ }, IdentityDictionary} @class{@t{ }, MethodDictionary} @class{@t{ }, WeakValueLookupTable} @class{@t{ }, WeakValueIdentityDictionary} @class{@t{ }, WeakKeyDictionary} @class{@t{ }, WeakKeyIdentityDictionary} @class{@t{ }, Set} @class{@t{ }, IdentitySet} @class{@t{ }, WeakSet} @class{@t{ }, WeakIdentitySet} @class{@t{ }, MappedCollection} @class{@t{ }, SequenceableCollection} @class{@t{ }, ArrayedCollection} @class{@t{ }, Array} @class{@t{ }, WeakArray} @class{@t{ }, ByteArray} @class{@t{ }, CharacterArray} @class{@t{ }, String} @class{@t{ }, Symbol} @class{@t{ }, UnicodeString} @class{@t{ }, CompiledCode} @class{@t{ }, CompiledBlock} @class{@t{ }, CompiledMethod} @class{@t{ }, Interval} @class{@t{ }, LargeArrayedCollection} @class{@t{ }, LargeArray} @class{@t{ }, LargeByteArray} @class{@t{ }, LargeWordArray} @class{@t{ }, WordArray} @class{@t{ }, LinkedList} @class{@t{ }, Semaphore} @class{@t{ }, OrderedCollection} @class{@t{ }, RunArray} @class{@t{ }, SortedCollection} @class{@t{ }, Stream} @class{@t{ }, FileDescriptor} @class{@t{ }, FileStream} @class{@t{ }, Generator} @class{@t{ }, ObjectDumper} @class{@t{ }, PositionableStream} @class{@t{ }, ReadStream} @class{@t{ }, WriteStream} @class{@t{ }, ReadWriteStream} @class{@t{ }, Random} @class{@t{ }, TextCollector} @superclass{@t{ }, Kernel.PackageInfo} @class{@t{ }, Package} @class{@t{ }, Link} @class{@t{ }, Process} @class{@t{ }, CallinProcess} @class{@t{ }, SymLink} @class{@t{ }, Magnitude} @class{@t{ }, Character} @class{@t{ }, UnicodeCharacter} @class{@t{ }, Date} @class{@t{ }, DateTime} @class{@t{ }, LookupKey} @class{@t{ }, Association} @class{@t{ }, HomedAssociation} @class{@t{ }, VariableBinding} @class{@t{ }, DeferredVariableBinding} @class{@t{ }, ProcessVariable} @class{@t{ }, Number} @class{@t{ }, Float} @class{@t{ }, FloatD} @class{@t{ }, FloatE} @class{@t{ }, FloatQ} @class{@t{ }, Fraction} @class{@t{ }, Integer} @class{@t{ }, LargeInteger} @class{@t{ }, LargeNegativeInteger} @class{@t{ }, LargePositiveInteger} @class{@t{ }, LargeZeroInteger} @class{@t{ }, SmallInteger} @class{@t{ }, ScaledDecimal} @class{@t{ }, Time} @class{@t{ }, Duration} @class{@t{ }, Memory} @class{@t{ }, Message} @class{@t{ }, DirectedMessage} @class{@t{ }, MethodInfo} @class{@t{ }, NetClients.URIResolver} @class{@t{ }, NetClients.URL} @class{@t{ }, ObjectMemory} @class{@t{ }, PackageLoader} @class{@t{ }, Permission} @class{@t{ }, Point} @class{@t{ }, ProcessEnvironment} @class{@t{ }, ProcessorScheduler} @class{@t{ }, Rectangle} @class{@t{ }, RecursionLock} @class{@t{ }, Regex} @class{@t{ }, RegexResults} @class{@t{ }, SecurityPolicy} @class{@t{ }, SharedQueue} @class{@t{ }, UndefinedObject} @class{@t{ }, ValueAdaptor} @class{@t{ }, NullValueHolder} @class{@t{ }, PluggableAdaptor} @class{@t{ }, DelayedAdaptor} @class{@t{ }, ValueHolder} @class{@t{ }, Promise} @enddetailmenu @endmenu @unmacro class @unmacro superclass @unmacro endmenu @unmacro beginmenu @unmacro enddetailmenu @unmacro begindetailmenu @node AbstractNamespace @section AbstractNamespace @clindex AbstractNamespace @table @b @item Defined in namespace Smalltalk @itemx Superclass: BindingDictionary @itemx Category: Language-Implementation I am a special form of dictionary. Classes hold on an instance of me; it is called their `environment'. @end table @menu * AbstractNamespace class-instance creation:: (class) * AbstractNamespace-accessing:: (instance) * AbstractNamespace-compiling:: (instance) * AbstractNamespace-copying:: (instance) * AbstractNamespace-namespace hierarchy:: (instance) * AbstractNamespace-overrides for superspaces:: (instance) * AbstractNamespace-printing:: (instance) * AbstractNamespace-testing:: (instance) @end menu @node AbstractNamespace class-instance creation @subsection AbstractNamespace class:@- instance creation @table @b @meindex new @slindex new @item new Disabled - use #new to create instances @meindex primNew:@-name:@- @item primNew:@- parent name:@- spaceName Private - Create a new namespace with the given name and parent, and add to the parent a key that references it. @end table @node AbstractNamespace-accessing @subsection AbstractNamespace:@- accessing @table @b @meindex allAssociations @item allAssociations Answer a Dictionary with all of the associations in the receiver and each of its superspaces (duplicate keys are associated to the associations that are deeper in the namespace hierarchy) @meindex allBehaviorsDo:@- @item allBehaviorsDo:@- aBlock Evaluate aBlock once for each class and metaclass in the namespace. @meindex allClassObjectsDo:@- @item allClassObjectsDo:@- aBlock Evaluate aBlock once for each class and metaclass in the namespace. @meindex allClassesDo:@- @item allClassesDo:@- aBlock Evaluate aBlock once for each class in the namespace. @meindex allMetaclassesDo:@- @item allMetaclassesDo:@- aBlock Evaluate aBlock once for each metaclass in the namespace. @meindex classAt:@- @item classAt:@- aKey Answer the value corrisponding to aKey if it is a class. Fail if either aKey is not found or it is associated to something different from a class. @meindex classAt:@-ifAbsent:@- @item classAt:@- aKey ifAbsent:@- aBlock Answer the value corrisponding to aKey if it is a class. Evaluate aBlock and answer its result if either aKey is not found or it is associated to something different from a class. @end table @node AbstractNamespace-compiling @subsection AbstractNamespace:@- compiling @table @b @meindex addSharedPool:@- @item addSharedPool:@- aDictionary Import the given bindings for classes compiled with me as environment. @meindex import:@- @item import:@- aDictionary Import the given bindings for classes compiled with me as environment. @meindex removeSharedPool:@- @item removeSharedPool:@- aDictionary Remove aDictionary from my list of direct pools. @meindex sharedPoolDictionaries @item sharedPoolDictionaries Answer the shared pools (not names) imported for my classes. @end table @node AbstractNamespace-copying @subsection AbstractNamespace:@- copying @table @b @meindex copyEmpty:@- @item copyEmpty:@- newSize Answer an empty copy of the receiver whose size is newSize @meindex whileCurrentDo:@- @item whileCurrentDo:@- aBlock Evaluate aBlock with the current namespace set to the receiver. Answer the result of the evaluation. @end table @node AbstractNamespace-namespace hierarchy @subsection AbstractNamespace:@- namespace hierarchy @table @b @meindex addSubspace:@- @item addSubspace:@- aSymbol Create a namespace named aSymbol, add it to the receiver's subspaces, and answer it. @meindex allSubassociationsDo:@- @item allSubassociationsDo:@- aBlock Invokes aBlock once for every association in each of the receiver's subspaces. @meindex allSubspaces @item allSubspaces Answer the direct and indirect subspaces of the receiver in a Set @meindex allSubspacesDo:@- @item allSubspacesDo:@- aBlock Invokes aBlock for all subspaces, both direct and indirect. @meindex allSuperspacesDo:@- @item allSuperspacesDo:@- aBlock Evaluate aBlock once for each of the receiver's superspaces @meindex includesClassNamed:@- @slindex includesKey:@- @slindex includesGlobalNamed:@- @item includesClassNamed:@- aString Answer whether the receiver or any of its superspaces include the given class -- note that this method (unlike #includesKey:@-) does not require aString to be interned and (unlike #includesGlobalNamed:@-) only returns true if the global is a class object. @meindex includesGlobalNamed:@- @slindex includesKey:@- @slindex includesClassNamed:@- @item includesGlobalNamed:@- aString Answer whether the receiver or any of its superspaces include the given key -- note that this method (unlike #includesKey:@-) does not require aString to be interned but (unlike #includesClassNamed:@-) returns true even if the global is not a class object. @meindex removeSubspace:@- @item removeSubspace:@- aSymbol Remove my subspace named aSymbol from the hierarchy. @meindex selectSubspaces:@- @item selectSubspaces:@- aBlock Return a Set of subspaces of the receiver satisfying aBlock. @meindex selectSuperspaces:@- @item selectSuperspaces:@- aBlock Return a Set of superspaces of the receiver satisfying aBlock. @meindex siblings @item siblings Answer all the other children of the same namespace as the receiver. @meindex siblingsDo:@- @item siblingsDo:@- aBlock Evaluate aBlock once for each of the other root namespaces, passing the namespace as a parameter. @meindex subspaces @item subspaces Answer the receiver's direct subspaces @meindex subspacesDo:@- @item subspacesDo:@- aBlock Invokes aBlock for all direct subspaces. @meindex superspace @item superspace Answer the receiver's superspace. @meindex superspace:@- @item superspace:@- aNamespace Set the superspace of the receiver to be 'aNamespace'. Also adds the receiver as a subspace of it. @meindex withAllSubspaces @item withAllSubspaces Answer a Set containing the receiver together with its direct and indirect subspaces @meindex withAllSubspacesDo:@- @item withAllSubspacesDo:@- aBlock Invokes aBlock for the receiver and all subclasses, both direct and indirect. @end table @node AbstractNamespace-overrides for superspaces @subsection AbstractNamespace:@- overrides for superspaces @table @b @meindex inheritedKeys @item inheritedKeys Answer a Set of all the keys in the receiver and its superspaces @meindex set:@-to:@- @item set:@- key to:@- newValue Assign newValue to the variable named as specified by `key'. This method won't define a new variable; instead if the key is not found it will search in superspaces and raising an error if the variable cannot be found in any of the superspaces. Answer newValue. @meindex set:@-to:@-ifAbsent:@- @item set:@- key to:@- newValue ifAbsent:@- aBlock Assign newValue to the variable named as specified by `key'. This method won't define a new variable; instead if the key is not found it will search in superspaces and evaluate aBlock if it is not found. Answer newValue. @meindex values @item values Answer a Bag containing the values of the receiver @end table @node AbstractNamespace-printing @subsection AbstractNamespace:@- printing @table @b @meindex name @item name Answer the receiver's name @meindex name:@- @item name:@- aSymbol Change the receiver's name to aSymbol @meindex nameIn:@- @item nameIn:@- aNamespace Answer Smalltalk code compiling to the receiver when the current namespace is aNamespace @meindex printOn:@- @item printOn:@- aStream Print a representation of the receiver @meindex storeOn:@- @item storeOn:@- aStream Store Smalltalk code compiling to the receiver @end table @node AbstractNamespace-testing @subsection AbstractNamespace:@- testing @table @b @meindex isNamespace @item isNamespace Answer `true'. @meindex isSmalltalk @item isSmalltalk Answer `false'. @end table @node AlternativeObjectProxy @section AlternativeObjectProxy @clindex AlternativeObjectProxy @table @b @item Defined in namespace Smalltalk @itemx Superclass: DumperProxy @itemx Category: Streams-Files I am a proxy that uses the same ObjectDumper to store an object which is not the object to be dumped, but from which the dumped object can be reconstructed. I am an abstract class, using me would result in infinite loops because by default I try to store the same object again and again. See the method comments for more information @end table @menu * AlternativeObjectProxy class-instance creation:: (class) * AlternativeObjectProxy-accessing:: (instance) @end menu @node AlternativeObjectProxy class-instance creation @subsection AlternativeObjectProxy class:@- instance creation @table @b @meindex acceptUsageForClass:@- @item acceptUsageForClass:@- aClass The receiver was asked to be used as a proxy for the class aClass. Answer whether the registration is fine. By default, answer true except if AlternativeObjectProxy itself is being used. @meindex on:@- @slindex on:@- @slindex dumpTo:@- @item on:@- anObject Answer a proxy to be used to save anObject. IMPORTANT:@- this method MUST be overridden so that the overridden version sends #on:@- to super passing an object that is NOT the same as anObject (alternatively, you can override #dumpTo:@-, which is what NullProxy does), because that would result in an infinite loop! This also means that AlternativeObjectProxy must never be used directly -- only as a superclass. @end table @node AlternativeObjectProxy-accessing @subsection AlternativeObjectProxy:@- accessing @table @b @meindex object @item object Reconstruct the object stored in the proxy and answer it. A subclass will usually override this @meindex object:@- @item object:@- theObject Set the object to be dumped to theObject. This should not be overridden. @meindex primObject @item primObject Reconstruct the object stored in the proxy and answer it. This method must not be overridden @end table @node ArithmeticError @section ArithmeticError @clindex ArithmeticError @table @b @item Defined in namespace Smalltalk @itemx Superclass: Error @itemx Category: Language-Exceptions An ArithmeticError exception is raised by numeric classes when a program tries to do something wrong, such as extracting the square root of a negative number. @end table @menu * ArithmeticError-description:: (instance) @end menu @node ArithmeticError-description @subsection ArithmeticError:@- description @table @b @meindex description @item description Answer a textual description of the exception. @meindex isResumable @item isResumable Answer true. Arithmetic exceptions are by default resumable. @end table @node Array @section Array @clindex Array @table @b @item Defined in namespace Smalltalk @itemx Superclass: ArrayedCollection @itemx Category: Collections-Sequenceable My instances are objects that have array-like properties:@- they are directly indexable by integers starting at 1, and they are fixed in size. I inherit object creation behavior messages such as #with:@-, as well as iteration and general access behavior from SequenceableCollection. @end table @menu * Array class-instance creation:: (class) * Array-built ins:: (instance) * Array-mutating objects:: (instance) * Array-printing:: (instance) * Array-testing:: (instance) @end menu @node Array class-instance creation @subsection Array class:@- instance creation @table @b @meindex from:@- @item from:@- anArray Answer anArray, which is expected to be an array specified with a brace-syntax expression per my inherited protocol. @end table @node Array-built ins @subsection Array:@- built ins @table @b @meindex at:@-ifAbsent:@- @item at:@- anIndex ifAbsent:@- aBlock Answer the index-th indexed instance variable of the receiver @meindex replaceFrom:@-to:@-with:@-startingAt:@- @item replaceFrom:@- start to:@- stop with:@- byteArray startingAt:@- replaceStart Replace the characters from start to stop with new characters whose ASCII codes are contained in byteArray, starting at the replaceStart location of byteArray @end table @node Array-mutating objects @subsection Array:@- mutating objects @table @b @meindex multiBecome:@- @item multiBecome:@- anArray Transform every object in the receiver in each corresponding object in anArray. anArray and the receiver must have the same size @end table @node Array-printing @subsection Array:@- printing @table @b @meindex isLiteralObject @item isLiteralObject Answer whether the receiver is expressible as a Smalltalk literal. @meindex printOn:@- @item printOn:@- aStream Print a representation for the receiver on aStream @meindex storeLiteralOn:@- @item storeLiteralOn:@- aStream Store a Smalltalk literal compiling to the receiver on aStream @meindex storeOn:@- @item storeOn:@- aStream Store Smalltalk code compiling to the receiver on aStream @end table @node Array-testing @subsection Array:@- testing @table @b @meindex isArray @item isArray Answer `true'. @end table @node ArrayedCollection @section ArrayedCollection @clindex ArrayedCollection @table @b @item Defined in namespace Smalltalk @itemx Superclass: SequenceableCollection @itemx Category: Collections-Sequenceable My instances are objects that are generally fixed size, and are accessed by an integer index. The ordering of my instance's elements is determined externally; I will not rearrange the order of the elements. @end table @menu * ArrayedCollection class-instance creation:: (class) * ArrayedCollection-basic:: (instance) * ArrayedCollection-built ins:: (instance) * ArrayedCollection-compiler:: (instance) * ArrayedCollection-copying Collections:: (instance) * ArrayedCollection-enumerating the elements of a collection:: (instance) * ArrayedCollection-sorting:: (instance) * ArrayedCollection-storing:: (instance) * ArrayedCollection-streams:: (instance) @end menu @node ArrayedCollection class-instance creation @subsection ArrayedCollection class:@- instance creation @table @b @meindex join:@- @item join:@- aCollection Where aCollection is a collection of SequenceableCollections, answer a new instance with all the elements therein, in order. @meindex join:@-separatedBy:@- @item join:@- aCollection separatedBy:@- sepCollection Where aCollection is a collection of SequenceableCollections, answer a new instance with all the elements therein, in order, each separated by an occurrence of sepCollection. @meindex new:@-withAll:@- @item new:@- size withAll:@- anObject Answer a collection with the given size, whose elements are all set to anObject @meindex streamContents:@- @item streamContents:@- aBlock Create a ReadWriteStream on an empty instance of the receiver; pass the stream to aBlock, then retrieve its contents and answer them. @meindex with:@- @item with:@- element1 Answer a collection whose only element is element1 @meindex with:@-with:@- @item with:@- element1 with:@- element2 Answer a collection whose only elements are the parameters in the order they were passed @meindex with:@-with:@-with:@- @item with:@- element1 with:@- element2 with:@- element3 Answer a collection whose only elements are the parameters in the order they were passed @meindex with:@-with:@-with:@-with:@- @item with:@- element1 with:@- element2 with:@- element3 with:@- element4 Answer a collection whose only elements are the parameters in the order they were passed @meindex with:@-with:@-with:@-with:@-with:@- @item with:@- element1 with:@- element2 with:@- element3 with:@- element4 with:@- element5 Answer a collection whose only elements are the parameters in the order they were passed @meindex withAll:@- @item withAll:@- aCollection Answer a collection whose elements are the same as those in aCollection @end table @node ArrayedCollection-basic @subsection ArrayedCollection:@- basic @table @b @meindex , @item , aSequenceableCollection Answer a new instance of an ArrayedCollection containing all the elements in the receiver, followed by all the elements in aSequenceableCollection @meindex add:@- @item add:@- value This method should not be called for instances of this class. @meindex atAll:@- @slindex collect:@- @item atAll:@- keyCollection Answer a collection of the same kind returned by #collect:@-, that only includes the values at the given indices. Fail if any of the values in keyCollection is out of bounds for the receiver. @meindex copyFrom:@-to:@- @item copyFrom:@- start to:@- stop Answer a new collection containing all the items in the receiver from the start-th and to the stop-th @meindex copyWith:@- @item copyWith:@- anElement Answer a new instance of an ArrayedCollection containing all the elements in the receiver, followed by the single item anElement @meindex copyWithout:@- @item copyWithout:@- oldElement Answer a copy of the receiver to which all occurrences of oldElement are removed @end table @node ArrayedCollection-built ins @subsection ArrayedCollection:@- built ins @table @b @meindex size @item size Answer the size of the receiver @end table @node ArrayedCollection-compiler @subsection ArrayedCollection:@- compiler @table @b @meindex literalEquals:@- @item literalEquals:@- anObject Not commented. @meindex literalHash @item literalHash Not commented. @end table @node ArrayedCollection-copying Collections @subsection ArrayedCollection:@- copying Collections @table @b @meindex copyReplaceAll:@-with:@- @item copyReplaceAll:@- oldSubCollection with:@- newSubCollection Answer a new collection in which all the sequences matching oldSubCollection are replaced with newSubCollection @meindex copyReplaceFrom:@-to:@-with:@- @item copyReplaceFrom:@- start to:@- stop with:@- replacementCollection Answer a new collection of the same class as the receiver that contains the same elements as the receiver, in the same order, except for elements from index `start' to index `stop'. If start < stop, these are replaced by the contents of the replacementCollection. Instead, If start = (stop + 1), like in `copyReplaceFrom:@- 4 to:@- 3 with:@- anArray', then every element of the receiver will be present in the answered copy; the operation will be an append if stop is equal to the size of the receiver or, if it is not, an insert before index `start'. @meindex copyReplaceFrom:@-to:@-withObject:@- @item copyReplaceFrom:@- start to:@- stop withObject:@- anObject Answer a new collection of the same class as the receiver that contains the same elements as the receiver, in the same order, except for elements from index `start' to index `stop'. If start < stop, these are replaced by stop-start+1 copies of anObject. Instead, If start = (stop + 1), then every element of the receiver will be present in the answered copy; the operation will be an append if stop is equal to the size of the receiver or, if it is not, an insert before index `start'. @meindex reverse @item reverse Answer the receivers' contents in reverse order @end table @node ArrayedCollection-enumerating the elements of a collection @subsection ArrayedCollection:@- enumerating the elements of a collection @table @b @meindex collect:@- @item collect:@- aBlock Answer a new instance of an ArrayedCollection containing all the results of evaluating aBlock passing each of the receiver's elements @meindex reject:@- @item reject:@- aBlock Answer a new instance of an ArrayedCollection containing all the elements in the receiver which, when passed to aBlock, answer false @meindex select:@- @item select:@- aBlock Answer a new instance of an ArrayedCollection containing all the elements in the receiver which, when passed to aBlock, answer true @meindex with:@-collect:@- @item with:@- aSequenceableCollection collect:@- aBlock Evaluate aBlock for each pair of elements took respectively from the receiver and from aSequenceableCollection; answer a collection of the same kind of the receiver, made with the block's return values. Fail if the receiver has not the same size as aSequenceableCollection. @end table @node ArrayedCollection-sorting @subsection ArrayedCollection:@- sorting @table @b @meindex sorted @slindex <= @item sorted Return a copy of the receiver sorted according to the default sort block, which uses #<= to compare items. @meindex sorted:@- @item sorted:@- sortBlock Return a copy of the receiver sorted according to the given sort block, which accepts pair of items and returns true if the first item is less than the second one. @end table @node ArrayedCollection-storing @subsection ArrayedCollection:@- storing @table @b @meindex storeOn:@- @item storeOn:@- aStream Store Smalltalk code compiling to the receiver on aStream @end table @node ArrayedCollection-streams @subsection ArrayedCollection:@- streams @table @b @meindex writeStream @item writeStream Answer a WriteStream streaming on the receiver @end table @node Association @section Association @clindex Association @table @b @item Defined in namespace Smalltalk @itemx Superclass: LookupKey @itemx Category: Language-Data types My instances represent a mapping between two objects. Typically, my "key" object is a symbol, but I don't require this. My "value" object has no conventions associated with it; it can be any object at all. @end table @menu * Association class-basic:: (class) * Association-accessing:: (instance) * Association-finalization:: (instance) * Association-printing:: (instance) * Association-storing:: (instance) * Association-testing:: (instance) @end menu @node Association class-basic @subsection Association class:@- basic @table @b @meindex key:@-value:@- @item key:@- aKey value:@- aValue Answer a new association with the given key and value @end table @node Association-accessing @subsection Association:@- accessing @table @b @meindex environment @item environment Answer nil. This is present to achieve polymorphism with instances of VariableBinding. @meindex environment:@- @item environment:@- aNamespace Do nothing. This is present to achieve polymorphism with instances of VariableBinding. @meindex key:@-value:@- @item key:@- aKey value:@- aValue Set the association's key to aKey, and its value to aValue @meindex value @item value Answer the association's value @meindex value:@- @item value:@- aValue Set the association's value to aValue @end table @node Association-finalization @subsection Association:@- finalization @table @b @meindex mourn @item mourn Finalize the receiver @end table @node Association-printing @subsection Association:@- printing @table @b @meindex printOn:@- @item printOn:@- aStream Put on aStream a representation of the receiver @end table @node Association-storing @subsection Association:@- storing @table @b @meindex storeOn:@- @item storeOn:@- aStream Put on aStream some Smalltalk code compiling to the receiver @end table @node Association-testing @subsection Association:@- testing @table @b @meindex = @slindex = @item = anAssociation Answer whether the association's key and value are the same as anAssociation's, or false if anAssociation is not an Association. As a special case, identical values are considered equal even if #= returns false (as is the case for NaN floating-point values). @meindex hash @item hash Answer an hash value for the receiver @end table @node Autoload @section Autoload @clindex Autoload @table @b @item Defined in namespace Smalltalk @itemx Superclass: none @itemx Category: Examples-Useful tools I am not a part of the normal Smalltalk kernel class system. I provide the ability to do late ("on-demand") loading of class definitions. Through me, you can define any class to be loaded when any message is sent to the class itself (such as to create an instance) or to its metaclass (such as #methodsFor:@- to extend it with class-side methods). @end table @menu * Autoload class-instance creation:: (class) * Autoload-accessing:: (instance) @end menu @node Autoload class-instance creation @subsection Autoload class:@- instance creation @table @b @meindex class:@-from:@- @item class:@- nameSymbol from:@- fileNameString Make Smalltalk automatically load the class named nameSymbol from fileNameString when needed @meindex class:@-in:@-from:@- @item class:@- nameSymbol in:@- aNamespace from:@- fileNameString Make Smalltalk automatically load the class named nameSymbol and residing in aNamespace from fileNameString when needed @meindex class:@-in:@-loader:@- @slindex autoload @item class:@- nameSymbol in:@- aNamespace loader:@- anObject Make Smalltalk automatically load the class named nameSymbol and residing in aNamespace. When the class is needed, anObject will be sent #autoload. By default, instances of FilePath and Package can be used. @meindex class:@-loader:@- @slindex autoload @item class:@- nameSymbol loader:@- anObject Make Smalltalk automatically load the class named nameSymbol. When the class is needed, anObject will be sent #autoload. By default, instances of FilePath and Package can be used. @end table @node Autoload-accessing @subsection Autoload:@- accessing @table @b @meindex class @item class We need it to access the metaclass instance, because that's what will load the file. @meindex doesNotUnderstand:@- @item doesNotUnderstand:@- aMessage Load the class and resend the message to it @end table @node Bag @section Bag @clindex Bag @table @b @item Defined in namespace Smalltalk @itemx Superclass: Collection @itemx Category: Collections-Unordered My instances are unordered collections of objects. You can think of me as a set with a memory; that is, if the same object is added to me twice, then I will report that that element has been stored twice. @end table @menu * Bag class-basic:: (class) * Bag-adding:: (instance) * Bag-enumerating the elements of a collection:: (instance) * Bag-extracting items:: (instance) * Bag-printing:: (instance) * Bag-removing:: (instance) * Bag-storing:: (instance) * Bag-testing collections:: (instance) @end menu @node Bag class-basic @subsection Bag class:@- basic @table @b @meindex new @item new Answer a new instance of the receiver @meindex new:@- @item new:@- size Answer a new instance of the receiver, with space for size distinct objects @end table @node Bag-adding @subsection Bag:@- adding @table @b @meindex add:@- @item add:@- newObject Add an occurrence of newObject to the receiver. Answer newObject. Fail if newObject is nil. @meindex add:@-withOccurrences:@- @item add:@- newObject withOccurrences:@- anInteger If anInteger > 0, add anInteger occurrences of newObject to the receiver. If anInteger < 0, remove them. Answer newObject. Fail if newObject is nil. @end table @node Bag-enumerating the elements of a collection @subsection Bag:@- enumerating the elements of a collection @table @b @meindex asSet @item asSet Answer a set with the elements of the receiver @meindex do:@- @item do:@- aBlock Evaluate the block for all members in the collection. @end table @node Bag-extracting items @subsection Bag:@- extracting items @table @b @meindex sortedByCount @item sortedByCount Answer a collection of counts with elements, sorted by decreasing count. @end table @node Bag-printing @subsection Bag:@- printing @table @b @meindex printOn:@- @item printOn:@- aStream Put on aStream a representation of the receiver @end table @node Bag-removing @subsection Bag:@- removing @table @b @meindex remove:@-ifAbsent:@- @item remove:@- oldObject ifAbsent:@- anExceptionBlock Remove oldObject from the collection and return it. If can't be found, answer instead the result of evaluationg anExceptionBlock @end table @node Bag-storing @subsection Bag:@- storing @table @b @meindex storeOn:@- @item storeOn:@- aStream Put on aStream some Smalltalk code compiling to the receiver @end table @node Bag-testing collections @subsection Bag:@- testing collections @table @b @meindex = @item = aBag Answer whether the receiver and aBag contain the same objects @meindex hash @item hash Answer an hash value for the receiver @meindex includes:@- @item includes:@- anObject Answer whether we include anObject @meindex occurrencesOf:@- @item occurrencesOf:@- anObject Answer the number of occurrences of anObject found in the receiver @meindex size @item size Answer the total number of objects found in the receiver @end table @node Behavior @section Behavior @clindex Behavior @table @b @item Defined in namespace Smalltalk @itemx Superclass: Object @itemx Category: Language-Implementation I am the parent class of all "class" type methods. My instances know about the subclass/superclass relationships between classes, contain the description that instances are created from, and hold the method dictionary that's associated with each class. I provide methods for compiling methods, modifying the class inheritance hierarchy, examining the method dictionary, and iterating over the class hierarchy. @end table @menu * Behavior-accessing class hierarchy:: (instance) * Behavior-accessing instances and variables:: (instance) * Behavior-accessing the method dictionary:: (instance) * Behavior-built ins:: (instance) * Behavior-builtin:: (instance) * Behavior-compilation:: (instance) * Behavior-compilation (alternative):: (instance) * Behavior-compiling:: (instance) * Behavior-compiling methods:: (instance) * Behavior-creating a class hierarchy:: (instance) * Behavior-enumerating:: (instance) * Behavior-evaluating:: (instance) * Behavior-instance creation:: (instance) * Behavior-instance variables:: (instance) * Behavior-method dictionary:: (instance) * Behavior-parsing class declarations:: (instance) * Behavior-pluggable behavior (not yet implemented):: (instance) * Behavior-printing hierarchy:: (instance) * Behavior-source code:: (instance) * Behavior-still unclassified:: (instance) * Behavior-support for lightweight classes:: (instance) * Behavior-testing functionality:: (instance) * Behavior-testing the class hierarchy:: (instance) * Behavior-testing the form of the instances:: (instance) * Behavior-testing the method dictionary:: (instance) @end menu @node Behavior-accessing class hierarchy @subsection Behavior:@- accessing class hierarchy @table @b @meindex allSubclasses @item allSubclasses Answer the direct and indirect subclasses of the receiver in a Set @meindex allSuperclasses @item allSuperclasses Answer all the receiver's superclasses in a collection @meindex subclasses @item subclasses Answer the direct subclasses of the receiver in a Set @meindex superclass @item superclass Answer the receiver's superclass (if any, otherwise answer nil) @meindex withAllSubclasses @item withAllSubclasses Answer a Set containing the receiver together with its direct and indirect subclasses @meindex withAllSuperclasses @item withAllSuperclasses Answer the receiver and all of its superclasses in a collection @end table @node Behavior-accessing instances and variables @subsection Behavior:@- accessing instances and variables @table @b @meindex allClassVarNames @item allClassVarNames Return all the class variables understood by the receiver @meindex allInstVarNames @item allInstVarNames Answer the names of every instance variables the receiver contained in the receiver's instances @meindex allInstances @item allInstances Returns a set of all instances of the receiver @meindex allSharedPoolDictionaries @item allSharedPoolDictionaries Return the shared pools defined by the class and any of its superclasses, in the correct search order. @meindex allSharedPools @item allSharedPools Return the names of the shared pools defined by the class and any of its superclasses, in the correct search order. @meindex classPool @item classPool Answer the class pool dictionary. Since Behavior does not support classes with class variables, we answer an empty one; adding variables to it results in an error. @meindex classVarNames @item classVarNames Answer all the class variables for instances of the receiver @meindex indexOfInstVar:@- @item indexOfInstVar:@- aString Answer the index of aString in the fixed instance variables of the instances of the receiver, or 0 if the variable is missing. @meindex indexOfInstVar:@-ifAbsent:@- @item indexOfInstVar:@- aString ifAbsent:@- aBlock Answer the index of aString in the fixed instance variables of the instances of the receiver, or 0 if the variable is missing. @meindex instVarNames @item instVarNames Answer an Array containing the instance variables defined by the receiver @meindex instanceCount @item instanceCount Return a count of all the instances of the receiver @meindex sharedPools @item sharedPools Return the names of the shared pools defined by the class @meindex subclassInstVarNames @item subclassInstVarNames Answer the names of the instance variables the receiver inherited from its superclass @end table @node Behavior-accessing the method dictionary @subsection Behavior:@- accessing the method dictionary @table @b @meindex >> @item >> selector Return the compiled method associated with selector, from the local method dictionary. Error if not found. @meindex allSelectors @item allSelectors Answer a Set of all the selectors understood by the receiver @meindex compiledMethodAt:@- @item compiledMethodAt:@- selector Return the compiled method associated with selector, from the local method dictionary. Error if not found. @meindex compiledMethodAt:@-ifAbsent:@- @item compiledMethodAt:@- selector ifAbsent:@- aBlock Return the compiled method associated with selector, from the local method dictionary. Evaluate aBlock if not found. @meindex formattedSourceStringAt:@- @item formattedSourceStringAt:@- selector Answer the method source code as a formatted string (if available) for the given selector. Requires package Parser. @meindex lookupAllSelectors:@- @item lookupAllSelectors:@- aSelector Answer a Set of all the compiled method associated with selector. from the local method dictionary and all of the superclasses. @meindex lookupSelector:@- @item lookupSelector:@- aSelector Return the compiled method associated with selector, from the local method dictionary or one of a superclass; return nil if not found. @meindex parseTreeFor:@- @item parseTreeFor:@- selector Answer the parse tree for the given selector, or nil if there was an error. Requires the Parser package to be loaded. @meindex selectorAt:@- @item selectorAt:@- method Return selector for the given CompiledMethod @meindex selectors @item selectors Answer a Set of the receiver's selectors @meindex sourceCodeAt:@- @item sourceCodeAt:@- selector Answer source code (if available) for the given selector. @meindex sourceCodeAt:@-ifAbsent:@- @item sourceCodeAt:@- selector ifAbsent:@- aBlock Answer source code (if available) for the given selector. @meindex sourceMethodAt:@- @item sourceMethodAt:@- selector This is too dependent on the original implementation @end table @node Behavior-built ins @subsection Behavior:@- built ins @table @b @meindex basicNewInFixedSpace @slindex basicNew @item basicNewInFixedSpace Create a new instance of a class with no indexed instance variables. The instance is guaranteed not to move across garbage collections. Like #basicNew, this method should not be overridden. @meindex basicNewInFixedSpace:@- @slindex basicNew:@- @item basicNewInFixedSpace:@- numInstanceVariables Create a new instance of a class with indexed instance variables. The instance has numInstanceVariables indexed instance variables. The instance is guaranteed not to move across garbage collections. Like #basicNew:@-, this method should not be overridden. @meindex flushCache @item flushCache Invalidate the method cache kept by the virtual machine. This message should not need to be called by user programs. @meindex methodsFor:@-ifTrue:@- @item methodsFor:@- category ifTrue:@- condition Compile the following code inside the receiver, with the given category, if condition is true; else ignore it @meindex primCompile:@- @slindex compile:@- @item primCompile:@- code Compile the code, a string or readable stream, with no category. Fail if the code does not obey Smalltalk syntax. Answer the generated CompiledMethod if it does. Do not send this in user code; use #compile:@- or related methods instead. @meindex primCompile:@-ifError:@- @slindex primCompile:@- @slindex compile:@-ifError:@- @item primCompile:@- code ifError:@- aBlock As with #primCompile:@-, but evaluate aBlock (passing the file name, line number and description of the error) if the code does not obey Smalltalk syntax. Do not send this in user code; use #compile:@-ifError:@- or related methods instead. @meindex someInstance @item someInstance Private - Answer the first instance of the receiver in the object table @end table @node Behavior-builtin @subsection Behavior:@- builtin @table @b @meindex basicNew @item basicNew Create a new instance of a class with no indexed instance variables; this method must not be overridden. @meindex basicNew:@- @item basicNew:@- numInstanceVariables Create a new instance of a class with indexed instance variables. The instance has numInstanceVariables indexed instance variables; this method must not be overridden. @meindex new @item new Create a new instance of a class with no indexed instance variables @meindex new:@- @item new:@- numInstanceVariables Create a new instance of a class with indexed instance variables. The instance has numInstanceVariables indexed instance variables. @end table @node Behavior-compilation @subsection Behavior:@- compilation @table @b @meindex scopeDictionary @item scopeDictionary Answer the dictionary that is used when the receiver is before a period in Smalltalk source code. @end table @node Behavior-compilation (alternative) @subsection Behavior:@- compilation (alternative) @table @b @meindex methods @item methods Don't use this, it's only present to file in from Smalltalk/V @meindex methodsFor @item methodsFor Don't use this, it's only present to file in from Dolphin Smalltalk @meindex methodsFor:@-ifFeatures:@- @item methodsFor:@- category ifFeatures:@- features Start compiling methods in the receiver if this implementation of Smalltalk has the given features, else skip the section @meindex methodsFor:@-stamp:@- @item methodsFor:@- category stamp:@- notUsed Don't use this, it's only present to file in from Squeak @meindex privateMethods @item privateMethods Don't use this, it's only present to file in from IBM Smalltalk @meindex publicMethods @item publicMethods Don't use this, it's only present to file in from IBM Smalltalk @end table @node Behavior-compiling @subsection Behavior:@- compiling @table @b @meindex compilerClass @item compilerClass Return the class that will be used to compile the parse nodes into bytecodes. @end table @node Behavior-compiling methods @subsection Behavior:@- compiling methods @table @b @meindex methodsFor:@- @item methodsFor:@- aCategoryString Calling this method prepares the parser to receive methods to be compiled and installed in the receiver's method dictionary. The methods are put in the category identified by the parameter. @meindex poolResolution @item poolResolution Answer a PoolResolution class to be used for resolving pool variables while compiling methods on this class. @end table @node Behavior-creating a class hierarchy @subsection Behavior:@- creating a class hierarchy @table @b @meindex addSubclass:@- @item addSubclass:@- aClass Add aClass asone of the receiver's subclasses. @meindex removeSubclass:@- @item removeSubclass:@- aClass Remove aClass from the list of the receiver's subclasses @meindex superclass:@- @item superclass:@- aClass Set the receiver's superclass. @end table @node Behavior-enumerating @subsection Behavior:@- enumerating @table @b @meindex allInstancesDo:@- @item allInstancesDo:@- aBlock Invokes aBlock for all instances of the receiver @meindex allSubclassesDo:@- @item allSubclassesDo:@- aBlock Invokes aBlock for all subclasses, both direct and indirect. @meindex allSubinstancesDo:@- @item allSubinstancesDo:@- aBlock Invokes aBlock for all instances of each of the receiver's subclasses. @meindex allSuperclassesDo:@- @item allSuperclassesDo:@- aBlock Invokes aBlock for all superclasses, both direct and indirect. @meindex selectSubclasses:@- @item selectSubclasses:@- aBlock Return a Set of subclasses of the receiver satisfying aBlock. @meindex selectSuperclasses:@- @item selectSuperclasses:@- aBlock Return a Set of superclasses of the receiver satisfying aBlock. @meindex subclassesDo:@- @item subclassesDo:@- aBlock Invokes aBlock for all direct subclasses. @meindex withAllSubclassesDo:@- @item withAllSubclassesDo:@- aBlock Invokes aBlock for the receiver and all subclasses, both direct and indirect. @meindex withAllSuperclassesDo:@- @item withAllSuperclassesDo:@- aBlock Invokes aBlock for the receiver and all superclasses, both direct and indirect. @end table @node Behavior-evaluating @subsection Behavior:@- evaluating @table @b @meindex evalString:@-to:@- @item evalString:@- aString to:@- anObject Answer the stack top at the end of the evaluation of the code in aString. The code is executed as part of anObject @meindex evalString:@-to:@-ifError:@- @item evalString:@- aString to:@- anObject ifError:@- aBlock Answer the stack top at the end of the evaluation of the code in aString. If aString cannot be parsed, evaluate aBlock (see compile:@-ifError:@-). The code is executed as part of anObject @meindex evaluate:@- @item evaluate:@- code Evaluate Smalltalk expression in 'code' and return result. @meindex evaluate:@-ifError:@- @item evaluate:@- code ifError:@- block Evaluate 'code'. If a parsing error is detected, invoke 'block' @meindex evaluate:@-notifying:@- @slindex error:@- @item evaluate:@- code notifying:@- requestor Evaluate Smalltalk expression in 'code'. If a parsing error is encountered, send #error:@- to requestor @meindex evaluate:@-to:@- @item evaluate:@- code to:@- anObject Evaluate Smalltalk expression as part of anObject's method definition @meindex evaluate:@-to:@-ifError:@- @item evaluate:@- code to:@- anObject ifError:@- block Evaluate Smalltalk expression as part of anObject's method definition. This method is used to support Inspector expression evaluation. If a parsing error is encountered, invoke error block, 'block' @end table @node Behavior-instance creation @subsection Behavior:@- instance creation @table @b @meindex newInFixedSpace @slindex new @item newInFixedSpace Create a new instance of a class without indexed instance variables. The instance is guaranteed not to move across garbage collections. If a subclass overrides #new, the changes will apply to this method too. @meindex newInFixedSpace:@- @slindex new:@- @item newInFixedSpace:@- numInstanceVariables Create a new instance of a class with indexed instance variables. The instance has numInstanceVariables indexed instance variables. The instance is guaranteed not to move across garbage collections. If a subclass overrides #new:@-, the changes will apply to this method too. @end table @node Behavior-instance variables @subsection Behavior:@- instance variables @table @b @meindex addInstVarName:@- @item addInstVarName:@- aString Add the given instance variable to instance of the receiver @meindex instanceVariableNames:@- @item instanceVariableNames:@- instVarNames Set the instance variables for the receiver to be those in instVarNames @meindex removeInstVarName:@- @item removeInstVarName:@- aString Remove the given instance variable from the receiver and recompile all of the receiver's subclasses @end table @node Behavior-method dictionary @subsection Behavior:@- method dictionary @table @b @meindex addSelector:@-withMethod:@- @item addSelector:@- selector withMethod:@- compiledMethod Add the given compiledMethod to the method dictionary, giving it the passed selector. Answer compiledMethod @meindex compile:@- @item compile:@- code Compile method source. If there are parsing errors, answer nil. Else, return a CompiledMethod result of compilation @meindex compile:@-ifError:@- @item compile:@- code ifError:@- block Compile method source. If there are parsing errors, invoke exception block, 'block' passing file name, line number and error. Return a CompiledMethod result of compilation @meindex compile:@-notifying:@- @slindex error:@- @item compile:@- code notifying:@- requestor Compile method source. If there are parsing errors, send #error:@- to the requestor object, else return a CompiledMethod result of compilation @meindex compileAll @item compileAll Recompile all selectors in the receiver. Ignore errors. @meindex compileAll:@- @slindex error:@- @item compileAll:@- aNotifier Recompile all selectors in the receiver. Notify aNotifier by sending #error:@- messages if something goes wrong. @meindex compileAllSubclasses @slindex error:@- @item compileAllSubclasses Recompile all selector of all subclasses. Notify aNotifier by sending #error:@- messages if something goes wrong. @meindex compileAllSubclasses:@- @slindex error:@- @item compileAllSubclasses:@- aNotifier Recompile all selector of all subclasses. Notify aNotifier by sending #error:@- messages if something goes wrong. @meindex createGetMethod:@- @item createGetMethod:@- what Create a method accessing the variable `what'. @meindex createGetMethod:@-default:@- @item createGetMethod:@- what default:@- value Create a method accessing the variable `what', with a default value of `value', using lazy initialization @meindex createSetMethod:@- @item createSetMethod:@- what Create a method which sets the variable `what'. @meindex decompile:@- @item decompile:@- selector Decompile the bytecodes for the given selector. @meindex defineAsyncCFunc:@-withSelectorArgs:@-args:@- @item defineAsyncCFunc:@- cFuncNameString withSelectorArgs:@- selectorAndArgs args:@- argsArray Please lookup the part on the C interface in the manual. This method is deprecated, you should use the asyncCCall:@-args:@- attribute. @meindex defineCFunc:@-withSelectorArgs:@-returning:@-args:@- @item defineCFunc:@- cFuncNameString withSelectorArgs:@- selectorAndArgs returning:@- returnTypeSymbol args:@- argsArray Please lookup the part on the C interface in the manual. This method is deprecated, you should use the cCall:@-returning:@-args:@- attribute. @meindex edit:@- @item edit:@- selector Open Emacs to edit the method with the passed selector, then compile it @meindex methodDictionary @item methodDictionary Answer the receiver's method dictionary. Don't modify the method dictionary unless you exactly know what you're doing @meindex methodDictionary:@- @item methodDictionary:@- aDictionary Set the receiver's method dictionary to aDictionary @meindex recompile:@- @item recompile:@- selector Recompile the given selector, answer nil if something goes wrong or the new CompiledMethod if everything's ok. @meindex recompile:@-notifying:@- @slindex error:@- @item recompile:@- selector notifying:@- aNotifier Recompile the given selector. If there are parsing errors, send #error:@- to the aNotifier object, else return a CompiledMethod result of compilation @meindex removeSelector:@- @item removeSelector:@- selector Remove the given selector from the method dictionary, answer the CompiledMethod attached to that selector @meindex removeSelector:@-ifAbsent:@- @item removeSelector:@- selector ifAbsent:@- aBlock Remove the given selector from the method dictionary, answer the CompiledMethod attached to that selector. If the selector cannot be found, answer the result of evaluating aBlock. @meindex selectorsAndMethodsDo:@- @item selectorsAndMethodsDo:@- aBlock Evaluate aBlock, passing for each evaluation a selector that's defined in the receiver and the corresponding method. @end table @node Behavior-parsing class declarations @subsection Behavior:@- parsing class declarations @table @b @meindex parseInstanceVariableString:@- @slindex parseVariableString:@- @item parseInstanceVariableString:@- variableString As with #parseVariableString:@-, but answer symbols that name the variables instead of strings. @meindex parseVariableString:@- @item parseVariableString:@- aString Answer an array of instance variable names. aString should specify these in traditional file-in `instanceVariableNames' format. Signal an error if aString contains something other than valid Smalltalk variables. @end table @node Behavior-pluggable behavior (not yet implemented) @subsection Behavior:@- pluggable behavior (not yet implemented) @table @b @meindex debuggerClass @slindex debuggingPriority @item debuggerClass Answer which class is to be used to debug a chain of contexts which includes the receiver. nil means 'do not debug'; other classes are sent #debuggingPriority and the one with the highest priority is picked. @meindex decompilerClass @item decompilerClass Answer the class that can be used to decompile methods, or nil if there is none (as is the case now). @meindex evaluatorClass @item evaluatorClass Answer the class that can be used to evaluate doits, or nil if there is none (as is the case now). @meindex parserClass @item parserClass Answer the class that can be used to parse methods, or nil if there is none (as is the case now). @end table @node Behavior-printing hierarchy @subsection Behavior:@- printing hierarchy @table @b @meindex hierarchyIndent @slindex printHierarchy @item hierarchyIndent Answer the indent to be used by #printHierarchy - 4 by default @meindex printFullHierarchy @item printFullHierarchy Print my full hierarchy (i.e. all my superclasses and subclasses) on the terminal. @meindex printHierarchy @item printHierarchy Print my entire subclass hierarchy on the terminal. @end table @node Behavior-source code @subsection Behavior:@- source code @table @b @meindex formattedSourceStringAt:@-ifAbsent:@- @item formattedSourceStringAt:@- aSelector ifAbsent:@- aBlock Answer the method source code as a formatted string. Requires package Parser. @end table @node Behavior-still unclassified @subsection Behavior:@- still unclassified @table @b @meindex allSharedPoolDictionariesDo:@- @item allSharedPoolDictionariesDo:@- aBlock Answer the shared pools visible from methods in the metaclass, in the correct search order. @meindex parseNodeAt:@- @item parseNodeAt:@- selector Available only when the Parser package is loaded--Answer an RBMethodNode that compiles to my method named by selector. @meindex updateInstanceVars:@-shape:@- @item updateInstanceVars:@- variableArray shape:@- shape Update instance variables and instance spec of the class and all its subclasses. variableArray lists the new variables, including inherited ones. @end table @node Behavior-support for lightweight classes @subsection Behavior:@- support for lightweight classes @table @b @meindex article @item article Answer an article (`a' or `an') which is ok for the receiver's name @meindex asClass @item asClass Answer the first superclass that is a full-fledged Class object @meindex environment @item environment Answer the namespace that this class belongs to - the same as the superclass, since Behavior does not support namespaces yet. @meindex name @item name Answer the class name; this prints to the name of the superclass enclosed in braces. This class name is used, for example, to print the receiver. @meindex nameIn:@- @item nameIn:@- aNamespace Answer the class name when the class is referenced from aNamespace - a dummy one, since Behavior does not support names. @meindex printOn:@-in:@- @item printOn:@- aStream in:@- aNamespace Answer the class name when the class is referenced from aNamespace - a dummy one, since Behavior does not support names. @meindex securityPolicy @item securityPolicy Not commented. @meindex securityPolicy:@- @item securityPolicy:@- aSecurityPolicy This method should not be called for instances of this class. @end table @node Behavior-testing functionality @subsection Behavior:@- testing functionality @table @b @meindex isBehavior @item isBehavior Answer `true'. @end table @node Behavior-testing the class hierarchy @subsection Behavior:@- testing the class hierarchy @table @b @meindex includesBehavior:@- @item includesBehavior:@- aClass Returns true if aClass is the receiver or a superclass of the receiver. @meindex inheritsFrom:@- @item inheritsFrom:@- aClass Returns true if aClass is a superclass of the receiver @meindex kindOfSubclass @item kindOfSubclass Return a string indicating the type of class the receiver is @meindex shape @item shape Answer the symbolic shape of my instances. @meindex shape:@- @slindex byte @slindex int8 @slindex character @slindex short @slindex word @slindex ushort @slindex int @slindex uint @slindex int64 @slindex uint64 @slindex utf32 @slindex float @slindex double @slindex pointer @slindex inherit @slindex inherit @item shape:@- shape Give the provided shape to the receiver's instances. The shape can be nil, or one of #byte #int8 #character #short #word #ushort #int #uint #int64 #uint64 #utf32 #float #double or #pointer. In addition, the special value #inherit means to use the shape of the superclass; note however that this is a static setting, and subclasses that used #inherit are not mutated when the superclass adopts a different shape. @end table @node Behavior-testing the form of the instances @subsection Behavior:@- testing the form of the instances @table @b @meindex instSize @item instSize Answer how many fixed instance variables are reserved to each of the receiver's instances @meindex isBits @item isBits Answer whether my instances' variables are immediate, non-OOP values. @meindex isFixed @item isFixed Answer whether the receiver's instances have no indexed instance variables @meindex isIdentity @item isIdentity Answer whether x = y implies x == y for instances of the receiver @meindex isImmediate @item isImmediate Answer whether, if x is an instance of the receiver, x copy == x @meindex isPointers @item isPointers Answer whether the instance variables of the receiver's instances are objects @meindex isVariable @item isVariable Answer whether the receiver's instances have indexed instance variables @end table @node Behavior-testing the method dictionary @subsection Behavior:@- testing the method dictionary @table @b @meindex canUnderstand:@- @item canUnderstand:@- selector Returns true if the instances of the receiver understand the given selector @meindex hasMethods @item hasMethods Return whether the receiver has any methods defined @meindex includesSelector:@- @item includesSelector:@- selector Returns true if the local method dictionary contains the given selector @meindex scopeHas:@-ifTrue:@- @item scopeHas:@- name ifTrue:@- aBlock If methods understood by the receiver's instances have access to a symbol named 'name', evaluate aBlock @meindex whichClassIncludesSelector:@- @item whichClassIncludesSelector:@- selector Answer which class in the receiver's hierarchy contains the implementation of selector used by instances of the class (nil if none does) @meindex whichSelectorsAccess:@- @item whichSelectorsAccess:@- instVarName Answer a Set of selectors which access the given instance variable @meindex whichSelectorsAssign:@- @item whichSelectorsAssign:@- instVarName Answer a Set of selectors which read the given instance variable @meindex whichSelectorsRead:@- @item whichSelectorsRead:@- instVarName Answer a Set of selectors which read the given instance variable @meindex whichSelectorsReferTo:@- @item whichSelectorsReferTo:@- anObject Returns a Set of selectors that refer to anObject @meindex whichSelectorsReferToByteCode:@- @item whichSelectorsReferToByteCode:@- aByteCode Return the collection of selectors in the class which reference the byte code, aByteCode @end table @node BindingDictionary @section BindingDictionary @clindex BindingDictionary @table @b @item Defined in namespace Smalltalk @itemx Superclass: Dictionary @itemx Category: Language-Implementation I am a special form of dictionary that provides special ways to access my keys, which typically begin with an uppercase letter; also, my associations are actually VariableBinding instances. My keys are (expected to be) symbols, so I use == to match searched keys to those in the dictionary -- this is done expecting that it brings a bit more speed. @end table @menu * BindingDictionary-accessing:: (instance) * BindingDictionary-basic & copying:: (instance) * BindingDictionary-copying:: (instance) * BindingDictionary-forward declarations:: (instance) * BindingDictionary-printing:: (instance) * BindingDictionary-testing:: (instance) @end menu @node BindingDictionary-accessing @subsection BindingDictionary:@- accessing @table @b @meindex define:@- @slindex at:@-put:@- @item define:@- aSymbol Define aSymbol as equal to nil inside the receiver. Fail if such a variable already exists (use #at:@-put:@- if you don't want to fail) @meindex doesNotUnderstand:@- @slindex Variable @slindex Variable @item doesNotUnderstand:@- aMessage Try to map unary selectors to read accesses to the Namespace, and one-argument keyword selectors to write accesses. Note that:@- a) this works only if the selector has an uppercase first letter; and b) `aNamespace Variable:@- value' is the same as `aNamespace set:@- #Variable to:@- value', not the same as `aNamespace at:@- #Variable put:@- value' --- the latter always refers to the current namespace, while the former won't define a new variable, instead searching in superspaces (and raising an error if the variable cannot be found). @meindex environment @item environment Answer the environment to which the receiver is connected. This can be the class for a dictionary that holds class variables, or the super-namespace. In general it is used to compute the receiver's name. @meindex environment:@- @item environment:@- anObject Set the environment to which the receiver is connected. This can be the class for a dictionary that holds class variables, or the super-namespace. In general it is used to compute the receiver's name. @meindex import:@-from:@- @item import:@- aSymbol from:@- aNamespace Add to the receiver the symbol aSymbol, associated to the same value as in aNamespace. Fail if aNamespace does not contain the given key. @meindex name @item name Answer the receiver's name, which by default is the same as the name of the receiver's environment. @meindex nameIn:@- @item nameIn:@- aNamespace Answer the receiver's name when referred to from aNamespace; by default the computation is deferred to the receiver's environment. @end table @node BindingDictionary-basic & copying @subsection BindingDictionary:@- basic & copying @table @b @meindex = @item = arg Answer whether the receiver is equal to arg. The equality test is by default the same as that for equal objects. = must not fail; answer false if the receiver cannot be compared to arg @meindex hash @slindex identityHash @item hash Answer an hash value for the receiver. This is the same as the object's #identityHash. @end table @node BindingDictionary-copying @subsection BindingDictionary:@- copying @table @b @meindex copy @item copy Answer the receiver. @meindex copyEmpty:@- @item copyEmpty:@- newSize Answer an empty copy of the receiver whose size is newSize @meindex copyEmptyForCollect @slindex collect:@- @item copyEmptyForCollect Answer an empty copy of the receiver which is filled in to compute the result of #collect:@- @meindex copyEmptyForCollect:@- @slindex collect:@- @item copyEmptyForCollect:@- size Answer an empty copy of the receiver which is filled in to compute the result of #collect:@- @meindex deepCopy @item deepCopy Answer the receiver. @meindex shallowCopy @item shallowCopy Answer the receiver. @end table @node BindingDictionary-forward declarations @subsection BindingDictionary:@- forward declarations @table @b @meindex at:@-put:@- @item at:@- key put:@- value Store value as associated to the given key. If any, recycle Associations temporarily stored by the compiler inside the `Undeclared' dictionary. @end table @node BindingDictionary-printing @subsection BindingDictionary:@- printing @table @b @meindex printOn:@-in:@- @item printOn:@- aStream in:@- aNamespace Print the receiver's name when referred to from aNamespace; by default the computation is deferred to the receiver's environment. @end table @node BindingDictionary-testing @subsection BindingDictionary:@- testing @table @b @meindex species @item species Answer `IdentityDictionary'. @end table @node BlockClosure @section BlockClosure @clindex BlockClosure @table @b @item Defined in namespace Smalltalk @itemx Superclass: Object @itemx Category: Language-Implementation I am a factotum class. My instances represent Smalltalk blocks, portions of executeable code that have access to the environment that they were declared in, take parameters, and can be passed around as objects to be executed by methods outside the current class. Block closures are sent a message to compute their value and create a new execution context; this property can be used in the construction of control flow methods. They also provide some methods that are used in the creation of Processes from blocks. @end table @menu * BlockClosure class-instance creation:: (class) * BlockClosure class-testing:: (class) * BlockClosure-accessing:: (instance) * BlockClosure-built ins:: (instance) * BlockClosure-control structures:: (instance) * BlockClosure-exception handling:: (instance) * BlockClosure-multiple process:: (instance) * BlockClosure-overriding:: (instance) * BlockClosure-testing:: (instance) * BlockClosure-unwind protection:: (instance) @end menu @node BlockClosure class-instance creation @subsection BlockClosure class:@- instance creation @table @b @meindex block:@- @item block:@- aCompiledBlock Answer a BlockClosure that activates the passed CompiledBlock. @meindex block:@-receiver:@- @item block:@- aCompiledBlock receiver:@- anObject Answer a BlockClosure that activates the passed CompiledBlock with the given receiver. @meindex block:@-receiver:@-outerContext:@- @item block:@- aCompiledBlock receiver:@- anObject outerContext:@- aContext Answer a BlockClosure that activates the passed CompiledBlock with the given receiver. @meindex numArgs:@-numTemps:@-bytecodes:@-depth:@-literals:@- @item numArgs:@- args numTemps:@- temps bytecodes:@- bytecodes depth:@- depth literals:@- literalArray Answer a BlockClosure for a new CompiledBlock that is created using the passed parameters. To make it work, you must put the BlockClosure into a CompiledMethod's literals. @end table @node BlockClosure class-testing @subsection BlockClosure class:@- testing @table @b @meindex isImmediate @item isImmediate Answer whether, if x is an instance of the receiver, x copy == x @end table @node BlockClosure-accessing @subsection BlockClosure:@- accessing @table @b @meindex argumentCount @item argumentCount Answer the number of arguments passed to the receiver @meindex block @item block Answer the CompiledBlock which contains the receiver's bytecodes @meindex block:@- @item block:@- aCompiledBlock Set the CompiledBlock which contains the receiver's bytecodes @meindex finalIP @item finalIP Answer the last instruction that can be executed by the receiver @meindex fixTemps @item fixTemps This should fix the values of the temporary variables used in the block that are ordinarily shared with the method in which the block is defined. Not defined yet, but it is not harmful that it isn't. Answer the receiver. @meindex initialIP @item initialIP Answer the initial instruction pointer into the receiver. @meindex method @item method Answer the CompiledMethod in which the receiver lies @meindex numArgs @item numArgs Answer the number of arguments passed to the receiver @meindex numTemps @item numTemps Answer the number of temporary variables used by the receiver @meindex outerContext @item outerContext Answer the method/block context which is the immediate outer of the receiver @meindex outerContext:@- @item outerContext:@- containingContext Set the method/block context which is the immediate outer of the receiver @meindex receiver @item receiver Answer the object that is used as `self' when executing the receiver (if nil, it might mean that the receiver is not valid though...) @meindex receiver:@- @item receiver:@- anObject Set the object that is used as `self' when executing the receiver @meindex stackDepth @item stackDepth Answer the number of stack slots needed for the receiver @end table @node BlockClosure-built ins @subsection BlockClosure:@- built ins @table @b @meindex cull:@- @item cull:@- arg1 Evaluate the receiver, passing arg1 as the only parameter if the receiver has parameters. @meindex cull:@-cull:@- @item cull:@- arg1 cull:@- arg2 Evaluate the receiver, passing arg1 and arg2 as parameters if the receiver accepts them. @meindex cull:@-cull:@-cull:@- @item cull:@- arg1 cull:@- arg2 cull:@- arg3 Evaluate the receiver, passing arg1, arg2 and arg3 as parameters if the receiver accepts them. @meindex value @item value Evaluate the receiver passing no parameters @meindex value:@- @item value:@- arg1 Evaluate the receiver passing arg1 as the only parameter @meindex value:@-value:@- @item value:@- arg1 value:@- arg2 Evaluate the receiver passing arg1 and arg2 as the parameters @meindex value:@-value:@-value:@- @item value:@- arg1 value:@- arg2 value:@- arg3 Evaluate the receiver passing arg1, arg2 and arg3 as the parameters @meindex valueWithArguments:@- @item valueWithArguments:@- argumentsArray Evaluate the receiver passing argArray's elements as the parameters @end table @node BlockClosure-control structures @subsection BlockClosure:@- control structures @table @b @meindex repeat @item repeat Evaluate the receiver 'forever' (actually until a return is executed or the process is terminated). @meindex whileFalse @item whileFalse Evaluate the receiver until it returns true @meindex whileFalse:@- @item whileFalse:@- aBlock Evaluate the receiver. If it returns false, evaluate aBlock and restart @meindex whileTrue @item whileTrue Evaluate the receiver until it returns false @meindex whileTrue:@- @item whileTrue:@- aBlock Evaluate the receiver. If it returns true, evaluate aBlock and restart @end table @node BlockClosure-exception handling @subsection BlockClosure:@- exception handling @table @b @meindex ifError:@- @slindex error:@- @item ifError:@- aBlock Evaluate the receiver; when #error:@- is called, pass to aBlock the receiver and the parameter, and answer the result of evaluating aBlock. If another exception is raised, it is passed to an outer handler; if no exception is raised, the result of evaluating the receiver is returned. @meindex on:@-do:@- @slindex return:@- @item on:@- anException do:@- aBlock Evaluate the receiver; when anException is signaled, evaluate aBlock passing a Signal describing the exception. Answer either the result of evaluating the receiver or the parameter of a Signal>>@-#return:@- @meindex on:@-do:@-on:@-do:@- @slindex return:@- @item on:@- e1 do:@- b1 on:@- e2 do:@- b2 Evaluate the receiver; when e1 or e2 are signaled, evaluate respectively b1 or b2, passing a Signal describing the exception. Answer either the result of evaluating the receiver or the argument of a Signal>>@-#return:@- @meindex on:@-do:@-on:@-do:@-on:@-do:@- @slindex return:@- @item on:@- e1 do:@- b1 on:@- e2 do:@- b2 on:@- e3 do:@- b3 Evaluate the receiver; when e1, e2 or e3 are signaled, evaluate respectively b1, b2 or b3, passing a Signal describing the exception. Answer either the result of evaluating the receiver or the parameter of a Signal>>@-#return:@- @meindex on:@-do:@-on:@-do:@-on:@-do:@-on:@-do:@- @slindex return:@- @item on:@- e1 do:@- b1 on:@- e2 do:@- b2 on:@- e3 do:@- b3 on:@- e4 do:@- b4 Evaluate the receiver; when e1, e2, e3 or e4 are signaled, evaluate respectively b1, b2, b3 or b4, passing a Signal describing the exception. Answer either the result of evaluating the receiver or the parameter of a Signal>>@-#return:@- @meindex on:@-do:@-on:@-do:@-on:@-do:@-on:@-do:@-on:@-do:@- @slindex return:@- @item on:@- e1 do:@- b1 on:@- e2 do:@- b2 on:@- e3 do:@- b3 on:@- e4 do:@- b4 on:@- e5 do:@- b5 Evaluate the receiver; when e1, e2, e3, e4 or e5 are signaled, evaluate respectively b1, b2, b3, b4 or b5, passing a Signal describing the exception. Answer either the result of evaluating the receiver or the parameter of a Signal>>@-#return:@- @end table @node BlockClosure-multiple process @subsection BlockClosure:@- multiple process @table @b @meindex fork @item fork Create a new process executing the receiver and start it @meindex forkAt:@- @item forkAt:@- priority Create a new process executing the receiver with given priority and start it @meindex forkWithoutPreemption @item forkWithoutPreemption Evaluate the receiver in a process that cannot be preempted. If the receiver expect a parameter, pass the current process. @meindex newProcess @item newProcess Create a new process executing the receiver in suspended state. The priority is the same as for the calling process. The receiver must not contain returns @meindex newProcessWith:@- @item newProcessWith:@- anArray Create a new process executing the receiver with the passed arguments, and leave it in suspended state. The priority is the same as for the calling process. The receiver must not contain returns @meindex valueWithoutInterrupts @item valueWithoutInterrupts Evaluate aBlock and delay all interrupts that are requested to the active process during its execution to after aBlock returns. @meindex valueWithoutPreemption @item valueWithoutPreemption Evaluate the receiver with external interrupts disabled. This effectively disables preemption as long as the block does not explicitly yield control, wait on semaphores, and the like. @end table @node BlockClosure-overriding @subsection BlockClosure:@- overriding @table @b @meindex copy @item copy Answer the receiver. @meindex deepCopy @item deepCopy Answer a shallow copy. @end table @node BlockClosure-testing @subsection BlockClosure:@- testing @table @b @meindex hasMethodReturn @item hasMethodReturn Answer whether the block contains a method return @end table @node BlockClosure-unwind protection @subsection BlockClosure:@- unwind protection @table @b @meindex ensure:@- @item ensure:@- aBlock Evaluate the receiver; when any exception is signaled exit returning the result of evaluating aBlock; if no exception is raised, return the result of evaluating aBlock when the receiver has ended @meindex ifCurtailed:@- @item ifCurtailed:@- aBlock Evaluate the receiver; if its execution triggers an unwind which truncates the execution of the block (`curtails' the block), evaluate aBlock. The three cases which can curtail the execution of the receiver are:@- a non-local return in the receiver, a non-local return in a block evaluated by the receiver which returns past the receiver itself, and an exception raised and not resumed during the execution of the receiver. @meindex valueWithUnwind @slindex valueWithUnwind @slindex ensure:@- @slindex on:@-do:@- @item valueWithUnwind Evaluate the receiver. Any errors caused by the block will cause a backtrace, but execution will continue in the method that sent #valueWithUnwind, after that call. Example:@- [ 1 / 0 ] valueWithUnwind. 'unwind works!' printNl. Important:@- this method is public, but it is intended to be used in very special cases (as a rule of thumb, use it only when the corresponding C code uses the _gst_prepare_execution_environment and _gst_finish_execution_environment functions). You should usually rely on #ensure:@- and #on:@-do:@-. @end table @node BlockContext @section BlockContext @clindex BlockContext @table @b @item Defined in namespace Smalltalk @itemx Superclass: ContextPart @itemx Category: Language-Implementation My instances represent executing Smalltalk blocks, which are portions of executeable code that have access to the environment that they were declared in, take parameters, and result from BlockClosure objects created to be executed by methods outside the current class. Block contexts are created by messages sent to compute a closure's value. They contain a stack and also provide some methods that can be used in inspection or debugging. @end table @menu * BlockContext-accessing:: (instance) * BlockContext-debugging:: (instance) * BlockContext-printing:: (instance) @end menu @node BlockContext-accessing @subsection BlockContext:@- accessing @table @b @meindex caller @item caller Answer the context that called the receiver @meindex home @item home Answer the MethodContext to which the receiver refers, or nil if it has been optimized away @meindex isBlock @item isBlock Answer whether the receiver is a block context @meindex isDisabled @slindex ensure:@- @item isDisabled Answers false, because contexts that are skipped when doing a return are always MethodContexts. BlockContexts are removed from the chain whenever a non-local return is done, while MethodContexts need to stay there in case there is a non-local return from the #ensure:@- block. @meindex isEnvironment @item isEnvironment To create a valid execution environment for the interpreter even before it starts, GST creates a fake context whose selector is nil and which can be used as a marker for the current execution environment. Answer whether the receiver is that kind of context (always false, since those contexts are always MethodContexts). @meindex isUnwind @slindex continue:@- @slindex ensure:@- @item isUnwind Answers whether the context must continue execution even after a non-local return (a return from the enclosing method of a block, or a call to the #continue:@- method of ContextPart). Such contexts are created only by #ensure:@- and are always MethodContexts. @meindex nthOuterContext:@- @item nthOuterContext:@- n Answer the n-th outer block/method context for the receiver @meindex outerContext @item outerContext Answer the outer block/method context for the receiver @end table @node BlockContext-debugging @subsection BlockContext:@- debugging @table @b @meindex isInternalExceptionHandlingContext @item isInternalExceptionHandlingContext Answer whether the receiver is a context that should be hidden to the user when presenting a backtrace. Such contexts are never blocks, but check the rest of the chain. @end table @node BlockContext-printing @subsection BlockContext:@- printing @table @b @meindex printOn:@- @item printOn:@- aStream Print a representation for the receiver on aStream @end table @node Boolean @section Boolean @clindex Boolean @table @b @item Defined in namespace Smalltalk @itemx Superclass: Object @itemx Category: Language-Data types I have two instances in the Smalltalk system:@- true and false. I provide methods that are conditional on boolean values, such as conditional execution and loops, and conditional testing, such as conditional and and conditional or. I should say that I appear to provide those operations; my subclasses True and False actually provide those operations. @end table @menu * Boolean class-testing:: (class) * Boolean-basic:: (instance) * Boolean-C hacks:: (instance) * Boolean-overriding:: (instance) * Boolean-storing:: (instance) @end menu @node Boolean class-testing @subsection Boolean class:@- testing @table @b @meindex isIdentity @item isIdentity Answer whether x = y implies x == y for instances of the receiver @meindex isImmediate @item isImmediate Answer whether, if x is an instance of the receiver, x copy == x @end table @node Boolean-basic @subsection Boolean:@- basic @table @b @meindex & @item & aBoolean This method's functionality should be implemented by subclasses of Boolean @meindex and:@- @item and:@- aBlock This method's functionality should be implemented by subclasses of Boolean @meindex eqv:@- @item eqv:@- aBoolean This method's functionality should be implemented by subclasses of Boolean @meindex ifFalse:@- @item ifFalse:@- falseBlock This method's functionality should be implemented by subclasses of Boolean @meindex ifFalse:@-ifTrue:@- @item ifFalse:@- falseBlock ifTrue:@- trueBlock This method's functionality should be implemented by subclasses of Boolean @meindex ifTrue:@- @item ifTrue:@- trueBlock This method's functionality should be implemented by subclasses of Boolean @meindex ifTrue:@-ifFalse:@- @item ifTrue:@- trueBlock ifFalse:@- falseBlock This method's functionality should be implemented by subclasses of Boolean @meindex not @item not This method's functionality should be implemented by subclasses of Boolean @meindex or:@- @item or:@- aBlock This method's functionality should be implemented by subclasses of Boolean @meindex xor:@- @item xor:@- aBoolean This method's functionality should be implemented by subclasses of Boolean @meindex | @item | aBoolean This method's functionality should be implemented by subclasses of Boolean @end table @node Boolean-C hacks @subsection Boolean:@- C hacks @table @b @meindex asCBooleanValue @item asCBooleanValue This method's functionality should be implemented by subclasses of Boolean @end table @node Boolean-overriding @subsection Boolean:@- overriding @table @b @meindex deepCopy @item deepCopy Answer the receiver. @meindex shallowCopy @item shallowCopy Answer the receiver. @end table @node Boolean-storing @subsection Boolean:@- storing @table @b @meindex isLiteralObject @item isLiteralObject Answer whether the receiver is expressible as a Smalltalk literal. @meindex storeLiteralOn:@- @item storeLiteralOn:@- aStream Store on aStream some Smalltalk code which compiles to the receiver @meindex storeOn:@- @item storeOn:@- aStream Store on aStream some Smalltalk code which compiles to the receiver @end table @node ByteArray @section ByteArray @clindex ByteArray @table @b @item Defined in namespace Smalltalk @itemx Superclass: ArrayedCollection @itemx Category: Collections-Sequenceable My instances are similar to strings in that they are both represented as a sequence of bytes, but my individual elements are integers, where as a String's elements are characters. @end table @menu * ByteArray class-instance creation:: (class) * ByteArray-basic:: (instance) * ByteArray-built ins:: (instance) * ByteArray-CObject:: (instance) * ByteArray-converting:: (instance) * ByteArray-more advanced accessing:: (instance) * ByteArray-storing:: (instance) @end menu @node ByteArray class-instance creation @subsection ByteArray class:@- instance creation @table @b @meindex fromCData:@-size:@- @item fromCData:@- aCObject size:@- anInteger Answer a ByteArray containing anInteger bytes starting at the location pointed to by aCObject @end table @node ByteArray-basic @subsection ByteArray:@- basic @table @b @meindex = @item = aCollection Answer whether the receiver's items match those in aCollection @meindex indexOf:@-startingAt:@- @item indexOf:@- anElement startingAt:@- anIndex Answer the first index > anIndex which contains anElement. Invoke exceptionBlock and answer its result if no item is found @meindex indexOf:@-startingAt:@-ifAbsent:@- @item indexOf:@- anElement startingAt:@- anIndex ifAbsent:@- exceptionBlock Answer the first index > anIndex which contains anElement. Invoke exceptionBlock and answer its result if no item is found @end table @node ByteArray-built ins @subsection ByteArray:@- built ins @table @b @meindex asCData:@- @item asCData:@- aCType Allocate memory with malloc for a copy of the receiver, and return it converted to a CObject with the given type @meindex at:@-ifAbsent:@- @item at:@- anIndex ifAbsent:@- aBlock Answer the index-th indexed instance variable of the receiver @meindex byteAt:@- @item byteAt:@- index Answer the index-th indexed instance variable of the receiver @meindex byteAt:@-put:@- @item byteAt:@- index put:@- value Store the `value' byte in the index-th indexed instance variable of the receiver @meindex hash @item hash Answer an hash value for the receiver @meindex replaceFrom:@-to:@-with:@-startingAt:@- @item replaceFrom:@- start to:@- stop with:@- aByteArray startingAt:@- replaceStart Replace the characters from start to stop with the bytes contained in aByteArray (which, actually, can be any variable byte class), starting at the replaceStart location of aByteArray @meindex replaceFrom:@-to:@-withString:@-startingAt:@- @item replaceFrom:@- start to:@- stop withString:@- aString startingAt:@- replaceStart Replace the characters from start to stop with the ASCII codes contained in aString (which, actually, can be any variable byte class), starting at the replaceStart location of aString @end table @node ByteArray-CObject @subsection ByteArray:@- CObject @table @b @meindex asCData @item asCData Allocate memory with malloc for a copy of the receiver, and return a pointer to it as a CByte. @meindex castTo:@- @item castTo:@- type Give access to the receiver as a value with the given CType. @end table @node ByteArray-converting @subsection ByteArray:@- converting @table @b @meindex asString @item asString Answer a String whose character's ASCII codes are the receiver's contents @meindex asUnicodeString @item asUnicodeString Answer a UnicodeString whose character's codes are the receiver's contents. This is not implemented unless you load the I18N package. @end table @node ByteArray-more advanced accessing @subsection ByteArray:@- more advanced accessing @table @b @meindex charAt:@- @item charAt:@- index Access the C char at the given index in the receiver. The value is returned as a Smalltalk Character. Indices are 1-based just like for other Smalltalk access. @meindex charAt:@-put:@- @item charAt:@- index put:@- value Store as a C char the Smalltalk Character or Integer object identified by `value', at the given index in the receiver, using sizeof(char) bytes - i.e. 1 byte. Indices are 1-based just like for other Smalltalk access. @meindex doubleAt:@- @item doubleAt:@- index Access the C double at the given index in the receiver. Indices are 1-based just like for other Smalltalk access. @meindex doubleAt:@-put:@- @item doubleAt:@- index put:@- value Store the Smalltalk Float object identified by `value', at the given index in the receiver, writing it like a C double. Indices are 1-based just like for other Smalltalk access. @meindex floatAt:@- @item floatAt:@- index Access the C float at the given index in the receiver. Indices are 1-based just like for other Smalltalk access. @meindex floatAt:@-put:@- @item floatAt:@- index put:@- value Store the Smalltalk Float object identified by `value', at the given index in the receiver, writing it like a C float. Indices are 1-based just like for other Smalltalk access. @meindex intAt:@- @item intAt:@- index Access the C int at the given index in the receiver. Indices are 1-based just like for other Smalltalk access. @meindex intAt:@-put:@- @item intAt:@- index put:@- value Store the Smalltalk Integer object identified by `value', at the given index in the receiver, using sizeof(int) bytes. Indices are 1-based just like for other Smalltalk access. @meindex longAt:@- @item longAt:@- index Access the C long int at the given index in the receiver. Indices are 1-based just like for other Smalltalk access. @meindex longAt:@-put:@- @item longAt:@- index put:@- value Store the Smalltalk Integer object identified by `value', at the given index in the receiver, using sizeof(long) bytes. Indices are 1-based just like for other Smalltalk access. @meindex longDoubleAt:@- @item longDoubleAt:@- index Access the C long double at the given index in the receiver. Indices are 1-based just like for other Smalltalk access. @meindex longDoubleAt:@-put:@- @item longDoubleAt:@- index put:@- value Store the Smalltalk Float object identified by `value', at the given index in the receiver, writing it like a C double. Indices are 1-based just like for other Smalltalk access. @meindex objectAt:@- @item objectAt:@- index Access the Smalltalk object (OOP) at the given index in the receiver. Indices are 1-based just like for other Smalltalk access. @meindex objectAt:@-put:@- @item objectAt:@- index put:@- value Store a pointer (OOP) to the Smalltalk object identified by `value', at the given index in the receiver. Indices are 1-based just like for other Smalltalk access. @meindex shortAt:@- @item shortAt:@- index Access the C short int at the given index in the receiver. Indices are 1-based just like for other Smalltalk access. @meindex shortAt:@-put:@- @item shortAt:@- index put:@- value Store the Smalltalk Integer object identified by `value', at the given index in the receiver, using sizeof(short) bytes. Indices are 1-based just like for other Smalltalk access. @meindex stringAt:@- @item stringAt:@- index Access the string pointed by the C `char *' at the given index in the receiver. Indices are 1-based just like for other Smalltalk access. @meindex stringAt:@-put:@- @item stringAt:@- index put:@- value Store the Smalltalk String object identified by `value', at the given index in the receiver, writing it like a *FRESHLY ALLOCATED* C string. It is the caller's responsibility to free it if necessary. Indices are 1-based just like for other Smalltalk access. @meindex ucharAt:@- @item ucharAt:@- index Access the C unsigned char at the given index in the receiver. The value is returned as a Smalltalk Character. Indices are 1-based just like for other Smalltalk access. @meindex ucharAt:@-put:@- @item ucharAt:@- index put:@- value Store as a C char the Smalltalk Character or Integer object identified by `value', at the given index in the receiver, using sizeof(char) bytes - i.e. 1 byte. Indices are 1-based just like for other Smalltalk access. @meindex uintAt:@- @item uintAt:@- index Access the C unsigned int at the given index in the receiver. Indices are 1-based just like for other Smalltalk access. @meindex uintAt:@-put:@- @item uintAt:@- index put:@- value Store the Smalltalk Integer object identified by `value', at the given index in the receiver, using sizeof(int) bytes. Indices are 1-based just like for other Smalltalk access. @meindex ulongAt:@- @item ulongAt:@- index Access the C unsigned long int at the given index in the receiver. Indices are 1-based just like for other Smalltalk access. @meindex ulongAt:@-put:@- @item ulongAt:@- index put:@- value Store the Smalltalk Integer object identified by `value', at the given index in the receiver, using sizeof(long) bytes. Indices are 1-based just like for other Smalltalk access. @meindex unsignedCharAt:@- @item unsignedCharAt:@- index Access the C unsigned char at the given index in the receiver. The value is returned as a Smalltalk Character. Indices are 1-based just like for other Smalltalk access. @meindex unsignedCharAt:@-put:@- @item unsignedCharAt:@- index put:@- value Store as a C char the Smalltalk Character or Integer object identified by `value', at the given index in the receiver, using sizeof(char) bytes - i.e. 1 byte. Indices are 1-based just like for other Smalltalk access. @meindex unsignedIntAt:@- @item unsignedIntAt:@- index Access the C unsigned int at the given index in the receiver. Indices are 1-based just like for other Smalltalk access. @meindex unsignedIntAt:@-put:@- @item unsignedIntAt:@- index put:@- value Store the Smalltalk Integer object identified by `value', at the given index in the receiver, using sizeof(int) bytes. Indices are 1-based just like for other Smalltalk access. @meindex unsignedLongAt:@- @item unsignedLongAt:@- index Access the C unsigned long int at the given index in the receiver. Indices are 1-based just like for other Smalltalk access. @meindex unsignedLongAt:@-put:@- @item unsignedLongAt:@- index put:@- value Store the Smalltalk Integer object identified by `value', at the given index in the receiver, using sizeof(long) bytes. Indices are 1-based just like for other Smalltalk access. @meindex unsignedShortAt:@- @item unsignedShortAt:@- index Access the C unsigned short int at the given index in the receiver. Indices are 1-based just like for other Smalltalk access. @meindex unsignedShortAt:@-put:@- @item unsignedShortAt:@- index put:@- value Store the Smalltalk Integer object identified by `value', at the given index in the receiver, using sizeof(short) bytes. Indices are 1-based just like for other Smalltalk access. @meindex ushortAt:@- @item ushortAt:@- index Access the C unsigned short int at the given index in the receiver. Indices are 1-based just like for other Smalltalk access. @meindex ushortAt:@-put:@- @item ushortAt:@- index put:@- value Store the Smalltalk Integer object identified by `value', at the given index in the receiver, using sizeof(short) bytes. Indices are 1-based just like for other Smalltalk access. @end table @node ByteArray-storing @subsection ByteArray:@- storing @table @b @meindex isLiteralObject @item isLiteralObject Answer whether the receiver is expressible as a Smalltalk literal. @meindex storeLiteralOn:@- @item storeLiteralOn:@- aStream Put a Smalltalk literal evaluating to the receiver on aStream. @meindex storeOn:@- @item storeOn:@- aStream Put Smalltalk code evaluating to the receiver on aStream. @end table @node CAggregate @section CAggregate @clindex CAggregate @table @b @item Defined in namespace Smalltalk @itemx Superclass: CObject @itemx Category: Language-C interface @end table @menu * CAggregate class-accessing:: (class) * CAggregate-accessing:: (instance) @end menu @node CAggregate class-accessing @subsection CAggregate class:@- accessing @table @b @meindex alignof @item alignof Answer the receiver's instances required aligment @meindex sizeof @item sizeof Answer the receiver's instances size @end table @node CAggregate-accessing @subsection CAggregate:@- accessing @table @b @meindex elementType @item elementType Answer the type over which the receiver is constructed. @end table @node CallinProcess @section CallinProcess @clindex CallinProcess @table @b @item Defined in namespace Smalltalk @itemx Superclass: Process @itemx Category: Language-Processes I represent a unit of computation for which external C code requested execution, so I must store the returned value once my computation terminates and I must not survive across image saves (since those who invoked me no longer exist). I am otherwise equivalent to a Process. @end table @menu * CallinProcess-debugging:: (instance) @end menu @node CallinProcess-debugging @subsection CallinProcess:@- debugging @table @b @meindex detach @item detach Continue running the receiver as a normal Process, and return nil from the callin. @end table @node CArray @section CArray @clindex CArray @table @b @item Defined in namespace Smalltalk @itemx Superclass: CAggregate @itemx Category: Language-C interface @end table @menu * CArray-accessing:: (instance) @end menu @node CArray-accessing @subsection CArray:@- accessing @table @b @meindex alignof @item alignof Answer the receiver's required aligment @meindex sizeof @item sizeof Answer the receiver's size @end table @node CArrayCType @section CArrayCType @clindex CArrayCType @table @b @item Defined in namespace Smalltalk @itemx Superclass: CPtrCType @itemx Category: Language-C interface @end table @menu * CArrayCType class-instance creation:: (class) * CArrayCType-accessing:: (instance) * CArrayCType-basic:: (instance) * CArrayCType-storing:: (instance) @end menu @node CArrayCType class-instance creation @subsection CArrayCType class:@- instance creation @table @b @meindex elementType:@- @item elementType:@- aCType This method should not be called for instances of this class. @meindex elementType:@-numberOfElements:@- @item elementType:@- aCType numberOfElements:@- anInteger Answer a new instance of CPtrCType that maps an array whose elements are of the given CType, and whose size is exactly anInteger elements (of course, anInteger only matters for allocation, not for access, since no out-of-bounds protection is provided for C objects). @meindex from:@- @item from:@- type Private - Called by CType>>from:@- for arrays @end table @node CArrayCType-accessing @subsection CArrayCType:@- accessing @table @b @meindex alignof @item alignof Answer the alignment of the receiver's instances @meindex numberOfElements @item numberOfElements Answer the number of elements in the receiver's instances @meindex sizeof @item sizeof Answer the size of the receiver's instances @end table @node CArrayCType-basic @subsection CArrayCType:@- basic @table @b @meindex = @item = anObject Return whether the receiver and anObject are equal. @meindex hash @item hash Return a hash code for the receiver. @end table @node CArrayCType-storing @subsection CArrayCType:@- storing @table @b @meindex storeOn:@- @item storeOn:@- aStream As with super. @end table @node CBoolean @section CBoolean @clindex CBoolean @table @b @item Defined in namespace Smalltalk @itemx Superclass: CByte @itemx Category: Language-C interface I return true if a byte is not zero, false otherwise. @end table @menu * CBoolean class-conversion:: (class) * CBoolean-accessing:: (instance) @end menu @node CBoolean class-conversion @subsection CBoolean class:@- conversion @table @b @meindex type @item type Answer a CType for the receiver @end table @node CBoolean-accessing @subsection CBoolean:@- accessing @table @b @meindex value @item value Get the receiver's value - answer true if it is != 0, false if it is 0. @meindex value:@- @item value:@- aBoolean Set the receiver's value - it's the same as for CBytes, but we get a Boolean, not a Character @end table @node CByte @section CByte @clindex CByte @table @b @item Defined in namespace Smalltalk @itemx Superclass: CUChar @itemx Category: Language-C interface You know what a byte is, don't you?!? @end table @menu * CByte class-conversion:: (class) * CByte-accessing:: (instance) @end menu @node CByte class-conversion @subsection CByte class:@- conversion @table @b @meindex cObjStoredType @item cObjStoredType Nothing special in the default case - answer a CType for the receiver @meindex type @item type Answer a CType for the receiver @end table @node CByte-accessing @subsection CByte:@- accessing @table @b @meindex cObjStoredType @item cObjStoredType Nothing special in the default case - answer the receiver's CType @meindex value @item value Answer the value the receiver is pointing to. The returned value is a SmallInteger @meindex value:@- @item value:@- aValue Set the receiver to point to the value, aValue (a SmallInteger). @end table @node CCallable @section CCallable @clindex CCallable @table @b @item Defined in namespace Smalltalk @itemx Superclass: CObject @itemx Category: Language-C interface I am not part of the Smalltalk definition. My instances contain information about C functions that can be called from within Smalltalk, such as number and type of parameters. This information is used by the C callout mechanism to perform the actual call-out to C routines. @end table @menu * CCallable class-instance creation:: (class) * CCallable-accessing:: (instance) * CCallable-calling:: (instance) * CCallable-restoring:: (instance) @end menu @node CCallable class-instance creation @subsection CCallable class:@- instance creation @table @b @meindex for:@-returning:@-withArgs:@- @item for:@- aCObject returning:@- returnTypeSymbol withArgs:@- argsArray Answer a CFunctionDescriptor with the given address, return type and arguments. The address will be reset to NULL upon image save (and it's the user's task to figure out a way to reinitialize it!) @end table @node CCallable-accessing @subsection CCallable:@- accessing @table @b @meindex isValid @item isValid Answer whether the object represents a valid function. @meindex returnType @item returnType Not commented. @end table @node CCallable-calling @subsection CCallable:@- calling @table @b @meindex asyncCall @slindex self @slindex selfSmalltalk @item asyncCall Perform the call-out for the function represented by the receiver. The arguments (and the receiver if one of the arguments has type #self or #selfSmalltalk) are taken from the parent context. Asynchronous call-outs don't return a value, but if the function calls back into Smalltalk the process that started the call-out is not suspended. @meindex asyncCallNoRetryFrom:@- @slindex self @slindex selfSmalltalk @slindex asyncCallFrom:@- @item asyncCallNoRetryFrom:@- aContext Perform the call-out for the function represented by the receiver. The arguments (and the receiver if one of the arguments has type #self or #selfSmalltalk) are taken from the base of the stack of aContext. Asynchronous call-outs don't return a value, but if the function calls back into Smalltalk the process that started the call-out is not suspended. Unlike #asyncCallFrom:@-, this method does not attempt to find functions in shared objects. @meindex callInto:@- @slindex self @slindex selfSmalltalk @item callInto:@- aValueHolder Perform the call-out for the function represented by the receiver. The arguments (and the receiver if one of the arguments has type #self or #selfSmalltalk) are taken from the parent context, and the the result is stored into aValueHolder. aValueHolder is also returned. @meindex callNoRetryFrom:@-into:@- @slindex self @slindex selfSmalltalk @slindex callFrom:@-into:@- @item callNoRetryFrom:@- aContext into:@- aValueHolder Perform the call-out for the function represented by the receiver. The arguments (and the receiver if one of the arguments has type #self or #selfSmalltalk) are taken from the base of the stack of aContext, and the result is stored into aValueHolder. aValueHolder is also returned. Unlike #callFrom:@-into:@-, this method does not attempt to find functions in shared objects. @end table @node CCallable-restoring @subsection CCallable:@- restoring @table @b @meindex link @item link Rebuild the object after the image is restarted. @end table @node CCallbackDescriptor @section CCallbackDescriptor @clindex CCallbackDescriptor @table @b @item Defined in namespace Smalltalk @itemx Superclass: CCallable @itemx Category: Language-C interface I am not part of the Smalltalk definition. My instances are able to convert blocks into C functions that can be passed to C. @end table @menu * CCallbackDescriptor class-instance creation:: (class) * CCallbackDescriptor-accessing:: (instance) * CCallbackDescriptor-restoring:: (instance) @end menu @node CCallbackDescriptor class-instance creation @subsection CCallbackDescriptor class:@- instance creation @table @b @meindex for:@-returning:@-withArgs:@- @item for:@- aBlock returning:@- returnTypeSymbol withArgs:@- argsArray Answer a CCallbackDescriptor with the given block, return type and arguments. @end table @node CCallbackDescriptor-accessing @subsection CCallbackDescriptor:@- accessing @table @b @meindex block @item block Answer the block of the function represented by the receiver. @meindex block:@- @item block:@- aBlock Set the block of the function represented by the receiver. @end table @node CCallbackDescriptor-restoring @subsection CCallbackDescriptor:@- restoring @table @b @meindex link @item link Make the address of the function point to the registered address. @end table @node CChar @section CChar @clindex CChar @table @b @item Defined in namespace Smalltalk @itemx Superclass: CScalar @itemx Category: Language-C interface @end table @menu * CChar class-accessing:: (class) * CChar-accessing:: (instance) * CChar-conversion:: (instance) @end menu @node CChar class-accessing @subsection CChar class:@- accessing @table @b @meindex alignof @item alignof Answer the receiver's instances required aligment @meindex cObjStoredType @item cObjStoredType Private - Answer an index referring to the receiver's instances scalar type @meindex sizeof @item sizeof Answer the receiver's instances size @end table @node CChar-accessing @subsection CChar:@- accessing @table @b @meindex alignof @item alignof Answer the receiver's required aligment @meindex cObjStoredType @item cObjStoredType Private - Answer an index referring to the receiver's scalar type @meindex sizeof @item sizeof Answer the receiver's size @end table @node CChar-conversion @subsection CChar:@- conversion @table @b @meindex asByteArray:@- @item asByteArray:@- size Convert size bytes pointed to by the receiver to a String @meindex asString @item asString Convert the data pointed to by the receiver, up to the first NULL byte, to a String @meindex asString:@- @item asString:@- size Convert size bytes pointed to by the receiver to a String @end table @node CCompound @section CCompound @clindex CCompound @table @b @item Defined in namespace Smalltalk @itemx Superclass: CObject @itemx Category: Language-C interface @end table @menu * CCompound class-instance creation:: (class) * CCompound class-subclass creation:: (class) * CCompound-debugging:: (instance) @end menu @node CCompound class-instance creation @subsection CCompound class:@- instance creation @table @b @meindex gcNew @item gcNew Allocate a new instance of the receiver, backed by garbage-collected storage. @meindex new @slindex addToBeFinalized @item new Allocate a new instance of the receiver. To free the memory after GC, remember to call #addToBeFinalized. @end table @node CCompound class-subclass creation @subsection CCompound class:@- subclass creation @table @b @meindex alignof @item alignof Answer 1, the alignment of an empty struct @meindex classPragmas @item classPragmas Return the pragmas that are written in the file-out of this class. @meindex compileSize:@-align:@- @item compileSize:@- size align:@- alignment Private - Compile sizeof and alignof methods @meindex declaration @item declaration Return the description of the fields in the receiver class. @meindex declaration:@- @item declaration:@- array This method's functionality should be implemented by subclasses of CCompound @meindex declaration:@-inject:@-into:@- @item declaration:@- array inject:@- startOffset into:@- aBlock Compile methods that implement the declaration in array. To compute the offset after each field, the value of the old offset plus the new field's size is passed to aBlock, together with the new field's alignment requirements. @meindex emitFieldNameTo:@-for:@- @slindex examineOn:@- @item emitFieldNameTo:@- str for:@- name Private - Emit onto the given stream the code for adding the given selector to the CCompound's #examineOn:@- method. @meindex newStruct:@-declaration:@- @slindex subclass:@-declaration:@- @item newStruct:@- structName declaration:@- array The old way to create a CStruct. Superseded by #subclass:@-declaration:@-... @meindex sizeof @item sizeof Answer 0, the size of an empty struct @meindex subclass:@-declaration:@-classVariableNames:@-poolDictionaries:@-category:@- @item subclass:@- structName declaration:@- array classVariableNames:@- cvn poolDictionaries:@- pd category:@- category Create a new class with the given name that contains code to implement the given C struct. All the parameters except `array' are the same as for a standard class creation message; see documentation for more information @end table @node CCompound-debugging @subsection CCompound:@- debugging @table @b @meindex examineOn:@- @item examineOn:@- aStream Print the contents of the receiver's fields on aStream @meindex fieldSelectorList @slindex examineOn:@- @item fieldSelectorList Answer a list of selectors whose return values should be printed by #examineOn:@-. @end table @node CDouble @section CDouble @clindex CDouble @table @b @item Defined in namespace Smalltalk @itemx Superclass: CScalar @itemx Category: Language-C interface @end table @menu * CDouble class-accessing:: (class) * CDouble-accessing:: (instance) @end menu @node CDouble class-accessing @subsection CDouble class:@- accessing @table @b @meindex alignof @item alignof Answer the receiver's instances required aligment @meindex cObjStoredType @item cObjStoredType Private - Answer an index referring to the receiver's instances scalar type @meindex sizeof @item sizeof Answer the receiver's instances size @end table @node CDouble-accessing @subsection CDouble:@- accessing @table @b @meindex alignof @item alignof Answer the receiver's required aligment @meindex cObjStoredType @item cObjStoredType Private - Answer an index referring to the receiver's scalar type @meindex sizeof @item sizeof Answer the receiver's size @end table @node CFloat @section CFloat @clindex CFloat @table @b @item Defined in namespace Smalltalk @itemx Superclass: CScalar @itemx Category: Language-C interface @end table @menu * CFloat class-accessing:: (class) * CFloat-accessing:: (instance) @end menu @node CFloat class-accessing @subsection CFloat class:@- accessing @table @b @meindex alignof @item alignof Answer the receiver's instances required aligment @meindex cObjStoredType @item cObjStoredType Private - Answer an index referring to the receiver's instances scalar type @meindex sizeof @item sizeof Answer the receiver's instances size @end table @node CFloat-accessing @subsection CFloat:@- accessing @table @b @meindex alignof @item alignof Answer the receiver's required aligment @meindex cObjStoredType @item cObjStoredType Private - Answer an index referring to the receiver's scalar type @meindex sizeof @item sizeof Answer the receiver's size @end table @node CFunctionDescriptor @section CFunctionDescriptor @clindex CFunctionDescriptor @table @b @item Defined in namespace Smalltalk @itemx Superclass: CCallable @itemx Category: Language-C interface I am not part of the Smalltalk definition. My instances contain information about C functions that can be called from within Smalltalk, such as number and type of parameters. This information is used by the C callout mechanism to perform the actual call-out to C routines. @end table @menu * CFunctionDescriptor class-instance creation:: (class) * CFunctionDescriptor class-testing:: (class) * CFunctionDescriptor-accessing:: (instance) * CFunctionDescriptor-printing:: (instance) * CFunctionDescriptor-restoring:: (instance) @end menu @node CFunctionDescriptor class-instance creation @subsection CFunctionDescriptor class:@- instance creation @table @b @meindex for:@-returning:@-withArgs:@- @item for:@- funcName returning:@- returnTypeSymbol withArgs:@- argsArray Answer a CFunctionDescriptor with the given function name, return type and arguments. funcName must be a String. @end table @node CFunctionDescriptor class-testing @subsection CFunctionDescriptor class:@- testing @table @b @meindex addressOf:@- @item addressOf:@- function Answer whether a function is registered (on the C side) with the given name or is dynamically loadable. @meindex isFunction:@- @item isFunction:@- function Answer whether a function is registered (on the C side) with the given name. @end table @node CFunctionDescriptor-accessing @subsection CFunctionDescriptor:@- accessing @table @b @meindex name @item name Answer the name of the function (on the C side) represented by the receiver @meindex name:@- @item name:@- aString Set the name of the function (on the C side) represented by the receiver @end table @node CFunctionDescriptor-printing @subsection CFunctionDescriptor:@- printing @table @b @meindex printOn:@- @item printOn:@- aStream Print a representation of the receiver onto aStream @end table @node CFunctionDescriptor-restoring @subsection CFunctionDescriptor:@- restoring @table @b @meindex link @item link Make the address of the function point to the registered address. @end table @node Character @section Character @clindex Character @table @b @item Defined in namespace Smalltalk @itemx Superclass: Magnitude @itemx Category: Language-Data types My instances represent the 256 characters of the character set. I provide messages to translate between integers and character objects, and provide names for some of the common unprintable characters. Character is always used (mostly for performance reasons) when referring to characters whose code point is between 0 and 127. Above 127, instead, more care is needed:@- Character refers to bytes that are used as part of encoding of a character, while UnicodeCharacter refers to the character itself. @end table @menu * Character class-built ins:: (class) * Character class-constants:: (class) * Character class-initializing lookup tables:: (class) * Character class-instance creation:: (class) * Character class-testing:: (class) * Character-built ins:: (instance) * Character-coercion methods:: (instance) * Character-comparing:: (instance) * Character-converting:: (instance) * Character-printing:: (instance) * Character-storing:: (instance) * Character-testing:: (instance) * Character-testing functionality:: (instance) @end menu @node Character class-built ins @subsection Character class:@- built ins @table @b @meindex asciiValue:@- @item asciiValue:@- anInteger Returns the character object corresponding to anInteger. Error if anInteger is not an integer, or not in 0..127. @meindex codePoint:@- @item codePoint:@- anInteger Returns the character object, possibly an UnicodeCharacter, corresponding to anInteger. Error if anInteger is not an integer, or not in 0..16r10FFFF. @meindex value:@- @item value:@- anInteger Returns the character object corresponding to anInteger. Error if anInteger is not an integer, or not in 0..255. @end table @node Character class-constants @subsection Character class:@- constants @table @b @meindex backspace @item backspace Returns the character 'backspace' @meindex bell @item bell Returns the character 'bel' @meindex cr @item cr Returns the character 'cr' @meindex eof @item eof Returns the character 'eof', also known as 'sub' @meindex eot @item eot Returns the character 'eot', also known as 'Ctrl-D' @meindex esc @item esc Returns the character 'esc' @meindex ff @item ff Returns the character 'ff', also known as 'newPage' @meindex lf @item lf Returns the character 'lf', also known as 'nl' @meindex newPage @item newPage Returns the character 'newPage', also known as 'ff' @meindex nl @item nl Returns the character 'nl', also known as 'lf' @meindex nul @item nul Returns the character 'nul' @meindex space @item space Returns the character 'space' @meindex tab @item tab Returns the character 'tab' @end table @node Character class-initializing lookup tables @subsection Character class:@- initializing lookup tables @table @b @meindex initialize @item initialize Initialize the lookup table which is used to make case and digit-to-char conversions faster. Indices in Table are ASCII values incremented by one. Indices 1-256 classify chars (0 = nothing special, 2 = separator, 48 = digit, 55 = uppercase, 3 = lowercase), indices 257-512 map to lowercase chars, indices 513-768 map to uppercase chars. @end table @node Character class-instance creation @subsection Character class:@- instance creation @table @b @meindex digitValue:@- @item digitValue:@- anInteger Returns a character that corresponds to anInteger. 0-9 map to $0-$9, 10-35 map to $A-$Z @end table @node Character class-testing @subsection Character class:@- testing @table @b @meindex isImmediate @item isImmediate Answer whether, if x is an instance of the receiver, x copy == x @end table @node Character-built ins @subsection Character:@- built ins @table @b @meindex = @item = char Boolean return value; true if the characters are equal @meindex asInteger @slindex codePoint @slindex asciiValue @slindex value @slindex asInteger @item asInteger Returns the integer value corresponding to self. #codePoint, #asciiValue, #value, and #asInteger are synonyms. @meindex asciiValue @slindex codePoint @slindex asciiValue @slindex value @slindex asInteger @item asciiValue Returns the integer value corresponding to self. #codePoint, #asciiValue, #value, and #asInteger are synonyms. @meindex codePoint @slindex codePoint @slindex asciiValue @slindex value @slindex asInteger @item codePoint Returns the integer value corresponding to self. #codePoint, #asciiValue, #value, and #asInteger are synonyms. @meindex value @slindex codePoint @slindex asciiValue @slindex value @slindex asInteger @item value Returns the integer value corresponding to self. #codePoint, #asciiValue, #value, and #asInteger are synonyms. @end table @node Character-coercion methods @subsection Character:@- coercion methods @table @b @meindex * @item * aNumber Returns a String with aNumber occurrences of the receiver. @meindex asLowercase @item asLowercase Returns self as a lowercase character if it's an uppercase letter, otherwise returns the character unchanged. @meindex asString @item asString Returns the character self as a string. Only valid if the character is between 0 and 255. @meindex asSymbol @item asSymbol Returns the character self as a symbol. @meindex asUnicodeString @item asUnicodeString Returns the character self as a Unicode string. @meindex asUppercase @item asUppercase Returns self as a uppercase character if it's an lowercase letter, otherwise returns the character unchanged. @end table @node Character-comparing @subsection Character:@- comparing @table @b @meindex < @item < aCharacter Compare the character's ASCII value. Answer whether the receiver's is the least. @meindex <= @item <= aCharacter Compare the character's ASCII value. Answer whether the receiver's is the least or their equal. @meindex > @item > aCharacter Compare the character's ASCII value. Answer whether the receiver's is the greatest. @meindex >= @item >= aCharacter Compare the character's ASCII value. Answer whether the receiver's is the greatest or their equal. @end table @node Character-converting @subsection Character:@- converting @table @b @meindex asCharacter @item asCharacter Return the receiver, since it is already a character. @meindex digitValue @item digitValue Returns the value of self interpreted as a digit. Here, 'digit' means either 0-9, or A-Z, which maps to 10-35. @end table @node Character-printing @subsection Character:@- printing @table @b @meindex displayOn:@- @slindex printOn:@- @item displayOn:@- aStream Print a representation of the receiver on aStream. Unlike #printOn:@-, this method strips the leading dollar. @meindex printOn:@- @item printOn:@- aStream Print a representation of the receiver on aStream @meindex storeLiteralOn:@- @item storeLiteralOn:@- aStream Store on aStream some Smalltalk code which compiles to the receiver @end table @node Character-storing @subsection Character:@- storing @table @b @meindex isLiteralObject @item isLiteralObject Answer whether the receiver is expressible as a Smalltalk literal. @meindex storeOn:@- @item storeOn:@- aStream Store Smalltalk code compiling to the receiver on aStream @end table @node Character-testing @subsection Character:@- testing @table @b @meindex isAlphaNumeric @item isAlphaNumeric True if self is a letter or a digit @meindex isDigit @item isDigit True if self is a 0-9 digit @meindex isDigit:@- @item isDigit:@- radix Answer whether the receiver is a valid character in the given radix. @meindex isLetter @item isLetter True if self is an upper- or lowercase letter @meindex isLowercase @item isLowercase True if self is a lowercase letter @meindex isPathSeparator @item isPathSeparator Returns true if self is a path separator ($/ or $\ under Windows, $/ only under Unix systems including Mac OS X). @meindex isPunctuation @item isPunctuation Returns true if self is one of '.,:@-;!?' @meindex isSeparator @item isSeparator Returns true if self is a space, cr, tab, nl, or newPage @meindex isUppercase @item isUppercase True if self is uppercase @meindex isVowel @item isVowel Returns true if self is a, e, i, o, or u; case insensitive @end table @node Character-testing functionality @subsection Character:@- testing functionality @table @b @meindex isCharacter @item isCharacter Answer True. We're definitely characters @end table @node CharacterArray @section CharacterArray @clindex CharacterArray @table @b @item Defined in namespace Smalltalk @itemx Superclass: ArrayedCollection @itemx Category: Collections-Text My instances represent a generic textual (string) data type. I provide accessing and manipulation methods for strings. @end table @menu * CharacterArray class-basic:: (class) * CharacterArray class-multibyte encodings:: (class) * CharacterArray-basic:: (instance) * CharacterArray-built ins:: (instance) * CharacterArray-comparing:: (instance) * CharacterArray-converting:: (instance) * CharacterArray-multibyte encodings:: (instance) * CharacterArray-still unclassified:: (instance) * CharacterArray-string processing:: (instance) * CharacterArray-testing functionality:: (instance) @end menu @node CharacterArray class-basic @subsection CharacterArray class:@- basic @table @b @meindex fromString:@- @item fromString:@- aCharacterArray Make up an instance of the receiver containing the same characters as aCharacterArray, and answer it. @meindex lineDelimiter @item lineDelimiter Answer a CharacterArray which one can use as a line delimiter. This is meant to be used on subclasses of CharacterArray. @end table @node CharacterArray class-multibyte encodings @subsection CharacterArray class:@- multibyte encodings @table @b @meindex isUnicode @item isUnicode Answer whether the receiver stores bytes (i.e. an encoded form) or characters (if true is returned). @end table @node CharacterArray-basic @subsection CharacterArray:@- basic @table @b @meindex valueAt:@-ifAbsent:@- @item valueAt:@- anIndex ifAbsent:@- aBlock Answer the ascii value of the anIndex-th character of the receiver, or evaluate aBlock and answer the result if the index is out of range. @end table @node CharacterArray-built ins @subsection CharacterArray:@- built ins @table @b @meindex valueAt:@- @item valueAt:@- index Answer the ascii value of index-th character variable of the receiver @meindex valueAt:@-put:@- @item valueAt:@- index put:@- value Store (Character value:@- value) in the index-th indexed instance variable of the receiver @end table @node CharacterArray-comparing @subsection CharacterArray:@- comparing @table @b @meindex < @item < aCharacterArray Return true if the receiver is less than aCharacterArray, ignoring case differences. @meindex <= @item <= aCharacterArray Returns true if the receiver is less than or equal to aCharacterArray, ignoring case differences. If is receiver is an initial substring of aCharacterArray, it is considered to be less than aCharacterArray. @meindex = @item = aString Answer whether the receiver's items match those in aCollection @meindex > @item > aCharacterArray Return true if the receiver is greater than aCharacterArray, ignoring case differences. @meindex >= @item >= aCharacterArray Returns true if the receiver is greater than or equal to aCharacterArray, ignoring case differences. If is aCharacterArray is an initial substring of the receiver, it is considered to be less than the receiver. @meindex indexOf:@-matchCase:@-startingAt:@- @item indexOf:@- aCharacterArray matchCase:@- aBoolean startingAt:@- anIndex Answer an Interval of indices in the receiver which match the aCharacterArray pattern. # in aCharacterArray means 'match any character', * in aCharacterArray means 'match any sequence of characters'. The first item of the returned interval is >= anIndex. If aBoolean is false, the search is case-insensitive, else it is case-sensitive. If no Interval matches the pattern, answer nil. @meindex match:@- @item match:@- aCharacterArray Answer whether aCharacterArray matches the pattern contained in the receiver. # in the receiver means 'match any character', * in receiver means 'match any sequence of characters'. @meindex match:@-ignoreCase:@- @item match:@- aCharacterArray ignoreCase:@- aBoolean Answer whether aCharacterArray matches the pattern contained in the receiver. # in the receiver means 'match any character', * in receiver means 'match any sequence of characters'. The case of alphabetic characters is ignored if aBoolean is true. @meindex sameAs:@- @item sameAs:@- aCharacterArray Returns true if the receiver is the same CharacterArray as aCharacterArray, ignoring case differences. @end table @node CharacterArray-converting @subsection CharacterArray:@- converting @table @b @meindex asByteArray @item asByteArray Return the receiver, converted to a ByteArray of ASCII values @meindex asClassPoolKey @item asClassPoolKey Return the receiver, ready to be put in a class pool dictionary @meindex asGlobalKey @item asGlobalKey Return the receiver, ready to be put in the Smalltalk dictionary @meindex asInteger @item asInteger Parse an Integer number from the receiver until the input character is invalid and answer the result at this point @meindex asLowercase @item asLowercase Returns a copy of self as a lowercase CharacterArray @meindex asNumber @item asNumber Parse a Number from the receiver until the input character is invalid and answer the result at this point @meindex asPoolKey @item asPoolKey Return the receiver, ready to be put in a pool dictionary @meindex asString @item asString But I already am a String! Really! @meindex asSymbol @item asSymbol Returns the symbol corresponding to the CharacterArray @meindex asUnicodeString @item asUnicodeString Answer a UnicodeString whose character's codes are the receiver's contents This is not implemented unless you load the I18N package. @meindex asUppercase @item asUppercase Returns a copy of self as an uppercase CharacterArray @meindex fileName @item fileName But I don't HAVE a file name! @meindex filePos @item filePos But I don't HAVE a file position! @meindex isNumeric @item isNumeric Answer whether the receiver denotes a number @meindex trimSeparators @item trimSeparators Return a copy of the reciever without any spaces on front or back. The implementation is protected against the `all blanks' case. @end table @node CharacterArray-multibyte encodings @subsection CharacterArray:@- multibyte encodings @table @b @meindex encoding @item encoding Answer the encoding used by the receiver. @meindex isUnicode @item isUnicode Answer whether the receiver stores bytes (i.e. an encoded form) or characters (if true is returned). @meindex numberOfCharacters @item numberOfCharacters Answer the number of Unicode characters in the receiver. This is not implemented unless you load the I18N package. @end table @node CharacterArray-still unclassified @subsection CharacterArray:@- still unclassified @table @b @meindex withUnixShellEscapes @item withUnixShellEscapes Answer the receiver with special shell characters converted to a backslash sequence. @meindex withWindowsShellEscapes @item withWindowsShellEscapes Answer the receiver with Windows shell characters escaped properly. @end table @node CharacterArray-string processing @subsection CharacterArray:@- string processing @table @b @meindex % @item % aCollection Answer the receiver with special escape sequences replaced by elements of aCollection. %n (1<=n<=9, A<=n<=Z) are replaced by the n-th element of aCollection (A being the 10-th element and so on until the 35th). %(string) sequences are accessed as strings, which makes sense only if aCollection is a Dictionary or LookupTable. In addition, the special pattern %n or %(string) is replaced with one of the two strings depending on the element of aCollection being true or false. The replaced elements are `displayed' (i.e. their displayString is used). @meindex bindWith:@- @item bindWith:@- s1 Answer the receiver with every %1 replaced by the displayString of s1 @meindex bindWith:@-with:@- @item bindWith:@- s1 with:@- s2 Answer the receiver with every %1 or %2 replaced by s1 or s2, respectively. s1 and s2 are `displayed' (i.e. their displayString is used) upon replacement. @meindex bindWith:@-with:@-with:@- @item bindWith:@- s1 with:@- s2 with:@- s3 Answer the receiver with every %1, %2 or %3 replaced by s1, s2 or s3, respectively. s1, s2 and s3 are `displayed' (i.e. their displayString is used) upon replacement. @meindex bindWith:@-with:@-with:@-with:@- @item bindWith:@- s1 with:@- s2 with:@- s3 with:@- s4 Answer the receiver with every %1, %2, %3 or %4 replaced by s1, s2, s3 or s4, respectively. s1, s2, s3 and s4 are `displayed' (i.e. their displayString is used) upon replacement. @meindex bindWithArguments:@- @item bindWithArguments:@- aCollection Answer the receiver with special escape sequences replaced by elements of aCollection. %n (1<=n<=9, A<=n<=Z) are replaced by the n-th element of aCollection (A being the 10-th element and so on until the 35th). %(string) sequences are accessed as strings, which makes sense only if aCollection is a Dictionary or LookupTable. In addition, the special pattern %n or %(string) is replaced with one of the two strings depending on the element of aCollection being true or false. The replaced elements are `displayed' (i.e. their displayString is used). @meindex contractTo:@- @item contractTo:@- smallSize Either return myself, or a copy shortened to smallSize characters by inserting an ellipsis (three dots:@- ...) @meindex lines @item lines Answer an Array of Strings each representing one line in the receiver. @meindex linesDo:@- @item linesDo:@- aBlock Evaluate aBlock once for every newline delimited line in the receiver, passing the line to the block. @meindex subStrings @item subStrings Answer an OrderedCollection of substrings of the receiver. A new substring start at the start of the receiver, or after every sequence of white space characters @meindex subStrings:@- @item subStrings:@- sep Answer an OrderedCollection of substrings of the receiver. A new substring start at the start of the receiver, or after every occurrence of one of the characters in sep @meindex substrings @item substrings Answer an OrderedCollection of substrings of the receiver. A new substring start at the start of the receiver, or after every sequence of white space characters. This message is preserved for backwards compatibility; the ANSI standard mandates `subStrings', with an uppercase s. @meindex substrings:@- @item substrings:@- sep Answer an OrderedCollection of substrings of the receiver. A new substring start at the start of the receiver, or after every occurrence of one of the characters in sep. This message is preserved for backwards compatibility; the ANSI standard mandates `subStrings:@-', with an uppercase s. @meindex withShellEscapes @item withShellEscapes Answer the receiver with special shell characters converted to a backslash sequence. @end table @node CharacterArray-testing functionality @subsection CharacterArray:@- testing functionality @table @b @meindex isCharacterArray @item isCharacterArray Answer `true'. @end table @node CInt @section CInt @clindex CInt @table @b @item Defined in namespace Smalltalk @itemx Superclass: CScalar @itemx Category: Language-C interface @end table @menu * CInt class-accessing:: (class) * CInt-accessing:: (instance) @end menu @node CInt class-accessing @subsection CInt class:@- accessing @table @b @meindex alignof @item alignof Answer the receiver's required aligment @meindex cObjStoredType @item cObjStoredType Private - Answer an index referring to the receiver's instances scalar type @meindex sizeof @item sizeof Answer the receiver's size @end table @node CInt-accessing @subsection CInt:@- accessing @table @b @meindex alignof @item alignof Answer the receiver's instances required aligment @meindex cObjStoredType @item cObjStoredType Private - Answer an index referring to the receiver's scalar type @meindex sizeof @item sizeof Answer the receiver's instances size @end table @node Class @section Class @clindex Class @table @b @item Defined in namespace Smalltalk @itemx Superclass: ClassDescription @itemx Category: Language-Implementation I am THE class object. My instances are the classes of the system. I provide information commonly attributed to classes:@- namely, the class name, class comment (you wouldn't be reading this if it weren't for me), a list of the instance variables of the class, and the class category. @end table @menu * Class class-initialize:: (class) * Class-accessing instances and variables:: (instance) * Class-filing:: (instance) * Class-instance creation:: (instance) * Class-instance creation - alternative:: (instance) * Class-pragmas:: (instance) * Class-printing:: (instance) * Class-saving and loading:: (instance) * Class-security:: (instance) * Class-still unclassified:: (instance) * Class-testing:: (instance) * Class-testing functionality:: (instance) @end menu @node Class class-initialize @subsection Class class:@- initialize @table @b @meindex initialize @item initialize Perform the special initialization of root classes. @end table @node Class-accessing instances and variables @subsection Class:@- accessing instances and variables @table @b @meindex addClassVarName:@- @item addClassVarName:@- aString Add a class variable with the given name to the class pool dictionary. @meindex addClassVarName:@-value:@- @item addClassVarName:@- aString value:@- valueBlock Add a class variable with the given name to the class pool dictionary, and evaluate valueBlock as its initializer. @meindex addSharedPool:@- @item addSharedPool:@- aDictionary Add the given shared pool to the list of the class' pool dictionaries @meindex allClassVarNames @item allClassVarNames Answer the names of the variables in the receiver's class pool dictionary and in each of the superclasses' class pool dictionaries @meindex bindingFor:@- @item bindingFor:@- aString Answer the variable binding for the class variable with the given name @meindex category @item category Answer the class category @meindex category:@- @item category:@- aString Change the class category to aString @meindex classPool @item classPool Answer the class pool dictionary @meindex classPragmas @item classPragmas Return the pragmas that are written in the file-out of this class. @meindex classVarNames @item classVarNames Answer the names of the variables in the class pool dictionary @meindex comment @item comment Answer the class comment @meindex comment:@- @item comment:@- aString Change the class name @meindex environment @item environment Answer `environment'. @meindex environment:@- @item environment:@- aNamespace Set the receiver's environment to aNamespace and recompile everything @meindex initialize @item initialize redefined in children (?) @meindex initializeAsRootClass @item initializeAsRootClass Perform special initialization reserved to root classes. @meindex name @item name Answer the class name @meindex removeClassVarName:@- @item removeClassVarName:@- aString Removes the class variable from the class, error if not present, or still in use. @meindex removeSharedPool:@- @item removeSharedPool:@- aDictionary Remove the given dictionary to the list of the class' pool dictionaries @meindex sharedPools @item sharedPools Return the names of the shared pools defined by the class @meindex superclass:@- @item superclass:@- aClass Set the receiver's superclass. @end table @node Class-filing @subsection Class:@- filing @table @b @meindex fileOutDeclarationOn:@- @item fileOutDeclarationOn:@- aFileStream File out class definition to aFileStream. Requires package Parser. @meindex fileOutOn:@- @item fileOutOn:@- aFileStream File out complete class description:@- class definition, class and instance methods. Requires package Parser. @end table @node Class-instance creation @subsection Class:@- instance creation @table @b @meindex extend @item extend Redefine a version of the receiver in the current namespace. Note:@- this method can bite you in various ways when sent to system classes; read the section on namespaces in the manual for some examples of the problems you can encounter. @meindex inheritShape @item inheritShape Answer whether subclasses will have by default the same shape as this class. The default is false. @meindex subclass:@- @item subclass:@- classNameString Define a subclass of the receiver with the given name. If the class is already defined, don't modify its instance or class variables but still, if necessary, recompile everything needed. @meindex subclass:@-instanceVariableNames:@-classVariableNames:@-poolDictionaries:@-category:@- @item subclass:@- classNameString instanceVariableNames:@- stringInstVarNames classVariableNames:@- stringOfClassVarNames poolDictionaries:@- stringOfPoolNames category:@- categoryNameString Define a fixed subclass of the receiver with the given name, instance variables, class variables, pool dictionaries and category. If the class is already defined, if necessary, recompile everything needed. @meindex variable:@-subclass:@-instanceVariableNames:@-classVariableNames:@-poolDictionaries:@-category:@- @slindex byte @slindex int8 @slindex character @slindex short @slindex ushort @slindex int @slindex uint @slindex int64 @slindex uint64 @slindex utf32 @slindex float @slindex double @slindex pointer @item variable:@- shape subclass:@- classNameString instanceVariableNames:@- stringInstVarNames classVariableNames:@- stringOfClassVarNames poolDictionaries:@- stringOfPoolNames category:@- categoryNameString Define a variable subclass of the receiver with the given name, shape, instance variables, class variables, pool dictionaries and category. If the class is already defined, if necessary, recompile everything needed. The shape can be one of #byte #int8 #character #short #ushort #int #uint #int64 #uint64 #utf32 #float #double or #pointer. @meindex variableByteSubclass:@-instanceVariableNames:@-classVariableNames:@-poolDictionaries:@-category:@- @item variableByteSubclass:@- classNameString instanceVariableNames:@- stringInstVarNames classVariableNames:@- stringOfClassVarNames poolDictionaries:@- stringOfPoolNames category:@- categoryNameString Define a byte variable subclass of the receiver with the given name, instance variables (must be ''), class variables, pool dictionaries and category. If the class is already defined, if necessary, recompile everything needed. @meindex variableSubclass:@-instanceVariableNames:@-classVariableNames:@-poolDictionaries:@-category:@- @item variableSubclass:@- classNameString instanceVariableNames:@- stringInstVarNames classVariableNames:@- stringOfClassVarNames poolDictionaries:@- stringOfPoolNames category:@- categoryNameString Define a variable pointer subclass of the receiver with the given name, instance variables, class variables, pool dictionaries and category. If the class is already defined, if necessary, recompile everything needed. @meindex variableWordSubclass:@-instanceVariableNames:@-classVariableNames:@-poolDictionaries:@-category:@- @item variableWordSubclass:@- classNameString instanceVariableNames:@- stringInstVarNames classVariableNames:@- stringOfClassVarNames poolDictionaries:@- stringOfPoolNames category:@- categoryNameString Define a word variable subclass of the receiver with the given name, instance variables (must be ''), class variables, pool dictionaries and category. If the class is already defined, if necessary, recompile everything needed. @end table @node Class-instance creation - alternative @subsection Class:@- instance creation - alternative @table @b @meindex categoriesFor:@-are:@- @item categoriesFor:@- method are:@- categories Don't use this, it is only present to file in from IBM Smalltalk @meindex subclass:@-classInstanceVariableNames:@-instanceVariableNames:@-classVariableNames:@-poolDictionaries:@- @item subclass:@- classNameString classInstanceVariableNames:@- stringClassInstVarNames instanceVariableNames:@- stringInstVarNames classVariableNames:@- stringOfClassVarNames poolDictionaries:@- stringOfPoolNames Don't use this, it is only present to file in from IBM Smalltalk @meindex subclass:@-instanceVariableNames:@-classVariableNames:@-poolDictionaries:@- @item subclass:@- classNameString instanceVariableNames:@- stringInstVarNames classVariableNames:@- stringOfClassVarNames poolDictionaries:@- stringOfPoolNames Don't use this, it is only present to file in from IBM Smalltalk @meindex variableByteSubclass:@-classInstanceVariableNames:@-classVariableNames:@-poolDictionaries:@- @item variableByteSubclass:@- classNameString classInstanceVariableNames:@- stringClassInstVarNames classVariableNames:@- stringOfClassVarNames poolDictionaries:@- stringOfPoolNames Don't use this, it is only present to file in from IBM Smalltalk @meindex variableByteSubclass:@-classVariableNames:@-poolDictionaries:@- @item variableByteSubclass:@- classNameString classVariableNames:@- stringOfClassVarNames poolDictionaries:@- stringOfPoolNames Don't use this, it is only present to file in from IBM Smalltalk @meindex variableLongSubclass:@-classInstanceVariableNames:@-classVariableNames:@-poolDictionaries:@- @item variableLongSubclass:@- classNameString classInstanceVariableNames:@- stringClassInstVarNames classVariableNames:@- stringOfClassVarNames poolDictionaries:@- stringOfPoolNames Don't use this, it is only present to file in from IBM Smalltalk @meindex variableLongSubclass:@-classVariableNames:@-poolDictionaries:@- @item variableLongSubclass:@- classNameString classVariableNames:@- stringOfClassVarNames poolDictionaries:@- stringOfPoolNames Don't use this, it is only present to file in from IBM Smalltalk @meindex variableSubclass:@-classInstanceVariableNames:@-instanceVariableNames:@-classVariableNames:@-poolDictionaries:@- @item variableSubclass:@- classNameString classInstanceVariableNames:@- stringClassInstVarNames instanceVariableNames:@- stringInstVarNames classVariableNames:@- stringOfClassVarNames poolDictionaries:@- stringOfPoolNames Don't use this, it is only present to file in from IBM Smalltalk @meindex variableSubclass:@-instanceVariableNames:@-classVariableNames:@-poolDictionaries:@- @item variableSubclass:@- classNameString instanceVariableNames:@- stringInstVarNames classVariableNames:@- stringOfClassVarNames poolDictionaries:@- stringOfPoolNames Don't use this, it is only present to file in from IBM Smalltalk @end table @node Class-pragmas @subsection Class:@- pragmas @table @b @meindex pragmaHandlerFor:@- @item pragmaHandlerFor:@- aSymbol Answer the (possibly inherited) registered handler for pragma aSymbol, or nil if not found. @meindex registerHandler:@-forPragma:@- @item registerHandler:@- aBlock forPragma:@- pragma While compiling methods, on every encounter of the pragma with the given name, call aBlock with the CompiledMethod and an array of pragma argument values. @end table @node Class-printing @subsection Class:@- printing @table @b @meindex article @item article Answer an article (`a' or `an') which is ok for the receiver's name @meindex printOn:@- @item printOn:@- aStream Print a representation of the receiver on aStream @meindex storeOn:@- @item storeOn:@- aStream Store Smalltalk code compiling to the receiver on aStream @end table @node Class-saving and loading @subsection Class:@- saving and loading @table @b @meindex binaryRepresentationVersion @item binaryRepresentationVersion Answer a number >= 0 which represents the current version of the object's representation. The default implementation answers zero. @meindex convertFromVersion:@-withFixedVariables:@-indexedVariables:@-for:@- @item convertFromVersion:@- version withFixedVariables:@- fixed indexedVariables:@- indexed for:@- anObjectDumper This method is called if a VersionableObjectProxy is attached to a class. It receives the version number that was stored for the object (or nil if the object did not use a VersionableObjectProxy), the fixed instance variables, the indexed instance variables, and the ObjectDumper that has read the object. The default implementation ignores the version and simply fills in an instance of the receiver with the given fixed and indexed instance variables (nil if the class instances are of fixed size). If instance variables were removed from the class, extras are ignored; if the class is now fixed and used to be indexed, indexed is not used. @meindex nonVersionedInstSize @item nonVersionedInstSize Answer the number of instance variables that the class used to have when objects were stored without using a VersionableObjectProxy. The default implementation answers the current instSize. @end table @node Class-security @subsection Class:@- security @table @b @meindex check:@- @item check:@- aPermission Not commented. @meindex securityPolicy @item securityPolicy Answer `securityPolicy'. @meindex securityPolicy:@- @item securityPolicy:@- aSecurityPolicy Not commented. @end table @node Class-still unclassified @subsection Class:@- still unclassified @table @b @meindex allSharedPoolDictionariesDo:@- @item allSharedPoolDictionariesDo:@- aBlock Answer the shared pools visible from methods in the metaclass, in the correct search order. @meindex fileOutHeaderOn:@- @item fileOutHeaderOn:@- aFileStream Not commented. @end table @node Class-testing @subsection Class:@- testing @table @b @meindex = @item = aClass Returns true if the two class objects are to be considered equal. @end table @node Class-testing functionality @subsection Class:@- testing functionality @table @b @meindex asClass @item asClass Answer the receiver. @meindex isClass @item isClass Answer `true'. @end table @node ClassDescription @section ClassDescription @clindex ClassDescription @table @b @item Defined in namespace Smalltalk @itemx Superclass: Behavior @itemx Category: Language-Implementation My instances provide methods that access classes by category, and allow whole categories of classes to be filed out to external disk files. @end table @menu * ClassDescription-compiling:: (instance) * ClassDescription-conversion:: (instance) * ClassDescription-copying:: (instance) * ClassDescription-filing:: (instance) * ClassDescription-organization of messages and classes:: (instance) * ClassDescription-parsing class declarations:: (instance) * ClassDescription-printing:: (instance) * ClassDescription-still unclassified:: (instance) @end menu @node ClassDescription-compiling @subsection ClassDescription:@- compiling @table @b @meindex compile:@-classified:@- @item compile:@- code classified:@- categoryName Compile code in the receiver, assigning the method to the given category. Answer the newly created CompiledMethod, or nil if an error was found. @meindex compile:@-classified:@-ifError:@- @item compile:@- code classified:@- categoryName ifError:@- block Compile method source and install in method category, categoryName. If there are parsing errors, invoke exception block, 'block' (see compile:@-ifError:@-). Return the method @meindex compile:@-classified:@-notifying:@- @item compile:@- code classified:@- categoryName notifying:@- requestor Compile method source and install in method category, categoryName. If there are parsing errors, send an error message to requestor @end table @node ClassDescription-conversion @subsection ClassDescription:@- conversion @table @b @meindex asClass @item asClass This method's functionality should be implemented by subclasses of ClassDescription @meindex asMetaclass @item asMetaclass Answer the metaclass associated to the receiver @meindex binding @item binding Answer a VariableBinding object whose value is the receiver @end table @node ClassDescription-copying @subsection ClassDescription:@- copying @table @b @meindex copy:@-from:@- @item copy:@- selector from:@- aClass Copy the given selector from aClass, assigning it the same category @meindex copy:@-from:@-classified:@- @item copy:@- selector from:@- aClass classified:@- categoryName Copy the given selector from aClass, assigning it the given category @meindex copyAll:@-from:@- @item copyAll:@- arrayOfSelectors from:@- class Copy all the selectors in arrayOfSelectors from class, assigning them the same category they have in class @meindex copyAll:@-from:@-classified:@- @item copyAll:@- arrayOfSelectors from:@- class classified:@- categoryName Copy all the selectors in arrayOfSelectors from aClass, assigning them the given category @meindex copyAllCategoriesFrom:@- @item copyAllCategoriesFrom:@- aClass Copy all the selectors in aClass, assigning them the original category @meindex copyCategory:@-from:@- @item copyCategory:@- categoryName from:@- aClass Copy all the selectors in from aClass that belong to the given category @meindex copyCategory:@-from:@-classified:@- @item copyCategory:@- categoryName from:@- aClass classified:@- newCategoryName Copy all the selectors in from aClass that belong to the given category, reclassifying them as belonging to the given category @end table @node ClassDescription-filing @subsection ClassDescription:@- filing @table @b @meindex fileOut:@- @item fileOut:@- fileName Open the given file and to file out a complete class description to it. Requires package Parser. @meindex fileOutCategory:@-to:@- @item fileOutCategory:@- categoryName to:@- fileName File out all the methods belonging to the method category, categoryName, to the fileName file. Requires package Parser. @meindex fileOutOn:@- @item fileOutOn:@- aFileStream File out complete class description:@- class definition, class and instance methods. Requires package Parser. @meindex fileOutSelector:@-to:@- @item fileOutSelector:@- selector to:@- fileName File out the given selector to fileName. Requires package Parser. @end table @node ClassDescription-organization of messages and classes @subsection ClassDescription:@- organization of messages and classes @table @b @meindex classify:@-under:@- @item classify:@- aSelector under:@- aString Put the method identified by the selector aSelector under the category given by aString. @meindex createGetMethod:@- @item createGetMethod:@- what Create a method accessing the variable `what'. @meindex createGetMethod:@-default:@- @item createGetMethod:@- what default:@- value Create a method accessing the variable `what', with a default value of `value', using lazy initialization @meindex createSetMethod:@- @item createSetMethod:@- what Create a method which sets the variable `what'. @meindex defineAsyncCFunc:@-withSelectorArgs:@-args:@- @item defineAsyncCFunc:@- cFuncNameString withSelectorArgs:@- selectorAndArgs args:@- argsArray See documentation. This function is deprecated, you should use the special syntax instead. @meindex defineCFunc:@-withSelectorArgs:@-returning:@-args:@- @item defineCFunc:@- cFuncNameString withSelectorArgs:@- selectorAndArgs returning:@- returnTypeSymbol args:@- argsArray See documentation. This function is deprecated, you should use the special syntax instead. @meindex removeCategory:@- @item removeCategory:@- aString Remove from the receiver every method belonging to the given category @meindex whichCategoryIncludesSelector:@- @item whichCategoryIncludesSelector:@- selector Answer the category for the given selector, or nil if the selector is not found @end table @node ClassDescription-parsing class declarations @subsection ClassDescription:@- parsing class declarations @table @b @meindex addSharedPool:@- @item addSharedPool:@- aDictionary Add the given shared pool to the list of the class' pool dictionaries @meindex import:@- @item import:@- aDictionary Add the given shared pool to the list of the class' pool dictionaries @end table @node ClassDescription-printing @subsection ClassDescription:@- printing @table @b @meindex classVariableString @item classVariableString This method's functionality should be implemented by subclasses of ClassDescription @meindex instanceVariableString @item instanceVariableString Answer a string containing the name of the receiver's instance variables. @meindex nameIn:@- @item nameIn:@- aNamespace Answer the class name when the class is referenced from aNamespace @meindex printOn:@-in:@- @item printOn:@- aStream in:@- aNamespace Print on aStream the class name when the class is referenced from aNamespace @meindex sharedVariableString @item sharedVariableString This method's functionality should be implemented by subclasses of ClassDescription @end table @node ClassDescription-still unclassified @subsection ClassDescription:@- still unclassified @table @b @meindex fileOutCategory:@-toStream:@- @item fileOutCategory:@- category toStream:@- aFileStream File out all the methods belonging to the method category, category, to aFileStream. Requires package Parser. @meindex fileOutSelector:@-toStream:@- @item fileOutSelector:@- aSymbol toStream:@- aFileStream File out all the methods belonging to the method category, category, to aFileStream. Requires package Parser. @end table @node CLong @section CLong @clindex CLong @table @b @item Defined in namespace Smalltalk @itemx Superclass: CScalar @itemx Category: Language-C interface @end table @menu * CLong class-accessing:: (class) * CLong-accessing:: (instance) @end menu @node CLong class-accessing @subsection CLong class:@- accessing @table @b @meindex alignof @item alignof Answer the receiver's instances required aligment @meindex cObjStoredType @item cObjStoredType Private - Answer an index referring to the receiver's instances scalar type @meindex sizeof @item sizeof Answer the receiver's instances size @end table @node CLong-accessing @subsection CLong:@- accessing @table @b @meindex alignof @item alignof Answer the receiver's required aligment @meindex cObjStoredType @item cObjStoredType Private - Answer an index referring to the receiver's scalar type @meindex sizeof @item sizeof Answer the receiver's size @end table @node CLongDouble @section CLongDouble @clindex CLongDouble @table @b @item Defined in namespace Smalltalk @itemx Superclass: CScalar @itemx Category: Language-C interface @end table @menu * CLongDouble class-accessing:: (class) * CLongDouble-accessing:: (instance) @end menu @node CLongDouble class-accessing @subsection CLongDouble class:@- accessing @table @b @meindex alignof @item alignof Answer the receiver's instances required aligment @meindex cObjStoredType @item cObjStoredType Private - Answer an index referring to the receiver's instances scalar type @meindex sizeof @item sizeof Answer the receiver's instances size @end table @node CLongDouble-accessing @subsection CLongDouble:@- accessing @table @b @meindex alignof @item alignof Answer the receiver's required aligment @meindex cObjStoredType @item cObjStoredType Private - Answer an index referring to the receiver's scalar type @meindex sizeof @item sizeof Answer the receiver's size @end table @node CLongLong @section CLongLong @clindex CLongLong @table @b @item Defined in namespace Smalltalk @itemx Superclass: CScalar @itemx Category: Language-C interface @end table @menu * CLongLong class-accessing:: (class) * CLongLong-accessing:: (instance) @end menu @node CLongLong class-accessing @subsection CLongLong class:@- accessing @table @b @meindex alignof @item alignof Answer the receiver's instances required aligment @meindex cObjStoredType @item cObjStoredType Private - Answer an index referring to the receiver's instances scalar type @meindex sizeof @item sizeof Answer the receiver's instances size @end table @node CLongLong-accessing @subsection CLongLong:@- accessing @table @b @meindex alignof @item alignof Answer the receiver's required aligment @meindex cObjStoredType @item cObjStoredType Private - Answer an index referring to the receiver's scalar type @meindex sizeof @item sizeof Answer the receiver's size @end table @node CObject @section CObject @clindex CObject @table @b @item Defined in namespace Smalltalk @itemx Superclass: Object @itemx Category: Language-C interface I am not part of the standard Smalltalk kernel class hierarchy. My instances contain values that are not interpreted by the Smalltalk system; they frequently hold "pointers" to data outside of the Smalltalk environment. The C callout mechanism allows my instances to be transformed into their corresponding C values for use in external routines. @end table @menu * CObject class-conversion:: (class) * CObject class-instance creation:: (class) * CObject class-primitive allocation:: (class) * CObject class-subclass creation:: (class) * CObject-accessing:: (instance) * CObject-basic:: (instance) * CObject-C data access:: (instance) * CObject-conversion:: (instance) * CObject-finalization:: (instance) * CObject-pointer-like behavior:: (instance) * CObject-testing:: (instance) * CObject-testing functionality:: (instance) @end menu @node CObject class-conversion @subsection CObject class:@- conversion @table @b @meindex type @item type Nothing special in the default case - answer a CType for the receiver @end table @node CObject class-instance creation @subsection CObject class:@- instance creation @table @b @meindex address:@- @item address:@- anInteger Answer a new object pointing to the passed address, anInteger @meindex alloc:@- @item alloc:@- nBytes Allocate nBytes bytes and return an instance of the receiver @meindex gcAlloc:@- @item gcAlloc:@- nBytes Allocate nBytes bytes and return an instance of the receiver @meindex gcNew:@- @item gcNew:@- nBytes Allocate nBytes bytes and return an instance of the receiver @meindex new @item new Answer a new object pointing to NULL. @meindex new:@- @item new:@- nBytes Allocate nBytes bytes and return an instance of the receiver @end table @node CObject class-primitive allocation @subsection CObject class:@- primitive allocation @table @b @meindex alloc:@-type:@- @item alloc:@- nBytes type:@- cTypeObject Allocate nBytes bytes and return a CObject of the given type @meindex gcAlloc:@-type:@- @item gcAlloc:@- nBytes type:@- cTypeObject Allocate nBytes bytes and return a CObject of the given type @end table @node CObject class-subclass creation @subsection CObject class:@- subclass creation @table @b @meindex inheritShape @item inheritShape Answer whether subclasses will have by default the same shape as this class. The default is true for the CObject hierarchy. @end table @node CObject-accessing @subsection CObject:@- accessing @table @b @meindex address @slindex storage @item address Answer the address the receiver is pointing to. The address can be absolute if the storage is nil, or relative to the Smalltalk object in #storage. In this case, an address of 0 corresponds to the first instance variable. @meindex address:@- @item address:@- anInteger Set the receiver to point to the passed address, anInteger @meindex isAbsolute @item isAbsolute Answer whether the object points into a garbage-collected Smalltalk storage, or it is an absolute address. @meindex printOn:@- @item printOn:@- aStream Print a representation of the receiver @meindex storage @item storage Answer the storage that the receiver is pointing into, or nil if the address is absolute. @meindex storage:@- @item storage:@- anObject Change the receiver to point to the storage of anObject. @meindex type:@- @item type:@- aCType Set the receiver's type to aCType. @end table @node CObject-basic @subsection CObject:@- basic @table @b @meindex = @item = anObject Return true if the receiver and aCObject are equal. @meindex hash @item hash Return a hash value for anObject. @end table @node CObject-C data access @subsection CObject:@- C data access @table @b @meindex at:@-put:@-type:@- @item at:@- byteOffset put:@- aValue type:@- aType Store aValue as data of the given type from byteOffset bytes after the pointer stored in the receiver @meindex at:@-type:@- @item at:@- byteOffset type:@- aType Answer some data of the given type from byteOffset bytes after the pointer stored in the receiver @meindex free @item free Free the receiver's pointer and set it to null. Big trouble hits you if the receiver doesn't point to the base of a malloc-ed area. @end table @node CObject-conversion @subsection CObject:@- conversion @table @b @meindex castTo:@- @item castTo:@- aType Answer another CObject, pointing to the same address as the receiver, but belonging to the aType CType. @meindex narrow @slindex cObject @item narrow This method is called on CObjects returned by a C call-out whose return type is specified as a CType; it mostly allows one to change the class of the returned CObject. By default it does nothing, and that's why it is not called when #cObject is used to specify the return type. @meindex type @item type Answer a CType for the receiver @end table @node CObject-finalization @subsection CObject:@- finalization @table @b @meindex finalize @slindex addToBeFinalized @slindex free @item finalize To make the VM call this, use #addToBeFinalized. It frees automatically any memory pointed to by the CObject. It is not automatically enabled because big trouble hits you if you use #free and the receiver doesn't point to the base of a malloc-ed area. @end table @node CObject-pointer-like behavior @subsection CObject:@- pointer-like behavior @table @b @meindex + @item + anInteger Return another instance of the receiver's class which points at &receiver[anInteger] (or, if you prefer, what `receiver + anInteger' does in C). @meindex - @item - intOrPtr If intOrPtr is an integer, return another instance of the receiver's class pointing at &receiver[-anInteger] (or, if you prefer, what `receiver - anInteger' does in C). If it is the same class as the receiver, return the difference in chars, i.e. in bytes, between the two pointed addresses (or, if you prefer, what `receiver - anotherCharPtr' does in C) @meindex addressAt:@- @item addressAt:@- anIndex Return a new CObject of the element type, corresponding to an object that is anIndex places past the receiver (remember that CObjects represent pointers and that C pointers behave like arrays). anIndex is zero-based, just like with all other C-style accessing. @meindex at:@- @item at:@- anIndex Dereference a pointer that is anIndex places past the receiver (remember that CObjects represent pointers and that C pointers behave like arrays). anIndex is zero-based, just like with all other C-style accessing. @meindex at:@-put:@- @item at:@- anIndex put:@- aValue Store anIndex places past the receiver the passed Smalltalk object or CObject `aValue'; if it is a CObject is dereferenced:@- that is, this method is equivalent either to cobj[anIndex]=aValue or cobj[anIndex]=*aValue. anIndex is zero-based, just like with all other C-style accessing. In both cases, aValue should be of the element type or of the corresponding Smalltalk type (that is, a String is ok for an array of CStrings) to avoid typing problems which however will not be signaled because C is untyped. @meindex decr @item decr Adjust the pointer by sizeof(dereferencedType) bytes down (i.e. --receiver) @meindex decrBy:@- @item decrBy:@- anInteger Adjust the pointer by anInteger elements down (i.e. receiver -= anInteger) @meindex incr @item incr Adjust the pointer by sizeof(dereferencedType) bytes up (i.e. ++receiver) @meindex incrBy:@- @item incrBy:@- anInteger Adjust the pointer by anInteger elements up (i.e. receiver += anInteger) @end table @node CObject-testing @subsection CObject:@- testing @table @b @meindex isNull @item isNull Return true if the receiver points to NULL. @end table @node CObject-testing functionality @subsection CObject:@- testing functionality @table @b @meindex isCObject @item isCObject Answer `true'. @end table @node Collection @section Collection @clindex Collection @table @b @item Defined in namespace Smalltalk @itemx Superclass: Iterable @itemx Category: Collections I am an abstract class. My instances are collections of objects. My subclasses may place some restrictions or add some definitions to how the objects are stored or organized; I say nothing about this. I merely provide some object creation and access routines for general collections of objects. @end table @menu * Collection class-instance creation:: (class) * Collection class-multibyte encodings:: (class) * Collection-adding:: (instance) * Collection-compiler:: (instance) * Collection-concatenating:: (instance) * Collection-converting:: (instance) * Collection-copying Collections:: (instance) * Collection-copying SequenceableCollections:: (instance) * Collection-enumeration:: (instance) * Collection-finalization:: (instance) * Collection-printing:: (instance) * Collection-removing:: (instance) * Collection-sorting:: (instance) * Collection-storing:: (instance) * Collection-testing collections:: (instance) @end menu @node Collection class-instance creation @subsection Collection class:@- instance creation @table @b @meindex from:@- @item from:@- anArray Convert anArray to an instance of the receiver. anArray is structured such that the instance can be conveniently and fully specified using brace-syntax, possibly by imposing some additional structure on anArray. @meindex join:@- @item join:@- aCollection Answer a collection formed by treating each element in aCollection as a `withAll:@-' argument collection to be added to a new instance. @meindex with:@- @item with:@- anObject Answer a collection whose only element is anObject @meindex with:@-with:@- @item with:@- firstObject with:@- secondObject Answer a collection whose only elements are the parameters in the order they were passed @meindex with:@-with:@-with:@- @item with:@- firstObject with:@- secondObject with:@- thirdObject Answer a collection whose only elements are the parameters in the order they were passed @meindex with:@-with:@-with:@-with:@- @item with:@- firstObject with:@- secondObject with:@- thirdObject with:@- fourthObject Answer a collection whose only elements are the parameters in the order they were passed @meindex with:@-with:@-with:@-with:@-with:@- @item with:@- firstObject with:@- secondObject with:@- thirdObject with:@- fourthObject with:@- fifthObject Answer a collection whose only elements are the parameters in the order they were passed @meindex withAll:@- @item withAll:@- aCollection Answer a collection whose elements are all those in aCollection @end table @node Collection class-multibyte encodings @subsection Collection class:@- multibyte encodings @table @b @meindex isUnicode @item isUnicode Answer true; the receiver is able to store arbitrary Unicode characters. @end table @node Collection-adding @subsection Collection:@- adding @table @b @meindex add:@- @item add:@- newObject Add newObject to the receiver, answer it @meindex addAll:@- @item addAll:@- aCollection Adds all the elements of 'aCollection' to the receiver, answer aCollection @end table @node Collection-compiler @subsection Collection:@- compiler @table @b @meindex literalEquals:@- @item literalEquals:@- anObject Not commented. @meindex literalHash @item literalHash Not commented. @end table @node Collection-concatenating @subsection Collection:@- concatenating @table @b @meindex join @item join Answer a new collection like my first element, with all the elements (in order) of all my elements, which should be collections. I use my first element instead of myself as a prototype because my elements are more likely to share the desired properties than I am, such as in:@- #('hello, ' 'world') join => 'hello, world' @end table @node Collection-converting @subsection Collection:@- converting @table @b @meindex asArray @item asArray Answer an Array containing all the elements in the receiver @meindex asBag @item asBag Answer a Bag containing all the elements in the receiver @meindex asByteArray @item asByteArray Answer a ByteArray containing all the elements in the receiver @meindex asOrderedCollection @item asOrderedCollection Answer an OrderedCollection containing all the elements in the receiver @meindex asRunArray @slindex do:@- @item asRunArray Answer the receiver converted to a RunArray. If the receiver is not ordered the order of the elements in the RunArray might not be the #do:@- order. @meindex asSet @item asSet Answer a Set containing all the elements in the receiver with no duplicates @meindex asSortedCollection @item asSortedCollection Answer a SortedCollection containing all the elements in the receiver with the default sort block - [ :a :b | a <= b ] @meindex asSortedCollection:@- @item asSortedCollection:@- aBlock Answer a SortedCollection whose elements are the elements of the receiver, sorted according to the sort block aBlock @meindex asString @item asString Answer a String containing all the elements in the receiver @meindex asUnicodeString @item asUnicodeString Answer a UnicodeString containing all the elements in the receiver @end table @node Collection-copying Collections @subsection Collection:@- copying Collections @table @b @meindex copyReplacing:@-withObject:@- @item copyReplacing:@- targetObject withObject:@- newObject Copy replacing each object which is = to targetObject with newObject @meindex copyWith:@- @item copyWith:@- newElement Answer a copy of the receiver to which newElement is added @meindex copyWithout:@- @item copyWithout:@- oldElement Answer a copy of the receiver to which all occurrences of oldElement are removed @end table @node Collection-copying SequenceableCollections @subsection Collection:@- copying SequenceableCollections @table @b @meindex , @slindex add:@- @item , anIterable Append anIterable at the end of a copy of the receiver (using #add:@-), and answer a new collection @end table @node Collection-enumeration @subsection Collection:@- enumeration @table @b @meindex anyOne @item anyOne Answer an unspecified element of the collection. @meindex beConsistent @slindex do:@- @item beConsistent This method is private, but it is quite interesting so it is documented. It ensures that a collection is in a consistent state before attempting to iterate on it; its presence reduces the number of overrides needed by collections who try to amortize their execution times. The default implementation does nothing, so it is optimized out by the virtual machine and so it loses very little on the performance side. Note that descendants of Collection have to call it explicitly since #do:@- is abstract in Collection. @meindex collect:@- @item collect:@- aBlock Answer a new instance of a Collection containing all the results of evaluating aBlock passing each of the receiver's elements @meindex gather:@- @slindex join @item gather:@- aBlock Answer a new instance of a Collection containing all the results of evaluating aBlock, joined together. aBlock should return collections. The result is the same kind as the first collection, returned by aBlock (as for #join). @meindex readStream @item readStream Answer a stream that gives elements of the receiver @meindex reject:@- @item reject:@- aBlock Answer a new instance of a Collection containing all the elements in the receiver which, when passed to aBlock, don't answer true @meindex select:@- @item select:@- aBlock Answer a new instance of a Collection containing all the elements in the receiver which, when passed to aBlock, answer true @end table @node Collection-finalization @subsection Collection:@- finalization @table @b @meindex mourn:@- @item mourn:@- anObject Private - anObject has been found to have a weak key, remove it and possibly finalize the key. @end table @node Collection-printing @subsection Collection:@- printing @table @b @meindex displayLines @item displayLines Print each element of the receiver to a line on standard output. @meindex examineOn:@- @item examineOn:@- aStream Print all the instance variables and objects in the receiver on aStream @meindex printOn:@- @item printOn:@- aStream Print a representation of the receiver on aStream @end table @node Collection-removing @subsection Collection:@- removing @table @b @meindex empty @item empty Remove everything from the receiver. @meindex remove:@- @item remove:@- oldObject Remove oldObject from the receiver. If absent, fail, else answer oldObject. @meindex remove:@-ifAbsent:@- @item remove:@- oldObject ifAbsent:@- anExceptionBlock Remove oldObject from the receiver. If absent, evaluate anExceptionBlock and answer the result, else answer oldObject. @meindex removeAll:@- @item removeAll:@- aCollection Remove each object in aCollection, answer aCollection, fail if some of them is absent. Warning:@- this could leave the collection in a semi-updated state. @meindex removeAll:@-ifAbsent:@- @item removeAll:@- aCollection ifAbsent:@- aBlock Remove each object in aCollection, answer aCollection; if some element is absent, pass it to aBlock. @meindex removeAllSuchThat:@- @item removeAllSuchThat:@- aBlock Remove from the receiver all objects for which aBlock returns true. @end table @node Collection-sorting @subsection Collection:@- sorting @table @b @meindex sorted @slindex <= @item sorted Return a sequenceable collection with the contents of the receiver sorted according to the default sort block, which uses #<= to compare items. @meindex sorted:@- @item sorted:@- sortBlock Return a sequenceable collection with the contents of the receiver sorted according to the given sort block, which accepts pair of items and returns true if the first item is less than the second one. @end table @node Collection-storing @subsection Collection:@- storing @table @b @meindex storeOn:@- @item storeOn:@- aStream Store Smalltalk code compiling to the receiver on aStream @end table @node Collection-testing collections @subsection Collection:@- testing collections @table @b @meindex capacity @item capacity Answer how many elements the receiver can hold before having to grow. @meindex identityIncludes:@- @item identityIncludes:@- anObject Answer whether we include the anObject object @meindex includes:@- @item includes:@- anObject Answer whether we include anObject @meindex includesAllOf:@- @item includesAllOf:@- aCollection Answer whether we include all of the objects in aCollection @meindex includesAnyOf:@- @item includesAnyOf:@- aCollection Answer whether we include any of the objects in aCollection @meindex isEmpty @item isEmpty Answer whether we are (still) empty @meindex isSequenceable @slindex at:@-/@-#at:@-put:@- @item isSequenceable Answer whether the receiver can be accessed by a numeric index with #at:@-/@-#at:@-put:@-. @meindex notEmpty @item notEmpty Answer whether we include at least one object @meindex occurrencesOf:@- @item occurrencesOf:@- anObject Answer how many occurrences of anObject we include @meindex size @item size Answer how many objects we include @end table @node CompiledBlock @section CompiledBlock @clindex CompiledBlock @table @b @item Defined in namespace Smalltalk @itemx Superclass: CompiledCode @itemx Category: Language-Implementation I represent a block that has been compiled. @end table @menu * CompiledBlock class-instance creation:: (class) * CompiledBlock-accessing:: (instance) * CompiledBlock-basic:: (instance) * CompiledBlock-printing:: (instance) * CompiledBlock-saving and loading:: (instance) @end menu @node CompiledBlock class-instance creation @subsection CompiledBlock class:@- instance creation @table @b @meindex new:@-header:@-method:@- @item new:@- numBytecodes header:@- anInteger method:@- outerMethod Answer a new instance of the receiver with room for the given number of bytecodes and the given header. @meindex numArgs:@-numTemps:@-bytecodes:@-depth:@-literals:@- @item numArgs:@- args numTemps:@- temps bytecodes:@- bytecodes depth:@- depth literals:@- literalArray Answer an (almost) full fledged CompiledBlock. To make it complete, you must either set the new object's `method' variable, or put it into a BlockClosure and put the BlockClosure into a CompiledMethod's literals. The clean-ness of the block is automatically computed. @end table @node CompiledBlock-accessing @subsection CompiledBlock:@- accessing @table @b @meindex flags @item flags Answer the `cleanness' of the block. 0 = clean; 1 = access to receiver variables and/or self; 2-30 = access to variables that are 1-29 contexts away; 31 = return from method or push thisContext @meindex method @item method Answer the CompiledMethod in which the receiver lies @meindex methodClass @item methodClass Answer the class in which the receiver is installed. @meindex methodClass:@- @item methodClass:@- methodClass Set the receiver's class instance variable @meindex numArgs @item numArgs Answer the number of arguments passed to the receiver @meindex numLiterals @item numLiterals Answer the number of literals for the receiver @meindex numTemps @item numTemps Answer the number of temporary variables used by the receiver @meindex selector @item selector Answer the selector through which the method is called @meindex selector:@- @item selector:@- aSymbol Set the selector through which the method is called @meindex sourceCodeLinesDelta @item sourceCodeLinesDelta Answer the delta from the numbers in LINE_NUMBER bytecodes to source code line numbers. @meindex sourceCodeMap @item sourceCodeMap Answer an array which maps bytecode indices to source code line numbers. 0 values represent invalid instruction pointer indices. @meindex stackDepth @item stackDepth Answer the number of stack slots needed for the receiver @end table @node CompiledBlock-basic @subsection CompiledBlock:@- basic @table @b @meindex = @item = aMethod Answer whether the receiver and aMethod are equal @meindex methodCategory @item methodCategory Answer the method category @meindex methodCategory:@- @item methodCategory:@- aCategory Set the method category to the given string @meindex methodSourceCode @item methodSourceCode Answer the method source code (a FileSegment or String or nil) @meindex methodSourceFile @item methodSourceFile Answer the file where the method source code is stored @meindex methodSourcePos @item methodSourcePos Answer the location where the method source code is stored in the methodSourceFile @meindex methodSourceString @item methodSourceString Answer the method source code as a string @end table @node CompiledBlock-printing @subsection CompiledBlock:@- printing @table @b @meindex printOn:@- @item printOn:@- aStream Print the receiver's class and selector on aStream @end table @node CompiledBlock-saving and loading @subsection CompiledBlock:@- saving and loading @table @b @meindex binaryRepresentationObject @slindex blockAt:@- @item binaryRepresentationObject This method is implemented to allow for a PluggableProxy to be used with CompiledBlocks. Answer a DirectedMessage which sends #blockAt:@- to the CompiledMethod containing the receiver. @end table @node CompiledCode @section CompiledCode @clindex CompiledCode @table @b @item Defined in namespace Smalltalk @itemx Superclass: ArrayedCollection @itemx Category: Language-Implementation I represent code that has been compiled. I am an abstract superclass for blocks and methods @end table @menu * CompiledCode class-cache flushing:: (class) * CompiledCode class-instance creation:: (class) * CompiledCode class-tables:: (class) * CompiledCode-accessing:: (instance) * CompiledCode-basic:: (instance) * CompiledCode-copying:: (instance) * CompiledCode-debugging:: (instance) * CompiledCode-decoding bytecodes:: (instance) * CompiledCode-literals - iteration:: (instance) * CompiledCode-security:: (instance) * CompiledCode-testing accesses:: (instance) * CompiledCode-translation:: (instance) @end menu @node CompiledCode class-cache flushing @subsection CompiledCode class:@- cache flushing @table @b @meindex flushTranslatorCache @item flushTranslatorCache Answer any kind of cache mantained by a just-in-time code translator in the virtual machine (if any). Do nothing for now. @end table @node CompiledCode class-instance creation @subsection CompiledCode class:@- instance creation @table @b @meindex new:@-header:@-literals:@- @item new:@- numBytecodes header:@- anInteger literals:@- literals Answer a new instance of the receiver with room for the given number of bytecodes and the given header @meindex new:@-header:@-numLiterals:@- @item new:@- numBytecodes header:@- anInteger numLiterals:@- numLiterals Answer a new instance of the receiver with room for the given number of bytecodes and the given header @end table @node CompiledCode class-tables @subsection CompiledCode class:@- tables @table @b @meindex bytecodeInfoTable @item bytecodeInfoTable Return a ByteArray which defines some properties of the bytecodes. For each bytecode, 4 bytes are reserved. The fourth byte is a flag byte:@- bit 7 means that the argument is a line number to be used in creating the bytecode->line number map. The first three have a meaning only for those bytecodes that represent a combination of operations:@- the combination can be BC1 ARG BC2 OPERAND if the fourth byte's bit 0 = 0 or BC1 OPERAND BC2 ARG if the fourth byte's bit 0 = 1 where BC1 is the first byte, BC2 is the second, ARG is the third and OPERAND is the bytecode argument as it appears in the bytecode stream. @meindex specialSelectors @item specialSelectors Answer an array of message names that don't need to be in literals to be sent in a method. Their position here reflects their integer code in bytecode. @meindex specialSelectorsNumArgs @slindex specialSelectors @item specialSelectorsNumArgs Answer a harmoniously-indexed array of arities for the messages answered by #specialSelectors. @end table @node CompiledCode-accessing @subsection CompiledCode:@- accessing @table @b @meindex at:@-put:@- @item at:@- anIndex put:@- aBytecode Store aBytecode as the anIndex-th bytecode @meindex blockAt:@- @item blockAt:@- anIndex Answer the CompiledBlock attached to the anIndex-th literal, assuming that the literal is a CompiledBlock or a BlockClosure. @meindex bytecodeAt:@- @item bytecodeAt:@- anIndex Answer the anIndex-th bytecode @meindex bytecodeAt:@-put:@- @item bytecodeAt:@- anIndex put:@- aBytecode Store aBytecode as the anIndex-th bytecode @meindex flags @item flags Private - Answer the optimization flags for the receiver @meindex isAnnotated @item isAnnotated Answer `false'. @meindex literalAt:@- @item literalAt:@- anIndex Answer the anIndex-th literal @meindex literalAt:@-put:@- @item literalAt:@- anInteger put:@- aValue Store aValue as the anIndex-th literal @meindex literals @item literals Answer the literals referenced by my code or any CompiledCode instances I own. @meindex method @item method Answer the parent method for the receiver, or self if it is a method. @meindex methodClass @item methodClass Answer the class in which the receiver is installed. @meindex methodClass:@- @item methodClass:@- methodClass Set the receiver's class instance variable @meindex numArgs @item numArgs Answer the number of arguments for the receiver @meindex numLiterals @item numLiterals Answer the number of literals for the receiver @meindex numTemps @item numTemps Answer the number of temporaries for the receiver @meindex primitive @item primitive Answer the primitive called by the receiver @meindex selector @item selector Answer the selector through which the method is called @meindex selector:@- @item selector:@- aSymbol Set the selector through which the method is called @meindex sourceCodeLinesDelta @item sourceCodeLinesDelta Answer the delta from the numbers in LINE_NUMBER bytecodes to source code line numbers. @meindex stackDepth @item stackDepth Answer the number of stack slots needed for the receiver @end table @node CompiledCode-basic @subsection CompiledCode:@- basic @table @b @meindex = @slindex # @item = aMethod Answer whether the receiver is the same object as arg. Testing for equality could break the browser, since it's possible to put arbitrary objects via #@-#(...), so this is safer. @meindex hash @item hash Answer an hash value for the receiver @meindex methodCategory @item methodCategory Answer the method category @meindex methodCategory:@- @item methodCategory:@- aCategory Set the method category to the given string @meindex methodSourceCode @item methodSourceCode Answer the method source code (a FileSegment or String or nil) @meindex methodSourceFile @item methodSourceFile Answer the file where the method source code is stored @meindex methodSourcePos @item methodSourcePos Answer the location where the method source code is stored in the methodSourceFile @meindex methodSourceString @item methodSourceString Answer the method source code as a string @end table @node CompiledCode-copying @subsection CompiledCode:@- copying @table @b @meindex deepCopy @item deepCopy Answer a deep copy of the receiver @end table @node CompiledCode-debugging @subsection CompiledCode:@- debugging @table @b @meindex examineOn:@- @item examineOn:@- aStream Print the contents of the receiver in a verbose way. @end table @node CompiledCode-decoding bytecodes @subsection CompiledCode:@- decoding bytecodes @table @b @meindex dispatchTo:@-with:@- @item dispatchTo:@- anObject with:@- param Disassemble the bytecodes and tell anObject about them in the form of message sends. param is given as an argument to every message send. @end table @node CompiledCode-literals - iteration @subsection CompiledCode:@- literals - iteration @table @b @meindex allLiteralSymbolsDo:@- @slindex allLiteralsDo:@- @item allLiteralSymbolsDo:@- aBlock As with #allLiteralsDo:@-, but only call aBlock with found Symbols. @meindex allLiteralsDo:@- @item allLiteralsDo:@- aBlock Walk my literals, descending into Arrays and Messages, invoking aBlock with each touched object. @meindex literalsDo:@- @item literalsDo:@- aBlock Invoke aBlock with each object immediately in my list of literals. @end table @node CompiledCode-security @subsection CompiledCode:@- security @table @b @meindex verify @item verify Verify the bytecodes for the receiver, and raise an exception if the verification process failed. @end table @node CompiledCode-testing accesses @subsection CompiledCode:@- testing accesses @table @b @meindex accesses:@- @item accesses:@- instVarIndex Answer whether the receiver accesses the instance variable with the given index @meindex assigns:@- @item assigns:@- instVarIndex Answer whether the receiver writes to the instance variable with the given index @meindex containsLiteral:@- @item containsLiteral:@- anObject Answer if the receiver contains a literal which is equal to anObject. @meindex hasBytecode:@-between:@-and:@- @item hasBytecode:@- byte between:@- firstIndex and:@- lastIndex Answer whether the receiver includes the `byte' bytecode in any of the indices between firstIndex and lastIndex. @meindex jumpDestinationAt:@-forward:@- @item jumpDestinationAt:@- anIndex forward:@- aBoolean Answer where the jump at bytecode index `anIndex' lands @meindex reads:@- @item reads:@- instVarIndex Answer whether the receiver reads the instance variable with the given index @meindex refersTo:@- @item refersTo:@- anObject Answer whether the receiver refers to the given object @meindex sendsToSuper @item sendsToSuper Answer whether the receiver includes a send to super. @meindex sourceCodeMap @item sourceCodeMap Answer an array which maps bytecode indices to source code line numbers. 0 values represent invalid instruction pointer indices. @end table @node CompiledCode-translation @subsection CompiledCode:@- translation @table @b @meindex discardTranslation @item discardTranslation Flush the just-in-time translated code for the receiver (if any). @end table @node CompiledMethod @section CompiledMethod @clindex CompiledMethod @table @b @item Defined in namespace Smalltalk @itemx Superclass: CompiledCode @itemx Category: Language-Implementation I represent methods that have been compiled. I can recompile methods from their source code, I can invoke Emacs to edit the source code for one of my instances, and I know how to access components of my instances. @end table @menu * CompiledMethod class-c call-outs:: (class) * CompiledMethod class-instance creation:: (class) * CompiledMethod class-lean images:: (class) * CompiledMethod-accessing:: (instance) * CompiledMethod-attributes:: (instance) * CompiledMethod-basic:: (instance) * CompiledMethod-c call-outs:: (instance) * CompiledMethod-compiling:: (instance) * CompiledMethod-invoking:: (instance) * CompiledMethod-printing:: (instance) * CompiledMethod-saving and loading:: (instance) * CompiledMethod-source code:: (instance) * CompiledMethod-testing:: (instance) @end menu @node CompiledMethod class-c call-outs @subsection CompiledMethod class:@- c call-outs @table @b @meindex asyncCCall:@-numArgs:@-attributes:@- @slindex asyncCCall:@-args:@- @item asyncCCall:@- descr numArgs:@- numArgs attributes:@- attributesArray Return a CompiledMethod corresponding to a #asyncCCall:@-args:@- pragma with the given arguments. @meindex cCall:@-numArgs:@-attributes:@- @slindex cCall:@-returning:@-args:@- @item cCall:@- descr numArgs:@- numArgs attributes:@- attributesArray Return a CompiledMethod corresponding to a #cCall:@-returning:@-args:@- pragma with the given arguments. @end table @node CompiledMethod class-instance creation @subsection CompiledMethod class:@- instance creation @table @b @meindex literals:@-numArgs:@-numTemps:@-attributes:@-bytecodes:@-depth:@- @item literals:@- lits numArgs:@- numArg numTemps:@- numTemp attributes:@- attrArray bytecodes:@- bytecodes depth:@- depth Answer a full fledged CompiledMethod. Construct the method header from the parameters, and set the literals and bytecodes to the provided ones. Also, the bytecodes are optimized and any embedded CompiledBlocks modified to refer to these literals and to the newly created CompiledMethod. @meindex numArgs:@- @slindex valueWithReceiver:@-withArguments:@- @item numArgs:@- args Create a user-defined method (one that is sent #valueWithReceiver:@-withArguments:@- when it is invoked) with numArgs arguments. This only makes sense when called for a subclass of CompiledMethod. @end table @node CompiledMethod class-lean images @subsection CompiledMethod class:@- lean images @table @b @meindex stripSourceCode @item stripSourceCode Remove all the references to method source code from the system @end table @node CompiledMethod-accessing @subsection CompiledMethod:@- accessing @table @b @meindex allBlocksDo:@- @item allBlocksDo:@- aBlock Evaluate aBlock, passing to it all the CompiledBlocks it holds @meindex allLiterals @item allLiterals Answer the literals referred to by the receiver and all the blocks in it @meindex flags @item flags Private - Answer the optimization flags for the receiver @meindex isOldSyntax @item isOldSyntax Answer whether the method was written with the old (chunk-format) syntax @meindex method @item method Answer the receiver, since it is already a method. @meindex methodCategory @item methodCategory Answer the method category @meindex methodCategory:@- @item methodCategory:@- aCategory Set the method category to the given string @meindex methodClass @item methodClass Answer the class in which the receiver is installed. @meindex methodClass:@- @item methodClass:@- methodClass Set the receiver's class instance variable @meindex noteOldSyntax @item noteOldSyntax Remember that the method is written with the old (chunk-format) syntax @meindex numArgs @item numArgs Answer the number of arguments for the receiver @meindex numTemps @item numTemps Answer the number of temporaries for the receiver @meindex primitive @item primitive Answer the primitive called by the receiver @meindex selector @item selector Answer the selector through which the method is called @meindex selector:@- @item selector:@- aSymbol Set the selector through which the method is called @meindex sourceCodeLinesDelta @item sourceCodeLinesDelta Answer the delta from the numbers in LINE_NUMBER bytecodes to source code line numbers. @meindex stackDepth @item stackDepth Answer the number of stack slots needed for the receiver @meindex withAllBlocksDo:@- @item withAllBlocksDo:@- aBlock Evaluate aBlock, passing the receiver and all the CompiledBlocks it holds @meindex withNewMethodClass:@- @item withNewMethodClass:@- class Answer either the receiver or a copy of it, with the method class set to class @meindex withNewMethodClass:@-selector:@- @item withNewMethodClass:@- class selector:@- selector Answer either the receiver or a copy of it, with the method class set to class @end table @node CompiledMethod-attributes @subsection CompiledMethod:@- attributes @table @b @meindex attributeAt:@- @item attributeAt:@- aSymbol Return a Message for the first attribute named aSymbol defined by the receiver, or answer an error if none was found. @meindex attributeAt:@-ifAbsent:@- @item attributeAt:@- aSymbol ifAbsent:@- aBlock Return a Message for the first attribute named aSymbol defined by the receiver, or evaluate aBlock is none was found. @meindex attributes @item attributes Return an Array of Messages, one for each attribute defined by the receiver. @meindex attributesDo:@- @item attributesDo:@- aBlock Evaluate aBlock once for each attribute defined by the receiver, passing a Message each time. @meindex isAnnotated @item isAnnotated If the receiver has any attributes, answer true. @meindex primitiveAttribute @item primitiveAttribute If the receiver defines a primitive, return a Message resembling the attribute that was used to define it. @end table @node CompiledMethod-basic @subsection CompiledMethod:@- basic @table @b @meindex = @item = aMethod Answer whether the receiver and aMethod are equal @meindex hash @item hash Answer an hash value for the receiver @end table @node CompiledMethod-c call-outs @subsection CompiledMethod:@- c call-outs @table @b @meindex isValidCCall @item isValidCCall Answer whether I appear to have the valid flags, information, and ops to invoke a C function and answer its result. @meindex rewriteAsAsyncCCall:@-args:@- @item rewriteAsAsyncCCall:@- func args:@- argsArray Not commented. @meindex rewriteAsCCall:@-for:@- @item rewriteAsCCall:@- funcOrDescr for:@- aClass Not commented. @meindex rewriteAsCCall:@-returning:@-args:@- @item rewriteAsCCall:@- func returning:@- returnType args:@- argsArray Not commented. @end table @node CompiledMethod-compiling @subsection CompiledMethod:@- compiling @table @b @meindex methodFormattedSourceString @item methodFormattedSourceString Answer the method source code as a string, formatted using the RBFormatter. Requires package Parser. @meindex methodParseNode @item methodParseNode Answer the parse tree for the receiver, or nil if there is an error. Requires package Parser. @meindex parserClass @item parserClass Answer a parser class, similar to Behavior>>parserClass, that can parse my source code. Requires package Parser. @meindex recompile @item recompile Recompile the method in the scope of the class where it leaves. @meindex recompileNotifying:@- @slindex error:@- @item recompileNotifying:@- aNotifier Recompile the method in the scope of the class where it leaves, notifying errors to aNotifier by sending it #error:@-. @end table @node CompiledMethod-invoking @subsection CompiledMethod:@- invoking @table @b @meindex valueWithReceiver:@-withArguments:@- @slindex subclassResponsibility @item valueWithReceiver:@- anObject withArguments:@- args Execute the method within anObject, passing the elements of the args Array as parameters. The method need not reside on the hierarchy from the receiver's class to Object -- it need not reside at all in a MethodDictionary, in fact -- but doing bad things will compromise stability of the Smalltalk virtual machine (and don't blame anybody but yourself). If the flags field of the method header is 6, this method instead provides a hook from which the virtual machine can call back whenever execution of the method is requested. In this case, invoking the method would cause an infinite loop (the VM asks the method to run, the method asks the VM to invoke it, and so on), so this method fails with a #subclassResponsibility error. @end table @node CompiledMethod-printing @subsection CompiledMethod:@- printing @table @b @meindex printOn:@- @item printOn:@- aStream Print the receiver's class and selector on aStream @meindex storeOn:@- @item storeOn:@- aStream Print code to create the receiver on aStream @end table @node CompiledMethod-saving and loading @subsection CompiledMethod:@- saving and loading @table @b @meindex binaryRepresentationObject @slindex >> @item binaryRepresentationObject This method is implemented to allow for a PluggableProxy to be used with CompiledMethods. Answer a DirectedMessage which sends #>> to the class object containing the receiver. @end table @node CompiledMethod-source code @subsection CompiledMethod:@- source code @table @b @meindex methodRecompilationSourceString @item methodRecompilationSourceString Answer the method source code as a string, ensuring that it is in new syntax (it has brackets). @meindex methodSourceCode @item methodSourceCode Answer the method source code (a FileSegment or String or nil) @meindex methodSourceFile @item methodSourceFile Answer the file where the method source code is stored @meindex methodSourcePos @item methodSourcePos Answer the location where the method source code is stored in the methodSourceFile @meindex methodSourceString @item methodSourceString Answer the method source code as a string @end table @node CompiledMethod-testing @subsection CompiledMethod:@- testing @table @b @meindex accesses:@- @item accesses:@- instVarIndex Answer whether the receiver or the blocks it contains accesses the instance variable with the given index @meindex assigns:@- @item assigns:@- instVarIndex Answer whether the receiver or the blocks it contains writes to the instance variable with the given index @meindex isAbstract @item isAbstract Answer whether the receiver is abstract. @meindex reads:@- @item reads:@- instVarIndex Answer whether the receiver or the blocks it contains reads to the instance variable with the given index @meindex sendsToSuper @item sendsToSuper Answer whether the receiver or the blocks it contains have sends to super @end table @node ContextPart @section ContextPart @clindex ContextPart @table @b @item Defined in namespace Smalltalk @itemx Superclass: Object @itemx Category: Language-Implementation My instances represent executing Smalltalk code, which represent the local environment of executable code. They contain a stack and also provide some methods that can be used in inspection or debugging. @end table @menu * ContextPart class-built ins:: (class) * ContextPart class-exception handling:: (class) * ContextPart-accessing:: (instance) * ContextPart-built ins:: (instance) * ContextPart-copying:: (instance) * ContextPart-debugging:: (instance) * ContextPart-enumerating:: (instance) * ContextPart-printing:: (instance) * ContextPart-security checks:: (instance) @end menu @node ContextPart class-built ins @subsection ContextPart class:@- built ins @table @b @meindex thisContext @item thisContext Return the value of the thisContext variable. Called internally when the variable is accessed. @end table @node ContextPart class-exception handling @subsection ContextPart class:@- exception handling @table @b @meindex backtrace @item backtrace Print a backtrace from the caller to the bottom of the stack on the Transcript @meindex backtraceOn:@- @item backtraceOn:@- aStream Print a backtrace from the caller to the bottom of the stack on aStream @end table @node ContextPart-accessing @subsection ContextPart:@- accessing @table @b @meindex at:@- @item at:@- index Answer the index-th slot in the receiver. Any read access from (self size + 1) to (self basicSize) will give nil. @meindex at:@-put:@- @item at:@- index put:@- anObject Answer the index-th slot in the receiver. Any write access from (self size + 1) to (self basicSize) will give an error unless nil is being written. This is because doing such an access first, and then updating sp, is racy:@- the garbage collector may trigger in the middle and move anObject, but the slot in the context won't be adjusted. @meindex client @item client Answer the client of this context, that is, the object that sent the message that created this context. Fail if the receiver has no parent @meindex currentFileName @item currentFileName Answer the name of the file where the method source code is @meindex environment @item environment To create a valid execution environment for the interpreter even before it starts, GST creates a fake context whose selector is nil and which can be used as a marker for the current execution environment. This method answers that context. For processes, it answers the process block itself @meindex home @item home Answer the MethodContext to which the receiver refers @meindex initialIP @item initialIP Answer the value of the instruction pointer when execution starts in the current context @meindex ip @item ip Answer the current instruction pointer into the receiver @meindex ip:@- @item ip:@- newIP Set the instruction pointer for the receiver @meindex isBlock @item isBlock Answer whether the receiver is a block context @meindex isDisabled @slindex continue:@- @slindex ensure:@- @item isDisabled Answers whether the context is skipped when doing a return. Contexts are marked as disabled whenever a non-local return is done (either by returning from the enclosing method of a block, or with the #continue:@- method of ContextPart) and there are unwind contexts such as those created by #ensure:@-. All non-unwind contexts are then marked as disabled. @meindex isEnvironment @item isEnvironment To create a valid execution environment for the interpreter even before it starts, GST creates a fake context which invokes a special ``termination'' method. Such a context can be used as a marker for the current execution environment. Answer whether the receiver is that kind of context. @meindex isProcess @slindex newProcess @item isProcess Answer whether the receiver represents a process context, i.e. a context created by BlockClosure>>@-#newProcess. Such a context can be recognized because it has no parent but its flags are different from those of the contexts created by the VM's prepareExecutionEnvironment function. @meindex isUnwind @slindex continue:@- @slindex ensure:@- @item isUnwind Answers whether the context must continue execution even after a non-local return (a return from the enclosing method of a block, or a call to the #continue:@- method of ContextPart). Such contexts are created by #ensure:@-. @meindex method @item method Return the CompiledMethod being executed @meindex methodClass @item methodClass Return the class in which the CompiledMethod being executed is defined @meindex numArgs @item numArgs Answer the number of arguments passed to the receiver @meindex numTemps @item numTemps Answer the number of temporaries used by the receiver @meindex parentContext @item parentContext Answer the context that called the receiver @meindex parentContext:@- @item parentContext:@- aContext Set the context to which the receiver will return @meindex push:@- @item push:@- anObject Push an object on the receiver's stack. @meindex receiver @item receiver Return the receiver (self) for the method being executed @meindex selector @item selector Return the selector for the method being executed @meindex size @item size Answer the number of valid fields for the receiver. Any read access from (self size + 1) to (self basicSize) will give nil. @meindex sp @item sp Answer the current stack pointer into the receiver @meindex sp:@- @item sp:@- newSP Set the stack pointer for the receiver. @meindex validSize @item validSize Answer how many elements in the receiver should be inspected @end table @node ContextPart-built ins @subsection ContextPart:@- built ins @table @b @meindex continue:@- @slindex ensure:@- @slindex ifCurtailed:@- @item continue:@- anObject Resume execution from the receiver, faking that the context on top of it in the execution chain has returned anObject. The receiver must belong to the same process as the executing context, otherwise the results are not predictable. All #ensure:@- (and possibly #ifCurtailed:@-) blocks between the currently executing context and the receiver are evaluated (which is not what would happen if you directly bashed at the parent context of thisContext). @end table @node ContextPart-copying @subsection ContextPart:@- copying @table @b @meindex copyStack @item copyStack Answer a copy of the entire stack. @meindex deepCopy @item deepCopy Answer a copy of the entire stack, but don't copy any of the other instance variables of the context. @end table @node ContextPart-debugging @subsection ContextPart:@- debugging @table @b @meindex currentLine @item currentLine Answer the 1-based number of the line that is pointed to by the receiver's instruction pointer. The DebugTools package caches information, thus making the implementation faster. @meindex currentLineInFile @item currentLineInFile Answer the 1-based number of the line that is pointed to by the receiver's instruction pointer, relative to the method's file. The implementation is slow unless the DebugTools package is loaded. @meindex debugger @item debugger Answer the debugger that is attached to the given context. It is always nil unless the DebugTools package is loaded. @meindex debuggerClass @item debuggerClass Answer which debugger should be used to debug the current context chain. The class with the highest debugging priority is picked among those mentioned in the chain. @meindex isInternalExceptionHandlingContext @item isInternalExceptionHandlingContext Answer whether the receiver is a context that should be hidden to the user when presenting a backtrace. @end table @node ContextPart-enumerating @subsection ContextPart:@- enumerating @table @b @meindex scanBacktraceFor:@-do:@- @item scanBacktraceFor:@- selectors do:@- aBlock Scan the backtrace for contexts whose selector is among those listed in selectors; if one is found, invoke aBlock passing the context. @meindex scanBacktraceForAttribute:@-do:@- @item scanBacktraceForAttribute:@- selector do:@- aBlock Scan the backtrace for contexts which have the attribute selector listed in selectors; if one is found, invoke aBlock passing the context and the attribute. @end table @node ContextPart-printing @subsection ContextPart:@- printing @table @b @meindex backtrace @item backtrace Print a backtrace from the receiver to the bottom of the stack on the Transcript. @meindex backtraceOn:@- @item backtraceOn:@- aStream Print a backtrace from the caller to the bottom of the stack on aStream. @end table @node ContextPart-security checks @subsection ContextPart:@- security checks @table @b @meindex checkSecurityFor:@- @item checkSecurityFor:@- perm Answer the receiver. @meindex doSecurityCheckForName:@-actions:@-target:@- @item doSecurityCheckForName:@- name actions:@- actions target:@- target Not commented. @meindex securityCheckForName:@- @item securityCheckForName:@- name Not commented. @meindex securityCheckForName:@-action:@- @item securityCheckForName:@- name action:@- action Not commented. @meindex securityCheckForName:@-actions:@-target:@- @item securityCheckForName:@- name actions:@- actions target:@- target Not commented. @meindex securityCheckForName:@-target:@- @item securityCheckForName:@- name target:@- target Not commented. @end table @node Continuation @section Continuation @clindex Continuation @table @b @item Defined in namespace Smalltalk @itemx Superclass: Object @itemx Category: Language-Implementation At my heart, I am something like the goto instruction; my creation sets the label, and my methods do the jump. However, this is a really powerful kind of goto instruction. If your hair is turning green at this point, don't worry as you will probably only deal with users of continuations, rather than with the concept itself. @end table @menu * Continuation class-instance creation:: (class) * Continuation-invocation:: (instance) @end menu @node Continuation class-instance creation @subsection Continuation class:@- instance creation @table @b @meindex current @item current Return a continuation. @meindex currentDo:@- @item currentDo:@- aBlock Pass a continuation to the one-argument block, aBlock and return the result of evaluating it. @meindex escapeDo:@- @item escapeDo:@- aBlock Pass a continuation to the one-argument block, knowing that aBlock does not fall off (either because it includes a method return, or because it yields control to another continuation). If it does, an exception will be signalled and the current process terminated. @end table @node Continuation-invocation @subsection Continuation:@- invocation @table @b @meindex callCC @item callCC Activate the original continuation, passing back in turn a continuation for the caller. The called continuation becomes unusable, and any attempt to reactivate it will cause an exception. This is not a limitation, in general, because this method is used to replace a continuation with another (see the implementation of the Generator class). @meindex oneShotValue @slindex value @item oneShotValue Return nil to the original continuation, which becomes unusable. Attempting to reactivate it will cause an exception. This is an optimization over #value. @meindex oneShotValue:@- @slindex value:@- @item oneShotValue:@- v Return anObject to the original continuation, which becomes unusable. Attempting to reactivate it will cause an exception. This is an optimization over #value:@-. @meindex value @item value Return nil to the original continuation, copying the stack to allow another activation. @meindex value:@- @item value:@- anObject Return anObject to the original continuation, copying the stack to allow another activation. @meindex valueWithArguments:@- @item valueWithArguments:@- aCollection Return the sole element of aCollection to the original continuation (or nil if aCollection is empty), copying the stack to allow another activation @end table @node CPtr @section CPtr @clindex CPtr @table @b @item Defined in namespace Smalltalk @itemx Superclass: CAggregate @itemx Category: Language-C interface @end table @menu * CPtr-accessing:: (instance) @end menu @node CPtr-accessing @subsection CPtr:@- accessing @table @b @meindex alignof @item alignof Answer the receiver's required aligment @meindex sizeof @item sizeof Answer the receiver's size @meindex value @item value Answer the address of the location pointed to by the receiver. @meindex value:@- @item value:@- anObject Set the address of the location pointed to by the receiver to anObject, which can be either an Integer or a CObject. if anObject is an Integer, it is interpreted as a 32-bit or 64-bit address. If it is a CObject, its address is stored. @end table @node CPtrCType @section CPtrCType @clindex CPtrCType @table @b @item Defined in namespace Smalltalk @itemx Superclass: CType @itemx Category: Language-C interface @end table @menu * CPtrCType class-instance creation:: (class) * CPtrCType-accessing:: (instance) * CPtrCType-basic:: (instance) * CPtrCType-storing:: (instance) @end menu @node CPtrCType class-instance creation @subsection CPtrCType class:@- instance creation @table @b @meindex elementType:@- @item elementType:@- aCType Answer a new instance of CPtrCType that maps pointers to the given CType @meindex from:@- @item from:@- type Private - Called by computeAggregateType:@- for pointers @end table @node CPtrCType-accessing @subsection CPtrCType:@- accessing @table @b @meindex elementType @item elementType Answer the type of the elements in the receiver's instances @end table @node CPtrCType-basic @subsection CPtrCType:@- basic @table @b @meindex = @item = anObject Return whether the receiver and anObject are equal. @meindex hash @item hash Return a hash code for the receiver. @end table @node CPtrCType-storing @subsection CPtrCType:@- storing @table @b @meindex storeOn:@- @item storeOn:@- aStream Not commented. @end table @node CScalar @section CScalar @clindex CScalar @table @b @item Defined in namespace Smalltalk @itemx Superclass: CObject @itemx Category: Language-C interface @end table @menu * CScalar class-instance creation:: (class) * CScalar-accessing:: (instance) @end menu @node CScalar class-instance creation @subsection CScalar class:@- instance creation @table @b @meindex gcValue:@- @item gcValue:@- anObject Answer a newly allocated CObject containing the passed value, anObject, in garbage-collected storage. @meindex type @item type Answer a CType for the receiver---for example, CByteType if the receiver is CByte. @meindex value:@- @slindex addToBeFinalized @item value:@- anObject Answer a newly allocated CObject containing the passed value, anObject. Remember to call #addToBeFinalized if you want the CObject to be automatically freed @end table @node CScalar-accessing @subsection CScalar:@- accessing @table @b @meindex cObjStoredType @slindex at:@-put:@- @item cObjStoredType Private - Provide a conversion from a CObject to a Smalltalk object to be stored by #at:@-put:@- @meindex value @item value Answer the value the receiver is pointing to. The exact returned value depends on the receiver's class @meindex value:@- @item value:@- aValue Set the receiver to point to the value, aValue. The exact meaning of aValue depends on the receiver's class @end table @node CScalarCType @section CScalarCType @clindex CScalarCType @table @b @item Defined in namespace Smalltalk @itemx Superclass: CType @itemx Category: Language-C interface @end table @menu * CScalarCType-accessing:: (instance) * CScalarCType-storing:: (instance) @end menu @node CScalarCType-accessing @subsection CScalarCType:@- accessing @table @b @meindex valueType @item valueType valueType is used as a means to communicate to the interpreter the underlying type of the data. For scalars, it is supplied by the CObject subclass. @end table @node CScalarCType-storing @subsection CScalarCType:@- storing @table @b @meindex storeOn:@- @item storeOn:@- aStream Store Smalltalk code that compiles to the receiver @end table @node CShort @section CShort @clindex CShort @table @b @item Defined in namespace Smalltalk @itemx Superclass: CScalar @itemx Category: Language-C interface @end table @menu * CShort class-accessing:: (class) * CShort-accessing:: (instance) @end menu @node CShort class-accessing @subsection CShort class:@- accessing @table @b @meindex alignof @item alignof Answer the receiver's instances required aligment @meindex cObjStoredType @item cObjStoredType Private - Answer an index referring to the receiver's instances scalar type @meindex sizeof @item sizeof Answer the receiver's instances size @end table @node CShort-accessing @subsection CShort:@- accessing @table @b @meindex alignof @item alignof Answer the receiver's required aligment @meindex cObjStoredType @item cObjStoredType Private - Answer an index referring to the receiver's scalar type @meindex sizeof @item sizeof Answer the receiver's size @end table @node CSmalltalk @section CSmalltalk @clindex CSmalltalk @table @b @item Defined in namespace Smalltalk @itemx Superclass: CScalar @itemx Category: Language-C interface @end table @menu * CSmalltalk class-accessing:: (class) * CSmalltalk-accessing:: (instance) @end menu @node CSmalltalk class-accessing @subsection CSmalltalk class:@- accessing @table @b @meindex alignof @item alignof Answer the receiver's instances required aligment @meindex cObjStoredType @item cObjStoredType Private - Answer an index referring to the receiver's instances scalar type @meindex sizeof @item sizeof Answer the receiver's instances size @end table @node CSmalltalk-accessing @subsection CSmalltalk:@- accessing @table @b @meindex alignof @item alignof Answer the receiver's required aligment @meindex cObjStoredType @item cObjStoredType Private - Answer an index referring to the receiver's scalar type @meindex sizeof @item sizeof Answer the receiver's size @end table @node CString @section CString @clindex CString @table @b @item Defined in namespace Smalltalk @itemx Superclass: CPtr @itemx Category: Language-C interface Technically, CString is really a pointer to CChar. However, it can be very useful as a distinct datatype because it is a separate datatype in Smalltalk, so we allow developers to express their semantics more precisely by using a more descriptive type. Note that like CChar is a pointer to char, CString is actually a *pointer* to string:@- a char ** in C terms. If you need to take a String out of a char *, use CChar>>@-#asString. In general, I behave like a cross between an array of characters and a pointer to a character. I provide the protocol for both data types. My #value method returns a Smalltalk String, as you would expect for a scalar datatype. @end table @menu * CString class-accessing:: (class) * CString class-instance creation:: (class) * CString-accessing:: (instance) @end menu @node CString class-accessing @subsection CString class:@- accessing @table @b @meindex cObjStoredType @slindex at:@-put:@- @item cObjStoredType Private - Provide a conversion from a CObject to a Smalltalk object to be stored by #at:@-put:@- @end table @node CString class-instance creation @subsection CString class:@- instance creation @table @b @meindex type @item type Answer a CType for the receiver---for example, CByteType if the receiver is CByte. @meindex value:@- @slindex addToBeFinalized @item value:@- anObject Answer a newly allocated CObject containing the passed value, anObject. Remember to call #addToBeFinalized if you want the CObject to be automatically freed @end table @node CString-accessing @subsection CString:@- accessing @table @b @meindex cObjStoredType @slindex at:@-put:@- @item cObjStoredType Private - Provide a conversion from a CObject to a Smalltalk object to be stored by #at:@-put:@- @meindex value @item value Answer the value the receiver is pointing to. The exact returned value depends on the receiver's class @meindex value:@- @item value:@- aValue Set the receiver to point to the value, aValue. The exact meaning of aValue depends on the receiver's class @end table @node CStringCType @section CStringCType @clindex CStringCType @table @b @item Defined in namespace Smalltalk @itemx Superclass: CScalarCType @itemx Category: Language-C interface @end table @menu * CStringCType-accessing:: (instance) @end menu @node CStringCType-accessing @subsection CStringCType:@- accessing @table @b @meindex elementType @item elementType Answer the type of the elements in the receiver's instances @end table @node CStruct @section CStruct @clindex CStruct @table @b @item Defined in namespace Smalltalk @itemx Superclass: CCompound @itemx Category: Language-C interface @end table @menu * CStruct class-subclass creation:: (class) @end menu @node CStruct class-subclass creation @subsection CStruct class:@- subclass creation @table @b @meindex declaration:@- @item declaration:@- array Compile methods that implement the declaration in array. @end table @node CType @section CType @clindex CType @table @b @item Defined in namespace Smalltalk @itemx Superclass: Object @itemx Category: Language-C interface I am not part of the standard Smalltalk kernel class hierarchy. I contain type information used by subclasses of CObject, which represents external C data items. My only instance variable, cObjectType, is used to hold onto the CObject subclass that gets created for a given CType. Used primarily in the C part of the interpreter because internally it cannot execute methods to get values, so it has a simple way to access instance variable which holds the desired subclass. My subclasses have instances which represent the actual data types; for the scalar types, there is only one instance created of each, but for the aggregate types, there is at least one instance per base type and/or number of elements. @end table @menu * CType class-C instance creation:: (class) * CType class-initialization:: (class) * CType-accessing:: (instance) * CType-basic:: (instance) * CType-C instance creation:: (instance) * CType-storing:: (instance) @end menu @node CType class-C instance creation @subsection CType class:@- C instance creation @table @b @meindex cObjectBinding:@- @item cObjectBinding:@- aCObjectSubclassBinding Create a new CType for the given subclass of CObject @meindex cObjectType:@- @item cObjectType:@- aCObjectSubclass Create a new CType for the given subclass of CObject @meindex computeAggregateType:@- @slindex array @slindex int @slindex ptr @item computeAggregateType:@- type Private - Called by from:@- for pointers/arrays. Format of type:@- (@-#array #int 3) or (@-#ptr #@{FooStruct@}) @meindex from:@- @item from:@- type Private - Pass the size, alignment, and description of CType for aBlock, given the field description in `type' (the second element of each pair). @end table @node CType class-initialization @subsection CType class:@- initialization @table @b @meindex initialize @item initialize Initialize the receiver's TypeMap @end table @node CType-accessing @subsection CType:@- accessing @table @b @meindex alignof @item alignof Answer the size of the receiver's instances @meindex arrayType:@- @item arrayType:@- size Answer a CArrayCType which represents an array with the given size of CObjects whose type is in turn represented by the receiver @meindex cObjectType @item cObjectType Answer the CObject subclass whose instance is created when new is sent to the receiver @meindex new:@- @item new:@- anInteger Allocate a new CObject with room for anInteger C objects of the type (class) identified by the receiver. It is the caller's responsibility to free the memory allocated for it. @meindex ptrType @item ptrType Answer a CPtrCType which represents a pointer to CObjects whose type is in turn represented by the receiver @meindex sizeof @item sizeof Answer the size of the receiver's instances @meindex valueType @item valueType valueType is used as a means to communicate to the interpreter the underlying type of the data. For anything but scalars, it's just 'self' @end table @node CType-basic @subsection CType:@- basic @table @b @meindex = @item = anObject Return whether the receiver and anObject are equal. @meindex hash @item hash Return a hash code for the receiver. @end table @node CType-C instance creation @subsection CType:@- C instance creation @table @b @meindex address:@- @item address:@- cObjOrInt Create a new CObject with the type (class) identified by the receiver, pointing to the given address (identified by an Integer or CObject). @meindex gcNew @item gcNew Allocate a new CObject with the type (class) identified by the receiver. The object is movable in memory, but on the other hand it is garbage-collected automatically. @meindex gcNew:@- @item gcNew:@- anInteger Allocate a new CObject with room for anInteger C object of the type (class) identified by the receiver. The object is movable in memory, but on the other hand it is garbage-collected automatically. @meindex new @item new Allocate a new CObject with the type (class) identified by the receiver. It is the caller's responsibility to free the memory allocated for it. @end table @node CType-storing @subsection CType:@- storing @table @b @meindex storeOn:@- @item storeOn:@- aStream Store Smalltalk code that compiles to the receiver @end table @node CUChar @section CUChar @clindex CUChar @table @b @item Defined in namespace Smalltalk @itemx Superclass: CScalar @itemx Category: Language-C interface @end table @menu * CUChar class-getting info:: (class) * CUChar-accessing:: (instance) @end menu @node CUChar class-getting info @subsection CUChar class:@- getting info @table @b @meindex alignof @item alignof Answer the receiver's instances required aligment @meindex cObjStoredType @item cObjStoredType Private - Answer an index referring to the receiver's instances scalar type @meindex sizeof @item sizeof Answer the receiver's instances size @end table @node CUChar-accessing @subsection CUChar:@- accessing @table @b @meindex alignof @item alignof Answer the receiver's required aligment @meindex cObjStoredType @item cObjStoredType Private - Answer an index referring to the receiver's scalar type @meindex sizeof @item sizeof Answer the receiver's size @end table @node CUInt @section CUInt @clindex CUInt @table @b @item Defined in namespace Smalltalk @itemx Superclass: CScalar @itemx Category: Language-C interface @end table @menu * CUInt class-accessing:: (class) * CUInt-accessing:: (instance) @end menu @node CUInt class-accessing @subsection CUInt class:@- accessing @table @b @meindex alignof @item alignof Answer the receiver's instances required aligment @meindex cObjStoredType @item cObjStoredType Private - Answer an index referring to the receiver's instances scalar type @meindex sizeof @item sizeof Answer the receiver's instances size @end table @node CUInt-accessing @subsection CUInt:@- accessing @table @b @meindex alignof @item alignof Answer the receiver's required aligment @meindex cObjStoredType @item cObjStoredType Private - Answer an index referring to the receiver's scalar type @meindex sizeof @item sizeof Answer the receiver's size @end table @node CULong @section CULong @clindex CULong @table @b @item Defined in namespace Smalltalk @itemx Superclass: CScalar @itemx Category: Language-C interface @end table @menu * CULong class-accessing:: (class) * CULong-accessing:: (instance) @end menu @node CULong class-accessing @subsection CULong class:@- accessing @table @b @meindex alignof @item alignof Answer the receiver's instances required aligment @meindex cObjStoredType @item cObjStoredType Private - Answer an index referring to the receiver's instances scalar type @meindex sizeof @item sizeof Answer the receiver's instances size @end table @node CULong-accessing @subsection CULong:@- accessing @table @b @meindex alignof @item alignof Answer the receiver's required aligment @meindex cObjStoredType @item cObjStoredType Private - Answer an index referring to the receiver's scalar type @meindex sizeof @item sizeof Answer the receiver's size @end table @node CULongLong @section CULongLong @clindex CULongLong @table @b @item Defined in namespace Smalltalk @itemx Superclass: CScalar @itemx Category: Language-C interface @end table @menu * CULongLong class-accessing:: (class) * CULongLong-accessing:: (instance) @end menu @node CULongLong class-accessing @subsection CULongLong class:@- accessing @table @b @meindex alignof @item alignof Answer the receiver's instances required aligment @meindex cObjStoredType @item cObjStoredType Private - Answer an index referring to the receiver's instances scalar type @meindex sizeof @item sizeof Answer the receiver's instances size @end table @node CULongLong-accessing @subsection CULongLong:@- accessing @table @b @meindex alignof @item alignof Answer the receiver's required aligment @meindex cObjStoredType @item cObjStoredType Private - Answer an index referring to the receiver's scalar type @meindex sizeof @item sizeof Answer the receiver's size @end table @node CUnion @section CUnion @clindex CUnion @table @b @item Defined in namespace Smalltalk @itemx Superclass: CCompound @itemx Category: Language-C interface @end table @menu * CUnion class-subclass creation:: (class) @end menu @node CUnion class-subclass creation @subsection CUnion class:@- subclass creation @table @b @meindex declaration:@- @item declaration:@- array Compile methods that implement the declaration in array. @end table @node CUShort @section CUShort @clindex CUShort @table @b @item Defined in namespace Smalltalk @itemx Superclass: CScalar @itemx Category: Language-C interface @end table @menu * CUShort class-accessing:: (class) * CUShort-accessing:: (instance) @end menu @node CUShort class-accessing @subsection CUShort class:@- accessing @table @b @meindex alignof @item alignof Answer the receiver's instances required aligment @meindex cObjStoredType @item cObjStoredType Private - Answer an index referring to the receiver's instances scalar type @meindex sizeof @item sizeof Answer the receiver's instances size @end table @node CUShort-accessing @subsection CUShort:@- accessing @table @b @meindex alignof @item alignof Answer the receiver's required aligment @meindex cObjStoredType @item cObjStoredType Private - Answer an index referring to the receiver's scalar type @meindex sizeof @item sizeof Answer the receiver's size @end table @node Date @section Date @clindex Date @table @b @item Defined in namespace Smalltalk @itemx Superclass: Magnitude @itemx Category: Language-Data types My instances represent dates. My base date is defined to be Jan 1, 1901. I provide methods for instance creation (including via "symbolic" dates, such as "Date newDay:@- 14 month:@- #Feb year:@- 1990". PLEASE BE WARNED -- use this class only for dates after 1582 AD; that's the beginning of the epoch. Dates before 1582 will not be correctly printed. In addition, since ten days were lost from October 5 through October 15, operations between a Gregorian date (after 15-Oct-1582) and a Julian date (before 5-Oct-1582) will give incorrect results; or, 4-Oct-1582 + 2 days will yield 6-Oct-1582 (a non-existent day!), not 16-Oct-1582. In fact, if you pass a year < 1582 to a method like #newDay:@-month:@-year:@- it will assume that it is a two-digit year (e.g. 90=1990, 1000=2900). The only way to create Julian calendar dates is with the #fromDays:@- instance creation method. @end table @menu * Date class-basic:: (class) * Date class-instance creation (ANSI):: (class) * Date class-instance creation (Blue Book):: (class) * Date-basic:: (instance) * Date-compatibility (non-ANSI):: (instance) * Date-date computations:: (instance) * Date-printing:: (instance) * Date-still unclassified:: (instance) * Date-storing:: (instance) * Date-testing:: (instance) @end menu @node Date class-basic @subsection Date class:@- basic @table @b @meindex abbreviationOfDay:@- @item abbreviationOfDay:@- dayIndex Answer the abbreviated name of the day of week corresponding to the given index @meindex dayOfWeek:@- @item dayOfWeek:@- dayName Answer the index of the day of week corresponding to the given name @meindex daysInMonth:@-forYear:@- @item daysInMonth:@- monthName forYear:@- yearInteger Answer the number of days in the given (named) month for the given year @meindex daysInYear:@- @item daysInYear:@- i Answer the number of days in the given year @meindex indexOfMonth:@- @item indexOfMonth:@- monthName Answer the index of the month corresponding to the given name @meindex initDayNameDict @item initDayNameDict Initialize the DayNameDict to the names of the days @meindex initMonthNameDict @item initMonthNameDict Initialize the MonthNameDict to the names of the months @meindex initialize @item initialize Initialize the receiver @meindex nameOfDay:@- @item nameOfDay:@- dayIndex Answer the name of the day of week corresponding to the given index @meindex nameOfMonth:@- @item nameOfMonth:@- monthIndex Answer the name of the month corresponding to the given index @meindex shortNameOfMonth:@- @item shortNameOfMonth:@- monthIndex Answer the name of the month corresponding to the given index @end table @node Date class-instance creation (ANSI) @subsection Date class:@- instance creation (ANSI) @table @b @meindex year:@-day:@-hour:@-minute:@-second:@- @item year:@- y day:@- d hour:@- h minute:@- min second:@- s Answer a Date denoting the d-th day of the given year @meindex year:@-month:@-day:@-hour:@-minute:@-second:@- @item year:@- y month:@- m day:@- d hour:@- h minute:@- min second:@- s Answer a Date denoting the d-th day of the given (as a number) month and year @end table @node Date class-instance creation (Blue Book) @subsection Date class:@- instance creation (Blue Book) @table @b @meindex dateAndTimeNow @item dateAndTimeNow Answer an array containing the current date and time @meindex fromDays:@- @item fromDays:@- dayCount Answer a Date denoting dayCount days past 1/1/1901 @meindex fromJulian:@- @item fromJulian:@- jd Answer a Date denoting the jd-th day in the astronomical Julian calendar. @meindex fromSeconds:@- @item fromSeconds:@- time Answer a Date denoting the date time seconds past Jan 1st, 1901 @meindex newDay:@-month:@-year:@- @item newDay:@- day month:@- monthName year:@- yearInteger Answer a Date denoting the dayCount day of the given (named) month and year @meindex newDay:@-monthIndex:@-year:@- @item newDay:@- day monthIndex:@- monthIndex year:@- yearInteger Answer a Date denoting the dayCount day of the given (as a number) month and year @meindex newDay:@-year:@- @item newDay:@- dayCount year:@- yearInteger Answer a Date denoting the dayCount day of the yearInteger year @meindex readFrom:@- @item readFrom:@- aStream Parse an instance of the receiver from aStream @meindex today @item today Answer a Date denoting the current date in local time @meindex utcDateAndTimeNow @item utcDateAndTimeNow Answer an array containing the current date and time in Coordinated Universal Time (UTC) @meindex utcToday @item utcToday Answer a Date denoting the current date in Coordinated Universal Time (UTC) @end table @node Date-basic @subsection Date:@- basic @table @b @meindex - @item - aDate Answer a new Duration counting the number of days between the receiver and aDate. @meindex addDays:@- @item addDays:@- dayCount Answer a new Date pointing dayCount past the receiver @meindex subtractDate:@- @item subtractDate:@- aDate Answer the number of days between aDate and the receiver (negative if the receiver is before aDate) @meindex subtractDays:@- @item subtractDays:@- dayCount Answer a new Date pointing dayCount before the receiver @end table @node Date-compatibility (non-ANSI) @subsection Date:@- compatibility (non-ANSI) @table @b @meindex day @item day Answer the day represented by the receiver @meindex dayName @item dayName Answer the day of week of the receiver as a Symbol @meindex shortMonthName @item shortMonthName Answer the abbreviated name of the month represented by the receiver @end table @node Date-date computations @subsection Date:@- date computations @table @b @meindex asSeconds @item asSeconds Answer the date as the number of seconds from 1/1/1901. @meindex dayOfMonth @slindex day @item dayOfMonth Answer the day represented by the receiver (same as #day) @meindex dayOfWeek @item dayOfWeek Answer the day of week of the receiver. 1 = Monday, 7 = Sunday @meindex dayOfWeekAbbreviation @item dayOfWeekAbbreviation Answer the day of week of the receiver as a Symbol @meindex dayOfWeekName @item dayOfWeekName Answer the day of week of the receiver as a Symbol @meindex dayOfYear @item dayOfYear Answer the days passed since 31/12 of last year; e.g. New Year's Day is 1 @meindex daysFromBaseDay @item daysFromBaseDay Answer the days passed since 1/1/1901 @meindex daysInMonth @item daysInMonth Answer the days in the month represented by the receiver @meindex daysInYear @item daysInYear Answer the days in the year represented by the receiver @meindex daysLeftInMonth @item daysLeftInMonth Answer the days to the end of the month represented by the receiver @meindex daysLeftInYear @item daysLeftInYear Answer the days to the end of the year represented by the receiver @meindex firstDayOfMonth @item firstDayOfMonth Answer a Date representing the first day of the month represented by the receiver @meindex isLeapYear @item isLeapYear Answer whether the receiver refers to a date in a leap year. @meindex lastDayOfMonth @item lastDayOfMonth Answer a Date representing the last day of the month represented by the receiver @meindex month @item month Answer the index of the month represented by the receiver @meindex monthAbbreviation @item monthAbbreviation Answer the abbreviated name of the month represented by the receiver @meindex monthIndex @item monthIndex Answer the index of the month represented by the receiver @meindex monthName @item monthName Answer the name of the month represented by the receiver @meindex year @item year Answer the year represented by the receiver @end table @node Date-printing @subsection Date:@- printing @table @b @meindex printOn:@- @item printOn:@- aStream Print a representation for the receiver on aStream @end table @node Date-still unclassified @subsection Date:@- still unclassified @table @b @meindex + @item + aDuration Answer a new Date or DateTime pointing aDuration time past the receiver. @end table @node Date-storing @subsection Date:@- storing @table @b @meindex storeOn:@- @item storeOn:@- aStream Store on aStream Smalltalk code compiling to the receiver @end table @node Date-testing @subsection Date:@- testing @table @b @meindex < @item < aDate Answer whether the receiver indicates a date preceding aDate @meindex = @item = aDate Answer whether the receiver indicates the same date as aDate @meindex hash @item hash Answer an hash value for the receievr @end table @node DateTime @section DateTime @clindex DateTime @table @b @item Defined in namespace Smalltalk @itemx Superclass: Date @itemx Category: Language-Data types My instances represent timestamps. @end table @menu * DateTime class-information:: (class) * DateTime class-instance creation:: (class) * DateTime class-instance creation (non-ANSI):: (class) * DateTime-basic:: (instance) * DateTime-computations:: (instance) * DateTime-printing:: (instance) * DateTime-splitting in dates & times:: (instance) * DateTime-storing:: (instance) * DateTime-testing:: (instance) * DateTime-time zones:: (instance) @end menu @node DateTime class-information @subsection DateTime class:@- information @table @b @meindex clockPrecision @item clockPrecision Answer `ClockPrecision'. @meindex initialize @item initialize Initialize the receiver's class variables @end table @node DateTime class-instance creation @subsection DateTime class:@- instance creation @table @b @meindex now @item now Answer an instance of the receiver referring to the current date and time. @meindex readFrom:@- @item readFrom:@- aStream Parse an instance of the receiver from aStream @meindex today @item today Answer an instance of the receiver referring to midnight of today in local time. @meindex year:@-day:@-hour:@-minute:@-second:@- @item year:@- y day:@- d hour:@- h minute:@- min second:@- s Answer a DateTime denoting the d-th day of the given year, and setting the time part to the given hour, minute, and second @meindex year:@-day:@-hour:@-minute:@-second:@-offset:@- @item year:@- y day:@- d hour:@- h minute:@- min second:@- s offset:@- ofs Answer a DateTime denoting the d-th day of the given year. Set the offset field to ofs (a Duration), and the time part to the given hour, minute, and second @meindex year:@-month:@-day:@-hour:@-minute:@-second:@- @item year:@- y month:@- m day:@- d hour:@- h minute:@- min second:@- s Answer a DateTime denoting the d-th day of the given (as a number) month and year, setting the time part to the given hour, minute, and second @meindex year:@-month:@-day:@-hour:@-minute:@-second:@-offset:@- @item year:@- y month:@- m day:@- d hour:@- h minute:@- min second:@- s offset:@- ofs Answer a DateTime denoting the d-th day of the given (as a number) month and year. Set the offset field to ofs (a Duration), and the the time part to the given hour, minute, and second @end table @node DateTime class-instance creation (non-ANSI) @subsection DateTime class:@- instance creation (non-ANSI) @table @b @meindex date:@-time:@- @item date:@- aDate time:@- aTime Answer a DateTime denoting the given date and time. Set the offset field to ofs (a Duration). @meindex date:@-time:@-offset:@- @item date:@- aDate time:@- aTime offset:@- ofs Answer a DateTime denoting the given date and time. Set the offset field to ofs (a Duration). @meindex fromDays:@-seconds:@- @item fromDays:@- days seconds:@- secs Answer a DateTime denoting the given date (as days since January 1, 1901) and time (as seconds since UTC midnight). @meindex fromDays:@-seconds:@-offset:@- @item fromDays:@- days seconds:@- secs offset:@- ofs Answer a DateTime denoting the given date (as days since January 1, 1901) and time (as seconds since midnight). Set the offset field to ofs (a Duration). @meindex fromSeconds:@- @item fromSeconds:@- secs Answer a DateTime denoting the given date and time (as seconds since January 1, 1901 midnight UTC). @meindex fromSeconds:@-offset:@- @item fromSeconds:@- secs offset:@- ofs Answer a DateTime denoting the given date and time (as seconds since January 1, 1901 midnight). Set the offset field to ofs (a Duration). @end table @node DateTime-basic @subsection DateTime:@- basic @table @b @meindex + @item + aDuration Answer a new Date pointing aDuration time past the receiver @meindex - @item - aDateTimeOrDuration Answer a new Date pointing dayCount before the receiver @end table @node DateTime-computations @subsection DateTime:@- computations @table @b @meindex asSeconds @item asSeconds Answer the date as the number of seconds from 1/1/1901. @meindex dayOfWeek @item dayOfWeek Answer the day of week of the receiver. Unlike Dates, DateAndTimes have 1 = Sunday, 7 = Saturday @meindex hour @item hour Answer the hour in a 24-hour clock @meindex hour12 @item hour12 Answer the hour in a 12-hour clock @meindex hour24 @item hour24 Answer the hour in a 24-hour clock @meindex meridianAbbreviation @slindex AM @slindex PM @item meridianAbbreviation Answer either #AM (for anti-meridian) or #PM (for post-meridian) @meindex minute @item minute Answer the minute @meindex second @item second Answer the month represented by the receiver @end table @node DateTime-printing @subsection DateTime:@- printing @table @b @meindex printOn:@- @item printOn:@- aStream Print a representation for the receiver on aStream @end table @node DateTime-splitting in dates & times @subsection DateTime:@- splitting in dates & times @table @b @meindex asDate @item asDate Answer a Date referring to the same day as the receiver @meindex asTime @item asTime Answer a Time referring to the same time (from midnight) as the receiver @meindex at:@- @item at:@- anIndex Since in the past timestamps were referred to as Arrays containing a Date and a Time (in this order), this method provides access to DateTime objects like if they were two-element Arrays. @end table @node DateTime-storing @subsection DateTime:@- storing @table @b @meindex storeOn:@- @item storeOn:@- aStream Store on aStream Smalltalk code compiling to the receiver @end table @node DateTime-testing @subsection DateTime:@- testing @table @b @meindex < @item < aDateTime Answer whether the receiver indicates a date preceding aDate @meindex = @item = aDateTime Answer whether the receiver indicates the same date as aDate @meindex hash @item hash Answer an hash value for the receievr @end table @node DateTime-time zones @subsection DateTime:@- time zones @table @b @meindex asLocal @item asLocal Answer the receiver, since DateTime objects store themselves in Local time @meindex asUTC @item asUTC Convert the receiver to UTC time, and answer a new DateTime object. @meindex offset @item offset Answer the receiver's offset from UTC to local time (e.g. +3600 seconds for Central Europe Time, -3600*6 seconds for Eastern Standard Time). The offset is expressed as a Duration @meindex offset:@- @item offset:@- anOffset Answer a copy of the receiver with the offset from UTC to local time changed to anOffset (a Duration). @meindex timeZoneAbbreviation @item timeZoneAbbreviation Answer an abbreviated indication of the receiver's offset, expressed as `shhmm', where `hh' is the number of hours and `mm' is the number of minutes between UTC and local time, and `s' can be `+' for the Eastern hemisphere and `-' for the Western hemisphere. @meindex timeZoneName @slindex timeZoneAbbreviation @item timeZoneName Answer the time zone name for the receiver (currently, it is simply `GMT +xxxx', where `xxxx' is the receiver's #timeZoneAbbreviation). @end table @node DeferredVariableBinding @section DeferredVariableBinding @clindex DeferredVariableBinding @table @b @item Defined in namespace Smalltalk @itemx Superclass: LookupKey @itemx Category: Language-Data types I represent a binding to a variable that is not tied to a particular dictionary until the first access. Then, lookup rules for global variables in the scope of a given class are used. @end table @menu * DeferredVariableBinding class-basic:: (class) * DeferredVariableBinding-basic:: (instance) * DeferredVariableBinding-storing:: (instance) @end menu @node DeferredVariableBinding class-basic @subsection DeferredVariableBinding class:@- basic @table @b @meindex key:@-class:@-defaultDictionary:@- @slindex resolveBinding @item key:@- aSymbol class:@- aClass defaultDictionary:@- aDictionary Answer a binding that will look up aSymbol as a variable in aClass's environment at first access. See #resolveBinding's comment for aDictionary's meaning. @meindex path:@-class:@-defaultDictionary:@- @slindex key:@-class:@-defaultDictionary:@- @item path:@- anArray class:@- aClass defaultDictionary:@- aDictionary As with #key:@-class:@-defaultDictionary:@-, but accepting an array of symbols, representing a namespace path, instead. @end table @node DeferredVariableBinding-basic @subsection DeferredVariableBinding:@- basic @table @b @meindex path @item path Answer the path followed after resolving the first key. @meindex value @item value Answer a new instance of the receiver with the given key and value @meindex value:@- @item value:@- anObject Answer a new instance of the receiver with the given key and value @end table @node DeferredVariableBinding-storing @subsection DeferredVariableBinding:@- storing @table @b @meindex printOn:@- @item printOn:@- aStream Put on aStream some Smalltalk code compiling to the receiver @meindex storeOn:@- @item storeOn:@- aStream Put on aStream some Smalltalk code compiling to the receiver @end table @node Delay @section Delay @clindex Delay @table @b @item Defined in namespace Smalltalk @itemx Superclass: Object @itemx Category: Kernel-Processes I am the ultimate agent for frustration in the world. I cause things to wait (sometimes much more than is appropriate, but it is those losing operating systems' fault). When a process sends one of my instances a wait message, that process goes to sleep for the interval specified when the instance was created. @end table @menu * Delay class-instance creation:: (class) * Delay class-still unclassified:: (class) * Delay class-timer process:: (class) * Delay-accessing:: (instance) * Delay-comparing:: (instance) * Delay-copying:: (instance) * Delay-delaying:: (instance) * Delay-initialization:: (instance) * Delay-instance creation:: (instance) * Delay-testing:: (instance) * Delay-timeout:: (instance) @end menu @node Delay class-instance creation @subsection Delay class:@- instance creation @table @b @meindex forMilliseconds:@- @item forMilliseconds:@- millisecondCount Answer a Delay waiting for millisecondCount milliseconds @meindex forNanoseconds:@- @item forNanoseconds:@- nanosecondCount Answer a Delay waiting for nanosecondCount nanoseconds @meindex forSeconds:@- @item forSeconds:@- secondCount Answer a Delay waiting for secondCount seconds @meindex untilMilliseconds:@- @item untilMilliseconds:@- millisecondCount Answer a Delay waiting until millisecondCount milliseconds after startup @meindex untilNanoseconds:@- @item untilNanoseconds:@- nanosecondCount Answer a Delay waiting until nanosecondCount nanoseconds after startup @end table @node Delay class-still unclassified @subsection Delay class:@- still unclassified @table @b @meindex update:@- @item update:@- aspect Prime the timer event loop when the image starts running. @end table @node Delay class-timer process @subsection Delay class:@- timer process @table @b @meindex activeDelay @item activeDelay Return the delay at the head of the queue. @meindex handleDelayRequestor @item handleDelayRequestor Handle a timer event; which can be either:@- - a schedule or unschedule request (DelayRequestor notNil) - a timer signal (not explicitly specified) We check for timer expiry every time we get a signal. @meindex runDelayProcess @item runDelayProcess Run the timer event loop. @meindex scheduleDelay:@- @item scheduleDelay:@- aDelay Private - Schedule this Delay. Run in the timer process, which is the only one that manipulates Queue. @meindex startDelayLoop @item startDelayLoop Start the timer event loop. @meindex unscheduleDelay:@- @item unscheduleDelay:@- aDelay Private - Unschedule this Delay. Run in the timer process, which is the only one that manipulates Queue. @end table @node Delay-accessing @subsection Delay:@- accessing @table @b @meindex asAbsolute @item asAbsolute Answer a delay that waits until the current delay's resumptionTime, or delayDuration milliseconds from now if that would be nil. May answer the receiver if it is already waiting until an absolute time. @meindex delayDuration @item delayDuration Answer the time I have left to wait, in milliseconds. @meindex isAbsolute @item isAbsolute Answer whether the receiver waits until an absolute time on the millisecond clock. @meindex resumptionTime @item resumptionTime Answer `resumptionTime'. @end table @node Delay-comparing @subsection Delay:@- comparing @table @b @meindex = @item = aDelay Answer whether the receiver and aDelay denote the same delay @meindex hash @item hash Answer an hash value for the receiver @end table @node Delay-copying @subsection Delay:@- copying @table @b @meindex postCopy @item postCopy Adjust the current delay so that it behaves as if it had just been created. @end table @node Delay-delaying @subsection Delay:@- delaying @table @b @meindex timedWaitOn:@- @item timedWaitOn:@- aSemaphore Schedule this Delay and wait on it. The current process will be suspended for the amount of time specified when this Delay was created, or until aSemaphore is signaled. @meindex wait @item wait Schedule this Delay and wait on it. The current process will be suspended for the amount of time specified when this Delay was created. @end table @node Delay-initialization @subsection Delay:@- initialization @table @b @meindex initForNanoseconds:@- @item initForNanoseconds:@- value Initialize a Delay waiting for millisecondCount milliseconds @end table @node Delay-instance creation @subsection Delay:@- instance creation @table @b @meindex initUntilNanoseconds:@- @item initUntilNanoseconds:@- value Initialize a Delay waiting for millisecondCount milliseconds after startup @end table @node Delay-testing @subsection Delay:@- testing @table @b @meindex isActive @item isActive Answer whether this Delay is being waited on. @end table @node Delay-timeout @subsection Delay:@- timeout @table @b @meindex value:@-onTimeoutDo:@- @item value:@- aBlock onTimeoutDo:@- aTimeoutBlock Execute aBlock for up to the time of my own delay; in case the code did not finish abort the execution, unwind the block and then evaluate aTimeoutBlock. @end table @node DelayedAdaptor @section DelayedAdaptor @clindex DelayedAdaptor @table @b @item Defined in namespace Smalltalk @itemx Superclass: PluggableAdaptor @itemx Category: Language-Data types I can be used where many expensive updates must be performed. My instances buffer the last value that was set, and only actually set the value when the #trigger message is sent. Apart from this, I'm equivalent to PluggableAdaptor. @end table @menu * DelayedAdaptor-accessing:: (instance) @end menu @node DelayedAdaptor-accessing @subsection DelayedAdaptor:@- accessing @table @b @meindex trigger @item trigger Really set the value of the receiver. @meindex value @item value Get the value of the receiver. @meindex value:@- @slindex trigger @item value:@- anObject Set the value of the receiver - actually, the value is cached and is not set until the #trigger method is sent. @end table @node Dictionary @section Dictionary @clindex Dictionary @table @b @item Defined in namespace Smalltalk @itemx Superclass: HashedCollection @itemx Category: Collections-Keyed I implement a dictionary, which is an object that is indexed by unique objects (typcially instances of Symbol), and associates another object with that index. I use the equality operator = to determine equality of indices. In almost all places where you would use a plain Dictionary, a LookupTable would be more efficient; see LookupTable's comment before you use it. I do have a couple of special features that are useful in certain special cases. @end table @menu * Dictionary class-instance creation:: (class) * Dictionary-accessing:: (instance) * Dictionary-awful ST-80 compatibility hacks:: (instance) * Dictionary-compilation:: (instance) * Dictionary-dictionary enumerating:: (instance) * Dictionary-dictionary removing:: (instance) * Dictionary-dictionary testing:: (instance) * Dictionary-namespace protocol:: (instance) * Dictionary-printing:: (instance) * Dictionary-rehashing:: (instance) * Dictionary-removing:: (instance) * Dictionary-storing:: (instance) * Dictionary-testing:: (instance) @end menu @node Dictionary class-instance creation @subsection Dictionary class:@- instance creation @table @b @meindex from:@- @item from:@- anArray Answer a new dictionary created from the keys and values of Associations in anArray, such as @{1 -> 2. 3 -> 4@}. anArray should be specified using brace-syntax. @meindex new @item new Create a new dictionary with a default size @end table @node Dictionary-accessing @subsection Dictionary:@- accessing @table @b @meindex add:@- @item add:@- newObject Add the newObject association to the receiver @meindex addAll:@- @item addAll:@- aCollection Adds all the elements of 'aCollection' to the receiver, answer aCollection @meindex associationAt:@- @item associationAt:@- key Answer the key/value Association for the given key. Fail if the key is not found @meindex associationAt:@-ifAbsent:@- @item associationAt:@- key ifAbsent:@- aBlock Answer the key/value Association for the given key. Evaluate aBlock (answering the result) if the key is not found @meindex associations @item associations Returns the content of a Dictionary as a Set of Associations. @meindex at:@- @item at:@- key Answer the value associated to the given key. Fail if the key is not found @meindex at:@-ifAbsent:@- @item at:@- key ifAbsent:@- aBlock Answer the value associated to the given key, or the result of evaluating aBlock if the key is not found @meindex at:@-ifAbsentPut:@- @item at:@- aKey ifAbsentPut:@- aBlock Answer the value associated to the given key. If the key is not found, evaluate aBlock and associate the result to aKey before returning. @meindex at:@-ifPresent:@- @item at:@- aKey ifPresent:@- aBlock If aKey is absent, answer nil. Else, evaluate aBlock passing the associated value and answer the result of the invocation @meindex at:@-put:@- @item at:@- key put:@- value Store value as associated to the given key @meindex atAll:@- @item atAll:@- keyCollection Answer a Dictionary that only includes the given keys. Fail if any of them is not found @meindex keyAtValue:@- @item keyAtValue:@- value Answer the key associated to the given value, or nil if the value is not found @meindex keyAtValue:@-ifAbsent:@- @item keyAtValue:@- value ifAbsent:@- exceptionBlock Answer the key associated to the given value. Evaluate exceptionBlock (answering the result) if the value is not found. IMPORTANT:@- == is used to compare values @meindex keys @item keys Answer a kind of Set containing the keys of the receiver @meindex values @item values Answer an Array containing the values of the receiver @end table @node Dictionary-awful ST-80 compatibility hacks @subsection Dictionary:@- awful ST-80 compatibility hacks @table @b @meindex findKeyIndex:@- @item findKeyIndex:@- key Tries to see if key exists as a the key of an indexed variable. As soon as nil or an association with the correct key is found, the index of that slot is answered @end table @node Dictionary-compilation @subsection Dictionary:@- compilation @table @b @meindex scopeDictionary @item scopeDictionary Answer the dictionary that is used when the receiver is before a period in Smalltalk source code. @end table @node Dictionary-dictionary enumerating @subsection Dictionary:@- dictionary enumerating @table @b @meindex associationsDo:@- @item associationsDo:@- aBlock Pass each association in the dictionary to aBlock @meindex collect:@- @item collect:@- aBlock Answer a new dictionary where the keys are the same and the values are obtained by passing each value to aBlock and collecting the return values @meindex do:@- @item do:@- aBlock Pass each value in the dictionary to aBlock @meindex keysAndValuesDo:@- @item keysAndValuesDo:@- aBlock Pass each key/value pair in the dictionary as two distinct parameters to aBlock @meindex keysDo:@- @item keysDo:@- aBlock Pass each key in the dictionary to aBlock @meindex reject:@- @item reject:@- aBlock Answer a new dictionary containing the key/value pairs for which aBlock returns false. aBlock only receives the value part of the pairs. @meindex select:@- @item select:@- aBlock Answer a new dictionary containing the key/value pairs for which aBlock returns true. aBlock only receives the value part of the pairs. @end table @node Dictionary-dictionary removing @subsection Dictionary:@- dictionary removing @table @b @meindex remove:@- @item remove:@- anAssociation Remove anAssociation's key from the dictionary @meindex remove:@-ifAbsent:@- @item remove:@- anAssociation ifAbsent:@- aBlock Remove anAssociation's key from the dictionary @meindex removeAllKeys:@- @item removeAllKeys:@- keys Remove all the keys in keys, without raising any errors @meindex removeAllKeys:@-ifAbsent:@- @item removeAllKeys:@- keys ifAbsent:@- aBlock Remove all the keys in keys, passing the missing keys as parameters to aBlock as they're encountered @meindex removeKey:@- @item removeKey:@- key Remove the passed key from the dictionary, fail if it is not found @meindex removeKey:@-ifAbsent:@- @item removeKey:@- key ifAbsent:@- aBlock Remove the passed key from the dictionary, answer the result of evaluating aBlock if it is not found @end table @node Dictionary-dictionary testing @subsection Dictionary:@- dictionary testing @table @b @meindex includes:@- @item includes:@- anObject Answer whether the receiver contains anObject as one of its values @meindex includesAssociation:@- @item includesAssociation:@- anAssociation Answer whether the receiver contains the key which is anAssociation's key and its value is anAssociation's value @meindex includesKey:@- @item includesKey:@- key Answer whether the receiver contains the given key @meindex occurrencesOf:@- @item occurrencesOf:@- aValue Answer whether the number of occurrences of aValue as one of the receiver's values @end table @node Dictionary-namespace protocol @subsection Dictionary:@- namespace protocol @table @b @meindex allSuperspaces @item allSuperspaces Answer all the receiver's superspaces in a collection @meindex allSuperspacesDo:@- @item allSuperspacesDo:@- aBlock Evaluate aBlock once for each of the receiver's superspaces (which is none for BindingDictionary). @meindex definedKeys @item definedKeys Answer a kind of Set containing the keys of the receiver @meindex definesKey:@- @item definesKey:@- key Answer whether the receiver defines the given key. `Defines' means that the receiver's superspaces, if any, are not considered. @meindex hereAssociationAt:@- @item hereAssociationAt:@- key Return the association for the variable named as specified by `key' *in this namespace*. If the key is not found search will *not* be carried on in superspaces and the method will fail. @meindex hereAssociationAt:@-ifAbsent:@- @item hereAssociationAt:@- key ifAbsent:@- aBlock Return the association for the variable named as specified by `key' *in this namespace*. If the key is not found search will *not* be carried on in superspaces and aBlock will be immediately evaluated. @meindex hereAt:@- @item hereAt:@- key Return the value associated to the variable named as specified by `key' *in this namespace*. If the key is not found search will *not* be carried on in superspaces and the method will fail. @meindex hereAt:@-ifAbsent:@- @item hereAt:@- key ifAbsent:@- aBlock Return the value associated to the variable named as specified by `key' *in this namespace*. If the key is not found search will *not* be carried on in superspaces and aBlock will be immediately evaluated. @meindex inheritsFrom:@- @item inheritsFrom:@- aNamespace Answer whether aNamespace is one of the receiver's direct and indirect superspaces @meindex superspace @item superspace Answer the receiver's superspace, which is nil for BindingDictionary. @meindex withAllSuperspaces @item withAllSuperspaces Answer the receiver and all of its superspaces in a collection, which is none for BindingDictionary @meindex withAllSuperspacesDo:@- @item withAllSuperspacesDo:@- aBlock Invokes aBlock for the receiver and all superspaces, both direct and indirect (though a BindingDictionary does not have any). @end table @node Dictionary-printing @subsection Dictionary:@- printing @table @b @meindex examineOn:@- @item examineOn:@- aStream Print all the instance variables and objects in the receiver on aStream @meindex printOn:@- @item printOn:@- aStream Print a representation of the receiver on aStream @end table @node Dictionary-rehashing @subsection Dictionary:@- rehashing @table @b @meindex rehash @item rehash Rehash the receiver @end table @node Dictionary-removing @subsection Dictionary:@- removing @table @b @meindex removeAllKeysSuchThat:@- @item removeAllKeysSuchThat:@- aBlock Remove from the receiver all keys for which aBlock returns true. @end table @node Dictionary-storing @subsection Dictionary:@- storing @table @b @meindex storeOn:@- @item storeOn:@- aStream Print Smalltalk code compiling to the receiver on aStream @end table @node Dictionary-testing @subsection Dictionary:@- testing @table @b @meindex = @item = aDictionary Answer whether the receiver and aDictionary are equal @meindex hash @item hash Answer the hash value for the receiver @end table @node DirectedMessage @section DirectedMessage @clindex DirectedMessage @table @b @item Defined in namespace Smalltalk @itemx Superclass: Message @itemx Category: Language-Implementation I represent a message send:@- I contain the receiver, selector and arguments for a message. @end table @menu * DirectedMessage class-creating instances:: (class) * DirectedMessage-accessing:: (instance) * DirectedMessage-basic:: (instance) * DirectedMessage-multiple process:: (instance) * DirectedMessage-saving and loading:: (instance) @end menu @node DirectedMessage class-creating instances @subsection DirectedMessage class:@- creating instances @table @b @meindex receiver:@-selector:@- @item receiver:@- anObject selector:@- aSymbol Create a new instance of the receiver @meindex receiver:@-selector:@-argument:@- @item receiver:@- receiverObject selector:@- aSymbol argument:@- argumentObject Create a new instance of the receiver @meindex receiver:@-selector:@-arguments:@- @item receiver:@- anObject selector:@- aSymbol arguments:@- anArray Create a new instance of the receiver @meindex selector:@-arguments:@- @item selector:@- aSymbol arguments:@- anArray This method should not be called for instances of this class. @meindex selector:@-arguments:@-receiver:@- @item selector:@- aSymbol arguments:@- anArray receiver:@- anObject Create a new instance of the receiver @end table @node DirectedMessage-accessing @subsection DirectedMessage:@- accessing @table @b @meindex receiver @item receiver Answer the receiver @meindex receiver:@- @item receiver:@- anObject Change the receiver @end table @node DirectedMessage-basic @subsection DirectedMessage:@- basic @table @b @meindex printOn:@- @item printOn:@- aStream Print a representation of the receiver on aStream @meindex send @item send Send the message @meindex value @item value Send the message (this message provides interoperability between DirectedMessages and blocks) @meindex value:@- @item value:@- anObject Send the message with the sole argument anObject (this message provides interoperability between DirectedMessages and blocks) @meindex value:@-value:@- @item value:@- obj1 value:@- obj2 Send the message with the arguments obj1 and obj2 (this message provides interoperability between DirectedMessages and blocks) @meindex valueWithArguments:@- @item valueWithArguments:@- anArray Send the message with the arguments replaced by anArray (this message provides interoperability between DirectedMessages and blocks) @end table @node DirectedMessage-multiple process @subsection DirectedMessage:@- multiple process @table @b @meindex fork @item fork Create a new process executing the receiver and start it @meindex forkAt:@- @item forkAt:@- priority Create a new process executing the receiver with given priority and start it @meindex newProcess @item newProcess Create a new process executing the receiver in suspended state. The priority is the same as for the calling process. The receiver must not contain returns @end table @node DirectedMessage-saving and loading @subsection DirectedMessage:@- saving and loading @table @b @meindex reconstructOriginalObject @item reconstructOriginalObject This method is used when DirectedMessages are used together with PluggableProxies (see ObjectDumper). It sends the receiver to reconstruct the object that was originally stored. @end table @node Directory @section Directory @clindex Directory @table @b @item Defined in namespace Smalltalk @itemx Superclass: Object @itemx Category: Streams-Files I am the counterpart of File in a tree-structured file system. I provide the notion of a current working directory and know several well-known places in the file system. However, all navigation methods for directories are under FilePath or File for efficiency reasons. Refer to the manual of FilePath for information on how to use the instances returned by my class methods. @end table @menu * Directory class-file name management:: (class) * Directory class-file operations:: (class) * Directory class-reading system defaults:: (class) @end menu @node Directory class-file name management @subsection Directory class:@- file name management @table @b @meindex append:@-to:@- @item append:@- fileName to:@- directory Answer the name of a file named `fileName' which resides in a directory named `directory'. @meindex pathSeparator @item pathSeparator Answer (as a Character) the character used to separate directory names @meindex pathSeparatorString @item pathSeparatorString Answer (in a String) the character used to separate directory names @end table @node Directory class-file operations @subsection Directory class:@- file operations @table @b @meindex allFilesMatching:@-do:@- @slindex allFilesMatching:@-do:@- @item allFilesMatching:@- aPattern do:@- aBlock Invoke #allFilesMatching:@-do:@- on the current working directory. @meindex create:@- @item create:@- dirName Create a directory named dirName and answer it. @meindex createTemporary:@- @item createTemporary:@- prefix Create an empty directory whose name starts with prefix and answer it. @meindex working @item working Answer the current working directory, not following symlinks. @meindex working:@- @item working:@- dirName Change the current working directory to dirName. @end table @node Directory class-reading system defaults @subsection Directory class:@- reading system defaults @table @b @meindex execPrefix @item execPrefix Answer the path to GNU Smalltalk's executable installation prefix @meindex home @item home Answer the path to the user's home directory @meindex image @item image Answer the path to GNU Smalltalk's image file @meindex kernel @item kernel Answer the path in which a local version of the GNU Smalltalk kernel's Smalltalk source files were searched when the image was created. @meindex libexec @item libexec Answer the path to GNU Smalltalk's auxiliary executables @meindex localKernel @item localKernel Answer the path to the GNU Smalltalk kernel's Smalltalk source files. Same as `Directory kernel' since GNU Smalltalk 3.0. @meindex module @item module Answer the path to GNU Smalltalk's dynamically loaded modules @meindex prefix @item prefix Answer the path to GNU Smalltalk's installation prefix @meindex systemKernel @item systemKernel Answer the path to the installed Smalltalk kernel source files. @meindex temporary @item temporary Answer the path in which temporary files can be created. This is read from the environment, and guessed if that fails. @meindex userBase @item userBase Answer the base path under which file for user customization of GNU Smalltalk are stored. @end table @node DLD @section DLD @clindex DLD @table @b @item Defined in namespace Smalltalk @itemx Superclass: Object @itemx Category: Language-C interface ...and Gandalf said:@- ``Many folk like to know beforehand what is to be set on the table; but those who have laboured to prepare the feast like to keep their secret; for wonder makes the words of praise louder.'' I am just an ancillary class used to reference some C functions. Most of my actual functionality is used by redefinitions of methods in CFunctionDescriptor. @end table @menu * DLD class-C call-outs:: (class) * DLD class-dynamic linking:: (class) @end menu @node DLD class-C call-outs @subsection DLD class:@- C call-outs @table @b @meindex defineCFunc:@-as:@- @item defineCFunc:@- aName as:@- aFuncAddr Register aFuncAddr as the target for cCalls to aName. @end table @node DLD class-dynamic linking @subsection DLD class:@- dynamic linking @table @b @meindex addLibrary:@- @item addLibrary:@- library Add library to the search path of libraries to be used by DLD. @meindex addLibraryHandle:@- @item addLibraryHandle:@- libraryHandle This is called internally by gst_dlopen. The library will be open and put in the search path. @meindex addModule:@- @item addModule:@- library Add library to the list of modules to be loaded when the image is started. The gst_initModule function in the library is called, but the library will not be put in the search path used whenever a C function is requested but not registered. @meindex defineExternFunc:@- @slindex primDefineExternFunc:@- @item defineExternFunc:@- aFuncName This method calls #primDefineExternFunc:@- to try to link to a function with the given name, and answers whether the linkage was successful. You can redefine this method to restrict the ability to do dynamic linking. @meindex initialize @item initialize Private - Initialize the receiver's class variables @meindex libraryList @item libraryList Answer a copy of the search path of libraries to be used by DLD @meindex moduleList @item moduleList Answer a copy of the modules reloaded when the image is started @meindex primDefineExternFunc:@- @item primDefineExternFunc:@- aFuncName This method tries to link to a function with the given name, and answers whether the linkage was successful. It should not be overridden. @meindex update:@- @item update:@- aspect Called on startup - Make DLD re-link and reset the addresses of all the externally defined functions @end table @node DumperProxy @section DumperProxy @clindex DumperProxy @table @b @item Defined in namespace Smalltalk @itemx Superclass: Object @itemx Category: Streams-Files I am an helper class for ObjectDumper. When an object cannot be saved in the standard way, you can register a subclass of me to provide special means to save that object. @end table @menu * DumperProxy class-accessing:: (class) * DumperProxy class-instance creation:: (class) * DumperProxy-saving and restoring:: (instance) @end menu @node DumperProxy class-accessing @subsection DumperProxy class:@- accessing @table @b @meindex acceptUsageForClass:@- @item acceptUsageForClass:@- aClass The receiver was asked to be used as a proxy for the class aClass. Answer whether the registration is fine. By default, answer true @meindex loadFrom:@- @item loadFrom:@- anObjectDumper Reload a proxy stored in anObjectDumper and reconstruct the object @end table @node DumperProxy class-instance creation @subsection DumperProxy class:@- instance creation @table @b @meindex on:@- @slindex dumpTo:@- @item on:@- anObject Answer a proxy to be used to save anObject. This method MUST be overridden and anObject must NOT be stored in the object's instance variables unless you override #dumpTo:@-, because that would result in an infinite loop! @end table @node DumperProxy-saving and restoring @subsection DumperProxy:@- saving and restoring @table @b @meindex dumpTo:@- @slindex loadFrom:@- @item dumpTo:@- anObjectDumper Dump the proxy to anObjectDumper -- the #loadFrom:@- class method will reconstruct the original object. @meindex object @item object Reconstruct the object stored in the proxy and answer it @end table @node Duration @section Duration @clindex Duration @table @b @item Defined in namespace Smalltalk @itemx Superclass: Time @itemx Category: Language-Data types My instances represent differences between timestamps. @end table @menu * Duration class-instance creation:: (class) * Duration class-instance creation (non ANSI):: (class) * Duration-arithmetics:: (instance) * Duration-processes:: (instance) * Duration-storing:: (instance) @end menu @node Duration class-instance creation @subsection Duration class:@- instance creation @table @b @meindex days:@- @item days:@- d Answer a duration of `d' days @meindex days:@-hours:@-minutes:@-seconds:@- @item days:@- d hours:@- h minutes:@- m seconds:@- s Answer a duration of `d' days and the given number of hours, minutes, and seconds. @meindex initialize @item initialize Initialize the receiver's instance variables @meindex milliseconds:@- @item milliseconds:@- msec Answer a duration of `msec' milliseconds @meindex readFrom:@- @item readFrom:@- aStream Parse an instance of the receiver (hours/minutes/seconds) from aStream @meindex weeks:@- @item weeks:@- w Answer a duration of `w' weeks @meindex zero @item zero Answer a duration of zero seconds. @end table @node Duration class-instance creation (non ANSI) @subsection Duration class:@- instance creation (non ANSI) @table @b @meindex fromDays:@-seconds:@-offset:@- @item fromDays:@- days seconds:@- secs offset:@- unused Answer a duration of `d' days and `secs' seconds. The last parameter is unused; this message is available for interoperability with the DateTime class. @end table @node Duration-arithmetics @subsection Duration:@- arithmetics @table @b @meindex * @item * factor Answer a Duration that is `factor' times longer than the receiver @meindex + @item + aDuration Answer a Duration that is the sum of the receiver and aDuration's lengths. @meindex - @item - aDuration Answer a Duration that is the difference of the receiver and aDuration's lengths. @meindex / @item / factorOrDuration If the parameter is a Duration, answer the ratio between the receiver and factorOrDuration. Else divide the receiver by factorOrDuration (a Number) and answer a new Duration that is correspondingly shorter. @meindex abs @item abs Answer a Duration that is as long as the receiver, but always in the future. @meindex days @item days Answer the number of days in the receiver @meindex isZero @item isZero Answer whether the receiver correspond to a duration of zero seconds. @meindex negated @item negated Answer a Duration that is as long as the receiver, but with past and future exchanged. @meindex negative @item negative Answer whether the receiver is in the past. @meindex positive @item positive Answer whether the receiver is a zero-second duration or is in the future. @meindex printOn:@- @item printOn:@- aStream Print a represention of the receiver on aStream. @end table @node Duration-processes @subsection Duration:@- processes @table @b @meindex wait @item wait Answer a Delay waiting for the amount of time represented by the receiver and start waiting on it. @end table @node Duration-storing @subsection Duration:@- storing @table @b @meindex storeOn:@- @item storeOn:@- aStream Store on aStream Smalltalk code compiling to the receiver @end table @node DynamicVariable @section DynamicVariable @clindex DynamicVariable @table @b @item Defined in namespace Smalltalk @itemx Superclass: Object @itemx Category: Language-Utilities I am a variable that is visible only in the stackframes outgoing from this one. Do not use DynamicVariable directly, instead create a subclass for each variable you want to use. You can override the #value class method, and call #valueIfAbsent:@- from there if you want the default value to be something else than nil. @end table @menu * DynamicVariable class-evaluating:: (class) @end menu @node DynamicVariable class-evaluating @subsection DynamicVariable class:@- evaluating @table @b @meindex use:@-during:@- @item use:@- anObject during:@- aBlock Not commented. @meindex value @item value Not commented. @meindex valueIfAbsent:@- @item valueIfAbsent:@- aBlock Not commented. @end table @node Error @section Error @clindex Error @table @b @item Defined in namespace Smalltalk @itemx Superclass: Exception @itemx Category: Language-Exceptions Error represents a fatal error. Instances of it are not resumable. @end table @menu * Error-exception description:: (instance) @end menu @node Error-exception description @subsection Error:@- exception description @table @b @meindex description @item description Answer a textual description of the exception. @meindex isResumable @item isResumable Answer false. Error exceptions are by default unresumable; subclasses can override this method if desired. @end table @node Exception @section Exception @clindex Exception @table @b @item Defined in namespace Smalltalk @itemx Superclass: Object @itemx Category: Language-Exceptions My instances describe an exception that has happened, and are passed to exception handlers. Classes describe the kind of exception. Apart from containing information on the generated exception, my instances contain methods that allow you to resume execution, leave the #on:@-do:@-... block, and pass the exception to an handler with a lower priority. @end table @menu * Exception class-comparison:: (class) * Exception class-creating ExceptionCollections:: (class) * Exception class-instance creation:: (class) * Exception class-interoperability with TrappableEvents:: (class) * Exception-accessing:: (instance) * Exception-built ins:: (instance) * Exception-comparison:: (instance) * Exception-copying:: (instance) * Exception-exception description:: (instance) * Exception-exception handling:: (instance) * Exception-exception signaling:: (instance) * Exception-still unclassified:: (instance) @end menu @node Exception class-comparison @subsection Exception class:@- comparison @table @b @meindex goodness:@- @item goodness:@- anExceptionClass Answer how good the receiver is at handling the given exception. A negative value indicates that the receiver is not able to handle the exception. @meindex handles:@- @item handles:@- anException Answer whether the receiver handles `anException'. @end table @node Exception class-creating ExceptionCollections @subsection Exception class:@- creating ExceptionCollections @table @b @meindex , @item , aTrappableEvent Answer an ExceptionCollection containing all the exceptions in the receiver and all the exceptions in aTrappableEvent @end table @node Exception class-instance creation @subsection Exception class:@- instance creation @table @b @meindex new @item new Create an instance of the receiver, which you will be able to signal later. @meindex signal @item signal Create an instance of the receiver, give it default attributes, and signal it immediately. @meindex signal:@- @item signal:@- messageText Create an instance of the receiver, set its message text, and signal it immediately. @end table @node Exception class-interoperability with TrappableEvents @subsection Exception class:@- interoperability with TrappableEvents @table @b @meindex allExceptionsDo:@- @item allExceptionsDo:@- aBlock Private - Pass ourselves to aBlock @end table @node Exception-accessing @subsection Exception:@- accessing @table @b @meindex basicMessageText @item basicMessageText Answer an exception's message text. Do not override this method. @meindex messageText @item messageText Answer an exception's message text. @meindex messageText:@- @item messageText:@- aString Set an exception's message text. @meindex tag @item tag Answer an exception's tag value. If not specified, it is the same as the message text. @meindex tag:@- @item tag:@- anObject Set an exception's tag value. If nil, the tag value will be the same as the message text. @end table @node Exception-built ins @subsection Exception:@- built ins @table @b @meindex resignalAsUnhandled:@- @slindex basicPrint @slindex printOn:@- @item resignalAsUnhandled:@- message This might start the debugger... Note that we use #basicPrint 'cause #printOn:@- might invoke an error. @end table @node Exception-comparison @subsection Exception:@- comparison @table @b @meindex = @item = anObject Answer whether the receiver is equal to anObject. This is true if either the receiver or its class are the same object as anObject. @end table @node Exception-copying @subsection Exception:@- copying @table @b @meindex postCopy @item postCopy Modify the receiver so that it does not refer to any instantiated exception handler. @end table @node Exception-exception description @subsection Exception:@- exception description @table @b @meindex defaultAction @item defaultAction Execute the default action that is attached to the receiver. @meindex description @item description Answer a textual description of the exception. @meindex isResumable @item isResumable Answer true. Exceptions are by default resumable. @end table @node Exception-exception handling @subsection Exception:@- exception handling @table @b @meindex context @slindex on:@-do:@- @item context Return the execution context for the #on:@-do:@- snippet @meindex isNested @item isNested Answer whether the current exception handler is within the scope of another handler for the same exception. @meindex outer @slindex outer @slindex outer @slindex pass @item outer Raise the exception that instantiated the receiver, passing the same parameters. If the receiver is resumable and the evaluated exception action resumes then the result returned from #outer will be the resumption value of the evaluated exception action. If the receiver is not resumable or if the exception action does not resume then this message will not return, and #outer will be equivalent to #pass. @meindex pass @slindex outer @item pass Yield control to the enclosing exception action for the receiver. Similar to #outer, but control does not return to the currently active exception handler. @meindex resignalAs:@- @item resignalAs:@- replacementException Reinstate all handlers and execute the handler for `replacementException'; control does not return to the currently active exception handler. The new Signal object that is created has the same contents as the receiver (this might or not be correct -- if it isn't you can use an idiom such as `sig retryUsing:@- [ replacementException signal ]) @meindex resume @item resume If the exception is resumable, resume the execution of the block that raised the exception; the method that was used to signal the exception will answer the receiver. Use this method IF AND ONLY IF you know who caused the exception and if it is possible to resume it in that particular case @meindex resume:@- @item resume:@- anObject If the exception is resumable, resume the execution of the block that raised the exception; the method that was used to signal the exception will answer anObject. Use this method IF AND ONLY IF you know who caused the exception and if it is possible to resume it in that particular case @meindex retry @slindex on:@-do:@- @item retry Re-execute the receiver of the #on:@-do:@- message. All handlers are reinstated:@- watch out, this can easily cause an infinite loop. @meindex retryUsing:@- @slindex signal @item retryUsing:@- aBlock Execute aBlock reinstating all handlers, and return its result from the #signal method. @meindex return @slindex on:@-do:@- @item return Exit the #on:@-do:@- snippet, answering nil to its caller. @meindex return:@- @slindex on:@-do:@- @item return:@- anObject Exit the #on:@-do:@- snippet, answering anObject to its caller. @end table @node Exception-exception signaling @subsection Exception:@- exception signaling @table @b @meindex signal @item signal Raise the exceptional event represented by the receiver @meindex signal:@- @item signal:@- messageText Raise the exceptional event represented by the receiver, setting its message text to messageText. @end table @node Exception-still unclassified @subsection Exception:@- still unclassified @table @b @meindex signalingContext @item signalingContext Return the execution context for the place that signaled the exception, or nil if it is not available anymore (for example if the exception handler has returned. @end table @node ExceptionSet @section ExceptionSet @clindex ExceptionSet @table @b @item Defined in namespace Smalltalk @itemx Superclass: Object @itemx Category: Language-Exceptions My instances are not real exceptions:@- they can only be used as arguments to #on:@-do:@-... methods in BlockClosure. They act as shortcuts that allows you to use the same handler for many exceptions without having to write duplicate code @end table @menu * ExceptionSet class-instance creation:: (class) * ExceptionSet-enumerating:: (instance) * ExceptionSet-instance creation:: (instance) @end menu @node ExceptionSet class-instance creation @subsection ExceptionSet class:@- instance creation @table @b @meindex new @item new Private - Answer a new, empty ExceptionSet @end table @node ExceptionSet-enumerating @subsection ExceptionSet:@- enumerating @table @b @meindex allExceptionsDo:@- @item allExceptionsDo:@- aBlock Private - Evaluate aBlock for every exception in the receiver. Answer the receiver @meindex goodness:@- @item goodness:@- exception Answer how good the receiver is at handling the given exception. A negative value indicates that the receiver is not able to handle the exception. @meindex handles:@- @item handles:@- exception Answer whether the receiver handles `exception'. @end table @node ExceptionSet-instance creation @subsection ExceptionSet:@- instance creation @table @b @meindex , @item , aTrappableEvent Answer an ExceptionSet containing all the exceptions in the receiver and all the exceptions in aTrappableEvent @end table @node False @section False @clindex False @table @b @item Defined in namespace Smalltalk @itemx Superclass: Boolean @itemx Category: Language-Data types I always tell lies. I have a single instance in the system, which represents the value false. @end table @menu * False-basic:: (instance) * False-C hacks:: (instance) * False-printing:: (instance) @end menu @node False-basic @subsection False:@- basic @table @b @meindex & @item & aBoolean We are false -- anded with anything, we always answer false @meindex and:@- @item and:@- aBlock We are false -- anded with anything, we always answer false @meindex eqv:@- @item eqv:@- aBoolean Answer whether the receiver and aBoolean represent the same boolean value @meindex ifFalse:@- @item ifFalse:@- falseBlock We are false -- evaluate the falseBlock @meindex ifFalse:@-ifTrue:@- @item ifFalse:@- falseBlock ifTrue:@- trueBlock We are false -- evaluate the falseBlock @meindex ifTrue:@- @item ifTrue:@- trueBlock We are false -- answer nil @meindex ifTrue:@-ifFalse:@- @item ifTrue:@- trueBlock ifFalse:@- falseBlock We are false -- evaluate the falseBlock @meindex not @item not We are false -- answer true @meindex or:@- @item or:@- aBlock We are false -- ored with anything, we always answer the other operand, so evaluate aBlock @meindex xor:@- @item xor:@- aBoolean Answer whether the receiver and aBoolean represent different boolean values @meindex | @item | aBoolean We are false -- ored with anything, we always answer the other operand @end table @node False-C hacks @subsection False:@- C hacks @table @b @meindex asCBooleanValue @item asCBooleanValue Answer `0'. @end table @node False-printing @subsection False:@- printing @table @b @meindex printOn:@- @item printOn:@- aStream Print a representation of the receiver on aStream @end table @node File @section File @clindex File @table @b @item Defined in namespace Smalltalk @itemx Superclass: FilePath @itemx Category: Streams-Files I enable access to the properties of files that are on disk. @end table @menu * File class-C functions:: (class) * File class-file operations:: (class) * File class-initialization:: (class) * File class-instance creation:: (class) * File class-reading system defaults:: (class) * File class-testing:: (class) * File-accessing:: (instance) * File-basic:: (instance) * File-directory operations:: (instance) * File-file name management:: (instance) * File-file operations:: (instance) * File-still unclassified:: (instance) * File-testing:: (instance) @end menu @node File class-C functions @subsection File class:@- C functions @table @b @meindex errno @item errno Answer the current value of C errno. @meindex stringError:@- @item stringError:@- errno Answer C strerror's result for errno. @end table @node File class-file operations @subsection File class:@- file operations @table @b @meindex checkError @item checkError Return whether an error had been reported or not. If there had been one, raise an exception too @meindex checkError:@- @item checkError:@- errno The error with the C code `errno' has been reported. If errno >= 1, raise an exception @meindex remove:@- @item remove:@- fileName Remove the file with the given path name @meindex rename:@-to:@- @item rename:@- oldFileName to:@- newFileName Rename the file with the given path name oldFileName to newFileName @meindex symlink:@-as:@- @item symlink:@- srcName as:@- destName Create a symlink for the srcName file with the given path name @meindex symlink:@-from:@- @item symlink:@- destName from:@- srcName Create a symlink named destName file from the given path (relative to destName) @meindex touch:@- @item touch:@- fileName Update the timestamp of the file with the given path name. @end table @node File class-initialization @subsection File class:@- initialization @table @b @meindex initialize @item initialize Initialize the receiver's class variables @end table @node File class-instance creation @subsection File class:@- instance creation @table @b @meindex name:@- @item name:@- aName Answer a new file with the given path. The path is turned into an absolute path. @meindex path:@- @item path:@- aString Answer a new file with the given path. The path is not validated until some of the fields of the newly created objects are accessed @end table @node File class-reading system defaults @subsection File class:@- reading system defaults @table @b @meindex executable @item executable Answer the full path to the executable being run. @meindex image @item image Answer the full path to the image being used. @end table @node File class-testing @subsection File class:@- testing @table @b @meindex exists:@- @item exists:@- fileName Answer whether a file with the given name exists @meindex isAccessible:@- @item isAccessible:@- fileName Answer whether a directory with the given name exists and can be accessed @meindex isExecutable:@- @item isExecutable:@- fileName Answer whether a file with the given name exists and can be executed @meindex isReadable:@- @item isReadable:@- fileName Answer whether a file with the given name exists and is readable @meindex isWriteable:@- @item isWriteable:@- fileName Answer whether a file with the given name exists and is writeable @end table @node File-accessing @subsection File:@- accessing @table @b @meindex asString @item asString Answer the name of the file identified by the receiver @meindex at:@- @item at:@- aString Answer a File or Directory object as appropriate for a file named 'aName' in the directory represented by the receiver. @meindex creationTime @item creationTime Answer the creation time of the file identified by the receiver. On some operating systems, this could actually be the last change time (the `last change time' has to do with permissions, ownership and the like). @meindex isDirectory @item isDirectory Answer whether the file is a directory. @meindex isSocket @item isSocket Answer whether the file is an AF_UNIX socket. @meindex isSymbolicLink @item isSymbolicLink Answer whether the file is a symbolic link. @meindex lastAccessTime @item lastAccessTime Answer the last access time of the file identified by the receiver @meindex lastChangeTime @item lastChangeTime Answer the last change time of the file identified by the receiver (the `last change time' has to do with permissions, ownership and the like). On some operating systems, this could actually be the file creation time. @meindex lastModifyTime @item lastModifyTime Answer the last modify time of the file identified by the receiver (the `last modify time' has to do with the actual file contents). @meindex mode @item mode Answer the permission bits for the file identified by the receiver @meindex mode:@- @item mode:@- anInteger Set the permission bits for the file identified by the receiver to be anInteger. @meindex name @item name Answer the name of the file identified by the receiver @meindex pathTo:@- @item pathTo:@- destName Compute the relative path from the receiver to destName. @meindex refresh @item refresh Refresh the statistics for the receiver @meindex size @item size Answer the size of the file identified by the receiver @end table @node File-basic @subsection File:@- basic @table @b @meindex = @item = aFile Answer whether the receiver represents the same file as the receiver. @meindex hash @item hash Answer a hash value for the receiver. @end table @node File-directory operations @subsection File:@- directory operations @table @b @meindex createDirectory @item createDirectory Create the receiver as a directory. @meindex namesDo:@- @item namesDo:@- aBlock Evaluate aBlock once for each file in the directory represented by the receiver, passing its name. aBlock should not return. @end table @node File-file name management @subsection File:@- file name management @table @b @meindex full @item full Answer the full name of the receiver, resolving the `.' and `..' directory entries, and answer the result. Answer nil if the name is invalid (such as '/usr/../../badname') @end table @node File-file operations @subsection File:@- file operations @table @b @meindex lastAccessTime:@-lastModifyTime:@- @item lastAccessTime:@- accessDateTime lastModifyTime:@- modifyDateTime Set the receiver's timestamps to be accessDateTime and modifyDateTime. @meindex open:@-mode:@-ifFail:@- @item open:@- class mode:@- mode ifFail:@- aBlock Open the receiver in the given mode (as answered by FileStream's class constant methods) @meindex owner:@-group:@- @item owner:@- ownerString group:@- groupString Set the receiver's owner and group to be ownerString and groupString. @meindex pathFrom:@- @item pathFrom:@- dir Compute the relative path from the directory dirName to the receiver @meindex remove @item remove Remove the file with the given path name @meindex renameTo:@- @item renameTo:@- newFileName Rename the file with the given path name to newFileName @meindex symlinkAs:@- @item symlinkAs:@- destName Create destName as a symbolic link of the receiver. The appropriate relative path is computed automatically. @meindex symlinkFrom:@- @item symlinkFrom:@- srcName Create the receiver as a symlink from path destName @end table @node File-still unclassified @subsection File:@- still unclassified @table @b @meindex , @item , aName Answer an object of the same kind as the receiver, whose name is suffixed with aName. @end table @node File-testing @subsection File:@- testing @table @b @meindex exists @item exists Answer whether a file with the name contained in the receiver does exist. @meindex isAbsolute @item isAbsolute Answer whether the receiver identifies an absolute path. @meindex isAccessible @item isAccessible Answer whether a directory with the name contained in the receiver does exist and is accessible @meindex isExecutable @item isExecutable Answer whether a file with the name contained in the receiver does exist and is executable @meindex isFileSystemPath @item isFileSystemPath Answer whether the receiver corresponds to a real filesystem path. @meindex isReadable @item isReadable Answer whether a file with the name contained in the receiver does exist and is readable @meindex isWriteable @item isWriteable Answer whether a file with the name contained in the receiver does exist and is writeable @end table @node FileDescriptor @section FileDescriptor @clindex FileDescriptor @table @b @item Defined in namespace Smalltalk @itemx Superclass: Stream @itemx Category: Streams-Files My instances are what conventional programmers think of as files. My instance creation methods accept the name of a disk file (or any named file object, such as /dev/rmt0 on UNIX or MTA0:@- on VMS). In addition, they accept a virtual filesystem path like `configure.gz@-#ugz' which can be used to transparently extract or decompress files from archives, or do arbitrary processing on the files. @end table @menu * FileDescriptor class-initialization:: (class) * FileDescriptor class-instance creation:: (class) * FileDescriptor class-still unclassified:: (class) * FileDescriptor-accessing:: (instance) * FileDescriptor-basic:: (instance) * FileDescriptor-binary I/O:: (instance) * FileDescriptor-built ins:: (instance) * FileDescriptor-class type methods:: (instance) * FileDescriptor-initialize-release:: (instance) * FileDescriptor-low-level access:: (instance) * FileDescriptor-overriding inherited methods:: (instance) * FileDescriptor-polymorphism:: (instance) * FileDescriptor-positioning:: (instance) * FileDescriptor-printing:: (instance) * FileDescriptor-testing:: (instance) @end menu @node FileDescriptor class-initialization @subsection FileDescriptor class:@- initialization @table @b @meindex initialize @item initialize Initialize the receiver's class variables @meindex update:@- @item update:@- aspect Close open files before quitting @end table @node FileDescriptor class-instance creation @subsection FileDescriptor class:@- instance creation @table @b @meindex append @item append Open for writing. The file is created if it does not exist. The stream is positioned at the end of the file. @meindex create @item create Open for reading and writing. The file is created if it does not exist, otherwise it is truncated. The stream is positioned at the beginning of the file. @meindex fopen:@-mode:@- @slindex append @slindex create @slindex readWrite @slindex read @slindex write @slindex close @slindex removeToBeFinalized @item fopen:@- fileName mode:@- fileMode Open fileName in the required mode - answered by #append, #create, #readWrite, #read or #write - and fail if the file cannot be opened. Else answer a new FileStream. For mode anyway you can use any standard C non-binary fopen mode. The file will be automatically closed upon GC if the object is not referenced anymore, but it is better to close it as soon as you're finished with it anyway, using #close. To keep a file open even when no references exist anymore, send it #removeToBeFinalized @meindex fopen:@-mode:@-ifFail:@- @slindex append @slindex create @slindex readWrite @slindex read @slindex write @slindex close @slindex removeToBeFinalized @item fopen:@- fileName mode:@- fileMode ifFail:@- aBlock Open fileName in the required mode - answered by #append, #create, #readWrite, #read or #write - and evaluate aBlock if the file cannot be opened. Else answer a new FileStream. For mode anyway you can use any The file will be automatically closed upon GC if the object is not referenced anymore, but it is better to close it as soon as you're finished with it anyway, using #close. To keep a file open even when no references exist anymore, send it #removeToBeFinalized @meindex on:@- @item on:@- fd Open a FileDescriptor on the given file descriptor. Read-write access is assumed. @meindex open:@- @slindex close @slindex removeToBeFinalized @item open:@- fileName Open fileName in read-write mode - fail if the file cannot be opened. Else answer a new FileStream. The file will be automatically closed upon GC if the object is not referenced anymore, but you should close it with #close anyway. To keep a file open, send it #removeToBeFinalized @meindex open:@-mode:@-ifFail:@- @slindex append @slindex create @slindex readWrite @slindex read @slindex write @slindex close @slindex removeToBeFinalized @item open:@- fileName mode:@- fileMode ifFail:@- aBlock Open fileName in the required mode - answered by #append, #create, #readWrite, #read or #write - and evaluate aBlock if the file cannot be opened. Else answer a new instance of the receiver. For mode anyway you can use any standard C non-binary fopen mode. fileName can be a `virtual filesystem' path, including URLs and '@-#' suffixes that are inspected by the virtual filesystem layers and replaced with tasks such as un-gzipping a file or extracting a file from an archive. The file will be automatically closed upon GC if the object is not referenced anymore, but it is better to close it as soon as you're finished with it anyway, using #close. To keep a file open even when no references exist anymore, send it #removeToBeFinalized @meindex openTemporaryFile:@- @item openTemporaryFile:@- baseName Open for writing a file whose name starts with baseName, followed by six random alphanumeric characters. The file is created with mode read/write and permissions 0666 or 0600 on most recent operating systems (beware, the former behavior might constitute a security problem). The file is opened with the O_EXCL flag, guaranteeing that when the method returns successfully we are the only user. @meindex popen:@-dir:@- @slindex read @slindex write @item popen:@- commandName dir:@- direction Open a pipe on the given command and fail if the file cannot be opened. Else answer a new FileStream. The pipe will not be automatically closed upon GC, even if the object is not referenced anymore, because when you close a pipe you have to wait for the associated process to terminate. direction is returned by #read or #write ('r' or 'w') and is interpreted from the point of view of Smalltalk:@- reading means Smalltalk reads the standard output of the command, writing means Smalltalk writes the standard input of the command. The other channel (stdin when reading, stdout when writing) is the same as GST's, unless commandName alters it. @meindex popen:@-dir:@-ifFail:@- @item popen:@- commandName dir:@- direction ifFail:@- aBlock Open a pipe on the given command and evaluate aBlock file cannot be opened. Else answer a new FileStream. The pipe will not be automatically closed upon GC, even if the object is not referenced anymore, because when you close a pipe you have to wait for the associated process to terminate. direction is interpreted from the point of view of Smalltalk:@- reading means that Smalltalk reads the standard output of the command, writing means that Smalltalk writes the standard input of the command @meindex read @item read Open text file for reading. The stream is positioned at the beginning of the file. @meindex readWrite @item readWrite Open for reading and writing. The stream is positioned at the beginning of the file. @meindex write @item write Truncate file to zero length or create text file for writing. The stream is positioned at the beginning of the file. @end table @node FileDescriptor class-still unclassified @subsection FileDescriptor class:@- still unclassified @table @b @meindex open:@-mode:@- @slindex append @slindex create @slindex readWrite @slindex read @slindex write @slindex close @slindex removeToBeFinalized @item open:@- fileName mode:@- fileMode Open fileName in the required mode - answered by #append, #create, #readWrite, #read or #write - and fail if the file cannot be opened. Else answer a new FileStream. For mode anyway you can use any standard C non-binary fopen mode. fileName can be a `virtual filesystem' path, including URLs and '@-#' suffixes that are inspected by the virtual filesystem layers and replaced with tasks such as un-gzipping a file or extracting a file from an archive. The file will be automatically closed upon GC if the object is not referenced anymore, but it is better to close it as soon as you're finished with it anyway, using #close. To keep a file open even when no references exist anymore, send it #removeToBeFinalized @end table @node FileDescriptor-accessing @subsection FileDescriptor:@- accessing @table @b @meindex canRead @item canRead Answer whether the file is open and we can read from it @meindex canWrite @item canWrite Answer whether the file is open and we can write from it @meindex ensureReadable @item ensureReadable If the file is open, wait until data can be read from it. The wait allows other Processes to run. @meindex ensureWriteable @item ensureWriteable If the file is open, wait until we can write to it. The wait allows other Processes to run. @meindex exceptionalCondition @item exceptionalCondition Answer whether the file is open and an exceptional condition (such as presence of out of band data) has occurred on it @meindex fd @item fd Return the OS file descriptor of the file @meindex file @item file Return the name of the file @meindex isOpen @item isOpen Answer whether the file is still open @meindex isPeerAlive @item isPeerAlive Present for compatibility with sockets. For files, it answers whether the file is still open @meindex isPipe @item isPipe Answer whether the file is a pipe or an actual disk file @meindex name @item name Return the name of the file @meindex waitForException @item waitForException If the file is open, wait until an exceptional condition (such as presence of out of band data) has occurred on it. The wait allows other Processes to run. @end table @node FileDescriptor-basic @subsection FileDescriptor:@- basic @table @b @meindex checkError @slindex checkError @item checkError Perform error checking. By default, we call File class>>@-#checkError. @meindex close @item close Close the file @meindex contents @item contents Answer the whole contents of the file @meindex copyFrom:@-to:@- @item copyFrom:@- from to:@- to Answer the contents of the file between the two given positions @meindex finalize @item finalize Close the file if it is still open by the time the object becomes garbage. @meindex invalidate @item invalidate Invalidate a file descriptor @meindex next @item next Return the next character in the file, or nil at eof @meindex nextByte @item nextByte Return the next byte in the file, or nil at eof @meindex nextPut:@- @item nextPut:@- aCharacter Store aCharacter on the file @meindex nextPutByte:@- @item nextPutByte:@- anInteger Store the byte, anInteger, on the file @meindex nextPutByteArray:@- @item nextPutByteArray:@- aByteArray Store aByteArray on the file @meindex peek @item peek Returns the next element of the stream without moving the pointer. Returns nil when at end of stream. @meindex peekFor:@- @item peekFor:@- anObject Returns whether the next element of the stream is equal to anObject, without moving the pointer if it is not. @meindex position @item position Answer the zero-based position from the start of the file @meindex position:@- @item position:@- n Set the file pointer to the zero-based position n @meindex reset @item reset Reset the stream to its beginning @meindex shutdown @item shutdown Close the transmission side of a full-duplex connection. This is useful on read-write pipes. @meindex size @item size Return the current size of the file, in bytes @meindex truncate @item truncate Truncate the file at the current position @end table @node FileDescriptor-binary I/O @subsection FileDescriptor:@- binary I/O @table @b @meindex nextByteArray:@- @item nextByteArray:@- numBytes Return the next numBytes bytes in the byte array @meindex nextDouble @item nextDouble Return the next 64-bit float in the byte array @meindex nextFloat @item nextFloat Return the next 32-bit float in the byte array @meindex nextLong @item nextLong Return the next 4 bytes in the byte array, interpreted as a 32 bit signed int @meindex nextLongLong @item nextLongLong Return the next 8 bytes in the byte array, interpreted as a 64 bit signed int @meindex nextPutDouble:@- @item nextPutDouble:@- aDouble Store aDouble as a 64-bit float in the byte array @meindex nextPutFloat:@- @item nextPutFloat:@- aFloat Return the next 32-bit float in the byte array @meindex nextPutInt64:@- @item nextPutInt64:@- anInteger Store anInteger (range:@- -2^63..2^64-1) on the byte array as 8 bytes @meindex nextPutLong:@- @item nextPutLong:@- anInteger Store anInteger (range:@- -2^31..2^32-1) on the byte array as 4 bytes @meindex nextPutShort:@- @item nextPutShort:@- anInteger Store anInteger (range:@- -32768..65535) on the byte array as 2 bytes @meindex nextShort @item nextShort Return the next 2 bytes in the byte array, interpreted as a 16 bit signed int @meindex nextSignedByte @item nextSignedByte Return the next byte in the byte array, interpreted as a 8 bit signed number @meindex nextUint64 @item nextUint64 Return the next 8 bytes in the byte array, interpreted as a 64 bit unsigned int @meindex nextUlong @item nextUlong Return the next 4 bytes in the byte array, interpreted as a 32 bit unsigned int @meindex nextUshort @item nextUshort Return the next 2 bytes in the byte array, interpreted as a 16 bit unsigned int @end table @node FileDescriptor-built ins @subsection FileDescriptor:@- built ins @table @b @meindex fileIn @item fileIn File in the contents of the receiver. During a file in operation, global variables (starting with an uppercase letter) that are not declared don't yield an `unknown variable' error. Instead, they are defined as nil in the `Undeclared' dictionary (a global variable residing in Smalltalk). As soon as you add the variable to a namespace (for example by creating a class) the Association will be removed from Undeclared and reused in the namespace, so that the old references will automagically point to the new value. @meindex fileOp:@- @item fileOp:@- ioFuncIndex Private - Used to limit the number of primitives used by FileStreams @meindex fileOp:@-ifFail:@- @item fileOp:@- ioFuncIndex ifFail:@- aBlock Private - Used to limit the number of primitives used by FileStreams. @meindex fileOp:@-with:@- @item fileOp:@- ioFuncIndex with:@- arg1 Private - Used to limit the number of primitives used by FileStreams @meindex fileOp:@-with:@-ifFail:@- @item fileOp:@- ioFuncIndex with:@- arg1 ifFail:@- aBlock Private - Used to limit the number of primitives used by FileStreams. @meindex fileOp:@-with:@-with:@- @item fileOp:@- ioFuncIndex with:@- arg1 with:@- arg2 Private - Used to limit the number of primitives used by FileStreams @meindex fileOp:@-with:@-with:@-ifFail:@- @item fileOp:@- ioFuncIndex with:@- arg1 with:@- arg2 ifFail:@- aBlock Private - Used to limit the number of primitives used by FileStreams. @meindex fileOp:@-with:@-with:@-with:@- @item fileOp:@- ioFuncIndex with:@- arg1 with:@- arg2 with:@- arg3 Private - Used to limit the number of primitives used by FileStreams @meindex fileOp:@-with:@-with:@-with:@-ifFail:@- @item fileOp:@- ioFuncIndex with:@- arg1 with:@- arg2 with:@- arg3 ifFail:@- aBlock Private - Used to limit the number of primitives used by FileStreams. @meindex fileOp:@-with:@-with:@-with:@-with:@- @item fileOp:@- ioFuncIndex with:@- arg1 with:@- arg2 with:@- arg3 with:@- arg4 Private - Used to limit the number of primitives used by FileStreams @meindex fileOp:@-with:@-with:@-with:@-with:@-ifFail:@- @item fileOp:@- ioFuncIndex with:@- arg1 with:@- arg2 with:@- arg3 with:@- arg4 ifFail:@- aBlock Private - Used to limit the number of primitives used by FileStreams. @end table @node FileDescriptor-class type methods @subsection FileDescriptor:@- class type methods @table @b @meindex isBinary @item isBinary We answer characters, so answer false @meindex isExternalStream @item isExternalStream We stream on an external entity (a file), so answer true @meindex isText @item isText We answer characters, so answer true @end table @node FileDescriptor-initialize-release @subsection FileDescriptor:@- initialize-release @table @b @meindex addToBeFinalized @item addToBeFinalized Add me to the list of open files. @meindex initialize @item initialize Initialize the receiver's instance variables @meindex readStream @item readStream Answer myself, or an alternate stream coerced for reading. @meindex removeToBeFinalized @item removeToBeFinalized Remove me from the list of open files. @end table @node FileDescriptor-low-level access @subsection FileDescriptor:@- low-level access @table @b @meindex next:@-putAll:@-startingAt:@- @item next:@- n putAll:@- aCollection startingAt:@- position Put the characters in the supplied range of aCollection in the file @meindex nextAvailable:@-into:@-startingAt:@- @item nextAvailable:@- n into:@- aCollection startingAt:@- position Ignoring any buffering, try to fill the given range of aCollection with the contents of the file @end table @node FileDescriptor-overriding inherited methods @subsection FileDescriptor:@- overriding inherited methods @table @b @meindex isEmpty @item isEmpty Answer whether the receiver is empty @meindex nextPutAllOn:@- @item nextPutAllOn:@- aStream Put all the characters of the receiver in aStream. @meindex reverseContents @item reverseContents Return the contents of the file from the last byte to the first @meindex setToEnd @item setToEnd Reset the file pointer to the end of the file @meindex skip:@- @item skip:@- anInteger Skip anInteger bytes in the file @end table @node FileDescriptor-polymorphism @subsection FileDescriptor:@- polymorphism @table @b @meindex pastEnd @item pastEnd The end of the stream has been reached. Signal a Notification. @end table @node FileDescriptor-positioning @subsection FileDescriptor:@- positioning @table @b @meindex isPositionable @slindex skip:@- @item isPositionable Answer true if the stream supports moving backwards with #skip:@-. @end table @node FileDescriptor-printing @subsection FileDescriptor:@- printing @table @b @meindex printOn:@- @item printOn:@- aStream Print a representation of the receiver on aStream @end table @node FileDescriptor-testing @subsection FileDescriptor:@- testing @table @b @meindex atEnd @item atEnd Answer whether data has come to an end @end table @node FilePath @section FilePath @clindex FilePath @table @b @item Defined in namespace Smalltalk @itemx Superclass: Object @itemx Category: Streams-Files I expose the syntax of file names, including paths. I know how to manipulate such a path by splitting it into its components. In addition, I expose information about files (both real and virtual) such as their size and timestamps. @end table @menu * FilePath class-file name management:: (class) * FilePath class-still unclassified:: (class) * FilePath-accessing:: (instance) * FilePath-converting:: (instance) * FilePath-decoration:: (instance) * FilePath-directory operations:: (instance) * FilePath-enumerating:: (instance) * FilePath-file name management:: (instance) * FilePath-file operations:: (instance) * FilePath-printing:: (instance) * FilePath-still unclassified:: (instance) * FilePath-testing:: (instance) * FilePath-virtual filesystems:: (instance) @end menu @node FilePath class-file name management @subsection FilePath class:@- file name management @table @b @meindex append:@-to:@- @item append:@- fileName to:@- directory Answer the name of a file named `fileName' which resides in a directory named `directory'. @meindex extensionFor:@- @item extensionFor:@- aString Answer the extension of a file named `aString'. Note:@- the extension includes an initial dot. @meindex fullNameFor:@- @item fullNameFor:@- aString Answer the full path to a file called `aString', resolving the `.' and `..' directory entries, and answer the result. `/..' is the same as '/'. @meindex pathFor:@- @item pathFor:@- aString Determine the path of the name of a file called `aString', and answer the result. With the exception of the root directory, the final slash is stripped. @meindex pathFor:@-ifNone:@- @item pathFor:@- aString ifNone:@- aBlock Determine the path of the name of a file called `aString', and answer the result. With the exception of the root directory, the final slash is stripped. If there is no path, evaluate aBlock and return the result. @meindex pathFrom:@-to:@- @item pathFrom:@- srcName to:@- destName Answer the relative path to destName when the current directory is srcName's directory. @meindex stripExtensionFrom:@- @item stripExtensionFrom:@- aString Remove the extension from the name of a file called `aString', and answer the result. @meindex stripFileNameFor:@- @item stripFileNameFor:@- aString Determine the path of the name of a file called `aString', and answer the result as a directory name including the final slash. @meindex stripPathFrom:@- @item stripPathFrom:@- aString Remove the path from the name of a file called `aString', and answer the file name plus extension. @end table @node FilePath class-still unclassified @subsection FilePath class:@- still unclassified @table @b @meindex isAbsolute:@- @item isAbsolute:@- aString Answer whether aString is an absolute ptah. @end table @node FilePath-accessing @subsection FilePath:@- accessing @table @b @meindex at:@- @item at:@- aName Answer a File or Directory object as appropriate for a file named 'aName' in the directory represented by the receiver. @meindex creationTime @item creationTime Answer the creation time of the file identified by the receiver. On some operating systems, this could actually be the last change time (the `last change time' has to do with permissions, ownership and the like). @meindex group:@- @item group:@- aString Set the group of the file identified by the receiver to be aString. @meindex includes:@- @item includes:@- aName Answer whether a file named `aName' exists in the directory represented by the receiver. @meindex lastAccessTime @item lastAccessTime Answer the last access time of the file identified by the receiver @meindex lastAccessTime:@- @item lastAccessTime:@- aDateTime Update the last access time of the file corresponding to the receiver, to be aDateTime. @meindex lastAccessTime:@-lastModifyTime:@- @item lastAccessTime:@- accessDateTime lastModifyTime:@- modifyDateTime Update the timestamps of the file corresponding to the receiver, to be accessDateTime and modifyDateTime. @meindex lastChangeTime @item lastChangeTime Answer the last change time of the file identified by the receiver (the `last change time' has to do with permissions, ownership and the like). On some operating systems, this could actually be the file creation time. @meindex lastModifyTime @item lastModifyTime Answer the last modify time of the file identified by the receiver (the `last modify time' has to do with the actual file contents). @meindex lastModifyTime:@- @item lastModifyTime:@- aDateTime Update the last modification timestamp of the file corresponding to the receiver, to be aDateTime. @meindex mode @item mode Answer the permission bits for the file identified by the receiver @meindex mode:@- @item mode:@- anInteger Set the permission bits for the file identified by the receiver to be anInteger. @meindex owner:@- @item owner:@- aString Set the owner of the file identified by the receiver to be aString. @meindex owner:@-group:@- @item owner:@- ownerString group:@- groupString Set the owner and group of the file identified by the receiver to be aString. @meindex pathTo:@- @item pathTo:@- destName Compute the relative path from the receiver to destName. @meindex refresh @item refresh Refresh the statistics for the receiver @meindex size @item size Answer the size of the file identified by the receiver @end table @node FilePath-converting @subsection FilePath:@- converting @table @b @meindex asFile @item asFile Answer the receiver. @end table @node FilePath-decoration @subsection FilePath:@- decoration @table @b @meindex all @item all Return a decorator of the receiver that will provide recursive descent into directories for iteration methods. Furthermore, iteration on the returned wrapper will not include '.' or '..' directory entries, and will include the receiver (directly, not via '.'). @end table @node FilePath-directory operations @subsection FilePath:@- directory operations @table @b @meindex createDirectories @item createDirectories Create the receiver as a directory, together with all its parents. @meindex createDirectory @item createDirectory Create the receiver as a directory, together with all its parents. @meindex nameAt:@- @item nameAt:@- aName Answer a FilePath for a file named `aName' residing in the directory represented by the receiver. @end table @node FilePath-enumerating @subsection FilePath:@- enumerating @table @b @meindex allFilesMatching:@-do:@- @slindex match:@- @item allFilesMatching:@- aPattern do:@- aBlock Evaluate aBlock on the File objects that match aPattern (according to String>>@-#match:@-) in the directory named by the receiver. Recursively descend into directories. @meindex directories @item directories Answer an Array with Directory objects for the subdirectories of the directory represented by the receiver. @meindex do:@- @item do:@- aBlock Evaluate aBlock once for each file in the directory represented by the receiver, passing a FilePath object (or a subclass) to it. It depends on the subclass whether iteration will include the '.' and '..' directory entries. @meindex entries @item entries Answer an Array with File or Directory objects for the contents of the directory represented by the receiver. @meindex entryNames @item entryNames Answer an Array with the names of the files in the directory represented by the receiver. @meindex files @item files Answer an Array with File objects for the contents of the directory represented by the receiver. @meindex filesMatching:@- @item filesMatching:@- aPattern Evaluate aBlock once for each file in the directory represented by the receiver, passing a File or Directory object to aBlock. Returns the *names* of the files for which aBlock returns true. @meindex filesMatching:@-do:@- @slindex match:@- @item filesMatching:@- aPattern do:@- block Evaluate block on the File objects that match aPattern (according to String>>@-#match:@-) in the directory named by the receiver. @meindex namesDo:@- @item namesDo:@- aBlock Evaluate aBlock once for each file in the directory represented by the receiver, passing its name. It depends on the subclass whether iteration will include the '.' and '..' directory entries. @meindex namesMatching:@-do:@- @slindex match:@- @item namesMatching:@- aPattern do:@- block Evaluate block on the file names that match aPattern (according to String>>@-#match:@-) in the directory named by the receiver. @meindex reject:@- @item reject:@- aBlock Evaluate aBlock once for each file in the directory represented by the receiver, passing a File or Directory object to aBlock. Returns the *names* of the files for which aBlock returns true. @meindex select:@- @item select:@- aBlock Evaluate aBlock once for each file in the directory represented by the receiver, passing a File or Directory object to aBlock. Returns the *names* of the files for which aBlock returns true. @end table @node FilePath-file name management @subsection FilePath:@- file name management @table @b @meindex directory @item directory Answer the Directory object for the receiver's path @meindex extension @item extension Answer the extension of the receiver @meindex full @item full Answer the full name of the receiver, resolving the `.' and `..' directory entries, and answer the result. Answer nil if the name is invalid (such as '/usr/../../badname') @meindex fullName @slindex name @item fullName Answer a String with the full path to the receiver (same as #name; it is useless to override this method). @meindex name @slindex fullName @item name Answer String with the full path to the receiver (same as #fullName). @meindex parent @item parent Answer the Directory object for the receiver's path @meindex path @item path Answer the path (if any) of the receiver @meindex stripExtension @item stripExtension Answer the path (if any) and file name of the receiver @meindex stripFileName @item stripFileName Answer the path of the receiver, always including a directory name (possibly `.') and the final directory separator @meindex stripPath @item stripPath Answer the file name and extension (if any) of the receiver @end table @node FilePath-file operations @subsection FilePath:@- file operations @table @b @meindex contents @item contents Open a read-only FileStream on the receiver, read its contents, close the stream and answer the contents @meindex fileIn @item fileIn File in the receiver @meindex open:@- @item open:@- mode Open the receiver in the given mode (as answered by FileStream's class constant methods) @meindex open:@-ifFail:@- @item open:@- mode ifFail:@- aBlock Open the receiver in the given mode (as answered by FileStream's class constant methods). Upon failure, evaluate aBlock. @meindex open:@-mode:@-ifFail:@- @item open:@- class mode:@- mode ifFail:@- aBlock Open the receiver in the given mode (as answered by FileStream's class constant methods) @meindex openDescriptor:@- @item openDescriptor:@- mode Open the receiver in the given mode (as answered by FileStream's class constant methods) @meindex openDescriptor:@-ifFail:@- @item openDescriptor:@- mode ifFail:@- aBlock Open the receiver in the given mode (as answered by FileStream's class constant methods). Upon failure, evaluate aBlock. @meindex pathFrom:@- @item pathFrom:@- dirName Compute the relative path from the directory dirName to the receiver @meindex readStream @item readStream Open a read-only FileStream on the receiver @meindex remove @item remove Remove the file identified by the receiver @meindex renameTo:@- @item renameTo:@- newName Rename the file identified by the receiver to newName @meindex symlinkAs:@- @item symlinkAs:@- destName Create destName as a symbolic link of the receiver. The appropriate relative path is computed automatically. @meindex symlinkFrom:@- @item symlinkFrom:@- srcName Create the receiver as a symbolic link from srcName (relative to the path of the receiver). @meindex touch @item touch Update the timestamp of the file corresponding to the receiver. @meindex withReadStreamDo:@- @item withReadStreamDo:@- aBlock Answer the result of invoking aBlock with a reading stream open on me, closing it when the dynamic extent of aBlock ends. @meindex withWriteStreamDo:@- @item withWriteStreamDo:@- aBlock Answer the result of invoking aBlock with a writing stream open on me, closing it when the dynamic extent of aBlock ends. @meindex writeStream @item writeStream Open a write-only FileStream on the receiver @end table @node FilePath-printing @subsection FilePath:@- printing @table @b @meindex asString @item asString Print a representation of the receiver on aStream. @meindex displayOn:@- @item displayOn:@- aStream Print a representation of the receiver on aStream. @meindex printOn:@- @item printOn:@- aStream Print a representation of the receiver on aStream. @meindex withShellEscapes @item withShellEscapes Return the representation of the receiver with shell characters escaped. @end table @node FilePath-still unclassified @subsection FilePath:@- still unclassified @table @b @meindex / @item / aName Answer a File or Directory object as appropriate for a file named 'aName' in the directory represented by the receiver. @end table @node FilePath-testing @subsection FilePath:@- testing @table @b @meindex exists @item exists Answer whether a file with the name contained in the receiver does exist. @meindex isAbsolute @item isAbsolute Answer whether the receiver identifies an absolute path. @meindex isAccessible @item isAccessible Answer whether a directory with the name contained in the receiver does exist and can be accessed @meindex isDirectory @item isDirectory Answer whether a file with the name contained in the receiver does exist and identifies a directory. @meindex isExecutable @item isExecutable Answer whether a file with the name contained in the receiver does exist and is executable @meindex isFile @item isFile Answer whether a file with the name contained in the receiver does exist and does not identify a directory. @meindex isFileSystemPath @item isFileSystemPath Answer whether the receiver corresponds to a real filesystem path. @meindex isReadable @item isReadable Answer whether a file with the name contained in the receiver does exist and is readable @meindex isRelative @item isRelative Answer whether the receiver identifies a relative path. @meindex isSymbolicLink @item isSymbolicLink Answer whether a file with the name contained in the receiver does exist and identifies a symbolic link. @meindex isWriteable @item isWriteable Answer whether a file with the name contained in the receiver does exist and is writeable @end table @node FilePath-virtual filesystems @subsection FilePath:@- virtual filesystems @table @b @meindex zip @item zip Not commented. @end table @node FileSegment @section FileSegment @clindex FileSegment @table @b @item Defined in namespace Smalltalk @itemx Superclass: Object @itemx Category: Language-Implementation My instances represent sections of files. I am primarily used by the compiler to record source code locations. I am not a part of the normal Smalltalk-80 kernel; I am specific to the GNU Smalltalk implementation. @end table @menu * FileSegment class-basic:: (class) * FileSegment class-installing:: (class) * FileSegment-basic:: (instance) * FileSegment-equality:: (instance) * FileSegment-printing:: (instance) @end menu @node FileSegment class-basic @subsection FileSegment class:@- basic @table @b @meindex on:@-startingAt:@-for:@- @item on:@- aFile startingAt:@- startPos for:@- sizeInteger Create a new FileSegment referring to the contents of the given file, from the startPos-th byte and for sizeInteger bytes. Note that FileSegments should always be created with full paths because relative paths are interpreted to be relative to the kernel directory. @end table @node FileSegment class-installing @subsection FileSegment class:@- installing @table @b @meindex relocate @item relocate Remove the kernel path from all paths that start with it. Needed to support $(DESTDIR) and relocatable installation. @end table @node FileSegment-basic @subsection FileSegment:@- basic @table @b @meindex asString @item asString Answer a String containing the required segment of the file @meindex copyFrom:@-to:@- @item copyFrom:@- from to:@- to Answer a String containing the given subsegment of the file. As for streams, from and to are 0-based. @meindex file @item file Answer the File object for the file containing the segment @meindex fileName @item fileName Answer the name of the file containing the segment @meindex filePos @item filePos Answer the position in the file where the segment starts @meindex relocateFrom:@-map:@- @item relocateFrom:@- startPath map:@- map If the path starts with startPath, remove that part of the path. map is a Dictionary that is used so that equal filenames stay equal, without increasing the amount of memory that the image uses. @meindex size @item size Answer the length of the segment @meindex withFileDo:@- @item withFileDo:@- aBlock Evaluate aBlock passing it the FileStream in which the segment identified by the receiver is stored @end table @node FileSegment-equality @subsection FileSegment:@- equality @table @b @meindex = @item = aFileSegment Answer whether the receiver and aFileSegment are equal. @meindex hash @item hash Answer an hash value for the receiver. @end table @node FileSegment-printing @subsection FileSegment:@- printing @table @b @meindex printedFileName @item printedFileName Answer a printed representation of the file containing the segment. While introducing some ambiguity, this representation is compact eliminates the path for kernel files, and produces a relative path from the current working directory for other files. @end table @node FileStream @section FileStream @clindex FileStream @table @b @item Defined in namespace Smalltalk @itemx Superclass: FileDescriptor @itemx Category: Streams-Files My instances are what conventional programmers think of as files. My instance creation methods accept the name of a disk file (or any named file object, such as /dev/rmt0 on UNIX or MTA0:@- on VMS). @end table @menu * FileStream class-file-in:: (class) * FileStream class-standard streams:: (class) * FileStream-basic:: (instance) * FileStream-buffering:: (instance) * FileStream-compiling:: (instance) * FileStream-initialize-release:: (instance) * FileStream-overriding inherited methods:: (instance) * FileStream-testing:: (instance) @end menu @node FileStream class-file-in @subsection FileStream class:@- file-in @table @b @meindex fileIn:@- @item fileIn:@- aFileName File in the aFileName file. During a file in operation, global variables (starting with an uppercase letter) that are not declared yet don't yield an `unknown variable' error. Instead, they are defined as nil in the `Undeclared' dictionary (a global variable residing in Smalltalk). As soon as you add the variable to a namespace (for example by creating a class) the Association will be removed from Undeclared and reused in the namespace, so that the old references will automagically point to the new value. @meindex fileIn:@-ifMissing:@- @item fileIn:@- aFileName ifMissing:@- aSymbol Conditionally do a file in, only if the key (often a class) specified by 'aSymbol' is not present in the Smalltalk system dictionary already. During a file in operation, global variables (starting with an uppercase letter) that are not declared don't yield an `unknown variable' error. Instead, they are defined as nil in the `Undeclared' dictionary (a global variable residing in Smalltalk). As soon as you add the variable to a namespace (for example by creating a class) the Association will be removed from Undeclared and reused in the namespace, so that the old references will automagically point to the new value. @meindex fileIn:@-ifTrue:@- @item fileIn:@- aFileName ifTrue:@- aBoolean Conditionally do a file in, only if the supplied boolean is true. During a file in operation, global variables (starting with an uppercase letter) that are not declared don't yield an `unknown variable' error. Instead, they are defined as nil in the `Undeclared' dictionary (a global variable residing in Smalltalk). As soon as you add the variable to a namespace (for example by creating a class) the Association will be removed from Undeclared and reused in the namespace, so that the old references will automagically point to the new value. @meindex fileIn:@-line:@-from:@-at:@- @item fileIn:@- aFileName line:@- lineInteger from:@- realFileName at:@- aCharPos File in the aFileName file giving errors such as if it was loaded from the given line, file name and starting position (instead of 1). @meindex generateMakefileOnto:@- @item generateMakefileOnto:@- aStream Generate a make file for the file-ins since record was last set to true. Store it on aStream @meindex initialize @item initialize Private - Initialize the receiver's class variables @meindex record:@- @slindex generateMakefileOnto:@- @item record:@- recordFlag Set whether Smalltalk should record information about nested file-ins. When recording is enabled, use #generateMakefileOnto:@- to automatically generate a valid makefile for the intervening file-ins. @meindex require:@- @item require:@- assoc Conditionally do a file in from the value of assoc, only if the key of assoc is not present in the Smalltalk system dictionary already. During a file in operation, global variables (starting with an uppercase letter) that are not declared don't yield an `unknown variable' error. Instead, they are defined as nil in the `Undeclared' dictionary (a global variable residing in Smalltalk). As soon as you add the variable to a namespace (for example by creating a class) the Association will be removed from Undeclared and reused in the namespace, so that the old references will automagically point to the new value. @meindex verbose:@- @item verbose:@- verboseFlag Set whether Smalltalk should output debugging messages when filing in @end table @node FileStream class-standard streams @subsection FileStream class:@- standard streams @table @b @meindex stderr @item stderr Answer a FileStream that is attached the Smalltalk program's standard error file handle, which can be used for error messages and diagnostics issued by the program. @meindex stdin @item stdin Answer a FileStream that is attached the Smalltalk program's standard input file handle, which is the normal source of input for the program. @meindex stdout @item stdout Answer a FileStream that is attached the Smalltalk program's standard output file handle; this is used for normal output from the program. @end table @node FileStream-basic @subsection FileStream:@- basic @table @b @meindex bufferStart @item bufferStart Private - Answer the offset from the start of the file corresponding to the beginning of the read buffer. @meindex copyFrom:@-to:@- @item copyFrom:@- from to:@- to Answer the contents of the file between the two given positions @meindex next @item next Return the next character in the file, or nil at eof @meindex nextPut:@- @item nextPut:@- aCharacter Store aCharacter on the file @meindex peek @item peek Return the next character in the file, or nil at eof. Don't advance the file pointer. @meindex position @item position Answer the zero-based position from the start of the file @meindex position:@- @item position:@- n Set the file pointer to the zero-based position n @meindex size @item size Return the current size of the file, in bytes @meindex truncate @item truncate Truncate the file at the current position @end table @node FileStream-buffering @subsection FileStream:@- buffering @table @b @meindex bufferSize @item bufferSize Answer the file's current buffer @meindex bufferSize:@- @item bufferSize:@- bufSize Flush the file and set the buffer's size to bufSize @meindex clean @item clean Synchronize the file descriptor's state with the object's state. @meindex fill @item fill Private - Fill the input buffer @meindex flush @item flush Flush the output buffer. @meindex newBuffer @item newBuffer Private - Answer a String to be used as the receiver's buffer @meindex next:@-bufferAll:@-startingAt:@- @item next:@- n bufferAll:@- aCollection startingAt:@- pos Private - Assuming that the buffer has space for n characters, store n characters of aCollection in the buffer, starting from the pos-th. @meindex nextAvailable:@-into:@-startingAt:@- @item nextAvailable:@- anInteger into:@- aCollection startingAt:@- pos Read up to anInteger bytes from the stream and store them into aCollection. Return the number of bytes read. @meindex nextAvailable:@-putAllOn:@- @item nextAvailable:@- anInteger putAllOn:@- aStream Copy up to anInteger bytes from the stream into aStream. Return the number of bytes read. @meindex pendingWrite @item pendingWrite Answer whether the output buffer is full. @end table @node FileStream-compiling @subsection FileStream:@- compiling @table @b @meindex segmentFrom:@-to:@- @slindex asString @item segmentFrom:@- startPos to:@- endPos Answer an object that, when sent #asString, will yield the result of sending `copyFrom:@- startPos to:@- endPos' to the receiver @end table @node FileStream-initialize-release @subsection FileStream:@- initialize-release @table @b @meindex initialize @item initialize Initialize the receiver's instance variables @end table @node FileStream-overriding inherited methods @subsection FileStream:@- overriding inherited methods @table @b @meindex next:@-putAll:@-startingAt:@- @item next:@- n putAll:@- aCollection startingAt:@- pos Write n values from aCollection, the first being at pos. @meindex nextLine @item nextLine Returns a collection of the same type that the stream accesses, containing the next line up to the next new-line character. Returns the entire rest of the stream's contents if no new-line character is found. @meindex nextPutAllOn:@- @item nextPutAllOn:@- aStream Put all the characters of the receiver in aStream. @meindex upTo:@- @item upTo:@- aCharacter Returns a collection of the same type that the stream accesses, containing data up to aCharacter. Returns the entire rest of the stream's contents if no such character is found. @end table @node FileStream-testing @subsection FileStream:@- testing @table @b @meindex atEnd @item atEnd Answer whether data has come to an end @end table @node Float @section Float @clindex Float @table @b @item Defined in namespace Smalltalk @itemx Superclass: Number @itemx Category: Language-Data types My instances represent floating point numbers that have arbitrary precision. Besides the standard numerical operations, they provide transcendental operations too. They implement IEEE-754 correctly if the hardware supports it. @end table @menu * Float class-byte-order dependancies:: (class) * Float class-characterization:: (class) * Float-arithmetic:: (instance) * Float-basic:: (instance) * Float-built ins:: (instance) * Float-coercing:: (instance) * Float-coercion:: (instance) * Float-comparing:: (instance) * Float-compiler:: (instance) * Float-converting:: (instance) * Float-floating point:: (instance) * Float-misc math:: (instance) * Float-printing:: (instance) * Float-storing:: (instance) * Float-testing:: (instance) * Float-testing functionality:: (instance) * Float-transcendental operations:: (instance) * Float-truncation and round off:: (instance) @end menu @node Float class-byte-order dependancies @subsection Float class:@- byte-order dependancies @table @b @meindex signByte @item signByte Answer the byte of the receiver that contains the sign bit @end table @node Float class-characterization @subsection Float class:@- characterization @table @b @meindex denormalized @item denormalized Answer whether instances of the receiver can be in denormalized form. @meindex e @item e Returns the value of e. Hope is that it is precise enough @meindex epsilon @item epsilon Return the smallest Float x for which is 1 + x ~= 1 @meindex fmin @item fmin Return the smallest Float that is > 0. @meindex fminDenormalized @item fminDenormalized Return the smallest Float that is > 0 if denormalized values are supported, else return 0. @meindex ln10 @item ln10 Returns the value of ln 10. Hope is that it is precise enough @meindex log10Base2 @item log10Base2 Returns the value of log2 10. Hope is that it is precise enough @meindex pi @item pi Returns the value of pi. Hope is that it is precise enough @meindex radix @item radix Answer the base in which computations between instances of the receiver are made. This should be 2 on about every known computer, so GNU Smalltalk always answers 2. @end table @node Float-arithmetic @subsection Float:@- arithmetic @table @b @meindex integerPart @item integerPart Return the receiver's integer part @meindex negated @item negated Return the negation of the receiver. Unlike 0-self, this converts correctly signed zeros. @meindex raisedToInteger:@- @item raisedToInteger:@- anInteger Return self raised to the anInteger-th power @end table @node Float-basic @subsection Float:@- basic @table @b @meindex hash @item hash Answer an hash value for the receiver. Not-a-number values do not have a hash code and cannot be put in a hashed collection. @end table @node Float-built ins @subsection Float:@- built ins @table @b @meindex arcCos @item arcCos Answer the arc-cosine of the receiver @meindex arcSin @item arcSin Answer the arc-sine of the receiver @meindex arcTan @item arcTan Answer the arc-tangent of the receiver @meindex ceiling @item ceiling Answer the integer part of the receiver, truncated towards +infinity @meindex cos @item cos Answer the cosine of the receiver @meindex exp @item exp Answer 'e' (2.718281828459...) raised to the receiver @meindex floor @item floor Answer the integer part of the receiver, truncated towards -infinity @meindex ln @item ln Answer the logarithm of the receiver in base 'e' (2.718281828459...) @meindex primHash @item primHash Private - Answer an hash value for the receiver @meindex raisedTo:@- @item raisedTo:@- aNumber Answer the receiver raised to its aNumber power @meindex sin @item sin Answer the sine of the receiver @meindex sqrt @item sqrt Answer the square root of the receiver @meindex tan @item tan Answer the tangent of the receiver @end table @node Float-coercing @subsection Float:@- coercing @table @b @meindex asExactFraction @item asExactFraction Convert the receiver into a fraction with optimal approximation, but with usually huge terms. @meindex asFraction @item asFraction Convert the receiver into a fraction with a good (but undefined) approximation @meindex truncated @item truncated Convert the receiver to an Integer. Only used for LargeIntegers, there are primitives for the other cases. @end table @node Float-coercion @subsection Float:@- coercion @table @b @meindex asCNumber @item asCNumber Convert the receiver to a kind of number that is understood by the C call-out mechanism. @end table @node Float-comparing @subsection Float:@- comparing @table @b @meindex max:@- @item max:@- aNumber Answer the maximum between the receiver and aNumber. Redefine in subclasses if necessary to ensure that if either self or aNumber is a NaN, it is always answered. @meindex min:@- @item min:@- aNumber Answer the minimum between the receiver and aNumber. Redefine in subclasses if necessary to ensure that if either self or aNumber is a NaN, it is always answered. @meindex withSignOf:@- @item withSignOf:@- aNumber Answer the receiver, with its sign possibly changed to match that of aNumber. @end table @node Float-compiler @subsection Float:@- compiler @table @b @meindex literalEquals:@- @item literalEquals:@- anObject Not commented. @meindex literalHash @item literalHash Not commented. @end table @node Float-converting @subsection Float:@- converting @table @b @meindex half @item half Answer 0.5 in the representation of the receiver @end table @node Float-floating point @subsection Float:@- floating point @table @b @meindex predecessor @item predecessor Not commented. @meindex successor @item successor Not commented. @end table @node Float-misc math @subsection Float:@- misc math @table @b @meindex log:@- @item log:@- aNumber Answer log base aNumber of the receiver @end table @node Float-printing @subsection Float:@- printing @table @b @meindex printOn:@- @item printOn:@- aStream Print a representation of the receiver on aStream @end table @node Float-storing @subsection Float:@- storing @table @b @meindex isLiteralObject @item isLiteralObject Answer whether the receiver is expressible as a Smalltalk literal. @meindex storeLiteralOn:@- @item storeLiteralOn:@- aStream Store on aStream some Smalltalk code which compiles to the receiver @meindex storeOn:@- @item storeOn:@- aStream Print a representation of the receiver on aStream @end table @node Float-testing @subsection Float:@- testing @table @b @meindex isExact @item isExact Answer whether the receiver performs exact arithmetic. Floats do not. @meindex isFinite @item isFinite Answer whether the receiver does not represent infinity, nor a NaN @meindex isInfinite @item isInfinite Answer whether the receiver represents positive or negative infinity @meindex isNaN @item isNaN Answer whether the receiver represents a NaN @meindex negative @item negative Answer whether the receiver is negative @meindex positive @item positive Answer whether the receiver is positive. Negative zero is not positive, so the definition is not simply >= 0. @meindex sign @item sign Answer 1 if the receiver is greater than 0, -1 if less than 0, else 0. Negative zero is the same as positive zero. @meindex strictlyPositive @item strictlyPositive Answer whether the receiver is > 0 @end table @node Float-testing functionality @subsection Float:@- testing functionality @table @b @meindex isFloat @item isFloat Answer `true'. @end table @node Float-transcendental operations @subsection Float:@- transcendental operations @table @b @meindex asFloat @item asFloat Just defined for completeness. Return the receiver. @meindex ceilingLog:@- @item ceilingLog:@- radix Answer (self log:@- radix) ceiling. Use exact arithmetic if radix is not a floating point value. @meindex estimatedLog @item estimatedLog Answer an estimate of (self abs floorLog:@- 10) @meindex floorLog:@- @item floorLog:@- radix Answer (self log:@- radix) floor. Use exact arithmetic if radix is not a floating point value. @meindex log @item log Answer log base 10 of the receiver. @end table @node Float-truncation and round off @subsection Float:@- truncation and round off @table @b @meindex rounded @item rounded Answer the receiver, rounded to the nearest integer @end table @node FloatD @section FloatD @clindex FloatD @table @b @item Defined in namespace Smalltalk @itemx Superclass: Float @itemx Category: Language-Data types My instances represent floating point numbers that have the same accuracy as C's "double" numbers. @end table @menu * FloatD class-byte-order dependencies:: (class) * FloatD class-characterization:: (class) * FloatD class-converting:: (class) * FloatD-built ins:: (instance) * FloatD-coercing:: (instance) * FloatD-converting:: (instance) @end menu @node FloatD class-byte-order dependencies @subsection FloatD class:@- byte-order dependencies @table @b @meindex fromBytes:@- @item fromBytes:@- aByteArray Answer a float with the bytes in aByteArray, which are in big-endian format. @meindex signByte @item signByte Answer the byte of the receiver that contains the sign bit @end table @node FloatD class-characterization @subsection FloatD class:@- characterization @table @b @meindex decimalDigits @item decimalDigits Return the number of decimal digits of precision for a FloatD. Technically, if P is the precision for the representation, then the decimal precision Q is the maximum number of decimal digits such that any floating point number with Q base 10 digits can be rounded to a floating point number with P base 2 digits and back again, without change to the Q decimal digits. @meindex emax @item emax Return the maximum allowable exponent for a FloatD that is finite. @meindex emin @item emin Return the maximum allowable exponent for a FloatD that is finite. @meindex fmax @item fmax Return the largest normalized FloatD that is not infinite. @meindex fminNormalized @item fminNormalized Return the smallest normalized FloatD that is > 0 @meindex infinity @item infinity Return a FloatD that represents positive infinity. @meindex nan @item nan Return a FloatD that represents a mathematically indeterminate value (e.g. Inf - Inf, Inf / Inf). @meindex negativeInfinity @item negativeInfinity Return a FloatD that represents negative infinity. @meindex precision @item precision Answer the number of bits in the mantissa. 1 + (2^-precision) = 1 @end table @node FloatD class-converting @subsection FloatD class:@- converting @table @b @meindex coerce:@- @item coerce:@- aNumber Answer aNumber converted to a FloatD @end table @node FloatD-built ins @subsection FloatD:@- built ins @table @b @meindex * @item * arg Multiply the receiver and arg and answer another Number @meindex + @item + arg Sum the receiver and arg and answer another Number @meindex - @item - arg Subtract arg from the receiver and answer another Number @meindex / @item / arg Divide the receiver by arg and answer another FloatD @meindex < @item < arg Answer whether the receiver is less than arg @meindex <= @item <= arg Answer whether the receiver is less than or equal to arg @meindex = @item = arg Answer whether the receiver is equal to arg @meindex > @item > arg Answer whether the receiver is greater than arg @meindex >= @item >= arg Answer whether the receiver is greater than or equal to arg @meindex asFloatE @item asFloatE Answer the receiver converted to a FloatE @meindex asFloatQ @item asFloatQ Answer the receiver converted to a FloatQ @meindex exponent @item exponent Answer the exponent of the receiver in mantissa*2^exponent representation ( |mantissa|<=1 ) @meindex fractionPart @item fractionPart Answer the fractional part of the receiver @meindex timesTwoPower:@- @item timesTwoPower:@- arg Answer the receiver multiplied by 2^arg @meindex truncated @item truncated Truncate the receiver towards zero and answer the result @meindex ~= @item ~= arg Answer whether the receiver is not equal to arg @end table @node FloatD-coercing @subsection FloatD:@- coercing @table @b @meindex asFloatD @item asFloatD Just defined for completeness. Return the receiver. @meindex coerce:@- @item coerce:@- aNumber Coerce aNumber to the receiver's class @meindex generality @item generality Answer the receiver's generality @meindex unity @item unity Coerce 1 to the receiver's class @meindex zero @item zero Coerce 0 to the receiver's class @end table @node FloatD-converting @subsection FloatD:@- converting @table @b @meindex half @item half Coerce 0.5 to the receiver's class @end table @node FloatE @section FloatE @clindex FloatE @table @b @item Defined in namespace Smalltalk @itemx Superclass: Float @itemx Category: Language-Data types My instances represent floating point numbers that have the same accuracy as C's "float" numbers. @end table @menu * FloatE class-byte-order dependancies:: (class) * FloatE class-byte-order dependencies:: (class) * FloatE class-characterization:: (class) * FloatE class-converting:: (class) * FloatE-built ins:: (instance) * FloatE-coercing:: (instance) * FloatE-converting:: (instance) @end menu @node FloatE class-byte-order dependancies @subsection FloatE class:@- byte-order dependancies @table @b @meindex signByte @item signByte Answer the byte of the receiver that contains the sign bit @end table @node FloatE class-byte-order dependencies @subsection FloatE class:@- byte-order dependencies @table @b @meindex fromBytes:@- @item fromBytes:@- aByteArray Answer a float with the bytes in aByteArray, which are in big-endian format. @end table @node FloatE class-characterization @subsection FloatE class:@- characterization @table @b @meindex decimalDigits @item decimalDigits Return the number of decimal digits of precision for a FloatE. Technically, if P is the precision for the representation, then the decimal precision Q is the maximum number of decimal digits such that any floating point number with Q base 10 digits can be rounded to a floating point number with P base 2 digits and back again, without change to the Q decimal digits. @meindex e @item e Returns the value of e. Hope is that it is precise enough @meindex emax @item emax Return the maximum allowable exponent for a FloatE that is finite. @meindex emin @item emin Return the maximum allowable exponent for a FloatE that is finite. @meindex fmax @item fmax Return the largest normalized FloatE that is not infinite. @meindex fminNormalized @item fminNormalized Return the smallest normalized FloatE that is > 0 @meindex infinity @item infinity Return a FloatE that represents positive infinity. @meindex ln10 @item ln10 Returns the value of ln 10. Hope is that it is precise enough @meindex log10Base2 @item log10Base2 Returns the value of log2 10. Hope is that it is precise enough @meindex nan @item nan Return a FloatE that represents a mathematically indeterminate value (e.g. Inf - Inf, Inf / Inf). @meindex negativeInfinity @item negativeInfinity Return a FloatE that represents negative infinity. @meindex pi @item pi Returns the value of pi. Hope is that it is precise enough @meindex precision @item precision Answer the number of bits in the mantissa. 1 + (2^-precision) = 1 @end table @node FloatE class-converting @subsection FloatE class:@- converting @table @b @meindex coerce:@- @item coerce:@- aNumber Answer aNumber converted to a FloatE @end table @node FloatE-built ins @subsection FloatE:@- built ins @table @b @meindex * @item * arg Multiply the receiver and arg and answer another Number @meindex + @item + arg Sum the receiver and arg and answer another Number @meindex - @item - arg Subtract arg from the receiver and answer another Number @meindex / @item / arg Divide the receiver by arg and answer another FloatE @meindex < @item < arg Answer whether the receiver is less than arg @meindex <= @item <= arg Answer whether the receiver is less than or equal to arg @meindex = @item = arg Answer whether the receiver is equal to arg @meindex > @item > arg Answer whether the receiver is greater than arg @meindex >= @item >= arg Answer whether the receiver is greater than or equal to arg @meindex asFloatD @item asFloatD Answer the receiver converted to a FloatD @meindex asFloatQ @item asFloatQ Answer the receiver converted to a FloatQ @meindex exponent @item exponent Answer the exponent of the receiver in mantissa*2^exponent representation ( |mantissa|<=1 ) @meindex fractionPart @item fractionPart Answer the fractional part of the receiver @meindex timesTwoPower:@- @item timesTwoPower:@- arg Answer the receiver multiplied by 2^arg @meindex truncated @item truncated Truncate the receiver towards zero and answer the result @meindex ~= @item ~= arg Answer whether the receiver is not equal to arg @end table @node FloatE-coercing @subsection FloatE:@- coercing @table @b @meindex asFloatE @item asFloatE Just defined for completeness. Return the receiver. @meindex coerce:@- @item coerce:@- aNumber Coerce aNumber to the receiver's class @meindex generality @item generality Answer the receiver's generality @meindex unity @item unity Coerce 1 to the receiver's class @meindex zero @item zero Coerce 0 to the receiver's class @end table @node FloatE-converting @subsection FloatE:@- converting @table @b @meindex half @item half Coerce 0.5 to the receiver's class @end table @node FloatQ @section FloatQ @clindex FloatQ @table @b @item Defined in namespace Smalltalk @itemx Superclass: Float @itemx Category: Language-Data types My instances represent floating point numbers that have the same accuracy as C's "long double" numbers. @end table @menu * FloatQ class-byte-order dependancies:: (class) * FloatQ class-characterization:: (class) * FloatQ class-converting:: (class) * FloatQ-built ins:: (instance) * FloatQ-coercing:: (instance) * FloatQ-converting:: (instance) @end menu @node FloatQ class-byte-order dependancies @subsection FloatQ class:@- byte-order dependancies @table @b @meindex signByte @item signByte Answer the byte of the receiver that contains the sign bit @end table @node FloatQ class-characterization @subsection FloatQ class:@- characterization @table @b @meindex decimalDigits @item decimalDigits Return the number of decimal digits of precision for a FloatQ. Technically, if P is the precision for the representation, then the decimal precision Q is the maximum number of decimal digits such that any floating point number with Q base 10 digits can be rounded to a floating point number with P base 2 digits and back again, without change to the Q decimal digits. @meindex e @item e Returns the value of e. Hope is that it is precise enough @meindex emax @item emax Return the maximum allowable exponent for a FloatQ that is finite. @meindex emin @item emin Return the maximum allowable exponent for a FloatQ that is finite. @meindex fmax @item fmax Return the largest normalized FloatQ that is not infinite. @meindex fminNormalized @item fminNormalized Return the smallest normalized FloatQ that is > 0 @meindex infinity @item infinity Return a FloatQ that represents positive infinity. @meindex ln10 @item ln10 Returns the value of ln 10. Hope is that it is precise enough @meindex log10Base2 @item log10Base2 Returns the value of log2 10. Hope is that it is precise enough @meindex nan @item nan Return a FloatQ that represents a mathematically indeterminate value (e.g. Inf - Inf, Inf / Inf). @meindex negativeInfinity @item negativeInfinity Return a FloatQ that represents negative infinity. @meindex pi @item pi Returns the value of pi. Hope is that it is precise enough @meindex precision @item precision Answer the number of bits in the mantissa. 1 + (2^-precision) = 1 @end table @node FloatQ class-converting @subsection FloatQ class:@- converting @table @b @meindex coerce:@- @item coerce:@- aNumber Answer aNumber converted to a FloatQ @end table @node FloatQ-built ins @subsection FloatQ:@- built ins @table @b @meindex * @item * arg Multiply the receiver and arg and answer another Number @meindex + @item + arg Sum the receiver and arg and answer another Number @meindex - @item - arg Subtract arg from the receiver and answer another Number @meindex / @item / arg Divide the receiver by arg and answer another FloatQ @meindex < @item < arg Answer whether the receiver is less than arg @meindex <= @item <= arg Answer whether the receiver is less than or equal to arg @meindex = @item = arg Answer whether the receiver is equal to arg @meindex > @item > arg Answer whether the receiver is greater than arg @meindex >= @item >= arg Answer whether the receiver is greater than or equal to arg @meindex asFloatD @item asFloatD Answer the receiver converted to a FloatD @meindex asFloatE @item asFloatE Answer the receiver converted to a FloatE @meindex exponent @item exponent Answer the exponent of the receiver in mantissa*2^exponent representation ( |mantissa|<=1 ) @meindex fractionPart @item fractionPart Answer the fractional part of the receiver @meindex timesTwoPower:@- @item timesTwoPower:@- arg Answer the receiver multiplied by 2^arg @meindex truncated @item truncated Truncate the receiver towards zero and answer the result @meindex ~= @item ~= arg Answer whether the receiver is not equal to arg @end table @node FloatQ-coercing @subsection FloatQ:@- coercing @table @b @meindex asFloatQ @item asFloatQ Just defined for completeness. Return the receiver. @meindex coerce:@- @item coerce:@- aNumber Coerce aNumber to the receiver's class @meindex generality @item generality Answer the receiver's generality @meindex unity @item unity Coerce 1 to the receiver's class @meindex zero @item zero Coerce 0 to the receiver's class @end table @node FloatQ-converting @subsection FloatQ:@- converting @table @b @meindex half @item half Coerce 0.5 to the receiver's class @end table @node Fraction @section Fraction @clindex Fraction @table @b @item Defined in namespace Smalltalk @itemx Superclass: Number @itemx Category: Language-Data types I represent rational numbers in the form (p/q) where p and q are integers. The arithmetic operations *, +, -, /, on fractions, all return a reduced fraction. @end table @menu * Fraction class-converting:: (class) * Fraction class-instance creation:: (class) * Fraction-accessing:: (instance) * Fraction-arithmetic:: (instance) * Fraction-coercing:: (instance) * Fraction-coercion:: (instance) * Fraction-comparing:: (instance) * Fraction-converting:: (instance) * Fraction-optimized cases:: (instance) * Fraction-printing:: (instance) * Fraction-testing:: (instance) @end menu @node Fraction class-converting @subsection Fraction class:@- converting @table @b @meindex coerce:@- @item coerce:@- aNumber Answer aNumber converted to a Fraction @end table @node Fraction class-instance creation @subsection Fraction class:@- instance creation @table @b @meindex initialize @item initialize Initialize the receiver's class variables @meindex numerator:@-denominator:@- @item numerator:@- nInteger denominator:@- dInteger Answer a new instance of fraction (nInteger/dInteger) @end table @node Fraction-accessing @subsection Fraction:@- accessing @table @b @meindex denominator @item denominator Answer the receiver's denominator @meindex numerator @item numerator Answer the receiver's numerator @end table @node Fraction-arithmetic @subsection Fraction:@- arithmetic @table @b @meindex * @item * aNumber Multiply two numbers and answer the result. @meindex + @item + aNumber Sum two numbers and answer the result. @meindex - @item - aNumber Subtract aNumber from the receiver and answer the result. @meindex / @item / aNumber Divide the receiver by aNumber and answer the result. @meindex // @item // aNumber Return the integer quotient of dividing the receiver by aNumber with truncation towards negative infinity. @meindex \\ @item \\ aNumber Return the remainder from dividing the receiver by aNumber, (using //). @meindex estimatedLog @item estimatedLog Answer an estimate of (self abs floorLog:@- 10) @end table @node Fraction-coercing @subsection Fraction:@- coercing @table @b @meindex ceiling @item ceiling Truncate the receiver towards positive infinity and return the truncated result @meindex coerce:@- @item coerce:@- aNumber Coerce aNumber to the receiver's class @meindex floor @item floor Truncate the receiver towards negative infinity and return the truncated result @meindex generality @item generality Return the receiver's generality @meindex truncated @item truncated Truncate the receiver and return the truncated result @meindex unity @item unity Coerce 1 to the receiver's class @meindex zero @item zero Coerce 0 to the receiver's class @end table @node Fraction-coercion @subsection Fraction:@- coercion @table @b @meindex asCNumber @item asCNumber Convert the receiver to a kind of number that is understood by the C call-out mechanism. @end table @node Fraction-comparing @subsection Fraction:@- comparing @table @b @meindex < @item < arg Test if the receiver is less than arg. @meindex <= @item <= arg Test if the receiver is less than or equal to arg. @meindex = @item = arg Test if the receiver equals arg. @meindex > @item > arg Test if the receiver is more than arg. @meindex >= @item >= arg Test if the receiver is greater than or equal to arg. @meindex hash @item hash Answer an hash value for the receiver @end table @node Fraction-converting @subsection Fraction:@- converting @table @b @meindex asExactFraction @item asExactFraction Answer the receiver, it is already a Fraction @meindex asFloatD @item asFloatD Answer the receiver converted to a FloatD @meindex asFloatE @item asFloatE Answer the receiver converted to a FloatD @meindex asFloatQ @item asFloatQ Answer the receiver converted to a FloatD @meindex asFraction @item asFraction Answer the receiver, it is already a Fraction @meindex integerPart @item integerPart Answer the integer part of the receiver, expressed as a Fraction @end table @node Fraction-optimized cases @subsection Fraction:@- optimized cases @table @b @meindex negated @item negated Return the receiver, with its sign changed. @meindex raisedToInteger:@- @item raisedToInteger:@- anInteger Return self raised to the anInteger-th power. @meindex reciprocal @item reciprocal Return the reciprocal of the receiver @meindex sqrt @item sqrt Return the square root of the receiver. @meindex squared @item squared Return the square of the receiver. @end table @node Fraction-printing @subsection Fraction:@- printing @table @b @meindex printOn:@- @item printOn:@- aStream Print a representation of the receiver on aStream @meindex storeOn:@- @item storeOn:@- aStream Store Smalltalk code compiling to the receiver on aStream @end table @node Fraction-testing @subsection Fraction:@- testing @table @b @meindex isRational @item isRational Answer whether the receiver is rational - true @end table @node Generator @section Generator @clindex Generator @table @b @item Defined in namespace Smalltalk @itemx Superclass: Stream @itemx Category: Streams-Generators A Generator object provides a way to use blocks to define a Stream of many return values. The return values are computed one at a time, as needed, and hence need not even be finite. A generator block is converted to a Generator with "Generator on:@- [...]". The Generator itself is passed to the block, and as soon as a message like #next, #peek, #atEnd or #peekFor:@- is sent to the generator, execution of the block starts/resumes and goes on until the generator's #yield:@- method is called:@- then the argument of #yield:@- will be the Generator's next element. If the block goes on to the end without calling #yield:@-, the Generator will produce no more elements and #atEnd will return true. You could achieve the effect of generators manually by writing your own class and storing all the local variables of the generator as instance variables. For example, returning a list of integers could be done by setting a variable to 0, and having the #next method increment it and return it. However, for a moderately complicated generator, writing a corresponding class would be much messier (and might lead to code duplication or inefficiency if you want to support #peek, #peekFor:@- and/or #atEnd):@- in general, providing a #do:@--like interface is easy, but not providing a Stream-like one (think binary trees). The idea of generators comes from other programming languages, in particular this interface looks much like Scheme streams and Python generators. But Python in turn mutuated the idea for example from Icon, where the idea of generators is central. In Icon, every expression and function call behaves like a generator, and if a statement manages scalars, it automatically uses up all the results that the corresponding generator provides; on the other hand, Icon does not represent generators as first-class objects like Python and Smalltalk do. @end table @menu * Generator class-instance creation:: (class) * Generator-stream protocol:: (instance) @end menu @node Generator class-instance creation @subsection Generator class:@- instance creation @table @b @meindex inject:@-into:@- @item inject:@- aValue into:@- aBlock Return an infinite generator; the first item is aValue, the following items are obtained by passing the previous value to aBlock. @meindex on:@- @slindex next @slindex yield:@- @item on:@- aBlock Return a generator and pass it to aBlock. When #next is sent to the generator, the block will start execution, and will be suspended again as soon as #yield:@- is sent from the block to the generator. @meindex on:@-do:@- @item on:@- aCollection do:@- aBlock Return a generator; for each item of aCollection, evaluate aBlock passing the generator and the item. @end table @node Generator-stream protocol @subsection Generator:@- stream protocol @table @b @meindex atEnd @item atEnd Answer whether more data can be generated. @meindex next @item next Evaluate the generator until it generates the next value or decides that nothing else can be generated. @meindex peek @slindex peek @slindex next @item peek Evaluate the generator until it generates the next value or decides that nothing else can be generated, and save the value so that #peek or #next will return it again. @meindex peekFor:@- @slindex peek @slindex next @item peekFor:@- anObject Evaluate the generator until it generates the next value or decides that nothing else can be generated, and if it is not equal to anObject, save the value so that #peek or #next will return it again. @meindex yield:@- @item yield:@- anObject When entering from the generator the code in the block is executed and control flow goes back to the consumer. When entering from the consumer, the code after the continuation is executed, which resumes execution of the generator block. @end table @node Getopt @section Getopt @clindex Getopt @table @b @item Defined in namespace Smalltalk @itemx Superclass: Object @itemx Category: Language-Data types This class is usually not instantiated. Class methods provide a way to parse command lines from Smalltalk. @end table @menu * Getopt class-instance creation:: (class) @end menu @node Getopt class-instance creation @subsection Getopt class:@- instance creation @table @b @meindex parse:@-with:@-do:@- @slindex parse:@-with:@-do:@-ifError:@- @item parse:@- args with:@- pattern do:@- actionBlock Parse the command-line arguments in args according to the syntax specified in pattern. For every command-line option found, the two-argument block actionBlock is evaluated passing the option name and the argument. For file names (or in general, other command-line arguments than options) the block's first argument will be nil. For options without arguments, or with unspecified optional arguments, the block's second argument will be nil. The option name will be passed as a character object for short options, and as a string for long options. If an error is found, nil is returned. For more information on the syntax of pattern, see #parse:@-with:@-do:@-ifError:@-. @meindex parse:@-with:@-do:@-ifError:@- @item parse:@- args with:@- pattern do:@- actionBlock ifError:@- errorBlock Parse the command-line arguments in args according to the syntax specified in pattern. For every command-line option found, the two-argument block actionBlock is evaluated passing the option name and the argument. For file names (or in general, other command-line arguments than options) the block's first argument will be nil. For options without arguments, or with unspecified optional arguments, the block's second argument will be nil. The option name will be passed as a character object for short options, and as a string for long options. If an error is found, the parsing is interrupted, errorBlock is evaluated, and the returned value is answered. Every whitespace-separated part (`word') of pattern specifies a command-line option. If a word ends with a colon, the option will have a mandatory argument. If a word ends with two colons, the option will have an optional argument. Before the colons, multiple option names (either short names like `-l' or long names like `--long') can be specified. Before passing the option to actionBlock, the name will be canonicalized to the last one. Prefixes of long options are accepted as long as they're unique, and they are canonicalized to the full name before passing it to actionBlock. Additionally, the full name of an option is accepted even if it is the prefix of a longer option. Mandatory arguments can appear in the next argument, or in the same argument (separated by an = for arguments to long options). Optional arguments must appear in the same argument. @end table @node Halt @section Halt @clindex Halt @table @b @item Defined in namespace Smalltalk @itemx Superclass: Exception @itemx Category: Language-Exceptions Halt represents a resumable error, usually a bug. @end table @menu * Halt-description:: (instance) @end menu @node Halt-description @subsection Halt:@- description @table @b @meindex description @item description Answer a textual description of the exception. @meindex isResumable @slindex halt @item isResumable Answer true. #halt exceptions are by default resumable. @end table @node HashedCollection @section HashedCollection @clindex HashedCollection @table @b @item Defined in namespace Smalltalk @itemx Superclass: Collection @itemx Category: Collections-Unordered I am an hashed collection that can store objects uniquely and give fast responses on their presence in the collection. @end table @menu * HashedCollection class-instance creation:: (class) * HashedCollection-accessing:: (instance) * HashedCollection-builtins:: (instance) * HashedCollection-copying:: (instance) * HashedCollection-enumerating the elements of a collection:: (instance) * HashedCollection-rehashing:: (instance) * HashedCollection-removing:: (instance) * HashedCollection-saving and loading:: (instance) * HashedCollection-storing:: (instance) * HashedCollection-testing collections:: (instance) @end menu @node HashedCollection class-instance creation @subsection HashedCollection class:@- instance creation @table @b @meindex new @item new Answer a new instance of the receiver with a default size @meindex new:@- @item new:@- anInteger Answer a new instance of the receiver with the given capacity @meindex withAll:@- @item withAll:@- aCollection Answer a collection whose elements are all those in aCollection @end table @node HashedCollection-accessing @subsection HashedCollection:@- accessing @table @b @meindex add:@- @item add:@- newObject Add newObject to the set, if and only if the set doesn't already contain an occurrence of it. Don't fail if a duplicate is found. Answer anObject @meindex at:@- @item at:@- index This method should not be called for instances of this class. @meindex at:@-put:@- @item at:@- index put:@- value This method should not be called for instances of this class. @end table @node HashedCollection-builtins @subsection HashedCollection:@- builtins @table @b @meindex primAt:@- @item primAt:@- anIndex Private - Answer the anIndex-th item of the hash table for the receiver. Using this instead of basicAt:@- allows for easier changes in the representation @meindex primAt:@-put:@- @item primAt:@- anIndex put:@- value Private - Store value in the anIndex-th item of the hash table for the receiver. Using this instead of basicAt:@-put:@- allows for easier changes in the representation @meindex primSize @item primSize Private - Answer the size of the hash table for the receiver. Using this instead of basicSize allows for easier changes in the representation @end table @node HashedCollection-copying @subsection HashedCollection:@- copying @table @b @meindex deepCopy @item deepCopy Returns a deep copy of the receiver (the instance variables are copies of the receiver's instance variables) @meindex shallowCopy @item shallowCopy Returns a shallow copy of the receiver (the instance variables are not copied) @end table @node HashedCollection-enumerating the elements of a collection @subsection HashedCollection:@- enumerating the elements of a collection @table @b @meindex do:@- @item do:@- aBlock Enumerate all the non-nil members of the set @end table @node HashedCollection-rehashing @subsection HashedCollection:@- rehashing @table @b @meindex rehash @item rehash Rehash the receiver @end table @node HashedCollection-removing @subsection HashedCollection:@- removing @table @b @meindex remove:@-ifAbsent:@- @item remove:@- oldObject ifAbsent:@- anExceptionBlock Remove oldObject from the set. If it is found, answer oldObject. Otherwise, evaluate anExceptionBlock and answer its value. @end table @node HashedCollection-saving and loading @subsection HashedCollection:@- saving and loading @table @b @meindex postLoad @item postLoad Called after loading an object; rehash the collection because identity objects will most likely mutate their hashes. @meindex postStore @slindex postLoad @item postStore Called after an object is dumped. Do nothing -- necessary because by default this calls #postLoad by default @end table @node HashedCollection-storing @subsection HashedCollection:@- storing @table @b @meindex storeOn:@- @item storeOn:@- aStream Store on aStream some Smalltalk code which compiles to the receiver @end table @node HashedCollection-testing collections @subsection HashedCollection:@- testing collections @table @b @meindex = @item = aHashedCollection Returns true if the two sets have the same membership, false if not @meindex capacity @item capacity Answer how many elements the receiver can hold before having to grow. @meindex hash @item hash Return the hash code for the members of the set. Since order is unimportant, we use a commutative operator to compute the hash value. @meindex includes:@- @item includes:@- anObject Answer whether the receiver contains an instance of anObject. @meindex isEmpty @item isEmpty Answer whether the receiver is empty. @meindex occurrencesOf:@- @item occurrencesOf:@- anObject Return the number of occurrences of anObject. Since we're a set, this is either 0 or 1. Nil is never directly in the set, so we special case it (the result is always 1). @meindex size @item size Answer the receiver's size @end table @node HomedAssociation @section HomedAssociation @clindex HomedAssociation @table @b @item Defined in namespace Smalltalk @itemx Superclass: Association @itemx Category: Language-Data types My instances represent know about their parent namespace, which is of use when implementing weak collections and finalizations. @end table @menu * HomedAssociation class-basic:: (class) * HomedAssociation-accessing:: (instance) * HomedAssociation-finalization:: (instance) * HomedAssociation-storing:: (instance) @end menu @node HomedAssociation class-basic @subsection HomedAssociation class:@- basic @table @b @meindex key:@-value:@-environment:@- @item key:@- aKey value:@- aValue environment:@- aNamespace Answer a new association with the given key and value @end table @node HomedAssociation-accessing @subsection HomedAssociation:@- accessing @table @b @meindex environment @item environment Answer the namespace in which I live. @meindex environment:@- @item environment:@- aNamespace Set the namespace in which I live to be aNamespace. @end table @node HomedAssociation-finalization @subsection HomedAssociation:@- finalization @table @b @meindex mourn @item mourn This message is sent to the receiver when the object is made ephemeron (which is common when HomedAssociations are used by a WeakKeyDictionary or a WeakSet). The mourning of the object's key is first of all demanded to the environment (which will likely remove the object from itself), and then performed as usual by clearing the key and value fields. @end table @node HomedAssociation-storing @subsection HomedAssociation:@- storing @table @b @meindex storeOn:@- @item storeOn:@- aStream Put on aStream some Smalltalk code compiling to the receiver @end table @node IdentityDictionary @section IdentityDictionary @clindex IdentityDictionary @table @b @item Defined in namespace Smalltalk @itemx Superclass: LookupTable @itemx Category: Collections-Keyed I am similar to LookupTable, except that I use the object identity comparision message == to determine equivalence of indices. @end table @menu @end menu @node IdentitySet @section IdentitySet @clindex IdentitySet @table @b @item Defined in namespace Smalltalk @itemx Superclass: Set @itemx Category: Collections-Unordered I am the typical set object; I can store any objects uniquely. I use the == operator to determine duplication of objects. @end table @menu * IdentitySet-testing:: (instance) @end menu @node IdentitySet-testing @subsection IdentitySet:@- testing @table @b @meindex identityIncludes:@- @slindex includes:@- @item identityIncludes:@- anObject Answer whether we include the anObject object; for IdentitySets this is identical to #includes:@- @end table @node Integer @section Integer @clindex Integer @table @b @item Defined in namespace Smalltalk @itemx Superclass: Number @itemx Category: Language-Data types I am the abstract integer class of the GNU Smalltalk system. My subclasses' instances can represent signed integers of various sizes (a subclass is picked according to the size), with varying efficiency. @end table @menu * Integer class-converting:: (class) * Integer-accessing:: (instance) * Integer-basic:: (instance) * Integer-bit operators:: (instance) * Integer-converting:: (instance) * Integer-extension:: (instance) * Integer-iterators:: (instance) * Integer-math methods:: (instance) * Integer-printing:: (instance) * Integer-storing:: (instance) * Integer-testing functionality:: (instance) @end menu @node Integer class-converting @subsection Integer class:@- converting @table @b @meindex coerce:@- @item coerce:@- aNumber Answer aNumber converted to a kind of Integer @end table @node Integer-accessing @subsection Integer:@- accessing @table @b @meindex denominator @item denominator Answer `1'. @meindex numerator @item numerator Answer the receiver. @end table @node Integer-basic @subsection Integer:@- basic @table @b @meindex hash @item hash Answer an hash value for the receiver @end table @node Integer-bit operators @subsection Integer:@- bit operators @table @b @meindex allMask:@- @item allMask:@- anInteger True if all 1 bits in anInteger are 1 in the receiver @meindex anyMask:@- @item anyMask:@- anInteger True if any 1 bits in anInteger are 1 in the receiver @meindex bitAt:@- @item bitAt:@- index Answer the index-th bit of the receiver (the LSB has an index of 1) @meindex bitAt:@-put:@- @item bitAt:@- index put:@- value Answer an integer which is identical to the receiver, possibly with the exception of the index-th bit of the receiver (the LSB having an index of 1), which assumes a value equal to the low-order bit of the second parameter. @meindex bitClear:@- @item bitClear:@- aMask Answer an Integer equal to the receiver, except that all the bits that are set in aMask are cleared. @meindex bitInvert @item bitInvert Return the 1's complement of the bits of the receiver @meindex clearBit:@- @item clearBit:@- index Clear the index-th bit of the receiver and answer a new Integer @meindex digitAt:@- @item digitAt:@- index Answer the index-th base-256 digit of the receiver (byte), expressed in two's complement @meindex highBit @item highBit Return the index of the highest order 1 bit of the receiver. @meindex isBitSet:@- @item isBitSet:@- index Answer whether the index-th bit of the receiver is set @meindex lowBit @item lowBit Return the index of the lowest order 1 bit of the receiver. @meindex noMask:@- @item noMask:@- anInteger Answer true if no 1 bits in anInteger are 1 in the receiver. @meindex setBit:@- @item setBit:@- index Set the index-th bit of the receiver and answer a new Integer @end table @node Integer-converting @subsection Integer:@- converting @table @b @meindex asCharacter @item asCharacter Return self as a Character or UnicodeCharacter object. @meindex asFraction @item asFraction Return the receiver converted to a fraction @meindex asScaledDecimal:@- @item asScaledDecimal:@- n Answer the receiver, converted to a ScaledDecimal object. The scale is forced to be 0. @meindex ceiling @item ceiling Return the receiver - it's already truncated @meindex coerce:@- @item coerce:@- aNumber Coerce aNumber to the receiver's class. @meindex floor @item floor Return the receiver - it's already truncated @meindex rounded @item rounded Return the receiver - it's already truncated @meindex truncated @item truncated Return the receiver - it's already truncated @end table @node Integer-extension @subsection Integer:@- extension @table @b @meindex alignTo:@- @item alignTo:@- anInteger Answer the receiver, truncated to the first higher or equal multiple of anInteger (which must be a power of two) @end table @node Integer-iterators @subsection Integer:@- iterators @table @b @meindex timesRepeat:@- @item timesRepeat:@- aBlock Evaluate aBlock a number of times equal to the receiver's value. Compiled in-line for no argument aBlocks without temporaries, and therefore not overridable. @end table @node Integer-math methods @subsection Integer:@- math methods @table @b @meindex binomial:@- @item binomial:@- anInteger Compute the number of combinations of anInteger objects among a number of objects given by the receiver. @meindex ceilingLog:@- @item ceilingLog:@- radix Answer (self log:@- radix) ceiling. Optimized to answer an integer. @meindex estimatedLog @item estimatedLog Answer an estimate of (self abs floorLog:@- 10) @meindex even @item even Return whether the receiver is even @meindex factorial @item factorial Return the receiver's factorial. @meindex floorLog:@- @item floorLog:@- radix Answer (self log:@- radix) floor. Optimized to answer an integer. @meindex gcd:@- @item gcd:@- anInteger Return the greatest common divisor (Euclid's algorithm) between the receiver and anInteger @meindex lcm:@- @item lcm:@- anInteger Return the least common multiple between the receiver and anInteger @meindex odd @item odd Return whether the receiver is odd @end table @node Integer-printing @subsection Integer:@- printing @table @b @meindex displayOn:@- @item displayOn:@- aStream Print on aStream the base 10 representation of the receiver @meindex displayString @item displayString Return the base 10 representation of the receiver @meindex isLiteralObject @item isLiteralObject Answer whether the receiver is expressible as a Smalltalk literal. @meindex printOn:@- @item printOn:@- aStream Print on aStream the base 10 representation of the receiver @meindex printOn:@-base:@- @item printOn:@- aStream base:@- b Print on aStream the base b representation of the receiver @meindex printOn:@-paddedWith:@-to:@- @item printOn:@- aStream paddedWith:@- padding to:@- size Print on aStream the base 10 representation of the receiver, padded if necessary to size characters with copies of padding. @meindex printOn:@-paddedWith:@-to:@-base:@- @item printOn:@- aStream paddedWith:@- padding to:@- size base:@- baseInteger Print on aStream the base b representation of the receiver, padded if necessary to size characters with copies of padding. @meindex printPaddedWith:@-to:@- @item printPaddedWith:@- padding to:@- size Return the base baseInteger representation of the receiver, padded if necessary to size characters with copies of padding. @meindex printPaddedWith:@-to:@-base:@- @item printPaddedWith:@- padding to:@- size base:@- baseInteger Return the base baseInteger representation of the receiver, padded if necessary to size characters with copies of padding. @meindex printString @item printString Return the base 10 representation of the receiver @meindex printString:@- @item printString:@- baseInteger Return the base baseInteger representation of the receiver @meindex printStringRadix:@- @item printStringRadix:@- baseInteger Return the base baseInteger representation of the receiver, with BBr in front of it @meindex radix:@- @slindex printStringRadix:@- @item radix:@- baseInteger Return the base baseInteger representation of the receiver, with BBr in front of it. This method is deprecated, use #printStringRadix:@- instead. @meindex storeLiteralOn:@- @item storeLiteralOn:@- aStream Store on aStream some Smalltalk code which compiles to the receiver @meindex storeOn:@-base:@- @item storeOn:@- aStream base:@- b Print on aStream Smalltalk code compiling to the receiver, represented in base b @end table @node Integer-storing @subsection Integer:@- storing @table @b @meindex storeOn:@- @item storeOn:@- aStream Print on aStream the base 10 representation of the receiver @meindex storeString @item storeString Return the base 10 representation of the receiver @end table @node Integer-testing functionality @subsection Integer:@- testing functionality @table @b @meindex isInteger @item isInteger Answer `true'. @meindex isRational @item isRational Answer whether the receiver is rational - true @end table @node Interval @section Interval @clindex Interval @table @b @item Defined in namespace Smalltalk @itemx Superclass: ArrayedCollection @itemx Category: Collections-Sequenceable My instances represent ranges of objects, typically Number type objects. I provide iteration/enumeration messages for producing all the members that my instance represents. @end table @menu * Interval class-instance creation:: (class) * Interval-basic:: (instance) * Interval-printing:: (instance) * Interval-storing:: (instance) * Interval-testing:: (instance) @end menu @node Interval class-instance creation @subsection Interval class:@- instance creation @table @b @meindex from:@-to:@- @item from:@- startInteger to:@- stopInteger Answer an Interval going from startInteger to the stopInteger, with a step of 1 @meindex from:@-to:@-by:@- @item from:@- startInteger to:@- stopInteger by:@- stepInteger Answer an Interval going from startInteger to the stopInteger, with a step of stepInteger @meindex withAll:@- @item withAll:@- aCollection Answer an Interval containing the same elements as aCollection. Fail if it is not possible to create one. @end table @node Interval-basic @subsection Interval:@- basic @table @b @meindex at:@- @item at:@- index Answer the index-th element of the receiver. @meindex at:@-put:@- @item at:@- index put:@- anObject This method should not be called for instances of this class. @meindex collect:@- @item collect:@- aBlock Evaluate the receiver for each element in aBlock, collect in an array the result of the evaluations. @meindex copyFrom:@-to:@- @item copyFrom:@- startIndex to:@- stopIndex Not commented. @meindex do:@- @item do:@- aBlock Evaluate the receiver for each element in aBlock @meindex isEmpty @item isEmpty Answer whether the receiver is empty. @meindex reverse @item reverse Answer a copy of the receiver with all of its items reversed @meindex size @item size Answer the number of elements in the receiver. @meindex species @item species Answer `Array'. @end table @node Interval-printing @subsection Interval:@- printing @table @b @meindex first @item first Not commented. @meindex increment @item increment Answer `step'. @meindex last @item last Answer the last value. @meindex printOn:@- @item printOn:@- aStream Print a representation for the receiver on aStream @end table @node Interval-storing @subsection Interval:@- storing @table @b @meindex storeOn:@- @item storeOn:@- aStream Store Smalltalk code compiling to the receiver on aStream @end table @node Interval-testing @subsection Interval:@- testing @table @b @meindex = @item = anInterval Answer whether anInterval is the same interval as the receiver @meindex hash @item hash Answer an hash value for the receiver @meindex isExact @item isExact Answer whether elements of the receiver are computed using exact arithmetic. This is true as long as the start and step value are exact (i.e. not floating-point). @end table @node Iterable @section Iterable @clindex Iterable @table @b @item Defined in namespace Smalltalk @itemx Superclass: Object @itemx Category: Collections I am an abstract class. My instances are collections of objects that can be iterated. The details on how they can be mutated (if at all possible) are left to the subclasses. @end table @menu * Iterable class-multibyte encodings:: (class) * Iterable-enumeration:: (instance) * Iterable-iteration:: (instance) * Iterable-streaming:: (instance) @end menu @node Iterable class-multibyte encodings @subsection Iterable class:@- multibyte encodings @table @b @meindex isUnicode @item isUnicode Answer true; the receiver is able to store arbitrary Unicode characters. @end table @node Iterable-enumeration @subsection Iterable:@- enumeration @table @b @meindex , @item , anIterable Answer an iterable that enumerates first the elements of the receiver and then the elements of anIterable. @meindex allSatisfy:@- @item allSatisfy:@- aBlock Search the receiver for an element for which aBlock returns false. Answer true if none does, false otherwise. @meindex anySatisfy:@- @item anySatisfy:@- aBlock Search the receiver for an element for which aBlock returns true. Answer true if some does, false otherwise. @meindex collect:@- @item collect:@- aBlock Answer a new instance of a Collection containing all the results of evaluating aBlock passing each of the receiver's elements @meindex conform:@- @item conform:@- aBlock Search the receiver for an element for which aBlock returns false. Answer true if none does, false otherwise. @meindex contains:@- @item contains:@- aBlock Search the receiver for an element for which aBlock returns true. Answer true if some does, false otherwise. @meindex count:@- @item count:@- aBlock Count the elements of the receiver for which aBlock returns true, and return their number. @meindex detect:@- @item detect:@- aBlock Search the receiver for an element for which aBlock returns true. If some does, answer it. If none does, fail @meindex detect:@-ifNone:@- @item detect:@- aBlock ifNone:@- exceptionBlock Search the receiver for an element for which aBlock returns true. If some does, answer it. If none does, answer the result of evaluating aBlock @meindex do:@- @item do:@- aBlock Enumerate each object of the receiver, passing them to aBlock @meindex do:@-separatedBy:@- @item do:@- aBlock separatedBy:@- separatorBlock Enumerate each object of the receiver, passing them to aBlock. Between every two invocations of aBlock, invoke separatorBlock @meindex fold:@- @item fold:@- binaryBlock First, pass to binaryBlock the first and second elements of the receiver; for each subsequent element, pass the result of the previous evaluation and an element. Answer the result of the last invocation, or the first element if the collection has size 1. Fail if the collection is empty. @meindex inject:@-into:@- @item inject:@- thisValue into:@- binaryBlock First, pass to binaryBlock thisValue and the first element of the receiver; for each subsequent element, pass the result of the previous evaluation and an element. Answer the result of the last invocation. @meindex noneSatisfy:@- @item noneSatisfy:@- aBlock Search the receiver for an element for which aBlock returns true. Answer true if none does, false otherwise. @meindex reject:@- @item reject:@- aBlock Answer a new instance of a Collection containing all the elements in the receiver which, when passed to aBlock, don't answer true @meindex select:@- @item select:@- aBlock Answer a new instance of a Collection containing all the elements in the receiver which, when passed to aBlock, answer true @end table @node Iterable-iteration @subsection Iterable:@- iteration @table @b @meindex ifNil:@-ifNotNilDo:@- @item ifNil:@- nilBlock ifNotNilDo:@- iterableBlock Evaluate nilBlock if the receiver is nil, else evaluate iterableBlock with each element of the receiver (which should be an Iterable). @meindex ifNotNilDo:@- @item ifNotNilDo:@- iterableBlock Evaluate iterableBlock with each element of the receiver (which should be an Iterable) if not nil. Else answer nil @meindex ifNotNilDo:@-ifNil:@- @item ifNotNilDo:@- iterableBlock ifNil:@- nilBlock Evaluate nilBlock if the receiver is nil, else evaluate iterableBlock, passing each element of the receiver (which should be an Iterable). @end table @node Iterable-streaming @subsection Iterable:@- streaming @table @b @meindex nextPutAllOn:@- @item nextPutAllOn:@- aStream Write all the objects in the receiver to aStream @meindex readStream @item readStream Return a stream with the same contents as the receiver. @end table @node LargeArray @section LargeArray @clindex LargeArray @table @b @item Defined in namespace Smalltalk @itemx Superclass: LargeArrayedCollection @itemx Category: Collections-Sequenceable I am similar to a plain array, but I'm specially designed to save memory when lots of items are nil. @end table @menu * LargeArray-overridden:: (instance) @end menu @node LargeArray-overridden @subsection LargeArray:@- overridden @table @b @meindex newCollection:@- @item newCollection:@- size Create an Array of the given size @end table @node LargeArrayedCollection @section LargeArrayedCollection @clindex LargeArrayedCollection @table @b @item Defined in namespace Smalltalk @itemx Superclass: ArrayedCollection @itemx Category: Collections-Sequenceable I am an abstract class specially designed to save memory when lots of items have the same value. @end table @menu * LargeArrayedCollection class-instance creation:: (class) * LargeArrayedCollection-accessing:: (instance) * LargeArrayedCollection-basic:: (instance) @end menu @node LargeArrayedCollection class-instance creation @subsection LargeArrayedCollection class:@- instance creation @table @b @meindex new:@- @item new:@- anInteger Answer a new instance of the receiver, with room for anInteger elements. @end table @node LargeArrayedCollection-accessing @subsection LargeArrayedCollection:@- accessing @table @b @meindex at:@- @item at:@- anIndex Answer the anIndex-th item of the receiver. @meindex at:@-put:@- @item at:@- anIndex put:@- anObject Replace the anIndex-th item of the receiver with anObject. @meindex compress @item compress Arrange the representation of the array for maximum memory saving. @end table @node LargeArrayedCollection-basic @subsection LargeArrayedCollection:@- basic @table @b @meindex = @item = aLargeArray Answer whether the receiver and aLargeArray have the same contents @meindex hash @item hash Answer an hash value for the receiver @meindex size @item size Answer the maximum valid index for the receiver @end table @node LargeByteArray @section LargeByteArray @clindex LargeByteArray @table @b @item Defined in namespace Smalltalk @itemx Superclass: LargeArrayedCollection @itemx Category: Collections-Sequenceable I am similar to a plain ByteArray, but I'm specially designed to save memory when lots of items are zero. @end table @menu * LargeByteArray-overridden:: (instance) @end menu @node LargeByteArray-overridden @subsection LargeByteArray:@- overridden @table @b @meindex costOfNewIndex @item costOfNewIndex Answer the maximum number of consecutive items set to the defaultElement that can be present in a compressed array. @meindex defaultElement @item defaultElement Answer the value which is hoped to be the most common in the array @meindex newCollection:@- @item newCollection:@- size Create a ByteArray of the given size @end table @node LargeInteger @section LargeInteger @clindex LargeInteger @table @b @item Defined in namespace Smalltalk @itemx Superclass: Integer @itemx Category: Language-Data types I represent a large integer, which has to be stored as a long sequence of bytes. I have methods to do arithmetics and comparisons, but I need some help from my children, LargePositiveInteger and LargeNegativeInteger, to speed them up a bit. @end table @menu * LargeInteger-accessing:: (instance) * LargeInteger-arithmetic:: (instance) * LargeInteger-bit operations:: (instance) * LargeInteger-built-ins:: (instance) * LargeInteger-coercion:: (instance) * LargeInteger-disabled:: (instance) * LargeInteger-primitive operations:: (instance) * LargeInteger-testing:: (instance) @end menu @node LargeInteger-accessing @subsection LargeInteger:@- accessing @table @b @meindex raisedToInteger:@- @item raisedToInteger:@- n Return self raised to the anInteger-th power @end table @node LargeInteger-arithmetic @subsection LargeInteger:@- arithmetic @table @b @meindex * @item * aNumber Multiply aNumber and the receiver, answer the result @meindex + @item + aNumber Sum the receiver and aNumber, answer the result @meindex - @item - aNumber Subtract aNumber from the receiver, answer the result @meindex / @item / aNumber Divide aNumber and the receiver, answer the result (an Integer or Fraction) @meindex // @item // aNumber Divide aNumber and the receiver, answer the result truncated towards -infinity @meindex \\ @item \\ aNumber Divide aNumber and the receiver, answer the remainder truncated towards -infinity @meindex divExact:@- @item divExact:@- aNumber Dividing receiver by arg assuming that the remainder is zero, and answer the result @meindex estimatedLog @item estimatedLog Answer an estimate of (self abs floorLog:@- 10) @meindex negated @item negated Answer the receiver's negated @meindex quo:@- @item quo:@- aNumber Divide aNumber and the receiver, answer the result truncated towards 0 @meindex rem:@- @item rem:@- aNumber Divide aNumber and the receiver, answer the remainder truncated towards 0 @end table @node LargeInteger-bit operations @subsection LargeInteger:@- bit operations @table @b @meindex bitAnd:@- @item bitAnd:@- aNumber Answer the receiver ANDed with aNumber @meindex bitAt:@- @item bitAt:@- aNumber Answer the aNumber-th bit in the receiver, where the LSB is 1 @meindex bitInvert @item bitInvert Answer the receiver's 1's complement @meindex bitOr:@- @item bitOr:@- aNumber Answer the receiver ORed with aNumber @meindex bitShift:@- @item bitShift:@- aNumber Answer the receiver shifted by aNumber places @meindex bitXor:@- @item bitXor:@- aNumber Answer the receiver XORed with aNumber @meindex lowBit @item lowBit Return the index of the lowest order 1 bit of the receiver. @end table @node LargeInteger-built-ins @subsection LargeInteger:@- built-ins @table @b @meindex at:@- @item at:@- anIndex Answer the anIndex-th byte in the receiver's representation @meindex at:@-put:@- @item at:@- anIndex put:@- aNumber Set the anIndex-th byte in the receiver's representation @meindex digitAt:@- @item digitAt:@- anIndex Answer the index-th base-256 digit of the receiver (byte), expressed in two's complement @meindex digitAt:@-put:@- @item digitAt:@- anIndex put:@- aNumber Set the anIndex-th base-256 digit in the receiver's representation @meindex digitLength @item digitLength Answer the number of base-256 digits in the receiver @meindex hash @item hash Answer an hash value for the receiver @meindex primReplaceFrom:@-to:@-with:@-startingAt:@- @item primReplaceFrom:@- start to:@- stop with:@- replacementString startingAt:@- replaceStart Private - Replace the characters from start to stop with new characters contained in replacementString (which, actually, can be any variable byte class), starting at the replaceStart location of replacementString @meindex size @item size Answer the number of indexed instance variable in the receiver @end table @node LargeInteger-coercion @subsection LargeInteger:@- coercion @table @b @meindex asCNumber @item asCNumber Convert the receiver to a kind of number that is understood by the C call-out mechanism. @meindex coerce:@- @item coerce:@- aNumber Truncate the number; if needed, convert it to LargeInteger representation. @meindex generality @item generality Answer the receiver's generality @meindex unity @item unity Coerce 1 to the receiver's class @meindex zero @item zero Coerce 0 to the receiver's class @end table @node LargeInteger-disabled @subsection LargeInteger:@- disabled @table @b @meindex asObject @item asObject This method always fails. The number of OOPs is far less than the minimum number represented with a LargeInteger. @meindex asObjectNoFail @item asObjectNoFail Answer `nil'. @end table @node LargeInteger-primitive operations @subsection LargeInteger:@- primitive operations @table @b @meindex basicLeftShift:@- @item basicLeftShift:@- totalShift Private - Left shift the receiver by aNumber places @meindex basicRightShift:@- @item basicRightShift:@- totalShift Private - Right shift the receiver by 'shift' places @meindex largeNegated @item largeNegated Private - Same as negated, but always answer a LargeInteger @end table @node LargeInteger-testing @subsection LargeInteger:@- testing @table @b @meindex < @item < aNumber Answer whether the receiver is smaller than aNumber @meindex <= @item <= aNumber Answer whether the receiver is smaller than aNumber or equal to it @meindex = @item = aNumber Answer whether the receiver and aNumber identify the same number. @meindex > @item > aNumber Answer whether the receiver is greater than aNumber @meindex >= @item >= aNumber Answer whether the receiver is greater than aNumber or equal to it @meindex ~= @item ~= aNumber Answer whether the receiver and aNumber identify different numbers. @end table @node LargeNegativeInteger @section LargeNegativeInteger @clindex LargeNegativeInteger @table @b @item Defined in namespace Smalltalk @itemx Superclass: LargeInteger @itemx Category: Language-Data types Just like my brother LargePositiveInteger, I provide a few methods that allow LargeInteger to determine the sign of a large integer in a fast way during its calculations. For example, I know that I am smaller than any LargePositiveInteger @end table @menu * LargeNegativeInteger-converting:: (instance) * LargeNegativeInteger-numeric testing:: (instance) * LargeNegativeInteger-reverting to LargePositiveInteger:: (instance) @end menu @node LargeNegativeInteger-converting @subsection LargeNegativeInteger:@- converting @table @b @meindex asFloatD @item asFloatD Answer the receiver converted to a FloatD @meindex asFloatE @item asFloatE Answer the receiver converted to a FloatE @meindex asFloatQ @item asFloatQ Answer the receiver converted to a FloatQ @end table @node LargeNegativeInteger-numeric testing @subsection LargeNegativeInteger:@- numeric testing @table @b @meindex abs @item abs Answer the receiver's absolute value. @meindex negative @item negative Answer whether the receiver is < 0 @meindex positive @item positive Answer whether the receiver is >= 0 @meindex sign @item sign Answer the receiver's sign @meindex strictlyPositive @item strictlyPositive Answer whether the receiver is > 0 @end table @node LargeNegativeInteger-reverting to LargePositiveInteger @subsection LargeNegativeInteger:@- reverting to LargePositiveInteger @table @b @meindex + @item + aNumber Sum the receiver and aNumber, answer the result @meindex - @item - aNumber Subtract aNumber from the receiver, answer the result @meindex gcd:@- @item gcd:@- anInteger Return the greatest common divisor between the receiver and anInteger @meindex highBit @item highBit Answer the receiver's highest bit's index @end table @node LargePositiveInteger @section LargePositiveInteger @clindex LargePositiveInteger @table @b @item Defined in namespace Smalltalk @itemx Superclass: LargeInteger @itemx Category: Language-Data types Just like my brother LargeNegativeInteger, I provide a few methods that allow LargeInteger to determine the sign of a large integer in a fast way during its calculations. For example, I know that I am larger than any LargeNegativeInteger. In addition I implement the guts of arbitrary precision arithmetic. @end table @menu * LargePositiveInteger-arithmetic:: (instance) * LargePositiveInteger-converting:: (instance) * LargePositiveInteger-helper byte-level methods:: (instance) * LargePositiveInteger-numeric testing:: (instance) * LargePositiveInteger-primitive operations:: (instance) @end menu @node LargePositiveInteger-arithmetic @subsection LargePositiveInteger:@- arithmetic @table @b @meindex + @item + aNumber Sum the receiver and aNumber, answer the result @meindex - @item - aNumber Subtract aNumber from the receiver, answer the result @meindex gcd:@- @item gcd:@- anInteger Calculate the GCD between the receiver and anInteger @meindex highBit @item highBit Answer the receiver's highest bit's index @end table @node LargePositiveInteger-converting @subsection LargePositiveInteger:@- converting @table @b @meindex asFloatD @item asFloatD Answer the receiver converted to a FloatD @meindex asFloatE @item asFloatE Answer the receiver converted to a FloatE @meindex asFloatQ @item asFloatQ Answer the receiver converted to a FloatQ @meindex replace:@-withStringBase:@- @item replace:@- str withStringBase:@- radix Return in a String str the base radix representation of the receiver. @end table @node LargePositiveInteger-helper byte-level methods @subsection LargePositiveInteger:@- helper byte-level methods @table @b @meindex bytes:@-from:@-compare:@- @item bytes:@- byteArray1 from:@- j compare:@- byteArray2 Private - Answer the sign of byteArray2 - byteArray1; the j-th byte of byteArray1 is compared with the first of byteArray2, the j+1-th with the second, and so on. @meindex bytes:@-from:@-subtract:@- @item bytes:@- byteArray1 from:@- j subtract:@- byteArray2 Private - Sutract the bytes in byteArray2 from those in byteArray1 @meindex bytes:@-multiply:@- @item bytes:@- bytes multiply:@- anInteger Private - Multiply the bytes in bytes by anInteger, which must be < 255. Put the result back in bytes. @meindex bytesLeftShift:@- @item bytesLeftShift:@- aByteArray Private - Left shift by 1 place the bytes in aByteArray @meindex bytesLeftShift:@-big:@- @item bytesLeftShift:@- aByteArray big:@- totalShift Private - Left shift the bytes in aByteArray by totalShift places @meindex bytesLeftShift:@-n:@- @item bytesLeftShift:@- aByteArray n:@- shift Private - Left shift by shift places the bytes in aByteArray (shift <= 7) @meindex bytesRightShift:@-big:@- @item bytesRightShift:@- aByteArray big:@- totalShift Private - Right shift the bytes in aByteArray by totalShift places @meindex bytesRightShift:@-n:@- @item bytesRightShift:@- bytes n:@- aNumber Private - Right shift the bytes in `bytes' by 'aNumber' places (shift <= 7) @meindex bytesTrailingZeros:@- @item bytesTrailingZeros:@- bytes Private - Answer the number of trailing zero bits in the receiver @meindex primDivide:@- @item primDivide:@- rhs Private - Implements Knuth's divide and correct algorithm from `Seminumerical Algorithms' 3rd Edition, section 4.3.1 (which is basically an enhanced version of the divide `algorithm' for two-digit divisors which is taught in primary school!!!) @end table @node LargePositiveInteger-numeric testing @subsection LargePositiveInteger:@- numeric testing @table @b @meindex abs @item abs Answer the receiver's absolute value @meindex negative @item negative Answer whether the receiver is < 0 @meindex positive @item positive Answer whether the receiver is >= 0 @meindex sign @item sign Answer the receiver's sign @meindex strictlyPositive @item strictlyPositive Answer whether the receiver is > 0 @end table @node LargePositiveInteger-primitive operations @subsection LargePositiveInteger:@- primitive operations @table @b @meindex divide:@-using:@- @item divide:@- aNumber using:@- aBlock Private - Divide the receiver by aNumber (unsigned division). Evaluate aBlock passing the result ByteArray, the remainder ByteArray, and whether the division had a remainder @meindex isSmall @item isSmall Private - Answer whether the receiver is small enough to employ simple scalar algorithms for division and multiplication @meindex multiply:@- @item multiply:@- aNumber Private - Multiply the receiver by aNumber (unsigned multiply) @end table @node LargeWordArray @section LargeWordArray @clindex LargeWordArray @table @b @item Defined in namespace Smalltalk @itemx Superclass: LargeArrayedCollection @itemx Category: Collections-Sequenceable I am similar to a plain WordArray, but I'm specially designed to save memory when lots of items are zero. @end table @menu * LargeWordArray-overridden:: (instance) @end menu @node LargeWordArray-overridden @subsection LargeWordArray:@- overridden @table @b @meindex defaultElement @item defaultElement Answer the value which is hoped to be the most common in the array @meindex newCollection:@- @item newCollection:@- size Create a WordArray of the given size @end table @node LargeZeroInteger @section LargeZeroInteger @clindex LargeZeroInteger @table @b @item Defined in namespace Smalltalk @itemx Superclass: LargePositiveInteger @itemx Category: Language-Data types I am quite a strange class. Indeed, the concept of a "large integer" that is zero is a weird one. Actually my only instance is zero but is represented like LargeIntegers, has the same generality as LargeIntegers, and so on. That only instance is stored in the class variable Zero, and is used in arithmetical methods, when we have to coerce a parameter that is zero. @end table @menu * LargeZeroInteger-accessing:: (instance) * LargeZeroInteger-arithmetic:: (instance) * LargeZeroInteger-numeric testing:: (instance) * LargeZeroInteger-printing:: (instance) @end menu @node LargeZeroInteger-accessing @subsection LargeZeroInteger:@- accessing @table @b @meindex at:@- @item at:@- anIndex Answer `0'. @meindex hash @item hash Answer `0'. @meindex size @item size Answer `0'. @end table @node LargeZeroInteger-arithmetic @subsection LargeZeroInteger:@- arithmetic @table @b @meindex * @item * aNumber Multiply aNumber and the receiver, answer the result @meindex + @item + aNumber Sum the receiver and aNumber, answer the result @meindex - @item - aNumber Subtract aNumber from the receiver, answer the result @meindex / @item / aNumber Divide aNumber and the receiver, answer the result (an Integer or Fraction) @meindex // @item // aNumber Divide aNumber and the receiver, answer the result truncated towards -infinity @meindex \\ @item \\ aNumber Divide aNumber and the receiver, answer the remainder truncated towards -infinity @meindex quo:@- @item quo:@- aNumber Divide aNumber and the receiver, answer the result truncated towards 0 @meindex rem:@- @item rem:@- aNumber Divide aNumber and the receiver, answer the remainder truncated towards 0 @end table @node LargeZeroInteger-numeric testing @subsection LargeZeroInteger:@- numeric testing @table @b @meindex sign @item sign Answer the receiver's sign @meindex strictlyPositive @item strictlyPositive Answer whether the receiver is > 0 @end table @node LargeZeroInteger-printing @subsection LargeZeroInteger:@- printing @table @b @meindex replace:@-withStringBase:@- @item replace:@- str withStringBase:@- radix Return in a string the base radix representation of the receiver. @end table @node Link @section Link @clindex Link @table @b @item Defined in namespace Smalltalk @itemx Superclass: Object @itemx Category: Collections-Sequenceable I represent simple linked lists. Generally, I am not used by myself, but rather a subclass adds other instance variables that hold the information for each node, and I hold the glue that keeps them together. @end table @menu * Link class-instance creation:: (class) * Link-basic:: (instance) * Link-iteration:: (instance) @end menu @node Link class-instance creation @subsection Link class:@- instance creation @table @b @meindex nextLink:@- @item nextLink:@- aLink Create an instance with the given next link @end table @node Link-basic @subsection Link:@- basic @table @b @meindex nextLink @item nextLink Answer the next item in the list @meindex nextLink:@- @item nextLink:@- aLink Set the next item in the list @end table @node Link-iteration @subsection Link:@- iteration @table @b @meindex at:@- @item at:@- index Retrieve a node (instance of Link) that is at a distance of `index' after the receiver. @meindex at:@-put:@- @item at:@- index put:@- object This method should not be called for instances of this class. @meindex do:@- @item do:@- aBlock Evaluate aBlock for each element in the list @meindex size @item size Answer the number of elements in the list. Warning:@- this is O(n) @end table @node LinkedList @section LinkedList @clindex LinkedList @table @b @item Defined in namespace Smalltalk @itemx Superclass: SequenceableCollection @itemx Category: Collections-Sequenceable I provide methods that access and manipulate linked lists. I assume that the elements of the linked list are subclasses of Link, because I use the methods that class Link supplies to implement my methods. @end table @menu * LinkedList-accessing:: (instance) * LinkedList-adding:: (instance) * LinkedList-enumerating:: (instance) * LinkedList-iteration:: (instance) * LinkedList-testing:: (instance) @end menu @node LinkedList-accessing @subsection LinkedList:@- accessing @table @b @meindex at:@- @item at:@- index Return the element that is index into the linked list. @meindex at:@-put:@- @item at:@- index put:@- object This method should not be called for instances of this class. @end table @node LinkedList-adding @subsection LinkedList:@- adding @table @b @meindex add:@- @item add:@- aLink Add aLink at the end of the list; return aLink. @meindex addFirst:@- @item addFirst:@- aLink Add aLink at the head of the list; return aLink. @meindex addLast:@- @item addLast:@- aLink Add aLink at then end of the list; return aLink. @meindex remove:@-ifAbsent:@- @item remove:@- aLink ifAbsent:@- aBlock Remove aLink from the list and return it, or invoke aBlock if it's not found in the list. @meindex removeFirst @item removeFirst Remove the first element from the list and return it, or error if the list is empty. @meindex removeLast @item removeLast Remove the final element from the list and return it, or error if the list is empty. @end table @node LinkedList-enumerating @subsection LinkedList:@- enumerating @table @b @meindex do:@- @item do:@- aBlock Enumerate each object in the list, passing it to aBlock (actual behavior might depend on the subclass of Link that is being used). @meindex identityIncludes:@- @item identityIncludes:@- anObject Answer whether we include the anObject object @meindex includes:@- @item includes:@- anObject Answer whether we include anObject @end table @node LinkedList-iteration @subsection LinkedList:@- iteration @table @b @meindex first @item first Retrieve the first element of the list and return it, or error if the list is empty. @meindex last @item last Retrieve the last element of the list and return it, or error if the list is empty. @end table @node LinkedList-testing @subsection LinkedList:@- testing @table @b @meindex isEmpty @item isEmpty Returns true if the list contains no members @meindex notEmpty @item notEmpty Returns true if the list contains at least a member @meindex size @item size Answer the number of elements in the list. Warning:@- this is O(n) @end table @node LookupKey @section LookupKey @clindex LookupKey @table @b @item Defined in namespace Smalltalk @itemx Superclass: Magnitude @itemx Category: Language-Data types I represent a key for looking up entries in a data structure. Subclasses of me, such as Association, typically represent dictionary entries. @end table @menu * LookupKey class-basic:: (class) * LookupKey-accessing:: (instance) * LookupKey-printing:: (instance) * LookupKey-storing:: (instance) * LookupKey-testing:: (instance) @end menu @node LookupKey class-basic @subsection LookupKey class:@- basic @table @b @meindex key:@- @item key:@- aKey Answer a new instance of the receiver with the given key and value @end table @node LookupKey-accessing @subsection LookupKey:@- accessing @table @b @meindex key @item key Answer the receiver's key @meindex key:@- @item key:@- aKey Set the receiver's key to aKey @end table @node LookupKey-printing @subsection LookupKey:@- printing @table @b @meindex printOn:@- @item printOn:@- aStream Put on aStream a representation of the receiver @end table @node LookupKey-storing @subsection LookupKey:@- storing @table @b @meindex storeOn:@- @item storeOn:@- aStream Put on aStream some Smalltalk code compiling to the receiver @end table @node LookupKey-testing @subsection LookupKey:@- testing @table @b @meindex < @item < aLookupKey Answer whether the receiver's key is less than aLookupKey's @meindex = @item = aLookupKey Answer whether the receiver's key and value are the same as aLookupKey's, or false if aLookupKey is not an instance of the receiver @meindex hash @item hash Answer an hash value for the receiver @end table @node LookupTable @section LookupTable @clindex LookupTable @table @b @item Defined in namespace Smalltalk @itemx Superclass: Dictionary @itemx Category: Collections-Keyed I am a more efficient variant of Dictionary that cannot be used as a pool dictionary of variables, as I don't use Associations to store key-value pairs. I also cannot have nil as a key; if you need to be able to store nil as a key, use Dictionary instead. I use the object equality comparison message #= to determine equivalence of indices. @end table @menu * LookupTable class-instance creation:: (class) * LookupTable-accessing:: (instance) * LookupTable-enumerating:: (instance) * LookupTable-hashing:: (instance) * LookupTable-rehashing:: (instance) * LookupTable-removing:: (instance) * LookupTable-storing:: (instance) @end menu @node LookupTable class-instance creation @subsection LookupTable class:@- instance creation @table @b @meindex new @item new Create a new LookupTable with a default size @end table @node LookupTable-accessing @subsection LookupTable:@- accessing @table @b @meindex add:@- @item add:@- anAssociation Add the anAssociation key to the receiver @meindex associationAt:@-ifAbsent:@- @item associationAt:@- key ifAbsent:@- aBlock Answer the key/value Association for the given key. Evaluate aBlock (answering the result) if the key is not found @meindex at:@-ifAbsent:@- @item at:@- key ifAbsent:@- aBlock Answer the value associated to the given key, or the result of evaluating aBlock if the key is not found @meindex at:@-ifPresent:@- @item at:@- aKey ifPresent:@- aBlock If aKey is absent, answer nil. Else, evaluate aBlock passing the associated value and answer the result of the invocation @meindex at:@-put:@- @item at:@- key put:@- value Store value as associated to the given key @end table @node LookupTable-enumerating @subsection LookupTable:@- enumerating @table @b @meindex associationsDo:@- @item associationsDo:@- aBlock Pass each association in the LookupTable to aBlock. @meindex do:@- @item do:@- aBlock Pass each value in the LookupTable to aBlock. @meindex keysAndValuesDo:@- @item keysAndValuesDo:@- aBlock Pass each key/value pair in the LookupTable as two distinct parameters to aBlock. @meindex keysDo:@- @item keysDo:@- aBlock Pass each key in the LookupTable to aBlock. @end table @node LookupTable-hashing @subsection LookupTable:@- hashing @table @b @meindex hash @item hash Answer the hash value for the receiver @end table @node LookupTable-rehashing @subsection LookupTable:@- rehashing @table @b @meindex rehash @item rehash Rehash the receiver @end table @node LookupTable-removing @subsection LookupTable:@- removing @table @b @meindex remove:@- @item remove:@- anAssociation Remove anAssociation's key from the dictionary @meindex remove:@-ifAbsent:@- @item remove:@- anAssociation ifAbsent:@- aBlock Remove anAssociation's key from the dictionary @meindex removeKey:@-ifAbsent:@- @item removeKey:@- key ifAbsent:@- aBlock Remove the passed key from the LookupTable, answer the result of evaluating aBlock if it is not found @end table @node LookupTable-storing @subsection LookupTable:@- storing @table @b @meindex storeOn:@- @item storeOn:@- aStream Print Smalltalk code compiling to the receiver on aStream @end table @node Magnitude @section Magnitude @clindex Magnitude @table @b @item Defined in namespace Smalltalk @itemx Superclass: Object @itemx Category: Language-Data types I am an abstract class. My objects represent things that are discrete and map to a number line. My instances can be compared with < and >. @end table @menu * Magnitude-basic:: (instance) * Magnitude-misc methods:: (instance) @end menu @node Magnitude-basic @subsection Magnitude:@- basic @table @b @meindex < @item < aMagnitude Answer whether the receiver is less than aMagnitude @meindex <= @item <= aMagnitude Answer whether the receiver is less than or equal to aMagnitude @meindex = @item = aMagnitude Answer whether the receiver is equal to aMagnitude @meindex > @item > aMagnitude Answer whether the receiver is greater than aMagnitude @meindex >= @item >= aMagnitude Answer whether the receiver is greater than or equal to aMagnitude @end table @node Magnitude-misc methods @subsection Magnitude:@- misc methods @table @b @meindex between:@-and:@- @item between:@- min and:@- max Returns true if object is inclusively between min and max. @meindex max:@- @item max:@- aMagnitude Returns the greatest object between the receiver and aMagnitude @meindex min:@- @item min:@- aMagnitude Returns the least object between the receiver and aMagnitude @end table @node MappedCollection @section MappedCollection @clindex MappedCollection @table @b @item Defined in namespace Smalltalk @itemx Superclass: Collection @itemx Category: Collections-Keyed I represent collections of objects that are indirectly indexed by names. There are really two collections involved:@- domain and a map. The map maps between external names and indices into domain, which contains the real association. In order to work properly, the domain must be an instance of a subclass of SequenceableCollection, and the map must be an instance of Dictionary, or of a subclass of SequenceableCollection. As an example of using me, consider implenting a Dictionary whose elements are indexed. The domain would be a SequenceableCollection with n elements, the map a Dictionary associating each key to an index in the domain. To access by key, to perform enumeration, etc. you would ask an instance of me; to access by index, you would access the domain directly. Another idea could be to implement row access or column access to a matrix implemented as a single n*m Array:@- the Array would be the domain, while the map would be an Interval. @end table @menu * MappedCollection class-instance creation:: (class) * MappedCollection-basic:: (instance) @end menu @node MappedCollection class-instance creation @subsection MappedCollection class:@- instance creation @table @b @meindex collection:@-map:@- @item collection:@- aCollection map:@- aMap Answer a new MappedCollection using the given domain (aCollection) and map @meindex new @slindex collection:@-map:@- @item new This method should not be used; instead, use #collection:@-map:@- to create MappedCollection. @end table @node MappedCollection-basic @subsection MappedCollection:@- basic @table @b @meindex add:@- @item add:@- anObject This method should not be called for instances of this class. @meindex at:@- @item at:@- key Answer the object at the given key @meindex at:@-put:@- @item at:@- key put:@- value Store value at the given key @meindex atAll:@- @item atAll:@- keyCollection Answer a new MappedCollection that only includes the given keys. The new MappedCollection might use keyCollection or consecutive integers for the keys, depending on the map's type. Fail if any of them is not found in the map. @meindex collect:@- @item collect:@- aBlock Answer a Collection with the same keys as the map, where accessing a key yields the value obtained by passing through aBlock the value accessible from the key in the receiver. The result need not be another MappedCollection @meindex contents @item contents Answer a bag with the receiver's values @meindex copyFrom:@-to:@- @item copyFrom:@- a to:@- b Answer a new collection containing all the items in the receiver from the a-th to the b-th. @meindex do:@- @item do:@- aBlock Evaluate aBlock for each object @meindex domain @item domain Answer the receiver's domain @meindex keys @item keys Answer the keys that can be used to access this collection. @meindex keysAndValuesDo:@- @item keysAndValuesDo:@- aBlock Evaluate aBlock passing two arguments, one being a key that can be used to access this collection, and the other one being the value. @meindex keysDo:@- @item keysDo:@- aBlock Evaluate aBlock on the keys that can be used to access this collection. @meindex map @item map Answer the receiver's map @meindex reject:@- @item reject:@- aBlock Answer the objects in the domain for which aBlock returns false @meindex select:@- @item select:@- aBlock Answer the objects in the domain for which aBlock returns true @meindex size @item size Answer the receiver's size @end table @node Memory @section Memory @clindex Memory @table @b @item Defined in namespace Smalltalk @itemx Superclass: Object @itemx Category: Language-Implementation I provide access to actual machine addresses of OOPs and objects. I have no instances; you send messages to my class to map between an object and the address of its OOP or object. In addition I provide direct memory access with different C types (ints, chars, OOPs, floats,...). @end table @menu * Memory class-accessing:: (class) @end menu @node Memory class-accessing @subsection Memory class:@- accessing @table @b @meindex at:@- @item at:@- anAddress Access the Smalltalk object (OOP) at the given address. @meindex at:@-put:@- @item at:@- anAddress put:@- aValue Store a pointer (OOP) to the Smalltalk object identified by `value' at the given address. @meindex bigEndian @item bigEndian Answer whether we're running on a big- or little-endian system. @meindex charAt:@- @item charAt:@- anAddress Access the C char at the given address. The value is returned as a Smalltalk Character. @meindex charAt:@-put:@- @item charAt:@- anAddress put:@- aValue Store as a C char the Smalltalk Character or Integer object identified by `value', at the given address, using sizeof(char) bytes - i.e. 1 byte. @meindex deref:@- @item deref:@- anAddress Access the C int pointed by the given address @meindex doubleAt:@- @item doubleAt:@- anAddress Access the C double at the given address. @meindex doubleAt:@-put:@- @item doubleAt:@- anAddress put:@- aValue Store the Smalltalk Float object identified by `value', at the given address, writing it like a C double. @meindex floatAt:@- @item floatAt:@- anAddress Access the C float at the given address. @meindex floatAt:@-put:@- @item floatAt:@- anAddress put:@- aValue Store the Smalltalk Float object identified by `value', at the given address, writing it like a C float. @meindex intAt:@- @item intAt:@- anAddress Access the C int at the given address. @meindex intAt:@-put:@- @item intAt:@- anAddress put:@- aValue Store the Smalltalk Integer object identified by `value', at the given address, using sizeof(int) bytes. @meindex longAt:@- @item longAt:@- anAddress Access the C long int at the given address. @meindex longAt:@-put:@- @item longAt:@- anAddress put:@- aValue Store the Smalltalk Integer object identified by `value', at the given address, using sizeof(long) bytes. @meindex longDoubleAt:@- @item longDoubleAt:@- anAddress Access the C long double at the given address. @meindex longDoubleAt:@-put:@- @item longDoubleAt:@- anAddress put:@- aValue Store the Smalltalk Float object identified by `value', at the given address, writing it like a C long double. @meindex shortAt:@- @item shortAt:@- anAddress Access the C short int at the given address. @meindex shortAt:@-put:@- @item shortAt:@- anAddress put:@- aValue Store the Smalltalk Integer object identified by `value', at the given address, using sizeof(short) bytes. @meindex stringAt:@- @item stringAt:@- anAddress Access the string pointed by the C `char *' at the given given address. @meindex stringAt:@-put:@- @item stringAt:@- anAddress put:@- aValue Store the Smalltalk String object identified by `value', at the given address in memory, writing it like a *FRESHLY ALLOCATED* C string. It is the caller's responsibility to free it if necessary. @meindex ucharAt:@-put:@- @item ucharAt:@- anAddress put:@- aValue Store as a C char the Smalltalk Character or Integer object identified by `value', at the given address, using sizeof(char) bytes - i.e. 1 byte. @meindex uintAt:@-put:@- @item uintAt:@- anAddress put:@- aValue Store the Smalltalk Integer object identified by `value', at the given address, using sizeof(int) bytes. @meindex ulongAt:@-put:@- @item ulongAt:@- anAddress put:@- aValue Store the Smalltalk Integer object identified by `value', at the given address, using sizeof(long) bytes. @meindex unsignedCharAt:@- @item unsignedCharAt:@- anAddress Access the C unsigned char at the given address. The value is returned as a Smalltalk Character. @meindex unsignedCharAt:@-put:@- @item unsignedCharAt:@- anAddress put:@- aValue Store as a C char the Smalltalk Character or Integer object identified by `value', at the given address, using sizeof(char) bytes - i.e. 1 byte. @meindex unsignedIntAt:@- @item unsignedIntAt:@- anAddress Access the C unsigned int at the given address. @meindex unsignedIntAt:@-put:@- @item unsignedIntAt:@- anAddress put:@- aValue Store the Smalltalk Integer object identified by `value', at the given address, using sizeof(int) bytes. @meindex unsignedLongAt:@- @item unsignedLongAt:@- anAddress Access the C unsigned long int at the given address. @meindex unsignedLongAt:@-put:@- @item unsignedLongAt:@- anAddress put:@- aValue Store the Smalltalk Integer object identified by `value', at the given address, using sizeof(long) bytes. @meindex unsignedShortAt:@- @item unsignedShortAt:@- anAddress Access the C unsigned short int at the given address. @meindex unsignedShortAt:@-put:@- @item unsignedShortAt:@- anAddress put:@- aValue Store the Smalltalk Integer object identified by `value', at the given address, using sizeof(short) bytes. @meindex ushortAt:@-put:@- @item ushortAt:@- anAddress put:@- aValue Store the Smalltalk Integer object identified by `value', at the given address, using sizeof(short) bytes. @end table @node Message @section Message @clindex Message @table @b @item Defined in namespace Smalltalk @itemx Superclass: Object @itemx Category: Language-Implementation I represent a message send. My instances are created to hold a message that has failed, so that error reporting methods can examine the sender and arguments, but also to represent method attributes (like since their syntax is isomorphic to that of a message send. @end table @menu * Message class-creating instances:: (class) * Message-accessing:: (instance) * Message-basic:: (instance) * Message-printing:: (instance) @end menu @node Message class-creating instances @subsection Message class:@- creating instances @table @b @meindex selector:@-argument:@- @item selector:@- aSymbol argument:@- anObject Create a new Message with the given selector and argument @meindex selector:@-arguments:@- @item selector:@- aSymbol arguments:@- anArray Create a new Message with the given selector and arguments @end table @node Message-accessing @subsection Message:@- accessing @table @b @meindex argument @item argument Answer the first of the receiver's arguments @meindex arguments @item arguments Answer the receiver's arguments @meindex arguments:@- @item arguments:@- anArray Set the receiver's arguments @meindex selector @item selector Answer the receiver's selector @meindex selector:@- @item selector:@- aSymbol Set the receiver's selector @end table @node Message-basic @subsection Message:@- basic @table @b @meindex printAsAttributeOn:@- @item printAsAttributeOn:@- aStream Print a representation of the receiver on aStream, modeling it after the source code for a attribute. @end table @node Message-printing @subsection Message:@- printing @table @b @meindex printOn:@- @item printOn:@- aStream Print a representation of the receiver on aStream @meindex reinvokeFor:@- @item reinvokeFor:@- aReceiver Resend to aReceiver - present for compatibility @meindex sendTo:@- @item sendTo:@- aReceiver Resend to aReceiver @end table @node MessageNotUnderstood @section MessageNotUnderstood @clindex MessageNotUnderstood @table @b @item Defined in namespace Smalltalk @itemx Superclass: Error @itemx Category: Language-Exceptions MessageNotUnderstood represents an error during message lookup. Signaling it is the default action of the #doesNotUnderstand:@- handler @end table @menu * MessageNotUnderstood-accessing:: (instance) * MessageNotUnderstood-description:: (instance) @end menu @node MessageNotUnderstood-accessing @subsection MessageNotUnderstood:@- accessing @table @b @meindex message @item message Answer the message that wasn't understood @meindex receiver @item receiver Answer the object to whom the message send was directed @end table @node MessageNotUnderstood-description @subsection MessageNotUnderstood:@- description @table @b @meindex description @item description Answer a textual description of the exception. @meindex isResumable @slindex doesNotUnderstand:@- @item isResumable Answer true. #doesNotUnderstand:@- exceptions are by default resumable. @end table @node Metaclass @section Metaclass @clindex Metaclass @table @b @item Defined in namespace Smalltalk @itemx Superclass: ClassDescription @itemx Category: Language-Implementation I am the root of the class hierarchy. My instances are metaclasses, one for each real class. My instances have a single instance, which they hold onto, which is the class that they are the metaclass of. I provide methods for creation of actual class objects from metaclass object, and the creation of metaclass objects, which are my instances. If this is confusing to you, it should be...the Smalltalk metaclass system is strange and complex. @end table @menu * Metaclass class-instance creation:: (class) * Metaclass-accessing:: (instance) * Metaclass-basic:: (instance) * Metaclass-compiling methods:: (instance) * Metaclass-delegation:: (instance) * Metaclass-filing:: (instance) * Metaclass-printing:: (instance) * Metaclass-testing functionality:: (instance) @end menu @node Metaclass class-instance creation @subsection Metaclass class:@- instance creation @table @b @meindex subclassOf:@- @item subclassOf:@- superMeta Answer a new metaclass representing a subclass of superMeta @end table @node Metaclass-accessing @subsection Metaclass:@- accessing @table @b @meindex instanceClass @item instanceClass Answer the only instance of the metaclass @meindex primaryInstance @item primaryInstance Answer the only instance of the metaclass - present for compatibility @meindex soleInstance @item soleInstance Answer the only instance of the metaclass - present for compatibility @end table @node Metaclass-basic @subsection Metaclass:@- basic @table @b @meindex name:@-environment:@-subclassOf:@- @item name:@- className environment:@- aNamespace subclassOf:@- theSuperclass Private - create a full featured class and install it, or change the superclass or shape of an existing one; instance variable names, class variable names and pool dictionaries are left untouched. @meindex name:@-environment:@-subclassOf:@-instanceVariableArray:@-shape:@-classPool:@-poolDictionaries:@-category:@- @item name:@- className environment:@- aNamespace subclassOf:@- newSuperclass instanceVariableArray:@- variableArray shape:@- shape classPool:@- classVarDict poolDictionaries:@- sharedPoolNames category:@- categoryName Private - create a full featured class and install it, or change an existing one @meindex name:@-environment:@-subclassOf:@-instanceVariableNames:@-shape:@-classVariableNames:@-poolDictionaries:@-category:@- @item name:@- newName environment:@- aNamespace subclassOf:@- theSuperclass instanceVariableNames:@- stringOfInstVarNames shape:@- shape classVariableNames:@- stringOfClassVarNames poolDictionaries:@- stringOfPoolNames category:@- categoryName Private - parse the instance and class variables, and the pool dictionaries, then create the class. @meindex newMeta:@-environment:@-subclassOf:@-instanceVariableArray:@-shape:@-classPool:@-poolDictionaries:@-category:@- @item newMeta:@- className environment:@- aNamespace subclassOf:@- theSuperclass instanceVariableArray:@- arrayOfInstVarNames shape:@- shape classPool:@- classVarDict poolDictionaries:@- sharedPoolNames category:@- categoryName Private - create a full featured class and install it @end table @node Metaclass-compiling methods @subsection Metaclass:@- compiling methods @table @b @meindex poolResolution @item poolResolution Use my instance's poolResolution. @end table @node Metaclass-delegation @subsection Metaclass:@- delegation @table @b @meindex addClassVarName:@- @item addClassVarName:@- aString Add a class variable with the given name to the class pool dictionary @meindex addSharedPool:@- @item addSharedPool:@- aDictionary Add the given shared pool to the list of the class' pool dictionaries @meindex allClassVarNames @item allClassVarNames Answer the names of the variables in the receiver's class pool dictionary and in each of the superclasses' class pool dictionaries @meindex allSharedPoolDictionariesDo:@- @item allSharedPoolDictionariesDo:@- aBlock Answer the shared pools visible from methods in the metaclass, in the correct search order. @meindex allSharedPools @item allSharedPools Return the names of the shared pools defined by the class and any of its superclasses @meindex category @item category Answer the class category @meindex classPool @item classPool Answer the class pool dictionary @meindex classVarNames @item classVarNames Answer the names of the variables in the class pool dictionary @meindex comment @item comment Answer the class comment @meindex debuggerClass @item debuggerClass Answer the debugger class that was set in the instance class @meindex environment @item environment Answer the namespace in which the receiver is implemented @meindex name @item name Answer the class name - it has none, actually @meindex pragmaHandlerFor:@- @item pragmaHandlerFor:@- aSymbol Answer the (possibly inherited) registered handler for pragma aSymbol, or nil if not found. @meindex removeClassVarName:@- @item removeClassVarName:@- aString Removes the class variable from the class, error if not present, or still in use. @meindex removeSharedPool:@- @item removeSharedPool:@- aDictionary Remove the given dictionary to the list of the class' pool dictionaries @meindex sharedPools @item sharedPools Return the names of the shared pools defined by the class @end table @node Metaclass-filing @subsection Metaclass:@- filing @table @b @meindex fileOutOn:@- @item fileOutOn:@- aFileStream File out complete class description:@- class definition, class and instance methods @end table @node Metaclass-printing @subsection Metaclass:@- printing @table @b @meindex nameIn:@- @item nameIn:@- aNamespace Answer the class name when the class is referenced from aNamespace. @meindex printOn:@- @item printOn:@- aStream Print a represention of the receiver on aStream @meindex printOn:@-in:@- @item printOn:@- aStream in:@- aNamespace Print on aStream the class name when the class is referenced from aNamespace. @meindex storeOn:@- @item storeOn:@- aStream Store Smalltalk code compiling to the receiver on aStream @end table @node Metaclass-testing functionality @subsection Metaclass:@- testing functionality @table @b @meindex asClass @item asClass Answer `instanceClass'. @meindex isMetaclass @item isMetaclass Answer `true'. @end table @node MethodContext @section MethodContext @clindex MethodContext @table @b @item Defined in namespace Smalltalk @itemx Superclass: ContextPart @itemx Category: Language-Implementation My instances represent an actively executing method. They record various bits of information about the execution environment, and contain the execution stack. @end table @menu * MethodContext-accessing:: (instance) * MethodContext-debugging:: (instance) * MethodContext-printing:: (instance) @end menu @node MethodContext-accessing @subsection MethodContext:@- accessing @table @b @meindex home @item home Answer the MethodContext to which the receiver refers (i.e. the receiver itself) @meindex isBlock @item isBlock Answer whether the receiver is a block context @meindex isDisabled @slindex ensure:@- @item isDisabled Answers whether the receiver has actually ended execution and will be skipped when doing a return. BlockContexts are removed from the chain whenever a non-local return is done, but MethodContexts need to stay there in case there is a non-local return from the #ensure:@- block. @meindex isEnvironment @item isEnvironment To create a valid execution environment for the interpreter even before it starts, GST creates a fake context which invokes a special ``termination'' method. Such a context can be used as a marker for the current execution environment. Answer whether the receiver is that kind of context. @meindex isUnwind @slindex continue:@- @slindex ensure:@- @item isUnwind Answers whether the context must continue execution even after a non-local return (a return from the enclosing method of a block, or a call to the #continue:@- method of ContextPart). Such contexts are created only by #ensure:@-. @meindex mark @slindex valueWithUnwind @item mark To create a valid execution environment for the interpreter even before it starts, GST creates a fake context which invokes a special ``termination'' method. A similar context is created by #valueWithUnwind, by using this method. @meindex sender @item sender Return the context from which the receiver was sent @end table @node MethodContext-debugging @subsection MethodContext:@- debugging @table @b @meindex isInternalExceptionHandlingContext @slindex exceptionHandlingInternal:@- @item isInternalExceptionHandlingContext Answer whether the receiver is a context that should be hidden to the user when presenting a backtrace. Such contexts are identified through the #exceptionHandlingInternal:@- attribute:@- if there is such a context in the backtrace, all those above it are marked as internal. That is, the attribute being set to true means that the context and all those above it are to be hidden, while the attribute being set to false means that the contexts above it must be hidden, but not the context itself. @end table @node MethodContext-printing @subsection MethodContext:@- printing @table @b @meindex printOn:@- @item printOn:@- aStream Print a representation for the receiver on aStream @end table @node MethodDictionary @section MethodDictionary @clindex MethodDictionary @table @b @item Defined in namespace Smalltalk @itemx Superclass: IdentityDictionary @itemx Category: Language-Implementation I am similar to an IdentityDictionary, except that removal and rehashing operations inside my instances look atomic to the interpreter. @end table @menu * MethodDictionary-adding:: (instance) * MethodDictionary-rehashing:: (instance) * MethodDictionary-removing:: (instance) @end menu @node MethodDictionary-adding @subsection MethodDictionary:@- adding @table @b @meindex at:@-put:@- @item at:@- key put:@- value Store value as associated to the given key @end table @node MethodDictionary-rehashing @subsection MethodDictionary:@- rehashing @table @b @meindex rehash @item rehash Rehash the receiver @end table @node MethodDictionary-removing @subsection MethodDictionary:@- removing @table @b @meindex remove:@- @item remove:@- anAssociation Remove anAssociation's key from the dictionary @meindex removeKey:@-ifAbsent:@- @item removeKey:@- anElement ifAbsent:@- aBlock Remove the passed key from the dictionary, answer the result of evaluating aBlock if it is not found @end table @node MethodInfo @section MethodInfo @clindex MethodInfo @table @b @item Defined in namespace Smalltalk @itemx Superclass: Object @itemx Category: Language-Implementation I provide information about particular methods. I can produce the category that a method was filed under, and can be used to access the source code of the method. @end table @menu * MethodInfo-accessing:: (instance) * MethodInfo-equality:: (instance) @end menu @node MethodInfo-accessing @subsection MethodInfo:@- accessing @table @b @meindex category @item category Answer the method category @meindex category:@- @item category:@- aCategory Set the method category @meindex methodClass @item methodClass Answer the class in which the method is defined @meindex methodClass:@- @item methodClass:@- aClass Set the class in which the method is defined @meindex selector @item selector Answer the selector through which the method is called @meindex selector:@- @item selector:@- aSymbol Set the selector through which the method is called @meindex sourceCode @item sourceCode Answer a FileSegment or String or nil containing the method source code @meindex sourceFile @item sourceFile Answer the name of the file where the method source code is @meindex sourcePos @item sourcePos Answer the starting position of the method source code in the sourceFile @meindex sourceString @item sourceString Answer a String containing the method source code @meindex stripSourceCode @item stripSourceCode Remove the reference to the source code for the method @end table @node MethodInfo-equality @subsection MethodInfo:@- equality @table @b @meindex = @item = aMethodInfo Compare the receiver and aMethodInfo, answer whether they're equal @meindex hash @item hash Answer an hash value for the receiver @end table @node Namespace @section Namespace @clindex Namespace @table @b @item Defined in namespace Smalltalk @itemx Superclass: AbstractNamespace @itemx Category: Language-Implementation I am a Namespace that has a super-namespace. @end table @menu * Namespace class-accessing:: (class) * Namespace class-disabling instance creation:: (class) * Namespace class-initialization:: (class) * Namespace-accessing:: (instance) * Namespace-namespace hierarchy:: (instance) * Namespace-overrides for superspaces:: (instance) * Namespace-printing:: (instance) @end menu @node Namespace class-accessing @subsection Namespace class:@- accessing @table @b @meindex current @item current Answer the current namespace @meindex current:@- @item current:@- aNamespaceOrClass Set the current namespace to be aNamespace or, if it is a class, its class pool (the Dictionary that holds class variables). @end table @node Namespace class-disabling instance creation @subsection Namespace class:@- disabling instance creation @table @b @meindex new @slindex addSubspace:@- @item new Disabled - use #addSubspace:@- to create instances @meindex new:@- @slindex addSubspace:@- @item new:@- size Disabled - use #addSubspace:@- to create instances @end table @node Namespace class-initialization @subsection Namespace class:@- initialization @table @b @meindex initialize @item initialize This actually is not needed, the job could be done in dict.c (function namespace_new). But I'm lazy and I prefer to rely on the Smalltalk implementation of IdentitySet. @end table @node Namespace-accessing @subsection Namespace:@- accessing @table @b @meindex inheritedKeys @item inheritedKeys Answer a Set of all the keys in the receiver and its superspaces @end table @node Namespace-namespace hierarchy @subsection Namespace:@- namespace hierarchy @table @b @meindex siblings @item siblings Answer all the other namespaces that inherit from the receiver's superspace. @meindex siblingsDo:@- @item siblingsDo:@- aBlock Evaluate aBlock once for each of the other namespaces that inherit from the receiver's superspace, passing the namespace as a parameter. @end table @node Namespace-overrides for superspaces @subsection Namespace:@- overrides for superspaces @table @b @meindex associationAt:@-ifAbsent:@- @item associationAt:@- key ifAbsent:@- aBlock Return the key/value pair associated to the variable named as specified by `key'. If the key is not found search will be brought on in superspaces, finally evaluating aBlock if the variable cannot be found in any of the superspaces. @meindex associationsDo:@- @item associationsDo:@- aBlock Pass each association in the namespace to aBlock @meindex at:@-ifAbsent:@- @item at:@- key ifAbsent:@- aBlock Return the value associated to the variable named as specified by `key'. If the key is not found search will be brought on in superspaces, finally evaluating aBlock if the variable cannot be found in any of the superspaces. @meindex at:@-ifPresent:@- @item at:@- key ifPresent:@- aBlock If aKey is absent from the receiver and all its superspaces, answer nil. Else, evaluate aBlock passing the associated value and answer the result of the invocation @meindex do:@- @item do:@- aBlock Pass each value in the namespace to aBlock @meindex includesKey:@- @item includesKey:@- key Answer whether the receiver or any of its superspaces contain the given key @meindex keysAndValuesDo:@- @item keysAndValuesDo:@- aBlock Pass to aBlock each of the receiver's keys and values, in two separate parameters @meindex keysDo:@- @item keysDo:@- aBlock Pass to aBlock each of the receiver's keys @meindex set:@-to:@-ifAbsent:@- @item set:@- key to:@- newValue ifAbsent:@- aBlock Assign newValue to the variable named as specified by `key'. This method won't define a new variable; instead if the key is not found it will search in superspaces and evaluate aBlock if it is not found. Answer newValue. @meindex size @item size Answer the number of keys in the receiver and each of its superspaces @end table @node Namespace-printing @subsection Namespace:@- printing @table @b @meindex nameIn:@- @item nameIn:@- aNamespace Answer Smalltalk code compiling to the receiver when the current namespace is aNamespace @meindex printOn:@-in:@- @item printOn:@- aStream in:@- aNamespace Print on aStream some Smalltalk code compiling to the receiver when the current namespace is aNamespace @meindex storeOn:@- @item storeOn:@- aStream Store Smalltalk code compiling to the receiver @end table @node NetClients.URIResolver @section NetClients.URIResolver @clindex NetClients.URIResolver @table @b @item Defined in namespace Smalltalk.NetClients @itemx Superclass: Object @itemx Category: NetClients-URIResolver This class publishes methods to download files from the Internet. @end table @menu * NetClients.URIResolver class-api:: (class) * NetClients.URIResolver class-instance creation:: (class) @end menu @node NetClients.URIResolver class-api @subsection NetClients.URIResolver class:@- api @table @b @meindex openOn:@- @item openOn:@- aURI Always raise an error, as this method is not supported without loading the additional NetClients package. @meindex openOn:@-ifFail:@- @item openOn:@- aURI ifFail:@- aBlock Always evaluate aBlock and answer the result if the additional NetClients package is not loaded. If it is, instead, return a WebEntity with the contents of the resource specified by anURI, and only evaluate the block if loading the resource fails. @meindex openStreamOn:@- @item openStreamOn:@- aURI Check if aURI can be fetched from the Internet or from the local system, and if so return a Stream with its contents. If this is not possible, raise an exception. @meindex openStreamOn:@-ifFail:@- @item openStreamOn:@- aURI ifFail:@- aBlock Check if aURI can be fetched from the Internet or from the local system, and if so return a Stream with its contents. If this is not possible, instead, evaluate the zero-argument block aBlock and answer the result of the evaluation. @end table @node NetClients.URIResolver class-instance creation @subsection NetClients.URIResolver class:@- instance creation @table @b @meindex on:@- @item on:@- anURL Answer a new URIResolver that will do its best to fetch the data for anURL from the Internet. @end table @node NetClients.URL @section NetClients.URL @clindex NetClients.URL @table @b @item Defined in namespace Smalltalk.NetClients @itemx Superclass: Object @itemx Category: NetClients-URIResolver Copyright (c) Kazuki Yasumatsu, 1995. All rights reserved. @end table @menu * NetClients.URL class-encoding URLs:: (class) * NetClients.URL class-instance creation:: (class) * NetClients.URL-accessing:: (instance) * NetClients.URL-comparing:: (instance) * NetClients.URL-copying:: (instance) * NetClients.URL-initialize-release:: (instance) * NetClients.URL-printing:: (instance) * NetClients.URL-still unclassified:: (instance) * NetClients.URL-testing:: (instance) * NetClients.URL-utilities:: (instance) @end menu @node NetClients.URL class-encoding URLs @subsection NetClients.URL class:@- encoding URLs @table @b @meindex decode:@- @item decode:@- aString Decode a text/x-www-form-urlencoded String into a text/plain String. @meindex encode:@- @item encode:@- anURL Encode a text/plain into a text/x-www-form-urlencoded String (those things with lots of % in them). @meindex initialize @item initialize Initialize the receiver's class variables. @end table @node NetClients.URL class-instance creation @subsection NetClients.URL class:@- instance creation @table @b @meindex fromString:@- @item fromString:@- aString Parse the given URL and answer an URL object based on it. @meindex new @item new Answer a 'blank' URL. @meindex scheme:@-host:@-path:@- @item scheme:@- schemeString host:@- hostString path:@- pathString Answer an URL object made from all the parts passed as arguments. @meindex scheme:@-host:@-port:@-path:@- @item scheme:@- schemeString host:@- hostString port:@- portNumber path:@- pathString Answer an URL object made from all the parts passed as arguments. @meindex scheme:@-path:@- @item scheme:@- schemeString path:@- pathString Answer an URL object made from all the parts passed as arguments. @meindex scheme:@-username:@-password:@-host:@-port:@-path:@- @item scheme:@- schemeString username:@- userString password:@- passwordString host:@- hostString port:@- portNumber path:@- pathString Answer an URL object made from all the parts passed as arguments. @end table @node NetClients.URL-accessing @subsection NetClients.URL:@- accessing @table @b @meindex asString @item asString Answer the full request string corresponding to the URL. This is how the URL would be printed in the address bar of a web browser, except that the query data is printed even if it is to be sent through a POST request. @meindex decodedFields @item decodedFields Convert the form fields to a Dictionary, answer nil if no question mark is found in the URL. @meindex decodedFile @item decodedFile Answer the file part of the URL, decoding it from x-www-form-urlencoded format. @meindex decodedFragment @item decodedFragment Answer the fragment part of the URL, decoding it from x-www-form-urlencoded format. @meindex fragment @item fragment Answer the fragment part of the URL, leaving it in x-www-form-urlencoded format. @meindex fragment:@- @item fragment:@- aString Set the fragment part of the URL, which should be in x-www-form-urlencoded format. @meindex fullRequestString @item fullRequestString Answer the full request string corresponding to the URL. This is how the URL would be printed in the address bar of a web browser, except that the query data is printed even if it is to be sent through a POST request. @meindex hasPostData @item hasPostData Answer whether the URL has a query part but is actually for an HTTP POST request and not really part of the URL (as it would be for the HTTP GET request). @meindex hasPostData:@- @item hasPostData:@- aBoolean Set whether the query part of the URL is actually the data for an HTTP POST request and not really part of the URL (as it would be for the HTTP GET request). @meindex host @item host Answer the host part of the URL. @meindex host:@- @item host:@- aString Set the host part of the URL to aString. @meindex newsGroup @item newsGroup If the receiver is an nntp url, return the news group. @meindex password @item password Answer the password part of the URL. @meindex password:@- @item password:@- aString Set the password part of the URL to aString. @meindex path @item path Answer the path part of the URL. @meindex path:@- @item path:@- aString Set the path part of the URL to aString. @meindex port @item port Answer the port number part of the URL. @meindex port:@- @item port:@- anInteger Set the port number part of the URL to anInteger. @meindex postData @item postData Answer whether the URL has a query part and it is meant for an HTTP POST request, answer it. Else answer nil. @meindex postData:@- @item postData:@- aString Associate to the URL some data that is meant to be sent through an HTTP POST request, answer it. @meindex query @item query Answer the query data associated to the URL. @meindex query:@- @item query:@- aString Set the query data associated to the URL to aString. @meindex requestString @item requestString Answer the URL as it would be sent in an HTTP stream (that is, the path and the query data, the latter only if it is to be sent with an HTTP POST request). @meindex scheme @item scheme Answer the URL's scheme. @meindex scheme:@- @item scheme:@- aString Set the URL's scheme to be aString. @meindex username @item username Answer the username part of the URL. @meindex username:@- @item username:@- aString Set the username part of the URL to aString. @end table @node NetClients.URL-comparing @subsection NetClients.URL:@- comparing @table @b @meindex = @item = anURL Answer whether the two URLs are equal. The file and anchor are converted to full 8-bit ASCII (contrast with urlencoded) and the comparison is case-sensitive; on the other hand, the protocol and host are compared without regard to case. @meindex hash @item hash Answer an hash value for the receiver @end table @node NetClients.URL-copying @subsection NetClients.URL:@- copying @table @b @meindex copyWithoutAuxiliaryParts @item copyWithoutAuxiliaryParts Answer a copy of the receiver where the fragment and query parts of the URL have been cleared. @meindex copyWithoutFragment @item copyWithoutFragment Answer a copy of the receiver where the fragment parts of the URL has been cleared. @meindex postCopy @item postCopy All the variables are copied when an URL object is copied. @end table @node NetClients.URL-initialize-release @subsection NetClients.URL:@- initialize-release @table @b @meindex initialize @item initialize Initialize the object to a consistent state. @end table @node NetClients.URL-printing @subsection NetClients.URL:@- printing @table @b @meindex printOn:@- @item printOn:@- stream Print a representation of the URL on the given stream. @end table @node NetClients.URL-still unclassified @subsection NetClients.URL:@- still unclassified @table @b @meindex contents @item contents Not commented. @meindex entity @item entity Not commented. @meindex readStream @item readStream Not commented. @end table @node NetClients.URL-testing @subsection NetClients.URL:@- testing @table @b @meindex canCache @item canCache Answer whether the URL is cacheable. The current implementation considers file URLs not to be cacheable, and everything else to be. @meindex hasFragment @item hasFragment Answer whether the URL points to a particular fragment (anchor) of the resource. @meindex hasQuery @item hasQuery Answer whether the URL includes query arguments to be submitted when retrieving the resource. @meindex isFileScheme @item isFileScheme Answer whether the URL is a file URL. @meindex isFragmentOnly @item isFragmentOnly Answer whether the URL only includes the name of a particular fragment (anchor) of the resource to which it refers. @end table @node NetClients.URL-utilities @subsection NetClients.URL:@- utilities @table @b @meindex construct:@- @item construct:@- anURL Construct an absolute URL based on the relative URL anURL and the base path represented by the receiver @end table @node Notification @section Notification @clindex Notification @table @b @item Defined in namespace Smalltalk @itemx Superclass: Exception @itemx Category: Language-Exceptions Notification represents a resumable, exceptional yet non-erroneous, situation. Signaling a notification in absence of an handler simply returns nil. @end table @menu * Notification-exception description:: (instance) @end menu @node Notification-exception description @subsection Notification:@- exception description @table @b @meindex defaultAction @item defaultAction Do the default action for notifications, which is to resume execution of the context which signaled the exception. @meindex description @item description Answer a textual description of the exception. @meindex isResumable @item isResumable Answer true. Notification exceptions are by default resumable. @end table @node NullProxy @section NullProxy @clindex NullProxy @table @b @item Defined in namespace Smalltalk @itemx Superclass: AlternativeObjectProxy @itemx Category: Streams-Files I am a proxy that does no special processing on the object to be saved. I can be used to disable proxies for particular subclasses. My subclasses add to the stored information, but share the fact that the format is about the same as that of #dump:@- without a proxy. @end table @menu * NullProxy class-instance creation:: (class) * NullProxy-accessing:: (instance) @end menu @node NullProxy class-instance creation @subsection NullProxy class:@- instance creation @table @b @meindex loadFrom:@- @item loadFrom:@- anObjectDumper Reload the object stored in anObjectDumper @end table @node NullProxy-accessing @subsection NullProxy:@- accessing @table @b @meindex dumpTo:@- @item dumpTo:@- anObjectDumper Dump the object stored in the proxy to anObjectDumper @end table @node NullValueHolder @section NullValueHolder @clindex NullValueHolder @table @b @item Defined in namespace Smalltalk @itemx Superclass: ValueAdaptor @itemx Category: Language-Data types I pretend to store my value in a variable, but I don't actually. You can use the only instance of my class (returned by `ValueHolder null') if you're not interested in a value that is returned as described in ValueHolder's comment. @end table @menu * NullValueHolder class-creating instances:: (class) * NullValueHolder-accessing:: (instance) @end menu @node NullValueHolder class-creating instances @subsection NullValueHolder class:@- creating instances @table @b @meindex new @item new Not used -- use `ValueHolder null' instead @meindex uniqueInstance @item uniqueInstance Answer the sole instance of NullValueHolder @end table @node NullValueHolder-accessing @subsection NullValueHolder:@- accessing @table @b @meindex value @item value Retrive the value of the receiver. Always answer nil @meindex value:@- @item value:@- anObject Set the value of the receiver. Do nothing, discard the value @end table @node Number @section Number @clindex Number @table @b @item Defined in namespace Smalltalk @itemx Superclass: Magnitude @itemx Category: Language-Data types I am an abstract class that provides operations on numbers, both floating point and integer. I provide some generic predicates, and supply the implicit type coercing code for binary operations. @end table @menu * Number class-converting:: (class) * Number class-testing:: (class) * Number-arithmetic:: (instance) * Number-coercion:: (instance) * Number-comparing:: (instance) * Number-converting:: (instance) * Number-copying:: (instance) * Number-error raising:: (instance) * Number-misc math:: (instance) * Number-point creation:: (instance) * Number-retrying:: (instance) * Number-shortcuts and iterators:: (instance) * Number-testing:: (instance) * Number-truncation and round off:: (instance) @end menu @node Number class-converting @subsection Number class:@- converting @table @b @meindex coerce:@- @item coerce:@- aNumber Answer aNumber - whatever class it belongs to, it is good @meindex readFrom:@- @item readFrom:@- aStream Answer the number read from the rest of aStream, converted to an instance of the receiver. If the receiver is number, the class of the result is undefined -- but the result is good. @meindex readFrom:@-radix:@- @item readFrom:@- aStream radix:@- anInteger Answer the number read from the rest of aStream, converted to an instance of the receiver. If the receiver is number, the class of the result is undefined -- but the result is good. The exponent (for example 1.2e-1) is only parsed if anInteger is 10. @end table @node Number class-testing @subsection Number class:@- testing @table @b @meindex isImmediate @item isImmediate Answer whether, if x is an instance of the receiver, x copy == x @end table @node Number-arithmetic @subsection Number:@- arithmetic @table @b @meindex * @item * aNumber Subtract the receiver and aNumber, answer the result @meindex + @item + aNumber Sum the receiver and aNumber, answer the result @meindex - @item - aNumber Subtract aNumber from the receiver, answer the result @meindex / @item / aNumber Divide the receiver by aNumber, answer the result (no loss of precision). Raise a ZeroDivide exception or return a valid (possibly infinite) continuation value if aNumber is zero. @meindex // @item // aNumber Return the integer quotient of dividing the receiver by aNumber with truncation towards negative infinity. Raise a ZeroDivide exception if aNumber is zero @meindex \\ @item \\ aNumber Return the remainder of dividing the receiver by aNumber with truncation towards negative infinity. Raise a ZeroDivide exception if aNumber is zero @meindex quo:@- @item quo:@- aNumber Return the integer quotient of dividing the receiver by aNumber with truncation towards zero. Raise a ZeroDivide exception if aNumber is zero @meindex reciprocal @item reciprocal Return the reciprocal of the receiver @meindex rem:@- @item rem:@- aNumber Return the remainder of dividing the receiver by aNumber with truncation towards zero. Raise a ZeroDivide exception if aNumber is zero @end table @node Number-coercion @subsection Number:@- coercion @table @b @meindex asCNumber @item asCNumber Convert the receiver to a kind of number that is understood by the C call-out mechanism. @end table @node Number-comparing @subsection Number:@- comparing @table @b @meindex max:@- @item max:@- aNumber Answer the maximum between the receiver and aNumber. Redefine in subclasses if necessary to ensure that if either self or aNumber is a NaN, it is always answered. @meindex min:@- @item min:@- aNumber Answer the minimum between the receiver and aNumber. Redefine in subclasses if necessary to ensure that if either self or aNumber is a NaN, it is always answered. @end table @node Number-converting @subsection Number:@- converting @table @b @meindex asExactFraction @item asExactFraction Return the receiver, converted to a Fraction retaining the exact value of the receiver. @meindex asFloat @item asFloat Convert the receiver to an arbitrary subclass of Float @meindex asFloatD @item asFloatD This method's functionality should be implemented by subclasses of Number @meindex asFloatE @item asFloatE This method's functionality should be implemented by subclasses of Number @meindex asFloatQ @item asFloatQ This method's functionality should be implemented by subclasses of Number @meindex asFraction @item asFraction This method's functionality should be implemented by subclasses of Number @meindex asNumber @item asNumber Answer the receiver, since it is already a number @meindex asRectangle @item asRectangle Answer an empty rectangle whose origin is (self asPoint) @meindex asScaledDecimal:@- @item asScaledDecimal:@- n Answer the receiver, converted to a ScaledDecimal object. @meindex asScaledDecimal:@-radix:@-scale:@- @item asScaledDecimal:@- denDigits radix:@- base scale:@- n Answer the receiver, divided by base^denDigits and converted to a ScaledDecimal object. @meindex asString @slindex displayString @item asString Answer the receiver's #displayString, which should be a good enough conversion to String for a number. @meindex coerce:@- @item coerce:@- aNumber Answer aNumber, converted to an integer or floating-point number. @meindex degreesToRadians @item degreesToRadians Convert the receiver to radians @meindex generality @item generality Answer the receiver's generality @meindex radiansToDegrees @item radiansToDegrees Convert the receiver from radians to degrees @meindex unity @item unity Coerce 1 to the receiver's class. The default implementation works, but is inefficient @meindex zero @item zero Coerce 0 to the receiver's class. The default implementation works, but is inefficient @end table @node Number-copying @subsection Number:@- copying @table @b @meindex deepCopy @item deepCopy Return the receiver - it's an immediate (immutable) object @meindex shallowCopy @item shallowCopy Return the receiver - it's an immediate (immutable) object @end table @node Number-error raising @subsection Number:@- error raising @table @b @meindex arithmeticError:@- @item arithmeticError:@- msg Raise an ArithmeticError exception having msg as its message text. @meindex zeroDivide @item zeroDivide Raise a division-by-zero (ZeroDivide) exception whose dividend is the receiver. @end table @node Number-misc math @subsection Number:@- misc math @table @b @meindex abs @item abs Answer the absolute value of the receiver @meindex arcCos @item arcCos Answer the arc cosine of the receiver @meindex arcCosh @item arcCosh Answer the hyperbolic arc-cosine of the receiver. @meindex arcSin @item arcSin Answer the arc sine of the receiver @meindex arcSinh @item arcSinh Answer the hyperbolic arc-sine of the receiver. @meindex arcTan @item arcTan Answer the arc tangent of the receiver @meindex arcTan:@- @item arcTan:@- x Answer the angle (measured counterclockwise) between (x, self) and a ray starting in (0, 0) and moving towards (1, 0) - i.e. 3 o'clock @meindex arcTanh @item arcTanh Answer the hyperbolic arc-tangent of the receiver. @meindex ceilingLog:@- @item ceilingLog:@- radix Answer (self log:@- radix) ceiling. Optimized to answer an integer. @meindex cos @item cos Answer the cosine of the receiver @meindex cosh @item cosh Answer the hyperbolic cosine of the receiver. @meindex estimatedLog @item estimatedLog Answer an estimate of (self abs floorLog:@- 10). This method should be overridden by subclasses, but Number's implementation does not raise errors - simply, it gives a correct result, so it is slow. @meindex exp @item exp Answer e raised to the receiver @meindex floorLog:@- @item floorLog:@- radix Answer (self log:@- radix) floor. Optimized to answer an integer. @meindex ln @item ln Answer log base e of the receiver @meindex log @item log Answer log base 10 of the receiver @meindex log:@- @item log:@- aNumber Answer log base aNumber of the receiver @meindex negated @item negated Answer the negated of the receiver @meindex positiveDifference:@- @item positiveDifference:@- aNumber Answer the positive difference of the receiver and aNumber, that is self - aNumber if it is positive, 0 otherwise. @meindex raisedTo:@- @item raisedTo:@- aNumber Return self raised to aNumber power @meindex raisedToInteger:@- @item raisedToInteger:@- anInteger Return self raised to the anInteger-th power @meindex sin @item sin Answer the sine of the receiver @meindex sinh @item sinh Answer the hyperbolic sine of the receiver. @meindex sqrt @item sqrt Answer the square root of the receiver @meindex squared @item squared Answer the square of the receiver @meindex tan @item tan Answer the tangent of the receiver @meindex tanh @item tanh Answer the hyperbolic tangent of the receiver. @meindex withSignOf:@- @item withSignOf:@- aNumber Answer the receiver, with its sign possibly changed to match that of aNumber. @end table @node Number-point creation @subsection Number:@- point creation @table @b @meindex @@ @item @@ y Answer a new point whose x is the receiver and whose y is y @meindex asPoint @item asPoint Answer a new point, self @@ self @end table @node Number-retrying @subsection Number:@- retrying @table @b @meindex retry:@-coercing:@- @slindex = @slindex ~= @item retry:@- aSymbol coercing:@- aNumber Coerce to the other number's class the one number between the receiver and aNumber which has the lowest, and retry calling aSymbol. aSymbol is supposed not to be #= or #~= (since those don't fail if aNumber is not a Number). @meindex retryDifferenceCoercing:@- @slindex - @item retryDifferenceCoercing:@- aNumber Coerce to the other number's class the one number between the receiver and aNumber which has the lowest, and retry calling #-. @meindex retryDivisionCoercing:@- @slindex / @item retryDivisionCoercing:@- aNumber Coerce to the other number's class the one number between the receiver and aNumber which has the lowest, and retry calling #/. @meindex retryEqualityCoercing:@- @slindex = @item retryEqualityCoercing:@- aNumber Coerce to the other number's class the one number between the receiver and aNumber which has the lowest, and retry calling #=. @meindex retryError @item retryError Raise an error---a retrying method was called with two arguments having the same generality. @meindex retryInequalityCoercing:@- @slindex ~= @item retryInequalityCoercing:@- aNumber Coerce to the other number's class the one number between the receiver and aNumber which has the lowest, and retry calling #~=. @meindex retryMultiplicationCoercing:@- @slindex * @item retryMultiplicationCoercing:@- aNumber Coerce to the other number's class the one number between the receiver and aNumber which has the lowest, and retry calling #*. @meindex retryRelationalOp:@-coercing:@- @item retryRelationalOp:@- aSymbol coercing:@- aNumber Coerce to the other number's class the one number between the receiver and aNumber which has the lowest, and retry calling aSymbol (<, <=, >, >=). @meindex retrySumCoercing:@- @slindex + @item retrySumCoercing:@- aNumber Coerce to the other number's class the one number between the receiver and aNumber which has the lowest, and retry calling #+. @end table @node Number-shortcuts and iterators @subsection Number:@- shortcuts and iterators @table @b @meindex to:@- @item to:@- stop Return an interval going from the receiver to stop by 1 @meindex to:@-by:@- @item to:@- stop by:@- step Return an interval going from the receiver to stop with the given step @meindex to:@-by:@-collect:@- @item to:@- stop by:@- step collect:@- aBlock Evaluate aBlock for each value in the interval going from the receiver to stop with the given step. The results are collected in an Array and returned. @meindex to:@-by:@-do:@- @item to:@- stop by:@- step do:@- aBlock Evaluate aBlock for each value in the interval going from the receiver to stop with the given step. Compiled in-line for integer literal steps, and for one-argument aBlocks without temporaries, and therefore not overridable. @meindex to:@-collect:@- @item to:@- stop collect:@- aBlock Evaluate aBlock for each value in the interval going from the receiver to stop by 1. The results are collected in an Array and returned. @meindex to:@-do:@- @item to:@- stop do:@- aBlock Evaluate aBlock for each value in the interval going from the receiver to stop by 1. Compiled in-line for one-argument aBlocks without temporaries, and therefore not overridable. @end table @node Number-testing @subsection Number:@- testing @table @b @meindex closeTo:@- @item closeTo:@- num Answer whether the receiver can be considered sufficiently close to num (this is done by checking equality if num is not a number, and by checking with 0.01% tolerance if num is a number). @meindex even @item even Returns true if self is divisible by 2 @meindex isExact @slindex subclassResponsibility @item isExact Answer whether the receiver performs exact arithmetic. Most numeric classes do (in fact the only exceptions is Float and its descendants), so the default is to answer true rather than calling #subclassResponsibility. @meindex isFinite @slindex subclassResponsibility @item isFinite Answer whether the receiver represents a finite quantity. Most numeric classes are for finite quantities, so the default is to answer true rather than calling #subclassResponsibility. @meindex isInfinite @slindex subclassResponsibility @item isInfinite Answer whether the receiver represents an infinite quantity. Most numeric classes are for finite quantities, so the default is to answer false rather than calling #subclassResponsibility. @meindex isNaN @slindex subclassResponsibility @item isNaN Answer whether the receiver is a Not-A-Number. Most numeric classes don't handle nans, so the default is to answer false rather than calling #subclassResponsibility. @meindex isNumber @item isNumber Answer `true'. @meindex isRational @item isRational Answer whether the receiver is rational - false by default @meindex negative @item negative Answer whether the receiver is < 0 @meindex odd @item odd Returns true if self is not divisible by 2 @meindex positive @item positive Answer whether the receiver is >= 0 @meindex sign @item sign Returns the sign of the receiver. @meindex strictlyPositive @item strictlyPositive Answer whether the receiver is > 0 @end table @node Number-truncation and round off @subsection Number:@- truncation and round off @table @b @meindex asInteger @item asInteger Answer the receiver, rounded to the nearest integer @meindex floor @item floor Return the integer nearest the receiver toward negative infinity. @meindex fractionPart @slindex integerPart @item fractionPart Answer a number which, summed to the #integerPart of the receiver, gives the receiver itself. @meindex integerPart @item integerPart Answer the receiver, truncated towards zero @meindex roundTo:@- @item roundTo:@- aNumber Answer the receiver, truncated to the nearest multiple of aNumber @meindex rounded @item rounded Returns the integer nearest the receiver @meindex truncateTo:@- @item truncateTo:@- aNumber Answer the receiver, truncated towards zero to a multiple of aNumber @meindex truncated @item truncated Answer the receiver, truncated towards zero @end table @node Object @section Object @clindex Object @table @b @item Defined in namespace Smalltalk @itemx Superclass: none @itemx Category: Language-Implementation I am the root of the Smalltalk class system. All classes in the system are subclasses of me. @end table @menu * Object class-initialization:: (class) * Object-built ins:: (instance) * Object-change and update:: (instance) * Object-class type methods:: (instance) * Object-compiler:: (instance) * Object-conversion:: (instance) * Object-copying:: (instance) * Object-debugging:: (instance) * Object-dependents access:: (instance) * Object-error raising:: (instance) * Object-finalization:: (instance) * Object-introspection:: (instance) * Object-printing:: (instance) * Object-relational operators:: (instance) * Object-saving and loading:: (instance) * Object-storing:: (instance) * Object-syntax shortcuts:: (instance) * Object-testing functionality:: (instance) * Object-VM callbacks:: (instance) @end menu @node Object class-initialization @subsection Object class:@- initialization @table @b @meindex dependencies @item dependencies Answer a dictionary that associates an object with its dependents. @meindex dependencies:@- @item dependencies:@- anObject Use anObject as the dictionary that associates an object with its dependents. @meindex finalizableObjects @item finalizableObjects Answer a set of finalizable objects. @meindex initialize @item initialize Initialize the Dependencies dictionary to be a WeakKeyIdentityDictionary. @meindex update:@- @item update:@- aspect Do any global tasks for the ObjectMemory events. @end table @node Object-built ins @subsection Object:@- built ins @table @b @meindex = @item = arg Answer whether the receiver is equal to arg. The equality test is by default the same as that for identical objects. = must not fail; answer false if the receiver cannot be compared to arg @meindex == @item == arg Answer whether the receiver is the same object as arg. This is a very fast test and is called 'object identity'. @meindex allOwners @item allOwners Return an Array of Objects that point to the receiver. @meindex asOop @item asOop Answer the object index associated to the receiver. The object index doesn't change when garbage collection is performed. @meindex at:@- @item at:@- anIndex Answer the index-th indexed instance variable of the receiver @meindex at:@-put:@- @item at:@- anIndex put:@- value Store value in the index-th indexed instance variable of the receiver @meindex basicAt:@- @item basicAt:@- anIndex Answer the index-th indexed instance variable of the receiver. This method must not be overridden, override at:@- instead @meindex basicAt:@-put:@- @item basicAt:@- anIndex put:@- value Store value in the index-th indexed instance variable of the receiver This method must not be overridden, override at:@-put:@- instead @meindex basicPrint @item basicPrint Print a basic representation of the receiver @meindex basicSize @item basicSize Answer the number of indexed instance variable in the receiver @meindex become:@- @slindex become:@- @item become:@- otherObject Change all references to the receiver into references to otherObject. Depending on the implementation, references to otherObject might or might not be transformed into the receiver (respectively, 'two-way become' and 'one-way become'). Implementations doing one-way become answer the receiver (so that it is not lost). Most implementations doing two-way become answer otherObject, but this is not assured - so do answer the receiver for consistency. GNU Smalltalk does two-way become and answers otherObject, but this might change in future versions:@- programs should not rely on the behavior and results of #become:@- . @meindex becomeForward:@- @item becomeForward:@- otherObject Change all references to the receiver into references to otherObject. References to otherObject are not transformed into the receiver. Answer the receiver so that it is not lost. @meindex changeClassTo:@- @item changeClassTo:@- aBehavior Mutate the class of the receiver to be aBehavior. Note:@- Tacitly assumes that the structure is the same for the original and new class!! @meindex checkIndexableBounds:@- @item checkIndexableBounds:@- index Private - Check the reason why an access to the given indexed instance variable failed @meindex checkIndexableBounds:@-ifAbsent:@- @item checkIndexableBounds:@- index ifAbsent:@- aBlock Private - Check the reason why an access to the given indexed instance variable failed. Evaluate aBlock for an invalid index. @meindex checkIndexableBounds:@-put:@- @item checkIndexableBounds:@- index put:@- object Private - Check the reason why a store to the given indexed instance variable failed @meindex class @item class Answer the class to which the receiver belongs @meindex halt @item halt Called to enter the debugger @meindex hash @item hash Answer an hash value for the receiver. This hash value is ok for objects that do not redefine ==. @meindex identityHash @item identityHash Answer an hash value for the receiver. This method must not be overridden @meindex instVarAt:@- @item instVarAt:@- index Answer the index-th instance variable of the receiver. This method must not be overridden. @meindex instVarAt:@-put:@- @item instVarAt:@- index put:@- value Store value in the index-th instance variable of the receiver. This method must not be overridden. @meindex isReadOnly @item isReadOnly Answer whether the object's indexed instance variables can be written @meindex isUntrusted @item isUntrusted Answer whether the object is to be considered untrusted. @meindex makeEphemeron @slindex mourn @item makeEphemeron Make the object an 'ephemeron'. An ephemeron is marked after all other objects, and if no references are found to the key except from the object itself, it is sent the #mourn message. @meindex makeFixed @item makeFixed Avoid that the receiver moves in memory across garbage collections. @meindex makeReadOnly:@- @item makeReadOnly:@- aBoolean Set whether the object's indexed instance variables can be written @meindex makeUntrusted:@- @item makeUntrusted:@- aBoolean Set whether the object is to be considered untrusted. @meindex makeWeak @slindex mourn @item makeWeak Make the object a 'weak' one. When an object is only referenced by weak objects, it is collected and the slots in the weak objects are changed to nils by the VM; the weak object is then sent the #mourn message. @meindex mark:@- @slindex mark:@- @slindex mark:@- @item mark:@- aSymbol Private - use this method to mark code which needs to be reworked, removed, etc. You can then find all senders of #mark:@- to find all marked methods or you can look for all senders of the symbol that you sent to #mark:@- to find a category of marked methods. @meindex nextInstance @item nextInstance Private - answer another instance of the receiver's class, or nil if the entire object table has been walked @meindex notYetImplemented @item notYetImplemented Called when a method defined by a class is not yet implemented, but is going to be @meindex perform:@- @item perform:@- selectorOrMessageOrMethod Send the unary message named selectorOrMessageOrMethod (if a Symbol) to the receiver, or the message and arguments it identifies (if a Message or DirectedMessage), or finally execute the method within the receiver (if a CompiledMethod). In the last case, the method need not reside on the hierarchy from the receiver's class to Object -- it need not reside at all in a MethodDictionary, in fact -- but doing bad things will compromise stability of the Smalltalk virtual machine (and don't blame anybody but yourself). This method should not be overridden @meindex perform:@-with:@- @item perform:@- selectorOrMethod with:@- arg1 Send the message named selectorOrMethod (if a Symbol) to the receiver, passing arg1 to it, or execute the method within the receiver (if a CompiledMethod). In the latter case, the method need not reside on the hierarchy from the receiver's class to Object -- it need not reside at all in a MethodDictionary, in fact -- but doing bad things will compromise stability of the Smalltalk virtual machine (and don't blame anybody but yourself). This method should not be overridden @meindex perform:@-with:@-with:@- @item perform:@- selectorOrMethod with:@- arg1 with:@- arg2 Send the message named selectorOrMethod (if a Symbol) to the receiver, passing arg1 and arg2 to it, or execute the method within the receiver (if a CompiledMethod). In the latter case, the method need not reside on the hierarchy from the receiver's class to Object -- it need not reside at all in a MethodDictionary, in fact -- but doing bad things will compromise stability of the Smalltalk virtual machine (and don't blame anybody but yourself). This method should not be overridden @meindex perform:@-with:@-with:@-with:@- @item perform:@- selectorOrMethod with:@- arg1 with:@- arg2 with:@- arg3 Send the message named selectorOrMethod (if a Symbol) to the receiver, passing the other arguments to it, or execute the method within the receiver (if a CompiledMethod). In the latter case, the method need not reside on the hierarchy from the receiver's class to Object -- it need not reside at all in a MethodDictionary, in fact -- but doing bad things will compromise stability of the Smalltalk virtual machine (and don't blame anybody but yourself). This method should not be overridden @meindex perform:@-with:@-with:@-with:@-with:@- @item perform:@- selectorOrMethod with:@- arg1 with:@- arg2 with:@- arg3 with:@- arg4 Send the message named selectorOrMethod (if a Symbol) to the receiver, passing the other arguments to it, or execute the method within the receiver (if a CompiledMethod). In the latter case, the method need not reside on the hierarchy from the receiver's class to Object -- it need not reside at all in a MethodDictionary, in fact -- but doing bad things will compromise stability of the Smalltalk virtual machine (and don't blame anybody but yourself). This method should not be overridden @meindex perform:@-withArguments:@- @item perform:@- selectorOrMethod withArguments:@- argumentsArray Send the message named selectorOrMethod (if a Symbol) to the receiver, passing the elements of argumentsArray as parameters, or execute the method within the receiver (if a CompiledMethod). In the latter case, the method need not reside on the hierarchy from the receiver's class to Object -- it need not reside at all in a MethodDictionary, in fact -- but doing bad things will compromise stability of the Smalltalk virtual machine (and don't blame anybody but yourself). This method should not be overridden @meindex primitiveFailed @item primitiveFailed Called when a VM primitive fails @meindex shallowCopy @item shallowCopy Returns a shallow copy of the receiver (the instance variables are not copied) @meindex shouldNotImplement @item shouldNotImplement Called when objects belonging to a class should not answer a selector defined by a superclass @meindex size @item size Answer the number of indexed instance variable in the receiver @meindex subclassResponsibility @item subclassResponsibility Called when a method defined by a class should be overridden in a subclass @meindex tenure @item tenure Move the object to oldspace. @end table @node Object-change and update @subsection Object:@- change and update @table @b @meindex broadcast:@- @item broadcast:@- aSymbol Send the unary message aSymbol to each of the receiver's dependents @meindex broadcast:@-with:@- @item broadcast:@- aSymbol with:@- anObject Send the message aSymbol to each of the receiver's dependents, passing anObject @meindex broadcast:@-with:@-with:@- @item broadcast:@- aSymbol with:@- arg1 with:@- arg2 Send the message aSymbol to each of the receiver's dependents, passing arg1 and arg2 as parameters @meindex broadcast:@-withArguments:@- @item broadcast:@- aSymbol withArguments:@- anArray Send the message aSymbol to each of the receiver's dependents, passing the parameters in anArray @meindex broadcast:@-withBlock:@- @item broadcast:@- aSymbol withBlock:@- aBlock Send the message aSymbol to each of the receiver's dependents, passing the result of evaluating aBlock with each dependent as the parameter @meindex changed @item changed Send update:@- for each of the receiver's dependents, passing them the receiver @meindex changed:@- @item changed:@- aParameter Send update:@- for each of the receiver's dependents, passing them aParameter @meindex update:@- @slindex changed @slindex changed:@- @item update:@- aParameter Default behavior is to do nothing. Called by #changed and #changed:@- @end table @node Object-class type methods @subsection Object:@- class type methods @table @b @meindex species @slindex class @slindex species @slindex copyEmpty:@- @item species This method has no unique definition. Generally speaking, methods which always return the same type usually don't use #class, but #species. For example, a PositionableStream's species is the class of the collection on which it is streaming (used by upTo:@-, upToAll:@-, upToEnd). Stream uses species for obtaining the class of next:@-'s return value, Collection uses it in its #copyEmpty:@- message, which in turn is used by all collection-returning methods. An Interval's species is Array (used by collect:@-, select:@-, reject:@-, etc.). @meindex yourself @item yourself Answer the receiver @end table @node Object-compiler @subsection Object:@- compiler @table @b @meindex literalEquals:@- @item literalEquals:@- anObject Not commented. @meindex literalHash @item literalHash Not commented. @end table @node Object-conversion @subsection Object:@- conversion @table @b @meindex asValue @item asValue Answer a ValueHolder whose initial value is the receiver. @end table @node Object-copying @subsection Object:@- copying @table @b @meindex copy @item copy Returns a shallow copy of the receiver (the instance variables are not copied). The shallow copy receives the message postCopy and the result of postCopy is passed back. @meindex deepCopy @item deepCopy Returns a deep copy of the receiver (the instance variables are copies of the receiver's instance variables) @meindex postCopy @item postCopy Performs any changes required to do on a copied object. This is the place where one could, for example, put code to replace objects with copies of the objects @end table @node Object-debugging @subsection Object:@- debugging @table @b @meindex examine @item examine Print all the instance variables of the receiver on the Transcript @meindex examineOn:@- @item examineOn:@- aStream Print all the instance variables of the receiver on aStream @meindex inspect @slindex examine @item inspect In a GUI environment, this opens a tool to examine and modify the receiver. In the default image, it just calls #examine. @meindex validSize @item validSize Answer how many elements in the receiver should be inspected @end table @node Object-dependents access @subsection Object:@- dependents access @table @b @meindex addDependent:@- @item addDependent:@- anObject Add anObject to the set of the receiver's dependents. Important:@- if an object has dependents, it won't be garbage collected. @meindex dependents @item dependents Answer a collection of the receiver's dependents. @meindex release @item release Remove all of the receiver's dependents from the set and allow the receiver to be garbage collected. @meindex removeDependent:@- @item removeDependent:@- anObject Remove anObject to the set of the receiver's dependents. No problem if anObject is not in the set of the receiver's dependents. @end table @node Object-error raising @subsection Object:@- error raising @table @b @meindex doesNotUnderstand:@- @item doesNotUnderstand:@- aMessage Called by the system when a selector was not found. message is a Message containing information on the receiver @meindex error:@- @item error:@- message Display a walkback for the receiver, with the given error message. Signal an `Error' exception. @meindex halt:@- @item halt:@- message Display a walkback for the receiver, with the given error message. Signal an `Halt' exception. @end table @node Object-finalization @subsection Object:@- finalization @table @b @meindex addToBeFinalized @slindex finalize @item addToBeFinalized Arrange things so that #finalize is sent to the object when the garbage collector finds out there are only weak references to it. @meindex finalize @item finalize Do nothing by default @meindex mourn @item mourn This method is sent by the VM to weak and ephemeron objects when one of their fields is found out to be garbage collectable (this means, for weak objects, that there are no references to it from non-weak objects, and for ephemeron objects, that the only paths to the first instance variable pass through other instance variables of the same ephemeron). The default behavior is to do nothing. @meindex removeToBeFinalized @slindex finalize @item removeToBeFinalized Unregister the object, so that #finalize is no longer sent to the object when the garbage collector finds out there are only weak references to it. @end table @node Object-introspection @subsection Object:@- introspection @table @b @meindex instVarNamed:@- @item instVarNamed:@- aString Answer the instance variable named aString in the receiver. @meindex instVarNamed:@-put:@- @item instVarNamed:@- aString put:@- anObject Answer the instance variable named aString in the receiver. @end table @node Object-printing @subsection Object:@- printing @table @b @meindex basicPrintNl @item basicPrintNl Print a basic representation of the receiver, followed by a new line. @meindex basicPrintOn:@- @item basicPrintOn:@- aStream Print a represention of the receiver on aStream @meindex display @slindex print @item display Print a represention of the receiver on the Transcript (stdout the GUI is not active). For most objects this is simply its #print representation, but for strings and characters, superfluous dollars or extra pair of quotes are stripped. @meindex displayNl @slindex printNl @item displayNl Print a represention of the receiver, then put a new line on the Transcript (stdout the GUI is not active). For most objects this is simply its #printNl representation, but for strings and characters, superfluous dollars or extra pair of quotes are stripped. @meindex displayOn:@- @slindex printOn:@- @item displayOn:@- aStream Print a represention of the receiver on aStream. For most objects this is simply its #printOn:@- representation, but for strings and characters, superfluous dollars or extra pair of quotes are stripped. @meindex displayString @slindex printString @item displayString Answer a String representing the receiver. For most objects this is simply its #printString, but for strings and characters, superfluous dollars or extra pair of quotes are stripped. @meindex print @item print Print a represention of the receiver on the Transcript (stdout the GUI is not active) @meindex printNl @item printNl Print a represention of the receiver on stdout, put a new line the Transcript (stdout the GUI is not active) @meindex printOn:@- @item printOn:@- aStream Print a represention of the receiver on aStream @meindex printString @item printString Answer a String representing the receiver @end table @node Object-relational operators @subsection Object:@- relational operators @table @b @meindex ~= @item ~= anObject Answer whether the receiver and anObject are not equal @meindex ~~ @item ~~ anObject Answer whether the receiver and anObject are not the same object @end table @node Object-saving and loading @subsection Object:@- saving and loading @table @b @meindex binaryRepresentationObject @item binaryRepresentationObject This method must be implemented if PluggableProxies are used with the receiver's class. The default implementation raises an exception. @meindex postLoad @item postLoad Called after loading an object; must restore it to the state before `preStore' was called. Do nothing by default @meindex postStore @slindex postLoad @item postStore Called after an object is dumped; must restore it to the state before `preStore' was called. Call #postLoad by default @meindex preStore @item preStore Called before dumping an object; it must *change* it (it must not answer a new object) if necessary. Do nothing by default @meindex reconstructOriginalObject @slindex binaryRepresentationObject @item reconstructOriginalObject Used if an instance of the receiver's class is returned as the #binaryRepresentationObject of another object. The default implementation raises an exception. @end table @node Object-storing @subsection Object:@- storing @table @b @meindex store @item store Put a String of Smalltalk code compiling to the receiver on the Transcript (stdout the GUI is not active) @meindex storeLiteralOn:@- @item storeLiteralOn:@- aStream Put a Smalltalk literal compiling to the receiver on aStream @meindex storeNl @item storeNl Put a String of Smalltalk code compiling to the receiver, followed by a new line, on the Transcript (stdout the GUI is not active) @meindex storeOn:@- @item storeOn:@- aStream Put Smalltalk code compiling to the receiver on aStream @meindex storeString @item storeString Answer a String of Smalltalk code compiling to the receiver @end table @node Object-syntax shortcuts @subsection Object:@- syntax shortcuts @table @b @meindex -> @item -> anObject Creates a new instance of Association with the receiver being the key and the argument becoming the value @end table @node Object-testing functionality @subsection Object:@- testing functionality @table @b @meindex ifNil:@- @item ifNil:@- nilBlock Evaluate nilBlock if the receiver is nil, else answer self @meindex ifNil:@-ifNotNil:@- @item ifNil:@- nilBlock ifNotNil:@- notNilBlock Evaluate nilBlock if the receiver is nil, else evaluate notNilBlock, passing the receiver. @meindex ifNotNil:@- @item ifNotNil:@- notNilBlock Evaluate notNilBlock if the receiver is not nil, passing the receiver. Else answer nil. @meindex ifNotNil:@-ifNil:@- @item ifNotNil:@- notNilBlock ifNil:@- nilBlock Evaluate nilBlock if the receiver is nil, else evaluate notNilBlock, passing the receiver. @meindex isArray @item isArray Answer `false'. @meindex isBehavior @item isBehavior Answer `false'. @meindex isCObject @item isCObject Answer `false'. @meindex isCharacter @item isCharacter Answer `false'. @meindex isCharacterArray @item isCharacterArray Answer `false'. @meindex isClass @item isClass Answer `false'. @meindex isFloat @item isFloat Answer `false'. @meindex isInteger @item isInteger Answer `false'. @meindex isKindOf:@- @item isKindOf:@- aClass Answer whether the receiver's class is aClass or a subclass of aClass @meindex isMemberOf:@- @item isMemberOf:@- aClass Returns true if the receiver is an instance of the class 'aClass' @meindex isMeta @item isMeta Same as isMetaclass @meindex isMetaClass @item isMetaClass Same as isMetaclass @meindex isMetaclass @item isMetaclass Answer `false'. @meindex isNamespace @item isNamespace Answer `false'. @meindex isNil @item isNil Answer whether the receiver is nil @meindex isNumber @item isNumber Answer `false'. @meindex isSmallInteger @item isSmallInteger Answer `false'. @meindex isString @item isString Answer `false'. @meindex isSymbol @item isSymbol Answer `false'. @meindex notNil @item notNil Answer whether the receiver is not nil @meindex respondsTo:@- @item respondsTo:@- aSymbol Returns true if the receiver understands the given selector @end table @node Object-VM callbacks @subsection Object:@- VM callbacks @table @b @meindex badReturnError @item badReturnError Called back when a block performs a bad return. @meindex mustBeBoolean @item mustBeBoolean Called by the system when ifTrue:@-*, ifFalse:@-*, and:@- or or:@- are sent to anything but a boolean @meindex noRunnableProcess @item noRunnableProcess Called back when all processes are suspended @meindex userInterrupt @item userInterrupt Called back when the user presses Ctrl-Break @end table @node ObjectDumper @section ObjectDumper @clindex ObjectDumper @table @b @item Defined in namespace Smalltalk @itemx Superclass: Stream @itemx Category: Streams-Files I'm not part of a normal Smalltalk system, but most Smalltalks provide a similar feature:@- that is, support for storing objects in a binary format; there are many advantages in using me instead of #storeOn:@- and the Smalltalk compiler. The data is stored in a very compact format, which has the side effect of making loading much faster when compared with compiling the Smalltalk code prepared by #storeOn:@-. In addition, my instances support circular references between objects, while #storeOn:@- supports it only if you know of such references at design time and you override #storeOn:@- to deal with them @end table @menu * ObjectDumper class-establishing proxy classes:: (class) * ObjectDumper class-instance creation:: (class) * ObjectDumper class-shortcuts:: (class) * ObjectDumper class-testing:: (class) * ObjectDumper-accessing:: (instance) * ObjectDumper-loading/dumping objects:: (instance) * ObjectDumper-stream interface:: (instance) @end menu @node ObjectDumper class-establishing proxy classes @subsection ObjectDumper class:@- establishing proxy classes @table @b @meindex disableProxyFor:@- @item disableProxyFor:@- aClass Disable proxies for instances of aClass and its descendants @meindex hasProxyFor:@- @item hasProxyFor:@- aClass Answer whether a proxy class has been registered for instances of aClass. @meindex proxyClassFor:@- @item proxyClassFor:@- anObject Answer the class of a valid proxy for an object, or nil if none could be found @meindex proxyFor:@- @item proxyFor:@- anObject Answer a valid proxy for an object, or the object itself if none could be found @meindex registerProxyClass:@-for:@- @item registerProxyClass:@- aProxyClass for:@- aClass Register the proxy class aProxyClass - descendent of DumperProxy - to be used for instances of aClass and its descendants @end table @node ObjectDumper class-instance creation @subsection ObjectDumper class:@- instance creation @table @b @meindex new @item new This method should not be called for instances of this class. @meindex on:@- @item on:@- aFileStream Answer an ObjectDumper working on aFileStream. @end table @node ObjectDumper class-shortcuts @subsection ObjectDumper class:@- shortcuts @table @b @meindex dump:@-to:@- @item dump:@- anObject to:@- aFileStream Dump anObject to aFileStream. Answer anObject @meindex loadFrom:@- @item loadFrom:@- aFileStream Load an object from aFileStream and answer it @end table @node ObjectDumper class-testing @subsection ObjectDumper class:@- testing @table @b @meindex example @item example This is a real torture test:@- it outputs recursive objects, identical objects multiple times, classes, metaclasses, integers, characters and proxies (which is also a test of more complex objects)! @end table @node ObjectDumper-accessing @subsection ObjectDumper:@- accessing @table @b @meindex flush @item flush `Forget' any information on previously stored objects. @meindex stream @item stream Answer the ByteStream to which the ObjectDumper will write and from which it will read. @meindex stream:@- @item stream:@- aByteStream Set the ByteStream to which the ObjectDumper will write and from which it will read. @end table @node ObjectDumper-loading/dumping objects @subsection ObjectDumper:@- loading/dumping objects @table @b @meindex dump:@- @item dump:@- anObject Dump anObject on the stream associated with the receiver. Answer anObject @meindex load @item load Load an object from the stream associated with the receiver and answer it @end table @node ObjectDumper-stream interface @subsection ObjectDumper:@- stream interface @table @b @meindex atEnd @item atEnd Answer whether the underlying stream is at EOF @meindex next @item next Load an object from the underlying stream @meindex nextPut:@- @item nextPut:@- anObject Store an object on the underlying stream @end table @node ObjectMemory @section ObjectMemory @clindex ObjectMemory @table @b @item Defined in namespace Smalltalk @itemx Superclass: Object @itemx Category: Language-Implementation I provide a few methods that enable one to tune the virtual machine's usage of memory. In addition, I can signal to my dependants some `events' that can happen during the virtual machine's life. ObjectMemory has both class-side and instance-side methods. In general, class-side methods provide means to tune the parameters of the memory manager, while instance-side methods are used together with the #current class-side method to take a look at statistics on the memory manager's state. @end table @menu * ObjectMemory class-accessing:: (class) * ObjectMemory class-builtins:: (class) * ObjectMemory class-initialization:: (class) * ObjectMemory class-saving the image:: (class) * ObjectMemory-accessing:: (instance) * ObjectMemory-builtins:: (instance) * ObjectMemory-derived information:: (instance) @end menu @node ObjectMemory class-accessing @subsection ObjectMemory class:@- accessing @table @b @meindex current @item current Return a snapshot of the VM's memory management statistics. @end table @node ObjectMemory class-builtins @subsection ObjectMemory class:@- builtins @table @b @meindex abort @item abort Quit the Smalltalk environment, dumping core. @meindex addressOf:@- @item addressOf:@- anObject Returns the address of the actual object that anObject references. Note that, with the exception of fixed objects this address is only valid until the next garbage collection; thus it's pretty risky to count on the address returned by this method for very long. @meindex addressOfOOP:@- @item addressOfOOP:@- anObject Returns the address of the OOP (object table slot) for anObject. The address is an Integer and will not change over time (i.e. is immune from garbage collector action) except if the virtual machine is stopped and restarted. @meindex bigObjectThreshold @item bigObjectThreshold Answer the smallest size for objects that are allocated outside the main heap in the hope of providing more locality of reference between small objects. @meindex bigObjectThreshold:@- @item bigObjectThreshold:@- bytes Set the smallest size for objects that are allocated outside the main heap in the hope of providing more locality of reference between small objects. bytes must be a positive SmallInteger. @meindex compact @item compact Force a full garbage collection, including compaction of oldspace @meindex finishIncrementalGC @item finishIncrementalGC Do a step in the incremental garbage collection. @meindex gcMessage @item gcMessage Answer whether messages indicating that garbage collection is taking place are printed on stdout @meindex gcMessage:@- @item gcMessage:@- aBoolean Set whether messages indicating that garbage collection is taking place are printed on stdout @meindex globalGarbageCollect @item globalGarbageCollect Force a full garbage collection @meindex growThresholdPercent @item growThresholdPercent Answer the percentage of the amount of memory used by the system grows which has to be full for the system to allocate more memory @meindex growThresholdPercent:@- @item growThresholdPercent:@- growPercent Set the percentage of the amount of memory used by the system grows which has to be full for the system to allocate more memory @meindex growTo:@- @item growTo:@- numBytes Grow the amount of memory used by the system grows to numBytes. @meindex incrementalGCStep @item incrementalGCStep Do a step in the incremental garbage collection. @meindex quit @item quit Quit the Smalltalk environment. Whether files are closed and other similar cleanup occurs depends on the platform @meindex quit:@- @item quit:@- exitStatus Quit the Smalltalk environment, passing the exitStatus integer to the OS. Files are closed and other similar cleanups occur. @meindex scavenge @item scavenge Force a minor garbage collection @meindex smoothingFactor @item smoothingFactor Answer the factor (between 0 and 1) used to smooth the statistics provided by the virtual machine about memory handling. 0 disables updating the averages, 1 disables the smoothing (the statistics return the last value). @meindex smoothingFactor:@- @item smoothingFactor:@- rate Set the factor (between 0 and 1) used to smooth the statistics provided by the virtual machine about memory handling. 0 disables updating the averages, 1 disables the smoothing (the statistics return the last value). @meindex spaceGrowRate @item spaceGrowRate Answer the rate with which the amount of memory used by the system grows @meindex spaceGrowRate:@- @item spaceGrowRate:@- rate Set the rate with which the amount of memory used by the system grows @end table @node ObjectMemory class-initialization @subsection ObjectMemory class:@- initialization @table @b @meindex changed:@- @item changed:@- aSymbol Not commented. @meindex initialize @item initialize Initialize the globals @end table @node ObjectMemory class-saving the image @subsection ObjectMemory class:@- saving the image @table @b @meindex snapshot @item snapshot Save a snapshot on the image file that was loaded on startup. @meindex snapshot:@- @item snapshot:@- aString Save an image on the aString file @end table @node ObjectMemory-accessing @subsection ObjectMemory:@- accessing @table @b @meindex allocFailures @item allocFailures Answer the number of times that the old-space allocator found no block that was at least as big as requested, and had to ask the operating system for more memory. @meindex allocMatches @item allocMatches Answer the number of times that the old-space allocator found a block that was exactly as big as requested. @meindex allocProbes @item allocProbes Answer the number of free blocks that the old-space allocator had to examine so far to allocate all the objects that are in old-space @meindex allocSplits @item allocSplits Answer the number of times that the old-space allocator could not find a block that was exactly as big as requested, and had to split a larger free block in two parts. @meindex bytesPerOOP @item bytesPerOOP Answer the number of bytes that is taken by an ordinary object pointer (in practice, a field such as a named instance variable). @meindex bytesPerOTE @item bytesPerOTE Answer the number of bytes that is taken by an object table entry (in practice, the overhead incurred by every object in the system, with the sole exception of SmallIntegers). @meindex edenSize @item edenSize Answer the number of bytes in the `eden' area of the young generation (in practice, the number of allocated bytes between two scavenges). @meindex edenUsedBytes @item edenUsedBytes Answer the number of bytes that are currently filled in the `eden' area of the young generation. @meindex fixedSpaceSize @item fixedSpaceSize Answer the number of bytes in the special heap devoted to objects that the garbage collector cannot move around in memory. @meindex fixedSpaceUsedBytes @item fixedSpaceUsedBytes Answer the number of bytes that are currently filled in the special heap devoted to objects that the garbage collector cannot move around in memory. @meindex numCompactions @item numCompactions Answer the number of oldspace compactions that happened since the VM was started. @meindex numFixedOOPs @item numFixedOOPs Answer the number of objects that the garbage collector cannot move around in memory. @meindex numFreeOTEs @item numFreeOTEs Answer the number of entries that are currently free in the object table. @meindex numGlobalGCs @item numGlobalGCs Answer the number of global garbage collections (collection of the entire heap) that happened since the VM was started. @meindex numGrowths @item numGrowths Answer the number of times that oldspace was grown since the VM was started. @meindex numOTEs @item numOTEs Answer the number of entries that are currently allocated for the object table. @meindex numOldOOPs @item numOldOOPs Answer the number of objects that reside in the old generation. @meindex numScavenges @item numScavenges Answer the number of scavenges (fast collections of the young generation) that happened since the VM was started. @meindex numWeakOOPs @item numWeakOOPs Answer the number of weak objects that the garbage collector is currently tracking. @meindex oldSpaceSize @item oldSpaceSize Answer the number of bytes in the old generation. @meindex oldSpaceUsedBytes @item oldSpaceUsedBytes Answer the number of bytes that are currently filled in the old generation. @meindex reclaimedBytesPerGlobalGC @item reclaimedBytesPerGlobalGC Answer the average number of bytes that are found to be garbage during a global garbage collections. @meindex reclaimedBytesPerScavenge @item reclaimedBytesPerScavenge Answer the average number of bytes that are found to be garbage during a scavenge. @meindex reclaimedPercentPerScavenge @item reclaimedPercentPerScavenge Answer the average percentage of allocated bytes that are found to be garbage during a scavenge. If this number falls below 60-70 you should definitely increment the size of the eden, because you risk that scavenging is eating a considerable fraction of your execution time; do the measurement on a restarted image, so that the extra tenuring incurred when creating long-lived objects such as classes or methods is not considered. @meindex survSpaceSize @item survSpaceSize Answer the number of bytes in the `survivor' area of the young generation (the area to which young objects are relocated during scavenges). @meindex survSpaceUsedBytes @item survSpaceUsedBytes Answer the number of bytes that are currently filled in the `survivor' area of the young generation. @meindex tenuredBytesPerScavenge @item tenuredBytesPerScavenge Answer the average number of bytes that are promoted to oldspace during a scavenge. @meindex timeBetweenGlobalGCs @item timeBetweenGlobalGCs Answer the average number of milliseconds between two global garbage collections. @meindex timeBetweenGrowths @item timeBetweenGrowths Answer the average number of milliseconds between decisions to grow the heap. @meindex timeBetweenScavenges @item timeBetweenScavenges Answer the average number of milliseconds between two scavenges (fast collections of the young generation). @meindex timeToCollect @item timeToCollect Answer the average number of milliseconds that a global garbage collection takes. @meindex timeToCompact @item timeToCompact Answer the average number of milliseconds that compacting the heap takes. This the same time that is taken by growing the heap. @meindex timeToScavenge @item timeToScavenge Answer the average number of milliseconds that a scavenge takes (fast collections of the young generation). @end table @node ObjectMemory-builtins @subsection ObjectMemory:@- builtins @table @b @meindex update @item update Update the values in the object to the current state of the VM. @end table @node ObjectMemory-derived information @subsection ObjectMemory:@- derived information @table @b @meindex scavengesBeforeTenuring @item scavengesBeforeTenuring Answer the number of scavenges that an object must on average survive before being promoted to oldspace; this is however only an estimate because objects that are reachable from oldspace have a higher probability to be tenured soon, while objects that are only reachable from thisContext have a lower probability to be tenured. Anyway, if this number falls below 2-3 you should definitely increment the size of eden and/or of survivor space, because you are tenuring too often and relying too much on global garbage collection to keep your heap clean; do the measurement on a restarted image, so that the extra tenuring incurred when creating long-lived objects such as classes or methods is not considered. @end table @node OrderedCollection @section OrderedCollection @clindex OrderedCollection @table @b @item Defined in namespace Smalltalk @itemx Superclass: SequenceableCollection @itemx Category: Collections-Sequenceable My instances represent ordered collections of arbitrary typed objects which are not directly accessible by an index. They can be accessed indirectly through an index, and can be manipulated by adding to the end or based on content (such as add:@-after:@-) @end table @menu * OrderedCollection class-instance creation:: (class) * OrderedCollection-accessing:: (instance) * OrderedCollection-adding:: (instance) * OrderedCollection-built ins:: (instance) * OrderedCollection-enumerating:: (instance) * OrderedCollection-removing:: (instance) @end menu @node OrderedCollection class-instance creation @subsection OrderedCollection class:@- instance creation @table @b @meindex new @item new Answer an OrderedCollection of default size @meindex new:@- @item new:@- anInteger Answer an OrderedCollection of size anInteger @end table @node OrderedCollection-accessing @subsection OrderedCollection:@- accessing @table @b @meindex at:@- @item at:@- anIndex Answer the anIndex-th item of the receiver @meindex at:@-put:@- @item at:@- anIndex put:@- anObject Store anObject at the anIndex-th item of the receiver, answer anObject @meindex first @item first Answer the first item of the receiver @meindex last @item last Answer the last item of the receiver @meindex size @item size Return the number of objects in the receiver @end table @node OrderedCollection-adding @subsection OrderedCollection:@- adding @table @b @meindex add:@- @item add:@- anObject Add anObject in the receiver, answer it @meindex add:@-after:@- @item add:@- newObject after:@- oldObject Add newObject in the receiver just after oldObject, answer it. Fail if oldObject can't be found @meindex add:@-afterIndex:@- @item add:@- newObject afterIndex:@- i Add newObject in the receiver just after the i-th, answer it. Fail if i < 0 or i > self size @meindex add:@-before:@- @item add:@- newObject before:@- oldObject Add newObject in the receiver just before oldObject, answer it. Fail if oldObject can't be found @meindex add:@-beforeIndex:@- @item add:@- newObject beforeIndex:@- i Add newObject in the receiver just before the i-th, answer it. Fail if i < 1 or i > self size + 1 @meindex addAll:@- @item addAll:@- aCollection Add every item of aCollection to the receiver, answer it @meindex addAll:@-after:@- @item addAll:@- newCollection after:@- oldObject Add every item of newCollection to the receiver just after oldObject, answer it. Fail if oldObject is not found @meindex addAll:@-afterIndex:@- @item addAll:@- newCollection afterIndex:@- i Add every item of newCollection to the receiver just after the i-th, answer it. Fail if i < 0 or i > self size @meindex addAll:@-before:@- @item addAll:@- newCollection before:@- oldObject Add every item of newCollection to the receiver just before oldObject, answer it. Fail if oldObject is not found @meindex addAll:@-beforeIndex:@- @item addAll:@- newCollection beforeIndex:@- i Add every item of newCollection to the receiver just before the i-th, answer it. Fail if i < 1 or i > self size + 1 @meindex addAllFirst:@- @item addAllFirst:@- aCollection Add every item of newCollection to the receiver right at the start of the receiver. Answer aCollection @meindex addAllLast:@- @item addAllLast:@- aCollection Add every item of newCollection to the receiver right at the end of the receiver. Answer aCollection @meindex addFirst:@- @item addFirst:@- newObject Add newObject to the receiver right at the start of the receiver. Answer newObject @meindex addLast:@- @item addLast:@- newObject Add newObject to the receiver right at the end of the receiver. Answer newObject @end table @node OrderedCollection-built ins @subsection OrderedCollection:@- built ins @table @b @meindex primReplaceFrom:@-to:@-with:@-startingAt:@- @item primReplaceFrom:@- start to:@- stop with:@- byteArray startingAt:@- replaceStart Replace the characters from start to stop with new characters whose ASCII codes are contained in byteArray, starting at the replaceStart location of byteArray @end table @node OrderedCollection-enumerating @subsection OrderedCollection:@- enumerating @table @b @meindex do:@- @item do:@- aBlock Evaluate aBlock for all the elements in the collection @end table @node OrderedCollection-removing @subsection OrderedCollection:@- removing @table @b @meindex identityRemove:@- @item identityRemove:@- oldObject Remove oldObject from the receiver. If absent, fail, else answer oldObject. @meindex identityRemove:@-ifAbsent:@- @item identityRemove:@- anObject ifAbsent:@- aBlock Remove anObject from the receiver. If it can't be found, answer the result of evaluating aBlock @meindex remove:@-ifAbsent:@- @item remove:@- anObject ifAbsent:@- aBlock Remove anObject from the receiver. If it can't be found, answer the result of evaluating aBlock @meindex removeAtIndex:@- @item removeAtIndex:@- anIndex Remove the object at index anIndex from the receiver. Fail if the index is out of bounds. @meindex removeFirst @item removeFirst Remove an object from the start of the receiver. Fail if the receiver is empty @meindex removeLast @item removeLast Remove an object from the end of the receiver. Fail if the receiver is empty @end table @node Package @section Package @clindex Package @table @b @item Defined in namespace Smalltalk @itemx Superclass: Kernel.PackageInfo @itemx Category: Language-Packaging I am not part of a standard Smalltalk system. I store internally the information on a Smalltalk package, and can output my description in XML. @end table @menu * Package class-accessing:: (class) * Package class-instance creation:: (class) * Package-accessing:: (instance) * Package-still unclassified:: (instance) * Package-version parsing:: (instance) @end menu @node Package class-accessing @subsection Package class:@- accessing @table @b @meindex tags @item tags Not commented. @end table @node Package class-instance creation @subsection Package class:@- instance creation @table @b @meindex parse:@- @item parse:@- file Answer a package from the XML description in file. @end table @node Package-accessing @subsection Package:@- accessing @table @b @meindex addBuiltFile:@- @item addBuiltFile:@- aString Not commented. @meindex addCallout:@- @item addCallout:@- aString Not commented. @meindex addFeature:@- @item addFeature:@- aString Not commented. @meindex addFile:@- @item addFile:@- aString Not commented. @meindex addFileIn:@- @item addFileIn:@- aString Not commented. @meindex addLibrary:@- @item addLibrary:@- aString Not commented. @meindex addModule:@- @item addModule:@- aString Not commented. @meindex addPrerequisite:@- @item addPrerequisite:@- aString Not commented. @meindex addSunitScript:@- @item addSunitScript:@- aString Not commented. @meindex baseDirectories @item baseDirectories Answer `baseDirectories'. @meindex baseDirectories:@- @item baseDirectories:@- aCollection Check if it's possible to resolve the names in the package according to the base directories in baseDirectories, which depend on where the packages.xml is found:@- the three possible places are 1) the system kernel directory's parent directory, 2) the local kernel directory's parent directory, 3) the local image directory (in order of decreasing priority). For a packages.xml found in the system kernel directory's parent directory, all three directories are searched. For a packages.xml found in the local kernel directory's parent directory, only directories 2 and 3 are searched. For a packages.xml directory in the local image directory, instead, only directory 3 is searched. @meindex builtFiles @item builtFiles Answer a (modifiable) OrderedCollection of files that are part of the package but are not distributed. @meindex callouts @item callouts Answer a (modifiable) Set of call-outs that are required to load the package. Their presence is checked after the libraries and modules are loaded so that you can do a kind of versioning. @meindex directory @item directory Answer the base directory from which to load the package. @meindex features @item features Answer a (modifiable) Set of features provided by the package. @meindex fileIns @item fileIns Answer a (modifiable) OrderedCollections of files that are to be filed-in to load the package. This is usually a subset of `files' and `builtFiles'. @meindex files @item files Answer a (modifiable) OrderedCollection of files that are part of the package. @meindex fullPathOf:@- @item fullPathOf:@- fileName Try appending 'self directory' and fileName to each of the directory in baseDirectories, and return the path to the first tried filename that exists. Raise a PackageNotAvailable exception if no directory is found that contains the file. @meindex libraries @item libraries Answer a (modifiable) Set of shared library names that are required to load the package. @meindex modules @item modules Answer a (modifiable) Set of modules that are required to load the package. @meindex namespace @item namespace Answer the namespace in which the package is loaded. @meindex namespace:@- @item namespace:@- aString Set to aString the namespace in which the package is loaded. @meindex prerequisites @item prerequisites Answer a (modifiable) Set of prerequisites. @meindex primFileIn @item primFileIn Private - File in the given package without paying attention at dependencies and C callout availability @meindex relativeDirectory @item relativeDirectory Answer the directory, relative to the packages file, from which to load the package. @meindex relativeDirectory:@- @item relativeDirectory:@- dir Set the directory, relative to the packages file, from which to load the package, to dir. @meindex startScript @item startScript Answer the start script for the package. @meindex startScript:@- @item startScript:@- aString Set the start script for the package to aString. @meindex stopScript @item stopScript Answer the start script for the package. @meindex stopScript:@- @item stopScript:@- aString Set the stop script for the package to aString. @meindex sunitScripts @item sunitScripts Answer a (modifiable) OrderedCollection of SUnit scripts that compose the package's test suite. @meindex test @item test Answer the test sub-package. @meindex test:@- @item test:@- aPackage Set the test sub-package to be aPackage. @meindex url @item url Answer the URL at which the package repository can be found. @meindex url:@- @item url:@- aString Set to aString the URL at which the package repository can be found. @meindex version @item version Not commented. @meindex version:@- @item version:@- aVersion Not commented. @end table @node Package-still unclassified @subsection Package:@- still unclassified @table @b @meindex checkTagIfInPath:@- @item checkTagIfInPath:@- aString Not commented. @meindex dir:@-tag:@- @item dir:@- file tag:@- aDictionary Not commented. @meindex isInPath @item isInPath Not commented. @meindex parseAttributes:@- @item parseAttributes:@- aString Not commented. @meindex path @item path Not commented. @meindex path:@- @item path:@- aString Not commented. @end table @node Package-version parsing @subsection Package:@- version parsing @table @b @meindex parseVersion:@- @item parseVersion:@- aString Not commented. @end table @node PackageLoader @section PackageLoader @clindex PackageLoader @table @b @item Defined in namespace Smalltalk @itemx Superclass: Object @itemx Category: Language-Packaging I am not part of a standard Smalltalk system. I provide methods for retrieving package information from an XML file and to load packages into a Smalltalk image, correctly handling dependencies. @end table @menu * PackageLoader class-accessing:: (class) * PackageLoader class-loading:: (class) * PackageLoader class-testing:: (class) @end menu @node PackageLoader class-accessing @subsection PackageLoader class:@- accessing @table @b @meindex builtFilesFor:@- @slindex directoryFor:@- @item builtFilesFor:@- package Answer a Set of Strings containing the filenames of the given package's machine-generated files (relative to the directory answered by #directoryFor:@-) @meindex calloutsFor:@- @slindex directoryFor:@- @item calloutsFor:@- package Answer a Set of Strings containing the filenames of the given package's required callouts (relative to the directory answered by #directoryFor:@-) @meindex directoryFor:@- @item directoryFor:@- package Answer a Directory object to the given package's files @meindex featuresFor:@- @item featuresFor:@- package Answer a Set of Strings containing the features provided by the given package. @meindex fileInsFor:@- @slindex directoryFor:@- @item fileInsFor:@- package Answer a Set of Strings containing the filenames of the given package's file-ins (relative to the directory answered by #directoryFor:@-) @meindex filesFor:@- @slindex directoryFor:@- @item filesFor:@- package Answer a Set of Strings containing the filenames of the given package's files (relative to the directory answered by #directoryFor:@-) @meindex flush @item flush Set to reload the `packages.xml' file the next time it is needed. @meindex ignoreCallouts @item ignoreCallouts Answer whether unavailable C callouts must generate errors or not. @meindex ignoreCallouts:@- @item ignoreCallouts:@- aBoolean Set whether unavailable C callouts must generate errors or not. @meindex librariesFor:@- @slindex directoryFor:@- @item librariesFor:@- package Answer a Set of Strings containing the filenames of the given package's libraries (relative to the directory answered by #directoryFor:@-) @meindex modulesFor:@- @slindex directoryFor:@- @item modulesFor:@- package Answer a Set of Strings containing the filenames of the given package's modules (relative to the directory answered by #directoryFor:@-) @meindex packageAt:@- @item packageAt:@- package Answer a Package object for the given package @meindex packageAt:@-ifAbsent:@- @item packageAt:@- package ifAbsent:@- aBlock Answer a Package object for the given package @meindex prerequisitesFor:@- @item prerequisitesFor:@- package Answer a Set of Strings containing the prerequisites for the given package @meindex refresh @item refresh Reload the `packages.xml' file in the image and kernel directories. The three possible places are 1) the kernel directory's parent directory, 2) the `.st' subdirectory of the user's home directory, 3) the local image directory (in order of decreasing priority). For a packages.xml found in the kernel directory's parent directory, all three directories are searched. For a packages.xml found in the `.st' subdirectory, only directories 2 and 3 are searched. For a packages.xml directory in the local image directory, finally, only directory 3 is searched. @meindex sunitScriptFor:@- @item sunitScriptFor:@- package Answer a Strings containing a SUnit script that describes the package's test suite. @end table @node PackageLoader class-loading @subsection PackageLoader class:@- loading @table @b @meindex fileInPackage:@- @item fileInPackage:@- package File in the given package into GNU Smalltalk. @meindex fileInPackages:@- @item fileInPackages:@- packagesList File in all the packages in packagesList into GNU Smalltalk. @end table @node PackageLoader class-testing @subsection PackageLoader class:@- testing @table @b @meindex canLoad:@- @item canLoad:@- package Answer whether all the needed pre-requisites for package are available. @end table @node Permission @section Permission @clindex Permission @table @b @item Defined in namespace Smalltalk @itemx Superclass: Object @itemx Category: Language-Security I am the basic class that represents whether operations that could harm the system's security are allowed or denied. @end table @menu * Permission class-testing:: (class) * Permission-accessing:: (instance) * Permission-testing:: (instance) @end menu @node Permission class-testing @subsection Permission class:@- testing @table @b @meindex allowing:@-target:@-action:@- @item allowing:@- aSymbol target:@- aTarget action:@- action Not commented. @meindex allowing:@-target:@-actions:@- @item allowing:@- aSymbol target:@- aTarget actions:@- actionsArray Not commented. @meindex denying:@-target:@-action:@- @item denying:@- aSymbol target:@- aTarget action:@- action Not commented. @meindex denying:@-target:@-actions:@- @item denying:@- aSymbol target:@- aTarget actions:@- actionsArray Not commented. @meindex granting:@-target:@-action:@- @item granting:@- aSymbol target:@- aTarget action:@- action Not commented. @meindex granting:@-target:@-actions:@- @item granting:@- aSymbol target:@- aTarget actions:@- actionsArray Not commented. @meindex name:@-target:@-action:@- @item name:@- aSymbol target:@- aTarget action:@- action Not commented. @meindex name:@-target:@-actions:@- @item name:@- aSymbol target:@- aTarget actions:@- actionsArray Not commented. @end table @node Permission-accessing @subsection Permission:@- accessing @table @b @meindex action:@- @item action:@- anObject Not commented. @meindex actions @item actions Answer `actions'. @meindex actions:@- @item actions:@- anObject Not commented. @meindex allow @item allow Not commented. @meindex allowing @item allowing Not commented. @meindex deny @item deny Not commented. @meindex denying @item denying Not commented. @meindex isAllowing @item isAllowing Answer `positive'. @meindex name @item name Answer `name'. @meindex name:@- @item name:@- anObject Not commented. @meindex target @item target Answer `target'. @meindex target:@- @item target:@- anObject Not commented. @end table @node Permission-testing @subsection Permission:@- testing @table @b @meindex check:@-for:@- @item check:@- aPermission for:@- anObject Not commented. @meindex implies:@- @item implies:@- aPermission Not commented. @end table @node PluggableAdaptor @section PluggableAdaptor @clindex PluggableAdaptor @table @b @item Defined in namespace Smalltalk @itemx Superclass: ValueAdaptor @itemx Category: Language-Data types I mediate between complex get/set behavior and the #value/@-#value:@- protocol used by ValueAdaptors. The get/set behavior can be implemented by two blocks, or can be delegated to another object with messages such as #someProperty to get and #someProperty:@- to set. @end table @menu * PluggableAdaptor class-creating instances:: (class) * PluggableAdaptor-accessing:: (instance) @end menu @node PluggableAdaptor class-creating instances @subsection PluggableAdaptor class:@- creating instances @table @b @meindex getBlock:@-putBlock:@- @slindex value @slindex value:@- @item getBlock:@- getBlock putBlock:@- putBlock Answer a PluggableAdaptor using the given blocks to implement #value and #value:@- @meindex on:@-aspect:@- @slindex value @slindex value:@- @item on:@- anObject aspect:@- aSymbol Answer a PluggableAdaptor using anObject's aSymbol message to implement #value, and anObject's aSymbol:@- message (aSymbol followed by a colon) to implement #value:@- @meindex on:@-getSelector:@-putSelector:@- @slindex value @slindex value:@- @item on:@- anObject getSelector:@- getSelector putSelector:@- putSelector Answer a PluggableAdaptor using anObject's getSelector message to implement #value, and anObject's putSelector message to implement #value:@- @meindex on:@-index:@- @slindex at:@- @slindex at:@-put:@- @slindex value @slindex value:@- @slindex at:@- @slindex at:@-put:@- @item on:@- anObject index:@- anIndex Answer a PluggableAdaptor using anObject's #at:@- and #at:@-put:@- message to implement #value and #value:@-; the first parameter of #at:@- and #at:@-put:@- is anIndex @meindex on:@-key:@- @slindex on:@-index:@- @item on:@- aDictionary key:@- aKey Same as #on:@-index:@-. Provided for clarity and completeness. @end table @node PluggableAdaptor-accessing @subsection PluggableAdaptor:@- accessing @table @b @meindex value @item value Get the value of the receiver. @meindex value:@- @item value:@- anObject Set the value of the receiver. @end table @node PluggableProxy @section PluggableProxy @clindex PluggableProxy @table @b @item Defined in namespace Smalltalk @itemx Superclass: AlternativeObjectProxy @itemx Category: Streams-Files I am a proxy that stores a different object and, upon load, sends #reconstructOriginalObject to that object (which can be a DirectedMessage, in which case the message is sent). The object to be stored is retrieved by sending #binaryRepresentationObject to the object. @end table @menu * PluggableProxy class-accessing:: (class) * PluggableProxy-saving and restoring:: (instance) @end menu @node PluggableProxy class-accessing @subsection PluggableProxy class:@- accessing @table @b @meindex on:@- @slindex binaryRepresentationObject @slindex preStore @slindex postStore @item on:@- anObject Answer a proxy to be used to save anObject. The proxy stores a different object obtained by sending to anObject the #binaryRepresentationObject message (embedded between #preStore and #postStore as usual). @end table @node PluggableProxy-saving and restoring @subsection PluggableProxy:@- saving and restoring @table @b @meindex object @slindex reconstructOriginalObject @slindex postLoad @item object Reconstruct the object stored in the proxy and answer it; the binaryRepresentationObject is sent the #reconstructOriginalObject message, and the resulting object is sent the #postLoad message. @end table @node Point @section Point @clindex Point @table @b @item Defined in namespace Smalltalk @itemx Superclass: Object @itemx Category: Language-Data types Beginning of a Point class for simple display manipulation. Has not been exhaustively tested but appears to work for the basic primitives and for the needs of the Rectangle class. @end table @menu * Point class-instance creation:: (class) * Point-accessing:: (instance) * Point-arithmetic:: (instance) * Point-comparing:: (instance) * Point-converting:: (instance) * Point-point functions:: (instance) * Point-printing:: (instance) * Point-storing:: (instance) * Point-truncation and round off:: (instance) @end menu @node Point class-instance creation @subsection Point class:@- instance creation @table @b @meindex new @item new Create a new point with both coordinates set to 0 @meindex x:@-y:@- @item x:@- xInteger y:@- yInteger Create a new point with the given coordinates @end table @node Point-accessing @subsection Point:@- accessing @table @b @meindex x @item x Answer the x coordinate @meindex x:@- @item x:@- aNumber Set the x coordinate to aNumber @meindex x:@-y:@- @item x:@- anXNumber y:@- aYNumber Set the x and y coordinate to anXNumber and aYNumber, respectively @meindex y @item y Answer the y coordinate @meindex y:@- @item y:@- aNumber Set the y coordinate to aNumber @end table @node Point-arithmetic @subsection Point:@- arithmetic @table @b @meindex * @item * scale Multiply the receiver by scale, which can be a Number or a Point @meindex + @item + delta Sum the receiver and delta, which can be a Number or a Point @meindex - @item - delta Subtract delta, which can be a Number or a Point, from the receiver @meindex / @item / scale Divide the receiver by scale, which can be a Number or a Point, with no loss of precision @meindex // @item // scale Divide the receiver by scale, which can be a Number or a Point, with truncation towards -infinity @meindex abs @item abs Answer a new point whose coordinates are the absolute values of the receiver's @end table @node Point-comparing @subsection Point:@- comparing @table @b @meindex < @item < aPoint Answer whether the receiver is higher and to the left of aPoint @meindex <= @item <= aPoint Answer whether aPoint is equal to the receiver, or the receiver is higher and to the left of aPoint @meindex = @item = aPoint Answer whether the receiver is equal to aPoint @meindex > @item > aPoint Answer whether the receiver is lower and to the right of aPoint @meindex >= @item >= aPoint Answer whether aPoint is equal to the receiver, or the receiver is lower and to the right of aPoint @meindex max:@- @item max:@- aPoint Answer self if it is lower and to the right of aPoint, aPoint otherwise @meindex min:@- @item min:@- aPoint Answer self if it is higher and to the left of aPoint, aPoint otherwise @end table @node Point-converting @subsection Point:@- converting @table @b @meindex asPoint @item asPoint Answer the receiver. @meindex asRectangle @item asRectangle Answer an empty rectangle whose origin is self @meindex corner:@- @item corner:@- aPoint Answer a Rectangle whose origin is the receiver and whose corner is aPoint @meindex extent:@- @item extent:@- aPoint Answer a Rectangle whose origin is the receiver and whose extent is aPoint @meindex hash @item hash Answer an hash value for the receiver @end table @node Point-point functions @subsection Point:@- point functions @table @b @meindex arcTan @item arcTan Answer the angle (measured counterclockwise) between the receiver and a ray starting in (0, 0) and moving towards (1, 0) - i.e. 3 o'clock @meindex dist:@- @item dist:@- aPoint Answer the distance between the receiver and aPoint @meindex dotProduct:@- @item dotProduct:@- aPoint Answer the dot product between the receiver and aPoint @meindex grid:@- @item grid:@- aPoint Answer a new point whose coordinates are rounded towards the nearest multiple of aPoint @meindex normal @item normal Rotate the Point 90degrees clockwise and get the unit vector @meindex transpose @item transpose Answer a new point whose coordinates are the receiver's coordinates exchanged (x becomes y, y becomes x) @meindex truncatedGrid:@- @item truncatedGrid:@- aPoint Answer a new point whose coordinates are rounded towards -infinity, to a multiple of grid (which must be a Point) @end table @node Point-printing @subsection Point:@- printing @table @b @meindex printOn:@- @item printOn:@- aStream Print a representation for the receiver on aStream @end table @node Point-storing @subsection Point:@- storing @table @b @meindex storeOn:@- @item storeOn:@- aStream Print Smalltalk code compiling to the receiver on aStream @end table @node Point-truncation and round off @subsection Point:@- truncation and round off @table @b @meindex rounded @item rounded Answer a new point whose coordinates are rounded to the nearest integer @meindex truncateTo:@- @item truncateTo:@- grid Answer a new point whose coordinates are rounded towards -infinity, to a multiple of grid (which must be a Number) @end table @node PositionableStream @section PositionableStream @clindex PositionableStream @table @b @item Defined in namespace Smalltalk @itemx Superclass: Stream @itemx Category: Streams-Collections My instances represent streams where explicit positioning is permitted. Thus, my streams act in a manner to normal disk files:@- you can read or write sequentially, but also position the file to a particular place whenever you choose. Generally, you'll want to use ReadStream, WriteStream or ReadWriteStream instead of me to create and use streams. @end table @menu * PositionableStream class-instance creation:: (class) * PositionableStream-accessing-reading:: (instance) * PositionableStream-class type methods:: (instance) * PositionableStream-compiling:: (instance) * PositionableStream-positioning:: (instance) * PositionableStream-still unclassified:: (instance) * PositionableStream-testing:: (instance) * PositionableStream-truncating:: (instance) @end menu @node PositionableStream class-instance creation @subsection PositionableStream class:@- instance creation @table @b @meindex on:@- @item on:@- aCollection Answer an instance of the receiver streaming on the whole contents of aCollection @meindex on:@-from:@-to:@- @item on:@- aCollection from:@- firstIndex to:@- lastIndex Answer an instance of the receiver streaming from the firstIndex-th item of aCollection to the lastIndex-th @end table @node PositionableStream-accessing-reading @subsection PositionableStream:@- accessing-reading @table @b @meindex close @item close Disassociate a stream from its backing store. @meindex contents @item contents Returns a collection of the same type that the stream accesses, up to and including the final element. @meindex copyFrom:@-to:@- @slindex position @item copyFrom:@- start to:@- end Answer the data on which the receiver is streaming, from the start-th item to the end-th. Note that this method is 0-based, unlike the one in Collection, because a Stream's #position method returns 0-based values. @meindex next @item next Answer the next item of the receiver. Returns nil when at end of stream. @meindex nextAvailable:@-into:@-startingAt:@- @item nextAvailable:@- anInteger into:@- aCollection startingAt:@- pos Place up to anInteger objects from the receiver into aCollection, starting from position pos in the collection and stopping if no more data is available. @meindex nextAvailable:@-putAllOn:@- @item nextAvailable:@- anInteger putAllOn:@- aStream Copy up to anInteger objects from the receiver into aStream, stopping if no more data is available. @meindex peek @item peek Returns the next element of the stream without moving the pointer. Returns nil when at end of stream. @meindex peekFor:@- @item peekFor:@- anObject Returns true and gobbles the next element from the stream of it is equal to anObject, returns false and doesn't gobble the next element if the next element is not equal to anObject. @meindex readStream @item readStream Answer a ReadStream on the same contents as the receiver @meindex reverseContents @item reverseContents Returns a collection of the same type that the stream accesses, up to and including the final element, but in reverse order. @meindex upTo:@- @item upTo:@- anObject Returns a collection of the same type that the stream accesses, up to but not including the object anObject. Returns the entire rest of the stream's contents if anObject is not present. @meindex upToEnd @item upToEnd Returns a collection of the same type that the stream accesses, containing the entire rest of the stream's contents. @end table @node PositionableStream-class type methods @subsection PositionableStream:@- class type methods @table @b @meindex isExternalStream @item isExternalStream We stream on a collection residing in the image, so answer false @meindex species @slindex upTo:@- @slindex select:@- @item species Return the type of the collections returned by #upTo:@- etc., which are the same kind as those returned by the collection with methods such as #select:@-. @end table @node PositionableStream-compiling @subsection PositionableStream:@- compiling @table @b @meindex name @item name Answer a string that represents what the receiver is streaming on @meindex segmentFrom:@-to:@- @slindex asString @item segmentFrom:@- startPos to:@- endPos Answer an object that, when sent #asString, will yield the result of sending `copyFrom:@- startPos to:@- endPos' to the receiver @end table @node PositionableStream-positioning @subsection PositionableStream:@- positioning @table @b @meindex basicPosition:@- @item basicPosition:@- anInteger Move the stream pointer to the anInteger-th object @meindex isPositionable @slindex skip:@- @item isPositionable Answer true if the stream supports moving backwards with #skip:@-. @meindex position @item position Answer the current value of the stream pointer @meindex position:@- @item position:@- anInteger Move the stream pointer to the anInteger-th object @meindex reset @item reset Move the stream back to its first element. For write-only streams, the stream is truncated there. @meindex setToEnd @item setToEnd Move the current position to the end of the stream. @meindex size @item size Answer the size of data on which we are streaming. @meindex skip:@- @item skip:@- anInteger Move the current position by anInteger places, either forwards or backwards. @end table @node PositionableStream-still unclassified @subsection PositionableStream:@- still unclassified @table @b @meindex nextPutAllOn:@- @item nextPutAllOn:@- aStream Write all the objects in the receiver to aStream. @end table @node PositionableStream-testing @subsection PositionableStream:@- testing @table @b @meindex atEnd @item atEnd Answer whether the objects in the stream have reached an end @meindex basicAtEnd @item basicAtEnd Answer whether the objects in the stream have reached an end. This method must NOT be overridden. @meindex isEmpty @item isEmpty Answer whether the stream has no objects @end table @node PositionableStream-truncating @subsection PositionableStream:@- truncating @table @b @meindex truncate @item truncate Truncate the receiver to the current position - only valid for writing streams @end table @node Process @section Process @clindex Process @table @b @item Defined in namespace Smalltalk @itemx Superclass: Link @itemx Category: Language-Processes I represent a unit of computation. My instances are independantly executable blocks that have a priority associated with them, and they can suspend themselves and resume themselves however they wish. @end table @menu * Process-accessing:: (instance) * Process-basic:: (instance) * Process-builtins:: (instance) * Process-debugging:: (instance) * Process-printing:: (instance) @end menu @node Process-accessing @subsection Process:@- accessing @table @b @meindex externalInterruptsEnabled @item externalInterruptsEnabled Answer whether the receiver is executed with interrupts enabled @meindex name @item name Answer the user-friendly name of the process. @meindex name:@- @item name:@- aString Give the name aString to the process @meindex priority @item priority Answer the receiver's priority @meindex priority:@- @item priority:@- anInteger Change the receiver's priority to anInteger @meindex queueInterrupt:@- @item queueInterrupt:@- aBlock Force the receiver to be interrupted and to evaluate aBlock as soon as it becomes the active process (this could mean NOW if the receiver is active). If the process is temporarily suspended or waiting on a semaphore, it is temporarily woken up so that the interrupt is processed as soon as the process priority allows to do. Answer the receiver. @meindex suspendedContext @item suspendedContext Answer the context that the process was executing at the time it was suspended. @meindex suspendedContext:@- @item suspendedContext:@- aContext Modify the context that the process was executing at the time it was suspended. @meindex valueWithoutInterrupts:@- @item valueWithoutInterrupts:@- aBlock Evaluate aBlock and delay all interrupts that are requested during its execution to after aBlock returns. @end table @node Process-basic @subsection Process:@- basic @table @b @meindex context @item context Return the execution context of the receiver. @meindex debugger @item debugger Return the object in charge of debugging the receiver. This always returns nil unless the DebugTools package is loaded. @meindex finalize @item finalize Terminate processes that are GCed while waiting on a dead semaphore. @meindex lowerPriority @slindex lowerPriority @slindex raisePriority @item lowerPriority Lower a bit the priority of the receiver. A #lowerPriority will cancel a previous #raisePriority, and vice versa. @meindex makeUntrusted:@- @item makeUntrusted:@- aBoolean Set whether the receiver is trusted or not. @meindex primTerminate @item primTerminate Terminate the receiver - This is nothing more than prohibiting to resume the process, then suspending it. @meindex raisePriority @slindex lowerPriority @slindex raisePriority @item raisePriority Raise a bit the priority of the receiver. A #lowerPriority will cancel a previous #raisePriority, and vice versa. @meindex singleStep @slindex singleStepWaitingOn:@- @item singleStep Execute a limited amount of code (usually a bytecode, or up to the next backward jump, or up to the next message send) of the receiver, which must in a ready-to-run state (neither executing nor terminating nor suspended), then restart running the current process. The current process should have higher priority than the receiver. For better performance, use the underlying primitive, Process>>@-#singleStepWaitingOn:@-. @meindex terminate @slindex ensure:@- @slindex ifCurtailed:@- @item terminate Terminate the receiver after having evaluated all the #ensure:@- and #ifCurtailed:@- blocks that are active in it. This is done by signalling a ProcessBeingTerminated notification. @meindex terminateOnQuit @slindex quit:@- @item terminateOnQuit Mark the receiver so that it is terminated when ObjectMemory class>>@-#quit:@- is sent. @end table @node Process-builtins @subsection Process:@- builtins @table @b @meindex resume @item resume Resume the receiver's execution @meindex singleStepWaitingOn:@- @item singleStepWaitingOn:@- aSemaphore Execute a limited amount of code (usually a bytecode, or up to the next backward jump, or up to the next message send) of the receiver, which must in a ready-to-run state (neither executing nor terminating nor suspended), then restart running the current process. aSemaphore is used as a means to synchronize the execution of the current process and the receiver and should have no signals on it. The current process should have higher priority than the receiver. @meindex suspend @item suspend Do nothing if we're already suspended. Note that the blue book made suspend a primitive - but the real primitive is yielding control to another process. Suspending is nothing more than taking ourselves out of every scheduling list and THEN yielding control to another process @meindex yield @item yield Yield control from the receiver to other processes @end table @node Process-debugging @subsection Process:@- debugging @table @b @meindex detach @item detach Do nothing, instances of Process are already detached. @end table @node Process-printing @subsection Process:@- printing @table @b @meindex printOn:@- @item printOn:@- aStream Print a representation of the receiver on aStream @end table @node ProcessEnvironment @section ProcessEnvironment @clindex ProcessEnvironment @table @b @item Defined in namespace Smalltalk @itemx Superclass: Object @itemx Category: Language-Processes I represent a proxy for thread-local variables defined for Smalltalk processes. Associations requested to me retrieve the thread-local value for the current process. For now, I don't provide the full protocol of a Dictionary; in particular the iteration protocol is absent. @end table @menu * ProcessEnvironment class-disabled:: (class) * ProcessEnvironment class-singleton:: (class) * ProcessEnvironment-accessing:: (instance) * ProcessEnvironment-dictionary removing:: (instance) * ProcessEnvironment-dictionary testing:: (instance) @end menu @node ProcessEnvironment class-disabled @subsection ProcessEnvironment class:@- disabled @table @b @meindex new @item new This method should not be called for instances of this class. @end table @node ProcessEnvironment class-singleton @subsection ProcessEnvironment class:@- singleton @table @b @meindex uniqueInstance @item uniqueInstance Return the singleton instance of ProcessEnvironment. @end table @node ProcessEnvironment-accessing @subsection ProcessEnvironment:@- accessing @table @b @meindex add:@- @item add:@- newObject Add the newObject association to the receiver @meindex associationAt:@- @item associationAt:@- key Answer the value associated to the given key, or the result of evaluating aBlock if the key is not found @meindex associationAt:@-ifAbsent:@- @item associationAt:@- key ifAbsent:@- aBlock Answer the value associated to the given key, or the result of evaluating aBlock if the key is not found @meindex at:@- @item at:@- key Answer the value associated to the given key. Return nil if the key is not found @meindex at:@-ifAbsent:@- @item at:@- key ifAbsent:@- aBlock Answer the value associated to the given key, or the result of evaluating aBlock if the key is not found @meindex at:@-ifAbsentPut:@- @item at:@- key ifAbsentPut:@- aBlock Answer the value associated to the given key, setting it to the result of evaluating aBlock if the key is not found. @meindex at:@-ifPresent:@- @item at:@- key ifPresent:@- aBlock Answer the value associated to the given key, or the result of evaluating aBlock if the key is not found @meindex at:@-put:@- @item at:@- key put:@- value Store value as associated to the given key @meindex keys @item keys Answer a kind of Set containing the keys of the receiver @end table @node ProcessEnvironment-dictionary removing @subsection ProcessEnvironment:@- dictionary removing @table @b @meindex remove:@- @item remove:@- anAssociation Remove anAssociation's key from the dictionary @meindex remove:@-ifAbsent:@- @item remove:@- anAssociation ifAbsent:@- aBlock Remove anAssociation's key from the dictionary @meindex removeAllKeys:@- @item removeAllKeys:@- keys Remove all the keys in keys, without raising any errors @meindex removeAllKeys:@-ifAbsent:@- @item removeAllKeys:@- keys ifAbsent:@- aBlock Remove all the keys in keys, passing the missing keys as parameters to aBlock as they're encountered @meindex removeKey:@- @item removeKey:@- aSymbol Remove the aSymbol key from the dictionary @meindex removeKey:@-ifAbsent:@- @item removeKey:@- aSymbol ifAbsent:@- aBlock Remove the aSymbol key from the dictionary @end table @node ProcessEnvironment-dictionary testing @subsection ProcessEnvironment:@- dictionary testing @table @b @meindex includesKey:@- @item includesKey:@- key Answer whether the receiver contains the given key @end table @node ProcessorScheduler @section ProcessorScheduler @clindex ProcessorScheduler @table @b @item Defined in namespace Smalltalk @itemx Superclass: Object @itemx Category: Language-Processes I provide methods that control the execution of processes. @end table @menu * ProcessorScheduler class-instance creation:: (class) * ProcessorScheduler-basic:: (instance) * ProcessorScheduler-built ins:: (instance) * ProcessorScheduler-idle tasks:: (instance) * ProcessorScheduler-printing:: (instance) * ProcessorScheduler-priorities:: (instance) * ProcessorScheduler-storing:: (instance) * ProcessorScheduler-timed invocation:: (instance) @end menu @node ProcessorScheduler class-instance creation @subsection ProcessorScheduler class:@- instance creation @table @b @meindex new @item new Error---new instances of ProcessorScheduler should not be created. @end table @node ProcessorScheduler-basic @subsection ProcessorScheduler:@- basic @table @b @meindex activeDebugger @item activeDebugger Answer the active process' debugger @meindex activePriority @item activePriority Answer the active process' priority @meindex activeProcess @item activeProcess Answer the active process @meindex processEnvironment @slindex associationAt:@- @item processEnvironment Answer another singleton object hosting thread-local variables for the Smalltalk processes. This acts like a normal Dictionary with a couple of differences:@- a) using #associationAt:@- will return special associations that retrieve a thread-local value; b) requesting missing keys will return nil, and removing them will be a nop. @meindex processesAt:@- @item processesAt:@- aPriority Answer a linked list of processes at the given priority @meindex terminateActive @item terminateActive Terminate the active process @meindex timeSlice @item timeSlice Answer the timeslice that is assigned to each Process before it is automatically preempted by the system (in milliseconds). An answer of zero means that preemptive multitasking is disabled. Note that the system by default is compiled without preemptive multitasking, and that even if it is enabled it will work only under BSD derivatives (or, in general, systems that support ITIMER_VIRTUAL). @meindex timeSlice:@- @item timeSlice:@- milliSeconds Set the timeslice that is assigned to each Process before it is automatically preempted by the system. Setting this to zero disables preemptive multitasking. Note that the system by default is compiled with preemptive multitasking disabled, and that even if it is enabled it will surely work only under BSD derivatives (or, in general, systems that support ITIMER_VIRTUAL). @meindex yield @item yield Let the active process yield control to other processes @end table @node ProcessorScheduler-built ins @subsection ProcessorScheduler:@- built ins @table @b @meindex disableInterrupts @slindex disableInterrupts @slindex enableInterrupts @item disableInterrupts Disable interrupts caused by external events while the current process is executing. Note that interrupts are disabled on a per-process basis, and that calling #disableInterrupts twice requires calling #enableInterrupts twice as well to re-enable interrupts. @meindex enableInterrupts @item enableInterrupts Re-enable interrupts caused by external events while the current process is executing. By default, interrupts are enabled. @end table @node ProcessorScheduler-idle tasks @subsection ProcessorScheduler:@- idle tasks @table @b @meindex idle @item idle Private - Call the next idle task. Return whether GNU Smalltalk should pause until the next OS signal. @meindex idleAdd:@- @item idleAdd:@- aBlock Register aBlock to be executed when things are idle @meindex initialize @item initialize Private - Start the finalization process. @meindex pause:@- @item pause:@- aBoolean Private - Pause for some time if aBoolean is false, or until a signal if it is true. @meindex startFinalizers @item startFinalizers Private - Fire a low-priority process to finalize the objects @meindex update:@- @item update:@- aSymbol If we left some work behind when the image was saved, do it now. @end table @node ProcessorScheduler-printing @subsection ProcessorScheduler:@- printing @table @b @meindex printOn:@- @item printOn:@- aStream Store onto aStream a printed representation of the receiver @end table @node ProcessorScheduler-priorities @subsection ProcessorScheduler:@- priorities @table @b @meindex highIOPriority @item highIOPriority Answer the priority for system high-priority I/O processes, such as a process handling input from a network. @meindex highestPriority @item highestPriority Answer the highest valid priority @meindex idlePriority @item idlePriority Answer the priority of idle processes. @meindex lowIOPriority @item lowIOPriority Answer the priority for system low-priority I/O processes. Examples are the process handling input from the user (keyboard, pointing device, etc.) and the process distributing input from a network. @meindex lowestPriority @item lowestPriority Answer the lowest valid priority @meindex priorityName:@- @item priorityName:@- priority Private - Answer a name for the given process priority @meindex systemBackgroundPriority @item systemBackgroundPriority Answer the priority for system background-priority processes. An incremental garbage collector could run at this level but now it runs at idlePriority instead. @meindex timingPriority @item timingPriority Answer the priority for system real-time processes. @meindex unpreemptedPriority @slindex valueWithoutPreemption @item unpreemptedPriority Answer the highest priority avilable in the system; never create a process with this priority, instead use BlockClosure>>@-#valueWithoutPreemption. @meindex userBackgroundPriority @item userBackgroundPriority Answer the priority for user background-priority processes @meindex userInterruptPriority @item userInterruptPriority Answer the priority for user interrupt-priority processes. Processes run at this level will preempt the window scheduler and should, therefore, not consume the processor forever. @meindex userSchedulingPriority @item userSchedulingPriority Answer the priority for user standard-priority processes @end table @node ProcessorScheduler-storing @subsection ProcessorScheduler:@- storing @table @b @meindex storeOn:@- @item storeOn:@- aStream Store onto aStream a Smalltalk expression which evaluates to the receiver @end table @node ProcessorScheduler-timed invocation @subsection ProcessorScheduler:@- timed invocation @table @b @meindex isTimeoutProgrammed @slindex signal:@-atMilliseconds:@- @item isTimeoutProgrammed Private - Answer whether there is a pending call to #signal:@-atMilliseconds:@- @meindex signal:@-atNanosecondClockValue:@- @item signal:@- aSemaphore atNanosecondClockValue:@- ns Private - signal 'aSemaphore' when the nanosecond clock reaches 'ns' nanoseconds. @meindex signal:@-onInterrupt:@- @item signal:@- aSemaphore onInterrupt:@- anIntegerSignalNumber Signal 'aSemaphore' when the given C signal occurs. @end table @node ProcessVariable @section ProcessVariable @clindex ProcessVariable @table @b @item Defined in namespace Smalltalk @itemx Superclass: LookupKey @itemx Category: Language-Processes I represent a proxy for a thread-local variable defined for a process. Requesting the value will return the thread-local setting for the current process. @end table @menu * ProcessVariable class-accessing:: (class) * ProcessVariable-accessing:: (instance) @end menu @node ProcessVariable class-accessing @subsection ProcessVariable class:@- accessing @table @b @meindex key:@- @item key:@- anObject Return a new ProcessVariable with the given key. Not that the key need not be a symbol or string, for example you could use an array #(@-#@{class name@} 'name'). Setting the variable's value will automatically create it in the current process, while removal must be done by hand through the ProcessEnvironment singleton object. @meindex new @item new Return a new ProcessVariable with a new anonymous but unique key. It is suggested to use a descriptive name instead to ease debugging. Setting the variable's value will automatically create it in the current process, while removal must be done by hand through the ProcessEnvironment singleton object. @end table @node ProcessVariable-accessing @subsection ProcessVariable:@- accessing @table @b @meindex environment @item environment Return the environment in which this ProcessVariable lives. This is the singleton instance of ProcessEnvironment for all variables. @meindex use:@-during:@- @item use:@- anObject during:@- aBlock Set the value of this variable to anObject during the execution of aBlock, then restore it. @meindex value @item value Return the value of this variable in the current process. @meindex value:@- @item value:@- anObject Set the value of the current process's copy of the variable to be anObject. @meindex valueIfAbsent:@- @item valueIfAbsent:@- aBlock Return the value of this variable in the current process. @end table @node Promise @section Promise @clindex Promise @table @b @item Defined in namespace Smalltalk @itemx Superclass: ValueHolder @itemx Category: Language-Data types I store my value in a variable, and know whether I have been initialized or not. If you ask for my value and I have not been initialized, I suspend the process until a value has been assigned. @end table @menu * Promise class-creating instances:: (class) * Promise-accessing:: (instance) * Promise-initializing:: (instance) * Promise-printing:: (instance) * Promise-still unclassified:: (instance) @end menu @node Promise class-creating instances @subsection Promise class:@- creating instances @table @b @meindex for:@- @slindex value @item for:@- aBlock Invoke aBlock at an indeterminate time in an indeterminate process before answering its value from #value sent to my result. @meindex null @item null This method should not be called for instances of this class. @end table @node Promise-accessing @subsection Promise:@- accessing @table @b @meindex hasError @slindex value @item hasError Answer whether calling #value will raise an exception. @meindex hasValue @slindex value @item hasValue Answer whether we already have a value (or calling #value will raise an error). @meindex value @item value Get the value of the receiver. @meindex value:@- @item value:@- anObject Set the value of the receiver. @end table @node Promise-initializing @subsection Promise:@- initializing @table @b @meindex initialize @item initialize Private - set the initial state of the receiver @end table @node Promise-printing @subsection Promise:@- printing @table @b @meindex printOn:@- @item printOn:@- aStream Print a representation of the receiver @end table @node Promise-still unclassified @subsection Promise:@- still unclassified @table @b @meindex errorValue:@- @slindex value @item errorValue:@- anException Private - Raise anException whenever #value is called. @end table @node Random @section Random @clindex Random @table @b @item Defined in namespace Smalltalk @itemx Superclass: Stream @itemx Category: Streams My instances are generator streams that produce random numbers, which are floating point values between 0 and 1. @end table @menu * Random class-instance creation:: (class) * Random class-shortcuts:: (class) * Random-basic:: (instance) * Random-testing:: (instance) @end menu @node Random class-instance creation @subsection Random class:@- instance creation @table @b @meindex new @item new Create a new random number generator whose seed is given by the current time on the millisecond clock @meindex seed:@- @item seed:@- aFloat Create a new random number generator whose seed is aFloat @end table @node Random class-shortcuts @subsection Random class:@- shortcuts @table @b @meindex between:@-and:@- @item between:@- low and:@- high Return a random integer between the given extrema @meindex next @item next Return a random number between 0 and 1 (excluded) @meindex source @item source Return a standard source of random numbers. @end table @node Random-basic @subsection Random:@- basic @table @b @meindex atEnd @item atEnd This stream never ends. Always answer false. @meindex between:@-and:@- @item between:@- low and:@- high Return a random integer between low and high. @meindex next @item next Return the next random number in the sequence. @meindex nextPut:@- @item nextPut:@- value This method should not be called for instances of this class. @end table @node Random-testing @subsection Random:@- testing @table @b @meindex chiSquare @item chiSquare Compute the chi-square of the random that this class generates. @meindex chiSquare:@-range:@- @item chiSquare:@- n range:@- r Return the chi-square deduced from calculating n random numbers in the 0..r range. @end table @node ReadStream @section ReadStream @clindex ReadStream @table @b @item Defined in namespace Smalltalk @itemx Superclass: PositionableStream @itemx Category: Streams-Collections I implement the set of read-only stream objects. You may read from my objects, but you may not write to them. @end table @menu * ReadStream class-instance creation:: (class) @end menu @node ReadStream class-instance creation @subsection ReadStream class:@- instance creation @table @b @meindex on:@- @item on:@- aCollection Answer a new stream working on aCollection from its start. @meindex on:@-from:@-to:@- @item on:@- aCollection from:@- firstIndex to:@- lastIndex Answer an instance of the receiver streaming from the firstIndex-th item of aCollection to the lastIndex-th @end table @node ReadWriteStream @section ReadWriteStream @clindex ReadWriteStream @table @b @item Defined in namespace Smalltalk @itemx Superclass: WriteStream @itemx Category: Streams-Collections I am the class of streams that may be read and written from simultaneously. In some sense, I am the best of both ReadStream and WriteStream. @end table @menu * ReadWriteStream class-instance creation:: (class) * ReadWriteStream-positioning:: (instance) @end menu @node ReadWriteStream class-instance creation @subsection ReadWriteStream class:@- instance creation @table @b @meindex on:@- @item on:@- aCollection Answer a new stream working on aCollection from its start. The stream starts at the front of aCollection. @meindex on:@-from:@-to:@- @item on:@- aCollection from:@- firstIndex to:@- lastIndex Answer an instance of the receiver streaming from the firstIndex-th item of aCollection to the lastIndex-th @meindex with:@- @item with:@- aCollection Answer a new instance of the receiver which streams from the end of aCollection. @end table @node ReadWriteStream-positioning @subsection ReadWriteStream:@- positioning @table @b @meindex contents @item contents Unlike WriteStreams, ReadWriteStreams return the whole contents of the underlying collection. @end table @node Rectangle @section Rectangle @clindex Rectangle @table @b @item Defined in namespace Smalltalk @itemx Superclass: Object @itemx Category: Language-Data types Beginning of the Rectangle class for simple display manipulation. Rectangles require the Point class to be available. An extension to the Point class is made here that since it requires Rectangles to be defined (see converting) @end table @menu * Rectangle class-instance creation:: (class) * Rectangle-accessing:: (instance) * Rectangle-copying:: (instance) * Rectangle-printing:: (instance) * Rectangle-rectangle functions:: (instance) * Rectangle-testing:: (instance) * Rectangle-transforming:: (instance) * Rectangle-truncation and round off:: (instance) @end menu @node Rectangle class-instance creation @subsection Rectangle class:@- instance creation @table @b @meindex left:@-right:@-top:@-bottom:@- @item left:@- leftNumber right:@- rightNumber top:@- topNumber bottom:@- bottomNumber Answer a rectangle with the given coordinates @meindex left:@-top:@-right:@-bottom:@- @item left:@- leftNumber top:@- topNumber right:@- rightNumber bottom:@- bottomNumber Answer a rectangle with the given coordinates @meindex new @item new Answer the (0 @@ 0 corner:@- 0 @@ 0) rectangle @meindex origin:@-corner:@- @item origin:@- originPoint corner:@- cornerPoint Answer a rectangle with the given corners @meindex origin:@-extent:@- @item origin:@- originPoint extent:@- extentPoint Answer a rectangle with the given origin and size @end table @node Rectangle-accessing @subsection Rectangle:@- accessing @table @b @meindex bottom @item bottom Answer the corner's y of the receiver @meindex bottom:@- @item bottom:@- aNumber Set the corner's y of the receiver @meindex bottomCenter @item bottomCenter Answer the center of the receiver's bottom side @meindex bottomLeft @item bottomLeft Answer the bottom-left corner of the receiver @meindex bottomLeft:@- @item bottomLeft:@- aPoint Answer the receiver with the bottom-left changed to aPoint @meindex bottomRight @item bottomRight Answer the bottom-right corner of the receiver @meindex bottomRight:@- @item bottomRight:@- aPoint Change the bottom-right corner of the receiver @meindex center @item center Answer the center of the receiver @meindex corner @item corner Answer the corner of the receiver @meindex corner:@- @item corner:@- aPoint Set the corner of the receiver @meindex extent @item extent Answer the extent of the receiver @meindex extent:@- @item extent:@- aPoint Change the size of the receiver, keeping the origin the same @meindex height @item height Answer the height of the receiver @meindex height:@- @item height:@- aNumber Set the height of the receiver @meindex left @item left Answer the x of the left edge of the receiver @meindex left:@- @item left:@- aValue Set the x of the left edge of the receiver @meindex left:@-top:@-right:@-bottom:@- @item left:@- l top:@- t right:@- r bottom:@- b Change all four the coordinates of the receiver's corners @meindex leftCenter @item leftCenter Answer the center of the receiver's left side @meindex origin @item origin Answer the top-left corner of the receiver @meindex origin:@- @item origin:@- aPoint Change the top-left corner of the receiver to aPoint @meindex origin:@-corner:@- @item origin:@- pnt1 corner:@- pnt2 Change both the origin (top-left corner) and the corner (bottom-right corner) of the receiver @meindex origin:@-extent:@- @item origin:@- pnt1 extent:@- pnt2 Change the top-left corner and the size of the receiver @meindex right @item right Answer the x of the bottom-right corner of the receiver @meindex right:@- @item right:@- aNumber Change the x of the bottom-right corner of the receiver @meindex rightCenter @item rightCenter Answer the center of the receiver's right side @meindex top @item top Answer the y of the receiver's top-left corner @meindex top:@- @item top:@- aValue Change the y of the receiver's top-left corner @meindex topCenter @item topCenter Answer the center of the receiver's top side @meindex topLeft @item topLeft Answer the receiver's top-left corner @meindex topLeft:@- @item topLeft:@- aPoint Change the receiver's top-left corner's coordinates to aPoint @meindex topRight @item topRight Answer the receiver's top-right corner @meindex topRight:@- @item topRight:@- aPoint Change the receiver's top-right corner to aPoint @meindex width @item width Answer the receiver's width @meindex width:@- @item width:@- aNumber Change the receiver's width to aNumber @end table @node Rectangle-copying @subsection Rectangle:@- copying @table @b @meindex copy @item copy Return a deep copy of the receiver for safety. @end table @node Rectangle-printing @subsection Rectangle:@- printing @table @b @meindex printOn:@- @item printOn:@- aStream Print a representation of the receiver on aStream @meindex storeOn:@- @item storeOn:@- aStream Store Smalltalk code compiling to the receiver on aStream @end table @node Rectangle-rectangle functions @subsection Rectangle:@- rectangle functions @table @b @meindex amountToTranslateWithin:@- @item amountToTranslateWithin:@- aRectangle Answer a Point so that if aRectangle is translated by that point, its origin lies within the receiver's. @meindex area @item area Answer the receiver's area. The area is the width times the height, so it is possible for it to be negative if the rectangle is not normalized. @meindex areasOutside:@- @item areasOutside:@- aRectangle Answer a collection of rectangles containing the parts of the receiver outside of aRectangle. For all points in the receiver, but outside aRectangle, exactly one rectangle in the collection will contain that point. @meindex expandBy:@- @item expandBy:@- delta Answer a new rectangle that is the receiver expanded by aValue:@- if aValue is a rectangle, calculate origin=origin-aValue origin, corner=corner+aValue corner; else calculate origin=origin-aValue, corner=corner+aValue. @meindex insetBy:@- @item insetBy:@- delta Answer a new rectangle that is the receiver inset by aValue:@- if aValue is a rectangle, calculate origin=origin+aValue origin, corner=corner-aValue corner; else calculate origin=origin+aValue, corner=corner-aValue. @meindex insetOriginBy:@-corner:@- @item insetOriginBy:@- originDelta corner:@- cornerDelta Answer a new rectangle that is the receiver inset so that origin=origin+originDelta, corner=corner-cornerDelta. The deltas can be points or numbers @meindex intersect:@- @item intersect:@- aRectangle Answers the rectangle (if any) created by the overlap of rectangles A and B. Answers nil if the rectangles do not overlap @meindex merge:@- @item merge:@- aRectangle Answer a new rectangle which is the smallest rectangle containing both the receiver and aRectangle. @meindex translatedToBeWithin:@- @item translatedToBeWithin:@- aRectangle Answer a copy of the receiver that does not extend beyond aRectangle. @end table @node Rectangle-testing @subsection Rectangle:@- testing @table @b @meindex = @item = aRectangle Answer whether the receiver is equal to aRectangle @meindex contains:@- @item contains:@- aRectangle Answer true if the receiver contains (see containsPoint:@-) both aRectangle's origin and aRectangle's corner @meindex containsPoint:@- @item containsPoint:@- aPoint Answer true if aPoint is equal to, or below and to the right of, the receiver's origin; and aPoint is above and to the left of the receiver's corner @meindex hash @item hash Answer an hash value for the receiver @meindex intersects:@- @item intersects:@- aRectangle Answer true if the receiver intersect aRectangle, i.e. if it contains (see containsPoint:@-) any of aRectangle corners or if aRectangle contains the receiver @end table @node Rectangle-transforming @subsection Rectangle:@- transforming @table @b @meindex moveBy:@- @item moveBy:@- aPoint Change the receiver so that the origin and corner are shifted by aPoint @meindex moveTo:@- @item moveTo:@- aPoint Change the receiver so that the origin moves to aPoint and the size remains unchanged @meindex scaleBy:@- @item scaleBy:@- scale Answer a copy of the receiver in which the origin and corner are multiplied by scale @meindex translateBy:@- @item translateBy:@- factor Answer a copy of the receiver in which the origin and corner are shifted by aPoint @end table @node Rectangle-truncation and round off @subsection Rectangle:@- truncation and round off @table @b @meindex rounded @item rounded Answer a copy of the receiver with the coordinates rounded to the nearest integers @end table @node RecursionLock @section RecursionLock @clindex RecursionLock @table @b @item Defined in namespace Smalltalk @itemx Superclass: Object @itemx Category: Language-Processes @end table @menu * RecursionLock class-instance creation:: (class) * RecursionLock-accessing:: (instance) * RecursionLock-mutual exclusion:: (instance) * RecursionLock-printing:: (instance) @end menu @node RecursionLock class-instance creation @subsection RecursionLock class:@- instance creation @table @b @meindex new @item new Answer a new semaphore @end table @node RecursionLock-accessing @subsection RecursionLock:@- accessing @table @b @meindex isOwnerProcess @item isOwnerProcess Answer whether the receiver is the owner of the lock. @meindex name @item name Answer a user-defined name for the lock. @meindex name:@- @item name:@- aString Set to aString the user-defined name for the lock. @meindex waitingProcesses @item waitingProcesses Answer the set of processes that are waiting on the semaphore. @meindex wouldBlock @slindex wait @item wouldBlock Answer whether sending #wait to the receiver would suspend the active process. @end table @node RecursionLock-mutual exclusion @subsection RecursionLock:@- mutual exclusion @table @b @meindex critical:@- @item critical:@- aBlock Wait for the receiver to be free, execute aBlock and signal the receiver again. Return the result of evaluating aBlock. @end table @node RecursionLock-printing @subsection RecursionLock:@- printing @table @b @meindex printOn:@- @item printOn:@- aStream Print a human-readable represention of the receiver on aStream. @end table @node Regex @section Regex @clindex Regex @table @b @item Defined in namespace Smalltalk @itemx Superclass: Object @itemx Category: Collections-Text A Regex is a read-only string for which the regular expression matcher can cache a compiled representation, thus speeding up matching. Regex objects are constructed automatically by methods that expect to match many times the same regular expression, but can also be constructed explicitly sending #asRegex to a String or Symbol. Creation of Regex objects inside a loop is of course slower than creating them outside the loop, but special care is taken so that the same Regex object is used whenever possible (when converting Strings to Regex, the cache is sought for an equivalent, already constructed Regex). @end table @menu * Regex class-instance creation:: (class) * Regex-basic:: (instance) * Regex-conversion:: (instance) * Regex-printing:: (instance) @end menu @node Regex class-instance creation @subsection Regex class:@- instance creation @table @b @meindex fromString:@- @item fromString:@- aString Like `aString asRegex'. @meindex new @item new Do not send this message. @end table @node Regex-basic @subsection Regex:@- basic @table @b @meindex at:@-put:@- @item at:@- anIndex put:@- anObject Fail. Regex objects are read-only. @meindex copy @item copy Answer the receiver; instances of Regex are identity objects because their only purpose is to ease caching, and we obtain better caching if we avoid copying Regex objects @end table @node Regex-conversion @subsection Regex:@- conversion @table @b @meindex asRegex @item asRegex Answer the receiver, which *is* a Regex! @meindex asString @item asString Answer the receiver, converted back to a String @meindex species @item species Answer `String'. @end table @node Regex-printing @subsection Regex:@- printing @table @b @meindex displayOn:@- @slindex printOn:@- @item displayOn:@- aStream Print a represention of the receiver on aStream. For most objects this is simply its #printOn:@- representation, but for strings and characters, superfluous dollars or extra pairs of quotes are stripped. @meindex displayString @slindex printString @item displayString Answer a String representing the receiver. For most objects this is simply its #printString, but for strings and characters, superfluous dollars or extra pair of quotes are stripped. @meindex printOn:@- @item printOn:@- aStream Print a represention of the receiver on aStream. @end table @node RegexResults @section RegexResults @clindex RegexResults @table @b @item Defined in namespace Smalltalk @itemx Superclass: Object @itemx Category: Collections-Text I hold the results of a regular expression match, and I can reconstruct which parts of the matched string were assigned to each subexpression. Methods such as #=~ return RegexResults objects, while others transform the string directly without passing the results object back to the caller. @end table @menu * RegexResults-accessing:: (instance) * RegexResults-testing:: (instance) @end menu @node RegexResults-accessing @subsection RegexResults:@- accessing @table @b @meindex asArray @item asArray If the regular expression was matched, return an Array with the subexpressions that were present in the regular expression. @meindex at:@- @item at:@- anIndex If the regular expression was matched, return the text of the anIndex-th subexpression in the successful match. @meindex from @item from If the regular expression was matched, return the index of the first character in the successful match. @meindex fromAt:@- @item fromAt:@- anIndex If the regular expression was matched, return the index of the first character of the anIndex-th subexpression in the successful match. @meindex intervalAt:@- @item intervalAt:@- anIndex If the regular expression was matched, return an Interval for the range of indices in the anIndex-th subexpression of the successful match. @meindex match @item match If the regular expression was matched, return the text of the successful match. @meindex matchInterval @item matchInterval If the regular expression was matched, return an Interval for the range of indices of the successful match. @meindex size @item size If the regular expression was matched, return the number of subexpressions that were present in the regular expression. @meindex subject @item subject If the regular expression was matched, return the text that was matched against it. @meindex to @item to If the regular expression was matched, return the index of the last character in the successful match. @meindex toAt:@- @item toAt:@- anIndex If the regular expression was matched, return the index of the last character of the anIndex-th subexpression in the successful match. @end table @node RegexResults-testing @subsection RegexResults:@- testing @table @b @meindex ifMatched:@- @item ifMatched:@- oneArgBlock If the regular expression was matched, pass the receiver to oneArgBlock and return its result. Otherwise, return nil. @meindex ifMatched:@-ifNotMatched:@- @item ifMatched:@- oneArgBlock ifNotMatched:@- zeroArgBlock If the regular expression was matched, evaluate oneArgBlock with the receiver as the argument. If it was not, evaluate zeroArgBlock. Answer the result of the block's evaluation. @meindex ifNotMatched:@- @item ifNotMatched:@- zeroArgBlock If the regular expression was matched, return the receiver. If it was not, evaluate zeroArgBlock and return its result. @meindex ifNotMatched:@-ifMatched:@- @item ifNotMatched:@- zeroArgBlock ifMatched:@- oneArgBlock If the regular expression was matched, evaluate oneArgBlock with the receiver as the argument. If it was not, evaluate zeroArgBlock. Answer the result of the block's evaluation. @meindex matched @item matched Answer whether the regular expression was matched @end table @node RootNamespace @section RootNamespace @clindex RootNamespace @table @b @item Defined in namespace Smalltalk @itemx Superclass: AbstractNamespace @itemx Category: Language-Implementation I am a special form of dictionary. Classes hold on an instance of me; it is called their `environment'. @end table @menu * RootNamespace class-instance creation:: (class) * RootNamespace-namespace hierarchy:: (instance) * RootNamespace-overrides for superspaces:: (instance) * RootNamespace-printing:: (instance) @end menu @node RootNamespace class-instance creation @subsection RootNamespace class:@- instance creation @table @b @meindex new:@- @item new:@- spaceName Create a new root namespace with the given name, and add to Smalltalk a key that references it. @end table @node RootNamespace-namespace hierarchy @subsection RootNamespace:@- namespace hierarchy @table @b @meindex siblings @item siblings Answer all the other root namespaces @meindex siblingsDo:@- @item siblingsDo:@- aBlock Evaluate aBlock once for each of the other root namespaces, passing the namespace as a parameter. @end table @node RootNamespace-overrides for superspaces @subsection RootNamespace:@- overrides for superspaces @table @b @meindex inheritedKeys @item inheritedKeys Answer a Set of all the keys in the receiver and its superspaces @meindex set:@-to:@-ifAbsent:@- @item set:@- key to:@- newValue ifAbsent:@- aBlock Assign newValue to the variable named as specified by `key'. This method won't define a new variable; instead if the key is not found it will search in superspaces and evaluate aBlock if it is not found. Answer newValue. @end table @node RootNamespace-printing @subsection RootNamespace:@- printing @table @b @meindex nameIn:@- @item nameIn:@- aNamespace Answer Smalltalk code compiling to the receiver when the current namespace is aNamespace @meindex printOn:@-in:@- @item printOn:@- aStream in:@- aNamespace Print on aStream some Smalltalk code compiling to the receiver when the current namespace is aNamespace @meindex storeOn:@- @item storeOn:@- aStream Store Smalltalk code compiling to the receiver @end table @node RunArray @section RunArray @clindex RunArray @table @b @item Defined in namespace Smalltalk @itemx Superclass: OrderedCollection @itemx Category: Collections-Sequenceable My instances are OrderedCollections that automatically apply Run Length Encoding compression to the things they store. Be careful when using me:@- I can provide great space savings, but my instances don't grant linear access time. RunArray's behavior currently is similar to that of OrderedCollection (you can add elements to RunArrays); maybe it should behave like an ArrayedCollection. @end table @menu * RunArray class-instance creation:: (class) * RunArray-accessing:: (instance) * RunArray-adding:: (instance) * RunArray-basic:: (instance) * RunArray-copying:: (instance) * RunArray-enumerating:: (instance) * RunArray-removing:: (instance) * RunArray-searching:: (instance) * RunArray-testing:: (instance) @end menu @node RunArray class-instance creation @subsection RunArray class:@- instance creation @table @b @meindex new @item new Answer an empty RunArray @meindex new:@- @item new:@- aSize Answer a RunArray with space for aSize runs @end table @node RunArray-accessing @subsection RunArray:@- accessing @table @b @meindex at:@- @item at:@- anIndex Answer the element at index anIndex @meindex at:@-put:@- @item at:@- anIndex put:@- anObject Replace the element at index anIndex with anObject and answer anObject @end table @node RunArray-adding @subsection RunArray:@- adding @table @b @meindex add:@-afterIndex:@- @item add:@- anObject afterIndex:@- anIndex Add anObject after the element at index anIndex @meindex addAll:@-afterIndex:@- @slindex do:@- @item addAll:@- aCollection afterIndex:@- anIndex Add all the elements of aCollection after the one at index anIndex. If aCollection is unordered, its elements could be added in an order which is not the #do:@- order @meindex addAllFirst:@- @slindex do:@- @item addAllFirst:@- aCollection Add all the elements of aCollection at the beginning of the receiver. If aCollection is unordered, its elements could be added in an order which is not the #do:@- order @meindex addAllLast:@- @slindex do:@- @item addAllLast:@- aCollection Add all the elements of aCollection at the end of the receiver. If aCollection is unordered, its elements could be added in an order which is not the #do:@- order @meindex addFirst:@- @item addFirst:@- anObject Add anObject at the beginning of the receiver. Watch out:@- this operation can cause serious performance pitfalls @meindex addLast:@- @item addLast:@- anObject Add anObject at the end of the receiver @end table @node RunArray-basic @subsection RunArray:@- basic @table @b @meindex first @item first Answer the first element in the receiver @meindex last @item last Answer the last element of the receiver @meindex size @item size Answer the number of elements in the receiver @end table @node RunArray-copying @subsection RunArray:@- copying @table @b @meindex deepCopy @slindex copy @item deepCopy Answer a copy of the receiver containing copies of the receiver's elements (@-#copy is used to obtain them) @meindex shallowCopy @item shallowCopy Answer a copy of the receiver. The elements are not copied @end table @node RunArray-enumerating @subsection RunArray:@- enumerating @table @b @meindex do:@- @item do:@- aBlock Enumerate all the objects in the receiver, passing each one to aBlock @meindex objectsAndRunLengthsDo:@- @item objectsAndRunLengthsDo:@- aBlock Enumerate all the runs in the receiver, passing to aBlock two parameters for every run:@- the first is the repeated object, the second is the number of copies @end table @node RunArray-removing @subsection RunArray:@- removing @table @b @meindex removeAtIndex:@- @item removeAtIndex:@- anIndex Remove the object at index anIndex from the receiver and answer the removed object @meindex removeFirst @item removeFirst Remove the first object from the receiver and answer the removed object @meindex removeLast @item removeLast Remove the last object from the receiver and answer the removed object @end table @node RunArray-searching @subsection RunArray:@- searching @table @b @meindex indexOf:@-startingAt:@-ifAbsent:@- @item indexOf:@- anObject startingAt:@- anIndex ifAbsent:@- aBlock Answer the index of the first copy of anObject in the receiver, starting the search at the element at index anIndex. If no equal object is found, answer the result of evaluating aBlock @end table @node RunArray-testing @subsection RunArray:@- testing @table @b @meindex = @item = anObject Answer true if the receiver is equal to anObject @meindex hash @item hash Answer an hash value for the receiver @end table @node ScaledDecimal @section ScaledDecimal @clindex ScaledDecimal @table @b @item Defined in namespace Smalltalk @itemx Superclass: Number @itemx Category: Language-Data types ScaledDecimal provides a numeric representation of fixed point decimal numbers able to accurately represent decimal fractions. It supports unbounded precision, with no limit to the number of digits before and after the decimal point. @end table @menu * ScaledDecimal class-instance creation:: (class) * ScaledDecimal-arithmetic:: (instance) * ScaledDecimal-coercion:: (instance) * ScaledDecimal-comparing:: (instance) * ScaledDecimal-constants:: (instance) * ScaledDecimal-printing:: (instance) * ScaledDecimal-storing:: (instance) @end menu @node ScaledDecimal class-instance creation @subsection ScaledDecimal class:@- instance creation @table @b @meindex newFromNumber:@-scale:@- @item newFromNumber:@- aNumber scale:@- scale Answer a new instance of ScaledDecimal, representing a decimal fraction with a decimal representation considered valid up to the scale-th digit. @end table @node ScaledDecimal-arithmetic @subsection ScaledDecimal:@- arithmetic @table @b @meindex * @item * aNumber Multiply two numbers and answer the result. @meindex + @item + aNumber Sum two numbers and answer the result. @meindex - @item - aNumber Subtract aNumber from the receiver and answer the result. @meindex / @item / aNumber Divide two numbers and answer the result. @meindex // @item // aNumber Answer the integer quotient after dividing the receiver by aNumber with truncation towards negative infinity. @meindex \\ @item \\ aNumber Answer the remainder after integer division the receiver by aNumber with truncation towards negative infinity. @end table @node ScaledDecimal-coercion @subsection ScaledDecimal:@- coercion @table @b @meindex asCNumber @item asCNumber Convert the receiver to a kind of number that is understood by the C call-out mechanism. @meindex asFloatD @item asFloatD Answer the receiver, converted to a FloatD @meindex asFloatE @item asFloatE Answer the receiver, converted to a FloatE @meindex asFloatQ @item asFloatQ Answer the receiver, converted to a FloatQ @meindex asFraction @item asFraction Answer the receiver, converted to a Fraction @meindex ceiling @item ceiling Answer the receiver, converted to an Integer and truncated towards +infinity. @meindex coerce:@- @item coerce:@- aNumber Answer aNumber, converted to a ScaledDecimal with the same scale as the receiver. @meindex fractionPart @item fractionPart Answer the fractional part of the receiver. @meindex generality @item generality Return the receiver's generality @meindex integerPart @item integerPart Answer the fractional part of the receiver. @meindex truncated @item truncated Answer the receiver, converted to an Integer and truncated towards -infinity. @end table @node ScaledDecimal-comparing @subsection ScaledDecimal:@- comparing @table @b @meindex < @item < aNumber Answer whether the receiver is less than arg. @meindex <= @item <= aNumber Answer whether the receiver is less than or equal to arg. @meindex = @item = arg Answer whether the receiver is equal to arg. @meindex > @item > aNumber Answer whether the receiver is greater than arg. @meindex >= @item >= aNumber Answer whether the receiver is greater than or equal to arg. @meindex hash @item hash Answer an hash value for the receiver. @meindex ~= @item ~= arg Answer whether the receiver is not equal arg. @end table @node ScaledDecimal-constants @subsection ScaledDecimal:@- constants @table @b @meindex one @item one Answer the receiver's representation of one. @meindex zero @item zero Answer the receiver's representation of zero. @end table @node ScaledDecimal-printing @subsection ScaledDecimal:@- printing @table @b @meindex displayOn:@- @slindex printString @item displayOn:@- aStream Print a representation of the receiver on aStream, intended to be directed to a user. In this particular case, the `scale' part of the #printString is not emitted. @meindex printOn:@- @item printOn:@- aStream Print a representation of the receiver on aStream. @end table @node ScaledDecimal-storing @subsection ScaledDecimal:@- storing @table @b @meindex isLiteralObject @item isLiteralObject Answer whether the receiver is expressible as a Smalltalk literal. @meindex storeLiteralOn:@- @item storeLiteralOn:@- aStream Store on aStream some Smalltalk code which compiles to the receiver @meindex storeOn:@- @item storeOn:@- aStream Print Smalltalk code that compiles to the receiver on aStream. @end table @node SecurityPolicy @section SecurityPolicy @clindex SecurityPolicy @table @b @item Defined in namespace Smalltalk @itemx Superclass: Object @itemx Category: Language-Security I am the class that represents which operations that could harm the system's security are allowed or denied to a particular class. If a class does not have a policy, it is allowed everything if it is trusted, and denied everything if it is untrusted @end table @menu * SecurityPolicy-modifying:: (instance) * SecurityPolicy-querying:: (instance) @end menu @node SecurityPolicy-modifying @subsection SecurityPolicy:@- modifying @table @b @meindex addPermission:@- @item addPermission:@- aPermission Not commented. @meindex owner:@- @item owner:@- aClass Not commented. @meindex removePermission:@- @item removePermission:@- aPermission Not commented. @meindex withOwner:@- @item withOwner:@- aClass Not commented. @end table @node SecurityPolicy-querying @subsection SecurityPolicy:@- querying @table @b @meindex check:@- @item check:@- aPermission Not commented. @meindex implies:@- @item implies:@- aPermission Not commented. @end table @node Semaphore @section Semaphore @clindex Semaphore @table @b @item Defined in namespace Smalltalk @itemx Superclass: LinkedList @itemx Category: Language-Processes My instances represent counting semaphores. I provide methods for signalling the semaphore's availability, and methods for waiting for its availability. I also provide some methods for implementing critical sections. @end table @menu * Semaphore class-instance creation:: (class) * Semaphore-accessing:: (instance) * Semaphore-builtins:: (instance) * Semaphore-mutual exclusion:: (instance) * Semaphore-printing:: (instance) @end menu @node Semaphore class-instance creation @subsection Semaphore class:@- instance creation @table @b @meindex forMutualExclusion @item forMutualExclusion Answer a new semaphore with a signal on it. These semaphores are a useful shortcut when you use semaphores as critical sections. @meindex new @item new Answer a new semaphore @end table @node Semaphore-accessing @subsection Semaphore:@- accessing @table @b @meindex name @item name Answer a user-friendly name for the receiver @meindex name:@- @item name:@- aString Answer a user-friendly name for the receiver @meindex waitingProcesses @item waitingProcesses Answer an Array of processes currently waiting on the receiver. @meindex wouldBlock @item wouldBlock Answer whether waiting on the receiver would suspend the current process. @end table @node Semaphore-builtins @subsection Semaphore:@- builtins @table @b @meindex lock @item lock Without putting the receiver to sleep, force processes that try to wait on the semaphore to block. Answer whether this was the case even before. @meindex notify @item notify Resume one of the processes that were waiting on the semaphore if there were any. Do not leave a signal on the semaphore if no process is waiting. @meindex notifyAll @item notifyAll Resume all the processes that were waiting on the semaphore if there were any. Do not leave a signal on the semaphore if no process is waiting. @meindex signal @item signal Signal the receiver, resuming a waiting process' if there is one @meindex wait @item wait Wait for the receiver to be signalled, suspending the executing process if it is not yet. Return nil if the wait was interrupted, the receiver otherwise. @meindex waitAfterSignalling:@- @slindex notify @slindex notifyAll @item waitAfterSignalling:@- aSemaphore Signal aSemaphore then, atomically, wait for the receiver to be signalled, suspending the executing process if it is not yet. This is needed to avoid race conditions when the #notify and #notifyAll are used before waiting on receiver:@- otherwise, if a process sends any of the two between the time aSemaphore is signaled and the time the process starts waiting on the receiver, the notification is lost. @end table @node Semaphore-mutual exclusion @subsection Semaphore:@- mutual exclusion @table @b @meindex critical:@- @item critical:@- aBlock Wait for the receiver to be free, execute aBlock and signal the receiver again. Return the result of evaluating aBlock. @end table @node Semaphore-printing @subsection Semaphore:@- printing @table @b @meindex printOn:@- @item printOn:@- aStream Print a human-readable represention of the receiver on aStream. @end table @node SequenceableCollection @section SequenceableCollection @clindex SequenceableCollection @table @b @item Defined in namespace Smalltalk @itemx Superclass: Collection @itemx Category: Collections-Sequenceable My instances represent collections of objects that are ordered. I provide some access and manipulation methods. @end table @menu * SequenceableCollection class-instance creation:: (class) * SequenceableCollection-basic:: (instance) * SequenceableCollection-comparing:: (instance) * SequenceableCollection-concatenating:: (instance) * SequenceableCollection-copying SequenceableCollections:: (instance) * SequenceableCollection-enumerating:: (instance) * SequenceableCollection-manipulation:: (instance) * SequenceableCollection-replacing items:: (instance) * SequenceableCollection-sorting:: (instance) * SequenceableCollection-still unclassified:: (instance) * SequenceableCollection-testing:: (instance) * SequenceableCollection-testing collections:: (instance) @end menu @node SequenceableCollection class-instance creation @subsection SequenceableCollection class:@- instance creation @table @b @meindex join:@-separatedBy:@- @item join:@- aCollection separatedBy:@- sepCollection Where aCollection is a collection of SequenceableCollections, answer a new instance with all the elements therein, in order, each separated by an occurrence of sepCollection. @end table @node SequenceableCollection-basic @subsection SequenceableCollection:@- basic @table @b @meindex after:@- @item after:@- oldObject Return the element after oldObject. Error if oldObject not found or if no following object is available @meindex allButFirst @item allButFirst Answer a copy of the receiver without the first object. @meindex allButFirst:@- @item allButFirst:@- n Answer a copy of the receiver without the first n objects. @meindex allButLast @item allButLast Answer a copy of the receiver without the last object. @meindex allButLast:@- @item allButLast:@- n Answer a copy of the receiver without the last n objects. @meindex at:@-ifAbsent:@- @item at:@- anIndex ifAbsent:@- aBlock Answer the anIndex-th item of the collection, or evaluate aBlock and answer the result if the index is out of range @meindex atAll:@- @slindex collect:@- @item atAll:@- keyCollection Answer a collection of the same kind returned by #collect:@-, that only includes the values at the given indices. Fail if any of the values in keyCollection is out of bounds for the receiver. @meindex atAll:@-put:@- @item atAll:@- aCollection put:@- anObject Put anObject at every index contained in aCollection @meindex atAllPut:@- @item atAllPut:@- anObject Put anObject at every index in the receiver @meindex atRandom @item atRandom Return a random item of the receiver. @meindex before:@- @item before:@- oldObject Return the element before oldObject. Error if oldObject not found or if no preceding object is available @meindex first @item first Answer the first item in the receiver @meindex first:@- @item first:@- n Answer the first n items in the receiver @meindex fourth @item fourth Answer the fourth item in the receiver @meindex identityIncludes:@- @item identityIncludes:@- anObject Answer whether we include the anObject object @meindex identityIndexOf:@- @item identityIndexOf:@- anElement Answer the index of the first occurrence of an object identical to anElement in the receiver. Answer 0 if no item is found @meindex identityIndexOf:@-ifAbsent:@- @item identityIndexOf:@- anElement ifAbsent:@- exceptionBlock Answer the index of the first occurrence of an object identical to anElement in the receiver. Invoke exceptionBlock and answer its result if no item is found @meindex identityIndexOf:@-startingAt:@- @item identityIndexOf:@- anElement startingAt:@- anIndex Answer the first index > anIndex which contains an object identical to anElement. Answer 0 if no item is found @meindex identityIndexOf:@-startingAt:@-ifAbsent:@- @item identityIndexOf:@- anObject startingAt:@- anIndex ifAbsent:@- exceptionBlock Answer the first index > anIndex which contains an object exactly identical to anObject. Invoke exceptionBlock and answer its result if no item is found @meindex identityIndexOfLast:@-ifAbsent:@- @item identityIndexOfLast:@- anElement ifAbsent:@- exceptionBlock Answer the last index which contains an object identical to anElement. Invoke exceptionBlock and answer its result if no item is found @meindex includes:@- @item includes:@- anObject Answer whether we include anObject @meindex indexOf:@- @item indexOf:@- anElement Answer the index of the first occurrence of anElement in the receiver. Answer 0 if no item is found @meindex indexOf:@-ifAbsent:@- @item indexOf:@- anElement ifAbsent:@- exceptionBlock Answer the index of the first occurrence of anElement in the receiver. Invoke exceptionBlock and answer its result if no item is found @meindex indexOf:@-startingAt:@- @item indexOf:@- anElement startingAt:@- anIndex Answer the first index > anIndex which contains anElement. Answer 0 if no item is found @meindex indexOf:@-startingAt:@-ifAbsent:@- @item indexOf:@- anElement startingAt:@- anIndex ifAbsent:@- exceptionBlock Answer the first index > anIndex which contains anElement. Invoke exceptionBlock and answer its result if no item is found @meindex indexOfLast:@-ifAbsent:@- @item indexOfLast:@- anElement ifAbsent:@- exceptionBlock Answer the last index which contains anElement. Invoke exceptionBlock and answer its result if no item is found @meindex indexOfSubCollection:@- @item indexOfSubCollection:@- aSubCollection Answer the first index > anIndex at which starts a sequence of items matching aSubCollection. Answer 0 if no such sequence is found. @meindex indexOfSubCollection:@-ifAbsent:@- @item indexOfSubCollection:@- aSubCollection ifAbsent:@- exceptionBlock Answer the first index > anIndex at which starts a sequence of items matching aSubCollection. Answer 0 if no such sequence is found. @meindex indexOfSubCollection:@-startingAt:@- @item indexOfSubCollection:@- aSubCollection startingAt:@- anIndex Answer the first index > anIndex at which starts a sequence of items matching aSubCollection. Answer 0 if no such sequence is found. @meindex indexOfSubCollection:@-startingAt:@-ifAbsent:@- @item indexOfSubCollection:@- aSubCollection startingAt:@- anIndex ifAbsent:@- exceptionBlock Answer the first index > anIndex at which starts a sequence of items matching aSubCollection. Invoke exceptionBlock and answer its result if no such sequence is found @meindex last @item last Answer the last item in the receiver @meindex last:@- @item last:@- n Answer the last n items in the receiver @meindex second @item second Answer the second item in the receiver @meindex third @item third Answer the third item in the receiver @end table @node SequenceableCollection-comparing @subsection SequenceableCollection:@- comparing @table @b @meindex endsWith:@- @item endsWith:@- aSequenceableCollection Returns true if the receiver ends with the same characters as aSequenceableCollection. @meindex startsWith:@- @item startsWith:@- aSequenceableCollection Returns true if the receiver starts with the same characters as aSequenceableCollection. @end table @node SequenceableCollection-concatenating @subsection SequenceableCollection:@- concatenating @table @b @meindex join:@- @item join:@- sepCollection Answer a new collection like my first element, with all the elements (in order) of all my elements (which should be collections) separated by sepCollection. I use my first element instead of myself as a prototype because my elements are more likely to share the desired properties than I am, such as in:@- #('hello,' 'world') join:@- ' ' => 'hello, world' @meindex with:@- @item with:@- aSequenceableCollection Return an Array with the same size as the receiver and aSequenceableCollection, each element of which is a 2-element Arrays including one element from the receiver and one from aSequenceableCollection. @meindex with:@-with:@- @item with:@- seqColl1 with:@- seqColl2 Return an Array with the same size as the receiver and the arguments, each element of which is a 3-element Arrays including one element from the receiver and one from each argument. @meindex with:@-with:@-with:@- @item with:@- seqColl1 with:@- seqColl2 with:@- seqColl3 Return an Array with the same size as the receiver and the arguments, each element of which is a 4-element Arrays including one element from the receiver and one from each argument. @end table @node SequenceableCollection-copying SequenceableCollections @subsection SequenceableCollection:@- copying SequenceableCollections @table @b @meindex copyAfter:@- @item copyAfter:@- anObject Answer a new collection holding all the elements of the receiver after the first occurrence of anObject, up to the last. @meindex copyAfterLast:@- @item copyAfterLast:@- anObject Answer a new collection holding all the elements of the receiver after the last occurrence of anObject, up to the last. @meindex copyFrom:@- @item copyFrom:@- start Answer a new collection containing all the items in the receiver from the start-th. @meindex copyFrom:@-to:@- @item copyFrom:@- start to:@- stop Answer a new collection containing all the items in the receiver from the start-th and to the stop-th @meindex copyReplaceAll:@-with:@- @item copyReplaceAll:@- oldSubCollection with:@- newSubCollection Answer a new collection in which all the sequences matching oldSubCollection are replaced with newSubCollection @meindex copyReplaceFrom:@-to:@-with:@- @item copyReplaceFrom:@- start to:@- stop with:@- replacementCollection Answer a new collection of the same class as the receiver that contains the same elements as the receiver, in the same order, except for elements from index `start' to index `stop'. If start < stop, these are replaced by the contents of the replacementCollection. Instead, If start = (stop + 1), like in `copyReplaceFrom:@- 4 to:@- 3 with:@- anArray', then every element of the receiver will be present in the answered copy; the operation will be an append if stop is equal to the size of the receiver or, if it is not, an insert before index `start'. @meindex copyReplaceFrom:@-to:@-withObject:@- @item copyReplaceFrom:@- start to:@- stop withObject:@- anObject Answer a new collection of the same class as the receiver that contains the same elements as the receiver, in the same order, except for elements from index `start' to index `stop'. If start < stop, these are replaced by stop-start+1 copies of anObject. Instead, If start = (stop + 1), then every element of the receiver will be present in the answered copy; the operation will be an append if stop is equal to the size of the receiver or, if it is not, an insert before index `start'. @meindex copyUpTo:@- @item copyUpTo:@- anObject Answer a new collection holding all the elements of the receiver from the first up to the first occurrence of anObject, excluded. @meindex copyUpToLast:@- @item copyUpToLast:@- anObject Answer a new collection holding all the elements of the receiver from the first up to the last occurrence of anObject, excluded. @meindex copyWithFirst:@- @item copyWithFirst:@- anObject Answer a new collection holding all the elements of the receiver after the first occurrence of anObject, up to the last. @end table @node SequenceableCollection-enumerating @subsection SequenceableCollection:@- enumerating @table @b @meindex anyOne @item anyOne Answer an unspecified element of the collection. @meindex do:@- @item do:@- aBlock Evaluate aBlock for all the elements in the sequenceable collection @meindex do:@-separatedBy:@- @item do:@- aBlock separatedBy:@- sepBlock Evaluate aBlock for all the elements in the sequenceable collection. Between each element, evaluate sepBlock without parameters. @meindex doWithIndex:@- @slindex keysAndValuesDo:@- @item doWithIndex:@- aBlock Evaluate aBlock for all the elements in the sequenceable collection, passing the index of each element as the second parameter. This method is mantained for backwards compatibility and is not mandated by the ANSI standard; use #keysAndValuesDo:@- @meindex findFirst:@- @item findFirst:@- aBlock Returns the index of the first element of the sequenceable collection for which aBlock returns true, or 0 if none @meindex findLast:@- @item findLast:@- aBlock Returns the index of the last element of the sequenceable collection for which aBlock returns true, or 0 if none does @meindex fold:@- @item fold:@- binaryBlock First, pass to binaryBlock the first and second elements of the receiver; for each subsequent element, pass the result of the previous evaluation and an element. Answer the result of the last invocation, or the first element if the collection has size 1. Fail if the collection is empty. @meindex from:@-to:@-do:@- @item from:@- startIndex to:@- stopIndex do:@- aBlock Evaluate aBlock for all the elements in the sequenceable collection whose indices are in the range index to stopIndex @meindex from:@-to:@-doWithIndex:@- @slindex from:@-to:@-keysAndValuesDo:@- @item from:@- startIndex to:@- stopIndex doWithIndex:@- aBlock Evaluate aBlock for all the elements in the sequenceable collection whose indices are in the range index to stopIndex, passing the index of each element as the second parameter. This method is mantained for backwards compatibility and is not mandated by the ANSI standard; use #from:@-to:@-keysAndValuesDo:@- @meindex from:@-to:@-keysAndValuesDo:@- @item from:@- startIndex to:@- stopIndex keysAndValuesDo:@- aBlock Evaluate aBlock for all the elements in the sequenceable collection whose indices are in the range index to stopIndex, passing the index of each element as the first parameter and the element as the second. @meindex keys @item keys Return an Interval corresponding to the valid indices in the receiver. @meindex keysAndValuesDo:@- @item keysAndValuesDo:@- aBlock Evaluate aBlock for all the elements in the sequenceable collection, passing the index of each element as the first parameter and the element as the second. @meindex readStream @item readStream Answer a ReadStream streaming on the receiver @meindex readWriteStream @item readWriteStream Answer a ReadWriteStream which streams on the receiver @meindex reverse @item reverse Answer the receivers' contents in reverse order @meindex reverseDo:@- @item reverseDo:@- aBlock Evaluate aBlock for all elements in the sequenceable collection, from the last to the first. @meindex with:@-collect:@- @item with:@- aSequenceableCollection collect:@- aBlock Evaluate aBlock for each pair of elements took respectively from the receiver and from aSequenceableCollection; answer a collection of the same kind of the receiver, made with the block's return values. Fail if the receiver has not the same size as aSequenceableCollection. @meindex with:@-do:@- @item with:@- aSequenceableCollection do:@- aBlock Evaluate aBlock for each pair of elements took respectively from the receiver and from aSequenceableCollection. Fail if the receiver has not the same size as aSequenceableCollection. @end table @node SequenceableCollection-manipulation @subsection SequenceableCollection:@- manipulation @table @b @meindex swap:@-with:@- @item swap:@- anIndex with:@- anotherIndex Swap the item at index anIndex with the item at index another index @end table @node SequenceableCollection-replacing items @subsection SequenceableCollection:@- replacing items @table @b @meindex replaceAll:@-with:@- @item replaceAll:@- anObject with:@- anotherObject In the receiver, replace every occurrence of anObject with anotherObject. @meindex replaceFrom:@-to:@-with:@- @item replaceFrom:@- start to:@- stop with:@- replacementCollection Replace the items from start to stop with replacementCollection's items from 1 to stop-start+1 (in unexpected order if the collection is not sequenceable). @meindex replaceFrom:@-to:@-with:@-startingAt:@- @item replaceFrom:@- start to:@- stop with:@- replacementCollection startingAt:@- repStart Replace the items from start to stop with replacementCollection's items from repStart to repStart+stop-start @meindex replaceFrom:@-to:@-withObject:@- @item replaceFrom:@- anIndex to:@- stopIndex withObject:@- replacementObject Replace every item from start to stop with replacementObject. @end table @node SequenceableCollection-sorting @subsection SequenceableCollection:@- sorting @table @b @meindex sort @slindex <= @item sort Sort the contents of the receiver according to the default sort block, which uses #<= to compare items. @meindex sort:@- @item sort:@- sortBlock Sort the contents of the receiver according to the given sort block, which accepts pair of items and returns true if the first item is less than the second one. @meindex sorted @slindex <= @item sorted Return a copy of the receiver sorted according to the default sort block, which uses #<= to compare items. @meindex sorted:@- @item sorted:@- sortBlock Return a copy of the receiver sorted according to the given sort block, which accepts pair of items and returns true if the first item is less than the second one. @end table @node SequenceableCollection-still unclassified @subsection SequenceableCollection:@- still unclassified @table @b @meindex nextPutAllOn:@- @item nextPutAllOn:@- aStream Write all the objects in the receiver to aStream @end table @node SequenceableCollection-testing @subsection SequenceableCollection:@- testing @table @b @meindex = @item = aCollection Answer whether the receiver's items match those in aCollection @meindex examineOn:@- @item examineOn:@- aStream Print all the instance variables and context of the receiver on aStream @meindex hash @item hash Answer an hash value for the receiver @meindex isSequenceable @slindex at:@-/@-#at:@-put:@- @item isSequenceable Answer whether the receiver can be accessed by a numeric index with #at:@-/@-#at:@-put:@-. @end table @node SequenceableCollection-testing collections @subsection SequenceableCollection:@- testing collections @table @b @meindex size @slindex do:@- @item size Answer a dummy size of 0, so that SequenceableCollection>>@-#do:@- works. @end table @node Set @section Set @clindex Set @table @b @item Defined in namespace Smalltalk @itemx Superclass: HashedCollection @itemx Category: Collections-Unordered I am the typical set object; I also known how to do arithmetic on my instances. @end table @menu * Set-arithmetic:: (instance) * Set-awful ST-80 compatibility hacks:: (instance) * Set-comparing:: (instance) @end menu @node Set-arithmetic @subsection Set:@- arithmetic @table @b @meindex & @item & aSet Compute the set intersection of the receiver and aSet. @meindex + @item + aSet Compute the set union of the receiver and aSet. @meindex - @item - aSet Compute the set difference of the receiver and aSet. @end table @node Set-awful ST-80 compatibility hacks @subsection Set:@- awful ST-80 compatibility hacks @table @b @meindex findObjectIndex:@- @item findObjectIndex:@- object Tries to see if anObject exists as an indexed variable. As soon as nil or anObject is found, the index of that slot is answered @end table @node Set-comparing @subsection Set:@- comparing @table @b @meindex < @item < aSet Answer whether the receiver is a strict subset of aSet @meindex <= @item <= aSet Answer whether the receiver is a subset of aSet @meindex > @item > aSet Answer whether the receiver is a strict superset of aSet @meindex >= @item >= aSet Answer whether the receiver is a superset of aSet @end table @node SharedQueue @section SharedQueue @clindex SharedQueue @table @b @item Defined in namespace Smalltalk @itemx Superclass: Object @itemx Category: Language-Processes My instances provide a guaranteed safe mechanism to allow for communication between processes. All access to the underlying data structures is controlled with critical sections so that things proceed smoothly. @end table @menu * SharedQueue class-instance creation:: (class) * SharedQueue-accessing:: (instance) @end menu @node SharedQueue class-instance creation @subsection SharedQueue class:@- instance creation @table @b @meindex new @item new Create a new instance of the receiver @meindex sortBlock:@- @item sortBlock:@- sortBlock Create a new instance of the receiver which implements a priority queue with the given sort block @end table @node SharedQueue-accessing @subsection SharedQueue:@- accessing @table @b @meindex isEmpty @item isEmpty Answer whether there is an object on the queue @meindex next @item next Wait for an object to be on the queue, then remove it and answer it @meindex nextPut:@- @item nextPut:@- value Put value on the queue and answer it @meindex peek @slindex next @item peek Wait for an object to be on the queue if necessary, then answer the same object that #next would answer without removing it. @end table @node SingletonProxy @section SingletonProxy @clindex SingletonProxy @table @b @item Defined in namespace Smalltalk @itemx Superclass: AlternativeObjectProxy @itemx Category: Streams-Files I am a proxy that stores the class of an object rather than the object itself, and pretends that a registered instance (which most likely is a singleton instance of the stored class) was stored instead. @end table @menu * SingletonProxy class-accessing:: (class) * SingletonProxy class-instance creation:: (class) * SingletonProxy-saving and restoring:: (instance) @end menu @node SingletonProxy class-accessing @subsection SingletonProxy class:@- accessing @table @b @meindex acceptUsageForClass:@- @item acceptUsageForClass:@- aClass The receiver was asked to be used as a proxy for the class aClass. The registration is fine if the class is actually a singleton. @end table @node SingletonProxy class-instance creation @subsection SingletonProxy class:@- instance creation @table @b @meindex on:@- @item on:@- anObject Answer a proxy to be used to save anObject. The proxy stores the class and restores the object by looking into a dictionary of class -> singleton objects. @end table @node SingletonProxy-saving and restoring @subsection SingletonProxy:@- saving and restoring @table @b @meindex object @slindex reconstructOriginalObject @slindex postLoad @item object Reconstruct the object stored in the proxy and answer it; the binaryRepresentationObject is sent the #reconstructOriginalObject message, and the resulting object is sent the #postLoad message. @end table @node SmallInteger @section SmallInteger @clindex SmallInteger @table @b @item Defined in namespace Smalltalk @itemx Superclass: Integer @itemx Category: Language-Data types I am the integer class of the GNU Smalltalk system. My instances can represent signed 30 bit integers and are as efficient as possible. @end table @menu * SmallInteger class-getting limits:: (class) * SmallInteger class-testing:: (class) * SmallInteger-bit arithmetic:: (instance) * SmallInteger-built ins:: (instance) * SmallInteger-builtins:: (instance) * SmallInteger-coercion:: (instance) * SmallInteger-coercion methods:: (instance) * SmallInteger-testing functionality:: (instance) @end menu @node SmallInteger class-getting limits @subsection SmallInteger class:@- getting limits @table @b @meindex bits @item bits Answer the number of bits (excluding the sign) that can be represented directly in an object pointer @meindex largest @item largest Answer the largest integer represented directly in an object pointer @meindex smallest @item smallest Answer the smallest integer represented directly in an object pointer @end table @node SmallInteger class-testing @subsection SmallInteger class:@- testing @table @b @meindex isIdentity @item isIdentity Answer whether x = y implies x == y for instances of the receiver @end table @node SmallInteger-bit arithmetic @subsection SmallInteger:@- bit arithmetic @table @b @meindex highBit @item highBit Return the index of the highest order 1 bit of the receiver @meindex lowBit @item lowBit Return the index of the lowest order 1 bit of the receiver. @end table @node SmallInteger-built ins @subsection SmallInteger:@- built ins @table @b @meindex * @item * arg Multiply the receiver and arg and answer another Number @meindex + @item + arg Sum the receiver and arg and answer another Number @meindex - @item - arg Subtract arg from the receiver and answer another Number @meindex / @item / arg Divide the receiver by arg and answer another Integer or Fraction @meindex // @item // arg Dividing receiver by arg (with truncation towards -infinity) and answer the result @meindex < @item < arg Answer whether the receiver is less than arg @meindex <= @item <= arg Answer whether the receiver is less than or equal to arg @meindex = @item = arg Answer whether the receiver is equal to arg @meindex == @item == arg Answer whether the receiver is the same object as arg @meindex > @item > arg Answer whether the receiver is greater than arg @meindex >= @item >= arg Answer whether the receiver is greater than or equal to arg @meindex \\ @item \\ arg Calculate the remainder of dividing receiver by arg (with truncation towards -infinity) and answer it @meindex asFloatD @item asFloatD Convert the receiver to a FloatD, answer the result @meindex asFloatE @item asFloatE Convert the receiver to a FloatE, answer the result @meindex asFloatQ @item asFloatQ Convert the receiver to a FloatQ, answer the result @meindex asObject @item asObject Answer the object whose index is in the receiver, nil if there is a free object, fail if index is out of bounds @meindex asObjectNoFail @item asObjectNoFail Answer the object whose index is in the receiver, or nil if no object is found at that index @meindex bitAnd:@- @item bitAnd:@- arg Do a bitwise AND between the receiver and arg, answer the result @meindex bitOr:@- @item bitOr:@- arg Do a bitwise OR between the receiver and arg, answer the result @meindex bitShift:@- @item bitShift:@- arg Shift the receiver by arg places to the left if arg > 0, by arg places to the right if arg < 0, answer another Number @meindex bitXor:@- @item bitXor:@- arg Do a bitwise XOR between the receiver and arg, answer the result @meindex divExact:@- @item divExact:@- arg Dividing receiver by arg assuming that the remainder is zero, and answer the result @meindex nextValidOop @item nextValidOop Answer the index of the first non-free OOP after the receiver. This is used internally; it is placed here to avoid polluting Object. @meindex quo:@- @item quo:@- arg Dividing receiver by arg (with truncation towards zero) and answer the result @meindex ~= @item ~= arg Answer whether the receiver is not equal to arg @meindex ~~ @item ~~ arg Answer whether the receiver is not the same object as arg @end table @node SmallInteger-builtins @subsection SmallInteger:@- builtins @table @b @meindex at:@- @item at:@- anIndex Answer the index-th indexed instance variable of the receiver. This method always fails. @meindex at:@-put:@- @item at:@- anIndex put:@- value Store value in the index-th indexed instance variable of the receiver This method always fails. @meindex basicAt:@- @item basicAt:@- anIndex Answer the index-th indexed instance variable of the receiver. This method always fails. @meindex basicAt:@-put:@- @item basicAt:@- anIndex put:@- value Store value in the index-th indexed instance variable of the receiver This method always fails. @meindex scramble @item scramble Answer the receiver with its bits mixed and matched. @end table @node SmallInteger-coercion @subsection SmallInteger:@- coercion @table @b @meindex asCNumber @item asCNumber Convert the receiver to a kind of number that is understood by the C call-out mechanism. @end table @node SmallInteger-coercion methods @subsection SmallInteger:@- coercion methods @table @b @meindex generality @item generality Return the receiver's generality @meindex unity @item unity Coerce 1 to the receiver's class @meindex zero @item zero Coerce 0 to the receiver's class @end table @node SmallInteger-testing functionality @subsection SmallInteger:@- testing functionality @table @b @meindex isSmallInteger @item isSmallInteger Answer `true'. @end table @node SortedCollection @section SortedCollection @clindex SortedCollection @table @b @item Defined in namespace Smalltalk @itemx Superclass: OrderedCollection @itemx Category: Collections-Sequenceable I am a collection of objects, stored and accessed according to some sorting criteria. I store things using heap sort and quick sort. My instances have a comparison block associated with them; this block takes two arguments and is a predicate which returns true if the first argument should be sorted earlier than the second. The default block is [ :a :b | a <= b ], but I will accept any block that conforms to the above criteria -- actually any object which responds to #value:@-value:@-. @end table @menu * SortedCollection class-hacking:: (class) * SortedCollection class-instance creation:: (class) * SortedCollection-basic:: (instance) * SortedCollection-copying:: (instance) * SortedCollection-disabled:: (instance) * SortedCollection-enumerating:: (instance) * SortedCollection-saving and loading:: (instance) * SortedCollection-searching:: (instance) * SortedCollection-sorting:: (instance) @end menu @node SortedCollection class-hacking @subsection SortedCollection class:@- hacking @table @b @meindex defaultSortBlock @item defaultSortBlock Answer a default sort block for the receiver. @end table @node SortedCollection class-instance creation @subsection SortedCollection class:@- instance creation @table @b @meindex new @item new Answer a new collection with a default size and sort block @meindex new:@- @item new:@- aSize Answer a new collection with a default sort block and the given size @meindex sortBlock:@- @item sortBlock:@- aSortBlock Answer a new collection with a default size and the given sort block @end table @node SortedCollection-basic @subsection SortedCollection:@- basic @table @b @meindex last @item last Answer the last item of the receiver @meindex removeLast @item removeLast Remove an object from the end of the receiver. Fail if the receiver is empty @meindex sortBlock @item sortBlock Answer the receiver's sort criteria @meindex sortBlock:@- @item sortBlock:@- aSortBlock Change the sort criteria for a sorted collection, resort the elements of the collection, and return it. @end table @node SortedCollection-copying @subsection SortedCollection:@- copying @table @b @meindex copyEmpty:@- @item copyEmpty:@- newSize Answer an empty copy of the receiver, with the same sort block as the receiver @end table @node SortedCollection-disabled @subsection SortedCollection:@- disabled @table @b @meindex add:@-afterIndex:@- @item add:@- anObject afterIndex:@- i This method should not be called for instances of this class. @meindex addAll:@-afterIndex:@- @item addAll:@- aCollection afterIndex:@- i This method should not be called for instances of this class. @meindex addAllFirst:@- @item addAllFirst:@- aCollection This method should not be called for instances of this class. @meindex addAllLast:@- @item addAllLast:@- aCollection This method should not be called for instances of this class. @meindex addFirst:@- @item addFirst:@- anObject This method should not be called for instances of this class. @meindex addLast:@- @item addLast:@- anObject This method should not be called for instances of this class. @meindex at:@-put:@- @item at:@- index put:@- anObject This method should not be called for instances of this class. @end table @node SortedCollection-enumerating @subsection SortedCollection:@- enumerating @table @b @meindex beConsistent @slindex do:@- @item beConsistent Prepare the receiver to be walked through with #do:@- or another enumeration method. @end table @node SortedCollection-saving and loading @subsection SortedCollection:@- saving and loading @table @b @meindex postLoad @item postLoad Restore the default sortBlock if it is nil @meindex preStore @item preStore Store the default sortBlock as nil @end table @node SortedCollection-searching @subsection SortedCollection:@- searching @table @b @meindex includes:@- @item includes:@- anObject Private - Answer whether the receiver includes an item which is equal to anObject @meindex indexOf:@-startingAt:@-ifAbsent:@- @item indexOf:@- anObject startingAt:@- index ifAbsent:@- aBlock Answer the first index > anIndex which contains anElement. Invoke exceptionBlock and answer its result if no item is found @meindex occurrencesOf:@- @item occurrencesOf:@- anObject Answer how many occurrences of anObject can be found in the receiver @end table @node SortedCollection-sorting @subsection SortedCollection:@- sorting @table @b @meindex sort @item sort Sort the contents of the receiver according to the given sort block, which accepts pair of items and returns true if the first item is less than the second one. Fails if the collections's sort block is not the same as the default sort block. @meindex sort:@- @item sort:@- sortBlock Sort the contents of the receiver according to the given sort block, which accepts pair of items and returns true if the first item is less than the second one. Fails if the sort block is not the same as the collection's sort block. @end table @node Stream @section Stream @clindex Stream @table @b @item Defined in namespace Smalltalk @itemx Superclass: Iterable @itemx Category: Streams I am an abstract class that provides interruptable sequential access to objects. I can return successive objects from a source, or accept successive objects and store them sequentially on a sink. I provide some simple iteration over the contents of one of my instances, and provide for writing collections sequentially. @end table @menu * Stream-accessing-reading:: (instance) * Stream-accessing-writing:: (instance) * Stream-basic:: (instance) * Stream-buffering:: (instance) * Stream-built ins:: (instance) * Stream-character writing:: (instance) * Stream-compiling:: (instance) * Stream-concatenating:: (instance) * Stream-enumerating:: (instance) * Stream-filing out:: (instance) * Stream-filtering:: (instance) * Stream-polymorphism:: (instance) * Stream-positioning:: (instance) * Stream-printing:: (instance) * Stream-still unclassified:: (instance) * Stream-storing:: (instance) * Stream-streaming protocol:: (instance) * Stream-testing:: (instance) @end menu @node Stream-accessing-reading @subsection Stream:@- accessing-reading @table @b @meindex contents @item contents Answer the whole contents of the receiver, from the next object to the last @meindex file @item file Return nil by default; not all streams have a file. @meindex name @item name Return nil by default; not all streams have a name. @meindex next @item next Return the next object in the receiver @meindex next:@- @item next:@- anInteger Return the next anInteger objects in the receiver @meindex nextAvailable:@- @item nextAvailable:@- anInteger Return up to anInteger objects in the receiver. Besides stopping if the end of the stream is reached, this may return less than this number of bytes for various reasons. For example, on files and sockets this operation could be non-blocking, or could do at most one I/O operation. @meindex nextAvailable:@-into:@-startingAt:@- @item nextAvailable:@- anInteger into:@- aCollection startingAt:@- pos Place the next anInteger objects from the receiver into aCollection, starting at position pos. Return the number of items stored. Besides stopping if the end of the stream is reached, this may return less than this number of bytes for various reasons. For example, on files and sockets this operation could be non-blocking, or could do at most one I/O operation. @meindex nextAvailable:@-putAllOn:@- @item nextAvailable:@- anInteger putAllOn:@- aStream Copy up to anInteger objects in the receiver to aStream. Besides stopping if the end of the stream is reached, this may return less than this number of bytes for various reasons. For example, on files and sockets this operation could be non-blocking, or could do at most one I/O operation. @meindex nextLine @item nextLine Returns a collection of the same type that the stream accesses, containing the next line up to the next new-line character. Returns the entire rest of the stream's contents if no new-line character is found. @meindex nextMatchFor:@- @item nextMatchFor:@- anObject Answer whether the next object is equal to anObject. Even if it does not, anObject is lost @meindex splitAt:@- @slindex = @item splitAt:@- anObject Answer an OrderedCollection of parts of the receiver. A new (possibly empty) part starts at the start of the receiver, or after every occurrence of an object which is equal to anObject (as compared by #=). @meindex upTo:@- @item upTo:@- anObject Returns a collection of the same type that the stream accesses, up to but not including the object anObject. Returns the entire rest of the stream's contents if anObject is not present. @meindex upToAll:@- @item upToAll:@- aCollection If there is a sequence of objects remaining in the stream that is equal to the sequence in aCollection, set the stream position just past that sequence and answer the elements up to, but not including, the sequence. Else, set the stream position to its end and answer all the remaining elements. @meindex upToEnd @item upToEnd Answer every item in the collection on which the receiver is streaming, from the next one to the last @end table @node Stream-accessing-writing @subsection Stream:@- accessing-writing @table @b @meindex next:@-put:@- @item next:@- anInteger put:@- anObject Write anInteger copies of anObject to the receiver @meindex next:@-putAll:@-startingAt:@- @item next:@- n putAll:@- aCollection startingAt:@- start Write n objects to the stream, reading them from aCollection and starting at the start-th item. @meindex nextPut:@- @item nextPut:@- anObject Write anObject to the receiver @meindex nextPutAll:@- @item nextPutAll:@- aCollection Write all the objects in aCollection to the receiver @meindex nextPutAllFlush:@- @item nextPutAllFlush:@- aCollection Put all the elements of aCollection in the stream, then flush the buffers if supported by the stream. @end table @node Stream-basic @subsection Stream:@- basic @table @b @meindex species @item species Answer `Array'. @end table @node Stream-buffering @subsection Stream:@- buffering @table @b @meindex next:@-into:@-startingAt:@- @item next:@- anInteger into:@- answer startingAt:@- pos Read up to anInteger bytes from the stream and store them into answer. Return the number of bytes that were read, raising an exception if we could not read the full amount of data. @meindex next:@-putAllOn:@- @item next:@- anInteger putAllOn:@- aStream Read up to anInteger bytes from the stream and store them into aStream. Return the number of bytes that were read, raising an exception if we could not read the full amount of data. @end table @node Stream-built ins @subsection Stream:@- built ins @table @b @meindex fileIn @item fileIn File in the contents of the receiver. During a file in operation, global variables (starting with an uppercase letter) that are not declared don't yield an `unknown variable' error. Instead, they are defined as nil in the `Undeclared' dictionary (a global variable residing in Smalltalk). As soon as you add the variable to a namespace (for example by creating a class) the Association will be removed from Undeclared and reused in the namespace, so that the old references will automagically point to the new value. @meindex fileInLine:@-file:@-at:@- @slindex line @slindex fileIn @item fileInLine:@- lineNum file:@- aFile at:@- charPosInt Private - Much like a preprocessor #line directive; it is used internally by #fileIn, and explicitly by the Emacs Smalltalk mode. @meindex fileInLine:@-fileName:@-at:@- @slindex line @slindex fileIn @item fileInLine:@- lineNum fileName:@- aString at:@- charPosInt Private - Much like a preprocessor #line directive; it is used internally by #fileIn, and explicitly by the Emacs Smalltalk mode. @end table @node Stream-character writing @subsection Stream:@- character writing @table @b @meindex cr @item cr Store a cr on the receiver @meindex crTab @item crTab Store a cr and a tab on the receiver @meindex encoding @item encoding Answer the encoding to be used when storing Unicode characters. @meindex isUnicode @item isUnicode Answer whether the receiver is able to store Unicode characters. Note that if this method returns true, the stream may or may not be able to store Characters (as opposed to UnicodeCharacters) whose value is above 127. @meindex nl @item nl Store a new line on the receiver @meindex nlTab @item nlTab Store a new line and a tab on the receiver @meindex space @item space Store a space on the receiver @meindex space:@- @item space:@- n Store n spaces on the receiver @meindex tab @item tab Store a tab on the receiver @meindex tab:@- @item tab:@- n Store n tabs on the receiver @end table @node Stream-compiling @subsection Stream:@- compiling @table @b @meindex segmentFrom:@-to:@- @slindex asString @item segmentFrom:@- startPos to:@- endPos Answer an object that, when sent #asString, will yield the result of sending `copyFrom:@- startPos to:@- endPos' to the receiver @end table @node Stream-concatenating @subsection Stream:@- concatenating @table @b @meindex with:@- @item with:@- aStream Return a new Stream whose elements are 2-element Arrays, including one element from the receiver and one from aStream. @meindex with:@-with:@- @item with:@- stream1 with:@- stream2 Return a new Stream whose elements are 3-element Arrays, including one element from the receiver and one from each argument. @meindex with:@-with:@-with:@- @item with:@- stream1 with:@- stream2 with:@- stream3 Return a new Stream whose elements are 3-element Arrays, including one element from the receiver and one from each argument. @end table @node Stream-enumerating @subsection Stream:@- enumerating @table @b @meindex do:@- @item do:@- aBlock Evaluate aBlock once for every object in the receiver @meindex linesDo:@- @item linesDo:@- aBlock Evaluate aBlock once for every line in the receiver (assuming the receiver is streaming on Characters). @end table @node Stream-filing out @subsection Stream:@- filing out @table @b @meindex fileOut:@- @item fileOut:@- aClass File out aClass on the receiver. If aClass is not a metaclass, file out class and instance methods; if aClass is a metaclass, file out only the class methods @end table @node Stream-filtering @subsection Stream:@- filtering @table @b @meindex , @item , anIterable Answer a new stream that concatenates the data in the receiver with the data in aStream. Both the receiver and aStream should be readable. @meindex collect:@- @item collect:@- aBlock Answer a new stream that will pass the returned objects through aBlock, and return whatever object is returned by aBlock instead. Note that when peeking in the returned stream, the block will be invoked multiple times, with possibly surprising results. @meindex lines @item lines Answer a new stream that answers lines from the receiver. @meindex peek @item peek Returns the next element of the stream without moving the pointer. Returns nil when at end of stream. Lookahead is implemented automatically for streams that are not positionable but can be copied. @meindex peekFor:@- @item peekFor:@- aCharacter Returns true and gobbles the next element from the stream of it is equal to anObject, returns false and doesn't gobble the next element if the next element is not equal to anObject. Lookahead is implemented automatically for streams that are not positionable but can be copied. @meindex reject:@- @item reject:@- aBlock Answer a new stream that only returns those objects for which aBlock returns false. Note that the returned stream will not be positionable. @meindex select:@- @item select:@- aBlock Answer a new stream that only returns those objects for which aBlock returns true. Note that the returned stream will not be positionable. @end table @node Stream-polymorphism @subsection Stream:@- polymorphism @table @b @meindex close @item close Do nothing. This is provided for consistency with file streams @meindex flush @item flush Do nothing. This is provided for consistency with file streams @meindex pastEnd @item pastEnd The end of the stream has been reached. Signal a Notification. @end table @node Stream-positioning @subsection Stream:@- positioning @table @b @meindex isPositionable @slindex skip:@- @item isPositionable Answer true if the stream supports moving backwards with #skip:@-. @meindex skip:@- @item skip:@- anInteger Move the position forwards by anInteger places @meindex skipSeparators @slindex next @slindex skipSeparators @item skipSeparators Advance the receiver until we find a character that is not a separator. Answer false if we reach the end of the stream, else answer true; in this case, sending #next will return the first non-separator character (possibly the same to which the stream pointed before #skipSeparators was sent). @meindex skipTo:@- @item skipTo:@- anObject Move the current position to after the next occurrence of anObject and return true if anObject was found. If anObject doesn't exist, the pointer is atEnd, and false is returned. @meindex skipToAll:@- @item skipToAll:@- aCollection If there is a sequence of objects remaining in the stream that is equal to the sequence in aCollection, set the stream position just past that sequence and answer true. Else, set the stream position to its end and answer false. @end table @node Stream-printing @subsection Stream:@- printing @table @b @meindex << @slindex display:@- @item << anObject This method is a short-cut for #display:@-; it prints anObject on the receiver by sending displayOn:@- to anObject. This method is provided so that you can use cascading and obtain better-looking code @meindex display:@- @item display:@- anObject Print anObject on the receiver by sending displayOn:@- to anObject. This method is provided so that you can use cascading and obtain better-looking code @meindex print:@- @item print:@- anObject Print anObject on the receiver by sending printOn:@- to anObject. This method is provided so that you can use cascading and obtain better-looking code @end table @node Stream-still unclassified @subsection Stream:@- still unclassified @table @b @meindex nextPutAllOn:@- @item nextPutAllOn:@- aStream Write all the objects in the receiver to aStream @end table @node Stream-storing @subsection Stream:@- storing @table @b @meindex store:@- @item store:@- anObject Print Smalltalk code compiling to anObject on the receiver, by sending storeOn:@- to anObject. This method is provided so that you can use cascading and obtain better-looking code @end table @node Stream-streaming protocol @subsection Stream:@- streaming protocol @table @b @meindex nextAvailablePutAllOn:@- @item nextAvailablePutAllOn:@- aStream Copy to aStream a more-or-less arbitrary amount of data. When used on files, this does at most one I/O operation. For other kinds of stream, the definition may vary. This method is used to do stream-to-stream copies. @end table @node Stream-testing @subsection Stream:@- testing @table @b @meindex atEnd @item atEnd Answer whether the stream has got to an end @meindex isExternalStream @item isExternalStream Answer whether the receiver streams on a file or socket. By default, answer false. @meindex isSequenceable @slindex at:@-/@-#at:@-put:@- @item isSequenceable Answer whether the receiver can be accessed by a numeric index with #at:@-/@-#at:@-put:@-. @meindex readStream @item readStream As a wild guess, return the receiver. WriteStreams should override this method. @end table @node String @section String @clindex String @table @b @item Defined in namespace Smalltalk @itemx Superclass: CharacterArray @itemx Category: Collections-Text My instances represent 8-bit character strings. Being a very common case, they are particularly optimized. Note that, if you care about multilingualization, you should treat String only as an encoded representation of a UnicodeString. The I18N package adds more Unicode-friendliness to the system so that encoding and decoding is performed automatically in more cases. In that case, String represents a case when the encoding is either unknown, irrelevant, or assumed to be the system default. @end table @menu * String class-instance creation:: (class) * String class-multibyte encodings:: (class) * String-accessing:: (instance) * String-basic:: (instance) * String-built ins:: (instance) * String-CObject:: (instance) * String-converting:: (instance) * String-filesystem:: (instance) * String-printing:: (instance) * String-regex:: (instance) * String-still unclassified:: (instance) * String-testing functionality:: (instance) @end menu @node String class-instance creation @subsection String class:@- instance creation @table @b @meindex fromCData:@- @item fromCData:@- aCObject Answer a String containing the bytes starting at the location pointed to by aCObject, up to the first NUL character. @meindex fromCData:@-size:@- @item fromCData:@- aCObject size:@- anInteger Answer a String containing anInteger bytes starting at the location pointed to by aCObject @end table @node String class-multibyte encodings @subsection String class:@- multibyte encodings @table @b @meindex isUnicode @item isUnicode Answer false; the receiver stores bytes (i.e. an encoded form), not characters. @end table @node String-accessing @subsection String:@- accessing @table @b @meindex byteAt:@- @item byteAt:@- index Answer the ascii value of index-th character variable of the receiver @meindex byteAt:@-put:@- @item byteAt:@- index put:@- value Store (Character value:@- value) in the index-th indexed instance variable of the receiver @end table @node String-basic @subsection String:@- basic @table @b @meindex , @item , aString Answer a new instance of an ArrayedCollection containing all the elements in the receiver, followed by all the elements in aSequenceableCollection @meindex = @item = aCollection Answer whether the receiver's items match those in aCollection @meindex indexOf:@-startingAt:@- @item indexOf:@- anElement startingAt:@- anIndex Answer the first index > anIndex which contains anElement. Invoke exceptionBlock and answer its result if no item is found @meindex indexOf:@-startingAt:@-ifAbsent:@- @item indexOf:@- anElement startingAt:@- anIndex ifAbsent:@- exceptionBlock Answer the first index > anIndex which contains anElement. Invoke exceptionBlock and answer its result if no item is found @end table @node String-built ins @subsection String:@- built ins @table @b @meindex asCData:@- @item asCData:@- aCType Allocate memory with malloc for a NULL-terminated copy of the receiver, and return a pointer to it as a CObject of the given type. @meindex at:@- @item at:@- anIndex Answer the index-th indexed instance variable of the receiver @meindex at:@-ifAbsent:@- @item at:@- anIndex ifAbsent:@- aBlock Answer the index-th indexed instance variable of the receiver @meindex at:@-put:@- @item at:@- anIndex put:@- value Store value in the index-th indexed instance variable of the receiver @meindex basicAt:@- @item basicAt:@- anIndex Answer the index-th indexed instance variable of the receiver. This method must not be overridden, override at:@- instead @meindex basicAt:@-put:@- @item basicAt:@- anIndex put:@- value Store value in the index-th indexed instance variable of the receiver This method must not be overridden, override at:@-put:@- instead @meindex hash @item hash Answer an hash value for the receiver @meindex replaceFrom:@-to:@-with:@-startingAt:@- @item replaceFrom:@- start to:@- stop with:@- aString startingAt:@- replaceStart Replace the characters from start to stop with new characters whose ASCII codes are contained in aString, starting at the replaceStart location of aString @meindex replaceFrom:@-to:@-withByteArray:@-startingAt:@- @item replaceFrom:@- start to:@- stop withByteArray:@- byteArray startingAt:@- replaceStart Replace the characters from start to stop with new characters whose ASCII codes are contained in byteArray, starting at the replaceStart location of byteArray @meindex similarityTo:@- @item similarityTo:@- aString Answer a number that denotes the similarity between aString and the receiver. 0 indicates equality, negative numbers indicate some difference. Implemented as a primitive for speed. @meindex size @item size Answer the size of the receiver @end table @node String-CObject @subsection String:@- CObject @table @b @meindex asCData @item asCData Allocate memory with malloc for a NULL-terminated copy of the receiver, and return a pointer to it as a CChar. @end table @node String-converting @subsection String:@- converting @table @b @meindex asByteArray @item asByteArray Return the receiver, converted to a ByteArray of ASCII values @meindex asString @item asString But I already am a String! Really! @meindex asSymbol @item asSymbol Returns the symbol corresponding to the receiver @meindex encoding @item encoding Answer the encoding of the receiver. This is not implemented unless you load the Iconv package. @end table @node String-filesystem @subsection String:@- filesystem @table @b @meindex / @item / aName Answer a File object as appropriate for a file named 'aName' in the directory represented by the receiver. @meindex asFile @item asFile Answer a File object for the file whose name is in the receiver. @end table @node String-printing @subsection String:@- printing @table @b @meindex displayOn:@- @slindex printOn:@- @item displayOn:@- aStream Print a representation of the receiver on aStream. Unlike #printOn:@-, this method strips extra quotes. @meindex displayString @slindex printString @item displayString Answer a String representing the receiver. For most objects this is simply its #printString, but for CharacterArrays and characters, superfluous dollars or extra pair of quotes are stripped. @meindex isLiteralObject @item isLiteralObject Answer whether the receiver is expressible as a Smalltalk literal. @meindex printOn:@- @item printOn:@- aStream Print a representation of the receiver on aStream @meindex storeLiteralOn:@- @item storeLiteralOn:@- aStream Store a Smalltalk literal compiling to the receiver on aStream @meindex storeOn:@- @item storeOn:@- aStream Store Smalltalk code compiling to the receiver on aStream @end table @node String-regex @subsection String:@- regex @table @b @meindex =~ @item =~ pattern Answer a RegexResults object for matching the receiver against the Regex or String object pattern. @meindex allOccurrencesOfRegex:@- @item allOccurrencesOfRegex:@- pattern Find all the matches of pattern within the receiver and collect them into an OrderedCollection. @meindex allOccurrencesOfRegex:@-do:@- @item allOccurrencesOfRegex:@- pattern do:@- aBlock Find all the matches of pattern within the receiver and pass the RegexResults objects to aBlock. @meindex allOccurrencesOfRegex:@-from:@-to:@- @item allOccurrencesOfRegex:@- pattern from:@- from to:@- to Find all the matches of pattern within the receiver and within the given range of indices. Collect them into an OrderedCollection, which is then returned. @meindex allOccurrencesOfRegex:@-from:@-to:@-do:@- @item allOccurrencesOfRegex:@- pattern from:@- from to:@- to do:@- aBlock Find all the matches of pattern within the receiver and within the given range of indices. For each match, pass the RegexResults object to aBlock. @meindex asRegex @item asRegex Answer the receiver, converted to a Regex object. @meindex copyFrom:@-to:@-replacingAllRegex:@-with:@- @slindex % @item copyFrom:@- from to:@- to replacingAllRegex:@- pattern with:@- aStringOrBlock Returns the substring of the receiver between from and to. Any match of pattern in that part of the string is replaced using aStringOrBlock as follows:@- if it is a block, a RegexResults object is passed, while if it is a string, %n sequences are replaced with the captured subexpressions of the match (as in #%). @meindex copyFrom:@-to:@-replacingRegex:@-with:@- @slindex % @item copyFrom:@- from to:@- to replacingRegex:@- pattern with:@- aStringOrBlock Returns the substring of the receiver between from and to. If pattern has a match in that part of the string, the match is replaced using aStringOrBlock as follows:@- if it is a block, a RegexResults object is passed, while if it is a string, %n sequences are replaced with the captured subexpressions of the match (as in #%). @meindex copyReplacingAllRegex:@-with:@- @slindex % @item copyReplacingAllRegex:@- pattern with:@- aStringOrBlock Returns the receiver after replacing all the matches of pattern (if any) using aStringOrBlock as follows:@- if it is a block, a RegexResults object is passed, while if it is a string, %n sequences are replaced with the captured subexpressions of the match (as in #%). @meindex copyReplacingRegex:@-with:@- @slindex % @item copyReplacingRegex:@- pattern with:@- aStringOrBlock Returns the receiver after replacing the first match of pattern (if any) using aStringOrBlock as follows:@- if it is a block, a RegexResults object is passed, while if it is a string, %n sequences are replaced with the captured subexpressions of the match (as in #%). @meindex indexOfRegex:@- @item indexOfRegex:@- regexString If an occurrence of the regex is present in the receiver, return the Interval corresponding to the leftmost-longest match. Otherwise return nil. @meindex indexOfRegex:@-from:@-to:@- @item indexOfRegex:@- regexString from:@- from to:@- to If an occurrence of the regex is present in the receiver, return the Interval corresponding to the leftmost-longest match occurring within the given range of indices. Otherwise return nil. @meindex indexOfRegex:@-from:@-to:@-ifAbsent:@- @item indexOfRegex:@- regexString from:@- from to:@- to ifAbsent:@- excBlock If an occurrence of the regex is present in the receiver, return the Interval corresponding to the leftmost-longest match occurring within the given indices. Otherwise, evaluate excBlock and return the result. @meindex indexOfRegex:@-ifAbsent:@- @item indexOfRegex:@- regexString ifAbsent:@- excBlock If an occurrence of the regex is present in the receiver, return the Interval corresponding to the leftmost-longest match. Otherwise, evaluate excBlock and return the result. @meindex indexOfRegex:@-startingAt:@- @item indexOfRegex:@- regexString startingAt:@- index If an occurrence of the regex is present in the receiver, return the Interval corresponding to the leftmost-longest match starting after the given index. Otherwise return nil. @meindex indexOfRegex:@-startingAt:@-ifAbsent:@- @item indexOfRegex:@- regexString startingAt:@- index ifAbsent:@- excBlock If an occurrence of the regex is present in the receiver, return the Interval corresponding to the leftmost-longest match starting after the given index. Otherwise, evaluate excBlock and return the result. @meindex matchRegex:@- @item matchRegex:@- pattern Answer whether the receiver is an exact match for the pattern. This means that the pattern is implicitly anchored at the beginning and the end. @meindex matchRegex:@-from:@-to:@- @item matchRegex:@- pattern from:@- from to:@- to Answer whether the given range of indices is an exact match for the pattern. This means that there is a match starting at from and ending at to (which is not necessarily the longest match starting at from). @meindex occurrencesOfRegex:@- @item occurrencesOfRegex:@- pattern Returns count of how many times pattern repeats in the receiver. @meindex occurrencesOfRegex:@-from:@-to:@- @item occurrencesOfRegex:@- pattern from:@- from to:@- to Return a count of how many times pattern repeats in the receiver within the given range of index. @meindex occurrencesOfRegex:@-startingAt:@- @item occurrencesOfRegex:@- pattern startingAt:@- index Returns count of how many times pattern repeats in the receiver, starting the search at the given index. @meindex onOccurrencesOfRegex:@-do:@- @item onOccurrencesOfRegex:@- pattern do:@- body Find all the matches of pattern within the receiver and, for each match, pass the RegexResults object to aBlock. @meindex onOccurrencesOfRegex:@-from:@-to:@-do:@- @item onOccurrencesOfRegex:@- pattern from:@- from to:@- to do:@- aBlock Find all the matches of pattern within the receiver and within the given range of indices. For each match, pass the RegexResults object to aBlock. @meindex replacingAllRegex:@-with:@- @slindex % @item replacingAllRegex:@- pattern with:@- aStringOrBlock Returns the receiver if the pattern has no match in it. Otherwise, any match of pattern in that part of the string is replaced using aStringOrBlock as follows:@- if it is a block, a RegexResults object is passed, while if it is a string, %n sequences are replaced with the captured subexpressions of the match (as in #%). @meindex replacingRegex:@-with:@- @slindex % @item replacingRegex:@- pattern with:@- aStringOrBlock Returns the receiver if the pattern has no match in it. If it has a match, it is replaced using aStringOrBlock as follows:@- if it is a block, a RegexResults object is passed, while if it is a string, %n sequences are replaced with the captured subexpressions of the match (as in #%). @meindex searchRegex:@- @slindex =~ @item searchRegex:@- pattern A synonym for #=~. Answer a RegexResults object for matching the receiver against the Regex or String object pattern. @meindex searchRegex:@-from:@-to:@- @item searchRegex:@- pattern from:@- from to:@- to Answer a RegexResults object for matching the receiver against the Regex or String object pattern, restricting the match to the specified range of indices. @meindex searchRegex:@-startingAt:@- @item searchRegex:@- pattern startingAt:@- anIndex Answer a RegexResults object for matching the receiver against the Regex or String object pattern, starting the match at index anIndex. @meindex tokenize:@- @item tokenize:@- pattern Split the receiver at every occurrence of pattern. All parts that do not match pattern are separated and stored into an Array of Strings that is returned. @meindex tokenize:@-from:@-to:@- @item tokenize:@- pattern from:@- from to:@- to Split the receiver at every occurrence of pattern (considering only the indices between from and to). All parts that do not match pattern are separated and stored into an Array of Strings that is returned. @meindex ~ @item ~ pattern Answer whether the receiver matched against the Regex or String object pattern. @end table @node String-still unclassified @subsection String:@- still unclassified @table @b @meindex escapeRegex @item escapeRegex Answer the receiver with all regex special characters escaped by a backslash. @end table @node String-testing functionality @subsection String:@- testing functionality @table @b @meindex isString @item isString Answer `true'. @end table @node Symbol @section Symbol @clindex Symbol @table @b @item Defined in namespace Smalltalk @itemx Superclass: String @itemx Category: Language-Implementation My instances are unique throughout the Smalltalk system. My instances behave for the most part like strings, except that they print differently, and I guarantee that any two instances that have the same printed representation are in fact the same instance. @end table @menu * Symbol class-built ins:: (class) * Symbol class-instance creation:: (class) * Symbol class-symbol table:: (class) * Symbol-accessing the method dictionary:: (instance) * Symbol-basic:: (instance) * Symbol-built ins:: (instance) * Symbol-converting:: (instance) * Symbol-misc:: (instance) * Symbol-storing:: (instance) * Symbol-testing:: (instance) * Symbol-testing functionality:: (instance) @end menu @node Symbol class-built ins @subsection Symbol class:@- built ins @table @b @meindex intern:@- @item intern:@- aString Private - Same as 'aString asSymbol' @end table @node Symbol class-instance creation @subsection Symbol class:@- instance creation @table @b @meindex internCharacter:@- @item internCharacter:@- aCharacter Answer the one-character symbol associated to the given character. @meindex new @item new This method should not be called for instances of this class. @meindex new:@- @item new:@- size This method should not be called for instances of this class. @meindex with:@- @item with:@- element1 Answer a collection whose only element is element1 @meindex with:@-with:@- @item with:@- element1 with:@- element2 Answer a collection whose only elements are the parameters in the order they were passed @meindex with:@-with:@-with:@- @item with:@- element1 with:@- element2 with:@- element3 Answer a collection whose only elements are the parameters in the order they were passed @meindex with:@-with:@-with:@-with:@- @item with:@- element1 with:@- element2 with:@- element3 with:@- element4 Answer a collection whose only elements are the parameters in the order they were passed @meindex with:@-with:@-with:@-with:@-with:@- @item with:@- element1 with:@- element2 with:@- element3 with:@- element4 with:@- element5 Answer a collection whose only elements are the parameters in the order they were passed @end table @node Symbol class-symbol table @subsection Symbol class:@- symbol table @table @b @meindex hasInterned:@-ifTrue:@- @slindex hash @item hasInterned:@- aString ifTrue:@- aBlock If aString has not been interned yet, answer false. Else, pass the interned version to aBlock and answer true. Note that this works because String>>@-#hash calculates the same hash value used by the VM when interning strings into the SymbolTable. Changing one of the hashing methods without changing the other will break this method. @meindex isSymbolString:@- @slindex hash @item isSymbolString:@- aString Answer whether aString has already been interned. Note that this works because String>>@-#hash calculates the same hash value used by the VM when interning strings into the SymbolTable. Changing one of the hashing methods without changing the other will break this method. @meindex rebuildTable @slindex hash @item rebuildTable Rebuild the SymbolTable, thereby garbage-collecting unreferenced Symbols. While this process is done, preemption is disabled because it is not acceptable to leave the SymbolTable in a partially updated state. Note that this works because String>>@-#hash calculates the same hash value used by the VM when interning strings into the SymbolTable. Changing one of the hashing methods without changing the other will break this method. @end table @node Symbol-accessing the method dictionary @subsection Symbol:@- accessing the method dictionary @table @b @meindex implementors @item implementors Answer a Set of all the compiled method associated with selector named by the receiver, which is supposed to be a valid message name. @end table @node Symbol-basic @subsection Symbol:@- basic @table @b @meindex deepCopy @item deepCopy Returns a deep copy of the receiver. As Symbols are identity objects, we actually return the receiver itself. @meindex keywords @slindex + @slindex not @slindex printOn:@- @slindex ifTrue:@-ifFalse:@- @item keywords Answer an array of keywords that compose the receiver, which is supposed to be a valid message name (@-#+, #not, #printOn:@-, #ifTrue:@-ifFalse:@-, etc.) @meindex numArgs @slindex + @slindex not @slindex printOn:@- @slindex ifTrue:@-ifFalse:@- @item numArgs Answer the number of arguments supported by the receiver, which is supposed to be a valid message name (@-#+, #not, #printOn:@-, #ifTrue:@-ifFalse:@-, etc.) @meindex shallowCopy @item shallowCopy Returns a deep copy of the receiver. As Symbols are identity objects, we actually return the receiver itself. @end table @node Symbol-built ins @subsection Symbol:@- built ins @table @b @meindex = @item = aSymbol Answer whether the receiver and aSymbol are the same object @meindex hash @item hash Answer an hash value for the receiver. Symbols are optimized for speed @end table @node Symbol-converting @subsection Symbol:@- converting @table @b @meindex asString @item asString Answer a String with the same characters as the receiver @meindex asSymbol @item asSymbol But we are already a Symbol, and furthermore, Symbols are identity objects! So answer the receiver. @end table @node Symbol-misc @subsection Symbol:@- misc @table @b @meindex species @item species Answer `String'. @end table @node Symbol-storing @subsection Symbol:@- storing @table @b @meindex displayOn:@- @slindex printOn:@- @item displayOn:@- aStream Print a represention of the receiver on aStream. For most objects this is simply its #printOn:@- representation, but for strings and characters, superfluous dollars or extra pairs of quotes are stripped. @meindex displayString @slindex printString @item displayString Answer a String representing the receiver. For most objects this is simply its #printString, but for strings and characters, superfluous dollars or extra pair of quotes are stripped. @meindex printOn:@- @item printOn:@- aStream Print a represention of the receiver on aStream. @meindex storeLiteralOn:@- @item storeLiteralOn:@- aStream Print Smalltalk code on aStream that compiles to the same symbol as the receiver. @meindex storeOn:@- @item storeOn:@- aStream Print Smalltalk code on aStream that compiles to the same symbol as the receiver. @end table @node Symbol-testing @subsection Symbol:@- testing @table @b @meindex isSimpleSymbol @item isSimpleSymbol Answer whether the receiver must be represented in quoted-string (e.g. #'abc-def') form. @end table @node Symbol-testing functionality @subsection Symbol:@- testing functionality @table @b @meindex isString @item isString Answer `false'. @meindex isSymbol @item isSymbol Answer `true'. @end table @node SymLink @section SymLink @clindex SymLink @table @b @item Defined in namespace Smalltalk @itemx Superclass: Link @itemx Category: Language-Implementation I am used to implement the Smalltalk symbol table. My instances are links that contain symbols, and the symbol table basically a hash table that points to chains of my instances. @end table @menu * SymLink class-instance creation:: (class) * SymLink-accessing:: (instance) * SymLink-iteration:: (instance) * SymLink-printing:: (instance) @end menu @node SymLink class-instance creation @subsection SymLink class:@- instance creation @table @b @meindex symbol:@-nextLink:@- @item symbol:@- aSymbol nextLink:@- aSymLink Answer a new SymLink, which refers to aSymbol and points to aSymLink as the next SymLink in the chain. @end table @node SymLink-accessing @subsection SymLink:@- accessing @table @b @meindex symbol @item symbol Answer the Symbol that the receiver refers to in the symbol table. @meindex symbol:@- @item symbol:@- aSymbol Set the Symbol that the receiver refers to in the symbol table. @end table @node SymLink-iteration @subsection SymLink:@- iteration @table @b @meindex do:@- @item do:@- aBlock Evaluate aBlock for each symbol in the list @end table @node SymLink-printing @subsection SymLink:@- printing @table @b @meindex printOn:@- @item printOn:@- aStream Print a representation of the receiver on aStream. @end table @node SystemDictionary @section SystemDictionary @clindex SystemDictionary @table @b @item Defined in namespace Smalltalk @itemx Superclass: RootNamespace @itemx Category: Language-Implementation I am a special namespace. I only have one instance, called "Smalltalk", which is known to the Smalltalk interpreter. I define several methods that are "system" related, such as #quitPrimitive. My instance also helps keep track of dependencies between objects. @end table @menu * SystemDictionary class-initialization:: (class) * SystemDictionary-basic:: (instance) * SystemDictionary-builtins:: (instance) * SystemDictionary-c call-outs:: (instance) * SystemDictionary-command-line:: (instance) * SystemDictionary-miscellaneous:: (instance) * SystemDictionary-printing:: (instance) * SystemDictionary-profiling:: (instance) * SystemDictionary-special accessing:: (instance) * SystemDictionary-testing:: (instance) @end menu @node SystemDictionary class-initialization @subsection SystemDictionary class:@- initialization @table @b @meindex initialize @item initialize Create the kernel's private namespace. @end table @node SystemDictionary-basic @subsection SystemDictionary:@- basic @table @b @meindex halt @item halt Interrupt interpreter @meindex hash @item hash Smalltalk usually contains a reference to itself, avoid infinite loops @end table @node SystemDictionary-builtins @subsection SystemDictionary:@- builtins @table @b @meindex basicBacktrace @item basicBacktrace Prints the method invocation stack backtrace, as an aid to debugging @meindex byteCodeCounter @item byteCodeCounter Answer the number of bytecodes executed by the VM @meindex debug @item debug This methods provides a way to break in the VM code. Set a breakpoint in _gst_debug and call this method near the point where you think the bug happens. @meindex declarationTrace @item declarationTrace Answer whether compiled bytecodes are printed on stdout @meindex declarationTrace:@- @item declarationTrace:@- aBoolean Set whether compiled bytecodes are printed on stdout @meindex executionTrace @item executionTrace Answer whether executed bytecodes are printed on stdout @meindex executionTrace:@- @item executionTrace:@- aBoolean Set whether executed bytecodes are printed on stdout @meindex getTraceFlag:@- @item getTraceFlag:@- anIndex Private - Returns a boolean value which is one of the interpreter's tracing flags @meindex setTraceFlag:@-to:@- @item setTraceFlag:@- anIndex to:@- aBoolean Private - Sets the value of one of the interpreter's tracing flags (indicated by 'anIndex') to the value aBoolean. @meindex verboseTrace @item verboseTrace Answer whether execution tracing prints the object on the stack top @meindex verboseTrace:@- @item verboseTrace:@- aBoolean Set whether execution tracing prints the object on the stack top @end table @node SystemDictionary-c call-outs @subsection SystemDictionary:@- c call-outs @table @b @meindex environ @item environ Not commented. @meindex getArgc @item getArgc Not commented. @meindex getArgv:@- @item getArgv:@- index Not commented. @meindex getenv:@- @item getenv:@- aString Not commented. @meindex putenv:@- @item putenv:@- aString Not commented. @meindex system:@- @item system:@- aString Not commented. @meindex system:@-withArguments:@- @item system:@- aString withArguments:@- args Not commented. @end table @node SystemDictionary-command-line @subsection SystemDictionary:@- command-line @table @b @meindex arguments:@-do:@- @slindex arguments:@-do:@-ifError:@- @item arguments:@- pattern do:@- actionBlock Parse the command-line arguments according to the syntax specified in pattern. For every command-line option found, the two-argument block actionBlock is evaluated passing the option name and the argument. For file names (or in general, other command-line arguments than options) the block's first argument will be nil. For options without arguments, or with unspecified optional arguments, the block's second argument will be nil. The option name will be passed as a character object for short options, and as a string for long options. If an error is found, nil is returned. For more information on the syntax of pattern, see #arguments:@-do:@-ifError:@-. @meindex arguments:@-do:@-ifError:@- @item arguments:@- pattern do:@- actionBlock ifError:@- errorBlock Parse the command-line arguments according to the syntax specified in pattern. For every command-line option found, the two-argument block actionBlock is evaluated passing the option name and the argument. For file names (or in general, other command-line arguments than options) the block's first argument will be nil. For options without arguments, or with unspecified optional arguments, the block's second argument will be nil. The option name will be passed as a character object for short options, and as a string for long options. If an error is found, the parsing is interrupted, errorBlock is evaluated, and the returned value is answered. Every whitespace-separated part (`word') of pattern specifies a command-line option. If a word ends with a colon, the option will have a mandatory argument. If a word ends with two colons, the option will have an optional argument. Before the colons, multiple option names (either short names like `-l' or long names like `--long') can be specified. Before passing the option to actionBlock, the name will be canonicalized to the last one. Prefixes of long options are accepted as long as they're unique, and they are canonicalized to the full name before passing it to actionBlock. Additionally, the full name of an option is accepted even if it is the prefix of a longer option. Mandatory arguments can appear in the next argument, or in the same argument (separated by an = for arguments to long options). Optional arguments must appear in the same argument. @end table @node SystemDictionary-miscellaneous @subsection SystemDictionary:@- miscellaneous @table @b @meindex arguments @item arguments Return the command line arguments after the -a switch @meindex backtrace @item backtrace Print a backtrace on the Transcript. @meindex hostSystem @item hostSystem Answer the triplet corresponding to the system for which GNU Smalltalk was built. @end table @node SystemDictionary-printing @subsection SystemDictionary:@- printing @table @b @meindex nameIn:@- @item nameIn:@- aNamespace Answer `'Smalltalk''. @meindex printOn:@-in:@- @item printOn:@- aStream in:@- aNamespace Store Smalltalk code compiling to the receiver @meindex storeOn:@- @item storeOn:@- aStream Store Smalltalk code compiling to the receiver @end table @node SystemDictionary-profiling @subsection SystemDictionary:@- profiling @table @b @meindex rawProfile:@- @item rawProfile:@- anIdentityDictionary Set the raw profile to be anIdentityDictionary and return the old one. @end table @node SystemDictionary-special accessing @subsection SystemDictionary:@- special accessing @table @b @meindex addFeature:@- @item addFeature:@- aFeature Add the aFeature feature to the Features set @meindex hasFeatures:@- @item hasFeatures:@- features Returns true if the feature or features in 'features' is one of the implementation dependent features present @meindex removeFeature:@- @item removeFeature:@- aFeature Remove the aFeature feature to the Features set @meindex version @item version Answer the current version of the GNU Smalltalk environment @end table @node SystemDictionary-testing @subsection SystemDictionary:@- testing @table @b @meindex imageLocal @item imageLocal Answer whether the kernel directory is a subdirectory of the image directory (non-local image) or not. @meindex isSmalltalk @item isSmalltalk Answer `true'. @end table @node SystemExceptions.AlreadyDefined @section SystemExceptions.AlreadyDefined @clindex SystemExceptions.AlreadyDefined @table @b @item Defined in namespace Smalltalk.SystemExceptions @itemx Superclass: SystemExceptions.InvalidArgument @itemx Category: Language-Exceptions I am raised when one tries to define a symbol (class or pool variable) that is already defined. @end table @menu * SystemExceptions.AlreadyDefined-accessing:: (instance) @end menu @node SystemExceptions.AlreadyDefined-accessing @subsection SystemExceptions.AlreadyDefined:@- accessing @table @b @meindex description @item description Answer a description for the error @end table @node SystemExceptions.ArgumentOutOfRange @section SystemExceptions.ArgumentOutOfRange @clindex SystemExceptions.ArgumentOutOfRange @table @b @item Defined in namespace Smalltalk.SystemExceptions @itemx Superclass: SystemExceptions.InvalidArgument @itemx Category: Language-Exceptions I am raised when one invokes a method with an argument outside of its valid range. @end table @menu * SystemExceptions.ArgumentOutOfRange class-signaling:: (class) * SystemExceptions.ArgumentOutOfRange-accessing:: (instance) @end menu @node SystemExceptions.ArgumentOutOfRange class-signaling @subsection SystemExceptions.ArgumentOutOfRange class:@- signaling @table @b @meindex signalOn:@-mustBeBetween:@-and:@- @item signalOn:@- value mustBeBetween:@- low and:@- high Raise the exception. The given value was not between low and high. @end table @node SystemExceptions.ArgumentOutOfRange-accessing @subsection SystemExceptions.ArgumentOutOfRange:@- accessing @table @b @meindex description @item description Answer a textual description of the exception. @meindex high @item high Answer the highest value that was permitted. @meindex high:@- @item high:@- aMagnitude Set the highest value that was permitted. @meindex low @item low Answer the lowest value that was permitted. @meindex low:@- @item low:@- aMagnitude Set the lowest value that was permitted. @end table @node SystemExceptions.BadReturn @section SystemExceptions.BadReturn @clindex SystemExceptions.BadReturn @table @b @item Defined in namespace Smalltalk.SystemExceptions @itemx Superclass: SystemExceptions.VMError @itemx Category: Language-Exceptions I am raised when one tries to return from an already-terminated method. @end table @menu * SystemExceptions.BadReturn-accessing:: (instance) @end menu @node SystemExceptions.BadReturn-accessing @subsection SystemExceptions.BadReturn:@- accessing @table @b @meindex description @item description Answer a textual description of the exception. @end table @node SystemExceptions.CInterfaceError @section SystemExceptions.CInterfaceError @clindex SystemExceptions.CInterfaceError @table @b @item Defined in namespace Smalltalk.SystemExceptions @itemx Superclass: SystemExceptions.PrimitiveFailed @itemx Category: Language-Exceptions I am raised when an error happens that is related to the C interface. @end table @menu * SystemExceptions.CInterfaceError-accessing:: (instance) @end menu @node SystemExceptions.CInterfaceError-accessing @subsection SystemExceptions.CInterfaceError:@- accessing @table @b @meindex description @item description Answer a textual description of the exception. @end table @node SystemExceptions.EmptyCollection @section SystemExceptions.EmptyCollection @clindex SystemExceptions.EmptyCollection @table @b @item Defined in namespace Smalltalk.SystemExceptions @itemx Superclass: SystemExceptions.InvalidValue @itemx Category: Language-Exceptions I am raised when one invokes a method on an empty collection. @end table @menu * SystemExceptions.EmptyCollection-accessing:: (instance) @end menu @node SystemExceptions.EmptyCollection-accessing @subsection SystemExceptions.EmptyCollection:@- accessing @table @b @meindex description @item description Answer a textual description of the exception. @end table @node SystemExceptions.EndOfStream @section SystemExceptions.EndOfStream @clindex SystemExceptions.EndOfStream @table @b @item Defined in namespace Smalltalk.SystemExceptions @itemx Superclass: Notification @itemx Category: Language-Exceptions I am raised when a stream reaches its end. @end table @menu * SystemExceptions.EndOfStream class-signaling:: (class) * SystemExceptions.EndOfStream-accessing:: (instance) @end menu @node SystemExceptions.EndOfStream class-signaling @subsection SystemExceptions.EndOfStream class:@- signaling @table @b @meindex signalOn:@- @item signalOn:@- stream Answer an exception reporting the parameter has reached its end. @end table @node SystemExceptions.EndOfStream-accessing @subsection SystemExceptions.EndOfStream:@- accessing @table @b @meindex description @item description Answer a textual description of the exception. @meindex stream @item stream Answer the stream whose end was reached. @meindex stream:@- @item stream:@- anObject Set the stream whose end was reached. @end table @node SystemExceptions.FileError @section SystemExceptions.FileError @clindex SystemExceptions.FileError @table @b @item Defined in namespace Smalltalk.SystemExceptions @itemx Superclass: SystemExceptions.PrimitiveFailed @itemx Category: Language-Exceptions I am raised when an error happens that is related to the file system. @end table @menu * SystemExceptions.FileError-accessing:: (instance) @end menu @node SystemExceptions.FileError-accessing @subsection SystemExceptions.FileError:@- accessing @table @b @meindex description @item description Answer a textual description of the exception. @end table @node SystemExceptions.IndexOutOfRange @section SystemExceptions.IndexOutOfRange @clindex SystemExceptions.IndexOutOfRange @table @b @item Defined in namespace Smalltalk.SystemExceptions @itemx Superclass: SystemExceptions.ArgumentOutOfRange @itemx Category: Language-Exceptions I am raised when one invokes am accessor method with an index outside of its valid range. @end table @menu * SystemExceptions.IndexOutOfRange class-signaling:: (class) * SystemExceptions.IndexOutOfRange-accessing:: (instance) @end menu @node SystemExceptions.IndexOutOfRange class-signaling @subsection SystemExceptions.IndexOutOfRange class:@- signaling @table @b @meindex signalOn:@-withIndex:@- @item signalOn:@- aCollection withIndex:@- value The given index was out of range in aCollection. @end table @node SystemExceptions.IndexOutOfRange-accessing @subsection SystemExceptions.IndexOutOfRange:@- accessing @table @b @meindex collection @item collection Answer the collection that triggered the error @meindex collection:@- @item collection:@- anObject Set the collection that triggered the error @meindex description @item description Answer a textual description of the exception. @meindex messageText @item messageText Answer an exception's message text. @end table @node SystemExceptions.InvalidArgument @section SystemExceptions.InvalidArgument @clindex SystemExceptions.InvalidArgument @table @b @item Defined in namespace Smalltalk.SystemExceptions @itemx Superclass: SystemExceptions.InvalidValue @itemx Category: Language-Exceptions I am raised when one invokes a method with an invalid argument. @end table @menu * SystemExceptions.InvalidArgument-accessing:: (instance) @end menu @node SystemExceptions.InvalidArgument-accessing @subsection SystemExceptions.InvalidArgument:@- accessing @table @b @meindex messageText @item messageText Answer an exception's message text. @end table @node SystemExceptions.InvalidProcessState @section SystemExceptions.InvalidProcessState @clindex SystemExceptions.InvalidProcessState @table @b @item Defined in namespace Smalltalk.SystemExceptions @itemx Superclass: SystemExceptions.InvalidValue @itemx Category: Language-Exceptions I am an error raised when trying to resume a terminated process, or stuff like that. @end table @menu * SystemExceptions.InvalidProcessState-accessing:: (instance) @end menu @node SystemExceptions.InvalidProcessState-accessing @subsection SystemExceptions.InvalidProcessState:@- accessing @table @b @meindex description @item description Answer a textual description of the exception. @end table @node SystemExceptions.InvalidSize @section SystemExceptions.InvalidSize @clindex SystemExceptions.InvalidSize @table @b @item Defined in namespace Smalltalk.SystemExceptions @itemx Superclass: SystemExceptions.InvalidArgument @itemx Category: Language-Exceptions I am raised when an argument has an invalid size. @end table @menu * SystemExceptions.InvalidSize-accessing:: (instance) @end menu @node SystemExceptions.InvalidSize-accessing @subsection SystemExceptions.InvalidSize:@- accessing @table @b @meindex description @item description Answer a textual description of the exception. @end table @node SystemExceptions.InvalidState @section SystemExceptions.InvalidState @clindex SystemExceptions.InvalidState @table @b @item Defined in namespace Smalltalk.SystemExceptions @itemx Superclass: SystemExceptions.InvalidValue @itemx Category: Language-Exceptions I am raised when one invokes a method and the receiver or an argument are in an invalid state for the method. @end table @menu * SystemExceptions.InvalidState-accessing:: (instance) @end menu @node SystemExceptions.InvalidState-accessing @subsection SystemExceptions.InvalidState:@- accessing @table @b @meindex messageText @item messageText Answer an exception's message text. @end table @node SystemExceptions.InvalidValue @section SystemExceptions.InvalidValue @clindex SystemExceptions.InvalidValue @table @b @item Defined in namespace Smalltalk.SystemExceptions @itemx Superclass: Error @itemx Category: Language-Exceptions I am raised when one invokes a method with an invalid receiver or argument. @end table @menu * SystemExceptions.InvalidValue class-signaling:: (class) * SystemExceptions.InvalidValue-accessing:: (instance) @end menu @node SystemExceptions.InvalidValue class-signaling @subsection SystemExceptions.InvalidValue class:@- signaling @table @b @meindex signalOn:@- @item signalOn:@- value Answer an exception reporting the parameter as invalid. @meindex signalOn:@-reason:@- @item signalOn:@- value reason:@- reason Answer an exception reporting `value' as invalid, for the given reason. @end table @node SystemExceptions.InvalidValue-accessing @subsection SystemExceptions.InvalidValue:@- accessing @table @b @meindex description @item description Answer a textual description of the exception. @meindex messageText @item messageText Answer an exception's message text. @meindex value @item value Answer the object that was found to be invalid. @meindex value:@- @item value:@- anObject Set the object that was found to be invalid. @end table @node SystemExceptions.MustBeBoolean @section SystemExceptions.MustBeBoolean @clindex SystemExceptions.MustBeBoolean @table @b @item Defined in namespace Smalltalk.SystemExceptions @itemx Superclass: SystemExceptions.WrongClass @itemx Category: Language-Exceptions I am raised when one invokes a boolean method on a non-boolean. @end table @menu * SystemExceptions.MustBeBoolean class-signaling:: (class) @end menu @node SystemExceptions.MustBeBoolean class-signaling @subsection SystemExceptions.MustBeBoolean class:@- signaling @table @b @meindex signalOn:@- @item signalOn:@- anObject Signal a new exception, with the bad value in question being anObject. @end table @node SystemExceptions.MutationError @section SystemExceptions.MutationError @clindex SystemExceptions.MutationError @table @b @item Defined in namespace Smalltalk.SystemExceptions @itemx Superclass: Error @itemx Category: Language-Exceptions I am an error raised when a class is mutated in an invalid way. @end table @menu * SystemExceptions.MutationError class-instance creation:: (class) * SystemExceptions.MutationError-accessing:: (instance) @end menu @node SystemExceptions.MutationError class-instance creation @subsection SystemExceptions.MutationError class:@- instance creation @table @b @meindex new @item new Create an instance of the receiver, which you will be able to signal later. @end table @node SystemExceptions.MutationError-accessing @subsection SystemExceptions.MutationError:@- accessing @table @b @meindex description @item description Answer a textual description of the exception. @end table @node SystemExceptions.NoRunnableProcess @section SystemExceptions.NoRunnableProcess @clindex SystemExceptions.NoRunnableProcess @table @b @item Defined in namespace Smalltalk.SystemExceptions @itemx Superclass: SystemExceptions.VMError @itemx Category: Language-Exceptions I am raised when no runnable process can be found in the image. @end table @menu * SystemExceptions.NoRunnableProcess-accessing:: (instance) @end menu @node SystemExceptions.NoRunnableProcess-accessing @subsection SystemExceptions.NoRunnableProcess:@- accessing @table @b @meindex description @item description Answer a textual description of the exception. @end table @node SystemExceptions.NotEnoughElements @section SystemExceptions.NotEnoughElements @clindex SystemExceptions.NotEnoughElements @table @b @item Defined in namespace Smalltalk.SystemExceptions @itemx Superclass: Error @itemx Category: Language-Exceptions I am raised when one invokes #next:@- but not enough items remain in the stream. @end table @menu * SystemExceptions.NotEnoughElements class-signaling:: (class) * SystemExceptions.NotEnoughElements-accessing:: (instance) @end menu @node SystemExceptions.NotEnoughElements class-signaling @subsection SystemExceptions.NotEnoughElements class:@- signaling @table @b @meindex signalOn:@- @item signalOn:@- remainingCount Answer an exception reporting the parameter as invalid. @end table @node SystemExceptions.NotEnoughElements-accessing @subsection SystemExceptions.NotEnoughElements:@- accessing @table @b @meindex description @item description Answer a textual description of the exception. @meindex messageText @item messageText Answer an exception's message text. @meindex remainingCount @item remainingCount Answer the number of items that were to be read. @meindex remainingCount:@- @item remainingCount:@- anObject Set the number of items that were to be read. @end table @node SystemExceptions.NotFound @section SystemExceptions.NotFound @clindex SystemExceptions.NotFound @table @b @item Defined in namespace Smalltalk.SystemExceptions @itemx Superclass: SystemExceptions.InvalidArgument @itemx Category: Language-Exceptions I am raised when something is searched without success. @end table @menu * SystemExceptions.NotFound class-accessing:: (class) * SystemExceptions.NotFound-accessing:: (instance) @end menu @node SystemExceptions.NotFound class-accessing @subsection SystemExceptions.NotFound class:@- accessing @table @b @meindex signalOn:@-reason:@- @item signalOn:@- value reason:@- aString Raise an exception:@- reason specifies the reason of the exception. @meindex signalOn:@-what:@- @item signalOn:@- value what:@- aString Raise an exception; aString specifies what was not found (a key, an object, a class, and so on). @end table @node SystemExceptions.NotFound-accessing @subsection SystemExceptions.NotFound:@- accessing @table @b @meindex description @item description Answer a textual description of the exception. @end table @node SystemExceptions.NotImplemented @section SystemExceptions.NotImplemented @clindex SystemExceptions.NotImplemented @table @b @item Defined in namespace Smalltalk.SystemExceptions @itemx Superclass: Error @itemx Category: Language-Exceptions I am raised when a method is called that has not been implemented. @end table @menu * SystemExceptions.NotImplemented-accessing:: (instance) @end menu @node SystemExceptions.NotImplemented-accessing @subsection SystemExceptions.NotImplemented:@- accessing @table @b @meindex description @item description Answer a textual description of the exception. @end table @node SystemExceptions.NotIndexable @section SystemExceptions.NotIndexable @clindex SystemExceptions.NotIndexable @table @b @item Defined in namespace Smalltalk.SystemExceptions @itemx Superclass: SystemExceptions.InvalidValue @itemx Category: Language-Exceptions I am raised when an object is not indexable. @end table @menu * SystemExceptions.NotIndexable-accessing:: (instance) @end menu @node SystemExceptions.NotIndexable-accessing @subsection SystemExceptions.NotIndexable:@- accessing @table @b @meindex description @item description Answer a textual description of the exception. @end table @node SystemExceptions.NotYetImplemented @section SystemExceptions.NotYetImplemented @clindex SystemExceptions.NotYetImplemented @table @b @item Defined in namespace Smalltalk.SystemExceptions @itemx Superclass: SystemExceptions.NotImplemented @itemx Category: Language-Exceptions I am raised when a method is called that has not been implemented yet. @end table @menu * SystemExceptions.NotYetImplemented-accessing:: (instance) @end menu @node SystemExceptions.NotYetImplemented-accessing @subsection SystemExceptions.NotYetImplemented:@- accessing @table @b @meindex description @item description Answer a textual description of the exception. @end table @node SystemExceptions.PackageNotAvailable @section SystemExceptions.PackageNotAvailable @clindex SystemExceptions.PackageNotAvailable @table @b @item Defined in namespace Smalltalk.SystemExceptions @itemx Superclass: SystemExceptions.NotFound @itemx Category: Language-Packaging @end table @menu * SystemExceptions.PackageNotAvailable class-still unclassified:: (class) * SystemExceptions.PackageNotAvailable-description:: (instance) @end menu @node SystemExceptions.PackageNotAvailable class-still unclassified @subsection SystemExceptions.PackageNotAvailable class:@- still unclassified @table @b @meindex signal:@- @item signal:@- aString Signal an exception saying that the package named aString can't be found. @meindex signal:@-reason:@- @item signal:@- package reason:@- reason Signal an exception saying that be package named package can't be found because the reason named reason. @end table @node SystemExceptions.PackageNotAvailable-description @subsection SystemExceptions.PackageNotAvailable:@- description @table @b @meindex isResumable @item isResumable Answer true. Package unavailability is resumable, because the package files might just lie elsewhere. @end table @node SystemExceptions.PrimitiveFailed @section SystemExceptions.PrimitiveFailed @clindex SystemExceptions.PrimitiveFailed @table @b @item Defined in namespace Smalltalk.SystemExceptions @itemx Superclass: SystemExceptions.VMError @itemx Category: Language-Exceptions I am raised when a primitive fails for some reason. @end table @menu * SystemExceptions.PrimitiveFailed-accessing:: (instance) @end menu @node SystemExceptions.PrimitiveFailed-accessing @subsection SystemExceptions.PrimitiveFailed:@- accessing @table @b @meindex description @item description Answer a textual description of the exception. @end table @node SystemExceptions.ProcessBeingTerminated @section SystemExceptions.ProcessBeingTerminated @clindex SystemExceptions.ProcessBeingTerminated @table @b @item Defined in namespace Smalltalk.SystemExceptions @itemx Superclass: Notification @itemx Category: Language-Exceptions I am raised when a process is terminated. @end table @menu * SystemExceptions.ProcessBeingTerminated class-still unclassified:: (class) * SystemExceptions.ProcessBeingTerminated-accessing:: (instance) @end menu @node SystemExceptions.ProcessBeingTerminated class-still unclassified @subsection SystemExceptions.ProcessBeingTerminated class:@- still unclassified @table @b @meindex initialize @item initialize Not commented. @end table @node SystemExceptions.ProcessBeingTerminated-accessing @subsection SystemExceptions.ProcessBeingTerminated:@- accessing @table @b @meindex description @item description Answer a textual description of the exception. @meindex semaphore @item semaphore If the process was waiting on a semaphore, answer it. @meindex semaphore:@- @item semaphore:@- aSemaphore If the process was waiting on a semaphore, answer it. @end table @node SystemExceptions.ProcessTerminated @section SystemExceptions.ProcessTerminated @clindex SystemExceptions.ProcessTerminated @table @b @item Defined in namespace Smalltalk.SystemExceptions @itemx Superclass: SystemExceptions.InvalidValue @itemx Category: Language-Exceptions I am raised when somebody tries to resume or interrupt a terminated process. @end table @menu * SystemExceptions.ProcessTerminated-accessing:: (instance) @end menu @node SystemExceptions.ProcessTerminated-accessing @subsection SystemExceptions.ProcessTerminated:@- accessing @table @b @meindex description @item description Answer a textual description of the exception. @end table @node SystemExceptions.ReadOnlyObject @section SystemExceptions.ReadOnlyObject @clindex SystemExceptions.ReadOnlyObject @table @b @item Defined in namespace Smalltalk.SystemExceptions @itemx Superclass: SystemExceptions.InvalidValue @itemx Category: Language-Exceptions I am raised when one writes to a read-only object. @end table @menu * SystemExceptions.ReadOnlyObject-accessing:: (instance) @end menu @node SystemExceptions.ReadOnlyObject-accessing @subsection SystemExceptions.ReadOnlyObject:@- accessing @table @b @meindex description @item description Answer a textual description of the exception. @end table @node SystemExceptions.SecurityError @section SystemExceptions.SecurityError @clindex SystemExceptions.SecurityError @table @b @item Defined in namespace Smalltalk.SystemExceptions @itemx Superclass: SystemExceptions.VMError @itemx Category: Language-Exceptions I am an error raised when an untrusted object tries to do an insecure operation. @end table @menu * SystemExceptions.SecurityError class-accessing:: (class) * SystemExceptions.SecurityError-accessing:: (instance) @end menu @node SystemExceptions.SecurityError class-accessing @subsection SystemExceptions.SecurityError class:@- accessing @table @b @meindex signal:@- @item signal:@- aPermission Raise the exception, setting to aPermission the permission that was tested and failed. @end table @node SystemExceptions.SecurityError-accessing @subsection SystemExceptions.SecurityError:@- accessing @table @b @meindex description @item description Answer a textual description of the exception. @meindex failedPermission @item failedPermission Answer the permission that was tested and that failed. @meindex failedPermission:@- @item failedPermission:@- anObject Set which permission was tested and failed. @end table @node SystemExceptions.ShouldNotImplement @section SystemExceptions.ShouldNotImplement @clindex SystemExceptions.ShouldNotImplement @table @b @item Defined in namespace Smalltalk.SystemExceptions @itemx Superclass: SystemExceptions.NotImplemented @itemx Category: Language-Exceptions I am raised when a method is called that a class wishes that is not called. @end table @menu * SystemExceptions.ShouldNotImplement-accessing:: (instance) @end menu @node SystemExceptions.ShouldNotImplement-accessing @subsection SystemExceptions.ShouldNotImplement:@- accessing @table @b @meindex description @item description Answer a textual description of the exception. @end table @node SystemExceptions.SubclassResponsibility @section SystemExceptions.SubclassResponsibility @clindex SystemExceptions.SubclassResponsibility @table @b @item Defined in namespace Smalltalk.SystemExceptions @itemx Superclass: SystemExceptions.ShouldNotImplement @itemx Category: Language-Exceptions I am raised when a method is called whose implementation is the responsibility of concrete subclass. @end table @menu * SystemExceptions.SubclassResponsibility-accessing:: (instance) @end menu @node SystemExceptions.SubclassResponsibility-accessing @subsection SystemExceptions.SubclassResponsibility:@- accessing @table @b @meindex description @item description Answer a textual description of the exception. @end table @node SystemExceptions.UnhandledException @section SystemExceptions.UnhandledException @clindex SystemExceptions.UnhandledException @table @b @item Defined in namespace Smalltalk.SystemExceptions @itemx Superclass: Exception @itemx Category: Language-Exception I am raised when a backtrace is shown to terminate the current process. @end table @menu * SystemExceptions.UnhandledException-accessing:: (instance) @end menu @node SystemExceptions.UnhandledException-accessing @subsection SystemExceptions.UnhandledException:@- accessing @table @b @meindex defaultAction @item defaultAction Terminate the current process. @meindex description @item description Answer a textual description of the exception. @meindex originalException @item originalException Answer the uncaught exception. @meindex originalException:@- @item originalException:@- anObject Set the uncaught exception to anObject. @end table @node SystemExceptions.UserInterrupt @section SystemExceptions.UserInterrupt @clindex SystemExceptions.UserInterrupt @table @b @item Defined in namespace Smalltalk.SystemExceptions @itemx Superclass: SystemExceptions.VMError @itemx Category: Language-Exceptions I am raised when one presses Ctrl-C. @end table @menu * SystemExceptions.UserInterrupt-accessing:: (instance) @end menu @node SystemExceptions.UserInterrupt-accessing @subsection SystemExceptions.UserInterrupt:@- accessing @table @b @meindex description @item description Answer a textual description of the exception. @end table @node SystemExceptions.VerificationError @section SystemExceptions.VerificationError @clindex SystemExceptions.VerificationError @table @b @item Defined in namespace Smalltalk.SystemExceptions @itemx Superclass: SystemExceptions.VMError @itemx Category: Language-Exceptions I am raised when the verification of a method fails. @end table @menu * SystemExceptions.VerificationError-accessing:: (instance) @end menu @node SystemExceptions.VerificationError-accessing @subsection SystemExceptions.VerificationError:@- accessing @table @b @meindex description @item description Answer a textual description of the exception. @end table @node SystemExceptions.VMError @section SystemExceptions.VMError @clindex SystemExceptions.VMError @table @b @item Defined in namespace Smalltalk.SystemExceptions @itemx Superclass: Error @itemx Category: Language-Exceptions I am an error related to the innards of the system. @end table @menu * SystemExceptions.VMError-accessing:: (instance) @end menu @node SystemExceptions.VMError-accessing @subsection SystemExceptions.VMError:@- accessing @table @b @meindex description @item description Answer a textual description of the exception. @end table @node SystemExceptions.WrongArgumentCount @section SystemExceptions.WrongArgumentCount @clindex SystemExceptions.WrongArgumentCount @table @b @item Defined in namespace Smalltalk.SystemExceptions @itemx Superclass: SystemExceptions.PrimitiveFailed @itemx Category: Language-Exceptions I am raised when one tries to evaluate a method (via #perform:@-...) or a block but passes the wrong number of arguments. @end table @menu * SystemExceptions.WrongArgumentCount-accessing:: (instance) @end menu @node SystemExceptions.WrongArgumentCount-accessing @subsection SystemExceptions.WrongArgumentCount:@- accessing @table @b @meindex description @item description Answer a textual description of the exception. @end table @node SystemExceptions.WrongClass @section SystemExceptions.WrongClass @clindex SystemExceptions.WrongClass @table @b @item Defined in namespace Smalltalk.SystemExceptions @itemx Superclass: SystemExceptions.InvalidValue @itemx Category: Language-Exceptions I am raised when an argument is constrained to be an instance of a determinate class, and this constraint is not respected by the caller. @end table @menu * SystemExceptions.WrongClass class-signaling:: (class) * SystemExceptions.WrongClass-accessing:: (instance) @end menu @node SystemExceptions.WrongClass class-signaling @subsection SystemExceptions.WrongClass class:@- signaling @table @b @meindex signalOn:@-mustBe:@- @item signalOn:@- anObject mustBe:@- aClassOrArray Raise an exception. The given object should have been an instance of one of the classes indicated by aClassOrArray (which should be a single class or an array of classes). Whether instances of subclasses are allowed should be clear from the context, though in general (i.e. with the exception of a few system messages) they should be. @end table @node SystemExceptions.WrongClass-accessing @subsection SystemExceptions.WrongClass:@- accessing @table @b @meindex description @item description Answer a textual description of the exception. @meindex messageText @item messageText Answer an exception's message text. @meindex validClasses @item validClasses Answer the list of classes whose instances would have been valid. @meindex validClasses:@- @item validClasses:@- aCollection Set the list of classes whose instances would have been valid. @meindex validClassesString @item validClassesString Answer the list of classes whose instances would have been valid, formatted as a string. @end table @node SystemExceptions.WrongMessageSent @section SystemExceptions.WrongMessageSent @clindex SystemExceptions.WrongMessageSent @table @b @item Defined in namespace Smalltalk.SystemExceptions @itemx Superclass: SystemExceptions.ShouldNotImplement @itemx Category: Language-Exceptions I am raised when a method is called that a class wishes that is not called. This exception also includes a suggestion on which message should be sent instead @end table @menu * SystemExceptions.WrongMessageSent class-signaling:: (class) * SystemExceptions.WrongMessageSent-accessing:: (instance) @end menu @node SystemExceptions.WrongMessageSent class-signaling @subsection SystemExceptions.WrongMessageSent class:@- signaling @table @b @meindex signalOn:@-useInstead:@- @item signalOn:@- selector useInstead:@- aSymbol Raise an exception, signaling which selector was sent and suggesting a valid alternative. @end table @node SystemExceptions.WrongMessageSent-accessing @subsection SystemExceptions.WrongMessageSent:@- accessing @table @b @meindex messageText @item messageText Answer an exception's message text. @meindex selector @item selector Answer which selector was sent. @meindex selector:@- @item selector:@- aSymbol Set which selector was sent. @meindex suggestedSelector @item suggestedSelector Answer a valid alternative to the selector that was used. @meindex suggestedSelector:@- @item suggestedSelector:@- aSymbol Set a valid alternative to the selector that was used. @end table @node TextCollector @section TextCollector @clindex TextCollector @table @b @item Defined in namespace Smalltalk @itemx Superclass: Stream @itemx Category: Streams I am a thread-safe class that maps between standard Stream protocol and a single message to another object (its selector is pluggable and should roughly correspond to #nextPutAll:@-). I am, in fact, the class that implements the global Transcript object. @end table @menu * TextCollector class-accessing:: (class) * TextCollector-accessing:: (instance) * TextCollector-printing:: (instance) * TextCollector-set up:: (instance) * TextCollector-storing:: (instance) @end menu @node TextCollector class-accessing @subsection TextCollector class:@- accessing @table @b @meindex message:@- @item message:@- receiverToSelectorAssociation Answer a new instance of the receiver, that uses the message identified by anAssociation to perform write operations. anAssociation's key is the receiver, while its value is the selector. @meindex new @item new This method should not be called for instances of this class. @end table @node TextCollector-accessing @subsection TextCollector:@- accessing @table @b @meindex cr @item cr Emit a new-line (carriage return) to the Transcript @meindex critical:@- @item critical:@- aBlock Evaluate aBlock while holding the Transcript lock @meindex endEntry @item endEntry Emit two new-lines. This method is present for compatibility with VisualWorks. @meindex next:@-put:@- @item next:@- anInteger put:@- anObject Write anInteger copies of anObject to the Transcript @meindex next:@-putAll:@-startingAt:@- @item next:@- n putAll:@- aString startingAt:@- pos Write aString to the Transcript @meindex nextPut:@- @item nextPut:@- aCharacter Emit aCharacter to the Transcript @meindex show:@- @item show:@- aString Write aString to the Transcript @meindex showCr:@- @item showCr:@- aString Write aString to the Transcript, followed by a new-line character @meindex showOnNewLine:@- @item showOnNewLine:@- aString Write aString to the Transcript, preceded by a new-line character @end table @node TextCollector-printing @subsection TextCollector:@- printing @table @b @meindex print:@- @item print:@- anObject Print anObject's representation to the Transcript @meindex printOn:@- @item printOn:@- aStream Print a representation of the receiver onto aStream @end table @node TextCollector-set up @subsection TextCollector:@- set up @table @b @meindex message @item message Answer an association representing the message to be sent to perform write operations. The key is the receiver, the value is the selector @meindex message:@- @item message:@- receiverToSelectorAssociation Set the message to be sent to perform write operations to the one represented by anAssociation. anAssociation's key is the receiver, while its value is the selector @end table @node TextCollector-storing @subsection TextCollector:@- storing @table @b @meindex store:@- @item store:@- anObject Print Smalltalk code which evaluates to anObject on the Transcript @meindex storeOn:@- @item storeOn:@- aStream Print Smalltalk code which evaluates to the receiver onto aStream @end table @node Time @section Time @clindex Time @table @b @item Defined in namespace Smalltalk @itemx Superclass: Magnitude @itemx Category: Language-Data types My instances represent times of the day. I provide methods for instance creation, methods that access components (hours, minutes, and seconds) of a time value, and a block execution timing facility. @end table @menu * Time class-basic (UTC):: (class) * Time class-builtins:: (class) * Time class-clocks:: (class) * Time class-initialization:: (class) * Time class-instance creation:: (class) * Time-accessing (ANSI for DateAndTimes):: (instance) * Time-accessing (non ANSI & for Durations):: (instance) * Time-arithmetic:: (instance) * Time-comparing:: (instance) @end menu @node Time class-basic (UTC) @subsection Time class:@- basic (UTC) @table @b @meindex midnight @item midnight Answer a time representing midnight in Coordinated Universal Time (UTC) @meindex utcNow @item utcNow Answer a time representing the current time of day in Coordinated Universal Time (UTC) @meindex utcSecondClock @slindex secondClock @item utcSecondClock Answer the number of seconds since the midnight of 1/1/1901 (unlike #secondClock, the reference time is here expressed as UTC, that is as Coordinated Universal Time). @end table @node Time class-builtins @subsection Time class:@- builtins @table @b @meindex primNanosecondClock @item primNanosecondClock Returns the number of milliseconds since midnight. @meindex primSecondClock @item primSecondClock Returns the number of seconds to/from 1/1/2000. @meindex timezone @item timezone Answer a String associated with the current timezone (either standard or daylight-saving) on this operating system. For example, the answer could be `EST' to indicate Eastern Standard Time; the answer can be empty and can't be assumed to be a three-character code such as `EST'. @meindex timezoneBias @item timezoneBias Specifies the current bias, in seconds, for local time translation for the current time. The bias is the difference, in seconds, between Coordinated Universal Time (UTC) and local time; a positive bias indicates that the local timezone is to the east of Greenwich (e.g. Europe, Asia), while a negative bias indicates that it is to the west (e.g. America) @meindex timezoneBias:@- @item timezoneBias:@- seconds Specifies the bias, in seconds, for local time translation for the given second clock value (0 being midnight of 1/1/1901). The bias is the difference, in seconds, between Coordinated Universal Time (UTC) and local time; a positive bias indicates that the local timezone is to the east of Greenwich (e.g. Europe, Asia), while a negative bias indicates that it is to the west (e.g. America) @end table @node Time class-clocks @subsection Time class:@- clocks @table @b @meindex millisecondClock @item millisecondClock Answer the number of milliseconds since startup. @meindex millisecondClockValue @item millisecondClockValue Answer the number of milliseconds since startup @meindex millisecondsPerDay @item millisecondsPerDay Answer the number of milliseconds in a day @meindex millisecondsToRun:@- @item millisecondsToRun:@- timedBlock Answer the number of milliseconds which timedBlock took to run @meindex nanosecondClock @item nanosecondClock Answer the number of nanoseconds since startup. @meindex nanosecondClockValue @item nanosecondClockValue Answer the number of milliseconds since startup @meindex secondClock @item secondClock Answer the number of seconds since the midnight of 1/1/1901 @end table @node Time class-initialization @subsection Time class:@- initialization @table @b @meindex initialize @item initialize Initialize the Time class after the image has been bootstrapped @meindex update:@- @item update:@- aspect Private - Initialize the receiver's instance variables @end table @node Time class-instance creation @subsection Time class:@- instance creation @table @b @meindex fromSeconds:@- @item fromSeconds:@- secondCount Answer a Time representing secondCount seconds past midnight @meindex hour:@- @item hour:@- h Answer a Time that is the given number of hours past midnight @meindex hour:@-minute:@-second:@- @item hour:@- h minute:@- m second:@- s Answer a Time that is the given number of hours, minutes and seconds past midnight @meindex hours:@- @item hours:@- h Answer a Time that is the given number of hours past midnight @meindex hours:@-minutes:@-seconds:@- @item hours:@- h minutes:@- m seconds:@- s Answer a Time that is the given number of hours, minutes and seconds past midnight @meindex minute:@- @item minute:@- m Answer a Time that is the given number of minutes past midnight @meindex minutes:@- @item minutes:@- m Answer a Time that is the given number of minutes past midnight @meindex new @item new Answer a Time representing midnight @meindex now @item now Answer a time representing the current time of day @meindex readFrom:@- @item readFrom:@- aStream Parse an instance of the receiver (hours/minutes/seconds) from aStream @meindex second:@- @item second:@- s Answer a Time that is the given number of seconds past midnight @meindex seconds:@- @item seconds:@- s Answer a Time that is the given number of seconds past midnight @end table @node Time-accessing (ANSI for DateAndTimes) @subsection Time:@- accessing (ANSI for DateAndTimes) @table @b @meindex hour @item hour Answer the number of hours in the receiver @meindex hour12 @item hour12 Answer the hour in a 12-hour clock @meindex hour24 @item hour24 Answer the hour in a 24-hour clock @meindex minute @item minute Answer the number of minutes in the receiver @meindex second @item second Answer the number of seconds in the receiver @end table @node Time-accessing (non ANSI & for Durations) @subsection Time:@- accessing (non ANSI & for Durations) @table @b @meindex asMilliseconds @item asMilliseconds Not commented. @meindex asNanoseconds @item asNanoseconds Not commented. @meindex asSeconds @item asSeconds Answer `seconds'. @meindex hours @item hours Answer the number of hours in the receiver @meindex minutes @item minutes Answer the number of minutes in the receiver @meindex seconds @item seconds Answer the number of seconds in the receiver @end table @node Time-arithmetic @subsection Time:@- arithmetic @table @b @meindex addSeconds:@- @item addSeconds:@- timeAmount Answer a new Time that is timeAmount seconds after the receiver @meindex addTime:@- @item addTime:@- timeAmount Answer a new Time that is timeAmount seconds after the receiver; timeAmount is a Time. @meindex printOn:@- @item printOn:@- aStream Print a representation of the receiver on aStream @meindex subtractTime:@- @item subtractTime:@- timeAmount Answer a new Time that is timeAmount seconds before the receiver; timeAmount is a Time. @end table @node Time-comparing @subsection Time:@- comparing @table @b @meindex < @item < aTime Answer whether the receiver is less than aTime @meindex = @item = aTime Answer whether the receiver is equal to aTime @meindex hash @item hash Answer an hash value for the receiver @end table @node True @section True @clindex True @table @b @item Defined in namespace Smalltalk @itemx Superclass: Boolean @itemx Category: Language-Data types I represent truth and justice in the world. My motto is "semper veritatis". @end table @menu * True-basic:: (instance) * True-C hacks:: (instance) * True-printing:: (instance) @end menu @node True-basic @subsection True:@- basic @table @b @meindex & @item & aBoolean We are true -- anded with anything, we always answer the other operand @meindex and:@- @item and:@- aBlock We are true -- anded with anything, we always answer the other operand, so evaluate aBlock @meindex eqv:@- @item eqv:@- aBoolean Answer whether the receiver and aBoolean represent the same boolean value @meindex ifFalse:@- @item ifFalse:@- falseBlock We are true -- answer nil @meindex ifFalse:@-ifTrue:@- @item ifFalse:@- falseBlock ifTrue:@- trueBlock We are true -- evaluate trueBlock @meindex ifTrue:@- @item ifTrue:@- trueBlock We are true -- evaluate trueBlock @meindex ifTrue:@-ifFalse:@- @item ifTrue:@- trueBlock ifFalse:@- falseBlock We are true -- evaluate trueBlock @meindex not @item not We are true -- answer false @meindex or:@- @item or:@- aBlock We are true -- ored with anything, we always answer true @meindex xor:@- @item xor:@- aBoolean Answer whether the receiver and aBoolean represent different boolean values @meindex | @item | aBoolean We are true -- ored with anything, we always answer true @end table @node True-C hacks @subsection True:@- C hacks @table @b @meindex asCBooleanValue @item asCBooleanValue Answer `1'. @end table @node True-printing @subsection True:@- printing @table @b @meindex printOn:@- @item printOn:@- aStream Print a representation of the receiver on aStream @end table @node UndefinedObject @section UndefinedObject @clindex UndefinedObject @table @b @item Defined in namespace Smalltalk @itemx Superclass: Object @itemx Category: Language-Implementation I have the questionable distinction of being a class with only one instance, which is the object "nil". @end table @menu * UndefinedObject-basic:: (instance) * UndefinedObject-class creation - alternative:: (instance) * UndefinedObject-class polymorphism:: (instance) * UndefinedObject-CObject interoperability:: (instance) * UndefinedObject-dependents access:: (instance) * UndefinedObject-iteration:: (instance) * UndefinedObject-printing:: (instance) * UndefinedObject-still unclassified:: (instance) * UndefinedObject-storing:: (instance) * UndefinedObject-testing:: (instance) @end menu @node UndefinedObject-basic @subsection UndefinedObject:@- basic @table @b @meindex copy @item copy Answer the receiver. @meindex deepCopy @item deepCopy Answer the receiver. @meindex shallowCopy @item shallowCopy Answer the receiver. @end table @node UndefinedObject-class creation - alternative @subsection UndefinedObject:@- class creation - alternative @table @b @meindex subclass:@-classInstanceVariableNames:@-instanceVariableNames:@-classVariableNames:@-poolDictionaries:@- @item subclass:@- classNameString classInstanceVariableNames:@- stringClassInstVarNames instanceVariableNames:@- stringInstVarNames classVariableNames:@- stringOfClassVarNames poolDictionaries:@- stringOfPoolNames Don't use this, it is only present to file in from IBM Smalltalk @meindex subclass:@-instanceVariableNames:@-classVariableNames:@-poolDictionaries:@- @item subclass:@- classNameString instanceVariableNames:@- stringInstVarNames classVariableNames:@- stringOfClassVarNames poolDictionaries:@- stringOfPoolNames Don't use this, it is only present to file in from IBM Smalltalk @meindex variableByteSubclass:@-classInstanceVariableNames:@-instanceVariableNames:@-classVariableNames:@-poolDictionaries:@- @item variableByteSubclass:@- classNameString classInstanceVariableNames:@- stringClassInstVarNames instanceVariableNames:@- stringInstVarNames classVariableNames:@- stringOfClassVarNames poolDictionaries:@- stringOfPoolNames Don't use this, it is only present to file in from IBM Smalltalk @meindex variableByteSubclass:@-instanceVariableNames:@-classVariableNames:@-poolDictionaries:@- @item variableByteSubclass:@- classNameString instanceVariableNames:@- stringInstVarNames classVariableNames:@- stringOfClassVarNames poolDictionaries:@- stringOfPoolNames Don't use this, it is only present to file in from IBM Smalltalk @meindex variableLongSubclass:@-classInstanceVariableNames:@-instanceVariableNames:@-classVariableNames:@-poolDictionaries:@- @item variableLongSubclass:@- classNameString classInstanceVariableNames:@- stringClassInstVarNames instanceVariableNames:@- stringInstVarNames classVariableNames:@- stringOfClassVarNames poolDictionaries:@- stringOfPoolNames Don't use this, it is only present to file in from IBM Smalltalk @meindex variableLongSubclass:@-instanceVariableNames:@-classVariableNames:@-poolDictionaries:@- @item variableLongSubclass:@- classNameString instanceVariableNames:@- stringInstVarNames classVariableNames:@- stringOfClassVarNames poolDictionaries:@- stringOfPoolNames Don't use this, it is only present to file in from IBM Smalltalk @meindex variableSubclass:@-classInstanceVariableNames:@-instanceVariableNames:@-classVariableNames:@-poolDictionaries:@- @item variableSubclass:@- classNameString classInstanceVariableNames:@- stringClassInstVarNames instanceVariableNames:@- stringInstVarNames classVariableNames:@- stringOfClassVarNames poolDictionaries:@- stringOfPoolNames Don't use this, it is only present to file in from IBM Smalltalk @meindex variableSubclass:@-instanceVariableNames:@-classVariableNames:@-poolDictionaries:@- @item variableSubclass:@- classNameString instanceVariableNames:@- stringInstVarNames classVariableNames:@- stringOfClassVarNames poolDictionaries:@- stringOfPoolNames Don't use this, it is only present to file in from IBM Smalltalk @end table @node UndefinedObject-class polymorphism @subsection UndefinedObject:@- class polymorphism @table @b @meindex allSubclasses @item allSubclasses Return all the classes in the system. @meindex instSize @item instSize Answer `0'. @meindex metaclassFor:@- @item metaclassFor:@- classNameString Create a Metaclass object for the given class name. The metaclass is a subclass of Class @meindex methodDictionary @item methodDictionary Answer `nil'. @meindex removeSubclass:@- @item removeSubclass:@- aClass Ignored -- necessary to support disjoint class hierarchies @meindex subclass:@- @item subclass:@- classNameString Define a subclass of the receiver with the given name. If the class is already defined, don't modify its instance or class variables but still, if necessary, recompile everything needed. @meindex subclass:@-instanceVariableNames:@-classVariableNames:@-poolDictionaries:@-category:@- @item subclass:@- classNameString instanceVariableNames:@- stringInstVarNames classVariableNames:@- stringOfClassVarNames poolDictionaries:@- stringOfPoolNames category:@- categoryNameString Define a fixed subclass of the receiver with the given name, instance variables, class variables, pool dictionaries and category. If the class is already defined, if necessary, recompile everything needed. @meindex variable:@-subclass:@-instanceVariableNames:@-classVariableNames:@-poolDictionaries:@-category:@- @slindex byte @slindex int8 @slindex character @slindex short @slindex ushort @slindex int @slindex uint @slindex int64 @slindex uint64 @slindex utf32 @slindex float @slindex double @slindex pointer @item variable:@- shape subclass:@- classNameString instanceVariableNames:@- stringInstVarNames classVariableNames:@- stringOfClassVarNames poolDictionaries:@- stringOfPoolNames category:@- categoryNameString Define a variable subclass of the receiver with the given name, shape, instance variables, class variables, pool dictionaries and category. If the class is already defined, if necessary, recompile everything needed. The shape can be one of #byte #int8 #character #short #ushort #int #uint #int64 #uint64 #utf32 #float #double or #pointer. @meindex variableByteSubclass:@-instanceVariableNames:@-classVariableNames:@-poolDictionaries:@-category:@- @item variableByteSubclass:@- classNameString instanceVariableNames:@- stringInstVarNames classVariableNames:@- stringOfClassVarNames poolDictionaries:@- stringOfPoolNames category:@- categoryNameString Define a byte variable subclass of the receiver with the given name, instance variables, class variables, pool dictionaries and category. If the class is already defined, if necessary, recompile everything needed. @meindex variableSubclass:@-instanceVariableNames:@-classVariableNames:@-poolDictionaries:@-category:@- @item variableSubclass:@- classNameString instanceVariableNames:@- stringInstVarNames classVariableNames:@- stringOfClassVarNames poolDictionaries:@- stringOfPoolNames category:@- categoryNameString Define a variable pointer subclass of the receiver with the given name, instance variables, class variables, pool dictionaries and category. If the class is already defined, if necessary, recompile everything needed. @meindex variableWordSubclass:@-instanceVariableNames:@-classVariableNames:@-poolDictionaries:@-category:@- @item variableWordSubclass:@- classNameString instanceVariableNames:@- stringInstVarNames classVariableNames:@- stringOfClassVarNames poolDictionaries:@- stringOfPoolNames category:@- categoryNameString Define a word variable subclass of the receiver with the given name, instance variables, class variables, pool dictionaries and category. If the class is already defined, if necessary, recompile everything needed. @end table @node UndefinedObject-CObject interoperability @subsection UndefinedObject:@- CObject interoperability @table @b @meindex free @item free Do nothing, a NULL pointer can be safely freed. @meindex narrow @item narrow Return the receiver:@- a NULL pointer is always nil, whatever its type. @end table @node UndefinedObject-dependents access @subsection UndefinedObject:@- dependents access @table @b @meindex addDependent:@- @item addDependent:@- ignored Fail, nil does not support dependents. @meindex release @item release Ignore this call, nil does not support dependents. @end table @node UndefinedObject-iteration @subsection UndefinedObject:@- iteration @table @b @meindex ifNil:@-ifNotNilDo:@- @item ifNil:@- nilBlock ifNotNilDo:@- iterableBlock Evaluate nilBlock if the receiver is nil, else evaluate iterableBlock with each element of the receiver (which should be an Iterable). @meindex ifNotNilDo:@- @item ifNotNilDo:@- iterableBlock Evaluate iterableBlock with each element of the receiver (which should be an Iterable) if not nil. Else answer nil @meindex ifNotNilDo:@-ifNil:@- @item ifNotNilDo:@- iterableBlock ifNil:@- nilBlock Evaluate nilBlock if the receiver is nil, else evaluate iterableBlock, passing each element of the receiver (which should be an Iterable). @end table @node UndefinedObject-printing @subsection UndefinedObject:@- printing @table @b @meindex printOn:@- @item printOn:@- aStream Print a representation of the receiver on aStream. @meindex printOn:@-in:@- @slindex printOn:@- @item printOn:@- aStream in:@- aNamespace Print on aStream a representation of the receiver as it would be accessed from aNamespace:@- nil is the same everywhere, so print the same as #printOn:@- @end table @node UndefinedObject-still unclassified @subsection UndefinedObject:@- still unclassified @table @b @meindex inheritsFrom:@- @item inheritsFrom:@- aClass Always return false, as nil inherits from nothing. @end table @node UndefinedObject-storing @subsection UndefinedObject:@- storing @table @b @meindex isLiteralObject @item isLiteralObject Answer whether the receiver is expressible as a Smalltalk literal. @meindex storeLiteralOn:@- @item storeLiteralOn:@- aStream Store on aStream some Smalltalk code which compiles to the receiver @meindex storeOn:@- @item storeOn:@- aStream Store Smalltalk code compiling to the receiver on aStream. @end table @node UndefinedObject-testing @subsection UndefinedObject:@- testing @table @b @meindex ifNil:@- @item ifNil:@- nilBlock Evaluate nilBlock if the receiver is nil, else answer nil @meindex ifNil:@-ifNotNil:@- @item ifNil:@- nilBlock ifNotNil:@- notNilBlock Evaluate nilBlock if the receiver is nil, else evaluate notNilBlock, passing the receiver. @meindex ifNotNil:@- @item ifNotNil:@- notNilBlock Evaluate notNilBlock if the receiver is not nil, passing the receiver. Else answer nil @meindex ifNotNil:@-ifNil:@- @item ifNotNil:@- notNilBlock ifNil:@- nilBlock Evaluate nilBlock if the receiver is nil, else evaluate notNilBlock, passing the receiver. @meindex isNil @item isNil Answer whether the receiver is the undefined object nil. Always answer true. @meindex isNull @item isNull Answer whether the receiver represents a NULL C pointer. Always answer true. @meindex notNil @item notNil Answer whether the receiver is not the undefined object nil. Always answer false. @end table @node UnicodeCharacter @section UnicodeCharacter @clindex UnicodeCharacter @table @b @item Defined in namespace Smalltalk @itemx Superclass: Character @itemx Category: Language-Data types My instances represent the over one million characters of the Unicode character set. It provides messages to translate between integers and character objects. UnicodeCharacter objects are created when accessing UnicodeStrings, or with Character class>>@-#codePoint:@-. @end table @menu * UnicodeCharacter class-built ins:: (class) * UnicodeCharacter-coercion methods:: (instance) @end menu @node UnicodeCharacter class-built ins @subsection UnicodeCharacter class:@- built ins @table @b @meindex value:@- @slindex value:@- @slindex codePoint:@- @item value:@- anInteger Returns the character object, possibly a Character, corresponding to anInteger. Error if anInteger is not an integer, or not in 0..16r10FFFF. This is only a primitive for speed. UnicodeCharacter's #value:@- method is equivalent to #codePoint:@- (which is the same for Character and UnicodeCharacter). @end table @node UnicodeCharacter-coercion methods @subsection UnicodeCharacter:@- coercion methods @table @b @meindex * @item * aNumber Returns a String with aNumber occurrences of the receiver. @end table @node UnicodeString @section UnicodeString @clindex UnicodeString @table @b @item Defined in namespace Smalltalk @itemx Superclass: CharacterArray @itemx Category: Collections-Text My instances represent Unicode string data types. Data is stored as 4-byte UTF-32 characters @end table @menu * UnicodeString class-converting:: (class) * UnicodeString class-multibyte encodings:: (class) * UnicodeString-built ins:: (instance) * UnicodeString-built-ins:: (instance) * UnicodeString-converting:: (instance) * UnicodeString-multibyte encodings:: (instance) @end menu @node UnicodeString class-converting @subsection UnicodeString class:@- converting @table @b @meindex fromString:@- @item fromString:@- aString Return the String, aString, converted to its Unicode representation. Unless the I18N package is loaded, this is not implemented. @end table @node UnicodeString class-multibyte encodings @subsection UnicodeString class:@- multibyte encodings @table @b @meindex defaultEncoding @item defaultEncoding Answer the encoding used by the receiver. Conventionally, we answer 'Unicode' to ensure that two UnicodeStrings always have the same encoding. @meindex isUnicode @item isUnicode Answer true; the receiver stores characters. @end table @node UnicodeString-built ins @subsection UnicodeString:@- built ins @table @b @meindex at:@-ifAbsent:@- @item at:@- anIndex ifAbsent:@- aBlock Answer the index-th indexed instance variable of the receiver @end table @node UnicodeString-built-ins @subsection UnicodeString:@- built-ins @table @b @meindex hash @item hash Answer an hash value for the receiver @end table @node UnicodeString-converting @subsection UnicodeString:@- converting @table @b @meindex asString @item asString Returns the string corresponding to the receiver. Without the Iconv package, unrecognized Unicode characters become $? characters. When it is loaded, an appropriate single- or multi-byte encoding could be used. @meindex asSymbol @item asSymbol Returns the symbol corresponding to the receiver @meindex asUnicodeString @item asUnicodeString But I already am a UnicodeString! Really! @meindex displayOn:@- @item displayOn:@- aStream Print a representation of the receiver on aStream @meindex printOn:@- @item printOn:@- aStream Print a representation of the receiver on aStream @end table @node UnicodeString-multibyte encodings @subsection UnicodeString:@- multibyte encodings @table @b @meindex encoding @item encoding Answer the encoding used by the receiver. Conventionally, we answer 'Unicode' to ensure that two UnicodeStrings always have the same encoding. @meindex numberOfCharacters @slindex size @item numberOfCharacters Answer the number of Unicode characters in the receiver. This is the same as #size for UnicodeString. @end table @node ValueAdaptor @section ValueAdaptor @clindex ValueAdaptor @table @b @item Defined in namespace Smalltalk @itemx Superclass: Object @itemx Category: Language-Data types My subclasses are used to access data from different objects with a consistent protocol. However, I'm an abstract class. @end table @menu * ValueAdaptor class-creating instances:: (class) * ValueAdaptor-accessing:: (instance) * ValueAdaptor-printing:: (instance) @end menu @node ValueAdaptor class-creating instances @subsection ValueAdaptor class:@- creating instances @table @b @meindex new @item new We don't know enough of subclasses to have a shared implementation of new @end table @node ValueAdaptor-accessing @subsection ValueAdaptor:@- accessing @table @b @meindex value @item value Retrive the value of the receiver. Must be implemented by ValueAdaptor's subclasses @meindex value:@- @item value:@- anObject Set the value of the receiver. Must be implemented by ValueAdaptor's subclasses @end table @node ValueAdaptor-printing @subsection ValueAdaptor:@- printing @table @b @meindex printOn:@- @item printOn:@- aStream Print a representation of the receiver @end table @node ValueHolder @section ValueHolder @clindex ValueHolder @table @b @item Defined in namespace Smalltalk @itemx Superclass: ValueAdaptor @itemx Category: Language-Data types I store my value in a variable. For example, you can use me to pass numbers by reference. Just instance me before calling a method and ask for my value after that method. There are a lot of other creative uses for my intances, though. @end table @menu * ValueHolder class-creating instances:: (class) * ValueHolder-accessing:: (instance) * ValueHolder-initializing:: (instance) @end menu @node ValueHolder class-creating instances @subsection ValueHolder class:@- creating instances @table @b @meindex new @item new Create a ValueHolder whose starting value is nil @meindex null @item null Answer the sole instance of NullValueHolder @meindex with:@- @item with:@- anObject Create a ValueHolder whose starting value is anObject @end table @node ValueHolder-accessing @subsection ValueHolder:@- accessing @table @b @meindex value @item value Get the value of the receiver. @meindex value:@- @item value:@- anObject Set the value of the receiver. @end table @node ValueHolder-initializing @subsection ValueHolder:@- initializing @table @b @meindex initialize @item initialize Private - set the initial value of the receiver @end table @node VariableBinding @section VariableBinding @clindex VariableBinding @table @b @item Defined in namespace Smalltalk @itemx Superclass: HomedAssociation @itemx Category: Language-Data types My instances represent a mapping between a key in a namespace and its value. I print different than a normal Association, and know about my parent namespace, otherwise my behavior is the same. @end table @menu * VariableBinding-compiler:: (instance) * VariableBinding-printing:: (instance) * VariableBinding-saving and loading:: (instance) * VariableBinding-storing:: (instance) * VariableBinding-testing:: (instance) @end menu @node VariableBinding-compiler @subsection VariableBinding:@- compiler @table @b @meindex literalEquals:@- @item literalEquals:@- anObject Not commented. @meindex literalHash @item literalHash Not commented. @end table @node VariableBinding-printing @subsection VariableBinding:@- printing @table @b @meindex path @item path Print a dotted path that compiles to the receiver's value @meindex printOn:@- @item printOn:@- aStream Put on aStream a representation of the receiver @end table @node VariableBinding-saving and loading @subsection VariableBinding:@- saving and loading @table @b @meindex binaryRepresentationObject @slindex at:@- @item binaryRepresentationObject This method is implemented to allow for a PluggableProxy to be used with VariableBindings. Answer a DirectedMessage which sends #at:@- to the environment that holds the receiver. @end table @node VariableBinding-storing @subsection VariableBinding:@- storing @table @b @meindex isLiteralObject @item isLiteralObject Answer whether the receiver is expressible as a Smalltalk literal. @meindex storeLiteralOn:@- @item storeLiteralOn:@- aStream Store on aStream some Smalltalk code which compiles to the receiver @meindex storeOn:@- @item storeOn:@- aStream Put on aStream some Smalltalk code compiling to the receiver @end table @node VariableBinding-testing @subsection VariableBinding:@- testing @table @b @meindex isDefined @item isDefined Answer true if this VariableBinding lives outside the Undeclared dictionary @end table @node VersionableObjectProxy @section VersionableObjectProxy @clindex VersionableObjectProxy @table @b @item Defined in namespace Smalltalk @itemx Superclass: NullProxy @itemx Category: Streams-Files I am a proxy that stores additional information to allow different versions of an object's representations to be handled by the program. VersionableObjectProxies are backwards compatible, that is you can support versioning even if you did not use a VersionableObjectProxy for that class when the object was originarily dumped. VersionableObjectProxy does not support classes that changed shape across different versions. See the method comments for more information. @end table @menu * VersionableObjectProxy class-saving and restoring:: (class) * VersionableObjectProxy-saving and restoring:: (instance) @end menu @node VersionableObjectProxy class-saving and restoring @subsection VersionableObjectProxy class:@- saving and restoring @table @b @meindex loadFrom:@- @slindex binaryRepresentationVersion @slindex convertFromVersion:@-withFixedVariables:@-instanceVariables:@-for:@- @slindex nonVersionedInstSize @item loadFrom:@- anObjectDumper Retrieve the object. If the version number doesn't match the #binaryRepresentationVersion answered by the class, call the class' #convertFromVersion:@-withFixedVariables:@-instanceVariables:@-for:@- method. The stored version number will be the first parameter to that method (or nil if the stored object did not employ a VersionableObjectProxy), the remaining parameters will be respectively the fixed instance variables, the indexed instance variables (or nil if the class is fixed), and the ObjectDumper itself. If no VersionableObjectProxy, the class is sent #nonVersionedInstSize to retrieve the number of fixed instance variables stored for the non-versioned object. @end table @node VersionableObjectProxy-saving and restoring @subsection VersionableObjectProxy:@- saving and restoring @table @b @meindex dumpTo:@- @item dumpTo:@- anObjectDumper Save the object with extra versioning information. @end table @node VFS.ArchiveFile @section VFS.ArchiveFile @clindex VFS.ArchiveFile @table @b @item Defined in namespace Smalltalk.VFS @itemx Superclass: VFS.FileWrapper @itemx Category: Streams-Files ArchiveFile handles virtual filesystems that have a directory structure of their own. The directories and files in the archive are instances of ArchiveMember, but the functionality resides entirely in ArchiveFile because the members will still ask the archive to get directory information on them, to extract them to a real file, and so on. @end table @menu * VFS.ArchiveFile-ArchiveMember protocol:: (instance) * VFS.ArchiveFile-directory operations:: (instance) * VFS.ArchiveFile-querying:: (instance) * VFS.ArchiveFile-still unclassified:: (instance) * VFS.ArchiveFile-TmpFileArchiveMember protocol:: (instance) @end menu @node VFS.ArchiveFile-ArchiveMember protocol @subsection VFS.ArchiveFile:@- ArchiveMember protocol @table @b @meindex fillMember:@- @slindex size:@-stCtime:@-stMtime:@-stAtime:@-isDirectory:@- @item fillMember:@- anArchiveMember Extract the information on anArchiveMember. Answer false if it actually does not exist in the archive; otherwise, answer true after having told anArchiveMember about them by sending #size:@-stCtime:@-stMtime:@-stAtime:@-isDirectory:@- to it. @meindex member:@-do:@- @item member:@- anArchiveMember do:@- aBlock Evaluate aBlock once for each file in the directory represented by anArchiveMember, passing its name. @meindex member:@-mode:@- @item member:@- anArchiveMember mode:@- bits Set the permission bits for the file in anArchiveMember. @meindex refresh @item refresh Extract the directory listing from the archive @meindex removeMember:@- @item removeMember:@- anArchiveMember Remove the member represented by anArchiveMember. @meindex updateMember:@- @item updateMember:@- anArchiveMember Update the member represented by anArchiveMember by copying the file into which it was extracted back to the archive. @end table @node VFS.ArchiveFile-directory operations @subsection VFS.ArchiveFile:@- directory operations @table @b @meindex at:@- @item at:@- aName Answer a FilePath for a file named `aName' residing in the directory represented by the receiver. @meindex nameAt:@- @item nameAt:@- aString Answer a FilePath for a file named `aName' residing in the directory represented by the receiver. @meindex namesDo:@- @item namesDo:@- aBlock Evaluate aBlock once for each file in the directory represented by the receiver, passing its name. @meindex release @item release Release the resources used by the receiver that don't survive when reloading a snapshot. @end table @node VFS.ArchiveFile-querying @subsection VFS.ArchiveFile:@- querying @table @b @meindex isAccessible @item isAccessible Answer whether a directory with the name contained in the receiver does exist and can be accessed @meindex isDirectory @item isDirectory Answer true. The archive can always be considered as a directory. @end table @node VFS.ArchiveFile-still unclassified @subsection VFS.ArchiveFile:@- still unclassified @table @b @meindex displayOn:@- @item displayOn:@- aStream Print a representation of the file identified by the receiver. @end table @node VFS.ArchiveFile-TmpFileArchiveMember protocol @subsection VFS.ArchiveFile:@- TmpFileArchiveMember protocol @table @b @meindex extractMember:@- @item extractMember:@- anArchiveMember Extract the contents of anArchiveMember into a file that resides on disk, and answer the name of the file. @meindex extractMember:@-into:@- @item extractMember:@- anArchiveMember into:@- file Extract the contents of anArchiveMember into a file that resides on disk, and answer the name of the file. @end table @node VFS.ArchiveMember @section VFS.ArchiveMember @clindex VFS.ArchiveMember @table @b @item Defined in namespace Smalltalk.VFS @itemx Superclass: FilePath @itemx Category: Streams-Files TmpFileArchiveMember is a handler class for members of archive files that creates temporary files when extracting files from an archive. @end table @menu * VFS.ArchiveMember-accessing:: (instance) * VFS.ArchiveMember-basic:: (instance) * VFS.ArchiveMember-delegation:: (instance) * VFS.ArchiveMember-directory operations:: (instance) * VFS.ArchiveMember-file operations:: (instance) * VFS.ArchiveMember-initializing:: (instance) * VFS.ArchiveMember-still unclassified:: (instance) * VFS.ArchiveMember-testing:: (instance) @end menu @node VFS.ArchiveMember-accessing @subsection VFS.ArchiveMember:@- accessing @table @b @meindex archive @item archive Answer the archive of which the receiver is a member. @meindex asString @slindex name @item asString Answer the name of the file identified by the receiver as answered by File>>@-#name. @meindex creationTime @item creationTime Answer the creation time of the file identified by the receiver. On some operating systems, this could actually be the last change time (the `last change time' has to do with permissions, ownership and the like). @meindex lastAccessTime @item lastAccessTime Answer the last access time of the file identified by the receiver @meindex lastChangeTime @item lastChangeTime Answer the last change time of the file identified by the receiver (the `last change time' has to do with permissions, ownership and the like). On some operating systems, this could actually be the file creation time. @meindex lastModifyTime @item lastModifyTime Answer the last modify time of the file identified by the receiver (the `last modify time' has to do with the actual file contents). @meindex name @item name Answer the receiver's file name. @meindex name:@- @item name:@- aName Set the receiver's file name to aName. @meindex refresh @item refresh Refresh the statistics for the receiver @meindex size @item size Answer the size of the file identified by the receiver @end table @node VFS.ArchiveMember-basic @subsection VFS.ArchiveMember:@- basic @table @b @meindex = @item = aFile Answer whether the receiver represents the same file as the receiver. @meindex hash @item hash Answer a hash value for the receiver. @end table @node VFS.ArchiveMember-delegation @subsection VFS.ArchiveMember:@- delegation @table @b @meindex full @item full Answer the size of the file identified by the receiver @end table @node VFS.ArchiveMember-directory operations @subsection VFS.ArchiveMember:@- directory operations @table @b @meindex at:@- @item at:@- aName Answer a FilePath for a file named `aName' residing in the directory represented by the receiver. @meindex createDirectory:@- @item createDirectory:@- dirName Create a subdirectory of the receiver, naming it dirName. @meindex namesDo:@- @item namesDo:@- aBlock Evaluate aBlock once for each file in the directory represented by the receiver, passing its name. @end table @node VFS.ArchiveMember-file operations @subsection VFS.ArchiveMember:@- file operations @table @b @meindex open:@-mode:@-ifFail:@- @item open:@- class mode:@- mode ifFail:@- aBlock Open the receiver in the given mode (as answered by FileStream's class constant methods) @meindex remove @item remove Remove the file with the given path name @meindex renameTo:@- @item renameTo:@- newFileName Rename the file with the given path name oldFileName to newFileName @meindex update:@- @item update:@- aspect Private - Update the in-archive version of the file before closing. @end table @node VFS.ArchiveMember-initializing @subsection VFS.ArchiveMember:@- initializing @table @b @meindex archive:@- @item archive:@- anArchiveFile Set the archive of which the receiver is a member. @meindex fillFrom:@- @item fillFrom:@- data Called back by the receiver's archive when the ArchiveMember asks for file information. @meindex size:@-stCtime:@-stMtime:@-stAtime:@-mode:@- @item size:@- bytes stCtime:@- ctime stMtime:@- mtime stAtime:@- atime mode:@- modeBits Set the file information for the receiver. @meindex size:@-stMtime:@-mode:@- @item size:@- bytes stMtime:@- mtime mode:@- modeBits Set the file information for the receiver. @end table @node VFS.ArchiveMember-still unclassified @subsection VFS.ArchiveMember:@- still unclassified @table @b @meindex , @item , aName Answer an object of the same kind as the receiver, whose name is suffixed with aName. @meindex displayOn:@- @item displayOn:@- aStream Print a representation of the file identified by the receiver. @meindex isAbsolute @item isAbsolute Answer whether the receiver identifies an absolute path. @end table @node VFS.ArchiveMember-testing @subsection VFS.ArchiveMember:@- testing @table @b @meindex exists @item exists Answer whether a file with the name contained in the receiver does exist. @meindex isAccessible @item isAccessible Answer whether a directory with the name contained in the receiver does exist and is accessible @meindex isDirectory @item isDirectory Answer whether a file with the name contained in the receiver does exist and identifies a directory. @meindex isExecutable @item isExecutable Answer whether a file with the name contained in the receiver does exist and is executable @meindex isReadable @item isReadable Answer whether a file with the name contained in the receiver does exist and is readable @meindex isSymbolicLink @item isSymbolicLink Answer whether a file with the name contained in the receiver does exist and identifies a symbolic link. @meindex isWriteable @item isWriteable Answer whether a file with the name contained in the receiver does exist and is writeable @meindex mode @item mode Answer the octal permissions for the file. @meindex mode:@- @item mode:@- mode Set the octal permissions for the file to be `mode'. @end table @node VFS.FileWrapper @section VFS.FileWrapper @clindex VFS.FileWrapper @table @b @item Defined in namespace Smalltalk.VFS @itemx Superclass: FilePath @itemx Category: Streams-Files FileWrapper gives information for virtual files that refer to a real file on disk. @end table @menu * VFS.FileWrapper class-initializing:: (class) * VFS.FileWrapper class-instance creation:: (class) * VFS.FileWrapper-accessing:: (instance) * VFS.FileWrapper-basic:: (instance) * VFS.FileWrapper-delegation:: (instance) * VFS.FileWrapper-enumerating:: (instance) * VFS.FileWrapper-file operations:: (instance) * VFS.FileWrapper-testing:: (instance) @end menu @node VFS.FileWrapper class-initializing @subsection VFS.FileWrapper class:@- initializing @table @b @meindex initialize @item initialize Register the receiver with ObjectMemory @meindex update:@- @item update:@- aspect Private - Remove the files before quitting, and register the virtual filesystems specified by the subclasses upon image load. @end table @node VFS.FileWrapper class-instance creation @subsection VFS.FileWrapper class:@- instance creation @table @b @meindex on:@- @item on:@- file Create an instance of this class representing the contents of the given file, under the virtual filesystem fsName. @end table @node VFS.FileWrapper-accessing @subsection VFS.FileWrapper:@- accessing @table @b @meindex asString @item asString Answer the string representation of the receiver's path. @meindex at:@- @item at:@- aName Answer a File or Directory object as appropriate for a file named 'aName' in the directory represented by the receiver. @meindex lastAccessTime:@-lastModifyTime:@- @item lastAccessTime:@- accessDateTime lastModifyTime:@- modifyDateTime Update the timestamps of the file corresponding to the receiver, to be accessDateTime and modifyDateTime. @meindex name @item name Answer the full path to the receiver. @meindex owner:@-group:@- @item owner:@- ownerString group:@- groupString Set the receiver's owner and group to be ownerString and groupString. @meindex pathTo:@- @item pathTo:@- destName Compute the relative path from the receiver to destName. @end table @node VFS.FileWrapper-basic @subsection VFS.FileWrapper:@- basic @table @b @meindex = @item = aFile Answer whether the receiver represents the same file as the receiver. @meindex hash @item hash Answer a hash value for the receiver. @end table @node VFS.FileWrapper-delegation @subsection VFS.FileWrapper:@- delegation @table @b @meindex creationTime @item creationTime Answer the creation time of the file identified by the receiver. On some operating systems, this could actually be the last change time (the `last change time' has to do with permissions, ownership and the like). @meindex full @item full Answer the size of the file identified by the receiver @meindex isExecutable @item isExecutable Answer whether a file with the name contained in the receiver does exist and is executable @meindex isReadable @item isReadable Answer whether a file with the name contained in the receiver does exist and is readable @meindex isWriteable @item isWriteable Answer whether a file with the name contained in the receiver does exist and is writeable @meindex lastAccessTime @item lastAccessTime Answer the last access time of the file identified by the receiver @meindex lastChangeTime @item lastChangeTime Answer the last change time of the file identified by the receiver (the `last change time' has to do with permissions, ownership and the like). On some operating systems, this could actually be the file creation time. @meindex lastModifyTime @item lastModifyTime Answer the last modify time of the file identified by the receiver (the `last modify time' has to do with the actual file contents). @meindex mode @item mode Answer the permission bits for the file identified by the receiver @meindex mode:@- @item mode:@- anInteger Answer the permission bits for the file identified by the receiver @meindex open:@-mode:@-ifFail:@- @item open:@- class mode:@- mode ifFail:@- aBlock Open the receiver in the given mode (as answered by FileStream's class constant methods) @meindex remove @item remove Remove the file with the given path name @meindex size @item size Answer the size of the file identified by the receiver @end table @node VFS.FileWrapper-enumerating @subsection VFS.FileWrapper:@- enumerating @table @b @meindex namesDo:@- @item namesDo:@- aBlock Evaluate aBlock once for each file in the directory represented by the receiver, passing its name. @end table @node VFS.FileWrapper-file operations @subsection VFS.FileWrapper:@- file operations @table @b @meindex pathFrom:@- @item pathFrom:@- dirName Compute the relative path from the directory dirName to the receiver @meindex renameTo:@- @item renameTo:@- newName Rename the file identified by the receiver to newName @meindex symlinkAs:@- @item symlinkAs:@- destName Create destName as a symbolic link of the receiver. The appropriate relative path is computed automatically. @meindex symlinkFrom:@- @item symlinkFrom:@- srcName Create the receiver as a symbolic link from srcName (relative to the path of the receiver). @end table @node VFS.FileWrapper-testing @subsection VFS.FileWrapper:@- testing @table @b @meindex exists @item exists Answer whether a file with the name contained in the receiver does exist. @meindex isAbsolute @item isAbsolute Answer whether the receiver identifies an absolute path. @meindex isAccessible @item isAccessible Answer whether a directory with the name contained in the receiver does exist and can be accessed @meindex isDirectory @item isDirectory Answer whether a file with the name contained in the receiver does exist identifies a directory. @meindex isSymbolicLink @item isSymbolicLink Answer whether a file with the name contained in the receiver does exist and identifies a symbolic link. @end table @node VFS.StoredZipMember @section VFS.StoredZipMember @clindex VFS.StoredZipMember @table @b @item Defined in namespace Smalltalk.VFS @itemx Superclass: VFS.TmpFileArchiveMember @itemx Category: Streams-Files ArchiveMember is the handler class for stored ZIP archive members, which are optimized. @end table @menu * VFS.StoredZipMember-accessing:: (instance) * VFS.StoredZipMember-opening:: (instance) @end menu @node VFS.StoredZipMember-accessing @subsection VFS.StoredZipMember:@- accessing @table @b @meindex offset @item offset Answer `offset'. @meindex offset:@- @item offset:@- anInteger Not commented. @end table @node VFS.StoredZipMember-opening @subsection VFS.StoredZipMember:@- opening @table @b @meindex open:@-mode:@-ifFail:@- @item open:@- class mode:@- mode ifFail:@- aBlock Not commented. @end table @node VFS.TmpFileArchiveMember @section VFS.TmpFileArchiveMember @clindex VFS.TmpFileArchiveMember @table @b @item Defined in namespace Smalltalk.VFS @itemx Superclass: VFS.ArchiveMember @itemx Category: Streams-Files @end table @menu * VFS.TmpFileArchiveMember-directory operations:: (instance) * VFS.TmpFileArchiveMember-finalization:: (instance) * VFS.TmpFileArchiveMember-still unclassified:: (instance) @end menu @node VFS.TmpFileArchiveMember-directory operations @subsection VFS.TmpFileArchiveMember:@- directory operations @table @b @meindex file @item file Answer the real file name which holds the file contents, or nil if it does not apply. @meindex open:@-mode:@-ifFail:@- @item open:@- class mode:@- mode ifFail:@- aBlock Open the receiver in the given mode (as answered by FileStream's class constant methods) @end table @node VFS.TmpFileArchiveMember-finalization @subsection VFS.TmpFileArchiveMember:@- finalization @table @b @meindex release @item release Release the resources used by the receiver that don't survive when reloading a snapshot. @end table @node VFS.TmpFileArchiveMember-still unclassified @subsection VFS.TmpFileArchiveMember:@- still unclassified @table @b @meindex extracted @item extracted Answer whether the file has already been extracted to disk. @end table @node VFS.ZipFile @section VFS.ZipFile @clindex VFS.ZipFile @table @b @item Defined in namespace Smalltalk.VFS @itemx Superclass: VFS.ArchiveFile @itemx Category: Streams-Files ZipFile transparently extracts files from a ZIP archive. @end table @menu * VFS.ZipFile-members:: (instance) @end menu @node VFS.ZipFile-members @subsection VFS.ZipFile:@- members @table @b @meindex centralDirectoryRangeIn:@- @item centralDirectoryRangeIn:@- f Not commented. @meindex createDirectory:@- @item createDirectory:@- dirName Create a subdirectory of the receiver, naming it dirName. @meindex extractMember:@-into:@- @item extractMember:@- anArchiveMember into:@- temp Extract the contents of anArchiveMember into a file that resides on disk, and answer the name of the file. @meindex fileData @item fileData Extract the directory listing from the archive @meindex member:@-mode:@- @item member:@- anArchiveMember mode:@- bits Set the permission bits for the file in anArchiveMember. @meindex removeMember:@- @item removeMember:@- anArchiveMember Remove the member represented by anArchiveMember. @meindex updateMember:@- @item updateMember:@- anArchiveMember Update the member represented by anArchiveMember by copying the file into which it was extracted back to the archive. @end table @node Warning @section Warning @clindex Warning @table @b @item Defined in namespace Smalltalk @itemx Superclass: Notification @itemx Category: Language-Exceptions Warning represents an `important' but resumable error. @end table @menu * Warning-exception description:: (instance) @end menu @node Warning-exception description @subsection Warning:@- exception description @table @b @meindex description @item description Answer a textual description of the exception. @end table @node WeakArray @section WeakArray @clindex WeakArray @table @b @item Defined in namespace Smalltalk @itemx Superclass: Array @itemx Category: Collections-Weak I am similar to a plain array, but my items are stored in a weak object, so I track which of them are garbage collected. @end table @menu * WeakArray class-instance creation:: (class) * WeakArray-accessing:: (instance) * WeakArray-conversion:: (instance) * WeakArray-loading:: (instance) @end menu @node WeakArray class-instance creation @subsection WeakArray class:@- instance creation @table @b @meindex new @item new Create a new WeakArray of size 0. @meindex new:@- @item new:@- size Create a new WeakArray of the given size. @end table @node WeakArray-accessing @subsection WeakArray:@- accessing @table @b @meindex aliveObjectsDo:@- @item aliveObjectsDo:@- aBlock Evaluate aBlock for all the elements in the array, excluding the garbage collected ones. Note:@- a finalized object stays alive until the next collection (the collector has no means to see whether it was resuscitated by the finalizer), so an object being alive does not mean that it is usable. @meindex at:@- @item at:@- index Answer the index-th item of the receiver, or nil if it has been garbage collected. @meindex at:@-put:@- @item at:@- index put:@- object Store the value associated to the given index; plus, store in nilValues whether the object is nil. nil objects whose associated item of nilValues is 1 were touched by the garbage collector. @meindex atAll:@-put:@- @item atAll:@- indices put:@- object Put object at every index contained in the indices collection @meindex atAllPut:@- @item atAllPut:@- object Put object at every index in the receiver @meindex clearGCFlag:@- @item clearGCFlag:@- index Clear the `object has been garbage collected' flag for the item at the given index @meindex do:@- @item do:@- aBlock Evaluate aBlock for all the elements in the array, including the garbage collected ones (pass nil for those). @meindex isAlive:@- @item isAlive:@- index Answer whether the item at the given index is still alive or has been garbage collected. Note:@- a finalized object stays alive until the next collection (the collector has no means to see whether it was resuscitated by the finalizer), so an object being alive does not mean that it is usable. @meindex size @item size Answer the number of items in the receiver @end table @node WeakArray-conversion @subsection WeakArray:@- conversion @table @b @meindex asArray @item asArray Answer a non-weak version of the receiver @meindex deepCopy @item deepCopy Returns a deep copy of the receiver (the instance variables are copies of the receiver's instance variables) @meindex shallowCopy @item shallowCopy Returns a shallow copy of the receiver (the instance variables are not copied) @meindex species @slindex copyEmpty:@- @item species Answer Array; this method is used in the #copyEmpty:@- message, which in turn is used by all collection-returning methods (collect:@-, select:@-, reject:@-, etc.). @end table @node WeakArray-loading @subsection WeakArray:@- loading @table @b @meindex postLoad @item postLoad Called after loading an object; must restore it to the state before `preStore' was called. Make it weak again @end table @node WeakIdentitySet @section WeakIdentitySet @clindex WeakIdentitySet @table @b @item Defined in namespace Smalltalk @itemx Superclass: WeakSet @itemx Category: Collections-Weak I am similar to a plain identity set, but my keys are stored in a weak array; I track which of them are garbage collected and, as soon as I encounter one of them, I swiftly remove all the garbage collected keys @end table @menu * WeakIdentitySet-accessing:: (instance) @end menu @node WeakIdentitySet-accessing @subsection WeakIdentitySet:@- accessing @table @b @meindex identityIncludes:@- @slindex includes:@- @item identityIncludes:@- anObject Answer whether I include anObject exactly. As I am an identity-set, this is the same as #includes:@-. @end table @node WeakKeyDictionary @section WeakKeyDictionary @clindex WeakKeyDictionary @table @b @item Defined in namespace Smalltalk @itemx Superclass: Dictionary @itemx Category: Collections-Weak I am similar to a plain Dictionary, but my keys are stored in a weak array; I track which of them are garbage collected and, as soon as I encounter one of them, I swiftly remove all the associations for the garbage collected keys @end table @menu * WeakKeyDictionary class-hacks:: (class) * WeakKeyDictionary-accessing:: (instance) @end menu @node WeakKeyDictionary class-hacks @subsection WeakKeyDictionary class:@- hacks @table @b @meindex postLoad @item postLoad Called after loading an object; must restore it to the state before `preStore' was called. Make it weak again @end table @node WeakKeyDictionary-accessing @subsection WeakKeyDictionary:@- accessing @table @b @meindex add:@- @item add:@- anAssociation Store value as associated to the given key. @meindex at:@-put:@- @item at:@- key put:@- value Store value as associated to the given key. @end table @node WeakKeyIdentityDictionary @section WeakKeyIdentityDictionary @clindex WeakKeyIdentityDictionary @table @b @item Defined in namespace Smalltalk @itemx Superclass: WeakKeyDictionary @itemx Category: Collections-Weak I am similar to a plain identity dictionary, but my keys are stored in a weak array; I track which of them are garbage collected and, as soon as I encounter one of them, I swiftly remove all the associations for the garbage collected keys @end table @menu @end menu @node WeakSet @section WeakSet @clindex WeakSet @table @b @item Defined in namespace Smalltalk @itemx Superclass: Set @itemx Category: Collections-Weak I am similar to a plain set, but my items are stored in a weak array; I track which of them are garbage collected and, as soon as I encounter one of them, I swiftly remove all. @end table @menu * WeakSet-accessing:: (instance) * WeakSet-copying:: (instance) * WeakSet-loading:: (instance) @end menu @node WeakSet-accessing @subsection WeakSet:@- accessing @table @b @meindex add:@- @item add:@- newObject Add newObject to the set, if and only if the set doesn't already contain an occurrence of it. Don't fail if a duplicate is found. Answer newObject @meindex do:@- @item do:@- aBlock Enumerate all the non-nil members of the set @end table @node WeakSet-copying @subsection WeakSet:@- copying @table @b @meindex deepCopy @item deepCopy Returns a deep copy of the receiver (the instance variables are copies of the receiver's instance variables) @meindex shallowCopy @item shallowCopy Returns a shallow copy of the receiver (the instance variables are not copied) @end table @node WeakSet-loading @subsection WeakSet:@- loading @table @b @meindex postLoad @item postLoad Called after loading an object; must restore it to the state before `preStore' was called. Make it weak again @end table @node WeakValueIdentityDictionary @section WeakValueIdentityDictionary @clindex WeakValueIdentityDictionary @table @b @item Defined in namespace Smalltalk @itemx Superclass: WeakValueLookupTable @itemx Category: Collections-Weak I am similar to a plain identity dictionary, but my values are stored in a weak array; I track which of the values are garbage collected and, as soon as one of them is accessed, I swiftly remove the associations for the garbage collected values @end table @menu @end menu @node WeakValueLookupTable @section WeakValueLookupTable @clindex WeakValueLookupTable @table @b @item Defined in namespace Smalltalk @itemx Superclass: LookupTable @itemx Category: Collections-Weak I am similar to a plain LookupTable, but my values are stored in a weak array; I track which of the values are garbage collected and, as soon as one of them is accessed, I swiftly remove the associations for the garbage collected values @end table @menu * WeakValueLookupTable class-hacks:: (class) * WeakValueLookupTable-hacks:: (instance) * WeakValueLookupTable-rehashing:: (instance) @end menu @node WeakValueLookupTable class-hacks @subsection WeakValueLookupTable class:@- hacks @table @b @meindex primNew:@- @item primNew:@- realSize Answer a new, uninitialized instance of the receiver with the given size @end table @node WeakValueLookupTable-hacks @subsection WeakValueLookupTable:@- hacks @table @b @meindex at:@-ifAbsent:@- @item at:@- key ifAbsent:@- aBlock Answer the value associated to the given key, or the result of evaluating aBlock if the key is not found @meindex at:@-ifPresent:@- @item at:@- key ifPresent:@- aBlock If aKey is absent, answer nil. Else, evaluate aBlock passing the associated value and answer the result of the invocation @meindex includesKey:@- @item includesKey:@- key Answer whether the receiver contains the given key. @end table @node WeakValueLookupTable-rehashing @subsection WeakValueLookupTable:@- rehashing @table @b @meindex rehash @item rehash Rehash the receiver @end table @node WordArray @section WordArray @clindex WordArray @table @b @item Defined in namespace Smalltalk @itemx Superclass: ArrayedCollection @itemx Category: Collections-Sequenceable I am similar to a plain array, but my items are 32-bit integers. @end table @menu * WordArray-built ins:: (instance) @end menu @node WordArray-built ins @subsection WordArray:@- built ins @table @b @meindex at:@-ifAbsent:@- @item at:@- anIndex ifAbsent:@- aBlock Answer the index-th indexed instance variable of the receiver @end table @node WriteStream @section WriteStream @clindex WriteStream @table @b @item Defined in namespace Smalltalk @itemx Superclass: PositionableStream @itemx Category: Streams-Collections I am the class of writeable streams. I only allow write operations to my instances; reading is strictly forbidden. @end table @menu * WriteStream class-instance creation:: (class) * WriteStream-accessing-writing:: (instance) * WriteStream-positioning:: (instance) @end menu @node WriteStream class-instance creation @subsection WriteStream class:@- instance creation @table @b @meindex on:@- @item on:@- aCollection Answer a new instance of the receiver which streams on aCollection. Every item of aCollection is discarded. @meindex with:@- @item with:@- aCollection Answer a new instance of the receiver which streams from the end of aCollection. @meindex with:@-from:@-to:@- @item with:@- aCollection from:@- firstIndex to:@- lastIndex Answer a new instance of the receiver which streams from the firstIndex-th item of aCollection to the lastIndex-th. The pointer is moved to the last item in that range. @end table @node WriteStream-accessing-writing @subsection WriteStream:@- accessing-writing @table @b @meindex contents @item contents Returns a collection of the same type that the stream accesses, up to and including the final element. @meindex next:@-putAll:@-startingAt:@- @item next:@- n putAll:@- aCollection startingAt:@- pos Put n characters or bytes of aCollection, starting at the pos-th, in the collection buffer. @meindex nextPut:@- @item nextPut:@- anObject Store anObject as the next item in the receiver. Grow the collection if necessary @meindex readStream @item readStream Answer a ReadStream on the same contents as the receiver @meindex reverseContents @item reverseContents Returns a collection of the same type that the stream accesses, up to and including the final element, but in reverse order. @end table @node WriteStream-positioning @subsection WriteStream:@- positioning @table @b @meindex emptyStream @item emptyStream Extension - Reset the stream @end table @node ZeroDivide @section ZeroDivide @clindex ZeroDivide @table @b @item Defined in namespace Smalltalk @itemx Superclass: ArithmeticError @itemx Category: Language-Exceptions A ZeroDivide exception is raised by numeric classes when a program tries to divide by zero. Information on the dividend is available to the handler. @end table @menu * ZeroDivide class-instance creation:: (class) * ZeroDivide-accessing:: (instance) * ZeroDivide-description:: (instance) @end menu @node ZeroDivide class-instance creation @subsection ZeroDivide class:@- instance creation @table @b @meindex dividend:@- @item dividend:@- aNumber Create a new ZeroDivide object remembering that the dividend was aNumber. @meindex new @item new Create a new ZeroDivide object; the dividend is conventionally set to zero. @end table @node ZeroDivide-accessing @subsection ZeroDivide:@- accessing @table @b @meindex dividend @item dividend Answer the number that was being divided by zero @end table @node ZeroDivide-description @subsection ZeroDivide:@- description @table @b @meindex description @item description Answer a textual description of the exception. @end table smalltalk-3.2.5/doc/stamp-10000644000175000017500000000013612130456006012375 00000000000000@set UPDATED 8 April 2013 @set UPDATED-MONTH April 2013 @set EDITION 3.2.5 @set VERSION 3.2.5 smalltalk-3.2.5/doc/categories0000644000175000017500000000320712123404352013241 00000000000000Here are the categories currently used in the image. You should use one of these if you think your class matches it: for example, use 'System-Debugger' for a debugger, or 'Collections-External' for disk-based collections, or 'Collections-Sequenceable' when implementing a BitArray... Category Example ------------------------------------------------------------------------------- 'Collections' Collection 'Collections-Keyed' MappedCollection, Dictionary hierarchy 'Collections-Unordered' Bag, Set, IdentitySet 'Collections-Sequenceable' SequenceableCollection hierarchy 'Collections-Weak' WeakSet/WeakLookupTable hierarchies, WeakArray 'Examples-Modules' examples/modules subdirectory 'Examples-Useful' Autoload, GenClass, Tokenizer, ... 'Examples-Cool' Philosophers, Queens, and other examples 'Graphics-Browser' ClassHierarchyBrowser, BrowserShell, BrowserMain 'Graphics-Windows' Blox and View hierarchies 'Language-Implementation' Behavior/ContextPart hierarchies, CompiledMethod 'Language-Data types' Magnitude/Boolean hierarchies, String 'Language-Processes' Process, Semaphore, ProcessorScheduler, ... 'Language-Exceptions' TrappableEvent hierarchy, ExceptionHandler, Signal 'Language-C interface' Memory, CObject and CType hierarchies 'Streams' Stream, TextCollector 'Streams-Collections' PositionableStream hierarchy 'Streams-Files' FileStream, File, Directory, ObjectDumper 'System-Compiler' Compiler hierarchy 'Sockets-Streams' AbstractSocket, DatagramSocket, ... 'Sockets-Protocols' AbstractSocketImpl, Datagram, UDPSocketImpl, ... 'I18n-...' i18n subdirectory smalltalk-3.2.5/doc/gst-libs.info0000644000175000017500000004674312130456010013602 00000000000000This is gst-libs.info, produced by makeinfo version 4.13 from /home/ich/source/smalltalk/release/smalltalk/doc/gst-libs-fixed.texi. INFO-DIR-SECTION Software development START-INFO-DIR-ENTRY * Smalltalk libraries: (gst-libs). The GNU Smalltalk class libraries. END-INFO-DIR-ENTRY Permission is granted to copy, distribute and/or modify this document under the terms of the GNU Free Documentation License, Version 1.2 or any later version published by the Free Software Foundation; with no Invariant Sections, with no Front-Cover Texts, and with no Back-Cover Texts. A copy of the license is included in the section entitled "GNU Free Documentation License".  Indirect: gst-libs.info-1: 697 gst-libs.info-2: 300012 gst-libs.info-3: 426753  Tag Table: (Indirect) Node: Top697 Node: BLOX package2065 Node: BLOX.BArc4695 Node: BLOX.BArc-accessing5016 Node: BLOX.BBalloon6562 Node: BLOX.BBalloon class-accessing7042 Node: BLOX.BBalloon-accessing7470 Node: BLOX.BBalloon-initializing7866 Node: BLOX.BBoundingBox8116 Node: BLOX.BBoundingBox-accessing8595 Node: BLOX.BButton11336 Node: BLOX.BButton class-instance creation11819 Node: BLOX.BButton-accessing12167 Node: BLOX.BButtonLike16368 Node: BLOX.BButtonLike-accessing16723 Node: BLOX.BCanvas17524 Node: BLOX.BCanvas-accessing18298 Node: BLOX.BCanvas-geometry management19158 Node: BLOX.BCanvas-widget protocol20877 Node: BLOX.BCanvasObject22102 Node: BLOX.BCanvasObject class-instance creation22652 Node: BLOX.BCanvasObject-accessing23069 Node: BLOX.BCanvasObject-widget protocol25019 Node: BLOX.BCheckMenuItem26304 Node: BLOX.BCheckMenuItem class-instance creation26759 Node: BLOX.BCheckMenuItem-accessing27082 Node: BLOX.BColorButton27544 Node: BLOX.BColorButton-accessing27981 Node: BLOX.BContainer28448 Node: BLOX.BContainer-accessing28903 Node: BLOX.BDialog29575 Node: BLOX.BDialog class-instance creation30206 Node: BLOX.BDialog class-prompters31123 Node: BLOX.BDialog-accessing34680 Node: BLOX.BDialog-widget protocol35888 Node: BLOX.BDropDown36790 Node: BLOX.BDropDown-accessing37730 Node: BLOX.BDropDown-callbacks43028 Node: BLOX.BDropDown-flexibility43654 Node: BLOX.BDropDown-list box accessing45149 Node: BLOX.BDropDown-widget protocol48200 Node: BLOX.BDropDownEdit49143 Node: BLOX.BDropDownEdit-accessing49687 Node: BLOX.BDropDownEdit-accessing-overrides51861 Node: BLOX.BDropDownEdit-text accessing52178 Node: BLOX.BDropDownList53588 Node: BLOX.BDropDownList-accessing54145 Node: BLOX.BDropDownList-callbacks56850 Node: BLOX.BDropDownList-list box accessing57550 Node: BLOX.BEdit57990 Node: BLOX.BEdit class-instance creation58415 Node: BLOX.BEdit-accessing58753 Node: BLOX.BEdit-widget protocol63136 Node: BLOX.BEmbeddedImage65114 Node: BLOX.BEmbeddedImage-accessing65473 Node: BLOX.BEmbeddedText66422 Node: BLOX.BEmbeddedText-accessing66792 Node: BLOX.BEventSet69748 Node: BLOX.BEventSet class-initializing70454 Node: BLOX.BEventSet-accessing70922 Node: BLOX.BEventSet-initializing71211 Node: BLOX.BEventTarget71594 Node: BLOX.BEventTarget-intercepting events71973 Node: BLOX.BExtended78047 Node: BLOX.BExtended-accessing78873 Node: BLOX.BExtended-customization79137 Node: BLOX.BForm80151 Node: BLOX.BForm-accessing80532 Node: BLOX.BImage81985 Node: BLOX.BImage class-arrows82578 Node: BLOX.BImage class-GNU83080 Node: BLOX.BImage class-icons83334 Node: BLOX.BImage class-instance creation83847 Node: BLOX.BImage class-small icons84605 Node: BLOX.BImage-accessing84987 Node: BLOX.BImage-image management88123 Node: BLOX.BImage-widget protocol90649 Node: BLOX.BLabel90958 Node: BLOX.BLabel class-initialization91358 Node: BLOX.BLabel class-instance creation91638 Node: BLOX.BLabel-accessing92023 Node: BLOX.BLine96738 Node: BLOX.BLine-accessing97092 Node: BLOX.BList97662 Node: BLOX.BList-accessing98045 Node: BLOX.BList-widget protocol110095 Node: BLOX.Blox111478 Node: BLOX.Blox class-C call-outs112615 Node: BLOX.Blox class-event dispatching112944 Node: BLOX.Blox class-instance creation113915 Node: BLOX.Blox class-utility114365 Node: BLOX.Blox-accessing117558 Node: BLOX.Blox-basic118913 Node: BLOX.Blox-creating children119510 Node: BLOX.Blox-customization120531 Node: BLOX.Blox-widget protocol121328 Node: BLOX.BMenu123589 Node: BLOX.BMenu class-instance creation123995 Node: BLOX.BMenu-accessing124412 Node: BLOX.BMenu-callback registration125261 Node: BLOX.BMenuBar126359 Node: BLOX.BMenuBar-accessing126702 Node: BLOX.BMenuItem126937 Node: BLOX.BMenuItem class-instance creation127435 Node: BLOX.BMenuItem-accessing127839 Node: BLOX.BMenuObject128667 Node: BLOX.BMenuObject-accessing129074 Node: BLOX.BMenuObject-callback131421 Node: BLOX.BOval132377 Node: BLOX.BPolyline132709 Node: BLOX.BPolyline-accessing133056 Node: BLOX.BPopupMenu135382 Node: BLOX.BPopupMenu-widget protocol135807 Node: BLOX.BPopupWindow136024 Node: BLOX.BPopupWindow-geometry management136635 Node: BLOX.BPrimitive138703 Node: BLOX.BPrimitive-accessing139102 Node: BLOX.BProgress139333 Node: BLOX.BProgress-accessing139673 Node: BLOX.BRadioButton140919 Node: BLOX.BRadioButton-accessing141276 Node: BLOX.BRadioGroup142164 Node: BLOX.BRadioGroup-accessing142805 Node: BLOX.BRadioGroup-widget protocol143280 Node: BLOX.BRectangle143610 Node: BLOX.BRectangle-accessing143966 Node: BLOX.BScrolledCanvas144454 Node: BLOX.BSpline144891 Node: BLOX.BSpline-accessing145236 Node: BLOX.BText145667 Node: BLOX.BText class-accessing146300 Node: BLOX.BText class-instance creation146643 Node: BLOX.BText-accessing147011 Node: BLOX.BText-attributes152878 Node: BLOX.BText-geometry management154149 Node: BLOX.BText-images155728 Node: BLOX.BText-inserting text157420 Node: BLOX.BText-position & lines159436 Node: BLOX.BTextAttributes161243 Node: BLOX.BTextAttributes class-instance-creation shortcuts161717 Node: BLOX.BTextAttributes-colors164581 Node: BLOX.BTextAttributes-setting attributes165670 Node: BLOX.BTextBindings169828 Node: BLOX.BTextBindings class-instance creation170380 Node: BLOX.BTextTags170632 Node: BLOX.BToggle171009 Node: BLOX.BToggle-accessing171406 Node: BLOX.BTransientWindow172304 Node: BLOX.BTransientWindow class-instance creation172831 Node: BLOX.BTransientWindow-widget protocol173450 Node: BLOX.BViewport174042 Node: BLOX.BViewport-accessing174491 Node: BLOX.BViewport-scrollbars174751 Node: BLOX.BWidget175711 Node: BLOX.BWidget class-popups176288 Node: BLOX.BWidget-accessing177543 Node: BLOX.BWidget-customization182169 Node: BLOX.BWidget-geometry management183798 Node: BLOX.BWidget-widget protocol200264 Node: BLOX.BWindow202305 Node: BLOX.BWindow class-instance creation202766 Node: BLOX.BWindow-accessing203203 Node: BLOX.BWindow-widget protocol205940 Node: BLOX.Gui210650 Node: BLOX.Gui-accessing211058 Node: Complex package211319 Node: Complex211592 Node: Complex class-instance creation212358 Node: Complex-comparing213051 Node: Complex-converting213448 Node: Complex-creation/coercion213930 Node: Complex-math214433 Node: Complex-printing215096 Node: Complex-testing215329 Node: Complex-transcendental functions215655 Node: DBI package216547 Node: DBI.ColumnInfo217139 Node: DBI.ColumnInfo-accessing217425 Node: DBI.ColumnInfo-printing217962 Node: DBI.Connection218285 Node: DBI.Connection class-connecting218779 Node: DBI.Connection class-initialization219712 Node: DBI.Connection-accessing220033 Node: DBI.Connection-connecting220752 Node: DBI.Connection-querying221037 Node: DBI.ConnectionInfo221807 Node: DBI.ConnectionInfo class-instance creation222201 Node: DBI.ConnectionInfo-accessing222702 Node: DBI.FieldConverter223288 Node: DBI.FieldConverter class-instance creation223676 Node: DBI.FieldConverter-actions223973 Node: DBI.FieldConverter-converting-smalltalk224313 Node: DBI.ResultSet224975 Node: DBI.ResultSet-accessing225590 Node: DBI.ResultSet-cursor access226575 Node: DBI.ResultSet-printing227052 Node: DBI.ResultSet-stream protocol227336 Node: DBI.Row227764 Node: DBI.Row-accessing228076 Node: DBI.Row-printing229024 Node: DBI.Statement229236 Node: DBI.Statement class-instance creation229578 Node: DBI.Statement-querying229856 Node: DBI.Table230402 Node: DBI.Table-accessing230698 Node: DBI.Table-core231122 Node: DBI.Table-printing231311 Node: DebugTools package231503 Node: Debugger231789 Node: Debugger class-disabling debugging232451 Node: Debugger class-instance creation232693 Node: Debugger class-source code233075 Node: Debugger-inferior process properties233349 Node: Debugger-stepping commands233849 Node: Iconv/I18N packages234946 Node: I18N.BigEndianFileStream237215 Node: I18N.EncodedStream237586 Node: I18N.EncodedStream class-initializing238132 Node: I18N.EncodedStream class-instance creation239024 Node: I18N.EncodedString240914 Node: I18N.EncodedString class-accessing241730 Node: I18N.EncodedString class-instance creation242059 Node: I18N.EncodedString-accessing242591 Node: I18N.EncodedString-copying243288 Node: I18N.EncodedString-initializing243612 Node: I18N.EncodedString-printing243930 Node: I18N.EncodedStringFactory244368 Node: I18N.EncodedStringFactory class-instance creation244973 Node: I18N.EncodedStringFactory-accessing245352 Node: I18N.EncodedStringFactory-instance creation245750 Node: I18N.Encoder246474 Node: I18N.Encoder class-instance creation247038 Node: I18N.Encoder-stream operations247474 Node: I18N.FileStreamSegment248833 Node: I18N.FileStreamSegment-basic249274 Node: I18N.IncompleteSequenceError249592 Node: I18N.IncompleteSequenceError-accessing250168 Node: I18N.InvalidCharsetError250432 Node: I18N.InvalidCharsetError-accessing250905 Node: I18N.InvalidSequenceError251153 Node: I18N.InvalidSequenceError-accessing251597 Node: I18N.LcMessages251849 Node: I18N.LcMessages class-accessing252320 Node: I18N.LcMessages-accessing252707 Node: I18N.LcMessages-opening MO files253446 Node: I18N.LcMessagesCatalog254244 Node: I18N.LcMessagesDomain254634 Node: I18N.LcMessagesDomain class-opening MO files255759 Node: I18N.LcMessagesDomain-handling the cache256150 Node: I18N.LcMessagesDomain-querying256689 Node: I18N.LcMessagesDummyDomain257812 Node: I18N.LcMessagesMoFileVersion0258246 Node: I18N.LcMessagesMoFileVersion0 class-documentation258954 Node: I18N.LcMessagesMoFileVersion0 class-plurals267018 Node: I18N.LcMessagesMoFileVersion0-flushing the cache267668 Node: I18N.LcMessagesTerritoryDomain268109 Node: I18N.LcMessagesTerritoryDomain class-instance creation268598 Node: I18N.LcMonetary268978 Node: I18N.LcMonetary class-accessing269527 Node: I18N.LcMonetary-printing269913 Node: I18N.LcMonetaryISO270712 Node: I18N.LcMonetaryISO class-accessing271021 Node: I18N.LcNumeric271297 Node: I18N.LcNumeric class-accessing271787 Node: I18N.LcNumeric-printing272168 Node: I18N.LcPrintFormats272672 Node: I18N.LcPrintFormats-printing273250 Node: I18N.LcTime273760 Node: I18N.LcTime class-accessing274273 Node: I18N.LcTime-printing274639 Node: I18N.LcTime-tests276935 Node: I18N.Locale277169 Node: I18N.Locale class-C call-outs277932 Node: I18N.Locale class-initialization278169 Node: I18N.Locale class-instance creation278595 Node: I18N.Locale-C call-outs279249 Node: I18N.Locale-subobjects279495 Node: I18N.LocaleConventions280124 Node: I18N.LocaleConventions class-accessing280585 Node: I18N.LocaleConventions-accessing281309 Node: I18N.LocaleData281640 Node: I18N.LocaleData class-accessing282167 Node: I18N.LocaleData class-database283238 Node: I18N.LocaleData-accessing283875 Node: I18N.LocaleData-initialization285048 Node: I18N.RTEAlternativeNode285448 Node: I18N.RTEAlternativeNode class-compiling285838 Node: I18N.RTEAlternativeNode-computing286258 Node: I18N.RTEBinaryNode286834 Node: I18N.RTEBinaryNode class-compiling287253 Node: I18N.RTEBinaryNode-compiling287621 Node: I18N.RTEBinaryNode-computing287932 Node: I18N.RTELiteralNode288474 Node: I18N.RTELiteralNode class-initializing288852 Node: I18N.RTELiteralNode-computing289165 Node: I18N.RTENegationNode289595 Node: I18N.RTENegationNode class-initializing289980 Node: I18N.RTENegationNode-computing290295 Node: I18N.RTEParameterNode290752 Node: I18N.RTEParameterNode-computing291090 Node: I18N.RunTimeExpression291407 Node: I18N.RunTimeExpression class-compiling291870 Node: I18N.RunTimeExpression class-initializing292494 Node: I18N.RunTimeExpression class-instance creation292869 Node: I18N.RunTimeExpression-computing293244 Node: Sockets package293669 Node: Sockets.AbstractSocket295806 Node: Sockets.AbstractSocket class-defaults297220 Node: Sockets.AbstractSocket class-instance creation298149 Node: Sockets.AbstractSocket class-timed-out operations298984 Node: Sockets.AbstractSocket class-well known ports300012 Node: Sockets.AbstractSocket-accessing302135 Node: Sockets.AbstractSocket-printing303607 Node: Sockets.AbstractSocket-socket options303939 Node: Sockets.AbstractSocket-stream protocol304896 Node: Sockets.AbstractSocket-testing305682 Node: Sockets.AbstractSocketImpl305978 Node: Sockets.AbstractSocketImpl class-abstract307271 Node: Sockets.AbstractSocketImpl class-C call-outs307745 Node: Sockets.AbstractSocketImpl class-C constants308826 Node: Sockets.AbstractSocketImpl class-socket creation309366 Node: Sockets.AbstractSocketImpl-accessing309752 Node: Sockets.AbstractSocketImpl-asynchronous operations310937 Node: Sockets.AbstractSocketImpl-C call-outs311697 Node: Sockets.AbstractSocketImpl-C constants312763 Node: Sockets.AbstractSocketImpl-socket operations313097 Node: Sockets.AbstractSocketImpl-socket options314982 Node: Sockets.CAddrInfoStruct317057 Node: Sockets.CAddrInfoStruct class-C call-outs317498 Node: Sockets.CAddrInfoStruct-C call-outs317827 Node: Sockets.CAddrInfoStruct-C function wrappers318201 Node: Sockets.CSockAddrIn6Struct318549 Node: Sockets.Datagram318818 Node: Sockets.Datagram class-instance creation319572 Node: Sockets.Datagram-accessing320903 Node: Sockets.DatagramSocket322197 Node: Sockets.DatagramSocket class-accessing323393 Node: Sockets.DatagramSocket class-initialization324085 Node: Sockets.DatagramSocket class-instance creation324471 Node: Sockets.DatagramSocket-accessing325513 Node: Sockets.DatagramSocket-direct operations326517 Node: Sockets.DatagramSocketImpl326852 Node: Sockets.DatagramSocketImpl class-parameters327481 Node: Sockets.DatagramSocketImpl-accessing327901 Node: Sockets.DatagramSocketImpl-C constants328350 Node: Sockets.DatagramSocketImpl-socket operations328820 Node: Sockets.DummyStream330054 Node: Sockets.ICMP6SocketImpl330325 Node: Sockets.ICMP6SocketImpl class-C constants330953 Node: Sockets.ICMPSocketImpl331186 Node: Sockets.ICMPSocketImpl class-C constants331810 Node: Sockets.IP6Address332041 Node: Sockets.IP6Address class-C constants332744 Node: Sockets.IP6Address class-constants333102 Node: Sockets.IP6Address class-initialization333497 Node: Sockets.IP6Address class-instance creation334121 Node: Sockets.IP6Address-accessing335229 Node: Sockets.IP6Address-printing335722 Node: Sockets.IPAddress335976 Node: Sockets.IPAddress class-C constants336672 Node: Sockets.IPAddress class-constants336966 Node: Sockets.IPAddress class-initialization337355 Node: Sockets.IPAddress class-instance creation337979 Node: Sockets.IPAddress-accessing341885 Node: Sockets.IPAddress-printing343049 Node: Sockets.MulticastSocket343298 Node: Sockets.MulticastSocket-instance creation344089 Node: Sockets.MulticastSocketImpl344938 Node: Sockets.MulticastSocketImpl-multicasting345429 Node: Sockets.OOBSocketImpl346234 Node: Sockets.OOBSocketImpl-C constants346773 Node: Sockets.OOBSocketImpl-implementation347025 Node: Sockets.RawSocketImpl347445 Node: Sockets.RawSocketImpl class-parameters347926 Node: Sockets.ReadBuffer348184 Node: Sockets.ReadBuffer class-instance creation348753 Node: Sockets.ReadBuffer-accessing-reading349246 Node: Sockets.ReadBuffer-buffer handling350311 Node: Sockets.ServerSocket351393 Node: Sockets.ServerSocket class-accessing352374 Node: Sockets.ServerSocket class-instance creation352712 Node: Sockets.ServerSocket-accessing354254 Node: Sockets.ServerSocket-initializing355203 Node: Sockets.Socket355618 Node: Sockets.Socket class-accessing356154 Node: Sockets.Socket class-tests356528 Node: Sockets.Socket class-well known ports359070 Node: Sockets.Socket-stream protocol359380 Node: Sockets.SocketAddress360423 Node: Sockets.SocketAddress class-abstract361493 Node: Sockets.SocketAddress class-accessing362253 Node: Sockets.SocketAddress class-C call-outs364165 Node: Sockets.SocketAddress class-C constants364559 Node: Sockets.SocketAddress class-creating sockets364995 Node: Sockets.SocketAddress class-host name lookup365620 Node: Sockets.SocketAddress class-initialization366457 Node: Sockets.SocketAddress-accessing367355 Node: Sockets.SocketAddress-testing368426 Node: Sockets.SocketImpl368716 Node: Sockets.SocketImpl class-parameters369241 Node: Sockets.SocketImpl-abstract369523 Node: Sockets.SocketImpl-socket operations369880 Node: Sockets.StreamSocket370342 Node: Sockets.StreamSocket class-accessing371114 Node: Sockets.StreamSocket class-initialize371809 Node: Sockets.StreamSocket class-instance creation372149 Node: Sockets.StreamSocket-accessing373052 Node: Sockets.StreamSocket-accessing-reading373427 Node: Sockets.StreamSocket-out-of-band data374068 Node: Sockets.StreamSocket-printing374448 Node: Sockets.StreamSocket-stream protocol374778 Node: Sockets.TCPSocketImpl376213 Node: Sockets.TCPSocketImpl class-C constants376869 Node: Sockets.TCPSocketImpl-socket options377205 Node: Sockets.UDPSocketImpl377587 Node: Sockets.UDPSocketImpl class-C constants378250 Node: Sockets.UDPSocketImpl-multicasting378551 Node: Sockets.UnixAddress379476 Node: Sockets.UnixAddress class-C constants380391 Node: Sockets.UnixAddress class-initialization380700 Node: Sockets.UnixAddress class-instance creation381338 Node: Sockets.UnixAddress-accessing381867 Node: Sockets.UnixAddress-printing382292 Node: Sockets.UnixAddress-testing382587 Node: Sockets.UnixDatagramSocketImpl382866 Node: Sockets.UnixDatagramSocketImpl-socket operations383398 Node: Sockets.UnixSocketImpl383658 Node: Sockets.UnixSocketImpl-socket operations384156 Node: Sockets.WriteBuffer384384 Node: Sockets.WriteBuffer-accessing-writing384933 Node: Sockets.WriteBuffer-buffer handling385313 Node: Sockets.WriteBuffer-testing385892 Node: ZLib package386123 Node: ZLib.DeflateStream387228 Node: ZLib.DeflateStream class-instance creation387613 Node: ZLib.DeflateWriteStream388090 Node: ZLib.GZipDeflateStream388464 Node: ZLib.GZipDeflateStream class-instance creation388884 Node: ZLib.GZipDeflateWriteStream389377 Node: ZLib.GZipInflateStream389750 Node: ZLib.InflateStream390106 Node: ZLib.RawDeflateStream390465 Node: ZLib.RawDeflateStream class-instance creation390872 Node: ZLib.RawDeflateWriteStream391605 Node: ZLib.RawDeflateWriteStream class-instance creation392031 Node: ZLib.RawInflateStream392518 Node: ZLib.RawInflateStream-positioning392914 Node: ZLib.ZlibError394005 Node: ZLib.ZlibError-accessing394377 Node: ZLib.ZlibReadStream394645 Node: ZLib.ZlibReadStream-accessing-reading395107 Node: ZLib.ZlibReadStream-streaming395697 Node: ZLib.ZlibStream396513 Node: ZLib.ZlibStream class-accessing397034 Node: ZLib.ZlibStream class-instance creation397759 Node: ZLib.ZlibStream-streaming398173 Node: ZLib.ZlibWriteStream398616 Node: ZLib.ZlibWriteStream-streaming399032 Node: XML/XPath/XSL packages400867 Node: Building a DOM from XML401241 Node: Building XML406696 Node: Using DTDs409883 Node: XSL Processing413174 Node: Attributions414630 Node: Class index415024 Node: Method index426753 Node: Cross-reference638102  End Tag Table smalltalk-3.2.5/doc/gst-base.info-50000644000175000017500000010753312130456007013726 00000000000000This is gst-base.info, produced by makeinfo version 4.13 from /home/ich/source/smalltalk/release/smalltalk/doc/gst-base-fixed.texi. INFO-DIR-SECTION Software development START-INFO-DIR-ENTRY * Smalltalk base classes: (gst-base). The GNU Smalltalk base classes. END-INFO-DIR-ENTRY Permission is granted to copy, distribute and/or modify this document under the terms of the GNU Free Documentation License, Version 1.2 or any later version published by the Free Software Foundation; with no Invariant Sections, with no Front-Cover Texts, and with no Back-Cover Texts. A copy of the license is included in the section entitled "GNU Free Documentation License".  File: gst-base.info, Node: Cross-reference, Prev: Method index, Up: Top Selector cross-reference ************************ [index] * Menu: * #: CompiledCode-basic. (line 6) * %: String-regex. (line 31) * *: Number-retrying. (line 32) * + <1>: Symbol-basic. (line 10) * +: Number-retrying. (line 41) * -: Number-retrying. (line 12) * /: Number-retrying. (line 16) * <= <1>: SequenceableCollection-sorting. (line 6) * <= <2>: Collection-sorting. (line 6) * <=: ArrayedCollection-sorting. (line 6) * = <1>: Stream-accessing-reading. (line 54) * = <2>: Number-retrying. (line 6) * =: Association-testing. (line 6) * =~: String-regex. (line 137) * >>: CompiledMethod-saving and loading. (line 6) * add_: Collection-copying SequenceableCollections. (line 6) * addSubspace_: Namespace class-disabling instance creation. (line 6) * addToBeFinalized <1>: CString class-instance creation. (line 10) * addToBeFinalized <2>: CScalar class-instance creation. (line 14) * addToBeFinalized <3>: CObject-finalization. (line 6) * addToBeFinalized: CCompound class-instance creation. (line 10) * allFilesMatching_do_: Directory class-file operations. (line 6) * allLiteralsDo_: CompiledCode-literals - iteration. (line 6) * AM: DateTime-computations. (line 22) * append <1>: FileDescriptor class-still unclassified. (line 6) * append: FileDescriptor class-instance creation. (line 15) * arguments_do_ifError_: SystemDictionary-command-line. (line 6) * array: CType class-C instance creation. (line 12) * asciiValue: Character-built ins. (line 9) * asInteger: Character-built ins. (line 9) * associationAt_: ProcessorScheduler-basic. (line 15) * asString <1>: Stream-compiling. (line 6) * asString <2>: PositionableStream-compiling. (line 9) * asString: FileStream-compiling. (line 6) * asyncCallFrom_: CCallable-calling. (line 14) * asyncCCall_args_: CompiledMethod class-c call-outs. (line 6) * at_ <1>: VariableBinding-saving and loading. (line 6) * at_: PluggableAdaptor class-creating instances. (line 20) * at_/#at_put_ <1>: Stream-testing. (line 13) * at_/#at_put_ <2>: SequenceableCollection-testing. (line 16) * at_/#at_put_: Collection-testing collections. (line 25) * at_put_ <1>: PluggableAdaptor class-creating instances. (line 20) * at_put_ <2>: CString-accessing. (line 6) * at_put_ <3>: CString class-accessing. (line 6) * at_put_ <4>: CScalar-accessing. (line 6) * at_put_: BindingDictionary-accessing. (line 6) * autoload: Autoload class-instance creation. (line 14) * basicNew: Behavior-built ins. (line 6) * basicNew_: Behavior-built ins. (line 11) * basicPrint: Exception-built ins. (line 6) * become_: Object-built ins. (line 44) * binaryRepresentationObject <1>: PluggableProxy class-accessing. (line 6) * binaryRepresentationObject: Object-saving and loading. (line 23) * binaryRepresentationVersion: VersionableObjectProxy class-saving and restoring. (line 6) * blockAt_: CompiledBlock-saving and loading. (line 6) * byte <1>: UndefinedObject-class polymorphism. (line 33) * byte <2>: Class-instance creation. (line 27) * byte: Behavior-testing the class hierarchy. (line 19) * callFrom_into_: CCallable-calling. (line 30) * cCall_returning_args_: CompiledMethod class-c call-outs. (line 10) * changed: Object-change and update. (line 34) * changed_: Object-change and update. (line 34) * character <1>: UndefinedObject-class polymorphism. (line 33) * character <2>: Class-instance creation. (line 27) * character: Behavior-testing the class hierarchy. (line 19) * checkError: FileDescriptor-basic. (line 6) * class: Object-class type methods. (line 6) * close <1>: FileDescriptor class-still unclassified. (line 6) * close: FileDescriptor class-instance creation. (line 15) * cObject: CObject-conversion. (line 10) * codePoint: Character-built ins. (line 9) * codePoint_: UnicodeCharacter class-built ins. (line 6) * collect_ <1>: SequenceableCollection-basic. (line 26) * collect_ <2>: BindingDictionary-copying. (line 12) * collect_: ArrayedCollection-basic. (line 14) * collection_map_: MappedCollection class-instance creation. (line 10) * compile_: Behavior-built ins. (line 25) * compile_ifError_: Behavior-built ins. (line 33) * continue_ <1>: MethodContext-accessing. (line 27) * continue_ <2>: ContextPart-accessing. (line 49) * continue_: BlockContext-accessing. (line 30) * convertFromVersion_withFixedVariables_instanceVariables_for_: VersionableObjectProxy class-saving and restoring. (line 6) * copy: RunArray-copying. (line 6) * copyEmpty_ <1>: WeakArray-conversion. (line 17) * copyEmpty_: Object-class type methods. (line 6) * create <1>: FileDescriptor class-still unclassified. (line 6) * create: FileDescriptor class-instance creation. (line 15) * day: Date-date computations. (line 9) * debuggingPriority: Behavior-pluggable behavior (not yet implemented). (line 6) * directoryFor_: PackageLoader class-accessing. (line 6) * disableInterrupts: ProcessorScheduler-built ins. (line 6) * display_: Stream-printing. (line 6) * displayString: Number-converting. (line 42) * do_ <1>: SortedCollection-enumerating. (line 6) * do_ <2>: SequenceableCollection-testing collections. (line 6) * do_ <3>: RunArray-adding. (line 9) * do_ <4>: Collection-enumeration. (line 9) * do_: Collection-converting. (line 19) * doesNotUnderstand_: MessageNotUnderstood-description. (line 9) * double <1>: UndefinedObject-class polymorphism. (line 33) * double <2>: Class-instance creation. (line 27) * double: Behavior-testing the class hierarchy. (line 19) * dumpTo_ <1>: DumperProxy class-instance creation. (line 6) * dumpTo_: AlternativeObjectProxy class-instance creation. (line 11) * enableInterrupts: ProcessorScheduler-built ins. (line 6) * ensure_ <1>: Process-basic. (line 41) * ensure_ <2>: MethodContext-accessing. (line 13) * ensure_ <3>: ContextPart-built ins. (line 6) * ensure_ <4>: ContextPart-accessing. (line 49) * ensure_ <5>: BlockContext-accessing. (line 16) * ensure_: BlockClosure-unwind protection. (line 21) * error_ <1>: CompiledMethod-compiling. (line 21) * error_ <2>: BlockClosure-exception handling. (line 6) * error_ <3>: Behavior-method dictionary. (line 19) * error_: Behavior-evaluating. (line 21) * examine: Object-debugging. (line 12) * examineOn_ <1>: CCompound-debugging. (line 9) * examineOn_: CCompound class-subclass creation. (line 28) * exceptionHandlingInternal_: MethodContext-debugging. (line 6) * fileIn: Stream-built ins. (line 16) * finalize: Object-finalization. (line 6) * float <1>: UndefinedObject-class polymorphism. (line 33) * float <2>: Class-instance creation. (line 27) * float: Behavior-testing the class hierarchy. (line 19) * free: CObject-finalization. (line 6) * from_to_keysAndValuesDo_: SequenceableCollection-enumerating. (line 42) * fullName: FilePath-file name management. (line 21) * generateMakefileOnto_: FileStream class-file-in. (line 51) * halt: Halt-description. (line 9) * hash: Symbol class-symbol table. (line 6) * identityHash: BindingDictionary-basic & copying. (line 11) * ifCurtailed_ <1>: Process-basic. (line 41) * ifCurtailed_: ContextPart-built ins. (line 6) * ifTrue_ifFalse_: Symbol-basic. (line 10) * includes_ <1>: WeakIdentitySet-accessing. (line 6) * includes_: IdentitySet-testing. (line 6) * includesClassNamed_: AbstractNamespace-namespace hierarchy. (line 29) * includesGlobalNamed_: AbstractNamespace-namespace hierarchy. (line 23) * includesKey_: AbstractNamespace-namespace hierarchy. (line 23) * inherit: Behavior-testing the class hierarchy. (line 19) * int <1>: UndefinedObject-class polymorphism. (line 33) * int <2>: CType class-C instance creation. (line 12) * int <3>: Class-instance creation. (line 27) * int: Behavior-testing the class hierarchy. (line 19) * int64 <1>: UndefinedObject-class polymorphism. (line 33) * int64 <2>: Class-instance creation. (line 27) * int64: Behavior-testing the class hierarchy. (line 19) * int8 <1>: UndefinedObject-class polymorphism. (line 33) * int8 <2>: Class-instance creation. (line 27) * int8: Behavior-testing the class hierarchy. (line 19) * integerPart: Number-truncation and round off. (line 12) * join: Collection-enumeration. (line 24) * key_class_defaultDictionary_: DeferredVariableBinding class-basic. (line 11) * keysAndValuesDo_: SequenceableCollection-enumerating. (line 17) * line: Stream-built ins. (line 16) * loadFrom_: DumperProxy-saving and restoring. (line 6) * lowerPriority: Process-basic. (line 17) * mark_: Object-built ins. (line 127) * match_: FilePath-enumerating. (line 6) * mourn: Object-built ins. (line 107) * name <1>: VFS.ArchiveMember-accessing. (line 9) * name: FilePath-file name management. (line 17) * new <1>: Behavior-instance creation. (line 6) * new: AbstractNamespace class-instance creation. (line 6) * new_: Behavior-instance creation. (line 12) * newProcess: ContextPart-accessing. (line 64) * next <1>: Stream-positioning. (line 12) * next <2>: SharedQueue-accessing. (line 15) * next <3>: Generator-stream protocol. (line 13) * next: Generator class-instance creation. (line 11) * nonVersionedInstSize: VersionableObjectProxy class-saving and restoring. (line 6) * not: Symbol-basic. (line 10) * notify: Semaphore-builtins. (line 29) * notifyAll: Semaphore-builtins. (line 29) * on_: AlternativeObjectProxy class-instance creation. (line 11) * on_do_ <1>: Exception-exception handling. (line 6) * on_do_: BlockClosure-unwind protection. (line 21) * on_index_: PluggableAdaptor class-creating instances. (line 25) * outer: Exception-exception handling. (line 13) * parse_with_do_ifError_: Getopt class-instance creation. (line 6) * parseVariableString_: Behavior-parsing class declarations. (line 6) * pass: Exception-exception handling. (line 13) * peek: Generator-stream protocol. (line 13) * PM: DateTime-computations. (line 22) * pointer <1>: UndefinedObject-class polymorphism. (line 33) * pointer <2>: Class-instance creation. (line 27) * pointer: Behavior-testing the class hierarchy. (line 19) * position: PositionableStream-accessing-reading. (line 13) * postLoad <1>: SingletonProxy-saving and restoring. (line 6) * postLoad <2>: PluggableProxy-saving and restoring. (line 6) * postLoad <3>: Object-saving and loading. (line 15) * postLoad: HashedCollection-saving and loading. (line 10) * postStore: PluggableProxy class-accessing. (line 6) * preStore: PluggableProxy class-accessing. (line 6) * primCompile_: Behavior-built ins. (line 33) * primDefineExternFunc_: DLD class-dynamic linking. (line 19) * print: Object-printing. (line 13) * printHierarchy: Behavior-printing hierarchy. (line 6) * printNl: Object-printing. (line 19) * printOn_ <1>: UndefinedObject-printing. (line 9) * printOn_ <2>: Symbol-storing. (line 6) * printOn_ <3>: Symbol-basic. (line 10) * printOn_ <4>: String-printing. (line 6) * printOn_ <5>: Regex-printing. (line 6) * printOn_ <6>: Object-printing. (line 26) * printOn_ <7>: Exception-built ins. (line 6) * printOn_: Character-printing. (line 6) * printString <1>: Symbol-storing. (line 12) * printString <2>: String-printing. (line 10) * printString <3>: ScaledDecimal-printing. (line 6) * printString <4>: Regex-printing. (line 12) * printString: Object-printing. (line 32) * printStringRadix_: Integer-printing. (line 47) * ptr: CType class-C instance creation. (line 12) * quit_: Process-basic. (line 46) * raisePriority: Process-basic. (line 17) * read <1>: FileDescriptor class-still unclassified. (line 6) * read: FileDescriptor class-instance creation. (line 15) * readWrite <1>: FileDescriptor class-still unclassified. (line 6) * readWrite: FileDescriptor class-instance creation. (line 15) * reconstructOriginalObject <1>: SingletonProxy-saving and restoring. (line 6) * reconstructOriginalObject: PluggableProxy-saving and restoring. (line 6) * removeToBeFinalized <1>: FileDescriptor class-still unclassified. (line 6) * removeToBeFinalized: FileDescriptor class-instance creation. (line 15) * resolveBinding: DeferredVariableBinding class-basic. (line 6) * return_: BlockClosure-exception handling. (line 13) * secondClock: Time class-basic (UTC). (line 14) * select_: PositionableStream-class type methods. (line 9) * self: CCallable-calling. (line 6) * selfSmalltalk: CCallable-calling. (line 6) * short <1>: UndefinedObject-class polymorphism. (line 33) * short <2>: Class-instance creation. (line 27) * short: Behavior-testing the class hierarchy. (line 19) * signal: Exception-exception handling. (line 53) * signal_atMilliseconds_: ProcessorScheduler-timed invocation. (line 6) * singleStepWaitingOn_: Process-basic. (line 32) * size: UnicodeString-multibyte encodings. (line 11) * size_stCtime_stMtime_stAtime_isDirectory_: VFS.ArchiveFile-ArchiveMember protocol. (line 6) * skip_ <1>: Stream-positioning. (line 6) * skip_ <2>: PositionableStream-positioning. (line 9) * skip_: FileDescriptor-positioning. (line 6) * skipSeparators: Stream-positioning. (line 12) * specialSelectors: CompiledCode class-tables. (line 26) * species: Object-class type methods. (line 6) * storage: CObject-accessing. (line 6) * subclass_declaration_: CCompound class-subclass creation. (line 32) * subclassResponsibility <1>: Number-testing. (line 14) * subclassResponsibility: CompiledMethod-invoking. (line 6) * timeZoneAbbreviation: DateTime-time zones. (line 29) * trigger: DelayedAdaptor-accessing. (line 12) * uint <1>: UndefinedObject-class polymorphism. (line 33) * uint <2>: Class-instance creation. (line 27) * uint: Behavior-testing the class hierarchy. (line 19) * uint64 <1>: UndefinedObject-class polymorphism. (line 33) * uint64 <2>: Class-instance creation. (line 27) * uint64: Behavior-testing the class hierarchy. (line 19) * upTo_: PositionableStream-class type methods. (line 9) * ushort <1>: UndefinedObject-class polymorphism. (line 33) * ushort <2>: Class-instance creation. (line 27) * ushort: Behavior-testing the class hierarchy. (line 19) * utf32 <1>: UndefinedObject-class polymorphism. (line 33) * utf32 <2>: Class-instance creation. (line 27) * utf32: Behavior-testing the class hierarchy. (line 19) * value <1>: Promise-still unclassified. (line 6) * value <2>: Promise-accessing. (line 6) * value <3>: Promise class-creating instances. (line 6) * value <4>: PluggableAdaptor class-creating instances. (line 6) * value <5>: Continuation-invocation. (line 14) * value: Character-built ins. (line 9) * value_ <1>: UnicodeCharacter class-built ins. (line 6) * value_ <2>: PluggableAdaptor class-creating instances. (line 6) * value_: Continuation-invocation. (line 19) * valueWithoutPreemption: ProcessorScheduler-priorities. (line 36) * valueWithReceiver_withArguments_: CompiledMethod class-instance creation. (line 13) * valueWithUnwind <1>: MethodContext-accessing. (line 33) * valueWithUnwind: BlockClosure-unwind protection. (line 21) * Variable: BindingDictionary-accessing. (line 10) * wait: RecursionLock-accessing. (line 18) * word: Behavior-testing the class hierarchy. (line 19) * write <1>: FileDescriptor class-still unclassified. (line 6) * write: FileDescriptor class-instance creation. (line 15) * yield_: Generator class-instance creation. (line 11) * ~=: Number-retrying. (line 6) smalltalk-3.2.5/doc/gst-load.10000644000175000017500000000231212130455701012763 00000000000000.\" DO NOT MODIFY THIS FILE! It was generated by help2man 1.28. .TH GST-LOAD "1" "April 2013" "gst-load version 3.2.5-4dc033e" "User Commands" .SH NAME gst-load \- test and load packages into a GNU Smalltalk image .SH DESCRIPTION .SS "Usage:" .IP gst-load [ flag ... ] package ... .SH OPTIONS .TP \fB\-q\fR \fB\-\-quiet\fR hide the output .TP \fB\-v\fR \fB\-\-verbose\fR show loaded files .TP \fB\-f\fR \fB\-\-force\fR reload package if already loaded .TP \fB\-n\fR \fB\-\-dry\-run\fR don't save the image after loading .TP \fB\-t\fR \fB\-\-test\fR run SUnit tests if available .TP \fB\-\-start\fR[=\fIARG\fR] start the package and keep running the image .TP \fB\-i\fR \fB\-\-rebuild\-image\fR load into a newly-created image .TP \fB\-I\fR \fB\-\-image\-file\fR=\fIFILE\fR load into the specified image .TP \fB\-\-kernel\-dir\fR=\fIPATH\fR use the specified kernel directory .TP \fB\-h\fR \fB\-\-help\fR show this message .TP \fB\-\-version\fR print version information and exit .SH "SEE ALSO" The full documentation for .B gst-load is maintained as a Texinfo manual. If the .B info and .B gst-load programs are properly installed at your site, the command .IP .B info gst .PP should give you access to the complete manual. smalltalk-3.2.5/doc/zlib.texi0000644000175000017500000003635412130455701013037 00000000000000@c Define the class index, method index, and selector cross-reference @ifclear CLASS-INDICES @set CLASS-INDICES @defindex cl @defcodeindex me @defcodeindex sl @end ifclear @c These are used for both TeX and HTML @set BEFORE1 @set AFTER1 @set BEFORE2 @set AFTER2 @ifinfo @c Use asis so that leading and trailing spaces are meaningful. @c Remember we're inside a @menu command, hence the blanks are @c kept in the output. @set BEFORE1 @asis{* } @set AFTER1 @asis{::} @set BEFORE2 @asis{ (} @set AFTER2 @asis{)} @end ifinfo @macro class {a,b} @value{BEFORE1}\a\\a\@b{\b\}@value{AFTER1} @end macro @macro superclass {a,b} \a\\a\@value{BEFORE2}@i{\b\}@value{AFTER2} @end macro @ifnotinfo @macro begindetailmenu @display @end macro @macro enddetailmenu @end display @end macro @end ifnotinfo @ifinfo @macro begindetailmenu @detailmenu @end macro @macro enddetailmenu @end detailmenu @end macro @end ifinfo @iftex @macro beginmenu @end macro @macro endmenu @end macro @end iftex @ifnottex @macro beginmenu @menu @end macro @macro endmenu @end menu @end macro @end ifnottex @beginmenu @ifnottex Alphabetic list: * ZLib.DeflateStream:: * ZLib.DeflateWriteStream:: * ZLib.GZipDeflateStream:: * ZLib.GZipDeflateWriteStream:: * ZLib.GZipInflateStream:: * ZLib.InflateStream:: * ZLib.RawDeflateStream:: * ZLib.RawDeflateWriteStream:: * ZLib.RawInflateStream:: * ZLib.ZlibError:: * ZLib.ZlibReadStream:: * ZLib.ZlibStream:: * ZLib.ZlibWriteStream:: @end ifnottex @ifinfo Class tree: @end ifinfo @iftex @section Tree @end iftex @ifnotinfo Classes documented in this manual are @b{boldfaced}. @end ifnotinfo @begindetailmenu @superclass{@t{}, Object} @superclass{@t{ }, Exception} @superclass{@t{ }, Error} @class{@t{ }, ZLib.ZlibError} @superclass{@t{ }, Iterable} @superclass{@t{ }, Stream} @class{@t{ }, ZLib.ZlibStream} @class{@t{ }, ZLib.ZlibReadStream} @class{@t{ }, ZLib.RawDeflateStream} @class{@t{ }, ZLib.DeflateStream} @class{@t{ }, ZLib.GZipDeflateStream} @class{@t{ }, ZLib.RawInflateStream} @class{@t{ }, ZLib.GZipInflateStream} @class{@t{ }, ZLib.InflateStream} @class{@t{ }, ZLib.ZlibWriteStream} @class{@t{ }, ZLib.RawDeflateWriteStream} @class{@t{ }, ZLib.DeflateWriteStream} @class{@t{ }, ZLib.GZipDeflateWriteStream} @enddetailmenu @endmenu @unmacro class @unmacro superclass @unmacro endmenu @unmacro beginmenu @unmacro enddetailmenu @unmacro begindetailmenu @node ZLib.DeflateStream @section ZLib.DeflateStream @clindex ZLib.DeflateStream @table @b @item Defined in namespace ZLib @itemx Superclass: ZLib.RawDeflateStream @itemx Category: Examples-Useful Instances of this class produce "standard" (zlib, RFC1950) deflated data. @end table @menu * ZLib.DeflateStream class-instance creation:: (class) @end menu @node ZLib.DeflateStream class-instance creation @subsection ZLib.DeflateStream class:@- instance creation @table @b @meindex compressingTo:@- @slindex nextPut:@- @item compressingTo:@- aStream Answer a stream that receives data via #nextPut:@- and compresses it onto aStream. @meindex compressingTo:@-level:@- @slindex nextPut:@- @item compressingTo:@- aStream level:@- level Answer a stream that receives data via #nextPut:@- and compresses it onto aStream with the given compression level. @end table @node ZLib.DeflateWriteStream @section ZLib.DeflateWriteStream @clindex ZLib.DeflateWriteStream @table @b @item Defined in namespace ZLib @itemx Superclass: ZLib.RawDeflateWriteStream @itemx Category: Examples-Useful Instances of this class produce "standard" (zlib, RFC1950) deflated data. @end table @menu @end menu @node ZLib.GZipDeflateStream @section ZLib.GZipDeflateStream @clindex ZLib.GZipDeflateStream @table @b @item Defined in namespace ZLib @itemx Superclass: ZLib.RawDeflateStream @itemx Category: Examples-Useful Instances of this class produce GZip (RFC1952) deflated data. @end table @menu * ZLib.GZipDeflateStream class-instance creation:: (class) @end menu @node ZLib.GZipDeflateStream class-instance creation @subsection ZLib.GZipDeflateStream class:@- instance creation @table @b @meindex compressingTo:@- @slindex nextPut:@- @item compressingTo:@- aStream Answer a stream that receives data via #nextPut:@- and compresses it onto aStream. @meindex compressingTo:@-level:@- @slindex nextPut:@- @item compressingTo:@- aStream level:@- level Answer a stream that receives data via #nextPut:@- and compresses it onto aStream with the given compression level. @end table @node ZLib.GZipDeflateWriteStream @section ZLib.GZipDeflateWriteStream @clindex ZLib.GZipDeflateWriteStream @table @b @item Defined in namespace ZLib @itemx Superclass: ZLib.RawDeflateWriteStream @itemx Category: Examples-Useful Instances of this class produce GZip (RFC1952) deflated data. @end table @menu @end menu @node ZLib.GZipInflateStream @section ZLib.GZipInflateStream @clindex ZLib.GZipInflateStream @table @b @item Defined in namespace ZLib @itemx Superclass: ZLib.RawInflateStream @itemx Category: Examples-Useful Instances of this class reinflate GZip (RFC1952) deflated data. @end table @menu @end menu @node ZLib.InflateStream @section ZLib.InflateStream @clindex ZLib.InflateStream @table @b @item Defined in namespace ZLib @itemx Superclass: ZLib.RawInflateStream @itemx Category: Examples-Useful Instances of this class reinflate "standard" (zlib, RFC1950) deflated data. @end table @menu @end menu @node ZLib.RawDeflateStream @section ZLib.RawDeflateStream @clindex ZLib.RawDeflateStream @table @b @item Defined in namespace ZLib @itemx Superclass: ZLib.ZlibReadStream @itemx Category: Examples-Useful Instances of this class produce "raw" (PKZIP) deflated data. @end table @menu * ZLib.RawDeflateStream class-instance creation:: (class) @end menu @node ZLib.RawDeflateStream class-instance creation @subsection ZLib.RawDeflateStream class:@- instance creation @table @b @meindex compressingTo:@- @slindex nextPut:@- @item compressingTo:@- aStream Answer a stream that receives data via #nextPut:@- and compresses it onto aStream. @meindex compressingTo:@-level:@- @slindex nextPut:@- @item compressingTo:@- aStream level:@- level Answer a stream that receives data via #nextPut:@- and compresses it onto aStream with the given compression level. @meindex on:@- @item on:@- aStream Answer a stream that compresses the data in aStream with the default compression level. @meindex on:@-level:@- @item on:@- aStream level:@- compressionLevel Answer a stream that compresses the data in aStream with the given compression level. @end table @node ZLib.RawDeflateWriteStream @section ZLib.RawDeflateWriteStream @clindex ZLib.RawDeflateWriteStream @table @b @item Defined in namespace ZLib @itemx Superclass: ZLib.ZlibWriteStream @itemx Category: Examples-Useful Instances of this class produce "raw" (PKZIP) deflated data. @end table @menu * ZLib.RawDeflateWriteStream class-instance creation:: (class) @end menu @node ZLib.RawDeflateWriteStream class-instance creation @subsection ZLib.RawDeflateWriteStream class:@- instance creation @table @b @meindex on:@- @item on:@- aWriteStream Answer a stream that compresses the data in aStream with the default compression level. @meindex on:@-level:@- @item on:@- aWriteStream level:@- compressionLevel Answer a stream that compresses the data in aStream with the given compression level. @end table @node ZLib.RawInflateStream @section ZLib.RawInflateStream @clindex ZLib.RawInflateStream @table @b @item Defined in namespace ZLib @itemx Superclass: ZLib.ZlibReadStream @itemx Category: Examples-Useful Instances of this class reinflate "raw" (PKZIP) deflated data. @end table @menu * ZLib.RawInflateStream-positioning:: (instance) @end menu @node ZLib.RawInflateStream-positioning @subsection ZLib.RawInflateStream:@- positioning @table @b @meindex copyFrom:@-to:@- @slindex position @item copyFrom:@- start to:@- end Answer the data on which the receiver is streaming, from the start-th item to the end-th. Note that this method is 0-based, unlike the one in Collection, because a Stream's #position method returns 0-based values. Notice that this class can only provide the illusion of random access, by appropriately rewinding the input stream or skipping compressed data. @meindex isPositionable @slindex skip:@- @item isPositionable Answer true if the stream supports moving backwards with #skip:@-. @meindex position:@- @item position:@- anInteger Set the current position in the stream to anInteger. Notice that this class can only provide the illusion of random access, by appropriately rewinding the input stream or skipping compressed data. @meindex reset @item reset Reset the stream to the beginning of the compressed data. @meindex skip:@- @item skip:@- anInteger Move the current position by anInteger places, either forwards or backwards. @end table @node ZLib.ZlibError @section ZLib.ZlibError @clindex ZLib.ZlibError @table @b @item Defined in namespace ZLib @itemx Superclass: Error @itemx Category: Examples-Useful This exception is raised whenever there is an error in a compressed stream. @end table @menu * ZLib.ZlibError-accessing:: (instance) @end menu @node ZLib.ZlibError-accessing @subsection ZLib.ZlibError:@- accessing @table @b @meindex stream @item stream Answer the ZlibStream that caused the error. @meindex stream:@- @item stream:@- anObject Set the ZlibStream that caused the error. @end table @node ZLib.ZlibReadStream @section ZLib.ZlibReadStream @clindex ZLib.ZlibReadStream @table @b @item Defined in namespace ZLib @itemx Superclass: ZLib.ZlibStream @itemx Category: Examples-Useful This abstract class implements the basic buffering that is used for communication with zlib. @end table @menu * ZLib.ZlibReadStream-accessing-reading:: (instance) * ZLib.ZlibReadStream-streaming:: (instance) @end menu @node ZLib.ZlibReadStream-accessing-reading @subsection ZLib.ZlibReadStream:@- accessing-reading @table @b @meindex nextAvailable:@-into:@-startingAt:@- @item nextAvailable:@- anInteger into:@- aCollection startingAt:@- pos Place up to anInteger objects from the receiver into aCollection, starting from position pos and stopping if no more data is available. @meindex nextAvailable:@-putAllOn:@- @item nextAvailable:@- anInteger putAllOn:@- aStream Copy up to anInteger objects from the receiver to aStream, stopping if no more data is available. @end table @node ZLib.ZlibReadStream-streaming @subsection ZLib.ZlibReadStream:@- streaming @table @b @meindex atEnd @item atEnd Answer whether the stream has got to an end @meindex next @item next Return the next object (character or byte) in the receiver. @meindex peek @item peek Returns the next element of the stream without moving the pointer. Returns nil when at end of stream. @meindex peekFor:@- @item peekFor:@- anObject Returns true and gobbles the next element from the stream of it is equal to anObject, returns false and doesn't gobble the next element if the next element is not equal to anObject. @meindex position @item position Answer the current value of the stream pointer. Note that only inflating streams support random access to the stream data. @end table @node ZLib.ZlibStream @section ZLib.ZlibStream @clindex ZLib.ZlibStream @table @b @item Defined in namespace ZLib @itemx Superclass: Stream @itemx Category: Examples-Useful This abstract class implements the basic interface to the zlib module. Its layout matches what is expected by the C code. @end table @menu * ZLib.ZlibStream class-accessing:: (class) * ZLib.ZlibStream class-instance creation:: (class) * ZLib.ZlibStream-streaming:: (instance) @end menu @node ZLib.ZlibStream class-accessing @subsection ZLib.ZlibStream class:@- accessing @table @b @meindex bufferSize @item bufferSize Answer the size of the output buffers that are passed to zlib. Each zlib stream uses a buffer of this size. @meindex bufferSize:@- @item bufferSize:@- anInteger Set the size of the output buffers that are passed to zlib. Each zlib stream uses a buffer of this size. @meindex defaultCompressionLevel @item defaultCompressionLevel Return the default compression level used by deflating streams. @meindex defaultCompressionLevel:@- @item defaultCompressionLevel:@- anInteger Set the default compression level used by deflating streams. It should be a number between 1 and 9. @end table @node ZLib.ZlibStream class-instance creation @subsection ZLib.ZlibStream class:@- instance creation @table @b @meindex new @item new This method should not be called for instances of this class. @meindex on:@- @item on:@- aStream Answer an instance of the receiver that decorates aStream. @end table @node ZLib.ZlibStream-streaming @subsection ZLib.ZlibStream:@- streaming @table @b @meindex isExternalStream @item isExternalStream Answer whether the receiver streams on a file or socket. @meindex name @item name Return the name of the underlying stream. @meindex species @slindex upTo:@- @item species Return the type of the collections returned by #upTo:@- etc. @meindex stream @item stream Answer the wrapped stream. @end table @node ZLib.ZlibWriteStream @section ZLib.ZlibWriteStream @clindex ZLib.ZlibWriteStream @table @b @item Defined in namespace ZLib @itemx Superclass: ZLib.ZlibStream @itemx Category: Examples-Useful This abstract class implements the basic buffering that is used for communication with zlib in a WriteStream decorator. @end table @menu * ZLib.ZlibWriteStream-streaming:: (instance) @end menu @node ZLib.ZlibWriteStream-streaming @subsection ZLib.ZlibWriteStream:@- streaming @table @b @meindex close @item close Finish the deflated output to the destination stream using Z_FINISH. The destination stream is closed, which implies flushing. @meindex contents @slindex contents @item contents Finish the deflated output to the destination stream using Z_FINISH and return the deflated data (requires the destination stream to support #contents). @meindex finish @item finish Finish the deflated output to the destination stream using Z_FINISH. The destination stream is not flushed. @meindex flush @item flush Flush the deflated output to the destination stream, and flush the destination stream. @meindex flushBuffer @item flushBuffer Flush the deflated output to the destination stream. @meindex flushDictionary @item flushDictionary Flush the deflated output to the destination stream using Z_FULL_FLUSH, and flush the destination stream. @meindex next:@-putAll:@-startingAt:@- @item next:@- n putAll:@- aCollection startingAt:@- pos Put n characters or bytes of aCollection, starting at the pos-th, in the deflation buffer. @meindex nextPut:@- @item nextPut:@- aByte Append a character or byte (depending on whether the destination stream works on a ByteArray or String) to the deflation buffer. @meindex partialFlush @item partialFlush Flush the deflated output to the destination stream using Z_PARTIAL_FLUSH, and flush the destination stream. @meindex position @item position Answer the number of compressed bytes written. @meindex readStream @slindex readStream @item readStream Finish the deflated output to the destination stream using Z_FINISH and return a ReadStream on the deflated data (requires the destination stream to support #readStream). @meindex syncFlush @item syncFlush Flush the deflated output to the destination stream using Z_SYNC_FLUSH, and flush the destination stream. Note that this includes the four bytes 0/0/255/255 at the end of the flush. @end table smalltalk-3.2.5/Makefile.in0000644000175000017500000015401312130455426012501 00000000000000# Makefile.in generated by automake 1.11.6 from Makefile.am. # @configure_input@ # Copyright (C) 1994, 1995, 1996, 1997, 1998, 1999, 2000, 2001, 2002, # 2003, 2004, 2005, 2006, 2007, 2008, 2009, 2010, 2011 Free Software # Foundation, Inc. # This Makefile.in is free software; the Free Software Foundation # gives unlimited permission to copy and/or distribute it, # with or without modifications, as long as this notice is preserved. # This program is distributed in the hope that it will be useful, # but WITHOUT ANY WARRANTY, to the extent permitted by law; without # even the implied warranty of MERCHANTABILITY or FITNESS FOR A # PARTICULAR PURPOSE. @SET_MAKE@ # Copyright 2000, 2001, 2002, 2003, 2004, 2005, 2006, 2007, 2008, 2009 # Free Software Foundation, Inc. # This program is free software; you can redistribute it and/or modify # it under the terms of the GNU General Public License as published by # the Free Software Foundation; either version 2, or (at your option) # any later version. # This program is distributed in the hope that it will be useful, # but WITHOUT ANY WARRANTY; without even the implied warranty of # MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the # GNU General Public License for more details. # You should have received a copy of the GNU General Public License # along with this program; if not, write to the Free Software # Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. VPATH = @srcdir@ am__make_dryrun = \ { \ am__dry=no; \ case $$MAKEFLAGS in \ *\\[\ \ ]*) \ echo 'am--echo: ; @echo "AM" OK' | $(MAKE) -f - 2>/dev/null \ | grep '^AM OK$$' >/dev/null || am__dry=yes;; \ *) \ for am__flg in $$MAKEFLAGS; do \ case $$am__flg in \ *=*|--*) ;; \ *n*) am__dry=yes; break;; \ esac; \ done;; \ esac; \ test $$am__dry = yes; \ } pkgdatadir = $(datadir)/@PACKAGE@ pkgincludedir = $(includedir)/@PACKAGE@ pkglibdir = $(libdir)/@PACKAGE@ pkglibexecdir = $(libexecdir)/@PACKAGE@ am__cd = CDPATH="$${ZSH_VERSION+.}$(PATH_SEPARATOR)" && cd install_sh_DATA = $(install_sh) -c -m 644 install_sh_PROGRAM = $(install_sh) -c install_sh_SCRIPT = $(install_sh) -c INSTALL_HEADER = $(INSTALL_DATA) transform = $(program_transform_name) NORMAL_INSTALL = : PRE_INSTALL = : POST_INSTALL = : NORMAL_UNINSTALL = : PRE_UNINSTALL = : POST_UNINSTALL = : build_triplet = @build@ host_triplet = @host@ @ENABLE_DISASSEMBLER_TRUE@am__append_1 = opcode bin_PROGRAMS = gst$(EXEEXT) @ENABLE_DISASSEMBLER_TRUE@am__append_2 = opcode/libdisass.la @ENABLE_DISASSEMBLER_TRUE@am__append_3 = opcode/libdisass.la @ENABLE_DISASSEMBLER_TRUE@am__append_4 = -I$(top_srcdir)/opcode noinst_PROGRAMS = gst-tool$(EXEEXT) EXTRA_PROGRAMS = winewrapper$(EXEEXT) subdir = . DIST_COMMON = README $(am__configure_deps) $(am__dist_lisp_LISP_DIST) \ $(dist_aclocal_DATA) $(dist_noinst_DATA) \ $(dist_noinst_SCRIPTS) $(srcdir)/Makefile.am \ $(srcdir)/Makefile.in $(srcdir)/config.h.in \ $(srcdir)/gnu-smalltalk.pc.in $(srcdir)/gst-config.in \ $(srcdir)/libc.la.in $(srcdir)/makesetup.in \ $(top_srcdir)/configure \ $(top_srcdir)/packages/blox/tests/package.xml.in AUTHORS \ COPYING COPYING.DOC COPYING.LIB ChangeLog INSTALL NEWS THANKS \ TODO build-aux/compile build-aux/config.guess \ build-aux/config.rpath build-aux/config.sub build-aux/depcomp \ build-aux/elisp-comp build-aux/install-sh build-aux/ltmain.sh \ build-aux/mdate-sh build-aux/missing build-aux/texinfo.tex \ build-aux/ylwrap ACLOCAL_M4 = $(top_srcdir)/aclocal.m4 am__aclocal_m4_deps = $(top_srcdir)/build-aux/bold.m4 \ $(top_srcdir)/build-aux/codeset.m4 \ $(top_srcdir)/build-aux/emacs-pkg.m4 \ $(top_srcdir)/build-aux/emacs-site-start.m4 \ $(top_srcdir)/build-aux/ext_goto.m4 \ $(top_srcdir)/build-aux/gawk.m4 $(top_srcdir)/build-aux/gcc.m4 \ $(top_srcdir)/build-aux/gl.m4 \ $(top_srcdir)/build-aux/glib-2.0.m4 \ $(top_srcdir)/build-aux/glut.m4 $(top_srcdir)/build-aux/gmp.m4 \ $(top_srcdir)/build-aux/gst-package.m4 \ $(top_srcdir)/build-aux/gtk-2.0.m4 \ $(top_srcdir)/build-aux/iconv.m4 \ $(top_srcdir)/build-aux/lib-ld.m4 \ $(top_srcdir)/build-aux/lib-link.m4 \ $(top_srcdir)/build-aux/lib-prefix.m4 \ $(top_srcdir)/build-aux/lib.m4 \ $(top_srcdir)/build-aux/libc-so-name.m4 \ $(top_srcdir)/build-aux/libtool.m4 \ $(top_srcdir)/build-aux/lightning.m4 \ $(top_srcdir)/build-aux/ln.m4 \ $(top_srcdir)/build-aux/localtime.m4 \ $(top_srcdir)/build-aux/lock.m4 \ $(top_srcdir)/build-aux/long-double.m4 \ $(top_srcdir)/build-aux/lrint.m4 \ $(top_srcdir)/build-aux/ltdl-gst.m4 \ $(top_srcdir)/build-aux/ltoptions.m4 \ $(top_srcdir)/build-aux/ltsugar.m4 \ $(top_srcdir)/build-aux/ltversion.m4 \ $(top_srcdir)/build-aux/lt~obsolete.m4 \ $(top_srcdir)/build-aux/modules.m4 \ $(top_srcdir)/build-aux/pkg.m4 $(top_srcdir)/build-aux/poll.m4 \ $(top_srcdir)/build-aux/readline.m4 \ $(top_srcdir)/build-aux/relocatable.m4 \ $(top_srcdir)/build-aux/setenv.m4 \ $(top_srcdir)/build-aux/snprintfv.m4 \ $(top_srcdir)/build-aux/sockets.m4 \ $(top_srcdir)/build-aux/sockpfaf.m4 \ $(top_srcdir)/build-aux/strtoul.m4 \ $(top_srcdir)/build-aux/sync-builtins.m4 \ $(top_srcdir)/build-aux/tcltk.m4 \ $(top_srcdir)/build-aux/version.m4 \ $(top_srcdir)/build-aux/vis-hidden.m4 \ $(top_srcdir)/build-aux/wine.m4 $(top_srcdir)/configure.ac am__configure_deps = $(am__aclocal_m4_deps) $(CONFIGURE_DEPENDENCIES) \ $(ACLOCAL_M4) am__CONFIG_DISTCLEAN_FILES = config.status config.cache config.log \ configure.lineno config.status.lineno mkinstalldirs = $(install_sh) -d CONFIG_HEADER = config.h CONFIG_CLEAN_FILES = makesetup libc.la packages/blox/tests/package.xml \ gnu-smalltalk.pc gst-config CONFIG_CLEAN_VPATH_FILES = am__installdirs = "$(DESTDIR)$(bindir)" "$(DESTDIR)$(bindir)" \ "$(DESTDIR)$(lispdir)" "$(DESTDIR)$(lispdir)" \ "$(DESTDIR)$(lispstartdir)" "$(DESTDIR)$(aclocaldir)" \ "$(DESTDIR)$(moduledir)" "$(DESTDIR)$(pkgconfigdir)" PROGRAMS = $(bin_PROGRAMS) $(noinst_PROGRAMS) am_gst_OBJECTS = main.$(OBJEXT) gst_OBJECTS = $(am_gst_OBJECTS) gst_LINK = $(LIBTOOL) --tag=CC $(AM_LIBTOOLFLAGS) $(LIBTOOLFLAGS) \ --mode=link $(CCLD) $(AM_CFLAGS) $(CFLAGS) $(gst_LDFLAGS) \ $(LDFLAGS) -o $@ am_gst_tool_OBJECTS = gst-tool.$(OBJEXT) gst_tool_OBJECTS = $(am_gst_tool_OBJECTS) gst_tool_LINK = $(LIBTOOL) --tag=CC $(AM_LIBTOOLFLAGS) $(LIBTOOLFLAGS) \ --mode=link $(CCLD) $(AM_CFLAGS) $(CFLAGS) $(gst_tool_LDFLAGS) \ $(LDFLAGS) -o $@ am_winewrapper_OBJECTS = winewrapper.$(OBJEXT) winewrapper_OBJECTS = $(am_winewrapper_OBJECTS) winewrapper_LDADD = $(LDADD) am__vpath_adj_setup = srcdirstrip=`echo "$(srcdir)" | sed 's|.|.|g'`; am__vpath_adj = case $$p in \ $(srcdir)/*) f=`echo "$$p" | sed "s|^$$srcdirstrip/||"`;; \ *) f=$$p;; \ esac; am__strip_dir = f=`echo $$p | sed -e 's|^.*/||'`; am__install_max = 40 am__nobase_strip_setup = \ srcdirstrip=`echo "$(srcdir)" | sed 's/[].[^$$\\*|]/\\\\&/g'` am__nobase_strip = \ for p in $$list; do echo "$$p"; done | sed -e "s|$$srcdirstrip/||" am__nobase_list = $(am__nobase_strip_setup); \ for p in $$list; do echo "$$p $$p"; done | \ sed "s| $$srcdirstrip/| |;"' / .*\//!s/ .*/ ./; s,\( .*\)/[^/]*$$,\1,' | \ $(AWK) 'BEGIN { files["."] = "" } { files[$$2] = files[$$2] " " $$1; \ if (++n[$$2] == $(am__install_max)) \ { print $$2, files[$$2]; n[$$2] = 0; files[$$2] = "" } } \ END { for (dir in files) print dir, files[dir] }' am__base_list = \ sed '$$!N;$$!N;$$!N;$$!N;$$!N;$$!N;$$!N;s/\n/ /g' | \ sed '$$!N;$$!N;$$!N;$$!N;s/\n/ /g' am__uninstall_files_from_dir = { \ test -z "$$files" \ || { test ! -d "$$dir" && test ! -f "$$dir" && test ! -r "$$dir"; } \ || { echo " ( cd '$$dir' && rm -f" $$files ")"; \ $(am__cd) "$$dir" && rm -f $$files; }; \ } SCRIPTS = $(bin_SCRIPTS) $(dist_noinst_SCRIPTS) DEFAULT_INCLUDES = -I.@am__isrc@ depcomp = $(SHELL) $(top_srcdir)/build-aux/depcomp am__depfiles_maybe = depfiles am__mv = mv -f COMPILE = $(CC) $(DEFS) $(DEFAULT_INCLUDES) $(INCLUDES) $(AM_CPPFLAGS) \ $(CPPFLAGS) $(AM_CFLAGS) $(CFLAGS) LTCOMPILE = $(LIBTOOL) --tag=CC $(AM_LIBTOOLFLAGS) $(LIBTOOLFLAGS) \ --mode=compile $(CC) $(DEFS) $(DEFAULT_INCLUDES) $(INCLUDES) \ $(AM_CPPFLAGS) $(CPPFLAGS) $(AM_CFLAGS) $(CFLAGS) CCLD = $(CC) LINK = $(LIBTOOL) --tag=CC $(AM_LIBTOOLFLAGS) $(LIBTOOLFLAGS) \ --mode=link $(CCLD) $(AM_CFLAGS) $(CFLAGS) $(AM_LDFLAGS) \ $(LDFLAGS) -o $@ SOURCES = $(gst_SOURCES) $(gst_tool_SOURCES) $(winewrapper_SOURCES) DIST_SOURCES = $(gst_SOURCES) $(gst_tool_SOURCES) \ $(winewrapper_SOURCES) RECURSIVE_TARGETS = all-recursive check-recursive dvi-recursive \ html-recursive info-recursive install-data-recursive \ install-dvi-recursive install-exec-recursive \ install-html-recursive install-info-recursive \ install-pdf-recursive install-ps-recursive install-recursive \ installcheck-recursive installdirs-recursive pdf-recursive \ ps-recursive uninstall-recursive am__can_run_installinfo = \ case $$AM_UPDATE_INFO_DIR in \ n|no|NO) false;; \ *) (install-info --version) >/dev/null 2>&1;; \ esac am__dist_lisp_LISP_DIST = smalltalk-mode.el dist_lispLISP_INSTALL = $(INSTALL_DATA) nodist_lispLISP_INSTALL = $(INSTALL_DATA) nodist_lispstartLISP_INSTALL = $(INSTALL_DATA) LISP = $(dist_lisp_LISP) $(nodist_lisp_LISP) $(nodist_lispstart_LISP) am__ELFILES = gst-mode.el smalltalk-mode-init.el smalltalk-mode.el am__ELCFILES = $(am__ELFILES:.el=.elc) ELCFILES = $(LISP:.el=.elc) elisp_comp = $(top_srcdir)/build-aux/elisp-comp DATA = $(dist_aclocal_DATA) $(dist_noinst_DATA) $(module_DATA) \ $(nodist_pkgconfig_DATA) $(noinst_DATA) HEADERS = $(nodist_noinst_HEADERS) RECURSIVE_CLEAN_TARGETS = mostlyclean-recursive clean-recursive \ distclean-recursive maintainer-clean-recursive AM_RECURSIVE_TARGETS = $(RECURSIVE_TARGETS:-recursive=) \ $(RECURSIVE_CLEAN_TARGETS:-recursive=) tags TAGS ctags CTAGS \ distdir dist dist-all distcheck ETAGS = etags CTAGS = ctags DISTFILES = $(DIST_COMMON) $(DIST_SOURCES) $(TEXINFOS) $(EXTRA_DIST) distdir = $(PACKAGE)-$(VERSION) top_distdir = $(distdir) am__remove_distdir = \ if test -d "$(distdir)"; then \ find "$(distdir)" -type d ! -perm -200 -exec chmod u+w {} ';' \ && rm -rf "$(distdir)" \ || { sleep 5 && rm -rf "$(distdir)"; }; \ else :; fi am__relativize = \ dir0=`pwd`; \ sed_first='s,^\([^/]*\)/.*$$,\1,'; \ sed_rest='s,^[^/]*/*,,'; \ sed_last='s,^.*/\([^/]*\)$$,\1,'; \ sed_butlast='s,/*[^/]*$$,,'; \ while test -n "$$dir1"; do \ first=`echo "$$dir1" | sed -e "$$sed_first"`; \ if test "$$first" != "."; then \ if test "$$first" = ".."; then \ dir2=`echo "$$dir0" | sed -e "$$sed_last"`/"$$dir2"; \ dir0=`echo "$$dir0" | sed -e "$$sed_butlast"`; \ else \ first2=`echo "$$dir2" | sed -e "$$sed_first"`; \ if test "$$first2" = "$$first"; then \ dir2=`echo "$$dir2" | sed -e "$$sed_rest"`; \ else \ dir2="../$$dir2"; \ fi; \ dir0="$$dir0"/"$$first"; \ fi; \ fi; \ dir1=`echo "$$dir1" | sed -e "$$sed_rest"`; \ done; \ reldir="$$dir2" DIST_ARCHIVES = $(distdir).tar.gz $(distdir).tar.xz GZIP_ENV = --best distuninstallcheck_listfiles = find . -type f -print am__distuninstallcheck_listfiles = $(distuninstallcheck_listfiles) \ | sed 's|^\./|$(prefix)/|' | grep -v '$(infodir)/dir$$' distcleancheck_listfiles = find . -type f -print ACLOCAL = @ACLOCAL@ ALLOCA = @ALLOCA@ ALL_PACKAGES = @ALL_PACKAGES@ AMTAR = @AMTAR@ AR = @AR@ AS = @AS@ ATK_CFLAGS = @ATK_CFLAGS@ ATK_LIBS = @ATK_LIBS@ AUTOCONF = @AUTOCONF@ AUTOHEADER = @AUTOHEADER@ AUTOM4TE = @AUTOM4TE@ AUTOMAKE = @AUTOMAKE@ AWK = @AWK@ BLOX_IMPLEMENTATION = @BLOX_IMPLEMENTATION@ BUILT_PACKAGES = @BUILT_PACKAGES@ CAIRO_CFLAGS = @CAIRO_CFLAGS@ CAIRO_LIBS = @CAIRO_LIBS@ CC = @CC@ CCDEPMODE = @CCDEPMODE@ CFLAGS = @CFLAGS@ CPP = @CPP@ CPPFLAGS = @CPPFLAGS@ CYGPATH_W = @CYGPATH_W@ DEFS = @DEFS@ DEPDIR = @DEPDIR@ DLLTOOL = @DLLTOOL@ DSYMUTIL = @DSYMUTIL@ DUMPBIN = @DUMPBIN@ ECHO_C = @ECHO_C@ ECHO_N = @ECHO_N@ ECHO_T = @ECHO_T@ EGREP = @EGREP@ EMACS = @EMACS@ EMACSLOADPATH = @EMACSLOADPATH@ EXEEXT = @EXEEXT@ FGREP = @FGREP@ GLIB_CFLAGS = @GLIB_CFLAGS@ GLIB_GENMARSHAL = @GLIB_GENMARSHAL@ GLIB_LIBS = @GLIB_LIBS@ GLIB_MKENUMS = @GLIB_MKENUMS@ GNUTLS_CFLAGS = @GNUTLS_CFLAGS@ GNUTLS_LIBS = @GNUTLS_LIBS@ GOBJECT_QUERY = @GOBJECT_QUERY@ GPERF = @GPERF@ GREP = @GREP@ GST_RUN = @GST_RUN@ GTHREAD_CFLAGS = @GTHREAD_CFLAGS@ GTHREAD_LIBS = @GTHREAD_LIBS@ GTK_CFLAGS = @GTK_CFLAGS@ GTK_LIBS = @GTK_LIBS@ ICON = @ICON@ INCFFI = @INCFFI@ INCLTDL = @INCLTDL@ INCSIGSEGV = @INCSIGSEGV@ INCSNPRINTFV = @INCSNPRINTFV@ INCTCLTK = @INCTCLTK@ INSTALL = @INSTALL@ INSTALL_DATA = @INSTALL_DATA@ INSTALL_INFO = @INSTALL_INFO@ INSTALL_PROGRAM = @INSTALL_PROGRAM@ INSTALL_SCRIPT = @INSTALL_SCRIPT@ INSTALL_STRIP_PROGRAM = @INSTALL_STRIP_PROGRAM@ LD = @LD@ LDFLAGS = @LDFLAGS@ LEX = @LEX@ LIBADD_DL = @LIBADD_DL@ LIBC_SO_DIR = @LIBC_SO_DIR@ LIBC_SO_NAME = @LIBC_SO_NAME@ LIBFFI = @LIBFFI@ LIBFFI_CFLAGS = @LIBFFI_CFLAGS@ LIBFFI_EXECUTABLE_LDFLAGS = @LIBFFI_EXECUTABLE_LDFLAGS@ LIBFFI_LIBS = @LIBFFI_LIBS@ LIBGLUT = @LIBGLUT@ LIBGMP = @LIBGMP@ LIBGST_CFLAGS = @LIBGST_CFLAGS@ LIBICONV = @LIBICONV@ LIBLTDL = @LIBLTDL@ LIBOBJS = @LIBOBJS@ LIBOPENGL = @LIBOPENGL@ LIBREADLINE = @LIBREADLINE@ LIBS = @LIBS@ LIBSIGSEGV = @LIBSIGSEGV@ LIBSNPRINTFV = @LIBSNPRINTFV@ LIBTCLTK = @LIBTCLTK@ LIBTHREAD = @LIBTHREAD@ LIBTOOL = @LIBTOOL@ LIPO = @LIPO@ LN = @LN@ LN_S = @LN_S@ LTALLOCA = @LTALLOCA@ LTLIBICONV = @LTLIBICONV@ LTLIBOBJS = @LTLIBOBJS@ MAINTAINER = @MAINTAINER@ MAKEINFO = @MAKEINFO@ MANIFEST_TOOL = @MANIFEST_TOOL@ MKDIR_P = @MKDIR_P@ MODULES = @MODULES@ NM = @NM@ NMEDIT = @NMEDIT@ OBJC = @OBJC@ OBJCDEPMODE = @OBJCDEPMODE@ OBJCFLAGS = @OBJCFLAGS@ OBJDUMP = @OBJDUMP@ OBJEXT = @OBJEXT@ OTOOL = @OTOOL@ OTOOL64 = @OTOOL64@ PACKAGE = smalltalk PACKAGE_BUGREPORT = @PACKAGE_BUGREPORT@ PACKAGE_DLOPEN_FLAGS = @PACKAGE_DLOPEN_FLAGS@ PACKAGE_NAME = @PACKAGE_NAME@ PACKAGE_STRING = @PACKAGE_STRING@ PACKAGE_TARNAME = @PACKAGE_TARNAME@ PACKAGE_URL = @PACKAGE_URL@ PACKAGE_VERSION = @PACKAGE_VERSION@ PANGO_CFLAGS = @PANGO_CFLAGS@ PANGO_LIBS = @PANGO_LIBS@ PATH_SEPARATOR = @PATH_SEPARATOR@ PKG_CONFIG = @PKG_CONFIG@ RANLIB = @RANLIB@ RELOCATABLE = @RELOCATABLE@ RELOC_CPPFLAGS = @RELOC_CPPFLAGS@ RELOC_LDFLAGS = @RELOC_LDFLAGS@ SDL_CFLAGS = @SDL_CFLAGS@ SDL_LIBS = @SDL_LIBS@ SED = @SED@ SET_MAKE = @SET_MAKE@ SHELL = @SHELL@ SOCKET_LIBS = @SOCKET_LIBS@ STRIP = @STRIP@ SYNC_CFLAGS = @SYNC_CFLAGS@ TCLSH = @TCLSH@ TIMEOUT = @TIMEOUT@ VERSION = @VERSION@ VERSION_INFO = @VERSION_INFO@ WINDRES = @WINDRES@ WINEWRAPPER = @WINEWRAPPER@ WINEWRAPPERDEP = @WINEWRAPPERDEP@ XMKMF = @XMKMF@ XZIP = @XZIP@ X_CFLAGS = @X_CFLAGS@ X_EXTRA_LIBS = @X_EXTRA_LIBS@ X_LIBS = @X_LIBS@ X_PRE_LIBS = @X_PRE_LIBS@ YACC = @YACC@ ZIP = @ZIP@ abs_builddir = @abs_builddir@ abs_srcdir = @abs_srcdir@ abs_top_builddir = @abs_top_builddir@ abs_top_srcdir = @abs_top_srcdir@ ac_ct_AR = @ac_ct_AR@ ac_ct_CC = @ac_ct_CC@ ac_ct_DUMPBIN = @ac_ct_DUMPBIN@ am__include = @am__include@ am__leading_dot = @am__leading_dot@ am__quote = @am__quote@ am__tar = @am__tar@ am__untar = @am__untar@ bindir = @bindir@ build = @build@ build_alias = @build_alias@ build_cpu = @build_cpu@ build_os = @build_os@ build_vendor = @build_vendor@ builddir = @builddir@ datadir = @datadir@ datarootdir = @datarootdir@ docdir = @docdir@ dvidir = @dvidir@ enable_mysql_tests = @enable_mysql_tests@ exec_prefix = @exec_prefix@ host = @host@ host_alias = @host_alias@ host_cpu = @host_cpu@ host_os = @host_os@ host_vendor = @host_vendor@ htmldir = @htmldir@ imagedir = @imagedir@ includedir = @includedir@ infodir = @infodir@ install_sh = @install_sh@ libdir = @libdir@ libexecdir = @libexecdir@ lispdir = @lispdir@ lispstartdir = @lispstartdir@ localedir = @localedir@ localstatedir = @localstatedir@ mandir = @mandir@ mkdir_p = @mkdir_p@ moduledir = @moduledir@ moduleexecdir = @moduleexecdir@ oldincludedir = @oldincludedir@ pdfdir = @pdfdir@ prefix = @prefix@ program_transform_name = @program_transform_name@ psdir = @psdir@ sbindir = @sbindir@ sharedstatedir = @sharedstatedir@ srcdir = @srcdir@ subdirs = @subdirs@ sysconfdir = @sysconfdir@ target_alias = @target_alias@ top_build_prefix = @top_build_prefix@ top_builddir = @top_builddir@ top_srcdir = @top_srcdir@ # Automake requirements AUTOMAKE_OPTIONS = gnu 1.11 dist-xz ACLOCAL_AMFLAGS = -I build-aux DISTCHECK_CONFIGURE_FLAGS = --without-system-libltdl --without-system-libsigsegv --without-system-libffi gstdatadir = $(pkgdatadir) DIST_SUBDIRS = lib-src snprintfv lightning sigsegv libffi opcode libgst \ . $(ALL_PACKAGES) tests doc SUBDIRS = lib-src lightning $(subdirs) $(am__append_1) libgst . \ $(BUILT_PACKAGES) doc tests # Running gst inside the build directory... GST_OPTS = --kernel-dir "@srcdir@/kernel" --image gst.im GST = $(WINEWRAPPER) ./gst$(EXEEXT) --no-user-files $(GST_OPTS) GST_PACKAGE = XZIP="$(XZIP)" $(WINEWRAPPER) ./gst-tool$(EXEEXT) gst-package $(GST_OPTS) ########################################################### # # Rules for configuration files # ########################################################### aclocaldir = $(datadir)/aclocal dist_aclocal_DATA = build-aux/gst.m4 build-aux/gst-package.m4 ########################################################### # # Rules for distributing the superops program # ########################################################### dist_noinst_DATA = Doxyfile smalltalk-mode-init.el.in gst-mode.el.in \ .gdbinit scripts/Finish.st gsticon.ico packages/xml/ChangeLog \ packages/seaside/PORTING superops/ChangeLog superops/Makefile \ superops/README superops/bool-array.cc superops/bool-array.h \ superops/bool-array.icc superops/byte_def.cc \ superops/byte_def.h superops/hash-table.cc \ superops/hash-table.h superops/hash.cc superops/hash.h \ superops/keyword-list.cc superops/keyword-list.h \ superops/keyword-list.icc superops/keyword.cc \ superops/keyword.h superops/keyword.icc \ superops/observer-list.cc superops/observer-list.h \ superops/options.cc superops/options.h superops/options.icc \ superops/positions.cc superops/positions.h \ superops/positions.icc superops/search.cc superops/search.h \ superops/superops.cc superops/table.cc superops/table.h \ superops/vm_def.cc superops/vm_def.h dist_noinst_SCRIPTS = build-aux/texi2dvi build-aux/texi2html \ build-aux/help2man build-aux/config.rpath ########################################################### # # Rules for scripts and data files # ########################################################### pkgconfigdir = $(libdir)/pkgconfig nodist_pkgconfig_DATA = gnu-smalltalk.pc @NEED_LIBC_LA_TRUE@module_DATA = libc.la noinst_DATA = gst.im bin_SCRIPTS = gst-config DISTCLEANFILES = termbold termnorm pkgrules.tmp config.h CLEANFILES = gst.im $(nodist_lisp_LISP) $(nodist_lispstart_LISP) @WITH_EMACS_TRUE@dist_lisp_LISP = smalltalk-mode.el @WITH_EMACS_TRUE@nodist_lispstart_LISP = smalltalk-mode-init.el @WITH_EMACS_COMINT_TRUE@@WITH_EMACS_TRUE@nodist_lisp_LISP = gst-mode.el @WITH_EMACS_COMINT_FALSE@LISP_WITH_EMACS_COMINT = ; @WITH_EMACS_COMINT_TRUE@LISP_WITH_EMACS_COMINT = ########################################################### # # Rules for building the VM # ########################################################### AM_CPPFLAGS = -I$(top_srcdir)/libgst -I$(top_srcdir)/lib-src \ -DCMD_XZIP="\"$(XZIP)\"" -DCMD_INSTALL="\"$(INSTALL)\"" \ -DCMD_LN_S="\"$(LN_S)\"" $(RELOC_CPPFLAGS) $(am__append_4) gst_SOURCES = main.c gst_LDADD = libgst/libgst.la lib-src/library.la @ICON@ $(am__append_2) gst_DEPENDENCIES = libgst/libgst.la lib-src/library.la @ICON@ \ $(am__append_3) gst_LDFLAGS = -export-dynamic $(RELOC_LDFLAGS) $(LIBFFI_EXECUTABLE_LDFLAGS) gst_tool_SOURCES = gst-tool.c gst_tool_LDADD = libgst/libgst.la lib-src/library.la @ICON@ gst_tool_DEPENDENCIES = libgst/libgst.la lib-src/library.la @ICON@ gst_tool_LDFLAGS = -export-dynamic $(RELOC_LDFLAGS) $(LIBFFI_EXECUTABLE_LDFLAGS) winewrapper_SOURCES = winewrapper.c GST_EXTRA_TOOLS = gst-reload gst-sunit gst-blox gst-package gst-convert \ gst-doc gst-remote gst-profile gst-browser nodist_noinst_HEADERS = config.h all: config.h $(MAKE) $(AM_MAKEFLAGS) all-recursive .SUFFIXES: .SUFFIXES: .c .lo .o .obj am--refresh: Makefile @: $(srcdir)/Makefile.in: $(srcdir)/Makefile.am $(am__configure_deps) @for dep in $?; do \ case '$(am__configure_deps)' in \ *$$dep*) \ echo ' cd $(srcdir) && $(AUTOMAKE) --gnu'; \ $(am__cd) $(srcdir) && $(AUTOMAKE) --gnu \ && exit 0; \ exit 1;; \ esac; \ done; \ echo ' cd $(top_srcdir) && $(AUTOMAKE) --gnu Makefile'; \ $(am__cd) $(top_srcdir) && \ $(AUTOMAKE) --gnu Makefile .PRECIOUS: Makefile Makefile: $(srcdir)/Makefile.in $(top_builddir)/config.status @case '$?' in \ *config.status*) \ echo ' $(SHELL) ./config.status'; \ $(SHELL) ./config.status;; \ *) \ echo ' cd $(top_builddir) && $(SHELL) ./config.status $@ $(am__depfiles_maybe)'; \ cd $(top_builddir) && $(SHELL) ./config.status $@ $(am__depfiles_maybe);; \ esac; $(top_builddir)/config.status: $(top_srcdir)/configure $(CONFIG_STATUS_DEPENDENCIES) $(SHELL) ./config.status --recheck $(top_srcdir)/configure: $(am__configure_deps) $(am__cd) $(srcdir) && $(AUTOCONF) $(ACLOCAL_M4): $(am__aclocal_m4_deps) $(am__cd) $(srcdir) && $(ACLOCAL) $(ACLOCAL_AMFLAGS) $(am__aclocal_m4_deps): config.h: stamp-h1 @if test ! -f $@; then rm -f stamp-h1; else :; fi @if test ! -f $@; then $(MAKE) $(AM_MAKEFLAGS) stamp-h1; else :; fi stamp-h1: $(srcdir)/config.h.in $(top_builddir)/config.status @rm -f stamp-h1 cd $(top_builddir) && $(SHELL) ./config.status config.h $(srcdir)/config.h.in: $(am__configure_deps) ($(am__cd) $(top_srcdir) && $(AUTOHEADER)) rm -f stamp-h1 touch $@ distclean-hdr: -rm -f config.h stamp-h1 makesetup: $(top_builddir)/config.status $(srcdir)/makesetup.in cd $(top_builddir) && $(SHELL) ./config.status $@ libc.la: $(top_builddir)/config.status $(srcdir)/libc.la.in cd $(top_builddir) && $(SHELL) ./config.status $@ packages/blox/tests/package.xml: $(top_builddir)/config.status $(top_srcdir)/packages/blox/tests/package.xml.in cd $(top_builddir) && $(SHELL) ./config.status $@ gnu-smalltalk.pc: $(top_builddir)/config.status $(srcdir)/gnu-smalltalk.pc.in cd $(top_builddir) && $(SHELL) ./config.status $@ gst-config: $(top_builddir)/config.status $(srcdir)/gst-config.in cd $(top_builddir) && $(SHELL) ./config.status $@ install-binPROGRAMS: $(bin_PROGRAMS) @$(NORMAL_INSTALL) @list='$(bin_PROGRAMS)'; test -n "$(bindir)" || list=; \ if test -n "$$list"; then \ echo " $(MKDIR_P) '$(DESTDIR)$(bindir)'"; \ $(MKDIR_P) "$(DESTDIR)$(bindir)" || exit 1; \ fi; \ for p in $$list; do echo "$$p $$p"; done | \ sed 's/$(EXEEXT)$$//' | \ while read p p1; do if test -f $$p || test -f $$p1; \ then echo "$$p"; echo "$$p"; else :; fi; \ done | \ sed -e 'p;s,.*/,,;n;h' -e 's|.*|.|' \ -e 'p;x;s,.*/,,;s/$(EXEEXT)$$//;$(transform);s/$$/$(EXEEXT)/' | \ sed 'N;N;N;s,\n, ,g' | \ $(AWK) 'BEGIN { files["."] = ""; dirs["."] = 1 } \ { d=$$3; if (dirs[d] != 1) { print "d", d; dirs[d] = 1 } \ if ($$2 == $$4) files[d] = files[d] " " $$1; \ else { print "f", $$3 "/" $$4, $$1; } } \ END { for (d in files) print "f", d, files[d] }' | \ while read type dir files; do \ if test "$$dir" = .; then dir=; else dir=/$$dir; fi; \ test -z "$$files" || { \ echo " $(INSTALL_PROGRAM_ENV) $(LIBTOOL) $(AM_LIBTOOLFLAGS) $(LIBTOOLFLAGS) --mode=install $(INSTALL_PROGRAM) $$files '$(DESTDIR)$(bindir)$$dir'"; \ $(INSTALL_PROGRAM_ENV) $(LIBTOOL) $(AM_LIBTOOLFLAGS) $(LIBTOOLFLAGS) --mode=install $(INSTALL_PROGRAM) $$files "$(DESTDIR)$(bindir)$$dir" || exit $$?; \ } \ ; done uninstall-binPROGRAMS: @$(NORMAL_UNINSTALL) @list='$(bin_PROGRAMS)'; test -n "$(bindir)" || list=; \ files=`for p in $$list; do echo "$$p"; done | \ sed -e 'h;s,^.*/,,;s/$(EXEEXT)$$//;$(transform)' \ -e 's/$$/$(EXEEXT)/' `; \ test -n "$$list" || exit 0; \ echo " ( cd '$(DESTDIR)$(bindir)' && rm -f" $$files ")"; \ cd "$(DESTDIR)$(bindir)" && rm -f $$files clean-binPROGRAMS: @list='$(bin_PROGRAMS)'; test -n "$$list" || exit 0; \ echo " rm -f" $$list; \ rm -f $$list || exit $$?; \ test -n "$(EXEEXT)" || exit 0; \ list=`for p in $$list; do echo "$$p"; done | sed 's/$(EXEEXT)$$//'`; \ echo " rm -f" $$list; \ rm -f $$list clean-noinstPROGRAMS: @list='$(noinst_PROGRAMS)'; test -n "$$list" || exit 0; \ echo " rm -f" $$list; \ rm -f $$list || exit $$?; \ test -n "$(EXEEXT)" || exit 0; \ list=`for p in $$list; do echo "$$p"; done | sed 's/$(EXEEXT)$$//'`; \ echo " rm -f" $$list; \ rm -f $$list gst$(EXEEXT): $(gst_OBJECTS) $(gst_DEPENDENCIES) $(EXTRA_gst_DEPENDENCIES) @rm -f gst$(EXEEXT) $(gst_LINK) $(gst_OBJECTS) $(gst_LDADD) $(LIBS) gst-tool$(EXEEXT): $(gst_tool_OBJECTS) $(gst_tool_DEPENDENCIES) $(EXTRA_gst_tool_DEPENDENCIES) @rm -f gst-tool$(EXEEXT) $(gst_tool_LINK) $(gst_tool_OBJECTS) $(gst_tool_LDADD) $(LIBS) winewrapper$(EXEEXT): $(winewrapper_OBJECTS) $(winewrapper_DEPENDENCIES) $(EXTRA_winewrapper_DEPENDENCIES) @rm -f winewrapper$(EXEEXT) $(LINK) $(winewrapper_OBJECTS) $(winewrapper_LDADD) $(LIBS) install-binSCRIPTS: $(bin_SCRIPTS) @$(NORMAL_INSTALL) @list='$(bin_SCRIPTS)'; test -n "$(bindir)" || list=; \ if test -n "$$list"; then \ echo " $(MKDIR_P) '$(DESTDIR)$(bindir)'"; \ $(MKDIR_P) "$(DESTDIR)$(bindir)" || exit 1; \ fi; \ for p in $$list; do \ if test -f "$$p"; then d=; else d="$(srcdir)/"; fi; \ if test -f "$$d$$p"; then echo "$$d$$p"; echo "$$p"; else :; fi; \ done | \ sed -e 'p;s,.*/,,;n' \ -e 'h;s|.*|.|' \ -e 'p;x;s,.*/,,;$(transform)' | sed 'N;N;N;s,\n, ,g' | \ $(AWK) 'BEGIN { files["."] = ""; dirs["."] = 1; } \ { d=$$3; if (dirs[d] != 1) { print "d", d; dirs[d] = 1 } \ if ($$2 == $$4) { files[d] = files[d] " " $$1; \ if (++n[d] == $(am__install_max)) { \ print "f", d, files[d]; n[d] = 0; files[d] = "" } } \ else { print "f", d "/" $$4, $$1 } } \ END { for (d in files) print "f", d, files[d] }' | \ while read type dir files; do \ if test "$$dir" = .; then dir=; else dir=/$$dir; fi; \ test -z "$$files" || { \ echo " $(INSTALL_SCRIPT) $$files '$(DESTDIR)$(bindir)$$dir'"; \ $(INSTALL_SCRIPT) $$files "$(DESTDIR)$(bindir)$$dir" || exit $$?; \ } \ ; done uninstall-binSCRIPTS: @$(NORMAL_UNINSTALL) @list='$(bin_SCRIPTS)'; test -n "$(bindir)" || exit 0; \ files=`for p in $$list; do echo "$$p"; done | \ sed -e 's,.*/,,;$(transform)'`; \ dir='$(DESTDIR)$(bindir)'; $(am__uninstall_files_from_dir) mostlyclean-compile: -rm -f *.$(OBJEXT) distclean-compile: -rm -f *.tab.c @AMDEP_TRUE@@am__include@ @am__quote@./$(DEPDIR)/gst-tool.Po@am__quote@ @AMDEP_TRUE@@am__include@ @am__quote@./$(DEPDIR)/main.Po@am__quote@ @AMDEP_TRUE@@am__include@ @am__quote@./$(DEPDIR)/winewrapper.Po@am__quote@ .c.o: @am__fastdepCC_TRUE@ $(COMPILE) -MT $@ -MD -MP -MF $(DEPDIR)/$*.Tpo -c -o $@ $< @am__fastdepCC_TRUE@ $(am__mv) $(DEPDIR)/$*.Tpo $(DEPDIR)/$*.Po @AMDEP_TRUE@@am__fastdepCC_FALSE@ source='$<' object='$@' libtool=no @AMDEPBACKSLASH@ @AMDEP_TRUE@@am__fastdepCC_FALSE@ DEPDIR=$(DEPDIR) $(CCDEPMODE) $(depcomp) @AMDEPBACKSLASH@ @am__fastdepCC_FALSE@ $(COMPILE) -c $< .c.obj: @am__fastdepCC_TRUE@ $(COMPILE) -MT $@ -MD -MP -MF $(DEPDIR)/$*.Tpo -c -o $@ `$(CYGPATH_W) '$<'` @am__fastdepCC_TRUE@ $(am__mv) $(DEPDIR)/$*.Tpo $(DEPDIR)/$*.Po @AMDEP_TRUE@@am__fastdepCC_FALSE@ source='$<' object='$@' libtool=no @AMDEPBACKSLASH@ @AMDEP_TRUE@@am__fastdepCC_FALSE@ DEPDIR=$(DEPDIR) $(CCDEPMODE) $(depcomp) @AMDEPBACKSLASH@ @am__fastdepCC_FALSE@ $(COMPILE) -c `$(CYGPATH_W) '$<'` .c.lo: @am__fastdepCC_TRUE@ $(LTCOMPILE) -MT $@ -MD -MP -MF $(DEPDIR)/$*.Tpo -c -o $@ $< @am__fastdepCC_TRUE@ $(am__mv) $(DEPDIR)/$*.Tpo $(DEPDIR)/$*.Plo @AMDEP_TRUE@@am__fastdepCC_FALSE@ source='$<' object='$@' libtool=yes @AMDEPBACKSLASH@ @AMDEP_TRUE@@am__fastdepCC_FALSE@ DEPDIR=$(DEPDIR) $(CCDEPMODE) $(depcomp) @AMDEPBACKSLASH@ @am__fastdepCC_FALSE@ $(LTCOMPILE) -c -o $@ $< mostlyclean-libtool: -rm -f *.lo clean-libtool: -rm -rf .libs _libs distclean-libtool: -rm -f libtool config.lt elc-stamp: $(LISP) @echo 'WARNING: Warnings can be ignored. :-)' @rm -f elc-temp && touch elc-temp if test "$(EMACS)" != no; then \ set x; \ list='$(LISP)'; for p in $$list; do \ if test -f "$$p"; then d=; else d="$(srcdir)/"; fi; \ set x "$$@" "$$d$$p"; shift; \ done; \ shift; \ EMACS="$(EMACS)" $(SHELL) $(elisp_comp) "$$@" || exit 1; \ else : ; fi @mv -f elc-temp $@ $(am__ELCFILES): elc-stamp @if $(am__make_dryrun); then dry=:; else dry=; fi; \ if test "$(EMACS)" != no && test ! -f $@; then \ $$dry trap 'rm -rf elc-lock elc-stamp' 1 2 13 15; \ if $$dry mkdir elc-lock 2>/dev/null; then \ $$dry rm -f elc-stamp; \ $(MAKE) $(AM_MAKEFLAGS) elc-stamp; \ $$dry rmdir elc-lock; \ else \ while test -d elc-lock && test -z "$$dry"; do sleep 1; done; \ $$dry test -f elc-stamp; exit $$?; \ fi; \ else : ; fi install-dist_lispLISP: $(dist_lisp_LISP) $(ELCFILES) @$(NORMAL_INSTALL) @if test "$(EMACS)" != no && test -n "$(lispdir)"; then \ list='$(dist_lisp_LISP)'; \ if test -n "$$list"; then \ echo " $(MKDIR_P) '$(DESTDIR)$(lispdir)'"; \ $(MKDIR_P) "$(DESTDIR)$(lispdir)" || exit 1; \ fi; \ for p in $$list; do \ if test -f "$$p"; then d=; else d="$(srcdir)/"; fi; \ $(am__strip_dir) \ echo " $(dist_lispLISP_INSTALL) '$$d$$p' '$(DESTDIR)$(lispdir)/$$f'"; \ $(dist_lispLISP_INSTALL) "$$d$$p" "$(DESTDIR)$(lispdir)/$$f" || exit $$?; \ if test -f $${p}c; then \ echo " $(dist_lispLISP_INSTALL) '$${p}c' '$(DESTDIR)$(lispdir)/$${f}c'"; \ $(dist_lispLISP_INSTALL) "$${p}c" "$(DESTDIR)$(lispdir)/$${f}c" || exit $$?; \ else : ; fi; \ done; \ else : ; fi uninstall-dist_lispLISP: @$(NORMAL_UNINSTALL) @test "$(EMACS)" != no && test -n "$(lispdir)" || exit 0; \ list='$(dist_lisp_LISP)'; \ files=`for p in $$list; do echo $$p; done | sed -e 's|^.*/||'`; \ files="$$files "`echo "$$files" | sed 's|$$|c|'`; \ dir='$(DESTDIR)$(lispdir)'; $(am__uninstall_files_from_dir) clean-lisp: -rm -f elc-stamp $(ELCFILES) install-nodist_lispLISP: $(nodist_lisp_LISP) $(ELCFILES) @$(NORMAL_INSTALL) @if test "$(EMACS)" != no && test -n "$(lispdir)"; then \ list='$(nodist_lisp_LISP)'; \ if test -n "$$list"; then \ echo " $(MKDIR_P) '$(DESTDIR)$(lispdir)'"; \ $(MKDIR_P) "$(DESTDIR)$(lispdir)" || exit 1; \ fi; \ for p in $$list; do \ if test -f "$$p"; then d=; else d="$(srcdir)/"; fi; \ $(am__strip_dir) \ echo " $(nodist_lispLISP_INSTALL) '$$d$$p' '$(DESTDIR)$(lispdir)/$$f'"; \ $(nodist_lispLISP_INSTALL) "$$d$$p" "$(DESTDIR)$(lispdir)/$$f" || exit $$?; \ if test -f $${p}c; then \ echo " $(nodist_lispLISP_INSTALL) '$${p}c' '$(DESTDIR)$(lispdir)/$${f}c'"; \ $(nodist_lispLISP_INSTALL) "$${p}c" "$(DESTDIR)$(lispdir)/$${f}c" || exit $$?; \ else : ; fi; \ done; \ else : ; fi uninstall-nodist_lispLISP: @$(NORMAL_UNINSTALL) @test "$(EMACS)" != no && test -n "$(lispdir)" || exit 0; \ list='$(nodist_lisp_LISP)'; \ files=`for p in $$list; do echo $$p; done | sed -e 's|^.*/||'`; \ files="$$files "`echo "$$files" | sed 's|$$|c|'`; \ dir='$(DESTDIR)$(lispdir)'; $(am__uninstall_files_from_dir) install-nodist_lispstartLISP: $(nodist_lispstart_LISP) $(ELCFILES) @$(NORMAL_INSTALL) @if test "$(EMACS)" != no && test -n "$(lispstartdir)"; then \ list='$(nodist_lispstart_LISP)'; \ if test -n "$$list"; then \ echo " $(MKDIR_P) '$(DESTDIR)$(lispstartdir)'"; \ $(MKDIR_P) "$(DESTDIR)$(lispstartdir)" || exit 1; \ fi; \ for p in $$list; do \ if test -f "$$p"; then d=; else d="$(srcdir)/"; fi; \ $(am__strip_dir) \ echo " $(nodist_lispstartLISP_INSTALL) '$$d$$p' '$(DESTDIR)$(lispstartdir)/$$f'"; \ $(nodist_lispstartLISP_INSTALL) "$$d$$p" "$(DESTDIR)$(lispstartdir)/$$f" || exit $$?; \ if test -f $${p}c; then \ echo " $(nodist_lispstartLISP_INSTALL) '$${p}c' '$(DESTDIR)$(lispstartdir)/$${f}c'"; \ $(nodist_lispstartLISP_INSTALL) "$${p}c" "$(DESTDIR)$(lispstartdir)/$${f}c" || exit $$?; \ else : ; fi; \ done; \ else : ; fi uninstall-nodist_lispstartLISP: @$(NORMAL_UNINSTALL) @test "$(EMACS)" != no && test -n "$(lispstartdir)" || exit 0; \ list='$(nodist_lispstart_LISP)'; \ files=`for p in $$list; do echo $$p; done | sed -e 's|^.*/||'`; \ files="$$files "`echo "$$files" | sed 's|$$|c|'`; \ dir='$(DESTDIR)$(lispstartdir)'; $(am__uninstall_files_from_dir) install-dist_aclocalDATA: $(dist_aclocal_DATA) @$(NORMAL_INSTALL) @list='$(dist_aclocal_DATA)'; test -n "$(aclocaldir)" || list=; \ if test -n "$$list"; then \ echo " $(MKDIR_P) '$(DESTDIR)$(aclocaldir)'"; \ $(MKDIR_P) "$(DESTDIR)$(aclocaldir)" || exit 1; \ fi; \ for p in $$list; do \ if test -f "$$p"; then d=; else d="$(srcdir)/"; fi; \ echo "$$d$$p"; \ done | $(am__base_list) | \ while read files; do \ echo " $(INSTALL_DATA) $$files '$(DESTDIR)$(aclocaldir)'"; \ $(INSTALL_DATA) $$files "$(DESTDIR)$(aclocaldir)" || exit $$?; \ done uninstall-dist_aclocalDATA: @$(NORMAL_UNINSTALL) @list='$(dist_aclocal_DATA)'; test -n "$(aclocaldir)" || list=; \ files=`for p in $$list; do echo $$p; done | sed -e 's|^.*/||'`; \ dir='$(DESTDIR)$(aclocaldir)'; $(am__uninstall_files_from_dir) install-moduleDATA: $(module_DATA) @$(NORMAL_INSTALL) @list='$(module_DATA)'; test -n "$(moduledir)" || list=; \ if test -n "$$list"; then \ echo " $(MKDIR_P) '$(DESTDIR)$(moduledir)'"; \ $(MKDIR_P) "$(DESTDIR)$(moduledir)" || exit 1; \ fi; \ for p in $$list; do \ if test -f "$$p"; then d=; else d="$(srcdir)/"; fi; \ echo "$$d$$p"; \ done | $(am__base_list) | \ while read files; do \ echo " $(INSTALL_DATA) $$files '$(DESTDIR)$(moduledir)'"; \ $(INSTALL_DATA) $$files "$(DESTDIR)$(moduledir)" || exit $$?; \ done uninstall-moduleDATA: @$(NORMAL_UNINSTALL) @list='$(module_DATA)'; test -n "$(moduledir)" || list=; \ files=`for p in $$list; do echo $$p; done | sed -e 's|^.*/||'`; \ dir='$(DESTDIR)$(moduledir)'; $(am__uninstall_files_from_dir) install-nodist_pkgconfigDATA: $(nodist_pkgconfig_DATA) @$(NORMAL_INSTALL) @list='$(nodist_pkgconfig_DATA)'; test -n "$(pkgconfigdir)" || list=; \ if test -n "$$list"; then \ echo " $(MKDIR_P) '$(DESTDIR)$(pkgconfigdir)'"; \ $(MKDIR_P) "$(DESTDIR)$(pkgconfigdir)" || exit 1; \ fi; \ for p in $$list; do \ if test -f "$$p"; then d=; else d="$(srcdir)/"; fi; \ echo "$$d$$p"; \ done | $(am__base_list) | \ while read files; do \ echo " $(INSTALL_DATA) $$files '$(DESTDIR)$(pkgconfigdir)'"; \ $(INSTALL_DATA) $$files "$(DESTDIR)$(pkgconfigdir)" || exit $$?; \ done uninstall-nodist_pkgconfigDATA: @$(NORMAL_UNINSTALL) @list='$(nodist_pkgconfig_DATA)'; test -n "$(pkgconfigdir)" || list=; \ files=`for p in $$list; do echo $$p; done | sed -e 's|^.*/||'`; \ dir='$(DESTDIR)$(pkgconfigdir)'; $(am__uninstall_files_from_dir) # This directory's subdirectories are mostly independent; you can cd # into them and run `make' without going through this Makefile. # To change the values of `make' variables: instead of editing Makefiles, # (1) if the variable is set in `config.status', edit `config.status' # (which will cause the Makefiles to be regenerated when you run `make'); # (2) otherwise, pass the desired values on the `make' command line. $(RECURSIVE_TARGETS): @fail= failcom='exit 1'; \ for f in x $$MAKEFLAGS; do \ case $$f in \ *=* | --[!k]*);; \ *k*) failcom='fail=yes';; \ esac; \ done; \ dot_seen=no; \ target=`echo $@ | sed s/-recursive//`; \ list='$(SUBDIRS)'; for subdir in $$list; do \ echo "Making $$target in $$subdir"; \ if test "$$subdir" = "."; then \ dot_seen=yes; \ local_target="$$target-am"; \ else \ local_target="$$target"; \ fi; \ ($(am__cd) $$subdir && $(MAKE) $(AM_MAKEFLAGS) $$local_target) \ || eval $$failcom; \ done; \ if test "$$dot_seen" = "no"; then \ $(MAKE) $(AM_MAKEFLAGS) "$$target-am" || exit 1; \ fi; test -z "$$fail" $(RECURSIVE_CLEAN_TARGETS): @fail= failcom='exit 1'; \ for f in x $$MAKEFLAGS; do \ case $$f in \ *=* | --[!k]*);; \ *k*) failcom='fail=yes';; \ esac; \ done; \ dot_seen=no; \ case "$@" in \ distclean-* | maintainer-clean-*) list='$(DIST_SUBDIRS)' ;; \ *) list='$(SUBDIRS)' ;; \ esac; \ rev=''; for subdir in $$list; do \ if test "$$subdir" = "."; then :; else \ rev="$$subdir $$rev"; \ fi; \ done; \ rev="$$rev ."; \ target=`echo $@ | sed s/-recursive//`; \ for subdir in $$rev; do \ echo "Making $$target in $$subdir"; \ if test "$$subdir" = "."; then \ local_target="$$target-am"; \ else \ local_target="$$target"; \ fi; \ ($(am__cd) $$subdir && $(MAKE) $(AM_MAKEFLAGS) $$local_target) \ || eval $$failcom; \ done && test -z "$$fail" tags-recursive: list='$(SUBDIRS)'; for subdir in $$list; do \ test "$$subdir" = . || ($(am__cd) $$subdir && $(MAKE) $(AM_MAKEFLAGS) tags); \ done ctags-recursive: list='$(SUBDIRS)'; for subdir in $$list; do \ test "$$subdir" = . || ($(am__cd) $$subdir && $(MAKE) $(AM_MAKEFLAGS) ctags); \ done ID: $(HEADERS) $(SOURCES) $(LISP) $(TAGS_FILES) list='$(SOURCES) $(HEADERS) $(LISP) $(TAGS_FILES)'; \ unique=`for i in $$list; do \ if test -f "$$i"; then echo $$i; else echo $(srcdir)/$$i; fi; \ done | \ $(AWK) '{ files[$$0] = 1; nonempty = 1; } \ END { if (nonempty) { for (i in files) print i; }; }'`; \ mkid -fID $$unique tags: TAGS TAGS: tags-recursive $(HEADERS) $(SOURCES) config.h.in $(TAGS_DEPENDENCIES) \ $(TAGS_FILES) $(LISP) set x; \ here=`pwd`; \ if ($(ETAGS) --etags-include --version) >/dev/null 2>&1; then \ include_option=--etags-include; \ empty_fix=.; \ else \ include_option=--include; \ empty_fix=; \ fi; \ list='$(SUBDIRS)'; for subdir in $$list; do \ if test "$$subdir" = .; then :; else \ test ! -f $$subdir/TAGS || \ set "$$@" "$$include_option=$$here/$$subdir/TAGS"; \ fi; \ done; \ list='$(SOURCES) $(HEADERS) config.h.in $(LISP) $(TAGS_FILES)'; \ unique=`for i in $$list; do \ if test -f "$$i"; then echo $$i; else echo $(srcdir)/$$i; fi; \ done | \ $(AWK) '{ files[$$0] = 1; nonempty = 1; } \ END { if (nonempty) { for (i in files) print i; }; }'`; \ shift; \ if test -z "$(ETAGS_ARGS)$$*$$unique"; then :; else \ test -n "$$unique" || unique=$$empty_fix; \ if test $$# -gt 0; then \ $(ETAGS) $(ETAGSFLAGS) $(AM_ETAGSFLAGS) $(ETAGS_ARGS) \ "$$@" $$unique; \ else \ $(ETAGS) $(ETAGSFLAGS) $(AM_ETAGSFLAGS) $(ETAGS_ARGS) \ $$unique; \ fi; \ fi ctags: CTAGS CTAGS: ctags-recursive $(HEADERS) $(SOURCES) config.h.in $(TAGS_DEPENDENCIES) \ $(TAGS_FILES) $(LISP) list='$(SOURCES) $(HEADERS) config.h.in $(LISP) $(TAGS_FILES)'; \ unique=`for i in $$list; do \ if test -f "$$i"; then echo $$i; else echo $(srcdir)/$$i; fi; \ done | \ $(AWK) '{ files[$$0] = 1; nonempty = 1; } \ END { if (nonempty) { for (i in files) print i; }; }'`; \ test -z "$(CTAGS_ARGS)$$unique" \ || $(CTAGS) $(CTAGSFLAGS) $(AM_CTAGSFLAGS) $(CTAGS_ARGS) \ $$unique GTAGS: here=`$(am__cd) $(top_builddir) && pwd` \ && $(am__cd) $(top_srcdir) \ && gtags -i $(GTAGS_ARGS) "$$here" distclean-tags: -rm -f TAGS ID GTAGS GRTAGS GSYMS GPATH tags distdir: $(DISTFILES) $(am__remove_distdir) test -d "$(distdir)" || mkdir "$(distdir)" @srcdirstrip=`echo "$(srcdir)" | sed 's/[].[^$$\\*]/\\\\&/g'`; \ topsrcdirstrip=`echo "$(top_srcdir)" | sed 's/[].[^$$\\*]/\\\\&/g'`; \ list='$(DISTFILES)'; \ dist_files=`for file in $$list; do echo $$file; done | \ sed -e "s|^$$srcdirstrip/||;t" \ -e "s|^$$topsrcdirstrip/|$(top_builddir)/|;t"`; \ case $$dist_files in \ */*) $(MKDIR_P) `echo "$$dist_files" | \ sed '/\//!d;s|^|$(distdir)/|;s,/[^/]*$$,,' | \ sort -u` ;; \ esac; \ for file in $$dist_files; do \ if test -f $$file || test -d $$file; then d=.; else d=$(srcdir); fi; \ if test -d $$d/$$file; then \ dir=`echo "/$$file" | sed -e 's,/[^/]*$$,,'`; \ if test -d "$(distdir)/$$file"; then \ find "$(distdir)/$$file" -type d ! -perm -700 -exec chmod u+rwx {} \;; \ fi; \ if test -d $(srcdir)/$$file && test $$d != $(srcdir); then \ cp -fpR $(srcdir)/$$file "$(distdir)$$dir" || exit 1; \ find "$(distdir)/$$file" -type d ! -perm -700 -exec chmod u+rwx {} \;; \ fi; \ cp -fpR $$d/$$file "$(distdir)$$dir" || exit 1; \ else \ test -f "$(distdir)/$$file" \ || cp -p $$d/$$file "$(distdir)/$$file" \ || exit 1; \ fi; \ done @list='$(DIST_SUBDIRS)'; for subdir in $$list; do \ if test "$$subdir" = .; then :; else \ $(am__make_dryrun) \ || test -d "$(distdir)/$$subdir" \ || $(MKDIR_P) "$(distdir)/$$subdir" \ || exit 1; \ dir1=$$subdir; dir2="$(distdir)/$$subdir"; \ $(am__relativize); \ new_distdir=$$reldir; \ dir1=$$subdir; dir2="$(top_distdir)"; \ $(am__relativize); \ new_top_distdir=$$reldir; \ echo " (cd $$subdir && $(MAKE) $(AM_MAKEFLAGS) top_distdir="$$new_top_distdir" distdir="$$new_distdir" \\"; \ echo " am__remove_distdir=: am__skip_length_check=: am__skip_mode_fix=: distdir)"; \ ($(am__cd) $$subdir && \ $(MAKE) $(AM_MAKEFLAGS) \ top_distdir="$$new_top_distdir" \ distdir="$$new_distdir" \ am__remove_distdir=: \ am__skip_length_check=: \ am__skip_mode_fix=: \ distdir) \ || exit 1; \ fi; \ done $(MAKE) $(AM_MAKEFLAGS) \ top_distdir="$(top_distdir)" distdir="$(distdir)" \ dist-hook -test -n "$(am__skip_mode_fix)" \ || find "$(distdir)" -type d ! -perm -755 \ -exec chmod u+rwx,go+rx {} \; -o \ ! -type d ! -perm -444 -links 1 -exec chmod a+r {} \; -o \ ! -type d ! -perm -400 -exec chmod a+r {} \; -o \ ! -type d ! -perm -444 -exec $(install_sh) -c -m a+r {} {} \; \ || chmod -R a+r "$(distdir)" dist-gzip: distdir tardir=$(distdir) && $(am__tar) | GZIP=$(GZIP_ENV) gzip -c >$(distdir).tar.gz $(am__remove_distdir) dist-bzip2: distdir tardir=$(distdir) && $(am__tar) | BZIP2=$${BZIP2--9} bzip2 -c >$(distdir).tar.bz2 $(am__remove_distdir) dist-lzip: distdir tardir=$(distdir) && $(am__tar) | lzip -c $${LZIP_OPT--9} >$(distdir).tar.lz $(am__remove_distdir) dist-lzma: distdir tardir=$(distdir) && $(am__tar) | lzma -9 -c >$(distdir).tar.lzma $(am__remove_distdir) dist-xz: distdir tardir=$(distdir) && $(am__tar) | XZ_OPT=$${XZ_OPT--e} xz -c >$(distdir).tar.xz $(am__remove_distdir) dist-tarZ: distdir tardir=$(distdir) && $(am__tar) | compress -c >$(distdir).tar.Z $(am__remove_distdir) dist-shar: distdir shar $(distdir) | GZIP=$(GZIP_ENV) gzip -c >$(distdir).shar.gz $(am__remove_distdir) dist-zip: distdir -rm -f $(distdir).zip zip -rq $(distdir).zip $(distdir) $(am__remove_distdir) dist dist-all: distdir tardir=$(distdir) && $(am__tar) | GZIP=$(GZIP_ENV) gzip -c >$(distdir).tar.gz tardir=$(distdir) && $(am__tar) | XZ_OPT=$${XZ_OPT--e} xz -c >$(distdir).tar.xz $(am__remove_distdir) # This target untars the dist file and tries a VPATH configuration. Then # it guarantees that the distribution is self-contained by making another # tarfile. distcheck: dist case '$(DIST_ARCHIVES)' in \ *.tar.gz*) \ GZIP=$(GZIP_ENV) gzip -dc $(distdir).tar.gz | $(am__untar) ;;\ *.tar.bz2*) \ bzip2 -dc $(distdir).tar.bz2 | $(am__untar) ;;\ *.tar.lzma*) \ lzma -dc $(distdir).tar.lzma | $(am__untar) ;;\ *.tar.lz*) \ lzip -dc $(distdir).tar.lz | $(am__untar) ;;\ *.tar.xz*) \ xz -dc $(distdir).tar.xz | $(am__untar) ;;\ *.tar.Z*) \ uncompress -c $(distdir).tar.Z | $(am__untar) ;;\ *.shar.gz*) \ GZIP=$(GZIP_ENV) gzip -dc $(distdir).shar.gz | unshar ;;\ *.zip*) \ unzip $(distdir).zip ;;\ esac chmod -R a-w $(distdir); chmod u+w $(distdir) mkdir $(distdir)/_build mkdir $(distdir)/_inst chmod a-w $(distdir) test -d $(distdir)/_build || exit 0; \ dc_install_base=`$(am__cd) $(distdir)/_inst && pwd | sed -e 's,^[^:\\/]:[\\/],/,'` \ && dc_destdir="$${TMPDIR-/tmp}/am-dc-$$$$/" \ && am__cwd=`pwd` \ && $(am__cd) $(distdir)/_build \ && ../configure --srcdir=.. --prefix="$$dc_install_base" \ $(AM_DISTCHECK_CONFIGURE_FLAGS) \ $(DISTCHECK_CONFIGURE_FLAGS) \ && $(MAKE) $(AM_MAKEFLAGS) \ && $(MAKE) $(AM_MAKEFLAGS) dvi \ && $(MAKE) $(AM_MAKEFLAGS) check \ && $(MAKE) $(AM_MAKEFLAGS) install \ && $(MAKE) $(AM_MAKEFLAGS) installcheck \ && $(MAKE) $(AM_MAKEFLAGS) uninstall \ && $(MAKE) $(AM_MAKEFLAGS) distuninstallcheck_dir="$$dc_install_base" \ distuninstallcheck \ && chmod -R a-w "$$dc_install_base" \ && ({ \ (cd ../.. && umask 077 && mkdir "$$dc_destdir") \ && $(MAKE) $(AM_MAKEFLAGS) DESTDIR="$$dc_destdir" install \ && $(MAKE) $(AM_MAKEFLAGS) DESTDIR="$$dc_destdir" uninstall \ && $(MAKE) $(AM_MAKEFLAGS) DESTDIR="$$dc_destdir" \ distuninstallcheck_dir="$$dc_destdir" distuninstallcheck; \ } || { rm -rf "$$dc_destdir"; exit 1; }) \ && rm -rf "$$dc_destdir" \ && $(MAKE) $(AM_MAKEFLAGS) dist \ && rm -rf $(DIST_ARCHIVES) \ && $(MAKE) $(AM_MAKEFLAGS) distcleancheck \ && cd "$$am__cwd" \ || exit 1 $(am__remove_distdir) @(echo "$(distdir) archives ready for distribution: "; \ list='$(DIST_ARCHIVES)'; for i in $$list; do echo $$i; done) | \ sed -e 1h -e 1s/./=/g -e 1p -e 1x -e '$$p' -e '$$x' distuninstallcheck: @test -n '$(distuninstallcheck_dir)' || { \ echo 'ERROR: trying to run $@ with an empty' \ '$$(distuninstallcheck_dir)' >&2; \ exit 1; \ }; \ $(am__cd) '$(distuninstallcheck_dir)' || { \ echo 'ERROR: cannot chdir into $(distuninstallcheck_dir)' >&2; \ exit 1; \ }; \ test `$(am__distuninstallcheck_listfiles) | wc -l` -eq 0 \ || { echo "ERROR: files left after uninstall:" ; \ if test -n "$(DESTDIR)"; then \ echo " (check DESTDIR support)"; \ fi ; \ $(distuninstallcheck_listfiles) ; \ exit 1; } >&2 distcleancheck: distclean @if test '$(srcdir)' = . ; then \ echo "ERROR: distcleancheck can only run from a VPATH build" ; \ exit 1 ; \ fi @test `$(distcleancheck_listfiles) | wc -l` -eq 0 \ || { echo "ERROR: files left in build directory after distclean:" ; \ $(distcleancheck_listfiles) ; \ exit 1; } >&2 check-am: all-am check: check-recursive all-am: Makefile $(PROGRAMS) $(SCRIPTS) $(LISP) $(ELCFILES) $(DATA) \ $(HEADERS) config.h all-local installdirs: installdirs-recursive installdirs-am: for dir in "$(DESTDIR)$(bindir)" "$(DESTDIR)$(bindir)" "$(DESTDIR)$(lispdir)" "$(DESTDIR)$(lispdir)" "$(DESTDIR)$(lispstartdir)" "$(DESTDIR)$(aclocaldir)" "$(DESTDIR)$(moduledir)" "$(DESTDIR)$(pkgconfigdir)"; do \ test -z "$$dir" || $(MKDIR_P) "$$dir"; \ done install: install-recursive install-exec: install-exec-recursive install-data: install-data-recursive uninstall: uninstall-recursive install-am: all-am @$(MAKE) $(AM_MAKEFLAGS) install-exec-am install-data-am installcheck: installcheck-recursive install-strip: if test -z '$(STRIP)'; then \ $(MAKE) $(AM_MAKEFLAGS) INSTALL_PROGRAM="$(INSTALL_STRIP_PROGRAM)" \ install_sh_PROGRAM="$(INSTALL_STRIP_PROGRAM)" INSTALL_STRIP_FLAG=-s \ install; \ else \ $(MAKE) $(AM_MAKEFLAGS) INSTALL_PROGRAM="$(INSTALL_STRIP_PROGRAM)" \ install_sh_PROGRAM="$(INSTALL_STRIP_PROGRAM)" INSTALL_STRIP_FLAG=-s \ "INSTALL_PROGRAM_ENV=STRIPPROG='$(STRIP)'" install; \ fi mostlyclean-generic: clean-generic: -test -z "$(CLEANFILES)" || rm -f $(CLEANFILES) distclean-generic: -test -z "$(CONFIG_CLEAN_FILES)" || rm -f $(CONFIG_CLEAN_FILES) -test . = "$(srcdir)" || test -z "$(CONFIG_CLEAN_VPATH_FILES)" || rm -f $(CONFIG_CLEAN_VPATH_FILES) -test -z "$(DISTCLEANFILES)" || rm -f $(DISTCLEANFILES) maintainer-clean-generic: @echo "This command is intended for maintainers to use" @echo "it deletes files that may require special tools to rebuild." clean: clean-recursive clean-am: clean-binPROGRAMS clean-generic clean-libtool clean-lisp \ clean-local clean-noinstPROGRAMS mostlyclean-am distclean: distclean-recursive -rm -f $(am__CONFIG_DISTCLEAN_FILES) -rm -rf ./$(DEPDIR) -rm -f Makefile distclean-am: clean-am distclean-compile distclean-generic \ distclean-hdr distclean-libtool distclean-tags dvi: dvi-recursive dvi-am: html: html-recursive html-am: info: info-recursive info-am: install-data-am: install-dist_aclocalDATA install-dist_lispLISP \ install-moduleDATA install-nodist_lispLISP \ install-nodist_lispstartLISP install-nodist_pkgconfigDATA @$(NORMAL_INSTALL) $(MAKE) $(AM_MAKEFLAGS) install-data-hook install-dvi: install-dvi-recursive install-dvi-am: install-exec-am: install-binPROGRAMS install-binSCRIPTS @$(NORMAL_INSTALL) $(MAKE) $(AM_MAKEFLAGS) install-exec-hook install-html: install-html-recursive install-html-am: install-info: install-info-recursive install-info-am: install-man: install-pdf: install-pdf-recursive install-pdf-am: install-ps: install-ps-recursive install-ps-am: installcheck-am: maintainer-clean: maintainer-clean-recursive -rm -f $(am__CONFIG_DISTCLEAN_FILES) -rm -rf $(top_srcdir)/autom4te.cache -rm -rf ./$(DEPDIR) -rm -f Makefile maintainer-clean-am: distclean-am maintainer-clean-generic mostlyclean: mostlyclean-recursive mostlyclean-am: mostlyclean-compile mostlyclean-generic \ mostlyclean-libtool pdf: pdf-recursive pdf-am: ps: ps-recursive ps-am: uninstall-am: uninstall-binPROGRAMS uninstall-binSCRIPTS \ uninstall-dist_aclocalDATA uninstall-dist_lispLISP \ uninstall-local uninstall-moduleDATA uninstall-nodist_lispLISP \ uninstall-nodist_lispstartLISP uninstall-nodist_pkgconfigDATA .MAKE: $(RECURSIVE_CLEAN_TARGETS) $(RECURSIVE_TARGETS) all \ ctags-recursive install-am install-data-am install-exec-am \ install-strip tags-recursive .PHONY: $(RECURSIVE_CLEAN_TARGETS) $(RECURSIVE_TARGETS) CTAGS GTAGS \ all all-am all-local am--refresh check check-am clean \ clean-binPROGRAMS clean-generic clean-libtool clean-lisp \ clean-local clean-noinstPROGRAMS ctags ctags-recursive dist \ dist-all dist-bzip2 dist-gzip dist-hook dist-lzip dist-lzma \ dist-shar dist-tarZ dist-xz dist-zip distcheck distclean \ distclean-compile distclean-generic distclean-hdr \ distclean-libtool distclean-tags distcleancheck distdir \ distuninstallcheck dvi dvi-am html html-am info info-am \ install install-am install-binPROGRAMS install-binSCRIPTS \ install-data install-data-am install-data-hook \ install-dist_aclocalDATA install-dist_lispLISP install-dvi \ install-dvi-am install-exec install-exec-am install-exec-hook \ install-html install-html-am install-info install-info-am \ install-man install-moduleDATA install-nodist_lispLISP \ install-nodist_lispstartLISP install-nodist_pkgconfigDATA \ install-pdf install-pdf-am install-ps install-ps-am \ install-strip installcheck installcheck-am installdirs \ installdirs-am maintainer-clean maintainer-clean-generic \ mostlyclean mostlyclean-compile mostlyclean-generic \ mostlyclean-libtool pdf pdf-am ps ps-am tags tags-recursive \ uninstall uninstall-am uninstall-binPROGRAMS \ uninstall-binSCRIPTS uninstall-dist_aclocalDATA \ uninstall-dist_lispLISP uninstall-local uninstall-moduleDATA \ uninstall-nodist_lispLISP uninstall-nodist_lispstartLISP \ uninstall-nodist_pkgconfigDATA smalltalk-mode-init.el: smalltalk-mode-init.el.in $(SED) -e "s,@\(lispdir\)@,$(lispdir)," \ -e "s/@\(WITH_EMACS_COMINT_TRUE\)@/$(LISP_WITH_EMACS_COMINT)/" \ $(srcdir)/smalltalk-mode-init.el.in > smalltalk-mode-init.el gst-mode.el: gst-mode.el.in $(SED) -e "s,@\(bindir\)@,$(bindir)," $(srcdir)/gst-mode.el.in \ > gst-mode.el uninstall-local:: @for i in gst-load $(GST_EXTRA_TOOLS); do \ echo rm -f "$(DESTDIR)$(bindir)/$$i$(EXEEXT)"; \ rm -f "$(DESTDIR)$(bindir)/$$i$(EXEEXT)"; \ done install-exec-hook:: $(INSTALL_PROGRAM_ENV) $(LIBTOOL) --mode=install $(INSTALL) gst-tool$(EXEEXT) "$(DESTDIR)$(bindir)/gst-load$(EXEEXT)" @for i in $(GST_EXTRA_TOOLS); do \ echo $(LN) -f "$(DESTDIR)$(bindir)/gst-load$(EXEEXT)" "$(DESTDIR)$(bindir)/$$i$(EXEEXT)"; \ $(LN) -f "$(DESTDIR)$(bindir)/gst-load$(EXEEXT)" "$(DESTDIR)$(bindir)/$$i$(EXEEXT)"; \ done # These two lines add a beatiful icon to the Win32 executable gsticon.o: gsticon.ico cd $(srcdir) && echo ProgramIcon ICON `$(CYGPATH_W) gsticon.ico` | \ $(WINDRES) -o $(abs_builddir)/gsticon.o gst.im: $(bin_PROGRAMS) $(srcdir)/kernel/stamp-classes $(WINEWRAPPERDEP) $(GST) -iQ /dev/null ########################################################### # # Rules for installing and distributing # # More rules are created by the GST_PACKAGE macros, # including the stamp files used for building the # documentation. Here we mimic those rules for the # kernel, whose file list lives in packages.xml # ########################################################### -include $(srcdir)/kernel/Makefile.frag all-local: $(srcdir)/kernel/stamp-classes # The slow rule for building the stamp-classes files uses gst-package, and # depends on packages.xml in order to run when the list of files in the # package might have changed. The fast rule just touches the file. We # could actually do without double-colon rules by using another stamp file # which depends on packages.xml and rebuilds all the stamp-classes files. $(srcdir)/kernel/Makefile.frag: $(srcdir)/packages.xml $(WINEWRAPPERDEP) (echo '$$(srcdir)/kernel/stamp-classes: \'; \ $(GST_PACKAGE) --list-files Kernel --vpath --srcdir="$(srcdir)" $(srcdir)/packages.xml | \ tr -d \\r | tr \\n ' '; \ echo; \ echo ' touch $$(srcdir)/kernel/stamp-classes') \ > $(srcdir)/kernel/Makefile.frag all-local: clean-local:: dist-hook:: $(GST_PACKAGE) --dist \ --distdir="$(distdir)" --srcdir="$(srcdir)" \ $(srcdir)/packages.xml cp -p $(srcdir)/kernel/stamp-classes $(distdir)/kernel/stamp-classes cp -p $(srcdir)/kernel/Makefile.frag $(distdir)/kernel/Makefile.frag # Build an image after installing the data; install-data runs after # install-exec, so the gst executable is already in bindir. # To install the kernel files, we use gst-package in --dist mode. install-data-hook:: $(GST_PACKAGE) --dist --copy --all-files \ --destdir="$(DESTDIR)" --target-dir="$(pkgdatadir)" \ --srcdir "$(srcdir)" $(srcdir)/packages.xml $(mkdir_p) $(DESTDIR)$(imagedir) cd $(DESTDIR)$(imagedir) && \ $(WINEWRAPPER) "$(abs_top_builddir)/gst$(EXEEXT)" --no-user-files -iS \ --kernel-dir "$(DESTDIR)$(pkgdatadir)/kernel" \ --image "$(DESTDIR)$(imagedir)/gst.im" \ -f "@abs_top_srcdir@/scripts/Finish.st" \ "$(imagedir)" $(MODULES) uninstall-local:: gst-tool$(EXEEXT) $(WINEWRAPPER) $(GST_PACKAGE) \ --uninstall --destdir="$(DESTDIR)" --target-dir "$(pkgdatadir)" \ --srcdir $(srcdir) $(DESTDIR)$(pkgdatadir)/packages.xml -rm -f $(DESTDIR)$(imagedir)/gst.im @PACKAGE_RULES@ # Tell versions [3.59,3.63) of GNU make to not export all variables. # Otherwise a system limit (for SysV at least) may be exceeded. .NOEXPORT: smalltalk-3.2.5/gst-config.in0000644000175000017500000000360512123404352013016 00000000000000#!/bin/sh : ${prefix:=@prefix@} : ${exec_prefix:=@exec_prefix@} : ${libdir:="@libdir@"} : ${datarootdir:=@datarootdir@} : ${pkglibdir:="@libdir@/@PACKAGE@"} : ${pkgdatadir:="@datadir@/@PACKAGE@"} : ${moduledir:="@moduledir@"} exec_prefix_set=no usage() { cat <&2 fi lib_gtk=yes while test $# -gt 0; do case "$1" in -*=*) optarg=`echo "$1" | sed 's/[-_a-zA-Z0-9]*=//'` ;; *) optarg= ;; esac case $1 in --prefix=*) prefix=$optarg if test $exec_prefix_set = no ; then exec_prefix=$optarg fi ;; --prefix) echo_prefix=yes ;; --exec-prefix=*) exec_prefix=$optarg exec_prefix_set=yes ;; --datadir) echo_datadir=yes ;; --libdir) echo_libdir=yes ;; --exec-prefix) echo_exec_prefix=yes ;; --help) usage 0 ;; --version) echo @VERSION@ ;; --cflags) echo_cflags=yes ;; --libs) echo_libs=yes ;; gst) lib_gst=yes ;; *) usage 1 1>&2 ;; esac shift done gst_libs="-L${libdir} @LIBS@" if test "$echo_prefix" = "yes"; then echo $prefix fi if test "$echo_exec_prefix" = "yes"; then echo $exec_prefix fi if test "$echo_cflags" = "yes"; then my_cflags= test @includedir@ != /usr/include & my_cflags=-I@includedir@ echo $my_cflags fi if test "$echo_libs" = "yes"; then my_gst_libs=-L@libdir@ for i in $gst_libs ; do test $i != -L@libdir@ && my_gst_libs="$my_gst_libs $i" done echo $my_gst_libs -lgst fi if test "$echo_datadir" = "yes"; then echo $pkgdatadir fi if test "$echo_libdir" = "yes"; then echo $moduledir fi smalltalk-3.2.5/gst-mode.el.in0000644000175000017500000003131712123404352013075 00000000000000;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;; ;;; ;;; Copyright 1988-92, 1994-95, 1999, 2000, 2003, 2007, 2008 ;;; Free Software Foundation, Inc. ;;; Written by Steve Byrne. ;;; ;;; This file is part of GNU Smalltalk. ;;; ;;; GNU Smalltalk is free software; you can redistribute it and/or modify it ;;; under the terms of the GNU General Public License as published by the Free ;;; Software Foundation; either version 2, or (at your option) any later ;;; version. ;;; ;;; GNU Smalltalk is distributed in the hope that it will be useful, but ;;; WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY ;;; or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License ;;; for more details. ;;; ;;; You should have received a copy of the GNU General Public License along ;;; with GNU Smalltalk; see the file COPYING. If not, write to the Free ;;; Software Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. ;;; ;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;;; ;;; Incorporates Frank Caggiano's changes for Emacs 19. ;;; Updates and changes for Emacs 20 and 21 by David Forster (require 'comint) (defvar smalltalk-prompt-pattern "^st> *" "Regexp to match prompts in smalltalk buffer.") (defvar *gst-process* nil "Holds the GNU Smalltalk process") (defvar gst-program-name "@bindir@/gst -V" "GNU Smalltalk command to run. Do not use the -a, -f or -- options.") (defvar smalltalk-command-string nil "Non nil means that we're accumulating output from Smalltalk") (defvar smalltalk-eval-data nil "?") (defvar smalltalk-ctl-t-map (let ((keymap (make-sparse-keymap))) (define-key keymap "\C-d" 'smalltalk-toggle-decl-tracing) (define-key keymap "\C-e" 'smalltalk-toggle-exec-tracing) (define-key keymap "\C-v" 'smalltalk-toggle-verbose-exec-tracing) keymap) "Keymap of subcommands of C-c C-t, tracing related commands") (defvar gst-mode-map (let ((keymap (copy-keymap comint-mode-map))) (define-key keymap "\C-c\C-t" smalltalk-ctl-t-map) (define-key keymap "\C-\M-f" 'smalltalk-forward-sexp) (define-key keymap "\C-\M-b" 'smalltalk-backward-sexp) (define-key keymap "\C-cd" 'smalltalk-doit) (define-key keymap "\C-cf" 'smalltalk-filein) (define-key keymap "\C-cp" 'smalltalk-print) (define-key keymap "\C-cq" 'smalltalk-quit) (define-key keymap "\C-cs" 'smalltalk-snapshot) keymap) "Keymap used in Smalltalk interactor mode.") (defun gst (command-line) "Invoke GNU Smalltalk" (interactive (list (if (null current-prefix-arg) gst-program-name (read-smalltalk-command)))) (setq gst-program-name command-line) (funcall (if (not (eq major-mode 'gst-mode)) #'switch-to-buffer-other-window ;; invoked from a Smalltalk interactor window, so stay ;; there #'identity) (apply 'make-gst "gst" (parse-smalltalk-command gst-program-name))) (setq *smalltalk-process* (get-buffer-process (current-buffer)))) (defun read-smalltalk-command (&optional command-line) "Reads the program name and arguments to pass to Smalltalk, providing COMMAND-LINE as a default (which itself defaults to `gst-program-name'), answering the string." (read-string "Invoke Smalltalk: " (or command-line gst-program-name))) (defun smalltalk-file-name (str) (if (file-name-directory str) (expand-file-name str) str)) (defun parse-smalltalk-command (&optional str) "Parse a list of command-line arguments from STR (default `gst-program-name'), adding --emacs-mode and answering the list." (unless str (setq str gst-program-name)) (let (start end result-args) (while (setq start (string-match "[^ \t]" str)) (setq end (or (string-match " " str start) (length str))) (push (smalltalk-file-name (substring str start end)) result-args) (if (null (cdr result-args)) (push "--emacs-mode" result-args)) (setq str (substring str end))) (nreverse result-args))) (defun make-gst (name &rest switches) (let ((buffer (get-buffer-create (concat "*" name "*"))) proc status size) (setq proc (get-buffer-process buffer)) (if proc (setq status (process-status proc))) (save-excursion (set-buffer buffer) ;; (setq size (buffer-size)) (if (memq status '(run stop)) nil (if proc (delete-process proc)) (setq proc (apply 'start-process name buffer "env" ;; I'm choosing to leave these here ;;"-" (format "TERMCAP=emacs:co#%d:tc=unknown:" (frame-width)) "TERM=emacs" "EMACS=t" switches)) (setq name (process-name proc))) (goto-char (point-max)) (set-marker (process-mark proc) (point)) (set-process-filter proc 'gst-filter) (gst-mode)) buffer)) (defun gst-filter (process string) "Make sure that the window continues to show the most recently output text." (let (where ch command-str) (setq where 0) ;fake to get through the gate (while (and string where) (if smalltalk-command-string (setq string (smalltalk-accum-command string))) (if (and string (setq where (string-match "\C-a\\|\C-b" string))) (progn (setq ch (aref string where)) (cond ((= ch ?\C-a) ;strip these out (setq string (concat (substring string 0 where) (substring string (1+ where))))) ((= ch ?\C-b) ;start of command (setq smalltalk-command-string "") ;start this off (setq string (substring string (1+ where)))))))) (save-excursion (set-buffer (process-buffer process)) (goto-char (point-max)) (and string (setq mode-status "idle") (insert string)) (if (process-mark process) (set-marker (process-mark process) (point-max))))) ;; (if (eq (process-buffer process) ;; (current-buffer)) ;; (goto-char (point-max))) ; (save-excursion ; (set-buffer (process-buffer process)) ; (goto-char (point-max)) ;; (set-window-point (get-buffer-window (current-buffer)) (point-max)) ; (sit-for 0)) (let ((buf (current-buffer))) (set-buffer (process-buffer process)) (goto-char (point-max)) (sit-for 0) (set-window-point (get-buffer-window (current-buffer)) (point-max)) (set-buffer buf))) (defun smalltalk-accum-command (string) (let (where) (setq where (string-match "\C-a" string)) (setq smalltalk-command-string (concat smalltalk-command-string (substring string 0 where))) (if where (progn (unwind-protect ;found the delimiter...do it (smalltalk-handle-command smalltalk-command-string) (setq smalltalk-command-string nil)) ;; return the remainder (substring string where)) ;; we ate it all and didn't do anything with it nil))) (defun smalltalk-handle-command (str) (eval (read str))) (defun gst-mode () "Major mode for interacting Smalltalk subprocesses. Entry to this mode calls the value of gst-mode-hook with no arguments, if that value is non-nil; likewise with the value of comint-mode-hook. gst-mode-hook is called after comint-mode-hook." (interactive) (kill-all-local-variables) (setq major-mode 'gst-mode) (setq mode-name "GST") (require 'comint) (comint-mode) (setq mode-line-format '("" mode-line-modified mode-line-buffer-identification " " global-mode-string " %[(" mode-name ": " mode-status "%n" mode-line-process ")%]----" (-3 . "%p") "-%-")) (setq comint-prompt-regexp smalltalk-prompt-pattern) (setq comint-use-prompt-regexp t) (use-local-map gst-mode-map) (make-local-variable 'mode-status) (make-local-variable 'smalltalk-command-string) (setq smalltalk-command-string nil) (setq mode-status "starting-up") (run-hooks 'comint-mode-hook 'gst-mode-hook)) (defun smalltalk-print-region (start end &optional label) (let (str filename line pos extra) (save-excursion (save-restriction (goto-char (max start end)) (smalltalk-backward-whitespace) (setq pos (point)) ;canonicalize (while (progn (smalltalk-backward-whitespace) (or (= (preceding-char) ?!) (= (preceding-char) ?.))) (backward-char 1)) (setq str (buffer-substring (min start end) (point))) (setq extra (buffer-substring (point) pos)) ;; unrelated, but reusing save-excursion (goto-char (min start end)) (setq pos (1- (point))) (setq filename (buffer-file-name)) (widen) (setq line (1+ (count-lines 1 (point)))))) (send-to-smalltalk (format "(%s) printNl%s\n" str extra) (or label "eval") (smalltalk-pos line pos)))) (defun smalltalk-eval-region (start end &optional label) "Evaluate START to END as a Smalltalk expression in Smalltalk window. If the expression does not end with an exclamation point, one will be added (at no charge)." (let (str filename line pos) (setq str (buffer-substring start end)) (save-excursion (save-restriction (goto-char (min start end)) (setq pos (point)) (setq filename (buffer-file-name)) (widen) (setq line (1+ (count-lines 1 (point)))))) (send-to-smalltalk (concat str "\n") (or label "eval") (smalltalk-pos line pos)))) (defun smalltalk-doit (use-line) (interactive "P") (let* ((start (or (mark) (point))) (end (point)) (rgn (if (or use-line (= start end)) (smalltalk-bound-expr) (cons start end)))) (smalltalk-eval-region (car rgn) (cdr rgn) "doIt"))) (defun smalltalk-print (use-line) (interactive "P") (let* ((start (or (mark) (point))) (end (point)) (rgn (if (or use-line (= start end)) (smalltalk-bound-expr) (cons start end)))) (smalltalk-print-region (car rgn) (cdr rgn) "printIt"))) (defun smalltalk-bound-expr () "Returns a cons of the region of the buffer that contains a smalltalk expression." (save-excursion (beginning-of-line) (cons (point) (progn (next-line) (smalltalk-backward-whitespace) (point))))) (defun smalltalk-pos (line pos) (let ((filename (buffer-file-name))) (if filename (list line filename pos) nil))) (defun smalltalk-compile (start end) (interactive "r") (let ((str (buffer-substring start end)) (filename (buffer-file-name)) (pos start) (line (save-excursion (save-restriction (widen) (setq line (1+ (line-number-at-pos start))))))) (send-to-smalltalk str "compile" (smalltalk-pos line pos)))) (defun smalltalk-quote-strings (str) (let (new-str) (save-excursion (set-buffer (get-buffer-create " st-dummy ")) (erase-buffer) (insert str) (goto-char 1) (while (and (not (eobp)) (search-forward "'" nil 'to-end)) (insert "'")) (buffer-string)))) (defun smalltalk-snapshot (&optional snapshot-name) (interactive (if current-prefix-arg (list (setq snapshot-name (expand-file-name (read-file-name "Snapshot to: ")))))) (if snapshot-name (send-to-smalltalk (format "ObjectMemory snapshot: '%s'\n" "Snapshot")) (send-to-smalltalk "ObjectMemory snapshot\n" "Snapshot"))) (defun smalltalk-quit () "Terminate the Smalltalk session and associated process. Emacs remains running." (interactive) (send-to-smalltalk "! ! ObjectMemory quit!" "Quitting")) (defun smalltalk-filein (filename) "Do a FileStream>>fileIn: on FILENAME." (interactive "fSmalltalk file to load: ") (send-to-smalltalk (format "FileStream fileIn: '%s'\n" (expand-file-name filename)) "fileIn")) (defun smalltalk-filein-buffer () (interactive) (send-to-smalltalk (buffer-string) "fileIn" (smalltalk-pos 1 1))) (defun smalltalk-toggle-decl-tracing () (interactive) (send-to-smalltalk "Smalltalk declarationTrace: Smalltalk declarationTrace not\n")) (defun smalltalk-toggle-exec-tracing () (interactive) (send-to-smalltalk "Smalltalk executionTrace: Smalltalk executionTrace not\n")) (defun smalltalk-toggle-verbose-exec-tracing () (interactive) (send-to-smalltalk "Smalltalk verboseTrace: Smalltalk verboseTrace not\n")) (defun send-to-smalltalk (str &optional mode fileinfo) (save-window-excursion (gst gst-program-name) (save-excursion (goto-char (point-max)) (beginning-of-line) (if (looking-at smalltalk-prompt-pattern) (progn (end-of-line) (insert "\n")))) (if mode (setq mode-status mode)) (if fileinfo (let (temp-file buf switch-back old-buf) (setq temp-file (concat "/tmp/" (make-temp-name "gst"))) (save-excursion (setq buf (get-buffer-create " zap-buffer ")) (set-buffer buf) (erase-buffer) (princ str buf) (write-region (point-min) (point-max) temp-file nil 'no-message) ) (kill-buffer buf) (process-send-string *smalltalk-process* (format "FileStream fileIn: '%s' line: %d from: '%s' at: %d\n" temp-file (nth 0 fileinfo) (nth 1 fileinfo) (nth 2 fileinfo)))) (comint-send-string *smalltalk-process* str)) (switch-to-buffer-other-window (process-buffer *smalltalk-process*)))) (provide 'gst-mode) smalltalk-3.2.5/configure.ac0000644000175000017500000007070212130343734012722 00000000000000dnl Hey Emacs, I want this in -*- Autoconf -*- mode, please. dnl --- dnl Copyright 1992-2009 Free Software Foundation, Inc. dnl Please see COPYING for a description your rights and responsibilities dnl with this software. dnl Process this file with autoconf to produce a configure script. dnl 2.63 needed by testsuite, actually AC_PREREQ(2.63) AC_INIT([GNU Smalltalk], 3.2.5, help-smalltalk@gnu.org, smalltalk, [http://smalltalk.gnu.org/]) MAINTAINER="bonzini@gnu.org" dnl CURRENT:REVISION:AGE means this is the REVISION-th version of dnl the CURRENT-th interface; all the interface from CURRENT-AGE dnl to CURRENT are supported. GST_REVISION(8:3:1) AC_CONFIG_AUX_DIR([build-aux]) AC_CONFIG_MACRO_DIR([build-aux]) AC_CONFIG_SRCDIR([main.c]) AC_CONFIG_TESTDIR(tests) AC_CONFIG_HEADERS([config.h]) GST_PROG_GAWK AM_INIT_AUTOMAKE AC_CANONICAL_HOST if test -d $srcdir/.git; then GIT_REVISION=-`git rev-parse --short HEAD 2>/dev/null || echo git` else GIT_REVISION= fi AC_DEFINE_UNQUOTED([PACKAGE_GIT_REVISION], ["$GIT_REVISION"], [The git version that GNU Smalltalk was compiled from.]) RSE_BOLD dnl dnl ------------------------------- PROGRAMS ------------------ { echo; echo "${term_bold}Build Tools:${term_norm}"; } >& AS_MESSAGE_FD GST_PROG_CC(strict-aliasing, dnl enabled optimizations gcse, dnl disabled optimizations all write-strings pointer-arith declaration-after-statement, dnl enabled warnings strict-aliasing pointer-sign long-double format switch) dnl disabled warnings if test "$GCC" != yes; then AC_MSG_ERROR([Please use GCC to compile GNU Smalltalk.]) fi case "$host" in alpha*-*-*) CFLAGS="$CFLAGS -mieee" ;; esac # We don't require Automake 1.10, so invoke _AM_DEPENDENCIES manually. And # since we actually use Objective-C only on Mac OS (for libsdl), for now we # get by with using gcc as an Objective-C compiler. AC_SUBST(OBJC, [$CC]) AC_SUBST(OBJCFLAGS, [$CFLAGS]) _AM_DEPENDENCIES(OBJC) AC_PROG_SED AC_PROG_LN_S GST_PROG_LN PKG_PROG_PKG_CONFIG AC_PATH_TOOL(WINDRES, windres, no) AC_PATH_PROG(INSTALL_INFO, install-info, :, $PATH:/sbin:/usr/sbin) AC_PATH_PROG(ZIP, zip, no, $PATH) AC_CHECK_PROG(TIMEOUT, timeout, [timeout 600s], [env]) if test "$ZIP" = no; then AC_MSG_ERROR([Please install InfoZIP to use GNU Smalltalk.]) fi # For Wine, compile in GST a generic path to zip.exe. For build time, # wrap the native zip with winewrapper to hide Windows paths from it. GST_WINE_IF([WINEWRAPPERDEP='winewrapper$(EXEEXT)' WINEWRAPPER='$(abs_top_builddir)/winewrapper$(EXEEXT)' XZIP='$(WINEWRAPPER) '$ZIP ZIP=zip.exe, AC_CONFIG_FILES([makesetup], [chmod +x makesetup])], [WINEWRAPPER= WINEWRAPPERDEP= XZIP=$ZIP]) AC_SUBST([WINEWRAPPER]) AC_SUBST([WINEWRAPPERDEP]) AC_SUBST([XZIP]) AC_ARG_WITH(emacs, [ --without-emacs disable Emacs modes for Smalltalk], , with_emacs=yes) test "$with_emacs" = no && EMACS=no AM_PATH_LISPDIR GST_PATH_LISPSTARTDIR GST_EMACS_PACKAGE(comint) AM_CONDITIONAL(WITH_EMACS, test "$EMACS" != no) AM_CONDITIONAL(WITH_EMACS_COMINT, test "$ac_cv_emacs_comint" != no) dnl We only want the GNU implementations AM_MISSING_PROG(LEX, flex, $missing_dir) AM_MISSING_PROG(YACC, bison, $missing_dir) AM_MISSING_PROG(GPERF, gperf, $missing_dir) AM_MISSING_PROG(AUTOM4TE, autom4te, $missing_dir) dnl dnl ------------------------------ SUBDIRS -------------------- PKG_CHECK_MODULES(GNUTLS, gnutls, [ac_cv_lib_gnutls_gnutls_global_init=yes], [GST_HAVE_LIB(gnutls, gnutls_global_init)]) if test "$ac_cv_lib_gnutls_gnutls_global_init" = yes; then AC_DEFINE(HAVE_GNUTLS, 1, [Define to 1 if gnutls is being used]) fi dnl Throw all these away in 3.3, and just require the system dnl lib{ltdl,ffi,sigsegv}. Before that, however, we need to dnl ensure Fedora has a cross-compiled libffi and libsigsegv. AC_ARG_WITH(system-libltdl, [ --with-system-libltdl[=PATH] use system libltdl.la (search in PATH if given)], [], [with_system_libltdl=detect]) GST_HAVE_LIB([ltdl], [lt_dlopen]) if test $with_system_libltdl = detect; then with_system_libltdl=$ac_cv_lib_ltdl_lt_dlopen fi if test $with_system_libltdl = no; then AC_MSG_WARN([using included copy of libltdl]) AC_MSG_WARN([this is deprecated and will go away]) AC_MSG_WARN([it is suggested to install libltdl]) AC_LIBOBJ(ltdl) AC_CONFIG_LINKS([lib-src/ltdl.h:lib-src/ltdl_.h]) INCLTDL= LIBLTDL= elif test $with_system_libltdl = yes; then INCLTDL= LIBLTDL=-lltdl else INCLTDL="-I$with_system_libltdl/../include" LIBLTDL="-L$with_system_libltdl -lltdl" fi AC_SUBST(INCLTDL) AC_SUBST(LIBLTDL) AC_ARG_WITH(system-libffi, [ --with-system-libffi[=PATH] use system libffi.la (search in PATH if given)], [], [with_system_libffi=detect]) PKG_CHECK_MODULES(LIBFFI, libffi, [ac_cv_lib_libffi_ffi_prep_cif=yes], [GST_HAVE_LIB(libffi, ffi_prep_cif)]) if test $with_system_libffi = detect; then with_system_libffi=$ac_cv_lib_libffi_ffi_prep_cif fi if test $with_system_libffi = no; then AC_MSG_WARN([using included copy of libffi]) AC_MSG_WARN([this is deprecated and will go away]) AC_MSG_WARN([it is suggested to install libffi]) AC_CONFIG_SUBDIRS(libffi) INCFFI='-I$(top_srcdir)/libffi/include -I$(top_builddir)/libffi/include' LIBFFI='$(top_builddir)/libffi/libffi.la' elif test $with_system_libffi = yes; then INCFFI=$LIBFFI_CFLAGS LIBFFI=${LIBFFI_LIBS:-'-lffi'} else INCFFI="-I$with_system_libffi/../include" LIBFFI="-L$with_system_libffi -lffi" fi case $host in *-*-darwin[[912]]* ) LIBFFI_EXECUTABLE_LDFLAGS=-Wl,-allow_stack_execute ;; *) LIBFFI_EXECUTABLE_LDFLAGS= ;; esac AC_SUBST(INCFFI) AC_SUBST(LIBFFI) AC_SUBST(LIBFFI_EXECUTABLE_LDFLAGS) case $ac_configure_args in *--enable-subdir) ;; *) ac_configure_args="$ac_configure_args --enable-subdir" ;; esac AC_SNPRINTFV_CONVENIENCE AC_CONFIG_SUBDIRS(snprintfv) AC_ARG_ENABLE(generational-gc, [ --disable-generational-gc disable generational garbage collection], , [case $host in *-k*bsd-gnu | \ *-*-cygwin* | *-*-mingw* | \ ia64-*-* | alpha*-*-* | sparc*-*-* ) enable_generational_gc=no ;; *) enable_generational_gc=yes ;; esac]) AC_ARG_WITH(system-libsigsegv, [ --with-system-libsigsegv[=PATH] use system libsigsegv.la likewise], [], [with_system_libsigsegv=detect]) GST_HAVE_LIB([sigsegv], [sigsegv_install_handler]) if test $with_system_libsigsegv = detect; then with_system_libsigsegv=$ac_cv_lib_sigsegv_sigsegv_install_handler fi if test $enable_generational_gc = no; then INCSIGSEGV= LIBSIGSEGV= else AC_DEFINE(HAVE_SIGSEGV_H, 1, [Define to 1 if libsigsegv is being used]) if test $with_system_libsigsegv = no; then case $host in x86_64-apple-darwin*) AC_MSG_ERROR(dnl [a pre-installed libsigsegv is required on 64-bit Darwin. To configure: error: proceed without it, use the --disable-generational-gc configure: error: option for configure.]) ;; *) AC_MSG_WARN([using included copy of libsigsegv]) AC_MSG_WARN([this is deprecated and will go away]) AC_MSG_WARN([it is suggested to install libsigsegv]) esac AC_CONFIG_SUBDIRS(sigsegv) INCSIGSEGV='-I$(top_srcdir)/sigsegv/src -I$(top_builddir)/sigsegv/src' LIBSIGSEGV='$(top_builddir)/sigsegv/src/libsigsegv_convenience.la' elif test $with_system_libsigsegv = yes; then INCSIGSEGV= LIBSIGSEGV=-lsigsegv else INCSIGSEGV="-I$with_system_libsigsegv/../include" LIBSIGSEGV="-L$with_system_libsigsegv -lsigsegv" fi fi AC_SUBST(INCSIGSEGV) AC_SUBST(LIBSIGSEGV) AC_ARG_WITH(imagedir, [ --with-imagedir=PATH path where to place the system image (default: /usr/local/var/lib/$PACKAGE)], [imagedir="$withval"], [imagedir=`echo "$libdir" | sed \ -e 's,${exec_prefix},${localstatedir},' \ -e "s,${exec_prefix},\${localstatedir}," `/$PACKAGE ]) AC_SUBST(imagedir) AC_ARG_WITH(moduledir, [ --with-moduledir=PATH path where to look for modules (default: /usr/local/lib/$PACKAGE)], [moduledir="$withval"], [moduledir='${pkglibdir}']) moduleexecdir='${moduledir}' AC_SUBST(moduledir) AC_SUBST(moduleexecdir) dnl dnl ------------------------------ C COMPILER / OS ------------ { echo; echo "${term_bold}Platform environment:${term_norm}"; } >& AS_MESSAGE_FD GST_C_SYNC_BUILTINS if test $gst_cv_have_sync_fetch_and_add = no; then AC_MSG_ERROR([Synchronization primitives not found, please use a newer compiler.]) fi GST_LOCK AC_SYS_LARGEFILE AC_C_INLINE AC_C_RESTRICT dnl Test for broken solaris include file. Should be moved to gnulib maybe? AC_MSG_CHECKING([for broken sys/avl.h]) AC_PREPROC_IFELSE([AC_LANG_SOURCE([#include #ifndef _AVL_H would be useless anyway #endif ])], [ AC_MSG_RESULT(yes) AC_DEFINE(_AVL_H, 1, [Define to 1 if, like Solaris, your system has a sys/avl.h header that pollutes the name space.])], [ AC_MSG_RESULT(no)]) GST_C_HIDDEN_VISIBILITY GST_C_LONG_DOUBLE GST_C_GOTO_VOID_P AC_DEFINE_UNQUOTED(HOST_SYSTEM, "$host", [Define to the host triplet.]) AC_DEFINE_UNQUOTED(EXEEXT, "$ac_exeext", [Define to the extension for executable files.]) case "$ac_exeext:$host_os" in :*) ac_argv_exeext= ;; .exe:cygwin*) ac_argv_exeext= ;; .exe:*) ac_argv_exeext=$ac_exeext ;; esac AC_DEFINE_UNQUOTED(ARGV_EXEEXT, "$ac_argv_exeext", [Define to the extension for executable files, as it appears in argv[0].]) AC_C_BIGENDIAN AC_CHECK_ALIGNOF(double) AC_CHECK_ALIGNOF(long double) AC_CHECK_ALIGNOF(long long) AC_CHECK_SIZEOF(off_t) AC_CHECK_SIZEOF(int) AC_CHECK_SIZEOF(long) AC_CHECK_SIZEOF(wchar_t, , [[ #include ]]) AC_CHECK_SIZEOF(OOP, , [[ typedef void *OOP;]]) AC_LIBTOOL_DLOPEN AC_LIBTOOL_WIN32_DLL AC_PROG_LIBTOOL LIBGST_CFLAGS="$SYNC_CFLAGS" case '$host_cpu: $CFLAGS ' in i*86:*' -pg '*) ;; i*86:*) LIBGST_CFLAGS="$LIBGST_CFLAGS -fomit-frame-pointer" ;; *) ;; esac AC_SUBST(LIBGST_CFLAGS) case "$host_os:$WINDRES" in *:no) ICON= ;; cygwin*|mingw*) ICON=gsticon.o ;; *) ICON= ;; esac AC_SUBST(ICON) dnl dnl ------------------------------- C LIBRARY ----------------- { echo; echo "${term_bold}C library features:${term_norm}"; } >& AS_MESSAGE_FD AC_TYPE_SIGNAL AC_TYPE_PID_T AC_TYPE_SIZE_T AC_HEADER_ASSERT AC_CHECK_HEADERS_ONCE(stdint.h inttypes.h unistd.h poll.h sys/ioctl.h \ sys/resource.h sys/utsname.h stropts.h sys/param.h stddef.h limits.h \ sys/timeb.h termios.h sys/mman.h sys/file.h execinfo.h utime.h \ sys/select.h sys/wait.h fcntl.h crt_externs.h, [], [], [AC_INCLUDES_DEFAULT]) AC_CHECK_MEMBERS([struct stat.st_mtim.tv_nsec, struct stat.st_mtimensec, struct stat.st_mtimespec.tv_nsec]) AC_TYPE_INT8_T AC_TYPE_INT16_T AC_TYPE_INT32_T AC_TYPE_INT64_T AC_TYPE_INTMAX_T AC_TYPE_INTPTR_T AC_TYPE_UINT8_T AC_TYPE_UINT16_T AC_TYPE_UINT32_T AC_TYPE_UINT64_T AC_TYPE_UINTMAX_T AC_TYPE_UINTPTR_T if test x$ac_cv_header_poll_h = xno; then AC_CONFIG_LINKS([lib-src/poll.h:lib-src/poll_.h]) fi AC_FUNC_ALLOCA AC_FUNC_OBSTACK AC_CHECK_LIB(m, atan) GST_REPLACE_POLL gt_FUNC_SETENV GST_SOCKETS AC_REPLACE_FUNCS(putenv strdup strerror strsignal mkstemp getpagesize \ getdtablesize strstr ftruncate floorl ceill sqrtl frexpl ldexpl asinl \ acosl atanl logl expl tanl sinl cosl powl truncl lrintl truncf lrintf \ lrint trunc strsep strpbrk symlink mkdtemp) AC_CHECK_FUNCS_ONCE(gethostname memcpy memmove sighold uname usleep lstat \ grantpt popen getrusage gettimeofday fork strchr utimes utime readlink \ sigsetmask alarm select mprotect madvise waitpid accept4 \ setsid spawnl pread pwrite _NSGetExecutablePath _NSGetEnviron \ chown getgrnam getpwnam endgrent endpwent setgroupent setpassent) if test "$ac_cv_func__NSGetEnviron" = yes; then AC_DEFINE([environ], [_NSGetEnviron()], [Define to an appropriate function call if the system does not provide the environ variable.]) fi AC_SEARCH_LIBS([nanosleep], [rt]) if test "$ac_cv_search_nanosleep" != no; then AC_DEFINE(HAVE_NANOSLEEP, 1, [Define if the system provides nanosleep.]) fi AC_SEARCH_LIBS([clock_gettime], [rt]) if test "$ac_cv_search_clock_gettime" != no; then AC_DEFINE(HAVE_CLOCK_GETTIME, 1, [Define if the system provides clock_gettime.]) fi AC_SEARCH_LIBS([timer_create], [rt]) if test "$ac_cv_search_timer_create" != no; then AC_DEFINE(HAVE_TIMER_CREATE, 1, [Define if the system provides timer_create.]) fi GST_FUNC_LRINT GST_FUNC_STRTOUL GST_FUNC_LOCALTIME { echo; echo "${term_bold}Dynamic linking capabilities:${term_norm}"; } >& AS_MESSAGE_FD GST_LIB_LTDL dnl ------------------------- OTHER LIBRARIES ------------------- { echo; echo "${term_bold}Auxiliary libraries:${term_norm}"; } >& AS_MESSAGE_FD GST_LIBC_SO_NAME GST_HAVE_GMP GST_HAVE_READLINE GST_PACKAGE_ALLOW_DISABLING GST_PACKAGE_PREFIX([packages]) GST_PACKAGE_DEPENDENCIES([gst-tool$(EXEEXT) gst.im $(WINEWRAPPERDEP)]) GST_PACKAGE_ENABLE([Announcements], [announcements]) GST_PACKAGE_ENABLE([BloxTK], [blox/tk], [GST_HAVE_TCLTK], [gst_cv_tcltk_libs], [Makefile], [blox-tk.la]) GST_PACKAGE_ENABLE([BLOXBrowser], [blox/browser]) GST_PACKAGE_ENABLE([Complex], [complex]) GST_PACKAGE_ENABLE([Continuations], [continuations]) GST_PACKAGE_ENABLE([CParser], [cpp]) GST_PACKAGE_ENABLE([DebugTools], [debug]) GST_PACKAGE_ENABLE([DBD-MySQL], [dbd-mysql]) AC_MSG_CHECKING([whether to run MySQL tests]) AC_ARG_ENABLE(mysql-tests, [ --enable-mysql-tests=USER:PWD:DATABASE test MySQL bindings [default=root:root:test]], , [enable_mysql_tests=no]) AC_SUBST(enable_mysql_tests) AC_MSG_RESULT($enable_mysql_tests) GST_PACKAGE_ENABLE([DBD-PostgreSQL], [dbd-postgresql], [GST_HAVE_LIB(pq, PQconnectdb)], [ac_cv_lib_pq_PQconnectdb]) GST_PACKAGE_ENABLE([DBD-SQLite], [dbd-sqlite], [AC_CHECK_HEADER([sqlite3.h]) GST_HAVE_LIB(sqlite3, sqlite3_clear_bindings)], [ac_cv_header_sqlite3_h], [Makefile], [dbd-sqlite3.la]) GST_PACKAGE_ENABLE([DBI], [dbi]) GST_PACKAGE_ENABLE([GDBM], [gdbm], [AC_CHECK_HEADER([gdbm.h])], [ac_cv_header_gdbm_h], [Makefile], [gdbm.la]) GST_PACKAGE_ENABLE([Glorp], [glorp]) GST_PACKAGE_ENABLE([Cairo], [cairo], [PKG_CHECK_MODULES([CAIRO], cairo, [gst_cv_cairo=yes], [gst_cv_cairo=no])], [gst_cv_cairo]) GST_PACKAGE_ENABLE([GTK], [gtk], [ AC_ARG_ENABLE(gtk, [ --enable-gtk={yes,no,blox} enable GTK+ bindings. Blox/GTK is experimental.], , enable_gtk=yes) if test "$enable_gtk" != no; then maybe_enable_gtk=$enable_gtk enable_gtk=no AM_PATH_GLIB_2_0(2.0.0, [ AM_PATH_GTK_2_0(2.0.0, [ PKG_CHECK_MODULES(ATK, atk >= 1.0.0, [ PKG_CHECK_MODULES(PANGO, pango >= 1.0.0, [ PKG_CHECK_MODULES(GTHREAD, gthread-2.0 >= 2.0.0, [enable_gtk=$maybe_enable_gtk]) ]) ]) ]) ], [], gobject) if test $enable_gtk = yes; then ac_save_LIBS=$LIBS ac_save_CFLAGS=$CFLAGS LIBS="$LIBS $GLIB_LIBS" CFLAGS="$CFLAGS $GLIB_CFLAGS" AC_CHECK_FUNCS([g_poll]) if test $ac_cv_func_g_poll = no; then AC_DEFINE([g_poll], [poll], [Define to poll if your glib does not provide g_poll.]) fi LIBS=$ac_save_LIBS CFLAGS=$ac_save_CFLAGS fi fi], [enable_gtk gst_cv_cairo], [Makefile], [gst-gtk.la]) GST_PACKAGE_ENABLE([BloxGTK], [blox/gtk],, [enable_gtk]) GST_PACKAGE_ENABLE([Blox], [blox/tests], [enable_blox=no case x"$enable_gtk" in xno|xnot\ found) ;; *) enable_blox=yes ;; esac case x"$gst_cv_tcltk_libs" in xno|xnot\ found) ;; *) enable_blox=yes ;; esac], [enable_blox], [package.xml]) GST_PACKAGE_ENABLE([WebServer], [httpd]) GST_PACKAGE_ENABLE([I18N], [i18n], [AC_CHECK_FUNCS_ONCE([nl_langinfo]) AM_LANGINFO_CODESET AM_ICONV], [ac_cv_func_nl_langinfo am_cv_func_iconv], [Makefile], [i18n.la]) GST_PACKAGE_ENABLE([Iconv], [iconv], [AM_ICONV], [am_cv_func_iconv], [Makefile], [iconv.la]) GST_PACKAGE_ENABLE([Java], [java]) GST_PACKAGE_ENABLE([Digest], [digest], [], [], [Makefile], [digest.la]) GST_PACKAGE_ENABLE([GNUPlot], [gnuplot]) GST_PACKAGE_ENABLE([Magritte], [magritte]) GST_PACKAGE_ENABLE([Magritte-Seaside], [seaside/magritte]) GST_PACKAGE_ENABLE([NCurses], [ncurses], [GST_HAVE_LIB(ncurses, initscr)], [ac_cv_lib_ncurses_initscr]) GST_PACKAGE_ENABLE([NetClients], [net], [], [], [Makefile]) GST_PACKAGE_ENABLE([DhbNumericalMethods], [numerics]) GST_PACKAGE_ENABLE([OpenGL], [opengl], [GST_HAVE_OPENGL], [gst_cv_opengl_libs], [Makefile], [gstopengl.la]) GST_PACKAGE_ENABLE([GLUT], [glut], [GST_HAVE_GLUT], [gst_cv_glut_libs], [Makefile], [gstglut.la]) GST_PACKAGE_ENABLE([LibSDL], [sdl/libsdl], [PKG_CHECK_MODULES(SDL, sdl >= 1.2.0, [gst_cv_sdl=yes], [gst_cv_sdl=no]) case "$SDL_LIBS" in *-framework,Cocoa* | *"-framework Cocoa"*) gst_cv_sdl_uses_cocoa=yes ;; *) gst_cv_sdl_uses_cocoa=no ;; esac save_CFLAGS=$CFLAGS save_LIBS=$LIBS CFLAGS="$CFLAGS $SDL_CFLAGS" LIBS="$LIBS $SDL_LIBS" AC_LINK_IFELSE([AC_LANG_SOURCE([ #include #include int main(int argc, char **argv) { SDL_Init(0); return 0; }])], [], [gst_cv_sdl=no]) LIBS=$save_LIBS CFLAGS=$save_CFLAGS # We do SDLmain's job on our own, and mingw32 is linked automatically # into the DLL. If we do not do this, libtool refuses to create a DLL # for the SDL module. SDL_LIBS=`echo " $SDL_LIBS " | sed 's/ -lSDLmain / /; s/ -lmingw32 / /' ` AM_CONDITIONAL([HAVE_COCOA], [test $gst_cv_sdl_uses_cocoa = yes])], [gst_cv_sdl], [Makefile], [sdl.la]) GST_PACKAGE_ENABLE([LibSDL_GL], [sdl/libsdl_gl], [], [gst_cv_sdl gst_cv_opengl_libs]) GST_PACKAGE_ENABLE([CairoSDL], [sdl/cairo], [], [gst_cv_cairo gst_cv_sdl]) GST_PACKAGE_ENABLE([LibSDL_image], [sdl/libsdl_image], [GST_HAVE_LIB(SDL_image, IMG_Linked_Version)], [ac_cv_lib_SDL_image_IMG_Linked_Version]) GST_PACKAGE_ENABLE([LibSDL_mixer], [sdl/libsdl_mixer], [GST_HAVE_LIB(SDL_mixer, Mix_Linked_Version)], [ac_cv_lib_SDL_mixer_Mix_Linked_Version]) GST_PACKAGE_ENABLE([LibSDL_sound], [sdl/libsdl_sound], [GST_HAVE_LIB(SDL_sound, Sound_GetLinkedVersion)], [ac_cv_lib_SDL_sound_Sound_GetLinkedVersion]) GST_PACKAGE_ENABLE([LibSDL_ttf], [sdl/libsdl_ttf], [GST_HAVE_LIB(SDL_ttf, TTF_Init)], [ac_cv_lib_SDL_ttf_TTF_Init]) GST_PACKAGE_ENABLE([Compiler], [stinst/compiler]) GST_PACKAGE_ENABLE([Parser], [stinst/parser]) GST_PACKAGE_ENABLE([ClassPublisher], [stinst/doc]) GST_PACKAGE_ENABLE([ProfileTools], [profile]) GST_PACKAGE_ENABLE([ROE], [roe]) GST_PACKAGE_ENABLE([SandstoneDb], [sandstonedb]) GST_PACKAGE_ENABLE([Seaside-Core], [seaside/core]) GST_PACKAGE_ENABLE([Seaside-Development], [seaside/dev]) GST_PACKAGE_ENABLE([Seaside-Examples], [seaside/examples]) GST_PACKAGE_ENABLE([Seaside], [seaside/swazoo]) GST_PACKAGE_ENABLE([Sport], [sport]) GST_PACKAGE_ENABLE([SUnit], [sunit]) GST_PACKAGE_ENABLE([Swazoo], [swazoo-httpd]) GST_PACKAGE_ENABLE([Sockets], [sockets], [], [gst_cv_sockets]) GST_PACKAGE_ENABLE([VFSAddOns], [vfs], [], [], [Makefile]) GST_PACKAGE_ENABLE([VisualGST], [visualgst]) GST_PACKAGE_ENABLE([XML-XMLNodeBuilder], [xml/builder]) GST_PACKAGE_ENABLE([XML-DOM], [xml/dom]) GST_PACKAGE_ENABLE([XML-ParserTests], [xml/tests]) GST_PACKAGE_ENABLE([XML-PullParser], [xml/pullparser]) GST_PACKAGE_ENABLE([XML-Expat], [xml/expat], [AC_CHECK_HEADER([expat.h]) GST_HAVE_LIB(expat, XML_ParserCreateNS)], [ac_cv_header_expat_h ac_cv_lib_expat_XML_ParserCreateNS], [Makefile], [expat.la]) GST_PACKAGE_ENABLE([XML-XMLParser], [xml/parser]) GST_PACKAGE_ENABLE([XML-SAXDriver], [xml/saxdriver]) GST_PACKAGE_ENABLE([XML-SAXParser], [xml/saxparser]) GST_PACKAGE_ENABLE([XPath], [xml/xpath]) GST_PACKAGE_ENABLE([XSL], [xml/xsl]) GST_PACKAGE_ENABLE([ZLib], [zlib], [AC_CHECK_HEADER([zlib.h]) GST_HAVE_LIB(z, inflate)], [ac_cv_header_zlib_h ac_cv_lib_z_inflate], [Makefile], [zlib.la]) if test "$enable_gtk" = blox; then BLOX_IMPLEMENTATION=BloxGTK else BLOX_IMPLEMENTATION=BloxTK fi AC_SUBST(BLOX_IMPLEMENTATION) AC_ARG_ENABLE(jit, [ --enable-jit enable dynamic translation to machine code], , enable_jit=no) LIGHTNING_CONFIGURE_IF_NOT_FOUND([], enable_jit=no) if test "$enable_jit" != no; then AC_DEFINE(ENABLE_JIT_TRANSLATION, 1, [Define to enable dynamic translation to machine code]) fi AC_ARG_ENABLE(disassembler, [ --enable-disassembler include a disassembler in the gst executable], , enable_disassembler=no) AM_CONDITIONAL(ENABLE_DISASSEMBLER, test "$enable_disassembler" != no) if test "$enable_disassembler" != no; then AC_DEFINE(ENABLE_DISASSEMBLER, 1, [Define to include a disassembler in the gst executable]) fi AC_ARG_ENABLE(dld, [ --disable-dld disable loading of external modules at runtime], , enable_dld=yes) if test "$enable_dld" != no; then AC_DEFINE(ENABLE_DLD, 1, [Define to enable usage of libltdl to load external modules at runtime]) fi AC_ARG_ENABLE(checking, [ --enable-checking enable assertions at runtime], , enable_checking=no) if test "$enable_checking" = no; then AC_DEFINE(OPTIMIZE, 1, [Define to disable assertion checking at runtime]) fi AC_ARG_ENABLE(preemption, [ --enable-preemption enable preemptive multitasking], , enable_preemption=no) if test "$enable_preemption" != no; then AC_DEFINE(ENABLE_PREEMPTION, 1, [Define to enable preemptive multitasking of Smalltalk processes]) fi GST_ARG_ENABLE_MODULES([Blox,TCP]) dnl dnl ------------------------------- RELOCATABILITY ------------ # See if we can make the installed binaries relocatable AC_MSG_CHECKING([whether to enable relocatable install]) AC_RELOCATABLE_NOP relocatable_reason=$RELOCATABLE # First of all, compute the final paths for the various components. AC_LIB_PREPARE_PREFIX acl_final_datadir=`echo "${datadir}" | sed \ -e "s,\\\${datarootdir},$datarootdir," \ -e "s,\\\${exec_prefix},$acl_final_exec_prefix," \ -e "s,\\\${prefix},$acl_final_prefix," ` acl_final_bindir=`echo "${bindir}" | sed \ -e "s,\\\${exec_prefix},$acl_final_exec_prefix," \ -e "s,\\\${prefix},$acl_final_prefix," ` acl_final_libdir=`echo "${libdir}" | sed \ -e "s,\\\${exec_prefix},$acl_final_exec_prefix," \ -e "s,\\\${prefix},$acl_final_prefix," ` acl_final_libexecdir=`echo "${libexecdir}" | sed \ -e "s,\\\${exec_prefix},$acl_final_exec_prefix," \ -e "s,\\\${prefix},$acl_final_prefix," ` acl_final_pkgdatadir="$acl_final_datadir/$PACKAGE" acl_final_pkglibdir="$acl_final_libdir/$PACKAGE" acl_final_imagedir=`echo "${imagedir}" | sed \ -e "s,\\\${localstatedir},$localstatedir," \ -e "s,\\\${pkgdatadir},$pkgdatadir," \ -e "s,\\\${datadir},$datadir," \ -e "s,\\\${docdir},$docdir," \ -e "s,\\\${datarootdir},$datarootdir," \ -e "s,\\\${pkglibdir},$acl_final_pkglibdir," \ -e "s,\\\${libdir},$acl_final_libdir," \ -e "s,\\\${exec_prefix},$acl_final_exec_prefix," \ -e "s,\\\${prefix},$acl_final_prefix," ` acl_final_moduledir=`echo "${moduledir}" | sed \ -e "s,\\\${localstatedir},$localstatedir," \ -e "s,\\\${pkgdatadir},$pkgdatadir," \ -e "s,\\\${datadir},$datadir," \ -e "s,\\\${docdir},$docdir," \ -e "s,\\\${datarootdir},$datarootdir," \ -e "s,\\\${pkglibdir},$acl_final_pkglibdir," \ -e "s,\\\${libdir},$acl_final_libdir," \ -e "s,\\\${exec_prefix},$acl_final_exec_prefix," \ -e "s,\\\${prefix},$acl_final_prefix," ` # If shared libraries are enabled, there are a few extra constraints. if test "$enable_shared" != no; then case $host in *-*-cygwin* | *-*-mingw*) # For Windows, the shared library will be installed in bindir anyway ;; *-gnu*) # For glibc, we can use a relative rpath via -Wl,-rpath,... case "$acl_final_libdir" in "${acl_final_exec_prefix}"/*) ;; /*) relocatable_reason='no, libdir outside exec_prefix' ;; *) relocatable_reason='no, relative libdir' ;; esac ;; *) relocatable_reason="no, relocatable shared libraries not supported on $host" ;; esac fi # Further OS-independent tests ensure that we can make relative # paths from the executable's location. if test "$relocatable_reason" = yes; then case "${acl_final_bindir}" in "${acl_final_exec_prefix}") ;; "${acl_final_exec_prefix}"/*) ;; /*) relocatable_reason='no, bindir outside exec_prefix' ;; *) relocatable_reason='no, relative bindir' ;; esac case "${acl_final_libexecdir}" in "${acl_final_exec_prefix}") ;; ${acl_final_exec_prefix}/*) ;; /*) relocatable_reason='no, libexecdir outside exec_prefix' ;; *) relocatable_reason='no, relative libexecdir' ;; esac case "${acl_final_datadir}" in ${acl_final_prefix}) ;; ${acl_final_prefix}/*) ;; /*) relocatable_reason='no, datadir outside prefix' ;; *) relocatable_reason='no, relative datadir' ;; esac case "${acl_final_imagedir}" in ${acl_final_prefix}) ;; ${acl_final_prefix}/*) ;; /*) relocatable_reason='no, imagedir outside prefix' ;; *) relocatable_reason='no, relative imagedir' ;; esac case "${acl_final_moduledir}" in ${acl_final_prefix}) ;; ${acl_final_prefix}/*) ;; /*) relocatable_reason='no, moduledir outside prefix' ;; *) relocatable_reason='no, relative moduledir' ;; esac test "$acl_final_prefix" != "$acl_final_exec_prefix" && \ relocatable_reason='no, prefix does not match exec prefix' fi # echo the relative path from ${acl_final_bindir} to $1 # (Works only if both are absolute.) [func_make_relpath () { dir=$1 idir=${acl_final_bindir} while true; do dfirst=`echo "$dir" | sed -n -e 's,^//*\([^/]*\).*$,/\1,p'` ifirst=`echo "$idir" | sed -n -e 's,^//*\([^/]*\).*$,/\1,p'` test x"$dfirst" = x && break test x"$ifirst" = x && break test "$dfirst" != "$ifirst" && break dir=`echo "$dir" | sed -e 's,^//*[^/]*,,'` idir=`echo "$idir" | sed -e 's,^//*[^/]*,,'` done idir=`echo "$idir" | sed -e 's,//*[^/]*,/..,g' -e 's,^/,,' ` echo "${idir:-.}$dir" }] case "$relocatable_reason" in yes) # Command-line option to include a relative search path for # shared libraries if test "$enable_shared" != no; then case "$host" in *-linux*) RELOC_LDFLAGS='-Wl,-rpath,"\$$ORIGIN/'`func_make_relpath ${acl_final_libdir}`'"' ;; esac fi KERNEL_PATH=`func_make_relpath ${acl_final_pkgdatadir}/kernel` IMAGE_PATH=`func_make_relpath ${acl_final_imagedir}` MODULE_PATH=`func_make_relpath ${acl_final_moduledir}` LIBEXEC_PATH=`func_make_relpath "${acl_final_libexecdir}/${PACKAGE}"` PREFIX=`func_make_relpath "${acl_final_prefix}"` EXEC_PREFIX=`func_make_relpath "${acl_final_exec_prefix}"` AC_DEFINE_UNQUOTED(KERNEL_PATH, "$KERNEL_PATH", [The relative path from the program to the kernel path. Defined only for relocatable installs.]) AC_DEFINE_UNQUOTED(IMAGE_PATH, "$IMAGE_PATH", [The relative path from the program to the image path. Defined only for relocatable installs.]) AC_DEFINE_UNQUOTED(MODULE_PATH, "$MODULE_PATH", [The relative path from the program to the module path. Defined only for relocatable installs.]) AC_DEFINE_UNQUOTED(LIBEXEC_PATH, "$LIBEXEC_PATH", [The relative path from the program to the per-package libexec path. Defined only for relocatable installs.]) AC_DEFINE_UNQUOTED(PREFIX, "$PREFIX", [The relative path from the program to the prefix. Defined only for relocatable installs.]) AC_DEFINE_UNQUOTED(EXEC_PREFIX, "$EXEC_PREFIX", [The relative path from the program to the exec_prefix. Defined only for relocatable installs.]) ;; *) # Pass paths on the command-line to allow specifying a prefix at "make" # time. RELOC_CPPFLAGS='-DKERNEL_PATH=\""${pkgdatadir}/kernel"\" \ -DIMAGE_PATH=\""${imagedir}"\" \ -DMODULE_PATH=\""${moduledir}"\" \ -DLIBEXEC_PATH=\""${libexecdir}/${PACKAGE}"\" \ -DPREFIX=\""${prefix}"\" \ -DEXEC_PREFIX=\""${exec_prefix}"\" ' ;; esac RELOC_CPPFLAGS=$RELOC_CPPFLAGS' \ -DDEFAULT_EXECUTABLE=\""${bindir}/gst${EXEEXT}"\"' AC_MSG_RESULT([$relocatable_reason]) AC_SUBST(RELOC_CPPFLAGS) AC_SUBST(RELOC_LDFLAGS) dnl dnl ------------------------------- FILE GENERATION ----------- { echo; echo "${term_bold}Output substitutions:${term_norm}"; } >& AS_MESSAGE_FD AC_CONFIG_COMMANDS_PRE([ LTLIBOBJS=`echo "$LIB@&t@OBJS" | sed 's,\.[[^.]]* ,.lo ,g;s,\.[[^.]]*$,.lo,'` LTALLOCA=`echo "$ALLOCA" | sed 's/\.o/.lo/g'` ]) GST_RUN='$(top_builddir)/gst -I $(top_builddir)/gst.im -f' AC_SUBST(GST_RUN) AC_SUBST(CFLAGS) AC_SUBST(INCLTDL) AC_SUBST(LIBLTDL) AC_SUBST(LTALLOCA) AC_SUBST(LTLIBOBJS) dnl Scripts & data files AC_CONFIG_FILES(gnu-smalltalk.pc) AC_CONFIG_FILES(gst-config, chmod +x gst-config) AC_CONFIG_FILES(tests/gst, chmod +x tests/gst) AC_CONFIG_FILES(tests/atlocal) dnl Master Makefile AC_CONFIG_FILES(Makefile) dnl VM makefiles AC_CONFIG_FILES(doc/Makefile lib-src/Makefile libgst/Makefile) AC_CONFIG_FILES(opcode/Makefile lightning/Makefile tests/Makefile) AC_OUTPUT smalltalk-3.2.5/README0000644000175000017500000000533412123404352011307 00000000000000 GNU Smalltalk is an implementation that closely follows the Smalltalk-80 language as described in the book `Smalltalk-80: the Language and its Implementation' by Adele Goldberg and David Robson. The Smalltalk programming language is an object oriented programming language. This means, for one thing, that when programming you are thinking of not only the data that an object contains, but also of the operations available on that object. The object's data representation capabilities and the operations available on the object are "inseparable"; the set of things that you can do with an object is defined precisely by the set of operations, which Smalltalk calls "methods", that are available for that object. You cannot even examine the contents of an object from the outside. To an outsider, the object is a black box that has some state and some operations available, but that's all you know. In the Smalltalk language, everything is an object. This includes numbers, executable procedures (methods), stack frames (called method contexts or block contexts), etc. Each object is an "instance" of a "class". A class can be thought of as a datatype and the set of functions that operate on that datatype. An instance is a particular variable of that datatype. When you want to perform an operation on an object, you send it a "message", and the object performs an operation that corresponds to that message. Unlike other Smalltalks (including Smalltalk-80), GNU Smalltalk emphasizes Smalltalk's rapid prototyping features rather than the graphical and easy-to-use nature of the programming environment (did you know that the first GUIs ran under Smalltalk?). The availability of a large body of system classes, once you learn them, makes it pretty easy to write complex programs which are usually a task for the so called "scripting languages". Therefore, even though we have a nice GUI environment including a class browser, the goal of the GNU Smalltalk project is currently to produce a complete system to be used to write your scripts in a clear, aesthetically pleasing, and philosophically appealing programming language. An example of what can be obtained with Smalltalk in this novel way can be found in the manual's class reference. That part of the manual is entirely generated by a Smalltalk program, starting from the source code for the system classes as distributed together with the system. Oh... of course ;-) GNU Smalltalk has bugs. And of course I like to hear from people who have something to say regarding it. So bug reports, suggestions, help, advices, source code contributions are all welcome. All you have to do is send mail to the GNU Smalltalk mailing list, at help-smalltalk@gnu.org. Answer is "almost" guaranteed. smalltalk-3.2.5/Doxyfile0000644000175000017500000012066512123404352012142 00000000000000# Doxyfile 1.3-rc2 # This file describes the settings to be used by the documentation system # doxygen (www.doxygen.org) for a project # # All text after a hash (#) is considered a comment and will be ignored # The format is: # TAG = value [value, ...] # For lists items can also be appended using: # TAG += value [value, ...] # Values that contain spaces should be placed between quotes (" ") #--------------------------------------------------------------------------- # General configuration options #--------------------------------------------------------------------------- # The PROJECT_NAME tag is a single word (or a sequence of words surrounded # by quotes) that should identify the project. PROJECT_NAME = "GNU Smalltalk" # The PROJECT_NUMBER tag can be used to enter a project or revision number. # This could be handy for archiving the generated documentation or # if some version control system is used. PROJECT_NUMBER = # The OUTPUT_DIRECTORY tag is used to specify the (relative or absolute) # base path where the generated documentation will be put. # If a relative path is entered, it will be relative to the location # where doxygen was started. If left blank the current directory will be used. OUTPUT_DIRECTORY = doxygen_docs # The OUTPUT_LANGUAGE tag is used to specify the language in which all # documentation generated by doxygen is written. Doxygen will use this # information to generate all constant output in the proper language. # The default language is English, other supported languages are: # Brazilian, Catalan, Chinese, Chinese-Traditional, Croatian, Czech, Danish, Dutch, # Finnish, French, German, Greek, Hungarian, Italian, Japanese, Japanese-en # (Japanese with english messages), Korean, Norwegian, Polish, Portuguese, # Romanian, Russian, Serbian, Slovak, Slovene, Spanish, Swedish and Ukrainian. OUTPUT_LANGUAGE = English # If the EXTRACT_ALL tag is set to YES doxygen will assume all entities in # documentation are documented, even if no documentation was available. # Private class members and static file members will be hidden unless # the EXTRACT_PRIVATE and EXTRACT_STATIC tags are set to YES EXTRACT_ALL = YES # If the EXTRACT_PRIVATE tag is set to YES all private members of a class # will be included in the documentation. EXTRACT_PRIVATE = NO # If the EXTRACT_STATIC tag is set to YES all static members of a file # will be included in the documentation. EXTRACT_STATIC = YES # If the EXTRACT_LOCAL_CLASSES tag is set to YES classes (and structs) # defined locally in source files will be included in the documentation. # If set to NO only classes defined in header files are included. EXTRACT_LOCAL_CLASSES = YES # If the HIDE_UNDOC_MEMBERS tag is set to YES, Doxygen will hide all # undocumented members of documented classes, files or namespaces. # If set to NO (the default) these members will be included in the # various overviews, but no documentation section is generated. # This option has no effect if EXTRACT_ALL is enabled. HIDE_UNDOC_MEMBERS = NO # If the HIDE_UNDOC_CLASSES tag is set to YES, Doxygen will hide all # undocumented classes that are normally visible in the class hierarchy. # If set to NO (the default) these class will be included in the various # overviews. This option has no effect if EXTRACT_ALL is enabled. HIDE_UNDOC_CLASSES = NO # If the HIDE_FRIEND_COMPOUNDS tag is set to YES, Doxygen will hide all # friend (class|struct|union) declarations. # If set to NO (the default) these declarations will be included in the # documentation. HIDE_FRIEND_COMPOUNDS = NO # If the HIDE_IN_BODY_DOCS tag is set to YES, Doxygen will hide any # documentation blocks found inside the body of a function. # If set to NO (the default) these blocks will be appended to the # function's detailed documentation block. HIDE_IN_BODY_DOCS = NO # If the BRIEF_MEMBER_DESC tag is set to YES (the default) Doxygen will # include brief member descriptions after the members that are listed in # the file and class documentation (similar to JavaDoc). # Set to NO to disable this. BRIEF_MEMBER_DESC = YES # If the REPEAT_BRIEF tag is set to YES (the default) Doxygen will prepend # the brief description of a member or function before the detailed description. # Note: if both HIDE_UNDOC_MEMBERS and BRIEF_MEMBER_DESC are set to NO, the # brief descriptions will be completely suppressed. REPEAT_BRIEF = YES # If the ALWAYS_DETAILED_SEC and REPEAT_BRIEF tags are both set to YES then # Doxygen will generate a detailed section even if there is only a brief # description. ALWAYS_DETAILED_SEC = NO # If the INLINE_INHERITED_MEMB tag is set to YES, doxygen will show all inherited # members of a class in the documentation of that class as if those members were # ordinary class members. Constructors, destructors and assignment operators of # the base classes will not be shown. INLINE_INHERITED_MEMB = NO # If the FULL_PATH_NAMES tag is set to YES then Doxygen will prepend the full # path before files name in the file list and in the header files. If set # to NO the shortest path that makes the file name unique will be used. FULL_PATH_NAMES = NO # If the FULL_PATH_NAMES tag is set to YES then the STRIP_FROM_PATH tag # can be used to strip a user defined part of the path. Stripping is # only done if one of the specified strings matches the left-hand part of # the path. It is allowed to use relative paths in the argument list. STRIP_FROM_PATH = # The INTERNAL_DOCS tag determines if documentation # that is typed after a \internal command is included. If the tag is set # to NO (the default) then the documentation will be excluded. # Set it to YES to include the internal documentation. INTERNAL_DOCS = NO # If the CASE_SENSE_NAMES tag is set to NO then Doxygen will only generate # file names in lower case letters. If set to YES upper case letters are also # allowed. This is useful if you have classes or files whose names only differ # in case and if your file system supports case sensitive file names. Windows # users are adviced to set this option to NO. CASE_SENSE_NAMES = NO # If the SHORT_NAMES tag is set to YES, doxygen will generate much shorter # (but less readable) file names. This can be useful is your file systems # doesn't support long names like on DOS, Mac, or CD-ROM. SHORT_NAMES = NO # If the HIDE_SCOPE_NAMES tag is set to NO (the default) then Doxygen # will show members with their full class and namespace scopes in the # documentation. If set to YES the scope will be hidden. HIDE_SCOPE_NAMES = NO # If the VERBATIM_HEADERS tag is set to YES (the default) then Doxygen # will generate a verbatim copy of the header file for each class for # which an include is specified. Set to NO to disable this. VERBATIM_HEADERS = YES # If the SHOW_INCLUDE_FILES tag is set to YES (the default) then Doxygen # will put list of the files that are included by a file in the documentation # of that file. SHOW_INCLUDE_FILES = YES # If the JAVADOC_AUTOBRIEF tag is set to YES then Doxygen # will interpret the first line (until the first dot) of a JavaDoc-style # comment as the brief description. If set to NO, the JavaDoc # comments will behave just like the Qt-style comments (thus requiring an # explict @brief command for a brief description. JAVADOC_AUTOBRIEF = NO # The MULTILINE_CPP_IS_BRIEF tag can be set to YES to make Doxygen # treat a multi-line C++ special comment block (i.e. a block of //! or /// # comments) as a brief description. This used to be the default behaviour. # The new default is to treat a multi-line C++ comment block as a detailed # description. Set this tag to YES if you prefer the old behaviour instead. MULTILINE_CPP_IS_BRIEF = NO # If the DETAILS_AT_TOP tag is set to YES then Doxygen # will output the detailed description near the top, like JavaDoc. # If set to NO, the detailed description appears after the member # documentation. DETAILS_AT_TOP = NO # If the INHERIT_DOCS tag is set to YES (the default) then an undocumented # member inherits the documentation from any documented member that it # reimplements. INHERIT_DOCS = YES # If the INLINE_INFO tag is set to YES (the default) then a tag [inline] # is inserted in the documentation for inline members. INLINE_INFO = YES # If the SORT_MEMBER_DOCS tag is set to YES (the default) then doxygen # will sort the (detailed) documentation of file and class members # alphabetically by member name. If set to NO the members will appear in # declaration order. SORT_MEMBER_DOCS = YES # If member grouping is used in the documentation and the DISTRIBUTE_GROUP_DOC # tag is set to YES, then doxygen will reuse the documentation of the first # member in the group (if any) for the other members of the group. By default # all members of a group must be documented explicitly. DISTRIBUTE_GROUP_DOC = NO # The TAB_SIZE tag can be used to set the number of spaces in a tab. # Doxygen uses this value to replace tabs by spaces in code fragments. TAB_SIZE = 8 # The GENERATE_TODOLIST tag can be used to enable (YES) or # disable (NO) the todo list. This list is created by putting \todo # commands in the documentation. GENERATE_TODOLIST = YES # The GENERATE_TESTLIST tag can be used to enable (YES) or # disable (NO) the test list. This list is created by putting \test # commands in the documentation. GENERATE_TESTLIST = YES # The GENERATE_BUGLIST tag can be used to enable (YES) or # disable (NO) the bug list. This list is created by putting \bug # commands in the documentation. GENERATE_BUGLIST = YES # The GENERATE_DEPRECATEDLIST tag can be used to enable (YES) or # disable (NO) the deprecated list. This list is created by putting # \deprecated commands in the documentation. GENERATE_DEPRECATEDLIST= YES # This tag can be used to specify a number of aliases that acts # as commands in the documentation. An alias has the form "name=value". # For example adding "sideeffect=\par Side Effects:\n" will allow you to # put the command \sideeffect (or @sideeffect) in the documentation, which # will result in a user defined paragraph with heading "Side Effects:". # You can put \n's in the value part of an alias to insert newlines. ALIASES = # The ENABLED_SECTIONS tag can be used to enable conditional # documentation sections, marked by \if sectionname ... \endif. ENABLED_SECTIONS = # The MAX_INITIALIZER_LINES tag determines the maximum number of lines # the initial value of a variable or define consist of for it to appear in # the documentation. If the initializer consists of more lines than specified # here it will be hidden. Use a value of 0 to hide initializers completely. # The appearance of the initializer of individual variables and defines in the # documentation can be controlled using \showinitializer or \hideinitializer # command in the documentation regardless of this setting. MAX_INITIALIZER_LINES = 30 # Set the OPTIMIZE_OUTPUT_FOR_C tag to YES if your project consists of C sources # only. Doxygen will then generate output that is more tailored for C. # For instance some of the names that are used will be different. The list # of all members will be omitted, etc. OPTIMIZE_OUTPUT_FOR_C = YES # Set the OPTIMIZE_OUTPUT_JAVA tag to YES if your project consists of Java sources # only. Doxygen will then generate output that is more tailored for Java. # For instance namespaces will be presented as packages, qualified scopes # will look different, etc. OPTIMIZE_OUTPUT_JAVA = NO # Set the SHOW_USED_FILES tag to NO to disable the list of files generated # at the bottom of the documentation of classes and structs. If set to YES the # list will mention the files that were used to generate the documentation. SHOW_USED_FILES = YES #--------------------------------------------------------------------------- # configuration options related to warning and progress messages #--------------------------------------------------------------------------- # The QUIET tag can be used to turn on/off the messages that are generated # by doxygen. Possible values are YES and NO. If left blank NO is used. QUIET = NO # The WARNINGS tag can be used to turn on/off the warning messages that are # generated by doxygen. Possible values are YES and NO. If left blank # NO is used. WARNINGS = YES # If WARN_IF_UNDOCUMENTED is set to YES, then doxygen will generate warnings # for undocumented members. If EXTRACT_ALL is set to YES then this flag will # automatically be disabled. WARN_IF_UNDOCUMENTED = YES # If WARN_IF_DOC_ERROR is set to YES, doxygen will generate warnings for # potential errors in the documentation, such as not documenting some # parameters in a documented function, or documenting parameters that # don't exist or using markup commands wrongly. WARN_IF_DOC_ERROR = YES # The WARN_FORMAT tag determines the format of the warning messages that # doxygen can produce. The string should contain the $file, $line, and $text # tags, which will be replaced by the file and line number from which the # warning originated and the warning text. WARN_FORMAT = "$file:$line: $text" # The WARN_LOGFILE tag can be used to specify a file to which warning # and error messages should be written. If left blank the output is written # to stderr. WARN_LOGFILE = #--------------------------------------------------------------------------- # configuration options related to the input files #--------------------------------------------------------------------------- # The INPUT tag can be used to specify the files and/or directories that contain # documented source files. You may enter file names like "myfile.cpp" or # directories like "/usr/src/myproject". Separate the files or directories # with spaces. INPUT = lib-src libgst . # If the value of the INPUT tag contains directories, you can use the # FILE_PATTERNS tag to specify one or more wildcard pattern (like *.cpp # and *.h) to filter out the source-files in the directories. If left # blank the following patterns are tested: # *.c *.cc *.cxx *.cpp *.c++ *.java *.ii *.ixx *.ipp *.i++ *.inl *.h *.hh *.hxx *.hpp # *.h++ *.idl *.odl FILE_PATTERNS = *.c *.inl *.h # The RECURSIVE tag can be used to turn specify whether or not subdirectories # should be searched for input files as well. Possible values are YES and NO. # If left blank NO is used. RECURSIVE = NO # The EXCLUDE tag can be used to specify files and/or directories that should # excluded from the INPUT source files. This way you can easily exclude a # subdirectory from a directory tree whose root is specified with the INPUT tag. EXCLUDE = # The EXCLUDE_SYMLINKS tag can be used select whether or not files or directories # that are symbolic links (a Unix filesystem feature) are excluded from the input. EXCLUDE_SYMLINKS = NO # If the value of the INPUT tag contains directories, you can use the # EXCLUDE_PATTERNS tag to specify one or more wildcard patterns to exclude # certain files from those directories. EXCLUDE_PATTERNS = # The EXAMPLE_PATH tag can be used to specify one or more files or # directories that contain example code fragments that are included (see # the \include command). EXAMPLE_PATH = # If the value of the EXAMPLE_PATH tag contains directories, you can use the # EXAMPLE_PATTERNS tag to specify one or more wildcard pattern (like *.cpp # and *.h) to filter out the source-files in the directories. If left # blank all files are included. EXAMPLE_PATTERNS = # If the EXAMPLE_RECURSIVE tag is set to YES then subdirectories will be # searched for input files to be used with the \include or \dontinclude # commands irrespective of the value of the RECURSIVE tag. # Possible values are YES and NO. If left blank NO is used. EXAMPLE_RECURSIVE = NO # The IMAGE_PATH tag can be used to specify one or more files or # directories that contain image that are included in the documentation (see # the \image command). IMAGE_PATH = # The INPUT_FILTER tag can be used to specify a program that doxygen should # invoke to filter for each input file. Doxygen will invoke the filter program # by executing (via popen()) the command , where # is the value of the INPUT_FILTER tag, and is the name of an # input file. Doxygen will then use the output that the filter program writes # to standard output. INPUT_FILTER = # If the FILTER_SOURCE_FILES tag is set to YES, the input filter (if set using # INPUT_FILTER) will be used to filter the input files when producing source # files to browse (i.e. when SOURCE_BROWSER is set to YES). FILTER_SOURCE_FILES = NO #--------------------------------------------------------------------------- # configuration options related to source browsing #--------------------------------------------------------------------------- # If the SOURCE_BROWSER tag is set to YES then a list of source files will # be generated. Documented entities will be cross-referenced with these sources. SOURCE_BROWSER = YES # Setting the INLINE_SOURCES tag to YES will include the body # of functions and classes directly in the documentation. INLINE_SOURCES = NO # Setting the STRIP_CODE_COMMENTS tag to YES (the default) will instruct # doxygen to hide any special comment blocks from generated source code # fragments. Normal C and C++ comments will always remain visible. STRIP_CODE_COMMENTS = NO # If the REFERENCED_BY_RELATION tag is set to YES (the default) # then for each documented function all documented # functions referencing it will be listed. REFERENCED_BY_RELATION = YES # If the REFERENCES_RELATION tag is set to YES (the default) # then for each documented function all documented entities # called/used by that function will be listed. REFERENCES_RELATION = YES #--------------------------------------------------------------------------- # configuration options related to the alphabetical class index #--------------------------------------------------------------------------- # If the ALPHABETICAL_INDEX tag is set to YES, an alphabetical index # of all compounds will be generated. Enable this if the project # contains a lot of classes, structs, unions or interfaces. ALPHABETICAL_INDEX = NO # If the alphabetical index is enabled (see ALPHABETICAL_INDEX) then # the COLS_IN_ALPHA_INDEX tag can be used to specify the number of columns # in which this list will be split (can be a number in the range [1..20]) COLS_IN_ALPHA_INDEX = 5 # In case all classes in a project start with a common prefix, all # classes will be put under the same header in the alphabetical index. # The IGNORE_PREFIX tag can be used to specify one or more prefixes that # should be ignored while generating the index headers. IGNORE_PREFIX = #--------------------------------------------------------------------------- # configuration options related to the HTML output #--------------------------------------------------------------------------- # If the GENERATE_HTML tag is set to YES (the default) Doxygen will # generate HTML output. GENERATE_HTML = YES # The HTML_OUTPUT tag is used to specify where the HTML docs will be put. # If a relative path is entered the value of OUTPUT_DIRECTORY will be # put in front of it. If left blank `html' will be used as the default path. HTML_OUTPUT = html # The HTML_FILE_EXTENSION tag can be used to specify the file extension for # each generated HTML page (for example: .htm,.php,.asp). If it is left blank # doxygen will generate files with .html extension. HTML_FILE_EXTENSION = .html # The HTML_HEADER tag can be used to specify a personal HTML header for # each generated HTML page. If it is left blank doxygen will generate a # standard header. HTML_HEADER = # The HTML_FOOTER tag can be used to specify a personal HTML footer for # each generated HTML page. If it is left blank doxygen will generate a # standard footer. HTML_FOOTER = # The HTML_STYLESHEET tag can be used to specify a user defined cascading # style sheet that is used by each HTML page. It can be used to # fine-tune the look of the HTML output. If the tag is left blank doxygen # will generate a default style sheet HTML_STYLESHEET = # If the HTML_ALIGN_MEMBERS tag is set to YES, the members of classes, # files or namespaces will be aligned in HTML using tables. If set to # NO a bullet list will be used. HTML_ALIGN_MEMBERS = YES # If the GENERATE_HTMLHELP tag is set to YES, additional index files # will be generated that can be used as input for tools like the # Microsoft HTML help workshop to generate a compressed HTML help file (.chm) # of the generated HTML documentation. GENERATE_HTMLHELP = NO # If the GENERATE_HTMLHELP tag is set to YES, the CHM_FILE tag can # be used to specify the file name of the resulting .chm file. You # can add a path in front of the file if the result should not be # written to the html output dir. CHM_FILE = # If the GENERATE_HTMLHELP tag is set to YES, the HHC_LOCATION tag can # be used to specify the location (absolute path including file name) of # the HTML help compiler (hhc.exe). If non empty doxygen will try to run # the html help compiler on the generated index.hhp. HHC_LOCATION = # If the GENERATE_HTMLHELP tag is set to YES, the GENERATE_CHI flag # controls if a separate .chi index file is generated (YES) or that # it should be included in the master .chm file (NO). GENERATE_CHI = NO # If the GENERATE_HTMLHELP tag is set to YES, the BINARY_TOC flag # controls whether a binary table of contents is generated (YES) or a # normal table of contents (NO) in the .chm file. BINARY_TOC = NO # The TOC_EXPAND flag can be set to YES to add extra items for group members # to the contents of the Html help documentation and to the tree view. TOC_EXPAND = NO # The DISABLE_INDEX tag can be used to turn on/off the condensed index at # top of each HTML page. The value NO (the default) enables the index and # the value YES disables it. DISABLE_INDEX = NO # This tag can be used to set the number of enum values (range [1..20]) # that doxygen will group on one line in the generated HTML documentation. ENUM_VALUES_PER_LINE = 4 # If the GENERATE_TREEVIEW tag is set to YES, a side panel will be # generated containing a tree-like index structure (just like the one that # is generated for HTML Help). For this to work a browser that supports # JavaScript and frames is required (for instance Mozilla, Netscape 4.0+, # or Internet explorer 4.0+). Note that for large projects the tree generation # can take a very long time. In such cases it is better to disable this feature. # Windows users are probably better off using the HTML help feature. GENERATE_TREEVIEW = YES # If the treeview is enabled (see GENERATE_TREEVIEW) then this tag can be # used to set the initial width (in pixels) of the frame in which the tree # is shown. TREEVIEW_WIDTH = 250 #--------------------------------------------------------------------------- # configuration options related to the LaTeX output #--------------------------------------------------------------------------- # If the GENERATE_LATEX tag is set to YES (the default) Doxygen will # generate Latex output. GENERATE_LATEX = NO # The LATEX_OUTPUT tag is used to specify where the LaTeX docs will be put. # If a relative path is entered the value of OUTPUT_DIRECTORY will be # put in front of it. If left blank `latex' will be used as the default path. LATEX_OUTPUT = latex # The LATEX_CMD_NAME tag can be used to specify the LaTeX command name to be # invoked. If left blank `latex' will be used as the default command name. LATEX_CMD_NAME = latex # The MAKEINDEX_CMD_NAME tag can be used to specify the command name to # generate index for LaTeX. If left blank `makeindex' will be used as the # default command name. MAKEINDEX_CMD_NAME = makeindex # If the COMPACT_LATEX tag is set to YES Doxygen generates more compact # LaTeX documents. This may be useful for small projects and may help to # save some trees in general. COMPACT_LATEX = NO # The PAPER_TYPE tag can be used to set the paper type that is used # by the printer. Possible values are: a4, a4wide, letter, legal and # executive. If left blank a4wide will be used. PAPER_TYPE = a4wide # The EXTRA_PACKAGES tag can be to specify one or more names of LaTeX # packages that should be included in the LaTeX output. EXTRA_PACKAGES = # The LATEX_HEADER tag can be used to specify a personal LaTeX header for # the generated latex document. The header should contain everything until # the first chapter. If it is left blank doxygen will generate a # standard header. Notice: only use this tag if you know what you are doing! LATEX_HEADER = # If the PDF_HYPERLINKS tag is set to YES, the LaTeX that is generated # is prepared for conversion to pdf (using ps2pdf). The pdf file will # contain links (just like the HTML output) instead of page references # This makes the output suitable for online browsing using a pdf viewer. PDF_HYPERLINKS = NO # If the USE_PDFLATEX tag is set to YES, pdflatex will be used instead of # plain latex in the generated Makefile. Set this option to YES to get a # higher quality PDF documentation. USE_PDFLATEX = NO # If the LATEX_BATCHMODE tag is set to YES, doxygen will add the \\batchmode. # command to the generated LaTeX files. This will instruct LaTeX to keep # running if errors occur, instead of asking the user for help. # This option is also used when generating formulas in HTML. LATEX_BATCHMODE = NO #--------------------------------------------------------------------------- # configuration options related to the RTF output #--------------------------------------------------------------------------- # If the GENERATE_RTF tag is set to YES Doxygen will generate RTF output # The RTF output is optimised for Word 97 and may not look very pretty with # other RTF readers or editors. GENERATE_RTF = NO # The RTF_OUTPUT tag is used to specify where the RTF docs will be put. # If a relative path is entered the value of OUTPUT_DIRECTORY will be # put in front of it. If left blank `rtf' will be used as the default path. RTF_OUTPUT = rtf # If the COMPACT_RTF tag is set to YES Doxygen generates more compact # RTF documents. This may be useful for small projects and may help to # save some trees in general. COMPACT_RTF = NO # If the RTF_HYPERLINKS tag is set to YES, the RTF that is generated # will contain hyperlink fields. The RTF file will # contain links (just like the HTML output) instead of page references. # This makes the output suitable for online browsing using WORD or other # programs which support those fields. # Note: wordpad (write) and others do not support links. RTF_HYPERLINKS = NO # Load stylesheet definitions from file. Syntax is similar to doxygen's # config file, i.e. a series of assigments. You only have to provide # replacements, missing definitions are set to their default value. RTF_STYLESHEET_FILE = # Set optional variables used in the generation of an rtf document. # Syntax is similar to doxygen's config file. RTF_EXTENSIONS_FILE = #--------------------------------------------------------------------------- # configuration options related to the man page output #--------------------------------------------------------------------------- # If the GENERATE_MAN tag is set to YES (the default) Doxygen will # generate man pages GENERATE_MAN = NO # The MAN_OUTPUT tag is used to specify where the man pages will be put. # If a relative path is entered the value of OUTPUT_DIRECTORY will be # put in front of it. If left blank `man' will be used as the default path. MAN_OUTPUT = man # The MAN_EXTENSION tag determines the extension that is added to # the generated man pages (default is the subroutine's section .3) MAN_EXTENSION = .3 # If the MAN_LINKS tag is set to YES and Doxygen generates man output, # then it will generate one additional man file for each entity # documented in the real man page(s). These additional files # only source the real man page, but without them the man command # would be unable to find the correct page. The default is NO. MAN_LINKS = NO #--------------------------------------------------------------------------- # configuration options related to the XML output #--------------------------------------------------------------------------- # If the GENERATE_XML tag is set to YES Doxygen will # generate an XML file that captures the structure of # the code including all documentation. Note that this # feature is still experimental and incomplete at the # moment. GENERATE_XML = NO # The XML_SCHEMA tag can be used to specify an XML schema, # which can be used by a validating XML parser to check the # syntax of the XML files. XML_SCHEMA = # The XML_DTD tag can be used to specify an XML DTD, # which can be used by a validating XML parser to check the # syntax of the XML files. XML_DTD = #--------------------------------------------------------------------------- # configuration options for the AutoGen Definitions output #--------------------------------------------------------------------------- # If the GENERATE_AUTOGEN_DEF tag is set to YES Doxygen will # generate an AutoGen Definitions (see autogen.sf.net) file # that captures the structure of the code including all # documentation. Note that this feature is still experimental # and incomplete at the moment. GENERATE_AUTOGEN_DEF = NO #--------------------------------------------------------------------------- # configuration options related to the Perl module output #--------------------------------------------------------------------------- # If the GENERATE_PERLMOD tag is set to YES Doxygen will # generate a Perl module file that captures the structure of # the code including all documentation. Note that this # feature is still experimental and incomplete at the # moment. GENERATE_PERLMOD = NO # If the PERLMOD_LATEX tag is set to YES Doxygen will generate # the necessary Makefile rules, Perl scripts and LaTeX code to be able # to generate PDF and DVI output from the Perl module output. PERLMOD_LATEX = NO # If the PERLMOD_PRETTY tag is set to YES the Perl module output will be # nicely formatted so it can be parsed by a human reader. This is useful # if you want to understand what is going on. On the other hand, if this # tag is set to NO the size of the Perl module output will be much smaller # and Perl will parse it just the same. PERLMOD_PRETTY = YES # The names of the make variables in the generated doxyrules.make file # are prefixed with the string contained in PERLMOD_MAKEVAR_PREFIX. # This is useful so different doxyrules.make files included by the same # Makefile don't overwrite each other's variables. PERLMOD_MAKEVAR_PREFIX = #--------------------------------------------------------------------------- # Configuration options related to the preprocessor #--------------------------------------------------------------------------- # If the ENABLE_PREPROCESSING tag is set to YES (the default) Doxygen will # evaluate all C-preprocessor directives found in the sources and include # files. ENABLE_PREPROCESSING = YES # If the MACRO_EXPANSION tag is set to YES Doxygen will expand all macro # names in the source code. If set to NO (the default) only conditional # compilation will be performed. Macro expansion can be done in a controlled # way by setting EXPAND_ONLY_PREDEF to YES. MACRO_EXPANSION = NO # If the EXPAND_ONLY_PREDEF and MACRO_EXPANSION tags are both set to YES # then the macro expansion is limited to the macros specified with the # PREDEFINED and EXPAND_AS_PREDEFINED tags. EXPAND_ONLY_PREDEF = NO # If the SEARCH_INCLUDES tag is set to YES (the default) the includes files # in the INCLUDE_PATH (see below) will be search if a #include is found. SEARCH_INCLUDES = YES # The INCLUDE_PATH tag can be used to specify one or more directories that # contain include files that are not input files but should be processed by # the preprocessor. INCLUDE_PATH = # You can use the INCLUDE_FILE_PATTERNS tag to specify one or more wildcard # patterns (like *.h and *.hpp) to filter out the header-files in the # directories. If left blank, the patterns specified with FILE_PATTERNS will # be used. INCLUDE_FILE_PATTERNS = # The PREDEFINED tag can be used to specify one or more macro names that # are defined before the preprocessor is started (similar to the -D option of # gcc). The argument of the tag is a list of macros of the form: name # or name=definition (no spaces). If the definition and the = are # omitted =1 is assumed. PREDEFINED = # If the MACRO_EXPANSION and EXPAND_ONLY_PREDEF tags are set to YES then # this tag can be used to specify a list of macro names that should be expanded. # The macro definition that is found in the sources will be used. # Use the PREDEFINED tag if you want to use a different macro definition. EXPAND_AS_DEFINED = # If the SKIP_FUNCTION_MACROS tag is set to YES (the default) then # doxygen's preprocessor will remove all function-like macros that are alone # on a line, have an all uppercase name, and do not end with a semicolon. Such # function macros are typically used for boiler-plate code, and will confuse the # parser if not removed. SKIP_FUNCTION_MACROS = YES #--------------------------------------------------------------------------- # Configuration::addtions related to external references #--------------------------------------------------------------------------- # The TAGFILES tag can be used to specify one or more tagfiles. TAGFILES = # When a file name is specified after GENERATE_TAGFILE, doxygen will create # a tag file that is based on the input files it reads. GENERATE_TAGFILE = # If the ALLEXTERNALS tag is set to YES all external classes will be listed # in the class index. If set to NO only the inherited external classes # will be listed. ALLEXTERNALS = NO # If the EXTERNAL_GROUPS tag is set to YES all external groups will be listed # in the modules index. If set to NO, only the current project's groups will # be listed. EXTERNAL_GROUPS = YES # The PERL_PATH should be the absolute path and name of the perl script # interpreter (i.e. the result of `which perl'). PERL_PATH = /usr/bin/perl #--------------------------------------------------------------------------- # Configuration options related to the dot tool #--------------------------------------------------------------------------- # If the CLASS_DIAGRAMS tag is set to YES (the default) Doxygen will # generate a inheritance diagram (in Html, RTF and LaTeX) for classes with base or # super classes. Setting the tag to NO turns the diagrams off. Note that this # option is superceded by the HAVE_DOT option below. This is only a fallback. It is # recommended to install and use dot, since it yield more powerful graphs. CLASS_DIAGRAMS = YES # If set to YES, the inheritance and collaboration graphs will hide # inheritance and usage relations if the target is undocumented # or is not a class. HIDE_UNDOC_RELATIONS = YES # If you set the HAVE_DOT tag to YES then doxygen will assume the dot tool is # available from the path. This tool is part of Graphviz, a graph visualization # toolkit from AT&T and Lucent Bell Labs. The other options in this section # have no effect if this option is set to NO (the default) HAVE_DOT = NO # If the CLASS_GRAPH and HAVE_DOT tags are set to YES then doxygen # will generate a graph for each documented class showing the direct and # indirect inheritance relations. Setting this tag to YES will force the # the CLASS_DIAGRAMS tag to NO. CLASS_GRAPH = YES # If the COLLABORATION_GRAPH and HAVE_DOT tags are set to YES then doxygen # will generate a graph for each documented class showing the direct and # indirect implementation dependencies (inheritance, containment, and # class references variables) of the class with other documented classes. COLLABORATION_GRAPH = YES # If set to YES, the inheritance and collaboration graphs will show the # relations between templates and their instances. TEMPLATE_RELATIONS = YES # If the ENABLE_PREPROCESSING, SEARCH_INCLUDES, INCLUDE_GRAPH, and HAVE_DOT # tags are set to YES then doxygen will generate a graph for each documented # file showing the direct and indirect include dependencies of the file with # other documented files. INCLUDE_GRAPH = YES # If the ENABLE_PREPROCESSING, SEARCH_INCLUDES, INCLUDED_BY_GRAPH, and # HAVE_DOT tags are set to YES then doxygen will generate a graph for each # documented header file showing the documented files that directly or # indirectly include this file. INCLUDED_BY_GRAPH = YES # If the GRAPHICAL_HIERARCHY and HAVE_DOT tags are set to YES then doxygen # will graphical hierarchy of all classes instead of a textual one. GRAPHICAL_HIERARCHY = YES # The DOT_IMAGE_FORMAT tag can be used to set the image format of the images # generated by dot. Possible values are png, jpg, or gif # If left blank png will be used. DOT_IMAGE_FORMAT = png # The tag DOT_PATH can be used to specify the path where the dot tool can be # found. If left blank, it is assumed the dot tool can be found on the path. DOT_PATH = # The DOTFILE_DIRS tag can be used to specify one or more directories that # contain dot files that are included in the documentation (see the # \dotfile command). DOTFILE_DIRS = # The MAX_DOT_GRAPH_WIDTH tag can be used to set the maximum allowed width # (in pixels) of the graphs generated by dot. If a graph becomes larger than # this value, doxygen will try to truncate the graph, so that it fits within # the specified constraint. Beware that most browsers cannot cope with very # large images. MAX_DOT_GRAPH_WIDTH = 1024 # The MAX_DOT_GRAPH_HEIGHT tag can be used to set the maximum allows height # (in pixels) of the graphs generated by dot. If a graph becomes larger than # this value, doxygen will try to truncate the graph, so that it fits within # the specified constraint. Beware that most browsers cannot cope with very # large images. MAX_DOT_GRAPH_HEIGHT = 1024 # If the GENERATE_LEGEND tag is set to YES (the default) Doxygen will # generate a legend page explaining the meaning of the various boxes and # arrows in the dot generated graphs. GENERATE_LEGEND = YES # If the DOT_CLEANUP tag is set to YES (the default) Doxygen will # remove the intermedate dot files that are used to generate # the various graphs. DOT_CLEANUP = YES #--------------------------------------------------------------------------- # Configuration::addtions related to the search engine #--------------------------------------------------------------------------- # The SEARCHENGINE tag specifies whether or not a search engine should be # used. If set to NO the values of all tags below this one will be ignored. SEARCHENGINE = NO # The CGI_NAME tag should be the name of the CGI script that # starts the search engine (doxysearch) with the correct parameters. # A script with this name will be generated by doxygen. CGI_NAME = search.cgi # The CGI_URL tag should be the absolute URL to the directory where the # cgi binaries are located. See the documentation of your http daemon for # details. CGI_URL = # The DOC_URL tag should be the absolute URL to the directory where the # documentation is located. If left blank the absolute path to the # documentation, with file:// prepended to it, will be used. DOC_URL = # The DOC_ABSPATH tag should be the absolute path to the directory where the # documentation is located. If left blank the directory on the local machine # will be used. DOC_ABSPATH = # The BIN_ABSPATH tag must point to the directory where the doxysearch binary # is installed. BIN_ABSPATH = /usr/local/bin/ # The EXT_DOC_PATHS tag can be used to specify one or more paths to # documentation generated for other projects. This allows doxysearch to search # the documentation for these projects as well. EXT_DOC_PATHS = smalltalk-3.2.5/libffi/0000755000175000017500000000000012130456004011734 500000000000000smalltalk-3.2.5/libffi/configure0000755000175000017500000157633712130455522013615 00000000000000#! /bin/sh # Guess values for system-dependent variables and create Makefiles. # Generated by GNU Autoconf 2.69 for libffi 3.0.9. # # Report bugs to . # # # Copyright (C) 1992-1996, 1998-2012 Free Software Foundation, Inc. # # # This configure script is free software; the Free Software Foundation # gives unlimited permission to copy, distribute and modify it. ## -------------------- ## ## M4sh Initialization. ## ## -------------------- ## # Be more Bourne compatible DUALCASE=1; export DUALCASE # for MKS sh if test -n "${ZSH_VERSION+set}" && (emulate sh) >/dev/null 2>&1; then : emulate sh NULLCMD=: # Pre-4.2 versions of Zsh do word splitting on ${1+"$@"}, which # is contrary to our usage. Disable this feature. alias -g '${1+"$@"}'='"$@"' setopt NO_GLOB_SUBST else case `(set -o) 2>/dev/null` in #( *posix*) : set -o posix ;; #( *) : ;; esac fi as_nl=' ' export as_nl # Printing a long string crashes Solaris 7 /usr/bin/printf. as_echo='\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\' as_echo=$as_echo$as_echo$as_echo$as_echo$as_echo as_echo=$as_echo$as_echo$as_echo$as_echo$as_echo$as_echo # Prefer a ksh shell builtin over an external printf program on Solaris, # but without wasting forks for bash or zsh. if test -z "$BASH_VERSION$ZSH_VERSION" \ && (test "X`print -r -- $as_echo`" = "X$as_echo") 2>/dev/null; then as_echo='print -r --' as_echo_n='print -rn --' elif (test "X`printf %s $as_echo`" = "X$as_echo") 2>/dev/null; then as_echo='printf %s\n' as_echo_n='printf %s' else if test "X`(/usr/ucb/echo -n -n $as_echo) 2>/dev/null`" = "X-n $as_echo"; then as_echo_body='eval /usr/ucb/echo -n "$1$as_nl"' as_echo_n='/usr/ucb/echo -n' else as_echo_body='eval expr "X$1" : "X\\(.*\\)"' as_echo_n_body='eval arg=$1; case $arg in #( *"$as_nl"*) expr "X$arg" : "X\\(.*\\)$as_nl"; arg=`expr "X$arg" : ".*$as_nl\\(.*\\)"`;; esac; expr "X$arg" : "X\\(.*\\)" | tr -d "$as_nl" ' export as_echo_n_body as_echo_n='sh -c $as_echo_n_body as_echo' fi export as_echo_body as_echo='sh -c $as_echo_body as_echo' fi # The user is always right. if test "${PATH_SEPARATOR+set}" != set; then PATH_SEPARATOR=: (PATH='/bin;/bin'; FPATH=$PATH; sh -c :) >/dev/null 2>&1 && { (PATH='/bin:/bin'; FPATH=$PATH; sh -c :) >/dev/null 2>&1 || PATH_SEPARATOR=';' } fi # IFS # We need space, tab and new line, in precisely that order. Quoting is # there to prevent editors from complaining about space-tab. # (If _AS_PATH_WALK were called with IFS unset, it would disable word # splitting by setting IFS to empty value.) IFS=" "" $as_nl" # Find who we are. Look in the path if we contain no directory separator. as_myself= case $0 in #(( *[\\/]* ) as_myself=$0 ;; *) as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. test -r "$as_dir/$0" && as_myself=$as_dir/$0 && break done IFS=$as_save_IFS ;; esac # We did not find ourselves, most probably we were run as `sh COMMAND' # in which case we are not to be found in the path. if test "x$as_myself" = x; then as_myself=$0 fi if test ! -f "$as_myself"; then $as_echo "$as_myself: error: cannot find myself; rerun with an absolute file name" >&2 exit 1 fi # Unset variables that we do not need and which cause bugs (e.g. in # pre-3.0 UWIN ksh). But do not cause bugs in bash 2.01; the "|| exit 1" # suppresses any "Segmentation fault" message there. '((' could # trigger a bug in pdksh 5.2.14. for as_var in BASH_ENV ENV MAIL MAILPATH do eval test x\${$as_var+set} = xset \ && ( (unset $as_var) || exit 1) >/dev/null 2>&1 && unset $as_var || : done PS1='$ ' PS2='> ' PS4='+ ' # NLS nuisances. LC_ALL=C export LC_ALL LANGUAGE=C export LANGUAGE # CDPATH. (unset CDPATH) >/dev/null 2>&1 && unset CDPATH # Use a proper internal environment variable to ensure we don't fall # into an infinite loop, continuously re-executing ourselves. if test x"${_as_can_reexec}" != xno && test "x$CONFIG_SHELL" != x; then _as_can_reexec=no; export _as_can_reexec; # We cannot yet assume a decent shell, so we have to provide a # neutralization value for shells without unset; and this also # works around shells that cannot unset nonexistent variables. # Preserve -v and -x to the replacement shell. BASH_ENV=/dev/null ENV=/dev/null (unset BASH_ENV) >/dev/null 2>&1 && unset BASH_ENV ENV case $- in # (((( *v*x* | *x*v* ) as_opts=-vx ;; *v* ) as_opts=-v ;; *x* ) as_opts=-x ;; * ) as_opts= ;; esac exec $CONFIG_SHELL $as_opts "$as_myself" ${1+"$@"} # Admittedly, this is quite paranoid, since all the known shells bail # out after a failed `exec'. $as_echo "$0: could not re-execute with $CONFIG_SHELL" >&2 as_fn_exit 255 fi # We don't want this to propagate to other subprocesses. { _as_can_reexec=; unset _as_can_reexec;} if test "x$CONFIG_SHELL" = x; then as_bourne_compatible="if test -n \"\${ZSH_VERSION+set}\" && (emulate sh) >/dev/null 2>&1; then : emulate sh NULLCMD=: # Pre-4.2 versions of Zsh do word splitting on \${1+\"\$@\"}, which # is contrary to our usage. Disable this feature. alias -g '\${1+\"\$@\"}'='\"\$@\"' setopt NO_GLOB_SUBST else case \`(set -o) 2>/dev/null\` in #( *posix*) : set -o posix ;; #( *) : ;; esac fi " as_required="as_fn_return () { (exit \$1); } as_fn_success () { as_fn_return 0; } as_fn_failure () { as_fn_return 1; } as_fn_ret_success () { return 0; } as_fn_ret_failure () { return 1; } exitcode=0 as_fn_success || { exitcode=1; echo as_fn_success failed.; } as_fn_failure && { exitcode=1; echo as_fn_failure succeeded.; } as_fn_ret_success || { exitcode=1; echo as_fn_ret_success failed.; } as_fn_ret_failure && { exitcode=1; echo as_fn_ret_failure succeeded.; } if ( set x; as_fn_ret_success y && test x = \"\$1\" ); then : else exitcode=1; echo positional parameters were not saved. fi test x\$exitcode = x0 || exit 1 test -x / || exit 1" as_suggested=" as_lineno_1=";as_suggested=$as_suggested$LINENO;as_suggested=$as_suggested" as_lineno_1a=\$LINENO as_lineno_2=";as_suggested=$as_suggested$LINENO;as_suggested=$as_suggested" as_lineno_2a=\$LINENO eval 'test \"x\$as_lineno_1'\$as_run'\" != \"x\$as_lineno_2'\$as_run'\" && test \"x\`expr \$as_lineno_1'\$as_run' + 1\`\" = \"x\$as_lineno_2'\$as_run'\"' || exit 1 test -n \"\${ZSH_VERSION+set}\${BASH_VERSION+set}\" || ( ECHO='\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\' ECHO=\$ECHO\$ECHO\$ECHO\$ECHO\$ECHO ECHO=\$ECHO\$ECHO\$ECHO\$ECHO\$ECHO\$ECHO PATH=/empty FPATH=/empty; export PATH FPATH test \"X\`printf %s \$ECHO\`\" = \"X\$ECHO\" \\ || test \"X\`print -r -- \$ECHO\`\" = \"X\$ECHO\" ) || exit 1 test \$(( 1 + 1 )) = 2 || exit 1" if (eval "$as_required") 2>/dev/null; then : as_have_required=yes else as_have_required=no fi if test x$as_have_required = xyes && (eval "$as_suggested") 2>/dev/null; then : else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR as_found=false for as_dir in /bin$PATH_SEPARATOR/usr/bin$PATH_SEPARATOR$PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. as_found=: case $as_dir in #( /*) for as_base in sh bash ksh sh5; do # Try only shells that exist, to save several forks. as_shell=$as_dir/$as_base if { test -f "$as_shell" || test -f "$as_shell.exe"; } && { $as_echo "$as_bourne_compatible""$as_required" | as_run=a "$as_shell"; } 2>/dev/null; then : CONFIG_SHELL=$as_shell as_have_required=yes if { $as_echo "$as_bourne_compatible""$as_suggested" | as_run=a "$as_shell"; } 2>/dev/null; then : break 2 fi fi done;; esac as_found=false done $as_found || { if { test -f "$SHELL" || test -f "$SHELL.exe"; } && { $as_echo "$as_bourne_compatible""$as_required" | as_run=a "$SHELL"; } 2>/dev/null; then : CONFIG_SHELL=$SHELL as_have_required=yes fi; } IFS=$as_save_IFS if test "x$CONFIG_SHELL" != x; then : export CONFIG_SHELL # We cannot yet assume a decent shell, so we have to provide a # neutralization value for shells without unset; and this also # works around shells that cannot unset nonexistent variables. # Preserve -v and -x to the replacement shell. BASH_ENV=/dev/null ENV=/dev/null (unset BASH_ENV) >/dev/null 2>&1 && unset BASH_ENV ENV case $- in # (((( *v*x* | *x*v* ) as_opts=-vx ;; *v* ) as_opts=-v ;; *x* ) as_opts=-x ;; * ) as_opts= ;; esac exec $CONFIG_SHELL $as_opts "$as_myself" ${1+"$@"} # Admittedly, this is quite paranoid, since all the known shells bail # out after a failed `exec'. $as_echo "$0: could not re-execute with $CONFIG_SHELL" >&2 exit 255 fi if test x$as_have_required = xno; then : $as_echo "$0: This script requires a shell more modern than all" $as_echo "$0: the shells that I found on your system." if test x${ZSH_VERSION+set} = xset ; then $as_echo "$0: In particular, zsh $ZSH_VERSION has bugs and should" $as_echo "$0: be upgraded to zsh 4.3.4 or later." else $as_echo "$0: Please tell bug-autoconf@gnu.org and $0: http://gcc.gnu.org/bugs.html about your system, $0: including any error possibly output before this $0: message. Then install a modern shell, or manually run $0: the script under such a shell if you do have one." fi exit 1 fi fi fi SHELL=${CONFIG_SHELL-/bin/sh} export SHELL # Unset more variables known to interfere with behavior of common tools. CLICOLOR_FORCE= GREP_OPTIONS= unset CLICOLOR_FORCE GREP_OPTIONS ## --------------------- ## ## M4sh Shell Functions. ## ## --------------------- ## # as_fn_unset VAR # --------------- # Portably unset VAR. as_fn_unset () { { eval $1=; unset $1;} } as_unset=as_fn_unset # as_fn_set_status STATUS # ----------------------- # Set $? to STATUS, without forking. as_fn_set_status () { return $1 } # as_fn_set_status # as_fn_exit STATUS # ----------------- # Exit the shell with STATUS, even in a "trap 0" or "set -e" context. as_fn_exit () { set +e as_fn_set_status $1 exit $1 } # as_fn_exit # as_fn_mkdir_p # ------------- # Create "$as_dir" as a directory, including parents if necessary. as_fn_mkdir_p () { case $as_dir in #( -*) as_dir=./$as_dir;; esac test -d "$as_dir" || eval $as_mkdir_p || { as_dirs= while :; do case $as_dir in #( *\'*) as_qdir=`$as_echo "$as_dir" | sed "s/'/'\\\\\\\\''/g"`;; #'( *) as_qdir=$as_dir;; esac as_dirs="'$as_qdir' $as_dirs" as_dir=`$as_dirname -- "$as_dir" || $as_expr X"$as_dir" : 'X\(.*[^/]\)//*[^/][^/]*/*$' \| \ X"$as_dir" : 'X\(//\)[^/]' \| \ X"$as_dir" : 'X\(//\)$' \| \ X"$as_dir" : 'X\(/\)' \| . 2>/dev/null || $as_echo X"$as_dir" | sed '/^X\(.*[^/]\)\/\/*[^/][^/]*\/*$/{ s//\1/ q } /^X\(\/\/\)[^/].*/{ s//\1/ q } /^X\(\/\/\)$/{ s//\1/ q } /^X\(\/\).*/{ s//\1/ q } s/.*/./; q'` test -d "$as_dir" && break done test -z "$as_dirs" || eval "mkdir $as_dirs" } || test -d "$as_dir" || as_fn_error $? "cannot create directory $as_dir" } # as_fn_mkdir_p # as_fn_executable_p FILE # ----------------------- # Test if FILE is an executable regular file. as_fn_executable_p () { test -f "$1" && test -x "$1" } # as_fn_executable_p # as_fn_append VAR VALUE # ---------------------- # Append the text in VALUE to the end of the definition contained in VAR. Take # advantage of any shell optimizations that allow amortized linear growth over # repeated appends, instead of the typical quadratic growth present in naive # implementations. if (eval "as_var=1; as_var+=2; test x\$as_var = x12") 2>/dev/null; then : eval 'as_fn_append () { eval $1+=\$2 }' else as_fn_append () { eval $1=\$$1\$2 } fi # as_fn_append # as_fn_arith ARG... # ------------------ # Perform arithmetic evaluation on the ARGs, and store the result in the # global $as_val. Take advantage of shells that can avoid forks. The arguments # must be portable across $(()) and expr. if (eval "test \$(( 1 + 1 )) = 2") 2>/dev/null; then : eval 'as_fn_arith () { as_val=$(( $* )) }' else as_fn_arith () { as_val=`expr "$@" || test $? -eq 1` } fi # as_fn_arith # as_fn_error STATUS ERROR [LINENO LOG_FD] # ---------------------------------------- # Output "`basename $0`: error: ERROR" to stderr. If LINENO and LOG_FD are # provided, also output the error to LOG_FD, referencing LINENO. Then exit the # script with STATUS, using 1 if that was 0. as_fn_error () { as_status=$1; test $as_status -eq 0 && as_status=1 if test "$4"; then as_lineno=${as_lineno-"$3"} as_lineno_stack=as_lineno_stack=$as_lineno_stack $as_echo "$as_me:${as_lineno-$LINENO}: error: $2" >&$4 fi $as_echo "$as_me: error: $2" >&2 as_fn_exit $as_status } # as_fn_error if expr a : '\(a\)' >/dev/null 2>&1 && test "X`expr 00001 : '.*\(...\)'`" = X001; then as_expr=expr else as_expr=false fi if (basename -- /) >/dev/null 2>&1 && test "X`basename -- / 2>&1`" = "X/"; then as_basename=basename else as_basename=false fi if (as_dir=`dirname -- /` && test "X$as_dir" = X/) >/dev/null 2>&1; then as_dirname=dirname else as_dirname=false fi as_me=`$as_basename -- "$0" || $as_expr X/"$0" : '.*/\([^/][^/]*\)/*$' \| \ X"$0" : 'X\(//\)$' \| \ X"$0" : 'X\(/\)' \| . 2>/dev/null || $as_echo X/"$0" | sed '/^.*\/\([^/][^/]*\)\/*$/{ s//\1/ q } /^X\/\(\/\/\)$/{ s//\1/ q } /^X\/\(\/\).*/{ s//\1/ q } s/.*/./; q'` # Avoid depending upon Character Ranges. as_cr_letters='abcdefghijklmnopqrstuvwxyz' as_cr_LETTERS='ABCDEFGHIJKLMNOPQRSTUVWXYZ' as_cr_Letters=$as_cr_letters$as_cr_LETTERS as_cr_digits='0123456789' as_cr_alnum=$as_cr_Letters$as_cr_digits as_lineno_1=$LINENO as_lineno_1a=$LINENO as_lineno_2=$LINENO as_lineno_2a=$LINENO eval 'test "x$as_lineno_1'$as_run'" != "x$as_lineno_2'$as_run'" && test "x`expr $as_lineno_1'$as_run' + 1`" = "x$as_lineno_2'$as_run'"' || { # Blame Lee E. McMahon (1931-1989) for sed's syntax. :-) sed -n ' p /[$]LINENO/= ' <$as_myself | sed ' s/[$]LINENO.*/&-/ t lineno b :lineno N :loop s/[$]LINENO\([^'$as_cr_alnum'_].*\n\)\(.*\)/\2\1\2/ t loop s/-\n.*// ' >$as_me.lineno && chmod +x "$as_me.lineno" || { $as_echo "$as_me: error: cannot create $as_me.lineno; rerun with a POSIX shell" >&2; as_fn_exit 1; } # If we had to re-execute with $CONFIG_SHELL, we're ensured to have # already done that, so ensure we don't try to do so again and fall # in an infinite loop. This has already happened in practice. _as_can_reexec=no; export _as_can_reexec # Don't try to exec as it changes $[0], causing all sort of problems # (the dirname of $[0] is not the place where we might find the # original and so on. Autoconf is especially sensitive to this). . "./$as_me.lineno" # Exit status is that of the last command. exit } ECHO_C= ECHO_N= ECHO_T= case `echo -n x` in #((((( -n*) case `echo 'xy\c'` in *c*) ECHO_T=' ';; # ECHO_T is single tab character. xy) ECHO_C='\c';; *) echo `echo ksh88 bug on AIX 6.1` > /dev/null ECHO_T=' ';; esac;; *) ECHO_N='-n';; esac rm -f conf$$ conf$$.exe conf$$.file if test -d conf$$.dir; then rm -f conf$$.dir/conf$$.file else rm -f conf$$.dir mkdir conf$$.dir 2>/dev/null fi if (echo >conf$$.file) 2>/dev/null; then if ln -s conf$$.file conf$$ 2>/dev/null; then as_ln_s='ln -s' # ... but there are two gotchas: # 1) On MSYS, both `ln -s file dir' and `ln file dir' fail. # 2) DJGPP < 2.04 has no symlinks; `ln -s' creates a wrapper executable. # In both cases, we have to default to `cp -pR'. ln -s conf$$.file conf$$.dir 2>/dev/null && test ! -f conf$$.exe || as_ln_s='cp -pR' elif ln conf$$.file conf$$ 2>/dev/null; then as_ln_s=ln else as_ln_s='cp -pR' fi else as_ln_s='cp -pR' fi rm -f conf$$ conf$$.exe conf$$.dir/conf$$.file conf$$.file rmdir conf$$.dir 2>/dev/null if mkdir -p . 2>/dev/null; then as_mkdir_p='mkdir -p "$as_dir"' else test -d ./-p && rmdir ./-p as_mkdir_p=false fi as_test_x='test -x' as_executable_p=as_fn_executable_p # Sed expression to map a string onto a valid CPP name. as_tr_cpp="eval sed 'y%*$as_cr_letters%P$as_cr_LETTERS%;s%[^_$as_cr_alnum]%_%g'" # Sed expression to map a string onto a valid variable name. as_tr_sh="eval sed 'y%*+%pp%;s%[^_$as_cr_alnum]%_%g'" SHELL=${CONFIG_SHELL-/bin/sh} test -n "$DJDIR" || exec 7<&0 &1 # Name of the host. # hostname on some systems (SVR3.2, old GNU/Linux) returns a bogus exit status, # so uname gets run too. ac_hostname=`(hostname || uname -n) 2>/dev/null | sed 1q` # # Initializations. # ac_default_prefix=/usr/local ac_clean_files= ac_config_libobj_dir=. LIBOBJS= cross_compiling=no subdirs= MFLAGS= MAKEFLAGS= # Identity of this package. PACKAGE_NAME='libffi' PACKAGE_TARNAME='libffi' PACKAGE_VERSION='3.0.9' PACKAGE_STRING='libffi 3.0.9' PACKAGE_BUGREPORT='http://gcc.gnu.org/bugs.html' PACKAGE_URL='' # Factoring default headers for most tests. ac_includes_default="\ #include #ifdef HAVE_SYS_TYPES_H # include #endif #ifdef HAVE_SYS_STAT_H # include #endif #ifdef STDC_HEADERS # include # include #else # ifdef HAVE_STDLIB_H # include # endif #endif #ifdef HAVE_STRING_H # if !defined STDC_HEADERS && defined HAVE_MEMORY_H # include # endif # include #endif #ifdef HAVE_STRINGS_H # include #endif #ifdef HAVE_INTTYPES_H # include #endif #ifdef HAVE_STDINT_H # include #endif #ifdef HAVE_UNISTD_H # include #endif" ac_subst_vars='am__EXEEXT_FALSE am__EXEEXT_TRUE LTLIBOBJS LIBOBJS TARGETDIR TARGET HAVE_LONG_DOUBLE ALLOCA PA64_HPUX_FALSE PA64_HPUX_TRUE PA_HPUX_FALSE PA_HPUX_TRUE PA_LINUX_FALSE PA_LINUX_TRUE SH64_FALSE SH64_TRUE SH_FALSE SH_TRUE X86_64_FALSE X86_64_TRUE S390_FALSE S390_TRUE FRV_FALSE FRV_TRUE LIBFFI_CRIS_FALSE LIBFFI_CRIS_TRUE AVR32_FALSE AVR32_TRUE ARM_FALSE ARM_TRUE POWERPC_FREEBSD_FALSE POWERPC_FREEBSD_TRUE POWERPC_DARWIN_FALSE POWERPC_DARWIN_TRUE POWERPC_AIX_FALSE POWERPC_AIX_TRUE POWERPC_FALSE POWERPC_TRUE M68K_FALSE M68K_TRUE M32R_FALSE M32R_TRUE IA64_FALSE IA64_TRUE ALPHA_FALSE ALPHA_TRUE X86_DARWIN_FALSE X86_DARWIN_TRUE X86_WIN64_FALSE X86_WIN64_TRUE X86_WIN32_FALSE X86_WIN32_TRUE X86_FREEBSD_FALSE X86_FREEBSD_TRUE X86_FALSE X86_TRUE SPARC_FALSE SPARC_TRUE MIPS_FALSE MIPS_TRUE AM_LTLDFLAGS AM_RUNTESTFLAGS TESTSUBDIR_FALSE TESTSUBDIR_TRUE CPP OTOOL64 OTOOL LIPO NMEDIT DSYMUTIL MANIFEST_TOOL RANLIB ac_ct_AR AR DLLTOOL OBJDUMP LN_S NM ac_ct_DUMPBIN DUMPBIN LD FGREP EGREP GREP SED LIBTOOL am__fastdepCCAS_FALSE am__fastdepCCAS_TRUE CCASDEPMODE CCASFLAGS CCAS am__fastdepCC_FALSE am__fastdepCC_TRUE CCDEPMODE am__nodep AMDEPBACKSLASH AMDEP_FALSE AMDEP_TRUE am__quote am__include DEPDIR OBJEXT EXEEXT ac_ct_CC CPPFLAGS LDFLAGS CFLAGS CC am__untar am__tar AMTAR am__leading_dot SET_MAKE AWK mkdir_p MKDIR_P INSTALL_STRIP_PROGRAM STRIP install_sh MAKEINFO AUTOHEADER AUTOMAKE AUTOCONF ACLOCAL VERSION PACKAGE CYGPATH_W am__isrc INSTALL_DATA INSTALL_SCRIPT INSTALL_PROGRAM target_os target_vendor target_cpu target host_os host_vendor host_cpu host build_os build_vendor build_cpu build target_alias host_alias build_alias LIBS ECHO_T ECHO_N ECHO_C DEFS mandir localedir libdir psdir pdfdir dvidir htmldir infodir docdir oldincludedir includedir localstatedir sharedstatedir sysconfdir datadir datarootdir libexecdir sbindir bindir program_transform_name prefix exec_prefix PACKAGE_URL PACKAGE_BUGREPORT PACKAGE_STRING PACKAGE_VERSION PACKAGE_TARNAME PACKAGE_NAME PATH_SEPARATOR SHELL' ac_subst_files='' ac_user_opts=' enable_option_checking enable_dependency_tracking enable_shared enable_static with_pic enable_fast_install with_gnu_ld with_sysroot enable_libtool_lock enable_debug enable_structs enable_raw_api enable_purify_safety ' ac_precious_vars='build_alias host_alias target_alias CCAS CCASFLAGS CPP CPPFLAGS' # Initialize some variables set by options. ac_init_help= ac_init_version=false ac_unrecognized_opts= ac_unrecognized_sep= # The variables have the same names as the options, with # dashes changed to underlines. cache_file=/dev/null exec_prefix=NONE no_create= no_recursion= prefix=NONE program_prefix=NONE program_suffix=NONE program_transform_name=s,x,x, silent= site= srcdir= verbose= x_includes=NONE x_libraries=NONE # Installation directory options. # These are left unexpanded so users can "make install exec_prefix=/foo" # and all the variables that are supposed to be based on exec_prefix # by default will actually change. # Use braces instead of parens because sh, perl, etc. also accept them. # (The list follows the same order as the GNU Coding Standards.) bindir='${exec_prefix}/bin' sbindir='${exec_prefix}/sbin' libexecdir='${exec_prefix}/libexec' datarootdir='${prefix}/share' datadir='${datarootdir}' sysconfdir='${prefix}/etc' sharedstatedir='${prefix}/com' localstatedir='${prefix}/var' includedir='${prefix}/include' oldincludedir='/usr/include' docdir='${datarootdir}/doc/${PACKAGE_TARNAME}' infodir='${datarootdir}/info' htmldir='${docdir}' dvidir='${docdir}' pdfdir='${docdir}' psdir='${docdir}' libdir='${exec_prefix}/lib' localedir='${datarootdir}/locale' mandir='${datarootdir}/man' ac_prev= ac_dashdash= for ac_option do # If the previous option needs an argument, assign it. if test -n "$ac_prev"; then eval $ac_prev=\$ac_option ac_prev= continue fi case $ac_option in *=?*) ac_optarg=`expr "X$ac_option" : '[^=]*=\(.*\)'` ;; *=) ac_optarg= ;; *) ac_optarg=yes ;; esac # Accept the important Cygnus configure options, so we can diagnose typos. case $ac_dashdash$ac_option in --) ac_dashdash=yes ;; -bindir | --bindir | --bindi | --bind | --bin | --bi) ac_prev=bindir ;; -bindir=* | --bindir=* | --bindi=* | --bind=* | --bin=* | --bi=*) bindir=$ac_optarg ;; -build | --build | --buil | --bui | --bu) ac_prev=build_alias ;; -build=* | --build=* | --buil=* | --bui=* | --bu=*) build_alias=$ac_optarg ;; -cache-file | --cache-file | --cache-fil | --cache-fi \ | --cache-f | --cache- | --cache | --cach | --cac | --ca | --c) ac_prev=cache_file ;; -cache-file=* | --cache-file=* | --cache-fil=* | --cache-fi=* \ | --cache-f=* | --cache-=* | --cache=* | --cach=* | --cac=* | --ca=* | --c=*) cache_file=$ac_optarg ;; --config-cache | -C) cache_file=config.cache ;; -datadir | --datadir | --datadi | --datad) ac_prev=datadir ;; -datadir=* | --datadir=* | --datadi=* | --datad=*) datadir=$ac_optarg ;; -datarootdir | --datarootdir | --datarootdi | --datarootd | --dataroot \ | --dataroo | --dataro | --datar) ac_prev=datarootdir ;; -datarootdir=* | --datarootdir=* | --datarootdi=* | --datarootd=* \ | --dataroot=* | --dataroo=* | --dataro=* | --datar=*) datarootdir=$ac_optarg ;; -disable-* | --disable-*) ac_useropt=`expr "x$ac_option" : 'x-*disable-\(.*\)'` # Reject names that are not valid shell variable names. expr "x$ac_useropt" : ".*[^-+._$as_cr_alnum]" >/dev/null && as_fn_error $? "invalid feature name: $ac_useropt" ac_useropt_orig=$ac_useropt ac_useropt=`$as_echo "$ac_useropt" | sed 's/[-+.]/_/g'` case $ac_user_opts in *" "enable_$ac_useropt" "*) ;; *) ac_unrecognized_opts="$ac_unrecognized_opts$ac_unrecognized_sep--disable-$ac_useropt_orig" ac_unrecognized_sep=', ';; esac eval enable_$ac_useropt=no ;; -docdir | --docdir | --docdi | --doc | --do) ac_prev=docdir ;; -docdir=* | --docdir=* | --docdi=* | --doc=* | --do=*) docdir=$ac_optarg ;; -dvidir | --dvidir | --dvidi | --dvid | --dvi | --dv) ac_prev=dvidir ;; -dvidir=* | --dvidir=* | --dvidi=* | --dvid=* | --dvi=* | --dv=*) dvidir=$ac_optarg ;; -enable-* | --enable-*) ac_useropt=`expr "x$ac_option" : 'x-*enable-\([^=]*\)'` # Reject names that are not valid shell variable names. expr "x$ac_useropt" : ".*[^-+._$as_cr_alnum]" >/dev/null && as_fn_error $? "invalid feature name: $ac_useropt" ac_useropt_orig=$ac_useropt ac_useropt=`$as_echo "$ac_useropt" | sed 's/[-+.]/_/g'` case $ac_user_opts in *" "enable_$ac_useropt" "*) ;; *) ac_unrecognized_opts="$ac_unrecognized_opts$ac_unrecognized_sep--enable-$ac_useropt_orig" ac_unrecognized_sep=', ';; esac eval enable_$ac_useropt=\$ac_optarg ;; -exec-prefix | --exec_prefix | --exec-prefix | --exec-prefi \ | --exec-pref | --exec-pre | --exec-pr | --exec-p | --exec- \ | --exec | --exe | --ex) ac_prev=exec_prefix ;; -exec-prefix=* | --exec_prefix=* | --exec-prefix=* | --exec-prefi=* \ | --exec-pref=* | --exec-pre=* | --exec-pr=* | --exec-p=* | --exec-=* \ | --exec=* | --exe=* | --ex=*) exec_prefix=$ac_optarg ;; -gas | --gas | --ga | --g) # Obsolete; use --with-gas. with_gas=yes ;; -help | --help | --hel | --he | -h) ac_init_help=long ;; -help=r* | --help=r* | --hel=r* | --he=r* | -hr*) ac_init_help=recursive ;; -help=s* | --help=s* | --hel=s* | --he=s* | -hs*) ac_init_help=short ;; -host | --host | --hos | --ho) ac_prev=host_alias ;; -host=* | --host=* | --hos=* | --ho=*) host_alias=$ac_optarg ;; -htmldir | --htmldir | --htmldi | --htmld | --html | --htm | --ht) ac_prev=htmldir ;; -htmldir=* | --htmldir=* | --htmldi=* | --htmld=* | --html=* | --htm=* \ | --ht=*) htmldir=$ac_optarg ;; -includedir | --includedir | --includedi | --included | --include \ | --includ | --inclu | --incl | --inc) ac_prev=includedir ;; -includedir=* | --includedir=* | --includedi=* | --included=* | --include=* \ | --includ=* | --inclu=* | --incl=* | --inc=*) includedir=$ac_optarg ;; -infodir | --infodir | --infodi | --infod | --info | --inf) ac_prev=infodir ;; -infodir=* | --infodir=* | --infodi=* | --infod=* | --info=* | --inf=*) infodir=$ac_optarg ;; -libdir | --libdir | --libdi | --libd) ac_prev=libdir ;; -libdir=* | --libdir=* | --libdi=* | --libd=*) libdir=$ac_optarg ;; -libexecdir | --libexecdir | --libexecdi | --libexecd | --libexec \ | --libexe | --libex | --libe) ac_prev=libexecdir ;; -libexecdir=* | --libexecdir=* | --libexecdi=* | --libexecd=* | --libexec=* \ | --libexe=* | --libex=* | --libe=*) libexecdir=$ac_optarg ;; -localedir | --localedir | --localedi | --localed | --locale) ac_prev=localedir ;; -localedir=* | --localedir=* | --localedi=* | --localed=* | --locale=*) localedir=$ac_optarg ;; -localstatedir | --localstatedir | --localstatedi | --localstated \ | --localstate | --localstat | --localsta | --localst | --locals) ac_prev=localstatedir ;; -localstatedir=* | --localstatedir=* | --localstatedi=* | --localstated=* \ | --localstate=* | --localstat=* | --localsta=* | --localst=* | --locals=*) localstatedir=$ac_optarg ;; -mandir | --mandir | --mandi | --mand | --man | --ma | --m) ac_prev=mandir ;; -mandir=* | --mandir=* | --mandi=* | --mand=* | --man=* | --ma=* | --m=*) mandir=$ac_optarg ;; -nfp | --nfp | --nf) # Obsolete; use --without-fp. with_fp=no ;; -no-create | --no-create | --no-creat | --no-crea | --no-cre \ | --no-cr | --no-c | -n) no_create=yes ;; -no-recursion | --no-recursion | --no-recursio | --no-recursi \ | --no-recurs | --no-recur | --no-recu | --no-rec | --no-re | --no-r) no_recursion=yes ;; -oldincludedir | --oldincludedir | --oldincludedi | --oldincluded \ | --oldinclude | --oldinclud | --oldinclu | --oldincl | --oldinc \ | --oldin | --oldi | --old | --ol | --o) ac_prev=oldincludedir ;; -oldincludedir=* | --oldincludedir=* | --oldincludedi=* | --oldincluded=* \ | --oldinclude=* | --oldinclud=* | --oldinclu=* | --oldincl=* | --oldinc=* \ | --oldin=* | --oldi=* | --old=* | --ol=* | --o=*) oldincludedir=$ac_optarg ;; -prefix | --prefix | --prefi | --pref | --pre | --pr | --p) ac_prev=prefix ;; -prefix=* | --prefix=* | --prefi=* | --pref=* | --pre=* | --pr=* | --p=*) prefix=$ac_optarg ;; -program-prefix | --program-prefix | --program-prefi | --program-pref \ | --program-pre | --program-pr | --program-p) ac_prev=program_prefix ;; -program-prefix=* | --program-prefix=* | --program-prefi=* \ | --program-pref=* | --program-pre=* | --program-pr=* | --program-p=*) program_prefix=$ac_optarg ;; -program-suffix | --program-suffix | --program-suffi | --program-suff \ | --program-suf | --program-su | --program-s) ac_prev=program_suffix ;; -program-suffix=* | --program-suffix=* | --program-suffi=* \ | --program-suff=* | --program-suf=* | --program-su=* | --program-s=*) program_suffix=$ac_optarg ;; -program-transform-name | --program-transform-name \ | --program-transform-nam | --program-transform-na \ | --program-transform-n | --program-transform- \ | --program-transform | --program-transfor \ | --program-transfo | --program-transf \ | --program-trans | --program-tran \ | --progr-tra | --program-tr | --program-t) ac_prev=program_transform_name ;; -program-transform-name=* | --program-transform-name=* \ | --program-transform-nam=* | --program-transform-na=* \ | --program-transform-n=* | --program-transform-=* \ | --program-transform=* | --program-transfor=* \ | --program-transfo=* | --program-transf=* \ | --program-trans=* | --program-tran=* \ | --progr-tra=* | --program-tr=* | --program-t=*) program_transform_name=$ac_optarg ;; -pdfdir | --pdfdir | --pdfdi | --pdfd | --pdf | --pd) ac_prev=pdfdir ;; -pdfdir=* | --pdfdir=* | --pdfdi=* | --pdfd=* | --pdf=* | --pd=*) pdfdir=$ac_optarg ;; -psdir | --psdir | --psdi | --psd | --ps) ac_prev=psdir ;; -psdir=* | --psdir=* | --psdi=* | --psd=* | --ps=*) psdir=$ac_optarg ;; -q | -quiet | --quiet | --quie | --qui | --qu | --q \ | -silent | --silent | --silen | --sile | --sil) silent=yes ;; -sbindir | --sbindir | --sbindi | --sbind | --sbin | --sbi | --sb) ac_prev=sbindir ;; -sbindir=* | --sbindir=* | --sbindi=* | --sbind=* | --sbin=* \ | --sbi=* | --sb=*) sbindir=$ac_optarg ;; -sharedstatedir | --sharedstatedir | --sharedstatedi \ | --sharedstated | --sharedstate | --sharedstat | --sharedsta \ | --sharedst | --shareds | --shared | --share | --shar \ | --sha | --sh) ac_prev=sharedstatedir ;; -sharedstatedir=* | --sharedstatedir=* | --sharedstatedi=* \ | --sharedstated=* | --sharedstate=* | --sharedstat=* | --sharedsta=* \ | --sharedst=* | --shareds=* | --shared=* | --share=* | --shar=* \ | --sha=* | --sh=*) sharedstatedir=$ac_optarg ;; -site | --site | --sit) ac_prev=site ;; -site=* | --site=* | --sit=*) site=$ac_optarg ;; -srcdir | --srcdir | --srcdi | --srcd | --src | --sr) ac_prev=srcdir ;; -srcdir=* | --srcdir=* | --srcdi=* | --srcd=* | --src=* | --sr=*) srcdir=$ac_optarg ;; -sysconfdir | --sysconfdir | --sysconfdi | --sysconfd | --sysconf \ | --syscon | --sysco | --sysc | --sys | --sy) ac_prev=sysconfdir ;; -sysconfdir=* | --sysconfdir=* | --sysconfdi=* | --sysconfd=* | --sysconf=* \ | --syscon=* | --sysco=* | --sysc=* | --sys=* | --sy=*) sysconfdir=$ac_optarg ;; -target | --target | --targe | --targ | --tar | --ta | --t) ac_prev=target_alias ;; -target=* | --target=* | --targe=* | --targ=* | --tar=* | --ta=* | --t=*) target_alias=$ac_optarg ;; -v | -verbose | --verbose | --verbos | --verbo | --verb) verbose=yes ;; -version | --version | --versio | --versi | --vers | -V) ac_init_version=: ;; -with-* | --with-*) ac_useropt=`expr "x$ac_option" : 'x-*with-\([^=]*\)'` # Reject names that are not valid shell variable names. expr "x$ac_useropt" : ".*[^-+._$as_cr_alnum]" >/dev/null && as_fn_error $? "invalid package name: $ac_useropt" ac_useropt_orig=$ac_useropt ac_useropt=`$as_echo "$ac_useropt" | sed 's/[-+.]/_/g'` case $ac_user_opts in *" "with_$ac_useropt" "*) ;; *) ac_unrecognized_opts="$ac_unrecognized_opts$ac_unrecognized_sep--with-$ac_useropt_orig" ac_unrecognized_sep=', ';; esac eval with_$ac_useropt=\$ac_optarg ;; -without-* | --without-*) ac_useropt=`expr "x$ac_option" : 'x-*without-\(.*\)'` # Reject names that are not valid shell variable names. expr "x$ac_useropt" : ".*[^-+._$as_cr_alnum]" >/dev/null && as_fn_error $? "invalid package name: $ac_useropt" ac_useropt_orig=$ac_useropt ac_useropt=`$as_echo "$ac_useropt" | sed 's/[-+.]/_/g'` case $ac_user_opts in *" "with_$ac_useropt" "*) ;; *) ac_unrecognized_opts="$ac_unrecognized_opts$ac_unrecognized_sep--without-$ac_useropt_orig" ac_unrecognized_sep=', ';; esac eval with_$ac_useropt=no ;; --x) # Obsolete; use --with-x. with_x=yes ;; -x-includes | --x-includes | --x-include | --x-includ | --x-inclu \ | --x-incl | --x-inc | --x-in | --x-i) ac_prev=x_includes ;; -x-includes=* | --x-includes=* | --x-include=* | --x-includ=* | --x-inclu=* \ | --x-incl=* | --x-inc=* | --x-in=* | --x-i=*) x_includes=$ac_optarg ;; -x-libraries | --x-libraries | --x-librarie | --x-librari \ | --x-librar | --x-libra | --x-libr | --x-lib | --x-li | --x-l) ac_prev=x_libraries ;; -x-libraries=* | --x-libraries=* | --x-librarie=* | --x-librari=* \ | --x-librar=* | --x-libra=* | --x-libr=* | --x-lib=* | --x-li=* | --x-l=*) x_libraries=$ac_optarg ;; -*) as_fn_error $? "unrecognized option: \`$ac_option' Try \`$0 --help' for more information" ;; *=*) ac_envvar=`expr "x$ac_option" : 'x\([^=]*\)='` # Reject names that are not valid shell variable names. case $ac_envvar in #( '' | [0-9]* | *[!_$as_cr_alnum]* ) as_fn_error $? "invalid variable name: \`$ac_envvar'" ;; esac eval $ac_envvar=\$ac_optarg export $ac_envvar ;; *) # FIXME: should be removed in autoconf 3.0. $as_echo "$as_me: WARNING: you should use --build, --host, --target" >&2 expr "x$ac_option" : ".*[^-._$as_cr_alnum]" >/dev/null && $as_echo "$as_me: WARNING: invalid host type: $ac_option" >&2 : "${build_alias=$ac_option} ${host_alias=$ac_option} ${target_alias=$ac_option}" ;; esac done if test -n "$ac_prev"; then ac_option=--`echo $ac_prev | sed 's/_/-/g'` as_fn_error $? "missing argument to $ac_option" fi if test -n "$ac_unrecognized_opts"; then case $enable_option_checking in no) ;; fatal) as_fn_error $? "unrecognized options: $ac_unrecognized_opts" ;; *) $as_echo "$as_me: WARNING: unrecognized options: $ac_unrecognized_opts" >&2 ;; esac fi # Check all directory arguments for consistency. for ac_var in exec_prefix prefix bindir sbindir libexecdir datarootdir \ datadir sysconfdir sharedstatedir localstatedir includedir \ oldincludedir docdir infodir htmldir dvidir pdfdir psdir \ libdir localedir mandir do eval ac_val=\$$ac_var # Remove trailing slashes. case $ac_val in */ ) ac_val=`expr "X$ac_val" : 'X\(.*[^/]\)' \| "X$ac_val" : 'X\(.*\)'` eval $ac_var=\$ac_val;; esac # Be sure to have absolute directory names. case $ac_val in [\\/$]* | ?:[\\/]* ) continue;; NONE | '' ) case $ac_var in *prefix ) continue;; esac;; esac as_fn_error $? "expected an absolute directory name for --$ac_var: $ac_val" done # There might be people who depend on the old broken behavior: `$host' # used to hold the argument of --host etc. # FIXME: To remove some day. build=$build_alias host=$host_alias target=$target_alias # FIXME: To remove some day. if test "x$host_alias" != x; then if test "x$build_alias" = x; then cross_compiling=maybe elif test "x$build_alias" != "x$host_alias"; then cross_compiling=yes fi fi ac_tool_prefix= test -n "$host_alias" && ac_tool_prefix=$host_alias- test "$silent" = yes && exec 6>/dev/null ac_pwd=`pwd` && test -n "$ac_pwd" && ac_ls_di=`ls -di .` && ac_pwd_ls_di=`cd "$ac_pwd" && ls -di .` || as_fn_error $? "working directory cannot be determined" test "X$ac_ls_di" = "X$ac_pwd_ls_di" || as_fn_error $? "pwd does not report name of working directory" # Find the source files, if location was not specified. if test -z "$srcdir"; then ac_srcdir_defaulted=yes # Try the directory containing this script, then the parent directory. ac_confdir=`$as_dirname -- "$as_myself" || $as_expr X"$as_myself" : 'X\(.*[^/]\)//*[^/][^/]*/*$' \| \ X"$as_myself" : 'X\(//\)[^/]' \| \ X"$as_myself" : 'X\(//\)$' \| \ X"$as_myself" : 'X\(/\)' \| . 2>/dev/null || $as_echo X"$as_myself" | sed '/^X\(.*[^/]\)\/\/*[^/][^/]*\/*$/{ s//\1/ q } /^X\(\/\/\)[^/].*/{ s//\1/ q } /^X\(\/\/\)$/{ s//\1/ q } /^X\(\/\).*/{ s//\1/ q } s/.*/./; q'` srcdir=$ac_confdir if test ! -r "$srcdir/$ac_unique_file"; then srcdir=.. fi else ac_srcdir_defaulted=no fi if test ! -r "$srcdir/$ac_unique_file"; then test "$ac_srcdir_defaulted" = yes && srcdir="$ac_confdir or .." as_fn_error $? "cannot find sources ($ac_unique_file) in $srcdir" fi ac_msg="sources are in $srcdir, but \`cd $srcdir' does not work" ac_abs_confdir=`( cd "$srcdir" && test -r "./$ac_unique_file" || as_fn_error $? "$ac_msg" pwd)` # When building in place, set srcdir=. if test "$ac_abs_confdir" = "$ac_pwd"; then srcdir=. fi # Remove unnecessary trailing slashes from srcdir. # Double slashes in file names in object file debugging info # mess up M-x gdb in Emacs. case $srcdir in */) srcdir=`expr "X$srcdir" : 'X\(.*[^/]\)' \| "X$srcdir" : 'X\(.*\)'`;; esac for ac_var in $ac_precious_vars; do eval ac_env_${ac_var}_set=\${${ac_var}+set} eval ac_env_${ac_var}_value=\$${ac_var} eval ac_cv_env_${ac_var}_set=\${${ac_var}+set} eval ac_cv_env_${ac_var}_value=\$${ac_var} done # # Report the --help message. # if test "$ac_init_help" = "long"; then # Omit some internal or obsolete options to make the list less imposing. # This message is too long to be a string in the A/UX 3.1 sh. cat <<_ACEOF \`configure' configures libffi 3.0.9 to adapt to many kinds of systems. Usage: $0 [OPTION]... [VAR=VALUE]... To assign environment variables (e.g., CC, CFLAGS...), specify them as VAR=VALUE. See below for descriptions of some of the useful variables. Defaults for the options are specified in brackets. Configuration: -h, --help display this help and exit --help=short display options specific to this package --help=recursive display the short help of all the included packages -V, --version display version information and exit -q, --quiet, --silent do not print \`checking ...' messages --cache-file=FILE cache test results in FILE [disabled] -C, --config-cache alias for \`--cache-file=config.cache' -n, --no-create do not create output files --srcdir=DIR find the sources in DIR [configure dir or \`..'] Installation directories: --prefix=PREFIX install architecture-independent files in PREFIX [$ac_default_prefix] --exec-prefix=EPREFIX install architecture-dependent files in EPREFIX [PREFIX] By default, \`make install' will install all the files in \`$ac_default_prefix/bin', \`$ac_default_prefix/lib' etc. You can specify an installation prefix other than \`$ac_default_prefix' using \`--prefix', for instance \`--prefix=\$HOME'. For better control, use the options below. Fine tuning of the installation directories: --bindir=DIR user executables [EPREFIX/bin] --sbindir=DIR system admin executables [EPREFIX/sbin] --libexecdir=DIR program executables [EPREFIX/libexec] --sysconfdir=DIR read-only single-machine data [PREFIX/etc] --sharedstatedir=DIR modifiable architecture-independent data [PREFIX/com] --localstatedir=DIR modifiable single-machine data [PREFIX/var] --libdir=DIR object code libraries [EPREFIX/lib] --includedir=DIR C header files [PREFIX/include] --oldincludedir=DIR C header files for non-gcc [/usr/include] --datarootdir=DIR read-only arch.-independent data root [PREFIX/share] --datadir=DIR read-only architecture-independent data [DATAROOTDIR] --infodir=DIR info documentation [DATAROOTDIR/info] --localedir=DIR locale-dependent data [DATAROOTDIR/locale] --mandir=DIR man documentation [DATAROOTDIR/man] --docdir=DIR documentation root [DATAROOTDIR/doc/libffi] --htmldir=DIR html documentation [DOCDIR] --dvidir=DIR dvi documentation [DOCDIR] --pdfdir=DIR pdf documentation [DOCDIR] --psdir=DIR ps documentation [DOCDIR] _ACEOF cat <<\_ACEOF Program names: --program-prefix=PREFIX prepend PREFIX to installed program names --program-suffix=SUFFIX append SUFFIX to installed program names --program-transform-name=PROGRAM run sed PROGRAM on installed program names System types: --build=BUILD configure for building on BUILD [guessed] --host=HOST cross-compile to build programs to run on HOST [BUILD] --target=TARGET configure for building compilers for TARGET [HOST] _ACEOF fi if test -n "$ac_init_help"; then case $ac_init_help in short | recursive ) echo "Configuration of libffi 3.0.9:";; esac cat <<\_ACEOF Optional Features: --disable-option-checking ignore unrecognized --enable/--with options --disable-FEATURE do not include FEATURE (same as --enable-FEATURE=no) --enable-FEATURE[=ARG] include FEATURE [ARG=yes] --disable-dependency-tracking speeds up one-time build --enable-dependency-tracking do not reject slow dependency extractors --enable-shared[=PKGS] build shared libraries [default=yes] --enable-static[=PKGS] build static libraries [default=yes] --enable-fast-install[=PKGS] optimize for fast installation [default=yes] --disable-libtool-lock avoid locking (might break parallel builds) --enable-debug debugging mode --disable-structs omit code for struct support --disable-raw-api make the raw api unavailable --enable-purify-safety purify-safe mode Optional Packages: --with-PACKAGE[=ARG] use PACKAGE [ARG=yes] --without-PACKAGE do not use PACKAGE (same as --with-PACKAGE=no) --with-pic[=PKGS] try to use only PIC/non-PIC objects [default=use both] --with-gnu-ld assume the C compiler uses GNU ld [default=no] --with-sysroot=DIR Search for dependent libraries within DIR (or the compiler's sysroot if not specified). Some influential environment variables: CC C compiler command CFLAGS C compiler flags LDFLAGS linker flags, e.g. -L if you have libraries in a nonstandard directory LIBS libraries to pass to the linker, e.g. -l CPPFLAGS (Objective) C/C++ preprocessor flags, e.g. -I if you have headers in a nonstandard directory CCAS assembler compiler command (defaults to CC) CCASFLAGS assembler compiler flags (defaults to CFLAGS) CPP C preprocessor Use these variables to override the choices made by `configure' or to help it to find libraries and programs with nonstandard names/locations. Report bugs to . _ACEOF ac_status=$? fi if test "$ac_init_help" = "recursive"; then # If there are subdirs, report their specific --help. for ac_dir in : $ac_subdirs_all; do test "x$ac_dir" = x: && continue test -d "$ac_dir" || { cd "$srcdir" && ac_pwd=`pwd` && srcdir=. && test -d "$ac_dir"; } || continue ac_builddir=. case "$ac_dir" in .) ac_dir_suffix= ac_top_builddir_sub=. ac_top_build_prefix= ;; *) ac_dir_suffix=/`$as_echo "$ac_dir" | sed 's|^\.[\\/]||'` # A ".." for each directory in $ac_dir_suffix. ac_top_builddir_sub=`$as_echo "$ac_dir_suffix" | sed 's|/[^\\/]*|/..|g;s|/||'` case $ac_top_builddir_sub in "") ac_top_builddir_sub=. ac_top_build_prefix= ;; *) ac_top_build_prefix=$ac_top_builddir_sub/ ;; esac ;; esac ac_abs_top_builddir=$ac_pwd ac_abs_builddir=$ac_pwd$ac_dir_suffix # for backward compatibility: ac_top_builddir=$ac_top_build_prefix case $srcdir in .) # We are building in place. ac_srcdir=. ac_top_srcdir=$ac_top_builddir_sub ac_abs_top_srcdir=$ac_pwd ;; [\\/]* | ?:[\\/]* ) # Absolute name. ac_srcdir=$srcdir$ac_dir_suffix; ac_top_srcdir=$srcdir ac_abs_top_srcdir=$srcdir ;; *) # Relative name. ac_srcdir=$ac_top_build_prefix$srcdir$ac_dir_suffix ac_top_srcdir=$ac_top_build_prefix$srcdir ac_abs_top_srcdir=$ac_pwd/$srcdir ;; esac ac_abs_srcdir=$ac_abs_top_srcdir$ac_dir_suffix cd "$ac_dir" || { ac_status=$?; continue; } # Check for guested configure. if test -f "$ac_srcdir/configure.gnu"; then echo && $SHELL "$ac_srcdir/configure.gnu" --help=recursive elif test -f "$ac_srcdir/configure"; then echo && $SHELL "$ac_srcdir/configure" --help=recursive else $as_echo "$as_me: WARNING: no configuration information is in $ac_dir" >&2 fi || ac_status=$? cd "$ac_pwd" || { ac_status=$?; break; } done fi test -n "$ac_init_help" && exit $ac_status if $ac_init_version; then cat <<\_ACEOF libffi configure 3.0.9 generated by GNU Autoconf 2.69 Copyright (C) 2012 Free Software Foundation, Inc. This configure script is free software; the Free Software Foundation gives unlimited permission to copy, distribute and modify it. _ACEOF exit fi ## ------------------------ ## ## Autoconf initialization. ## ## ------------------------ ## # ac_fn_c_try_compile LINENO # -------------------------- # Try to compile conftest.$ac_ext, and return whether this succeeded. ac_fn_c_try_compile () { as_lineno=${as_lineno-"$1"} as_lineno_stack=as_lineno_stack=$as_lineno_stack rm -f conftest.$ac_objext if { { ac_try="$ac_compile" case "(($ac_try" in *\"* | *\`* | *\\*) ac_try_echo=\$ac_try;; *) ac_try_echo=$ac_try;; esac eval ac_try_echo="\"\$as_me:${as_lineno-$LINENO}: $ac_try_echo\"" $as_echo "$ac_try_echo"; } >&5 (eval "$ac_compile") 2>conftest.err ac_status=$? if test -s conftest.err; then grep -v '^ *+' conftest.err >conftest.er1 cat conftest.er1 >&5 mv -f conftest.er1 conftest.err fi $as_echo "$as_me:${as_lineno-$LINENO}: \$? = $ac_status" >&5 test $ac_status = 0; } && { test -z "$ac_c_werror_flag" || test ! -s conftest.err } && test -s conftest.$ac_objext; then : ac_retval=0 else $as_echo "$as_me: failed program was:" >&5 sed 's/^/| /' conftest.$ac_ext >&5 ac_retval=1 fi eval $as_lineno_stack; ${as_lineno_stack:+:} unset as_lineno as_fn_set_status $ac_retval } # ac_fn_c_try_compile # ac_fn_c_try_link LINENO # ----------------------- # Try to link conftest.$ac_ext, and return whether this succeeded. ac_fn_c_try_link () { as_lineno=${as_lineno-"$1"} as_lineno_stack=as_lineno_stack=$as_lineno_stack rm -f conftest.$ac_objext conftest$ac_exeext if { { ac_try="$ac_link" case "(($ac_try" in *\"* | *\`* | *\\*) ac_try_echo=\$ac_try;; *) ac_try_echo=$ac_try;; esac eval ac_try_echo="\"\$as_me:${as_lineno-$LINENO}: $ac_try_echo\"" $as_echo "$ac_try_echo"; } >&5 (eval "$ac_link") 2>conftest.err ac_status=$? if test -s conftest.err; then grep -v '^ *+' conftest.err >conftest.er1 cat conftest.er1 >&5 mv -f conftest.er1 conftest.err fi $as_echo "$as_me:${as_lineno-$LINENO}: \$? = $ac_status" >&5 test $ac_status = 0; } && { test -z "$ac_c_werror_flag" || test ! -s conftest.err } && test -s conftest$ac_exeext && { test "$cross_compiling" = yes || test -x conftest$ac_exeext }; then : ac_retval=0 else $as_echo "$as_me: failed program was:" >&5 sed 's/^/| /' conftest.$ac_ext >&5 ac_retval=1 fi # Delete the IPA/IPO (Inter Procedural Analysis/Optimization) information # created by the PGI compiler (conftest_ipa8_conftest.oo), as it would # interfere with the next link command; also delete a directory that is # left behind by Apple's compiler. We do this before executing the actions. rm -rf conftest.dSYM conftest_ipa8_conftest.oo eval $as_lineno_stack; ${as_lineno_stack:+:} unset as_lineno as_fn_set_status $ac_retval } # ac_fn_c_try_link # ac_fn_c_check_header_compile LINENO HEADER VAR INCLUDES # ------------------------------------------------------- # Tests whether HEADER exists and can be compiled using the include files in # INCLUDES, setting the cache variable VAR accordingly. ac_fn_c_check_header_compile () { as_lineno=${as_lineno-"$1"} as_lineno_stack=as_lineno_stack=$as_lineno_stack { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $2" >&5 $as_echo_n "checking for $2... " >&6; } if eval \${$3+:} false; then : $as_echo_n "(cached) " >&6 else cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ $4 #include <$2> _ACEOF if ac_fn_c_try_compile "$LINENO"; then : eval "$3=yes" else eval "$3=no" fi rm -f core conftest.err conftest.$ac_objext conftest.$ac_ext fi eval ac_res=\$$3 { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_res" >&5 $as_echo "$ac_res" >&6; } eval $as_lineno_stack; ${as_lineno_stack:+:} unset as_lineno } # ac_fn_c_check_header_compile # ac_fn_c_try_cpp LINENO # ---------------------- # Try to preprocess conftest.$ac_ext, and return whether this succeeded. ac_fn_c_try_cpp () { as_lineno=${as_lineno-"$1"} as_lineno_stack=as_lineno_stack=$as_lineno_stack if { { ac_try="$ac_cpp conftest.$ac_ext" case "(($ac_try" in *\"* | *\`* | *\\*) ac_try_echo=\$ac_try;; *) ac_try_echo=$ac_try;; esac eval ac_try_echo="\"\$as_me:${as_lineno-$LINENO}: $ac_try_echo\"" $as_echo "$ac_try_echo"; } >&5 (eval "$ac_cpp conftest.$ac_ext") 2>conftest.err ac_status=$? if test -s conftest.err; then grep -v '^ *+' conftest.err >conftest.er1 cat conftest.er1 >&5 mv -f conftest.er1 conftest.err fi $as_echo "$as_me:${as_lineno-$LINENO}: \$? = $ac_status" >&5 test $ac_status = 0; } > conftest.i && { test -z "$ac_c_preproc_warn_flag$ac_c_werror_flag" || test ! -s conftest.err }; then : ac_retval=0 else $as_echo "$as_me: failed program was:" >&5 sed 's/^/| /' conftest.$ac_ext >&5 ac_retval=1 fi eval $as_lineno_stack; ${as_lineno_stack:+:} unset as_lineno as_fn_set_status $ac_retval } # ac_fn_c_try_cpp # ac_fn_c_try_run LINENO # ---------------------- # Try to link conftest.$ac_ext, and return whether this succeeded. Assumes # that executables *can* be run. ac_fn_c_try_run () { as_lineno=${as_lineno-"$1"} as_lineno_stack=as_lineno_stack=$as_lineno_stack if { { ac_try="$ac_link" case "(($ac_try" in *\"* | *\`* | *\\*) ac_try_echo=\$ac_try;; *) ac_try_echo=$ac_try;; esac eval ac_try_echo="\"\$as_me:${as_lineno-$LINENO}: $ac_try_echo\"" $as_echo "$ac_try_echo"; } >&5 (eval "$ac_link") 2>&5 ac_status=$? $as_echo "$as_me:${as_lineno-$LINENO}: \$? = $ac_status" >&5 test $ac_status = 0; } && { ac_try='./conftest$ac_exeext' { { case "(($ac_try" in *\"* | *\`* | *\\*) ac_try_echo=\$ac_try;; *) ac_try_echo=$ac_try;; esac eval ac_try_echo="\"\$as_me:${as_lineno-$LINENO}: $ac_try_echo\"" $as_echo "$ac_try_echo"; } >&5 (eval "$ac_try") 2>&5 ac_status=$? $as_echo "$as_me:${as_lineno-$LINENO}: \$? = $ac_status" >&5 test $ac_status = 0; }; }; then : ac_retval=0 else $as_echo "$as_me: program exited with status $ac_status" >&5 $as_echo "$as_me: failed program was:" >&5 sed 's/^/| /' conftest.$ac_ext >&5 ac_retval=$ac_status fi rm -rf conftest.dSYM conftest_ipa8_conftest.oo eval $as_lineno_stack; ${as_lineno_stack:+:} unset as_lineno as_fn_set_status $ac_retval } # ac_fn_c_try_run # ac_fn_c_check_func LINENO FUNC VAR # ---------------------------------- # Tests whether FUNC exists, setting the cache variable VAR accordingly ac_fn_c_check_func () { as_lineno=${as_lineno-"$1"} as_lineno_stack=as_lineno_stack=$as_lineno_stack { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $2" >&5 $as_echo_n "checking for $2... " >&6; } if eval \${$3+:} false; then : $as_echo_n "(cached) " >&6 else cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ /* Define $2 to an innocuous variant, in case declares $2. For example, HP-UX 11i declares gettimeofday. */ #define $2 innocuous_$2 /* System header to define __stub macros and hopefully few prototypes, which can conflict with char $2 (); below. Prefer to if __STDC__ is defined, since exists even on freestanding compilers. */ #ifdef __STDC__ # include #else # include #endif #undef $2 /* Override any GCC internal prototype to avoid an error. Use char because int might match the return type of a GCC builtin and then its argument prototype would still apply. */ #ifdef __cplusplus extern "C" #endif char $2 (); /* The GNU C library defines this for functions which it implements to always fail with ENOSYS. Some functions are actually named something starting with __ and the normal name is an alias. */ #if defined __stub_$2 || defined __stub___$2 choke me #endif int main () { return $2 (); ; return 0; } _ACEOF if ac_fn_c_try_link "$LINENO"; then : eval "$3=yes" else eval "$3=no" fi rm -f core conftest.err conftest.$ac_objext \ conftest$ac_exeext conftest.$ac_ext fi eval ac_res=\$$3 { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_res" >&5 $as_echo "$ac_res" >&6; } eval $as_lineno_stack; ${as_lineno_stack:+:} unset as_lineno } # ac_fn_c_check_func # ac_fn_c_check_type LINENO TYPE VAR INCLUDES # ------------------------------------------- # Tests whether TYPE exists after having included INCLUDES, setting cache # variable VAR accordingly. ac_fn_c_check_type () { as_lineno=${as_lineno-"$1"} as_lineno_stack=as_lineno_stack=$as_lineno_stack { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $2" >&5 $as_echo_n "checking for $2... " >&6; } if eval \${$3+:} false; then : $as_echo_n "(cached) " >&6 else eval "$3=no" cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ $4 int main () { if (sizeof ($2)) return 0; ; return 0; } _ACEOF if ac_fn_c_try_compile "$LINENO"; then : cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ $4 int main () { if (sizeof (($2))) return 0; ; return 0; } _ACEOF if ac_fn_c_try_compile "$LINENO"; then : else eval "$3=yes" fi rm -f core conftest.err conftest.$ac_objext conftest.$ac_ext fi rm -f core conftest.err conftest.$ac_objext conftest.$ac_ext fi eval ac_res=\$$3 { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_res" >&5 $as_echo "$ac_res" >&6; } eval $as_lineno_stack; ${as_lineno_stack:+:} unset as_lineno } # ac_fn_c_check_type # ac_fn_c_compute_int LINENO EXPR VAR INCLUDES # -------------------------------------------- # Tries to find the compile-time value of EXPR in a program that includes # INCLUDES, setting VAR accordingly. Returns whether the value could be # computed ac_fn_c_compute_int () { as_lineno=${as_lineno-"$1"} as_lineno_stack=as_lineno_stack=$as_lineno_stack if test "$cross_compiling" = yes; then # Depending upon the size, compute the lo and hi bounds. cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ $4 int main () { static int test_array [1 - 2 * !(($2) >= 0)]; test_array [0] = 0; return test_array [0]; ; return 0; } _ACEOF if ac_fn_c_try_compile "$LINENO"; then : ac_lo=0 ac_mid=0 while :; do cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ $4 int main () { static int test_array [1 - 2 * !(($2) <= $ac_mid)]; test_array [0] = 0; return test_array [0]; ; return 0; } _ACEOF if ac_fn_c_try_compile "$LINENO"; then : ac_hi=$ac_mid; break else as_fn_arith $ac_mid + 1 && ac_lo=$as_val if test $ac_lo -le $ac_mid; then ac_lo= ac_hi= break fi as_fn_arith 2 '*' $ac_mid + 1 && ac_mid=$as_val fi rm -f core conftest.err conftest.$ac_objext conftest.$ac_ext done else cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ $4 int main () { static int test_array [1 - 2 * !(($2) < 0)]; test_array [0] = 0; return test_array [0]; ; return 0; } _ACEOF if ac_fn_c_try_compile "$LINENO"; then : ac_hi=-1 ac_mid=-1 while :; do cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ $4 int main () { static int test_array [1 - 2 * !(($2) >= $ac_mid)]; test_array [0] = 0; return test_array [0]; ; return 0; } _ACEOF if ac_fn_c_try_compile "$LINENO"; then : ac_lo=$ac_mid; break else as_fn_arith '(' $ac_mid ')' - 1 && ac_hi=$as_val if test $ac_mid -le $ac_hi; then ac_lo= ac_hi= break fi as_fn_arith 2 '*' $ac_mid && ac_mid=$as_val fi rm -f core conftest.err conftest.$ac_objext conftest.$ac_ext done else ac_lo= ac_hi= fi rm -f core conftest.err conftest.$ac_objext conftest.$ac_ext fi rm -f core conftest.err conftest.$ac_objext conftest.$ac_ext # Binary search between lo and hi bounds. while test "x$ac_lo" != "x$ac_hi"; do as_fn_arith '(' $ac_hi - $ac_lo ')' / 2 + $ac_lo && ac_mid=$as_val cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ $4 int main () { static int test_array [1 - 2 * !(($2) <= $ac_mid)]; test_array [0] = 0; return test_array [0]; ; return 0; } _ACEOF if ac_fn_c_try_compile "$LINENO"; then : ac_hi=$ac_mid else as_fn_arith '(' $ac_mid ')' + 1 && ac_lo=$as_val fi rm -f core conftest.err conftest.$ac_objext conftest.$ac_ext done case $ac_lo in #(( ?*) eval "$3=\$ac_lo"; ac_retval=0 ;; '') ac_retval=1 ;; esac else cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ $4 static long int longval () { return $2; } static unsigned long int ulongval () { return $2; } #include #include int main () { FILE *f = fopen ("conftest.val", "w"); if (! f) return 1; if (($2) < 0) { long int i = longval (); if (i != ($2)) return 1; fprintf (f, "%ld", i); } else { unsigned long int i = ulongval (); if (i != ($2)) return 1; fprintf (f, "%lu", i); } /* Do not output a trailing newline, as this causes \r\n confusion on some platforms. */ return ferror (f) || fclose (f) != 0; ; return 0; } _ACEOF if ac_fn_c_try_run "$LINENO"; then : echo >>conftest.val; read $3 config.log <<_ACEOF This file contains any messages produced by compilers while running configure, to aid debugging if configure makes a mistake. It was created by libffi $as_me 3.0.9, which was generated by GNU Autoconf 2.69. Invocation command line was $ $0 $@ _ACEOF exec 5>>config.log { cat <<_ASUNAME ## --------- ## ## Platform. ## ## --------- ## hostname = `(hostname || uname -n) 2>/dev/null | sed 1q` uname -m = `(uname -m) 2>/dev/null || echo unknown` uname -r = `(uname -r) 2>/dev/null || echo unknown` uname -s = `(uname -s) 2>/dev/null || echo unknown` uname -v = `(uname -v) 2>/dev/null || echo unknown` /usr/bin/uname -p = `(/usr/bin/uname -p) 2>/dev/null || echo unknown` /bin/uname -X = `(/bin/uname -X) 2>/dev/null || echo unknown` /bin/arch = `(/bin/arch) 2>/dev/null || echo unknown` /usr/bin/arch -k = `(/usr/bin/arch -k) 2>/dev/null || echo unknown` /usr/convex/getsysinfo = `(/usr/convex/getsysinfo) 2>/dev/null || echo unknown` /usr/bin/hostinfo = `(/usr/bin/hostinfo) 2>/dev/null || echo unknown` /bin/machine = `(/bin/machine) 2>/dev/null || echo unknown` /usr/bin/oslevel = `(/usr/bin/oslevel) 2>/dev/null || echo unknown` /bin/universe = `(/bin/universe) 2>/dev/null || echo unknown` _ASUNAME as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. $as_echo "PATH: $as_dir" done IFS=$as_save_IFS } >&5 cat >&5 <<_ACEOF ## ----------- ## ## Core tests. ## ## ----------- ## _ACEOF # Keep a trace of the command line. # Strip out --no-create and --no-recursion so they do not pile up. # Strip out --silent because we don't want to record it for future runs. # Also quote any args containing shell meta-characters. # Make two passes to allow for proper duplicate-argument suppression. ac_configure_args= ac_configure_args0= ac_configure_args1= ac_must_keep_next=false for ac_pass in 1 2 do for ac_arg do case $ac_arg in -no-create | --no-c* | -n | -no-recursion | --no-r*) continue ;; -q | -quiet | --quiet | --quie | --qui | --qu | --q \ | -silent | --silent | --silen | --sile | --sil) continue ;; *\'*) ac_arg=`$as_echo "$ac_arg" | sed "s/'/'\\\\\\\\''/g"` ;; esac case $ac_pass in 1) as_fn_append ac_configure_args0 " '$ac_arg'" ;; 2) as_fn_append ac_configure_args1 " '$ac_arg'" if test $ac_must_keep_next = true; then ac_must_keep_next=false # Got value, back to normal. else case $ac_arg in *=* | --config-cache | -C | -disable-* | --disable-* \ | -enable-* | --enable-* | -gas | --g* | -nfp | --nf* \ | -q | -quiet | --q* | -silent | --sil* | -v | -verb* \ | -with-* | --with-* | -without-* | --without-* | --x) case "$ac_configure_args0 " in "$ac_configure_args1"*" '$ac_arg' "* ) continue ;; esac ;; -* ) ac_must_keep_next=true ;; esac fi as_fn_append ac_configure_args " '$ac_arg'" ;; esac done done { ac_configure_args0=; unset ac_configure_args0;} { ac_configure_args1=; unset ac_configure_args1;} # When interrupted or exit'd, cleanup temporary files, and complete # config.log. We remove comments because anyway the quotes in there # would cause problems or look ugly. # WARNING: Use '\'' to represent an apostrophe within the trap. # WARNING: Do not start the trap code with a newline, due to a FreeBSD 4.0 bug. trap 'exit_status=$? # Save into config.log some information that might help in debugging. { echo $as_echo "## ---------------- ## ## Cache variables. ## ## ---------------- ##" echo # The following way of writing the cache mishandles newlines in values, ( for ac_var in `(set) 2>&1 | sed -n '\''s/^\([a-zA-Z_][a-zA-Z0-9_]*\)=.*/\1/p'\''`; do eval ac_val=\$$ac_var case $ac_val in #( *${as_nl}*) case $ac_var in #( *_cv_*) { $as_echo "$as_me:${as_lineno-$LINENO}: WARNING: cache variable $ac_var contains a newline" >&5 $as_echo "$as_me: WARNING: cache variable $ac_var contains a newline" >&2;} ;; esac case $ac_var in #( _ | IFS | as_nl) ;; #( BASH_ARGV | BASH_SOURCE) eval $ac_var= ;; #( *) { eval $ac_var=; unset $ac_var;} ;; esac ;; esac done (set) 2>&1 | case $as_nl`(ac_space='\'' '\''; set) 2>&1` in #( *${as_nl}ac_space=\ *) sed -n \ "s/'\''/'\''\\\\'\'''\''/g; s/^\\([_$as_cr_alnum]*_cv_[_$as_cr_alnum]*\\)=\\(.*\\)/\\1='\''\\2'\''/p" ;; #( *) sed -n "/^[_$as_cr_alnum]*_cv_[_$as_cr_alnum]*=/p" ;; esac | sort ) echo $as_echo "## ----------------- ## ## Output variables. ## ## ----------------- ##" echo for ac_var in $ac_subst_vars do eval ac_val=\$$ac_var case $ac_val in *\'\''*) ac_val=`$as_echo "$ac_val" | sed "s/'\''/'\''\\\\\\\\'\'''\''/g"`;; esac $as_echo "$ac_var='\''$ac_val'\''" done | sort echo if test -n "$ac_subst_files"; then $as_echo "## ------------------- ## ## File substitutions. ## ## ------------------- ##" echo for ac_var in $ac_subst_files do eval ac_val=\$$ac_var case $ac_val in *\'\''*) ac_val=`$as_echo "$ac_val" | sed "s/'\''/'\''\\\\\\\\'\'''\''/g"`;; esac $as_echo "$ac_var='\''$ac_val'\''" done | sort echo fi if test -s confdefs.h; then $as_echo "## ----------- ## ## confdefs.h. ## ## ----------- ##" echo cat confdefs.h echo fi test "$ac_signal" != 0 && $as_echo "$as_me: caught signal $ac_signal" $as_echo "$as_me: exit $exit_status" } >&5 rm -f core *.core core.conftest.* && rm -f -r conftest* confdefs* conf$$* $ac_clean_files && exit $exit_status ' 0 for ac_signal in 1 2 13 15; do trap 'ac_signal='$ac_signal'; as_fn_exit 1' $ac_signal done ac_signal=0 # confdefs.h avoids OS command line length limits that DEFS can exceed. rm -f -r conftest* confdefs.h $as_echo "/* confdefs.h */" > confdefs.h # Predefined preprocessor variables. cat >>confdefs.h <<_ACEOF #define PACKAGE_NAME "$PACKAGE_NAME" _ACEOF cat >>confdefs.h <<_ACEOF #define PACKAGE_TARNAME "$PACKAGE_TARNAME" _ACEOF cat >>confdefs.h <<_ACEOF #define PACKAGE_VERSION "$PACKAGE_VERSION" _ACEOF cat >>confdefs.h <<_ACEOF #define PACKAGE_STRING "$PACKAGE_STRING" _ACEOF cat >>confdefs.h <<_ACEOF #define PACKAGE_BUGREPORT "$PACKAGE_BUGREPORT" _ACEOF cat >>confdefs.h <<_ACEOF #define PACKAGE_URL "$PACKAGE_URL" _ACEOF # Let the site file select an alternate cache file if it wants to. # Prefer an explicitly selected file to automatically selected ones. ac_site_file1=NONE ac_site_file2=NONE if test -n "$CONFIG_SITE"; then # We do not want a PATH search for config.site. case $CONFIG_SITE in #(( -*) ac_site_file1=./$CONFIG_SITE;; */*) ac_site_file1=$CONFIG_SITE;; *) ac_site_file1=./$CONFIG_SITE;; esac elif test "x$prefix" != xNONE; then ac_site_file1=$prefix/share/config.site ac_site_file2=$prefix/etc/config.site else ac_site_file1=$ac_default_prefix/share/config.site ac_site_file2=$ac_default_prefix/etc/config.site fi for ac_site_file in "$ac_site_file1" "$ac_site_file2" do test "x$ac_site_file" = xNONE && continue if test /dev/null != "$ac_site_file" && test -r "$ac_site_file"; then { $as_echo "$as_me:${as_lineno-$LINENO}: loading site script $ac_site_file" >&5 $as_echo "$as_me: loading site script $ac_site_file" >&6;} sed 's/^/| /' "$ac_site_file" >&5 . "$ac_site_file" \ || { { $as_echo "$as_me:${as_lineno-$LINENO}: error: in \`$ac_pwd':" >&5 $as_echo "$as_me: error: in \`$ac_pwd':" >&2;} as_fn_error $? "failed to load site script $ac_site_file See \`config.log' for more details" "$LINENO" 5; } fi done if test -r "$cache_file"; then # Some versions of bash will fail to source /dev/null (special files # actually), so we avoid doing that. DJGPP emulates it as a regular file. if test /dev/null != "$cache_file" && test -f "$cache_file"; then { $as_echo "$as_me:${as_lineno-$LINENO}: loading cache $cache_file" >&5 $as_echo "$as_me: loading cache $cache_file" >&6;} case $cache_file in [\\/]* | ?:[\\/]* ) . "$cache_file";; *) . "./$cache_file";; esac fi else { $as_echo "$as_me:${as_lineno-$LINENO}: creating cache $cache_file" >&5 $as_echo "$as_me: creating cache $cache_file" >&6;} >$cache_file fi # Check that the precious variables saved in the cache have kept the same # value. ac_cache_corrupted=false for ac_var in $ac_precious_vars; do eval ac_old_set=\$ac_cv_env_${ac_var}_set eval ac_new_set=\$ac_env_${ac_var}_set eval ac_old_val=\$ac_cv_env_${ac_var}_value eval ac_new_val=\$ac_env_${ac_var}_value case $ac_old_set,$ac_new_set in set,) { $as_echo "$as_me:${as_lineno-$LINENO}: error: \`$ac_var' was set to \`$ac_old_val' in the previous run" >&5 $as_echo "$as_me: error: \`$ac_var' was set to \`$ac_old_val' in the previous run" >&2;} ac_cache_corrupted=: ;; ,set) { $as_echo "$as_me:${as_lineno-$LINENO}: error: \`$ac_var' was not set in the previous run" >&5 $as_echo "$as_me: error: \`$ac_var' was not set in the previous run" >&2;} ac_cache_corrupted=: ;; ,);; *) if test "x$ac_old_val" != "x$ac_new_val"; then # differences in whitespace do not lead to failure. ac_old_val_w=`echo x $ac_old_val` ac_new_val_w=`echo x $ac_new_val` if test "$ac_old_val_w" != "$ac_new_val_w"; then { $as_echo "$as_me:${as_lineno-$LINENO}: error: \`$ac_var' has changed since the previous run:" >&5 $as_echo "$as_me: error: \`$ac_var' has changed since the previous run:" >&2;} ac_cache_corrupted=: else { $as_echo "$as_me:${as_lineno-$LINENO}: warning: ignoring whitespace changes in \`$ac_var' since the previous run:" >&5 $as_echo "$as_me: warning: ignoring whitespace changes in \`$ac_var' since the previous run:" >&2;} eval $ac_var=\$ac_old_val fi { $as_echo "$as_me:${as_lineno-$LINENO}: former value: \`$ac_old_val'" >&5 $as_echo "$as_me: former value: \`$ac_old_val'" >&2;} { $as_echo "$as_me:${as_lineno-$LINENO}: current value: \`$ac_new_val'" >&5 $as_echo "$as_me: current value: \`$ac_new_val'" >&2;} fi;; esac # Pass precious variables to config.status. if test "$ac_new_set" = set; then case $ac_new_val in *\'*) ac_arg=$ac_var=`$as_echo "$ac_new_val" | sed "s/'/'\\\\\\\\''/g"` ;; *) ac_arg=$ac_var=$ac_new_val ;; esac case " $ac_configure_args " in *" '$ac_arg' "*) ;; # Avoid dups. Use of quotes ensures accuracy. *) as_fn_append ac_configure_args " '$ac_arg'" ;; esac fi done if $ac_cache_corrupted; then { $as_echo "$as_me:${as_lineno-$LINENO}: error: in \`$ac_pwd':" >&5 $as_echo "$as_me: error: in \`$ac_pwd':" >&2;} { $as_echo "$as_me:${as_lineno-$LINENO}: error: changes in the environment can compromise the build" >&5 $as_echo "$as_me: error: changes in the environment can compromise the build" >&2;} as_fn_error $? "run \`make distclean' and/or \`rm $cache_file' and start over" "$LINENO" 5 fi ## -------------------- ## ## Main body of script. ## ## -------------------- ## ac_ext=c ac_cpp='$CPP $CPPFLAGS' ac_compile='$CC -c $CFLAGS $CPPFLAGS conftest.$ac_ext >&5' ac_link='$CC -o conftest$ac_exeext $CFLAGS $CPPFLAGS $LDFLAGS conftest.$ac_ext $LIBS >&5' ac_compiler_gnu=$ac_cv_c_compiler_gnu ac_config_headers="$ac_config_headers fficonfig.h" ac_aux_dir= for ac_dir in ../build-aux "$srcdir"/../build-aux; do if test -f "$ac_dir/install-sh"; then ac_aux_dir=$ac_dir ac_install_sh="$ac_aux_dir/install-sh -c" break elif test -f "$ac_dir/install.sh"; then ac_aux_dir=$ac_dir ac_install_sh="$ac_aux_dir/install.sh -c" break elif test -f "$ac_dir/shtool"; then ac_aux_dir=$ac_dir ac_install_sh="$ac_aux_dir/shtool install -c" break fi done if test -z "$ac_aux_dir"; then as_fn_error $? "cannot find install-sh, install.sh, or shtool in ../build-aux \"$srcdir\"/../build-aux" "$LINENO" 5 fi # These three variables are undocumented and unsupported, # and are intended to be withdrawn in a future Autoconf release. # They can cause serious problems if a builder's source tree is in a directory # whose full name contains unusual characters. ac_config_guess="$SHELL $ac_aux_dir/config.guess" # Please don't use this var. ac_config_sub="$SHELL $ac_aux_dir/config.sub" # Please don't use this var. ac_configure="$SHELL $ac_aux_dir/configure" # Please don't use this var. # Make sure we can run config.sub. $SHELL "$ac_aux_dir/config.sub" sun4 >/dev/null 2>&1 || as_fn_error $? "cannot run $SHELL $ac_aux_dir/config.sub" "$LINENO" 5 { $as_echo "$as_me:${as_lineno-$LINENO}: checking build system type" >&5 $as_echo_n "checking build system type... " >&6; } if ${ac_cv_build+:} false; then : $as_echo_n "(cached) " >&6 else ac_build_alias=$build_alias test "x$ac_build_alias" = x && ac_build_alias=`$SHELL "$ac_aux_dir/config.guess"` test "x$ac_build_alias" = x && as_fn_error $? "cannot guess build type; you must specify one" "$LINENO" 5 ac_cv_build=`$SHELL "$ac_aux_dir/config.sub" $ac_build_alias` || as_fn_error $? "$SHELL $ac_aux_dir/config.sub $ac_build_alias failed" "$LINENO" 5 fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_cv_build" >&5 $as_echo "$ac_cv_build" >&6; } case $ac_cv_build in *-*-*) ;; *) as_fn_error $? "invalid value of canonical build" "$LINENO" 5;; esac build=$ac_cv_build ac_save_IFS=$IFS; IFS='-' set x $ac_cv_build shift build_cpu=$1 build_vendor=$2 shift; shift # Remember, the first character of IFS is used to create $*, # except with old shells: build_os=$* IFS=$ac_save_IFS case $build_os in *\ *) build_os=`echo "$build_os" | sed 's/ /-/g'`;; esac { $as_echo "$as_me:${as_lineno-$LINENO}: checking host system type" >&5 $as_echo_n "checking host system type... " >&6; } if ${ac_cv_host+:} false; then : $as_echo_n "(cached) " >&6 else if test "x$host_alias" = x; then ac_cv_host=$ac_cv_build else ac_cv_host=`$SHELL "$ac_aux_dir/config.sub" $host_alias` || as_fn_error $? "$SHELL $ac_aux_dir/config.sub $host_alias failed" "$LINENO" 5 fi fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_cv_host" >&5 $as_echo "$ac_cv_host" >&6; } case $ac_cv_host in *-*-*) ;; *) as_fn_error $? "invalid value of canonical host" "$LINENO" 5;; esac host=$ac_cv_host ac_save_IFS=$IFS; IFS='-' set x $ac_cv_host shift host_cpu=$1 host_vendor=$2 shift; shift # Remember, the first character of IFS is used to create $*, # except with old shells: host_os=$* IFS=$ac_save_IFS case $host_os in *\ *) host_os=`echo "$host_os" | sed 's/ /-/g'`;; esac { $as_echo "$as_me:${as_lineno-$LINENO}: checking target system type" >&5 $as_echo_n "checking target system type... " >&6; } if ${ac_cv_target+:} false; then : $as_echo_n "(cached) " >&6 else if test "x$target_alias" = x; then ac_cv_target=$ac_cv_host else ac_cv_target=`$SHELL "$ac_aux_dir/config.sub" $target_alias` || as_fn_error $? "$SHELL $ac_aux_dir/config.sub $target_alias failed" "$LINENO" 5 fi fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_cv_target" >&5 $as_echo "$ac_cv_target" >&6; } case $ac_cv_target in *-*-*) ;; *) as_fn_error $? "invalid value of canonical target" "$LINENO" 5;; esac target=$ac_cv_target ac_save_IFS=$IFS; IFS='-' set x $ac_cv_target shift target_cpu=$1 target_vendor=$2 shift; shift # Remember, the first character of IFS is used to create $*, # except with old shells: target_os=$* IFS=$ac_save_IFS case $target_os in *\ *) target_os=`echo "$target_os" | sed 's/ /-/g'`;; esac # The aliases save the names the user supplied, while $host etc. # will get canonicalized. test -n "$target_alias" && test "$program_prefix$program_suffix$program_transform_name" = \ NONENONEs,x,x, && program_prefix=${target_alias}- target_alias=${target_alias-$host_alias} . ${srcdir}/configure.host am__api_version='1.11' # Find a good install program. We prefer a C program (faster), # so one script is as good as another. But avoid the broken or # incompatible versions: # SysV /etc/install, /usr/sbin/install # SunOS /usr/etc/install # IRIX /sbin/install # AIX /bin/install # AmigaOS /C/install, which installs bootblocks on floppy discs # AIX 4 /usr/bin/installbsd, which doesn't work without a -g flag # AFS /usr/afsws/bin/install, which mishandles nonexistent args # SVR4 /usr/ucb/install, which tries to use the nonexistent group "staff" # OS/2's system install, which has a completely different semantic # ./install, which can be erroneously created by make from ./install.sh. # Reject install programs that cannot install multiple files. { $as_echo "$as_me:${as_lineno-$LINENO}: checking for a BSD-compatible install" >&5 $as_echo_n "checking for a BSD-compatible install... " >&6; } if test -z "$INSTALL"; then if ${ac_cv_path_install+:} false; then : $as_echo_n "(cached) " >&6 else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. # Account for people who put trailing slashes in PATH elements. case $as_dir/ in #(( ./ | .// | /[cC]/* | \ /etc/* | /usr/sbin/* | /usr/etc/* | /sbin/* | /usr/afsws/bin/* | \ ?:[\\/]os2[\\/]install[\\/]* | ?:[\\/]OS2[\\/]INSTALL[\\/]* | \ /usr/ucb/* ) ;; *) # OSF1 and SCO ODT 3.0 have their own names for install. # Don't use installbsd from OSF since it installs stuff as root # by default. for ac_prog in ginstall scoinst install; do for ac_exec_ext in '' $ac_executable_extensions; do if as_fn_executable_p "$as_dir/$ac_prog$ac_exec_ext"; then if test $ac_prog = install && grep dspmsg "$as_dir/$ac_prog$ac_exec_ext" >/dev/null 2>&1; then # AIX install. It has an incompatible calling convention. : elif test $ac_prog = install && grep pwplus "$as_dir/$ac_prog$ac_exec_ext" >/dev/null 2>&1; then # program-specific install script used by HP pwplus--don't use. : else rm -rf conftest.one conftest.two conftest.dir echo one > conftest.one echo two > conftest.two mkdir conftest.dir if "$as_dir/$ac_prog$ac_exec_ext" -c conftest.one conftest.two "`pwd`/conftest.dir" && test -s conftest.one && test -s conftest.two && test -s conftest.dir/conftest.one && test -s conftest.dir/conftest.two then ac_cv_path_install="$as_dir/$ac_prog$ac_exec_ext -c" break 3 fi fi fi done done ;; esac done IFS=$as_save_IFS rm -rf conftest.one conftest.two conftest.dir fi if test "${ac_cv_path_install+set}" = set; then INSTALL=$ac_cv_path_install else # As a last resort, use the slow shell script. Don't cache a # value for INSTALL within a source directory, because that will # break other packages using the cache if that directory is # removed, or if the value is a relative name. INSTALL=$ac_install_sh fi fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $INSTALL" >&5 $as_echo "$INSTALL" >&6; } # Use test -z because SunOS4 sh mishandles braces in ${var-val}. # It thinks the first close brace ends the variable substitution. test -z "$INSTALL_PROGRAM" && INSTALL_PROGRAM='${INSTALL}' test -z "$INSTALL_SCRIPT" && INSTALL_SCRIPT='${INSTALL}' test -z "$INSTALL_DATA" && INSTALL_DATA='${INSTALL} -m 644' { $as_echo "$as_me:${as_lineno-$LINENO}: checking whether build environment is sane" >&5 $as_echo_n "checking whether build environment is sane... " >&6; } # Just in case sleep 1 echo timestamp > conftest.file # Reject unsafe characters in $srcdir or the absolute working directory # name. Accept space and tab only in the latter. am_lf=' ' case `pwd` in *[\\\"\#\$\&\'\`$am_lf]*) as_fn_error $? "unsafe absolute working directory name" "$LINENO" 5;; esac case $srcdir in *[\\\"\#\$\&\'\`$am_lf\ \ ]*) as_fn_error $? "unsafe srcdir value: \`$srcdir'" "$LINENO" 5;; esac # Do `set' in a subshell so we don't clobber the current shell's # arguments. Must try -L first in case configure is actually a # symlink; some systems play weird games with the mod time of symlinks # (eg FreeBSD returns the mod time of the symlink's containing # directory). if ( set X `ls -Lt "$srcdir/configure" conftest.file 2> /dev/null` if test "$*" = "X"; then # -L didn't work. set X `ls -t "$srcdir/configure" conftest.file` fi rm -f conftest.file if test "$*" != "X $srcdir/configure conftest.file" \ && test "$*" != "X conftest.file $srcdir/configure"; then # If neither matched, then we have a broken ls. This can happen # if, for instance, CONFIG_SHELL is bash and it inherits a # broken ls alias from the environment. This has actually # happened. Such a system could not be considered "sane". as_fn_error $? "ls -t appears to fail. Make sure there is not a broken alias in your environment" "$LINENO" 5 fi test "$2" = conftest.file ) then # Ok. : else as_fn_error $? "newly created file is older than distributed files! Check your system clock" "$LINENO" 5 fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: yes" >&5 $as_echo "yes" >&6; } test "$program_prefix" != NONE && program_transform_name="s&^&$program_prefix&;$program_transform_name" # Use a double $ so make ignores it. test "$program_suffix" != NONE && program_transform_name="s&\$&$program_suffix&;$program_transform_name" # Double any \ or $. # By default was `s,x,x', remove it if useless. ac_script='s/[\\$]/&&/g;s/;s,x,x,$//' program_transform_name=`$as_echo "$program_transform_name" | sed "$ac_script"` # expand $ac_aux_dir to an absolute path am_aux_dir=`cd $ac_aux_dir && pwd` if test x"${MISSING+set}" != xset; then case $am_aux_dir in *\ * | *\ *) MISSING="\${SHELL} \"$am_aux_dir/missing\"" ;; *) MISSING="\${SHELL} $am_aux_dir/missing" ;; esac fi # Use eval to expand $SHELL if eval "$MISSING --run true"; then am_missing_run="$MISSING --run " else am_missing_run= { $as_echo "$as_me:${as_lineno-$LINENO}: WARNING: \`missing' script is too old or missing" >&5 $as_echo "$as_me: WARNING: \`missing' script is too old or missing" >&2;} fi if test x"${install_sh}" != xset; then case $am_aux_dir in *\ * | *\ *) install_sh="\${SHELL} '$am_aux_dir/install-sh'" ;; *) install_sh="\${SHELL} $am_aux_dir/install-sh" esac fi # Installed binaries are usually stripped using `strip' when the user # run `make install-strip'. However `strip' might not be the right # tool to use in cross-compilation environments, therefore Automake # will honor the `STRIP' environment variable to overrule this program. if test "$cross_compiling" != no; then if test -n "$ac_tool_prefix"; then # Extract the first word of "${ac_tool_prefix}strip", so it can be a program name with args. set dummy ${ac_tool_prefix}strip; ac_word=$2 { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $ac_word" >&5 $as_echo_n "checking for $ac_word... " >&6; } if ${ac_cv_prog_STRIP+:} false; then : $as_echo_n "(cached) " >&6 else if test -n "$STRIP"; then ac_cv_prog_STRIP="$STRIP" # Let the user override the test. else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_exec_ext in '' $ac_executable_extensions; do if as_fn_executable_p "$as_dir/$ac_word$ac_exec_ext"; then ac_cv_prog_STRIP="${ac_tool_prefix}strip" $as_echo "$as_me:${as_lineno-$LINENO}: found $as_dir/$ac_word$ac_exec_ext" >&5 break 2 fi done done IFS=$as_save_IFS fi fi STRIP=$ac_cv_prog_STRIP if test -n "$STRIP"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $STRIP" >&5 $as_echo "$STRIP" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi fi if test -z "$ac_cv_prog_STRIP"; then ac_ct_STRIP=$STRIP # Extract the first word of "strip", so it can be a program name with args. set dummy strip; ac_word=$2 { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $ac_word" >&5 $as_echo_n "checking for $ac_word... " >&6; } if ${ac_cv_prog_ac_ct_STRIP+:} false; then : $as_echo_n "(cached) " >&6 else if test -n "$ac_ct_STRIP"; then ac_cv_prog_ac_ct_STRIP="$ac_ct_STRIP" # Let the user override the test. else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_exec_ext in '' $ac_executable_extensions; do if as_fn_executable_p "$as_dir/$ac_word$ac_exec_ext"; then ac_cv_prog_ac_ct_STRIP="strip" $as_echo "$as_me:${as_lineno-$LINENO}: found $as_dir/$ac_word$ac_exec_ext" >&5 break 2 fi done done IFS=$as_save_IFS fi fi ac_ct_STRIP=$ac_cv_prog_ac_ct_STRIP if test -n "$ac_ct_STRIP"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_ct_STRIP" >&5 $as_echo "$ac_ct_STRIP" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi if test "x$ac_ct_STRIP" = x; then STRIP=":" else case $cross_compiling:$ac_tool_warned in yes:) { $as_echo "$as_me:${as_lineno-$LINENO}: WARNING: using cross tools not prefixed with host triplet" >&5 $as_echo "$as_me: WARNING: using cross tools not prefixed with host triplet" >&2;} ac_tool_warned=yes ;; esac STRIP=$ac_ct_STRIP fi else STRIP="$ac_cv_prog_STRIP" fi fi INSTALL_STRIP_PROGRAM="\$(install_sh) -c -s" { $as_echo "$as_me:${as_lineno-$LINENO}: checking for a thread-safe mkdir -p" >&5 $as_echo_n "checking for a thread-safe mkdir -p... " >&6; } if test -z "$MKDIR_P"; then if ${ac_cv_path_mkdir+:} false; then : $as_echo_n "(cached) " >&6 else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH$PATH_SEPARATOR/opt/sfw/bin do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_prog in mkdir gmkdir; do for ac_exec_ext in '' $ac_executable_extensions; do as_fn_executable_p "$as_dir/$ac_prog$ac_exec_ext" || continue case `"$as_dir/$ac_prog$ac_exec_ext" --version 2>&1` in #( 'mkdir (GNU coreutils) '* | \ 'mkdir (coreutils) '* | \ 'mkdir (fileutils) '4.1*) ac_cv_path_mkdir=$as_dir/$ac_prog$ac_exec_ext break 3;; esac done done done IFS=$as_save_IFS fi test -d ./--version && rmdir ./--version if test "${ac_cv_path_mkdir+set}" = set; then MKDIR_P="$ac_cv_path_mkdir -p" else # As a last resort, use the slow shell script. Don't cache a # value for MKDIR_P within a source directory, because that will # break other packages using the cache if that directory is # removed, or if the value is a relative name. MKDIR_P="$ac_install_sh -d" fi fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $MKDIR_P" >&5 $as_echo "$MKDIR_P" >&6; } mkdir_p="$MKDIR_P" case $mkdir_p in [\\/$]* | ?:[\\/]*) ;; */*) mkdir_p="\$(top_builddir)/$mkdir_p" ;; esac for ac_prog in gawk mawk nawk awk do # Extract the first word of "$ac_prog", so it can be a program name with args. set dummy $ac_prog; ac_word=$2 { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $ac_word" >&5 $as_echo_n "checking for $ac_word... " >&6; } if ${ac_cv_prog_AWK+:} false; then : $as_echo_n "(cached) " >&6 else if test -n "$AWK"; then ac_cv_prog_AWK="$AWK" # Let the user override the test. else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_exec_ext in '' $ac_executable_extensions; do if as_fn_executable_p "$as_dir/$ac_word$ac_exec_ext"; then ac_cv_prog_AWK="$ac_prog" $as_echo "$as_me:${as_lineno-$LINENO}: found $as_dir/$ac_word$ac_exec_ext" >&5 break 2 fi done done IFS=$as_save_IFS fi fi AWK=$ac_cv_prog_AWK if test -n "$AWK"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $AWK" >&5 $as_echo "$AWK" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi test -n "$AWK" && break done { $as_echo "$as_me:${as_lineno-$LINENO}: checking whether ${MAKE-make} sets \$(MAKE)" >&5 $as_echo_n "checking whether ${MAKE-make} sets \$(MAKE)... " >&6; } set x ${MAKE-make} ac_make=`$as_echo "$2" | sed 's/+/p/g; s/[^a-zA-Z0-9_]/_/g'` if eval \${ac_cv_prog_make_${ac_make}_set+:} false; then : $as_echo_n "(cached) " >&6 else cat >conftest.make <<\_ACEOF SHELL = /bin/sh all: @echo '@@@%%%=$(MAKE)=@@@%%%' _ACEOF # GNU make sometimes prints "make[1]: Entering ...", which would confuse us. case `${MAKE-make} -f conftest.make 2>/dev/null` in *@@@%%%=?*=@@@%%%*) eval ac_cv_prog_make_${ac_make}_set=yes;; *) eval ac_cv_prog_make_${ac_make}_set=no;; esac rm -f conftest.make fi if eval test \$ac_cv_prog_make_${ac_make}_set = yes; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: yes" >&5 $as_echo "yes" >&6; } SET_MAKE= else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } SET_MAKE="MAKE=${MAKE-make}" fi rm -rf .tst 2>/dev/null mkdir .tst 2>/dev/null if test -d .tst; then am__leading_dot=. else am__leading_dot=_ fi rmdir .tst 2>/dev/null if test "`cd $srcdir && pwd`" != "`pwd`"; then # Use -I$(srcdir) only when $(srcdir) != ., so that make's output # is not polluted with repeated "-I." am__isrc=' -I$(srcdir)' # test to see if srcdir already configured if test -f $srcdir/config.status; then as_fn_error $? "source directory already configured; run \"make distclean\" there first" "$LINENO" 5 fi fi # test whether we have cygpath if test -z "$CYGPATH_W"; then if (cygpath --version) >/dev/null 2>/dev/null; then CYGPATH_W='cygpath -w' else CYGPATH_W=echo fi fi # Define the identity of the package. PACKAGE='libffi' VERSION='3.0.9' cat >>confdefs.h <<_ACEOF #define PACKAGE "$PACKAGE" _ACEOF cat >>confdefs.h <<_ACEOF #define VERSION "$VERSION" _ACEOF # Some tools Automake needs. ACLOCAL=${ACLOCAL-"${am_missing_run}aclocal-${am__api_version}"} AUTOCONF=${AUTOCONF-"${am_missing_run}autoconf"} AUTOMAKE=${AUTOMAKE-"${am_missing_run}automake-${am__api_version}"} AUTOHEADER=${AUTOHEADER-"${am_missing_run}autoheader"} MAKEINFO=${MAKEINFO-"${am_missing_run}makeinfo"} # We need awk for the "check" target. The system "awk" is bad on # some platforms. # Always define AMTAR for backward compatibility. Yes, it's still used # in the wild :-( We should find a proper way to deprecate it ... AMTAR='$${TAR-tar}' am__tar='$${TAR-tar} chof - "$$tardir"' am__untar='$${TAR-tar} xf -' # The same as in boehm-gc and libstdc++. Have to borrow it from there. # We must force CC to /not/ be precious variables; otherwise # the wrong, non-multilib-adjusted value will be used in multilibs. # As a side effect, we have to subst CFLAGS ourselves. ac_ext=c ac_cpp='$CPP $CPPFLAGS' ac_compile='$CC -c $CFLAGS $CPPFLAGS conftest.$ac_ext >&5' ac_link='$CC -o conftest$ac_exeext $CFLAGS $CPPFLAGS $LDFLAGS conftest.$ac_ext $LIBS >&5' ac_compiler_gnu=$ac_cv_c_compiler_gnu if test -n "$ac_tool_prefix"; then # Extract the first word of "${ac_tool_prefix}gcc", so it can be a program name with args. set dummy ${ac_tool_prefix}gcc; ac_word=$2 { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $ac_word" >&5 $as_echo_n "checking for $ac_word... " >&6; } if ${ac_cv_prog_CC+:} false; then : $as_echo_n "(cached) " >&6 else if test -n "$CC"; then ac_cv_prog_CC="$CC" # Let the user override the test. else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_exec_ext in '' $ac_executable_extensions; do if as_fn_executable_p "$as_dir/$ac_word$ac_exec_ext"; then ac_cv_prog_CC="${ac_tool_prefix}gcc" $as_echo "$as_me:${as_lineno-$LINENO}: found $as_dir/$ac_word$ac_exec_ext" >&5 break 2 fi done done IFS=$as_save_IFS fi fi CC=$ac_cv_prog_CC if test -n "$CC"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $CC" >&5 $as_echo "$CC" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi fi if test -z "$ac_cv_prog_CC"; then ac_ct_CC=$CC # Extract the first word of "gcc", so it can be a program name with args. set dummy gcc; ac_word=$2 { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $ac_word" >&5 $as_echo_n "checking for $ac_word... " >&6; } if ${ac_cv_prog_ac_ct_CC+:} false; then : $as_echo_n "(cached) " >&6 else if test -n "$ac_ct_CC"; then ac_cv_prog_ac_ct_CC="$ac_ct_CC" # Let the user override the test. else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_exec_ext in '' $ac_executable_extensions; do if as_fn_executable_p "$as_dir/$ac_word$ac_exec_ext"; then ac_cv_prog_ac_ct_CC="gcc" $as_echo "$as_me:${as_lineno-$LINENO}: found $as_dir/$ac_word$ac_exec_ext" >&5 break 2 fi done done IFS=$as_save_IFS fi fi ac_ct_CC=$ac_cv_prog_ac_ct_CC if test -n "$ac_ct_CC"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_ct_CC" >&5 $as_echo "$ac_ct_CC" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi if test "x$ac_ct_CC" = x; then CC="" else case $cross_compiling:$ac_tool_warned in yes:) { $as_echo "$as_me:${as_lineno-$LINENO}: WARNING: using cross tools not prefixed with host triplet" >&5 $as_echo "$as_me: WARNING: using cross tools not prefixed with host triplet" >&2;} ac_tool_warned=yes ;; esac CC=$ac_ct_CC fi else CC="$ac_cv_prog_CC" fi if test -z "$CC"; then if test -n "$ac_tool_prefix"; then # Extract the first word of "${ac_tool_prefix}cc", so it can be a program name with args. set dummy ${ac_tool_prefix}cc; ac_word=$2 { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $ac_word" >&5 $as_echo_n "checking for $ac_word... " >&6; } if ${ac_cv_prog_CC+:} false; then : $as_echo_n "(cached) " >&6 else if test -n "$CC"; then ac_cv_prog_CC="$CC" # Let the user override the test. else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_exec_ext in '' $ac_executable_extensions; do if as_fn_executable_p "$as_dir/$ac_word$ac_exec_ext"; then ac_cv_prog_CC="${ac_tool_prefix}cc" $as_echo "$as_me:${as_lineno-$LINENO}: found $as_dir/$ac_word$ac_exec_ext" >&5 break 2 fi done done IFS=$as_save_IFS fi fi CC=$ac_cv_prog_CC if test -n "$CC"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $CC" >&5 $as_echo "$CC" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi fi fi if test -z "$CC"; then # Extract the first word of "cc", so it can be a program name with args. set dummy cc; ac_word=$2 { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $ac_word" >&5 $as_echo_n "checking for $ac_word... " >&6; } if ${ac_cv_prog_CC+:} false; then : $as_echo_n "(cached) " >&6 else if test -n "$CC"; then ac_cv_prog_CC="$CC" # Let the user override the test. else ac_prog_rejected=no as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_exec_ext in '' $ac_executable_extensions; do if as_fn_executable_p "$as_dir/$ac_word$ac_exec_ext"; then if test "$as_dir/$ac_word$ac_exec_ext" = "/usr/ucb/cc"; then ac_prog_rejected=yes continue fi ac_cv_prog_CC="cc" $as_echo "$as_me:${as_lineno-$LINENO}: found $as_dir/$ac_word$ac_exec_ext" >&5 break 2 fi done done IFS=$as_save_IFS if test $ac_prog_rejected = yes; then # We found a bogon in the path, so make sure we never use it. set dummy $ac_cv_prog_CC shift if test $# != 0; then # We chose a different compiler from the bogus one. # However, it has the same basename, so the bogon will be chosen # first if we set CC to just the basename; use the full file name. shift ac_cv_prog_CC="$as_dir/$ac_word${1+' '}$@" fi fi fi fi CC=$ac_cv_prog_CC if test -n "$CC"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $CC" >&5 $as_echo "$CC" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi fi if test -z "$CC"; then if test -n "$ac_tool_prefix"; then for ac_prog in cl.exe do # Extract the first word of "$ac_tool_prefix$ac_prog", so it can be a program name with args. set dummy $ac_tool_prefix$ac_prog; ac_word=$2 { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $ac_word" >&5 $as_echo_n "checking for $ac_word... " >&6; } if ${ac_cv_prog_CC+:} false; then : $as_echo_n "(cached) " >&6 else if test -n "$CC"; then ac_cv_prog_CC="$CC" # Let the user override the test. else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_exec_ext in '' $ac_executable_extensions; do if as_fn_executable_p "$as_dir/$ac_word$ac_exec_ext"; then ac_cv_prog_CC="$ac_tool_prefix$ac_prog" $as_echo "$as_me:${as_lineno-$LINENO}: found $as_dir/$ac_word$ac_exec_ext" >&5 break 2 fi done done IFS=$as_save_IFS fi fi CC=$ac_cv_prog_CC if test -n "$CC"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $CC" >&5 $as_echo "$CC" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi test -n "$CC" && break done fi if test -z "$CC"; then ac_ct_CC=$CC for ac_prog in cl.exe do # Extract the first word of "$ac_prog", so it can be a program name with args. set dummy $ac_prog; ac_word=$2 { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $ac_word" >&5 $as_echo_n "checking for $ac_word... " >&6; } if ${ac_cv_prog_ac_ct_CC+:} false; then : $as_echo_n "(cached) " >&6 else if test -n "$ac_ct_CC"; then ac_cv_prog_ac_ct_CC="$ac_ct_CC" # Let the user override the test. else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_exec_ext in '' $ac_executable_extensions; do if as_fn_executable_p "$as_dir/$ac_word$ac_exec_ext"; then ac_cv_prog_ac_ct_CC="$ac_prog" $as_echo "$as_me:${as_lineno-$LINENO}: found $as_dir/$ac_word$ac_exec_ext" >&5 break 2 fi done done IFS=$as_save_IFS fi fi ac_ct_CC=$ac_cv_prog_ac_ct_CC if test -n "$ac_ct_CC"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_ct_CC" >&5 $as_echo "$ac_ct_CC" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi test -n "$ac_ct_CC" && break done if test "x$ac_ct_CC" = x; then CC="" else case $cross_compiling:$ac_tool_warned in yes:) { $as_echo "$as_me:${as_lineno-$LINENO}: WARNING: using cross tools not prefixed with host triplet" >&5 $as_echo "$as_me: WARNING: using cross tools not prefixed with host triplet" >&2;} ac_tool_warned=yes ;; esac CC=$ac_ct_CC fi fi fi test -z "$CC" && { { $as_echo "$as_me:${as_lineno-$LINENO}: error: in \`$ac_pwd':" >&5 $as_echo "$as_me: error: in \`$ac_pwd':" >&2;} as_fn_error $? "no acceptable C compiler found in \$PATH See \`config.log' for more details" "$LINENO" 5; } # Provide some information about the compiler. $as_echo "$as_me:${as_lineno-$LINENO}: checking for C compiler version" >&5 set X $ac_compile ac_compiler=$2 for ac_option in --version -v -V -qversion; do { { ac_try="$ac_compiler $ac_option >&5" case "(($ac_try" in *\"* | *\`* | *\\*) ac_try_echo=\$ac_try;; *) ac_try_echo=$ac_try;; esac eval ac_try_echo="\"\$as_me:${as_lineno-$LINENO}: $ac_try_echo\"" $as_echo "$ac_try_echo"; } >&5 (eval "$ac_compiler $ac_option >&5") 2>conftest.err ac_status=$? if test -s conftest.err; then sed '10a\ ... rest of stderr output deleted ... 10q' conftest.err >conftest.er1 cat conftest.er1 >&5 fi rm -f conftest.er1 conftest.err $as_echo "$as_me:${as_lineno-$LINENO}: \$? = $ac_status" >&5 test $ac_status = 0; } done cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ int main () { ; return 0; } _ACEOF ac_clean_files_save=$ac_clean_files ac_clean_files="$ac_clean_files a.out a.out.dSYM a.exe b.out" # Try to create an executable without -o first, disregard a.out. # It will help us diagnose broken compilers, and finding out an intuition # of exeext. { $as_echo "$as_me:${as_lineno-$LINENO}: checking whether the C compiler works" >&5 $as_echo_n "checking whether the C compiler works... " >&6; } ac_link_default=`$as_echo "$ac_link" | sed 's/ -o *conftest[^ ]*//'` # The possible output files: ac_files="a.out conftest.exe conftest a.exe a_out.exe b.out conftest.*" ac_rmfiles= for ac_file in $ac_files do case $ac_file in *.$ac_ext | *.xcoff | *.tds | *.d | *.pdb | *.xSYM | *.bb | *.bbg | *.map | *.inf | *.dSYM | *.o | *.obj ) ;; * ) ac_rmfiles="$ac_rmfiles $ac_file";; esac done rm -f $ac_rmfiles if { { ac_try="$ac_link_default" case "(($ac_try" in *\"* | *\`* | *\\*) ac_try_echo=\$ac_try;; *) ac_try_echo=$ac_try;; esac eval ac_try_echo="\"\$as_me:${as_lineno-$LINENO}: $ac_try_echo\"" $as_echo "$ac_try_echo"; } >&5 (eval "$ac_link_default") 2>&5 ac_status=$? $as_echo "$as_me:${as_lineno-$LINENO}: \$? = $ac_status" >&5 test $ac_status = 0; }; then : # Autoconf-2.13 could set the ac_cv_exeext variable to `no'. # So ignore a value of `no', otherwise this would lead to `EXEEXT = no' # in a Makefile. We should not override ac_cv_exeext if it was cached, # so that the user can short-circuit this test for compilers unknown to # Autoconf. for ac_file in $ac_files '' do test -f "$ac_file" || continue case $ac_file in *.$ac_ext | *.xcoff | *.tds | *.d | *.pdb | *.xSYM | *.bb | *.bbg | *.map | *.inf | *.dSYM | *.o | *.obj ) ;; [ab].out ) # We found the default executable, but exeext='' is most # certainly right. break;; *.* ) if test "${ac_cv_exeext+set}" = set && test "$ac_cv_exeext" != no; then :; else ac_cv_exeext=`expr "$ac_file" : '[^.]*\(\..*\)'` fi # We set ac_cv_exeext here because the later test for it is not # safe: cross compilers may not add the suffix if given an `-o' # argument, so we may need to know it at that point already. # Even if this section looks crufty: it has the advantage of # actually working. break;; * ) break;; esac done test "$ac_cv_exeext" = no && ac_cv_exeext= else ac_file='' fi if test -z "$ac_file"; then : { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } $as_echo "$as_me: failed program was:" >&5 sed 's/^/| /' conftest.$ac_ext >&5 { { $as_echo "$as_me:${as_lineno-$LINENO}: error: in \`$ac_pwd':" >&5 $as_echo "$as_me: error: in \`$ac_pwd':" >&2;} as_fn_error 77 "C compiler cannot create executables See \`config.log' for more details" "$LINENO" 5; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: yes" >&5 $as_echo "yes" >&6; } fi { $as_echo "$as_me:${as_lineno-$LINENO}: checking for C compiler default output file name" >&5 $as_echo_n "checking for C compiler default output file name... " >&6; } { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_file" >&5 $as_echo "$ac_file" >&6; } ac_exeext=$ac_cv_exeext rm -f -r a.out a.out.dSYM a.exe conftest$ac_cv_exeext b.out ac_clean_files=$ac_clean_files_save { $as_echo "$as_me:${as_lineno-$LINENO}: checking for suffix of executables" >&5 $as_echo_n "checking for suffix of executables... " >&6; } if { { ac_try="$ac_link" case "(($ac_try" in *\"* | *\`* | *\\*) ac_try_echo=\$ac_try;; *) ac_try_echo=$ac_try;; esac eval ac_try_echo="\"\$as_me:${as_lineno-$LINENO}: $ac_try_echo\"" $as_echo "$ac_try_echo"; } >&5 (eval "$ac_link") 2>&5 ac_status=$? $as_echo "$as_me:${as_lineno-$LINENO}: \$? = $ac_status" >&5 test $ac_status = 0; }; then : # If both `conftest.exe' and `conftest' are `present' (well, observable) # catch `conftest.exe'. For instance with Cygwin, `ls conftest' will # work properly (i.e., refer to `conftest.exe'), while it won't with # `rm'. for ac_file in conftest.exe conftest conftest.*; do test -f "$ac_file" || continue case $ac_file in *.$ac_ext | *.xcoff | *.tds | *.d | *.pdb | *.xSYM | *.bb | *.bbg | *.map | *.inf | *.dSYM | *.o | *.obj ) ;; *.* ) ac_cv_exeext=`expr "$ac_file" : '[^.]*\(\..*\)'` break;; * ) break;; esac done else { { $as_echo "$as_me:${as_lineno-$LINENO}: error: in \`$ac_pwd':" >&5 $as_echo "$as_me: error: in \`$ac_pwd':" >&2;} as_fn_error $? "cannot compute suffix of executables: cannot compile and link See \`config.log' for more details" "$LINENO" 5; } fi rm -f conftest conftest$ac_cv_exeext { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_cv_exeext" >&5 $as_echo "$ac_cv_exeext" >&6; } rm -f conftest.$ac_ext EXEEXT=$ac_cv_exeext ac_exeext=$EXEEXT cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ #include int main () { FILE *f = fopen ("conftest.out", "w"); return ferror (f) || fclose (f) != 0; ; return 0; } _ACEOF ac_clean_files="$ac_clean_files conftest.out" # Check that the compiler produces executables we can run. If not, either # the compiler is broken, or we cross compile. { $as_echo "$as_me:${as_lineno-$LINENO}: checking whether we are cross compiling" >&5 $as_echo_n "checking whether we are cross compiling... " >&6; } if test "$cross_compiling" != yes; then { { ac_try="$ac_link" case "(($ac_try" in *\"* | *\`* | *\\*) ac_try_echo=\$ac_try;; *) ac_try_echo=$ac_try;; esac eval ac_try_echo="\"\$as_me:${as_lineno-$LINENO}: $ac_try_echo\"" $as_echo "$ac_try_echo"; } >&5 (eval "$ac_link") 2>&5 ac_status=$? $as_echo "$as_me:${as_lineno-$LINENO}: \$? = $ac_status" >&5 test $ac_status = 0; } if { ac_try='./conftest$ac_cv_exeext' { { case "(($ac_try" in *\"* | *\`* | *\\*) ac_try_echo=\$ac_try;; *) ac_try_echo=$ac_try;; esac eval ac_try_echo="\"\$as_me:${as_lineno-$LINENO}: $ac_try_echo\"" $as_echo "$ac_try_echo"; } >&5 (eval "$ac_try") 2>&5 ac_status=$? $as_echo "$as_me:${as_lineno-$LINENO}: \$? = $ac_status" >&5 test $ac_status = 0; }; }; then cross_compiling=no else if test "$cross_compiling" = maybe; then cross_compiling=yes else { { $as_echo "$as_me:${as_lineno-$LINENO}: error: in \`$ac_pwd':" >&5 $as_echo "$as_me: error: in \`$ac_pwd':" >&2;} as_fn_error $? "cannot run C compiled programs. If you meant to cross compile, use \`--host'. See \`config.log' for more details" "$LINENO" 5; } fi fi fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $cross_compiling" >&5 $as_echo "$cross_compiling" >&6; } rm -f conftest.$ac_ext conftest$ac_cv_exeext conftest.out ac_clean_files=$ac_clean_files_save { $as_echo "$as_me:${as_lineno-$LINENO}: checking for suffix of object files" >&5 $as_echo_n "checking for suffix of object files... " >&6; } if ${ac_cv_objext+:} false; then : $as_echo_n "(cached) " >&6 else cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ int main () { ; return 0; } _ACEOF rm -f conftest.o conftest.obj if { { ac_try="$ac_compile" case "(($ac_try" in *\"* | *\`* | *\\*) ac_try_echo=\$ac_try;; *) ac_try_echo=$ac_try;; esac eval ac_try_echo="\"\$as_me:${as_lineno-$LINENO}: $ac_try_echo\"" $as_echo "$ac_try_echo"; } >&5 (eval "$ac_compile") 2>&5 ac_status=$? $as_echo "$as_me:${as_lineno-$LINENO}: \$? = $ac_status" >&5 test $ac_status = 0; }; then : for ac_file in conftest.o conftest.obj conftest.*; do test -f "$ac_file" || continue; case $ac_file in *.$ac_ext | *.xcoff | *.tds | *.d | *.pdb | *.xSYM | *.bb | *.bbg | *.map | *.inf | *.dSYM ) ;; *) ac_cv_objext=`expr "$ac_file" : '.*\.\(.*\)'` break;; esac done else $as_echo "$as_me: failed program was:" >&5 sed 's/^/| /' conftest.$ac_ext >&5 { { $as_echo "$as_me:${as_lineno-$LINENO}: error: in \`$ac_pwd':" >&5 $as_echo "$as_me: error: in \`$ac_pwd':" >&2;} as_fn_error $? "cannot compute suffix of object files: cannot compile See \`config.log' for more details" "$LINENO" 5; } fi rm -f conftest.$ac_cv_objext conftest.$ac_ext fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_cv_objext" >&5 $as_echo "$ac_cv_objext" >&6; } OBJEXT=$ac_cv_objext ac_objext=$OBJEXT { $as_echo "$as_me:${as_lineno-$LINENO}: checking whether we are using the GNU C compiler" >&5 $as_echo_n "checking whether we are using the GNU C compiler... " >&6; } if ${ac_cv_c_compiler_gnu+:} false; then : $as_echo_n "(cached) " >&6 else cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ int main () { #ifndef __GNUC__ choke me #endif ; return 0; } _ACEOF if ac_fn_c_try_compile "$LINENO"; then : ac_compiler_gnu=yes else ac_compiler_gnu=no fi rm -f core conftest.err conftest.$ac_objext conftest.$ac_ext ac_cv_c_compiler_gnu=$ac_compiler_gnu fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_cv_c_compiler_gnu" >&5 $as_echo "$ac_cv_c_compiler_gnu" >&6; } if test $ac_compiler_gnu = yes; then GCC=yes else GCC= fi ac_test_CFLAGS=${CFLAGS+set} ac_save_CFLAGS=$CFLAGS { $as_echo "$as_me:${as_lineno-$LINENO}: checking whether $CC accepts -g" >&5 $as_echo_n "checking whether $CC accepts -g... " >&6; } if ${ac_cv_prog_cc_g+:} false; then : $as_echo_n "(cached) " >&6 else ac_save_c_werror_flag=$ac_c_werror_flag ac_c_werror_flag=yes ac_cv_prog_cc_g=no CFLAGS="-g" cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ int main () { ; return 0; } _ACEOF if ac_fn_c_try_compile "$LINENO"; then : ac_cv_prog_cc_g=yes else CFLAGS="" cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ int main () { ; return 0; } _ACEOF if ac_fn_c_try_compile "$LINENO"; then : else ac_c_werror_flag=$ac_save_c_werror_flag CFLAGS="-g" cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ int main () { ; return 0; } _ACEOF if ac_fn_c_try_compile "$LINENO"; then : ac_cv_prog_cc_g=yes fi rm -f core conftest.err conftest.$ac_objext conftest.$ac_ext fi rm -f core conftest.err conftest.$ac_objext conftest.$ac_ext fi rm -f core conftest.err conftest.$ac_objext conftest.$ac_ext ac_c_werror_flag=$ac_save_c_werror_flag fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_cv_prog_cc_g" >&5 $as_echo "$ac_cv_prog_cc_g" >&6; } if test "$ac_test_CFLAGS" = set; then CFLAGS=$ac_save_CFLAGS elif test $ac_cv_prog_cc_g = yes; then if test "$GCC" = yes; then CFLAGS="-g -O2" else CFLAGS="-g" fi else if test "$GCC" = yes; then CFLAGS="-O2" else CFLAGS= fi fi { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $CC option to accept ISO C89" >&5 $as_echo_n "checking for $CC option to accept ISO C89... " >&6; } if ${ac_cv_prog_cc_c89+:} false; then : $as_echo_n "(cached) " >&6 else ac_cv_prog_cc_c89=no ac_save_CC=$CC cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ #include #include struct stat; /* Most of the following tests are stolen from RCS 5.7's src/conf.sh. */ struct buf { int x; }; FILE * (*rcsopen) (struct buf *, struct stat *, int); static char *e (p, i) char **p; int i; { return p[i]; } static char *f (char * (*g) (char **, int), char **p, ...) { char *s; va_list v; va_start (v,p); s = g (p, va_arg (v,int)); va_end (v); return s; } /* OSF 4.0 Compaq cc is some sort of almost-ANSI by default. It has function prototypes and stuff, but not '\xHH' hex character constants. These don't provoke an error unfortunately, instead are silently treated as 'x'. The following induces an error, until -std is added to get proper ANSI mode. Curiously '\x00'!='x' always comes out true, for an array size at least. It's necessary to write '\x00'==0 to get something that's true only with -std. */ int osf4_cc_array ['\x00' == 0 ? 1 : -1]; /* IBM C 6 for AIX is almost-ANSI by default, but it replaces macro parameters inside strings and character constants. */ #define FOO(x) 'x' int xlc6_cc_array[FOO(a) == 'x' ? 1 : -1]; int test (int i, double x); struct s1 {int (*f) (int a);}; struct s2 {int (*f) (double a);}; int pairnames (int, char **, FILE *(*)(struct buf *, struct stat *, int), int, int); int argc; char **argv; int main () { return f (e, argv, 0) != argv[0] || f (e, argv, 1) != argv[1]; ; return 0; } _ACEOF for ac_arg in '' -qlanglvl=extc89 -qlanglvl=ansi -std \ -Ae "-Aa -D_HPUX_SOURCE" "-Xc -D__EXTENSIONS__" do CC="$ac_save_CC $ac_arg" if ac_fn_c_try_compile "$LINENO"; then : ac_cv_prog_cc_c89=$ac_arg fi rm -f core conftest.err conftest.$ac_objext test "x$ac_cv_prog_cc_c89" != "xno" && break done rm -f conftest.$ac_ext CC=$ac_save_CC fi # AC_CACHE_VAL case "x$ac_cv_prog_cc_c89" in x) { $as_echo "$as_me:${as_lineno-$LINENO}: result: none needed" >&5 $as_echo "none needed" >&6; } ;; xno) { $as_echo "$as_me:${as_lineno-$LINENO}: result: unsupported" >&5 $as_echo "unsupported" >&6; } ;; *) CC="$CC $ac_cv_prog_cc_c89" { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_cv_prog_cc_c89" >&5 $as_echo "$ac_cv_prog_cc_c89" >&6; } ;; esac if test "x$ac_cv_prog_cc_c89" != xno; then : fi ac_ext=c ac_cpp='$CPP $CPPFLAGS' ac_compile='$CC -c $CFLAGS $CPPFLAGS conftest.$ac_ext >&5' ac_link='$CC -o conftest$ac_exeext $CFLAGS $CPPFLAGS $LDFLAGS conftest.$ac_ext $LIBS >&5' ac_compiler_gnu=$ac_cv_c_compiler_gnu DEPDIR="${am__leading_dot}deps" ac_config_commands="$ac_config_commands depfiles" am_make=${MAKE-make} cat > confinc << 'END' am__doit: @echo this is the am__doit target .PHONY: am__doit END # If we don't find an include directive, just comment out the code. { $as_echo "$as_me:${as_lineno-$LINENO}: checking for style of include used by $am_make" >&5 $as_echo_n "checking for style of include used by $am_make... " >&6; } am__include="#" am__quote= _am_result=none # First try GNU make style include. echo "include confinc" > confmf # Ignore all kinds of additional output from `make'. case `$am_make -s -f confmf 2> /dev/null` in #( *the\ am__doit\ target*) am__include=include am__quote= _am_result=GNU ;; esac # Now try BSD make style include. if test "$am__include" = "#"; then echo '.include "confinc"' > confmf case `$am_make -s -f confmf 2> /dev/null` in #( *the\ am__doit\ target*) am__include=.include am__quote="\"" _am_result=BSD ;; esac fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $_am_result" >&5 $as_echo "$_am_result" >&6; } rm -f confinc confmf # Check whether --enable-dependency-tracking was given. if test "${enable_dependency_tracking+set}" = set; then : enableval=$enable_dependency_tracking; fi if test "x$enable_dependency_tracking" != xno; then am_depcomp="$ac_aux_dir/depcomp" AMDEPBACKSLASH='\' am__nodep='_no' fi if test "x$enable_dependency_tracking" != xno; then AMDEP_TRUE= AMDEP_FALSE='#' else AMDEP_TRUE='#' AMDEP_FALSE= fi depcc="$CC" am_compiler_list= { $as_echo "$as_me:${as_lineno-$LINENO}: checking dependency style of $depcc" >&5 $as_echo_n "checking dependency style of $depcc... " >&6; } if ${am_cv_CC_dependencies_compiler_type+:} false; then : $as_echo_n "(cached) " >&6 else if test -z "$AMDEP_TRUE" && test -f "$am_depcomp"; then # We make a subdir and do the tests there. Otherwise we can end up # making bogus files that we don't know about and never remove. For # instance it was reported that on HP-UX the gcc test will end up # making a dummy file named `D' -- because `-MD' means `put the output # in D'. rm -rf conftest.dir mkdir conftest.dir # Copy depcomp to subdir because otherwise we won't find it if we're # using a relative directory. cp "$am_depcomp" conftest.dir cd conftest.dir # We will build objects and dependencies in a subdirectory because # it helps to detect inapplicable dependency modes. For instance # both Tru64's cc and ICC support -MD to output dependencies as a # side effect of compilation, but ICC will put the dependencies in # the current directory while Tru64 will put them in the object # directory. mkdir sub am_cv_CC_dependencies_compiler_type=none if test "$am_compiler_list" = ""; then am_compiler_list=`sed -n 's/^#*\([a-zA-Z0-9]*\))$/\1/p' < ./depcomp` fi am__universal=false case " $depcc " in #( *\ -arch\ *\ -arch\ *) am__universal=true ;; esac for depmode in $am_compiler_list; do # Setup a source with many dependencies, because some compilers # like to wrap large dependency lists on column 80 (with \), and # we should not choose a depcomp mode which is confused by this. # # We need to recreate these files for each test, as the compiler may # overwrite some of them when testing with obscure command lines. # This happens at least with the AIX C compiler. : > sub/conftest.c for i in 1 2 3 4 5 6; do echo '#include "conftst'$i'.h"' >> sub/conftest.c # Using `: > sub/conftst$i.h' creates only sub/conftst1.h with # Solaris 8's {/usr,}/bin/sh. touch sub/conftst$i.h done echo "${am__include} ${am__quote}sub/conftest.Po${am__quote}" > confmf # We check with `-c' and `-o' for the sake of the "dashmstdout" # mode. It turns out that the SunPro C++ compiler does not properly # handle `-M -o', and we need to detect this. Also, some Intel # versions had trouble with output in subdirs am__obj=sub/conftest.${OBJEXT-o} am__minus_obj="-o $am__obj" case $depmode in gcc) # This depmode causes a compiler race in universal mode. test "$am__universal" = false || continue ;; nosideeffect) # after this tag, mechanisms are not by side-effect, so they'll # only be used when explicitly requested if test "x$enable_dependency_tracking" = xyes; then continue else break fi ;; msvc7 | msvc7msys | msvisualcpp | msvcmsys) # This compiler won't grok `-c -o', but also, the minuso test has # not run yet. These depmodes are late enough in the game, and # so weak that their functioning should not be impacted. am__obj=conftest.${OBJEXT-o} am__minus_obj= ;; none) break ;; esac if depmode=$depmode \ source=sub/conftest.c object=$am__obj \ depfile=sub/conftest.Po tmpdepfile=sub/conftest.TPo \ $SHELL ./depcomp $depcc -c $am__minus_obj sub/conftest.c \ >/dev/null 2>conftest.err && grep sub/conftst1.h sub/conftest.Po > /dev/null 2>&1 && grep sub/conftst6.h sub/conftest.Po > /dev/null 2>&1 && grep $am__obj sub/conftest.Po > /dev/null 2>&1 && ${MAKE-make} -s -f confmf > /dev/null 2>&1; then # icc doesn't choke on unknown options, it will just issue warnings # or remarks (even with -Werror). So we grep stderr for any message # that says an option was ignored or not supported. # When given -MP, icc 7.0 and 7.1 complain thusly: # icc: Command line warning: ignoring option '-M'; no argument required # The diagnosis changed in icc 8.0: # icc: Command line remark: option '-MP' not supported if (grep 'ignoring option' conftest.err || grep 'not supported' conftest.err) >/dev/null 2>&1; then :; else am_cv_CC_dependencies_compiler_type=$depmode break fi fi done cd .. rm -rf conftest.dir else am_cv_CC_dependencies_compiler_type=none fi fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $am_cv_CC_dependencies_compiler_type" >&5 $as_echo "$am_cv_CC_dependencies_compiler_type" >&6; } CCDEPMODE=depmode=$am_cv_CC_dependencies_compiler_type if test "x$enable_dependency_tracking" != xno \ && test "$am_cv_CC_dependencies_compiler_type" = gcc3; then am__fastdepCC_TRUE= am__fastdepCC_FALSE='#' else am__fastdepCC_TRUE='#' am__fastdepCC_FALSE= fi # By default we simply use the C compiler to build assembly code. test "${CCAS+set}" = set || CCAS=$CC test "${CCASFLAGS+set}" = set || CCASFLAGS=$CFLAGS depcc="$CCAS" am_compiler_list= { $as_echo "$as_me:${as_lineno-$LINENO}: checking dependency style of $depcc" >&5 $as_echo_n "checking dependency style of $depcc... " >&6; } if ${am_cv_CCAS_dependencies_compiler_type+:} false; then : $as_echo_n "(cached) " >&6 else if test -z "$AMDEP_TRUE" && test -f "$am_depcomp"; then # We make a subdir and do the tests there. Otherwise we can end up # making bogus files that we don't know about and never remove. For # instance it was reported that on HP-UX the gcc test will end up # making a dummy file named `D' -- because `-MD' means `put the output # in D'. rm -rf conftest.dir mkdir conftest.dir # Copy depcomp to subdir because otherwise we won't find it if we're # using a relative directory. cp "$am_depcomp" conftest.dir cd conftest.dir # We will build objects and dependencies in a subdirectory because # it helps to detect inapplicable dependency modes. For instance # both Tru64's cc and ICC support -MD to output dependencies as a # side effect of compilation, but ICC will put the dependencies in # the current directory while Tru64 will put them in the object # directory. mkdir sub am_cv_CCAS_dependencies_compiler_type=none if test "$am_compiler_list" = ""; then am_compiler_list=`sed -n 's/^#*\([a-zA-Z0-9]*\))$/\1/p' < ./depcomp` fi am__universal=false for depmode in $am_compiler_list; do # Setup a source with many dependencies, because some compilers # like to wrap large dependency lists on column 80 (with \), and # we should not choose a depcomp mode which is confused by this. # # We need to recreate these files for each test, as the compiler may # overwrite some of them when testing with obscure command lines. # This happens at least with the AIX C compiler. : > sub/conftest.c for i in 1 2 3 4 5 6; do echo '#include "conftst'$i'.h"' >> sub/conftest.c # Using `: > sub/conftst$i.h' creates only sub/conftst1.h with # Solaris 8's {/usr,}/bin/sh. touch sub/conftst$i.h done echo "${am__include} ${am__quote}sub/conftest.Po${am__quote}" > confmf # We check with `-c' and `-o' for the sake of the "dashmstdout" # mode. It turns out that the SunPro C++ compiler does not properly # handle `-M -o', and we need to detect this. Also, some Intel # versions had trouble with output in subdirs am__obj=sub/conftest.${OBJEXT-o} am__minus_obj="-o $am__obj" case $depmode in gcc) # This depmode causes a compiler race in universal mode. test "$am__universal" = false || continue ;; nosideeffect) # after this tag, mechanisms are not by side-effect, so they'll # only be used when explicitly requested if test "x$enable_dependency_tracking" = xyes; then continue else break fi ;; msvc7 | msvc7msys | msvisualcpp | msvcmsys) # This compiler won't grok `-c -o', but also, the minuso test has # not run yet. These depmodes are late enough in the game, and # so weak that their functioning should not be impacted. am__obj=conftest.${OBJEXT-o} am__minus_obj= ;; none) break ;; esac if depmode=$depmode \ source=sub/conftest.c object=$am__obj \ depfile=sub/conftest.Po tmpdepfile=sub/conftest.TPo \ $SHELL ./depcomp $depcc -c $am__minus_obj sub/conftest.c \ >/dev/null 2>conftest.err && grep sub/conftst1.h sub/conftest.Po > /dev/null 2>&1 && grep sub/conftst6.h sub/conftest.Po > /dev/null 2>&1 && grep $am__obj sub/conftest.Po > /dev/null 2>&1 && ${MAKE-make} -s -f confmf > /dev/null 2>&1; then # icc doesn't choke on unknown options, it will just issue warnings # or remarks (even with -Werror). So we grep stderr for any message # that says an option was ignored or not supported. # When given -MP, icc 7.0 and 7.1 complain thusly: # icc: Command line warning: ignoring option '-M'; no argument required # The diagnosis changed in icc 8.0: # icc: Command line remark: option '-MP' not supported if (grep 'ignoring option' conftest.err || grep 'not supported' conftest.err) >/dev/null 2>&1; then :; else am_cv_CCAS_dependencies_compiler_type=$depmode break fi fi done cd .. rm -rf conftest.dir else am_cv_CCAS_dependencies_compiler_type=none fi fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $am_cv_CCAS_dependencies_compiler_type" >&5 $as_echo "$am_cv_CCAS_dependencies_compiler_type" >&6; } CCASDEPMODE=depmode=$am_cv_CCAS_dependencies_compiler_type if test "x$enable_dependency_tracking" != xno \ && test "$am_cv_CCAS_dependencies_compiler_type" = gcc3; then am__fastdepCCAS_TRUE= am__fastdepCCAS_FALSE='#' else am__fastdepCCAS_TRUE='#' am__fastdepCCAS_FALSE= fi if test "x$CC" != xcc; then { $as_echo "$as_me:${as_lineno-$LINENO}: checking whether $CC and cc understand -c and -o together" >&5 $as_echo_n "checking whether $CC and cc understand -c and -o together... " >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: checking whether cc understands -c and -o together" >&5 $as_echo_n "checking whether cc understands -c and -o together... " >&6; } fi set dummy $CC; ac_cc=`$as_echo "$2" | sed 's/[^a-zA-Z0-9_]/_/g;s/^[0-9]/_/'` if eval \${ac_cv_prog_cc_${ac_cc}_c_o+:} false; then : $as_echo_n "(cached) " >&6 else cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ int main () { ; return 0; } _ACEOF # Make sure it works both with $CC and with simple cc. # We do the test twice because some compilers refuse to overwrite an # existing .o file with -o, though they will create one. ac_try='$CC -c conftest.$ac_ext -o conftest2.$ac_objext >&5' rm -f conftest2.* if { { case "(($ac_try" in *\"* | *\`* | *\\*) ac_try_echo=\$ac_try;; *) ac_try_echo=$ac_try;; esac eval ac_try_echo="\"\$as_me:${as_lineno-$LINENO}: $ac_try_echo\"" $as_echo "$ac_try_echo"; } >&5 (eval "$ac_try") 2>&5 ac_status=$? $as_echo "$as_me:${as_lineno-$LINENO}: \$? = $ac_status" >&5 test $ac_status = 0; } && test -f conftest2.$ac_objext && { { case "(($ac_try" in *\"* | *\`* | *\\*) ac_try_echo=\$ac_try;; *) ac_try_echo=$ac_try;; esac eval ac_try_echo="\"\$as_me:${as_lineno-$LINENO}: $ac_try_echo\"" $as_echo "$ac_try_echo"; } >&5 (eval "$ac_try") 2>&5 ac_status=$? $as_echo "$as_me:${as_lineno-$LINENO}: \$? = $ac_status" >&5 test $ac_status = 0; }; then eval ac_cv_prog_cc_${ac_cc}_c_o=yes if test "x$CC" != xcc; then # Test first that cc exists at all. if { ac_try='cc -c conftest.$ac_ext >&5' { { case "(($ac_try" in *\"* | *\`* | *\\*) ac_try_echo=\$ac_try;; *) ac_try_echo=$ac_try;; esac eval ac_try_echo="\"\$as_me:${as_lineno-$LINENO}: $ac_try_echo\"" $as_echo "$ac_try_echo"; } >&5 (eval "$ac_try") 2>&5 ac_status=$? $as_echo "$as_me:${as_lineno-$LINENO}: \$? = $ac_status" >&5 test $ac_status = 0; }; }; then ac_try='cc -c conftest.$ac_ext -o conftest2.$ac_objext >&5' rm -f conftest2.* if { { case "(($ac_try" in *\"* | *\`* | *\\*) ac_try_echo=\$ac_try;; *) ac_try_echo=$ac_try;; esac eval ac_try_echo="\"\$as_me:${as_lineno-$LINENO}: $ac_try_echo\"" $as_echo "$ac_try_echo"; } >&5 (eval "$ac_try") 2>&5 ac_status=$? $as_echo "$as_me:${as_lineno-$LINENO}: \$? = $ac_status" >&5 test $ac_status = 0; } && test -f conftest2.$ac_objext && { { case "(($ac_try" in *\"* | *\`* | *\\*) ac_try_echo=\$ac_try;; *) ac_try_echo=$ac_try;; esac eval ac_try_echo="\"\$as_me:${as_lineno-$LINENO}: $ac_try_echo\"" $as_echo "$ac_try_echo"; } >&5 (eval "$ac_try") 2>&5 ac_status=$? $as_echo "$as_me:${as_lineno-$LINENO}: \$? = $ac_status" >&5 test $ac_status = 0; }; then # cc works too. : else # cc exists but doesn't like -o. eval ac_cv_prog_cc_${ac_cc}_c_o=no fi fi fi else eval ac_cv_prog_cc_${ac_cc}_c_o=no fi rm -f core conftest* fi if eval test \$ac_cv_prog_cc_${ac_cc}_c_o = yes; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: yes" >&5 $as_echo "yes" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } $as_echo "#define NO_MINUS_C_MINUS_O 1" >>confdefs.h fi # FIXME: we rely on the cache variable name because # there is no other way. set dummy $CC am_cc=`echo $2 | sed 's/[^a-zA-Z0-9_]/_/g;s/^[0-9]/_/'` eval am_t=\$ac_cv_prog_cc_${am_cc}_c_o if test "$am_t" != yes; then # Losing compiler, so override with the script. # FIXME: It is wrong to rewrite CC. # But if we don't then we get into trouble of one sort or another. # A longer-term fix would be to have automake use am__CC in this case, # and then we could set am__CC="\$(top_srcdir)/compile \$(CC)" CC="$am_aux_dir/compile $CC" fi case `pwd` in *\ * | *\ *) { $as_echo "$as_me:${as_lineno-$LINENO}: WARNING: Libtool does not cope well with whitespace in \`pwd\`" >&5 $as_echo "$as_me: WARNING: Libtool does not cope well with whitespace in \`pwd\`" >&2;} ;; esac macro_version='2.4.2' macro_revision='1.3337' ltmain="$ac_aux_dir/ltmain.sh" # Backslashify metacharacters that are still active within # double-quoted strings. sed_quote_subst='s/\(["`$\\]\)/\\\1/g' # Same as above, but do not quote variable references. double_quote_subst='s/\(["`\\]\)/\\\1/g' # Sed substitution to delay expansion of an escaped shell variable in a # double_quote_subst'ed string. delay_variable_subst='s/\\\\\\\\\\\$/\\\\\\$/g' # Sed substitution to delay expansion of an escaped single quote. delay_single_quote_subst='s/'\''/'\'\\\\\\\'\''/g' # Sed substitution to avoid accidental globbing in evaled expressions no_glob_subst='s/\*/\\\*/g' ECHO='\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\' ECHO=$ECHO$ECHO$ECHO$ECHO$ECHO ECHO=$ECHO$ECHO$ECHO$ECHO$ECHO$ECHO { $as_echo "$as_me:${as_lineno-$LINENO}: checking how to print strings" >&5 $as_echo_n "checking how to print strings... " >&6; } # Test print first, because it will be a builtin if present. if test "X`( print -r -- -n ) 2>/dev/null`" = X-n && \ test "X`print -r -- $ECHO 2>/dev/null`" = "X$ECHO"; then ECHO='print -r --' elif test "X`printf %s $ECHO 2>/dev/null`" = "X$ECHO"; then ECHO='printf %s\n' else # Use this function as a fallback that always works. func_fallback_echo () { eval 'cat <<_LTECHO_EOF $1 _LTECHO_EOF' } ECHO='func_fallback_echo' fi # func_echo_all arg... # Invoke $ECHO with all args, space-separated. func_echo_all () { $ECHO "" } case "$ECHO" in printf*) { $as_echo "$as_me:${as_lineno-$LINENO}: result: printf" >&5 $as_echo "printf" >&6; } ;; print*) { $as_echo "$as_me:${as_lineno-$LINENO}: result: print -r" >&5 $as_echo "print -r" >&6; } ;; *) { $as_echo "$as_me:${as_lineno-$LINENO}: result: cat" >&5 $as_echo "cat" >&6; } ;; esac { $as_echo "$as_me:${as_lineno-$LINENO}: checking for a sed that does not truncate output" >&5 $as_echo_n "checking for a sed that does not truncate output... " >&6; } if ${ac_cv_path_SED+:} false; then : $as_echo_n "(cached) " >&6 else ac_script=s/aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa/bbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbbb/ for ac_i in 1 2 3 4 5 6 7; do ac_script="$ac_script$as_nl$ac_script" done echo "$ac_script" 2>/dev/null | sed 99q >conftest.sed { ac_script=; unset ac_script;} if test -z "$SED"; then ac_path_SED_found=false # Loop through the user's path and test for each of PROGNAME-LIST as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_prog in sed gsed; do for ac_exec_ext in '' $ac_executable_extensions; do ac_path_SED="$as_dir/$ac_prog$ac_exec_ext" as_fn_executable_p "$ac_path_SED" || continue # Check for GNU ac_path_SED and select it if it is found. # Check for GNU $ac_path_SED case `"$ac_path_SED" --version 2>&1` in *GNU*) ac_cv_path_SED="$ac_path_SED" ac_path_SED_found=:;; *) ac_count=0 $as_echo_n 0123456789 >"conftest.in" while : do cat "conftest.in" "conftest.in" >"conftest.tmp" mv "conftest.tmp" "conftest.in" cp "conftest.in" "conftest.nl" $as_echo '' >> "conftest.nl" "$ac_path_SED" -f conftest.sed < "conftest.nl" >"conftest.out" 2>/dev/null || break diff "conftest.out" "conftest.nl" >/dev/null 2>&1 || break as_fn_arith $ac_count + 1 && ac_count=$as_val if test $ac_count -gt ${ac_path_SED_max-0}; then # Best one so far, save it but keep looking for a better one ac_cv_path_SED="$ac_path_SED" ac_path_SED_max=$ac_count fi # 10*(2^10) chars as input seems more than enough test $ac_count -gt 10 && break done rm -f conftest.in conftest.tmp conftest.nl conftest.out;; esac $ac_path_SED_found && break 3 done done done IFS=$as_save_IFS if test -z "$ac_cv_path_SED"; then as_fn_error $? "no acceptable sed could be found in \$PATH" "$LINENO" 5 fi else ac_cv_path_SED=$SED fi fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_cv_path_SED" >&5 $as_echo "$ac_cv_path_SED" >&6; } SED="$ac_cv_path_SED" rm -f conftest.sed test -z "$SED" && SED=sed Xsed="$SED -e 1s/^X//" { $as_echo "$as_me:${as_lineno-$LINENO}: checking for grep that handles long lines and -e" >&5 $as_echo_n "checking for grep that handles long lines and -e... " >&6; } if ${ac_cv_path_GREP+:} false; then : $as_echo_n "(cached) " >&6 else if test -z "$GREP"; then ac_path_GREP_found=false # Loop through the user's path and test for each of PROGNAME-LIST as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH$PATH_SEPARATOR/usr/xpg4/bin do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_prog in grep ggrep; do for ac_exec_ext in '' $ac_executable_extensions; do ac_path_GREP="$as_dir/$ac_prog$ac_exec_ext" as_fn_executable_p "$ac_path_GREP" || continue # Check for GNU ac_path_GREP and select it if it is found. # Check for GNU $ac_path_GREP case `"$ac_path_GREP" --version 2>&1` in *GNU*) ac_cv_path_GREP="$ac_path_GREP" ac_path_GREP_found=:;; *) ac_count=0 $as_echo_n 0123456789 >"conftest.in" while : do cat "conftest.in" "conftest.in" >"conftest.tmp" mv "conftest.tmp" "conftest.in" cp "conftest.in" "conftest.nl" $as_echo 'GREP' >> "conftest.nl" "$ac_path_GREP" -e 'GREP$' -e '-(cannot match)-' < "conftest.nl" >"conftest.out" 2>/dev/null || break diff "conftest.out" "conftest.nl" >/dev/null 2>&1 || break as_fn_arith $ac_count + 1 && ac_count=$as_val if test $ac_count -gt ${ac_path_GREP_max-0}; then # Best one so far, save it but keep looking for a better one ac_cv_path_GREP="$ac_path_GREP" ac_path_GREP_max=$ac_count fi # 10*(2^10) chars as input seems more than enough test $ac_count -gt 10 && break done rm -f conftest.in conftest.tmp conftest.nl conftest.out;; esac $ac_path_GREP_found && break 3 done done done IFS=$as_save_IFS if test -z "$ac_cv_path_GREP"; then as_fn_error $? "no acceptable grep could be found in $PATH$PATH_SEPARATOR/usr/xpg4/bin" "$LINENO" 5 fi else ac_cv_path_GREP=$GREP fi fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_cv_path_GREP" >&5 $as_echo "$ac_cv_path_GREP" >&6; } GREP="$ac_cv_path_GREP" { $as_echo "$as_me:${as_lineno-$LINENO}: checking for egrep" >&5 $as_echo_n "checking for egrep... " >&6; } if ${ac_cv_path_EGREP+:} false; then : $as_echo_n "(cached) " >&6 else if echo a | $GREP -E '(a|b)' >/dev/null 2>&1 then ac_cv_path_EGREP="$GREP -E" else if test -z "$EGREP"; then ac_path_EGREP_found=false # Loop through the user's path and test for each of PROGNAME-LIST as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH$PATH_SEPARATOR/usr/xpg4/bin do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_prog in egrep; do for ac_exec_ext in '' $ac_executable_extensions; do ac_path_EGREP="$as_dir/$ac_prog$ac_exec_ext" as_fn_executable_p "$ac_path_EGREP" || continue # Check for GNU ac_path_EGREP and select it if it is found. # Check for GNU $ac_path_EGREP case `"$ac_path_EGREP" --version 2>&1` in *GNU*) ac_cv_path_EGREP="$ac_path_EGREP" ac_path_EGREP_found=:;; *) ac_count=0 $as_echo_n 0123456789 >"conftest.in" while : do cat "conftest.in" "conftest.in" >"conftest.tmp" mv "conftest.tmp" "conftest.in" cp "conftest.in" "conftest.nl" $as_echo 'EGREP' >> "conftest.nl" "$ac_path_EGREP" 'EGREP$' < "conftest.nl" >"conftest.out" 2>/dev/null || break diff "conftest.out" "conftest.nl" >/dev/null 2>&1 || break as_fn_arith $ac_count + 1 && ac_count=$as_val if test $ac_count -gt ${ac_path_EGREP_max-0}; then # Best one so far, save it but keep looking for a better one ac_cv_path_EGREP="$ac_path_EGREP" ac_path_EGREP_max=$ac_count fi # 10*(2^10) chars as input seems more than enough test $ac_count -gt 10 && break done rm -f conftest.in conftest.tmp conftest.nl conftest.out;; esac $ac_path_EGREP_found && break 3 done done done IFS=$as_save_IFS if test -z "$ac_cv_path_EGREP"; then as_fn_error $? "no acceptable egrep could be found in $PATH$PATH_SEPARATOR/usr/xpg4/bin" "$LINENO" 5 fi else ac_cv_path_EGREP=$EGREP fi fi fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_cv_path_EGREP" >&5 $as_echo "$ac_cv_path_EGREP" >&6; } EGREP="$ac_cv_path_EGREP" { $as_echo "$as_me:${as_lineno-$LINENO}: checking for fgrep" >&5 $as_echo_n "checking for fgrep... " >&6; } if ${ac_cv_path_FGREP+:} false; then : $as_echo_n "(cached) " >&6 else if echo 'ab*c' | $GREP -F 'ab*c' >/dev/null 2>&1 then ac_cv_path_FGREP="$GREP -F" else if test -z "$FGREP"; then ac_path_FGREP_found=false # Loop through the user's path and test for each of PROGNAME-LIST as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH$PATH_SEPARATOR/usr/xpg4/bin do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_prog in fgrep; do for ac_exec_ext in '' $ac_executable_extensions; do ac_path_FGREP="$as_dir/$ac_prog$ac_exec_ext" as_fn_executable_p "$ac_path_FGREP" || continue # Check for GNU ac_path_FGREP and select it if it is found. # Check for GNU $ac_path_FGREP case `"$ac_path_FGREP" --version 2>&1` in *GNU*) ac_cv_path_FGREP="$ac_path_FGREP" ac_path_FGREP_found=:;; *) ac_count=0 $as_echo_n 0123456789 >"conftest.in" while : do cat "conftest.in" "conftest.in" >"conftest.tmp" mv "conftest.tmp" "conftest.in" cp "conftest.in" "conftest.nl" $as_echo 'FGREP' >> "conftest.nl" "$ac_path_FGREP" FGREP < "conftest.nl" >"conftest.out" 2>/dev/null || break diff "conftest.out" "conftest.nl" >/dev/null 2>&1 || break as_fn_arith $ac_count + 1 && ac_count=$as_val if test $ac_count -gt ${ac_path_FGREP_max-0}; then # Best one so far, save it but keep looking for a better one ac_cv_path_FGREP="$ac_path_FGREP" ac_path_FGREP_max=$ac_count fi # 10*(2^10) chars as input seems more than enough test $ac_count -gt 10 && break done rm -f conftest.in conftest.tmp conftest.nl conftest.out;; esac $ac_path_FGREP_found && break 3 done done done IFS=$as_save_IFS if test -z "$ac_cv_path_FGREP"; then as_fn_error $? "no acceptable fgrep could be found in $PATH$PATH_SEPARATOR/usr/xpg4/bin" "$LINENO" 5 fi else ac_cv_path_FGREP=$FGREP fi fi fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_cv_path_FGREP" >&5 $as_echo "$ac_cv_path_FGREP" >&6; } FGREP="$ac_cv_path_FGREP" test -z "$GREP" && GREP=grep # Check whether --with-gnu-ld was given. if test "${with_gnu_ld+set}" = set; then : withval=$with_gnu_ld; test "$withval" = no || with_gnu_ld=yes else with_gnu_ld=no fi ac_prog=ld if test "$GCC" = yes; then # Check if gcc -print-prog-name=ld gives a path. { $as_echo "$as_me:${as_lineno-$LINENO}: checking for ld used by $CC" >&5 $as_echo_n "checking for ld used by $CC... " >&6; } case $host in *-*-mingw*) # gcc leaves a trailing carriage return which upsets mingw ac_prog=`($CC -print-prog-name=ld) 2>&5 | tr -d '\015'` ;; *) ac_prog=`($CC -print-prog-name=ld) 2>&5` ;; esac case $ac_prog in # Accept absolute paths. [\\/]* | ?:[\\/]*) re_direlt='/[^/][^/]*/\.\./' # Canonicalize the pathname of ld ac_prog=`$ECHO "$ac_prog"| $SED 's%\\\\%/%g'` while $ECHO "$ac_prog" | $GREP "$re_direlt" > /dev/null 2>&1; do ac_prog=`$ECHO $ac_prog| $SED "s%$re_direlt%/%"` done test -z "$LD" && LD="$ac_prog" ;; "") # If it fails, then pretend we aren't using GCC. ac_prog=ld ;; *) # If it is relative, then search for the first ld in PATH. with_gnu_ld=unknown ;; esac elif test "$with_gnu_ld" = yes; then { $as_echo "$as_me:${as_lineno-$LINENO}: checking for GNU ld" >&5 $as_echo_n "checking for GNU ld... " >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: checking for non-GNU ld" >&5 $as_echo_n "checking for non-GNU ld... " >&6; } fi if ${lt_cv_path_LD+:} false; then : $as_echo_n "(cached) " >&6 else if test -z "$LD"; then lt_save_ifs="$IFS"; IFS=$PATH_SEPARATOR for ac_dir in $PATH; do IFS="$lt_save_ifs" test -z "$ac_dir" && ac_dir=. if test -f "$ac_dir/$ac_prog" || test -f "$ac_dir/$ac_prog$ac_exeext"; then lt_cv_path_LD="$ac_dir/$ac_prog" # Check to see if the program is GNU ld. I'd rather use --version, # but apparently some variants of GNU ld only accept -v. # Break only if it was the GNU/non-GNU ld that we prefer. case `"$lt_cv_path_LD" -v 2>&1 &5 $as_echo "$LD" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi test -z "$LD" && as_fn_error $? "no acceptable ld found in \$PATH" "$LINENO" 5 { $as_echo "$as_me:${as_lineno-$LINENO}: checking if the linker ($LD) is GNU ld" >&5 $as_echo_n "checking if the linker ($LD) is GNU ld... " >&6; } if ${lt_cv_prog_gnu_ld+:} false; then : $as_echo_n "(cached) " >&6 else # I'd rather use --version here, but apparently some GNU lds only accept -v. case `$LD -v 2>&1 &5 $as_echo "$lt_cv_prog_gnu_ld" >&6; } with_gnu_ld=$lt_cv_prog_gnu_ld { $as_echo "$as_me:${as_lineno-$LINENO}: checking for BSD- or MS-compatible name lister (nm)" >&5 $as_echo_n "checking for BSD- or MS-compatible name lister (nm)... " >&6; } if ${lt_cv_path_NM+:} false; then : $as_echo_n "(cached) " >&6 else if test -n "$NM"; then # Let the user override the test. lt_cv_path_NM="$NM" else lt_nm_to_check="${ac_tool_prefix}nm" if test -n "$ac_tool_prefix" && test "$build" = "$host"; then lt_nm_to_check="$lt_nm_to_check nm" fi for lt_tmp_nm in $lt_nm_to_check; do lt_save_ifs="$IFS"; IFS=$PATH_SEPARATOR for ac_dir in $PATH /usr/ccs/bin/elf /usr/ccs/bin /usr/ucb /bin; do IFS="$lt_save_ifs" test -z "$ac_dir" && ac_dir=. tmp_nm="$ac_dir/$lt_tmp_nm" if test -f "$tmp_nm" || test -f "$tmp_nm$ac_exeext" ; then # Check to see if the nm accepts a BSD-compat flag. # Adding the `sed 1q' prevents false positives on HP-UX, which says: # nm: unknown option "B" ignored # Tru64's nm complains that /dev/null is an invalid object file case `"$tmp_nm" -B /dev/null 2>&1 | sed '1q'` in */dev/null* | *'Invalid file or object type'*) lt_cv_path_NM="$tmp_nm -B" break ;; *) case `"$tmp_nm" -p /dev/null 2>&1 | sed '1q'` in */dev/null*) lt_cv_path_NM="$tmp_nm -p" break ;; *) lt_cv_path_NM=${lt_cv_path_NM="$tmp_nm"} # keep the first match, but continue # so that we can try to find one that supports BSD flags ;; esac ;; esac fi done IFS="$lt_save_ifs" done : ${lt_cv_path_NM=no} fi fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $lt_cv_path_NM" >&5 $as_echo "$lt_cv_path_NM" >&6; } if test "$lt_cv_path_NM" != "no"; then NM="$lt_cv_path_NM" else # Didn't find any BSD compatible name lister, look for dumpbin. if test -n "$DUMPBIN"; then : # Let the user override the test. else if test -n "$ac_tool_prefix"; then for ac_prog in dumpbin "link -dump" do # Extract the first word of "$ac_tool_prefix$ac_prog", so it can be a program name with args. set dummy $ac_tool_prefix$ac_prog; ac_word=$2 { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $ac_word" >&5 $as_echo_n "checking for $ac_word... " >&6; } if ${ac_cv_prog_DUMPBIN+:} false; then : $as_echo_n "(cached) " >&6 else if test -n "$DUMPBIN"; then ac_cv_prog_DUMPBIN="$DUMPBIN" # Let the user override the test. else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_exec_ext in '' $ac_executable_extensions; do if as_fn_executable_p "$as_dir/$ac_word$ac_exec_ext"; then ac_cv_prog_DUMPBIN="$ac_tool_prefix$ac_prog" $as_echo "$as_me:${as_lineno-$LINENO}: found $as_dir/$ac_word$ac_exec_ext" >&5 break 2 fi done done IFS=$as_save_IFS fi fi DUMPBIN=$ac_cv_prog_DUMPBIN if test -n "$DUMPBIN"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $DUMPBIN" >&5 $as_echo "$DUMPBIN" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi test -n "$DUMPBIN" && break done fi if test -z "$DUMPBIN"; then ac_ct_DUMPBIN=$DUMPBIN for ac_prog in dumpbin "link -dump" do # Extract the first word of "$ac_prog", so it can be a program name with args. set dummy $ac_prog; ac_word=$2 { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $ac_word" >&5 $as_echo_n "checking for $ac_word... " >&6; } if ${ac_cv_prog_ac_ct_DUMPBIN+:} false; then : $as_echo_n "(cached) " >&6 else if test -n "$ac_ct_DUMPBIN"; then ac_cv_prog_ac_ct_DUMPBIN="$ac_ct_DUMPBIN" # Let the user override the test. else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_exec_ext in '' $ac_executable_extensions; do if as_fn_executable_p "$as_dir/$ac_word$ac_exec_ext"; then ac_cv_prog_ac_ct_DUMPBIN="$ac_prog" $as_echo "$as_me:${as_lineno-$LINENO}: found $as_dir/$ac_word$ac_exec_ext" >&5 break 2 fi done done IFS=$as_save_IFS fi fi ac_ct_DUMPBIN=$ac_cv_prog_ac_ct_DUMPBIN if test -n "$ac_ct_DUMPBIN"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_ct_DUMPBIN" >&5 $as_echo "$ac_ct_DUMPBIN" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi test -n "$ac_ct_DUMPBIN" && break done if test "x$ac_ct_DUMPBIN" = x; then DUMPBIN=":" else case $cross_compiling:$ac_tool_warned in yes:) { $as_echo "$as_me:${as_lineno-$LINENO}: WARNING: using cross tools not prefixed with host triplet" >&5 $as_echo "$as_me: WARNING: using cross tools not prefixed with host triplet" >&2;} ac_tool_warned=yes ;; esac DUMPBIN=$ac_ct_DUMPBIN fi fi case `$DUMPBIN -symbols /dev/null 2>&1 | sed '1q'` in *COFF*) DUMPBIN="$DUMPBIN -symbols" ;; *) DUMPBIN=: ;; esac fi if test "$DUMPBIN" != ":"; then NM="$DUMPBIN" fi fi test -z "$NM" && NM=nm { $as_echo "$as_me:${as_lineno-$LINENO}: checking the name lister ($NM) interface" >&5 $as_echo_n "checking the name lister ($NM) interface... " >&6; } if ${lt_cv_nm_interface+:} false; then : $as_echo_n "(cached) " >&6 else lt_cv_nm_interface="BSD nm" echo "int some_variable = 0;" > conftest.$ac_ext (eval echo "\"\$as_me:$LINENO: $ac_compile\"" >&5) (eval "$ac_compile" 2>conftest.err) cat conftest.err >&5 (eval echo "\"\$as_me:$LINENO: $NM \\\"conftest.$ac_objext\\\"\"" >&5) (eval "$NM \"conftest.$ac_objext\"" 2>conftest.err > conftest.out) cat conftest.err >&5 (eval echo "\"\$as_me:$LINENO: output\"" >&5) cat conftest.out >&5 if $GREP 'External.*some_variable' conftest.out > /dev/null; then lt_cv_nm_interface="MS dumpbin" fi rm -f conftest* fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $lt_cv_nm_interface" >&5 $as_echo "$lt_cv_nm_interface" >&6; } { $as_echo "$as_me:${as_lineno-$LINENO}: checking whether ln -s works" >&5 $as_echo_n "checking whether ln -s works... " >&6; } LN_S=$as_ln_s if test "$LN_S" = "ln -s"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: yes" >&5 $as_echo "yes" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no, using $LN_S" >&5 $as_echo "no, using $LN_S" >&6; } fi # find the maximum length of command line arguments { $as_echo "$as_me:${as_lineno-$LINENO}: checking the maximum length of command line arguments" >&5 $as_echo_n "checking the maximum length of command line arguments... " >&6; } if ${lt_cv_sys_max_cmd_len+:} false; then : $as_echo_n "(cached) " >&6 else i=0 teststring="ABCD" case $build_os in msdosdjgpp*) # On DJGPP, this test can blow up pretty badly due to problems in libc # (any single argument exceeding 2000 bytes causes a buffer overrun # during glob expansion). Even if it were fixed, the result of this # check would be larger than it should be. lt_cv_sys_max_cmd_len=12288; # 12K is about right ;; gnu*) # Under GNU Hurd, this test is not required because there is # no limit to the length of command line arguments. # Libtool will interpret -1 as no limit whatsoever lt_cv_sys_max_cmd_len=-1; ;; cygwin* | mingw* | cegcc*) # On Win9x/ME, this test blows up -- it succeeds, but takes # about 5 minutes as the teststring grows exponentially. # Worse, since 9x/ME are not pre-emptively multitasking, # you end up with a "frozen" computer, even though with patience # the test eventually succeeds (with a max line length of 256k). # Instead, let's just punt: use the minimum linelength reported by # all of the supported platforms: 8192 (on NT/2K/XP). lt_cv_sys_max_cmd_len=8192; ;; mint*) # On MiNT this can take a long time and run out of memory. lt_cv_sys_max_cmd_len=8192; ;; amigaos*) # On AmigaOS with pdksh, this test takes hours, literally. # So we just punt and use a minimum line length of 8192. lt_cv_sys_max_cmd_len=8192; ;; netbsd* | freebsd* | openbsd* | darwin* | dragonfly*) # This has been around since 386BSD, at least. Likely further. if test -x /sbin/sysctl; then lt_cv_sys_max_cmd_len=`/sbin/sysctl -n kern.argmax` elif test -x /usr/sbin/sysctl; then lt_cv_sys_max_cmd_len=`/usr/sbin/sysctl -n kern.argmax` else lt_cv_sys_max_cmd_len=65536 # usable default for all BSDs fi # And add a safety zone lt_cv_sys_max_cmd_len=`expr $lt_cv_sys_max_cmd_len \/ 4` lt_cv_sys_max_cmd_len=`expr $lt_cv_sys_max_cmd_len \* 3` ;; interix*) # We know the value 262144 and hardcode it with a safety zone (like BSD) lt_cv_sys_max_cmd_len=196608 ;; os2*) # The test takes a long time on OS/2. lt_cv_sys_max_cmd_len=8192 ;; osf*) # Dr. Hans Ekkehard Plesser reports seeing a kernel panic running configure # due to this test when exec_disable_arg_limit is 1 on Tru64. It is not # nice to cause kernel panics so lets avoid the loop below. # First set a reasonable default. lt_cv_sys_max_cmd_len=16384 # if test -x /sbin/sysconfig; then case `/sbin/sysconfig -q proc exec_disable_arg_limit` in *1*) lt_cv_sys_max_cmd_len=-1 ;; esac fi ;; sco3.2v5*) lt_cv_sys_max_cmd_len=102400 ;; sysv5* | sco5v6* | sysv4.2uw2*) kargmax=`grep ARG_MAX /etc/conf/cf.d/stune 2>/dev/null` if test -n "$kargmax"; then lt_cv_sys_max_cmd_len=`echo $kargmax | sed 's/.*[ ]//'` else lt_cv_sys_max_cmd_len=32768 fi ;; *) lt_cv_sys_max_cmd_len=`(getconf ARG_MAX) 2> /dev/null` if test -n "$lt_cv_sys_max_cmd_len" && \ test undefined != "$lt_cv_sys_max_cmd_len"; then lt_cv_sys_max_cmd_len=`expr $lt_cv_sys_max_cmd_len \/ 4` lt_cv_sys_max_cmd_len=`expr $lt_cv_sys_max_cmd_len \* 3` else # Make teststring a little bigger before we do anything with it. # a 1K string should be a reasonable start. for i in 1 2 3 4 5 6 7 8 ; do teststring=$teststring$teststring done SHELL=${SHELL-${CONFIG_SHELL-/bin/sh}} # If test is not a shell built-in, we'll probably end up computing a # maximum length that is only half of the actual maximum length, but # we can't tell. while { test "X"`env echo "$teststring$teststring" 2>/dev/null` \ = "X$teststring$teststring"; } >/dev/null 2>&1 && test $i != 17 # 1/2 MB should be enough do i=`expr $i + 1` teststring=$teststring$teststring done # Only check the string length outside the loop. lt_cv_sys_max_cmd_len=`expr "X$teststring" : ".*" 2>&1` teststring= # Add a significant safety factor because C++ compilers can tack on # massive amounts of additional arguments before passing them to the # linker. It appears as though 1/2 is a usable value. lt_cv_sys_max_cmd_len=`expr $lt_cv_sys_max_cmd_len \/ 2` fi ;; esac fi if test -n $lt_cv_sys_max_cmd_len ; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $lt_cv_sys_max_cmd_len" >&5 $as_echo "$lt_cv_sys_max_cmd_len" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: none" >&5 $as_echo "none" >&6; } fi max_cmd_len=$lt_cv_sys_max_cmd_len : ${CP="cp -f"} : ${MV="mv -f"} : ${RM="rm -f"} { $as_echo "$as_me:${as_lineno-$LINENO}: checking whether the shell understands some XSI constructs" >&5 $as_echo_n "checking whether the shell understands some XSI constructs... " >&6; } # Try some XSI features xsi_shell=no ( _lt_dummy="a/b/c" test "${_lt_dummy##*/},${_lt_dummy%/*},${_lt_dummy#??}"${_lt_dummy%"$_lt_dummy"}, \ = c,a/b,b/c, \ && eval 'test $(( 1 + 1 )) -eq 2 \ && test "${#_lt_dummy}" -eq 5' ) >/dev/null 2>&1 \ && xsi_shell=yes { $as_echo "$as_me:${as_lineno-$LINENO}: result: $xsi_shell" >&5 $as_echo "$xsi_shell" >&6; } { $as_echo "$as_me:${as_lineno-$LINENO}: checking whether the shell understands \"+=\"" >&5 $as_echo_n "checking whether the shell understands \"+=\"... " >&6; } lt_shell_append=no ( foo=bar; set foo baz; eval "$1+=\$2" && test "$foo" = barbaz ) \ >/dev/null 2>&1 \ && lt_shell_append=yes { $as_echo "$as_me:${as_lineno-$LINENO}: result: $lt_shell_append" >&5 $as_echo "$lt_shell_append" >&6; } if ( (MAIL=60; unset MAIL) || exit) >/dev/null 2>&1; then lt_unset=unset else lt_unset=false fi # test EBCDIC or ASCII case `echo X|tr X '\101'` in A) # ASCII based system # \n is not interpreted correctly by Solaris 8 /usr/ucb/tr lt_SP2NL='tr \040 \012' lt_NL2SP='tr \015\012 \040\040' ;; *) # EBCDIC based system lt_SP2NL='tr \100 \n' lt_NL2SP='tr \r\n \100\100' ;; esac { $as_echo "$as_me:${as_lineno-$LINENO}: checking how to convert $build file names to $host format" >&5 $as_echo_n "checking how to convert $build file names to $host format... " >&6; } if ${lt_cv_to_host_file_cmd+:} false; then : $as_echo_n "(cached) " >&6 else case $host in *-*-mingw* ) case $build in *-*-mingw* ) # actually msys lt_cv_to_host_file_cmd=func_convert_file_msys_to_w32 ;; *-*-cygwin* ) lt_cv_to_host_file_cmd=func_convert_file_cygwin_to_w32 ;; * ) # otherwise, assume *nix lt_cv_to_host_file_cmd=func_convert_file_nix_to_w32 ;; esac ;; *-*-cygwin* ) case $build in *-*-mingw* ) # actually msys lt_cv_to_host_file_cmd=func_convert_file_msys_to_cygwin ;; *-*-cygwin* ) lt_cv_to_host_file_cmd=func_convert_file_noop ;; * ) # otherwise, assume *nix lt_cv_to_host_file_cmd=func_convert_file_nix_to_cygwin ;; esac ;; * ) # unhandled hosts (and "normal" native builds) lt_cv_to_host_file_cmd=func_convert_file_noop ;; esac fi to_host_file_cmd=$lt_cv_to_host_file_cmd { $as_echo "$as_me:${as_lineno-$LINENO}: result: $lt_cv_to_host_file_cmd" >&5 $as_echo "$lt_cv_to_host_file_cmd" >&6; } { $as_echo "$as_me:${as_lineno-$LINENO}: checking how to convert $build file names to toolchain format" >&5 $as_echo_n "checking how to convert $build file names to toolchain format... " >&6; } if ${lt_cv_to_tool_file_cmd+:} false; then : $as_echo_n "(cached) " >&6 else #assume ordinary cross tools, or native build. lt_cv_to_tool_file_cmd=func_convert_file_noop case $host in *-*-mingw* ) case $build in *-*-mingw* ) # actually msys lt_cv_to_tool_file_cmd=func_convert_file_msys_to_w32 ;; esac ;; esac fi to_tool_file_cmd=$lt_cv_to_tool_file_cmd { $as_echo "$as_me:${as_lineno-$LINENO}: result: $lt_cv_to_tool_file_cmd" >&5 $as_echo "$lt_cv_to_tool_file_cmd" >&6; } { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $LD option to reload object files" >&5 $as_echo_n "checking for $LD option to reload object files... " >&6; } if ${lt_cv_ld_reload_flag+:} false; then : $as_echo_n "(cached) " >&6 else lt_cv_ld_reload_flag='-r' fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $lt_cv_ld_reload_flag" >&5 $as_echo "$lt_cv_ld_reload_flag" >&6; } reload_flag=$lt_cv_ld_reload_flag case $reload_flag in "" | " "*) ;; *) reload_flag=" $reload_flag" ;; esac reload_cmds='$LD$reload_flag -o $output$reload_objs' case $host_os in cygwin* | mingw* | pw32* | cegcc*) if test "$GCC" != yes; then reload_cmds=false fi ;; darwin*) if test "$GCC" = yes; then reload_cmds='$LTCC $LTCFLAGS -nostdlib ${wl}-r -o $output$reload_objs' else reload_cmds='$LD$reload_flag -o $output$reload_objs' fi ;; esac if test -n "$ac_tool_prefix"; then # Extract the first word of "${ac_tool_prefix}objdump", so it can be a program name with args. set dummy ${ac_tool_prefix}objdump; ac_word=$2 { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $ac_word" >&5 $as_echo_n "checking for $ac_word... " >&6; } if ${ac_cv_prog_OBJDUMP+:} false; then : $as_echo_n "(cached) " >&6 else if test -n "$OBJDUMP"; then ac_cv_prog_OBJDUMP="$OBJDUMP" # Let the user override the test. else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_exec_ext in '' $ac_executable_extensions; do if as_fn_executable_p "$as_dir/$ac_word$ac_exec_ext"; then ac_cv_prog_OBJDUMP="${ac_tool_prefix}objdump" $as_echo "$as_me:${as_lineno-$LINENO}: found $as_dir/$ac_word$ac_exec_ext" >&5 break 2 fi done done IFS=$as_save_IFS fi fi OBJDUMP=$ac_cv_prog_OBJDUMP if test -n "$OBJDUMP"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $OBJDUMP" >&5 $as_echo "$OBJDUMP" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi fi if test -z "$ac_cv_prog_OBJDUMP"; then ac_ct_OBJDUMP=$OBJDUMP # Extract the first word of "objdump", so it can be a program name with args. set dummy objdump; ac_word=$2 { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $ac_word" >&5 $as_echo_n "checking for $ac_word... " >&6; } if ${ac_cv_prog_ac_ct_OBJDUMP+:} false; then : $as_echo_n "(cached) " >&6 else if test -n "$ac_ct_OBJDUMP"; then ac_cv_prog_ac_ct_OBJDUMP="$ac_ct_OBJDUMP" # Let the user override the test. else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_exec_ext in '' $ac_executable_extensions; do if as_fn_executable_p "$as_dir/$ac_word$ac_exec_ext"; then ac_cv_prog_ac_ct_OBJDUMP="objdump" $as_echo "$as_me:${as_lineno-$LINENO}: found $as_dir/$ac_word$ac_exec_ext" >&5 break 2 fi done done IFS=$as_save_IFS fi fi ac_ct_OBJDUMP=$ac_cv_prog_ac_ct_OBJDUMP if test -n "$ac_ct_OBJDUMP"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_ct_OBJDUMP" >&5 $as_echo "$ac_ct_OBJDUMP" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi if test "x$ac_ct_OBJDUMP" = x; then OBJDUMP="false" else case $cross_compiling:$ac_tool_warned in yes:) { $as_echo "$as_me:${as_lineno-$LINENO}: WARNING: using cross tools not prefixed with host triplet" >&5 $as_echo "$as_me: WARNING: using cross tools not prefixed with host triplet" >&2;} ac_tool_warned=yes ;; esac OBJDUMP=$ac_ct_OBJDUMP fi else OBJDUMP="$ac_cv_prog_OBJDUMP" fi test -z "$OBJDUMP" && OBJDUMP=objdump { $as_echo "$as_me:${as_lineno-$LINENO}: checking how to recognize dependent libraries" >&5 $as_echo_n "checking how to recognize dependent libraries... " >&6; } if ${lt_cv_deplibs_check_method+:} false; then : $as_echo_n "(cached) " >&6 else lt_cv_file_magic_cmd='$MAGIC_CMD' lt_cv_file_magic_test_file= lt_cv_deplibs_check_method='unknown' # Need to set the preceding variable on all platforms that support # interlibrary dependencies. # 'none' -- dependencies not supported. # `unknown' -- same as none, but documents that we really don't know. # 'pass_all' -- all dependencies passed with no checks. # 'test_compile' -- check by making test program. # 'file_magic [[regex]]' -- check by looking for files in library path # which responds to the $file_magic_cmd with a given extended regex. # If you have `file' or equivalent on your system and you're not sure # whether `pass_all' will *always* work, you probably want this one. case $host_os in aix[4-9]*) lt_cv_deplibs_check_method=pass_all ;; beos*) lt_cv_deplibs_check_method=pass_all ;; bsdi[45]*) lt_cv_deplibs_check_method='file_magic ELF [0-9][0-9]*-bit [ML]SB (shared object|dynamic lib)' lt_cv_file_magic_cmd='/usr/bin/file -L' lt_cv_file_magic_test_file=/shlib/libc.so ;; cygwin*) # func_win32_libid is a shell function defined in ltmain.sh lt_cv_deplibs_check_method='file_magic ^x86 archive import|^x86 DLL' lt_cv_file_magic_cmd='func_win32_libid' ;; mingw* | pw32*) # Base MSYS/MinGW do not provide the 'file' command needed by # func_win32_libid shell function, so use a weaker test based on 'objdump', # unless we find 'file', for example because we are cross-compiling. # func_win32_libid assumes BSD nm, so disallow it if using MS dumpbin. if ( test "$lt_cv_nm_interface" = "BSD nm" && file / ) >/dev/null 2>&1; then lt_cv_deplibs_check_method='file_magic ^x86 archive import|^x86 DLL' lt_cv_file_magic_cmd='func_win32_libid' else # Keep this pattern in sync with the one in func_win32_libid. lt_cv_deplibs_check_method='file_magic file format (pei*-i386(.*architecture: i386)?|pe-arm-wince|pe-x86-64)' lt_cv_file_magic_cmd='$OBJDUMP -f' fi ;; cegcc*) # use the weaker test based on 'objdump'. See mingw*. lt_cv_deplibs_check_method='file_magic file format pe-arm-.*little(.*architecture: arm)?' lt_cv_file_magic_cmd='$OBJDUMP -f' ;; darwin* | rhapsody*) lt_cv_deplibs_check_method=pass_all ;; freebsd* | dragonfly*) if echo __ELF__ | $CC -E - | $GREP __ELF__ > /dev/null; then case $host_cpu in i*86 ) # Not sure whether the presence of OpenBSD here was a mistake. # Let's accept both of them until this is cleared up. lt_cv_deplibs_check_method='file_magic (FreeBSD|OpenBSD|DragonFly)/i[3-9]86 (compact )?demand paged shared library' lt_cv_file_magic_cmd=/usr/bin/file lt_cv_file_magic_test_file=`echo /usr/lib/libc.so.*` ;; esac else lt_cv_deplibs_check_method=pass_all fi ;; haiku*) lt_cv_deplibs_check_method=pass_all ;; hpux10.20* | hpux11*) lt_cv_file_magic_cmd=/usr/bin/file case $host_cpu in ia64*) lt_cv_deplibs_check_method='file_magic (s[0-9][0-9][0-9]|ELF-[0-9][0-9]) shared object file - IA64' lt_cv_file_magic_test_file=/usr/lib/hpux32/libc.so ;; hppa*64*) lt_cv_deplibs_check_method='file_magic (s[0-9][0-9][0-9]|ELF[ -][0-9][0-9])(-bit)?( [LM]SB)? shared object( file)?[, -]* PA-RISC [0-9]\.[0-9]' lt_cv_file_magic_test_file=/usr/lib/pa20_64/libc.sl ;; *) lt_cv_deplibs_check_method='file_magic (s[0-9][0-9][0-9]|PA-RISC[0-9]\.[0-9]) shared library' lt_cv_file_magic_test_file=/usr/lib/libc.sl ;; esac ;; interix[3-9]*) # PIC code is broken on Interix 3.x, that's why |\.a not |_pic\.a here lt_cv_deplibs_check_method='match_pattern /lib[^/]+(\.so|\.a)$' ;; irix5* | irix6* | nonstopux*) case $LD in *-32|*"-32 ") libmagic=32-bit;; *-n32|*"-n32 ") libmagic=N32;; *-64|*"-64 ") libmagic=64-bit;; *) libmagic=never-match;; esac lt_cv_deplibs_check_method=pass_all ;; # This must be glibc/ELF. linux* | k*bsd*-gnu | kopensolaris*-gnu | gnu*) lt_cv_deplibs_check_method=pass_all ;; netbsd* | netbsdelf*-gnu) if echo __ELF__ | $CC -E - | $GREP __ELF__ > /dev/null; then lt_cv_deplibs_check_method='match_pattern /lib[^/]+(\.so\.[0-9]+\.[0-9]+|_pic\.a)$' else lt_cv_deplibs_check_method='match_pattern /lib[^/]+(\.so|_pic\.a)$' fi ;; newos6*) lt_cv_deplibs_check_method='file_magic ELF [0-9][0-9]*-bit [ML]SB (executable|dynamic lib)' lt_cv_file_magic_cmd=/usr/bin/file lt_cv_file_magic_test_file=/usr/lib/libnls.so ;; *nto* | *qnx*) lt_cv_deplibs_check_method=pass_all ;; openbsd*) if test -z "`echo __ELF__ | $CC -E - | $GREP __ELF__`" || test "$host_os-$host_cpu" = "openbsd2.8-powerpc"; then lt_cv_deplibs_check_method='match_pattern /lib[^/]+(\.so\.[0-9]+\.[0-9]+|\.so|_pic\.a)$' else lt_cv_deplibs_check_method='match_pattern /lib[^/]+(\.so\.[0-9]+\.[0-9]+|_pic\.a)$' fi ;; osf3* | osf4* | osf5*) lt_cv_deplibs_check_method=pass_all ;; rdos*) lt_cv_deplibs_check_method=pass_all ;; solaris*) lt_cv_deplibs_check_method=pass_all ;; sysv5* | sco3.2v5* | sco5v6* | unixware* | OpenUNIX* | sysv4*uw2*) lt_cv_deplibs_check_method=pass_all ;; sysv4 | sysv4.3*) case $host_vendor in motorola) lt_cv_deplibs_check_method='file_magic ELF [0-9][0-9]*-bit [ML]SB (shared object|dynamic lib) M[0-9][0-9]* Version [0-9]' lt_cv_file_magic_test_file=`echo /usr/lib/libc.so*` ;; ncr) lt_cv_deplibs_check_method=pass_all ;; sequent) lt_cv_file_magic_cmd='/bin/file' lt_cv_deplibs_check_method='file_magic ELF [0-9][0-9]*-bit [LM]SB (shared object|dynamic lib )' ;; sni) lt_cv_file_magic_cmd='/bin/file' lt_cv_deplibs_check_method="file_magic ELF [0-9][0-9]*-bit [LM]SB dynamic lib" lt_cv_file_magic_test_file=/lib/libc.so ;; siemens) lt_cv_deplibs_check_method=pass_all ;; pc) lt_cv_deplibs_check_method=pass_all ;; esac ;; tpf*) lt_cv_deplibs_check_method=pass_all ;; esac fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $lt_cv_deplibs_check_method" >&5 $as_echo "$lt_cv_deplibs_check_method" >&6; } file_magic_glob= want_nocaseglob=no if test "$build" = "$host"; then case $host_os in mingw* | pw32*) if ( shopt | grep nocaseglob ) >/dev/null 2>&1; then want_nocaseglob=yes else file_magic_glob=`echo aAbBcCdDeEfFgGhHiIjJkKlLmMnNoOpPqQrRsStTuUvVwWxXyYzZ | $SED -e "s/\(..\)/s\/[\1]\/[\1]\/g;/g"` fi ;; esac fi file_magic_cmd=$lt_cv_file_magic_cmd deplibs_check_method=$lt_cv_deplibs_check_method test -z "$deplibs_check_method" && deplibs_check_method=unknown if test -n "$ac_tool_prefix"; then # Extract the first word of "${ac_tool_prefix}dlltool", so it can be a program name with args. set dummy ${ac_tool_prefix}dlltool; ac_word=$2 { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $ac_word" >&5 $as_echo_n "checking for $ac_word... " >&6; } if ${ac_cv_prog_DLLTOOL+:} false; then : $as_echo_n "(cached) " >&6 else if test -n "$DLLTOOL"; then ac_cv_prog_DLLTOOL="$DLLTOOL" # Let the user override the test. else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_exec_ext in '' $ac_executable_extensions; do if as_fn_executable_p "$as_dir/$ac_word$ac_exec_ext"; then ac_cv_prog_DLLTOOL="${ac_tool_prefix}dlltool" $as_echo "$as_me:${as_lineno-$LINENO}: found $as_dir/$ac_word$ac_exec_ext" >&5 break 2 fi done done IFS=$as_save_IFS fi fi DLLTOOL=$ac_cv_prog_DLLTOOL if test -n "$DLLTOOL"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $DLLTOOL" >&5 $as_echo "$DLLTOOL" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi fi if test -z "$ac_cv_prog_DLLTOOL"; then ac_ct_DLLTOOL=$DLLTOOL # Extract the first word of "dlltool", so it can be a program name with args. set dummy dlltool; ac_word=$2 { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $ac_word" >&5 $as_echo_n "checking for $ac_word... " >&6; } if ${ac_cv_prog_ac_ct_DLLTOOL+:} false; then : $as_echo_n "(cached) " >&6 else if test -n "$ac_ct_DLLTOOL"; then ac_cv_prog_ac_ct_DLLTOOL="$ac_ct_DLLTOOL" # Let the user override the test. else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_exec_ext in '' $ac_executable_extensions; do if as_fn_executable_p "$as_dir/$ac_word$ac_exec_ext"; then ac_cv_prog_ac_ct_DLLTOOL="dlltool" $as_echo "$as_me:${as_lineno-$LINENO}: found $as_dir/$ac_word$ac_exec_ext" >&5 break 2 fi done done IFS=$as_save_IFS fi fi ac_ct_DLLTOOL=$ac_cv_prog_ac_ct_DLLTOOL if test -n "$ac_ct_DLLTOOL"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_ct_DLLTOOL" >&5 $as_echo "$ac_ct_DLLTOOL" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi if test "x$ac_ct_DLLTOOL" = x; then DLLTOOL="false" else case $cross_compiling:$ac_tool_warned in yes:) { $as_echo "$as_me:${as_lineno-$LINENO}: WARNING: using cross tools not prefixed with host triplet" >&5 $as_echo "$as_me: WARNING: using cross tools not prefixed with host triplet" >&2;} ac_tool_warned=yes ;; esac DLLTOOL=$ac_ct_DLLTOOL fi else DLLTOOL="$ac_cv_prog_DLLTOOL" fi test -z "$DLLTOOL" && DLLTOOL=dlltool { $as_echo "$as_me:${as_lineno-$LINENO}: checking how to associate runtime and link libraries" >&5 $as_echo_n "checking how to associate runtime and link libraries... " >&6; } if ${lt_cv_sharedlib_from_linklib_cmd+:} false; then : $as_echo_n "(cached) " >&6 else lt_cv_sharedlib_from_linklib_cmd='unknown' case $host_os in cygwin* | mingw* | pw32* | cegcc*) # two different shell functions defined in ltmain.sh # decide which to use based on capabilities of $DLLTOOL case `$DLLTOOL --help 2>&1` in *--identify-strict*) lt_cv_sharedlib_from_linklib_cmd=func_cygming_dll_for_implib ;; *) lt_cv_sharedlib_from_linklib_cmd=func_cygming_dll_for_implib_fallback ;; esac ;; *) # fallback: assume linklib IS sharedlib lt_cv_sharedlib_from_linklib_cmd="$ECHO" ;; esac fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $lt_cv_sharedlib_from_linklib_cmd" >&5 $as_echo "$lt_cv_sharedlib_from_linklib_cmd" >&6; } sharedlib_from_linklib_cmd=$lt_cv_sharedlib_from_linklib_cmd test -z "$sharedlib_from_linklib_cmd" && sharedlib_from_linklib_cmd=$ECHO if test -n "$ac_tool_prefix"; then for ac_prog in ar do # Extract the first word of "$ac_tool_prefix$ac_prog", so it can be a program name with args. set dummy $ac_tool_prefix$ac_prog; ac_word=$2 { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $ac_word" >&5 $as_echo_n "checking for $ac_word... " >&6; } if ${ac_cv_prog_AR+:} false; then : $as_echo_n "(cached) " >&6 else if test -n "$AR"; then ac_cv_prog_AR="$AR" # Let the user override the test. else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_exec_ext in '' $ac_executable_extensions; do if as_fn_executable_p "$as_dir/$ac_word$ac_exec_ext"; then ac_cv_prog_AR="$ac_tool_prefix$ac_prog" $as_echo "$as_me:${as_lineno-$LINENO}: found $as_dir/$ac_word$ac_exec_ext" >&5 break 2 fi done done IFS=$as_save_IFS fi fi AR=$ac_cv_prog_AR if test -n "$AR"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $AR" >&5 $as_echo "$AR" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi test -n "$AR" && break done fi if test -z "$AR"; then ac_ct_AR=$AR for ac_prog in ar do # Extract the first word of "$ac_prog", so it can be a program name with args. set dummy $ac_prog; ac_word=$2 { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $ac_word" >&5 $as_echo_n "checking for $ac_word... " >&6; } if ${ac_cv_prog_ac_ct_AR+:} false; then : $as_echo_n "(cached) " >&6 else if test -n "$ac_ct_AR"; then ac_cv_prog_ac_ct_AR="$ac_ct_AR" # Let the user override the test. else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_exec_ext in '' $ac_executable_extensions; do if as_fn_executable_p "$as_dir/$ac_word$ac_exec_ext"; then ac_cv_prog_ac_ct_AR="$ac_prog" $as_echo "$as_me:${as_lineno-$LINENO}: found $as_dir/$ac_word$ac_exec_ext" >&5 break 2 fi done done IFS=$as_save_IFS fi fi ac_ct_AR=$ac_cv_prog_ac_ct_AR if test -n "$ac_ct_AR"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_ct_AR" >&5 $as_echo "$ac_ct_AR" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi test -n "$ac_ct_AR" && break done if test "x$ac_ct_AR" = x; then AR="false" else case $cross_compiling:$ac_tool_warned in yes:) { $as_echo "$as_me:${as_lineno-$LINENO}: WARNING: using cross tools not prefixed with host triplet" >&5 $as_echo "$as_me: WARNING: using cross tools not prefixed with host triplet" >&2;} ac_tool_warned=yes ;; esac AR=$ac_ct_AR fi fi : ${AR=ar} : ${AR_FLAGS=cru} { $as_echo "$as_me:${as_lineno-$LINENO}: checking for archiver @FILE support" >&5 $as_echo_n "checking for archiver @FILE support... " >&6; } if ${lt_cv_ar_at_file+:} false; then : $as_echo_n "(cached) " >&6 else lt_cv_ar_at_file=no cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ int main () { ; return 0; } _ACEOF if ac_fn_c_try_compile "$LINENO"; then : echo conftest.$ac_objext > conftest.lst lt_ar_try='$AR $AR_FLAGS libconftest.a @conftest.lst >&5' { { eval echo "\"\$as_me\":${as_lineno-$LINENO}: \"$lt_ar_try\""; } >&5 (eval $lt_ar_try) 2>&5 ac_status=$? $as_echo "$as_me:${as_lineno-$LINENO}: \$? = $ac_status" >&5 test $ac_status = 0; } if test "$ac_status" -eq 0; then # Ensure the archiver fails upon bogus file names. rm -f conftest.$ac_objext libconftest.a { { eval echo "\"\$as_me\":${as_lineno-$LINENO}: \"$lt_ar_try\""; } >&5 (eval $lt_ar_try) 2>&5 ac_status=$? $as_echo "$as_me:${as_lineno-$LINENO}: \$? = $ac_status" >&5 test $ac_status = 0; } if test "$ac_status" -ne 0; then lt_cv_ar_at_file=@ fi fi rm -f conftest.* libconftest.a fi rm -f core conftest.err conftest.$ac_objext conftest.$ac_ext fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $lt_cv_ar_at_file" >&5 $as_echo "$lt_cv_ar_at_file" >&6; } if test "x$lt_cv_ar_at_file" = xno; then archiver_list_spec= else archiver_list_spec=$lt_cv_ar_at_file fi if test -n "$ac_tool_prefix"; then # Extract the first word of "${ac_tool_prefix}strip", so it can be a program name with args. set dummy ${ac_tool_prefix}strip; ac_word=$2 { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $ac_word" >&5 $as_echo_n "checking for $ac_word... " >&6; } if ${ac_cv_prog_STRIP+:} false; then : $as_echo_n "(cached) " >&6 else if test -n "$STRIP"; then ac_cv_prog_STRIP="$STRIP" # Let the user override the test. else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_exec_ext in '' $ac_executable_extensions; do if as_fn_executable_p "$as_dir/$ac_word$ac_exec_ext"; then ac_cv_prog_STRIP="${ac_tool_prefix}strip" $as_echo "$as_me:${as_lineno-$LINENO}: found $as_dir/$ac_word$ac_exec_ext" >&5 break 2 fi done done IFS=$as_save_IFS fi fi STRIP=$ac_cv_prog_STRIP if test -n "$STRIP"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $STRIP" >&5 $as_echo "$STRIP" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi fi if test -z "$ac_cv_prog_STRIP"; then ac_ct_STRIP=$STRIP # Extract the first word of "strip", so it can be a program name with args. set dummy strip; ac_word=$2 { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $ac_word" >&5 $as_echo_n "checking for $ac_word... " >&6; } if ${ac_cv_prog_ac_ct_STRIP+:} false; then : $as_echo_n "(cached) " >&6 else if test -n "$ac_ct_STRIP"; then ac_cv_prog_ac_ct_STRIP="$ac_ct_STRIP" # Let the user override the test. else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_exec_ext in '' $ac_executable_extensions; do if as_fn_executable_p "$as_dir/$ac_word$ac_exec_ext"; then ac_cv_prog_ac_ct_STRIP="strip" $as_echo "$as_me:${as_lineno-$LINENO}: found $as_dir/$ac_word$ac_exec_ext" >&5 break 2 fi done done IFS=$as_save_IFS fi fi ac_ct_STRIP=$ac_cv_prog_ac_ct_STRIP if test -n "$ac_ct_STRIP"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_ct_STRIP" >&5 $as_echo "$ac_ct_STRIP" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi if test "x$ac_ct_STRIP" = x; then STRIP=":" else case $cross_compiling:$ac_tool_warned in yes:) { $as_echo "$as_me:${as_lineno-$LINENO}: WARNING: using cross tools not prefixed with host triplet" >&5 $as_echo "$as_me: WARNING: using cross tools not prefixed with host triplet" >&2;} ac_tool_warned=yes ;; esac STRIP=$ac_ct_STRIP fi else STRIP="$ac_cv_prog_STRIP" fi test -z "$STRIP" && STRIP=: if test -n "$ac_tool_prefix"; then # Extract the first word of "${ac_tool_prefix}ranlib", so it can be a program name with args. set dummy ${ac_tool_prefix}ranlib; ac_word=$2 { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $ac_word" >&5 $as_echo_n "checking for $ac_word... " >&6; } if ${ac_cv_prog_RANLIB+:} false; then : $as_echo_n "(cached) " >&6 else if test -n "$RANLIB"; then ac_cv_prog_RANLIB="$RANLIB" # Let the user override the test. else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_exec_ext in '' $ac_executable_extensions; do if as_fn_executable_p "$as_dir/$ac_word$ac_exec_ext"; then ac_cv_prog_RANLIB="${ac_tool_prefix}ranlib" $as_echo "$as_me:${as_lineno-$LINENO}: found $as_dir/$ac_word$ac_exec_ext" >&5 break 2 fi done done IFS=$as_save_IFS fi fi RANLIB=$ac_cv_prog_RANLIB if test -n "$RANLIB"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $RANLIB" >&5 $as_echo "$RANLIB" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi fi if test -z "$ac_cv_prog_RANLIB"; then ac_ct_RANLIB=$RANLIB # Extract the first word of "ranlib", so it can be a program name with args. set dummy ranlib; ac_word=$2 { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $ac_word" >&5 $as_echo_n "checking for $ac_word... " >&6; } if ${ac_cv_prog_ac_ct_RANLIB+:} false; then : $as_echo_n "(cached) " >&6 else if test -n "$ac_ct_RANLIB"; then ac_cv_prog_ac_ct_RANLIB="$ac_ct_RANLIB" # Let the user override the test. else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_exec_ext in '' $ac_executable_extensions; do if as_fn_executable_p "$as_dir/$ac_word$ac_exec_ext"; then ac_cv_prog_ac_ct_RANLIB="ranlib" $as_echo "$as_me:${as_lineno-$LINENO}: found $as_dir/$ac_word$ac_exec_ext" >&5 break 2 fi done done IFS=$as_save_IFS fi fi ac_ct_RANLIB=$ac_cv_prog_ac_ct_RANLIB if test -n "$ac_ct_RANLIB"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_ct_RANLIB" >&5 $as_echo "$ac_ct_RANLIB" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi if test "x$ac_ct_RANLIB" = x; then RANLIB=":" else case $cross_compiling:$ac_tool_warned in yes:) { $as_echo "$as_me:${as_lineno-$LINENO}: WARNING: using cross tools not prefixed with host triplet" >&5 $as_echo "$as_me: WARNING: using cross tools not prefixed with host triplet" >&2;} ac_tool_warned=yes ;; esac RANLIB=$ac_ct_RANLIB fi else RANLIB="$ac_cv_prog_RANLIB" fi test -z "$RANLIB" && RANLIB=: # Determine commands to create old-style static archives. old_archive_cmds='$AR $AR_FLAGS $oldlib$oldobjs' old_postinstall_cmds='chmod 644 $oldlib' old_postuninstall_cmds= if test -n "$RANLIB"; then case $host_os in openbsd*) old_postinstall_cmds="$old_postinstall_cmds~\$RANLIB -t \$tool_oldlib" ;; *) old_postinstall_cmds="$old_postinstall_cmds~\$RANLIB \$tool_oldlib" ;; esac old_archive_cmds="$old_archive_cmds~\$RANLIB \$tool_oldlib" fi case $host_os in darwin*) lock_old_archive_extraction=yes ;; *) lock_old_archive_extraction=no ;; esac # If no C compiler was specified, use CC. LTCC=${LTCC-"$CC"} # If no C compiler flags were specified, use CFLAGS. LTCFLAGS=${LTCFLAGS-"$CFLAGS"} # Allow CC to be a program name with arguments. compiler=$CC # Check for command to grab the raw symbol name followed by C symbol from nm. { $as_echo "$as_me:${as_lineno-$LINENO}: checking command to parse $NM output from $compiler object" >&5 $as_echo_n "checking command to parse $NM output from $compiler object... " >&6; } if ${lt_cv_sys_global_symbol_pipe+:} false; then : $as_echo_n "(cached) " >&6 else # These are sane defaults that work on at least a few old systems. # [They come from Ultrix. What could be older than Ultrix?!! ;)] # Character class describing NM global symbol codes. symcode='[BCDEGRST]' # Regexp to match symbols that can be accessed directly from C. sympat='\([_A-Za-z][_A-Za-z0-9]*\)' # Define system-specific variables. case $host_os in aix*) symcode='[BCDT]' ;; cygwin* | mingw* | pw32* | cegcc*) symcode='[ABCDGISTW]' ;; hpux*) if test "$host_cpu" = ia64; then symcode='[ABCDEGRST]' fi ;; irix* | nonstopux*) symcode='[BCDEGRST]' ;; osf*) symcode='[BCDEGQRST]' ;; solaris*) symcode='[BDRT]' ;; sco3.2v5*) symcode='[DT]' ;; sysv4.2uw2*) symcode='[DT]' ;; sysv5* | sco5v6* | unixware* | OpenUNIX*) symcode='[ABDT]' ;; sysv4) symcode='[DFNSTU]' ;; esac # If we're using GNU nm, then use its standard symbol codes. case `$NM -V 2>&1` in *GNU* | *'with BFD'*) symcode='[ABCDGIRSTW]' ;; esac # Transform an extracted symbol line into a proper C declaration. # Some systems (esp. on ia64) link data and code symbols differently, # so use this general approach. lt_cv_sys_global_symbol_to_cdecl="sed -n -e 's/^T .* \(.*\)$/extern int \1();/p' -e 's/^$symcode* .* \(.*\)$/extern char \1;/p'" # Transform an extracted symbol line into symbol name and symbol address lt_cv_sys_global_symbol_to_c_name_address="sed -n -e 's/^: \([^ ]*\)[ ]*$/ {\\\"\1\\\", (void *) 0},/p' -e 's/^$symcode* \([^ ]*\) \([^ ]*\)$/ {\"\2\", (void *) \&\2},/p'" lt_cv_sys_global_symbol_to_c_name_address_lib_prefix="sed -n -e 's/^: \([^ ]*\)[ ]*$/ {\\\"\1\\\", (void *) 0},/p' -e 's/^$symcode* \([^ ]*\) \(lib[^ ]*\)$/ {\"\2\", (void *) \&\2},/p' -e 's/^$symcode* \([^ ]*\) \([^ ]*\)$/ {\"lib\2\", (void *) \&\2},/p'" # Handle CRLF in mingw tool chain opt_cr= case $build_os in mingw*) opt_cr=`$ECHO 'x\{0,1\}' | tr x '\015'` # option cr in regexp ;; esac # Try without a prefix underscore, then with it. for ac_symprfx in "" "_"; do # Transform symcode, sympat, and symprfx into a raw symbol and a C symbol. symxfrm="\\1 $ac_symprfx\\2 \\2" # Write the raw and C identifiers. if test "$lt_cv_nm_interface" = "MS dumpbin"; then # Fake it for dumpbin and say T for any non-static function # and D for any global variable. # Also find C++ and __fastcall symbols from MSVC++, # which start with @ or ?. lt_cv_sys_global_symbol_pipe="$AWK '"\ " {last_section=section; section=\$ 3};"\ " /^COFF SYMBOL TABLE/{for(i in hide) delete hide[i]};"\ " /Section length .*#relocs.*(pick any)/{hide[last_section]=1};"\ " \$ 0!~/External *\|/{next};"\ " / 0+ UNDEF /{next}; / UNDEF \([^|]\)*()/{next};"\ " {if(hide[section]) next};"\ " {f=0}; \$ 0~/\(\).*\|/{f=1}; {printf f ? \"T \" : \"D \"};"\ " {split(\$ 0, a, /\||\r/); split(a[2], s)};"\ " s[1]~/^[@?]/{print s[1], s[1]; next};"\ " s[1]~prfx {split(s[1],t,\"@\"); print t[1], substr(t[1],length(prfx))}"\ " ' prfx=^$ac_symprfx" else lt_cv_sys_global_symbol_pipe="sed -n -e 's/^.*[ ]\($symcode$symcode*\)[ ][ ]*$ac_symprfx$sympat$opt_cr$/$symxfrm/p'" fi lt_cv_sys_global_symbol_pipe="$lt_cv_sys_global_symbol_pipe | sed '/ __gnu_lto/d'" # Check to see that the pipe works correctly. pipe_works=no rm -f conftest* cat > conftest.$ac_ext <<_LT_EOF #ifdef __cplusplus extern "C" { #endif char nm_test_var; void nm_test_func(void); void nm_test_func(void){} #ifdef __cplusplus } #endif int main(){nm_test_var='a';nm_test_func();return(0);} _LT_EOF if { { eval echo "\"\$as_me\":${as_lineno-$LINENO}: \"$ac_compile\""; } >&5 (eval $ac_compile) 2>&5 ac_status=$? $as_echo "$as_me:${as_lineno-$LINENO}: \$? = $ac_status" >&5 test $ac_status = 0; }; then # Now try to grab the symbols. nlist=conftest.nm if { { eval echo "\"\$as_me\":${as_lineno-$LINENO}: \"$NM conftest.$ac_objext \| "$lt_cv_sys_global_symbol_pipe" \> $nlist\""; } >&5 (eval $NM conftest.$ac_objext \| "$lt_cv_sys_global_symbol_pipe" \> $nlist) 2>&5 ac_status=$? $as_echo "$as_me:${as_lineno-$LINENO}: \$? = $ac_status" >&5 test $ac_status = 0; } && test -s "$nlist"; then # Try sorting and uniquifying the output. if sort "$nlist" | uniq > "$nlist"T; then mv -f "$nlist"T "$nlist" else rm -f "$nlist"T fi # Make sure that we snagged all the symbols we need. if $GREP ' nm_test_var$' "$nlist" >/dev/null; then if $GREP ' nm_test_func$' "$nlist" >/dev/null; then cat <<_LT_EOF > conftest.$ac_ext /* Keep this code in sync between libtool.m4, ltmain, lt_system.h, and tests. */ #if defined(_WIN32) || defined(__CYGWIN__) || defined(_WIN32_WCE) /* DATA imports from DLLs on WIN32 con't be const, because runtime relocations are performed -- see ld's documentation on pseudo-relocs. */ # define LT_DLSYM_CONST #elif defined(__osf__) /* This system does not cope well with relocations in const data. */ # define LT_DLSYM_CONST #else # define LT_DLSYM_CONST const #endif #ifdef __cplusplus extern "C" { #endif _LT_EOF # Now generate the symbol file. eval "$lt_cv_sys_global_symbol_to_cdecl"' < "$nlist" | $GREP -v main >> conftest.$ac_ext' cat <<_LT_EOF >> conftest.$ac_ext /* The mapping between symbol names and symbols. */ LT_DLSYM_CONST struct { const char *name; void *address; } lt__PROGRAM__LTX_preloaded_symbols[] = { { "@PROGRAM@", (void *) 0 }, _LT_EOF $SED "s/^$symcode$symcode* \(.*\) \(.*\)$/ {\"\2\", (void *) \&\2},/" < "$nlist" | $GREP -v main >> conftest.$ac_ext cat <<\_LT_EOF >> conftest.$ac_ext {0, (void *) 0} }; /* This works around a problem in FreeBSD linker */ #ifdef FREEBSD_WORKAROUND static const void *lt_preloaded_setup() { return lt__PROGRAM__LTX_preloaded_symbols; } #endif #ifdef __cplusplus } #endif _LT_EOF # Now try linking the two files. mv conftest.$ac_objext conftstm.$ac_objext lt_globsym_save_LIBS=$LIBS lt_globsym_save_CFLAGS=$CFLAGS LIBS="conftstm.$ac_objext" CFLAGS="$CFLAGS$lt_prog_compiler_no_builtin_flag" if { { eval echo "\"\$as_me\":${as_lineno-$LINENO}: \"$ac_link\""; } >&5 (eval $ac_link) 2>&5 ac_status=$? $as_echo "$as_me:${as_lineno-$LINENO}: \$? = $ac_status" >&5 test $ac_status = 0; } && test -s conftest${ac_exeext}; then pipe_works=yes fi LIBS=$lt_globsym_save_LIBS CFLAGS=$lt_globsym_save_CFLAGS else echo "cannot find nm_test_func in $nlist" >&5 fi else echo "cannot find nm_test_var in $nlist" >&5 fi else echo "cannot run $lt_cv_sys_global_symbol_pipe" >&5 fi else echo "$progname: failed program was:" >&5 cat conftest.$ac_ext >&5 fi rm -rf conftest* conftst* # Do not use the global_symbol_pipe unless it works. if test "$pipe_works" = yes; then break else lt_cv_sys_global_symbol_pipe= fi done fi if test -z "$lt_cv_sys_global_symbol_pipe"; then lt_cv_sys_global_symbol_to_cdecl= fi if test -z "$lt_cv_sys_global_symbol_pipe$lt_cv_sys_global_symbol_to_cdecl"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: failed" >&5 $as_echo "failed" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: ok" >&5 $as_echo "ok" >&6; } fi # Response file support. if test "$lt_cv_nm_interface" = "MS dumpbin"; then nm_file_list_spec='@' elif $NM --help 2>/dev/null | grep '[@]FILE' >/dev/null; then nm_file_list_spec='@' fi { $as_echo "$as_me:${as_lineno-$LINENO}: checking for sysroot" >&5 $as_echo_n "checking for sysroot... " >&6; } # Check whether --with-sysroot was given. if test "${with_sysroot+set}" = set; then : withval=$with_sysroot; else with_sysroot=no fi lt_sysroot= case ${with_sysroot} in #( yes) if test "$GCC" = yes; then lt_sysroot=`$CC --print-sysroot 2>/dev/null` fi ;; #( /*) lt_sysroot=`echo "$with_sysroot" | sed -e "$sed_quote_subst"` ;; #( no|'') ;; #( *) { $as_echo "$as_me:${as_lineno-$LINENO}: result: ${with_sysroot}" >&5 $as_echo "${with_sysroot}" >&6; } as_fn_error $? "The sysroot must be an absolute path." "$LINENO" 5 ;; esac { $as_echo "$as_me:${as_lineno-$LINENO}: result: ${lt_sysroot:-no}" >&5 $as_echo "${lt_sysroot:-no}" >&6; } # Check whether --enable-libtool-lock was given. if test "${enable_libtool_lock+set}" = set; then : enableval=$enable_libtool_lock; fi test "x$enable_libtool_lock" != xno && enable_libtool_lock=yes # Some flags need to be propagated to the compiler or linker for good # libtool support. case $host in ia64-*-hpux*) # Find out which ABI we are using. echo 'int i;' > conftest.$ac_ext if { { eval echo "\"\$as_me\":${as_lineno-$LINENO}: \"$ac_compile\""; } >&5 (eval $ac_compile) 2>&5 ac_status=$? $as_echo "$as_me:${as_lineno-$LINENO}: \$? = $ac_status" >&5 test $ac_status = 0; }; then case `/usr/bin/file conftest.$ac_objext` in *ELF-32*) HPUX_IA64_MODE="32" ;; *ELF-64*) HPUX_IA64_MODE="64" ;; esac fi rm -rf conftest* ;; *-*-irix6*) # Find out which ABI we are using. echo '#line '$LINENO' "configure"' > conftest.$ac_ext if { { eval echo "\"\$as_me\":${as_lineno-$LINENO}: \"$ac_compile\""; } >&5 (eval $ac_compile) 2>&5 ac_status=$? $as_echo "$as_me:${as_lineno-$LINENO}: \$? = $ac_status" >&5 test $ac_status = 0; }; then if test "$lt_cv_prog_gnu_ld" = yes; then case `/usr/bin/file conftest.$ac_objext` in *32-bit*) LD="${LD-ld} -melf32bsmip" ;; *N32*) LD="${LD-ld} -melf32bmipn32" ;; *64-bit*) LD="${LD-ld} -melf64bmip" ;; esac else case `/usr/bin/file conftest.$ac_objext` in *32-bit*) LD="${LD-ld} -32" ;; *N32*) LD="${LD-ld} -n32" ;; *64-bit*) LD="${LD-ld} -64" ;; esac fi fi rm -rf conftest* ;; x86_64-*kfreebsd*-gnu|x86_64-*linux*|ppc*-*linux*|powerpc*-*linux*| \ s390*-*linux*|s390*-*tpf*|sparc*-*linux*) # Find out which ABI we are using. echo 'int i;' > conftest.$ac_ext if { { eval echo "\"\$as_me\":${as_lineno-$LINENO}: \"$ac_compile\""; } >&5 (eval $ac_compile) 2>&5 ac_status=$? $as_echo "$as_me:${as_lineno-$LINENO}: \$? = $ac_status" >&5 test $ac_status = 0; }; then case `/usr/bin/file conftest.o` in *32-bit*) case $host in x86_64-*kfreebsd*-gnu) LD="${LD-ld} -m elf_i386_fbsd" ;; x86_64-*linux*) case `/usr/bin/file conftest.o` in *x86-64*) LD="${LD-ld} -m elf32_x86_64" ;; *) LD="${LD-ld} -m elf_i386" ;; esac ;; ppc64-*linux*|powerpc64-*linux*) LD="${LD-ld} -m elf32ppclinux" ;; s390x-*linux*) LD="${LD-ld} -m elf_s390" ;; sparc64-*linux*) LD="${LD-ld} -m elf32_sparc" ;; esac ;; *64-bit*) case $host in x86_64-*kfreebsd*-gnu) LD="${LD-ld} -m elf_x86_64_fbsd" ;; x86_64-*linux*) LD="${LD-ld} -m elf_x86_64" ;; ppc*-*linux*|powerpc*-*linux*) LD="${LD-ld} -m elf64ppc" ;; s390*-*linux*|s390*-*tpf*) LD="${LD-ld} -m elf64_s390" ;; sparc*-*linux*) LD="${LD-ld} -m elf64_sparc" ;; esac ;; esac fi rm -rf conftest* ;; *-*-sco3.2v5*) # On SCO OpenServer 5, we need -belf to get full-featured binaries. SAVE_CFLAGS="$CFLAGS" CFLAGS="$CFLAGS -belf" { $as_echo "$as_me:${as_lineno-$LINENO}: checking whether the C compiler needs -belf" >&5 $as_echo_n "checking whether the C compiler needs -belf... " >&6; } if ${lt_cv_cc_needs_belf+:} false; then : $as_echo_n "(cached) " >&6 else ac_ext=c ac_cpp='$CPP $CPPFLAGS' ac_compile='$CC -c $CFLAGS $CPPFLAGS conftest.$ac_ext >&5' ac_link='$CC -o conftest$ac_exeext $CFLAGS $CPPFLAGS $LDFLAGS conftest.$ac_ext $LIBS >&5' ac_compiler_gnu=$ac_cv_c_compiler_gnu cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ int main () { ; return 0; } _ACEOF if ac_fn_c_try_link "$LINENO"; then : lt_cv_cc_needs_belf=yes else lt_cv_cc_needs_belf=no fi rm -f core conftest.err conftest.$ac_objext \ conftest$ac_exeext conftest.$ac_ext ac_ext=c ac_cpp='$CPP $CPPFLAGS' ac_compile='$CC -c $CFLAGS $CPPFLAGS conftest.$ac_ext >&5' ac_link='$CC -o conftest$ac_exeext $CFLAGS $CPPFLAGS $LDFLAGS conftest.$ac_ext $LIBS >&5' ac_compiler_gnu=$ac_cv_c_compiler_gnu fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $lt_cv_cc_needs_belf" >&5 $as_echo "$lt_cv_cc_needs_belf" >&6; } if test x"$lt_cv_cc_needs_belf" != x"yes"; then # this is probably gcc 2.8.0, egcs 1.0 or newer; no need for -belf CFLAGS="$SAVE_CFLAGS" fi ;; *-*solaris*) # Find out which ABI we are using. echo 'int i;' > conftest.$ac_ext if { { eval echo "\"\$as_me\":${as_lineno-$LINENO}: \"$ac_compile\""; } >&5 (eval $ac_compile) 2>&5 ac_status=$? $as_echo "$as_me:${as_lineno-$LINENO}: \$? = $ac_status" >&5 test $ac_status = 0; }; then case `/usr/bin/file conftest.o` in *64-bit*) case $lt_cv_prog_gnu_ld in yes*) case $host in i?86-*-solaris*) LD="${LD-ld} -m elf_x86_64" ;; sparc*-*-solaris*) LD="${LD-ld} -m elf64_sparc" ;; esac # GNU ld 2.21 introduced _sol2 emulations. Use them if available. if ${LD-ld} -V | grep _sol2 >/dev/null 2>&1; then LD="${LD-ld}_sol2" fi ;; *) if ${LD-ld} -64 -r -o conftest2.o conftest.o >/dev/null 2>&1; then LD="${LD-ld} -64" fi ;; esac ;; esac fi rm -rf conftest* ;; esac need_locks="$enable_libtool_lock" if test -n "$ac_tool_prefix"; then # Extract the first word of "${ac_tool_prefix}mt", so it can be a program name with args. set dummy ${ac_tool_prefix}mt; ac_word=$2 { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $ac_word" >&5 $as_echo_n "checking for $ac_word... " >&6; } if ${ac_cv_prog_MANIFEST_TOOL+:} false; then : $as_echo_n "(cached) " >&6 else if test -n "$MANIFEST_TOOL"; then ac_cv_prog_MANIFEST_TOOL="$MANIFEST_TOOL" # Let the user override the test. else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_exec_ext in '' $ac_executable_extensions; do if as_fn_executable_p "$as_dir/$ac_word$ac_exec_ext"; then ac_cv_prog_MANIFEST_TOOL="${ac_tool_prefix}mt" $as_echo "$as_me:${as_lineno-$LINENO}: found $as_dir/$ac_word$ac_exec_ext" >&5 break 2 fi done done IFS=$as_save_IFS fi fi MANIFEST_TOOL=$ac_cv_prog_MANIFEST_TOOL if test -n "$MANIFEST_TOOL"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $MANIFEST_TOOL" >&5 $as_echo "$MANIFEST_TOOL" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi fi if test -z "$ac_cv_prog_MANIFEST_TOOL"; then ac_ct_MANIFEST_TOOL=$MANIFEST_TOOL # Extract the first word of "mt", so it can be a program name with args. set dummy mt; ac_word=$2 { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $ac_word" >&5 $as_echo_n "checking for $ac_word... " >&6; } if ${ac_cv_prog_ac_ct_MANIFEST_TOOL+:} false; then : $as_echo_n "(cached) " >&6 else if test -n "$ac_ct_MANIFEST_TOOL"; then ac_cv_prog_ac_ct_MANIFEST_TOOL="$ac_ct_MANIFEST_TOOL" # Let the user override the test. else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_exec_ext in '' $ac_executable_extensions; do if as_fn_executable_p "$as_dir/$ac_word$ac_exec_ext"; then ac_cv_prog_ac_ct_MANIFEST_TOOL="mt" $as_echo "$as_me:${as_lineno-$LINENO}: found $as_dir/$ac_word$ac_exec_ext" >&5 break 2 fi done done IFS=$as_save_IFS fi fi ac_ct_MANIFEST_TOOL=$ac_cv_prog_ac_ct_MANIFEST_TOOL if test -n "$ac_ct_MANIFEST_TOOL"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_ct_MANIFEST_TOOL" >&5 $as_echo "$ac_ct_MANIFEST_TOOL" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi if test "x$ac_ct_MANIFEST_TOOL" = x; then MANIFEST_TOOL=":" else case $cross_compiling:$ac_tool_warned in yes:) { $as_echo "$as_me:${as_lineno-$LINENO}: WARNING: using cross tools not prefixed with host triplet" >&5 $as_echo "$as_me: WARNING: using cross tools not prefixed with host triplet" >&2;} ac_tool_warned=yes ;; esac MANIFEST_TOOL=$ac_ct_MANIFEST_TOOL fi else MANIFEST_TOOL="$ac_cv_prog_MANIFEST_TOOL" fi test -z "$MANIFEST_TOOL" && MANIFEST_TOOL=mt { $as_echo "$as_me:${as_lineno-$LINENO}: checking if $MANIFEST_TOOL is a manifest tool" >&5 $as_echo_n "checking if $MANIFEST_TOOL is a manifest tool... " >&6; } if ${lt_cv_path_mainfest_tool+:} false; then : $as_echo_n "(cached) " >&6 else lt_cv_path_mainfest_tool=no echo "$as_me:$LINENO: $MANIFEST_TOOL '-?'" >&5 $MANIFEST_TOOL '-?' 2>conftest.err > conftest.out cat conftest.err >&5 if $GREP 'Manifest Tool' conftest.out > /dev/null; then lt_cv_path_mainfest_tool=yes fi rm -f conftest* fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $lt_cv_path_mainfest_tool" >&5 $as_echo "$lt_cv_path_mainfest_tool" >&6; } if test "x$lt_cv_path_mainfest_tool" != xyes; then MANIFEST_TOOL=: fi case $host_os in rhapsody* | darwin*) if test -n "$ac_tool_prefix"; then # Extract the first word of "${ac_tool_prefix}dsymutil", so it can be a program name with args. set dummy ${ac_tool_prefix}dsymutil; ac_word=$2 { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $ac_word" >&5 $as_echo_n "checking for $ac_word... " >&6; } if ${ac_cv_prog_DSYMUTIL+:} false; then : $as_echo_n "(cached) " >&6 else if test -n "$DSYMUTIL"; then ac_cv_prog_DSYMUTIL="$DSYMUTIL" # Let the user override the test. else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_exec_ext in '' $ac_executable_extensions; do if as_fn_executable_p "$as_dir/$ac_word$ac_exec_ext"; then ac_cv_prog_DSYMUTIL="${ac_tool_prefix}dsymutil" $as_echo "$as_me:${as_lineno-$LINENO}: found $as_dir/$ac_word$ac_exec_ext" >&5 break 2 fi done done IFS=$as_save_IFS fi fi DSYMUTIL=$ac_cv_prog_DSYMUTIL if test -n "$DSYMUTIL"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $DSYMUTIL" >&5 $as_echo "$DSYMUTIL" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi fi if test -z "$ac_cv_prog_DSYMUTIL"; then ac_ct_DSYMUTIL=$DSYMUTIL # Extract the first word of "dsymutil", so it can be a program name with args. set dummy dsymutil; ac_word=$2 { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $ac_word" >&5 $as_echo_n "checking for $ac_word... " >&6; } if ${ac_cv_prog_ac_ct_DSYMUTIL+:} false; then : $as_echo_n "(cached) " >&6 else if test -n "$ac_ct_DSYMUTIL"; then ac_cv_prog_ac_ct_DSYMUTIL="$ac_ct_DSYMUTIL" # Let the user override the test. else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_exec_ext in '' $ac_executable_extensions; do if as_fn_executable_p "$as_dir/$ac_word$ac_exec_ext"; then ac_cv_prog_ac_ct_DSYMUTIL="dsymutil" $as_echo "$as_me:${as_lineno-$LINENO}: found $as_dir/$ac_word$ac_exec_ext" >&5 break 2 fi done done IFS=$as_save_IFS fi fi ac_ct_DSYMUTIL=$ac_cv_prog_ac_ct_DSYMUTIL if test -n "$ac_ct_DSYMUTIL"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_ct_DSYMUTIL" >&5 $as_echo "$ac_ct_DSYMUTIL" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi if test "x$ac_ct_DSYMUTIL" = x; then DSYMUTIL=":" else case $cross_compiling:$ac_tool_warned in yes:) { $as_echo "$as_me:${as_lineno-$LINENO}: WARNING: using cross tools not prefixed with host triplet" >&5 $as_echo "$as_me: WARNING: using cross tools not prefixed with host triplet" >&2;} ac_tool_warned=yes ;; esac DSYMUTIL=$ac_ct_DSYMUTIL fi else DSYMUTIL="$ac_cv_prog_DSYMUTIL" fi if test -n "$ac_tool_prefix"; then # Extract the first word of "${ac_tool_prefix}nmedit", so it can be a program name with args. set dummy ${ac_tool_prefix}nmedit; ac_word=$2 { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $ac_word" >&5 $as_echo_n "checking for $ac_word... " >&6; } if ${ac_cv_prog_NMEDIT+:} false; then : $as_echo_n "(cached) " >&6 else if test -n "$NMEDIT"; then ac_cv_prog_NMEDIT="$NMEDIT" # Let the user override the test. else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_exec_ext in '' $ac_executable_extensions; do if as_fn_executable_p "$as_dir/$ac_word$ac_exec_ext"; then ac_cv_prog_NMEDIT="${ac_tool_prefix}nmedit" $as_echo "$as_me:${as_lineno-$LINENO}: found $as_dir/$ac_word$ac_exec_ext" >&5 break 2 fi done done IFS=$as_save_IFS fi fi NMEDIT=$ac_cv_prog_NMEDIT if test -n "$NMEDIT"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $NMEDIT" >&5 $as_echo "$NMEDIT" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi fi if test -z "$ac_cv_prog_NMEDIT"; then ac_ct_NMEDIT=$NMEDIT # Extract the first word of "nmedit", so it can be a program name with args. set dummy nmedit; ac_word=$2 { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $ac_word" >&5 $as_echo_n "checking for $ac_word... " >&6; } if ${ac_cv_prog_ac_ct_NMEDIT+:} false; then : $as_echo_n "(cached) " >&6 else if test -n "$ac_ct_NMEDIT"; then ac_cv_prog_ac_ct_NMEDIT="$ac_ct_NMEDIT" # Let the user override the test. else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_exec_ext in '' $ac_executable_extensions; do if as_fn_executable_p "$as_dir/$ac_word$ac_exec_ext"; then ac_cv_prog_ac_ct_NMEDIT="nmedit" $as_echo "$as_me:${as_lineno-$LINENO}: found $as_dir/$ac_word$ac_exec_ext" >&5 break 2 fi done done IFS=$as_save_IFS fi fi ac_ct_NMEDIT=$ac_cv_prog_ac_ct_NMEDIT if test -n "$ac_ct_NMEDIT"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_ct_NMEDIT" >&5 $as_echo "$ac_ct_NMEDIT" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi if test "x$ac_ct_NMEDIT" = x; then NMEDIT=":" else case $cross_compiling:$ac_tool_warned in yes:) { $as_echo "$as_me:${as_lineno-$LINENO}: WARNING: using cross tools not prefixed with host triplet" >&5 $as_echo "$as_me: WARNING: using cross tools not prefixed with host triplet" >&2;} ac_tool_warned=yes ;; esac NMEDIT=$ac_ct_NMEDIT fi else NMEDIT="$ac_cv_prog_NMEDIT" fi if test -n "$ac_tool_prefix"; then # Extract the first word of "${ac_tool_prefix}lipo", so it can be a program name with args. set dummy ${ac_tool_prefix}lipo; ac_word=$2 { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $ac_word" >&5 $as_echo_n "checking for $ac_word... " >&6; } if ${ac_cv_prog_LIPO+:} false; then : $as_echo_n "(cached) " >&6 else if test -n "$LIPO"; then ac_cv_prog_LIPO="$LIPO" # Let the user override the test. else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_exec_ext in '' $ac_executable_extensions; do if as_fn_executable_p "$as_dir/$ac_word$ac_exec_ext"; then ac_cv_prog_LIPO="${ac_tool_prefix}lipo" $as_echo "$as_me:${as_lineno-$LINENO}: found $as_dir/$ac_word$ac_exec_ext" >&5 break 2 fi done done IFS=$as_save_IFS fi fi LIPO=$ac_cv_prog_LIPO if test -n "$LIPO"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $LIPO" >&5 $as_echo "$LIPO" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi fi if test -z "$ac_cv_prog_LIPO"; then ac_ct_LIPO=$LIPO # Extract the first word of "lipo", so it can be a program name with args. set dummy lipo; ac_word=$2 { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $ac_word" >&5 $as_echo_n "checking for $ac_word... " >&6; } if ${ac_cv_prog_ac_ct_LIPO+:} false; then : $as_echo_n "(cached) " >&6 else if test -n "$ac_ct_LIPO"; then ac_cv_prog_ac_ct_LIPO="$ac_ct_LIPO" # Let the user override the test. else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_exec_ext in '' $ac_executable_extensions; do if as_fn_executable_p "$as_dir/$ac_word$ac_exec_ext"; then ac_cv_prog_ac_ct_LIPO="lipo" $as_echo "$as_me:${as_lineno-$LINENO}: found $as_dir/$ac_word$ac_exec_ext" >&5 break 2 fi done done IFS=$as_save_IFS fi fi ac_ct_LIPO=$ac_cv_prog_ac_ct_LIPO if test -n "$ac_ct_LIPO"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_ct_LIPO" >&5 $as_echo "$ac_ct_LIPO" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi if test "x$ac_ct_LIPO" = x; then LIPO=":" else case $cross_compiling:$ac_tool_warned in yes:) { $as_echo "$as_me:${as_lineno-$LINENO}: WARNING: using cross tools not prefixed with host triplet" >&5 $as_echo "$as_me: WARNING: using cross tools not prefixed with host triplet" >&2;} ac_tool_warned=yes ;; esac LIPO=$ac_ct_LIPO fi else LIPO="$ac_cv_prog_LIPO" fi if test -n "$ac_tool_prefix"; then # Extract the first word of "${ac_tool_prefix}otool", so it can be a program name with args. set dummy ${ac_tool_prefix}otool; ac_word=$2 { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $ac_word" >&5 $as_echo_n "checking for $ac_word... " >&6; } if ${ac_cv_prog_OTOOL+:} false; then : $as_echo_n "(cached) " >&6 else if test -n "$OTOOL"; then ac_cv_prog_OTOOL="$OTOOL" # Let the user override the test. else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_exec_ext in '' $ac_executable_extensions; do if as_fn_executable_p "$as_dir/$ac_word$ac_exec_ext"; then ac_cv_prog_OTOOL="${ac_tool_prefix}otool" $as_echo "$as_me:${as_lineno-$LINENO}: found $as_dir/$ac_word$ac_exec_ext" >&5 break 2 fi done done IFS=$as_save_IFS fi fi OTOOL=$ac_cv_prog_OTOOL if test -n "$OTOOL"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $OTOOL" >&5 $as_echo "$OTOOL" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi fi if test -z "$ac_cv_prog_OTOOL"; then ac_ct_OTOOL=$OTOOL # Extract the first word of "otool", so it can be a program name with args. set dummy otool; ac_word=$2 { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $ac_word" >&5 $as_echo_n "checking for $ac_word... " >&6; } if ${ac_cv_prog_ac_ct_OTOOL+:} false; then : $as_echo_n "(cached) " >&6 else if test -n "$ac_ct_OTOOL"; then ac_cv_prog_ac_ct_OTOOL="$ac_ct_OTOOL" # Let the user override the test. else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_exec_ext in '' $ac_executable_extensions; do if as_fn_executable_p "$as_dir/$ac_word$ac_exec_ext"; then ac_cv_prog_ac_ct_OTOOL="otool" $as_echo "$as_me:${as_lineno-$LINENO}: found $as_dir/$ac_word$ac_exec_ext" >&5 break 2 fi done done IFS=$as_save_IFS fi fi ac_ct_OTOOL=$ac_cv_prog_ac_ct_OTOOL if test -n "$ac_ct_OTOOL"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_ct_OTOOL" >&5 $as_echo "$ac_ct_OTOOL" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi if test "x$ac_ct_OTOOL" = x; then OTOOL=":" else case $cross_compiling:$ac_tool_warned in yes:) { $as_echo "$as_me:${as_lineno-$LINENO}: WARNING: using cross tools not prefixed with host triplet" >&5 $as_echo "$as_me: WARNING: using cross tools not prefixed with host triplet" >&2;} ac_tool_warned=yes ;; esac OTOOL=$ac_ct_OTOOL fi else OTOOL="$ac_cv_prog_OTOOL" fi if test -n "$ac_tool_prefix"; then # Extract the first word of "${ac_tool_prefix}otool64", so it can be a program name with args. set dummy ${ac_tool_prefix}otool64; ac_word=$2 { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $ac_word" >&5 $as_echo_n "checking for $ac_word... " >&6; } if ${ac_cv_prog_OTOOL64+:} false; then : $as_echo_n "(cached) " >&6 else if test -n "$OTOOL64"; then ac_cv_prog_OTOOL64="$OTOOL64" # Let the user override the test. else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_exec_ext in '' $ac_executable_extensions; do if as_fn_executable_p "$as_dir/$ac_word$ac_exec_ext"; then ac_cv_prog_OTOOL64="${ac_tool_prefix}otool64" $as_echo "$as_me:${as_lineno-$LINENO}: found $as_dir/$ac_word$ac_exec_ext" >&5 break 2 fi done done IFS=$as_save_IFS fi fi OTOOL64=$ac_cv_prog_OTOOL64 if test -n "$OTOOL64"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $OTOOL64" >&5 $as_echo "$OTOOL64" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi fi if test -z "$ac_cv_prog_OTOOL64"; then ac_ct_OTOOL64=$OTOOL64 # Extract the first word of "otool64", so it can be a program name with args. set dummy otool64; ac_word=$2 { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $ac_word" >&5 $as_echo_n "checking for $ac_word... " >&6; } if ${ac_cv_prog_ac_ct_OTOOL64+:} false; then : $as_echo_n "(cached) " >&6 else if test -n "$ac_ct_OTOOL64"; then ac_cv_prog_ac_ct_OTOOL64="$ac_ct_OTOOL64" # Let the user override the test. else as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. for ac_exec_ext in '' $ac_executable_extensions; do if as_fn_executable_p "$as_dir/$ac_word$ac_exec_ext"; then ac_cv_prog_ac_ct_OTOOL64="otool64" $as_echo "$as_me:${as_lineno-$LINENO}: found $as_dir/$ac_word$ac_exec_ext" >&5 break 2 fi done done IFS=$as_save_IFS fi fi ac_ct_OTOOL64=$ac_cv_prog_ac_ct_OTOOL64 if test -n "$ac_ct_OTOOL64"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_ct_OTOOL64" >&5 $as_echo "$ac_ct_OTOOL64" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi if test "x$ac_ct_OTOOL64" = x; then OTOOL64=":" else case $cross_compiling:$ac_tool_warned in yes:) { $as_echo "$as_me:${as_lineno-$LINENO}: WARNING: using cross tools not prefixed with host triplet" >&5 $as_echo "$as_me: WARNING: using cross tools not prefixed with host triplet" >&2;} ac_tool_warned=yes ;; esac OTOOL64=$ac_ct_OTOOL64 fi else OTOOL64="$ac_cv_prog_OTOOL64" fi { $as_echo "$as_me:${as_lineno-$LINENO}: checking for -single_module linker flag" >&5 $as_echo_n "checking for -single_module linker flag... " >&6; } if ${lt_cv_apple_cc_single_mod+:} false; then : $as_echo_n "(cached) " >&6 else lt_cv_apple_cc_single_mod=no if test -z "${LT_MULTI_MODULE}"; then # By default we will add the -single_module flag. You can override # by either setting the environment variable LT_MULTI_MODULE # non-empty at configure time, or by adding -multi_module to the # link flags. rm -rf libconftest.dylib* echo "int foo(void){return 1;}" > conftest.c echo "$LTCC $LTCFLAGS $LDFLAGS -o libconftest.dylib \ -dynamiclib -Wl,-single_module conftest.c" >&5 $LTCC $LTCFLAGS $LDFLAGS -o libconftest.dylib \ -dynamiclib -Wl,-single_module conftest.c 2>conftest.err _lt_result=$? # If there is a non-empty error log, and "single_module" # appears in it, assume the flag caused a linker warning if test -s conftest.err && $GREP single_module conftest.err; then cat conftest.err >&5 # Otherwise, if the output was created with a 0 exit code from # the compiler, it worked. elif test -f libconftest.dylib && test $_lt_result -eq 0; then lt_cv_apple_cc_single_mod=yes else cat conftest.err >&5 fi rm -rf libconftest.dylib* rm -f conftest.* fi fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $lt_cv_apple_cc_single_mod" >&5 $as_echo "$lt_cv_apple_cc_single_mod" >&6; } { $as_echo "$as_me:${as_lineno-$LINENO}: checking for -exported_symbols_list linker flag" >&5 $as_echo_n "checking for -exported_symbols_list linker flag... " >&6; } if ${lt_cv_ld_exported_symbols_list+:} false; then : $as_echo_n "(cached) " >&6 else lt_cv_ld_exported_symbols_list=no save_LDFLAGS=$LDFLAGS echo "_main" > conftest.sym LDFLAGS="$LDFLAGS -Wl,-exported_symbols_list,conftest.sym" cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ int main () { ; return 0; } _ACEOF if ac_fn_c_try_link "$LINENO"; then : lt_cv_ld_exported_symbols_list=yes else lt_cv_ld_exported_symbols_list=no fi rm -f core conftest.err conftest.$ac_objext \ conftest$ac_exeext conftest.$ac_ext LDFLAGS="$save_LDFLAGS" fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $lt_cv_ld_exported_symbols_list" >&5 $as_echo "$lt_cv_ld_exported_symbols_list" >&6; } { $as_echo "$as_me:${as_lineno-$LINENO}: checking for -force_load linker flag" >&5 $as_echo_n "checking for -force_load linker flag... " >&6; } if ${lt_cv_ld_force_load+:} false; then : $as_echo_n "(cached) " >&6 else lt_cv_ld_force_load=no cat > conftest.c << _LT_EOF int forced_loaded() { return 2;} _LT_EOF echo "$LTCC $LTCFLAGS -c -o conftest.o conftest.c" >&5 $LTCC $LTCFLAGS -c -o conftest.o conftest.c 2>&5 echo "$AR cru libconftest.a conftest.o" >&5 $AR cru libconftest.a conftest.o 2>&5 echo "$RANLIB libconftest.a" >&5 $RANLIB libconftest.a 2>&5 cat > conftest.c << _LT_EOF int main() { return 0;} _LT_EOF echo "$LTCC $LTCFLAGS $LDFLAGS -o conftest conftest.c -Wl,-force_load,./libconftest.a" >&5 $LTCC $LTCFLAGS $LDFLAGS -o conftest conftest.c -Wl,-force_load,./libconftest.a 2>conftest.err _lt_result=$? if test -s conftest.err && $GREP force_load conftest.err; then cat conftest.err >&5 elif test -f conftest && test $_lt_result -eq 0 && $GREP forced_load conftest >/dev/null 2>&1 ; then lt_cv_ld_force_load=yes else cat conftest.err >&5 fi rm -f conftest.err libconftest.a conftest conftest.c rm -rf conftest.dSYM fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $lt_cv_ld_force_load" >&5 $as_echo "$lt_cv_ld_force_load" >&6; } case $host_os in rhapsody* | darwin1.[012]) _lt_dar_allow_undefined='${wl}-undefined ${wl}suppress' ;; darwin1.*) _lt_dar_allow_undefined='${wl}-flat_namespace ${wl}-undefined ${wl}suppress' ;; darwin*) # darwin 5.x on # if running on 10.5 or later, the deployment target defaults # to the OS version, if on x86, and 10.4, the deployment # target defaults to 10.4. Don't you love it? case ${MACOSX_DEPLOYMENT_TARGET-10.0},$host in 10.0,*86*-darwin8*|10.0,*-darwin[91]*) _lt_dar_allow_undefined='${wl}-undefined ${wl}dynamic_lookup' ;; 10.[012]*) _lt_dar_allow_undefined='${wl}-flat_namespace ${wl}-undefined ${wl}suppress' ;; 10.*) _lt_dar_allow_undefined='${wl}-undefined ${wl}dynamic_lookup' ;; esac ;; esac if test "$lt_cv_apple_cc_single_mod" = "yes"; then _lt_dar_single_mod='$single_module' fi if test "$lt_cv_ld_exported_symbols_list" = "yes"; then _lt_dar_export_syms=' ${wl}-exported_symbols_list,$output_objdir/${libname}-symbols.expsym' else _lt_dar_export_syms='~$NMEDIT -s $output_objdir/${libname}-symbols.expsym ${lib}' fi if test "$DSYMUTIL" != ":" && test "$lt_cv_ld_force_load" = "no"; then _lt_dsymutil='~$DSYMUTIL $lib || :' else _lt_dsymutil= fi ;; esac ac_ext=c ac_cpp='$CPP $CPPFLAGS' ac_compile='$CC -c $CFLAGS $CPPFLAGS conftest.$ac_ext >&5' ac_link='$CC -o conftest$ac_exeext $CFLAGS $CPPFLAGS $LDFLAGS conftest.$ac_ext $LIBS >&5' ac_compiler_gnu=$ac_cv_c_compiler_gnu { $as_echo "$as_me:${as_lineno-$LINENO}: checking how to run the C preprocessor" >&5 $as_echo_n "checking how to run the C preprocessor... " >&6; } # On Suns, sometimes $CPP names a directory. if test -n "$CPP" && test -d "$CPP"; then CPP= fi if test -z "$CPP"; then if ${ac_cv_prog_CPP+:} false; then : $as_echo_n "(cached) " >&6 else # Double quotes because CPP needs to be expanded for CPP in "$CC -E" "$CC -E -traditional-cpp" "/lib/cpp" do ac_preproc_ok=false for ac_c_preproc_warn_flag in '' yes do # Use a header file that comes with gcc, so configuring glibc # with a fresh cross-compiler works. # Prefer to if __STDC__ is defined, since # exists even on freestanding compilers. # On the NeXT, cc -E runs the code through the compiler's parser, # not just through cpp. "Syntax error" is here to catch this case. cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ #ifdef __STDC__ # include #else # include #endif Syntax error _ACEOF if ac_fn_c_try_cpp "$LINENO"; then : else # Broken: fails on valid input. continue fi rm -f conftest.err conftest.i conftest.$ac_ext # OK, works on sane cases. Now check whether nonexistent headers # can be detected and how. cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ #include _ACEOF if ac_fn_c_try_cpp "$LINENO"; then : # Broken: success on invalid input. continue else # Passes both tests. ac_preproc_ok=: break fi rm -f conftest.err conftest.i conftest.$ac_ext done # Because of `break', _AC_PREPROC_IFELSE's cleaning code was skipped. rm -f conftest.i conftest.err conftest.$ac_ext if $ac_preproc_ok; then : break fi done ac_cv_prog_CPP=$CPP fi CPP=$ac_cv_prog_CPP else ac_cv_prog_CPP=$CPP fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $CPP" >&5 $as_echo "$CPP" >&6; } ac_preproc_ok=false for ac_c_preproc_warn_flag in '' yes do # Use a header file that comes with gcc, so configuring glibc # with a fresh cross-compiler works. # Prefer to if __STDC__ is defined, since # exists even on freestanding compilers. # On the NeXT, cc -E runs the code through the compiler's parser, # not just through cpp. "Syntax error" is here to catch this case. cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ #ifdef __STDC__ # include #else # include #endif Syntax error _ACEOF if ac_fn_c_try_cpp "$LINENO"; then : else # Broken: fails on valid input. continue fi rm -f conftest.err conftest.i conftest.$ac_ext # OK, works on sane cases. Now check whether nonexistent headers # can be detected and how. cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ #include _ACEOF if ac_fn_c_try_cpp "$LINENO"; then : # Broken: success on invalid input. continue else # Passes both tests. ac_preproc_ok=: break fi rm -f conftest.err conftest.i conftest.$ac_ext done # Because of `break', _AC_PREPROC_IFELSE's cleaning code was skipped. rm -f conftest.i conftest.err conftest.$ac_ext if $ac_preproc_ok; then : else { { $as_echo "$as_me:${as_lineno-$LINENO}: error: in \`$ac_pwd':" >&5 $as_echo "$as_me: error: in \`$ac_pwd':" >&2;} as_fn_error $? "C preprocessor \"$CPP\" fails sanity check See \`config.log' for more details" "$LINENO" 5; } fi ac_ext=c ac_cpp='$CPP $CPPFLAGS' ac_compile='$CC -c $CFLAGS $CPPFLAGS conftest.$ac_ext >&5' ac_link='$CC -o conftest$ac_exeext $CFLAGS $CPPFLAGS $LDFLAGS conftest.$ac_ext $LIBS >&5' ac_compiler_gnu=$ac_cv_c_compiler_gnu { $as_echo "$as_me:${as_lineno-$LINENO}: checking for ANSI C header files" >&5 $as_echo_n "checking for ANSI C header files... " >&6; } if ${ac_cv_header_stdc+:} false; then : $as_echo_n "(cached) " >&6 else cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ #include #include #include #include int main () { ; return 0; } _ACEOF if ac_fn_c_try_compile "$LINENO"; then : ac_cv_header_stdc=yes else ac_cv_header_stdc=no fi rm -f core conftest.err conftest.$ac_objext conftest.$ac_ext if test $ac_cv_header_stdc = yes; then # SunOS 4.x string.h does not declare mem*, contrary to ANSI. cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ #include _ACEOF if (eval "$ac_cpp conftest.$ac_ext") 2>&5 | $EGREP "memchr" >/dev/null 2>&1; then : else ac_cv_header_stdc=no fi rm -f conftest* fi if test $ac_cv_header_stdc = yes; then # ISC 2.0.2 stdlib.h does not declare free, contrary to ANSI. cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ #include _ACEOF if (eval "$ac_cpp conftest.$ac_ext") 2>&5 | $EGREP "free" >/dev/null 2>&1; then : else ac_cv_header_stdc=no fi rm -f conftest* fi if test $ac_cv_header_stdc = yes; then # /bin/cc in Irix-4.0.5 gets non-ANSI ctype macros unless using -ansi. if test "$cross_compiling" = yes; then : : else cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ #include #include #if ((' ' & 0x0FF) == 0x020) # define ISLOWER(c) ('a' <= (c) && (c) <= 'z') # define TOUPPER(c) (ISLOWER(c) ? 'A' + ((c) - 'a') : (c)) #else # define ISLOWER(c) \ (('a' <= (c) && (c) <= 'i') \ || ('j' <= (c) && (c) <= 'r') \ || ('s' <= (c) && (c) <= 'z')) # define TOUPPER(c) (ISLOWER(c) ? ((c) | 0x40) : (c)) #endif #define XOR(e, f) (((e) && !(f)) || (!(e) && (f))) int main () { int i; for (i = 0; i < 256; i++) if (XOR (islower (i), ISLOWER (i)) || toupper (i) != TOUPPER (i)) return 2; return 0; } _ACEOF if ac_fn_c_try_run "$LINENO"; then : else ac_cv_header_stdc=no fi rm -f core *.core core.conftest.* gmon.out bb.out conftest$ac_exeext \ conftest.$ac_objext conftest.beam conftest.$ac_ext fi fi fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_cv_header_stdc" >&5 $as_echo "$ac_cv_header_stdc" >&6; } if test $ac_cv_header_stdc = yes; then $as_echo "#define STDC_HEADERS 1" >>confdefs.h fi # On IRIX 5.3, sys/types and inttypes.h are conflicting. for ac_header in sys/types.h sys/stat.h stdlib.h string.h memory.h strings.h \ inttypes.h stdint.h unistd.h do : as_ac_Header=`$as_echo "ac_cv_header_$ac_header" | $as_tr_sh` ac_fn_c_check_header_compile "$LINENO" "$ac_header" "$as_ac_Header" "$ac_includes_default " if eval test \"x\$"$as_ac_Header"\" = x"yes"; then : cat >>confdefs.h <<_ACEOF #define `$as_echo "HAVE_$ac_header" | $as_tr_cpp` 1 _ACEOF fi done for ac_header in dlfcn.h do : ac_fn_c_check_header_compile "$LINENO" "dlfcn.h" "ac_cv_header_dlfcn_h" "$ac_includes_default " if test "x$ac_cv_header_dlfcn_h" = xyes; then : cat >>confdefs.h <<_ACEOF #define HAVE_DLFCN_H 1 _ACEOF fi done # Set options enable_dlopen=no enable_win32_dll=no # Check whether --enable-shared was given. if test "${enable_shared+set}" = set; then : enableval=$enable_shared; p=${PACKAGE-default} case $enableval in yes) enable_shared=yes ;; no) enable_shared=no ;; *) enable_shared=no # Look at the argument we got. We use all the common list separators. lt_save_ifs="$IFS"; IFS="${IFS}$PATH_SEPARATOR," for pkg in $enableval; do IFS="$lt_save_ifs" if test "X$pkg" = "X$p"; then enable_shared=yes fi done IFS="$lt_save_ifs" ;; esac else enable_shared=yes fi # Check whether --enable-static was given. if test "${enable_static+set}" = set; then : enableval=$enable_static; p=${PACKAGE-default} case $enableval in yes) enable_static=yes ;; no) enable_static=no ;; *) enable_static=no # Look at the argument we got. We use all the common list separators. lt_save_ifs="$IFS"; IFS="${IFS}$PATH_SEPARATOR," for pkg in $enableval; do IFS="$lt_save_ifs" if test "X$pkg" = "X$p"; then enable_static=yes fi done IFS="$lt_save_ifs" ;; esac else enable_static=yes fi # Check whether --with-pic was given. if test "${with_pic+set}" = set; then : withval=$with_pic; lt_p=${PACKAGE-default} case $withval in yes|no) pic_mode=$withval ;; *) pic_mode=default # Look at the argument we got. We use all the common list separators. lt_save_ifs="$IFS"; IFS="${IFS}$PATH_SEPARATOR," for lt_pkg in $withval; do IFS="$lt_save_ifs" if test "X$lt_pkg" = "X$lt_p"; then pic_mode=yes fi done IFS="$lt_save_ifs" ;; esac else pic_mode=default fi test -z "$pic_mode" && pic_mode=default # Check whether --enable-fast-install was given. if test "${enable_fast_install+set}" = set; then : enableval=$enable_fast_install; p=${PACKAGE-default} case $enableval in yes) enable_fast_install=yes ;; no) enable_fast_install=no ;; *) enable_fast_install=no # Look at the argument we got. We use all the common list separators. lt_save_ifs="$IFS"; IFS="${IFS}$PATH_SEPARATOR," for pkg in $enableval; do IFS="$lt_save_ifs" if test "X$pkg" = "X$p"; then enable_fast_install=yes fi done IFS="$lt_save_ifs" ;; esac else enable_fast_install=yes fi # This can be used to rebuild libtool when needed LIBTOOL_DEPS="$ltmain" # Always use our own libtool. LIBTOOL='$(SHELL) $(top_builddir)/libtool' test -z "$LN_S" && LN_S="ln -s" if test -n "${ZSH_VERSION+set}" ; then setopt NO_GLOB_SUBST fi { $as_echo "$as_me:${as_lineno-$LINENO}: checking for objdir" >&5 $as_echo_n "checking for objdir... " >&6; } if ${lt_cv_objdir+:} false; then : $as_echo_n "(cached) " >&6 else rm -f .libs 2>/dev/null mkdir .libs 2>/dev/null if test -d .libs; then lt_cv_objdir=.libs else # MS-DOS does not allow filenames that begin with a dot. lt_cv_objdir=_libs fi rmdir .libs 2>/dev/null fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $lt_cv_objdir" >&5 $as_echo "$lt_cv_objdir" >&6; } objdir=$lt_cv_objdir cat >>confdefs.h <<_ACEOF #define LT_OBJDIR "$lt_cv_objdir/" _ACEOF case $host_os in aix3*) # AIX sometimes has problems with the GCC collect2 program. For some # reason, if we set the COLLECT_NAMES environment variable, the problems # vanish in a puff of smoke. if test "X${COLLECT_NAMES+set}" != Xset; then COLLECT_NAMES= export COLLECT_NAMES fi ;; esac # Global variables: ofile=libtool can_build_shared=yes # All known linkers require a `.a' archive for static linking (except MSVC, # which needs '.lib'). libext=a with_gnu_ld="$lt_cv_prog_gnu_ld" old_CC="$CC" old_CFLAGS="$CFLAGS" # Set sane defaults for various variables test -z "$CC" && CC=cc test -z "$LTCC" && LTCC=$CC test -z "$LTCFLAGS" && LTCFLAGS=$CFLAGS test -z "$LD" && LD=ld test -z "$ac_objext" && ac_objext=o for cc_temp in $compiler""; do case $cc_temp in compile | *[\\/]compile | ccache | *[\\/]ccache ) ;; distcc | *[\\/]distcc | purify | *[\\/]purify ) ;; \-*) ;; *) break;; esac done cc_basename=`$ECHO "$cc_temp" | $SED "s%.*/%%; s%^$host_alias-%%"` # Only perform the check for file, if the check method requires it test -z "$MAGIC_CMD" && MAGIC_CMD=file case $deplibs_check_method in file_magic*) if test "$file_magic_cmd" = '$MAGIC_CMD'; then { $as_echo "$as_me:${as_lineno-$LINENO}: checking for ${ac_tool_prefix}file" >&5 $as_echo_n "checking for ${ac_tool_prefix}file... " >&6; } if ${lt_cv_path_MAGIC_CMD+:} false; then : $as_echo_n "(cached) " >&6 else case $MAGIC_CMD in [\\/*] | ?:[\\/]*) lt_cv_path_MAGIC_CMD="$MAGIC_CMD" # Let the user override the test with a path. ;; *) lt_save_MAGIC_CMD="$MAGIC_CMD" lt_save_ifs="$IFS"; IFS=$PATH_SEPARATOR ac_dummy="/usr/bin$PATH_SEPARATOR$PATH" for ac_dir in $ac_dummy; do IFS="$lt_save_ifs" test -z "$ac_dir" && ac_dir=. if test -f $ac_dir/${ac_tool_prefix}file; then lt_cv_path_MAGIC_CMD="$ac_dir/${ac_tool_prefix}file" if test -n "$file_magic_test_file"; then case $deplibs_check_method in "file_magic "*) file_magic_regex=`expr "$deplibs_check_method" : "file_magic \(.*\)"` MAGIC_CMD="$lt_cv_path_MAGIC_CMD" if eval $file_magic_cmd \$file_magic_test_file 2> /dev/null | $EGREP "$file_magic_regex" > /dev/null; then : else cat <<_LT_EOF 1>&2 *** Warning: the command libtool uses to detect shared libraries, *** $file_magic_cmd, produces output that libtool cannot recognize. *** The result is that libtool may fail to recognize shared libraries *** as such. This will affect the creation of libtool libraries that *** depend on shared libraries, but programs linked with such libtool *** libraries will work regardless of this problem. Nevertheless, you *** may want to report the problem to your system manager and/or to *** bug-libtool@gnu.org _LT_EOF fi ;; esac fi break fi done IFS="$lt_save_ifs" MAGIC_CMD="$lt_save_MAGIC_CMD" ;; esac fi MAGIC_CMD="$lt_cv_path_MAGIC_CMD" if test -n "$MAGIC_CMD"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $MAGIC_CMD" >&5 $as_echo "$MAGIC_CMD" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi if test -z "$lt_cv_path_MAGIC_CMD"; then if test -n "$ac_tool_prefix"; then { $as_echo "$as_me:${as_lineno-$LINENO}: checking for file" >&5 $as_echo_n "checking for file... " >&6; } if ${lt_cv_path_MAGIC_CMD+:} false; then : $as_echo_n "(cached) " >&6 else case $MAGIC_CMD in [\\/*] | ?:[\\/]*) lt_cv_path_MAGIC_CMD="$MAGIC_CMD" # Let the user override the test with a path. ;; *) lt_save_MAGIC_CMD="$MAGIC_CMD" lt_save_ifs="$IFS"; IFS=$PATH_SEPARATOR ac_dummy="/usr/bin$PATH_SEPARATOR$PATH" for ac_dir in $ac_dummy; do IFS="$lt_save_ifs" test -z "$ac_dir" && ac_dir=. if test -f $ac_dir/file; then lt_cv_path_MAGIC_CMD="$ac_dir/file" if test -n "$file_magic_test_file"; then case $deplibs_check_method in "file_magic "*) file_magic_regex=`expr "$deplibs_check_method" : "file_magic \(.*\)"` MAGIC_CMD="$lt_cv_path_MAGIC_CMD" if eval $file_magic_cmd \$file_magic_test_file 2> /dev/null | $EGREP "$file_magic_regex" > /dev/null; then : else cat <<_LT_EOF 1>&2 *** Warning: the command libtool uses to detect shared libraries, *** $file_magic_cmd, produces output that libtool cannot recognize. *** The result is that libtool may fail to recognize shared libraries *** as such. This will affect the creation of libtool libraries that *** depend on shared libraries, but programs linked with such libtool *** libraries will work regardless of this problem. Nevertheless, you *** may want to report the problem to your system manager and/or to *** bug-libtool@gnu.org _LT_EOF fi ;; esac fi break fi done IFS="$lt_save_ifs" MAGIC_CMD="$lt_save_MAGIC_CMD" ;; esac fi MAGIC_CMD="$lt_cv_path_MAGIC_CMD" if test -n "$MAGIC_CMD"; then { $as_echo "$as_me:${as_lineno-$LINENO}: result: $MAGIC_CMD" >&5 $as_echo "$MAGIC_CMD" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi else MAGIC_CMD=: fi fi fi ;; esac # Use C for the default configuration in the libtool script lt_save_CC="$CC" ac_ext=c ac_cpp='$CPP $CPPFLAGS' ac_compile='$CC -c $CFLAGS $CPPFLAGS conftest.$ac_ext >&5' ac_link='$CC -o conftest$ac_exeext $CFLAGS $CPPFLAGS $LDFLAGS conftest.$ac_ext $LIBS >&5' ac_compiler_gnu=$ac_cv_c_compiler_gnu # Source file extension for C test sources. ac_ext=c # Object file extension for compiled C test sources. objext=o objext=$objext # Code to be used in simple compile tests lt_simple_compile_test_code="int some_variable = 0;" # Code to be used in simple link tests lt_simple_link_test_code='int main(){return(0);}' # If no C compiler was specified, use CC. LTCC=${LTCC-"$CC"} # If no C compiler flags were specified, use CFLAGS. LTCFLAGS=${LTCFLAGS-"$CFLAGS"} # Allow CC to be a program name with arguments. compiler=$CC # Save the default compiler, since it gets overwritten when the other # tags are being tested, and _LT_TAGVAR(compiler, []) is a NOP. compiler_DEFAULT=$CC # save warnings/boilerplate of simple test code ac_outfile=conftest.$ac_objext echo "$lt_simple_compile_test_code" >conftest.$ac_ext eval "$ac_compile" 2>&1 >/dev/null | $SED '/^$/d; /^ *+/d' >conftest.err _lt_compiler_boilerplate=`cat conftest.err` $RM conftest* ac_outfile=conftest.$ac_objext echo "$lt_simple_link_test_code" >conftest.$ac_ext eval "$ac_link" 2>&1 >/dev/null | $SED '/^$/d; /^ *+/d' >conftest.err _lt_linker_boilerplate=`cat conftest.err` $RM -r conftest* ## CAVEAT EMPTOR: ## There is no encapsulation within the following macros, do not change ## the running order or otherwise move them around unless you know exactly ## what you are doing... if test -n "$compiler"; then lt_prog_compiler_no_builtin_flag= if test "$GCC" = yes; then case $cc_basename in nvcc*) lt_prog_compiler_no_builtin_flag=' -Xcompiler -fno-builtin' ;; *) lt_prog_compiler_no_builtin_flag=' -fno-builtin' ;; esac { $as_echo "$as_me:${as_lineno-$LINENO}: checking if $compiler supports -fno-rtti -fno-exceptions" >&5 $as_echo_n "checking if $compiler supports -fno-rtti -fno-exceptions... " >&6; } if ${lt_cv_prog_compiler_rtti_exceptions+:} false; then : $as_echo_n "(cached) " >&6 else lt_cv_prog_compiler_rtti_exceptions=no ac_outfile=conftest.$ac_objext echo "$lt_simple_compile_test_code" > conftest.$ac_ext lt_compiler_flag="-fno-rtti -fno-exceptions" # Insert the option either (1) after the last *FLAGS variable, or # (2) before a word containing "conftest.", or (3) at the end. # Note that $ac_compile itself does not contain backslashes and begins # with a dollar sign (not a hyphen), so the echo should work correctly. # The option is referenced via a variable to avoid confusing sed. lt_compile=`echo "$ac_compile" | $SED \ -e 's:.*FLAGS}\{0,1\} :&$lt_compiler_flag :; t' \ -e 's: [^ ]*conftest\.: $lt_compiler_flag&:; t' \ -e 's:$: $lt_compiler_flag:'` (eval echo "\"\$as_me:$LINENO: $lt_compile\"" >&5) (eval "$lt_compile" 2>conftest.err) ac_status=$? cat conftest.err >&5 echo "$as_me:$LINENO: \$? = $ac_status" >&5 if (exit $ac_status) && test -s "$ac_outfile"; then # The compiler can only warn and ignore the option if not recognized # So say no if there are warnings other than the usual output. $ECHO "$_lt_compiler_boilerplate" | $SED '/^$/d' >conftest.exp $SED '/^$/d; /^ *+/d' conftest.err >conftest.er2 if test ! -s conftest.er2 || diff conftest.exp conftest.er2 >/dev/null; then lt_cv_prog_compiler_rtti_exceptions=yes fi fi $RM conftest* fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $lt_cv_prog_compiler_rtti_exceptions" >&5 $as_echo "$lt_cv_prog_compiler_rtti_exceptions" >&6; } if test x"$lt_cv_prog_compiler_rtti_exceptions" = xyes; then lt_prog_compiler_no_builtin_flag="$lt_prog_compiler_no_builtin_flag -fno-rtti -fno-exceptions" else : fi fi lt_prog_compiler_wl= lt_prog_compiler_pic= lt_prog_compiler_static= if test "$GCC" = yes; then lt_prog_compiler_wl='-Wl,' lt_prog_compiler_static='-static' case $host_os in aix*) # All AIX code is PIC. if test "$host_cpu" = ia64; then # AIX 5 now supports IA64 processor lt_prog_compiler_static='-Bstatic' fi ;; amigaos*) case $host_cpu in powerpc) # see comment about AmigaOS4 .so support lt_prog_compiler_pic='-fPIC' ;; m68k) # FIXME: we need at least 68020 code to build shared libraries, but # adding the `-m68020' flag to GCC prevents building anything better, # like `-m68040'. lt_prog_compiler_pic='-m68020 -resident32 -malways-restore-a4' ;; esac ;; beos* | irix5* | irix6* | nonstopux* | osf3* | osf4* | osf5*) # PIC is the default for these OSes. ;; mingw* | cygwin* | pw32* | os2* | cegcc*) # This hack is so that the source file can tell whether it is being # built for inclusion in a dll (and should export symbols for example). # Although the cygwin gcc ignores -fPIC, still need this for old-style # (--disable-auto-import) libraries lt_prog_compiler_pic='-DDLL_EXPORT' ;; darwin* | rhapsody*) # PIC is the default on this platform # Common symbols not allowed in MH_DYLIB files lt_prog_compiler_pic='-fno-common' ;; haiku*) # PIC is the default for Haiku. # The "-static" flag exists, but is broken. lt_prog_compiler_static= ;; hpux*) # PIC is the default for 64-bit PA HP-UX, but not for 32-bit # PA HP-UX. On IA64 HP-UX, PIC is the default but the pic flag # sets the default TLS model and affects inlining. case $host_cpu in hppa*64*) # +Z the default ;; *) lt_prog_compiler_pic='-fPIC' ;; esac ;; interix[3-9]*) # Interix 3.x gcc -fpic/-fPIC options generate broken code. # Instead, we relocate shared libraries at runtime. ;; msdosdjgpp*) # Just because we use GCC doesn't mean we suddenly get shared libraries # on systems that don't support them. lt_prog_compiler_can_build_shared=no enable_shared=no ;; *nto* | *qnx*) # QNX uses GNU C++, but need to define -shared option too, otherwise # it will coredump. lt_prog_compiler_pic='-fPIC -shared' ;; sysv4*MP*) if test -d /usr/nec; then lt_prog_compiler_pic=-Kconform_pic fi ;; *) lt_prog_compiler_pic='-fPIC' ;; esac case $cc_basename in nvcc*) # Cuda Compiler Driver 2.2 lt_prog_compiler_wl='-Xlinker ' if test -n "$lt_prog_compiler_pic"; then lt_prog_compiler_pic="-Xcompiler $lt_prog_compiler_pic" fi ;; esac else # PORTME Check for flag to pass linker flags through the system compiler. case $host_os in aix*) lt_prog_compiler_wl='-Wl,' if test "$host_cpu" = ia64; then # AIX 5 now supports IA64 processor lt_prog_compiler_static='-Bstatic' else lt_prog_compiler_static='-bnso -bI:/lib/syscalls.exp' fi ;; mingw* | cygwin* | pw32* | os2* | cegcc*) # This hack is so that the source file can tell whether it is being # built for inclusion in a dll (and should export symbols for example). lt_prog_compiler_pic='-DDLL_EXPORT' ;; hpux9* | hpux10* | hpux11*) lt_prog_compiler_wl='-Wl,' # PIC is the default for IA64 HP-UX and 64-bit HP-UX, but # not for PA HP-UX. case $host_cpu in hppa*64*|ia64*) # +Z the default ;; *) lt_prog_compiler_pic='+Z' ;; esac # Is there a better lt_prog_compiler_static that works with the bundled CC? lt_prog_compiler_static='${wl}-a ${wl}archive' ;; irix5* | irix6* | nonstopux*) lt_prog_compiler_wl='-Wl,' # PIC (with -KPIC) is the default. lt_prog_compiler_static='-non_shared' ;; linux* | k*bsd*-gnu | kopensolaris*-gnu | gnu*) case $cc_basename in # old Intel for x86_64 which still supported -KPIC. ecc*) lt_prog_compiler_wl='-Wl,' lt_prog_compiler_pic='-KPIC' lt_prog_compiler_static='-static' ;; # icc used to be incompatible with GCC. # ICC 10 doesn't accept -KPIC any more. icc* | ifort*) lt_prog_compiler_wl='-Wl,' lt_prog_compiler_pic='-fPIC' lt_prog_compiler_static='-static' ;; # Lahey Fortran 8.1. lf95*) lt_prog_compiler_wl='-Wl,' lt_prog_compiler_pic='--shared' lt_prog_compiler_static='--static' ;; nagfor*) # NAG Fortran compiler lt_prog_compiler_wl='-Wl,-Wl,,' lt_prog_compiler_pic='-PIC' lt_prog_compiler_static='-Bstatic' ;; pgcc* | pgf77* | pgf90* | pgf95* | pgfortran*) # Portland Group compilers (*not* the Pentium gcc compiler, # which looks to be a dead project) lt_prog_compiler_wl='-Wl,' lt_prog_compiler_pic='-fpic' lt_prog_compiler_static='-Bstatic' ;; ccc*) lt_prog_compiler_wl='-Wl,' # All Alpha code is PIC. lt_prog_compiler_static='-non_shared' ;; xl* | bgxl* | bgf* | mpixl*) # IBM XL C 8.0/Fortran 10.1, 11.1 on PPC and BlueGene lt_prog_compiler_wl='-Wl,' lt_prog_compiler_pic='-qpic' lt_prog_compiler_static='-qstaticlink' ;; *) case `$CC -V 2>&1 | sed 5q` in *Sun\ Ceres\ Fortran* | *Sun*Fortran*\ [1-7].* | *Sun*Fortran*\ 8.[0-3]*) # Sun Fortran 8.3 passes all unrecognized flags to the linker lt_prog_compiler_pic='-KPIC' lt_prog_compiler_static='-Bstatic' lt_prog_compiler_wl='' ;; *Sun\ F* | *Sun*Fortran*) lt_prog_compiler_pic='-KPIC' lt_prog_compiler_static='-Bstatic' lt_prog_compiler_wl='-Qoption ld ' ;; *Sun\ C*) # Sun C 5.9 lt_prog_compiler_pic='-KPIC' lt_prog_compiler_static='-Bstatic' lt_prog_compiler_wl='-Wl,' ;; *Intel*\ [CF]*Compiler*) lt_prog_compiler_wl='-Wl,' lt_prog_compiler_pic='-fPIC' lt_prog_compiler_static='-static' ;; *Portland\ Group*) lt_prog_compiler_wl='-Wl,' lt_prog_compiler_pic='-fpic' lt_prog_compiler_static='-Bstatic' ;; esac ;; esac ;; newsos6) lt_prog_compiler_pic='-KPIC' lt_prog_compiler_static='-Bstatic' ;; *nto* | *qnx*) # QNX uses GNU C++, but need to define -shared option too, otherwise # it will coredump. lt_prog_compiler_pic='-fPIC -shared' ;; osf3* | osf4* | osf5*) lt_prog_compiler_wl='-Wl,' # All OSF/1 code is PIC. lt_prog_compiler_static='-non_shared' ;; rdos*) lt_prog_compiler_static='-non_shared' ;; solaris*) lt_prog_compiler_pic='-KPIC' lt_prog_compiler_static='-Bstatic' case $cc_basename in f77* | f90* | f95* | sunf77* | sunf90* | sunf95*) lt_prog_compiler_wl='-Qoption ld ';; *) lt_prog_compiler_wl='-Wl,';; esac ;; sunos4*) lt_prog_compiler_wl='-Qoption ld ' lt_prog_compiler_pic='-PIC' lt_prog_compiler_static='-Bstatic' ;; sysv4 | sysv4.2uw2* | sysv4.3*) lt_prog_compiler_wl='-Wl,' lt_prog_compiler_pic='-KPIC' lt_prog_compiler_static='-Bstatic' ;; sysv4*MP*) if test -d /usr/nec ;then lt_prog_compiler_pic='-Kconform_pic' lt_prog_compiler_static='-Bstatic' fi ;; sysv5* | unixware* | sco3.2v5* | sco5v6* | OpenUNIX*) lt_prog_compiler_wl='-Wl,' lt_prog_compiler_pic='-KPIC' lt_prog_compiler_static='-Bstatic' ;; unicos*) lt_prog_compiler_wl='-Wl,' lt_prog_compiler_can_build_shared=no ;; uts4*) lt_prog_compiler_pic='-pic' lt_prog_compiler_static='-Bstatic' ;; *) lt_prog_compiler_can_build_shared=no ;; esac fi case $host_os in # For platforms which do not support PIC, -DPIC is meaningless: *djgpp*) lt_prog_compiler_pic= ;; *) lt_prog_compiler_pic="$lt_prog_compiler_pic -DPIC" ;; esac { $as_echo "$as_me:${as_lineno-$LINENO}: checking for $compiler option to produce PIC" >&5 $as_echo_n "checking for $compiler option to produce PIC... " >&6; } if ${lt_cv_prog_compiler_pic+:} false; then : $as_echo_n "(cached) " >&6 else lt_cv_prog_compiler_pic=$lt_prog_compiler_pic fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $lt_cv_prog_compiler_pic" >&5 $as_echo "$lt_cv_prog_compiler_pic" >&6; } lt_prog_compiler_pic=$lt_cv_prog_compiler_pic # # Check to make sure the PIC flag actually works. # if test -n "$lt_prog_compiler_pic"; then { $as_echo "$as_me:${as_lineno-$LINENO}: checking if $compiler PIC flag $lt_prog_compiler_pic works" >&5 $as_echo_n "checking if $compiler PIC flag $lt_prog_compiler_pic works... " >&6; } if ${lt_cv_prog_compiler_pic_works+:} false; then : $as_echo_n "(cached) " >&6 else lt_cv_prog_compiler_pic_works=no ac_outfile=conftest.$ac_objext echo "$lt_simple_compile_test_code" > conftest.$ac_ext lt_compiler_flag="$lt_prog_compiler_pic -DPIC" # Insert the option either (1) after the last *FLAGS variable, or # (2) before a word containing "conftest.", or (3) at the end. # Note that $ac_compile itself does not contain backslashes and begins # with a dollar sign (not a hyphen), so the echo should work correctly. # The option is referenced via a variable to avoid confusing sed. lt_compile=`echo "$ac_compile" | $SED \ -e 's:.*FLAGS}\{0,1\} :&$lt_compiler_flag :; t' \ -e 's: [^ ]*conftest\.: $lt_compiler_flag&:; t' \ -e 's:$: $lt_compiler_flag:'` (eval echo "\"\$as_me:$LINENO: $lt_compile\"" >&5) (eval "$lt_compile" 2>conftest.err) ac_status=$? cat conftest.err >&5 echo "$as_me:$LINENO: \$? = $ac_status" >&5 if (exit $ac_status) && test -s "$ac_outfile"; then # The compiler can only warn and ignore the option if not recognized # So say no if there are warnings other than the usual output. $ECHO "$_lt_compiler_boilerplate" | $SED '/^$/d' >conftest.exp $SED '/^$/d; /^ *+/d' conftest.err >conftest.er2 if test ! -s conftest.er2 || diff conftest.exp conftest.er2 >/dev/null; then lt_cv_prog_compiler_pic_works=yes fi fi $RM conftest* fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $lt_cv_prog_compiler_pic_works" >&5 $as_echo "$lt_cv_prog_compiler_pic_works" >&6; } if test x"$lt_cv_prog_compiler_pic_works" = xyes; then case $lt_prog_compiler_pic in "" | " "*) ;; *) lt_prog_compiler_pic=" $lt_prog_compiler_pic" ;; esac else lt_prog_compiler_pic= lt_prog_compiler_can_build_shared=no fi fi # # Check to make sure the static flag actually works. # wl=$lt_prog_compiler_wl eval lt_tmp_static_flag=\"$lt_prog_compiler_static\" { $as_echo "$as_me:${as_lineno-$LINENO}: checking if $compiler static flag $lt_tmp_static_flag works" >&5 $as_echo_n "checking if $compiler static flag $lt_tmp_static_flag works... " >&6; } if ${lt_cv_prog_compiler_static_works+:} false; then : $as_echo_n "(cached) " >&6 else lt_cv_prog_compiler_static_works=no save_LDFLAGS="$LDFLAGS" LDFLAGS="$LDFLAGS $lt_tmp_static_flag" echo "$lt_simple_link_test_code" > conftest.$ac_ext if (eval $ac_link 2>conftest.err) && test -s conftest$ac_exeext; then # The linker can only warn and ignore the option if not recognized # So say no if there are warnings if test -s conftest.err; then # Append any errors to the config.log. cat conftest.err 1>&5 $ECHO "$_lt_linker_boilerplate" | $SED '/^$/d' > conftest.exp $SED '/^$/d; /^ *+/d' conftest.err >conftest.er2 if diff conftest.exp conftest.er2 >/dev/null; then lt_cv_prog_compiler_static_works=yes fi else lt_cv_prog_compiler_static_works=yes fi fi $RM -r conftest* LDFLAGS="$save_LDFLAGS" fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $lt_cv_prog_compiler_static_works" >&5 $as_echo "$lt_cv_prog_compiler_static_works" >&6; } if test x"$lt_cv_prog_compiler_static_works" = xyes; then : else lt_prog_compiler_static= fi { $as_echo "$as_me:${as_lineno-$LINENO}: checking if $compiler supports -c -o file.$ac_objext" >&5 $as_echo_n "checking if $compiler supports -c -o file.$ac_objext... " >&6; } if ${lt_cv_prog_compiler_c_o+:} false; then : $as_echo_n "(cached) " >&6 else lt_cv_prog_compiler_c_o=no $RM -r conftest 2>/dev/null mkdir conftest cd conftest mkdir out echo "$lt_simple_compile_test_code" > conftest.$ac_ext lt_compiler_flag="-o out/conftest2.$ac_objext" # Insert the option either (1) after the last *FLAGS variable, or # (2) before a word containing "conftest.", or (3) at the end. # Note that $ac_compile itself does not contain backslashes and begins # with a dollar sign (not a hyphen), so the echo should work correctly. lt_compile=`echo "$ac_compile" | $SED \ -e 's:.*FLAGS}\{0,1\} :&$lt_compiler_flag :; t' \ -e 's: [^ ]*conftest\.: $lt_compiler_flag&:; t' \ -e 's:$: $lt_compiler_flag:'` (eval echo "\"\$as_me:$LINENO: $lt_compile\"" >&5) (eval "$lt_compile" 2>out/conftest.err) ac_status=$? cat out/conftest.err >&5 echo "$as_me:$LINENO: \$? = $ac_status" >&5 if (exit $ac_status) && test -s out/conftest2.$ac_objext then # The compiler can only warn and ignore the option if not recognized # So say no if there are warnings $ECHO "$_lt_compiler_boilerplate" | $SED '/^$/d' > out/conftest.exp $SED '/^$/d; /^ *+/d' out/conftest.err >out/conftest.er2 if test ! -s out/conftest.er2 || diff out/conftest.exp out/conftest.er2 >/dev/null; then lt_cv_prog_compiler_c_o=yes fi fi chmod u+w . 2>&5 $RM conftest* # SGI C++ compiler will create directory out/ii_files/ for # template instantiation test -d out/ii_files && $RM out/ii_files/* && rmdir out/ii_files $RM out/* && rmdir out cd .. $RM -r conftest $RM conftest* fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $lt_cv_prog_compiler_c_o" >&5 $as_echo "$lt_cv_prog_compiler_c_o" >&6; } { $as_echo "$as_me:${as_lineno-$LINENO}: checking if $compiler supports -c -o file.$ac_objext" >&5 $as_echo_n "checking if $compiler supports -c -o file.$ac_objext... " >&6; } if ${lt_cv_prog_compiler_c_o+:} false; then : $as_echo_n "(cached) " >&6 else lt_cv_prog_compiler_c_o=no $RM -r conftest 2>/dev/null mkdir conftest cd conftest mkdir out echo "$lt_simple_compile_test_code" > conftest.$ac_ext lt_compiler_flag="-o out/conftest2.$ac_objext" # Insert the option either (1) after the last *FLAGS variable, or # (2) before a word containing "conftest.", or (3) at the end. # Note that $ac_compile itself does not contain backslashes and begins # with a dollar sign (not a hyphen), so the echo should work correctly. lt_compile=`echo "$ac_compile" | $SED \ -e 's:.*FLAGS}\{0,1\} :&$lt_compiler_flag :; t' \ -e 's: [^ ]*conftest\.: $lt_compiler_flag&:; t' \ -e 's:$: $lt_compiler_flag:'` (eval echo "\"\$as_me:$LINENO: $lt_compile\"" >&5) (eval "$lt_compile" 2>out/conftest.err) ac_status=$? cat out/conftest.err >&5 echo "$as_me:$LINENO: \$? = $ac_status" >&5 if (exit $ac_status) && test -s out/conftest2.$ac_objext then # The compiler can only warn and ignore the option if not recognized # So say no if there are warnings $ECHO "$_lt_compiler_boilerplate" | $SED '/^$/d' > out/conftest.exp $SED '/^$/d; /^ *+/d' out/conftest.err >out/conftest.er2 if test ! -s out/conftest.er2 || diff out/conftest.exp out/conftest.er2 >/dev/null; then lt_cv_prog_compiler_c_o=yes fi fi chmod u+w . 2>&5 $RM conftest* # SGI C++ compiler will create directory out/ii_files/ for # template instantiation test -d out/ii_files && $RM out/ii_files/* && rmdir out/ii_files $RM out/* && rmdir out cd .. $RM -r conftest $RM conftest* fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $lt_cv_prog_compiler_c_o" >&5 $as_echo "$lt_cv_prog_compiler_c_o" >&6; } hard_links="nottested" if test "$lt_cv_prog_compiler_c_o" = no && test "$need_locks" != no; then # do not overwrite the value of need_locks provided by the user { $as_echo "$as_me:${as_lineno-$LINENO}: checking if we can lock with hard links" >&5 $as_echo_n "checking if we can lock with hard links... " >&6; } hard_links=yes $RM conftest* ln conftest.a conftest.b 2>/dev/null && hard_links=no touch conftest.a ln conftest.a conftest.b 2>&5 || hard_links=no ln conftest.a conftest.b 2>/dev/null && hard_links=no { $as_echo "$as_me:${as_lineno-$LINENO}: result: $hard_links" >&5 $as_echo "$hard_links" >&6; } if test "$hard_links" = no; then { $as_echo "$as_me:${as_lineno-$LINENO}: WARNING: \`$CC' does not support \`-c -o', so \`make -j' may be unsafe" >&5 $as_echo "$as_me: WARNING: \`$CC' does not support \`-c -o', so \`make -j' may be unsafe" >&2;} need_locks=warn fi else need_locks=no fi { $as_echo "$as_me:${as_lineno-$LINENO}: checking whether the $compiler linker ($LD) supports shared libraries" >&5 $as_echo_n "checking whether the $compiler linker ($LD) supports shared libraries... " >&6; } runpath_var= allow_undefined_flag= always_export_symbols=no archive_cmds= archive_expsym_cmds= compiler_needs_object=no enable_shared_with_static_runtimes=no export_dynamic_flag_spec= export_symbols_cmds='$NM $libobjs $convenience | $global_symbol_pipe | $SED '\''s/.* //'\'' | sort | uniq > $export_symbols' hardcode_automatic=no hardcode_direct=no hardcode_direct_absolute=no hardcode_libdir_flag_spec= hardcode_libdir_separator= hardcode_minus_L=no hardcode_shlibpath_var=unsupported inherit_rpath=no link_all_deplibs=unknown module_cmds= module_expsym_cmds= old_archive_from_new_cmds= old_archive_from_expsyms_cmds= thread_safe_flag_spec= whole_archive_flag_spec= # include_expsyms should be a list of space-separated symbols to be *always* # included in the symbol list include_expsyms= # exclude_expsyms can be an extended regexp of symbols to exclude # it will be wrapped by ` (' and `)$', so one must not match beginning or # end of line. Example: `a|bc|.*d.*' will exclude the symbols `a' and `bc', # as well as any symbol that contains `d'. exclude_expsyms='_GLOBAL_OFFSET_TABLE_|_GLOBAL__F[ID]_.*' # Although _GLOBAL_OFFSET_TABLE_ is a valid symbol C name, most a.out # platforms (ab)use it in PIC code, but their linkers get confused if # the symbol is explicitly referenced. Since portable code cannot # rely on this symbol name, it's probably fine to never include it in # preloaded symbol tables. # Exclude shared library initialization/finalization symbols. extract_expsyms_cmds= case $host_os in cygwin* | mingw* | pw32* | cegcc*) # FIXME: the MSVC++ port hasn't been tested in a loooong time # When not using gcc, we currently assume that we are using # Microsoft Visual C++. if test "$GCC" != yes; then with_gnu_ld=no fi ;; interix*) # we just hope/assume this is gcc and not c89 (= MSVC++) with_gnu_ld=yes ;; openbsd*) with_gnu_ld=no ;; linux* | k*bsd*-gnu | gnu*) link_all_deplibs=no ;; esac ld_shlibs=yes # On some targets, GNU ld is compatible enough with the native linker # that we're better off using the native interface for both. lt_use_gnu_ld_interface=no if test "$with_gnu_ld" = yes; then case $host_os in aix*) # The AIX port of GNU ld has always aspired to compatibility # with the native linker. However, as the warning in the GNU ld # block says, versions before 2.19.5* couldn't really create working # shared libraries, regardless of the interface used. case `$LD -v 2>&1` in *\ \(GNU\ Binutils\)\ 2.19.5*) ;; *\ \(GNU\ Binutils\)\ 2.[2-9]*) ;; *\ \(GNU\ Binutils\)\ [3-9]*) ;; *) lt_use_gnu_ld_interface=yes ;; esac ;; *) lt_use_gnu_ld_interface=yes ;; esac fi if test "$lt_use_gnu_ld_interface" = yes; then # If archive_cmds runs LD, not CC, wlarc should be empty wlarc='${wl}' # Set some defaults for GNU ld with shared library support. These # are reset later if shared libraries are not supported. Putting them # here allows them to be overridden if necessary. runpath_var=LD_RUN_PATH hardcode_libdir_flag_spec='${wl}-rpath ${wl}$libdir' export_dynamic_flag_spec='${wl}--export-dynamic' # ancient GNU ld didn't support --whole-archive et. al. if $LD --help 2>&1 | $GREP 'no-whole-archive' > /dev/null; then whole_archive_flag_spec="$wlarc"'--whole-archive$convenience '"$wlarc"'--no-whole-archive' else whole_archive_flag_spec= fi supports_anon_versioning=no case `$LD -v 2>&1` in *GNU\ gold*) supports_anon_versioning=yes ;; *\ [01].* | *\ 2.[0-9].* | *\ 2.10.*) ;; # catch versions < 2.11 *\ 2.11.93.0.2\ *) supports_anon_versioning=yes ;; # RH7.3 ... *\ 2.11.92.0.12\ *) supports_anon_versioning=yes ;; # Mandrake 8.2 ... *\ 2.11.*) ;; # other 2.11 versions *) supports_anon_versioning=yes ;; esac # See if GNU ld supports shared libraries. case $host_os in aix[3-9]*) # On AIX/PPC, the GNU linker is very broken if test "$host_cpu" != ia64; then ld_shlibs=no cat <<_LT_EOF 1>&2 *** Warning: the GNU linker, at least up to release 2.19, is reported *** to be unable to reliably create shared libraries on AIX. *** Therefore, libtool is disabling shared libraries support. If you *** really care for shared libraries, you may want to install binutils *** 2.20 or above, or modify your PATH so that a non-GNU linker is found. *** You will then need to restart the configuration process. _LT_EOF fi ;; amigaos*) case $host_cpu in powerpc) # see comment about AmigaOS4 .so support archive_cmds='$CC -shared $libobjs $deplibs $compiler_flags ${wl}-soname $wl$soname -o $lib' archive_expsym_cmds='' ;; m68k) archive_cmds='$RM $output_objdir/a2ixlibrary.data~$ECHO "#define NAME $libname" > $output_objdir/a2ixlibrary.data~$ECHO "#define LIBRARY_ID 1" >> $output_objdir/a2ixlibrary.data~$ECHO "#define VERSION $major" >> $output_objdir/a2ixlibrary.data~$ECHO "#define REVISION $revision" >> $output_objdir/a2ixlibrary.data~$AR $AR_FLAGS $lib $libobjs~$RANLIB $lib~(cd $output_objdir && a2ixlibrary -32)' hardcode_libdir_flag_spec='-L$libdir' hardcode_minus_L=yes ;; esac ;; beos*) if $LD --help 2>&1 | $GREP ': supported targets:.* elf' > /dev/null; then allow_undefined_flag=unsupported # Joseph Beckenbach says some releases of gcc # support --undefined. This deserves some investigation. FIXME archive_cmds='$CC -nostart $libobjs $deplibs $compiler_flags ${wl}-soname $wl$soname -o $lib' else ld_shlibs=no fi ;; cygwin* | mingw* | pw32* | cegcc*) # _LT_TAGVAR(hardcode_libdir_flag_spec, ) is actually meaningless, # as there is no search path for DLLs. hardcode_libdir_flag_spec='-L$libdir' export_dynamic_flag_spec='${wl}--export-all-symbols' allow_undefined_flag=unsupported always_export_symbols=no enable_shared_with_static_runtimes=yes export_symbols_cmds='$NM $libobjs $convenience | $global_symbol_pipe | $SED -e '\''/^[BCDGRS][ ]/s/.*[ ]\([^ ]*\)/\1 DATA/;s/^.*[ ]__nm__\([^ ]*\)[ ][^ ]*/\1 DATA/;/^I[ ]/d;/^[AITW][ ]/s/.* //'\'' | sort | uniq > $export_symbols' exclude_expsyms='[_]+GLOBAL_OFFSET_TABLE_|[_]+GLOBAL__[FID]_.*|[_]+head_[A-Za-z0-9_]+_dll|[A-Za-z0-9_]+_dll_iname' if $LD --help 2>&1 | $GREP 'auto-import' > /dev/null; then archive_cmds='$CC -shared $libobjs $deplibs $compiler_flags -o $output_objdir/$soname ${wl}--enable-auto-image-base -Xlinker --out-implib -Xlinker $lib' # If the export-symbols file already is a .def file (1st line # is EXPORTS), use it as is; otherwise, prepend... archive_expsym_cmds='if test "x`$SED 1q $export_symbols`" = xEXPORTS; then cp $export_symbols $output_objdir/$soname.def; else echo EXPORTS > $output_objdir/$soname.def; cat $export_symbols >> $output_objdir/$soname.def; fi~ $CC -shared $output_objdir/$soname.def $libobjs $deplibs $compiler_flags -o $output_objdir/$soname ${wl}--enable-auto-image-base -Xlinker --out-implib -Xlinker $lib' else ld_shlibs=no fi ;; haiku*) archive_cmds='$CC -shared $libobjs $deplibs $compiler_flags ${wl}-soname $wl$soname -o $lib' link_all_deplibs=yes ;; interix[3-9]*) hardcode_direct=no hardcode_shlibpath_var=no hardcode_libdir_flag_spec='${wl}-rpath,$libdir' export_dynamic_flag_spec='${wl}-E' # Hack: On Interix 3.x, we cannot compile PIC because of a broken gcc. # Instead, shared libraries are loaded at an image base (0x10000000 by # default) and relocated if they conflict, which is a slow very memory # consuming and fragmenting process. To avoid this, we pick a random, # 256 KiB-aligned image base between 0x50000000 and 0x6FFC0000 at link # time. Moving up from 0x10000000 also allows more sbrk(2) space. archive_cmds='$CC -shared $pic_flag $libobjs $deplibs $compiler_flags ${wl}-h,$soname ${wl}--image-base,`expr ${RANDOM-$$} % 4096 / 2 \* 262144 + 1342177280` -o $lib' archive_expsym_cmds='sed "s,^,_," $export_symbols >$output_objdir/$soname.expsym~$CC -shared $pic_flag $libobjs $deplibs $compiler_flags ${wl}-h,$soname ${wl}--retain-symbols-file,$output_objdir/$soname.expsym ${wl}--image-base,`expr ${RANDOM-$$} % 4096 / 2 \* 262144 + 1342177280` -o $lib' ;; gnu* | linux* | tpf* | k*bsd*-gnu | kopensolaris*-gnu) tmp_diet=no if test "$host_os" = linux-dietlibc; then case $cc_basename in diet\ *) tmp_diet=yes;; # linux-dietlibc with static linking (!diet-dyn) esac fi if $LD --help 2>&1 | $EGREP ': supported targets:.* elf' > /dev/null \ && test "$tmp_diet" = no then tmp_addflag=' $pic_flag' tmp_sharedflag='-shared' case $cc_basename,$host_cpu in pgcc*) # Portland Group C compiler whole_archive_flag_spec='${wl}--whole-archive`for conv in $convenience\"\"; do test -n \"$conv\" && new_convenience=\"$new_convenience,$conv\"; done; func_echo_all \"$new_convenience\"` ${wl}--no-whole-archive' tmp_addflag=' $pic_flag' ;; pgf77* | pgf90* | pgf95* | pgfortran*) # Portland Group f77 and f90 compilers whole_archive_flag_spec='${wl}--whole-archive`for conv in $convenience\"\"; do test -n \"$conv\" && new_convenience=\"$new_convenience,$conv\"; done; func_echo_all \"$new_convenience\"` ${wl}--no-whole-archive' tmp_addflag=' $pic_flag -Mnomain' ;; ecc*,ia64* | icc*,ia64*) # Intel C compiler on ia64 tmp_addflag=' -i_dynamic' ;; efc*,ia64* | ifort*,ia64*) # Intel Fortran compiler on ia64 tmp_addflag=' -i_dynamic -nofor_main' ;; ifc* | ifort*) # Intel Fortran compiler tmp_addflag=' -nofor_main' ;; lf95*) # Lahey Fortran 8.1 whole_archive_flag_spec= tmp_sharedflag='--shared' ;; xl[cC]* | bgxl[cC]* | mpixl[cC]*) # IBM XL C 8.0 on PPC (deal with xlf below) tmp_sharedflag='-qmkshrobj' tmp_addflag= ;; nvcc*) # Cuda Compiler Driver 2.2 whole_archive_flag_spec='${wl}--whole-archive`for conv in $convenience\"\"; do test -n \"$conv\" && new_convenience=\"$new_convenience,$conv\"; done; func_echo_all \"$new_convenience\"` ${wl}--no-whole-archive' compiler_needs_object=yes ;; esac case `$CC -V 2>&1 | sed 5q` in *Sun\ C*) # Sun C 5.9 whole_archive_flag_spec='${wl}--whole-archive`new_convenience=; for conv in $convenience\"\"; do test -z \"$conv\" || new_convenience=\"$new_convenience,$conv\"; done; func_echo_all \"$new_convenience\"` ${wl}--no-whole-archive' compiler_needs_object=yes tmp_sharedflag='-G' ;; *Sun\ F*) # Sun Fortran 8.3 tmp_sharedflag='-G' ;; esac archive_cmds='$CC '"$tmp_sharedflag""$tmp_addflag"' $libobjs $deplibs $compiler_flags ${wl}-soname $wl$soname -o $lib' if test "x$supports_anon_versioning" = xyes; then archive_expsym_cmds='echo "{ global:" > $output_objdir/$libname.ver~ cat $export_symbols | sed -e "s/\(.*\)/\1;/" >> $output_objdir/$libname.ver~ echo "local: *; };" >> $output_objdir/$libname.ver~ $CC '"$tmp_sharedflag""$tmp_addflag"' $libobjs $deplibs $compiler_flags ${wl}-soname $wl$soname ${wl}-version-script ${wl}$output_objdir/$libname.ver -o $lib' fi case $cc_basename in xlf* | bgf* | bgxlf* | mpixlf*) # IBM XL Fortran 10.1 on PPC cannot create shared libs itself whole_archive_flag_spec='--whole-archive$convenience --no-whole-archive' hardcode_libdir_flag_spec='${wl}-rpath ${wl}$libdir' archive_cmds='$LD -shared $libobjs $deplibs $linker_flags -soname $soname -o $lib' if test "x$supports_anon_versioning" = xyes; then archive_expsym_cmds='echo "{ global:" > $output_objdir/$libname.ver~ cat $export_symbols | sed -e "s/\(.*\)/\1;/" >> $output_objdir/$libname.ver~ echo "local: *; };" >> $output_objdir/$libname.ver~ $LD -shared $libobjs $deplibs $linker_flags -soname $soname -version-script $output_objdir/$libname.ver -o $lib' fi ;; esac else ld_shlibs=no fi ;; netbsd* | netbsdelf*-gnu) if echo __ELF__ | $CC -E - | $GREP __ELF__ >/dev/null; then archive_cmds='$LD -Bshareable $libobjs $deplibs $linker_flags -o $lib' wlarc= else archive_cmds='$CC -shared $pic_flag $libobjs $deplibs $compiler_flags ${wl}-soname $wl$soname -o $lib' archive_expsym_cmds='$CC -shared $pic_flag $libobjs $deplibs $compiler_flags ${wl}-soname $wl$soname ${wl}-retain-symbols-file $wl$export_symbols -o $lib' fi ;; solaris*) if $LD -v 2>&1 | $GREP 'BFD 2\.8' > /dev/null; then ld_shlibs=no cat <<_LT_EOF 1>&2 *** Warning: The releases 2.8.* of the GNU linker cannot reliably *** create shared libraries on Solaris systems. Therefore, libtool *** is disabling shared libraries support. We urge you to upgrade GNU *** binutils to release 2.9.1 or newer. Another option is to modify *** your PATH or compiler configuration so that the native linker is *** used, and then restart. _LT_EOF elif $LD --help 2>&1 | $GREP ': supported targets:.* elf' > /dev/null; then archive_cmds='$CC -shared $pic_flag $libobjs $deplibs $compiler_flags ${wl}-soname $wl$soname -o $lib' archive_expsym_cmds='$CC -shared $pic_flag $libobjs $deplibs $compiler_flags ${wl}-soname $wl$soname ${wl}-retain-symbols-file $wl$export_symbols -o $lib' else ld_shlibs=no fi ;; sysv5* | sco3.2v5* | sco5v6* | unixware* | OpenUNIX*) case `$LD -v 2>&1` in *\ [01].* | *\ 2.[0-9].* | *\ 2.1[0-5].*) ld_shlibs=no cat <<_LT_EOF 1>&2 *** Warning: Releases of the GNU linker prior to 2.16.91.0.3 can not *** reliably create shared libraries on SCO systems. Therefore, libtool *** is disabling shared libraries support. We urge you to upgrade GNU *** binutils to release 2.16.91.0.3 or newer. Another option is to modify *** your PATH or compiler configuration so that the native linker is *** used, and then restart. _LT_EOF ;; *) # For security reasons, it is highly recommended that you always # use absolute paths for naming shared libraries, and exclude the # DT_RUNPATH tag from executables and libraries. But doing so # requires that you compile everything twice, which is a pain. if $LD --help 2>&1 | $GREP ': supported targets:.* elf' > /dev/null; then hardcode_libdir_flag_spec='${wl}-rpath ${wl}$libdir' archive_cmds='$CC -shared $libobjs $deplibs $compiler_flags ${wl}-soname $wl$soname -o $lib' archive_expsym_cmds='$CC -shared $libobjs $deplibs $compiler_flags ${wl}-soname $wl$soname ${wl}-retain-symbols-file $wl$export_symbols -o $lib' else ld_shlibs=no fi ;; esac ;; sunos4*) archive_cmds='$LD -assert pure-text -Bshareable -o $lib $libobjs $deplibs $linker_flags' wlarc= hardcode_direct=yes hardcode_shlibpath_var=no ;; *) if $LD --help 2>&1 | $GREP ': supported targets:.* elf' > /dev/null; then archive_cmds='$CC -shared $pic_flag $libobjs $deplibs $compiler_flags ${wl}-soname $wl$soname -o $lib' archive_expsym_cmds='$CC -shared $pic_flag $libobjs $deplibs $compiler_flags ${wl}-soname $wl$soname ${wl}-retain-symbols-file $wl$export_symbols -o $lib' else ld_shlibs=no fi ;; esac if test "$ld_shlibs" = no; then runpath_var= hardcode_libdir_flag_spec= export_dynamic_flag_spec= whole_archive_flag_spec= fi else # PORTME fill in a description of your system's linker (not GNU ld) case $host_os in aix3*) allow_undefined_flag=unsupported always_export_symbols=yes archive_expsym_cmds='$LD -o $output_objdir/$soname $libobjs $deplibs $linker_flags -bE:$export_symbols -T512 -H512 -bM:SRE~$AR $AR_FLAGS $lib $output_objdir/$soname' # Note: this linker hardcodes the directories in LIBPATH if there # are no directories specified by -L. hardcode_minus_L=yes if test "$GCC" = yes && test -z "$lt_prog_compiler_static"; then # Neither direct hardcoding nor static linking is supported with a # broken collect2. hardcode_direct=unsupported fi ;; aix[4-9]*) if test "$host_cpu" = ia64; then # On IA64, the linker does run time linking by default, so we don't # have to do anything special. aix_use_runtimelinking=no exp_sym_flag='-Bexport' no_entry_flag="" else # If we're using GNU nm, then we don't want the "-C" option. # -C means demangle to AIX nm, but means don't demangle with GNU nm # Also, AIX nm treats weak defined symbols like other global # defined symbols, whereas GNU nm marks them as "W". if $NM -V 2>&1 | $GREP 'GNU' > /dev/null; then export_symbols_cmds='$NM -Bpg $libobjs $convenience | awk '\''{ if (((\$ 2 == "T") || (\$ 2 == "D") || (\$ 2 == "B") || (\$ 2 == "W")) && (substr(\$ 3,1,1) != ".")) { print \$ 3 } }'\'' | sort -u > $export_symbols' else export_symbols_cmds='$NM -BCpg $libobjs $convenience | awk '\''{ if (((\$ 2 == "T") || (\$ 2 == "D") || (\$ 2 == "B")) && (substr(\$ 3,1,1) != ".")) { print \$ 3 } }'\'' | sort -u > $export_symbols' fi aix_use_runtimelinking=no # Test if we are trying to use run time linking or normal # AIX style linking. If -brtl is somewhere in LDFLAGS, we # need to do runtime linking. case $host_os in aix4.[23]|aix4.[23].*|aix[5-9]*) for ld_flag in $LDFLAGS; do if (test $ld_flag = "-brtl" || test $ld_flag = "-Wl,-brtl"); then aix_use_runtimelinking=yes break fi done ;; esac exp_sym_flag='-bexport' no_entry_flag='-bnoentry' fi # When large executables or shared objects are built, AIX ld can # have problems creating the table of contents. If linking a library # or program results in "error TOC overflow" add -mminimal-toc to # CXXFLAGS/CFLAGS for g++/gcc. In the cases where that is not # enough to fix the problem, add -Wl,-bbigtoc to LDFLAGS. archive_cmds='' hardcode_direct=yes hardcode_direct_absolute=yes hardcode_libdir_separator=':' link_all_deplibs=yes file_list_spec='${wl}-f,' if test "$GCC" = yes; then case $host_os in aix4.[012]|aix4.[012].*) # We only want to do this on AIX 4.2 and lower, the check # below for broken collect2 doesn't work under 4.3+ collect2name=`${CC} -print-prog-name=collect2` if test -f "$collect2name" && strings "$collect2name" | $GREP resolve_lib_name >/dev/null then # We have reworked collect2 : else # We have old collect2 hardcode_direct=unsupported # It fails to find uninstalled libraries when the uninstalled # path is not listed in the libpath. Setting hardcode_minus_L # to unsupported forces relinking hardcode_minus_L=yes hardcode_libdir_flag_spec='-L$libdir' hardcode_libdir_separator= fi ;; esac shared_flag='-shared' if test "$aix_use_runtimelinking" = yes; then shared_flag="$shared_flag "'${wl}-G' fi link_all_deplibs=no else # not using gcc if test "$host_cpu" = ia64; then # VisualAge C++, Version 5.5 for AIX 5L for IA-64, Beta 3 Release # chokes on -Wl,-G. The following line is correct: shared_flag='-G' else if test "$aix_use_runtimelinking" = yes; then shared_flag='${wl}-G' else shared_flag='${wl}-bM:SRE' fi fi fi export_dynamic_flag_spec='${wl}-bexpall' # It seems that -bexpall does not export symbols beginning with # underscore (_), so it is better to generate a list of symbols to export. always_export_symbols=yes if test "$aix_use_runtimelinking" = yes; then # Warning - without using the other runtime loading flags (-brtl), # -berok will link without error, but may produce a broken library. allow_undefined_flag='-berok' # Determine the default libpath from the value encoded in an # empty executable. if test "${lt_cv_aix_libpath+set}" = set; then aix_libpath=$lt_cv_aix_libpath else if ${lt_cv_aix_libpath_+:} false; then : $as_echo_n "(cached) " >&6 else cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ int main () { ; return 0; } _ACEOF if ac_fn_c_try_link "$LINENO"; then : lt_aix_libpath_sed=' /Import File Strings/,/^$/ { /^0/ { s/^0 *\([^ ]*\) *$/\1/ p } }' lt_cv_aix_libpath_=`dump -H conftest$ac_exeext 2>/dev/null | $SED -n -e "$lt_aix_libpath_sed"` # Check for a 64-bit object if we didn't find anything. if test -z "$lt_cv_aix_libpath_"; then lt_cv_aix_libpath_=`dump -HX64 conftest$ac_exeext 2>/dev/null | $SED -n -e "$lt_aix_libpath_sed"` fi fi rm -f core conftest.err conftest.$ac_objext \ conftest$ac_exeext conftest.$ac_ext if test -z "$lt_cv_aix_libpath_"; then lt_cv_aix_libpath_="/usr/lib:/lib" fi fi aix_libpath=$lt_cv_aix_libpath_ fi hardcode_libdir_flag_spec='${wl}-blibpath:$libdir:'"$aix_libpath" archive_expsym_cmds='$CC -o $output_objdir/$soname $libobjs $deplibs '"\${wl}$no_entry_flag"' $compiler_flags `if test "x${allow_undefined_flag}" != "x"; then func_echo_all "${wl}${allow_undefined_flag}"; else :; fi` '"\${wl}$exp_sym_flag:\$export_symbols $shared_flag" else if test "$host_cpu" = ia64; then hardcode_libdir_flag_spec='${wl}-R $libdir:/usr/lib:/lib' allow_undefined_flag="-z nodefs" archive_expsym_cmds="\$CC $shared_flag"' -o $output_objdir/$soname $libobjs $deplibs '"\${wl}$no_entry_flag"' $compiler_flags ${wl}${allow_undefined_flag} '"\${wl}$exp_sym_flag:\$export_symbols" else # Determine the default libpath from the value encoded in an # empty executable. if test "${lt_cv_aix_libpath+set}" = set; then aix_libpath=$lt_cv_aix_libpath else if ${lt_cv_aix_libpath_+:} false; then : $as_echo_n "(cached) " >&6 else cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ int main () { ; return 0; } _ACEOF if ac_fn_c_try_link "$LINENO"; then : lt_aix_libpath_sed=' /Import File Strings/,/^$/ { /^0/ { s/^0 *\([^ ]*\) *$/\1/ p } }' lt_cv_aix_libpath_=`dump -H conftest$ac_exeext 2>/dev/null | $SED -n -e "$lt_aix_libpath_sed"` # Check for a 64-bit object if we didn't find anything. if test -z "$lt_cv_aix_libpath_"; then lt_cv_aix_libpath_=`dump -HX64 conftest$ac_exeext 2>/dev/null | $SED -n -e "$lt_aix_libpath_sed"` fi fi rm -f core conftest.err conftest.$ac_objext \ conftest$ac_exeext conftest.$ac_ext if test -z "$lt_cv_aix_libpath_"; then lt_cv_aix_libpath_="/usr/lib:/lib" fi fi aix_libpath=$lt_cv_aix_libpath_ fi hardcode_libdir_flag_spec='${wl}-blibpath:$libdir:'"$aix_libpath" # Warning - without using the other run time loading flags, # -berok will link without error, but may produce a broken library. no_undefined_flag=' ${wl}-bernotok' allow_undefined_flag=' ${wl}-berok' if test "$with_gnu_ld" = yes; then # We only use this code for GNU lds that support --whole-archive. whole_archive_flag_spec='${wl}--whole-archive$convenience ${wl}--no-whole-archive' else # Exported symbols can be pulled into shared objects from archives whole_archive_flag_spec='$convenience' fi archive_cmds_need_lc=yes # This is similar to how AIX traditionally builds its shared libraries. archive_expsym_cmds="\$CC $shared_flag"' -o $output_objdir/$soname $libobjs $deplibs ${wl}-bnoentry $compiler_flags ${wl}-bE:$export_symbols${allow_undefined_flag}~$AR $AR_FLAGS $output_objdir/$libname$release.a $output_objdir/$soname' fi fi ;; amigaos*) case $host_cpu in powerpc) # see comment about AmigaOS4 .so support archive_cmds='$CC -shared $libobjs $deplibs $compiler_flags ${wl}-soname $wl$soname -o $lib' archive_expsym_cmds='' ;; m68k) archive_cmds='$RM $output_objdir/a2ixlibrary.data~$ECHO "#define NAME $libname" > $output_objdir/a2ixlibrary.data~$ECHO "#define LIBRARY_ID 1" >> $output_objdir/a2ixlibrary.data~$ECHO "#define VERSION $major" >> $output_objdir/a2ixlibrary.data~$ECHO "#define REVISION $revision" >> $output_objdir/a2ixlibrary.data~$AR $AR_FLAGS $lib $libobjs~$RANLIB $lib~(cd $output_objdir && a2ixlibrary -32)' hardcode_libdir_flag_spec='-L$libdir' hardcode_minus_L=yes ;; esac ;; bsdi[45]*) export_dynamic_flag_spec=-rdynamic ;; cygwin* | mingw* | pw32* | cegcc*) # When not using gcc, we currently assume that we are using # Microsoft Visual C++. # hardcode_libdir_flag_spec is actually meaningless, as there is # no search path for DLLs. case $cc_basename in cl*) # Native MSVC hardcode_libdir_flag_spec=' ' allow_undefined_flag=unsupported always_export_symbols=yes file_list_spec='@' # Tell ltmain to make .lib files, not .a files. libext=lib # Tell ltmain to make .dll files, not .so files. shrext_cmds=".dll" # FIXME: Setting linknames here is a bad hack. archive_cmds='$CC -o $output_objdir/$soname $libobjs $compiler_flags $deplibs -Wl,-dll~linknames=' archive_expsym_cmds='if test "x`$SED 1q $export_symbols`" = xEXPORTS; then sed -n -e 's/\\\\\\\(.*\\\\\\\)/-link\\\ -EXPORT:\\\\\\\1/' -e '1\\\!p' < $export_symbols > $output_objdir/$soname.exp; else sed -e 's/\\\\\\\(.*\\\\\\\)/-link\\\ -EXPORT:\\\\\\\1/' < $export_symbols > $output_objdir/$soname.exp; fi~ $CC -o $tool_output_objdir$soname $libobjs $compiler_flags $deplibs "@$tool_output_objdir$soname.exp" -Wl,-DLL,-IMPLIB:"$tool_output_objdir$libname.dll.lib"~ linknames=' # The linker will not automatically build a static lib if we build a DLL. # _LT_TAGVAR(old_archive_from_new_cmds, )='true' enable_shared_with_static_runtimes=yes exclude_expsyms='_NULL_IMPORT_DESCRIPTOR|_IMPORT_DESCRIPTOR_.*' export_symbols_cmds='$NM $libobjs $convenience | $global_symbol_pipe | $SED -e '\''/^[BCDGRS][ ]/s/.*[ ]\([^ ]*\)/\1,DATA/'\'' | $SED -e '\''/^[AITW][ ]/s/.*[ ]//'\'' | sort | uniq > $export_symbols' # Don't use ranlib old_postinstall_cmds='chmod 644 $oldlib' postlink_cmds='lt_outputfile="@OUTPUT@"~ lt_tool_outputfile="@TOOL_OUTPUT@"~ case $lt_outputfile in *.exe|*.EXE) ;; *) lt_outputfile="$lt_outputfile.exe" lt_tool_outputfile="$lt_tool_outputfile.exe" ;; esac~ if test "$MANIFEST_TOOL" != ":" && test -f "$lt_outputfile.manifest"; then $MANIFEST_TOOL -manifest "$lt_tool_outputfile.manifest" -outputresource:"$lt_tool_outputfile" || exit 1; $RM "$lt_outputfile.manifest"; fi' ;; *) # Assume MSVC wrapper hardcode_libdir_flag_spec=' ' allow_undefined_flag=unsupported # Tell ltmain to make .lib files, not .a files. libext=lib # Tell ltmain to make .dll files, not .so files. shrext_cmds=".dll" # FIXME: Setting linknames here is a bad hack. archive_cmds='$CC -o $lib $libobjs $compiler_flags `func_echo_all "$deplibs" | $SED '\''s/ -lc$//'\''` -link -dll~linknames=' # The linker will automatically build a .lib file if we build a DLL. old_archive_from_new_cmds='true' # FIXME: Should let the user specify the lib program. old_archive_cmds='lib -OUT:$oldlib$oldobjs$old_deplibs' enable_shared_with_static_runtimes=yes ;; esac ;; darwin* | rhapsody*) archive_cmds_need_lc=no hardcode_direct=no hardcode_automatic=yes hardcode_shlibpath_var=unsupported if test "$lt_cv_ld_force_load" = "yes"; then whole_archive_flag_spec='`for conv in $convenience\"\"; do test -n \"$conv\" && new_convenience=\"$new_convenience ${wl}-force_load,$conv\"; done; func_echo_all \"$new_convenience\"`' else whole_archive_flag_spec='' fi link_all_deplibs=yes allow_undefined_flag="$_lt_dar_allow_undefined" case $cc_basename in ifort*) _lt_dar_can_shared=yes ;; *) _lt_dar_can_shared=$GCC ;; esac if test "$_lt_dar_can_shared" = "yes"; then output_verbose_link_cmd=func_echo_all archive_cmds="\$CC -dynamiclib \$allow_undefined_flag -o \$lib \$libobjs \$deplibs \$compiler_flags -install_name \$rpath/\$soname \$verstring $_lt_dar_single_mod${_lt_dsymutil}" module_cmds="\$CC \$allow_undefined_flag -o \$lib -bundle \$libobjs \$deplibs \$compiler_flags${_lt_dsymutil}" archive_expsym_cmds="sed 's,^,_,' < \$export_symbols > \$output_objdir/\${libname}-symbols.expsym~\$CC -dynamiclib \$allow_undefined_flag -o \$lib \$libobjs \$deplibs \$compiler_flags -install_name \$rpath/\$soname \$verstring ${_lt_dar_single_mod}${_lt_dar_export_syms}${_lt_dsymutil}" module_expsym_cmds="sed -e 's,^,_,' < \$export_symbols > \$output_objdir/\${libname}-symbols.expsym~\$CC \$allow_undefined_flag -o \$lib -bundle \$libobjs \$deplibs \$compiler_flags${_lt_dar_export_syms}${_lt_dsymutil}" else ld_shlibs=no fi ;; dgux*) archive_cmds='$LD -G -h $soname -o $lib $libobjs $deplibs $linker_flags' hardcode_libdir_flag_spec='-L$libdir' hardcode_shlibpath_var=no ;; # FreeBSD 2.2.[012] allows us to include c++rt0.o to get C++ constructor # support. Future versions do this automatically, but an explicit c++rt0.o # does not break anything, and helps significantly (at the cost of a little # extra space). freebsd2.2*) archive_cmds='$LD -Bshareable -o $lib $libobjs $deplibs $linker_flags /usr/lib/c++rt0.o' hardcode_libdir_flag_spec='-R$libdir' hardcode_direct=yes hardcode_shlibpath_var=no ;; # Unfortunately, older versions of FreeBSD 2 do not have this feature. freebsd2.*) archive_cmds='$LD -Bshareable -o $lib $libobjs $deplibs $linker_flags' hardcode_direct=yes hardcode_minus_L=yes hardcode_shlibpath_var=no ;; # FreeBSD 3 and greater uses gcc -shared to do shared libraries. freebsd* | dragonfly*) archive_cmds='$CC -shared $pic_flag -o $lib $libobjs $deplibs $compiler_flags' hardcode_libdir_flag_spec='-R$libdir' hardcode_direct=yes hardcode_shlibpath_var=no ;; hpux9*) if test "$GCC" = yes; then archive_cmds='$RM $output_objdir/$soname~$CC -shared $pic_flag ${wl}+b ${wl}$install_libdir -o $output_objdir/$soname $libobjs $deplibs $compiler_flags~test $output_objdir/$soname = $lib || mv $output_objdir/$soname $lib' else archive_cmds='$RM $output_objdir/$soname~$LD -b +b $install_libdir -o $output_objdir/$soname $libobjs $deplibs $linker_flags~test $output_objdir/$soname = $lib || mv $output_objdir/$soname $lib' fi hardcode_libdir_flag_spec='${wl}+b ${wl}$libdir' hardcode_libdir_separator=: hardcode_direct=yes # hardcode_minus_L: Not really in the search PATH, # but as the default location of the library. hardcode_minus_L=yes export_dynamic_flag_spec='${wl}-E' ;; hpux10*) if test "$GCC" = yes && test "$with_gnu_ld" = no; then archive_cmds='$CC -shared $pic_flag ${wl}+h ${wl}$soname ${wl}+b ${wl}$install_libdir -o $lib $libobjs $deplibs $compiler_flags' else archive_cmds='$LD -b +h $soname +b $install_libdir -o $lib $libobjs $deplibs $linker_flags' fi if test "$with_gnu_ld" = no; then hardcode_libdir_flag_spec='${wl}+b ${wl}$libdir' hardcode_libdir_separator=: hardcode_direct=yes hardcode_direct_absolute=yes export_dynamic_flag_spec='${wl}-E' # hardcode_minus_L: Not really in the search PATH, # but as the default location of the library. hardcode_minus_L=yes fi ;; hpux11*) if test "$GCC" = yes && test "$with_gnu_ld" = no; then case $host_cpu in hppa*64*) archive_cmds='$CC -shared ${wl}+h ${wl}$soname -o $lib $libobjs $deplibs $compiler_flags' ;; ia64*) archive_cmds='$CC -shared $pic_flag ${wl}+h ${wl}$soname ${wl}+nodefaultrpath -o $lib $libobjs $deplibs $compiler_flags' ;; *) archive_cmds='$CC -shared $pic_flag ${wl}+h ${wl}$soname ${wl}+b ${wl}$install_libdir -o $lib $libobjs $deplibs $compiler_flags' ;; esac else case $host_cpu in hppa*64*) archive_cmds='$CC -b ${wl}+h ${wl}$soname -o $lib $libobjs $deplibs $compiler_flags' ;; ia64*) archive_cmds='$CC -b ${wl}+h ${wl}$soname ${wl}+nodefaultrpath -o $lib $libobjs $deplibs $compiler_flags' ;; *) # Older versions of the 11.00 compiler do not understand -b yet # (HP92453-01 A.11.01.20 doesn't, HP92453-01 B.11.X.35175-35176.GP does) { $as_echo "$as_me:${as_lineno-$LINENO}: checking if $CC understands -b" >&5 $as_echo_n "checking if $CC understands -b... " >&6; } if ${lt_cv_prog_compiler__b+:} false; then : $as_echo_n "(cached) " >&6 else lt_cv_prog_compiler__b=no save_LDFLAGS="$LDFLAGS" LDFLAGS="$LDFLAGS -b" echo "$lt_simple_link_test_code" > conftest.$ac_ext if (eval $ac_link 2>conftest.err) && test -s conftest$ac_exeext; then # The linker can only warn and ignore the option if not recognized # So say no if there are warnings if test -s conftest.err; then # Append any errors to the config.log. cat conftest.err 1>&5 $ECHO "$_lt_linker_boilerplate" | $SED '/^$/d' > conftest.exp $SED '/^$/d; /^ *+/d' conftest.err >conftest.er2 if diff conftest.exp conftest.er2 >/dev/null; then lt_cv_prog_compiler__b=yes fi else lt_cv_prog_compiler__b=yes fi fi $RM -r conftest* LDFLAGS="$save_LDFLAGS" fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $lt_cv_prog_compiler__b" >&5 $as_echo "$lt_cv_prog_compiler__b" >&6; } if test x"$lt_cv_prog_compiler__b" = xyes; then archive_cmds='$CC -b ${wl}+h ${wl}$soname ${wl}+b ${wl}$install_libdir -o $lib $libobjs $deplibs $compiler_flags' else archive_cmds='$LD -b +h $soname +b $install_libdir -o $lib $libobjs $deplibs $linker_flags' fi ;; esac fi if test "$with_gnu_ld" = no; then hardcode_libdir_flag_spec='${wl}+b ${wl}$libdir' hardcode_libdir_separator=: case $host_cpu in hppa*64*|ia64*) hardcode_direct=no hardcode_shlibpath_var=no ;; *) hardcode_direct=yes hardcode_direct_absolute=yes export_dynamic_flag_spec='${wl}-E' # hardcode_minus_L: Not really in the search PATH, # but as the default location of the library. hardcode_minus_L=yes ;; esac fi ;; irix5* | irix6* | nonstopux*) if test "$GCC" = yes; then archive_cmds='$CC -shared $pic_flag $libobjs $deplibs $compiler_flags ${wl}-soname ${wl}$soname `test -n "$verstring" && func_echo_all "${wl}-set_version ${wl}$verstring"` ${wl}-update_registry ${wl}${output_objdir}/so_locations -o $lib' # Try to use the -exported_symbol ld option, if it does not # work, assume that -exports_file does not work either and # implicitly export all symbols. # This should be the same for all languages, so no per-tag cache variable. { $as_echo "$as_me:${as_lineno-$LINENO}: checking whether the $host_os linker accepts -exported_symbol" >&5 $as_echo_n "checking whether the $host_os linker accepts -exported_symbol... " >&6; } if ${lt_cv_irix_exported_symbol+:} false; then : $as_echo_n "(cached) " >&6 else save_LDFLAGS="$LDFLAGS" LDFLAGS="$LDFLAGS -shared ${wl}-exported_symbol ${wl}foo ${wl}-update_registry ${wl}/dev/null" cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ int foo (void) { return 0; } _ACEOF if ac_fn_c_try_link "$LINENO"; then : lt_cv_irix_exported_symbol=yes else lt_cv_irix_exported_symbol=no fi rm -f core conftest.err conftest.$ac_objext \ conftest$ac_exeext conftest.$ac_ext LDFLAGS="$save_LDFLAGS" fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $lt_cv_irix_exported_symbol" >&5 $as_echo "$lt_cv_irix_exported_symbol" >&6; } if test "$lt_cv_irix_exported_symbol" = yes; then archive_expsym_cmds='$CC -shared $pic_flag $libobjs $deplibs $compiler_flags ${wl}-soname ${wl}$soname `test -n "$verstring" && func_echo_all "${wl}-set_version ${wl}$verstring"` ${wl}-update_registry ${wl}${output_objdir}/so_locations ${wl}-exports_file ${wl}$export_symbols -o $lib' fi else archive_cmds='$CC -shared $libobjs $deplibs $compiler_flags -soname $soname `test -n "$verstring" && func_echo_all "-set_version $verstring"` -update_registry ${output_objdir}/so_locations -o $lib' archive_expsym_cmds='$CC -shared $libobjs $deplibs $compiler_flags -soname $soname `test -n "$verstring" && func_echo_all "-set_version $verstring"` -update_registry ${output_objdir}/so_locations -exports_file $export_symbols -o $lib' fi archive_cmds_need_lc='no' hardcode_libdir_flag_spec='${wl}-rpath ${wl}$libdir' hardcode_libdir_separator=: inherit_rpath=yes link_all_deplibs=yes ;; netbsd* | netbsdelf*-gnu) if echo __ELF__ | $CC -E - | $GREP __ELF__ >/dev/null; then archive_cmds='$LD -Bshareable -o $lib $libobjs $deplibs $linker_flags' # a.out else archive_cmds='$LD -shared -o $lib $libobjs $deplibs $linker_flags' # ELF fi hardcode_libdir_flag_spec='-R$libdir' hardcode_direct=yes hardcode_shlibpath_var=no ;; newsos6) archive_cmds='$LD -G -h $soname -o $lib $libobjs $deplibs $linker_flags' hardcode_direct=yes hardcode_libdir_flag_spec='${wl}-rpath ${wl}$libdir' hardcode_libdir_separator=: hardcode_shlibpath_var=no ;; *nto* | *qnx*) ;; openbsd*) if test -f /usr/libexec/ld.so; then hardcode_direct=yes hardcode_shlibpath_var=no hardcode_direct_absolute=yes if test -z "`echo __ELF__ | $CC -E - | $GREP __ELF__`" || test "$host_os-$host_cpu" = "openbsd2.8-powerpc"; then archive_cmds='$CC -shared $pic_flag -o $lib $libobjs $deplibs $compiler_flags' archive_expsym_cmds='$CC -shared $pic_flag -o $lib $libobjs $deplibs $compiler_flags ${wl}-retain-symbols-file,$export_symbols' hardcode_libdir_flag_spec='${wl}-rpath,$libdir' export_dynamic_flag_spec='${wl}-E' else case $host_os in openbsd[01].* | openbsd2.[0-7] | openbsd2.[0-7].*) archive_cmds='$LD -Bshareable -o $lib $libobjs $deplibs $linker_flags' hardcode_libdir_flag_spec='-R$libdir' ;; *) archive_cmds='$CC -shared $pic_flag -o $lib $libobjs $deplibs $compiler_flags' hardcode_libdir_flag_spec='${wl}-rpath,$libdir' ;; esac fi else ld_shlibs=no fi ;; os2*) hardcode_libdir_flag_spec='-L$libdir' hardcode_minus_L=yes allow_undefined_flag=unsupported archive_cmds='$ECHO "LIBRARY $libname INITINSTANCE" > $output_objdir/$libname.def~$ECHO "DESCRIPTION \"$libname\"" >> $output_objdir/$libname.def~echo DATA >> $output_objdir/$libname.def~echo " SINGLE NONSHARED" >> $output_objdir/$libname.def~echo EXPORTS >> $output_objdir/$libname.def~emxexp $libobjs >> $output_objdir/$libname.def~$CC -Zdll -Zcrtdll -o $lib $libobjs $deplibs $compiler_flags $output_objdir/$libname.def' old_archive_from_new_cmds='emximp -o $output_objdir/$libname.a $output_objdir/$libname.def' ;; osf3*) if test "$GCC" = yes; then allow_undefined_flag=' ${wl}-expect_unresolved ${wl}\*' archive_cmds='$CC -shared${allow_undefined_flag} $libobjs $deplibs $compiler_flags ${wl}-soname ${wl}$soname `test -n "$verstring" && func_echo_all "${wl}-set_version ${wl}$verstring"` ${wl}-update_registry ${wl}${output_objdir}/so_locations -o $lib' else allow_undefined_flag=' -expect_unresolved \*' archive_cmds='$CC -shared${allow_undefined_flag} $libobjs $deplibs $compiler_flags -soname $soname `test -n "$verstring" && func_echo_all "-set_version $verstring"` -update_registry ${output_objdir}/so_locations -o $lib' fi archive_cmds_need_lc='no' hardcode_libdir_flag_spec='${wl}-rpath ${wl}$libdir' hardcode_libdir_separator=: ;; osf4* | osf5*) # as osf3* with the addition of -msym flag if test "$GCC" = yes; then allow_undefined_flag=' ${wl}-expect_unresolved ${wl}\*' archive_cmds='$CC -shared${allow_undefined_flag} $pic_flag $libobjs $deplibs $compiler_flags ${wl}-msym ${wl}-soname ${wl}$soname `test -n "$verstring" && func_echo_all "${wl}-set_version ${wl}$verstring"` ${wl}-update_registry ${wl}${output_objdir}/so_locations -o $lib' hardcode_libdir_flag_spec='${wl}-rpath ${wl}$libdir' else allow_undefined_flag=' -expect_unresolved \*' archive_cmds='$CC -shared${allow_undefined_flag} $libobjs $deplibs $compiler_flags -msym -soname $soname `test -n "$verstring" && func_echo_all "-set_version $verstring"` -update_registry ${output_objdir}/so_locations -o $lib' archive_expsym_cmds='for i in `cat $export_symbols`; do printf "%s %s\\n" -exported_symbol "\$i" >> $lib.exp; done; printf "%s\\n" "-hidden">> $lib.exp~ $CC -shared${allow_undefined_flag} ${wl}-input ${wl}$lib.exp $compiler_flags $libobjs $deplibs -soname $soname `test -n "$verstring" && $ECHO "-set_version $verstring"` -update_registry ${output_objdir}/so_locations -o $lib~$RM $lib.exp' # Both c and cxx compiler support -rpath directly hardcode_libdir_flag_spec='-rpath $libdir' fi archive_cmds_need_lc='no' hardcode_libdir_separator=: ;; solaris*) no_undefined_flag=' -z defs' if test "$GCC" = yes; then wlarc='${wl}' archive_cmds='$CC -shared $pic_flag ${wl}-z ${wl}text ${wl}-h ${wl}$soname -o $lib $libobjs $deplibs $compiler_flags' archive_expsym_cmds='echo "{ global:" > $lib.exp~cat $export_symbols | $SED -e "s/\(.*\)/\1;/" >> $lib.exp~echo "local: *; };" >> $lib.exp~ $CC -shared $pic_flag ${wl}-z ${wl}text ${wl}-M ${wl}$lib.exp ${wl}-h ${wl}$soname -o $lib $libobjs $deplibs $compiler_flags~$RM $lib.exp' else case `$CC -V 2>&1` in *"Compilers 5.0"*) wlarc='' archive_cmds='$LD -G${allow_undefined_flag} -h $soname -o $lib $libobjs $deplibs $linker_flags' archive_expsym_cmds='echo "{ global:" > $lib.exp~cat $export_symbols | $SED -e "s/\(.*\)/\1;/" >> $lib.exp~echo "local: *; };" >> $lib.exp~ $LD -G${allow_undefined_flag} -M $lib.exp -h $soname -o $lib $libobjs $deplibs $linker_flags~$RM $lib.exp' ;; *) wlarc='${wl}' archive_cmds='$CC -G${allow_undefined_flag} -h $soname -o $lib $libobjs $deplibs $compiler_flags' archive_expsym_cmds='echo "{ global:" > $lib.exp~cat $export_symbols | $SED -e "s/\(.*\)/\1;/" >> $lib.exp~echo "local: *; };" >> $lib.exp~ $CC -G${allow_undefined_flag} -M $lib.exp -h $soname -o $lib $libobjs $deplibs $compiler_flags~$RM $lib.exp' ;; esac fi hardcode_libdir_flag_spec='-R$libdir' hardcode_shlibpath_var=no case $host_os in solaris2.[0-5] | solaris2.[0-5].*) ;; *) # The compiler driver will combine and reorder linker options, # but understands `-z linker_flag'. GCC discards it without `$wl', # but is careful enough not to reorder. # Supported since Solaris 2.6 (maybe 2.5.1?) if test "$GCC" = yes; then whole_archive_flag_spec='${wl}-z ${wl}allextract$convenience ${wl}-z ${wl}defaultextract' else whole_archive_flag_spec='-z allextract$convenience -z defaultextract' fi ;; esac link_all_deplibs=yes ;; sunos4*) if test "x$host_vendor" = xsequent; then # Use $CC to link under sequent, because it throws in some extra .o # files that make .init and .fini sections work. archive_cmds='$CC -G ${wl}-h $soname -o $lib $libobjs $deplibs $compiler_flags' else archive_cmds='$LD -assert pure-text -Bstatic -o $lib $libobjs $deplibs $linker_flags' fi hardcode_libdir_flag_spec='-L$libdir' hardcode_direct=yes hardcode_minus_L=yes hardcode_shlibpath_var=no ;; sysv4) case $host_vendor in sni) archive_cmds='$LD -G -h $soname -o $lib $libobjs $deplibs $linker_flags' hardcode_direct=yes # is this really true??? ;; siemens) ## LD is ld it makes a PLAMLIB ## CC just makes a GrossModule. archive_cmds='$LD -G -o $lib $libobjs $deplibs $linker_flags' reload_cmds='$CC -r -o $output$reload_objs' hardcode_direct=no ;; motorola) archive_cmds='$LD -G -h $soname -o $lib $libobjs $deplibs $linker_flags' hardcode_direct=no #Motorola manual says yes, but my tests say they lie ;; esac runpath_var='LD_RUN_PATH' hardcode_shlibpath_var=no ;; sysv4.3*) archive_cmds='$LD -G -h $soname -o $lib $libobjs $deplibs $linker_flags' hardcode_shlibpath_var=no export_dynamic_flag_spec='-Bexport' ;; sysv4*MP*) if test -d /usr/nec; then archive_cmds='$LD -G -h $soname -o $lib $libobjs $deplibs $linker_flags' hardcode_shlibpath_var=no runpath_var=LD_RUN_PATH hardcode_runpath_var=yes ld_shlibs=yes fi ;; sysv4*uw2* | sysv5OpenUNIX* | sysv5UnixWare7.[01].[10]* | unixware7* | sco3.2v5.0.[024]*) no_undefined_flag='${wl}-z,text' archive_cmds_need_lc=no hardcode_shlibpath_var=no runpath_var='LD_RUN_PATH' if test "$GCC" = yes; then archive_cmds='$CC -shared ${wl}-h,$soname -o $lib $libobjs $deplibs $compiler_flags' archive_expsym_cmds='$CC -shared ${wl}-Bexport:$export_symbols ${wl}-h,$soname -o $lib $libobjs $deplibs $compiler_flags' else archive_cmds='$CC -G ${wl}-h,$soname -o $lib $libobjs $deplibs $compiler_flags' archive_expsym_cmds='$CC -G ${wl}-Bexport:$export_symbols ${wl}-h,$soname -o $lib $libobjs $deplibs $compiler_flags' fi ;; sysv5* | sco3.2v5* | sco5v6*) # Note: We can NOT use -z defs as we might desire, because we do not # link with -lc, and that would cause any symbols used from libc to # always be unresolved, which means just about no library would # ever link correctly. If we're not using GNU ld we use -z text # though, which does catch some bad symbols but isn't as heavy-handed # as -z defs. no_undefined_flag='${wl}-z,text' allow_undefined_flag='${wl}-z,nodefs' archive_cmds_need_lc=no hardcode_shlibpath_var=no hardcode_libdir_flag_spec='${wl}-R,$libdir' hardcode_libdir_separator=':' link_all_deplibs=yes export_dynamic_flag_spec='${wl}-Bexport' runpath_var='LD_RUN_PATH' if test "$GCC" = yes; then archive_cmds='$CC -shared ${wl}-h,$soname -o $lib $libobjs $deplibs $compiler_flags' archive_expsym_cmds='$CC -shared ${wl}-Bexport:$export_symbols ${wl}-h,$soname -o $lib $libobjs $deplibs $compiler_flags' else archive_cmds='$CC -G ${wl}-h,$soname -o $lib $libobjs $deplibs $compiler_flags' archive_expsym_cmds='$CC -G ${wl}-Bexport:$export_symbols ${wl}-h,$soname -o $lib $libobjs $deplibs $compiler_flags' fi ;; uts4*) archive_cmds='$LD -G -h $soname -o $lib $libobjs $deplibs $linker_flags' hardcode_libdir_flag_spec='-L$libdir' hardcode_shlibpath_var=no ;; *) ld_shlibs=no ;; esac if test x$host_vendor = xsni; then case $host in sysv4 | sysv4.2uw2* | sysv4.3* | sysv5*) export_dynamic_flag_spec='${wl}-Blargedynsym' ;; esac fi fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ld_shlibs" >&5 $as_echo "$ld_shlibs" >&6; } test "$ld_shlibs" = no && can_build_shared=no with_gnu_ld=$with_gnu_ld # # Do we need to explicitly link libc? # case "x$archive_cmds_need_lc" in x|xyes) # Assume -lc should be added archive_cmds_need_lc=yes if test "$enable_shared" = yes && test "$GCC" = yes; then case $archive_cmds in *'~'*) # FIXME: we may have to deal with multi-command sequences. ;; '$CC '*) # Test whether the compiler implicitly links with -lc since on some # systems, -lgcc has to come before -lc. If gcc already passes -lc # to ld, don't add -lc before -lgcc. { $as_echo "$as_me:${as_lineno-$LINENO}: checking whether -lc should be explicitly linked in" >&5 $as_echo_n "checking whether -lc should be explicitly linked in... " >&6; } if ${lt_cv_archive_cmds_need_lc+:} false; then : $as_echo_n "(cached) " >&6 else $RM conftest* echo "$lt_simple_compile_test_code" > conftest.$ac_ext if { { eval echo "\"\$as_me\":${as_lineno-$LINENO}: \"$ac_compile\""; } >&5 (eval $ac_compile) 2>&5 ac_status=$? $as_echo "$as_me:${as_lineno-$LINENO}: \$? = $ac_status" >&5 test $ac_status = 0; } 2>conftest.err; then soname=conftest lib=conftest libobjs=conftest.$ac_objext deplibs= wl=$lt_prog_compiler_wl pic_flag=$lt_prog_compiler_pic compiler_flags=-v linker_flags=-v verstring= output_objdir=. libname=conftest lt_save_allow_undefined_flag=$allow_undefined_flag allow_undefined_flag= if { { eval echo "\"\$as_me\":${as_lineno-$LINENO}: \"$archive_cmds 2\>\&1 \| $GREP \" -lc \" \>/dev/null 2\>\&1\""; } >&5 (eval $archive_cmds 2\>\&1 \| $GREP \" -lc \" \>/dev/null 2\>\&1) 2>&5 ac_status=$? $as_echo "$as_me:${as_lineno-$LINENO}: \$? = $ac_status" >&5 test $ac_status = 0; } then lt_cv_archive_cmds_need_lc=no else lt_cv_archive_cmds_need_lc=yes fi allow_undefined_flag=$lt_save_allow_undefined_flag else cat conftest.err 1>&5 fi $RM conftest* fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $lt_cv_archive_cmds_need_lc" >&5 $as_echo "$lt_cv_archive_cmds_need_lc" >&6; } archive_cmds_need_lc=$lt_cv_archive_cmds_need_lc ;; esac fi ;; esac { $as_echo "$as_me:${as_lineno-$LINENO}: checking dynamic linker characteristics" >&5 $as_echo_n "checking dynamic linker characteristics... " >&6; } if test "$GCC" = yes; then case $host_os in darwin*) lt_awk_arg="/^libraries:/,/LR/" ;; *) lt_awk_arg="/^libraries:/" ;; esac case $host_os in mingw* | cegcc*) lt_sed_strip_eq="s,=\([A-Za-z]:\),\1,g" ;; *) lt_sed_strip_eq="s,=/,/,g" ;; esac lt_search_path_spec=`$CC -print-search-dirs | awk $lt_awk_arg | $SED -e "s/^libraries://" -e $lt_sed_strip_eq` case $lt_search_path_spec in *\;*) # if the path contains ";" then we assume it to be the separator # otherwise default to the standard path separator (i.e. ":") - it is # assumed that no part of a normal pathname contains ";" but that should # okay in the real world where ";" in dirpaths is itself problematic. lt_search_path_spec=`$ECHO "$lt_search_path_spec" | $SED 's/;/ /g'` ;; *) lt_search_path_spec=`$ECHO "$lt_search_path_spec" | $SED "s/$PATH_SEPARATOR/ /g"` ;; esac # Ok, now we have the path, separated by spaces, we can step through it # and add multilib dir if necessary. lt_tmp_lt_search_path_spec= lt_multi_os_dir=`$CC $CPPFLAGS $CFLAGS $LDFLAGS -print-multi-os-directory 2>/dev/null` for lt_sys_path in $lt_search_path_spec; do if test -d "$lt_sys_path/$lt_multi_os_dir"; then lt_tmp_lt_search_path_spec="$lt_tmp_lt_search_path_spec $lt_sys_path/$lt_multi_os_dir" else test -d "$lt_sys_path" && \ lt_tmp_lt_search_path_spec="$lt_tmp_lt_search_path_spec $lt_sys_path" fi done lt_search_path_spec=`$ECHO "$lt_tmp_lt_search_path_spec" | awk ' BEGIN {RS=" "; FS="/|\n";} { lt_foo=""; lt_count=0; for (lt_i = NF; lt_i > 0; lt_i--) { if ($lt_i != "" && $lt_i != ".") { if ($lt_i == "..") { lt_count++; } else { if (lt_count == 0) { lt_foo="/" $lt_i lt_foo; } else { lt_count--; } } } } if (lt_foo != "") { lt_freq[lt_foo]++; } if (lt_freq[lt_foo] == 1) { print lt_foo; } }'` # AWK program above erroneously prepends '/' to C:/dos/paths # for these hosts. case $host_os in mingw* | cegcc*) lt_search_path_spec=`$ECHO "$lt_search_path_spec" |\ $SED 's,/\([A-Za-z]:\),\1,g'` ;; esac sys_lib_search_path_spec=`$ECHO "$lt_search_path_spec" | $lt_NL2SP` else sys_lib_search_path_spec="/lib /usr/lib /usr/local/lib" fi library_names_spec= libname_spec='lib$name' soname_spec= shrext_cmds=".so" postinstall_cmds= postuninstall_cmds= finish_cmds= finish_eval= shlibpath_var= shlibpath_overrides_runpath=unknown version_type=none dynamic_linker="$host_os ld.so" sys_lib_dlsearch_path_spec="/lib /usr/lib" need_lib_prefix=unknown hardcode_into_libs=no # when you set need_version to no, make sure it does not cause -set_version # flags to be left without arguments need_version=unknown case $host_os in aix3*) version_type=linux # correct to gnu/linux during the next big refactor library_names_spec='${libname}${release}${shared_ext}$versuffix $libname.a' shlibpath_var=LIBPATH # AIX 3 has no versioning support, so we append a major version to the name. soname_spec='${libname}${release}${shared_ext}$major' ;; aix[4-9]*) version_type=linux # correct to gnu/linux during the next big refactor need_lib_prefix=no need_version=no hardcode_into_libs=yes if test "$host_cpu" = ia64; then # AIX 5 supports IA64 library_names_spec='${libname}${release}${shared_ext}$major ${libname}${release}${shared_ext}$versuffix $libname${shared_ext}' shlibpath_var=LD_LIBRARY_PATH else # With GCC up to 2.95.x, collect2 would create an import file # for dependence libraries. The import file would start with # the line `#! .'. This would cause the generated library to # depend on `.', always an invalid library. This was fixed in # development snapshots of GCC prior to 3.0. case $host_os in aix4 | aix4.[01] | aix4.[01].*) if { echo '#if __GNUC__ > 2 || (__GNUC__ == 2 && __GNUC_MINOR__ >= 97)' echo ' yes ' echo '#endif'; } | ${CC} -E - | $GREP yes > /dev/null; then : else can_build_shared=no fi ;; esac # AIX (on Power*) has no versioning support, so currently we can not hardcode correct # soname into executable. Probably we can add versioning support to # collect2, so additional links can be useful in future. if test "$aix_use_runtimelinking" = yes; then # If using run time linking (on AIX 4.2 or later) use lib.so # instead of lib.a to let people know that these are not # typical AIX shared libraries. library_names_spec='${libname}${release}${shared_ext}$versuffix ${libname}${release}${shared_ext}$major $libname${shared_ext}' else # We preserve .a as extension for shared libraries through AIX4.2 # and later when we are not doing run time linking. library_names_spec='${libname}${release}.a $libname.a' soname_spec='${libname}${release}${shared_ext}$major' fi shlibpath_var=LIBPATH fi ;; amigaos*) case $host_cpu in powerpc) # Since July 2007 AmigaOS4 officially supports .so libraries. # When compiling the executable, add -use-dynld -Lsobjs: to the compileline. library_names_spec='${libname}${release}${shared_ext}$versuffix ${libname}${release}${shared_ext}$major $libname${shared_ext}' ;; m68k) library_names_spec='$libname.ixlibrary $libname.a' # Create ${libname}_ixlibrary.a entries in /sys/libs. finish_eval='for lib in `ls $libdir/*.ixlibrary 2>/dev/null`; do libname=`func_echo_all "$lib" | $SED '\''s%^.*/\([^/]*\)\.ixlibrary$%\1%'\''`; test $RM /sys/libs/${libname}_ixlibrary.a; $show "cd /sys/libs && $LN_S $lib ${libname}_ixlibrary.a"; cd /sys/libs && $LN_S $lib ${libname}_ixlibrary.a || exit 1; done' ;; esac ;; beos*) library_names_spec='${libname}${shared_ext}' dynamic_linker="$host_os ld.so" shlibpath_var=LIBRARY_PATH ;; bsdi[45]*) version_type=linux # correct to gnu/linux during the next big refactor need_version=no library_names_spec='${libname}${release}${shared_ext}$versuffix ${libname}${release}${shared_ext}$major $libname${shared_ext}' soname_spec='${libname}${release}${shared_ext}$major' finish_cmds='PATH="\$PATH:/sbin" ldconfig $libdir' shlibpath_var=LD_LIBRARY_PATH sys_lib_search_path_spec="/shlib /usr/lib /usr/X11/lib /usr/contrib/lib /lib /usr/local/lib" sys_lib_dlsearch_path_spec="/shlib /usr/lib /usr/local/lib" # the default ld.so.conf also contains /usr/contrib/lib and # /usr/X11R6/lib (/usr/X11 is a link to /usr/X11R6), but let us allow # libtool to hard-code these into programs ;; cygwin* | mingw* | pw32* | cegcc*) version_type=windows shrext_cmds=".dll" need_version=no need_lib_prefix=no case $GCC,$cc_basename in yes,*) # gcc library_names_spec='$libname.dll.a' # DLL is installed to $(libdir)/../bin by postinstall_cmds postinstall_cmds='base_file=`basename \${file}`~ dlpath=`$SHELL 2>&1 -c '\''. $dir/'\''\${base_file}'\''i; echo \$dlname'\''`~ dldir=$destdir/`dirname \$dlpath`~ test -d \$dldir || mkdir -p \$dldir~ $install_prog $dir/$dlname \$dldir/$dlname~ chmod a+x \$dldir/$dlname~ if test -n '\''$stripme'\'' && test -n '\''$striplib'\''; then eval '\''$striplib \$dldir/$dlname'\'' || exit \$?; fi' postuninstall_cmds='dldll=`$SHELL 2>&1 -c '\''. $file; echo \$dlname'\''`~ dlpath=$dir/\$dldll~ $RM \$dlpath' shlibpath_overrides_runpath=yes case $host_os in cygwin*) # Cygwin DLLs use 'cyg' prefix rather than 'lib' soname_spec='`echo ${libname} | sed -e 's/^lib/cyg/'``echo ${release} | $SED -e 's/[.]/-/g'`${versuffix}${shared_ext}' sys_lib_search_path_spec="$sys_lib_search_path_spec /usr/lib/w32api" ;; mingw* | cegcc*) # MinGW DLLs use traditional 'lib' prefix soname_spec='${libname}`echo ${release} | $SED -e 's/[.]/-/g'`${versuffix}${shared_ext}' ;; pw32*) # pw32 DLLs use 'pw' prefix rather than 'lib' library_names_spec='`echo ${libname} | sed -e 's/^lib/pw/'``echo ${release} | $SED -e 's/[.]/-/g'`${versuffix}${shared_ext}' ;; esac dynamic_linker='Win32 ld.exe' ;; *,cl*) # Native MSVC libname_spec='$name' soname_spec='${libname}`echo ${release} | $SED -e 's/[.]/-/g'`${versuffix}${shared_ext}' library_names_spec='${libname}.dll.lib' case $build_os in mingw*) sys_lib_search_path_spec= lt_save_ifs=$IFS IFS=';' for lt_path in $LIB do IFS=$lt_save_ifs # Let DOS variable expansion print the short 8.3 style file name. lt_path=`cd "$lt_path" 2>/dev/null && cmd //C "for %i in (".") do @echo %~si"` sys_lib_search_path_spec="$sys_lib_search_path_spec $lt_path" done IFS=$lt_save_ifs # Convert to MSYS style. sys_lib_search_path_spec=`$ECHO "$sys_lib_search_path_spec" | sed -e 's|\\\\|/|g' -e 's| \\([a-zA-Z]\\):| /\\1|g' -e 's|^ ||'` ;; cygwin*) # Convert to unix form, then to dos form, then back to unix form # but this time dos style (no spaces!) so that the unix form looks # like /cygdrive/c/PROGRA~1:/cygdr... sys_lib_search_path_spec=`cygpath --path --unix "$LIB"` sys_lib_search_path_spec=`cygpath --path --dos "$sys_lib_search_path_spec" 2>/dev/null` sys_lib_search_path_spec=`cygpath --path --unix "$sys_lib_search_path_spec" | $SED -e "s/$PATH_SEPARATOR/ /g"` ;; *) sys_lib_search_path_spec="$LIB" if $ECHO "$sys_lib_search_path_spec" | $GREP ';[c-zC-Z]:/' >/dev/null; then # It is most probably a Windows format PATH. sys_lib_search_path_spec=`$ECHO "$sys_lib_search_path_spec" | $SED -e 's/;/ /g'` else sys_lib_search_path_spec=`$ECHO "$sys_lib_search_path_spec" | $SED -e "s/$PATH_SEPARATOR/ /g"` fi # FIXME: find the short name or the path components, as spaces are # common. (e.g. "Program Files" -> "PROGRA~1") ;; esac # DLL is installed to $(libdir)/../bin by postinstall_cmds postinstall_cmds='base_file=`basename \${file}`~ dlpath=`$SHELL 2>&1 -c '\''. $dir/'\''\${base_file}'\''i; echo \$dlname'\''`~ dldir=$destdir/`dirname \$dlpath`~ test -d \$dldir || mkdir -p \$dldir~ $install_prog $dir/$dlname \$dldir/$dlname' postuninstall_cmds='dldll=`$SHELL 2>&1 -c '\''. $file; echo \$dlname'\''`~ dlpath=$dir/\$dldll~ $RM \$dlpath' shlibpath_overrides_runpath=yes dynamic_linker='Win32 link.exe' ;; *) # Assume MSVC wrapper library_names_spec='${libname}`echo ${release} | $SED -e 's/[.]/-/g'`${versuffix}${shared_ext} $libname.lib' dynamic_linker='Win32 ld.exe' ;; esac # FIXME: first we should search . and the directory the executable is in shlibpath_var=PATH ;; darwin* | rhapsody*) dynamic_linker="$host_os dyld" version_type=darwin need_lib_prefix=no need_version=no library_names_spec='${libname}${release}${major}$shared_ext ${libname}$shared_ext' soname_spec='${libname}${release}${major}$shared_ext' shlibpath_overrides_runpath=yes shlibpath_var=DYLD_LIBRARY_PATH shrext_cmds='`test .$module = .yes && echo .so || echo .dylib`' sys_lib_search_path_spec="$sys_lib_search_path_spec /usr/local/lib" sys_lib_dlsearch_path_spec='/usr/local/lib /lib /usr/lib' ;; dgux*) version_type=linux # correct to gnu/linux during the next big refactor need_lib_prefix=no need_version=no library_names_spec='${libname}${release}${shared_ext}$versuffix ${libname}${release}${shared_ext}$major $libname$shared_ext' soname_spec='${libname}${release}${shared_ext}$major' shlibpath_var=LD_LIBRARY_PATH ;; freebsd* | dragonfly*) # DragonFly does not have aout. When/if they implement a new # versioning mechanism, adjust this. if test -x /usr/bin/objformat; then objformat=`/usr/bin/objformat` else case $host_os in freebsd[23].*) objformat=aout ;; *) objformat=elf ;; esac fi version_type=freebsd-$objformat case $version_type in freebsd-elf*) library_names_spec='${libname}${release}${shared_ext}$versuffix ${libname}${release}${shared_ext} $libname${shared_ext}' need_version=no need_lib_prefix=no ;; freebsd-*) library_names_spec='${libname}${release}${shared_ext}$versuffix $libname${shared_ext}$versuffix' need_version=yes ;; esac shlibpath_var=LD_LIBRARY_PATH case $host_os in freebsd2.*) shlibpath_overrides_runpath=yes ;; freebsd3.[01]* | freebsdelf3.[01]*) shlibpath_overrides_runpath=yes hardcode_into_libs=yes ;; freebsd3.[2-9]* | freebsdelf3.[2-9]* | \ freebsd4.[0-5] | freebsdelf4.[0-5] | freebsd4.1.1 | freebsdelf4.1.1) shlibpath_overrides_runpath=no hardcode_into_libs=yes ;; *) # from 4.6 on, and DragonFly shlibpath_overrides_runpath=yes hardcode_into_libs=yes ;; esac ;; haiku*) version_type=linux # correct to gnu/linux during the next big refactor need_lib_prefix=no need_version=no dynamic_linker="$host_os runtime_loader" library_names_spec='${libname}${release}${shared_ext}$versuffix ${libname}${release}${shared_ext}${major} ${libname}${shared_ext}' soname_spec='${libname}${release}${shared_ext}$major' shlibpath_var=LIBRARY_PATH shlibpath_overrides_runpath=yes sys_lib_dlsearch_path_spec='/boot/home/config/lib /boot/common/lib /boot/system/lib' hardcode_into_libs=yes ;; hpux9* | hpux10* | hpux11*) # Give a soname corresponding to the major version so that dld.sl refuses to # link against other versions. version_type=sunos need_lib_prefix=no need_version=no case $host_cpu in ia64*) shrext_cmds='.so' hardcode_into_libs=yes dynamic_linker="$host_os dld.so" shlibpath_var=LD_LIBRARY_PATH shlibpath_overrides_runpath=yes # Unless +noenvvar is specified. library_names_spec='${libname}${release}${shared_ext}$versuffix ${libname}${release}${shared_ext}$major $libname${shared_ext}' soname_spec='${libname}${release}${shared_ext}$major' if test "X$HPUX_IA64_MODE" = X32; then sys_lib_search_path_spec="/usr/lib/hpux32 /usr/local/lib/hpux32 /usr/local/lib" else sys_lib_search_path_spec="/usr/lib/hpux64 /usr/local/lib/hpux64" fi sys_lib_dlsearch_path_spec=$sys_lib_search_path_spec ;; hppa*64*) shrext_cmds='.sl' hardcode_into_libs=yes dynamic_linker="$host_os dld.sl" shlibpath_var=LD_LIBRARY_PATH # How should we handle SHLIB_PATH shlibpath_overrides_runpath=yes # Unless +noenvvar is specified. library_names_spec='${libname}${release}${shared_ext}$versuffix ${libname}${release}${shared_ext}$major $libname${shared_ext}' soname_spec='${libname}${release}${shared_ext}$major' sys_lib_search_path_spec="/usr/lib/pa20_64 /usr/ccs/lib/pa20_64" sys_lib_dlsearch_path_spec=$sys_lib_search_path_spec ;; *) shrext_cmds='.sl' dynamic_linker="$host_os dld.sl" shlibpath_var=SHLIB_PATH shlibpath_overrides_runpath=no # +s is required to enable SHLIB_PATH library_names_spec='${libname}${release}${shared_ext}$versuffix ${libname}${release}${shared_ext}$major $libname${shared_ext}' soname_spec='${libname}${release}${shared_ext}$major' ;; esac # HP-UX runs *really* slowly unless shared libraries are mode 555, ... postinstall_cmds='chmod 555 $lib' # or fails outright, so override atomically: install_override_mode=555 ;; interix[3-9]*) version_type=linux # correct to gnu/linux during the next big refactor need_lib_prefix=no need_version=no library_names_spec='${libname}${release}${shared_ext}$versuffix ${libname}${release}${shared_ext}$major ${libname}${shared_ext}' soname_spec='${libname}${release}${shared_ext}$major' dynamic_linker='Interix 3.x ld.so.1 (PE, like ELF)' shlibpath_var=LD_LIBRARY_PATH shlibpath_overrides_runpath=no hardcode_into_libs=yes ;; irix5* | irix6* | nonstopux*) case $host_os in nonstopux*) version_type=nonstopux ;; *) if test "$lt_cv_prog_gnu_ld" = yes; then version_type=linux # correct to gnu/linux during the next big refactor else version_type=irix fi ;; esac need_lib_prefix=no need_version=no soname_spec='${libname}${release}${shared_ext}$major' library_names_spec='${libname}${release}${shared_ext}$versuffix ${libname}${release}${shared_ext}$major ${libname}${release}${shared_ext} $libname${shared_ext}' case $host_os in irix5* | nonstopux*) libsuff= shlibsuff= ;; *) case $LD in # libtool.m4 will add one of these switches to LD *-32|*"-32 "|*-melf32bsmip|*"-melf32bsmip ") libsuff= shlibsuff= libmagic=32-bit;; *-n32|*"-n32 "|*-melf32bmipn32|*"-melf32bmipn32 ") libsuff=32 shlibsuff=N32 libmagic=N32;; *-64|*"-64 "|*-melf64bmip|*"-melf64bmip ") libsuff=64 shlibsuff=64 libmagic=64-bit;; *) libsuff= shlibsuff= libmagic=never-match;; esac ;; esac shlibpath_var=LD_LIBRARY${shlibsuff}_PATH shlibpath_overrides_runpath=no sys_lib_search_path_spec="/usr/lib${libsuff} /lib${libsuff} /usr/local/lib${libsuff}" sys_lib_dlsearch_path_spec="/usr/lib${libsuff} /lib${libsuff}" hardcode_into_libs=yes ;; # No shared lib support for Linux oldld, aout, or coff. linux*oldld* | linux*aout* | linux*coff*) dynamic_linker=no ;; # This must be glibc/ELF. linux* | k*bsd*-gnu | kopensolaris*-gnu | gnu*) version_type=linux # correct to gnu/linux during the next big refactor need_lib_prefix=no need_version=no library_names_spec='${libname}${release}${shared_ext}$versuffix ${libname}${release}${shared_ext}$major $libname${shared_ext}' soname_spec='${libname}${release}${shared_ext}$major' finish_cmds='PATH="\$PATH:/sbin" ldconfig -n $libdir' shlibpath_var=LD_LIBRARY_PATH shlibpath_overrides_runpath=no # Some binutils ld are patched to set DT_RUNPATH if ${lt_cv_shlibpath_overrides_runpath+:} false; then : $as_echo_n "(cached) " >&6 else lt_cv_shlibpath_overrides_runpath=no save_LDFLAGS=$LDFLAGS save_libdir=$libdir eval "libdir=/foo; wl=\"$lt_prog_compiler_wl\"; \ LDFLAGS=\"\$LDFLAGS $hardcode_libdir_flag_spec\"" cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ int main () { ; return 0; } _ACEOF if ac_fn_c_try_link "$LINENO"; then : if ($OBJDUMP -p conftest$ac_exeext) 2>/dev/null | grep "RUNPATH.*$libdir" >/dev/null; then : lt_cv_shlibpath_overrides_runpath=yes fi fi rm -f core conftest.err conftest.$ac_objext \ conftest$ac_exeext conftest.$ac_ext LDFLAGS=$save_LDFLAGS libdir=$save_libdir fi shlibpath_overrides_runpath=$lt_cv_shlibpath_overrides_runpath # This implies no fast_install, which is unacceptable. # Some rework will be needed to allow for fast_install # before this can be enabled. hardcode_into_libs=yes # Append ld.so.conf contents to the search path if test -f /etc/ld.so.conf; then lt_ld_extra=`awk '/^include / { system(sprintf("cd /etc; cat %s 2>/dev/null", \$2)); skip = 1; } { if (!skip) print \$0; skip = 0; }' < /etc/ld.so.conf | $SED -e 's/#.*//;/^[ ]*hwcap[ ]/d;s/[:, ]/ /g;s/=[^=]*$//;s/=[^= ]* / /g;s/"//g;/^$/d' | tr '\n' ' '` sys_lib_dlsearch_path_spec="/lib /usr/lib $lt_ld_extra" fi # We used to test for /lib/ld.so.1 and disable shared libraries on # powerpc, because MkLinux only supported shared libraries with the # GNU dynamic linker. Since this was broken with cross compilers, # most powerpc-linux boxes support dynamic linking these days and # people can always --disable-shared, the test was removed, and we # assume the GNU/Linux dynamic linker is in use. dynamic_linker='GNU/Linux ld.so' ;; netbsdelf*-gnu) version_type=linux need_lib_prefix=no need_version=no library_names_spec='${libname}${release}${shared_ext}$versuffix ${libname}${release}${shared_ext}$major ${libname}${shared_ext}' soname_spec='${libname}${release}${shared_ext}$major' shlibpath_var=LD_LIBRARY_PATH shlibpath_overrides_runpath=no hardcode_into_libs=yes dynamic_linker='NetBSD ld.elf_so' ;; netbsd*) version_type=sunos need_lib_prefix=no need_version=no if echo __ELF__ | $CC -E - | $GREP __ELF__ >/dev/null; then library_names_spec='${libname}${release}${shared_ext}$versuffix ${libname}${shared_ext}$versuffix' finish_cmds='PATH="\$PATH:/sbin" ldconfig -m $libdir' dynamic_linker='NetBSD (a.out) ld.so' else library_names_spec='${libname}${release}${shared_ext}$versuffix ${libname}${release}${shared_ext}$major ${libname}${shared_ext}' soname_spec='${libname}${release}${shared_ext}$major' dynamic_linker='NetBSD ld.elf_so' fi shlibpath_var=LD_LIBRARY_PATH shlibpath_overrides_runpath=yes hardcode_into_libs=yes ;; newsos6) version_type=linux # correct to gnu/linux during the next big refactor library_names_spec='${libname}${release}${shared_ext}$versuffix ${libname}${release}${shared_ext}$major $libname${shared_ext}' shlibpath_var=LD_LIBRARY_PATH shlibpath_overrides_runpath=yes ;; *nto* | *qnx*) version_type=qnx need_lib_prefix=no need_version=no library_names_spec='${libname}${release}${shared_ext}$versuffix ${libname}${release}${shared_ext}$major $libname${shared_ext}' soname_spec='${libname}${release}${shared_ext}$major' shlibpath_var=LD_LIBRARY_PATH shlibpath_overrides_runpath=no hardcode_into_libs=yes dynamic_linker='ldqnx.so' ;; openbsd*) version_type=sunos sys_lib_dlsearch_path_spec="/usr/lib" need_lib_prefix=no # Some older versions of OpenBSD (3.3 at least) *do* need versioned libs. case $host_os in openbsd3.3 | openbsd3.3.*) need_version=yes ;; *) need_version=no ;; esac library_names_spec='${libname}${release}${shared_ext}$versuffix ${libname}${shared_ext}$versuffix' finish_cmds='PATH="\$PATH:/sbin" ldconfig -m $libdir' shlibpath_var=LD_LIBRARY_PATH if test -z "`echo __ELF__ | $CC -E - | $GREP __ELF__`" || test "$host_os-$host_cpu" = "openbsd2.8-powerpc"; then case $host_os in openbsd2.[89] | openbsd2.[89].*) shlibpath_overrides_runpath=no ;; *) shlibpath_overrides_runpath=yes ;; esac else shlibpath_overrides_runpath=yes fi ;; os2*) libname_spec='$name' shrext_cmds=".dll" need_lib_prefix=no library_names_spec='$libname${shared_ext} $libname.a' dynamic_linker='OS/2 ld.exe' shlibpath_var=LIBPATH ;; osf3* | osf4* | osf5*) version_type=osf need_lib_prefix=no need_version=no soname_spec='${libname}${release}${shared_ext}$major' library_names_spec='${libname}${release}${shared_ext}$versuffix ${libname}${release}${shared_ext}$major $libname${shared_ext}' shlibpath_var=LD_LIBRARY_PATH sys_lib_search_path_spec="/usr/shlib /usr/ccs/lib /usr/lib/cmplrs/cc /usr/lib /usr/local/lib /var/shlib" sys_lib_dlsearch_path_spec="$sys_lib_search_path_spec" ;; rdos*) dynamic_linker=no ;; solaris*) version_type=linux # correct to gnu/linux during the next big refactor need_lib_prefix=no need_version=no library_names_spec='${libname}${release}${shared_ext}$versuffix ${libname}${release}${shared_ext}$major $libname${shared_ext}' soname_spec='${libname}${release}${shared_ext}$major' shlibpath_var=LD_LIBRARY_PATH shlibpath_overrides_runpath=yes hardcode_into_libs=yes # ldd complains unless libraries are executable postinstall_cmds='chmod +x $lib' ;; sunos4*) version_type=sunos library_names_spec='${libname}${release}${shared_ext}$versuffix ${libname}${shared_ext}$versuffix' finish_cmds='PATH="\$PATH:/usr/etc" ldconfig $libdir' shlibpath_var=LD_LIBRARY_PATH shlibpath_overrides_runpath=yes if test "$with_gnu_ld" = yes; then need_lib_prefix=no fi need_version=yes ;; sysv4 | sysv4.3*) version_type=linux # correct to gnu/linux during the next big refactor library_names_spec='${libname}${release}${shared_ext}$versuffix ${libname}${release}${shared_ext}$major $libname${shared_ext}' soname_spec='${libname}${release}${shared_ext}$major' shlibpath_var=LD_LIBRARY_PATH case $host_vendor in sni) shlibpath_overrides_runpath=no need_lib_prefix=no runpath_var=LD_RUN_PATH ;; siemens) need_lib_prefix=no ;; motorola) need_lib_prefix=no need_version=no shlibpath_overrides_runpath=no sys_lib_search_path_spec='/lib /usr/lib /usr/ccs/lib' ;; esac ;; sysv4*MP*) if test -d /usr/nec ;then version_type=linux # correct to gnu/linux during the next big refactor library_names_spec='$libname${shared_ext}.$versuffix $libname${shared_ext}.$major $libname${shared_ext}' soname_spec='$libname${shared_ext}.$major' shlibpath_var=LD_LIBRARY_PATH fi ;; sysv5* | sco3.2v5* | sco5v6* | unixware* | OpenUNIX* | sysv4*uw2*) version_type=freebsd-elf need_lib_prefix=no need_version=no library_names_spec='${libname}${release}${shared_ext}$versuffix ${libname}${release}${shared_ext} $libname${shared_ext}' soname_spec='${libname}${release}${shared_ext}$major' shlibpath_var=LD_LIBRARY_PATH shlibpath_overrides_runpath=yes hardcode_into_libs=yes if test "$with_gnu_ld" = yes; then sys_lib_search_path_spec='/usr/local/lib /usr/gnu/lib /usr/ccs/lib /usr/lib /lib' else sys_lib_search_path_spec='/usr/ccs/lib /usr/lib' case $host_os in sco3.2v5*) sys_lib_search_path_spec="$sys_lib_search_path_spec /lib" ;; esac fi sys_lib_dlsearch_path_spec='/usr/lib' ;; tpf*) # TPF is a cross-target only. Preferred cross-host = GNU/Linux. version_type=linux # correct to gnu/linux during the next big refactor need_lib_prefix=no need_version=no library_names_spec='${libname}${release}${shared_ext}$versuffix ${libname}${release}${shared_ext}$major $libname${shared_ext}' shlibpath_var=LD_LIBRARY_PATH shlibpath_overrides_runpath=no hardcode_into_libs=yes ;; uts4*) version_type=linux # correct to gnu/linux during the next big refactor library_names_spec='${libname}${release}${shared_ext}$versuffix ${libname}${release}${shared_ext}$major $libname${shared_ext}' soname_spec='${libname}${release}${shared_ext}$major' shlibpath_var=LD_LIBRARY_PATH ;; *) dynamic_linker=no ;; esac { $as_echo "$as_me:${as_lineno-$LINENO}: result: $dynamic_linker" >&5 $as_echo "$dynamic_linker" >&6; } test "$dynamic_linker" = no && can_build_shared=no variables_saved_for_relink="PATH $shlibpath_var $runpath_var" if test "$GCC" = yes; then variables_saved_for_relink="$variables_saved_for_relink GCC_EXEC_PREFIX COMPILER_PATH LIBRARY_PATH" fi if test "${lt_cv_sys_lib_search_path_spec+set}" = set; then sys_lib_search_path_spec="$lt_cv_sys_lib_search_path_spec" fi if test "${lt_cv_sys_lib_dlsearch_path_spec+set}" = set; then sys_lib_dlsearch_path_spec="$lt_cv_sys_lib_dlsearch_path_spec" fi { $as_echo "$as_me:${as_lineno-$LINENO}: checking how to hardcode library paths into programs" >&5 $as_echo_n "checking how to hardcode library paths into programs... " >&6; } hardcode_action= if test -n "$hardcode_libdir_flag_spec" || test -n "$runpath_var" || test "X$hardcode_automatic" = "Xyes" ; then # We can hardcode non-existent directories. if test "$hardcode_direct" != no && # If the only mechanism to avoid hardcoding is shlibpath_var, we # have to relink, otherwise we might link with an installed library # when we should be linking with a yet-to-be-installed one ## test "$_LT_TAGVAR(hardcode_shlibpath_var, )" != no && test "$hardcode_minus_L" != no; then # Linking always hardcodes the temporary library directory. hardcode_action=relink else # We can link without hardcoding, and we can hardcode nonexisting dirs. hardcode_action=immediate fi else # We cannot hardcode anything, or else we can only hardcode existing # directories. hardcode_action=unsupported fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $hardcode_action" >&5 $as_echo "$hardcode_action" >&6; } if test "$hardcode_action" = relink || test "$inherit_rpath" = yes; then # Fast installation is not supported enable_fast_install=no elif test "$shlibpath_overrides_runpath" = yes || test "$enable_shared" = no; then # Fast installation is not necessary enable_fast_install=needless fi if test "x$enable_dlopen" != xyes; then enable_dlopen=unknown enable_dlopen_self=unknown enable_dlopen_self_static=unknown else lt_cv_dlopen=no lt_cv_dlopen_libs= case $host_os in beos*) lt_cv_dlopen="load_add_on" lt_cv_dlopen_libs= lt_cv_dlopen_self=yes ;; mingw* | pw32* | cegcc*) lt_cv_dlopen="LoadLibrary" lt_cv_dlopen_libs= ;; cygwin*) lt_cv_dlopen="dlopen" lt_cv_dlopen_libs= ;; darwin*) # if libdl is installed we need to link against it { $as_echo "$as_me:${as_lineno-$LINENO}: checking for dlopen in -ldl" >&5 $as_echo_n "checking for dlopen in -ldl... " >&6; } if ${ac_cv_lib_dl_dlopen+:} false; then : $as_echo_n "(cached) " >&6 else ac_check_lib_save_LIBS=$LIBS LIBS="-ldl $LIBS" cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ /* Override any GCC internal prototype to avoid an error. Use char because int might match the return type of a GCC builtin and then its argument prototype would still apply. */ #ifdef __cplusplus extern "C" #endif char dlopen (); int main () { return dlopen (); ; return 0; } _ACEOF if ac_fn_c_try_link "$LINENO"; then : ac_cv_lib_dl_dlopen=yes else ac_cv_lib_dl_dlopen=no fi rm -f core conftest.err conftest.$ac_objext \ conftest$ac_exeext conftest.$ac_ext LIBS=$ac_check_lib_save_LIBS fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_cv_lib_dl_dlopen" >&5 $as_echo "$ac_cv_lib_dl_dlopen" >&6; } if test "x$ac_cv_lib_dl_dlopen" = xyes; then : lt_cv_dlopen="dlopen" lt_cv_dlopen_libs="-ldl" else lt_cv_dlopen="dyld" lt_cv_dlopen_libs= lt_cv_dlopen_self=yes fi ;; *) ac_fn_c_check_func "$LINENO" "shl_load" "ac_cv_func_shl_load" if test "x$ac_cv_func_shl_load" = xyes; then : lt_cv_dlopen="shl_load" else { $as_echo "$as_me:${as_lineno-$LINENO}: checking for shl_load in -ldld" >&5 $as_echo_n "checking for shl_load in -ldld... " >&6; } if ${ac_cv_lib_dld_shl_load+:} false; then : $as_echo_n "(cached) " >&6 else ac_check_lib_save_LIBS=$LIBS LIBS="-ldld $LIBS" cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ /* Override any GCC internal prototype to avoid an error. Use char because int might match the return type of a GCC builtin and then its argument prototype would still apply. */ #ifdef __cplusplus extern "C" #endif char shl_load (); int main () { return shl_load (); ; return 0; } _ACEOF if ac_fn_c_try_link "$LINENO"; then : ac_cv_lib_dld_shl_load=yes else ac_cv_lib_dld_shl_load=no fi rm -f core conftest.err conftest.$ac_objext \ conftest$ac_exeext conftest.$ac_ext LIBS=$ac_check_lib_save_LIBS fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_cv_lib_dld_shl_load" >&5 $as_echo "$ac_cv_lib_dld_shl_load" >&6; } if test "x$ac_cv_lib_dld_shl_load" = xyes; then : lt_cv_dlopen="shl_load" lt_cv_dlopen_libs="-ldld" else ac_fn_c_check_func "$LINENO" "dlopen" "ac_cv_func_dlopen" if test "x$ac_cv_func_dlopen" = xyes; then : lt_cv_dlopen="dlopen" else { $as_echo "$as_me:${as_lineno-$LINENO}: checking for dlopen in -ldl" >&5 $as_echo_n "checking for dlopen in -ldl... " >&6; } if ${ac_cv_lib_dl_dlopen+:} false; then : $as_echo_n "(cached) " >&6 else ac_check_lib_save_LIBS=$LIBS LIBS="-ldl $LIBS" cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ /* Override any GCC internal prototype to avoid an error. Use char because int might match the return type of a GCC builtin and then its argument prototype would still apply. */ #ifdef __cplusplus extern "C" #endif char dlopen (); int main () { return dlopen (); ; return 0; } _ACEOF if ac_fn_c_try_link "$LINENO"; then : ac_cv_lib_dl_dlopen=yes else ac_cv_lib_dl_dlopen=no fi rm -f core conftest.err conftest.$ac_objext \ conftest$ac_exeext conftest.$ac_ext LIBS=$ac_check_lib_save_LIBS fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_cv_lib_dl_dlopen" >&5 $as_echo "$ac_cv_lib_dl_dlopen" >&6; } if test "x$ac_cv_lib_dl_dlopen" = xyes; then : lt_cv_dlopen="dlopen" lt_cv_dlopen_libs="-ldl" else { $as_echo "$as_me:${as_lineno-$LINENO}: checking for dlopen in -lsvld" >&5 $as_echo_n "checking for dlopen in -lsvld... " >&6; } if ${ac_cv_lib_svld_dlopen+:} false; then : $as_echo_n "(cached) " >&6 else ac_check_lib_save_LIBS=$LIBS LIBS="-lsvld $LIBS" cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ /* Override any GCC internal prototype to avoid an error. Use char because int might match the return type of a GCC builtin and then its argument prototype would still apply. */ #ifdef __cplusplus extern "C" #endif char dlopen (); int main () { return dlopen (); ; return 0; } _ACEOF if ac_fn_c_try_link "$LINENO"; then : ac_cv_lib_svld_dlopen=yes else ac_cv_lib_svld_dlopen=no fi rm -f core conftest.err conftest.$ac_objext \ conftest$ac_exeext conftest.$ac_ext LIBS=$ac_check_lib_save_LIBS fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_cv_lib_svld_dlopen" >&5 $as_echo "$ac_cv_lib_svld_dlopen" >&6; } if test "x$ac_cv_lib_svld_dlopen" = xyes; then : lt_cv_dlopen="dlopen" lt_cv_dlopen_libs="-lsvld" else { $as_echo "$as_me:${as_lineno-$LINENO}: checking for dld_link in -ldld" >&5 $as_echo_n "checking for dld_link in -ldld... " >&6; } if ${ac_cv_lib_dld_dld_link+:} false; then : $as_echo_n "(cached) " >&6 else ac_check_lib_save_LIBS=$LIBS LIBS="-ldld $LIBS" cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ /* Override any GCC internal prototype to avoid an error. Use char because int might match the return type of a GCC builtin and then its argument prototype would still apply. */ #ifdef __cplusplus extern "C" #endif char dld_link (); int main () { return dld_link (); ; return 0; } _ACEOF if ac_fn_c_try_link "$LINENO"; then : ac_cv_lib_dld_dld_link=yes else ac_cv_lib_dld_dld_link=no fi rm -f core conftest.err conftest.$ac_objext \ conftest$ac_exeext conftest.$ac_ext LIBS=$ac_check_lib_save_LIBS fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_cv_lib_dld_dld_link" >&5 $as_echo "$ac_cv_lib_dld_dld_link" >&6; } if test "x$ac_cv_lib_dld_dld_link" = xyes; then : lt_cv_dlopen="dld_link" lt_cv_dlopen_libs="-ldld" fi fi fi fi fi fi ;; esac if test "x$lt_cv_dlopen" != xno; then enable_dlopen=yes else enable_dlopen=no fi case $lt_cv_dlopen in dlopen) save_CPPFLAGS="$CPPFLAGS" test "x$ac_cv_header_dlfcn_h" = xyes && CPPFLAGS="$CPPFLAGS -DHAVE_DLFCN_H" save_LDFLAGS="$LDFLAGS" wl=$lt_prog_compiler_wl eval LDFLAGS=\"\$LDFLAGS $export_dynamic_flag_spec\" save_LIBS="$LIBS" LIBS="$lt_cv_dlopen_libs $LIBS" { $as_echo "$as_me:${as_lineno-$LINENO}: checking whether a program can dlopen itself" >&5 $as_echo_n "checking whether a program can dlopen itself... " >&6; } if ${lt_cv_dlopen_self+:} false; then : $as_echo_n "(cached) " >&6 else if test "$cross_compiling" = yes; then : lt_cv_dlopen_self=cross else lt_dlunknown=0; lt_dlno_uscore=1; lt_dlneed_uscore=2 lt_status=$lt_dlunknown cat > conftest.$ac_ext <<_LT_EOF #line $LINENO "configure" #include "confdefs.h" #if HAVE_DLFCN_H #include #endif #include #ifdef RTLD_GLOBAL # define LT_DLGLOBAL RTLD_GLOBAL #else # ifdef DL_GLOBAL # define LT_DLGLOBAL DL_GLOBAL # else # define LT_DLGLOBAL 0 # endif #endif /* We may have to define LT_DLLAZY_OR_NOW in the command line if we find out it does not work in some platform. */ #ifndef LT_DLLAZY_OR_NOW # ifdef RTLD_LAZY # define LT_DLLAZY_OR_NOW RTLD_LAZY # else # ifdef DL_LAZY # define LT_DLLAZY_OR_NOW DL_LAZY # else # ifdef RTLD_NOW # define LT_DLLAZY_OR_NOW RTLD_NOW # else # ifdef DL_NOW # define LT_DLLAZY_OR_NOW DL_NOW # else # define LT_DLLAZY_OR_NOW 0 # endif # endif # endif # endif #endif /* When -fvisbility=hidden is used, assume the code has been annotated correspondingly for the symbols needed. */ #if defined(__GNUC__) && (((__GNUC__ == 3) && (__GNUC_MINOR__ >= 3)) || (__GNUC__ > 3)) int fnord () __attribute__((visibility("default"))); #endif int fnord () { return 42; } int main () { void *self = dlopen (0, LT_DLGLOBAL|LT_DLLAZY_OR_NOW); int status = $lt_dlunknown; if (self) { if (dlsym (self,"fnord")) status = $lt_dlno_uscore; else { if (dlsym( self,"_fnord")) status = $lt_dlneed_uscore; else puts (dlerror ()); } /* dlclose (self); */ } else puts (dlerror ()); return status; } _LT_EOF if { { eval echo "\"\$as_me\":${as_lineno-$LINENO}: \"$ac_link\""; } >&5 (eval $ac_link) 2>&5 ac_status=$? $as_echo "$as_me:${as_lineno-$LINENO}: \$? = $ac_status" >&5 test $ac_status = 0; } && test -s conftest${ac_exeext} 2>/dev/null; then (./conftest; exit; ) >&5 2>/dev/null lt_status=$? case x$lt_status in x$lt_dlno_uscore) lt_cv_dlopen_self=yes ;; x$lt_dlneed_uscore) lt_cv_dlopen_self=yes ;; x$lt_dlunknown|x*) lt_cv_dlopen_self=no ;; esac else : # compilation failed lt_cv_dlopen_self=no fi fi rm -fr conftest* fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $lt_cv_dlopen_self" >&5 $as_echo "$lt_cv_dlopen_self" >&6; } if test "x$lt_cv_dlopen_self" = xyes; then wl=$lt_prog_compiler_wl eval LDFLAGS=\"\$LDFLAGS $lt_prog_compiler_static\" { $as_echo "$as_me:${as_lineno-$LINENO}: checking whether a statically linked program can dlopen itself" >&5 $as_echo_n "checking whether a statically linked program can dlopen itself... " >&6; } if ${lt_cv_dlopen_self_static+:} false; then : $as_echo_n "(cached) " >&6 else if test "$cross_compiling" = yes; then : lt_cv_dlopen_self_static=cross else lt_dlunknown=0; lt_dlno_uscore=1; lt_dlneed_uscore=2 lt_status=$lt_dlunknown cat > conftest.$ac_ext <<_LT_EOF #line $LINENO "configure" #include "confdefs.h" #if HAVE_DLFCN_H #include #endif #include #ifdef RTLD_GLOBAL # define LT_DLGLOBAL RTLD_GLOBAL #else # ifdef DL_GLOBAL # define LT_DLGLOBAL DL_GLOBAL # else # define LT_DLGLOBAL 0 # endif #endif /* We may have to define LT_DLLAZY_OR_NOW in the command line if we find out it does not work in some platform. */ #ifndef LT_DLLAZY_OR_NOW # ifdef RTLD_LAZY # define LT_DLLAZY_OR_NOW RTLD_LAZY # else # ifdef DL_LAZY # define LT_DLLAZY_OR_NOW DL_LAZY # else # ifdef RTLD_NOW # define LT_DLLAZY_OR_NOW RTLD_NOW # else # ifdef DL_NOW # define LT_DLLAZY_OR_NOW DL_NOW # else # define LT_DLLAZY_OR_NOW 0 # endif # endif # endif # endif #endif /* When -fvisbility=hidden is used, assume the code has been annotated correspondingly for the symbols needed. */ #if defined(__GNUC__) && (((__GNUC__ == 3) && (__GNUC_MINOR__ >= 3)) || (__GNUC__ > 3)) int fnord () __attribute__((visibility("default"))); #endif int fnord () { return 42; } int main () { void *self = dlopen (0, LT_DLGLOBAL|LT_DLLAZY_OR_NOW); int status = $lt_dlunknown; if (self) { if (dlsym (self,"fnord")) status = $lt_dlno_uscore; else { if (dlsym( self,"_fnord")) status = $lt_dlneed_uscore; else puts (dlerror ()); } /* dlclose (self); */ } else puts (dlerror ()); return status; } _LT_EOF if { { eval echo "\"\$as_me\":${as_lineno-$LINENO}: \"$ac_link\""; } >&5 (eval $ac_link) 2>&5 ac_status=$? $as_echo "$as_me:${as_lineno-$LINENO}: \$? = $ac_status" >&5 test $ac_status = 0; } && test -s conftest${ac_exeext} 2>/dev/null; then (./conftest; exit; ) >&5 2>/dev/null lt_status=$? case x$lt_status in x$lt_dlno_uscore) lt_cv_dlopen_self_static=yes ;; x$lt_dlneed_uscore) lt_cv_dlopen_self_static=yes ;; x$lt_dlunknown|x*) lt_cv_dlopen_self_static=no ;; esac else : # compilation failed lt_cv_dlopen_self_static=no fi fi rm -fr conftest* fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $lt_cv_dlopen_self_static" >&5 $as_echo "$lt_cv_dlopen_self_static" >&6; } fi CPPFLAGS="$save_CPPFLAGS" LDFLAGS="$save_LDFLAGS" LIBS="$save_LIBS" ;; esac case $lt_cv_dlopen_self in yes|no) enable_dlopen_self=$lt_cv_dlopen_self ;; *) enable_dlopen_self=unknown ;; esac case $lt_cv_dlopen_self_static in yes|no) enable_dlopen_self_static=$lt_cv_dlopen_self_static ;; *) enable_dlopen_self_static=unknown ;; esac fi striplib= old_striplib= { $as_echo "$as_me:${as_lineno-$LINENO}: checking whether stripping libraries is possible" >&5 $as_echo_n "checking whether stripping libraries is possible... " >&6; } if test -n "$STRIP" && $STRIP -V 2>&1 | $GREP "GNU strip" >/dev/null; then test -z "$old_striplib" && old_striplib="$STRIP --strip-debug" test -z "$striplib" && striplib="$STRIP --strip-unneeded" { $as_echo "$as_me:${as_lineno-$LINENO}: result: yes" >&5 $as_echo "yes" >&6; } else # FIXME - insert some real tests, host_os isn't really good enough case $host_os in darwin*) if test -n "$STRIP" ; then striplib="$STRIP -x" old_striplib="$STRIP -S" { $as_echo "$as_me:${as_lineno-$LINENO}: result: yes" >&5 $as_echo "yes" >&6; } else { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } fi ;; *) { $as_echo "$as_me:${as_lineno-$LINENO}: result: no" >&5 $as_echo "no" >&6; } ;; esac fi # Report which library types will actually be built { $as_echo "$as_me:${as_lineno-$LINENO}: checking if libtool supports shared libraries" >&5 $as_echo_n "checking if libtool supports shared libraries... " >&6; } { $as_echo "$as_me:${as_lineno-$LINENO}: result: $can_build_shared" >&5 $as_echo "$can_build_shared" >&6; } { $as_echo "$as_me:${as_lineno-$LINENO}: checking whether to build shared libraries" >&5 $as_echo_n "checking whether to build shared libraries... " >&6; } test "$can_build_shared" = "no" && enable_shared=no # On AIX, shared libraries and static libraries use the same namespace, and # are all built from PIC. case $host_os in aix3*) test "$enable_shared" = yes && enable_static=no if test -n "$RANLIB"; then archive_cmds="$archive_cmds~\$RANLIB \$lib" postinstall_cmds='$RANLIB $lib' fi ;; aix[4-9]*) if test "$host_cpu" != ia64 && test "$aix_use_runtimelinking" = no ; then test "$enable_shared" = yes && enable_static=no fi ;; esac { $as_echo "$as_me:${as_lineno-$LINENO}: result: $enable_shared" >&5 $as_echo "$enable_shared" >&6; } { $as_echo "$as_me:${as_lineno-$LINENO}: checking whether to build static libraries" >&5 $as_echo_n "checking whether to build static libraries... " >&6; } # Make sure either enable_shared or enable_static is yes. test "$enable_shared" = yes || enable_static=yes { $as_echo "$as_me:${as_lineno-$LINENO}: result: $enable_static" >&5 $as_echo "$enable_static" >&6; } fi ac_ext=c ac_cpp='$CPP $CPPFLAGS' ac_compile='$CC -c $CFLAGS $CPPFLAGS conftest.$ac_ext >&5' ac_link='$CC -o conftest$ac_exeext $CFLAGS $CPPFLAGS $LDFLAGS conftest.$ac_ext $LIBS >&5' ac_compiler_gnu=$ac_cv_c_compiler_gnu CC="$lt_save_CC" ac_config_commands="$ac_config_commands libtool" # Only expand once: if test -d $srcdir/testsuite; then TESTSUBDIR_TRUE= TESTSUBDIR_FALSE='#' else TESTSUBDIR_TRUE='#' TESTSUBDIR_FALSE= fi TARGETDIR="unknown" case "$host" in alpha*-*-*) TARGET=ALPHA; TARGETDIR=alpha; # Support 128-bit long double, changeable via command-line switch. HAVE_LONG_DOUBLE='defined(__LONG_DOUBLE_128__)' ;; arm*-*-*) TARGET=ARM; TARGETDIR=arm ;; amd64-*-freebsd* | amd64-*-openbsd*) TARGET=X86_64; TARGETDIR=x86 ;; avr32*-*-*) TARGET=AVR32; TARGETDIR=avr32 ;; cris-*-*) TARGET=LIBFFI_CRIS; TARGETDIR=cris ;; frv-*-*) TARGET=FRV; TARGETDIR=frv ;; hppa*-*-linux* | parisc*-*-linux*) TARGET=PA_LINUX; TARGETDIR=pa ;; hppa*64-*-hpux*) TARGET=PA64_HPUX; TARGETDIR=pa ;; hppa*-*-hpux*) TARGET=PA_HPUX; TARGETDIR=pa ;; i?86-*-freebsd* | i?86-*-openbsd* | i?86-*-dragonfly*) TARGET=X86_FREEBSD; TARGETDIR=x86 ;; i?86-win32* | i?86-*-cygwin* | i?86-*-mingw* | i?86-*-os2*) TARGET=X86_WIN32; TARGETDIR=x86 # All mingw/cygwin/win32 builds require this for sharedlib AM_LTLDFLAGS="-no-undefined" ;; i?86-*-darwin*) TARGET=X86_DARWIN; TARGETDIR=x86 ;; i?86-*-solaris2.1[0-9]*) TARGET=X86_64; TARGETDIR=x86 ;; i?86-*-*) TARGET=X86; TARGETDIR=x86 ;; ia64*-*-*) TARGET=IA64; TARGETDIR=ia64 ;; m32r*-*-*) TARGET=M32R; TARGETDIR=m32r ;; m68k-*-*) TARGET=M68K; TARGETDIR=m68k ;; mips-sgi-irix5.* | mips-sgi-irix6.*) TARGET=MIPS; TARGETDIR=mips ;; mips*-*-linux*) # Support 128-bit long double for NewABI. HAVE_LONG_DOUBLE='defined(__mips64)' TARGET=MIPS; TARGETDIR=mips ;; powerpc*-*-linux* | powerpc-*-sysv*) TARGET=POWERPC; TARGETDIR=powerpc ;; powerpc-*-beos*) TARGET=POWERPC; TARGETDIR=powerpc ;; powerpc-*-darwin*) TARGET=POWERPC_DARWIN; TARGETDIR=powerpc ;; powerpc-*-aix* | rs6000-*-aix*) TARGET=POWERPC_AIX; TARGETDIR=powerpc ;; powerpc-*-freebsd*) TARGET=POWERPC_FREEBSD; TARGETDIR=powerpc ;; powerpc64-*-freebsd*) TARGET=POWERPC; TARGETDIR=powerpc ;; powerpc*-*-rtems*) TARGET=POWERPC; TARGETDIR=powerpc ;; s390-*-* | s390x-*-*) TARGET=S390; TARGETDIR=s390 ;; sh-*-* | sh[34]*-*-*) TARGET=SH; TARGETDIR=sh ;; sh64-*-* | sh5*-*-*) TARGET=SH64; TARGETDIR=sh64 ;; sparc*-*-*) TARGET=SPARC; TARGETDIR=sparc ;; x86_64-*-darwin*) TARGET=X86_DARWIN; TARGETDIR=x86 ;; x86_64-*-cygwin* | x86_64-*-mingw*) TARGET=X86_WIN64; TARGETDIR=x86 ;; x86_64-*-*) TARGET=X86_64; TARGETDIR=x86 ;; esac if test $TARGETDIR = unknown; then as_fn_error $? "\"libffi has not been ported to $host.\"" "$LINENO" 5 fi if test x$TARGET = xMIPS; then MIPS_TRUE= MIPS_FALSE='#' else MIPS_TRUE='#' MIPS_FALSE= fi if test x$TARGET = xSPARC; then SPARC_TRUE= SPARC_FALSE='#' else SPARC_TRUE='#' SPARC_FALSE= fi if test x$TARGET = xX86; then X86_TRUE= X86_FALSE='#' else X86_TRUE='#' X86_FALSE= fi if test x$TARGET = xX86_FREEBSD; then X86_FREEBSD_TRUE= X86_FREEBSD_FALSE='#' else X86_FREEBSD_TRUE='#' X86_FREEBSD_FALSE= fi if test x$TARGET = xX86_WIN32; then X86_WIN32_TRUE= X86_WIN32_FALSE='#' else X86_WIN32_TRUE='#' X86_WIN32_FALSE= fi if test x$TARGET = xX86_WIN64; then X86_WIN64_TRUE= X86_WIN64_FALSE='#' else X86_WIN64_TRUE='#' X86_WIN64_FALSE= fi if test x$TARGET = xX86_DARWIN; then X86_DARWIN_TRUE= X86_DARWIN_FALSE='#' else X86_DARWIN_TRUE='#' X86_DARWIN_FALSE= fi if test x$TARGET = xALPHA; then ALPHA_TRUE= ALPHA_FALSE='#' else ALPHA_TRUE='#' ALPHA_FALSE= fi if test x$TARGET = xIA64; then IA64_TRUE= IA64_FALSE='#' else IA64_TRUE='#' IA64_FALSE= fi if test x$TARGET = xM32R; then M32R_TRUE= M32R_FALSE='#' else M32R_TRUE='#' M32R_FALSE= fi if test x$TARGET = xM68K; then M68K_TRUE= M68K_FALSE='#' else M68K_TRUE='#' M68K_FALSE= fi if test x$TARGET = xPOWERPC; then POWERPC_TRUE= POWERPC_FALSE='#' else POWERPC_TRUE='#' POWERPC_FALSE= fi if test x$TARGET = xPOWERPC_AIX; then POWERPC_AIX_TRUE= POWERPC_AIX_FALSE='#' else POWERPC_AIX_TRUE='#' POWERPC_AIX_FALSE= fi if test x$TARGET = xPOWERPC_DARWIN; then POWERPC_DARWIN_TRUE= POWERPC_DARWIN_FALSE='#' else POWERPC_DARWIN_TRUE='#' POWERPC_DARWIN_FALSE= fi if test x$TARGET = xPOWERPC_FREEBSD; then POWERPC_FREEBSD_TRUE= POWERPC_FREEBSD_FALSE='#' else POWERPC_FREEBSD_TRUE='#' POWERPC_FREEBSD_FALSE= fi if test x$TARGET = xARM; then ARM_TRUE= ARM_FALSE='#' else ARM_TRUE='#' ARM_FALSE= fi if test x$TARGET = xAVR32; then AVR32_TRUE= AVR32_FALSE='#' else AVR32_TRUE='#' AVR32_FALSE= fi if test x$TARGET = xLIBFFI_CRIS; then LIBFFI_CRIS_TRUE= LIBFFI_CRIS_FALSE='#' else LIBFFI_CRIS_TRUE='#' LIBFFI_CRIS_FALSE= fi if test x$TARGET = xFRV; then FRV_TRUE= FRV_FALSE='#' else FRV_TRUE='#' FRV_FALSE= fi if test x$TARGET = xS390; then S390_TRUE= S390_FALSE='#' else S390_TRUE='#' S390_FALSE= fi if test x$TARGET = xX86_64; then X86_64_TRUE= X86_64_FALSE='#' else X86_64_TRUE='#' X86_64_FALSE= fi if test x$TARGET = xSH; then SH_TRUE= SH_FALSE='#' else SH_TRUE='#' SH_FALSE= fi if test x$TARGET = xSH64; then SH64_TRUE= SH64_FALSE='#' else SH64_TRUE='#' SH64_FALSE= fi if test x$TARGET = xPA_LINUX; then PA_LINUX_TRUE= PA_LINUX_FALSE='#' else PA_LINUX_TRUE='#' PA_LINUX_FALSE= fi if test x$TARGET = xPA_HPUX; then PA_HPUX_TRUE= PA_HPUX_FALSE='#' else PA_HPUX_TRUE='#' PA_HPUX_FALSE= fi if test x$TARGET = xPA64_HPUX; then PA64_HPUX_TRUE= PA64_HPUX_FALSE='#' else PA64_HPUX_TRUE='#' PA64_HPUX_FALSE= fi { $as_echo "$as_me:${as_lineno-$LINENO}: checking for ANSI C header files" >&5 $as_echo_n "checking for ANSI C header files... " >&6; } if ${ac_cv_header_stdc+:} false; then : $as_echo_n "(cached) " >&6 else cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ #include #include #include #include int main () { ; return 0; } _ACEOF if ac_fn_c_try_compile "$LINENO"; then : ac_cv_header_stdc=yes else ac_cv_header_stdc=no fi rm -f core conftest.err conftest.$ac_objext conftest.$ac_ext if test $ac_cv_header_stdc = yes; then # SunOS 4.x string.h does not declare mem*, contrary to ANSI. cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ #include _ACEOF if (eval "$ac_cpp conftest.$ac_ext") 2>&5 | $EGREP "memchr" >/dev/null 2>&1; then : else ac_cv_header_stdc=no fi rm -f conftest* fi if test $ac_cv_header_stdc = yes; then # ISC 2.0.2 stdlib.h does not declare free, contrary to ANSI. cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ #include _ACEOF if (eval "$ac_cpp conftest.$ac_ext") 2>&5 | $EGREP "free" >/dev/null 2>&1; then : else ac_cv_header_stdc=no fi rm -f conftest* fi if test $ac_cv_header_stdc = yes; then # /bin/cc in Irix-4.0.5 gets non-ANSI ctype macros unless using -ansi. if test "$cross_compiling" = yes; then : : else cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ #include #include #if ((' ' & 0x0FF) == 0x020) # define ISLOWER(c) ('a' <= (c) && (c) <= 'z') # define TOUPPER(c) (ISLOWER(c) ? 'A' + ((c) - 'a') : (c)) #else # define ISLOWER(c) \ (('a' <= (c) && (c) <= 'i') \ || ('j' <= (c) && (c) <= 'r') \ || ('s' <= (c) && (c) <= 'z')) # define TOUPPER(c) (ISLOWER(c) ? ((c) | 0x40) : (c)) #endif #define XOR(e, f) (((e) && !(f)) || (!(e) && (f))) int main () { int i; for (i = 0; i < 256; i++) if (XOR (islower (i), ISLOWER (i)) || toupper (i) != TOUPPER (i)) return 2; return 0; } _ACEOF if ac_fn_c_try_run "$LINENO"; then : else ac_cv_header_stdc=no fi rm -f core *.core core.conftest.* gmon.out bb.out conftest$ac_exeext \ conftest.$ac_objext conftest.beam conftest.$ac_ext fi fi fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_cv_header_stdc" >&5 $as_echo "$ac_cv_header_stdc" >&6; } if test $ac_cv_header_stdc = yes; then $as_echo "#define STDC_HEADERS 1" >>confdefs.h fi for ac_func in memcpy do : ac_fn_c_check_func "$LINENO" "memcpy" "ac_cv_func_memcpy" if test "x$ac_cv_func_memcpy" = xyes; then : cat >>confdefs.h <<_ACEOF #define HAVE_MEMCPY 1 _ACEOF fi done ac_fn_c_check_type "$LINENO" "size_t" "ac_cv_type_size_t" "$ac_includes_default" if test "x$ac_cv_type_size_t" = xyes; then : else cat >>confdefs.h <<_ACEOF #define size_t unsigned int _ACEOF fi # The Ultrix 4.2 mips builtin alloca declared by alloca.h only works # for constant arguments. Useless! { $as_echo "$as_me:${as_lineno-$LINENO}: checking for working alloca.h" >&5 $as_echo_n "checking for working alloca.h... " >&6; } if ${ac_cv_working_alloca_h+:} false; then : $as_echo_n "(cached) " >&6 else cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ #include int main () { char *p = (char *) alloca (2 * sizeof (int)); if (p) return 0; ; return 0; } _ACEOF if ac_fn_c_try_link "$LINENO"; then : ac_cv_working_alloca_h=yes else ac_cv_working_alloca_h=no fi rm -f core conftest.err conftest.$ac_objext \ conftest$ac_exeext conftest.$ac_ext fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_cv_working_alloca_h" >&5 $as_echo "$ac_cv_working_alloca_h" >&6; } if test $ac_cv_working_alloca_h = yes; then $as_echo "#define HAVE_ALLOCA_H 1" >>confdefs.h fi { $as_echo "$as_me:${as_lineno-$LINENO}: checking for alloca" >&5 $as_echo_n "checking for alloca... " >&6; } if ${ac_cv_func_alloca_works+:} false; then : $as_echo_n "(cached) " >&6 else cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ #ifdef __GNUC__ # define alloca __builtin_alloca #else # ifdef _MSC_VER # include # define alloca _alloca # else # ifdef HAVE_ALLOCA_H # include # else # ifdef _AIX #pragma alloca # else # ifndef alloca /* predefined by HP cc +Olibcalls */ void *alloca (size_t); # endif # endif # endif # endif #endif int main () { char *p = (char *) alloca (1); if (p) return 0; ; return 0; } _ACEOF if ac_fn_c_try_link "$LINENO"; then : ac_cv_func_alloca_works=yes else ac_cv_func_alloca_works=no fi rm -f core conftest.err conftest.$ac_objext \ conftest$ac_exeext conftest.$ac_ext fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_cv_func_alloca_works" >&5 $as_echo "$ac_cv_func_alloca_works" >&6; } if test $ac_cv_func_alloca_works = yes; then $as_echo "#define HAVE_ALLOCA 1" >>confdefs.h else # The SVR3 libPW and SVR4 libucb both contain incompatible functions # that cause trouble. Some versions do not even contain alloca or # contain a buggy version. If you still want to use their alloca, # use ar to extract alloca.o from them instead of compiling alloca.c. ALLOCA=\${LIBOBJDIR}alloca.$ac_objext $as_echo "#define C_ALLOCA 1" >>confdefs.h { $as_echo "$as_me:${as_lineno-$LINENO}: checking whether \`alloca.c' needs Cray hooks" >&5 $as_echo_n "checking whether \`alloca.c' needs Cray hooks... " >&6; } if ${ac_cv_os_cray+:} false; then : $as_echo_n "(cached) " >&6 else cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ #if defined CRAY && ! defined CRAY2 webecray #else wenotbecray #endif _ACEOF if (eval "$ac_cpp conftest.$ac_ext") 2>&5 | $EGREP "webecray" >/dev/null 2>&1; then : ac_cv_os_cray=yes else ac_cv_os_cray=no fi rm -f conftest* fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_cv_os_cray" >&5 $as_echo "$ac_cv_os_cray" >&6; } if test $ac_cv_os_cray = yes; then for ac_func in _getb67 GETB67 getb67; do as_ac_var=`$as_echo "ac_cv_func_$ac_func" | $as_tr_sh` ac_fn_c_check_func "$LINENO" "$ac_func" "$as_ac_var" if eval test \"x\$"$as_ac_var"\" = x"yes"; then : cat >>confdefs.h <<_ACEOF #define CRAY_STACKSEG_END $ac_func _ACEOF break fi done fi { $as_echo "$as_me:${as_lineno-$LINENO}: checking stack direction for C alloca" >&5 $as_echo_n "checking stack direction for C alloca... " >&6; } if ${ac_cv_c_stack_direction+:} false; then : $as_echo_n "(cached) " >&6 else if test "$cross_compiling" = yes; then : ac_cv_c_stack_direction=0 else cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ $ac_includes_default int find_stack_direction (int *addr, int depth) { int dir, dummy = 0; if (! addr) addr = &dummy; *addr = addr < &dummy ? 1 : addr == &dummy ? 0 : -1; dir = depth ? find_stack_direction (addr, depth - 1) : 0; return dir + dummy; } int main (int argc, char **argv) { return find_stack_direction (0, argc + !argv + 20) < 0; } _ACEOF if ac_fn_c_try_run "$LINENO"; then : ac_cv_c_stack_direction=1 else ac_cv_c_stack_direction=-1 fi rm -f core *.core core.conftest.* gmon.out bb.out conftest$ac_exeext \ conftest.$ac_objext conftest.beam conftest.$ac_ext fi fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_cv_c_stack_direction" >&5 $as_echo "$ac_cv_c_stack_direction" >&6; } cat >>confdefs.h <<_ACEOF #define STACK_DIRECTION $ac_cv_c_stack_direction _ACEOF fi # The cast to long int works around a bug in the HP C Compiler # version HP92453-01 B.11.11.23709.GP, which incorrectly rejects # declarations like `int a3[[(sizeof (unsigned char)) >= 0]];'. # This bug is HP SR number 8606223364. { $as_echo "$as_me:${as_lineno-$LINENO}: checking size of double" >&5 $as_echo_n "checking size of double... " >&6; } if ${ac_cv_sizeof_double+:} false; then : $as_echo_n "(cached) " >&6 else if ac_fn_c_compute_int "$LINENO" "(long int) (sizeof (double))" "ac_cv_sizeof_double" "$ac_includes_default"; then : else if test "$ac_cv_type_double" = yes; then { { $as_echo "$as_me:${as_lineno-$LINENO}: error: in \`$ac_pwd':" >&5 $as_echo "$as_me: error: in \`$ac_pwd':" >&2;} as_fn_error 77 "cannot compute sizeof (double) See \`config.log' for more details" "$LINENO" 5; } else ac_cv_sizeof_double=0 fi fi fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_cv_sizeof_double" >&5 $as_echo "$ac_cv_sizeof_double" >&6; } cat >>confdefs.h <<_ACEOF #define SIZEOF_DOUBLE $ac_cv_sizeof_double _ACEOF # The cast to long int works around a bug in the HP C Compiler # version HP92453-01 B.11.11.23709.GP, which incorrectly rejects # declarations like `int a3[[(sizeof (unsigned char)) >= 0]];'. # This bug is HP SR number 8606223364. { $as_echo "$as_me:${as_lineno-$LINENO}: checking size of long double" >&5 $as_echo_n "checking size of long double... " >&6; } if ${ac_cv_sizeof_long_double+:} false; then : $as_echo_n "(cached) " >&6 else if ac_fn_c_compute_int "$LINENO" "(long int) (sizeof (long double))" "ac_cv_sizeof_long_double" "$ac_includes_default"; then : else if test "$ac_cv_type_long_double" = yes; then { { $as_echo "$as_me:${as_lineno-$LINENO}: error: in \`$ac_pwd':" >&5 $as_echo "$as_me: error: in \`$ac_pwd':" >&2;} as_fn_error 77 "cannot compute sizeof (long double) See \`config.log' for more details" "$LINENO" 5; } else ac_cv_sizeof_long_double=0 fi fi fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_cv_sizeof_long_double" >&5 $as_echo "$ac_cv_sizeof_long_double" >&6; } cat >>confdefs.h <<_ACEOF #define SIZEOF_LONG_DOUBLE $ac_cv_sizeof_long_double _ACEOF # Also AC_SUBST this variable for ffi.h. if test -z "$HAVE_LONG_DOUBLE"; then HAVE_LONG_DOUBLE=0 if test $ac_cv_sizeof_double != $ac_cv_sizeof_long_double; then if test $ac_cv_sizeof_long_double != 0; then HAVE_LONG_DOUBLE=1 $as_echo "#define HAVE_LONG_DOUBLE 1" >>confdefs.h fi fi fi { $as_echo "$as_me:${as_lineno-$LINENO}: checking whether byte ordering is bigendian" >&5 $as_echo_n "checking whether byte ordering is bigendian... " >&6; } if ${ac_cv_c_bigendian+:} false; then : $as_echo_n "(cached) " >&6 else ac_cv_c_bigendian=unknown # See if we're dealing with a universal compiler. cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ #ifndef __APPLE_CC__ not a universal capable compiler #endif typedef int dummy; _ACEOF if ac_fn_c_try_compile "$LINENO"; then : # Check for potential -arch flags. It is not universal unless # there are at least two -arch flags with different values. ac_arch= ac_prev= for ac_word in $CC $CFLAGS $CPPFLAGS $LDFLAGS; do if test -n "$ac_prev"; then case $ac_word in i?86 | x86_64 | ppc | ppc64) if test -z "$ac_arch" || test "$ac_arch" = "$ac_word"; then ac_arch=$ac_word else ac_cv_c_bigendian=universal break fi ;; esac ac_prev= elif test "x$ac_word" = "x-arch"; then ac_prev=arch fi done fi rm -f core conftest.err conftest.$ac_objext conftest.$ac_ext if test $ac_cv_c_bigendian = unknown; then # See if sys/param.h defines the BYTE_ORDER macro. cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ #include #include int main () { #if ! (defined BYTE_ORDER && defined BIG_ENDIAN \ && defined LITTLE_ENDIAN && BYTE_ORDER && BIG_ENDIAN \ && LITTLE_ENDIAN) bogus endian macros #endif ; return 0; } _ACEOF if ac_fn_c_try_compile "$LINENO"; then : # It does; now see whether it defined to BIG_ENDIAN or not. cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ #include #include int main () { #if BYTE_ORDER != BIG_ENDIAN not big endian #endif ; return 0; } _ACEOF if ac_fn_c_try_compile "$LINENO"; then : ac_cv_c_bigendian=yes else ac_cv_c_bigendian=no fi rm -f core conftest.err conftest.$ac_objext conftest.$ac_ext fi rm -f core conftest.err conftest.$ac_objext conftest.$ac_ext fi if test $ac_cv_c_bigendian = unknown; then # See if defines _LITTLE_ENDIAN or _BIG_ENDIAN (e.g., Solaris). cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ #include int main () { #if ! (defined _LITTLE_ENDIAN || defined _BIG_ENDIAN) bogus endian macros #endif ; return 0; } _ACEOF if ac_fn_c_try_compile "$LINENO"; then : # It does; now see whether it defined to _BIG_ENDIAN or not. cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ #include int main () { #ifndef _BIG_ENDIAN not big endian #endif ; return 0; } _ACEOF if ac_fn_c_try_compile "$LINENO"; then : ac_cv_c_bigendian=yes else ac_cv_c_bigendian=no fi rm -f core conftest.err conftest.$ac_objext conftest.$ac_ext fi rm -f core conftest.err conftest.$ac_objext conftest.$ac_ext fi if test $ac_cv_c_bigendian = unknown; then # Compile a test program. if test "$cross_compiling" = yes; then : # Try to guess by grepping values from an object file. cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ short int ascii_mm[] = { 0x4249, 0x4765, 0x6E44, 0x6961, 0x6E53, 0x7953, 0 }; short int ascii_ii[] = { 0x694C, 0x5454, 0x656C, 0x6E45, 0x6944, 0x6E61, 0 }; int use_ascii (int i) { return ascii_mm[i] + ascii_ii[i]; } short int ebcdic_ii[] = { 0x89D3, 0xE3E3, 0x8593, 0x95C5, 0x89C4, 0x9581, 0 }; short int ebcdic_mm[] = { 0xC2C9, 0xC785, 0x95C4, 0x8981, 0x95E2, 0xA8E2, 0 }; int use_ebcdic (int i) { return ebcdic_mm[i] + ebcdic_ii[i]; } extern int foo; int main () { return use_ascii (foo) == use_ebcdic (foo); ; return 0; } _ACEOF if ac_fn_c_try_compile "$LINENO"; then : if grep BIGenDianSyS conftest.$ac_objext >/dev/null; then ac_cv_c_bigendian=yes fi if grep LiTTleEnDian conftest.$ac_objext >/dev/null ; then if test "$ac_cv_c_bigendian" = unknown; then ac_cv_c_bigendian=no else # finding both strings is unlikely to happen, but who knows? ac_cv_c_bigendian=unknown fi fi fi rm -f core conftest.err conftest.$ac_objext conftest.$ac_ext else cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ $ac_includes_default int main () { /* Are we little or big endian? From Harbison&Steele. */ union { long int l; char c[sizeof (long int)]; } u; u.l = 1; return u.c[sizeof (long int) - 1] == 1; ; return 0; } _ACEOF if ac_fn_c_try_run "$LINENO"; then : ac_cv_c_bigendian=no else ac_cv_c_bigendian=yes fi rm -f core *.core core.conftest.* gmon.out bb.out conftest$ac_exeext \ conftest.$ac_objext conftest.beam conftest.$ac_ext fi fi fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $ac_cv_c_bigendian" >&5 $as_echo "$ac_cv_c_bigendian" >&6; } case $ac_cv_c_bigendian in #( yes) $as_echo "#define WORDS_BIGENDIAN 1" >>confdefs.h ;; #( no) ;; #( universal) $as_echo "#define AC_APPLE_UNIVERSAL_BUILD 1" >>confdefs.h ;; #( *) as_fn_error $? "unknown endianness presetting ac_cv_c_bigendian=no (or yes) will help" "$LINENO" 5 ;; esac { $as_echo "$as_me:${as_lineno-$LINENO}: checking assembler .cfi pseudo-op support" >&5 $as_echo_n "checking assembler .cfi pseudo-op support... " >&6; } if ${libffi_cv_as_cfi_pseudo_op+:} false; then : $as_echo_n "(cached) " >&6 else libffi_cv_as_cfi_pseudo_op=unknown cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ asm (".cfi_startproc\n\t.cfi_endproc"); int main () { ; return 0; } _ACEOF if ac_fn_c_try_compile "$LINENO"; then : libffi_cv_as_cfi_pseudo_op=yes else libffi_cv_as_cfi_pseudo_op=no fi rm -f core conftest.err conftest.$ac_objext conftest.$ac_ext fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $libffi_cv_as_cfi_pseudo_op" >&5 $as_echo "$libffi_cv_as_cfi_pseudo_op" >&6; } if test "x$libffi_cv_as_cfi_pseudo_op" = xyes; then $as_echo "#define HAVE_AS_CFI_PSEUDO_OP 1" >>confdefs.h fi if test x$TARGET = xSPARC; then { $as_echo "$as_me:${as_lineno-$LINENO}: checking assembler and linker support unaligned pc related relocs" >&5 $as_echo_n "checking assembler and linker support unaligned pc related relocs... " >&6; } if ${libffi_cv_as_sparc_ua_pcrel+:} false; then : $as_echo_n "(cached) " >&6 else save_CFLAGS="$CFLAGS" save_LDFLAGS="$LDFLAGS" CFLAGS="$CFLAGS -fpic" LDFLAGS="$LDFLAGS -shared" cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ asm (".text; foo: nop; .data; .align 4; .byte 0; .uaword %r_disp32(foo); .text"); int main () { ; return 0; } _ACEOF if ac_fn_c_try_link "$LINENO"; then : libffi_cv_as_sparc_ua_pcrel=yes else libffi_cv_as_sparc_ua_pcrel=no fi rm -f core conftest.err conftest.$ac_objext \ conftest$ac_exeext conftest.$ac_ext CFLAGS="$save_CFLAGS" LDFLAGS="$save_LDFLAGS" fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $libffi_cv_as_sparc_ua_pcrel" >&5 $as_echo "$libffi_cv_as_sparc_ua_pcrel" >&6; } if test "x$libffi_cv_as_sparc_ua_pcrel" = xyes; then $as_echo "#define HAVE_AS_SPARC_UA_PCREL 1" >>confdefs.h fi { $as_echo "$as_me:${as_lineno-$LINENO}: checking assembler .register pseudo-op support" >&5 $as_echo_n "checking assembler .register pseudo-op support... " >&6; } if ${libffi_cv_as_register_pseudo_op+:} false; then : $as_echo_n "(cached) " >&6 else libffi_cv_as_register_pseudo_op=unknown # Check if we have .register cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ asm (".register %g2, #scratch"); int main () { ; return 0; } _ACEOF if ac_fn_c_try_compile "$LINENO"; then : libffi_cv_as_register_pseudo_op=yes else libffi_cv_as_register_pseudo_op=no fi rm -f core conftest.err conftest.$ac_objext conftest.$ac_ext fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $libffi_cv_as_register_pseudo_op" >&5 $as_echo "$libffi_cv_as_register_pseudo_op" >&6; } if test "x$libffi_cv_as_register_pseudo_op" = xyes; then $as_echo "#define HAVE_AS_REGISTER_PSEUDO_OP 1" >>confdefs.h fi fi if test x$TARGET = xX86 || test x$TARGET = xX86_WIN32 || test x$TARGET = xX86_64; then { $as_echo "$as_me:${as_lineno-$LINENO}: checking assembler supports pc related relocs" >&5 $as_echo_n "checking assembler supports pc related relocs... " >&6; } if ${libffi_cv_as_x86_pcrel+:} false; then : $as_echo_n "(cached) " >&6 else libffi_cv_as_x86_pcrel=yes echo '.text; foo: nop; .data; .long foo-.; .text' > conftest.s if $CC $CFLAGS -c conftest.s 2>&1 | $EGREP -i 'illegal|warning' > /dev/null; then libffi_cv_as_x86_pcrel=no fi fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $libffi_cv_as_x86_pcrel" >&5 $as_echo "$libffi_cv_as_x86_pcrel" >&6; } if test "x$libffi_cv_as_x86_pcrel" = xyes; then $as_echo "#define HAVE_AS_X86_PCREL 1" >>confdefs.h fi { $as_echo "$as_me:${as_lineno-$LINENO}: checking assembler .ascii pseudo-op support" >&5 $as_echo_n "checking assembler .ascii pseudo-op support... " >&6; } if ${libffi_cv_as_ascii_pseudo_op+:} false; then : $as_echo_n "(cached) " >&6 else libffi_cv_as_ascii_pseudo_op=unknown # Check if we have .ascii cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ asm (".ascii \"string\""); int main () { ; return 0; } _ACEOF if ac_fn_c_try_compile "$LINENO"; then : libffi_cv_as_ascii_pseudo_op=yes else libffi_cv_as_ascii_pseudo_op=no fi rm -f core conftest.err conftest.$ac_objext conftest.$ac_ext fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $libffi_cv_as_ascii_pseudo_op" >&5 $as_echo "$libffi_cv_as_ascii_pseudo_op" >&6; } if test "x$libffi_cv_as_ascii_pseudo_op" = xyes; then $as_echo "#define HAVE_AS_ASCII_PSEUDO_OP 1" >>confdefs.h fi { $as_echo "$as_me:${as_lineno-$LINENO}: checking assembler .string pseudo-op support" >&5 $as_echo_n "checking assembler .string pseudo-op support... " >&6; } if ${libffi_cv_as_string_pseudo_op+:} false; then : $as_echo_n "(cached) " >&6 else libffi_cv_as_string_pseudo_op=unknown # Check if we have .string cat confdefs.h - <<_ACEOF >conftest.$ac_ext /* end confdefs.h. */ asm (".string \"string\""); int main () { ; return 0; } _ACEOF if ac_fn_c_try_compile "$LINENO"; then : libffi_cv_as_string_pseudo_op=yes else libffi_cv_as_string_pseudo_op=no fi rm -f core conftest.err conftest.$ac_objext conftest.$ac_ext fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $libffi_cv_as_string_pseudo_op" >&5 $as_echo "$libffi_cv_as_string_pseudo_op" >&6; } if test "x$libffi_cv_as_string_pseudo_op" = xyes; then $as_echo "#define HAVE_AS_STRING_PSEUDO_OP 1" >>confdefs.h fi fi case "$target" in *-apple-darwin10* | *-*-freebsd* | *-*-openbsd* | *-pc-solaris*) $as_echo "#define FFI_MMAP_EXEC_WRIT 1" >>confdefs.h ;; esac if test x$TARGET = xX86_64; then { $as_echo "$as_me:${as_lineno-$LINENO}: checking assembler supports unwind section type" >&5 $as_echo_n "checking assembler supports unwind section type... " >&6; } if ${libffi_cv_as_x86_64_unwind_section_type+:} false; then : $as_echo_n "(cached) " >&6 else libffi_cv_as_x86_64_unwind_section_type=yes echo '.section .eh_frame,"a",@unwind' > conftest.s if $CC $CFLAGS -c conftest.s 2>&1 | grep -i warning > /dev/null; then libffi_cv_as_x86_64_unwind_section_type=no fi fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $libffi_cv_as_x86_64_unwind_section_type" >&5 $as_echo "$libffi_cv_as_x86_64_unwind_section_type" >&6; } if test "x$libffi_cv_as_x86_64_unwind_section_type" = xyes; then $as_echo "#define HAVE_AS_X86_64_UNWIND_SECTION_TYPE 1" >>confdefs.h fi fi { $as_echo "$as_me:${as_lineno-$LINENO}: checking whether .eh_frame section should be read-only" >&5 $as_echo_n "checking whether .eh_frame section should be read-only... " >&6; } if ${libffi_cv_ro_eh_frame+:} false; then : $as_echo_n "(cached) " >&6 else libffi_cv_ro_eh_frame=no echo 'extern void foo (void); void bar (void) { foo (); foo (); }' > conftest.c if $CC $CFLAGS -S -fpic -fexceptions -o conftest.s conftest.c > /dev/null 2>&1; then if grep '.section.*eh_frame.*"a"' conftest.s > /dev/null; then libffi_cv_ro_eh_frame=yes elif grep '.section.*eh_frame.*#alloc' conftest.c \ | grep -v '#write' > /dev/null; then libffi_cv_ro_eh_frame=yes fi fi rm -f conftest.* fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $libffi_cv_ro_eh_frame" >&5 $as_echo "$libffi_cv_ro_eh_frame" >&6; } if test "x$libffi_cv_ro_eh_frame" = xyes; then $as_echo "#define HAVE_RO_EH_FRAME 1" >>confdefs.h $as_echo "#define EH_FRAME_FLAGS \"a\"" >>confdefs.h else $as_echo "#define EH_FRAME_FLAGS \"aw\"" >>confdefs.h fi { $as_echo "$as_me:${as_lineno-$LINENO}: checking for __attribute__((visibility(\"hidden\")))" >&5 $as_echo_n "checking for __attribute__((visibility(\"hidden\")))... " >&6; } if ${libffi_cv_hidden_visibility_attribute+:} false; then : $as_echo_n "(cached) " >&6 else echo 'int __attribute__ ((visibility ("hidden"))) foo (void) { return 1; }' > conftest.c libffi_cv_hidden_visibility_attribute=no if { ac_try='${CC-cc} -Werror -S conftest.c -o conftest.s 1>&5' { { eval echo "\"\$as_me\":${as_lineno-$LINENO}: \"$ac_try\""; } >&5 (eval $ac_try) 2>&5 ac_status=$? $as_echo "$as_me:${as_lineno-$LINENO}: \$? = $ac_status" >&5 test $ac_status = 0; }; }; then if grep '\.hidden.*foo' conftest.s >/dev/null; then libffi_cv_hidden_visibility_attribute=yes fi fi rm -f conftest.* fi { $as_echo "$as_me:${as_lineno-$LINENO}: result: $libffi_cv_hidden_visibility_attribute" >&5 $as_echo "$libffi_cv_hidden_visibility_attribute" >&6; } if test $libffi_cv_hidden_visibility_attribute = yes; then $as_echo "#define HAVE_HIDDEN_VISIBILITY_ATTRIBUTE 1" >>confdefs.h fi # Check whether --enable-debug was given. if test "${enable_debug+set}" = set; then : enableval=$enable_debug; if test "$enable_debug" = "yes"; then $as_echo "#define FFI_DEBUG 1" >>confdefs.h fi fi # Check whether --enable-structs was given. if test "${enable_structs+set}" = set; then : enableval=$enable_structs; if test "$enable_structs" = "no"; then $as_echo "#define FFI_NO_STRUCTS 1" >>confdefs.h fi fi # Check whether --enable-raw-api was given. if test "${enable_raw_api+set}" = set; then : enableval=$enable_raw_api; if test "$enable_raw_api" = "no"; then $as_echo "#define FFI_NO_RAW_API 1" >>confdefs.h fi fi # Check whether --enable-purify-safety was given. if test "${enable_purify_safety+set}" = set; then : enableval=$enable_purify_safety; if test "$enable_purify_safety" = "yes"; then $as_echo "#define USING_PURIFY 1" >>confdefs.h fi fi ac_config_commands="$ac_config_commands include" ac_config_commands="$ac_config_commands src" ac_config_links="$ac_config_links include/ffitarget.h:src/$TARGETDIR/ffitarget.h" ac_config_files="$ac_config_files include/Makefile include/ffi.h Makefile" cat >confcache <<\_ACEOF # This file is a shell script that caches the results of configure # tests run on this system so they can be shared between configure # scripts and configure runs, see configure's option --config-cache. # It is not useful on other systems. If it contains results you don't # want to keep, you may remove or edit it. # # config.status only pays attention to the cache file if you give it # the --recheck option to rerun configure. # # `ac_cv_env_foo' variables (set or unset) will be overridden when # loading this file, other *unset* `ac_cv_foo' will be assigned the # following values. _ACEOF # The following way of writing the cache mishandles newlines in values, # but we know of no workaround that is simple, portable, and efficient. # So, we kill variables containing newlines. # Ultrix sh set writes to stderr and can't be redirected directly, # and sets the high bit in the cache file unless we assign to the vars. ( for ac_var in `(set) 2>&1 | sed -n 's/^\([a-zA-Z_][a-zA-Z0-9_]*\)=.*/\1/p'`; do eval ac_val=\$$ac_var case $ac_val in #( *${as_nl}*) case $ac_var in #( *_cv_*) { $as_echo "$as_me:${as_lineno-$LINENO}: WARNING: cache variable $ac_var contains a newline" >&5 $as_echo "$as_me: WARNING: cache variable $ac_var contains a newline" >&2;} ;; esac case $ac_var in #( _ | IFS | as_nl) ;; #( BASH_ARGV | BASH_SOURCE) eval $ac_var= ;; #( *) { eval $ac_var=; unset $ac_var;} ;; esac ;; esac done (set) 2>&1 | case $as_nl`(ac_space=' '; set) 2>&1` in #( *${as_nl}ac_space=\ *) # `set' does not quote correctly, so add quotes: double-quote # substitution turns \\\\ into \\, and sed turns \\ into \. sed -n \ "s/'/'\\\\''/g; s/^\\([_$as_cr_alnum]*_cv_[_$as_cr_alnum]*\\)=\\(.*\\)/\\1='\\2'/p" ;; #( *) # `set' quotes correctly as required by POSIX, so do not add quotes. sed -n "/^[_$as_cr_alnum]*_cv_[_$as_cr_alnum]*=/p" ;; esac | sort ) | sed ' /^ac_cv_env_/b end t clear :clear s/^\([^=]*\)=\(.*[{}].*\)$/test "${\1+set}" = set || &/ t end s/^\([^=]*\)=\(.*\)$/\1=${\1=\2}/ :end' >>confcache if diff "$cache_file" confcache >/dev/null 2>&1; then :; else if test -w "$cache_file"; then if test "x$cache_file" != "x/dev/null"; then { $as_echo "$as_me:${as_lineno-$LINENO}: updating cache $cache_file" >&5 $as_echo "$as_me: updating cache $cache_file" >&6;} if test ! -f "$cache_file" || test -h "$cache_file"; then cat confcache >"$cache_file" else case $cache_file in #( */* | ?:*) mv -f confcache "$cache_file"$$ && mv -f "$cache_file"$$ "$cache_file" ;; #( *) mv -f confcache "$cache_file" ;; esac fi fi else { $as_echo "$as_me:${as_lineno-$LINENO}: not updating unwritable cache $cache_file" >&5 $as_echo "$as_me: not updating unwritable cache $cache_file" >&6;} fi fi rm -f confcache test "x$prefix" = xNONE && prefix=$ac_default_prefix # Let make expand exec_prefix. test "x$exec_prefix" = xNONE && exec_prefix='${prefix}' DEFS=-DHAVE_CONFIG_H ac_libobjs= ac_ltlibobjs= U= for ac_i in : $LIBOBJS; do test "x$ac_i" = x: && continue # 1. Remove the extension, and $U if already installed. ac_script='s/\$U\././;s/\.o$//;s/\.obj$//' ac_i=`$as_echo "$ac_i" | sed "$ac_script"` # 2. Prepend LIBOBJDIR. When used with automake>=1.10 LIBOBJDIR # will be set to the directory where LIBOBJS objects are built. as_fn_append ac_libobjs " \${LIBOBJDIR}$ac_i\$U.$ac_objext" as_fn_append ac_ltlibobjs " \${LIBOBJDIR}$ac_i"'$U.lo' done LIBOBJS=$ac_libobjs LTLIBOBJS=$ac_ltlibobjs if test -n "$EXEEXT"; then am__EXEEXT_TRUE= am__EXEEXT_FALSE='#' else am__EXEEXT_TRUE='#' am__EXEEXT_FALSE= fi if test -z "${AMDEP_TRUE}" && test -z "${AMDEP_FALSE}"; then as_fn_error $? "conditional \"AMDEP\" was never defined. Usually this means the macro was only invoked conditionally." "$LINENO" 5 fi if test -z "${am__fastdepCC_TRUE}" && test -z "${am__fastdepCC_FALSE}"; then as_fn_error $? "conditional \"am__fastdepCC\" was never defined. Usually this means the macro was only invoked conditionally." "$LINENO" 5 fi if test -z "${am__fastdepCCAS_TRUE}" && test -z "${am__fastdepCCAS_FALSE}"; then as_fn_error $? "conditional \"am__fastdepCCAS\" was never defined. Usually this means the macro was only invoked conditionally." "$LINENO" 5 fi if test -z "${TESTSUBDIR_TRUE}" && test -z "${TESTSUBDIR_FALSE}"; then as_fn_error $? "conditional \"TESTSUBDIR\" was never defined. Usually this means the macro was only invoked conditionally." "$LINENO" 5 fi if test -z "${MIPS_TRUE}" && test -z "${MIPS_FALSE}"; then as_fn_error $? "conditional \"MIPS\" was never defined. Usually this means the macro was only invoked conditionally." "$LINENO" 5 fi if test -z "${SPARC_TRUE}" && test -z "${SPARC_FALSE}"; then as_fn_error $? "conditional \"SPARC\" was never defined. Usually this means the macro was only invoked conditionally." "$LINENO" 5 fi if test -z "${X86_TRUE}" && test -z "${X86_FALSE}"; then as_fn_error $? "conditional \"X86\" was never defined. Usually this means the macro was only invoked conditionally." "$LINENO" 5 fi if test -z "${X86_FREEBSD_TRUE}" && test -z "${X86_FREEBSD_FALSE}"; then as_fn_error $? "conditional \"X86_FREEBSD\" was never defined. Usually this means the macro was only invoked conditionally." "$LINENO" 5 fi if test -z "${X86_WIN32_TRUE}" && test -z "${X86_WIN32_FALSE}"; then as_fn_error $? "conditional \"X86_WIN32\" was never defined. Usually this means the macro was only invoked conditionally." "$LINENO" 5 fi if test -z "${X86_WIN64_TRUE}" && test -z "${X86_WIN64_FALSE}"; then as_fn_error $? "conditional \"X86_WIN64\" was never defined. Usually this means the macro was only invoked conditionally." "$LINENO" 5 fi if test -z "${X86_DARWIN_TRUE}" && test -z "${X86_DARWIN_FALSE}"; then as_fn_error $? "conditional \"X86_DARWIN\" was never defined. Usually this means the macro was only invoked conditionally." "$LINENO" 5 fi if test -z "${ALPHA_TRUE}" && test -z "${ALPHA_FALSE}"; then as_fn_error $? "conditional \"ALPHA\" was never defined. Usually this means the macro was only invoked conditionally." "$LINENO" 5 fi if test -z "${IA64_TRUE}" && test -z "${IA64_FALSE}"; then as_fn_error $? "conditional \"IA64\" was never defined. Usually this means the macro was only invoked conditionally." "$LINENO" 5 fi if test -z "${M32R_TRUE}" && test -z "${M32R_FALSE}"; then as_fn_error $? "conditional \"M32R\" was never defined. Usually this means the macro was only invoked conditionally." "$LINENO" 5 fi if test -z "${M68K_TRUE}" && test -z "${M68K_FALSE}"; then as_fn_error $? "conditional \"M68K\" was never defined. Usually this means the macro was only invoked conditionally." "$LINENO" 5 fi if test -z "${POWERPC_TRUE}" && test -z "${POWERPC_FALSE}"; then as_fn_error $? "conditional \"POWERPC\" was never defined. Usually this means the macro was only invoked conditionally." "$LINENO" 5 fi if test -z "${POWERPC_AIX_TRUE}" && test -z "${POWERPC_AIX_FALSE}"; then as_fn_error $? "conditional \"POWERPC_AIX\" was never defined. Usually this means the macro was only invoked conditionally." "$LINENO" 5 fi if test -z "${POWERPC_DARWIN_TRUE}" && test -z "${POWERPC_DARWIN_FALSE}"; then as_fn_error $? "conditional \"POWERPC_DARWIN\" was never defined. Usually this means the macro was only invoked conditionally." "$LINENO" 5 fi if test -z "${POWERPC_FREEBSD_TRUE}" && test -z "${POWERPC_FREEBSD_FALSE}"; then as_fn_error $? "conditional \"POWERPC_FREEBSD\" was never defined. Usually this means the macro was only invoked conditionally." "$LINENO" 5 fi if test -z "${ARM_TRUE}" && test -z "${ARM_FALSE}"; then as_fn_error $? "conditional \"ARM\" was never defined. Usually this means the macro was only invoked conditionally." "$LINENO" 5 fi if test -z "${AVR32_TRUE}" && test -z "${AVR32_FALSE}"; then as_fn_error $? "conditional \"AVR32\" was never defined. Usually this means the macro was only invoked conditionally." "$LINENO" 5 fi if test -z "${LIBFFI_CRIS_TRUE}" && test -z "${LIBFFI_CRIS_FALSE}"; then as_fn_error $? "conditional \"LIBFFI_CRIS\" was never defined. Usually this means the macro was only invoked conditionally." "$LINENO" 5 fi if test -z "${FRV_TRUE}" && test -z "${FRV_FALSE}"; then as_fn_error $? "conditional \"FRV\" was never defined. Usually this means the macro was only invoked conditionally." "$LINENO" 5 fi if test -z "${S390_TRUE}" && test -z "${S390_FALSE}"; then as_fn_error $? "conditional \"S390\" was never defined. Usually this means the macro was only invoked conditionally." "$LINENO" 5 fi if test -z "${X86_64_TRUE}" && test -z "${X86_64_FALSE}"; then as_fn_error $? "conditional \"X86_64\" was never defined. Usually this means the macro was only invoked conditionally." "$LINENO" 5 fi if test -z "${SH_TRUE}" && test -z "${SH_FALSE}"; then as_fn_error $? "conditional \"SH\" was never defined. Usually this means the macro was only invoked conditionally." "$LINENO" 5 fi if test -z "${SH64_TRUE}" && test -z "${SH64_FALSE}"; then as_fn_error $? "conditional \"SH64\" was never defined. Usually this means the macro was only invoked conditionally." "$LINENO" 5 fi if test -z "${PA_LINUX_TRUE}" && test -z "${PA_LINUX_FALSE}"; then as_fn_error $? "conditional \"PA_LINUX\" was never defined. Usually this means the macro was only invoked conditionally." "$LINENO" 5 fi if test -z "${PA_HPUX_TRUE}" && test -z "${PA_HPUX_FALSE}"; then as_fn_error $? "conditional \"PA_HPUX\" was never defined. Usually this means the macro was only invoked conditionally." "$LINENO" 5 fi if test -z "${PA64_HPUX_TRUE}" && test -z "${PA64_HPUX_FALSE}"; then as_fn_error $? "conditional \"PA64_HPUX\" was never defined. Usually this means the macro was only invoked conditionally." "$LINENO" 5 fi : "${CONFIG_STATUS=./config.status}" ac_write_fail=0 ac_clean_files_save=$ac_clean_files ac_clean_files="$ac_clean_files $CONFIG_STATUS" { $as_echo "$as_me:${as_lineno-$LINENO}: creating $CONFIG_STATUS" >&5 $as_echo "$as_me: creating $CONFIG_STATUS" >&6;} as_write_fail=0 cat >$CONFIG_STATUS <<_ASEOF || as_write_fail=1 #! $SHELL # Generated by $as_me. # Run this file to recreate the current configuration. # Compiler output produced by configure, useful for debugging # configure, is in config.log if it exists. debug=false ac_cs_recheck=false ac_cs_silent=false SHELL=\${CONFIG_SHELL-$SHELL} export SHELL _ASEOF cat >>$CONFIG_STATUS <<\_ASEOF || as_write_fail=1 ## -------------------- ## ## M4sh Initialization. ## ## -------------------- ## # Be more Bourne compatible DUALCASE=1; export DUALCASE # for MKS sh if test -n "${ZSH_VERSION+set}" && (emulate sh) >/dev/null 2>&1; then : emulate sh NULLCMD=: # Pre-4.2 versions of Zsh do word splitting on ${1+"$@"}, which # is contrary to our usage. Disable this feature. alias -g '${1+"$@"}'='"$@"' setopt NO_GLOB_SUBST else case `(set -o) 2>/dev/null` in #( *posix*) : set -o posix ;; #( *) : ;; esac fi as_nl=' ' export as_nl # Printing a long string crashes Solaris 7 /usr/bin/printf. as_echo='\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\\' as_echo=$as_echo$as_echo$as_echo$as_echo$as_echo as_echo=$as_echo$as_echo$as_echo$as_echo$as_echo$as_echo # Prefer a ksh shell builtin over an external printf program on Solaris, # but without wasting forks for bash or zsh. if test -z "$BASH_VERSION$ZSH_VERSION" \ && (test "X`print -r -- $as_echo`" = "X$as_echo") 2>/dev/null; then as_echo='print -r --' as_echo_n='print -rn --' elif (test "X`printf %s $as_echo`" = "X$as_echo") 2>/dev/null; then as_echo='printf %s\n' as_echo_n='printf %s' else if test "X`(/usr/ucb/echo -n -n $as_echo) 2>/dev/null`" = "X-n $as_echo"; then as_echo_body='eval /usr/ucb/echo -n "$1$as_nl"' as_echo_n='/usr/ucb/echo -n' else as_echo_body='eval expr "X$1" : "X\\(.*\\)"' as_echo_n_body='eval arg=$1; case $arg in #( *"$as_nl"*) expr "X$arg" : "X\\(.*\\)$as_nl"; arg=`expr "X$arg" : ".*$as_nl\\(.*\\)"`;; esac; expr "X$arg" : "X\\(.*\\)" | tr -d "$as_nl" ' export as_echo_n_body as_echo_n='sh -c $as_echo_n_body as_echo' fi export as_echo_body as_echo='sh -c $as_echo_body as_echo' fi # The user is always right. if test "${PATH_SEPARATOR+set}" != set; then PATH_SEPARATOR=: (PATH='/bin;/bin'; FPATH=$PATH; sh -c :) >/dev/null 2>&1 && { (PATH='/bin:/bin'; FPATH=$PATH; sh -c :) >/dev/null 2>&1 || PATH_SEPARATOR=';' } fi # IFS # We need space, tab and new line, in precisely that order. Quoting is # there to prevent editors from complaining about space-tab. # (If _AS_PATH_WALK were called with IFS unset, it would disable word # splitting by setting IFS to empty value.) IFS=" "" $as_nl" # Find who we are. Look in the path if we contain no directory separator. as_myself= case $0 in #(( *[\\/]* ) as_myself=$0 ;; *) as_save_IFS=$IFS; IFS=$PATH_SEPARATOR for as_dir in $PATH do IFS=$as_save_IFS test -z "$as_dir" && as_dir=. test -r "$as_dir/$0" && as_myself=$as_dir/$0 && break done IFS=$as_save_IFS ;; esac # We did not find ourselves, most probably we were run as `sh COMMAND' # in which case we are not to be found in the path. if test "x$as_myself" = x; then as_myself=$0 fi if test ! -f "$as_myself"; then $as_echo "$as_myself: error: cannot find myself; rerun with an absolute file name" >&2 exit 1 fi # Unset variables that we do not need and which cause bugs (e.g. in # pre-3.0 UWIN ksh). But do not cause bugs in bash 2.01; the "|| exit 1" # suppresses any "Segmentation fault" message there. '((' could # trigger a bug in pdksh 5.2.14. for as_var in BASH_ENV ENV MAIL MAILPATH do eval test x\${$as_var+set} = xset \ && ( (unset $as_var) || exit 1) >/dev/null 2>&1 && unset $as_var || : done PS1='$ ' PS2='> ' PS4='+ ' # NLS nuisances. LC_ALL=C export LC_ALL LANGUAGE=C export LANGUAGE # CDPATH. (unset CDPATH) >/dev/null 2>&1 && unset CDPATH # as_fn_error STATUS ERROR [LINENO LOG_FD] # ---------------------------------------- # Output "`basename $0`: error: ERROR" to stderr. If LINENO and LOG_FD are # provided, also output the error to LOG_FD, referencing LINENO. Then exit the # script with STATUS, using 1 if that was 0. as_fn_error () { as_status=$1; test $as_status -eq 0 && as_status=1 if test "$4"; then as_lineno=${as_lineno-"$3"} as_lineno_stack=as_lineno_stack=$as_lineno_stack $as_echo "$as_me:${as_lineno-$LINENO}: error: $2" >&$4 fi $as_echo "$as_me: error: $2" >&2 as_fn_exit $as_status } # as_fn_error # as_fn_set_status STATUS # ----------------------- # Set $? to STATUS, without forking. as_fn_set_status () { return $1 } # as_fn_set_status # as_fn_exit STATUS # ----------------- # Exit the shell with STATUS, even in a "trap 0" or "set -e" context. as_fn_exit () { set +e as_fn_set_status $1 exit $1 } # as_fn_exit # as_fn_unset VAR # --------------- # Portably unset VAR. as_fn_unset () { { eval $1=; unset $1;} } as_unset=as_fn_unset # as_fn_append VAR VALUE # ---------------------- # Append the text in VALUE to the end of the definition contained in VAR. Take # advantage of any shell optimizations that allow amortized linear growth over # repeated appends, instead of the typical quadratic growth present in naive # implementations. if (eval "as_var=1; as_var+=2; test x\$as_var = x12") 2>/dev/null; then : eval 'as_fn_append () { eval $1+=\$2 }' else as_fn_append () { eval $1=\$$1\$2 } fi # as_fn_append # as_fn_arith ARG... # ------------------ # Perform arithmetic evaluation on the ARGs, and store the result in the # global $as_val. Take advantage of shells that can avoid forks. The arguments # must be portable across $(()) and expr. if (eval "test \$(( 1 + 1 )) = 2") 2>/dev/null; then : eval 'as_fn_arith () { as_val=$(( $* )) }' else as_fn_arith () { as_val=`expr "$@" || test $? -eq 1` } fi # as_fn_arith if expr a : '\(a\)' >/dev/null 2>&1 && test "X`expr 00001 : '.*\(...\)'`" = X001; then as_expr=expr else as_expr=false fi if (basename -- /) >/dev/null 2>&1 && test "X`basename -- / 2>&1`" = "X/"; then as_basename=basename else as_basename=false fi if (as_dir=`dirname -- /` && test "X$as_dir" = X/) >/dev/null 2>&1; then as_dirname=dirname else as_dirname=false fi as_me=`$as_basename -- "$0" || $as_expr X/"$0" : '.*/\([^/][^/]*\)/*$' \| \ X"$0" : 'X\(//\)$' \| \ X"$0" : 'X\(/\)' \| . 2>/dev/null || $as_echo X/"$0" | sed '/^.*\/\([^/][^/]*\)\/*$/{ s//\1/ q } /^X\/\(\/\/\)$/{ s//\1/ q } /^X\/\(\/\).*/{ s//\1/ q } s/.*/./; q'` # Avoid depending upon Character Ranges. as_cr_letters='abcdefghijklmnopqrstuvwxyz' as_cr_LETTERS='ABCDEFGHIJKLMNOPQRSTUVWXYZ' as_cr_Letters=$as_cr_letters$as_cr_LETTERS as_cr_digits='0123456789' as_cr_alnum=$as_cr_Letters$as_cr_digits ECHO_C= ECHO_N= ECHO_T= case `echo -n x` in #((((( -n*) case `echo 'xy\c'` in *c*) ECHO_T=' ';; # ECHO_T is single tab character. xy) ECHO_C='\c';; *) echo `echo ksh88 bug on AIX 6.1` > /dev/null ECHO_T=' ';; esac;; *) ECHO_N='-n';; esac rm -f conf$$ conf$$.exe conf$$.file if test -d conf$$.dir; then rm -f conf$$.dir/conf$$.file else rm -f conf$$.dir mkdir conf$$.dir 2>/dev/null fi if (echo >conf$$.file) 2>/dev/null; then if ln -s conf$$.file conf$$ 2>/dev/null; then as_ln_s='ln -s' # ... but there are two gotchas: # 1) On MSYS, both `ln -s file dir' and `ln file dir' fail. # 2) DJGPP < 2.04 has no symlinks; `ln -s' creates a wrapper executable. # In both cases, we have to default to `cp -pR'. ln -s conf$$.file conf$$.dir 2>/dev/null && test ! -f conf$$.exe || as_ln_s='cp -pR' elif ln conf$$.file conf$$ 2>/dev/null; then as_ln_s=ln else as_ln_s='cp -pR' fi else as_ln_s='cp -pR' fi rm -f conf$$ conf$$.exe conf$$.dir/conf$$.file conf$$.file rmdir conf$$.dir 2>/dev/null # as_fn_mkdir_p # ------------- # Create "$as_dir" as a directory, including parents if necessary. as_fn_mkdir_p () { case $as_dir in #( -*) as_dir=./$as_dir;; esac test -d "$as_dir" || eval $as_mkdir_p || { as_dirs= while :; do case $as_dir in #( *\'*) as_qdir=`$as_echo "$as_dir" | sed "s/'/'\\\\\\\\''/g"`;; #'( *) as_qdir=$as_dir;; esac as_dirs="'$as_qdir' $as_dirs" as_dir=`$as_dirname -- "$as_dir" || $as_expr X"$as_dir" : 'X\(.*[^/]\)//*[^/][^/]*/*$' \| \ X"$as_dir" : 'X\(//\)[^/]' \| \ X"$as_dir" : 'X\(//\)$' \| \ X"$as_dir" : 'X\(/\)' \| . 2>/dev/null || $as_echo X"$as_dir" | sed '/^X\(.*[^/]\)\/\/*[^/][^/]*\/*$/{ s//\1/ q } /^X\(\/\/\)[^/].*/{ s//\1/ q } /^X\(\/\/\)$/{ s//\1/ q } /^X\(\/\).*/{ s//\1/ q } s/.*/./; q'` test -d "$as_dir" && break done test -z "$as_dirs" || eval "mkdir $as_dirs" } || test -d "$as_dir" || as_fn_error $? "cannot create directory $as_dir" } # as_fn_mkdir_p if mkdir -p . 2>/dev/null; then as_mkdir_p='mkdir -p "$as_dir"' else test -d ./-p && rmdir ./-p as_mkdir_p=false fi # as_fn_executable_p FILE # ----------------------- # Test if FILE is an executable regular file. as_fn_executable_p () { test -f "$1" && test -x "$1" } # as_fn_executable_p as_test_x='test -x' as_executable_p=as_fn_executable_p # Sed expression to map a string onto a valid CPP name. as_tr_cpp="eval sed 'y%*$as_cr_letters%P$as_cr_LETTERS%;s%[^_$as_cr_alnum]%_%g'" # Sed expression to map a string onto a valid variable name. as_tr_sh="eval sed 'y%*+%pp%;s%[^_$as_cr_alnum]%_%g'" exec 6>&1 ## ----------------------------------- ## ## Main body of $CONFIG_STATUS script. ## ## ----------------------------------- ## _ASEOF test $as_write_fail = 0 && chmod +x $CONFIG_STATUS || ac_write_fail=1 cat >>$CONFIG_STATUS <<\_ACEOF || ac_write_fail=1 # Save the log message, to keep $0 and so on meaningful, and to # report actual input values of CONFIG_FILES etc. instead of their # values after options handling. ac_log=" This file was extended by libffi $as_me 3.0.9, which was generated by GNU Autoconf 2.69. Invocation command line was CONFIG_FILES = $CONFIG_FILES CONFIG_HEADERS = $CONFIG_HEADERS CONFIG_LINKS = $CONFIG_LINKS CONFIG_COMMANDS = $CONFIG_COMMANDS $ $0 $@ on `(hostname || uname -n) 2>/dev/null | sed 1q` " _ACEOF case $ac_config_files in *" "*) set x $ac_config_files; shift; ac_config_files=$*;; esac case $ac_config_headers in *" "*) set x $ac_config_headers; shift; ac_config_headers=$*;; esac cat >>$CONFIG_STATUS <<_ACEOF || ac_write_fail=1 # Files that config.status was made for. config_files="$ac_config_files" config_headers="$ac_config_headers" config_links="$ac_config_links" config_commands="$ac_config_commands" _ACEOF cat >>$CONFIG_STATUS <<\_ACEOF || ac_write_fail=1 ac_cs_usage="\ \`$as_me' instantiates files and other configuration actions from templates according to the current configuration. Unless the files and actions are specified as TAGs, all are instantiated by default. Usage: $0 [OPTION]... [TAG]... -h, --help print this help, then exit -V, --version print version number and configuration settings, then exit --config print configuration, then exit -q, --quiet, --silent do not print progress messages -d, --debug don't remove temporary files --recheck update $as_me by reconfiguring in the same conditions --file=FILE[:TEMPLATE] instantiate the configuration file FILE --header=FILE[:TEMPLATE] instantiate the configuration header FILE Configuration files: $config_files Configuration headers: $config_headers Configuration links: $config_links Configuration commands: $config_commands Report bugs to ." _ACEOF cat >>$CONFIG_STATUS <<_ACEOF || ac_write_fail=1 ac_cs_config="`$as_echo "$ac_configure_args" | sed 's/^ //; s/[\\""\`\$]/\\\\&/g'`" ac_cs_version="\\ libffi config.status 3.0.9 configured by $0, generated by GNU Autoconf 2.69, with options \\"\$ac_cs_config\\" Copyright (C) 2012 Free Software Foundation, Inc. This config.status script is free software; the Free Software Foundation gives unlimited permission to copy, distribute and modify it." ac_pwd='$ac_pwd' srcdir='$srcdir' INSTALL='$INSTALL' MKDIR_P='$MKDIR_P' AWK='$AWK' test -n "\$AWK" || AWK=awk _ACEOF cat >>$CONFIG_STATUS <<\_ACEOF || ac_write_fail=1 # The default lists apply if the user does not specify any file. ac_need_defaults=: while test $# != 0 do case $1 in --*=?*) ac_option=`expr "X$1" : 'X\([^=]*\)='` ac_optarg=`expr "X$1" : 'X[^=]*=\(.*\)'` ac_shift=: ;; --*=) ac_option=`expr "X$1" : 'X\([^=]*\)='` ac_optarg= ac_shift=: ;; *) ac_option=$1 ac_optarg=$2 ac_shift=shift ;; esac case $ac_option in # Handling of the options. -recheck | --recheck | --rechec | --reche | --rech | --rec | --re | --r) ac_cs_recheck=: ;; --version | --versio | --versi | --vers | --ver | --ve | --v | -V ) $as_echo "$ac_cs_version"; exit ;; --config | --confi | --conf | --con | --co | --c ) $as_echo "$ac_cs_config"; exit ;; --debug | --debu | --deb | --de | --d | -d ) debug=: ;; --file | --fil | --fi | --f ) $ac_shift case $ac_optarg in *\'*) ac_optarg=`$as_echo "$ac_optarg" | sed "s/'/'\\\\\\\\''/g"` ;; '') as_fn_error $? "missing file argument" ;; esac as_fn_append CONFIG_FILES " '$ac_optarg'" ac_need_defaults=false;; --header | --heade | --head | --hea ) $ac_shift case $ac_optarg in *\'*) ac_optarg=`$as_echo "$ac_optarg" | sed "s/'/'\\\\\\\\''/g"` ;; esac as_fn_append CONFIG_HEADERS " '$ac_optarg'" ac_need_defaults=false;; --he | --h) # Conflict between --help and --header as_fn_error $? "ambiguous option: \`$1' Try \`$0 --help' for more information.";; --help | --hel | -h ) $as_echo "$ac_cs_usage"; exit ;; -q | -quiet | --quiet | --quie | --qui | --qu | --q \ | -silent | --silent | --silen | --sile | --sil | --si | --s) ac_cs_silent=: ;; # This is an error. -*) as_fn_error $? "unrecognized option: \`$1' Try \`$0 --help' for more information." ;; *) as_fn_append ac_config_targets " $1" ac_need_defaults=false ;; esac shift done ac_configure_extra_args= if $ac_cs_silent; then exec 6>/dev/null ac_configure_extra_args="$ac_configure_extra_args --silent" fi _ACEOF cat >>$CONFIG_STATUS <<_ACEOF || ac_write_fail=1 if \$ac_cs_recheck; then set X $SHELL '$0' $ac_configure_args \$ac_configure_extra_args --no-create --no-recursion shift \$as_echo "running CONFIG_SHELL=$SHELL \$*" >&6 CONFIG_SHELL='$SHELL' export CONFIG_SHELL exec "\$@" fi _ACEOF cat >>$CONFIG_STATUS <<\_ACEOF || ac_write_fail=1 exec 5>>config.log { echo sed 'h;s/./-/g;s/^.../## /;s/...$/ ##/;p;x;p;x' <<_ASBOX ## Running $as_me. ## _ASBOX $as_echo "$ac_log" } >&5 _ACEOF cat >>$CONFIG_STATUS <<_ACEOF || ac_write_fail=1 # # INIT-COMMANDS # AMDEP_TRUE="$AMDEP_TRUE" ac_aux_dir="$ac_aux_dir" # The HP-UX ksh and POSIX shell print the target directory to stdout # if CDPATH is set. (unset CDPATH) >/dev/null 2>&1 && unset CDPATH sed_quote_subst='$sed_quote_subst' double_quote_subst='$double_quote_subst' delay_variable_subst='$delay_variable_subst' macro_version='`$ECHO "$macro_version" | $SED "$delay_single_quote_subst"`' macro_revision='`$ECHO "$macro_revision" | $SED "$delay_single_quote_subst"`' enable_shared='`$ECHO "$enable_shared" | $SED "$delay_single_quote_subst"`' enable_static='`$ECHO "$enable_static" | $SED "$delay_single_quote_subst"`' pic_mode='`$ECHO "$pic_mode" | $SED "$delay_single_quote_subst"`' enable_fast_install='`$ECHO "$enable_fast_install" | $SED "$delay_single_quote_subst"`' SHELL='`$ECHO "$SHELL" | $SED "$delay_single_quote_subst"`' ECHO='`$ECHO "$ECHO" | $SED "$delay_single_quote_subst"`' PATH_SEPARATOR='`$ECHO "$PATH_SEPARATOR" | $SED "$delay_single_quote_subst"`' host_alias='`$ECHO "$host_alias" | $SED "$delay_single_quote_subst"`' host='`$ECHO "$host" | $SED "$delay_single_quote_subst"`' host_os='`$ECHO "$host_os" | $SED "$delay_single_quote_subst"`' build_alias='`$ECHO "$build_alias" | $SED "$delay_single_quote_subst"`' build='`$ECHO "$build" | $SED "$delay_single_quote_subst"`' build_os='`$ECHO "$build_os" | $SED "$delay_single_quote_subst"`' SED='`$ECHO "$SED" | $SED "$delay_single_quote_subst"`' Xsed='`$ECHO "$Xsed" | $SED "$delay_single_quote_subst"`' GREP='`$ECHO "$GREP" | $SED "$delay_single_quote_subst"`' EGREP='`$ECHO "$EGREP" | $SED "$delay_single_quote_subst"`' FGREP='`$ECHO "$FGREP" | $SED "$delay_single_quote_subst"`' LD='`$ECHO "$LD" | $SED "$delay_single_quote_subst"`' NM='`$ECHO "$NM" | $SED "$delay_single_quote_subst"`' LN_S='`$ECHO "$LN_S" | $SED "$delay_single_quote_subst"`' max_cmd_len='`$ECHO "$max_cmd_len" | $SED "$delay_single_quote_subst"`' ac_objext='`$ECHO "$ac_objext" | $SED "$delay_single_quote_subst"`' exeext='`$ECHO "$exeext" | $SED "$delay_single_quote_subst"`' lt_unset='`$ECHO "$lt_unset" | $SED "$delay_single_quote_subst"`' lt_SP2NL='`$ECHO "$lt_SP2NL" | $SED "$delay_single_quote_subst"`' lt_NL2SP='`$ECHO "$lt_NL2SP" | $SED "$delay_single_quote_subst"`' lt_cv_to_host_file_cmd='`$ECHO "$lt_cv_to_host_file_cmd" | $SED "$delay_single_quote_subst"`' lt_cv_to_tool_file_cmd='`$ECHO "$lt_cv_to_tool_file_cmd" | $SED "$delay_single_quote_subst"`' reload_flag='`$ECHO "$reload_flag" | $SED "$delay_single_quote_subst"`' reload_cmds='`$ECHO "$reload_cmds" | $SED "$delay_single_quote_subst"`' OBJDUMP='`$ECHO "$OBJDUMP" | $SED "$delay_single_quote_subst"`' deplibs_check_method='`$ECHO "$deplibs_check_method" | $SED "$delay_single_quote_subst"`' file_magic_cmd='`$ECHO "$file_magic_cmd" | $SED "$delay_single_quote_subst"`' file_magic_glob='`$ECHO "$file_magic_glob" | $SED "$delay_single_quote_subst"`' want_nocaseglob='`$ECHO "$want_nocaseglob" | $SED "$delay_single_quote_subst"`' DLLTOOL='`$ECHO "$DLLTOOL" | $SED "$delay_single_quote_subst"`' sharedlib_from_linklib_cmd='`$ECHO "$sharedlib_from_linklib_cmd" | $SED "$delay_single_quote_subst"`' AR='`$ECHO "$AR" | $SED "$delay_single_quote_subst"`' AR_FLAGS='`$ECHO "$AR_FLAGS" | $SED "$delay_single_quote_subst"`' archiver_list_spec='`$ECHO "$archiver_list_spec" | $SED "$delay_single_quote_subst"`' STRIP='`$ECHO "$STRIP" | $SED "$delay_single_quote_subst"`' RANLIB='`$ECHO "$RANLIB" | $SED "$delay_single_quote_subst"`' old_postinstall_cmds='`$ECHO "$old_postinstall_cmds" | $SED "$delay_single_quote_subst"`' old_postuninstall_cmds='`$ECHO "$old_postuninstall_cmds" | $SED "$delay_single_quote_subst"`' old_archive_cmds='`$ECHO "$old_archive_cmds" | $SED "$delay_single_quote_subst"`' lock_old_archive_extraction='`$ECHO "$lock_old_archive_extraction" | $SED "$delay_single_quote_subst"`' CC='`$ECHO "$CC" | $SED "$delay_single_quote_subst"`' CFLAGS='`$ECHO "$CFLAGS" | $SED "$delay_single_quote_subst"`' compiler='`$ECHO "$compiler" | $SED "$delay_single_quote_subst"`' GCC='`$ECHO "$GCC" | $SED "$delay_single_quote_subst"`' lt_cv_sys_global_symbol_pipe='`$ECHO "$lt_cv_sys_global_symbol_pipe" | $SED "$delay_single_quote_subst"`' lt_cv_sys_global_symbol_to_cdecl='`$ECHO "$lt_cv_sys_global_symbol_to_cdecl" | $SED "$delay_single_quote_subst"`' lt_cv_sys_global_symbol_to_c_name_address='`$ECHO "$lt_cv_sys_global_symbol_to_c_name_address" | $SED "$delay_single_quote_subst"`' lt_cv_sys_global_symbol_to_c_name_address_lib_prefix='`$ECHO "$lt_cv_sys_global_symbol_to_c_name_address_lib_prefix" | $SED "$delay_single_quote_subst"`' nm_file_list_spec='`$ECHO "$nm_file_list_spec" | $SED "$delay_single_quote_subst"`' lt_sysroot='`$ECHO "$lt_sysroot" | $SED "$delay_single_quote_subst"`' objdir='`$ECHO "$objdir" | $SED "$delay_single_quote_subst"`' MAGIC_CMD='`$ECHO "$MAGIC_CMD" | $SED "$delay_single_quote_subst"`' lt_prog_compiler_no_builtin_flag='`$ECHO "$lt_prog_compiler_no_builtin_flag" | $SED "$delay_single_quote_subst"`' lt_prog_compiler_pic='`$ECHO "$lt_prog_compiler_pic" | $SED "$delay_single_quote_subst"`' lt_prog_compiler_wl='`$ECHO "$lt_prog_compiler_wl" | $SED "$delay_single_quote_subst"`' lt_prog_compiler_static='`$ECHO "$lt_prog_compiler_static" | $SED "$delay_single_quote_subst"`' lt_cv_prog_compiler_c_o='`$ECHO "$lt_cv_prog_compiler_c_o" | $SED "$delay_single_quote_subst"`' need_locks='`$ECHO "$need_locks" | $SED "$delay_single_quote_subst"`' MANIFEST_TOOL='`$ECHO "$MANIFEST_TOOL" | $SED "$delay_single_quote_subst"`' DSYMUTIL='`$ECHO "$DSYMUTIL" | $SED "$delay_single_quote_subst"`' NMEDIT='`$ECHO "$NMEDIT" | $SED "$delay_single_quote_subst"`' LIPO='`$ECHO "$LIPO" | $SED "$delay_single_quote_subst"`' OTOOL='`$ECHO "$OTOOL" | $SED "$delay_single_quote_subst"`' OTOOL64='`$ECHO "$OTOOL64" | $SED "$delay_single_quote_subst"`' libext='`$ECHO "$libext" | $SED "$delay_single_quote_subst"`' shrext_cmds='`$ECHO "$shrext_cmds" | $SED "$delay_single_quote_subst"`' extract_expsyms_cmds='`$ECHO "$extract_expsyms_cmds" | $SED "$delay_single_quote_subst"`' archive_cmds_need_lc='`$ECHO "$archive_cmds_need_lc" | $SED "$delay_single_quote_subst"`' enable_shared_with_static_runtimes='`$ECHO "$enable_shared_with_static_runtimes" | $SED "$delay_single_quote_subst"`' export_dynamic_flag_spec='`$ECHO "$export_dynamic_flag_spec" | $SED "$delay_single_quote_subst"`' whole_archive_flag_spec='`$ECHO "$whole_archive_flag_spec" | $SED "$delay_single_quote_subst"`' compiler_needs_object='`$ECHO "$compiler_needs_object" | $SED "$delay_single_quote_subst"`' old_archive_from_new_cmds='`$ECHO "$old_archive_from_new_cmds" | $SED "$delay_single_quote_subst"`' old_archive_from_expsyms_cmds='`$ECHO "$old_archive_from_expsyms_cmds" | $SED "$delay_single_quote_subst"`' archive_cmds='`$ECHO "$archive_cmds" | $SED "$delay_single_quote_subst"`' archive_expsym_cmds='`$ECHO "$archive_expsym_cmds" | $SED "$delay_single_quote_subst"`' module_cmds='`$ECHO "$module_cmds" | $SED "$delay_single_quote_subst"`' module_expsym_cmds='`$ECHO "$module_expsym_cmds" | $SED "$delay_single_quote_subst"`' with_gnu_ld='`$ECHO "$with_gnu_ld" | $SED "$delay_single_quote_subst"`' allow_undefined_flag='`$ECHO "$allow_undefined_flag" | $SED "$delay_single_quote_subst"`' no_undefined_flag='`$ECHO "$no_undefined_flag" | $SED "$delay_single_quote_subst"`' hardcode_libdir_flag_spec='`$ECHO "$hardcode_libdir_flag_spec" | $SED "$delay_single_quote_subst"`' hardcode_libdir_separator='`$ECHO "$hardcode_libdir_separator" | $SED "$delay_single_quote_subst"`' hardcode_direct='`$ECHO "$hardcode_direct" | $SED "$delay_single_quote_subst"`' hardcode_direct_absolute='`$ECHO "$hardcode_direct_absolute" | $SED "$delay_single_quote_subst"`' hardcode_minus_L='`$ECHO "$hardcode_minus_L" | $SED "$delay_single_quote_subst"`' hardcode_shlibpath_var='`$ECHO "$hardcode_shlibpath_var" | $SED "$delay_single_quote_subst"`' hardcode_automatic='`$ECHO "$hardcode_automatic" | $SED "$delay_single_quote_subst"`' inherit_rpath='`$ECHO "$inherit_rpath" | $SED "$delay_single_quote_subst"`' link_all_deplibs='`$ECHO "$link_all_deplibs" | $SED "$delay_single_quote_subst"`' always_export_symbols='`$ECHO "$always_export_symbols" | $SED "$delay_single_quote_subst"`' export_symbols_cmds='`$ECHO "$export_symbols_cmds" | $SED "$delay_single_quote_subst"`' exclude_expsyms='`$ECHO "$exclude_expsyms" | $SED "$delay_single_quote_subst"`' include_expsyms='`$ECHO "$include_expsyms" | $SED "$delay_single_quote_subst"`' prelink_cmds='`$ECHO "$prelink_cmds" | $SED "$delay_single_quote_subst"`' postlink_cmds='`$ECHO "$postlink_cmds" | $SED "$delay_single_quote_subst"`' file_list_spec='`$ECHO "$file_list_spec" | $SED "$delay_single_quote_subst"`' variables_saved_for_relink='`$ECHO "$variables_saved_for_relink" | $SED "$delay_single_quote_subst"`' need_lib_prefix='`$ECHO "$need_lib_prefix" | $SED "$delay_single_quote_subst"`' need_version='`$ECHO "$need_version" | $SED "$delay_single_quote_subst"`' version_type='`$ECHO "$version_type" | $SED "$delay_single_quote_subst"`' runpath_var='`$ECHO "$runpath_var" | $SED "$delay_single_quote_subst"`' shlibpath_var='`$ECHO "$shlibpath_var" | $SED "$delay_single_quote_subst"`' shlibpath_overrides_runpath='`$ECHO "$shlibpath_overrides_runpath" | $SED "$delay_single_quote_subst"`' libname_spec='`$ECHO "$libname_spec" | $SED "$delay_single_quote_subst"`' library_names_spec='`$ECHO "$library_names_spec" | $SED "$delay_single_quote_subst"`' soname_spec='`$ECHO "$soname_spec" | $SED "$delay_single_quote_subst"`' install_override_mode='`$ECHO "$install_override_mode" | $SED "$delay_single_quote_subst"`' postinstall_cmds='`$ECHO "$postinstall_cmds" | $SED "$delay_single_quote_subst"`' postuninstall_cmds='`$ECHO "$postuninstall_cmds" | $SED "$delay_single_quote_subst"`' finish_cmds='`$ECHO "$finish_cmds" | $SED "$delay_single_quote_subst"`' finish_eval='`$ECHO "$finish_eval" | $SED "$delay_single_quote_subst"`' hardcode_into_libs='`$ECHO "$hardcode_into_libs" | $SED "$delay_single_quote_subst"`' sys_lib_search_path_spec='`$ECHO "$sys_lib_search_path_spec" | $SED "$delay_single_quote_subst"`' sys_lib_dlsearch_path_spec='`$ECHO "$sys_lib_dlsearch_path_spec" | $SED "$delay_single_quote_subst"`' hardcode_action='`$ECHO "$hardcode_action" | $SED "$delay_single_quote_subst"`' enable_dlopen='`$ECHO "$enable_dlopen" | $SED "$delay_single_quote_subst"`' enable_dlopen_self='`$ECHO "$enable_dlopen_self" | $SED "$delay_single_quote_subst"`' enable_dlopen_self_static='`$ECHO "$enable_dlopen_self_static" | $SED "$delay_single_quote_subst"`' old_striplib='`$ECHO "$old_striplib" | $SED "$delay_single_quote_subst"`' striplib='`$ECHO "$striplib" | $SED "$delay_single_quote_subst"`' LTCC='$LTCC' LTCFLAGS='$LTCFLAGS' compiler='$compiler_DEFAULT' # A function that is used when there is no print builtin or printf. func_fallback_echo () { eval 'cat <<_LTECHO_EOF \$1 _LTECHO_EOF' } # Quote evaled strings. for var in SHELL \ ECHO \ PATH_SEPARATOR \ SED \ GREP \ EGREP \ FGREP \ LD \ NM \ LN_S \ lt_SP2NL \ lt_NL2SP \ reload_flag \ OBJDUMP \ deplibs_check_method \ file_magic_cmd \ file_magic_glob \ want_nocaseglob \ DLLTOOL \ sharedlib_from_linklib_cmd \ AR \ AR_FLAGS \ archiver_list_spec \ STRIP \ RANLIB \ CC \ CFLAGS \ compiler \ lt_cv_sys_global_symbol_pipe \ lt_cv_sys_global_symbol_to_cdecl \ lt_cv_sys_global_symbol_to_c_name_address \ lt_cv_sys_global_symbol_to_c_name_address_lib_prefix \ nm_file_list_spec \ lt_prog_compiler_no_builtin_flag \ lt_prog_compiler_pic \ lt_prog_compiler_wl \ lt_prog_compiler_static \ lt_cv_prog_compiler_c_o \ need_locks \ MANIFEST_TOOL \ DSYMUTIL \ NMEDIT \ LIPO \ OTOOL \ OTOOL64 \ shrext_cmds \ export_dynamic_flag_spec \ whole_archive_flag_spec \ compiler_needs_object \ with_gnu_ld \ allow_undefined_flag \ no_undefined_flag \ hardcode_libdir_flag_spec \ hardcode_libdir_separator \ exclude_expsyms \ include_expsyms \ file_list_spec \ variables_saved_for_relink \ libname_spec \ library_names_spec \ soname_spec \ install_override_mode \ finish_eval \ old_striplib \ striplib; do case \`eval \\\\\$ECHO \\\\""\\\\\$\$var"\\\\"\` in *[\\\\\\\`\\"\\\$]*) eval "lt_\$var=\\\\\\"\\\`\\\$ECHO \\"\\\$\$var\\" | \\\$SED \\"\\\$sed_quote_subst\\"\\\`\\\\\\"" ;; *) eval "lt_\$var=\\\\\\"\\\$\$var\\\\\\"" ;; esac done # Double-quote double-evaled strings. for var in reload_cmds \ old_postinstall_cmds \ old_postuninstall_cmds \ old_archive_cmds \ extract_expsyms_cmds \ old_archive_from_new_cmds \ old_archive_from_expsyms_cmds \ archive_cmds \ archive_expsym_cmds \ module_cmds \ module_expsym_cmds \ export_symbols_cmds \ prelink_cmds \ postlink_cmds \ postinstall_cmds \ postuninstall_cmds \ finish_cmds \ sys_lib_search_path_spec \ sys_lib_dlsearch_path_spec; do case \`eval \\\\\$ECHO \\\\""\\\\\$\$var"\\\\"\` in *[\\\\\\\`\\"\\\$]*) eval "lt_\$var=\\\\\\"\\\`\\\$ECHO \\"\\\$\$var\\" | \\\$SED -e \\"\\\$double_quote_subst\\" -e \\"\\\$sed_quote_subst\\" -e \\"\\\$delay_variable_subst\\"\\\`\\\\\\"" ;; *) eval "lt_\$var=\\\\\\"\\\$\$var\\\\\\"" ;; esac done ac_aux_dir='$ac_aux_dir' xsi_shell='$xsi_shell' lt_shell_append='$lt_shell_append' # See if we are running on zsh, and set the options which allow our # commands through without removal of \ escapes INIT. if test -n "\${ZSH_VERSION+set}" ; then setopt NO_GLOB_SUBST fi PACKAGE='$PACKAGE' VERSION='$VERSION' TIMESTAMP='$TIMESTAMP' RM='$RM' ofile='$ofile' TARGETDIR="$TARGETDIR" _ACEOF cat >>$CONFIG_STATUS <<\_ACEOF || ac_write_fail=1 # Handling of arguments. for ac_config_target in $ac_config_targets do case $ac_config_target in "fficonfig.h") CONFIG_HEADERS="$CONFIG_HEADERS fficonfig.h" ;; "depfiles") CONFIG_COMMANDS="$CONFIG_COMMANDS depfiles" ;; "libtool") CONFIG_COMMANDS="$CONFIG_COMMANDS libtool" ;; "include") CONFIG_COMMANDS="$CONFIG_COMMANDS include" ;; "src") CONFIG_COMMANDS="$CONFIG_COMMANDS src" ;; "include/ffitarget.h") CONFIG_LINKS="$CONFIG_LINKS include/ffitarget.h:src/$TARGETDIR/ffitarget.h" ;; "include/Makefile") CONFIG_FILES="$CONFIG_FILES include/Makefile" ;; "include/ffi.h") CONFIG_FILES="$CONFIG_FILES include/ffi.h" ;; "Makefile") CONFIG_FILES="$CONFIG_FILES Makefile" ;; *) as_fn_error $? "invalid argument: \`$ac_config_target'" "$LINENO" 5;; esac done # If the user did not use the arguments to specify the items to instantiate, # then the envvar interface is used. Set only those that are not. # We use the long form for the default assignment because of an extremely # bizarre bug on SunOS 4.1.3. if $ac_need_defaults; then test "${CONFIG_FILES+set}" = set || CONFIG_FILES=$config_files test "${CONFIG_HEADERS+set}" = set || CONFIG_HEADERS=$config_headers test "${CONFIG_LINKS+set}" = set || CONFIG_LINKS=$config_links test "${CONFIG_COMMANDS+set}" = set || CONFIG_COMMANDS=$config_commands fi # Have a temporary directory for convenience. Make it in the build tree # simply because there is no reason against having it here, and in addition, # creating and moving files from /tmp can sometimes cause problems. # Hook for its removal unless debugging. # Note that there is a small window in which the directory will not be cleaned: # after its creation but before its name has been assigned to `$tmp'. $debug || { tmp= ac_tmp= trap 'exit_status=$? : "${ac_tmp:=$tmp}" { test ! -d "$ac_tmp" || rm -fr "$ac_tmp"; } && exit $exit_status ' 0 trap 'as_fn_exit 1' 1 2 13 15 } # Create a (secure) tmp directory for tmp files. { tmp=`(umask 077 && mktemp -d "./confXXXXXX") 2>/dev/null` && test -d "$tmp" } || { tmp=./conf$$-$RANDOM (umask 077 && mkdir "$tmp") } || as_fn_error $? "cannot create a temporary directory in ." "$LINENO" 5 ac_tmp=$tmp # Set up the scripts for CONFIG_FILES section. # No need to generate them if there are no CONFIG_FILES. # This happens for instance with `./config.status config.h'. if test -n "$CONFIG_FILES"; then ac_cr=`echo X | tr X '\015'` # On cygwin, bash can eat \r inside `` if the user requested igncr. # But we know of no other shell where ac_cr would be empty at this # point, so we can use a bashism as a fallback. if test "x$ac_cr" = x; then eval ac_cr=\$\'\\r\' fi ac_cs_awk_cr=`$AWK 'BEGIN { print "a\rb" }' /dev/null` if test "$ac_cs_awk_cr" = "a${ac_cr}b"; then ac_cs_awk_cr='\\r' else ac_cs_awk_cr=$ac_cr fi echo 'BEGIN {' >"$ac_tmp/subs1.awk" && _ACEOF { echo "cat >conf$$subs.awk <<_ACEOF" && echo "$ac_subst_vars" | sed 's/.*/&!$&$ac_delim/' && echo "_ACEOF" } >conf$$subs.sh || as_fn_error $? "could not make $CONFIG_STATUS" "$LINENO" 5 ac_delim_num=`echo "$ac_subst_vars" | grep -c '^'` ac_delim='%!_!# ' for ac_last_try in false false false false false :; do . ./conf$$subs.sh || as_fn_error $? "could not make $CONFIG_STATUS" "$LINENO" 5 ac_delim_n=`sed -n "s/.*$ac_delim\$/X/p" conf$$subs.awk | grep -c X` if test $ac_delim_n = $ac_delim_num; then break elif $ac_last_try; then as_fn_error $? "could not make $CONFIG_STATUS" "$LINENO" 5 else ac_delim="$ac_delim!$ac_delim _$ac_delim!! " fi done rm -f conf$$subs.sh cat >>$CONFIG_STATUS <<_ACEOF || ac_write_fail=1 cat >>"\$ac_tmp/subs1.awk" <<\\_ACAWK && _ACEOF sed -n ' h s/^/S["/; s/!.*/"]=/ p g s/^[^!]*!// :repl t repl s/'"$ac_delim"'$// t delim :nl h s/\(.\{148\}\)..*/\1/ t more1 s/["\\]/\\&/g; s/^/"/; s/$/\\n"\\/ p n b repl :more1 s/["\\]/\\&/g; s/^/"/; s/$/"\\/ p g s/.\{148\}// t nl :delim h s/\(.\{148\}\)..*/\1/ t more2 s/["\\]/\\&/g; s/^/"/; s/$/"/ p b :more2 s/["\\]/\\&/g; s/^/"/; s/$/"\\/ p g s/.\{148\}// t delim ' >$CONFIG_STATUS || ac_write_fail=1 rm -f conf$$subs.awk cat >>$CONFIG_STATUS <<_ACEOF || ac_write_fail=1 _ACAWK cat >>"\$ac_tmp/subs1.awk" <<_ACAWK && for (key in S) S_is_set[key] = 1 FS = "" } { line = $ 0 nfields = split(line, field, "@") substed = 0 len = length(field[1]) for (i = 2; i < nfields; i++) { key = field[i] keylen = length(key) if (S_is_set[key]) { value = S[key] line = substr(line, 1, len) "" value "" substr(line, len + keylen + 3) len += length(value) + length(field[++i]) substed = 1 } else len += 1 + keylen } print line } _ACAWK _ACEOF cat >>$CONFIG_STATUS <<\_ACEOF || ac_write_fail=1 if sed "s/$ac_cr//" < /dev/null > /dev/null 2>&1; then sed "s/$ac_cr\$//; s/$ac_cr/$ac_cs_awk_cr/g" else cat fi < "$ac_tmp/subs1.awk" > "$ac_tmp/subs.awk" \ || as_fn_error $? "could not setup config files machinery" "$LINENO" 5 _ACEOF # VPATH may cause trouble with some makes, so we remove sole $(srcdir), # ${srcdir} and @srcdir@ entries from VPATH if srcdir is ".", strip leading and # trailing colons and then remove the whole line if VPATH becomes empty # (actually we leave an empty line to preserve line numbers). if test "x$srcdir" = x.; then ac_vpsub='/^[ ]*VPATH[ ]*=[ ]*/{ h s/// s/^/:/ s/[ ]*$/:/ s/:\$(srcdir):/:/g s/:\${srcdir}:/:/g s/:@srcdir@:/:/g s/^:*// s/:*$// x s/\(=[ ]*\).*/\1/ G s/\n// s/^[^=]*=[ ]*$// }' fi cat >>$CONFIG_STATUS <<\_ACEOF || ac_write_fail=1 fi # test -n "$CONFIG_FILES" # Set up the scripts for CONFIG_HEADERS section. # No need to generate them if there are no CONFIG_HEADERS. # This happens for instance with `./config.status Makefile'. if test -n "$CONFIG_HEADERS"; then cat >"$ac_tmp/defines.awk" <<\_ACAWK || BEGIN { _ACEOF # Transform confdefs.h into an awk script `defines.awk', embedded as # here-document in config.status, that substitutes the proper values into # config.h.in to produce config.h. # Create a delimiter string that does not exist in confdefs.h, to ease # handling of long lines. ac_delim='%!_!# ' for ac_last_try in false false :; do ac_tt=`sed -n "/$ac_delim/p" confdefs.h` if test -z "$ac_tt"; then break elif $ac_last_try; then as_fn_error $? "could not make $CONFIG_HEADERS" "$LINENO" 5 else ac_delim="$ac_delim!$ac_delim _$ac_delim!! " fi done # For the awk script, D is an array of macro values keyed by name, # likewise P contains macro parameters if any. Preserve backslash # newline sequences. ac_word_re=[_$as_cr_Letters][_$as_cr_alnum]* sed -n ' s/.\{148\}/&'"$ac_delim"'/g t rset :rset s/^[ ]*#[ ]*define[ ][ ]*/ / t def d :def s/\\$// t bsnl s/["\\]/\\&/g s/^ \('"$ac_word_re"'\)\(([^()]*)\)[ ]*\(.*\)/P["\1"]="\2"\ D["\1"]=" \3"/p s/^ \('"$ac_word_re"'\)[ ]*\(.*\)/D["\1"]=" \2"/p d :bsnl s/["\\]/\\&/g s/^ \('"$ac_word_re"'\)\(([^()]*)\)[ ]*\(.*\)/P["\1"]="\2"\ D["\1"]=" \3\\\\\\n"\\/p t cont s/^ \('"$ac_word_re"'\)[ ]*\(.*\)/D["\1"]=" \2\\\\\\n"\\/p t cont d :cont n s/.\{148\}/&'"$ac_delim"'/g t clear :clear s/\\$// t bsnlc s/["\\]/\\&/g; s/^/"/; s/$/"/p d :bsnlc s/["\\]/\\&/g; s/^/"/; s/$/\\\\\\n"\\/p b cont ' >$CONFIG_STATUS || ac_write_fail=1 cat >>$CONFIG_STATUS <<_ACEOF || ac_write_fail=1 for (key in D) D_is_set[key] = 1 FS = "" } /^[\t ]*#[\t ]*(define|undef)[\t ]+$ac_word_re([\t (]|\$)/ { line = \$ 0 split(line, arg, " ") if (arg[1] == "#") { defundef = arg[2] mac1 = arg[3] } else { defundef = substr(arg[1], 2) mac1 = arg[2] } split(mac1, mac2, "(") #) macro = mac2[1] prefix = substr(line, 1, index(line, defundef) - 1) if (D_is_set[macro]) { # Preserve the white space surrounding the "#". print prefix "define", macro P[macro] D[macro] next } else { # Replace #undef with comments. This is necessary, for example, # in the case of _POSIX_SOURCE, which is predefined and required # on some systems where configure will not decide to define it. if (defundef == "undef") { print "/*", prefix defundef, macro, "*/" next } } } { print } _ACAWK _ACEOF cat >>$CONFIG_STATUS <<\_ACEOF || ac_write_fail=1 as_fn_error $? "could not setup config headers machinery" "$LINENO" 5 fi # test -n "$CONFIG_HEADERS" eval set X " :F $CONFIG_FILES :H $CONFIG_HEADERS :L $CONFIG_LINKS :C $CONFIG_COMMANDS" shift for ac_tag do case $ac_tag in :[FHLC]) ac_mode=$ac_tag; continue;; esac case $ac_mode$ac_tag in :[FHL]*:*);; :L* | :C*:*) as_fn_error $? "invalid tag \`$ac_tag'" "$LINENO" 5;; :[FH]-) ac_tag=-:-;; :[FH]*) ac_tag=$ac_tag:$ac_tag.in;; esac ac_save_IFS=$IFS IFS=: set x $ac_tag IFS=$ac_save_IFS shift ac_file=$1 shift case $ac_mode in :L) ac_source=$1;; :[FH]) ac_file_inputs= for ac_f do case $ac_f in -) ac_f="$ac_tmp/stdin";; *) # Look for the file first in the build tree, then in the source tree # (if the path is not absolute). The absolute path cannot be DOS-style, # because $ac_f cannot contain `:'. test -f "$ac_f" || case $ac_f in [\\/$]*) false;; *) test -f "$srcdir/$ac_f" && ac_f="$srcdir/$ac_f";; esac || as_fn_error 1 "cannot find input file: \`$ac_f'" "$LINENO" 5;; esac case $ac_f in *\'*) ac_f=`$as_echo "$ac_f" | sed "s/'/'\\\\\\\\''/g"`;; esac as_fn_append ac_file_inputs " '$ac_f'" done # Let's still pretend it is `configure' which instantiates (i.e., don't # use $as_me), people would be surprised to read: # /* config.h. Generated by config.status. */ configure_input='Generated from '` $as_echo "$*" | sed 's|^[^:]*/||;s|:[^:]*/|, |g' `' by configure.' if test x"$ac_file" != x-; then configure_input="$ac_file. $configure_input" { $as_echo "$as_me:${as_lineno-$LINENO}: creating $ac_file" >&5 $as_echo "$as_me: creating $ac_file" >&6;} fi # Neutralize special characters interpreted by sed in replacement strings. case $configure_input in #( *\&* | *\|* | *\\* ) ac_sed_conf_input=`$as_echo "$configure_input" | sed 's/[\\\\&|]/\\\\&/g'`;; #( *) ac_sed_conf_input=$configure_input;; esac case $ac_tag in *:-:* | *:-) cat >"$ac_tmp/stdin" \ || as_fn_error $? "could not create $ac_file" "$LINENO" 5 ;; esac ;; esac ac_dir=`$as_dirname -- "$ac_file" || $as_expr X"$ac_file" : 'X\(.*[^/]\)//*[^/][^/]*/*$' \| \ X"$ac_file" : 'X\(//\)[^/]' \| \ X"$ac_file" : 'X\(//\)$' \| \ X"$ac_file" : 'X\(/\)' \| . 2>/dev/null || $as_echo X"$ac_file" | sed '/^X\(.*[^/]\)\/\/*[^/][^/]*\/*$/{ s//\1/ q } /^X\(\/\/\)[^/].*/{ s//\1/ q } /^X\(\/\/\)$/{ s//\1/ q } /^X\(\/\).*/{ s//\1/ q } s/.*/./; q'` as_dir="$ac_dir"; as_fn_mkdir_p ac_builddir=. case "$ac_dir" in .) ac_dir_suffix= ac_top_builddir_sub=. ac_top_build_prefix= ;; *) ac_dir_suffix=/`$as_echo "$ac_dir" | sed 's|^\.[\\/]||'` # A ".." for each directory in $ac_dir_suffix. ac_top_builddir_sub=`$as_echo "$ac_dir_suffix" | sed 's|/[^\\/]*|/..|g;s|/||'` case $ac_top_builddir_sub in "") ac_top_builddir_sub=. ac_top_build_prefix= ;; *) ac_top_build_prefix=$ac_top_builddir_sub/ ;; esac ;; esac ac_abs_top_builddir=$ac_pwd ac_abs_builddir=$ac_pwd$ac_dir_suffix # for backward compatibility: ac_top_builddir=$ac_top_build_prefix case $srcdir in .) # We are building in place. ac_srcdir=. ac_top_srcdir=$ac_top_builddir_sub ac_abs_top_srcdir=$ac_pwd ;; [\\/]* | ?:[\\/]* ) # Absolute name. ac_srcdir=$srcdir$ac_dir_suffix; ac_top_srcdir=$srcdir ac_abs_top_srcdir=$srcdir ;; *) # Relative name. ac_srcdir=$ac_top_build_prefix$srcdir$ac_dir_suffix ac_top_srcdir=$ac_top_build_prefix$srcdir ac_abs_top_srcdir=$ac_pwd/$srcdir ;; esac ac_abs_srcdir=$ac_abs_top_srcdir$ac_dir_suffix case $ac_mode in :F) # # CONFIG_FILE # case $INSTALL in [\\/$]* | ?:[\\/]* ) ac_INSTALL=$INSTALL ;; *) ac_INSTALL=$ac_top_build_prefix$INSTALL ;; esac ac_MKDIR_P=$MKDIR_P case $MKDIR_P in [\\/$]* | ?:[\\/]* ) ;; */*) ac_MKDIR_P=$ac_top_build_prefix$MKDIR_P ;; esac _ACEOF cat >>$CONFIG_STATUS <<\_ACEOF || ac_write_fail=1 # If the template does not know about datarootdir, expand it. # FIXME: This hack should be removed a few years after 2.60. ac_datarootdir_hack=; ac_datarootdir_seen= ac_sed_dataroot=' /datarootdir/ { p q } /@datadir@/p /@docdir@/p /@infodir@/p /@localedir@/p /@mandir@/p' case `eval "sed -n \"\$ac_sed_dataroot\" $ac_file_inputs"` in *datarootdir*) ac_datarootdir_seen=yes;; *@datadir@*|*@docdir@*|*@infodir@*|*@localedir@*|*@mandir@*) { $as_echo "$as_me:${as_lineno-$LINENO}: WARNING: $ac_file_inputs seems to ignore the --datarootdir setting" >&5 $as_echo "$as_me: WARNING: $ac_file_inputs seems to ignore the --datarootdir setting" >&2;} _ACEOF cat >>$CONFIG_STATUS <<_ACEOF || ac_write_fail=1 ac_datarootdir_hack=' s&@datadir@&$datadir&g s&@docdir@&$docdir&g s&@infodir@&$infodir&g s&@localedir@&$localedir&g s&@mandir@&$mandir&g s&\\\${datarootdir}&$datarootdir&g' ;; esac _ACEOF # Neutralize VPATH when `$srcdir' = `.'. # Shell code in configure.ac might set extrasub. # FIXME: do we really want to maintain this feature? cat >>$CONFIG_STATUS <<_ACEOF || ac_write_fail=1 ac_sed_extra="$ac_vpsub $extrasub _ACEOF cat >>$CONFIG_STATUS <<\_ACEOF || ac_write_fail=1 :t /@[a-zA-Z_][a-zA-Z_0-9]*@/!b s|@configure_input@|$ac_sed_conf_input|;t t s&@top_builddir@&$ac_top_builddir_sub&;t t s&@top_build_prefix@&$ac_top_build_prefix&;t t s&@srcdir@&$ac_srcdir&;t t s&@abs_srcdir@&$ac_abs_srcdir&;t t s&@top_srcdir@&$ac_top_srcdir&;t t s&@abs_top_srcdir@&$ac_abs_top_srcdir&;t t s&@builddir@&$ac_builddir&;t t s&@abs_builddir@&$ac_abs_builddir&;t t s&@abs_top_builddir@&$ac_abs_top_builddir&;t t s&@INSTALL@&$ac_INSTALL&;t t s&@MKDIR_P@&$ac_MKDIR_P&;t t $ac_datarootdir_hack " eval sed \"\$ac_sed_extra\" "$ac_file_inputs" | $AWK -f "$ac_tmp/subs.awk" \ >$ac_tmp/out || as_fn_error $? "could not create $ac_file" "$LINENO" 5 test -z "$ac_datarootdir_hack$ac_datarootdir_seen" && { ac_out=`sed -n '/\${datarootdir}/p' "$ac_tmp/out"`; test -n "$ac_out"; } && { ac_out=`sed -n '/^[ ]*datarootdir[ ]*:*=/p' \ "$ac_tmp/out"`; test -z "$ac_out"; } && { $as_echo "$as_me:${as_lineno-$LINENO}: WARNING: $ac_file contains a reference to the variable \`datarootdir' which seems to be undefined. Please make sure it is defined" >&5 $as_echo "$as_me: WARNING: $ac_file contains a reference to the variable \`datarootdir' which seems to be undefined. Please make sure it is defined" >&2;} rm -f "$ac_tmp/stdin" case $ac_file in -) cat "$ac_tmp/out" && rm -f "$ac_tmp/out";; *) rm -f "$ac_file" && mv "$ac_tmp/out" "$ac_file";; esac \ || as_fn_error $? "could not create $ac_file" "$LINENO" 5 ;; :H) # # CONFIG_HEADER # if test x"$ac_file" != x-; then { $as_echo "/* $configure_input */" \ && eval '$AWK -f "$ac_tmp/defines.awk"' "$ac_file_inputs" } >"$ac_tmp/config.h" \ || as_fn_error $? "could not create $ac_file" "$LINENO" 5 if diff "$ac_file" "$ac_tmp/config.h" >/dev/null 2>&1; then { $as_echo "$as_me:${as_lineno-$LINENO}: $ac_file is unchanged" >&5 $as_echo "$as_me: $ac_file is unchanged" >&6;} else rm -f "$ac_file" mv "$ac_tmp/config.h" "$ac_file" \ || as_fn_error $? "could not create $ac_file" "$LINENO" 5 fi else $as_echo "/* $configure_input */" \ && eval '$AWK -f "$ac_tmp/defines.awk"' "$ac_file_inputs" \ || as_fn_error $? "could not create -" "$LINENO" 5 fi # Compute "$ac_file"'s index in $config_headers. _am_arg="$ac_file" _am_stamp_count=1 for _am_header in $config_headers :; do case $_am_header in $_am_arg | $_am_arg:* ) break ;; * ) _am_stamp_count=`expr $_am_stamp_count + 1` ;; esac done echo "timestamp for $_am_arg" >`$as_dirname -- "$_am_arg" || $as_expr X"$_am_arg" : 'X\(.*[^/]\)//*[^/][^/]*/*$' \| \ X"$_am_arg" : 'X\(//\)[^/]' \| \ X"$_am_arg" : 'X\(//\)$' \| \ X"$_am_arg" : 'X\(/\)' \| . 2>/dev/null || $as_echo X"$_am_arg" | sed '/^X\(.*[^/]\)\/\/*[^/][^/]*\/*$/{ s//\1/ q } /^X\(\/\/\)[^/].*/{ s//\1/ q } /^X\(\/\/\)$/{ s//\1/ q } /^X\(\/\).*/{ s//\1/ q } s/.*/./; q'`/stamp-h$_am_stamp_count ;; :L) # # CONFIG_LINK # if test "$ac_source" = "$ac_file" && test "$srcdir" = '.'; then : else # Prefer the file from the source tree if names are identical. if test "$ac_source" = "$ac_file" || test ! -r "$ac_source"; then ac_source=$srcdir/$ac_source fi { $as_echo "$as_me:${as_lineno-$LINENO}: linking $ac_source to $ac_file" >&5 $as_echo "$as_me: linking $ac_source to $ac_file" >&6;} if test ! -r "$ac_source"; then as_fn_error $? "$ac_source: file not found" "$LINENO" 5 fi rm -f "$ac_file" # Try a relative symlink, then a hard link, then a copy. case $ac_source in [\\/$]* | ?:[\\/]* ) ac_rel_source=$ac_source ;; *) ac_rel_source=$ac_top_build_prefix$ac_source ;; esac ln -s "$ac_rel_source" "$ac_file" 2>/dev/null || ln "$ac_source" "$ac_file" 2>/dev/null || cp -p "$ac_source" "$ac_file" || as_fn_error $? "cannot link or copy $ac_source to $ac_file" "$LINENO" 5 fi ;; :C) { $as_echo "$as_me:${as_lineno-$LINENO}: executing $ac_file commands" >&5 $as_echo "$as_me: executing $ac_file commands" >&6;} ;; esac case $ac_file$ac_mode in "depfiles":C) test x"$AMDEP_TRUE" != x"" || { # Autoconf 2.62 quotes --file arguments for eval, but not when files # are listed without --file. Let's play safe and only enable the eval # if we detect the quoting. case $CONFIG_FILES in *\'*) eval set x "$CONFIG_FILES" ;; *) set x $CONFIG_FILES ;; esac shift for mf do # Strip MF so we end up with the name of the file. mf=`echo "$mf" | sed -e 's/:.*$//'` # Check whether this is an Automake generated Makefile or not. # We used to match only the files named `Makefile.in', but # some people rename them; so instead we look at the file content. # Grep'ing the first line is not enough: some people post-process # each Makefile.in and add a new line on top of each file to say so. # Grep'ing the whole file is not good either: AIX grep has a line # limit of 2048, but all sed's we know have understand at least 4000. if sed -n 's,^#.*generated by automake.*,X,p' "$mf" | grep X >/dev/null 2>&1; then dirpart=`$as_dirname -- "$mf" || $as_expr X"$mf" : 'X\(.*[^/]\)//*[^/][^/]*/*$' \| \ X"$mf" : 'X\(//\)[^/]' \| \ X"$mf" : 'X\(//\)$' \| \ X"$mf" : 'X\(/\)' \| . 2>/dev/null || $as_echo X"$mf" | sed '/^X\(.*[^/]\)\/\/*[^/][^/]*\/*$/{ s//\1/ q } /^X\(\/\/\)[^/].*/{ s//\1/ q } /^X\(\/\/\)$/{ s//\1/ q } /^X\(\/\).*/{ s//\1/ q } s/.*/./; q'` else continue fi # Extract the definition of DEPDIR, am__include, and am__quote # from the Makefile without running `make'. DEPDIR=`sed -n 's/^DEPDIR = //p' < "$mf"` test -z "$DEPDIR" && continue am__include=`sed -n 's/^am__include = //p' < "$mf"` test -z "am__include" && continue am__quote=`sed -n 's/^am__quote = //p' < "$mf"` # When using ansi2knr, U may be empty or an underscore; expand it U=`sed -n 's/^U = //p' < "$mf"` # Find all dependency output files, they are included files with # $(DEPDIR) in their names. We invoke sed twice because it is the # simplest approach to changing $(DEPDIR) to its actual value in the # expansion. for file in `sed -n " s/^$am__include $am__quote\(.*(DEPDIR).*\)$am__quote"'$/\1/p' <"$mf" | \ sed -e 's/\$(DEPDIR)/'"$DEPDIR"'/g' -e 's/\$U/'"$U"'/g'`; do # Make sure the directory exists. test -f "$dirpart/$file" && continue fdir=`$as_dirname -- "$file" || $as_expr X"$file" : 'X\(.*[^/]\)//*[^/][^/]*/*$' \| \ X"$file" : 'X\(//\)[^/]' \| \ X"$file" : 'X\(//\)$' \| \ X"$file" : 'X\(/\)' \| . 2>/dev/null || $as_echo X"$file" | sed '/^X\(.*[^/]\)\/\/*[^/][^/]*\/*$/{ s//\1/ q } /^X\(\/\/\)[^/].*/{ s//\1/ q } /^X\(\/\/\)$/{ s//\1/ q } /^X\(\/\).*/{ s//\1/ q } s/.*/./; q'` as_dir=$dirpart/$fdir; as_fn_mkdir_p # echo "creating $dirpart/$file" echo '# dummy' > "$dirpart/$file" done done } ;; "libtool":C) # See if we are running on zsh, and set the options which allow our # commands through without removal of \ escapes. if test -n "${ZSH_VERSION+set}" ; then setopt NO_GLOB_SUBST fi cfgfile="${ofile}T" trap "$RM \"$cfgfile\"; exit 1" 1 2 15 $RM "$cfgfile" cat <<_LT_EOF >> "$cfgfile" #! $SHELL # `$ECHO "$ofile" | sed 's%^.*/%%'` - Provide generalized library-building support services. # Generated automatically by $as_me ($PACKAGE$TIMESTAMP) $VERSION # Libtool was configured on host `(hostname || uname -n) 2>/dev/null | sed 1q`: # NOTE: Changes made to this file will be lost: look at ltmain.sh. # # Copyright (C) 1996, 1997, 1998, 1999, 2000, 2001, 2003, 2004, 2005, # 2006, 2007, 2008, 2009, 2010, 2011 Free Software # Foundation, Inc. # Written by Gordon Matzigkeit, 1996 # # This file is part of GNU Libtool. # # GNU Libtool is free software; you can redistribute it and/or # modify it under the terms of the GNU General Public License as # published by the Free Software Foundation; either version 2 of # the License, or (at your option) any later version. # # As a special exception to the GNU General Public License, # if you distribute this file as part of a program or library that # is built using GNU Libtool, you may include this file under the # same distribution terms that you use for the rest of that program. # # GNU Libtool is distributed in the hope that it will be useful, # but WITHOUT ANY WARRANTY; without even the implied warranty of # MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the # GNU General Public License for more details. # # You should have received a copy of the GNU General Public License # along with GNU Libtool; see the file COPYING. If not, a copy # can be downloaded from http://www.gnu.org/licenses/gpl.html, or # obtained by writing to the Free Software Foundation, Inc., # 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. # The names of the tagged configurations supported by this script. available_tags="" # ### BEGIN LIBTOOL CONFIG # Which release of libtool.m4 was used? macro_version=$macro_version macro_revision=$macro_revision # Whether or not to build shared libraries. build_libtool_libs=$enable_shared # Whether or not to build static libraries. build_old_libs=$enable_static # What type of objects to build. pic_mode=$pic_mode # Whether or not to optimize for fast installation. fast_install=$enable_fast_install # Shell to use when invoking shell scripts. SHELL=$lt_SHELL # An echo program that protects backslashes. ECHO=$lt_ECHO # The PATH separator for the build system. PATH_SEPARATOR=$lt_PATH_SEPARATOR # The host system. host_alias=$host_alias host=$host host_os=$host_os # The build system. build_alias=$build_alias build=$build build_os=$build_os # A sed program that does not truncate output. SED=$lt_SED # Sed that helps us avoid accidentally triggering echo(1) options like -n. Xsed="\$SED -e 1s/^X//" # A grep program that handles long lines. GREP=$lt_GREP # An ERE matcher. EGREP=$lt_EGREP # A literal string matcher. FGREP=$lt_FGREP # A BSD- or MS-compatible name lister. NM=$lt_NM # Whether we need soft or hard links. LN_S=$lt_LN_S # What is the maximum length of a command? max_cmd_len=$max_cmd_len # Object file suffix (normally "o"). objext=$ac_objext # Executable file suffix (normally ""). exeext=$exeext # whether the shell understands "unset". lt_unset=$lt_unset # turn spaces into newlines. SP2NL=$lt_lt_SP2NL # turn newlines into spaces. NL2SP=$lt_lt_NL2SP # convert \$build file names to \$host format. to_host_file_cmd=$lt_cv_to_host_file_cmd # convert \$build files to toolchain format. to_tool_file_cmd=$lt_cv_to_tool_file_cmd # An object symbol dumper. OBJDUMP=$lt_OBJDUMP # Method to check whether dependent libraries are shared objects. deplibs_check_method=$lt_deplibs_check_method # Command to use when deplibs_check_method = "file_magic". file_magic_cmd=$lt_file_magic_cmd # How to find potential files when deplibs_check_method = "file_magic". file_magic_glob=$lt_file_magic_glob # Find potential files using nocaseglob when deplibs_check_method = "file_magic". want_nocaseglob=$lt_want_nocaseglob # DLL creation program. DLLTOOL=$lt_DLLTOOL # Command to associate shared and link libraries. sharedlib_from_linklib_cmd=$lt_sharedlib_from_linklib_cmd # The archiver. AR=$lt_AR # Flags to create an archive. AR_FLAGS=$lt_AR_FLAGS # How to feed a file listing to the archiver. archiver_list_spec=$lt_archiver_list_spec # A symbol stripping program. STRIP=$lt_STRIP # Commands used to install an old-style archive. RANLIB=$lt_RANLIB old_postinstall_cmds=$lt_old_postinstall_cmds old_postuninstall_cmds=$lt_old_postuninstall_cmds # Whether to use a lock for old archive extraction. lock_old_archive_extraction=$lock_old_archive_extraction # A C compiler. LTCC=$lt_CC # LTCC compiler flags. LTCFLAGS=$lt_CFLAGS # Take the output of nm and produce a listing of raw symbols and C names. global_symbol_pipe=$lt_lt_cv_sys_global_symbol_pipe # Transform the output of nm in a proper C declaration. global_symbol_to_cdecl=$lt_lt_cv_sys_global_symbol_to_cdecl # Transform the output of nm in a C name address pair. global_symbol_to_c_name_address=$lt_lt_cv_sys_global_symbol_to_c_name_address # Transform the output of nm in a C name address pair when lib prefix is needed. global_symbol_to_c_name_address_lib_prefix=$lt_lt_cv_sys_global_symbol_to_c_name_address_lib_prefix # Specify filename containing input files for \$NM. nm_file_list_spec=$lt_nm_file_list_spec # The root where to search for dependent libraries,and in which our libraries should be installed. lt_sysroot=$lt_sysroot # The name of the directory that contains temporary libtool files. objdir=$objdir # Used to examine libraries when file_magic_cmd begins with "file". MAGIC_CMD=$MAGIC_CMD # Must we lock files when doing compilation? need_locks=$lt_need_locks # Manifest tool. MANIFEST_TOOL=$lt_MANIFEST_TOOL # Tool to manipulate archived DWARF debug symbol files on Mac OS X. DSYMUTIL=$lt_DSYMUTIL # Tool to change global to local symbols on Mac OS X. NMEDIT=$lt_NMEDIT # Tool to manipulate fat objects and archives on Mac OS X. LIPO=$lt_LIPO # ldd/readelf like tool for Mach-O binaries on Mac OS X. OTOOL=$lt_OTOOL # ldd/readelf like tool for 64 bit Mach-O binaries on Mac OS X 10.4. OTOOL64=$lt_OTOOL64 # Old archive suffix (normally "a"). libext=$libext # Shared library suffix (normally ".so"). shrext_cmds=$lt_shrext_cmds # The commands to extract the exported symbol list from a shared archive. extract_expsyms_cmds=$lt_extract_expsyms_cmds # Variables whose values should be saved in libtool wrapper scripts and # restored at link time. variables_saved_for_relink=$lt_variables_saved_for_relink # Do we need the "lib" prefix for modules? need_lib_prefix=$need_lib_prefix # Do we need a version for libraries? need_version=$need_version # Library versioning type. version_type=$version_type # Shared library runtime path variable. runpath_var=$runpath_var # Shared library path variable. shlibpath_var=$shlibpath_var # Is shlibpath searched before the hard-coded library search path? shlibpath_overrides_runpath=$shlibpath_overrides_runpath # Format of library name prefix. libname_spec=$lt_libname_spec # List of archive names. First name is the real one, the rest are links. # The last name is the one that the linker finds with -lNAME library_names_spec=$lt_library_names_spec # The coded name of the library, if different from the real name. soname_spec=$lt_soname_spec # Permission mode override for installation of shared libraries. install_override_mode=$lt_install_override_mode # Command to use after installation of a shared archive. postinstall_cmds=$lt_postinstall_cmds # Command to use after uninstallation of a shared archive. postuninstall_cmds=$lt_postuninstall_cmds # Commands used to finish a libtool library installation in a directory. finish_cmds=$lt_finish_cmds # As "finish_cmds", except a single script fragment to be evaled but # not shown. finish_eval=$lt_finish_eval # Whether we should hardcode library paths into libraries. hardcode_into_libs=$hardcode_into_libs # Compile-time system search path for libraries. sys_lib_search_path_spec=$lt_sys_lib_search_path_spec # Run-time system search path for libraries. sys_lib_dlsearch_path_spec=$lt_sys_lib_dlsearch_path_spec # Whether dlopen is supported. dlopen_support=$enable_dlopen # Whether dlopen of programs is supported. dlopen_self=$enable_dlopen_self # Whether dlopen of statically linked programs is supported. dlopen_self_static=$enable_dlopen_self_static # Commands to strip libraries. old_striplib=$lt_old_striplib striplib=$lt_striplib # The linker used to build libraries. LD=$lt_LD # How to create reloadable object files. reload_flag=$lt_reload_flag reload_cmds=$lt_reload_cmds # Commands used to build an old-style archive. old_archive_cmds=$lt_old_archive_cmds # A language specific compiler. CC=$lt_compiler # Is the compiler the GNU compiler? with_gcc=$GCC # Compiler flag to turn off builtin functions. no_builtin_flag=$lt_lt_prog_compiler_no_builtin_flag # Additional compiler flags for building library objects. pic_flag=$lt_lt_prog_compiler_pic # How to pass a linker flag through the compiler. wl=$lt_lt_prog_compiler_wl # Compiler flag to prevent dynamic linking. link_static_flag=$lt_lt_prog_compiler_static # Does compiler simultaneously support -c and -o options? compiler_c_o=$lt_lt_cv_prog_compiler_c_o # Whether or not to add -lc for building shared libraries. build_libtool_need_lc=$archive_cmds_need_lc # Whether or not to disallow shared libs when runtime libs are static. allow_libtool_libs_with_static_runtimes=$enable_shared_with_static_runtimes # Compiler flag to allow reflexive dlopens. export_dynamic_flag_spec=$lt_export_dynamic_flag_spec # Compiler flag to generate shared objects directly from archives. whole_archive_flag_spec=$lt_whole_archive_flag_spec # Whether the compiler copes with passing no objects directly. compiler_needs_object=$lt_compiler_needs_object # Create an old-style archive from a shared archive. old_archive_from_new_cmds=$lt_old_archive_from_new_cmds # Create a temporary old-style archive to link instead of a shared archive. old_archive_from_expsyms_cmds=$lt_old_archive_from_expsyms_cmds # Commands used to build a shared archive. archive_cmds=$lt_archive_cmds archive_expsym_cmds=$lt_archive_expsym_cmds # Commands used to build a loadable module if different from building # a shared archive. module_cmds=$lt_module_cmds module_expsym_cmds=$lt_module_expsym_cmds # Whether we are building with GNU ld or not. with_gnu_ld=$lt_with_gnu_ld # Flag that allows shared libraries with undefined symbols to be built. allow_undefined_flag=$lt_allow_undefined_flag # Flag that enforces no undefined symbols. no_undefined_flag=$lt_no_undefined_flag # Flag to hardcode \$libdir into a binary during linking. # This must work even if \$libdir does not exist hardcode_libdir_flag_spec=$lt_hardcode_libdir_flag_spec # Whether we need a single "-rpath" flag with a separated argument. hardcode_libdir_separator=$lt_hardcode_libdir_separator # Set to "yes" if using DIR/libNAME\${shared_ext} during linking hardcodes # DIR into the resulting binary. hardcode_direct=$hardcode_direct # Set to "yes" if using DIR/libNAME\${shared_ext} during linking hardcodes # DIR into the resulting binary and the resulting library dependency is # "absolute",i.e impossible to change by setting \${shlibpath_var} if the # library is relocated. hardcode_direct_absolute=$hardcode_direct_absolute # Set to "yes" if using the -LDIR flag during linking hardcodes DIR # into the resulting binary. hardcode_minus_L=$hardcode_minus_L # Set to "yes" if using SHLIBPATH_VAR=DIR during linking hardcodes DIR # into the resulting binary. hardcode_shlibpath_var=$hardcode_shlibpath_var # Set to "yes" if building a shared library automatically hardcodes DIR # into the library and all subsequent libraries and executables linked # against it. hardcode_automatic=$hardcode_automatic # Set to yes if linker adds runtime paths of dependent libraries # to runtime path list. inherit_rpath=$inherit_rpath # Whether libtool must link a program against all its dependency libraries. link_all_deplibs=$link_all_deplibs # Set to "yes" if exported symbols are required. always_export_symbols=$always_export_symbols # The commands to list exported symbols. export_symbols_cmds=$lt_export_symbols_cmds # Symbols that should not be listed in the preloaded symbols. exclude_expsyms=$lt_exclude_expsyms # Symbols that must always be exported. include_expsyms=$lt_include_expsyms # Commands necessary for linking programs (against libraries) with templates. prelink_cmds=$lt_prelink_cmds # Commands necessary for finishing linking programs. postlink_cmds=$lt_postlink_cmds # Specify filename containing input files. file_list_spec=$lt_file_list_spec # How to hardcode a shared library path into an executable. hardcode_action=$hardcode_action # ### END LIBTOOL CONFIG _LT_EOF case $host_os in aix3*) cat <<\_LT_EOF >> "$cfgfile" # AIX sometimes has problems with the GCC collect2 program. For some # reason, if we set the COLLECT_NAMES environment variable, the problems # vanish in a puff of smoke. if test "X${COLLECT_NAMES+set}" != Xset; then COLLECT_NAMES= export COLLECT_NAMES fi _LT_EOF ;; esac ltmain="$ac_aux_dir/ltmain.sh" # We use sed instead of cat because bash on DJGPP gets confused if # if finds mixed CR/LF and LF-only lines. Since sed operates in # text mode, it properly converts lines to CR/LF. This bash problem # is reportedly fixed, but why not run on old versions too? sed '$q' "$ltmain" >> "$cfgfile" \ || (rm -f "$cfgfile"; exit 1) if test x"$xsi_shell" = xyes; then sed -e '/^func_dirname ()$/,/^} # func_dirname /c\ func_dirname ()\ {\ \ case ${1} in\ \ */*) func_dirname_result="${1%/*}${2}" ;;\ \ * ) func_dirname_result="${3}" ;;\ \ esac\ } # Extended-shell func_dirname implementation' "$cfgfile" > $cfgfile.tmp \ && mv -f "$cfgfile.tmp" "$cfgfile" \ || (rm -f "$cfgfile" && cp "$cfgfile.tmp" "$cfgfile" && rm -f "$cfgfile.tmp") test 0 -eq $? || _lt_function_replace_fail=: sed -e '/^func_basename ()$/,/^} # func_basename /c\ func_basename ()\ {\ \ func_basename_result="${1##*/}"\ } # Extended-shell func_basename implementation' "$cfgfile" > $cfgfile.tmp \ && mv -f "$cfgfile.tmp" "$cfgfile" \ || (rm -f "$cfgfile" && cp "$cfgfile.tmp" "$cfgfile" && rm -f "$cfgfile.tmp") test 0 -eq $? || _lt_function_replace_fail=: sed -e '/^func_dirname_and_basename ()$/,/^} # func_dirname_and_basename /c\ func_dirname_and_basename ()\ {\ \ case ${1} in\ \ */*) func_dirname_result="${1%/*}${2}" ;;\ \ * ) func_dirname_result="${3}" ;;\ \ esac\ \ func_basename_result="${1##*/}"\ } # Extended-shell func_dirname_and_basename implementation' "$cfgfile" > $cfgfile.tmp \ && mv -f "$cfgfile.tmp" "$cfgfile" \ || (rm -f "$cfgfile" && cp "$cfgfile.tmp" "$cfgfile" && rm -f "$cfgfile.tmp") test 0 -eq $? || _lt_function_replace_fail=: sed -e '/^func_stripname ()$/,/^} # func_stripname /c\ func_stripname ()\ {\ \ # pdksh 5.2.14 does not do ${X%$Y} correctly if both X and Y are\ \ # positional parameters, so assign one to ordinary parameter first.\ \ func_stripname_result=${3}\ \ func_stripname_result=${func_stripname_result#"${1}"}\ \ func_stripname_result=${func_stripname_result%"${2}"}\ } # Extended-shell func_stripname implementation' "$cfgfile" > $cfgfile.tmp \ && mv -f "$cfgfile.tmp" "$cfgfile" \ || (rm -f "$cfgfile" && cp "$cfgfile.tmp" "$cfgfile" && rm -f "$cfgfile.tmp") test 0 -eq $? || _lt_function_replace_fail=: sed -e '/^func_split_long_opt ()$/,/^} # func_split_long_opt /c\ func_split_long_opt ()\ {\ \ func_split_long_opt_name=${1%%=*}\ \ func_split_long_opt_arg=${1#*=}\ } # Extended-shell func_split_long_opt implementation' "$cfgfile" > $cfgfile.tmp \ && mv -f "$cfgfile.tmp" "$cfgfile" \ || (rm -f "$cfgfile" && cp "$cfgfile.tmp" "$cfgfile" && rm -f "$cfgfile.tmp") test 0 -eq $? || _lt_function_replace_fail=: sed -e '/^func_split_short_opt ()$/,/^} # func_split_short_opt /c\ func_split_short_opt ()\ {\ \ func_split_short_opt_arg=${1#??}\ \ func_split_short_opt_name=${1%"$func_split_short_opt_arg"}\ } # Extended-shell func_split_short_opt implementation' "$cfgfile" > $cfgfile.tmp \ && mv -f "$cfgfile.tmp" "$cfgfile" \ || (rm -f "$cfgfile" && cp "$cfgfile.tmp" "$cfgfile" && rm -f "$cfgfile.tmp") test 0 -eq $? || _lt_function_replace_fail=: sed -e '/^func_lo2o ()$/,/^} # func_lo2o /c\ func_lo2o ()\ {\ \ case ${1} in\ \ *.lo) func_lo2o_result=${1%.lo}.${objext} ;;\ \ *) func_lo2o_result=${1} ;;\ \ esac\ } # Extended-shell func_lo2o implementation' "$cfgfile" > $cfgfile.tmp \ && mv -f "$cfgfile.tmp" "$cfgfile" \ || (rm -f "$cfgfile" && cp "$cfgfile.tmp" "$cfgfile" && rm -f "$cfgfile.tmp") test 0 -eq $? || _lt_function_replace_fail=: sed -e '/^func_xform ()$/,/^} # func_xform /c\ func_xform ()\ {\ func_xform_result=${1%.*}.lo\ } # Extended-shell func_xform implementation' "$cfgfile" > $cfgfile.tmp \ && mv -f "$cfgfile.tmp" "$cfgfile" \ || (rm -f "$cfgfile" && cp "$cfgfile.tmp" "$cfgfile" && rm -f "$cfgfile.tmp") test 0 -eq $? || _lt_function_replace_fail=: sed -e '/^func_arith ()$/,/^} # func_arith /c\ func_arith ()\ {\ func_arith_result=$(( $* ))\ } # Extended-shell func_arith implementation' "$cfgfile" > $cfgfile.tmp \ && mv -f "$cfgfile.tmp" "$cfgfile" \ || (rm -f "$cfgfile" && cp "$cfgfile.tmp" "$cfgfile" && rm -f "$cfgfile.tmp") test 0 -eq $? || _lt_function_replace_fail=: sed -e '/^func_len ()$/,/^} # func_len /c\ func_len ()\ {\ func_len_result=${#1}\ } # Extended-shell func_len implementation' "$cfgfile" > $cfgfile.tmp \ && mv -f "$cfgfile.tmp" "$cfgfile" \ || (rm -f "$cfgfile" && cp "$cfgfile.tmp" "$cfgfile" && rm -f "$cfgfile.tmp") test 0 -eq $? || _lt_function_replace_fail=: fi if test x"$lt_shell_append" = xyes; then sed -e '/^func_append ()$/,/^} # func_append /c\ func_append ()\ {\ eval "${1}+=\\${2}"\ } # Extended-shell func_append implementation' "$cfgfile" > $cfgfile.tmp \ && mv -f "$cfgfile.tmp" "$cfgfile" \ || (rm -f "$cfgfile" && cp "$cfgfile.tmp" "$cfgfile" && rm -f "$cfgfile.tmp") test 0 -eq $? || _lt_function_replace_fail=: sed -e '/^func_append_quoted ()$/,/^} # func_append_quoted /c\ func_append_quoted ()\ {\ \ func_quote_for_eval "${2}"\ \ eval "${1}+=\\\\ \\$func_quote_for_eval_result"\ } # Extended-shell func_append_quoted implementation' "$cfgfile" > $cfgfile.tmp \ && mv -f "$cfgfile.tmp" "$cfgfile" \ || (rm -f "$cfgfile" && cp "$cfgfile.tmp" "$cfgfile" && rm -f "$cfgfile.tmp") test 0 -eq $? || _lt_function_replace_fail=: # Save a `func_append' function call where possible by direct use of '+=' sed -e 's%func_append \([a-zA-Z_]\{1,\}\) "%\1+="%g' $cfgfile > $cfgfile.tmp \ && mv -f "$cfgfile.tmp" "$cfgfile" \ || (rm -f "$cfgfile" && cp "$cfgfile.tmp" "$cfgfile" && rm -f "$cfgfile.tmp") test 0 -eq $? || _lt_function_replace_fail=: else # Save a `func_append' function call even when '+=' is not available sed -e 's%func_append \([a-zA-Z_]\{1,\}\) "%\1="$\1%g' $cfgfile > $cfgfile.tmp \ && mv -f "$cfgfile.tmp" "$cfgfile" \ || (rm -f "$cfgfile" && cp "$cfgfile.tmp" "$cfgfile" && rm -f "$cfgfile.tmp") test 0 -eq $? || _lt_function_replace_fail=: fi if test x"$_lt_function_replace_fail" = x":"; then { $as_echo "$as_me:${as_lineno-$LINENO}: WARNING: Unable to substitute extended shell functions in $ofile" >&5 $as_echo "$as_me: WARNING: Unable to substitute extended shell functions in $ofile" >&2;} fi mv -f "$cfgfile" "$ofile" || (rm -f "$ofile" && cp "$cfgfile" "$ofile" && rm -f "$cfgfile") chmod +x "$ofile" ;; "include":C) test -d include || mkdir include ;; "src":C) test -d src || mkdir src test -d src/$TARGETDIR || mkdir src/$TARGETDIR ;; esac done # for ac_tag as_fn_exit 0 _ACEOF ac_clean_files=$ac_clean_files_save test $ac_write_fail = 0 || as_fn_error $? "write failure creating $CONFIG_STATUS" "$LINENO" 5 # configure is writing to config.log, and then calls config.status. # config.status does its own redirection, appending to config.log. # Unfortunately, on DOS this fails, as config.log is still kept open # by configure, so config.status won't be able to write to it; its # output is simply discarded. So we exec the FD to /dev/null, # effectively closing config.log, so it can be properly (re)opened and # appended to by config.status. When coming back to configure, we # need to make the FD available again. if test "$no_create" != yes; then ac_cs_success=: ac_config_status_args= test "$silent" = yes && ac_config_status_args="$ac_config_status_args --quiet" exec 5>/dev/null $SHELL $CONFIG_STATUS $ac_config_status_args || ac_cs_success=false exec 5>>config.log # Use ||, not &&, to avoid exiting from the if with $? = 1, which # would make configure fail if this is the last instruction. $ac_cs_success || as_fn_exit 1 fi if test -n "$ac_unrecognized_opts" && test "$enable_option_checking" != no; then { $as_echo "$as_me:${as_lineno-$LINENO}: WARNING: unrecognized options: $ac_unrecognized_opts" >&5 $as_echo "$as_me: WARNING: unrecognized options: $ac_unrecognized_opts" >&2;} fi smalltalk-3.2.5/libffi/fficonfig.h.in0000644000175000017500000001153712130455532014400 00000000000000/* fficonfig.h.in. Generated from configure.ac by autoheader. */ /* Define if building universal (internal helper macro) */ #undef AC_APPLE_UNIVERSAL_BUILD /* Define to one of `_getb67', `GETB67', `getb67' for Cray-2 and Cray-YMP systems. This function is required for `alloca.c' support on those systems. */ #undef CRAY_STACKSEG_END /* Define to 1 if using `alloca.c'. */ #undef C_ALLOCA /* Define to the flags needed for the .section .eh_frame directive. */ #undef EH_FRAME_FLAGS /* Define this if you want extra debugging. */ #undef FFI_DEBUG /* Cannot use malloc on this target, so, we revert to alternative means */ #undef FFI_MMAP_EXEC_WRIT /* Define this is you do not want support for the raw API. */ #undef FFI_NO_RAW_API /* Define this is you do not want support for aggregate types. */ #undef FFI_NO_STRUCTS /* Define to 1 if you have `alloca', as a function or macro. */ #undef HAVE_ALLOCA /* Define to 1 if you have and it should be used (not on Ultrix). */ #undef HAVE_ALLOCA_H /* Define if your assembler supports .ascii. */ #undef HAVE_AS_ASCII_PSEUDO_OP /* Define if your assembler supports .cfi_* directives. */ #undef HAVE_AS_CFI_PSEUDO_OP /* Define if your assembler supports .register. */ #undef HAVE_AS_REGISTER_PSEUDO_OP /* Define if your assembler and linker support unaligned PC relative relocs. */ #undef HAVE_AS_SPARC_UA_PCREL /* Define if your assembler supports .string. */ #undef HAVE_AS_STRING_PSEUDO_OP /* Define if your assembler supports unwind section type. */ #undef HAVE_AS_X86_64_UNWIND_SECTION_TYPE /* Define if your assembler supports PC relative relocs. */ #undef HAVE_AS_X86_PCREL /* Define to 1 if you have the header file. */ #undef HAVE_DLFCN_H /* Define if __attribute__((visibility("hidden"))) is supported. */ #undef HAVE_HIDDEN_VISIBILITY_ATTRIBUTE /* Define to 1 if you have the header file. */ #undef HAVE_INTTYPES_H /* Define if you have the long double type and it is bigger than a double */ #undef HAVE_LONG_DOUBLE /* Define to 1 if you have the `memcpy' function. */ #undef HAVE_MEMCPY /* Define to 1 if you have the header file. */ #undef HAVE_MEMORY_H /* Define if .eh_frame sections should be read-only. */ #undef HAVE_RO_EH_FRAME /* Define to 1 if you have the header file. */ #undef HAVE_STDINT_H /* Define to 1 if you have the header file. */ #undef HAVE_STDLIB_H /* Define to 1 if you have the header file. */ #undef HAVE_STRINGS_H /* Define to 1 if you have the header file. */ #undef HAVE_STRING_H /* Define to 1 if you have the header file. */ #undef HAVE_SYS_STAT_H /* Define to 1 if you have the header file. */ #undef HAVE_SYS_TYPES_H /* Define to 1 if you have the header file. */ #undef HAVE_UNISTD_H /* Define to the sub-directory in which libtool stores uninstalled libraries. */ #undef LT_OBJDIR /* Define to 1 if your C compiler doesn't accept -c and -o together. */ #undef NO_MINUS_C_MINUS_O /* Name of package */ #undef PACKAGE /* Define to the address where bug reports for this package should be sent. */ #undef PACKAGE_BUGREPORT /* Define to the full name of this package. */ #undef PACKAGE_NAME /* Define to the full name and version of this package. */ #undef PACKAGE_STRING /* Define to the one symbol short name of this package. */ #undef PACKAGE_TARNAME /* Define to the home page for this package. */ #undef PACKAGE_URL /* Define to the version of this package. */ #undef PACKAGE_VERSION /* The size of `double', as computed by sizeof. */ #undef SIZEOF_DOUBLE /* The size of `long double', as computed by sizeof. */ #undef SIZEOF_LONG_DOUBLE /* If using the C implementation of alloca, define if you know the direction of stack growth for your system; otherwise it will be automatically deduced at runtime. STACK_DIRECTION > 0 => grows toward higher addresses STACK_DIRECTION < 0 => grows toward lower addresses STACK_DIRECTION = 0 => direction of growth unknown */ #undef STACK_DIRECTION /* Define to 1 if you have the ANSI C header files. */ #undef STDC_HEADERS /* Define this if you are using Purify and want to suppress spurious messages. */ #undef USING_PURIFY /* Version number of package */ #undef VERSION /* Define WORDS_BIGENDIAN to 1 if your processor stores words with the most significant byte first (like Motorola and SPARC, unlike Intel). */ #if defined AC_APPLE_UNIVERSAL_BUILD # if defined __BIG_ENDIAN__ # define WORDS_BIGENDIAN 1 # endif #else # ifndef WORDS_BIGENDIAN # undef WORDS_BIGENDIAN # endif #endif /* Define to `unsigned int' if does not define. */ #undef size_t #ifdef HAVE_HIDDEN_VISIBILITY_ATTRIBUTE #ifdef LIBFFI_ASM #define FFI_HIDDEN(name) .hidden name #else #define FFI_HIDDEN __attribute__ ((visibility ("hidden"))) #endif #else #ifdef LIBFFI_ASM #define FFI_HIDDEN(name) #else #define FFI_HIDDEN #endif #endif smalltalk-3.2.5/libffi/ChangeLog.libgcj0000644000175000017500000000211712130343734014665 000000000000002004-01-14 Kelley Cook * configure.in: Add in AC_PREREQ(2.13) 2003-02-20 Alexandre Oliva * configure.in: Propagate ORIGINAL_LD_FOR_MULTILIBS to config.status. * configure: Rebuilt. 2002-01-27 Alexandre Oliva * configure.in (toolexecdir, toolexeclibdir): Set and AC_SUBST. Remove USE_LIBDIR conditional. * Makefile.am (toolexecdir, toolexeclibdir): Don't override. * Makefile.in, configure: Rebuilt. Mon Aug 9 18:33:38 1999 Rainer Orth * include/Makefile.in: Rebuilt. * Makefile.in: Rebuilt * Makefile.am (toolexeclibdir): Add $(MULTISUBDIR) even for native builds. Use USE_LIBDIR. * configure: Rebuilt. * configure.in (USE_LIBDIR): Define for native builds. Use lowercase in configure --help explanations. 1999-08-08 Anthony Green * include/ffi.h.in (FFI_FN): Remove `...'. 1999-08-08 Anthony Green * Makefile.in: Rebuilt. * Makefile.am (AM_CFLAGS): Compile with -fexceptions. * src/x86/sysv.S: Add exception handling metadata. smalltalk-3.2.5/libffi/aclocal.m40000644000175000017500000011050512130455521013521 00000000000000# generated automatically by aclocal 1.11.6 -*- Autoconf -*- # Copyright (C) 1996, 1997, 1998, 1999, 2000, 2001, 2002, 2003, 2004, # 2005, 2006, 2007, 2008, 2009, 2010, 2011 Free Software Foundation, # Inc. # This file is free software; the Free Software Foundation # gives unlimited permission to copy and/or distribute it, # with or without modifications, as long as this notice is preserved. # This program is distributed in the hope that it will be useful, # but WITHOUT ANY WARRANTY, to the extent permitted by law; without # even the implied warranty of MERCHANTABILITY or FITNESS FOR A # PARTICULAR PURPOSE. m4_ifndef([AC_AUTOCONF_VERSION], [m4_copy([m4_PACKAGE_VERSION], [AC_AUTOCONF_VERSION])])dnl m4_if(m4_defn([AC_AUTOCONF_VERSION]), [2.69],, [m4_warning([this file was generated for autoconf 2.69. You have another version of autoconf. It may work, but is not guaranteed to. If you have problems, you may need to regenerate the build system entirely. To do so, use the procedure documented by the package, typically `autoreconf'.])]) # Copyright (C) 2002, 2003, 2005, 2006, 2007, 2008, 2011 Free Software # Foundation, Inc. # # This file is free software; the Free Software Foundation # gives unlimited permission to copy and/or distribute it, # with or without modifications, as long as this notice is preserved. # serial 1 # AM_AUTOMAKE_VERSION(VERSION) # ---------------------------- # Automake X.Y traces this macro to ensure aclocal.m4 has been # generated from the m4 files accompanying Automake X.Y. # (This private macro should not be called outside this file.) AC_DEFUN([AM_AUTOMAKE_VERSION], [am__api_version='1.11' dnl Some users find AM_AUTOMAKE_VERSION and mistake it for a way to dnl require some minimum version. Point them to the right macro. m4_if([$1], [1.11.6], [], [AC_FATAL([Do not call $0, use AM_INIT_AUTOMAKE([$1]).])])dnl ]) # _AM_AUTOCONF_VERSION(VERSION) # ----------------------------- # aclocal traces this macro to find the Autoconf version. # This is a private macro too. Using m4_define simplifies # the logic in aclocal, which can simply ignore this definition. m4_define([_AM_AUTOCONF_VERSION], []) # AM_SET_CURRENT_AUTOMAKE_VERSION # ------------------------------- # Call AM_AUTOMAKE_VERSION and AM_AUTOMAKE_VERSION so they can be traced. # This function is AC_REQUIREd by AM_INIT_AUTOMAKE. AC_DEFUN([AM_SET_CURRENT_AUTOMAKE_VERSION], [AM_AUTOMAKE_VERSION([1.11.6])dnl m4_ifndef([AC_AUTOCONF_VERSION], [m4_copy([m4_PACKAGE_VERSION], [AC_AUTOCONF_VERSION])])dnl _AM_AUTOCONF_VERSION(m4_defn([AC_AUTOCONF_VERSION]))]) # Figure out how to run the assembler. -*- Autoconf -*- # Copyright (C) 2001, 2003, 2004, 2005, 2006 Free Software Foundation, Inc. # # This file is free software; the Free Software Foundation # gives unlimited permission to copy and/or distribute it, # with or without modifications, as long as this notice is preserved. # serial 5 # AM_PROG_AS # ---------- AC_DEFUN([AM_PROG_AS], [# By default we simply use the C compiler to build assembly code. AC_REQUIRE([AC_PROG_CC]) test "${CCAS+set}" = set || CCAS=$CC test "${CCASFLAGS+set}" = set || CCASFLAGS=$CFLAGS AC_ARG_VAR([CCAS], [assembler compiler command (defaults to CC)]) AC_ARG_VAR([CCASFLAGS], [assembler compiler flags (defaults to CFLAGS)]) _AM_IF_OPTION([no-dependencies],, [_AM_DEPENDENCIES([CCAS])])dnl ]) # AM_AUX_DIR_EXPAND -*- Autoconf -*- # Copyright (C) 2001, 2003, 2005, 2011 Free Software Foundation, Inc. # # This file is free software; the Free Software Foundation # gives unlimited permission to copy and/or distribute it, # with or without modifications, as long as this notice is preserved. # serial 1 # For projects using AC_CONFIG_AUX_DIR([foo]), Autoconf sets # $ac_aux_dir to `$srcdir/foo'. In other projects, it is set to # `$srcdir', `$srcdir/..', or `$srcdir/../..'. # # Of course, Automake must honor this variable whenever it calls a # tool from the auxiliary directory. The problem is that $srcdir (and # therefore $ac_aux_dir as well) can be either absolute or relative, # depending on how configure is run. This is pretty annoying, since # it makes $ac_aux_dir quite unusable in subdirectories: in the top # source directory, any form will work fine, but in subdirectories a # relative path needs to be adjusted first. # # $ac_aux_dir/missing # fails when called from a subdirectory if $ac_aux_dir is relative # $top_srcdir/$ac_aux_dir/missing # fails if $ac_aux_dir is absolute, # fails when called from a subdirectory in a VPATH build with # a relative $ac_aux_dir # # The reason of the latter failure is that $top_srcdir and $ac_aux_dir # are both prefixed by $srcdir. In an in-source build this is usually # harmless because $srcdir is `.', but things will broke when you # start a VPATH build or use an absolute $srcdir. # # So we could use something similar to $top_srcdir/$ac_aux_dir/missing, # iff we strip the leading $srcdir from $ac_aux_dir. That would be: # am_aux_dir='\$(top_srcdir)/'`expr "$ac_aux_dir" : "$srcdir//*\(.*\)"` # and then we would define $MISSING as # MISSING="\${SHELL} $am_aux_dir/missing" # This will work as long as MISSING is not called from configure, because # unfortunately $(top_srcdir) has no meaning in configure. # However there are other variables, like CC, which are often used in # configure, and could therefore not use this "fixed" $ac_aux_dir. # # Another solution, used here, is to always expand $ac_aux_dir to an # absolute PATH. The drawback is that using absolute paths prevent a # configured tree to be moved without reconfiguration. AC_DEFUN([AM_AUX_DIR_EXPAND], [dnl Rely on autoconf to set up CDPATH properly. AC_PREREQ([2.50])dnl # expand $ac_aux_dir to an absolute path am_aux_dir=`cd $ac_aux_dir && pwd` ]) # AM_CONDITIONAL -*- Autoconf -*- # Copyright (C) 1997, 2000, 2001, 2003, 2004, 2005, 2006, 2008 # Free Software Foundation, Inc. # # This file is free software; the Free Software Foundation # gives unlimited permission to copy and/or distribute it, # with or without modifications, as long as this notice is preserved. # serial 9 # AM_CONDITIONAL(NAME, SHELL-CONDITION) # ------------------------------------- # Define a conditional. AC_DEFUN([AM_CONDITIONAL], [AC_PREREQ(2.52)dnl ifelse([$1], [TRUE], [AC_FATAL([$0: invalid condition: $1])], [$1], [FALSE], [AC_FATAL([$0: invalid condition: $1])])dnl AC_SUBST([$1_TRUE])dnl AC_SUBST([$1_FALSE])dnl _AM_SUBST_NOTMAKE([$1_TRUE])dnl _AM_SUBST_NOTMAKE([$1_FALSE])dnl m4_define([_AM_COND_VALUE_$1], [$2])dnl if $2; then $1_TRUE= $1_FALSE='#' else $1_TRUE='#' $1_FALSE= fi AC_CONFIG_COMMANDS_PRE( [if test -z "${$1_TRUE}" && test -z "${$1_FALSE}"; then AC_MSG_ERROR([[conditional "$1" was never defined. Usually this means the macro was only invoked conditionally.]]) fi])]) # Copyright (C) 1999, 2000, 2001, 2002, 2003, 2004, 2005, 2006, 2009, # 2010, 2011 Free Software Foundation, Inc. # # This file is free software; the Free Software Foundation # gives unlimited permission to copy and/or distribute it, # with or without modifications, as long as this notice is preserved. # serial 12 # There are a few dirty hacks below to avoid letting `AC_PROG_CC' be # written in clear, in which case automake, when reading aclocal.m4, # will think it sees a *use*, and therefore will trigger all it's # C support machinery. Also note that it means that autoscan, seeing # CC etc. in the Makefile, will ask for an AC_PROG_CC use... # _AM_DEPENDENCIES(NAME) # ---------------------- # See how the compiler implements dependency checking. # NAME is "CC", "CXX", "GCJ", or "OBJC". # We try a few techniques and use that to set a single cache variable. # # We don't AC_REQUIRE the corresponding AC_PROG_CC since the latter was # modified to invoke _AM_DEPENDENCIES(CC); we would have a circular # dependency, and given that the user is not expected to run this macro, # just rely on AC_PROG_CC. AC_DEFUN([_AM_DEPENDENCIES], [AC_REQUIRE([AM_SET_DEPDIR])dnl AC_REQUIRE([AM_OUTPUT_DEPENDENCY_COMMANDS])dnl AC_REQUIRE([AM_MAKE_INCLUDE])dnl AC_REQUIRE([AM_DEP_TRACK])dnl ifelse([$1], CC, [depcc="$CC" am_compiler_list=], [$1], CXX, [depcc="$CXX" am_compiler_list=], [$1], OBJC, [depcc="$OBJC" am_compiler_list='gcc3 gcc'], [$1], UPC, [depcc="$UPC" am_compiler_list=], [$1], GCJ, [depcc="$GCJ" am_compiler_list='gcc3 gcc'], [depcc="$$1" am_compiler_list=]) AC_CACHE_CHECK([dependency style of $depcc], [am_cv_$1_dependencies_compiler_type], [if test -z "$AMDEP_TRUE" && test -f "$am_depcomp"; then # We make a subdir and do the tests there. Otherwise we can end up # making bogus files that we don't know about and never remove. For # instance it was reported that on HP-UX the gcc test will end up # making a dummy file named `D' -- because `-MD' means `put the output # in D'. rm -rf conftest.dir mkdir conftest.dir # Copy depcomp to subdir because otherwise we won't find it if we're # using a relative directory. cp "$am_depcomp" conftest.dir cd conftest.dir # We will build objects and dependencies in a subdirectory because # it helps to detect inapplicable dependency modes. For instance # both Tru64's cc and ICC support -MD to output dependencies as a # side effect of compilation, but ICC will put the dependencies in # the current directory while Tru64 will put them in the object # directory. mkdir sub am_cv_$1_dependencies_compiler_type=none if test "$am_compiler_list" = ""; then am_compiler_list=`sed -n ['s/^#*\([a-zA-Z0-9]*\))$/\1/p'] < ./depcomp` fi am__universal=false m4_case([$1], [CC], [case " $depcc " in #( *\ -arch\ *\ -arch\ *) am__universal=true ;; esac], [CXX], [case " $depcc " in #( *\ -arch\ *\ -arch\ *) am__universal=true ;; esac]) for depmode in $am_compiler_list; do # Setup a source with many dependencies, because some compilers # like to wrap large dependency lists on column 80 (with \), and # we should not choose a depcomp mode which is confused by this. # # We need to recreate these files for each test, as the compiler may # overwrite some of them when testing with obscure command lines. # This happens at least with the AIX C compiler. : > sub/conftest.c for i in 1 2 3 4 5 6; do echo '#include "conftst'$i'.h"' >> sub/conftest.c # Using `: > sub/conftst$i.h' creates only sub/conftst1.h with # Solaris 8's {/usr,}/bin/sh. touch sub/conftst$i.h done echo "${am__include} ${am__quote}sub/conftest.Po${am__quote}" > confmf # We check with `-c' and `-o' for the sake of the "dashmstdout" # mode. It turns out that the SunPro C++ compiler does not properly # handle `-M -o', and we need to detect this. Also, some Intel # versions had trouble with output in subdirs am__obj=sub/conftest.${OBJEXT-o} am__minus_obj="-o $am__obj" case $depmode in gcc) # This depmode causes a compiler race in universal mode. test "$am__universal" = false || continue ;; nosideeffect) # after this tag, mechanisms are not by side-effect, so they'll # only be used when explicitly requested if test "x$enable_dependency_tracking" = xyes; then continue else break fi ;; msvc7 | msvc7msys | msvisualcpp | msvcmsys) # This compiler won't grok `-c -o', but also, the minuso test has # not run yet. These depmodes are late enough in the game, and # so weak that their functioning should not be impacted. am__obj=conftest.${OBJEXT-o} am__minus_obj= ;; none) break ;; esac if depmode=$depmode \ source=sub/conftest.c object=$am__obj \ depfile=sub/conftest.Po tmpdepfile=sub/conftest.TPo \ $SHELL ./depcomp $depcc -c $am__minus_obj sub/conftest.c \ >/dev/null 2>conftest.err && grep sub/conftst1.h sub/conftest.Po > /dev/null 2>&1 && grep sub/conftst6.h sub/conftest.Po > /dev/null 2>&1 && grep $am__obj sub/conftest.Po > /dev/null 2>&1 && ${MAKE-make} -s -f confmf > /dev/null 2>&1; then # icc doesn't choke on unknown options, it will just issue warnings # or remarks (even with -Werror). So we grep stderr for any message # that says an option was ignored or not supported. # When given -MP, icc 7.0 and 7.1 complain thusly: # icc: Command line warning: ignoring option '-M'; no argument required # The diagnosis changed in icc 8.0: # icc: Command line remark: option '-MP' not supported if (grep 'ignoring option' conftest.err || grep 'not supported' conftest.err) >/dev/null 2>&1; then :; else am_cv_$1_dependencies_compiler_type=$depmode break fi fi done cd .. rm -rf conftest.dir else am_cv_$1_dependencies_compiler_type=none fi ]) AC_SUBST([$1DEPMODE], [depmode=$am_cv_$1_dependencies_compiler_type]) AM_CONDITIONAL([am__fastdep$1], [ test "x$enable_dependency_tracking" != xno \ && test "$am_cv_$1_dependencies_compiler_type" = gcc3]) ]) # AM_SET_DEPDIR # ------------- # Choose a directory name for dependency files. # This macro is AC_REQUIREd in _AM_DEPENDENCIES AC_DEFUN([AM_SET_DEPDIR], [AC_REQUIRE([AM_SET_LEADING_DOT])dnl AC_SUBST([DEPDIR], ["${am__leading_dot}deps"])dnl ]) # AM_DEP_TRACK # ------------ AC_DEFUN([AM_DEP_TRACK], [AC_ARG_ENABLE(dependency-tracking, [ --disable-dependency-tracking speeds up one-time build --enable-dependency-tracking do not reject slow dependency extractors]) if test "x$enable_dependency_tracking" != xno; then am_depcomp="$ac_aux_dir/depcomp" AMDEPBACKSLASH='\' am__nodep='_no' fi AM_CONDITIONAL([AMDEP], [test "x$enable_dependency_tracking" != xno]) AC_SUBST([AMDEPBACKSLASH])dnl _AM_SUBST_NOTMAKE([AMDEPBACKSLASH])dnl AC_SUBST([am__nodep])dnl _AM_SUBST_NOTMAKE([am__nodep])dnl ]) # Generate code to set up dependency tracking. -*- Autoconf -*- # Copyright (C) 1999, 2000, 2001, 2002, 2003, 2004, 2005, 2008 # Free Software Foundation, Inc. # # This file is free software; the Free Software Foundation # gives unlimited permission to copy and/or distribute it, # with or without modifications, as long as this notice is preserved. #serial 5 # _AM_OUTPUT_DEPENDENCY_COMMANDS # ------------------------------ AC_DEFUN([_AM_OUTPUT_DEPENDENCY_COMMANDS], [{ # Autoconf 2.62 quotes --file arguments for eval, but not when files # are listed without --file. Let's play safe and only enable the eval # if we detect the quoting. case $CONFIG_FILES in *\'*) eval set x "$CONFIG_FILES" ;; *) set x $CONFIG_FILES ;; esac shift for mf do # Strip MF so we end up with the name of the file. mf=`echo "$mf" | sed -e 's/:.*$//'` # Check whether this is an Automake generated Makefile or not. # We used to match only the files named `Makefile.in', but # some people rename them; so instead we look at the file content. # Grep'ing the first line is not enough: some people post-process # each Makefile.in and add a new line on top of each file to say so. # Grep'ing the whole file is not good either: AIX grep has a line # limit of 2048, but all sed's we know have understand at least 4000. if sed -n 's,^#.*generated by automake.*,X,p' "$mf" | grep X >/dev/null 2>&1; then dirpart=`AS_DIRNAME("$mf")` else continue fi # Extract the definition of DEPDIR, am__include, and am__quote # from the Makefile without running `make'. DEPDIR=`sed -n 's/^DEPDIR = //p' < "$mf"` test -z "$DEPDIR" && continue am__include=`sed -n 's/^am__include = //p' < "$mf"` test -z "am__include" && continue am__quote=`sed -n 's/^am__quote = //p' < "$mf"` # When using ansi2knr, U may be empty or an underscore; expand it U=`sed -n 's/^U = //p' < "$mf"` # Find all dependency output files, they are included files with # $(DEPDIR) in their names. We invoke sed twice because it is the # simplest approach to changing $(DEPDIR) to its actual value in the # expansion. for file in `sed -n " s/^$am__include $am__quote\(.*(DEPDIR).*\)$am__quote"'$/\1/p' <"$mf" | \ sed -e 's/\$(DEPDIR)/'"$DEPDIR"'/g' -e 's/\$U/'"$U"'/g'`; do # Make sure the directory exists. test -f "$dirpart/$file" && continue fdir=`AS_DIRNAME(["$file"])` AS_MKDIR_P([$dirpart/$fdir]) # echo "creating $dirpart/$file" echo '# dummy' > "$dirpart/$file" done done } ])# _AM_OUTPUT_DEPENDENCY_COMMANDS # AM_OUTPUT_DEPENDENCY_COMMANDS # ----------------------------- # This macro should only be invoked once -- use via AC_REQUIRE. # # This code is only required when automatic dependency tracking # is enabled. FIXME. This creates each `.P' file that we will # need in order to bootstrap the dependency handling code. AC_DEFUN([AM_OUTPUT_DEPENDENCY_COMMANDS], [AC_CONFIG_COMMANDS([depfiles], [test x"$AMDEP_TRUE" != x"" || _AM_OUTPUT_DEPENDENCY_COMMANDS], [AMDEP_TRUE="$AMDEP_TRUE" ac_aux_dir="$ac_aux_dir"]) ]) # Do all the work for Automake. -*- Autoconf -*- # Copyright (C) 1996, 1997, 1998, 1999, 2000, 2001, 2002, 2003, 2004, # 2005, 2006, 2008, 2009 Free Software Foundation, Inc. # # This file is free software; the Free Software Foundation # gives unlimited permission to copy and/or distribute it, # with or without modifications, as long as this notice is preserved. # serial 16 # This macro actually does too much. Some checks are only needed if # your package does certain things. But this isn't really a big deal. # AM_INIT_AUTOMAKE(PACKAGE, VERSION, [NO-DEFINE]) # AM_INIT_AUTOMAKE([OPTIONS]) # ----------------------------------------------- # The call with PACKAGE and VERSION arguments is the old style # call (pre autoconf-2.50), which is being phased out. PACKAGE # and VERSION should now be passed to AC_INIT and removed from # the call to AM_INIT_AUTOMAKE. # We support both call styles for the transition. After # the next Automake release, Autoconf can make the AC_INIT # arguments mandatory, and then we can depend on a new Autoconf # release and drop the old call support. AC_DEFUN([AM_INIT_AUTOMAKE], [AC_PREREQ([2.62])dnl dnl Autoconf wants to disallow AM_ names. We explicitly allow dnl the ones we care about. m4_pattern_allow([^AM_[A-Z]+FLAGS$])dnl AC_REQUIRE([AM_SET_CURRENT_AUTOMAKE_VERSION])dnl AC_REQUIRE([AC_PROG_INSTALL])dnl if test "`cd $srcdir && pwd`" != "`pwd`"; then # Use -I$(srcdir) only when $(srcdir) != ., so that make's output # is not polluted with repeated "-I." AC_SUBST([am__isrc], [' -I$(srcdir)'])_AM_SUBST_NOTMAKE([am__isrc])dnl # test to see if srcdir already configured if test -f $srcdir/config.status; then AC_MSG_ERROR([source directory already configured; run "make distclean" there first]) fi fi # test whether we have cygpath if test -z "$CYGPATH_W"; then if (cygpath --version) >/dev/null 2>/dev/null; then CYGPATH_W='cygpath -w' else CYGPATH_W=echo fi fi AC_SUBST([CYGPATH_W]) # Define the identity of the package. dnl Distinguish between old-style and new-style calls. m4_ifval([$2], [m4_ifval([$3], [_AM_SET_OPTION([no-define])])dnl AC_SUBST([PACKAGE], [$1])dnl AC_SUBST([VERSION], [$2])], [_AM_SET_OPTIONS([$1])dnl dnl Diagnose old-style AC_INIT with new-style AM_AUTOMAKE_INIT. m4_if(m4_ifdef([AC_PACKAGE_NAME], 1)m4_ifdef([AC_PACKAGE_VERSION], 1), 11,, [m4_fatal([AC_INIT should be called with package and version arguments])])dnl AC_SUBST([PACKAGE], ['AC_PACKAGE_TARNAME'])dnl AC_SUBST([VERSION], ['AC_PACKAGE_VERSION'])])dnl _AM_IF_OPTION([no-define],, [AC_DEFINE_UNQUOTED(PACKAGE, "$PACKAGE", [Name of package]) AC_DEFINE_UNQUOTED(VERSION, "$VERSION", [Version number of package])])dnl # Some tools Automake needs. AC_REQUIRE([AM_SANITY_CHECK])dnl AC_REQUIRE([AC_ARG_PROGRAM])dnl AM_MISSING_PROG(ACLOCAL, aclocal-${am__api_version}) AM_MISSING_PROG(AUTOCONF, autoconf) AM_MISSING_PROG(AUTOMAKE, automake-${am__api_version}) AM_MISSING_PROG(AUTOHEADER, autoheader) AM_MISSING_PROG(MAKEINFO, makeinfo) AC_REQUIRE([AM_PROG_INSTALL_SH])dnl AC_REQUIRE([AM_PROG_INSTALL_STRIP])dnl AC_REQUIRE([AM_PROG_MKDIR_P])dnl # We need awk for the "check" target. The system "awk" is bad on # some platforms. AC_REQUIRE([AC_PROG_AWK])dnl AC_REQUIRE([AC_PROG_MAKE_SET])dnl AC_REQUIRE([AM_SET_LEADING_DOT])dnl _AM_IF_OPTION([tar-ustar], [_AM_PROG_TAR([ustar])], [_AM_IF_OPTION([tar-pax], [_AM_PROG_TAR([pax])], [_AM_PROG_TAR([v7])])]) _AM_IF_OPTION([no-dependencies],, [AC_PROVIDE_IFELSE([AC_PROG_CC], [_AM_DEPENDENCIES(CC)], [define([AC_PROG_CC], defn([AC_PROG_CC])[_AM_DEPENDENCIES(CC)])])dnl AC_PROVIDE_IFELSE([AC_PROG_CXX], [_AM_DEPENDENCIES(CXX)], [define([AC_PROG_CXX], defn([AC_PROG_CXX])[_AM_DEPENDENCIES(CXX)])])dnl AC_PROVIDE_IFELSE([AC_PROG_OBJC], [_AM_DEPENDENCIES(OBJC)], [define([AC_PROG_OBJC], defn([AC_PROG_OBJC])[_AM_DEPENDENCIES(OBJC)])])dnl ]) _AM_IF_OPTION([silent-rules], [AC_REQUIRE([AM_SILENT_RULES])])dnl dnl The `parallel-tests' driver may need to know about EXEEXT, so add the dnl `am__EXEEXT' conditional if _AM_COMPILER_EXEEXT was seen. This macro dnl is hooked onto _AC_COMPILER_EXEEXT early, see below. AC_CONFIG_COMMANDS_PRE(dnl [m4_provide_if([_AM_COMPILER_EXEEXT], [AM_CONDITIONAL([am__EXEEXT], [test -n "$EXEEXT"])])])dnl ]) dnl Hook into `_AC_COMPILER_EXEEXT' early to learn its expansion. Do not dnl add the conditional right here, as _AC_COMPILER_EXEEXT may be further dnl mangled by Autoconf and run in a shell conditional statement. m4_define([_AC_COMPILER_EXEEXT], m4_defn([_AC_COMPILER_EXEEXT])[m4_provide([_AM_COMPILER_EXEEXT])]) # When config.status generates a header, we must update the stamp-h file. # This file resides in the same directory as the config header # that is generated. The stamp files are numbered to have different names. # Autoconf calls _AC_AM_CONFIG_HEADER_HOOK (when defined) in the # loop where config.status creates the headers, so we can generate # our stamp files there. AC_DEFUN([_AC_AM_CONFIG_HEADER_HOOK], [# Compute $1's index in $config_headers. _am_arg=$1 _am_stamp_count=1 for _am_header in $config_headers :; do case $_am_header in $_am_arg | $_am_arg:* ) break ;; * ) _am_stamp_count=`expr $_am_stamp_count + 1` ;; esac done echo "timestamp for $_am_arg" >`AS_DIRNAME(["$_am_arg"])`/stamp-h[]$_am_stamp_count]) # Copyright (C) 2001, 2003, 2005, 2008, 2011 Free Software Foundation, # Inc. # # This file is free software; the Free Software Foundation # gives unlimited permission to copy and/or distribute it, # with or without modifications, as long as this notice is preserved. # serial 1 # AM_PROG_INSTALL_SH # ------------------ # Define $install_sh. AC_DEFUN([AM_PROG_INSTALL_SH], [AC_REQUIRE([AM_AUX_DIR_EXPAND])dnl if test x"${install_sh}" != xset; then case $am_aux_dir in *\ * | *\ *) install_sh="\${SHELL} '$am_aux_dir/install-sh'" ;; *) install_sh="\${SHELL} $am_aux_dir/install-sh" esac fi AC_SUBST(install_sh)]) # Copyright (C) 2003, 2005 Free Software Foundation, Inc. # # This file is free software; the Free Software Foundation # gives unlimited permission to copy and/or distribute it, # with or without modifications, as long as this notice is preserved. # serial 2 # Check whether the underlying file-system supports filenames # with a leading dot. For instance MS-DOS doesn't. AC_DEFUN([AM_SET_LEADING_DOT], [rm -rf .tst 2>/dev/null mkdir .tst 2>/dev/null if test -d .tst; then am__leading_dot=. else am__leading_dot=_ fi rmdir .tst 2>/dev/null AC_SUBST([am__leading_dot])]) # Check to see how 'make' treats includes. -*- Autoconf -*- # Copyright (C) 2001, 2002, 2003, 2005, 2009 Free Software Foundation, Inc. # # This file is free software; the Free Software Foundation # gives unlimited permission to copy and/or distribute it, # with or without modifications, as long as this notice is preserved. # serial 4 # AM_MAKE_INCLUDE() # ----------------- # Check to see how make treats includes. AC_DEFUN([AM_MAKE_INCLUDE], [am_make=${MAKE-make} cat > confinc << 'END' am__doit: @echo this is the am__doit target .PHONY: am__doit END # If we don't find an include directive, just comment out the code. AC_MSG_CHECKING([for style of include used by $am_make]) am__include="#" am__quote= _am_result=none # First try GNU make style include. echo "include confinc" > confmf # Ignore all kinds of additional output from `make'. case `$am_make -s -f confmf 2> /dev/null` in #( *the\ am__doit\ target*) am__include=include am__quote= _am_result=GNU ;; esac # Now try BSD make style include. if test "$am__include" = "#"; then echo '.include "confinc"' > confmf case `$am_make -s -f confmf 2> /dev/null` in #( *the\ am__doit\ target*) am__include=.include am__quote="\"" _am_result=BSD ;; esac fi AC_SUBST([am__include]) AC_SUBST([am__quote]) AC_MSG_RESULT([$_am_result]) rm -f confinc confmf ]) # Copyright (C) 1999, 2000, 2001, 2003, 2004, 2005, 2008 # Free Software Foundation, Inc. # # This file is free software; the Free Software Foundation # gives unlimited permission to copy and/or distribute it, # with or without modifications, as long as this notice is preserved. # serial 6 # AM_PROG_CC_C_O # -------------- # Like AC_PROG_CC_C_O, but changed for automake. AC_DEFUN([AM_PROG_CC_C_O], [AC_REQUIRE([AC_PROG_CC_C_O])dnl AC_REQUIRE([AM_AUX_DIR_EXPAND])dnl AC_REQUIRE_AUX_FILE([compile])dnl # FIXME: we rely on the cache variable name because # there is no other way. set dummy $CC am_cc=`echo $[2] | sed ['s/[^a-zA-Z0-9_]/_/g;s/^[0-9]/_/']` eval am_t=\$ac_cv_prog_cc_${am_cc}_c_o if test "$am_t" != yes; then # Losing compiler, so override with the script. # FIXME: It is wrong to rewrite CC. # But if we don't then we get into trouble of one sort or another. # A longer-term fix would be to have automake use am__CC in this case, # and then we could set am__CC="\$(top_srcdir)/compile \$(CC)" CC="$am_aux_dir/compile $CC" fi dnl Make sure AC_PROG_CC is never called again, or it will override our dnl setting of CC. m4_define([AC_PROG_CC], [m4_fatal([AC_PROG_CC cannot be called after AM_PROG_CC_C_O])]) ]) # Fake the existence of programs that GNU maintainers use. -*- Autoconf -*- # Copyright (C) 1997, 1999, 2000, 2001, 2003, 2004, 2005, 2008 # Free Software Foundation, Inc. # # This file is free software; the Free Software Foundation # gives unlimited permission to copy and/or distribute it, # with or without modifications, as long as this notice is preserved. # serial 6 # AM_MISSING_PROG(NAME, PROGRAM) # ------------------------------ AC_DEFUN([AM_MISSING_PROG], [AC_REQUIRE([AM_MISSING_HAS_RUN]) $1=${$1-"${am_missing_run}$2"} AC_SUBST($1)]) # AM_MISSING_HAS_RUN # ------------------ # Define MISSING if not defined so far and test if it supports --run. # If it does, set am_missing_run to use it, otherwise, to nothing. AC_DEFUN([AM_MISSING_HAS_RUN], [AC_REQUIRE([AM_AUX_DIR_EXPAND])dnl AC_REQUIRE_AUX_FILE([missing])dnl if test x"${MISSING+set}" != xset; then case $am_aux_dir in *\ * | *\ *) MISSING="\${SHELL} \"$am_aux_dir/missing\"" ;; *) MISSING="\${SHELL} $am_aux_dir/missing" ;; esac fi # Use eval to expand $SHELL if eval "$MISSING --run true"; then am_missing_run="$MISSING --run " else am_missing_run= AC_MSG_WARN([`missing' script is too old or missing]) fi ]) # Copyright (C) 2003, 2004, 2005, 2006, 2011 Free Software Foundation, # Inc. # # This file is free software; the Free Software Foundation # gives unlimited permission to copy and/or distribute it, # with or without modifications, as long as this notice is preserved. # serial 1 # AM_PROG_MKDIR_P # --------------- # Check for `mkdir -p'. AC_DEFUN([AM_PROG_MKDIR_P], [AC_PREREQ([2.60])dnl AC_REQUIRE([AC_PROG_MKDIR_P])dnl dnl Automake 1.8 to 1.9.6 used to define mkdir_p. We now use MKDIR_P, dnl while keeping a definition of mkdir_p for backward compatibility. dnl @MKDIR_P@ is magic: AC_OUTPUT adjusts its value for each Makefile. dnl However we cannot define mkdir_p as $(MKDIR_P) for the sake of dnl Makefile.ins that do not define MKDIR_P, so we do our own dnl adjustment using top_builddir (which is defined more often than dnl MKDIR_P). AC_SUBST([mkdir_p], ["$MKDIR_P"])dnl case $mkdir_p in [[\\/$]]* | ?:[[\\/]]*) ;; */*) mkdir_p="\$(top_builddir)/$mkdir_p" ;; esac ]) # Helper functions for option handling. -*- Autoconf -*- # Copyright (C) 2001, 2002, 2003, 2005, 2008, 2010 Free Software # Foundation, Inc. # # This file is free software; the Free Software Foundation # gives unlimited permission to copy and/or distribute it, # with or without modifications, as long as this notice is preserved. # serial 5 # _AM_MANGLE_OPTION(NAME) # ----------------------- AC_DEFUN([_AM_MANGLE_OPTION], [[_AM_OPTION_]m4_bpatsubst($1, [[^a-zA-Z0-9_]], [_])]) # _AM_SET_OPTION(NAME) # -------------------- # Set option NAME. Presently that only means defining a flag for this option. AC_DEFUN([_AM_SET_OPTION], [m4_define(_AM_MANGLE_OPTION([$1]), 1)]) # _AM_SET_OPTIONS(OPTIONS) # ------------------------ # OPTIONS is a space-separated list of Automake options. AC_DEFUN([_AM_SET_OPTIONS], [m4_foreach_w([_AM_Option], [$1], [_AM_SET_OPTION(_AM_Option)])]) # _AM_IF_OPTION(OPTION, IF-SET, [IF-NOT-SET]) # ------------------------------------------- # Execute IF-SET if OPTION is set, IF-NOT-SET otherwise. AC_DEFUN([_AM_IF_OPTION], [m4_ifset(_AM_MANGLE_OPTION([$1]), [$2], [$3])]) # Check to make sure that the build environment is sane. -*- Autoconf -*- # Copyright (C) 1996, 1997, 2000, 2001, 2003, 2005, 2008 # Free Software Foundation, Inc. # # This file is free software; the Free Software Foundation # gives unlimited permission to copy and/or distribute it, # with or without modifications, as long as this notice is preserved. # serial 5 # AM_SANITY_CHECK # --------------- AC_DEFUN([AM_SANITY_CHECK], [AC_MSG_CHECKING([whether build environment is sane]) # Just in case sleep 1 echo timestamp > conftest.file # Reject unsafe characters in $srcdir or the absolute working directory # name. Accept space and tab only in the latter. am_lf=' ' case `pwd` in *[[\\\"\#\$\&\'\`$am_lf]]*) AC_MSG_ERROR([unsafe absolute working directory name]);; esac case $srcdir in *[[\\\"\#\$\&\'\`$am_lf\ \ ]]*) AC_MSG_ERROR([unsafe srcdir value: `$srcdir']);; esac # Do `set' in a subshell so we don't clobber the current shell's # arguments. Must try -L first in case configure is actually a # symlink; some systems play weird games with the mod time of symlinks # (eg FreeBSD returns the mod time of the symlink's containing # directory). if ( set X `ls -Lt "$srcdir/configure" conftest.file 2> /dev/null` if test "$[*]" = "X"; then # -L didn't work. set X `ls -t "$srcdir/configure" conftest.file` fi rm -f conftest.file if test "$[*]" != "X $srcdir/configure conftest.file" \ && test "$[*]" != "X conftest.file $srcdir/configure"; then # If neither matched, then we have a broken ls. This can happen # if, for instance, CONFIG_SHELL is bash and it inherits a # broken ls alias from the environment. This has actually # happened. Such a system could not be considered "sane". AC_MSG_ERROR([ls -t appears to fail. Make sure there is not a broken alias in your environment]) fi test "$[2]" = conftest.file ) then # Ok. : else AC_MSG_ERROR([newly created file is older than distributed files! Check your system clock]) fi AC_MSG_RESULT(yes)]) # Copyright (C) 2001, 2003, 2005, 2011 Free Software Foundation, Inc. # # This file is free software; the Free Software Foundation # gives unlimited permission to copy and/or distribute it, # with or without modifications, as long as this notice is preserved. # serial 1 # AM_PROG_INSTALL_STRIP # --------------------- # One issue with vendor `install' (even GNU) is that you can't # specify the program used to strip binaries. This is especially # annoying in cross-compiling environments, where the build's strip # is unlikely to handle the host's binaries. # Fortunately install-sh will honor a STRIPPROG variable, so we # always use install-sh in `make install-strip', and initialize # STRIPPROG with the value of the STRIP variable (set by the user). AC_DEFUN([AM_PROG_INSTALL_STRIP], [AC_REQUIRE([AM_PROG_INSTALL_SH])dnl # Installed binaries are usually stripped using `strip' when the user # run `make install-strip'. However `strip' might not be the right # tool to use in cross-compilation environments, therefore Automake # will honor the `STRIP' environment variable to overrule this program. dnl Don't test for $cross_compiling = yes, because it might be `maybe'. if test "$cross_compiling" != no; then AC_CHECK_TOOL([STRIP], [strip], :) fi INSTALL_STRIP_PROGRAM="\$(install_sh) -c -s" AC_SUBST([INSTALL_STRIP_PROGRAM])]) # Copyright (C) 2006, 2008, 2010 Free Software Foundation, Inc. # # This file is free software; the Free Software Foundation # gives unlimited permission to copy and/or distribute it, # with or without modifications, as long as this notice is preserved. # serial 3 # _AM_SUBST_NOTMAKE(VARIABLE) # --------------------------- # Prevent Automake from outputting VARIABLE = @VARIABLE@ in Makefile.in. # This macro is traced by Automake. AC_DEFUN([_AM_SUBST_NOTMAKE]) # AM_SUBST_NOTMAKE(VARIABLE) # -------------------------- # Public sister of _AM_SUBST_NOTMAKE. AC_DEFUN([AM_SUBST_NOTMAKE], [_AM_SUBST_NOTMAKE($@)]) # Check how to create a tarball. -*- Autoconf -*- # Copyright (C) 2004, 2005, 2012 Free Software Foundation, Inc. # # This file is free software; the Free Software Foundation # gives unlimited permission to copy and/or distribute it, # with or without modifications, as long as this notice is preserved. # serial 2 # _AM_PROG_TAR(FORMAT) # -------------------- # Check how to create a tarball in format FORMAT. # FORMAT should be one of `v7', `ustar', or `pax'. # # Substitute a variable $(am__tar) that is a command # writing to stdout a FORMAT-tarball containing the directory # $tardir. # tardir=directory && $(am__tar) > result.tar # # Substitute a variable $(am__untar) that extract such # a tarball read from stdin. # $(am__untar) < result.tar AC_DEFUN([_AM_PROG_TAR], [# Always define AMTAR for backward compatibility. Yes, it's still used # in the wild :-( We should find a proper way to deprecate it ... AC_SUBST([AMTAR], ['$${TAR-tar}']) m4_if([$1], [v7], [am__tar='$${TAR-tar} chof - "$$tardir"' am__untar='$${TAR-tar} xf -'], [m4_case([$1], [ustar],, [pax],, [m4_fatal([Unknown tar format])]) AC_MSG_CHECKING([how to create a $1 tar archive]) # Loop over all known methods to create a tar archive until one works. _am_tools='gnutar m4_if([$1], [ustar], [plaintar]) pax cpio none' _am_tools=${am_cv_prog_tar_$1-$_am_tools} # Do not fold the above two line into one, because Tru64 sh and # Solaris sh will not grok spaces in the rhs of `-'. for _am_tool in $_am_tools do case $_am_tool in gnutar) for _am_tar in tar gnutar gtar; do AM_RUN_LOG([$_am_tar --version]) && break done am__tar="$_am_tar --format=m4_if([$1], [pax], [posix], [$1]) -chf - "'"$$tardir"' am__tar_="$_am_tar --format=m4_if([$1], [pax], [posix], [$1]) -chf - "'"$tardir"' am__untar="$_am_tar -xf -" ;; plaintar) # Must skip GNU tar: if it does not support --format= it doesn't create # ustar tarball either. (tar --version) >/dev/null 2>&1 && continue am__tar='tar chf - "$$tardir"' am__tar_='tar chf - "$tardir"' am__untar='tar xf -' ;; pax) am__tar='pax -L -x $1 -w "$$tardir"' am__tar_='pax -L -x $1 -w "$tardir"' am__untar='pax -r' ;; cpio) am__tar='find "$$tardir" -print | cpio -o -H $1 -L' am__tar_='find "$tardir" -print | cpio -o -H $1 -L' am__untar='cpio -i -H $1 -d' ;; none) am__tar=false am__tar_=false am__untar=false ;; esac # If the value was cached, stop now. We just wanted to have am__tar # and am__untar set. test -n "${am_cv_prog_tar_$1}" && break # tar/untar a dummy directory, and stop if the command works rm -rf conftest.dir mkdir conftest.dir echo GrepMe > conftest.dir/file AM_RUN_LOG([tardir=conftest.dir && eval $am__tar_ >conftest.tar]) rm -rf conftest.dir if test -s conftest.tar; then AM_RUN_LOG([$am__untar /dev/null 2>&1 && break fi done rm -rf conftest.dir AC_CACHE_VAL([am_cv_prog_tar_$1], [am_cv_prog_tar_$1=$_am_tool]) AC_MSG_RESULT([$am_cv_prog_tar_$1])]) AC_SUBST([am__tar]) AC_SUBST([am__untar]) ]) # _AM_PROG_TAR m4_include([../build-aux/libtool.m4]) m4_include([../build-aux/ltoptions.m4]) m4_include([../build-aux/ltsugar.m4]) m4_include([../build-aux/ltversion.m4]) m4_include([../build-aux/lt~obsolete.m4]) smalltalk-3.2.5/libffi/ChangeLog0000644000175000017500000044656312130343734013455 000000000000002012-01-19 Jakub Jelinek PR rtl-optimization/48496 * src/ia64/ffi.c (ffi_call): Fix up aliasing violations. 2010-08-20 Mark Wielaard * src/closures.c (open_temp_exec_file_mnt): Check if getmntent_r returns NULL. 2010-08-09 Andreas Tobler * configure.ac: Add target powerpc64-*-freebsd*. * configure: Regenerate. * testsuite/libffi.call/cls_align_longdouble_split.c: Pass -mlong-double-128 only to linux targets. * testsuite/libffi.call/cls_align_longdouble_split2.c: Likewise. * testsuite/libffi.call/cls_longdouble.c: Likewise. * testsuite/libffi.call/huge_struct.c: Likewise. 2010-07-10 Evan Phoenix * src/closures.c (selinux_enabled_check): Fix strncmp usage bug. 2010-07-07 Dan Horák * include/ffi.h.in: Protect #define with #ifndef. * src/powerpc/ffitarget.h: Ditto. * src/s390/ffitarget.h: Ditto. * src/sparc/ffitarget.h: Ditto. 2010-07-07 Neil Roberts * src/x86/sysv.S (ffi_call_SYSV): Align the stack pointer to 16-bytes. 2010-07-02 Jakub Jelinek * Makefile.am (AM_MAKEFLAGS): Pass also mandir to submakes. * Makefile.in: Regenerated. 2010-05-19 Rainer Orth * configure.ac (libffi_cv_as_x86_pcrel): Check for illegal in as output, too. (libffi_cv_as_ascii_pseudo_op): Check for .ascii. (libffi_cv_as_string_pseudo_op): Check for .string. * configure: Regenerate. * fficonfig.h.in: Regenerate. * src/x86/sysv.S (.eh_frame): Use .ascii, .string or error. 2010-05-05 Michael Kohler * src/dlmalloc.c (dlfree): Fix spelling. * src/ia64/ffi.c (ffi_prep_cif_machdep): Ditto. * configure.ac: Ditto. * configure: Rebuilt. 2010-04-13 Dan Witte * msvcc.sh: Build with -W3 instead of -Wall. * src/powerpc/ffi_darwin.c: Remove build warnings. * src/x86/ffi.c: Ditto. * src/x86/ffitarget.h: Ditto. 2010-04-12 Dan Witte Walter Meinl * configure.ac: Add OS/2 support. * configure: Rebuilt. * src/closures.c: Ditto. * src/dlmalloc.c: Ditto. * src/x86/win32.S: Ditto. 2010-04-07 Jakub Jelinek * testsuite/libffi.call/err_bad_abi.c: Remove unused args variable. 2010-04-02 Ralf Wildenhues * Makefile.in: Regenerate. * aclocal.m4: Regenerate. * include/Makefile.in: Regenerate. * man/Makefile.in: Regenerate. * testsuite/Makefile.in: Regenerate. 2010-03-15 Rainer Orth * configure.ac (libffi_cv_as_x86_64_unwind_section_type): New test. * configure: Regenerate. * fficonfig.h.in: Regenerate. * libffi/src/x86/unix64.S (.eh_frame) [HAVE_AS_X86_64_UNWIND_SECTION_TYPE]: Use @unwind section type. 2010-03-14 Matthias Klose * src/x86/ffi64.c: Fix typo in comment. * src/x86/ffi.c: Use /* ... */ comment style. 2010-02-24 Rainer Orth * doc/libffi.texi (The Closure API): Fix typo. * doc/libffi.info: Remove. 2010-02-15 Matthias Klose * src/arm/sysv.S (__ARM_ARCH__): Define for processor __ARM_ARCH_7EM__. 2010-01-15 Anthony Green * README: Add notes on building with Microsoft Visual C++. 2010-01-15 Daniel Witte * msvcc.sh: New file. * src/x86/win32.S: Port assembly routines to MSVC and #ifdef. * src/x86/ffi.c: Tweak function declaration and remove excess parens. * include/ffi.h.in: Add __declspec(align(8)) to typedef struct ffi_closure. * src/x86/ffi.c: Merge ffi_call_SYSV and ffi_call_STDCALL into new function ffi_call_win32 on X86_WIN32. * src/x86/win32.S (ffi_call_SYSV): Rename to ffi_call_win32. (ffi_call_STDCALL): Remove. * src/prep_cif.c (ffi_prep_cif): Move stack space allocation code to ffi_prep_cif_machdep for x86. * src/x86/ffi.c (ffi_prep_cif_machdep): To here. 2010-01-15 Oliver Kiddle * src/x86/ffitarget.h (ffi_abi): Check for __i386 and __amd64 for Sun Studio compiler compatibility. 2010-01-12 Conrad Irwin * doc/libffi.texi: Add closure example. 2010-01-07 Rainer Orth PR libffi/40701 * testsuite/libffi.call/ffitest.h [__alpha__ && __osf__] (PRIdLL, PRIuLL, PRId64, PRIu64, PRIuPTR): Define. * testsuite/libffi.call/cls_align_sint64.c: Add -Wno-format on alpha*-dec-osf*. * testsuite/libffi.call/cls_align_uint64.c: Likewise. * testsuite/libffi.call/cls_ulonglong.c: Likewise. * testsuite/libffi.call/return_ll1.c: Likewise. * testsuite/libffi.call/stret_medium2.c: Likewise. * testsuite/libffi.special/ffitestcxx.h (allocate_mmap): Cast MAP_FAILED to char *. 2010-01-06 Rainer Orth * src/mips/n32.S: Use .abicalls and .eh_frame with __GNUC__. 2009-12-31 Anthony Green * README: Update for libffi 3.0.9. 2009-12-27 Matthias Klose * configure.ac (HAVE_LONG_DOUBLE): Define for mips when appropriate. * configure: Rebuilt. 2009-12-26 Anthony Green * testsuite/libffi.call/cls_longdouble_va.c: Mark as xfail for avr32*-*-*. * testsuite/libffi.call/cls_double_va.c: Ditto. 2009-12-26 Andreas Tobler * testsuite/libffi.call/ffitest.h: Conditionally include stdint.h and inttypes.h. * testsuite/libffi.special/unwindtest.cc: Ditto. 2009-12-26 Andreas Tobler * configure.ac: Add amd64-*-openbsd*. * configure: Rebuilt. * testsuite/lib/libffi-dg.exp (libffi_target_compile): Link openbsd programs with -lpthread. 2009-12-26 Anthony Green * testsuite/libffi.call/cls_double_va.c, testsuite/libffi.call/cls_longdouble.c, testsuite/libffi.call/cls_longdouble_va.c, testsuite/libffi.call/cls_pointer.c, testsuite/libffi.call/cls_pointer_stack.c: Remove xfail for mips*-*-* and arm*-*-*. * testsuite/libffi.call/cls_align_longdouble_split.c, testsuite/libffi.call/cls_align_longdouble_split2.c, testsuite/libffi.call/stret_medium2.c, testsuite/libffi.call/stret_medium.c, testsuite/libffi.call/stret_large.c, testsuite/libffi.call/stret_large2.c: Remove xfail for arm*-*-*. 2009-12-31 Kay Tietz * testsuite/libffi.call/ffitest.h, testsuite/libffi.special/ffitestcxx.h (PRIdLL, PRuLL): Fix definitions. 2009-12-31 Carlo Bramini * configure.ac (AM_LTLDFLAGS): Define for windows hosts. * Makefile.am (libffi_la_LDFLAGS): Add AM_LTLDFLAGS. * configure: Rebuilt. * Makefile.in: Rebuilt. 2009-12-31 Anthony Green Blake Chaffin. * testsuite/libffi.call/huge_struct.c: New test case from Blake Chaffin @ Apple. 2009-12-28 David Edelsohn * src/powerpc/ffi_darwin.c (ffi_prep_args): Copy abi and nargs to local variables. (aix_adjust_aggregate_sizes): New function. (ffi_prep_cif_machdep): Call it. 2009-12-26 Andreas Tobler * configure.ac: Define FFI_MMAP_EXEC_WRIT for the given targets. * configure: Regenerate. * fficonfig.h.in: Likewise. * src/closures.c: Remove the FFI_MMAP_EXEC_WRIT definition for Solaris/x86. 2009-12-26 Andreas Schwab * src/powerpc/ffi.c (ffi_prep_args_SYSV): Advance intarg_count when a float arguments is passed in memory. (ffi_closure_helper_SYSV): Mark general registers as used up when a 64bit or soft-float long double argument is passed in memory. 2009-12-25 Matthias Klose * man/ffi_call.3: Fix #include in examples. * doc/libffi.texi: Add dircategory. 2009-12-25 Frank Everdij * include/ffi.h.in: Placed '__GNUC__' ifdef around '__attribute__((aligned(8)))' in ffi_closure, fixes compile for IRIX MIPSPro c99. * include/ffi_common.h: Added '__sgi' define to non '__attribute__((__mode__()))' integer typedefs. * src/mips/ffi.c (ffi_call, ffi_closure_mips_inner_O32, ffi_closure_mips_inner_N32): Added 'defined(_MIPSEB)' to BE check. (ffi_closure_mips_inner_O32, ffi_closure_mips_inner_N32): Added FFI_LONGDOUBLE support and alignment(N32 only). * src/mips/ffitarget.h: Corrected '#include ' for IRIX and fixed non '__attribute__((__mode__()))' integer typedefs. * src/mips/n32.S: Put '#ifdef linux' around '.abicalls' and '.eh_frame' since they are Linux/GNU Assembler specific. 2009-12-25 Bradley Smith * configure.ac, Makefile.am, src/avr32/ffi.c, src/avr32/ffitarget.h, src/avr32/sysv.S: Add AVR32 port. * configure, Makefile.in: Rebuilt. 2009-12-21 Andreas Tobler * configure.ac: Make i?86 build on FreeBSD and OpenBSD. * configure: Regenerate. 2009-12-15 John David Anglin * testsuite/libffi.call/ffitest.h: Define PRIuPTR on PA HP-UX. 2009-12-13 John David Anglin * src/pa/ffi.c (ffi_closure_inner_pa32): Handle FFI_TYPE_LONGDOUBLE type on HP-UX. 2009-12-11 Eric Botcazou * src/sparc/ffi.c (ffi_closure_sparc_inner_v9): Properly align 'long double' arguments. 2009-12-11 Eric Botcazou * testsuite/libffi.call/ffitest.h: Define PRIuPTR on Solaris < 10. 2009-12-10 Rainer Orth PR libffi/40700 * src/closures.c [X86_64 && __sun__ && __svr4__] (FFI_MMAP_EXEC_WRIT): Define. 2009-12-08 David Daney * testsuite/libffi.call/stret_medium.c: Remove xfail for mips*-*-* * testsuite/libffi.call/cls_align_longdouble_split2.c: Same. * testsuite/libffi.call/stret_large.c: Same. * testsuite/libffi.call/cls_align_longdouble_split.c: Same. * testsuite/libffi.call/stret_large2.c: Same. * testsuite/libffi.call/stret_medium2.c: Same. 2009-12-07 David Edelsohn * src/powerpc/aix_closure.S (libffi_closure_ASM): Fix tablejump typo. 2009-12-05 David Edelsohn * src/powerpc/aix.S: Update AIX32 code to be consistent with AIX64 code. * src/powerpc/aix_closure.S: Same. 2009-12-05 Ralf Wildenhues * Makefile.in: Regenerate. * configure: Regenerate. * include/Makefile.in: Regenerate. * man/Makefile.in: Regenerate. * testsuite/Makefile.in: Regenerate. 2009-12-04 David Edelsohn * src/powerpc/aix_closure.S: Reorganize 64-bit code to match linux64_closure.S. 2009-12-04 Uros Bizjak PR libffi/41908 * src/x86/ffi64.c (classify_argument): Update from gcc/config/i386/i386.c. (ffi_closure_unix64_inner): Do not use the address of two consecutive SSE registers directly. * testsuite/libffi.call/cls_dbls_struct.c (main): Remove xfail for x86_64 linux targets. 2009-12-04 David Edelsohn * src/powerpc/ffi_darwin.c (ffi_closure_helper_DARWIN): Increment pfr for long double split between fpr13 and stack. 2009-12-03 David Edelsohn * src/powerpc/ffi_darwin.c (ffi_prep_args): Increment next_arg and fparg_count twice for long double. 2009-12-03 David Edelsohn PR libffi/42243 * src/powerpc/ffi_darwin.c (ffi_prep_args): Remove extra parentheses. 2009-12-03 Uros Bizjak * testsuite/libffi.call/cls_longdouble_va.c (main): Fix format string. Remove xfails for x86 linux targets. 2009-12-02 David Edelsohn * src/powerpc/ffi_darwin.c (ffi_prep_args): Fix typo in INT64 case. 2009-12-01 David Edelsohn * src/powerpc/aix.S (ffi_call_AIX): Convert to more standard register usage. Call ffi_prep_args directly. Add long double return value support. * src/powerpc/ffi_darwin.c (ffi_prep_args): Double arg increment applies to FFI_TYPE_DOUBLE. Correct fpr_base increment typo. Separate FFI_TYPE_SINT32 and FFI_TYPE_UINT32 cases. (ffi_prep_cif_machdep): Only 16 byte stack alignment in 64 bit mode. (ffi_closure_helper_DARWIN): Remove nf and ng counters. Move temp into case. * src/powerpc/aix_closure.S: Maintain 16 byte stack alignment. Allocate result area between params and FPRs. 2009-11-30 David Edelsohn PR target/35484 * src/powerpc/ffitarget.h (POWERPC64): Define for PPC64 Linux and AIX64. * src/powerpc/aix.S: Implement AIX64 version. * src/powerpc/aix_closure.S: Implement AIX64 version. (ffi_closure_ASM): Use extsb, lha and displament addresses. * src/powerpc/ffi_darwin.c (ffi_prep_args): Implement AIX64 support. (ffi_prep_cif_machdep): Same. (ffi_call): Same. (ffi_closure_helper_DARWIN): Same. 2009-11-02 Andreas Tobler PR libffi/41908 * testsuite/libffi.call/testclosure.c: New test. 2009-09-28 Kai Tietz * src/x86/win64.S (_ffi_call_win64 stack): Remove for gnu assembly version use of ___chkstk. 2009-09-23 Matthias Klose PR libffi/40242, PR libffi/41443 * src/arm/sysv.S (__ARM_ARCH__): Define for processors __ARM_ARCH_6T2__, __ARM_ARCH_6M__, __ARM_ARCH_7__, __ARM_ARCH_7A__, __ARM_ARCH_7R__, __ARM_ARCH_7M__. Change the conditionals to __SOFTFP__ || __ARM_EABI__ for -mfloat-abi=softfp to work. 2009-09-17 Loren J. Rittle PR testsuite/32843 (strikes again) * src/x86/ffi.c (ffi_prep_cif_machdep): Add X86_FREEBSD to enable proper extension on char and short. 2009-09-15 David Daney * src/java_raw_api.c (ffi_java_raw_to_rvalue): Remove special handling for FFI_TYPE_POINTER. * src/mips/ffitarget.h (FFI_TYPE_STRUCT_D_SOFT, FFI_TYPE_STRUCT_F_SOFT, FFI_TYPE_STRUCT_DD_SOFT, FFI_TYPE_STRUCT_FF_SOFT, FFI_TYPE_STRUCT_FD_SOFT, FFI_TYPE_STRUCT_DF_SOFT, FFI_TYPE_STRUCT_SOFT): New defines. (FFI_N32_SOFT_FLOAT, FFI_N64_SOFT_FLOAT): New ffi_abi enumerations. (enum ffi_abi): Set FFI_DEFAULT_ABI for soft-float. * src/mips/n32.S (ffi_call_N32): Add handling for soft-float structure and pointer returns. (ffi_closure_N32): Add handling for pointer returns. * src/mips/ffi.c (ffi_prep_args, calc_n32_struct_flags, calc_n32_return_struct_flags): Handle soft-float. (ffi_prep_cif_machdep): Handle soft-float, fix pointer handling. (ffi_call_N32): Declare proper argument types. (ffi_call, copy_struct_N32, ffi_closure_mips_inner_N32): Handle soft-float. 2009-08-24 Ralf Wildenhues * configure.ac (AC_PREREQ): Bump to 2.64. 2009-08-22 Ralf Wildenhues * Makefile.am (install-html, install-pdf): Remove. * Makefile.in: Regenerate. * Makefile.in: Regenerate. * aclocal.m4: Regenerate. * configure: Regenerate. * fficonfig.h.in: Regenerate. * include/Makefile.in: Regenerate. * man/Makefile.in: Regenerate. * testsuite/Makefile.in: Regenerate. 2009-07-30 Ralf Wildenhues * configure.ac (_AC_ARG_VAR_PRECIOUS): Use m4_rename_force. 2009-07-24 Dave Korn PR libffi/40807 * src/x86/ffi.c (ffi_prep_cif_machdep): Also use sign/zero-extending return types for X86_WIN32. * src/x86/win32.S (_ffi_call_SYSV): Handle omitted return types. (_ffi_call_STDCALL, _ffi_closure_SYSV, _ffi_closure_raw_SYSV, _ffi_closure_STDCALL): Likewise. * src/closures.c (is_selinux_enabled): Define to const 0 for Cygwin. (dlmmap, dlmunmap): Also use these functions on Cygwin. 2009-07-11 Richard Sandiford PR testsuite/40699 PR testsuite/40707 PR testsuite/40709 * testsuite/lib/libffi-dg.exp: Revert 2009-07-02, 2009-07-01 and 2009-06-30 commits. 2009-07-01 Richard Sandiford * testsuite/lib/libffi-dg.exp (libffi-init): Set ld_library_path to "" before adding paths. (This reinstates an assignment that was removed by my 2009-06-30 commit, but changes the initial value from "." to "".) 2009-07-01 H.J. Lu PR testsuite/40601 * testsuite/lib/libffi-dg.exp (libffi-init): Properly set gccdir. Adjust ld_library_path for gcc only if gccdir isn't empty. 2009-06-30 Richard Sandiford * testsuite/lib/libffi-dg.exp (libffi-init): Don't add "." to ld_library_path. Use add_path. Add just find_libgcc_s to ld_library_path, not every libgcc multilib directory. 2009-06-16 Wim Lewis * src/powerpc/ffi.c: Avoid clobbering cr3 and cr4, which are supposed to be callee-saved. * src/powerpc/sysv.S (small_struct_return_value): Fix overrun of return buffer for odd-size structs. 2009-06-16 Andreas Tobler PR libffi/40444 * testsuite/lib/libffi-dg.exp (libffi_target_compile): Add allow_stack_execute for Darwin. 2009-06-16 Andrew Haley * configure.ac (TARGETDIR): Add missing blank lines. * configure: Regenerate. 2009-06-16 Andrew Haley * testsuite/libffi.call/cls_align_sint64.c, testsuite/libffi.call/cls_align_uint64.c, testsuite/libffi.call/cls_longdouble_va.c, testsuite/libffi.call/cls_ulonglong.c, testsuite/libffi.call/return_ll1.c, testsuite/libffi.call/stret_medium2.c: Fix printf format specifiers. * testsuite/libffi.call/ffitest.h, testsuite/libffi.special/ffitestcxx.h (PRIdLL, PRIuLL): Define. 2009-06-15 Andrew Haley * testsuite/libffi.call/err_bad_typedef.c: xfail everywhere. * testsuite/libffi.call/err_bad_abi.c: Likewise. 2009-06-12 Andrew Haley * Makefile.am: Remove info_TEXINFOS. 2009-06-12 Andrew Haley * ChangeLog.libffi: testsuite/libffi.call/cls_align_sint64.c, testsuite/libffi.call/cls_align_uint64.c, testsuite/libffi.call/cls_ulonglong.c, testsuite/libffi.call/return_ll1.c, testsuite/libffi.call/stret_medium2.c: Fix printf format specifiers. testsuite/libffi.special/unwindtest.cc: include stdint.h. 2009-06-11 Timothy Wall * Makefile.am, configure.ac, include/ffi.h.in, include/ffi_common.h, src/closures.c, src/dlmalloc.c, src/x86/ffi.c, src/x86/ffitarget.h, src/x86/win64.S (new), README: Added win64 support (mingw or MSVC) * Makefile.in, include/Makefile.in, man/Makefile.in, testsuite/Makefile.in, configure, aclocal.m4: Regenerated * ltcf-c.sh: properly escape cygwin/w32 path * man/ffi_call.3: Clarify size requirements for return value. * src/x86/ffi64.c: Fix filename in comment. * src/x86/win32.S: Remove unused extern. * testsuite/libffi.call/closure_fn0.c, testsuite/libffi.call/closure_fn1.c, testsuite/libffi.call/closure_fn2.c, testsuite/libffi.call/closure_fn3.c, testsuite/libffi.call/closure_fn4.c, testsuite/libffi.call/closure_fn5.c, testsuite/libffi.call/closure_fn6.c, testsuite/libffi.call/closure_stdcall.c, testsuite/libffi.call/cls_12byte.c, testsuite/libffi.call/cls_16byte.c, testsuite/libffi.call/cls_18byte.c, testsuite/libffi.call/cls_19byte.c, testsuite/libffi.call/cls_1_1byte.c, testsuite/libffi.call/cls_20byte.c, testsuite/libffi.call/cls_20byte1.c, testsuite/libffi.call/cls_24byte.c, testsuite/libffi.call/cls_2byte.c, testsuite/libffi.call/cls_3_1byte.c, testsuite/libffi.call/cls_3byte1.c, testsuite/libffi.call/cls_3byte2.c, testsuite/libffi.call/cls_4_1byte.c, testsuite/libffi.call/cls_4byte.c, testsuite/libffi.call/cls_5_1_byte.c, testsuite/libffi.call/cls_5byte.c, testsuite/libffi.call/cls_64byte.c, testsuite/libffi.call/cls_6_1_byte.c, testsuite/libffi.call/cls_6byte.c, testsuite/libffi.call/cls_7_1_byte.c, testsuite/libffi.call/cls_7byte.c, testsuite/libffi.call/cls_8byte.c, testsuite/libffi.call/cls_9byte1.c, testsuite/libffi.call/cls_9byte2.c, testsuite/libffi.call/cls_align_double.c, testsuite/libffi.call/cls_align_float.c, testsuite/libffi.call/cls_align_longdouble.c, testsuite/libffi.call/cls_align_longdouble_split.c, testsuite/libffi.call/cls_align_longdouble_split2.c, testsuite/libffi.call/cls_align_pointer.c, testsuite/libffi.call/cls_align_sint16.c, testsuite/libffi.call/cls_align_sint32.c, testsuite/libffi.call/cls_align_sint64.c, testsuite/libffi.call/cls_align_uint16.c, testsuite/libffi.call/cls_align_uint32.c, testsuite/libffi.call/cls_align_uint64.c, testsuite/libffi.call/cls_dbls_struct.c, testsuite/libffi.call/cls_double.c, testsuite/libffi.call/cls_double_va.c, testsuite/libffi.call/cls_float.c, testsuite/libffi.call/cls_longdouble.c, testsuite/libffi.call/cls_longdouble_va.c, testsuite/libffi.call/cls_multi_schar.c, testsuite/libffi.call/cls_multi_sshort.c, testsuite/libffi.call/cls_multi_sshortchar.c, testsuite/libffi.call/cls_multi_uchar.c, testsuite/libffi.call/cls_multi_ushort.c, testsuite/libffi.call/cls_multi_ushortchar.c, testsuite/libffi.call/cls_pointer.c, testsuite/libffi.call/cls_pointer_stack.c, testsuite/libffi.call/cls_schar.c, testsuite/libffi.call/cls_sint.c, testsuite/libffi.call/cls_sshort.c, testsuite/libffi.call/cls_uchar.c, testsuite/libffi.call/cls_uint.c, testsuite/libffi.call/cls_ulonglong.c, testsuite/libffi.call/cls_ushort.c, testsuite/libffi.call/err_bad_abi.c, testsuite/libffi.call/err_bad_typedef.c, testsuite/libffi.call/float2.c, testsuite/libffi.call/huge_struct.c, testsuite/libffi.call/nested_struct.c, testsuite/libffi.call/nested_struct1.c, testsuite/libffi.call/nested_struct10.c, testsuite/libffi.call/nested_struct2.c, testsuite/libffi.call/nested_struct3.c, testsuite/libffi.call/nested_struct4.c, testsuite/libffi.call/nested_struct5.c, testsuite/libffi.call/nested_struct6.c, testsuite/libffi.call/nested_struct7.c, testsuite/libffi.call/nested_struct8.c, testsuite/libffi.call/nested_struct9.c, testsuite/libffi.call/problem1.c, testsuite/libffi.call/return_ldl.c, testsuite/libffi.call/return_ll1.c, testsuite/libffi.call/stret_large.c, testsuite/libffi.call/stret_large2.c, testsuite/libffi.call/stret_medium.c, testsuite/libffi.call/stret_medium2.c, testsuite/libffi.special/unwindtest.cc: use ffi_closure_alloc instead of checking for MMAP. Use intptr_t instead of long casts. 2009-06-11 Kaz Kojima * testsuite/libffi.call/cls_longdouble_va.c: Add xfail sh*-*-linux-*. * testsuite/libffi.call/err_bad_abi.c: Add xfail sh*-*-*. * testsuite/libffi.call/err_bad_typedef.c: Likewise. 2009-06-09 Andrew Haley * src/x86/freebsd.S: Add missing file. 2009-06-08 Andrew Haley Import from libffi 3.0.8: * doc/libffi.texi: New file. * doc/libffi.info: Likewise. * doc/stamp-vti: Likewise. * man/Makefile.am: New file. * man/ffi_call.3: New file. * Makefile.am (EXTRA_DIST): Add src/x86/darwin64.S, src/dlmalloc.c. (nodist_libffi_la_SOURCES): Add X86_FREEBSD. * configure.ac: Bump version to 3.0.8. parisc*-*-linux*: Add. i386-*-freebsd* | i386-*-openbsd*: Add. powerpc-*-beos*: Add. AM_CONDITIONAL X86_FREEBSD: Add. AC_CONFIG_FILES: Add man/Makefile. * include/ffi.h.in (FFI_FN): Change void (*)() to void (*)(void). 2009-06-08 Andrew Haley * README: Import from libffi 3.0.8. 2009-06-08 Andrew Haley * testsuite/libffi.call/err_bad_abi.c: Add xfails. * testsuite/libffi.call/cls_longdouble_va.c: Add xfails. * testsuite/libffi.call/cls_dbls_struct.c: Add xfail x86_64-*-linux-*. * testsuite/libffi.call/err_bad_typedef.c: Add xfails. * testsuite/libffi.call/stret_medium2.c: Add __UNUSED__ to args. * testsuite/libffi.call/stret_medium.c: Likewise. * testsuite/libffi.call/stret_large2.c: Likewise. * testsuite/libffi.call/stret_large.c: Likewise. 2008-12-26 Timothy Wall * testsuite/libffi.call/cls_longdouble.c, testsuite/libffi.call/cls_longdouble_va.c, testsuite/libffi.call/cls_align_longdouble.c, testsuite/libffi.call/cls_align_longdouble_split.c, testsuite/libffi.call/cls_align_longdouble_split2.c: mark expected failures on x86_64 cygwin/mingw. 2008-12-22 Timothy Wall * testsuite/libffi.call/closure_fn0.c, testsuite/libffi.call/closure_fn1.c, testsuite/libffi.call/closure_fn2.c, testsuite/libffi.call/closure_fn3.c, testsuite/libffi.call/closure_fn4.c, testsuite/libffi.call/closure_fn5.c, testsuite/libffi.call/closure_fn6.c, testsuite/libffi.call/closure_loc_fn0.c, testsuite/libffi.call/closure_stdcall.c, testsuite/libffi.call/cls_align_pointer.c, testsuite/libffi.call/cls_pointer.c, testsuite/libffi.call/cls_pointer_stack.c: use portable cast from pointer to integer (intptr_t). * testsuite/libffi.call/cls_longdouble.c: disable for win64. 2008-07-24 Anthony Green * testsuite/libffi.call/cls_dbls_struct.c, testsuite/libffi.call/cls_double_va.c, testsuite/libffi.call/cls_longdouble.c, testsuite/libffi.call/cls_longdouble_va.c, testsuite/libffi.call/cls_pointer.c, testsuite/libffi.call/cls_pointer_stack.c, testsuite/libffi.call/err_bad_abi.c: Clean up failures from compiler warnings. 2008-03-04 Anthony Green Blake Chaffin hos@tamanegi.org * testsuite/libffi.call/cls_align_longdouble_split2.c testsuite/libffi.call/cls_align_longdouble_split.c testsuite/libffi.call/cls_dbls_struct.c testsuite/libffi.call/cls_double_va.c testsuite/libffi.call/cls_longdouble.c testsuite/libffi.call/cls_longdouble_va.c testsuite/libffi.call/cls_pointer.c testsuite/libffi.call/cls_pointer_stack.c testsuite/libffi.call/err_bad_abi.c testsuite/libffi.call/err_bad_typedef.c testsuite/libffi.call/stret_large2.c testsuite/libffi.call/stret_large.c testsuite/libffi.call/stret_medium2.c testsuite/libffi.call/stret_medium.c: New tests from Apple. 2009-06-05 Andrew Haley * src/x86/ffitarget.h, src/x86/ffi.c: Merge stdcall changes from libffi. 2009-06-04 Andrew Haley * src/x86/ffitarget.h, src/x86/win32.S, src/x86/ffi.c: Back out stdcall changes. 2008-02-26 Anthony Green Thomas Heller * src/x86/ffi.c (ffi_closure_SYSV_inner): Change C++ comment to C comment. 2008-02-03 Timothy Wall * src/x86/ffi.c (FFI_INIT_TRAMPOLINE_STDCALL): Calculate jump return offset based on code pointer, not data pointer. 2008-01-31 Timothy Wall * testsuite/libffi.call/closure_stdcall.c: Add test for stdcall closures. * src/x86/ffitarget.h: Increase size of trampoline for stdcall closures. * src/x86/win32.S: Add assembly for stdcall closure. * src/x86/ffi.c: Initialize stdcall closure trampoline. 2009-06-04 Andrew Haley * include/ffi.h.in: Change void (*)() to void (*)(void). * src/x86/ffi.c: Likewise. 2009-06-04 Andrew Haley * src/powerpc/ppc_closure.S: Insert licence header. * src/powerpc/linux64_closure.S: Likewise. * src/m68k/sysv.S: Likewise. * src/sh64/ffi.c: Change void (*)() to void (*)(void). * src/powerpc/ffi.c: Likewise. * src/powerpc/ffi_darwin.c: Likewise. * src/m32r/ffi.c: Likewise. * src/sh64/ffi.c: Likewise. * src/x86/ffi64.c: Likewise. * src/alpha/ffi.c: Likewise. * src/alpha/osf.S: Likewise. * src/frv/ffi.c: Likewise. * src/s390/ffi.c: Likewise. * src/pa/ffi.c: Likewise. * src/pa/hpux32.S: Likewise. * src/ia64/unix.S: Likewise. * src/ia64/ffi.c: Likewise. * src/sparc/ffi.c: Likewise. * src/mips/ffi.c: Likewise. * src/sh/ffi.c: Likewise. 2008-02-15 David Daney * src/mips/ffi.c (USE__BUILTIN___CLEAR_CACHE): Define (conditionally), and use it to include cachectl.h. (ffi_prep_closure_loc): Fix cache flushing. * src/mips/ffitarget.h (_ABIN32, _ABI64, _ABIO32): Define. 2009-06-04 Andrew Haley include/ffi.h.in, src/arm/ffitarget.h, src/arm/ffi.c, src/arm/sysv.S, src/powerpc/ffitarget.h, src/closures.c, src/sh64/ffitarget.h, src/sh64/ffi.c, src/sh64/sysv.S, src/types.c, src/x86/ffi64.c, src/x86/ffitarget.h, src/x86/win32.S, src/x86/darwin.S, src/x86/ffi.c, src/x86/sysv.S, src/x86/unix64.S, src/alpha/ffitarget.h, src/alpha/ffi.c, src/alpha/osf.S, src/m68k/ffitarget.h, src/frv/ffitarget.h, src/frv/ffi.c, src/s390/ffitarget.h, src/s390/sysv.S, src/cris/ffitarget.h, src/pa/linux.S, src/pa/ffitarget.h, src/pa/ffi.c, src/raw_api.c, src/ia64/ffitarget.h, src/ia64/unix.S, src/ia64/ffi.c, src/ia64/ia64_flags.h, src/java_raw_api.c, src/debug.c, src/sparc/v9.S, src/sparc/ffitarget.h, src/sparc/ffi.c, src/sparc/v8.S, src/mips/ffitarget.h, src/mips/n32.S, src/mips/o32.S, src/mips/ffi.c, src/prep_cif.c, src/sh/ffitarget.h, src/sh/ffi.c, src/sh/sysv.S: Update license text. 2009-05-22 Dave Korn * src/x86/win32.S (_ffi_closure_STDCALL): New function. (.eh_frame): Add FDE for it. 2009-05-22 Dave Korn * configure.ac: Also check if assembler supports pc-relative relocs on X86_WIN32 targets. * configure: Regenerate. * src/x86/win32.S (ffi_prep_args): Declare extern, not global. (_ffi_call_SYSV): Add missing function type symbol .def and add EH markup labels. (_ffi_call_STDCALL): Likewise. (_ffi_closure_SYSV): Likewise. (_ffi_closure_raw_SYSV): Likewise. (.eh_frame): Add hand-crafted EH data. 2009-04-09 Jakub Jelinek * testsuite/lib/libffi-dg.exp: Change copyright header to refer to version 3 of the GNU General Public License and to point readers at the COPYING3 file and the FSF's license web page. * testsuite/libffi.call/call.exp: Likewise. * testsuite/libffi.special/special.exp: Likewise. 2009-03-01 Ralf Wildenhues * configure: Regenerate. 2008-12-18 Rainer Orth PR libffi/26048 * configure.ac (HAVE_AS_X86_PCREL): New test. * configure: Regenerate. * fficonfig.h.in: Regenerate. * src/x86/sysv.S [!FFI_NO_RAW_API]: Precalculate RAW_CLOSURE_CIF_OFFSET, RAW_CLOSURE_FUN_OFFSET, RAW_CLOSURE_USER_DATA_OFFSET for the Solaris 10/x86 assembler. (.eh_frame): Only use SYMBOL-. iff HAVE_AS_X86_PCREL. * src/x86/unix64.S (.Lstore_table): Move to .text section. (.Lload_table): Likewise. (.eh_frame): Only use SYMBOL-. iff HAVE_AS_X86_PCREL. 2008-12-18 Ralf Wildenhues * configure: Regenerate. 2008-11-21 Eric Botcazou * src/sparc/ffi.c (ffi_prep_cif_machdep): Add support for signed/unsigned int8/16 return values. * src/sparc/v8.S (ffi_call_v8): Likewise. (ffi_closure_v8): Likewise. 2008-09-26 Peter O'Gorman Steve Ellcey * configure: Regenerate for new libtool. * Makefile.in: Ditto. * include/Makefile.in: Ditto. * aclocal.m4: Ditto. 2008-08-25 Andreas Tobler * src/powerpc/ffitarget.h (ffi_abi): Add FFI_LINUX and FFI_LINUX_SOFT_FLOAT to the POWERPC_FREEBSD enum. Add note about flag bits used for FFI_SYSV_TYPE_SMALL_STRUCT. Adjust copyright notice. * src/powerpc/ffi.c: Add two new flags to indicate if we have one register or two register to use for FFI_SYSV structs. (ffi_prep_cif_machdep): Pass the right register flag introduced above. (ffi_closure_helper_SYSV): Fix the return type for FFI_SYSV_TYPE_SMALL_STRUCT. Comment. Adjust copyright notice. 2008-07-16 Kaz Kojima * src/sh/ffi.c (ffi_prep_closure_loc): Turn INSN into an unsigned int. 2008-06-17 Ralf Wildenhues * configure: Regenerate. * include/Makefile.in: Regenerate. * testsuite/Makefile.in: Regenerate. 2008-06-07 Joseph Myers * configure.ac (parisc*-*-linux*, powerpc-*-sysv*, powerpc-*-beos*): Remove. * configure: Regenerate. 2008-05-09 Julian Brown * Makefile.am (LTLDFLAGS): New. (libffi_la_LDFLAGS): Use above. * Makefile.in: Regenerate. 2008-04-18 Paolo Bonzini PR bootstrap/35457 * aclocal.m4: Regenerate. * configure: Regenerate. 2008-03-26 Kaz Kojima * src/sh/sysv.S: Add .note.GNU-stack on Linux. * src/sh64/sysv.S: Likewise. 2008-03-26 Daniel Jacobowitz * src/arm/sysv.S: Fix ARM comment marker. 2008-03-26 Jakub Jelinek * src/alpha/osf.S: Add .note.GNU-stack on Linux. * src/s390/sysv.S: Likewise. * src/powerpc/ppc_closure.S: Likewise. * src/powerpc/sysv.S: Likewise. * src/x86/unix64.S: Likewise. * src/x86/sysv.S: Likewise. * src/sparc/v8.S: Likewise. * src/sparc/v9.S: Likewise. * src/m68k/sysv.S: Likewise. * src/arm/sysv.S: Likewise. 2008-03-16 Ralf Wildenhues * aclocal.m4: Regenerate. * configure: Likewise. * Makefile.in: Likewise. * include/Makefile.in: Likewise. * testsuite/Makefile.in: Likewise. 2008-02-12 Bjoern Koenig Andreas Tobler * configure.ac: Add amd64-*-freebsd* target. * configure: Regenerate. 2008-01-30 H.J. Lu PR libffi/34612 * src/x86/sysv.S (ffi_closure_SYSV): Pop 4 byte from stack when returning struct. * testsuite/libffi.call/call.exp: Add "-O2 -fomit-frame-pointer" tests. 2008-01-24 David Edelsohn * configure: Regenerate. 2008-01-06 Andreas Tobler * src/x86/ffi.c (ffi_prep_cif_machdep): Fix thinko. 2008-01-05 Andreas Tobler PR testsuite/32843 * src/x86/ffi.c (ffi_prep_cif_machdep): Add code for signed/unsigned int8/16 for X86_DARWIN. Updated copyright info. Handle one and two byte structs with special cif->flags. * src/x86/ffitarget.h: Add special types for one and two byte structs. Updated copyright info. * src/x86/darwin.S (ffi_call_SYSV): Rewrite to use a jump table like sysv.S Remove code to pop args from the stack after call. Special-case signed/unsigned for int8/16, one and two byte structs. (ffi_closure_raw_SYSV): Handle FFI_TYPE_UINT8, FFI_TYPE_SINT8, FFI_TYPE_UINT16, FFI_TYPE_SINT16, FFI_TYPE_UINT32, FFI_TYPE_SINT32. Updated copyright info. 2007-12-08 David Daney * src/mips/n32.S (ffi_call_N32): Replace dadd with ADDU, dsub with SUBU, add with ADDU and use smaller code sequences. 2007-12-07 David Daney * src/mips/ffi.c (ffi_prep_cif_machdep): Handle long double return type. 2007-12-06 David Daney * include/ffi.h.in (FFI_SIZEOF_JAVA_RAW): Define if not already defined. (ffi_java_raw): New typedef. (ffi_java_raw_call, ffi_java_ptrarray_to_raw, ffi_java_raw_to_ptrarray): Change parameter types from ffi_raw to ffi_java_raw. (ffi_java_raw_closure) : Same. (ffi_prep_java_raw_closure, ffi_prep_java_raw_closure_loc): Change parameter types. * src/java_raw_api.c (ffi_java_raw_size): Replace FFI_SIZEOF_ARG with FFI_SIZEOF_JAVA_RAW. (ffi_java_raw_to_ptrarray): Change type of raw to ffi_java_raw. Replace FFI_SIZEOF_ARG with FFI_SIZEOF_JAVA_RAW. Use sizeof(ffi_java_raw) for alignment calculations. (ffi_java_ptrarray_to_raw): Same. (ffi_java_rvalue_to_raw): Add special handling for FFI_TYPE_POINTER if FFI_SIZEOF_JAVA_RAW == 4. (ffi_java_raw_to_rvalue): Same. (ffi_java_raw_call): Change type of raw to ffi_java_raw. (ffi_java_translate_args): Same. (ffi_prep_java_raw_closure_loc, ffi_prep_java_raw_closure): Change parameter types. * src/mips/ffitarget.h (FFI_SIZEOF_JAVA_RAW): Define for N32 ABI. 2007-12-06 David Daney * src/mips/n32.S (ffi_closure_N32): Use 64-bit add instruction on pointer values. 2007-12-01 Andreas Tobler PR libffi/31937 * src/powerpc/ffitarget.h: Introduce new ABI FFI_LINUX_SOFT_FLOAT. Add local FFI_TYPE_UINT128 to handle soft-float long-double-128. * src/powerpc/ffi.c: Distinguish between __NO_FPRS__ and not and set the NUM_FPR_ARG_REGISTERS according to. Add support for potential soft-float support under hard-float architecture. (ffi_prep_args_SYSV): Set NUM_FPR_ARG_REGISTERS to 0 in case of FFI_LINUX_SOFT_FLOAT, handle float, doubles and long-doubles according to the FFI_LINUX_SOFT_FLOAT ABI. (ffi_prep_cif_machdep): Likewise. (ffi_closure_helper_SYSV): Likewise. * src/powerpc/ppc_closure.S: Make sure not to store float/double on archs where __NO_FPRS__ is true. Add FFI_TYPE_UINT128 support. * src/powerpc/sysv.S: Add support for soft-float long-double-128. Adjust copyright notice. 2007-11-25 Andreas Tobler * src/closures.c: Move defintion of MAYBE_UNUSED from here to ... * include/ffi_common.h: ... here. Update copyright. 2007-11-17 Andreas Tobler * src/powerpc/sysv.S: Load correct cr to compare if we have long double. * src/powerpc/linux64.S: Likewise. * src/powerpc/ffi.c: Add a comment to show which part goes into cr6. * testsuite/libffi.call/return_ldl.c: New test. 2007-09-04 * src/arm/sysv.S (UNWIND): New. (Whole file): Conditionally compile unwinder directives. * src/arm/sysv.S: Add unwinder directives. * src/arm/ffi.c (ffi_prep_args): Align structs by at least 4 bytes. Only treat r0 as a struct address if we're actually returning a struct by address. Only copy the bytes that are actually within a struct. (ffi_prep_cif_machdep): A Composite Type not larger than 4 bytes is returned in r0, not passed by address. (ffi_call): Allocate a word-sized temporary for the case where a composite is returned in r0. (ffi_prep_incoming_args_SYSV): Align as necessary. 2007-08-05 Steven Newbury * src/arm/ffi.c (FFI_INIT_TRAMPOLINE): Use __clear_cache instead of directly using the sys_cacheflush syscall. 2007-07-27 Andrew Haley * src/arm/sysv.S (ffi_closure_SYSV): Add soft-float. 2007-09-03 Maciej W. Rozycki * Makefile.am: Unify MIPS_IRIX and MIPS_LINUX into MIPS. * configure.ac: Likewise. * Makefile.in: Regenerate. * include/Makefile.in: Likewise. * testsuite/Makefile.in: Likewise. * configure: Likewise. 2007-08-24 David Daney * testsuite/libffi.call/return_sl.c: New test. 2007-08-10 David Daney * testsuite/libffi.call/cls_multi_ushort.c, testsuite/libffi.call/cls_align_uint16.c, testsuite/libffi.call/nested_struct1.c, testsuite/libffi.call/nested_struct3.c, testsuite/libffi.call/cls_7_1_byte.c, testsuite/libffi.call/nested_struct5.c, testsuite/libffi.call/cls_double.c, testsuite/libffi.call/nested_struct7.c, testsuite/libffi.call/cls_sint.c, testsuite/libffi.call/nested_struct9.c, testsuite/libffi.call/cls_20byte1.c, testsuite/libffi.call/cls_multi_sshortchar.c, testsuite/libffi.call/cls_align_sint64.c, testsuite/libffi.call/cls_3byte2.c, testsuite/libffi.call/cls_multi_schar.c, testsuite/libffi.call/cls_multi_uchar.c, testsuite/libffi.call/cls_19byte.c, testsuite/libffi.call/cls_9byte1.c, testsuite/libffi.call/cls_align_float.c, testsuite/libffi.call/closure_fn1.c, testsuite/libffi.call/problem1.c, testsuite/libffi.call/closure_fn3.c, testsuite/libffi.call/cls_sshort.c, testsuite/libffi.call/closure_fn5.c, testsuite/libffi.call/cls_align_double.c, testsuite/libffi.call/nested_struct.c, testsuite/libffi.call/cls_2byte.c, testsuite/libffi.call/nested_struct10.c, testsuite/libffi.call/cls_4byte.c, testsuite/libffi.call/cls_6byte.c, testsuite/libffi.call/cls_8byte.c, testsuite/libffi.call/cls_multi_sshort.c, testsuite/libffi.call/cls_align_sint16.c, testsuite/libffi.call/cls_align_uint32.c, testsuite/libffi.call/cls_20byte.c, testsuite/libffi.call/cls_float.c, testsuite/libffi.call/nested_struct2.c, testsuite/libffi.call/cls_5_1_byte.c, testsuite/libffi.call/nested_struct4.c, testsuite/libffi.call/cls_24byte.c, testsuite/libffi.call/nested_struct6.c, testsuite/libffi.call/cls_64byte.c, testsuite/libffi.call/nested_struct8.c, testsuite/libffi.call/cls_uint.c, testsuite/libffi.call/cls_multi_ushortchar.c, testsuite/libffi.call/cls_schar.c, testsuite/libffi.call/cls_uchar.c, testsuite/libffi.call/cls_align_uint64.c, testsuite/libffi.call/cls_ulonglong.c, testsuite/libffi.call/cls_align_longdouble.c, testsuite/libffi.call/cls_1_1byte.c, testsuite/libffi.call/cls_12byte.c, testsuite/libffi.call/cls_3_1byte.c, testsuite/libffi.call/cls_3byte1.c, testsuite/libffi.call/cls_4_1byte.c, testsuite/libffi.call/cls_6_1_byte.c, testsuite/libffi.call/cls_16byte.c, testsuite/libffi.call/cls_18byte.c, testsuite/libffi.call/closure_fn0.c, testsuite/libffi.call/cls_9byte2.c, testsuite/libffi.call/closure_fn2.c, testsuite/libffi.call/closure_fn4.c, testsuite/libffi.call/cls_ushort.c, testsuite/libffi.call/closure_fn6.c, testsuite/libffi.call/cls_5byte.c, testsuite/libffi.call/cls_align_pointer.c, testsuite/libffi.call/cls_7byte.c, testsuite/libffi.call/cls_align_sint32.c, testsuite/libffi.special/unwindtest_ffi_call.cc, testsuite/libffi.special/unwindtest.cc: Remove xfail for mips64*-*-*. 2007-08-10 David Daney PR libffi/28313 * configure.ac: Don't treat mips64 as a special case. * Makefile.am (nodist_libffi_la_SOURCES): Add n32.S. * configure: Regenerate * Makefile.in: Ditto. * fficonfig.h.in: Ditto. * src/mips/ffitarget.h (REG_L, REG_S, SUBU, ADDU, SRL, LI): Indent. (LA, EH_FRAME_ALIGN, FDE_ADDR_BYTES): New preprocessor macros. (FFI_DEFAULT_ABI): Set for n64 case. (FFI_CLOSURES, FFI_TRAMPOLINE_SIZE): Define for n32 and n64 cases. * src/mips/n32.S (ffi_call_N32): Add debug macros and labels for FDE. (ffi_closure_N32): New function. (.eh_frame): New section * src/mips/o32.S: Clean up comments. (ffi_closure_O32): Pass ffi_closure parameter in $12. * src/mips/ffi.c: Use FFI_MIPS_N32 instead of _MIPS_SIM == _ABIN32 throughout. (FFI_MIPS_STOP_HERE): New, use in place of ffi_stop_here. (ffi_prep_args): Use unsigned long to hold pointer values. Rewrite to support n32/n64 ABIs. (calc_n32_struct_flags): Rewrite. (calc_n32_return_struct_flags): Remove unused variable. Reverse position of flag bits. (ffi_prep_cif_machdep): Rewrite n32 portion. (ffi_call): Enable for n64. Add special handling for small structure return values. (ffi_prep_closure_loc): Add n32 and n64 support. (ffi_closure_mips_inner_O32): Add cast to silence warning. (copy_struct_N32, ffi_closure_mips_inner_N32): New functions. 2007-08-08 David Daney * testsuite/libffi.call/ffitest.h (ffi_type_mylong): Remove definition. * testsuite/libffi.call/cls_align_uint16.c (main): Use correct type specifiers. * testsuite/libffi.call/nested_struct1.c (main): Ditto. * testsuite/libffi.call/cls_sint.c (main): Ditto. * testsuite/libffi.call/nested_struct9.c (main): Ditto. * testsuite/libffi.call/cls_20byte1.c (main): Ditto. * testsuite/libffi.call/cls_9byte1.c (main): Ditto. * testsuite/libffi.call/closure_fn1.c (main): Ditto. * testsuite/libffi.call/closure_fn3.c (main): Ditto. * testsuite/libffi.call/return_dbl2.c (main): Ditto. * testsuite/libffi.call/cls_sshort.c (main): Ditto. * testsuite/libffi.call/return_fl3.c (main): Ditto. * testsuite/libffi.call/closure_fn5.c (main): Ditto. * testsuite/libffi.call/nested_struct.c (main): Ditto. * testsuite/libffi.call/nested_struct10.c (main): Ditto. * testsuite/libffi.call/return_ll1.c (main): Ditto. * testsuite/libffi.call/cls_8byte.c (main): Ditto. * testsuite/libffi.call/cls_align_uint32.c (main): Ditto. * testsuite/libffi.call/cls_align_sint16.c (main): Ditto. * testsuite/libffi.call/cls_20byte.c (main): Ditto. * testsuite/libffi.call/nested_struct2.c (main): Ditto. * testsuite/libffi.call/cls_24byte.c (main): Ditto. * testsuite/libffi.call/nested_struct6.c (main): Ditto. * testsuite/libffi.call/cls_uint.c (main): Ditto. * testsuite/libffi.call/cls_12byte.c (main): Ditto. * testsuite/libffi.call/cls_16byte.c (main): Ditto. * testsuite/libffi.call/closure_fn0.c (main): Ditto. * testsuite/libffi.call/cls_9byte2.c (main): Ditto. * testsuite/libffi.call/closure_fn2.c (main): Ditto. * testsuite/libffi.call/return_dbl1.c (main): Ditto. * testsuite/libffi.call/closure_fn4.c (main): Ditto. * testsuite/libffi.call/closure_fn6.c (main): Ditto. * testsuite/libffi.call/cls_align_sint32.c (main): Ditto. 2007-08-07 Andrew Haley * src/x86/sysv.S (ffi_closure_raw_SYSV): Fix typo in previous checkin. 2007-08-06 Andrew Haley PR testsuite/32843 * src/x86/sysv.S (ffi_closure_raw_SYSV): Handle FFI_TYPE_UINT8, FFI_TYPE_SINT8, FFI_TYPE_UINT16, FFI_TYPE_SINT16, FFI_TYPE_UINT32, FFI_TYPE_SINT32. 2007-08-02 David Daney * testsuite/libffi.call/return_ul.c (main): Define return type as ffi_arg. Use proper printf conversion specifier. 2007-07-30 Andrew Haley PR testsuite/32843 * src/x86/ffi.c (ffi_prep_cif_machdep): in x86 case, add code for signed/unsigned int8/16. * src/x86/sysv.S (ffi_call_SYSV): Rewrite to: Use a jump table. Remove code to pop args from the stack after call. Special-case signed/unsigned int8/16. * testsuite/libffi.call/return_sc.c (main): Revert. 2007-07-26 Richard Guenther PR testsuite/32843 * testsuite/libffi.call/return_sc.c (main): Verify call result as signed char, not ffi_arg. 2007-07-16 Rainer Orth * configure.ac (i?86-*-solaris2.1[0-9]): Set TARGET to X86_64. * configure: Regenerate. 2007-07-11 David Daney * src/mips/ffi.c: Don't include sys/cachectl.h. (ffi_prep_closure_loc): Use __builtin___clear_cache() instead of cacheflush(). 2007-05-18 Aurelien Jarno * src/arm/ffi.c (ffi_prep_closure_loc): Renamed and ajusted from (ffi_prep_closure): ... this. (FFI_INIT_TRAMPOLINE): Adjust. 2005-12-31 Phil Blundell * src/arm/ffi.c (ffi_prep_incoming_args_SYSV, ffi_closure_SYSV_inner, ffi_prep_closure): New, add closure support. * src/arm/sysv.S(ffi_closure_SYSV): Likewise. * src/arm/ffitarget.h (FFI_TRAMPOLINE_SIZE): Likewise. (FFI_CLOSURES): Enable closure support. 2007-07-03 Andrew Haley * testsuite/libffi.call/cls_multi_ushort.c, testsuite/libffi.call/cls_align_uint16.c, testsuite/libffi.call/nested_struct1.c, testsuite/libffi.call/nested_struct3.c, testsuite/libffi.call/cls_7_1_byte.c, testsuite/libffi.call/cls_double.c, testsuite/libffi.call/nested_struct5.c, testsuite/libffi.call/nested_struct7.c, testsuite/libffi.call/cls_sint.c, testsuite/libffi.call/nested_struct9.c, testsuite/libffi.call/cls_20byte1.c, testsuite/libffi.call/cls_multi_sshortchar.c, testsuite/libffi.call/cls_align_sint64.c, testsuite/libffi.call/cls_3byte2.c, testsuite/libffi.call/cls_multi_schar.c, testsuite/libffi.call/cls_multi_uchar.c, testsuite/libffi.call/cls_19byte.c, testsuite/libffi.call/cls_9byte1.c, testsuite/libffi.call/cls_align_float.c, testsuite/libffi.call/closure_fn1.c, testsuite/libffi.call/problem1.c, testsuite/libffi.call/closure_fn3.c, testsuite/libffi.call/cls_sshort.c, testsuite/libffi.call/closure_fn5.c, testsuite/libffi.call/cls_align_double.c, testsuite/libffi.call/cls_2byte.c, testsuite/libffi.call/nested_struct.c, testsuite/libffi.call/nested_struct10.c, testsuite/libffi.call/cls_4byte.c, testsuite/libffi.call/cls_6byte.c, testsuite/libffi.call/cls_8byte.c, testsuite/libffi.call/cls_multi_sshort.c, testsuite/libffi.call/cls_align_uint32.c, testsuite/libffi.call/cls_align_sint16.c, testsuite/libffi.call/cls_float.c, testsuite/libffi.call/cls_20byte.c, testsuite/libffi.call/cls_5_1_byte.c, testsuite/libffi.call/nested_struct2.c, testsuite/libffi.call/cls_24byte.c, testsuite/libffi.call/nested_struct4.c, testsuite/libffi.call/nested_struct6.c, testsuite/libffi.call/cls_64byte.c, testsuite/libffi.call/nested_struct8.c, testsuite/libffi.call/cls_uint.c, testsuite/libffi.call/cls_multi_ushortchar.c, testsuite/libffi.call/cls_schar.c, testsuite/libffi.call/cls_uchar.c, testsuite/libffi.call/cls_align_uint64.c, testsuite/libffi.call/cls_ulonglong.c, testsuite/libffi.call/cls_align_longdouble.c, testsuite/libffi.call/cls_1_1byte.c, testsuite/libffi.call/cls_12byte.c, testsuite/libffi.call/cls_3_1byte.c, testsuite/libffi.call/cls_3byte1.c, testsuite/libffi.call/cls_4_1byte.c, testsuite/libffi.call/cls_6_1_byte.c, testsuite/libffi.call/cls_16byte.c, testsuite/libffi.call/cls_18byte.c, testsuite/libffi.call/closure_fn0.c, testsuite/libffi.call/cls_9byte2.c, testsuite/libffi.call/closure_fn2.c, testsuite/libffi.call/closure_fn4.c, testsuite/libffi.call/cls_ushort.c, testsuite/libffi.call/closure_fn6.c, testsuite/libffi.call/cls_5byte.c, testsuite/libffi.call/cls_align_pointer.c, testsuite/libffi.call/cls_7byte.c, testsuite/libffi.call/cls_align_sint32.c, testsuite/libffi.special/unwindtest_ffi_call.cc, testsuite/libffi.special/unwindtest.cc: Enable for ARM. 2007-07-05 H.J. Lu * aclocal.m4: Regenerated. 2007-06-02 Paolo Bonzini * configure: Regenerate. 2007-05-23 Steve Ellcey * Makefile.in: Regenerate. * configure: Regenerate. * aclocal.m4: Regenerate. * include/Makefile.in: Regenerate. * testsuite/Makefile.in: Regenerate. 2007-05-10 Roman Zippel * src/m68k/ffi.c (ffi_prep_incoming_args_SYSV, ffi_closure_SYSV_inner,ffi_prep_closure): New, add closure support. * src/m68k/sysv.S(ffi_closure_SYSV,ffi_closure_struct_SYSV): Likewise. * src/m68k/ffitarget.h (FFI_TRAMPOLINE_SIZE): Likewise. (FFI_CLOSURES): Enable closure support. 2007-05-10 Roman Zippel * configure.ac (HAVE_AS_CFI_PSEUDO_OP): New test. * configure: Regenerate. * fficonfig.h.in: Regenerate. * src/m68k/sysv.S (CFI_STARTPROC,CFI_ENDPROC, CFI_OFFSET,CFI_DEF_CFA): New macros. (ffi_call_SYSV): Add callframe annotation. 2007-05-10 Roman Zippel * src/m68k/ffi.c (ffi_prep_args,ffi_prep_cif_machdep): Fix numerous test suite failures. * src/m68k/sysv.S (ffi_call_SYSV): Likewise. 2007-04-11 Paolo Bonzini * Makefile.am (EXTRA_DIST): Bring up to date. * Makefile.in: Regenerate. * src/frv/eabi.S: Remove RCS keyword. 2007-04-06 Richard Henderson * configure.ac: Tidy target case. (HAVE_LONG_DOUBLE): Allow the target to override. * configure: Regenerate. * include/ffi.h.in: Don't define ffi_type_foo if LIBFFI_HIDE_BASIC_TYPES is defined. (ffi_type_longdouble): If not HAVE_LONG_DOUBLE, define to ffi_type_double. * types.c (LIBFFI_HIDE_BASIC_TYPES): Define. (FFI_TYPEDEF, ffi_type_void): Mark the data const. (ffi_type_longdouble): Special case for Alpha. Don't define if long double == double. * src/alpha/ffi.c (FFI_TYPE_LONGDOUBLE): Assert unique value. (ffi_prep_cif_machdep): Handle it as the 128-bit type. (ffi_call, ffi_closure_osf_inner): Likewise. (ffi_closure_osf_inner): Likewise. Mark hidden. (ffi_call_osf, ffi_closure_osf): Mark hidden. * src/alpha/ffitarget.h (FFI_LAST_ABI): Tidy definition. * src/alpha/osf.S (ffi_call_osf, ffi_closure_osf): Mark hidden. (load_table): Handle 128-bit long double. * testsuite/libffi.call/float4.c: Add -mieee for alpha. 2007-04-06 Tom Tromey PR libffi/31491: * README: Fixed bug in example. 2007-04-03 Jakub Jelinek * src/closures.c: Include sys/statfs.h. (_GNU_SOURCE): Define on Linux. (FFI_MMAP_EXEC_SELINUX): Define. (selinux_enabled): New variable. (selinux_enabled_check): New function. (is_selinux_enabled): Define. (dlmmap): Use it. 2007-03-24 Uros Bizjak * testsuite/libffi.call/return_fl2.c (return_fl): Mark as static. Use 'volatile float sum' to create sum of floats to avoid false negative due to excess precision on ix86 targets. (main): Ditto. 2007-03-08 Alexandre Oliva * src/powerpc/ffi.c (flush_icache): Fix left-over from previous patch. (ffi_prep_closure_loc): Remove unneeded casts. Add needed ones. 2007-03-07 Alexandre Oliva * include/ffi.h.in (ffi_closure_alloc, ffi_closure_free): New. (ffi_prep_closure_loc): New. (ffi_prep_raw_closure_loc): New. (ffi_prep_java_raw_closure_loc): New. * src/closures.c: New file. * src/dlmalloc.c [FFI_MMAP_EXEC_WRIT] (struct malloc_segment): Replace sflags with exec_offset. [FFI_MMAP_EXEC_WRIT] (mmap_exec_offset, add_segment_exec_offset, sub_segment_exec_offset): New macros. (get_segment_flags, set_segment_flags, check_segment_merge): New macros. (is_mmapped_segment, is_extern_segment): Use get_segment_flags. (add_segment, sys_alloc, create_mspace, create_mspace_with_base, destroy_mspace): Use new macros. (sys_alloc): Silence warning. * Makefile.am (libffi_la_SOURCES): Add src/closures.c. * Makefile.in: Rebuilt. * src/prep_cif [FFI_CLOSURES] (ffi_prep_closure): Implement in terms of ffi_prep_closure_loc. * src/raw_api.c (ffi_prep_raw_closure_loc): Renamed and adjusted from... (ffi_prep_raw_closure): ... this. Re-implement in terms of the renamed version. * src/java_raw_api (ffi_prep_java_raw_closure_loc): Renamed and adjusted from... (ffi_prep_java_raw_closure): ... this. Re-implement in terms of the renamed version. * src/alpha/ffi.c (ffi_prep_closure_loc): Renamed from (ffi_prep_closure): ... this. * src/pa/ffi.c: Likewise. * src/cris/ffi.c: Likewise. Adjust. * src/frv/ffi.c: Likewise. * src/ia64/ffi.c: Likewise. * src/mips/ffi.c: Likewise. * src/powerpc/ffi_darwin.c: Likewise. * src/s390/ffi.c: Likewise. * src/sh/ffi.c: Likewise. * src/sh64/ffi.c: Likewise. * src/sparc/ffi.c: Likewise. * src/x86/ffi64.c: Likewise. * src/x86/ffi.c: Likewise. (FFI_INIT_TRAMPOLINE): Adjust. (ffi_prep_raw_closure_loc): Renamed and adjusted from... (ffi_prep_raw_closure): ... this. * src/powerpc/ffi.c (ffi_prep_closure_loc): Renamed from (ffi_prep_closure): ... this. (flush_icache): Adjust. 2007-03-07 Alexandre Oliva * src/dlmalloc.c: New file, imported version 2.8.3 of Doug Lea's malloc. 2007-03-01 Brooks Moses * Makefile.am: Add dummy install-pdf target. * Makefile.in: Regenerate 2007-02-13 Andreas Krebbel * src/s390/ffi.c (ffi_prep_args, ffi_prep_cif_machdep, ffi_closure_helper_SYSV): Add long double handling. 2007-02-02 Jakub Jelinek * src/powerpc/linux64.S (ffi_call_LINUX64): Move restore of r2 immediately after bctrl instruction. 2007-01-18 Alexandre Oliva * Makefile.am (all-recursive, install-recursive, mostlyclean-recursive, clean-recursive, distclean-recursive, maintainer-clean-recursive): Add missing targets. * Makefile.in: Rebuilt. 2006-12-14 Andreas Tobler * configure.ac: Add TARGET for x86_64-*-darwin*. * Makefile.am (nodist_libffi_la_SOURCES): Add rules for 64-bit sources for X86_DARWIN. * src/x86/ffitarget.h: Set trampoline size for x86_64-*-darwin*. * src/x86/darwin64.S: New file for x86_64-*-darwin* support. * configure: Regenerate. * Makefile.in: Regenerate. * include/Makefile.in: Regenerate. * testsuite/Makefile.in: Regenerate. * testsuite/libffi.special/unwindtest_ffi_call.cc: New test case for ffi_call only. 2006-12-13 Andreas Tobler * aclocal.m4: Regenerate with aclocal -I .. as written in the Makefile.am. 2006-10-31 Geoffrey Keating * src/powerpc/ffi_darwin.c (darwin_adjust_aggregate_sizes): New. (ffi_prep_cif_machdep): Call darwin_adjust_aggregate_sizes for Darwin. * testsuite/libffi.call/nested_struct4.c: Remove Darwin XFAIL. * testsuite/libffi.call/nested_struct6.c: Remove Darwin XFAIL. 2006-10-10 Paolo Bonzini Sandro Tolaini * configure.ac [i*86-*-darwin*]: Set X86_DARWIN symbol and conditional. * configure: Regenerated. * Makefile.am (nodist_libffi_la_SOURCES) [X86_DARWIN]: New case. (EXTRA_DIST): Add src/x86/darwin.S. * Makefile.in: Regenerated. * include/Makefile.in: Regenerated. * testsuite/Makefile.in: Regenerated. * src/x86/ffi.c (ffi_prep_cif_machdep) [X86_DARWIN]: Treat like X86_WIN32, and additionally align stack to 16 bytes. * src/x86/darwin.S: New, based on sysv.S. * src/prep_cif.c (ffi_prep_cif) [X86_DARWIN]: Align > 8-byte structs. 2006-09-12 David Daney PR libffi/23935 * include/Makefile.am: Install both ffi.h and ffitarget.h in $(libdir)/gcc/$(target_alias)/$(gcc_version)/include. * aclocal.m4: Regenerated for automake 1.9.6. * Makefile.in: Regenerated. * include/Makefile.in: Regenerated. * testsuite/Makefile.in: Regenerated. 2006-08-17 Andreas Tobler * include/ffi_common.h (struct): Revert accidental commit. 2006-08-15 Andreas Tobler * include/ffi_common.h: Remove lint directives. * include/ffi.h.in: Likewise. 2006-07-25 Torsten Schoenfeld * include/ffi.h.in (ffi_type_ulong, ffi_type_slong): Define correctly for 32-bit architectures. * testsuite/libffi.call/return_ul.c: New test case. 2006-07-19 David Daney * testsuite/libffi.call/closure_fn6.c: Remove xfail for mips, xfail remains for mips64. 2006-05-23 Carlos O'Donell * Makefile.am: Add install-html target. Add install-html to .PHONY * Makefile.in: Regenerate. * aclocal.m4: Regenerate. * include/Makefile.in: Regenerate. * testsuite/Makefile.in: Regenerate. 2006-05-18 John David Anglin * pa/ffi.c (ffi_prep_args_pa32): Load floating point arguments from stack slot. 2006-04-22 Andreas Tobler * README: Remove notice about 'Crazy Comments'. * src/debug.c: Remove lint directives. Cleanup white spaces. * src/java_raw_api.c: Likewise. * src/prep_cif.c: Likewise. * src/raw_api.c: Likewise. * src/ffitest.c: Delete. No longer needed, all test cases migrated to the testsuite. * src/arm/ffi.c: Remove lint directives. * src/m32r/ffi.c: Likewise. * src/pa/ffi.c: Likewise. * src/powerpc/ffi.c: Likewise. * src/powerpc/ffi_darwin.c: Likewise. * src/sh/ffi.c: Likewise. * src/sh64/ffi.c: Likewise. * src/x86/ffi.c: Likewise. * testsuite/libffi.call/float2.c: Likewise. * testsuite/libffi.call/promotion.c: Likewise. * testsuite/libffi.call/struct1.c: Likewise. 2006-04-13 Andreas Tobler * src/pa/hpux32.S: Correct unwind offset calculation for ffi_closure_pa32. * src/pa/linux.S: Likewise. 2006-04-12 James E Wilson PR libgcj/26483 * src/ia64/ffi.c (stf_spill, ldf_fill): Rewrite as macros. (hfa_type_load): Call stf_spill. (hfa_type_store): Call ldf_fill. (ffi_call): Adjust calls to above routines. Add local temps for macro result. 2006-04-10 Matthias Klose * testsuite/lib/libffi-dg.exp (libffi-init): Recognize multilib directory names containing underscores. 2006-04-07 James E Wilson * testsuite/libffi.call/float4.c: New testcase. 2006-04-05 John David Anglin Andreas Tobler * Makefile.am: Add PA_HPUX port. * Makefile.in: Regenerate. * include/Makefile.in: Likewise. * testsuite/Makefile.in: Likewise. * configure.ac: Add PA_HPUX rules. * configure: Regenerate. * src/pa/ffitarget.h: Rename linux target to PA_LINUX. Add PA_HPUX and PA64_HPUX. Rename FFI_LINUX ABI to FFI_PA32 ABI. (FFI_TRAMPOLINE_SIZE): Define for 32-bit HP-UX targets. (FFI_TYPE_SMALL_STRUCT2): Define. (FFI_TYPE_SMALL_STRUCT4): Likewise. (FFI_TYPE_SMALL_STRUCT8): Likewise. (FFI_TYPE_SMALL_STRUCT3): Redefine. (FFI_TYPE_SMALL_STRUCT5): Likewise. (FFI_TYPE_SMALL_STRUCT6): Likewise. (FFI_TYPE_SMALL_STRUCT7): Likewise. * src/pa/ffi.c (ROUND_DOWN): Delete. (fldw, fstw, fldd, fstd): Use '__asm__'. (ffi_struct_type): Add support for FFI_TYPE_SMALL_STRUCT2, FFI_TYPE_SMALL_STRUCT4 and FFI_TYPE_SMALL_STRUCT8. (ffi_prep_args_LINUX): Rename to ffi_prep_args_pa32. Update comment. Simplify incrementing of stack slot variable. Change type of local 'n' to unsigned int. (ffi_size_stack_LINUX): Rename to ffi_size_stack_pa32. Handle long double on PA_HPUX. (ffi_prep_cif_machdep): Likewise. (ffi_call): Likewise. (ffi_closure_inner_LINUX): Rename to ffi_closure_inner_pa32. Change return type to ffi_status. Simplify incrementing of stack slot variable. Only copy floating point argument registers when PA_LINUX is true. Reformat debug statement. Add support for FFI_TYPE_SMALL_STRUCT2, FFI_TYPE_SMALL_STRUCT4 and FFI_TYPE_SMALL_STRUCT8. (ffi_closure_LINUX): Rename to ffi_closure_pa32. Add 'extern' to declaration. (ffi_prep_closure): Make linux trampoline conditional on PA_LINUX. Add nops to cache flush. Add trampoline for PA_HPUX. * src/pa/hpux32.S: New file. * src/pa/linux.S (ffi_call_LINUX): Rename to ffi_call_pa32. Rename ffi_prep_args_LINUX to ffi_prep_args_pa32. Localize labels. Add support for 2, 4 and 8-byte small structs. Handle unaligned destinations in 3, 5, 6 and 7-byte small structs. Order argument type checks so that common argument types appear first. (ffi_closure_LINUX): Rename to ffi_closure_pa32. Rename ffi_closure_inner_LINUX to ffi_closure_inner_pa32. 2006-03-24 Alan Modra * src/powerpc/ffitarget.h (enum ffi_abi): Add FFI_LINUX. Default for 32-bit using IBM extended double format. Fix FFI_LAST_ABI. * src/powerpc/ffi.c (ffi_prep_args_SYSV): Handle linux variant of FFI_TYPE_LONGDOUBLE. (ffi_prep_args64): Assert using IBM extended double. (ffi_prep_cif_machdep): Don't munge FFI_TYPE_LONGDOUBLE type. Handle FFI_LINUX FFI_TYPE_LONGDOUBLE return and args. (ffi_call): Handle FFI_LINUX. (ffi_closure_helper_SYSV): Non FFI_LINUX long double return needs gpr3 return pointer as for struct return. Handle FFI_LINUX FFI_TYPE_LONGDOUBLE return and args. Don't increment "nf" unnecessarily. * src/powerpc/ppc_closure.S (ffi_closure_SYSV): Load both f1 and f2 for FFI_TYPE_LONGDOUBLE. Move epilogue insns into case table. Don't use r6 as pointer to results, instead use sp offset. Don't make a special call to load lr with case table address, instead use offset from previous call. * src/powerpc/sysv.S (ffi_call_SYSV): Save long double return. * src/powerpc/linux64.S (ffi_call_LINUX64): Simplify long double return. 2006-03-15 Kaz Kojima * src/sh64/ffi.c (ffi_prep_cif_machdep): Handle float arguments passed with FP registers correctly. (ffi_closure_helper_SYSV): Likewise. * src/sh64/sysv.S: Likewise. 2006-03-01 Andreas Tobler * testsuite/libffi.special/unwindtest.cc (closure_test_fn): Mark cif, args and userdata unused. (closure_test_fn1): Mark cif and userdata unused. (main): Remove unused res. 2006-02-28 Andreas Tobler * testsuite/libffi.call/call.exp: Adjust FSF address. Add test runs for -O2, -O3, -Os and the warning flags -W -Wall. * testsuite/libffi.special/special.exp: Likewise. * testsuite/libffi.call/ffitest.h: Add an __UNUSED__ macro to mark unused parameter unused for gcc or else do nothing. * testsuite/libffi.special/ffitestcxx.h: Likewise. * testsuite/libffi.call/cls_12byte.c (cls_struct_12byte_gn): Mark cif and userdata unused. * testsuite/libffi.call/cls_16byte.c (cls_struct_16byte_gn): Likewise. * testsuite/libffi.call/cls_18byte.c (cls_struct_18byte_gn): Likewise. * testsuite/libffi.call/cls_19byte.c (cls_struct_19byte_gn): Likewise. * testsuite/libffi.call/cls_1_1byte.c (cls_struct_1_1byte_gn): Likewise. * testsuite/libffi.call/cls_20byte.c (cls_struct_20byte_gn): Likewise. * testsuite/libffi.call/cls_20byte1.c (cls_struct_20byte_gn): Likewise. * testsuite/libffi.call/cls_24byte.c (cls_struct_24byte_gn): Likewise. * testsuite/libffi.call/cls_2byte.c (cls_struct_2byte_gn): Likewise. * testsuite/libffi.call/cls_3_1byte.c (cls_struct_3_1byte_gn): Likewise. * testsuite/libffi.call/cls_3byte1.c (cls_struct_3byte_gn): Likewise. * testsuite/libffi.call/cls_3byte2.c (cls_struct_3byte_gn1): Likewise. * testsuite/libffi.call/cls_4_1byte.c (cls_struct_4_1byte_gn): Likewise. * testsuite/libffi.call/cls_4byte.c (cls_struct_4byte_gn): Likewise. * testsuite/libffi.call/cls_5_1_byte.c (cls_struct_5byte_gn): Likewise. * testsuite/libffi.call/cls_5byte.c (cls_struct_5byte_gn): Likewise. * testsuite/libffi.call/cls_64byte.c (cls_struct_64byte_gn): Likewise. * testsuite/libffi.call/cls_6_1_byte.c (cls_struct_6byte_gn): Likewise. * testsuite/libffi.call/cls_6byte.c (cls_struct_6byte_gn): Likewise. * testsuite/libffi.call/cls_7_1_byte.c (cls_struct_7byte_gn): Likewise. * testsuite/libffi.call/cls_7byte.c (cls_struct_7byte_gn): Likewise. * testsuite/libffi.call/cls_8byte.c (cls_struct_8byte_gn): Likewise. * testsuite/libffi.call/cls_9byte1.c (cls_struct_9byte_gn): Likewise. * testsuite/libffi.call/cls_9byte2.c (cls_struct_9byte_gn): Likewise. * testsuite/libffi.call/cls_align_double.c (cls_struct_align_gn): Likewise. * testsuite/libffi.call/cls_align_float.c (cls_struct_align_gn): Likewise. * testsuite/libffi.call/cls_align_longdouble.c (cls_struct_align_gn): Likewise. * testsuite/libffi.call/cls_align_pointer.c (cls_struct_align_fn): Cast void* to avoid compiler warning. (main): Likewise. (cls_struct_align_gn): Mark cif and userdata unused. * testsuite/libffi.call/cls_align_sint16.c (cls_struct_align_gn): Likewise. * testsuite/libffi.call/cls_align_sint32.c (cls_struct_align_gn): Likewise. * testsuite/libffi.call/cls_align_sint64.c (cls_struct_align_gn): Likewise. * testsuite/libffi.call/cls_align_uint16.c (cls_struct_align_gn): Likewise. * testsuite/libffi.call/cls_align_uint32.c (cls_struct_align_gn): Likewise. * testsuite/libffi.call/cls_double.c (cls_ret_double_fn): Likewise. * testsuite/libffi.call/cls_float.c (cls_ret_float_fn): Likewise. * testsuite/libffi.call/cls_multi_schar.c (test_func_gn): Mark cif and data unused. (main): Cast res_call to silence gcc. * testsuite/libffi.call/cls_multi_sshort.c (test_func_gn): Mark cif and data unused. (main): Cast res_call to silence gcc. * testsuite/libffi.call/cls_multi_sshortchar.c (test_func_gn): Mark cif and data unused. (main): Cast res_call to silence gcc. * testsuite/libffi.call/cls_multi_uchar.c (test_func_gn): Mark cif and data unused. (main): Cast res_call to silence gcc. * testsuite/libffi.call/cls_multi_ushort.c (test_func_gn): Mark cif and data unused. (main): Cast res_call to silence gcc. * testsuite/libffi.call/cls_multi_ushortchar.c (test_func_gn): Mark cif and data unused. (main): Cast res_call to silence gcc. * testsuite/libffi.call/cls_schar.c (cls_ret_schar_fn): Mark cif and userdata unused. (cls_ret_schar_fn): Cast printf parameter to silence gcc. * testsuite/libffi.call/cls_sint.c (cls_ret_sint_fn): Mark cif and userdata unused. (cls_ret_sint_fn): Cast printf parameter to silence gcc. * testsuite/libffi.call/cls_sshort.c (cls_ret_sshort_fn): Mark cif and userdata unused. (cls_ret_sshort_fn): Cast printf parameter to silence gcc. * testsuite/libffi.call/cls_uchar.c (cls_ret_uchar_fn): Mark cif and userdata unused. (cls_ret_uchar_fn): Cast printf parameter to silence gcc. * testsuite/libffi.call/cls_uint.c (cls_ret_uint_fn): Mark cif and userdata unused. (cls_ret_uint_fn): Cast printf parameter to silence gcc. * testsuite/libffi.call/cls_ulonglong.c (cls_ret_ulonglong_fn): Mark cif and userdata unused. * testsuite/libffi.call/cls_ushort.c (cls_ret_ushort_fn): Mark cif and userdata unused. (cls_ret_ushort_fn): Cast printf parameter to silence gcc. * testsuite/libffi.call/float.c (floating): Remove unused parameter e. * testsuite/libffi.call/float1.c (main): Remove unused variable i. Cleanup white spaces. * testsuite/libffi.call/negint.c (checking): Remove unused variable i. * testsuite/libffi.call/nested_struct.c (cls_struct_combined_gn): Mark cif and userdata unused. * testsuite/libffi.call/nested_struct1.c (cls_struct_combined_gn): Likewise. * testsuite/libffi.call/nested_struct10.c (B_gn): Likewise. * testsuite/libffi.call/nested_struct2.c (B_fn): Adjust printf formatters to silence gcc. (B_gn): Mark cif and userdata unused. * testsuite/libffi.call/nested_struct3.c (B_gn): Mark cif and userdata unused. * testsuite/libffi.call/nested_struct4.c: Mention related PR. (B_gn): Mark cif and userdata unused. * testsuite/libffi.call/nested_struct5.c (B_gn): Mark cif and userdata unused. * testsuite/libffi.call/nested_struct6.c: Mention related PR. (B_gn): Mark cif and userdata unused. * testsuite/libffi.call/nested_struct7.c (B_gn): Mark cif and userdata unused. * testsuite/libffi.call/nested_struct8.c (B_gn): Likewise. * testsuite/libffi.call/nested_struct9.c (B_gn): Likewise. * testsuite/libffi.call/problem1.c (stub): Likewise. * testsuite/libffi.call/pyobjc-tc.c (main): Cast the result to silence gcc. * testsuite/libffi.call/return_fl2.c (return_fl): Add the note mentioned in the last commit for this test case in the test case itself. * testsuite/libffi.call/closure_fn0.c (closure_test_fn0): Mark cif as unused. * testsuite/libffi.call/closure_fn1.c (closure_test_fn1): Likewise. * testsuite/libffi.call/closure_fn2.c (closure_test_fn2): Likewise. * testsuite/libffi.call/closure_fn3.c (closure_test_fn3): Likewise. * testsuite/libffi.call/closure_fn4.c (closure_test_fn0): Likewise. * testsuite/libffi.call/closure_fn5.c (closure_test_fn5): Likewise. * testsuite/libffi.call/closure_fn6.c (closure_test_fn0): Likewise. 2006-02-22 Kaz Kojima * src/sh/sysv.S: Fix register numbers in the FDE for ffi_closure_SYSV. 2006-02-20 Andreas Tobler * testsuite/libffi.call/return_fl2.c (return_fl): Remove static declaration to avoid a false negative on ix86. See PR323. 2006-02-18 Kaz Kojima * src/sh/ffi.c (ffi_closure_helper_SYSV): Remove unused variable and cast integer to void * if needed. Update the pointer to the FP register saved area correctly. 2006-02-17 Andreas Tobler * testsuite/libffi.call/nested_struct6.c: XFAIL this test until PR25630 is fixed. * testsuite/libffi.call/nested_struct4.c: Likewise. 2006-02-16 Andreas Tobler * testsuite/libffi.call/return_dbl.c: New test case. * testsuite/libffi.call/return_dbl1.c: Likewise. * testsuite/libffi.call/return_dbl2.c: Likewise. * testsuite/libffi.call/return_fl.c: Likewise. * testsuite/libffi.call/return_fl1.c: Likewise. * testsuite/libffi.call/return_fl2.c: Likewise. * testsuite/libffi.call/return_fl3.c: Likewise. * testsuite/libffi.call/closure_fn6.c: Likewise. * testsuite/libffi.call/nested_struct2.c: Remove ffi_type_mylong definition. * testsuite/libffi.call/ffitest.h: Add ffi_type_mylong definition here to be used by other test cases too. * testsuite/libffi.call/nested_struct10.c: New test case. * testsuite/libffi.call/nested_struct9.c: Likewise. * testsuite/libffi.call/nested_struct8.c: Likewise. * testsuite/libffi.call/nested_struct7.c: Likewise. * testsuite/libffi.call/nested_struct6.c: Likewise. * testsuite/libffi.call/nested_struct5.c: Likewise. * testsuite/libffi.call/nested_struct4.c: Likewise. 2006-01-21 Andreas Tobler * configure.ac: Enable libffi for sparc64-*-freebsd*. * configure: Rebuilt. 2006-01-18 Jakub Jelinek * src/powerpc/sysv.S (smst_two_register): Don't call __ashldi3, instead do the shifting inline. * src/powerpc/ppc_closure.S (ffi_closure_SYSV): Don't compute %r5 shift count unconditionally. Simplify load sequences for 1, 2, 3, 4 and 8 byte structs, for the remaining struct sizes don't call __lshrdi3, instead do the shifting inline. 2005-12-07 Thiemo Seufer * src/mips/ffitarget.h: Remove obsolete sgidefs.h include. Add missing parentheses. * src/mips/o32.S (ffi_call_O32): Code formatting. Define and use A3_OFF, FP_OFF, RA_OFF. Micro-optimizations. (ffi_closure_O32): Likewise, but with newly defined A3_OFF2, A2_OFF2, A1_OFF2, A0_OFF2, RA_OFF2, FP_OFF2, S0_OFF2, GP_OFF2, V1_OFF2, V0_OFF2, FA_1_1_OFF2, FA_1_0_OFF2, FA_0_1_OFF2, FA_0_0_OFF2. * src/mips/ffi.c (ffi_prep_args): Code formatting. Fix endianness bugs. (ffi_prep_closure): Improve trampoline instruction scheduling. (ffi_closure_mips_inner_O32): Fix endianness bugs. 2005-12-03 Alan Modra * src/powerpc/ffi.c: Formatting. (ffi_prep_args_SYSV): Avoid possible aliasing problems by using unions. (ffi_prep_args64): Likewise. 2005-09-30 Geoffrey Keating * testsuite/lib/libffi-dg.exp (libffi_target_compile): For darwin, use -shared-libgcc not -lgcc_s, and explain why. 2005-09-26 Tom Tromey * testsuite/libffi.call/float1.c (value_type): New typedef. (CANARY): New define. (main): Check for result buffer overflow. * src/powerpc/linux64.S: Handle linux64 long double returns. * src/powerpc/ffi.c (FLAG_RETURNS_128BITS): New constant. (ffi_prep_cif_machdep): Handle linux64 long double returns. 2005-08-25 Alan Modra PR target/23404 * src/powerpc/ffi.c (ffi_prep_args_SYSV): Correct placement of stack homed fp args. (ffi_status ffi_prep_cif_machdep): Correct stack sizing for same. 2005-08-11 Jakub Jelinek * configure.ac (HAVE_HIDDEN_VISIBILITY_ATTRIBUTE): New test. (AH_BOTTOM): Add FFI_HIDDEN definition. * configure: Rebuilt. * fficonfig.h.in: Rebuilt. * src/powerpc/ffi.c (hidden): Remove. (ffi_closure_LINUX64, ffi_prep_args64, ffi_call_LINUX64, ffi_closure_helper_LINUX64): Use FFI_HIDDEN instead of hidden. * src/powerpc/linux64_closure.S (ffi_closure_LINUX64, .ffi_closure_LINUX64): Use FFI_HIDDEN instead of .hidden. * src/x86/ffi.c (ffi_closure_SYSV, ffi_closure_raw_SYSV): Remove, add FFI_HIDDEN to its prototype. (ffi_closure_SYSV_inner): New. * src/x86/sysv.S (ffi_closure_SYSV, ffi_closure_raw_SYSV): New. * src/x86/win32.S (ffi_closure_SYSV, ffi_closure_raw_SYSV): New. 2005-08-10 Alfred M. Szmidt PR libffi/21819: * configure: Rebuilt. * configure.ac: Handle i*86-*-gnu*. 2005-08-09 Jakub Jelinek * src/powerpc/ppc_closure.S (ffi_closure_SYSV): Use DW_CFA_offset_extended_sf rather than DW_CFA_GNU_negative_offset_extended. * src/powerpc/sysv.S (ffi_call_SYSV): Likewise. 2005-07-22 SUGIOKA Toshinobu * src/sh/sysv.S (ffi_call_SYSV): Stop argument popping correctly on sh3. (ffi_closure_SYSV): Change the stack layout for sh3 struct argument. * src/sh/ffi.c (ffi_prep_args): Fix sh3 argument copy, when it is partially on register. (ffi_closure_helper_SYSV): Likewise. (ffi_prep_cif_machdep): Don't set too many cif->flags. 2005-07-20 Kaz Kojima * src/sh/ffi.c (ffi_call): Handle small structures correctly. Remove empty line. * src/sh64/ffi.c (simple_type): Remove. (return_type): Handle small structures correctly. (ffi_prep_args): Likewise. (ffi_call): Likewise. (ffi_closure_helper_SYSV): Likewise. * src/sh64/sysv.S (ffi_call_SYSV): Handle 1, 2 and 4-byte return. Emit position independent code if PIC and remove wrong datalabel prefixes from EH data. 2005-07-19 Andreas Tobler * Makefile.am (nodist_libffi_la_SOURCES): Add POWERPC_FREEBSD. * Makefile.in: Regenerate. * include/Makefile.in: Likewise. * testsuite/Makefile.in: Likewise. * configure.ac: Add POWERPC_FREEBSD rules. * configure: Regenerate. * src/powerpc/ffitarget.h: Add POWERPC_FREEBSD rules. (FFI_SYSV_TYPE_SMALL_STRUCT): Define. * src/powerpc/ffi.c: Add flags to handle small structure returns in ffi_call_SYSV. (ffi_prep_cif_machdep): Handle small structures for SYSV 4 ABI. Aka FFI_SYSV. (ffi_closure_helper_SYSV): Likewise. * src/powerpc/ppc_closure.S: Add return types for small structures. * src/powerpc/sysv.S: Add bits to handle small structures for final SYSV 4 ABI. 2005-07-10 Andreas Tobler * testsuite/libffi.call/cls_5_1_byte.c: New test file. * testsuite/libffi.call/cls_6_1_byte.c: Likewise. * testsuite/libffi.call/cls_7_1_byte.c: Likewise. 2005-07-05 Randolph Chung * src/pa/ffi.c (ffi_struct_type): Rename FFI_TYPE_SMALL_STRUCT1 as FFI_TYPE_SMALL_STRUCT3. Break out handling for 5-7 byte structures. Kill compilation warnings. (ffi_closure_inner_LINUX): Print return values as hex in debug message. Rename FFI_TYPE_SMALL_STRUCT1 as FFI_TYPE_SMALL_STRUCT3. Properly handle 5-7 byte structure returns. * src/pa/ffitarget.h (FFI_TYPE_SMALL_STRUCT1) (FFI_TYPE_SMALL_STRUCT2): Remove. (FFI_TYPE_SMALL_STRUCT3, FFI_TYPE_SMALL_STRUCT5) (FFI_TYPE_SMALL_STRUCT6, FFI_TYPE_SMALL_STRUCT7): Define. * src/pa/linux.S: Mark source file as using PA1.1 assembly. (checksmst1, checksmst2): Remove. (checksmst3): Optimize handling of 3-byte struct returns. (checksmst567): Properly handle 5-7 byte struct returns. 2005-06-15 Rainer Orth PR libgcj/21943 * src/mips/n32.S: Enforce PIC code. * src/mips/o32.S: Likewise. 2005-06-15 Rainer Orth * configure.ac: Treat i*86-*-solaris2.10 and up as X86_64. * configure: Regenerate. 2005-06-01 Alan Modra * src/powerpc/ppc_closure.S (ffi_closure_SYSV): Don't use JUMPTARGET to call ffi_closure_helper_SYSV. Append @local instead. * src/powerpc/sysv.S (ffi_call_SYSV): Likewise for ffi_prep_args_SYSV. 2005-05-17 Kelley Cook * configure.ac: Use AC_C_BIGENDIAN instead of AC_C_BIGENDIAN_CROSS. Use AC_CHECK_SIZEOF instead of AC_COMPILE_CHECK_SIZEOF. * Makefile.am (ACLOCAL_AMFLAGS): Remove -I ../config. * aclocal.m4, configure, fficonfig.h.in, Makefile.in, include/Makefile.in, testsuite/Makefile.in: Regenerate. 2005-05-09 Mike Stump * configure: Regenerate. 2005-05-08 Richard Henderson PR libffi/21285 * src/alpha/osf.S: Update unwind into to match code. 2005-05-04 Andreas Degert Richard Henderson * src/x86/ffi64.c (ffi_prep_cif_machdep): Save sse-used flag in bit 11 of flags. (ffi_call): Mask return type field. Pass ssecount to ffi_call_unix64. (ffi_prep_closure): Set carry bit if sse-used flag set. * src/x86/unix64.S (ffi_call_unix64): Add ssecount argument. Only load sse registers if ssecount non-zero. (ffi_closure_unix64): Only save sse registers if carry set on entry. 2005-04-29 Ralf Corsepius * configure.ac: Add i*86-*-rtems*, sparc*-*-rtems*, powerpc-*rtems*, arm*-*-rtems*, sh-*-rtems*. * configure: Regenerate. 2005-04-20 Hans-Peter Nilsson * testsuite/lib/libffi-dg.exp (libffi-dg-test-1): In regsub use, have Tcl8.3-compatible intermediate variable. 2005-04-18 Simon Posnjak Hans-Peter Nilsson * Makefile.am: Add CRIS support. * configure.ac: Likewise. * Makefile.in, configure, testsuite/Makefile.in, include/Makefile.in: Regenerate. * src/cris: New directory. * src/cris/ffi.c, src/cris/sysv.S, src/cris/ffitarget.h: New files. * src/prep_cif.c (ffi_prep_cif): Wrap in #ifndef __CRIS__. * testsuite/lib/libffi-dg.exp (libffi-dg-test-1): Replace \n with \r?\n in output tests. 2005-04-12 Mike Stump * configure: Regenerate. 2005-03-30 Hans Boehm * src/ia64/ffitarget.h (ffi_arg): Use long long instead of DI. 2005-03-30 Steve Ellcey * src/ia64/ffitarget.h (ffi_arg) ADD DI attribute. (ffi_sarg) Ditto. * src/ia64/unix.S (ffi_closure_unix): Extend gp to 64 bits in ILP32 mode. Load 64 bits even for short data. 2005-03-23 Mike Stump * src/powerpc/darwin.S: Update for -m64 multilib. * src/powerpc/darwin_closure.S: Likewise. 2005-03-21 Zack Weinberg * configure.ac: Do not invoke TL_AC_GCC_VERSION. Do not set tool_include_dir. * aclocal.m4, configure, Makefile.in, testsuite/Makefile.in: Regenerate. * include/Makefile.am: Set gcc_version and toollibffidir. * include/Makefile.in: Regenerate. 2005-02-22 Andrew Haley * src/powerpc/ffi.c (ffi_prep_cif_machdep): Bump alignment to odd-numbered register pairs for 64-bit integer types. 2005-02-23 Andreas Tobler PR libffi/20104 * testsuite/libffi.call/return_ll1.c: New test case. 2005-02-11 Janis Johnson * testsuite/libffi.call/cls_align_longdouble.c: Remove dg-options. * testsuite/libffi.call/float.c: Ditto. * testsuite/libffi.call/float2.c: Ditto. * testsuite/libffi.call/float3.c: Ditto. 2005-02-08 Andreas Tobler * src/frv/ffitarget.h: Remove PPC stuff which does not belong to frv. 2005-01-12 Eric Botcazou * testsuite/libffi.special/special.exp (cxx_options): Add -shared-libgcc. 2004-12-31 Richard Henderson * src/types.c (FFI_AGGREGATE_TYPEDEF): Remove. (FFI_TYPEDEF): Rename from FFI_INTEGRAL_TYPEDEF. Replace size and offset parameters with a type parameter; deduce size and structure alignment. Update all users. 2004-12-31 Richard Henderson * src/types.c (FFI_TYPE_POINTER): Define with sizeof. (FFI_TYPE_LONGDOUBLE): Fix for ia64. * src/ia64/ffitarget.h (struct ffi_ia64_trampoline_struct): Move into ffi_prep_closure. * src/ia64/ia64_flags.h, src/ia64/ffi.c, src/ia64/unix.S: Rewrite from scratch. 2004-12-27 Richard Henderson * src/x86/unix64.S: Fix typo in unwind info. 2004-12-25 Richard Henderson * src/x86/ffi64.c (struct register_args): Rename from stackLayout. (enum x86_64_reg_class): Add X86_64_COMPLEX_X87_CLASS. (merge_classes): Check for it. (SSE_CLASS_P): New. (classify_argument): Pass byte_offset by value; perform all updates inside struct case. (examine_argument): Add classes argument; handle X86_64_COMPLEX_X87_CLASS. (ffi_prep_args): Merge into ... (ffi_call): ... here. Share stack frame with ffi_call_unix64. (ffi_prep_cif_machdep): Setup cif->flags for proper structure return. (ffi_fill_return_value): Remove. (ffi_prep_closure): Remove dead assert. (ffi_closure_unix64_inner): Rename from ffi_closure_UNIX64_inner. Rewrite to use struct register_args instead of va_list. Create flags for handling structure returns. * src/x86/unix64.S: Remove dead strings. (ffi_call_unix64): Rename from ffi_call_UNIX64. Rewrite to share stack frame with ffi_call. Handle structure returns properly. (float2sse, floatfloat2sse, double2sse): Remove. (sse2float, sse2double, sse2floatfloat): Remove. (ffi_closure_unix64): Rename from ffi_closure_UNIX64. Rewrite to handle structure returns properly. 2004-12-08 David Edelsohn * Makefile.am (AM_MAKEFLAGS): Remove duplicate LIBCFLAGS and PICFLAG. * Makefile.in: Regenerated. 2004-12-02 Richard Sandiford * configure.ac: Use TL_AC_GCC_VERSION to set gcc_version. * configure, aclocal.m4, Makefile.in: Regenerate. * include/Makefile.in, testsuite/Makefile.in: Regenerate. 2004-11-29 Kelley Cook * configure: Regenerate for libtool change. 2004-11-25 Kelley Cook * configure: Regenerate for libtool reversion. 2004-11-24 Kelley Cook * configure: Regenerate for libtool change. 2004-11-23 John David Anglin * testsuite/lib/libffi-dg.exp: Use new procs in target-libpath.exp. 2004-11-23 Richard Sandiford * src/mips/o32.S (ffi_call_O32, ffi_closure_O32): Use jalr instead of jal. Use an absolute encoding for the frame information. 2004-11-23 Kelley Cook * Makefile.am: Remove no-dependencies. Add ACLOCAL_AMFLAGS. * acinclude.m4: Delete logic for sincludes. * aclocal.m4, Makefile.in, configure: Regenerate. * include/Makefile: Likewise. * testsuite/Makefile: Likewise. 2004-11-22 Eric Botcazou * src/sparc/ffi.c (ffi_prep_closure): Align doubles and 64-bit integers on a 8-byte boundary. * src/sparc/v8.S (ffi_closure_v8): Reserve frame space for arguments. 2004-10-27 Richard Earnshaw * src/arm/ffi.c (ffi_prep_cif_machdep): Handle functions that return long long values. Round stack allocation to a multiple of 8 bytes for ATPCS compatibility. * src/arm/sysv.S (ffi_call_SYSV): Rework to avoid use of APCS register names. Handle returning long long types. Add Thumb and interworking support. Improve soft-float code. 2004-10-27 Richard Earnshaw * testsuite/lib/libffi-db.exp (load_gcc_lib): New function. (libffi_exit): New function. (libffi_init): Build the testglue wrapper if needed. 2004-10-25 Eric Botcazou PR other/18138 * testsuite/lib/libffi-dg.exp: Accept more than one multilib libgcc. 2004-10-25 Kazuhiro Inaoka * src/m32r/libffitarget.h (FFI_CLOSURES): Set to 0. 2004-10-20 Kaz Kojima * src/sh/sysv.S (ffi_call_SYSV): Don't align for double data. * testsuite/libffi.call/float3.c: New test case. 2004-10-18 Kaz Kojima * src/sh/ffi.c (ffi_prep_closure): Set T bit in trampoline for the function returning a structure pointed with R2. * src/sh/sysv.S (ffi_closure_SYSV): Use R2 as the pointer to the structure return value if T bit set. Emit position independent code and EH data if PIC. 2004-10-13 Kazuhiro Inaoka * Makefile.am: Add m32r support. * configure.ac: Likewise. * Makefile.in: Regenerate. * confiugre: Regenerate. * src/types.c: Add m32r port to FFI_INTERNAL_TYPEDEF (uint64, sint64, double, longdouble) * src/m32r: New directory. * src/m32r/ffi.c: New file. * src/m32r/sysv.S: Likewise. * src/m32r/ffitarget.h: Likewise. 2004-10-02 Kaz Kojima * testsuite/libffi.call/negint.c: New test case. 2004-09-14 H.J. Lu PR libgcj/17465 * testsuite/lib/libffi-dg.exp: Don't use global ld_library_path. Set up LD_LIBRARY_PATH, SHLIB_PATH, LD_LIBRARYN32_PATH, LD_LIBRARY64_PATH, LD_LIBRARY_PATH_32, LD_LIBRARY_PATH_64 and DYLD_LIBRARY_PATH. 2004-09-05 Andreas Tobler * testsuite/libffi.call/many_win32.c: Remove whitespaces. * testsuite/libffi.call/promotion.c: Likewise. * testsuite/libffi.call/return_ll.c: Remove unused var. Cleanup whitespaces. * testsuite/libffi.call/return_sc.c: Likewise. * testsuite/libffi.call/return_uc.c: Likewise. 2004-09-05 Andreas Tobler * src/powerpc/darwin.S: Fix comments and identation. * src/powerpc/darwin_closure.S: Likewise. 2004-09-02 Andreas Tobler * src/powerpc/ffi_darwin.c: Add flag for longdouble return values. (ffi_prep_args): Handle longdouble arguments. (ffi_prep_cif_machdep): Set flags for longdouble. Calculate space for longdouble. (ffi_closure_helper_DARWIN): Add closure handling for longdouble. * src/powerpc/darwin.S (_ffi_call_DARWIN): Add handling of longdouble values. * src/powerpc/darwin_closure.S (_ffi_closure_ASM): Likewise. * src/types.c: Defined longdouble size and alignment for darwin. 2004-09-02 Andreas Tobler * src/powerpc/aix.S: Remove whitespaces. * src/powerpc/aix_closure.S: Likewise. * src/powerpc/asm.h: Likewise. * src/powerpc/ffi.c: Likewise. * src/powerpc/ffitarget.h: Likewise. * src/powerpc/linux64.S: Likewise. * src/powerpc/linux64_closure.S: Likewise. * src/powerpc/ppc_closure.S: Likewise. * src/powerpc/sysv.S: Likewise. 2004-08-30 Anthony Green * Makefile.am: Add frv support. * Makefile.in, testsuite/Makefile.in: Rebuilt. * configure.ac: Read configure.host. * configure.in: Read configure.host. * configure.host: New file. frv-elf needs libgloss. * include/ffi.h.in: Force ffi_closure to have a nice big (8) alignment. This is needed to frv and shouldn't harm the others. * include/ffi_common.h (ALIGN_DOWN): New macro. * src/frv/ffi.c, src/frv/ffitarget.h, src/frv/eabi.S: New files. 2004-08-24 David Daney * testsuite/libffi.call/closure_fn0.c: Xfail mips64* instead of mips*. * testsuite/libffi.call/closure_fn1.c: Likewise. * testsuite/libffi.call/closure_fn2.c Likewise. * testsuite/libffi.call/closure_fn3.c: Likewise. * testsuite/libffi.call/closure_fn4.c: Likewise. * testsuite/libffi.call/closure_fn5.c: Likewise. * testsuite/libffi.call/cls_18byte.c: Likewise. * testsuite/libffi.call/cls_19byte.c: Likewise. * testsuite/libffi.call/cls_1_1byte.c: Likewise. * testsuite/libffi.call/cls_20byte.c: Likewise. * testsuite/libffi.call/cls_20byte1.c: Likewise. * testsuite/libffi.call/cls_24byte.c: Likewise. * testsuite/libffi.call/cls_2byte.c: Likewise. * testsuite/libffi.call/cls_3_1byte.c: Likewise. * testsuite/libffi.call/cls_3byte1.c: Likewise. * testsuite/libffi.call/cls_3byte2.c: Likewise. * testsuite/libffi.call/cls_4_1byte.c: Likewise. * testsuite/libffi.call/cls_4byte.c: Likewise. * testsuite/libffi.call/cls_64byte.c: Likewise. * testsuite/libffi.call/cls_6byte.c: Likewise. * testsuite/libffi.call/cls_7byte.c: Likewise. * testsuite/libffi.call/cls_8byte.c: Likewise. * testsuite/libffi.call/cls_9byte1.c: Likewise. * testsuite/libffi.call/cls_9byte2.c: Likewise. * testsuite/libffi.call/cls_align_double.c: Likewise. * testsuite/libffi.call/cls_align_float.c: Likewise. * testsuite/libffi.call/cls_align_longdouble.c: Likewise. * testsuite/libffi.call/cls_align_pointer.c: Likewise. * testsuite/libffi.call/cls_align_sint16.c: Likewise. * testsuite/libffi.call/cls_align_sint32.c: Likewise. * testsuite/libffi.call/cls_align_sint64.c: Likewise. * testsuite/libffi.call/cls_align_uint16.c: Likewise. * testsuite/libffi.call/cls_align_uint32.c: Likewise. * testsuite/libffi.call/cls_align_uint64.c: Likewise. * testsuite/libffi.call/cls_double.c: Likewise. * testsuite/libffi.call/cls_float.c: Likewise. * testsuite/libffi.call/cls_multi_schar.c: Likewise. * testsuite/libffi.call/cls_multi_sshort.c: Likewise. * testsuite/libffi.call/cls_multi_sshortchar.c: Likewise. * testsuite/libffi.call/cls_multi_uchar.c: Likewise. * testsuite/libffi.call/cls_multi_ushort.c: Likewise. * testsuite/libffi.call/cls_multi_ushortchar.c: Likewise. * testsuite/libffi.call/cls_schar.c: Likewise. * testsuite/libffi.call/cls_sint.c: Likewise. * testsuite/libffi.call/cls_sshort.c: Likewise. * testsuite/libffi.call/cls_uchar.c: Likewise. * testsuite/libffi.call/cls_uint.c: Likewise. * testsuite/libffi.call/cls_ulonglong.c: Likewise. * testsuite/libffi.call/cls_ushort.c: Likewise. * testsuite/libffi.call/nested_struct.c: Likewise. * testsuite/libffi.call/nested_struct1.c: Likewise. * testsuite/libffi.call/nested_struct2.c: Likewise. * testsuite/libffi.call/nested_struct3.c: Likewise. * testsuite/libffi.call/problem1.c: Likewise. * testsuite/libffi.special/unwindtest.cc: Likewise. * testsuite/libffi.call/cls_12byte.c: Likewise and set return value to zero. * testsuite/libffi.call/cls_16byte.c: Likewise. * testsuite/libffi.call/cls_5byte.c: Likewise. 2004-08-23 David Daney PR libgcj/13141 * src/mips/ffitarget.h (FFI_O32_SOFT_FLOAT): New ABI. * src/mips/ffi.c (ffi_prep_args): Fix alignment calculation. (ffi_prep_cif_machdep): Handle FFI_O32_SOFT_FLOAT floating point parameters and return types. (ffi_call): Handle FFI_O32_SOFT_FLOAT ABI. (ffi_prep_closure): Ditto. (ffi_closure_mips_inner_O32): Handle FFI_O32_SOFT_FLOAT ABI, fix alignment calculations. * src/mips/o32.S (ffi_closure_O32): Don't use floating point instructions if FFI_O32_SOFT_FLOAT, make stack frame ABI compliant. 2004-08-14 Casey Marshall * src/mips/ffi.c (ffi_pref_cif_machdep): set `cif->flags' to contain `FFI_TYPE_UINT64' as return type for any 64-bit integer (O32 ABI only). (ffi_prep_closure): new function. (ffi_closure_mips_inner_O32): new function. * src/mips/ffitarget.h: Define `FFI_CLOSURES' and `FFI_TRAMPOLINE_SIZE' appropriately if the ABI is o32. * src/mips/o32.S (ffi_call_O32): add labels for .eh_frame. Return 64 bit integers correctly. (ffi_closure_O32): new function. Added DWARF-2 unwind info for both functions. 2004-08-10 Andrew Haley * src/x86/ffi64.c (ffi_prep_args ): 8-align all stack arguments. 2004-08-01 Robert Millan * configure.ac: Detect knetbsd-gnu and kfreebsd-gnu. * configure: Regenerate. 2004-07-30 Maciej W. Rozycki * acinclude.m4 (AC_FUNC_MMAP_BLACKLIST): Check for and mmap() explicitly instead of relying on preset autoconf cache variables. * aclocal.m4: Regenerate. * configure: Regenerate. 2004-07-11 Ulrich Weigand * src/s390/ffi.c (ffi_prep_args): Fix C aliasing violation. (ffi_check_float_struct): Remove unused prototype. 2004-06-30 Geoffrey Keating * src/powerpc/ffi_darwin.c (flush_icache): ';' is a comment character on Darwin, use '\n\t' instead. 2004-06-26 Matthias Klose * libtool-version: Fix typo in revision/age. 2004-06-17 Matthias Klose * libtool-version: New. * Makefile.am (libffi_la_LDFLAGS): Use -version-info for soname. * Makefile.in: Regenerate. 2004-06-15 Paolo Bonzini * Makefile.am: Remove useless multilib rules. * Makefile.in: Regenerate. * aclocal.m4: Regenerate with automake 1.8.5. * configure.ac: Remove useless multilib configury. * configure: Regenerate. 2004-06-15 Paolo Bonzini * .cvsignore: New file. 2004-06-10 Jakub Jelinek * src/ia64/unix.S (ffi_call_unix): Insert group barrier break fp_done. (ffi_closure_UNIX): Fix f14/f15 adjustment if FLOAT_SZ is ever changed from 8. 2004-06-06 Sean McNeil * configure.ac: Add x86_64-*-freebsd* support. * configure: Regenerate. 2004-04-26 Joe Buck Bug 15093 * configure.ac: Test for existence of mmap and sys/mman.h before checking blacklist. Fix suggested by Jim Wilson. * configure: Regenerate. 2004-04-26 Matt Austern * src/powerpc/darwin.S: Go through a non-lazy pointer for initial FDE location. * src/powerpc/darwin_closure.S: Likewise. 2004-04-24 Andreas Tobler * testsuite/libffi.call/cls_multi_schar.c (main): Fix initialization error. Reported by Thomas Heller . * testsuite/libffi.call/cls_multi_sshort.c (main): Likewise. * testsuite/libffi.call/cls_multi_ushort.c (main): Likewise. 2004-03-20 Matthias Klose * src/pa/linux.S: Fix typo. 2004-03-19 Matthias Klose * Makefile.am: Update. * Makefile.in: Regenerate. * src/pa/ffi.h.in: Remove. * src/pa/ffitarget.h: New file. 2004-02-10 Randolph Chung * Makefile.am: Add PA support. * Makefile.in: Regenerate. * include/Makefile.in: Regenerate. * configure.ac: Add PA target. * configure: Regenerate. * src/pa/ffi.c: New file. * src/pa/ffi.h.in: Add PA support. * src/pa/linux.S: New file. * prep_cif.c: Add PA support. 2004-03-16 Hosaka Yuji * src/types.c: Fix alignment size of X86_WIN32 case int64 and double. * src/x86/ffi.c (ffi_prep_args): Replace ecif->cif->rtype->type with ecif->cif->flags. (ffi_call, ffi_prep_incoming_args_SYSV): Replace cif->rtype->type with cif->flags. (ffi_prep_cif_machdep): Add X86_WIN32 struct case. (ffi_closure_SYSV): Add 1 or 2-bytes struct case for X86_WIN32. * src/x86/win32.S (retstruct1b, retstruct2b, sc_retstruct1b, sc_retstruct2b): Add for 1 or 2-bytes struct case. 2004-03-15 Kelley Cook * configure.in: Rename file to ... * configure.ac: ... this. * fficonfig.h.in: Regenerate. * Makefile.in: Regenerate. * include/Makefile.in: Regenerate. * testsuite/Makefile.in: Regenerate. 2004-03-12 Matt Austern * src/powerpc/darwin.S: Fix EH information so it corresponds to changes in EH format resulting from addition of linkonce support. * src/powerpc/darwin_closure.S: Likewise. 2004-03-11 Andreas Tobler Paolo Bonzini * Makefile.am (AUTOMAKE_OPTIONS): Set them. Remove VPATH. Remove rules for object files. Remove multilib support. (AM_CCASFLAGS): Add. * configure.in (AC_CONFIG_HEADERS): Relace AM_CONFIG_HEADER. (AC_PREREQ): Bump version to 2.59. (AC_INIT): Fill with version info and bug address. (ORIGINAL_LD_FOR_MULTILIBS): Remove. (AM_ENABLE_MULTILIB): Use this instead of AC_ARG_ENABLE. De-precious CC so that the right flags are passed down to multilibs. (AC_MSG_ERROR): Replace obsolete macro AC_ERROR. (AC_CONFIG_FILES): Replace obsolete macro AC_LINK_FILES. (AC_OUTPUT): Reorganize the output with AC_CONFIG_COMMANDS. * configure: Rebuilt. * aclocal.m4: Likewise. * Makefile.in, include/Makefile.in, testsuite/Makefile.in: Likewise. * fficonfig.h.in: Likewise. 2004-03-11 Andreas Schwab * src/ia64/ffi.c (ffi_prep_incoming_args_UNIX): Get floating point arguments from fp registers only for the first 8 parameter slots. Don't convert a float parameter when passed in memory. 2004-03-09 Hans-Peter Nilsson * configure: Regenerate for config/accross.m4 correction. 2004-02-25 Matt Kraai * src/powerpc/ffi.c (ffi_prep_args_SYSV): Change ecif->cif->bytes to bytes. (ffi_prep_cif_machdep): Add braces around nested if statement. 2004-02-09 Alan Modra * src/types.c (pointer): POWERPC64 has 8 byte pointers. * src/powerpc/ffi.c (ffi_prep_args64): Correct long double handling. (ffi_closure_helper_LINUX64): Fix typo. * testsuite/libffi.call/cls_align_longdouble.c: Pass -mlong-double-128 for powerpc64-*-*. * testsuite/libffi.call/float.c: Likewise. * testsuite/libffi.call/float2.c: Likewise. 2004-02-08 Alan Modra * src/powerpc/ffi.c (ffi_prep_cif_machdep ): Correct long double function return and long double arg handling. (ffi_closure_helper_LINUX64): Formatting. Delete unused "ng" var. Use "end_pfr" instead of "nf". Correct long double handling. Localise "temp". * src/powerpc/linux64.S (ffi_call_LINUX64): Save f2 long double return value. * src/powerpc/linux64_closure.S (ffi_closure_LINUX64): Allocate space for long double return value. Adjust stack frame and offsets. Load f2 long double return. 2004-02-07 Alan Modra * src/types.c: Use 16 byte long double for POWERPC64. 2004-01-25 Eric Botcazou * src/sparc/ffi.c (ffi_prep_args_v9): Shift the parameter array when the structure return address is passed in %o0. (ffi_V9_return_struct): Rename into ffi_v9_layout_struct. (ffi_v9_layout_struct): Align the field following a nested structure on a word boundary. Use memmove instead of memcpy. (ffi_call): Update call to ffi_V9_return_struct. (ffi_prep_closure): Define 'ctx' only for V8. (ffi_closure_sparc_inner): Clone into ffi_closure_sparc_inner_v8 and ffi_closure_sparc_inner_v9. (ffi_closure_sparc_inner_v8): Return long doubles by reference. Always skip the structure return address. For structures and long doubles, copy the argument directly. (ffi_closure_sparc_inner_v9): Skip the structure return address only if required. Shift the maximum floating-point slot accordingly. For big structures, copy the argument directly; otherwise, left-justify the argument and call ffi_v9_layout_struct to lay out the structure on the stack. * src/sparc/v8.S: Undef STACKFRAME before defining it. (ffi_closure_v8): Pass the structure return address. Update call to ffi_closure_sparc_inner_v8. Short-circuit FFI_TYPE_INT handling. Skip the 'unimp' insn when returning long doubles and structures. * src/sparc/v9.S: Undef STACKFRAME before defining it. (ffi_closure_v9): Increase the frame size by 2 words. Short-circuit FFI_TYPE_INT handling. Load structures both in integers and floating-point registers on return. * README: Update status of the SPARC port. 2004-01-24 Andreas Tobler * testsuite/libffi.call/pyobjc-tc.c (main): Treat result value as of type ffi_arg. * testsuite/libffi.call/struct3.c (main): Fix CHECK. 2004-01-22 Ulrich Weigand * testsuite/libffi.call/cls_uint.c (cls_ret_uint_fn): Treat result value as of type ffi_arg, not unsigned int. 2004-01-21 Michael Ritzert * ffi64.c (ffi_prep_args): Cast the RHS of an assignment instead of the LHS. 2004-01-12 Andreas Tobler * testsuite/lib/libffi-dg.exp: Set LD_LIBRARY_PATH_32 for Solaris. 2004-01-08 Rainer Orth * testsuite/libffi.call/ffitest.h (allocate_mmap): Cast MAP_FAILED to void *. 2003-12-10 Richard Henderson * testsuite/libffi.call/cls_align_pointer.c: Cast pointers to size_t instead of int. 2003-12-04 Hosaka Yuji * testsuite/libffi.call/many_win32.c: Include . * testsuite/libffi.call/many_win32.c (main): Replace variable int i with unsigned long ul. * testsuite/libffi.call/cls_align_uint64.c: New test case. * testsuite/libffi.call/cls_align_sint64.c: Likewise. * testsuite/libffi.call/cls_align_uint32.c: Likewise. * testsuite/libffi.call/cls_align_sint32.c: Likewise. * testsuite/libffi.call/cls_align_uint16.c: Likewise. * testsuite/libffi.call/cls_align_sint16.c: Likewise. * testsuite/libffi.call/cls_align_float.c: Likewise. * testsuite/libffi.call/cls_align_double.c: Likewise. * testsuite/libffi.call/cls_align_longdouble.c: Likewise. * testsuite/libffi.call/cls_align_pointer.c: Likewise. 2003-12-02 Hosaka Yuji PR other/13221 * src/x86/ffi.c (ffi_prep_args, ffi_prep_incoming_args_SYSV): Align arguments to 32 bits. 2003-12-01 Andreas Tobler PR other/13221 * testsuite/libffi.call/cls_multi_sshort.c: New test case. * testsuite/libffi.call/cls_multi_sshortchar.c: Likewise. * testsuite/libffi.call/cls_multi_uchar.c: Likewise. * testsuite/libffi.call/cls_multi_schar.c: Likewise. * testsuite/libffi.call/cls_multi_ushortchar.c: Likewise. * testsuite/libffi.call/cls_multi_ushort.c: Likewise. * testsuite/libffi.special/unwindtest.cc: Cosmetics. 2003-11-26 Kaveh R. Ghazi * testsuite/libffi.call/ffitest.h: Include . * testsuite/libffi.special/ffitestcxx.h: Likewise. 2003-11-22 Andreas Tobler * Makefile.in: Rebuilt. * configure: Likewise. * testsuite/libffi.special/unwindtest.cc: Convert the mmap to the right type. 2003-11-21 Andreas Jaeger Andreas Tobler * acinclude.m4: Add AC_FUNC_MMAP_BLACKLIST. * configure.in: Call AC_FUNC_MMAP_BLACKLIST. * Makefile.in: Rebuilt. * aclocal.m4: Likewise. * configure: Likewise. * fficonfig.h.in: Likewise. * testsuite/lib/libffi-dg.exp: Add include dir. * testsuite/libffi.call/ffitest.h: Add MMAP definitions. * testsuite/libffi.special/ffitestcxx.h: Likewise. * testsuite/libffi.call/closure_fn0.c: Use MMAP functionality for ffi_closure if available. * testsuite/libffi.call/closure_fn1.c: Likewise. * testsuite/libffi.call/closure_fn2.c: Likewise. * testsuite/libffi.call/closure_fn3.c: Likewise. * testsuite/libffi.call/closure_fn4.c: Likewise. * testsuite/libffi.call/closure_fn5.c: Likewise. * testsuite/libffi.call/cls_12byte.c: Likewise. * testsuite/libffi.call/cls_16byte.c: Likewise. * testsuite/libffi.call/cls_18byte.c: Likewise. * testsuite/libffi.call/cls_19byte.c: Likewise. * testsuite/libffi.call/cls_1_1byte.c: Likewise. * testsuite/libffi.call/cls_20byte.c: Likewise. * testsuite/libffi.call/cls_20byte1.c: Likewise. * testsuite/libffi.call/cls_24byte.c: Likewise. * testsuite/libffi.call/cls_2byte.c: Likewise. * testsuite/libffi.call/cls_3_1byte.c: Likewise. * testsuite/libffi.call/cls_3byte1.c: Likewise. * testsuite/libffi.call/cls_3byte2.c: Likewise. * testsuite/libffi.call/cls_4_1byte.c: Likewise. * testsuite/libffi.call/cls_4byte.c: Likewise. * testsuite/libffi.call/cls_5byte.c: Likewise. * testsuite/libffi.call/cls_64byte.c: Likewise. * testsuite/libffi.call/cls_6byte.c: Likewise. * testsuite/libffi.call/cls_7byte.c: Likewise. * testsuite/libffi.call/cls_8byte.c: Likewise. * testsuite/libffi.call/cls_9byte1.c: Likewise. * testsuite/libffi.call/cls_9byte2.c: Likewise. * testsuite/libffi.call/cls_double.c: Likewise. * testsuite/libffi.call/cls_float.c: Likewise. * testsuite/libffi.call/cls_schar.c: Likewise. * testsuite/libffi.call/cls_sint.c: Likewise. * testsuite/libffi.call/cls_sshort.c: Likewise. * testsuite/libffi.call/cls_uchar.c: Likewise. * testsuite/libffi.call/cls_uint.c: Likewise. * testsuite/libffi.call/cls_ulonglong.c: Likewise. * testsuite/libffi.call/cls_ushort.c: Likewise. * testsuite/libffi.call/nested_struct.c: Likewise. * testsuite/libffi.call/nested_struct1.c: Likewise. * testsuite/libffi.call/nested_struct2.c: Likewise. * testsuite/libffi.call/nested_struct3.c: Likewise. * testsuite/libffi.call/problem1.c: Likewise. * testsuite/libffi.special/unwindtest.cc: Likewise. 2003-11-20 Andreas Tobler * testsuite/lib/libffi-dg.exp: Make the -lgcc_s conditional. 2003-11-19 Andreas Tobler * testsuite/lib/libffi-dg.exp: Add DYLD_LIBRARY_PATH for darwin. Add -lgcc_s to additional flags. 2003-11-12 Andreas Tobler * configure.in, include/Makefile.am: PR libgcj/11147, install the ffitarget.h header file in a gcc versioned and target dependent place. * configure: Regenerated. * Makefile.in, include/Makefile.in: Likewise. * testsuite/Makefile.in: Likewise. 2003-11-09 Andreas Tobler * testsuite/libffi.call/closure_fn0.c: Print result and check with dg-output to make debugging easier. * testsuite/libffi.call/closure_fn1.c: Likewise. * testsuite/libffi.call/closure_fn2.c: Likewise. * testsuite/libffi.call/closure_fn3.c: Likewise. * testsuite/libffi.call/closure_fn4.c: Likewise. * testsuite/libffi.call/closure_fn5.c: Likewise. * testsuite/libffi.call/cls_12byte.c: Likewise. * testsuite/libffi.call/cls_16byte.c: Likewise. * testsuite/libffi.call/cls_18byte.c: Likewise. * testsuite/libffi.call/cls_19byte.c: Likewise. * testsuite/libffi.call/cls_1_1byte.c: Likewise. * testsuite/libffi.call/cls_20byte.c: Likewise. * testsuite/libffi.call/cls_20byte1.c: Likewise. * testsuite/libffi.call/cls_24byte.c: Likewise. * testsuite/libffi.call/cls_2byte.c: Likewise. * testsuite/libffi.call/cls_3_1byte.c: Likewise. * testsuite/libffi.call/cls_3byte1.c: Likewise. * testsuite/libffi.call/cls_3byte2.c: Likewise. * testsuite/libffi.call/cls_4_1byte.c: Likewise. * testsuite/libffi.call/cls_4byte.c: Likewise. * testsuite/libffi.call/cls_5byte.c: Likewise. * testsuite/libffi.call/cls_64byte.c: Likewise. * testsuite/libffi.call/cls_6byte.c: Likewise. * testsuite/libffi.call/cls_7byte.c: Likewise. * testsuite/libffi.call/cls_8byte.c: Likewise. * testsuite/libffi.call/cls_9byte1.c: Likewise. * testsuite/libffi.call/cls_9byte2.c: Likewise. * testsuite/libffi.call/cls_double.c: Likewise. * testsuite/libffi.call/cls_float.c: Likewise. * testsuite/libffi.call/cls_schar.c: Likewise. * testsuite/libffi.call/cls_sint.c: Likewise. * testsuite/libffi.call/cls_sshort.c: Likewise. * testsuite/libffi.call/cls_uchar.c: Likewise. * testsuite/libffi.call/cls_uint.c: Likewise. * testsuite/libffi.call/cls_ulonglong.c: Likewise. * testsuite/libffi.call/cls_ushort.c: Likewise. * testsuite/libffi.call/problem1.c: Likewise. * testsuite/libffi.special/unwindtest.cc: Make ffi_closure static. 2003-11-08 Andreas Tobler * testsuite/libffi.call/cls_9byte2.c: New test case. * testsuite/libffi.call/cls_9byte1.c: Likewise. * testsuite/libffi.call/cls_64byte.c: Likewise. * testsuite/libffi.call/cls_20byte1.c: Likewise. * testsuite/libffi.call/cls_19byte.c: Likewise. * testsuite/libffi.call/cls_18byte.c: Likewise. * testsuite/libffi.call/closure_fn4.c: Likewise. * testsuite/libffi.call/closure_fn5.c: Likewise. * testsuite/libffi.call/cls_schar.c: Likewise. * testsuite/libffi.call/cls_sint.c: Likewise. * testsuite/libffi.call/cls_sshort.c: Likewise. * testsuite/libffi.call/nested_struct2.c: Likewise. * testsuite/libffi.call/nested_struct3.c: Likewise. 2003-11-08 Andreas Tobler * testsuite/libffi.call/cls_double.c: Do a check on the result. * testsuite/libffi.call/cls_uchar.c: Likewise. * testsuite/libffi.call/cls_uint.c: Likewise. * testsuite/libffi.call/cls_ulonglong.c: Likewise. * testsuite/libffi.call/cls_ushort.c: Likewise. * testsuite/libffi.call/return_sc.c: Cleanup whitespaces. 2003-11-06 Andreas Tobler * src/prep_cif.c (ffi_prep_cif): Move the validity check after the initialization. 2003-10-23 Andreas Tobler * src/java_raw_api.c (ffi_java_ptrarray_to_raw): Replace FFI_ASSERT(FALSE) with FFI_ASSERT(0). 2003-10-22 David Daney * src/mips/ffitarget.h: Replace undefined UINT32 and friends with __attribute__((__mode__(__SI__))) and friends. 2003-10-22 Andreas Schwab * src/ia64/ffi.c: Replace FALSE/TRUE with false/true. 2003-10-21 Andreas Tobler * configure.in: AC_LINK_FILES(ffitarget.h). * configure: Regenerate. * Makefile.in: Likewise. * include/Makefile.in: Likewise. * testsuite/Makefile.in: Likewise. * fficonfig.h.in: Likewise. 2003-10-21 Paolo Bonzini Richard Henderson Avoid that ffi.h includes fficonfig.h. * Makefile.am (EXTRA_DIST): Include ffitarget.h files (TARGET_SRC_MIPS_GCC): Renamed to TARGET_SRC_MIPS_IRIX. (TARGET_SRC_MIPS_SGI): Removed. (MIPS_GCC): Renamed to TARGET_SRC_MIPS_IRIX. (MIPS_SGI): Removed. (CLEANFILES): Removed. (mostlyclean-am, clean-am, mostlyclean-sub, clean-sub): New targets. * acconfig.h: Removed. * configure.in: Compute sizeofs only for double and long double. Use them to define and subst HAVE_LONG_DOUBLE. Include comments into AC_DEFINE instead of using acconfig.h. Create include/ffitarget.h instead of include/fficonfig.h. Rename MIPS_GCC to MIPS_IRIX, drop MIPS_SGI since we are in gcc's tree. AC_DEFINE EH_FRAME_FLAGS. * include/Makefile.am (DISTCLEANFILES): New automake macro. (hack_DATA): Add ffitarget.h. * include/ffi.h.in: Remove all system specific definitions. Declare raw API even if it is not installed, why bother? Use limits.h instead of SIZEOF_* to define ffi_type_*. Do not define EH_FRAME_FLAGS, it is in fficonfig.h now. Include ffitarget.h instead of fficonfig.h. Remove ALIGN macro. (UINT_ARG, INT_ARG): Removed, use ffi_arg and ffi_sarg instead. * include/ffi_common.h (bool): Do not define. (ffi_assert): Accept failed assertion. (ffi_type_test): Return void and accept file/line. (FFI_ASSERT): Pass stringized failed assertion. (FFI_ASSERT_AT): New macro. (FFI_ASSERT_VALID_TYPE): New macro. (UINT8, SINT8, UINT16, SINT16, UINT32, SINT32, UINT64, SINT64): Define here with gcc's __attribute__ macro instead of in ffi.h (FLOAT32, ALIGN): Define here instead of in ffi.h * include/ffi-mips.h: Removed. Its content moved to src/mips/ffitarget.h after separating assembly and C sections. * src/alpha/ffi.c, src/alpha/ffi.c, src/java_raw_api.c src/prep_cif.c, src/raw_api.c, src/ia64/ffi.c, src/mips/ffi.c, src/mips/n32.S, src/mips/o32.S, src/mips/ffitarget.h, src/sparc/ffi.c, src/x86/ffi64.c: SIZEOF_ARG -> FFI_SIZEOF_ARG. * src/ia64/ffi.c: Include stdbool.h (provided by GCC 2.95+). * src/debug.c (ffi_assert): Accept stringized failed assertion. (ffi_type_test): Rewritten. * src/prep-cif.c (initialize_aggregate, ffi_prep_cif): Call FFI_ASSERT_VALID_TYPE. * src/alpha/ffitarget.h, src/arm/ffitarget.h, src/ia64/ffitarget.h, src/m68k/ffitarget.h, src/mips/ffitarget.h, src/powerpc/ffitarget.h, src/s390/ffitarget.h, src/sh/ffitarget.h, src/sh64/ffitarget.h, src/sparc/ffitarget.h, src/x86/ffitarget.h: New files. * src/alpha/osf.S, src/arm/sysv.S, src/ia64/unix.S, src/m68k/sysv.S, src/mips/n32.S, src/mips/o32.S, src/powerpc/aix.S, src/powerpc/darwin.S, src/powerpc/ffi_darwin.c, src/powerpc/linux64.S, src/powerpc/linux64_closure.S, src/powerpc/ppc_closure.S, src/powerpc/sysv.S, src/s390/sysv.S, src/sh/sysv.S, src/sh64/sysv.S, src/sparc/v8.S, src/sparc/v9.S, src/x86/sysv.S, src/x86/unix64.S, src/x86/win32.S: include fficonfig.h 2003-10-20 Rainer Orth * src/mips/ffi.c: Use _ABIN32, _ABIO32 instead of external _MIPS_SIM_NABI32, _MIPS_SIM_ABI32. 2003-10-19 Andreas Tobler * src/powerpc/ffi_darwin.c (ffi_prep_args): Declare bytes again. Used when FFI_DEBUG = 1. 2003-10-14 Alan Modra * src/types.c (double, longdouble): Default POWERPC64 to 8 byte size and align. 2003-10-06 Rainer Orth * include/ffi_mips.h: Define FFI_MIPS_N32 for N32/N64 ABIs, FFI_MIPS_O32 for O32 ABI. 2003-10-01 Andreas Tobler * testsuite/lib/libffi-dg.exp: Set LD_LIBRARY_PATH_64 for SPARC64. Cleanup whitespaces. 2003-09-19 Andreas Tobler * testsuite/libffi.call/closure_fn0.c: Xfail mips, arm, strongarm, xscale. Cleanup whitespaces. * testsuite/libffi.call/closure_fn1.c: Likewise. * testsuite/libffi.call/closure_fn2.c: Likewise. * testsuite/libffi.call/closure_fn3.c: Likewise. * testsuite/libffi.call/cls_12byte.c: Likewise. * testsuite/libffi.call/cls_16byte.c: Likewise. * testsuite/libffi.call/cls_1_1byte.c: Likewise. * testsuite/libffi.call/cls_20byte.c: Likewise. * testsuite/libffi.call/cls_24byte.c: Likewise. * testsuite/libffi.call/cls_2byte.c: Likewise. * testsuite/libffi.call/cls_3_1byte.c: Likewise. * testsuite/libffi.call/cls_3byte1.c: Likewise. * testsuite/libffi.call/cls_3byte2.c: Likewise. * testsuite/libffi.call/cls_4_1byte.c: Likewise. * testsuite/libffi.call/cls_4byte.c: Likewise. * testsuite/libffi.call/cls_5byte.c: Likewise. * testsuite/libffi.call/cls_6byte.c: Likewise. * testsuite/libffi.call/cls_7byte.c: Likewise. * testsuite/libffi.call/cls_8byte.c: Likewise. * testsuite/libffi.call/cls_double.c: Likewise. * testsuite/libffi.call/cls_float.c: Likewise. * testsuite/libffi.call/cls_uchar.c: Likewise. * testsuite/libffi.call/cls_uint.c: Likewise. * testsuite/libffi.call/cls_ulonglong.c: Likewise. * testsuite/libffi.call/cls_ushort.c: Likewise. * testsuite/libffi.call/nested_struct.c: Likewise. * testsuite/libffi.call/nested_struct1.c: Likewise. * testsuite/libffi.call/problem1.c: Likewise. * testsuite/libffi.special/unwindtest.cc: Likewise. * testsuite/libffi.call/pyobjc-tc.c: Cleanup whitespaces. 2003-09-18 David Edelsohn * src/powerpc/aix.S: Cleanup whitespaces. * src/powerpc/aix_closure.S: Likewise. 2003-09-18 Andreas Tobler * src/powerpc/darwin.S: Cleanup whitespaces, comment formatting. * src/powerpc/darwin_closure.S: Likewise. * src/powerpc/ffi_darwin.c: Likewise. 2003-09-18 Andreas Tobler David Edelsohn * src/types.c (double): Add AIX and Darwin to the right TYPEDEF. * src/powerpc/aix_closure.S: Remove the pointer to the outgoing parameter stack. * src/powerpc/darwin_closure.S: Likewise. * src/powerpc/ffi_darwin.c (ffi_prep_args): Handle structures according to the Darwin/AIX ABI. (ffi_prep_cif_machdep): Likewise. (ffi_closure_helper_DARWIN): Likewise. Remove the outgoing parameter stack logic. Simplify the evaluation of the different CASE types. (ffi_prep_clousure): Avoid the casts on lvalues. Change the branch statement in the trampoline code. 2003-09-18 Kaz Kojima * src/sh/ffi.c (ffi_prep_args): Take account into the alignement for the register size. (ffi_closure_helper_SYSV): Handle the structure return value address correctly. (ffi_closure_helper_SYSV): Return the appropriate type when the registers are used for the structure return value. * src/sh/sysv.S (ffi_closure_SYSV): Fix the stack layout for the 64-bit return value. Update copyright years. 2003-09-17 Rainer Orth * testsuite/lib/libffi-dg.exp (libffi_target_compile): Search in srcdir for ffi_mips.h. 2003-09-12 Alan Modra * src/prep_cif.c (initialize_aggregate): Include tail padding in structure size. * src/powerpc/linux64_closure.S (ffi_closure_LINUX64): Correct placement of float result. * testsuite/libffi.special/unwindtest.cc (closure_test_fn1): Correct cast of "resp" for big-endian 64 bit machines. 2003-09-11 Alan Modra * src/types.c (double, longdouble): Merge identical SH and ARM typedefs, and add POWERPC64. * src/powerpc/ffi.c (ffi_prep_args64): Correct next_arg calc for struct split over gpr and rest. (ffi_prep_cif_machdep): Correct intarg_count for structures. * src/powerpc/linux64.S (ffi_call_LINUX64): Fix gpr offsets. 2003-09-09 Andreas Tobler * src/powerpc/ffi.c (ffi_closure_helper_SYSV) Handle struct passing correctly. 2003-09-09 Alan Modra * configure: Regenerate. 2003-09-04 Andreas Tobler * Makefile.am: Remove build rules for ffitest. * Makefile.in: Rebuilt. 2003-09-04 Andreas Tobler * src/java_raw_api.c: Include to fix compiler warning about implicit declaration of abort(). 2003-09-04 Andreas Tobler * Makefile.am: Add dejagnu test framework. Fixes PR other/11411. * Makefile.in: Rebuilt. * configure.in: Add dejagnu test framework. * configure: Rebuilt. * testsuite/Makefile.am: New file. * testsuite/Makefile.in: Built * testsuite/lib/libffi-dg.exp: New file. * testsuite/config/default.exp: Likewise. * testsuite/libffi.call/call.exp: Likewise. * testsuite/libffi.call/ffitest.h: Likewise. * testsuite/libffi.call/closure_fn0.c: Likewise. * testsuite/libffi.call/closure_fn1.c: Likewise. * testsuite/libffi.call/closure_fn2.c: Likewise. * testsuite/libffi.call/closure_fn3.c: Likewise. * testsuite/libffi.call/cls_1_1byte.c: Likewise. * testsuite/libffi.call/cls_3_1byte.c: Likewise. * testsuite/libffi.call/cls_4_1byte.c: Likewise. * testsuite/libffi.call/cls_2byte.c: Likewise. * testsuite/libffi.call/cls_3byte1.c: Likewise. * testsuite/libffi.call/cls_3byte2.c: Likewise. * testsuite/libffi.call/cls_4byte.c: Likewise. * testsuite/libffi.call/cls_5byte.c: Likewise. * testsuite/libffi.call/cls_6byte.c: Likewise. * testsuite/libffi.call/cls_7byte.c: Likewise. * testsuite/libffi.call/cls_8byte.c: Likewise. * testsuite/libffi.call/cls_12byte.c: Likewise. * testsuite/libffi.call/cls_16byte.c: Likewise. * testsuite/libffi.call/cls_20byte.c: Likewise. * testsuite/libffi.call/cls_24byte.c: Likewise. * testsuite/libffi.call/cls_double.c: Likewise. * testsuite/libffi.call/cls_float.c: Likewise. * testsuite/libffi.call/cls_uchar.c: Likewise. * testsuite/libffi.call/cls_uint.c: Likewise. * testsuite/libffi.call/cls_ulonglong.c: Likewise. * testsuite/libffi.call/cls_ushort.c: Likewise. * testsuite/libffi.call/float.c: Likewise. * testsuite/libffi.call/float1.c: Likewise. * testsuite/libffi.call/float2.c: Likewise. * testsuite/libffi.call/many.c: Likewise. * testsuite/libffi.call/many_win32.c: Likewise. * testsuite/libffi.call/nested_struct.c: Likewise. * testsuite/libffi.call/nested_struct1.c: Likewise. * testsuite/libffi.call/pyobjc-tc.c: Likewise. * testsuite/libffi.call/problem1.c: Likewise. * testsuite/libffi.call/promotion.c: Likewise. * testsuite/libffi.call/return_ll.c: Likewise. * testsuite/libffi.call/return_sc.c: Likewise. * testsuite/libffi.call/return_uc.c: Likewise. * testsuite/libffi.call/strlen.c: Likewise. * testsuite/libffi.call/strlen_win32.c: Likewise. * testsuite/libffi.call/struct1.c: Likewise. * testsuite/libffi.call/struct2.c: Likewise. * testsuite/libffi.call/struct3.c: Likewise. * testsuite/libffi.call/struct4.c: Likewise. * testsuite/libffi.call/struct5.c: Likewise. * testsuite/libffi.call/struct6.c: Likewise. * testsuite/libffi.call/struct7.c: Likewise. * testsuite/libffi.call/struct8.c: Likewise. * testsuite/libffi.call/struct9.c: Likewise. * testsuite/libffi.special/special.exp: New file. * testsuite/libffi.special/ffitestcxx.h: Likewise. * testsuite/libffi.special/unwindtest.cc: Likewise. 2003-08-13 Kaz Kojima * src/sh/ffi.c (OFS_INT16): Set 0 for little endian case. Update copyright years. 2003-08-02 Alan Modra * src/powerpc/ffi.c (ffi_prep_args64): Modify for changed gcc structure passing. (ffi_closure_helper_LINUX64): Likewise. * src/powerpc/linux64.S: Remove code writing to parm save area. * src/powerpc/linux64_closure.S (ffi_closure_LINUX64): Use return address in lr from ffi_closure_helper_LINUX64 call to calculate table address. Optimize function tail. 2003-07-28 Andreas Tobler * src/sparc/ffi.c: Handle all floating point registers. * src/sparc/v9.S: Likewise. Fixes second part of PR target/11410. 2003-07-11 Gerald Pfeifer * README: Note that libffi is not part of GCC. Update the project URL and status. 2003-06-19 Franz Sirl * src/powerpc/ppc_closure.S: Include ffi.h. 2003-06-13 Rainer Orth * src/x86/sysv.S: Avoid gas-only .uleb128/.sleb128 directives. Use C style comments. 2003-06-13 Kaz Kojima * Makefile.am: Add SHmedia support. Fix a typo of SH support. * Makefile.in: Regenerate. * configure.in (sh64-*-linux*, sh5*-*-linux*): Add target. * configure: Regenerate. * include/ffi.h.in: Add SHmedia support. * src/sh64/ffi.c: New file. * src/sh64/sysv.S: New file. 2003-05-16 Jakub Jelinek * configure.in (HAVE_RO_EH_FRAME): Check whether .eh_frame section should be read-only. * configure: Rebuilt. * fficonfig.h.in: Rebuilt. * include/ffi.h.in (EH_FRAME_FLAGS): Define. * src/alpha/osf.S: Use EH_FRAME_FLAGS. * src/powerpc/linux64.S: Likewise. * src/powerpc/linux64_closure.S: Likewise. Include ffi.h. * src/powerpc/sysv.S: Use EH_FRAME_FLAGS. Use pcrel encoding if -fpic/-fPIC/-mrelocatable. * src/powerpc/powerpc_closure.S: Likewise. * src/sparc/v8.S: If HAVE_RO_EH_FRAME is defined, don't include #write in .eh_frame flags. * src/sparc/v9.S: Likewise. * src/x86/unix64.S: Use EH_FRAME_FLAGS. * src/x86/sysv.S: Likewise. Use pcrel encoding if -fpic/-fPIC. * src/s390/sysv.S: Use EH_FRAME_FLAGS. Include ffi.h. 2003-05-07 Jeff Sturm Fixes PR bootstrap/10656 * configure.in (HAVE_AS_REGISTER_PSEUDO_OP): Test assembler support for .register pseudo-op. * src/sparc/v8.S: Use it. * fficonfig.h.in: Rebuilt. * configure: Rebuilt. 2003-04-18 Jakub Jelinek * include/ffi.h.in (POWERPC64): Define if 64-bit. (enum ffi_abi): Add FFI_LINUX64 on POWERPC. Make it the default on POWERPC64. (FFI_TRAMPOLINE_SIZE): Define to 24 on POWERPC64. * configure.in: Change powerpc-*-linux* into powerpc*-*-linux*. * configure: Rebuilt. * src/powerpc/ffi.c (hidden): Define. (ffi_prep_args_SYSV): Renamed from ffi_prep_args. Cast pointers to unsigned long to shut up warnings. (NUM_GPR_ARG_REGISTERS64, NUM_FPR_ARG_REGISTERS64, ASM_NEEDS_REGISTERS64): New. (ffi_prep_args64): New function. (ffi_prep_cif_machdep): Handle FFI_LINUX64 ABI. (ffi_call): Likewise. (ffi_prep_closure): Likewise. (flush_icache): Surround by #ifndef POWERPC64. (ffi_dblfl): New union type. (ffi_closure_helper_SYSV): Use it to avoid aliasing problems. (ffi_closure_helper_LINUX64): New function. * src/powerpc/ppc_closure.S: Surround whole file by #ifndef __powerpc64__. * src/powerpc/sysv.S: Likewise. (ffi_call_SYSV): Rename ffi_prep_args to ffi_prep_args_SYSV. * src/powerpc/linux64.S: New file. * src/powerpc/linux64_closure.S: New file. * Makefile.am (EXTRA_DIST): Add src/powerpc/linux64.S and src/powerpc/linux64_closure.S. (TARGET_SRC_POWERPC): Likewise. * src/ffitest.c (closure_test_fn, closure_test_fn1, closure_test_fn2, closure_test_fn3): Fix result printing on big-endian 64-bit machines. (main): Print tst2_arg instead of uninitialized tst2_result. * src/ffitest.c (main): Hide what closure pointer really points to from the compiler. 2003-04-16 Richard Earnshaw * configure.in (arm-*-netbsdelf*): Add configuration. (configure): Regenerated. 2003-04-04 Loren J. Rittle * include/Makefile.in: Regenerate. 2003-03-21 Zdenek Dvorak * libffi/include/ffi.h.in: Define X86 instead of X86_64 in 32 bit mode. * libffi/src/x86/ffi.c (ffi_closure_SYSV, ffi_closure_raw_SYSV): Receive closure pointer through parameter, read args using __builtin_dwarf_cfa. (FFI_INIT_TRAMPOLINE): Send closure reference through eax. 2003-03-12 Andreas Schwab * configure.in: Avoid trailing /. in toolexeclibdir. * configure: Rebuilt. 2003-03-03 Andreas Tobler * src/powerpc/darwin_closure.S: Recode to fit dynamic libraries. 2003-02-06 Andreas Tobler * libffi/src/powerpc/darwin_closure.S: Fix alignement bug, allocate 8 bytes for the result. * libffi/src/powerpc/aix_closure.S: Likewise. * libffi/src/powerpc/ffi_darwin.c: Update stackframe description for aix/darwin_closure.S. 2003-02-06 Jakub Jelinek * src/s390/ffi.c (ffi_closure_helper_SYSV): Add hidden visibility attribute. 2003-01-31 Christian Cornelssen , Andreas Schwab * configure.in: Adjust command to source config-ml.in to account for changes to the libffi_basedir definition. (libffi_basedir): Remove ${srcdir} from value and include trailing slash if nonempty. * configure: Regenerate. 2003-01-29 Franz Sirl * src/powerpc/ppc_closure.S: Recode to fit shared libs. 2003-01-28 Andrew Haley * include/ffi.h.in: Enable FFI_CLOSURES for x86_64. * src/x86/ffi64.c (ffi_prep_closure): New. (ffi_closure_UNIX64_inner): New. * src/x86/unix64.S (ffi_closure_UNIX64): New. 2003-01-27 Alexandre Oliva * configure.in (toolexecdir, toolexeclibdir): Set and AC_SUBST. Remove USE_LIBDIR conditional. * Makefile.am (toolexecdir, toolexeclibdir): Don't override. * Makefile.in, configure: Rebuilt. 2003-01027 David Edelsohn * Makefile.am (TARGET_SRC_POWERPC_AIX): Fix typo. * Makefile.in: Regenerate. 2003-01-22 Andrew Haley * src/powerpc/darwin.S (_ffi_call_AIX): Add Augmentation size to unwind info. 2003-01-21 Andreas Tobler * src/powerpc/darwin.S: Add unwind info. * src/powerpc/darwin_closure.S: Likewise. 2003-01-14 Andrew Haley * src/x86/ffi64.c (ffi_prep_args): Check for void retval. (ffi_prep_cif_machdep): Likewise. * src/x86/unix64.S: Add unwind info. 2003-01-14 Andreas Jaeger * src/ffitest.c (main): Only use ffi_closures if those are supported. 2003-01-13 Andreas Tobler * libffi/src/ffitest.c add closure testcases 2003-01-13 Kevin B. Hendricks * libffi/src/powerpc/ffi.c fix alignment bug for float (4 byte aligned iso 8 byte) 2003-01-09 Geoffrey Keating * src/powerpc/ffi_darwin.c: Remove RCS version string. * src/powerpc/darwin.S: Remove RCS version string. 2003-01-03 Jeff Sturm * include/ffi.h.in: Add closure defines for SPARC, SPARC64. * src/ffitest.c (main): Use static storage for closure. * src/sparc/ffi.c (ffi_prep_closure, ffi_closure_sparc_inner): New. * src/sparc/v8.S (ffi_closure_v8): New. * src/sparc/v9.S (ffi_closure_v9): New. 2002-11-10 Ranjit Mathew * include/ffi.h.in: Added FFI_STDCALL ffi_type enumeration for X86_WIN32. * src/x86/win32.S: Added ffi_call_STDCALL function definition. * src/x86/ffi.c (ffi_call/ffi_raw_call): Added switch cases for recognising FFI_STDCALL and calling ffi_call_STDCALL if target is X86_WIN32. * src/ffitest.c (my_stdcall_strlen/stdcall_many): stdcall versions of the "my_strlen" and "many" test functions (for X86_WIN32). Added test cases to test stdcall invocation using these functions. 2002-12-02 Kaz Kojima * src/sh/sysv.S: Add DWARF2 unwind info. 2002-11-27 Ulrich Weigand * src/s390/sysv.S (.eh_frame section): Make section read-only. 2002-11-26 Jim Wilson * src/types.c (FFI_TYPE_POINTER): Has size 8 on IA64. 2002-11-23 H.J. Lu * acinclude.m4: Add dummy AM_PROG_LIBTOOL. Include ../config/accross.m4. * aclocal.m4; Rebuild. * configure: Likewise. 2002-11-15 Ulrich Weigand * src/s390/sysv.S (.eh_frame section): Adapt to pcrel FDE encoding. 2002-11-11 DJ Delorie * configure.in: Look for common files in the right place. 2002-10-08 Ulrich Weigand * src/java_raw_api.c (ffi_java_raw_to_ptrarray): Interpret raw data as _Jv_word values, not ffi_raw. (ffi_java_ptrarray_to_raw): Likewise. (ffi_java_rvalue_to_raw): New function. (ffi_java_raw_call): Call it. (ffi_java_raw_to_rvalue): New function. (ffi_java_translate_args): Call it. * src/ffitest.c (closure_test_fn): Interpret return value as ffi_arg, not int. * src/s390/ffi.c (ffi_prep_cif_machdep): Add missing FFI_TYPE_POINTER case. (ffi_closure_helper_SYSV): Likewise. Also, assume return values extended to word size. 2002-10-02 Andreas Jaeger * src/x86/ffi64.c (ffi_prep_cif_machdep): Remove debug output. 2002-10-01 Bo Thorsen * include/ffi.h.in: Fix i386 win32 compilation. 2002-09-30 Ulrich Weigand * configure.in: Add s390x-*-linux-* target. * configure: Regenerate. * include/ffi.h.in: Define S390X for s390x targets. (FFI_CLOSURES): Define for s390/s390x. (FFI_TRAMPOLINE_SIZE): Likewise. (FFI_NATIVE_RAW_API): Likewise. * src/prep_cif.c (ffi_prep_cif): Do not compute stack space for s390. * src/types.c (FFI_TYPE_POINTER): Use 8-byte pointers on s390x. * src/s390/ffi.c: Major rework of existing code. Add support for s390x targets. Add closure support. * src/s390/sysv.S: Likewise. 2002-09-29 Richard Earnshaw * src/arm/sysv.S: Fix typo. 2002-09-28 Richard Earnshaw * src/arm/sysv.S: If we don't have machine/asm.h and the pre-processor has defined __USER_LABEL_PREFIX__, then use it in CNAME. (ffi_call_SYSV): Handle soft-float. 2002-09-27 Bo Thorsen * include/ffi.h.in: Fix multilib x86-64 support. 2002-09-22 Kaveh R. Ghazi * Makefile.am (all-multi): Fix multilib parallel build. 2002-07-19 Kaz Kojima * configure.in (sh[34]*-*-linux*): Add brackets. * configure: Regenerate. 2002-07-18 Kaz Kojima * Makefile.am: Add SH support. * Makefile.in: Regenerate. * configure.in (sh-*-linux*, sh[34]*-*-linux*): Add target. * configure: Regenerate. * include/ffi.h.in: Add SH support. * src/sh/ffi.c: New file. * src/sh/sysv.S: New file. * src/types.c: Add SH support. 2002-07-16 Bo Thorsen * src/x86/ffi64.c: New file that adds x86-64 support. * src/x86/unix64.S: New file that handles argument setup for x86-64. * src/x86/sysv.S: Don't use this on x86-64. * src/x86/ffi.c: Don't use this on x86-64. Remove unused vars. * src/prep_cif.c (ffi_prep_cif): Don't do stack size calculation for x86-64. * src/ffitest.c (struct6): New test that tests a special case in the x86-64 ABI. (struct7): Likewise. (struct8): Likewise. (struct9): Likewise. (closure_test_fn): Silence warning about this when it's not used. (main): Add the new tests. (main): Fix a couple of wrong casts and silence some compiler warnings. * include/ffi.h.in: Add x86-64 ABI definition. * fficonfig.h.in: Regenerate. * Makefile.am: Add x86-64 support. * configure.in: Likewise. * Makefile.in: Regenerate. * configure: Likewise. 2002-06-24 Bo Thorsen * src/types.c: Merge settings for similar architectures. Add x86-64 sizes and alignments. 2002-06-23 Bo Thorsen * src/arm/ffi.c (ffi_prep_args): Remove unused vars. * src/sparc/ffi.c (ffi_prep_args_v8): Likewise. * src/mips/ffi.c (ffi_prep_args): Likewise. * src/m68k/ffi.c (ffi_prep_args): Likewise. 2002-07-18 H.J. Lu (hjl@gnu.org) * Makefile.am (TARGET_SRC_MIPS_LINUX): New. (libffi_la_SOURCES): Support MIPS_LINUX. (libffi_convenience_la_SOURCES): Likewise. * Makefile.in: Regenerated. * configure.in (mips64*-*): Skip. (mips*-*-linux*): New. * configure: Regenerated. * src/mips/ffi.c: Include . 2002-06-06 Ulrich Weigand * src/s390/sysv.S: Save/restore %r6. Add DWARF-2 unwind info. 2002-05-27 Roger Sayle * src/x86/ffi.c (ffi_prep_args): Remove reference to avn. 2002-05-27 Bo Thorsen * src/x86/ffi.c (ffi_prep_args): Remove unused variable and fix formatting. 2002-05-13 Andreas Tobler * src/powerpc/ffi_darwin.c (ffi_prep_closure): Declare fd at beginning of function (for older apple cc). 2002-05-08 Alexandre Oliva * configure.in (ORIGINAL_LD_FOR_MULTILIBS): Preserve LD at script entry, and set LD to it when configuring multilibs. * configure: Rebuilt. 2002-05-05 Jason Thorpe * configure.in (sparc64-*-netbsd*): Add target. (sparc-*-netbsdelf*): Likewise. * configure: Regenerate. 2002-04-28 David S. Miller * configure.in, configure: Fix SPARC test in previous change. 2002-04-29 Gerhard Tonn * Makefile.am: Add Linux for S/390 support. * Makefile.in: Regenerate. * configure.in: Add Linux for S/390 support. * configure: Regenerate. * include/ffi.h.in: Add Linux for S/390 support. * src/s390/ffi.c: New file from libffi CVS tree. * src/s390/sysv.S: New file from libffi CVS tree. 2002-04-28 Jakub Jelinek * configure.in (HAVE_AS_SPARC_UA_PCREL): Check for working %r_disp32(). * src/sparc/v8.S: Use it. * src/sparc/v9.S: Likewise. * fficonfig.h.in: Rebuilt. * configure: Rebuilt. 2002-04-08 Hans Boehm * src/java_raw_api.c (ffi_java_raw_size): Handle FFI_TYPE_DOUBLE correctly. * src/ia64/unix.S: Add unwind information. Fix comments. Save sp in a way that's compatible with unwind info. (ffi_call_unix): Correctly restore sp in all cases. * src/ia64/ffi.c: Add, fix comments. 2002-04-08 Jakub Jelinek * src/sparc/v8.S: Make .eh_frame dependent on target word size. 2002-04-06 Jason Thorpe * configure.in (alpha*-*-netbsd*): Add target. * configure: Regenerate. 2002-04-04 Jeff Sturm * src/sparc/v8.S: Add unwind info. * src/sparc/v9.S: Likewise. 2002-03-30 Krister Walfridsson * configure.in: Enable i*86-*-netbsdelf*. * configure: Rebuilt. 2002-03-29 David Billinghurst PR other/2620 * src/mips/n32.s: Delete * src/mips/o32.s: Delete 2002-03-21 Loren J. Rittle * configure.in: Enable alpha*-*-freebsd*. * configure: Rebuilt. 2002-03-17 Bryce McKinlay * Makefile.am: libfficonvenience -> libffi_convenience. * Makefile.in: Rebuilt. * Makefile.am: Define ffitest_OBJECTS. * Makefile.in: Rebuilt. 2002-03-07 Andreas Tobler David Edelsohn * Makefile.am (EXTRA_DIST): Add Darwin and AIX closure files. (TARGET_SRC_POWERPC_AIX): Add aix_closure.S. (TARGET_SRC_POWERPC_DARWIN): Add darwin_closure.S. * Makefile.in: Regenerate. * include/ffi.h.in: Add AIX and Darwin closure definitions. * src/powerpc/ffi_darwin.c (ffi_prep_closure): New function. (flush_icache, flush_range): New functions. (ffi_closure_helper_DARWIN): New function. * src/powerpc/aix_closure.S: New file. * src/powerpc/darwin_closure.S: New file. 2002-02-24 Jeff Sturm * include/ffi.h.in: Add typedef for ffi_arg. * src/ffitest.c (main): Declare rint with ffi_arg. 2002-02-21 Andreas Tobler * src/powerpc/ffi_darwin.c (ffi_prep_args): Skip appropriate number of GPRs for floating-point arguments. 2002-01-31 Anthony Green * configure: Rebuilt. * configure.in: Replace CHECK_SIZEOF and endian tests with cross-compiler friendly macros. * aclocal.m4 (AC_COMPILE_CHECK_SIZEOF, AC_C_BIGENDIAN_CROSS): New macros. 2002-01-18 David Edelsohn * src/powerpc/darwin.S (_ffi_call_AIX): New. * src/powerpc/aix.S (ffi_call_DARWIN): New. 2002-01-17 David Edelsohn * Makefile.am (EXTRA_DIST): Add Darwin and AIX files. (TARGET_SRC_POWERPC_AIX): New. (POWERPC_AIX): New stanza. * Makefile.in: Regenerate. * configure.in: Add AIX case. * configure: Regenerate. * include/ffi.h.in (ffi_abi): Add FFI_AIX. * src/powerpc/ffi_darwin.c (ffi_status): Use "long" to scale frame size. Fix "long double" support. (ffi_call): Add FFI_AIX case. * src/powerpc/aix.S: New. 2001-10-09 John Hornkvist Implement Darwin PowerPC ABI. * configure.in: Handle powerpc-*-darwin*. * Makefile.am: Set source files for POWERPC_DARWIN. * configure: Rebuilt. * Makefile.in: Rebuilt. * include/ffi.h.in: Define FFI_DARWIN and FFI_DEFAULT_ABI for POWERPC_DARWIN. * src/powerpc/darwin.S: New file. * src/powerpc/ffi_darwin.c: New file. 2001-10-07 Joseph S. Myers * src/x86/ffi.c: Fix spelling error of "separate" as "seperate". 2001-07-16 Rainer Orth * src/x86/sysv.S: Avoid gas-only .balign directive. Use C style comments. 2001-07-16 Rainer Orth * src/alpha/ffi.c (ffi_prep_closure): Avoid gas-only mnemonic. Fixes PR bootstrap/3563. 2001-06-26 Rainer Orth * src/alpha/osf.S (ffi_closure_osf): Use .rdata for ECOFF. 2001-06-25 Rainer Orth * configure.in: Recognize sparc*-sun-* host. * configure: Regenerate. 2001-06-06 Andrew Haley * src/alpha/osf.S (__FRAME_BEGIN__): Conditionalize for ELF. 2001-06-03 Andrew Haley * src/alpha/osf.S: Add unwind info. * src/powerpc/sysv.S: Add unwind info. * src/powerpc/ppc_closure.S: Likewise. 2000-05-31 Jeff Sturm * configure.in: Fix AC_ARG_ENABLE usage. * configure: Rebuilt. 2001-05-06 Bryce McKinlay * configure.in: Remove warning about beta code. * configure: Rebuilt. 2001-04-25 Hans Boehm * src/ia64/unix.S: Restore stack pointer when returning from ffi_closure_UNIX. * src/ia64/ffi.c: Fix typo in comment. 2001-04-18 Jim Wilson * src/ia64/unix.S: Delete unnecessary increment and decrement of loc2 to eliminate RAW DV. 2001-04-12 Bryce McKinlay * Makefile.am: Make a libtool convenience library. * Makefile.in: Rebuilt. 2001-03-29 Bryce McKinlay * configure.in: Use different syntax for subdirectory creation. * configure: Rebuilt. 2001-03-27 Jon Beniston * configure.in: Added X86_WIN32 target (Win32, CygWin, MingW). * configure: Rebuilt. * Makefile.am: Added X86_WIN32 target support. * Makefile.in: Rebuilt. * include/ffi.h.in: Added X86_WIN32 target support. * src/ffitest.c: Doesn't run structure tests for X86_WIN32 targets. * src/types.c: Added X86_WIN32 target support. * src/x86/win32.S: New file. Based on sysv.S, but with EH stuff removed and made to work with CygWin's gas. 2001-03-26 Bryce McKinlay * configure.in: Make target subdirectory in build dir. * Makefile.am: Override suffix based rules to specify correct output subdirectory. * Makefile.in: Rebuilt. * configure: Rebuilt. 2001-03-23 Kevin B Hendricks * src/powerpc/ppc_closure.S: New file. * src/powerpc/ffi.c (ffi_prep_args): Fixed ABI compatibility bug involving long long and register pairs. (ffi_prep_closure): New function. (flush_icache): Likewise. (ffi_closure_helper_SYSV): Likewise. * include/ffi.h.in (FFI_CLOSURES): Define on PPC. (FFI_TRAMPOLINE_SIZE): Likewise. (FFI_NATIVE_RAW_API): Likewise. * Makefile.in: Rebuilt. * Makefile.am (EXTRA_DIST): Added src/powerpc/ppc_closure.S. (TARGET_SRC_POWERPC): Likewise. 2001-03-19 Tom Tromey * Makefile.in: Rebuilt. * Makefile.am (ffitest_LDFLAGS): New macro. 2001-03-02 Nick Clifton * include/ffi.h.in: Remove RCS ident string. * include/ffi_mips.h: Remove RCS ident string. * src/debug.c: Remove RCS ident string. * src/ffitest.c: Remove RCS ident string. * src/prep_cif.c: Remove RCS ident string. * src/types.c: Remove RCS ident string. * src/alpha/ffi.c: Remove RCS ident string. * src/alpha/osf.S: Remove RCS ident string. * src/arm/ffi.c: Remove RCS ident string. * src/arm/sysv.S: Remove RCS ident string. * src/mips/ffi.c: Remove RCS ident string. * src/mips/n32.S: Remove RCS ident string. * src/mips/o32.S: Remove RCS ident string. * src/sparc/ffi.c: Remove RCS ident string. * src/sparc/v8.S: Remove RCS ident string. * src/sparc/v9.S: Remove RCS ident string. * src/x86/ffi.c: Remove RCS ident string. * src/x86/sysv.S: Remove RCS ident string. 2001-02-08 Joseph S. Myers * include/ffi.h.in: Change sourceware.cygnus.com references to gcc.gnu.org. 2000-12-09 Richard Henderson * src/alpha/ffi.c (ffi_call): Simplify struct return test. (ffi_closure_osf_inner): Index rather than increment avalue and arg_types. Give ffi_closure_osf the raw return value type. * src/alpha/osf.S (ffi_closure_osf): Handle return value type promotion. 2000-12-07 Richard Henderson * src/raw_api.c (ffi_translate_args): Fix typo. (ffi_prep_closure): Likewise. * include/ffi.h.in [ALPHA]: Define FFI_CLOSURES and FFI_TRAMPOLINE_SIZE. * src/alpha/ffi.c (ffi_prep_cif_machdep): Adjust minimal cif->bytes for new ffi_call_osf implementation. (ffi_prep_args): Absorb into ... (ffi_call): ... here. Do all stack allocation here and avoid a callback function. (ffi_prep_closure, ffi_closure_osf_inner): New. * src/alpha/osf.S (ffi_call_osf): Reimplement with no callback. (ffi_closure_osf): New. 2000-09-10 Alexandre Oliva * config.guess, config.sub, install-sh: Removed. * ltconfig, ltmain.sh, missing, mkinstalldirs: Likewise. * Makefile.in: Rebuilt. * acinclude.m4: Include libtool macros from the top level. * aclocal.m4, configure: Rebuilt. 2000-08-22 Alexandre Oliva * configure.in [i*86-*-freebsd*] (TARGET, TARGETDIR): Set. * configure: Rebuilt. 2000-05-11 Scott Bambrough * libffi/src/arm/sysv.S (ffi_call_SYSV): Doubles are not saved to memory correctly. Use conditional instructions, not branches where possible. 2000-05-04 Tom Tromey * configure: Rebuilt. * configure.in: Match `arm*-*-linux-*'. From Chris Dornan . 2000-04-28 Jakub Jelinek * Makefile.am (SUBDIRS): Define. (AM_MAKEFLAGS): Likewise. (Multilib support.): Add section. * Makefile.in: Rebuilt. * ltconfig (extra_compiler_flags, extra_compiler_flags_value): New variables. Set for gcc using -print-multi-lib. Export them to libtool. (sparc64-*-linux-gnu*): Use libsuff 64 for search paths. * ltmain.sh (B|b|V): Don't throw away gcc's -B, -b and -V options for -shared links. (extra_compiler_flags_value, extra_compiler_flags): Check these for extra compiler options which need to be passed down in compiler_flags. 2000-04-16 Anthony Green * configure: Rebuilt. * configure.in: Change i*86-pc-linux* to i*86-*-linux*. 2000-04-14 Jakub Jelinek * include/ffi.h.in (SPARC64): Define for 64bit SPARC builds. Set SPARC FFI_DEFAULT_ABI based on SPARC64 define. * src/sparc/ffi.c (ffi_prep_args_v8): Renamed from ffi_prep_args. Replace all void * sizeofs with sizeof(int). Only compare type with FFI_TYPE_LONGDOUBLE if LONGDOUBLE is different than DOUBLE. Remove FFI_TYPE_SINT32 and FFI_TYPE_UINT32 cases (handled elsewhere). (ffi_prep_args_v9): New function. (ffi_prep_cif_machdep): Handle V9 ABI and long long on V8. (ffi_V9_return_struct): New function. (ffi_call): Handle FFI_V9 ABI from 64bit code and FFI_V8 ABI from 32bit code (not yet cross-arch calls). * src/sparc/v8.S: Add struct return delay nop. Handle long long. * src/sparc/v9.S: New file. * src/prep_cif.c (ffi_prep_cif): Return structure pointer is used on sparc64 only for structures larger than 32 bytes. Pass by reference for structures is done for structure arguments larger than 16 bytes. * src/ffitest.c (main): Use 64bit rint on sparc64. Run long long tests on sparc. * src/types.c (FFI_TYPE_POINTER): Pointer is 64bit on alpha and sparc64. (FFI_TYPE_LONGDOUBLE): long double is 128 bit aligned to 128 bits on sparc64. * configure.in (sparc-*-linux*): New supported target. (sparc64-*-linux*): Likewise. * configure: Rebuilt. * Makefile.am: Add v9.S to SPARC files. * Makefile.in: Likewise. (LINK): Surround $(CCLD) into double quotes, so that multilib compiles work correctly. 2000-04-04 Alexandre Petit-Bianco * configure: Rebuilt. * configure.in: (i*86-*-solaris*): New libffi target. Patch proposed by Bryce McKinlay. 2000-03-20 Tom Tromey * Makefile.in: Hand edit for java_raw_api.lo. 2000-03-08 Bryce McKinlay * config.guess, config.sub: Update from the gcc tree. Fix for PR libgcj/168. 2000-03-03 Tom Tromey * Makefile.in: Fixed ia64 by hand. * configure: Rebuilt. * configure.in (--enable-multilib): New option. (libffi_basedir): New subst. (AC_OUTPUT): Added multilib code. 2000-03-02 Tom Tromey * Makefile.in: Rebuilt. * Makefile.am (TARGET_SRC_IA64): Use `ia64', not `alpha', as directory name. 2000-02-25 Hans Boehm * src/ia64/ffi.c, src/ia64/ia64_flags.h, src/ia64/unix.S: New files. * src/raw_api.c (ffi_translate_args): Fixed typo in argument list. (ffi_prep_raw_closure): Use ffi_translate_args, not ffi_closure_translate. * src/java_raw_api.c: New file. * src/ffitest.c (closure_test_fn): New function. (main): Define `rint' as long long on IA64. Added new test when FFI_CLOSURES is defined. * include/ffi.h.in (ALIGN): Use size_t, not unsigned. (ffi_abi): Recognize IA64. (ffi_raw): Added `flt' field. Added "Java raw API" code. * configure.in: Recognize ia64. * Makefile.am (TARGET_SRC_IA64): New macro. (libffi_la_common_SOURCES): Added java_raw_api.c. (libffi_la_SOURCES): Define in IA64 case. 2000-01-04 Tom Tromey * Makefile.in: Rebuilt with newer automake. 1999-12-31 Tom Tromey * Makefile.am (INCLUDES): Added -I$(top_srcdir)/src. 1999-09-01 Tom Tromey * include/ffi.h.in: Removed PACKAGE and VERSION defines and undefs. * fficonfig.h.in: Rebuilt. * configure: Rebuilt. * configure.in: Pass 3rd argument to AM_INIT_AUTOMAKE. Use AM_PROG_LIBTOOL (automake 1.4 compatibility). * acconfig.h: Don't #undef PACKAGE or VERSION. 1999-08-09 Anthony Green * include/ffi.h.in: Try to work around messy header problem with PACKAGE and VERSION. * configure: Rebuilt. * configure.in: Change version to 2.00-beta. * fficonfig.h.in: Rebuilt. * acconfig.h (FFI_NO_STRUCTS, FFI_NO_RAW_API): Define. * src/x86/ffi.c (ffi_raw_call): Rename. 1999-08-02 Kresten Krab Thorup * src/x86/ffi.c (ffi_closure_SYSV): New function. (ffi_prep_incoming_args_SYSV): Ditto. (ffi_prep_closure): Ditto. (ffi_closure_raw_SYSV): Ditto. (ffi_prep_raw_closure): More ditto. (ffi_call_raw): Final ditto. * include/ffi.h.in: Add definitions for closure and raw API. * src/x86/ffi.c (ffi_prep_cif_machdep): Added case for FFI_TYPE_UINT64. * Makefile.am (libffi_la_common_SOURCES): Added raw_api.c * src/raw_api.c: New file. * include/ffi.h.in (ffi_raw): New type. (UINT_ARG, SINT_ARG): New defines. (ffi_closure, ffi_raw_closure): New types. (ffi_prep_closure, ffi_prep_raw_closure): New declarations. * configure.in: Add check for endianness and sizeof void*. * src/x86/sysv.S (ffi_call_SYSV): Call fixup routine via argument, instead of directly. * configure: Rebuilt. Thu Jul 8 14:28:42 1999 Anthony Green * configure.in: Add x86 and powerpc BeOS configurations. From Makoto Kato . 1999-05-09 Anthony Green * configure.in: Add warning about this being beta code. Remove src/Makefile.am from the picture. * configure: Rebuilt. * Makefile.am: Move logic from src/Makefile.am. Add changes to support libffi as a target library. * Makefile.in: Rebuilt. * aclocal.m4, config.guess, config.sub, ltconfig, ltmain.sh: Upgraded to new autoconf, automake, libtool. * README: Tweaks. * LICENSE: Update copyright date. * src/Makefile.am, src/Makefile.in: Removed. 1998-11-29 Anthony Green * include/ChangeLog: Removed. * src/ChangeLog: Removed. * src/mips/ChangeLog: Removed. * src/sparc/ChangeLog: Remboved. * src/x86/ChangeLog: Removed. * ChangeLog.v1: Created. smalltalk-3.2.5/libffi/Makefile.am0000644000175000017500000001002212130343734013710 00000000000000## Process this with automake to create Makefile.in AUTOMAKE_OPTIONS = foreign subdir-objects ACLOCAL_AMFLAGS = -I ../build-aux SUBDIRS = include EXTRA_DIST = LICENSE ChangeLog.v1 ChangeLog.libgcj configure.host \ src/alpha/ffi.c src/alpha/osf.S src/alpha/ffitarget.h \ src/arm/ffi.c src/arm/sysv.S src/arm/ffitarget.h \ src/avr32/ffi.c src/avr32/sysv.S src/avr32/ffitarget.h \ src/cris/ffi.c src/cris/sysv.S src/cris/ffitarget.h \ src/ia64/ffi.c src/ia64/ffitarget.h src/ia64/ia64_flags.h \ src/ia64/unix.S \ src/mips/ffi.c src/mips/n32.S src/mips/o32.S \ src/mips/ffitarget.h \ src/m32r/ffi.c src/m32r/sysv.S src/m32r/ffitarget.h \ src/m68k/ffi.c src/m68k/sysv.S src/m68k/ffitarget.h \ src/powerpc/ffi.c src/powerpc/sysv.S \ src/powerpc/linux64.S src/powerpc/linux64_closure.S \ src/powerpc/ppc_closure.S src/powerpc/asm.h \ src/powerpc/aix.S src/powerpc/darwin.S \ src/powerpc/aix_closure.S src/powerpc/darwin_closure.S \ src/powerpc/ffi_darwin.c src/powerpc/ffitarget.h \ src/s390/ffi.c src/s390/sysv.S src/s390/ffitarget.h \ src/sh/ffi.c src/sh/sysv.S src/sh/ffitarget.h \ src/sh64/ffi.c src/sh64/sysv.S src/sh64/ffitarget.h \ src/sparc/v8.S src/sparc/v9.S src/sparc/ffitarget.h \ src/sparc/ffi.c src/x86/darwin64.S \ src/x86/ffi.c src/x86/sysv.S src/x86/win32.S src/x86/darwin.S \ src/x86/ffi64.c src/x86/unix64.S src/x86/ffitarget.h \ src/pa/ffitarget.h src/pa/ffi.c src/pa/linux.S src/pa/hpux32.S \ src/frv/ffi.c src/frv/eabi.S src/frv/ffitarget.h src/dlmalloc.c ## ################################################################ noinst_LTLIBRARIES = libffi.la libffi_la_SOURCES = src/debug.c src/prep_cif.c src/types.c \ src/raw_api.c src/java_raw_api.c src/closures.c nodist_libffi_la_SOURCES = if MIPS nodist_libffi_la_SOURCES += src/mips/ffi.c src/mips/o32.S src/mips/n32.S endif if X86 nodist_libffi_la_SOURCES += src/x86/ffi.c src/x86/sysv.S endif if X86_FREEBSD nodist_libffi_la_SOURCES += src/x86/ffi.c src/x86/freebsd.S endif if X86_WIN32 nodist_libffi_la_SOURCES += src/x86/ffi.c src/x86/win32.S endif if X86_WIN64 nodist_libffi_la_SOURCES += src/x86/ffi.c src/x86/win64.S endif if X86_DARWIN nodist_libffi_la_SOURCES += src/x86/ffi.c src/x86/darwin.S src/x86/ffi64.c src/x86/darwin64.S endif if SPARC nodist_libffi_la_SOURCES += src/sparc/ffi.c src/sparc/v8.S src/sparc/v9.S endif if ALPHA nodist_libffi_la_SOURCES += src/alpha/ffi.c src/alpha/osf.S endif if IA64 nodist_libffi_la_SOURCES += src/ia64/ffi.c src/ia64/unix.S endif if M32R nodist_libffi_la_SOURCES += src/m32r/sysv.S src/m32r/ffi.c endif if M68K nodist_libffi_la_SOURCES += src/m68k/ffi.c src/m68k/sysv.S endif if POWERPC nodist_libffi_la_SOURCES += src/powerpc/ffi.c src/powerpc/sysv.S src/powerpc/ppc_closure.S src/powerpc/linux64.S src/powerpc/linux64_closure.S endif if POWERPC_AIX nodist_libffi_la_SOURCES += src/powerpc/ffi_darwin.c src/powerpc/aix.S src/powerpc/aix_closure.S endif if POWERPC_DARWIN nodist_libffi_la_SOURCES += src/powerpc/ffi_darwin.c src/powerpc/darwin.S src/powerpc/darwin_closure.S endif if POWERPC_FREEBSD nodist_libffi_la_SOURCES += src/powerpc/ffi.c src/powerpc/sysv.S src/powerpc/ppc_closure.S endif if ARM nodist_libffi_la_SOURCES += src/arm/sysv.S src/arm/ffi.c endif if AVR32 nodist_libffi_la_SOURCES += src/avr32/sysv.S src/avr32/ffi.c endif if LIBFFI_CRIS nodist_libffi_la_SOURCES += src/cris/sysv.S src/cris/ffi.c endif if FRV nodist_libffi_la_SOURCES += src/frv/eabi.S src/frv/ffi.c endif if S390 nodist_libffi_la_SOURCES += src/s390/sysv.S src/s390/ffi.c endif if X86_64 nodist_libffi_la_SOURCES += src/x86/ffi64.c src/x86/unix64.S src/x86/ffi.c src/x86/sysv.S endif if SH nodist_libffi_la_SOURCES += src/sh/sysv.S src/sh/ffi.c endif if SH64 nodist_libffi_la_SOURCES += src/sh64/sysv.S src/sh64/ffi.c endif if PA_LINUX nodist_libffi_la_SOURCES += src/pa/linux.S src/pa/ffi.c endif if PA_HPUX nodist_libffi_la_SOURCES += src/pa/hpux32.S src/pa/ffi.c endif AM_CFLAGS = -Wall -g -fexceptions AM_CPPFLAGS = -I. -I$(top_srcdir)/include -Iinclude -I$(top_srcdir)/src AM_CCASFLAGS = $(AM_CPPFLAGS) # No install-html support .PHONY: install-html install-html: smalltalk-3.2.5/libffi/Makefile.in0000644000175000017500000015150612130455522013735 00000000000000# Makefile.in generated by automake 1.11.6 from Makefile.am. # @configure_input@ # Copyright (C) 1994, 1995, 1996, 1997, 1998, 1999, 2000, 2001, 2002, # 2003, 2004, 2005, 2006, 2007, 2008, 2009, 2010, 2011 Free Software # Foundation, Inc. # This Makefile.in is free software; the Free Software Foundation # gives unlimited permission to copy and/or distribute it, # with or without modifications, as long as this notice is preserved. # This program is distributed in the hope that it will be useful, # but WITHOUT ANY WARRANTY, to the extent permitted by law; without # even the implied warranty of MERCHANTABILITY or FITNESS FOR A # PARTICULAR PURPOSE. @SET_MAKE@ VPATH = @srcdir@ am__make_dryrun = \ { \ am__dry=no; \ case $$MAKEFLAGS in \ *\\[\ \ ]*) \ echo 'am--echo: ; @echo "AM" OK' | $(MAKE) -f - 2>/dev/null \ | grep '^AM OK$$' >/dev/null || am__dry=yes;; \ *) \ for am__flg in $$MAKEFLAGS; do \ case $$am__flg in \ *=*|--*) ;; \ *n*) am__dry=yes; break;; \ esac; \ done;; \ esac; \ test $$am__dry = yes; \ } pkgdatadir = $(datadir)/@PACKAGE@ pkgincludedir = $(includedir)/@PACKAGE@ pkglibdir = $(libdir)/@PACKAGE@ pkglibexecdir = $(libexecdir)/@PACKAGE@ am__cd = CDPATH="$${ZSH_VERSION+.}$(PATH_SEPARATOR)" && cd install_sh_DATA = $(install_sh) -c -m 644 install_sh_PROGRAM = $(install_sh) -c install_sh_SCRIPT = $(install_sh) -c INSTALL_HEADER = $(INSTALL_DATA) transform = $(program_transform_name) NORMAL_INSTALL = : PRE_INSTALL = : POST_INSTALL = : NORMAL_UNINSTALL = : PRE_UNINSTALL = : POST_UNINSTALL = : build_triplet = @build@ host_triplet = @host@ target_triplet = @target@ @MIPS_TRUE@am__append_1 = src/mips/ffi.c src/mips/o32.S src/mips/n32.S @X86_TRUE@am__append_2 = src/x86/ffi.c src/x86/sysv.S @X86_FREEBSD_TRUE@am__append_3 = src/x86/ffi.c src/x86/freebsd.S @X86_WIN32_TRUE@am__append_4 = src/x86/ffi.c src/x86/win32.S @X86_WIN64_TRUE@am__append_5 = src/x86/ffi.c src/x86/win64.S @X86_DARWIN_TRUE@am__append_6 = src/x86/ffi.c src/x86/darwin.S src/x86/ffi64.c src/x86/darwin64.S @SPARC_TRUE@am__append_7 = src/sparc/ffi.c src/sparc/v8.S src/sparc/v9.S @ALPHA_TRUE@am__append_8 = src/alpha/ffi.c src/alpha/osf.S @IA64_TRUE@am__append_9 = src/ia64/ffi.c src/ia64/unix.S @M32R_TRUE@am__append_10 = src/m32r/sysv.S src/m32r/ffi.c @M68K_TRUE@am__append_11 = src/m68k/ffi.c src/m68k/sysv.S @POWERPC_TRUE@am__append_12 = src/powerpc/ffi.c src/powerpc/sysv.S src/powerpc/ppc_closure.S src/powerpc/linux64.S src/powerpc/linux64_closure.S @POWERPC_AIX_TRUE@am__append_13 = src/powerpc/ffi_darwin.c src/powerpc/aix.S src/powerpc/aix_closure.S @POWERPC_DARWIN_TRUE@am__append_14 = src/powerpc/ffi_darwin.c src/powerpc/darwin.S src/powerpc/darwin_closure.S @POWERPC_FREEBSD_TRUE@am__append_15 = src/powerpc/ffi.c src/powerpc/sysv.S src/powerpc/ppc_closure.S @ARM_TRUE@am__append_16 = src/arm/sysv.S src/arm/ffi.c @AVR32_TRUE@am__append_17 = src/avr32/sysv.S src/avr32/ffi.c @LIBFFI_CRIS_TRUE@am__append_18 = src/cris/sysv.S src/cris/ffi.c @FRV_TRUE@am__append_19 = src/frv/eabi.S src/frv/ffi.c @S390_TRUE@am__append_20 = src/s390/sysv.S src/s390/ffi.c @X86_64_TRUE@am__append_21 = src/x86/ffi64.c src/x86/unix64.S src/x86/ffi.c src/x86/sysv.S @SH_TRUE@am__append_22 = src/sh/sysv.S src/sh/ffi.c @SH64_TRUE@am__append_23 = src/sh64/sysv.S src/sh64/ffi.c @PA_LINUX_TRUE@am__append_24 = src/pa/linux.S src/pa/ffi.c @PA_HPUX_TRUE@am__append_25 = src/pa/hpux32.S src/pa/ffi.c subdir = . DIST_COMMON = README $(am__configure_deps) \ $(srcdir)/../build-aux/compile \ $(srcdir)/../build-aux/config.guess \ $(srcdir)/../build-aux/config.sub \ $(srcdir)/../build-aux/depcomp \ $(srcdir)/../build-aux/install-sh \ $(srcdir)/../build-aux/ltmain.sh \ $(srcdir)/../build-aux/missing $(srcdir)/Makefile.am \ $(srcdir)/Makefile.in $(srcdir)/fficonfig.h.in \ $(top_srcdir)/configure ../build-aux/compile \ ../build-aux/config.guess ../build-aux/config.rpath \ ../build-aux/config.sub ../build-aux/depcomp \ ../build-aux/elisp-comp ../build-aux/install-sh \ ../build-aux/ltmain.sh ../build-aux/mdate-sh \ ../build-aux/missing ../build-aux/texinfo.tex \ ../build-aux/ylwrap ChangeLog TODO ACLOCAL_M4 = $(top_srcdir)/aclocal.m4 am__aclocal_m4_deps = $(top_srcdir)/../build-aux/libtool.m4 \ $(top_srcdir)/../build-aux/ltoptions.m4 \ $(top_srcdir)/../build-aux/ltsugar.m4 \ $(top_srcdir)/../build-aux/ltversion.m4 \ $(top_srcdir)/../build-aux/lt~obsolete.m4 \ $(top_srcdir)/configure.ac am__configure_deps = $(am__aclocal_m4_deps) $(CONFIGURE_DEPENDENCIES) \ $(ACLOCAL_M4) am__CONFIG_DISTCLEAN_FILES = config.status config.cache config.log \ configure.lineno config.status.lineno mkinstalldirs = $(install_sh) -d CONFIG_HEADER = fficonfig.h CONFIG_CLEAN_FILES = CONFIG_CLEAN_VPATH_FILES = LTLIBRARIES = $(noinst_LTLIBRARIES) libffi_la_LIBADD = am__dirstamp = $(am__leading_dot)dirstamp am_libffi_la_OBJECTS = src/debug.lo src/prep_cif.lo src/types.lo \ src/raw_api.lo src/java_raw_api.lo src/closures.lo @MIPS_TRUE@am__objects_1 = src/mips/ffi.lo src/mips/o32.lo \ @MIPS_TRUE@ src/mips/n32.lo @X86_TRUE@am__objects_2 = src/x86/ffi.lo src/x86/sysv.lo @X86_FREEBSD_TRUE@am__objects_3 = src/x86/ffi.lo src/x86/freebsd.lo @X86_WIN32_TRUE@am__objects_4 = src/x86/ffi.lo src/x86/win32.lo @X86_WIN64_TRUE@am__objects_5 = src/x86/ffi.lo src/x86/win64.lo @X86_DARWIN_TRUE@am__objects_6 = src/x86/ffi.lo src/x86/darwin.lo \ @X86_DARWIN_TRUE@ src/x86/ffi64.lo src/x86/darwin64.lo @SPARC_TRUE@am__objects_7 = src/sparc/ffi.lo src/sparc/v8.lo \ @SPARC_TRUE@ src/sparc/v9.lo @ALPHA_TRUE@am__objects_8 = src/alpha/ffi.lo src/alpha/osf.lo @IA64_TRUE@am__objects_9 = src/ia64/ffi.lo src/ia64/unix.lo @M32R_TRUE@am__objects_10 = src/m32r/sysv.lo src/m32r/ffi.lo @M68K_TRUE@am__objects_11 = src/m68k/ffi.lo src/m68k/sysv.lo @POWERPC_TRUE@am__objects_12 = src/powerpc/ffi.lo src/powerpc/sysv.lo \ @POWERPC_TRUE@ src/powerpc/ppc_closure.lo \ @POWERPC_TRUE@ src/powerpc/linux64.lo \ @POWERPC_TRUE@ src/powerpc/linux64_closure.lo @POWERPC_AIX_TRUE@am__objects_13 = src/powerpc/ffi_darwin.lo \ @POWERPC_AIX_TRUE@ src/powerpc/aix.lo \ @POWERPC_AIX_TRUE@ src/powerpc/aix_closure.lo @POWERPC_DARWIN_TRUE@am__objects_14 = src/powerpc/ffi_darwin.lo \ @POWERPC_DARWIN_TRUE@ src/powerpc/darwin.lo \ @POWERPC_DARWIN_TRUE@ src/powerpc/darwin_closure.lo @POWERPC_FREEBSD_TRUE@am__objects_15 = src/powerpc/ffi.lo \ @POWERPC_FREEBSD_TRUE@ src/powerpc/sysv.lo \ @POWERPC_FREEBSD_TRUE@ src/powerpc/ppc_closure.lo @ARM_TRUE@am__objects_16 = src/arm/sysv.lo src/arm/ffi.lo @AVR32_TRUE@am__objects_17 = src/avr32/sysv.lo src/avr32/ffi.lo @LIBFFI_CRIS_TRUE@am__objects_18 = src/cris/sysv.lo src/cris/ffi.lo @FRV_TRUE@am__objects_19 = src/frv/eabi.lo src/frv/ffi.lo @S390_TRUE@am__objects_20 = src/s390/sysv.lo src/s390/ffi.lo @X86_64_TRUE@am__objects_21 = src/x86/ffi64.lo src/x86/unix64.lo \ @X86_64_TRUE@ src/x86/ffi.lo src/x86/sysv.lo @SH_TRUE@am__objects_22 = src/sh/sysv.lo src/sh/ffi.lo @SH64_TRUE@am__objects_23 = src/sh64/sysv.lo src/sh64/ffi.lo @PA_LINUX_TRUE@am__objects_24 = src/pa/linux.lo src/pa/ffi.lo @PA_HPUX_TRUE@am__objects_25 = src/pa/hpux32.lo src/pa/ffi.lo nodist_libffi_la_OBJECTS = $(am__objects_1) $(am__objects_2) \ $(am__objects_3) $(am__objects_4) $(am__objects_5) \ $(am__objects_6) $(am__objects_7) $(am__objects_8) \ $(am__objects_9) $(am__objects_10) $(am__objects_11) \ $(am__objects_12) $(am__objects_13) $(am__objects_14) \ $(am__objects_15) $(am__objects_16) $(am__objects_17) \ $(am__objects_18) $(am__objects_19) $(am__objects_20) \ $(am__objects_21) $(am__objects_22) $(am__objects_23) \ $(am__objects_24) $(am__objects_25) libffi_la_OBJECTS = $(am_libffi_la_OBJECTS) \ $(nodist_libffi_la_OBJECTS) DEFAULT_INCLUDES = -I.@am__isrc@ depcomp = $(SHELL) $(top_srcdir)/../build-aux/depcomp am__depfiles_maybe = depfiles am__mv = mv -f CPPASCOMPILE = $(CCAS) $(DEFS) $(DEFAULT_INCLUDES) $(INCLUDES) \ $(AM_CPPFLAGS) $(CPPFLAGS) $(AM_CCASFLAGS) $(CCASFLAGS) LTCPPASCOMPILE = $(LIBTOOL) $(AM_LIBTOOLFLAGS) $(LIBTOOLFLAGS) \ --mode=compile $(CCAS) $(DEFS) $(DEFAULT_INCLUDES) $(INCLUDES) \ $(AM_CPPFLAGS) $(CPPFLAGS) $(AM_CCASFLAGS) $(CCASFLAGS) COMPILE = $(CC) $(DEFS) $(DEFAULT_INCLUDES) $(INCLUDES) $(AM_CPPFLAGS) \ $(CPPFLAGS) $(AM_CFLAGS) $(CFLAGS) LTCOMPILE = $(LIBTOOL) --tag=CC $(AM_LIBTOOLFLAGS) $(LIBTOOLFLAGS) \ --mode=compile $(CC) $(DEFS) $(DEFAULT_INCLUDES) $(INCLUDES) \ $(AM_CPPFLAGS) $(CPPFLAGS) $(AM_CFLAGS) $(CFLAGS) CCLD = $(CC) LINK = $(LIBTOOL) --tag=CC $(AM_LIBTOOLFLAGS) $(LIBTOOLFLAGS) \ --mode=link $(CCLD) $(AM_CFLAGS) $(CFLAGS) $(AM_LDFLAGS) \ $(LDFLAGS) -o $@ SOURCES = $(libffi_la_SOURCES) $(nodist_libffi_la_SOURCES) DIST_SOURCES = $(libffi_la_SOURCES) RECURSIVE_TARGETS = all-recursive check-recursive dvi-recursive \ html-recursive info-recursive install-data-recursive \ install-dvi-recursive install-exec-recursive \ install-html-recursive install-info-recursive \ install-pdf-recursive install-ps-recursive install-recursive \ installcheck-recursive installdirs-recursive pdf-recursive \ ps-recursive uninstall-recursive am__can_run_installinfo = \ case $$AM_UPDATE_INFO_DIR in \ n|no|NO) false;; \ *) (install-info --version) >/dev/null 2>&1;; \ esac RECURSIVE_CLEAN_TARGETS = mostlyclean-recursive clean-recursive \ distclean-recursive maintainer-clean-recursive AM_RECURSIVE_TARGETS = $(RECURSIVE_TARGETS:-recursive=) \ $(RECURSIVE_CLEAN_TARGETS:-recursive=) tags TAGS ctags CTAGS \ distdir dist dist-all distcheck ETAGS = etags CTAGS = ctags DIST_SUBDIRS = $(SUBDIRS) DISTFILES = $(DIST_COMMON) $(DIST_SOURCES) $(TEXINFOS) $(EXTRA_DIST) distdir = $(PACKAGE)-$(VERSION) top_distdir = $(distdir) am__remove_distdir = \ if test -d "$(distdir)"; then \ find "$(distdir)" -type d ! -perm -200 -exec chmod u+w {} ';' \ && rm -rf "$(distdir)" \ || { sleep 5 && rm -rf "$(distdir)"; }; \ else :; fi am__relativize = \ dir0=`pwd`; \ sed_first='s,^\([^/]*\)/.*$$,\1,'; \ sed_rest='s,^[^/]*/*,,'; \ sed_last='s,^.*/\([^/]*\)$$,\1,'; \ sed_butlast='s,/*[^/]*$$,,'; \ while test -n "$$dir1"; do \ first=`echo "$$dir1" | sed -e "$$sed_first"`; \ if test "$$first" != "."; then \ if test "$$first" = ".."; then \ dir2=`echo "$$dir0" | sed -e "$$sed_last"`/"$$dir2"; \ dir0=`echo "$$dir0" | sed -e "$$sed_butlast"`; \ else \ first2=`echo "$$dir2" | sed -e "$$sed_first"`; \ if test "$$first2" = "$$first"; then \ dir2=`echo "$$dir2" | sed -e "$$sed_rest"`; \ else \ dir2="../$$dir2"; \ fi; \ dir0="$$dir0"/"$$first"; \ fi; \ fi; \ dir1=`echo "$$dir1" | sed -e "$$sed_rest"`; \ done; \ reldir="$$dir2" DIST_ARCHIVES = $(distdir).tar.gz GZIP_ENV = --best distuninstallcheck_listfiles = find . -type f -print am__distuninstallcheck_listfiles = $(distuninstallcheck_listfiles) \ | sed 's|^\./|$(prefix)/|' | grep -v '$(infodir)/dir$$' distcleancheck_listfiles = find . -type f -print ACLOCAL = @ACLOCAL@ ALLOCA = @ALLOCA@ AMTAR = @AMTAR@ AM_LTLDFLAGS = @AM_LTLDFLAGS@ AM_RUNTESTFLAGS = @AM_RUNTESTFLAGS@ AR = @AR@ AUTOCONF = @AUTOCONF@ AUTOHEADER = @AUTOHEADER@ AUTOMAKE = @AUTOMAKE@ AWK = @AWK@ CC = @CC@ CCAS = @CCAS@ CCASDEPMODE = @CCASDEPMODE@ CCASFLAGS = @CCASFLAGS@ CCDEPMODE = @CCDEPMODE@ CFLAGS = @CFLAGS@ CPP = @CPP@ CPPFLAGS = @CPPFLAGS@ CYGPATH_W = @CYGPATH_W@ DEFS = @DEFS@ DEPDIR = @DEPDIR@ DLLTOOL = @DLLTOOL@ DSYMUTIL = @DSYMUTIL@ DUMPBIN = @DUMPBIN@ ECHO_C = @ECHO_C@ ECHO_N = @ECHO_N@ ECHO_T = @ECHO_T@ EGREP = @EGREP@ EXEEXT = @EXEEXT@ FGREP = @FGREP@ GREP = @GREP@ HAVE_LONG_DOUBLE = @HAVE_LONG_DOUBLE@ INSTALL = @INSTALL@ INSTALL_DATA = @INSTALL_DATA@ INSTALL_PROGRAM = @INSTALL_PROGRAM@ INSTALL_SCRIPT = @INSTALL_SCRIPT@ INSTALL_STRIP_PROGRAM = @INSTALL_STRIP_PROGRAM@ LD = @LD@ LDFLAGS = @LDFLAGS@ LIBOBJS = @LIBOBJS@ LIBS = @LIBS@ LIBTOOL = @LIBTOOL@ LIPO = @LIPO@ LN_S = @LN_S@ LTLIBOBJS = @LTLIBOBJS@ MAKEINFO = @MAKEINFO@ MANIFEST_TOOL = @MANIFEST_TOOL@ MKDIR_P = @MKDIR_P@ NM = @NM@ NMEDIT = @NMEDIT@ OBJDUMP = @OBJDUMP@ OBJEXT = @OBJEXT@ OTOOL = @OTOOL@ OTOOL64 = @OTOOL64@ PACKAGE = @PACKAGE@ PACKAGE_BUGREPORT = @PACKAGE_BUGREPORT@ PACKAGE_NAME = @PACKAGE_NAME@ PACKAGE_STRING = @PACKAGE_STRING@ PACKAGE_TARNAME = @PACKAGE_TARNAME@ PACKAGE_URL = @PACKAGE_URL@ PACKAGE_VERSION = @PACKAGE_VERSION@ PATH_SEPARATOR = @PATH_SEPARATOR@ RANLIB = @RANLIB@ SED = @SED@ SET_MAKE = @SET_MAKE@ SHELL = @SHELL@ STRIP = @STRIP@ TARGET = @TARGET@ TARGETDIR = @TARGETDIR@ VERSION = @VERSION@ abs_builddir = @abs_builddir@ abs_srcdir = @abs_srcdir@ abs_top_builddir = @abs_top_builddir@ abs_top_srcdir = @abs_top_srcdir@ ac_ct_AR = @ac_ct_AR@ ac_ct_CC = @ac_ct_CC@ ac_ct_DUMPBIN = @ac_ct_DUMPBIN@ am__include = @am__include@ am__leading_dot = @am__leading_dot@ am__quote = @am__quote@ am__tar = @am__tar@ am__untar = @am__untar@ bindir = @bindir@ build = @build@ build_alias = @build_alias@ build_cpu = @build_cpu@ build_os = @build_os@ build_vendor = @build_vendor@ builddir = @builddir@ datadir = @datadir@ datarootdir = @datarootdir@ docdir = @docdir@ dvidir = @dvidir@ exec_prefix = @exec_prefix@ host = @host@ host_alias = @host_alias@ host_cpu = @host_cpu@ host_os = @host_os@ host_vendor = @host_vendor@ htmldir = @htmldir@ includedir = @includedir@ infodir = @infodir@ install_sh = @install_sh@ libdir = @libdir@ libexecdir = @libexecdir@ localedir = @localedir@ localstatedir = @localstatedir@ mandir = @mandir@ mkdir_p = @mkdir_p@ oldincludedir = @oldincludedir@ pdfdir = @pdfdir@ prefix = @prefix@ program_transform_name = @program_transform_name@ psdir = @psdir@ sbindir = @sbindir@ sharedstatedir = @sharedstatedir@ srcdir = @srcdir@ sysconfdir = @sysconfdir@ target = @target@ target_alias = @target_alias@ target_cpu = @target_cpu@ target_os = @target_os@ target_vendor = @target_vendor@ top_build_prefix = @top_build_prefix@ top_builddir = @top_builddir@ top_srcdir = @top_srcdir@ AUTOMAKE_OPTIONS = foreign subdir-objects ACLOCAL_AMFLAGS = -I ../build-aux SUBDIRS = include EXTRA_DIST = LICENSE ChangeLog.v1 ChangeLog.libgcj configure.host \ src/alpha/ffi.c src/alpha/osf.S src/alpha/ffitarget.h \ src/arm/ffi.c src/arm/sysv.S src/arm/ffitarget.h \ src/avr32/ffi.c src/avr32/sysv.S src/avr32/ffitarget.h \ src/cris/ffi.c src/cris/sysv.S src/cris/ffitarget.h \ src/ia64/ffi.c src/ia64/ffitarget.h src/ia64/ia64_flags.h \ src/ia64/unix.S \ src/mips/ffi.c src/mips/n32.S src/mips/o32.S \ src/mips/ffitarget.h \ src/m32r/ffi.c src/m32r/sysv.S src/m32r/ffitarget.h \ src/m68k/ffi.c src/m68k/sysv.S src/m68k/ffitarget.h \ src/powerpc/ffi.c src/powerpc/sysv.S \ src/powerpc/linux64.S src/powerpc/linux64_closure.S \ src/powerpc/ppc_closure.S src/powerpc/asm.h \ src/powerpc/aix.S src/powerpc/darwin.S \ src/powerpc/aix_closure.S src/powerpc/darwin_closure.S \ src/powerpc/ffi_darwin.c src/powerpc/ffitarget.h \ src/s390/ffi.c src/s390/sysv.S src/s390/ffitarget.h \ src/sh/ffi.c src/sh/sysv.S src/sh/ffitarget.h \ src/sh64/ffi.c src/sh64/sysv.S src/sh64/ffitarget.h \ src/sparc/v8.S src/sparc/v9.S src/sparc/ffitarget.h \ src/sparc/ffi.c src/x86/darwin64.S \ src/x86/ffi.c src/x86/sysv.S src/x86/win32.S src/x86/darwin.S \ src/x86/ffi64.c src/x86/unix64.S src/x86/ffitarget.h \ src/pa/ffitarget.h src/pa/ffi.c src/pa/linux.S src/pa/hpux32.S \ src/frv/ffi.c src/frv/eabi.S src/frv/ffitarget.h src/dlmalloc.c noinst_LTLIBRARIES = libffi.la libffi_la_SOURCES = src/debug.c src/prep_cif.c src/types.c \ src/raw_api.c src/java_raw_api.c src/closures.c nodist_libffi_la_SOURCES = $(am__append_1) $(am__append_2) \ $(am__append_3) $(am__append_4) $(am__append_5) \ $(am__append_6) $(am__append_7) $(am__append_8) \ $(am__append_9) $(am__append_10) $(am__append_11) \ $(am__append_12) $(am__append_13) $(am__append_14) \ $(am__append_15) $(am__append_16) $(am__append_17) \ $(am__append_18) $(am__append_19) $(am__append_20) \ $(am__append_21) $(am__append_22) $(am__append_23) \ $(am__append_24) $(am__append_25) AM_CFLAGS = -Wall -g -fexceptions AM_CPPFLAGS = -I. -I$(top_srcdir)/include -Iinclude -I$(top_srcdir)/src AM_CCASFLAGS = $(AM_CPPFLAGS) all: fficonfig.h $(MAKE) $(AM_MAKEFLAGS) all-recursive .SUFFIXES: .SUFFIXES: .S .c .lo .o .obj am--refresh: Makefile @: $(srcdir)/Makefile.in: $(srcdir)/Makefile.am $(am__configure_deps) @for dep in $?; do \ case '$(am__configure_deps)' in \ *$$dep*) \ echo ' cd $(srcdir) && $(AUTOMAKE) --foreign'; \ $(am__cd) $(srcdir) && $(AUTOMAKE) --foreign \ && exit 0; \ exit 1;; \ esac; \ done; \ echo ' cd $(top_srcdir) && $(AUTOMAKE) --foreign Makefile'; \ $(am__cd) $(top_srcdir) && \ $(AUTOMAKE) --foreign Makefile .PRECIOUS: Makefile Makefile: $(srcdir)/Makefile.in $(top_builddir)/config.status @case '$?' in \ *config.status*) \ echo ' $(SHELL) ./config.status'; \ $(SHELL) ./config.status;; \ *) \ echo ' cd $(top_builddir) && $(SHELL) ./config.status $@ $(am__depfiles_maybe)'; \ cd $(top_builddir) && $(SHELL) ./config.status $@ $(am__depfiles_maybe);; \ esac; $(top_builddir)/config.status: $(top_srcdir)/configure $(CONFIG_STATUS_DEPENDENCIES) $(SHELL) ./config.status --recheck $(top_srcdir)/configure: $(am__configure_deps) $(am__cd) $(srcdir) && $(AUTOCONF) $(ACLOCAL_M4): $(am__aclocal_m4_deps) $(am__cd) $(srcdir) && $(ACLOCAL) $(ACLOCAL_AMFLAGS) $(am__aclocal_m4_deps): fficonfig.h: stamp-h1 @if test ! -f $@; then rm -f stamp-h1; else :; fi @if test ! -f $@; then $(MAKE) $(AM_MAKEFLAGS) stamp-h1; else :; fi stamp-h1: $(srcdir)/fficonfig.h.in $(top_builddir)/config.status @rm -f stamp-h1 cd $(top_builddir) && $(SHELL) ./config.status fficonfig.h $(srcdir)/fficonfig.h.in: $(am__configure_deps) ($(am__cd) $(top_srcdir) && $(AUTOHEADER)) rm -f stamp-h1 touch $@ distclean-hdr: -rm -f fficonfig.h stamp-h1 clean-noinstLTLIBRARIES: -test -z "$(noinst_LTLIBRARIES)" || rm -f $(noinst_LTLIBRARIES) @list='$(noinst_LTLIBRARIES)'; for p in $$list; do \ dir="`echo $$p | sed -e 's|/[^/]*$$||'`"; \ test "$$dir" != "$$p" || dir=.; \ echo "rm -f \"$${dir}/so_locations\""; \ rm -f "$${dir}/so_locations"; \ done src/$(am__dirstamp): @$(MKDIR_P) src @: > src/$(am__dirstamp) src/$(DEPDIR)/$(am__dirstamp): @$(MKDIR_P) src/$(DEPDIR) @: > src/$(DEPDIR)/$(am__dirstamp) src/debug.lo: src/$(am__dirstamp) src/$(DEPDIR)/$(am__dirstamp) src/prep_cif.lo: src/$(am__dirstamp) src/$(DEPDIR)/$(am__dirstamp) src/types.lo: src/$(am__dirstamp) src/$(DEPDIR)/$(am__dirstamp) src/raw_api.lo: src/$(am__dirstamp) src/$(DEPDIR)/$(am__dirstamp) src/java_raw_api.lo: src/$(am__dirstamp) src/$(DEPDIR)/$(am__dirstamp) src/closures.lo: src/$(am__dirstamp) src/$(DEPDIR)/$(am__dirstamp) src/mips/$(am__dirstamp): @$(MKDIR_P) src/mips @: > src/mips/$(am__dirstamp) src/mips/$(DEPDIR)/$(am__dirstamp): @$(MKDIR_P) src/mips/$(DEPDIR) @: > src/mips/$(DEPDIR)/$(am__dirstamp) src/mips/ffi.lo: src/mips/$(am__dirstamp) \ src/mips/$(DEPDIR)/$(am__dirstamp) src/mips/o32.lo: src/mips/$(am__dirstamp) \ src/mips/$(DEPDIR)/$(am__dirstamp) src/mips/n32.lo: src/mips/$(am__dirstamp) \ src/mips/$(DEPDIR)/$(am__dirstamp) src/x86/$(am__dirstamp): @$(MKDIR_P) src/x86 @: > src/x86/$(am__dirstamp) src/x86/$(DEPDIR)/$(am__dirstamp): @$(MKDIR_P) src/x86/$(DEPDIR) @: > src/x86/$(DEPDIR)/$(am__dirstamp) src/x86/ffi.lo: src/x86/$(am__dirstamp) \ src/x86/$(DEPDIR)/$(am__dirstamp) src/x86/sysv.lo: src/x86/$(am__dirstamp) \ src/x86/$(DEPDIR)/$(am__dirstamp) src/x86/freebsd.lo: src/x86/$(am__dirstamp) \ src/x86/$(DEPDIR)/$(am__dirstamp) src/x86/win32.lo: src/x86/$(am__dirstamp) \ src/x86/$(DEPDIR)/$(am__dirstamp) src/x86/win64.lo: src/x86/$(am__dirstamp) \ src/x86/$(DEPDIR)/$(am__dirstamp) src/x86/darwin.lo: src/x86/$(am__dirstamp) \ src/x86/$(DEPDIR)/$(am__dirstamp) src/x86/ffi64.lo: src/x86/$(am__dirstamp) \ src/x86/$(DEPDIR)/$(am__dirstamp) src/x86/darwin64.lo: src/x86/$(am__dirstamp) \ src/x86/$(DEPDIR)/$(am__dirstamp) src/sparc/$(am__dirstamp): @$(MKDIR_P) src/sparc @: > src/sparc/$(am__dirstamp) src/sparc/$(DEPDIR)/$(am__dirstamp): @$(MKDIR_P) src/sparc/$(DEPDIR) @: > src/sparc/$(DEPDIR)/$(am__dirstamp) src/sparc/ffi.lo: src/sparc/$(am__dirstamp) \ src/sparc/$(DEPDIR)/$(am__dirstamp) src/sparc/v8.lo: src/sparc/$(am__dirstamp) \ src/sparc/$(DEPDIR)/$(am__dirstamp) src/sparc/v9.lo: src/sparc/$(am__dirstamp) \ src/sparc/$(DEPDIR)/$(am__dirstamp) src/alpha/$(am__dirstamp): @$(MKDIR_P) src/alpha @: > src/alpha/$(am__dirstamp) src/alpha/$(DEPDIR)/$(am__dirstamp): @$(MKDIR_P) src/alpha/$(DEPDIR) @: > src/alpha/$(DEPDIR)/$(am__dirstamp) src/alpha/ffi.lo: src/alpha/$(am__dirstamp) \ src/alpha/$(DEPDIR)/$(am__dirstamp) src/alpha/osf.lo: src/alpha/$(am__dirstamp) \ src/alpha/$(DEPDIR)/$(am__dirstamp) src/ia64/$(am__dirstamp): @$(MKDIR_P) src/ia64 @: > src/ia64/$(am__dirstamp) src/ia64/$(DEPDIR)/$(am__dirstamp): @$(MKDIR_P) src/ia64/$(DEPDIR) @: > src/ia64/$(DEPDIR)/$(am__dirstamp) src/ia64/ffi.lo: src/ia64/$(am__dirstamp) \ src/ia64/$(DEPDIR)/$(am__dirstamp) src/ia64/unix.lo: src/ia64/$(am__dirstamp) \ src/ia64/$(DEPDIR)/$(am__dirstamp) src/m32r/$(am__dirstamp): @$(MKDIR_P) src/m32r @: > src/m32r/$(am__dirstamp) src/m32r/$(DEPDIR)/$(am__dirstamp): @$(MKDIR_P) src/m32r/$(DEPDIR) @: > src/m32r/$(DEPDIR)/$(am__dirstamp) src/m32r/sysv.lo: src/m32r/$(am__dirstamp) \ src/m32r/$(DEPDIR)/$(am__dirstamp) src/m32r/ffi.lo: src/m32r/$(am__dirstamp) \ src/m32r/$(DEPDIR)/$(am__dirstamp) src/m68k/$(am__dirstamp): @$(MKDIR_P) src/m68k @: > src/m68k/$(am__dirstamp) src/m68k/$(DEPDIR)/$(am__dirstamp): @$(MKDIR_P) src/m68k/$(DEPDIR) @: > src/m68k/$(DEPDIR)/$(am__dirstamp) src/m68k/ffi.lo: src/m68k/$(am__dirstamp) \ src/m68k/$(DEPDIR)/$(am__dirstamp) src/m68k/sysv.lo: src/m68k/$(am__dirstamp) \ src/m68k/$(DEPDIR)/$(am__dirstamp) src/powerpc/$(am__dirstamp): @$(MKDIR_P) src/powerpc @: > src/powerpc/$(am__dirstamp) src/powerpc/$(DEPDIR)/$(am__dirstamp): @$(MKDIR_P) src/powerpc/$(DEPDIR) @: > src/powerpc/$(DEPDIR)/$(am__dirstamp) src/powerpc/ffi.lo: src/powerpc/$(am__dirstamp) \ src/powerpc/$(DEPDIR)/$(am__dirstamp) src/powerpc/sysv.lo: src/powerpc/$(am__dirstamp) \ src/powerpc/$(DEPDIR)/$(am__dirstamp) src/powerpc/ppc_closure.lo: src/powerpc/$(am__dirstamp) \ src/powerpc/$(DEPDIR)/$(am__dirstamp) src/powerpc/linux64.lo: src/powerpc/$(am__dirstamp) \ src/powerpc/$(DEPDIR)/$(am__dirstamp) src/powerpc/linux64_closure.lo: src/powerpc/$(am__dirstamp) \ src/powerpc/$(DEPDIR)/$(am__dirstamp) src/powerpc/ffi_darwin.lo: src/powerpc/$(am__dirstamp) \ src/powerpc/$(DEPDIR)/$(am__dirstamp) src/powerpc/aix.lo: src/powerpc/$(am__dirstamp) \ src/powerpc/$(DEPDIR)/$(am__dirstamp) src/powerpc/aix_closure.lo: src/powerpc/$(am__dirstamp) \ src/powerpc/$(DEPDIR)/$(am__dirstamp) src/powerpc/darwin.lo: src/powerpc/$(am__dirstamp) \ src/powerpc/$(DEPDIR)/$(am__dirstamp) src/powerpc/darwin_closure.lo: src/powerpc/$(am__dirstamp) \ src/powerpc/$(DEPDIR)/$(am__dirstamp) src/arm/$(am__dirstamp): @$(MKDIR_P) src/arm @: > src/arm/$(am__dirstamp) src/arm/$(DEPDIR)/$(am__dirstamp): @$(MKDIR_P) src/arm/$(DEPDIR) @: > src/arm/$(DEPDIR)/$(am__dirstamp) src/arm/sysv.lo: src/arm/$(am__dirstamp) \ src/arm/$(DEPDIR)/$(am__dirstamp) src/arm/ffi.lo: src/arm/$(am__dirstamp) \ src/arm/$(DEPDIR)/$(am__dirstamp) src/avr32/$(am__dirstamp): @$(MKDIR_P) src/avr32 @: > src/avr32/$(am__dirstamp) src/avr32/$(DEPDIR)/$(am__dirstamp): @$(MKDIR_P) src/avr32/$(DEPDIR) @: > src/avr32/$(DEPDIR)/$(am__dirstamp) src/avr32/sysv.lo: src/avr32/$(am__dirstamp) \ src/avr32/$(DEPDIR)/$(am__dirstamp) src/avr32/ffi.lo: src/avr32/$(am__dirstamp) \ src/avr32/$(DEPDIR)/$(am__dirstamp) src/cris/$(am__dirstamp): @$(MKDIR_P) src/cris @: > src/cris/$(am__dirstamp) src/cris/$(DEPDIR)/$(am__dirstamp): @$(MKDIR_P) src/cris/$(DEPDIR) @: > src/cris/$(DEPDIR)/$(am__dirstamp) src/cris/sysv.lo: src/cris/$(am__dirstamp) \ src/cris/$(DEPDIR)/$(am__dirstamp) src/cris/ffi.lo: src/cris/$(am__dirstamp) \ src/cris/$(DEPDIR)/$(am__dirstamp) src/frv/$(am__dirstamp): @$(MKDIR_P) src/frv @: > src/frv/$(am__dirstamp) src/frv/$(DEPDIR)/$(am__dirstamp): @$(MKDIR_P) src/frv/$(DEPDIR) @: > src/frv/$(DEPDIR)/$(am__dirstamp) src/frv/eabi.lo: src/frv/$(am__dirstamp) \ src/frv/$(DEPDIR)/$(am__dirstamp) src/frv/ffi.lo: src/frv/$(am__dirstamp) \ src/frv/$(DEPDIR)/$(am__dirstamp) src/s390/$(am__dirstamp): @$(MKDIR_P) src/s390 @: > src/s390/$(am__dirstamp) src/s390/$(DEPDIR)/$(am__dirstamp): @$(MKDIR_P) src/s390/$(DEPDIR) @: > src/s390/$(DEPDIR)/$(am__dirstamp) src/s390/sysv.lo: src/s390/$(am__dirstamp) \ src/s390/$(DEPDIR)/$(am__dirstamp) src/s390/ffi.lo: src/s390/$(am__dirstamp) \ src/s390/$(DEPDIR)/$(am__dirstamp) src/x86/unix64.lo: src/x86/$(am__dirstamp) \ src/x86/$(DEPDIR)/$(am__dirstamp) src/sh/$(am__dirstamp): @$(MKDIR_P) src/sh @: > src/sh/$(am__dirstamp) src/sh/$(DEPDIR)/$(am__dirstamp): @$(MKDIR_P) src/sh/$(DEPDIR) @: > src/sh/$(DEPDIR)/$(am__dirstamp) src/sh/sysv.lo: src/sh/$(am__dirstamp) \ src/sh/$(DEPDIR)/$(am__dirstamp) src/sh/ffi.lo: src/sh/$(am__dirstamp) src/sh/$(DEPDIR)/$(am__dirstamp) src/sh64/$(am__dirstamp): @$(MKDIR_P) src/sh64 @: > src/sh64/$(am__dirstamp) src/sh64/$(DEPDIR)/$(am__dirstamp): @$(MKDIR_P) src/sh64/$(DEPDIR) @: > src/sh64/$(DEPDIR)/$(am__dirstamp) src/sh64/sysv.lo: src/sh64/$(am__dirstamp) \ src/sh64/$(DEPDIR)/$(am__dirstamp) src/sh64/ffi.lo: src/sh64/$(am__dirstamp) \ src/sh64/$(DEPDIR)/$(am__dirstamp) src/pa/$(am__dirstamp): @$(MKDIR_P) src/pa @: > src/pa/$(am__dirstamp) src/pa/$(DEPDIR)/$(am__dirstamp): @$(MKDIR_P) src/pa/$(DEPDIR) @: > src/pa/$(DEPDIR)/$(am__dirstamp) src/pa/linux.lo: src/pa/$(am__dirstamp) \ src/pa/$(DEPDIR)/$(am__dirstamp) src/pa/ffi.lo: src/pa/$(am__dirstamp) src/pa/$(DEPDIR)/$(am__dirstamp) src/pa/hpux32.lo: src/pa/$(am__dirstamp) \ src/pa/$(DEPDIR)/$(am__dirstamp) libffi.la: $(libffi_la_OBJECTS) $(libffi_la_DEPENDENCIES) $(EXTRA_libffi_la_DEPENDENCIES) $(LINK) $(libffi_la_OBJECTS) $(libffi_la_LIBADD) $(LIBS) mostlyclean-compile: -rm -f *.$(OBJEXT) -rm -f src/alpha/ffi.$(OBJEXT) -rm -f src/alpha/ffi.lo -rm -f src/alpha/osf.$(OBJEXT) -rm -f src/alpha/osf.lo -rm -f src/arm/ffi.$(OBJEXT) -rm -f src/arm/ffi.lo -rm -f src/arm/sysv.$(OBJEXT) -rm -f src/arm/sysv.lo -rm -f src/avr32/ffi.$(OBJEXT) -rm -f src/avr32/ffi.lo -rm -f src/avr32/sysv.$(OBJEXT) -rm -f src/avr32/sysv.lo -rm -f src/closures.$(OBJEXT) -rm -f src/closures.lo -rm -f src/cris/ffi.$(OBJEXT) -rm -f src/cris/ffi.lo -rm -f src/cris/sysv.$(OBJEXT) -rm -f src/cris/sysv.lo -rm -f src/debug.$(OBJEXT) -rm -f src/debug.lo -rm -f src/frv/eabi.$(OBJEXT) -rm -f src/frv/eabi.lo -rm -f src/frv/ffi.$(OBJEXT) -rm -f src/frv/ffi.lo -rm -f src/ia64/ffi.$(OBJEXT) -rm -f src/ia64/ffi.lo -rm -f src/ia64/unix.$(OBJEXT) -rm -f src/ia64/unix.lo -rm -f src/java_raw_api.$(OBJEXT) -rm -f src/java_raw_api.lo -rm -f src/m32r/ffi.$(OBJEXT) -rm -f src/m32r/ffi.lo -rm -f src/m32r/sysv.$(OBJEXT) -rm -f src/m32r/sysv.lo -rm -f src/m68k/ffi.$(OBJEXT) -rm -f src/m68k/ffi.lo -rm -f src/m68k/sysv.$(OBJEXT) -rm -f src/m68k/sysv.lo -rm -f src/mips/ffi.$(OBJEXT) -rm -f src/mips/ffi.lo -rm -f src/mips/n32.$(OBJEXT) -rm -f src/mips/n32.lo -rm -f src/mips/o32.$(OBJEXT) -rm -f src/mips/o32.lo -rm -f src/pa/ffi.$(OBJEXT) -rm -f src/pa/ffi.lo -rm -f src/pa/hpux32.$(OBJEXT) -rm -f src/pa/hpux32.lo -rm -f src/pa/linux.$(OBJEXT) -rm -f src/pa/linux.lo -rm -f src/powerpc/aix.$(OBJEXT) -rm -f src/powerpc/aix.lo -rm -f src/powerpc/aix_closure.$(OBJEXT) -rm -f src/powerpc/aix_closure.lo -rm -f src/powerpc/darwin.$(OBJEXT) -rm -f src/powerpc/darwin.lo -rm -f src/powerpc/darwin_closure.$(OBJEXT) -rm -f src/powerpc/darwin_closure.lo -rm -f src/powerpc/ffi.$(OBJEXT) -rm -f src/powerpc/ffi.lo -rm -f src/powerpc/ffi_darwin.$(OBJEXT) -rm -f src/powerpc/ffi_darwin.lo -rm -f src/powerpc/linux64.$(OBJEXT) -rm -f src/powerpc/linux64.lo -rm -f src/powerpc/linux64_closure.$(OBJEXT) -rm -f src/powerpc/linux64_closure.lo -rm -f src/powerpc/ppc_closure.$(OBJEXT) -rm -f src/powerpc/ppc_closure.lo -rm -f src/powerpc/sysv.$(OBJEXT) -rm -f src/powerpc/sysv.lo -rm -f src/prep_cif.$(OBJEXT) -rm -f src/prep_cif.lo -rm -f src/raw_api.$(OBJEXT) -rm -f src/raw_api.lo -rm -f src/s390/ffi.$(OBJEXT) -rm -f src/s390/ffi.lo -rm -f src/s390/sysv.$(OBJEXT) -rm -f src/s390/sysv.lo -rm -f src/sh/ffi.$(OBJEXT) -rm -f src/sh/ffi.lo -rm -f src/sh/sysv.$(OBJEXT) -rm -f src/sh/sysv.lo -rm -f src/sh64/ffi.$(OBJEXT) -rm -f src/sh64/ffi.lo -rm -f src/sh64/sysv.$(OBJEXT) -rm -f src/sh64/sysv.lo -rm -f src/sparc/ffi.$(OBJEXT) -rm -f src/sparc/ffi.lo -rm -f src/sparc/v8.$(OBJEXT) -rm -f src/sparc/v8.lo -rm -f src/sparc/v9.$(OBJEXT) -rm -f src/sparc/v9.lo -rm -f src/types.$(OBJEXT) -rm -f src/types.lo -rm -f src/x86/darwin.$(OBJEXT) -rm -f src/x86/darwin.lo -rm -f src/x86/darwin64.$(OBJEXT) -rm -f src/x86/darwin64.lo -rm -f src/x86/ffi.$(OBJEXT) -rm -f src/x86/ffi.lo -rm -f src/x86/ffi64.$(OBJEXT) -rm -f src/x86/ffi64.lo -rm -f src/x86/freebsd.$(OBJEXT) -rm -f src/x86/freebsd.lo -rm -f src/x86/sysv.$(OBJEXT) -rm -f src/x86/sysv.lo -rm -f src/x86/unix64.$(OBJEXT) -rm -f src/x86/unix64.lo -rm -f src/x86/win32.$(OBJEXT) -rm -f src/x86/win32.lo -rm -f src/x86/win64.$(OBJEXT) -rm -f src/x86/win64.lo distclean-compile: -rm -f *.tab.c @AMDEP_TRUE@@am__include@ @am__quote@src/$(DEPDIR)/closures.Plo@am__quote@ @AMDEP_TRUE@@am__include@ @am__quote@src/$(DEPDIR)/debug.Plo@am__quote@ @AMDEP_TRUE@@am__include@ @am__quote@src/$(DEPDIR)/java_raw_api.Plo@am__quote@ @AMDEP_TRUE@@am__include@ @am__quote@src/$(DEPDIR)/prep_cif.Plo@am__quote@ @AMDEP_TRUE@@am__include@ @am__quote@src/$(DEPDIR)/raw_api.Plo@am__quote@ @AMDEP_TRUE@@am__include@ @am__quote@src/$(DEPDIR)/types.Plo@am__quote@ @AMDEP_TRUE@@am__include@ @am__quote@src/alpha/$(DEPDIR)/ffi.Plo@am__quote@ @AMDEP_TRUE@@am__include@ @am__quote@src/alpha/$(DEPDIR)/osf.Plo@am__quote@ @AMDEP_TRUE@@am__include@ @am__quote@src/arm/$(DEPDIR)/ffi.Plo@am__quote@ @AMDEP_TRUE@@am__include@ @am__quote@src/arm/$(DEPDIR)/sysv.Plo@am__quote@ @AMDEP_TRUE@@am__include@ @am__quote@src/avr32/$(DEPDIR)/ffi.Plo@am__quote@ @AMDEP_TRUE@@am__include@ @am__quote@src/avr32/$(DEPDIR)/sysv.Plo@am__quote@ @AMDEP_TRUE@@am__include@ @am__quote@src/cris/$(DEPDIR)/ffi.Plo@am__quote@ @AMDEP_TRUE@@am__include@ @am__quote@src/cris/$(DEPDIR)/sysv.Plo@am__quote@ @AMDEP_TRUE@@am__include@ @am__quote@src/frv/$(DEPDIR)/eabi.Plo@am__quote@ @AMDEP_TRUE@@am__include@ @am__quote@src/frv/$(DEPDIR)/ffi.Plo@am__quote@ @AMDEP_TRUE@@am__include@ @am__quote@src/ia64/$(DEPDIR)/ffi.Plo@am__quote@ @AMDEP_TRUE@@am__include@ @am__quote@src/ia64/$(DEPDIR)/unix.Plo@am__quote@ @AMDEP_TRUE@@am__include@ @am__quote@src/m32r/$(DEPDIR)/ffi.Plo@am__quote@ @AMDEP_TRUE@@am__include@ @am__quote@src/m32r/$(DEPDIR)/sysv.Plo@am__quote@ @AMDEP_TRUE@@am__include@ @am__quote@src/m68k/$(DEPDIR)/ffi.Plo@am__quote@ @AMDEP_TRUE@@am__include@ @am__quote@src/m68k/$(DEPDIR)/sysv.Plo@am__quote@ @AMDEP_TRUE@@am__include@ @am__quote@src/mips/$(DEPDIR)/ffi.Plo@am__quote@ @AMDEP_TRUE@@am__include@ @am__quote@src/mips/$(DEPDIR)/n32.Plo@am__quote@ @AMDEP_TRUE@@am__include@ @am__quote@src/mips/$(DEPDIR)/o32.Plo@am__quote@ @AMDEP_TRUE@@am__include@ @am__quote@src/pa/$(DEPDIR)/ffi.Plo@am__quote@ @AMDEP_TRUE@@am__include@ @am__quote@src/pa/$(DEPDIR)/hpux32.Plo@am__quote@ @AMDEP_TRUE@@am__include@ @am__quote@src/pa/$(DEPDIR)/linux.Plo@am__quote@ @AMDEP_TRUE@@am__include@ @am__quote@src/powerpc/$(DEPDIR)/aix.Plo@am__quote@ @AMDEP_TRUE@@am__include@ @am__quote@src/powerpc/$(DEPDIR)/aix_closure.Plo@am__quote@ @AMDEP_TRUE@@am__include@ @am__quote@src/powerpc/$(DEPDIR)/darwin.Plo@am__quote@ @AMDEP_TRUE@@am__include@ @am__quote@src/powerpc/$(DEPDIR)/darwin_closure.Plo@am__quote@ @AMDEP_TRUE@@am__include@ @am__quote@src/powerpc/$(DEPDIR)/ffi.Plo@am__quote@ @AMDEP_TRUE@@am__include@ @am__quote@src/powerpc/$(DEPDIR)/ffi_darwin.Plo@am__quote@ @AMDEP_TRUE@@am__include@ @am__quote@src/powerpc/$(DEPDIR)/linux64.Plo@am__quote@ @AMDEP_TRUE@@am__include@ @am__quote@src/powerpc/$(DEPDIR)/linux64_closure.Plo@am__quote@ @AMDEP_TRUE@@am__include@ @am__quote@src/powerpc/$(DEPDIR)/ppc_closure.Plo@am__quote@ @AMDEP_TRUE@@am__include@ @am__quote@src/powerpc/$(DEPDIR)/sysv.Plo@am__quote@ @AMDEP_TRUE@@am__include@ @am__quote@src/s390/$(DEPDIR)/ffi.Plo@am__quote@ @AMDEP_TRUE@@am__include@ @am__quote@src/s390/$(DEPDIR)/sysv.Plo@am__quote@ @AMDEP_TRUE@@am__include@ @am__quote@src/sh/$(DEPDIR)/ffi.Plo@am__quote@ @AMDEP_TRUE@@am__include@ @am__quote@src/sh/$(DEPDIR)/sysv.Plo@am__quote@ @AMDEP_TRUE@@am__include@ @am__quote@src/sh64/$(DEPDIR)/ffi.Plo@am__quote@ @AMDEP_TRUE@@am__include@ @am__quote@src/sh64/$(DEPDIR)/sysv.Plo@am__quote@ @AMDEP_TRUE@@am__include@ @am__quote@src/sparc/$(DEPDIR)/ffi.Plo@am__quote@ @AMDEP_TRUE@@am__include@ @am__quote@src/sparc/$(DEPDIR)/v8.Plo@am__quote@ @AMDEP_TRUE@@am__include@ @am__quote@src/sparc/$(DEPDIR)/v9.Plo@am__quote@ @AMDEP_TRUE@@am__include@ @am__quote@src/x86/$(DEPDIR)/darwin.Plo@am__quote@ @AMDEP_TRUE@@am__include@ @am__quote@src/x86/$(DEPDIR)/darwin64.Plo@am__quote@ @AMDEP_TRUE@@am__include@ @am__quote@src/x86/$(DEPDIR)/ffi.Plo@am__quote@ @AMDEP_TRUE@@am__include@ @am__quote@src/x86/$(DEPDIR)/ffi64.Plo@am__quote@ @AMDEP_TRUE@@am__include@ @am__quote@src/x86/$(DEPDIR)/freebsd.Plo@am__quote@ @AMDEP_TRUE@@am__include@ @am__quote@src/x86/$(DEPDIR)/sysv.Plo@am__quote@ @AMDEP_TRUE@@am__include@ @am__quote@src/x86/$(DEPDIR)/unix64.Plo@am__quote@ @AMDEP_TRUE@@am__include@ @am__quote@src/x86/$(DEPDIR)/win32.Plo@am__quote@ @AMDEP_TRUE@@am__include@ @am__quote@src/x86/$(DEPDIR)/win64.Plo@am__quote@ .S.o: @am__fastdepCCAS_TRUE@ depbase=`echo $@ | sed 's|[^/]*$$|$(DEPDIR)/&|;s|\.o$$||'`;\ @am__fastdepCCAS_TRUE@ $(CPPASCOMPILE) -MT $@ -MD -MP -MF $$depbase.Tpo -c -o $@ $< &&\ @am__fastdepCCAS_TRUE@ $(am__mv) $$depbase.Tpo $$depbase.Po @AMDEP_TRUE@@am__fastdepCCAS_FALSE@ source='$<' object='$@' libtool=no @AMDEPBACKSLASH@ @AMDEP_TRUE@@am__fastdepCCAS_FALSE@ DEPDIR=$(DEPDIR) $(CCASDEPMODE) $(depcomp) @AMDEPBACKSLASH@ @am__fastdepCCAS_FALSE@ $(CPPASCOMPILE) -c -o $@ $< .S.obj: @am__fastdepCCAS_TRUE@ depbase=`echo $@ | sed 's|[^/]*$$|$(DEPDIR)/&|;s|\.obj$$||'`;\ @am__fastdepCCAS_TRUE@ $(CPPASCOMPILE) -MT $@ -MD -MP -MF $$depbase.Tpo -c -o $@ `$(CYGPATH_W) '$<'` &&\ @am__fastdepCCAS_TRUE@ $(am__mv) $$depbase.Tpo $$depbase.Po @AMDEP_TRUE@@am__fastdepCCAS_FALSE@ source='$<' object='$@' libtool=no @AMDEPBACKSLASH@ @AMDEP_TRUE@@am__fastdepCCAS_FALSE@ DEPDIR=$(DEPDIR) $(CCASDEPMODE) $(depcomp) @AMDEPBACKSLASH@ @am__fastdepCCAS_FALSE@ $(CPPASCOMPILE) -c -o $@ `$(CYGPATH_W) '$<'` .S.lo: @am__fastdepCCAS_TRUE@ depbase=`echo $@ | sed 's|[^/]*$$|$(DEPDIR)/&|;s|\.lo$$||'`;\ @am__fastdepCCAS_TRUE@ $(LTCPPASCOMPILE) -MT $@ -MD -MP -MF $$depbase.Tpo -c -o $@ $< &&\ @am__fastdepCCAS_TRUE@ $(am__mv) $$depbase.Tpo $$depbase.Plo @AMDEP_TRUE@@am__fastdepCCAS_FALSE@ source='$<' object='$@' libtool=yes @AMDEPBACKSLASH@ @AMDEP_TRUE@@am__fastdepCCAS_FALSE@ DEPDIR=$(DEPDIR) $(CCASDEPMODE) $(depcomp) @AMDEPBACKSLASH@ @am__fastdepCCAS_FALSE@ $(LTCPPASCOMPILE) -c -o $@ $< .c.o: @am__fastdepCC_TRUE@ depbase=`echo $@ | sed 's|[^/]*$$|$(DEPDIR)/&|;s|\.o$$||'`;\ @am__fastdepCC_TRUE@ $(COMPILE) -MT $@ -MD -MP -MF $$depbase.Tpo -c -o $@ $< &&\ @am__fastdepCC_TRUE@ $(am__mv) $$depbase.Tpo $$depbase.Po @AMDEP_TRUE@@am__fastdepCC_FALSE@ source='$<' object='$@' libtool=no @AMDEPBACKSLASH@ @AMDEP_TRUE@@am__fastdepCC_FALSE@ DEPDIR=$(DEPDIR) $(CCDEPMODE) $(depcomp) @AMDEPBACKSLASH@ @am__fastdepCC_FALSE@ $(COMPILE) -c -o $@ $< .c.obj: @am__fastdepCC_TRUE@ depbase=`echo $@ | sed 's|[^/]*$$|$(DEPDIR)/&|;s|\.obj$$||'`;\ @am__fastdepCC_TRUE@ $(COMPILE) -MT $@ -MD -MP -MF $$depbase.Tpo -c -o $@ `$(CYGPATH_W) '$<'` &&\ @am__fastdepCC_TRUE@ $(am__mv) $$depbase.Tpo $$depbase.Po @AMDEP_TRUE@@am__fastdepCC_FALSE@ source='$<' object='$@' libtool=no @AMDEPBACKSLASH@ @AMDEP_TRUE@@am__fastdepCC_FALSE@ DEPDIR=$(DEPDIR) $(CCDEPMODE) $(depcomp) @AMDEPBACKSLASH@ @am__fastdepCC_FALSE@ $(COMPILE) -c -o $@ `$(CYGPATH_W) '$<'` .c.lo: @am__fastdepCC_TRUE@ depbase=`echo $@ | sed 's|[^/]*$$|$(DEPDIR)/&|;s|\.lo$$||'`;\ @am__fastdepCC_TRUE@ $(LTCOMPILE) -MT $@ -MD -MP -MF $$depbase.Tpo -c -o $@ $< &&\ @am__fastdepCC_TRUE@ $(am__mv) $$depbase.Tpo $$depbase.Plo @AMDEP_TRUE@@am__fastdepCC_FALSE@ source='$<' object='$@' libtool=yes @AMDEPBACKSLASH@ @AMDEP_TRUE@@am__fastdepCC_FALSE@ DEPDIR=$(DEPDIR) $(CCDEPMODE) $(depcomp) @AMDEPBACKSLASH@ @am__fastdepCC_FALSE@ $(LTCOMPILE) -c -o $@ $< mostlyclean-libtool: -rm -f *.lo clean-libtool: -rm -rf .libs _libs -rm -rf src/.libs src/_libs -rm -rf src/alpha/.libs src/alpha/_libs -rm -rf src/arm/.libs src/arm/_libs -rm -rf src/avr32/.libs src/avr32/_libs -rm -rf src/cris/.libs src/cris/_libs -rm -rf src/frv/.libs src/frv/_libs -rm -rf src/ia64/.libs src/ia64/_libs -rm -rf src/m32r/.libs src/m32r/_libs -rm -rf src/m68k/.libs src/m68k/_libs -rm -rf src/mips/.libs src/mips/_libs -rm -rf src/pa/.libs src/pa/_libs -rm -rf src/powerpc/.libs src/powerpc/_libs -rm -rf src/s390/.libs src/s390/_libs -rm -rf src/sh/.libs src/sh/_libs -rm -rf src/sh64/.libs src/sh64/_libs -rm -rf src/sparc/.libs src/sparc/_libs -rm -rf src/x86/.libs src/x86/_libs distclean-libtool: -rm -f libtool config.lt # This directory's subdirectories are mostly independent; you can cd # into them and run `make' without going through this Makefile. # To change the values of `make' variables: instead of editing Makefiles, # (1) if the variable is set in `config.status', edit `config.status' # (which will cause the Makefiles to be regenerated when you run `make'); # (2) otherwise, pass the desired values on the `make' command line. $(RECURSIVE_TARGETS): @fail= failcom='exit 1'; \ for f in x $$MAKEFLAGS; do \ case $$f in \ *=* | --[!k]*);; \ *k*) failcom='fail=yes';; \ esac; \ done; \ dot_seen=no; \ target=`echo $@ | sed s/-recursive//`; \ list='$(SUBDIRS)'; for subdir in $$list; do \ echo "Making $$target in $$subdir"; \ if test "$$subdir" = "."; then \ dot_seen=yes; \ local_target="$$target-am"; \ else \ local_target="$$target"; \ fi; \ ($(am__cd) $$subdir && $(MAKE) $(AM_MAKEFLAGS) $$local_target) \ || eval $$failcom; \ done; \ if test "$$dot_seen" = "no"; then \ $(MAKE) $(AM_MAKEFLAGS) "$$target-am" || exit 1; \ fi; test -z "$$fail" $(RECURSIVE_CLEAN_TARGETS): @fail= failcom='exit 1'; \ for f in x $$MAKEFLAGS; do \ case $$f in \ *=* | --[!k]*);; \ *k*) failcom='fail=yes';; \ esac; \ done; \ dot_seen=no; \ case "$@" in \ distclean-* | maintainer-clean-*) list='$(DIST_SUBDIRS)' ;; \ *) list='$(SUBDIRS)' ;; \ esac; \ rev=''; for subdir in $$list; do \ if test "$$subdir" = "."; then :; else \ rev="$$subdir $$rev"; \ fi; \ done; \ rev="$$rev ."; \ target=`echo $@ | sed s/-recursive//`; \ for subdir in $$rev; do \ echo "Making $$target in $$subdir"; \ if test "$$subdir" = "."; then \ local_target="$$target-am"; \ else \ local_target="$$target"; \ fi; \ ($(am__cd) $$subdir && $(MAKE) $(AM_MAKEFLAGS) $$local_target) \ || eval $$failcom; \ done && test -z "$$fail" tags-recursive: list='$(SUBDIRS)'; for subdir in $$list; do \ test "$$subdir" = . || ($(am__cd) $$subdir && $(MAKE) $(AM_MAKEFLAGS) tags); \ done ctags-recursive: list='$(SUBDIRS)'; for subdir in $$list; do \ test "$$subdir" = . || ($(am__cd) $$subdir && $(MAKE) $(AM_MAKEFLAGS) ctags); \ done ID: $(HEADERS) $(SOURCES) $(LISP) $(TAGS_FILES) list='$(SOURCES) $(HEADERS) $(LISP) $(TAGS_FILES)'; \ unique=`for i in $$list; do \ if test -f "$$i"; then echo $$i; else echo $(srcdir)/$$i; fi; \ done | \ $(AWK) '{ files[$$0] = 1; nonempty = 1; } \ END { if (nonempty) { for (i in files) print i; }; }'`; \ mkid -fID $$unique tags: TAGS TAGS: tags-recursive $(HEADERS) $(SOURCES) fficonfig.h.in $(TAGS_DEPENDENCIES) \ $(TAGS_FILES) $(LISP) set x; \ here=`pwd`; \ if ($(ETAGS) --etags-include --version) >/dev/null 2>&1; then \ include_option=--etags-include; \ empty_fix=.; \ else \ include_option=--include; \ empty_fix=; \ fi; \ list='$(SUBDIRS)'; for subdir in $$list; do \ if test "$$subdir" = .; then :; else \ test ! -f $$subdir/TAGS || \ set "$$@" "$$include_option=$$here/$$subdir/TAGS"; \ fi; \ done; \ list='$(SOURCES) $(HEADERS) fficonfig.h.in $(LISP) $(TAGS_FILES)'; \ unique=`for i in $$list; do \ if test -f "$$i"; then echo $$i; else echo $(srcdir)/$$i; fi; \ done | \ $(AWK) '{ files[$$0] = 1; nonempty = 1; } \ END { if (nonempty) { for (i in files) print i; }; }'`; \ shift; \ if test -z "$(ETAGS_ARGS)$$*$$unique"; then :; else \ test -n "$$unique" || unique=$$empty_fix; \ if test $$# -gt 0; then \ $(ETAGS) $(ETAGSFLAGS) $(AM_ETAGSFLAGS) $(ETAGS_ARGS) \ "$$@" $$unique; \ else \ $(ETAGS) $(ETAGSFLAGS) $(AM_ETAGSFLAGS) $(ETAGS_ARGS) \ $$unique; \ fi; \ fi ctags: CTAGS CTAGS: ctags-recursive $(HEADERS) $(SOURCES) fficonfig.h.in $(TAGS_DEPENDENCIES) \ $(TAGS_FILES) $(LISP) list='$(SOURCES) $(HEADERS) fficonfig.h.in $(LISP) $(TAGS_FILES)'; \ unique=`for i in $$list; do \ if test -f "$$i"; then echo $$i; else echo $(srcdir)/$$i; fi; \ done | \ $(AWK) '{ files[$$0] = 1; nonempty = 1; } \ END { if (nonempty) { for (i in files) print i; }; }'`; \ test -z "$(CTAGS_ARGS)$$unique" \ || $(CTAGS) $(CTAGSFLAGS) $(AM_CTAGSFLAGS) $(CTAGS_ARGS) \ $$unique GTAGS: here=`$(am__cd) $(top_builddir) && pwd` \ && $(am__cd) $(top_srcdir) \ && gtags -i $(GTAGS_ARGS) "$$here" distclean-tags: -rm -f TAGS ID GTAGS GRTAGS GSYMS GPATH tags distdir: $(DISTFILES) $(am__remove_distdir) test -d "$(distdir)" || mkdir "$(distdir)" @srcdirstrip=`echo "$(srcdir)" | sed 's/[].[^$$\\*]/\\\\&/g'`; \ topsrcdirstrip=`echo "$(top_srcdir)" | sed 's/[].[^$$\\*]/\\\\&/g'`; \ list='$(DISTFILES)'; \ dist_files=`for file in $$list; do echo $$file; done | \ sed -e "s|^$$srcdirstrip/||;t" \ -e "s|^$$topsrcdirstrip/|$(top_builddir)/|;t"`; \ case $$dist_files in \ */*) $(MKDIR_P) `echo "$$dist_files" | \ sed '/\//!d;s|^|$(distdir)/|;s,/[^/]*$$,,' | \ sort -u` ;; \ esac; \ for file in $$dist_files; do \ if test -f $$file || test -d $$file; then d=.; else d=$(srcdir); fi; \ if test -d $$d/$$file; then \ dir=`echo "/$$file" | sed -e 's,/[^/]*$$,,'`; \ if test -d "$(distdir)/$$file"; then \ find "$(distdir)/$$file" -type d ! -perm -700 -exec chmod u+rwx {} \;; \ fi; \ if test -d $(srcdir)/$$file && test $$d != $(srcdir); then \ cp -fpR $(srcdir)/$$file "$(distdir)$$dir" || exit 1; \ find "$(distdir)/$$file" -type d ! -perm -700 -exec chmod u+rwx {} \;; \ fi; \ cp -fpR $$d/$$file "$(distdir)$$dir" || exit 1; \ else \ test -f "$(distdir)/$$file" \ || cp -p $$d/$$file "$(distdir)/$$file" \ || exit 1; \ fi; \ done @list='$(DIST_SUBDIRS)'; for subdir in $$list; do \ if test "$$subdir" = .; then :; else \ $(am__make_dryrun) \ || test -d "$(distdir)/$$subdir" \ || $(MKDIR_P) "$(distdir)/$$subdir" \ || exit 1; \ dir1=$$subdir; dir2="$(distdir)/$$subdir"; \ $(am__relativize); \ new_distdir=$$reldir; \ dir1=$$subdir; dir2="$(top_distdir)"; \ $(am__relativize); \ new_top_distdir=$$reldir; \ echo " (cd $$subdir && $(MAKE) $(AM_MAKEFLAGS) top_distdir="$$new_top_distdir" distdir="$$new_distdir" \\"; \ echo " am__remove_distdir=: am__skip_length_check=: am__skip_mode_fix=: distdir)"; \ ($(am__cd) $$subdir && \ $(MAKE) $(AM_MAKEFLAGS) \ top_distdir="$$new_top_distdir" \ distdir="$$new_distdir" \ am__remove_distdir=: \ am__skip_length_check=: \ am__skip_mode_fix=: \ distdir) \ || exit 1; \ fi; \ done -test -n "$(am__skip_mode_fix)" \ || find "$(distdir)" -type d ! -perm -755 \ -exec chmod u+rwx,go+rx {} \; -o \ ! -type d ! -perm -444 -links 1 -exec chmod a+r {} \; -o \ ! -type d ! -perm -400 -exec chmod a+r {} \; -o \ ! -type d ! -perm -444 -exec $(install_sh) -c -m a+r {} {} \; \ || chmod -R a+r "$(distdir)" dist-gzip: distdir tardir=$(distdir) && $(am__tar) | GZIP=$(GZIP_ENV) gzip -c >$(distdir).tar.gz $(am__remove_distdir) dist-bzip2: distdir tardir=$(distdir) && $(am__tar) | BZIP2=$${BZIP2--9} bzip2 -c >$(distdir).tar.bz2 $(am__remove_distdir) dist-lzip: distdir tardir=$(distdir) && $(am__tar) | lzip -c $${LZIP_OPT--9} >$(distdir).tar.lz $(am__remove_distdir) dist-lzma: distdir tardir=$(distdir) && $(am__tar) | lzma -9 -c >$(distdir).tar.lzma $(am__remove_distdir) dist-xz: distdir tardir=$(distdir) && $(am__tar) | XZ_OPT=$${XZ_OPT--e} xz -c >$(distdir).tar.xz $(am__remove_distdir) dist-tarZ: distdir tardir=$(distdir) && $(am__tar) | compress -c >$(distdir).tar.Z $(am__remove_distdir) dist-shar: distdir shar $(distdir) | GZIP=$(GZIP_ENV) gzip -c >$(distdir).shar.gz $(am__remove_distdir) dist-zip: distdir -rm -f $(distdir).zip zip -rq $(distdir).zip $(distdir) $(am__remove_distdir) dist dist-all: distdir tardir=$(distdir) && $(am__tar) | GZIP=$(GZIP_ENV) gzip -c >$(distdir).tar.gz $(am__remove_distdir) # This target untars the dist file and tries a VPATH configuration. Then # it guarantees that the distribution is self-contained by making another # tarfile. distcheck: dist case '$(DIST_ARCHIVES)' in \ *.tar.gz*) \ GZIP=$(GZIP_ENV) gzip -dc $(distdir).tar.gz | $(am__untar) ;;\ *.tar.bz2*) \ bzip2 -dc $(distdir).tar.bz2 | $(am__untar) ;;\ *.tar.lzma*) \ lzma -dc $(distdir).tar.lzma | $(am__untar) ;;\ *.tar.lz*) \ lzip -dc $(distdir).tar.lz | $(am__untar) ;;\ *.tar.xz*) \ xz -dc $(distdir).tar.xz | $(am__untar) ;;\ *.tar.Z*) \ uncompress -c $(distdir).tar.Z | $(am__untar) ;;\ *.shar.gz*) \ GZIP=$(GZIP_ENV) gzip -dc $(distdir).shar.gz | unshar ;;\ *.zip*) \ unzip $(distdir).zip ;;\ esac chmod -R a-w $(distdir); chmod u+w $(distdir) mkdir $(distdir)/_build mkdir $(distdir)/_inst chmod a-w $(distdir) test -d $(distdir)/_build || exit 0; \ dc_install_base=`$(am__cd) $(distdir)/_inst && pwd | sed -e 's,^[^:\\/]:[\\/],/,'` \ && dc_destdir="$${TMPDIR-/tmp}/am-dc-$$$$/" \ && am__cwd=`pwd` \ && $(am__cd) $(distdir)/_build \ && ../configure --srcdir=.. --prefix="$$dc_install_base" \ $(AM_DISTCHECK_CONFIGURE_FLAGS) \ $(DISTCHECK_CONFIGURE_FLAGS) \ && $(MAKE) $(AM_MAKEFLAGS) \ && $(MAKE) $(AM_MAKEFLAGS) dvi \ && $(MAKE) $(AM_MAKEFLAGS) check \ && $(MAKE) $(AM_MAKEFLAGS) install \ && $(MAKE) $(AM_MAKEFLAGS) installcheck \ && $(MAKE) $(AM_MAKEFLAGS) uninstall \ && $(MAKE) $(AM_MAKEFLAGS) distuninstallcheck_dir="$$dc_install_base" \ distuninstallcheck \ && chmod -R a-w "$$dc_install_base" \ && ({ \ (cd ../.. && umask 077 && mkdir "$$dc_destdir") \ && $(MAKE) $(AM_MAKEFLAGS) DESTDIR="$$dc_destdir" install \ && $(MAKE) $(AM_MAKEFLAGS) DESTDIR="$$dc_destdir" uninstall \ && $(MAKE) $(AM_MAKEFLAGS) DESTDIR="$$dc_destdir" \ distuninstallcheck_dir="$$dc_destdir" distuninstallcheck; \ } || { rm -rf "$$dc_destdir"; exit 1; }) \ && rm -rf "$$dc_destdir" \ && $(MAKE) $(AM_MAKEFLAGS) dist \ && rm -rf $(DIST_ARCHIVES) \ && $(MAKE) $(AM_MAKEFLAGS) distcleancheck \ && cd "$$am__cwd" \ || exit 1 $(am__remove_distdir) @(echo "$(distdir) archives ready for distribution: "; \ list='$(DIST_ARCHIVES)'; for i in $$list; do echo $$i; done) | \ sed -e 1h -e 1s/./=/g -e 1p -e 1x -e '$$p' -e '$$x' distuninstallcheck: @test -n '$(distuninstallcheck_dir)' || { \ echo 'ERROR: trying to run $@ with an empty' \ '$$(distuninstallcheck_dir)' >&2; \ exit 1; \ }; \ $(am__cd) '$(distuninstallcheck_dir)' || { \ echo 'ERROR: cannot chdir into $(distuninstallcheck_dir)' >&2; \ exit 1; \ }; \ test `$(am__distuninstallcheck_listfiles) | wc -l` -eq 0 \ || { echo "ERROR: files left after uninstall:" ; \ if test -n "$(DESTDIR)"; then \ echo " (check DESTDIR support)"; \ fi ; \ $(distuninstallcheck_listfiles) ; \ exit 1; } >&2 distcleancheck: distclean @if test '$(srcdir)' = . ; then \ echo "ERROR: distcleancheck can only run from a VPATH build" ; \ exit 1 ; \ fi @test `$(distcleancheck_listfiles) | wc -l` -eq 0 \ || { echo "ERROR: files left in build directory after distclean:" ; \ $(distcleancheck_listfiles) ; \ exit 1; } >&2 check-am: all-am check: check-recursive all-am: Makefile $(LTLIBRARIES) fficonfig.h installdirs: installdirs-recursive installdirs-am: install: install-recursive install-exec: install-exec-recursive install-data: install-data-recursive uninstall: uninstall-recursive install-am: all-am @$(MAKE) $(AM_MAKEFLAGS) install-exec-am install-data-am installcheck: installcheck-recursive install-strip: if test -z '$(STRIP)'; then \ $(MAKE) $(AM_MAKEFLAGS) INSTALL_PROGRAM="$(INSTALL_STRIP_PROGRAM)" \ install_sh_PROGRAM="$(INSTALL_STRIP_PROGRAM)" INSTALL_STRIP_FLAG=-s \ install; \ else \ $(MAKE) $(AM_MAKEFLAGS) INSTALL_PROGRAM="$(INSTALL_STRIP_PROGRAM)" \ install_sh_PROGRAM="$(INSTALL_STRIP_PROGRAM)" INSTALL_STRIP_FLAG=-s \ "INSTALL_PROGRAM_ENV=STRIPPROG='$(STRIP)'" install; \ fi mostlyclean-generic: clean-generic: distclean-generic: -test -z "$(CONFIG_CLEAN_FILES)" || rm -f $(CONFIG_CLEAN_FILES) -test . = "$(srcdir)" || test -z "$(CONFIG_CLEAN_VPATH_FILES)" || rm -f $(CONFIG_CLEAN_VPATH_FILES) -rm -f src/$(DEPDIR)/$(am__dirstamp) -rm -f src/$(am__dirstamp) -rm -f src/alpha/$(DEPDIR)/$(am__dirstamp) -rm -f src/alpha/$(am__dirstamp) -rm -f src/arm/$(DEPDIR)/$(am__dirstamp) -rm -f src/arm/$(am__dirstamp) -rm -f src/avr32/$(DEPDIR)/$(am__dirstamp) -rm -f src/avr32/$(am__dirstamp) -rm -f src/cris/$(DEPDIR)/$(am__dirstamp) -rm -f src/cris/$(am__dirstamp) -rm -f src/frv/$(DEPDIR)/$(am__dirstamp) -rm -f src/frv/$(am__dirstamp) -rm -f src/ia64/$(DEPDIR)/$(am__dirstamp) -rm -f src/ia64/$(am__dirstamp) -rm -f src/m32r/$(DEPDIR)/$(am__dirstamp) -rm -f src/m32r/$(am__dirstamp) -rm -f src/m68k/$(DEPDIR)/$(am__dirstamp) -rm -f src/m68k/$(am__dirstamp) -rm -f src/mips/$(DEPDIR)/$(am__dirstamp) -rm -f src/mips/$(am__dirstamp) -rm -f src/pa/$(DEPDIR)/$(am__dirstamp) -rm -f src/pa/$(am__dirstamp) -rm -f src/powerpc/$(DEPDIR)/$(am__dirstamp) -rm -f src/powerpc/$(am__dirstamp) -rm -f src/s390/$(DEPDIR)/$(am__dirstamp) -rm -f src/s390/$(am__dirstamp) -rm -f src/sh/$(DEPDIR)/$(am__dirstamp) -rm -f src/sh/$(am__dirstamp) -rm -f src/sh64/$(DEPDIR)/$(am__dirstamp) -rm -f src/sh64/$(am__dirstamp) -rm -f src/sparc/$(DEPDIR)/$(am__dirstamp) -rm -f src/sparc/$(am__dirstamp) -rm -f src/x86/$(DEPDIR)/$(am__dirstamp) -rm -f src/x86/$(am__dirstamp) maintainer-clean-generic: @echo "This command is intended for maintainers to use" @echo "it deletes files that may require special tools to rebuild." clean: clean-recursive clean-am: clean-generic clean-libtool clean-noinstLTLIBRARIES \ mostlyclean-am distclean: distclean-recursive -rm -f $(am__CONFIG_DISTCLEAN_FILES) -rm -rf src/$(DEPDIR) src/alpha/$(DEPDIR) src/arm/$(DEPDIR) src/avr32/$(DEPDIR) src/cris/$(DEPDIR) src/frv/$(DEPDIR) src/ia64/$(DEPDIR) src/m32r/$(DEPDIR) src/m68k/$(DEPDIR) src/mips/$(DEPDIR) src/pa/$(DEPDIR) src/powerpc/$(DEPDIR) src/s390/$(DEPDIR) src/sh/$(DEPDIR) src/sh64/$(DEPDIR) src/sparc/$(DEPDIR) src/x86/$(DEPDIR) -rm -f Makefile distclean-am: clean-am distclean-compile distclean-generic \ distclean-hdr distclean-libtool distclean-tags dvi: dvi-recursive dvi-am: html: html-recursive html-am: info: info-recursive info-am: install-data-am: install-dvi: install-dvi-recursive install-dvi-am: install-exec-am: install-html-am: install-info: install-info-recursive install-info-am: install-man: install-pdf: install-pdf-recursive install-pdf-am: install-ps: install-ps-recursive install-ps-am: installcheck-am: maintainer-clean: maintainer-clean-recursive -rm -f $(am__CONFIG_DISTCLEAN_FILES) -rm -rf $(top_srcdir)/autom4te.cache -rm -rf src/$(DEPDIR) src/alpha/$(DEPDIR) src/arm/$(DEPDIR) src/avr32/$(DEPDIR) src/cris/$(DEPDIR) src/frv/$(DEPDIR) src/ia64/$(DEPDIR) src/m32r/$(DEPDIR) src/m68k/$(DEPDIR) src/mips/$(DEPDIR) src/pa/$(DEPDIR) src/powerpc/$(DEPDIR) src/s390/$(DEPDIR) src/sh/$(DEPDIR) src/sh64/$(DEPDIR) src/sparc/$(DEPDIR) src/x86/$(DEPDIR) -rm -f Makefile maintainer-clean-am: distclean-am maintainer-clean-generic mostlyclean: mostlyclean-recursive mostlyclean-am: mostlyclean-compile mostlyclean-generic \ mostlyclean-libtool pdf: pdf-recursive pdf-am: ps: ps-recursive ps-am: uninstall-am: .MAKE: $(RECURSIVE_CLEAN_TARGETS) $(RECURSIVE_TARGETS) all \ ctags-recursive install-am install-strip tags-recursive .PHONY: $(RECURSIVE_CLEAN_TARGETS) $(RECURSIVE_TARGETS) CTAGS GTAGS \ all all-am am--refresh check check-am clean clean-generic \ clean-libtool clean-noinstLTLIBRARIES ctags ctags-recursive \ dist dist-all dist-bzip2 dist-gzip dist-lzip dist-lzma \ dist-shar dist-tarZ dist-xz dist-zip distcheck distclean \ distclean-compile distclean-generic distclean-hdr \ distclean-libtool distclean-tags distcleancheck distdir \ distuninstallcheck dvi dvi-am html html-am info info-am \ install install-am install-data install-data-am install-dvi \ install-dvi-am install-exec install-exec-am install-html \ install-html-am install-info install-info-am install-man \ install-pdf install-pdf-am install-ps install-ps-am \ install-strip installcheck installcheck-am installdirs \ installdirs-am maintainer-clean maintainer-clean-generic \ mostlyclean mostlyclean-compile mostlyclean-generic \ mostlyclean-libtool pdf pdf-am ps ps-am tags tags-recursive \ uninstall uninstall-am # No install-html support .PHONY: install-html install-html: # Tell versions [3.59,3.63) of GNU make to not export all variables. # Otherwise a system limit (for SysV at least) may be exceeded. .NOEXPORT: smalltalk-3.2.5/libffi/ChangeLog.v10000644000175000017500000005474012130343734013772 00000000000000The libffi version 1 ChangeLog archive. Version 1 of libffi had per-directory ChangeLogs. Current and future versions have a single ChangeLog file in the root directory. The version 1 ChangeLogs have all been concatonated into this file for future reference only. --- libffi ---------------------------------------------------------------- Mon Oct 5 02:17:50 1998 Anthony Green * configure.in: Boosted rev. * configure, Makefile.in, aclocal.m4: Rebuilt. * README: Boosted rev and updated release notes. Mon Oct 5 01:03:03 1998 Anthony Green * configure.in: Boosted rev. * configure, Makefile.in, aclocal.m4: Rebuilt. * README: Boosted rev and updated release notes. 1998-07-25 Andreas Schwab * m68k/ffi.c (ffi_prep_cif_machdep): Use bitmask for cif->flags. Correctly handle small structures. (ffi_prep_args): Also handle small structures. (ffi_call): Pass size of return type to ffi_call_SYSV. * m68k/sysv.S: Adjust for above changes. Correctly align small structures in the return value. * types.c (uint64, sint64) [M68K]: Change alignment to 4. Fri Apr 17 17:26:58 1998 Anthony Green * configure.in: Boosted rev. * configure,Makefile.in,aclocal.m4: Rebuilt. * README: Boosted rev and added release notes. Sun Feb 22 00:50:41 1998 Geoff Keating * configure.in: Add PowerPC config bits. 1998-02-14 Andreas Schwab * configure.in: Add m68k config bits. Change AC_CANONICAL_SYSTEM to AC_CANONICAL_HOST, this is not a compiler. Use $host instead of $target. Remove AC_CHECK_SIZEOF(char), we already know the result. Fix argument of AC_ARG_ENABLE. * configure, fficonfig.h.in: Rebuilt. Tue Feb 10 20:53:40 1998 Richard Henderson * configure.in: Add Alpha config bits. Tue May 13 13:39:20 1997 Anthony Green * README: Updated dates and reworded Irix comments. * configure.in: Removed AC_PROG_RANLIB. * Makefile.in, aclocal.m4, config.guess, config.sub, configure, ltmain.sh, */Makefile.in: libtoolized again and rebuilt with automake and autoconf. Sat May 10 18:44:50 1997 Tom Tromey * configure, aclocal.m4: Rebuilt. * configure.in: Don't compute EXTRADIST; now handled in src/Makefile.in. Removed macros implied by AM_INIT_AUTOMAKE. Don't run AM_MAINTAINER_MODE. Thu May 8 14:34:05 1997 Anthony Green * missing, ltmain.sh, ltconfig.sh: Created. These are new files required by automake and libtool. * README: Boosted rev to 1.14. Added notes. * acconfig.h: Moved PACKAGE and VERSION for new automake. * configure.in: Changes for libtool. * Makefile.am (check): make test now make check. Uses libtool now. * Makefile.in, configure.in, aclocal.h, fficonfig.h.in: Rebuilt. Thu May 1 16:27:07 1997 Anthony Green * missing: Added file required by new automake. Tue Nov 26 14:10:42 1996 Anthony Green * acconfig.h: Added USING_PURIFY flag. This is defined when --enable-purify-safety was used at configure time. * configure.in (allsources): Added --enable-purify-safety switch. (VERSION): Boosted rev to 1.13. * configure: Rebuilt. Fri Nov 22 06:46:12 1996 Anthony Green * configure.in (VERSION): Boosted rev to 1.12. Removed special CFLAGS hack for gcc. * configure: Rebuilt. * README: Boosted rev to 1.12. Added notes. * Many files: Cygnus Support changed to Cygnus Solutions. Wed Oct 30 11:15:25 1996 Anthony Green * configure.in (VERSION): Boosted rev to 1.11. * configure: Rebuilt. * README: Boosted rev to 1.11. Added notes about GNU make. Tue Oct 29 12:25:12 1996 Anthony Green * configure.in: Fixed -Wall trick. (VERSION): Boosted rev. * configure: Rebuilt * acconfig.h: Needed for --enable-debug configure switch. * README: Boosted rev to 1.09. Added more notes on building libffi, and LCLint. * configure.in: Added --enable-debug switch. Boosted rev to 1.09. * configure: Rebuilt Tue Oct 15 13:11:28 1996 Anthony Green * configure.in (VERSION): Boosted rev to 1.08 * configure: Rebuilt. * README: Added n32 bug fix notes. * Makefile.am: Added "make lint" production. * Makefile.in: Rebuilt. Mon Oct 14 10:54:46 1996 Anthony Green * README: Added web page reference. * configure.in, README: Boosted rev to 1.05 * configure: Rebuilt. * README: Fixed n32 sample code. Fri Oct 11 17:09:28 1996 Anthony Green * README: Added sparc notes. * configure.in, README: Boosted rev to 1.04. * configure: Rebuilt. Thu Oct 10 10:31:03 1996 Anthony Green * configure.in, README: Boosted rev to 1.03. * configure: Rebuilt. * README: Added struct notes. * Makefile.am (EXTRA_DIST): Added LICENSE to distribution. * Makefile.in: Rebuilt. * README: Removed Linux section. No special notes now because aggregates arg/return types work. Wed Oct 9 16:16:42 1996 Anthony Green * README, configure.in (VERSION): Boosted rev to 1.02 * configure: Rebuilt. Tue Oct 8 11:56:33 1996 Anthony Green * README (NOTE): Added n32 notes. * Makefile.am: Added test production. * Makefile: Rebuilt * README: spell checked! * configure.in (VERSION): Boosted rev to 1.01 * configure: Rebuilt. Mon Oct 7 15:50:22 1996 Anthony Green * configure.in: Added nasty bit to support SGI tools. * configure: Rebuilt. * README: Added SGI notes. Added note about automake bug. Mon Oct 7 11:00:28 1996 Anthony Green * README: Rewrote intro, and fixed examples. Fri Oct 4 10:19:55 1996 Anthony Green * configure.in: -D$TARGET is no longer used as a compiler switch. It is now inserted into ffi.h at configure time. * configure: Rebuilt. * FFI_ABI and FFI_STATUS are now ffi_abi and ffi_status. Thu Oct 3 13:47:34 1996 Anthony Green * README, LICENSE: Created. Wrote some docs. * configure.in: Don't barf on i586-unknown-linuxaout. Added EXTRADIST code for "make dist". * configure: Rebuilt. * */Makefile.in: Rebuilt with patched automake. Tue Oct 1 17:12:25 1996 Anthony Green * Makefile.am, aclocal.m4, config.guess, config.sub, configure.in, fficonfig.h.in, install-sh, mkinstalldirs, stamp-h.in: Created * Makefile.in, configure: Generated --- libffi/include -------------------------------------------------------- Tue Feb 24 13:09:36 1998 Anthony Green * ffi_mips.h: Updated FFI_TYPE_STRUCT_* values based on ffi.h.in changes. This is a work-around for SGI's "simple" assembler. Sun Feb 22 00:51:55 1998 Geoff Keating * ffi.h.in: PowerPC support. 1998-02-14 Andreas Schwab * ffi.h.in: Add m68k support. (FFI_TYPE_LONGDOUBLE): Make it a separate value. Tue Feb 10 20:55:16 1998 Richard Henderson * ffi.h.in (SIZEOF_ARG): Use a pointer type by default. * ffi.h.in: Alpha support. Fri Nov 22 06:48:45 1996 Anthony Green * ffi.h.in, ffi_common.h: Cygnus Support -> Cygnus Solutions. Wed Nov 20 22:31:01 1996 Anthony Green * ffi.h.in: Added ffi_type_void definition. Tue Oct 29 12:22:40 1996 Anthony Green * Makefile.am (hack_DATA): Always install ffi_mips.h. * ffi.h.in: Removed FFI_DEBUG. It's now in the correct place (acconfig.h). Added #include for size_t definition. Tue Oct 15 17:23:35 1996 Anthony Green * ffi.h.in, ffi_common.h, ffi_mips.h: More clean up. Commented out #define of FFI_DEBUG. Tue Oct 15 13:01:06 1996 Anthony Green * ffi_common.h: Added bool definition. * ffi.h.in, ffi_common.h: Clean up based on LCLint output. Added funny /*@...@*/ comments to annotate source. Mon Oct 14 12:29:23 1996 Anthony Green * ffi.h.in: Interface changes based on feedback from Jim Blandy. Fri Oct 11 16:49:35 1996 Anthony Green * ffi.h.in: Small change for sparc support. Thu Oct 10 14:53:37 1996 Anthony Green * ffi_mips.h: Added FFI_TYPE_STRUCT_* definitions for special structure return types. Wed Oct 9 13:55:57 1996 Anthony Green * ffi.h.in: Added SIZEOF_ARG definition for X86 Tue Oct 8 11:40:36 1996 Anthony Green * ffi.h.in (FFI_FN): Added macro for eliminating compiler warnings. Use it to case your function pointers to the proper type. * ffi_mips.h (SIZEOF_ARG): Added magic to fix type promotion bug. * Makefile.am (EXTRA_DIST): Added ffi_mips.h to EXTRA_DIST. * Makefile: Rebuilt. * ffi_mips.h: Created. Moved all common mips definitions here. Mon Oct 7 10:58:12 1996 Anthony Green * ffi.h.in: The SGI assember is very picky about parens. Redefined some macros to avoid problems. * ffi.h.in: Added FFI_DEFAULT_ABI definitions. Also added externs for pointer, and 64bit integral ffi_types. Fri Oct 4 09:51:37 1996 Anthony Green * ffi.h.in: Added FFI_ABI member to ffi_cif and changed function prototypes accordingly. Added #define @TARGET@. Now programs including ffi.h don't have to specify this themselves. Thu Oct 3 15:36:44 1996 Anthony Green * ffi.h.in: Changed ffi_prep_cif's values from void* to void** * Makefile.am (EXTRA_DIST): Added EXTRA_DIST for "make dist" to work. * Makefile.in: Regenerated. Wed Oct 2 10:16:59 1996 Anthony Green * Makefile.am: Created * Makefile.in: Generated * ffi_common.h: Added rcsid comment Tue Oct 1 17:13:51 1996 Anthony Green * ffi.h.in, ffi_common.h: Created --- libffi/src ------------------------------------------------------------ Mon Oct 5 02:17:50 1998 Anthony Green * arm/ffi.c, arm/sysv.S: Created. * Makefile.am: Added arm files. * Makefile.in: Rebuilt. Mon Oct 5 01:41:38 1998 Anthony Green * Makefile.am (libffi_la_LDFLAGS): Incremented revision. Sun Oct 4 16:27:17 1998 Anthony Green * alpha/osf.S (ffi_call_osf): Patch for DU assembler. * ffitest.c (main): long long and long double return values work for x86. Fri Apr 17 11:50:58 1998 Anthony Green * Makefile.in: Rebuilt. * ffitest.c (main): Floating point tests not executed for systems with broken lond double (SunOS 4 w/ GCC). * types.c: Fixed x86 alignment info for long long types. Thu Apr 16 07:15:28 1998 Anthony Green * ffitest.c: Added more notes about GCC bugs under Irix 6. Wed Apr 15 08:42:22 1998 Anthony Green * ffitest.c (struct5): New test function. (main): New test with struct5. Thu Mar 5 10:48:11 1998 Anthony Green * prep_cif.c (initialize_aggregate): Fix assertion for nested structures. Tue Feb 24 16:33:41 1998 Anthony Green * prep_cif.c (ffi_prep_cif): Added long double support for sparc. Sun Feb 22 00:52:18 1998 Geoff Keating * powerpc/asm.h: New file. * powerpc/ffi.c: New file. * powerpc/sysv.S: New file. * Makefile.am: PowerPC port. * ffitest.c (main): Allow all tests to run even in presence of gcc bug on PowerPC. 1998-02-17 Anthony Green * mips/ffi.c: Fixed comment typo. * x86/ffi.c (ffi_prep_cif_machdep), x86/sysv.S (retfloat): Fixed x86 long double return handling. * types.c: Fixed x86 long double alignment info. 1998-02-14 Andreas Schwab * types.c: Add m68k support. * ffitest.c (floating): Add long double parameter. (return_ll, ldblit): New functions to test long long and long double return value. (main): Fix type error in assignment of ts[1-4]_type.elements. Add tests for long long and long double arguments and return values. * prep_cif.c (ffi_prep_cif) [M68K]: Don't allocate argument for struct value pointer. * m68k/ffi.c, m68k/sysv.S: New files. * Makefile.am: Add bits for m68k port. Add kludge to work around automake deficiency. (test): Don't require "." in $PATH. * Makefile.in: Rebuilt. Wed Feb 11 07:36:50 1998 Anthony Green * Makefile.in: Rebuilt. Tue Feb 10 20:56:00 1998 Richard Henderson * alpha/ffi.c, alpha/osf.S: New files. * Makefile.am: Alpha port. Tue Nov 18 14:12:07 1997 Anthony Green * mips/ffi.c (ffi_prep_cif_machdep): Initialize rstruct_flag for n32. Tue Jun 3 17:18:20 1997 Anthony Green * ffitest.c (main): Added hack to get structure tests working correctly. Sat May 10 19:06:42 1997 Tom Tromey * Makefile.in: Rebuilt. * Makefile.am (EXTRA_DIST): Explicitly list all distributable files in subdirs. (VERSION, CC): Removed. Thu May 8 17:19:01 1997 Anthony Green * Makefile.am: Many changes for new automake and libtool. * Makefile.in: Rebuilt. Fri Nov 22 06:57:56 1996 Anthony Green * ffitest.c (main): Fixed test case for non mips machines. Wed Nov 20 22:31:59 1996 Anthony Green * types.c: Added ffi_type_void declaration. Tue Oct 29 13:07:19 1996 Anthony Green * ffitest.c (main): Fixed character constants. (main): Emit warning for structure test 3 failure on Sun. * Makefile.am (VPATH): Fixed VPATH def'n so automake won't strip it out. Moved distdir hack from libffi to automake. (ffitest): Added missing -c for $(COMPILE) (change in automake). * Makefile.in: Rebuilt. Tue Oct 15 13:08:20 1996 Anthony Green * Makefile.am: Added "make lint" production. * Makefile.in: Rebuilt. * prep_cif.c (STACK_ARG_SIZE): Improved STACK_ARG_SIZE macro. Clean up based on LCLint output. Added funny /*@...@*/ comments to annotate source. * ffitest.c, debug.c: Cleaned up code. Mon Oct 14 12:26:56 1996 Anthony Green * ffitest.c: Changes based on interface changes. * prep_cif.c (ffi_prep_cif): Cleaned up interface based on feedback from Jim Blandy. Fri Oct 11 15:53:18 1996 Anthony Green * ffitest.c: Reordered tests while porting to sparc. Made changes to handle lame structure passing for sparc. Removed calls to fflush(). * prep_cif.c (ffi_prep_cif): Added special case for sparc aggregate type arguments. Thu Oct 10 09:56:51 1996 Anthony Green * ffitest.c (main): Added structure passing/returning tests. * prep_cif.c (ffi_prep_cif): Perform proper initialization of structure return types if needed. (initialize_aggregate): Bug fix Wed Oct 9 16:04:20 1996 Anthony Green * types.c: Added special definitions for x86 (double doesn't need double word alignment). * ffitest.c: Added many tests Tue Oct 8 09:19:22 1996 Anthony Green * prep_cif.c (ffi_prep_cif): Fixed assertion. * debug.c (ffi_assert): Must return a non void now. * Makefile.am: Added test production. * Makefile: Rebuilt. * ffitest.c (main): Created. * types.c: Created. Stripped common code out of */ffi.c. * prep_cif.c: Added missing stdlib.h include. * debug.c (ffi_type_test): Used "a" to eliminate compiler warnings in non-debug builds. Included ffi_common.h. Mon Oct 7 15:36:42 1996 Anthony Green * Makefile.am: Added a rule for .s -> .o This is required by the SGI compiler. * Makefile: Rebuilt. Fri Oct 4 09:51:08 1996 Anthony Green * prep_cif.c (initialize_aggregate): Moved abi specification to ffi_prep_cif(). Thu Oct 3 15:37:37 1996 Anthony Green * prep_cif.c (ffi_prep_cif): Changed values from void* to void**. (initialize_aggregate): Fixed aggregate type initialization. * Makefile.am (EXTRA_DIST): Added support code for "make dist". * Makefile.in: Regenerated. Wed Oct 2 11:41:57 1996 Anthony Green * debug.c, prep_cif: Created. * Makefile.am: Added debug.o and prep_cif.o to OBJ. * Makefile.in: Regenerated. * Makefile.am (INCLUDES): Added missing -I../include * Makefile.in: Regenerated. Tue Oct 1 17:11:51 1996 Anthony Green * error.c, Makefile.am: Created. * Makefile.in: Generated. --- libffi/src/x86 -------------------------------------------------------- Sun Oct 4 16:27:17 1998 Anthony Green * sysv.S (retlongdouble): Fixed long long return value support. * ffi.c (ffi_prep_cif_machdep): Ditto. Wed May 13 04:30:33 1998 Anthony Green * ffi.c (ffi_prep_cif_machdep): Fixed long double return value support. Wed Apr 15 08:43:20 1998 Anthony Green * ffi.c (ffi_prep_args): small struct support was missing. Thu May 8 16:53:58 1997 Anthony Green * objects.mak: Removed. Mon Dec 2 15:12:58 1996 Tom Tromey * sysv.S: Use .balign, for a.out Linux boxes. Tue Oct 15 13:06:50 1996 Anthony Green * ffi.c: Clean up based on LCLint output. Added funny /*@...@*/ comments to annotate source. Fri Oct 11 16:43:38 1996 Anthony Green * ffi.c (ffi_call): Added assertion for bad ABIs. Wed Oct 9 13:57:27 1996 Anthony Green * sysv.S (retdouble): Fixed double return problems. * ffi.c (ffi_call): Corrected fn arg definition. (ffi_prep_cif_machdep): Fixed double return problems Tue Oct 8 12:12:49 1996 Anthony Green * ffi.c: Moved ffi_type definitions to types.c. (ffi_prep_args): Fixed type promotion bug. Mon Oct 7 15:53:06 1996 Anthony Green * ffi.c (FFI_*_TYPEDEF): Removed redundant ';' Fri Oct 4 09:54:53 1996 Anthony Green * ffi.c (ffi_call): Removed FFI_ABI arg, and swapped remaining args. Wed Oct 2 10:07:05 1996 Anthony Green * ffi.c, sysv.S, objects.mak: Created. (ffi_prep_cif): cif->rvalue no longer initialized to NULL. (ffi_prep_cif_machdep): Moved machine independent cif processing to src/prep_cif.c. Introduced ffi_prep_cif_machdep(). --- libffi/src/mips ------------------------------------------------------- Tue Feb 17 17:18:07 1998 Anthony Green * o32.S: Fixed typo in comment. * ffi.c (ffi_prep_cif_machdep): Fixed argument processing. Thu May 8 16:53:58 1997 Anthony Green * o32.s, n32.s: Wrappers for SGI tool support. * objects.mak: Removed. Tue Oct 29 14:37:45 1996 Anthony Green * ffi.c (ffi_prep_args): Changed int z to size_t z. Tue Oct 15 13:17:25 1996 Anthony Green * n32.S: Fixed bad stack munging. * ffi.c: Moved prototypes for ffi_call_?32() to here from ffi_mips.h because extended_cif is not defined in ffi_mips.h. Mon Oct 14 12:42:02 1996 Anthony Green * ffi.c: Interface changes based on feedback from Jim Blandy. Thu Oct 10 11:22:16 1996 Anthony Green * n32.S, ffi.c: Lots of changes to support passing and returning structures with the n32 calling convention. * n32.S: Fixed fn pointer bug. * ffi.c (ffi_prep_cif_machdep): Fix for o32 structure return values. (ffi_prep_args): Fixed n32 structure passing when structures partially fit in registers. Wed Oct 9 13:49:25 1996 Anthony Green * objects.mak: Added n32.o. * n32.S: Created. * ffi.c (ffi_prep_args): Added magic to support proper n32 processing. Tue Oct 8 10:37:35 1996 Anthony Green * ffi.c: Moved ffi_type definitions to types.c. (ffi_prep_args): Fixed type promotion bug. * o32.S: This code is only built for o32 compiles. A lot of the #define cruft has moved to ffi_mips.h. * ffi.c (ffi_prep_cif_machdep): Fixed arg flags. Second arg is only processed if the first is either a float or double. Mon Oct 7 15:33:59 1996 Anthony Green * o32.S: Modified to compile under each of o32, n32 and n64. * ffi.c (FFI_*_TYPEDEF): Removed redundant ';' Fri Oct 4 09:53:25 1996 Anthony Green * ffi.c (ffi_call): Removed FFI_ABI arg, and swapped remaining args. Wed Oct 2 17:41:22 1996 Anthony Green * o32.S: Removed crufty definitions. Wed Oct 2 12:53:42 1996 Anthony Green * ffi.c (ffi_prep_cif): cif->rvalue no longer initialized to NULL. (ffi_prep_cif_machdep): Moved all machine independent cif processing to src/prep_cif.c. Introduced ffi_prep_cif_machdep. Return types of FFI_TYPE_STRUCT are no different than FFI_TYPE_INT. Tue Oct 1 17:11:02 1996 Anthony Green * ffi.c, o32.S, object.mak: Created --- libffi/src/sparc ------------------------------------------------------ Tue Feb 24 16:33:18 1998 Anthony Green * ffi.c (ffi_prep_args): Added long double support. Thu May 8 16:53:58 1997 Anthony Green * objects.mak: Removed. Thu May 1 16:07:56 1997 Anthony Green * v8.S: Fixed minor portability problem reported by Russ McManus . Tue Nov 26 14:12:43 1996 Anthony Green * v8.S: Used STACKFRAME define elsewhere. * ffi.c (ffi_prep_args): Zero out space when USING_PURIFY is set. (ffi_prep_cif_machdep): Allocate the correct stack frame space for functions with < 6 args. Tue Oct 29 15:08:55 1996 Anthony Green * ffi.c (ffi_prep_args): int z is now size_t z. Mon Oct 14 13:31:24 1996 Anthony Green * v8.S (ffi_call_V8): Gordon rewrites this again. It looks great now. * ffi.c (ffi_call): The comment about hijacked registers is no longer valid after gordoni hacked v8.S. * v8.S (ffi_call_V8): Rewrote with gordoni. Much simpler. * v8.S, ffi.c: ffi_call() had changed to accept more than two args, so v8.S had to change (because it hijacks incoming arg registers). * ffi.c: Interface changes based on feedback from Jim Blandy. Thu Oct 10 17:48:16 1996 Anthony Green * ffi.c, v8.S, objects.mak: Created. smalltalk-3.2.5/libffi/configure.ac0000644000175000017500000002767112130343734014164 00000000000000dnl Process this with autoconf to create configure AC_PREREQ(2.64) AC_INIT([libffi], [3.0.9], [http://gcc.gnu.org/bugs.html]) AC_CONFIG_HEADERS([fficonfig.h]) AC_CONFIG_AUX_DIR(../build-aux) AC_CONFIG_MACRO_DIR(../build-aux) AC_CANONICAL_SYSTEM target_alias=${target_alias-$host_alias} . ${srcdir}/configure.host AM_INIT_AUTOMAKE # The same as in boehm-gc and libstdc++. Have to borrow it from there. # We must force CC to /not/ be precious variables; otherwise # the wrong, non-multilib-adjusted value will be used in multilibs. # As a side effect, we have to subst CFLAGS ourselves. m4_rename([_AC_ARG_VAR_PRECIOUS],[real_PRECIOUS]) m4_define([_AC_ARG_VAR_PRECIOUS],[]) AC_PROG_CC m4_rename_force([real_PRECIOUS],[_AC_ARG_VAR_PRECIOUS]) AC_SUBST(CFLAGS) AM_PROG_AS AM_PROG_CC_C_O AC_PROG_LIBTOOL dnl The -no-testsuite modules omit the test subdir. AM_CONDITIONAL(TESTSUBDIR, test -d $srcdir/testsuite) TARGETDIR="unknown" case "$host" in alpha*-*-*) TARGET=ALPHA; TARGETDIR=alpha; # Support 128-bit long double, changeable via command-line switch. HAVE_LONG_DOUBLE='defined(__LONG_DOUBLE_128__)' ;; arm*-*-*) TARGET=ARM; TARGETDIR=arm ;; amd64-*-freebsd* | amd64-*-openbsd*) TARGET=X86_64; TARGETDIR=x86 ;; avr32*-*-*) TARGET=AVR32; TARGETDIR=avr32 ;; cris-*-*) TARGET=LIBFFI_CRIS; TARGETDIR=cris ;; frv-*-*) TARGET=FRV; TARGETDIR=frv ;; hppa*-*-linux* | parisc*-*-linux*) TARGET=PA_LINUX; TARGETDIR=pa ;; hppa*64-*-hpux*) TARGET=PA64_HPUX; TARGETDIR=pa ;; hppa*-*-hpux*) TARGET=PA_HPUX; TARGETDIR=pa ;; i?86-*-freebsd* | i?86-*-openbsd* | i?86-*-dragonfly*) TARGET=X86_FREEBSD; TARGETDIR=x86 ;; i?86-win32* | i?86-*-cygwin* | i?86-*-mingw* | i?86-*-os2*) TARGET=X86_WIN32; TARGETDIR=x86 # All mingw/cygwin/win32 builds require this for sharedlib AM_LTLDFLAGS="-no-undefined" ;; i?86-*-darwin*) TARGET=X86_DARWIN; TARGETDIR=x86 ;; i?86-*-solaris2.1[[0-9]]*) TARGET=X86_64; TARGETDIR=x86 ;; i?86-*-*) TARGET=X86; TARGETDIR=x86 ;; ia64*-*-*) TARGET=IA64; TARGETDIR=ia64 ;; m32r*-*-*) TARGET=M32R; TARGETDIR=m32r ;; m68k-*-*) TARGET=M68K; TARGETDIR=m68k ;; mips-sgi-irix5.* | mips-sgi-irix6.*) TARGET=MIPS; TARGETDIR=mips ;; mips*-*-linux*) # Support 128-bit long double for NewABI. HAVE_LONG_DOUBLE='defined(__mips64)' TARGET=MIPS; TARGETDIR=mips ;; powerpc*-*-linux* | powerpc-*-sysv*) TARGET=POWERPC; TARGETDIR=powerpc ;; powerpc-*-beos*) TARGET=POWERPC; TARGETDIR=powerpc ;; powerpc-*-darwin*) TARGET=POWERPC_DARWIN; TARGETDIR=powerpc ;; powerpc-*-aix* | rs6000-*-aix*) TARGET=POWERPC_AIX; TARGETDIR=powerpc ;; powerpc-*-freebsd*) TARGET=POWERPC_FREEBSD; TARGETDIR=powerpc ;; powerpc64-*-freebsd*) TARGET=POWERPC; TARGETDIR=powerpc ;; powerpc*-*-rtems*) TARGET=POWERPC; TARGETDIR=powerpc ;; s390-*-* | s390x-*-*) TARGET=S390; TARGETDIR=s390 ;; sh-*-* | sh[[34]]*-*-*) TARGET=SH; TARGETDIR=sh ;; sh64-*-* | sh5*-*-*) TARGET=SH64; TARGETDIR=sh64 ;; sparc*-*-*) TARGET=SPARC; TARGETDIR=sparc ;; x86_64-*-darwin*) TARGET=X86_DARWIN; TARGETDIR=x86 ;; x86_64-*-cygwin* | x86_64-*-mingw*) TARGET=X86_WIN64; TARGETDIR=x86 ;; x86_64-*-*) TARGET=X86_64; TARGETDIR=x86 ;; esac AC_SUBST(AM_RUNTESTFLAGS) AC_SUBST(AM_LTLDFLAGS) if test $TARGETDIR = unknown; then AC_MSG_ERROR(["libffi has not been ported to $host."]) fi AM_CONDITIONAL(MIPS, test x$TARGET = xMIPS) AM_CONDITIONAL(SPARC, test x$TARGET = xSPARC) AM_CONDITIONAL(X86, test x$TARGET = xX86) AM_CONDITIONAL(X86_FREEBSD, test x$TARGET = xX86_FREEBSD) AM_CONDITIONAL(X86_WIN32, test x$TARGET = xX86_WIN32) AM_CONDITIONAL(X86_WIN64, test x$TARGET = xX86_WIN64) AM_CONDITIONAL(X86_DARWIN, test x$TARGET = xX86_DARWIN) AM_CONDITIONAL(ALPHA, test x$TARGET = xALPHA) AM_CONDITIONAL(IA64, test x$TARGET = xIA64) AM_CONDITIONAL(M32R, test x$TARGET = xM32R) AM_CONDITIONAL(M68K, test x$TARGET = xM68K) AM_CONDITIONAL(POWERPC, test x$TARGET = xPOWERPC) AM_CONDITIONAL(POWERPC_AIX, test x$TARGET = xPOWERPC_AIX) AM_CONDITIONAL(POWERPC_DARWIN, test x$TARGET = xPOWERPC_DARWIN) AM_CONDITIONAL(POWERPC_FREEBSD, test x$TARGET = xPOWERPC_FREEBSD) AM_CONDITIONAL(ARM, test x$TARGET = xARM) AM_CONDITIONAL(AVR32, test x$TARGET = xAVR32) AM_CONDITIONAL(LIBFFI_CRIS, test x$TARGET = xLIBFFI_CRIS) AM_CONDITIONAL(FRV, test x$TARGET = xFRV) AM_CONDITIONAL(S390, test x$TARGET = xS390) AM_CONDITIONAL(X86_64, test x$TARGET = xX86_64) AM_CONDITIONAL(SH, test x$TARGET = xSH) AM_CONDITIONAL(SH64, test x$TARGET = xSH64) AM_CONDITIONAL(PA_LINUX, test x$TARGET = xPA_LINUX) AM_CONDITIONAL(PA_HPUX, test x$TARGET = xPA_HPUX) AM_CONDITIONAL(PA64_HPUX, test x$TARGET = xPA64_HPUX) AC_HEADER_STDC AC_CHECK_FUNCS(memcpy) AC_FUNC_ALLOCA AC_CHECK_SIZEOF(double) AC_CHECK_SIZEOF(long double) # Also AC_SUBST this variable for ffi.h. if test -z "$HAVE_LONG_DOUBLE"; then HAVE_LONG_DOUBLE=0 if test $ac_cv_sizeof_double != $ac_cv_sizeof_long_double; then if test $ac_cv_sizeof_long_double != 0; then HAVE_LONG_DOUBLE=1 AC_DEFINE(HAVE_LONG_DOUBLE, 1, [Define if you have the long double type and it is bigger than a double]) fi fi fi AC_SUBST(HAVE_LONG_DOUBLE) AC_C_BIGENDIAN AC_CACHE_CHECK([assembler .cfi pseudo-op support], libffi_cv_as_cfi_pseudo_op, [ libffi_cv_as_cfi_pseudo_op=unknown AC_TRY_COMPILE([asm (".cfi_startproc\n\t.cfi_endproc");],, [libffi_cv_as_cfi_pseudo_op=yes], [libffi_cv_as_cfi_pseudo_op=no]) ]) if test "x$libffi_cv_as_cfi_pseudo_op" = xyes; then AC_DEFINE(HAVE_AS_CFI_PSEUDO_OP, 1, [Define if your assembler supports .cfi_* directives.]) fi if test x$TARGET = xSPARC; then AC_CACHE_CHECK([assembler and linker support unaligned pc related relocs], libffi_cv_as_sparc_ua_pcrel, [ save_CFLAGS="$CFLAGS" save_LDFLAGS="$LDFLAGS" CFLAGS="$CFLAGS -fpic" LDFLAGS="$LDFLAGS -shared" AC_TRY_LINK([asm (".text; foo: nop; .data; .align 4; .byte 0; .uaword %r_disp32(foo); .text");],, [libffi_cv_as_sparc_ua_pcrel=yes], [libffi_cv_as_sparc_ua_pcrel=no]) CFLAGS="$save_CFLAGS" LDFLAGS="$save_LDFLAGS"]) if test "x$libffi_cv_as_sparc_ua_pcrel" = xyes; then AC_DEFINE(HAVE_AS_SPARC_UA_PCREL, 1, [Define if your assembler and linker support unaligned PC relative relocs.]) fi AC_CACHE_CHECK([assembler .register pseudo-op support], libffi_cv_as_register_pseudo_op, [ libffi_cv_as_register_pseudo_op=unknown # Check if we have .register AC_TRY_COMPILE([asm (".register %g2, #scratch");],, [libffi_cv_as_register_pseudo_op=yes], [libffi_cv_as_register_pseudo_op=no]) ]) if test "x$libffi_cv_as_register_pseudo_op" = xyes; then AC_DEFINE(HAVE_AS_REGISTER_PSEUDO_OP, 1, [Define if your assembler supports .register.]) fi fi if test x$TARGET = xX86 || test x$TARGET = xX86_WIN32 || test x$TARGET = xX86_64; then AC_CACHE_CHECK([assembler supports pc related relocs], libffi_cv_as_x86_pcrel, [ libffi_cv_as_x86_pcrel=yes echo '.text; foo: nop; .data; .long foo-.; .text' > conftest.s if $CC $CFLAGS -c conftest.s 2>&1 | $EGREP -i 'illegal|warning' > /dev/null; then libffi_cv_as_x86_pcrel=no fi ]) if test "x$libffi_cv_as_x86_pcrel" = xyes; then AC_DEFINE(HAVE_AS_X86_PCREL, 1, [Define if your assembler supports PC relative relocs.]) fi AC_CACHE_CHECK([assembler .ascii pseudo-op support], libffi_cv_as_ascii_pseudo_op, [ libffi_cv_as_ascii_pseudo_op=unknown # Check if we have .ascii AC_TRY_COMPILE([asm (".ascii \"string\"");],, [libffi_cv_as_ascii_pseudo_op=yes], [libffi_cv_as_ascii_pseudo_op=no]) ]) if test "x$libffi_cv_as_ascii_pseudo_op" = xyes; then AC_DEFINE(HAVE_AS_ASCII_PSEUDO_OP, 1, [Define if your assembler supports .ascii.]) fi AC_CACHE_CHECK([assembler .string pseudo-op support], libffi_cv_as_string_pseudo_op, [ libffi_cv_as_string_pseudo_op=unknown # Check if we have .string AC_TRY_COMPILE([asm (".string \"string\"");],, [libffi_cv_as_string_pseudo_op=yes], [libffi_cv_as_string_pseudo_op=no]) ]) if test "x$libffi_cv_as_string_pseudo_op" = xyes; then AC_DEFINE(HAVE_AS_STRING_PSEUDO_OP, 1, [Define if your assembler supports .string.]) fi fi case "$target" in *-apple-darwin10* | *-*-freebsd* | *-*-openbsd* | *-pc-solaris*) AC_DEFINE(FFI_MMAP_EXEC_WRIT, 1, [Cannot use malloc on this target, so, we revert to alternative means]) ;; esac if test x$TARGET = xX86_64; then AC_CACHE_CHECK([assembler supports unwind section type], libffi_cv_as_x86_64_unwind_section_type, [ libffi_cv_as_x86_64_unwind_section_type=yes echo '.section .eh_frame,"a",@unwind' > conftest.s if $CC $CFLAGS -c conftest.s 2>&1 | grep -i warning > /dev/null; then libffi_cv_as_x86_64_unwind_section_type=no fi ]) if test "x$libffi_cv_as_x86_64_unwind_section_type" = xyes; then AC_DEFINE(HAVE_AS_X86_64_UNWIND_SECTION_TYPE, 1, [Define if your assembler supports unwind section type.]) fi fi AC_CACHE_CHECK([whether .eh_frame section should be read-only], libffi_cv_ro_eh_frame, [ libffi_cv_ro_eh_frame=no echo 'extern void foo (void); void bar (void) { foo (); foo (); }' > conftest.c if $CC $CFLAGS -S -fpic -fexceptions -o conftest.s conftest.c > /dev/null 2>&1; then if grep '.section.*eh_frame.*"a"' conftest.s > /dev/null; then libffi_cv_ro_eh_frame=yes elif grep '.section.*eh_frame.*#alloc' conftest.c \ | grep -v '#write' > /dev/null; then libffi_cv_ro_eh_frame=yes fi fi rm -f conftest.* ]) if test "x$libffi_cv_ro_eh_frame" = xyes; then AC_DEFINE(HAVE_RO_EH_FRAME, 1, [Define if .eh_frame sections should be read-only.]) AC_DEFINE(EH_FRAME_FLAGS, "a", [Define to the flags needed for the .section .eh_frame directive.]) else AC_DEFINE(EH_FRAME_FLAGS, "aw", [Define to the flags needed for the .section .eh_frame directive.]) fi AC_CACHE_CHECK([for __attribute__((visibility("hidden")))], libffi_cv_hidden_visibility_attribute, [ echo 'int __attribute__ ((visibility ("hidden"))) foo (void) { return 1; }' > conftest.c libffi_cv_hidden_visibility_attribute=no if AC_TRY_COMMAND(${CC-cc} -Werror -S conftest.c -o conftest.s 1>&AS_MESSAGE_LOG_FD); then if grep '\.hidden.*foo' conftest.s >/dev/null; then libffi_cv_hidden_visibility_attribute=yes fi fi rm -f conftest.* ]) if test $libffi_cv_hidden_visibility_attribute = yes; then AC_DEFINE(HAVE_HIDDEN_VISIBILITY_ATTRIBUTE, 1, [Define if __attribute__((visibility("hidden"))) is supported.]) fi AH_BOTTOM([ #ifdef HAVE_HIDDEN_VISIBILITY_ATTRIBUTE #ifdef LIBFFI_ASM #define FFI_HIDDEN(name) .hidden name #else #define FFI_HIDDEN __attribute__ ((visibility ("hidden"))) #endif #else #ifdef LIBFFI_ASM #define FFI_HIDDEN(name) #else #define FFI_HIDDEN #endif #endif ]) AC_SUBST(TARGET) AC_SUBST(TARGETDIR) AC_SUBST(SHELL) AC_ARG_ENABLE(debug, [ --enable-debug debugging mode], if test "$enable_debug" = "yes"; then AC_DEFINE(FFI_DEBUG, 1, [Define this if you want extra debugging.]) fi) AC_ARG_ENABLE(structs, [ --disable-structs omit code for struct support], if test "$enable_structs" = "no"; then AC_DEFINE(FFI_NO_STRUCTS, 1, [Define this is you do not want support for aggregate types.]) fi) AC_ARG_ENABLE(raw-api, [ --disable-raw-api make the raw api unavailable], if test "$enable_raw_api" = "no"; then AC_DEFINE(FFI_NO_RAW_API, 1, [Define this is you do not want support for the raw API.]) fi) AC_ARG_ENABLE(purify-safety, [ --enable-purify-safety purify-safe mode], if test "$enable_purify_safety" = "yes"; then AC_DEFINE(USING_PURIFY, 1, [Define this if you are using Purify and want to suppress spurious messages.]) fi) AC_CONFIG_COMMANDS(include, [test -d include || mkdir include]) AC_CONFIG_COMMANDS(src, [ test -d src || mkdir src test -d src/$TARGETDIR || mkdir src/$TARGETDIR ], [TARGETDIR="$TARGETDIR"]) AC_CONFIG_LINKS(include/ffitarget.h:src/$TARGETDIR/ffitarget.h) AC_CONFIG_FILES(include/Makefile include/ffi.h Makefile) AC_OUTPUT smalltalk-3.2.5/libffi/README0000644000175000017500000002326512130343734012551 00000000000000This directory contains the libffi package, which is not part of GCC but shipped with GCC as convenience. Status ====== libffi-3.0.9 was released on December 31, 2009. Check the libffi web page for updates: . What is libffi? =============== Compilers for high level languages generate code that follow certain conventions. These conventions are necessary, in part, for separate compilation to work. One such convention is the "calling convention". The "calling convention" is essentially a set of assumptions made by the compiler about where function arguments will be found on entry to a function. A "calling convention" also specifies where the return value for a function is found. Some programs may not know at the time of compilation what arguments are to be passed to a function. For instance, an interpreter may be told at run-time about the number and types of arguments used to call a given function. Libffi can be used in such programs to provide a bridge from the interpreter program to compiled code. The libffi library provides a portable, high level programming interface to various calling conventions. This allows a programmer to call any function specified by a call interface description at run time. FFI stands for Foreign Function Interface. A foreign function interface is the popular name for the interface that allows code written in one language to call code written in another language. The libffi library really only provides the lowest, machine dependent layer of a fully featured foreign function interface. A layer must exist above libffi that handles type conversions for values passed between the two languages. Supported Platforms =================== Libffi has been ported to many different platforms. For specific configuration details and testing status, please refer to the wiki page here: http://www.moxielogic.org/wiki/index.php?title=Libffi_3.0.9 At the time of release, the following basic configurations have been tested: |--------------+------------------| | Architecture | Operating System | |--------------+------------------| | Alpha | Linux | | ARM | Linux | | AVR32 | Linux | | HPPA | HPUX | | IA-64 | Linux | | MIPS | IRIX | | MIPS | Linux | | MIPS64 | Linux | | PowerPC | Linux | | PowerPC | Mac OSX | | PowerPC | FreeBSD | | PowerPC64 | Linux | | S390 | Linux | | S390X | Linux | | SPARC | Linux | | SPARC | Solaris | | SPARC64 | Linux | | SPARC64 | FreeBSD | | X86 | FreeBSD | | X86 | kFreeBSD | | X86 | Linux | | X86 | Mac OSX | | X86 | OpenBSD | | X86 | OS/2 | | X86 | Solaris | | X86 | Windows/Cygwin | | X86 | Windows/MingW | | X86-64 | FreeBSD | | X86-64 | Linux | | X86-64 | OpenBSD | |--------------+------------------| Please send additional platform test results to libffi-discuss@sourceware.org and feel free to update the wiki page above. Installing libffi ================= First you must configure the distribution for your particular system. Go to the directory you wish to build libffi in and run the "configure" program found in the root directory of the libffi source distribution. You may want to tell configure where to install the libffi library and header files. To do that, use the --prefix configure switch. Libffi will install under /usr/local by default. If you want to enable extra run-time debugging checks use the the --enable-debug configure switch. This is useful when your program dies mysteriously while using libffi. Another useful configure switch is --enable-purify-safety. Using this will add some extra code which will suppress certain warnings when you are using Purify with libffi. Only use this switch when using Purify, as it will slow down the library. It's also possible to build libffi on Windows platforms with Microsoft's Visual C++ compiler. In this case, use the msvcc.sh wrapper script during configuration like so: path/to/configure --enable-shared --enable-static \ CC=path/to/msvcc.sh LD=link \ CPP=\"cl -nologo -EP\" Configure has many other options. Use "configure --help" to see them all. Once configure has finished, type "make". Note that you must be using GNU make. You can ftp GNU make from prep.ai.mit.edu:/pub/gnu. To ensure that libffi is working as advertised, type "make check". This will require that you have DejaGNU installed. To install the library and header files, type "make install". History ======= See the ChangeLog files for details. 3.0.10 ???-??-?? Fix the N64 build on mips-sgi-irix6.5. Testsuite fixes for Tru64 Unix. Enable builds with Microsoft's compiler. Enable x86 builds with Sun's compiler. 3.0.9 Dec-31-09 Add AVR32 and win64 ports. Add ARM softfp support. Many fixes for AIX, Solaris, HP-UX, *BSD. Several PowerPC and x86-64 bug fixes. Build DLL for windows. 3.0.8 Dec-19-08 Add *BSD, BeOS, and PA-Linux support. 3.0.7 Nov-11-08 Fix for ppc FreeBSD. (thanks to Andreas Tobler) 3.0.6 Jul-17-08 Fix for closures on sh. Mark the sh/sh64 stack as non-executable. (both thanks to Kaz Kojima) 3.0.5 Apr-3-08 Fix libffi.pc file. Fix #define ARM for IcedTea users. Fix x86 closure bug. 3.0.4 Feb-24-08 Fix x86 OpenBSD configury. 3.0.3 Feb-22-08 Enable x86 OpenBSD thanks to Thomas Heller, and x86-64 FreeBSD thanks to Björn König and Andreas Tobler. Clean up test instruction in README. 3.0.2 Feb-21-08 Improved x86 FreeBSD support. Thanks to Björn König. 3.0.1 Feb-15-08 Fix instruction cache flushing bug on MIPS. Thanks to David Daney. 3.0.0 Feb-15-08 Many changes, mostly thanks to the GCC project. Cygnus Solutions is now Red Hat. [10 years go by...] 1.20 Oct-5-98 Raffaele Sena produces ARM port. 1.19 Oct-5-98 Fixed x86 long double and long long return support. m68k bug fixes from Andreas Schwab. Patch for DU assembler compatibility for the Alpha from Richard Henderson. 1.18 Apr-17-98 Bug fixes and MIPS configuration changes. 1.17 Feb-24-98 Bug fixes and m68k port from Andreas Schwab. PowerPC port from Geoffrey Keating. Various bug x86, Sparc and MIPS bug fixes. 1.16 Feb-11-98 Richard Henderson produces Alpha port. 1.15 Dec-4-97 Fixed an n32 ABI bug. New libtool, auto* support. 1.14 May-13-97 libtool is now used to generate shared and static libraries. Fixed a minor portability problem reported by Russ McManus . 1.13 Dec-2-96 Added --enable-purify-safety to keep Purify from complaining about certain low level code. Sparc fix for calling functions with < 6 args. Linux x86 a.out fix. 1.12 Nov-22-96 Added missing ffi_type_void, needed for supporting void return types. Fixed test case for non MIPS machines. Cygnus Support is now Cygnus Solutions. 1.11 Oct-30-96 Added notes about GNU make. 1.10 Oct-29-96 Added configuration fix for non GNU compilers. 1.09 Oct-29-96 Added --enable-debug configure switch. Clean-ups based on LCLint feedback. ffi_mips.h is always installed. Many configuration fixes. Fixed ffitest.c for sparc builds. 1.08 Oct-15-96 Fixed n32 problem. Many clean-ups. 1.07 Oct-14-96 Gordon Irlam rewrites v8.S again. Bug fixes. 1.06 Oct-14-96 Gordon Irlam improved the sparc port. 1.05 Oct-14-96 Interface changes based on feedback. 1.04 Oct-11-96 Sparc port complete (modulo struct passing bug). 1.03 Oct-10-96 Passing struct args, and returning struct values works for all architectures/calling conventions. Expanded tests. 1.02 Oct-9-96 Added SGI n32 support. Fixed bugs in both o32 and Linux support. Added "make test". 1.01 Oct-8-96 Fixed float passing bug in mips version. Restructured some of the code. Builds cleanly with SGI tools. 1.00 Oct-7-96 First release. No public announcement. Authors & Credits ================= libffi was originally written by Anthony Green . The developers of the GNU Compiler Collection project have made innumerable valuable contributions. See the ChangeLog file for details. Some of the ideas behind libffi were inspired by Gianni Mariani's free gencall library for Silicon Graphics machines. The closure mechanism was designed and implemented by Kresten Krab Thorup. Major processor architecture ports were contributed by the following developers: alpha Richard Henderson arm Raffaele Sena cris Simon Posnjak, Hans-Peter Nilsson frv Anthony Green ia64 Hans Boehm m32r Kazuhiro Inaoka m68k Andreas Schwab mips Anthony Green, Casey Marshall mips64 David Daney pa Randolph Chung, Dave Anglin, Andreas Tobler powerpc Geoffrey Keating, Andreas Tobler, David Edelsohn, John Hornkvist powerpc64 Jakub Jelinek s390 Gerhard Tonn, Ulrich Weigand sh Kaz Kojima sh64 Kaz Kojima sparc Anthony Green, Gordon Irlam x86 Anthony Green, Jon Beniston x86-64 Bo Thorsen Jesper Skov and Andrew Haley both did more than their fair share of stepping through the code and tracking down bugs. Thanks also to Tom Tromey for bug fixes, documentation and configuration help. Thanks to Jim Blandy, who provided some useful feedback on the libffi interface. Andreas Tobler has done a tremendous amount of work on the testsuite. Alex Oliva solved the executable page problem for SElinux. The list above is almost certainly incomplete and inaccurate. I'm happy to make corrections or additions upon request. If you have a problem, or have found a bug, please send a note to green@redhat.com. smalltalk-3.2.5/libffi/LICENSE0000644000175000017500000000204412130343734012666 00000000000000libffi - Copyright (c) 1996-2003 Red Hat, Inc. Permission is hereby granted, free of charge, to any person obtaining a copy of this software and associated documentation files (the ``Software''), to deal in the Software without restriction, including without limitation the rights to use, copy, modify, merge, publish, distribute, sublicense, and/or sell copies of the Software, and to permit persons to whom the Software is furnished to do so, subject to the following conditions: The above copyright notice and this permission notice shall be included in all copies or substantial portions of the Software. THE SOFTWARE IS PROVIDED ``AS IS'', WITHOUT WARRANTY OF ANY KIND, EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL CYGNUS SOLUTIONS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. smalltalk-3.2.5/libffi/TODO0000644000175000017500000000002712130343734012350 00000000000000- Merge with GCC tree. smalltalk-3.2.5/libffi/src/0000755000175000017500000000000012130456004012523 500000000000000smalltalk-3.2.5/libffi/src/x86/0000755000175000017500000000000012130456004013150 500000000000000smalltalk-3.2.5/libffi/src/x86/win32.S0000644000175000017500000007015412130343734014172 00000000000000/* ----------------------------------------------------------------------- win32.S - Copyright (c) 1996, 1998, 2001, 2002, 2009 Red Hat, Inc. Copyright (c) 2001 John Beniton Copyright (c) 2002 Ranjit Mathew Copyright (c) 2009 Daniel Witte X86 Foreign Function Interface Permission is hereby granted, free of charge, to any person obtaining a copy of this software and associated documentation files (the ``Software''), to deal in the Software without restriction, including without limitation the rights to use, copy, modify, merge, publish, distribute, sublicense, and/or sell copies of the Software, and to permit persons to whom the Software is furnished to do so, subject to the following conditions: The above copyright notice and this permission notice shall be included in all copies or substantial portions of the Software. THE SOFTWARE IS PROVIDED ``AS IS'', WITHOUT WARRANTY OF ANY KIND, EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. ----------------------------------------------------------------------- */ #define LIBFFI_ASM #include #include #ifdef _MSC_VER .386 .MODEL FLAT, C EXTRN ffi_closure_SYSV_inner:NEAR _TEXT SEGMENT ffi_call_win32 PROC NEAR, ffi_prep_args : NEAR PTR DWORD, ecif : NEAR PTR DWORD, cif_bytes : DWORD, cif_flags : DWORD, rvalue : NEAR PTR DWORD, fn : NEAR PTR DWORD ;; Make room for all of the new args. mov ecx, cif_bytes sub esp, ecx mov eax, esp ;; Place all of the ffi_prep_args in position push ecif push eax call ffi_prep_args ;; Return stack to previous state and call the function add esp, 8 call fn ;; cdecl: we restore esp in the epilogue, so there's no need to ;; remove the space we pushed for the args. ;; stdcall: the callee has already cleaned the stack. ;; Load ecx with the return type code mov ecx, cif_flags ;; If the return value pointer is NULL, assume no return value. cmp rvalue, 0 jne ca_jumptable ;; Even if there is no space for the return value, we are ;; obliged to handle floating-point values. cmp ecx, FFI_TYPE_FLOAT jne ca_epilogue fstp st(0) jmp ca_epilogue ca_jumptable: jmp [ca_jumpdata + 4 * ecx] ca_jumpdata: ;; Do not insert anything here between label and jump table. dd offset ca_epilogue ;; FFI_TYPE_VOID dd offset ca_retint ;; FFI_TYPE_INT dd offset ca_retfloat ;; FFI_TYPE_FLOAT dd offset ca_retdouble ;; FFI_TYPE_DOUBLE dd offset ca_retlongdouble ;; FFI_TYPE_LONGDOUBLE dd offset ca_retint8 ;; FFI_TYPE_UINT8 dd offset ca_retint8 ;; FFI_TYPE_SINT8 dd offset ca_retint16 ;; FFI_TYPE_UINT16 dd offset ca_retint16 ;; FFI_TYPE_SINT16 dd offset ca_retint ;; FFI_TYPE_UINT32 dd offset ca_retint ;; FFI_TYPE_SINT32 dd offset ca_retint64 ;; FFI_TYPE_UINT64 dd offset ca_retint64 ;; FFI_TYPE_SINT64 dd offset ca_epilogue ;; FFI_TYPE_STRUCT dd offset ca_retint ;; FFI_TYPE_POINTER dd offset ca_retint8 ;; FFI_TYPE_SMALL_STRUCT_1B dd offset ca_retint16 ;; FFI_TYPE_SMALL_STRUCT_2B dd offset ca_retint ;; FFI_TYPE_SMALL_STRUCT_4B ca_retint8: ;; Load %ecx with the pointer to storage for the return value mov ecx, rvalue mov [ecx + 0], al jmp ca_epilogue ca_retint16: ;; Load %ecx with the pointer to storage for the return value mov ecx, rvalue mov [ecx + 0], ax jmp ca_epilogue ca_retint: ;; Load %ecx with the pointer to storage for the return value mov ecx, rvalue mov [ecx + 0], eax jmp ca_epilogue ca_retint64: ;; Load %ecx with the pointer to storage for the return value mov ecx, rvalue mov [ecx + 0], eax mov [ecx + 4], edx jmp ca_epilogue ca_retfloat: ;; Load %ecx with the pointer to storage for the return value mov ecx, rvalue fstp DWORD PTR [ecx] jmp ca_epilogue ca_retdouble: ;; Load %ecx with the pointer to storage for the return value mov ecx, rvalue fstp QWORD PTR [ecx] jmp ca_epilogue ca_retlongdouble: ;; Load %ecx with the pointer to storage for the return value mov ecx, rvalue fstp TBYTE PTR [ecx] jmp ca_epilogue ca_epilogue: ;; Epilogue code is autogenerated. ret ffi_call_win32 ENDP ffi_closure_SYSV PROC NEAR FORCEFRAME ;; the ffi_closure ctx is passed in eax by the trampoline. sub esp, 40 lea edx, [ebp - 24] mov [ebp - 12], edx ;; resp lea edx, [ebp + 8] mov [esp + 8], edx ;; args lea edx, [ebp - 12] mov [esp + 4], edx ;; &resp mov [esp], eax ;; closure call ffi_closure_SYSV_inner mov ecx, [ebp - 12] cs_jumptable: jmp [cs_jumpdata + 4 * eax] cs_jumpdata: ;; Do not insert anything here between the label and jump table. dd offset cs_epilogue ;; FFI_TYPE_VOID dd offset cs_retint ;; FFI_TYPE_INT dd offset cs_retfloat ;; FFI_TYPE_FLOAT dd offset cs_retdouble ;; FFI_TYPE_DOUBLE dd offset cs_retlongdouble ;; FFI_TYPE_LONGDOUBLE dd offset cs_retint8 ;; FFI_TYPE_UINT8 dd offset cs_retint8 ;; FFI_TYPE_SINT8 dd offset cs_retint16 ;; FFI_TYPE_UINT16 dd offset cs_retint16 ;; FFI_TYPE_SINT16 dd offset cs_retint ;; FFI_TYPE_UINT32 dd offset cs_retint ;; FFI_TYPE_SINT32 dd offset cs_retint64 ;; FFI_TYPE_UINT64 dd offset cs_retint64 ;; FFI_TYPE_SINT64 dd offset cs_retstruct ;; FFI_TYPE_STRUCT dd offset cs_retint ;; FFI_TYPE_POINTER dd offset cs_retint8 ;; FFI_TYPE_SMALL_STRUCT_1B dd offset cs_retint16 ;; FFI_TYPE_SMALL_STRUCT_2B dd offset cs_retint ;; FFI_TYPE_SMALL_STRUCT_4B cs_retint8: mov al, [ecx] jmp cs_epilogue cs_retint16: mov ax, [ecx] jmp cs_epilogue cs_retint: mov eax, [ecx] jmp cs_epilogue cs_retint64: mov eax, [ecx + 0] mov edx, [ecx + 4] jmp cs_epilogue cs_retfloat: fld DWORD PTR [ecx] jmp cs_epilogue cs_retdouble: fld QWORD PTR [ecx] jmp cs_epilogue cs_retlongdouble: fld TBYTE PTR [ecx] jmp cs_epilogue cs_retstruct: ;; Caller expects us to pop struct return value pointer hidden arg. ;; Epilogue code is autogenerated. ret 4 cs_epilogue: ;; Epilogue code is autogenerated. ret ffi_closure_SYSV ENDP #if !FFI_NO_RAW_API #define RAW_CLOSURE_CIF_OFFSET ((FFI_TRAMPOLINE_SIZE + 3) AND NOT 3) #define RAW_CLOSURE_FUN_OFFSET (RAW_CLOSURE_CIF_OFFSET + 4) #define RAW_CLOSURE_USER_DATA_OFFSET (RAW_CLOSURE_FUN_OFFSET + 4) #define CIF_FLAGS_OFFSET 20 ffi_closure_raw_SYSV PROC NEAR USES esi ;; the ffi_closure ctx is passed in eax by the trampoline. sub esp, 40 mov esi, [eax + RAW_CLOSURE_CIF_OFFSET] ;; closure->cif mov edx, [eax + RAW_CLOSURE_USER_DATA_OFFSET] ;; closure->user_data mov [esp + 12], edx ;; user_data lea edx, [ebp + 8] mov [esp + 8], edx ;; raw_args lea edx, [ebp - 24] mov [esp + 4], edx ;; &res mov [esp], esi ;; cif call DWORD PTR [eax + RAW_CLOSURE_FUN_OFFSET] ;; closure->fun mov eax, [esi + CIF_FLAGS_OFFSET] ;; cif->flags lea ecx, [ebp - 24] cr_jumptable: jmp [cr_jumpdata + 4 * eax] cr_jumpdata: ;; Do not insert anything here between the label and jump table. dd offset cr_epilogue ;; FFI_TYPE_VOID dd offset cr_retint ;; FFI_TYPE_INT dd offset cr_retfloat ;; FFI_TYPE_FLOAT dd offset cr_retdouble ;; FFI_TYPE_DOUBLE dd offset cr_retlongdouble ;; FFI_TYPE_LONGDOUBLE dd offset cr_retint8 ;; FFI_TYPE_UINT8 dd offset cr_retint8 ;; FFI_TYPE_SINT8 dd offset cr_retint16 ;; FFI_TYPE_UINT16 dd offset cr_retint16 ;; FFI_TYPE_SINT16 dd offset cr_retint ;; FFI_TYPE_UINT32 dd offset cr_retint ;; FFI_TYPE_SINT32 dd offset cr_retint64 ;; FFI_TYPE_UINT64 dd offset cr_retint64 ;; FFI_TYPE_SINT64 dd offset cr_epilogue ;; FFI_TYPE_STRUCT dd offset cr_retint ;; FFI_TYPE_POINTER dd offset cr_retint8 ;; FFI_TYPE_SMALL_STRUCT_1B dd offset cr_retint16 ;; FFI_TYPE_SMALL_STRUCT_2B dd offset cr_retint ;; FFI_TYPE_SMALL_STRUCT_4B cr_retint8: mov al, [ecx] jmp cr_epilogue cr_retint16: mov ax, [ecx] jmp cr_epilogue cr_retint: mov eax, [ecx] jmp cr_epilogue cr_retint64: mov eax, [ecx + 0] mov edx, [ecx + 4] jmp cr_epilogue cr_retfloat: fld DWORD PTR [ecx] jmp cr_epilogue cr_retdouble: fld QWORD PTR [ecx] jmp cr_epilogue cr_retlongdouble: fld TBYTE PTR [ecx] jmp cr_epilogue cr_epilogue: ;; Epilogue code is autogenerated. ret ffi_closure_raw_SYSV ENDP #endif /* !FFI_NO_RAW_API */ ffi_closure_STDCALL PROC NEAR FORCEFRAME ;; the ffi_closure ctx is passed in eax by the trampoline. sub esp, 40 lea edx, [ebp - 24] mov [ebp - 12], edx ;; resp lea edx, [ebp + 12] ;; account for stub return address on stack mov [esp + 8], edx ;; args lea edx, [ebp - 12] mov [esp + 4], edx ;; &resp mov [esp], eax ;; closure call ffi_closure_SYSV_inner mov ecx, [ebp - 12] cd_jumptable: jmp [cd_jumpdata + 4 * eax] cd_jumpdata: ;; Do not insert anything here between the label and jump table. dd offset cd_epilogue ;; FFI_TYPE_VOID dd offset cd_retint ;; FFI_TYPE_INT dd offset cd_retfloat ;; FFI_TYPE_FLOAT dd offset cd_retdouble ;; FFI_TYPE_DOUBLE dd offset cd_retlongdouble ;; FFI_TYPE_LONGDOUBLE dd offset cd_retint8 ;; FFI_TYPE_UINT8 dd offset cd_retint8 ;; FFI_TYPE_SINT8 dd offset cd_retint16 ;; FFI_TYPE_UINT16 dd offset cd_retint16 ;; FFI_TYPE_SINT16 dd offset cd_retint ;; FFI_TYPE_UINT32 dd offset cd_retint ;; FFI_TYPE_SINT32 dd offset cd_retint64 ;; FFI_TYPE_UINT64 dd offset cd_retint64 ;; FFI_TYPE_SINT64 dd offset cd_epilogue ;; FFI_TYPE_STRUCT dd offset cd_retint ;; FFI_TYPE_POINTER dd offset cd_retint8 ;; FFI_TYPE_SMALL_STRUCT_1B dd offset cd_retint16 ;; FFI_TYPE_SMALL_STRUCT_2B dd offset cd_retint ;; FFI_TYPE_SMALL_STRUCT_4B cd_retint8: mov al, [ecx] jmp cd_epilogue cd_retint16: mov ax, [ecx] jmp cd_epilogue cd_retint: mov eax, [ecx] jmp cd_epilogue cd_retint64: mov eax, [ecx + 0] mov edx, [ecx + 4] jmp cd_epilogue cd_retfloat: fld DWORD PTR [ecx] jmp cd_epilogue cd_retdouble: fld QWORD PTR [ecx] jmp cd_epilogue cd_retlongdouble: fld TBYTE PTR [ecx] jmp cd_epilogue cd_epilogue: ;; Epilogue code is autogenerated. ret ffi_closure_STDCALL ENDP _TEXT ENDS END #else .text # This assumes we are using gas. .balign 16 .globl _ffi_call_win32 #ifndef __OS2__ .def _ffi_call_win32; .scl 2; .type 32; .endef #endif _ffi_call_win32: .LFB1: pushl %ebp .LCFI0: movl %esp,%ebp .LCFI1: # Make room for all of the new args. movl 16(%ebp),%ecx subl %ecx,%esp movl %esp,%eax # Place all of the ffi_prep_args in position pushl 12(%ebp) pushl %eax call *8(%ebp) # Return stack to previous state and call the function addl $8,%esp # FIXME: Align the stack to a 128-bit boundary to avoid # potential performance hits. call *28(%ebp) # stdcall functions pop arguments off the stack themselves # Load %ecx with the return type code movl 20(%ebp),%ecx # If the return value pointer is NULL, assume no return value. cmpl $0,24(%ebp) jne 0f # Even if there is no space for the return value, we are # obliged to handle floating-point values. cmpl $FFI_TYPE_FLOAT,%ecx jne .Lnoretval fstp %st(0) jmp .Lepilogue 0: call 1f # Do not insert anything here between the call and the jump table. .Lstore_table: .long .Lnoretval /* FFI_TYPE_VOID */ .long .Lretint /* FFI_TYPE_INT */ .long .Lretfloat /* FFI_TYPE_FLOAT */ .long .Lretdouble /* FFI_TYPE_DOUBLE */ .long .Lretlongdouble /* FFI_TYPE_LONGDOUBLE */ .long .Lretuint8 /* FFI_TYPE_UINT8 */ .long .Lretsint8 /* FFI_TYPE_SINT8 */ .long .Lretuint16 /* FFI_TYPE_UINT16 */ .long .Lretsint16 /* FFI_TYPE_SINT16 */ .long .Lretint /* FFI_TYPE_UINT32 */ .long .Lretint /* FFI_TYPE_SINT32 */ .long .Lretint64 /* FFI_TYPE_UINT64 */ .long .Lretint64 /* FFI_TYPE_SINT64 */ .long .Lretstruct /* FFI_TYPE_STRUCT */ .long .Lretint /* FFI_TYPE_POINTER */ .long .Lretstruct1b /* FFI_TYPE_SMALL_STRUCT_1B */ .long .Lretstruct2b /* FFI_TYPE_SMALL_STRUCT_2B */ .long .Lretstruct4b /* FFI_TYPE_SMALL_STRUCT_4B */ 1: add %ecx, %ecx add %ecx, %ecx add (%esp),%ecx add $4, %esp jmp *(%ecx) /* Sign/zero extend as appropriate. */ .Lretsint8: movsbl %al, %eax jmp .Lretint .Lretsint16: movswl %ax, %eax jmp .Lretint .Lretuint8: movzbl %al, %eax jmp .Lretint .Lretuint16: movzwl %ax, %eax jmp .Lretint .Lretint: # Load %ecx with the pointer to storage for the return value movl 24(%ebp),%ecx movl %eax,0(%ecx) jmp .Lepilogue .Lretfloat: # Load %ecx with the pointer to storage for the return value movl 24(%ebp),%ecx fstps (%ecx) jmp .Lepilogue .Lretdouble: # Load %ecx with the pointer to storage for the return value movl 24(%ebp),%ecx fstpl (%ecx) jmp .Lepilogue .Lretlongdouble: # Load %ecx with the pointer to storage for the return value movl 24(%ebp),%ecx fstpt (%ecx) jmp .Lepilogue .Lretint64: # Load %ecx with the pointer to storage for the return value movl 24(%ebp),%ecx movl %eax,0(%ecx) movl %edx,4(%ecx) jmp .Lepilogue .Lretstruct1b: # Load %ecx with the pointer to storage for the return value movl 24(%ebp),%ecx movb %al,0(%ecx) jmp .Lepilogue .Lretstruct2b: # Load %ecx with the pointer to storage for the return value movl 24(%ebp),%ecx movw %ax,0(%ecx) jmp .Lepilogue .Lretstruct4b: # Load %ecx with the pointer to storage for the return value movl 24(%ebp),%ecx movl %eax,0(%ecx) jmp .Lepilogue .Lretstruct: # Nothing to do! .Lnoretval: .Lepilogue: movl %ebp,%esp popl %ebp ret .ffi_call_win32_end: .LFE1: # This assumes we are using gas. .balign 16 .globl _ffi_closure_SYSV #ifndef __OS2__ .def _ffi_closure_SYSV; .scl 2; .type 32; .endef #endif _ffi_closure_SYSV: .LFB3: pushl %ebp .LCFI4: movl %esp, %ebp .LCFI5: subl $40, %esp leal -24(%ebp), %edx movl %edx, -12(%ebp) /* resp */ leal 8(%ebp), %edx movl %edx, 4(%esp) /* args = __builtin_dwarf_cfa () */ leal -12(%ebp), %edx movl %edx, (%esp) /* &resp */ call _ffi_closure_SYSV_inner movl -12(%ebp), %ecx 0: call 1f # Do not insert anything here between the call and the jump table. .Lcls_store_table: .long .Lcls_noretval /* FFI_TYPE_VOID */ .long .Lcls_retint /* FFI_TYPE_INT */ .long .Lcls_retfloat /* FFI_TYPE_FLOAT */ .long .Lcls_retdouble /* FFI_TYPE_DOUBLE */ .long .Lcls_retldouble /* FFI_TYPE_LONGDOUBLE */ .long .Lcls_retuint8 /* FFI_TYPE_UINT8 */ .long .Lcls_retsint8 /* FFI_TYPE_SINT8 */ .long .Lcls_retuint16 /* FFI_TYPE_UINT16 */ .long .Lcls_retsint16 /* FFI_TYPE_SINT16 */ .long .Lcls_retint /* FFI_TYPE_UINT32 */ .long .Lcls_retint /* FFI_TYPE_SINT32 */ .long .Lcls_retllong /* FFI_TYPE_UINT64 */ .long .Lcls_retllong /* FFI_TYPE_SINT64 */ .long .Lcls_retstruct /* FFI_TYPE_STRUCT */ .long .Lcls_retint /* FFI_TYPE_POINTER */ .long .Lcls_retstruct1 /* FFI_TYPE_SMALL_STRUCT_1B */ .long .Lcls_retstruct2 /* FFI_TYPE_SMALL_STRUCT_2B */ .long .Lcls_retstruct4 /* FFI_TYPE_SMALL_STRUCT_4B */ 1: add %eax, %eax add %eax, %eax add (%esp),%eax add $4, %esp jmp *(%eax) /* Sign/zero extend as appropriate. */ .Lcls_retsint8: movsbl (%ecx), %eax jmp .Lcls_epilogue .Lcls_retsint16: movswl (%ecx), %eax jmp .Lcls_epilogue .Lcls_retuint8: movzbl (%ecx), %eax jmp .Lcls_epilogue .Lcls_retuint16: movzwl (%ecx), %eax jmp .Lcls_epilogue .Lcls_retint: movl (%ecx), %eax jmp .Lcls_epilogue .Lcls_retfloat: flds (%ecx) jmp .Lcls_epilogue .Lcls_retdouble: fldl (%ecx) jmp .Lcls_epilogue .Lcls_retldouble: fldt (%ecx) jmp .Lcls_epilogue .Lcls_retllong: movl (%ecx), %eax movl 4(%ecx), %edx jmp .Lcls_epilogue .Lcls_retstruct1: movsbl (%ecx), %eax jmp .Lcls_epilogue .Lcls_retstruct2: movswl (%ecx), %eax jmp .Lcls_epilogue .Lcls_retstruct4: movl (%ecx), %eax jmp .Lcls_epilogue .Lcls_retstruct: # Caller expects us to pop struct return value pointer hidden arg. movl %ebp, %esp popl %ebp ret $0x4 .Lcls_noretval: .Lcls_epilogue: movl %ebp, %esp popl %ebp ret .ffi_closure_SYSV_end: .LFE3: #if !FFI_NO_RAW_API #define RAW_CLOSURE_CIF_OFFSET ((FFI_TRAMPOLINE_SIZE + 3) & ~3) #define RAW_CLOSURE_FUN_OFFSET (RAW_CLOSURE_CIF_OFFSET + 4) #define RAW_CLOSURE_USER_DATA_OFFSET (RAW_CLOSURE_FUN_OFFSET + 4) #define CIF_FLAGS_OFFSET 20 # This assumes we are using gas. .balign 16 .globl _ffi_closure_raw_SYSV #ifndef __OS2__ .def _ffi_closure_raw_SYSV; .scl 2; .type 32; .endef #endif _ffi_closure_raw_SYSV: .LFB4: pushl %ebp .LCFI6: movl %esp, %ebp .LCFI7: pushl %esi .LCFI8: subl $36, %esp movl RAW_CLOSURE_CIF_OFFSET(%eax), %esi /* closure->cif */ movl RAW_CLOSURE_USER_DATA_OFFSET(%eax), %edx /* closure->user_data */ movl %edx, 12(%esp) /* user_data */ leal 8(%ebp), %edx /* __builtin_dwarf_cfa () */ movl %edx, 8(%esp) /* raw_args */ leal -24(%ebp), %edx movl %edx, 4(%esp) /* &res */ movl %esi, (%esp) /* cif */ call *RAW_CLOSURE_FUN_OFFSET(%eax) /* closure->fun */ movl CIF_FLAGS_OFFSET(%esi), %eax /* rtype */ 0: call 1f # Do not insert anything here between the call and the jump table. .Lrcls_store_table: .long .Lrcls_noretval /* FFI_TYPE_VOID */ .long .Lrcls_retint /* FFI_TYPE_INT */ .long .Lrcls_retfloat /* FFI_TYPE_FLOAT */ .long .Lrcls_retdouble /* FFI_TYPE_DOUBLE */ .long .Lrcls_retldouble /* FFI_TYPE_LONGDOUBLE */ .long .Lrcls_retuint8 /* FFI_TYPE_UINT8 */ .long .Lrcls_retsint8 /* FFI_TYPE_SINT8 */ .long .Lrcls_retuint16 /* FFI_TYPE_UINT16 */ .long .Lrcls_retsint16 /* FFI_TYPE_SINT16 */ .long .Lrcls_retint /* FFI_TYPE_UINT32 */ .long .Lrcls_retint /* FFI_TYPE_SINT32 */ .long .Lrcls_retllong /* FFI_TYPE_UINT64 */ .long .Lrcls_retllong /* FFI_TYPE_SINT64 */ .long .Lrcls_retstruct /* FFI_TYPE_STRUCT */ .long .Lrcls_retint /* FFI_TYPE_POINTER */ .long .Lrcls_retstruct1 /* FFI_TYPE_SMALL_STRUCT_1B */ .long .Lrcls_retstruct2 /* FFI_TYPE_SMALL_STRUCT_2B */ .long .Lrcls_retstruct4 /* FFI_TYPE_SMALL_STRUCT_4B */ 1: add %eax, %eax add %eax, %eax add (%esp),%eax add $4, %esp jmp *(%eax) /* Sign/zero extend as appropriate. */ .Lrcls_retsint8: movsbl -24(%ebp), %eax jmp .Lrcls_epilogue .Lrcls_retsint16: movswl -24(%ebp), %eax jmp .Lrcls_epilogue .Lrcls_retuint8: movzbl -24(%ebp), %eax jmp .Lrcls_epilogue .Lrcls_retuint16: movzwl -24(%ebp), %eax jmp .Lrcls_epilogue .Lrcls_retint: movl -24(%ebp), %eax jmp .Lrcls_epilogue .Lrcls_retfloat: flds -24(%ebp) jmp .Lrcls_epilogue .Lrcls_retdouble: fldl -24(%ebp) jmp .Lrcls_epilogue .Lrcls_retldouble: fldt -24(%ebp) jmp .Lrcls_epilogue .Lrcls_retllong: movl -24(%ebp), %eax movl -20(%ebp), %edx jmp .Lrcls_epilogue .Lrcls_retstruct1: movsbl -24(%ebp), %eax jmp .Lrcls_epilogue .Lrcls_retstruct2: movswl -24(%ebp), %eax jmp .Lrcls_epilogue .Lrcls_retstruct4: movl -24(%ebp), %eax jmp .Lrcls_epilogue .Lrcls_retstruct: # Nothing to do! .Lrcls_noretval: .Lrcls_epilogue: addl $36, %esp popl %esi popl %ebp ret .ffi_closure_raw_SYSV_end: .LFE4: #endif /* !FFI_NO_RAW_API */ # This assumes we are using gas. .balign 16 .globl _ffi_closure_STDCALL #ifndef __OS2__ .def _ffi_closure_STDCALL; .scl 2; .type 32; .endef #endif _ffi_closure_STDCALL: .LFB5: pushl %ebp .LCFI9: movl %esp, %ebp .LCFI10: subl $40, %esp leal -24(%ebp), %edx movl %edx, -12(%ebp) /* resp */ leal 12(%ebp), %edx /* account for stub return address on stack */ movl %edx, 4(%esp) /* args */ leal -12(%ebp), %edx movl %edx, (%esp) /* &resp */ call _ffi_closure_SYSV_inner movl -12(%ebp), %ecx 0: call 1f # Do not insert anything here between the call and the jump table. .Lscls_store_table: .long .Lscls_noretval /* FFI_TYPE_VOID */ .long .Lscls_retint /* FFI_TYPE_INT */ .long .Lscls_retfloat /* FFI_TYPE_FLOAT */ .long .Lscls_retdouble /* FFI_TYPE_DOUBLE */ .long .Lscls_retldouble /* FFI_TYPE_LONGDOUBLE */ .long .Lscls_retuint8 /* FFI_TYPE_UINT8 */ .long .Lscls_retsint8 /* FFI_TYPE_SINT8 */ .long .Lscls_retuint16 /* FFI_TYPE_UINT16 */ .long .Lscls_retsint16 /* FFI_TYPE_SINT16 */ .long .Lscls_retint /* FFI_TYPE_UINT32 */ .long .Lscls_retint /* FFI_TYPE_SINT32 */ .long .Lscls_retllong /* FFI_TYPE_UINT64 */ .long .Lscls_retllong /* FFI_TYPE_SINT64 */ .long .Lscls_retstruct /* FFI_TYPE_STRUCT */ .long .Lscls_retint /* FFI_TYPE_POINTER */ .long .Lscls_retstruct1 /* FFI_TYPE_SMALL_STRUCT_1B */ .long .Lscls_retstruct2 /* FFI_TYPE_SMALL_STRUCT_2B */ .long .Lscls_retstruct4 /* FFI_TYPE_SMALL_STRUCT_4B */ 1: add %eax, %eax add %eax, %eax add (%esp),%eax add $4, %esp jmp *(%eax) /* Sign/zero extend as appropriate. */ .Lscls_retsint8: movsbl (%ecx), %eax jmp .Lscls_epilogue .Lscls_retsint16: movswl (%ecx), %eax jmp .Lscls_epilogue .Lscls_retuint8: movzbl (%ecx), %eax jmp .Lscls_epilogue .Lscls_retuint16: movzwl (%ecx), %eax jmp .Lscls_epilogue .Lscls_retint: movl (%ecx), %eax jmp .Lscls_epilogue .Lscls_retfloat: flds (%ecx) jmp .Lscls_epilogue .Lscls_retdouble: fldl (%ecx) jmp .Lscls_epilogue .Lscls_retldouble: fldt (%ecx) jmp .Lscls_epilogue .Lscls_retllong: movl (%ecx), %eax movl 4(%ecx), %edx jmp .Lscls_epilogue .Lscls_retstruct1: movsbl (%ecx), %eax jmp .Lscls_epilogue .Lscls_retstruct2: movswl (%ecx), %eax jmp .Lscls_epilogue .Lscls_retstruct4: movl (%ecx), %eax jmp .Lscls_epilogue .Lscls_retstruct: # Nothing to do! .Lscls_noretval: .Lscls_epilogue: movl %ebp, %esp popl %ebp ret .ffi_closure_STDCALL_end: .LFE5: #ifndef __OS2__ .section .eh_frame,"w" #endif .Lframe1: .LSCIE1: .long .LECIE1-.LASCIE1 /* Length of Common Information Entry */ .LASCIE1: .long 0x0 /* CIE Identifier Tag */ .byte 0x1 /* CIE Version */ #ifdef __PIC__ .ascii "zR\0" /* CIE Augmentation */ #else .ascii "\0" /* CIE Augmentation */ #endif .byte 0x1 /* .uleb128 0x1; CIE Code Alignment Factor */ .byte 0x7c /* .sleb128 -4; CIE Data Alignment Factor */ .byte 0x8 /* CIE RA Column */ #ifdef __PIC__ .byte 0x1 /* .uleb128 0x1; Augmentation size */ .byte 0x1b /* FDE Encoding (pcrel sdata4) */ #endif .byte 0xc /* DW_CFA_def_cfa CFA = r4 + 4 = 4(%esp) */ .byte 0x4 /* .uleb128 0x4 */ .byte 0x4 /* .uleb128 0x4 */ .byte 0x88 /* DW_CFA_offset, column 0x8 %eip at CFA + 1 * -4 */ .byte 0x1 /* .uleb128 0x1 */ .align 4 .LECIE1: .LSFDE1: .long .LEFDE1-.LASFDE1 /* FDE Length */ .LASFDE1: .long .LASFDE1-.Lframe1 /* FDE CIE offset */ #if defined __PIC__ && defined HAVE_AS_X86_PCREL .long .LFB1-. /* FDE initial location */ #else .long .LFB1 #endif .long .LFE1-.LFB1 /* FDE address range */ #ifdef __PIC__ .byte 0x0 /* .uleb128 0x0; Augmentation size */ #endif /* DW_CFA_xxx CFI instructions go here. */ .byte 0x4 /* DW_CFA_advance_loc4 */ .long .LCFI0-.LFB1 .byte 0xe /* DW_CFA_def_cfa_offset CFA = r4 + 8 = 8(%esp) */ .byte 0x8 /* .uleb128 0x8 */ .byte 0x85 /* DW_CFA_offset, column 0x5 %ebp at CFA + 2 * -4 */ .byte 0x2 /* .uleb128 0x2 */ .byte 0x4 /* DW_CFA_advance_loc4 */ .long .LCFI1-.LCFI0 .byte 0xd /* DW_CFA_def_cfa_register CFA = r5 = %ebp */ .byte 0x5 /* .uleb128 0x5 */ /* End of DW_CFA_xxx CFI instructions. */ .align 4 .LEFDE1: .LSFDE3: .long .LEFDE3-.LASFDE3 /* FDE Length */ .LASFDE3: .long .LASFDE3-.Lframe1 /* FDE CIE offset */ #if defined __PIC__ && defined HAVE_AS_X86_PCREL .long .LFB3-. /* FDE initial location */ #else .long .LFB3 #endif .long .LFE3-.LFB3 /* FDE address range */ #ifdef __PIC__ .byte 0x0 /* .uleb128 0x0; Augmentation size */ #endif /* DW_CFA_xxx CFI instructions go here. */ .byte 0x4 /* DW_CFA_advance_loc4 */ .long .LCFI4-.LFB3 .byte 0xe /* DW_CFA_def_cfa_offset CFA = r4 + 8 = 8(%esp) */ .byte 0x8 /* .uleb128 0x8 */ .byte 0x85 /* DW_CFA_offset, column 0x5 %ebp at CFA + 2 * -4 */ .byte 0x2 /* .uleb128 0x2 */ .byte 0x4 /* DW_CFA_advance_loc4 */ .long .LCFI5-.LCFI4 .byte 0xd /* DW_CFA_def_cfa_register CFA = r5 = %ebp */ .byte 0x5 /* .uleb128 0x5 */ /* End of DW_CFA_xxx CFI instructions. */ .align 4 .LEFDE3: #if !FFI_NO_RAW_API .LSFDE4: .long .LEFDE4-.LASFDE4 /* FDE Length */ .LASFDE4: .long .LASFDE4-.Lframe1 /* FDE CIE offset */ #if defined __PIC__ && defined HAVE_AS_X86_PCREL .long .LFB4-. /* FDE initial location */ #else .long .LFB4 #endif .long .LFE4-.LFB4 /* FDE address range */ #ifdef __PIC__ .byte 0x0 /* .uleb128 0x0; Augmentation size */ #endif /* DW_CFA_xxx CFI instructions go here. */ .byte 0x4 /* DW_CFA_advance_loc4 */ .long .LCFI6-.LFB4 .byte 0xe /* DW_CFA_def_cfa_offset CFA = r4 + 8 = 8(%esp) */ .byte 0x8 /* .uleb128 0x8 */ .byte 0x85 /* DW_CFA_offset, column 0x5 %ebp at CFA + 2 * -4 */ .byte 0x2 /* .uleb128 0x2 */ .byte 0x4 /* DW_CFA_advance_loc4 */ .long .LCFI7-.LCFI6 .byte 0xd /* DW_CFA_def_cfa_register CFA = r5 = %ebp */ .byte 0x5 /* .uleb128 0x5 */ .byte 0x4 /* DW_CFA_advance_loc4 */ .long .LCFI8-.LCFI7 .byte 0x86 /* DW_CFA_offset, column 0x6 %esi at CFA + 3 * -4 */ .byte 0x3 /* .uleb128 0x3 */ /* End of DW_CFA_xxx CFI instructions. */ .align 4 .LEFDE4: #endif /* !FFI_NO_RAW_API */ .LSFDE5: .long .LEFDE5-.LASFDE5 /* FDE Length */ .LASFDE5: .long .LASFDE5-.Lframe1 /* FDE CIE offset */ #if defined __PIC__ && defined HAVE_AS_X86_PCREL .long .LFB5-. /* FDE initial location */ #else .long .LFB5 #endif .long .LFE5-.LFB5 /* FDE address range */ #ifdef __PIC__ .byte 0x0 /* .uleb128 0x0; Augmentation size */ #endif /* DW_CFA_xxx CFI instructions go here. */ .byte 0x4 /* DW_CFA_advance_loc4 */ .long .LCFI9-.LFB5 .byte 0xe /* DW_CFA_def_cfa_offset CFA = r4 + 8 = 8(%esp) */ .byte 0x8 /* .uleb128 0x8 */ .byte 0x85 /* DW_CFA_offset, column 0x5 %ebp at CFA + 2 * -4 */ .byte 0x2 /* .uleb128 0x2 */ .byte 0x4 /* DW_CFA_advance_loc4 */ .long .LCFI10-.LCFI9 .byte 0xd /* DW_CFA_def_cfa_register CFA = r5 = %ebp */ .byte 0x5 /* .uleb128 0x5 */ /* End of DW_CFA_xxx CFI instructions. */ .align 4 .LEFDE5: #endif /* !_MSC_VER */ smalltalk-3.2.5/libffi/src/x86/ffi64.c0000644000175000017500000004170012130343734014161 00000000000000/* ----------------------------------------------------------------------- ffi64.c - Copyright (c) 2002, 2007 Bo Thorsen Copyright (c) 2008 Red Hat, Inc. x86-64 Foreign Function Interface Permission is hereby granted, free of charge, to any person obtaining a copy of this software and associated documentation files (the ``Software''), to deal in the Software without restriction, including without limitation the rights to use, copy, modify, merge, publish, distribute, sublicense, and/or sell copies of the Software, and to permit persons to whom the Software is furnished to do so, subject to the following conditions: The above copyright notice and this permission notice shall be included in all copies or substantial portions of the Software. THE SOFTWARE IS PROVIDED ``AS IS'', WITHOUT WARRANTY OF ANY KIND, EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. ----------------------------------------------------------------------- */ #include #include #include #include #ifdef __x86_64__ #define MAX_GPR_REGS 6 #define MAX_SSE_REGS 8 struct register_args { /* Registers for argument passing. */ UINT64 gpr[MAX_GPR_REGS]; __int128_t sse[MAX_SSE_REGS]; }; extern void ffi_call_unix64 (void *args, unsigned long bytes, unsigned flags, void *raddr, void (*fnaddr)(void), unsigned ssecount); /* All reference to register classes here is identical to the code in gcc/config/i386/i386.c. Do *not* change one without the other. */ /* Register class used for passing given 64bit part of the argument. These represent classes as documented by the PS ABI, with the exception of SSESF, SSEDF classes, that are basically SSE class, just gcc will use SF or DFmode move instead of DImode to avoid reformatting penalties. Similary we play games with INTEGERSI_CLASS to use cheaper SImode moves whenever possible (upper half does contain padding). */ enum x86_64_reg_class { X86_64_NO_CLASS, X86_64_INTEGER_CLASS, X86_64_INTEGERSI_CLASS, X86_64_SSE_CLASS, X86_64_SSESF_CLASS, X86_64_SSEDF_CLASS, X86_64_SSEUP_CLASS, X86_64_X87_CLASS, X86_64_X87UP_CLASS, X86_64_COMPLEX_X87_CLASS, X86_64_MEMORY_CLASS }; #define MAX_CLASSES 4 #define SSE_CLASS_P(X) ((X) >= X86_64_SSE_CLASS && X <= X86_64_SSEUP_CLASS) /* x86-64 register passing implementation. See x86-64 ABI for details. Goal of this code is to classify each 8bytes of incoming argument by the register class and assign registers accordingly. */ /* Return the union class of CLASS1 and CLASS2. See the x86-64 PS ABI for details. */ static enum x86_64_reg_class merge_classes (enum x86_64_reg_class class1, enum x86_64_reg_class class2) { /* Rule #1: If both classes are equal, this is the resulting class. */ if (class1 == class2) return class1; /* Rule #2: If one of the classes is NO_CLASS, the resulting class is the other class. */ if (class1 == X86_64_NO_CLASS) return class2; if (class2 == X86_64_NO_CLASS) return class1; /* Rule #3: If one of the classes is MEMORY, the result is MEMORY. */ if (class1 == X86_64_MEMORY_CLASS || class2 == X86_64_MEMORY_CLASS) return X86_64_MEMORY_CLASS; /* Rule #4: If one of the classes is INTEGER, the result is INTEGER. */ if ((class1 == X86_64_INTEGERSI_CLASS && class2 == X86_64_SSESF_CLASS) || (class2 == X86_64_INTEGERSI_CLASS && class1 == X86_64_SSESF_CLASS)) return X86_64_INTEGERSI_CLASS; if (class1 == X86_64_INTEGER_CLASS || class1 == X86_64_INTEGERSI_CLASS || class2 == X86_64_INTEGER_CLASS || class2 == X86_64_INTEGERSI_CLASS) return X86_64_INTEGER_CLASS; /* Rule #5: If one of the classes is X87, X87UP, or COMPLEX_X87 class, MEMORY is used. */ if (class1 == X86_64_X87_CLASS || class1 == X86_64_X87UP_CLASS || class1 == X86_64_COMPLEX_X87_CLASS || class2 == X86_64_X87_CLASS || class2 == X86_64_X87UP_CLASS || class2 == X86_64_COMPLEX_X87_CLASS) return X86_64_MEMORY_CLASS; /* Rule #6: Otherwise class SSE is used. */ return X86_64_SSE_CLASS; } /* Classify the argument of type TYPE and mode MODE. CLASSES will be filled by the register class used to pass each word of the operand. The number of words is returned. In case the parameter should be passed in memory, 0 is returned. As a special case for zero sized containers, classes[0] will be NO_CLASS and 1 is returned. See the x86-64 PS ABI for details. */ static int classify_argument (ffi_type *type, enum x86_64_reg_class classes[], size_t byte_offset) { switch (type->type) { case FFI_TYPE_UINT8: case FFI_TYPE_SINT8: case FFI_TYPE_UINT16: case FFI_TYPE_SINT16: case FFI_TYPE_UINT32: case FFI_TYPE_SINT32: case FFI_TYPE_UINT64: case FFI_TYPE_SINT64: case FFI_TYPE_POINTER: { int size = byte_offset + type->size; if (size <= 4) { classes[0] = X86_64_INTEGERSI_CLASS; return 1; } else if (size <= 8) { classes[0] = X86_64_INTEGER_CLASS; return 1; } else if (size <= 12) { classes[0] = X86_64_INTEGER_CLASS; classes[1] = X86_64_INTEGERSI_CLASS; return 2; } else if (size <= 16) { classes[0] = classes[1] = X86_64_INTEGERSI_CLASS; return 2; } else FFI_ASSERT (0); } case FFI_TYPE_FLOAT: if (!(byte_offset % 8)) classes[0] = X86_64_SSESF_CLASS; else classes[0] = X86_64_SSE_CLASS; return 1; case FFI_TYPE_DOUBLE: classes[0] = X86_64_SSEDF_CLASS; return 1; case FFI_TYPE_LONGDOUBLE: classes[0] = X86_64_X87_CLASS; classes[1] = X86_64_X87UP_CLASS; return 2; case FFI_TYPE_STRUCT: { const int UNITS_PER_WORD = 8; int words = (type->size + UNITS_PER_WORD - 1) / UNITS_PER_WORD; ffi_type **ptr; int i; enum x86_64_reg_class subclasses[MAX_CLASSES]; /* If the struct is larger than 32 bytes, pass it on the stack. */ if (type->size > 32) return 0; for (i = 0; i < words; i++) classes[i] = X86_64_NO_CLASS; /* Zero sized arrays or structures are NO_CLASS. We return 0 to signalize memory class, so handle it as special case. */ if (!words) { classes[0] = X86_64_NO_CLASS; return 1; } /* Merge the fields of structure. */ for (ptr = type->elements; *ptr != NULL; ptr++) { int num; byte_offset = ALIGN (byte_offset, (*ptr)->alignment); num = classify_argument (*ptr, subclasses, byte_offset % 8); if (num == 0) return 0; for (i = 0; i < num; i++) { int pos = byte_offset / 8; classes[i + pos] = merge_classes (subclasses[i], classes[i + pos]); } byte_offset += (*ptr)->size; } if (words > 2) { /* When size > 16 bytes, if the first one isn't X86_64_SSE_CLASS or any other ones aren't X86_64_SSEUP_CLASS, everything should be passed in memory. */ if (classes[0] != X86_64_SSE_CLASS) return 0; for (i = 1; i < words; i++) if (classes[i] != X86_64_SSEUP_CLASS) return 0; } /* Final merger cleanup. */ for (i = 0; i < words; i++) { /* If one class is MEMORY, everything should be passed in memory. */ if (classes[i] == X86_64_MEMORY_CLASS) return 0; /* The X86_64_SSEUP_CLASS should be always preceded by X86_64_SSE_CLASS or X86_64_SSEUP_CLASS. */ if (classes[i] == X86_64_SSEUP_CLASS && classes[i - 1] != X86_64_SSE_CLASS && classes[i - 1] != X86_64_SSEUP_CLASS) { /* The first one should never be X86_64_SSEUP_CLASS. */ FFI_ASSERT (i != 0); classes[i] = X86_64_SSE_CLASS; } /* If X86_64_X87UP_CLASS isn't preceded by X86_64_X87_CLASS, everything should be passed in memory. */ if (classes[i] == X86_64_X87UP_CLASS && (classes[i - 1] != X86_64_X87_CLASS)) { /* The first one should never be X86_64_X87UP_CLASS. */ FFI_ASSERT (i != 0); return 0; } } return words; } default: FFI_ASSERT(0); } return 0; /* Never reached. */ } /* Examine the argument and return set number of register required in each class. Return zero iff parameter should be passed in memory, otherwise the number of registers. */ static int examine_argument (ffi_type *type, enum x86_64_reg_class classes[MAX_CLASSES], _Bool in_return, int *pngpr, int *pnsse) { int i, n, ngpr, nsse; n = classify_argument (type, classes, 0); if (n == 0) return 0; ngpr = nsse = 0; for (i = 0; i < n; ++i) switch (classes[i]) { case X86_64_INTEGER_CLASS: case X86_64_INTEGERSI_CLASS: ngpr++; break; case X86_64_SSE_CLASS: case X86_64_SSESF_CLASS: case X86_64_SSEDF_CLASS: nsse++; break; case X86_64_NO_CLASS: case X86_64_SSEUP_CLASS: break; case X86_64_X87_CLASS: case X86_64_X87UP_CLASS: case X86_64_COMPLEX_X87_CLASS: return in_return != 0; default: abort (); } *pngpr = ngpr; *pnsse = nsse; return n; } /* Perform machine dependent cif processing. */ ffi_status ffi_prep_cif_machdep (ffi_cif *cif) { int gprcount, ssecount, i, avn, n, ngpr, nsse, flags; enum x86_64_reg_class classes[MAX_CLASSES]; size_t bytes; gprcount = ssecount = 0; flags = cif->rtype->type; if (flags != FFI_TYPE_VOID) { n = examine_argument (cif->rtype, classes, 1, &ngpr, &nsse); if (n == 0) { /* The return value is passed in memory. A pointer to that memory is the first argument. Allocate a register for it. */ gprcount++; /* We don't have to do anything in asm for the return. */ flags = FFI_TYPE_VOID; } else if (flags == FFI_TYPE_STRUCT) { /* Mark which registers the result appears in. */ _Bool sse0 = SSE_CLASS_P (classes[0]); _Bool sse1 = n == 2 && SSE_CLASS_P (classes[1]); if (sse0 && !sse1) flags |= 1 << 8; else if (!sse0 && sse1) flags |= 1 << 9; else if (sse0 && sse1) flags |= 1 << 10; /* Mark the true size of the structure. */ flags |= cif->rtype->size << 12; } } /* Go over all arguments and determine the way they should be passed. If it's in a register and there is space for it, let that be so. If not, add it's size to the stack byte count. */ for (bytes = 0, i = 0, avn = cif->nargs; i < avn; i++) { if (examine_argument (cif->arg_types[i], classes, 0, &ngpr, &nsse) == 0 || gprcount + ngpr > MAX_GPR_REGS || ssecount + nsse > MAX_SSE_REGS) { long align = cif->arg_types[i]->alignment; if (align < 8) align = 8; bytes = ALIGN(bytes, align); bytes += cif->arg_types[i]->size; } else { gprcount += ngpr; ssecount += nsse; } } if (ssecount) flags |= 1 << 11; cif->flags = flags; cif->bytes = bytes; return FFI_OK; } void ffi_call (ffi_cif *cif, void (*fn)(void), void *rvalue, void **avalue) { enum x86_64_reg_class classes[MAX_CLASSES]; char *stack, *argp; ffi_type **arg_types; int gprcount, ssecount, ngpr, nsse, i, avn; _Bool ret_in_memory; struct register_args *reg_args; /* Can't call 32-bit mode from 64-bit mode. */ FFI_ASSERT (cif->abi == FFI_UNIX64); /* If the return value is a struct and we don't have a return value address then we need to make one. Note the setting of flags to VOID above in ffi_prep_cif_machdep. */ ret_in_memory = (cif->rtype->type == FFI_TYPE_STRUCT && (cif->flags & 0xff) == FFI_TYPE_VOID); if (rvalue == NULL && ret_in_memory) rvalue = alloca (cif->rtype->size); /* Allocate the space for the arguments, plus 4 words of temp space. */ stack = alloca (sizeof (struct register_args) + cif->bytes + 4*8); reg_args = (struct register_args *) stack; argp = stack + sizeof (struct register_args); gprcount = ssecount = 0; /* If the return value is passed in memory, add the pointer as the first integer argument. */ if (ret_in_memory) reg_args->gpr[gprcount++] = (long) rvalue; avn = cif->nargs; arg_types = cif->arg_types; for (i = 0; i < avn; ++i) { size_t size = arg_types[i]->size; int n; n = examine_argument (arg_types[i], classes, 0, &ngpr, &nsse); if (n == 0 || gprcount + ngpr > MAX_GPR_REGS || ssecount + nsse > MAX_SSE_REGS) { long align = arg_types[i]->alignment; /* Stack arguments are *always* at least 8 byte aligned. */ if (align < 8) align = 8; /* Pass this argument in memory. */ argp = (void *) ALIGN (argp, align); memcpy (argp, avalue[i], size); argp += size; } else { /* The argument is passed entirely in registers. */ char *a = (char *) avalue[i]; int j; for (j = 0; j < n; j++, a += 8, size -= 8) { switch (classes[j]) { case X86_64_INTEGER_CLASS: case X86_64_INTEGERSI_CLASS: reg_args->gpr[gprcount] = 0; memcpy (®_args->gpr[gprcount], a, size < 8 ? size : 8); gprcount++; break; case X86_64_SSE_CLASS: case X86_64_SSEDF_CLASS: reg_args->sse[ssecount++] = *(UINT64 *) a; break; case X86_64_SSESF_CLASS: reg_args->sse[ssecount++] = *(UINT32 *) a; break; default: abort(); } } } } ffi_call_unix64 (stack, cif->bytes + sizeof (struct register_args), cif->flags, rvalue, fn, ssecount); } extern void ffi_closure_unix64(void); ffi_status ffi_prep_closure_loc (ffi_closure* closure, ffi_cif* cif, void (*fun)(ffi_cif*, void*, void**, void*), void *user_data, void *codeloc) { volatile unsigned short *tramp; tramp = (volatile unsigned short *) &closure->tramp[0]; tramp[0] = 0xbb49; /* mov , %r11 */ *(void * volatile *) &tramp[1] = ffi_closure_unix64; tramp[5] = 0xba49; /* mov , %r10 */ *(void * volatile *) &tramp[6] = codeloc; /* Set the carry bit iff the function uses any sse registers. This is clc or stc, together with the first byte of the jmp. */ tramp[10] = cif->flags & (1 << 11) ? 0x49f9 : 0x49f8; tramp[11] = 0xe3ff; /* jmp *%r11 */ closure->cif = cif; closure->fun = fun; closure->user_data = user_data; return FFI_OK; } int ffi_closure_unix64_inner(ffi_closure *closure, void *rvalue, struct register_args *reg_args, char *argp) { ffi_cif *cif; void **avalue; ffi_type **arg_types; long i, avn; int gprcount, ssecount, ngpr, nsse; int ret; cif = closure->cif; avalue = alloca(cif->nargs * sizeof(void *)); gprcount = ssecount = 0; ret = cif->rtype->type; if (ret != FFI_TYPE_VOID) { enum x86_64_reg_class classes[MAX_CLASSES]; int n = examine_argument (cif->rtype, classes, 1, &ngpr, &nsse); if (n == 0) { /* The return value goes in memory. Arrange for the closure return value to go directly back to the original caller. */ rvalue = (void *) reg_args->gpr[gprcount++]; /* We don't have to do anything in asm for the return. */ ret = FFI_TYPE_VOID; } else if (ret == FFI_TYPE_STRUCT && n == 2) { /* Mark which register the second word of the structure goes in. */ _Bool sse0 = SSE_CLASS_P (classes[0]); _Bool sse1 = SSE_CLASS_P (classes[1]); if (!sse0 && sse1) ret |= 1 << 8; else if (sse0 && !sse1) ret |= 1 << 9; } } avn = cif->nargs; arg_types = cif->arg_types; for (i = 0; i < avn; ++i) { enum x86_64_reg_class classes[MAX_CLASSES]; int n; n = examine_argument (arg_types[i], classes, 0, &ngpr, &nsse); if (n == 0 || gprcount + ngpr > MAX_GPR_REGS || ssecount + nsse > MAX_SSE_REGS) { long align = arg_types[i]->alignment; /* Stack arguments are *always* at least 8 byte aligned. */ if (align < 8) align = 8; /* Pass this argument in memory. */ argp = (void *) ALIGN (argp, align); avalue[i] = argp; argp += arg_types[i]->size; } /* If the argument is in a single register, or two consecutive integer registers, then we can use that address directly. */ else if (n == 1 || (n == 2 && !(SSE_CLASS_P (classes[0]) || SSE_CLASS_P (classes[1])))) { /* The argument is in a single register. */ if (SSE_CLASS_P (classes[0])) { avalue[i] = ®_args->sse[ssecount]; ssecount += n; } else { avalue[i] = ®_args->gpr[gprcount]; gprcount += n; } } /* Otherwise, allocate space to make them consecutive. */ else { char *a = alloca (16); int j; avalue[i] = a; for (j = 0; j < n; j++, a += 8) { if (SSE_CLASS_P (classes[j])) memcpy (a, ®_args->sse[ssecount++], 8); else memcpy (a, ®_args->gpr[gprcount++], 8); } } } /* Invoke the closure. */ closure->fun (cif, rvalue, avalue, closure->user_data); /* Tell assembly how to perform return type promotions. */ return ret; } #endif /* __x86_64__ */ smalltalk-3.2.5/libffi/src/x86/unix64.S0000644000175000017500000002621712130343734014366 00000000000000/* ----------------------------------------------------------------------- unix64.S - Copyright (c) 2002 Bo Thorsen Copyright (c) 2008 Red Hat, Inc x86-64 Foreign Function Interface Permission is hereby granted, free of charge, to any person obtaining a copy of this software and associated documentation files (the ``Software''), to deal in the Software without restriction, including without limitation the rights to use, copy, modify, merge, publish, distribute, sublicense, and/or sell copies of the Software, and to permit persons to whom the Software is furnished to do so, subject to the following conditions: The above copyright notice and this permission notice shall be included in all copies or substantial portions of the Software. THE SOFTWARE IS PROVIDED ``AS IS'', WITHOUT WARRANTY OF ANY KIND, EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. ----------------------------------------------------------------------- */ #ifdef __x86_64__ #define LIBFFI_ASM #include #include .text /* ffi_call_unix64 (void *args, unsigned long bytes, unsigned flags, void *raddr, void (*fnaddr)(void)); Bit o trickiness here -- ARGS+BYTES is the base of the stack frame for this function. This has been allocated by ffi_call. We also deallocate some of the stack that has been alloca'd. */ .align 2 .globl ffi_call_unix64 .type ffi_call_unix64,@function ffi_call_unix64: .LUW0: movq (%rsp), %r10 /* Load return address. */ leaq (%rdi, %rsi), %rax /* Find local stack base. */ movq %rdx, (%rax) /* Save flags. */ movq %rcx, 8(%rax) /* Save raddr. */ movq %rbp, 16(%rax) /* Save old frame pointer. */ movq %r10, 24(%rax) /* Relocate return address. */ movq %rax, %rbp /* Finalize local stack frame. */ .LUW1: movq %rdi, %r10 /* Save a copy of the register area. */ movq %r8, %r11 /* Save a copy of the target fn. */ movl %r9d, %eax /* Set number of SSE registers. */ /* Load up all argument registers. */ movq (%r10), %rdi movq 8(%r10), %rsi movq 16(%r10), %rdx movq 24(%r10), %rcx movq 32(%r10), %r8 movq 40(%r10), %r9 testl %eax, %eax jnz .Lload_sse .Lret_from_load_sse: /* Deallocate the reg arg area. */ leaq 176(%r10), %rsp /* Call the user function. */ call *%r11 /* Deallocate stack arg area; local stack frame in redzone. */ leaq 24(%rbp), %rsp movq 0(%rbp), %rcx /* Reload flags. */ movq 8(%rbp), %rdi /* Reload raddr. */ movq 16(%rbp), %rbp /* Reload old frame pointer. */ .LUW2: /* The first byte of the flags contains the FFI_TYPE. */ movzbl %cl, %r10d leaq .Lstore_table(%rip), %r11 movslq (%r11, %r10, 4), %r10 addq %r11, %r10 jmp *%r10 .Lstore_table: .long .Lst_void-.Lstore_table /* FFI_TYPE_VOID */ .long .Lst_sint32-.Lstore_table /* FFI_TYPE_INT */ .long .Lst_float-.Lstore_table /* FFI_TYPE_FLOAT */ .long .Lst_double-.Lstore_table /* FFI_TYPE_DOUBLE */ .long .Lst_ldouble-.Lstore_table /* FFI_TYPE_LONGDOUBLE */ .long .Lst_uint8-.Lstore_table /* FFI_TYPE_UINT8 */ .long .Lst_sint8-.Lstore_table /* FFI_TYPE_SINT8 */ .long .Lst_uint16-.Lstore_table /* FFI_TYPE_UINT16 */ .long .Lst_sint16-.Lstore_table /* FFI_TYPE_SINT16 */ .long .Lst_uint32-.Lstore_table /* FFI_TYPE_UINT32 */ .long .Lst_sint32-.Lstore_table /* FFI_TYPE_SINT32 */ .long .Lst_int64-.Lstore_table /* FFI_TYPE_UINT64 */ .long .Lst_int64-.Lstore_table /* FFI_TYPE_SINT64 */ .long .Lst_struct-.Lstore_table /* FFI_TYPE_STRUCT */ .long .Lst_int64-.Lstore_table /* FFI_TYPE_POINTER */ .align 2 .Lst_void: ret .align 2 .Lst_uint8: movzbq %al, %rax movq %rax, (%rdi) ret .align 2 .Lst_sint8: movsbq %al, %rax movq %rax, (%rdi) ret .align 2 .Lst_uint16: movzwq %ax, %rax movq %rax, (%rdi) .align 2 .Lst_sint16: movswq %ax, %rax movq %rax, (%rdi) ret .align 2 .Lst_uint32: movl %eax, %eax movq %rax, (%rdi) .align 2 .Lst_sint32: cltq movq %rax, (%rdi) ret .align 2 .Lst_int64: movq %rax, (%rdi) ret .align 2 .Lst_float: movss %xmm0, (%rdi) ret .align 2 .Lst_double: movsd %xmm0, (%rdi) ret .Lst_ldouble: fstpt (%rdi) ret .align 2 .Lst_struct: leaq -20(%rsp), %rsi /* Scratch area in redzone. */ /* We have to locate the values now, and since we don't want to write too much data into the user's return value, we spill the value to a 16 byte scratch area first. Bits 8, 9, and 10 control where the values are located. Only one of the three bits will be set; see ffi_prep_cif_machdep for the pattern. */ movd %xmm0, %r10 movd %xmm1, %r11 testl $0x100, %ecx cmovnz %rax, %rdx cmovnz %r10, %rax testl $0x200, %ecx cmovnz %r10, %rdx testl $0x400, %ecx cmovnz %r10, %rax cmovnz %r11, %rdx movq %rax, (%rsi) movq %rdx, 8(%rsi) /* Bits 12-31 contain the true size of the structure. Copy from the scratch area to the true destination. */ shrl $12, %ecx rep movsb ret /* Many times we can avoid loading any SSE registers at all. It's not worth an indirect jump to load the exact set of SSE registers needed; zero or all is a good compromise. */ .align 2 .LUW3: .Lload_sse: movdqa 48(%r10), %xmm0 movdqa 64(%r10), %xmm1 movdqa 80(%r10), %xmm2 movdqa 96(%r10), %xmm3 movdqa 112(%r10), %xmm4 movdqa 128(%r10), %xmm5 movdqa 144(%r10), %xmm6 movdqa 160(%r10), %xmm7 jmp .Lret_from_load_sse .LUW4: .size ffi_call_unix64,.-ffi_call_unix64 .align 2 .globl ffi_closure_unix64 .type ffi_closure_unix64,@function ffi_closure_unix64: .LUW5: /* The carry flag is set by the trampoline iff SSE registers are used. Don't clobber it before the branch instruction. */ leaq -200(%rsp), %rsp .LUW6: movq %rdi, (%rsp) movq %rsi, 8(%rsp) movq %rdx, 16(%rsp) movq %rcx, 24(%rsp) movq %r8, 32(%rsp) movq %r9, 40(%rsp) jc .Lsave_sse .Lret_from_save_sse: movq %r10, %rdi leaq 176(%rsp), %rsi movq %rsp, %rdx leaq 208(%rsp), %rcx call ffi_closure_unix64_inner@PLT /* Deallocate stack frame early; return value is now in redzone. */ addq $200, %rsp .LUW7: /* The first byte of the return value contains the FFI_TYPE. */ movzbl %al, %r10d leaq .Lload_table(%rip), %r11 movslq (%r11, %r10, 4), %r10 addq %r11, %r10 jmp *%r10 .Lload_table: .long .Lld_void-.Lload_table /* FFI_TYPE_VOID */ .long .Lld_int32-.Lload_table /* FFI_TYPE_INT */ .long .Lld_float-.Lload_table /* FFI_TYPE_FLOAT */ .long .Lld_double-.Lload_table /* FFI_TYPE_DOUBLE */ .long .Lld_ldouble-.Lload_table /* FFI_TYPE_LONGDOUBLE */ .long .Lld_int8-.Lload_table /* FFI_TYPE_UINT8 */ .long .Lld_int8-.Lload_table /* FFI_TYPE_SINT8 */ .long .Lld_int16-.Lload_table /* FFI_TYPE_UINT16 */ .long .Lld_int16-.Lload_table /* FFI_TYPE_SINT16 */ .long .Lld_int32-.Lload_table /* FFI_TYPE_UINT32 */ .long .Lld_int32-.Lload_table /* FFI_TYPE_SINT32 */ .long .Lld_int64-.Lload_table /* FFI_TYPE_UINT64 */ .long .Lld_int64-.Lload_table /* FFI_TYPE_SINT64 */ .long .Lld_struct-.Lload_table /* FFI_TYPE_STRUCT */ .long .Lld_int64-.Lload_table /* FFI_TYPE_POINTER */ .align 2 .Lld_void: ret .align 2 .Lld_int8: movzbl -24(%rsp), %eax ret .align 2 .Lld_int16: movzwl -24(%rsp), %eax ret .align 2 .Lld_int32: movl -24(%rsp), %eax ret .align 2 .Lld_int64: movq -24(%rsp), %rax ret .align 2 .Lld_float: movss -24(%rsp), %xmm0 ret .align 2 .Lld_double: movsd -24(%rsp), %xmm0 ret .align 2 .Lld_ldouble: fldt -24(%rsp) ret .align 2 .Lld_struct: /* There are four possibilities here, %rax/%rdx, %xmm0/%rax, %rax/%xmm0, %xmm0/%xmm1. We collapse two by always loading both rdx and xmm1 with the second word. For the remaining, bit 8 set means xmm0 gets the second word, and bit 9 means that rax gets the second word. */ movq -24(%rsp), %rcx movq -16(%rsp), %rdx movq -16(%rsp), %xmm1 testl $0x100, %eax cmovnz %rdx, %rcx movd %rcx, %xmm0 testl $0x200, %eax movq -24(%rsp), %rax cmovnz %rdx, %rax ret /* See the comment above .Lload_sse; the same logic applies here. */ .align 2 .LUW8: .Lsave_sse: movdqa %xmm0, 48(%rsp) movdqa %xmm1, 64(%rsp) movdqa %xmm2, 80(%rsp) movdqa %xmm3, 96(%rsp) movdqa %xmm4, 112(%rsp) movdqa %xmm5, 128(%rsp) movdqa %xmm6, 144(%rsp) movdqa %xmm7, 160(%rsp) jmp .Lret_from_save_sse .LUW9: .size ffi_closure_unix64,.-ffi_closure_unix64 #ifdef HAVE_AS_X86_64_UNWIND_SECTION_TYPE .section .eh_frame,"a",@unwind #else .section .eh_frame,"a",@progbits #endif .Lframe1: .long .LECIE1-.LSCIE1 /* CIE Length */ .LSCIE1: .long 0 /* CIE Identifier Tag */ .byte 1 /* CIE Version */ .ascii "zR\0" /* CIE Augmentation */ .uleb128 1 /* CIE Code Alignment Factor */ .sleb128 -8 /* CIE Data Alignment Factor */ .byte 0x10 /* CIE RA Column */ .uleb128 1 /* Augmentation size */ .byte 0x1b /* FDE Encoding (pcrel sdata4) */ .byte 0xc /* DW_CFA_def_cfa, %rsp offset 8 */ .uleb128 7 .uleb128 8 .byte 0x80+16 /* DW_CFA_offset, %rip offset 1*-8 */ .uleb128 1 .align 8 .LECIE1: .LSFDE1: .long .LEFDE1-.LASFDE1 /* FDE Length */ .LASFDE1: .long .LASFDE1-.Lframe1 /* FDE CIE offset */ #if HAVE_AS_X86_PCREL .long .LUW0-. /* FDE initial location */ #else .long .LUW0@rel #endif .long .LUW4-.LUW0 /* FDE address range */ .uleb128 0x0 /* Augmentation size */ .byte 0x4 /* DW_CFA_advance_loc4 */ .long .LUW1-.LUW0 /* New stack frame based off rbp. This is a itty bit of unwind trickery in that the CFA *has* changed. There is no easy way to describe it correctly on entry to the function. Fortunately, it doesn't matter too much since at all points we can correctly unwind back to ffi_call. Note that the location to which we moved the return address is (the new) CFA-8, so from the perspective of the unwind info, it hasn't moved. */ .byte 0xc /* DW_CFA_def_cfa, %rbp offset 32 */ .uleb128 6 .uleb128 32 .byte 0x80+6 /* DW_CFA_offset, %rbp offset 2*-8 */ .uleb128 2 .byte 0xa /* DW_CFA_remember_state */ .byte 0x4 /* DW_CFA_advance_loc4 */ .long .LUW2-.LUW1 .byte 0xc /* DW_CFA_def_cfa, %rsp offset 8 */ .uleb128 7 .uleb128 8 .byte 0xc0+6 /* DW_CFA_restore, %rbp */ .byte 0x4 /* DW_CFA_advance_loc4 */ .long .LUW3-.LUW2 .byte 0xb /* DW_CFA_restore_state */ .align 8 .LEFDE1: .LSFDE3: .long .LEFDE3-.LASFDE3 /* FDE Length */ .LASFDE3: .long .LASFDE3-.Lframe1 /* FDE CIE offset */ #if HAVE_AS_X86_PCREL .long .LUW5-. /* FDE initial location */ #else .long .LUW5@rel #endif .long .LUW9-.LUW5 /* FDE address range */ .uleb128 0x0 /* Augmentation size */ .byte 0x4 /* DW_CFA_advance_loc4 */ .long .LUW6-.LUW5 .byte 0xe /* DW_CFA_def_cfa_offset */ .uleb128 208 .byte 0xa /* DW_CFA_remember_state */ .byte 0x4 /* DW_CFA_advance_loc4 */ .long .LUW7-.LUW6 .byte 0xe /* DW_CFA_def_cfa_offset */ .uleb128 8 .byte 0x4 /* DW_CFA_advance_loc4 */ .long .LUW8-.LUW7 .byte 0xb /* DW_CFA_restore_state */ .align 8 .LEFDE3: #endif /* __x86_64__ */ #if defined __ELF__ && defined __linux__ .section .note.GNU-stack,"",@progbits #endif smalltalk-3.2.5/libffi/src/x86/ffitarget.h0000644000175000017500000000676012130343734015232 00000000000000/* -----------------------------------------------------------------*-C-*- ffitarget.h - Copyright (c) 1996-2003, 2010 Red Hat, Inc. Copyright (C) 2008 Free Software Foundation, Inc. Target configuration macros for x86 and x86-64. Permission is hereby granted, free of charge, to any person obtaining a copy of this software and associated documentation files (the ``Software''), to deal in the Software without restriction, including without limitation the rights to use, copy, modify, merge, publish, distribute, sublicense, and/or sell copies of the Software, and to permit persons to whom the Software is furnished to do so, subject to the following conditions: The above copyright notice and this permission notice shall be included in all copies or substantial portions of the Software. THE SOFTWARE IS PROVIDED ``AS IS'', WITHOUT WARRANTY OF ANY KIND, EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. ----------------------------------------------------------------------- */ #ifndef LIBFFI_TARGET_H #define LIBFFI_TARGET_H /* ---- System specific configurations ----------------------------------- */ #if defined (X86_64) && defined (__i386__) #undef X86_64 #define X86 #endif #ifdef X86_WIN64 #define FFI_SIZEOF_ARG 8 #define USE_BUILTIN_FFS 0 /* not yet implemented in mingw-64 */ #endif /* ---- Generic type definitions ----------------------------------------- */ #ifndef LIBFFI_ASM #ifdef X86_WIN64 #ifdef _MSC_VER typedef unsigned __int64 ffi_arg; typedef __int64 ffi_sarg; #else typedef unsigned long long ffi_arg; typedef long long ffi_sarg; #endif #else typedef unsigned long ffi_arg; typedef signed long ffi_sarg; #endif typedef enum ffi_abi { FFI_FIRST_ABI = 0, /* ---- Intel x86 Win32 ---------- */ #ifdef X86_WIN32 FFI_SYSV, FFI_STDCALL, /* TODO: Add fastcall support for the sake of completeness */ FFI_DEFAULT_ABI = FFI_SYSV, #endif #ifdef X86_WIN64 FFI_WIN64, FFI_DEFAULT_ABI = FFI_WIN64, #else /* ---- Intel x86 and AMD x86-64 - */ #if !defined(X86_WIN32) && (defined(__i386__) || defined(__x86_64__) || defined(__i386) || defined(__amd64)) FFI_SYSV, FFI_UNIX64, /* Unix variants all use the same ABI for x86-64 */ #if defined(__i386__) || defined(__i386) FFI_DEFAULT_ABI = FFI_SYSV, #else FFI_DEFAULT_ABI = FFI_UNIX64, #endif #endif #endif /* X86_WIN64 */ FFI_LAST_ABI = FFI_DEFAULT_ABI + 1 } ffi_abi; #endif /* ---- Definitions for closures ----------------------------------------- */ #define FFI_CLOSURES 1 #define FFI_TYPE_SMALL_STRUCT_1B (FFI_TYPE_LAST + 1) #define FFI_TYPE_SMALL_STRUCT_2B (FFI_TYPE_LAST + 2) #define FFI_TYPE_SMALL_STRUCT_4B (FFI_TYPE_LAST + 3) #if defined (X86_64) || (defined (__x86_64__) && defined (X86_DARWIN)) #define FFI_TRAMPOLINE_SIZE 24 #define FFI_NATIVE_RAW_API 0 #else #ifdef X86_WIN32 #define FFI_TRAMPOLINE_SIZE 13 #else #ifdef X86_WIN64 #define FFI_TRAMPOLINE_SIZE 29 #define FFI_NATIVE_RAW_API 0 #define FFI_NO_RAW_API 1 #else #define FFI_TRAMPOLINE_SIZE 10 #endif #endif #ifndef X86_WIN64 #define FFI_NATIVE_RAW_API 1 /* x86 has native raw api support */ #endif #endif #endif smalltalk-3.2.5/libffi/src/x86/darwin.S0000644000175000017500000002314312130343734014510 00000000000000/* ----------------------------------------------------------------------- darwin.S - Copyright (c) 1996, 1998, 2001, 2002, 2003, 2005 Red Hat, Inc. Copyright (C) 2008 Free Software Foundation, Inc. X86 Foreign Function Interface Permission is hereby granted, free of charge, to any person obtaining a copy of this software and associated documentation files (the ``Software''), to deal in the Software without restriction, including without limitation the rights to use, copy, modify, merge, publish, distribute, sublicense, and/or sell copies of the Software, and to permit persons to whom the Software is furnished to do so, subject to the following conditions: The above copyright notice and this permission notice shall be included in all copies or substantial portions of the Software. THE SOFTWARE IS PROVIDED ``AS IS'', WITHOUT WARRANTY OF ANY KIND, EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. ----------------------------------------------------------------------- */ #ifndef __x86_64__ #define LIBFFI_ASM #include #include .text .globl _ffi_prep_args .align 4 .globl _ffi_call_SYSV _ffi_call_SYSV: .LFB1: pushl %ebp .LCFI0: movl %esp,%ebp .LCFI1: subl $8,%esp /* Make room for all of the new args. */ movl 16(%ebp),%ecx subl %ecx,%esp movl %esp,%eax /* Place all of the ffi_prep_args in position */ subl $8,%esp pushl 12(%ebp) pushl %eax call *8(%ebp) /* Return stack to previous state and call the function */ addl $16,%esp call *28(%ebp) /* Load %ecx with the return type code */ movl 20(%ebp),%ecx /* Protect %esi. We're going to pop it in the epilogue. */ pushl %esi /* If the return value pointer is NULL, assume no return value. */ cmpl $0,24(%ebp) jne 0f /* Even if there is no space for the return value, we are obliged to handle floating-point values. */ cmpl $FFI_TYPE_FLOAT,%ecx jne noretval fstp %st(0) jmp epilogue 0: .align 4 call 1f .Lstore_table: .long noretval-.Lstore_table /* FFI_TYPE_VOID */ .long retint-.Lstore_table /* FFI_TYPE_INT */ .long retfloat-.Lstore_table /* FFI_TYPE_FLOAT */ .long retdouble-.Lstore_table /* FFI_TYPE_DOUBLE */ .long retlongdouble-.Lstore_table /* FFI_TYPE_LONGDOUBLE */ .long retuint8-.Lstore_table /* FFI_TYPE_UINT8 */ .long retsint8-.Lstore_table /* FFI_TYPE_SINT8 */ .long retuint16-.Lstore_table /* FFI_TYPE_UINT16 */ .long retsint16-.Lstore_table /* FFI_TYPE_SINT16 */ .long retint-.Lstore_table /* FFI_TYPE_UINT32 */ .long retint-.Lstore_table /* FFI_TYPE_SINT32 */ .long retint64-.Lstore_table /* FFI_TYPE_UINT64 */ .long retint64-.Lstore_table /* FFI_TYPE_SINT64 */ .long retstruct-.Lstore_table /* FFI_TYPE_STRUCT */ .long retint-.Lstore_table /* FFI_TYPE_POINTER */ .long retstruct1b-.Lstore_table /* FFI_TYPE_SMALL_STRUCT_1B */ .long retstruct2b-.Lstore_table /* FFI_TYPE_SMALL_STRUCT_2B */ 1: pop %esi add (%esi, %ecx, 4), %esi jmp *%esi /* Sign/zero extend as appropriate. */ retsint8: movsbl %al, %eax jmp retint retsint16: movswl %ax, %eax jmp retint retuint8: movzbl %al, %eax jmp retint retuint16: movzwl %ax, %eax jmp retint retfloat: /* Load %ecx with the pointer to storage for the return value */ movl 24(%ebp),%ecx fstps (%ecx) jmp epilogue retdouble: /* Load %ecx with the pointer to storage for the return value */ movl 24(%ebp),%ecx fstpl (%ecx) jmp epilogue retlongdouble: /* Load %ecx with the pointer to storage for the return value */ movl 24(%ebp),%ecx fstpt (%ecx) jmp epilogue retint64: /* Load %ecx with the pointer to storage for the return value */ movl 24(%ebp),%ecx movl %eax,0(%ecx) movl %edx,4(%ecx) jmp epilogue retstruct1b: /* Load %ecx with the pointer to storage for the return value */ movl 24(%ebp),%ecx movb %al,0(%ecx) jmp epilogue retstruct2b: /* Load %ecx with the pointer to storage for the return value */ movl 24(%ebp),%ecx movw %ax,0(%ecx) jmp epilogue retint: /* Load %ecx with the pointer to storage for the return value */ movl 24(%ebp),%ecx movl %eax,0(%ecx) retstruct: /* Nothing to do! */ noretval: epilogue: popl %esi movl %ebp,%esp popl %ebp ret .LFE1: .ffi_call_SYSV_end: .align 4 FFI_HIDDEN (ffi_closure_SYSV) .globl _ffi_closure_SYSV _ffi_closure_SYSV: .LFB2: pushl %ebp .LCFI2: movl %esp, %ebp .LCFI3: subl $40, %esp leal -24(%ebp), %edx movl %edx, -12(%ebp) /* resp */ leal 8(%ebp), %edx movl %edx, 4(%esp) /* args = __builtin_dwarf_cfa () */ leal -12(%ebp), %edx movl %edx, (%esp) /* &resp */ movl %ebx, 8(%esp) .LCFI7: call L_ffi_closure_SYSV_inner$stub movl 8(%esp), %ebx movl -12(%ebp), %ecx cmpl $FFI_TYPE_INT, %eax je .Lcls_retint /* Handle FFI_TYPE_UINT8, FFI_TYPE_SINT8, FFI_TYPE_UINT16, FFI_TYPE_SINT16, FFI_TYPE_UINT32, FFI_TYPE_SINT32. */ cmpl $FFI_TYPE_UINT64, %eax jge 0f cmpl $FFI_TYPE_UINT8, %eax jge .Lcls_retint 0: cmpl $FFI_TYPE_FLOAT, %eax je .Lcls_retfloat cmpl $FFI_TYPE_DOUBLE, %eax je .Lcls_retdouble cmpl $FFI_TYPE_LONGDOUBLE, %eax je .Lcls_retldouble cmpl $FFI_TYPE_SINT64, %eax je .Lcls_retllong cmpl $FFI_TYPE_SMALL_STRUCT_1B, %eax je .Lcls_retstruct1b cmpl $FFI_TYPE_SMALL_STRUCT_2B, %eax je .Lcls_retstruct2b cmpl $FFI_TYPE_STRUCT, %eax je .Lcls_retstruct .Lcls_epilogue: movl %ebp, %esp popl %ebp ret .Lcls_retint: movl (%ecx), %eax jmp .Lcls_epilogue .Lcls_retfloat: flds (%ecx) jmp .Lcls_epilogue .Lcls_retdouble: fldl (%ecx) jmp .Lcls_epilogue .Lcls_retldouble: fldt (%ecx) jmp .Lcls_epilogue .Lcls_retllong: movl (%ecx), %eax movl 4(%ecx), %edx jmp .Lcls_epilogue .Lcls_retstruct1b: movsbl (%ecx), %eax jmp .Lcls_epilogue .Lcls_retstruct2b: movswl (%ecx), %eax jmp .Lcls_epilogue .Lcls_retstruct: lea -8(%ebp),%esp movl %ebp, %esp popl %ebp ret $4 .LFE2: #if !FFI_NO_RAW_API #define RAW_CLOSURE_CIF_OFFSET ((FFI_TRAMPOLINE_SIZE + 3) & ~3) #define RAW_CLOSURE_FUN_OFFSET (RAW_CLOSURE_CIF_OFFSET + 4) #define RAW_CLOSURE_USER_DATA_OFFSET (RAW_CLOSURE_FUN_OFFSET + 4) #define CIF_FLAGS_OFFSET 20 .align 4 FFI_HIDDEN (ffi_closure_raw_SYSV) .globl _ffi_closure_raw_SYSV _ffi_closure_raw_SYSV: .LFB3: pushl %ebp .LCFI4: movl %esp, %ebp .LCFI5: pushl %esi .LCFI6: subl $36, %esp movl RAW_CLOSURE_CIF_OFFSET(%eax), %esi /* closure->cif */ movl RAW_CLOSURE_USER_DATA_OFFSET(%eax), %edx /* closure->user_data */ movl %edx, 12(%esp) /* user_data */ leal 8(%ebp), %edx /* __builtin_dwarf_cfa () */ movl %edx, 8(%esp) /* raw_args */ leal -24(%ebp), %edx movl %edx, 4(%esp) /* &res */ movl %esi, (%esp) /* cif */ call *RAW_CLOSURE_FUN_OFFSET(%eax) /* closure->fun */ movl CIF_FLAGS_OFFSET(%esi), %eax /* rtype */ cmpl $FFI_TYPE_INT, %eax je .Lrcls_retint /* Handle FFI_TYPE_UINT8, FFI_TYPE_SINT8, FFI_TYPE_UINT16, FFI_TYPE_SINT16, FFI_TYPE_UINT32, FFI_TYPE_SINT32. */ cmpl $FFI_TYPE_UINT64, %eax jge 0f cmpl $FFI_TYPE_UINT8, %eax jge .Lrcls_retint 0: cmpl $FFI_TYPE_FLOAT, %eax je .Lrcls_retfloat cmpl $FFI_TYPE_DOUBLE, %eax je .Lrcls_retdouble cmpl $FFI_TYPE_LONGDOUBLE, %eax je .Lrcls_retldouble cmpl $FFI_TYPE_SINT64, %eax je .Lrcls_retllong .Lrcls_epilogue: addl $36, %esp popl %esi popl %ebp ret .Lrcls_retint: movl -24(%ebp), %eax jmp .Lrcls_epilogue .Lrcls_retfloat: flds -24(%ebp) jmp .Lrcls_epilogue .Lrcls_retdouble: fldl -24(%ebp) jmp .Lrcls_epilogue .Lrcls_retldouble: fldt -24(%ebp) jmp .Lrcls_epilogue .Lrcls_retllong: movl -24(%ebp), %eax movl -20(%ebp), %edx jmp .Lrcls_epilogue .LFE3: #endif .section __IMPORT,__jump_table,symbol_stubs,self_modifying_code+pure_instructions,5 L_ffi_closure_SYSV_inner$stub: .indirect_symbol _ffi_closure_SYSV_inner hlt ; hlt ; hlt ; hlt ; hlt .section __TEXT,__eh_frame,coalesced,no_toc+strip_static_syms+live_support EH_frame1: .set L$set$0,LECIE1-LSCIE1 .long L$set$0 LSCIE1: .long 0x0 .byte 0x1 .ascii "zR\0" .byte 0x1 .byte 0x7c .byte 0x8 .byte 0x1 .byte 0x10 .byte 0xc .byte 0x5 .byte 0x4 .byte 0x88 .byte 0x1 .align 2 LECIE1: .globl _ffi_call_SYSV.eh _ffi_call_SYSV.eh: LSFDE1: .set L$set$1,LEFDE1-LASFDE1 .long L$set$1 LASFDE1: .long LASFDE1-EH_frame1 .long .LFB1-. .set L$set$2,.LFE1-.LFB1 .long L$set$2 .byte 0x0 .byte 0x4 .set L$set$3,.LCFI0-.LFB1 .long L$set$3 .byte 0xe .byte 0x8 .byte 0x84 .byte 0x2 .byte 0x4 .set L$set$4,.LCFI1-.LCFI0 .long L$set$4 .byte 0xd .byte 0x4 .align 2 LEFDE1: .globl _ffi_closure_SYSV.eh _ffi_closure_SYSV.eh: LSFDE2: .set L$set$5,LEFDE2-LASFDE2 .long L$set$5 LASFDE2: .long LASFDE2-EH_frame1 .long .LFB2-. .set L$set$6,.LFE2-.LFB2 .long L$set$6 .byte 0x0 .byte 0x4 .set L$set$7,.LCFI2-.LFB2 .long L$set$7 .byte 0xe .byte 0x8 .byte 0x84 .byte 0x2 .byte 0x4 .set L$set$8,.LCFI3-.LCFI2 .long L$set$8 .byte 0xd .byte 0x4 .align 2 LEFDE2: #if !FFI_NO_RAW_API .globl _ffi_closure_raw_SYSV.eh _ffi_closure_raw_SYSV.eh: LSFDE3: .set L$set$10,LEFDE3-LASFDE3 .long L$set$10 LASFDE3: .long LASFDE3-EH_frame1 .long .LFB3-. .set L$set$11,.LFE3-.LFB3 .long L$set$11 .byte 0x0 .byte 0x4 .set L$set$12,.LCFI4-.LFB3 .long L$set$12 .byte 0xe .byte 0x8 .byte 0x84 .byte 0x2 .byte 0x4 .set L$set$13,.LCFI5-.LCFI4 .long L$set$13 .byte 0xd .byte 0x4 .byte 0x4 .set L$set$14,.LCFI6-.LCFI5 .long L$set$14 .byte 0x85 .byte 0x3 .align 2 LEFDE3: #endif #endif /* ifndef __x86_64__ */ smalltalk-3.2.5/libffi/src/x86/darwin64.S0000644000175000017500000002614312130343734014665 00000000000000/* ----------------------------------------------------------------------- darwin64.S - Copyright (c) 2006 Free Software Foundation, Inc. Copyright (c) 2008 Red Hat, Inc. derived from unix64.S x86-64 Foreign Function Interface for Darwin. Permission is hereby granted, free of charge, to any person obtaining a copy of this software and associated documentation files (the ``Software''), to deal in the Software without restriction, including without limitation the rights to use, copy, modify, merge, publish, distribute, sublicense, and/or sell copies of the Software, and to permit persons to whom the Software is furnished to do so, subject to the following conditions: The above copyright notice and this permission notice shall be included in all copies or substantial portions of the Software. THE SOFTWARE IS PROVIDED ``AS IS'', WITHOUT WARRANTY OF ANY KIND, EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHOR BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. ----------------------------------------------------------------------- */ #ifdef __x86_64__ #define LIBFFI_ASM #include #include .file "darwin64.S" .text /* ffi_call_unix64 (void *args, unsigned long bytes, unsigned flags, void *raddr, void (*fnaddr)(void)); Bit o trickiness here -- ARGS+BYTES is the base of the stack frame for this function. This has been allocated by ffi_call. We also deallocate some of the stack that has been alloca'd. */ .align 3 .globl _ffi_call_unix64 _ffi_call_unix64: LUW0: movq (%rsp), %r10 /* Load return address. */ leaq (%rdi, %rsi), %rax /* Find local stack base. */ movq %rdx, (%rax) /* Save flags. */ movq %rcx, 8(%rax) /* Save raddr. */ movq %rbp, 16(%rax) /* Save old frame pointer. */ movq %r10, 24(%rax) /* Relocate return address. */ movq %rax, %rbp /* Finalize local stack frame. */ LUW1: movq %rdi, %r10 /* Save a copy of the register area. */ movq %r8, %r11 /* Save a copy of the target fn. */ movl %r9d, %eax /* Set number of SSE registers. */ /* Load up all argument registers. */ movq (%r10), %rdi movq 8(%r10), %rsi movq 16(%r10), %rdx movq 24(%r10), %rcx movq 32(%r10), %r8 movq 40(%r10), %r9 testl %eax, %eax jnz Lload_sse Lret_from_load_sse: /* Deallocate the reg arg area. */ leaq 176(%r10), %rsp /* Call the user function. */ call *%r11 /* Deallocate stack arg area; local stack frame in redzone. */ leaq 24(%rbp), %rsp movq 0(%rbp), %rcx /* Reload flags. */ movq 8(%rbp), %rdi /* Reload raddr. */ movq 16(%rbp), %rbp /* Reload old frame pointer. */ LUW2: /* The first byte of the flags contains the FFI_TYPE. */ movzbl %cl, %r10d leaq Lstore_table(%rip), %r11 movslq (%r11, %r10, 4), %r10 addq %r11, %r10 jmp *%r10 Lstore_table: .long Lst_void-Lstore_table /* FFI_TYPE_VOID */ .long Lst_sint32-Lstore_table /* FFI_TYPE_INT */ .long Lst_float-Lstore_table /* FFI_TYPE_FLOAT */ .long Lst_double-Lstore_table /* FFI_TYPE_DOUBLE */ .long Lst_ldouble-Lstore_table /* FFI_TYPE_LONGDOUBLE */ .long Lst_uint8-Lstore_table /* FFI_TYPE_UINT8 */ .long Lst_sint8-Lstore_table /* FFI_TYPE_SINT8 */ .long Lst_uint16-Lstore_table /* FFI_TYPE_UINT16 */ .long Lst_sint16-Lstore_table /* FFI_TYPE_SINT16 */ .long Lst_uint32-Lstore_table /* FFI_TYPE_UINT32 */ .long Lst_sint32-Lstore_table /* FFI_TYPE_SINT32 */ .long Lst_int64-Lstore_table /* FFI_TYPE_UINT64 */ .long Lst_int64-Lstore_table /* FFI_TYPE_SINT64 */ .long Lst_struct-Lstore_table /* FFI_TYPE_STRUCT */ .long Lst_int64-Lstore_table /* FFI_TYPE_POINTER */ .text .align 3 Lst_void: ret .align 3 Lst_uint8: movzbq %al, %rax movq %rax, (%rdi) ret .align 3 Lst_sint8: movsbq %al, %rax movq %rax, (%rdi) ret .align 3 Lst_uint16: movzwq %ax, %rax movq %rax, (%rdi) .align 3 Lst_sint16: movswq %ax, %rax movq %rax, (%rdi) ret .align 3 Lst_uint32: movl %eax, %eax movq %rax, (%rdi) .align 3 Lst_sint32: cltq movq %rax, (%rdi) ret .align 3 Lst_int64: movq %rax, (%rdi) ret .align 3 Lst_float: movss %xmm0, (%rdi) ret .align 3 Lst_double: movsd %xmm0, (%rdi) ret Lst_ldouble: fstpt (%rdi) ret .align 3 Lst_struct: leaq -20(%rsp), %rsi /* Scratch area in redzone. */ /* We have to locate the values now, and since we don't want to write too much data into the user's return value, we spill the value to a 16 byte scratch area first. Bits 8, 9, and 10 control where the values are located. Only one of the three bits will be set; see ffi_prep_cif_machdep for the pattern. */ movd %xmm0, %r10 movd %xmm1, %r11 testl $0x100, %ecx cmovnz %rax, %rdx cmovnz %r10, %rax testl $0x200, %ecx cmovnz %r10, %rdx testl $0x400, %ecx cmovnz %r10, %rax cmovnz %r11, %rdx movq %rax, (%rsi) movq %rdx, 8(%rsi) /* Bits 12-31 contain the true size of the structure. Copy from the scratch area to the true destination. */ shrl $12, %ecx rep movsb ret /* Many times we can avoid loading any SSE registers at all. It's not worth an indirect jump to load the exact set of SSE registers needed; zero or all is a good compromise. */ .align 3 LUW3: Lload_sse: movdqa 48(%r10), %xmm0 movdqa 64(%r10), %xmm1 movdqa 80(%r10), %xmm2 movdqa 96(%r10), %xmm3 movdqa 112(%r10), %xmm4 movdqa 128(%r10), %xmm5 movdqa 144(%r10), %xmm6 movdqa 160(%r10), %xmm7 jmp Lret_from_load_sse LUW4: .align 3 .globl _ffi_closure_unix64 _ffi_closure_unix64: LUW5: /* The carry flag is set by the trampoline iff SSE registers are used. Don't clobber it before the branch instruction. */ leaq -200(%rsp), %rsp LUW6: movq %rdi, (%rsp) movq %rsi, 8(%rsp) movq %rdx, 16(%rsp) movq %rcx, 24(%rsp) movq %r8, 32(%rsp) movq %r9, 40(%rsp) jc Lsave_sse Lret_from_save_sse: movq %r10, %rdi leaq 176(%rsp), %rsi movq %rsp, %rdx leaq 208(%rsp), %rcx call _ffi_closure_unix64_inner /* Deallocate stack frame early; return value is now in redzone. */ addq $200, %rsp LUW7: /* The first byte of the return value contains the FFI_TYPE. */ movzbl %al, %r10d leaq Lload_table(%rip), %r11 movslq (%r11, %r10, 4), %r10 addq %r11, %r10 jmp *%r10 Lload_table: .long Lld_void-Lload_table /* FFI_TYPE_VOID */ .long Lld_int32-Lload_table /* FFI_TYPE_INT */ .long Lld_float-Lload_table /* FFI_TYPE_FLOAT */ .long Lld_double-Lload_table /* FFI_TYPE_DOUBLE */ .long Lld_ldouble-Lload_table /* FFI_TYPE_LONGDOUBLE */ .long Lld_int8-Lload_table /* FFI_TYPE_UINT8 */ .long Lld_int8-Lload_table /* FFI_TYPE_SINT8 */ .long Lld_int16-Lload_table /* FFI_TYPE_UINT16 */ .long Lld_int16-Lload_table /* FFI_TYPE_SINT16 */ .long Lld_int32-Lload_table /* FFI_TYPE_UINT32 */ .long Lld_int32-Lload_table /* FFI_TYPE_SINT32 */ .long Lld_int64-Lload_table /* FFI_TYPE_UINT64 */ .long Lld_int64-Lload_table /* FFI_TYPE_SINT64 */ .long Lld_struct-Lload_table /* FFI_TYPE_STRUCT */ .long Lld_int64-Lload_table /* FFI_TYPE_POINTER */ .text .align 3 Lld_void: ret .align 3 Lld_int8: movzbl -24(%rsp), %eax ret .align 3 Lld_int16: movzwl -24(%rsp), %eax ret .align 3 Lld_int32: movl -24(%rsp), %eax ret .align 3 Lld_int64: movq -24(%rsp), %rax ret .align 3 Lld_float: movss -24(%rsp), %xmm0 ret .align 3 Lld_double: movsd -24(%rsp), %xmm0 ret .align 3 Lld_ldouble: fldt -24(%rsp) ret .align 3 Lld_struct: /* There are four possibilities here, %rax/%rdx, %xmm0/%rax, %rax/%xmm0, %xmm0/%xmm1. We collapse two by always loading both rdx and xmm1 with the second word. For the remaining, bit 8 set means xmm0 gets the second word, and bit 9 means that rax gets the second word. */ movq -24(%rsp), %rcx movq -16(%rsp), %rdx movq -16(%rsp), %xmm1 testl $0x100, %eax cmovnz %rdx, %rcx movd %rcx, %xmm0 testl $0x200, %eax movq -24(%rsp), %rax cmovnz %rdx, %rax ret /* See the comment above Lload_sse; the same logic applies here. */ .align 3 LUW8: Lsave_sse: movdqa %xmm0, 48(%rsp) movdqa %xmm1, 64(%rsp) movdqa %xmm2, 80(%rsp) movdqa %xmm3, 96(%rsp) movdqa %xmm4, 112(%rsp) movdqa %xmm5, 128(%rsp) movdqa %xmm6, 144(%rsp) movdqa %xmm7, 160(%rsp) jmp Lret_from_save_sse LUW9: .section __TEXT,__eh_frame,coalesced,no_toc+strip_static_syms+live_support EH_frame1: .set L$set$0,LECIE1-LSCIE1 /* CIE Length */ .long L$set$0 LSCIE1: .long 0x0 /* CIE Identifier Tag */ .byte 0x1 /* CIE Version */ .ascii "zR\0" /* CIE Augmentation */ .byte 0x1 /* uleb128 0x1; CIE Code Alignment Factor */ .byte 0x78 /* sleb128 -8; CIE Data Alignment Factor */ .byte 0x10 /* CIE RA Column */ .byte 0x1 /* uleb128 0x1; Augmentation size */ .byte 0x10 /* FDE Encoding (pcrel sdata4) */ .byte 0xc /* DW_CFA_def_cfa, %rsp offset 8 */ .byte 0x7 /* uleb128 0x7 */ .byte 0x8 /* uleb128 0x8 */ .byte 0x90 /* DW_CFA_offset, column 0x10 */ .byte 0x1 .align 3 LECIE1: .globl _ffi_call_unix64.eh _ffi_call_unix64.eh: LSFDE1: .set L$set$1,LEFDE1-LASFDE1 /* FDE Length */ .long L$set$1 LASFDE1: .long LASFDE1-EH_frame1 /* FDE CIE offset */ .quad LUW0-. /* FDE initial location */ .set L$set$2,LUW4-LUW0 /* FDE address range */ .quad L$set$2 .byte 0x0 /* Augmentation size */ .byte 0x4 /* DW_CFA_advance_loc4 */ .set L$set$3,LUW1-LUW0 .long L$set$3 /* New stack frame based off rbp. This is a itty bit of unwind trickery in that the CFA *has* changed. There is no easy way to describe it correctly on entry to the function. Fortunately, it doesn't matter too much since at all points we can correctly unwind back to ffi_call. Note that the location to which we moved the return address is (the new) CFA-8, so from the perspective of the unwind info, it hasn't moved. */ .byte 0xc /* DW_CFA_def_cfa, %rbp offset 32 */ .byte 0x6 .byte 0x20 .byte 0x80+6 /* DW_CFA_offset, %rbp offset 2*-8 */ .byte 0x2 .byte 0xa /* DW_CFA_remember_state */ .byte 0x4 /* DW_CFA_advance_loc4 */ .set L$set$4,LUW2-LUW1 .long L$set$4 .byte 0xc /* DW_CFA_def_cfa, %rsp offset 8 */ .byte 0x7 .byte 0x8 .byte 0xc0+6 /* DW_CFA_restore, %rbp */ .byte 0x4 /* DW_CFA_advance_loc4 */ .set L$set$5,LUW3-LUW2 .long L$set$5 .byte 0xb /* DW_CFA_restore_state */ .align 3 LEFDE1: .globl _ffi_closure_unix64.eh _ffi_closure_unix64.eh: LSFDE3: .set L$set$6,LEFDE3-LASFDE3 /* FDE Length */ .long L$set$6 LASFDE3: .long LASFDE3-EH_frame1 /* FDE CIE offset */ .quad LUW5-. /* FDE initial location */ .set L$set$7,LUW9-LUW5 /* FDE address range */ .quad L$set$7 .byte 0x0 /* Augmentation size */ .byte 0x4 /* DW_CFA_advance_loc4 */ .set L$set$8,LUW6-LUW5 .long L$set$8 .byte 0xe /* DW_CFA_def_cfa_offset */ .byte 208,1 /* uleb128 208 */ .byte 0xa /* DW_CFA_remember_state */ .byte 0x4 /* DW_CFA_advance_loc4 */ .set L$set$9,LUW7-LUW6 .long L$set$9 .byte 0xe /* DW_CFA_def_cfa_offset */ .byte 0x8 .byte 0x4 /* DW_CFA_advance_loc4 */ .set L$set$10,LUW8-LUW7 .long L$set$10 .byte 0xb /* DW_CFA_restore_state */ .align 3 LEFDE3: .subsections_via_symbols #endif /* __x86_64__ */ smalltalk-3.2.5/libffi/src/x86/sysv.S0000644000175000017500000002670712130343734014241 00000000000000/* ----------------------------------------------------------------------- sysv.S - Copyright (c) 1996, 1998, 2001-2003, 2005, 2008, 2010 Red Hat, Inc. X86 Foreign Function Interface Permission is hereby granted, free of charge, to any person obtaining a copy of this software and associated documentation files (the ``Software''), to deal in the Software without restriction, including without limitation the rights to use, copy, modify, merge, publish, distribute, sublicense, and/or sell copies of the Software, and to permit persons to whom the Software is furnished to do so, subject to the following conditions: The above copyright notice and this permission notice shall be included in all copies or substantial portions of the Software. THE SOFTWARE IS PROVIDED ``AS IS'', WITHOUT WARRANTY OF ANY KIND, EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. ----------------------------------------------------------------------- */ #ifndef __x86_64__ #define LIBFFI_ASM #include #include .text .globl ffi_prep_args .align 4 .globl ffi_call_SYSV .type ffi_call_SYSV,@function ffi_call_SYSV: .LFB1: pushl %ebp .LCFI0: movl %esp,%ebp .LCFI1: /* Make room for all of the new args. */ movl 16(%ebp),%ecx subl %ecx,%esp /* Align the stack pointer to 16-bytes */ andl $0xfffffff0, %esp movl %esp,%eax /* Place all of the ffi_prep_args in position */ pushl 12(%ebp) pushl %eax call *8(%ebp) /* Return stack to previous state and call the function */ addl $8,%esp call *28(%ebp) /* Load %ecx with the return type code */ movl 20(%ebp),%ecx /* Protect %esi. We're going to pop it in the epilogue. */ pushl %esi /* If the return value pointer is NULL, assume no return value. */ cmpl $0,24(%ebp) jne 0f /* Even if there is no space for the return value, we are obliged to handle floating-point values. */ cmpl $FFI_TYPE_FLOAT,%ecx jne noretval fstp %st(0) jmp epilogue 0: call 1f .Lstore_table: .long noretval-.Lstore_table /* FFI_TYPE_VOID */ .long retint-.Lstore_table /* FFI_TYPE_INT */ .long retfloat-.Lstore_table /* FFI_TYPE_FLOAT */ .long retdouble-.Lstore_table /* FFI_TYPE_DOUBLE */ .long retlongdouble-.Lstore_table /* FFI_TYPE_LONGDOUBLE */ .long retuint8-.Lstore_table /* FFI_TYPE_UINT8 */ .long retsint8-.Lstore_table /* FFI_TYPE_SINT8 */ .long retuint16-.Lstore_table /* FFI_TYPE_UINT16 */ .long retsint16-.Lstore_table /* FFI_TYPE_SINT16 */ .long retint-.Lstore_table /* FFI_TYPE_UINT32 */ .long retint-.Lstore_table /* FFI_TYPE_SINT32 */ .long retint64-.Lstore_table /* FFI_TYPE_UINT64 */ .long retint64-.Lstore_table /* FFI_TYPE_SINT64 */ .long retstruct-.Lstore_table /* FFI_TYPE_STRUCT */ .long retint-.Lstore_table /* FFI_TYPE_POINTER */ 1: pop %esi add (%esi, %ecx, 4), %esi jmp *%esi /* Sign/zero extend as appropriate. */ retsint8: movsbl %al, %eax jmp retint retsint16: movswl %ax, %eax jmp retint retuint8: movzbl %al, %eax jmp retint retuint16: movzwl %ax, %eax jmp retint retfloat: /* Load %ecx with the pointer to storage for the return value */ movl 24(%ebp),%ecx fstps (%ecx) jmp epilogue retdouble: /* Load %ecx with the pointer to storage for the return value */ movl 24(%ebp),%ecx fstpl (%ecx) jmp epilogue retlongdouble: /* Load %ecx with the pointer to storage for the return value */ movl 24(%ebp),%ecx fstpt (%ecx) jmp epilogue retint64: /* Load %ecx with the pointer to storage for the return value */ movl 24(%ebp),%ecx movl %eax,0(%ecx) movl %edx,4(%ecx) jmp epilogue retint: /* Load %ecx with the pointer to storage for the return value */ movl 24(%ebp),%ecx movl %eax,0(%ecx) retstruct: /* Nothing to do! */ noretval: epilogue: popl %esi movl %ebp,%esp popl %ebp ret .LFE1: .ffi_call_SYSV_end: .size ffi_call_SYSV,.ffi_call_SYSV_end-ffi_call_SYSV .align 4 FFI_HIDDEN (ffi_closure_SYSV) .globl ffi_closure_SYSV .type ffi_closure_SYSV, @function ffi_closure_SYSV: .LFB2: pushl %ebp .LCFI2: movl %esp, %ebp .LCFI3: subl $40, %esp leal -24(%ebp), %edx movl %edx, -12(%ebp) /* resp */ leal 8(%ebp), %edx movl %edx, 4(%esp) /* args = __builtin_dwarf_cfa () */ leal -12(%ebp), %edx movl %edx, (%esp) /* &resp */ #if defined HAVE_HIDDEN_VISIBILITY_ATTRIBUTE || !defined __PIC__ call ffi_closure_SYSV_inner #else movl %ebx, 8(%esp) .LCFI7: call 1f 1: popl %ebx addl $_GLOBAL_OFFSET_TABLE_+[.-1b], %ebx call ffi_closure_SYSV_inner@PLT movl 8(%esp), %ebx #endif movl -12(%ebp), %ecx cmpl $FFI_TYPE_INT, %eax je .Lcls_retint /* Handle FFI_TYPE_UINT8, FFI_TYPE_SINT8, FFI_TYPE_UINT16, FFI_TYPE_SINT16, FFI_TYPE_UINT32, FFI_TYPE_SINT32. */ cmpl $FFI_TYPE_UINT64, %eax jge 0f cmpl $FFI_TYPE_UINT8, %eax jge .Lcls_retint 0: cmpl $FFI_TYPE_FLOAT, %eax je .Lcls_retfloat cmpl $FFI_TYPE_DOUBLE, %eax je .Lcls_retdouble cmpl $FFI_TYPE_LONGDOUBLE, %eax je .Lcls_retldouble cmpl $FFI_TYPE_SINT64, %eax je .Lcls_retllong cmpl $FFI_TYPE_STRUCT, %eax je .Lcls_retstruct .Lcls_epilogue: movl %ebp, %esp popl %ebp ret .Lcls_retint: movl (%ecx), %eax jmp .Lcls_epilogue .Lcls_retfloat: flds (%ecx) jmp .Lcls_epilogue .Lcls_retdouble: fldl (%ecx) jmp .Lcls_epilogue .Lcls_retldouble: fldt (%ecx) jmp .Lcls_epilogue .Lcls_retllong: movl (%ecx), %eax movl 4(%ecx), %edx jmp .Lcls_epilogue .Lcls_retstruct: movl %ebp, %esp popl %ebp ret $4 .LFE2: .size ffi_closure_SYSV, .-ffi_closure_SYSV #if !FFI_NO_RAW_API /* Precalculate for e.g. the Solaris 10/x86 assembler. */ #if FFI_TRAMPOLINE_SIZE == 10 #define RAW_CLOSURE_CIF_OFFSET 12 #define RAW_CLOSURE_FUN_OFFSET 16 #define RAW_CLOSURE_USER_DATA_OFFSET 20 #elif FFI_TRAMPOLINE_SIZE == 24 #define RAW_CLOSURE_CIF_OFFSET 24 #define RAW_CLOSURE_FUN_OFFSET 28 #define RAW_CLOSURE_USER_DATA_OFFSET 32 #else #define RAW_CLOSURE_CIF_OFFSET ((FFI_TRAMPOLINE_SIZE + 3) & ~3) #define RAW_CLOSURE_FUN_OFFSET (RAW_CLOSURE_CIF_OFFSET + 4) #define RAW_CLOSURE_USER_DATA_OFFSET (RAW_CLOSURE_FUN_OFFSET + 4) #endif #define CIF_FLAGS_OFFSET 20 .align 4 FFI_HIDDEN (ffi_closure_raw_SYSV) .globl ffi_closure_raw_SYSV .type ffi_closure_raw_SYSV, @function ffi_closure_raw_SYSV: .LFB3: pushl %ebp .LCFI4: movl %esp, %ebp .LCFI5: pushl %esi .LCFI6: subl $36, %esp movl RAW_CLOSURE_CIF_OFFSET(%eax), %esi /* closure->cif */ movl RAW_CLOSURE_USER_DATA_OFFSET(%eax), %edx /* closure->user_data */ movl %edx, 12(%esp) /* user_data */ leal 8(%ebp), %edx /* __builtin_dwarf_cfa () */ movl %edx, 8(%esp) /* raw_args */ leal -24(%ebp), %edx movl %edx, 4(%esp) /* &res */ movl %esi, (%esp) /* cif */ call *RAW_CLOSURE_FUN_OFFSET(%eax) /* closure->fun */ movl CIF_FLAGS_OFFSET(%esi), %eax /* rtype */ cmpl $FFI_TYPE_INT, %eax je .Lrcls_retint /* Handle FFI_TYPE_UINT8, FFI_TYPE_SINT8, FFI_TYPE_UINT16, FFI_TYPE_SINT16, FFI_TYPE_UINT32, FFI_TYPE_SINT32. */ cmpl $FFI_TYPE_UINT64, %eax jge 0f cmpl $FFI_TYPE_UINT8, %eax jge .Lrcls_retint 0: cmpl $FFI_TYPE_FLOAT, %eax je .Lrcls_retfloat cmpl $FFI_TYPE_DOUBLE, %eax je .Lrcls_retdouble cmpl $FFI_TYPE_LONGDOUBLE, %eax je .Lrcls_retldouble cmpl $FFI_TYPE_SINT64, %eax je .Lrcls_retllong .Lrcls_epilogue: addl $36, %esp popl %esi popl %ebp ret .Lrcls_retint: movl -24(%ebp), %eax jmp .Lrcls_epilogue .Lrcls_retfloat: flds -24(%ebp) jmp .Lrcls_epilogue .Lrcls_retdouble: fldl -24(%ebp) jmp .Lrcls_epilogue .Lrcls_retldouble: fldt -24(%ebp) jmp .Lrcls_epilogue .Lrcls_retllong: movl -24(%ebp), %eax movl -20(%ebp), %edx jmp .Lrcls_epilogue .LFE3: .size ffi_closure_raw_SYSV, .-ffi_closure_raw_SYSV #endif .section .eh_frame,EH_FRAME_FLAGS,@progbits .Lframe1: .long .LECIE1-.LSCIE1 /* Length of Common Information Entry */ .LSCIE1: .long 0x0 /* CIE Identifier Tag */ .byte 0x1 /* CIE Version */ #ifdef HAVE_AS_ASCII_PSEUDO_OP #ifdef __PIC__ .ascii "zR\0" /* CIE Augmentation */ #else .ascii "\0" /* CIE Augmentation */ #endif #elif defined HAVE_AS_STRING_PSEUDO_OP #ifdef __PIC__ .string "zR" /* CIE Augmentation */ #else .string "" /* CIE Augmentation */ #endif #else #error missing .ascii/.string #endif .byte 0x1 /* .uleb128 0x1; CIE Code Alignment Factor */ .byte 0x7c /* .sleb128 -4; CIE Data Alignment Factor */ .byte 0x8 /* CIE RA Column */ #ifdef __PIC__ .byte 0x1 /* .uleb128 0x1; Augmentation size */ .byte 0x1b /* FDE Encoding (pcrel sdata4) */ #endif .byte 0xc /* DW_CFA_def_cfa */ .byte 0x4 /* .uleb128 0x4 */ .byte 0x4 /* .uleb128 0x4 */ .byte 0x88 /* DW_CFA_offset, column 0x8 */ .byte 0x1 /* .uleb128 0x1 */ .align 4 .LECIE1: .LSFDE1: .long .LEFDE1-.LASFDE1 /* FDE Length */ .LASFDE1: .long .LASFDE1-.Lframe1 /* FDE CIE offset */ #if defined __PIC__ && defined HAVE_AS_X86_PCREL .long .LFB1-. /* FDE initial location */ #elif defined __PIC__ .long .LFB1@rel #else .long .LFB1 #endif .long .LFE1-.LFB1 /* FDE address range */ #ifdef __PIC__ .byte 0x0 /* .uleb128 0x0; Augmentation size */ #endif .byte 0x4 /* DW_CFA_advance_loc4 */ .long .LCFI0-.LFB1 .byte 0xe /* DW_CFA_def_cfa_offset */ .byte 0x8 /* .uleb128 0x8 */ .byte 0x85 /* DW_CFA_offset, column 0x5 */ .byte 0x2 /* .uleb128 0x2 */ .byte 0x4 /* DW_CFA_advance_loc4 */ .long .LCFI1-.LCFI0 .byte 0xd /* DW_CFA_def_cfa_register */ .byte 0x5 /* .uleb128 0x5 */ .align 4 .LEFDE1: .LSFDE2: .long .LEFDE2-.LASFDE2 /* FDE Length */ .LASFDE2: .long .LASFDE2-.Lframe1 /* FDE CIE offset */ #if defined __PIC__ && defined HAVE_AS_X86_PCREL .long .LFB2-. /* FDE initial location */ #elif defined __PIC__ .long .LFB2@rel #else .long .LFB2 #endif .long .LFE2-.LFB2 /* FDE address range */ #ifdef __PIC__ .byte 0x0 /* .uleb128 0x0; Augmentation size */ #endif .byte 0x4 /* DW_CFA_advance_loc4 */ .long .LCFI2-.LFB2 .byte 0xe /* DW_CFA_def_cfa_offset */ .byte 0x8 /* .uleb128 0x8 */ .byte 0x85 /* DW_CFA_offset, column 0x5 */ .byte 0x2 /* .uleb128 0x2 */ .byte 0x4 /* DW_CFA_advance_loc4 */ .long .LCFI3-.LCFI2 .byte 0xd /* DW_CFA_def_cfa_register */ .byte 0x5 /* .uleb128 0x5 */ #if !defined HAVE_HIDDEN_VISIBILITY_ATTRIBUTE && defined __PIC__ .byte 0x4 /* DW_CFA_advance_loc4 */ .long .LCFI7-.LCFI3 .byte 0x83 /* DW_CFA_offset, column 0x3 */ .byte 0xa /* .uleb128 0xa */ #endif .align 4 .LEFDE2: #if !FFI_NO_RAW_API .LSFDE3: .long .LEFDE3-.LASFDE3 /* FDE Length */ .LASFDE3: .long .LASFDE3-.Lframe1 /* FDE CIE offset */ #if defined __PIC__ && defined HAVE_AS_X86_PCREL .long .LFB3-. /* FDE initial location */ #elif defined __PIC__ .long .LFB3@rel #else .long .LFB3 #endif .long .LFE3-.LFB3 /* FDE address range */ #ifdef __PIC__ .byte 0x0 /* .uleb128 0x0; Augmentation size */ #endif .byte 0x4 /* DW_CFA_advance_loc4 */ .long .LCFI4-.LFB3 .byte 0xe /* DW_CFA_def_cfa_offset */ .byte 0x8 /* .uleb128 0x8 */ .byte 0x85 /* DW_CFA_offset, column 0x5 */ .byte 0x2 /* .uleb128 0x2 */ .byte 0x4 /* DW_CFA_advance_loc4 */ .long .LCFI5-.LCFI4 .byte 0xd /* DW_CFA_def_cfa_register */ .byte 0x5 /* .uleb128 0x5 */ .byte 0x4 /* DW_CFA_advance_loc4 */ .long .LCFI6-.LCFI5 .byte 0x86 /* DW_CFA_offset, column 0x6 */ .byte 0x3 /* .uleb128 0x3 */ .align 4 .LEFDE3: #endif #endif /* ifndef __x86_64__ */ #if defined __ELF__ && defined __linux__ .section .note.GNU-stack,"",@progbits #endif smalltalk-3.2.5/libffi/src/x86/ffi.c0000644000175000017500000004476712130343734014027 00000000000000/* ----------------------------------------------------------------------- ffi.c - Copyright (c) 1996, 1998, 1999, 2001, 2007, 2008 Red Hat, Inc. Copyright (c) 2002 Ranjit Mathew Copyright (c) 2002 Bo Thorsen Copyright (c) 2002 Roger Sayle Copyright (C) 2008 Free Software Foundation, Inc. x86 Foreign Function Interface Permission is hereby granted, free of charge, to any person obtaining a copy of this software and associated documentation files (the ``Software''), to deal in the Software without restriction, including without limitation the rights to use, copy, modify, merge, publish, distribute, sublicense, and/or sell copies of the Software, and to permit persons to whom the Software is furnished to do so, subject to the following conditions: The above copyright notice and this permission notice shall be included in all copies or substantial portions of the Software. THE SOFTWARE IS PROVIDED ``AS IS'', WITHOUT WARRANTY OF ANY KIND, EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. ----------------------------------------------------------------------- */ #if !defined(__x86_64__) || defined(_WIN64) #ifdef _WIN64 #include #endif #include #include #include /* ffi_prep_args is called by the assembly routine once stack space has been allocated for the function's arguments */ void ffi_prep_args(char *stack, extended_cif *ecif) { register unsigned int i; register void **p_argv; register char *argp; register ffi_type **p_arg; argp = stack; if (ecif->cif->flags == FFI_TYPE_STRUCT #ifdef X86_WIN64 && (ecif->cif->rtype->size != 1 && ecif->cif->rtype->size != 2 && ecif->cif->rtype->size != 4 && ecif->cif->rtype->size != 8) #endif ) { *(void **) argp = ecif->rvalue; argp += sizeof(void*); } p_argv = ecif->avalue; for (i = ecif->cif->nargs, p_arg = ecif->cif->arg_types; i != 0; i--, p_arg++) { size_t z; /* Align if necessary */ if ((sizeof(void*) - 1) & (size_t) argp) argp = (char *) ALIGN(argp, sizeof(void*)); z = (*p_arg)->size; #ifdef X86_WIN64 if (z > sizeof(ffi_arg) || ((*p_arg)->type == FFI_TYPE_STRUCT && (z != 1 && z != 2 && z != 4 && z != 8)) #if FFI_TYPE_DOUBLE != FFI_TYPE_LONGDOUBLE || ((*p_arg)->type == FFI_TYPE_LONGDOUBLE) #endif ) { z = sizeof(ffi_arg); *(void **)argp = *p_argv; } else if ((*p_arg)->type == FFI_TYPE_FLOAT) { memcpy(argp, *p_argv, z); } else #endif if (z < sizeof(ffi_arg)) { z = sizeof(ffi_arg); switch ((*p_arg)->type) { case FFI_TYPE_SINT8: *(ffi_sarg *) argp = (ffi_sarg)*(SINT8 *)(* p_argv); break; case FFI_TYPE_UINT8: *(ffi_arg *) argp = (ffi_arg)*(UINT8 *)(* p_argv); break; case FFI_TYPE_SINT16: *(ffi_sarg *) argp = (ffi_sarg)*(SINT16 *)(* p_argv); break; case FFI_TYPE_UINT16: *(ffi_arg *) argp = (ffi_arg)*(UINT16 *)(* p_argv); break; case FFI_TYPE_SINT32: *(ffi_sarg *) argp = (ffi_sarg)*(SINT32 *)(* p_argv); break; case FFI_TYPE_UINT32: *(ffi_arg *) argp = (ffi_arg)*(UINT32 *)(* p_argv); break; case FFI_TYPE_STRUCT: *(ffi_arg *) argp = *(ffi_arg *)(* p_argv); break; default: FFI_ASSERT(0); } } else { memcpy(argp, *p_argv, z); } p_argv++; #ifdef X86_WIN64 argp += (z + sizeof(void*) - 1) & ~(sizeof(void*) - 1); #else argp += z; #endif } return; } /* Perform machine dependent cif processing */ ffi_status ffi_prep_cif_machdep(ffi_cif *cif) { unsigned int i; ffi_type **ptr; /* Set the return type flag */ switch (cif->rtype->type) { case FFI_TYPE_VOID: #if defined(X86) || defined (X86_WIN32) || defined(X86_FREEBSD) || defined(X86_DARWIN) || defined(X86_WIN64) case FFI_TYPE_UINT8: case FFI_TYPE_UINT16: case FFI_TYPE_SINT8: case FFI_TYPE_SINT16: #endif #ifdef X86_WIN64 case FFI_TYPE_UINT32: case FFI_TYPE_SINT32: #endif case FFI_TYPE_SINT64: case FFI_TYPE_FLOAT: case FFI_TYPE_DOUBLE: #ifndef X86_WIN64 #if FFI_TYPE_DOUBLE != FFI_TYPE_LONGDOUBLE case FFI_TYPE_LONGDOUBLE: #endif #endif cif->flags = (unsigned) cif->rtype->type; break; case FFI_TYPE_UINT64: #ifdef X86_WIN64 case FFI_TYPE_POINTER: #endif cif->flags = FFI_TYPE_SINT64; break; case FFI_TYPE_STRUCT: #ifndef X86 if (cif->rtype->size == 1) { cif->flags = FFI_TYPE_SMALL_STRUCT_1B; /* same as char size */ } else if (cif->rtype->size == 2) { cif->flags = FFI_TYPE_SMALL_STRUCT_2B; /* same as short size */ } else if (cif->rtype->size == 4) { #ifdef X86_WIN64 cif->flags = FFI_TYPE_SMALL_STRUCT_4B; #else cif->flags = FFI_TYPE_INT; /* same as int type */ #endif } else if (cif->rtype->size == 8) { cif->flags = FFI_TYPE_SINT64; /* same as int64 type */ } else #endif { cif->flags = FFI_TYPE_STRUCT; /* allocate space for return value pointer */ cif->bytes += ALIGN(sizeof(void*), FFI_SIZEOF_ARG); } break; default: #ifdef X86_WIN64 cif->flags = FFI_TYPE_SINT64; break; case FFI_TYPE_INT: cif->flags = FFI_TYPE_SINT32; #else cif->flags = FFI_TYPE_INT; #endif break; } for (ptr = cif->arg_types, i = cif->nargs; i > 0; i--, ptr++) { if (((*ptr)->alignment - 1) & cif->bytes) cif->bytes = ALIGN(cif->bytes, (*ptr)->alignment); cif->bytes += ALIGN((*ptr)->size, FFI_SIZEOF_ARG); } #ifdef X86_WIN64 /* ensure space for storing four registers */ cif->bytes += 4 * sizeof(ffi_arg); #endif #ifdef X86_DARWIN cif->bytes = (cif->bytes + 15) & ~0xF; #endif return FFI_OK; } #ifdef X86_WIN64 extern int ffi_call_win64(void (*)(char *, extended_cif *), extended_cif *, unsigned, unsigned, unsigned *, void (*fn)(void)); #elif defined(X86_WIN32) extern void ffi_call_win32(void (*)(char *, extended_cif *), extended_cif *, unsigned, unsigned, unsigned *, void (*fn)(void)); #else extern void ffi_call_SYSV(void (*)(char *, extended_cif *), extended_cif *, unsigned, unsigned, unsigned *, void (*fn)(void)); #endif void ffi_call(ffi_cif *cif, void (*fn)(void), void *rvalue, void **avalue) { extended_cif ecif; ecif.cif = cif; ecif.avalue = avalue; /* If the return value is a struct and we don't have a return */ /* value address then we need to make one */ #ifdef X86_WIN64 if (rvalue == NULL && cif->flags == FFI_TYPE_STRUCT && cif->rtype->size != 1 && cif->rtype->size != 2 && cif->rtype->size != 4 && cif->rtype->size != 8) { ecif.rvalue = alloca((cif->rtype->size + 0xF) & ~0xF); } #else if (rvalue == NULL && cif->flags == FFI_TYPE_STRUCT) { ecif.rvalue = alloca(cif->rtype->size); } #endif else ecif.rvalue = rvalue; switch (cif->abi) { #ifdef X86_WIN64 case FFI_WIN64: { /* Make copies of all struct arguments NOTE: not sure if responsibility should be here or in caller */ unsigned int i; for (i=0; i < cif->nargs;i++) { size_t size = cif->arg_types[i]->size; if ((cif->arg_types[i]->type == FFI_TYPE_STRUCT && (size != 1 && size != 2 && size != 4 && size != 8)) #if FFI_TYPE_LONGDOUBLE != FFI_TYPE_DOUBLE || cif->arg_types[i]->type == FFI_TYPE_LONGDOUBLE #endif ) { void *local = alloca(size); memcpy(local, avalue[i], size); avalue[i] = local; } } ffi_call_win64(ffi_prep_args, &ecif, cif->bytes, cif->flags, ecif.rvalue, fn); } break; #elif defined(X86_WIN32) case FFI_SYSV: case FFI_STDCALL: ffi_call_win32(ffi_prep_args, &ecif, cif->bytes, cif->flags, ecif.rvalue, fn); break; #else case FFI_SYSV: ffi_call_SYSV(ffi_prep_args, &ecif, cif->bytes, cif->flags, ecif.rvalue, fn); break; #endif default: FFI_ASSERT(0); break; } } /** private members **/ /* The following __attribute__((regparm(1))) decorations will have no effect on MSVC - standard cdecl convention applies. */ static void ffi_prep_incoming_args_SYSV (char *stack, void **ret, void** args, ffi_cif* cif); void FFI_HIDDEN ffi_closure_SYSV (ffi_closure *) __attribute__ ((regparm(1))); unsigned int FFI_HIDDEN ffi_closure_SYSV_inner (ffi_closure *, void **, void *) __attribute__ ((regparm(1))); void FFI_HIDDEN ffi_closure_raw_SYSV (ffi_raw_closure *) __attribute__ ((regparm(1))); #ifdef X86_WIN32 void FFI_HIDDEN ffi_closure_STDCALL (ffi_closure *) __attribute__ ((regparm(1))); #endif #ifdef X86_WIN64 void FFI_HIDDEN ffi_closure_win64 (ffi_closure *); #endif /* This function is jumped to by the trampoline */ #ifdef X86_WIN64 void * FFI_HIDDEN ffi_closure_win64_inner (ffi_closure *closure, void *args) { ffi_cif *cif; void **arg_area; void *result; void *resp = &result; cif = closure->cif; arg_area = (void**) alloca (cif->nargs * sizeof (void*)); /* this call will initialize ARG_AREA, such that each * element in that array points to the corresponding * value on the stack; and if the function returns * a structure, it will change RESP to point to the * structure return address. */ ffi_prep_incoming_args_SYSV(args, &resp, arg_area, cif); (closure->fun) (cif, resp, arg_area, closure->user_data); /* The result is returned in rax. This does the right thing for result types except for floats; we have to 'mov xmm0, rax' in the caller to correct this. TODO: structure sizes of 3 5 6 7 are returned by reference, too!!! */ return cif->rtype->size > sizeof(void *) ? resp : *(void **)resp; } #else unsigned int FFI_HIDDEN __attribute__ ((regparm(1))) ffi_closure_SYSV_inner (ffi_closure *closure, void **respp, void *args) { /* our various things... */ ffi_cif *cif; void **arg_area; cif = closure->cif; arg_area = (void**) alloca (cif->nargs * sizeof (void*)); /* this call will initialize ARG_AREA, such that each * element in that array points to the corresponding * value on the stack; and if the function returns * a structure, it will change RESP to point to the * structure return address. */ ffi_prep_incoming_args_SYSV(args, respp, arg_area, cif); (closure->fun) (cif, *respp, arg_area, closure->user_data); return cif->flags; } #endif /* !X86_WIN64 */ static void ffi_prep_incoming_args_SYSV(char *stack, void **rvalue, void **avalue, ffi_cif *cif) { register unsigned int i; register void **p_argv; register char *argp; register ffi_type **p_arg; argp = stack; #ifdef X86_WIN64 if (cif->rtype->size > sizeof(ffi_arg) || (cif->flags == FFI_TYPE_STRUCT && (cif->rtype->size != 1 && cif->rtype->size != 2 && cif->rtype->size != 4 && cif->rtype->size != 8))) { *rvalue = *(void **) argp; argp += sizeof(void *); } #else if ( cif->flags == FFI_TYPE_STRUCT ) { *rvalue = *(void **) argp; argp += sizeof(void *); } #endif p_argv = avalue; for (i = cif->nargs, p_arg = cif->arg_types; (i != 0); i--, p_arg++) { size_t z; /* Align if necessary */ if ((sizeof(void*) - 1) & (size_t) argp) { argp = (char *) ALIGN(argp, sizeof(void*)); } #ifdef X86_WIN64 if ((*p_arg)->size > sizeof(ffi_arg) || ((*p_arg)->type == FFI_TYPE_STRUCT && ((*p_arg)->size != 1 && (*p_arg)->size != 2 && (*p_arg)->size != 4 && (*p_arg)->size != 8))) { z = sizeof(void *); *p_argv = *(void **)argp; } else #endif { z = (*p_arg)->size; /* because we're little endian, this is what it turns into. */ *p_argv = (void*) argp; } p_argv++; #ifdef X86_WIN64 argp += (z + sizeof(void*) - 1) & ~(sizeof(void*) - 1); #else argp += z; #endif } return; } #define FFI_INIT_TRAMPOLINE_WIN64(TRAMP,FUN,CTX,MASK) \ { unsigned char *__tramp = (unsigned char*)(TRAMP); \ void* __fun = (void*)(FUN); \ void* __ctx = (void*)(CTX); \ *(unsigned char*) &__tramp[0] = 0x41; \ *(unsigned char*) &__tramp[1] = 0xbb; \ *(unsigned int*) &__tramp[2] = MASK; /* mov $mask, %r11 */ \ *(unsigned char*) &__tramp[6] = 0x48; \ *(unsigned char*) &__tramp[7] = 0xb8; \ *(void**) &__tramp[8] = __ctx; /* mov __ctx, %rax */ \ *(unsigned char *) &__tramp[16] = 0x49; \ *(unsigned char *) &__tramp[17] = 0xba; \ *(void**) &__tramp[18] = __fun; /* mov __fun, %r10 */ \ *(unsigned char *) &__tramp[26] = 0x41; \ *(unsigned char *) &__tramp[27] = 0xff; \ *(unsigned char *) &__tramp[28] = 0xe2; /* jmp %r10 */ \ } /* How to make a trampoline. Derived from gcc/config/i386/i386.c. */ #define FFI_INIT_TRAMPOLINE(TRAMP,FUN,CTX) \ { unsigned char *__tramp = (unsigned char*)(TRAMP); \ unsigned int __fun = (unsigned int)(FUN); \ unsigned int __ctx = (unsigned int)(CTX); \ unsigned int __dis = __fun - (__ctx + 10); \ *(unsigned char*) &__tramp[0] = 0xb8; \ *(unsigned int*) &__tramp[1] = __ctx; /* movl __ctx, %eax */ \ *(unsigned char *) &__tramp[5] = 0xe9; \ *(unsigned int*) &__tramp[6] = __dis; /* jmp __fun */ \ } #define FFI_INIT_TRAMPOLINE_STDCALL(TRAMP,FUN,CTX,SIZE) \ { unsigned char *__tramp = (unsigned char*)(TRAMP); \ unsigned int __fun = (unsigned int)(FUN); \ unsigned int __ctx = (unsigned int)(CTX); \ unsigned int __dis = __fun - (__ctx + 10); \ unsigned short __size = (unsigned short)(SIZE); \ *(unsigned char*) &__tramp[0] = 0xb8; \ *(unsigned int*) &__tramp[1] = __ctx; /* movl __ctx, %eax */ \ *(unsigned char *) &__tramp[5] = 0xe8; \ *(unsigned int*) &__tramp[6] = __dis; /* call __fun */ \ *(unsigned char *) &__tramp[10] = 0xc2; \ *(unsigned short*) &__tramp[11] = __size; /* ret __size */ \ } /* the cif must already be prep'ed */ ffi_status ffi_prep_closure_loc (ffi_closure* closure, ffi_cif* cif, void (*fun)(ffi_cif*,void*,void**,void*), void *user_data, void *codeloc) { #ifdef X86_WIN64 #define ISFLOAT(IDX) (cif->arg_types[IDX]->type == FFI_TYPE_FLOAT || cif->arg_types[IDX]->type == FFI_TYPE_DOUBLE) #define FLAG(IDX) (cif->nargs>(IDX)&&ISFLOAT(IDX)?(1<<(IDX)):0) if (cif->abi == FFI_WIN64) { int mask = FLAG(0)|FLAG(1)|FLAG(2)|FLAG(3); FFI_INIT_TRAMPOLINE_WIN64 (&closure->tramp[0], &ffi_closure_win64, codeloc, mask); /* make sure we can execute here */ } #else if (cif->abi == FFI_SYSV) { FFI_INIT_TRAMPOLINE (&closure->tramp[0], &ffi_closure_SYSV, (void*)codeloc); } #ifdef X86_WIN32 else if (cif->abi == FFI_STDCALL) { FFI_INIT_TRAMPOLINE_STDCALL (&closure->tramp[0], &ffi_closure_STDCALL, (void*)codeloc, cif->bytes); } #endif /* X86_WIN32 */ #endif /* !X86_WIN64 */ else { return FFI_BAD_ABI; } closure->cif = cif; closure->user_data = user_data; closure->fun = fun; return FFI_OK; } /* ------- Native raw API support -------------------------------- */ #if !FFI_NO_RAW_API ffi_status ffi_prep_raw_closure_loc (ffi_raw_closure* closure, ffi_cif* cif, void (*fun)(ffi_cif*,void*,ffi_raw*,void*), void *user_data, void *codeloc) { int i; if (cif->abi != FFI_SYSV) { return FFI_BAD_ABI; } /* we currently don't support certain kinds of arguments for raw closures. This should be implemented by a separate assembly language routine, since it would require argument processing, something we don't do now for performance. */ for (i = cif->nargs-1; i >= 0; i--) { FFI_ASSERT (cif->arg_types[i]->type != FFI_TYPE_STRUCT); FFI_ASSERT (cif->arg_types[i]->type != FFI_TYPE_LONGDOUBLE); } FFI_INIT_TRAMPOLINE (&closure->tramp[0], &ffi_closure_raw_SYSV, codeloc); closure->cif = cif; closure->user_data = user_data; closure->fun = fun; return FFI_OK; } static void ffi_prep_args_raw(char *stack, extended_cif *ecif) { memcpy (stack, ecif->avalue, ecif->cif->bytes); } /* we borrow this routine from libffi (it must be changed, though, to * actually call the function passed in the first argument. as of * libffi-1.20, this is not the case.) */ void ffi_raw_call(ffi_cif *cif, void (*fn)(void), void *rvalue, ffi_raw *fake_avalue) { extended_cif ecif; void **avalue = (void **)fake_avalue; ecif.cif = cif; ecif.avalue = avalue; /* If the return value is a struct and we don't have a return */ /* value address then we need to make one */ if ((rvalue == NULL) && (cif->rtype->type == FFI_TYPE_STRUCT)) { ecif.rvalue = alloca(cif->rtype->size); } else ecif.rvalue = rvalue; switch (cif->abi) { #ifdef X86_WIN32 case FFI_SYSV: case FFI_STDCALL: ffi_call_win32(ffi_prep_args_raw, &ecif, cif->bytes, cif->flags, ecif.rvalue, fn); break; #else case FFI_SYSV: ffi_call_SYSV(ffi_prep_args_raw, &ecif, cif->bytes, cif->flags, ecif.rvalue, fn); break; #endif default: FFI_ASSERT(0); break; } } #endif #endif /* !__x86_64__ || X86_WIN64 */ smalltalk-3.2.5/libffi/src/frv/0000755000175000017500000000000012130456004013320 500000000000000smalltalk-3.2.5/libffi/src/frv/eabi.S0000644000175000017500000000652612130343734014302 00000000000000/* ----------------------------------------------------------------------- eabi.S - Copyright (c) 2004 Anthony Green FR-V Assembly glue. Permission is hereby granted, free of charge, to any person obtaining a copy of this software and associated documentation files (the ``Software''), to deal in the Software without restriction, including without limitation the rights to use, copy, modify, merge, publish, distribute, sublicense, and/or sell copies of the Software, and to permit persons to whom the Software is furnished to do so, subject to the following conditions: The above copyright notice and this permission notice shall be included in all copies or substantial portions of the Software. THE SOFTWARE IS PROVIDED ``AS IS'', WITHOUT WARRANTY OF ANY KIND, EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHOR BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. ----------------------------------------------------------------------- */ #define LIBFFI_ASM #include #include .globl ffi_prep_args_EABI .text .p2align 4 .globl ffi_call_EABI .type ffi_call_EABI, @function # gr8 : ffi_prep_args # gr9 : &ecif # gr10: cif->bytes # gr11: fig->flags # gr12: ecif.rvalue # gr13: fn ffi_call_EABI: addi sp, #-80, sp sti fp, @(sp, #24) addi sp, #24, fp movsg lr, gr5 /* Make room for the new arguments. */ /* subi sp, fp, gr10 */ /* Store return address and incoming args on stack. */ sti gr5, @(fp, #8) sti gr8, @(fp, #-4) sti gr9, @(fp, #-8) sti gr10, @(fp, #-12) sti gr11, @(fp, #-16) sti gr12, @(fp, #-20) sti gr13, @(fp, #-24) sub sp, gr10, sp /* Call ffi_prep_args. */ ldi @(fp, #-4), gr4 addi sp, #0, gr8 ldi @(fp, #-8), gr9 #ifdef __FRV_FDPIC__ ldd @(gr4, gr0), gr14 calll @(gr14, gr0) #else calll @(gr4, gr0) #endif /* ffi_prep_args returns the new stack pointer. */ mov gr8, gr4 ldi @(sp, #0), gr8 ldi @(sp, #4), gr9 ldi @(sp, #8), gr10 ldi @(sp, #12), gr11 ldi @(sp, #16), gr12 ldi @(sp, #20), gr13 /* Always copy the return value pointer into the hidden parameter register. This is only strictly necessary when we're returning an aggregate type, but it doesn't hurt to do this all the time, and it saves a branch. */ ldi @(fp, #-20), gr3 /* Use the ffi_prep_args return value for the new sp. */ mov gr4, sp /* Call the target function. */ ldi @(fp, -24), gr4 #ifdef __FRV_FDPIC__ ldd @(gr4, gr0), gr14 calll @(gr14, gr0) #else calll @(gr4, gr0) #endif /* Store the result. */ ldi @(fp, #-16), gr10 /* fig->flags */ ldi @(fp, #-20), gr4 /* ecif.rvalue */ /* Is the return value stored in two registers? */ cmpi gr10, #8, icc0 bne icc0, 0, .L2 /* Yes, save them. */ sti gr8, @(gr4, #0) sti gr9, @(gr4, #4) bra .L3 .L2: /* Is the return value a structure? */ cmpi gr10, #-1, icc0 beq icc0, 0, .L3 /* No, save a 4 byte return value. */ sti gr8, @(gr4, #0) .L3: /* Restore the stack, and return. */ ldi @(fp, 8), gr5 ld @(fp, gr0), fp addi sp,#80,sp jmpl @(gr5,gr0) .size ffi_call_EABI, .-ffi_call_EABI smalltalk-3.2.5/libffi/src/frv/ffitarget.h0000644000175000017500000000402212130343734015367 00000000000000/* -----------------------------------------------------------------*-C-*- ffitarget.h - Copyright (c) 1996-2004 Red Hat, Inc. Target configuration macros for FR-V Permission is hereby granted, free of charge, to any person obtaining a copy of this software and associated documentation files (the ``Software''), to deal in the Software without restriction, including without limitation the rights to use, copy, modify, merge, publish, distribute, sublicense, and/or sell copies of the Software, and to permit persons to whom the Software is furnished to do so, subject to the following conditions: The above copyright notice and this permission notice shall be included in all copies or substantial portions of the Software. THE SOFTWARE IS PROVIDED ``AS IS'', WITHOUT WARRANTY OF ANY KIND, EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. ----------------------------------------------------------------------- */ #ifndef LIBFFI_TARGET_H #define LIBFFI_TARGET_H /* ---- System specific configurations ----------------------------------- */ #ifndef LIBFFI_ASM typedef unsigned long ffi_arg; typedef signed long ffi_sarg; typedef enum ffi_abi { FFI_FIRST_ABI = 0, #ifdef FRV FFI_EABI, FFI_DEFAULT_ABI = FFI_EABI, #endif FFI_LAST_ABI = FFI_DEFAULT_ABI + 1 } ffi_abi; #endif /* ---- Definitions for closures ----------------------------------------- */ #define FFI_CLOSURES 1 #define FFI_NATIVE_RAW_API 0 #ifdef __FRV_FDPIC__ /* Trampolines are 8 4-byte instructions long. */ #define FFI_TRAMPOLINE_SIZE (8*4) #else /* Trampolines are 5 4-byte instructions long. */ #define FFI_TRAMPOLINE_SIZE (5*4) #endif #endif smalltalk-3.2.5/libffi/src/frv/ffi.c0000644000175000017500000002040012130343734014151 00000000000000/* ----------------------------------------------------------------------- ffi.c - Copyright (C) 2004 Anthony Green Copyright (C) 2007 Free Software Foundation, Inc. Copyright (C) 2008 Red Hat, Inc. FR-V Foreign Function Interface Permission is hereby granted, free of charge, to any person obtaining a copy of this software and associated documentation files (the ``Software''), to deal in the Software without restriction, including without limitation the rights to use, copy, modify, merge, publish, distribute, sublicense, and/or sell copies of the Software, and to permit persons to whom the Software is furnished to do so, subject to the following conditions: The above copyright notice and this permission notice shall be included in all copies or substantial portions of the Software. THE SOFTWARE IS PROVIDED ``AS IS'', WITHOUT WARRANTY OF ANY KIND, EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. ----------------------------------------------------------------------- */ #include #include #include /* ffi_prep_args is called by the assembly routine once stack space has been allocated for the function's arguments */ void *ffi_prep_args(char *stack, extended_cif *ecif) { register unsigned int i; register void **p_argv; register char *argp; register ffi_type **p_arg; register int count = 0; p_argv = ecif->avalue; argp = stack; for (i = ecif->cif->nargs, p_arg = ecif->cif->arg_types; (i != 0); i--, p_arg++) { size_t z; z = (*p_arg)->size; if ((*p_arg)->type == FFI_TYPE_STRUCT) { z = sizeof(void*); *(void **) argp = *p_argv; } /* if ((*p_arg)->type == FFI_TYPE_FLOAT) { if (count > 24) { // This is going on the stack. Turn it into a double. *(double *) argp = (double) *(float*)(* p_argv); z = sizeof(double); } else *(void **) argp = *(void **)(* p_argv); } */ else if (z < sizeof(int)) { z = sizeof(int); switch ((*p_arg)->type) { case FFI_TYPE_SINT8: *(signed int *) argp = (signed int)*(SINT8 *)(* p_argv); break; case FFI_TYPE_UINT8: *(unsigned int *) argp = (unsigned int)*(UINT8 *)(* p_argv); break; case FFI_TYPE_SINT16: *(signed int *) argp = (signed int)*(SINT16 *)(* p_argv); break; case FFI_TYPE_UINT16: *(unsigned int *) argp = (unsigned int)*(UINT16 *)(* p_argv); break; default: FFI_ASSERT(0); } } else if (z == sizeof(int)) { *(unsigned int *) argp = (unsigned int)*(UINT32 *)(* p_argv); } else { memcpy(argp, *p_argv, z); } p_argv++; argp += z; count += z; } return (stack + ((count > 24) ? 24 : ALIGN_DOWN(count, 8))); } /* Perform machine dependent cif processing */ ffi_status ffi_prep_cif_machdep(ffi_cif *cif) { if (cif->rtype->type == FFI_TYPE_STRUCT) cif->flags = -1; else cif->flags = cif->rtype->size; cif->bytes = ALIGN (cif->bytes, 8); return FFI_OK; } extern void ffi_call_EABI(void *(*)(char *, extended_cif *), extended_cif *, unsigned, unsigned, unsigned *, void (*fn)(void)); void ffi_call(ffi_cif *cif, void (*fn)(void), void *rvalue, void **avalue) { extended_cif ecif; ecif.cif = cif; ecif.avalue = avalue; /* If the return value is a struct and we don't have a return */ /* value address then we need to make one */ if ((rvalue == NULL) && (cif->rtype->type == FFI_TYPE_STRUCT)) { ecif.rvalue = alloca(cif->rtype->size); } else ecif.rvalue = rvalue; switch (cif->abi) { case FFI_EABI: ffi_call_EABI(ffi_prep_args, &ecif, cif->bytes, cif->flags, ecif.rvalue, fn); break; default: FFI_ASSERT(0); break; } } void ffi_closure_eabi (unsigned arg1, unsigned arg2, unsigned arg3, unsigned arg4, unsigned arg5, unsigned arg6) { /* This function is called by a trampoline. The trampoline stows a pointer to the ffi_closure object in gr7. We must save this pointer in a place that will persist while we do our work. */ register ffi_closure *creg __asm__ ("gr7"); ffi_closure *closure = creg; /* Arguments that don't fit in registers are found on the stack at a fixed offset above the current frame pointer. */ register char *frame_pointer __asm__ ("fp"); char *stack_args = frame_pointer + 16; /* Lay the register arguments down in a continuous chunk of memory. */ unsigned register_args[6] = { arg1, arg2, arg3, arg4, arg5, arg6 }; ffi_cif *cif = closure->cif; ffi_type **arg_types = cif->arg_types; void **avalue = alloca (cif->nargs * sizeof(void *)); char *ptr = (char *) register_args; int i; /* Find the address of each argument. */ for (i = 0; i < cif->nargs; i++) { switch (arg_types[i]->type) { case FFI_TYPE_SINT8: case FFI_TYPE_UINT8: avalue[i] = ptr + 3; break; case FFI_TYPE_SINT16: case FFI_TYPE_UINT16: avalue[i] = ptr + 2; break; case FFI_TYPE_SINT32: case FFI_TYPE_UINT32: case FFI_TYPE_FLOAT: avalue[i] = ptr; break; case FFI_TYPE_STRUCT: avalue[i] = *(void**)ptr; break; default: /* This is an 8-byte value. */ avalue[i] = ptr; ptr += 4; break; } ptr += 4; /* If we've handled more arguments than fit in registers, start looking at the those passed on the stack. */ if (ptr == ((char *)register_args + (6*4))) ptr = stack_args; } /* Invoke the closure. */ if (cif->rtype->type == FFI_TYPE_STRUCT) { /* The caller allocates space for the return structure, and passes a pointer to this space in gr3. Use this value directly as the return value. */ register void *return_struct_ptr __asm__("gr3"); (closure->fun) (cif, return_struct_ptr, avalue, closure->user_data); } else { /* Allocate space for the return value and call the function. */ long long rvalue; (closure->fun) (cif, &rvalue, avalue, closure->user_data); /* Functions return 4-byte or smaller results in gr8. 8-byte values also use gr9. We fill the both, even for small return values, just to avoid a branch. */ asm ("ldi @(%0, #0), gr8" : : "r" (&rvalue)); asm ("ldi @(%0, #0), gr9" : : "r" (&((int *) &rvalue)[1])); } } ffi_status ffi_prep_closure_loc (ffi_closure* closure, ffi_cif* cif, void (*fun)(ffi_cif*, void*, void**, void*), void *user_data, void *codeloc) { unsigned int *tramp = (unsigned int *) &closure->tramp[0]; unsigned long fn = (long) ffi_closure_eabi; unsigned long cls = (long) codeloc; #ifdef __FRV_FDPIC__ register void *got __asm__("gr15"); #endif int i; fn = (unsigned long) ffi_closure_eabi; #ifdef __FRV_FDPIC__ tramp[0] = &((unsigned int *)codeloc)[2]; tramp[1] = got; tramp[2] = 0x8cfc0000 + (fn & 0xffff); /* setlos lo(fn), gr6 */ tramp[3] = 0x8efc0000 + (cls & 0xffff); /* setlos lo(cls), gr7 */ tramp[4] = 0x8cf80000 + (fn >> 16); /* sethi hi(fn), gr6 */ tramp[5] = 0x8ef80000 + (cls >> 16); /* sethi hi(cls), gr7 */ tramp[6] = 0x9cc86000; /* ldi @(gr6, #0), gr14 */ tramp[7] = 0x8030e000; /* jmpl @(gr14, gr0) */ #else tramp[0] = 0x8cfc0000 + (fn & 0xffff); /* setlos lo(fn), gr6 */ tramp[1] = 0x8efc0000 + (cls & 0xffff); /* setlos lo(cls), gr7 */ tramp[2] = 0x8cf80000 + (fn >> 16); /* sethi hi(fn), gr6 */ tramp[3] = 0x8ef80000 + (cls >> 16); /* sethi hi(cls), gr7 */ tramp[4] = 0x80300006; /* jmpl @(gr0, gr6) */ #endif closure->cif = cif; closure->fun = fun; closure->user_data = user_data; /* Cache flushing. */ for (i = 0; i < FFI_TRAMPOLINE_SIZE; i++) __asm__ volatile ("dcf @(%0,%1)\n\tici @(%2,%1)" :: "r" (tramp), "r" (i), "r" (codeloc)); return FFI_OK; } smalltalk-3.2.5/libffi/src/pa/0000755000175000017500000000000012130456004013123 500000000000000smalltalk-3.2.5/libffi/src/pa/ffitarget.h0000644000175000017500000000450712130343734015202 00000000000000/* -----------------------------------------------------------------*-C-*- ffitarget.h - Copyright (c) 1996-2003 Red Hat, Inc. Target configuration macros for hppa. Permission is hereby granted, free of charge, to any person obtaining a copy of this software and associated documentation files (the ``Software''), to deal in the Software without restriction, including without limitation the rights to use, copy, modify, merge, publish, distribute, sublicense, and/or sell copies of the Software, and to permit persons to whom the Software is furnished to do so, subject to the following conditions: The above copyright notice and this permission notice shall be included in all copies or substantial portions of the Software. THE SOFTWARE IS PROVIDED ``AS IS'', WITHOUT WARRANTY OF ANY KIND, EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. ----------------------------------------------------------------------- */ #ifndef LIBFFI_TARGET_H #define LIBFFI_TARGET_H /* ---- System specific configurations ----------------------------------- */ #ifndef LIBFFI_ASM typedef unsigned long ffi_arg; typedef signed long ffi_sarg; typedef enum ffi_abi { FFI_FIRST_ABI = 0, #ifdef PA_LINUX FFI_PA32, FFI_DEFAULT_ABI = FFI_PA32, #endif #ifdef PA_HPUX FFI_PA32, FFI_DEFAULT_ABI = FFI_PA32, #endif #ifdef PA64_HPUX #error "PA64_HPUX FFI is not yet implemented" FFI_PA64, FFI_DEFAULT_ABI = FFI_PA64, #endif FFI_LAST_ABI = FFI_DEFAULT_ABI + 1 } ffi_abi; #endif /* ---- Definitions for closures ----------------------------------------- */ #define FFI_CLOSURES 1 #define FFI_NATIVE_RAW_API 0 #ifdef PA_LINUX #define FFI_TRAMPOLINE_SIZE 32 #else #define FFI_TRAMPOLINE_SIZE 40 #endif #define FFI_TYPE_SMALL_STRUCT2 -1 #define FFI_TYPE_SMALL_STRUCT3 -2 #define FFI_TYPE_SMALL_STRUCT4 -3 #define FFI_TYPE_SMALL_STRUCT5 -4 #define FFI_TYPE_SMALL_STRUCT6 -5 #define FFI_TYPE_SMALL_STRUCT7 -6 #define FFI_TYPE_SMALL_STRUCT8 -7 #endif smalltalk-3.2.5/libffi/src/pa/linux.S0000644000175000017500000002174312130343734014342 00000000000000/* ----------------------------------------------------------------------- linux.S - (c) 2003-2004 Randolph Chung (c) 2008 Red Hat, Inc. HPPA Foreign Function Interface Permission is hereby granted, free of charge, to any person obtaining a copy of this software and associated documentation files (the ``Software''), to deal in the Software without restriction, including without limitation the rights to use, copy, modify, merge, publish, distribute, sublicense, and/or sell copies of the Software, and to permit persons to whom the Software is furnished to do so, subject to the following conditions: The above copyright notice and this permission notice shall be included in all copies or substantial portions of the Software. THE SOFTWARE IS PROVIDED ``AS IS'', WITHOUT WARRANTY OF ANY KIND, EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL RENESAS TECHNOLOGY BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. ----------------------------------------------------------------------- */ #define LIBFFI_ASM #include #include .text .level 1.1 .align 4 /* void ffi_call_pa32(void (*)(char *, extended_cif *), extended_cif *ecif, unsigned bytes, unsigned flags, unsigned *rvalue, void (*fn)(void)); */ .export ffi_call_pa32,code .import ffi_prep_args_pa32,code .type ffi_call_pa32, @function .LFB1: ffi_call_pa32: .proc .callinfo FRAME=64,CALLS,SAVE_RP,SAVE_SP,ENTRY_GR=4 .entry stw %rp, -20(%sp) copy %r3, %r1 .LCFI11: copy %sp, %r3 .LCFI12: /* Setup the stack for calling prep_args... We want the stack to look like this: [ Previous stack ] <- %r3 [ 64-bytes register save area ] <- %r4 [ Stack space for actual call, passed as ] <- %arg0 [ arg0 to ffi_prep_args_pa32 ] [ Stack for calling prep_args ] <- %sp */ stwm %r1, 64(%sp) stw %r4, 12(%r3) .LCFI13: copy %sp, %r4 addl %arg2, %r4, %arg0 /* arg stack */ stw %arg3, -48(%r3) /* save flags; we need it later */ /* Call prep_args: %arg0(stack) -- set up above %arg1(ecif) -- same as incoming param %arg2(bytes) -- same as incoming param */ bl ffi_prep_args_pa32,%r2 ldo 64(%arg0), %sp ldo -64(%sp), %sp /* now %sp should point where %arg0 was pointing. */ /* Load the arguments that should be passed in registers The fp args were loaded by the prep_args function. */ ldw -36(%sp), %arg0 ldw -40(%sp), %arg1 ldw -44(%sp), %arg2 ldw -48(%sp), %arg3 /* in case the function is going to return a structure we need to give it a place to put the result. */ ldw -52(%r3), %ret0 /* %ret0 <- rvalue */ ldw -56(%r3), %r22 /* %r22 <- function to call */ bl $$dyncall, %r31 /* Call the user function */ copy %r31, %rp /* Prepare to store the result; we need to recover flags and rvalue. */ ldw -48(%r3), %r21 /* r21 <- flags */ ldw -52(%r3), %r20 /* r20 <- rvalue */ /* Store the result according to the return type. */ .Lcheckint: comib,<>,n FFI_TYPE_INT, %r21, .Lcheckint8 b .Ldone stw %ret0, 0(%r20) .Lcheckint8: comib,<>,n FFI_TYPE_UINT8, %r21, .Lcheckint16 b .Ldone stb %ret0, 0(%r20) .Lcheckint16: comib,<>,n FFI_TYPE_UINT16, %r21, .Lcheckdbl b .Ldone sth %ret0, 0(%r20) .Lcheckdbl: comib,<>,n FFI_TYPE_DOUBLE, %r21, .Lcheckfloat b .Ldone fstd %fr4,0(%r20) .Lcheckfloat: comib,<>,n FFI_TYPE_FLOAT, %r21, .Lcheckll b .Ldone fstw %fr4L,0(%r20) .Lcheckll: comib,<>,n FFI_TYPE_UINT64, %r21, .Lchecksmst2 stw %ret0, 0(%r20) b .Ldone stw %ret1, 4(%r20) .Lchecksmst2: comib,<>,n FFI_TYPE_SMALL_STRUCT2, %r21, .Lchecksmst3 /* 2-byte structs are returned in ret0 as ????xxyy. */ extru %ret0, 23, 8, %r22 stbs,ma %r22, 1(%r20) b .Ldone stb %ret0, 0(%r20) .Lchecksmst3: comib,<>,n FFI_TYPE_SMALL_STRUCT3, %r21, .Lchecksmst4 /* 3-byte structs are returned in ret0 as ??xxyyzz. */ extru %ret0, 15, 8, %r22 stbs,ma %r22, 1(%r20) extru %ret0, 23, 8, %r22 stbs,ma %r22, 1(%r20) b .Ldone stb %ret0, 0(%r20) .Lchecksmst4: comib,<>,n FFI_TYPE_SMALL_STRUCT4, %r21, .Lchecksmst5 /* 4-byte structs are returned in ret0 as wwxxyyzz. */ extru %ret0, 7, 8, %r22 stbs,ma %r22, 1(%r20) extru %ret0, 15, 8, %r22 stbs,ma %r22, 1(%r20) extru %ret0, 23, 8, %r22 stbs,ma %r22, 1(%r20) b .Ldone stb %ret0, 0(%r20) .Lchecksmst5: comib,<>,n FFI_TYPE_SMALL_STRUCT5, %r21, .Lchecksmst6 /* 5 byte values are returned right justified: ret0 ret1 5: ??????aa bbccddee */ stbs,ma %ret0, 1(%r20) extru %ret1, 7, 8, %r22 stbs,ma %r22, 1(%r20) extru %ret1, 15, 8, %r22 stbs,ma %r22, 1(%r20) extru %ret1, 23, 8, %r22 stbs,ma %r22, 1(%r20) b .Ldone stb %ret1, 0(%r20) .Lchecksmst6: comib,<>,n FFI_TYPE_SMALL_STRUCT6, %r21, .Lchecksmst7 /* 6 byte values are returned right justified: ret0 ret1 6: ????aabb ccddeeff */ extru %ret0, 23, 8, %r22 stbs,ma %r22, 1(%r20) stbs,ma %ret0, 1(%r20) extru %ret1, 7, 8, %r22 stbs,ma %r22, 1(%r20) extru %ret1, 15, 8, %r22 stbs,ma %r22, 1(%r20) extru %ret1, 23, 8, %r22 stbs,ma %r22, 1(%r20) b .Ldone stb %ret1, 0(%r20) .Lchecksmst7: comib,<>,n FFI_TYPE_SMALL_STRUCT7, %r21, .Lchecksmst8 /* 7 byte values are returned right justified: ret0 ret1 7: ??aabbcc ddeeffgg */ extru %ret0, 15, 8, %r22 stbs,ma %r22, 1(%r20) extru %ret0, 23, 8, %r22 stbs,ma %r22, 1(%r20) stbs,ma %ret0, 1(%r20) extru %ret1, 7, 8, %r22 stbs,ma %r22, 1(%r20) extru %ret1, 15, 8, %r22 stbs,ma %r22, 1(%r20) extru %ret1, 23, 8, %r22 stbs,ma %r22, 1(%r20) b .Ldone stb %ret1, 0(%r20) .Lchecksmst8: comib,<>,n FFI_TYPE_SMALL_STRUCT8, %r21, .Ldone /* 8 byte values are returned right justified: ret0 ret1 8: aabbccdd eeffgghh */ extru %ret0, 7, 8, %r22 stbs,ma %r22, 1(%r20) extru %ret0, 15, 8, %r22 stbs,ma %r22, 1(%r20) extru %ret0, 23, 8, %r22 stbs,ma %r22, 1(%r20) stbs,ma %ret0, 1(%r20) extru %ret1, 7, 8, %r22 stbs,ma %r22, 1(%r20) extru %ret1, 15, 8, %r22 stbs,ma %r22, 1(%r20) extru %ret1, 23, 8, %r22 stbs,ma %r22, 1(%r20) stb %ret1, 0(%r20) .Ldone: /* all done, return */ copy %r4, %sp /* pop arg stack */ ldw 12(%r3), %r4 ldwm -64(%sp), %r3 /* .. and pop stack */ ldw -20(%sp), %rp bv %r0(%rp) nop .exit .procend .LFE1: /* void ffi_closure_pa32(void); Called with closure argument in %r21 */ .export ffi_closure_pa32,code .import ffi_closure_inner_pa32,code .type ffi_closure_pa32, @function .LFB2: ffi_closure_pa32: .proc .callinfo FRAME=64,CALLS,SAVE_RP,SAVE_SP,ENTRY_GR=3 .entry stw %rp, -20(%sp) .LCFI20: copy %r3, %r1 .LCFI21: copy %sp, %r3 .LCFI22: stwm %r1, 64(%sp) /* Put arguments onto the stack and call ffi_closure_inner. */ stw %arg0, -36(%r3) stw %arg1, -40(%r3) stw %arg2, -44(%r3) stw %arg3, -48(%r3) copy %r21, %arg0 bl ffi_closure_inner_pa32, %r2 copy %r3, %arg1 ldwm -64(%sp), %r3 ldw -20(%sp), %rp ldw -36(%sp), %ret0 bv %r0(%r2) ldw -40(%sp), %ret1 .exit .procend .LFE2: .section ".eh_frame",EH_FRAME_FLAGS,@progbits .Lframe1: .word .LECIE1-.LSCIE1 ;# Length of Common Information Entry .LSCIE1: .word 0x0 ;# CIE Identifier Tag .byte 0x1 ;# CIE Version .ascii "\0" ;# CIE Augmentation .uleb128 0x1 ;# CIE Code Alignment Factor .sleb128 4 ;# CIE Data Alignment Factor .byte 0x2 ;# CIE RA Column .byte 0xc ;# DW_CFA_def_cfa .uleb128 0x1e .uleb128 0x0 .align 4 .LECIE1: .LSFDE1: .word .LEFDE1-.LASFDE1 ;# FDE Length .LASFDE1: .word .LASFDE1-.Lframe1 ;# FDE CIE offset .word .LFB1 ;# FDE initial location .word .LFE1-.LFB1 ;# FDE address range .byte 0x4 ;# DW_CFA_advance_loc4 .word .LCFI11-.LFB1 .byte 0x83 ;# DW_CFA_offset, column 0x3 .uleb128 0x0 .byte 0x11 ;# DW_CFA_offset_extended_sf; save r2 at [r30-20] .uleb128 0x2 .sleb128 -5 .byte 0x4 ;# DW_CFA_advance_loc4 .word .LCFI12-.LCFI11 .byte 0xd ;# DW_CFA_def_cfa_register = r3 .uleb128 0x3 .byte 0x4 ;# DW_CFA_advance_loc4 .word .LCFI13-.LCFI12 .byte 0x84 ;# DW_CFA_offset, column 0x4 .uleb128 0x3 .align 4 .LEFDE1: .LSFDE2: .word .LEFDE2-.LASFDE2 ;# FDE Length .LASFDE2: .word .LASFDE2-.Lframe1 ;# FDE CIE offset .word .LFB2 ;# FDE initial location .word .LFE2-.LFB2 ;# FDE address range .byte 0x4 ;# DW_CFA_advance_loc4 .word .LCFI21-.LFB2 .byte 0x83 ;# DW_CFA_offset, column 0x3 .uleb128 0x0 .byte 0x11 ;# DW_CFA_offset_extended_sf .uleb128 0x2 .sleb128 -5 .byte 0x4 ;# DW_CFA_advance_loc4 .word .LCFI22-.LCFI21 .byte 0xd ;# DW_CFA_def_cfa_register = r3 .uleb128 0x3 .align 4 .LEFDE2: smalltalk-3.2.5/libffi/src/pa/ffi.c0000644000175000017500000004701212130343734013764 00000000000000/* ----------------------------------------------------------------------- ffi.c - (c) 2003-2004 Randolph Chung (c) 2008 Red Hat, Inc. HPPA Foreign Function Interface HP-UX PA ABI support (c) 2006 Free Software Foundation, Inc. Permission is hereby granted, free of charge, to any person obtaining a copy of this software and associated documentation files (the ``Software''), to deal in the Software without restriction, including without limitation the rights to use, copy, modify, merge, publish, distribute, sublicense, and/or sell copies of the Software, and to permit persons to whom the Software is furnished to do so, subject to the following conditions: The above copyright notice and this permission notice shall be included in all copies or substantial portions of the Software. THE SOFTWARE IS PROVIDED ``AS IS'', WITHOUT WARRANTY OF ANY KIND, EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. ----------------------------------------------------------------------- */ #include #include #include #include #define ROUND_UP(v, a) (((size_t)(v) + (a) - 1) & ~((a) - 1)) #define MIN_STACK_SIZE 64 #define FIRST_ARG_SLOT 9 #define DEBUG_LEVEL 0 #define fldw(addr, fpreg) \ __asm__ volatile ("fldw 0(%0), %%" #fpreg "L" : : "r"(addr) : #fpreg) #define fstw(fpreg, addr) \ __asm__ volatile ("fstw %%" #fpreg "L, 0(%0)" : : "r"(addr)) #define fldd(addr, fpreg) \ __asm__ volatile ("fldd 0(%0), %%" #fpreg : : "r"(addr) : #fpreg) #define fstd(fpreg, addr) \ __asm__ volatile ("fstd %%" #fpreg "L, 0(%0)" : : "r"(addr)) #define debug(lvl, x...) do { if (lvl <= DEBUG_LEVEL) { printf(x); } } while (0) static inline int ffi_struct_type(ffi_type *t) { size_t sz = t->size; /* Small structure results are passed in registers, larger ones are passed by pointer. Note that small structures of size 2, 4 and 8 differ from the corresponding integer types in that they have different alignment requirements. */ if (sz <= 1) return FFI_TYPE_UINT8; else if (sz == 2) return FFI_TYPE_SMALL_STRUCT2; else if (sz == 3) return FFI_TYPE_SMALL_STRUCT3; else if (sz == 4) return FFI_TYPE_SMALL_STRUCT4; else if (sz == 5) return FFI_TYPE_SMALL_STRUCT5; else if (sz == 6) return FFI_TYPE_SMALL_STRUCT6; else if (sz == 7) return FFI_TYPE_SMALL_STRUCT7; else if (sz <= 8) return FFI_TYPE_SMALL_STRUCT8; else return FFI_TYPE_STRUCT; /* else, we pass it by pointer. */ } /* PA has a downward growing stack, which looks like this: Offset [ Variable args ] SP = (4*(n+9)) arg word N ... SP-52 arg word 4 [ Fixed args ] SP-48 arg word 3 SP-44 arg word 2 SP-40 arg word 1 SP-36 arg word 0 [ Frame marker ] ... SP-20 RP SP-4 previous SP The first four argument words on the stack are reserved for use by the callee. Instead, the general and floating registers replace the first four argument slots. Non FP arguments are passed solely in the general registers. FP arguments are passed in both general and floating registers when using libffi. Non-FP 32-bit args are passed in gr26, gr25, gr24 and gr23. Non-FP 64-bit args are passed in register pairs, starting on an odd numbered register (i.e. r25+r26 and r23+r24). FP 32-bit arguments are passed in fr4L, fr5L, fr6L and fr7L. FP 64-bit arguments are passed in fr5 and fr7. The registers are allocated in the same manner as stack slots. This allows the callee to save its arguments on the stack if necessary: arg word 3 -> gr23 or fr7L arg word 2 -> gr24 or fr6L or fr7R arg word 1 -> gr25 or fr5L arg word 0 -> gr26 or fr4L or fr5R Note that fr4R and fr6R are never used for arguments (i.e., doubles are not passed in fr4 or fr6). The rest of the arguments are passed on the stack starting at SP-52, but 64-bit arguments need to be aligned to an 8-byte boundary This means we can have holes either in the register allocation, or in the stack. */ /* ffi_prep_args is called by the assembly routine once stack space has been allocated for the function's arguments The following code will put everything into the stack frame (which was allocated by the asm routine), and on return the asm routine will load the arguments that should be passed by register into the appropriate registers NOTE: We load floating point args in this function... that means we assume gcc will not mess with fp regs in here. */ void ffi_prep_args_pa32(UINT32 *stack, extended_cif *ecif, unsigned bytes) { register unsigned int i; register ffi_type **p_arg; register void **p_argv; unsigned int slot = FIRST_ARG_SLOT; char *dest_cpy; size_t len; debug(1, "%s: stack = %p, ecif = %p, bytes = %u\n", __FUNCTION__, stack, ecif, bytes); p_arg = ecif->cif->arg_types; p_argv = ecif->avalue; for (i = 0; i < ecif->cif->nargs; i++) { int type = (*p_arg)->type; switch (type) { case FFI_TYPE_SINT8: *(SINT32 *)(stack - slot) = *(SINT8 *)(*p_argv); break; case FFI_TYPE_UINT8: *(UINT32 *)(stack - slot) = *(UINT8 *)(*p_argv); break; case FFI_TYPE_SINT16: *(SINT32 *)(stack - slot) = *(SINT16 *)(*p_argv); break; case FFI_TYPE_UINT16: *(UINT32 *)(stack - slot) = *(UINT16 *)(*p_argv); break; case FFI_TYPE_UINT32: case FFI_TYPE_SINT32: case FFI_TYPE_POINTER: debug(3, "Storing UINT32 %u in slot %u\n", *(UINT32 *)(*p_argv), slot); *(UINT32 *)(stack - slot) = *(UINT32 *)(*p_argv); break; case FFI_TYPE_UINT64: case FFI_TYPE_SINT64: /* Align slot for 64-bit type. */ slot += (slot & 1) ? 1 : 2; *(UINT64 *)(stack - slot) = *(UINT64 *)(*p_argv); break; case FFI_TYPE_FLOAT: /* First 4 args go in fr4L - fr7L. */ debug(3, "Storing UINT32(float) in slot %u\n", slot); *(UINT32 *)(stack - slot) = *(UINT32 *)(*p_argv); switch (slot - FIRST_ARG_SLOT) { /* First 4 args go in fr4L - fr7L. */ case 0: fldw(stack - slot, fr4); break; case 1: fldw(stack - slot, fr5); break; case 2: fldw(stack - slot, fr6); break; case 3: fldw(stack - slot, fr7); break; } break; case FFI_TYPE_DOUBLE: /* Align slot for 64-bit type. */ slot += (slot & 1) ? 1 : 2; debug(3, "Storing UINT64(double) at slot %u\n", slot); *(UINT64 *)(stack - slot) = *(UINT64 *)(*p_argv); switch (slot - FIRST_ARG_SLOT) { /* First 2 args go in fr5, fr7. */ case 1: fldd(stack - slot, fr5); break; case 3: fldd(stack - slot, fr7); break; } break; #ifdef PA_HPUX case FFI_TYPE_LONGDOUBLE: /* Long doubles are passed in the same manner as structures larger than 8 bytes. */ *(UINT32 *)(stack - slot) = (UINT32)(*p_argv); break; #endif case FFI_TYPE_STRUCT: /* Structs smaller or equal than 4 bytes are passed in one register. Structs smaller or equal 8 bytes are passed in two registers. Larger structures are passed by pointer. */ len = (*p_arg)->size; if (len <= 4) { dest_cpy = (char *)(stack - slot) + 4 - len; memcpy(dest_cpy, (char *)*p_argv, len); } else if (len <= 8) { slot += (slot & 1) ? 1 : 2; dest_cpy = (char *)(stack - slot) + 8 - len; memcpy(dest_cpy, (char *)*p_argv, len); } else *(UINT32 *)(stack - slot) = (UINT32)(*p_argv); break; default: FFI_ASSERT(0); } slot++; p_arg++; p_argv++; } /* Make sure we didn't mess up and scribble on the stack. */ { unsigned int n; debug(5, "Stack setup:\n"); for (n = 0; n < (bytes + 3) / 4; n++) { if ((n%4) == 0) { debug(5, "\n%08x: ", (unsigned int)(stack - n)); } debug(5, "%08x ", *(stack - n)); } debug(5, "\n"); } FFI_ASSERT(slot * 4 <= bytes); return; } static void ffi_size_stack_pa32(ffi_cif *cif) { ffi_type **ptr; int i; int z = 0; /* # stack slots */ for (ptr = cif->arg_types, i = 0; i < cif->nargs; ptr++, i++) { int type = (*ptr)->type; switch (type) { case FFI_TYPE_DOUBLE: case FFI_TYPE_UINT64: case FFI_TYPE_SINT64: z += 2 + (z & 1); /* must start on even regs, so we may waste one */ break; #ifdef PA_HPUX case FFI_TYPE_LONGDOUBLE: #endif case FFI_TYPE_STRUCT: z += 1; /* pass by ptr, callee will copy */ break; default: /* <= 32-bit values */ z++; } } /* We can fit up to 6 args in the default 64-byte stack frame, if we need more, we need more stack. */ if (z <= 6) cif->bytes = MIN_STACK_SIZE; /* min stack size */ else cif->bytes = 64 + ROUND_UP((z - 6) * sizeof(UINT32), MIN_STACK_SIZE); debug(3, "Calculated stack size is %u bytes\n", cif->bytes); } /* Perform machine dependent cif processing. */ ffi_status ffi_prep_cif_machdep(ffi_cif *cif) { /* Set the return type flag */ switch (cif->rtype->type) { case FFI_TYPE_VOID: case FFI_TYPE_FLOAT: case FFI_TYPE_DOUBLE: cif->flags = (unsigned) cif->rtype->type; break; #ifdef PA_HPUX case FFI_TYPE_LONGDOUBLE: /* Long doubles are treated like a structure. */ cif->flags = FFI_TYPE_STRUCT; break; #endif case FFI_TYPE_STRUCT: /* For the return type we have to check the size of the structures. If the size is smaller or equal 4 bytes, the result is given back in one register. If the size is smaller or equal 8 bytes than we return the result in two registers. But if the size is bigger than 8 bytes, we work with pointers. */ cif->flags = ffi_struct_type(cif->rtype); break; case FFI_TYPE_UINT64: case FFI_TYPE_SINT64: cif->flags = FFI_TYPE_UINT64; break; default: cif->flags = FFI_TYPE_INT; break; } /* Lucky us, because of the unique PA ABI we get to do our own stack sizing. */ switch (cif->abi) { case FFI_PA32: ffi_size_stack_pa32(cif); break; default: FFI_ASSERT(0); break; } return FFI_OK; } extern void ffi_call_pa32(void (*)(UINT32 *, extended_cif *, unsigned), extended_cif *, unsigned, unsigned, unsigned *, void (*fn)(void)); void ffi_call(ffi_cif *cif, void (*fn)(void), void *rvalue, void **avalue) { extended_cif ecif; ecif.cif = cif; ecif.avalue = avalue; /* If the return value is a struct and we don't have a return value address then we need to make one. */ if (rvalue == NULL #ifdef PA_HPUX && (cif->rtype->type == FFI_TYPE_STRUCT || cif->rtype->type == FFI_TYPE_LONGDOUBLE)) #else && cif->rtype->type == FFI_TYPE_STRUCT) #endif { ecif.rvalue = alloca(cif->rtype->size); } else ecif.rvalue = rvalue; switch (cif->abi) { case FFI_PA32: debug(3, "Calling ffi_call_pa32: ecif=%p, bytes=%u, flags=%u, rvalue=%p, fn=%p\n", &ecif, cif->bytes, cif->flags, ecif.rvalue, (void *)fn); ffi_call_pa32(ffi_prep_args_pa32, &ecif, cif->bytes, cif->flags, ecif.rvalue, fn); break; default: FFI_ASSERT(0); break; } } #if FFI_CLOSURES /* This is more-or-less an inverse of ffi_call -- we have arguments on the stack, and we need to fill them into a cif structure and invoke the user function. This really ought to be in asm to make sure the compiler doesn't do things we don't expect. */ ffi_status ffi_closure_inner_pa32(ffi_closure *closure, UINT32 *stack) { ffi_cif *cif; void **avalue; void *rvalue; UINT32 ret[2]; /* function can return up to 64-bits in registers */ ffi_type **p_arg; char *tmp; int i, avn; unsigned int slot = FIRST_ARG_SLOT; register UINT32 r28 asm("r28"); cif = closure->cif; /* If returning via structure, callee will write to our pointer. */ if (cif->flags == FFI_TYPE_STRUCT) rvalue = (void *)r28; else rvalue = &ret[0]; avalue = (void **)alloca(cif->nargs * FFI_SIZEOF_ARG); avn = cif->nargs; p_arg = cif->arg_types; for (i = 0; i < avn; i++) { int type = (*p_arg)->type; switch (type) { case FFI_TYPE_SINT8: case FFI_TYPE_UINT8: case FFI_TYPE_SINT16: case FFI_TYPE_UINT16: case FFI_TYPE_SINT32: case FFI_TYPE_UINT32: case FFI_TYPE_POINTER: avalue[i] = (char *)(stack - slot) + sizeof(UINT32) - (*p_arg)->size; break; case FFI_TYPE_SINT64: case FFI_TYPE_UINT64: slot += (slot & 1) ? 1 : 2; avalue[i] = (void *)(stack - slot); break; case FFI_TYPE_FLOAT: #ifdef PA_LINUX /* The closure call is indirect. In Linux, floating point arguments in indirect calls with a prototype are passed in the floating point registers instead of the general registers. So, we need to replace what was previously stored in the current slot with the value in the corresponding floating point register. */ switch (slot - FIRST_ARG_SLOT) { case 0: fstw(fr4, (void *)(stack - slot)); break; case 1: fstw(fr5, (void *)(stack - slot)); break; case 2: fstw(fr6, (void *)(stack - slot)); break; case 3: fstw(fr7, (void *)(stack - slot)); break; } #endif avalue[i] = (void *)(stack - slot); break; case FFI_TYPE_DOUBLE: slot += (slot & 1) ? 1 : 2; #ifdef PA_LINUX /* See previous comment for FFI_TYPE_FLOAT. */ switch (slot - FIRST_ARG_SLOT) { case 1: fstd(fr5, (void *)(stack - slot)); break; case 3: fstd(fr7, (void *)(stack - slot)); break; } #endif avalue[i] = (void *)(stack - slot); break; #ifdef PA_HPUX case FFI_TYPE_LONGDOUBLE: /* Long doubles are treated like a big structure. */ avalue[i] = (void *) *(stack - slot); break; #endif case FFI_TYPE_STRUCT: /* Structs smaller or equal than 4 bytes are passed in one register. Structs smaller or equal 8 bytes are passed in two registers. Larger structures are passed by pointer. */ if((*p_arg)->size <= 4) { avalue[i] = (void *)(stack - slot) + sizeof(UINT32) - (*p_arg)->size; } else if ((*p_arg)->size <= 8) { slot += (slot & 1) ? 1 : 2; avalue[i] = (void *)(stack - slot) + sizeof(UINT64) - (*p_arg)->size; } else avalue[i] = (void *) *(stack - slot); break; default: FFI_ASSERT(0); } slot++; p_arg++; } /* Invoke the closure. */ (closure->fun) (cif, rvalue, avalue, closure->user_data); debug(3, "after calling function, ret[0] = %08x, ret[1] = %08x\n", ret[0], ret[1]); /* Store the result using the lower 2 bytes of the flags. */ switch (cif->flags) { case FFI_TYPE_UINT8: *(stack - FIRST_ARG_SLOT) = (UINT8)(ret[0] >> 24); break; case FFI_TYPE_SINT8: *(stack - FIRST_ARG_SLOT) = (SINT8)(ret[0] >> 24); break; case FFI_TYPE_UINT16: *(stack - FIRST_ARG_SLOT) = (UINT16)(ret[0] >> 16); break; case FFI_TYPE_SINT16: *(stack - FIRST_ARG_SLOT) = (SINT16)(ret[0] >> 16); break; case FFI_TYPE_INT: case FFI_TYPE_SINT32: case FFI_TYPE_UINT32: *(stack - FIRST_ARG_SLOT) = ret[0]; break; case FFI_TYPE_SINT64: case FFI_TYPE_UINT64: *(stack - FIRST_ARG_SLOT) = ret[0]; *(stack - FIRST_ARG_SLOT - 1) = ret[1]; break; case FFI_TYPE_DOUBLE: fldd(rvalue, fr4); break; case FFI_TYPE_FLOAT: fldw(rvalue, fr4); break; case FFI_TYPE_STRUCT: /* Don't need a return value, done by caller. */ break; case FFI_TYPE_SMALL_STRUCT2: case FFI_TYPE_SMALL_STRUCT3: case FFI_TYPE_SMALL_STRUCT4: tmp = (void*)(stack - FIRST_ARG_SLOT); tmp += 4 - cif->rtype->size; memcpy((void*)tmp, &ret[0], cif->rtype->size); break; case FFI_TYPE_SMALL_STRUCT5: case FFI_TYPE_SMALL_STRUCT6: case FFI_TYPE_SMALL_STRUCT7: case FFI_TYPE_SMALL_STRUCT8: { unsigned int ret2[2]; int off; /* Right justify ret[0] and ret[1] */ switch (cif->flags) { case FFI_TYPE_SMALL_STRUCT5: off = 3; break; case FFI_TYPE_SMALL_STRUCT6: off = 2; break; case FFI_TYPE_SMALL_STRUCT7: off = 1; break; default: off = 0; break; } memset (ret2, 0, sizeof (ret2)); memcpy ((char *)ret2 + off, ret, 8 - off); *(stack - FIRST_ARG_SLOT) = ret2[0]; *(stack - FIRST_ARG_SLOT - 1) = ret2[1]; } break; case FFI_TYPE_POINTER: case FFI_TYPE_VOID: break; default: debug(0, "assert with cif->flags: %d\n",cif->flags); FFI_ASSERT(0); break; } return FFI_OK; } /* Fill in a closure to refer to the specified fun and user_data. cif specifies the argument and result types for fun. The cif must already be prep'ed. */ extern void ffi_closure_pa32(void); ffi_status ffi_prep_closure_loc (ffi_closure* closure, ffi_cif* cif, void (*fun)(ffi_cif*,void*,void**,void*), void *user_data, void *codeloc) { UINT32 *tramp = (UINT32 *)(closure->tramp); #ifdef PA_HPUX UINT32 *tmp; #endif FFI_ASSERT (cif->abi == FFI_PA32); /* Make a small trampoline that will branch to our handler function. Use PC-relative addressing. */ #ifdef PA_LINUX tramp[0] = 0xeaa00000; /* b,l .+8,%r21 ; %r21 <- pc+8 */ tramp[1] = 0xd6a01c1e; /* depi 0,31,2,%r21 ; mask priv bits */ tramp[2] = 0x4aa10028; /* ldw 20(%r21),%r1 ; load plabel */ tramp[3] = 0x36b53ff1; /* ldo -8(%r21),%r21 ; get closure addr */ tramp[4] = 0x0c201096; /* ldw 0(%r1),%r22 ; address of handler */ tramp[5] = 0xeac0c000; /* bv%r0(%r22) ; branch to handler */ tramp[6] = 0x0c281093; /* ldw 4(%r1),%r19 ; GP of handler */ tramp[7] = ((UINT32)(ffi_closure_pa32) & ~2); /* Flush d/icache -- have to flush up 2 two lines because of alignment. */ __asm__ volatile( "fdc 0(%0)\n\t" "fdc %1(%0)\n\t" "fic 0(%%sr4, %0)\n\t" "fic %1(%%sr4, %0)\n\t" "sync\n\t" "nop\n\t" "nop\n\t" "nop\n\t" "nop\n\t" "nop\n\t" "nop\n\t" "nop\n" : : "r"((unsigned long)tramp & ~31), "r"(32 /* stride */) : "memory"); #endif #ifdef PA_HPUX tramp[0] = 0xeaa00000; /* b,l .+8,%r21 ; %r21 <- pc+8 */ tramp[1] = 0xd6a01c1e; /* depi 0,31,2,%r21 ; mask priv bits */ tramp[2] = 0x4aa10038; /* ldw 28(%r21),%r1 ; load plabel */ tramp[3] = 0x36b53ff1; /* ldo -8(%r21),%r21 ; get closure addr */ tramp[4] = 0x0c201096; /* ldw 0(%r1),%r22 ; address of handler */ tramp[5] = 0x02c010b4; /* ldsid (%r22),%r20 ; load space id */ tramp[6] = 0x00141820; /* mtsp %r20,%sr0 ; into %sr0 */ tramp[7] = 0xe2c00000; /* be 0(%sr0,%r22) ; branch to handler */ tramp[8] = 0x0c281093; /* ldw 4(%r1),%r19 ; GP of handler */ tramp[9] = ((UINT32)(ffi_closure_pa32) & ~2); /* Flush d/icache -- have to flush three lines because of alignment. */ __asm__ volatile( "copy %1,%0\n\t" "fdc,m %2(%0)\n\t" "fdc,m %2(%0)\n\t" "fdc,m %2(%0)\n\t" "ldsid (%1),%0\n\t" "mtsp %0,%%sr0\n\t" "copy %1,%0\n\t" "fic,m %2(%%sr0,%0)\n\t" "fic,m %2(%%sr0,%0)\n\t" "fic,m %2(%%sr0,%0)\n\t" "sync\n\t" "nop\n\t" "nop\n\t" "nop\n\t" "nop\n\t" "nop\n\t" "nop\n\t" "nop\n" : "=&r" ((unsigned long)tmp) : "r" ((unsigned long)tramp & ~31), "r" (32/* stride */) : "memory"); #endif closure->cif = cif; closure->user_data = user_data; closure->fun = fun; return FFI_OK; } #endif smalltalk-3.2.5/libffi/src/pa/hpux32.S0000644000175000017500000002201212130343734014322 00000000000000/* ----------------------------------------------------------------------- hpux32.S - Copyright (c) 2006 Free Software Foundation, Inc. (c) 2008 Red Hat, Inc. based on src/pa/linux.S HP-UX PA Foreign Function Interface Permission is hereby granted, free of charge, to any person obtaining a copy of this software and associated documentation files (the ``Software''), to deal in the Software without restriction, including without limitation the rights to use, copy, modify, merge, publish, distribute, sublicense, and/or sell copies of the Software, and to permit persons to whom the Software is furnished to do so, subject to the following conditions: The above copyright notice and this permission notice shall be included in all copies or substantial portions of the Software. THE SOFTWARE IS PROVIDED ``AS IS'', WITHOUT WARRANTY OF ANY KIND, EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHOR BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. ----------------------------------------------------------------------- */ #define LIBFFI_ASM #include #include .LEVEL 1.1 .SPACE $PRIVATE$ .IMPORT $global$,DATA .IMPORT $$dyncall,MILLICODE .SUBSPA $DATA$ .align 4 /* void ffi_call_pa32(void (*)(char *, extended_cif *), extended_cif *ecif, unsigned bytes, unsigned flags, unsigned *rvalue, void (*fn)(void)); */ .export ffi_call_pa32,ENTRY,PRIV_LEV=3 .import ffi_prep_args_pa32,CODE .SPACE $TEXT$ .SUBSPA $CODE$ .align 4 L$FB1 ffi_call_pa32 .proc .callinfo FRAME=64,CALLS,SAVE_RP,SAVE_SP,ENTRY_GR=4 .entry stw %rp, -20(%sp) copy %r3, %r1 L$CFI11 copy %sp, %r3 L$CFI12 /* Setup the stack for calling prep_args... We want the stack to look like this: [ Previous stack ] <- %r3 [ 64-bytes register save area ] <- %r4 [ Stack space for actual call, passed as ] <- %arg0 [ arg0 to ffi_prep_args_pa32 ] [ Stack for calling prep_args ] <- %sp */ stwm %r1, 64(%sp) stw %r4, 12(%r3) L$CFI13 copy %sp, %r4 addl %arg2, %r4, %arg0 ; arg stack stw %arg3, -48(%r3) ; save flags we need it later /* Call prep_args: %arg0(stack) -- set up above %arg1(ecif) -- same as incoming param %arg2(bytes) -- same as incoming param */ bl ffi_prep_args_pa32,%r2 ldo 64(%arg0), %sp ldo -64(%sp), %sp /* now %sp should point where %arg0 was pointing. */ /* Load the arguments that should be passed in registers The fp args are loaded by the prep_args function. */ ldw -36(%sp), %arg0 ldw -40(%sp), %arg1 ldw -44(%sp), %arg2 ldw -48(%sp), %arg3 /* in case the function is going to return a structure we need to give it a place to put the result. */ ldw -52(%r3), %ret0 ; %ret0 <- rvalue ldw -56(%r3), %r22 ; %r22 <- function to call bl $$dyncall, %r31 ; Call the user function copy %r31, %rp /* Prepare to store the result; we need to recover flags and rvalue. */ ldw -48(%r3), %r21 ; r21 <- flags ldw -52(%r3), %r20 ; r20 <- rvalue /* Store the result according to the return type. The most likely types should come first. */ L$checkint comib,<>,n FFI_TYPE_INT, %r21, L$checkint8 b L$done stw %ret0, 0(%r20) L$checkint8 comib,<>,n FFI_TYPE_UINT8, %r21, L$checkint16 b L$done stb %ret0, 0(%r20) L$checkint16 comib,<>,n FFI_TYPE_UINT16, %r21, L$checkdbl b L$done sth %ret0, 0(%r20) L$checkdbl comib,<>,n FFI_TYPE_DOUBLE, %r21, L$checkfloat b L$done fstd %fr4,0(%r20) L$checkfloat comib,<>,n FFI_TYPE_FLOAT, %r21, L$checkll b L$done fstw %fr4L,0(%r20) L$checkll comib,<>,n FFI_TYPE_UINT64, %r21, L$checksmst2 stw %ret0, 0(%r20) b L$done stw %ret1, 4(%r20) L$checksmst2 comib,<>,n FFI_TYPE_SMALL_STRUCT2, %r21, L$checksmst3 /* 2-byte structs are returned in ret0 as ????xxyy. */ extru %ret0, 23, 8, %r22 stbs,ma %r22, 1(%r20) b L$done stb %ret0, 0(%r20) L$checksmst3 comib,<>,n FFI_TYPE_SMALL_STRUCT3, %r21, L$checksmst4 /* 3-byte structs are returned in ret0 as ??xxyyzz. */ extru %ret0, 15, 8, %r22 stbs,ma %r22, 1(%r20) extru %ret0, 23, 8, %r22 stbs,ma %r22, 1(%r20) b L$done stb %ret0, 0(%r20) L$checksmst4 comib,<>,n FFI_TYPE_SMALL_STRUCT4, %r21, L$checksmst5 /* 4-byte structs are returned in ret0 as wwxxyyzz. */ extru %ret0, 7, 8, %r22 stbs,ma %r22, 1(%r20) extru %ret0, 15, 8, %r22 stbs,ma %r22, 1(%r20) extru %ret0, 23, 8, %r22 stbs,ma %r22, 1(%r20) b L$done stb %ret0, 0(%r20) L$checksmst5 comib,<>,n FFI_TYPE_SMALL_STRUCT5, %r21, L$checksmst6 /* 5 byte values are returned right justified: ret0 ret1 5: ??????aa bbccddee */ stbs,ma %ret0, 1(%r20) extru %ret1, 7, 8, %r22 stbs,ma %r22, 1(%r20) extru %ret1, 15, 8, %r22 stbs,ma %r22, 1(%r20) extru %ret1, 23, 8, %r22 stbs,ma %r22, 1(%r20) b L$done stb %ret1, 0(%r20) L$checksmst6 comib,<>,n FFI_TYPE_SMALL_STRUCT6, %r21, L$checksmst7 /* 6 byte values are returned right justified: ret0 ret1 6: ????aabb ccddeeff */ extru %ret0, 23, 8, %r22 stbs,ma %r22, 1(%r20) stbs,ma %ret0, 1(%r20) extru %ret1, 7, 8, %r22 stbs,ma %r22, 1(%r20) extru %ret1, 15, 8, %r22 stbs,ma %r22, 1(%r20) extru %ret1, 23, 8, %r22 stbs,ma %r22, 1(%r20) b L$done stb %ret1, 0(%r20) L$checksmst7 comib,<>,n FFI_TYPE_SMALL_STRUCT7, %r21, L$checksmst8 /* 7 byte values are returned right justified: ret0 ret1 7: ??aabbcc ddeeffgg */ extru %ret0, 15, 8, %r22 stbs,ma %r22, 1(%r20) extru %ret0, 23, 8, %r22 stbs,ma %r22, 1(%r20) stbs,ma %ret0, 1(%r20) extru %ret1, 7, 8, %r22 stbs,ma %r22, 1(%r20) extru %ret1, 15, 8, %r22 stbs,ma %r22, 1(%r20) extru %ret1, 23, 8, %r22 stbs,ma %r22, 1(%r20) b L$done stb %ret1, 0(%r20) L$checksmst8 comib,<>,n FFI_TYPE_SMALL_STRUCT8, %r21, L$done /* 8 byte values are returned right justified: ret0 ret1 8: aabbccdd eeffgghh */ extru %ret0, 7, 8, %r22 stbs,ma %r22, 1(%r20) extru %ret0, 15, 8, %r22 stbs,ma %r22, 1(%r20) extru %ret0, 23, 8, %r22 stbs,ma %r22, 1(%r20) stbs,ma %ret0, 1(%r20) extru %ret1, 7, 8, %r22 stbs,ma %r22, 1(%r20) extru %ret1, 15, 8, %r22 stbs,ma %r22, 1(%r20) extru %ret1, 23, 8, %r22 stbs,ma %r22, 1(%r20) stb %ret1, 0(%r20) L$done /* all done, return */ copy %r4, %sp ; pop arg stack ldw 12(%r3), %r4 ldwm -64(%sp), %r3 ; .. and pop stack ldw -20(%sp), %rp bv %r0(%rp) nop .exit .procend L$FE1 /* void ffi_closure_pa32(void); Called with closure argument in %r21 */ .SPACE $TEXT$ .SUBSPA $CODE$ .export ffi_closure_pa32,ENTRY,PRIV_LEV=3,RTNVAL=GR .import ffi_closure_inner_pa32,CODE .align 4 L$FB2 ffi_closure_pa32 .proc .callinfo FRAME=64,CALLS,SAVE_RP,SAVE_SP,ENTRY_GR=3 .entry stw %rp, -20(%sp) copy %r3, %r1 L$CFI21 copy %sp, %r3 L$CFI22 stwm %r1, 64(%sp) /* Put arguments onto the stack and call ffi_closure_inner. */ stw %arg0, -36(%r3) stw %arg1, -40(%r3) stw %arg2, -44(%r3) stw %arg3, -48(%r3) copy %r21, %arg0 bl ffi_closure_inner_pa32, %r2 copy %r3, %arg1 ldwm -64(%sp), %r3 ldw -20(%sp), %rp ldw -36(%sp), %ret0 bv %r0(%rp) ldw -40(%sp), %ret1 .exit .procend L$FE2: .SPACE $PRIVATE$ .SUBSPA $DATA$ .align 4 .EXPORT _GLOBAL__F_ffi_call_pa32,DATA _GLOBAL__F_ffi_call_pa32 L$frame1: .word L$ECIE1-L$SCIE1 ;# Length of Common Information Entry L$SCIE1: .word 0x0 ;# CIE Identifier Tag .byte 0x1 ;# CIE Version .ascii "\0" ;# CIE Augmentation .uleb128 0x1 ;# CIE Code Alignment Factor .sleb128 4 ;# CIE Data Alignment Factor .byte 0x2 ;# CIE RA Column .byte 0xc ;# DW_CFA_def_cfa .uleb128 0x1e .uleb128 0x0 .align 4 L$ECIE1: L$SFDE1: .word L$EFDE1-L$ASFDE1 ;# FDE Length L$ASFDE1: .word L$ASFDE1-L$frame1 ;# FDE CIE offset .word L$FB1 ;# FDE initial location .word L$FE1-L$FB1 ;# FDE address range .byte 0x4 ;# DW_CFA_advance_loc4 .word L$CFI11-L$FB1 .byte 0x83 ;# DW_CFA_offset, column 0x3 .uleb128 0x0 .byte 0x11 ;# DW_CFA_offset_extended_sf; save r2 at [r30-20] .uleb128 0x2 .sleb128 -5 .byte 0x4 ;# DW_CFA_advance_loc4 .word L$CFI12-L$CFI11 .byte 0xd ;# DW_CFA_def_cfa_register = r3 .uleb128 0x3 .byte 0x4 ;# DW_CFA_advance_loc4 .word L$CFI13-L$CFI12 .byte 0x84 ;# DW_CFA_offset, column 0x4 .uleb128 0x3 .align 4 L$EFDE1: L$SFDE2: .word L$EFDE2-L$ASFDE2 ;# FDE Length L$ASFDE2: .word L$ASFDE2-L$frame1 ;# FDE CIE offset .word L$FB2 ;# FDE initial location .word L$FE2-L$FB2 ;# FDE address range .byte 0x4 ;# DW_CFA_advance_loc4 .word L$CFI21-L$FB2 .byte 0x83 ;# DW_CFA_offset, column 0x3 .uleb128 0x0 .byte 0x11 ;# DW_CFA_offset_extended_sf .uleb128 0x2 .sleb128 -5 .byte 0x4 ;# DW_CFA_advance_loc4 .word L$CFI22-L$CFI21 .byte 0xd ;# DW_CFA_def_cfa_register = r3 .uleb128 0x3 .align 4 L$EFDE2: smalltalk-3.2.5/libffi/src/sh/0000755000175000017500000000000012130456004013135 500000000000000smalltalk-3.2.5/libffi/src/sh/ffitarget.h0000644000175000017500000000340512130343734015210 00000000000000/* -----------------------------------------------------------------*-C-*- ffitarget.h - Copyright (c) 1996-2003 Red Hat, Inc. Target configuration macros for SuperH. Permission is hereby granted, free of charge, to any person obtaining a copy of this software and associated documentation files (the ``Software''), to deal in the Software without restriction, including without limitation the rights to use, copy, modify, merge, publish, distribute, sublicense, and/or sell copies of the Software, and to permit persons to whom the Software is furnished to do so, subject to the following conditions: The above copyright notice and this permission notice shall be included in all copies or substantial portions of the Software. THE SOFTWARE IS PROVIDED ``AS IS'', WITHOUT WARRANTY OF ANY KIND, EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. ----------------------------------------------------------------------- */ #ifndef LIBFFI_TARGET_H #define LIBFFI_TARGET_H /* ---- Generic type definitions ----------------------------------------- */ #ifndef LIBFFI_ASM typedef unsigned long ffi_arg; typedef signed long ffi_sarg; typedef enum ffi_abi { FFI_FIRST_ABI = 0, FFI_SYSV, FFI_DEFAULT_ABI = FFI_SYSV, FFI_LAST_ABI = FFI_DEFAULT_ABI + 1 } ffi_abi; #endif #define FFI_CLOSURES 1 #define FFI_TRAMPOLINE_SIZE 16 #define FFI_NATIVE_RAW_API 0 #endif smalltalk-3.2.5/libffi/src/sh/sysv.S0000644000175000017500000003453712130343734014226 00000000000000/* ----------------------------------------------------------------------- sysv.S - Copyright (c) 2002, 2003, 2004, 2006, 2008 Kaz Kojima SuperH Foreign Function Interface Permission is hereby granted, free of charge, to any person obtaining a copy of this software and associated documentation files (the ``Software''), to deal in the Software without restriction, including without limitation the rights to use, copy, modify, merge, publish, distribute, sublicense, and/or sell copies of the Software, and to permit persons to whom the Software is furnished to do so, subject to the following conditions: The above copyright notice and this permission notice shall be included in all copies or substantial portions of the Software. THE SOFTWARE IS PROVIDED ``AS IS'', WITHOUT WARRANTY OF ANY KIND, EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. ----------------------------------------------------------------------- */ #define LIBFFI_ASM #include #include #ifdef HAVE_MACHINE_ASM_H #include #else /* XXX these lose for some platforms, I'm sure. */ #define CNAME(x) x #define ENTRY(x) .globl CNAME(x); .type CNAME(x),%function; CNAME(x): #endif #if defined(__HITACHI__) #define STRUCT_VALUE_ADDRESS_WITH_ARG 1 #else #define STRUCT_VALUE_ADDRESS_WITH_ARG 0 #endif .text # r4: ffi_prep_args # r5: &ecif # r6: bytes # r7: flags # sp+0: rvalue # sp+4: fn # This assumes we are using gas. ENTRY(ffi_call_SYSV) # Save registers .LFB1: mov.l r8,@-r15 .LCFI0: mov.l r9,@-r15 .LCFI1: mov.l r10,@-r15 .LCFI2: mov.l r12,@-r15 .LCFI3: mov.l r14,@-r15 .LCFI4: sts.l pr,@-r15 .LCFI5: mov r15,r14 .LCFI6: #if defined(__SH4__) mov r6,r8 mov r7,r9 sub r6,r15 add #-16,r15 mov #~7,r0 and r0,r15 mov r4,r0 jsr @r0 mov r15,r4 mov r9,r1 shlr8 r9 shlr8 r9 shlr8 r9 mov #FFI_TYPE_STRUCT,r2 cmp/eq r2,r9 bf 1f #if STRUCT_VALUE_ADDRESS_WITH_ARG mov.l @r15+,r4 bra 2f mov #5,r2 #else mov.l @r15+,r10 #endif 1: mov #4,r2 2: mov #4,r3 L_pass: cmp/pl r8 bf L_call_it mov r1,r0 and #3,r0 L_pass_d: cmp/eq #FFI_TYPE_DOUBLE,r0 bf L_pass_f mov r3,r0 and #1,r0 tst r0,r0 bt 1f add #1,r3 1: mov #12,r0 cmp/hs r0,r3 bt/s 3f shlr2 r1 bsr L_pop_d nop 3: add #2,r3 bra L_pass add #-8,r8 L_pop_d: mov r3,r0 add r0,r0 add r3,r0 add #-12,r0 braf r0 nop #ifdef __LITTLE_ENDIAN__ fmov.s @r15+,fr5 rts fmov.s @r15+,fr4 fmov.s @r15+,fr7 rts fmov.s @r15+,fr6 fmov.s @r15+,fr9 rts fmov.s @r15+,fr8 fmov.s @r15+,fr11 rts fmov.s @r15+,fr10 #else fmov.s @r15+,fr4 rts fmov.s @r15+,fr5 fmov.s @r15+,fr6 rts fmov.s @r15+,fr7 fmov.s @r15+,fr8 rts fmov.s @r15+,fr9 fmov.s @r15+,fr10 rts fmov.s @r15+,fr11 #endif L_pass_f: cmp/eq #FFI_TYPE_FLOAT,r0 bf L_pass_i mov #12,r0 cmp/hs r0,r3 bt/s 2f shlr2 r1 bsr L_pop_f nop 2: add #1,r3 bra L_pass add #-4,r8 L_pop_f: mov r3,r0 shll2 r0 add #-16,r0 braf r0 nop #ifdef __LITTLE_ENDIAN__ rts fmov.s @r15+,fr5 rts fmov.s @r15+,fr4 rts fmov.s @r15+,fr7 rts fmov.s @r15+,fr6 rts fmov.s @r15+,fr9 rts fmov.s @r15+,fr8 rts fmov.s @r15+,fr11 rts fmov.s @r15+,fr10 #else rts fmov.s @r15+,fr4 rts fmov.s @r15+,fr5 rts fmov.s @r15+,fr6 rts fmov.s @r15+,fr7 rts fmov.s @r15+,fr8 rts fmov.s @r15+,fr9 rts fmov.s @r15+,fr10 rts fmov.s @r15+,fr11 #endif L_pass_i: cmp/eq #FFI_TYPE_INT,r0 bf L_call_it mov #8,r0 cmp/hs r0,r2 bt/s 2f shlr2 r1 bsr L_pop_i nop 2: add #1,r2 bra L_pass add #-4,r8 L_pop_i: mov r2,r0 shll2 r0 add #-16,r0 braf r0 nop rts mov.l @r15+,r4 rts mov.l @r15+,r5 rts mov.l @r15+,r6 rts mov.l @r15+,r7 L_call_it: # call function #if (! STRUCT_VALUE_ADDRESS_WITH_ARG) mov r10, r2 #endif mov.l @(28,r14),r1 jsr @r1 nop L_ret_d: mov #FFI_TYPE_DOUBLE,r2 cmp/eq r2,r9 bf L_ret_ll mov.l @(24,r14),r1 #ifdef __LITTLE_ENDIAN__ fmov.s fr1,@r1 add #4,r1 bra L_epilogue fmov.s fr0,@r1 #else fmov.s fr0,@r1 add #4,r1 bra L_epilogue fmov.s fr1,@r1 #endif L_ret_ll: mov #FFI_TYPE_SINT64,r2 cmp/eq r2,r9 bt/s 1f mov #FFI_TYPE_UINT64,r2 cmp/eq r2,r9 bf L_ret_f 1: mov.l @(24,r14),r2 mov.l r0,@r2 bra L_epilogue mov.l r1,@(4,r2) L_ret_f: mov #FFI_TYPE_FLOAT,r2 cmp/eq r2,r9 bf L_ret_i mov.l @(24,r14),r1 bra L_epilogue fmov.s fr0,@r1 L_ret_i: mov #FFI_TYPE_INT,r2 cmp/eq r2,r9 bf L_epilogue mov.l @(24,r14),r1 bra L_epilogue mov.l r0,@r1 L_epilogue: # Remove the space we pushed for the args mov r14,r15 lds.l @r15+,pr mov.l @r15+,r14 mov.l @r15+,r12 mov.l @r15+,r10 mov.l @r15+,r9 rts mov.l @r15+,r8 #else mov r6,r8 mov r7,r9 sub r6,r15 add #-16,r15 mov #~7,r0 and r0,r15 mov r4,r0 jsr @r0 mov r15,r4 mov r9,r3 shlr8 r9 shlr8 r9 shlr8 r9 mov #FFI_TYPE_STRUCT,r2 cmp/eq r2,r9 bf 1f #if STRUCT_VALUE_ADDRESS_WITH_ARG mov.l @r15+,r4 bra 2f mov #5,r2 #else mov.l @r15+,r10 #endif 1: mov #4,r2 2: L_pass: cmp/pl r8 bf L_call_it mov r3,r0 and #3,r0 L_pass_d: cmp/eq #FFI_TYPE_DOUBLE,r0 bf L_pass_i mov r15,r0 and #7,r0 tst r0,r0 bt 1f add #4,r15 1: mov #8,r0 cmp/hs r0,r2 bt/s 2f shlr2 r3 bsr L_pop_d nop 2: add #2,r2 bra L_pass add #-8,r8 L_pop_d: mov r2,r0 add r0,r0 add r2,r0 add #-12,r0 add r0,r0 braf r0 nop mov.l @r15+,r4 rts mov.l @r15+,r5 mov.l @r15+,r5 rts mov.l @r15+,r6 mov.l @r15+,r6 rts mov.l @r15+,r7 rts mov.l @r15+,r7 L_pass_i: cmp/eq #FFI_TYPE_INT,r0 bf L_call_it mov #8,r0 cmp/hs r0,r2 bt/s 2f shlr2 r3 bsr L_pop_i nop 2: add #1,r2 bra L_pass add #-4,r8 L_pop_i: mov r2,r0 shll2 r0 add #-16,r0 braf r0 nop rts mov.l @r15+,r4 rts mov.l @r15+,r5 rts mov.l @r15+,r6 rts mov.l @r15+,r7 L_call_it: # call function #if (! STRUCT_VALUE_ADDRESS_WITH_ARG) mov r10, r2 #endif mov.l @(28,r14),r1 jsr @r1 nop L_ret_d: mov #FFI_TYPE_DOUBLE,r2 cmp/eq r2,r9 bf L_ret_ll mov.l @(24,r14),r2 mov.l r0,@r2 bra L_epilogue mov.l r1,@(4,r2) L_ret_ll: mov #FFI_TYPE_SINT64,r2 cmp/eq r2,r9 bt/s 1f mov #FFI_TYPE_UINT64,r2 cmp/eq r2,r9 bf L_ret_i 1: mov.l @(24,r14),r2 mov.l r0,@r2 bra L_epilogue mov.l r1,@(4,r2) L_ret_i: mov #FFI_TYPE_FLOAT,r2 cmp/eq r2,r9 bt 1f mov #FFI_TYPE_INT,r2 cmp/eq r2,r9 bf L_epilogue 1: mov.l @(24,r14),r1 bra L_epilogue mov.l r0,@r1 L_epilogue: # Remove the space we pushed for the args mov r14,r15 lds.l @r15+,pr mov.l @r15+,r14 mov.l @r15+,r12 mov.l @r15+,r10 mov.l @r15+,r9 rts mov.l @r15+,r8 #endif .LFE1: .ffi_call_SYSV_end: .size CNAME(ffi_call_SYSV),.ffi_call_SYSV_end-CNAME(ffi_call_SYSV) .globl ffi_closure_helper_SYSV ENTRY(ffi_closure_SYSV) .LFB2: mov.l r7,@-r15 .LCFI7: mov.l r6,@-r15 .LCFI8: mov.l r5,@-r15 .LCFI9: mov.l r4,@-r15 .LCFIA: mov.l r14,@-r15 .LCFIB: sts.l pr,@-r15 /* Stack layout: xx bytes (on stack parameters) 16 bytes (register parameters) 4 bytes (saved frame pointer) 4 bytes (saved return address) 32 bytes (floating register parameters, SH-4 only) 8 bytes (result) 4 bytes (pad) 4 bytes (5th arg) <- new stack pointer */ .LCFIC: #if defined(__SH4__) add #-48,r15 #else add #-16,r15 #endif .LCFID: mov r15,r14 .LCFIE: #if defined(__SH4__) mov r14,r1 add #48,r1 #ifdef __LITTLE_ENDIAN__ fmov.s fr10,@-r1 fmov.s fr11,@-r1 fmov.s fr8,@-r1 fmov.s fr9,@-r1 fmov.s fr6,@-r1 fmov.s fr7,@-r1 fmov.s fr4,@-r1 fmov.s fr5,@-r1 #else fmov.s fr11,@-r1 fmov.s fr10,@-r1 fmov.s fr9,@-r1 fmov.s fr8,@-r1 fmov.s fr7,@-r1 fmov.s fr6,@-r1 fmov.s fr5,@-r1 fmov.s fr4,@-r1 #endif mov r1,r7 mov r14,r6 add #56,r6 #else mov r14,r6 add #24,r6 #endif bt/s 10f mov r2, r5 mov r14,r1 add #8,r1 mov r1,r5 10: mov r14,r1 #if defined(__SH4__) add #72,r1 #else add #40,r1 #endif mov.l r1,@r14 #ifdef PIC mov.l L_got,r1 mova L_got,r0 add r0,r1 mov.l L_helper,r0 add r1,r0 #else mov.l L_helper,r0 #endif jsr @r0 mov r3,r4 shll r0 mov r0,r1 mova L_table,r0 add r1,r0 mov.w @r0,r0 mov r14,r2 braf r0 add #8,r2 0: .align 2 #ifdef PIC L_got: .long _GLOBAL_OFFSET_TABLE_ L_helper: .long ffi_closure_helper_SYSV@GOTOFF #else L_helper: .long ffi_closure_helper_SYSV #endif L_table: .short L_case_v - 0b /* FFI_TYPE_VOID */ .short L_case_i - 0b /* FFI_TYPE_INT */ #if defined(__SH4__) .short L_case_f - 0b /* FFI_TYPE_FLOAT */ .short L_case_d - 0b /* FFI_TYPE_DOUBLE */ .short L_case_d - 0b /* FFI_TYPE_LONGDOUBLE */ #else .short L_case_i - 0b /* FFI_TYPE_FLOAT */ .short L_case_ll - 0b /* FFI_TYPE_DOUBLE */ .short L_case_ll - 0b /* FFI_TYPE_LONGDOUBLE */ #endif .short L_case_uq - 0b /* FFI_TYPE_UINT8 */ .short L_case_q - 0b /* FFI_TYPE_SINT8 */ .short L_case_uh - 0b /* FFI_TYPE_UINT16 */ .short L_case_h - 0b /* FFI_TYPE_SINT16 */ .short L_case_i - 0b /* FFI_TYPE_UINT32 */ .short L_case_i - 0b /* FFI_TYPE_SINT32 */ .short L_case_ll - 0b /* FFI_TYPE_UINT64 */ .short L_case_ll - 0b /* FFI_TYPE_SINT64 */ .short L_case_v - 0b /* FFI_TYPE_STRUCT */ .short L_case_i - 0b /* FFI_TYPE_POINTER */ #if defined(__SH4__) L_case_d: #ifdef __LITTLE_ENDIAN__ fmov.s @r2+,fr1 bra L_case_v fmov.s @r2,fr0 #else fmov.s @r2+,fr0 bra L_case_v fmov.s @r2,fr1 #endif L_case_f: bra L_case_v fmov.s @r2,fr0 #endif L_case_ll: mov.l @r2+,r0 bra L_case_v mov.l @r2,r1 L_case_i: bra L_case_v mov.l @r2,r0 L_case_q: #ifdef __LITTLE_ENDIAN__ #else add #3,r2 #endif bra L_case_v mov.b @r2,r0 L_case_uq: #ifdef __LITTLE_ENDIAN__ #else add #3,r2 #endif mov.b @r2,r0 bra L_case_v extu.b r0,r0 L_case_h: #ifdef __LITTLE_ENDIAN__ #else add #2,r2 #endif bra L_case_v mov.w @r2,r0 L_case_uh: #ifdef __LITTLE_ENDIAN__ #else add #2,r2 #endif mov.w @r2,r0 extu.w r0,r0 /* fall through */ L_case_v: #if defined(__SH4__) add #48,r15 #else add #16,r15 #endif lds.l @r15+,pr mov.l @r15+,r14 rts add #16,r15 .LFE2: .ffi_closure_SYSV_end: .size CNAME(ffi_closure_SYSV),.ffi_closure_SYSV_end-CNAME(ffi_closure_SYSV) #if defined __ELF__ && defined __linux__ .section .note.GNU-stack,"",@progbits #endif .section ".eh_frame","aw",@progbits __FRAME_BEGIN__: .4byte .LECIE1-.LSCIE1 /* Length of Common Information Entry */ .LSCIE1: .4byte 0x0 /* CIE Identifier Tag */ .byte 0x1 /* CIE Version */ #ifdef PIC .ascii "zR\0" /* CIE Augmentation */ #else .byte 0x0 /* CIE Augmentation */ #endif .byte 0x1 /* uleb128 0x1; CIE Code Alignment Factor */ .byte 0x7c /* sleb128 -4; CIE Data Alignment Factor */ .byte 0x11 /* CIE RA Column */ #ifdef PIC .uleb128 0x1 /* Augmentation size */ .byte 0x10 /* FDE Encoding (pcrel) */ #endif .byte 0xc /* DW_CFA_def_cfa */ .byte 0xf /* uleb128 0xf */ .byte 0x0 /* uleb128 0x0 */ .align 2 .LECIE1: .LSFDE1: .4byte .LEFDE1-.LASFDE1 /* FDE Length */ .LASFDE1: .4byte .LASFDE1-__FRAME_BEGIN__ /* FDE CIE offset */ #ifdef PIC .4byte .LFB1-. /* FDE initial location */ #else .4byte .LFB1 /* FDE initial location */ #endif .4byte .LFE1-.LFB1 /* FDE address range */ #ifdef PIC .uleb128 0x0 /* Augmentation size */ #endif .byte 0x4 /* DW_CFA_advance_loc4 */ .4byte .LCFI0-.LFB1 .byte 0xe /* DW_CFA_def_cfa_offset */ .byte 0x4 /* uleb128 0x4 */ .byte 0x4 /* DW_CFA_advance_loc4 */ .4byte .LCFI1-.LCFI0 .byte 0xe /* DW_CFA_def_cfa_offset */ .byte 0x8 /* uleb128 0x4 */ .byte 0x4 /* DW_CFA_advance_loc4 */ .4byte .LCFI2-.LCFI1 .byte 0xe /* DW_CFA_def_cfa_offset */ .byte 0xc /* uleb128 0x4 */ .byte 0x4 /* DW_CFA_advance_loc4 */ .4byte .LCFI3-.LCFI2 .byte 0xe /* DW_CFA_def_cfa_offset */ .byte 0x10 /* uleb128 0x4 */ .byte 0x4 /* DW_CFA_advance_loc4 */ .4byte .LCFI4-.LCFI3 .byte 0xe /* DW_CFA_def_cfa_offset */ .byte 0x14 /* uleb128 0x4 */ .byte 0x4 /* DW_CFA_advance_loc4 */ .4byte .LCFI5-.LCFI4 .byte 0xe /* DW_CFA_def_cfa_offset */ .byte 0x18 /* uleb128 0x4 */ .byte 0x91 /* DW_CFA_offset, column 0x11 */ .byte 0x6 /* uleb128 0x6 */ .byte 0x8e /* DW_CFA_offset, column 0xe */ .byte 0x5 /* uleb128 0x5 */ .byte 0x8c /* DW_CFA_offset, column 0xc */ .byte 0x4 /* uleb128 0x4 */ .byte 0x8a /* DW_CFA_offset, column 0xa */ .byte 0x3 /* uleb128 0x3 */ .byte 0x89 /* DW_CFA_offset, column 0x9 */ .byte 0x2 /* uleb128 0x2 */ .byte 0x88 /* DW_CFA_offset, column 0x8 */ .byte 0x1 /* uleb128 0x1 */ .byte 0x4 /* DW_CFA_advance_loc4 */ .4byte .LCFI6-.LCFI5 .byte 0xd /* DW_CFA_def_cfa_register */ .byte 0xe /* uleb128 0xe */ .align 2 .LEFDE1: .LSFDE3: .4byte .LEFDE3-.LASFDE3 /* FDE Length */ .LASFDE3: .4byte .LASFDE3-__FRAME_BEGIN__ /* FDE CIE offset */ #ifdef PIC .4byte .LFB2-. /* FDE initial location */ #else .4byte .LFB2 /* FDE initial location */ #endif .4byte .LFE2-.LFB2 /* FDE address range */ #ifdef PIC .uleb128 0x0 /* Augmentation size */ #endif .byte 0x4 /* DW_CFA_advance_loc4 */ .4byte .LCFI7-.LFB2 .byte 0xe /* DW_CFA_def_cfa_offset */ .byte 0x4 /* uleb128 0x4 */ .byte 0x4 /* DW_CFA_advance_loc4 */ .4byte .LCFI8-.LCFI7 .byte 0xe /* DW_CFA_def_cfa_offset */ .byte 0x8 /* uleb128 0x4 */ .byte 0x4 /* DW_CFA_advance_loc4 */ .4byte .LCFI9-.LCFI8 .byte 0xe /* DW_CFA_def_cfa_offset */ .byte 0xc /* uleb128 0x4 */ .byte 0x4 /* DW_CFA_advance_loc4 */ .4byte .LCFIA-.LCFI9 .byte 0xe /* DW_CFA_def_cfa_offset */ .byte 0x10 /* uleb128 0x4 */ .byte 0x4 /* DW_CFA_advance_loc4 */ .4byte .LCFIB-.LCFIA .byte 0xe /* DW_CFA_def_cfa_offset */ .byte 0x14 /* uleb128 0x4 */ .byte 0x4 /* DW_CFA_advance_loc4 */ .4byte .LCFIC-.LCFIB .byte 0xe /* DW_CFA_def_cfa_offset */ .byte 0x18 /* uleb128 0x4 */ .byte 0x4 /* DW_CFA_advance_loc4 */ .4byte .LCFID-.LCFIC .byte 0xe /* DW_CFA_def_cfa_offset */ #if defined(__SH4__) .byte 24+48 /* uleb128 24+48 */ #else .byte 24+16 /* uleb128 24+16 */ #endif .byte 0x91 /* DW_CFA_offset, column 0x11 */ .byte 0x6 /* uleb128 0x6 */ .byte 0x8e /* DW_CFA_offset, column 0xe */ .byte 0x5 /* uleb128 0x5 */ .byte 0x84 /* DW_CFA_offset, column 0x4 */ .byte 0x4 /* uleb128 0x4 */ .byte 0x85 /* DW_CFA_offset, column 0x5 */ .byte 0x3 /* uleb128 0x3 */ .byte 0x86 /* DW_CFA_offset, column 0x6 */ .byte 0x2 /* uleb128 0x2 */ .byte 0x87 /* DW_CFA_offset, column 0x7 */ .byte 0x1 /* uleb128 0x1 */ .byte 0x4 /* DW_CFA_advance_loc4 */ .4byte .LCFIE-.LCFID .byte 0xd /* DW_CFA_def_cfa_register */ .byte 0xe /* uleb128 0xe */ .align 2 .LEFDE3: smalltalk-3.2.5/libffi/src/sh/ffi.c0000644000175000017500000003562512130343734014005 00000000000000/* ----------------------------------------------------------------------- ffi.c - Copyright (c) 2002, 2003, 2004, 2005, 2006, 2007, 2008 Kaz Kojima Copyright (c) 2008 Red Hat, Inc. SuperH Foreign Function Interface Permission is hereby granted, free of charge, to any person obtaining a copy of this software and associated documentation files (the ``Software''), to deal in the Software without restriction, including without limitation the rights to use, copy, modify, merge, publish, distribute, sublicense, and/or sell copies of the Software, and to permit persons to whom the Software is furnished to do so, subject to the following conditions: The above copyright notice and this permission notice shall be included in all copies or substantial portions of the Software. THE SOFTWARE IS PROVIDED ``AS IS'', WITHOUT WARRANTY OF ANY KIND, EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. ----------------------------------------------------------------------- */ #include #include #include #define NGREGARG 4 #if defined(__SH4__) #define NFREGARG 8 #endif #if defined(__HITACHI__) #define STRUCT_VALUE_ADDRESS_WITH_ARG 1 #else #define STRUCT_VALUE_ADDRESS_WITH_ARG 0 #endif /* If the structure has essentialy an unique element, return its type. */ static int simple_type (ffi_type *arg) { if (arg->type != FFI_TYPE_STRUCT) return arg->type; else if (arg->elements[1]) return FFI_TYPE_STRUCT; return simple_type (arg->elements[0]); } static int return_type (ffi_type *arg) { unsigned short type; if (arg->type != FFI_TYPE_STRUCT) return arg->type; type = simple_type (arg->elements[0]); if (! arg->elements[1]) { switch (type) { case FFI_TYPE_SINT8: case FFI_TYPE_UINT8: case FFI_TYPE_SINT16: case FFI_TYPE_UINT16: case FFI_TYPE_SINT32: case FFI_TYPE_UINT32: return FFI_TYPE_INT; default: return type; } } /* gcc uses r0/r1 pair for some kind of structures. */ if (arg->size <= 2 * sizeof (int)) { int i = 0; ffi_type *e; while ((e = arg->elements[i++])) { type = simple_type (e); switch (type) { case FFI_TYPE_SINT32: case FFI_TYPE_UINT32: case FFI_TYPE_INT: case FFI_TYPE_FLOAT: return FFI_TYPE_UINT64; default: break; } } } return FFI_TYPE_STRUCT; } /* ffi_prep_args is called by the assembly routine once stack space has been allocated for the function's arguments */ void ffi_prep_args(char *stack, extended_cif *ecif) { register unsigned int i; register int tmp; register unsigned int avn; register void **p_argv; register char *argp; register ffi_type **p_arg; int greg, ireg; #if defined(__SH4__) int freg = 0; #endif tmp = 0; argp = stack; if (return_type (ecif->cif->rtype) == FFI_TYPE_STRUCT) { *(void **) argp = ecif->rvalue; argp += 4; ireg = STRUCT_VALUE_ADDRESS_WITH_ARG ? 1 : 0; } else ireg = 0; /* Set arguments for registers. */ greg = ireg; avn = ecif->cif->nargs; p_argv = ecif->avalue; for (i = 0, p_arg = ecif->cif->arg_types; i < avn; i++, p_arg++, p_argv++) { size_t z; z = (*p_arg)->size; if (z < sizeof(int)) { if (greg++ >= NGREGARG) continue; z = sizeof(int); switch ((*p_arg)->type) { case FFI_TYPE_SINT8: *(signed int *) argp = (signed int)*(SINT8 *)(* p_argv); break; case FFI_TYPE_UINT8: *(unsigned int *) argp = (unsigned int)*(UINT8 *)(* p_argv); break; case FFI_TYPE_SINT16: *(signed int *) argp = (signed int)*(SINT16 *)(* p_argv); break; case FFI_TYPE_UINT16: *(unsigned int *) argp = (unsigned int)*(UINT16 *)(* p_argv); break; case FFI_TYPE_STRUCT: *(unsigned int *) argp = (unsigned int)*(UINT32 *)(* p_argv); break; default: FFI_ASSERT(0); } argp += z; } else if (z == sizeof(int)) { #if defined(__SH4__) if ((*p_arg)->type == FFI_TYPE_FLOAT) { if (freg++ >= NFREGARG) continue; } else #endif { if (greg++ >= NGREGARG) continue; } *(unsigned int *) argp = (unsigned int)*(UINT32 *)(* p_argv); argp += z; } #if defined(__SH4__) else if ((*p_arg)->type == FFI_TYPE_DOUBLE) { if (freg + 1 >= NFREGARG) continue; freg = (freg + 1) & ~1; freg += 2; memcpy (argp, *p_argv, z); argp += z; } #endif else { int n = (z + sizeof (int) - 1) / sizeof (int); #if defined(__SH4__) if (greg + n - 1 >= NGREGARG) continue; #else if (greg >= NGREGARG) continue; #endif greg += n; memcpy (argp, *p_argv, z); argp += n * sizeof (int); } } /* Set arguments on stack. */ greg = ireg; #if defined(__SH4__) freg = 0; #endif p_argv = ecif->avalue; for (i = 0, p_arg = ecif->cif->arg_types; i < avn; i++, p_arg++, p_argv++) { size_t z; z = (*p_arg)->size; if (z < sizeof(int)) { if (greg++ < NGREGARG) continue; z = sizeof(int); switch ((*p_arg)->type) { case FFI_TYPE_SINT8: *(signed int *) argp = (signed int)*(SINT8 *)(* p_argv); break; case FFI_TYPE_UINT8: *(unsigned int *) argp = (unsigned int)*(UINT8 *)(* p_argv); break; case FFI_TYPE_SINT16: *(signed int *) argp = (signed int)*(SINT16 *)(* p_argv); break; case FFI_TYPE_UINT16: *(unsigned int *) argp = (unsigned int)*(UINT16 *)(* p_argv); break; case FFI_TYPE_STRUCT: *(unsigned int *) argp = (unsigned int)*(UINT32 *)(* p_argv); break; default: FFI_ASSERT(0); } argp += z; } else if (z == sizeof(int)) { #if defined(__SH4__) if ((*p_arg)->type == FFI_TYPE_FLOAT) { if (freg++ < NFREGARG) continue; } else #endif { if (greg++ < NGREGARG) continue; } *(unsigned int *) argp = (unsigned int)*(UINT32 *)(* p_argv); argp += z; } #if defined(__SH4__) else if ((*p_arg)->type == FFI_TYPE_DOUBLE) { if (freg + 1 < NFREGARG) { freg = (freg + 1) & ~1; freg += 2; continue; } memcpy (argp, *p_argv, z); argp += z; } #endif else { int n = (z + sizeof (int) - 1) / sizeof (int); if (greg + n - 1 < NGREGARG) { greg += n; continue; } #if (! defined(__SH4__)) else if (greg < NGREGARG) { greg = NGREGARG; continue; } #endif memcpy (argp, *p_argv, z); argp += n * sizeof (int); } } return; } /* Perform machine dependent cif processing */ ffi_status ffi_prep_cif_machdep(ffi_cif *cif) { int i, j; int size, type; int n, m; int greg; #if defined(__SH4__) int freg = 0; #endif cif->flags = 0; greg = ((return_type (cif->rtype) == FFI_TYPE_STRUCT) && STRUCT_VALUE_ADDRESS_WITH_ARG) ? 1 : 0; #if defined(__SH4__) for (i = j = 0; i < cif->nargs && j < 12; i++) { type = (cif->arg_types)[i]->type; switch (type) { case FFI_TYPE_FLOAT: if (freg >= NFREGARG) continue; freg++; cif->flags += ((cif->arg_types)[i]->type) << (2 * j); j++; break; case FFI_TYPE_DOUBLE: if ((freg + 1) >= NFREGARG) continue; freg = (freg + 1) & ~1; freg += 2; cif->flags += ((cif->arg_types)[i]->type) << (2 * j); j++; break; default: size = (cif->arg_types)[i]->size; n = (size + sizeof (int) - 1) / sizeof (int); if (greg + n - 1 >= NGREGARG) continue; greg += n; for (m = 0; m < n; m++) cif->flags += FFI_TYPE_INT << (2 * j++); break; } } #else for (i = j = 0; i < cif->nargs && j < 4; i++) { size = (cif->arg_types)[i]->size; n = (size + sizeof (int) - 1) / sizeof (int); if (greg >= NGREGARG) continue; else if (greg + n - 1 >= NGREGARG) n = NGREGARG - greg; greg += n; for (m = 0; m < n; m++) cif->flags += FFI_TYPE_INT << (2 * j++); } #endif /* Set the return type flag */ switch (cif->rtype->type) { case FFI_TYPE_STRUCT: cif->flags += (unsigned) (return_type (cif->rtype)) << 24; break; case FFI_TYPE_VOID: case FFI_TYPE_FLOAT: case FFI_TYPE_DOUBLE: case FFI_TYPE_SINT64: case FFI_TYPE_UINT64: cif->flags += (unsigned) cif->rtype->type << 24; break; default: cif->flags += FFI_TYPE_INT << 24; break; } return FFI_OK; } extern void ffi_call_SYSV(void (*)(char *, extended_cif *), extended_cif *, unsigned, unsigned, unsigned *, void (*fn)(void)); void ffi_call(ffi_cif *cif, void (*fn)(void), void *rvalue, void **avalue) { extended_cif ecif; UINT64 trvalue; ecif.cif = cif; ecif.avalue = avalue; /* If the return value is a struct and we don't have a return */ /* value address then we need to make one */ if (cif->rtype->type == FFI_TYPE_STRUCT && return_type (cif->rtype) != FFI_TYPE_STRUCT) ecif.rvalue = &trvalue; else if ((rvalue == NULL) && (cif->rtype->type == FFI_TYPE_STRUCT)) { ecif.rvalue = alloca(cif->rtype->size); } else ecif.rvalue = rvalue; switch (cif->abi) { case FFI_SYSV: ffi_call_SYSV(ffi_prep_args, &ecif, cif->bytes, cif->flags, ecif.rvalue, fn); break; default: FFI_ASSERT(0); break; } if (rvalue && cif->rtype->type == FFI_TYPE_STRUCT && return_type (cif->rtype) != FFI_TYPE_STRUCT) memcpy (rvalue, &trvalue, cif->rtype->size); } extern void ffi_closure_SYSV (void); #if defined(__SH4__) extern void __ic_invalidate (void *line); #endif ffi_status ffi_prep_closure_loc (ffi_closure* closure, ffi_cif* cif, void (*fun)(ffi_cif*, void*, void**, void*), void *user_data, void *codeloc) { unsigned int *tramp; unsigned int insn; FFI_ASSERT (cif->abi == FFI_GCC_SYSV); tramp = (unsigned int *) &closure->tramp[0]; /* Set T bit if the function returns a struct pointed with R2. */ insn = (return_type (cif->rtype) == FFI_TYPE_STRUCT ? 0x0018 /* sett */ : 0x0008 /* clrt */); #ifdef __LITTLE_ENDIAN__ tramp[0] = 0xd301d102; tramp[1] = 0x0000412b | (insn << 16); #else tramp[0] = 0xd102d301; tramp[1] = 0x412b0000 | insn; #endif *(void **) &tramp[2] = (void *)codeloc; /* ctx */ *(void **) &tramp[3] = (void *)ffi_closure_SYSV; /* funaddr */ closure->cif = cif; closure->fun = fun; closure->user_data = user_data; #if defined(__SH4__) /* Flush the icache. */ __ic_invalidate(codeloc); #endif return FFI_OK; } /* Basically the trampoline invokes ffi_closure_SYSV, and on * entry, r3 holds the address of the closure. * After storing the registers that could possibly contain * parameters to be passed into the stack frame and setting * up space for a return value, ffi_closure_SYSV invokes the * following helper function to do most of the work. */ #ifdef __LITTLE_ENDIAN__ #define OFS_INT8 0 #define OFS_INT16 0 #else #define OFS_INT8 3 #define OFS_INT16 2 #endif int ffi_closure_helper_SYSV (ffi_closure *closure, void *rvalue, unsigned long *pgr, unsigned long *pfr, unsigned long *pst) { void **avalue; ffi_type **p_arg; int i, avn; int ireg, greg = 0; #if defined(__SH4__) int freg = 0; #endif ffi_cif *cif; cif = closure->cif; avalue = alloca(cif->nargs * sizeof(void *)); /* Copy the caller's structure return value address so that the closure returns the data directly to the caller. */ if (cif->rtype->type == FFI_TYPE_STRUCT && STRUCT_VALUE_ADDRESS_WITH_ARG) { rvalue = (void *) *pgr++; ireg = 1; } else ireg = 0; cif = closure->cif; greg = ireg; avn = cif->nargs; /* Grab the addresses of the arguments from the stack frame. */ for (i = 0, p_arg = cif->arg_types; i < avn; i++, p_arg++) { size_t z; z = (*p_arg)->size; if (z < sizeof(int)) { if (greg++ >= NGREGARG) continue; z = sizeof(int); switch ((*p_arg)->type) { case FFI_TYPE_SINT8: case FFI_TYPE_UINT8: avalue[i] = (((char *)pgr) + OFS_INT8); break; case FFI_TYPE_SINT16: case FFI_TYPE_UINT16: avalue[i] = (((char *)pgr) + OFS_INT16); break; case FFI_TYPE_STRUCT: avalue[i] = pgr; break; default: FFI_ASSERT(0); } pgr++; } else if (z == sizeof(int)) { #if defined(__SH4__) if ((*p_arg)->type == FFI_TYPE_FLOAT) { if (freg++ >= NFREGARG) continue; avalue[i] = pfr; pfr++; } else #endif { if (greg++ >= NGREGARG) continue; avalue[i] = pgr; pgr++; } } #if defined(__SH4__) else if ((*p_arg)->type == FFI_TYPE_DOUBLE) { if (freg + 1 >= NFREGARG) continue; if (freg & 1) pfr++; freg = (freg + 1) & ~1; freg += 2; avalue[i] = pfr; pfr += 2; } #endif else { int n = (z + sizeof (int) - 1) / sizeof (int); #if defined(__SH4__) if (greg + n - 1 >= NGREGARG) continue; #else if (greg >= NGREGARG) continue; #endif greg += n; avalue[i] = pgr; pgr += n; } } greg = ireg; #if defined(__SH4__) freg = 0; #endif for (i = 0, p_arg = cif->arg_types; i < avn; i++, p_arg++) { size_t z; z = (*p_arg)->size; if (z < sizeof(int)) { if (greg++ < NGREGARG) continue; z = sizeof(int); switch ((*p_arg)->type) { case FFI_TYPE_SINT8: case FFI_TYPE_UINT8: avalue[i] = (((char *)pst) + OFS_INT8); break; case FFI_TYPE_SINT16: case FFI_TYPE_UINT16: avalue[i] = (((char *)pst) + OFS_INT16); break; case FFI_TYPE_STRUCT: avalue[i] = pst; break; default: FFI_ASSERT(0); } pst++; } else if (z == sizeof(int)) { #if defined(__SH4__) if ((*p_arg)->type == FFI_TYPE_FLOAT) { if (freg++ < NFREGARG) continue; } else #endif { if (greg++ < NGREGARG) continue; } avalue[i] = pst; pst++; } #if defined(__SH4__) else if ((*p_arg)->type == FFI_TYPE_DOUBLE) { if (freg + 1 < NFREGARG) { freg = (freg + 1) & ~1; freg += 2; continue; } avalue[i] = pst; pst += 2; } #endif else { int n = (z + sizeof (int) - 1) / sizeof (int); if (greg + n - 1 < NGREGARG) { greg += n; continue; } #if (! defined(__SH4__)) else if (greg < NGREGARG) { greg += n; pst += greg - NGREGARG; continue; } #endif avalue[i] = pst; pst += n; } } (closure->fun) (cif, rvalue, avalue, closure->user_data); /* Tell ffi_closure_SYSV how to perform return type promotions. */ return return_type (cif->rtype); } smalltalk-3.2.5/libffi/src/cris/0000755000175000017500000000000012130456004013463 500000000000000smalltalk-3.2.5/libffi/src/cris/ffitarget.h0000644000175000017500000000365312130343734015543 00000000000000/* -----------------------------------------------------------------*-C-*- ffitarget.h - Copyright (c) 1996-2003 Red Hat, Inc. Target configuration macros for CRIS. Permission is hereby granted, free of charge, to any person obtaining a copy of this software and associated documentation files (the ``Software''), to deal in the Software without restriction, including without limitation the rights to use, copy, modify, merge, publish, distribute, sublicense, and/or sell copies of the Software, and to permit persons to whom the Software is furnished to do so, subject to the following conditions: The above copyright notice and this permission notice shall be included in all copies or substantial portions of the Software. THE SOFTWARE IS PROVIDED ``AS IS'', WITHOUT WARRANTY OF ANY KIND, EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. ----------------------------------------------------------------------- */ #ifndef LIBFFI_TARGET_H #define LIBFFI_TARGET_H #ifndef LIBFFI_ASM typedef unsigned long ffi_arg; typedef signed long ffi_sarg; typedef enum ffi_abi { FFI_FIRST_ABI = 0, FFI_SYSV, FFI_DEFAULT_ABI = FFI_SYSV, FFI_LAST_ABI = FFI_DEFAULT_ABI + 1 } ffi_abi; #endif /* ---- Definitions for closures ----------------------------------------- */ #define FFI_CLOSURES 1 #define FFI_CRIS_TRAMPOLINE_CODE_PART_SIZE 36 #define FFI_CRIS_TRAMPOLINE_DATA_PART_SIZE (7*4) #define FFI_TRAMPOLINE_SIZE \ (FFI_CRIS_TRAMPOLINE_CODE_PART_SIZE + FFI_CRIS_TRAMPOLINE_DATA_PART_SIZE) #define FFI_NATIVE_RAW_API 0 #endif smalltalk-3.2.5/libffi/src/cris/sysv.S0000644000175000017500000001254712130343734014551 00000000000000/* ----------------------------------------------------------------------- sysv.S - Copyright (c) 2004 Simon Posnjak Copyright (c) 2005 Axis Communications AB CRIS Foreign Function Interface Permission is hereby granted, free of charge, to any person obtaining a copy of this software and associated documentation files (the ``Software''), to deal in the Software without restriction, including without limitation the rights to use, copy, modify, merge, publish, distribute, sublicense, and/or sell copies of the Software, and to permit persons to whom the Software is furnished to do so, subject to the following conditions: The above copyright notice and this permission notice shall be included in all copies or substantial portions of the Software. THE SOFTWARE IS PROVIDED ``AS IS'', WITHOUT WARRANTY OF ANY KIND, EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL SIMON POSNJAK BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. ----------------------------------------------------------------------- */ #define LIBFFI_ASM #include #define CONCAT(x,y) x ## y #define XCONCAT(x,y) CONCAT (x, y) #define L(x) XCONCAT (__USER_LABEL_PREFIX__, x) .text ;; OK, when we get called we should have this (according to ;; AXIS ETRAX 100LX Programmer's Manual chapter 6.3). ;; ;; R10: ffi_prep_args (func. pointer) ;; R11: &ecif ;; R12: cif->bytes ;; R13: fig->flags ;; sp+0: ecif.rvalue ;; sp+4: fn (function pointer to the function that we need to call) .globl L(ffi_call_SYSV) .type L(ffi_call_SYSV),@function .hidden L(ffi_call_SYSV) L(ffi_call_SYSV): ;; Save the regs to the stack. push $srp ;; Used for stack pointer saving. push $r6 ;; Used for function address pointer. push $r7 ;; Used for stack pointer saving. push $r8 ;; We save fig->flags to stack we will need them after we ;; call The Function. push $r13 ;; Saving current stack pointer. move.d $sp,$r8 move.d $sp,$r6 ;; Move address of ffi_prep_args to r13. move.d $r10,$r13 ;; Make room on the stack for the args of fn. sub.d $r12,$sp ;; Function void ffi_prep_args(char *stack, extended_cif *ecif) parameters are: ;; r10 <-- stack pointer ;; r11 <-- &ecif (already there) move.d $sp,$r10 ;; Call the function. jsr $r13 ;; Save the size of the structures which are passed on stack. move.d $r10,$r7 ;; Move first four args in to r10..r13. move.d [$sp+0],$r10 move.d [$sp+4],$r11 move.d [$sp+8],$r12 move.d [$sp+12],$r13 ;; Adjust the stack and check if any parameters are given on stack. addq 16,$sp sub.d $r7,$r6 cmp.d $sp,$r6 bpl go_on nop go_on_no_params_on_stack: move.d $r6,$sp go_on: ;; Discover if we need to put rval address in to r9. move.d [$r8+0],$r7 cmpq FFI_TYPE_STRUCT,$r7 bne call_now nop ;; Move rval address to $r9. move.d [$r8+20],$r9 call_now: ;; Move address of The Function in to r7. move.d [$r8+24],$r7 ;; Call The Function. jsr $r7 ;; Reset stack. move.d $r8,$sp ;; Load rval type (fig->flags) in to r13. pop $r13 ;; Detect rval type. cmpq FFI_TYPE_VOID,$r13 beq epilogue cmpq FFI_TYPE_STRUCT,$r13 beq epilogue cmpq FFI_TYPE_DOUBLE,$r13 beq return_double_or_longlong cmpq FFI_TYPE_UINT64,$r13 beq return_double_or_longlong cmpq FFI_TYPE_SINT64,$r13 beq return_double_or_longlong nop ;; Just return the 32 bit value. ba return nop return_double_or_longlong: ;; Load half of the rval to r10 and the other half to r11. move.d [$sp+16],$r13 move.d $r10,[$r13] addq 4,$r13 move.d $r11,[$r13] ba epilogue nop return: ;; Load the rval to r10. move.d [$sp+16],$r13 move.d $r10,[$r13] epilogue: pop $r8 pop $r7 pop $r6 Jump [$sp+] .size ffi_call_SYSV,.-ffi_call_SYSV /* Save R10..R13 into an array, somewhat like varargs. Copy the next argument too, to simplify handling of any straddling parameter. Save R9 and SP after those. Jump to function handling the rest. Since this is a template, copied and the main function filled in by the user. */ .globl L(ffi_cris_trampoline_template) .type L(ffi_cris_trampoline_template),@function .hidden L(ffi_cris_trampoline_template) L(ffi_cris_trampoline_template): 0: /* The value we get for "PC" is right after the prefix instruction, two bytes from the beginning, i.e. 0b+2. */ move.d $r10,[$pc+2f-(0b+2)] move.d $pc,$r10 1: addq 2f-1b+4,$r10 move.d $r11,[$r10+] move.d $r12,[$r10+] move.d $r13,[$r10+] move.d [$sp],$r11 move.d $r11,[$r10+] move.d $r9,[$r10+] move.d $sp,[$r10+] subq FFI_CRIS_TRAMPOLINE_DATA_PART_SIZE,$r10 move.d 0,$r11 3: jump 0 2: .size ffi_cris_trampoline_template,.-0b /* This macro create a constant usable as "extern const int \name" in C from within libffi, when \name has no prefix decoration. */ .macro const name,value .globl \name .type \name,@object .hidden \name \name: .dword \value .size \name,4 .endm /* Constants for offsets within the trampoline. We could do this with just symbols, avoiding memory contents and memory accesses, but the C usage code would look a bit stranger. */ const L(ffi_cris_trampoline_fn_offset),2b-4-0b const L(ffi_cris_trampoline_closure_offset),3b-4-0b smalltalk-3.2.5/libffi/src/cris/ffi.c0000644000175000017500000002267212130343734014331 00000000000000/* ----------------------------------------------------------------------- ffi.c - Copyright (c) 1998 Cygnus Solutions Copyright (c) 2004 Simon Posnjak Copyright (c) 2005 Axis Communications AB Copyright (C) 2007 Free Software Foundation, Inc. CRIS Foreign Function Interface Permission is hereby granted, free of charge, to any person obtaining a copy of this software and associated documentation files (the ``Software''), to deal in the Software without restriction, including without limitation the rights to use, copy, modify, merge, publish, distribute, sublicense, and/or sell copies of the Software, and to permit persons to whom the Software is furnished to do so, subject to the following conditions: The above copyright notice and this permission notice shall be included in all copies or substantial portions of the Software. THE SOFTWARE IS PROVIDED ``AS IS'', WITHOUT WARRANTY OF ANY KIND, EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL SIMON POSNJAK BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. ----------------------------------------------------------------------- */ #include #include #define STACK_ARG_SIZE(x) ALIGN(x, FFI_SIZEOF_ARG) static ffi_status initialize_aggregate_packed_struct (ffi_type * arg) { ffi_type **ptr; FFI_ASSERT (arg != NULL); FFI_ASSERT (arg->elements != NULL); FFI_ASSERT (arg->size == 0); FFI_ASSERT (arg->alignment == 0); ptr = &(arg->elements[0]); while ((*ptr) != NULL) { if (((*ptr)->size == 0) && (initialize_aggregate_packed_struct ((*ptr)) != FFI_OK)) return FFI_BAD_TYPEDEF; FFI_ASSERT (ffi_type_test ((*ptr))); arg->size += (*ptr)->size; arg->alignment = (arg->alignment > (*ptr)->alignment) ? arg->alignment : (*ptr)->alignment; ptr++; } if (arg->size == 0) return FFI_BAD_TYPEDEF; else return FFI_OK; } int ffi_prep_args (char *stack, extended_cif * ecif) { unsigned int i; unsigned int struct_count = 0; void **p_argv; char *argp; ffi_type **p_arg; argp = stack; p_argv = ecif->avalue; for (i = ecif->cif->nargs, p_arg = ecif->cif->arg_types; (i != 0); i--, p_arg++) { size_t z; switch ((*p_arg)->type) { case FFI_TYPE_STRUCT: { z = (*p_arg)->size; if (z <= 4) { memcpy (argp, *p_argv, z); z = 4; } else if (z <= 8) { memcpy (argp, *p_argv, z); z = 8; } else { unsigned int uiLocOnStack; z = sizeof (void *); uiLocOnStack = 4 * ecif->cif->nargs + struct_count; struct_count = struct_count + (*p_arg)->size; *(unsigned int *) argp = (unsigned int) (UINT32 *) (stack + uiLocOnStack); memcpy ((stack + uiLocOnStack), *p_argv, (*p_arg)->size); } break; } default: z = (*p_arg)->size; if (z < sizeof (int)) { switch ((*p_arg)->type) { case FFI_TYPE_SINT8: *(signed int *) argp = (signed int) *(SINT8 *) (*p_argv); break; case FFI_TYPE_UINT8: *(unsigned int *) argp = (unsigned int) *(UINT8 *) (*p_argv); break; case FFI_TYPE_SINT16: *(signed int *) argp = (signed int) *(SINT16 *) (*p_argv); break; case FFI_TYPE_UINT16: *(unsigned int *) argp = (unsigned int) *(UINT16 *) (*p_argv); break; default: FFI_ASSERT (0); } z = sizeof (int); } else if (z == sizeof (int)) *(unsigned int *) argp = (unsigned int) *(UINT32 *) (*p_argv); else memcpy (argp, *p_argv, z); break; } p_argv++; argp += z; } return (struct_count); } ffi_status ffi_prep_cif (ffi_cif * cif, ffi_abi abi, unsigned int nargs, ffi_type * rtype, ffi_type ** atypes) { unsigned bytes = 0; unsigned int i; ffi_type **ptr; FFI_ASSERT (cif != NULL); FFI_ASSERT ((abi > FFI_FIRST_ABI) && (abi <= FFI_DEFAULT_ABI)); cif->abi = abi; cif->arg_types = atypes; cif->nargs = nargs; cif->rtype = rtype; cif->flags = 0; if ((cif->rtype->size == 0) && (initialize_aggregate_packed_struct (cif->rtype) != FFI_OK)) return FFI_BAD_TYPEDEF; FFI_ASSERT_VALID_TYPE (cif->rtype); for (ptr = cif->arg_types, i = cif->nargs; i > 0; i--, ptr++) { if (((*ptr)->size == 0) && (initialize_aggregate_packed_struct ((*ptr)) != FFI_OK)) return FFI_BAD_TYPEDEF; FFI_ASSERT_VALID_TYPE (*ptr); if (((*ptr)->alignment - 1) & bytes) bytes = ALIGN (bytes, (*ptr)->alignment); if ((*ptr)->type == FFI_TYPE_STRUCT) { if ((*ptr)->size > 8) { bytes += (*ptr)->size; bytes += sizeof (void *); } else { if ((*ptr)->size > 4) bytes += 8; else bytes += 4; } } else bytes += STACK_ARG_SIZE ((*ptr)->size); } cif->bytes = bytes; return ffi_prep_cif_machdep (cif); } ffi_status ffi_prep_cif_machdep (ffi_cif * cif) { switch (cif->rtype->type) { case FFI_TYPE_VOID: case FFI_TYPE_STRUCT: case FFI_TYPE_FLOAT: case FFI_TYPE_DOUBLE: case FFI_TYPE_SINT64: case FFI_TYPE_UINT64: cif->flags = (unsigned) cif->rtype->type; break; default: cif->flags = FFI_TYPE_INT; break; } return FFI_OK; } extern void ffi_call_SYSV (int (*)(char *, extended_cif *), extended_cif *, unsigned, unsigned, unsigned *, void (*fn) ()) __attribute__ ((__visibility__ ("hidden"))); void ffi_call (ffi_cif * cif, void (*fn) (), void *rvalue, void **avalue) { extended_cif ecif; ecif.cif = cif; ecif.avalue = avalue; if ((rvalue == NULL) && (cif->rtype->type == FFI_TYPE_STRUCT)) { ecif.rvalue = alloca (cif->rtype->size); } else ecif.rvalue = rvalue; switch (cif->abi) { case FFI_SYSV: ffi_call_SYSV (ffi_prep_args, &ecif, cif->bytes, cif->flags, ecif.rvalue, fn); break; default: FFI_ASSERT (0); break; } } /* Because the following variables are not exported outside libffi, we mark them hidden. */ /* Assembly code for the jump stub. */ extern const char ffi_cris_trampoline_template[] __attribute__ ((__visibility__ ("hidden"))); /* Offset into ffi_cris_trampoline_template of where to put the ffi_prep_closure_inner function. */ extern const int ffi_cris_trampoline_fn_offset __attribute__ ((__visibility__ ("hidden"))); /* Offset into ffi_cris_trampoline_template of where to put the closure data. */ extern const int ffi_cris_trampoline_closure_offset __attribute__ ((__visibility__ ("hidden"))); /* This function is sibling-called (jumped to) by the closure trampoline. We get R10..R13 at PARAMS[0..3] and a copy of [SP] at PARAMS[4] to simplify handling of a straddling parameter. A copy of R9 is at PARAMS[5] and SP at PARAMS[6]. These parameters are put at the appropriate place in CLOSURE which is then executed and the return value is passed back to the caller. */ static unsigned long long ffi_prep_closure_inner (void **params, ffi_closure* closure) { char *register_args = (char *) params; void *struct_ret = params[5]; char *stack_args = params[6]; char *ptr = register_args; ffi_cif *cif = closure->cif; ffi_type **arg_types = cif->arg_types; /* Max room needed is number of arguments as 64-bit values. */ void **avalue = alloca (closure->cif->nargs * sizeof(void *)); int i; int doing_regs; long long llret = 0; /* Find the address of each argument. */ for (i = 0, doing_regs = 1; i < cif->nargs; i++) { /* Types up to and including 8 bytes go by-value. */ if (arg_types[i]->size <= 4) { avalue[i] = ptr; ptr += 4; } else if (arg_types[i]->size <= 8) { avalue[i] = ptr; ptr += 8; } else { FFI_ASSERT (arg_types[i]->type == FFI_TYPE_STRUCT); /* Passed by-reference, so copy the pointer. */ avalue[i] = *(void **) ptr; ptr += 4; } /* If we've handled more arguments than fit in registers, start looking at the those passed on the stack. Step over the first one if we had a straddling parameter. */ if (doing_regs && ptr >= register_args + 4*4) { ptr = stack_args + ((ptr > register_args + 4*4) ? 4 : 0); doing_regs = 0; } } /* Invoke the closure. */ (closure->fun) (cif, cif->rtype->type == FFI_TYPE_STRUCT /* The caller allocated space for the return structure, and passed a pointer to this space in R9. */ ? struct_ret /* We take advantage of being able to ignore that the high part isn't set if the return value is not in R10:R11, but in R10 only. */ : (void *) &llret, avalue, closure->user_data); return llret; } /* API function: Prepare the trampoline. */ ffi_status ffi_prep_closure_loc (ffi_closure* closure, ffi_cif* cif, void (*fun)(ffi_cif *, void *, void **, void*), void *user_data, void *codeloc) { void *innerfn = ffi_prep_closure_inner; FFI_ASSERT (cif->abi == FFI_SYSV); closure->cif = cif; closure->user_data = user_data; closure->fun = fun; memcpy (closure->tramp, ffi_cris_trampoline_template, FFI_CRIS_TRAMPOLINE_CODE_PART_SIZE); memcpy (closure->tramp + ffi_cris_trampoline_fn_offset, &innerfn, sizeof (void *)); memcpy (closure->tramp + ffi_cris_trampoline_closure_offset, &codeloc, sizeof (void *)); return FFI_OK; } smalltalk-3.2.5/libffi/src/dlmalloc.c0000644000175000017500000054601612130343734014417 00000000000000/* This is a version (aka dlmalloc) of malloc/free/realloc written by Doug Lea and released to the public domain, as explained at http://creativecommons.org/licenses/publicdomain. Send questions, comments, complaints, performance data, etc to dl@cs.oswego.edu * Version 2.8.3 Thu Sep 22 11:16:15 2005 Doug Lea (dl at gee) Note: There may be an updated version of this malloc obtainable at ftp://gee.cs.oswego.edu/pub/misc/malloc.c Check before installing! * Quickstart This library is all in one file to simplify the most common usage: ftp it, compile it (-O3), and link it into another program. All of the compile-time options default to reasonable values for use on most platforms. You might later want to step through various compile-time and dynamic tuning options. For convenience, an include file for code using this malloc is at: ftp://gee.cs.oswego.edu/pub/misc/malloc-2.8.3.h You don't really need this .h file unless you call functions not defined in your system include files. The .h file contains only the excerpts from this file needed for using this malloc on ANSI C/C++ systems, so long as you haven't changed compile-time options about naming and tuning parameters. If you do, then you can create your own malloc.h that does include all settings by cutting at the point indicated below. Note that you may already by default be using a C library containing a malloc that is based on some version of this malloc (for example in linux). You might still want to use the one in this file to customize settings or to avoid overheads associated with library versions. * Vital statistics: Supported pointer/size_t representation: 4 or 8 bytes size_t MUST be an unsigned type of the same width as pointers. (If you are using an ancient system that declares size_t as a signed type, or need it to be a different width than pointers, you can use a previous release of this malloc (e.g. 2.7.2) supporting these.) Alignment: 8 bytes (default) This suffices for nearly all current machines and C compilers. However, you can define MALLOC_ALIGNMENT to be wider than this if necessary (up to 128bytes), at the expense of using more space. Minimum overhead per allocated chunk: 4 or 8 bytes (if 4byte sizes) 8 or 16 bytes (if 8byte sizes) Each malloced chunk has a hidden word of overhead holding size and status information, and additional cross-check word if FOOTERS is defined. Minimum allocated size: 4-byte ptrs: 16 bytes (including overhead) 8-byte ptrs: 32 bytes (including overhead) Even a request for zero bytes (i.e., malloc(0)) returns a pointer to something of the minimum allocatable size. The maximum overhead wastage (i.e., number of extra bytes allocated than were requested in malloc) is less than or equal to the minimum size, except for requests >= mmap_threshold that are serviced via mmap(), where the worst case wastage is about 32 bytes plus the remainder from a system page (the minimal mmap unit); typically 4096 or 8192 bytes. Security: static-safe; optionally more or less The "security" of malloc refers to the ability of malicious code to accentuate the effects of errors (for example, freeing space that is not currently malloc'ed or overwriting past the ends of chunks) in code that calls malloc. This malloc guarantees not to modify any memory locations below the base of heap, i.e., static variables, even in the presence of usage errors. The routines additionally detect most improper frees and reallocs. All this holds as long as the static bookkeeping for malloc itself is not corrupted by some other means. This is only one aspect of security -- these checks do not, and cannot, detect all possible programming errors. If FOOTERS is defined nonzero, then each allocated chunk carries an additional check word to verify that it was malloced from its space. These check words are the same within each execution of a program using malloc, but differ across executions, so externally crafted fake chunks cannot be freed. This improves security by rejecting frees/reallocs that could corrupt heap memory, in addition to the checks preventing writes to statics that are always on. This may further improve security at the expense of time and space overhead. (Note that FOOTERS may also be worth using with MSPACES.) By default detected errors cause the program to abort (calling "abort()"). You can override this to instead proceed past errors by defining PROCEED_ON_ERROR. In this case, a bad free has no effect, and a malloc that encounters a bad address caused by user overwrites will ignore the bad address by dropping pointers and indices to all known memory. This may be appropriate for programs that should continue if at all possible in the face of programming errors, although they may run out of memory because dropped memory is never reclaimed. If you don't like either of these options, you can define CORRUPTION_ERROR_ACTION and USAGE_ERROR_ACTION to do anything else. And if if you are sure that your program using malloc has no errors or vulnerabilities, you can define INSECURE to 1, which might (or might not) provide a small performance improvement. Thread-safety: NOT thread-safe unless USE_LOCKS defined When USE_LOCKS is defined, each public call to malloc, free, etc is surrounded with either a pthread mutex or a win32 spinlock (depending on WIN32). This is not especially fast, and can be a major bottleneck. It is designed only to provide minimal protection in concurrent environments, and to provide a basis for extensions. If you are using malloc in a concurrent program, consider instead using ptmalloc, which is derived from a version of this malloc. (See http://www.malloc.de). System requirements: Any combination of MORECORE and/or MMAP/MUNMAP This malloc can use unix sbrk or any emulation (invoked using the CALL_MORECORE macro) and/or mmap/munmap or any emulation (invoked using CALL_MMAP/CALL_MUNMAP) to get and release system memory. On most unix systems, it tends to work best if both MORECORE and MMAP are enabled. On Win32, it uses emulations based on VirtualAlloc. It also uses common C library functions like memset. Compliance: I believe it is compliant with the Single Unix Specification (See http://www.unix.org). Also SVID/XPG, ANSI C, and probably others as well. * Overview of algorithms This is not the fastest, most space-conserving, most portable, or most tunable malloc ever written. However it is among the fastest while also being among the most space-conserving, portable and tunable. Consistent balance across these factors results in a good general-purpose allocator for malloc-intensive programs. In most ways, this malloc is a best-fit allocator. Generally, it chooses the best-fitting existing chunk for a request, with ties broken in approximately least-recently-used order. (This strategy normally maintains low fragmentation.) However, for requests less than 256bytes, it deviates from best-fit when there is not an exactly fitting available chunk by preferring to use space adjacent to that used for the previous small request, as well as by breaking ties in approximately most-recently-used order. (These enhance locality of series of small allocations.) And for very large requests (>= 256Kb by default), it relies on system memory mapping facilities, if supported. (This helps avoid carrying around and possibly fragmenting memory used only for large chunks.) All operations (except malloc_stats and mallinfo) have execution times that are bounded by a constant factor of the number of bits in a size_t, not counting any clearing in calloc or copying in realloc, or actions surrounding MORECORE and MMAP that have times proportional to the number of non-contiguous regions returned by system allocation routines, which is often just 1. The implementation is not very modular and seriously overuses macros. Perhaps someday all C compilers will do as good a job inlining modular code as can now be done by brute-force expansion, but now, enough of them seem not to. Some compilers issue a lot of warnings about code that is dead/unreachable only on some platforms, and also about intentional uses of negation on unsigned types. All known cases of each can be ignored. For a longer but out of date high-level description, see http://gee.cs.oswego.edu/dl/html/malloc.html * MSPACES If MSPACES is defined, then in addition to malloc, free, etc., this file also defines mspace_malloc, mspace_free, etc. These are versions of malloc routines that take an "mspace" argument obtained using create_mspace, to control all internal bookkeeping. If ONLY_MSPACES is defined, only these versions are compiled. So if you would like to use this allocator for only some allocations, and your system malloc for others, you can compile with ONLY_MSPACES and then do something like... static mspace mymspace = create_mspace(0,0); // for example #define mymalloc(bytes) mspace_malloc(mymspace, bytes) (Note: If you only need one instance of an mspace, you can instead use "USE_DL_PREFIX" to relabel the global malloc.) You can similarly create thread-local allocators by storing mspaces as thread-locals. For example: static __thread mspace tlms = 0; void* tlmalloc(size_t bytes) { if (tlms == 0) tlms = create_mspace(0, 0); return mspace_malloc(tlms, bytes); } void tlfree(void* mem) { mspace_free(tlms, mem); } Unless FOOTERS is defined, each mspace is completely independent. You cannot allocate from one and free to another (although conformance is only weakly checked, so usage errors are not always caught). If FOOTERS is defined, then each chunk carries around a tag indicating its originating mspace, and frees are directed to their originating spaces. ------------------------- Compile-time options --------------------------- Be careful in setting #define values for numerical constants of type size_t. On some systems, literal values are not automatically extended to size_t precision unless they are explicitly casted. WIN32 default: defined if _WIN32 defined Defining WIN32 sets up defaults for MS environment and compilers. Otherwise defaults are for unix. MALLOC_ALIGNMENT default: (size_t)8 Controls the minimum alignment for malloc'ed chunks. It must be a power of two and at least 8, even on machines for which smaller alignments would suffice. It may be defined as larger than this though. Note however that code and data structures are optimized for the case of 8-byte alignment. MSPACES default: 0 (false) If true, compile in support for independent allocation spaces. This is only supported if HAVE_MMAP is true. ONLY_MSPACES default: 0 (false) If true, only compile in mspace versions, not regular versions. USE_LOCKS default: 0 (false) Causes each call to each public routine to be surrounded with pthread or WIN32 mutex lock/unlock. (If set true, this can be overridden on a per-mspace basis for mspace versions.) FOOTERS default: 0 If true, provide extra checking and dispatching by placing information in the footers of allocated chunks. This adds space and time overhead. INSECURE default: 0 If true, omit checks for usage errors and heap space overwrites. USE_DL_PREFIX default: NOT defined Causes compiler to prefix all public routines with the string 'dl'. This can be useful when you only want to use this malloc in one part of a program, using your regular system malloc elsewhere. ABORT default: defined as abort() Defines how to abort on failed checks. On most systems, a failed check cannot die with an "assert" or even print an informative message, because the underlying print routines in turn call malloc, which will fail again. Generally, the best policy is to simply call abort(). It's not very useful to do more than this because many errors due to overwriting will show up as address faults (null, odd addresses etc) rather than malloc-triggered checks, so will also abort. Also, most compilers know that abort() does not return, so can better optimize code conditionally calling it. PROCEED_ON_ERROR default: defined as 0 (false) Controls whether detected bad addresses cause them to bypassed rather than aborting. If set, detected bad arguments to free and realloc are ignored. And all bookkeeping information is zeroed out upon a detected overwrite of freed heap space, thus losing the ability to ever return it from malloc again, but enabling the application to proceed. If PROCEED_ON_ERROR is defined, the static variable malloc_corruption_error_count is compiled in and can be examined to see if errors have occurred. This option generates slower code than the default abort policy. DEBUG default: NOT defined The DEBUG setting is mainly intended for people trying to modify this code or diagnose problems when porting to new platforms. However, it may also be able to better isolate user errors than just using runtime checks. The assertions in the check routines spell out in more detail the assumptions and invariants underlying the algorithms. The checking is fairly extensive, and will slow down execution noticeably. Calling malloc_stats or mallinfo with DEBUG set will attempt to check every non-mmapped allocated and free chunk in the course of computing the summaries. ABORT_ON_ASSERT_FAILURE default: defined as 1 (true) Debugging assertion failures can be nearly impossible if your version of the assert macro causes malloc to be called, which will lead to a cascade of further failures, blowing the runtime stack. ABORT_ON_ASSERT_FAILURE cause assertions failures to call abort(), which will usually make debugging easier. MALLOC_FAILURE_ACTION default: sets errno to ENOMEM, or no-op on win32 The action to take before "return 0" when malloc fails to be able to return memory because there is none available. HAVE_MORECORE default: 1 (true) unless win32 or ONLY_MSPACES True if this system supports sbrk or an emulation of it. MORECORE default: sbrk The name of the sbrk-style system routine to call to obtain more memory. See below for guidance on writing custom MORECORE functions. The type of the argument to sbrk/MORECORE varies across systems. It cannot be size_t, because it supports negative arguments, so it is normally the signed type of the same width as size_t (sometimes declared as "intptr_t"). It doesn't much matter though. Internally, we only call it with arguments less than half the max value of a size_t, which should work across all reasonable possibilities, although sometimes generating compiler warnings. See near the end of this file for guidelines for creating a custom version of MORECORE. MORECORE_CONTIGUOUS default: 1 (true) If true, take advantage of fact that consecutive calls to MORECORE with positive arguments always return contiguous increasing addresses. This is true of unix sbrk. It does not hurt too much to set it true anyway, since malloc copes with non-contiguities. Setting it false when definitely non-contiguous saves time and possibly wasted space it would take to discover this though. MORECORE_CANNOT_TRIM default: NOT defined True if MORECORE cannot release space back to the system when given negative arguments. This is generally necessary only if you are using a hand-crafted MORECORE function that cannot handle negative arguments. HAVE_MMAP default: 1 (true) True if this system supports mmap or an emulation of it. If so, and HAVE_MORECORE is not true, MMAP is used for all system allocation. If set and HAVE_MORECORE is true as well, MMAP is primarily used to directly allocate very large blocks. It is also used as a backup strategy in cases where MORECORE fails to provide space from system. Note: A single call to MUNMAP is assumed to be able to unmap memory that may have be allocated using multiple calls to MMAP, so long as they are adjacent. HAVE_MREMAP default: 1 on linux, else 0 If true realloc() uses mremap() to re-allocate large blocks and extend or shrink allocation spaces. MMAP_CLEARS default: 1 on unix True if mmap clears memory so calloc doesn't need to. This is true for standard unix mmap using /dev/zero. USE_BUILTIN_FFS default: 0 (i.e., not used) Causes malloc to use the builtin ffs() function to compute indices. Some compilers may recognize and intrinsify ffs to be faster than the supplied C version. Also, the case of x86 using gcc is special-cased to an asm instruction, so is already as fast as it can be, and so this setting has no effect. (On most x86s, the asm version is only slightly faster than the C version.) malloc_getpagesize default: derive from system includes, or 4096. The system page size. To the extent possible, this malloc manages memory from the system in page-size units. This may be (and usually is) a function rather than a constant. This is ignored if WIN32, where page size is determined using getSystemInfo during initialization. USE_DEV_RANDOM default: 0 (i.e., not used) Causes malloc to use /dev/random to initialize secure magic seed for stamping footers. Otherwise, the current time is used. NO_MALLINFO default: 0 If defined, don't compile "mallinfo". This can be a simple way of dealing with mismatches between system declarations and those in this file. MALLINFO_FIELD_TYPE default: size_t The type of the fields in the mallinfo struct. This was originally defined as "int" in SVID etc, but is more usefully defined as size_t. The value is used only if HAVE_USR_INCLUDE_MALLOC_H is not set REALLOC_ZERO_BYTES_FREES default: not defined This should be set if a call to realloc with zero bytes should be the same as a call to free. Some people think it should. Otherwise, since this malloc returns a unique pointer for malloc(0), so does realloc(p, 0). LACKS_UNISTD_H, LACKS_FCNTL_H, LACKS_SYS_PARAM_H, LACKS_SYS_MMAN_H LACKS_STRINGS_H, LACKS_STRING_H, LACKS_SYS_TYPES_H, LACKS_ERRNO_H LACKS_STDLIB_H default: NOT defined unless on WIN32 Define these if your system does not have these header files. You might need to manually insert some of the declarations they provide. DEFAULT_GRANULARITY default: page size if MORECORE_CONTIGUOUS, system_info.dwAllocationGranularity in WIN32, otherwise 64K. Also settable using mallopt(M_GRANULARITY, x) The unit for allocating and deallocating memory from the system. On most systems with contiguous MORECORE, there is no reason to make this more than a page. However, systems with MMAP tend to either require or encourage larger granularities. You can increase this value to prevent system allocation functions to be called so often, especially if they are slow. The value must be at least one page and must be a power of two. Setting to 0 causes initialization to either page size or win32 region size. (Note: In previous versions of malloc, the equivalent of this option was called "TOP_PAD") DEFAULT_TRIM_THRESHOLD default: 2MB Also settable using mallopt(M_TRIM_THRESHOLD, x) The maximum amount of unused top-most memory to keep before releasing via malloc_trim in free(). Automatic trimming is mainly useful in long-lived programs using contiguous MORECORE. Because trimming via sbrk can be slow on some systems, and can sometimes be wasteful (in cases where programs immediately afterward allocate more large chunks) the value should be high enough so that your overall system performance would improve by releasing this much memory. As a rough guide, you might set to a value close to the average size of a process (program) running on your system. Releasing this much memory would allow such a process to run in memory. Generally, it is worth tuning trim thresholds when a program undergoes phases where several large chunks are allocated and released in ways that can reuse each other's storage, perhaps mixed with phases where there are no such chunks at all. The trim value must be greater than page size to have any useful effect. To disable trimming completely, you can set to MAX_SIZE_T. Note that the trick some people use of mallocing a huge space and then freeing it at program startup, in an attempt to reserve system memory, doesn't have the intended effect under automatic trimming, since that memory will immediately be returned to the system. DEFAULT_MMAP_THRESHOLD default: 256K Also settable using mallopt(M_MMAP_THRESHOLD, x) The request size threshold for using MMAP to directly service a request. Requests of at least this size that cannot be allocated using already-existing space will be serviced via mmap. (If enough normal freed space already exists it is used instead.) Using mmap segregates relatively large chunks of memory so that they can be individually obtained and released from the host system. A request serviced through mmap is never reused by any other request (at least not directly; the system may just so happen to remap successive requests to the same locations). Segregating space in this way has the benefits that: Mmapped space can always be individually released back to the system, which helps keep the system level memory demands of a long-lived program low. Also, mapped memory doesn't become `locked' between other chunks, as can happen with normally allocated chunks, which means that even trimming via malloc_trim would not release them. However, it has the disadvantage that the space cannot be reclaimed, consolidated, and then used to service later requests, as happens with normal chunks. The advantages of mmap nearly always outweigh disadvantages for "large" chunks, but the value of "large" may vary across systems. The default is an empirically derived value that works well in most systems. You can disable mmap by setting to MAX_SIZE_T. */ #ifndef WIN32 #ifdef _WIN32 #define WIN32 1 #endif /* _WIN32 */ #endif /* WIN32 */ #ifdef WIN32 #define WIN32_LEAN_AND_MEAN #include #define HAVE_MMAP 1 #define HAVE_MORECORE 0 #define LACKS_UNISTD_H #define LACKS_SYS_PARAM_H #define LACKS_SYS_MMAN_H #define LACKS_STRING_H #define LACKS_STRINGS_H #define LACKS_SYS_TYPES_H #define LACKS_ERRNO_H #define MALLOC_FAILURE_ACTION #define MMAP_CLEARS 0 /* WINCE and some others apparently don't clear */ #endif /* WIN32 */ #ifdef __OS2__ #define INCL_DOS #include #define HAVE_MMAP 1 #define HAVE_MORECORE 0 #define LACKS_SYS_MMAN_H #endif /* __OS2__ */ #if defined(DARWIN) || defined(_DARWIN) /* Mac OSX docs advise not to use sbrk; it seems better to use mmap */ #ifndef HAVE_MORECORE #define HAVE_MORECORE 0 #define HAVE_MMAP 1 #endif /* HAVE_MORECORE */ #endif /* DARWIN */ #ifndef LACKS_SYS_TYPES_H #include /* For size_t */ #endif /* LACKS_SYS_TYPES_H */ /* The maximum possible size_t value has all bits set */ #define MAX_SIZE_T (~(size_t)0) #ifndef ONLY_MSPACES #define ONLY_MSPACES 0 #endif /* ONLY_MSPACES */ #ifndef MSPACES #if ONLY_MSPACES #define MSPACES 1 #else /* ONLY_MSPACES */ #define MSPACES 0 #endif /* ONLY_MSPACES */ #endif /* MSPACES */ #ifndef MALLOC_ALIGNMENT #define MALLOC_ALIGNMENT ((size_t)8U) #endif /* MALLOC_ALIGNMENT */ #ifndef FOOTERS #define FOOTERS 0 #endif /* FOOTERS */ #ifndef ABORT #define ABORT abort() #endif /* ABORT */ #ifndef ABORT_ON_ASSERT_FAILURE #define ABORT_ON_ASSERT_FAILURE 1 #endif /* ABORT_ON_ASSERT_FAILURE */ #ifndef PROCEED_ON_ERROR #define PROCEED_ON_ERROR 0 #endif /* PROCEED_ON_ERROR */ #ifndef USE_LOCKS #define USE_LOCKS 0 #endif /* USE_LOCKS */ #ifndef INSECURE #define INSECURE 0 #endif /* INSECURE */ #ifndef HAVE_MMAP #define HAVE_MMAP 1 #endif /* HAVE_MMAP */ #ifndef MMAP_CLEARS #define MMAP_CLEARS 1 #endif /* MMAP_CLEARS */ #ifndef HAVE_MREMAP #ifdef linux #define HAVE_MREMAP 1 #else /* linux */ #define HAVE_MREMAP 0 #endif /* linux */ #endif /* HAVE_MREMAP */ #ifndef MALLOC_FAILURE_ACTION #define MALLOC_FAILURE_ACTION errno = ENOMEM; #endif /* MALLOC_FAILURE_ACTION */ #ifndef HAVE_MORECORE #if ONLY_MSPACES #define HAVE_MORECORE 0 #else /* ONLY_MSPACES */ #define HAVE_MORECORE 1 #endif /* ONLY_MSPACES */ #endif /* HAVE_MORECORE */ #if !HAVE_MORECORE #define MORECORE_CONTIGUOUS 0 #else /* !HAVE_MORECORE */ #ifndef MORECORE #define MORECORE sbrk #endif /* MORECORE */ #ifndef MORECORE_CONTIGUOUS #define MORECORE_CONTIGUOUS 1 #endif /* MORECORE_CONTIGUOUS */ #endif /* HAVE_MORECORE */ #ifndef DEFAULT_GRANULARITY #if MORECORE_CONTIGUOUS #define DEFAULT_GRANULARITY (0) /* 0 means to compute in init_mparams */ #else /* MORECORE_CONTIGUOUS */ #define DEFAULT_GRANULARITY ((size_t)64U * (size_t)1024U) #endif /* MORECORE_CONTIGUOUS */ #endif /* DEFAULT_GRANULARITY */ #ifndef DEFAULT_TRIM_THRESHOLD #ifndef MORECORE_CANNOT_TRIM #define DEFAULT_TRIM_THRESHOLD ((size_t)2U * (size_t)1024U * (size_t)1024U) #else /* MORECORE_CANNOT_TRIM */ #define DEFAULT_TRIM_THRESHOLD MAX_SIZE_T #endif /* MORECORE_CANNOT_TRIM */ #endif /* DEFAULT_TRIM_THRESHOLD */ #ifndef DEFAULT_MMAP_THRESHOLD #if HAVE_MMAP #define DEFAULT_MMAP_THRESHOLD ((size_t)256U * (size_t)1024U) #else /* HAVE_MMAP */ #define DEFAULT_MMAP_THRESHOLD MAX_SIZE_T #endif /* HAVE_MMAP */ #endif /* DEFAULT_MMAP_THRESHOLD */ #ifndef USE_BUILTIN_FFS #define USE_BUILTIN_FFS 0 #endif /* USE_BUILTIN_FFS */ #ifndef USE_DEV_RANDOM #define USE_DEV_RANDOM 0 #endif /* USE_DEV_RANDOM */ #ifndef NO_MALLINFO #define NO_MALLINFO 0 #endif /* NO_MALLINFO */ #ifndef MALLINFO_FIELD_TYPE #define MALLINFO_FIELD_TYPE size_t #endif /* MALLINFO_FIELD_TYPE */ /* mallopt tuning options. SVID/XPG defines four standard parameter numbers for mallopt, normally defined in malloc.h. None of these are used in this malloc, so setting them has no effect. But this malloc does support the following options. */ #define M_TRIM_THRESHOLD (-1) #define M_GRANULARITY (-2) #define M_MMAP_THRESHOLD (-3) /* ------------------------ Mallinfo declarations ------------------------ */ #if !NO_MALLINFO /* This version of malloc supports the standard SVID/XPG mallinfo routine that returns a struct containing usage properties and statistics. It should work on any system that has a /usr/include/malloc.h defining struct mallinfo. The main declaration needed is the mallinfo struct that is returned (by-copy) by mallinfo(). The malloinfo struct contains a bunch of fields that are not even meaningful in this version of malloc. These fields are are instead filled by mallinfo() with other numbers that might be of interest. HAVE_USR_INCLUDE_MALLOC_H should be set if you have a /usr/include/malloc.h file that includes a declaration of struct mallinfo. If so, it is included; else a compliant version is declared below. These must be precisely the same for mallinfo() to work. The original SVID version of this struct, defined on most systems with mallinfo, declares all fields as ints. But some others define as unsigned long. If your system defines the fields using a type of different width than listed here, you MUST #include your system version and #define HAVE_USR_INCLUDE_MALLOC_H. */ /* #define HAVE_USR_INCLUDE_MALLOC_H */ #ifdef HAVE_USR_INCLUDE_MALLOC_H #include "/usr/include/malloc.h" #else /* HAVE_USR_INCLUDE_MALLOC_H */ struct mallinfo { MALLINFO_FIELD_TYPE arena; /* non-mmapped space allocated from system */ MALLINFO_FIELD_TYPE ordblks; /* number of free chunks */ MALLINFO_FIELD_TYPE smblks; /* always 0 */ MALLINFO_FIELD_TYPE hblks; /* always 0 */ MALLINFO_FIELD_TYPE hblkhd; /* space in mmapped regions */ MALLINFO_FIELD_TYPE usmblks; /* maximum total allocated space */ MALLINFO_FIELD_TYPE fsmblks; /* always 0 */ MALLINFO_FIELD_TYPE uordblks; /* total allocated space */ MALLINFO_FIELD_TYPE fordblks; /* total free space */ MALLINFO_FIELD_TYPE keepcost; /* releasable (via malloc_trim) space */ }; #endif /* HAVE_USR_INCLUDE_MALLOC_H */ #endif /* NO_MALLINFO */ #ifdef __cplusplus extern "C" { #endif /* __cplusplus */ #if !ONLY_MSPACES /* ------------------- Declarations of public routines ------------------- */ #ifndef USE_DL_PREFIX #define dlcalloc calloc #define dlfree free #define dlmalloc malloc #define dlmemalign memalign #define dlrealloc realloc #define dlvalloc valloc #define dlpvalloc pvalloc #define dlmallinfo mallinfo #define dlmallopt mallopt #define dlmalloc_trim malloc_trim #define dlmalloc_stats malloc_stats #define dlmalloc_usable_size malloc_usable_size #define dlmalloc_footprint malloc_footprint #define dlmalloc_max_footprint malloc_max_footprint #define dlindependent_calloc independent_calloc #define dlindependent_comalloc independent_comalloc #endif /* USE_DL_PREFIX */ /* malloc(size_t n) Returns a pointer to a newly allocated chunk of at least n bytes, or null if no space is available, in which case errno is set to ENOMEM on ANSI C systems. If n is zero, malloc returns a minimum-sized chunk. (The minimum size is 16 bytes on most 32bit systems, and 32 bytes on 64bit systems.) Note that size_t is an unsigned type, so calls with arguments that would be negative if signed are interpreted as requests for huge amounts of space, which will often fail. The maximum supported value of n differs across systems, but is in all cases less than the maximum representable value of a size_t. */ void* dlmalloc(size_t); /* free(void* p) Releases the chunk of memory pointed to by p, that had been previously allocated using malloc or a related routine such as realloc. It has no effect if p is null. If p was not malloced or already freed, free(p) will by default cause the current program to abort. */ void dlfree(void*); /* calloc(size_t n_elements, size_t element_size); Returns a pointer to n_elements * element_size bytes, with all locations set to zero. */ void* dlcalloc(size_t, size_t); /* realloc(void* p, size_t n) Returns a pointer to a chunk of size n that contains the same data as does chunk p up to the minimum of (n, p's size) bytes, or null if no space is available. The returned pointer may or may not be the same as p. The algorithm prefers extending p in most cases when possible, otherwise it employs the equivalent of a malloc-copy-free sequence. If p is null, realloc is equivalent to malloc. If space is not available, realloc returns null, errno is set (if on ANSI) and p is NOT freed. if n is for fewer bytes than already held by p, the newly unused space is lopped off and freed if possible. realloc with a size argument of zero (re)allocates a minimum-sized chunk. The old unix realloc convention of allowing the last-free'd chunk to be used as an argument to realloc is not supported. */ void* dlrealloc(void*, size_t); /* memalign(size_t alignment, size_t n); Returns a pointer to a newly allocated chunk of n bytes, aligned in accord with the alignment argument. The alignment argument should be a power of two. If the argument is not a power of two, the nearest greater power is used. 8-byte alignment is guaranteed by normal malloc calls, so don't bother calling memalign with an argument of 8 or less. Overreliance on memalign is a sure way to fragment space. */ void* dlmemalign(size_t, size_t); /* valloc(size_t n); Equivalent to memalign(pagesize, n), where pagesize is the page size of the system. If the pagesize is unknown, 4096 is used. */ void* dlvalloc(size_t); /* mallopt(int parameter_number, int parameter_value) Sets tunable parameters The format is to provide a (parameter-number, parameter-value) pair. mallopt then sets the corresponding parameter to the argument value if it can (i.e., so long as the value is meaningful), and returns 1 if successful else 0. SVID/XPG/ANSI defines four standard param numbers for mallopt, normally defined in malloc.h. None of these are use in this malloc, so setting them has no effect. But this malloc also supports other options in mallopt. See below for details. Briefly, supported parameters are as follows (listed defaults are for "typical" configurations). Symbol param # default allowed param values M_TRIM_THRESHOLD -1 2*1024*1024 any (MAX_SIZE_T disables) M_GRANULARITY -2 page size any power of 2 >= page size M_MMAP_THRESHOLD -3 256*1024 any (or 0 if no MMAP support) */ int dlmallopt(int, int); /* malloc_footprint(); Returns the number of bytes obtained from the system. The total number of bytes allocated by malloc, realloc etc., is less than this value. Unlike mallinfo, this function returns only a precomputed result, so can be called frequently to monitor memory consumption. Even if locks are otherwise defined, this function does not use them, so results might not be up to date. */ size_t dlmalloc_footprint(void); /* malloc_max_footprint(); Returns the maximum number of bytes obtained from the system. This value will be greater than current footprint if deallocated space has been reclaimed by the system. The peak number of bytes allocated by malloc, realloc etc., is less than this value. Unlike mallinfo, this function returns only a precomputed result, so can be called frequently to monitor memory consumption. Even if locks are otherwise defined, this function does not use them, so results might not be up to date. */ size_t dlmalloc_max_footprint(void); #if !NO_MALLINFO /* mallinfo() Returns (by copy) a struct containing various summary statistics: arena: current total non-mmapped bytes allocated from system ordblks: the number of free chunks smblks: always zero. hblks: current number of mmapped regions hblkhd: total bytes held in mmapped regions usmblks: the maximum total allocated space. This will be greater than current total if trimming has occurred. fsmblks: always zero uordblks: current total allocated space (normal or mmapped) fordblks: total free space keepcost: the maximum number of bytes that could ideally be released back to system via malloc_trim. ("ideally" means that it ignores page restrictions etc.) Because these fields are ints, but internal bookkeeping may be kept as longs, the reported values may wrap around zero and thus be inaccurate. */ struct mallinfo dlmallinfo(void); #endif /* NO_MALLINFO */ /* independent_calloc(size_t n_elements, size_t element_size, void* chunks[]); independent_calloc is similar to calloc, but instead of returning a single cleared space, it returns an array of pointers to n_elements independent elements that can hold contents of size elem_size, each of which starts out cleared, and can be independently freed, realloc'ed etc. The elements are guaranteed to be adjacently allocated (this is not guaranteed to occur with multiple callocs or mallocs), which may also improve cache locality in some applications. The "chunks" argument is optional (i.e., may be null, which is probably the most typical usage). If it is null, the returned array is itself dynamically allocated and should also be freed when it is no longer needed. Otherwise, the chunks array must be of at least n_elements in length. It is filled in with the pointers to the chunks. In either case, independent_calloc returns this pointer array, or null if the allocation failed. If n_elements is zero and "chunks" is null, it returns a chunk representing an array with zero elements (which should be freed if not wanted). Each element must be individually freed when it is no longer needed. If you'd like to instead be able to free all at once, you should instead use regular calloc and assign pointers into this space to represent elements. (In this case though, you cannot independently free elements.) independent_calloc simplifies and speeds up implementations of many kinds of pools. It may also be useful when constructing large data structures that initially have a fixed number of fixed-sized nodes, but the number is not known at compile time, and some of the nodes may later need to be freed. For example: struct Node { int item; struct Node* next; }; struct Node* build_list() { struct Node** pool; int n = read_number_of_nodes_needed(); if (n <= 0) return 0; pool = (struct Node**)(independent_calloc(n, sizeof(struct Node), 0); if (pool == 0) die(); // organize into a linked list... struct Node* first = pool[0]; for (i = 0; i < n-1; ++i) pool[i]->next = pool[i+1]; free(pool); // Can now free the array (or not, if it is needed later) return first; } */ void** dlindependent_calloc(size_t, size_t, void**); /* independent_comalloc(size_t n_elements, size_t sizes[], void* chunks[]); independent_comalloc allocates, all at once, a set of n_elements chunks with sizes indicated in the "sizes" array. It returns an array of pointers to these elements, each of which can be independently freed, realloc'ed etc. The elements are guaranteed to be adjacently allocated (this is not guaranteed to occur with multiple callocs or mallocs), which may also improve cache locality in some applications. The "chunks" argument is optional (i.e., may be null). If it is null the returned array is itself dynamically allocated and should also be freed when it is no longer needed. Otherwise, the chunks array must be of at least n_elements in length. It is filled in with the pointers to the chunks. In either case, independent_comalloc returns this pointer array, or null if the allocation failed. If n_elements is zero and chunks is null, it returns a chunk representing an array with zero elements (which should be freed if not wanted). Each element must be individually freed when it is no longer needed. If you'd like to instead be able to free all at once, you should instead use a single regular malloc, and assign pointers at particular offsets in the aggregate space. (In this case though, you cannot independently free elements.) independent_comallac differs from independent_calloc in that each element may have a different size, and also that it does not automatically clear elements. independent_comalloc can be used to speed up allocation in cases where several structs or objects must always be allocated at the same time. For example: struct Head { ... } struct Foot { ... } void send_message(char* msg) { int msglen = strlen(msg); size_t sizes[3] = { sizeof(struct Head), msglen, sizeof(struct Foot) }; void* chunks[3]; if (independent_comalloc(3, sizes, chunks) == 0) die(); struct Head* head = (struct Head*)(chunks[0]); char* body = (char*)(chunks[1]); struct Foot* foot = (struct Foot*)(chunks[2]); // ... } In general though, independent_comalloc is worth using only for larger values of n_elements. For small values, you probably won't detect enough difference from series of malloc calls to bother. Overuse of independent_comalloc can increase overall memory usage, since it cannot reuse existing noncontiguous small chunks that might be available for some of the elements. */ void** dlindependent_comalloc(size_t, size_t*, void**); /* pvalloc(size_t n); Equivalent to valloc(minimum-page-that-holds(n)), that is, round up n to nearest pagesize. */ void* dlpvalloc(size_t); /* malloc_trim(size_t pad); If possible, gives memory back to the system (via negative arguments to sbrk) if there is unused memory at the `high' end of the malloc pool or in unused MMAP segments. You can call this after freeing large blocks of memory to potentially reduce the system-level memory requirements of a program. However, it cannot guarantee to reduce memory. Under some allocation patterns, some large free blocks of memory will be locked between two used chunks, so they cannot be given back to the system. The `pad' argument to malloc_trim represents the amount of free trailing space to leave untrimmed. If this argument is zero, only the minimum amount of memory to maintain internal data structures will be left. Non-zero arguments can be supplied to maintain enough trailing space to service future expected allocations without having to re-obtain memory from the system. Malloc_trim returns 1 if it actually released any memory, else 0. */ int dlmalloc_trim(size_t); /* malloc_usable_size(void* p); Returns the number of bytes you can actually use in an allocated chunk, which may be more than you requested (although often not) due to alignment and minimum size constraints. You can use this many bytes without worrying about overwriting other allocated objects. This is not a particularly great programming practice. malloc_usable_size can be more useful in debugging and assertions, for example: p = malloc(n); assert(malloc_usable_size(p) >= 256); */ size_t dlmalloc_usable_size(void*); /* malloc_stats(); Prints on stderr the amount of space obtained from the system (both via sbrk and mmap), the maximum amount (which may be more than current if malloc_trim and/or munmap got called), and the current number of bytes allocated via malloc (or realloc, etc) but not yet freed. Note that this is the number of bytes allocated, not the number requested. It will be larger than the number requested because of alignment and bookkeeping overhead. Because it includes alignment wastage as being in use, this figure may be greater than zero even when no user-level chunks are allocated. The reported current and maximum system memory can be inaccurate if a program makes other calls to system memory allocation functions (normally sbrk) outside of malloc. malloc_stats prints only the most commonly interesting statistics. More information can be obtained by calling mallinfo. */ void dlmalloc_stats(void); #endif /* ONLY_MSPACES */ #if MSPACES /* mspace is an opaque type representing an independent region of space that supports mspace_malloc, etc. */ typedef void* mspace; /* create_mspace creates and returns a new independent space with the given initial capacity, or, if 0, the default granularity size. It returns null if there is no system memory available to create the space. If argument locked is non-zero, the space uses a separate lock to control access. The capacity of the space will grow dynamically as needed to service mspace_malloc requests. You can control the sizes of incremental increases of this space by compiling with a different DEFAULT_GRANULARITY or dynamically setting with mallopt(M_GRANULARITY, value). */ mspace create_mspace(size_t capacity, int locked); /* destroy_mspace destroys the given space, and attempts to return all of its memory back to the system, returning the total number of bytes freed. After destruction, the results of access to all memory used by the space become undefined. */ size_t destroy_mspace(mspace msp); /* create_mspace_with_base uses the memory supplied as the initial base of a new mspace. Part (less than 128*sizeof(size_t) bytes) of this space is used for bookkeeping, so the capacity must be at least this large. (Otherwise 0 is returned.) When this initial space is exhausted, additional memory will be obtained from the system. Destroying this space will deallocate all additionally allocated space (if possible) but not the initial base. */ mspace create_mspace_with_base(void* base, size_t capacity, int locked); /* mspace_malloc behaves as malloc, but operates within the given space. */ void* mspace_malloc(mspace msp, size_t bytes); /* mspace_free behaves as free, but operates within the given space. If compiled with FOOTERS==1, mspace_free is not actually needed. free may be called instead of mspace_free because freed chunks from any space are handled by their originating spaces. */ void mspace_free(mspace msp, void* mem); /* mspace_realloc behaves as realloc, but operates within the given space. If compiled with FOOTERS==1, mspace_realloc is not actually needed. realloc may be called instead of mspace_realloc because realloced chunks from any space are handled by their originating spaces. */ void* mspace_realloc(mspace msp, void* mem, size_t newsize); /* mspace_calloc behaves as calloc, but operates within the given space. */ void* mspace_calloc(mspace msp, size_t n_elements, size_t elem_size); /* mspace_memalign behaves as memalign, but operates within the given space. */ void* mspace_memalign(mspace msp, size_t alignment, size_t bytes); /* mspace_independent_calloc behaves as independent_calloc, but operates within the given space. */ void** mspace_independent_calloc(mspace msp, size_t n_elements, size_t elem_size, void* chunks[]); /* mspace_independent_comalloc behaves as independent_comalloc, but operates within the given space. */ void** mspace_independent_comalloc(mspace msp, size_t n_elements, size_t sizes[], void* chunks[]); /* mspace_footprint() returns the number of bytes obtained from the system for this space. */ size_t mspace_footprint(mspace msp); /* mspace_max_footprint() returns the peak number of bytes obtained from the system for this space. */ size_t mspace_max_footprint(mspace msp); #if !NO_MALLINFO /* mspace_mallinfo behaves as mallinfo, but reports properties of the given space. */ struct mallinfo mspace_mallinfo(mspace msp); #endif /* NO_MALLINFO */ /* mspace_malloc_stats behaves as malloc_stats, but reports properties of the given space. */ void mspace_malloc_stats(mspace msp); /* mspace_trim behaves as malloc_trim, but operates within the given space. */ int mspace_trim(mspace msp, size_t pad); /* An alias for mallopt. */ int mspace_mallopt(int, int); #endif /* MSPACES */ #ifdef __cplusplus }; /* end of extern "C" */ #endif /* __cplusplus */ /* ======================================================================== To make a fully customizable malloc.h header file, cut everything above this line, put into file malloc.h, edit to suit, and #include it on the next line, as well as in programs that use this malloc. ======================================================================== */ /* #include "malloc.h" */ /*------------------------------ internal #includes ---------------------- */ #ifdef _MSC_VER #pragma warning( disable : 4146 ) /* no "unsigned" warnings */ #endif /* _MSC_VER */ #include /* for printing in malloc_stats */ #ifndef LACKS_ERRNO_H #include /* for MALLOC_FAILURE_ACTION */ #endif /* LACKS_ERRNO_H */ #if FOOTERS #include /* for magic initialization */ #endif /* FOOTERS */ #ifndef LACKS_STDLIB_H #include /* for abort() */ #endif /* LACKS_STDLIB_H */ #ifdef DEBUG #if ABORT_ON_ASSERT_FAILURE #define assert(x) if(!(x)) ABORT #else /* ABORT_ON_ASSERT_FAILURE */ #include #endif /* ABORT_ON_ASSERT_FAILURE */ #else /* DEBUG */ #define assert(x) #endif /* DEBUG */ #ifndef LACKS_STRING_H #include /* for memset etc */ #endif /* LACKS_STRING_H */ #if USE_BUILTIN_FFS #ifndef LACKS_STRINGS_H #include /* for ffs */ #endif /* LACKS_STRINGS_H */ #endif /* USE_BUILTIN_FFS */ #if HAVE_MMAP #ifndef LACKS_SYS_MMAN_H #include /* for mmap */ #endif /* LACKS_SYS_MMAN_H */ #ifndef LACKS_FCNTL_H #include #endif /* LACKS_FCNTL_H */ #endif /* HAVE_MMAP */ #if HAVE_MORECORE #ifndef LACKS_UNISTD_H #include /* for sbrk */ #else /* LACKS_UNISTD_H */ #if !defined(__FreeBSD__) && !defined(__OpenBSD__) && !defined(__NetBSD__) extern void* sbrk(ptrdiff_t); #endif /* FreeBSD etc */ #endif /* LACKS_UNISTD_H */ #endif /* HAVE_MMAP */ #ifndef WIN32 #ifndef malloc_getpagesize # ifdef _SC_PAGESIZE /* some SVR4 systems omit an underscore */ # ifndef _SC_PAGE_SIZE # define _SC_PAGE_SIZE _SC_PAGESIZE # endif # endif # ifdef _SC_PAGE_SIZE # define malloc_getpagesize sysconf(_SC_PAGE_SIZE) # else # if defined(BSD) || defined(DGUX) || defined(HAVE_GETPAGESIZE) extern size_t getpagesize(); # define malloc_getpagesize getpagesize() # else # ifdef WIN32 /* use supplied emulation of getpagesize */ # define malloc_getpagesize getpagesize() # else # ifndef LACKS_SYS_PARAM_H # include # endif # ifdef EXEC_PAGESIZE # define malloc_getpagesize EXEC_PAGESIZE # else # ifdef NBPG # ifndef CLSIZE # define malloc_getpagesize NBPG # else # define malloc_getpagesize (NBPG * CLSIZE) # endif # else # ifdef NBPC # define malloc_getpagesize NBPC # else # ifdef PAGESIZE # define malloc_getpagesize PAGESIZE # else /* just guess */ # define malloc_getpagesize ((size_t)4096U) # endif # endif # endif # endif # endif # endif # endif #endif #endif /* ------------------- size_t and alignment properties -------------------- */ /* The byte and bit size of a size_t */ #define SIZE_T_SIZE (sizeof(size_t)) #define SIZE_T_BITSIZE (sizeof(size_t) << 3) /* Some constants coerced to size_t */ /* Annoying but necessary to avoid errors on some plaftorms */ #define SIZE_T_ZERO ((size_t)0) #define SIZE_T_ONE ((size_t)1) #define SIZE_T_TWO ((size_t)2) #define TWO_SIZE_T_SIZES (SIZE_T_SIZE<<1) #define FOUR_SIZE_T_SIZES (SIZE_T_SIZE<<2) #define SIX_SIZE_T_SIZES (FOUR_SIZE_T_SIZES+TWO_SIZE_T_SIZES) #define HALF_MAX_SIZE_T (MAX_SIZE_T / 2U) /* The bit mask value corresponding to MALLOC_ALIGNMENT */ #define CHUNK_ALIGN_MASK (MALLOC_ALIGNMENT - SIZE_T_ONE) /* True if address a has acceptable alignment */ #define is_aligned(A) (((size_t)((A)) & (CHUNK_ALIGN_MASK)) == 0) /* the number of bytes to offset an address to align it */ #define align_offset(A)\ ((((size_t)(A) & CHUNK_ALIGN_MASK) == 0)? 0 :\ ((MALLOC_ALIGNMENT - ((size_t)(A) & CHUNK_ALIGN_MASK)) & CHUNK_ALIGN_MASK)) /* -------------------------- MMAP preliminaries ------------------------- */ /* If HAVE_MORECORE or HAVE_MMAP are false, we just define calls and checks to fail so compiler optimizer can delete code rather than using so many "#if"s. */ /* MORECORE and MMAP must return MFAIL on failure */ #define MFAIL ((void*)(MAX_SIZE_T)) #define CMFAIL ((char*)(MFAIL)) /* defined for convenience */ #if !HAVE_MMAP #define IS_MMAPPED_BIT (SIZE_T_ZERO) #define USE_MMAP_BIT (SIZE_T_ZERO) #define CALL_MMAP(s) MFAIL #define CALL_MUNMAP(a, s) (-1) #define DIRECT_MMAP(s) MFAIL #else /* HAVE_MMAP */ #define IS_MMAPPED_BIT (SIZE_T_ONE) #define USE_MMAP_BIT (SIZE_T_ONE) #if !defined(WIN32) && !defined (__OS2__) #define CALL_MUNMAP(a, s) munmap((a), (s)) #define MMAP_PROT (PROT_READ|PROT_WRITE) #if !defined(MAP_ANONYMOUS) && defined(MAP_ANON) #define MAP_ANONYMOUS MAP_ANON #endif /* MAP_ANON */ #ifdef MAP_ANONYMOUS #define MMAP_FLAGS (MAP_PRIVATE|MAP_ANONYMOUS) #define CALL_MMAP(s) mmap(0, (s), MMAP_PROT, MMAP_FLAGS, -1, 0) #else /* MAP_ANONYMOUS */ /* Nearly all versions of mmap support MAP_ANONYMOUS, so the following is unlikely to be needed, but is supplied just in case. */ #define MMAP_FLAGS (MAP_PRIVATE) static int dev_zero_fd = -1; /* Cached file descriptor for /dev/zero. */ #define CALL_MMAP(s) ((dev_zero_fd < 0) ? \ (dev_zero_fd = open("/dev/zero", O_RDWR), \ mmap(0, (s), MMAP_PROT, MMAP_FLAGS, dev_zero_fd, 0)) : \ mmap(0, (s), MMAP_PROT, MMAP_FLAGS, dev_zero_fd, 0)) #endif /* MAP_ANONYMOUS */ #define DIRECT_MMAP(s) CALL_MMAP(s) #elif defined(__OS2__) /* OS/2 MMAP via DosAllocMem */ static void* os2mmap(size_t size) { void* ptr; if (DosAllocMem(&ptr, size, OBJ_ANY|PAG_COMMIT|PAG_READ|PAG_WRITE) && DosAllocMem(&ptr, size, PAG_COMMIT|PAG_READ|PAG_WRITE)) return MFAIL; return ptr; } #define os2direct_mmap(n) os2mmap(n) /* This function supports releasing coalesed segments */ static int os2munmap(void* ptr, size_t size) { while (size) { ULONG ulSize = size; ULONG ulFlags = 0; if (DosQueryMem(ptr, &ulSize, &ulFlags) != 0) return -1; if ((ulFlags & PAG_BASE) == 0 ||(ulFlags & PAG_COMMIT) == 0 || ulSize > size) return -1; if (DosFreeMem(ptr) != 0) return -1; ptr = ( void * ) ( ( char * ) ptr + ulSize ); size -= ulSize; } return 0; } #define CALL_MMAP(s) os2mmap(s) #define CALL_MUNMAP(a, s) os2munmap((a), (s)) #define DIRECT_MMAP(s) os2direct_mmap(s) #else /* WIN32 */ /* Win32 MMAP via VirtualAlloc */ static void* win32mmap(size_t size) { void* ptr = VirtualAlloc(0, size, MEM_RESERVE|MEM_COMMIT, PAGE_EXECUTE_READWRITE); return (ptr != 0)? ptr: MFAIL; } /* For direct MMAP, use MEM_TOP_DOWN to minimize interference */ static void* win32direct_mmap(size_t size) { void* ptr = VirtualAlloc(0, size, MEM_RESERVE|MEM_COMMIT|MEM_TOP_DOWN, PAGE_EXECUTE_READWRITE); return (ptr != 0)? ptr: MFAIL; } /* This function supports releasing coalesed segments */ static int win32munmap(void* ptr, size_t size) { MEMORY_BASIC_INFORMATION minfo; char* cptr = ptr; while (size) { if (VirtualQuery(cptr, &minfo, sizeof(minfo)) == 0) return -1; if (minfo.BaseAddress != cptr || minfo.AllocationBase != cptr || minfo.State != MEM_COMMIT || minfo.RegionSize > size) return -1; if (VirtualFree(cptr, 0, MEM_RELEASE) == 0) return -1; cptr += minfo.RegionSize; size -= minfo.RegionSize; } return 0; } #define CALL_MMAP(s) win32mmap(s) #define CALL_MUNMAP(a, s) win32munmap((a), (s)) #define DIRECT_MMAP(s) win32direct_mmap(s) #endif /* WIN32 */ #endif /* HAVE_MMAP */ #if HAVE_MMAP && HAVE_MREMAP #define CALL_MREMAP(addr, osz, nsz, mv) mremap((addr), (osz), (nsz), (mv)) #else /* HAVE_MMAP && HAVE_MREMAP */ #define CALL_MREMAP(addr, osz, nsz, mv) MFAIL #endif /* HAVE_MMAP && HAVE_MREMAP */ #if HAVE_MORECORE #define CALL_MORECORE(S) MORECORE(S) #else /* HAVE_MORECORE */ #define CALL_MORECORE(S) MFAIL #endif /* HAVE_MORECORE */ /* mstate bit set if continguous morecore disabled or failed */ #define USE_NONCONTIGUOUS_BIT (4U) /* segment bit set in create_mspace_with_base */ #define EXTERN_BIT (8U) /* --------------------------- Lock preliminaries ------------------------ */ #if USE_LOCKS /* When locks are defined, there are up to two global locks: * If HAVE_MORECORE, morecore_mutex protects sequences of calls to MORECORE. In many cases sys_alloc requires two calls, that should not be interleaved with calls by other threads. This does not protect against direct calls to MORECORE by other threads not using this lock, so there is still code to cope the best we can on interference. * magic_init_mutex ensures that mparams.magic and other unique mparams values are initialized only once. */ #if !defined(WIN32) && !defined(__OS2__) /* By default use posix locks */ #include #define MLOCK_T pthread_mutex_t #define INITIAL_LOCK(l) pthread_mutex_init(l, NULL) #define ACQUIRE_LOCK(l) pthread_mutex_lock(l) #define RELEASE_LOCK(l) pthread_mutex_unlock(l) #if HAVE_MORECORE static MLOCK_T morecore_mutex = PTHREAD_MUTEX_INITIALIZER; #endif /* HAVE_MORECORE */ static MLOCK_T magic_init_mutex = PTHREAD_MUTEX_INITIALIZER; #elif defined(__OS2__) #define MLOCK_T HMTX #define INITIAL_LOCK(l) DosCreateMutexSem(0, l, 0, FALSE) #define ACQUIRE_LOCK(l) DosRequestMutexSem(*l, SEM_INDEFINITE_WAIT) #define RELEASE_LOCK(l) DosReleaseMutexSem(*l) #if HAVE_MORECORE static MLOCK_T morecore_mutex; #endif /* HAVE_MORECORE */ static MLOCK_T magic_init_mutex; #else /* WIN32 */ /* Because lock-protected regions have bounded times, and there are no recursive lock calls, we can use simple spinlocks. */ #define MLOCK_T long static int win32_acquire_lock (MLOCK_T *sl) { for (;;) { #ifdef InterlockedCompareExchangePointer if (!InterlockedCompareExchange(sl, 1, 0)) return 0; #else /* Use older void* version */ if (!InterlockedCompareExchange((void**)sl, (void*)1, (void*)0)) return 0; #endif /* InterlockedCompareExchangePointer */ Sleep (0); } } static void win32_release_lock (MLOCK_T *sl) { InterlockedExchange (sl, 0); } #define INITIAL_LOCK(l) *(l)=0 #define ACQUIRE_LOCK(l) win32_acquire_lock(l) #define RELEASE_LOCK(l) win32_release_lock(l) #if HAVE_MORECORE static MLOCK_T morecore_mutex; #endif /* HAVE_MORECORE */ static MLOCK_T magic_init_mutex; #endif /* WIN32 */ #define USE_LOCK_BIT (2U) #else /* USE_LOCKS */ #define USE_LOCK_BIT (0U) #define INITIAL_LOCK(l) #endif /* USE_LOCKS */ #if USE_LOCKS && HAVE_MORECORE #define ACQUIRE_MORECORE_LOCK() ACQUIRE_LOCK(&morecore_mutex); #define RELEASE_MORECORE_LOCK() RELEASE_LOCK(&morecore_mutex); #else /* USE_LOCKS && HAVE_MORECORE */ #define ACQUIRE_MORECORE_LOCK() #define RELEASE_MORECORE_LOCK() #endif /* USE_LOCKS && HAVE_MORECORE */ #if USE_LOCKS #define ACQUIRE_MAGIC_INIT_LOCK() ACQUIRE_LOCK(&magic_init_mutex); #define RELEASE_MAGIC_INIT_LOCK() RELEASE_LOCK(&magic_init_mutex); #else /* USE_LOCKS */ #define ACQUIRE_MAGIC_INIT_LOCK() #define RELEASE_MAGIC_INIT_LOCK() #endif /* USE_LOCKS */ /* ----------------------- Chunk representations ------------------------ */ /* (The following includes lightly edited explanations by Colin Plumb.) The malloc_chunk declaration below is misleading (but accurate and necessary). It declares a "view" into memory allowing access to necessary fields at known offsets from a given base. Chunks of memory are maintained using a `boundary tag' method as originally described by Knuth. (See the paper by Paul Wilson ftp://ftp.cs.utexas.edu/pub/garbage/allocsrv.ps for a survey of such techniques.) Sizes of free chunks are stored both in the front of each chunk and at the end. This makes consolidating fragmented chunks into bigger chunks fast. The head fields also hold bits representing whether chunks are free or in use. Here are some pictures to make it clearer. They are "exploded" to show that the state of a chunk can be thought of as extending from the high 31 bits of the head field of its header through the prev_foot and PINUSE_BIT bit of the following chunk header. A chunk that's in use looks like: chunk-> +-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+ | Size of previous chunk (if P = 1) | +-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+ +-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+ |P| | Size of this chunk 1| +-+ mem-> +-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+ | | +- -+ | | +- -+ | : +- size - sizeof(size_t) available payload bytes -+ : | chunk-> +- -+ | | +-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+ +-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+ |1| | Size of next chunk (may or may not be in use) | +-+ mem-> +-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+ And if it's free, it looks like this: chunk-> +- -+ | User payload (must be in use, or we would have merged!) | +-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+ +-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+ |P| | Size of this chunk 0| +-+ mem-> +-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+ | Next pointer | +-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+ | Prev pointer | +-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+ | : +- size - sizeof(struct chunk) unused bytes -+ : | chunk-> +-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+ | Size of this chunk | +-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+ +-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+ |0| | Size of next chunk (must be in use, or we would have merged)| +-+ mem-> +-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+ | : +- User payload -+ : | +-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+ |0| +-+ Note that since we always merge adjacent free chunks, the chunks adjacent to a free chunk must be in use. Given a pointer to a chunk (which can be derived trivially from the payload pointer) we can, in O(1) time, find out whether the adjacent chunks are free, and if so, unlink them from the lists that they are on and merge them with the current chunk. Chunks always begin on even word boundaries, so the mem portion (which is returned to the user) is also on an even word boundary, and thus at least double-word aligned. The P (PINUSE_BIT) bit, stored in the unused low-order bit of the chunk size (which is always a multiple of two words), is an in-use bit for the *previous* chunk. If that bit is *clear*, then the word before the current chunk size contains the previous chunk size, and can be used to find the front of the previous chunk. The very first chunk allocated always has this bit set, preventing access to non-existent (or non-owned) memory. If pinuse is set for any given chunk, then you CANNOT determine the size of the previous chunk, and might even get a memory addressing fault when trying to do so. The C (CINUSE_BIT) bit, stored in the unused second-lowest bit of the chunk size redundantly records whether the current chunk is inuse. This redundancy enables usage checks within free and realloc, and reduces indirection when freeing and consolidating chunks. Each freshly allocated chunk must have both cinuse and pinuse set. That is, each allocated chunk borders either a previously allocated and still in-use chunk, or the base of its memory arena. This is ensured by making all allocations from the the `lowest' part of any found chunk. Further, no free chunk physically borders another one, so each free chunk is known to be preceded and followed by either inuse chunks or the ends of memory. Note that the `foot' of the current chunk is actually represented as the prev_foot of the NEXT chunk. This makes it easier to deal with alignments etc but can be very confusing when trying to extend or adapt this code. The exceptions to all this are 1. The special chunk `top' is the top-most available chunk (i.e., the one bordering the end of available memory). It is treated specially. Top is never included in any bin, is used only if no other chunk is available, and is released back to the system if it is very large (see M_TRIM_THRESHOLD). In effect, the top chunk is treated as larger (and thus less well fitting) than any other available chunk. The top chunk doesn't update its trailing size field since there is no next contiguous chunk that would have to index off it. However, space is still allocated for it (TOP_FOOT_SIZE) to enable separation or merging when space is extended. 3. Chunks allocated via mmap, which have the lowest-order bit (IS_MMAPPED_BIT) set in their prev_foot fields, and do not set PINUSE_BIT in their head fields. Because they are allocated one-by-one, each must carry its own prev_foot field, which is also used to hold the offset this chunk has within its mmapped region, which is needed to preserve alignment. Each mmapped chunk is trailed by the first two fields of a fake next-chunk for sake of usage checks. */ struct malloc_chunk { size_t prev_foot; /* Size of previous chunk (if free). */ size_t head; /* Size and inuse bits. */ struct malloc_chunk* fd; /* double links -- used only if free. */ struct malloc_chunk* bk; }; typedef struct malloc_chunk mchunk; typedef struct malloc_chunk* mchunkptr; typedef struct malloc_chunk* sbinptr; /* The type of bins of chunks */ typedef unsigned int bindex_t; /* Described below */ typedef unsigned int binmap_t; /* Described below */ typedef unsigned int flag_t; /* The type of various bit flag sets */ /* ------------------- Chunks sizes and alignments ----------------------- */ #define MCHUNK_SIZE (sizeof(mchunk)) #if FOOTERS #define CHUNK_OVERHEAD (TWO_SIZE_T_SIZES) #else /* FOOTERS */ #define CHUNK_OVERHEAD (SIZE_T_SIZE) #endif /* FOOTERS */ /* MMapped chunks need a second word of overhead ... */ #define MMAP_CHUNK_OVERHEAD (TWO_SIZE_T_SIZES) /* ... and additional padding for fake next-chunk at foot */ #define MMAP_FOOT_PAD (FOUR_SIZE_T_SIZES) /* The smallest size we can malloc is an aligned minimal chunk */ #define MIN_CHUNK_SIZE\ ((MCHUNK_SIZE + CHUNK_ALIGN_MASK) & ~CHUNK_ALIGN_MASK) /* conversion from malloc headers to user pointers, and back */ #define chunk2mem(p) ((void*)((char*)(p) + TWO_SIZE_T_SIZES)) #define mem2chunk(mem) ((mchunkptr)((char*)(mem) - TWO_SIZE_T_SIZES)) /* chunk associated with aligned address A */ #define align_as_chunk(A) (mchunkptr)((A) + align_offset(chunk2mem(A))) /* Bounds on request (not chunk) sizes. */ #define MAX_REQUEST ((-MIN_CHUNK_SIZE) << 2) #define MIN_REQUEST (MIN_CHUNK_SIZE - CHUNK_OVERHEAD - SIZE_T_ONE) /* pad request bytes into a usable size */ #define pad_request(req) \ (((req) + CHUNK_OVERHEAD + CHUNK_ALIGN_MASK) & ~CHUNK_ALIGN_MASK) /* pad request, checking for minimum (but not maximum) */ #define request2size(req) \ (((req) < MIN_REQUEST)? MIN_CHUNK_SIZE : pad_request(req)) /* ------------------ Operations on head and foot fields ----------------- */ /* The head field of a chunk is or'ed with PINUSE_BIT when previous adjacent chunk in use, and or'ed with CINUSE_BIT if this chunk is in use. If the chunk was obtained with mmap, the prev_foot field has IS_MMAPPED_BIT set, otherwise holding the offset of the base of the mmapped region to the base of the chunk. */ #define PINUSE_BIT (SIZE_T_ONE) #define CINUSE_BIT (SIZE_T_TWO) #define INUSE_BITS (PINUSE_BIT|CINUSE_BIT) /* Head value for fenceposts */ #define FENCEPOST_HEAD (INUSE_BITS|SIZE_T_SIZE) /* extraction of fields from head words */ #define cinuse(p) ((p)->head & CINUSE_BIT) #define pinuse(p) ((p)->head & PINUSE_BIT) #define chunksize(p) ((p)->head & ~(INUSE_BITS)) #define clear_pinuse(p) ((p)->head &= ~PINUSE_BIT) #define clear_cinuse(p) ((p)->head &= ~CINUSE_BIT) /* Treat space at ptr +/- offset as a chunk */ #define chunk_plus_offset(p, s) ((mchunkptr)(((char*)(p)) + (s))) #define chunk_minus_offset(p, s) ((mchunkptr)(((char*)(p)) - (s))) /* Ptr to next or previous physical malloc_chunk. */ #define next_chunk(p) ((mchunkptr)( ((char*)(p)) + ((p)->head & ~INUSE_BITS))) #define prev_chunk(p) ((mchunkptr)( ((char*)(p)) - ((p)->prev_foot) )) /* extract next chunk's pinuse bit */ #define next_pinuse(p) ((next_chunk(p)->head) & PINUSE_BIT) /* Get/set size at footer */ #define get_foot(p, s) (((mchunkptr)((char*)(p) + (s)))->prev_foot) #define set_foot(p, s) (((mchunkptr)((char*)(p) + (s)))->prev_foot = (s)) /* Set size, pinuse bit, and foot */ #define set_size_and_pinuse_of_free_chunk(p, s)\ ((p)->head = (s|PINUSE_BIT), set_foot(p, s)) /* Set size, pinuse bit, foot, and clear next pinuse */ #define set_free_with_pinuse(p, s, n)\ (clear_pinuse(n), set_size_and_pinuse_of_free_chunk(p, s)) #define is_mmapped(p)\ (!((p)->head & PINUSE_BIT) && ((p)->prev_foot & IS_MMAPPED_BIT)) /* Get the internal overhead associated with chunk p */ #define overhead_for(p)\ (is_mmapped(p)? MMAP_CHUNK_OVERHEAD : CHUNK_OVERHEAD) /* Return true if malloced space is not necessarily cleared */ #if MMAP_CLEARS #define calloc_must_clear(p) (!is_mmapped(p)) #else /* MMAP_CLEARS */ #define calloc_must_clear(p) (1) #endif /* MMAP_CLEARS */ /* ---------------------- Overlaid data structures ----------------------- */ /* When chunks are not in use, they are treated as nodes of either lists or trees. "Small" chunks are stored in circular doubly-linked lists, and look like this: chunk-> +-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+ | Size of previous chunk | +-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+ `head:' | Size of chunk, in bytes |P| mem-> +-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+ | Forward pointer to next chunk in list | +-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+ | Back pointer to previous chunk in list | +-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+ | Unused space (may be 0 bytes long) . . . . | nextchunk-> +-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+ `foot:' | Size of chunk, in bytes | +-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+ Larger chunks are kept in a form of bitwise digital trees (aka tries) keyed on chunksizes. Because malloc_tree_chunks are only for free chunks greater than 256 bytes, their size doesn't impose any constraints on user chunk sizes. Each node looks like: chunk-> +-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+ | Size of previous chunk | +-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+ `head:' | Size of chunk, in bytes |P| mem-> +-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+ | Forward pointer to next chunk of same size | +-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+ | Back pointer to previous chunk of same size | +-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+ | Pointer to left child (child[0]) | +-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+ | Pointer to right child (child[1]) | +-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+ | Pointer to parent | +-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+ | bin index of this chunk | +-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+ | Unused space . . | nextchunk-> +-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+ `foot:' | Size of chunk, in bytes | +-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+-+ Each tree holding treenodes is a tree of unique chunk sizes. Chunks of the same size are arranged in a circularly-linked list, with only the oldest chunk (the next to be used, in our FIFO ordering) actually in the tree. (Tree members are distinguished by a non-null parent pointer.) If a chunk with the same size an an existing node is inserted, it is linked off the existing node using pointers that work in the same way as fd/bk pointers of small chunks. Each tree contains a power of 2 sized range of chunk sizes (the smallest is 0x100 <= x < 0x180), which is is divided in half at each tree level, with the chunks in the smaller half of the range (0x100 <= x < 0x140 for the top nose) in the left subtree and the larger half (0x140 <= x < 0x180) in the right subtree. This is, of course, done by inspecting individual bits. Using these rules, each node's left subtree contains all smaller sizes than its right subtree. However, the node at the root of each subtree has no particular ordering relationship to either. (The dividing line between the subtree sizes is based on trie relation.) If we remove the last chunk of a given size from the interior of the tree, we need to replace it with a leaf node. The tree ordering rules permit a node to be replaced by any leaf below it. The smallest chunk in a tree (a common operation in a best-fit allocator) can be found by walking a path to the leftmost leaf in the tree. Unlike a usual binary tree, where we follow left child pointers until we reach a null, here we follow the right child pointer any time the left one is null, until we reach a leaf with both child pointers null. The smallest chunk in the tree will be somewhere along that path. The worst case number of steps to add, find, or remove a node is bounded by the number of bits differentiating chunks within bins. Under current bin calculations, this ranges from 6 up to 21 (for 32 bit sizes) or up to 53 (for 64 bit sizes). The typical case is of course much better. */ struct malloc_tree_chunk { /* The first four fields must be compatible with malloc_chunk */ size_t prev_foot; size_t head; struct malloc_tree_chunk* fd; struct malloc_tree_chunk* bk; struct malloc_tree_chunk* child[2]; struct malloc_tree_chunk* parent; bindex_t index; }; typedef struct malloc_tree_chunk tchunk; typedef struct malloc_tree_chunk* tchunkptr; typedef struct malloc_tree_chunk* tbinptr; /* The type of bins of trees */ /* A little helper macro for trees */ #define leftmost_child(t) ((t)->child[0] != 0? (t)->child[0] : (t)->child[1]) /* ----------------------------- Segments -------------------------------- */ /* Each malloc space may include non-contiguous segments, held in a list headed by an embedded malloc_segment record representing the top-most space. Segments also include flags holding properties of the space. Large chunks that are directly allocated by mmap are not included in this list. They are instead independently created and destroyed without otherwise keeping track of them. Segment management mainly comes into play for spaces allocated by MMAP. Any call to MMAP might or might not return memory that is adjacent to an existing segment. MORECORE normally contiguously extends the current space, so this space is almost always adjacent, which is simpler and faster to deal with. (This is why MORECORE is used preferentially to MMAP when both are available -- see sys_alloc.) When allocating using MMAP, we don't use any of the hinting mechanisms (inconsistently) supported in various implementations of unix mmap, or distinguish reserving from committing memory. Instead, we just ask for space, and exploit contiguity when we get it. It is probably possible to do better than this on some systems, but no general scheme seems to be significantly better. Management entails a simpler variant of the consolidation scheme used for chunks to reduce fragmentation -- new adjacent memory is normally prepended or appended to an existing segment. However, there are limitations compared to chunk consolidation that mostly reflect the fact that segment processing is relatively infrequent (occurring only when getting memory from system) and that we don't expect to have huge numbers of segments: * Segments are not indexed, so traversal requires linear scans. (It would be possible to index these, but is not worth the extra overhead and complexity for most programs on most platforms.) * New segments are only appended to old ones when holding top-most memory; if they cannot be prepended to others, they are held in different segments. Except for the top-most segment of an mstate, each segment record is kept at the tail of its segment. Segments are added by pushing segment records onto the list headed by &mstate.seg for the containing mstate. Segment flags control allocation/merge/deallocation policies: * If EXTERN_BIT set, then we did not allocate this segment, and so should not try to deallocate or merge with others. (This currently holds only for the initial segment passed into create_mspace_with_base.) * If IS_MMAPPED_BIT set, the segment may be merged with other surrounding mmapped segments and trimmed/de-allocated using munmap. * If neither bit is set, then the segment was obtained using MORECORE so can be merged with surrounding MORECORE'd segments and deallocated/trimmed using MORECORE with negative arguments. */ struct malloc_segment { char* base; /* base address */ size_t size; /* allocated size */ struct malloc_segment* next; /* ptr to next segment */ #if FFI_MMAP_EXEC_WRIT /* The mmap magic is supposed to store the address of the executable segment at the very end of the requested block. */ # define mmap_exec_offset(b,s) (*(ptrdiff_t*)((b)+(s)-sizeof(ptrdiff_t))) /* We can only merge segments if their corresponding executable segments are at identical offsets. */ # define check_segment_merge(S,b,s) \ (mmap_exec_offset((b),(s)) == (S)->exec_offset) # define add_segment_exec_offset(p,S) ((char*)(p) + (S)->exec_offset) # define sub_segment_exec_offset(p,S) ((char*)(p) - (S)->exec_offset) /* The removal of sflags only works with HAVE_MORECORE == 0. */ # define get_segment_flags(S) (IS_MMAPPED_BIT) # define set_segment_flags(S,v) \ (((v) != IS_MMAPPED_BIT) ? (ABORT, (v)) : \ (((S)->exec_offset = \ mmap_exec_offset((S)->base, (S)->size)), \ (mmap_exec_offset((S)->base + (S)->exec_offset, (S)->size) != \ (S)->exec_offset) ? (ABORT, (v)) : \ (mmap_exec_offset((S)->base, (S)->size) = 0), (v))) /* We use an offset here, instead of a pointer, because then, when base changes, we don't have to modify this. On architectures with segmented addresses, this might not work. */ ptrdiff_t exec_offset; #else # define get_segment_flags(S) ((S)->sflags) # define set_segment_flags(S,v) ((S)->sflags = (v)) # define check_segment_merge(S,b,s) (1) flag_t sflags; /* mmap and extern flag */ #endif }; #define is_mmapped_segment(S) (get_segment_flags(S) & IS_MMAPPED_BIT) #define is_extern_segment(S) (get_segment_flags(S) & EXTERN_BIT) typedef struct malloc_segment msegment; typedef struct malloc_segment* msegmentptr; /* ---------------------------- malloc_state ----------------------------- */ /* A malloc_state holds all of the bookkeeping for a space. The main fields are: Top The topmost chunk of the currently active segment. Its size is cached in topsize. The actual size of topmost space is topsize+TOP_FOOT_SIZE, which includes space reserved for adding fenceposts and segment records if necessary when getting more space from the system. The size at which to autotrim top is cached from mparams in trim_check, except that it is disabled if an autotrim fails. Designated victim (dv) This is the preferred chunk for servicing small requests that don't have exact fits. It is normally the chunk split off most recently to service another small request. Its size is cached in dvsize. The link fields of this chunk are not maintained since it is not kept in a bin. SmallBins An array of bin headers for free chunks. These bins hold chunks with sizes less than MIN_LARGE_SIZE bytes. Each bin contains chunks of all the same size, spaced 8 bytes apart. To simplify use in double-linked lists, each bin header acts as a malloc_chunk pointing to the real first node, if it exists (else pointing to itself). This avoids special-casing for headers. But to avoid waste, we allocate only the fd/bk pointers of bins, and then use repositioning tricks to treat these as the fields of a chunk. TreeBins Treebins are pointers to the roots of trees holding a range of sizes. There are 2 equally spaced treebins for each power of two from TREE_SHIFT to TREE_SHIFT+16. The last bin holds anything larger. Bin maps There is one bit map for small bins ("smallmap") and one for treebins ("treemap). Each bin sets its bit when non-empty, and clears the bit when empty. Bit operations are then used to avoid bin-by-bin searching -- nearly all "search" is done without ever looking at bins that won't be selected. The bit maps conservatively use 32 bits per map word, even if on 64bit system. For a good description of some of the bit-based techniques used here, see Henry S. Warren Jr's book "Hacker's Delight" (and supplement at http://hackersdelight.org/). Many of these are intended to reduce the branchiness of paths through malloc etc, as well as to reduce the number of memory locations read or written. Segments A list of segments headed by an embedded malloc_segment record representing the initial space. Address check support The least_addr field is the least address ever obtained from MORECORE or MMAP. Attempted frees and reallocs of any address less than this are trapped (unless INSECURE is defined). Magic tag A cross-check field that should always hold same value as mparams.magic. Flags Bits recording whether to use MMAP, locks, or contiguous MORECORE Statistics Each space keeps track of current and maximum system memory obtained via MORECORE or MMAP. Locking If USE_LOCKS is defined, the "mutex" lock is acquired and released around every public call using this mspace. */ /* Bin types, widths and sizes */ #define NSMALLBINS (32U) #define NTREEBINS (32U) #define SMALLBIN_SHIFT (3U) #define SMALLBIN_WIDTH (SIZE_T_ONE << SMALLBIN_SHIFT) #define TREEBIN_SHIFT (8U) #define MIN_LARGE_SIZE (SIZE_T_ONE << TREEBIN_SHIFT) #define MAX_SMALL_SIZE (MIN_LARGE_SIZE - SIZE_T_ONE) #define MAX_SMALL_REQUEST (MAX_SMALL_SIZE - CHUNK_ALIGN_MASK - CHUNK_OVERHEAD) struct malloc_state { binmap_t smallmap; binmap_t treemap; size_t dvsize; size_t topsize; char* least_addr; mchunkptr dv; mchunkptr top; size_t trim_check; size_t magic; mchunkptr smallbins[(NSMALLBINS+1)*2]; tbinptr treebins[NTREEBINS]; size_t footprint; size_t max_footprint; flag_t mflags; #if USE_LOCKS MLOCK_T mutex; /* locate lock among fields that rarely change */ #endif /* USE_LOCKS */ msegment seg; }; typedef struct malloc_state* mstate; /* ------------- Global malloc_state and malloc_params ------------------- */ /* malloc_params holds global properties, including those that can be dynamically set using mallopt. There is a single instance, mparams, initialized in init_mparams. */ struct malloc_params { size_t magic; size_t page_size; size_t granularity; size_t mmap_threshold; size_t trim_threshold; flag_t default_mflags; }; static struct malloc_params mparams; /* The global malloc_state used for all non-"mspace" calls */ static struct malloc_state _gm_; #define gm (&_gm_) #define is_global(M) ((M) == &_gm_) #define is_initialized(M) ((M)->top != 0) /* -------------------------- system alloc setup ------------------------- */ /* Operations on mflags */ #define use_lock(M) ((M)->mflags & USE_LOCK_BIT) #define enable_lock(M) ((M)->mflags |= USE_LOCK_BIT) #define disable_lock(M) ((M)->mflags &= ~USE_LOCK_BIT) #define use_mmap(M) ((M)->mflags & USE_MMAP_BIT) #define enable_mmap(M) ((M)->mflags |= USE_MMAP_BIT) #define disable_mmap(M) ((M)->mflags &= ~USE_MMAP_BIT) #define use_noncontiguous(M) ((M)->mflags & USE_NONCONTIGUOUS_BIT) #define disable_contiguous(M) ((M)->mflags |= USE_NONCONTIGUOUS_BIT) #define set_lock(M,L)\ ((M)->mflags = (L)?\ ((M)->mflags | USE_LOCK_BIT) :\ ((M)->mflags & ~USE_LOCK_BIT)) /* page-align a size */ #define page_align(S)\ (((S) + (mparams.page_size)) & ~(mparams.page_size - SIZE_T_ONE)) /* granularity-align a size */ #define granularity_align(S)\ (((S) + (mparams.granularity)) & ~(mparams.granularity - SIZE_T_ONE)) #define is_page_aligned(S)\ (((size_t)(S) & (mparams.page_size - SIZE_T_ONE)) == 0) #define is_granularity_aligned(S)\ (((size_t)(S) & (mparams.granularity - SIZE_T_ONE)) == 0) /* True if segment S holds address A */ #define segment_holds(S, A)\ ((char*)(A) >= S->base && (char*)(A) < S->base + S->size) /* Return segment holding given address */ static msegmentptr segment_holding(mstate m, char* addr) { msegmentptr sp = &m->seg; for (;;) { if (addr >= sp->base && addr < sp->base + sp->size) return sp; if ((sp = sp->next) == 0) return 0; } } /* Return true if segment contains a segment link */ static int has_segment_link(mstate m, msegmentptr ss) { msegmentptr sp = &m->seg; for (;;) { if ((char*)sp >= ss->base && (char*)sp < ss->base + ss->size) return 1; if ((sp = sp->next) == 0) return 0; } } #ifndef MORECORE_CANNOT_TRIM #define should_trim(M,s) ((s) > (M)->trim_check) #else /* MORECORE_CANNOT_TRIM */ #define should_trim(M,s) (0) #endif /* MORECORE_CANNOT_TRIM */ /* TOP_FOOT_SIZE is padding at the end of a segment, including space that may be needed to place segment records and fenceposts when new noncontiguous segments are added. */ #define TOP_FOOT_SIZE\ (align_offset(chunk2mem(0))+pad_request(sizeof(struct malloc_segment))+MIN_CHUNK_SIZE) /* ------------------------------- Hooks -------------------------------- */ /* PREACTION should be defined to return 0 on success, and nonzero on failure. If you are not using locking, you can redefine these to do anything you like. */ #if USE_LOCKS /* Ensure locks are initialized */ #define GLOBALLY_INITIALIZE() (mparams.page_size == 0 && init_mparams()) #define PREACTION(M) ((GLOBALLY_INITIALIZE() || use_lock(M))? ACQUIRE_LOCK(&(M)->mutex) : 0) #define POSTACTION(M) { if (use_lock(M)) RELEASE_LOCK(&(M)->mutex); } #else /* USE_LOCKS */ #ifndef PREACTION #define PREACTION(M) (0) #endif /* PREACTION */ #ifndef POSTACTION #define POSTACTION(M) #endif /* POSTACTION */ #endif /* USE_LOCKS */ /* CORRUPTION_ERROR_ACTION is triggered upon detected bad addresses. USAGE_ERROR_ACTION is triggered on detected bad frees and reallocs. The argument p is an address that might have triggered the fault. It is ignored by the two predefined actions, but might be useful in custom actions that try to help diagnose errors. */ #if PROCEED_ON_ERROR /* A count of the number of corruption errors causing resets */ int malloc_corruption_error_count; /* default corruption action */ static void reset_on_error(mstate m); #define CORRUPTION_ERROR_ACTION(m) reset_on_error(m) #define USAGE_ERROR_ACTION(m, p) #else /* PROCEED_ON_ERROR */ #ifndef CORRUPTION_ERROR_ACTION #define CORRUPTION_ERROR_ACTION(m) ABORT #endif /* CORRUPTION_ERROR_ACTION */ #ifndef USAGE_ERROR_ACTION #define USAGE_ERROR_ACTION(m,p) ABORT #endif /* USAGE_ERROR_ACTION */ #endif /* PROCEED_ON_ERROR */ /* -------------------------- Debugging setup ---------------------------- */ #if ! DEBUG #define check_free_chunk(M,P) #define check_inuse_chunk(M,P) #define check_malloced_chunk(M,P,N) #define check_mmapped_chunk(M,P) #define check_malloc_state(M) #define check_top_chunk(M,P) #else /* DEBUG */ #define check_free_chunk(M,P) do_check_free_chunk(M,P) #define check_inuse_chunk(M,P) do_check_inuse_chunk(M,P) #define check_top_chunk(M,P) do_check_top_chunk(M,P) #define check_malloced_chunk(M,P,N) do_check_malloced_chunk(M,P,N) #define check_mmapped_chunk(M,P) do_check_mmapped_chunk(M,P) #define check_malloc_state(M) do_check_malloc_state(M) static void do_check_any_chunk(mstate m, mchunkptr p); static void do_check_top_chunk(mstate m, mchunkptr p); static void do_check_mmapped_chunk(mstate m, mchunkptr p); static void do_check_inuse_chunk(mstate m, mchunkptr p); static void do_check_free_chunk(mstate m, mchunkptr p); static void do_check_malloced_chunk(mstate m, void* mem, size_t s); static void do_check_tree(mstate m, tchunkptr t); static void do_check_treebin(mstate m, bindex_t i); static void do_check_smallbin(mstate m, bindex_t i); static void do_check_malloc_state(mstate m); static int bin_find(mstate m, mchunkptr x); static size_t traverse_and_check(mstate m); #endif /* DEBUG */ /* ---------------------------- Indexing Bins ---------------------------- */ #define is_small(s) (((s) >> SMALLBIN_SHIFT) < NSMALLBINS) #define small_index(s) ((s) >> SMALLBIN_SHIFT) #define small_index2size(i) ((i) << SMALLBIN_SHIFT) #define MIN_SMALL_INDEX (small_index(MIN_CHUNK_SIZE)) /* addressing by index. See above about smallbin repositioning */ #define smallbin_at(M, i) ((sbinptr)((char*)&((M)->smallbins[(i)<<1]))) #define treebin_at(M,i) (&((M)->treebins[i])) /* assign tree index for size S to variable I */ #if defined(__GNUC__) && defined(i386) #define compute_tree_index(S, I)\ {\ size_t X = S >> TREEBIN_SHIFT;\ if (X == 0)\ I = 0;\ else if (X > 0xFFFF)\ I = NTREEBINS-1;\ else {\ unsigned int K;\ __asm__("bsrl %1,%0\n\t" : "=r" (K) : "rm" (X));\ I = (bindex_t)((K << 1) + ((S >> (K + (TREEBIN_SHIFT-1)) & 1)));\ }\ } #else /* GNUC */ #define compute_tree_index(S, I)\ {\ size_t X = S >> TREEBIN_SHIFT;\ if (X == 0)\ I = 0;\ else if (X > 0xFFFF)\ I = NTREEBINS-1;\ else {\ unsigned int Y = (unsigned int)X;\ unsigned int N = ((Y - 0x100) >> 16) & 8;\ unsigned int K = (((Y <<= N) - 0x1000) >> 16) & 4;\ N += K;\ N += K = (((Y <<= K) - 0x4000) >> 16) & 2;\ K = 14 - N + ((Y <<= K) >> 15);\ I = (K << 1) + ((S >> (K + (TREEBIN_SHIFT-1)) & 1));\ }\ } #endif /* GNUC */ /* Bit representing maximum resolved size in a treebin at i */ #define bit_for_tree_index(i) \ (i == NTREEBINS-1)? (SIZE_T_BITSIZE-1) : (((i) >> 1) + TREEBIN_SHIFT - 2) /* Shift placing maximum resolved bit in a treebin at i as sign bit */ #define leftshift_for_tree_index(i) \ ((i == NTREEBINS-1)? 0 : \ ((SIZE_T_BITSIZE-SIZE_T_ONE) - (((i) >> 1) + TREEBIN_SHIFT - 2))) /* The size of the smallest chunk held in bin with index i */ #define minsize_for_tree_index(i) \ ((SIZE_T_ONE << (((i) >> 1) + TREEBIN_SHIFT)) | \ (((size_t)((i) & SIZE_T_ONE)) << (((i) >> 1) + TREEBIN_SHIFT - 1))) /* ------------------------ Operations on bin maps ----------------------- */ /* bit corresponding to given index */ #define idx2bit(i) ((binmap_t)(1) << (i)) /* Mark/Clear bits with given index */ #define mark_smallmap(M,i) ((M)->smallmap |= idx2bit(i)) #define clear_smallmap(M,i) ((M)->smallmap &= ~idx2bit(i)) #define smallmap_is_marked(M,i) ((M)->smallmap & idx2bit(i)) #define mark_treemap(M,i) ((M)->treemap |= idx2bit(i)) #define clear_treemap(M,i) ((M)->treemap &= ~idx2bit(i)) #define treemap_is_marked(M,i) ((M)->treemap & idx2bit(i)) /* index corresponding to given bit */ #if defined(__GNUC__) && defined(i386) #define compute_bit2idx(X, I)\ {\ unsigned int J;\ __asm__("bsfl %1,%0\n\t" : "=r" (J) : "rm" (X));\ I = (bindex_t)J;\ } #else /* GNUC */ #if USE_BUILTIN_FFS #define compute_bit2idx(X, I) I = ffs(X)-1 #else /* USE_BUILTIN_FFS */ #define compute_bit2idx(X, I)\ {\ unsigned int Y = X - 1;\ unsigned int K = Y >> (16-4) & 16;\ unsigned int N = K; Y >>= K;\ N += K = Y >> (8-3) & 8; Y >>= K;\ N += K = Y >> (4-2) & 4; Y >>= K;\ N += K = Y >> (2-1) & 2; Y >>= K;\ N += K = Y >> (1-0) & 1; Y >>= K;\ I = (bindex_t)(N + Y);\ } #endif /* USE_BUILTIN_FFS */ #endif /* GNUC */ /* isolate the least set bit of a bitmap */ #define least_bit(x) ((x) & -(x)) /* mask with all bits to left of least bit of x on */ #define left_bits(x) ((x<<1) | -(x<<1)) /* mask with all bits to left of or equal to least bit of x on */ #define same_or_left_bits(x) ((x) | -(x)) /* ----------------------- Runtime Check Support ------------------------- */ /* For security, the main invariant is that malloc/free/etc never writes to a static address other than malloc_state, unless static malloc_state itself has been corrupted, which cannot occur via malloc (because of these checks). In essence this means that we believe all pointers, sizes, maps etc held in malloc_state, but check all of those linked or offsetted from other embedded data structures. These checks are interspersed with main code in a way that tends to minimize their run-time cost. When FOOTERS is defined, in addition to range checking, we also verify footer fields of inuse chunks, which can be used guarantee that the mstate controlling malloc/free is intact. This is a streamlined version of the approach described by William Robertson et al in "Run-time Detection of Heap-based Overflows" LISA'03 http://www.usenix.org/events/lisa03/tech/robertson.html The footer of an inuse chunk holds the xor of its mstate and a random seed, that is checked upon calls to free() and realloc(). This is (probablistically) unguessable from outside the program, but can be computed by any code successfully malloc'ing any chunk, so does not itself provide protection against code that has already broken security through some other means. Unlike Robertson et al, we always dynamically check addresses of all offset chunks (previous, next, etc). This turns out to be cheaper than relying on hashes. */ #if !INSECURE /* Check if address a is at least as high as any from MORECORE or MMAP */ #define ok_address(M, a) ((char*)(a) >= (M)->least_addr) /* Check if address of next chunk n is higher than base chunk p */ #define ok_next(p, n) ((char*)(p) < (char*)(n)) /* Check if p has its cinuse bit on */ #define ok_cinuse(p) cinuse(p) /* Check if p has its pinuse bit on */ #define ok_pinuse(p) pinuse(p) #else /* !INSECURE */ #define ok_address(M, a) (1) #define ok_next(b, n) (1) #define ok_cinuse(p) (1) #define ok_pinuse(p) (1) #endif /* !INSECURE */ #if (FOOTERS && !INSECURE) /* Check if (alleged) mstate m has expected magic field */ #define ok_magic(M) ((M)->magic == mparams.magic) #else /* (FOOTERS && !INSECURE) */ #define ok_magic(M) (1) #endif /* (FOOTERS && !INSECURE) */ /* In gcc, use __builtin_expect to minimize impact of checks */ #if !INSECURE #if defined(__GNUC__) && __GNUC__ >= 3 #define RTCHECK(e) __builtin_expect(e, 1) #else /* GNUC */ #define RTCHECK(e) (e) #endif /* GNUC */ #else /* !INSECURE */ #define RTCHECK(e) (1) #endif /* !INSECURE */ /* macros to set up inuse chunks with or without footers */ #if !FOOTERS #define mark_inuse_foot(M,p,s) /* Set cinuse bit and pinuse bit of next chunk */ #define set_inuse(M,p,s)\ ((p)->head = (((p)->head & PINUSE_BIT)|s|CINUSE_BIT),\ ((mchunkptr)(((char*)(p)) + (s)))->head |= PINUSE_BIT) /* Set cinuse and pinuse of this chunk and pinuse of next chunk */ #define set_inuse_and_pinuse(M,p,s)\ ((p)->head = (s|PINUSE_BIT|CINUSE_BIT),\ ((mchunkptr)(((char*)(p)) + (s)))->head |= PINUSE_BIT) /* Set size, cinuse and pinuse bit of this chunk */ #define set_size_and_pinuse_of_inuse_chunk(M, p, s)\ ((p)->head = (s|PINUSE_BIT|CINUSE_BIT)) #else /* FOOTERS */ /* Set foot of inuse chunk to be xor of mstate and seed */ #define mark_inuse_foot(M,p,s)\ (((mchunkptr)((char*)(p) + (s)))->prev_foot = ((size_t)(M) ^ mparams.magic)) #define get_mstate_for(p)\ ((mstate)(((mchunkptr)((char*)(p) +\ (chunksize(p))))->prev_foot ^ mparams.magic)) #define set_inuse(M,p,s)\ ((p)->head = (((p)->head & PINUSE_BIT)|s|CINUSE_BIT),\ (((mchunkptr)(((char*)(p)) + (s)))->head |= PINUSE_BIT), \ mark_inuse_foot(M,p,s)) #define set_inuse_and_pinuse(M,p,s)\ ((p)->head = (s|PINUSE_BIT|CINUSE_BIT),\ (((mchunkptr)(((char*)(p)) + (s)))->head |= PINUSE_BIT),\ mark_inuse_foot(M,p,s)) #define set_size_and_pinuse_of_inuse_chunk(M, p, s)\ ((p)->head = (s|PINUSE_BIT|CINUSE_BIT),\ mark_inuse_foot(M, p, s)) #endif /* !FOOTERS */ /* ---------------------------- setting mparams -------------------------- */ /* Initialize mparams */ static int init_mparams(void) { if (mparams.page_size == 0) { size_t s; mparams.mmap_threshold = DEFAULT_MMAP_THRESHOLD; mparams.trim_threshold = DEFAULT_TRIM_THRESHOLD; #if MORECORE_CONTIGUOUS mparams.default_mflags = USE_LOCK_BIT|USE_MMAP_BIT; #else /* MORECORE_CONTIGUOUS */ mparams.default_mflags = USE_LOCK_BIT|USE_MMAP_BIT|USE_NONCONTIGUOUS_BIT; #endif /* MORECORE_CONTIGUOUS */ #if (FOOTERS && !INSECURE) { #if USE_DEV_RANDOM int fd; unsigned char buf[sizeof(size_t)]; /* Try to use /dev/urandom, else fall back on using time */ if ((fd = open("/dev/urandom", O_RDONLY)) >= 0 && read(fd, buf, sizeof(buf)) == sizeof(buf)) { s = *((size_t *) buf); close(fd); } else #endif /* USE_DEV_RANDOM */ s = (size_t)(time(0) ^ (size_t)0x55555555U); s |= (size_t)8U; /* ensure nonzero */ s &= ~(size_t)7U; /* improve chances of fault for bad values */ } #else /* (FOOTERS && !INSECURE) */ s = (size_t)0x58585858U; #endif /* (FOOTERS && !INSECURE) */ ACQUIRE_MAGIC_INIT_LOCK(); if (mparams.magic == 0) { mparams.magic = s; /* Set up lock for main malloc area */ INITIAL_LOCK(&gm->mutex); gm->mflags = mparams.default_mflags; } RELEASE_MAGIC_INIT_LOCK(); #if !defined(WIN32) && !defined(__OS2__) mparams.page_size = malloc_getpagesize; mparams.granularity = ((DEFAULT_GRANULARITY != 0)? DEFAULT_GRANULARITY : mparams.page_size); #elif defined (__OS2__) /* if low-memory is used, os2munmap() would break if it were anything other than 64k */ mparams.page_size = 4096u; mparams.granularity = 65536u; #else /* WIN32 */ { SYSTEM_INFO system_info; GetSystemInfo(&system_info); mparams.page_size = system_info.dwPageSize; mparams.granularity = system_info.dwAllocationGranularity; } #endif /* WIN32 */ /* Sanity-check configuration: size_t must be unsigned and as wide as pointer type. ints must be at least 4 bytes. alignment must be at least 8. Alignment, min chunk size, and page size must all be powers of 2. */ if ((sizeof(size_t) != sizeof(char*)) || (MAX_SIZE_T < MIN_CHUNK_SIZE) || (sizeof(int) < 4) || (MALLOC_ALIGNMENT < (size_t)8U) || ((MALLOC_ALIGNMENT & (MALLOC_ALIGNMENT-SIZE_T_ONE)) != 0) || ((MCHUNK_SIZE & (MCHUNK_SIZE-SIZE_T_ONE)) != 0) || ((mparams.granularity & (mparams.granularity-SIZE_T_ONE)) != 0) || ((mparams.page_size & (mparams.page_size-SIZE_T_ONE)) != 0)) ABORT; } return 0; } /* support for mallopt */ static int change_mparam(int param_number, int value) { size_t val = (size_t)value; init_mparams(); switch(param_number) { case M_TRIM_THRESHOLD: mparams.trim_threshold = val; return 1; case M_GRANULARITY: if (val >= mparams.page_size && ((val & (val-1)) == 0)) { mparams.granularity = val; return 1; } else return 0; case M_MMAP_THRESHOLD: mparams.mmap_threshold = val; return 1; default: return 0; } } #if DEBUG /* ------------------------- Debugging Support --------------------------- */ /* Check properties of any chunk, whether free, inuse, mmapped etc */ static void do_check_any_chunk(mstate m, mchunkptr p) { assert((is_aligned(chunk2mem(p))) || (p->head == FENCEPOST_HEAD)); assert(ok_address(m, p)); } /* Check properties of top chunk */ static void do_check_top_chunk(mstate m, mchunkptr p) { msegmentptr sp = segment_holding(m, (char*)p); size_t sz = chunksize(p); assert(sp != 0); assert((is_aligned(chunk2mem(p))) || (p->head == FENCEPOST_HEAD)); assert(ok_address(m, p)); assert(sz == m->topsize); assert(sz > 0); assert(sz == ((sp->base + sp->size) - (char*)p) - TOP_FOOT_SIZE); assert(pinuse(p)); assert(!next_pinuse(p)); } /* Check properties of (inuse) mmapped chunks */ static void do_check_mmapped_chunk(mstate m, mchunkptr p) { size_t sz = chunksize(p); size_t len = (sz + (p->prev_foot & ~IS_MMAPPED_BIT) + MMAP_FOOT_PAD); assert(is_mmapped(p)); assert(use_mmap(m)); assert((is_aligned(chunk2mem(p))) || (p->head == FENCEPOST_HEAD)); assert(ok_address(m, p)); assert(!is_small(sz)); assert((len & (mparams.page_size-SIZE_T_ONE)) == 0); assert(chunk_plus_offset(p, sz)->head == FENCEPOST_HEAD); assert(chunk_plus_offset(p, sz+SIZE_T_SIZE)->head == 0); } /* Check properties of inuse chunks */ static void do_check_inuse_chunk(mstate m, mchunkptr p) { do_check_any_chunk(m, p); assert(cinuse(p)); assert(next_pinuse(p)); /* If not pinuse and not mmapped, previous chunk has OK offset */ assert(is_mmapped(p) || pinuse(p) || next_chunk(prev_chunk(p)) == p); if (is_mmapped(p)) do_check_mmapped_chunk(m, p); } /* Check properties of free chunks */ static void do_check_free_chunk(mstate m, mchunkptr p) { size_t sz = p->head & ~(PINUSE_BIT|CINUSE_BIT); mchunkptr next = chunk_plus_offset(p, sz); do_check_any_chunk(m, p); assert(!cinuse(p)); assert(!next_pinuse(p)); assert (!is_mmapped(p)); if (p != m->dv && p != m->top) { if (sz >= MIN_CHUNK_SIZE) { assert((sz & CHUNK_ALIGN_MASK) == 0); assert(is_aligned(chunk2mem(p))); assert(next->prev_foot == sz); assert(pinuse(p)); assert (next == m->top || cinuse(next)); assert(p->fd->bk == p); assert(p->bk->fd == p); } else /* markers are always of size SIZE_T_SIZE */ assert(sz == SIZE_T_SIZE); } } /* Check properties of malloced chunks at the point they are malloced */ static void do_check_malloced_chunk(mstate m, void* mem, size_t s) { if (mem != 0) { mchunkptr p = mem2chunk(mem); size_t sz = p->head & ~(PINUSE_BIT|CINUSE_BIT); do_check_inuse_chunk(m, p); assert((sz & CHUNK_ALIGN_MASK) == 0); assert(sz >= MIN_CHUNK_SIZE); assert(sz >= s); /* unless mmapped, size is less than MIN_CHUNK_SIZE more than request */ assert(is_mmapped(p) || sz < (s + MIN_CHUNK_SIZE)); } } /* Check a tree and its subtrees. */ static void do_check_tree(mstate m, tchunkptr t) { tchunkptr head = 0; tchunkptr u = t; bindex_t tindex = t->index; size_t tsize = chunksize(t); bindex_t idx; compute_tree_index(tsize, idx); assert(tindex == idx); assert(tsize >= MIN_LARGE_SIZE); assert(tsize >= minsize_for_tree_index(idx)); assert((idx == NTREEBINS-1) || (tsize < minsize_for_tree_index((idx+1)))); do { /* traverse through chain of same-sized nodes */ do_check_any_chunk(m, ((mchunkptr)u)); assert(u->index == tindex); assert(chunksize(u) == tsize); assert(!cinuse(u)); assert(!next_pinuse(u)); assert(u->fd->bk == u); assert(u->bk->fd == u); if (u->parent == 0) { assert(u->child[0] == 0); assert(u->child[1] == 0); } else { assert(head == 0); /* only one node on chain has parent */ head = u; assert(u->parent != u); assert (u->parent->child[0] == u || u->parent->child[1] == u || *((tbinptr*)(u->parent)) == u); if (u->child[0] != 0) { assert(u->child[0]->parent == u); assert(u->child[0] != u); do_check_tree(m, u->child[0]); } if (u->child[1] != 0) { assert(u->child[1]->parent == u); assert(u->child[1] != u); do_check_tree(m, u->child[1]); } if (u->child[0] != 0 && u->child[1] != 0) { assert(chunksize(u->child[0]) < chunksize(u->child[1])); } } u = u->fd; } while (u != t); assert(head != 0); } /* Check all the chunks in a treebin. */ static void do_check_treebin(mstate m, bindex_t i) { tbinptr* tb = treebin_at(m, i); tchunkptr t = *tb; int empty = (m->treemap & (1U << i)) == 0; if (t == 0) assert(empty); if (!empty) do_check_tree(m, t); } /* Check all the chunks in a smallbin. */ static void do_check_smallbin(mstate m, bindex_t i) { sbinptr b = smallbin_at(m, i); mchunkptr p = b->bk; unsigned int empty = (m->smallmap & (1U << i)) == 0; if (p == b) assert(empty); if (!empty) { for (; p != b; p = p->bk) { size_t size = chunksize(p); mchunkptr q; /* each chunk claims to be free */ do_check_free_chunk(m, p); /* chunk belongs in bin */ assert(small_index(size) == i); assert(p->bk == b || chunksize(p->bk) == chunksize(p)); /* chunk is followed by an inuse chunk */ q = next_chunk(p); if (q->head != FENCEPOST_HEAD) do_check_inuse_chunk(m, q); } } } /* Find x in a bin. Used in other check functions. */ static int bin_find(mstate m, mchunkptr x) { size_t size = chunksize(x); if (is_small(size)) { bindex_t sidx = small_index(size); sbinptr b = smallbin_at(m, sidx); if (smallmap_is_marked(m, sidx)) { mchunkptr p = b; do { if (p == x) return 1; } while ((p = p->fd) != b); } } else { bindex_t tidx; compute_tree_index(size, tidx); if (treemap_is_marked(m, tidx)) { tchunkptr t = *treebin_at(m, tidx); size_t sizebits = size << leftshift_for_tree_index(tidx); while (t != 0 && chunksize(t) != size) { t = t->child[(sizebits >> (SIZE_T_BITSIZE-SIZE_T_ONE)) & 1]; sizebits <<= 1; } if (t != 0) { tchunkptr u = t; do { if (u == (tchunkptr)x) return 1; } while ((u = u->fd) != t); } } } return 0; } /* Traverse each chunk and check it; return total */ static size_t traverse_and_check(mstate m) { size_t sum = 0; if (is_initialized(m)) { msegmentptr s = &m->seg; sum += m->topsize + TOP_FOOT_SIZE; while (s != 0) { mchunkptr q = align_as_chunk(s->base); mchunkptr lastq = 0; assert(pinuse(q)); while (segment_holds(s, q) && q != m->top && q->head != FENCEPOST_HEAD) { sum += chunksize(q); if (cinuse(q)) { assert(!bin_find(m, q)); do_check_inuse_chunk(m, q); } else { assert(q == m->dv || bin_find(m, q)); assert(lastq == 0 || cinuse(lastq)); /* Not 2 consecutive free */ do_check_free_chunk(m, q); } lastq = q; q = next_chunk(q); } s = s->next; } } return sum; } /* Check all properties of malloc_state. */ static void do_check_malloc_state(mstate m) { bindex_t i; size_t total; /* check bins */ for (i = 0; i < NSMALLBINS; ++i) do_check_smallbin(m, i); for (i = 0; i < NTREEBINS; ++i) do_check_treebin(m, i); if (m->dvsize != 0) { /* check dv chunk */ do_check_any_chunk(m, m->dv); assert(m->dvsize == chunksize(m->dv)); assert(m->dvsize >= MIN_CHUNK_SIZE); assert(bin_find(m, m->dv) == 0); } if (m->top != 0) { /* check top chunk */ do_check_top_chunk(m, m->top); assert(m->topsize == chunksize(m->top)); assert(m->topsize > 0); assert(bin_find(m, m->top) == 0); } total = traverse_and_check(m); assert(total <= m->footprint); assert(m->footprint <= m->max_footprint); } #endif /* DEBUG */ /* ----------------------------- statistics ------------------------------ */ #if !NO_MALLINFO static struct mallinfo internal_mallinfo(mstate m) { struct mallinfo nm = { 0, 0, 0, 0, 0, 0, 0, 0, 0, 0 }; if (!PREACTION(m)) { check_malloc_state(m); if (is_initialized(m)) { size_t nfree = SIZE_T_ONE; /* top always free */ size_t mfree = m->topsize + TOP_FOOT_SIZE; size_t sum = mfree; msegmentptr s = &m->seg; while (s != 0) { mchunkptr q = align_as_chunk(s->base); while (segment_holds(s, q) && q != m->top && q->head != FENCEPOST_HEAD) { size_t sz = chunksize(q); sum += sz; if (!cinuse(q)) { mfree += sz; ++nfree; } q = next_chunk(q); } s = s->next; } nm.arena = sum; nm.ordblks = nfree; nm.hblkhd = m->footprint - sum; nm.usmblks = m->max_footprint; nm.uordblks = m->footprint - mfree; nm.fordblks = mfree; nm.keepcost = m->topsize; } POSTACTION(m); } return nm; } #endif /* !NO_MALLINFO */ static void internal_malloc_stats(mstate m) { if (!PREACTION(m)) { size_t maxfp = 0; size_t fp = 0; size_t used = 0; check_malloc_state(m); if (is_initialized(m)) { msegmentptr s = &m->seg; maxfp = m->max_footprint; fp = m->footprint; used = fp - (m->topsize + TOP_FOOT_SIZE); while (s != 0) { mchunkptr q = align_as_chunk(s->base); while (segment_holds(s, q) && q != m->top && q->head != FENCEPOST_HEAD) { if (!cinuse(q)) used -= chunksize(q); q = next_chunk(q); } s = s->next; } } fprintf(stderr, "max system bytes = %10lu\n", (unsigned long)(maxfp)); fprintf(stderr, "system bytes = %10lu\n", (unsigned long)(fp)); fprintf(stderr, "in use bytes = %10lu\n", (unsigned long)(used)); POSTACTION(m); } } /* ----------------------- Operations on smallbins ----------------------- */ /* Various forms of linking and unlinking are defined as macros. Even the ones for trees, which are very long but have very short typical paths. This is ugly but reduces reliance on inlining support of compilers. */ /* Link a free chunk into a smallbin */ #define insert_small_chunk(M, P, S) {\ bindex_t I = small_index(S);\ mchunkptr B = smallbin_at(M, I);\ mchunkptr F = B;\ assert(S >= MIN_CHUNK_SIZE);\ if (!smallmap_is_marked(M, I))\ mark_smallmap(M, I);\ else if (RTCHECK(ok_address(M, B->fd)))\ F = B->fd;\ else {\ CORRUPTION_ERROR_ACTION(M);\ }\ B->fd = P;\ F->bk = P;\ P->fd = F;\ P->bk = B;\ } /* Unlink a chunk from a smallbin */ #define unlink_small_chunk(M, P, S) {\ mchunkptr F = P->fd;\ mchunkptr B = P->bk;\ bindex_t I = small_index(S);\ assert(P != B);\ assert(P != F);\ assert(chunksize(P) == small_index2size(I));\ if (F == B)\ clear_smallmap(M, I);\ else if (RTCHECK((F == smallbin_at(M,I) || ok_address(M, F)) &&\ (B == smallbin_at(M,I) || ok_address(M, B)))) {\ F->bk = B;\ B->fd = F;\ }\ else {\ CORRUPTION_ERROR_ACTION(M);\ }\ } /* Unlink the first chunk from a smallbin */ #define unlink_first_small_chunk(M, B, P, I) {\ mchunkptr F = P->fd;\ assert(P != B);\ assert(P != F);\ assert(chunksize(P) == small_index2size(I));\ if (B == F)\ clear_smallmap(M, I);\ else if (RTCHECK(ok_address(M, F))) {\ B->fd = F;\ F->bk = B;\ }\ else {\ CORRUPTION_ERROR_ACTION(M);\ }\ } /* Replace dv node, binning the old one */ /* Used only when dvsize known to be small */ #define replace_dv(M, P, S) {\ size_t DVS = M->dvsize;\ if (DVS != 0) {\ mchunkptr DV = M->dv;\ assert(is_small(DVS));\ insert_small_chunk(M, DV, DVS);\ }\ M->dvsize = S;\ M->dv = P;\ } /* ------------------------- Operations on trees ------------------------- */ /* Insert chunk into tree */ #define insert_large_chunk(M, X, S) {\ tbinptr* H;\ bindex_t I;\ compute_tree_index(S, I);\ H = treebin_at(M, I);\ X->index = I;\ X->child[0] = X->child[1] = 0;\ if (!treemap_is_marked(M, I)) {\ mark_treemap(M, I);\ *H = X;\ X->parent = (tchunkptr)H;\ X->fd = X->bk = X;\ }\ else {\ tchunkptr T = *H;\ size_t K = S << leftshift_for_tree_index(I);\ for (;;) {\ if (chunksize(T) != S) {\ tchunkptr* C = &(T->child[(K >> (SIZE_T_BITSIZE-SIZE_T_ONE)) & 1]);\ K <<= 1;\ if (*C != 0)\ T = *C;\ else if (RTCHECK(ok_address(M, C))) {\ *C = X;\ X->parent = T;\ X->fd = X->bk = X;\ break;\ }\ else {\ CORRUPTION_ERROR_ACTION(M);\ break;\ }\ }\ else {\ tchunkptr F = T->fd;\ if (RTCHECK(ok_address(M, T) && ok_address(M, F))) {\ T->fd = F->bk = X;\ X->fd = F;\ X->bk = T;\ X->parent = 0;\ break;\ }\ else {\ CORRUPTION_ERROR_ACTION(M);\ break;\ }\ }\ }\ }\ } /* Unlink steps: 1. If x is a chained node, unlink it from its same-sized fd/bk links and choose its bk node as its replacement. 2. If x was the last node of its size, but not a leaf node, it must be replaced with a leaf node (not merely one with an open left or right), to make sure that lefts and rights of descendents correspond properly to bit masks. We use the rightmost descendent of x. We could use any other leaf, but this is easy to locate and tends to counteract removal of leftmosts elsewhere, and so keeps paths shorter than minimally guaranteed. This doesn't loop much because on average a node in a tree is near the bottom. 3. If x is the base of a chain (i.e., has parent links) relink x's parent and children to x's replacement (or null if none). */ #define unlink_large_chunk(M, X) {\ tchunkptr XP = X->parent;\ tchunkptr R;\ if (X->bk != X) {\ tchunkptr F = X->fd;\ R = X->bk;\ if (RTCHECK(ok_address(M, F))) {\ F->bk = R;\ R->fd = F;\ }\ else {\ CORRUPTION_ERROR_ACTION(M);\ }\ }\ else {\ tchunkptr* RP;\ if (((R = *(RP = &(X->child[1]))) != 0) ||\ ((R = *(RP = &(X->child[0]))) != 0)) {\ tchunkptr* CP;\ while ((*(CP = &(R->child[1])) != 0) ||\ (*(CP = &(R->child[0])) != 0)) {\ R = *(RP = CP);\ }\ if (RTCHECK(ok_address(M, RP)))\ *RP = 0;\ else {\ CORRUPTION_ERROR_ACTION(M);\ }\ }\ }\ if (XP != 0) {\ tbinptr* H = treebin_at(M, X->index);\ if (X == *H) {\ if ((*H = R) == 0) \ clear_treemap(M, X->index);\ }\ else if (RTCHECK(ok_address(M, XP))) {\ if (XP->child[0] == X) \ XP->child[0] = R;\ else \ XP->child[1] = R;\ }\ else\ CORRUPTION_ERROR_ACTION(M);\ if (R != 0) {\ if (RTCHECK(ok_address(M, R))) {\ tchunkptr C0, C1;\ R->parent = XP;\ if ((C0 = X->child[0]) != 0) {\ if (RTCHECK(ok_address(M, C0))) {\ R->child[0] = C0;\ C0->parent = R;\ }\ else\ CORRUPTION_ERROR_ACTION(M);\ }\ if ((C1 = X->child[1]) != 0) {\ if (RTCHECK(ok_address(M, C1))) {\ R->child[1] = C1;\ C1->parent = R;\ }\ else\ CORRUPTION_ERROR_ACTION(M);\ }\ }\ else\ CORRUPTION_ERROR_ACTION(M);\ }\ }\ } /* Relays to large vs small bin operations */ #define insert_chunk(M, P, S)\ if (is_small(S)) insert_small_chunk(M, P, S)\ else { tchunkptr TP = (tchunkptr)(P); insert_large_chunk(M, TP, S); } #define unlink_chunk(M, P, S)\ if (is_small(S)) unlink_small_chunk(M, P, S)\ else { tchunkptr TP = (tchunkptr)(P); unlink_large_chunk(M, TP); } /* Relays to internal calls to malloc/free from realloc, memalign etc */ #if ONLY_MSPACES #define internal_malloc(m, b) mspace_malloc(m, b) #define internal_free(m, mem) mspace_free(m,mem); #else /* ONLY_MSPACES */ #if MSPACES #define internal_malloc(m, b)\ (m == gm)? dlmalloc(b) : mspace_malloc(m, b) #define internal_free(m, mem)\ if (m == gm) dlfree(mem); else mspace_free(m,mem); #else /* MSPACES */ #define internal_malloc(m, b) dlmalloc(b) #define internal_free(m, mem) dlfree(mem) #endif /* MSPACES */ #endif /* ONLY_MSPACES */ /* ----------------------- Direct-mmapping chunks ----------------------- */ /* Directly mmapped chunks are set up with an offset to the start of the mmapped region stored in the prev_foot field of the chunk. This allows reconstruction of the required argument to MUNMAP when freed, and also allows adjustment of the returned chunk to meet alignment requirements (especially in memalign). There is also enough space allocated to hold a fake next chunk of size SIZE_T_SIZE to maintain the PINUSE bit so frees can be checked. */ /* Malloc using mmap */ static void* mmap_alloc(mstate m, size_t nb) { size_t mmsize = granularity_align(nb + SIX_SIZE_T_SIZES + CHUNK_ALIGN_MASK); if (mmsize > nb) { /* Check for wrap around 0 */ char* mm = (char*)(DIRECT_MMAP(mmsize)); if (mm != CMFAIL) { size_t offset = align_offset(chunk2mem(mm)); size_t psize = mmsize - offset - MMAP_FOOT_PAD; mchunkptr p = (mchunkptr)(mm + offset); p->prev_foot = offset | IS_MMAPPED_BIT; (p)->head = (psize|CINUSE_BIT); mark_inuse_foot(m, p, psize); chunk_plus_offset(p, psize)->head = FENCEPOST_HEAD; chunk_plus_offset(p, psize+SIZE_T_SIZE)->head = 0; if (mm < m->least_addr) m->least_addr = mm; if ((m->footprint += mmsize) > m->max_footprint) m->max_footprint = m->footprint; assert(is_aligned(chunk2mem(p))); check_mmapped_chunk(m, p); return chunk2mem(p); } } return 0; } /* Realloc using mmap */ static mchunkptr mmap_resize(mstate m, mchunkptr oldp, size_t nb) { size_t oldsize = chunksize(oldp); if (is_small(nb)) /* Can't shrink mmap regions below small size */ return 0; /* Keep old chunk if big enough but not too big */ if (oldsize >= nb + SIZE_T_SIZE && (oldsize - nb) <= (mparams.granularity << 1)) return oldp; else { size_t offset = oldp->prev_foot & ~IS_MMAPPED_BIT; size_t oldmmsize = oldsize + offset + MMAP_FOOT_PAD; size_t newmmsize = granularity_align(nb + SIX_SIZE_T_SIZES + CHUNK_ALIGN_MASK); char* cp = (char*)CALL_MREMAP((char*)oldp - offset, oldmmsize, newmmsize, 1); if (cp != CMFAIL) { mchunkptr newp = (mchunkptr)(cp + offset); size_t psize = newmmsize - offset - MMAP_FOOT_PAD; newp->head = (psize|CINUSE_BIT); mark_inuse_foot(m, newp, psize); chunk_plus_offset(newp, psize)->head = FENCEPOST_HEAD; chunk_plus_offset(newp, psize+SIZE_T_SIZE)->head = 0; if (cp < m->least_addr) m->least_addr = cp; if ((m->footprint += newmmsize - oldmmsize) > m->max_footprint) m->max_footprint = m->footprint; check_mmapped_chunk(m, newp); return newp; } } return 0; } /* -------------------------- mspace management -------------------------- */ /* Initialize top chunk and its size */ static void init_top(mstate m, mchunkptr p, size_t psize) { /* Ensure alignment */ size_t offset = align_offset(chunk2mem(p)); p = (mchunkptr)((char*)p + offset); psize -= offset; m->top = p; m->topsize = psize; p->head = psize | PINUSE_BIT; /* set size of fake trailing chunk holding overhead space only once */ chunk_plus_offset(p, psize)->head = TOP_FOOT_SIZE; m->trim_check = mparams.trim_threshold; /* reset on each update */ } /* Initialize bins for a new mstate that is otherwise zeroed out */ static void init_bins(mstate m) { /* Establish circular links for smallbins */ bindex_t i; for (i = 0; i < NSMALLBINS; ++i) { sbinptr bin = smallbin_at(m,i); bin->fd = bin->bk = bin; } } #if PROCEED_ON_ERROR /* default corruption action */ static void reset_on_error(mstate m) { int i; ++malloc_corruption_error_count; /* Reinitialize fields to forget about all memory */ m->smallbins = m->treebins = 0; m->dvsize = m->topsize = 0; m->seg.base = 0; m->seg.size = 0; m->seg.next = 0; m->top = m->dv = 0; for (i = 0; i < NTREEBINS; ++i) *treebin_at(m, i) = 0; init_bins(m); } #endif /* PROCEED_ON_ERROR */ /* Allocate chunk and prepend remainder with chunk in successor base. */ static void* prepend_alloc(mstate m, char* newbase, char* oldbase, size_t nb) { mchunkptr p = align_as_chunk(newbase); mchunkptr oldfirst = align_as_chunk(oldbase); size_t psize = (char*)oldfirst - (char*)p; mchunkptr q = chunk_plus_offset(p, nb); size_t qsize = psize - nb; set_size_and_pinuse_of_inuse_chunk(m, p, nb); assert((char*)oldfirst > (char*)q); assert(pinuse(oldfirst)); assert(qsize >= MIN_CHUNK_SIZE); /* consolidate remainder with first chunk of old base */ if (oldfirst == m->top) { size_t tsize = m->topsize += qsize; m->top = q; q->head = tsize | PINUSE_BIT; check_top_chunk(m, q); } else if (oldfirst == m->dv) { size_t dsize = m->dvsize += qsize; m->dv = q; set_size_and_pinuse_of_free_chunk(q, dsize); } else { if (!cinuse(oldfirst)) { size_t nsize = chunksize(oldfirst); unlink_chunk(m, oldfirst, nsize); oldfirst = chunk_plus_offset(oldfirst, nsize); qsize += nsize; } set_free_with_pinuse(q, qsize, oldfirst); insert_chunk(m, q, qsize); check_free_chunk(m, q); } check_malloced_chunk(m, chunk2mem(p), nb); return chunk2mem(p); } /* Add a segment to hold a new noncontiguous region */ static void add_segment(mstate m, char* tbase, size_t tsize, flag_t mmapped) { /* Determine locations and sizes of segment, fenceposts, old top */ char* old_top = (char*)m->top; msegmentptr oldsp = segment_holding(m, old_top); char* old_end = oldsp->base + oldsp->size; size_t ssize = pad_request(sizeof(struct malloc_segment)); char* rawsp = old_end - (ssize + FOUR_SIZE_T_SIZES + CHUNK_ALIGN_MASK); size_t offset = align_offset(chunk2mem(rawsp)); char* asp = rawsp + offset; char* csp = (asp < (old_top + MIN_CHUNK_SIZE))? old_top : asp; mchunkptr sp = (mchunkptr)csp; msegmentptr ss = (msegmentptr)(chunk2mem(sp)); mchunkptr tnext = chunk_plus_offset(sp, ssize); mchunkptr p = tnext; int nfences = 0; /* reset top to new space */ init_top(m, (mchunkptr)tbase, tsize - TOP_FOOT_SIZE); /* Set up segment record */ assert(is_aligned(ss)); set_size_and_pinuse_of_inuse_chunk(m, sp, ssize); *ss = m->seg; /* Push current record */ m->seg.base = tbase; m->seg.size = tsize; set_segment_flags(&m->seg, mmapped); m->seg.next = ss; /* Insert trailing fenceposts */ for (;;) { mchunkptr nextp = chunk_plus_offset(p, SIZE_T_SIZE); p->head = FENCEPOST_HEAD; ++nfences; if ((char*)(&(nextp->head)) < old_end) p = nextp; else break; } assert(nfences >= 2); /* Insert the rest of old top into a bin as an ordinary free chunk */ if (csp != old_top) { mchunkptr q = (mchunkptr)old_top; size_t psize = csp - old_top; mchunkptr tn = chunk_plus_offset(q, psize); set_free_with_pinuse(q, psize, tn); insert_chunk(m, q, psize); } check_top_chunk(m, m->top); } /* -------------------------- System allocation -------------------------- */ /* Get memory from system using MORECORE or MMAP */ static void* sys_alloc(mstate m, size_t nb) { char* tbase = CMFAIL; size_t tsize = 0; flag_t mmap_flag = 0; init_mparams(); /* Directly map large chunks */ if (use_mmap(m) && nb >= mparams.mmap_threshold) { void* mem = mmap_alloc(m, nb); if (mem != 0) return mem; } /* Try getting memory in any of three ways (in most-preferred to least-preferred order): 1. A call to MORECORE that can normally contiguously extend memory. (disabled if not MORECORE_CONTIGUOUS or not HAVE_MORECORE or or main space is mmapped or a previous contiguous call failed) 2. A call to MMAP new space (disabled if not HAVE_MMAP). Note that under the default settings, if MORECORE is unable to fulfill a request, and HAVE_MMAP is true, then mmap is used as a noncontiguous system allocator. This is a useful backup strategy for systems with holes in address spaces -- in this case sbrk cannot contiguously expand the heap, but mmap may be able to find space. 3. A call to MORECORE that cannot usually contiguously extend memory. (disabled if not HAVE_MORECORE) */ if (MORECORE_CONTIGUOUS && !use_noncontiguous(m)) { char* br = CMFAIL; msegmentptr ss = (m->top == 0)? 0 : segment_holding(m, (char*)m->top); size_t asize = 0; ACQUIRE_MORECORE_LOCK(); if (ss == 0) { /* First time through or recovery */ char* base = (char*)CALL_MORECORE(0); if (base != CMFAIL) { asize = granularity_align(nb + TOP_FOOT_SIZE + SIZE_T_ONE); /* Adjust to end on a page boundary */ if (!is_page_aligned(base)) asize += (page_align((size_t)base) - (size_t)base); /* Can't call MORECORE if size is negative when treated as signed */ if (asize < HALF_MAX_SIZE_T && (br = (char*)(CALL_MORECORE(asize))) == base) { tbase = base; tsize = asize; } } } else { /* Subtract out existing available top space from MORECORE request. */ asize = granularity_align(nb - m->topsize + TOP_FOOT_SIZE + SIZE_T_ONE); /* Use mem here only if it did continuously extend old space */ if (asize < HALF_MAX_SIZE_T && (br = (char*)(CALL_MORECORE(asize))) == ss->base+ss->size) { tbase = br; tsize = asize; } } if (tbase == CMFAIL) { /* Cope with partial failure */ if (br != CMFAIL) { /* Try to use/extend the space we did get */ if (asize < HALF_MAX_SIZE_T && asize < nb + TOP_FOOT_SIZE + SIZE_T_ONE) { size_t esize = granularity_align(nb + TOP_FOOT_SIZE + SIZE_T_ONE - asize); if (esize < HALF_MAX_SIZE_T) { char* end = (char*)CALL_MORECORE(esize); if (end != CMFAIL) asize += esize; else { /* Can't use; try to release */ (void)CALL_MORECORE(-asize); br = CMFAIL; } } } } if (br != CMFAIL) { /* Use the space we did get */ tbase = br; tsize = asize; } else disable_contiguous(m); /* Don't try contiguous path in the future */ } RELEASE_MORECORE_LOCK(); } if (HAVE_MMAP && tbase == CMFAIL) { /* Try MMAP */ size_t req = nb + TOP_FOOT_SIZE + SIZE_T_ONE; size_t rsize = granularity_align(req); if (rsize > nb) { /* Fail if wraps around zero */ char* mp = (char*)(CALL_MMAP(rsize)); if (mp != CMFAIL) { tbase = mp; tsize = rsize; mmap_flag = IS_MMAPPED_BIT; } } } if (HAVE_MORECORE && tbase == CMFAIL) { /* Try noncontiguous MORECORE */ size_t asize = granularity_align(nb + TOP_FOOT_SIZE + SIZE_T_ONE); if (asize < HALF_MAX_SIZE_T) { char* br = CMFAIL; char* end = CMFAIL; ACQUIRE_MORECORE_LOCK(); br = (char*)(CALL_MORECORE(asize)); end = (char*)(CALL_MORECORE(0)); RELEASE_MORECORE_LOCK(); if (br != CMFAIL && end != CMFAIL && br < end) { size_t ssize = end - br; if (ssize > nb + TOP_FOOT_SIZE) { tbase = br; tsize = ssize; } } } } if (tbase != CMFAIL) { if ((m->footprint += tsize) > m->max_footprint) m->max_footprint = m->footprint; if (!is_initialized(m)) { /* first-time initialization */ m->seg.base = m->least_addr = tbase; m->seg.size = tsize; set_segment_flags(&m->seg, mmap_flag); m->magic = mparams.magic; init_bins(m); if (is_global(m)) init_top(m, (mchunkptr)tbase, tsize - TOP_FOOT_SIZE); else { /* Offset top by embedded malloc_state */ mchunkptr mn = next_chunk(mem2chunk(m)); init_top(m, mn, (size_t)((tbase + tsize) - (char*)mn) -TOP_FOOT_SIZE); } } else { /* Try to merge with an existing segment */ msegmentptr sp = &m->seg; while (sp != 0 && tbase != sp->base + sp->size) sp = sp->next; if (sp != 0 && !is_extern_segment(sp) && check_segment_merge(sp, tbase, tsize) && (get_segment_flags(sp) & IS_MMAPPED_BIT) == mmap_flag && segment_holds(sp, m->top)) { /* append */ sp->size += tsize; init_top(m, m->top, m->topsize + tsize); } else { if (tbase < m->least_addr) m->least_addr = tbase; sp = &m->seg; while (sp != 0 && sp->base != tbase + tsize) sp = sp->next; if (sp != 0 && !is_extern_segment(sp) && check_segment_merge(sp, tbase, tsize) && (get_segment_flags(sp) & IS_MMAPPED_BIT) == mmap_flag) { char* oldbase = sp->base; sp->base = tbase; sp->size += tsize; return prepend_alloc(m, tbase, oldbase, nb); } else add_segment(m, tbase, tsize, mmap_flag); } } if (nb < m->topsize) { /* Allocate from new or extended top space */ size_t rsize = m->topsize -= nb; mchunkptr p = m->top; mchunkptr r = m->top = chunk_plus_offset(p, nb); r->head = rsize | PINUSE_BIT; set_size_and_pinuse_of_inuse_chunk(m, p, nb); check_top_chunk(m, m->top); check_malloced_chunk(m, chunk2mem(p), nb); return chunk2mem(p); } } MALLOC_FAILURE_ACTION; return 0; } /* ----------------------- system deallocation -------------------------- */ /* Unmap and unlink any mmapped segments that don't contain used chunks */ static size_t release_unused_segments(mstate m) { size_t released = 0; msegmentptr pred = &m->seg; msegmentptr sp = pred->next; while (sp != 0) { char* base = sp->base; size_t size = sp->size; msegmentptr next = sp->next; if (is_mmapped_segment(sp) && !is_extern_segment(sp)) { mchunkptr p = align_as_chunk(base); size_t psize = chunksize(p); /* Can unmap if first chunk holds entire segment and not pinned */ if (!cinuse(p) && (char*)p + psize >= base + size - TOP_FOOT_SIZE) { tchunkptr tp = (tchunkptr)p; assert(segment_holds(sp, (char*)sp)); if (p == m->dv) { m->dv = 0; m->dvsize = 0; } else { unlink_large_chunk(m, tp); } if (CALL_MUNMAP(base, size) == 0) { released += size; m->footprint -= size; /* unlink obsoleted record */ sp = pred; sp->next = next; } else { /* back out if cannot unmap */ insert_large_chunk(m, tp, psize); } } } pred = sp; sp = next; } return released; } static int sys_trim(mstate m, size_t pad) { size_t released = 0; if (pad < MAX_REQUEST && is_initialized(m)) { pad += TOP_FOOT_SIZE; /* ensure enough room for segment overhead */ if (m->topsize > pad) { /* Shrink top space in granularity-size units, keeping at least one */ size_t unit = mparams.granularity; size_t extra = ((m->topsize - pad + (unit - SIZE_T_ONE)) / unit - SIZE_T_ONE) * unit; msegmentptr sp = segment_holding(m, (char*)m->top); if (!is_extern_segment(sp)) { if (is_mmapped_segment(sp)) { if (HAVE_MMAP && sp->size >= extra && !has_segment_link(m, sp)) { /* can't shrink if pinned */ size_t newsize = sp->size - extra; /* Prefer mremap, fall back to munmap */ if ((CALL_MREMAP(sp->base, sp->size, newsize, 0) != MFAIL) || (CALL_MUNMAP(sp->base + newsize, extra) == 0)) { released = extra; } } } else if (HAVE_MORECORE) { if (extra >= HALF_MAX_SIZE_T) /* Avoid wrapping negative */ extra = (HALF_MAX_SIZE_T) + SIZE_T_ONE - unit; ACQUIRE_MORECORE_LOCK(); { /* Make sure end of memory is where we last set it. */ char* old_br = (char*)(CALL_MORECORE(0)); if (old_br == sp->base + sp->size) { char* rel_br = (char*)(CALL_MORECORE(-extra)); char* new_br = (char*)(CALL_MORECORE(0)); if (rel_br != CMFAIL && new_br < old_br) released = old_br - new_br; } } RELEASE_MORECORE_LOCK(); } } if (released != 0) { sp->size -= released; m->footprint -= released; init_top(m, m->top, m->topsize - released); check_top_chunk(m, m->top); } } /* Unmap any unused mmapped segments */ if (HAVE_MMAP) released += release_unused_segments(m); /* On failure, disable autotrim to avoid repeated failed future calls */ if (released == 0) m->trim_check = MAX_SIZE_T; } return (released != 0)? 1 : 0; } /* ---------------------------- malloc support --------------------------- */ /* allocate a large request from the best fitting chunk in a treebin */ static void* tmalloc_large(mstate m, size_t nb) { tchunkptr v = 0; size_t rsize = -nb; /* Unsigned negation */ tchunkptr t; bindex_t idx; compute_tree_index(nb, idx); if ((t = *treebin_at(m, idx)) != 0) { /* Traverse tree for this bin looking for node with size == nb */ size_t sizebits = nb << leftshift_for_tree_index(idx); tchunkptr rst = 0; /* The deepest untaken right subtree */ for (;;) { tchunkptr rt; size_t trem = chunksize(t) - nb; if (trem < rsize) { v = t; if ((rsize = trem) == 0) break; } rt = t->child[1]; t = t->child[(sizebits >> (SIZE_T_BITSIZE-SIZE_T_ONE)) & 1]; if (rt != 0 && rt != t) rst = rt; if (t == 0) { t = rst; /* set t to least subtree holding sizes > nb */ break; } sizebits <<= 1; } } if (t == 0 && v == 0) { /* set t to root of next non-empty treebin */ binmap_t leftbits = left_bits(idx2bit(idx)) & m->treemap; if (leftbits != 0) { bindex_t i; binmap_t leastbit = least_bit(leftbits); compute_bit2idx(leastbit, i); t = *treebin_at(m, i); } } while (t != 0) { /* find smallest of tree or subtree */ size_t trem = chunksize(t) - nb; if (trem < rsize) { rsize = trem; v = t; } t = leftmost_child(t); } /* If dv is a better fit, return 0 so malloc will use it */ if (v != 0 && rsize < (size_t)(m->dvsize - nb)) { if (RTCHECK(ok_address(m, v))) { /* split */ mchunkptr r = chunk_plus_offset(v, nb); assert(chunksize(v) == rsize + nb); if (RTCHECK(ok_next(v, r))) { unlink_large_chunk(m, v); if (rsize < MIN_CHUNK_SIZE) set_inuse_and_pinuse(m, v, (rsize + nb)); else { set_size_and_pinuse_of_inuse_chunk(m, v, nb); set_size_and_pinuse_of_free_chunk(r, rsize); insert_chunk(m, r, rsize); } return chunk2mem(v); } } CORRUPTION_ERROR_ACTION(m); } return 0; } /* allocate a small request from the best fitting chunk in a treebin */ static void* tmalloc_small(mstate m, size_t nb) { tchunkptr t, v; size_t rsize; bindex_t i; binmap_t leastbit = least_bit(m->treemap); compute_bit2idx(leastbit, i); v = t = *treebin_at(m, i); rsize = chunksize(t) - nb; while ((t = leftmost_child(t)) != 0) { size_t trem = chunksize(t) - nb; if (trem < rsize) { rsize = trem; v = t; } } if (RTCHECK(ok_address(m, v))) { mchunkptr r = chunk_plus_offset(v, nb); assert(chunksize(v) == rsize + nb); if (RTCHECK(ok_next(v, r))) { unlink_large_chunk(m, v); if (rsize < MIN_CHUNK_SIZE) set_inuse_and_pinuse(m, v, (rsize + nb)); else { set_size_and_pinuse_of_inuse_chunk(m, v, nb); set_size_and_pinuse_of_free_chunk(r, rsize); replace_dv(m, r, rsize); } return chunk2mem(v); } } CORRUPTION_ERROR_ACTION(m); return 0; } /* --------------------------- realloc support --------------------------- */ static void* internal_realloc(mstate m, void* oldmem, size_t bytes) { if (bytes >= MAX_REQUEST) { MALLOC_FAILURE_ACTION; return 0; } if (!PREACTION(m)) { mchunkptr oldp = mem2chunk(oldmem); size_t oldsize = chunksize(oldp); mchunkptr next = chunk_plus_offset(oldp, oldsize); mchunkptr newp = 0; void* extra = 0; /* Try to either shrink or extend into top. Else malloc-copy-free */ if (RTCHECK(ok_address(m, oldp) && ok_cinuse(oldp) && ok_next(oldp, next) && ok_pinuse(next))) { size_t nb = request2size(bytes); if (is_mmapped(oldp)) newp = mmap_resize(m, oldp, nb); else if (oldsize >= nb) { /* already big enough */ size_t rsize = oldsize - nb; newp = oldp; if (rsize >= MIN_CHUNK_SIZE) { mchunkptr remainder = chunk_plus_offset(newp, nb); set_inuse(m, newp, nb); set_inuse(m, remainder, rsize); extra = chunk2mem(remainder); } } else if (next == m->top && oldsize + m->topsize > nb) { /* Expand into top */ size_t newsize = oldsize + m->topsize; size_t newtopsize = newsize - nb; mchunkptr newtop = chunk_plus_offset(oldp, nb); set_inuse(m, oldp, nb); newtop->head = newtopsize |PINUSE_BIT; m->top = newtop; m->topsize = newtopsize; newp = oldp; } } else { USAGE_ERROR_ACTION(m, oldmem); POSTACTION(m); return 0; } POSTACTION(m); if (newp != 0) { if (extra != 0) { internal_free(m, extra); } check_inuse_chunk(m, newp); return chunk2mem(newp); } else { void* newmem = internal_malloc(m, bytes); if (newmem != 0) { size_t oc = oldsize - overhead_for(oldp); memcpy(newmem, oldmem, (oc < bytes)? oc : bytes); internal_free(m, oldmem); } return newmem; } } return 0; } /* --------------------------- memalign support -------------------------- */ static void* internal_memalign(mstate m, size_t alignment, size_t bytes) { if (alignment <= MALLOC_ALIGNMENT) /* Can just use malloc */ return internal_malloc(m, bytes); if (alignment < MIN_CHUNK_SIZE) /* must be at least a minimum chunk size */ alignment = MIN_CHUNK_SIZE; if ((alignment & (alignment-SIZE_T_ONE)) != 0) {/* Ensure a power of 2 */ size_t a = MALLOC_ALIGNMENT << 1; while (a < alignment) a <<= 1; alignment = a; } if (bytes >= MAX_REQUEST - alignment) { if (m != 0) { /* Test isn't needed but avoids compiler warning */ MALLOC_FAILURE_ACTION; } } else { size_t nb = request2size(bytes); size_t req = nb + alignment + MIN_CHUNK_SIZE - CHUNK_OVERHEAD; char* mem = (char*)internal_malloc(m, req); if (mem != 0) { void* leader = 0; void* trailer = 0; mchunkptr p = mem2chunk(mem); if (PREACTION(m)) return 0; if ((((size_t)(mem)) % alignment) != 0) { /* misaligned */ /* Find an aligned spot inside chunk. Since we need to give back leading space in a chunk of at least MIN_CHUNK_SIZE, if the first calculation places us at a spot with less than MIN_CHUNK_SIZE leader, we can move to the next aligned spot. We've allocated enough total room so that this is always possible. */ char* br = (char*)mem2chunk((size_t)(((size_t)(mem + alignment - SIZE_T_ONE)) & -alignment)); char* pos = ((size_t)(br - (char*)(p)) >= MIN_CHUNK_SIZE)? br : br+alignment; mchunkptr newp = (mchunkptr)pos; size_t leadsize = pos - (char*)(p); size_t newsize = chunksize(p) - leadsize; if (is_mmapped(p)) { /* For mmapped chunks, just adjust offset */ newp->prev_foot = p->prev_foot + leadsize; newp->head = (newsize|CINUSE_BIT); } else { /* Otherwise, give back leader, use the rest */ set_inuse(m, newp, newsize); set_inuse(m, p, leadsize); leader = chunk2mem(p); } p = newp; } /* Give back spare room at the end */ if (!is_mmapped(p)) { size_t size = chunksize(p); if (size > nb + MIN_CHUNK_SIZE) { size_t remainder_size = size - nb; mchunkptr remainder = chunk_plus_offset(p, nb); set_inuse(m, p, nb); set_inuse(m, remainder, remainder_size); trailer = chunk2mem(remainder); } } assert (chunksize(p) >= nb); assert((((size_t)(chunk2mem(p))) % alignment) == 0); check_inuse_chunk(m, p); POSTACTION(m); if (leader != 0) { internal_free(m, leader); } if (trailer != 0) { internal_free(m, trailer); } return chunk2mem(p); } } return 0; } /* ------------------------ comalloc/coalloc support --------------------- */ static void** ialloc(mstate m, size_t n_elements, size_t* sizes, int opts, void* chunks[]) { /* This provides common support for independent_X routines, handling all of the combinations that can result. The opts arg has: bit 0 set if all elements are same size (using sizes[0]) bit 1 set if elements should be zeroed */ size_t element_size; /* chunksize of each element, if all same */ size_t contents_size; /* total size of elements */ size_t array_size; /* request size of pointer array */ void* mem; /* malloced aggregate space */ mchunkptr p; /* corresponding chunk */ size_t remainder_size; /* remaining bytes while splitting */ void** marray; /* either "chunks" or malloced ptr array */ mchunkptr array_chunk; /* chunk for malloced ptr array */ flag_t was_enabled; /* to disable mmap */ size_t size; size_t i; /* compute array length, if needed */ if (chunks != 0) { if (n_elements == 0) return chunks; /* nothing to do */ marray = chunks; array_size = 0; } else { /* if empty req, must still return chunk representing empty array */ if (n_elements == 0) return (void**)internal_malloc(m, 0); marray = 0; array_size = request2size(n_elements * (sizeof(void*))); } /* compute total element size */ if (opts & 0x1) { /* all-same-size */ element_size = request2size(*sizes); contents_size = n_elements * element_size; } else { /* add up all the sizes */ element_size = 0; contents_size = 0; for (i = 0; i != n_elements; ++i) contents_size += request2size(sizes[i]); } size = contents_size + array_size; /* Allocate the aggregate chunk. First disable direct-mmapping so malloc won't use it, since we would not be able to later free/realloc space internal to a segregated mmap region. */ was_enabled = use_mmap(m); disable_mmap(m); mem = internal_malloc(m, size - CHUNK_OVERHEAD); if (was_enabled) enable_mmap(m); if (mem == 0) return 0; if (PREACTION(m)) return 0; p = mem2chunk(mem); remainder_size = chunksize(p); assert(!is_mmapped(p)); if (opts & 0x2) { /* optionally clear the elements */ memset((size_t*)mem, 0, remainder_size - SIZE_T_SIZE - array_size); } /* If not provided, allocate the pointer array as final part of chunk */ if (marray == 0) { size_t array_chunk_size; array_chunk = chunk_plus_offset(p, contents_size); array_chunk_size = remainder_size - contents_size; marray = (void**) (chunk2mem(array_chunk)); set_size_and_pinuse_of_inuse_chunk(m, array_chunk, array_chunk_size); remainder_size = contents_size; } /* split out elements */ for (i = 0; ; ++i) { marray[i] = chunk2mem(p); if (i != n_elements-1) { if (element_size != 0) size = element_size; else size = request2size(sizes[i]); remainder_size -= size; set_size_and_pinuse_of_inuse_chunk(m, p, size); p = chunk_plus_offset(p, size); } else { /* the final element absorbs any overallocation slop */ set_size_and_pinuse_of_inuse_chunk(m, p, remainder_size); break; } } #if DEBUG if (marray != chunks) { /* final element must have exactly exhausted chunk */ if (element_size != 0) { assert(remainder_size == element_size); } else { assert(remainder_size == request2size(sizes[i])); } check_inuse_chunk(m, mem2chunk(marray)); } for (i = 0; i != n_elements; ++i) check_inuse_chunk(m, mem2chunk(marray[i])); #endif /* DEBUG */ POSTACTION(m); return marray; } /* -------------------------- public routines ---------------------------- */ #if !ONLY_MSPACES void* dlmalloc(size_t bytes) { /* Basic algorithm: If a small request (< 256 bytes minus per-chunk overhead): 1. If one exists, use a remainderless chunk in associated smallbin. (Remainderless means that there are too few excess bytes to represent as a chunk.) 2. If it is big enough, use the dv chunk, which is normally the chunk adjacent to the one used for the most recent small request. 3. If one exists, split the smallest available chunk in a bin, saving remainder in dv. 4. If it is big enough, use the top chunk. 5. If available, get memory from system and use it Otherwise, for a large request: 1. Find the smallest available binned chunk that fits, and use it if it is better fitting than dv chunk, splitting if necessary. 2. If better fitting than any binned chunk, use the dv chunk. 3. If it is big enough, use the top chunk. 4. If request size >= mmap threshold, try to directly mmap this chunk. 5. If available, get memory from system and use it The ugly goto's here ensure that postaction occurs along all paths. */ if (!PREACTION(gm)) { void* mem; size_t nb; if (bytes <= MAX_SMALL_REQUEST) { bindex_t idx; binmap_t smallbits; nb = (bytes < MIN_REQUEST)? MIN_CHUNK_SIZE : pad_request(bytes); idx = small_index(nb); smallbits = gm->smallmap >> idx; if ((smallbits & 0x3U) != 0) { /* Remainderless fit to a smallbin. */ mchunkptr b, p; idx += ~smallbits & 1; /* Uses next bin if idx empty */ b = smallbin_at(gm, idx); p = b->fd; assert(chunksize(p) == small_index2size(idx)); unlink_first_small_chunk(gm, b, p, idx); set_inuse_and_pinuse(gm, p, small_index2size(idx)); mem = chunk2mem(p); check_malloced_chunk(gm, mem, nb); goto postaction; } else if (nb > gm->dvsize) { if (smallbits != 0) { /* Use chunk in next nonempty smallbin */ mchunkptr b, p, r; size_t rsize; bindex_t i; binmap_t leftbits = (smallbits << idx) & left_bits(idx2bit(idx)); binmap_t leastbit = least_bit(leftbits); compute_bit2idx(leastbit, i); b = smallbin_at(gm, i); p = b->fd; assert(chunksize(p) == small_index2size(i)); unlink_first_small_chunk(gm, b, p, i); rsize = small_index2size(i) - nb; /* Fit here cannot be remainderless if 4byte sizes */ if (SIZE_T_SIZE != 4 && rsize < MIN_CHUNK_SIZE) set_inuse_and_pinuse(gm, p, small_index2size(i)); else { set_size_and_pinuse_of_inuse_chunk(gm, p, nb); r = chunk_plus_offset(p, nb); set_size_and_pinuse_of_free_chunk(r, rsize); replace_dv(gm, r, rsize); } mem = chunk2mem(p); check_malloced_chunk(gm, mem, nb); goto postaction; } else if (gm->treemap != 0 && (mem = tmalloc_small(gm, nb)) != 0) { check_malloced_chunk(gm, mem, nb); goto postaction; } } } else if (bytes >= MAX_REQUEST) nb = MAX_SIZE_T; /* Too big to allocate. Force failure (in sys alloc) */ else { nb = pad_request(bytes); if (gm->treemap != 0 && (mem = tmalloc_large(gm, nb)) != 0) { check_malloced_chunk(gm, mem, nb); goto postaction; } } if (nb <= gm->dvsize) { size_t rsize = gm->dvsize - nb; mchunkptr p = gm->dv; if (rsize >= MIN_CHUNK_SIZE) { /* split dv */ mchunkptr r = gm->dv = chunk_plus_offset(p, nb); gm->dvsize = rsize; set_size_and_pinuse_of_free_chunk(r, rsize); set_size_and_pinuse_of_inuse_chunk(gm, p, nb); } else { /* exhaust dv */ size_t dvs = gm->dvsize; gm->dvsize = 0; gm->dv = 0; set_inuse_and_pinuse(gm, p, dvs); } mem = chunk2mem(p); check_malloced_chunk(gm, mem, nb); goto postaction; } else if (nb < gm->topsize) { /* Split top */ size_t rsize = gm->topsize -= nb; mchunkptr p = gm->top; mchunkptr r = gm->top = chunk_plus_offset(p, nb); r->head = rsize | PINUSE_BIT; set_size_and_pinuse_of_inuse_chunk(gm, p, nb); mem = chunk2mem(p); check_top_chunk(gm, gm->top); check_malloced_chunk(gm, mem, nb); goto postaction; } mem = sys_alloc(gm, nb); postaction: POSTACTION(gm); return mem; } return 0; } void dlfree(void* mem) { /* Consolidate freed chunks with preceding or succeeding bordering free chunks, if they exist, and then place in a bin. Intermixed with special cases for top, dv, mmapped chunks, and usage errors. */ if (mem != 0) { mchunkptr p = mem2chunk(mem); #if FOOTERS mstate fm = get_mstate_for(p); if (!ok_magic(fm)) { USAGE_ERROR_ACTION(fm, p); return; } #else /* FOOTERS */ #define fm gm #endif /* FOOTERS */ if (!PREACTION(fm)) { check_inuse_chunk(fm, p); if (RTCHECK(ok_address(fm, p) && ok_cinuse(p))) { size_t psize = chunksize(p); mchunkptr next = chunk_plus_offset(p, psize); if (!pinuse(p)) { size_t prevsize = p->prev_foot; if ((prevsize & IS_MMAPPED_BIT) != 0) { prevsize &= ~IS_MMAPPED_BIT; psize += prevsize + MMAP_FOOT_PAD; if (CALL_MUNMAP((char*)p - prevsize, psize) == 0) fm->footprint -= psize; goto postaction; } else { mchunkptr prev = chunk_minus_offset(p, prevsize); psize += prevsize; p = prev; if (RTCHECK(ok_address(fm, prev))) { /* consolidate backward */ if (p != fm->dv) { unlink_chunk(fm, p, prevsize); } else if ((next->head & INUSE_BITS) == INUSE_BITS) { fm->dvsize = psize; set_free_with_pinuse(p, psize, next); goto postaction; } } else goto erroraction; } } if (RTCHECK(ok_next(p, next) && ok_pinuse(next))) { if (!cinuse(next)) { /* consolidate forward */ if (next == fm->top) { size_t tsize = fm->topsize += psize; fm->top = p; p->head = tsize | PINUSE_BIT; if (p == fm->dv) { fm->dv = 0; fm->dvsize = 0; } if (should_trim(fm, tsize)) sys_trim(fm, 0); goto postaction; } else if (next == fm->dv) { size_t dsize = fm->dvsize += psize; fm->dv = p; set_size_and_pinuse_of_free_chunk(p, dsize); goto postaction; } else { size_t nsize = chunksize(next); psize += nsize; unlink_chunk(fm, next, nsize); set_size_and_pinuse_of_free_chunk(p, psize); if (p == fm->dv) { fm->dvsize = psize; goto postaction; } } } else set_free_with_pinuse(p, psize, next); insert_chunk(fm, p, psize); check_free_chunk(fm, p); goto postaction; } } erroraction: USAGE_ERROR_ACTION(fm, p); postaction: POSTACTION(fm); } } #if !FOOTERS #undef fm #endif /* FOOTERS */ } void* dlcalloc(size_t n_elements, size_t elem_size) { void* mem; size_t req = 0; if (n_elements != 0) { req = n_elements * elem_size; if (((n_elements | elem_size) & ~(size_t)0xffff) && (req / n_elements != elem_size)) req = MAX_SIZE_T; /* force downstream failure on overflow */ } mem = dlmalloc(req); if (mem != 0 && calloc_must_clear(mem2chunk(mem))) memset(mem, 0, req); return mem; } void* dlrealloc(void* oldmem, size_t bytes) { if (oldmem == 0) return dlmalloc(bytes); #ifdef REALLOC_ZERO_BYTES_FREES if (bytes == 0) { dlfree(oldmem); return 0; } #endif /* REALLOC_ZERO_BYTES_FREES */ else { #if ! FOOTERS mstate m = gm; #else /* FOOTERS */ mstate m = get_mstate_for(mem2chunk(oldmem)); if (!ok_magic(m)) { USAGE_ERROR_ACTION(m, oldmem); return 0; } #endif /* FOOTERS */ return internal_realloc(m, oldmem, bytes); } } void* dlmemalign(size_t alignment, size_t bytes) { return internal_memalign(gm, alignment, bytes); } void** dlindependent_calloc(size_t n_elements, size_t elem_size, void* chunks[]) { size_t sz = elem_size; /* serves as 1-element array */ return ialloc(gm, n_elements, &sz, 3, chunks); } void** dlindependent_comalloc(size_t n_elements, size_t sizes[], void* chunks[]) { return ialloc(gm, n_elements, sizes, 0, chunks); } void* dlvalloc(size_t bytes) { size_t pagesz; init_mparams(); pagesz = mparams.page_size; return dlmemalign(pagesz, bytes); } void* dlpvalloc(size_t bytes) { size_t pagesz; init_mparams(); pagesz = mparams.page_size; return dlmemalign(pagesz, (bytes + pagesz - SIZE_T_ONE) & ~(pagesz - SIZE_T_ONE)); } int dlmalloc_trim(size_t pad) { int result = 0; if (!PREACTION(gm)) { result = sys_trim(gm, pad); POSTACTION(gm); } return result; } size_t dlmalloc_footprint(void) { return gm->footprint; } size_t dlmalloc_max_footprint(void) { return gm->max_footprint; } #if !NO_MALLINFO struct mallinfo dlmallinfo(void) { return internal_mallinfo(gm); } #endif /* NO_MALLINFO */ void dlmalloc_stats() { internal_malloc_stats(gm); } size_t dlmalloc_usable_size(void* mem) { if (mem != 0) { mchunkptr p = mem2chunk(mem); if (cinuse(p)) return chunksize(p) - overhead_for(p); } return 0; } int dlmallopt(int param_number, int value) { return change_mparam(param_number, value); } #endif /* !ONLY_MSPACES */ /* ----------------------------- user mspaces ---------------------------- */ #if MSPACES static mstate init_user_mstate(char* tbase, size_t tsize) { size_t msize = pad_request(sizeof(struct malloc_state)); mchunkptr mn; mchunkptr msp = align_as_chunk(tbase); mstate m = (mstate)(chunk2mem(msp)); memset(m, 0, msize); INITIAL_LOCK(&m->mutex); msp->head = (msize|PINUSE_BIT|CINUSE_BIT); m->seg.base = m->least_addr = tbase; m->seg.size = m->footprint = m->max_footprint = tsize; m->magic = mparams.magic; m->mflags = mparams.default_mflags; disable_contiguous(m); init_bins(m); mn = next_chunk(mem2chunk(m)); init_top(m, mn, (size_t)((tbase + tsize) - (char*)mn) - TOP_FOOT_SIZE); check_top_chunk(m, m->top); return m; } mspace create_mspace(size_t capacity, int locked) { mstate m = 0; size_t msize = pad_request(sizeof(struct malloc_state)); init_mparams(); /* Ensure pagesize etc initialized */ if (capacity < (size_t) -(msize + TOP_FOOT_SIZE + mparams.page_size)) { size_t rs = ((capacity == 0)? mparams.granularity : (capacity + TOP_FOOT_SIZE + msize)); size_t tsize = granularity_align(rs); char* tbase = (char*)(CALL_MMAP(tsize)); if (tbase != CMFAIL) { m = init_user_mstate(tbase, tsize); set_segment_flags(&m->seg, IS_MMAPPED_BIT); set_lock(m, locked); } } return (mspace)m; } mspace create_mspace_with_base(void* base, size_t capacity, int locked) { mstate m = 0; size_t msize = pad_request(sizeof(struct malloc_state)); init_mparams(); /* Ensure pagesize etc initialized */ if (capacity > msize + TOP_FOOT_SIZE && capacity < (size_t) -(msize + TOP_FOOT_SIZE + mparams.page_size)) { m = init_user_mstate((char*)base, capacity); set_segment_flags(&m->seg, EXTERN_BIT); set_lock(m, locked); } return (mspace)m; } size_t destroy_mspace(mspace msp) { size_t freed = 0; mstate ms = (mstate)msp; if (ok_magic(ms)) { msegmentptr sp = &ms->seg; while (sp != 0) { char* base = sp->base; size_t size = sp->size; flag_t flag = get_segment_flags(sp); sp = sp->next; if ((flag & IS_MMAPPED_BIT) && !(flag & EXTERN_BIT) && CALL_MUNMAP(base, size) == 0) freed += size; } } else { USAGE_ERROR_ACTION(ms,ms); } return freed; } /* mspace versions of routines are near-clones of the global versions. This is not so nice but better than the alternatives. */ void* mspace_malloc(mspace msp, size_t bytes) { mstate ms = (mstate)msp; if (!ok_magic(ms)) { USAGE_ERROR_ACTION(ms,ms); return 0; } if (!PREACTION(ms)) { void* mem; size_t nb; if (bytes <= MAX_SMALL_REQUEST) { bindex_t idx; binmap_t smallbits; nb = (bytes < MIN_REQUEST)? MIN_CHUNK_SIZE : pad_request(bytes); idx = small_index(nb); smallbits = ms->smallmap >> idx; if ((smallbits & 0x3U) != 0) { /* Remainderless fit to a smallbin. */ mchunkptr b, p; idx += ~smallbits & 1; /* Uses next bin if idx empty */ b = smallbin_at(ms, idx); p = b->fd; assert(chunksize(p) == small_index2size(idx)); unlink_first_small_chunk(ms, b, p, idx); set_inuse_and_pinuse(ms, p, small_index2size(idx)); mem = chunk2mem(p); check_malloced_chunk(ms, mem, nb); goto postaction; } else if (nb > ms->dvsize) { if (smallbits != 0) { /* Use chunk in next nonempty smallbin */ mchunkptr b, p, r; size_t rsize; bindex_t i; binmap_t leftbits = (smallbits << idx) & left_bits(idx2bit(idx)); binmap_t leastbit = least_bit(leftbits); compute_bit2idx(leastbit, i); b = smallbin_at(ms, i); p = b->fd; assert(chunksize(p) == small_index2size(i)); unlink_first_small_chunk(ms, b, p, i); rsize = small_index2size(i) - nb; /* Fit here cannot be remainderless if 4byte sizes */ if (SIZE_T_SIZE != 4 && rsize < MIN_CHUNK_SIZE) set_inuse_and_pinuse(ms, p, small_index2size(i)); else { set_size_and_pinuse_of_inuse_chunk(ms, p, nb); r = chunk_plus_offset(p, nb); set_size_and_pinuse_of_free_chunk(r, rsize); replace_dv(ms, r, rsize); } mem = chunk2mem(p); check_malloced_chunk(ms, mem, nb); goto postaction; } else if (ms->treemap != 0 && (mem = tmalloc_small(ms, nb)) != 0) { check_malloced_chunk(ms, mem, nb); goto postaction; } } } else if (bytes >= MAX_REQUEST) nb = MAX_SIZE_T; /* Too big to allocate. Force failure (in sys alloc) */ else { nb = pad_request(bytes); if (ms->treemap != 0 && (mem = tmalloc_large(ms, nb)) != 0) { check_malloced_chunk(ms, mem, nb); goto postaction; } } if (nb <= ms->dvsize) { size_t rsize = ms->dvsize - nb; mchunkptr p = ms->dv; if (rsize >= MIN_CHUNK_SIZE) { /* split dv */ mchunkptr r = ms->dv = chunk_plus_offset(p, nb); ms->dvsize = rsize; set_size_and_pinuse_of_free_chunk(r, rsize); set_size_and_pinuse_of_inuse_chunk(ms, p, nb); } else { /* exhaust dv */ size_t dvs = ms->dvsize; ms->dvsize = 0; ms->dv = 0; set_inuse_and_pinuse(ms, p, dvs); } mem = chunk2mem(p); check_malloced_chunk(ms, mem, nb); goto postaction; } else if (nb < ms->topsize) { /* Split top */ size_t rsize = ms->topsize -= nb; mchunkptr p = ms->top; mchunkptr r = ms->top = chunk_plus_offset(p, nb); r->head = rsize | PINUSE_BIT; set_size_and_pinuse_of_inuse_chunk(ms, p, nb); mem = chunk2mem(p); check_top_chunk(ms, ms->top); check_malloced_chunk(ms, mem, nb); goto postaction; } mem = sys_alloc(ms, nb); postaction: POSTACTION(ms); return mem; } return 0; } void mspace_free(mspace msp, void* mem) { if (mem != 0) { mchunkptr p = mem2chunk(mem); #if FOOTERS mstate fm = get_mstate_for(p); #else /* FOOTERS */ mstate fm = (mstate)msp; #endif /* FOOTERS */ if (!ok_magic(fm)) { USAGE_ERROR_ACTION(fm, p); return; } if (!PREACTION(fm)) { check_inuse_chunk(fm, p); if (RTCHECK(ok_address(fm, p) && ok_cinuse(p))) { size_t psize = chunksize(p); mchunkptr next = chunk_plus_offset(p, psize); if (!pinuse(p)) { size_t prevsize = p->prev_foot; if ((prevsize & IS_MMAPPED_BIT) != 0) { prevsize &= ~IS_MMAPPED_BIT; psize += prevsize + MMAP_FOOT_PAD; if (CALL_MUNMAP((char*)p - prevsize, psize) == 0) fm->footprint -= psize; goto postaction; } else { mchunkptr prev = chunk_minus_offset(p, prevsize); psize += prevsize; p = prev; if (RTCHECK(ok_address(fm, prev))) { /* consolidate backward */ if (p != fm->dv) { unlink_chunk(fm, p, prevsize); } else if ((next->head & INUSE_BITS) == INUSE_BITS) { fm->dvsize = psize; set_free_with_pinuse(p, psize, next); goto postaction; } } else goto erroraction; } } if (RTCHECK(ok_next(p, next) && ok_pinuse(next))) { if (!cinuse(next)) { /* consolidate forward */ if (next == fm->top) { size_t tsize = fm->topsize += psize; fm->top = p; p->head = tsize | PINUSE_BIT; if (p == fm->dv) { fm->dv = 0; fm->dvsize = 0; } if (should_trim(fm, tsize)) sys_trim(fm, 0); goto postaction; } else if (next == fm->dv) { size_t dsize = fm->dvsize += psize; fm->dv = p; set_size_and_pinuse_of_free_chunk(p, dsize); goto postaction; } else { size_t nsize = chunksize(next); psize += nsize; unlink_chunk(fm, next, nsize); set_size_and_pinuse_of_free_chunk(p, psize); if (p == fm->dv) { fm->dvsize = psize; goto postaction; } } } else set_free_with_pinuse(p, psize, next); insert_chunk(fm, p, psize); check_free_chunk(fm, p); goto postaction; } } erroraction: USAGE_ERROR_ACTION(fm, p); postaction: POSTACTION(fm); } } } void* mspace_calloc(mspace msp, size_t n_elements, size_t elem_size) { void* mem; size_t req = 0; mstate ms = (mstate)msp; if (!ok_magic(ms)) { USAGE_ERROR_ACTION(ms,ms); return 0; } if (n_elements != 0) { req = n_elements * elem_size; if (((n_elements | elem_size) & ~(size_t)0xffff) && (req / n_elements != elem_size)) req = MAX_SIZE_T; /* force downstream failure on overflow */ } mem = internal_malloc(ms, req); if (mem != 0 && calloc_must_clear(mem2chunk(mem))) memset(mem, 0, req); return mem; } void* mspace_realloc(mspace msp, void* oldmem, size_t bytes) { if (oldmem == 0) return mspace_malloc(msp, bytes); #ifdef REALLOC_ZERO_BYTES_FREES if (bytes == 0) { mspace_free(msp, oldmem); return 0; } #endif /* REALLOC_ZERO_BYTES_FREES */ else { #if FOOTERS mchunkptr p = mem2chunk(oldmem); mstate ms = get_mstate_for(p); #else /* FOOTERS */ mstate ms = (mstate)msp; #endif /* FOOTERS */ if (!ok_magic(ms)) { USAGE_ERROR_ACTION(ms,ms); return 0; } return internal_realloc(ms, oldmem, bytes); } } void* mspace_memalign(mspace msp, size_t alignment, size_t bytes) { mstate ms = (mstate)msp; if (!ok_magic(ms)) { USAGE_ERROR_ACTION(ms,ms); return 0; } return internal_memalign(ms, alignment, bytes); } void** mspace_independent_calloc(mspace msp, size_t n_elements, size_t elem_size, void* chunks[]) { size_t sz = elem_size; /* serves as 1-element array */ mstate ms = (mstate)msp; if (!ok_magic(ms)) { USAGE_ERROR_ACTION(ms,ms); return 0; } return ialloc(ms, n_elements, &sz, 3, chunks); } void** mspace_independent_comalloc(mspace msp, size_t n_elements, size_t sizes[], void* chunks[]) { mstate ms = (mstate)msp; if (!ok_magic(ms)) { USAGE_ERROR_ACTION(ms,ms); return 0; } return ialloc(ms, n_elements, sizes, 0, chunks); } int mspace_trim(mspace msp, size_t pad) { int result = 0; mstate ms = (mstate)msp; if (ok_magic(ms)) { if (!PREACTION(ms)) { result = sys_trim(ms, pad); POSTACTION(ms); } } else { USAGE_ERROR_ACTION(ms,ms); } return result; } void mspace_malloc_stats(mspace msp) { mstate ms = (mstate)msp; if (ok_magic(ms)) { internal_malloc_stats(ms); } else { USAGE_ERROR_ACTION(ms,ms); } } size_t mspace_footprint(mspace msp) { size_t result; mstate ms = (mstate)msp; if (ok_magic(ms)) { result = ms->footprint; } USAGE_ERROR_ACTION(ms,ms); return result; } size_t mspace_max_footprint(mspace msp) { size_t result; mstate ms = (mstate)msp; if (ok_magic(ms)) { result = ms->max_footprint; } USAGE_ERROR_ACTION(ms,ms); return result; } #if !NO_MALLINFO struct mallinfo mspace_mallinfo(mspace msp) { mstate ms = (mstate)msp; if (!ok_magic(ms)) { USAGE_ERROR_ACTION(ms,ms); } return internal_mallinfo(ms); } #endif /* NO_MALLINFO */ int mspace_mallopt(int param_number, int value) { return change_mparam(param_number, value); } #endif /* MSPACES */ /* -------------------- Alternative MORECORE functions ------------------- */ /* Guidelines for creating a custom version of MORECORE: * For best performance, MORECORE should allocate in multiples of pagesize. * MORECORE may allocate more memory than requested. (Or even less, but this will usually result in a malloc failure.) * MORECORE must not allocate memory when given argument zero, but instead return one past the end address of memory from previous nonzero call. * For best performance, consecutive calls to MORECORE with positive arguments should return increasing addresses, indicating that space has been contiguously extended. * Even though consecutive calls to MORECORE need not return contiguous addresses, it must be OK for malloc'ed chunks to span multiple regions in those cases where they do happen to be contiguous. * MORECORE need not handle negative arguments -- it may instead just return MFAIL when given negative arguments. Negative arguments are always multiples of pagesize. MORECORE must not misinterpret negative args as large positive unsigned args. You can suppress all such calls from even occurring by defining MORECORE_CANNOT_TRIM, As an example alternative MORECORE, here is a custom allocator kindly contributed for pre-OSX macOS. It uses virtually but not necessarily physically contiguous non-paged memory (locked in, present and won't get swapped out). You can use it by uncommenting this section, adding some #includes, and setting up the appropriate defines above: #define MORECORE osMoreCore There is also a shutdown routine that should somehow be called for cleanup upon program exit. #define MAX_POOL_ENTRIES 100 #define MINIMUM_MORECORE_SIZE (64 * 1024U) static int next_os_pool; void *our_os_pools[MAX_POOL_ENTRIES]; void *osMoreCore(int size) { void *ptr = 0; static void *sbrk_top = 0; if (size > 0) { if (size < MINIMUM_MORECORE_SIZE) size = MINIMUM_MORECORE_SIZE; if (CurrentExecutionLevel() == kTaskLevel) ptr = PoolAllocateResident(size + RM_PAGE_SIZE, 0); if (ptr == 0) { return (void *) MFAIL; } // save ptrs so they can be freed during cleanup our_os_pools[next_os_pool] = ptr; next_os_pool++; ptr = (void *) ((((size_t) ptr) + RM_PAGE_MASK) & ~RM_PAGE_MASK); sbrk_top = (char *) ptr + size; return ptr; } else if (size < 0) { // we don't currently support shrink behavior return (void *) MFAIL; } else { return sbrk_top; } } // cleanup any allocated memory pools // called as last thing before shutting down driver void osCleanupMem(void) { void **ptr; for (ptr = our_os_pools; ptr < &our_os_pools[MAX_POOL_ENTRIES]; ptr++) if (*ptr) { PoolDeallocate(*ptr); *ptr = 0; } } */ /* ----------------------------------------------------------------------- History: V2.8.3 Thu Sep 22 11:16:32 2005 Doug Lea (dl at gee) * Add max_footprint functions * Ensure all appropriate literals are size_t * Fix conditional compilation problem for some #define settings * Avoid concatenating segments with the one provided in create_mspace_with_base * Rename some variables to avoid compiler shadowing warnings * Use explicit lock initialization. * Better handling of sbrk interference. * Simplify and fix segment insertion, trimming and mspace_destroy * Reinstate REALLOC_ZERO_BYTES_FREES option from 2.7.x * Thanks especially to Dennis Flanagan for help on these. V2.8.2 Sun Jun 12 16:01:10 2005 Doug Lea (dl at gee) * Fix memalign brace error. V2.8.1 Wed Jun 8 16:11:46 2005 Doug Lea (dl at gee) * Fix improper #endif nesting in C++ * Add explicit casts needed for C++ V2.8.0 Mon May 30 14:09:02 2005 Doug Lea (dl at gee) * Use trees for large bins * Support mspaces * Use segments to unify sbrk-based and mmap-based system allocation, removing need for emulation on most platforms without sbrk. * Default safety checks * Optional footer checks. Thanks to William Robertson for the idea. * Internal code refactoring * Incorporate suggestions and platform-specific changes. Thanks to Dennis Flanagan, Colin Plumb, Niall Douglas, Aaron Bachmann, Emery Berger, and others. * Speed up non-fastbin processing enough to remove fastbins. * Remove useless cfree() to avoid conflicts with other apps. * Remove internal memcpy, memset. Compilers handle builtins better. * Remove some options that no one ever used and rename others. V2.7.2 Sat Aug 17 09:07:30 2002 Doug Lea (dl at gee) * Fix malloc_state bitmap array misdeclaration V2.7.1 Thu Jul 25 10:58:03 2002 Doug Lea (dl at gee) * Allow tuning of FIRST_SORTED_BIN_SIZE * Use PTR_UINT as type for all ptr->int casts. Thanks to John Belmonte. * Better detection and support for non-contiguousness of MORECORE. Thanks to Andreas Mueller, Conal Walsh, and Wolfram Gloger * Bypass most of malloc if no frees. Thanks To Emery Berger. * Fix freeing of old top non-contiguous chunk im sysmalloc. * Raised default trim and map thresholds to 256K. * Fix mmap-related #defines. Thanks to Lubos Lunak. * Fix copy macros; added LACKS_FCNTL_H. Thanks to Neal Walfield. * Branch-free bin calculation * Default trim and mmap thresholds now 256K. V2.7.0 Sun Mar 11 14:14:06 2001 Doug Lea (dl at gee) * Introduce independent_comalloc and independent_calloc. Thanks to Michael Pachos for motivation and help. * Make optional .h file available * Allow > 2GB requests on 32bit systems. * new WIN32 sbrk, mmap, munmap, lock code from . Thanks also to Andreas Mueller , and Anonymous. * Allow override of MALLOC_ALIGNMENT (Thanks to Ruud Waij for helping test this.) * memalign: check alignment arg * realloc: don't try to shift chunks backwards, since this leads to more fragmentation in some programs and doesn't seem to help in any others. * Collect all cases in malloc requiring system memory into sysmalloc * Use mmap as backup to sbrk * Place all internal state in malloc_state * Introduce fastbins (although similar to 2.5.1) * Many minor tunings and cosmetic improvements * Introduce USE_PUBLIC_MALLOC_WRAPPERS, USE_MALLOC_LOCK * Introduce MALLOC_FAILURE_ACTION, MORECORE_CONTIGUOUS Thanks to Tony E. Bennett and others. * Include errno.h to support default failure action. V2.6.6 Sun Dec 5 07:42:19 1999 Doug Lea (dl at gee) * return null for negative arguments * Added Several WIN32 cleanups from Martin C. Fong * Add 'LACKS_SYS_PARAM_H' for those systems without 'sys/param.h' (e.g. WIN32 platforms) * Cleanup header file inclusion for WIN32 platforms * Cleanup code to avoid Microsoft Visual C++ compiler complaints * Add 'USE_DL_PREFIX' to quickly allow co-existence with existing memory allocation routines * Set 'malloc_getpagesize' for WIN32 platforms (needs more work) * Use 'assert' rather than 'ASSERT' in WIN32 code to conform to usage of 'assert' in non-WIN32 code * Improve WIN32 'sbrk()' emulation's 'findRegion()' routine to avoid infinite loop * Always call 'fREe()' rather than 'free()' V2.6.5 Wed Jun 17 15:57:31 1998 Doug Lea (dl at gee) * Fixed ordering problem with boundary-stamping V2.6.3 Sun May 19 08:17:58 1996 Doug Lea (dl at gee) * Added pvalloc, as recommended by H.J. Liu * Added 64bit pointer support mainly from Wolfram Gloger * Added anonymously donated WIN32 sbrk emulation * Malloc, calloc, getpagesize: add optimizations from Raymond Nijssen * malloc_extend_top: fix mask error that caused wastage after foreign sbrks * Add linux mremap support code from HJ Liu V2.6.2 Tue Dec 5 06:52:55 1995 Doug Lea (dl at gee) * Integrated most documentation with the code. * Add support for mmap, with help from Wolfram Gloger (Gloger@lrz.uni-muenchen.de). * Use last_remainder in more cases. * Pack bins using idea from colin@nyx10.cs.du.edu * Use ordered bins instead of best-fit threshhold * Eliminate block-local decls to simplify tracing and debugging. * Support another case of realloc via move into top * Fix error occuring when initial sbrk_base not word-aligned. * Rely on page size for units instead of SBRK_UNIT to avoid surprises about sbrk alignment conventions. * Add mallinfo, mallopt. Thanks to Raymond Nijssen (raymond@es.ele.tue.nl) for the suggestion. * Add `pad' argument to malloc_trim and top_pad mallopt parameter. * More precautions for cases where other routines call sbrk, courtesy of Wolfram Gloger (Gloger@lrz.uni-muenchen.de). * Added macros etc., allowing use in linux libc from H.J. Lu (hjl@gnu.ai.mit.edu) * Inverted this history list V2.6.1 Sat Dec 2 14:10:57 1995 Doug Lea (dl at gee) * Re-tuned and fixed to behave more nicely with V2.6.0 changes. * Removed all preallocation code since under current scheme the work required to undo bad preallocations exceeds the work saved in good cases for most test programs. * No longer use return list or unconsolidated bins since no scheme using them consistently outperforms those that don't given above changes. * Use best fit for very large chunks to prevent some worst-cases. * Added some support for debugging V2.6.0 Sat Nov 4 07:05:23 1995 Doug Lea (dl at gee) * Removed footers when chunks are in use. Thanks to Paul Wilson (wilson@cs.texas.edu) for the suggestion. V2.5.4 Wed Nov 1 07:54:51 1995 Doug Lea (dl at gee) * Added malloc_trim, with help from Wolfram Gloger (wmglo@Dent.MED.Uni-Muenchen.DE). V2.5.3 Tue Apr 26 10:16:01 1994 Doug Lea (dl at g) V2.5.2 Tue Apr 5 16:20:40 1994 Doug Lea (dl at g) * realloc: try to expand in both directions * malloc: swap order of clean-bin strategy; * realloc: only conditionally expand backwards * Try not to scavenge used bins * Use bin counts as a guide to preallocation * Occasionally bin return list chunks in first scan * Add a few optimizations from colin@nyx10.cs.du.edu V2.5.1 Sat Aug 14 15:40:43 1993 Doug Lea (dl at g) * faster bin computation & slightly different binning * merged all consolidations to one part of malloc proper (eliminating old malloc_find_space & malloc_clean_bin) * Scan 2 returns chunks (not just 1) * Propagate failure in realloc if malloc returns 0 * Add stuff to allow compilation on non-ANSI compilers from kpv@research.att.com V2.5 Sat Aug 7 07:41:59 1993 Doug Lea (dl at g.oswego.edu) * removed potential for odd address access in prev_chunk * removed dependency on getpagesize.h * misc cosmetics and a bit more internal documentation * anticosmetics: mangled names in macros to evade debugger strangeness * tested on sparc, hp-700, dec-mips, rs6000 with gcc & native cc (hp, dec only) allowing Detlefs & Zorn comparison study (in SIGPLAN Notices.) Trial version Fri Aug 28 13:14:29 1992 Doug Lea (dl at g.oswego.edu) * Based loosely on libg++-1.2X malloc. (It retains some of the overall structure of old version, but most details differ.) */ smalltalk-3.2.5/libffi/src/m32r/0000755000175000017500000000000012130456004013306 500000000000000smalltalk-3.2.5/libffi/src/m32r/ffitarget.h0000644000175000017500000000340012130343734015354 00000000000000/* -----------------------------------------------------------------*-C-*- ffitarget.h - Copyright (c) 2004 Renesas Technology. Target configuration macros for M32R. Permission is hereby granted, free of charge, to any person obtaining a copy of this software and associated documentation files (the ``Software''), to deal in the Software without restriction, including without limitation the rights to use, copy, modify, merge, publish, distribute, sublicense, and/or sell copies of the Software, and to permit persons to whom the Software is furnished to do so, subject to the following conditions: The above copyright notice and this permission notice shall be included in all copies or substantial portions of the Software. THE SOFTWARE IS PROVIDED ``AS IS'', WITHOUT WARRANTY OF ANY KIND, EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL RENESAS TECHNOLOGY BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. ----------------------------------------------------------------------- */ #ifndef LIBFFI_TARGET_H #define LIBFFI_TARGET_H /* ---- Generic type definitions ----------------------------------------- */ #ifndef LIBFFI_ASM typedef unsigned long ffi_arg; typedef signed long ffi_sarg; typedef enum ffi_abi { FFI_FIRST_ABI = 0, FFI_SYSV, FFI_DEFAULT_ABI = FFI_SYSV, FFI_LAST_ABI = FFI_DEFAULT_ABI + 1 } ffi_abi; #endif #define FFI_CLOSURES 0 #define FFI_TRAMPOLINE_SIZE 24 #define FFI_NATIVE_RAW_API 0 #endif smalltalk-3.2.5/libffi/src/m32r/sysv.S0000644000175000017500000000575212130343734014374 00000000000000/* ----------------------------------------------------------------------- sysv.S - Copyright (c) 2004 Renesas Technology M32R Foreign Function Interface Permission is hereby granted, free of charge, to any person obtaining a copy of this software and associated documentation files (the ``Software''), to deal in the Software without restriction, including without limitation the rights to use, copy, modify, merge, publish, distribute, sublicense, and/or sell copies of the Software, and to permit persons to whom the Software is furnished to do so, subject to the following conditions: The above copyright notice and this permission notice shall be included in all copies or substantial portions of the Software. THE SOFTWARE IS PROVIDED ``AS IS'', WITHOUT WARRANTY OF ANY KIND, EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL RENESAS TECHNOLOGY BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. ----------------------------------------------------------------------- */ #define LIBFFI_ASM #include #include #ifdef HAVE_MACHINE_ASM_H #include #else /* XXX these lose for some platforms, I'm sure. */ #define CNAME(x) x #define ENTRY(x) .globl CNAME(x)! .type CNAME(x),%function! CNAME(x): #endif .text /* R0: ffi_prep_args */ /* R1: &ecif */ /* R2: cif->bytes */ /* R3: fig->flags */ /* sp+0: ecif.rvalue */ /* sp+4: fn */ /* This assumes we are using gas. */ ENTRY(ffi_call_SYSV) /* Save registers. */ push fp push lr push r3 push r2 push r1 push r0 mv fp, sp /* Make room for all of the new args. */ sub sp, r2 /* Place all of the ffi_prep_args in position. */ mv lr, r0 mv r0, sp /* R1 already set. */ /* And call. */ jl lr /* Move first 4 parameters in registers... */ ld r0, @(0,sp) ld r1, @(4,sp) ld r2, @(8,sp) ld r3, @(12,sp) /* ...and adjust the stack. */ ld lr, @(8,fp) cmpi lr, #16 bc adjust_stack ldi lr, #16 adjust_stack: add sp, lr /* Call the function. */ ld lr, @(28,fp) jl lr /* Remove the space we pushed for the args. */ mv sp, fp /* Load R2 with the pointer to storage for the return value. */ ld r2, @(24,sp) /* Load R3 with the return type code. */ ld r3, @(12,sp) /* If the return value pointer is NULL, assume no return value. */ beqz r2, epilogue /* Return INT. */ ldi r4, #FFI_TYPE_INT bne r3, r4, return_double st r0, @r2 bra epilogue return_double: /* Return DOUBLE or LONGDOUBLE. */ ldi r4, #FFI_TYPE_DOUBLE bne r3, r4, epilogue st r0, @r2 st r1, @(4,r2) epilogue: pop r0 pop r1 pop r2 pop r3 pop lr pop fp jmp lr .ffi_call_SYSV_end: .size CNAME(ffi_call_SYSV),.ffi_call_SYSV_end-CNAME(ffi_call_SYSV) smalltalk-3.2.5/libffi/src/m32r/ffi.c0000644000175000017500000001271512130343734014151 00000000000000/* ----------------------------------------------------------------------- ffi.c - Copyright (c) 2004 Renesas Technology Copyright (c) 2008 Red Hat, Inc. M32R Foreign Function Interface Permission is hereby granted, free of charge, to any person obtaining a copy of this software and associated documentation files (the ``Software''), to deal in the Software without restriction, including without limitation the rights to use, copy, modify, merge, publish, distribute, sublicense, and/or sell copies of the Software, and to permit persons to whom the Software is furnished to do so, subject to the following conditions: The above copyright notice and this permission notice shall be included in all copies or substantial portions of the Software. THE SOFTWARE IS PROVIDED ``AS IS'', WITHOUT WARRANTY OF ANY KIND, EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL RENESAS TECHNOLOGY BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. ----------------------------------------------------------------------- */ #include #include #include /* ffi_prep_args is called by the assembly routine once stack space has been allocated for the function's arguments. */ void ffi_prep_args(char *stack, extended_cif *ecif) { unsigned int i; int tmp; unsigned int avn; void **p_argv; char *argp; ffi_type **p_arg; tmp = 0; argp = stack; if (ecif->cif->rtype->type == FFI_TYPE_STRUCT && ecif->cif->rtype->size > 8) { *(void **) argp = ecif->rvalue; argp += 4; } avn = ecif->cif->nargs; p_argv = ecif->avalue; for (i = ecif->cif->nargs, p_arg = ecif->cif->arg_types; (i != 0) && (avn != 0); i--, p_arg++) { size_t z; /* Align if necessary. */ if (((*p_arg)->alignment - 1) & (unsigned) argp) argp = (char *) ALIGN (argp, (*p_arg)->alignment); if (avn != 0) { avn--; z = (*p_arg)->size; if (z < sizeof (int)) { z = sizeof (int); switch ((*p_arg)->type) { case FFI_TYPE_SINT8: *(signed int *) argp = (signed int)*(SINT8 *)(* p_argv); break; case FFI_TYPE_UINT8: *(unsigned int *) argp = (unsigned int)*(UINT8 *)(* p_argv); break; case FFI_TYPE_SINT16: *(signed int *) argp = (signed int)*(SINT16 *)(* p_argv); break; case FFI_TYPE_UINT16: *(unsigned int *) argp = (unsigned int)*(UINT16 *)(* p_argv); break; case FFI_TYPE_STRUCT: z = (*p_arg)->size; if ((*p_arg)->alignment != 1) memcpy (argp, *p_argv, z); else memcpy (argp + 4 - z, *p_argv, z); z = sizeof (int); break; default: FFI_ASSERT(0); } } else if (z == sizeof (int)) { *(unsigned int *) argp = (unsigned int)*(UINT32 *)(* p_argv); } else { if ((*p_arg)->type == FFI_TYPE_STRUCT) { if (z > 8) { *(unsigned int *) argp = (unsigned int)(void *)(* p_argv); z = sizeof(void *); } else { memcpy(argp, *p_argv, z); z = 8; } } else { /* Double or long long 64bit. */ memcpy (argp, *p_argv, z); } } p_argv++; argp += z; } } return; } /* Perform machine dependent cif processing. */ ffi_status ffi_prep_cif_machdep(ffi_cif *cif) { /* Set the return type flag. */ switch (cif->rtype->type) { case FFI_TYPE_VOID: cif->flags = (unsigned) cif->rtype->type; break; case FFI_TYPE_STRUCT: if (cif->rtype->size <= 4) cif->flags = FFI_TYPE_INT; else if (cif->rtype->size <= 8) cif->flags = FFI_TYPE_DOUBLE; else cif->flags = (unsigned) cif->rtype->type; break; case FFI_TYPE_SINT64: case FFI_TYPE_UINT64: case FFI_TYPE_DOUBLE: cif->flags = FFI_TYPE_DOUBLE; break; case FFI_TYPE_FLOAT: default: cif->flags = FFI_TYPE_INT; break; } return FFI_OK; } extern void ffi_call_SYSV(void (*)(char *, extended_cif *), extended_cif *, unsigned, unsigned, unsigned *, void (*fn)(void)); void ffi_call(ffi_cif *cif, void (*fn)(void), void *rvalue, void **avalue) { extended_cif ecif; ecif.cif = cif; ecif.avalue = avalue; /* If the return value is a struct and we don't have a return value address then we need to make one. */ if ((rvalue == NULL) && (cif->rtype->type == FFI_TYPE_STRUCT)) { ecif.rvalue = alloca (cif->rtype->size); } else ecif.rvalue = rvalue; switch (cif->abi) { case FFI_SYSV: ffi_call_SYSV(ffi_prep_args, &ecif, cif->bytes, cif->flags, ecif.rvalue, fn); if (cif->rtype->type == FFI_TYPE_STRUCT) { int size = cif->rtype->size; int align = cif->rtype->alignment; if (size < 4) { if (align == 1) *(unsigned long *)(ecif.rvalue) <<= (4 - size) * 8; } else if (4 < size && size < 8) { if (align == 1) { memcpy (ecif.rvalue, ecif.rvalue + 8-size, size); } else if (align == 2) { if (size & 1) size += 1; if (size != 8) memcpy (ecif.rvalue, ecif.rvalue + 8-size, size); } } } break; default: FFI_ASSERT(0); break; } } smalltalk-3.2.5/libffi/src/alpha/0000755000175000017500000000000012130456004013610 500000000000000smalltalk-3.2.5/libffi/src/alpha/ffitarget.h0000644000175000017500000000335312130343734015665 00000000000000/* -----------------------------------------------------------------*-C-*- ffitarget.h - Copyright (c) 1996-2003 Red Hat, Inc. Target configuration macros for Alpha. Permission is hereby granted, free of charge, to any person obtaining a copy of this software and associated documentation files (the ``Software''), to deal in the Software without restriction, including without limitation the rights to use, copy, modify, merge, publish, distribute, sublicense, and/or sell copies of the Software, and to permit persons to whom the Software is furnished to do so, subject to the following conditions: The above copyright notice and this permission notice shall be included in all copies or substantial portions of the Software. THE SOFTWARE IS PROVIDED ``AS IS'', WITHOUT WARRANTY OF ANY KIND, EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. ----------------------------------------------------------------------- */ #ifndef LIBFFI_TARGET_H #define LIBFFI_TARGET_H #ifndef LIBFFI_ASM typedef unsigned long ffi_arg; typedef signed long ffi_sarg; typedef enum ffi_abi { FFI_FIRST_ABI = 0, FFI_OSF, FFI_LAST_ABI, FFI_DEFAULT_ABI = FFI_OSF } ffi_abi; #endif /* ---- Definitions for closures ----------------------------------------- */ #define FFI_CLOSURES 1 #define FFI_TRAMPOLINE_SIZE 24 #define FFI_NATIVE_RAW_API 0 #endif smalltalk-3.2.5/libffi/src/alpha/osf.S0000644000175000017500000001716012130343734014455 00000000000000/* ----------------------------------------------------------------------- osf.S - Copyright (c) 1998, 2001, 2007, 2008 Red Hat Alpha/OSF Foreign Function Interface Permission is hereby granted, free of charge, to any person obtaining a copy of this software and associated documentation files (the ``Software''), to deal in the Software without restriction, including without limitation the rights to use, copy, modify, merge, publish, distribute, sublicense, and/or sell copies of the Software, and to permit persons to whom the Software is furnished to do so, subject to the following conditions: The above copyright notice and this permission notice shall be included in all copies or substantial portions of the Software. THE SOFTWARE IS PROVIDED ``AS IS'', WITHOUT WARRANTY OF ANY KIND, EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. ----------------------------------------------------------------------- */ #define LIBFFI_ASM #include #include .arch ev6 .text /* ffi_call_osf (void *args, unsigned long bytes, unsigned flags, void *raddr, void (*fnaddr)(void)); Bit o trickiness here -- ARGS+BYTES is the base of the stack frame for this function. This has been allocated by ffi_call. We also deallocate some of the stack that has been alloca'd. */ .align 3 .globl ffi_call_osf .ent ffi_call_osf FFI_HIDDEN(ffi_call_osf) ffi_call_osf: .frame $15, 32, $26, 0 .mask 0x4008000, -32 $LFB1: addq $16,$17,$1 mov $16, $30 stq $26, 0($1) stq $15, 8($1) stq $18, 16($1) mov $1, $15 $LCFI1: .prologue 0 stq $19, 24($1) mov $20, $27 # Load up all of the (potential) argument registers. ldq $16, 0($30) ldt $f16, 0($30) ldt $f17, 8($30) ldq $17, 8($30) ldt $f18, 16($30) ldq $18, 16($30) ldt $f19, 24($30) ldq $19, 24($30) ldt $f20, 32($30) ldq $20, 32($30) ldt $f21, 40($30) ldq $21, 40($30) # Deallocate the register argument area. lda $30, 48($30) jsr $26, ($27), 0 ldgp $29, 0($26) # If the return value pointer is NULL, assume no return value. ldq $19, 24($15) ldq $18, 16($15) ldq $26, 0($15) $LCFI2: beq $19, $noretval # Store the return value out in the proper type. cmpeq $18, FFI_TYPE_INT, $1 bne $1, $retint cmpeq $18, FFI_TYPE_FLOAT, $2 bne $2, $retfloat cmpeq $18, FFI_TYPE_DOUBLE, $3 bne $3, $retdouble .align 3 $noretval: ldq $15, 8($15) ret .align 4 $retint: stq $0, 0($19) nop ldq $15, 8($15) ret .align 4 $retfloat: sts $f0, 0($19) nop ldq $15, 8($15) ret .align 4 $retdouble: stt $f0, 0($19) nop ldq $15, 8($15) ret $LFE1: .end ffi_call_osf /* ffi_closure_osf(...) Receives the closure argument in $1. */ .align 3 .globl ffi_closure_osf .ent ffi_closure_osf FFI_HIDDEN(ffi_closure_osf) ffi_closure_osf: .frame $30, 16*8, $26, 0 .mask 0x4000000, -16*8 $LFB2: ldgp $29, 0($27) subq $30, 16*8, $30 $LCFI5: stq $26, 0($30) $LCFI6: .prologue 1 # Store all of the potential argument registers in va_list format. stt $f16, 4*8($30) stt $f17, 5*8($30) stt $f18, 6*8($30) stt $f19, 7*8($30) stt $f20, 8*8($30) stt $f21, 9*8($30) stq $16, 10*8($30) stq $17, 11*8($30) stq $18, 12*8($30) stq $19, 13*8($30) stq $20, 14*8($30) stq $21, 15*8($30) # Call ffi_closure_osf_inner to do the bulk of the work. mov $1, $16 lda $17, 2*8($30) lda $18, 10*8($30) jsr $26, ffi_closure_osf_inner ldgp $29, 0($26) ldq $26, 0($30) # Load up the return value in the proper type. lda $1, $load_table s4addq $0, $1, $1 ldl $1, 0($1) addq $1, $29, $1 jmp $31, ($1), $load_32 .align 4 $load_none: addq $30, 16*8, $30 ret .align 4 $load_float: lds $f0, 16($30) nop addq $30, 16*8, $30 ret .align 4 $load_double: ldt $f0, 16($30) nop addq $30, 16*8, $30 ret .align 4 $load_u8: #ifdef __alpha_bwx__ ldbu $0, 16($30) nop #else ldq $0, 16($30) and $0, 255, $0 #endif addq $30, 16*8, $30 ret .align 4 $load_s8: #ifdef __alpha_bwx__ ldbu $0, 16($30) sextb $0, $0 #else ldq $0, 16($30) sll $0, 56, $0 sra $0, 56, $0 #endif addq $30, 16*8, $30 ret .align 4 $load_u16: #ifdef __alpha_bwx__ ldwu $0, 16($30) nop #else ldq $0, 16($30) zapnot $0, 3, $0 #endif addq $30, 16*8, $30 ret .align 4 $load_s16: #ifdef __alpha_bwx__ ldwu $0, 16($30) sextw $0, $0 #else ldq $0, 16($30) sll $0, 48, $0 sra $0, 48, $0 #endif addq $30, 16*8, $30 ret .align 4 $load_32: ldl $0, 16($30) nop addq $30, 16*8, $30 ret .align 4 $load_64: ldq $0, 16($30) nop addq $30, 16*8, $30 ret $LFE2: .end ffi_closure_osf #ifdef __ELF__ .section .rodata #else .rdata #endif $load_table: .gprel32 $load_none # FFI_TYPE_VOID .gprel32 $load_32 # FFI_TYPE_INT .gprel32 $load_float # FFI_TYPE_FLOAT .gprel32 $load_double # FFI_TYPE_DOUBLE .gprel32 $load_none # FFI_TYPE_LONGDOUBLE .gprel32 $load_u8 # FFI_TYPE_UINT8 .gprel32 $load_s8 # FFI_TYPE_SINT8 .gprel32 $load_u16 # FFI_TYPE_UINT16 .gprel32 $load_s16 # FFI_TYPE_SINT16 .gprel32 $load_32 # FFI_TYPE_UINT32 .gprel32 $load_32 # FFI_TYPE_SINT32 .gprel32 $load_64 # FFI_TYPE_UINT64 .gprel32 $load_64 # FFI_TYPE_SINT64 .gprel32 $load_none # FFI_TYPE_STRUCT .gprel32 $load_64 # FFI_TYPE_POINTER /* Assert that the table above is in sync with ffi.h. */ #if FFI_TYPE_FLOAT != 2 \ || FFI_TYPE_DOUBLE != 3 \ || FFI_TYPE_UINT8 != 5 \ || FFI_TYPE_SINT8 != 6 \ || FFI_TYPE_UINT16 != 7 \ || FFI_TYPE_SINT16 != 8 \ || FFI_TYPE_UINT32 != 9 \ || FFI_TYPE_SINT32 != 10 \ || FFI_TYPE_UINT64 != 11 \ || FFI_TYPE_SINT64 != 12 \ || FFI_TYPE_STRUCT != 13 \ || FFI_TYPE_POINTER != 14 \ || FFI_TYPE_LAST != 14 #error "osf.S out of sync with ffi.h" #endif #ifdef __ELF__ .section .eh_frame,EH_FRAME_FLAGS,@progbits __FRAME_BEGIN__: .4byte $LECIE1-$LSCIE1 # Length of Common Information Entry $LSCIE1: .4byte 0x0 # CIE Identifier Tag .byte 0x1 # CIE Version .ascii "zR\0" # CIE Augmentation .byte 0x1 # uleb128 0x1; CIE Code Alignment Factor .byte 0x78 # sleb128 -8; CIE Data Alignment Factor .byte 26 # CIE RA Column .byte 0x1 # uleb128 0x1; Augmentation size .byte 0x1b # FDE Encoding (pcrel sdata4) .byte 0xc # DW_CFA_def_cfa .byte 30 # uleb128 column 30 .byte 0 # uleb128 offset 0 .align 3 $LECIE1: $LSFDE1: .4byte $LEFDE1-$LASFDE1 # FDE Length $LASFDE1: .4byte $LASFDE1-__FRAME_BEGIN__ # FDE CIE offset .4byte $LFB1-. # FDE initial location .4byte $LFE1-$LFB1 # FDE address range .byte 0x0 # uleb128 0x0; Augmentation size .byte 0x4 # DW_CFA_advance_loc4 .4byte $LCFI1-$LFB1 .byte 0x9a # DW_CFA_offset, column 26 .byte 4 # uleb128 4*-8 .byte 0x8f # DW_CFA_offset, column 15 .byte 0x3 # uleb128 3*-8 .byte 0xc # DW_CFA_def_cfa .byte 15 # uleb128 column 15 .byte 32 # uleb128 offset 32 .byte 0x4 # DW_CFA_advance_loc4 .4byte $LCFI2-$LCFI1 .byte 0xda # DW_CFA_restore, column 26 .align 3 $LEFDE1: $LSFDE3: .4byte $LEFDE3-$LASFDE3 # FDE Length $LASFDE3: .4byte $LASFDE3-__FRAME_BEGIN__ # FDE CIE offset .4byte $LFB2-. # FDE initial location .4byte $LFE2-$LFB2 # FDE address range .byte 0x0 # uleb128 0x0; Augmentation size .byte 0x4 # DW_CFA_advance_loc4 .4byte $LCFI5-$LFB2 .byte 0xe # DW_CFA_def_cfa_offset .byte 0x80,0x1 # uleb128 128 .byte 0x4 # DW_CFA_advance_loc4 .4byte $LCFI6-$LCFI5 .byte 0x9a # DW_CFA_offset, column 26 .byte 16 # uleb128 offset 16*-8 .align 3 $LEFDE3: #ifdef __linux__ .section .note.GNU-stack,"",@progbits #endif #endif smalltalk-3.2.5/libffi/src/alpha/ffi.c0000644000175000017500000001632312130343734014452 00000000000000/* ----------------------------------------------------------------------- ffi.c - Copyright (c) 1998, 2001, 2007, 2008 Red Hat, Inc. Alpha Foreign Function Interface Permission is hereby granted, free of charge, to any person obtaining a copy of this software and associated documentation files (the ``Software''), to deal in the Software without restriction, including without limitation the rights to use, copy, modify, merge, publish, distribute, sublicense, and/or sell copies of the Software, and to permit persons to whom the Software is furnished to do so, subject to the following conditions: The above copyright notice and this permission notice shall be included in all copies or substantial portions of the Software. THE SOFTWARE IS PROVIDED ``AS IS'', WITHOUT WARRANTY OF ANY KIND, EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. ----------------------------------------------------------------------- */ #include #include #include /* Force FFI_TYPE_LONGDOUBLE to be different than FFI_TYPE_DOUBLE; all further uses in this file will refer to the 128-bit type. */ #if defined(__LONG_DOUBLE_128__) # if FFI_TYPE_LONGDOUBLE != 4 # error FFI_TYPE_LONGDOUBLE out of date # endif #else # undef FFI_TYPE_LONGDOUBLE # define FFI_TYPE_LONGDOUBLE 4 #endif extern void ffi_call_osf(void *, unsigned long, unsigned, void *, void (*)(void)) FFI_HIDDEN; extern void ffi_closure_osf(void) FFI_HIDDEN; ffi_status ffi_prep_cif_machdep(ffi_cif *cif) { /* Adjust cif->bytes to represent a minimum 6 words for the temporary register argument loading area. */ if (cif->bytes < 6*FFI_SIZEOF_ARG) cif->bytes = 6*FFI_SIZEOF_ARG; /* Set the return type flag */ switch (cif->rtype->type) { case FFI_TYPE_STRUCT: case FFI_TYPE_FLOAT: case FFI_TYPE_DOUBLE: cif->flags = cif->rtype->type; break; case FFI_TYPE_LONGDOUBLE: /* 128-bit long double is returned in memory, like a struct. */ cif->flags = FFI_TYPE_STRUCT; break; default: cif->flags = FFI_TYPE_INT; break; } return FFI_OK; } void ffi_call(ffi_cif *cif, void (*fn)(void), void *rvalue, void **avalue) { unsigned long *stack, *argp; long i, avn; ffi_type **arg_types; /* If the return value is a struct and we don't have a return value address then we need to make one. */ if (rvalue == NULL && cif->flags == FFI_TYPE_STRUCT) rvalue = alloca(cif->rtype->size); /* Allocate the space for the arguments, plus 4 words of temp space for ffi_call_osf. */ argp = stack = alloca(cif->bytes + 4*FFI_SIZEOF_ARG); if (cif->flags == FFI_TYPE_STRUCT) *(void **) argp++ = rvalue; i = 0; avn = cif->nargs; arg_types = cif->arg_types; while (i < avn) { size_t size = (*arg_types)->size; switch ((*arg_types)->type) { case FFI_TYPE_SINT8: *(SINT64 *) argp = *(SINT8 *)(* avalue); break; case FFI_TYPE_UINT8: *(SINT64 *) argp = *(UINT8 *)(* avalue); break; case FFI_TYPE_SINT16: *(SINT64 *) argp = *(SINT16 *)(* avalue); break; case FFI_TYPE_UINT16: *(SINT64 *) argp = *(UINT16 *)(* avalue); break; case FFI_TYPE_SINT32: case FFI_TYPE_UINT32: /* Note that unsigned 32-bit quantities are sign extended. */ *(SINT64 *) argp = *(SINT32 *)(* avalue); break; case FFI_TYPE_SINT64: case FFI_TYPE_UINT64: case FFI_TYPE_POINTER: *(UINT64 *) argp = *(UINT64 *)(* avalue); break; case FFI_TYPE_FLOAT: if (argp - stack < 6) { /* Note the conversion -- all the fp regs are loaded as doubles. The in-register format is the same. */ *(double *) argp = *(float *)(* avalue); } else *(float *) argp = *(float *)(* avalue); break; case FFI_TYPE_DOUBLE: *(double *) argp = *(double *)(* avalue); break; case FFI_TYPE_LONGDOUBLE: /* 128-bit long double is passed by reference. */ *(long double **) argp = (long double *)(* avalue); size = sizeof (long double *); break; case FFI_TYPE_STRUCT: memcpy(argp, *avalue, (*arg_types)->size); break; default: FFI_ASSERT(0); } argp += ALIGN(size, FFI_SIZEOF_ARG) / FFI_SIZEOF_ARG; i++, arg_types++, avalue++; } ffi_call_osf(stack, cif->bytes, cif->flags, rvalue, fn); } ffi_status ffi_prep_closure_loc (ffi_closure* closure, ffi_cif* cif, void (*fun)(ffi_cif*, void*, void**, void*), void *user_data, void *codeloc) { unsigned int *tramp; tramp = (unsigned int *) &closure->tramp[0]; tramp[0] = 0x47fb0401; /* mov $27,$1 */ tramp[1] = 0xa77b0010; /* ldq $27,16($27) */ tramp[2] = 0x6bfb0000; /* jmp $31,($27),0 */ tramp[3] = 0x47ff041f; /* nop */ *(void **) &tramp[4] = ffi_closure_osf; closure->cif = cif; closure->fun = fun; closure->user_data = user_data; /* Flush the Icache. Tru64 UNIX as doesn't understand the imb mnemonic, so use call_pal instead, since both Compaq as and gas can handle it. 0x86 is PAL_imb in Tru64 UNIX . */ asm volatile ("call_pal 0x86" : : : "memory"); return FFI_OK; } long FFI_HIDDEN ffi_closure_osf_inner(ffi_closure *closure, void *rvalue, unsigned long *argp) { ffi_cif *cif; void **avalue; ffi_type **arg_types; long i, avn, argn; cif = closure->cif; avalue = alloca(cif->nargs * sizeof(void *)); argn = 0; /* Copy the caller's structure return address to that the closure returns the data directly to the caller. */ if (cif->flags == FFI_TYPE_STRUCT) { rvalue = (void *) argp[0]; argn = 1; } i = 0; avn = cif->nargs; arg_types = cif->arg_types; /* Grab the addresses of the arguments from the stack frame. */ while (i < avn) { size_t size = arg_types[i]->size; switch (arg_types[i]->type) { case FFI_TYPE_SINT8: case FFI_TYPE_UINT8: case FFI_TYPE_SINT16: case FFI_TYPE_UINT16: case FFI_TYPE_SINT32: case FFI_TYPE_UINT32: case FFI_TYPE_SINT64: case FFI_TYPE_UINT64: case FFI_TYPE_POINTER: case FFI_TYPE_STRUCT: avalue[i] = &argp[argn]; break; case FFI_TYPE_FLOAT: if (argn < 6) { /* Floats coming from registers need conversion from double back to float format. */ *(float *)&argp[argn - 6] = *(double *)&argp[argn - 6]; avalue[i] = &argp[argn - 6]; } else avalue[i] = &argp[argn]; break; case FFI_TYPE_DOUBLE: avalue[i] = &argp[argn - (argn < 6 ? 6 : 0)]; break; case FFI_TYPE_LONGDOUBLE: /* 128-bit long double is passed by reference. */ avalue[i] = (long double *) argp[argn]; size = sizeof (long double *); break; default: abort (); } argn += ALIGN(size, FFI_SIZEOF_ARG) / FFI_SIZEOF_ARG; i++; } /* Invoke the closure. */ closure->fun (cif, rvalue, avalue, closure->user_data); /* Tell ffi_closure_osf how to perform return type promotions. */ return cif->rtype->type; } smalltalk-3.2.5/libffi/src/s390/0000755000175000017500000000000012130456004013221 500000000000000smalltalk-3.2.5/libffi/src/s390/ffitarget.h0000644000175000017500000000371712130343734015302 00000000000000/* -----------------------------------------------------------------*-C-*- ffitarget.h - Copyright (c) 1996-2003 Red Hat, Inc. Target configuration macros for S390. Permission is hereby granted, free of charge, to any person obtaining a copy of this software and associated documentation files (the ``Software''), to deal in the Software without restriction, including without limitation the rights to use, copy, modify, merge, publish, distribute, sublicense, and/or sell copies of the Software, and to permit persons to whom the Software is furnished to do so, subject to the following conditions: The above copyright notice and this permission notice shall be included in all copies or substantial portions of the Software. THE SOFTWARE IS PROVIDED ``AS IS'', WITHOUT WARRANTY OF ANY KIND, EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. ----------------------------------------------------------------------- */ #ifndef LIBFFI_TARGET_H #define LIBFFI_TARGET_H #if defined (__s390x__) #ifndef S390X #define S390X #endif #endif /* ---- System specific configurations ----------------------------------- */ #ifndef LIBFFI_ASM typedef unsigned long ffi_arg; typedef signed long ffi_sarg; typedef enum ffi_abi { FFI_FIRST_ABI = 0, FFI_SYSV, FFI_DEFAULT_ABI = FFI_SYSV, FFI_LAST_ABI = FFI_DEFAULT_ABI + 1 } ffi_abi; #endif /* ---- Definitions for closures ----------------------------------------- */ #define FFI_CLOSURES 1 #ifdef S390X #define FFI_TRAMPOLINE_SIZE 32 #else #define FFI_TRAMPOLINE_SIZE 16 #endif #define FFI_NATIVE_RAW_API 0 #endif smalltalk-3.2.5/libffi/src/s390/sysv.S0000644000175000017500000002504112130343734014300 00000000000000/* ----------------------------------------------------------------------- sysv.S - Copyright (c) 2000 Software AG Copyright (c) 2008 Red Hat, Inc. S390 Foreign Function Interface Permission is hereby granted, free of charge, to any person obtaining a copy of this software and associated documentation files (the ``Software''), to deal in the Software without restriction, including without limitation the rights to use, copy, modify, merge, publish, distribute, sublicense, and/or sell copies of the Software, and to permit persons to whom the Software is furnished to do so, subject to the following conditions: The above copyright notice and this permission notice shall be included in all copies or substantial portions of the Software. THE SOFTWARE IS PROVIDED ``AS IS'', WITHOUT WARRANTY OF ANY KIND, EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. ----------------------------------------------------------------------- */ #define LIBFFI_ASM #include #include #ifndef __s390x__ .text # r2: cif->bytes # r3: &ecif # r4: ffi_prep_args # r5: ret_type # r6: ecif.rvalue # ov: fn # This assumes we are using gas. .globl ffi_call_SYSV .type ffi_call_SYSV,%function ffi_call_SYSV: .LFB1: stm %r6,%r15,24(%r15) # Save registers .LCFI0: basr %r13,0 # Set up base register .Lbase: lr %r11,%r15 # Set up frame pointer .LCFI1: sr %r15,%r2 ahi %r15,-96-48 # Allocate stack lr %r8,%r6 # Save ecif.rvalue sr %r9,%r9 ic %r9,.Ltable-.Lbase(%r13,%r5) # Load epilog address l %r7,96(%r11) # Load function address st %r11,0(%r15) # Set up back chain ahi %r11,-48 # Register save area .LCFI2: la %r2,96(%r15) # Save area # r3 already holds &ecif basr %r14,%r4 # Call ffi_prep_args lm %r2,%r6,0(%r11) # Load arguments ld %f0,32(%r11) ld %f2,40(%r11) la %r14,0(%r13,%r9) # Set return address br %r7 # ... and call function .LretNone: # Return void l %r4,48+56(%r11) lm %r6,%r15,48+24(%r11) br %r4 .LretFloat: l %r4,48+56(%r11) ste %f0,0(%r8) # Return float lm %r6,%r15,48+24(%r11) br %r4 .LretDouble: l %r4,48+56(%r11) std %f0,0(%r8) # Return double lm %r6,%r15,48+24(%r11) br %r4 .LretInt32: l %r4,48+56(%r11) st %r2,0(%r8) # Return int lm %r6,%r15,48+24(%r11) br %r4 .LretInt64: l %r4,48+56(%r11) stm %r2,%r3,0(%r8) # Return long long lm %r6,%r15,48+24(%r11) br %r4 .Ltable: .byte .LretNone-.Lbase # FFI390_RET_VOID .byte .LretNone-.Lbase # FFI390_RET_STRUCT .byte .LretFloat-.Lbase # FFI390_RET_FLOAT .byte .LretDouble-.Lbase # FFI390_RET_DOUBLE .byte .LretInt32-.Lbase # FFI390_RET_INT32 .byte .LretInt64-.Lbase # FFI390_RET_INT64 .LFE1: .ffi_call_SYSV_end: .size ffi_call_SYSV,.ffi_call_SYSV_end-ffi_call_SYSV .globl ffi_closure_SYSV .type ffi_closure_SYSV,%function ffi_closure_SYSV: .LFB2: stm %r12,%r15,48(%r15) # Save registers .LCFI10: basr %r13,0 # Set up base register .Lcbase: stm %r2,%r6,8(%r15) # Save arguments std %f0,64(%r15) std %f2,72(%r15) lr %r1,%r15 # Set up stack frame ahi %r15,-96 .LCFI11: l %r12,.Lchelper-.Lcbase(%r13) # Get helper function lr %r2,%r0 # Closure la %r3,8(%r1) # GPRs la %r4,64(%r1) # FPRs la %r5,96(%r1) # Overflow st %r1,0(%r15) # Set up back chain bas %r14,0(%r12,%r13) # Call helper l %r4,96+56(%r15) ld %f0,96+64(%r15) # Load return registers lm %r2,%r3,96+8(%r15) lm %r12,%r15,96+48(%r15) br %r4 .align 4 .Lchelper: .long ffi_closure_helper_SYSV-.Lcbase .LFE2: .ffi_closure_SYSV_end: .size ffi_closure_SYSV,.ffi_closure_SYSV_end-ffi_closure_SYSV .section .eh_frame,EH_FRAME_FLAGS,@progbits .Lframe1: .4byte .LECIE1-.LSCIE1 # Length of Common Information Entry .LSCIE1: .4byte 0x0 # CIE Identifier Tag .byte 0x1 # CIE Version .ascii "zR\0" # CIE Augmentation .uleb128 0x1 # CIE Code Alignment Factor .sleb128 -4 # CIE Data Alignment Factor .byte 0xe # CIE RA Column .uleb128 0x1 # Augmentation size .byte 0x1b # FDE Encoding (pcrel sdata4) .byte 0xc # DW_CFA_def_cfa .uleb128 0xf .uleb128 0x60 .align 4 .LECIE1: .LSFDE1: .4byte .LEFDE1-.LASFDE1 # FDE Length .LASFDE1: .4byte .LASFDE1-.Lframe1 # FDE CIE offset .4byte .LFB1-. # FDE initial location .4byte .LFE1-.LFB1 # FDE address range .uleb128 0x0 # Augmentation size .byte 0x4 # DW_CFA_advance_loc4 .4byte .LCFI0-.LFB1 .byte 0x8f # DW_CFA_offset, column 0xf .uleb128 0x9 .byte 0x8e # DW_CFA_offset, column 0xe .uleb128 0xa .byte 0x8d # DW_CFA_offset, column 0xd .uleb128 0xb .byte 0x8c # DW_CFA_offset, column 0xc .uleb128 0xc .byte 0x8b # DW_CFA_offset, column 0xb .uleb128 0xd .byte 0x8a # DW_CFA_offset, column 0xa .uleb128 0xe .byte 0x89 # DW_CFA_offset, column 0x9 .uleb128 0xf .byte 0x88 # DW_CFA_offset, column 0x8 .uleb128 0x10 .byte 0x87 # DW_CFA_offset, column 0x7 .uleb128 0x11 .byte 0x86 # DW_CFA_offset, column 0x6 .uleb128 0x12 .byte 0x4 # DW_CFA_advance_loc4 .4byte .LCFI1-.LCFI0 .byte 0xd # DW_CFA_def_cfa_register .uleb128 0xb .byte 0x4 # DW_CFA_advance_loc4 .4byte .LCFI2-.LCFI1 .byte 0xe # DW_CFA_def_cfa_offset .uleb128 0x90 .align 4 .LEFDE1: .LSFDE2: .4byte .LEFDE2-.LASFDE2 # FDE Length .LASFDE2: .4byte .LASFDE2-.Lframe1 # FDE CIE offset .4byte .LFB2-. # FDE initial location .4byte .LFE2-.LFB2 # FDE address range .uleb128 0x0 # Augmentation size .byte 0x4 # DW_CFA_advance_loc4 .4byte .LCFI10-.LFB2 .byte 0x8f # DW_CFA_offset, column 0xf .uleb128 0x9 .byte 0x8e # DW_CFA_offset, column 0xe .uleb128 0xa .byte 0x8d # DW_CFA_offset, column 0xd .uleb128 0xb .byte 0x8c # DW_CFA_offset, column 0xc .uleb128 0xc .byte 0x4 # DW_CFA_advance_loc4 .4byte .LCFI11-.LCFI10 .byte 0xe # DW_CFA_def_cfa_offset .uleb128 0xc0 .align 4 .LEFDE2: #else .text # r2: cif->bytes # r3: &ecif # r4: ffi_prep_args # r5: ret_type # r6: ecif.rvalue # ov: fn # This assumes we are using gas. .globl ffi_call_SYSV .type ffi_call_SYSV,%function ffi_call_SYSV: .LFB1: stmg %r6,%r15,48(%r15) # Save registers .LCFI0: larl %r13,.Lbase # Set up base register lgr %r11,%r15 # Set up frame pointer .LCFI1: sgr %r15,%r2 aghi %r15,-160-80 # Allocate stack lgr %r8,%r6 # Save ecif.rvalue llgc %r9,.Ltable-.Lbase(%r13,%r5) # Load epilog address lg %r7,160(%r11) # Load function address stg %r11,0(%r15) # Set up back chain aghi %r11,-80 # Register save area .LCFI2: la %r2,160(%r15) # Save area # r3 already holds &ecif basr %r14,%r4 # Call ffi_prep_args lmg %r2,%r6,0(%r11) # Load arguments ld %f0,48(%r11) ld %f2,56(%r11) ld %f4,64(%r11) ld %f6,72(%r11) la %r14,0(%r13,%r9) # Set return address br %r7 # ... and call function .Lbase: .LretNone: # Return void lg %r4,80+112(%r11) lmg %r6,%r15,80+48(%r11) br %r4 .LretFloat: lg %r4,80+112(%r11) ste %f0,0(%r8) # Return float lmg %r6,%r15,80+48(%r11) br %r4 .LretDouble: lg %r4,80+112(%r11) std %f0,0(%r8) # Return double lmg %r6,%r15,80+48(%r11) br %r4 .LretInt32: lg %r4,80+112(%r11) st %r2,0(%r8) # Return int lmg %r6,%r15,80+48(%r11) br %r4 .LretInt64: lg %r4,80+112(%r11) stg %r2,0(%r8) # Return long lmg %r6,%r15,80+48(%r11) br %r4 .Ltable: .byte .LretNone-.Lbase # FFI390_RET_VOID .byte .LretNone-.Lbase # FFI390_RET_STRUCT .byte .LretFloat-.Lbase # FFI390_RET_FLOAT .byte .LretDouble-.Lbase # FFI390_RET_DOUBLE .byte .LretInt32-.Lbase # FFI390_RET_INT32 .byte .LretInt64-.Lbase # FFI390_RET_INT64 .LFE1: .ffi_call_SYSV_end: .size ffi_call_SYSV,.ffi_call_SYSV_end-ffi_call_SYSV .globl ffi_closure_SYSV .type ffi_closure_SYSV,%function ffi_closure_SYSV: .LFB2: stmg %r14,%r15,112(%r15) # Save registers .LCFI10: stmg %r2,%r6,16(%r15) # Save arguments std %f0,128(%r15) std %f2,136(%r15) std %f4,144(%r15) std %f6,152(%r15) lgr %r1,%r15 # Set up stack frame aghi %r15,-160 .LCFI11: lgr %r2,%r0 # Closure la %r3,16(%r1) # GPRs la %r4,128(%r1) # FPRs la %r5,160(%r1) # Overflow stg %r1,0(%r15) # Set up back chain brasl %r14,ffi_closure_helper_SYSV # Call helper lg %r14,160+112(%r15) ld %f0,160+128(%r15) # Load return registers lg %r2,160+16(%r15) la %r15,160(%r15) br %r14 .LFE2: .ffi_closure_SYSV_end: .size ffi_closure_SYSV,.ffi_closure_SYSV_end-ffi_closure_SYSV .section .eh_frame,EH_FRAME_FLAGS,@progbits .Lframe1: .4byte .LECIE1-.LSCIE1 # Length of Common Information Entry .LSCIE1: .4byte 0x0 # CIE Identifier Tag .byte 0x1 # CIE Version .ascii "zR\0" # CIE Augmentation .uleb128 0x1 # CIE Code Alignment Factor .sleb128 -8 # CIE Data Alignment Factor .byte 0xe # CIE RA Column .uleb128 0x1 # Augmentation size .byte 0x1b # FDE Encoding (pcrel sdata4) .byte 0xc # DW_CFA_def_cfa .uleb128 0xf .uleb128 0xa0 .align 8 .LECIE1: .LSFDE1: .4byte .LEFDE1-.LASFDE1 # FDE Length .LASFDE1: .4byte .LASFDE1-.Lframe1 # FDE CIE offset .4byte .LFB1-. # FDE initial location .4byte .LFE1-.LFB1 # FDE address range .uleb128 0x0 # Augmentation size .byte 0x4 # DW_CFA_advance_loc4 .4byte .LCFI0-.LFB1 .byte 0x8f # DW_CFA_offset, column 0xf .uleb128 0x5 .byte 0x8e # DW_CFA_offset, column 0xe .uleb128 0x6 .byte 0x8d # DW_CFA_offset, column 0xd .uleb128 0x7 .byte 0x8c # DW_CFA_offset, column 0xc .uleb128 0x8 .byte 0x8b # DW_CFA_offset, column 0xb .uleb128 0x9 .byte 0x8a # DW_CFA_offset, column 0xa .uleb128 0xa .byte 0x89 # DW_CFA_offset, column 0x9 .uleb128 0xb .byte 0x88 # DW_CFA_offset, column 0x8 .uleb128 0xc .byte 0x87 # DW_CFA_offset, column 0x7 .uleb128 0xd .byte 0x86 # DW_CFA_offset, column 0x6 .uleb128 0xe .byte 0x4 # DW_CFA_advance_loc4 .4byte .LCFI1-.LCFI0 .byte 0xd # DW_CFA_def_cfa_register .uleb128 0xb .byte 0x4 # DW_CFA_advance_loc4 .4byte .LCFI2-.LCFI1 .byte 0xe # DW_CFA_def_cfa_offset .uleb128 0xf0 .align 8 .LEFDE1: .LSFDE2: .4byte .LEFDE2-.LASFDE2 # FDE Length .LASFDE2: .4byte .LASFDE2-.Lframe1 # FDE CIE offset .4byte .LFB2-. # FDE initial location .4byte .LFE2-.LFB2 # FDE address range .uleb128 0x0 # Augmentation size .byte 0x4 # DW_CFA_advance_loc4 .4byte .LCFI10-.LFB2 .byte 0x8f # DW_CFA_offset, column 0xf .uleb128 0x5 .byte 0x8e # DW_CFA_offset, column 0xe .uleb128 0x6 .byte 0x4 # DW_CFA_advance_loc4 .4byte .LCFI11-.LCFI10 .byte 0xe # DW_CFA_def_cfa_offset .uleb128 0x140 .align 8 .LEFDE2: #endif #if defined __ELF__ && defined __linux__ .section .note.GNU-stack,"",@progbits #endif smalltalk-3.2.5/libffi/src/s390/ffi.c0000644000175000017500000005456112130343734014071 00000000000000/* ----------------------------------------------------------------------- ffi.c - Copyright (c) 2000, 2007 Software AG Copyright (c) 2008 Red Hat, Inc S390 Foreign Function Interface Permission is hereby granted, free of charge, to any person obtaining a copy of this software and associated documentation files (the ``Software''), to deal in the Software without restriction, including without limitation the rights to use, copy, modify, merge, publish, distribute, sublicense, and/or sell copies of the Software, and to permit persons to whom the Software is furnished to do so, subject to the following conditions: The above copyright notice and this permission notice shall be included in all copies or substantial portions of the Software. THE SOFTWARE IS PROVIDED ``AS IS'', WITHOUT WARRANTY OF ANY KIND, EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHOR BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. ----------------------------------------------------------------------- */ /*====================================================================*/ /* Includes */ /* -------- */ /*====================================================================*/ #include #include #include #include /*====================== End of Includes =============================*/ /*====================================================================*/ /* Defines */ /* ------- */ /*====================================================================*/ /* Maximum number of GPRs available for argument passing. */ #define MAX_GPRARGS 5 /* Maximum number of FPRs available for argument passing. */ #ifdef __s390x__ #define MAX_FPRARGS 4 #else #define MAX_FPRARGS 2 #endif /* Round to multiple of 16. */ #define ROUND_SIZE(size) (((size) + 15) & ~15) /* If these values change, sysv.S must be adapted! */ #define FFI390_RET_VOID 0 #define FFI390_RET_STRUCT 1 #define FFI390_RET_FLOAT 2 #define FFI390_RET_DOUBLE 3 #define FFI390_RET_INT32 4 #define FFI390_RET_INT64 5 /*===================== End of Defines ===============================*/ /*====================================================================*/ /* Prototypes */ /* ---------- */ /*====================================================================*/ static void ffi_prep_args (unsigned char *, extended_cif *); void #if __GNUC__ > 3 || (__GNUC__ == 3 && __GNUC_MINOR__ > 2) __attribute__ ((visibility ("hidden"))) #endif ffi_closure_helper_SYSV (ffi_closure *, unsigned long *, unsigned long long *, unsigned long *); /*====================== End of Prototypes ===========================*/ /*====================================================================*/ /* Externals */ /* --------- */ /*====================================================================*/ extern void ffi_call_SYSV(unsigned, extended_cif *, void (*)(unsigned char *, extended_cif *), unsigned, void *, void (*fn)(void)); extern void ffi_closure_SYSV(void); /*====================== End of Externals ============================*/ /*====================================================================*/ /* */ /* Name - ffi_check_struct_type. */ /* */ /* Function - Determine if a structure can be passed within a */ /* general purpose or floating point register. */ /* */ /*====================================================================*/ static int ffi_check_struct_type (ffi_type *arg) { size_t size = arg->size; /* If the struct has just one element, look at that element to find out whether to consider the struct as floating point. */ while (arg->type == FFI_TYPE_STRUCT && arg->elements[0] && !arg->elements[1]) arg = arg->elements[0]; /* Structs of size 1, 2, 4, and 8 are passed in registers, just like the corresponding int/float types. */ switch (size) { case 1: return FFI_TYPE_UINT8; case 2: return FFI_TYPE_UINT16; case 4: if (arg->type == FFI_TYPE_FLOAT) return FFI_TYPE_FLOAT; else return FFI_TYPE_UINT32; case 8: if (arg->type == FFI_TYPE_DOUBLE) return FFI_TYPE_DOUBLE; else return FFI_TYPE_UINT64; default: break; } /* Other structs are passed via a pointer to the data. */ return FFI_TYPE_POINTER; } /*======================== End of Routine ============================*/ /*====================================================================*/ /* */ /* Name - ffi_prep_args. */ /* */ /* Function - Prepare parameters for call to function. */ /* */ /* ffi_prep_args is called by the assembly routine once stack space */ /* has been allocated for the function's arguments. */ /* */ /*====================================================================*/ static void ffi_prep_args (unsigned char *stack, extended_cif *ecif) { /* The stack space will be filled with those areas: FPR argument register save area (highest addresses) GPR argument register save area temporary struct copies overflow argument area (lowest addresses) We set up the following pointers: p_fpr: bottom of the FPR area (growing upwards) p_gpr: bottom of the GPR area (growing upwards) p_ov: bottom of the overflow area (growing upwards) p_struct: top of the struct copy area (growing downwards) All areas are kept aligned to twice the word size. */ int gpr_off = ecif->cif->bytes; int fpr_off = gpr_off + ROUND_SIZE (MAX_GPRARGS * sizeof (long)); unsigned long long *p_fpr = (unsigned long long *)(stack + fpr_off); unsigned long *p_gpr = (unsigned long *)(stack + gpr_off); unsigned char *p_struct = (unsigned char *)p_gpr; unsigned long *p_ov = (unsigned long *)stack; int n_fpr = 0; int n_gpr = 0; int n_ov = 0; ffi_type **ptr; void **p_argv = ecif->avalue; int i; /* If we returning a structure then we set the first parameter register to the address of where we are returning this structure. */ if (ecif->cif->flags == FFI390_RET_STRUCT) p_gpr[n_gpr++] = (unsigned long) ecif->rvalue; /* Now for the arguments. */ for (ptr = ecif->cif->arg_types, i = ecif->cif->nargs; i > 0; i--, ptr++, p_argv++) { void *arg = *p_argv; int type = (*ptr)->type; #if FFI_TYPE_LONGDOUBLE != FFI_TYPE_DOUBLE /* 16-byte long double is passed like a struct. */ if (type == FFI_TYPE_LONGDOUBLE) type = FFI_TYPE_STRUCT; #endif /* Check how a structure type is passed. */ if (type == FFI_TYPE_STRUCT) { type = ffi_check_struct_type (*ptr); /* If we pass the struct via pointer, copy the data. */ if (type == FFI_TYPE_POINTER) { p_struct -= ROUND_SIZE ((*ptr)->size); memcpy (p_struct, (char *)arg, (*ptr)->size); arg = &p_struct; } } /* Now handle all primitive int/pointer/float data types. */ switch (type) { case FFI_TYPE_DOUBLE: if (n_fpr < MAX_FPRARGS) p_fpr[n_fpr++] = *(unsigned long long *) arg; else #ifdef __s390x__ p_ov[n_ov++] = *(unsigned long *) arg; #else p_ov[n_ov++] = ((unsigned long *) arg)[0], p_ov[n_ov++] = ((unsigned long *) arg)[1]; #endif break; case FFI_TYPE_FLOAT: if (n_fpr < MAX_FPRARGS) p_fpr[n_fpr++] = (long long) *(unsigned int *) arg << 32; else p_ov[n_ov++] = *(unsigned int *) arg; break; case FFI_TYPE_POINTER: if (n_gpr < MAX_GPRARGS) p_gpr[n_gpr++] = (unsigned long)*(unsigned char **) arg; else p_ov[n_ov++] = (unsigned long)*(unsigned char **) arg; break; case FFI_TYPE_UINT64: case FFI_TYPE_SINT64: #ifdef __s390x__ if (n_gpr < MAX_GPRARGS) p_gpr[n_gpr++] = *(unsigned long *) arg; else p_ov[n_ov++] = *(unsigned long *) arg; #else if (n_gpr == MAX_GPRARGS-1) n_gpr = MAX_GPRARGS; if (n_gpr < MAX_GPRARGS) p_gpr[n_gpr++] = ((unsigned long *) arg)[0], p_gpr[n_gpr++] = ((unsigned long *) arg)[1]; else p_ov[n_ov++] = ((unsigned long *) arg)[0], p_ov[n_ov++] = ((unsigned long *) arg)[1]; #endif break; case FFI_TYPE_UINT32: if (n_gpr < MAX_GPRARGS) p_gpr[n_gpr++] = *(unsigned int *) arg; else p_ov[n_ov++] = *(unsigned int *) arg; break; case FFI_TYPE_INT: case FFI_TYPE_SINT32: if (n_gpr < MAX_GPRARGS) p_gpr[n_gpr++] = *(signed int *) arg; else p_ov[n_ov++] = *(signed int *) arg; break; case FFI_TYPE_UINT16: if (n_gpr < MAX_GPRARGS) p_gpr[n_gpr++] = *(unsigned short *) arg; else p_ov[n_ov++] = *(unsigned short *) arg; break; case FFI_TYPE_SINT16: if (n_gpr < MAX_GPRARGS) p_gpr[n_gpr++] = *(signed short *) arg; else p_ov[n_ov++] = *(signed short *) arg; break; case FFI_TYPE_UINT8: if (n_gpr < MAX_GPRARGS) p_gpr[n_gpr++] = *(unsigned char *) arg; else p_ov[n_ov++] = *(unsigned char *) arg; break; case FFI_TYPE_SINT8: if (n_gpr < MAX_GPRARGS) p_gpr[n_gpr++] = *(signed char *) arg; else p_ov[n_ov++] = *(signed char *) arg; break; default: FFI_ASSERT (0); break; } } } /*======================== End of Routine ============================*/ /*====================================================================*/ /* */ /* Name - ffi_prep_cif_machdep. */ /* */ /* Function - Perform machine dependent CIF processing. */ /* */ /*====================================================================*/ ffi_status ffi_prep_cif_machdep(ffi_cif *cif) { size_t struct_size = 0; int n_gpr = 0; int n_fpr = 0; int n_ov = 0; ffi_type **ptr; int i; /* Determine return value handling. */ switch (cif->rtype->type) { /* Void is easy. */ case FFI_TYPE_VOID: cif->flags = FFI390_RET_VOID; break; /* Structures are returned via a hidden pointer. */ case FFI_TYPE_STRUCT: cif->flags = FFI390_RET_STRUCT; n_gpr++; /* We need one GPR to pass the pointer. */ break; /* Floating point values are returned in fpr 0. */ case FFI_TYPE_FLOAT: cif->flags = FFI390_RET_FLOAT; break; case FFI_TYPE_DOUBLE: cif->flags = FFI390_RET_DOUBLE; break; #if FFI_TYPE_LONGDOUBLE != FFI_TYPE_DOUBLE case FFI_TYPE_LONGDOUBLE: cif->flags = FFI390_RET_STRUCT; n_gpr++; break; #endif /* Integer values are returned in gpr 2 (and gpr 3 for 64-bit values on 31-bit machines). */ case FFI_TYPE_UINT64: case FFI_TYPE_SINT64: cif->flags = FFI390_RET_INT64; break; case FFI_TYPE_POINTER: case FFI_TYPE_INT: case FFI_TYPE_UINT32: case FFI_TYPE_SINT32: case FFI_TYPE_UINT16: case FFI_TYPE_SINT16: case FFI_TYPE_UINT8: case FFI_TYPE_SINT8: /* These are to be extended to word size. */ #ifdef __s390x__ cif->flags = FFI390_RET_INT64; #else cif->flags = FFI390_RET_INT32; #endif break; default: FFI_ASSERT (0); break; } /* Now for the arguments. */ for (ptr = cif->arg_types, i = cif->nargs; i > 0; i--, ptr++) { int type = (*ptr)->type; #if FFI_TYPE_LONGDOUBLE != FFI_TYPE_DOUBLE /* 16-byte long double is passed like a struct. */ if (type == FFI_TYPE_LONGDOUBLE) type = FFI_TYPE_STRUCT; #endif /* Check how a structure type is passed. */ if (type == FFI_TYPE_STRUCT) { type = ffi_check_struct_type (*ptr); /* If we pass the struct via pointer, we must reserve space to copy its data for proper call-by-value semantics. */ if (type == FFI_TYPE_POINTER) struct_size += ROUND_SIZE ((*ptr)->size); } /* Now handle all primitive int/float data types. */ switch (type) { /* The first MAX_FPRARGS floating point arguments go in FPRs, the rest overflow to the stack. */ case FFI_TYPE_DOUBLE: if (n_fpr < MAX_FPRARGS) n_fpr++; else n_ov += sizeof (double) / sizeof (long); break; case FFI_TYPE_FLOAT: if (n_fpr < MAX_FPRARGS) n_fpr++; else n_ov++; break; /* On 31-bit machines, 64-bit integers are passed in GPR pairs, if one is still available, or else on the stack. If only one register is free, skip the register (it won't be used for any subsequent argument either). */ #ifndef __s390x__ case FFI_TYPE_UINT64: case FFI_TYPE_SINT64: if (n_gpr == MAX_GPRARGS-1) n_gpr = MAX_GPRARGS; if (n_gpr < MAX_GPRARGS) n_gpr += 2; else n_ov += 2; break; #endif /* Everything else is passed in GPRs (until MAX_GPRARGS have been used) or overflows to the stack. */ default: if (n_gpr < MAX_GPRARGS) n_gpr++; else n_ov++; break; } } /* Total stack space as required for overflow arguments and temporary structure copies. */ cif->bytes = ROUND_SIZE (n_ov * sizeof (long)) + struct_size; return FFI_OK; } /*======================== End of Routine ============================*/ /*====================================================================*/ /* */ /* Name - ffi_call. */ /* */ /* Function - Call the FFI routine. */ /* */ /*====================================================================*/ void ffi_call(ffi_cif *cif, void (*fn)(void), void *rvalue, void **avalue) { int ret_type = cif->flags; extended_cif ecif; ecif.cif = cif; ecif.avalue = avalue; ecif.rvalue = rvalue; /* If we don't have a return value, we need to fake one. */ if (rvalue == NULL) { if (ret_type == FFI390_RET_STRUCT) ecif.rvalue = alloca (cif->rtype->size); else ret_type = FFI390_RET_VOID; } switch (cif->abi) { case FFI_SYSV: ffi_call_SYSV (cif->bytes, &ecif, ffi_prep_args, ret_type, ecif.rvalue, fn); break; default: FFI_ASSERT (0); break; } } /*======================== End of Routine ============================*/ /*====================================================================*/ /* */ /* Name - ffi_closure_helper_SYSV. */ /* */ /* Function - Call a FFI closure target function. */ /* */ /*====================================================================*/ void ffi_closure_helper_SYSV (ffi_closure *closure, unsigned long *p_gpr, unsigned long long *p_fpr, unsigned long *p_ov) { unsigned long long ret_buffer; void *rvalue = &ret_buffer; void **avalue; void **p_arg; int n_gpr = 0; int n_fpr = 0; int n_ov = 0; ffi_type **ptr; int i; /* Allocate buffer for argument list pointers. */ p_arg = avalue = alloca (closure->cif->nargs * sizeof (void *)); /* If we returning a structure, pass the structure address directly to the target function. Otherwise, have the target function store the return value to the GPR save area. */ if (closure->cif->flags == FFI390_RET_STRUCT) rvalue = (void *) p_gpr[n_gpr++]; /* Now for the arguments. */ for (ptr = closure->cif->arg_types, i = closure->cif->nargs; i > 0; i--, p_arg++, ptr++) { int deref_struct_pointer = 0; int type = (*ptr)->type; #if FFI_TYPE_LONGDOUBLE != FFI_TYPE_DOUBLE /* 16-byte long double is passed like a struct. */ if (type == FFI_TYPE_LONGDOUBLE) type = FFI_TYPE_STRUCT; #endif /* Check how a structure type is passed. */ if (type == FFI_TYPE_STRUCT) { type = ffi_check_struct_type (*ptr); /* If we pass the struct via pointer, remember to retrieve the pointer later. */ if (type == FFI_TYPE_POINTER) deref_struct_pointer = 1; } /* Pointers are passed like UINTs of the same size. */ if (type == FFI_TYPE_POINTER) #ifdef __s390x__ type = FFI_TYPE_UINT64; #else type = FFI_TYPE_UINT32; #endif /* Now handle all primitive int/float data types. */ switch (type) { case FFI_TYPE_DOUBLE: if (n_fpr < MAX_FPRARGS) *p_arg = &p_fpr[n_fpr++]; else *p_arg = &p_ov[n_ov], n_ov += sizeof (double) / sizeof (long); break; case FFI_TYPE_FLOAT: if (n_fpr < MAX_FPRARGS) *p_arg = &p_fpr[n_fpr++]; else *p_arg = (char *)&p_ov[n_ov++] + sizeof (long) - 4; break; case FFI_TYPE_UINT64: case FFI_TYPE_SINT64: #ifdef __s390x__ if (n_gpr < MAX_GPRARGS) *p_arg = &p_gpr[n_gpr++]; else *p_arg = &p_ov[n_ov++]; #else if (n_gpr == MAX_GPRARGS-1) n_gpr = MAX_GPRARGS; if (n_gpr < MAX_GPRARGS) *p_arg = &p_gpr[n_gpr], n_gpr += 2; else *p_arg = &p_ov[n_ov], n_ov += 2; #endif break; case FFI_TYPE_INT: case FFI_TYPE_UINT32: case FFI_TYPE_SINT32: if (n_gpr < MAX_GPRARGS) *p_arg = (char *)&p_gpr[n_gpr++] + sizeof (long) - 4; else *p_arg = (char *)&p_ov[n_ov++] + sizeof (long) - 4; break; case FFI_TYPE_UINT16: case FFI_TYPE_SINT16: if (n_gpr < MAX_GPRARGS) *p_arg = (char *)&p_gpr[n_gpr++] + sizeof (long) - 2; else *p_arg = (char *)&p_ov[n_ov++] + sizeof (long) - 2; break; case FFI_TYPE_UINT8: case FFI_TYPE_SINT8: if (n_gpr < MAX_GPRARGS) *p_arg = (char *)&p_gpr[n_gpr++] + sizeof (long) - 1; else *p_arg = (char *)&p_ov[n_ov++] + sizeof (long) - 1; break; default: FFI_ASSERT (0); break; } /* If this is a struct passed via pointer, we need to actually retrieve that pointer. */ if (deref_struct_pointer) *p_arg = *(void **)*p_arg; } /* Call the target function. */ (closure->fun) (closure->cif, rvalue, avalue, closure->user_data); /* Convert the return value. */ switch (closure->cif->rtype->type) { /* Void is easy, and so is struct. */ case FFI_TYPE_VOID: case FFI_TYPE_STRUCT: #if FFI_TYPE_LONGDOUBLE != FFI_TYPE_DOUBLE case FFI_TYPE_LONGDOUBLE: #endif break; /* Floating point values are returned in fpr 0. */ case FFI_TYPE_FLOAT: p_fpr[0] = (long long) *(unsigned int *) rvalue << 32; break; case FFI_TYPE_DOUBLE: p_fpr[0] = *(unsigned long long *) rvalue; break; /* Integer values are returned in gpr 2 (and gpr 3 for 64-bit values on 31-bit machines). */ case FFI_TYPE_UINT64: case FFI_TYPE_SINT64: #ifdef __s390x__ p_gpr[0] = *(unsigned long *) rvalue; #else p_gpr[0] = ((unsigned long *) rvalue)[0], p_gpr[1] = ((unsigned long *) rvalue)[1]; #endif break; case FFI_TYPE_POINTER: case FFI_TYPE_UINT32: case FFI_TYPE_UINT16: case FFI_TYPE_UINT8: p_gpr[0] = *(unsigned long *) rvalue; break; case FFI_TYPE_INT: case FFI_TYPE_SINT32: case FFI_TYPE_SINT16: case FFI_TYPE_SINT8: p_gpr[0] = *(signed long *) rvalue; break; default: FFI_ASSERT (0); break; } } /*======================== End of Routine ============================*/ /*====================================================================*/ /* */ /* Name - ffi_prep_closure_loc. */ /* */ /* Function - Prepare a FFI closure. */ /* */ /*====================================================================*/ ffi_status ffi_prep_closure_loc (ffi_closure *closure, ffi_cif *cif, void (*fun) (ffi_cif *, void *, void **, void *), void *user_data, void *codeloc) { FFI_ASSERT (cif->abi == FFI_SYSV); #ifndef __s390x__ *(short *)&closure->tramp [0] = 0x0d10; /* basr %r1,0 */ *(short *)&closure->tramp [2] = 0x9801; /* lm %r0,%r1,6(%r1) */ *(short *)&closure->tramp [4] = 0x1006; *(short *)&closure->tramp [6] = 0x07f1; /* br %r1 */ *(long *)&closure->tramp [8] = (long)codeloc; *(long *)&closure->tramp[12] = (long)&ffi_closure_SYSV; #else *(short *)&closure->tramp [0] = 0x0d10; /* basr %r1,0 */ *(short *)&closure->tramp [2] = 0xeb01; /* lmg %r0,%r1,14(%r1) */ *(short *)&closure->tramp [4] = 0x100e; *(short *)&closure->tramp [6] = 0x0004; *(short *)&closure->tramp [8] = 0x07f1; /* br %r1 */ *(long *)&closure->tramp[16] = (long)codeloc; *(long *)&closure->tramp[24] = (long)&ffi_closure_SYSV; #endif closure->cif = cif; closure->user_data = user_data; closure->fun = fun; return FFI_OK; } /*======================== End of Routine ============================*/ smalltalk-3.2.5/libffi/src/sparc/0000755000175000017500000000000012130456004013633 500000000000000smalltalk-3.2.5/libffi/src/sparc/v8.S0000644000175000017500000001540512130343734014246 00000000000000/* ----------------------------------------------------------------------- v8.S - Copyright (c) 1996, 1997, 2003, 2004, 2008 Red Hat, Inc. SPARC Foreign Function Interface Permission is hereby granted, free of charge, to any person obtaining a copy of this software and associated documentation files (the ``Software''), to deal in the Software without restriction, including without limitation the rights to use, copy, modify, merge, publish, distribute, sublicense, and/or sell copies of the Software, and to permit persons to whom the Software is furnished to do so, subject to the following conditions: The above copyright notice and this permission notice shall be included in all copies or substantial portions of the Software. THE SOFTWARE IS PROVIDED ``AS IS'', WITHOUT WARRANTY OF ANY KIND, EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. ----------------------------------------------------------------------- */ #define LIBFFI_ASM #include #include #define STACKFRAME 96 /* Minimum stack framesize for SPARC */ #define ARGS (64+4) /* Offset of register area in frame */ .text .align 8 .globl ffi_call_v8 .globl _ffi_call_v8 ffi_call_v8: _ffi_call_v8: .LLFB1: save %sp, -STACKFRAME, %sp .LLCFI0: sub %sp, %i2, %sp ! alloca() space in stack for frame to set up add %sp, STACKFRAME, %l0 ! %l0 has start of ! frame to set up mov %l0, %o0 ! call routine to set up frame call %i0 mov %i1, %o1 ! (delay) ld [%l0+ARGS], %o0 ! call foreign function ld [%l0+ARGS+4], %o1 ld [%l0+ARGS+8], %o2 ld [%l0+ARGS+12], %o3 ld [%l0+ARGS+16], %o4 ld [%l0+ARGS+20], %o5 call %i5 mov %l0, %sp ! (delay) switch to frame nop ! STRUCT returning functions skip 12 instead of 8 bytes ! If the return value pointer is NULL, assume no return value. tst %i4 bz done nop cmp %i3, FFI_TYPE_INT be,a done st %o0, [%i4] ! (delay) cmp %i3, FFI_TYPE_FLOAT be,a done st %f0, [%i4+0] ! (delay) cmp %i3, FFI_TYPE_DOUBLE be,a double st %f0, [%i4+0] ! (delay) cmp %i3, FFI_TYPE_SINT8 be,a sint8 sll %o0, 24, %o0 ! (delay) cmp %i3, FFI_TYPE_UINT8 be,a uint8 sll %o0, 24, %o0 ! (delay) cmp %i3, FFI_TYPE_SINT16 be,a sint16 sll %o0, 16, %o0 ! (delay) cmp %i3, FFI_TYPE_UINT16 be,a uint16 sll %o0, 16, %o0 ! (delay) cmp %i3, FFI_TYPE_SINT64 be,a longlong st %o0, [%i4+0] ! (delay) done: ret restore double: st %f1, [%i4+4] ret restore sint8: sra %o0, 24, %o0 st %o0, [%i4+0] ret restore uint8: srl %o0, 24, %o0 st %o0, [%i4+0] ret restore sint16: sra %o0, 16, %o0 st %o0, [%i4+0] ret restore uint16: srl %o0, 16, %o0 st %o0, [%i4+0] ret restore longlong: st %o1, [%i4+4] ret restore .LLFE1: .ffi_call_v8_end: .size ffi_call_v8,.ffi_call_v8_end-ffi_call_v8 #undef STACKFRAME #define STACKFRAME 104 /* 16*4 register window + 1*4 struct return + 6*4 args backing store + 3*4 locals */ /* ffi_closure_v8(...) Receives the closure argument in %g2. */ .text .align 8 .globl ffi_closure_v8 ffi_closure_v8: #ifdef HAVE_AS_REGISTER_PSEUDO_OP .register %g2, #scratch #endif .LLFB2: ! Reserve frame space for all arguments in case ! we need to align them on a 8-byte boundary. ld [%g2+FFI_TRAMPOLINE_SIZE], %g1 ld [%g1+4], %g1 sll %g1, 3, %g1 add %g1, STACKFRAME, %g1 ! %g1 == STACKFRAME + 8*nargs neg %g1 save %sp, %g1, %sp .LLCFI1: ! Store all of the potential argument registers in va_list format. st %i0, [%fp+68+0] st %i1, [%fp+68+4] st %i2, [%fp+68+8] st %i3, [%fp+68+12] st %i4, [%fp+68+16] st %i5, [%fp+68+20] ! Call ffi_closure_sparc_inner to do the bulk of the work. mov %g2, %o0 add %fp, -8, %o1 add %fp, 64, %o2 call ffi_closure_sparc_inner_v8 add %fp, -16, %o3 ! Load up the return value in the proper type. ! See ffi_prep_cif_machdep for the list of cases. cmp %o0, FFI_TYPE_VOID be done1 cmp %o0, FFI_TYPE_INT be done1 ld [%fp-8], %i0 cmp %o0, FFI_TYPE_FLOAT be,a done1 ld [%fp-8], %f0 cmp %o0, FFI_TYPE_DOUBLE be,a done1 ldd [%fp-8], %f0 #if FFI_TYPE_LONGDOUBLE != FFI_TYPE_DOUBLE cmp %o0, FFI_TYPE_LONGDOUBLE be done2 #endif cmp %o0, FFI_TYPE_STRUCT be done2 cmp %o0, FFI_TYPE_SINT64 be,a done1 ldd [%fp-8], %i0 ld [%fp-8], %i0 done1: jmp %i7+8 restore done2: ! Skip 'unimp'. jmp %i7+12 restore .LLFE2: .ffi_closure_v8_end: .size ffi_closure_v8,.ffi_closure_v8_end-ffi_closure_v8 #ifdef SPARC64 #define WS 8 #define nword xword #define uanword uaxword #else #define WS 4 #define nword long #define uanword uaword #endif #ifdef HAVE_RO_EH_FRAME .section ".eh_frame",#alloc #else .section ".eh_frame",#alloc,#write #endif .LLframe1: .uaword .LLECIE1-.LLSCIE1 ! Length of Common Information Entry .LLSCIE1: .uaword 0x0 ! CIE Identifier Tag .byte 0x1 ! CIE Version .ascii "zR\0" ! CIE Augmentation .byte 0x1 ! uleb128 0x1; CIE Code Alignment Factor .byte 0x80-WS ! sleb128 -WS; CIE Data Alignment Factor .byte 0xf ! CIE RA Column .byte 0x1 ! uleb128 0x1; Augmentation size #ifdef HAVE_AS_SPARC_UA_PCREL .byte 0x1b ! FDE Encoding (pcrel sdata4) #else .byte 0x50 ! FDE Encoding (aligned absolute) #endif .byte 0xc ! DW_CFA_def_cfa .byte 0xe ! uleb128 0xe .byte 0x0 ! uleb128 0x0 .align WS .LLECIE1: .LLSFDE1: .uaword .LLEFDE1-.LLASFDE1 ! FDE Length .LLASFDE1: .uaword .LLASFDE1-.LLframe1 ! FDE CIE offset #ifdef HAVE_AS_SPARC_UA_PCREL .uaword %r_disp32(.LLFB1) .uaword .LLFE1-.LLFB1 ! FDE address range #else .align WS .nword .LLFB1 .uanword .LLFE1-.LLFB1 ! FDE address range #endif .byte 0x0 ! uleb128 0x0; Augmentation size .byte 0x4 ! DW_CFA_advance_loc4 .uaword .LLCFI0-.LLFB1 .byte 0xd ! DW_CFA_def_cfa_register .byte 0x1e ! uleb128 0x1e .byte 0x2d ! DW_CFA_GNU_window_save .byte 0x9 ! DW_CFA_register .byte 0xf ! uleb128 0xf .byte 0x1f ! uleb128 0x1f .align WS .LLEFDE1: .LLSFDE2: .uaword .LLEFDE2-.LLASFDE2 ! FDE Length .LLASFDE2: .uaword .LLASFDE2-.LLframe1 ! FDE CIE offset #ifdef HAVE_AS_SPARC_UA_PCREL .uaword %r_disp32(.LLFB2) .uaword .LLFE2-.LLFB2 ! FDE address range #else .align WS .nword .LLFB2 .uanword .LLFE2-.LLFB2 ! FDE address range #endif .byte 0x0 ! uleb128 0x0; Augmentation size .byte 0x4 ! DW_CFA_advance_loc4 .uaword .LLCFI1-.LLFB2 .byte 0xd ! DW_CFA_def_cfa_register .byte 0x1e ! uleb128 0x1e .byte 0x2d ! DW_CFA_GNU_window_save .byte 0x9 ! DW_CFA_register .byte 0xf ! uleb128 0xf .byte 0x1f ! uleb128 0x1f .align WS .LLEFDE2: #if defined __ELF__ && defined __linux__ .section .note.GNU-stack,"",@progbits #endif smalltalk-3.2.5/libffi/src/sparc/ffitarget.h0000644000175000017500000000407012130343734015705 00000000000000/* -----------------------------------------------------------------*-C-*- ffitarget.h - Copyright (c) 1996-2003 Red Hat, Inc. Target configuration macros for SPARC. Permission is hereby granted, free of charge, to any person obtaining a copy of this software and associated documentation files (the ``Software''), to deal in the Software without restriction, including without limitation the rights to use, copy, modify, merge, publish, distribute, sublicense, and/or sell copies of the Software, and to permit persons to whom the Software is furnished to do so, subject to the following conditions: The above copyright notice and this permission notice shall be included in all copies or substantial portions of the Software. THE SOFTWARE IS PROVIDED ``AS IS'', WITHOUT WARRANTY OF ANY KIND, EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. ----------------------------------------------------------------------- */ #ifndef LIBFFI_TARGET_H #define LIBFFI_TARGET_H /* ---- System specific configurations ----------------------------------- */ #if defined(__arch64__) || defined(__sparcv9) #ifndef SPARC64 #define SPARC64 #endif #endif #ifndef LIBFFI_ASM typedef unsigned long ffi_arg; typedef signed long ffi_sarg; typedef enum ffi_abi { FFI_FIRST_ABI = 0, FFI_V8, FFI_V8PLUS, FFI_V9, #ifdef SPARC64 FFI_DEFAULT_ABI = FFI_V9, #else FFI_DEFAULT_ABI = FFI_V8, #endif FFI_LAST_ABI = FFI_DEFAULT_ABI + 1 } ffi_abi; #endif /* ---- Definitions for closures ----------------------------------------- */ #define FFI_CLOSURES 1 #define FFI_NATIVE_RAW_API 0 #ifdef SPARC64 #define FFI_TRAMPOLINE_SIZE 24 #else #define FFI_TRAMPOLINE_SIZE 16 #endif #endif smalltalk-3.2.5/libffi/src/sparc/v9.S0000644000175000017500000001635712130343734014256 00000000000000/* ----------------------------------------------------------------------- v9.S - Copyright (c) 2000, 2003, 2004, 2008 Red Hat, Inc. SPARC 64-bit Foreign Function Interface Permission is hereby granted, free of charge, to any person obtaining a copy of this software and associated documentation files (the ``Software''), to deal in the Software without restriction, including without limitation the rights to use, copy, modify, merge, publish, distribute, sublicense, and/or sell copies of the Software, and to permit persons to whom the Software is furnished to do so, subject to the following conditions: The above copyright notice and this permission notice shall be included in all copies or substantial portions of the Software. THE SOFTWARE IS PROVIDED ``AS IS'', WITHOUT WARRANTY OF ANY KIND, EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. ----------------------------------------------------------------------- */ #define LIBFFI_ASM #include #include #ifdef SPARC64 /* Only compile this in for 64bit builds, because otherwise the object file will have inproper architecture due to used instructions. */ #define STACKFRAME 128 /* Minimum stack framesize for SPARC */ #define STACK_BIAS 2047 #define ARGS (128) /* Offset of register area in frame */ .text .align 8 .globl ffi_call_v9 .globl _ffi_call_v9 ffi_call_v9: _ffi_call_v9: .LLFB1: save %sp, -STACKFRAME, %sp .LLCFI0: sub %sp, %i2, %sp ! alloca() space in stack for frame to set up add %sp, STACKFRAME+STACK_BIAS, %l0 ! %l0 has start of ! frame to set up mov %l0, %o0 ! call routine to set up frame call %i0 mov %i1, %o1 ! (delay) brz,pt %o0, 1f ldx [%l0+ARGS], %o0 ! call foreign function ldd [%l0+ARGS], %f0 ldd [%l0+ARGS+8], %f2 ldd [%l0+ARGS+16], %f4 ldd [%l0+ARGS+24], %f6 ldd [%l0+ARGS+32], %f8 ldd [%l0+ARGS+40], %f10 ldd [%l0+ARGS+48], %f12 ldd [%l0+ARGS+56], %f14 ldd [%l0+ARGS+64], %f16 ldd [%l0+ARGS+72], %f18 ldd [%l0+ARGS+80], %f20 ldd [%l0+ARGS+88], %f22 ldd [%l0+ARGS+96], %f24 ldd [%l0+ARGS+104], %f26 ldd [%l0+ARGS+112], %f28 ldd [%l0+ARGS+120], %f30 1: ldx [%l0+ARGS+8], %o1 ldx [%l0+ARGS+16], %o2 ldx [%l0+ARGS+24], %o3 ldx [%l0+ARGS+32], %o4 ldx [%l0+ARGS+40], %o5 call %i5 sub %l0, STACK_BIAS, %sp ! (delay) switch to frame ! If the return value pointer is NULL, assume no return value. brz,pn %i4, done nop cmp %i3, FFI_TYPE_INT be,a,pt %icc, done stx %o0, [%i4+0] ! (delay) cmp %i3, FFI_TYPE_FLOAT be,a,pn %icc, done st %f0, [%i4+0] ! (delay) cmp %i3, FFI_TYPE_DOUBLE be,a,pn %icc, done std %f0, [%i4+0] ! (delay) cmp %i3, FFI_TYPE_STRUCT be,pn %icc, dostruct cmp %i3, FFI_TYPE_LONGDOUBLE bne,pt %icc, done nop std %f0, [%i4+0] std %f2, [%i4+8] done: ret restore dostruct: /* This will not work correctly for unions. */ stx %o0, [%i4+0] stx %o1, [%i4+8] stx %o2, [%i4+16] stx %o3, [%i4+24] std %f0, [%i4+32] std %f2, [%i4+40] std %f4, [%i4+48] std %f6, [%i4+56] ret restore .LLFE1: .ffi_call_v9_end: .size ffi_call_v9,.ffi_call_v9_end-ffi_call_v9 #undef STACKFRAME #define STACKFRAME 336 /* 16*8 register window + 6*8 args backing store + 20*8 locals */ #define FP %fp+STACK_BIAS /* ffi_closure_v9(...) Receives the closure argument in %g1. */ .text .align 8 .globl ffi_closure_v9 ffi_closure_v9: .LLFB2: save %sp, -STACKFRAME, %sp .LLCFI1: ! Store all of the potential argument registers in va_list format. stx %i0, [FP+128+0] stx %i1, [FP+128+8] stx %i2, [FP+128+16] stx %i3, [FP+128+24] stx %i4, [FP+128+32] stx %i5, [FP+128+40] ! Store possible floating point argument registers too. std %f0, [FP-128] std %f2, [FP-120] std %f4, [FP-112] std %f6, [FP-104] std %f8, [FP-96] std %f10, [FP-88] std %f12, [FP-80] std %f14, [FP-72] std %f16, [FP-64] std %f18, [FP-56] std %f20, [FP-48] std %f22, [FP-40] std %f24, [FP-32] std %f26, [FP-24] std %f28, [FP-16] std %f30, [FP-8] ! Call ffi_closure_sparc_inner to do the bulk of the work. mov %g1, %o0 add %fp, STACK_BIAS-160, %o1 add %fp, STACK_BIAS+128, %o2 call ffi_closure_sparc_inner_v9 add %fp, STACK_BIAS-128, %o3 ! Load up the return value in the proper type. ! See ffi_prep_cif_machdep for the list of cases. cmp %o0, FFI_TYPE_VOID be,pn %icc, done1 cmp %o0, FFI_TYPE_INT be,pn %icc, integer cmp %o0, FFI_TYPE_FLOAT be,a,pn %icc, done1 ld [FP-160], %f0 cmp %o0, FFI_TYPE_DOUBLE be,a,pn %icc, done1 ldd [FP-160], %f0 #if FFI_TYPE_LONGDOUBLE != FFI_TYPE_DOUBLE cmp %o0, FFI_TYPE_LONGDOUBLE be,a,pn %icc, longdouble1 ldd [FP-160], %f0 #endif ! FFI_TYPE_STRUCT ldx [FP-152], %i1 ldx [FP-144], %i2 ldx [FP-136], %i3 ldd [FP-160], %f0 ldd [FP-152], %f2 ldd [FP-144], %f4 ldd [FP-136], %f6 integer: ldx [FP-160], %i0 done1: ret restore #if FFI_TYPE_LONGDOUBLE != FFI_TYPE_DOUBLE longdouble1: ldd [FP-152], %f2 ret restore #endif .LLFE2: .ffi_closure_v9_end: .size ffi_closure_v9,.ffi_closure_v9_end-ffi_closure_v9 #ifdef HAVE_RO_EH_FRAME .section ".eh_frame",#alloc #else .section ".eh_frame",#alloc,#write #endif .LLframe1: .uaword .LLECIE1-.LLSCIE1 ! Length of Common Information Entry .LLSCIE1: .uaword 0x0 ! CIE Identifier Tag .byte 0x1 ! CIE Version .ascii "zR\0" ! CIE Augmentation .byte 0x1 ! uleb128 0x1; CIE Code Alignment Factor .byte 0x78 ! sleb128 -8; CIE Data Alignment Factor .byte 0xf ! CIE RA Column .byte 0x1 ! uleb128 0x1; Augmentation size #ifdef HAVE_AS_SPARC_UA_PCREL .byte 0x1b ! FDE Encoding (pcrel sdata4) #else .byte 0x50 ! FDE Encoding (aligned absolute) #endif .byte 0xc ! DW_CFA_def_cfa .byte 0xe ! uleb128 0xe .byte 0xff,0xf ! uleb128 0x7ff .align 8 .LLECIE1: .LLSFDE1: .uaword .LLEFDE1-.LLASFDE1 ! FDE Length .LLASFDE1: .uaword .LLASFDE1-.LLframe1 ! FDE CIE offset #ifdef HAVE_AS_SPARC_UA_PCREL .uaword %r_disp32(.LLFB1) .uaword .LLFE1-.LLFB1 ! FDE address range #else .align 8 .xword .LLFB1 .uaxword .LLFE1-.LLFB1 ! FDE address range #endif .byte 0x0 ! uleb128 0x0; Augmentation size .byte 0x4 ! DW_CFA_advance_loc4 .uaword .LLCFI0-.LLFB1 .byte 0xd ! DW_CFA_def_cfa_register .byte 0x1e ! uleb128 0x1e .byte 0x2d ! DW_CFA_GNU_window_save .byte 0x9 ! DW_CFA_register .byte 0xf ! uleb128 0xf .byte 0x1f ! uleb128 0x1f .align 8 .LLEFDE1: .LLSFDE2: .uaword .LLEFDE2-.LLASFDE2 ! FDE Length .LLASFDE2: .uaword .LLASFDE2-.LLframe1 ! FDE CIE offset #ifdef HAVE_AS_SPARC_UA_PCREL .uaword %r_disp32(.LLFB2) .uaword .LLFE2-.LLFB2 ! FDE address range #else .align 8 .xword .LLFB2 .uaxword .LLFE2-.LLFB2 ! FDE address range #endif .byte 0x0 ! uleb128 0x0; Augmentation size .byte 0x4 ! DW_CFA_advance_loc4 .uaword .LLCFI1-.LLFB2 .byte 0xd ! DW_CFA_def_cfa_register .byte 0x1e ! uleb128 0x1e .byte 0x2d ! DW_CFA_GNU_window_save .byte 0x9 ! DW_CFA_register .byte 0xf ! uleb128 0xf .byte 0x1f ! uleb128 0x1f .align 8 .LLEFDE2: #endif #ifdef __linux__ .section .note.GNU-stack,"",@progbits #endif smalltalk-3.2.5/libffi/src/sparc/ffi.c0000644000175000017500000003656112130343734014503 00000000000000/* ----------------------------------------------------------------------- ffi.c - Copyright (c) 1996, 2003, 2004, 2007, 2008 Red Hat, Inc. SPARC Foreign Function Interface Permission is hereby granted, free of charge, to any person obtaining a copy of this software and associated documentation files (the ``Software''), to deal in the Software without restriction, including without limitation the rights to use, copy, modify, merge, publish, distribute, sublicense, and/or sell copies of the Software, and to permit persons to whom the Software is furnished to do so, subject to the following conditions: The above copyright notice and this permission notice shall be included in all copies or substantial portions of the Software. THE SOFTWARE IS PROVIDED ``AS IS'', WITHOUT WARRANTY OF ANY KIND, EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. ----------------------------------------------------------------------- */ #include #include #include /* ffi_prep_args is called by the assembly routine once stack space has been allocated for the function's arguments */ void ffi_prep_args_v8(char *stack, extended_cif *ecif) { int i; void **p_argv; char *argp; ffi_type **p_arg; /* Skip 16 words for the window save area */ argp = stack + 16*sizeof(int); /* This should only really be done when we are returning a structure, however, it's faster just to do it all the time... if ( ecif->cif->rtype->type == FFI_TYPE_STRUCT ) */ *(int *) argp = (long)ecif->rvalue; /* And 1 word for the structure return value. */ argp += sizeof(int); #ifdef USING_PURIFY /* Purify will probably complain in our assembly routine, unless we zero out this memory. */ ((int*)argp)[0] = 0; ((int*)argp)[1] = 0; ((int*)argp)[2] = 0; ((int*)argp)[3] = 0; ((int*)argp)[4] = 0; ((int*)argp)[5] = 0; #endif p_argv = ecif->avalue; for (i = ecif->cif->nargs, p_arg = ecif->cif->arg_types; i; i--, p_arg++) { size_t z; if ((*p_arg)->type == FFI_TYPE_STRUCT #if FFI_TYPE_LONGDOUBLE != FFI_TYPE_DOUBLE || (*p_arg)->type == FFI_TYPE_LONGDOUBLE #endif ) { *(unsigned int *) argp = (unsigned long)(* p_argv); z = sizeof(int); } else { z = (*p_arg)->size; if (z < sizeof(int)) { z = sizeof(int); switch ((*p_arg)->type) { case FFI_TYPE_SINT8: *(signed int *) argp = *(SINT8 *)(* p_argv); break; case FFI_TYPE_UINT8: *(unsigned int *) argp = *(UINT8 *)(* p_argv); break; case FFI_TYPE_SINT16: *(signed int *) argp = *(SINT16 *)(* p_argv); break; case FFI_TYPE_UINT16: *(unsigned int *) argp = *(UINT16 *)(* p_argv); break; default: FFI_ASSERT(0); } } else { memcpy(argp, *p_argv, z); } } p_argv++; argp += z; } return; } int ffi_prep_args_v9(char *stack, extended_cif *ecif) { int i, ret = 0; int tmp; void **p_argv; char *argp; ffi_type **p_arg; tmp = 0; /* Skip 16 words for the window save area */ argp = stack + 16*sizeof(long long); #ifdef USING_PURIFY /* Purify will probably complain in our assembly routine, unless we zero out this memory. */ ((long long*)argp)[0] = 0; ((long long*)argp)[1] = 0; ((long long*)argp)[2] = 0; ((long long*)argp)[3] = 0; ((long long*)argp)[4] = 0; ((long long*)argp)[5] = 0; #endif p_argv = ecif->avalue; if (ecif->cif->rtype->type == FFI_TYPE_STRUCT && ecif->cif->rtype->size > 32) { *(unsigned long long *) argp = (unsigned long)ecif->rvalue; argp += sizeof(long long); tmp = 1; } for (i = 0, p_arg = ecif->cif->arg_types; i < ecif->cif->nargs; i++, p_arg++) { size_t z; z = (*p_arg)->size; switch ((*p_arg)->type) { case FFI_TYPE_STRUCT: if (z > 16) { /* For structures larger than 16 bytes we pass reference. */ *(unsigned long long *) argp = (unsigned long)* p_argv; argp += sizeof(long long); tmp++; p_argv++; continue; } /* FALLTHROUGH */ case FFI_TYPE_FLOAT: case FFI_TYPE_DOUBLE: #if FFI_TYPE_LONGDOUBLE != FFI_TYPE_DOUBLE case FFI_TYPE_LONGDOUBLE: #endif ret = 1; /* We should promote into FP regs as well as integer. */ break; } if (z < sizeof(long long)) { switch ((*p_arg)->type) { case FFI_TYPE_SINT8: *(signed long long *) argp = *(SINT8 *)(* p_argv); break; case FFI_TYPE_UINT8: *(unsigned long long *) argp = *(UINT8 *)(* p_argv); break; case FFI_TYPE_SINT16: *(signed long long *) argp = *(SINT16 *)(* p_argv); break; case FFI_TYPE_UINT16: *(unsigned long long *) argp = *(UINT16 *)(* p_argv); break; case FFI_TYPE_SINT32: *(signed long long *) argp = *(SINT32 *)(* p_argv); break; case FFI_TYPE_UINT32: *(unsigned long long *) argp = *(UINT32 *)(* p_argv); break; case FFI_TYPE_FLOAT: *(float *) (argp + 4) = *(FLOAT32 *)(* p_argv); /* Right justify */ break; case FFI_TYPE_STRUCT: memcpy(argp, *p_argv, z); break; default: FFI_ASSERT(0); } z = sizeof(long long); tmp++; } else if (z == sizeof(long long)) { memcpy(argp, *p_argv, z); z = sizeof(long long); tmp++; } else { if ((tmp & 1) && (*p_arg)->alignment > 8) { tmp++; argp += sizeof(long long); } memcpy(argp, *p_argv, z); z = 2 * sizeof(long long); tmp += 2; } p_argv++; argp += z; } return ret; } /* Perform machine dependent cif processing */ ffi_status ffi_prep_cif_machdep(ffi_cif *cif) { int wordsize; if (cif->abi != FFI_V9) { wordsize = 4; /* If we are returning a struct, this will already have been added. Otherwise we need to add it because it's always got to be there! */ if (cif->rtype->type != FFI_TYPE_STRUCT) cif->bytes += wordsize; /* sparc call frames require that space is allocated for 6 args, even if they aren't used. Make that space if necessary. */ if (cif->bytes < 4*6+4) cif->bytes = 4*6+4; } else { wordsize = 8; /* sparc call frames require that space is allocated for 6 args, even if they aren't used. Make that space if necessary. */ if (cif->bytes < 8*6) cif->bytes = 8*6; } /* Adjust cif->bytes. to include 16 words for the window save area, and maybe the struct/union return pointer area, */ cif->bytes += 16 * wordsize; /* The stack must be 2 word aligned, so round bytes up appropriately. */ cif->bytes = ALIGN(cif->bytes, 2 * wordsize); /* Set the return type flag */ switch (cif->rtype->type) { case FFI_TYPE_VOID: case FFI_TYPE_FLOAT: case FFI_TYPE_DOUBLE: #if FFI_TYPE_LONGDOUBLE != FFI_TYPE_DOUBLE case FFI_TYPE_LONGDOUBLE: #endif cif->flags = cif->rtype->type; break; case FFI_TYPE_STRUCT: if (cif->abi == FFI_V9 && cif->rtype->size > 32) cif->flags = FFI_TYPE_VOID; else cif->flags = FFI_TYPE_STRUCT; break; case FFI_TYPE_SINT8: case FFI_TYPE_UINT8: case FFI_TYPE_SINT16: case FFI_TYPE_UINT16: if (cif->abi == FFI_V9) cif->flags = FFI_TYPE_INT; else cif->flags = cif->rtype->type; break; case FFI_TYPE_SINT64: case FFI_TYPE_UINT64: if (cif->abi == FFI_V9) cif->flags = FFI_TYPE_INT; else cif->flags = FFI_TYPE_SINT64; break; default: cif->flags = FFI_TYPE_INT; break; } return FFI_OK; } int ffi_v9_layout_struct(ffi_type *arg, int off, char *ret, char *intg, char *flt) { ffi_type **ptr = &arg->elements[0]; while (*ptr != NULL) { if (off & ((*ptr)->alignment - 1)) off = ALIGN(off, (*ptr)->alignment); switch ((*ptr)->type) { case FFI_TYPE_STRUCT: off = ffi_v9_layout_struct(*ptr, off, ret, intg, flt); off = ALIGN(off, FFI_SIZEOF_ARG); break; case FFI_TYPE_FLOAT: case FFI_TYPE_DOUBLE: #if FFI_TYPE_LONGDOUBLE != FFI_TYPE_DOUBLE case FFI_TYPE_LONGDOUBLE: #endif memmove(ret + off, flt + off, (*ptr)->size); off += (*ptr)->size; break; default: memmove(ret + off, intg + off, (*ptr)->size); off += (*ptr)->size; break; } ptr++; } return off; } #ifdef SPARC64 extern int ffi_call_v9(void *, extended_cif *, unsigned, unsigned, unsigned *, void (*fn)(void)); #else extern int ffi_call_v8(void *, extended_cif *, unsigned, unsigned, unsigned *, void (*fn)(void)); #endif void ffi_call(ffi_cif *cif, void (*fn)(void), void *rvalue, void **avalue) { extended_cif ecif; void *rval = rvalue; ecif.cif = cif; ecif.avalue = avalue; /* If the return value is a struct and we don't have a return */ /* value address then we need to make one */ ecif.rvalue = rvalue; if (cif->rtype->type == FFI_TYPE_STRUCT) { if (cif->rtype->size <= 32) rval = alloca(64); else { rval = NULL; if (rvalue == NULL) ecif.rvalue = alloca(cif->rtype->size); } } switch (cif->abi) { case FFI_V8: #ifdef SPARC64 /* We don't yet support calling 32bit code from 64bit */ FFI_ASSERT(0); #else ffi_call_v8(ffi_prep_args_v8, &ecif, cif->bytes, cif->flags, rvalue, fn); #endif break; case FFI_V9: #ifdef SPARC64 ffi_call_v9(ffi_prep_args_v9, &ecif, cif->bytes, cif->flags, rval, fn); if (rvalue && rval && cif->rtype->type == FFI_TYPE_STRUCT) ffi_v9_layout_struct(cif->rtype, 0, (char *)rvalue, (char *)rval, ((char *)rval)+32); #else /* And vice versa */ FFI_ASSERT(0); #endif break; default: FFI_ASSERT(0); break; } } #ifdef SPARC64 extern void ffi_closure_v9(void); #else extern void ffi_closure_v8(void); #endif ffi_status ffi_prep_closure_loc (ffi_closure* closure, ffi_cif* cif, void (*fun)(ffi_cif*, void*, void**, void*), void *user_data, void *codeloc) { unsigned int *tramp = (unsigned int *) &closure->tramp[0]; unsigned long fn; #ifdef SPARC64 /* Trampoline address is equal to the closure address. We take advantage of that to reduce the trampoline size by 8 bytes. */ FFI_ASSERT (cif->abi == FFI_V9); fn = (unsigned long) ffi_closure_v9; tramp[0] = 0x83414000; /* rd %pc, %g1 */ tramp[1] = 0xca586010; /* ldx [%g1+16], %g5 */ tramp[2] = 0x81c14000; /* jmp %g5 */ tramp[3] = 0x01000000; /* nop */ *((unsigned long *) &tramp[4]) = fn; #else unsigned long ctx = (unsigned long) codeloc; FFI_ASSERT (cif->abi == FFI_V8); fn = (unsigned long) ffi_closure_v8; tramp[0] = 0x03000000 | fn >> 10; /* sethi %hi(fn), %g1 */ tramp[1] = 0x05000000 | ctx >> 10; /* sethi %hi(ctx), %g2 */ tramp[2] = 0x81c06000 | (fn & 0x3ff); /* jmp %g1+%lo(fn) */ tramp[3] = 0x8410a000 | (ctx & 0x3ff);/* or %g2, %lo(ctx) */ #endif closure->cif = cif; closure->fun = fun; closure->user_data = user_data; /* Flush the Icache. FIXME: alignment isn't certain, assume 8 bytes */ #ifdef SPARC64 asm volatile ("flush %0" : : "r" (closure) : "memory"); asm volatile ("flush %0" : : "r" (((char *) closure) + 8) : "memory"); #else asm volatile ("iflush %0" : : "r" (closure) : "memory"); asm volatile ("iflush %0" : : "r" (((char *) closure) + 8) : "memory"); #endif return FFI_OK; } int ffi_closure_sparc_inner_v8(ffi_closure *closure, void *rvalue, unsigned long *gpr, unsigned long *scratch) { ffi_cif *cif; ffi_type **arg_types; void **avalue; int i, argn; cif = closure->cif; arg_types = cif->arg_types; avalue = alloca(cif->nargs * sizeof(void *)); /* Copy the caller's structure return address so that the closure returns the data directly to the caller. */ if (cif->flags == FFI_TYPE_STRUCT #if FFI_TYPE_LONGDOUBLE != FFI_TYPE_DOUBLE || cif->flags == FFI_TYPE_LONGDOUBLE #endif ) rvalue = (void *) gpr[0]; /* Always skip the structure return address. */ argn = 1; /* Grab the addresses of the arguments from the stack frame. */ for (i = 0; i < cif->nargs; i++) { if (arg_types[i]->type == FFI_TYPE_STRUCT #if FFI_TYPE_LONGDOUBLE != FFI_TYPE_DOUBLE || arg_types[i]->type == FFI_TYPE_LONGDOUBLE #endif ) { /* Straight copy of invisible reference. */ avalue[i] = (void *)gpr[argn++]; } else if ((arg_types[i]->type == FFI_TYPE_DOUBLE || arg_types[i]->type == FFI_TYPE_SINT64 || arg_types[i]->type == FFI_TYPE_UINT64) /* gpr is 8-byte aligned. */ && (argn % 2) != 0) { /* Align on a 8-byte boundary. */ scratch[0] = gpr[argn]; scratch[1] = gpr[argn+1]; avalue[i] = scratch; scratch -= 2; argn += 2; } else { /* Always right-justify. */ argn += ALIGN(arg_types[i]->size, FFI_SIZEOF_ARG) / FFI_SIZEOF_ARG; avalue[i] = ((char *) &gpr[argn]) - arg_types[i]->size; } } /* Invoke the closure. */ (closure->fun) (cif, rvalue, avalue, closure->user_data); /* Tell ffi_closure_sparc how to perform return type promotions. */ return cif->rtype->type; } int ffi_closure_sparc_inner_v9(ffi_closure *closure, void *rvalue, unsigned long *gpr, double *fpr) { ffi_cif *cif; ffi_type **arg_types; void **avalue; int i, argn, fp_slot_max; cif = closure->cif; arg_types = cif->arg_types; avalue = alloca(cif->nargs * sizeof(void *)); /* Copy the caller's structure return address so that the closure returns the data directly to the caller. */ if (cif->flags == FFI_TYPE_VOID && cif->rtype->type == FFI_TYPE_STRUCT) { rvalue = (void *) gpr[0]; /* Skip the structure return address. */ argn = 1; } else argn = 0; fp_slot_max = 16 - argn; /* Grab the addresses of the arguments from the stack frame. */ for (i = 0; i < cif->nargs; i++) { if (arg_types[i]->type == FFI_TYPE_STRUCT) { if (arg_types[i]->size > 16) { /* Straight copy of invisible reference. */ avalue[i] = (void *)gpr[argn++]; } else { /* Left-justify. */ ffi_v9_layout_struct(arg_types[i], 0, (char *) &gpr[argn], (char *) &gpr[argn], (char *) &fpr[argn]); avalue[i] = &gpr[argn]; argn += ALIGN(arg_types[i]->size, FFI_SIZEOF_ARG) / FFI_SIZEOF_ARG; } } else { /* Right-justify. */ argn += ALIGN(arg_types[i]->size, FFI_SIZEOF_ARG) / FFI_SIZEOF_ARG; /* Align on a 16-byte boundary. */ #if FFI_TYPE_LONGDOUBLE != FFI_TYPE_DOUBLE if (arg_types[i]->type == FFI_TYPE_LONGDOUBLE && (argn % 2) != 0) argn++; #endif if (i < fp_slot_max && (arg_types[i]->type == FFI_TYPE_FLOAT || arg_types[i]->type == FFI_TYPE_DOUBLE #if FFI_TYPE_LONGDOUBLE != FFI_TYPE_DOUBLE || arg_types[i]->type == FFI_TYPE_LONGDOUBLE #endif )) avalue[i] = ((char *) &fpr[argn]) - arg_types[i]->size; else avalue[i] = ((char *) &gpr[argn]) - arg_types[i]->size; } } /* Invoke the closure. */ (closure->fun) (cif, rvalue, avalue, closure->user_data); /* Tell ffi_closure_sparc how to perform return type promotions. */ return cif->rtype->type; } smalltalk-3.2.5/libffi/src/types.c0000644000175000017500000000553012130343734013763 00000000000000/* ----------------------------------------------------------------------- types.c - Copyright (c) 1996, 1998 Red Hat, Inc. Predefined ffi_types needed by libffi. Permission is hereby granted, free of charge, to any person obtaining a copy of this software and associated documentation files (the ``Software''), to deal in the Software without restriction, including without limitation the rights to use, copy, modify, merge, publish, distribute, sublicense, and/or sell copies of the Software, and to permit persons to whom the Software is furnished to do so, subject to the following conditions: The above copyright notice and this permission notice shall be included in all copies or substantial portions of the Software. THE SOFTWARE IS PROVIDED ``AS IS'', WITHOUT WARRANTY OF ANY KIND, EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. ----------------------------------------------------------------------- */ /* Hide the basic type definitions from the header file, so that we can redefine them here as "const". */ #define LIBFFI_HIDE_BASIC_TYPES #include #include /* Type definitions */ #define FFI_TYPEDEF(name, type, id) \ struct struct_align_##name { \ char c; \ type x; \ }; \ const ffi_type ffi_type_##name = { \ sizeof(type), \ offsetof(struct struct_align_##name, x), \ id, NULL \ } /* Size and alignment are fake here. They must not be 0. */ const ffi_type ffi_type_void = { 1, 1, FFI_TYPE_VOID, NULL }; FFI_TYPEDEF(uint8, UINT8, FFI_TYPE_UINT8); FFI_TYPEDEF(sint8, SINT8, FFI_TYPE_SINT8); FFI_TYPEDEF(uint16, UINT16, FFI_TYPE_UINT16); FFI_TYPEDEF(sint16, SINT16, FFI_TYPE_SINT16); FFI_TYPEDEF(uint32, UINT32, FFI_TYPE_UINT32); FFI_TYPEDEF(sint32, SINT32, FFI_TYPE_SINT32); FFI_TYPEDEF(uint64, UINT64, FFI_TYPE_UINT64); FFI_TYPEDEF(sint64, SINT64, FFI_TYPE_SINT64); FFI_TYPEDEF(pointer, void*, FFI_TYPE_POINTER); FFI_TYPEDEF(float, float, FFI_TYPE_FLOAT); FFI_TYPEDEF(double, double, FFI_TYPE_DOUBLE); #ifdef __alpha__ /* Even if we're not configured to default to 128-bit long double, maintain binary compatibility, as -mlong-double-128 can be used at any time. */ /* Validate the hard-coded number below. */ # if defined(__LONG_DOUBLE_128__) && FFI_TYPE_LONGDOUBLE != 4 # error FFI_TYPE_LONGDOUBLE out of date # endif const ffi_type ffi_type_longdouble = { 16, 16, 4, NULL }; #elif FFI_TYPE_LONGDOUBLE != FFI_TYPE_DOUBLE FFI_TYPEDEF(longdouble, long double, FFI_TYPE_LONGDOUBLE); #endif smalltalk-3.2.5/libffi/src/ia64/0000755000175000017500000000000012130456004013266 500000000000000smalltalk-3.2.5/libffi/src/ia64/unix.S0000644000175000017500000002660112130343734014327 00000000000000/* ----------------------------------------------------------------------- unix.S - Copyright (c) 1998, 2008 Red Hat, Inc. Copyright (c) 2000 Hewlett Packard Company IA64/unix Foreign Function Interface Primary author: Hans Boehm, HP Labs Loosely modeled on Cygnus code for other platforms. Permission is hereby granted, free of charge, to any person obtaining a copy of this software and associated documentation files (the ``Software''), to deal in the Software without restriction, including without limitation the rights to use, copy, modify, merge, publish, distribute, sublicense, and/or sell copies of the Software, and to permit persons to whom the Software is furnished to do so, subject to the following conditions: The above copyright notice and this permission notice shall be included in all copies or substantial portions of the Software. THE SOFTWARE IS PROVIDED ``AS IS'', WITHOUT WARRANTY OF ANY KIND, EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. ----------------------------------------------------------------------- */ #define LIBFFI_ASM #include #include #include "ia64_flags.h" .pred.safe_across_calls p1-p5,p16-p63 .text /* int ffi_call_unix (struct ia64_args *stack, PTR64 rvalue, void (*fn)(void), int flags); */ .align 16 .global ffi_call_unix .proc ffi_call_unix ffi_call_unix: .prologue /* Bit o trickiness. We actually share a stack frame with ffi_call. Rely on the fact that ffi_call uses a vframe and don't bother tracking one here at all. */ .fframe 0 .save ar.pfs, r36 // loc0 alloc loc0 = ar.pfs, 4, 3, 8, 0 .save rp, loc1 mov loc1 = b0 .body add r16 = 16, in0 mov loc2 = gp mov r8 = in1 ;; /* Load up all of the argument registers. */ ldf.fill f8 = [in0], 32 ldf.fill f9 = [r16], 32 ;; ldf.fill f10 = [in0], 32 ldf.fill f11 = [r16], 32 ;; ldf.fill f12 = [in0], 32 ldf.fill f13 = [r16], 32 ;; ldf.fill f14 = [in0], 32 ldf.fill f15 = [r16], 24 ;; ld8 out0 = [in0], 16 ld8 out1 = [r16], 16 ;; ld8 out2 = [in0], 16 ld8 out3 = [r16], 16 ;; ld8 out4 = [in0], 16 ld8 out5 = [r16], 16 ;; ld8 out6 = [in0] ld8 out7 = [r16] ;; /* Deallocate the register save area from the stack frame. */ mov sp = in0 /* Call the target function. */ ld8 r16 = [in2], 8 ;; ld8 gp = [in2] mov b6 = r16 br.call.sptk.many b0 = b6 ;; /* Dispatch to handle return value. */ mov gp = loc2 zxt1 r16 = in3 ;; mov ar.pfs = loc0 addl r18 = @ltoffx(.Lst_table), gp ;; ld8.mov r18 = [r18], .Lst_table mov b0 = loc1 ;; shladd r18 = r16, 3, r18 ;; ld8 r17 = [r18] shr in3 = in3, 8 ;; add r17 = r17, r18 ;; mov b6 = r17 br b6 ;; .Lst_void: br.ret.sptk.many b0 ;; .Lst_uint8: zxt1 r8 = r8 ;; st8 [in1] = r8 br.ret.sptk.many b0 ;; .Lst_sint8: sxt1 r8 = r8 ;; st8 [in1] = r8 br.ret.sptk.many b0 ;; .Lst_uint16: zxt2 r8 = r8 ;; st8 [in1] = r8 br.ret.sptk.many b0 ;; .Lst_sint16: sxt2 r8 = r8 ;; st8 [in1] = r8 br.ret.sptk.many b0 ;; .Lst_uint32: zxt4 r8 = r8 ;; st8 [in1] = r8 br.ret.sptk.many b0 ;; .Lst_sint32: sxt4 r8 = r8 ;; st8 [in1] = r8 br.ret.sptk.many b0 ;; .Lst_int64: st8 [in1] = r8 br.ret.sptk.many b0 ;; .Lst_float: stfs [in1] = f8 br.ret.sptk.many b0 ;; .Lst_double: stfd [in1] = f8 br.ret.sptk.many b0 ;; .Lst_ldouble: stfe [in1] = f8 br.ret.sptk.many b0 ;; .Lst_small_struct: add sp = -16, sp cmp.lt p6, p0 = 8, in3 cmp.lt p7, p0 = 16, in3 cmp.lt p8, p0 = 24, in3 ;; add r16 = 8, sp add r17 = 16, sp add r18 = 24, sp ;; st8 [sp] = r8 (p6) st8 [r16] = r9 mov out0 = in1 (p7) st8 [r17] = r10 (p8) st8 [r18] = r11 mov out1 = sp mov out2 = in3 br.call.sptk.many b0 = memcpy# ;; mov ar.pfs = loc0 mov b0 = loc1 mov gp = loc2 br.ret.sptk.many b0 .Lst_hfa_float: add r16 = 4, in1 cmp.lt p6, p0 = 4, in3 ;; stfs [in1] = f8, 8 (p6) stfs [r16] = f9, 8 cmp.lt p7, p0 = 8, in3 cmp.lt p8, p0 = 12, in3 ;; (p7) stfs [in1] = f10, 8 (p8) stfs [r16] = f11, 8 cmp.lt p9, p0 = 16, in3 cmp.lt p10, p0 = 20, in3 ;; (p9) stfs [in1] = f12, 8 (p10) stfs [r16] = f13, 8 cmp.lt p6, p0 = 24, in3 cmp.lt p7, p0 = 28, in3 ;; (p6) stfs [in1] = f14 (p7) stfs [r16] = f15 br.ret.sptk.many b0 ;; .Lst_hfa_double: add r16 = 8, in1 cmp.lt p6, p0 = 8, in3 ;; stfd [in1] = f8, 16 (p6) stfd [r16] = f9, 16 cmp.lt p7, p0 = 16, in3 cmp.lt p8, p0 = 24, in3 ;; (p7) stfd [in1] = f10, 16 (p8) stfd [r16] = f11, 16 cmp.lt p9, p0 = 32, in3 cmp.lt p10, p0 = 40, in3 ;; (p9) stfd [in1] = f12, 16 (p10) stfd [r16] = f13, 16 cmp.lt p6, p0 = 48, in3 cmp.lt p7, p0 = 56, in3 ;; (p6) stfd [in1] = f14 (p7) stfd [r16] = f15 br.ret.sptk.many b0 ;; .Lst_hfa_ldouble: add r16 = 16, in1 cmp.lt p6, p0 = 16, in3 ;; stfe [in1] = f8, 32 (p6) stfe [r16] = f9, 32 cmp.lt p7, p0 = 32, in3 cmp.lt p8, p0 = 48, in3 ;; (p7) stfe [in1] = f10, 32 (p8) stfe [r16] = f11, 32 cmp.lt p9, p0 = 64, in3 cmp.lt p10, p0 = 80, in3 ;; (p9) stfe [in1] = f12, 32 (p10) stfe [r16] = f13, 32 cmp.lt p6, p0 = 96, in3 cmp.lt p7, p0 = 112, in3 ;; (p6) stfe [in1] = f14 (p7) stfe [r16] = f15 br.ret.sptk.many b0 ;; .endp ffi_call_unix .align 16 .global ffi_closure_unix .proc ffi_closure_unix #define FRAME_SIZE (8*16 + 8*8 + 8*16) ffi_closure_unix: .prologue .save ar.pfs, r40 // loc0 alloc loc0 = ar.pfs, 8, 4, 4, 0 .fframe FRAME_SIZE add r12 = -FRAME_SIZE, r12 .save rp, loc1 mov loc1 = b0 .save ar.unat, loc2 mov loc2 = ar.unat .body /* Retrieve closure pointer and real gp. */ #ifdef _ILP32 addp4 out0 = 0, gp addp4 gp = 16, gp #else mov out0 = gp add gp = 16, gp #endif ;; ld8 gp = [gp] /* Spill all of the possible argument registers. */ add r16 = 16 + 8*16, sp add r17 = 16 + 8*16 + 16, sp ;; stf.spill [r16] = f8, 32 stf.spill [r17] = f9, 32 mov loc3 = gp ;; stf.spill [r16] = f10, 32 stf.spill [r17] = f11, 32 ;; stf.spill [r16] = f12, 32 stf.spill [r17] = f13, 32 ;; stf.spill [r16] = f14, 32 stf.spill [r17] = f15, 24 ;; .mem.offset 0, 0 st8.spill [r16] = in0, 16 .mem.offset 8, 0 st8.spill [r17] = in1, 16 add out1 = 16 + 8*16, sp ;; .mem.offset 0, 0 st8.spill [r16] = in2, 16 .mem.offset 8, 0 st8.spill [r17] = in3, 16 add out2 = 16, sp ;; .mem.offset 0, 0 st8.spill [r16] = in4, 16 .mem.offset 8, 0 st8.spill [r17] = in5, 16 mov out3 = r8 ;; .mem.offset 0, 0 st8.spill [r16] = in6 .mem.offset 8, 0 st8.spill [r17] = in7 /* Invoke ffi_closure_unix_inner for the hard work. */ br.call.sptk.many b0 = ffi_closure_unix_inner ;; /* Dispatch to handle return value. */ mov gp = loc3 zxt1 r16 = r8 ;; addl r18 = @ltoffx(.Lld_table), gp mov ar.pfs = loc0 ;; ld8.mov r18 = [r18], .Lld_table mov b0 = loc1 ;; shladd r18 = r16, 3, r18 mov ar.unat = loc2 ;; ld8 r17 = [r18] shr r8 = r8, 8 ;; add r17 = r17, r18 add r16 = 16, sp ;; mov b6 = r17 br b6 ;; .label_state 1 .Lld_void: .restore sp add sp = FRAME_SIZE, sp br.ret.sptk.many b0 ;; .Lld_int: .body .copy_state 1 ld8 r8 = [r16] .restore sp add sp = FRAME_SIZE, sp br.ret.sptk.many b0 ;; .Lld_float: .body .copy_state 1 ldfs f8 = [r16] .restore sp add sp = FRAME_SIZE, sp br.ret.sptk.many b0 ;; .Lld_double: .body .copy_state 1 ldfd f8 = [r16] .restore sp add sp = FRAME_SIZE, sp br.ret.sptk.many b0 ;; .Lld_ldouble: .body .copy_state 1 ldfe f8 = [r16] .restore sp add sp = FRAME_SIZE, sp br.ret.sptk.many b0 ;; .Lld_small_struct: .body .copy_state 1 add r17 = 8, r16 cmp.lt p6, p0 = 8, r8 cmp.lt p7, p0 = 16, r8 cmp.lt p8, p0 = 24, r8 ;; ld8 r8 = [r16], 16 (p6) ld8 r9 = [r17], 16 ;; (p7) ld8 r10 = [r16] (p8) ld8 r11 = [r17] .restore sp add sp = FRAME_SIZE, sp br.ret.sptk.many b0 ;; .Lld_hfa_float: .body .copy_state 1 add r17 = 4, r16 cmp.lt p6, p0 = 4, r8 ;; ldfs f8 = [r16], 8 (p6) ldfs f9 = [r17], 8 cmp.lt p7, p0 = 8, r8 cmp.lt p8, p0 = 12, r8 ;; (p7) ldfs f10 = [r16], 8 (p8) ldfs f11 = [r17], 8 cmp.lt p9, p0 = 16, r8 cmp.lt p10, p0 = 20, r8 ;; (p9) ldfs f12 = [r16], 8 (p10) ldfs f13 = [r17], 8 cmp.lt p6, p0 = 24, r8 cmp.lt p7, p0 = 28, r8 ;; (p6) ldfs f14 = [r16] (p7) ldfs f15 = [r17] .restore sp add sp = FRAME_SIZE, sp br.ret.sptk.many b0 ;; .Lld_hfa_double: .body .copy_state 1 add r17 = 8, r16 cmp.lt p6, p0 = 8, r8 ;; ldfd f8 = [r16], 16 (p6) ldfd f9 = [r17], 16 cmp.lt p7, p0 = 16, r8 cmp.lt p8, p0 = 24, r8 ;; (p7) ldfd f10 = [r16], 16 (p8) ldfd f11 = [r17], 16 cmp.lt p9, p0 = 32, r8 cmp.lt p10, p0 = 40, r8 ;; (p9) ldfd f12 = [r16], 16 (p10) ldfd f13 = [r17], 16 cmp.lt p6, p0 = 48, r8 cmp.lt p7, p0 = 56, r8 ;; (p6) ldfd f14 = [r16] (p7) ldfd f15 = [r17] .restore sp add sp = FRAME_SIZE, sp br.ret.sptk.many b0 ;; .Lld_hfa_ldouble: .body .copy_state 1 add r17 = 16, r16 cmp.lt p6, p0 = 16, r8 ;; ldfe f8 = [r16], 32 (p6) ldfe f9 = [r17], 32 cmp.lt p7, p0 = 32, r8 cmp.lt p8, p0 = 48, r8 ;; (p7) ldfe f10 = [r16], 32 (p8) ldfe f11 = [r17], 32 cmp.lt p9, p0 = 64, r8 cmp.lt p10, p0 = 80, r8 ;; (p9) ldfe f12 = [r16], 32 (p10) ldfe f13 = [r17], 32 cmp.lt p6, p0 = 96, r8 cmp.lt p7, p0 = 112, r8 ;; (p6) ldfe f14 = [r16] (p7) ldfe f15 = [r17] .restore sp add sp = FRAME_SIZE, sp br.ret.sptk.many b0 ;; .endp ffi_closure_unix .section .rodata .align 8 .Lst_table: data8 @pcrel(.Lst_void) // FFI_TYPE_VOID data8 @pcrel(.Lst_sint32) // FFI_TYPE_INT data8 @pcrel(.Lst_float) // FFI_TYPE_FLOAT data8 @pcrel(.Lst_double) // FFI_TYPE_DOUBLE data8 @pcrel(.Lst_ldouble) // FFI_TYPE_LONGDOUBLE data8 @pcrel(.Lst_uint8) // FFI_TYPE_UINT8 data8 @pcrel(.Lst_sint8) // FFI_TYPE_SINT8 data8 @pcrel(.Lst_uint16) // FFI_TYPE_UINT16 data8 @pcrel(.Lst_sint16) // FFI_TYPE_SINT16 data8 @pcrel(.Lst_uint32) // FFI_TYPE_UINT32 data8 @pcrel(.Lst_sint32) // FFI_TYPE_SINT32 data8 @pcrel(.Lst_int64) // FFI_TYPE_UINT64 data8 @pcrel(.Lst_int64) // FFI_TYPE_SINT64 data8 @pcrel(.Lst_void) // FFI_TYPE_STRUCT data8 @pcrel(.Lst_int64) // FFI_TYPE_POINTER data8 @pcrel(.Lst_small_struct) // FFI_IA64_TYPE_SMALL_STRUCT data8 @pcrel(.Lst_hfa_float) // FFI_IA64_TYPE_HFA_FLOAT data8 @pcrel(.Lst_hfa_double) // FFI_IA64_TYPE_HFA_DOUBLE data8 @pcrel(.Lst_hfa_ldouble) // FFI_IA64_TYPE_HFA_LDOUBLE .Lld_table: data8 @pcrel(.Lld_void) // FFI_TYPE_VOID data8 @pcrel(.Lld_int) // FFI_TYPE_INT data8 @pcrel(.Lld_float) // FFI_TYPE_FLOAT data8 @pcrel(.Lld_double) // FFI_TYPE_DOUBLE data8 @pcrel(.Lld_ldouble) // FFI_TYPE_LONGDOUBLE data8 @pcrel(.Lld_int) // FFI_TYPE_UINT8 data8 @pcrel(.Lld_int) // FFI_TYPE_SINT8 data8 @pcrel(.Lld_int) // FFI_TYPE_UINT16 data8 @pcrel(.Lld_int) // FFI_TYPE_SINT16 data8 @pcrel(.Lld_int) // FFI_TYPE_UINT32 data8 @pcrel(.Lld_int) // FFI_TYPE_SINT32 data8 @pcrel(.Lld_int) // FFI_TYPE_UINT64 data8 @pcrel(.Lld_int) // FFI_TYPE_SINT64 data8 @pcrel(.Lld_void) // FFI_TYPE_STRUCT data8 @pcrel(.Lld_int) // FFI_TYPE_POINTER data8 @pcrel(.Lld_small_struct) // FFI_IA64_TYPE_SMALL_STRUCT data8 @pcrel(.Lld_hfa_float) // FFI_IA64_TYPE_HFA_FLOAT data8 @pcrel(.Lld_hfa_double) // FFI_IA64_TYPE_HFA_DOUBLE data8 @pcrel(.Lld_hfa_ldouble) // FFI_IA64_TYPE_HFA_LDOUBLE #if defined __ELF__ && defined __linux__ .section .note.GNU-stack,"",@progbits #endif smalltalk-3.2.5/libffi/src/ia64/ia64_flags.h0000644000175000017500000000363512130343734015312 00000000000000/* ----------------------------------------------------------------------- ia64_flags.h - Copyright (c) 2000 Hewlett Packard Company IA64/unix Foreign Function Interface Original author: Hans Boehm, HP Labs Permission is hereby granted, free of charge, to any person obtaining a copy of this software and associated documentation files (the ``Software''), to deal in the Software without restriction, including without limitation the rights to use, copy, modify, merge, publish, distribute, sublicense, and/or sell copies of the Software, and to permit persons to whom the Software is furnished to do so, subject to the following conditions: The above copyright notice and this permission notice shall be included in all copies or substantial portions of the Software. THE SOFTWARE IS PROVIDED ``AS IS'', WITHOUT WARRANTY OF ANY KIND, EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. ----------------------------------------------------------------------- */ /* "Type" codes used between assembly and C. When used as a part of a cfi->flags value, the low byte will be these extra type codes, and bits 8-31 will be the actual size of the type. */ /* Small structures containing N words in integer registers. */ #define FFI_IA64_TYPE_SMALL_STRUCT (FFI_TYPE_LAST + 1) /* Homogeneous Floating Point Aggregates (HFAs) which are returned in FP registers. */ #define FFI_IA64_TYPE_HFA_FLOAT (FFI_TYPE_LAST + 2) #define FFI_IA64_TYPE_HFA_DOUBLE (FFI_TYPE_LAST + 3) #define FFI_IA64_TYPE_HFA_LDOUBLE (FFI_TYPE_LAST + 4) smalltalk-3.2.5/libffi/src/ia64/ffitarget.h0000644000175000017500000000364012130343734015342 00000000000000/* -----------------------------------------------------------------*-C-*- ffitarget.h - Copyright (c) 1996-2003 Red Hat, Inc. Target configuration macros for IA-64. Permission is hereby granted, free of charge, to any person obtaining a copy of this software and associated documentation files (the ``Software''), to deal in the Software without restriction, including without limitation the rights to use, copy, modify, merge, publish, distribute, sublicense, and/or sell copies of the Software, and to permit persons to whom the Software is furnished to do so, subject to the following conditions: The above copyright notice and this permission notice shall be included in all copies or substantial portions of the Software. THE SOFTWARE IS PROVIDED ``AS IS'', WITHOUT WARRANTY OF ANY KIND, EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. ----------------------------------------------------------------------- */ #ifndef LIBFFI_TARGET_H #define LIBFFI_TARGET_H #ifndef LIBFFI_ASM typedef unsigned long long ffi_arg; typedef signed long long ffi_sarg; typedef enum ffi_abi { FFI_FIRST_ABI = 0, FFI_UNIX, /* Linux and all Unix variants use the same conventions */ FFI_DEFAULT_ABI = FFI_UNIX, FFI_LAST_ABI = FFI_DEFAULT_ABI + 1 } ffi_abi; #endif /* ---- Definitions for closures ----------------------------------------- */ #define FFI_CLOSURES 1 #define FFI_TRAMPOLINE_SIZE 24 /* Really the following struct, which */ /* can be interpreted as a C function */ /* descriptor: */ #endif smalltalk-3.2.5/libffi/src/ia64/ffi.c0000644000175000017500000003605012130343734014127 00000000000000/* ----------------------------------------------------------------------- ffi.c - Copyright (c) 1998, 2007, 2008 Red Hat, Inc. Copyright (c) 2000 Hewlett Packard Company IA64 Foreign Function Interface Permission is hereby granted, free of charge, to any person obtaining a copy of this software and associated documentation files (the ``Software''), to deal in the Software without restriction, including without limitation the rights to use, copy, modify, merge, publish, distribute, sublicense, and/or sell copies of the Software, and to permit persons to whom the Software is furnished to do so, subject to the following conditions: The above copyright notice and this permission notice shall be included in all copies or substantial portions of the Software. THE SOFTWARE IS PROVIDED ``AS IS'', WITHOUT WARRANTY OF ANY KIND, EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. ----------------------------------------------------------------------- */ #include #include #include #include #include #include "ia64_flags.h" /* A 64-bit pointer value. In LP64 mode, this is effectively a plain pointer. In ILP32 mode, it's a pointer that's been extended to 64 bits by "addp4". */ typedef void *PTR64 __attribute__((mode(DI))); /* Memory image of fp register contents. This is the implementation specific format used by ldf.fill/stf.spill. All we care about is that it wants a 16 byte aligned slot. */ typedef struct { UINT64 x[2] __attribute__((aligned(16))); } fpreg; /* The stack layout given to ffi_call_unix and ffi_closure_unix_inner. */ struct ia64_args { fpreg fp_regs[8]; /* Contents of 8 fp arg registers. */ UINT64 gp_regs[8]; /* Contents of 8 gp arg registers. */ UINT64 other_args[]; /* Arguments passed on stack, variable size. */ }; /* Adjust ADDR, a pointer to an 8 byte slot, to point to the low LEN bytes. */ static inline void * endian_adjust (void *addr, size_t len) { #ifdef __BIG_ENDIAN__ return addr + (8 - len); #else return addr; #endif } /* Store VALUE to ADDR in the current cpu implementation's fp spill format. This is a macro instead of a function, so that it works for all 3 floating point types without type conversions. Type conversion to long double breaks the denorm support. */ #define stf_spill(addr, value) \ asm ("stf.spill %0 = %1%P0" : "=m" (*addr) : "f"(value)); /* Load a value from ADDR, which is in the current cpu implementation's fp spill format. As above, this must also be a macro. */ #define ldf_fill(result, addr) \ asm ("ldf.fill %0 = %1%P1" : "=f"(result) : "m"(*addr)); /* Return the size of the C type associated with with TYPE. Which will be one of the FFI_IA64_TYPE_HFA_* values. */ static size_t hfa_type_size (int type) { switch (type) { case FFI_IA64_TYPE_HFA_FLOAT: return sizeof(float); case FFI_IA64_TYPE_HFA_DOUBLE: return sizeof(double); case FFI_IA64_TYPE_HFA_LDOUBLE: return sizeof(__float80); default: abort (); } } /* Load from ADDR a value indicated by TYPE. Which will be one of the FFI_IA64_TYPE_HFA_* values. */ static void hfa_type_load (fpreg *fpaddr, int type, void *addr) { switch (type) { case FFI_IA64_TYPE_HFA_FLOAT: stf_spill (fpaddr, *(float *) addr); return; case FFI_IA64_TYPE_HFA_DOUBLE: stf_spill (fpaddr, *(double *) addr); return; case FFI_IA64_TYPE_HFA_LDOUBLE: stf_spill (fpaddr, *(__float80 *) addr); return; default: abort (); } } /* Load VALUE into ADDR as indicated by TYPE. Which will be one of the FFI_IA64_TYPE_HFA_* values. */ static void hfa_type_store (int type, void *addr, fpreg *fpaddr) { switch (type) { case FFI_IA64_TYPE_HFA_FLOAT: { float result; ldf_fill (result, fpaddr); *(float *) addr = result; break; } case FFI_IA64_TYPE_HFA_DOUBLE: { double result; ldf_fill (result, fpaddr); *(double *) addr = result; break; } case FFI_IA64_TYPE_HFA_LDOUBLE: { __float80 result; ldf_fill (result, fpaddr); *(__float80 *) addr = result; break; } default: abort (); } } /* Is TYPE a struct containing floats, doubles, or extended doubles, all of the same fp type? If so, return the element type. Return FFI_TYPE_VOID if not. */ static int hfa_element_type (ffi_type *type, int nested) { int element = FFI_TYPE_VOID; switch (type->type) { case FFI_TYPE_FLOAT: /* We want to return VOID for raw floating-point types, but the synthetic HFA type if we're nested within an aggregate. */ if (nested) element = FFI_IA64_TYPE_HFA_FLOAT; break; case FFI_TYPE_DOUBLE: /* Similarly. */ if (nested) element = FFI_IA64_TYPE_HFA_DOUBLE; break; case FFI_TYPE_LONGDOUBLE: /* Similarly, except that that HFA is true for double extended, but not quad precision. Both have sizeof == 16, so tell the difference based on the precision. */ if (LDBL_MANT_DIG == 64 && nested) element = FFI_IA64_TYPE_HFA_LDOUBLE; break; case FFI_TYPE_STRUCT: { ffi_type **ptr = &type->elements[0]; for (ptr = &type->elements[0]; *ptr ; ptr++) { int sub_element = hfa_element_type (*ptr, 1); if (sub_element == FFI_TYPE_VOID) return FFI_TYPE_VOID; if (element == FFI_TYPE_VOID) element = sub_element; else if (element != sub_element) return FFI_TYPE_VOID; } } break; default: return FFI_TYPE_VOID; } return element; } /* Perform machine dependent cif processing. */ ffi_status ffi_prep_cif_machdep(ffi_cif *cif) { int flags; /* Adjust cif->bytes to include space for the bits of the ia64_args frame that precedes the integer register portion. The estimate that the generic bits did for the argument space required is good enough for the integer component. */ cif->bytes += offsetof(struct ia64_args, gp_regs[0]); if (cif->bytes < sizeof(struct ia64_args)) cif->bytes = sizeof(struct ia64_args); /* Set the return type flag. */ flags = cif->rtype->type; switch (cif->rtype->type) { case FFI_TYPE_LONGDOUBLE: /* Leave FFI_TYPE_LONGDOUBLE as meaning double extended precision, and encode quad precision as a two-word integer structure. */ if (LDBL_MANT_DIG != 64) flags = FFI_IA64_TYPE_SMALL_STRUCT | (16 << 8); break; case FFI_TYPE_STRUCT: { size_t size = cif->rtype->size; int hfa_type = hfa_element_type (cif->rtype, 0); if (hfa_type != FFI_TYPE_VOID) { size_t nelts = size / hfa_type_size (hfa_type); if (nelts <= 8) flags = hfa_type | (size << 8); } else { if (size <= 32) flags = FFI_IA64_TYPE_SMALL_STRUCT | (size << 8); } } break; default: break; } cif->flags = flags; return FFI_OK; } extern int ffi_call_unix (struct ia64_args *, PTR64, void (*)(void), UINT64); void ffi_call(ffi_cif *cif, void (*fn)(void), void *rvalue, void **avalue) { struct ia64_args *stack; long i, avn, gpcount, fpcount; ffi_type **p_arg; FFI_ASSERT (cif->abi == FFI_UNIX); /* If we have no spot for a return value, make one. */ if (rvalue == NULL && cif->rtype->type != FFI_TYPE_VOID) rvalue = alloca (cif->rtype->size); /* Allocate the stack frame. */ stack = alloca (cif->bytes); gpcount = fpcount = 0; avn = cif->nargs; for (i = 0, p_arg = cif->arg_types; i < avn; i++, p_arg++) { switch ((*p_arg)->type) { case FFI_TYPE_SINT8: stack->gp_regs[gpcount++] = *(SINT8 *)avalue[i]; break; case FFI_TYPE_UINT8: stack->gp_regs[gpcount++] = *(UINT8 *)avalue[i]; break; case FFI_TYPE_SINT16: stack->gp_regs[gpcount++] = *(SINT16 *)avalue[i]; break; case FFI_TYPE_UINT16: stack->gp_regs[gpcount++] = *(UINT16 *)avalue[i]; break; case FFI_TYPE_SINT32: stack->gp_regs[gpcount++] = *(SINT32 *)avalue[i]; break; case FFI_TYPE_UINT32: stack->gp_regs[gpcount++] = *(UINT32 *)avalue[i]; break; case FFI_TYPE_SINT64: case FFI_TYPE_UINT64: stack->gp_regs[gpcount++] = *(UINT64 *)avalue[i]; break; case FFI_TYPE_POINTER: stack->gp_regs[gpcount++] = (UINT64)(PTR64) *(void **)avalue[i]; break; case FFI_TYPE_FLOAT: if (gpcount < 8 && fpcount < 8) stf_spill (&stack->fp_regs[fpcount++], *(float *)avalue[i]); { UINT32 tmp; memcpy (&tmp, avalue[i], sizeof (UINT32)); stack->gp_regs[gpcount++] = tmp; } break; case FFI_TYPE_DOUBLE: if (gpcount < 8 && fpcount < 8) stf_spill (&stack->fp_regs[fpcount++], *(double *)avalue[i]); memcpy (&stack->gp_regs[gpcount++], avalue[i], sizeof (UINT64)); break; case FFI_TYPE_LONGDOUBLE: if (gpcount & 1) gpcount++; if (LDBL_MANT_DIG == 64 && gpcount < 8 && fpcount < 8) stf_spill (&stack->fp_regs[fpcount++], *(__float80 *)avalue[i]); memcpy (&stack->gp_regs[gpcount], avalue[i], 16); gpcount += 2; break; case FFI_TYPE_STRUCT: { size_t size = (*p_arg)->size; size_t align = (*p_arg)->alignment; int hfa_type = hfa_element_type (*p_arg, 0); FFI_ASSERT (align <= 16); if (align == 16 && (gpcount & 1)) gpcount++; if (hfa_type != FFI_TYPE_VOID) { size_t hfa_size = hfa_type_size (hfa_type); size_t offset = 0; size_t gp_offset = gpcount * 8; while (fpcount < 8 && offset < size && gp_offset < 8 * 8) { hfa_type_load (&stack->fp_regs[fpcount], hfa_type, avalue[i] + offset); offset += hfa_size; gp_offset += hfa_size; fpcount += 1; } } memcpy (&stack->gp_regs[gpcount], avalue[i], size); gpcount += (size + 7) / 8; } break; default: abort (); } } ffi_call_unix (stack, rvalue, fn, cif->flags); } /* Closures represent a pair consisting of a function pointer, and some user data. A closure is invoked by reinterpreting the closure as a function pointer, and branching to it. Thus we can make an interpreted function callable as a C function: We turn the interpreter itself, together with a pointer specifying the interpreted procedure, into a closure. For IA64, function pointer are already pairs consisting of a code pointer, and a gp pointer. The latter is needed to access global variables. Here we set up such a pair as the first two words of the closure (in the "trampoline" area), but we replace the gp pointer with a pointer to the closure itself. We also add the real gp pointer to the closure. This allows the function entry code to both retrieve the user data, and to restire the correct gp pointer. */ extern void ffi_closure_unix (); ffi_status ffi_prep_closure_loc (ffi_closure* closure, ffi_cif* cif, void (*fun)(ffi_cif*,void*,void**,void*), void *user_data, void *codeloc) { /* The layout of a function descriptor. A C function pointer really points to one of these. */ struct ia64_fd { UINT64 code_pointer; UINT64 gp; }; struct ffi_ia64_trampoline_struct { UINT64 code_pointer; /* Pointer to ffi_closure_unix. */ UINT64 fake_gp; /* Pointer to closure, installed as gp. */ UINT64 real_gp; /* Real gp value. */ }; struct ffi_ia64_trampoline_struct *tramp; struct ia64_fd *fd; FFI_ASSERT (cif->abi == FFI_UNIX); tramp = (struct ffi_ia64_trampoline_struct *)closure->tramp; fd = (struct ia64_fd *)(void *)ffi_closure_unix; tramp->code_pointer = fd->code_pointer; tramp->real_gp = fd->gp; tramp->fake_gp = (UINT64)(PTR64)codeloc; closure->cif = cif; closure->user_data = user_data; closure->fun = fun; return FFI_OK; } UINT64 ffi_closure_unix_inner (ffi_closure *closure, struct ia64_args *stack, void *rvalue, void *r8) { ffi_cif *cif; void **avalue; ffi_type **p_arg; long i, avn, gpcount, fpcount; cif = closure->cif; avn = cif->nargs; avalue = alloca (avn * sizeof (void *)); /* If the structure return value is passed in memory get that location from r8 so as to pass the value directly back to the caller. */ if (cif->flags == FFI_TYPE_STRUCT) rvalue = r8; gpcount = fpcount = 0; for (i = 0, p_arg = cif->arg_types; i < avn; i++, p_arg++) { switch ((*p_arg)->type) { case FFI_TYPE_SINT8: case FFI_TYPE_UINT8: avalue[i] = endian_adjust(&stack->gp_regs[gpcount++], 1); break; case FFI_TYPE_SINT16: case FFI_TYPE_UINT16: avalue[i] = endian_adjust(&stack->gp_regs[gpcount++], 2); break; case FFI_TYPE_SINT32: case FFI_TYPE_UINT32: avalue[i] = endian_adjust(&stack->gp_regs[gpcount++], 4); break; case FFI_TYPE_SINT64: case FFI_TYPE_UINT64: avalue[i] = &stack->gp_regs[gpcount++]; break; case FFI_TYPE_POINTER: avalue[i] = endian_adjust(&stack->gp_regs[gpcount++], sizeof(void*)); break; case FFI_TYPE_FLOAT: if (gpcount < 8 && fpcount < 8) { fpreg *addr = &stack->fp_regs[fpcount++]; float result; avalue[i] = addr; ldf_fill (result, addr); *(float *)addr = result; } else avalue[i] = endian_adjust(&stack->gp_regs[gpcount], 4); gpcount++; break; case FFI_TYPE_DOUBLE: if (gpcount < 8 && fpcount < 8) { fpreg *addr = &stack->fp_regs[fpcount++]; double result; avalue[i] = addr; ldf_fill (result, addr); *(double *)addr = result; } else avalue[i] = &stack->gp_regs[gpcount]; gpcount++; break; case FFI_TYPE_LONGDOUBLE: if (gpcount & 1) gpcount++; if (LDBL_MANT_DIG == 64 && gpcount < 8 && fpcount < 8) { fpreg *addr = &stack->fp_regs[fpcount++]; __float80 result; avalue[i] = addr; ldf_fill (result, addr); *(__float80 *)addr = result; } else avalue[i] = &stack->gp_regs[gpcount]; gpcount += 2; break; case FFI_TYPE_STRUCT: { size_t size = (*p_arg)->size; size_t align = (*p_arg)->alignment; int hfa_type = hfa_element_type (*p_arg, 0); FFI_ASSERT (align <= 16); if (align == 16 && (gpcount & 1)) gpcount++; if (hfa_type != FFI_TYPE_VOID) { size_t hfa_size = hfa_type_size (hfa_type); size_t offset = 0; size_t gp_offset = gpcount * 8; void *addr = alloca (size); avalue[i] = addr; while (fpcount < 8 && offset < size && gp_offset < 8 * 8) { hfa_type_store (hfa_type, addr + offset, &stack->fp_regs[fpcount]); offset += hfa_size; gp_offset += hfa_size; fpcount += 1; } if (offset < size) memcpy (addr + offset, (char *)stack->gp_regs + gp_offset, size - offset); } else avalue[i] = &stack->gp_regs[gpcount]; gpcount += (size + 7) / 8; } break; default: abort (); } } closure->fun (cif, rvalue, avalue, closure->user_data); return cif->flags; } smalltalk-3.2.5/libffi/src/powerpc/0000755000175000017500000000000012130456004014202 500000000000000smalltalk-3.2.5/libffi/src/powerpc/asm.h0000644000175000017500000001032612130343734015062 00000000000000/* ----------------------------------------------------------------------- asm.h - Copyright (c) 1998 Geoffrey Keating PowerPC Assembly glue. Permission is hereby granted, free of charge, to any person obtaining a copy of this software and associated documentation files (the ``Software''), to deal in the Software without restriction, including without limitation the rights to use, copy, modify, merge, publish, distribute, sublicense, and/or sell copies of the Software, and to permit persons to whom the Software is furnished to do so, subject to the following conditions: The above copyright notice and this permission notice shall be included in all copies or substantial portions of the Software. THE SOFTWARE IS PROVIDED ``AS IS'', WITHOUT WARRANTY OF ANY KIND, EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHOR BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. ----------------------------------------------------------------------- */ #define ASM_GLOBAL_DIRECTIVE .globl #define C_SYMBOL_NAME(name) name /* Macro for a label. */ #ifdef __STDC__ #define C_LABEL(name) name##: #else #define C_LABEL(name) name/**/: #endif /* This seems to always be the case on PPC. */ #define ALIGNARG(log2) log2 /* For ELF we need the `.type' directive to make shared libs work right. */ #define ASM_TYPE_DIRECTIVE(name,typearg) .type name,typearg; #define ASM_SIZE_DIRECTIVE(name) .size name,.-name /* If compiled for profiling, call `_mcount' at the start of each function. */ #ifdef PROF /* The mcount code relies on a the return address being on the stack to locate our caller and so it can restore it; so store one just for its benefit. */ #ifdef PIC #define CALL_MCOUNT \ .pushsection; \ .section ".data"; \ .align ALIGNARG(2); \ 0:.long 0; \ .previous; \ mflr %r0; \ stw %r0,4(%r1); \ bl _GLOBAL_OFFSET_TABLE_@local-4; \ mflr %r11; \ lwz %r0,0b@got(%r11); \ bl JUMPTARGET(_mcount); #else /* PIC */ #define CALL_MCOUNT \ .section ".data"; \ .align ALIGNARG(2); \ 0:.long 0; \ .previous; \ mflr %r0; \ lis %r11,0b@ha; \ stw %r0,4(%r1); \ addi %r0,%r11,0b@l; \ bl JUMPTARGET(_mcount); #endif /* PIC */ #else /* PROF */ #define CALL_MCOUNT /* Do nothing. */ #endif /* PROF */ #define ENTRY(name) \ ASM_GLOBAL_DIRECTIVE C_SYMBOL_NAME(name); \ ASM_TYPE_DIRECTIVE (C_SYMBOL_NAME(name),@function) \ .align ALIGNARG(2); \ C_LABEL(name) \ CALL_MCOUNT #define EALIGN_W_0 /* No words to insert. */ #define EALIGN_W_1 nop #define EALIGN_W_2 nop;nop #define EALIGN_W_3 nop;nop;nop #define EALIGN_W_4 EALIGN_W_3;nop #define EALIGN_W_5 EALIGN_W_4;nop #define EALIGN_W_6 EALIGN_W_5;nop #define EALIGN_W_7 EALIGN_W_6;nop /* EALIGN is like ENTRY, but does alignment to 'words'*4 bytes past a 2^align boundary. */ #ifdef PROF #define EALIGN(name, alignt, words) \ ASM_GLOBAL_DIRECTIVE C_SYMBOL_NAME(name); \ ASM_TYPE_DIRECTIVE (C_SYMBOL_NAME(name),@function) \ .align ALIGNARG(2); \ C_LABEL(name) \ CALL_MCOUNT \ b 0f; \ .align ALIGNARG(alignt); \ EALIGN_W_##words; \ 0: #else /* PROF */ #define EALIGN(name, alignt, words) \ ASM_GLOBAL_DIRECTIVE C_SYMBOL_NAME(name); \ ASM_TYPE_DIRECTIVE (C_SYMBOL_NAME(name),@function) \ .align ALIGNARG(alignt); \ EALIGN_W_##words; \ C_LABEL(name) #endif #define END(name) \ ASM_SIZE_DIRECTIVE(name) #ifdef PIC #define JUMPTARGET(name) name##@plt #else #define JUMPTARGET(name) name #endif /* Local labels stripped out by the linker. */ #define L(x) .L##x smalltalk-3.2.5/libffi/src/powerpc/linux64.S0000644000175000017500000001156512130343734015574 00000000000000/* ----------------------------------------------------------------------- sysv.h - Copyright (c) 2003 Jakub Jelinek Copyright (c) 2008 Red Hat, Inc. PowerPC64 Assembly glue. Permission is hereby granted, free of charge, to any person obtaining a copy of this software and associated documentation files (the ``Software''), to deal in the Software without restriction, including without limitation the rights to use, copy, modify, merge, publish, distribute, sublicense, and/or sell copies of the Software, and to permit persons to whom the Software is furnished to do so, subject to the following conditions: The above copyright notice and this permission notice shall be included in all copies or substantial portions of the Software. THE SOFTWARE IS PROVIDED ``AS IS'', WITHOUT WARRANTY OF ANY KIND, EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. ----------------------------------------------------------------------- */ #define LIBFFI_ASM #include #include #ifdef __powerpc64__ .hidden ffi_call_LINUX64, .ffi_call_LINUX64 .globl ffi_call_LINUX64, .ffi_call_LINUX64 .section ".opd","aw" .align 3 ffi_call_LINUX64: .quad .ffi_call_LINUX64,.TOC.@tocbase,0 .size ffi_call_LINUX64,24 .type .ffi_call_LINUX64,@function .text .ffi_call_LINUX64: .LFB1: mflr %r0 std %r28, -32(%r1) std %r29, -24(%r1) std %r30, -16(%r1) std %r31, -8(%r1) std %r0, 16(%r1) mr %r28, %r1 /* our AP. */ .LCFI0: stdux %r1, %r1, %r4 mr %r31, %r5 /* flags, */ mr %r30, %r6 /* rvalue, */ mr %r29, %r7 /* function address. */ std %r2, 40(%r1) /* Call ffi_prep_args64. */ mr %r4, %r1 bl .ffi_prep_args64 ld %r0, 0(%r29) ld %r2, 8(%r29) ld %r11, 16(%r29) /* Now do the call. */ /* Set up cr1 with bits 4-7 of the flags. */ mtcrf 0x40, %r31 /* Get the address to call into CTR. */ mtctr %r0 /* Load all those argument registers. */ ld %r3, -32-(8*8)(%r28) ld %r4, -32-(7*8)(%r28) ld %r5, -32-(6*8)(%r28) ld %r6, -32-(5*8)(%r28) bf- 5, 1f ld %r7, -32-(4*8)(%r28) ld %r8, -32-(3*8)(%r28) ld %r9, -32-(2*8)(%r28) ld %r10, -32-(1*8)(%r28) 1: /* Load all the FP registers. */ bf- 6, 2f lfd %f1, -32-(21*8)(%r28) lfd %f2, -32-(20*8)(%r28) lfd %f3, -32-(19*8)(%r28) lfd %f4, -32-(18*8)(%r28) lfd %f5, -32-(17*8)(%r28) lfd %f6, -32-(16*8)(%r28) lfd %f7, -32-(15*8)(%r28) lfd %f8, -32-(14*8)(%r28) lfd %f9, -32-(13*8)(%r28) lfd %f10, -32-(12*8)(%r28) lfd %f11, -32-(11*8)(%r28) lfd %f12, -32-(10*8)(%r28) lfd %f13, -32-(9*8)(%r28) 2: /* Make the call. */ bctrl /* This must follow the call immediately, the unwinder uses this to find out if r2 has been saved or not. */ ld %r2, 40(%r1) /* Now, deal with the return value. */ mtcrf 0x01, %r31 bt- 30, .Ldone_return_value bt- 29, .Lfp_return_value std %r3, 0(%r30) /* Fall through... */ .Ldone_return_value: /* Restore the registers we used and return. */ mr %r1, %r28 ld %r0, 16(%r28) ld %r28, -32(%r1) mtlr %r0 ld %r29, -24(%r1) ld %r30, -16(%r1) ld %r31, -8(%r1) blr .Lfp_return_value: bf 28, .Lfloat_return_value stfd %f1, 0(%r30) mtcrf 0x02, %r31 /* cr6 */ bf 27, .Ldone_return_value stfd %f2, 8(%r30) b .Ldone_return_value .Lfloat_return_value: stfs %f1, 0(%r30) b .Ldone_return_value .LFE1: .long 0 .byte 0,12,0,1,128,4,0,0 .size .ffi_call_LINUX64,.-.ffi_call_LINUX64 .section .eh_frame,EH_FRAME_FLAGS,@progbits .Lframe1: .4byte .LECIE1-.LSCIE1 # Length of Common Information Entry .LSCIE1: .4byte 0x0 # CIE Identifier Tag .byte 0x1 # CIE Version .ascii "zR\0" # CIE Augmentation .uleb128 0x1 # CIE Code Alignment Factor .sleb128 -8 # CIE Data Alignment Factor .byte 0x41 # CIE RA Column .uleb128 0x1 # Augmentation size .byte 0x14 # FDE Encoding (pcrel udata8) .byte 0xc # DW_CFA_def_cfa .uleb128 0x1 .uleb128 0x0 .align 3 .LECIE1: .LSFDE1: .4byte .LEFDE1-.LASFDE1 # FDE Length .LASFDE1: .4byte .LASFDE1-.Lframe1 # FDE CIE offset .8byte .LFB1-. # FDE initial location .8byte .LFE1-.LFB1 # FDE address range .uleb128 0x0 # Augmentation size .byte 0x2 # DW_CFA_advance_loc1 .byte .LCFI0-.LFB1 .byte 0xd # DW_CFA_def_cfa_register .uleb128 0x1c .byte 0x11 # DW_CFA_offset_extended_sf .uleb128 0x41 .sleb128 -2 .byte 0x9f # DW_CFA_offset, column 0x1f .uleb128 0x1 .byte 0x9e # DW_CFA_offset, column 0x1e .uleb128 0x2 .byte 0x9d # DW_CFA_offset, column 0x1d .uleb128 0x3 .byte 0x9c # DW_CFA_offset, column 0x1c .uleb128 0x4 .align 3 .LEFDE1: #endif #if defined __ELF__ && defined __linux__ .section .note.GNU-stack,"",@progbits #endif smalltalk-3.2.5/libffi/src/powerpc/ffi_darwin.c0000644000175000017500000006274112130343734016415 00000000000000/* ----------------------------------------------------------------------- ffi_darwin.c Copyright (C) 1998 Geoffrey Keating Copyright (C) 2001 John Hornkvist Copyright (C) 2002, 2006, 2007, 2009 Free Software Foundation, Inc. FFI support for Darwin and AIX. Permission is hereby granted, free of charge, to any person obtaining a copy of this software and associated documentation files (the ``Software''), to deal in the Software without restriction, including without limitation the rights to use, copy, modify, merge, publish, distribute, sublicense, and/or sell copies of the Software, and to permit persons to whom the Software is furnished to do so, subject to the following conditions: The above copyright notice and this permission notice shall be included in all copies or substantial portions of the Software. THE SOFTWARE IS PROVIDED ``AS IS'', WITHOUT WARRANTY OF ANY KIND, EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHOR BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. ----------------------------------------------------------------------- */ #include #include #include extern void ffi_closure_ASM (void); enum { /* The assembly depends on these exact flags. */ FLAG_RETURNS_NOTHING = 1 << (31-30), /* These go in cr7 */ FLAG_RETURNS_FP = 1 << (31-29), FLAG_RETURNS_64BITS = 1 << (31-28), FLAG_RETURNS_128BITS = 1 << (31-31), FLAG_ARG_NEEDS_COPY = 1 << (31- 7), FLAG_FP_ARGUMENTS = 1 << (31- 6), /* cr1.eq; specified by ABI */ FLAG_4_GPR_ARGUMENTS = 1 << (31- 5), FLAG_RETVAL_REFERENCE = 1 << (31- 4) }; /* About the DARWIN ABI. */ enum { NUM_GPR_ARG_REGISTERS = 8, NUM_FPR_ARG_REGISTERS = 13 }; enum { ASM_NEEDS_REGISTERS = 4 }; /* ffi_prep_args is called by the assembly routine once stack space has been allocated for the function's arguments. The stack layout we want looks like this: | Return address from ffi_call_DARWIN | higher addresses |--------------------------------------------| | Previous backchain pointer 4 | stack pointer here |--------------------------------------------|<+ <<< on entry to | Saved r28-r31 4*4 | | ffi_call_DARWIN |--------------------------------------------| | | Parameters (at least 8*4=32) | | |--------------------------------------------| | | Space for GPR2 4 | | |--------------------------------------------| | stack | | Reserved 2*4 | | grows | |--------------------------------------------| | down V | Space for callee's LR 4 | | |--------------------------------------------| | lower addresses | Saved CR 4 | | |--------------------------------------------| | stack pointer here | Current backchain pointer 4 |-/ during |--------------------------------------------| <<< ffi_call_DARWIN */ void ffi_prep_args (extended_cif *ecif, unsigned long *const stack) { const unsigned bytes = ecif->cif->bytes; const unsigned flags = ecif->cif->flags; const unsigned nargs = ecif->cif->nargs; const ffi_abi abi = ecif->cif->abi; /* 'stacktop' points at the previous backchain pointer. */ unsigned long *const stacktop = stack + (bytes / sizeof(unsigned long)); /* 'fpr_base' points at the space for fpr1, and grows upwards as we use FPR registers. */ double *fpr_base = (double *) (stacktop - ASM_NEEDS_REGISTERS) - NUM_FPR_ARG_REGISTERS; int fparg_count = 0; /* 'next_arg' grows up as we put parameters in it. */ unsigned long *next_arg = stack + 6; /* 6 reserved positions. */ int i; double double_tmp; void **p_argv = ecif->avalue; unsigned long gprvalue; ffi_type** ptr = ecif->cif->arg_types; char *dest_cpy; unsigned size_al = 0; /* Check that everything starts aligned properly. */ FFI_ASSERT(((unsigned) (char *) stack & 0xF) == 0); FFI_ASSERT(((unsigned) (char *) stacktop & 0xF) == 0); FFI_ASSERT((bytes & 0xF) == 0); /* Deal with return values that are actually pass-by-reference. Rule: Return values are referenced by r3, so r4 is the first parameter. */ if (flags & FLAG_RETVAL_REFERENCE) *next_arg++ = (unsigned long) (char *) ecif->rvalue; /* Now for the arguments. */ for (i = nargs; i > 0; i--, ptr++, p_argv++) { switch ((*ptr)->type) { /* If a floating-point parameter appears before all of the general- purpose registers are filled, the corresponding GPRs that match the size of the floating-point parameter are skipped. */ case FFI_TYPE_FLOAT: double_tmp = *(float *) *p_argv; if (fparg_count >= NUM_FPR_ARG_REGISTERS) *(double *)next_arg = double_tmp; else *fpr_base++ = double_tmp; next_arg++; fparg_count++; FFI_ASSERT(flags & FLAG_FP_ARGUMENTS); break; case FFI_TYPE_DOUBLE: double_tmp = *(double *) *p_argv; if (fparg_count >= NUM_FPR_ARG_REGISTERS) *(double *)next_arg = double_tmp; else *fpr_base++ = double_tmp; #ifdef POWERPC64 next_arg++; #else next_arg += 2; #endif fparg_count++; FFI_ASSERT(flags & FLAG_FP_ARGUMENTS); break; #if FFI_TYPE_LONGDOUBLE != FFI_TYPE_DOUBLE case FFI_TYPE_LONGDOUBLE: #ifdef POWERPC64 if (fparg_count < NUM_FPR_ARG_REGISTERS) *(long double *) fpr_base++ = *(long double *) *p_argv; else *(long double *) next_arg = *(long double *) *p_argv; next_arg += 2; fparg_count += 2; #else double_tmp = ((double *) *p_argv)[0]; if (fparg_count < NUM_FPR_ARG_REGISTERS) *fpr_base++ = double_tmp; else *(double *) next_arg = double_tmp; next_arg += 2; fparg_count++; double_tmp = ((double *) *p_argv)[1]; if (fparg_count < NUM_FPR_ARG_REGISTERS) *fpr_base++ = double_tmp; else *(double *) next_arg = double_tmp; next_arg += 2; fparg_count++; #endif FFI_ASSERT(flags & FLAG_FP_ARGUMENTS); break; #endif case FFI_TYPE_UINT64: case FFI_TYPE_SINT64: #ifdef POWERPC64 gprvalue = *(long long *) *p_argv; goto putgpr; #else *(long long *) next_arg = *(long long *) *p_argv; next_arg += 2; #endif break; case FFI_TYPE_POINTER: gprvalue = *(unsigned long *) *p_argv; goto putgpr; case FFI_TYPE_UINT8: gprvalue = *(unsigned char *) *p_argv; goto putgpr; case FFI_TYPE_SINT8: gprvalue = *(signed char *) *p_argv; goto putgpr; case FFI_TYPE_UINT16: gprvalue = *(unsigned short *) *p_argv; goto putgpr; case FFI_TYPE_SINT16: gprvalue = *(signed short *) *p_argv; goto putgpr; case FFI_TYPE_STRUCT: #ifdef POWERPC64 dest_cpy = (char *) next_arg; size_al = (*ptr)->size; if ((*ptr)->elements[0]->type == 3) size_al = ALIGN((*ptr)->size, 8); if (size_al < 3 && abi == FFI_DARWIN) dest_cpy += 4 - size_al; memcpy ((char *) dest_cpy, (char *) *p_argv, size_al); next_arg += (size_al + 7) / 8; #else dest_cpy = (char *) next_arg; /* Structures that match the basic modes (QI 1 byte, HI 2 bytes, SI 4 bytes) are aligned as if they were those modes. Structures with 3 byte in size are padded upwards. */ size_al = (*ptr)->size; /* If the first member of the struct is a double, then align the struct to double-word. */ if ((*ptr)->elements[0]->type == FFI_TYPE_DOUBLE) size_al = ALIGN((*ptr)->size, 8); if (size_al < 3 && abi == FFI_DARWIN) dest_cpy += 4 - size_al; memcpy((char *) dest_cpy, (char *) *p_argv, size_al); next_arg += (size_al + 3) / 4; #endif break; case FFI_TYPE_INT: case FFI_TYPE_SINT32: gprvalue = *(signed int *) *p_argv; goto putgpr; case FFI_TYPE_UINT32: gprvalue = *(unsigned int *) *p_argv; putgpr: *next_arg++ = gprvalue; break; default: break; } } /* Check that we didn't overrun the stack... */ //FFI_ASSERT(gpr_base <= stacktop - ASM_NEEDS_REGISTERS); //FFI_ASSERT((unsigned *)fpr_base // <= stacktop - ASM_NEEDS_REGISTERS - NUM_GPR_ARG_REGISTERS); //FFI_ASSERT(flags & FLAG_4_GPR_ARGUMENTS || intarg_count <= 4); } /* Adjust the size of S to be correct for Darwin. On Darwin, the first field of a structure has natural alignment. */ static void darwin_adjust_aggregate_sizes (ffi_type *s) { int i; if (s->type != FFI_TYPE_STRUCT) return; s->size = 0; for (i = 0; s->elements[i] != NULL; i++) { ffi_type *p; int align; p = s->elements[i]; darwin_adjust_aggregate_sizes (p); if (i == 0 && (p->type == FFI_TYPE_UINT64 || p->type == FFI_TYPE_SINT64 || p->type == FFI_TYPE_DOUBLE || p->alignment == 8)) align = 8; else if (p->alignment == 16 || p->alignment < 4) align = p->alignment; else align = 4; s->size = ALIGN(s->size, align) + p->size; } s->size = ALIGN(s->size, s->alignment); if (s->elements[0]->type == FFI_TYPE_UINT64 || s->elements[0]->type == FFI_TYPE_SINT64 || s->elements[0]->type == FFI_TYPE_DOUBLE || s->elements[0]->alignment == 8) s->alignment = s->alignment > 8 ? s->alignment : 8; /* Do not add additional tail padding. */ } /* Adjust the size of S to be correct for AIX. Word-align double unless it is the first member of a structure. */ static void aix_adjust_aggregate_sizes (ffi_type *s) { int i; if (s->type != FFI_TYPE_STRUCT) return; s->size = 0; for (i = 0; s->elements[i] != NULL; i++) { ffi_type *p; int align; p = s->elements[i]; aix_adjust_aggregate_sizes (p); align = p->alignment; if (i != 0 && p->type == FFI_TYPE_DOUBLE) align = 4; s->size = ALIGN(s->size, align) + p->size; } s->size = ALIGN(s->size, s->alignment); if (s->elements[0]->type == FFI_TYPE_UINT64 || s->elements[0]->type == FFI_TYPE_SINT64 || s->elements[0]->type == FFI_TYPE_DOUBLE || s->elements[0]->alignment == 8) s->alignment = s->alignment > 8 ? s->alignment : 8; /* Do not add additional tail padding. */ } /* Perform machine dependent cif processing. */ ffi_status ffi_prep_cif_machdep (ffi_cif *cif) { /* All this is for the DARWIN ABI. */ unsigned i; ffi_type **ptr; unsigned bytes; int fparg_count = 0, intarg_count = 0; unsigned flags = 0; unsigned size_al = 0; /* All the machine-independent calculation of cif->bytes will be wrong. All the calculation of structure sizes will also be wrong. Redo the calculation for DARWIN. */ if (cif->abi == FFI_DARWIN) { darwin_adjust_aggregate_sizes (cif->rtype); for (i = 0; i < cif->nargs; i++) darwin_adjust_aggregate_sizes (cif->arg_types[i]); } if (cif->abi == FFI_AIX) { aix_adjust_aggregate_sizes (cif->rtype); for (i = 0; i < cif->nargs; i++) aix_adjust_aggregate_sizes (cif->arg_types[i]); } /* Space for the frame pointer, callee's LR, CR, etc, and for the asm's temp regs. */ bytes = (6 + ASM_NEEDS_REGISTERS) * sizeof(long); /* Return value handling. The rules are as follows: - 32-bit (or less) integer values are returned in gpr3; - Structures of size <= 4 bytes also returned in gpr3; - 64-bit integer values and structures between 5 and 8 bytes are returned in gpr3 and gpr4; - Single/double FP values are returned in fpr1; - Long double FP (if not equivalent to double) values are returned in fpr1 and fpr2; - Larger structures values are allocated space and a pointer is passed as the first argument. */ switch (cif->rtype->type) { #if FFI_TYPE_LONGDOUBLE != FFI_TYPE_DOUBLE case FFI_TYPE_LONGDOUBLE: flags |= FLAG_RETURNS_128BITS; flags |= FLAG_RETURNS_FP; break; #endif case FFI_TYPE_DOUBLE: flags |= FLAG_RETURNS_64BITS; /* Fall through. */ case FFI_TYPE_FLOAT: flags |= FLAG_RETURNS_FP; break; case FFI_TYPE_UINT64: case FFI_TYPE_SINT64: #ifdef POWERPC64 case FFI_TYPE_POINTER: #endif flags |= FLAG_RETURNS_64BITS; break; case FFI_TYPE_STRUCT: flags |= FLAG_RETVAL_REFERENCE; flags |= FLAG_RETURNS_NOTHING; intarg_count++; break; case FFI_TYPE_VOID: flags |= FLAG_RETURNS_NOTHING; break; default: /* Returns 32-bit integer, or similar. Nothing to do here. */ break; } /* The first NUM_GPR_ARG_REGISTERS words of integer arguments, and the first NUM_FPR_ARG_REGISTERS fp arguments, go in registers; the rest goes on the stack. Structures are passed as a pointer to a copy of the structure. Stuff on the stack needs to keep proper alignment. */ for (ptr = cif->arg_types, i = cif->nargs; i > 0; i--, ptr++) { switch ((*ptr)->type) { case FFI_TYPE_FLOAT: case FFI_TYPE_DOUBLE: fparg_count++; /* If this FP arg is going on the stack, it must be 8-byte-aligned. */ if (fparg_count > NUM_FPR_ARG_REGISTERS && intarg_count%2 != 0) intarg_count++; break; #if FFI_TYPE_LONGDOUBLE != FFI_TYPE_DOUBLE case FFI_TYPE_LONGDOUBLE: fparg_count += 2; /* If this FP arg is going on the stack, it must be 8-byte-aligned. */ if (fparg_count > NUM_FPR_ARG_REGISTERS && intarg_count%2 != 0) intarg_count++; intarg_count +=2; break; #endif case FFI_TYPE_UINT64: case FFI_TYPE_SINT64: /* 'long long' arguments are passed as two words, but either both words must fit in registers or both go on the stack. If they go on the stack, they must be 8-byte-aligned. */ if (intarg_count == NUM_GPR_ARG_REGISTERS-1 || (intarg_count >= NUM_GPR_ARG_REGISTERS && intarg_count%2 != 0)) intarg_count++; intarg_count += 2; break; case FFI_TYPE_STRUCT: size_al = (*ptr)->size; /* If the first member of the struct is a double, then align the struct to double-word. */ if ((*ptr)->elements[0]->type == FFI_TYPE_DOUBLE) size_al = ALIGN((*ptr)->size, 8); #ifdef POWERPC64 intarg_count += (size_al + 7) / 8; #else intarg_count += (size_al + 3) / 4; #endif break; default: /* Everything else is passed as a 4-byte word in a GPR, either the object itself or a pointer to it. */ intarg_count++; break; } } if (fparg_count != 0) flags |= FLAG_FP_ARGUMENTS; /* Space for the FPR registers, if needed. */ if (fparg_count != 0) bytes += NUM_FPR_ARG_REGISTERS * sizeof(double); /* Stack space. */ #ifdef POWERPC64 if ((intarg_count + fparg_count) > NUM_GPR_ARG_REGISTERS) bytes += (intarg_count + fparg_count) * sizeof(long); #else if ((intarg_count + 2 * fparg_count) > NUM_GPR_ARG_REGISTERS) bytes += (intarg_count + 2 * fparg_count) * sizeof(long); #endif else bytes += NUM_GPR_ARG_REGISTERS * sizeof(long); /* The stack space allocated needs to be a multiple of 16 bytes. */ bytes = (bytes + 15) & ~0xF; cif->flags = flags; cif->bytes = bytes; return FFI_OK; } extern void ffi_call_AIX(extended_cif *, long, unsigned, unsigned *, void (*fn)(void), void (*fn2)(void)); extern void ffi_call_DARWIN(extended_cif *, long, unsigned, unsigned *, void (*fn)(void), void (*fn2)(void)); void ffi_call (ffi_cif *cif, void (*fn)(void), void *rvalue, void **avalue) { extended_cif ecif; ecif.cif = cif; ecif.avalue = avalue; /* If the return value is a struct and we don't have a return value address then we need to make one. */ if ((rvalue == NULL) && (cif->rtype->type == FFI_TYPE_STRUCT)) { ecif.rvalue = alloca (cif->rtype->size); } else ecif.rvalue = rvalue; switch (cif->abi) { case FFI_AIX: ffi_call_AIX(&ecif, -(long)cif->bytes, cif->flags, ecif.rvalue, fn, FFI_FN(ffi_prep_args)); break; case FFI_DARWIN: ffi_call_DARWIN(&ecif, -(long)cif->bytes, cif->flags, ecif.rvalue, fn, FFI_FN(ffi_prep_args)); break; default: FFI_ASSERT(0); break; } } static void flush_icache(char *); static void flush_range(char *, int); /* The layout of a function descriptor. A C function pointer really points to one of these. */ typedef struct aix_fd_struct { void *code_pointer; void *toc; } aix_fd; /* here I'd like to add the stack frame layout we use in darwin_closure.S and aix_clsoure.S SP previous -> +---------------------------------------+ <--- child frame | back chain to caller 4 | +---------------------------------------+ 4 | saved CR 4 | +---------------------------------------+ 8 | saved LR 4 | +---------------------------------------+ 12 | reserved for compilers 4 | +---------------------------------------+ 16 | reserved for binders 4 | +---------------------------------------+ 20 | saved TOC pointer 4 | +---------------------------------------+ 24 | always reserved 8*4=32 (previous GPRs)| | according to the linkage convention | | from AIX | +---------------------------------------+ 56 | our FPR area 13*8=104 | | f1 | | . | | f13 | +---------------------------------------+ 160 | result area 8 | +---------------------------------------+ 168 | alignement to the next multiple of 16 | SP current --> +---------------------------------------+ 176 <- parent frame | back chain to caller 4 | +---------------------------------------+ 180 | saved CR 4 | +---------------------------------------+ 184 | saved LR 4 | +---------------------------------------+ 188 | reserved for compilers 4 | +---------------------------------------+ 192 | reserved for binders 4 | +---------------------------------------+ 196 | saved TOC pointer 4 | +---------------------------------------+ 200 | always reserved 8*4=32 we store our | | GPRs here | | r3 | | . | | r10 | +---------------------------------------+ 232 | overflow part | +---------------------------------------+ xxx | ???? | +---------------------------------------+ xxx */ ffi_status ffi_prep_closure_loc (ffi_closure* closure, ffi_cif* cif, void (*fun)(ffi_cif*, void*, void**, void*), void *user_data, void *codeloc) { unsigned int *tramp; struct ffi_aix_trampoline_struct *tramp_aix; aix_fd *fd; switch (cif->abi) { case FFI_DARWIN: FFI_ASSERT (cif->abi == FFI_DARWIN); tramp = (unsigned int *) &closure->tramp[0]; tramp[0] = 0x7c0802a6; /* mflr r0 */ tramp[1] = 0x429f000d; /* bcl- 20,4*cr7+so,0x10 */ tramp[4] = 0x7d6802a6; /* mflr r11 */ tramp[5] = 0x818b0000; /* lwz r12,0(r11) function address */ tramp[6] = 0x7c0803a6; /* mtlr r0 */ tramp[7] = 0x7d8903a6; /* mtctr r12 */ tramp[8] = 0x816b0004; /* lwz r11,4(r11) static chain */ tramp[9] = 0x4e800420; /* bctr */ tramp[2] = (unsigned long) ffi_closure_ASM; /* function */ tramp[3] = (unsigned long) codeloc; /* context */ closure->cif = cif; closure->fun = fun; closure->user_data = user_data; /* Flush the icache. Only necessary on Darwin. */ flush_range(codeloc, FFI_TRAMPOLINE_SIZE); break; case FFI_AIX: tramp_aix = (struct ffi_aix_trampoline_struct *) (closure->tramp); fd = (aix_fd *)(void *)ffi_closure_ASM; FFI_ASSERT (cif->abi == FFI_AIX); tramp_aix->code_pointer = fd->code_pointer; tramp_aix->toc = fd->toc; tramp_aix->static_chain = codeloc; closure->cif = cif; closure->fun = fun; closure->user_data = user_data; default: FFI_ASSERT(0); break; } return FFI_OK; } static void flush_icache(char *addr) { #ifndef _AIX __asm__ volatile ( "dcbf 0,%0\n" "\tsync\n" "\ticbi 0,%0\n" "\tsync\n" "\tisync" : : "r"(addr) : "memory"); #endif } static void flush_range(char * addr1, int size) { #define MIN_LINE_SIZE 32 int i; for (i = 0; i < size; i += MIN_LINE_SIZE) flush_icache(addr1+i); flush_icache(addr1+size-1); } typedef union { float f; double d; } ffi_dblfl; int ffi_closure_helper_DARWIN (ffi_closure *, void *, unsigned long *, ffi_dblfl *); /* Basically the trampoline invokes ffi_closure_ASM, and on entry, r11 holds the address of the closure. After storing the registers that could possibly contain parameters to be passed into the stack frame and setting up space for a return value, ffi_closure_ASM invokes the following helper function to do most of the work. */ int ffi_closure_helper_DARWIN (ffi_closure *closure, void *rvalue, unsigned long *pgr, ffi_dblfl *pfr) { /* rvalue is the pointer to space for return value in closure assembly pgr is the pointer to where r3-r10 are stored in ffi_closure_ASM pfr is the pointer to where f1-f13 are stored in ffi_closure_ASM. */ typedef double ldbits[2]; union ldu { ldbits lb; long double ld; }; void ** avalue; ffi_type ** arg_types; long i, avn; ffi_cif * cif; ffi_dblfl * end_pfr = pfr + NUM_FPR_ARG_REGISTERS; unsigned size_al; cif = closure->cif; avalue = alloca (cif->nargs * sizeof(void *)); /* Copy the caller's structure return value address so that the closure returns the data directly to the caller. */ if (cif->rtype->type == FFI_TYPE_STRUCT) { rvalue = (void *) *pgr; pgr++; } i = 0; avn = cif->nargs; arg_types = cif->arg_types; /* Grab the addresses of the arguments from the stack frame. */ while (i < avn) { switch (arg_types[i]->type) { case FFI_TYPE_SINT8: case FFI_TYPE_UINT8: #ifdef POWERPC64 avalue[i] = (char *) pgr + 7; #else avalue[i] = (char *) pgr + 3; #endif pgr++; break; case FFI_TYPE_SINT16: case FFI_TYPE_UINT16: #ifdef POWERPC64 avalue[i] = (char *) pgr + 6; #else avalue[i] = (char *) pgr + 2; #endif pgr++; break; case FFI_TYPE_SINT32: case FFI_TYPE_UINT32: #ifdef POWERPC64 avalue[i] = (char *) pgr + 4; #else case FFI_TYPE_POINTER: avalue[i] = pgr; #endif pgr++; break; case FFI_TYPE_STRUCT: #ifdef POWERPC64 size_al = arg_types[i]->size; if (arg_types[i]->elements[0]->type == FFI_TYPE_DOUBLE) size_al = ALIGN (arg_types[i]->size, 8); if (size_al < 3 && cif->abi == FFI_DARWIN) avalue[i] = (char *) pgr + 8 - size_al; else avalue[i] = pgr; pgr += (size_al + 7) / 8; #else /* Structures that match the basic modes (QI 1 byte, HI 2 bytes, SI 4 bytes) are aligned as if they were those modes. */ size_al = arg_types[i]->size; /* If the first member of the struct is a double, then align the struct to double-word. */ if (arg_types[i]->elements[0]->type == FFI_TYPE_DOUBLE) size_al = ALIGN(arg_types[i]->size, 8); if (size_al < 3 && cif->abi == FFI_DARWIN) avalue[i] = (char*) pgr + 4 - size_al; else avalue[i] = pgr; pgr += (size_al + 3) / 4; #endif break; case FFI_TYPE_SINT64: case FFI_TYPE_UINT64: #ifdef POWERPC64 case FFI_TYPE_POINTER: avalue[i] = pgr; pgr++; break; #else /* Long long ints are passed in two gpr's. */ avalue[i] = pgr; pgr += 2; break; #endif case FFI_TYPE_FLOAT: /* A float value consumes a GPR. There are 13 64bit floating point registers. */ if (pfr < end_pfr) { double temp = pfr->d; pfr->f = (float) temp; avalue[i] = pfr; pfr++; } else { avalue[i] = pgr; } pgr++; break; case FFI_TYPE_DOUBLE: /* A double value consumes two GPRs. There are 13 64bit floating point registers. */ if (pfr < end_pfr) { avalue[i] = pfr; pfr++; } else { avalue[i] = pgr; } #ifdef POWERPC64 pgr++; #else pgr += 2; #endif break; #if FFI_TYPE_LONGDOUBLE != FFI_TYPE_DOUBLE case FFI_TYPE_LONGDOUBLE: #ifdef POWERPC64 if (pfr + 1 < end_pfr) { avalue[i] = pfr; pfr += 2; } else { if (pfr < end_pfr) { *pgr = *(unsigned long *) pfr; pfr++; } avalue[i] = pgr; } pgr += 2; #else /* POWERPC64 */ /* A long double value consumes four GPRs and two FPRs. There are 13 64bit floating point registers. */ if (pfr + 1 < end_pfr) { avalue[i] = pfr; pfr += 2; } /* Here we have the situation where one part of the long double is stored in fpr13 and the other part is already on the stack. We use a union to pass the long double to avalue[i]. */ else if (pfr + 1 == end_pfr) { union ldu temp_ld; memcpy (&temp_ld.lb[0], pfr, sizeof(ldbits)); memcpy (&temp_ld.lb[1], pgr + 2, sizeof(ldbits)); avalue[i] = &temp_ld.ld; pfr++; } else { avalue[i] = pgr; } pgr += 4; #endif /* POWERPC64 */ break; #endif default: FFI_ASSERT(0); } i++; } (closure->fun) (cif, rvalue, avalue, closure->user_data); /* Tell ffi_closure_ASM to perform return type promotions. */ return cif->rtype->type; } smalltalk-3.2.5/libffi/src/powerpc/aix.S0000644000175000017500000001475312130343734015046 00000000000000/* ----------------------------------------------------------------------- aix.S - Copyright (c) 2002,2009 Free Software Foundation, Inc. based on darwin.S by John Hornkvist PowerPC Assembly glue. Permission is hereby granted, free of charge, to any person obtaining a copy of this software and associated documentation files (the ``Software''), to deal in the Software without restriction, including without limitation the rights to use, copy, modify, merge, publish, distribute, sublicense, and/or sell copies of the Software, and to permit persons to whom the Software is furnished to do so, subject to the following conditions: The above copyright notice and this permission notice shall be included in all copies or substantial portions of the Software. THE SOFTWARE IS PROVIDED ``AS IS'', WITHOUT WARRANTY OF ANY KIND, EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHOR BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. ----------------------------------------------------------------------- */ .set r0,0 .set r1,1 .set r2,2 .set r3,3 .set r4,4 .set r5,5 .set r6,6 .set r7,7 .set r8,8 .set r9,9 .set r10,10 .set r11,11 .set r12,12 .set r13,13 .set r14,14 .set r15,15 .set r16,16 .set r17,17 .set r18,18 .set r19,19 .set r20,20 .set r21,21 .set r22,22 .set r23,23 .set r24,24 .set r25,25 .set r26,26 .set r27,27 .set r28,28 .set r29,29 .set r30,30 .set r31,31 .set f0,0 .set f1,1 .set f2,2 .set f3,3 .set f4,4 .set f5,5 .set f6,6 .set f7,7 .set f8,8 .set f9,9 .set f10,10 .set f11,11 .set f12,12 .set f13,13 .set f14,14 .set f15,15 .set f16,16 .set f17,17 .set f18,18 .set f19,19 .set f20,20 .set f21,21 #define LIBFFI_ASM #include #include #define JUMPTARGET(name) name #define L(x) x .file "aix.S" .toc /* void ffi_call_AIX(extended_cif *ecif, unsigned long bytes, * unsigned int flags, unsigned int *rvalue, * void (*fn)(), * void (*prep_args)(extended_cif*, unsigned *const)); * r3=ecif, r4=bytes, r5=flags, r6=rvalue, r7=fn, r8=prep_args */ .csect .text[PR] .align 2 .globl ffi_call_AIX .globl .ffi_call_AIX .csect ffi_call_AIX[DS] ffi_call_AIX: #ifdef __64BIT__ .llong .ffi_call_AIX, TOC[tc0], 0 .csect .text[PR] .ffi_call_AIX: /* Save registers we use. */ mflr r0 std r28,-32(r1) std r29,-24(r1) std r30,-16(r1) std r31, -8(r1) std r0, 16(r1) mr r28, r1 /* our AP. */ stdux r1, r1, r4 /* Save arguments over call... */ mr r31, r5 /* flags, */ mr r30, r6 /* rvalue, */ mr r29, r7 /* function address. */ std r2, 40(r1) /* Call ffi_prep_args. */ mr r4, r1 bl .ffi_prep_args /* Now do the call. */ ld r0, 0(r29) ld r2, 8(r29) ld r11, 16(r29) /* Set up cr1 with bits 4-7 of the flags. */ mtcrf 0x40, r31 mtctr r0 /* Load all those argument registers. */ // We have set up a nice stack frame, just load it into registers. ld r3, 40+(1*8)(r1) ld r4, 40+(2*8)(r1) ld r5, 40+(3*8)(r1) ld r6, 40+(4*8)(r1) nop ld r7, 40+(5*8)(r1) ld r8, 40+(6*8)(r1) ld r9, 40+(7*8)(r1) ld r10,40+(8*8)(r1) L1: /* Load all the FP registers. */ bf 6,L2 // 2f + 0x18 lfd f1,-32-(13*8)(r28) lfd f2,-32-(12*8)(r28) lfd f3,-32-(11*8)(r28) lfd f4,-32-(10*8)(r28) nop lfd f5,-32-(9*8)(r28) lfd f6,-32-(8*8)(r28) lfd f7,-32-(7*8)(r28) lfd f8,-32-(6*8)(r28) nop lfd f9,-32-(5*8)(r28) lfd f10,-32-(4*8)(r28) lfd f11,-32-(3*8)(r28) lfd f12,-32-(2*8)(r28) nop lfd f13,-32-(1*8)(r28) L2: /* Make the call. */ bctrl ld r2, 40(r1) /* Now, deal with the return value. */ mtcrf 0x01, r31 bt 30, L(done_return_value) bt 29, L(fp_return_value) std r3, 0(r30) /* Fall through... */ L(done_return_value): /* Restore the registers we used and return. */ mr r1, r28 ld r0, 16(r28) ld r28, -32(r1) mtlr r0 ld r29, -24(r1) ld r30, -16(r1) ld r31, -8(r1) blr L(fp_return_value): bf 28, L(float_return_value) stfd f1, 0(r30) bf 31, L(done_return_value) stfd f2, 8(r30) b L(done_return_value) L(float_return_value): stfs f1, 0(r30) b L(done_return_value) #else /* ! __64BIT__ */ .long .ffi_call_AIX, TOC[tc0], 0 .csect .text[PR] .ffi_call_AIX: /* Save registers we use. */ mflr r0 stw r28,-16(r1) stw r29,-12(r1) stw r30, -8(r1) stw r31, -4(r1) stw r0, 8(r1) mr r28, r1 /* out AP. */ stwux r1, r1, r4 /* Save arguments over call... */ mr r31, r5 /* flags, */ mr r30, r6 /* rvalue, */ mr r29, r7 /* function address, */ stw r2, 20(r1) /* Call ffi_prep_args. */ mr r4, r1 bl .ffi_prep_args /* Now do the call. */ lwz r0, 0(r29) lwz r2, 4(r29) lwz r11, 8(r29) /* Set up cr1 with bits 4-7 of the flags. */ mtcrf 0x40, r31 mtctr r0 /* Load all those argument registers. */ // We have set up a nice stack frame, just load it into registers. lwz r3, 20+(1*4)(r1) lwz r4, 20+(2*4)(r1) lwz r5, 20+(3*4)(r1) lwz r6, 20+(4*4)(r1) nop lwz r7, 20+(5*4)(r1) lwz r8, 20+(6*4)(r1) lwz r9, 20+(7*4)(r1) lwz r10,20+(8*4)(r1) L1: /* Load all the FP registers. */ bf 6,L2 // 2f + 0x18 lfd f1,-16-(13*8)(r28) lfd f2,-16-(12*8)(r28) lfd f3,-16-(11*8)(r28) lfd f4,-16-(10*8)(r28) nop lfd f5,-16-(9*8)(r28) lfd f6,-16-(8*8)(r28) lfd f7,-16-(7*8)(r28) lfd f8,-16-(6*8)(r28) nop lfd f9,-16-(5*8)(r28) lfd f10,-16-(4*8)(r28) lfd f11,-16-(3*8)(r28) lfd f12,-16-(2*8)(r28) nop lfd f13,-16-(1*8)(r28) L2: /* Make the call. */ bctrl lwz r2, 20(r1) /* Now, deal with the return value. */ mtcrf 0x01, r31 bt 30, L(done_return_value) bt 29, L(fp_return_value) stw r3, 0(r30) bf 28, L(done_return_value) stw r4, 4(r30) /* Fall through... */ L(done_return_value): /* Restore the registers we used and return. */ mr r1, r28 lwz r0, 8(r28) lwz r28,-16(r1) mtlr r0 lwz r29,-12(r1) lwz r30, -8(r1) lwz r31, -4(r1) blr L(fp_return_value): bf 28, L(float_return_value) stfd f1, 0(r30) b L(done_return_value) L(float_return_value): stfs f1, 0(r30) b L(done_return_value) #endif .long 0 .byte 0,0,0,1,128,4,0,0 //END(ffi_call_AIX) .csect .text[PR] .align 2 .globl ffi_call_DARWIN .globl .ffi_call_DARWIN .csect ffi_call_DARWIN[DS] ffi_call_DARWIN: #ifdef __64BIT__ .llong .ffi_call_DARWIN, TOC[tc0], 0 #else .long .ffi_call_DARWIN, TOC[tc0], 0 #endif .csect .text[PR] .ffi_call_DARWIN: blr .long 0 .byte 0,0,0,0,0,0,0,0 //END(ffi_call_DARWIN) smalltalk-3.2.5/libffi/src/powerpc/aix_closure.S0000644000175000017500000002143112130343734016571 00000000000000/* ----------------------------------------------------------------------- aix_closure.S - Copyright (c) 2002, 2003, 2009 Free Software Foundation, Inc. based on darwin_closure.S PowerPC Assembly glue. Permission is hereby granted, free of charge, to any person obtaining a copy of this software and associated documentation files (the ``Software''), to deal in the Software without restriction, including without limitation the rights to use, copy, modify, merge, publish, distribute, sublicense, and/or sell copies of the Software, and to permit persons to whom the Software is furnished to do so, subject to the following conditions: The above copyright notice and this permission notice shall be included in all copies or substantial portions of the Software. THE SOFTWARE IS PROVIDED ``AS IS'', WITHOUT WARRANTY OF ANY KIND, EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHOR BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. ----------------------------------------------------------------------- */ .set r0,0 .set r1,1 .set r2,2 .set r3,3 .set r4,4 .set r5,5 .set r6,6 .set r7,7 .set r8,8 .set r9,9 .set r10,10 .set r11,11 .set r12,12 .set r13,13 .set r14,14 .set r15,15 .set r16,16 .set r17,17 .set r18,18 .set r19,19 .set r20,20 .set r21,21 .set r22,22 .set r23,23 .set r24,24 .set r25,25 .set r26,26 .set r27,27 .set r28,28 .set r29,29 .set r30,30 .set r31,31 .set f0,0 .set f1,1 .set f2,2 .set f3,3 .set f4,4 .set f5,5 .set f6,6 .set f7,7 .set f8,8 .set f9,9 .set f10,10 .set f11,11 .set f12,12 .set f13,13 .set f14,14 .set f15,15 .set f16,16 .set f17,17 .set f18,18 .set f19,19 .set f20,20 .set f21,21 #define LIBFFI_ASM #define JUMPTARGET(name) name #define L(x) x .file "aix_closure.S" .toc LC..60: .tc L..60[TC],L..60 .csect .text[PR] .align 2 .csect .text[PR] .align 2 .globl ffi_closure_ASM .globl .ffi_closure_ASM .csect ffi_closure_ASM[DS] ffi_closure_ASM: #ifdef __64BIT__ .llong .ffi_closure_ASM, TOC[tc0], 0 .csect .text[PR] .ffi_closure_ASM: /* we want to build up an area for the parameters passed */ /* in registers (both floating point and integer) */ /* we store gpr 3 to gpr 10 (aligned to 4) in the parents outgoing area */ std r3, 48+(0*8)(r1) std r4, 48+(1*8)(r1) std r5, 48+(2*8)(r1) std r6, 48+(3*8)(r1) mflr r0 std r7, 48+(4*8)(r1) std r8, 48+(5*8)(r1) std r9, 48+(6*8)(r1) std r10, 48+(7*8)(r1) std r0, 16(r1) /* save the return address */ /* 48 Bytes (Linkage Area) */ /* 64 Bytes (params) */ /* 16 Bytes (result) */ /* 104 Bytes (13*8 from FPR) */ /* 8 Bytes (alignment) */ /* 240 Bytes */ stdu r1, -240(r1) /* skip over caller save area keep stack aligned to 16 */ /* next save fpr 1 to fpr 13 (aligned to 8) */ stfd f1, 128+(0*8)(r1) stfd f2, 128+(1*8)(r1) stfd f3, 128+(2*8)(r1) stfd f4, 128+(3*8)(r1) stfd f5, 128+(4*8)(r1) stfd f6, 128+(5*8)(r1) stfd f7, 128+(6*8)(r1) stfd f8, 128+(7*8)(r1) stfd f9, 128+(8*8)(r1) stfd f10, 128+(9*8)(r1) stfd f11, 128+(10*8)(r1) stfd f12, 128+(11*8)(r1) stfd f13, 128+(12*8)(r1) /* set up registers for the routine that actually does the work */ /* get the context pointer from the trampoline */ mr r3, r11 /* now load up the pointer to the result storage */ addi r4, r1, 112 /* now load up the pointer to the saved gpr registers */ addi r5, r1, 288 /* now load up the pointer to the saved fpr registers */ addi r6, r1, 128 /* make the call */ bl .ffi_closure_helper_DARWIN nop /* now r3 contains the return type */ /* so use it to look up in a table */ /* so we know how to deal with each type */ /* look up the proper starting point in table */ /* by using return type as offset */ ld r4, LC..60(2) /* get address of jump table */ sldi r3, r3, 4 /* now multiply return type by 16 */ ld r0, 240+16(r1) /* load return address */ add r3, r3, r4 /* add contents of table to table address */ mtctr r3 bctr /* jump to it */ /* Each fragment must be exactly 16 bytes long (4 instructions). Align to 16 byte boundary for cache and dispatch efficiency. */ .align 4 L..60: /* case FFI_TYPE_VOID */ mtlr r0 addi r1, r1, 240 blr nop /* case FFI_TYPE_INT */ lwa r3, 112+4(r1) mtlr r0 addi r1, r1, 240 blr /* case FFI_TYPE_FLOAT */ lfs f1, 112+0(r1) mtlr r0 addi r1, r1, 240 blr /* case FFI_TYPE_DOUBLE */ lfd f1, 112+0(r1) mtlr r0 addi r1, r1, 240 blr /* case FFI_TYPE_LONGDOUBLE */ lfd f1, 112+0(r1) mtlr r0 lfd f2, 112+8(r1) b L..finish /* case FFI_TYPE_UINT8 */ lbz r3, 112+7(r1) mtlr r0 addi r1, r1, 240 blr /* case FFI_TYPE_SINT8 */ lbz r3, 112+7(r1) mtlr r0 extsb r3, r3 b L..finish /* case FFI_TYPE_UINT16 */ lhz r3, 112+6(r1) mtlr r0 L..finish: addi r1, r1, 240 blr /* case FFI_TYPE_SINT16 */ lha r3, 112+6(r1) mtlr r0 addi r1, r1, 240 blr /* case FFI_TYPE_UINT32 */ lwz r3, 112+4(r1) mtlr r0 addi r1, r1, 240 blr /* case FFI_TYPE_SINT32 */ lwa r3, 112+4(r1) mtlr r0 addi r1, r1, 240 blr /* case FFI_TYPE_UINT64 */ ld r3, 112+0(r1) mtlr r0 addi r1, r1, 240 blr /* case FFI_TYPE_SINT64 */ ld r3, 112+0(r1) mtlr r0 addi r1, r1, 240 blr /* case FFI_TYPE_STRUCT */ mtlr r0 addi r1, r1, 240 blr nop /* case FFI_TYPE_POINTER */ ld r3, 112+0(r1) mtlr r0 addi r1, r1, 240 blr #else /* ! __64BIT__ */ .long .ffi_closure_ASM, TOC[tc0], 0 .csect .text[PR] .ffi_closure_ASM: /* we want to build up an area for the parameters passed */ /* in registers (both floating point and integer) */ /* we store gpr 3 to gpr 10 (aligned to 4) in the parents outgoing area */ stw r3, 24+(0*4)(r1) stw r4, 24+(1*4)(r1) stw r5, 24+(2*4)(r1) stw r6, 24+(3*4)(r1) mflr r0 stw r7, 24+(4*4)(r1) stw r8, 24+(5*4)(r1) stw r9, 24+(6*4)(r1) stw r10, 24+(7*4)(r1) stw r0, 8(r1) /* 24 Bytes (Linkage Area) */ /* 32 Bytes (params) */ /* 16 Bytes (result) */ /* 104 Bytes (13*8 from FPR) */ /* 176 Bytes */ stwu r1, -176(r1) /* skip over caller save area keep stack aligned to 16 */ /* next save fpr 1 to fpr 13 (aligned to 8) */ stfd f1, 72+(0*8)(r1) stfd f2, 72+(1*8)(r1) stfd f3, 72+(2*8)(r1) stfd f4, 72+(3*8)(r1) stfd f5, 72+(4*8)(r1) stfd f6, 72+(5*8)(r1) stfd f7, 72+(6*8)(r1) stfd f8, 72+(7*8)(r1) stfd f9, 72+(8*8)(r1) stfd f10, 72+(9*8)(r1) stfd f11, 72+(10*8)(r1) stfd f12, 72+(11*8)(r1) stfd f13, 72+(12*8)(r1) /* set up registers for the routine that actually does the work */ /* get the context pointer from the trampoline */ mr r3, r11 /* now load up the pointer to the result storage */ addi r4, r1, 56 /* now load up the pointer to the saved gpr registers */ addi r5, r1, 200 /* now load up the pointer to the saved fpr registers */ addi r6, r1, 72 /* make the call */ bl .ffi_closure_helper_DARWIN nop /* now r3 contains the return type */ /* so use it to look up in a table */ /* so we know how to deal with each type */ /* look up the proper starting point in table */ /* by using return type as offset */ lwz r4, LC..60(2) /* get address of jump table */ slwi r3, r3, 4 /* now multiply return type by 4 */ lwz r0, 176+8(r1) /* load return address */ add r3, r3, r4 /* add contents of table to table address */ mtctr r3 bctr /* jump to it */ /* Each fragment must be exactly 16 bytes long (4 instructions). Align to 16 byte boundary for cache and dispatch efficiency. */ .align 4 L..60: /* case FFI_TYPE_VOID */ mtlr r0 addi r1, r1, 176 blr nop /* case FFI_TYPE_INT */ lwz r3, 56+0(r1) mtlr r0 addi r1, r1, 176 blr /* case FFI_TYPE_FLOAT */ lfs f1, 56+0(r1) mtlr r0 addi r1, r1, 176 blr /* case FFI_TYPE_DOUBLE */ lfd f1, 56+0(r1) mtlr r0 addi r1, r1, 176 blr /* case FFI_TYPE_LONGDOUBLE */ lfd f1, 56+0(r1) mtlr r0 lfd f2, 56+8(r1) b L..finish /* case FFI_TYPE_UINT8 */ lbz r3, 56+3(r1) mtlr r0 addi r1, r1, 176 blr /* case FFI_TYPE_SINT8 */ lbz r3, 56+3(r1) mtlr r0 extsb r3, r3 b L..finish /* case FFI_TYPE_UINT16 */ lhz r3, 56+2(r1) mtlr r0 addi r1, r1, 176 blr /* case FFI_TYPE_SINT16 */ lha r3, 56+2(r1) mtlr r0 addi r1, r1, 176 blr /* case FFI_TYPE_UINT32 */ lwz r3, 56+0(r1) mtlr r0 addi r1, r1, 176 blr /* case FFI_TYPE_SINT32 */ lwz r3, 56+0(r1) mtlr r0 addi r1, r1, 176 blr /* case FFI_TYPE_UINT64 */ lwz r3, 56+0(r1) mtlr r0 lwz r4, 56+4(r1) b L..finish /* case FFI_TYPE_SINT64 */ lwz r3, 56+0(r1) mtlr r0 lwz r4, 56+4(r1) b L..finish /* case FFI_TYPE_STRUCT */ mtlr r0 addi r1, r1, 176 blr nop /* case FFI_TYPE_POINTER */ lwz r3, 56+0(r1) mtlr r0 L..finish: addi r1, r1, 176 blr #endif /* END(ffi_closure_ASM) */ smalltalk-3.2.5/libffi/src/powerpc/linux64_closure.S0000644000175000017500000001340312130343734017321 00000000000000/* ----------------------------------------------------------------------- sysv.h - Copyright (c) 2003 Jakub Jelinek Copyright (c) 2008 Red Hat, Inc. PowerPC64 Assembly glue. Permission is hereby granted, free of charge, to any person obtaining a copy of this software and associated documentation files (the ``Software''), to deal in the Software without restriction, including without limitation the rights to use, copy, modify, merge, publish, distribute, sublicense, and/or sell copies of the Software, and to permit persons to whom the Software is furnished to do so, subject to the following conditions: The above copyright notice and this permission notice shall be included in all copies or substantial portions of the Software. THE SOFTWARE IS PROVIDED ``AS IS'', WITHOUT WARRANTY OF ANY KIND, EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. ----------------------------------------------------------------------- */ #define LIBFFI_ASM #include #include .file "linux64_closure.S" #ifdef __powerpc64__ FFI_HIDDEN (ffi_closure_LINUX64) FFI_HIDDEN (.ffi_closure_LINUX64) .globl ffi_closure_LINUX64, .ffi_closure_LINUX64 .section ".opd","aw" .align 3 ffi_closure_LINUX64: .quad .ffi_closure_LINUX64,.TOC.@tocbase,0 .size ffi_closure_LINUX64,24 .type .ffi_closure_LINUX64,@function .text .ffi_closure_LINUX64: .LFB1: # save general regs into parm save area std %r3, 48(%r1) std %r4, 56(%r1) std %r5, 64(%r1) std %r6, 72(%r1) mflr %r0 std %r7, 80(%r1) std %r8, 88(%r1) std %r9, 96(%r1) std %r10, 104(%r1) std %r0, 16(%r1) # mandatory 48 bytes special reg save area + 64 bytes parm save area # + 16 bytes retval area + 13*8 bytes fpr save area + round to 16 stdu %r1, -240(%r1) .LCFI0: # next save fpr 1 to fpr 13 stfd %f1, 128+(0*8)(%r1) stfd %f2, 128+(1*8)(%r1) stfd %f3, 128+(2*8)(%r1) stfd %f4, 128+(3*8)(%r1) stfd %f5, 128+(4*8)(%r1) stfd %f6, 128+(5*8)(%r1) stfd %f7, 128+(6*8)(%r1) stfd %f8, 128+(7*8)(%r1) stfd %f9, 128+(8*8)(%r1) stfd %f10, 128+(9*8)(%r1) stfd %f11, 128+(10*8)(%r1) stfd %f12, 128+(11*8)(%r1) stfd %f13, 128+(12*8)(%r1) # set up registers for the routine that actually does the work # get the context pointer from the trampoline mr %r3, %r11 # now load up the pointer to the result storage addi %r4, %r1, 112 # now load up the pointer to the parameter save area # in the previous frame addi %r5, %r1, 240 + 48 # now load up the pointer to the saved fpr registers */ addi %r6, %r1, 128 # make the call bl .ffi_closure_helper_LINUX64 .Lret: # now r3 contains the return type # so use it to look up in a table # so we know how to deal with each type # look up the proper starting point in table # by using return type as offset mflr %r4 # move address of .Lret to r4 sldi %r3, %r3, 4 # now multiply return type by 16 addi %r4, %r4, .Lret_type0 - .Lret ld %r0, 240+16(%r1) add %r3, %r3, %r4 # add contents of table to table address mtctr %r3 bctr # jump to it # Each of the ret_typeX code fragments has to be exactly 16 bytes long # (4 instructions). For cache effectiveness we align to a 16 byte boundary # first. .align 4 .Lret_type0: # case FFI_TYPE_VOID mtlr %r0 addi %r1, %r1, 240 blr nop # case FFI_TYPE_INT lwa %r3, 112+4(%r1) mtlr %r0 addi %r1, %r1, 240 blr # case FFI_TYPE_FLOAT lfs %f1, 112+0(%r1) mtlr %r0 addi %r1, %r1, 240 blr # case FFI_TYPE_DOUBLE lfd %f1, 112+0(%r1) mtlr %r0 addi %r1, %r1, 240 blr # case FFI_TYPE_LONGDOUBLE lfd %f1, 112+0(%r1) mtlr %r0 lfd %f2, 112+8(%r1) b .Lfinish # case FFI_TYPE_UINT8 lbz %r3, 112+7(%r1) mtlr %r0 addi %r1, %r1, 240 blr # case FFI_TYPE_SINT8 lbz %r3, 112+7(%r1) extsb %r3,%r3 mtlr %r0 b .Lfinish # case FFI_TYPE_UINT16 lhz %r3, 112+6(%r1) mtlr %r0 .Lfinish: addi %r1, %r1, 240 blr # case FFI_TYPE_SINT16 lha %r3, 112+6(%r1) mtlr %r0 addi %r1, %r1, 240 blr # case FFI_TYPE_UINT32 lwz %r3, 112+4(%r1) mtlr %r0 addi %r1, %r1, 240 blr # case FFI_TYPE_SINT32 lwa %r3, 112+4(%r1) mtlr %r0 addi %r1, %r1, 240 blr # case FFI_TYPE_UINT64 ld %r3, 112+0(%r1) mtlr %r0 addi %r1, %r1, 240 blr # case FFI_TYPE_SINT64 ld %r3, 112+0(%r1) mtlr %r0 addi %r1, %r1, 240 blr # case FFI_TYPE_STRUCT mtlr %r0 addi %r1, %r1, 240 blr nop # case FFI_TYPE_POINTER ld %r3, 112+0(%r1) mtlr %r0 addi %r1, %r1, 240 blr # esac .LFE1: .long 0 .byte 0,12,0,1,128,0,0,0 .size .ffi_closure_LINUX64,.-.ffi_closure_LINUX64 .section .eh_frame,EH_FRAME_FLAGS,@progbits .Lframe1: .4byte .LECIE1-.LSCIE1 # Length of Common Information Entry .LSCIE1: .4byte 0x0 # CIE Identifier Tag .byte 0x1 # CIE Version .ascii "zR\0" # CIE Augmentation .uleb128 0x1 # CIE Code Alignment Factor .sleb128 -8 # CIE Data Alignment Factor .byte 0x41 # CIE RA Column .uleb128 0x1 # Augmentation size .byte 0x14 # FDE Encoding (pcrel udata8) .byte 0xc # DW_CFA_def_cfa .uleb128 0x1 .uleb128 0x0 .align 3 .LECIE1: .LSFDE1: .4byte .LEFDE1-.LASFDE1 # FDE Length .LASFDE1: .4byte .LASFDE1-.Lframe1 # FDE CIE offset .8byte .LFB1-. # FDE initial location .8byte .LFE1-.LFB1 # FDE address range .uleb128 0x0 # Augmentation size .byte 0x2 # DW_CFA_advance_loc1 .byte .LCFI0-.LFB1 .byte 0xe # DW_CFA_def_cfa_offset .uleb128 240 .byte 0x11 # DW_CFA_offset_extended_sf .uleb128 0x41 .sleb128 -2 .align 3 .LEFDE1: #endif #if defined __ELF__ && defined __linux__ .section .note.GNU-stack,"",@progbits #endif smalltalk-3.2.5/libffi/src/powerpc/ffitarget.h0000644000175000017500000000727412130343734016265 00000000000000/* -----------------------------------------------------------------*-C-*- ffitarget.h - Copyright (c) 1996-2003 Red Hat, Inc. Copyright (C) 2007, 2008 Free Software Foundation, Inc Target configuration macros for PowerPC. Permission is hereby granted, free of charge, to any person obtaining a copy of this software and associated documentation files (the ``Software''), to deal in the Software without restriction, including without limitation the rights to use, copy, modify, merge, publish, distribute, sublicense, and/or sell copies of the Software, and to permit persons to whom the Software is furnished to do so, subject to the following conditions: The above copyright notice and this permission notice shall be included in all copies or substantial portions of the Software. THE SOFTWARE IS PROVIDED ``AS IS'', WITHOUT WARRANTY OF ANY KIND, EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. ----------------------------------------------------------------------- */ #ifndef LIBFFI_TARGET_H #define LIBFFI_TARGET_H /* ---- System specific configurations ----------------------------------- */ #if defined (POWERPC) && defined (__powerpc64__) /* linux64 */ #ifndef POWERPC64 #define POWERPC64 #endif #elif defined (POWERPC_DARWIN) && defined (__ppc64__) /* Darwin */ #ifndef POWERPC64 #define POWERPC64 #endif #elif defined (POWERPC_AIX) && defined (__64BIT__) /* AIX64 */ #ifndef POWERPC64 #define POWERPC64 #endif #endif #ifndef LIBFFI_ASM typedef unsigned long ffi_arg; typedef signed long ffi_sarg; typedef enum ffi_abi { FFI_FIRST_ABI = 0, #ifdef POWERPC FFI_SYSV, FFI_GCC_SYSV, FFI_LINUX64, FFI_LINUX, FFI_LINUX_SOFT_FLOAT, # ifdef POWERPC64 FFI_DEFAULT_ABI = FFI_LINUX64, # else # if (!defined(__NO_FPRS__) && (__LDBL_MANT_DIG__ == 106)) FFI_DEFAULT_ABI = FFI_LINUX, # else # ifdef __NO_FPRS__ FFI_DEFAULT_ABI = FFI_LINUX_SOFT_FLOAT, # else FFI_DEFAULT_ABI = FFI_GCC_SYSV, # endif # endif # endif #endif #ifdef POWERPC_AIX FFI_AIX, FFI_DARWIN, FFI_DEFAULT_ABI = FFI_AIX, #endif #ifdef POWERPC_DARWIN FFI_AIX, FFI_DARWIN, FFI_DEFAULT_ABI = FFI_DARWIN, #endif #ifdef POWERPC_FREEBSD FFI_SYSV, FFI_GCC_SYSV, FFI_LINUX64, FFI_LINUX, FFI_LINUX_SOFT_FLOAT, FFI_DEFAULT_ABI = FFI_SYSV, #endif FFI_LAST_ABI } ffi_abi; #endif /* ---- Definitions for closures ----------------------------------------- */ #define FFI_CLOSURES 1 #define FFI_NATIVE_RAW_API 0 /* For additional types like the below, take care about the order in ppc_closures.S. They must follow after the FFI_TYPE_LAST. */ /* Needed for soft-float long-double-128 support. */ #define FFI_TYPE_UINT128 (FFI_TYPE_LAST + 1) /* Needed for FFI_SYSV small structure returns. We use two flag bits, (FLAG_SYSV_SMST_R3, FLAG_SYSV_SMST_R4) which are defined in ffi.c, to determine the exact return type and its size. */ #define FFI_SYSV_TYPE_SMALL_STRUCT (FFI_TYPE_LAST + 2) #if defined(POWERPC64) || defined(POWERPC_AIX) #define FFI_TRAMPOLINE_SIZE 24 #else /* POWERPC || POWERPC_AIX */ #define FFI_TRAMPOLINE_SIZE 40 #endif #ifndef LIBFFI_ASM #if defined(POWERPC_DARWIN) || defined(POWERPC_AIX) struct ffi_aix_trampoline_struct { void * code_pointer; /* Pointer to ffi_closure_ASM */ void * toc; /* TOC */ void * static_chain; /* Pointer to closure */ }; #endif #endif #endif smalltalk-3.2.5/libffi/src/powerpc/ppc_closure.S0000644000175000017500000001573212130343734016601 00000000000000/* ----------------------------------------------------------------------- sysv.h - Copyright (c) 2003 Jakub Jelinek Copyright (c) 2008 Red Hat, Inc. PowerPC Assembly glue. Permission is hereby granted, free of charge, to any person obtaining a copy of this software and associated documentation files (the ``Software''), to deal in the Software without restriction, including without limitation the rights to use, copy, modify, merge, publish, distribute, sublicense, and/or sell copies of the Software, and to permit persons to whom the Software is furnished to do so, subject to the following conditions: The above copyright notice and this permission notice shall be included in all copies or substantial portions of the Software. THE SOFTWARE IS PROVIDED ``AS IS'', WITHOUT WARRANTY OF ANY KIND, EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. ----------------------------------------------------------------------- */ #define LIBFFI_ASM #include #include #include .file "ppc_closure.S" #ifndef __powerpc64__ ENTRY(ffi_closure_SYSV) .LFB1: stwu %r1,-144(%r1) .LCFI0: mflr %r0 .LCFI1: stw %r0,148(%r1) # we want to build up an areas for the parameters passed # in registers (both floating point and integer) # so first save gpr 3 to gpr 10 (aligned to 4) stw %r3, 16(%r1) stw %r4, 20(%r1) stw %r5, 24(%r1) stw %r6, 28(%r1) stw %r7, 32(%r1) stw %r8, 36(%r1) stw %r9, 40(%r1) stw %r10,44(%r1) #ifndef __NO_FPRS__ # next save fpr 1 to fpr 8 (aligned to 8) stfd %f1, 48(%r1) stfd %f2, 56(%r1) stfd %f3, 64(%r1) stfd %f4, 72(%r1) stfd %f5, 80(%r1) stfd %f6, 88(%r1) stfd %f7, 96(%r1) stfd %f8, 104(%r1) #endif # set up registers for the routine that actually does the work # get the context pointer from the trampoline mr %r3,%r11 # now load up the pointer to the result storage addi %r4,%r1,112 # now load up the pointer to the saved gpr registers addi %r5,%r1,16 # now load up the pointer to the saved fpr registers */ addi %r6,%r1,48 # now load up the pointer to the outgoing parameter # stack in the previous frame # i.e. the previous frame pointer + 8 addi %r7,%r1,152 # make the call bl ffi_closure_helper_SYSV@local .Lret: # now r3 contains the return type # so use it to look up in a table # so we know how to deal with each type # look up the proper starting point in table # by using return type as offset mflr %r4 # move address of .Lret to r4 slwi %r3,%r3,4 # now multiply return type by 16 addi %r4, %r4, .Lret_type0 - .Lret lwz %r0,148(%r1) add %r3,%r3,%r4 # add contents of table to table address mtctr %r3 bctr # jump to it .LFE1: # Each of the ret_typeX code fragments has to be exactly 16 bytes long # (4 instructions). For cache effectiveness we align to a 16 byte boundary # first. .align 4 # case FFI_TYPE_VOID .Lret_type0: mtlr %r0 addi %r1,%r1,144 blr nop # case FFI_TYPE_INT lwz %r3,112+0(%r1) mtlr %r0 .Lfinish: addi %r1,%r1,144 blr # case FFI_TYPE_FLOAT lfs %f1,112+0(%r1) mtlr %r0 addi %r1,%r1,144 blr # case FFI_TYPE_DOUBLE lfd %f1,112+0(%r1) mtlr %r0 addi %r1,%r1,144 blr # case FFI_TYPE_LONGDOUBLE lfd %f1,112+0(%r1) lfd %f2,112+8(%r1) mtlr %r0 b .Lfinish # case FFI_TYPE_UINT8 lbz %r3,112+3(%r1) mtlr %r0 addi %r1,%r1,144 blr # case FFI_TYPE_SINT8 lbz %r3,112+3(%r1) extsb %r3,%r3 mtlr %r0 b .Lfinish # case FFI_TYPE_UINT16 lhz %r3,112+2(%r1) mtlr %r0 addi %r1,%r1,144 blr # case FFI_TYPE_SINT16 lha %r3,112+2(%r1) mtlr %r0 addi %r1,%r1,144 blr # case FFI_TYPE_UINT32 lwz %r3,112+0(%r1) mtlr %r0 addi %r1,%r1,144 blr # case FFI_TYPE_SINT32 lwz %r3,112+0(%r1) mtlr %r0 addi %r1,%r1,144 blr # case FFI_TYPE_UINT64 lwz %r3,112+0(%r1) lwz %r4,112+4(%r1) mtlr %r0 b .Lfinish # case FFI_TYPE_SINT64 lwz %r3,112+0(%r1) lwz %r4,112+4(%r1) mtlr %r0 b .Lfinish # case FFI_TYPE_STRUCT mtlr %r0 addi %r1,%r1,144 blr nop # case FFI_TYPE_POINTER lwz %r3,112+0(%r1) mtlr %r0 addi %r1,%r1,144 blr # case FFI_TYPE_UINT128 lwz %r3,112+0(%r1) lwz %r4,112+4(%r1) lwz %r5,112+8(%r1) bl .Luint128 # The return types below are only used when the ABI type is FFI_SYSV. # case FFI_SYSV_TYPE_SMALL_STRUCT + 1. One byte struct. lbz %r3,112+0(%r1) mtlr %r0 addi %r1,%r1,144 blr # case FFI_SYSV_TYPE_SMALL_STRUCT + 2. Two byte struct. lhz %r3,112+0(%r1) mtlr %r0 addi %r1,%r1,144 blr # case FFI_SYSV_TYPE_SMALL_STRUCT + 3. Three byte struct. lwz %r3,112+0(%r1) srwi %r3,%r3,8 mtlr %r0 b .Lfinish # case FFI_SYSV_TYPE_SMALL_STRUCT + 4. Four byte struct. lwz %r3,112+0(%r1) mtlr %r0 addi %r1,%r1,144 blr # case FFI_SYSV_TYPE_SMALL_STRUCT + 5. Five byte struct. lwz %r3,112+0(%r1) lwz %r4,112+4(%r1) li %r5,24 b .Lstruct567 # case FFI_SYSV_TYPE_SMALL_STRUCT + 6. Six byte struct. lwz %r3,112+0(%r1) lwz %r4,112+4(%r1) li %r5,16 b .Lstruct567 # case FFI_SYSV_TYPE_SMALL_STRUCT + 7. Seven byte struct. lwz %r3,112+0(%r1) lwz %r4,112+4(%r1) li %r5,8 b .Lstruct567 # case FFI_SYSV_TYPE_SMALL_STRUCT + 8. Eight byte struct. lwz %r3,112+0(%r1) lwz %r4,112+4(%r1) mtlr %r0 b .Lfinish .Lstruct567: subfic %r6,%r5,32 srw %r4,%r4,%r5 slw %r6,%r3,%r6 srw %r3,%r3,%r5 or %r4,%r6,%r4 mtlr %r0 addi %r1,%r1,144 blr .Luint128: lwz %r6,112+12(%r1) mtlr %r0 addi %r1,%r1,144 blr END(ffi_closure_SYSV) .section ".eh_frame",EH_FRAME_FLAGS,@progbits .Lframe1: .4byte .LECIE1-.LSCIE1 # Length of Common Information Entry .LSCIE1: .4byte 0x0 # CIE Identifier Tag .byte 0x1 # CIE Version #if defined _RELOCATABLE || defined __PIC__ .ascii "zR\0" # CIE Augmentation #else .ascii "\0" # CIE Augmentation #endif .uleb128 0x1 # CIE Code Alignment Factor .sleb128 -4 # CIE Data Alignment Factor .byte 0x41 # CIE RA Column #if defined _RELOCATABLE || defined __PIC__ .uleb128 0x1 # Augmentation size .byte 0x1b # FDE Encoding (pcrel sdata4) #endif .byte 0xc # DW_CFA_def_cfa .uleb128 0x1 .uleb128 0x0 .align 2 .LECIE1: .LSFDE1: .4byte .LEFDE1-.LASFDE1 # FDE Length .LASFDE1: .4byte .LASFDE1-.Lframe1 # FDE CIE offset #if defined _RELOCATABLE || defined __PIC__ .4byte .LFB1-. # FDE initial location #else .4byte .LFB1 # FDE initial location #endif .4byte .LFE1-.LFB1 # FDE address range #if defined _RELOCATABLE || defined __PIC__ .uleb128 0x0 # Augmentation size #endif .byte 0x4 # DW_CFA_advance_loc4 .4byte .LCFI0-.LFB1 .byte 0xe # DW_CFA_def_cfa_offset .uleb128 144 .byte 0x4 # DW_CFA_advance_loc4 .4byte .LCFI1-.LCFI0 .byte 0x11 # DW_CFA_offset_extended_sf .uleb128 0x41 .sleb128 -1 .align 2 .LEFDE1: #endif #if defined __ELF__ && defined __linux__ .section .note.GNU-stack,"",@progbits #endif smalltalk-3.2.5/libffi/src/powerpc/darwin.S0000644000175000017500000001373012130343734015543 00000000000000/* ----------------------------------------------------------------------- darwin.S - Copyright (c) 2000 John Hornkvist Copyright (c) 2004 Free Software Foundation, Inc. PowerPC Assembly glue. Permission is hereby granted, free of charge, to any person obtaining a copy of this software and associated documentation files (the ``Software''), to deal in the Software without restriction, including without limitation the rights to use, copy, modify, merge, publish, distribute, sublicense, and/or sell copies of the Software, and to permit persons to whom the Software is furnished to do so, subject to the following conditions: The above copyright notice and this permission notice shall be included in all copies or substantial portions of the Software. THE SOFTWARE IS PROVIDED ``AS IS'', WITHOUT WARRANTY OF ANY KIND, EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHOR BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. ----------------------------------------------------------------------- */ #if defined(__ppc64__) #define MODE_CHOICE(x, y) y #else #define MODE_CHOICE(x, y) x #endif #define g_long MODE_CHOICE(long, quad) /* usage is ".g_long" */ #define LOG2_GPR_BYTES MODE_CHOICE(2,3) /* log2(GPR_BYTES) */ #define LIBFFI_ASM #include #include #define JUMPTARGET(name) name #define L(x) x .text .align 2 .globl _ffi_prep_args .text .align 2 .globl _ffi_call_DARWIN .text .align 2 _ffi_call_DARWIN: LFB0: mr r12,r8 /* We only need r12 until the call, so it doesn't have to be saved. */ LFB1: /* Save the old stack pointer as AP. */ mr r8,r1 LCFI0: /* Allocate the stack space we need. */ stwux r1,r1,r4 /* Save registers we use. */ mflr r9 stw r28,-16(r8) stw r29,-12(r8) stw r30,-8(r8) stw r31,-4(r8) stw r9,8(r8) stw r2,20(r1) LCFI1: /* Save arguments over call. */ mr r31,r5 /* flags, */ mr r30,r6 /* rvalue, */ mr r29,r7 /* function address, */ mr r28,r8 /* our AP. */ LCFI2: /* Call ffi_prep_args. */ mr r4,r1 li r9,0 mtctr r12 /* r12 holds address of _ffi_prep_args. */ bctrl lwz r2,20(r1) /* Now do the call. Set up cr1 with bits 4-7 of the flags. */ mtcrf 0x40,r31 /* Get the address to call into CTR. */ mtctr r29 /* Load all those argument registers. We have set up a nice stack frame, just load it into registers. */ lwz r3,20+(1*4)(r1) lwz r4,20+(2*4)(r1) lwz r5,20+(3*4)(r1) lwz r6,20+(4*4)(r1) nop lwz r7,20+(5*4)(r1) lwz r8,20+(6*4)(r1) lwz r9,20+(7*4)(r1) lwz r10,20+(8*4)(r1) L1: /* Load all the FP registers. */ bf 6,L2 /* No floats to load. */ lfd f1,-16-(13*8)(r28) lfd f2,-16-(12*8)(r28) lfd f3,-16-(11*8)(r28) lfd f4,-16-(10*8)(r28) nop lfd f5,-16-(9*8)(r28) lfd f6,-16-(8*8)(r28) lfd f7,-16-(7*8)(r28) lfd f8,-16-(6*8)(r28) nop lfd f9,-16-(5*8)(r28) lfd f10,-16-(4*8)(r28) lfd f11,-16-(3*8)(r28) lfd f12,-16-(2*8)(r28) nop lfd f13,-16-(1*8)(r28) L2: mr r12,r29 /* Put the target address in r12 as specified. */ mtctr r12 nop nop /* Make the call. */ bctrl /* Now, deal with the return value. */ mtcrf 0x01,r31 bt 30,L(done_return_value) bt 29,L(fp_return_value) stw r3,0(r30) bf 28,L(done_return_value) stw r4,4(r30) /* Fall through. */ L(done_return_value): /* Restore the registers we used and return. */ lwz r9,8(r28) lwz r31,-4(r28) mtlr r9 lwz r30,-8(r28) lwz r29,-12(r28) lwz r28,-16(r28) lwz r1,0(r1) blr L(fp_return_value): /* Do we have long double to store? */ bf 31,L(fd_return_value) stfd f1,0(r30) stfd f2,8(r30) b L(done_return_value) L(fd_return_value): /* Do we have double to store? */ bf 28,L(float_return_value) stfd f1,0(r30) b L(done_return_value) L(float_return_value): /* We only have a float to store. */ stfs f1,0(r30) b L(done_return_value) LFE1: /* END(_ffi_call_DARWIN) */ /* Provide a null definition of _ffi_call_AIX. */ .text .align 2 .globl _ffi_call_AIX .text .align 2 _ffi_call_AIX: blr /* END(_ffi_call_AIX) */ .data .section __TEXT,__eh_frame,coalesced,no_toc+strip_static_syms EH_frame1: .set L$set$0,LECIE1-LSCIE1 .long L$set$0 ; Length of Common Information Entry LSCIE1: .long 0x0 ; CIE Identifier Tag .byte 0x1 ; CIE Version .ascii "zR\0" ; CIE Augmentation .byte 0x1 ; uleb128 0x1; CIE Code Alignment Factor .byte 0x7c ; sleb128 -4; CIE Data Alignment Factor .byte 0x41 ; CIE RA Column .byte 0x1 ; uleb128 0x1; Augmentation size .byte 0x90 ; FDE Encoding (indirect pcrel) .byte 0xc ; DW_CFA_def_cfa .byte 0x1 ; uleb128 0x1 .byte 0x0 ; uleb128 0x0 .align LOG2_GPR_BYTES LECIE1: .globl _ffi_call_DARWIN.eh _ffi_call_DARWIN.eh: LSFDE1: .set L$set$1,LEFDE1-LASFDE1 .long L$set$1 ; FDE Length LASFDE1: .long LASFDE1-EH_frame1 ; FDE CIE offset .g_long LLFB0$non_lazy_ptr-. ; FDE initial location .set L$set$3,LFE1-LFB0 .g_long L$set$3 ; FDE address range .byte 0x0 ; uleb128 0x0; Augmentation size .byte 0x4 ; DW_CFA_advance_loc4 .set L$set$4,LCFI0-LFB1 .long L$set$4 .byte 0xd ; DW_CFA_def_cfa_register .byte 0x08 ; uleb128 0x08 .byte 0x4 ; DW_CFA_advance_loc4 .set L$set$5,LCFI1-LCFI0 .long L$set$5 .byte 0x11 ; DW_CFA_offset_extended_sf .byte 0x41 ; uleb128 0x41 .byte 0x7e ; sleb128 -2 .byte 0x9f ; DW_CFA_offset, column 0x1f .byte 0x1 ; uleb128 0x1 .byte 0x9e ; DW_CFA_offset, column 0x1e .byte 0x2 ; uleb128 0x2 .byte 0x9d ; DW_CFA_offset, column 0x1d .byte 0x3 ; uleb128 0x3 .byte 0x9c ; DW_CFA_offset, column 0x1c .byte 0x4 ; uleb128 0x4 .byte 0x4 ; DW_CFA_advance_loc4 .set L$set$6,LCFI2-LCFI1 .long L$set$6 .byte 0xd ; DW_CFA_def_cfa_register .byte 0x1c ; uleb128 0x1c .align LOG2_GPR_BYTES LEFDE1: .data .align LOG2_GPR_BYTES LLFB0$non_lazy_ptr: .g_long LFB0 smalltalk-3.2.5/libffi/src/powerpc/darwin_closure.S0000644000175000017500000001611312130343734017275 00000000000000/* ----------------------------------------------------------------------- darwin_closure.S - Copyright (c) 2002, 2003, 2004, Free Software Foundation, Inc. based on ppc_closure.S PowerPC Assembly glue. Permission is hereby granted, free of charge, to any person obtaining a copy of this software and associated documentation files (the ``Software''), to deal in the Software without restriction, including without limitation the rights to use, copy, modify, merge, publish, distribute, sublicense, and/or sell copies of the Software, and to permit persons to whom the Software is furnished to do so, subject to the following conditions: The above copyright notice and this permission notice shall be included in all copies or substantial portions of the Software. THE SOFTWARE IS PROVIDED ``AS IS'', WITHOUT WARRANTY OF ANY KIND, EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHOR BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. ----------------------------------------------------------------------- */ #define LIBFFI_ASM #define L(x) x #if defined(__ppc64__) #define MODE_CHOICE(x, y) y #else #define MODE_CHOICE(x, y) x #endif #define lgu MODE_CHOICE(lwzu, ldu) #define g_long MODE_CHOICE(long, quad) /* usage is ".g_long" */ #define LOG2_GPR_BYTES MODE_CHOICE(2,3) /* log2(GPR_BYTES) */ .file "darwin_closure.S" .text .align LOG2_GPR_BYTES .globl _ffi_closure_ASM .text .align LOG2_GPR_BYTES _ffi_closure_ASM: LFB1: mflr r0 /* extract return address */ stw r0,8(r1) /* save the return address */ LCFI0: /* 24 Bytes (Linkage Area) 32 Bytes (outgoing parameter area, always reserved) 104 Bytes (13*8 from FPR) 16 Bytes (result) 176 Bytes */ stwu r1,-176(r1) /* skip over caller save area keep stack aligned to 16. */ LCFI1: /* We want to build up an area for the parameters passed in registers. (both floating point and integer) */ /* We store gpr 3 to gpr 10 (aligned to 4) in the parents outgoing area. */ stw r3,200(r1) stw r4,204(r1) stw r5,208(r1) stw r6,212(r1) stw r7,216(r1) stw r8,220(r1) stw r9,224(r1) stw r10,228(r1) /* We save fpr 1 to fpr 13. (aligned to 8) */ stfd f1,56(r1) stfd f2,64(r1) stfd f3,72(r1) stfd f4,80(r1) stfd f5,88(r1) stfd f6,96(r1) stfd f7,104(r1) stfd f8,112(r1) stfd f9,120(r1) stfd f10,128(r1) stfd f11,136(r1) stfd f12,144(r1) stfd f13,152(r1) /* Set up registers for the routine that actually does the work get the context pointer from the trampoline. */ mr r3,r11 /* Now load up the pointer to the result storage. */ addi r4,r1,160 /* Now load up the pointer to the saved gpr registers. */ addi r5,r1,200 /* Now load up the pointer to the saved fpr registers. */ addi r6,r1,56 /* Make the call. */ bl Lffi_closure_helper_DARWIN$stub /* Now r3 contains the return type so use it to look up in a table so we know how to deal with each type. */ /* Look up the proper starting point in table by using return type as offset. */ addi r5,r1,160 /* Get pointer to results area. */ bl Lget_ret_type0_addr /* Get pointer to Lret_type0 into LR. */ mflr r4 /* Move to r4. */ slwi r3,r3,4 /* Now multiply return type by 16. */ add r3,r3,r4 /* Add contents of table to table address. */ mtctr r3 bctr /* Jump to it. */ LFE1: /* Each of the ret_typeX code fragments has to be exactly 16 bytes long (4 instructions). For cache effectiveness we align to a 16 byte boundary first. */ .align 4 nop nop nop Lget_ret_type0_addr: blrl /* case FFI_TYPE_VOID */ Lret_type0: b Lfinish nop nop nop /* case FFI_TYPE_INT */ Lret_type1: lwz r3,0(r5) b Lfinish nop nop /* case FFI_TYPE_FLOAT */ Lret_type2: lfs f1,0(r5) b Lfinish nop nop /* case FFI_TYPE_DOUBLE */ Lret_type3: lfd f1,0(r5) b Lfinish nop nop /* case FFI_TYPE_LONGDOUBLE */ Lret_type4: lfd f1,0(r5) lfd f2,8(r5) b Lfinish nop /* case FFI_TYPE_UINT8 */ Lret_type5: lbz r3,3(r5) b Lfinish nop nop /* case FFI_TYPE_SINT8 */ Lret_type6: lbz r3,3(r5) extsb r3,r3 b Lfinish nop /* case FFI_TYPE_UINT16 */ Lret_type7: lhz r3,2(r5) b Lfinish nop nop /* case FFI_TYPE_SINT16 */ Lret_type8: lha r3,2(r5) b Lfinish nop nop /* case FFI_TYPE_UINT32 */ Lret_type9: lwz r3,0(r5) b Lfinish nop nop /* case FFI_TYPE_SINT32 */ Lret_type10: lwz r3,0(r5) b Lfinish nop nop /* case FFI_TYPE_UINT64 */ Lret_type11: lwz r3,0(r5) lwz r4,4(r5) b Lfinish nop /* case FFI_TYPE_SINT64 */ Lret_type12: lwz r3,0(r5) lwz r4,4(r5) b Lfinish nop /* case FFI_TYPE_STRUCT */ Lret_type13: b Lfinish nop nop nop /* case FFI_TYPE_POINTER */ Lret_type14: lwz r3,0(r5) b Lfinish nop nop /* case done */ Lfinish: addi r1,r1,176 /* Restore stack pointer. */ lwz r0,8(r1) /* Get return address. */ mtlr r0 /* Reset link register. */ blr /* END(ffi_closure_ASM) */ .data .section __TEXT,__eh_frame,coalesced,no_toc+strip_static_syms+live_support EH_frame1: .set L$set$0,LECIE1-LSCIE1 .long L$set$0 ; Length of Common Information Entry LSCIE1: .long 0x0 ; CIE Identifier Tag .byte 0x1 ; CIE Version .ascii "zR\0" ; CIE Augmentation .byte 0x1 ; uleb128 0x1; CIE Code Alignment Factor .byte 0x7c ; sleb128 -4; CIE Data Alignment Factor .byte 0x41 ; CIE RA Column .byte 0x1 ; uleb128 0x1; Augmentation size .byte 0x90 ; FDE Encoding (indirect pcrel) .byte 0xc ; DW_CFA_def_cfa .byte 0x1 ; uleb128 0x1 .byte 0x0 ; uleb128 0x0 .align LOG2_GPR_BYTES LECIE1: .globl _ffi_closure_ASM.eh _ffi_closure_ASM.eh: LSFDE1: .set L$set$1,LEFDE1-LASFDE1 .long L$set$1 ; FDE Length LASFDE1: .long LASFDE1-EH_frame1 ; FDE CIE offset .g_long LLFB1$non_lazy_ptr-. ; FDE initial location .set L$set$3,LFE1-LFB1 .g_long L$set$3 ; FDE address range .byte 0x0 ; uleb128 0x0; Augmentation size .byte 0x4 ; DW_CFA_advance_loc4 .set L$set$3,LCFI1-LCFI0 .long L$set$3 .byte 0xe ; DW_CFA_def_cfa_offset .byte 176,1 ; uleb128 176 .byte 0x4 ; DW_CFA_advance_loc4 .set L$set$4,LCFI0-LFB1 .long L$set$4 .byte 0x11 ; DW_CFA_offset_extended_sf .byte 0x41 ; uleb128 0x41 .byte 0x7e ; sleb128 -2 .align LOG2_GPR_BYTES LEFDE1: .data .align LOG2_GPR_BYTES LDFCM0: .section __TEXT,__picsymbolstub1,symbol_stubs,pure_instructions,32 .align LOG2_GPR_BYTES Lffi_closure_helper_DARWIN$stub: #if 1 .indirect_symbol _ffi_closure_helper_DARWIN mflr r0 bcl 20,31,LO$ffi_closure_helper_DARWIN LO$ffi_closure_helper_DARWIN: mflr r11 addis r11,r11,ha16(L_ffi_closure_helper_DARWIN$lazy_ptr - LO$ffi_closure_helper_DARWIN) mtlr r0 lgu r12,lo16(L_ffi_closure_helper_DARWIN$lazy_ptr - LO$ffi_closure_helper_DARWIN)(r11) mtctr r12 bctr .lazy_symbol_pointer L_ffi_closure_helper_DARWIN$lazy_ptr: .indirect_symbol _ffi_closure_helper_DARWIN .g_long dyld_stub_binding_helper #endif .data .align LOG2_GPR_BYTES LLFB1$non_lazy_ptr: .g_long LFB1 smalltalk-3.2.5/libffi/src/powerpc/sysv.S0000644000175000017500000001465412130343734015271 00000000000000/* ----------------------------------------------------------------------- sysv.S - Copyright (c) 1998 Geoffrey Keating Copyright (C) 2007 Free Software Foundation, Inc PowerPC Assembly glue. Permission is hereby granted, free of charge, to any person obtaining a copy of this software and associated documentation files (the ``Software''), to deal in the Software without restriction, including without limitation the rights to use, copy, modify, merge, publish, distribute, sublicense, and/or sell copies of the Software, and to permit persons to whom the Software is furnished to do so, subject to the following conditions: The above copyright notice and this permission notice shall be included in all copies or substantial portions of the Software. THE SOFTWARE IS PROVIDED ``AS IS'', WITHOUT WARRANTY OF ANY KIND, EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. ----------------------------------------------------------------------- */ #define LIBFFI_ASM #include #include #include #ifndef __powerpc64__ .globl ffi_prep_args_SYSV ENTRY(ffi_call_SYSV) .LFB1: /* Save the old stack pointer as AP. */ mr %r8,%r1 .LCFI0: /* Allocate the stack space we need. */ stwux %r1,%r1,%r4 /* Save registers we use. */ mflr %r9 stw %r28,-16(%r8) .LCFI1: stw %r29,-12(%r8) .LCFI2: stw %r30, -8(%r8) .LCFI3: stw %r31, -4(%r8) .LCFI4: stw %r9, 4(%r8) .LCFI5: /* Save arguments over call... */ mr %r31,%r5 /* flags, */ mr %r30,%r6 /* rvalue, */ mr %r29,%r7 /* function address, */ mr %r28,%r8 /* our AP. */ .LCFI6: /* Call ffi_prep_args_SYSV. */ mr %r4,%r1 bl ffi_prep_args_SYSV@local /* Now do the call. */ /* Set up cr1 with bits 4-7 of the flags. */ mtcrf 0x40,%r31 /* Get the address to call into CTR. */ mtctr %r29 /* Load all those argument registers. */ lwz %r3,-16-(8*4)(%r28) lwz %r4,-16-(7*4)(%r28) lwz %r5,-16-(6*4)(%r28) lwz %r6,-16-(5*4)(%r28) bf- 5,1f nop lwz %r7,-16-(4*4)(%r28) lwz %r8,-16-(3*4)(%r28) lwz %r9,-16-(2*4)(%r28) lwz %r10,-16-(1*4)(%r28) nop 1: /* Load all the FP registers. */ bf- 6,2f lfd %f1,-16-(8*4)-(8*8)(%r28) lfd %f2,-16-(8*4)-(7*8)(%r28) lfd %f3,-16-(8*4)-(6*8)(%r28) lfd %f4,-16-(8*4)-(5*8)(%r28) nop lfd %f5,-16-(8*4)-(4*8)(%r28) lfd %f6,-16-(8*4)-(3*8)(%r28) lfd %f7,-16-(8*4)-(2*8)(%r28) lfd %f8,-16-(8*4)-(1*8)(%r28) 2: /* Make the call. */ bctrl /* Now, deal with the return value. */ mtcrf 0x01,%r31 /* cr7 */ bt- 31,L(small_struct_return_value) bt- 30,L(done_return_value) bt- 29,L(fp_return_value) stw %r3,0(%r30) bf+ 28,L(done_return_value) stw %r4,4(%r30) mtcrf 0x02,%r31 /* cr6 */ bf 27,L(done_return_value) stw %r5,8(%r30) stw %r6,12(%r30) /* Fall through... */ L(done_return_value): /* Restore the registers we used and return. */ lwz %r9, 4(%r28) lwz %r31, -4(%r28) mtlr %r9 lwz %r30, -8(%r28) lwz %r29,-12(%r28) lwz %r28,-16(%r28) lwz %r1,0(%r1) blr L(fp_return_value): bf 28,L(float_return_value) stfd %f1,0(%r30) mtcrf 0x02,%r31 /* cr6 */ bf 27,L(done_return_value) stfd %f2,8(%r30) b L(done_return_value) L(float_return_value): stfs %f1,0(%r30) b L(done_return_value) L(small_struct_return_value): extrwi %r6,%r31,2,19 /* number of bytes padding = shift/8 */ mtcrf 0x02,%r31 /* copy flags to cr[24:27] (cr6) */ extrwi %r5,%r31,5,19 /* r5 <- number of bits of padding */ subfic %r6,%r6,4 /* r6 <- number of useful bytes in r3 */ bf- 25,L(done_return_value) /* struct in r3 ? if not, done. */ /* smst_one_register: */ slw %r3,%r3,%r5 /* Left-justify value in r3 */ mtxer %r6 /* move byte count to XER ... */ stswx %r3,0,%r30 /* ... and store that many bytes */ bf+ 26,L(done_return_value) /* struct in r3:r4 ? */ add %r6,%r6,%r30 /* adjust pointer */ stswi %r4,%r6,4 /* store last four bytes */ b L(done_return_value) .LFE1: END(ffi_call_SYSV) .section ".eh_frame",EH_FRAME_FLAGS,@progbits .Lframe1: .4byte .LECIE1-.LSCIE1 /* Length of Common Information Entry */ .LSCIE1: .4byte 0x0 /* CIE Identifier Tag */ .byte 0x1 /* CIE Version */ #if defined _RELOCATABLE || defined __PIC__ .ascii "zR\0" /* CIE Augmentation */ #else .ascii "\0" /* CIE Augmentation */ #endif .uleb128 0x1 /* CIE Code Alignment Factor */ .sleb128 -4 /* CIE Data Alignment Factor */ .byte 0x41 /* CIE RA Column */ #if defined _RELOCATABLE || defined __PIC__ .uleb128 0x1 /* Augmentation size */ .byte 0x1b /* FDE Encoding (pcrel sdata4) */ #endif .byte 0xc /* DW_CFA_def_cfa */ .uleb128 0x1 .uleb128 0x0 .align 2 .LECIE1: .LSFDE1: .4byte .LEFDE1-.LASFDE1 /* FDE Length */ .LASFDE1: .4byte .LASFDE1-.Lframe1 /* FDE CIE offset */ #if defined _RELOCATABLE || defined __PIC__ .4byte .LFB1-. /* FDE initial location */ #else .4byte .LFB1 /* FDE initial location */ #endif .4byte .LFE1-.LFB1 /* FDE address range */ #if defined _RELOCATABLE || defined __PIC__ .uleb128 0x0 /* Augmentation size */ #endif .byte 0x4 /* DW_CFA_advance_loc4 */ .4byte .LCFI0-.LFB1 .byte 0xd /* DW_CFA_def_cfa_register */ .uleb128 0x08 .byte 0x4 /* DW_CFA_advance_loc4 */ .4byte .LCFI5-.LCFI0 .byte 0x11 /* DW_CFA_offset_extended_sf */ .uleb128 0x41 .sleb128 -1 .byte 0x9f /* DW_CFA_offset, column 0x1f */ .uleb128 0x1 .byte 0x9e /* DW_CFA_offset, column 0x1e */ .uleb128 0x2 .byte 0x9d /* DW_CFA_offset, column 0x1d */ .uleb128 0x3 .byte 0x9c /* DW_CFA_offset, column 0x1c */ .uleb128 0x4 .byte 0x4 /* DW_CFA_advance_loc4 */ .4byte .LCFI6-.LCFI5 .byte 0xd /* DW_CFA_def_cfa_register */ .uleb128 0x1c .align 2 .LEFDE1: #endif #if defined __ELF__ && defined __linux__ .section .note.GNU-stack,"",@progbits #endif smalltalk-3.2.5/libffi/src/powerpc/ffi.c0000644000175000017500000011422012130343734015037 00000000000000/* ----------------------------------------------------------------------- ffi.c - Copyright (c) 1998 Geoffrey Keating Copyright (C) 2007, 2008 Free Software Foundation, Inc Copyright (C) 2008 Red Hat, Inc PowerPC Foreign Function Interface Permission is hereby granted, free of charge, to any person obtaining a copy of this software and associated documentation files (the ``Software''), to deal in the Software without restriction, including without limitation the rights to use, copy, modify, merge, publish, distribute, sublicense, and/or sell copies of the Software, and to permit persons to whom the Software is furnished to do so, subject to the following conditions: The above copyright notice and this permission notice shall be included in all copies or substantial portions of the Software. THE SOFTWARE IS PROVIDED ``AS IS'', WITHOUT WARRANTY OF ANY KIND, EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHOR BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. ----------------------------------------------------------------------- */ #include #include #include #include extern void ffi_closure_SYSV (void); extern void FFI_HIDDEN ffi_closure_LINUX64 (void); enum { /* The assembly depends on these exact flags. */ FLAG_RETURNS_SMST = 1 << (31-31), /* Used for FFI_SYSV small structs. */ FLAG_RETURNS_NOTHING = 1 << (31-30), /* These go in cr7 */ FLAG_RETURNS_FP = 1 << (31-29), FLAG_RETURNS_64BITS = 1 << (31-28), FLAG_RETURNS_128BITS = 1 << (31-27), /* cr6 */ FLAG_SYSV_SMST_R4 = 1 << (31-26), /* use r4 for FFI_SYSV 8 byte structs. */ FLAG_SYSV_SMST_R3 = 1 << (31-25), /* use r3 for FFI_SYSV 4 byte structs. */ /* Bits (31-24) through (31-19) store shift value for SMST */ FLAG_ARG_NEEDS_COPY = 1 << (31- 7), FLAG_FP_ARGUMENTS = 1 << (31- 6), /* cr1.eq; specified by ABI */ FLAG_4_GPR_ARGUMENTS = 1 << (31- 5), FLAG_RETVAL_REFERENCE = 1 << (31- 4) }; /* About the SYSV ABI. */ unsigned int NUM_GPR_ARG_REGISTERS = 8; #ifndef __NO_FPRS__ unsigned int NUM_FPR_ARG_REGISTERS = 8; #else unsigned int NUM_FPR_ARG_REGISTERS = 0; #endif enum { ASM_NEEDS_REGISTERS = 4 }; /* ffi_prep_args_SYSV is called by the assembly routine once stack space has been allocated for the function's arguments. The stack layout we want looks like this: | Return address from ffi_call_SYSV 4bytes | higher addresses |--------------------------------------------| | Previous backchain pointer 4 | stack pointer here |--------------------------------------------|<+ <<< on entry to | Saved r28-r31 4*4 | | ffi_call_SYSV |--------------------------------------------| | | GPR registers r3-r10 8*4 | | ffi_call_SYSV |--------------------------------------------| | | FPR registers f1-f8 (optional) 8*8 | | |--------------------------------------------| | stack | | Space for copied structures | | grows | |--------------------------------------------| | down V | Parameters that didn't fit in registers | | |--------------------------------------------| | lower addresses | Space for callee's LR 4 | | |--------------------------------------------| | stack pointer here | Current backchain pointer 4 |-/ during |--------------------------------------------| <<< ffi_call_SYSV */ void ffi_prep_args_SYSV (extended_cif *ecif, unsigned *const stack) { const unsigned bytes = ecif->cif->bytes; const unsigned flags = ecif->cif->flags; typedef union { char *c; unsigned *u; long long *ll; float *f; double *d; } valp; /* 'stacktop' points at the previous backchain pointer. */ valp stacktop; /* 'gpr_base' points at the space for gpr3, and grows upwards as we use GPR registers. */ valp gpr_base; int intarg_count; /* 'fpr_base' points at the space for fpr1, and grows upwards as we use FPR registers. */ valp fpr_base; int fparg_count; /* 'copy_space' grows down as we put structures in it. It should stay 16-byte aligned. */ valp copy_space; /* 'next_arg' grows up as we put parameters in it. */ valp next_arg; int i, ii MAYBE_UNUSED; ffi_type **ptr; double double_tmp; union { void **v; char **c; signed char **sc; unsigned char **uc; signed short **ss; unsigned short **us; unsigned int **ui; long long **ll; float **f; double **d; } p_argv; size_t struct_copy_size; unsigned gprvalue; if (ecif->cif->abi == FFI_LINUX_SOFT_FLOAT) NUM_FPR_ARG_REGISTERS = 0; stacktop.c = (char *) stack + bytes; gpr_base.u = stacktop.u - ASM_NEEDS_REGISTERS - NUM_GPR_ARG_REGISTERS; intarg_count = 0; fpr_base.d = gpr_base.d - NUM_FPR_ARG_REGISTERS; fparg_count = 0; copy_space.c = ((flags & FLAG_FP_ARGUMENTS) ? fpr_base.c : gpr_base.c); next_arg.u = stack + 2; /* Check that everything starts aligned properly. */ FFI_ASSERT (((unsigned) (char *) stack & 0xF) == 0); FFI_ASSERT (((unsigned) copy_space.c & 0xF) == 0); FFI_ASSERT (((unsigned) stacktop.c & 0xF) == 0); FFI_ASSERT ((bytes & 0xF) == 0); FFI_ASSERT (copy_space.c >= next_arg.c); /* Deal with return values that are actually pass-by-reference. */ if (flags & FLAG_RETVAL_REFERENCE) { *gpr_base.u++ = (unsigned long) (char *) ecif->rvalue; intarg_count++; } /* Now for the arguments. */ p_argv.v = ecif->avalue; for (ptr = ecif->cif->arg_types, i = ecif->cif->nargs; i > 0; i--, ptr++, p_argv.v++) { switch ((*ptr)->type) { case FFI_TYPE_FLOAT: /* With FFI_LINUX_SOFT_FLOAT floats are handled like UINT32. */ if (ecif->cif->abi == FFI_LINUX_SOFT_FLOAT) goto soft_float_prep; double_tmp = **p_argv.f; if (fparg_count >= NUM_FPR_ARG_REGISTERS) { *next_arg.f = (float) double_tmp; next_arg.u += 1; intarg_count++; } else *fpr_base.d++ = double_tmp; fparg_count++; FFI_ASSERT (flags & FLAG_FP_ARGUMENTS); break; case FFI_TYPE_DOUBLE: /* With FFI_LINUX_SOFT_FLOAT doubles are handled like UINT64. */ if (ecif->cif->abi == FFI_LINUX_SOFT_FLOAT) goto soft_double_prep; double_tmp = **p_argv.d; if (fparg_count >= NUM_FPR_ARG_REGISTERS) { if (intarg_count >= NUM_GPR_ARG_REGISTERS && intarg_count % 2 != 0) { intarg_count++; next_arg.u++; } *next_arg.d = double_tmp; next_arg.u += 2; } else *fpr_base.d++ = double_tmp; fparg_count++; FFI_ASSERT (flags & FLAG_FP_ARGUMENTS); break; #if FFI_TYPE_LONGDOUBLE != FFI_TYPE_DOUBLE case FFI_TYPE_LONGDOUBLE: if ((ecif->cif->abi != FFI_LINUX) && (ecif->cif->abi != FFI_LINUX_SOFT_FLOAT)) goto do_struct; /* The soft float ABI for long doubles works like this, a long double is passed in four consecutive gprs if available. A maximum of 2 long doubles can be passed in gprs. If we do not have 4 gprs left, the long double is passed on the stack, 4-byte aligned. */ if (ecif->cif->abi == FFI_LINUX_SOFT_FLOAT) { unsigned int int_tmp = (*p_argv.ui)[0]; if (intarg_count >= NUM_GPR_ARG_REGISTERS - 3) { if (intarg_count < NUM_GPR_ARG_REGISTERS) intarg_count += NUM_GPR_ARG_REGISTERS - intarg_count; *next_arg.u = int_tmp; next_arg.u++; for (ii = 1; ii < 4; ii++) { int_tmp = (*p_argv.ui)[ii]; *next_arg.u = int_tmp; next_arg.u++; } } else { *gpr_base.u++ = int_tmp; for (ii = 1; ii < 4; ii++) { int_tmp = (*p_argv.ui)[ii]; *gpr_base.u++ = int_tmp; } } intarg_count +=4; } else { double_tmp = (*p_argv.d)[0]; if (fparg_count >= NUM_FPR_ARG_REGISTERS - 1) { if (intarg_count >= NUM_GPR_ARG_REGISTERS && intarg_count % 2 != 0) { intarg_count++; next_arg.u++; } *next_arg.d = double_tmp; next_arg.u += 2; double_tmp = (*p_argv.d)[1]; *next_arg.d = double_tmp; next_arg.u += 2; } else { *fpr_base.d++ = double_tmp; double_tmp = (*p_argv.d)[1]; *fpr_base.d++ = double_tmp; } fparg_count += 2; FFI_ASSERT (flags & FLAG_FP_ARGUMENTS); } break; #endif case FFI_TYPE_UINT64: case FFI_TYPE_SINT64: soft_double_prep: if (intarg_count == NUM_GPR_ARG_REGISTERS-1) intarg_count++; if (intarg_count >= NUM_GPR_ARG_REGISTERS) { if (intarg_count % 2 != 0) { intarg_count++; next_arg.u++; } *next_arg.ll = **p_argv.ll; next_arg.u += 2; } else { /* whoops: abi states only certain register pairs * can be used for passing long long int * specifically (r3,r4), (r5,r6), (r7,r8), * (r9,r10) and if next arg is long long but * not correct starting register of pair then skip * until the proper starting register */ if (intarg_count % 2 != 0) { intarg_count ++; gpr_base.u++; } *gpr_base.ll++ = **p_argv.ll; } intarg_count += 2; break; case FFI_TYPE_STRUCT: #if FFI_TYPE_LONGDOUBLE != FFI_TYPE_DOUBLE do_struct: #endif struct_copy_size = ((*ptr)->size + 15) & ~0xF; copy_space.c -= struct_copy_size; memcpy (copy_space.c, *p_argv.c, (*ptr)->size); gprvalue = (unsigned long) copy_space.c; FFI_ASSERT (copy_space.c > next_arg.c); FFI_ASSERT (flags & FLAG_ARG_NEEDS_COPY); goto putgpr; case FFI_TYPE_UINT8: gprvalue = **p_argv.uc; goto putgpr; case FFI_TYPE_SINT8: gprvalue = **p_argv.sc; goto putgpr; case FFI_TYPE_UINT16: gprvalue = **p_argv.us; goto putgpr; case FFI_TYPE_SINT16: gprvalue = **p_argv.ss; goto putgpr; case FFI_TYPE_INT: case FFI_TYPE_UINT32: case FFI_TYPE_SINT32: case FFI_TYPE_POINTER: soft_float_prep: gprvalue = **p_argv.ui; putgpr: if (intarg_count >= NUM_GPR_ARG_REGISTERS) *next_arg.u++ = gprvalue; else *gpr_base.u++ = gprvalue; intarg_count++; break; } } /* Check that we didn't overrun the stack... */ FFI_ASSERT (copy_space.c >= next_arg.c); FFI_ASSERT (gpr_base.u <= stacktop.u - ASM_NEEDS_REGISTERS); FFI_ASSERT (fpr_base.u <= stacktop.u - ASM_NEEDS_REGISTERS - NUM_GPR_ARG_REGISTERS); FFI_ASSERT (flags & FLAG_4_GPR_ARGUMENTS || intarg_count <= 4); } /* About the LINUX64 ABI. */ enum { NUM_GPR_ARG_REGISTERS64 = 8, NUM_FPR_ARG_REGISTERS64 = 13 }; enum { ASM_NEEDS_REGISTERS64 = 4 }; /* ffi_prep_args64 is called by the assembly routine once stack space has been allocated for the function's arguments. The stack layout we want looks like this: | Ret addr from ffi_call_LINUX64 8bytes | higher addresses |--------------------------------------------| | CR save area 8bytes | |--------------------------------------------| | Previous backchain pointer 8 | stack pointer here |--------------------------------------------|<+ <<< on entry to | Saved r28-r31 4*8 | | ffi_call_LINUX64 |--------------------------------------------| | | GPR registers r3-r10 8*8 | | |--------------------------------------------| | | FPR registers f1-f13 (optional) 13*8 | | |--------------------------------------------| | | Parameter save area | | |--------------------------------------------| | | TOC save area 8 | | |--------------------------------------------| | stack | | Linker doubleword 8 | | grows | |--------------------------------------------| | down V | Compiler doubleword 8 | | |--------------------------------------------| | lower addresses | Space for callee's LR 8 | | |--------------------------------------------| | | CR save area 8 | | |--------------------------------------------| | stack pointer here | Current backchain pointer 8 |-/ during |--------------------------------------------| <<< ffi_call_LINUX64 */ void FFI_HIDDEN ffi_prep_args64 (extended_cif *ecif, unsigned long *const stack) { const unsigned long bytes = ecif->cif->bytes; const unsigned long flags = ecif->cif->flags; typedef union { char *c; unsigned long *ul; float *f; double *d; } valp; /* 'stacktop' points at the previous backchain pointer. */ valp stacktop; /* 'next_arg' points at the space for gpr3, and grows upwards as we use GPR registers, then continues at rest. */ valp gpr_base; valp gpr_end; valp rest; valp next_arg; /* 'fpr_base' points at the space for fpr3, and grows upwards as we use FPR registers. */ valp fpr_base; int fparg_count; int i, words; ffi_type **ptr; double double_tmp; union { void **v; char **c; signed char **sc; unsigned char **uc; signed short **ss; unsigned short **us; signed int **si; unsigned int **ui; unsigned long **ul; float **f; double **d; } p_argv; unsigned long gprvalue; stacktop.c = (char *) stack + bytes; gpr_base.ul = stacktop.ul - ASM_NEEDS_REGISTERS64 - NUM_GPR_ARG_REGISTERS64; gpr_end.ul = gpr_base.ul + NUM_GPR_ARG_REGISTERS64; rest.ul = stack + 6 + NUM_GPR_ARG_REGISTERS64; fpr_base.d = gpr_base.d - NUM_FPR_ARG_REGISTERS64; fparg_count = 0; next_arg.ul = gpr_base.ul; /* Check that everything starts aligned properly. */ FFI_ASSERT (((unsigned long) (char *) stack & 0xF) == 0); FFI_ASSERT (((unsigned long) stacktop.c & 0xF) == 0); FFI_ASSERT ((bytes & 0xF) == 0); /* Deal with return values that are actually pass-by-reference. */ if (flags & FLAG_RETVAL_REFERENCE) *next_arg.ul++ = (unsigned long) (char *) ecif->rvalue; /* Now for the arguments. */ p_argv.v = ecif->avalue; for (ptr = ecif->cif->arg_types, i = ecif->cif->nargs; i > 0; i--, ptr++, p_argv.v++) { switch ((*ptr)->type) { case FFI_TYPE_FLOAT: double_tmp = **p_argv.f; *next_arg.f = (float) double_tmp; if (++next_arg.ul == gpr_end.ul) next_arg.ul = rest.ul; if (fparg_count < NUM_FPR_ARG_REGISTERS64) *fpr_base.d++ = double_tmp; fparg_count++; FFI_ASSERT (flags & FLAG_FP_ARGUMENTS); break; case FFI_TYPE_DOUBLE: double_tmp = **p_argv.d; *next_arg.d = double_tmp; if (++next_arg.ul == gpr_end.ul) next_arg.ul = rest.ul; if (fparg_count < NUM_FPR_ARG_REGISTERS64) *fpr_base.d++ = double_tmp; fparg_count++; FFI_ASSERT (flags & FLAG_FP_ARGUMENTS); break; #if FFI_TYPE_LONGDOUBLE != FFI_TYPE_DOUBLE case FFI_TYPE_LONGDOUBLE: double_tmp = (*p_argv.d)[0]; *next_arg.d = double_tmp; if (++next_arg.ul == gpr_end.ul) next_arg.ul = rest.ul; if (fparg_count < NUM_FPR_ARG_REGISTERS64) *fpr_base.d++ = double_tmp; fparg_count++; double_tmp = (*p_argv.d)[1]; *next_arg.d = double_tmp; if (++next_arg.ul == gpr_end.ul) next_arg.ul = rest.ul; if (fparg_count < NUM_FPR_ARG_REGISTERS64) *fpr_base.d++ = double_tmp; fparg_count++; FFI_ASSERT (__LDBL_MANT_DIG__ == 106); FFI_ASSERT (flags & FLAG_FP_ARGUMENTS); break; #endif case FFI_TYPE_STRUCT: words = ((*ptr)->size + 7) / 8; if (next_arg.ul >= gpr_base.ul && next_arg.ul + words > gpr_end.ul) { size_t first = gpr_end.c - next_arg.c; memcpy (next_arg.c, *p_argv.c, first); memcpy (rest.c, *p_argv.c + first, (*ptr)->size - first); next_arg.c = rest.c + words * 8 - first; } else { char *where = next_arg.c; /* Structures with size less than eight bytes are passed left-padded. */ if ((*ptr)->size < 8) where += 8 - (*ptr)->size; memcpy (where, *p_argv.c, (*ptr)->size); next_arg.ul += words; if (next_arg.ul == gpr_end.ul) next_arg.ul = rest.ul; } break; case FFI_TYPE_UINT8: gprvalue = **p_argv.uc; goto putgpr; case FFI_TYPE_SINT8: gprvalue = **p_argv.sc; goto putgpr; case FFI_TYPE_UINT16: gprvalue = **p_argv.us; goto putgpr; case FFI_TYPE_SINT16: gprvalue = **p_argv.ss; goto putgpr; case FFI_TYPE_UINT32: gprvalue = **p_argv.ui; goto putgpr; case FFI_TYPE_INT: case FFI_TYPE_SINT32: gprvalue = **p_argv.si; goto putgpr; case FFI_TYPE_UINT64: case FFI_TYPE_SINT64: case FFI_TYPE_POINTER: gprvalue = **p_argv.ul; putgpr: *next_arg.ul++ = gprvalue; if (next_arg.ul == gpr_end.ul) next_arg.ul = rest.ul; break; } } FFI_ASSERT (flags & FLAG_4_GPR_ARGUMENTS || (next_arg.ul >= gpr_base.ul && next_arg.ul <= gpr_base.ul + 4)); } /* Perform machine dependent cif processing */ ffi_status ffi_prep_cif_machdep (ffi_cif *cif) { /* All this is for the SYSV and LINUX64 ABI. */ int i; ffi_type **ptr; unsigned bytes; int fparg_count = 0, intarg_count = 0; unsigned flags = 0; unsigned struct_copy_size = 0; unsigned type = cif->rtype->type; unsigned size = cif->rtype->size; if (cif->abi == FFI_LINUX_SOFT_FLOAT) NUM_FPR_ARG_REGISTERS = 0; if (cif->abi != FFI_LINUX64) { /* All the machine-independent calculation of cif->bytes will be wrong. Redo the calculation for SYSV. */ /* Space for the frame pointer, callee's LR, and the asm's temp regs. */ bytes = (2 + ASM_NEEDS_REGISTERS) * sizeof (int); /* Space for the GPR registers. */ bytes += NUM_GPR_ARG_REGISTERS * sizeof (int); } else { /* 64-bit ABI. */ /* Space for backchain, CR, LR, cc/ld doubleword, TOC and the asm's temp regs. */ bytes = (6 + ASM_NEEDS_REGISTERS64) * sizeof (long); /* Space for the mandatory parm save area and general registers. */ bytes += 2 * NUM_GPR_ARG_REGISTERS64 * sizeof (long); } /* Return value handling. The rules for SYSV are as follows: - 32-bit (or less) integer values are returned in gpr3; - Structures of size <= 4 bytes also returned in gpr3; - 64-bit integer values and structures between 5 and 8 bytes are returned in gpr3 and gpr4; - Single/double FP values are returned in fpr1; - Larger structures are allocated space and a pointer is passed as the first argument. - long doubles (if not equivalent to double) are returned in fpr1,fpr2 for Linux and as for large structs for SysV. For LINUX64: - integer values in gpr3; - Structures/Unions by reference; - Single/double FP values in fpr1, long double in fpr1,fpr2. - soft-float float/doubles are treated as UINT32/UINT64 respectivley. - soft-float long doubles are returned in gpr3-gpr6. */ switch (type) { #if FFI_TYPE_LONGDOUBLE != FFI_TYPE_DOUBLE case FFI_TYPE_LONGDOUBLE: if (cif->abi != FFI_LINUX && cif->abi != FFI_LINUX64 && cif->abi != FFI_LINUX_SOFT_FLOAT) goto byref; flags |= FLAG_RETURNS_128BITS; /* Fall through. */ #endif case FFI_TYPE_DOUBLE: flags |= FLAG_RETURNS_64BITS; /* Fall through. */ case FFI_TYPE_FLOAT: /* With FFI_LINUX_SOFT_FLOAT no fp registers are used. */ if (cif->abi != FFI_LINUX_SOFT_FLOAT) flags |= FLAG_RETURNS_FP; break; case FFI_TYPE_UINT64: case FFI_TYPE_SINT64: flags |= FLAG_RETURNS_64BITS; break; case FFI_TYPE_STRUCT: if (cif->abi == FFI_SYSV) { /* The final SYSV ABI says that structures smaller or equal 8 bytes are returned in r3/r4. The FFI_GCC_SYSV ABI instead returns them in memory. */ /* Treat structs with size <= 8 bytes. */ if (size <= 8) { flags |= FLAG_RETURNS_SMST; /* These structs are returned in r3. We pack the type and the precalculated shift value (needed in the sysv.S) into flags. The same applies for the structs returned in r3/r4. */ if (size <= 4) { flags |= FLAG_SYSV_SMST_R3; flags |= 8 * (4 - size) << 8; break; } /* These structs are returned in r3 and r4. See above. */ if (size <= 8) { flags |= FLAG_SYSV_SMST_R3 | FLAG_SYSV_SMST_R4; flags |= 8 * (8 - size) << 8; break; } } } #if FFI_TYPE_LONGDOUBLE != FFI_TYPE_DOUBLE byref: #endif intarg_count++; flags |= FLAG_RETVAL_REFERENCE; /* Fall through. */ case FFI_TYPE_VOID: flags |= FLAG_RETURNS_NOTHING; break; default: /* Returns 32-bit integer, or similar. Nothing to do here. */ break; } if (cif->abi != FFI_LINUX64) /* The first NUM_GPR_ARG_REGISTERS words of integer arguments, and the first NUM_FPR_ARG_REGISTERS fp arguments, go in registers; the rest goes on the stack. Structures and long doubles (if not equivalent to double) are passed as a pointer to a copy of the structure. Stuff on the stack needs to keep proper alignment. */ for (ptr = cif->arg_types, i = cif->nargs; i > 0; i--, ptr++) { switch ((*ptr)->type) { case FFI_TYPE_FLOAT: /* With FFI_LINUX_SOFT_FLOAT floats are handled like UINT32. */ if (cif->abi == FFI_LINUX_SOFT_FLOAT) goto soft_float_cif; fparg_count++; /* floating singles are not 8-aligned on stack */ break; #if FFI_TYPE_LONGDOUBLE != FFI_TYPE_DOUBLE case FFI_TYPE_LONGDOUBLE: if (cif->abi != FFI_LINUX && cif->abi != FFI_LINUX_SOFT_FLOAT) goto do_struct; if (cif->abi == FFI_LINUX_SOFT_FLOAT) { if (intarg_count >= NUM_GPR_ARG_REGISTERS - 3 || intarg_count < NUM_GPR_ARG_REGISTERS) /* A long double in FFI_LINUX_SOFT_FLOAT can use only a set of four consecutive gprs. If we have not enough, we have to adjust the intarg_count value. */ intarg_count += NUM_GPR_ARG_REGISTERS - intarg_count; intarg_count += 4; break; } else fparg_count++; /* Fall thru */ #endif case FFI_TYPE_DOUBLE: /* With FFI_LINUX_SOFT_FLOAT doubles are handled like UINT64. */ if (cif->abi == FFI_LINUX_SOFT_FLOAT) goto soft_double_cif; fparg_count++; /* If this FP arg is going on the stack, it must be 8-byte-aligned. */ if (fparg_count > NUM_FPR_ARG_REGISTERS && intarg_count >= NUM_GPR_ARG_REGISTERS && intarg_count % 2 != 0) intarg_count++; break; case FFI_TYPE_UINT64: case FFI_TYPE_SINT64: soft_double_cif: /* 'long long' arguments are passed as two words, but either both words must fit in registers or both go on the stack. If they go on the stack, they must be 8-byte-aligned. Also, only certain register pairs can be used for passing long long int -- specifically (r3,r4), (r5,r6), (r7,r8), (r9,r10). */ if (intarg_count == NUM_GPR_ARG_REGISTERS-1 || intarg_count % 2 != 0) intarg_count++; intarg_count += 2; break; case FFI_TYPE_STRUCT: #if FFI_TYPE_LONGDOUBLE != FFI_TYPE_DOUBLE do_struct: #endif /* We must allocate space for a copy of these to enforce pass-by-value. Pad the space up to a multiple of 16 bytes (the maximum alignment required for anything under the SYSV ABI). */ struct_copy_size += ((*ptr)->size + 15) & ~0xF; /* Fall through (allocate space for the pointer). */ default: soft_float_cif: /* Everything else is passed as a 4-byte word in a GPR, either the object itself or a pointer to it. */ intarg_count++; break; } } else for (ptr = cif->arg_types, i = cif->nargs; i > 0; i--, ptr++) { switch ((*ptr)->type) { #if FFI_TYPE_LONGDOUBLE != FFI_TYPE_DOUBLE case FFI_TYPE_LONGDOUBLE: if (cif->abi == FFI_LINUX_SOFT_FLOAT) intarg_count += 4; else { fparg_count += 2; intarg_count += 2; } break; #endif case FFI_TYPE_FLOAT: case FFI_TYPE_DOUBLE: fparg_count++; intarg_count++; break; case FFI_TYPE_STRUCT: intarg_count += ((*ptr)->size + 7) / 8; break; default: /* Everything else is passed as a 8-byte word in a GPR, either the object itself or a pointer to it. */ intarg_count++; break; } } if (fparg_count != 0) flags |= FLAG_FP_ARGUMENTS; if (intarg_count > 4) flags |= FLAG_4_GPR_ARGUMENTS; if (struct_copy_size != 0) flags |= FLAG_ARG_NEEDS_COPY; if (cif->abi != FFI_LINUX64) { /* Space for the FPR registers, if needed. */ if (fparg_count != 0) bytes += NUM_FPR_ARG_REGISTERS * sizeof (double); /* Stack space. */ if (intarg_count > NUM_GPR_ARG_REGISTERS) bytes += (intarg_count - NUM_GPR_ARG_REGISTERS) * sizeof (int); if (fparg_count > NUM_FPR_ARG_REGISTERS) bytes += (fparg_count - NUM_FPR_ARG_REGISTERS) * sizeof (double); } else { /* Space for the FPR registers, if needed. */ if (fparg_count != 0) bytes += NUM_FPR_ARG_REGISTERS64 * sizeof (double); /* Stack space. */ if (intarg_count > NUM_GPR_ARG_REGISTERS64) bytes += (intarg_count - NUM_GPR_ARG_REGISTERS64) * sizeof (long); } /* The stack space allocated needs to be a multiple of 16 bytes. */ bytes = (bytes + 15) & ~0xF; /* Add in the space for the copied structures. */ bytes += struct_copy_size; cif->flags = flags; cif->bytes = bytes; return FFI_OK; } extern void ffi_call_SYSV(extended_cif *, unsigned, unsigned, unsigned *, void (*fn)(void)); extern void FFI_HIDDEN ffi_call_LINUX64(extended_cif *, unsigned long, unsigned long, unsigned long *, void (*fn)(void)); void ffi_call(ffi_cif *cif, void (*fn)(void), void *rvalue, void **avalue) { extended_cif ecif; ecif.cif = cif; ecif.avalue = avalue; /* If the return value is a struct and we don't have a return */ /* value address then we need to make one */ if ((rvalue == NULL) && (cif->rtype->type == FFI_TYPE_STRUCT)) { ecif.rvalue = alloca(cif->rtype->size); } else ecif.rvalue = rvalue; switch (cif->abi) { #ifndef POWERPC64 case FFI_SYSV: case FFI_GCC_SYSV: case FFI_LINUX: case FFI_LINUX_SOFT_FLOAT: ffi_call_SYSV (&ecif, -cif->bytes, cif->flags, ecif.rvalue, fn); break; #else case FFI_LINUX64: ffi_call_LINUX64 (&ecif, -(long) cif->bytes, cif->flags, ecif.rvalue, fn); break; #endif default: FFI_ASSERT (0); break; } } #ifndef POWERPC64 #define MIN_CACHE_LINE_SIZE 8 static void flush_icache (char *wraddr, char *xaddr, int size) { int i; for (i = 0; i < size; i += MIN_CACHE_LINE_SIZE) __asm__ volatile ("icbi 0,%0;" "dcbf 0,%1;" : : "r" (xaddr + i), "r" (wraddr + i) : "memory"); __asm__ volatile ("icbi 0,%0;" "dcbf 0,%1;" "sync;" "isync;" : : "r"(xaddr + size - 1), "r"(wraddr + size - 1) : "memory"); } #endif ffi_status ffi_prep_closure_loc (ffi_closure *closure, ffi_cif *cif, void (*fun) (ffi_cif *, void *, void **, void *), void *user_data, void *codeloc) { #ifdef POWERPC64 void **tramp = (void **) &closure->tramp[0]; FFI_ASSERT (cif->abi == FFI_LINUX64); /* Copy function address and TOC from ffi_closure_LINUX64. */ memcpy (tramp, (char *) ffi_closure_LINUX64, 16); tramp[2] = codeloc; #else unsigned int *tramp; FFI_ASSERT (cif->abi == FFI_GCC_SYSV || cif->abi == FFI_SYSV); tramp = (unsigned int *) &closure->tramp[0]; tramp[0] = 0x7c0802a6; /* mflr r0 */ tramp[1] = 0x4800000d; /* bl 10 */ tramp[4] = 0x7d6802a6; /* mflr r11 */ tramp[5] = 0x7c0803a6; /* mtlr r0 */ tramp[6] = 0x800b0000; /* lwz r0,0(r11) */ tramp[7] = 0x816b0004; /* lwz r11,4(r11) */ tramp[8] = 0x7c0903a6; /* mtctr r0 */ tramp[9] = 0x4e800420; /* bctr */ *(void **) &tramp[2] = (void *) ffi_closure_SYSV; /* function */ *(void **) &tramp[3] = codeloc; /* context */ /* Flush the icache. */ flush_icache ((char *)tramp, (char *)codeloc, FFI_TRAMPOLINE_SIZE); #endif closure->cif = cif; closure->fun = fun; closure->user_data = user_data; return FFI_OK; } typedef union { float f; double d; } ffi_dblfl; int ffi_closure_helper_SYSV (ffi_closure *, void *, unsigned long *, ffi_dblfl *, unsigned long *); /* Basically the trampoline invokes ffi_closure_SYSV, and on * entry, r11 holds the address of the closure. * After storing the registers that could possibly contain * parameters to be passed into the stack frame and setting * up space for a return value, ffi_closure_SYSV invokes the * following helper function to do most of the work */ int ffi_closure_helper_SYSV (ffi_closure *closure, void *rvalue, unsigned long *pgr, ffi_dblfl *pfr, unsigned long *pst) { /* rvalue is the pointer to space for return value in closure assembly */ /* pgr is the pointer to where r3-r10 are stored in ffi_closure_SYSV */ /* pfr is the pointer to where f1-f8 are stored in ffi_closure_SYSV */ /* pst is the pointer to outgoing parameter stack in original caller */ void ** avalue; ffi_type ** arg_types; long i, avn; long nf; /* number of floating registers already used */ long ng; /* number of general registers already used */ ffi_cif * cif; double temp; unsigned size; cif = closure->cif; avalue = alloca (cif->nargs * sizeof (void *)); size = cif->rtype->size; nf = 0; ng = 0; /* Copy the caller's structure return value address so that the closure returns the data directly to the caller. For FFI_SYSV the result is passed in r3/r4 if the struct size is less or equal 8 bytes. */ if ((cif->rtype->type == FFI_TYPE_STRUCT && !((cif->abi == FFI_SYSV) && (size <= 8))) #if FFI_TYPE_LONGDOUBLE != FFI_TYPE_DOUBLE || (cif->rtype->type == FFI_TYPE_LONGDOUBLE && cif->abi != FFI_LINUX && cif->abi != FFI_LINUX_SOFT_FLOAT) #endif ) { rvalue = (void *) *pgr; ng++; pgr++; } i = 0; avn = cif->nargs; arg_types = cif->arg_types; /* Grab the addresses of the arguments from the stack frame. */ while (i < avn) { switch (arg_types[i]->type) { case FFI_TYPE_SINT8: case FFI_TYPE_UINT8: /* there are 8 gpr registers used to pass values */ if (ng < 8) { avalue[i] = (char *) pgr + 3; ng++; pgr++; } else { avalue[i] = (char *) pst + 3; pst++; } break; case FFI_TYPE_SINT16: case FFI_TYPE_UINT16: /* there are 8 gpr registers used to pass values */ if (ng < 8) { avalue[i] = (char *) pgr + 2; ng++; pgr++; } else { avalue[i] = (char *) pst + 2; pst++; } break; case FFI_TYPE_SINT32: case FFI_TYPE_UINT32: case FFI_TYPE_POINTER: soft_float_closure: /* there are 8 gpr registers used to pass values */ if (ng < 8) { avalue[i] = pgr; ng++; pgr++; } else { avalue[i] = pst; pst++; } break; case FFI_TYPE_STRUCT: #if FFI_TYPE_LONGDOUBLE != FFI_TYPE_DOUBLE do_struct: #endif /* Structs are passed by reference. The address will appear in a gpr if it is one of the first 8 arguments. */ if (ng < 8) { avalue[i] = (void *) *pgr; ng++; pgr++; } else { avalue[i] = (void *) *pst; pst++; } break; case FFI_TYPE_SINT64: case FFI_TYPE_UINT64: soft_double_closure: /* passing long long ints are complex, they must * be passed in suitable register pairs such as * (r3,r4) or (r5,r6) or (r6,r7), or (r7,r8) or (r9,r10) * and if the entire pair aren't available then the outgoing * parameter stack is used for both but an alignment of 8 * must will be kept. So we must either look in pgr * or pst to find the correct address for this type * of parameter. */ if (ng < 7) { if (ng & 0x01) { /* skip r4, r6, r8 as starting points */ ng++; pgr++; } avalue[i] = pgr; ng += 2; pgr += 2; } else { if (((long) pst) & 4) pst++; avalue[i] = pst; pst += 2; ng = 8; } break; case FFI_TYPE_FLOAT: /* With FFI_LINUX_SOFT_FLOAT floats are handled like UINT32. */ if (cif->abi == FFI_LINUX_SOFT_FLOAT) goto soft_float_closure; /* unfortunately float values are stored as doubles * in the ffi_closure_SYSV code (since we don't check * the type in that routine). */ /* there are 8 64bit floating point registers */ if (nf < 8) { temp = pfr->d; pfr->f = (float) temp; avalue[i] = pfr; nf++; pfr++; } else { /* FIXME? here we are really changing the values * stored in the original calling routines outgoing * parameter stack. This is probably a really * naughty thing to do but... */ avalue[i] = pst; pst += 1; } break; case FFI_TYPE_DOUBLE: /* With FFI_LINUX_SOFT_FLOAT doubles are handled like UINT64. */ if (cif->abi == FFI_LINUX_SOFT_FLOAT) goto soft_double_closure; /* On the outgoing stack all values are aligned to 8 */ /* there are 8 64bit floating point registers */ if (nf < 8) { avalue[i] = pfr; nf++; pfr++; } else { if (((long) pst) & 4) pst++; avalue[i] = pst; pst += 2; } break; #if FFI_TYPE_LONGDOUBLE != FFI_TYPE_DOUBLE case FFI_TYPE_LONGDOUBLE: if (cif->abi != FFI_LINUX && cif->abi != FFI_LINUX_SOFT_FLOAT) goto do_struct; if (cif->abi == FFI_LINUX_SOFT_FLOAT) { /* Test if for the whole long double, 4 gprs are available. otherwise the stuff ends up on the stack. */ if (ng < 5) { avalue[i] = pgr; pgr += 4; ng += 4; } else { avalue[i] = pst; pst += 4; ng = 8; } break; } if (nf < 7) { avalue[i] = pfr; pfr += 2; nf += 2; } else { if (((long) pst) & 4) pst++; avalue[i] = pst; pst += 4; nf = 8; } break; #endif default: FFI_ASSERT (0); } i++; } (closure->fun) (cif, rvalue, avalue, closure->user_data); /* Tell ffi_closure_SYSV how to perform return type promotions. Because the FFI_SYSV ABI returns the structures <= 8 bytes in r3/r4 we have to tell ffi_closure_SYSV how to treat them. We combine the base type FFI_SYSV_TYPE_SMALL_STRUCT - 1 with the size of the struct. So a one byte struct gets the return type 16. Return type 1 to 15 are already used and we never have a struct with size zero. That is the reason for the subtraction of 1. See the comment in ffitarget.h about ordering. */ if (cif->abi == FFI_SYSV && cif->rtype->type == FFI_TYPE_STRUCT && size <= 8) return (FFI_SYSV_TYPE_SMALL_STRUCT - 1) + size; #if FFI_TYPE_LONGDOUBLE != FFI_TYPE_DOUBLE else if (cif->rtype->type == FFI_TYPE_LONGDOUBLE && cif->abi != FFI_LINUX && cif->abi != FFI_LINUX_SOFT_FLOAT) return FFI_TYPE_STRUCT; #endif /* With FFI_LINUX_SOFT_FLOAT floats and doubles are handled like UINT32 respectivley UINT64. */ if (cif->abi == FFI_LINUX_SOFT_FLOAT) { switch (cif->rtype->type) { case FFI_TYPE_FLOAT: return FFI_TYPE_UINT32; break; case FFI_TYPE_DOUBLE: return FFI_TYPE_UINT64; break; #if FFI_TYPE_LONGDOUBLE != FFI_TYPE_DOUBLE case FFI_TYPE_LONGDOUBLE: return FFI_TYPE_UINT128; break; #endif default: return cif->rtype->type; } } else { return cif->rtype->type; } } int FFI_HIDDEN ffi_closure_helper_LINUX64 (ffi_closure *, void *, unsigned long *, ffi_dblfl *); int FFI_HIDDEN ffi_closure_helper_LINUX64 (ffi_closure *closure, void *rvalue, unsigned long *pst, ffi_dblfl *pfr) { /* rvalue is the pointer to space for return value in closure assembly */ /* pst is the pointer to parameter save area (r3-r10 are stored into its first 8 slots by ffi_closure_LINUX64) */ /* pfr is the pointer to where f1-f13 are stored in ffi_closure_LINUX64 */ void **avalue; ffi_type **arg_types; long i, avn; ffi_cif *cif; ffi_dblfl *end_pfr = pfr + NUM_FPR_ARG_REGISTERS64; cif = closure->cif; avalue = alloca (cif->nargs * sizeof (void *)); /* Copy the caller's structure return value address so that the closure returns the data directly to the caller. */ if (cif->rtype->type == FFI_TYPE_STRUCT) { rvalue = (void *) *pst; pst++; } i = 0; avn = cif->nargs; arg_types = cif->arg_types; /* Grab the addresses of the arguments from the stack frame. */ while (i < avn) { switch (arg_types[i]->type) { case FFI_TYPE_SINT8: case FFI_TYPE_UINT8: avalue[i] = (char *) pst + 7; pst++; break; case FFI_TYPE_SINT16: case FFI_TYPE_UINT16: avalue[i] = (char *) pst + 6; pst++; break; case FFI_TYPE_SINT32: case FFI_TYPE_UINT32: avalue[i] = (char *) pst + 4; pst++; break; case FFI_TYPE_SINT64: case FFI_TYPE_UINT64: case FFI_TYPE_POINTER: avalue[i] = pst; pst++; break; case FFI_TYPE_STRUCT: /* Structures with size less than eight bytes are passed left-padded. */ if (arg_types[i]->size < 8) avalue[i] = (char *) pst + 8 - arg_types[i]->size; else avalue[i] = pst; pst += (arg_types[i]->size + 7) / 8; break; case FFI_TYPE_FLOAT: /* unfortunately float values are stored as doubles * in the ffi_closure_LINUX64 code (since we don't check * the type in that routine). */ /* there are 13 64bit floating point registers */ if (pfr < end_pfr) { double temp = pfr->d; pfr->f = (float) temp; avalue[i] = pfr; pfr++; } else avalue[i] = pst; pst++; break; case FFI_TYPE_DOUBLE: /* On the outgoing stack all values are aligned to 8 */ /* there are 13 64bit floating point registers */ if (pfr < end_pfr) { avalue[i] = pfr; pfr++; } else avalue[i] = pst; pst++; break; #if FFI_TYPE_LONGDOUBLE != FFI_TYPE_DOUBLE case FFI_TYPE_LONGDOUBLE: if (pfr + 1 < end_pfr) { avalue[i] = pfr; pfr += 2; } else { if (pfr < end_pfr) { /* Passed partly in f13 and partly on the stack. Move it all to the stack. */ *pst = *(unsigned long *) pfr; pfr++; } avalue[i] = pst; } pst += 2; break; #endif default: FFI_ASSERT (0); } i++; } (closure->fun) (cif, rvalue, avalue, closure->user_data); /* Tell ffi_closure_LINUX64 how to perform return type promotions. */ return cif->rtype->type; } smalltalk-3.2.5/libffi/src/debug.c0000644000175000017500000000427112130343734013706 00000000000000/* ----------------------------------------------------------------------- debug.c - Copyright (c) 1996 Red Hat, Inc. Permission is hereby granted, free of charge, to any person obtaining a copy of this software and associated documentation files (the ``Software''), to deal in the Software without restriction, including without limitation the rights to use, copy, modify, merge, publish, distribute, sublicense, and/or sell copies of the Software, and to permit persons to whom the Software is furnished to do so, subject to the following conditions: The above copyright notice and this permission notice shall be included in all copies or substantial portions of the Software. THE SOFTWARE IS PROVIDED ``AS IS'', WITHOUT WARRANTY OF ANY KIND, EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. ----------------------------------------------------------------------- */ #include #include #include #include /* General debugging routines */ void ffi_stop_here(void) { /* This function is only useful for debugging purposes. Place a breakpoint on ffi_stop_here to be notified of significant events. */ } /* This function should only be called via the FFI_ASSERT() macro */ void ffi_assert(char *expr, char *file, int line) { fprintf(stderr, "ASSERTION FAILURE: %s at %s:%d\n", expr, file, line); ffi_stop_here(); abort(); } /* Perform a sanity check on an ffi_type structure */ void ffi_type_test(ffi_type *a, char *file, int line) { FFI_ASSERT_AT(a != NULL, file, line); FFI_ASSERT_AT(a->type <= FFI_TYPE_LAST, file, line); FFI_ASSERT_AT(a->type == FFI_TYPE_VOID || a->size > 0, file, line); FFI_ASSERT_AT(a->type == FFI_TYPE_VOID || a->alignment > 0, file, line); FFI_ASSERT_AT(a->type != FFI_TYPE_STRUCT || a->elements != NULL, file, line); } smalltalk-3.2.5/libffi/src/arm/0000755000175000017500000000000012130456004013302 500000000000000smalltalk-3.2.5/libffi/src/arm/ffitarget.h0000644000175000017500000000340212130343734015352 00000000000000/* -----------------------------------------------------------------*-C-*- ffitarget.h - Copyright (c) 1996-2003 Red Hat, Inc. Target configuration macros for ARM. Permission is hereby granted, free of charge, to any person obtaining a copy of this software and associated documentation files (the ``Software''), to deal in the Software without restriction, including without limitation the rights to use, copy, modify, merge, publish, distribute, sublicense, and/or sell copies of the Software, and to permit persons to whom the Software is furnished to do so, subject to the following conditions: The above copyright notice and this permission notice shall be included in all copies or substantial portions of the Software. THE SOFTWARE IS PROVIDED ``AS IS'', WITHOUT WARRANTY OF ANY KIND, EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. ----------------------------------------------------------------------- */ #ifndef LIBFFI_TARGET_H #define LIBFFI_TARGET_H #ifndef LIBFFI_ASM typedef unsigned long ffi_arg; typedef signed long ffi_sarg; typedef enum ffi_abi { FFI_FIRST_ABI = 0, FFI_SYSV, FFI_DEFAULT_ABI = FFI_SYSV, FFI_LAST_ABI = FFI_DEFAULT_ABI + 1 } ffi_abi; #endif /* ---- Definitions for closures ----------------------------------------- */ #define FFI_CLOSURES 1 #define FFI_TRAMPOLINE_SIZE 20 #define FFI_NATIVE_RAW_API 0 #endif smalltalk-3.2.5/libffi/src/arm/sysv.S0000644000175000017500000001545512130343734014371 00000000000000/* ----------------------------------------------------------------------- sysv.S - Copyright (c) 1998, 2008 Red Hat, Inc. ARM Foreign Function Interface Permission is hereby granted, free of charge, to any person obtaining a copy of this software and associated documentation files (the ``Software''), to deal in the Software without restriction, including without limitation the rights to use, copy, modify, merge, publish, distribute, sublicense, and/or sell copies of the Software, and to permit persons to whom the Software is furnished to do so, subject to the following conditions: The above copyright notice and this permission notice shall be included in all copies or substantial portions of the Software. THE SOFTWARE IS PROVIDED ``AS IS'', WITHOUT WARRANTY OF ANY KIND, EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. ----------------------------------------------------------------------- */ #define LIBFFI_ASM #include #include #ifdef HAVE_MACHINE_ASM_H #include #else #ifdef __USER_LABEL_PREFIX__ #define CONCAT1(a, b) CONCAT2(a, b) #define CONCAT2(a, b) a ## b /* Use the right prefix for global labels. */ #define CNAME(x) CONCAT1 (__USER_LABEL_PREFIX__, x) #else #define CNAME(x) x #endif #define ENTRY(x) .globl CNAME(x); .type CNAME(x),%function; CNAME(x): #endif #ifdef __ELF__ #define LSYM(x) .x #else #define LSYM(x) x #endif /* We need a better way of testing for this, but for now, this is all we can do. */ @ This selects the minimum architecture level required. #define __ARM_ARCH__ 3 #if defined(__ARM_ARCH_4__) || defined(__ARM_ARCH_4T__) # undef __ARM_ARCH__ # define __ARM_ARCH__ 4 #endif #if defined(__ARM_ARCH_5__) || defined(__ARM_ARCH_5T__) \ || defined(__ARM_ARCH_5E__) || defined(__ARM_ARCH_5TE__) \ || defined(__ARM_ARCH_5TEJ__) # undef __ARM_ARCH__ # define __ARM_ARCH__ 5 #endif #if defined(__ARM_ARCH_6__) || defined(__ARM_ARCH_6J__) \ || defined(__ARM_ARCH_6K__) || defined(__ARM_ARCH_6Z__) \ || defined(__ARM_ARCH_6ZK__) || defined(__ARM_ARCH_6T2__) \ || defined(__ARM_ARCH_6M__) # undef __ARM_ARCH__ # define __ARM_ARCH__ 6 #endif #if defined(__ARM_ARCH_7__) || defined(__ARM_ARCH_7A__) \ || defined(__ARM_ARCH_7R__) || defined(__ARM_ARCH_7M__) \ || defined(__ARM_ARCH_7EM__) # undef __ARM_ARCH__ # define __ARM_ARCH__ 7 #endif #if __ARM_ARCH__ >= 5 # define call_reg(x) blx x #elif defined (__ARM_ARCH_4T__) # define call_reg(x) mov lr, pc ; bx x # if defined(__thumb__) || defined(__THUMB_INTERWORK__) # define __INTERWORKING__ # endif #else # define call_reg(x) mov lr, pc ; mov pc, x #endif /* Conditionally compile unwinder directives. */ #ifdef __ARM_EABI__ #define UNWIND #else #define UNWIND @ #endif #if defined(__thumb__) && !defined(__THUMB_INTERWORK__) .macro ARM_FUNC_START name .text .align 0 .thumb .thumb_func ENTRY(\name) bx pc nop .arm UNWIND .fnstart /* A hook to tell gdb that we've switched to ARM mode. Also used to call directly from other local arm routines. */ _L__\name: .endm #else .macro ARM_FUNC_START name .text .align 0 .arm ENTRY(\name) UNWIND .fnstart .endm #endif .macro RETLDM regs=, cond=, dirn=ia #if defined (__INTERWORKING__) .ifc "\regs","" ldr\cond lr, [sp], #4 .else ldm\cond\dirn sp!, {\regs, lr} .endif bx\cond lr #else .ifc "\regs","" ldr\cond pc, [sp], #4 .else ldm\cond\dirn sp!, {\regs, pc} .endif #endif .endm @ r0: ffi_prep_args @ r1: &ecif @ r2: cif->bytes @ r3: fig->flags @ sp+0: ecif.rvalue @ sp+4: fn @ This assumes we are using gas. ARM_FUNC_START ffi_call_SYSV @ Save registers stmfd sp!, {r0-r3, fp, lr} UNWIND .save {r0-r3, fp, lr} mov fp, sp UNWIND .setfp fp, sp @ Make room for all of the new args. sub sp, fp, r2 @ Place all of the ffi_prep_args in position mov ip, r0 mov r0, sp @ r1 already set @ Call ffi_prep_args(stack, &ecif) call_reg(ip) @ move first 4 parameters in registers ldmia sp, {r0-r3} @ and adjust stack ldr ip, [fp, #8] cmp ip, #16 movhs ip, #16 add sp, sp, ip @ call (fn) (...) ldr ip, [fp, #28] call_reg(ip) @ Remove the space we pushed for the args mov sp, fp @ Load r2 with the pointer to storage for the return value ldr r2, [sp, #24] @ Load r3 with the return type code ldr r3, [sp, #12] @ If the return value pointer is NULL, assume no return value. cmp r2, #0 beq LSYM(Lepilogue) @ return INT cmp r3, #FFI_TYPE_INT #if defined(__SOFTFP__) || defined(__ARM_EABI__) cmpne r3, #FFI_TYPE_FLOAT #endif streq r0, [r2] beq LSYM(Lepilogue) @ return INT64 cmp r3, #FFI_TYPE_SINT64 #if defined(__SOFTFP__) || defined(__ARM_EABI__) cmpne r3, #FFI_TYPE_DOUBLE #endif stmeqia r2, {r0, r1} #if !defined(__SOFTFP__) && !defined(__ARM_EABI__) beq LSYM(Lepilogue) @ return FLOAT cmp r3, #FFI_TYPE_FLOAT stfeqs f0, [r2] beq LSYM(Lepilogue) @ return DOUBLE or LONGDOUBLE cmp r3, #FFI_TYPE_DOUBLE stfeqd f0, [r2] #endif LSYM(Lepilogue): RETLDM "r0-r3,fp" .ffi_call_SYSV_end: UNWIND .fnend .size CNAME(ffi_call_SYSV),.ffi_call_SYSV_end-CNAME(ffi_call_SYSV) /* unsigned int FFI_HIDDEN ffi_closure_SYSV_inner (closure, respp, args) ffi_closure *closure; void **respp; void *args; */ ARM_FUNC_START ffi_closure_SYSV UNWIND .pad #16 add ip, sp, #16 stmfd sp!, {ip, lr} UNWIND .save {r0, lr} add r2, sp, #8 .pad #16 sub sp, sp, #16 str sp, [sp, #8] add r1, sp, #8 bl ffi_closure_SYSV_inner cmp r0, #FFI_TYPE_INT beq .Lretint cmp r0, #FFI_TYPE_FLOAT #if defined(__SOFTFP__) || defined(__ARM_EABI__) beq .Lretint #else beq .Lretfloat #endif cmp r0, #FFI_TYPE_DOUBLE #if defined(__SOFTFP__) || defined(__ARM_EABI__) beq .Lretlonglong #else beq .Lretdouble #endif cmp r0, #FFI_TYPE_LONGDOUBLE #if defined(__SOFTFP__) || defined(__ARM_EABI__) beq .Lretlonglong #else beq .Lretlongdouble #endif cmp r0, #FFI_TYPE_SINT64 beq .Lretlonglong .Lclosure_epilogue: add sp, sp, #16 ldmfd sp, {sp, pc} .Lretint: ldr r0, [sp] b .Lclosure_epilogue .Lretlonglong: ldr r0, [sp] ldr r1, [sp, #4] b .Lclosure_epilogue #if !defined(__SOFTFP__) && !defined(__ARM_EABI__) .Lretfloat: ldfs f0, [sp] b .Lclosure_epilogue .Lretdouble: ldfd f0, [sp] b .Lclosure_epilogue .Lretlongdouble: ldfd f0, [sp] b .Lclosure_epilogue #endif .ffi_closure_SYSV_end: UNWIND .fnend .size CNAME(ffi_closure_SYSV),.ffi_closure_SYSV_end-CNAME(ffi_closure_SYSV) #if defined __ELF__ && defined __linux__ .section .note.GNU-stack,"",%progbits #endif smalltalk-3.2.5/libffi/src/arm/ffi.c0000644000175000017500000001744612130343734014153 00000000000000/* ----------------------------------------------------------------------- ffi.c - Copyright (c) 1998, 2008 Red Hat, Inc. ARM Foreign Function Interface Permission is hereby granted, free of charge, to any person obtaining a copy of this software and associated documentation files (the ``Software''), to deal in the Software without restriction, including without limitation the rights to use, copy, modify, merge, publish, distribute, sublicense, and/or sell copies of the Software, and to permit persons to whom the Software is furnished to do so, subject to the following conditions: The above copyright notice and this permission notice shall be included in all copies or substantial portions of the Software. THE SOFTWARE IS PROVIDED ``AS IS'', WITHOUT WARRANTY OF ANY KIND, EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. ----------------------------------------------------------------------- */ #include #include #include /* ffi_prep_args is called by the assembly routine once stack space has been allocated for the function's arguments */ void ffi_prep_args(char *stack, extended_cif *ecif) { register unsigned int i; register void **p_argv; register char *argp; register ffi_type **p_arg; argp = stack; if ( ecif->cif->flags == FFI_TYPE_STRUCT ) { *(void **) argp = ecif->rvalue; argp += 4; } p_argv = ecif->avalue; for (i = ecif->cif->nargs, p_arg = ecif->cif->arg_types; (i != 0); i--, p_arg++) { size_t z; /* Align if necessary */ if (((*p_arg)->alignment - 1) & (unsigned) argp) { argp = (char *) ALIGN(argp, (*p_arg)->alignment); } if ((*p_arg)->type == FFI_TYPE_STRUCT) argp = (char *) ALIGN(argp, 4); z = (*p_arg)->size; if (z < sizeof(int)) { z = sizeof(int); switch ((*p_arg)->type) { case FFI_TYPE_SINT8: *(signed int *) argp = (signed int)*(SINT8 *)(* p_argv); break; case FFI_TYPE_UINT8: *(unsigned int *) argp = (unsigned int)*(UINT8 *)(* p_argv); break; case FFI_TYPE_SINT16: *(signed int *) argp = (signed int)*(SINT16 *)(* p_argv); break; case FFI_TYPE_UINT16: *(unsigned int *) argp = (unsigned int)*(UINT16 *)(* p_argv); break; case FFI_TYPE_STRUCT: memcpy(argp, *p_argv, (*p_arg)->size); break; default: FFI_ASSERT(0); } } else if (z == sizeof(int)) { *(unsigned int *) argp = (unsigned int)*(UINT32 *)(* p_argv); } else { memcpy(argp, *p_argv, z); } p_argv++; argp += z; } return; } /* Perform machine dependent cif processing */ ffi_status ffi_prep_cif_machdep(ffi_cif *cif) { /* Round the stack up to a multiple of 8 bytes. This isn't needed everywhere, but it is on some platforms, and it doesn't harm anything when it isn't needed. */ cif->bytes = (cif->bytes + 7) & ~7; /* Set the return type flag */ switch (cif->rtype->type) { case FFI_TYPE_VOID: case FFI_TYPE_FLOAT: case FFI_TYPE_DOUBLE: cif->flags = (unsigned) cif->rtype->type; break; case FFI_TYPE_SINT64: case FFI_TYPE_UINT64: cif->flags = (unsigned) FFI_TYPE_SINT64; break; case FFI_TYPE_STRUCT: if (cif->rtype->size <= 4) /* A Composite Type not larger than 4 bytes is returned in r0. */ cif->flags = (unsigned)FFI_TYPE_INT; else /* A Composite Type larger than 4 bytes, or whose size cannot be determined statically ... is stored in memory at an address passed [in r0]. */ cif->flags = (unsigned)FFI_TYPE_STRUCT; break; default: cif->flags = FFI_TYPE_INT; break; } return FFI_OK; } extern void ffi_call_SYSV(void (*)(char *, extended_cif *), extended_cif *, unsigned, unsigned, unsigned *, void (*fn)(void)); void ffi_call(ffi_cif *cif, void (*fn)(void), void *rvalue, void **avalue) { extended_cif ecif; int small_struct = (cif->flags == FFI_TYPE_INT && cif->rtype->type == FFI_TYPE_STRUCT); ecif.cif = cif; ecif.avalue = avalue; unsigned int temp; /* If the return value is a struct and we don't have a return */ /* value address then we need to make one */ if ((rvalue == NULL) && (cif->flags == FFI_TYPE_STRUCT)) { ecif.rvalue = alloca(cif->rtype->size); } else if (small_struct) ecif.rvalue = &temp; else ecif.rvalue = rvalue; switch (cif->abi) { case FFI_SYSV: ffi_call_SYSV(ffi_prep_args, &ecif, cif->bytes, cif->flags, ecif.rvalue, fn); break; default: FFI_ASSERT(0); break; } if (small_struct) memcpy (rvalue, &temp, cif->rtype->size); } /** private members **/ static void ffi_prep_incoming_args_SYSV (char *stack, void **ret, void** args, ffi_cif* cif); void ffi_closure_SYSV (ffi_closure *); /* This function is jumped to by the trampoline */ unsigned int ffi_closure_SYSV_inner (closure, respp, args) ffi_closure *closure; void **respp; void *args; { // our various things... ffi_cif *cif; void **arg_area; cif = closure->cif; arg_area = (void**) alloca (cif->nargs * sizeof (void*)); /* this call will initialize ARG_AREA, such that each * element in that array points to the corresponding * value on the stack; and if the function returns * a structure, it will re-set RESP to point to the * structure return address. */ ffi_prep_incoming_args_SYSV(args, respp, arg_area, cif); (closure->fun) (cif, *respp, arg_area, closure->user_data); return cif->flags; } /*@-exportheader@*/ static void ffi_prep_incoming_args_SYSV(char *stack, void **rvalue, void **avalue, ffi_cif *cif) /*@=exportheader@*/ { register unsigned int i; register void **p_argv; register char *argp; register ffi_type **p_arg; argp = stack; if ( cif->flags == FFI_TYPE_STRUCT ) { *rvalue = *(void **) argp; argp += 4; } p_argv = avalue; for (i = cif->nargs, p_arg = cif->arg_types; (i != 0); i--, p_arg++) { size_t z; size_t alignment = (*p_arg)->alignment; if (alignment < 4) alignment = 4; /* Align if necessary */ if ((alignment - 1) & (unsigned) argp) { argp = (char *) ALIGN(argp, alignment); } z = (*p_arg)->size; /* because we're little endian, this is what it turns into. */ *p_argv = (void*) argp; p_argv++; argp += z; } return; } /* How to make a trampoline. */ #define FFI_INIT_TRAMPOLINE(TRAMP,FUN,CTX) \ ({ unsigned char *__tramp = (unsigned char*)(TRAMP); \ unsigned int __fun = (unsigned int)(FUN); \ unsigned int __ctx = (unsigned int)(CTX); \ *(unsigned int*) &__tramp[0] = 0xe92d000f; /* stmfd sp!, {r0-r3} */ \ *(unsigned int*) &__tramp[4] = 0xe59f0000; /* ldr r0, [pc] */ \ *(unsigned int*) &__tramp[8] = 0xe59ff000; /* ldr pc, [pc] */ \ *(unsigned int*) &__tramp[12] = __ctx; \ *(unsigned int*) &__tramp[16] = __fun; \ __clear_cache((&__tramp[0]), (&__tramp[19])); \ }) /* the cif must already be prep'ed */ ffi_status ffi_prep_closure_loc (ffi_closure* closure, ffi_cif* cif, void (*fun)(ffi_cif*,void*,void**,void*), void *user_data, void *codeloc) { FFI_ASSERT (cif->abi == FFI_SYSV); FFI_INIT_TRAMPOLINE (&closure->tramp[0], \ &ffi_closure_SYSV, \ codeloc); closure->cif = cif; closure->user_data = user_data; closure->fun = fun; return FFI_OK; } smalltalk-3.2.5/libffi/src/avr32/0000755000175000017500000000000012130456004013460 500000000000000smalltalk-3.2.5/libffi/src/avr32/ffitarget.h0000644000175000017500000000343712130343734015540 00000000000000/* -----------------------------------------------------------------*-C-*- ffitarget.h - Copyright (c) 2009 Bradley Smith Target configuration macros for AVR32. Permission is hereby granted, free of charge, to any person obtaining a copy of this software and associated documentation files (the ``Software''), to deal in the Software without restriction, including without limitation the rights to use, copy, modify, merge, publish, distribute, sublicense, and/or sell copies of the Software, and to permit persons to whom the Software is furnished to do so, subject to the following conditions: The above copyright notice and this permission notice shall be included in all copies or substantial portions of the Software. THE SOFTWARE IS PROVIDED ``AS IS'', WITHOUT WARRANTY OF ANY KIND, EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. ----------------------------------------------------------------------- */ #ifndef LIBFFI_TARGET_H #define LIBFFI_TARGET_H #ifndef LIBFFI_ASM typedef unsigned long ffi_arg; typedef signed long ffi_sarg; typedef enum ffi_abi { FFI_FIRST_ABI = 0, FFI_SYSV, FFI_DEFAULT_ABI = FFI_SYSV, FFI_LAST_ABI = FFI_DEFAULT_ABI + 1 } ffi_abi; #endif #define FFI_EXTRA_CIF_FIELDS unsigned int rstruct_flag /* Definitions for closures */ #define FFI_CLOSURES 1 #define FFI_TRAMPOLINE_SIZE 36 #define FFI_NATIVE_RAW_API 0 #endif smalltalk-3.2.5/libffi/src/avr32/sysv.S0000644000175000017500000001135012130343734014535 00000000000000/* ----------------------------------------------------------------------- sysv.S - Copyright (c) 2009 Bradley Smith AVR32 Foreign Function Interface Permission is hereby granted, free of charge, to any person obtaining a copy of this software and associated documentation files (the ``Software''), to deal in the Software without restriction, including without limitation the rights to use, copy, modify, merge, publish, distribute, sublicense, and/or sell copies of the Software, and to permit persons to whom the Software is furnished to do so, subject to the following conditions: The above copyright notice and this permission notice shall be included in all copies or substantial portions of the Software. THE SOFTWARE IS PROVIDED ``AS IS'', WITHOUT WARRANTY OF ANY KIND, EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. --------------------------------------------------------------------- */ #define LIBFFI_ASM #include #include /* r12: ffi_prep_args * r11: &ecif * r10: size * r9: cif->flags * r8: ecif.rvalue * sp+0: cif->rstruct_flag * sp+4: fn */ .text .align 1 .globl ffi_call_SYSV .type ffi_call_SYSV, @function ffi_call_SYSV: stm --sp, r0,r1,lr stm --sp, r8-r12 mov r0, sp /* Make room for all of the new args. */ sub sp, r10 /* Pad to make way for potential skipped registers */ sub sp, 20 /* Call ffi_prep_args(stack, &ecif). */ /* r11 already set */ mov r1, r12 mov r12, sp icall r1 /* Save new argument size */ mov r1, r12 /* Move first 5 parameters in registers. */ ldm sp++, r8-r12 /* call (fn) (...). */ ld.w r1, r0[36] icall r1 /* Remove the space we pushed for the args. */ mov sp, r0 /* Load r1 with the rstruct flag. */ ld.w r1, sp[32] /* Load r9 with the return type code. */ ld.w r9, sp[12] /* Load r8 with the return value pointer. */ ld.w r8, sp[16] /* If the return value pointer is NULL, assume no return value. */ cp.w r8, 0 breq .Lend /* Check if return type is actually a struct */ cp.w r1, 0 breq 1f /* Return 8bit */ cp.w r9, FFI_TYPE_UINT8 breq .Lstore8 /* Return 16bit */ cp.w r9, FFI_TYPE_UINT16 breq .Lstore16 1: /* Return 32bit */ cp.w r9, FFI_TYPE_UINT32 breq .Lstore32 cp.w r9, FFI_TYPE_UINT16 breq .Lstore32 cp.w r9, FFI_TYPE_UINT8 breq .Lstore32 /* Return 64bit */ cp.w r9, FFI_TYPE_UINT64 breq .Lstore64 /* Didn't match anything */ bral .Lend .Lstore64: st.w r8[0], r11 st.w r8[4], r10 bral .Lend .Lstore32: st.w r8[0], r12 bral .Lend .Lstore16: st.h r8[0], r12 bral .Lend .Lstore8: st.b r8[0], r12 bral .Lend .Lend: sub sp, -20 ldm sp++, r0,r1,pc .size ffi_call_SYSV, . - ffi_call_SYSV /* r12: __ctx * r11: __rstruct_flag * r10: __inner */ .align 1 .globl ffi_closure_SYSV .type ffi_closure_SYSV, @function ffi_closure_SYSV: stm --sp, r0,lr mov r0, r11 mov r8, r10 sub r10, sp, -8 sub sp, 12 st.w sp[8], sp sub r11, sp, -8 icall r8 /* Check if return type is actually a struct */ cp.w r0, 0 breq 1f /* Return 8bit */ cp.w r12, FFI_TYPE_UINT8 breq .Lget8 /* Return 16bit */ cp.w r12, FFI_TYPE_UINT16 breq .Lget16 1: /* Return 32bit */ cp.w r12, FFI_TYPE_UINT32 breq .Lget32 cp.w r12, FFI_TYPE_UINT16 breq .Lget32 cp.w r12, FFI_TYPE_UINT8 breq .Lget32 /* Return 64bit */ cp.w r12, FFI_TYPE_UINT64 breq .Lget64 /* Didn't match anything */ bral .Lclend .Lget64: ld.w r11, sp[0] ld.w r10, sp[4] bral .Lclend .Lget32: ld.w r12, sp[0] bral .Lclend .Lget16: ld.uh r12, sp[0] bral .Lclend .Lget8: ld.ub r12, sp[0] bral .Lclend .Lclend: sub sp, -12 ldm sp++, r0,lr sub sp, -20 mov pc, lr .size ffi_closure_SYSV, . - ffi_closure_SYSV #if defined __ELF__ && defined __linux__ .section .note.GNU-stack,"",@progbits #endif smalltalk-3.2.5/libffi/src/avr32/ffi.c0000644000175000017500000003005212130343734014315 00000000000000/* ----------------------------------------------------------------------- ffi.c - Copyright (c) 2009 Bradley Smith AVR32 Foreign Function Interface Permission is hereby granted, free of charge, to any person obtaining a copy of this software and associated documentation files (the ``Software''), to deal in the Software without restriction, including without limitation the rights to use, copy, modify, merge, publish, distribute, sublicense, and/or sell copies of the Software, and to permit persons to whom the Software is furnished to do so, subject to the following conditions: The above copyright notice and this permission notice shall be included in all copies or substantial portions of the Software. THE SOFTWARE IS PROVIDED ``AS IS'', WITHOUT WARRANTY OF ANY KIND, EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. ----------------------------------------------------------------------- */ #include #include #include #include #include #include /* #define DEBUG */ extern void ffi_call_SYSV(void (*)(char *, extended_cif *), extended_cif *, unsigned int, unsigned int, unsigned int*, unsigned int, void (*fn)(void)); extern void ffi_closure_SYSV (ffi_closure *); unsigned int pass_struct_on_stack(ffi_type *type) { if(type->type != FFI_TYPE_STRUCT) return 0; if(type->alignment < type->size && !(type->size == 4 || type->size == 8) && !(type->size == 8 && type->alignment >= 4)) return 1; if(type->size == 3 || type->size == 5 || type->size == 6 || type->size == 7) return 1; return 0; } /* ffi_prep_args is called by the assembly routine once stack space * has been allocated for the function's arguments * * This is annoyingly complex since we need to keep track of used * registers. */ void ffi_prep_args(char *stack, extended_cif *ecif) { unsigned int i; void **p_argv; ffi_type **p_arg; char *reg_base = stack; char *stack_base = stack + 20; unsigned int stack_offset = 0; unsigned int reg_mask = 0; p_argv = ecif->avalue; /* If cif->flags is struct then we know it's not passed in registers */ if(ecif->cif->flags == FFI_TYPE_STRUCT) { *(void**)reg_base = ecif->rvalue; reg_mask |= 1; } for(i = 0, p_arg = ecif->cif->arg_types; i < ecif->cif->nargs; i++, p_arg++) { size_t z = (*p_arg)->size; int alignment = (*p_arg)->alignment; int type = (*p_arg)->type; char *addr = 0; if(z % 4 != 0) z += (4 - z % 4); if(reg_mask != 0x1f) { if(pass_struct_on_stack(*p_arg)) { addr = stack_base + stack_offset; stack_offset += z; } else if(z == sizeof(int)) { char index = 0; while((reg_mask >> index) & 1) index++; addr = reg_base + (index * 4); reg_mask |= (1 << index); } else if(z == 2 * sizeof(int)) { if(!((reg_mask >> 1) & 1)) { addr = reg_base + 4; reg_mask |= (3 << 1); } else if(!((reg_mask >> 3) & 1)) { addr = reg_base + 12; reg_mask |= (3 << 3); } } } if(!addr) { addr = stack_base + stack_offset; stack_offset += z; } if(type == FFI_TYPE_STRUCT && (*p_arg)->elements[1] == NULL) type = (*p_arg)->elements[0]->type; switch(type) { case FFI_TYPE_UINT8: *(unsigned int *)addr = (unsigned int)*(UINT8 *)(*p_argv); break; case FFI_TYPE_SINT8: *(signed int *)addr = (signed int)*(SINT8 *)(*p_argv); break; case FFI_TYPE_UINT16: *(unsigned int *)addr = (unsigned int)*(UINT16 *)(*p_argv); break; case FFI_TYPE_SINT16: *(signed int *)addr = (signed int)*(SINT16 *)(*p_argv); break; default: memcpy(addr, *p_argv, z); } p_argv++; } #ifdef DEBUG /* Debugging */ for(i = 0; i < 5; i++) { if((reg_mask & (1 << i)) == 0) printf("r%d: (unused)\n", 12 - i); else printf("r%d: 0x%08x\n", 12 - i, ((unsigned int*)reg_base)[i]); } for(i = 0; i < stack_offset / 4; i++) { printf("sp+%d: 0x%08x\n", i*4, ((unsigned int*)stack_base)[i]); } #endif } /* Perform machine dependent cif processing */ ffi_status ffi_prep_cif_machdep(ffi_cif *cif) { /* Round the stack up to a multiple of 8 bytes. This isn't needed * everywhere, but it is on some platforms, and it doesn't harm * anything when it isn't needed. */ cif->bytes = (cif->bytes + 7) & ~7; /* Flag to indicate that he return value is in fact a struct */ cif->rstruct_flag = 0; /* Set the return type flag */ switch(cif->rtype->type) { case FFI_TYPE_SINT8: case FFI_TYPE_UINT8: cif->flags = (unsigned)FFI_TYPE_UINT8; break; case FFI_TYPE_SINT16: case FFI_TYPE_UINT16: cif->flags = (unsigned)FFI_TYPE_UINT16; break; case FFI_TYPE_FLOAT: case FFI_TYPE_SINT32: case FFI_TYPE_UINT32: case FFI_TYPE_POINTER: cif->flags = (unsigned)FFI_TYPE_UINT32; break; case FFI_TYPE_DOUBLE: case FFI_TYPE_SINT64: case FFI_TYPE_UINT64: cif->flags = (unsigned)FFI_TYPE_UINT64; break; case FFI_TYPE_STRUCT: cif->rstruct_flag = 1; if(!pass_struct_on_stack(cif->rtype)) { if(cif->rtype->size <= 1) cif->flags = (unsigned)FFI_TYPE_UINT8; else if(cif->rtype->size <= 2) cif->flags = (unsigned)FFI_TYPE_UINT16; else if(cif->rtype->size <= 4) cif->flags = (unsigned)FFI_TYPE_UINT32; else if(cif->rtype->size <= 8) cif->flags = (unsigned)FFI_TYPE_UINT64; else cif->flags = (unsigned)cif->rtype->type; } else cif->flags = (unsigned)cif->rtype->type; break; default: cif->flags = (unsigned)cif->rtype->type; break; } return FFI_OK; } void ffi_call(ffi_cif *cif, void (*fn)(void), void *rvalue, void **avalue) { extended_cif ecif; unsigned int size = 0, i = 0; ffi_type **p_arg; ecif.cif = cif; ecif.avalue = avalue; for(i = 0, p_arg = cif->arg_types; i < cif->nargs; i++, p_arg++) size += (*p_arg)->size + (4 - (*p_arg)->size % 4); /* If the return value is a struct and we don't have a return value * address then we need to make one */ /* If cif->flags is struct then it's not suitable for registers */ if((rvalue == NULL) && (cif->flags == FFI_TYPE_STRUCT)) ecif.rvalue = alloca(cif->rtype->size); else ecif.rvalue = rvalue; switch(cif->abi) { case FFI_SYSV: ffi_call_SYSV(ffi_prep_args, &ecif, size, cif->flags, ecif.rvalue, cif->rstruct_flag, fn); break; default: FFI_ASSERT(0); break; } } static void ffi_prep_incoming_args_SYSV(char *stack, void **rvalue, void **avalue, ffi_cif *cif) { register unsigned int i, reg_mask = 0; register void **p_argv; register ffi_type **p_arg; register char *reg_base = stack; register char *stack_base = stack + 20; register unsigned int stack_offset = 0; #ifdef DEBUG /* Debugging */ for(i = 0; i < cif->nargs + 7; i++) { printf("sp+%d: 0x%08x\n", i*4, ((unsigned int*)stack)[i]); } #endif /* If cif->flags is struct then we know it's not passed in registers */ if(cif->flags == FFI_TYPE_STRUCT) { *rvalue = *(void **)reg_base; reg_mask |= 1; } p_argv = avalue; for(i = 0, p_arg = cif->arg_types; i < cif->nargs; i++, p_arg++) { size_t z = (*p_arg)->size; int alignment = (*p_arg)->alignment; *p_argv = 0; if(z % 4 != 0) z += (4 - z % 4); if(reg_mask != 0x1f) { if(pass_struct_on_stack(*p_arg)) { *p_argv = (void*)stack_base + stack_offset; stack_offset += z; } else if(z <= sizeof(int)) { char index = 0; while((reg_mask >> index) & 1) index++; *p_argv = (void*)reg_base + (index * 4); reg_mask |= (1 << index); } else if(z == 2 * sizeof(int)) { if(!((reg_mask >> 1) & 1)) { *p_argv = (void*)reg_base + 4; reg_mask |= (3 << 1); } else if(!((reg_mask >> 3) & 1)) { *p_argv = (void*)reg_base + 12; reg_mask |= (3 << 3); } } } if(!*p_argv) { *p_argv = (void*)stack_base + stack_offset; stack_offset += z; } if((*p_arg)->type != FFI_TYPE_STRUCT || (*p_arg)->elements[1] == NULL) { if(alignment == 1) **(unsigned int**)p_argv <<= 24; else if(alignment == 2) **(unsigned int**)p_argv <<= 16; } p_argv++; } #ifdef DEBUG /* Debugging */ for(i = 0; i < cif->nargs; i++) { printf("sp+%d: 0x%08x\n", i*4, *(((unsigned int**)avalue)[i])); } #endif } /* This function is jumped to by the trampoline */ unsigned int ffi_closure_SYSV_inner(ffi_closure *closure, void **respp, void *args) { ffi_cif *cif; void **arg_area; unsigned int i, size = 0; ffi_type **p_arg; cif = closure->cif; for(i = 0, p_arg = cif->arg_types; i < cif->nargs; i++, p_arg++) size += (*p_arg)->size + (4 - (*p_arg)->size % 4); arg_area = (void **)alloca(size); /* this call will initialize ARG_AREA, such that each element in that * array points to the corresponding value on the stack; and if the * function returns a structure, it will re-set RESP to point to the * structure return address. */ ffi_prep_incoming_args_SYSV(args, respp, arg_area, cif); (closure->fun)(cif, *respp, arg_area, closure->user_data); return cif->flags; } ffi_status ffi_prep_closure_loc(ffi_closure* closure, ffi_cif* cif, void (*fun)(ffi_cif*, void*, void**, void*), void *user_data, void *codeloc) { FFI_ASSERT(cif->abi == FFI_SYSV); unsigned char *__tramp = (unsigned char*)(&closure->tramp[0]); unsigned int __fun = (unsigned int)(&ffi_closure_SYSV); unsigned int __ctx = (unsigned int)(codeloc); unsigned int __rstruct_flag = (unsigned int)(cif->rstruct_flag); unsigned int __inner = (unsigned int)(&ffi_closure_SYSV_inner); *(unsigned int*) &__tramp[0] = 0xebcd1f00; /* pushm r8-r12 */ *(unsigned int*) &__tramp[4] = 0xfefc0010; /* ld.w r12, pc[16] */ *(unsigned int*) &__tramp[8] = 0xfefb0010; /* ld.w r11, pc[16] */ *(unsigned int*) &__tramp[12] = 0xfefa0010; /* ld.w r10, pc[16] */ *(unsigned int*) &__tramp[16] = 0xfeff0010; /* ld.w pc, pc[16] */ *(unsigned int*) &__tramp[20] = __ctx; *(unsigned int*) &__tramp[24] = __rstruct_flag; *(unsigned int*) &__tramp[28] = __inner; *(unsigned int*) &__tramp[32] = __fun; syscall(__NR_cacheflush, 0, (&__tramp[0]), 36); closure->cif = cif; closure->user_data = user_data; closure->fun = fun; return FFI_OK; } smalltalk-3.2.5/libffi/src/mips/0000755000175000017500000000000012130456004013473 500000000000000smalltalk-3.2.5/libffi/src/mips/n32.S0000644000175000017500000003426512130343734014160 00000000000000/* ----------------------------------------------------------------------- n32.S - Copyright (c) 1996, 1998, 2005, 2007, 2009, 2010 Red Hat, Inc. MIPS Foreign Function Interface Permission is hereby granted, free of charge, to any person obtaining a copy of this software and associated documentation files (the ``Software''), to deal in the Software without restriction, including without limitation the rights to use, copy, modify, merge, publish, distribute, sublicense, and/or sell copies of the Software, and to permit persons to whom the Software is furnished to do so, subject to the following conditions: The above copyright notice and this permission notice shall be included in all copies or substantial portions of the Software. THE SOFTWARE IS PROVIDED ``AS IS'', WITHOUT WARRANTY OF ANY KIND, EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. ----------------------------------------------------------------------- */ #define LIBFFI_ASM #include #include /* Only build this code if we are compiling for n32 */ #if defined(FFI_MIPS_N32) #define callback a0 #define bytes a2 #define flags a3 #define raddr a4 #define fn a5 #define SIZEOF_FRAME ( 8 * FFI_SIZEOF_ARG ) #ifdef __GNUC__ .abicalls #endif .text .align 2 .globl ffi_call_N32 .ent ffi_call_N32 ffi_call_N32: .LFB3: .frame $fp, SIZEOF_FRAME, ra .mask 0xc0000000,-FFI_SIZEOF_ARG .fmask 0x00000000,0 # Prologue SUBU $sp, SIZEOF_FRAME # Frame size .LCFI0: REG_S $fp, SIZEOF_FRAME - 2*FFI_SIZEOF_ARG($sp) # Save frame pointer REG_S ra, SIZEOF_FRAME - 1*FFI_SIZEOF_ARG($sp) # Save return address .LCFI1: move $fp, $sp .LCFI3: move t9, callback # callback function pointer REG_S bytes, 2*FFI_SIZEOF_ARG($fp) # bytes REG_S flags, 3*FFI_SIZEOF_ARG($fp) # flags REG_S raddr, 4*FFI_SIZEOF_ARG($fp) # raddr REG_S fn, 5*FFI_SIZEOF_ARG($fp) # fn # Allocate at least 4 words in the argstack move v0, bytes bge bytes, 4 * FFI_SIZEOF_ARG, bigger LI v0, 4 * FFI_SIZEOF_ARG b sixteen bigger: ADDU t4, v0, 2 * FFI_SIZEOF_ARG -1 # make sure it is aligned and v0, t4, -2 * FFI_SIZEOF_ARG # to a proper boundry. sixteen: SUBU $sp, $sp, v0 # move the stack pointer to reflect the # arg space move a0, $sp # 4 * FFI_SIZEOF_ARG ADDU a3, $fp, 3 * FFI_SIZEOF_ARG # Call ffi_prep_args jal t9 # Copy the stack pointer to t9 move t9, $sp # Fix the stack if there are more than 8 64bit slots worth # of arguments. # Load the number of bytes REG_L t6, 2*FFI_SIZEOF_ARG($fp) # Is it bigger than 8 * FFI_SIZEOF_ARG? daddiu t8, t6, -(8 * FFI_SIZEOF_ARG) bltz t8, loadregs ADDU t9, t9, t8 loadregs: REG_L t6, 3*FFI_SIZEOF_ARG($fp) # load the flags word into t6. and t4, t6, ((1< #include /* Only build this code if we are compiling for o32 */ #if defined(FFI_MIPS_O32) #define callback a0 #define bytes a2 #define flags a3 #define SIZEOF_FRAME (4 * FFI_SIZEOF_ARG + 2 * FFI_SIZEOF_ARG) #define A3_OFF (SIZEOF_FRAME + 3 * FFI_SIZEOF_ARG) #define FP_OFF (SIZEOF_FRAME - 2 * FFI_SIZEOF_ARG) #define RA_OFF (SIZEOF_FRAME - 1 * FFI_SIZEOF_ARG) .abicalls .text .align 2 .globl ffi_call_O32 .ent ffi_call_O32 ffi_call_O32: $LFB0: # Prologue SUBU $sp, SIZEOF_FRAME # Frame size $LCFI0: REG_S $fp, FP_OFF($sp) # Save frame pointer $LCFI1: REG_S ra, RA_OFF($sp) # Save return address $LCFI2: move $fp, $sp $LCFI3: move t9, callback # callback function pointer REG_S flags, A3_OFF($fp) # flags # Allocate at least 4 words in the argstack LI v0, 4 * FFI_SIZEOF_ARG blt bytes, v0, sixteen ADDU v0, bytes, 7 # make sure it is aligned and v0, -8 # to an 8 byte boundry sixteen: SUBU $sp, v0 # move the stack pointer to reflect the # arg space ADDU a0, $sp, 4 * FFI_SIZEOF_ARG jalr t9 REG_L t0, A3_OFF($fp) # load the flags word SRL t2, t0, 4 # shift our arg info and t0, ((1<<4)-1) # mask out the return type ADDU $sp, 4 * FFI_SIZEOF_ARG # adjust $sp to new args bnez t0, pass_d # make it quick for int REG_L a0, 0*FFI_SIZEOF_ARG($sp) # just go ahead and load the REG_L a1, 1*FFI_SIZEOF_ARG($sp) # four regs. REG_L a2, 2*FFI_SIZEOF_ARG($sp) REG_L a3, 3*FFI_SIZEOF_ARG($sp) b call_it pass_d: bne t0, FFI_ARGS_D, pass_f l.d $f12, 0*FFI_SIZEOF_ARG($sp) # load $fp regs from args REG_L a2, 2*FFI_SIZEOF_ARG($sp) # passing a double REG_L a3, 3*FFI_SIZEOF_ARG($sp) b call_it pass_f: bne t0, FFI_ARGS_F, pass_d_d l.s $f12, 0*FFI_SIZEOF_ARG($sp) # load $fp regs from args REG_L a1, 1*FFI_SIZEOF_ARG($sp) # passing a float REG_L a2, 2*FFI_SIZEOF_ARG($sp) REG_L a3, 3*FFI_SIZEOF_ARG($sp) b call_it pass_d_d: bne t0, FFI_ARGS_DD, pass_f_f l.d $f12, 0*FFI_SIZEOF_ARG($sp) # load $fp regs from args l.d $f14, 2*FFI_SIZEOF_ARG($sp) # passing two doubles b call_it pass_f_f: bne t0, FFI_ARGS_FF, pass_d_f l.s $f12, 0*FFI_SIZEOF_ARG($sp) # load $fp regs from args l.s $f14, 1*FFI_SIZEOF_ARG($sp) # passing two floats REG_L a2, 2*FFI_SIZEOF_ARG($sp) REG_L a3, 3*FFI_SIZEOF_ARG($sp) b call_it pass_d_f: bne t0, FFI_ARGS_DF, pass_f_d l.d $f12, 0*FFI_SIZEOF_ARG($sp) # load $fp regs from args l.s $f14, 2*FFI_SIZEOF_ARG($sp) # passing double and float REG_L a3, 3*FFI_SIZEOF_ARG($sp) b call_it pass_f_d: # assume that the only other combination must be float then double # bne t0, FFI_ARGS_F_D, call_it l.s $f12, 0*FFI_SIZEOF_ARG($sp) # load $fp regs from args l.d $f14, 2*FFI_SIZEOF_ARG($sp) # passing double and float call_it: # Load the function pointer REG_L t9, SIZEOF_FRAME + 5*FFI_SIZEOF_ARG($fp) # If the return value pointer is NULL, assume no return value. REG_L t1, SIZEOF_FRAME + 4*FFI_SIZEOF_ARG($fp) beqz t1, noretval bne t2, FFI_TYPE_INT, retlonglong jalr t9 REG_L t0, SIZEOF_FRAME + 4*FFI_SIZEOF_ARG($fp) REG_S v0, 0(t0) b epilogue retlonglong: # Really any 64-bit int, signed or not. bne t2, FFI_TYPE_UINT64, retfloat jalr t9 REG_L t0, SIZEOF_FRAME + 4*FFI_SIZEOF_ARG($fp) REG_S v1, 4(t0) REG_S v0, 0(t0) b epilogue retfloat: bne t2, FFI_TYPE_FLOAT, retdouble jalr t9 REG_L t0, SIZEOF_FRAME + 4*FFI_SIZEOF_ARG($fp) s.s $f0, 0(t0) b epilogue retdouble: bne t2, FFI_TYPE_DOUBLE, noretval jalr t9 REG_L t0, SIZEOF_FRAME + 4*FFI_SIZEOF_ARG($fp) s.d $f0, 0(t0) b epilogue noretval: jalr t9 # Epilogue epilogue: move $sp, $fp REG_L $fp, FP_OFF($sp) # Restore frame pointer REG_L ra, RA_OFF($sp) # Restore return address ADDU $sp, SIZEOF_FRAME # Fix stack pointer j ra $LFE0: .end ffi_call_O32 /* ffi_closure_O32. Expects address of the passed-in ffi_closure in t4 ($12). Stores any arguments passed in registers onto the stack, then calls ffi_closure_mips_inner_O32, which then decodes them. Stack layout: 3 - a3 save 2 - a2 save 1 - a1 save 0 - a0 save, original sp -1 - ra save -2 - fp save -3 - $16 (s0) save -4 - cprestore -5 - return value high (v1) -6 - return value low (v0) -7 - f14 (le high, be low) -8 - f14 (le low, be high) -9 - f12 (le high, be low) -10 - f12 (le low, be high) -11 - Called function a3 save -12 - Called function a2 save -13 - Called function a1 save -14 - Called function a0 save, our sp and fp point here */ #define SIZEOF_FRAME2 (14 * FFI_SIZEOF_ARG) #define A3_OFF2 (SIZEOF_FRAME2 + 3 * FFI_SIZEOF_ARG) #define A2_OFF2 (SIZEOF_FRAME2 + 2 * FFI_SIZEOF_ARG) #define A1_OFF2 (SIZEOF_FRAME2 + 1 * FFI_SIZEOF_ARG) #define A0_OFF2 (SIZEOF_FRAME2 + 0 * FFI_SIZEOF_ARG) #define RA_OFF2 (SIZEOF_FRAME2 - 1 * FFI_SIZEOF_ARG) #define FP_OFF2 (SIZEOF_FRAME2 - 2 * FFI_SIZEOF_ARG) #define S0_OFF2 (SIZEOF_FRAME2 - 3 * FFI_SIZEOF_ARG) #define GP_OFF2 (SIZEOF_FRAME2 - 4 * FFI_SIZEOF_ARG) #define V1_OFF2 (SIZEOF_FRAME2 - 5 * FFI_SIZEOF_ARG) #define V0_OFF2 (SIZEOF_FRAME2 - 6 * FFI_SIZEOF_ARG) #define FA_1_1_OFF2 (SIZEOF_FRAME2 - 7 * FFI_SIZEOF_ARG) #define FA_1_0_OFF2 (SIZEOF_FRAME2 - 8 * FFI_SIZEOF_ARG) #define FA_0_1_OFF2 (SIZEOF_FRAME2 - 9 * FFI_SIZEOF_ARG) #define FA_0_0_OFF2 (SIZEOF_FRAME2 - 10 * FFI_SIZEOF_ARG) .text .align 2 .globl ffi_closure_O32 .ent ffi_closure_O32 ffi_closure_O32: $LFB1: # Prologue .frame $fp, SIZEOF_FRAME2, ra .set noreorder .cpload t9 .set reorder SUBU $sp, SIZEOF_FRAME2 .cprestore GP_OFF2 $LCFI4: REG_S $16, S0_OFF2($sp) # Save s0 REG_S $fp, FP_OFF2($sp) # Save frame pointer REG_S ra, RA_OFF2($sp) # Save return address $LCFI6: move $fp, $sp $LCFI7: # Store all possible argument registers. If there are more than # four arguments, then they are stored above where we put a3. REG_S a0, A0_OFF2($fp) REG_S a1, A1_OFF2($fp) REG_S a2, A2_OFF2($fp) REG_S a3, A3_OFF2($fp) # Load ABI enum to s0 REG_L $16, 20($12) # cif pointer follows tramp. REG_L $16, 0($16) # abi is first member. li $13, 1 # FFI_O32 bne $16, $13, 1f # Skip fp save if FFI_O32_SOFT_FLOAT # Store all possible float/double registers. s.d $f12, FA_0_0_OFF2($fp) s.d $f14, FA_1_0_OFF2($fp) 1: # Call ffi_closure_mips_inner_O32 to do the work. la t9, ffi_closure_mips_inner_O32 move a0, $12 # Pointer to the ffi_closure addu a1, $fp, V0_OFF2 addu a2, $fp, A0_OFF2 addu a3, $fp, FA_0_0_OFF2 jalr t9 # Load the return value into the appropriate register. move $8, $2 li $9, FFI_TYPE_VOID beq $8, $9, closure_done li $13, 1 # FFI_O32 bne $16, $13, 1f # Skip fp restore if FFI_O32_SOFT_FLOAT li $9, FFI_TYPE_FLOAT l.s $f0, V0_OFF2($fp) beq $8, $9, closure_done li $9, FFI_TYPE_DOUBLE l.d $f0, V0_OFF2($fp) beq $8, $9, closure_done 1: REG_L $3, V1_OFF2($fp) REG_L $2, V0_OFF2($fp) closure_done: # Epilogue move $sp, $fp REG_L $16, S0_OFF2($sp) # Restore s0 REG_L $fp, FP_OFF2($sp) # Restore frame pointer REG_L ra, RA_OFF2($sp) # Restore return address ADDU $sp, SIZEOF_FRAME2 j ra $LFE1: .end ffi_closure_O32 /* DWARF-2 unwind info. */ .section .eh_frame,"a",@progbits $Lframe0: .4byte $LECIE0-$LSCIE0 # Length of Common Information Entry $LSCIE0: .4byte 0x0 # CIE Identifier Tag .byte 0x1 # CIE Version .ascii "zR\0" # CIE Augmentation .uleb128 0x1 # CIE Code Alignment Factor .sleb128 4 # CIE Data Alignment Factor .byte 0x1f # CIE RA Column .uleb128 0x1 # Augmentation size .byte 0x00 # FDE Encoding (absptr) .byte 0xc # DW_CFA_def_cfa .uleb128 0x1d .uleb128 0x0 .align 2 $LECIE0: $LSFDE0: .4byte $LEFDE0-$LASFDE0 # FDE Length $LASFDE0: .4byte $LASFDE0-$Lframe0 # FDE CIE offset .4byte $LFB0 # FDE initial location .4byte $LFE0-$LFB0 # FDE address range .uleb128 0x0 # Augmentation size .byte 0x4 # DW_CFA_advance_loc4 .4byte $LCFI0-$LFB0 .byte 0xe # DW_CFA_def_cfa_offset .uleb128 0x18 .byte 0x4 # DW_CFA_advance_loc4 .4byte $LCFI2-$LCFI0 .byte 0x11 # DW_CFA_offset_extended_sf .uleb128 0x1e # $fp .sleb128 -2 # SIZEOF_FRAME2 - 2*FFI_SIZEOF_ARG($sp) .byte 0x11 # DW_CFA_offset_extended_sf .uleb128 0x1f # $ra .sleb128 -1 # SIZEOF_FRAME2 - 1*FFI_SIZEOF_ARG($sp) .byte 0x4 # DW_CFA_advance_loc4 .4byte $LCFI3-$LCFI2 .byte 0xc # DW_CFA_def_cfa .uleb128 0x1e .uleb128 0x18 .align 2 $LEFDE0: $LSFDE1: .4byte $LEFDE1-$LASFDE1 # FDE Length $LASFDE1: .4byte $LASFDE1-$Lframe0 # FDE CIE offset .4byte $LFB1 # FDE initial location .4byte $LFE1-$LFB1 # FDE address range .uleb128 0x0 # Augmentation size .byte 0x4 # DW_CFA_advance_loc4 .4byte $LCFI4-$LFB1 .byte 0xe # DW_CFA_def_cfa_offset .uleb128 0x38 .byte 0x4 # DW_CFA_advance_loc4 .4byte $LCFI6-$LCFI4 .byte 0x11 # DW_CFA_offset_extended_sf .uleb128 0x10 # $16 .sleb128 -3 # SIZEOF_FRAME2 - 3*FFI_SIZEOF_ARG($sp) .byte 0x11 # DW_CFA_offset_extended_sf .uleb128 0x1e # $fp .sleb128 -2 # SIZEOF_FRAME2 - 2*FFI_SIZEOF_ARG($sp) .byte 0x11 # DW_CFA_offset_extended_sf .uleb128 0x1f # $ra .sleb128 -1 # SIZEOF_FRAME2 - 1*FFI_SIZEOF_ARG($sp) .byte 0x4 # DW_CFA_advance_loc4 .4byte $LCFI7-$LCFI6 .byte 0xc # DW_CFA_def_cfa .uleb128 0x1e .uleb128 0x38 .align 2 $LEFDE1: #endif smalltalk-3.2.5/libffi/src/mips/ffitarget.h0000644000175000017500000001407512130343734015553 00000000000000/* -----------------------------------------------------------------*-C-*- ffitarget.h - Copyright (c) 1996-2003 Red Hat, Inc. Target configuration macros for MIPS. Permission is hereby granted, free of charge, to any person obtaining a copy of this software and associated documentation files (the ``Software''), to deal in the Software without restriction, including without limitation the rights to use, copy, modify, merge, publish, distribute, sublicense, and/or sell copies of the Software, and to permit persons to whom the Software is furnished to do so, subject to the following conditions: The above copyright notice and this permission notice shall be included in all copies or substantial portions of the Software. THE SOFTWARE IS PROVIDED ``AS IS'', WITHOUT WARRANTY OF ANY KIND, EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. ----------------------------------------------------------------------- */ #ifndef LIBFFI_TARGET_H #define LIBFFI_TARGET_H #ifdef linux # include #else # include #endif # ifndef _ABIN32 # define _ABIN32 _MIPS_SIM_NABI32 # endif # ifndef _ABI64 # define _ABI64 _MIPS_SIM_ABI64 # endif # ifndef _ABIO32 # define _ABIO32 _MIPS_SIM_ABI32 # endif #if !defined(_MIPS_SIM) -- something is very wrong -- #else # if (_MIPS_SIM==_ABIN32 && defined(_ABIN32)) || (_MIPS_SIM==_ABI64 && defined(_ABI64)) # define FFI_MIPS_N32 # else # if (_MIPS_SIM==_ABIO32 && defined(_ABIO32)) # define FFI_MIPS_O32 # else -- this is an unsupported platform -- # endif # endif #endif #ifdef FFI_MIPS_O32 /* O32 stack frames have 32bit integer args */ # define FFI_SIZEOF_ARG 4 #else /* N32 and N64 frames have 64bit integer args */ # define FFI_SIZEOF_ARG 8 # if _MIPS_SIM == _ABIN32 # define FFI_SIZEOF_JAVA_RAW 4 # endif #endif #define FFI_FLAG_BITS 2 /* SGI's strange assembler requires that we multiply by 4 rather than shift left by FFI_FLAG_BITS */ #define FFI_ARGS_D FFI_TYPE_DOUBLE #define FFI_ARGS_F FFI_TYPE_FLOAT #define FFI_ARGS_DD FFI_TYPE_DOUBLE * 4 + FFI_TYPE_DOUBLE #define FFI_ARGS_FF FFI_TYPE_FLOAT * 4 + FFI_TYPE_FLOAT #define FFI_ARGS_FD FFI_TYPE_DOUBLE * 4 + FFI_TYPE_FLOAT #define FFI_ARGS_DF FFI_TYPE_FLOAT * 4 + FFI_TYPE_DOUBLE /* Needed for N32 structure returns */ #define FFI_TYPE_SMALLSTRUCT FFI_TYPE_UINT8 #define FFI_TYPE_SMALLSTRUCT2 FFI_TYPE_SINT8 #if 0 /* The SGI assembler can't handle this.. */ #define FFI_TYPE_STRUCT_DD (( FFI_ARGS_DD ) << 4) + FFI_TYPE_STRUCT /* (and so on) */ #else /* ...so we calculate these by hand! */ #define FFI_TYPE_STRUCT_D 61 #define FFI_TYPE_STRUCT_F 45 #define FFI_TYPE_STRUCT_DD 253 #define FFI_TYPE_STRUCT_FF 173 #define FFI_TYPE_STRUCT_FD 237 #define FFI_TYPE_STRUCT_DF 189 #define FFI_TYPE_STRUCT_SMALL 93 #define FFI_TYPE_STRUCT_SMALL2 109 /* and for n32 soft float, add 16 * 2^4 */ #define FFI_TYPE_STRUCT_D_SOFT 317 #define FFI_TYPE_STRUCT_F_SOFT 301 #define FFI_TYPE_STRUCT_DD_SOFT 509 #define FFI_TYPE_STRUCT_FF_SOFT 429 #define FFI_TYPE_STRUCT_FD_SOFT 493 #define FFI_TYPE_STRUCT_DF_SOFT 445 #define FFI_TYPE_STRUCT_SOFT 16 #endif #ifdef LIBFFI_ASM #define v0 $2 #define v1 $3 #define a0 $4 #define a1 $5 #define a2 $6 #define a3 $7 #define a4 $8 #define a5 $9 #define a6 $10 #define a7 $11 #define t0 $8 #define t1 $9 #define t2 $10 #define t3 $11 #define t4 $12 #define t5 $13 #define t6 $14 #define t7 $15 #define t8 $24 #define t9 $25 #define ra $31 #ifdef FFI_MIPS_O32 # define REG_L lw # define REG_S sw # define SUBU subu # define ADDU addu # define SRL srl # define LI li #else /* !FFI_MIPS_O32 */ # define REG_L ld # define REG_S sd # define SUBU dsubu # define ADDU daddu # define SRL dsrl # define LI dli # if (_MIPS_SIM==_ABI64) # define LA dla # define EH_FRAME_ALIGN 3 # define FDE_ADDR_BYTES .8byte # else # define LA la # define EH_FRAME_ALIGN 2 # define FDE_ADDR_BYTES .4byte # endif /* _MIPS_SIM==_ABI64 */ #endif /* !FFI_MIPS_O32 */ #else /* !LIBFFI_ASM */ # ifdef __GNUC__ # ifdef FFI_MIPS_O32 /* O32 stack frames have 32bit integer args */ typedef unsigned int ffi_arg __attribute__((__mode__(__SI__))); typedef signed int ffi_sarg __attribute__((__mode__(__SI__))); #else /* N32 and N64 frames have 64bit integer args */ typedef unsigned int ffi_arg __attribute__((__mode__(__DI__))); typedef signed int ffi_sarg __attribute__((__mode__(__DI__))); # endif # else # ifdef FFI_MIPS_O32 /* O32 stack frames have 32bit integer args */ typedef __uint32_t ffi_arg; typedef __int32_t ffi_sarg; # else /* N32 and N64 frames have 64bit integer args */ typedef __uint64_t ffi_arg; typedef __int64_t ffi_sarg; # endif # endif /* __GNUC__ */ typedef enum ffi_abi { FFI_FIRST_ABI = 0, FFI_O32, FFI_N32, FFI_N64, FFI_O32_SOFT_FLOAT, FFI_N32_SOFT_FLOAT, FFI_N64_SOFT_FLOAT, #ifdef FFI_MIPS_O32 #ifdef __mips_soft_float FFI_DEFAULT_ABI = FFI_O32_SOFT_FLOAT, #else FFI_DEFAULT_ABI = FFI_O32, #endif #else # if _MIPS_SIM==_ABI64 # ifdef __mips_soft_float FFI_DEFAULT_ABI = FFI_N64_SOFT_FLOAT, # else FFI_DEFAULT_ABI = FFI_N64, # endif # else # ifdef __mips_soft_float FFI_DEFAULT_ABI = FFI_N32_SOFT_FLOAT, # else FFI_DEFAULT_ABI = FFI_N32, # endif # endif #endif FFI_LAST_ABI = FFI_DEFAULT_ABI + 1 } ffi_abi; #define FFI_EXTRA_CIF_FIELDS unsigned rstruct_flag #endif /* !LIBFFI_ASM */ /* ---- Definitions for closures ----------------------------------------- */ #if defined(FFI_MIPS_O32) #define FFI_CLOSURES 1 #define FFI_TRAMPOLINE_SIZE 20 #else /* N32/N64. */ # define FFI_CLOSURES 1 #if _MIPS_SIM==_ABI64 #define FFI_TRAMPOLINE_SIZE 52 #else #define FFI_TRAMPOLINE_SIZE 20 #endif #endif /* FFI_MIPS_O32 */ #define FFI_NATIVE_RAW_API 0 #endif smalltalk-3.2.5/libffi/src/mips/ffi.c0000644000175000017500000006304312130343734014336 00000000000000/* ----------------------------------------------------------------------- ffi.c - Copyright (c) 1996, 2007, 2008 Red Hat, Inc. Copyright (c) 2008 David Daney MIPS Foreign Function Interface Permission is hereby granted, free of charge, to any person obtaining a copy of this software and associated documentation files (the ``Software''), to deal in the Software without restriction, including without limitation the rights to use, copy, modify, merge, publish, distribute, sublicense, and/or sell copies of the Software, and to permit persons to whom the Software is furnished to do so, subject to the following conditions: The above copyright notice and this permission notice shall be included in all copies or substantial portions of the Software. THE SOFTWARE IS PROVIDED ``AS IS'', WITHOUT WARRANTY OF ANY KIND, EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. ----------------------------------------------------------------------- */ #include #include #include #ifdef __GNUC__ # if (__GNUC__ > 4) || ((__GNUC__ == 4) && (__GNUC_MINOR__ >= 3)) # define USE__BUILTIN___CLEAR_CACHE 1 # endif #endif #ifndef USE__BUILTIN___CLEAR_CACHE #include #endif #ifdef FFI_DEBUG # define FFI_MIPS_STOP_HERE() ffi_stop_here() #else # define FFI_MIPS_STOP_HERE() do {} while(0) #endif #ifdef FFI_MIPS_N32 #define FIX_ARGP \ FFI_ASSERT(argp <= &stack[bytes]); \ if (argp == &stack[bytes]) \ { \ argp = stack; \ FFI_MIPS_STOP_HERE(); \ } #else #define FIX_ARGP #endif /* ffi_prep_args is called by the assembly routine once stack space has been allocated for the function's arguments */ static void ffi_prep_args(char *stack, extended_cif *ecif, int bytes, int flags) { int i; void **p_argv; char *argp; ffi_type **p_arg; #ifdef FFI_MIPS_N32 /* If more than 8 double words are used, the remainder go on the stack. We reorder stuff on the stack here to support this easily. */ if (bytes > 8 * sizeof(ffi_arg)) argp = &stack[bytes - (8 * sizeof(ffi_arg))]; else argp = stack; #else argp = stack; #endif memset(stack, 0, bytes); #ifdef FFI_MIPS_N32 if ( ecif->cif->rstruct_flag != 0 ) #else if ( ecif->cif->rtype->type == FFI_TYPE_STRUCT ) #endif { *(ffi_arg *) argp = (ffi_arg) ecif->rvalue; argp += sizeof(ffi_arg); FIX_ARGP; } p_argv = ecif->avalue; for (i = 0, p_arg = ecif->cif->arg_types; i < ecif->cif->nargs; i++, p_arg++) { size_t z; unsigned int a; /* Align if necessary. */ a = (*p_arg)->alignment; if (a < sizeof(ffi_arg)) a = sizeof(ffi_arg); if ((a - 1) & (unsigned long) argp) { argp = (char *) ALIGN(argp, a); FIX_ARGP; } z = (*p_arg)->size; if (z <= sizeof(ffi_arg)) { int type = (*p_arg)->type; z = sizeof(ffi_arg); /* The size of a pointer depends on the ABI */ if (type == FFI_TYPE_POINTER) type = (ecif->cif->abi == FFI_N64 || ecif->cif->abi == FFI_N64_SOFT_FLOAT) ? FFI_TYPE_SINT64 : FFI_TYPE_SINT32; if (i < 8 && (ecif->cif->abi == FFI_N32_SOFT_FLOAT || ecif->cif->abi == FFI_N64_SOFT_FLOAT)) { switch (type) { case FFI_TYPE_FLOAT: type = FFI_TYPE_UINT32; break; case FFI_TYPE_DOUBLE: type = FFI_TYPE_UINT64; break; default: break; } } switch (type) { case FFI_TYPE_SINT8: *(ffi_arg *)argp = *(SINT8 *)(* p_argv); break; case FFI_TYPE_UINT8: *(ffi_arg *)argp = *(UINT8 *)(* p_argv); break; case FFI_TYPE_SINT16: *(ffi_arg *)argp = *(SINT16 *)(* p_argv); break; case FFI_TYPE_UINT16: *(ffi_arg *)argp = *(UINT16 *)(* p_argv); break; case FFI_TYPE_SINT32: *(ffi_arg *)argp = *(SINT32 *)(* p_argv); break; case FFI_TYPE_UINT32: *(ffi_arg *)argp = *(UINT32 *)(* p_argv); break; /* This can only happen with 64bit slots. */ case FFI_TYPE_FLOAT: *(float *) argp = *(float *)(* p_argv); break; /* Handle structures. */ default: memcpy(argp, *p_argv, (*p_arg)->size); break; } } else { #ifdef FFI_MIPS_O32 memcpy(argp, *p_argv, z); #else { unsigned long end = (unsigned long) argp + z; unsigned long cap = (unsigned long) stack + bytes; /* Check if the data will fit within the register space. Handle it if it doesn't. */ if (end <= cap) memcpy(argp, *p_argv, z); else { unsigned long portion = cap - (unsigned long)argp; memcpy(argp, *p_argv, portion); argp = stack; z -= portion; memcpy(argp, (void*)((unsigned long)(*p_argv) + portion), z); } } #endif } p_argv++; argp += z; FIX_ARGP; } } #ifdef FFI_MIPS_N32 /* The n32 spec says that if "a chunk consists solely of a double float field (but not a double, which is part of a union), it is passed in a floating point register. Any other chunk is passed in an integer register". This code traverses structure definitions and generates the appropriate flags. */ static unsigned calc_n32_struct_flags(int soft_float, ffi_type *arg, unsigned *loc, unsigned *arg_reg) { unsigned flags = 0; unsigned index = 0; ffi_type *e; if (soft_float) return 0; while ((e = arg->elements[index])) { /* Align this object. */ *loc = ALIGN(*loc, e->alignment); if (e->type == FFI_TYPE_DOUBLE) { /* Already aligned to FFI_SIZEOF_ARG. */ *arg_reg = *loc / FFI_SIZEOF_ARG; if (*arg_reg > 7) break; flags += (FFI_TYPE_DOUBLE << (*arg_reg * FFI_FLAG_BITS)); *loc += e->size; } else *loc += e->size; index++; } /* Next Argument register at alignment of FFI_SIZEOF_ARG. */ *arg_reg = ALIGN(*loc, FFI_SIZEOF_ARG) / FFI_SIZEOF_ARG; return flags; } static unsigned calc_n32_return_struct_flags(int soft_float, ffi_type *arg) { unsigned flags = 0; unsigned small = FFI_TYPE_SMALLSTRUCT; ffi_type *e; /* Returning structures under n32 is a tricky thing. A struct with only one or two floating point fields is returned in $f0 (and $f2 if necessary). Any other struct results at most 128 bits are returned in $2 (the first 64 bits) and $3 (remainder, if necessary). Larger structs are handled normally. */ if (arg->size > 16) return 0; if (arg->size > 8) small = FFI_TYPE_SMALLSTRUCT2; e = arg->elements[0]; if (e->type == FFI_TYPE_DOUBLE) flags = FFI_TYPE_DOUBLE; else if (e->type == FFI_TYPE_FLOAT) flags = FFI_TYPE_FLOAT; if (flags && (e = arg->elements[1])) { if (e->type == FFI_TYPE_DOUBLE) flags += FFI_TYPE_DOUBLE << FFI_FLAG_BITS; else if (e->type == FFI_TYPE_FLOAT) flags += FFI_TYPE_FLOAT << FFI_FLAG_BITS; else return small; if (flags && (arg->elements[2])) { /* There are three arguments and the first two are floats! This must be passed the old way. */ return small; } if (soft_float) flags += FFI_TYPE_STRUCT_SOFT; } else if (!flags) return small; return flags; } #endif /* Perform machine dependent cif processing */ ffi_status ffi_prep_cif_machdep(ffi_cif *cif) { cif->flags = 0; #ifdef FFI_MIPS_O32 /* Set the flags necessary for O32 processing. FFI_O32_SOFT_FLOAT * does not have special handling for floating point args. */ if (cif->rtype->type != FFI_TYPE_STRUCT && cif->abi == FFI_O32) { if (cif->nargs > 0) { switch ((cif->arg_types)[0]->type) { case FFI_TYPE_FLOAT: case FFI_TYPE_DOUBLE: cif->flags += (cif->arg_types)[0]->type; break; default: break; } if (cif->nargs > 1) { /* Only handle the second argument if the first is a float or double. */ if (cif->flags) { switch ((cif->arg_types)[1]->type) { case FFI_TYPE_FLOAT: case FFI_TYPE_DOUBLE: cif->flags += (cif->arg_types)[1]->type << FFI_FLAG_BITS; break; default: break; } } } } } /* Set the return type flag */ if (cif->abi == FFI_O32_SOFT_FLOAT) { switch (cif->rtype->type) { case FFI_TYPE_VOID: case FFI_TYPE_STRUCT: cif->flags += cif->rtype->type << (FFI_FLAG_BITS * 2); break; case FFI_TYPE_SINT64: case FFI_TYPE_UINT64: case FFI_TYPE_DOUBLE: cif->flags += FFI_TYPE_UINT64 << (FFI_FLAG_BITS * 2); break; case FFI_TYPE_FLOAT: default: cif->flags += FFI_TYPE_INT << (FFI_FLAG_BITS * 2); break; } } else { /* FFI_O32 */ switch (cif->rtype->type) { case FFI_TYPE_VOID: case FFI_TYPE_STRUCT: case FFI_TYPE_FLOAT: case FFI_TYPE_DOUBLE: cif->flags += cif->rtype->type << (FFI_FLAG_BITS * 2); break; case FFI_TYPE_SINT64: case FFI_TYPE_UINT64: cif->flags += FFI_TYPE_UINT64 << (FFI_FLAG_BITS * 2); break; default: cif->flags += FFI_TYPE_INT << (FFI_FLAG_BITS * 2); break; } } #endif #ifdef FFI_MIPS_N32 /* Set the flags necessary for N32 processing */ { int type; unsigned arg_reg = 0; unsigned loc = 0; unsigned count = (cif->nargs < 8) ? cif->nargs : 8; unsigned index = 0; unsigned struct_flags = 0; int soft_float = (cif->abi == FFI_N32_SOFT_FLOAT || cif->abi == FFI_N64_SOFT_FLOAT); if (cif->rtype->type == FFI_TYPE_STRUCT) { struct_flags = calc_n32_return_struct_flags(soft_float, cif->rtype); if (struct_flags == 0) { /* This means that the structure is being passed as a hidden argument */ arg_reg = 1; count = (cif->nargs < 7) ? cif->nargs : 7; cif->rstruct_flag = !0; } else cif->rstruct_flag = 0; } else cif->rstruct_flag = 0; while (count-- > 0 && arg_reg < 8) { type = (cif->arg_types)[index]->type; if (soft_float) { switch (type) { case FFI_TYPE_FLOAT: type = FFI_TYPE_UINT32; break; case FFI_TYPE_DOUBLE: type = FFI_TYPE_UINT64; break; default: break; } } switch (type) { case FFI_TYPE_FLOAT: case FFI_TYPE_DOUBLE: cif->flags += ((cif->arg_types)[index]->type << (arg_reg * FFI_FLAG_BITS)); arg_reg++; break; case FFI_TYPE_LONGDOUBLE: /* Align it. */ arg_reg = ALIGN(arg_reg, 2); /* Treat it as two adjacent doubles. */ if (soft_float) { arg_reg += 2; } else { cif->flags += (FFI_TYPE_DOUBLE << (arg_reg * FFI_FLAG_BITS)); arg_reg++; cif->flags += (FFI_TYPE_DOUBLE << (arg_reg * FFI_FLAG_BITS)); arg_reg++; } break; case FFI_TYPE_STRUCT: loc = arg_reg * FFI_SIZEOF_ARG; cif->flags += calc_n32_struct_flags(soft_float, (cif->arg_types)[index], &loc, &arg_reg); break; default: arg_reg++; break; } index++; } /* Set the return type flag */ switch (cif->rtype->type) { case FFI_TYPE_STRUCT: { if (struct_flags == 0) { /* The structure is returned through a hidden first argument. Do nothing, 'cause FFI_TYPE_VOID is 0 */ } else { /* The structure is returned via some tricky mechanism */ cif->flags += FFI_TYPE_STRUCT << (FFI_FLAG_BITS * 8); cif->flags += struct_flags << (4 + (FFI_FLAG_BITS * 8)); } break; } case FFI_TYPE_VOID: /* Do nothing, 'cause FFI_TYPE_VOID is 0 */ break; case FFI_TYPE_POINTER: if (cif->abi == FFI_N32_SOFT_FLOAT || cif->abi == FFI_N32) cif->flags += FFI_TYPE_SINT32 << (FFI_FLAG_BITS * 8); else cif->flags += FFI_TYPE_INT << (FFI_FLAG_BITS * 8); break; case FFI_TYPE_FLOAT: if (soft_float) { cif->flags += FFI_TYPE_SINT32 << (FFI_FLAG_BITS * 8); break; } /* else fall through */ case FFI_TYPE_DOUBLE: if (soft_float) cif->flags += FFI_TYPE_INT << (FFI_FLAG_BITS * 8); else cif->flags += cif->rtype->type << (FFI_FLAG_BITS * 8); break; case FFI_TYPE_LONGDOUBLE: /* Long double is returned as if it were a struct containing two doubles. */ if (soft_float) { cif->flags += FFI_TYPE_STRUCT << (FFI_FLAG_BITS * 8); cif->flags += FFI_TYPE_SMALLSTRUCT2 << (4 + (FFI_FLAG_BITS * 8)); } else { cif->flags += FFI_TYPE_STRUCT << (FFI_FLAG_BITS * 8); cif->flags += (FFI_TYPE_DOUBLE + (FFI_TYPE_DOUBLE << FFI_FLAG_BITS)) << (4 + (FFI_FLAG_BITS * 8)); } break; default: cif->flags += FFI_TYPE_INT << (FFI_FLAG_BITS * 8); break; } } #endif return FFI_OK; } /* Low level routine for calling O32 functions */ extern int ffi_call_O32(void (*)(char *, extended_cif *, int, int), extended_cif *, unsigned, unsigned, unsigned *, void (*)(void)); /* Low level routine for calling N32 functions */ extern int ffi_call_N32(void (*)(char *, extended_cif *, int, int), extended_cif *, unsigned, unsigned, void *, void (*)(void)); void ffi_call(ffi_cif *cif, void (*fn)(void), void *rvalue, void **avalue) { extended_cif ecif; ecif.cif = cif; ecif.avalue = avalue; /* If the return value is a struct and we don't have a return */ /* value address then we need to make one */ if ((rvalue == NULL) && (cif->rtype->type == FFI_TYPE_STRUCT)) ecif.rvalue = alloca(cif->rtype->size); else ecif.rvalue = rvalue; switch (cif->abi) { #ifdef FFI_MIPS_O32 case FFI_O32: case FFI_O32_SOFT_FLOAT: ffi_call_O32(ffi_prep_args, &ecif, cif->bytes, cif->flags, ecif.rvalue, fn); break; #endif #ifdef FFI_MIPS_N32 case FFI_N32: case FFI_N32_SOFT_FLOAT: case FFI_N64: case FFI_N64_SOFT_FLOAT: { int copy_rvalue = 0; int copy_offset = 0; char *rvalue_copy = ecif.rvalue; if (cif->rtype->type == FFI_TYPE_STRUCT && cif->rtype->size < 16) { /* For structures smaller than 16 bytes we clobber memory in 8 byte increments. Make a copy so we don't clobber the callers memory outside of the struct bounds. */ rvalue_copy = alloca(16); copy_rvalue = 1; } else if (cif->rtype->type == FFI_TYPE_FLOAT && (cif->abi == FFI_N64_SOFT_FLOAT || cif->abi == FFI_N32_SOFT_FLOAT)) { rvalue_copy = alloca (8); copy_rvalue = 1; #if defined(__MIPSEB__) || defined(_MIPSEB) copy_offset = 4; #endif } ffi_call_N32(ffi_prep_args, &ecif, cif->bytes, cif->flags, rvalue_copy, fn); if (copy_rvalue) memcpy(ecif.rvalue, rvalue_copy + copy_offset, cif->rtype->size); } break; #endif default: FFI_ASSERT(0); break; } } #if FFI_CLOSURES #if defined(FFI_MIPS_O32) extern void ffi_closure_O32(void); #else extern void ffi_closure_N32(void); #endif /* FFI_MIPS_O32 */ ffi_status ffi_prep_closure_loc (ffi_closure *closure, ffi_cif *cif, void (*fun)(ffi_cif*,void*,void**,void*), void *user_data, void *codeloc) { unsigned int *tramp = (unsigned int *) &closure->tramp[0]; void * fn; char *clear_location = (char *) codeloc; #if defined(FFI_MIPS_O32) FFI_ASSERT(cif->abi == FFI_O32 || cif->abi == FFI_O32_SOFT_FLOAT); fn = ffi_closure_O32; #else /* FFI_MIPS_N32 */ FFI_ASSERT(cif->abi == FFI_N32 || cif->abi == FFI_N64); fn = ffi_closure_N32; #endif /* FFI_MIPS_O32 */ #if defined(FFI_MIPS_O32) || (_MIPS_SIM ==_ABIN32) /* lui $25,high(fn) */ tramp[0] = 0x3c190000 | ((unsigned)fn >> 16); /* ori $25,low(fn) */ tramp[1] = 0x37390000 | ((unsigned)fn & 0xffff); /* lui $12,high(codeloc) */ tramp[2] = 0x3c0c0000 | ((unsigned)codeloc >> 16); /* jr $25 */ tramp[3] = 0x03200008; /* ori $12,low(codeloc) */ tramp[4] = 0x358c0000 | ((unsigned)codeloc & 0xffff); #else /* N64 has a somewhat larger trampoline. */ /* lui $25,high(fn) */ tramp[0] = 0x3c190000 | ((unsigned long)fn >> 48); /* lui $12,high(codeloc) */ tramp[1] = 0x3c0c0000 | ((unsigned long)codeloc >> 48); /* ori $25,mid-high(fn) */ tramp[2] = 0x37390000 | (((unsigned long)fn >> 32 ) & 0xffff); /* ori $12,mid-high(codeloc) */ tramp[3] = 0x358c0000 | (((unsigned long)codeloc >> 32) & 0xffff); /* dsll $25,$25,16 */ tramp[4] = 0x0019cc38; /* dsll $12,$12,16 */ tramp[5] = 0x000c6438; /* ori $25,mid-low(fn) */ tramp[6] = 0x37390000 | (((unsigned long)fn >> 16 ) & 0xffff); /* ori $12,mid-low(codeloc) */ tramp[7] = 0x358c0000 | (((unsigned long)codeloc >> 16) & 0xffff); /* dsll $25,$25,16 */ tramp[8] = 0x0019cc38; /* dsll $12,$12,16 */ tramp[9] = 0x000c6438; /* ori $25,low(fn) */ tramp[10] = 0x37390000 | ((unsigned long)fn & 0xffff); /* jr $25 */ tramp[11] = 0x03200008; /* ori $12,low(codeloc) */ tramp[12] = 0x358c0000 | ((unsigned long)codeloc & 0xffff); #endif closure->cif = cif; closure->fun = fun; closure->user_data = user_data; #ifdef USE__BUILTIN___CLEAR_CACHE __builtin___clear_cache(clear_location, clear_location + FFI_TRAMPOLINE_SIZE); #else cacheflush (clear_location, FFI_TRAMPOLINE_SIZE, ICACHE); #endif return FFI_OK; } /* * Decodes the arguments to a function, which will be stored on the * stack. AR is the pointer to the beginning of the integer arguments * (and, depending upon the arguments, some floating-point arguments * as well). FPR is a pointer to the area where floating point * registers have been saved, if any. * * RVALUE is the location where the function return value will be * stored. CLOSURE is the prepared closure to invoke. * * This function should only be called from assembly, which is in * turn called from a trampoline. * * Returns the function return type. * * Based on the similar routine for sparc. */ int ffi_closure_mips_inner_O32 (ffi_closure *closure, void *rvalue, ffi_arg *ar, double *fpr) { ffi_cif *cif; void **avaluep; ffi_arg *avalue; ffi_type **arg_types; int i, avn, argn, seen_int; cif = closure->cif; avalue = alloca (cif->nargs * sizeof (ffi_arg)); avaluep = alloca (cif->nargs * sizeof (ffi_arg)); seen_int = (cif->abi == FFI_O32_SOFT_FLOAT); argn = 0; if ((cif->flags >> (FFI_FLAG_BITS * 2)) == FFI_TYPE_STRUCT) { rvalue = (void *)(UINT32)ar[0]; argn = 1; } i = 0; avn = cif->nargs; arg_types = cif->arg_types; while (i < avn) { if (i < 2 && !seen_int && (arg_types[i]->type == FFI_TYPE_FLOAT || arg_types[i]->type == FFI_TYPE_DOUBLE || arg_types[i]->type == FFI_TYPE_LONGDOUBLE)) { #if defined(__MIPSEB__) || defined(_MIPSEB) if (arg_types[i]->type == FFI_TYPE_FLOAT) avaluep[i] = ((char *) &fpr[i]) + sizeof (float); else #endif avaluep[i] = (char *) &fpr[i]; } else { if (arg_types[i]->alignment == 8 && (argn & 0x1)) argn++; switch (arg_types[i]->type) { case FFI_TYPE_SINT8: avaluep[i] = &avalue[i]; *(SINT8 *) &avalue[i] = (SINT8) ar[argn]; break; case FFI_TYPE_UINT8: avaluep[i] = &avalue[i]; *(UINT8 *) &avalue[i] = (UINT8) ar[argn]; break; case FFI_TYPE_SINT16: avaluep[i] = &avalue[i]; *(SINT16 *) &avalue[i] = (SINT16) ar[argn]; break; case FFI_TYPE_UINT16: avaluep[i] = &avalue[i]; *(UINT16 *) &avalue[i] = (UINT16) ar[argn]; break; default: avaluep[i] = (char *) &ar[argn]; break; } seen_int = 1; } argn += ALIGN(arg_types[i]->size, FFI_SIZEOF_ARG) / FFI_SIZEOF_ARG; i++; } /* Invoke the closure. */ (closure->fun) (cif, rvalue, avaluep, closure->user_data); if (cif->abi == FFI_O32_SOFT_FLOAT) { switch (cif->rtype->type) { case FFI_TYPE_FLOAT: return FFI_TYPE_INT; case FFI_TYPE_DOUBLE: return FFI_TYPE_UINT64; default: return cif->rtype->type; } } else { return cif->rtype->type; } } #if defined(FFI_MIPS_N32) static void copy_struct_N32(char *target, unsigned offset, ffi_abi abi, ffi_type *type, int argn, unsigned arg_offset, ffi_arg *ar, ffi_arg *fpr, int soft_float) { ffi_type **elt_typep = type->elements; while(*elt_typep) { ffi_type *elt_type = *elt_typep; unsigned o; char *tp; char *argp; char *fpp; o = ALIGN(offset, elt_type->alignment); arg_offset += o - offset; offset = o; argn += arg_offset / sizeof(ffi_arg); arg_offset = arg_offset % sizeof(ffi_arg); argp = (char *)(ar + argn); fpp = (char *)(argn >= 8 ? ar + argn : fpr + argn); tp = target + offset; if (elt_type->type == FFI_TYPE_DOUBLE && !soft_float) *(double *)tp = *(double *)fpp; else memcpy(tp, argp + arg_offset, elt_type->size); offset += elt_type->size; arg_offset += elt_type->size; elt_typep++; argn += arg_offset / sizeof(ffi_arg); arg_offset = arg_offset % sizeof(ffi_arg); } } /* * Decodes the arguments to a function, which will be stored on the * stack. AR is the pointer to the beginning of the integer * arguments. FPR is a pointer to the area where floating point * registers have been saved. * * RVALUE is the location where the function return value will be * stored. CLOSURE is the prepared closure to invoke. * * This function should only be called from assembly, which is in * turn called from a trampoline. * * Returns the function return flags. * */ int ffi_closure_mips_inner_N32 (ffi_closure *closure, void *rvalue, ffi_arg *ar, ffi_arg *fpr) { ffi_cif *cif; void **avaluep; ffi_arg *avalue; ffi_type **arg_types; int i, avn, argn; int soft_float; ffi_arg *argp; cif = closure->cif; soft_float = cif->abi == FFI_N64_SOFT_FLOAT || cif->abi == FFI_N32_SOFT_FLOAT; avalue = alloca (cif->nargs * sizeof (ffi_arg)); avaluep = alloca (cif->nargs * sizeof (ffi_arg)); argn = 0; if (cif->rstruct_flag) { #if _MIPS_SIM==_ABIN32 rvalue = (void *)(UINT32)ar[0]; #else /* N64 */ rvalue = (void *)ar[0]; #endif argn = 1; } i = 0; avn = cif->nargs; arg_types = cif->arg_types; while (i < avn) { if (arg_types[i]->type == FFI_TYPE_FLOAT || arg_types[i]->type == FFI_TYPE_DOUBLE || arg_types[i]->type == FFI_TYPE_LONGDOUBLE) { argp = (argn >= 8 || soft_float) ? ar + argn : fpr + argn; if ((arg_types[i]->type == FFI_TYPE_LONGDOUBLE) && ((unsigned)argp & (arg_types[i]->alignment-1))) { argp=(ffi_arg*)ALIGN(argp,arg_types[i]->alignment); argn++; } #if defined(__MIPSEB__) || defined(_MIPSEB) if (arg_types[i]->type == FFI_TYPE_FLOAT && argn < 8) avaluep[i] = ((char *) argp) + sizeof (float); else #endif avaluep[i] = (char *) argp; } else { unsigned type = arg_types[i]->type; if (arg_types[i]->alignment > sizeof(ffi_arg)) argn = ALIGN(argn, arg_types[i]->alignment / sizeof(ffi_arg)); argp = ar + argn; /* The size of a pointer depends on the ABI */ if (type == FFI_TYPE_POINTER) type = (cif->abi == FFI_N64 || cif->abi == FFI_N64_SOFT_FLOAT) ? FFI_TYPE_SINT64 : FFI_TYPE_SINT32; if (soft_float && type == FFI_TYPE_FLOAT) type = FFI_TYPE_UINT32; switch (type) { case FFI_TYPE_SINT8: avaluep[i] = &avalue[i]; *(SINT8 *) &avalue[i] = (SINT8) *argp; break; case FFI_TYPE_UINT8: avaluep[i] = &avalue[i]; *(UINT8 *) &avalue[i] = (UINT8) *argp; break; case FFI_TYPE_SINT16: avaluep[i] = &avalue[i]; *(SINT16 *) &avalue[i] = (SINT16) *argp; break; case FFI_TYPE_UINT16: avaluep[i] = &avalue[i]; *(UINT16 *) &avalue[i] = (UINT16) *argp; break; case FFI_TYPE_SINT32: avaluep[i] = &avalue[i]; *(SINT32 *) &avalue[i] = (SINT32) *argp; break; case FFI_TYPE_UINT32: avaluep[i] = &avalue[i]; *(UINT32 *) &avalue[i] = (UINT32) *argp; break; case FFI_TYPE_STRUCT: if (argn < 8) { /* Allocate space for the struct as at least part of it was passed in registers. */ avaluep[i] = alloca(arg_types[i]->size); copy_struct_N32(avaluep[i], 0, cif->abi, arg_types[i], argn, 0, ar, fpr, soft_float); break; } /* Else fall through. */ default: avaluep[i] = (char *) argp; break; } } argn += ALIGN(arg_types[i]->size, sizeof(ffi_arg)) / sizeof(ffi_arg); i++; } /* Invoke the closure. */ (closure->fun) (cif, rvalue, avaluep, closure->user_data); return cif->flags >> (FFI_FLAG_BITS * 8); } #endif /* FFI_MIPS_N32 */ #endif /* FFI_CLOSURES */ smalltalk-3.2.5/libffi/src/java_raw_api.c0000644000175000017500000002043112130343734015237 00000000000000/* ----------------------------------------------------------------------- java_raw_api.c - Copyright (c) 1999, 2007, 2008 Red Hat, Inc. Cloned from raw_api.c Raw_api.c author: Kresten Krab Thorup Java_raw_api.c author: Hans-J. Boehm $Id $ Permission is hereby granted, free of charge, to any person obtaining a copy of this software and associated documentation files (the ``Software''), to deal in the Software without restriction, including without limitation the rights to use, copy, modify, merge, publish, distribute, sublicense, and/or sell copies of the Software, and to permit persons to whom the Software is furnished to do so, subject to the following conditions: The above copyright notice and this permission notice shall be included in all copies or substantial portions of the Software. THE SOFTWARE IS PROVIDED ``AS IS'', WITHOUT WARRANTY OF ANY KIND, EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. ----------------------------------------------------------------------- */ /* This defines a Java- and 64-bit specific variant of the raw API. */ /* It assumes that "raw" argument blocks look like Java stacks on a */ /* 64-bit machine. Arguments that can be stored in a single stack */ /* stack slots (longs, doubles) occupy 128 bits, but only the first */ /* 64 bits are actually used. */ #include #include #include #if !defined(NO_JAVA_RAW_API) && !defined(FFI_NO_RAW_API) size_t ffi_java_raw_size (ffi_cif *cif) { size_t result = 0; int i; ffi_type **at = cif->arg_types; for (i = cif->nargs-1; i >= 0; i--, at++) { switch((*at) -> type) { case FFI_TYPE_UINT64: case FFI_TYPE_SINT64: case FFI_TYPE_DOUBLE: result += 2 * FFI_SIZEOF_JAVA_RAW; break; case FFI_TYPE_STRUCT: /* No structure parameters in Java. */ abort(); default: result += FFI_SIZEOF_JAVA_RAW; } } return result; } void ffi_java_raw_to_ptrarray (ffi_cif *cif, ffi_java_raw *raw, void **args) { unsigned i; ffi_type **tp = cif->arg_types; #if WORDS_BIGENDIAN for (i = 0; i < cif->nargs; i++, tp++, args++) { switch ((*tp)->type) { case FFI_TYPE_UINT8: case FFI_TYPE_SINT8: *args = (void*) ((char*)(raw++) + 3); break; case FFI_TYPE_UINT16: case FFI_TYPE_SINT16: *args = (void*) ((char*)(raw++) + 2); break; #if FFI_SIZEOF_JAVA_RAW == 8 case FFI_TYPE_UINT64: case FFI_TYPE_SINT64: case FFI_TYPE_DOUBLE: *args = (void *)raw; raw += 2; break; #endif case FFI_TYPE_POINTER: *args = (void*) &(raw++)->ptr; break; default: *args = raw; raw += ALIGN ((*tp)->size, sizeof(ffi_java_raw)) / sizeof(ffi_java_raw); } } #else /* WORDS_BIGENDIAN */ #if !PDP /* then assume little endian */ for (i = 0; i < cif->nargs; i++, tp++, args++) { #if FFI_SIZEOF_JAVA_RAW == 8 switch((*tp)->type) { case FFI_TYPE_UINT64: case FFI_TYPE_SINT64: case FFI_TYPE_DOUBLE: *args = (void*) raw; raw += 2; break; default: *args = (void*) raw++; } #else /* FFI_SIZEOF_JAVA_RAW != 8 */ *args = (void*) raw; raw += ALIGN ((*tp)->size, sizeof(ffi_java_raw)) / sizeof(ffi_java_raw); #endif /* FFI_SIZEOF_JAVA_RAW == 8 */ } #else #error "pdp endian not supported" #endif /* ! PDP */ #endif /* WORDS_BIGENDIAN */ } void ffi_java_ptrarray_to_raw (ffi_cif *cif, void **args, ffi_java_raw *raw) { unsigned i; ffi_type **tp = cif->arg_types; for (i = 0; i < cif->nargs; i++, tp++, args++) { switch ((*tp)->type) { case FFI_TYPE_UINT8: #if WORDS_BIGENDIAN *(UINT32*)(raw++) = *(UINT8*) (*args); #else (raw++)->uint = *(UINT8*) (*args); #endif break; case FFI_TYPE_SINT8: #if WORDS_BIGENDIAN *(SINT32*)(raw++) = *(SINT8*) (*args); #else (raw++)->sint = *(SINT8*) (*args); #endif break; case FFI_TYPE_UINT16: #if WORDS_BIGENDIAN *(UINT32*)(raw++) = *(UINT16*) (*args); #else (raw++)->uint = *(UINT16*) (*args); #endif break; case FFI_TYPE_SINT16: #if WORDS_BIGENDIAN *(SINT32*)(raw++) = *(SINT16*) (*args); #else (raw++)->sint = *(SINT16*) (*args); #endif break; case FFI_TYPE_UINT32: #if WORDS_BIGENDIAN *(UINT32*)(raw++) = *(UINT32*) (*args); #else (raw++)->uint = *(UINT32*) (*args); #endif break; case FFI_TYPE_SINT32: #if WORDS_BIGENDIAN *(SINT32*)(raw++) = *(SINT32*) (*args); #else (raw++)->sint = *(SINT32*) (*args); #endif break; case FFI_TYPE_FLOAT: (raw++)->flt = *(FLOAT32*) (*args); break; #if FFI_SIZEOF_JAVA_RAW == 8 case FFI_TYPE_UINT64: case FFI_TYPE_SINT64: case FFI_TYPE_DOUBLE: raw->uint = *(UINT64*) (*args); raw += 2; break; #endif case FFI_TYPE_POINTER: (raw++)->ptr = **(void***) args; break; default: #if FFI_SIZEOF_JAVA_RAW == 8 FFI_ASSERT(0); /* Should have covered all cases */ #else memcpy ((void*) raw->data, (void*)*args, (*tp)->size); raw += ALIGN ((*tp)->size, sizeof(ffi_java_raw)) / sizeof(ffi_java_raw); #endif } } } #if !FFI_NATIVE_RAW_API static void ffi_java_rvalue_to_raw (ffi_cif *cif, void *rvalue) { #if WORDS_BIGENDIAN && FFI_SIZEOF_ARG == 8 switch (cif->rtype->type) { case FFI_TYPE_UINT8: case FFI_TYPE_UINT16: case FFI_TYPE_UINT32: *(UINT64 *)rvalue <<= 32; break; case FFI_TYPE_SINT8: case FFI_TYPE_SINT16: case FFI_TYPE_SINT32: case FFI_TYPE_INT: #if FFI_SIZEOF_JAVA_RAW == 4 case FFI_TYPE_POINTER: #endif *(SINT64 *)rvalue <<= 32; break; default: break; } #endif } static void ffi_java_raw_to_rvalue (ffi_cif *cif, void *rvalue) { #if WORDS_BIGENDIAN && FFI_SIZEOF_ARG == 8 switch (cif->rtype->type) { case FFI_TYPE_UINT8: case FFI_TYPE_UINT16: case FFI_TYPE_UINT32: *(UINT64 *)rvalue >>= 32; break; case FFI_TYPE_SINT8: case FFI_TYPE_SINT16: case FFI_TYPE_SINT32: case FFI_TYPE_INT: *(SINT64 *)rvalue >>= 32; break; default: break; } #endif } /* This is a generic definition of ffi_raw_call, to be used if the * native system does not provide a machine-specific implementation. * Having this, allows code to be written for the raw API, without * the need for system-specific code to handle input in that format; * these following couple of functions will handle the translation forth * and back automatically. */ void ffi_java_raw_call (ffi_cif *cif, void (*fn)(void), void *rvalue, ffi_java_raw *raw) { void **avalue = (void**) alloca (cif->nargs * sizeof (void*)); ffi_java_raw_to_ptrarray (cif, raw, avalue); ffi_call (cif, fn, rvalue, avalue); ffi_java_rvalue_to_raw (cif, rvalue); } #if FFI_CLOSURES /* base system provides closures */ static void ffi_java_translate_args (ffi_cif *cif, void *rvalue, void **avalue, void *user_data) { ffi_java_raw *raw = (ffi_java_raw*)alloca (ffi_java_raw_size (cif)); ffi_raw_closure *cl = (ffi_raw_closure*)user_data; ffi_java_ptrarray_to_raw (cif, avalue, raw); (*cl->fun) (cif, rvalue, raw, cl->user_data); ffi_java_raw_to_rvalue (cif, rvalue); } ffi_status ffi_prep_java_raw_closure_loc (ffi_java_raw_closure* cl, ffi_cif *cif, void (*fun)(ffi_cif*,void*,ffi_java_raw*,void*), void *user_data, void *codeloc) { ffi_status status; status = ffi_prep_closure_loc ((ffi_closure*) cl, cif, &ffi_java_translate_args, codeloc, codeloc); if (status == FFI_OK) { cl->fun = fun; cl->user_data = user_data; } return status; } /* Again, here is the generic version of ffi_prep_raw_closure, which * will install an intermediate "hub" for translation of arguments from * the pointer-array format, to the raw format */ ffi_status ffi_prep_java_raw_closure (ffi_java_raw_closure* cl, ffi_cif *cif, void (*fun)(ffi_cif*,void*,ffi_java_raw*,void*), void *user_data) { return ffi_prep_java_raw_closure_loc (cl, cif, fun, user_data, cl); } #endif /* FFI_CLOSURES */ #endif /* !FFI_NATIVE_RAW_API */ #endif /* !FFI_NO_RAW_API */ smalltalk-3.2.5/libffi/src/m68k/0000755000175000017500000000000012130456004013310 500000000000000smalltalk-3.2.5/libffi/src/m68k/ffitarget.h0000644000175000017500000000341312130343734015362 00000000000000/* -----------------------------------------------------------------*-C-*- ffitarget.h - Copyright (c) 1996-2003 Red Hat, Inc. Target configuration macros for Motorola 68K. Permission is hereby granted, free of charge, to any person obtaining a copy of this software and associated documentation files (the ``Software''), to deal in the Software without restriction, including without limitation the rights to use, copy, modify, merge, publish, distribute, sublicense, and/or sell copies of the Software, and to permit persons to whom the Software is furnished to do so, subject to the following conditions: The above copyright notice and this permission notice shall be included in all copies or substantial portions of the Software. THE SOFTWARE IS PROVIDED ``AS IS'', WITHOUT WARRANTY OF ANY KIND, EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. ----------------------------------------------------------------------- */ #ifndef LIBFFI_TARGET_H #define LIBFFI_TARGET_H #ifndef LIBFFI_ASM typedef unsigned long ffi_arg; typedef signed long ffi_sarg; typedef enum ffi_abi { FFI_FIRST_ABI = 0, FFI_SYSV, FFI_DEFAULT_ABI = FFI_SYSV, FFI_LAST_ABI = FFI_DEFAULT_ABI + 1 } ffi_abi; #endif /* ---- Definitions for closures ----------------------------------------- */ #define FFI_CLOSURES 1 #define FFI_TRAMPOLINE_SIZE 16 #define FFI_NATIVE_RAW_API 0 #endif smalltalk-3.2.5/libffi/src/m68k/sysv.S0000644000175000017500000001130012130343734014360 00000000000000/* ----------------------------------------------------------------------- sysv.S - Copyright (c) 1998 Andreas Schwab Copyright (c) 2008 Red Hat, Inc. m68k Foreign Function Interface Permission is hereby granted, free of charge, to any person obtaining a copy of this software and associated documentation files (the ``Software''), to deal in the Software without restriction, including without limitation the rights to use, copy, modify, merge, publish, distribute, sublicense, and/or sell copies of the Software, and to permit persons to whom the Software is furnished to do so, subject to the following conditions: The above copyright notice and this permission notice shall be included in all copies or substantial portions of the Software. THE SOFTWARE IS PROVIDED ``AS IS'', WITHOUT WARRANTY OF ANY KIND, EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. ----------------------------------------------------------------------- */ #define LIBFFI_ASM #include #include #ifdef HAVE_AS_CFI_PSEUDO_OP #define CFI_STARTPROC() .cfi_startproc #define CFI_OFFSET(reg,off) .cfi_offset reg,off #define CFI_DEF_CFA(reg,off) .cfi_def_cfa reg,off #define CFI_ENDPROC() .cfi_endproc #else #define CFI_STARTPROC() #define CFI_OFFSET(reg,off) #define CFI_DEF_CFA(reg,off) #define CFI_ENDPROC() #endif .text .globl ffi_call_SYSV .type ffi_call_SYSV,@function .align 4 ffi_call_SYSV: CFI_STARTPROC() link %fp,#0 CFI_OFFSET(14,-8) CFI_DEF_CFA(14,8) move.l %d2,-(%sp) CFI_OFFSET(2,-12) | Make room for all of the new args. sub.l 12(%fp),%sp | Call ffi_prep_args move.l 8(%fp),-(%sp) pea 4(%sp) #if !defined __PIC__ jsr ffi_prep_args #else bsr.l ffi_prep_args@PLTPC #endif addq.l #8,%sp | Pass pointer to struct value, if any move.l %a0,%a1 | Call the function move.l 24(%fp),%a0 jsr (%a0) | Remove the space we pushed for the args add.l 12(%fp),%sp | Load the pointer to storage for the return value move.l 20(%fp),%a1 | Load the return type code move.l 16(%fp),%d2 | If the return value pointer is NULL, assume no return value. tst.l %a1 jbeq noretval btst #0,%d2 jbeq retlongint move.l %d0,(%a1) jbra epilogue retlongint: btst #1,%d2 jbeq retfloat move.l %d0,(%a1) move.l %d1,4(%a1) jbra epilogue retfloat: btst #2,%d2 jbeq retdouble fmove.s %fp0,(%a1) jbra epilogue retdouble: btst #3,%d2 jbeq retlongdouble fmove.d %fp0,(%a1) jbra epilogue retlongdouble: btst #4,%d2 jbeq retpointer fmove.x %fp0,(%a1) jbra epilogue retpointer: btst #5,%d2 jbeq retstruct1 move.l %a0,(%a1) jbra epilogue retstruct1: btst #6,%d2 jbeq retstruct2 move.b %d0,(%a1) jbra epilogue retstruct2: btst #7,%d2 jbeq noretval move.w %d0,(%a1) noretval: epilogue: move.l (%sp)+,%d2 unlk %fp rts CFI_ENDPROC() .size ffi_call_SYSV,.-ffi_call_SYSV .globl ffi_closure_SYSV .type ffi_closure_SYSV, @function .align 4 ffi_closure_SYSV: CFI_STARTPROC() link %fp,#-12 CFI_OFFSET(14,-8) CFI_DEF_CFA(14,8) move.l %sp,-12(%fp) pea 8(%fp) pea -12(%fp) move.l %a0,-(%sp) #if !defined __PIC__ jsr ffi_closure_SYSV_inner #else bsr.l ffi_closure_SYSV_inner@PLTPC #endif lsr.l #1,%d0 jne 1f jcc .Lcls_epilogue move.l -12(%fp),%d0 .Lcls_epilogue: unlk %fp rts 1: lea -12(%fp),%a0 lsr.l #2,%d0 jne 1f jcs .Lcls_ret_float move.l (%a0)+,%d0 move.l (%a0),%d1 jra .Lcls_epilogue .Lcls_ret_float: fmove.s (%a0),%fp0 jra .Lcls_epilogue 1: lsr.l #2,%d0 jne 1f jcs .Lcls_ret_ldouble fmove.d (%a0),%fp0 jra .Lcls_epilogue .Lcls_ret_ldouble: fmove.x (%a0),%fp0 jra .Lcls_epilogue 1: lsr.l #2,%d0 jne .Lcls_ret_struct2 jcs .Lcls_ret_struct1 move.l (%a0),%a0 move.l %a0,%d0 jra .Lcls_epilogue .Lcls_ret_struct1: move.b (%a0),%d0 jra .Lcls_epilogue .Lcls_ret_struct2: move.w (%a0),%d0 jra .Lcls_epilogue CFI_ENDPROC() .size ffi_closure_SYSV,.-ffi_closure_SYSV .globl ffi_closure_struct_SYSV .type ffi_closure_struct_SYSV, @function .align 4 ffi_closure_struct_SYSV: CFI_STARTPROC() link %fp,#0 CFI_OFFSET(14,-8) CFI_DEF_CFA(14,8) move.l %sp,-12(%fp) pea 8(%fp) move.l %a1,-(%sp) move.l %a0,-(%sp) #if !defined __PIC__ jsr ffi_closure_SYSV_inner #else bsr.l ffi_closure_SYSV_inner@PLTPC #endif unlk %fp rts CFI_ENDPROC() .size ffi_closure_struct_SYSV,.-ffi_closure_struct_SYSV #if defined __ELF__ && defined __linux__ .section .note.GNU-stack,"",@progbits #endif smalltalk-3.2.5/libffi/src/m68k/ffi.c0000644000175000017500000001307312130343734014151 00000000000000/* ----------------------------------------------------------------------- ffi.c m68k Foreign Function Interface ----------------------------------------------------------------------- */ #include #include #include #include #include #include void ffi_call_SYSV (extended_cif *, unsigned, unsigned, void *, void (*fn) ()); void *ffi_prep_args (void *stack, extended_cif *ecif); void ffi_closure_SYSV (ffi_closure *); void ffi_closure_struct_SYSV (ffi_closure *); unsigned int ffi_closure_SYSV_inner (ffi_closure *closure, void *resp, void *args); /* ffi_prep_args is called by the assembly routine once stack space has been allocated for the function's arguments. */ void * ffi_prep_args (void *stack, extended_cif *ecif) { unsigned int i; void **p_argv; char *argp; ffi_type **p_arg; void *struct_value_ptr; argp = stack; if (ecif->cif->rtype->type == FFI_TYPE_STRUCT && !ecif->cif->flags) struct_value_ptr = ecif->rvalue; else struct_value_ptr = NULL; p_argv = ecif->avalue; for (i = ecif->cif->nargs, p_arg = ecif->cif->arg_types; i != 0; i--, p_arg++) { size_t z; z = (*p_arg)->size; if (z < sizeof (int)) { switch ((*p_arg)->type) { case FFI_TYPE_SINT8: *(signed int *) argp = (signed int) *(SINT8 *) *p_argv; break; case FFI_TYPE_UINT8: *(unsigned int *) argp = (unsigned int) *(UINT8 *) *p_argv; break; case FFI_TYPE_SINT16: *(signed int *) argp = (signed int) *(SINT16 *) *p_argv; break; case FFI_TYPE_UINT16: *(unsigned int *) argp = (unsigned int) *(UINT16 *) *p_argv; break; case FFI_TYPE_STRUCT: memcpy (argp + sizeof (int) - z, *p_argv, z); break; default: FFI_ASSERT (0); } z = sizeof (int); } else { memcpy (argp, *p_argv, z); /* Align if necessary. */ if ((sizeof(int) - 1) & z) z = ALIGN(z, sizeof(int)); } p_argv++; argp += z; } return struct_value_ptr; } #define CIF_FLAGS_INT 1 #define CIF_FLAGS_DINT 2 #define CIF_FLAGS_FLOAT 4 #define CIF_FLAGS_DOUBLE 8 #define CIF_FLAGS_LDOUBLE 16 #define CIF_FLAGS_POINTER 32 #define CIF_FLAGS_STRUCT1 64 #define CIF_FLAGS_STRUCT2 128 /* Perform machine dependent cif processing */ ffi_status ffi_prep_cif_machdep (ffi_cif *cif) { /* Set the return type flag */ switch (cif->rtype->type) { case FFI_TYPE_VOID: cif->flags = 0; break; case FFI_TYPE_STRUCT: switch (cif->rtype->size) { case 1: cif->flags = CIF_FLAGS_STRUCT1; break; case 2: cif->flags = CIF_FLAGS_STRUCT2; break; case 4: cif->flags = CIF_FLAGS_INT; break; case 8: cif->flags = CIF_FLAGS_DINT; break; default: cif->flags = 0; break; } break; case FFI_TYPE_FLOAT: cif->flags = CIF_FLAGS_FLOAT; break; case FFI_TYPE_DOUBLE: cif->flags = CIF_FLAGS_DOUBLE; break; case FFI_TYPE_LONGDOUBLE: cif->flags = CIF_FLAGS_LDOUBLE; break; case FFI_TYPE_POINTER: cif->flags = CIF_FLAGS_POINTER; break; case FFI_TYPE_SINT64: case FFI_TYPE_UINT64: cif->flags = CIF_FLAGS_DINT; break; default: cif->flags = CIF_FLAGS_INT; break; } return FFI_OK; } void ffi_call (ffi_cif *cif, void (*fn) (), void *rvalue, void **avalue) { extended_cif ecif; ecif.cif = cif; ecif.avalue = avalue; /* If the return value is a struct and we don't have a return value address then we need to make one. */ if (rvalue == NULL && cif->rtype->type == FFI_TYPE_STRUCT && cif->rtype->size > 8) ecif.rvalue = alloca (cif->rtype->size); else ecif.rvalue = rvalue; switch (cif->abi) { case FFI_SYSV: ffi_call_SYSV (&ecif, cif->bytes, cif->flags, ecif.rvalue, fn); break; default: FFI_ASSERT (0); break; } } static void ffi_prep_incoming_args_SYSV (char *stack, void **avalue, ffi_cif *cif) { unsigned int i; void **p_argv; char *argp; ffi_type **p_arg; argp = stack; p_argv = avalue; for (i = cif->nargs, p_arg = cif->arg_types; (i != 0); i--, p_arg++) { size_t z; z = (*p_arg)->size; if (z <= 4) { *p_argv = (void *) (argp + 4 - z); z = 4; } else { *p_argv = (void *) argp; /* Align if necessary */ if ((sizeof(int) - 1) & z) z = ALIGN(z, sizeof(int)); } p_argv++; argp += z; } } unsigned int ffi_closure_SYSV_inner (ffi_closure *closure, void *resp, void *args) { ffi_cif *cif; void **arg_area; cif = closure->cif; arg_area = (void**) alloca (cif->nargs * sizeof (void *)); ffi_prep_incoming_args_SYSV(args, arg_area, cif); (closure->fun) (cif, resp, arg_area, closure->user_data); return cif->flags; } ffi_status ffi_prep_closure_loc (ffi_closure* closure, ffi_cif* cif, void (*fun)(ffi_cif*,void*,void**,void*), void *user_data, void *codeloc) { FFI_ASSERT (cif->abi == FFI_SYSV); *(unsigned short *)closure->tramp = 0x207c; *(void **)(closure->tramp + 2) = codeloc; *(unsigned short *)(closure->tramp + 6) = 0x4ef9; if (cif->rtype->type == FFI_TYPE_STRUCT && !cif->flags) *(void **)(closure->tramp + 8) = ffi_closure_struct_SYSV; else *(void **)(closure->tramp + 8) = ffi_closure_SYSV; syscall(SYS_cacheflush, codeloc, FLUSH_SCOPE_LINE, FLUSH_CACHE_BOTH, FFI_TRAMPOLINE_SIZE); closure->cif = cif; closure->user_data = user_data; closure->fun = fun; return FFI_OK; } smalltalk-3.2.5/libffi/src/prep_cif.c0000644000175000017500000001227312130343734014410 00000000000000/* ----------------------------------------------------------------------- prep_cif.c - Copyright (c) 1996, 1998, 2007 Red Hat, Inc. Permission is hereby granted, free of charge, to any person obtaining a copy of this software and associated documentation files (the ``Software''), to deal in the Software without restriction, including without limitation the rights to use, copy, modify, merge, publish, distribute, sublicense, and/or sell copies of the Software, and to permit persons to whom the Software is furnished to do so, subject to the following conditions: The above copyright notice and this permission notice shall be included in all copies or substantial portions of the Software. THE SOFTWARE IS PROVIDED ``AS IS'', WITHOUT WARRANTY OF ANY KIND, EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. ----------------------------------------------------------------------- */ #include #include #include /* Round up to FFI_SIZEOF_ARG. */ #define STACK_ARG_SIZE(x) ALIGN(x, FFI_SIZEOF_ARG) /* Perform machine independent initialization of aggregate type specifications. */ static ffi_status initialize_aggregate(ffi_type *arg) { ffi_type **ptr; FFI_ASSERT(arg != NULL); FFI_ASSERT(arg->elements != NULL); FFI_ASSERT(arg->size == 0); FFI_ASSERT(arg->alignment == 0); ptr = &(arg->elements[0]); while ((*ptr) != NULL) { if (((*ptr)->size == 0) && (initialize_aggregate((*ptr)) != FFI_OK)) return FFI_BAD_TYPEDEF; /* Perform a sanity check on the argument type */ FFI_ASSERT_VALID_TYPE(*ptr); arg->size = ALIGN(arg->size, (*ptr)->alignment); arg->size += (*ptr)->size; arg->alignment = (arg->alignment > (*ptr)->alignment) ? arg->alignment : (*ptr)->alignment; ptr++; } /* Structure size includes tail padding. This is important for structures that fit in one register on ABIs like the PowerPC64 Linux ABI that right justify small structs in a register. It's also needed for nested structure layout, for example struct A { long a; char b; }; struct B { struct A x; char y; }; should find y at an offset of 2*sizeof(long) and result in a total size of 3*sizeof(long). */ arg->size = ALIGN (arg->size, arg->alignment); if (arg->size == 0) return FFI_BAD_TYPEDEF; else return FFI_OK; } #ifndef __CRIS__ /* The CRIS ABI specifies structure elements to have byte alignment only, so it completely overrides this functions, which assumes "natural" alignment and padding. */ /* Perform machine independent ffi_cif preparation, then call machine dependent routine. */ ffi_status ffi_prep_cif(ffi_cif *cif, ffi_abi abi, unsigned int nargs, ffi_type *rtype, ffi_type **atypes) { unsigned bytes = 0; unsigned int i; ffi_type **ptr; FFI_ASSERT(cif != NULL); FFI_ASSERT((abi > FFI_FIRST_ABI) && (abi <= FFI_DEFAULT_ABI)); cif->abi = abi; cif->arg_types = atypes; cif->nargs = nargs; cif->rtype = rtype; cif->flags = 0; /* Initialize the return type if necessary */ if ((cif->rtype->size == 0) && (initialize_aggregate(cif->rtype) != FFI_OK)) return FFI_BAD_TYPEDEF; /* Perform a sanity check on the return type */ FFI_ASSERT_VALID_TYPE(cif->rtype); /* x86, x86-64 and s390 stack space allocation is handled in prep_machdep. */ #if !defined M68K && !defined __i386__ && !defined __x86_64__ && !defined S390 && !defined PA /* Make space for the return structure pointer */ if (cif->rtype->type == FFI_TYPE_STRUCT #ifdef SPARC && (cif->abi != FFI_V9 || cif->rtype->size > 32) #endif ) bytes = STACK_ARG_SIZE(sizeof(void*)); #endif for (ptr = cif->arg_types, i = cif->nargs; i > 0; i--, ptr++) { /* Initialize any uninitialized aggregate type definitions */ if (((*ptr)->size == 0) && (initialize_aggregate((*ptr)) != FFI_OK)) return FFI_BAD_TYPEDEF; /* Perform a sanity check on the argument type, do this check after the initialization. */ FFI_ASSERT_VALID_TYPE(*ptr); #if !defined __i386__ && !defined __x86_64__ && !defined S390 && !defined PA #ifdef SPARC if (((*ptr)->type == FFI_TYPE_STRUCT && ((*ptr)->size > 16 || cif->abi != FFI_V9)) || ((*ptr)->type == FFI_TYPE_LONGDOUBLE && cif->abi != FFI_V9)) bytes += sizeof(void*); else #endif { /* Add any padding if necessary */ if (((*ptr)->alignment - 1) & bytes) bytes = ALIGN(bytes, (*ptr)->alignment); bytes += STACK_ARG_SIZE((*ptr)->size); } #endif } cif->bytes = bytes; /* Perform machine dependent cif processing */ return ffi_prep_cif_machdep(cif); } #endif /* not __CRIS__ */ #if FFI_CLOSURES ffi_status ffi_prep_closure (ffi_closure* closure, ffi_cif* cif, void (*fun)(ffi_cif*,void*,void**,void*), void *user_data) { return ffi_prep_closure_loc (closure, cif, fun, user_data, closure); } #endif smalltalk-3.2.5/libffi/src/sh64/0000755000175000017500000000000012130456004013307 500000000000000smalltalk-3.2.5/libffi/src/sh64/ffitarget.h0000644000175000017500000000361512130343734015365 00000000000000/* -----------------------------------------------------------------*-C-*- ffitarget.h - Copyright (c) 1996-2003 Red Hat, Inc. Target configuration macros for SuperH - SHmedia. Permission is hereby granted, free of charge, to any person obtaining a copy of this software and associated documentation files (the ``Software''), to deal in the Software without restriction, including without limitation the rights to use, copy, modify, merge, publish, distribute, sublicense, and/or sell copies of the Software, and to permit persons to whom the Software is furnished to do so, subject to the following conditions: The above copyright notice and this permission notice shall be included in all copies or substantial portions of the Software. THE SOFTWARE IS PROVIDED ``AS IS'', WITHOUT WARRANTY OF ANY KIND, EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. ----------------------------------------------------------------------- */ #ifndef LIBFFI_TARGET_H #define LIBFFI_TARGET_H /* ---- Generic type definitions ----------------------------------------- */ #ifndef LIBFFI_ASM typedef unsigned long ffi_arg; typedef signed long ffi_sarg; typedef enum ffi_abi { FFI_FIRST_ABI = 0, FFI_SYSV, FFI_DEFAULT_ABI = FFI_SYSV, FFI_LAST_ABI = FFI_DEFAULT_ABI + 1 } ffi_abi; #define FFI_EXTRA_CIF_FIELDS long long flags2 #endif /* ---- Definitions for closures ----------------------------------------- */ #define FFI_CLOSURES 1 #define FFI_TRAMPOLINE_SIZE 32 #define FFI_NATIVE_RAW_API 0 #endif smalltalk-3.2.5/libffi/src/sh64/sysv.S0000644000175000017500000002665512130343734014402 00000000000000/* ----------------------------------------------------------------------- sysv.S - Copyright (c) 2003, 2004, 2006, 2008 Kaz Kojima SuperH SHmedia Foreign Function Interface Permission is hereby granted, free of charge, to any person obtaining a copy of this software and associated documentation files (the ``Software''), to deal in the Software without restriction, including without limitation the rights to use, copy, modify, merge, publish, distribute, sublicense, and/or sell copies of the Software, and to permit persons to whom the Software is furnished to do so, subject to the following conditions: The above copyright notice and this permission notice shall be included in all copies or substantial portions of the Software. THE SOFTWARE IS PROVIDED ``AS IS'', WITHOUT WARRANTY OF ANY KIND, EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. ----------------------------------------------------------------------- */ #define LIBFFI_ASM #include #include #ifdef HAVE_MACHINE_ASM_H #include #else /* XXX these lose for some platforms, I'm sure. */ #define CNAME(x) x #define ENTRY(x) .globl CNAME(x); .type CNAME(x),%function; CNAME(x): #endif #ifdef __LITTLE_ENDIAN__ #define OFS_FLT 0 #else #define OFS_FLT 4 #endif .section .text..SHmedia32,"ax" # r2: ffi_prep_args # r3: &ecif # r4: bytes # r5: flags # r6: flags2 # r7: rvalue # r8: fn # This assumes we are using gas. .align 5 ENTRY(ffi_call_SYSV) # Save registers .LFB1: addi.l r15, -48, r15 .LCFI0: st.q r15, 40, r32 st.q r15, 32, r31 st.q r15, 24, r30 st.q r15, 16, r29 st.q r15, 8, r28 st.l r15, 4, r18 st.l r15, 0, r14 .LCFI1: add.l r15, r63, r14 .LCFI2: # add r4, r63, r28 add r5, r63, r29 add r6, r63, r30 add r7, r63, r31 add r8, r63, r32 addi r4, (64 + 7), r4 andi r4, ~7, r4 sub.l r15, r4, r15 ptabs/l r2, tr0 add r15, r63, r2 blink tr0, r18 addi r15, 64, r22 movi 0, r0 movi 0, r1 movi -1, r23 pt/l 1f, tr1 bnei/l r29, FFI_TYPE_STRUCT, tr1 ld.l r15, 0, r19 addi r15, 8, r15 addi r0, 1, r0 1: .L_pass: andi r30, 3, r20 shlri r30, 2, r30 pt/l .L_call_it, tr0 pt/l .L_pass_i, tr1 pt/l .L_pass_f, tr2 beqi/l r20, FFI_TYPE_VOID, tr0 beqi/l r20, FFI_TYPE_INT, tr1 beqi/l r20, FFI_TYPE_FLOAT, tr2 .L_pass_d: addi r0, 1, r0 pt/l 3f, tr0 movi 12, r20 bge/l r1, r20, tr0 pt/l .L_pop_d, tr1 pt/l 2f, tr0 blink tr1, r63 2: addi.l r15, 8, r15 3: pt/l .L_pass, tr0 addi r1, 2, r1 blink tr0, r63 .L_pop_d: pt/l .L_pop_d_tbl, tr1 gettr tr1, r20 shlli r1, 2, r21 add r20, r21, r20 ptabs/l r20, tr1 blink tr1, r63 .L_pop_d_tbl: fld.d r15, 0, dr0 blink tr0, r63 fld.d r15, 0, dr2 blink tr0, r63 fld.d r15, 0, dr4 blink tr0, r63 fld.d r15, 0, dr6 blink tr0, r63 fld.d r15, 0, dr8 blink tr0, r63 fld.d r15, 0, dr10 blink tr0, r63 .L_pass_f: addi r0, 1, r0 pt/l 3f, tr0 movi 12, r20 bge/l r1, r20, tr0 pt/l .L_pop_f, tr1 pt/l 2f, tr0 blink tr1, r63 2: addi.l r15, 8, r15 3: pt/l .L_pass, tr0 blink tr0, r63 .L_pop_f: pt/l .L_pop_f_tbl, tr1 pt/l 5f, tr2 gettr tr1, r20 bge/l r23, r63, tr2 add r1, r63, r23 shlli r1, 3, r21 addi r1, 2, r1 add r20, r21, r20 ptabs/l r20, tr1 blink tr1, r63 5: addi r23, 1, r21 movi -1, r23 shlli r21, 3, r21 add r20, r21, r20 ptabs/l r20, tr1 blink tr1, r63 .L_pop_f_tbl: fld.s r15, OFS_FLT, fr0 blink tr0, r63 fld.s r15, OFS_FLT, fr1 blink tr0, r63 fld.s r15, OFS_FLT, fr2 blink tr0, r63 fld.s r15, OFS_FLT, fr3 blink tr0, r63 fld.s r15, OFS_FLT, fr4 blink tr0, r63 fld.s r15, OFS_FLT, fr5 blink tr0, r63 fld.s r15, OFS_FLT, fr6 blink tr0, r63 fld.s r15, OFS_FLT, fr7 blink tr0, r63 fld.s r15, OFS_FLT, fr8 blink tr0, r63 fld.s r15, OFS_FLT, fr9 blink tr0, r63 fld.s r15, OFS_FLT, fr10 blink tr0, r63 fld.s r15, OFS_FLT, fr11 blink tr0, r63 .L_pass_i: pt/l 3f, tr0 movi 8, r20 bge/l r0, r20, tr0 pt/l .L_pop_i, tr1 pt/l 2f, tr0 blink tr1, r63 2: addi.l r15, 8, r15 3: pt/l .L_pass, tr0 addi r0, 1, r0 blink tr0, r63 .L_pop_i: pt/l .L_pop_i_tbl, tr1 gettr tr1, r20 shlli r0, 3, r21 add r20, r21, r20 ptabs/l r20, tr1 blink tr1, r63 .L_pop_i_tbl: ld.q r15, 0, r2 blink tr0, r63 ld.q r15, 0, r3 blink tr0, r63 ld.q r15, 0, r4 blink tr0, r63 ld.q r15, 0, r5 blink tr0, r63 ld.q r15, 0, r6 blink tr0, r63 ld.q r15, 0, r7 blink tr0, r63 ld.q r15, 0, r8 blink tr0, r63 ld.q r15, 0, r9 blink tr0, r63 .L_call_it: # call function pt/l 1f, tr1 bnei/l r29, FFI_TYPE_STRUCT, tr1 add r19, r63, r2 1: add r22, r63, r15 ptabs/l r32, tr0 blink tr0, r18 pt/l .L_ret_i, tr0 pt/l .L_ret_ll, tr1 pt/l .L_ret_d, tr2 pt/l .L_ret_f, tr3 pt/l .L_epilogue, tr4 beqi/l r29, FFI_TYPE_INT, tr0 beqi/l r29, FFI_TYPE_UINT32, tr0 beqi/l r29, FFI_TYPE_SINT64, tr1 beqi/l r29, FFI_TYPE_UINT64, tr1 beqi/l r29, FFI_TYPE_DOUBLE, tr2 beqi/l r29, FFI_TYPE_FLOAT, tr3 pt/l .L_ret_q, tr0 pt/l .L_ret_h, tr1 beqi/l r29, FFI_TYPE_UINT8, tr0 beqi/l r29, FFI_TYPE_UINT16, tr1 blink tr4, r63 .L_ret_d: fst.d r31, 0, dr0 blink tr4, r63 .L_ret_ll: st.q r31, 0, r2 blink tr4, r63 .L_ret_f: fst.s r31, OFS_FLT, fr0 blink tr4, r63 .L_ret_q: st.b r31, 0, r2 blink tr4, r63 .L_ret_h: st.w r31, 0, r2 blink tr4, r63 .L_ret_i: st.l r31, 0, r2 # Fall .L_epilogue: # Remove the space we pushed for the args add r14, r63, r15 ld.l r15, 0, r14 ld.l r15, 4, r18 ld.q r15, 8, r28 ld.q r15, 16, r29 ld.q r15, 24, r30 ld.q r15, 32, r31 ld.q r15, 40, r32 addi.l r15, 48, r15 ptabs r18, tr0 blink tr0, r63 .LFE1: .ffi_call_SYSV_end: .size CNAME(ffi_call_SYSV),.ffi_call_SYSV_end-CNAME(ffi_call_SYSV) .align 5 ENTRY(ffi_closure_SYSV) .LFB2: addi.l r15, -136, r15 .LCFI3: st.l r15, 12, r18 st.l r15, 8, r14 st.l r15, 4, r12 .LCFI4: add r15, r63, r14 .LCFI5: /* Stack layout: ... 64 bytes (register parameters) 48 bytes (floating register parameters) 8 bytes (result) 4 bytes (r18) 4 bytes (r14) 4 bytes (r12) 4 bytes (for align) <- new stack pointer */ fst.d r14, 24, dr0 fst.d r14, 32, dr2 fst.d r14, 40, dr4 fst.d r14, 48, dr6 fst.d r14, 56, dr8 fst.d r14, 64, dr10 st.q r14, 72, r2 st.q r14, 80, r3 st.q r14, 88, r4 st.q r14, 96, r5 st.q r14, 104, r6 st.q r14, 112, r7 st.q r14, 120, r8 st.q r14, 128, r9 add r1, r63, r2 addi r14, 16, r3 addi r14, 72, r4 addi r14, 24, r5 addi r14, 136, r6 #ifdef PIC movi (((datalabel _GLOBAL_OFFSET_TABLE_-(.LPCS0-.)) >> 16) & 65535), r12 shori ((datalabel _GLOBAL_OFFSET_TABLE_-(.LPCS0-.)) & 65535), r12 .LPCS0: ptrel/u r12, tr0 movi ((ffi_closure_helper_SYSV@GOTPLT) & 65535), r1 gettr tr0, r12 ldx.l r1, r12, r1 ptabs r1, tr0 #else pt/l ffi_closure_helper_SYSV, tr0 #endif blink tr0, r18 shlli r2, 1, r1 movi (((datalabel .L_table) >> 16) & 65535), r2 shori ((datalabel .L_table) & 65535), r2 ldx.w r2, r1, r1 add r1, r2, r1 pt/l .L_case_v, tr1 ptabs r1, tr0 blink tr0, r63 .align 2 .L_table: .word .L_case_v - datalabel .L_table /* FFI_TYPE_VOID */ .word .L_case_i - datalabel .L_table /* FFI_TYPE_INT */ .word .L_case_f - datalabel .L_table /* FFI_TYPE_FLOAT */ .word .L_case_d - datalabel .L_table /* FFI_TYPE_DOUBLE */ .word .L_case_d - datalabel .L_table /* FFI_TYPE_LONGDOUBLE */ .word .L_case_uq - datalabel .L_table /* FFI_TYPE_UINT8 */ .word .L_case_q - datalabel .L_table /* FFI_TYPE_SINT8 */ .word .L_case_uh - datalabel .L_table /* FFI_TYPE_UINT16 */ .word .L_case_h - datalabel .L_table /* FFI_TYPE_SINT16 */ .word .L_case_i - datalabel .L_table /* FFI_TYPE_UINT32 */ .word .L_case_i - datalabel .L_table /* FFI_TYPE_SINT32 */ .word .L_case_ll - datalabel .L_table /* FFI_TYPE_UINT64 */ .word .L_case_ll - datalabel .L_table /* FFI_TYPE_SINT64 */ .word .L_case_v - datalabel .L_table /* FFI_TYPE_STRUCT */ .word .L_case_i - datalabel .L_table /* FFI_TYPE_POINTER */ .align 2 .L_case_d: fld.d r14, 16, dr0 blink tr1, r63 .L_case_f: fld.s r14, 16, fr0 blink tr1, r63 .L_case_ll: ld.q r14, 16, r2 blink tr1, r63 .L_case_i: ld.l r14, 16, r2 blink tr1, r63 .L_case_q: ld.b r14, 16, r2 blink tr1, r63 .L_case_uq: ld.ub r14, 16, r2 blink tr1, r63 .L_case_h: ld.w r14, 16, r2 blink tr1, r63 .L_case_uh: ld.uw r14, 16, r2 blink tr1, r63 .L_case_v: add.l r14, r63, r15 ld.l r15, 4, r12 ld.l r15, 8, r14 ld.l r15, 12, r18 addi.l r15, 136, r15 ptabs r18, tr0 blink tr0, r63 .LFE2: .ffi_closure_SYSV_end: .size CNAME(ffi_closure_SYSV),.ffi_closure_SYSV_end-CNAME(ffi_closure_SYSV) #if defined __ELF__ && defined __linux__ .section .note.GNU-stack,"",@progbits #endif .section ".eh_frame","aw",@progbits __FRAME_BEGIN__: .4byte .LECIE1-.LSCIE1 /* Length of Common Information Entry */ .LSCIE1: .4byte 0x0 /* CIE Identifier Tag */ .byte 0x1 /* CIE Version */ #ifdef PIC .ascii "zR\0" /* CIE Augmentation */ #else .byte 0x0 /* CIE Augmentation */ #endif .uleb128 0x1 /* CIE Code Alignment Factor */ .sleb128 -4 /* CIE Data Alignment Factor */ .byte 0x12 /* CIE RA Column */ #ifdef PIC .uleb128 0x1 /* Augmentation size */ .byte 0x10 /* FDE Encoding (pcrel) */ #endif .byte 0xc /* DW_CFA_def_cfa */ .uleb128 0xf .uleb128 0x0 .align 2 .LECIE1: .LSFDE1: .4byte datalabel .LEFDE1-datalabel .LASFDE1 /* FDE Length */ .LASFDE1: .4byte datalabel .LASFDE1-datalabel __FRAME_BEGIN__ #ifdef PIC .4byte .LFB1-. /* FDE initial location */ #else .4byte .LFB1 /* FDE initial location */ #endif .4byte datalabel .LFE1-datalabel .LFB1 /* FDE address range */ #ifdef PIC .uleb128 0x0 /* Augmentation size */ #endif .byte 0x4 /* DW_CFA_advance_loc4 */ .4byte datalabel .LCFI0-datalabel .LFB1 .byte 0xe /* DW_CFA_def_cfa_offset */ .uleb128 0x30 .byte 0x4 /* DW_CFA_advance_loc4 */ .4byte datalabel .LCFI1-datalabel .LCFI0 .byte 0x8e /* DW_CFA_offset, column 0xe */ .uleb128 0xc .byte 0x92 /* DW_CFA_offset, column 0x12 */ .uleb128 0xb .byte 0x9c /* DW_CFA_offset, column 0x1c */ .uleb128 0xa .byte 0x9d /* DW_CFA_offset, column 0x1d */ .uleb128 0x8 .byte 0x9e /* DW_CFA_offset, column 0x1e */ .uleb128 0x6 .byte 0x9f /* DW_CFA_offset, column 0x1f */ .uleb128 0x4 .byte 0xa0 /* DW_CFA_offset, column 0x20 */ .uleb128 0x2 .byte 0x4 /* DW_CFA_advance_loc4 */ .4byte datalabel .LCFI2-datalabel .LCFI1 .byte 0xd /* DW_CFA_def_cfa_register */ .uleb128 0xe .align 2 .LEFDE1: .LSFDE3: .4byte datalabel .LEFDE3-datalabel .LASFDE3 /* FDE Length */ .LASFDE3: .4byte datalabel .LASFDE3-datalabel __FRAME_BEGIN__ #ifdef PIC .4byte .LFB2-. /* FDE initial location */ #else .4byte .LFB2 /* FDE initial location */ #endif .4byte datalabel .LFE2-datalabel .LFB2 /* FDE address range */ #ifdef PIC .uleb128 0x0 /* Augmentation size */ #endif .byte 0x4 /* DW_CFA_advance_loc4 */ .4byte datalabel .LCFI3-datalabel .LFB2 .byte 0xe /* DW_CFA_def_cfa_offset */ .uleb128 0x88 .byte 0x4 /* DW_CFA_advance_loc4 */ .4byte datalabel .LCFI4-datalabel .LCFI3 .byte 0x8c /* DW_CFA_offset, column 0xc */ .uleb128 0x21 .byte 0x8e /* DW_CFA_offset, column 0xe */ .uleb128 0x20 .byte 0x92 /* DW_CFA_offset, column 0x12 */ .uleb128 0x1f .byte 0x4 /* DW_CFA_advance_loc4 */ .4byte datalabel .LCFI5-datalabel .LCFI4 .byte 0xd /* DW_CFA_def_cfa_register */ .uleb128 0xe .align 2 .LEFDE3: smalltalk-3.2.5/libffi/src/sh64/ffi.c0000644000175000017500000002602712130343734014153 00000000000000/* ----------------------------------------------------------------------- ffi.c - Copyright (c) 2003, 2004, 2006, 2007 Kaz Kojima Copyright (c) 2008 Anthony Green SuperH SHmedia Foreign Function Interface Permission is hereby granted, free of charge, to any person obtaining a copy of this software and associated documentation files (the ``Software''), to deal in the Software without restriction, including without limitation the rights to use, copy, modify, merge, publish, distribute, sublicense, and/or sell copies of the Software, and to permit persons to whom the Software is furnished to do so, subject to the following conditions: The above copyright notice and this permission notice shall be included in all copies or substantial portions of the Software. THE SOFTWARE IS PROVIDED ``AS IS'', WITHOUT WARRANTY OF ANY KIND, EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. ----------------------------------------------------------------------- */ #include #include #include #define NGREGARG 8 #define NFREGARG 12 static int return_type (ffi_type *arg) { if (arg->type != FFI_TYPE_STRUCT) return arg->type; /* gcc uses r2 if the result can be packed in on register. */ if (arg->size <= sizeof (UINT8)) return FFI_TYPE_UINT8; else if (arg->size <= sizeof (UINT16)) return FFI_TYPE_UINT16; else if (arg->size <= sizeof (UINT32)) return FFI_TYPE_UINT32; else if (arg->size <= sizeof (UINT64)) return FFI_TYPE_UINT64; return FFI_TYPE_STRUCT; } /* ffi_prep_args is called by the assembly routine once stack space has been allocated for the function's arguments */ void ffi_prep_args(char *stack, extended_cif *ecif) { register unsigned int i; register unsigned int avn; register void **p_argv; register char *argp; register ffi_type **p_arg; argp = stack; if (return_type (ecif->cif->rtype) == FFI_TYPE_STRUCT) { *(void **) argp = ecif->rvalue; argp += sizeof (UINT64); } avn = ecif->cif->nargs; p_argv = ecif->avalue; for (i = 0, p_arg = ecif->cif->arg_types; i < avn; i++, p_arg++, p_argv++) { size_t z; int align; z = (*p_arg)->size; align = (*p_arg)->alignment; if (z < sizeof (UINT32)) { switch ((*p_arg)->type) { case FFI_TYPE_SINT8: *(SINT64 *) argp = (SINT64) *(SINT8 *)(*p_argv); break; case FFI_TYPE_UINT8: *(UINT64 *) argp = (UINT64) *(UINT8 *)(*p_argv); break; case FFI_TYPE_SINT16: *(SINT64 *) argp = (SINT64) *(SINT16 *)(*p_argv); break; case FFI_TYPE_UINT16: *(UINT64 *) argp = (UINT64) *(UINT16 *)(*p_argv); break; case FFI_TYPE_STRUCT: memcpy (argp, *p_argv, z); break; default: FFI_ASSERT(0); } argp += sizeof (UINT64); } else if (z == sizeof (UINT32) && align == sizeof (UINT32)) { switch ((*p_arg)->type) { case FFI_TYPE_INT: case FFI_TYPE_SINT32: *(SINT64 *) argp = (SINT64) *(SINT32 *) (*p_argv); break; case FFI_TYPE_FLOAT: case FFI_TYPE_POINTER: case FFI_TYPE_UINT32: case FFI_TYPE_STRUCT: *(UINT64 *) argp = (UINT64) *(UINT32 *) (*p_argv); break; default: FFI_ASSERT(0); break; } argp += sizeof (UINT64); } else if (z == sizeof (UINT64) && align == sizeof (UINT64) && ((int) *p_argv & (sizeof (UINT64) - 1)) == 0) { *(UINT64 *) argp = *(UINT64 *) (*p_argv); argp += sizeof (UINT64); } else { int n = (z + sizeof (UINT64) - 1) / sizeof (UINT64); memcpy (argp, *p_argv, z); argp += n * sizeof (UINT64); } } return; } /* Perform machine dependent cif processing */ ffi_status ffi_prep_cif_machdep(ffi_cif *cif) { int i, j; int size, type; int n, m; int greg; int freg; int fpair = -1; greg = (return_type (cif->rtype) == FFI_TYPE_STRUCT ? 1 : 0); freg = 0; cif->flags2 = 0; for (i = j = 0; i < cif->nargs; i++) { type = (cif->arg_types)[i]->type; switch (type) { case FFI_TYPE_FLOAT: greg++; cif->bytes += sizeof (UINT64) - sizeof (float); if (freg >= NFREGARG - 1) continue; if (fpair < 0) { fpair = freg; freg += 2; } else fpair = -1; cif->flags2 += ((cif->arg_types)[i]->type) << (2 * j++); break; case FFI_TYPE_DOUBLE: if (greg++ >= NGREGARG && (freg + 1) >= NFREGARG) continue; if ((freg + 1) < NFREGARG) { freg += 2; cif->flags2 += ((cif->arg_types)[i]->type) << (2 * j++); } else cif->flags2 += FFI_TYPE_INT << (2 * j++); break; default: size = (cif->arg_types)[i]->size; if (size < sizeof (UINT64)) cif->bytes += sizeof (UINT64) - size; n = (size + sizeof (UINT64) - 1) / sizeof (UINT64); if (greg >= NGREGARG) continue; else if (greg + n - 1 >= NGREGARG) greg = NGREGARG; else greg += n; for (m = 0; m < n; m++) cif->flags2 += FFI_TYPE_INT << (2 * j++); break; } } /* Set the return type flag */ switch (cif->rtype->type) { case FFI_TYPE_STRUCT: cif->flags = return_type (cif->rtype); break; case FFI_TYPE_VOID: case FFI_TYPE_FLOAT: case FFI_TYPE_DOUBLE: case FFI_TYPE_SINT64: case FFI_TYPE_UINT64: cif->flags = cif->rtype->type; break; default: cif->flags = FFI_TYPE_INT; break; } return FFI_OK; } /*@-declundef@*/ /*@-exportheader@*/ extern void ffi_call_SYSV(void (*)(char *, extended_cif *), /*@out@*/ extended_cif *, unsigned, unsigned, long long, /*@out@*/ unsigned *, void (*fn)(void)); /*@=declundef@*/ /*@=exportheader@*/ void ffi_call(/*@dependent@*/ ffi_cif *cif, void (*fn)(void), /*@out@*/ void *rvalue, /*@dependent@*/ void **avalue) { extended_cif ecif; UINT64 trvalue; ecif.cif = cif; ecif.avalue = avalue; /* If the return value is a struct and we don't have a return */ /* value address then we need to make one */ if (cif->rtype->type == FFI_TYPE_STRUCT && return_type (cif->rtype) != FFI_TYPE_STRUCT) ecif.rvalue = &trvalue; else if ((rvalue == NULL) && (cif->rtype->type == FFI_TYPE_STRUCT)) { ecif.rvalue = alloca(cif->rtype->size); } else ecif.rvalue = rvalue; switch (cif->abi) { case FFI_SYSV: ffi_call_SYSV(ffi_prep_args, &ecif, cif->bytes, cif->flags, cif->flags2, ecif.rvalue, fn); break; default: FFI_ASSERT(0); break; } if (rvalue && cif->rtype->type == FFI_TYPE_STRUCT && return_type (cif->rtype) != FFI_TYPE_STRUCT) memcpy (rvalue, &trvalue, cif->rtype->size); } extern void ffi_closure_SYSV (void); extern void __ic_invalidate (void *line); ffi_status ffi_prep_closure_loc (ffi_closure *closure, ffi_cif *cif, void (*fun)(ffi_cif*, void*, void**, void*), void *user_data, void *codeloc) { unsigned int *tramp; FFI_ASSERT (cif->abi == FFI_GCC_SYSV); tramp = (unsigned int *) &closure->tramp[0]; /* Since ffi_closure is an aligned object, the ffi trampoline is called as an SHcompact code. Sigh. SHcompact part: mova @(1,pc),r0; add #1,r0; jmp @r0; nop; SHmedia part: movi fnaddr >> 16,r1; shori fnaddr,r1; ptabs/l r1,tr0 movi cxt >> 16,r1; shori cxt,r1; blink tr0,r63 */ #ifdef __LITTLE_ENDIAN__ tramp[0] = 0x7001c701; tramp[1] = 0x0009402b; #else tramp[0] = 0xc7017001; tramp[1] = 0x402b0009; #endif tramp[2] = 0xcc000010 | (((UINT32) ffi_closure_SYSV) >> 16) << 10; tramp[3] = 0xc8000010 | (((UINT32) ffi_closure_SYSV) & 0xffff) << 10; tramp[4] = 0x6bf10600; tramp[5] = 0xcc000010 | (((UINT32) codeloc) >> 16) << 10; tramp[6] = 0xc8000010 | (((UINT32) codeloc) & 0xffff) << 10; tramp[7] = 0x4401fff0; closure->cif = cif; closure->fun = fun; closure->user_data = user_data; /* Flush the icache. */ asm volatile ("ocbwb %0,0; synco; icbi %1,0; synci" : : "r" (tramp), "r"(codeloc)); return FFI_OK; } /* Basically the trampoline invokes ffi_closure_SYSV, and on * entry, r3 holds the address of the closure. * After storing the registers that could possibly contain * parameters to be passed into the stack frame and setting * up space for a return value, ffi_closure_SYSV invokes the * following helper function to do most of the work. */ int ffi_closure_helper_SYSV (ffi_closure *closure, UINT64 *rvalue, UINT64 *pgr, UINT64 *pfr, UINT64 *pst) { void **avalue; ffi_type **p_arg; int i, avn; int greg, freg; ffi_cif *cif; int fpair = -1; cif = closure->cif; avalue = alloca (cif->nargs * sizeof (void *)); /* Copy the caller's structure return value address so that the closure returns the data directly to the caller. */ if (return_type (cif->rtype) == FFI_TYPE_STRUCT) { rvalue = (UINT64 *) *pgr; greg = 1; } else greg = 0; freg = 0; cif = closure->cif; avn = cif->nargs; /* Grab the addresses of the arguments from the stack frame. */ for (i = 0, p_arg = cif->arg_types; i < avn; i++, p_arg++) { size_t z; void *p; z = (*p_arg)->size; if (z < sizeof (UINT32)) { p = pgr + greg++; switch ((*p_arg)->type) { case FFI_TYPE_SINT8: case FFI_TYPE_UINT8: case FFI_TYPE_SINT16: case FFI_TYPE_UINT16: case FFI_TYPE_STRUCT: #ifdef __LITTLE_ENDIAN__ avalue[i] = p; #else avalue[i] = ((char *) p) + sizeof (UINT32) - z; #endif break; default: FFI_ASSERT(0); } } else if (z == sizeof (UINT32)) { if ((*p_arg)->type == FFI_TYPE_FLOAT) { if (freg < NFREGARG - 1) { if (fpair >= 0) { avalue[i] = (UINT32 *) pfr + fpair; fpair = -1; } else { #ifdef __LITTLE_ENDIAN__ fpair = freg; avalue[i] = (UINT32 *) pfr + (1 ^ freg); #else fpair = 1 ^ freg; avalue[i] = (UINT32 *) pfr + freg; #endif freg += 2; } } else #ifdef __LITTLE_ENDIAN__ avalue[i] = pgr + greg; #else avalue[i] = (UINT32 *) (pgr + greg) + 1; #endif } else #ifdef __LITTLE_ENDIAN__ avalue[i] = pgr + greg; #else avalue[i] = (UINT32 *) (pgr + greg) + 1; #endif greg++; } else if ((*p_arg)->type == FFI_TYPE_DOUBLE) { if (freg + 1 >= NFREGARG) avalue[i] = pgr + greg; else { avalue[i] = pfr + (freg >> 1); freg += 2; } greg++; } else { int n = (z + sizeof (UINT64) - 1) / sizeof (UINT64); avalue[i] = pgr + greg; greg += n; } } (closure->fun) (cif, rvalue, avalue, closure->user_data); /* Tell ffi_closure_SYSV how to perform return type promotions. */ return return_type (cif->rtype); } smalltalk-3.2.5/libffi/src/closures.c0000644000175000017500000004011612130343734014455 00000000000000/* ----------------------------------------------------------------------- closures.c - Copyright (c) 2007 Red Hat, Inc. Copyright (C) 2007, 2009 Free Software Foundation, Inc Code to allocate and deallocate memory for closures. Permission is hereby granted, free of charge, to any person obtaining a copy of this software and associated documentation files (the ``Software''), to deal in the Software without restriction, including without limitation the rights to use, copy, modify, merge, publish, distribute, sublicense, and/or sell copies of the Software, and to permit persons to whom the Software is furnished to do so, subject to the following conditions: The above copyright notice and this permission notice shall be included in all copies or substantial portions of the Software. THE SOFTWARE IS PROVIDED ``AS IS'', WITHOUT WARRANTY OF ANY KIND, EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. ----------------------------------------------------------------------- */ #if defined __linux__ && !defined _GNU_SOURCE #define _GNU_SOURCE 1 #endif #include #include #ifndef FFI_MMAP_EXEC_WRIT # if __gnu_linux__ /* This macro indicates it may be forbidden to map anonymous memory with both write and execute permission. Code compiled when this option is defined will attempt to map such pages once, but if it fails, it falls back to creating a temporary file in a writable and executable filesystem and mapping pages from it into separate locations in the virtual memory space, one location writable and another executable. */ # define FFI_MMAP_EXEC_WRIT 1 # define HAVE_MNTENT 1 # endif # if defined(X86_WIN32) || defined(X86_WIN64) || defined(__OS2__) /* Windows systems may have Data Execution Protection (DEP) enabled, which requires the use of VirtualMalloc/VirtualFree to alloc/free executable memory. */ # define FFI_MMAP_EXEC_WRIT 1 # endif #endif #if FFI_MMAP_EXEC_WRIT && !defined FFI_MMAP_EXEC_SELINUX # ifdef __linux__ /* When defined to 1 check for SELinux and if SELinux is active, don't attempt PROT_EXEC|PROT_WRITE mapping at all, as that might cause audit messages. */ # define FFI_MMAP_EXEC_SELINUX 1 # endif #endif #if FFI_CLOSURES # if FFI_MMAP_EXEC_WRIT #define USE_LOCKS 1 #define USE_DL_PREFIX 1 #ifdef __GNUC__ #ifndef USE_BUILTIN_FFS #define USE_BUILTIN_FFS 1 #endif #endif /* We need to use mmap, not sbrk. */ #define HAVE_MORECORE 0 /* We could, in theory, support mremap, but it wouldn't buy us anything. */ #define HAVE_MREMAP 0 /* We have no use for this, so save some code and data. */ #define NO_MALLINFO 1 /* We need all allocations to be in regular segments, otherwise we lose track of the corresponding code address. */ #define DEFAULT_MMAP_THRESHOLD MAX_SIZE_T /* Don't allocate more than a page unless needed. */ #define DEFAULT_GRANULARITY ((size_t)malloc_getpagesize) #if FFI_CLOSURE_TEST /* Don't release single pages, to avoid a worst-case scenario of continuously allocating and releasing single pages, but release pairs of pages, which should do just as well given that allocations are likely to be small. */ #define DEFAULT_TRIM_THRESHOLD ((size_t)malloc_getpagesize) #endif #include #include #include #include #ifndef _MSC_VER #include #endif #include #include #if !defined(X86_WIN32) && !defined(X86_WIN64) #ifdef HAVE_MNTENT #include #endif /* HAVE_MNTENT */ #include #include /* We don't want sys/mman.h to be included after we redefine mmap and dlmunmap. */ #include #define LACKS_SYS_MMAN_H 1 #if FFI_MMAP_EXEC_SELINUX #include #include static int selinux_enabled = -1; static int selinux_enabled_check (void) { struct statfs sfs; FILE *f; char *buf = NULL; size_t len = 0; if (statfs ("/selinux", &sfs) >= 0 && (unsigned int) sfs.f_type == 0xf97cff8cU) return 1; f = fopen ("/proc/mounts", "r"); if (f == NULL) return 0; while (getline (&buf, &len, f) >= 0) { char *p = strchr (buf, ' '); if (p == NULL) break; p = strchr (p + 1, ' '); if (p == NULL) break; if (strncmp (p + 1, "selinuxfs ", 10) == 0) { free (buf); fclose (f); return 1; } } free (buf); fclose (f); return 0; } #define is_selinux_enabled() (selinux_enabled >= 0 ? selinux_enabled \ : (selinux_enabled = selinux_enabled_check ())) #else #define is_selinux_enabled() 0 #endif /* !FFI_MMAP_EXEC_SELINUX */ #elif defined (__CYGWIN__) #include /* Cygwin is Linux-like, but not quite that Linux-like. */ #define is_selinux_enabled() 0 #endif /* !defined(X86_WIN32) && !defined(X86_WIN64) */ /* Declare all functions defined in dlmalloc.c as static. */ static void *dlmalloc(size_t); static void dlfree(void*); static void *dlcalloc(size_t, size_t) MAYBE_UNUSED; static void *dlrealloc(void *, size_t) MAYBE_UNUSED; static void *dlmemalign(size_t, size_t) MAYBE_UNUSED; static void *dlvalloc(size_t) MAYBE_UNUSED; static int dlmallopt(int, int) MAYBE_UNUSED; static size_t dlmalloc_footprint(void) MAYBE_UNUSED; static size_t dlmalloc_max_footprint(void) MAYBE_UNUSED; static void** dlindependent_calloc(size_t, size_t, void**) MAYBE_UNUSED; static void** dlindependent_comalloc(size_t, size_t*, void**) MAYBE_UNUSED; static void *dlpvalloc(size_t) MAYBE_UNUSED; static int dlmalloc_trim(size_t) MAYBE_UNUSED; static size_t dlmalloc_usable_size(void*) MAYBE_UNUSED; static void dlmalloc_stats(void) MAYBE_UNUSED; #if !(defined(X86_WIN32) || defined(X86_WIN64) || defined(__OS2__)) || defined (__CYGWIN__) /* Use these for mmap and munmap within dlmalloc.c. */ static void *dlmmap(void *, size_t, int, int, int, off_t); static int dlmunmap(void *, size_t); #endif /* !(defined(X86_WIN32) || defined(X86_WIN64) || defined(__OS2__)) || defined (__CYGWIN__) */ #define mmap dlmmap #define munmap dlmunmap #include "dlmalloc.c" #undef mmap #undef munmap #if !(defined(X86_WIN32) || defined(X86_WIN64) || defined(__OS2__)) || defined (__CYGWIN__) /* A mutex used to synchronize access to *exec* variables in this file. */ static pthread_mutex_t open_temp_exec_file_mutex = PTHREAD_MUTEX_INITIALIZER; /* A file descriptor of a temporary file from which we'll map executable pages. */ static int execfd = -1; /* The amount of space already allocated from the temporary file. */ static size_t execsize = 0; /* Open a temporary file name, and immediately unlink it. */ static int open_temp_exec_file_name (char *name) { int fd = mkstemp (name); if (fd != -1) unlink (name); return fd; } /* Open a temporary file in the named directory. */ static int open_temp_exec_file_dir (const char *dir) { static const char suffix[] = "/ffiXXXXXX"; int lendir = strlen (dir); char *tempname = __builtin_alloca (lendir + sizeof (suffix)); if (!tempname) return -1; memcpy (tempname, dir, lendir); memcpy (tempname + lendir, suffix, sizeof (suffix)); return open_temp_exec_file_name (tempname); } /* Open a temporary file in the directory in the named environment variable. */ static int open_temp_exec_file_env (const char *envvar) { const char *value = getenv (envvar); if (!value) return -1; return open_temp_exec_file_dir (value); } #ifdef HAVE_MNTENT /* Open a temporary file in an executable and writable mount point listed in the mounts file. Subsequent calls with the same mounts keep searching for mount points in the same file. Providing NULL as the mounts file closes the file. */ static int open_temp_exec_file_mnt (const char *mounts) { static const char *last_mounts; static FILE *last_mntent; if (mounts != last_mounts) { if (last_mntent) endmntent (last_mntent); last_mounts = mounts; if (mounts) last_mntent = setmntent (mounts, "r"); else last_mntent = NULL; } if (!last_mntent) return -1; for (;;) { int fd; struct mntent mnt; char buf[MAXPATHLEN * 3]; if (getmntent_r (last_mntent, &mnt, buf, sizeof (buf)) == NULL) return -1; if (hasmntopt (&mnt, "ro") || hasmntopt (&mnt, "noexec") || access (mnt.mnt_dir, W_OK)) continue; fd = open_temp_exec_file_dir (mnt.mnt_dir); if (fd != -1) return fd; } } #endif /* HAVE_MNTENT */ /* Instructions to look for a location to hold a temporary file that can be mapped in for execution. */ static struct { int (*func)(const char *); const char *arg; int repeat; } open_temp_exec_file_opts[] = { { open_temp_exec_file_env, "TMPDIR", 0 }, { open_temp_exec_file_dir, "/tmp", 0 }, { open_temp_exec_file_dir, "/var/tmp", 0 }, { open_temp_exec_file_dir, "/dev/shm", 0 }, { open_temp_exec_file_env, "HOME", 0 }, #ifdef HAVE_MNTENT { open_temp_exec_file_mnt, "/etc/mtab", 1 }, { open_temp_exec_file_mnt, "/proc/mounts", 1 }, #endif /* HAVE_MNTENT */ }; /* Current index into open_temp_exec_file_opts. */ static int open_temp_exec_file_opts_idx = 0; /* Reset a current multi-call func, then advances to the next entry. If we're at the last, go back to the first and return nonzero, otherwise return zero. */ static int open_temp_exec_file_opts_next (void) { if (open_temp_exec_file_opts[open_temp_exec_file_opts_idx].repeat) open_temp_exec_file_opts[open_temp_exec_file_opts_idx].func (NULL); open_temp_exec_file_opts_idx++; if (open_temp_exec_file_opts_idx == (sizeof (open_temp_exec_file_opts) / sizeof (*open_temp_exec_file_opts))) { open_temp_exec_file_opts_idx = 0; return 1; } return 0; } /* Return a file descriptor of a temporary zero-sized file in a writable and exexutable filesystem. */ static int open_temp_exec_file (void) { int fd; do { fd = open_temp_exec_file_opts[open_temp_exec_file_opts_idx].func (open_temp_exec_file_opts[open_temp_exec_file_opts_idx].arg); if (!open_temp_exec_file_opts[open_temp_exec_file_opts_idx].repeat || fd == -1) { if (open_temp_exec_file_opts_next ()) break; } } while (fd == -1); return fd; } /* Map in a chunk of memory from the temporary exec file into separate locations in the virtual memory address space, one writable and one executable. Returns the address of the writable portion, after storing an offset to the corresponding executable portion at the last word of the requested chunk. */ static void * dlmmap_locked (void *start, size_t length, int prot, int flags, off_t offset) { void *ptr; if (execfd == -1) { open_temp_exec_file_opts_idx = 0; retry_open: execfd = open_temp_exec_file (); if (execfd == -1) return MFAIL; } offset = execsize; if (ftruncate (execfd, offset + length)) return MFAIL; flags &= ~(MAP_PRIVATE | MAP_ANONYMOUS); flags |= MAP_SHARED; ptr = mmap (NULL, length, (prot & ~PROT_WRITE) | PROT_EXEC, flags, execfd, offset); if (ptr == MFAIL) { if (!offset) { close (execfd); goto retry_open; } ftruncate (execfd, offset); return MFAIL; } else if (!offset && open_temp_exec_file_opts[open_temp_exec_file_opts_idx].repeat) open_temp_exec_file_opts_next (); start = mmap (start, length, prot, flags, execfd, offset); if (start == MFAIL) { munmap (ptr, length); ftruncate (execfd, offset); return start; } mmap_exec_offset ((char *)start, length) = (char*)ptr - (char*)start; execsize += length; return start; } /* Map in a writable and executable chunk of memory if possible. Failing that, fall back to dlmmap_locked. */ static void * dlmmap (void *start, size_t length, int prot, int flags, int fd, off_t offset) { void *ptr; assert (start == NULL && length % malloc_getpagesize == 0 && prot == (PROT_READ | PROT_WRITE) && flags == (MAP_PRIVATE | MAP_ANONYMOUS) && fd == -1 && offset == 0); #if FFI_CLOSURE_TEST printf ("mapping in %zi\n", length); #endif if (execfd == -1 && !is_selinux_enabled ()) { ptr = mmap (start, length, prot | PROT_EXEC, flags, fd, offset); if (ptr != MFAIL || (errno != EPERM && errno != EACCES)) /* Cool, no need to mess with separate segments. */ return ptr; /* If MREMAP_DUP is ever introduced and implemented, try mmap with ((prot & ~PROT_WRITE) | PROT_EXEC) and mremap with MREMAP_DUP and prot at this point. */ } if (execsize == 0 || execfd == -1) { pthread_mutex_lock (&open_temp_exec_file_mutex); ptr = dlmmap_locked (start, length, prot, flags, offset); pthread_mutex_unlock (&open_temp_exec_file_mutex); return ptr; } return dlmmap_locked (start, length, prot, flags, offset); } /* Release memory at the given address, as well as the corresponding executable page if it's separate. */ static int dlmunmap (void *start, size_t length) { /* We don't bother decreasing execsize or truncating the file, since we can't quite tell whether we're unmapping the end of the file. We don't expect frequent deallocation anyway. If we did, we could locate pages in the file by writing to the pages being deallocated and checking that the file contents change. Yuck. */ msegmentptr seg = segment_holding (gm, start); void *code; #if FFI_CLOSURE_TEST printf ("unmapping %zi\n", length); #endif if (seg && (code = add_segment_exec_offset (start, seg)) != start) { int ret = munmap (code, length); if (ret) return ret; } return munmap (start, length); } #if FFI_CLOSURE_FREE_CODE /* Return segment holding given code address. */ static msegmentptr segment_holding_code (mstate m, char* addr) { msegmentptr sp = &m->seg; for (;;) { if (addr >= add_segment_exec_offset (sp->base, sp) && addr < add_segment_exec_offset (sp->base, sp) + sp->size) return sp; if ((sp = sp->next) == 0) return 0; } } #endif #endif /* !(defined(X86_WIN32) || defined(X86_WIN64) || defined(__OS2__)) || defined (__CYGWIN__) */ /* Allocate a chunk of memory with the given size. Returns a pointer to the writable address, and sets *CODE to the executable corresponding virtual address. */ void * ffi_closure_alloc (size_t size, void **code) { void *ptr; if (!code) return NULL; ptr = dlmalloc (size); if (ptr) { msegmentptr seg = segment_holding (gm, ptr); *code = add_segment_exec_offset (ptr, seg); } return ptr; } /* Release a chunk of memory allocated with ffi_closure_alloc. If FFI_CLOSURE_FREE_CODE is nonzero, the given address can be the writable or the executable address given. Otherwise, only the writable address can be provided here. */ void ffi_closure_free (void *ptr) { #if FFI_CLOSURE_FREE_CODE msegmentptr seg = segment_holding_code (gm, ptr); if (seg) ptr = sub_segment_exec_offset (ptr, seg); #endif dlfree (ptr); } #if FFI_CLOSURE_TEST /* Do some internal sanity testing to make sure allocation and deallocation of pages are working as intended. */ int main () { void *p[3]; #define GET(idx, len) do { p[idx] = dlmalloc (len); printf ("allocated %zi for p[%i]\n", (len), (idx)); } while (0) #define PUT(idx) do { printf ("freeing p[%i]\n", (idx)); dlfree (p[idx]); } while (0) GET (0, malloc_getpagesize / 2); GET (1, 2 * malloc_getpagesize - 64 * sizeof (void*)); PUT (1); GET (1, 2 * malloc_getpagesize); GET (2, malloc_getpagesize / 2); PUT (1); PUT (0); PUT (2); return 0; } #endif /* FFI_CLOSURE_TEST */ # else /* ! FFI_MMAP_EXEC_WRIT */ /* On many systems, memory returned by malloc is writable and executable, so just use it. */ #include void * ffi_closure_alloc (size_t size, void **code) { if (!code) return NULL; return *code = malloc (size); } void ffi_closure_free (void *ptr) { free (ptr); } # endif /* ! FFI_MMAP_EXEC_WRIT */ #endif /* FFI_CLOSURES */ smalltalk-3.2.5/libffi/src/raw_api.c0000644000175000017500000001366312130343734014247 00000000000000/* ----------------------------------------------------------------------- raw_api.c - Copyright (c) 1999, 2008 Red Hat, Inc. Author: Kresten Krab Thorup Permission is hereby granted, free of charge, to any person obtaining a copy of this software and associated documentation files (the ``Software''), to deal in the Software without restriction, including without limitation the rights to use, copy, modify, merge, publish, distribute, sublicense, and/or sell copies of the Software, and to permit persons to whom the Software is furnished to do so, subject to the following conditions: The above copyright notice and this permission notice shall be included in all copies or substantial portions of the Software. THE SOFTWARE IS PROVIDED ``AS IS'', WITHOUT WARRANTY OF ANY KIND, EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. ----------------------------------------------------------------------- */ /* This file defines generic functions for use with the raw api. */ #include #include #if !FFI_NO_RAW_API size_t ffi_raw_size (ffi_cif *cif) { size_t result = 0; int i; ffi_type **at = cif->arg_types; for (i = cif->nargs-1; i >= 0; i--, at++) { #if !FFI_NO_STRUCTS if ((*at)->type == FFI_TYPE_STRUCT) result += ALIGN (sizeof (void*), FFI_SIZEOF_ARG); else #endif result += ALIGN ((*at)->size, FFI_SIZEOF_ARG); } return result; } void ffi_raw_to_ptrarray (ffi_cif *cif, ffi_raw *raw, void **args) { unsigned i; ffi_type **tp = cif->arg_types; #if WORDS_BIGENDIAN for (i = 0; i < cif->nargs; i++, tp++, args++) { switch ((*tp)->type) { case FFI_TYPE_UINT8: case FFI_TYPE_SINT8: *args = (void*) ((char*)(raw++) + FFI_SIZEOF_ARG - 1); break; case FFI_TYPE_UINT16: case FFI_TYPE_SINT16: *args = (void*) ((char*)(raw++) + FFI_SIZEOF_ARG - 2); break; #if FFI_SIZEOF_ARG >= 4 case FFI_TYPE_UINT32: case FFI_TYPE_SINT32: *args = (void*) ((char*)(raw++) + FFI_SIZEOF_ARG - 4); break; #endif #if !FFI_NO_STRUCTS case FFI_TYPE_STRUCT: *args = (raw++)->ptr; break; #endif case FFI_TYPE_POINTER: *args = (void*) &(raw++)->ptr; break; default: *args = raw; raw += ALIGN ((*tp)->size, FFI_SIZEOF_ARG) / FFI_SIZEOF_ARG; } } #else /* WORDS_BIGENDIAN */ #if !PDP /* then assume little endian */ for (i = 0; i < cif->nargs; i++, tp++, args++) { #if !FFI_NO_STRUCTS if ((*tp)->type == FFI_TYPE_STRUCT) { *args = (raw++)->ptr; } else #endif { *args = (void*) raw; raw += ALIGN ((*tp)->size, sizeof (void*)) / sizeof (void*); } } #else #error "pdp endian not supported" #endif /* ! PDP */ #endif /* WORDS_BIGENDIAN */ } void ffi_ptrarray_to_raw (ffi_cif *cif, void **args, ffi_raw *raw) { unsigned i; ffi_type **tp = cif->arg_types; for (i = 0; i < cif->nargs; i++, tp++, args++) { switch ((*tp)->type) { case FFI_TYPE_UINT8: (raw++)->uint = *(UINT8*) (*args); break; case FFI_TYPE_SINT8: (raw++)->sint = *(SINT8*) (*args); break; case FFI_TYPE_UINT16: (raw++)->uint = *(UINT16*) (*args); break; case FFI_TYPE_SINT16: (raw++)->sint = *(SINT16*) (*args); break; #if FFI_SIZEOF_ARG >= 4 case FFI_TYPE_UINT32: (raw++)->uint = *(UINT32*) (*args); break; case FFI_TYPE_SINT32: (raw++)->sint = *(SINT32*) (*args); break; #endif #if !FFI_NO_STRUCTS case FFI_TYPE_STRUCT: (raw++)->ptr = *args; break; #endif case FFI_TYPE_POINTER: (raw++)->ptr = **(void***) args; break; default: memcpy ((void*) raw->data, (void*)*args, (*tp)->size); raw += ALIGN ((*tp)->size, FFI_SIZEOF_ARG) / FFI_SIZEOF_ARG; } } } #if !FFI_NATIVE_RAW_API /* This is a generic definition of ffi_raw_call, to be used if the * native system does not provide a machine-specific implementation. * Having this, allows code to be written for the raw API, without * the need for system-specific code to handle input in that format; * these following couple of functions will handle the translation forth * and back automatically. */ void ffi_raw_call (ffi_cif *cif, void (*fn)(void), void *rvalue, ffi_raw *raw) { void **avalue = (void**) alloca (cif->nargs * sizeof (void*)); ffi_raw_to_ptrarray (cif, raw, avalue); ffi_call (cif, fn, rvalue, avalue); } #if FFI_CLOSURES /* base system provides closures */ static void ffi_translate_args (ffi_cif *cif, void *rvalue, void **avalue, void *user_data) { ffi_raw *raw = (ffi_raw*)alloca (ffi_raw_size (cif)); ffi_raw_closure *cl = (ffi_raw_closure*)user_data; ffi_ptrarray_to_raw (cif, avalue, raw); (*cl->fun) (cif, rvalue, raw, cl->user_data); } ffi_status ffi_prep_raw_closure_loc (ffi_raw_closure* cl, ffi_cif *cif, void (*fun)(ffi_cif*,void*,ffi_raw*,void*), void *user_data, void *codeloc) { ffi_status status; status = ffi_prep_closure_loc ((ffi_closure*) cl, cif, &ffi_translate_args, codeloc, codeloc); if (status == FFI_OK) { cl->fun = fun; cl->user_data = user_data; } return status; } #endif /* FFI_CLOSURES */ #endif /* !FFI_NATIVE_RAW_API */ #if FFI_CLOSURES /* Again, here is the generic version of ffi_prep_raw_closure, which * will install an intermediate "hub" for translation of arguments from * the pointer-array format, to the raw format */ ffi_status ffi_prep_raw_closure (ffi_raw_closure* cl, ffi_cif *cif, void (*fun)(ffi_cif*,void*,ffi_raw*,void*), void *user_data) { return ffi_prep_raw_closure_loc (cl, cif, fun, user_data, cl); } #endif /* FFI_CLOSURES */ #endif /* !FFI_NO_RAW_API */ smalltalk-3.2.5/libffi/include/0000755000175000017500000000000012130456004013357 500000000000000smalltalk-3.2.5/libffi/include/ffi_common.h0000644000175000017500000000573112130343734015577 00000000000000/* ----------------------------------------------------------------------- ffi_common.h - Copyright (c) 1996 Red Hat, Inc. Copyright (C) 2007 Free Software Foundation, Inc Common internal definitions and macros. Only necessary for building libffi. ----------------------------------------------------------------------- */ #ifndef FFI_COMMON_H #define FFI_COMMON_H #ifdef __cplusplus extern "C" { #endif #include /* Do not move this. Some versions of AIX are very picky about where this is positioned. */ #ifdef __GNUC__ /* mingw64 defines this already in malloc.h. */ #ifndef alloca # define alloca __builtin_alloca #endif # define MAYBE_UNUSED __attribute__((__unused__)) #else # define MAYBE_UNUSED # if HAVE_ALLOCA_H # include # else # ifdef _AIX #pragma alloca # else # ifndef alloca /* predefined by HP cc +Olibcalls */ # ifdef _MSC_VER # define alloca _alloca # else char *alloca (); # endif # endif # endif # endif #endif /* Check for the existence of memcpy. */ #if STDC_HEADERS # include #else # ifndef HAVE_MEMCPY # define memcpy(d, s, n) bcopy ((s), (d), (n)) # endif #endif #if defined(FFI_DEBUG) #include #endif #ifdef FFI_DEBUG void ffi_assert(char *expr, char *file, int line); void ffi_stop_here(void); void ffi_type_test(ffi_type *a, char *file, int line); #define FFI_ASSERT(x) ((x) ? (void)0 : ffi_assert(#x, __FILE__,__LINE__)) #define FFI_ASSERT_AT(x, f, l) ((x) ? 0 : ffi_assert(#x, (f), (l))) #define FFI_ASSERT_VALID_TYPE(x) ffi_type_test (x, __FILE__, __LINE__) #else #define FFI_ASSERT(x) #define FFI_ASSERT_AT(x, f, l) #define FFI_ASSERT_VALID_TYPE(x) #endif #define ALIGN(v, a) (((((size_t) (v))-1) | ((a)-1))+1) #define ALIGN_DOWN(v, a) (((size_t) (v)) & -a) /* Perform machine dependent cif processing */ ffi_status ffi_prep_cif_machdep(ffi_cif *cif); /* Extended cif, used in callback from assembly routine */ typedef struct { ffi_cif *cif; void *rvalue; void **avalue; } extended_cif; /* Terse sized type definitions. */ #if defined(_MSC_VER) || defined(__sgi) typedef unsigned char UINT8; typedef signed char SINT8; typedef unsigned short UINT16; typedef signed short SINT16; typedef unsigned int UINT32; typedef signed int SINT32; # ifdef _MSC_VER typedef unsigned __int64 UINT64; typedef signed __int64 SINT64; # else # include typedef uint64_t UINT64; typedef int64_t SINT64; # endif #else typedef unsigned int UINT8 __attribute__((__mode__(__QI__))); typedef signed int SINT8 __attribute__((__mode__(__QI__))); typedef unsigned int UINT16 __attribute__((__mode__(__HI__))); typedef signed int SINT16 __attribute__((__mode__(__HI__))); typedef unsigned int UINT32 __attribute__((__mode__(__SI__))); typedef signed int SINT32 __attribute__((__mode__(__SI__))); typedef unsigned int UINT64 __attribute__((__mode__(__DI__))); typedef signed int SINT64 __attribute__((__mode__(__DI__))); #endif typedef float FLOAT32; #ifdef __cplusplus } #endif #endif smalltalk-3.2.5/libffi/include/Makefile.am0000644000175000017500000000026012130343734015336 00000000000000## Process this with automake to create Makefile.in AUTOMAKE_OPTIONS=foreign DISTCLEANFILES=ffitarget.h EXTRA_DIST=ffi.h.in ffi_common.h nodist_noinst_HEADERS = ffitarget.h smalltalk-3.2.5/libffi/include/Makefile.in0000644000175000017500000003106712130455522015357 00000000000000# Makefile.in generated by automake 1.11.6 from Makefile.am. # @configure_input@ # Copyright (C) 1994, 1995, 1996, 1997, 1998, 1999, 2000, 2001, 2002, # 2003, 2004, 2005, 2006, 2007, 2008, 2009, 2010, 2011 Free Software # Foundation, Inc. # This Makefile.in is free software; the Free Software Foundation # gives unlimited permission to copy and/or distribute it, # with or without modifications, as long as this notice is preserved. # This program is distributed in the hope that it will be useful, # but WITHOUT ANY WARRANTY, to the extent permitted by law; without # even the implied warranty of MERCHANTABILITY or FITNESS FOR A # PARTICULAR PURPOSE. @SET_MAKE@ VPATH = @srcdir@ am__make_dryrun = \ { \ am__dry=no; \ case $$MAKEFLAGS in \ *\\[\ \ ]*) \ echo 'am--echo: ; @echo "AM" OK' | $(MAKE) -f - 2>/dev/null \ | grep '^AM OK$$' >/dev/null || am__dry=yes;; \ *) \ for am__flg in $$MAKEFLAGS; do \ case $$am__flg in \ *=*|--*) ;; \ *n*) am__dry=yes; break;; \ esac; \ done;; \ esac; \ test $$am__dry = yes; \ } pkgdatadir = $(datadir)/@PACKAGE@ pkgincludedir = $(includedir)/@PACKAGE@ pkglibdir = $(libdir)/@PACKAGE@ pkglibexecdir = $(libexecdir)/@PACKAGE@ am__cd = CDPATH="$${ZSH_VERSION+.}$(PATH_SEPARATOR)" && cd install_sh_DATA = $(install_sh) -c -m 644 install_sh_PROGRAM = $(install_sh) -c install_sh_SCRIPT = $(install_sh) -c INSTALL_HEADER = $(INSTALL_DATA) transform = $(program_transform_name) NORMAL_INSTALL = : PRE_INSTALL = : POST_INSTALL = : NORMAL_UNINSTALL = : PRE_UNINSTALL = : POST_UNINSTALL = : build_triplet = @build@ host_triplet = @host@ target_triplet = @target@ subdir = include DIST_COMMON = $(srcdir)/Makefile.am $(srcdir)/Makefile.in \ $(srcdir)/ffi.h.in ACLOCAL_M4 = $(top_srcdir)/aclocal.m4 am__aclocal_m4_deps = $(top_srcdir)/../build-aux/libtool.m4 \ $(top_srcdir)/../build-aux/ltoptions.m4 \ $(top_srcdir)/../build-aux/ltsugar.m4 \ $(top_srcdir)/../build-aux/ltversion.m4 \ $(top_srcdir)/../build-aux/lt~obsolete.m4 \ $(top_srcdir)/configure.ac am__configure_deps = $(am__aclocal_m4_deps) $(CONFIGURE_DEPENDENCIES) \ $(ACLOCAL_M4) mkinstalldirs = $(install_sh) -d CONFIG_HEADER = $(top_builddir)/fficonfig.h CONFIG_CLEAN_FILES = ffi.h ffitarget.h CONFIG_CLEAN_VPATH_FILES = SOURCES = DIST_SOURCES = am__can_run_installinfo = \ case $$AM_UPDATE_INFO_DIR in \ n|no|NO) false;; \ *) (install-info --version) >/dev/null 2>&1;; \ esac HEADERS = $(nodist_noinst_HEADERS) ETAGS = etags CTAGS = ctags DISTFILES = $(DIST_COMMON) $(DIST_SOURCES) $(TEXINFOS) $(EXTRA_DIST) ACLOCAL = @ACLOCAL@ ALLOCA = @ALLOCA@ AMTAR = @AMTAR@ AM_LTLDFLAGS = @AM_LTLDFLAGS@ AM_RUNTESTFLAGS = @AM_RUNTESTFLAGS@ AR = @AR@ AUTOCONF = @AUTOCONF@ AUTOHEADER = @AUTOHEADER@ AUTOMAKE = @AUTOMAKE@ AWK = @AWK@ CC = @CC@ CCAS = @CCAS@ CCASDEPMODE = @CCASDEPMODE@ CCASFLAGS = @CCASFLAGS@ CCDEPMODE = @CCDEPMODE@ CFLAGS = @CFLAGS@ CPP = @CPP@ CPPFLAGS = @CPPFLAGS@ CYGPATH_W = @CYGPATH_W@ DEFS = @DEFS@ DEPDIR = @DEPDIR@ DLLTOOL = @DLLTOOL@ DSYMUTIL = @DSYMUTIL@ DUMPBIN = @DUMPBIN@ ECHO_C = @ECHO_C@ ECHO_N = @ECHO_N@ ECHO_T = @ECHO_T@ EGREP = @EGREP@ EXEEXT = @EXEEXT@ FGREP = @FGREP@ GREP = @GREP@ HAVE_LONG_DOUBLE = @HAVE_LONG_DOUBLE@ INSTALL = @INSTALL@ INSTALL_DATA = @INSTALL_DATA@ INSTALL_PROGRAM = @INSTALL_PROGRAM@ INSTALL_SCRIPT = @INSTALL_SCRIPT@ INSTALL_STRIP_PROGRAM = @INSTALL_STRIP_PROGRAM@ LD = @LD@ LDFLAGS = @LDFLAGS@ LIBOBJS = @LIBOBJS@ LIBS = @LIBS@ LIBTOOL = @LIBTOOL@ LIPO = @LIPO@ LN_S = @LN_S@ LTLIBOBJS = @LTLIBOBJS@ MAKEINFO = @MAKEINFO@ MANIFEST_TOOL = @MANIFEST_TOOL@ MKDIR_P = @MKDIR_P@ NM = @NM@ NMEDIT = @NMEDIT@ OBJDUMP = @OBJDUMP@ OBJEXT = @OBJEXT@ OTOOL = @OTOOL@ OTOOL64 = @OTOOL64@ PACKAGE = @PACKAGE@ PACKAGE_BUGREPORT = @PACKAGE_BUGREPORT@ PACKAGE_NAME = @PACKAGE_NAME@ PACKAGE_STRING = @PACKAGE_STRING@ PACKAGE_TARNAME = @PACKAGE_TARNAME@ PACKAGE_URL = @PACKAGE_URL@ PACKAGE_VERSION = @PACKAGE_VERSION@ PATH_SEPARATOR = @PATH_SEPARATOR@ RANLIB = @RANLIB@ SED = @SED@ SET_MAKE = @SET_MAKE@ SHELL = @SHELL@ STRIP = @STRIP@ TARGET = @TARGET@ TARGETDIR = @TARGETDIR@ VERSION = @VERSION@ abs_builddir = @abs_builddir@ abs_srcdir = @abs_srcdir@ abs_top_builddir = @abs_top_builddir@ abs_top_srcdir = @abs_top_srcdir@ ac_ct_AR = @ac_ct_AR@ ac_ct_CC = @ac_ct_CC@ ac_ct_DUMPBIN = @ac_ct_DUMPBIN@ am__include = @am__include@ am__leading_dot = @am__leading_dot@ am__quote = @am__quote@ am__tar = @am__tar@ am__untar = @am__untar@ bindir = @bindir@ build = @build@ build_alias = @build_alias@ build_cpu = @build_cpu@ build_os = @build_os@ build_vendor = @build_vendor@ builddir = @builddir@ datadir = @datadir@ datarootdir = @datarootdir@ docdir = @docdir@ dvidir = @dvidir@ exec_prefix = @exec_prefix@ host = @host@ host_alias = @host_alias@ host_cpu = @host_cpu@ host_os = @host_os@ host_vendor = @host_vendor@ htmldir = @htmldir@ includedir = @includedir@ infodir = @infodir@ install_sh = @install_sh@ libdir = @libdir@ libexecdir = @libexecdir@ localedir = @localedir@ localstatedir = @localstatedir@ mandir = @mandir@ mkdir_p = @mkdir_p@ oldincludedir = @oldincludedir@ pdfdir = @pdfdir@ prefix = @prefix@ program_transform_name = @program_transform_name@ psdir = @psdir@ sbindir = @sbindir@ sharedstatedir = @sharedstatedir@ srcdir = @srcdir@ sysconfdir = @sysconfdir@ target = @target@ target_alias = @target_alias@ target_cpu = @target_cpu@ target_os = @target_os@ target_vendor = @target_vendor@ top_build_prefix = @top_build_prefix@ top_builddir = @top_builddir@ top_srcdir = @top_srcdir@ AUTOMAKE_OPTIONS = foreign DISTCLEANFILES = ffitarget.h EXTRA_DIST = ffi.h.in ffi_common.h nodist_noinst_HEADERS = ffitarget.h all: all-am .SUFFIXES: $(srcdir)/Makefile.in: $(srcdir)/Makefile.am $(am__configure_deps) @for dep in $?; do \ case '$(am__configure_deps)' in \ *$$dep*) \ ( cd $(top_builddir) && $(MAKE) $(AM_MAKEFLAGS) am--refresh ) \ && { if test -f $@; then exit 0; else break; fi; }; \ exit 1;; \ esac; \ done; \ echo ' cd $(top_srcdir) && $(AUTOMAKE) --foreign include/Makefile'; \ $(am__cd) $(top_srcdir) && \ $(AUTOMAKE) --foreign include/Makefile .PRECIOUS: Makefile Makefile: $(srcdir)/Makefile.in $(top_builddir)/config.status @case '$?' in \ *config.status*) \ cd $(top_builddir) && $(MAKE) $(AM_MAKEFLAGS) am--refresh;; \ *) \ echo ' cd $(top_builddir) && $(SHELL) ./config.status $(subdir)/$@ $(am__depfiles_maybe)'; \ cd $(top_builddir) && $(SHELL) ./config.status $(subdir)/$@ $(am__depfiles_maybe);; \ esac; $(top_builddir)/config.status: $(top_srcdir)/configure $(CONFIG_STATUS_DEPENDENCIES) cd $(top_builddir) && $(MAKE) $(AM_MAKEFLAGS) am--refresh $(top_srcdir)/configure: $(am__configure_deps) cd $(top_builddir) && $(MAKE) $(AM_MAKEFLAGS) am--refresh $(ACLOCAL_M4): $(am__aclocal_m4_deps) cd $(top_builddir) && $(MAKE) $(AM_MAKEFLAGS) am--refresh $(am__aclocal_m4_deps): ffi.h: $(top_builddir)/config.status $(srcdir)/ffi.h.in cd $(top_builddir) && $(SHELL) ./config.status $(subdir)/$@ mostlyclean-libtool: -rm -f *.lo clean-libtool: -rm -rf .libs _libs ID: $(HEADERS) $(SOURCES) $(LISP) $(TAGS_FILES) list='$(SOURCES) $(HEADERS) $(LISP) $(TAGS_FILES)'; \ unique=`for i in $$list; do \ if test -f "$$i"; then echo $$i; else echo $(srcdir)/$$i; fi; \ done | \ $(AWK) '{ files[$$0] = 1; nonempty = 1; } \ END { if (nonempty) { for (i in files) print i; }; }'`; \ mkid -fID $$unique tags: TAGS TAGS: $(HEADERS) $(SOURCES) $(TAGS_DEPENDENCIES) \ $(TAGS_FILES) $(LISP) set x; \ here=`pwd`; \ list='$(SOURCES) $(HEADERS) $(LISP) $(TAGS_FILES)'; \ unique=`for i in $$list; do \ if test -f "$$i"; then echo $$i; else echo $(srcdir)/$$i; fi; \ done | \ $(AWK) '{ files[$$0] = 1; nonempty = 1; } \ END { if (nonempty) { for (i in files) print i; }; }'`; \ shift; \ if test -z "$(ETAGS_ARGS)$$*$$unique"; then :; else \ test -n "$$unique" || unique=$$empty_fix; \ if test $$# -gt 0; then \ $(ETAGS) $(ETAGSFLAGS) $(AM_ETAGSFLAGS) $(ETAGS_ARGS) \ "$$@" $$unique; \ else \ $(ETAGS) $(ETAGSFLAGS) $(AM_ETAGSFLAGS) $(ETAGS_ARGS) \ $$unique; \ fi; \ fi ctags: CTAGS CTAGS: $(HEADERS) $(SOURCES) $(TAGS_DEPENDENCIES) \ $(TAGS_FILES) $(LISP) list='$(SOURCES) $(HEADERS) $(LISP) $(TAGS_FILES)'; \ unique=`for i in $$list; do \ if test -f "$$i"; then echo $$i; else echo $(srcdir)/$$i; fi; \ done | \ $(AWK) '{ files[$$0] = 1; nonempty = 1; } \ END { if (nonempty) { for (i in files) print i; }; }'`; \ test -z "$(CTAGS_ARGS)$$unique" \ || $(CTAGS) $(CTAGSFLAGS) $(AM_CTAGSFLAGS) $(CTAGS_ARGS) \ $$unique GTAGS: here=`$(am__cd) $(top_builddir) && pwd` \ && $(am__cd) $(top_srcdir) \ && gtags -i $(GTAGS_ARGS) "$$here" distclean-tags: -rm -f TAGS ID GTAGS GRTAGS GSYMS GPATH tags distdir: $(DISTFILES) @srcdirstrip=`echo "$(srcdir)" | sed 's/[].[^$$\\*]/\\\\&/g'`; \ topsrcdirstrip=`echo "$(top_srcdir)" | sed 's/[].[^$$\\*]/\\\\&/g'`; \ list='$(DISTFILES)'; \ dist_files=`for file in $$list; do echo $$file; done | \ sed -e "s|^$$srcdirstrip/||;t" \ -e "s|^$$topsrcdirstrip/|$(top_builddir)/|;t"`; \ case $$dist_files in \ */*) $(MKDIR_P) `echo "$$dist_files" | \ sed '/\//!d;s|^|$(distdir)/|;s,/[^/]*$$,,' | \ sort -u` ;; \ esac; \ for file in $$dist_files; do \ if test -f $$file || test -d $$file; then d=.; else d=$(srcdir); fi; \ if test -d $$d/$$file; then \ dir=`echo "/$$file" | sed -e 's,/[^/]*$$,,'`; \ if test -d "$(distdir)/$$file"; then \ find "$(distdir)/$$file" -type d ! -perm -700 -exec chmod u+rwx {} \;; \ fi; \ if test -d $(srcdir)/$$file && test $$d != $(srcdir); then \ cp -fpR $(srcdir)/$$file "$(distdir)$$dir" || exit 1; \ find "$(distdir)/$$file" -type d ! -perm -700 -exec chmod u+rwx {} \;; \ fi; \ cp -fpR $$d/$$file "$(distdir)$$dir" || exit 1; \ else \ test -f "$(distdir)/$$file" \ || cp -p $$d/$$file "$(distdir)/$$file" \ || exit 1; \ fi; \ done check-am: all-am check: check-am all-am: Makefile $(HEADERS) installdirs: install: install-am install-exec: install-exec-am install-data: install-data-am uninstall: uninstall-am install-am: all-am @$(MAKE) $(AM_MAKEFLAGS) install-exec-am install-data-am installcheck: installcheck-am install-strip: if test -z '$(STRIP)'; then \ $(MAKE) $(AM_MAKEFLAGS) INSTALL_PROGRAM="$(INSTALL_STRIP_PROGRAM)" \ install_sh_PROGRAM="$(INSTALL_STRIP_PROGRAM)" INSTALL_STRIP_FLAG=-s \ install; \ else \ $(MAKE) $(AM_MAKEFLAGS) INSTALL_PROGRAM="$(INSTALL_STRIP_PROGRAM)" \ install_sh_PROGRAM="$(INSTALL_STRIP_PROGRAM)" INSTALL_STRIP_FLAG=-s \ "INSTALL_PROGRAM_ENV=STRIPPROG='$(STRIP)'" install; \ fi mostlyclean-generic: clean-generic: distclean-generic: -test -z "$(CONFIG_CLEAN_FILES)" || rm -f $(CONFIG_CLEAN_FILES) -test . = "$(srcdir)" || test -z "$(CONFIG_CLEAN_VPATH_FILES)" || rm -f $(CONFIG_CLEAN_VPATH_FILES) -test -z "$(DISTCLEANFILES)" || rm -f $(DISTCLEANFILES) maintainer-clean-generic: @echo "This command is intended for maintainers to use" @echo "it deletes files that may require special tools to rebuild." clean: clean-am clean-am: clean-generic clean-libtool mostlyclean-am distclean: distclean-am -rm -f Makefile distclean-am: clean-am distclean-generic distclean-tags dvi: dvi-am dvi-am: html: html-am html-am: info: info-am info-am: install-data-am: install-dvi: install-dvi-am install-dvi-am: install-exec-am: install-html: install-html-am install-html-am: install-info: install-info-am install-info-am: install-man: install-pdf: install-pdf-am install-pdf-am: install-ps: install-ps-am install-ps-am: installcheck-am: maintainer-clean: maintainer-clean-am -rm -f Makefile maintainer-clean-am: distclean-am maintainer-clean-generic mostlyclean: mostlyclean-am mostlyclean-am: mostlyclean-generic mostlyclean-libtool pdf: pdf-am pdf-am: ps: ps-am ps-am: uninstall-am: .MAKE: install-am install-strip .PHONY: CTAGS GTAGS all all-am check check-am clean clean-generic \ clean-libtool ctags distclean distclean-generic \ distclean-libtool distclean-tags distdir dvi dvi-am html \ html-am info info-am install install-am install-data \ install-data-am install-dvi install-dvi-am install-exec \ install-exec-am install-html install-html-am install-info \ install-info-am install-man install-pdf install-pdf-am \ install-ps install-ps-am install-strip installcheck \ installcheck-am installdirs maintainer-clean \ maintainer-clean-generic mostlyclean mostlyclean-generic \ mostlyclean-libtool pdf pdf-am ps ps-am tags uninstall \ uninstall-am # Tell versions [3.59,3.63) of GNU make to not export all variables. # Otherwise a system limit (for SysV at least) may be exceeded. .NOEXPORT: smalltalk-3.2.5/libffi/include/ffi.h.in0000644000175000017500000002536212130343734014636 00000000000000/* -----------------------------------------------------------------*-C-*- libffi @VERSION@ - Copyright (c) 1996-2003, 2007, 2008 Red Hat, Inc. Permission is hereby granted, free of charge, to any person obtaining a copy of this software and associated documentation files (the ``Software''), to deal in the Software without restriction, including without limitation the rights to use, copy, modify, merge, publish, distribute, sublicense, and/or sell copies of the Software, and to permit persons to whom the Software is furnished to do so, subject to the following conditions: The above copyright notice and this permission notice shall be included in all copies or substantial portions of the Software. THE SOFTWARE IS PROVIDED ``AS IS'', WITHOUT WARRANTY OF ANY KIND, EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. ----------------------------------------------------------------------- */ /* ------------------------------------------------------------------- The basic API is described in the README file. The raw API is designed to bypass some of the argument packing and unpacking on architectures for which it can be avoided. The closure API allows interpreted functions to be packaged up inside a C function pointer, so that they can be called as C functions, with no understanding on the client side that they are interpreted. It can also be used in other cases in which it is necessary to package up a user specified parameter and a function pointer as a single function pointer. The closure API must be implemented in order to get its functionality, e.g. for use by gij. Routines are provided to emulate the raw API if the underlying platform doesn't allow faster implementation. More details on the raw and cloure API can be found in: http://gcc.gnu.org/ml/java/1999-q3/msg00138.html and http://gcc.gnu.org/ml/java/1999-q3/msg00174.html -------------------------------------------------------------------- */ #ifndef LIBFFI_H #define LIBFFI_H #ifdef __cplusplus extern "C" { #endif /* Specify which architecture libffi is configured for. */ #ifndef @TARGET@ #define @TARGET@ #endif /* ---- System configuration information --------------------------------- */ #include #ifndef LIBFFI_ASM #ifdef _MSC_VER #define __attribute__(X) #endif #include #include /* LONG_LONG_MAX is not always defined (not if STRICT_ANSI, for example). But we can find it either under the correct ANSI name, or under GNU C's internal name. */ #ifdef LONG_LONG_MAX # define FFI_LONG_LONG_MAX LONG_LONG_MAX #else # ifdef LLONG_MAX # define FFI_LONG_LONG_MAX LLONG_MAX # else # ifdef __GNUC__ # define FFI_LONG_LONG_MAX __LONG_LONG_MAX__ # endif # endif #endif /* The closure code assumes that this works on pointers, i.e. a size_t */ /* can hold a pointer. */ typedef struct _ffi_type { size_t size; unsigned short alignment; unsigned short type; struct _ffi_type **elements; } ffi_type; #ifndef LIBFFI_HIDE_BASIC_TYPES #if SCHAR_MAX == 127 # define ffi_type_uchar ffi_type_uint8 # define ffi_type_schar ffi_type_sint8 #else #error "char size not supported" #endif #if SHRT_MAX == 32767 # define ffi_type_ushort ffi_type_uint16 # define ffi_type_sshort ffi_type_sint16 #elif SHRT_MAX == 2147483647 # define ffi_type_ushort ffi_type_uint32 # define ffi_type_sshort ffi_type_sint32 #else #error "short size not supported" #endif #if INT_MAX == 32767 # define ffi_type_uint ffi_type_uint16 # define ffi_type_sint ffi_type_sint16 #elif INT_MAX == 2147483647 # define ffi_type_uint ffi_type_uint32 # define ffi_type_sint ffi_type_sint32 #elif INT_MAX == 9223372036854775807 # define ffi_type_uint ffi_type_uint64 # define ffi_type_sint ffi_type_sint64 #else #error "int size not supported" #endif #if LONG_MAX == 2147483647 # if FFI_LONG_LONG_MAX != 9223372036854775807 #error "no 64-bit data type supported" # endif #elif LONG_MAX != 9223372036854775807 #error "long size not supported" #endif #if LONG_MAX == 2147483647 # define ffi_type_ulong ffi_type_uint32 # define ffi_type_slong ffi_type_sint32 #elif LONG_MAX == 9223372036854775807 # define ffi_type_ulong ffi_type_uint64 # define ffi_type_slong ffi_type_sint64 #else #error "long size not supported" #endif /* These are defined in types.c */ extern ffi_type ffi_type_void; extern ffi_type ffi_type_uint8; extern ffi_type ffi_type_sint8; extern ffi_type ffi_type_uint16; extern ffi_type ffi_type_sint16; extern ffi_type ffi_type_uint32; extern ffi_type ffi_type_sint32; extern ffi_type ffi_type_uint64; extern ffi_type ffi_type_sint64; extern ffi_type ffi_type_float; extern ffi_type ffi_type_double; extern ffi_type ffi_type_pointer; #if @HAVE_LONG_DOUBLE@ extern ffi_type ffi_type_longdouble; #else #define ffi_type_longdouble ffi_type_double #endif #endif /* LIBFFI_HIDE_BASIC_TYPES */ typedef enum { FFI_OK = 0, FFI_BAD_TYPEDEF, FFI_BAD_ABI } ffi_status; typedef unsigned FFI_TYPE; typedef struct { ffi_abi abi; unsigned nargs; ffi_type **arg_types; ffi_type *rtype; unsigned bytes; unsigned flags; #ifdef FFI_EXTRA_CIF_FIELDS FFI_EXTRA_CIF_FIELDS; #endif } ffi_cif; /* ---- Definitions for the raw API -------------------------------------- */ #ifndef FFI_SIZEOF_ARG # if LONG_MAX == 2147483647 # define FFI_SIZEOF_ARG 4 # elif LONG_MAX == 9223372036854775807 # define FFI_SIZEOF_ARG 8 # endif #endif #ifndef FFI_SIZEOF_JAVA_RAW # define FFI_SIZEOF_JAVA_RAW FFI_SIZEOF_ARG #endif typedef union { ffi_sarg sint; ffi_arg uint; float flt; char data[FFI_SIZEOF_ARG]; void* ptr; } ffi_raw; #if FFI_SIZEOF_JAVA_RAW == 4 && FFI_SIZEOF_ARG == 8 /* This is a special case for mips64/n32 ABI (and perhaps others) where sizeof(void *) is 4 and FFI_SIZEOF_ARG is 8. */ typedef union { signed int sint; unsigned int uint; float flt; char data[FFI_SIZEOF_JAVA_RAW]; void* ptr; } ffi_java_raw; #else typedef ffi_raw ffi_java_raw; #endif void ffi_raw_call (ffi_cif *cif, void (*fn)(void), void *rvalue, ffi_raw *avalue); void ffi_ptrarray_to_raw (ffi_cif *cif, void **args, ffi_raw *raw); void ffi_raw_to_ptrarray (ffi_cif *cif, ffi_raw *raw, void **args); size_t ffi_raw_size (ffi_cif *cif); /* This is analogous to the raw API, except it uses Java parameter */ /* packing, even on 64-bit machines. I.e. on 64-bit machines */ /* longs and doubles are followed by an empty 64-bit word. */ void ffi_java_raw_call (ffi_cif *cif, void (*fn)(void), void *rvalue, ffi_java_raw *avalue); void ffi_java_ptrarray_to_raw (ffi_cif *cif, void **args, ffi_java_raw *raw); void ffi_java_raw_to_ptrarray (ffi_cif *cif, ffi_java_raw *raw, void **args); size_t ffi_java_raw_size (ffi_cif *cif); /* ---- Definitions for closures ----------------------------------------- */ #if FFI_CLOSURES #ifdef _MSC_VER __declspec(align(8)) #endif typedef struct { char tramp[FFI_TRAMPOLINE_SIZE]; ffi_cif *cif; void (*fun)(ffi_cif*,void*,void**,void*); void *user_data; #ifdef __GNUC__ } ffi_closure __attribute__((aligned (8))); #else } ffi_closure; #endif void *ffi_closure_alloc (size_t size, void **code); void ffi_closure_free (void *); ffi_status ffi_prep_closure (ffi_closure*, ffi_cif *, void (*fun)(ffi_cif*,void*,void**,void*), void *user_data); ffi_status ffi_prep_closure_loc (ffi_closure*, ffi_cif *, void (*fun)(ffi_cif*,void*,void**,void*), void *user_data, void*codeloc); typedef struct { char tramp[FFI_TRAMPOLINE_SIZE]; ffi_cif *cif; #if !FFI_NATIVE_RAW_API /* if this is enabled, then a raw closure has the same layout as a regular closure. We use this to install an intermediate handler to do the transaltion, void** -> ffi_raw*. */ void (*translate_args)(ffi_cif*,void*,void**,void*); void *this_closure; #endif void (*fun)(ffi_cif*,void*,ffi_raw*,void*); void *user_data; } ffi_raw_closure; typedef struct { char tramp[FFI_TRAMPOLINE_SIZE]; ffi_cif *cif; #if !FFI_NATIVE_RAW_API /* if this is enabled, then a raw closure has the same layout as a regular closure. We use this to install an intermediate handler to do the transaltion, void** -> ffi_raw*. */ void (*translate_args)(ffi_cif*,void*,void**,void*); void *this_closure; #endif void (*fun)(ffi_cif*,void*,ffi_java_raw*,void*); void *user_data; } ffi_java_raw_closure; ffi_status ffi_prep_raw_closure (ffi_raw_closure*, ffi_cif *cif, void (*fun)(ffi_cif*,void*,ffi_raw*,void*), void *user_data); ffi_status ffi_prep_raw_closure_loc (ffi_raw_closure*, ffi_cif *cif, void (*fun)(ffi_cif*,void*,ffi_raw*,void*), void *user_data, void *codeloc); ffi_status ffi_prep_java_raw_closure (ffi_java_raw_closure*, ffi_cif *cif, void (*fun)(ffi_cif*,void*,ffi_java_raw*,void*), void *user_data); ffi_status ffi_prep_java_raw_closure_loc (ffi_java_raw_closure*, ffi_cif *cif, void (*fun)(ffi_cif*,void*,ffi_java_raw*,void*), void *user_data, void *codeloc); #endif /* FFI_CLOSURES */ /* ---- Public interface definition -------------------------------------- */ ffi_status ffi_prep_cif(ffi_cif *cif, ffi_abi abi, unsigned int nargs, ffi_type *rtype, ffi_type **atypes); void ffi_call(ffi_cif *cif, void (*fn)(void), void *rvalue, void **avalue); /* Useful for eliminating compiler warnings */ #define FFI_FN(f) ((void (*)(void))f) /* ---- Definitions shared with assembly code ---------------------------- */ #endif /* If these change, update src/mips/ffitarget.h. */ #define FFI_TYPE_VOID 0 #define FFI_TYPE_INT 1 #define FFI_TYPE_FLOAT 2 #define FFI_TYPE_DOUBLE 3 #if @HAVE_LONG_DOUBLE@ #define FFI_TYPE_LONGDOUBLE 4 #else #define FFI_TYPE_LONGDOUBLE FFI_TYPE_DOUBLE #endif #define FFI_TYPE_UINT8 5 #define FFI_TYPE_SINT8 6 #define FFI_TYPE_UINT16 7 #define FFI_TYPE_SINT16 8 #define FFI_TYPE_UINT32 9 #define FFI_TYPE_SINT32 10 #define FFI_TYPE_UINT64 11 #define FFI_TYPE_SINT64 12 #define FFI_TYPE_STRUCT 13 #define FFI_TYPE_POINTER 14 /* This should always refer to the last type code (for sanity checks) */ #define FFI_TYPE_LAST FFI_TYPE_POINTER #ifdef __cplusplus } #endif #endif smalltalk-3.2.5/libffi/configure.host0000644000175000017500000000041312130343734014537 00000000000000# configure.host # # This shell script handles all host based configuration for libffi. # # THIS TABLE IS SORTED. KEEP IT THAT WAY. case "${host}" in frv*-elf) LDFLAGS=`echo $LDFLAGS | sed "s/\-B[^ ]*libgloss\/frv\///"`\ -B`pwd`/../libgloss/frv/ ;; esac smalltalk-3.2.5/TODO0000644000175000017500000000544012123404352011115 00000000000000 * File classes ** maybe add renaming as in Squeak's Rio? * OpenGL ** use GetProcAddress ** split nurbs into separate package * Bindings ** Expat ** gnutls ** 3D gnuplot? * maybe ** prepared statements support for other DBI backends ** cookies and redirects for HTTPClient ---------------------------------------------------------------------- * sometime ** upgrade XML parser for package files *** support arch-dependent packages that are installed in the image path ** some kind of sandboxing (partly done) ** add check in/check out to the browser so that .st files remain in sync. Maybe with CVS support (see Smalltalk/X). ** cute BlockClosure implementations ---------------------------------------------------------------------- * bindings ** use zlib bindings to implement direct ZIP-file access in VFS. ** provide cool examples of XML using RSS feeds, SOAP, XML-RPC, whatever. ---------------------------------------------------------------------- * code auditing ** check endian-cleanness of ByteStream's float and double I/O. Possibly fix by mutuating code from the Java package. * VM ** create combined pop/push tree codes in the JIT compiler. They're still there from the old bytecode set and they should improve performance by ~5%. ** Fix some copy & paste redundancies in comp.c (the small iteration to find out the length of loops) and opt.c (basic block handling in the verifier and in the JIT compiler's analysis pass). ** Use multiple malloc-ed areas for the OOP table, and make heap.c only an implementation detail of alloc.c (not really necessary anymore with MAP_NORESERVE, and quite complicated) ** Implement polymorphic inline caching * Java ** Write more native methods. Some, such as network methods, are easy. Reflection is hard especially for arrays. ** Pass exception in a temporary rather than in the top of the stack; not very hard, and should make the JITter happy about exceptions. * Blox ** Use GTK. Might or might not use libgnomeui for the canvas widget. I have already written a custom geometry manager compatible with Tk's placer. ** Clean up the browser's code *** remove stray sends of #initialize. A good project to learn about the reflection system (e.g. identify initializations from outside #new and so on). *** simplify UI creation (too many panes!) * other ** finish the smalltalk CPP and C header file parser ** print entities correctly in the URIResolver. A file named abc&def should print abc&def in the file list. * emacs mode ** emacs isearch c-u c-s should search for a string anchored at the start of a line (possibly with blanks), to help finding method definitions. ** fix $. to be handled specially -- indenter gets confused on ch == $. ifTrue: ** fix emacs mode so when a compile error occurs, it can be scanned ala C-x` smalltalk-3.2.5/AUTHORS0000644000175000017500000000265212123404352011477 00000000000000--------------------------------------- The system --------------- GNU Smalltalk development up to version 1.1.5 by: Steve Byrne GNU Smalltalk development starting with version 1.6 by: Paolo Bonzini GUI development: Gwenael Casaccio (VisualGST) Brad Diller and Steve Byrne (BLOX) superops program: Parts by Douglas C. Schmidt and Bruno Haible. --------------------------------------- Manuals ------------------ GNU Smalltalk user guide by: Steve Byrne Paolo Bonzini GNU Smalltalk tutorial by: Andy Valencia --------------------------------------- Other goodies ------------ Cincom Inc. (part of network toolkit, XML packages) Mike Anderson (PostgreSQL driver) Tony Garnock-Jones, Brad Watson (Cairo and LibSDL bindings) Olivier Blanc (OpenGL bindings) Federico G. Stilman (STT) Daniele Sciascia (SQLite driver) Josh Miller (MySQL driver) Ken Treis, Travis Griggs and others (WikiWorks) Janko Mivsek and others (Swazoo) Avi Bryant, Philippe Marshall, Lukas Renggli and others (Seaside) Ramon Leon (SandstoneDb) Kazuki Yasumatsu (part of network toolkit) Aoki Atsushi (Lisp and Prolog interpreters) Didier Besset (Numerical methods library) The Refactory, Inc. (Refactoring Browser) --------------------------------------- Other contributors ------- Other contributors are listed in the THANKS file. smalltalk-3.2.5/libc.la.in0000644000175000017500000000065612123404352012265 00000000000000# libc.la - a libtool library file # Generated by GNU libtool # Created for GNU Smalltalk's dynamic loading mechanism. # The name that we can dlopen(3). dlname='@LIBC_SO_NAME@' # Names of this library. library_names='@LIBC_SO_NAME@' # Libraries that this one depends upon. dependency_libs='' # Is this an already installed library? installed=yes # Directory that this library needs to be installed in: libdir='@LIBC_SO_DIR@' smalltalk-3.2.5/packages/0000755000175000017500000000000012130456022012257 500000000000000smalltalk-3.2.5/packages/httpd/0000755000175000017500000000000012130456013013402 500000000000000smalltalk-3.2.5/packages/httpd/Makefile.frag0000644000175000017500000000116412123404352015703 00000000000000WebServer_FILES = \ packages/httpd/FileServer.st packages/httpd/Haiku.st packages/httpd/STT.st packages/httpd/WebServer.st packages/httpd/WikiServer.st packages/httpd/edit.jpg packages/httpd/example1.stt packages/httpd/example2.stt packages/httpd/find.jpg packages/httpd/head.jpg packages/httpd/help.jpg packages/httpd/history.jpg packages/httpd/next.jpg packages/httpd/prev.jpg packages/httpd/recent.jpg packages/httpd/rename.jpg packages/httpd/test.st packages/httpd/top.jpg packages/httpd/ChangeLog $(WebServer_FILES): $(srcdir)/packages/httpd/stamp-classes: $(WebServer_FILES) touch $(srcdir)/packages/httpd/stamp-classes smalltalk-3.2.5/packages/httpd/example1.stt0000644000175000017500000000037412123404352015577 00000000000000 {%= self class %}
    ' . &t2h_anchor('', $href, $entry) . '  ' . $descr . "
    ' . $entry . '' . $descr . "
    {% 1 to: 10 do: [ :each | %} {% ] %}
    {%= each printString %} {%= (each * 2) printString %}
    smalltalk-3.2.5/packages/httpd/WebServer.st0000644000175000017500000010210512123404352015576 00000000000000"====================================================================== | | Generic web-server framework | | ======================================================================" "====================================================================== | | Copyright 2000, 2001 Travis Griggs and Ken Treis | Written by Travis Griggs, Ken Treis and others. | Port to GNU Smalltalk, enhancements and refactoring by Paolo Bonzini. | | This file is part of GNU Smalltalk. | | GNU Smalltalk is free software; you can redistribute it and/or modify it | under the terms of the GNU General Public License as published by the Free | Software Foundation; either version 2, or (at your option) any later version. | | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS | FOR A PARTICULAR PURPOSE. See the GNU General Public License for more | details. | | You should have received a copy of the GNU General Public License along with | GNU Smalltalk; see the file COPYING. If not, write to the Free Software | Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. | ======================================================================" NetServer subclass: WebServer [ | virtualHosts defaultVirtualHost log | Version := nil. WebServer class >> version [ | number | Version isNil ifFalse: [^Version]. number := Smalltalk version subStrings detect: [:each | (each at: 1) isDigit] ifNone: ["???" '0.0']. ^Version := 'GNU-WikiWorks/' , number ] log: action uri: location time: time [ "self times nextPut: (Array with: action with: location with: time)" Transcript print: time; space; nextPutAll: action; space; print: location; nl ] log [ "self times" log isNil ifTrue: [log := WriteStream on: Array new]. ^log ] depth [ ^-1 ] addVirtualHost: aServlet [ virtualHosts addComponent: aServlet ] defaultVirtualHost [ ^defaultVirtualHost ] defaultVirtualHost: anHost [ virtualHosts rootServlet: (virtualHosts componentNamed: anHost). defaultVirtualHost := anHost ] handler [ ^virtualHosts rootServlet ] handler: aServlet [ aServlet name: self defaultVirtualHost. virtualHosts addComponent: aServlet; rootServlet: aServlet ] respondTo: aRequest [ | host handler | host := aRequest at: #HOST ifAbsent: [self defaultVirtualHost]. (virtualHosts hasComponentNamed: host) ifFalse: [host := self defaultVirtualHost]. (virtualHosts componentNamed: host) respondTo: aRequest ] initialize [ super initialize. virtualHosts := CompositeServlet new. virtualHosts parent: self. self defaultVirtualHost: Sockets.SocketAddress localHostName; handler: CompositeServlet new ] uriOn: aStream [ aStream nextPutAll: 'http:/' ] newSession [ ^WebSession new ] ] NetSession subclass: WebSession [ next [ ^WebRequest for: self socket ] log: req time: time [ self server log: req action uri: req location time: time ] ] Object subclass: Servlet [ | name parent | Servlet class >> named: aString [ ^(self new) name: aString; yourself ] depth [ ^parent depth + 1 ] name [ ^name ] name: aString [ name := aString ] parent [ ^parent ] parent: anObject [ parent := anObject ] uriOn: aStream [ self printOn: aStream ] printOn: aStream [ parent uriOn: aStream. self name isNil ifTrue: [^self]. aStream nextPut: $/. aStream nextPutAll: self name ] ] Servlet subclass: CompositeServlet [ | components rootServlet errorServlet | CompositeServlet class >> new [ ^self onError: ErrorServlet new ] CompositeServlet class >> onError: aServlet [ ^self onError: aServlet onRoot: ServletList new ] CompositeServlet class >> onError: aServlet onRoot: anotherServlet [ ^super new onError: aServlet onRoot: anotherServlet ] errorServlet [ ^errorServlet ] errorServlet: aServlet [ errorServlet := aServlet. aServlet parent: self ] rootServlet [ ^rootServlet ] rootServlet: aServlet [ rootServlet := aServlet. aServlet parent: self ] addComponent: aServlet [ components at: aServlet name put: aServlet. aServlet parent: self ] componentNamed: aString [ ^components at: aString ifAbsent: [errorServlet] ] components [ ^components copy ] hasComponentNamed: aString [ ^components includesKey: aString ] onError: aServlet onRoot: anotherServlet [ components := Dictionary new. self errorServlet: aServlet. self rootServlet: anotherServlet. anotherServlet parent: self ] respondTo: aRequest [ | componentName | aRequest location size < self depth ifTrue: [^rootServlet respondTo: aRequest]. componentName := aRequest location at: self depth. (self hasComponentNamed: componentName) ifFalse: [^errorServlet respondTo: aRequest]. ^(self componentNamed: componentName) respondTo: aRequest ] ] Servlet subclass: ServletList [ respondTo: aRequest [ | stream | stream := aRequest stream. parent components isEmpty ifTrue: [^(ErrorResponse unavailable) respondTo: aRequest; nl]. aRequest pageFollows. stream nextPutAll: 'Top page'; nl. stream nextPutAll: '

    Welcome to my server!!

    '; nl. stream nextPutAll: 'This server contains the following sites:'; nl. stream nextPutAll: '
      '; nl. parent components keys asSortedCollection do: [:each | stream nextPutAll: '
    • '; nextPutAll: each; nextPutAll: ''; nextPutAll: ', a '; print: (parent componentNamed: each) class; nl]. stream nextPutAll: '
    '; nl. stream nextPutAll: ''; nl; nl ] ] Servlet subclass: ErrorServlet [ respondTo: aRequest [ | response | response := parent components isEmpty ifFalse: [ErrorResponse notFound] ifTrue: [ErrorResponse unavailable]. (#('HEAD' 'GET' 'POST') includes: aRequest action) ifFalse: [response := ErrorResponse acceptableMethods: #('HEAD' 'GET' 'POST')]. response respondTo: aRequest ] ] Stream subclass: WebResponse [ | responseStream request | << anObject [ responseStream display: anObject ] nl [ responseStream nl ] nextPut: aCharacter [ responseStream nextPut: aCharacter ] nextPutUrl: aString [ responseStream nextPutAll: (URL encode: aString) ] nextPutAll: aString [ responseStream nextPutAll: aString ] do: aBlock [ self shouldNotImplement ] next [ self shouldNotImplement ] atEnd [ ^true ] isErrorResponse [ ^false ] modifiedTime [ ^DateTime now ] respondTo: aRequest [ responseStream := aRequest stream. request := aRequest. self notModified ifTrue: [self sendNotModifiedResponse] ifFalse: [self sendHeader. aRequest isHead ifFalse: [self sendBody]]. responseStream := request := nil ] notModified [ | ifModSince modTime | ifModSince := request dateTimeAt: #'IF-MODIFIED-SINCE' ifAbsent: [nil]. modTime := self modifiedTime. ^ifModSince notNil and: [modTime <= ifModSince] ] request [ ^request ] responseStream [ ^responseStream ] sendBody [ ] contentLength [ ^nil ] sendHeader [ | stream | stream := responseStream. responseStream := CrLfStream on: stream. self sendResponseType. self sendServerHeaders. self sendStandardHeaders. self sendModifiedTime. self sendMimeType. self sendHeaderSeparator. "Send the body as binary" responseStream := stream ] sendHeaderSeparator [ self nl ] sendNotModifiedResponse [ ^self nextPutAll: 'HTTP/1.1 304 Not modified'; sendServerHeaders; sendModifiedTime; sendHeaderSeparator; yourself ] sendMimeType [ self nextPutAll: 'Content-Type: text/html'; nl ] sendResponseType [ self nextPutAll: 'HTTP/1.1 200 Page follows'; nl ] sendServerHeaders [ self nextPutAll: 'Date: '; sendTimestamp: DateTime now; nl; nextPutAll: 'Server: '; nextPutAll: WebServer version; nl ] sendStandardHeaders [ | length | length := self contentLength. length isNil ifTrue: [request moreRequests: false] ifFalse: [self << 'Content-Length: '; << length; nl]. self << 'Connection: '; << (request at: #Connection); nl ] sendModifiedTime [ self << 'Last-Modified: '; sendTimestamp: self modifiedTime; nl ] sendTimestamp: aTimestamp [ | utc | utc := aTimestamp offset = Duration zero ifTrue: [aTimestamp] ifFalse: [aTimestamp asUTC]. self nextPutAll: aTimestamp dayOfWeekAbbreviation; nextPutAll: (aTimestamp day < 10 ifTrue: [', 0'] ifFalse: [', ']); print: aTimestamp day; space; nextPutAll: aTimestamp monthAbbreviation; space; print: aTimestamp year; space; print: aTimestamp asTime; nextPutAll: ' GMT' ] lineBreak [ self << '
    '; nl ] heading: aBlock [ self heading: aBlock level: 1 ] heading: aBlock level: anInteger [ self << ''. aBlock value. self << ''; nl ] horizontalLine [ self << '
    '; nl ] image: fileNameBlock linkTo: urlBlock titled: titleBlock [ self << ''.
	titleBlock value.
	self << '' ] image: fileNameBlock titled: titleBlock [ self << ''.
	titleBlock value.
	self << '' ] linkTo: urlBlock titled: titleBlock [ self << ''. titleBlock value. self << '' ] listItem: aBlock [ self << '
  • '. aBlock value. self << '
  • '; nl ] monospace: aBlock [ self << '
    '.
    	aBlock value.
    	self
    	    << '
    '; nl ] para: aBlock [ self << '

    '. aBlock value. self << '

    '; nl ] bold: aBlock [ self << ''. aBlock value. self << ''; nl ] italic: aBlock [ self << ''. aBlock value. self << ''; nl ] tr: aBlock [ self << ''. aBlock value. self << ''; nl ] td: aBlock [ self << ''. aBlock value. self << ''; nl ] ] Object subclass: WebRequest [ | originator stream action clientData postData location uri | EndOfLine := nil. EndOfRequest := nil. WebRequest class >> initialize [ EndOfLine := String with: Character cr with: Character nl. EndOfRequest := EndOfLine , EndOfLine ] WebRequest class >> for: aClientConnection [ ^self new initConnection: aClientConnection ] WebRequest class >> new [ ^super new initialize ] action [ ^action ] action: aString [ action := aString ] at: aSymbol [ ^clientData at: aSymbol ] at: aSymbol ifAbsent: aBlock [ ^clientData at: aSymbol ifAbsent: aBlock ] at: aSymbol ifPresent: aBlock [ ^clientData at: aSymbol ifPresent: aBlock ] dateTimeAt: aSymbol [ ^self parseTimestamp: (clientData at: aSymbol) ] dateTimeAt: aSymbol ifAbsent: aBlock [ ^self parseTimestamp: (clientData at: aSymbol ifAbsent: [^aBlock value]) ] dateTimeAt: aSymbol ifPresent: aBlock [ ^clientData at: aSymbol ifPresent: [:value | aBlock value: (self parseTimestamp: value)] ] enumeratePostData: aBlock [ postData keysAndValuesDo: aBlock ] getRequest [ | saveStream version | saveStream := stream. stream := CrLfStream on: saveStream. self extractAction. self extractLocation. version := stream upTo: Character cr. stream next. "Get nl" self extractClientData: version. (action sameAs: 'POST') ifTrue: [self extractPostData: version contentLength: (clientData at: #'CONTENT-LENGTH' ifAbsent: [nil])]. "Get back to binary mode" stream := saveStream ] hasPostData [ ^postData notEmpty ] postDataAt: aSymbol ifPresent: aBlock [ ^postData at: aSymbol ifPresent: aBlock ] location [ ^location ] isHead [ ^action sameAs: 'HEAD' ] originator [ ^originator ] pageFollows [ WebResponse new respondTo: self ] moreRequests [ ^(self at: #Connection) sameAs: 'keep-alive' ] moreRequests: aBoolean [ self at: #Connection put: (aBoolean ifTrue: ['Keep-Alive'] ifFalse: ['close']) ] postDataAt: aSymbol [ ^postData at: aSymbol ] postDataAt: aSymbol ifAbsent: aBlock [ ^postData at: aSymbol ifAbsent: aBlock ] stream [ ^stream ] stream: aStream [ stream := aStream. originator := stream remoteAddress name ] uri [ ^uri ] initConnection: aClientConnection [ | ec | self stream: aClientConnection; getRequest ] initialize [ postData := IdentityDictionary new. clientData := IdentityDictionary new. location := OrderedCollection new ] release [ stream flush. self moreRequests ifFalse: [stream close]. ^super release ] parseTimestamp: ts [ | tok d m y time | tok := ts subStrings. (tok at: 1) last = $, ifFalse: ["asctime: Sun Nov 6 08:49:37 1994" ts size = 5 ifFalse: [^nil]. m := (ts at: 2) asSymbol. d := (ts at: 3) asInteger. y := (ts at: 5) asInteger. time := ts at: 4. ^self makeTimestamp: d month: m year: y time: time]. (tok at: 1) size = 4 ifTrue: ["RFC 822: Sun, 06 Nov 1994 08:49:37 GMT" ts size = 6 ifFalse: [^nil]. d := (ts at: 2) asInteger. m := (ts at: 3) asSymbol. y := (ts at: 4) asInteger. time := ts at: 5. ^self makeTimestamp: d month: m year: y time: time]. "RFC 850 (obsolete): Sunday, 06-Nov-94 08:49:37 GMT" ts size = 4 ifFalse: [^nil]. d := ts at: 2. time := ts at: 3. d size = 9 ifFalse: [^nil]. y := (d at: 8) base10DigitValue * 10 + (d at: 9) base10DigitValue + 1900. m := (d copyFrom: 4 to: 6) asSymbol. d := (d at: 1) base10DigitValue * 10 + (d at: 2) base10DigitValue. ^self makeTimestamp: d month: m year: y time: time ] makeTimestamp: d month: m year: y time: t [ | month sec | t size = 8 ifFalse: [^nil]. month := #(#Jan #Feb #Mar #Apr #May #Jun #Jul #Aug #Sep #Oct #Nov #Dec) indexOf: m ifAbsent: [^nil]. sec := ((t at: 1) base10DigitValue * 10 + (t at: 2) base10DigitValue) * 3600 + (((t at: 4) base10DigitValue * 10 + (t at: 5) base10DigitValue) * 60) + ((t at: 7) base10DigitValue * 10 + (t at: 8) base10DigitValue). ^(DateTime newDay: d monthIndex: month year: y) addSeconds: sec ] at: aSymbol put: aValue [ ^clientData at: aSymbol put: aValue ] endOfLine [ ^EndOfLine ] endOfRequest [ ^EndOfRequest ] extractAction [ action := stream upTo: Character space ] extractClientData: clientVersion [ "Default depends on version" | rs | self at: #Connection put: (clientVersion = '1.0' ifTrue: ['close'] ifFalse: ['keep-alive']). rs := (stream upToAll: self endOfRequest) readStream. [rs atEnd] whileFalse: [self at: (rs upTo: $:) trimSeparators asUppercase asSymbol put: (rs upTo: Character cr) trimSeparators] ] extractLocation [ uri := (stream upToAll: 'HTTP/') trimSeparators. location := uri subStrings: $?. location isEmpty ifTrue: [self error: 'Empty uri: ' , uri , '.']. location size = 2 ifTrue: [self extractQueryData: (location at: 2)]. location := (location at: 1) subStrings: $/. location := location collect: [:each | URL decode: each]. location := location reject: [:each | each isEmpty] ] extractPostData: clientVersion contentLength: contentLength [ | s | clientVersion ~= '1.0' ifTrue: [stream nextPutAll: 'HTTP/1.1 100 Continue'; nl; nl]. (self at: #'CONTENT-TYPE' ifAbsent: [nil]) ~= 'application/x-www-form-urlencoded' ifTrue: [^self]. "TODO: Parse the stream directly, rather than loading it all into memory, because it could be large." s := contentLength notNil ifTrue: [stream next: contentLength asInteger] ifFalse: [stream upTo: Character cr]. ^self extractQueryData: s ] extractQueryData: query [ (query subStrings: $&) do: [:each | | pair | pair := each subStrings: $=. self postDataAt: (URL decode: pair first) asSymbol put: (URL decode: (pair at: 2 ifAbsent: ['']))] ] postDataAt: aSymbol put: aValue [ ^postData at: aSymbol put: aValue ] ] WebResponse subclass: ErrorResponse [ | errorCode additionalHeaders | ErrorNames := nil. ErrorDescriptions := nil. ErrorResponse class >> three [ ^#(#(300 'Multiple Choices' '

    The requested resource corresponds to any one of a set of representations. You can select a preferred representation.

    ') #(301 'Moved Permanently' '

    The requested resource has been assigned a new permanent URL and any future references to this resource should be done using one of the returned URLs.

    ') #(302 'Moved Temporarily' '

    The requested resource resides temporarily under a different URI. This is likely to be a response to a POST request which has to retrieve a fixed entity, since many clients do not interpret 303 responses (See Other) correctly.

    ') #(303 'See Other' '

    The response to the request can be found under a different URL and should be retrieved using the supplied Location.

    ') #(304 'Not Modified' '') #(305 'Use Proxy' '

    The requested resource must be accessed through the proxy given by the Location field.

    ')) ] ErrorResponse class >> four [ ^#(#(400 'Bad Request' '

    The request could not be understood by the server due to malformed syntax.

    ') #(401 'Unauthorized' '

    The request requires user authentication.

    ') #(402 'Payment Required' '

    This code is reserved for future use.

    ') #(403 'Forbidden' '

    The server understood the request, but is refusing to fulfill it.

    ') #(404 'Not Found' '

    The requested URL was not found on this server.

    ') #(405 'Method Not Allowed' '

    The specified method is not allowed for the resource identified by the specified URL.

    ') #(406 'Not Acceptable' '

    The resource identified by the request is only capable of generating response entities which have content characteristics not acceptable according to the accept headers sent in the request.

    ') #(407 'Proxy Authentication Required' '

    To proceed, the client must first authenticate itself with the proxy.

    ') #(408 'Request Timeout' '

    The client did not produce a request within the time that the server was prepared to wait.

    ') #(409 'Conflict' '

    The request could not be completed due to a conflict with the current state of the resource.

    ') #(410 'Gone' '

    The requested resource is no longer available at the server and no forwarding address is known. This condition should be considered permanent.

    ') #(411 'Length Required' '

    The server refuses to accept the request without a defined Content-Length header field.

    ') #(412 'Precondition Failed' '

    The precondition given in one or more of the request-header fields evaluated to false when it was tested on the server.

    ') #(413 'Request Entity Too Large' '

    The server is refusing to process a request because the request entity is larger than the server is willing or able to process.

    ') #(414 'Request-URI Too Long' '

    The server is refusing to service the request because the requested URL is longer than the server is willing to interpret. This condition is most likely due to a client''s improper conversion of a POST request with long query information to a GET request.

    ') #(415 'Unsupported Media Type' '

    The server is refusing to service the request because the entity of the request is in a format not supported by the requested resource for the requested method.

    ')) ] ErrorResponse class >> five [ ^#(#(500 'Internal Server Error' '

    The server encountered an unexpected condition which prevented it from fulfilling the request.

    ') #(501 'Not Implemented' '

    The server does not support the functionality required to fulfill the request. The server does not recognize the request method and is not capable of supporting it for any resource.

    ') #(502 'Bad Gateway' '

    The server, while acting as a gateway or proxy, received an invalid response from the upstream server it accessed in attempting to fulfill the request.

    ') #(503 'Service Unavailable' '

    The server is currently unable to handle the request due to a temporary overloading or maintenance of the server. This is a temporary condition.

    ') #(504 'Gateway Timeout' '

    The server, while acting as a gateway or proxy, did not receive a timely response from the upstream server it accessed in attempting to complete the request.

    ') #(505 'HTTP Version Not Supported' '

    The server does not support, or refuses to support, the HTTP protocol version that was used in the request message.

    ')) ] ErrorResponse class >> initialize [ ErrorNames := IdentityDictionary new. ErrorDescriptions := IdentityDictionary new. self initialize: self three. self initialize: self four. self initialize: self five ] ErrorResponse class >> initialize: arrayOfArrays [ arrayOfArrays do: [:array | ErrorNames at: (array at: 1) put: (array at: 2). ErrorDescriptions at: (array at: 1) put: (array at: 3)] ] ErrorResponse class >> nameAt: error [ ^ErrorNames at: error ifAbsent: [(error < 300 or: [error > 599]) ifTrue: [self nameAt: 500] ifFalse: [self nameAt: error // 100 * 100]] ] ErrorResponse class >> descriptionAt: error [ ^ErrorDescriptions at: error ifAbsent: [(error < 300 or: [error > 599]) ifTrue: [self descriptionAt: 500] ifFalse: [self descriptionAt: error // 100 * 100]] ] ErrorResponse class >> errorCode: code [ ^self new errorCode: code ] ErrorResponse class >> notModified [ ^self errorCode: 304 ] ErrorResponse class >> noContent [ ^self errorCode: 204 ] ErrorResponse class >> resetContent [ ^self errorCode: 205 ] ErrorResponse class >> unavailable [ ^self errorCode: 503 ] ErrorResponse class >> forbidden [ ^self errorCode: 403 ] ErrorResponse class >> notFound [ ^self errorCode: 404 ] ErrorResponse class >> gone [ ^self errorCode: 410 ] ErrorResponse class >> seeOtherURI: anotherURI [ ^(self errorCode: 303) addHeader: 'Location: ' , anotherURI; yourself ] ErrorResponse class >> movedTemporarilyTo: anotherURI [ ^(self errorCode: 302) addHeader: 'Location: ' , anotherURI; yourself ] ErrorResponse class >> movedPermanentlyTo: anotherURI [ ^(self errorCode: 301) addHeader: 'Location: ' , anotherURI; yourself ] ErrorResponse class >> unauthorized: aString [ ^(self errorCode: 401) addHeader: 'WWW-Authenticate: ' , aString; yourself ] ErrorResponse class >> acceptableMethods: anArray [ | header | header := String streamContents: [:s | s nextPutAll: 'Allow: '. anArray do: [:each | s nextPutAll: each] separatedBy: [s nextPutAll: ', ']]. ^(self errorCode: 405) addHeader: header; yourself ] isErrorResponse [ ^true ] errorCode: code [ errorCode := code. ^self ] addHeader: aString [ additionalHeaders isNil ifTrue: [additionalHeaders := OrderedCollection new]. ^additionalHeaders add: aString ] sendResponseType [ self << 'HTTP/1.1 '; << errorCode; space; << (self class nameAt: errorCode); nl ] sendStandardHeaders [ super sendStandardHeaders. additionalHeaders isNil ifTrue: [^self]. additionalHeaders do: [:each | self << each; nl] ] noMessageBody [ ^#(204 205 304) includes: errorCode ] sendBody [ | description | self noMessageBody ifTrue: [^self]. description := self class descriptionAt: errorCode. description isEmpty ifTrue: [^self]. self << ''; nl; << ''; << errorCode; space; << (self class nameAt: errorCode); << ''; nl; << ''; nl; heading: [self << errorCode; space; << (self class nameAt: errorCode)]; << description; << 'originator: '; << request originator displayString; lineBreak; << 'action: '; << request action displayString; lineBreak; << 'location: '. request location do: [:each | self << $/ << each]. request enumeratePostData: [:key :val | self lineBreak; << key; << ' = '; nl; << val; nl]. self lineBreak; horizontalLine; italic: [self << WebServer version]; << '' ] ] Object subclass: WebAuthorizer [ | authorizer | WebAuthorizer class >> fromString: aString [ ^self new authorizer: aString ] WebAuthorizer class >> loginID: aLoginID password: aPassword [ ^(self new) loginID: aLoginID password: aPassword; yourself ] authorize: aRequest [ | trial | trial := aRequest at: #AUTHORIZATION ifAbsent: [nil]. ^trial = self authorizer ] authorizer [ ^authorizer ] authorizer: aString [ authorizer := aString ] challengeFor: aServlet [ ^'Basic realm="%1"' % {aServlet name} ] authorize: aRequest in: aServlet ifAuthorized: aBlock [ ^(self authorize: aRequest) ifTrue: [aBlock value] ifFalse: [(ErrorResponse unauthorized: (self challengeFor: aServlet)) respondTo: aRequest. ^nil] ] loginID: aName password: aPassword [ "(self loginID: 'aName' password: 'aPassword') authorizer = 'Basic YU5hbWU6YVBhc3N3b3Jk'" | plain plainSize i chars stream | aName isNil | aPassword isNil ifTrue: [^nil]. chars := 'ABCDEFGHIJKLMNOPQRSTUVWXYZabcdefghijklmnopqrstuvwxyz0123456789+/'. plain := (aName , ':' , aPassword) asByteArray. plainSize := plain size. plain size \\ 3 = 0 ifFalse: [plain := plain , (ByteArray new: 3 - (plain size \\ 3))]. i := 1. stream := WriteStream on: String new. stream nextPutAll: 'Basic '. [i < plain size] whileTrue: [stream nextPut: (chars at: (plain at: i) // 4 + 1); nextPut: (chars at: (plain at: i) \\ 4 * 16 + ((plain at: i + 1) // 16) + 1); nextPut: (chars at: (plain at: i + 1) \\ 16 * 4 + ((plain at: i + 2) // 64) + 1); nextPut: (chars at: (plain at: i + 2) \\ 64 + 1). i := i + 3]. authorizer := stream contents. i := authorizer size. plain size - plainSize timesRepeat: [authorizer at: i put: $=. i := i - 1] ] ] Character extend [ base10DigitValue [ ^self isDigit ifTrue: [self asciiValue - 48] ifFalse: [0] ] ] Eval [ ErrorResponse initialize. WebRequest initialize ] smalltalk-3.2.5/packages/httpd/FileServer.st0000644000175000017500000005717412123404352015757 00000000000000"====================================================================== | | File server plug-in | | ======================================================================" "====================================================================== | | Copyright 2000, 2001, 2008 Travis Griggs and Ken Treis | Written by Travis Griggs, Ken Treis and others. | Port to GNU Smalltalk, enhancements and refactory by Paolo Bonzini. | | This file is part of GNU Smalltalk. | | GNU Smalltalk is free software; you can redistribute it and/or modify it | under the terms of the GNU General Public License as published by the Free | Software Foundation; either version 2, or (at your option) any later version. | | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS | FOR A PARTICULAR PURPOSE. See the GNU General Public License for more | details. | | You should have received a copy of the GNU General Public License along with | GNU Smalltalk; see the file COPYING. If not, write to the Free Software | Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. | ======================================================================" WebResponse subclass: FileSystemResponse [ | file | FileSystemResponse class >> file: aFile [ ^self new file: aFile ] file: aFile [ file := aFile ] modifiedTime [ ^file lastModifyTime ] ] FileSystemResponse subclass: DirectoryResponse [ chopName: aString [ ^aString size > self maxNameLength ifTrue: [(aString copyFrom: 1 to: self maxNameLength - 3) , '...'] ifFalse: [aString] ] maxNameLength [ ^30 ] maxSizeLength [ ^6 ] sendMetaHeaders [ "While caching of file responses is generally desirable (even though it can be incorrect if somebody does some uploading), caching directory responses can be extremely confusing and could yield incorrect uploads (where someone thinks he uploaded something and actually didn't)" self << ''; nl. self << ''; nl ] sendBody [ self << 'Directory Listing for '; << request uri; << ''; nl; sendMetaHeaders; << '

    Directory Contents:

    ';
    	    nl;
    	    << 'Name';
    	    next: self maxNameLength - 1 put: $ ;
    	    << 'Modified on	       Size';
    	    nl;
    	    << '
    '; nl. (File name: file name) entryNames asSortedCollection do: [:each | self sendFileProperties: each]. self << '

    '; nl. self << ''; nl. self << '
    '; nl. self << '' ] sendFileProperties: each [ | isDirectory choppedName name subDirFile parent slash | each = '.' ifTrue: [^self]. subDirFile := file / each. subDirFile isReadable ifFalse: [^self]. isDirectory := subDirFile isDirectory. choppedName := isDirectory ifTrue: [self chopName: (each copyWith: $/)] ifFalse: [self chopName: each]. each = '..' ifTrue: [slash := request uri findLast: [:each | each == $/]. slash = 1 ifTrue: [^self]. self << '' << choppedName << ''. self next: self maxNameLength - choppedName size + 3 put: $ . self sendModifyTimeFor: subDirFile. isDirectory ifFalse: [self sendFileSizeFor: subDirFile]. self nl ] sendModifyTimeFor: aFile [ | date | date := aFile lastModifyTime at: 1. date day < 10 ifTrue: [self nextPut: $0]. self << date << ' ' ] sendFileSizeFor: aFile [ | size type printString | size := [aFile size] on: Error do: [:ex | ex return: nil]. size isNil ifTrue: [^self]. printString := String new: self maxSizeLength withAll: $ . type := #('Bytes' 'KB' 'MB' 'GB' 'TB') detect: [:each | | found | found := size < 10000. found ifFalse: [size := (size + 512) // 1024]. found] ifNone: [^self next: self maxSizeLength put: $*; << ' huge!']. printString := printString , size rounded printString. printString := printString copyFrom: printString size + 1 - self maxSizeLength. self << printString; space; << type ] ] DirectoryResponse subclass: UploadResponse [ respondTo: aRequest [ self doUpload: aRequest. super respondTo: aRequest ] doUpload: aRequest [ "This is not a general multipart/form-data parser. The only things it lacks is the ability to parse more than one field (with the last boundary identified by two trailing dashes) and to build a dictionary with the contents of each form field." | boundary str i remoteName uploadStream subHeaders | request := aRequest. boundary := self boundaryString. boundary isNil ifTrue: [^self]. (request stream) skipToAll: boundary; nextLine. subHeaders := self getSubHeaders. subHeaders isEmpty ifTrue: [^self]. str := subHeaders at: #'CONTENT-DISPOSITION' ifAbsent: ['']. i := str indexOfSubCollection: 'filename="' ifAbsent: [0]. i = 0 ifTrue: [^self]. i := i + 10. (str at: i) == $" ifTrue: [^self]. remoteName := str copyFrom: i to: (str indexOf: $" startingAt: i) - 1. remoteName := URL decode: remoteName. "### not sure about this..." uploadStream := (self localFileFor: remoteName) writeStream. "Collect at least 128 bytes of content (of course, stop if we see a boundary). We need this quantity because M$ Internet Explorer 4.0 for Mac appends 128 bytes of Mac file system info which we must remove." boundary := boundary precompileSearch. str := self nextChunk. [i := boundary searchIn: str startingAt: 1. i notNil and: [str size < 128]] whileTrue: [str := str , self nextChunk]. ((str at: 1) asciiValue = 0 and: [(str at: 2) asciiValue = remoteName size and: [(str copyFrom: 3 to: remoteName size + 2) = remoteName]]) ifTrue: [str := str copyFrom: 129 to: str size. i := i - 128]. "Now do the real work" [i > 0] whileFalse: [request stream isPeerAlive ifFalse: [uploadStream close. (self localFileFor: remoteName) remove. ^self]. "While we don't encounter a chunk which could contain the boundary, copy at maximum speed." [i := boundary possibleMatchSearchIn: str startingAt: 5. i > 0] whileFalse: [uploadStream nextPutAll: str. str := self nextChunk]. "The boundary could be here. We have to look more carefully." i := boundary searchIn: str startingAt: i - 4. i > 0 ifFalse: ["Not found, but it might finish in the next chunk..." uploadStream nextPutAll: (str copyFrom: 1 to: i - 5). str := (str copyFrom: i - 4 to: str size) , self nextChunk. i := boundary searchIn: str startingAt: 1]]. "Save the last chunk in the file (the first if we didn't go through the while loop." i > 5 ifTrue: [uploadStream nextPutAll: (str copyFrom: 1 to: i - 5)]. "Clean things up..." uploadStream close ] nextChunk [ request stream isPeerAlive ifFalse: [^'']. ^request stream nextAvailable: 1024 ] localFileFor: remoteName [ | idx fileName | idx := remoteName findLast: [:each | ':/\' includes: each]. fileName := remoteName copyFrom: idx + 1. ^file at: fileName ] getSubHeaders [ | hdr subHeaders line colon | subHeaders := LookupTable new. [line := request stream nextLine. colon := line indexOf: $:. colon = 0] whileFalse: [subHeaders at: (line copyFrom: 1 to: colon - 1) asUppercase asSymbol put: (line copyFrom: colon + 1) trimSeparators]. ^subHeaders ] boundaryString [ "Decode multipart form data boundary information from a header line that looks like the following line: Content-Type: multipart/form-data; boundary=-----" | str | str := (request at: #'CONTENT-TYPE' ifAbsent: ['']) readStream. (str upTo: $;) = 'multipart/form-data' ifFalse: [^nil]. str skipTo: $=. "Boundary lines *always* start with two dashes" ^'--' , str upToEnd ] ] FileSystemResponse subclass: FileResponse [ | fileStream | FileResponse class >> file: aFile [ ^ [| fileStream | fileStream := aFile readStream. (super file: aFile) fileStream: fileStream; yourself] on: Error do: [:ex | ex return: ErrorResponse forbidden] ] mimeType [ ^ContentHandler contentTypeFor: file name ] respondTo: aRequest [ [super respondTo: aRequest] ensure: [fileStream close] ] sendBody [ | size data read | size := fileStream size. [size > 0] whileTrue: [data := fileStream next: (read := size min: 2000). size := size - read. self nextPutAll: data] ] contentLength [ ^fileStream size ] sendMimeType [ self << 'Content-Type: '; << self mimeType; nl ] sendStandardHeaders [ super sendStandardHeaders. self << 'Accept-Ranges: bytes'; nl ] fileStream: aStream [ fileStream := aStream ] ] FileResponse subclass: RangeResponse [ | range | RangeResponse class >> file: aFile range: aRangeSpecification [ | response | response := self file: aFile. ^response isErrorResponse ifTrue: [response] ifFalse: [response range: aRangeSpecification] ] range: aRangeSpecification [ range := aRangeSpecification. range fileSize: fileStream size ] sendBody [ self sendBody: range ] sendBody: range [ | size data read | size := range last - range first + 1. fileStream position: range first. [size > 0] whileTrue: [data := fileStream next: (read := size min: 2000). size := size - read. self nextPutAll: data] ] sendStandardHeaders [ super sendStandardHeaders. range sendStandardHeadersOn: self ] contentLength [ ^range last - range first + 1 ] ] RangeResponse subclass: MultiRangeResponse [ | mimeType boundary | getBoundary [ ^'------%1-!-GST-!-%2' % {Time secondClock. Time millisecondClock} ] mimeType [ "Cache the MIME type as computed by the FileResponse implementation" mimeType isNil ifTrue: [mimeType := super mimeType]. ^mimeType ] sendBody [ range do: [:each | self << '--'; << boundary; nl. self << 'Content-type: '; << self mimeType; nl. each sendStandardHeadersOn: self; nl. self sendBody: each]. self << '--'; << boundary; << '--'; nl ] sendMimeType [ boundary := self getBoundary. self << 'Content-type: multipart/byteranges; boundary='; << boundary; nl ] contentLength [ ^nil ] ] Object subclass: RangeSpecification [ RangeSpecification class >> on: aString [ "Parse the `Range' header field, answer an instance of a subclass of RangeSpecification. From RFC 2068 (HTTP 1.1) -- 1# means comma-separated list with at least one element: byte-ranges-specifier = bytes-unit '=' byte-range-set byte-range-set = 1#( byte-range-spec | suffix-byte-range-spec ) byte-range-spec = first-byte-pos '-' [last-byte-pos] first-byte-pos = 1*DIGIT last-byte-pos = 1*DIGIT suffix-byte-range-spec = '-' suffix-length suffix-length = 1*DIGIT' " | stream partial current n first which ch | stream := ReadStream on: aString. partial := nil. which := #first. "Read the unit" (stream upToAll: 'bytes=') isEmpty ifFalse: [^nil]. stream atEnd ifTrue: [^nil]. [n := nil. [ch := stream atEnd ifTrue: [$, "Fake an empty entry at end"] ifFalse: [stream next]. ch isDigit] whileTrue: [n := n isNil ifTrue: [ch digitValue] ifFalse: [n * 10 + ch digitValue]]. ch == $- ifTrue: ["Check for invalid range specifications" which == #last ifTrue: [^nil]. which := #last. first := n]. ch == $, ifTrue: ["Check for invalid range specifications" which == #first ifTrue: [^nil]. first > n ifTrue: [^nil]. n = -1 & (first = -1) ifTrue: [^nil]. which := #first. current := SingleRangeSpecification new. current first: first; last: n. partial := partial isNil ifTrue: [current] ifFalse: [partial , current]. stream atEnd ifTrue: [^partial]]] repeat ] , anotherRange [ self subclassResponsibility ] do: aBlock [ self subclassResponsibility ] fileSize: size [ self subclassResponsibility ] sendStandardHeadersOn: aStream [ ] printOn: aStream [ self do: [:each | each sendStandardHeadersOn: aStream] ] ] RangeSpecification subclass: SingleRangeSpecification [ | first last size | first [ ^first ] last [ ^last ] first: anInteger [ first := anInteger ] last: anInteger [ last := anInteger ] , anotherRange [ ^(MultiRangeSpecification with: self) , anotherRange; yourself ] do: aBlock [ aBlock value: self ] fileSize: fSize [ size := fSize. "-500: first = nil, last = 500" first isNil ifTrue: [first := last + size - 1. last := size - 1]. "9500-: first = 9500, last = nil" last isNil ifTrue: [last := size - 1] ] sendStandardHeadersOn: aStream [ aStream << 'Content-range: bytes ' << first << $- << last << $/ << size. aStream nl ] size [ ^1 ] ] RangeSpecification subclass: MultiRangeSpecification [ | subranges | MultiRangeSpecification class >> with: aRange [ ^(self new initialize) , aRange; yourself ] initialize [ subranges := OrderedCollection new ] , anotherRange [ anotherRange do: [:each | subranges add: each]. ^self ] do: aBlock [ subranges do: aBlock ] fileSize: fSize [ self do: [:each | each fileSize: fSize] ] sendStandardHeadersOn: aStream [ ] size [ ^subranges size ] ] Servlet subclass: FileWebServer [ | initialDirectory uploadAuthorizer | FileWebServer class >> named: aString [ ^self new name: aString ] FileWebServer class >> named: aString directory: dirString [ ^(self new) name: aString; directory: dirString; yourself ] FileWebServer class >> new [ ^(super new) initialize; yourself ] fileResponse: file request: aRequest [ | range | range := aRequest at: #RANGE ifAbsent: [nil]. range isNil ifTrue: [^FileResponse file: file]. range := RangeSpecification on: range. range size = 1 ifTrue: [^RangeResponse file: file range: range]. ^MultiRangeResponse file: file range: range ] directoryResponse: aDirectory request: aRequest [ | listable | listable := aDirectory isReadable. (aRequest action sameAs: 'POST') ifTrue: [^listable ifTrue: [self uploadResponse: aDirectory request: aRequest] ifFalse: [ErrorResponse acceptableMethods: #('HEAD' 'GET')]]. ^(self indexResponse: aDirectory request: aRequest) ifNil: [listable ifTrue: [DirectoryResponse file: aDirectory] ifFalse: [ErrorResponse forbidden]] ] indexResponse: aDirectory request: aRequest [ self indexFileNames do: [:each | | indexFile | indexFile := aDirectory / each. indexFile isReadable ifTrue: [^self fileResponse: indexFile request: aRequest]]. ^nil ] respondTo: aRequest [ | response | response := (#('HEAD' 'GET' 'POST') includes: aRequest action asUppercase) ifTrue: [self responseFor: aRequest] ifFalse: [ErrorResponse acceptableMethods: #('HEAD' 'GET' 'POST')]. response isNil ifFalse: [response respondTo: aRequest] ] responseFor: aRequest [ | file path | path := aRequest location. file := initialDirectory. path from: self depth to: path size do: [:each | (self isValidName: each) ifFalse: [^ErrorResponse notFound]. file isDirectory ifFalse: [^ErrorResponse notFound]. file := file directoryAt: each. file isReadable ifFalse: [^file isDirectory ifTrue: [ErrorResponse notFound] ifFalse: [ErrorResponse forbidden]]]. file isDirectory ifTrue: [^self directoryResponse: file request: aRequest]. ^self fileResponse: file request: aRequest ] directory: aDirectory [ initialDirectory := File name: aDirectory ] indexFileNames [ ^#('index.html' 'index.htm' 'default.html' 'default.htm') ] initialize [ initialDirectory := Directory working. uploadAuthorizer := WebAuthorizer new. name := 'File' ] isValidName: aString [ "Don't allow people to put strange characters or .. in a file directory. If we allowed .., then someone could grab our password file." ^(aString indexOfSubCollection: '..') = 0 and: [aString conform: [:each | each asInteger >= 32 and: [each asInteger < 127]]] ] uploadAuthorizer [ ^uploadAuthorizer ] uploadAuthorizer: aWebAuthorizer [ uploadAuthorizer := aWebAuthorizer ] uploadLoginID: aLoginID password: aPassword [ uploadAuthorizer := WebAuthorizer loginID: aLoginID password: aPassword ] uploadResponse: aDirectory request: aRequest [ ^uploadAuthorizer authorize: aRequest in: self ifAuthorized: [UploadResponse file: aDirectory] ] ] CharacterArray extend [ precompileSearch [ "Compile the receiver into some object that answers #searchIn:startingAt: and #possibleMatchSearchIn:startingAt:" | encoding size | size := self size. encoding := size > 254 ifTrue: [Array new: 513 withAll: size] ifFalse: [ByteArray new: 513 withAll: size]. "To find the last char of self, moving forwards" 1 to: size do: [:i | encoding at: 2 + (self valueAt: i) put: size - i]. "To find the first char of self, moving backwards" size to: 1 by: -1 do: [:i | encoding at: 258 + (self valueAt: i) put: i - 1]. ^Array with: self with: encoding ] boyerMooreSearch: string encoding: encoding startingAt: minPos [ | idx searchSize size ofs | searchSize := encoding at: 1. idx := minPos + searchSize - 1. size := self size. [idx < size] whileTrue: [ofs := encoding at: 2 + (self valueAt: idx). ofs = 0 ifTrue: ["Look behind for the full searched string" ofs := searchSize. [(ofs := ofs - 1) == 0 ifTrue: [^idx - searchSize + 1]. (string at: ofs) == (self at: idx - searchSize + ofs)] whileTrue. "Sorry not found... yet" ofs := 1]. idx := idx + ofs]. ^0 ] boyerMoorePossibleMatchSearch: encoding startingAt: minPos [ | idx searchSize ofs result | searchSize := encoding at: 1. idx := self size. result := 0. [idx > minPos] whileTrue: [ofs := encoding at: 258 + (self valueAt: idx). ofs = 0 ifTrue: [result := idx. ofs := 1]. idx := idx - ofs]. ^result ] ] ArrayedCollection extend [ searchIn: aString startingAt: minPos [ "Same as `aString indexOfSubCollection: ... ifAbsent: [ 0 ]', where the searched string is the string that was precompiled in the receiver. Optimized for minPos < self size - minPos (otherwise, you're likely to win if you first use #possibleMatchSearchIn:startingAt:)" ^aString boyerMooreSearch: (self at: 1) encoding: (self at: 2) startingAt: minPos ] possibleMatchSearchIn: aString startingAt: minPos [ "Search for the first possible match starting from the minPos-th item in the string that was precompiled in the receiver. This is not necessarily the first occurrence of the first character (a later occurrence, or none at all, could be returned if the algorithm discovers that the first cannot be part of a match). Optimized for minPos > self size - minPos (otherwise, you're likely to win if you use #searchIn:startingAt: directly)" ^aString boyerMoorePossibleMatchSearch: (self at: 2) startingAt: minPos ] ] WebServer class extend [ publishMyHomeDir [ "WebServer myHomeDirWiki" | handler name dir | self terminateServer: 8080. name := '~' , (File stripPathFrom: Directory home). dir := Directory home , '/pub-www'. "Add a file server on a particular directory." handler := (self initializeServer: 8080) handler. handler addComponent: (FileWebServer named: name directory: dir) ] ] smalltalk-3.2.5/packages/httpd/rename.jpg0000644000175000017500000000437012123404352015300 00000000000000ÿØÿàJFIFÿÛCÿÛCÿÀ$/"ÿÄ ÿĵ}!1AQa"q2‘¡#B±ÁRÑð$3br‚ %&'()*456789:CDEFGHIJSTUVWXYZcdefghijstuvwxyzƒ„…†‡ˆ‰Š’“”•–—˜™š¢£¤¥¦§¨©ª²³´µ¶·¸¹ºÂÃÄÅÆÇÈÉÊÒÓÔÕÖרÙÚáâãäåæçèéêñòóôõö÷øùúÿÄ ÿĵw!1AQaq"2B‘¡±Á #3RðbrÑ $4á%ñ&'()*56789:CDEFGHIJSTUVWXYZcdefghijstuvwxyz‚ƒ„…†‡ˆ‰Š’“”•–—˜™š¢£¤¥¦§¨©ª²³´µ¶·¸¹ºÂÃÄÅÆÇÈÉÊÒÓÔÕÖרÙÚâãäåæçèéêòóôõö÷øùúÿÚ ?þþ(£ ô9¦HÛRFUþ!I ´“od)ÉöÇ9={c?Jæ ñ¯„®¼WàX;\ÚkÇÅ™bð§„?á(kû=Jüø7H½ñ Èð¥…ô H·Öí¯õ/†¼µºvKa Ú>›©Çg¬Øþ}Šñ *¡‰XxRœªB§,î¶ŽÍÆÛ»ÚÉùŸÊ9ßÒÓ‚²Üádôp5êWÃbÕ CšøiŸÎTÔnÜÔ¹m¾·±ýà™Ÿ|gôö¤¶pÃ>£§zðÿÙËâÆ£ñ¿àï„>$êÞÔ¼âIšãEÔˆ²»žÄêz]×–†ÿÃ׿fû^›rñ[ËqcyÓ[ZÌïo¹ó^q𯻣V5éR­M·N¬T––ѤÖUæQåøì>gÂf8V冯ӅZm§á4¥ÓÕ;5  cŒsþ¿Nô‡n}Ý@9È'Ö²uÝMt=WÖš'4.ÿRku`*ÙZKtÑ …fm‚lkàwýµüu¥à%>ßjzŸ‹¼'àŸ‰Z–“á]Kâwï´?‡¿µ ?ÂÓ½ÿƒ¾ßi6þ4ß¡ø±¯,5WCÑá]&Ý­¼Iz“ݾñT0¶öÒåRÚɾˢ}ö9ñù¶,åxÊ’‚¨´´%%ºZò§Õúï½Oñoì ûxëĚNjü[û:|+×|Iâ éõ=kY¾ðž5ö§¨Ü±{›ëÙ¼œÏu#’]Û,Ç’I5ò®Ÿÿ¢ø#aûQIñSLð¿‚ü5ðkOðŸ„cÓ>xw@·²¶Ô> hW¾17¾!Ö\ÚmM>MÄV–ín¼Í æë\Å7¹Û#ÄÚ{ÞÞxŸá¿…|=áýoÂß5ø…â}Rñ&©ð§â¯‚~/†üWá¯|¹½Ð5=wÅ?|0º4:~,½¹7j,Eé¶¶¹âµOۿǶ~¿Ö`ø¦¯‰=½ÅÜp<²x•èdåNUp´ý¤$ª«S÷Ú³•£v›’v{ïmÎóL‡Ã Ç…¯ŒÈ°¿YÃU†58ác’–Ѝã)F~ÑMEé-¶gé-½¼¶ðÚÚý´(‘E H±Çq€ˆ‘¢ð *€ÀíVç™^>µùûã_Û'Ç>Ôµë4ûÿ‰Ðxî_ éš„üCñWÇþ½ðÔ^ÑŸÄ:‘­ÜxoÄVËe¯èêº}½ôº.¹f’2Úêö²NÐ\Æ‚Onê“ìÑÅáëÎtèÎò¢ìÒMYéî»Ù]u].~…—æùv:­l&¥ê`ýÙÕǒÖ\®é$㢲ÙXݺ´¶½³¹³»†;‹K»imn­åPÑOo1Ñ52ËÃz]µ•ö‘ñûþ½>îÞ+p·6ÚËxwCmM\7Û_Jî<Ç@ÔQY*T¹ ýœoËkÙmîé±TÂ7ÌðÔÜ­~HÞÊÖW¶Ë¢Ùü]ðgáO!¿O|>ð§‰?´õ];^¼“VѬîî$×4½%´ b;©"ó-µH´)f±[ˆÝ%ûĶ¥ÌÉwúf—¦h:f£hšuŽ‘£é6Všf•¥i–Xiºf›an–¶6}¬i•”6±EQF«qÆ¨Šª¢ŠÑB”¥$å»I]ï¹¥*4©Î¬éÒŒ%7«QI½[Õ¥w¯sÿÙsmalltalk-3.2.5/packages/httpd/top.jpg0000644000175000017500000000340612123404352014632 00000000000000ÿØÿàJFIFÿÛCÿÛCÿÀ$/"ÿÄ ÿĵ}!1AQa"q2‘¡#B±ÁRÑð$3br‚ %&'()*456789:CDEFGHIJSTUVWXYZcdefghijstuvwxyzƒ„…†‡ˆ‰Š’“”•–—˜™š¢£¤¥¦§¨©ª²³´µ¶·¸¹ºÂÃÄÅÆÇÈÉÊÒÓÔÕÖרÙÚáâãäåæçèéêñòóôõö÷øùúÿÄ ÿĵw!1AQaq"2B‘¡±Á #3RðbrÑ $4á%ñ&'()*56789:CDEFGHIJSTUVWXYZcdefghijstuvwxyz‚ƒ„…†‡ˆ‰Š’“”•–—˜™š¢£¤¥¦§¨©ª²³´µ¶·¸¹ºÂÃÄÅÆÇÈÉÊÒÓÔÕÖרÙÚâãäåæçèéêòóôõö÷øùúÿÚ ?þþ(¢ŠBy#pGõ¤ ¤¬ G§^ß…|EûþØ>ýŒ?g¯|Jº–ÂóÇ:œoá¿…Þ¼w'Ä>4Ô`—ìFh!*í£ØÂ“_ß°x¶ÓÚ•.n-Õÿ> |cý´¿àž?¾|sý°|gãÏ|ý­4ÓÄ;ok^%ÖÛá7ˆuZëYÓn.t­AÚ?xŽÏE¼¶Ôg±µ‚šÆëYÓ-í$¹Òb•>{1â.]¥…)Õ£*õ#ðaã9(S•O)IôÕE7±ù'x½’ðಠF_ˆÇÓŒiṮtRt2š8Š‘£†«ŒÝ¥V¤¶Ž°¦FœlXTU3R°Ö4ë-WK¼µÔ4íFÖÞöÆúÊx®¬îí.¢IíîmnafK‹y"‘««†RA¯WÐ&šM;§ª?Y„áR©NJtæ“‹N馮škFšÕ0¢Š)”|Wñïöø/ûJübø]ñ‹âÝ÷üIuðŠk[¯x MnÅ~­Ý¾©±=Þ«á·ÑÙõ9nï-tÁzç˺‡G¶¶™Ý7öOÚözøgûMü&ñ'Á¿ŠºDšŸ„¼G²¼–R¥ž±¤_Ø\Gw¦kZ bìíZÚî(Þ)6:0ß ñÍo,ÐÉó×ÄÏÚ'âgÃ?Œß´%²iþñÃo…_³ïÁˆV æ¡q£jïâÏx»öƒðñ“û^Û@¹û>‘uwà/E¨Ï9–-*ÇKkëkk‰e¹…’ÿöœø§¦ø×@øAsá_OñZøÉoð±üG¯âð-¶›ª~Îÿ¾=Yx£ì2ifòMVØxãM›FûH-ͽðÕ-õ`µñå,µKNXkK'·…ý«÷ “ÞêJ2QòOcó:¸¾§W=ÃbrxÆ·Õ• rgŒ’u0ñUož2*‘¤´J0v庿џ³ïÁ ösøSáoƒ¾ñŒ|Iá_[ͧørãÇZµ¦·®iúCNóZh‹¨Úé¶Þv—h²¬ÑÑšÞÝ#¶Gò"†8ý§ž§§aÎyë‘^Gð+â=ïÅŸ…þñΩ¥Z躭üúþ•«éÖrjdzÏ…|G«xOWŸEÔf¶…õ }KDºžÂáá‰ç²¹‚WÊ]¯G ¨ªV<´#È»FÉÅ+뵺Éã—Ã*Ë£•STrØÐ¤°ðWJ4y³I6ÚJµÝìQEnzG¯ü)øiâ½u¼MâoøO_×äðö¡áWWдíBòóº¬w꿚êÝþ‡,Zޤ­k6ø6ê—@ 3‰<«Ä_²GÀ_ZøKoèº7‡~|CÔ>'Úø[AÒt=?Ãþ$ñV¡ðçÆ_ ^çŶM¥HÚ¨‹AñœóA,r[ÝÅw il·_g´6Ò”W<éR“|ÔâîÕî–ºÃ}<—Üx¹ŽRÕ0Tg)T¦ÛtàÛ~Ö“»n:³ßôM EðÖ‘¦xÚN› è:-¶™£èº5®™¤éZu”)mga¦éÖq$66PÛÇqE,q¢E ´Q[¤’I+$zôãB„T!’I$’JÉ$´I-?ÿÙsmalltalk-3.2.5/packages/httpd/edit.jpg0000644000175000017500000000376712123404352014767 00000000000000ÿØÿàJFIFÿÛCÿÛCÿÀ$/"ÿÄ ÿĵ}!1AQa"q2‘¡#B±ÁRÑð$3br‚ %&'()*456789:CDEFGHIJSTUVWXYZcdefghijstuvwxyzƒ„…†‡ˆ‰Š’“”•–—˜™š¢£¤¥¦§¨©ª²³´µ¶·¸¹ºÂÃÄÅÆÇÈÉÊÒÓÔÕÖרÙÚáâãäåæçèéêñòóôõö÷øùúÿÄ ÿĵw!1AQaq"2B‘¡±Á #3RðbrÑ $4á%ñ&'()*56789:CDEFGHIJSTUVWXYZcdefghijstuvwxyz‚ƒ„…†‡ˆ‰Š’“”•–—˜™š¢£¤¥¦§¨©ª²³´µ¶·¸¹ºÂÃÄÅÆÇÈÉÊÒÓÔÕÖרÙÚâãäåæçèéêòóôõö÷øùúÿÚ ?þþ(¢³µmWNÐôëÝ_W¾´ÓtÍ2ÒâÿPÔ/î"´²²²´…纻»ºÖ8-£†7ww`¨ªYˆ4›I]»$Lçp”æùavÞÉw/Hé—‘•cPK8sô㟥~süjý¿~øgãÏex¯ÂÐ|Rø‰¤x—POkñÞjžðZiv^ ƒKŽít¹"OøŠãÄzÝ¿öQ¿Ó#Ž 2úK­JÚñtí?Tùö¢ÿ‚‚\øçÄïÁÏÿÂCᯆ¾#Õu…ÿð²ü3÷ü'š§Œ4Ùx;Å'Ã:Eåµì^´×Ú]álä²ñ«6§2ø{QÑu«¯Ž2fø%V‘ãÛëßµ¿…íµ‡ž0»¿øcà±y{Ý.ÎOøOHH,õÝ/@›LÑžÎÙ­,ô±ÚèZ>¢¿ü3ò˜ÌßĬKOÚ¸É{Z²Ò1JKš)ÛK¤ìþãð~ ñˆ8“6¥Ã~aV)ЭŒÆNñ¥J1šöR¶ŽP½¤µod~°þÍ?¼AñGÀ·“x²ëÃ:ljü'â-WÂïŠ| ®¿ü]y£¼EÓM¶†ÊÆÞ+[[tXâ†XbPaDq Â ÇáÁ¸Iè;úcŒ{µôÔc(S§²ç©“}߯_™û^Y‡Äa°\>3ñ8špJSîÕ·}}]›Üð9}züûŠù{öŽø{ñ§âtžð×Ã_xOž¶× ñ7õmxøž÷TÕ†õMRðï„4ÝÃZ¾˜n´{ë´¼›U–ëQkG¶Ñ“H»Ñõ{f÷ì_P`/¿ œ“Óø5ó_íGñ»_øà +\ð·‚îücâ/øËÃ^Ñ\én¡êž)¸šÖËXñF­¯ëzm¥£\CŽ›m=ýŠë^ ÖôoCM}Yu \ñj”°ÕUy8ÒJò¶ŽÊÎÚwëêqqÀË'ƼƭJ8Gš£¤Ú›ŠjN)¥{fº¦ÕÖæ€d?‡ø®|gñ-­·Šþ&øPмAyu.ŸgcáOx£Hðl ¸×|áxQ“GÕ®t£©Ç.©y>£¯Éi«¾™6±.•maciõŠ€ (ùTch逌ØpkòÏâ÷í1ñþÏàÜÚUÖ™áoƒŸæøñÛâˆ5vïOÕMÿ…ks¤xÃÒøkKð÷НìôËíTø’ÇW”É­jñh"Èiõ·¸þÖµÝø½ñ÷ãOü,¿‡~ø_â_ø?Q¾ý©mþêÚ¯‹ü;<+­èsþÇz߯g6‰§O¡_iÖOâ‰4æìúȾ[$NoäÓ§“Duf_†R… . ¸·hë)Tz_«}ï§cãòÞ$áL’•J9^_:0©*\”ýú•1/Fõæ”’Ö\Ú.‡é•ÈÉ(„ã%T°2G8öÍ>½³ô¸¾d¥k\F8ÿ¯µaø“@мW¢jÞñF‹¥x‹Ãºæu¤ëZ·co©éÆ•©A5ž¡¦jšuäo þŸ=¬’Å42£G$r²:²±QI¤ÓM]=>DU„*Sœ*ENVi¤ÓOtÓѯ&yÌ¿~ \x[Fð-dž· Ðnu»Ý— Ð'ðö‘{âhõ»ÞiÚ<¶& K½Bx/¤HÃÝ®¿z· ºœIÔj¿~jðjÖÚ·¼#ª[kšî‹â}jßPðö—y±â_ x{Ä:¬SÛ2ê݈𿆅ÜÁ綱ȂÒ,¢³T©^OÙÆút]K§E¢8a‚Á$ÚÂRM¨ëìáwHôû+EÙhŽè€{”´QZž‘ÿÙsmalltalk-3.2.5/packages/httpd/STT.st0000644000175000017500000002304312123404352014347 00000000000000"===================================================================== | | Smalltalk templates | | ======================================================================" "====================================================================== | | Copyright 2002 Federico G. Stilman | Porting by Markus Fritsche and Paolo Bonzini | Integration with the web server framework by Paolo Bonzini. | | This file is part of GNU Smalltalk. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" Object subclass: STTTemplate [ | sttCode cache asStringSelector | %{ ] %} is valid %{ 1 to: 5 do: [ "Comment" %} yes
    %{ ] %} is not valid This restriction might be removed in the future. The template is evaluated by sending #evaluateOn: or #evaluateOn:stream: and returns the output stream (available to the code as the variable `out''). The first (or only) argument of these two methods is available to the code as `self'').'> STTTemplate class >> test [ | sttTest | sttTest := ' {%= self class %} {% self to: 10 do: [ :each | %} {% ] %}
    {%= each printString %} {%= (each * 2) printString %}
    '. ^(STTTemplate on: sttTest) evaluateOn: 1 ] STTTemplate class >> test2 [ | sttTest | sttTest := ' {%= self class %} {% out nextPutAll: ''This is another test''; nl. 1 to: 15 do: [:x | out nextPutAll: ''

    This paragraph was manually sent out '', (self * x) printString, ''

    ''; nl ]. out nextPutAll: ''After all this ST code goes the final HTML closing tag''. %} '. ^(STTTemplate on: sttTest) evaluateOn: 3 ] STTTemplate class >> on: aString [ "Creates an instance of the receiver on aString" ^self on: aString asStringSelector: self defaultAsStringSelector ] STTTemplate class >> on: aString asStringSelector: aSymbol [ "Creates an instance of the receiver on aString" ^self new initializeOn: aString asStringSelector: aSymbol ] STTTemplate class >> defaultAsStringSelector [ ^#displayString ] cache [ "Returns the receiver's cached object" ^cache ] cache: anObject [ "Save anObject in the receiver's cache" cache := anObject ] initializeCache [ "Initialize the receiver's cache" cache := nil ] isCached [ "Tell if the receiver is cached or not. In the future this will consider the fact that a cached object may become old after some time, and that means that the object is NOT cached anymore." ^self cache notNil ] asSmalltalkCodeOn: anObject [ "Returns the equivalent version of the receiver as a Smalltalk CompiledMethod" | method stream | self isCached ifTrue: [^self cache]. stream := String new writeStream. self writeSmalltalkCodeOn: stream. method := anObject class compile: stream. self cache: method. anObject class removeSelector: method selector. ^method ] writeSmalltalkCodeOn: stream [ "Write the equivalent version of the receiver as Smalltalk code on the given stream" | sttOpenIndex sttCloseIndex lastIndex sttCodeIndex smalltalkExpression | stream nextPutAll: 'STT_Cache'; print: self asOop; nextPutAll: ': out ['; nl. lastIndex := 1. [(sttOpenIndex := self sttCode indexOfSubCollection: '{%' startingAt: lastIndex) > 0] whileTrue: [self writeOutputCodeFor: (self sttCode copyFrom: lastIndex to: sttOpenIndex - 1) on: stream. sttCloseIndex := self sttCode indexOfSubCollection: '%}' startingAt: sttOpenIndex ifAbsent: [^self error: 'Missing closing tag']. sttCodeIndex := sttOpenIndex + 2. (sttCode at: sttOpenIndex + 2) = $= ifTrue: [stream nextPutAll: 'out nextPutAll: ('. sttCodeIndex := sttCodeIndex + 1]. smalltalkExpression := sttCode copyFrom: sttCodeIndex to: sttCloseIndex - 1. smalltalkExpression := smalltalkExpression trimSeparators. stream nextPutAll: smalltalkExpression. (sttCode at: sttOpenIndex + 2) = $= ifTrue: [stream nextPutAll: ') ' , self asStringSelector asString. sttCodeIndex := sttCodeIndex + 1]. ('|[({.' includes: smalltalkExpression last) ifFalse: [stream nextPut: $.]. stream nl. lastIndex := sttCloseIndex + 2]. self writeOutputCodeFor: (self sttCode copyFrom: lastIndex to: sttCode size) on: stream. stream nextPutAll: '^out ]' ] writeOutputCodeFor: aString on: aStream [ "Writes on aStream the required Smalltalk code for outputing aString on 'out'" aStream nextPutAll: 'out nextPutAll: '''; nextPutAll: aString; nextPutAll: '''.'; nl ] evaluateOn: anObject [ "Evaluates the receiver to anObject" ^(self evaluateOn: anObject stream: String new writeStream) contents ] evaluateOn: anObject stream: out [ "Evaluates the receiver to anObject" ^anObject perform: (self asSmalltalkCodeOn: anObject) with: out ] sttCode [ "Returns the receiver's Smalltalk Template code" ^sttCode ] asStringSelector [ "Returns the selector used to show objects as Strings on the receiver" ^asStringSelector ] asStringSelector: aSymbol [ "Sets the selector used to show objects as Strings on the receiver" asStringSelector := aSymbol ] initializeOn: aString asStringSelector: aSymbol [ sttCode := aString. asStringSelector := aSymbol. self initializeCache ] ] WebResponse subclass: STTResponse [ | stt | STTResponse class >> respondTo: aRequest with: aSTTTemplate [ (self new) stt: aSTTTemplate; respondTo: aRequest ] sendBody [ [self stt evaluateOn: self stream: responseStream] on: Error do: [:ex | responseStream << ex messageText; nl; << '
    '.
    		Smalltalk backtraceOn: responseStream.
    		responseStream
    		    nl;
    		    << '
    '. ex return] ] stt [ ^stt ] stt: aSTTTemplate [ stt := aSTTTemplate ] ] Servlet subclass: STTServlet [ | stt | respondTo: aRequest [ STTResponse respondTo: aRequest with: self stt ] stt [ ^stt ] stt: aSTTTemplate [ (aSTTTemplate isKindOf: File) ifTrue: [self stt: aSTTTemplate readStream contents. ^self]. (aSTTTemplate isKindOf: Stream) ifTrue: [self stt: aSTTTemplate contents. ^self]. (aSTTTemplate isKindOf: STTTemplate) ifFalse: [self stt: (STTTemplate on: aSTTTemplate). ^self]. stt := aSTTTemplate ] ] FileWebServer subclass: STTFileWebServer [ | knownSTTs | initialize [ super initialize. knownSTTs := LookupTable new ] fileResponse: file request: aRequest [ | stt | ('*.stt' match: file name) ifFalse: [^super fileResponse: file request: aRequest]. stt := knownSTTs at: file name ifAbsentPut: [STTTemplate on: file readStream contents]. ^STTResponse new stt: stt ] ] WebServer class extend [ publishMyFileSystem [ "Watch out!! Security hole, they could steal /etc/passwd!!" "WebServer publishMyFileSystem" | handler | self terminateServer: 8080. "Add a file server on a particular directory." handler := (self initializeServer: 8080) handler. handler addComponent: (STTFileWebServer named: 'disk' directory: '/') ] ] smalltalk-3.2.5/packages/httpd/ChangeLog0000644000175000017500000000165112123404352015100 000000000000002010-12-04 Paolo Bonzini * package.xml: Remove now superfluous tags. 2010-02-19 Paolo Bonzini * FileServer.st: Do not use instance-based exceptions. 2009-08-21 Paolo Bonzini * test.st: Do not use rockBottomPriority. 2008-08-06 Paolo Bonzini * FileServer.st: Do not use #nextHunk. 2008-07-15 Paolo Bonzini * WebServer.st: Use Sockets namespace. 2008-04-07 Paolo Bonzini * FileServer.st: Use new File classes. * WikiServer.st: Likewise. 2008-03-18 Paolo Bonzini * FileServer.st: Use #nextHunk. 2007-10-07 Paolo Bonzini * STT.st: Add brackets around compiled methods. 2007-07-18 Paolo Bonzini * STT.st: Use #compile: on the WriteStream. 2007-07-18 Stephen Compall * STT.st: Use #compile:. smalltalk-3.2.5/packages/httpd/find.jpg0000644000175000017500000000330012123404352014741 00000000000000ÿØÿàJFIFÿÛCÿÛCÿÀ0"ÿÄ ÿĵ}!1AQa"q2‘¡#B±ÁRÑð$3br‚ %&'()*456789:CDEFGHIJSTUVWXYZcdefghijstuvwxyzƒ„…†‡ˆ‰Š’“”•–—˜™š¢£¤¥¦§¨©ª²³´µ¶·¸¹ºÂÃÄÅÆÇÈÉÊÒÓÔÕÖרÙÚáâãäåæçèéêñòóôõö÷øùúÿÄ ÿĵw!1AQaq"2B‘¡±Á #3RðbrÑ $4á%ñ&'()*56789:CDEFGHIJSTUVWXYZcdefghijstuvwxyz‚ƒ„…†‡ˆ‰Š’“”•–—˜™š¢£¤¥¦§¨©ª²³´µ¶·¸¹ºÂÃÄÅÆÇÈÉÊÒÓÔÕÖרÙÚâãäåæçèéêòóôõö÷øùúÿÚ ?þì¾)xñ>øBïÄK§gS“PÑ<=áÍ n–Äë¾*ñn·§xcÂÚC_¼26Úã^Õ¬#¸»h¥K;všîHÞ8W•ÿÂ#ûHýˆëßð·üÿ !AqÿølçáÎe¿²¾Õÿ 'ö÷›Ï—ý§ý£³ÌjþÆòÿâ__ÁH¿n/ |½økð?À~¿ø­ûDø«âÃxSáï†n!:†‡üi£k¶×è[YÌj‹§\i°[IçƒP¹¸ŽkU·ûJýAí]¯J±xGþ¿ãÿü-VÒÅ×ü!§Áp¯…Öá”F |j:—ü!bÃí ~q®5à„oþÏóÑϘñxz¸ŠÔUf况ùoe/åmiͦÝ‚©Ä™6?8̲ØcgR®V š¥í9cVW¼9 ¬æ­wöûsð—Æ Wøc{ñ+ÄÞ_„m<.ž+µñÝÄòjƒÂÚ×€õ=SBñžœ·6–‹&µ¾³¢ê)k4êÚŒ öÐbæ$¯Að׊4é£TÑŸPbÐ\Zk·á­oMšûKÓõ«k=gþ%Ó­5 RþÌÕtù^ÖòÚ ˆ…Ò¬±#åGÊzÿì÷âþ˾7øMâ›_ x‹ÆŸ_Å>$ñM–¡Û|ÿ WŒ|[yã9´ËfÔ´½÷¾Òo.­¬´û™ìÒæh4+[©áŽíäˆÖ¿c‹üMñ­ç‰|ðÇ_øC.‹ñ6Ïáç€õ].ÇPÑ<1y­|ý¾x´ïÝè­§èqé×?>&$ܰ[ê–oj]L–ê®'Nqtp‹NJž­¸Ëšn|͵%(Ž$ï+icЩ™qAPÊ#Ž¤á‡‹ns¥':®ª©9IS¨£ 1…7+BRn¥­fþåÕüK¡h:‡…t­cQŽÏPñ®»s០[&‚X$_ øGÄWe¥1ÆSLdexã}ì<þ]?¥~lø7öaø§ ü]øUñ Ä~ øaâïøÆ>0Ô¾3ê~0½½ø6ƒìƒâO‚“|/°:€e¸±Ð—â~¨oÙaÕÖÂk}B]jKi5‹«èÛk®üXû!‘þxD^|8¾û*üL¾hŠ5­oSµø§áõ»o‡j²ü? A¥^i‰ˆ?‰.ulg°ðò[ Ë0¸ºµUibpÓÃ8ÎJ F¤›„as6 •ÛæJ×NÊ1r{÷ey¶/eLÇ-«—Êj¥N½G*TèÓŸ<š¢£Í)º‘Š…á' r©-_‰xköAýŸü?ûHøÏöÓ| l¿¼_¤iúV§â;›ËËØ-­£X]êš6™u+Á£ë7º\:m¥íź£Ko¥¢(®u¼úÅ!‹$ì\€vŒñœvëE¶8*¼Pæ”Û²Jï™jí»óÜâáü.… {%= self class %} {% out nextPutAll: 'This is another test'; nl. 1 to: 15 do: [:x | out nextPutAll: '

    This paragraph was manually sent out ', x printString, '

    '; nl ]. out nextPutAll: 'After all this ST code goes the final HTML closing tag'. %} smalltalk-3.2.5/packages/httpd/Haiku.st0000644000175000017500000000270012123404352014733 00000000000000ErrorResponse class extend [ haikuErrorMessages: aBoolean [ aBoolean ifFalse: [self initialize] ifTrue: [self initialize: self haiku] ] haiku [ ^#(#(404 'Not found' '

    Rather than a beep
    Or a rude error message,
    These words: "File not found."

    The requested URL was not found on this server.

    ') #(410 'Gone' '

    You step in the stream,
    but the water has moved on.
    This page is not here.

    The requested resource is no longer available at the server and no forwarding address is known. This condition should be considered permanent.

    ') #(414 'Request-URI Too Long' '

    Out of memory.
    We wish to hold the whole sky,
    But we never will.

    The server is refusing to service the request because the requested URL is longer than the server is willing to interpret. This condition is most likely due to a client''s improper conversion of a POST request with long query information to a GET request.

    ') #(503 'Service unavailable' '

    Stay the patient course
    Of little worth is your ire
    The network is down.

    The server is currently unable to handle the request due to a temporary overloading or maintenance of the server. This is a temporary condition.

    ')) ] ] Eval [ ErrorResponse haikuErrorMessages: true ] smalltalk-3.2.5/packages/httpd/prev.jpg0000644000175000017500000000413412123404352015003 00000000000000ÿØÿàJFIFÿÛCÿÛCÿÀ$/"ÿÄ ÿĵ}!1AQa"q2‘¡#B±ÁRÑð$3br‚ %&'()*456789:CDEFGHIJSTUVWXYZcdefghijstuvwxyzƒ„…†‡ˆ‰Š’“”•–—˜™š¢£¤¥¦§¨©ª²³´µ¶·¸¹ºÂÃÄÅÆÇÈÉÊÒÓÔÕÖרÙÚáâãäåæçèéêñòóôõö÷øùúÿÄ ÿĵw!1AQaq"2B‘¡±Á #3RðbrÑ $4á%ñ&'()*56789:CDEFGHIJSTUVWXYZcdefghijstuvwxyz‚ƒ„…†‡ˆ‰Š’“”•–—˜™š¢£¤¥¦§¨©ª²³´µ¶·¸¹ºÂÃÄÅÆÇÈÉÊÒÓÔÕÖרÙÚâãäåæçèéêòóôõö÷øùúÿÚ ?þþ(¢Š—'ž™=ºÂÃH¯Àø)_üãOì_ûDXüðÃÿ‡>%Ðî¾xwÆ/©x­|Lu1¬k>&Óg¶S¤ë–ð­šÅ¢[²f2û¦}ÎFÐ>Søÿ×ý£>+|tø/ð·[øSð†ÇGø•ñcá×€5kí5ý ¾ßè?í-¼çxÒy¼eð÷ìS]Ç¢,ºwˆVêâ;K›Q§ÜòÕÆaèMÓ«7F.oÝ“\©+»¥o;omv¹äⳬ»ˆ–]´`ê5ìêI(GY7(ÅÇÝZµ{¨ëk+Ÿpê>ðæ­qö½SBÑõ ­‹ÚotÛ+©ü´,R?6x¶Íœ ÇMUƒÁž¶š+› hO‘ÍðèútrÃ4N)b’;pÑÈ®•J‚"¾.°ý¶u ?Ãc]øƒð[Åž–êoˆz‡`h¼i§Ãã¿øOžñ—„¼àK/Š_ ü%­ë·‰4ÍkŶºl—Z„'Tøk«ÚB×q;«ƒ]ý°¶ðÚ]Ë¡Úî²o5;?¶ÄWËÛæm9-[ämê“Oᾫ];>Ç›,߆\ç^Q§:‘´å%AÊJéIIûœÍµªi={'o½Çííý?nã-íž$ú×É·íEsmá -Bøi«x›XÕ|_ûEx3H𮛪™5 GTø¬|KщƒÈÒešc¬\ü:vŠ-î.mƬ±Ã üñ$7•ðâÕÏÆ\xƒRÒ4Oëzv·{¡ë¾Ò5/^Üx~ö kNÚÃÄ6_¾xG[ðþ½&‘ªi—oc¨h6²%¾¥mx;ã'†´ÿ xîÉõ=ÏÅ>ñSé¥lä¶¾¾ð–·m­év×Ñ_Y̯do¬íÙü±êP<Ã*¤‹£¥|%øc£i:†…¥xÂ6&¯á-;Àz¦máý.-'PðV’ÚûéÞ½ÓV×Ⱥðô/â¿´xÚøŸÞeÚ%ÜQTéÓuªTtâæâ—5•íÚûÛÈk ‡–>µYP„ª¸F.N1rq´½×+^Ú½/m_s IýŸ¾è:E–…¤|+ð-Ž‘¦øÓLø§ØCá­([ÙøûF‚ÊÏFñ•º5©ò¼Mgc§iÖö—£ý"ÚßN··†D†‘,kþø’ïM¼ñÃ?ëWz6¹©xKºÕ<9¥_\YkšÝý¦±¬ê0KsjÌ“]kn™yp3¶k½.ÖæEií ’2Š^Æ£eT–œªÛ®–±+ƒö\ŸT¥Éh«{8ZÉ«ikheßþÍ¿µ={Zñ>£ðwáÅïˆÞkë¬}ªþémÑ~×}/—™4¥å“Ë]îØQNhÁ¹Â”a6žª)=R¾©_^¥á°˜J5¥V–*¯šòŒ#;¸ßT“ÖÊúëcÿÙsmalltalk-3.2.5/packages/httpd/recent.jpg0000644000175000017500000000475412123404352015317 00000000000000ÿØÿàJFIFÿÛCÿÛCÿÀ$/"ÿÄ ÿĵ}!1AQa"q2‘¡#B±ÁRÑð$3br‚ %&'()*456789:CDEFGHIJSTUVWXYZcdefghijstuvwxyzƒ„…†‡ˆ‰Š’“”•–—˜™š¢£¤¥¦§¨©ª²³´µ¶·¸¹ºÂÃÄÅÆÇÈÉÊÒÓÔÕÖרÙÚáâãäåæçèéêñòóôõö÷øùúÿÄ ÿĵw!1AQaq"2B‘¡±Á #3RðbrÑ $4á%ñ&'()*56789:CDEFGHIJSTUVWXYZcdefghijstuvwxyz‚ƒ„…†‡ˆ‰Š’“”•–—˜™š¢£¤¥¦§¨©ª²³´µ¶·¸¹ºÂÃÄÅÆÇÈÉÊÒÓÔÕÖרÙÚâãäåæçèéêòóôõö÷øùúÿÚ ?þþ(¢ŠòŸŠ?~ü²Òn)ñ™àûÍOÄ_üa®´ñøwÂß<ã…:׊žÙb’á<mñBÓ—ÆREñ4É¥=ëB‰–6ŽEN7áõµ†±ûY~ÑÚ‡ˆV9|cáo ü(ðï#¼òé_ 5íS×%Ô´Dl›Hµ_‰Öž7·Ô%k^7Ãý>+€é¦Ù”øWã¿Â¯|>ÿ‚[üGø_ûPh´8þ~Ïž Ò~xãáÿÄïx¯PÔþ$ü3ð¤z?‚¼DÄ_ <3/€µy¼g¤øN+¬¯5Y.‡ˆ®¬ež(×ý7ȯŒ¯N•|Lt°ê³³Z?bìÔ§uÏ–\¯d–©Ÿ›füO`ðùŽs†§—e°Ì$éÊ»_P—,–#uìe_’«¤ù\QæM¶~ÓðpÀƒÇ×<þ!ñŒ¶¾Ó|WàK üÕ|-â+ ?øvÖãÄ¿ln®uO \ê¾ ·ðÅss¥ë6óßéö1ØÚ\Xˆ¬®5”2ÏâþÕ_àñŽŸð«Pð‡ øƒã-{áͧ„µKM[^¹ðV¤ü@øwñsâDòø‘çÓ¡»Ôu 7Jø'âøB–Qj·:–˜€éžtþO“‰y>>ð¬§R|²Œ\ã ÉEIFq‹Qâ“Mé%mZ><Ÿ‡UR¥,Êñ4ªWTëR§*ôèb*ÆŸ´…:ð§8ª©©Fë–¢Z¶ž¿qxSÂÚ‚|5 x?š]ž…ᯠèún èÚt+oc¥húEœ:~›§Z[¨Ä6ÐÙÛAj8 ¥t§oÃ¥~eOûp|L¿´ÒôŸ ü$ƒÄ>>³ð×Ä?xƒAÒ“Å:ÖŸ®ÿÂñOÆŸ ô¿ øcRÓ4Bt{­WRðN¡;êz”fÛJv‘Ii}ö‡šÛÜüûCxÃÄ?5_†3ðµ§€í&Äóx/NÖ4&«âë¢Ioâ=ÇQhÒx[Ä2ÜÛjW3]hvšŠêÚD1£Ü%ÆË¯#¾Že‚›§N”šRPQ÷Z¤“ŠOnÊÝ—T}f]Æü/ZXL¬¡{ t¢©J4Ò«MJ”S²ŠJ6‹Iû²qŠZ£éßx7ž<Ðîü5ãOèþ(Ð/ÚK#\Óíµ+ &²¹†þÆçì÷Q²¥Ý½ý½¼öó(Á=´sÂé,hëÈØüøEaaªiV? üe¦ë:>áýZÆ×@Ó µÔ´_ ë¾ ñG‡ôÛèc€-͵§‰ WikiPage class >> newVersionOf: aWikiPage by: anAuthor [ ^(self new) previousVersion: aWikiPage; author: anAuthor; yourself ] WikiPage class >> new [ ^super new initialize ] allTitles [ | oc | oc := OrderedCollection new. self allTitlesInto: oc. ^oc ] allTitlesInto: aCollection [ self subclassResponsibility ] author [ ^author ] contents [ ^self subclassResponsibility ] references: aString [ ^(aString match: self contents) or: [aString match: self title] ] operationSynopsis [ ^self subclassResponsibility ] timestamp [ ^timestamp ] title [ ^self subclassResponsibility ] versionAt: aNumber [ self versionsDo: [:each | each versionNumber = aNumber ifTrue: [^each]]. ^self subscriptBoundsError: aNumber ] versionNumber [ self subclassResponsibility ] versionsDo: aBlock [ self subclassResponsibility ] versionsReverseDo: aBlock [ self subclassResponsibility ] printOn: aStream [ aStream nextPut: $[; nextPutAll: self title; nextPut: $(; print: self versionNumber; nextPut: $); nextPut: $]; nl; nextPutAll: self contents; nl. aStream nextPut: ${; nextPutAll: author; space; print: timestamp; nextPut: $} ] changeTitle: aTitle by: anAuthor [ | newGuy | aTitle = self title ifTrue: [^self]. newGuy := RenamedWikiPage newVersionOf: self by: anAuthor. newGuy title: aTitle. ^newGuy ] newContents: aContents by: anAuthor [ | newGuy | aContents = self contents ifTrue: [^self]. newGuy := EditedWikiPage newVersionOf: self by: anAuthor. newGuy contents: aContents. ^newGuy ] author: anObject [ author := anObject ] initialize [ timestamp := DateTime now. author := '' ] saveToFile: aFileStream under: aWikiPM [ aFileStream nextPutAll: author; nl. aFileStream print: timestamp asSeconds; nl. ^self ] loadFromFile: rs under: aWikiPM [ | timestamp author seconds | author := rs nextLine. seconds := rs nextLine asNumber. timestamp := (Date year: 1901 day: 1 hour: 0 minute: 0 second: 0) + (Duration seconds: seconds). self author: author; timestamp: timestamp ] timestamp: value [ timestamp := value ] ] WikiPage subclass: OriginalWikiPage [ | title | allTitlesInto: aCollection [ aCollection add: title ] contents [ ^'Describe ' , title , ' here...' ] operationSynopsis [ ^'Created' ] title [ ^title ] title: aString [ title := aString ] versionNumber [ ^0 ] versionsDo: aBlock [ aBlock value: self ] versionsReverseDo: aBlock [ aBlock value: self ] saveToFile: aFileStream under: aWikiPM [ super saveToFile: aFileStream under: aWikiPM. aFileStream nextPutAll: title. ^self ] loadFromFile: rs under: aWikiPM [ super loadFromFile: rs under: aWikiPM. self title: rs upToEnd ] ] WikiPage subclass: ChangedWikiPage [ | previousVersion | allTitlesInto: aCollection [ previousVersion allTitlesInto: aCollection ] contents [ ^previousVersion contents ] previousVersion [ ^previousVersion ] previousVersion: anObject [ previousVersion := anObject ] title [ ^previousVersion title ] versionNumber [ ^previousVersion versionNumber + 1 ] versionsDo: aBlock [ aBlock value: self. previousVersion versionsDo: aBlock ] versionsReverseDo: aBlock [ previousVersion versionsReverseDo: aBlock. aBlock value: self ] saveToFile: aFileStream under: aWikiPM [ super saveToFile: aFileStream under: aWikiPM. aFileStream print: (aWikiPM idForPage: self previousVersion); nl. ^self ] loadFromFile: rs under: aWikiPM [ | id | super loadFromFile: rs under: aWikiPM. id := rs nextLine. self previousVersion: (aWikiPM loadPage: id) ] ] ChangedWikiPage subclass: EditedWikiPage [ | contents | contents [ ^contents ] contents: aString [ "trim off trailing CRs" | index | index := aString size. [index > 1 and: [(aString at: index) = Character nl]] whileTrue: [index := index - 1]. contents := aString copyFrom: 1 to: index ] operationSynopsis [ ^'Edited' ] saveToFile: aFileStream under: aWikiPM [ super saveToFile: aFileStream under: aWikiPM. aFileStream nextPutAll: contents. ^self ] loadFromFile: rs under: aWikiPM [ super loadFromFile: rs under: aWikiPM. self contents: rs upToEnd ] ] ChangedWikiPage subclass: RenamedWikiPage [ | title | allTitlesInto: aCollection [ aCollection add: title. ^super allTitlesInto: aCollection ] operationSynopsis [ ^'Renamed' ] title [ ^title ] title: aString [ title := aString ] saveToFile: aFileStream under: aWikiPM [ super saveToFile: aFileStream under: aWikiPM. aFileStream nextPutAll: title. ^self ] loadFromFile: rs under: aWikiPM [ super loadFromFile: rs under: aWikiPM. self title: rs upToEnd ] ] Object subclass: WikiSettings [ | dictionary | WikiSettings class >> cookieString: aString [ ^self new fromCookieString: aString ] WikiSettings class >> new [ ^super new initialize ] loadFromFile: aFileStream [ | line | [(line := aFileStream nextLine) isEmpty] whileFalse: [line := line substrings: $=. line size = 2 ifTrue: [self at: (line at: 1) put: (line at: 2)] ifFalse: [self at: (line at: 1) put: true]] ] saveToFile: ws [ | line | self settingsDo: [:key :value | value == false ifFalse: [line := key. value == true ifFalse: [line := line , '=' , 'value']. ws nextPutAll: line; nl]]. ws nl ] initialize [ dictionary := Dictionary new ] at: name put: value [ ^dictionary at: name put: value ] at: name default: default [ ^dictionary at: name ifAbsentPut: [default] ] backgroundColor [ ^self at: 'bc' default: '#ffffff' ] backgroundColor: anObject [ self at: 'bc' put: anObject ] linkColor [ ^self at: 'lc' default: '#0000ff' ] linkColor: anObject [ self at: 'lc' put: anObject ] tableBackgroundColor [ ^self at: 'tbc' default: '#ffe0ff' ] tableBackgroundColor: anObject [ self at: 'tbc' put: anObject ] textColor [ ^self at: 'tc' default: '#000000' ] textColor: anObject [ self at: 'tc' put: anObject ] visitedLinkColor [ ^self at: 'vlc' default: '#551a8b' ] visitedLinkColor: anObject [ self at: 'vlc' put: anObject ] ] Servlet subclass: Wiki [ | settings pages rootPageTitle syntaxPageTitle fileServer persistanceManager | Wiki class >> named: aString [ ^self new name: aString ] Wiki class >> new [ ^super new initialize ] initialize [ pages := Dictionary new. settings := WikiSettings new. self name: 'Wiki'. self rootPageTitle: 'Duh Tawp'. self syntaxPageTitle: 'Duh Rools' ] redirectToRootPage: aRequest [ aRequest location addLast: self rootPageTitle , '.html'. "self sendPageFor: aRequest." ^(ErrorResponse movedTemporarilyTo: self printString , '/' , aRequest location last) respondTo: aRequest ] removeHTMLFrom: pageTitle [ pageTitle size > 5 ifFalse: [^pageTitle]. ^(pageTitle copyFrom: pageTitle size - 4 to: pageTitle size = '.html') ifTrue: [pageTitle copyFrom: 1 to: pageTitle size - 5] ifFalse: [pageTitle] ] sendPageFor: aRequest [ | pageTitle | pageTitle := self removeHTMLFrom: aRequest location last. ^(self hasPageTitled: pageTitle) ifTrue: [WikiPageHTML respondTo: aRequest in: self] ifFalse: [WikiAbsentPageHTML respondTo: aRequest in: self] ] replyToGetRequest: aRequest [ | rClass size | size := aRequest location size - self depth + 1. size < 2 ifTrue: [size = 0 ifTrue: [^self redirectToRootPage: aRequest]. ^(aRequest location last sameAs: 'RECENT CHANGES') ifTrue: [WikiChangesHTML respondTo: aRequest in: self] ifFalse: [self sendPageFor: aRequest]]. rClass := size = 2 ifTrue: [self classForCommand: aRequest] ifFalse: [WikiErrorHTML]. ^rClass respondTo: aRequest in: self ] classForCommand: aRequest [ | cmd page | cmd := aRequest location at: self depth. page := aRequest location last. (cmd sameAs: 'CREATE') ifTrue: [self createPageFor: aRequest. ^WikiEditHTML]. (self hasPageTitled: page) ifFalse: [^WikiAbsentPageHTML]. (cmd sameAs: 'EDIT') ifTrue: [^WikiEditHTML]. (cmd sameAs: 'HISTORY') ifTrue: [^WikiHistoryHTML]. (cmd sameAs: 'RENAME') ifTrue: [^WikiRenameHTML]. (cmd sameAs: 'REFS') ifTrue: [^WikiReferencesHTML]. (cmd sameAs: 'VERSION') ifTrue: [^WikiVersionHTML]. ^WikiErrorHTML ] replyToPostEditRequest: aRequest [ | newPage currentPage newContents | currentPage := self pageTitled: aRequest location last. newContents := aRequest postDataAt: #NEWCONTENTS. newPage := currentPage newContents: newContents by: aRequest originator. self addPage: newPage. self sendPageFor: aRequest ] replyToPostRenameRequest: aRequest [ | currentPage newTitle newPage | currentPage := self pageTitled: aRequest location last. newTitle := aRequest postDataAt: #NEWTITLE. ((self hasPageTitled: newTitle) and: [(self pageTitled: newTitle) ~= currentPage]) ifTrue: [^WikiRenameConflictHTML respondTo: aRequest in: self]. newPage := currentPage changeTitle: newTitle by: aRequest originator. self addPage: newPage. self sendPageFor: aRequest ] replyToPostRequest: aRequest [ | cmd | cmd := aRequest postDataAt: #COMMAND. (cmd sameAs: 'EDIT') ifTrue: [^self replyToPostEditRequest: aRequest]. (cmd sameAs: 'RENAME') ifTrue: [^self replyToPostRenameRequest: aRequest]. (cmd sameAs: 'SEARCH') ifTrue: [^self replyToPostSearchRequest: aRequest]. self replyToUnknownRequest: aRequest ] replyToPostSearchRequest: aRequest [ ^WikiReferencesHTML respondTo: aRequest in: self ] replyToUnknownRequest: aRequest [ ^WikiErrorHTML respondTo: aRequest in: self ] respondTo: aRequest [ (aRequest action sameAs: 'HEAD') ifTrue: [^self replyToGetRequest: aRequest]. (aRequest action sameAs: 'GET') ifTrue: [^self replyToGetRequest: aRequest]. (aRequest action sameAs: 'POST') ifTrue: [^self replyToPostRequest: aRequest]. ^(ErrorResponse acceptableMethods: #('HEAD' 'GET' 'POST')) respondTo: aRequest ] syntaxPageTitle [ ^(self pageTitled: syntaxPageTitle) title ] syntaxPageTitle: aString [ syntaxPageTitle notNil ifTrue: [pages removeKey: syntaxPageTitle asUppercase]. syntaxPageTitle := aString. self addPage: self newSyntaxPage ] filesPath [ ^fileServer isNil ifTrue: [nil] ifFalse: [fileServer printString] ] filesPath: aString [ | path | aString isNil ifTrue: [^self fileServer: nil]. path := (aString at: 1) == $/ ifTrue: [WebServer current handler] ifFalse: [self parent]. (aString substrings: $/) do: [:each | each isEmpty ifFalse: [path := path componentNamed: each]]. self fileServer: path ] fileServer [ ^fileServer ] fileServer: aString [ fileServer := aString ] name [ ^name ] name: aString [ name := aString ] persistanceManager: aWikiPersistanceManager [ persistanceManager := aWikiPersistanceManager. aWikiPersistanceManager wiki: self ] rootPageTitle [ ^(self pageTitled: rootPageTitle) title ] rootPageTitle: aString [ rootPageTitle notNil ifTrue: [pages removeKey: rootPageTitle asUppercase]. rootPageTitle := aString. self addPage: (OriginalWikiPage new title: rootPageTitle) ] save [ persistanceManager save ] settings [ ^settings ] startDate [ ^((self pageTitled: self rootPageTitle) versionAt: 0) timestamp ] loadFromFile: aFileStream [ | path | settings loadFromFile: aFileStream. self name: aFileStream nextLine. self rootPageTitle: aFileStream nextLine. self syntaxPageTitle: aFileStream nextLine. path := aFileStream nextLine. path = '' ifTrue: [path := nil]. self filesPath: path. ^self ] saveToFile: ws [ settings saveToFile: ws. ws nextPutAll: self name; nl. ws nextPutAll: self rootPageTitle; nl. ws nextPutAll: self syntaxPageTitle; nl. self filesPath isNil ifTrue: [ws nextPutAll: ''; nl] ifFalse: [ws nextPutAll: self filesPath; nl]. ^self ] addPage: aPage [ aPage allTitles do: [:each | pages at: each asUppercase put: aPage]. persistanceManager isNil ifFalse: [persistanceManager addPage: aPage] ] currentPageTitleFor: aString [ ^(aString sameAs: 'Changes') ifTrue: ['Recent Changes'] ifFalse: [(pages at: aString asUppercase) title] ] currentTitleOf: aString [ ^(aString sameAs: 'RECENT CHANGES') ifTrue: [aString] ifFalse: [(self pageTitled: aString) title] ] syntaxPage [ ^self pageTitled: syntaxPageTitle ] hasPageTitled: aString [ ^(pages includesKey: aString asUppercase) or: [aString sameAs: 'RECENT CHANGES'] ] allPagesDo: aBlock [ pages do: aBlock ] pagesDo: aBlock [ "when enumerating the pages dictionary, we want to filter to only those entries whose titles are current, this avoids double enumerating a page that might have two or more titles in it's history" pages keysAndValuesDo: [:title :page | (page title sameAs: title) ifTrue: [aBlock value: page]] ] pageTitled: aString [ ^pages at: aString asUppercase ] createPageFor: aRequest [ (self hasPageTitled: aRequest location last) ifFalse: [self addPage: ((OriginalWikiPage new) author: aRequest originator; title: aRequest location last; yourself)] ] newSyntaxPage [ ^(OriginalWikiPage new title: syntaxPageTitle) newContents: self newSyntaxPageContents by: '' ] newSyntaxPageContents [ ^'The Wiki''s a place where anybody can edit anything. To do so just follow the Edit this page link at the top or bottom of a page. The formatting rules are pretty simple: . Links are created by placing square brackets around the link name (e.g. [[aPageName]). If you need to create a [[ character, use two of them (e.g. "[[[["). You don''t need to double up the ] character unless you actually want to use it as part of the link name. . If you want to create a link to an "outside" source, just include the full internet protocol name (e.g. [[http://www.somesite.com] or [[mailto:someone@somewhere.com] or [[ftp://somesite.ftp]). . If you want a link (either internal or outside) by another name, then place both the desired name and the actual link target as a pair separated by > character (e.g. [[The Top > Home Page] or [[me > mailto:myname@myplace.com]). . Carriage returns create a new paragraph . Use any HTML you want. The Wiki formatting rules will not be applied between a PRE tag. . To create a horizontal line, start a line with ''----''. . To create a bullet list item, start a line with a . character. . To create a numbered list item, start a line with a # character. . To create a heading, start a line with a * character. More consecutive asterisks yield lower level headings. . To create a table, start the line with two | (vertical bar) characters. For each cell in the row, separate again by two | characters. Successive lines that start with the two | characters are made into the same table. . To publish your edits, press the save button. If you don''t want to publish, just press your browser''s Back button. ' ] ] Wiki subclass: ProtectedWiki [ | authorizer | replyToRequest: aRequest [ self authorizer authorize: aRequest in: self ifAuthorized: [super replyToRequest: aRequest] ] ] ProtectedWiki subclass: ReadOnlyWiki [ replyToPostEditRequest: aRequest [ self authorizer authorize: aRequest in: self ifAuthorized: [super replyToPostEditRequest: aRequest] ] replyToPostRenameRequest: aRequest [ self authorizer authorize: aRequest in: self ifAuthorized: [super replyToPostRenameRequest: aRequest] ] ] ProtectedWiki subclass: PasswordWiki [ authorizer [ ^authorizer ] authorizer: aWebAuthorizer [ authorizer := aWebAuthorizer. self fileServer isNil ifFalse: [self fileServer uploadAuthorizer: aWebAuthorizer] ] loginID: aLoginID password: aPassword [ self authorizer: (WebAuthorizer loginID: aLoginID password: aPassword) ] loadFromFile: aFileStream [ super loadFromFile: aFileStream. self authorizer: (WebAuthorizer fromString: aFileStream nextLine). ^self ] saveToFile: ws [ super saveToFile: ws. ws nextPutAll: self authorizer authorizer; nl. ^self ] ] WebResponse subclass: WikiHTML [ | wiki page | WikiHTML class >> new [ ^super new initialize ] WikiHTML class >> respondTo: aRequest in: aWiki [ ^(self new) wiki: aWiki; respondTo: aRequest ] initialize [ ] browserTitle [ ^self wikiName , ': ' , self pageTitle ] encodedPageTitle [ ^(URL encode: self page title) , '.html' ] settings [ ^wiki settings ] page [ page isNil ifTrue: [page := wiki pageTitled: request location last]. ^page ] pageTitle [ ^self page title ] emitIcon: imageBlock linkTo: nameBlock titled: titleBlock [ self wiki filesPath isNil ifFalse: [^self image: imageBlock linkTo: nameBlock titled: titleBlock; nl]. self td: [self linkTo: nameBlock titled: titleBlock] ] emitCommonIcons [ self emitIcon: [self << self wiki filesPath << '/help.jpg'] linkTo: [self << self wiki; << $/; nextPutUrl: self wiki syntaxPageTitle] titled: [self << self wiki syntaxPageTitle]; emitIcon: [self << self wiki filesPath << '/recent.jpg'] linkTo: [self << self wiki << '/RECENT+CHANGES'] titled: [self << 'Recent changes']; emitIcon: [self << self wiki filesPath << '/top.jpg'] linkTo: [self << self wiki << $/] titled: [self << 'Back to Top'] ] sendBody [ "subclasses will usually want to do more here" self emitStart. self emitIcons. self emitFinish ] emitFinish [ self nl; << '
    '; nl; << '' ] emitSearch: aString [ self horizontalLine. (self << '
    '; nl. self << ''; nl. (self << ''; nl. self wiki filesPath isNil ifFalse: [self << '
    '; nl ] emitStart [ (self << '' << self browserTitle << ' self emitIconsStart; emitCommonIcons; emitIconsEnd ] emitIconsEnd [ self wiki filesPath isNil ifFalse: [self << '
    '; nl] ifTrue: [self nl; << ''; nl; << ''; nl] ] emitIconsStart [ self wiki filesPath isNil ifFalse: [^self image: [self << self wiki filesPath << '/head.jpg'] titled: [self << self wiki]]. self << ''; nl ] emitUrlForCommand: commandName [ self << self wiki << $/ << commandName << $/ << self encodedPageTitle ] emitUrlOfPage [ self << self wiki << $/ << self encodedPageTitle ] linkToPage: aPage [ self linkTo: [self << self wiki; << $/; nextPutUrl: aPage title] titled: [self << aPage title] ] wiki [ ^wiki ] wiki: anObject [ wiki := anObject ] wikiName [ ^wiki name ] ] WikiHTML subclass: WikiPageHTML [ | contentStream currentChar lastChar inBullets inNumbers heading inTable | ParseTable := nil. WikiPageHTML class >> initialize [ ParseTable := Array new: 256. ParseTable at: 1 + Character cr asciiValue put: #processCr. ParseTable at: 1 + Character nl asciiValue put: #processNl. ParseTable at: 1 + $[ asciiValue put: #processLeftBracket. ParseTable at: 1 + $. asciiValue put: #processDot. ParseTable at: 1 + $# asciiValue put: #processPound. ParseTable at: 1 + $- asciiValue put: #processDash. ParseTable at: 1 + $* asciiValue put: #processStar. ParseTable at: 1 + $| asciiValue put: #processPipe. ParseTable at: 1 + $< asciiValue put: #processLeftAngle ] isExternalAddress: linkAddress [ "Faster than #match:" ^#('http:' 'https:' 'mailto:' 'file:' 'ftp:' 'news:' 'gopher:' 'telnet:') anySatisfy: [:each | each size < linkAddress size and: [(1 to: each size) allSatisfy: [:index | (each at: index) == (linkAddress at: index)]]] ] isImage: linkAddress [ "Faster than #match:" ^#('.gif' '.jpeg' '.jpg' '.jpe') anySatisfy: [:each | each size < linkAddress size and: [(1 to: each size) allSatisfy: [:index | (each at: index) == (linkAddress at: linkAddress size - each size + index)]]] ] linkAddressIn: aString [ | rs | rs := aString readStream. rs skipTo: $>. ^(rs atEnd ifTrue: [aString] ifFalse: [rs upToEnd]) trimSeparators ] linkNameIn: aString [ | rs | rs := aString readStream. ^(rs upTo: $>) trimSeparators ] addCurrentChar [ self responseStream nextPut: currentChar ] atLineStart [ ^lastChar == Character nl or: [lastChar == nil] ] closeBulletItem [ self << ''; nl. contentStream peek == $. ifFalse: [inBullets := false. self << ''; nl] ] closeHeading [ (self << ''; nl. heading := nil ] closeNumberItem [ self << ''; nl. contentStream peek == $# ifFalse: [inNumbers := false. self << ''; nl] ] closeTableRow [ | pos | self << ''; nl. pos := contentStream position. (contentStream peekFor: $|) ifTrue: [(contentStream peekFor: $|) ifTrue: [inTable := false. self << '
    '; nl]]. contentStream position: pos ] processNextChar [ | selector | lastChar := currentChar. currentChar := contentStream next. selector := ParseTable at: currentChar value + 1. ^selector isNil ifTrue: [self addCurrentChar] ifFalse: [self perform: selector] ] processDot [ self atLineStart ifFalse: [^self addCurrentChar]. inBullets ifFalse: [self << '
      '; nl. inBullets := true]. self << '
    • ' ] processStar [ self atLineStart ifFalse: [^self addCurrentChar]. heading := 2. [contentStream peekFor: $*] whileTrue: [heading := heading + 1]. self << '' ] processCr [ contentStream peekFor: Character nl. currentChar := Character nl. self processNl ] processNl [ inBullets ifTrue: [^self closeBulletItem]. inNumbers ifTrue: [^self closeNumberItem]. inTable ifTrue: [^self closeTableRow]. heading isNil ifFalse: [^self closeHeading]. self lineBreak ] processDash [ self atLineStart ifFalse: [^self addCurrentChar]. contentStream skipTo: Character nl. self horizontalLine. lastChar := Character nl ] processLeftAngle [ | s | s := String new writeStream. self addCurrentChar. [currentChar := contentStream next. currentChar == $> or: [currentChar == $ ]] whileFalse: [s nextPut: currentChar]. self << (s := s contents) << currentChar. (s sameAs: 'PRE') ifFalse: [^self]. [contentStream atEnd ifTrue: [^self]. self << (contentStream upTo: $<) << $<. self << (s := contentStream upTo: $>) << $>. s sameAs: '/PRE'] whileFalse ] processLeftBracket [ | linkAddress linkName link | (contentStream peekFor: $[) ifTrue: [^self addCurrentChar]. link := contentStream upTo: $]. [contentStream peekFor: $]] whileTrue: [link := link , ']' , (contentStream upTo: $])]. linkName := self linkNameIn: link. linkAddress := self linkAddressIn: link. (self isExternalAddress: linkAddress) ifTrue: ["external outside link" ^self << '' << linkName << '']. linkAddress = linkName ifTrue: [self emitLink: linkName] ifFalse: [self emitLink: linkName to: linkAddress] ] processPipe [ (contentStream peekFor: $|) ifTrue: [self atLineStart ifTrue: [inTable ifFalse: [self << ''; nl. inTable := true]. self << ''; nl. self td: [self linkTo: [self << self wiki; << '/VERSION/'; nextPutUrl: each title; << '?n='; << each versionNumber] titled: [self << each versionNumber]]. self td: [self << each operationSynopsis]. self td: [self << each author]. self td: [self sendTimestamp: each timestamp]. self << ''; nl ] titleSuffix [ ^' (history)' ] ] WikiCommandHTML subclass: WikiRenameHTML [ titleSuffix [ ^' (rename)' ] emitForm [ self heading: [self << 'Rename'. self linkTo: [self emitUrlForCommand: 'REFS'] titled: [self << self pageTitle]]. self << '
      '; nl. self << ''; nl. self << ''; lineBreak. self << ''; nl. self << ''; nl ] sendBody [ self emitStart. self emitIcons. self emitForm. self emitFinish ] ] Object subclass: WikiPersistanceManager [ | wiki | wiki [ ^wiki ] wiki: aWiki [ wiki := aWiki. self reset ] allPagesDo: aBlock [ wiki allPagesDo: aBlock ] addPage: aPage [ ] load [ self subclassResponsibility ] save [ self subclassResponsibility ] ] WikiPersistanceManager subclass: FlatFileWiki [ | directory fileCounter idMap | FlatFileWiki class >> directory: aDirectory [ ^self new directory: aDirectory ] reset [ directory exists ifFalse: [Directory create: directory name]. idMap := IdentityDictionary new. fileCounter := -1 ] idForPage: aPage [ ^idMap at: aPage ifAbsentPut: [self savePage: aPage] ] indexIn: aFilename [ | tail | tail := aFilename stripPath. ^(tail copyFrom: 1 to: tail size - 4) asNumber ] nextFileCounter [ ^fileCounter := fileCounter + 1 ] loadPage: id [ ^self loadPageInFile: (directory at: id , '.pag') ] loadPageInFile: aFilename [ | index rs page | index := self indexIn: aFilename. ^idMap at: index ifAbsentPut: [| type | Transcript show: '.'. rs := aFilename readStream. type := rs nextLine asSymbol. [page := (Smalltalk at: type) new. page loadFromFile: rs under: self] ensure: [rs close]. page] ] loadPages [ | latestVersions pageMap | idMap := pageMap := IdentityDictionary new. directory filesMatching: '*.pag' do: [:fn | self loadPageInFile: fn]. idMap := IdentityDictionary new. pageMap keysAndValuesDo: [:i :page | idMap at: page put: i]. latestVersions := pageMap asSet. pageMap do: [:page | "Remove all versions older than `each' from latest" page versionsDo: [:each | each == page ifFalse: [latestVersions remove: each ifAbsent: []]]]. latestVersions do: [:page | self wiki addPage: page] ] load [ | rs fn | self reset. (fn := directory at: 'wiki.conf') exists ifFalse: [self error: 'wiki directory doesn''t exist']. rs := fn readStream. [| type | type := rs nextLine asSymbol. self wiki: (Smalltalk at: type) new. self wiki loadFromFile: rs] ensure: [rs close]. self loadPages. self wiki persistanceManager: self. ^self wiki ] savePage: aPage [ | id ws | id := self nextFileCounter. idMap at: aPage put: id. ws := (self directory at: id printString , '.pag') writeStream. [ws nextPutAll: aPage class name; nl. aPage saveToFile: ws under: self] ensure: [ws close]. ^id ] savePages [ self allPagesDo: [:aPage | self savePage: aPage] ] save [ | ws | self reset. directory exists ifFalse: [Directory create: directory name]. ws := (directory at: 'wiki.conf') writeStream. [ws nextPutAll: wiki class name; nl. wiki saveToFile: ws] ensure: [ws close]. self savePages ] directory [ ^directory ] directory: aFilename [ directory := File name: aFilename ] addPage: aPage [ self idForPage: aPage. ^self ] ] WebServer class extend [ wikiDirectories [ ^#('GnuSmalltalkWiki') ] initializeImages [ (self at: 8080) handler addComponent: (FileWebServer named: 'images' directory: (Directory kernel / '../WebServer.star') zip) ] initializeWiki [ "Only run this method the first time." "WikiServer initializeNormalWiki" self initializeImages. self wikiDirectories do: [:eachName | "Only run this method the first time." | wiki | wiki := Wiki new. wiki persistanceManager: (FlatFileWiki directory: eachName). wiki name: eachName. wiki rootPageTitle: 'Home Page'. wiki syntaxPageTitle: 'Wiki Syntax'. wiki filesPath: '/images'. wiki save. (self at: 8080) handler addComponent: wiki]. (self at: 8080) start ] initializeWikiNoImages [ "Only run this method the first time." "WikiServer initializeWikiNoImages" self wikiDirectories do: [:eachName | "Only run this method the first time." | wiki | wiki := Wiki new. wiki persistanceManager: (FlatFileWiki directory: eachName). wiki name: eachName. wiki rootPageTitle: 'Home Page'. wiki syntaxPageTitle: 'Wiki Syntax'. wiki save. (self at: 8080) handler addComponent: wiki]. (self at: 8080) start ] restartWiki [ "WikiServer restartWiki" self initializeImages. self wikiDirectories do: [:eachName | (self at: 8080) handler addComponent: (FlatFileWiki directory: eachName) load]. (self at: 8080) start ] restartWikiNoImages [ "WikiServer restartWikiNoImages" self wikiDirectories do: [:eachName | (self at: 8080) handler addComponent: (((FlatFileWiki directory: eachName) load) filesPath: nil; yourself)]. (self at: 8080) start ] ] Eval [ WikiPageHTML initialize ] smalltalk-3.2.5/packages/httpd/test.st0000644000175000017500000000064612123404352014660 00000000000000Eval [ PackageLoader fileInPackage: 'WebServer' ] Namespace current: NetClients.WikiWorks [ Smalltalk arguments do: [:each | FileStream fileIn: each] ] Eval [ ObjectMemory snapshot ] Namespace current: NetClients.WikiWorks [ WebServer publishMyFileSystem. "WebServer initializeWiki." "WebServer restartWikiNoImages." "WebServer restartWiki." Processor activeProcess suspend ] smalltalk-3.2.5/packages/httpd/help.jpg0000644000175000017500000000406112123404352014756 00000000000000ÿØÿàJFIFÿÛCÿÛCÿÀ$/"ÿÄ ÿĵ}!1AQa"q2‘¡#B±ÁRÑð$3br‚ %&'()*456789:CDEFGHIJSTUVWXYZcdefghijstuvwxyzƒ„…†‡ˆ‰Š’“”•–—˜™š¢£¤¥¦§¨©ª²³´µ¶·¸¹ºÂÃÄÅÆÇÈÉÊÒÓÔÕÖרÙÚáâãäåæçèéêñòóôõö÷øùúÿÄ ÿĵw!1AQaq"2B‘¡±Á #3RðbrÑ $4á%ñ&'()*56789:CDEFGHIJSTUVWXYZcdefghijstuvwxyz‚ƒ„…†‡ˆ‰Š’“”•–—˜™š¢£¤¥¦§¨©ª²³´µ¶·¸¹ºÂÃÄÅÆÇÈÉÊÒÓÔÕÖרÙÚâãäåæçèéêòóôõö÷øùúÿÚ ?þþ) Š ?@2ii žŒ?B0h½·?/¾/ÿÁ`?aσ5ñÃÍ{âˆ5Ÿø?^Õ¼1âÍ3Ãñ^£…®èWÓ麶™s©Ýi–ö·sÃmÿ]´»¸°¶}s[R†k«-'M}A´bWŸðAÙâ÷‚5Ï‹¿´Œ<-¯ü;ø{ã¯é^ð‡5Èïì¦ñ<_Û']A§ê,—i6QÛ[XßO[Á­\µ´Œ©+?ÇG6Íéq+©,>6†#ÚJ¤hÆjxhE^œª7&½ë¥ªM½’º¿óµ=ñ â¾KÁxêÙOeù²ÅOK.¥ˆXœž8)áªbêάáûå(«Ns•ù"“ÿ¥z(¢¾ÄþІàg×'ðÿ=)yúñøæƒ“Ðãž½r?Ïò¯ý¥¾!xŸáoÂ=GÆ^·[ÝzÏÆ ô{{#œi⿊ž ðž«an5 ¸-㼟IÖ¯¢‚I§Š(¦š9^DT,2«R4iT«;¸ÒŒ¤ì®ì“nË«·N§a£—`q™†!7CNuf¢¹¤ãN.R²êíesòþ ¢xG]ø›ð çÄÿ³íñæãš/‰5Wø!©ÝØiZ$÷:î…,úgˆã·øs®y×R¾‰g$?½·"! Øûƒ/îö‡rך6—xöRiíw§ÙÜÉe*•–ͧ¶Žf¶•J)FÎQ² å@é_kŸ·‡¼?<^Ö¼ ö_¢ñ4 CŸŠt *Ö?‡zgu­kU·ñ…Ò‹{ÈgÓ¾'|?[8„+3Ýø“ɹ[[{KËÈ)h¶5þ¥â˱§øO]ñ‹ãÍCগð£Ãw–>×´«Ÿ‰ßüIñ:y%!Ñ‹âÏÙêüY¦ÝxÃãçto[ƒÇ>/“Ä÷Þ øñ‡LðüçÅzÌš„šŠÙÛ"Ý\Ës$ú‰’VÔdº3L\¢¼ì]*œä©EI¸Êüª÷k•½·¶—ÞÚl|'e¹t0XšÀQ…IÖ¥7%J NNRƒ“j7rpJ ½\}ÛÛCíïxÃ?|-¦xCÂiÚ˜o§‚ ‹ýGV¼ž÷WÔnõcSÔµm^î{½cW¼Ö5 û»Ë˹溻º½šââY&‘ݺæ$GùæŠ+Ц”aÅ(Æ)$–‰%]½ÂS§K †¥JœiÒ§NŒb”c¨¤”R²I$’IYÿÙsmalltalk-3.2.5/packages/httpd/history.jpg0000644000175000017500000000407612123404352015535 00000000000000ÿØÿàJFIFÿÛCÿÛCÿÀ$/"ÿÄ ÿĵ}!1AQa"q2‘¡#B±ÁRÑð$3br‚ %&'()*456789:CDEFGHIJSTUVWXYZcdefghijstuvwxyzƒ„…†‡ˆ‰Š’“”•–—˜™š¢£¤¥¦§¨©ª²³´µ¶·¸¹ºÂÃÄÅÆÇÈÉÊÒÓÔÕÖרÙÚáâãäåæçèéêñòóôõö÷øùúÿÄ ÿĵw!1AQaq"2B‘¡±Á #3RðbrÑ $4á%ñ&'()*56789:CDEFGHIJSTUVWXYZcdefghijstuvwxyz‚ƒ„…†‡ˆ‰Š’“”•–—˜™š¢£¤¥¦§¨©ª²³´µ¶·¸¹ºÂÃÄÅÆÇÈÉÊÒÓÔÕÖרÙÚâãäåæçèéêòóôõö÷øùúÿÚ ?þýøÇl~¥ýzt÷ïô¤9ÇNžß‡çúVŠgÖí|5¯ÜøfÖÞûÄú6©>‡es'“kw«Ec<šu­Ä þê /Vvu\žÕ-¤›zõï÷Õ¨©R©UÅÍRNVм•ì—Vú.§˜üNøýð×á&·àÏ x»_··ñõÛ]Ã:r$ºýÝËìóÜ6VÙw9À´ÏŠ´Ã?„šïÃÿ x¿^··ñ'Äßè> 𦉤šþ§â V×Iµ—ìÁ·Gf“ÝÄdŒï_Ǿ³ñöžñü§ÂWì.ãø£ø÷Èð×…µ)&¶ÐìÒ ¥:M¦»å{íˆùŠýÙ' ëwšÑüi}«Ø\ÚÝøëÁòHšÆ¥}¬ßË6ž.-á”Ç…\E*¬ù”švv´yow²ø–ûß¹Á‹Ìðx B8ªŽ—´Œç~VÒŒTœšMGYÅ+îÚKS¹øÙû|-øÏñá¿Å}GNJøƒð×ÄZΗâ(#K«Ûki’išƒ*ÿ¤Û°û»²TŽ*Ÿ±ß¿?~üYÔl#Ò~!ü$ñ¿…|[¥x‚ÊÝëP‡ÃšÕ޲Ú>¡&ßô‹i~Å´IO3"¸KÛ¦ÇW½†ÏáÇÁÿøþh>-Ø|,Õ,4Ï| µ×#¹¸ÓüyuyzÞ¾øÃï…omî|åɧx¦ê8Õ“-½ä6Ýýïí‡àm2}Uõ?üG³Ðâ›Ä¶þñ0Ñ´;Í'â-Ç‚¾ è <[ƒítïM¨¬¶ž-ñž®­a¥¶«h%Ôt5Õ,a’á|åýWÛÏ’›U% ’—+IÊ6qÚJéÛUÕÅ}¥–€±²Ì*OBQÆÖ¥ˆ¯'MÆ­FÞÊ·3Š<_"ç‹ÝÁ7y+ýjTàN{‚GùïNv9ÆAÜúóÏzõ)Ô§U7NWQvvèû>ÍuOT}¾C KUUTß,­vKx˪’êž«K Àeô+ƒô"¼&óöqøO}iáëkõãðͯ‹,´r5½YÞ|Cð‡Å?+²]=¦ñ§€ü3r¥÷£²{h¶ÛÍ4nQQVœ'~ ~ëZ¤ô¼]µét¾äscèѬœjÒUÉ%iEIYÊ ­SÑ´›]ZO¢9CöLøG©j:–·|ÿ¯ÓþÙªj"h¡-Ì7fÖëζH¡E¿eŸƒ‡UÕuWÒ|E<·÷zµüW~8ñö‹¢]x—Çš/ÄÏIá½ ÷[’Ï@Ž<;£ßÝ-¬1©kO"!¬’@åÍ= ¿ÜÃÞnþê×Yo¦»/¹[ËðÓÿa£ï'ÝC]fõ÷uÕ'ò]ŽSDð§‡õ?Ûƒâ'‹î´Ëvñ'‚¿f?ƒz‰«¢ìº]#â'ÅŽ÷¾!±º`qsºøgáǶÈÜËy´‘tà}oÜ{ŸèMWN%–IsNMù»îüô=²1…Æ{¸í)³´!@·”šŒ\žŠ*ïÑV« 4jÖ©gJ.R²»²WvKW§DpŸþ;ü ø ¥éº×Åÿˆø¤ëa¥ÞøŽù,a¾½EG{[MÃ3J#p̪ –?($w^ñO‡¼i i~+ð¦±câ ë–qjF³¦N—Vœàùw6—²ÄØ$0àóoáCöûÿ‚‹üLý¸Â>ñÏ€|-àm;ᯈñ/ÁÊ“†EˆThà1^Æ¿¶­Œœ©ÆTêÁ¯ÝÁJSQœ£îÝ»3ú ã½.ü€üJ@sÛçÜR×ÞYi¦ÇõEÓþ¾aL–4š7ŠTY#•Z9#p]mue# ¥IÈ<Å;ôà ùÎ3×é^Eñ£âF³ð˺n¯áÏ XøÃÄ÷Œ<à­DÕ|E/…4©5ë–º%µÞ©¯[h¤¶| rf™¡Óîædˆ¬p»•3œiÅÎ ßFÿvþF8ŠÔ°ô*V®Ú¥IsKG'oðÅ6ýw?0?à§¿ðLýSö³ðßÃhþé¿ <â_ x‡_Ô|Gsu¤[h â =rÓN·æûBÒ[«˜f²g\ƒæ·!ˆ#í¯ØÛöUðßìÓð?áwµ- Á—¿xÊúݼQ7à6qÚ.#’KÕÓâïÛ'âô<Ð>|5ðÀñߊÿ>|BƒÆž=k?EªüUøááoi–^¾ð÷…õ­oH¿ð~§wxu§²·‹I¸¿O’Æÿ]Ò­6ƒªx‹\Ñä¿ðæ—rö§‹¼BÞ/ñMÔ/-±9Ô|TßÚW¨IK›èÒêey£GVÞ|ø3©i×MïÃ?Üi×¶·¶—¶²hV;Øï¼`¿nd¼ýÎnîÏëkq!iãÕ§—QŽE¼šYœ¢°t(¹Mº1nVOÝZ«%g¦ªÚzhyßQÁ7VOIÊ¥”Ÿ³…ä½Õfíª²JÏKi±ê–6šežao¥†Ÿk•¤+²kKHÖ h"A÷#HcEQØ(k¡¶éñ¢ŠÝè•´Ûó=¤£•’HÿÙsmalltalk-3.2.5/packages/httpd/package.xml0000644000175000017500000000116112123404352015437 00000000000000 WebServer NetClients.WikiWorks NetClients WebServer.st FileServer.st WikiServer.st STT.st Haiku.st edit.jpg example1.stt example2.stt find.jpg head.jpg help.jpg history.jpg next.jpg prev.jpg recent.jpg rename.jpg test.st top.jpg ChangeLog smalltalk-3.2.5/packages/httpd/head.jpg0000644000175000017500000002241012123404352014725 00000000000000ÿØÿàJFIFÿÛCÿÛCÿÀ$È"ÿÄ ÿĵ}!1AQa"q2‘¡#B±ÁRÑð$3br‚ %&'()*456789:CDEFGHIJSTUVWXYZcdefghijstuvwxyzƒ„…†‡ˆ‰Š’“”•–—˜™š¢£¤¥¦§¨©ª²³´µ¶·¸¹ºÂÃÄÅÆÇÈÉÊÒÓÔÕÖרÙÚáâãäåæçèéêñòóôõö÷øùúÿÄ ÿĵw!1AQaq"2B‘¡±Á #3RðbrÑ $4á%ñ&'()*56789:CDEFGHIJSTUVWXYZcdefghijstuvwxyz‚ƒ„…†‡ˆ‰Š’“”•–—˜™š¢£¤¥¦§¨©ª²³´µ¶·¸¹ºÂÃÄÅÆÇÈÉÊÒÓÔÕÖרÙÚâãäåæçèéêòóôõö÷øùúÿÚ ?þàj_ø—áÇìÇûF|Cðf¥ýãüø½ã? jÿc°Ô²¼Ká‡Þ!×4-Kû?UµžÖûÈÕ,meòn`šÞ_+dÑI2,ý›¼Qñ7]ñ¿-n¼[ñ·â/Áû? ø~mÆ´GÁK¾>_ˆSjšÂëZƒáû„ÞŸ[ð¤ziKuuáˆÒ+©’+MRÿ}Ô6_QxßÁžøà¿ü<ñž›ý³àÿx__ðgŠô¶_éßÚ¾ñF“w¡ëºoö†•uÕŸ¥ß]Eç[O Ä^nøeŽEWEpÏ ZxØb>°áBœb”§ïI:œÜÑæP³RŽñ”›Š³‡/½óXœ›0Äñ&6þÕ©‡Ë0”iEa©Ô®•Z©âÕGRš«3§(Ö¢ÛÕe*Qägz¥|qàÏÚcÆ^"ñÃýWXøqáý#à߯ˆÞ/øeð×Åv^9¾Õ¿×§Ñ´¿†Þ)Òd°×’ÙüCà­~OŠ¿ÅzÞ´W]ø3áïÁïk·HóÉ©¢éöQKg5ünŸf×ø‹á7ïxËEñÿ‰<+a¬x·ÃÞñtRöKÉÛ¾=}¼W¥I¦‹‘ix·K¡XGçO—ð½Ô²Ã õê\V2ª””pu• ×^ô’’åwRѧ¬S玖rŠŒ½×#^ Ãg¸¬ iðöcO,ÇûHÞ¥Zq©e%(Tj2„×´¦§íè§YÖ¥ uZ£:…O„ŸÏÅ_ jž,‡F>—>$øGCí!©{Iø}ãÏø/#-Œ+ki©ÜørêòÖ%3iuo ¸“Ìùmü\ø‘¤|ø]ñ⦽my}¤|=ðˆ<_}§éè^ÿQ‹BÓ.5ÓlWiòâH‹açVªa¯à/øWႼ+ðïÀÚRè~ðVƒ¦xkÃZBÞj‰Óôm"Ö;+i5Zî{½FqIæ\]O5ÌîZYæ–WwmOø{Dñw‡µß x›K³Öü7â}Tð÷ˆ4]B!=†¯¢kV3麶—}q5Å…ÍÄR¡á’V­Tc‰úªŒªGë~ÎÎV¼}§.ö²¼Tµµ“k¡µ*9ÂÈáB¦*—öÿÕy]n^j+éYÔQP¦åEVÕ.H7“ŠmŸ1þÍ¿´o‰þ5k¾8ðçŠ~ÿÂ+7…´¿ ëšoˆ´‹OЉá]rÛÄw> µºÐ£¸ø¯ðŸð’irh–ív-ìî­%·×-&Žâ7i­¡úÖ¼Ÿá·Á¿ |,›T›Ãú÷ÄídjvÖ)Ä‹Ÿ>&Zhúv˜÷/gc ZøûÅ:Œz8ježxUo/ÞÝonnE­°‹Ö*pPÅCã**¸„åy-¬äÜV‰l¬¶é®¦\;C;ÃejKs·+Ÿü#ýµu/Šÿ´_iÿ oWÀ^-ñ?ÄO x{Å–6?åÕ´à]Zø«Æï­|Óü1¦øcY‹Á÷±Ù;Å:Õ½Öµ¤ÚM“ÝÝ®›÷Õxg…ÿg‡~ ñľ:ðÅ×Ä=iu¯ø”ø>ÓâÇÄÅø^ž$ñœš”þ&ÖÓásx¬è"æêóXÕnš°8ïõ 5(m£ÔvÝ/¹Ö xêtª,´kÖsm8«%Xék/´¤õ»³Júiæp¶‰°˜M>*Ì(æY„«ÊTçB N’PK’øª¬×73Qš5¢£ÏïÚgãßÅë+/ŒÚÂ? øzÃEøAsð³KñÇÄmcÇZ–…â{m{Ç—†uË+ÀÞ°ð.¥°¶~ ×4Yn./µ:+™ ƒZø…ñ/Æþ=»Ò<# Is'‡¼áýOâ'‰µ 4_Ãwyw*Û[Ȇâyüˆã„ÇÁ^–-ã0õ©UPÃÁ5Q9o­þvÖ‰©Á§«æK•ü¾gÏeÄVc€ÇG”Ѓ†*œª$¤¹¹¯ìž¢›q÷c8â0Ò§'Ï/mû){Í|££þÓ§Uøƒgðþ„‡â‚|gñ·ÃÏø]$ñ_€üðÇïe¤ý‹PÑ|!á›Í__ÖSSÔLìu}OSñ&¯nf“j*XøOH·UÝo#ɦ%be<:ÂÍE{DªÝEÚœ›×^gÊ¡]{í´ìœz³˜çU+åÉq*Œ*0Æ^4䣅ä•YÍs§%UºP¡K–ñ_Y”çMòÆ¥/s¢Š+¬÷Š( Å¿Úóâ¯ÆßÚcöÒð¯ü«àÄm{àï…4/ÛüTý§>*ø*æ}?ÇÚ†f6“Ûø;ÃšŠ´O¤Ç5–µák‹i§¹ñ½º\/Øl/moµ¥ÿ‚"~Êv6pÞx7âí!àˆJ'±ø£¢|W?ð—ÿjÄ7è޴š¶v7K ’­¬NÞ^!–ݰëãßüaáïØÃþ ;yñ“ã%òøsáí…ðNð…ñ#T3iþðŒtð÷F—Oñµ=˜†Þ8î~h+y![éÐüHÓµ BæÚÊ;‡‡é¿ÛÃötñ¿Œ<9ñ3ö™ðwí½ûCüÐüðgVñ‘à†_n|5ð×R»ð¯‡µ}oMÔYôíZÞ]Råìâ’u,ò«Ä"výÚö8\kÏqy†^³Œ~VÊu#C ¥FTÔåN2¦•NhZU')>fÓQþVþÎÉx†~'g¼W°ñŠ8s<Ça¾¥_JL¯'¡ÏW EZtð´ëa# _¶ £[ZµI{YJ›?šà¥^ ø¯ð/þ 7€~ ücñň^ø…á+Sø³uu«XxƒÆ=ÇÄÝwPðÍÆ³%Ö¥qr5ü->ƒmt²Þ]Ÿ?NlÝ]`O'¯Á4ümãÿ~:Á8¾1ëZƳâ¯ÚÆ¥ãï^*×Ý¥ºñÿÀjpÜX]Ãt ‰-Í•ö­c<± ™ÞÞOÜé‘íMuó÷ãÏŽ¼iñ+þ ð»Æ¿üYâ?øÇZñäXñW‹uCÄ>!ÕNñïâ“`ÚŽ±ªÜKqzÐé–6Vñ™$bÚÇ!Q@ýÿ‚¤ü1ñgÂ/ø(GÁ2K¯‹Ÿ².¹÷Œôë7û<ž;ø©\ÜGão jrÅc4²YYÅ©êŽÌ %ž•â}~óæž;rœ”êòãcŸ`£QRÀeùlåJR•IKYb]hɶÜêSŒiÕRm¹J®ù™âa±’¥Ä°ñG‡(â£á^àìMLJÕq5ªðþc êY…’”§ü[¾øwðörÒ¾#[ü5ðωtM Ä>5ðññE¾‰||ÏkßdÑ4›»‹‹,_5Ôi§þÍû¤£ßà™¾ý–>5øOâ7Àßô†–RøžO|ñOЧñGÃÏ[ÂúΠMm´¶NºÒõ}NÞþ9u5‰¤k0‘KjY¤2|Lý˜¿à›ßðP?øêã[Ò¼ ãŒ~Ö¼Aà?ê¾ ñN­à¯ŠÞÖü­7‚µ(¼g£iöwÂÚ^è`°¾Öl/­$³·ˆéSÉfðHßžøPÿðOOø(çìµû?þÉÿ>!|CðWƹ*²ñ¿‚4tØõãMB×K´²´Ó¡«iŽláÕ¡À× -ÝÞ›ª›Y~f8Xeµècqø­:¸Èòcèâ%õžj¸„©FTÚ¼Ô£ S¥ZPöq»k™ŒQÉ0Ü™å¼IÄÜ3–qΟÒX~(ÀfÕ¿¶=®;4QÀÒ­„”ÄC R­<=\ Z‡Õ(ÊøIÓUiŸ£?ÿà¨ÿ>|uø‡û3Áð«ö†øñ¿À‰áo±x/áoý?ÅòøÞ_x;Jñ´ ág°ñ1¸vFµ§iË{ihгÈlâ¿XØ×œhðXÿ€÷ÖúÇ…u߃´Ï‡¿h_´ðÔ²çü*mGUøË¯jW¶GS†év·+o.ûéþÝ6Ÿzˆ¥â±ž9-žã?öjU?ðX?ø)‡ÃÙ±C`n ß >P{Ur;킹oƒ±Æ¿ð]_ÚÁÖ4W“öCð›;ª¨go´þϱîv,Û"‰r{F£ ëžcÊtjÓÇÓ…,VeˆÀÆ¥ÉN1Nohœª%EZö†¾ô$Ór÷ëqo‰ëåøì/a0Ø<óŒ3n§†–U ‹ „Ãbój4q^×ëP©[N9|T\œ0íM{\=YAºŸ[þÉÿ·÷¿jˆ;ø1¨ü/ø·ðãí ÏÅ~!øWñ‹Ã-áýzO ßO§A»§![Çý¹á¶•/`²•“Ä–rÙ­å»I4\WÆ?ø(¾§ðïâ/Œ¾xö+ý²>8ÞøZm ľ,ø}ð¢âÿÀR^gXj1¯‡¼E§ÜÞI«·—|Ö[[F 1ù¨CW’øÅßþ ð¡ U€ß~Á:‹Þ˜TDo>'|Jè h`–vŠ äk"ãÇþ xëöÃÿ‚‘]|wñï‡ÿkÅý‘>ü/ø½âO†ÚÂÿü8ðÞ«ñ tÿÙ¸¼OãÿëšÔWÚ̺^³o‹ ÃX\_i7²Cgcö^[–k™{/¨G:ÙœqXŠ0•*49ªÓ¡ÍÊJµHQ§ÊªEI¦Üš÷a«·E^9ã‚— QÍñþ3£æ™} ¸X«c°™n†*u«G1Åa²ì#¥OF5§JU\-CyË“õöSý¯þ~Ø>ñŠ>§ŠôMGÁ^%¹ðŽüñ C‡Ã>?ðGˆ-ü–>#Ðíõ¸­üÔŠcÝO{[‹wtºµº‚ÿÙþPñëþÁŸ?õ$²¯pÿ‚2XÙiŸ´üÃNÓ¾$Ý|b²²ø­ðÊÖÛâ¥ö­c®Þ|AŽOã|ð–]kZlÒ[ê³Þ²™Úâ9L¥Ñ˜kÃÿeÿù@Oǯû|hÿԒʼécëæXL3¢±˳¸Ë–Ön•\=+«9/yA7ÊÜnß+µŽ­Å§ä|+Ÿçq§×Â^$P¬è¨ªr– •àUD¡:°N¤pʤ•:“§Í){98rGí»ûAüJøÿ©ÿ‚Ú|+Ô¾1x3Äž0øaû:Í?Äφsêz&‡ é^ø5ᆺð—‹<]¤j¶óéZ޵6·k.—dXõð¦¦dhŘYZ¾þÚÖ~?ð·ÅÏë³íƒð‡Iø?à-Wâ¦>3|²ðEçŒ,t};TÕ.ô/‡ÖÃÆ_ð’xŸìÚTÛm˜Û¦ë˜çO4üÿ‚…G#Á¿b¹Ö)/ ~Ç—7r¤nékoÿ J{>vE"(¼ùà@Í€^d@w2ƒûûr~Ó7ß³ì—ñgãß­|=âÏøOÞ¾ð¦¨^™ô{¹|mã? øHñÔztë&¥¡Û\x¢ ÖHe‰oËìésš&N¼zø|niŠ©˜:8,_«(r)¥CÛJ÷÷\ß.³º‹vHú̳<£ˆxß:ÅñML¿‡xo…8kWðÑÄEQŽY›J¤éÅÉM:sÃμÕ$§ˆr;B |›wÿlÓ¼8ãÄßbOÛá—Á¼ÛIqñsÆ?n¬tmO½ ]g^²KÆŽËI-!c$·nÑìh"äXê·üßĺŒÿa?xÃÂÚ¾µáŸ|[øâ_ë6eͦ­¡kºÌ¦‘©Ú™XÛϧÝ[Ê›•[l£ +æOŽ?¿hýsö'ñ×íûDÁKõ]OFñŸìñâïi¿ < ᯆß¾øÇ]ñ7­wQðßÂÛ vÒe_Øj s=ŽØ¬"¾ÔÕÄÐ,7pGp´?iOùBŸìƒôý“ÿôm•râsʶ;Áã¹¥N¦u麑¡ ‰7˪ÃÕ© &šR|é§vÓÓÁÎø»Œqü-âWñ7¶«„Åp½|Ó ,]®†20”Õ¥O*Æc(Æ…XTŒ©Â¼–"„”§QKÜûöûÿ“Çÿ‚WÿÙwø•ÿ¨¿…ëë~Ø? ü#ûDx/ö[Ñ|9ñâwÆi¿ðkz/Ã}#AÔôß…Þg·ø·â–·âi–þѤ†24‰®ï¤O)c³io´Øï>ÿ‚¬[|O½øùÿà±ø/¨xoGø¥ñâ~Ÿà­kÅÖó^xsBÖ/¼9áE×uK(#v½†ÆÞiî–.UšKDᙢuÿ‚_øÃŸ<ñŸöWøåở þÜ“x—ZñÿÄOˆ^'Õ.µË¿ÚƒÃ·:…íÖ“ãÿø«W¶†mGG´Óî$UÒcU[x£¸¿Ž3ru¨ì=(ãëQâËMýZÌMלow‡j…>žÞªO—žÑPRqçŸ,O±¥Å†_âÇpÆK&£ÄÖ\êfxŠ\øvépþS%•á_ðÿ´±ÑŒý“ÄrÒ§B%N8ŒC¥Dý«¢Š+íèࢊ(˾0|øQñÿÁ7¿~2øÃÿ¼º†S•agZ®,Ãáêâ(ÑÃT•:4á)áðê¢ÃЛŒS• µeF”›…%V¢„cÏ+øGìëû(|ý“´/økà€áÑ4ñOÛõ[[5°‚ëí>5ñ¥-®ÛDTÙ ‘Æq¸¡oš¾tøçÿªý‰?hké¾ñ>±dº~±ã}_PÕüWãMBË|rÏf¾!ñ%õÌÚF<ð[Ksg§ýŽÎâkHešÝä†&BŠòieye,ÎxŠYu x…oi4Ôù¤õ—2Š—3»»½ßSápÁx.2Äfø.Êð™¬i{eŠ¥—á)âj“j¥UZUEVjMN§74“|ÍÝž¯á¯€ |ñƒâOÇ¿xOû;âÏÅÝ7ÃZOÄ?ÿnø–ïþ?ÁúVŸ¢xvßû ûY—MÒ~Ϧivo±³¶y¼ó´²3»UÑÿgoƒšÇ_þÒÚOƒþÉñ³Æþ´ðŠät«''*«M*IÊMÍ{ÍÊM½]þÁdY"¬› £†ÅTÇÓ_W£jx겫:¸È.OwRuëJ¦"6­9V«)Mº“nÕ÷À?„º—Çö‘½ðŸñ§@ð ¿ ôŸÿnø–?²xmSUÖ¥Ðÿá‹Y]&|êzÖ§/Úe±{Áö‚àF‘¢|“ñ_þ Gû ügøŸ«|Zñ·ÂÏŠ¼Mª^k~2‡Ã¾3ñ—…4?kïç^êºî‘áírÞ8õîÌ—3X›9/.g–æñ®'–I¢¸ñÙv_ˆ£ÉˆÀQ¯ UŒÚ(I9ɨ¹µ(´æã£–íh݉8C„ó\ÕóN˳*±ÔqS†#†­ âjT§J¦"Q©JQ•z”’§:­:’§îJN:F|ý’ÿgÙPñö¥ðá¦ðâ‰×Zç Ò5Ýéš”Þ]et1e£k:ÕÍŸ‡­í×_ÕÂæÁiý¯÷ˆþ\[(x_ö9ýœ<ð _ý—¼5ðëû7à_‰âÖ¡×<ÿ wŽï>݈nRóX_øI¯üO.±mç\F˜uÌxÄE‘EÓ…8`¨Â8Ô„b©ÁF0ªÔªÅ%(Ôi:‘ZM¤ä›G­C…xc †¡ƒÃpæ„ÂÒÅP¥J<<)Ó¡ŽœjchÓ„i¨Â–2¤cÁû4x‹ÀÖ:ÏÀû_øoáå¿u G\¹·‡Â~¶Òí|/`šÜš¡ÔÖöÁtM"Kkÿ¶ÿhEs§Ev·_jA5|÷ðKþ ±ûüÐ~%øoÁ_ æÔ´‹ºü"¾=³ñ·‰üGã ]gÂhþu¯†ÆŸ¬jOkicÛM<3Eß$Óo7måÀ"(¬keø ˜¬-Z˜*3«F„$éAÊ0µ¹#'Æ6”—*iZM[Vy™‡ ðÆ+=Èq¸®Àbq˜6# BµLuháÕ5aJ¤©¹Ó£ÉV¬=”‡-J‘å´äŸ›xWþõÿøðž¡®ßÁð5õ´ÖôísG‡Oñ?~!kºo‡ô¿iwÚ>©máë{¿æÆóìWò›mBG›T°ž(®ì/­®âI‡Õ~%ý“gÿüð‡ìíâ/hüðü"ð‰ø?þ¯ÚeÂQ¼-ÿˆâÕ/¾ÊcOøù¾›ÏÇúG“E–)ÊèМ(å¸zQ¬¥¨Ñ§8¹k%¥e£ºÑi¡ËÃÜ Á~[Š¡€àì«C1XŠˆQËð”¡^Œ«IJhÂŒUZMB§5(>HÝ{ªÝ—þü,ø¡ã/… Current := nil. TestSuitesScripter class >> run: script quiet: quiet verbose: verbose [ | result | result := self withScript: script do: [:scripter | | suite | suite := scripter value. "Set log policy to write to stdout." quiet ifTrue: [suite logPolicy: TestLogPolicy null]. verbose ifTrue: [suite logPolicy: (TestVerboseLog on: stdout)]. (quiet or: [verbose]) ifFalse: [suite logPolicy: (TestCondensedLog on: stdout)]. suite run]. "Print result depending on verboseness." quiet ifFalse: [result runCount < result passedCount ifTrue: [stdout nl]. result printNl. result errorCount > 0 ifTrue: [stdout nextPutAll: 'Errors:'; nl. (result errors asSortedCollection: [:a :b | a printString <= b printString]) do: [:each | stdout nextPutAll: ' '; print: each; nl]]. result failureCount > 0 ifTrue: [stdout nextPutAll: 'Failures:'; nl. (result failures asSortedCollection: [:a :b | a printString <= b printString]) do: [:each | stdout nextPutAll: ' '; print: each; nl]]]. ^result ] TestSuitesScripter class >> current [ ^Current ] TestSuitesScripter class >> variableAt: aString ifAbsent: aBlock [ self current isNil ifTrue: [^aBlock value]. ^self current variableAt: aString ifAbsent: aBlock ] TestSuitesScripter class >> run: aString [ ^self withScript: aString do: [:scripter | scripter value run] ] TestSuitesScripter class >> withScript: aString do: aBlock [ | previous | previous := Current. ^[aBlock value: (Current := self script: aString)] sunitEnsure: [Current := previous] ] TestSuitesScripter class >> script: aString [ ^self new setScript: aString ] printOn: aStream [ super printOn: aStream. script isNil ifTrue: [^self]. aStream nextPut: $<; nextPutAll: script; nextPut: $> ] singleSuiteScript: aString [ | useHierarchy realName testCase | aString last = $* ifTrue: [realName := aString copyFrom: 1 to: aString size - 1. useHierarchy := true] ifFalse: [realName := aString. useHierarchy := false]. realName isEmpty ifTrue: [^nil]. testCase := SUnitNameResolver classNamed: realName. testCase isNil ifTrue: [^nil]. ^useHierarchy ifTrue: [self hierarchyOfTestSuitesFrom: testCase] ifFalse: [testCase suite] ] variableAt: aString put: valueString [ ^variables at: aString put: valueString ] variableAt: aString ifAbsent: aBlock [ ^variables at: aString ifAbsent: aBlock ] parseVariable: name [ | value ch | name isEmpty ifTrue: [self error: 'empty variable name']. (stream peekFor: $') ifFalse: [value := stream peek isSeparator ifTrue: [''] ifFalse: [(self getNextWord: '') ifNil: ['']]. ^self variableAt: name put: value]. value := WriteStream on: String new. [stream atEnd ifTrue: [self error: 'unterminated string']. (ch := stream next) ~= $' or: [stream peekFor: $']] whileTrue: [value nextPut: ch]. ^self variableAt: name put: value contents ] getNextToken [ | word | [self skipWhitespace. word := self getNextWord: '='. stream peekFor: $=] whileTrue: [self parseVariable: word]. ^word ] skipWhitespace [ [self skipComments. stream atEnd ifTrue: [^nil]. stream peek isSeparator] whileTrue: [stream next] ] getNextWord: extraDelimiters [ | word ch | stream atEnd ifTrue: [^nil]. word := WriteStream on: String new. [ch := stream peek. ch isSeparator ifTrue: [^word contents]. (extraDelimiters includes: ch) ifTrue: [^word contents]. word nextPut: stream next. stream atEnd ifTrue: [^word contents]] repeat ] hierarchyOfTestSuitesFrom: aTestCase [ | subSuite | subSuite := TestSuite new. aTestCase isAbstract ifFalse: [subSuite addTest: aTestCase suite]. aTestCase allSubclasses do: [:each | each isAbstract ifFalse: [subSuite addTest: each suite]]. ^subSuite ] setScript: aString [ variables := Dictionary new. script := aString ] skipComments [ [stream peekFor: $"] whileTrue: [stream skipTo: $"] ] value [ | suite subSuite token | suite := TestSuite new. stream := ReadStream on: script. [stream atEnd] whileFalse: [token := self getNextToken. token notNil ifTrue: [subSuite := self singleSuiteScript: token. subSuite notNil ifTrue: [suite addTest: subSuite]]]. ^suite ] ] smalltalk-3.2.5/packages/sunit/SUnit.st0000644000175000017500000005606212123404352014765 00000000000000Object subclass: TestSuite [ | tests resources name | TestSuite class >> named: aString [ ^(self new) name: aString; yourself ] run [ | result | result := TestResult new. self resources do: [:res | res isAvailable ifFalse: [^res signalInitializationError]]. [self run: result] sunitEnsure: [self resources do: [:each | each reset]]. ^result ] run: aResult [ self tests do: [:each | self sunitChanged: each. each run: aResult] ] addTest: aTest [ self tests add: aTest ] addTests: aCollection [ aCollection do: [:eachTest | self addTest: eachTest] ] defaultResources [ ^self tests inject: Set new into: [:coll :testCase | coll addAll: testCase resources; yourself] ] isLogging [ ^true ] logPolicy: aLogPolicy [ self tests do: [:each | each isLogging ifTrue: [each logPolicy: aLogPolicy]] ] name [ ^name ] name: aString [ name := aString ] resources [ resources isNil ifTrue: [resources := self defaultResources]. ^resources ] resources: anObject [ resources := anObject ] tests [ tests isNil ifTrue: [tests := OrderedCollection new]. ^tests ] addDependentToHierachy: anObject [ self sunitAddDependent: anObject. self tests do: [:each | each addDependentToHierachy: anObject] ] removeDependentFromHierachy: anObject [ self sunitRemoveDependent: anObject. self tests do: [:each | each removeDependentFromHierachy: anObject] ] ] Object subclass: TestResource [ | name description | TestResource class [ | current | ] TestResource class >> new [ ^super new initialize ] TestResource class >> reset [ current notNil ifTrue: [[current tearDown] ensure: [current := nil]] ] TestResource class >> signalInitializationError [ ^TestResult signalErrorWith: 'Resource ' , self name , ' could not be initialized' ] TestResource class >> isAbstract [ "Override to true if a TestResource subclass is Abstract and should not have TestCase instances built from it" ^self name = #TestResource ] TestResource class >> isAvailable [ ^self current notNil and: [self current isAvailable] ] TestResource class >> isUnavailable [ ^self isAvailable not ] TestResource class >> current [ current isNil ifTrue: [current := self new]. ^current ] TestResource class >> current: aTestResource [ current := aTestResource ] TestResource class >> resources [ ^#() ] description [ description isNil ifTrue: [^'']. ^description ] description: aString [ description := aString ] name [ name isNil ifTrue: [^self printString]. ^name ] name: aString [ name := aString ] resources [ ^self class resources ] setUp [ "Does nothing. Subclasses should override this to initialize their resource" ] signalInitializationError [ ^self class signalInitializationError ] tearDown [ "Does nothing. Subclasses should override this to tear down their resource" ] isAvailable [ "override to provide information on the readiness of the resource" ^true ] isUnavailable [ "override to provide information on the readiness of the resource" ^self isAvailable not ] printOn: aStream [ aStream nextPutAll: self class printString ] initialize [ self setUp ] ] Object subclass: TestResult [ | failures errors passed | TestResult class >> error [ ^SUnitNameResolver errorObject ] TestResult class >> failure [ ^TestFailure ] TestResult class >> resumableFailure [ ^ResumableTestFailure ] TestResult class >> signalErrorWith: aString [ self error sunitSignalWith: aString ] TestResult class >> signalFailureWith: aString [ self failure sunitSignalWith: aString ] TestResult class >> new [ ^super new initialize ] correctCount [ "depreciated - use #passedCount" ^self passedCount ] defects [ ^(OrderedCollection new) addAll: self errors; addAll: self failures; yourself ] errorCount [ ^self errors size ] errors [ ^self unexpectedErrors ] expectedDefectCount [ ^self expectedDefects size ] expectedDefects [ ^errors , failures asOrderedCollection select: [:each | each shouldPass not] ] expectedPassCount [ ^self expectedPasses size ] expectedPasses [ ^passed select: [:each | each shouldPass] ] unexpectedErrorCount [ ^self unexpectedErrors size ] unexpectedErrors [ ^errors select: [:each | each shouldPass] ] unexpectedFailureCount [ ^self unexpectedFailures size ] unexpectedFailures [ ^failures select: [:each | each shouldPass] ] unexpectedPassCount [ ^self unexpectedPasses size ] unexpectedPasses [ ^passed select: [:each | each shouldPass not] ] failureCount [ ^self failures size ] failures [ ^failures ] passed [ ^self expectedPasses, self expectedDefects ] passedCount [ ^self passed size ] runCount [ ^passed size + failures size + errors size ] tests [ ^(OrderedCollection new: self runCount) addAll: passed; addAll: errors; addAll: failures; yourself ] hasErrors [ ^self errors size > 0 ] hasFailures [ ^self failures size > 0 ] hasPassed [ ^self hasErrors not and: [self hasFailures not] ] isError: aTestCase [ ^self errors includes: aTestCase ] isFailure: aTestCase [ ^self failures includes: aTestCase ] isPassed: aTestCase [ ^self passed includes: aTestCase ] initialize [ errors := Set new. failures := Set new. passed := OrderedCollection new. ] runCase: aTestCase [ | testCasePassed | aTestCase logPolicy startTestCase: aTestCase. testCasePassed := [ [aTestCase runCase. true] sunitOn: self class failure do: [:signal | failures add: aTestCase. signal sunitExitWith: false]] sunitOn: self class error do: [:signal | (errors includes: aTestCase) ifFalse: [aTestCase logError: signal]. errors add: aTestCase. signal sunitExitWith: false]. aTestCase logPolicy flush. testCasePassed ifTrue: [passed add: aTestCase] ] printOn: aStream [ aStream nextPutAll: self runCount printString; nextPutAll: ' run'. self expectedPassCount > 0 ifTrue: [ aStream nextPutAll: ', '; nextPutAll: self expectedPassCount printString; nextPutAll: ' passes' ]. self expectedDefectCount > 0 ifTrue: [ aStream nextPutAll: ', '; nextPutAll: self expectedDefectCount printString; nextPutAll: ' expected failures' ]. self unexpectedFailureCount > 0 ifTrue: [ aStream nextPutAll: ', '; nextPutAll: self unexpectedFailureCount printString; nextPutAll: ' failures' ]. self unexpectedErrorCount > 0 ifTrue: [ aStream nextPutAll: ', '; nextPutAll: self unexpectedErrorCount printString; nextPutAll: ' errors' ]. self unexpectedPassCount > 0 ifTrue: [ aStream nextPutAll: ', '; nextPutAll: self unexpectedPassCount printString; nextPutAll: ' unexpected passes' ] ] ] Object subclass: TestLogPolicy [ | logDevice testCase | the device on which the test results are logged testCase the test case that''s being run '> TestLogPolicy class >> null [ ^TestLogPolicy on: (WriteStream on: String new) ] TestLogPolicy class >> on: aStream [ ^self new initialize: aStream ] initialize: aStream [ logDevice := aStream ] logDevice [ ^logDevice ] testCase [ ^testCase ] flush [ logDevice flush ] logError: exception [ ] logFailure: failure [ ] logSuccess [ ] nextPut: aCharacter [ logDevice nextPut: aCharacter ] nextPutAll: aString [ logDevice nextPutAll: aString ] print: anObject [ anObject printOn: logDevice ] showCr: aString [ logDevice nextPutAll: aString; nl ] space [ logDevice nextPut: $ ] startTestCase: aTestCase [ testCase := aTestCase ] ] TestLogPolicy subclass: TestVerboseLog [ | hadSuccesses | >#testMethod1 . TestCaseName>>#testMethod2 .. TestCaseName>>#testMethod3 .... FAILURE: failure description 1 ... ERROR FAILURE: failure description 2 TestCaseName>>#testMethod4 ................. where each dot is a successful assertion.'> flush [ hadSuccesses ifTrue: [self showCr: '']. hadSuccesses := false. super flush ] logError: exception [ exception messageText displayNl. Smalltalk backtrace. self flush. self showCr: 'ERROR' ] logFailure: failure [ self flush. (failure isNil) ifTrue: [self showCr: 'FAILURE: Assertion failed']; ifFalse: [self showCr: 'FAILURE: ' , failure] ] logSuccess [ hadSuccesses := true. self nextPut: $. ] startTestCase: aTestCase [ super startTestCase: aTestCase. hadSuccesses := true. self print: aTestCase; space ] ] TestVerboseLog subclass: TestCondensedLog [ | realLogDevice hadProblems | flush [ super flush. hadProblems ifTrue: [realLogDevice nextPutAll: self logDevice contents; flush]. self logDevice reset ] initialize: aStream [ realLogDevice := aStream. super initialize: (WriteStream on: String new) ] logError: exception [ hadProblems := true. super logError: exception ] logFailure: failure [ hadProblems := true. super logFailure: failure ] startTestCase: aTestCase [ hadProblems := false. super startTestCase: aTestCase ] ] TestLogPolicy subclass: TestFailureLog [ logFailure: failure [ failure isNil ifFalse: [self print: self testCase; nextPutAll: ': '; showCr: failure] ] ] Object subclass: TestCase [ | testSelector logPolicy | TestCase class >> debug: aSymbol [ ^(self selector: aSymbol) debug ] TestCase class >> run: aSymbol [ ^(self selector: aSymbol) run ] TestCase class >> selector: aSymbol [ ^self new setTestSelector: aSymbol ] TestCase class >> suite [ ^self buildSuite ] TestCase class >> buildSuite [ | suite | ^self isAbstract ifTrue: [suite := self suiteClass named: self name asString. self allSubclasses do: [:each | each isAbstract ifFalse: [suite addTest: each buildSuiteFromSelectors]]. suite] ifFalse: [self buildSuiteFromSelectors] ] TestCase class >> buildSuiteFromAllSelectors [ ^self buildSuiteFromMethods: self allTestSelectors ] TestCase class >> buildSuiteFromLocalSelectors [ ^self buildSuiteFromMethods: self testSelectors ] TestCase class >> buildSuiteFromMethods: testMethods [ ^testMethods inject: (self suiteClass named: self name asString) into: [:suite :selector | suite addTest: (self selector: selector); yourself] ] TestCase class >> buildSuiteFromSelectors [ ^self shouldInheritSelectors ifTrue: [self buildSuiteFromAllSelectors] ifFalse: [self buildSuiteFromLocalSelectors] ] TestCase class >> suiteClass [ ^TestSuite ] TestCase class >> allTestSelectors [ ^self sunitAllSelectors select: [:each | 'test*' sunitMatch: each] ] TestCase class >> resources [ ^#() ] TestCase class >> sunitVersion [ ^'3.1' ] TestCase class >> testSelectors [ ^self sunitSelectors select: [:each | 'test*' sunitMatch: each] ] TestCase class >> isAbstract [ "Override to true if a TestCase subclass is Abstract and should not have TestCase instances built from it" ^self name = #TestCase ] TestCase class >> shouldInheritSelectors [ "I should inherit from an Abstract superclass but not from a concrete one by default, unless I have no testSelectors in which case I must be expecting to inherit them from my superclass. If a test case with selectors wants to inherit selectors from a concrete superclass, override this to true in that subclass." ^self superclass isAbstract or: [self testSelectors isEmpty "$QA Ignore:Sends system method(superclass)$"] ] assert: aBoolean [ aBoolean ifTrue: [self logSuccess] ifFalse: [self logFailure: nil. TestResult failure sunitSignalWith: 'Assertion failed'] ] assert: aBoolean description: aString [ aBoolean ifTrue: [self logSuccess] ifFalse: [self logFailure: aString. TestResult failure sunitSignalWith: aString] ] assert: aBoolean description: aString resumable: resumableBoolean [ | exception | aBoolean ifTrue: [self logSuccess] ifFalse: [self logFailure: aString. exception := resumableBoolean ifTrue: [TestResult resumableFailure] ifFalse: [TestResult failure]. exception sunitSignalWith: aString] ] deny: aBoolean [ self assert: aBoolean not ] deny: aBoolean description: aString [ self assert: aBoolean not description: aString ] deny: aBoolean description: aString resumable: resumableBoolean [ self assert: aBoolean not description: aString resumable: resumableBoolean ] logError: aSignal [ self logPolicy logError: aSignal ] logFailure: anObject [ self logPolicy logFailure: anObject ] logPolicy [ logPolicy isNil ifTrue: [logPolicy := self defaultLogPolicy]. ^logPolicy ] logPolicy: aLogPolicy [ logPolicy := aLogPolicy ] logSuccess [ self logPolicy logSuccess ] defaultLogPolicy [ ^self isLogging ifTrue: [self defaultLogPolicyClass on: self failureLog] ifFalse: [TestLogPolicy null] ] defaultLogPolicyClass [ ^TestCondensedLog ] resources [ | allResources resourceQueue | allResources := Set new. resourceQueue := OrderedCollection new. resourceQueue addAll: self class resources. [resourceQueue isEmpty] whileFalse: [| next | next := resourceQueue removeFirst. allResources add: next. resourceQueue addAll: next resources]. ^allResources ] selector [ ^testSelector ] should: aBlock [ self assert: aBlock value ] should: aBlock description: aString [ self assert: aBlock value description: aString ] should: aBlock raise: anExceptionalEvent [ ^self assert: (self executeShould: aBlock inScopeOf: anExceptionalEvent) ] should: aBlock raise: anExceptionalEvent description: aString [ ^self assert: (self executeShould: aBlock inScopeOf: anExceptionalEvent) description: aString ] shouldnt: aBlock [ self deny: aBlock value ] shouldnt: aBlock description: aString [ self deny: aBlock value description: aString ] shouldnt: aBlock raise: anExceptionalEvent [ ^self assert: (self executeShould: aBlock inScopeOf: anExceptionalEvent) not ] shouldnt: aBlock raise: anExceptionalEvent description: aString [ ^self assert: (self executeShould: aBlock inScopeOf: anExceptionalEvent) not description: aString ] signalFailure: aString [ TestResult failure sunitSignalWith: aString ] debug [ self resources do: [:res | res isAvailable ifFalse: [^res signalInitializationError]]. [(self class selector: testSelector) logPolicy: TestLogPolicy null; runCase] sunitEnsure: [self resources do: [:each | each reset]] ] debugAsFailure [ | semaphore | semaphore := Semaphore new. self resources do: [:res | res isAvailable ifFalse: [^res signalInitializationError]]. [semaphore wait. self resources do: [:each | each reset]] fork. (self class selector: testSelector) runCaseAsFailure: semaphore ] failureLog [ ^SUnitNameResolver defaultLogDevice ] isLogging [ "By default, we're not logging failures. If you override this in a subclass, make sure that you override #failureLog" ^true ] openDebuggerOnFailingTestMethod [ "SUnit has halted one step in front of the failing test method. Step over the 'self halt' and send into 'self perform: testSelector' to see the failure from the beginning" self halt; performTest ] run [ | result | result := TestResult new. self run: result. ^result ] run: aResult [ aResult runCase: self ] runCase [ [self setUp. self performTest] sunitEnsure: [self tearDown] ] runCaseAsFailure: aSemaphore [ [self setUp. self openDebuggerOnFailingTestMethod] sunitEnsure: [self tearDown. aSemaphore signal] ] setUp [ ] tearDown [ ] expectedFailures [ ^Array new ] shouldPass [ "Unless the selector is in the list we get from #expectedFailures, we expect it to pass" ^(self expectedFailures includes: testSelector) not ] executeShould: aBlock inScopeOf: anExceptionalEvent [ ^ [aBlock value. false] sunitOn: anExceptionalEvent do: [:ex | ex sunitExitWith: true] ] performTest [ self perform: testSelector sunitAsSymbol ] setTestSelector: aSymbol [ testSelector := aSymbol ] addDependentToHierachy: anObject [ "an empty method. for Composite compability with TestSuite" ] removeDependentFromHierachy: anObject [ "an empty method. for Composite compability with TestSuite" ] printOn: aStream [ aStream nextPutAll: self class printString; nextPutAll: '>>#'; nextPutAll: testSelector printString. ] ] smalltalk-3.2.5/packages/sunit/SUnitTests.st0000644000175000017500000002764712123404352016017 00000000000000TestCase subclass: ResumableTestFailureTestCase [ errorTest [ 1 zork ] failureLog [ ^SUnitNameResolver defaultLogDevice ] failureTest [ self assert: false description: 'You should see me' resumable: true; assert: false description: 'You should see me too' resumable: true; assert: false description: 'You should see me last' resumable: false; assert: false description: 'You should not see me' resumable: true ] isLogging [ ^false ] okTest [ self assert: true ] regularTestFailureTest [ self assert: false description: 'You should see me' ] resumableTestFailureTest [ self assert: false description: 'You should see me' resumable: true; assert: false description: 'You should see me too' resumable: true; assert: false description: 'You should see me last' resumable: false; assert: false description: 'You should not see me' resumable: true ] testResumable [ | result suite | suite := TestSuite new. suite addTest: (self class selector: #errorTest). suite addTest: (self class selector: #regularTestFailureTest). suite addTest: (self class selector: #resumableTestFailureTest). suite addTest: (self class selector: #okTest). result := suite run. self assert: result failures size = 2; assert: result errors size = 1 ] ] TestCase subclass: SUnitTest [ SUnitTest class >> shouldInheritSelectors [ "answer true to inherit selectors from superclasses" ^false ] testAssert [ self assert: true. self deny: false ] testDefects [ | result suite error failure | suite := TestSuite new. suite addTest: (error := SUnitClientTest selector: #error). suite addTest: (failure := SUnitClientTest selector: #fail). result := suite run. self assert: (result defects includes: error). self assert: (result defects includes: failure). self assertForTestResult: result runCount: 2 passed: 0 failed: 1 errors: 1 ] testDialectLocalizedException [ self should: [TestResult signalFailureWith: 'Foo'] raise: TestResult failure. self should: [TestResult signalErrorWith: 'Foo'] raise: TestResult error ] testDoubleError [ | case result | case := SUnitClientTest selector: #doubleError. result := case run. self assertForTestResult: result runCount: 1 passed: 0 failed: 0 errors: 1 ] testError [ | case result | case := SUnitClientTest selector: #error. result := case run. self assertForTestResult: result runCount: 1 passed: 0 failed: 0 errors: 1. case := SUnitClientTest selector: #errorShouldntRaise. result := case run. self assertForTestResult: result runCount: 1 passed: 0 failed: 0 errors: 1 ] testException [ self should: [self error: 'foo'] raise: TestResult error ] testFail [ | case result | case := SUnitClientTest selector: #fail. result := case run. self assertForTestResult: result runCount: 1 passed: 0 failed: 1 errors: 0 ] testIsNotRerunOnDebug [ | case | case := SUnitClientTest selector: #testRanOnlyOnce. case run. case debug ] testRan [ | case | case := SUnitClientTest selector: #setRun. self assert: case hasSetup ~= true. case run. self assert: case hasSetup == true. self assert: case hasRun == true ] testResult [ | case result | case := SUnitClientTest selector: #noop. result := case run. self assertForTestResult: result runCount: 1 passed: 1 failed: 0 errors: 0 ] testResumable [ | result suite | (suite := TestSuite new) addTest: (SUnitClientTest selector: #errorTest). suite addTest: (SUnitClientTest selector: #regularTestFailureTest). suite addTest: (SUnitClientTest selector: #resumableTestFailureTest). suite addTest: (SUnitClientTest selector: #okTest). result := suite run. self assert: result failures size = 2; assert: result errors size = 1 ] testRunning [ (SUnitDelay forSeconds: 1) wait ] testShould [ self should: [true]. self shouldnt: [false] ] testSuite [ | suite result | suite := TestSuite new. suite addTest: (SUnitClientTest selector: #noop). suite addTest: (SUnitClientTest selector: #fail). suite addTest: (SUnitClientTest selector: #error). result := suite run. self assertForTestResult: result runCount: 3 passed: 1 failed: 1 errors: 1 ] testExpectedFailures [ | result suite expected failed error | suite := TestSuite new. suite addTest: (expected := SUnitClientTest selector: #generateExpectedFailure). suite addTest: (failed := SUnitClientTest selector: #generateUnexpectedSuccess). result := suite run. self assert: (result expectedDefects includes: expected). self assert: (result unexpectedPasses includes: failed). self assertForTestResult: result runCount: 2 passed: 1 failed: 1 errors: 0 ] assertForTestResult: aResult runCount: aRunCount passed: aPassedCount failed: aFailureCount errors: anErrorCount [ self assert: aResult runCount = aRunCount; assert: aResult passedCount = aPassedCount; assert: aResult failureCount = aFailureCount; assert: aResult errorCount = anErrorCount ] testPrintString [ "Make sure that a new test can be printed" self shouldnt: [TestCase new printString] raise: Exception; assert: TestCase new printString = 'TestCase>>#nil'. ] isLogging [ ^true ] ] TestResource subclass: SimpleTestResource [ | runningState hasRun hasSetup hasRanOnce | hasRun [ ^hasRun ] hasSetup [ ^hasSetup ] isAvailable [ ^self runningState == self startedStateSymbol ] runningState [ ^runningState ] runningState: aSymbol [ runningState := aSymbol ] setRun [ hasRun := true ] setUp [ self runningState: self startedStateSymbol. hasSetup := true ] startedStateSymbol [ ^#started ] stoppedStateSymbol [ ^#stopped ] tearDown [ self runningState: self stoppedStateSymbol ] ] TestCase subclass: SUnitClientTest [ | hasRun hasSetup | doubleError [ [3 zork] sunitEnsure: [10 zork] ] error [ 3 zork ] errorShouldntRaise [ self shouldnt: [self someMessageThatIsntUnderstood] raise: SUnitNameResolver notificationObject ] errorTest [ 1 zork. ^self ] fail [ self assert: false ] isLogging [ ^false ] noop [ ] okTest [ self assert: true. ^self ] regularTestFailureTest [ self assert: false description: 'You should see me'. ^self ] resumableTestFailureTest [ self assert: false description: 'You should see me' resumable: true; assert: false description: 'You should see me too' resumable: true; assert: false description: 'You should see me last' resumable: false; assert: false description: 'You should not see me' resumable: true. ^self ] setRun [ hasRun := true ] testRanOnlyOnce [ self assert: hasRun ~= true. hasRun := true ] hasRun [ ^hasRun ] hasSetup [ ^hasSetup ] setUp [ hasSetup := true ] expectedFailures [ ^#(#generateExpectedFailure #generateUnexpectedSuccess) ] generateExpectedFailure [ self assert: false ] generateUnexpectedSuccess [ self assert: true ] ] TestCase subclass: ExampleSetTest [ | full empty | testAdd [ empty add: 5. self assert: (empty includes: 5) ] testGrow [ empty addAll: (1 to: 100). self assert: empty size = 100 ] testIllegal [ self should: [empty at: 5] raise: TestResult error. self should: [empty at: 5 put: #abc] raise: TestResult error ] testIncludes [ self assert: (full includes: 5). self assert: (full includes: #abc) ] testOccurrences [ self assert: (empty occurrencesOf: 0) = 0. self assert: (full occurrencesOf: 5) = 1. full add: 5. self assert: (full occurrencesOf: 5) = 1 ] testRemove [ full remove: 5. self assert: (full includes: #abc). self deny: (full includes: 5) ] setUp [ empty := Set new. full := Set with: 5 with: #abc ] ] TestCase subclass: SimpleTestResourceTestCase [ | resource | SimpleTestResourceTestCase class >> resources [ ^(Set new) add: SimpleTestResource; yourself ] dummy [ self assert: true ] error [ 'foo' odd ] fail [ self assert: false ] setRun [ resource setRun ] setUp [ resource := SimpleTestResource current ] testRan [ | case | case := self class selector: #setRun. case run. self assert: resource hasSetup. self assert: resource hasRun ] testResourceInitRelease [ | result suite error failure | suite := TestSuite new. suite addTest: (error := self class selector: #error). suite addTest: (failure := self class selector: #fail). suite addTest: (self class selector: #dummy). result := suite run. self assert: resource hasSetup ] testResourcesCollection [ | collection | collection := self resources. self assert: collection size = 1 ] ] smalltalk-3.2.5/packages/sunit/SUnitScriptTests.st0000644000175000017500000001126612123404352017172 00000000000000"====================================================================== | | SUnit testing framework scripting system | | This file is in the public domain. | ======================================================================" SUnitTest subclass: TestSuitesHierarchyScriptTest [ testRanOnlyOnce [ self assert: true ] ] TestSuitesHierarchyScriptTest subclass: TestSuitesCompoundScriptTest [ testRanOnlyOnce [ self assert: true ] ] TestCase subclass: TestSuitesScriptTest [ suiteFor: aScript [ ^(TestSuitesScripter script: aScript) value ] compile: aScript [ ^(TestSuitesScripter script: aScript) value; yourself ] testCompoundScript [ | allTestCaseClasses superCase subCase | allTestCaseClasses := (self suiteFor: 'TestSuitesHierarchyScriptTest TestSuitesCompoundScriptTest') tests. self assert: allTestCaseClasses size = 2. superCase := (allTestCaseClasses at: 1) tests first. self assert: superCase class sunitName sunitAsSymbol = #TestSuitesHierarchyScriptTest. subCase := (allTestCaseClasses at: 2) tests first. self assert: subCase class sunitName sunitAsSymbol = #TestSuitesCompoundScriptTest ] testEmbeddedNameCommentScript [ | suite | suite := self suiteFor: ' "This comment contains the name of a SUnitTest Case" TestSuitesScriptTest'. self assert: suite tests size = 1 ] testEmptyCommentScript [ | suite | suite := self suiteFor: ' " " TestSuitesScriptTest'. self assert: suite tests size = 1 ] testEmptyHierarchyScript [ | suite | suite := self suiteFor: '*'. self assert: suite tests isEmpty ] testEmptyScript [ | suite | suite := self suiteFor: ''. self assert: suite tests isEmpty ] testHierarchyScript [ | allTestCaseClasses superCase subCase suite | suite := self suiteFor: 'TestSuitesHierarchyScriptTest*'. allTestCaseClasses := suite tests. self assert: allTestCaseClasses size = 1. superCase := (allTestCaseClasses first tests at: 1) tests first. self assert: superCase class sunitName sunitAsSymbol = #TestSuitesHierarchyScriptTest. subCase := (allTestCaseClasses first tests at: 2) tests first. self assert: subCase class sunitName sunitAsSymbol = #TestSuitesCompoundScriptTest ] testOpenCommentScript [ | suite | suite := self suiteFor: ' "SUnitTest'. self assert: suite tests isEmpty ] testSimpleScript [ | allTestCaseClasses case suite | suite := self suiteFor: 'TestSuitesHierarchyScriptTest'. allTestCaseClasses := suite tests. self assert: allTestCaseClasses size = 1. case := (allTestCaseClasses at: 1) tests at: 1. self assert: case class sunitName sunitAsSymbol = #TestSuitesHierarchyScriptTest ] testSingleWordCommentScript [ | suite | suite := self suiteFor: ' "SUnitTest" TestSuitesScriptTest'. self assert: suite tests size = 1 ] testTwoCommentsScript [ | suite | suite := self suiteFor: ' " SUnitTest " " SUnitTest " TestSuitesScriptTest'. self assert: suite tests size = 1. suite := self suiteFor: ' " SUnitTest "" SUnitTest " TestSuitesScriptTest'. self assert: suite tests size = 1 ] testStringVariableScript [ | scripter | scripter := self compile: 'var1=''value'' var2=''''''quoted "not SUnitTest and not a comment" '''''' TestSuitesScriptTest'. self assert: (scripter variableAt: 'var1' ifAbsent: [42]) = 'value'. self assert: (scripter variableAt: 'var2' ifAbsent: [42]) = '''quoted "not SUnitTest and not a comment" '''. self assert: (scripter variableAt: 'var3' ifAbsent: [42]) = 42. self assert: scripter value tests size = 1 ] testVariableScript [ | scripter | scripter := self compile: ' var1=value TestSuitesScriptTest'. self assert: (scripter variableAt: 'var1' ifAbsent: [42]) = 'value'. self assert: (scripter variableAt: 'var2' ifAbsent: [42]) = 42. self assert: scripter value tests size = 1 ] testEmptyVariableScript [ | scripter | scripter := self compile: ' var1= TestSuitesScriptTest'. self assert: (scripter variableAt: 'var1' ifAbsent: [42]) = ''. self assert: (scripter variableAt: 'var2' ifAbsent: [42]) = 42. self assert: scripter value tests size = 1 ] ] smalltalk-3.2.5/packages/sunit/SUnitPreload.st0000644000175000017500000000503312123404352016264 00000000000000Exception subclass: TestFailure [ ] Delay subclass: SUnitDelay [ ] TestFailure subclass: ResumableTestFailure [ sunitExitWith: aValue [ ^self resume: aValue ] ] Object subclass: SUnitNameResolver [ SUnitNameResolver class >> classNamed: aSymbol [ ^(aSymbol substrings: $.) inject: Smalltalk into: [:space :key | space at: key asSymbol ifAbsent: [^nil]] ] SUnitNameResolver class >> defaultLogDevice [ ^Transcript ] SUnitNameResolver class >> errorObject [ ^Error ] SUnitNameResolver class >> mnuExceptionObject [ ^MessageNotUnderstood ] SUnitNameResolver class >> notificationObject [ ^Notification ] ] Object extend [ sunitAddDependent: anObject [ self addDependent: anObject ] sunitChanged: aspect [ self changed: aspect ] sunitRemoveDependent: anObject [ self removeDependent: anObject ] ] BlockClosure extend [ sunitEnsure: aBlock [ ^self ensure: aBlock ] sunitOn: aSignal do: anExceptionBlock [ ^self on: aSignal do: anExceptionBlock ] ] Behavior extend [ sunitAllSelectors [ ^self allSelectors asSortedCollection asOrderedCollection ] sunitSelectors [ ^self selectors asSortedCollection asOrderedCollection ] ] String extend [ sunitAsSymbol [ ^self asSymbol ] sunitMatch: aString [ ^self match: aString ] sunitSubStrings [ ^self substrings ] ] Exception class extend [ sunitSignalWith: aString [ ^self signal: aString ] ] Exception extend [ sunitExitWith: aValue [ ^self return: aValue ] ] String extend [ sunitAsClass [ ^SUnitNameResolver classNamed: self ] ] Class extend [ sunitName [ ^self name ] ] smalltalk-3.2.5/packages/sunit/stamp-classes0000644000175000017500000000000012123404352016032 00000000000000smalltalk-3.2.5/packages/sunit/package.xml0000644000175000017500000000046112123404352015460 00000000000000 SUnit SUnitPreload.st SUnit.st SUnitScript.st SUnitTest TestSuitesScriptTest SUnitTests.st SUnitScriptTests.st smalltalk-3.2.5/packages/ncurses/0000755000175000017500000000000012130456015013743 500000000000000smalltalk-3.2.5/packages/ncurses/Makefile.frag0000644000175000017500000000030712123404352016240 00000000000000NCurses_FILES = \ packages/ncurses/ncurses.st packages/ncurses/ChangeLog $(NCurses_FILES): $(srcdir)/packages/ncurses/stamp-classes: $(NCurses_FILES) touch $(srcdir)/packages/ncurses/stamp-classes smalltalk-3.2.5/packages/ncurses/ncurses.st0000644000175000017500000031620412123404352015722 00000000000000"====================================================================== | | ncurses declarations | | ======================================================================" "====================================================================== | | Copyright 2006 Free Software Foundation, Inc. | Written by Brad Watson | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" "====================================================================== | | Notes: implemented without callbacks. See the ncurses man pages | for a description of the wrapped ncurses library functions. | ======================================================================" CStruct subclass: NCWindow [ StdScreen := nil. NCWindow class >> colorBlack [ ^0 ] NCWindow class >> colorBlue [ ^4 ] NCWindow class >> colorCyan [ ^6 ] NCWindow class >> colorGreen [ ^2 ] NCWindow class >> colorMagenta [ ^5 ] NCWindow class >> colorRed [ ^1 ] NCWindow class >> colorWhite [ ^7 ] NCWindow class >> colorYellow [ ^3 ] NCWindow class >> endLine [ ^2 ] NCWindow class >> err [ ^-1 ] NCWindow class >> false [ ^0 ] NCWindow class >> fullWin [ ^4 ] NCWindow class >> hasMoved [ ^1620 ] NCWindow class >> isPad [ ^1610 ] NCWindow class >> keyA1 [ ^534 ] NCWindow class >> keyA3 [ ^535 ] NCWindow class >> keyBackspace [ ^407 ] NCWindow class >> keyBreak [ ^401 ] NCWindow class >> keyB2 [ ^536 ] NCWindow class >> keyBeg [ ^542 ] NCWindow class >> keyBtab [ ^541 ] NCWindow class >> keyC1 [ ^537 ] NCWindow class >> keyC3 [ ^540 ] NCWindow class >> keyCancel [ ^543 ] NCWindow class >> keyCatab [ ^526 ] NCWindow class >> keyClose [ ^544 ] NCWindow class >> keyCommand [ ^545 ] NCWindow class >> keyCopy [ ^546 ] NCWindow class >> keyCreate [ ^547 ] NCWindow class >> keyClear [ ^515 ] NCWindow class >> keyCodeYes [ ^400 ] NCWindow class >> keyCtab [ ^525 ] NCWindow class >> keyDl [ ^510 ] NCWindow class >> keyDc [ ^512 ] NCWindow class >> keyDown [ ^402 ] NCWindow class >> keyEic [ ^514 ] NCWindow class >> keyEnd [ ^550 ] NCWindow class >> keyEnter [ ^527 ] NCWindow class >> keyEol [ ^517 ] NCWindow class >> keyEos [ ^516 ] NCWindow class >> keyEvent [ ^633 ] NCWindow class >> keyExit [ ^551 ] NCWindow class >> keyFind [ ^552 ] NCWindow class >> keyHelp [ ^553 ] NCWindow class >> keyHome [ ^406 ] NCWindow class >> keyIl [ ^511 ] NCWindow class >> keyIc [ ^513 ] NCWindow class >> keyLeft [ ^404 ] NCWindow class >> keyLl [ ^533 ] NCWindow class >> keyMax [ ^777 ] NCWindow class >> keyMark [ ^554 ] NCWindow class >> keyMessage [ ^555 ] NCWindow class >> keyMin [ ^401 ] NCWindow class >> keyMouse [ ^631 ] NCWindow class >> keyMove [ ^556 ] NCWindow class >> keyNext [ ^557 ] NCWindow class >> keyNpage [ ^522 ] NCWindow class >> keyOpen [ ^560 ] NCWindow class >> keyOptions [ ^561 ] NCWindow class >> keyPrevious [ ^562 ] NCWindow class >> keyPrint [ ^532 ] NCWindow class >> keyPpage [ ^523 ] NCWindow class >> keyRedo [ ^563 ] NCWindow class >> keyReference [ ^564 ] NCWindow class >> keyRefresh [ ^565 ] NCWindow class >> keyReplace [ ^566 ] NCWindow class >> keyReset [ ^531 ] NCWindow class >> keyResize [ ^632 ] NCWindow class >> keyRestart [ ^567 ] NCWindow class >> keyResume [ ^570 ] NCWindow class >> keyRight [ ^405 ] NCWindow class >> keySave [ ^571 ] NCWindow class >> keySbeg [ ^572 ] NCWindow class >> keyScancel [ ^573 ] NCWindow class >> keyScommand [ ^574 ] NCWindow class >> keyScopy [ ^575 ] NCWindow class >> keyScreate [ ^576 ] NCWindow class >> keySdc [ ^577 ] NCWindow class >> keySdel [ ^600 ] NCWindow class >> keySelect [ ^601 ] NCWindow class >> keySend [ ^602 ] NCWindow class >> keySeol [ ^603 ] NCWindow class >> keySexit [ ^604 ] NCWindow class >> keySf [ ^520 ] NCWindow class >> keySfind [ ^605 ] NCWindow class >> keyShelp [ ^606 ] NCWindow class >> keyShome [ ^607 ] NCWindow class >> keySic [ ^610 ] NCWindow class >> keySleft [ ^611 ] NCWindow class >> keySmessage [ ^612 ] NCWindow class >> keySmove [ ^613 ] NCWindow class >> keySnext [ ^614 ] NCWindow class >> keySoptions [ ^615 ] NCWindow class >> keySprevious [ ^616 ] NCWindow class >> keySprint [ ^617 ] NCWindow class >> keySr [ ^521 ] NCWindow class >> keySredo [ ^620 ] NCWindow class >> keySreplace [ ^621 ] NCWindow class >> keySReset [ ^530 ] NCWindow class >> keySright [ ^622 ] NCWindow class >> keySrsume [ ^623 ] NCWindow class >> keySsave [ ^624 ] NCWindow class >> keySsuspend [ ^625 ] NCWindow class >> keyStab [ ^524 ] NCWindow class >> keySundo [ ^626 ] NCWindow class >> keySuspend [ ^627 ] NCWindow class >> keyUndo [ ^630 ] NCWindow class >> keyUp [ ^403 ] NCWindow class >> noChange [ ^-1 ] NCWindow class >> newIndex [ ^-1 ] NCWindow class >> ok [ ^0 ] NCWindow class >> subWin [ ^0 ] NCWindow class >> scrollWin [ ^8 ] NCWindow class >> true [ ^1 ] NCWindow class >> wrapped [ ^64 ] NCWindow class >> addch: aChar [ "I put the character given to me into my window at the current position, and then advance the current position. See the man(3) addch entry for a description of my c function call." "int addch (const chtype);" ] NCWindow class >> addchnstr: aString n: anInt [ "I put at most n charaters of the character/attributes string given to me into my window starting at the current position, and then advance the current position. See the man(3) addchnstr entry for a description of my c function call." "int addchnstr (const chtype *, int);" ] NCWindow class >> addchstr: aString [ "I put the character/attributes in the string given to me into my window starting at the current position, and then advance the current position. See the man(3) addchstr entry for a description of my c function call." "int addchstr (const chtype *);" ] NCWindow class >> addnstr: aString n: anInt [ "I put at most n characters in the string given to me into my window starting at the current position, and then advance the current position. See the man(3) addnstr entry for a description of my c function call." "int addnstr (const char *, int);" ] NCWindow class >> addstr: aString [ "I put the characters in the string given to me into my window starting at the current position, and then advance the current position. See the man(3) addnstr entry for a description of my c function call." "int addstr (const char *);" ] NCWindow class >> assumeDefaultColors: anInt1 bg: anInt2 [ "I change my windows default background and forground colors to the values given to me. See the man(3) assume_default_colors entry for a description of my c function call." "int assume_default_colors (int, int);" ] NCWindow class >> attrGet: cObject1 pair: cObject2 opts: cObject3 [ "I retrieve attribute values for my window from a file. See the man(3) attr_get entry for a description of my c function call." "int attr_get (attr_t *, short *, void *);" ] NCWindow class >> attrOff: anInt opts: cObject [ "I turn off the named attribute given to me in my window. See the man(3) attr_off for a description of my c function call." "int attr_off (attr_t, void *);" ] NCWindow class >> attrOn: anInt opts: cObject [ "I turn on the named attribute given to me in my window. See the man(3) attr_on for a description of my c function call." "int attr_on (attr_t, void *);" ] NCWindow class >> attrSet: anInt1 pair: anInt2 opts: cObject [ "I set the attribute color-pair in my window to the value given to me. See the man(3) attr_set entry for a description of my c function call." "int attr_set (attr_t, short, void *);" ] NCWindow class >> attroff: anInt [ "I turn off the named attribute given to me in my window. See the man(3) attroff for a description of my c function call." "int attroff (NCURSES_ATTR_T);" ] NCWindow class >> attron: anInt [ "I turn on the named attribute given to me in my window. See the man(3) attron for a description of my c function call." "int attron (NCURSES_ATTR_T);" ] NCWindow class >> attrset: anInt [ "I set the attribute color-pair in my window to the value given to me. See the man(3) attrset entry for a description of my c function call." "int attrset (NCURSES_ATTR_T);" ] NCWindow class >> baudrate [ "I return the output speed of the terminal. See the man(3) baudrate entry for a description of my c function call." "int baudrate (void);" ] NCWindow class >> beep [ "I ring the terminal alarm. See the man(3) beep entry for a description of my c function call." "int beep (void);" ] NCWindow class >> bkgd: aChar [ "I set the background property of my window and apply it to every character in the window to the value given to me. See the man(3) bkgd entry for a description of my c function call." "int bkgd (chtype);" ] NCWindow class >> bkgdset: aChar [ "I set the background property of the characters in my window to the value given to me. See the man(3) bkgdset entry for a description of my c function call." "void bkgdset (chtype);" ] NCWindow class >> border: aChar1 rs: aChar2 ts: aChar3 bs: aChar4 tl: aChar5 tr: aChar6 bl: aChar7 br: aChar8 [ "I draw a border around the edges of my window using the character attributes given to me. See the man(3) border entry for a description of my c function call." "int border (chtype, chtype, chtype, chtype, chtype, chtype, chtype, chtype);" ] NCWindow class >> canChangeColor [ "I return true if the terminal has color capabilities that can be changed. See the man(3) can_change_color entry for a description of my c function call." "bool can_change_color (void);" ] NCWindow class >> cbreak [ "I disable line buffering and erase/kill character processing. See the man(3) cbreak entry for a description of my c function call." "int cbreak (void);" ] NCWindow class >> chgat: anInt1 attr: anInt2 color: anInt3 opts: cObject [ "I change up to n character attributes starting at the current position. See the man(3) chgat entry for a description for my c function calls." "int chgat (int, attr_t, short, const void *);" ] NCWindow class >> clear [ "I put a blank in every character position in my window and set up the window to be re-painted the next time that it is refreshed. See the man(3) clear entry for a description of my c function calls." "int clear (void);" ] NCWindow class >> clrtobot [ "I erase the current screen from the right of the current cursor position all the way to the bottom right of the screen. See the man(3) clrtobot entry for a description of my c function call." "int clrtobot (void);" ] NCWindow class >> clrtoeol [ "I erase the current line in my window to the right of the current cursor location. See the man(3) clrtoeol entry for a description of my c function calls." "int clrtoeol (void);" ] NCWindow class >> colorContent: anInt red: cObject1 green: cObject2 blue: cObject3 [ "I extract the amount of RGB components in the color attribute given to me. See the man(3) color_content entry for a description of my c function call." "int color_content (short, short*, short*, short*);" ] NCWindow class >> colorPair: anInt [ "I return the number of color pair attributes that my terminal can support. See the man(3) COLOR_PAIR entry for a description of my c function call." "int COLOR_PAIR (int)" ] NCWindow class >> colorSet: anInt opts: cObject [ "I set the current color of my window to the color pair attribute given to me. See the man(3) color_set entry for a description of my c function call." "int color_set (short, void*);" ] NCWindow class >> cursesVersion [ "I return the version number and patch level of my ncurses library. See the man(3) curses_version entry for a description of my c function call." "(const char *) curses_version (void);" ] NCWindow class >> cursSet: anInt [ "I set the cursor visibility in my window to the visibility given to me and then return the previous cursor state. See the man(3) curs_set entry for a description of my c function call." "int curs_set (int);" ] NCWindow class >> defineKey: aString keycode: anInt [ "I define a keycode with its' corresponding control string. See the man(3) define_key entry for a description of my c function call." "int define_key (const char *, int);" ] NCWindow class >> defProgMode [ "I save the current terminals program state. See the man(3) def_prog_mode entry for a description of my c function call." "int def_prog_mode (void);" ] NCWindow class >> defShellMode [ "I save the current terminals shell state. See the man(3) def_shell_mode entry for a description of my c function call." "int def_shell_mode (void);" ] NCWindow class >> delayOutput: anInt [ "I put padding characters into the output while I delay for the number of milli-seconds given to me. See the man(3) delay_output for a description of my c function call." "int delay_output (int);" ] NCWindow class >> delch [ "I delete the character underneath the current cursor position and then shift the characters to the right of the cursor one position to the left. See the man(3) delch entry for a description of my c function call." "int delch (void);" ] NCWindow class >> deleteln [ "I delete the line under the current cursor position, move all of the lines below the cursor up one line and clear the last line. See the man(3) deleteln entry for a description of my c function call." "int deleteln (void);" ] NCWindow class >> doupdate [ "I transmit the difference between the virtual screen and the physcial screen to the physical screen. See the man(3) doupdate entry for a description of my c function call." "int doupdate (void);" ] NCWindow class >> echo [ "I turn on the echoing of characters by getch to the screen as they are typed. See the man(3) echo entry for a description of my c function call." "int echo (void);" ] NCWindow class >> echochar: aChar [ "I put the character given to me at the current cursor position, advance the cursor, and then refresh the screen. See the man(3) echochar entry for a description of my c function call." "int echochar (const chtype);" ] NCWindow class >> endwin [ "I restore the tty mode, position the cursor to the lower left-hand corner of the screen and reset the terminal into the proper non-visual mode. See the man(3) endwin entry for a description of my c function call." "int endwin (void);" ] NCWindow class >> erase [ "I put blanks into every position in the screen. See the man(3) erase entry for a description of my c function call." "int erase (void);" ] NCWindow class >> erasechar [ "I return the current character. See the man(3) erasechar for a description of my c function." "char erasechar (void);" ] NCWindow class >> filter [ "I restrict terminal input and output to a single line. See the man(3) filter entry for a description of my c function." "void filter (void);" ] NCWindow class >> flash [ "I flash the terminal. See the man(3) entry for a description of my c function call." "int flash (void);" ] NCWindow class >> flushinp [ "I discard any unprocessed keystrokes. See the man(3) entry for a description of my c function call." "int flushinp (void);" ] NCWindow class >> getch [ "I read a keystroke from my window. See the man(3) getch entry for a description of my c function call." "int getch (void);" ] NCWindow class >> getnstr: aString n: anInt [ "I read at most n keystrokes from the stdscr window until a return or linefeed key is pressed. See the man(3) getnstr entry for a description of my c function call." "int getnstr (char *, int);" ] NCWindow class >> getstr: aString [ "I read keystrokes from the stdscr window until a return or linefeed key is pressed. See the man(3) getstr entry for a description of my c function call." "int getstr (char *);" ] NCWindow class >> halfdelay: anInt [ "I return either a character or an error if a key is not pressed within the number of 10ths of seconds given to me. See the man(3) halfdelay entry for a description of my c function call." "int halfdelay (int);" ] NCWindow class >> hasColors [ "I return true if my terminal supports colors. See the man(3) has_colors entry for a description of my c function call." "bool has_colors (void);" ] NCWindow class >> hasIc [ "I return true if my terminal has insert/delete character capabilities. See the man(3) has_ic entry for a description of my c function call." "bool has_ic (void);" ] NCWindow class >> hasIl [ "I return true if my terminal has insert/delete line capabilities. See the man(3) has_ic entry for a description of my c function call." "bool has_il (void);" ] NCWindow class >> hline: aChar n: anInt [ "I draw a horizontal line in the terminal using the character given to me of at most n characters. See the man(3) hline entry for a description of my c function call." "int hline (chtype, int);" ] NCWindow class >> inch [ "I return the character/attribute at the current cursor position in the terminal. See the man(3) inch entry for a description of my c function call." "chtype inch (void);" ] NCWindow class >> inchnstr: aString n: anInt [ "I return the character/attribute string of at most n characters at the current cursor position in the terminal. See the man(3) inchnstr entry for a description of my c function call." "int inchnstr (chtype *, int);" ] NCWindow class >> inchstr: aString [ "I return the character/attribute string of characters at the current cursor position in the terminal. See the man(3) inchstr entry for a description of my c function call." "int inchstr (chtype *);" ] NCWindow class >> initColor: anInt1 red: anInt2 green: anInt3 blue: anInt4 [ "I change the definition of a color. See the man(3) init_color entry for a description of my c function call." "int init_color (short, short, short, short);" ] NCWindow class >> initPair: anInt1 f: anInt2 b: anInt3 [ "I initialize a color pair. See the man(3) init_pair for a description of my c function call." "int init_pair (short, short, short);" ] NCWindow class >> initscr [ "WINDOW *initscr (void);" ^StdScreen := self primInitScr ] NCWindow class >> innstr: aString n: anInt [ "I extract up to n characters into a string starting at the current curor position in the terminal. See the man(3) innstr entry for a description of my c function call." "int innstr (char *, int);" ] NCWindow class >> insch: aChar [ "I put the character given to me in the terminal at the current cursor position and shift the remaining characters in the line one position to the right. See the man(3) insch entry for a description of my c function call." "int insch (chtype);" ] NCWindow class >> insdelln: anInt [ "I insert the number of blank lines given to me above the current line and delete the same number of lines from the bottom. See the man(3) insdelln entry for a description of my c function call." "int insdelln (int);" ] NCWindow class >> insertln [ "I insert a blank line in the terminal above the current line and delete the bottom line. See the man(3) insertln entry for a description of my c function call." "int insertln (void);" ] NCWindow class >> insnstr: aString n: anInt [ "I insert at most n characters in the string given to me into the terminal starting at the one character before current cursor position. The remaining characters in the line are shifted to the right. See the man(3) insnstr entry for a description of my c function call." "int insnstr (const char *, int);" ] NCWindow class >> insstr: aString [ "I insert the characters in the string given to me into the terminal starting at the one character before current cursor position. The remaining characters in the line are shifted to the right. See the man(3) insstr entry for a description of my c function call." "int insstr (const char *);" ] NCWindow class >> instr: aString [ "I return the string of characters in the terminal starting at the current cursor position. See the man(3) instr entry for a description of my c function call." "int instr (char *);" ] NCWindow class >> isendwin [ "I return true if a refresh message has not been sent since an endwin message was sent. Otherwise, I return false. See the man(3) isendwin entry for a description of my c function call." "bool isendwin (void);" ] NCWindow class >> isTermResized: anInt1 columns: anInt2 [ "I return true if the resizeTerm:columns: message was sent, it would change the terminal structures. Otherwise, I return false. See the man(3) is_term_resized entry for a description of my c function call." "bool is_term_resized (int, int);" ] NCWindow class >> keybound: int1 count: int2 [ "I return the string defined in terminfo for the number of entries given to me starting with the keycode given to me. See the man(3) keybound entry for a description of my c function call." "char *keybound (int, int);" ] NCWindow class >> keyDefined: aString [ "I return the keycode for the string given to me if it exists. I return 0 if there is no match, and I return -1 if the string is a substring of more than one string in keycode/string associations. See the man(3) key_defined entry for a description of my c function call." "int key_defined (const char *);" ] NCWindow class >> keyname: anInt [ "I return a string corresponding to the key given to me. See the man(3) keyname entry for a description of my c function call." "const char *keyname (int);" ] NCWindow class >> keyok: anInt enabled: aBool [ "I enable or disable the keycode given to me. See the man(3) keyok entry for a description of my c function call." "int keyok (int, bool);" ] NCWindow class >> killchar [ "I return the line kill character. See the man(3) killchar entry for a description of my c function call." "char killchar (void);" ] NCWindow class >> longname [ "I return a string with a verbose description of the current terminal. See the man(3) longname entry for a description of my c function call." "char *longname (void);" ] NCWindow class >> move: anInt1 x: anInt2 [ "I move the cursor in the terminal to the position given to me. See the man(3) move entry for a description of my c function call." "int move (int, int);" ] NCWindow class >> mvaddch: anInt1 x: anInt2 ch: aChar [ "I add a character to the terminal at the current cursor location and then advance the cursor to the coordinates given to me. See the man(3) mvaddch entry for a description of my c function call." "int mvaddch (int, int, const chtype);" ] NCWindow class >> mvaddchstr: anInt1 x: anInt2 str: aString [ "I copy the characters and attributes of the string given to me into the terinal starting at the location specified by the coordinates given to me. See the man(3) mvwaddchstr entry for a description of my c function call." "int mvaddchstr (int, int, const chtype *);" ] NCWindow class >> mvaddchnstr: anInt1 x: anInt2 str: aString n: anInt3 [ "I copy up to n characters and attributes of the string given to me into the terinal starting at the location specified by the coordinates given to me. See the man(3) mvwaddchnstr entry for a description of my c function call." "int mvaddchnstr (int, int, const chtype *, int);" ] NCWindow class >> mvaddnstr: anInt1 x: anInt2 str: aString n: anInt3 [ "I copy up to n characters of the string given to me to the terminal starting at the location specified by the coordinates given to me. See the man(3) mvaddnstr entry for a description of my c function call." "int mvaddnstr (int, int, const char *, int);" ] NCWindow class >> mvaddstr: anInt1 x: anInt2 str: aString [ "I copy the string given to me to the terminal starting at the location specified by the coordinates given to me. See the man(3) mvaddnstr entry for a description of my c function call." "int mvaddstr (int, int, const char *);" ] NCWindow class >> mvchgat: anInt1 x: anInt2 n: anInt3 attr: anInt4 color: anInt5 opts: cObject [ "I change the color and attribute of next n characters in the terminal starting at the location specified by the coordinates given to me. See the man(3) mvwchgat entry for a description of my c function call." "int mvchgat (int, int, int, attr_t, short, const void *);" ] NCWindow class >> mvcur: anInt1 oldCol: anInt2 newRow: anInt3 newCol: anInt4 [ "I move the cursor immediately in the terminal from the old row and column to the new row and column given to me. See the man(3) mvcur entry for a description of my c function call." "int mvcur (int, int, int, int);" ] NCWindow class >> mvdelch: anInt1 x: anInt2 [ "I move the cursor to the coordinates given to me in the terminal, delete the character under the cursor, and then shift the remaining characters in the line one position to the left. See the man(3) mvwdelch entry for description of my c function call." "int mvdelch (int, int);" ] NCWindow class >> mvgetch: anInt1 x: anInt2 [ "I position the cursor to the location in the terminal specified by the coordinates given to me, I read a character. See the man(3) mvgetch entry for a description of my c function call." "int mvgetch (int, int);" ] NCWindow class >> mvgetnstr: anInt1 x: anInt2 str: aString n: anInt3 [ "I position the cursor to the location in my window specified by the coordinates given to me, and then I read at most n characters until a carriage return or newline is pressed. See the man(3) mvgetnstr entry for a description of my c function call." "int mvgetnstr (int, int, char *, int);" ] NCWindow class >> mvgetstr: anInt1 x: anInt2 str: aString [ "I position the cursor to the location in the terminal specified by the coordinates given to me, and thenI read characters until a carriage return or a newline is pressed. See man(3) mvgetstr entry for a description of my c function call." "int mvgetstr (int, int, char *);" ] NCWindow class >> mvhline: anInt1 x: anInt2 ch: aChar n: anInt3 [ "I position the cursor to the location in the terminal specified by the coordinates given to me, and then I write a horizontal line of at most n characters comprised of the character given to me. See the man(3) mvhline entry for a description of my c function call." "int mvhline (int, int, chtype, int);" ] NCWindow class >> mvinch: anInt1 x: anInt2 [ "I return the character or attribute at the cursor location specifed by the coordinates given to me. See the man(3) mvinch entry for a description of my c call function." "chtype mvinch (int, int);" ] NCWindow class >> mvinchnstr: anInt1 x: anInt2 str: aString n: anInt3 [ "I return a null terminated array of characters or attributes from the terminal of at most n characters starting at the cursor location specified by the coordinates given to me. See the man(3) mvinchnstr entry for a description of my c function call." "int mvinchnstr (int, int, chtype *, int);" ] NCWindow class >> mvinchstr: anInt1 x: anInt2 str: aString [ "I return a null terminated array of characters or attributes from within the terminal starting at the cursor location given by the coordinates given to me. See the man(3) mvinchstr entry for a description of my c call function." "int mvinchstr (int, int, chtype *);" ] NCWindow class >> mvinnstr: anInt1 x: anInt2 str: aString n: anInt3 [ "I return a string of characters from the termimal stripped of attributes starting at the location given to me as coordinates. See the man(3) mvinnstr entry for a description of my c function call." "int mvinnstr (int, int, char *, int);" ] NCWindow class >> mvinsch: anInt1 x: anInt2 ch: aChar [ "I insert a character in the terminal before the location given to me as coordinates. The remaining characters in the line are shifted one position to the right. See the man(3) mvwinsch entry for a description of my c function call." "int mvinsch (int, int, chtype);" ] NCWindow class >> mvinsnstr: anInt1 x: anInt2 str: aString n: anInt3 [ "I insert a string of at most n characters in the terminal before the location given to me as coordinates. The remaining characters in the line are shifted one position to the right. See the man(3) mvinsnstr entry for a description of my c function call." "int mvinsnstr (int, int, const char *, int);" ] NCWindow class >> mvinsstr: anInt1 x: anInt2 str: aString [ "I insert a string before the location in the terminal given to me as coordinates. The remaining characters in the line are shifted one position to the right. See the man(3) mvinsstr entry for a description of my c function call." "int mvinsstr (int, int, const char *);" ] NCWindow class >> mvinstr: anInt1 x: anInt2 str: aString [ "I return a string of characters from the terminal starting from the location given to me as coordinates. See the man(3) mvinstr for a description of my c function call." "int mvinstr (int, int, char *);" ] NCWindow class >> mvprintw: anInt1 x: anInt2 str: aString [ "I print a formated string in the terminal at the location given to me as coordinates. See the man(3) mvprintw entry for a description of my c function call." "int mvprintw (int, int, const char *, ...)" ] NCWindow class >> mvprintw: anInt1 x: anInt2 str: aString args: anArray [ "I print a formated string and arguments in the terminal at the location given to me as coordinates. See the man(3) mvprintw entry for a description of my c function call." "int mvprintw (int, int, const char *, ...)" ] NCWindow class >> mvscanw: anInt1 x: anInt2 str: aString args: anArray [ "I scan a string from within the terminal at the location given to me as coordinates. See the man(3) mvscanw entry for a description of my c function call." "int mvscanw (int, int, const char *, ...)" ] NCWindow class >> mvvline: anInt1 x: anInt2 ch: aChar n: anInt3 [ "I position the cursor to the location in the terminal specified by the coordinates given to me, and then write a vertical line of at most n characters comprised of the character given to me. See the man(3) mvvline entry for a description of my c function call." "int mvvline (int, int, chtype, int);" ] NCWindow class >> napms: anInt [ "I sleep for the number of milliseconds given to me. See the man(3) napms entry for a description of my c function call." "int napms (int);" ] NCWindow class >> newpad: anInt1 ncols: anInt2 [ "I create a new specialized instance of a window. My size is specified by the number of rows and columns given to me. See the man(3) newpad entry for a description of my c function call." "WINDOW *newpad (int, int);" ] NCWindow class >> newwin: anInt1 cols: anInt2 beginY: anInt3 beginX: anInt4 [ "I create a new window structure at the location given to me as coordinates. My size is specified by the number of rows and columns given to me. See the man(3) newwin entry for a description of my c function call." "WINDOW *newwin (int, int, int, int);" ] NCWindow class >> nl [ "I tell the display device to display newline on input and newline/return on output. See the man(3) nl entry for a description of my c function call." "int nl (void);" ] NCWindow class >> nocbreak [ "I tell the tty driver to enable line buffering and to process erase and kill characters. See the man(3) nocbreak entry for a description of my c function call." "int nocbreak (void);" ] NCWindow class >> noecho [ "I disable getch from echoing characters as they are typed. See the man(3) noecho entry for a description of my c function call." "int noecho (void);" ] NCWindow class >> nonl [ "I tell the display device to no display newline on input or newline/return on output. See the man(3) nonl entry for a description of my c function call." "int nonl (void);" ] NCWindow class >> noqiflush [ "I turn off termio input and output queue interrupt flushing. See the man(3) noqiflush entry for a description of my c function call." "void noqiflush (void);" ] NCWindow class >> noraw [ "I set the terminal to the non-raw mode. See the man(3) noraw entry for a decription of my c function call." "int noraw (void);" ] NCWindow class >> pairContent: anInt f: cObject1 b: cObject2 [ "I map a color-pair number into it's foreground and background color components. See the man(3) pair_content entry for a description of my c function call." "int pair_content (short, short*, short*);" ] NCWindow class >> pairNumber: anInt [ "I return the color pair number associate with the pair attribute given to me. See the man(3) PAIR_NUMBER entry for a description of my c function call." "int PAIR_NUMBER (int);" ] NCWindow class >> primInitScr [ "WINDOW *initscr (void);" ] NCWindow class >> printw: aString [ "I display formatted output. See then man(3) printw entry for a description of my c function call." "int printw (const char *, ...)" ] NCWindow class >> printw: aString args: anArray [ "I display formatted output given a string and arguments. See then man(3) printw entry for a description of my c function call." "int printw (const char *, ...)" ] NCWindow class >> putp: aString [ "I am a lowlevel print routine used to interface with the terminfo database. See the man(3) putp entry for a description of my c function call." "int putp (const char *);" ] NCWindow class >> qiflush [ "I turn on termio input and output queue interrupt flushing. See the man(3) qiflush entry for a description of my c function call." "void qiflush (void);" ] NCWindow class >> raw [ "I put the terminal in raw input mode. See the man(3) entry for a description of my c function call." "int raw (void);" ] NCWindow class >> refresh [ "I physically move the contents of stdscr to the physical screen. See then man(3) refresh entry for a description of my c function call." "int refresh (void);" ] NCWindow class >> resetProgMode [ "I restore the terminal to the 'program' state. See the man(3) reset_prog_mode entry for a description of my c function call." "int reset_prog_mode (void);" ] NCWindow class >> resetShellMode [ "I restore the terminal to the 'shell' state. See the man(3) reset_shell_mode entry for a description of my c function call." "int reset_shell_mode (void);" ] NCWindow class >> resetty [ "I restore the state of the terminal modes to the state saved by the last savetty message. See the man(3) resetty entry for a description of my c function call." "int resetty (void);" ] NCWindow class >> resizeTerm: anInt1 columns: anInt2 [ "I resize the current and the standard windows to the number of rows and columns given to me. See the man(3) resizeterm entry for a description of my c function call." "int resizeterm (int, int);" ] NCWindow class >> savetty [ "I save the state of the terminal modes. See the man(3) savetty entry for a description of my c function call." "int savetty (void);" ] NCWindow class >> scanw: aString args: anArray [ "I scan an input string. See the man(3) scanw entry for a description of my c function call." "int scanw (const char *, ...)" ] NCWindow class >> scrDump: aString [ "I dump the contents of the virtual screen to a file. See the man(3) scr_dump entry for a description of my c function call." "int scr_dump (const char *);" ] NCWindow class >> scrInit: aString [ "I initialize the cursors structures based on the contents of a file. See the man(3) scr_init entry for a description of my c function call." "int scr_init (const char *);" ] NCWindow class >> scrRestore: aString [ "I load the contents of a file previously saved by the scr_dump into the virtual screen. See the man(3) scr_restore entry for a description of my c function call." "int scr_restore (const char *);" ] NCWindow class >> scrSet: aString [ "I load the contents of a file and perform a combination of scr_init and scr_restore operations. See the man(3) scr_set entry for a description of my c function call." "int scr_set (const char *);" ] NCWindow class >> scrl: anInt [ "I scroll up the terminal the number of lines given to me. See the man(3) scrl entry for a description of my c function call." "int scrl (int);" ] NCWindow class >> setTerm: cObject [ "I switch between different terminals. See the man(3) set_term entry for a description of my c function call." "SCREEN *set_term (SCREEN *);" ] NCWindow class >> setscrreg: anInt1 bot: anInt2 [ "I enable a scroll region within a window between the top and bottom lines given to me. See the man(3) setscrreg entry for a description of my c function call." "int setscrreg (int, int);" ] NCWindow class >> slkAttr [ "I return the attribute used for the softkeys. See the man(3) slk_attr entyr for a description of the c function call." "attr_t slk_attr (void);" ] NCWindow class >> slkAttrSet: anInt1 colorPair: anInt2 opts: cObject [ "I set the attribute color-pair for the soft keys to the value given to me. See the man(3) slk_attr_set entry for a description of my c function call." "int slk_attr_set (const attr_t, short, void*);" ] NCWindow class >> slkAttroff: aChar [ "I turn off the named attribute given to me for the soft keys. See the man(3) slk_attr_off for a description of my c function call." "int slk_attroff (const chtype);" ] NCWindow class >> slkAttron: aChar [ "I turn on the named attribute given to me for the soft keys. See the man(3) slk_attr_on for a description of my c function call." "int slk_attron (const chtype);" ] NCWindow class >> slkAttrset: aChar [ "I set the attribute color-pair for the soft keys to the value given to me. See the man(3) slk_attrset entry for a description of my c function call." "int slk_attrset (const chtype);" ] NCWindow class >> slkClear [ "I clear the soft labels from the screen. See the man(3) slk_attr entry for a description of my c function call." "int slk_clear (void);" ] NCWindow class >> slkColor: anInt [ "I set the current color of the soft keys to the color pair attribute given to me. See the man(3) slk_color entry for a description of my c function call." "int slk_color (short);" ] NCWindow class >> slkInit: anInt [ "I establish the format of the soft key label presentation using the value given to me. See the man(3) slk_init entry for a description of my c function call." "int slk_init (int);" ] NCWindow class >> slkLabel: anInt [ "I return the label text for the label number given to me. See the man(3) slk_label entry for a description of my c function call." "char *slk_label (int);" ] NCWindow class >> slkNoutrefresh [ "I commit the differences between the soft labels in the virtual screen and the physical screen to the physical screen. See the man(3)slk_noutrefresh entry for a description of my c function call." "int slk_noutrefresh (void);" ] NCWindow class >> slkRefresh [ "I commit the soft labels in the virtual screen to the physical screen. See the man(3)slk_refresh entry for a description of my c function call." "int slk_refresh (void);" ] NCWindow class >> slkRestore [ "I restore the labels to the screen after a slk_clear. See the man(3) entry for description of my c function call." "int slk_restore (void);" ] NCWindow class >> slkSet: anInt1 label: aString format: anInt2 [ "I set the label text for the label number given to me using the format given to me. See the man(3) slk_set entry for a description of my c function call." "int slk_set (int, const char *, int);" ] NCWindow class >> slkTouch [ "I cause all of the soft labels in the virtual screen to be commited to the physical screen the next time a slk_noutrefresh is sent. See the man(3) slk_touch entry for a description of my c function call." "int slk_touch (void);" ] NCWindow class >> standend [ "I turn off all attributes in the screen. See the man(3) standend entry for a description of my c function call." "int standend (void);" ] NCWindow class >> standout [ "I turn on the best highlighting available in the screen. See the man(3) standout entry for a description of my c function call." "int standout (void);" ] NCWindow class >> startColor [ "I intitialize the color table. See the man(3) start_color entry for a description of my c function call." "int start_color (void);" ] NCWindow class >> stdscr [ "WINDOW *stdscr;" ^StdScreen ] NCWindow class >> termattrs [ "I return the logical OR of the attributes supported by my terminal. See the man(3) termattrs entry for a description of my c function call." "chtype termattrs (void);" ] NCWindow class >> termname [ "I return the terminal name used by setupterm. See the man(3) termname entry for a description of my c function call." "char *termname (void);" ] NCWindow class >> tigetflag: aString [ "I return the compatibillity corresponding to the terminfo capinfo given to me. See the man(3) tigetflag entry for a description of my c function call." "int tigetflag (const char *);" ] NCWindow class >> tigetnum: aString [ "I return the compatibillity corresponding to the terminfo capinfo given to me. See the man(3) tigetnum entry for a description of my c function call." "int tigetnum (const char *);" ] NCWindow class >> tigetstr: aString [ "I return the compatibillity corresponding to the terminfo capinfo given to me. See the man(3) tigetstr entry for a description of my c function call." "char *tigetstr (const char *);" ] NCWindow class >> timeout: anInt [ "I configure blocking and non-blocking reads in the terminal based on the value given to me. See the man(3) timeout entry for a description of my c function call." "void timeout (int);" ] NCWindow class >> tparm: aString [ "I instantiate the string given to me with the arguments given to me. See the man(3) tparm entry for a description of my c function call." "char *tparm (const char *, ...);" ] NCWindow class >> tparm: aString args: anArray [ "I instantiate the string given to me with the arguments given to me. See the man(3) tparm entry for a description of my c function call." "char *tparm (const char *, ...);" ] NCWindow class >> typeahead: anInt [ "I set typeahead fd to be checked to the fd given to me. See the man(3) typeahead entry for a description of my c function calls." "int typeahead (int);" ] NCWindow class >> ungetch: anInt [ "I push the character given to me back onto the input stream to be re-read. See the man(3) ungetc entry for a description of my c function call." "int ungetch (int);" ] NCWindow class >> useDefaultColors [ "I tell the ncurses library to use the default background and foreground colors. See the man(3) use_default_colors entry for a description of my c function call." "int use_default_colors (void);" ] NCWindow class >> useEnv: aBoolean [ "I cause the number of columns and rows to be used in the window to be determined by the value of environment variables if I am given the boolean value true. See the man(3) use_env entry for a description of my c function call." "void use_env (bool);" ] NCWindow class >> useExtendedNames: aBoolean [ "I enable using user-defined terminfo names if I am given the boolean value true. See the man(3) use_extended_names entry for a description for a description of my c function call." "int use_extended_names (bool);" ] NCWindow class >> vidattr: aChar [ "I display a string in the terminal using the attribute given to me. See the man(3) vidattr entry for a description of my c function call." "int vidattr (chtype);" ] NCWindow class >> vline: aChar n: anInt [ "I write a vertical line of at most n characters comprised of the character given to me in the terminal. See the man(3) vline entry for a description of my c function call." "int vline (chtype, int);" ] NCWindow class >> clock [ | screen | self initscr; noecho; cbreak; refresh. screen := self newwin: 13 cols: 27 beginY: 1 beginX: 1. screen nodelay: true. [screen wgetch = $q asInteger] whileFalse: [screen mvwprintw: 3 x: 6 str: Date today printString; mvwprintw: 5 x: 6 str: Time now printString; wrefresh. (Delay forSeconds: 1) wait]. self endwin ] NCWindow class >> helloWorld [ self initscr; printw: 'hello world'; refresh; getch; endwin ] box: aChar1 withHorizontalChar: aChar2 [ "I draw a box using the characters sent as arguments. See the man(3) box entry for a description of my c function call." "int box (WINDOW *, chtype, chtype);" ] clearok: aBoolean [ "I cause the screen to be cleared and re-drawn from scratch the next time the refresh message is sent when I receive the boolean value 'true' as an argument. See the man(3) clearok entry for a description of my c function call." "int clearok (WINDOW *, bool);" ] copywin: cObject sourceMinimumRow: anInt1 sourceMinimumColumn: anInt2 destinationMinimumRow: anInt3 destinationMinimumColumn: anInt4 destinationMaximumRow: anInt5 destinationMaximumColumn: anInt6 overlay: anInt7 [ "I overlay or overwrite a destination window with my window. See the man(3) copywin entry for a description of my c function call." "int copywin (const WINDOW*, WINDOW*, int, int, int, int, int, int, int);" ] delscreen: cObject [ "I release the storage associated with a screen structure. See the man(3) delscreen entry for a description of my c function call." "void delscreen (SCREEN *);" ] delwin [ "I release the storage associated with my window structure. See the man(3) delwin entry for a description of my c function call." "int delwin (WINDOW *);" ] derwin: anInt1 forColumns: anInt2 atY: anInt3 atX: anInt4 [ "I return a new window with the given number lines and columns with the top left corner at the location given as coorindates. See the man(3) derwin entry for a description of my c function call." "WINDOW *derwin (WINDOW *, int, int, int, int);" ] dupwin [ "I return a duplicate of my window. See the man(3) dupwin entry for a description of my c function call." "WINDOW *dupwin (WINDOW *);" ] getbkgd [ "I return my windows' attribute/character pair. See the man(3) getbkgd entry for a description of my c function call." "chtype getbkgd (WINDOW *);" ] idcok: aBoolean [ "I enable or disable the use of the hardware character insert/delete terminal feature if it's available. See the man(3) idcok entry for a description of my c function call." "void idcok (WINDOW *, bool);" ] idlok: aBoolean [ "I enable or disable the use of the hardware line insert/delete terminal feature if it's available. See the man(3) idlok entry for a description of my c function call." "int idlok (WINDOW *, bool);" ] immedok: aBoolean [ "I enable or disable the automatic refresh of my window whenever it's updated. See the man(3) immedok entry for a description of my c function call." "void immedok (WINDOW *, bool);" ] intrflush: aBoolean [ "I enable or disable flushing the tty driver queue whenever an interrupt key is pressed. See then man(3) intrflush entry for a description of my c call function." "int intrflush (WINDOW *, bool);" ] isLinetouched: anInt [ "I return true if the line number sent to me as a parameter is within my window otherwise I return false. See the man(3) is_linetouched entry for a description of my c function call." "bool is_linetouched (WINDOW *, int);" ] isWintouched [ "I return true if my window has been updated since the last refresh message was sent. See the man(3) is_wintouched entry for a description of my c function call." "bool is_wintouched (WINDOW *);" ] keypad: aBoolean [ "I enable or disable the use of the keyboard keypad. See the man(3) keypad entry for a description of my c function call." "int keypad (WINDOW *, bool);" ] leaveok: aBoolean [ "I enable or disable leaving the cursor at the location an update places it. See the man(3) leaveok entry for a description of my c function call." "int leaveok (WINDOW *, bool);" ] meta: aBoolean [ "I ask the tty driver to return 8-bits if I'm passed the boolean value true, and 7-bits if I'm passed the boolean value false. See the man(3) meta entry for a description of my c function call." "int meta (WINDOW *, bool);" ] mvderwin: anInt1 parX: anInt2 [ "I move a subwindow within my window to new location and put it's top left corner at the location given to me as a coordinates. See the man(3) mvderwin entry for a description of my c function call." "int mvderwin (WINDOW *, int, int);" ] mvwaddch: anInt1 x: anInt2 ch: aChar [ "I add a character to my window at the current cursor location after advancing the cursor to the coordinates given to me. See the man(3) mvwaddch entry for a description of my c function call." "int mvwaddch (WINDOW *, int, int, const chtype);" ] mvwaddchnstr: anInt1 x: anInt2 str: aString n: anInt3 [ "I copy up to n characters of the string and attributes given to me into my window starting at the location specified by the coordinates given to me. See the man(3) mvwaddchnstr entry for a description of my c function call." "int mvwaddchnstr (WINDOW *, int, int, const chtype *, int);" ] mvwaddchstr: anInt1 x: anInt2 str: aString [ "I copy the string and attributes given to me into my window starting at the location specified by the point given to me. See the man(3) mvwaddchnstr entry for a description of my c function call." "int mvwaddchstr (WINDOW *, int, int, const chtype *);" ] mvwaddnstr: anInt1 x: anInt2 str: aString n: anInt3 [ "I copy up to n characters of the string given to me in my window starting at the location specified by the coordinates given to me. See the man(3) mvwaddnstr entry for a description of my c function call." "int mvwaddnstr (WINDOW *, int, int, const char *, int);" ] mvwaddstr: anInt1 x: anInt2 str: aString [ "I copy the string given to me into my window starting at the location given to me as a point. See the man(3) mvwaddstr entry for a description of my c function call." "int mvwaddstr (WINDOW *, int, int, const char *);" ] mvwchgat: anInt1 x: anInt2 n: anInt3 attr: anInt4 color: anInt5 opts: cObject [ "I change the color and attribute of next n characters in my window starting at the location specified by the point given to me. See the man(3) mvwchgat entry for a description of my c function call." "int mvwchgat (WINDOW *, int, int, int, attr_t, short, const void *);" ] mvwdelch: anInt1 x: anInt2 [ "I move the cursor to the coordinates given to me in my window, delete the character under the cursor, and then shift the remaining characters in the line one position to the left. See the man(3) mvwdelch entry for description of my c function call." "int mvwdelch (WINDOW *, int, int);" ] mvwgetch: anInt1 x: anInt2 [ "I position the cursor to the location in my window specified by the point given to me, I read a character. See the man(3) mvwgetch entry for a description of my c function call." "int mvwgetch (WINDOW *, int, int);" ] mvwgetnstr: anInt1 x: anInt2 str: aString n: anInt3 [ "I position the cursor to the location in my window specified by the coordinates given to me, and then I read at most n characters until a carriage return or newline is pressed. See the man(3) mvwgetnstr entry for a description of my c function call." "int mvwgetnstr (WINDOW *, int, int, char *, int);" ] mvwgetstr: anInt1 x: anInt2 str: aString [ "I position the cursor to the location in my window specified by the coordinates given to me, and thenI read characters until a carriage return or a newline is pressed. See man(3) mvwgetstr entry for a description of my c function call." "int mvwgetstr (WINDOW *, int, int, char *);" ] mvwhline: anInt1 x: anInt2 ch: aChar n: anInt3 [ "I position the cursor to the location in my window specified by the coordinates given to me, and then I write a horizontal line of at most n characters comprised of the character given to me. See the man(3) mvwhline entry for a description of my c function call." "int mvwhline (WINDOW *, int, int, chtype, int);" ] mvwin: anInt1 x: anInt2 [ "I move the top-left-corner of my window to the location given to me as coordinates. See the man(3) mvwin entry for a description of my c function call." "int mvwin (WINDOW *, int, int);" ] mvwinch: anInt1 x: anInt2 [ "I return the character or attribute at the cursor location specifed by the coordinates given to me. See the man(3) mvwinch entry for a description of my c call function." "chtype mvwinch (WINDOW *, int, int);" ] mvwinchnstr: anInt1 x: anInt2 str: aString n: anInt3 [ "I return a null terminated array of characters or attributes from my window of at most n characters starting at the cursor location specified by the coordinates given to me. See the man(3) mvwinchnstr entry for a description of my c function call." "int mvwinchnstr (WINDOW *, int, int, chtype *, int);" ] mvwinchstr: anInt1 x: anInt2 str: aString [ "I return a null terminated array of characters or attributes from within my window starting at the cursor location given by the coordinates given to me. See the man(3) mvwinchstr entry for a description of my c call function." "int mvwinchstr (WINDOW *, int, int, chtype *);" ] mvwinnstr: anInt1 x: anInt2 str: aString n: anInt3 [ "I return a string of characters from my window stripped of attributes starting at the location given to me as coordinates. See the man(3) mvwinnstr entry for a description of my c function call." "int mvwinnstr (WINDOW *, int, int, char *, int);" ] mvwinsch: anInt1 x: anInt2 ch: aChar [ "I insert a character in my window before the location given to me as coordinates. The remaining characters in the line are shifted one position to the right. See the man(3) mvwinsch entry for a description of my c function call." "int mvwinsch (WINDOW *, int, int, chtype);" ] mvwinsnstr: anInt1 x: anInt2 str: aString n: anInt3 [ "I insert a string of at most n characters in my window before the location given to me as coordinates. The remaining characters in the line are shifted one position to the right. See the man(3) mvwinsnstr entry for a description of my c function call." "int mvwinsnstr (WINDOW *, int, int, const char *, int);" ] mvwinsstr: anInt1 x: anInt2 str: aString [ "I insert a string before the location in my window given to me as coordinates. The remaining characters in the line are shifted one position to the right. See the man(3) mvwinsstr entry for a description of my c function call." "int mvwinsstr (WINDOW *, int, int, const char *);" ] mvwinstr: anInt1 x: anInt2 str: aString [ "I return a string of characters from my window starting from the location given to me as coordinates. See the man(3) mvwinstr for a description of my c function call." "int mvwinstr (WINDOW *, int, int, char *);" ] mvwprintw: anInt1 x: anInt2 str: aString [ "I print a string in my window at the location given to me as coordinates. See the man(3) mvwprintw entry for a description of my c function call." "int mvwprintw (WINDOW*, int, int, const char *)" ] mvwprintw: anInt1 x: anInt2 str: aString args: anArray [ "I print a formated string and arguments in my window at the location given to me as coordinates. See the man(3) mvwprintw entry for a description of my c function call." "int mvwprintw (WINDOW*, int, int, const char *, ...)" ] mvwscanw: anInt1 x: anInt2 str: aString args: anArray [ "I scan a string from within my window at the location given to me a point. See the man(3) mvwscanw entry for a description of my c function call." "int mvwscanw (WINDOW *, int, int, const char *, ...)" ] mvwvline: anInt1 x: anInt2 ch: aChar n: anInt3 [ "I position the cursor to the location in my window specified by the coordinates given to me, then I write a vertical line of at most n characters comprised of the character given to me. See the man(3) mvwvline entry for a description of my c function call." "int mvwvline (WINDOW *, int, int, chtype, int);" ] nodelay: aBoolean [ "I set getch to be non-blocking in my window if I'm given a value of true. Otherwise I set getch be blocking. See the man(3) nodelay entry for a description of my c function call." "int nodelay (WINDOW *, bool);" ] notimeout: aBoolean [ "I turn off the timer for reading an escape sequence by wgetch for my window if I am given the boolean value true. Otherwise, I turn the timer on. See the man(3) notimeout entry for a description of my c functtion call." "int notimeout (WINDOW *, bool);" ] overlay: cObject [ "I overlay the window given to me with my window. See the man(3) overlay entry for a description of my c function call." "int overlay (const WINDOW*, WINDOW *);" ] overwrite: cObject [ "I overwrite the window given to me with my window. See the man(3) overwrite entry for a description of my c function call." "int overwrite (const WINDOW*, WINDOW *);" ] pechochar: aChar [ "I output a character to the pad in my window. See the man(3) pechochar entry for a description of my c function call." "int pechochar (WINDOW *, const chtype);" ] pnoutrefresh: anInt1 pmincol: anInt2 sminrow: anInt3 smincol: anInt4 smaxrow: anInt5 smaxcol: anInt6 [ "I copy my windows pad to the virtual screen. See the man(3) pnoutrefresh entry for a description of my c function call." "int pnoutrefresh (WINDOW*, int, int, int, int, int, int);" ] prefresh: anInt1 pmincol: anInt2 sminrow: anInt3 smincol: anInt4 smaxrow: anInt5 smaxcol: anInt6 [ "I copy the pad in my window to the physical screen. See the man(3) entry for a description of my c function call." "int prefresh (WINDOW *, int, int, int, int, int, int);" ] redrawwin [ "I tag all the lines in my window to be output during the next refresh. See the man(3) redrawwin entry for a description of my c function call." "int redrawwin (WINDOW *);" ] scroll [ "I scroll up my window up one line. See the man(3) scroll entry for a description of my c function call." "int scroll (WINDOW *);" ] scrollok: aBoolean [ "I enable scrolling the window when the cursor is within a scroll region if I am given the boolean value true. Otherwise, I disable scrolling the window when the cursor is in the scroll region." "int scrollok (WINDOW *, bool);" ] subpad: anInt1 ncols: anInt2 beginY: anInt3 beginX: anInt4 [ "I create a sub-window within a pad in my window of the given size and location. See the man(3) subpad entry for a description of my c function call." "WINDOW *subpad (WINDOW *, int, int, int, int);" ] subwin: anInt1 ncols: anInt2 beginY: anInt3 beginX: anInt4 [ "I create a new sub-window with m y window of the given size and location. See the man(3) subwin entry for a description of my c function call." "WINDOW *subwin (WINDOW *, int, int, int, int);" ] syncok: aBoolean [ "I enable the automatic updating of ancestor windows when a change occurs if my window if given the boolean true value. See the man(3) syncok entry for a description of my c function call." "int syncok (WINDOW *, bool);" ] touchline: anInt1 count: anInt2 [ "I configure the lines in my window given to me to be redrawn during the next refresh. See the man(3) touchline entry for a description of my c function call." "int touchline (WINDOW *, int, int);" ] touchwin [ "I configure my window to be to be redraw during the next refresh. See the man(3) touchwin entry for a description of my c function call." "int touchwin (WINDOW *);" ] untouchwin [ "I mark all the lines in my windows as untouched since the last refresh. See the man(3) untouchwin entry for a description of my c function call." "int untouchwin (WINDOW *);" ] waddch: aChar [ "I add a character given to me to my window at the current cursor location and then advance the cursor. See the man(3) waddch entry for a description of my c function call." "int waddch (WINDOW *, const chtype);" ] waddchnstr: aString n: anInt [ "I copy up to n characters of the string and attributes given to me into my window starting at the location specified by the coordinates given to me. See the man(3) mvwaddchnstr entry for a description of my c function call." "int waddchnstr (WINDOW *, const chtype *, int);" ] waddchstr: aString [ "I copy the string and attributes given to me into my window. See the man(3) waddchstr entry for a description of my c function call." "int waddchstr (WINDOW *, const chtype *);" ] waddnstr: aString n: anInt [ "I copy up to n characters of the string given to me in my window. See the man(3) waddnstr entry for a description of my c function call." "int waddnstr (WINDOW *, const char *, int);" ] waddstr: aString [ "I copy the string given to me into my window. See the man(3) waddstr entry for a description of my c function call." "int waddstr (WINDOW *, const char *);" ] wattrGet: cObject2 opts: cObject3 [ "I return the attribute and color pair for my window. See the man(3) wattr_get entry for a description of my c function call." "int wattr_get (WINDOW *, attr_t *, short *, void *);" ] wattrOff: anInt opts: cObject [ "I turn off the attributes given to me for my window. See the man(3) wattr_off entry for a description of my c function call." "int wattr_off (WINDOW *, attr_t, void *);" ] wattrOn: anInt opts: cObject [ "I turn on the named attribute given to me in my window. See the man(3) wattr_on for a description of my c function call." "int wattr_on (WINDOW *, attr_t, void *);" ] wattrSet: anInt1 pair: anInt2 opts: cObject [ "I set the attribute color-pair in my window to the value given to me. See the man(3) attr_set entry for a description of my c function call." "int wattr_set (WINDOW *, attr_t, short, void *);" ] wattroff: anInt [ "I turn off the named attribute given to me in my window. See the man(3) wattroff for a description of my c function call." "int wattroff (WINDOW *, int);" ] wattron: anInt [ "I turn on the named attribute given to me in my window. See the man(3) wattron for a description of my c function call." "int wattron (WINDOW *, int);" ] wattrset: anInt [ "I set the attribute color-pair in my window to the value given to me. See the man(3) wattrset entry for a description of my c function call." "int wattrset (WINDOW *, int);" ] wbkgd: aChar [ "I set the background attribute given to me to every character in the window. See the man(3) wbkgd entry for a description of my c function call." "int wbkgd (WINDOW *, chtype);" ] wbkgdset: aChar [ "I set the background to to the value given to me to every position in the window. See the man(3) wbkgdset entry for a description of my c function call." "void wbkgdset (WINDOW *, chtype);" ] wborder: aChar1 rs: aChar2 ts: aChar3 bs: aChar4 tl: aChar5 tr: aChar6 bl: aChar7 br: aChar9 [ "I draw a box around the edge of my window using the character attributes given to me. See the man(3) wborder entry for a description of my c function call." "int wborder (WINDOW *, chtype, chtype, chtype, chtype, chtype, chtype, chtype, chtype);" ] wchgat: anInt1 attr: anInt2 color: anInt3 opts: cObject [ "I change the color and attribute in my window. See the man(3) wchgat entry for a description of my c function call." "int wchgat (WINDOW *, int, attr_t, short, const void *);" ] wclear [ "I put a blank in every character position in my window and set up the window to be re-painted the next time that it is refreshed. See the man(3) wclear entry for a description of my c function calls." "int wclear (WINDOW *);" ] wclrtobot [ "I erase my window from the right of the current cursor position all the way to the bottom right of the screen. See the man(3) wclrtobot entry for a description of my c function call." "int wclrtobot (WINDOW *);" ] wclrtoeol [ "I erase the current line in my window to the right of the current cursor location. See the man(3) wclrtoeol entry for a description of my c function calls." "int wclrtoeol (WINDOW *);" ] wcolorSet: anInt opts: cObject [ "I set the current color of my window to the color pair attribute given to me. See the man(3) wcolor_set entry for a description of my c function call." "int wcolor_set (WINDOW*, short, void*);" ] wcursyncup [ "I set the cursor position in all of my ancestor windows to the current location in my window. See the man(3) wcursyncup entry for a description of my c function call." "void wcursyncup (WINDOW *);" ] wdelch [ "I delete the character under the cursor, and then shift the remaining characters in the line one position to the left. See the man(3) wdelch entry for description of my c function call." "int wdelch (WINDOW *);" ] wdeleteln [ "I delete the line under the current cursor position, move all of the lines below the cursor up one line and clear the last line. See the man(3) wdeleteln entry for a description of my c function call." "int wdeleteln (WINDOW *);" ] wechochar: aChar [ "I put the character given to me at the current cursor position, advance the cursor, and then refresh the screen. See the man(3) wechochar entry for a description of my c function call." "int wechochar (WINDOW *, const chtype);" ] werase [ "I put blanks into every position in the screen. See the man(3) werase entry for a description of my c function call." "int werase (WINDOW *);" ] wgetch [ "I read a keystroke from my window. See the man(3) wgetch entry for a description of my c function call." "int wgetch (WINDOW *);" ] wgetnstr: aString n: anInt [ "I read at most n keystrokes from nm window until a return or linefeed key is pressed. See the man(3) wgetnstr entry for a description of my c function call." "int wgetnstr (WINDOW *, char *, int);" ] wgetstr: aString [ "I read keystrokes from my window until a return or linefeed key is pressed. See the man(3) wgetstr entry for a description of my c function call." "int wgetstr (WINDOW *, char *);" ] whline: aChar n: anInt [ "I draw a horizontal line in my window using the character given to me of at most n characters. See the man(3) hline entry for a description of my c function call." "int whline (WINDOW *, chtype, int);" ] winch [ "I return the character or attribute at the current cursor location in my window. See the man(3) winch entry for a description of my c call function." "chtype winch (WINDOW *);" ] winchnstr: aString n: anInt [ "I return a null terminated array of characters or attributes from my window of at most n characters starting at the current cursor location. See the man(3) winchnstr entry for a description of my c function call." "int winchnstr (WINDOW *, chtype *, int);" ] winchstr: aString [ "I return a null terminated array of characters or attributes from within my window starting at the current cursor location. See the man(3) winchstr entry for a description of my c call function." "int winchstr (WINDOW *, chtype *);" ] winnstr: aString n: anInt [ "I return a string of characters from my window stripped of attributes starting at the current cursor location. See the man(3) winnstr entry for a description of my c function call." "int winnstr (WINDOW *, char *, int);" ] winsch: aChar [ "I insert a character in my window before the current cursor location. The remaining characters in the line are shifted one position to the right. See the man(3) winsch entry for a description of my c function call." "int winsch (WINDOW *, chtype);" ] winsdelln: anInt [ "I insert the number of blank lines given to me in my window above the current line and delete the same number of lines from the bottom. See the man(3) winsdelln entry for a description of my c function call." "int winsdelln (WINDOW *, int);" ] winsertln [ "I insert a blank line in my window above the current line and delete the bottom line. See the man(3) winsertln entry for a description of my c function call." "int winsertln (WINDOW *);" ] winsnstr: aString n: anInt [ "I insert a string of at most n characters in my window before the location of the current cursor. The remaining characters in the line are shifted one position to the right. See the man(3) winsnstr entry for a description of my c function call." "int winsnstr (WINDOW *, const char *, int);" ] winsstr: aString [ "I insert a string before the location of the cursor in my window. The remaining characters in the line are shifted one position to the right. See the man(3) winsstr entry for a description of my c function call." "int winsstr (WINDOW *, const char *);" ] winstr: aString [ "I return a string of characters from my window starting from the location of the cursor. See the man(3) mvwinstr for a description of my c function call." "int winstr (WINDOW *, char *);" ] wmove: anInt1 x: anInt2 [ "I move the cursor in my window to the position given to me. See the man(3) wmove entry for a description of my c function call." "int wmove (WINDOW *, int, int);" ] wnoutrefresh [ "I update the virtual screen with the contents of my window. See the man(3) wnoutrefresh entry for a description of my c function call." "int wnoutrefresh (WINDOW *);" ] wprintw: aString [ "I print a string in my window at the location of the cursor. See the man(3) wprintw entry for a description of my c function call." "int wprintw (WINDOW *, const char *, ...)" ] wprintw: aString args: anArray [ "I print string and arguments in my window at the location of the cursor. See the man(3) wprintw entry for a description of my c function call." "int wprintw (WINDOW *, const char *, ...)" ] wredrawln: anInt1 x: anInt2 [ "I mark the lines given to me in window to be redrawn by the next refresh. See the man(3) wredrawln entry for a description for my c function call." "int wredrawln (WINDOW *, int, int);" ] wrefresh [ "I copy my window to the physical screen. See the man(3) wrefresh entry for a description of my c function call." "int wrefresh (WINDOW *);" ] wresize: anInt1 columns: anInt2 [ "I adjust my window to the dimensions given to me. See the man(3) wresize entry for a description of my c function call." "int wresize (WINDOW *, int, int);" ] wscanw: aString args: anArray [ "I scan a string from within my window at the location of the cursor See the man(3) mvwscanw entry for a description of my c function call." "int wscanw (WINDOW *, const char *, ...)" ] wscrl: anInt [ "I scroll up my window the number of lines given to me. See the man(3) wscrl entry for a description of my c function call." "int wscrl (WINDOW *, int);" ] wsetscrreg: anInt1 x: anInt2 [ "I enable a scroll region within my window between the top and bottom lines given to me. See the man(3) wsetscrreg entry for a description of my c function call." "int wsetscrreg (WINDOW *, int, int);" ] wstandend [ "I turn off all attributes in the window. See the man(3) wstandend entry for a description of my c function call." "int wstandend (WINDOW *);" ] wstandout [ "I turn on the best highlighting available in the window. See the man(3) wstandout entry for a description of my c function call." "int wstandout (WINDOW *);" ] wsyncdown [ "I mark the same lines in my window for refresh as the lines that have been marked for refresh in my ancestor windows. See the man(3) wsyncdown entry for a description of my c function call." "void wsyncdown (WINDOW *);" ] wsyncup [ "I mark the same lines in my ancestore windows for refresh as the lines that have been marked for refresh in my window. See the man(3) wsyncup entry for a description of my c function call." "void wsyncup (WINDOW *);" ] wtimeout: anInt [ "I configure blocking and non-blocking reads in the window based on the value given to me. See the man(3) wtimeout entry for a description of my c function call." "void wtimeout (WINDOW *, int);" ] wtouchln: anInt1 n: anInt2 changed: anInt3 [ "I mark/unmark the number of lines in my window for refresh given to me. See the man(3) wtouchln for a description of my c function call." "int wtouchln (WINDOW *, int, int, int);" ] wvline: aChar n: anInt [ "I write a vertical line of at most n characters comprised of the character given to me. See the man(3) wvline entry for a description of my c function call." "int wvline (WINDOW *, chtype, int);" ] ] smalltalk-3.2.5/packages/ncurses/ChangeLog0000644000175000017500000000031312123404352015431 000000000000002010-12-04 Paolo Bonzini * package.xml: Remove now superfluous tags. 2007-08-13 Paolo Bonzini * ncurses.st: Switch to the new syntax for "returning:". smalltalk-3.2.5/packages/ncurses/stamp-classes0000644000175000017500000000000012123404352016352 00000000000000smalltalk-3.2.5/packages/ncurses/package.xml0000644000175000017500000000020312123404352015772 00000000000000 NCurses ncurses.st libncurses ChangeLog smalltalk-3.2.5/packages/magritte/0000755000175000017500000000000012130456014014074 500000000000000smalltalk-3.2.5/packages/magritte/Makefile.frag0000644000175000017500000000043112130343733016373 00000000000000Magritte_FILES = \ packages/magritte/magritte-gst.st packages/magritte/magritte-model.st packages/magritte/PORTING packages/magritte/magritte-tests.st $(Magritte_FILES): $(srcdir)/packages/magritte/stamp-classes: $(Magritte_FILES) touch $(srcdir)/packages/magritte/stamp-classes smalltalk-3.2.5/packages/magritte/magritte-model.st0000644000175000017500000044571512123404352017316 00000000000000String extend [ matches: aString [ aString isEmpty ifTrue: [^true]. ^(aString includesAnyOf: '*#') ifTrue: [aString match: self] ifFalse: [self includesSubstring: aString caseSensitive: false] ] ] Error subclass: MAError [ displayString [ ^self printString ] ] MAError subclass: MAPropertyError [ ] MAError subclass: MAReadError [ ] MAError subclass: MAValidationError [ | resumable | MAValidationError class >> description: aDescription signal: aString [ ^(self new) setDescription: aDescription; signal: aString; yourself ] beResumable [ resumable := true ] isResumable [ ^resumable ] printOn: aStream [ (self tag isDescription and: [self tag label notNil]) ifTrue: [aStream nextPutAll: self tag label; nextPutAll: ': ']. aStream nextPutAll: self messageText ] setDescription: aDescription [ self tag: aDescription. resumable := false ] ] MAValidationError subclass: MAConditionError [ ] MAValidationError subclass: MAConflictError [ ] MAValidationError subclass: MAKindError [ ] MAValidationError subclass: MAMultipleErrors [ | collection | MAMultipleErrors class >> description: aDescription errors: aCollection signal: aString [ ^(self new) setDescription: aDescription; setCollection: aCollection; signal: aString; yourself ] collection [ ^collection ] printOn: aStream [ self collection do: [:each | aStream print: each] separatedBy: [aStream nextPut: Character nl] ] setCollection: aCollection [ collection := aCollection ] ] MAValidationError subclass: MARangeError [ ] MAValidationError subclass: MARequiredError [ ] MAError subclass: MAWriteError [ ] nil subclass: MAProxyObject [ | realSubject | MAProxyObject class >> on: anObject [ ^self basicNew realSubject: anObject ] copy [ "It doesn't make sense to copy proxies in most cases, the real-subject needs to be looked up and will probably return a new instance on every call anyway." ^self ] doesNotUnderstand: aMessage [ ^self realSubject perform: aMessage selector withArguments: aMessage arguments ] isMorph [ "Answer ==false==, since I am no morph. Squeak is calling this method after image-startup and might lock if I do not answer to this message." ^false ] isNil [ "This method is required to properly return ==true== if the ==realSubject== is ==nil==." ^self realSubject isNil ] printOn: aStream [ "Print the receiver on ==aStream== but within square-brackets to show that it is a proxied instance." aStream nextPut: $[; print: self realSubject; nextPut: $] ] printString [ ^String streamContents: [:stream | self printOn: stream] ] realSubject [ ^realSubject ] realSubject: anObject [ realSubject := anObject ] ] MAProxyObject subclass: MADynamicObject [ realSubject [ ^super realSubject on: SystemExceptions.UnhandledException do: [:err | nil] ] ] ArrayedCollection extend [ copyWithAll: aCollection [ ^(self species new: self size + aCollection size) replaceFrom: 1 to: self size with: self startingAt: 1; replaceFrom: self size + 1 to: self size + aCollection size with: aCollection startingAt: 1; yourself ] ] Class extend [ descriptionContainer [ "Return the default description container." ^(Magritte.MAPriorityContainer new) label: self label; yourself ] label [ "Answer a human-readable name of the receiving class. This implementation tries to be smart and return a nice label, unfortunately for a lot of classes this doesn't work well so subclasses might want to override this method and return soemthing more meaningfull to end-users." | start input | start := self name findFirst: [:each | each isLowercase]. input := (self name copyFrom: (1 max: start - 1) to: self name size) readStream. ^String streamContents: [:stream | [input atEnd] whileFalse: [stream nextPut: input next. (input atEnd or: [input peek isLowercase]) ifFalse: [stream nextPut: Character space]]] ] ] Collection extend [ asMultilineString [ ^String streamContents: [:stream | self do: [:each | stream nextPutAll: each] separatedBy: [stream nextPut: Character nl]] ] copyWithAll: aCollection [ ^(self copy) addAll: aCollection; yourself ] copyWithoutFirst: anObject [ | done | done := false. ^self reject: [:each | (each = anObject and: [done not]) and: [done := true]] ] ] BlockClosure extend [ asDynamicObject [ "Answer an object that will automatically evaluate the receiver when it receives a message. It will eventually pass the message to the resulting object. Use with caution, for details see *MADynamicObject*." ^Magritte.MADynamicObject on: self ] ] SequenceableCollection extend [ asAccessor [ ^Magritte.MAChainAccessor accessors: self ] moveDown: anObject [ | first second | first := self identityIndexOf: anObject ifAbsent: [^0]. second := first < self size ifTrue: [first + 1] ifFalse: [^first]. self swap: first with: second. ^second ] moveUp: anObject [ | first second | first := self identityIndexOf: anObject ifAbsent: [^0]. second := first > 1 ifTrue: [first - 1] ifFalse: [^first]. self swap: first with: second. ^second ] reduce: aBlock [ | result | self isEmpty ifTrue: [^nil]. result := self first. 2 to: self size do: [:index | result := aBlock value: result value: (self at: index)]. ^result ] ] Symbol extend [ asAccessor [ ^Magritte.MASelectorAccessor selector: self ] isDescriptionDefinition [ "Answer wheter the receiver is a method selector following the naming conventions of a description definition." ^self isDescriptionSelector and: [self isUnary] ] isDescriptionExtension: aSelector [ "Answer wheter the receiver is a method selector following the naming conventions of a description extension to aSelector." ^self isDescriptionSelector and: [self numArgs = 1 and: [self startsWith: aSelector]] ] isDescriptionSelector [ "Answer wheter the receiver is a method selector following the naming conventions of a description selector." ^self ~= #description and: [self startsWith: #description] ] ] Object subclass: MAAdaptiveModel [ | description values | MAAdaptiveModel class >> description: aDescription [ ^(self new) description: aDescription; yourself ] MAAdaptiveModel class >> new [ ^self basicNew initialize ] defaultDescription [ ^MAContainer new ] defaultDictionary [ ^Dictionary new ] description [ "Answer the description of the receiver." ^description ] description: aDescription [ description := aDescription ] initialize [ self description: self defaultDescription. self values: self defaultDictionary ] readUsing: aDescription [ "Answer the actual value of ==aDescription== within the receiver, ==nil== if not present." ^self values at: aDescription ifAbsent: [nil] ] values [ "Answer a dictionary mapping description to actual values." ^values ] values: aDictionary [ values := aDictionary ] write: anObject using: aDescription [ "Set ==anObject== to be that actual value of the receiver for ==aDescription==." self values at: aDescription put: anObject ] ] Object subclass: MADescriptionBuilder [ | cache | Default := nil. MADescriptionBuilder class >> default [ ^Default ] MADescriptionBuilder class >> default: aBuilder [ Default := aBuilder ] MADescriptionBuilder class >> for: anObject [ ^self default for: anObject ] MADescriptionBuilder class >> initialize [ self default: MANamedBuilder new ] MADescriptionBuilder class >> new [ ^self basicNew initialize ] build: anObject [ self subclassResponsibility ] finalize [ super finalize. self flush ] flush [ cache := IdentityDictionary new ] for: anObject [ ^cache at: anObject ifAbsentPut: [self build: anObject] ] initialize [ self flush ] ] MADescriptionBuilder subclass: MANamedBuilder [ build: anObject [ | selectors container description | selectors := anObject class allSelectors select: [:each | each isDescriptionSelector]. container := self build: anObject for: self containerSelector in: selectors. ^(selectors select: [:each | each isDescriptionDefinition]) inject: (cache at: anObject put: container) into: [:result :each | self containerSelector = each ifFalse: [description := self build: anObject for: each in: selectors. description isDescription ifTrue: [result add: description]]. result] ] build: anObject for: aSelector in: aCollection [ ^(aCollection select: [:each | each isDescriptionExtension: aSelector]) inject: (anObject perform: aSelector) into: [:result :each | anObject perform: each with: result] ] containerSelector [ ^#descriptionContainer ] ] Object subclass: MAFileModel [ | filename mimetype filesize | MimeTypes := nil. MAFileModel class >> defaultMimeType [ ^'application/octet-stream' ] MAFileModel class >> defaultMimeTypes [ ^#('ai' 'application/postscript' 'aif' 'audio/x-aiff' 'aifc' 'audio/x-aiff' 'aiff' 'audio/x-aiff' 'asc' 'text/plain' 'au' 'audio/basic' 'avi' 'video/x-msvideo' 'bcpio' 'application/x-bcpio' 'bin' 'application/octet-stream' 'c' 'text/plain' 'cc' 'text/plain' 'ccad' 'application/clariscad' 'cdf' 'application/x-netcdf' 'class' 'application/octet-stream' 'cpio' 'application/x-cpio' 'cpt' 'application/mac-compactpro' 'csh' 'application/x-csh' 'css' 'text/css' 'dcr' 'application/x-director' 'dir' 'application/x-director' 'dms' 'application/octet-stream' 'doc' 'application/msword' 'drw' 'application/drafting' 'dvi' 'application/x-dvi' 'dwg' 'application/acad' 'dxf' 'application/dxf' 'dxr' 'application/x-director' 'eps' 'application/postscript' 'etx' 'text/x-setext' 'exe' 'application/octet-stream' 'ez' 'application/andrew-inset' 'f' 'text/plain' 'f90' 'text/plain' 'fli' 'video/x-fli' 'gif' 'image/gif' 'gtar' 'application/x-gtar' 'gz' 'application/x-gzip' 'h' 'text/plain' 'hdf' 'application/x-hdf' 'hh' 'text/plain' 'hqx' 'application/mac-binhex40' 'htm' 'text/html' 'html' 'text/html' 'ice' 'x-conference/x-cooltalk' 'ief' 'image/ief' 'iges' 'model/iges' 'igs' 'model/iges' 'ips' 'application/x-ipscript' 'ipx' 'application/x-ipix' 'jpe' 'image/jpeg' 'jpeg' 'image/jpeg' 'jpg' 'image/jpeg' 'js' 'application/x-javascript' 'kar' 'audio/midi' 'latex' 'application/x-latex' 'lha' 'application/octet-stream' 'lsp' 'application/x-lisp' 'lzh' 'application/octet-stream' 'm' 'text/plain' 'man' 'application/x-troff-man' 'me' 'application/x-troff-me' 'mesh' 'model/mesh' 'mid' 'audio/midi' 'midi' 'audio/midi' 'mif' 'application/vnd.mif' 'mime' 'www/mime' 'mov' 'video/quicktime' 'movie' 'video/x-sgi-movie' 'mp2' 'audio/mpeg' 'mp3' 'audio/mpeg' 'mpe' 'video/mpeg' 'mpeg' 'video/mpeg' 'mpg' 'video/mpeg' 'mpga' 'audio/mpeg' 'ms' 'application/x-troff-ms' 'msh' 'model/mesh' 'nc' 'application/x-netcdf' 'oda' 'application/oda' 'pbm' 'image/x-portable-bitmap' 'pdb' 'chemical/x-pdb' 'pdf' 'application/pdf' 'pgm' 'image/x-portable-graymap' 'pgn' 'application/x-chess-pgn' 'png' 'image/png' 'pnm' 'image/x-portable-anymap' 'pot' 'application/mspowerpoint' 'ppm' 'image/x-portable-pixmap' 'pps' 'application/mspowerpoint' 'ppt' 'application/mspowerpoint' 'ppz' 'application/mspowerpoint' 'pre' 'application/x-freelance' 'prt' 'application/pro_eng' 'ps' 'application/postscript' 'qt' 'video/quicktime' 'ra' 'audio/x-realaudio' 'ram' 'audio/x-pn-realaudio' 'ras' 'image/cmu-raster' 'rgb' 'image/x-rgb' 'rm' 'audio/x-pn-realaudio' 'roff' 'application/x-troff' 'rpm' 'audio/x-pn-realaudio-plugin' 'rtf' 'text/rtf' 'rtx' 'text/richtext' 'scm' 'application/x-lotusscreencam' 'set' 'application/set' 'sgm' 'text/sgml' 'sgml' 'text/sgml' 'sh' 'application/x-sh' 'shar' 'application/x-shar' 'silo' 'model/mesh' 'sit' 'application/x-stuffit' 'skd' 'application/x-koan' 'skm' 'application/x-koan' 'skp' 'application/x-koan' 'skt' 'application/x-koan' 'smi' 'application/smil' 'smil' 'application/smil' 'snd' 'audio/basic' 'sol' 'application/solids' 'spl' 'application/x-futuresplash' 'src' 'application/x-wais-source' 'step' 'application/STEP' 'stl' 'application/SLA' 'stp' 'application/STEP' 'sv4cpio' 'application/x-sv4cpio' 'sv4crc' 'application/x-sv4crc' 'swf' 'application/x-shockwave-flash' 't' 'application/x-troff' 'tar' 'application/x-tar' 'tcl' 'application/x-tcl' 'tex' 'application/x-tex' 'texi' 'application/x-texinfo' 'texinfo' 'application/x-texinfo' 'tif' 'image/tiff' 'tiff' 'image/tiff' 'tr' 'application/x-troff' 'tsi' 'audio/TSP-audio' 'tsp' 'application/dsptype' 'tsv' 'text/tab-separated-values' 'txt' 'text/plain' 'unv' 'application/i-deas' 'ustar' 'application/x-ustar' 'vcd' 'application/x-cdlink' 'vda' 'application/vda' 'viv' 'video/vnd.vivo' 'vivo' 'video/vnd.vivo' 'vrml' 'model/vrml' 'wav' 'audio/x-wav' 'wrl' 'model/vrml' 'xbm' 'image/x-xbitmap' 'xlc' 'application/vnd.ms-excel' 'xll' 'application/vnd.ms-excel' 'xlm' 'application/vnd.ms-excel' 'xls' 'application/vnd.ms-excel' 'xlw' 'application/vnd.ms-excel' 'xml' 'text/xml' 'xpm' 'image/x-xpixmap' 'xwd' 'image/x-xwindowdump' 'xyz' 'chemical/x-pdb' 'zip' 'application/zip') ] MAFileModel class >> initialize [ MimeTypes := Dictionary new. 1 to: self defaultMimeTypes size by: 2 do: [:index | MimeTypes at: (self defaultMimeTypes at: index) put: (self defaultMimeTypes at: index + 1)] ] MAFileModel class >> mimetypeFor: aString [ ^self mimetypes at: aString ifAbsent: [self defaultMimeType] ] MAFileModel class >> mimetypes [ ^MimeTypes ] MAFileModel class >> new [ ^self basicNew initialize ] = anObject [ ^self species = anObject species and: [self filename = anObject filename and: [self mimetype = anObject mimetype]] ] contents [ "Answer the contents of the file. This method is supposed to be overridden by concrete subclasses." self subclassResponsibility ] contents: aByteArray [ "Set the contents of the receiver. This method is supposed to be overridden by concrete subclasses." filesize := aByteArray size ] extension [ "Answer the file-extension." ^self filename copyAfterLast: $. ] filename [ "Answer the filename of the receiver." ^filename ] filename: aString [ filename := aString ] filesize [ "Answer the size of the file." ^filesize ] finalize [ "Cleanup after a file is removed, subclasses might require to specialize this method." self initialize ] hash [ ^self filename hash bitXor: self mimetype hash ] initialize [ filesize := 0. filename := 'unknown'. mimetype := self class defaultMimeType ] isApplication [ "Return ==true== if the mimetype of the receiver is application-data. This message will match types like: application/postscript, application/zip, application/pdf, etc." ^self maintype = 'application' ] isAudio [ "Return ==true== if the mimetype of the receiver is audio-data. This message will match types like: audio/basic, audio/tone, audio/mpeg, etc." ^self maintype = 'audio' ] isEmpty [ ^self filesize = 0 ] isImage [ "Return ==true== if the mimetype of the receiver is image-data. This message will match types like: image/jpeg, image/gif, image/png, image/tiff, etc." ^self maintype = 'image' ] isText [ "Return ==true== if the mimetype of the receiver is text-data. This message will match types like: text/plain, text/html, text/sgml, text/css, text/xml, text/richtext, etc." ^self maintype = 'text' ] isVideo [ "Return ==true== if the mimetype of the receiver is video-data. This message will match types like: video/mpeg, video/quicktime, etc." ^self maintype = 'video' ] maintype [ "Answer the first part of the mime-type." ^self mimetype copyUpTo: $/ ] mimetype [ "Answer the mimetype of the receiver." ^mimetype ] mimetype: aString [ mimetype := aString ] subtype [ "Answer the second part of the mime-type." ^self mimetype copyAfter: $/ ] ] MAFileModel subclass: MAExternalFileModel [ | location | MAExternalFileModel class [ | baseDirectory baseUrl | ] MAExternalFileModel class >> baseDirectory [ ^baseDirectory ifNil: [Directory working / 'files'] ] MAExternalFileModel class >> baseDirectory: aStringOrDirectory [ "Defines the base-directory where the files are stored. If this value is set to nil, it default to a subdirectory of of the current image-location." baseDirectory := aStringOrDirectory isString ifTrue: [aStringOrDirectory asFile] ifFalse: [aStringOrDirectory] ] MAExternalFileModel class >> baseUrl [ ^baseUrl ] MAExternalFileModel class >> baseUrl: aString [ "Defines the base-URL where the files are served from, when using an external web server. This setting is left to nil by default, causing the files to be served trough the image." baseUrl := aString isNil ifFalse: [aString last = $/ ifFalse: [aString] ifTrue: [aString copyUpToLast: $/]] ] MAExternalFileModel class >> initialize [ baseDirectory := baseUrl := nil ] baseDirectory [ ^self class baseDirectory ] baseUrl [ ^self class baseUrl ] contents [ | stream | ^(self directory exists and: [self directory includes: self filename]) ifFalse: [ByteArray new] ifTrue: [stream := self readStream. [stream contents asByteArray] ensure: [stream close]] ] contents: aByteArray [ | stream | stream := self writeStream. [stream nextPutAll: aByteArray asByteArray] ensure: [stream close]. super contents: aByteArray ] directory [ ^self location inject: self baseDirectory into: [:result :each | result / each] ] finalize [ | directory | directory := self directory. directory exists ifTrue: [directory all remove]. "[(directory := directory parent) entries isEmpty] whileTrue: [directory all remove]." super finalize. location := nil ] location [ ^location ifNil: [location := self uniqueLocation: self locationDefinition] ] locationDefinition [ ^#(#(2 '63450af8d9c2e17b') #(30 'iaojv41bw67e0tud5m9rgplqfy8x3cs2kznh')) ] postCopy [ | previous | super postCopy. previous := self contents. location := nil. self contents: previous ] readStream [ ^(self directory / self filename) readStream ] uniqueLocation: aLocationDefinition [ "Finds an unique path to be used and create the necessary sub directories." | valid result directory definition | valid := false. result := Array new: aLocationDefinition size. [valid] whileFalse: [directory := self baseDirectory createDirectories. result keysAndValuesDo: [:index :value | definition := aLocationDefinition at: index. result at: index put: ((String new: definition first) collect: [:each | definition second atRandom]). directory := directory / (result at: index). directory exists ifFalse: [directory createDirectories. valid := true]]]. ^result ] writeStream [ ^(self directory / self filename) writeStream ] ] MAFileModel subclass: MAMemoryFileModel [ | contents | contents [ ^contents ifNil: [contents := ByteArray new] ] contents: aByteArray [ super contents: aByteArray. contents := aByteArray asByteArray ] finalize [ super finalize. contents := nil ] ] Object subclass: MAObject [ | properties | MAObject class >> initialize [ MACompatibility openWorkspace: self license titled: 'Magritte License' ] MAObject class >> isAbstract [ ^true ] MAObject class >> license [ "Return a string with the license of the package. This string shall not be removed or altered in any case." ^'The MIT License Copyright (c) 2003-' , Date today year asString , ' Lukas Renggli, renggli at gmail.com Copyright (c) 2003-' , Date today year asString , ' Software Composition Group, University of Bern, Switzerland Permission is hereby granted, free of charge, to any person obtaining a copy of this software and associated documentation files (the "Software"), to deal in the Software without restriction, including without limitation the rights to use, copy, modify, merge, publish, distribute, sublicense, and/or sell copies of the Software, and to permit persons to whom the Software is furnished to do so, subject to the following conditions: The above copyright notice and this permission notice shall be included in all copies or substantial portions of the Software. THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE.' ] MAObject class >> new [ "Create a new instance of the receiving class and checks if it is concrete." self isAbstract ifTrue: [self error: self name , ' is abstract.']. ^self basicNew initialize ] MAObject class >> withAllConcreteClasses [ ^Array streamContents: [:stream | self withAllConcreteClassesDo: [:each | stream nextPut: each]] ] MAObject class >> withAllConcreteClassesDo: aBlock [ self withAllSubclassesDo: [:each | each isAbstract ifFalse: [aBlock value: each]] ] = anObject [ "Answer whether the receiver and the argument represent the same object. This default implementation checks if the species of the compared objects are the same, so that superclasses might call super before performing their own check. Also redefine the message ==#hash== when redefining this message." ^self species = anObject species ] acceptMagritte: aVisitor [ ] errorPropertyNotFound: aSelector [ MAPropertyError signal: 'Property ' , aSelector , ' not found.' ] hasProperty: aKey [ "Test if the property ==aKey== is defined within the receiver." ^self properties includesKey: aKey ] hash [ "Answer a SmallInteger whose value is related to the receiver's identity. Also redefine the message ==#= == when redefining this message." ^self species hash ] initialize [ ] postCopy [ "This method is called whenever a shallow copy of the receiver is made. Redefine this method in subclasses to copy other fields as necessary. Never forget to call super, else class invariants might be violated." super postCopy. properties := properties copy ] properties [ "Answer the property dictionary of the receiver." ^properties ifNil: [properties := Dictionary new] ] propertyAt: aKey [ "Answer the value of the property ==aKey==, raises an error if the property doesn't exist." ^self propertyAt: aKey ifAbsent: [self errorPropertyNotFound: aKey] ] propertyAt: aKey ifAbsent: aBlock [ "Answer the value of the property ==aKey==, or the result of ==aBlock== if the property doesn't exist." ^self properties at: aKey ifAbsent: aBlock ] propertyAt: aKey ifAbsentPut: aBlock [ "Answer the value of the property ==aKey==, or if the property doesn't exist adds and answers the result of evaluating ==aBlock==." ^self properties at: aKey ifAbsentPut: aBlock ] propertyAt: aKey ifPresent: aBlock [ "Lookup the property ==aKey==, if it is present, answer the value of evaluating ==aBlock== block with the value. Otherwise, answer ==nil==." ^self properties at: aKey ifPresent: aBlock ] propertyAt: aKey put: aValue [ "Adds or replaces the property ==aKey== with ==aValue==." ^self properties at: aKey put: aValue ] ] MAObject subclass: MAAccessor [ asAccessor [ ^self ] canRead: aModel [ "Test if ==aModel== can be read." ^false ] canWrite: aModel [ "Test if ==aModel== can be written." ^false ] printOn: aStream [ self storeOn: aStream ] read: aModel [ "Read from ==aModel== using the access-strategy of the receiver." ^nil ] storeOn: aStream [ aStream store: self class; nextPutAll: ' new' ] write: anObject to: aModel [ "Write ==anObject== to ==aModel== using the access-strategy of the receiver." ] ] MAAccessor subclass: MADelegatorAccessor [ | next | MADelegatorAccessor class >> isAbstract [ ^false ] MADelegatorAccessor class >> on: anAccessor [ ^self new next: anAccessor ] = anObject [ ^super = anObject and: [self next = anObject next] ] canRead: aModel [ ^self next canRead: aModel ] canWrite: aModel [ ^self next canWrite: aModel ] hash [ ^super hash bitXor: self next hash ] next [ ^next ] next: anAccessor [ next := anAccessor asAccessor ] postCopy [ super postCopy. next := next copy ] read: aModel [ ^self next read: aModel ] storeOn: aStream [ aStream nextPut: $(; store: self class; nextPutAll: ' on: '; store: self next; nextPut: $) ] write: anObject to: aModel [ self next write: anObject to: aModel ] ] MADelegatorAccessor subclass: MAChainAccessor [ | accessor | MAChainAccessor class >> accessor: anAccessor next: aNextAccessor [ self deprecated: 'Obsolete, use #on:accessor: instead.'. ^self on: anAccessor accessor: aNextAccessor ] MAChainAccessor class >> accessors: aSequenceableCollection [ aSequenceableCollection isEmpty ifTrue: [self error: 'Unable to create accessor sequence from empty collection.']. aSequenceableCollection size = 1 ifTrue: [^aSequenceableCollection first asAccessor]. ^self on: aSequenceableCollection first asAccessor accessor: (self accessors: aSequenceableCollection allButFirst) ] MAChainAccessor class >> on: anAccessor accessor: anotherAccessor [ ^(self on: anAccessor) accessor: anotherAccessor ] MAChainAccessor class >> selectors: aSequenceableCollection [ self deprecated: 'Obsolete, use #accessors: instead.'. ^self accessors: aSequenceableCollection ] = anObject [ ^super = anObject and: [self accessor = anObject accessor] ] accessor [ ^accessor ] accessor: anAccessor [ accessor := anAccessor ] canRead: aModel [ ^(super canRead: aModel) and: [self accessor canRead: (self next read: aModel)] ] canWrite: aModel [ ^(super canRead: aModel) and: [self accessor canWrite: (self next read: aModel)] ] hash [ ^super hash bitXor: self accessor hash ] postCopy [ super postCopy. accessor := accessor copy ] read: aModel [ ^self accessor read: (super read: aModel) ] storeOn: aStream [ aStream nextPut: $(; store: self class; nextPutAll: ' on: '; store: self next; nextPutAll: ' accessor: '; store: self accessor; nextPut: $) ] write: anObject to: aModel [ self accessor write: anObject to: (super read: aModel) ] ] MAAccessor subclass: MADictionaryAccessor [ | key | MADictionaryAccessor class >> isAbstract [ ^false ] MADictionaryAccessor class >> key: aSymbol [ ^(self new) key: aSymbol; yourself ] = anObject [ ^super = anObject and: [self key = anObject key] ] canRead: aModel [ ^true ] canWrite: aModel [ ^true ] hash [ ^super hash bitXor: self key hash ] key [ ^key ] key: aKey [ key := aKey ] read: aModel [ ^aModel at: self key ifAbsent: [nil] ] storeOn: aStream [ aStream nextPut: $(; store: self class; nextPutAll: ' key: '; store: self key; nextPut: $) ] write: anObject to: aModel [ aModel at: self key put: anObject ] ] MAAccessor subclass: MAIdentityAccessor [ MAIdentityAccessor class >> isAbstract [ ^false ] canRead: aModel [ ^true ] read: aModel [ ^aModel ] write: anObject to: aModel [ MAWriteError signal: 'Not supposed to write to ' , aModel asString , '.' ] ] MAAccessor subclass: MANullAccessor [ | uuid | MANullAccessor class >> isAbstract [ ^false ] MANullAccessor class >> new [ ^self uuid: MACompatibility uuid ] MANullAccessor class >> uuid: anUUID [ ^(self basicNew) uuid: anUUID; yourself ] = anObject [ ^super = anObject and: [self uuid = anObject uuid] ] hash [ ^super hash bitXor: self uuid hash ] read: aModel [ MAReadError signal: 'This message is not appropriate for this object' ] storeOn: aStream [ aStream nextPut: $(; store: self class; nextPutAll: ' uuid: '; store: self uuid; nextPut: $) ] uuid [ ^uuid ] uuid: anObject [ uuid := anObject ] write: anObject to: aModel [ MAWriteError signal: 'This message is not appropriate for this object' ] ] MAAccessor subclass: MAPluggableAccessor [ | readBlock writeBlock | MAPluggableAccessor class >> isAbstract [ ^false ] MAPluggableAccessor class >> read: aReadBlock write: aWriteBlock [ ^(self new) readBlock: aReadBlock; writeBlock: aWriteBlock; yourself ] = anObject [ ^super = anObject and: [self readBlock = anObject readBlock and: [self writeBlock = anObject writeBlock]] ] canRead: aModel [ ^self readBlock notNil ] canWrite: aModel [ ^self writeBlock notNil ] hash [ ^super hash bitXor: (self readBlock hash bitXor: self writeBlock hash) ] read: aModel [ ^self readBlock value: aModel ] readBlock [ ^readBlock ] readBlock: aBlock [ readBlock := aBlock ] storeBlock: aBlock on: aStream [ aStream nextPutAll: aBlock decompile asString allButFirst allButLast ] storeOn: aStream [ aStream nextPut: $(; store: self class; nextPutAll: ' read: '. self storeBlock: self readBlock on: aStream. aStream nextPutAll: ' write: '. self storeBlock: self writeBlock on: aStream. aStream nextPut: $) ] write: anObject to: aModel [ self writeBlock value: aModel value: anObject ] writeBlock [ ^writeBlock ] writeBlock: aBlock [ writeBlock := aBlock ] ] MAAccessor subclass: MASelectorAccessor [ | readSelector writeSelector | MASelectorAccessor class >> isAbstract [ ^false ] MASelectorAccessor class >> read: aSelector [ ^self read: aSelector write: nil ] MASelectorAccessor class >> read: aReadSelector write: aWriteSelector [ ^(self new) readSelector: aReadSelector; writeSelector: aWriteSelector; yourself ] MASelectorAccessor class >> selector: aSelector [ ^(self new) selector: aSelector; yourself ] MASelectorAccessor class >> write: aSelector [ ^self read: nil write: aSelector ] = anObject [ ^super = anObject and: [self readSelector = anObject readSelector and: [self writeSelector = anObject writeSelector]] ] canRead: aModel [ ^self readSelector notNil and: [aModel respondsTo: self readSelector] ] canWrite: aModel [ ^self writeSelector notNil and: [aModel respondsTo: self writeSelector] ] hash [ ^super hash bitXor: (self readSelector hash bitXor: self writeSelector hash) ] read: aModel [ ^aModel perform: self readSelector ] readSelector [ ^readSelector ] readSelector: aSelector [ readSelector := aSelector ] selector [ ^self readSelector ] selector: aSelector [ self readSelector: aSelector asSymbol. self writeSelector: (aSelector asString copyWith: $:) asSymbol ] storeOn: aStream [ aStream nextPut: $(; store: self class; nextPutAll: ' read: '; store: self readSelector; nextPutAll: ' write: '; store: self writeSelector; nextPut: $) ] write: anObject to: aModel [ aModel perform: self writeSelector with: anObject ] writeSelector [ ^writeSelector ] writeSelector: aSelector [ writeSelector := aSelector ] ] MASelectorAccessor subclass: MAAutoSelectorAccessor [ categoryName [ ^#'accessing-generated' ] createReadAccessor: aClass [ (aClass selectors includes: self readSelector) ifTrue: [^self]. aClass compile: (String streamContents: [:stream | stream nextPutAll: self readSelector, ' ['; cr. stream tab; nextPutAll: '^ '; nextPutAll: self readSelector, ' ]']) classified: self categoryName ] createVariable: aClass [ (aClass allInstVarNames includes: self readSelector) ifTrue: [^self]. aClass addInstVarName: self readSelector ] createWriteAccessor: aClass [ (aClass selectors includes: self writeSelector) ifTrue: [^self]. aClass compile: (String streamContents: [:stream | stream nextPutAll: self writeSelector; space; nextPutAll: 'anObject ['; cr. stream tab; nextPutAll: self readSelector; nextPutAll: ' := anObject ]']) classified: self categoryName ] read: aModel [ (self canRead: aModel) ifFalse: [self createVariable: aModel class. self createReadAccessor: aModel class]. ^super read: aModel ] write: anObject to: aModel [ (self canWrite: aModel) ifFalse: [self createVariable: aModel class. self createWriteAccessor: aModel class]. super write: anObject to: aModel ] ] MAAccessor subclass: MAVariableAccessor [ | name | MAVariableAccessor class >> isAbstract [ ^false ] MAVariableAccessor class >> name: aString [ ^(self new) name: aString asSymbol; yourself ] = anObject [ ^super = anObject and: [self name = anObject name] ] canRead: aModel [ ^aModel class allInstVarNames includes: self name ] canWrite: aModel [ ^self canRead: aModel ] hash [ ^super hash bitXor: self name hash ] name [ ^name ] name: aString [ name := aString ] read: aModel [ ^aModel instVarNamed: self name ] storeOn: aStream [ aStream nextPut: $(; store: self class; nextPutAll: ' name: '; store: self name; nextPut: $) ] write: anObject to: aModel [ aModel instVarNamed: self name put: anObject ] ] ValueHolder subclass: MADescriptionHolder [ MADescriptionHolder class >> descriptionClasses [ ^(OrderedCollection new) add: MAStringDescription; add: MAMemoDescription; add: MASymbolDescription; add: MAPasswordDescription; add: MABooleanDescription; add: MASingleOptionDescription; add: MAMultipleOptionDescription; add: MAToOneRelationDescription; add: MAToManyRelationDescription; add: MANumberDescription; add: MADurationDescription; add: MADateDescription; add: MATimeDescription; add: MATimeStampDescription; add: MATokenDescription; add: MAFileDescription; add: MAClassDescription; add: MATableDescription; yourself ] MADescriptionHolder class >> descriptionValue [ ^(MASingleOptionDescription new) options: self descriptionClasses; reference: MAClassDescription new; groupBy: #grouping; selectorAccessor: 'contents'; label: 'Type'; priority: 20; yourself ] MADescriptionHolder class >> groupChoice [ ^(Set new) add: MABooleanDescription; add: MASingleOptionDescription; add: MAMultipleOptionDescription; add: MAToOneRelationDescription; add: MAToManyRelationDescription; yourself ] MADescriptionHolder class >> groupMagnitude [ ^(Set new) add: MANumberDescription; add: MADurationDescription; add: MADateDescription; add: MATimeDescription; add: MATimeStampDescription; yourself ] MADescriptionHolder class >> groupMisc [ ^(Set new) add: MAFileDescription; add: MAClassDescription; add: MATableDescription; yourself ] MADescriptionHolder class >> groupOf: aClass [ (self groupText includes: aClass) ifTrue: [^'Text']. (self groupChoice includes: aClass) ifTrue: [^'Choice']. (self groupMagnitude includes: aClass) ifTrue: [^'Magnitude']. (self groupPick includes: aClass) ifTrue: [^'Pick']. (self groupMisc includes: aClass) ifTrue: [^'Miscellaneous']. ^'Other' ] MADescriptionHolder class >> groupPick [ ^(Set new) add: MATokenDescription; yourself ] MADescriptionHolder class >> groupText [ ^(Set new) add: MAStringDescription; add: MAMemoDescription; add: MASymbolDescription; add: MAPasswordDescription; yourself ] initialize [ self contents: self class descriptionClasses first ] ] MAObject subclass: MADescription [ | accessor | >descriptionTitle = ^ MAStringDescription new = autoAccessor: #title; = label: ''Title''; = priority: 20; = beRequired; = yourself. The selector ==#title== is the name of the accessor method used by Magritte to retrieve the value from the model. In the above case Magritte creates the accessor method and the instance variable automatically, if necessary. The label is used to give the field a name and will be printed next to the input box if a visual GUI is created from this description. The write-accessor is automatically deduced by adding a colon to the read-selector, in this example ==#title:==. You can specify your own accessor strategy using one of the subclasses of ==*MAAccessor*==. If you have multiple description within the same object, the ==#priority:# field is used to order them. Assign a low priority to have descriptions traversed first.'> MADescription class >> accessor: anAccessor [ self deprecated: 'Obsolete, use instance side configuration methods.'. ^self new accessor: anAccessor ] MADescription class >> accessor: anAccessor label: aString [ self deprecated: 'Obsolete, use instance side configuration methods.'. ^self accessor: anAccessor label: aString priority: self defaultPriority ] MADescription class >> accessor: anAccessor label: aString priority: aNumber [ self deprecated: 'Obsolete, use instance side configuration methods.'. ^self accessor: anAccessor label: aString priority: aNumber default: self defaultDefault ] MADescription class >> accessor: anAccessor label: aString priority: aNumber default: anObject [ self deprecated: 'Obsolete, use instance side configuration methods.'. ^(self new) accessor: anAccessor; label: aString; priority: aNumber; default: anObject; yourself ] MADescription class >> auto: aSelector [ self deprecated: 'Obsolete, use instance side configuration methods.'. ^self accessor: (MAAutoSelectorAccessor selector: aSelector) ] MADescription class >> auto: aSelector label: aString [ self deprecated: 'Obsolete, use instance side configuration methods.'. ^self accessor: (MAAutoSelectorAccessor selector: aSelector) label: aString ] MADescription class >> auto: aSelector label: aString priority: aNumber [ self deprecated: 'Obsolete, use instance side configuration methods.'. ^self accessor: (MAAutoSelectorAccessor selector: aSelector) label: aString priority: aNumber ] MADescription class >> auto: aSelector label: aString priority: aNumber default: anObject [ self deprecated: 'Obsolete, use instance side configuration methods.'. ^self accessor: (MAAutoSelectorAccessor selector: aSelector) label: aString priority: aNumber default: anObject ] MADescription class >> grouping [ ^MADescriptionHolder groupOf: self ] MADescription class >> defaultAccessor [ ^MANullAccessor new ] MADescription class >> defaultComment [ ^nil ] MADescription class >> defaultConditions [ ^Array new ] MADescription class >> defaultDefault [ ^nil ] MADescription class >> defaultGroup [ ^nil ] MADescription class >> defaultLabel [ ^String new ] MADescription class >> defaultPersistent [ ^true ] MADescription class >> defaultPriority [ ^0 ] MADescription class >> defaultReadonly [ ^false ] MADescription class >> defaultRequired [ ^false ] MADescription class >> defaultStringReader [ ^MAStringReader ] MADescription class >> defaultStringWriter [ ^MAStringWriter ] MADescription class >> defaultUndefined [ ^String new ] MADescription class >> defaultValidator [ ^MAValidatorVisitor ] MADescription class >> defaultVisible [ ^true ] MADescription class >> descriptionComment [ ^(MAMemoDescription new) accessor: #comment; label: 'Comment'; priority: 110; default: self defaultComment; yourself ] MADescription class >> descriptionDefault [ ^self isAbstract ifFalse: [(self new) accessor: #default; label: 'Default'; priority: 130; default: self defaultDefault; yourself] ] MADescription class >> descriptionGroup [ ^(MAStringDescription new) accessor: #group; default: self defaultGroup; label: 'Group'; priority: 105; yourself ] MADescription class >> descriptionLabel [ ^(MAStringDescription new) accessor: #label; label: 'Label'; priority: 100; default: self defaultLabel; yourself ] MADescription class >> descriptionName [ ^(MAStringDescription new) accessor: #name; label: 'Kind'; priority: 0; beReadonly; yourself ] MADescription class >> descriptionPriority [ ^(MANumberDescription new) accessor: #priority; label: 'Priority'; priority: 130; default: self defaultPriority; beRequired; yourself ] MADescription class >> descriptionReadonly [ ^(MABooleanDescription new) accessor: #readonly; label: 'Readonly'; priority: 200; default: self defaultReadonly; yourself ] MADescription class >> descriptionRequired [ ^(MABooleanDescription new) accessor: #required; label: 'Required'; priority: 220; default: self defaultRequired; yourself ] MADescription class >> descriptionStringReader [ ^(MASingleOptionDescription new) accessor: #stringReader; label: 'String Reader'; priority: 300; default: self defaultStringReader; options: [self defaultStringReader withAllSubclasses] asDynamicObject; reference: MAClassDescription new; yourself ] MADescription class >> descriptionStringWriter [ ^(MASingleOptionDescription new) accessor: #stringWriter; label: 'String Writer'; priority: 310; default: self defaultStringWriter; options: [self defaultStringWriter withAllSubclasses] asDynamicObject; reference: MAClassDescription new; yourself ] MADescription class >> descriptionUndefined [ ^(MAStringDescription new) accessor: #undefined; label: 'Undefined String'; priority: 140; default: self defaultUndefined; yourself ] MADescription class >> descriptionValidator [ ^(MASingleOptionDescription new) accessor: #validator; label: 'Validator'; priority: 250; default: self defaultValidator; options: [self defaultValidator withAllSubclasses] asDynamicObject; reference: MAClassDescription new; yourself ] MADescription class >> descriptionVisible [ ^(MABooleanDescription new) accessor: #visible; label: 'Visible'; priority: 210; default: self defaultVisible; yourself ] MADescription class >> null [ self deprecated: 'Obsolete, use instance side configuration methods.'. ^self accessor: (MANullAccessor uuid: MACompatibility uuid) ] MADescription class >> null: anUuid [ self deprecated: 'Obsolete, use instance side configuration methods.'. ^self accessor: (MANullAccessor uuid: anUuid) ] MADescription class >> null: anUuid label: aString [ self deprecated: 'Obsolete, use instance side configuration methods.'. ^self accessor: (MANullAccessor uuid: anUuid) label: aString ] MADescription class >> null: anUuid label: aString priority: aNumber [ self deprecated: 'Obsolete, use instance side configuration methods.'. ^self accessor: (MANullAccessor uuid: anUuid) label: aString priority: aNumber ] MADescription class >> null: anUuid label: aString priority: aNumber default: anObject [ self deprecated: 'Obsolete, use instance side configuration methods.'. ^self accessor: (MANullAccessor uuid: anUuid) label: aString priority: aNumber default: anObject ] MADescription class >> read: aReadBlock write: aWriteBlock [ self deprecated: 'Obsolete, use instance side configuration methods.'. ^self accessor: (MAPluggableAccessor read: aReadBlock write: aWriteBlock) ] MADescription class >> read: aReadBlock write: aWriteBlock label: aString [ self deprecated: 'Obsolete, use instance side configuration methods.'. ^self accessor: (MAPluggableAccessor read: aReadBlock write: aWriteBlock) label: aString ] MADescription class >> read: aReadBlock write: aWriteBlock label: aString priority: aNumber [ self deprecated: 'Obsolete, use instance side configuration methods.'. ^self accessor: (MAPluggableAccessor read: aReadBlock write: aWriteBlock) label: aString priority: aNumber ] MADescription class >> read: aReadBlock write: aWriteBlock label: aString priority: aNumber default: anObject [ self deprecated: 'Obsolete, use instance side configuration methods.'. ^self accessor: (MAPluggableAccessor read: aReadBlock write: aWriteBlock) label: aString priority: aNumber default: anObject ] MADescription class >> selector: aSelector [ self deprecated: 'Obsolete, use instance side configuration methods.'. ^self accessor: (MASelectorAccessor selector: aSelector) ] MADescription class >> selector: aSelector label: aString [ self deprecated: 'Obsolete, use instance side configuration methods.'. ^self accessor: (MASelectorAccessor selector: aSelector) label: aString ] MADescription class >> selector: aSelector label: aString priority: aNumber [ self deprecated: 'Obsolete, use instance side configuration methods.'. ^self accessor: (MASelectorAccessor selector: aSelector) label: aString priority: aNumber ] MADescription class >> selector: aSelector label: aString priority: aNumber default: anObject [ self deprecated: 'Obsolete, use instance side configuration methods.'. ^self accessor: (MASelectorAccessor selector: aSelector) label: aString priority: aNumber default: anObject ] MADescription class >> selectors: anArray [ self deprecated: 'Obsolete, use instance side configuration methods.'. ^self accessor: (MAChainAccessor selectors: anArray) ] MADescription class >> selectors: anArray label: aString [ self deprecated: 'Obsolete, use instance side configuration methods.'. ^self accessor: (MAChainAccessor selectors: anArray) label: aString ] MADescription class >> selectors: anArray label: aString priority: aNumber [ self deprecated: 'Obsolete, use instance side configuration methods.'. ^self accessor: (MAChainAccessor selectors: anArray) label: aString priority: aNumber ] MADescription class >> selectors: anArray label: aString priority: aNumber default: anObject [ self deprecated: 'Obsolete, use instance side configuration methods.'. ^self accessor: (MAChainAccessor selectors: anArray) label: aString priority: aNumber default: anObject ] , aDescription [ "Concatenate the receiver and ==aDescription== to one composed description. Answer a description container containing both descriptions." ^(self asContainer copy) addAll: aDescription asContainer; yourself ] <= anObject [ "Answer whether the receiver should precede ==anObject== in a priority container." ^self priority <= anObject priority ] = anObject [ ^super = anObject and: [self accessor = anObject accessor] ] acceptMagritte: aVisitor [ aVisitor visitDescription: self ] accessor [ "Answer the access-strategy of the model-value described by the receiver." ^accessor ifNil: [accessor := self class defaultAccessor] ] accessor: anObject [ accessor := anObject asAccessor ] addCondition: aCondition [ self addCondition: aCondition labelled: aCondition asString ] addCondition: aCondition labelled: aString [ "Add ==aCondition== as an additional validation condition to the receiver and give it the label ==aString==. The first argument is either a block-context, a composite of the subclasses of ==*MACondition*==, or any other object that responds to ==#value:== with ==true== or ==false==." self conditions: (self conditions copyWith: (Association key: aCondition value: aString)) ] asContainer [ "Answer a description container of the receiver." self subclassResponsibility ] autoAccessor: aSelector [ "Uses ==aSelector== to read from the model. Creates read and write accessors and instance-variables if necessary. This is very conveniant for prototyping and can later be changed to a ==*selectorAccessor:*== using a simple rewrite rule." self accessor: (MAAutoSelectorAccessor selector: aSelector) ] beHidden [ self visible: false ] beOptional [ self required: false ] beReadonly [ self readonly: true ] beRequired [ self required: true ] beVisible [ self visible: true ] beWriteable [ self readonly: false ] chainAccessor: anArray [ "Uses ==anArray== of selectors to read from the model." self accessor: (MAChainAccessor accessors: anArray) ] comment [ "Answer a comment or help-text giving a hint what this description is used for. GUIs that are built from this description might display it as a tool-tip." ^self propertyAt: #comment ifAbsent: [self class defaultComment] ] comment: aString [ self propertyAt: #comment put: aString ] conditions [ "Answer a collection of additional conditions that need to be fulfilled so that the described model is valid. Internally the collection associates conditions, that are either blocks or subclasses of *MACondition*, with an error string." ^self propertyAt: #conditions ifAbsent: [self class defaultConditions] ] conditions: anArray [ self propertyAt: #conditions put: anArray ] conflictErrorMessage [ ^self propertyAt: #conflictErrorMessage ifAbsent: ['Input is conflicting with concurrent modification'] ] conflictErrorMessage: aString [ ^self propertyAt: #conflictErrorMessage put: aString ] default [ ^nil ] default: anObject [ ] fromString: aString [ "Answer an object being parsed from ==aString==." ^self fromString: aString reader: self stringReader ] fromString: aString reader: aParser [ "Answer an object being parsed from ==aString== using ==aParser==." ^aParser read: aString readStream description: self ] fromStringCollection: aCollection [ "Answer a collection of objects being parsed from ==aCollection== of strings." ^self fromStringCollection: aCollection reader: self stringReader ] fromStringCollection: aCollection reader: aParser [ "Answer a collection of objects being parsed from ==aCollection== of strings using ==aParser==." ^aCollection collect: [:each | self fromString: each reader: aParser] ] group [ "Answer the group of the receiving description. The group is a string used to categorize and group descriptions. Certain display interpreters with be able to use this information to improve the useability." ^self propertyAt: #group ifAbsent: [self class defaultGroup] ] group: aString [ "Answer the group of the receiving description. The group is a string used to categorize and group descriptions. Certain display interpreters with be able to use this information to improve the useability." ^self propertyAt: #group put: aString ] hasChildren [ "Answer ==true== if the receiver has any child-descriptions. A description container usually has children." ^false ] hasComment [ "Answer ==true== if the the receiver has got a non empty comment." ^self comment isEmptyOrNil not ] hasLabel [ "Answer ==true== if the the receiver has got a non empty label." ^self label isEmptyOrNil not ] hash [ ^super hash bitXor: self accessor hash ] isContainer [ "Answer ==true== if the receiver is a description container." ^false ] isDescription [ "Answer ==true== if the receiver is a description." ^true ] isGrouped [ ^false ] isReadonly [ ^self readonly ] isRequired [ ^self required ] isSatisfiedBy: anObject [ "Answer ==true== if ==anObject== is a valid instance of the receiver's description." [self validate: anObject] on: MAValidationError do: [:err | ^false]. ^true ] isSortable [ "Answer ==true== if the described object can be trivially sorted, e.g. it answers to #<=." ^false ] isVisible [ ^self visible ] kind [ "Answer the base-class (type) the receiver is describing. The default implementation answers the most generic class: Object, the root of the Smalltalk class hierarchy. Subclasses might refine this choice." ^Object ] kindErrorMessage [ ^self propertyAt: #kindErrorMessage ifAbsent: ['Invalid input given'] ] kindErrorMessage: aString [ ^self propertyAt: #kindErrorMessage put: aString ] label [ "Answer the label of the receiving description. The label is mostly used as an identifier that is printed next to the input field when building a GUI from the receiver." ^self propertyAt: #label ifAbsent: [self class defaultLabel] ] label: aString [ self propertyAt: #label put: aString ] multipleErrorsMessage [ ^self propertyAt: #multipleErrorsMessage ifAbsent: ['Multiple errors'] ] multipleErrorsMessage: aString [ ^self propertyAt: #multipleErrorsMessage put: aString ] name [ "Answer the name of the description, a human-readable string describing the type." ^self class label ] postCopy [ super postCopy. accessor := accessor copy ] printOn: aStream [ super printOn: aStream. aStream nextPutAll: ' label: '; print: self label. aStream nextPutAll: ' comment: '; print: self comment ] priority [ "Answer a number that is the priority of the receiving description. Priorities are used to give descriptions an explicit order by sorting them according to this number." ^self propertyAt: #priority ifAbsent: [self class defaultPriority] ] priority: aNumber [ self propertyAt: #priority put: aNumber ] propertyAccessor: aSelector [ "Uses ==aSelector== to read from the property dictionary of the model." self accessor: ((MAChainAccessor on: #properties) accessor: (MADictionaryAccessor key: aSelector)) ] readonly [ "Answer ==true== if the model described by the receiver is read-only." ^self propertyAt: #readonly ifAbsent: [self class defaultReadonly] ] readonly: aBoolean [ self propertyAt: #readonly put: aBoolean ] required [ "Answer ==true== if the model described by the receiver is required, this is it cannot be ==nil==." ^self propertyAt: #required ifAbsent: [self class defaultRequired] ] required: aBoolean [ self propertyAt: #required put: aBoolean ] requiredErrorMessage [ ^self propertyAt: #requiredErrorMessage ifAbsent: ['Input is required but no input given'] ] requiredErrorMessage: aString [ ^self propertyAt: #requiredErrorMessage put: aString ] selectorAccessor: aSelector [ "Uses ==aSelector== to read from the model." self accessor: (MASelectorAccessor selector: aSelector) ] stringReader [ "Answer a Visitor that can be used to parse the model described by the receiver from a string." ^self propertyAt: #stringReader ifAbsent: [self class defaultStringReader] ] stringReader: aClass [ self propertyAt: #stringReader put: aClass ] stringWriter [ "Answer a Visitor that can be used to convert the model described by the receiver to a string." ^self propertyAt: #stringWriter ifAbsent: [self class defaultStringWriter] ] stringWriter: aClass [ self propertyAt: #stringWriter put: aClass ] toString: anObject [ "Answer a string being formatted from ==anObject==." ^self toString: anObject writer: self stringWriter ] toString: anObject writer: aFormatter [ "Answer a string being formatted from ==anObject== using ==aFormatter==." ^aFormatter write: anObject description: self ] toStringCollection: aCollection [ "Answer a collection of strings being formatted from ==aCollection==." ^self toStringCollection: aCollection writer: self stringWriter ] toStringCollection: aCollection writer: aFormatter [ "Answer a collection of strings being formatted from ==aCollection== using ==aFormatter==." ^aCollection collect: [:each | self toString: each writer: aFormatter] ] undefined [ "Answer a string that is printed whenever the model described by the receiver is ==nil==." ^(self propertyAt: #undefined ifAbsent: [self class defaultUndefined]) ifNil: [self class defaultUndefined] ] undefined: aString [ self propertyAt: #undefined put: aString ] validate: anObject [ "Validate ==anObject== in the context of the describing-receiver, raises an error in case of a problem. If ==anObject== is ==nil== and not required, most tests will be skipped. Do not override this message, instead have a look at ==#validateSpecific:== what is usually a better place to define the behaviour your description requires." self validator on: anObject description: self ] validateConditions: anObject [ "Validate ==anObject== to satisfy all its custom conditions." self conditions do: [:each | (each key value: anObject) ifFalse: [MAConditionError description: self signal: each value]] ] validateKind: anObject [ "Validate ==anObject== to be of the right kind." (anObject isKindOf: self kind) ifFalse: [MAKindError description: self signal: self kindErrorMessage] ] validateRequired: anObject [ "Validate ==anObject== not to be ==nil== if it is required." (self isRequired and: [anObject isNil]) ifTrue: [MARequiredError description: self signal: self requiredErrorMessage] ] validateSpecific: anObject [ "Validate ==anObject== to satisfy its descriptions specific validation rules. Subclasses mostly want to override this method." ] validator [ "Answer a Visitor that can be used to validate the model described by the receiver." ^self propertyAt: #validator ifAbsent: [self class defaultValidator] ] validator: aClass [ self propertyAt: #validator put: aClass ] visible [ "Answer ==true== if the model described by the receiver is visible, as an opposite to hidden." ^self propertyAt: #visible ifAbsent: [self class defaultVisible] ] visible: aBoolean [ self propertyAt: #visible put: aBoolean ] ] MADescription subclass: MAContainer [ | children | MAContainer class >> defaultAccessor [ ^MAIdentityAccessor new ] MAContainer class >> defaultCollection [ ^OrderedCollection new ] MAContainer class >> descriptionChildren [ ^(MAToManyRelationDescription new) accessor: (MASelectorAccessor read: #children write: #setChildren:); classes: [MAElementDescription withAllConcreteClasses] asDynamicObject; default: self defaultCollection; label: 'Elements'; priority: 400; beOrdered; yourself ] MAContainer class >> descriptionDefault [ ^nil ] MAContainer class >> isAbstract [ ^false ] MAContainer class >> with: aDescription [ ^(self new) add: aDescription; yourself ] MAContainer class >> withAll: aCollection [ ^(self new) addAll: aCollection; yourself ] = anObject [ ^super = anObject and: [self children = anObject children] ] acceptMagritte: aVisitor [ aVisitor visitContainer: self ] add: aDescription [ self children add: aDescription ] addAll: aCollection [ self children addAll: aCollection ] allSatisfy: aBlock [ ^self children allSatisfy: aBlock ] anySatisfy: aBlock [ ^self children anySatisfy: aBlock ] asContainer [ ^self ] at: anIndex [ ^self children at: anIndex ] at: anIndex ifAbsent: aBlock [ ^self children at: anIndex ifAbsent: aBlock ] children [ ^children ] collect: aBlock [ ^(self copy) setChildren: (self children collect: aBlock); yourself ] copyEmpty [ ^(self copy) setChildren: self class defaultCollection; yourself ] copyFrom: aStartIndex to: anEndIndex [ ^(self copy) setChildren: (self children copyFrom: aStartIndex to: anEndIndex); yourself ] copyWithout: anObject [ ^self reject: [:each | each = anObject] ] copyWithoutAll: aCollection [ ^self reject: [:each | aCollection includes: each] ] detect: aBlock [ ^self children detect: aBlock ] detect: aBlock ifNone: anExceptionBlock [ ^self children detect: aBlock ifNone: anExceptionBlock ] do: aBlock [ self children do: aBlock ] do: aBlock separatedBy: aSeparatorBlock [ self children do: aBlock separatedBy: aSeparatorBlock ] errorNotFound: aDescription [ self error: aDescription class label , ' not found.' ] hasChildren [ ^self notEmpty ] hash [ ^super hash bitXor: self children hash ] includes: aDescription [ ^self children includes: aDescription ] initialize [ super initialize. self setChildren: self class defaultCollection ] inject: anObject into: aBlock [ ^self children inject: anObject into: aBlock ] intersection: aCollection [ ^(self copy) setChildren: (self children intersection: aCollection); yourself ] isContainer [ ^true ] isEmpty [ ^self children isEmpty ] keysAndValuesDo: aBlock [ self children keysAndValuesDo: aBlock ] moveDown: aDescription [ self children moveDown: aDescription ] moveUp: aDescription [ self children moveUp: aDescription ] noneSatisfy: aBlock [ ^self children noneSatisfy: aBlock ] notEmpty [ ^self children notEmpty ] postCopy [ super postCopy. self setChildren: self children copy ] reject: aBlock [ ^(self copy) setChildren: (self children reject: aBlock); yourself ] remove: aDescription [ self children remove: aDescription ifAbsent: [self errorNotFound: aDescription] ] removeAll [ self setChildren: self class defaultCollection ] select: aBlock [ ^(self copy) setChildren: (self children select: aBlock); yourself ] setChildren: aCollection [ children := aCollection ] size [ ^self children size ] union: aContainer [ ^(self copy) addAll: (aContainer reject: [:each | self includes: each]); yourself ] with: aCollection do: aBlock [ self children with: aCollection do: aBlock ] ] MAContainer subclass: MAPriorityContainer [ MAPriorityContainer class >> defaultCollection [ ^SortedCollection new ] acceptMagritte: aVisitor [ aVisitor visitPriorityContainer: self ] moveDown: aDescription [ self shouldNotImplement ] moveUp: aDescription [ self shouldNotImplement ] resort [ self setChildren: self children copy ] setChildren: aCollection [ super setChildren: aCollection asSortedCollection ] ] MADescription subclass: MAElementDescription [ acceptMagritte: aVisitor [ aVisitor visitElementDescription: self ] asContainer [ ^MAContainer with: self ] default [ ^self propertyAt: #default ifAbsent: [self class defaultDefault] ] default: anObject [ self propertyAt: #default put: anObject ] ] MAElementDescription subclass: MABooleanDescription [ MABooleanDescription class >> defaultFalseString [ ^self defaultFalseStrings first ] MABooleanDescription class >> defaultFalseStrings [ ^#('false' 'f' 'no' 'n' '0' 'off') ] MABooleanDescription class >> defaultTrueString [ ^self defaultTrueStrings first ] MABooleanDescription class >> defaultTrueStrings [ ^#('true' 't' 'yes' 'y' '1' 'on') ] MABooleanDescription class >> descriptionFalseString [ ^(MAStringDescription new) accessor: #falseString; default: self defaultFalseString; label: 'False String'; priority: 410; yourself ] MABooleanDescription class >> descriptionRequired [ ^nil ] MABooleanDescription class >> descriptionTrueString [ ^(MAStringDescription new) accessor: #trueString; default: self defaultTrueString; label: 'True String'; priority: 400; yourself ] MABooleanDescription class >> isAbstract [ ^false ] MABooleanDescription class >> label [ ^'Boolean' ] acceptMagritte: aVisitor [ aVisitor visitBooleanDescription: self ] allOptions [ ^self options ] allOptionsWith: anObject [ ^self options ] falseString [ ^self propertyAt: #falseString ifAbsent: [self class defaultFalseString] ] falseString: aString [ ^self propertyAt: #falseString put: aString ] falseStrings [ ^self class defaultFalseStrings ] isExtensible [ ^false ] kind [ ^Boolean ] labelForOption: anObject [ anObject == true ifTrue: [^self trueString]. anObject == false ifTrue: [^self falseString]. ^self undefined ] options [ ^Array with: false with: true ] reference [ ^self ] trueString [ ^self propertyAt: #trueString ifAbsent: [self class defaultTrueString] ] trueString: aString [ ^self propertyAt: #trueString put: aString ] trueStrings [ ^self class defaultTrueStrings ] ] MAElementDescription subclass: MAClassDescription [ MAClassDescription class >> isAbstract [ ^false ] MAClassDescription class >> label [ ^'Class' ] acceptMagritte: aVisitor [ aVisitor visitClassDescription: self ] kind [ ^Class ] ] MAElementDescription subclass: MAFileDescription [ MAFileDescription class >> isAbstract [ ^false ] MAFileDescription class >> label [ ^'File' ] acceptMagritte: aVisitor [ aVisitor visitFileDescription: self ] kind [ ^self propertyAt: #modelClass ifAbsent: [MAMemoryFileModel] ] kind: aClass [ "Set the file model class to be used." self propertyAt: #modelClass put: aClass ] ] MAElementDescription subclass: MAMagnitudeDescription [ MAMagnitudeDescription class >> defaultMax [ ^nil ] MAMagnitudeDescription class >> defaultMin [ ^nil ] MAMagnitudeDescription class >> descriptionMax [ ^(self new) accessor: #max; label: 'Maximum'; priority: 410; yourself ] MAMagnitudeDescription class >> descriptionMin [ ^(self new) accessor: #min; label: 'Min'; priority: 400; yourself ] acceptMagritte: aVisitor [ aVisitor visitMagnitudeDescription: self ] isSortable [ ^true ] isWithinRange: anObject [ ^(self min isNil or: [self min <= anObject]) and: [self max isNil or: [self max >= anObject]] ] max [ ^self propertyAt: #max ifAbsent: [self class defaultMax] ] max: aMagnitudeOrNil [ "Set the maximum for accepted values, or ==nil== if open." ^self propertyAt: #max put: aMagnitudeOrNil ] min [ ^self propertyAt: #min ifAbsent: [self class defaultMin] ] min: aMagnitudeOrNil [ "Set the minimum for accepted values, or ==nil== if open." ^self propertyAt: #min put: aMagnitudeOrNil ] min: aMinimumObject max: aMaximumObject [ "Set the minimum and maximum of accepted values, or ==nil== if open." self min: aMinimumObject; max: aMaximumObject ] rangeErrorMessage [ | min max | ^self propertyAt: #rangeErrorMessage ifAbsent: [min := self toString: self min. max := self toString: self max. (self min notNil and: [self max notNil]) ifTrue: [^'Input must be between ' , min , ' and ' , max]. (self min notNil and: [self max isNil]) ifTrue: [^'Input must be above or equeal to ' , min]. (self min isNil and: [self max notNil]) ifTrue: [^'Input must be below or equal to ' , max]] ] rangeErrorMessage: aString [ ^self propertyAt: #rangeErrorMessage put: aString ] validateSpecific: anObject [ super validateSpecific: anObject. (self isWithinRange: anObject) ifFalse: [MARangeError description: self signal: self rangeErrorMessage] ] ] MAMagnitudeDescription subclass: MADateDescription [ MADateDescription class >> isAbstract [ ^false ] MADateDescription class >> label [ ^'Date' ] acceptMagritte: aVisitor [ aVisitor visitDateDescription: self ] kind [ ^Date ] ] MAMagnitudeDescription subclass: MADurationDescription [ MADurationDescription class >> isAbstract [ ^false ] MADurationDescription class >> label [ ^'Duration' ] acceptMagritte: aVisitor [ aVisitor visitDurationDescription: self ] kind [ ^Duration ] ] MAMagnitudeDescription subclass: MANumberDescription [ MANumberDescription class >> isAbstract [ ^false ] MANumberDescription class >> label [ ^'Number' ] acceptMagritte: aVisitor [ aVisitor visitNumberDescription: self ] beInteger [ self addCondition: [:value | value isInteger] labelled: 'No integer was entered' ] kind [ ^Number ] ] MAMagnitudeDescription subclass: MATimeDescription [ MATimeDescription class >> isAbstract [ ^false ] MATimeDescription class >> label [ ^'Time' ] acceptMagritte: aVisitor [ aVisitor visitTimeDescription: self ] kind [ ^Time ] ] MAMagnitudeDescription subclass: MATimeStampDescription [ MATimeStampDescription class >> isAbstract [ ^false ] MATimeStampDescription class >> label [ ^'Timestamp' ] acceptMagritte: aVisitor [ aVisitor visitTimeStampDescription: self ] kind [ ^DateTime ] ] MAElementDescription subclass: MAReferenceDescription [ | reference | MAReferenceDescription class >> defaultReference [ ^MAStringDescription new ] MAReferenceDescription class >> descriptionReference [ ^(MAToOneRelationDescription new) accessor: #reference; classes: [MADescription withAllConcreteClasses] asDynamicObject; label: 'Description'; priority: 400; beRequired; yourself ] acceptMagritte: aVisitor [ aVisitor visitReferenceDescription: self ] postCopy [ super postCopy. reference := reference copy ] reference [ ^reference ifNil: [reference := self class defaultReference] ] reference: aDescription [ reference := aDescription ] ] MAReferenceDescription subclass: MAOptionDescription [ | options | MAOptionDescription class >> defaultOptions [ ^OrderedCollection new ] MAOptionDescription class >> defaultSorted [ ^false ] MAOptionDescription class >> descriptionDefault [ ^nil ] MAOptionDescription class >> descriptionOptions [ ^(MAMemoDescription new) accessor: #optionsTextual; label: 'Options'; priority: 410; default: self defaultOptions; yourself ] MAOptionDescription class >> descriptionSorted [ ^(MABooleanDescription new) accessor: #sorted; label: 'Sorted'; priority: 240; default: self defaultSorted; yourself ] acceptMagritte: aVisitor [ aVisitor visitOptionDescription: self ] allOptions [ ^self prepareOptions: self options copy ] allOptionsWith: anObject [ ^self prepareOptions: ((self shouldNotInclude: anObject) ifFalse: [self options copyWith: anObject] ifTrue: [self options copy]) ] beSorted [ self sorted: true ] beUnsorted [ self sorted: false ] isSorted [ ^self sorted ] labelForOption: anObject [ self propertyAt: #labels ifPresent: [:labels | labels at: anObject ifPresent: [:value | ^value]]. ^self reference toString: anObject ] options [ ^options ifNil: [options := self class defaultOptions] ] options: anArray [ options := anArray ] optionsAndLabels: aCollection [ "Set the options to be the keys of aCollection and the labels to be the values of aCollection." self options: (aCollection collect: [:assoc | assoc key]). self propertyAt: #labels put: (aCollection inject: IdentityDictionary new into: [:result :assoc | result add: assoc; yourself]) ] optionsTextual [ ^(self reference toStringCollection: self options) asMultilineString ] optionsTextual: aString [ | lines | lines := (aString ifNil: [String new]) lines. ^self options: (self reference fromStringCollection: lines) ] postCopy [ super postCopy. options := options copy ] prepareOptions: aCollection [ ^self isSorted ifFalse: [aCollection asArray] ifTrue: [(aCollection asArray) sort: self sortBlock; yourself] ] shouldNotInclude: anObject [ ^anObject isNil or: [self options includes: anObject] ] sortBlock [ ^ [:a :b | (self reference toString: a) <= (self reference toString: b)] ] sorted [ ^self propertyAt: #sorted ifAbsent: [self class defaultSorted] ] sorted: aBoolean [ ^self propertyAt: #sorted put: aBoolean ] undefined: aString [ super undefined: aString. self reference isNil ifFalse: [self reference undefined: aString] ] ] MAOptionDescription subclass: MAMultipleOptionDescription [ MAMultipleOptionDescription class >> defaultDistinct [ ^false ] MAMultipleOptionDescription class >> defaultOrdered [ ^false ] MAMultipleOptionDescription class >> descriptionDistinct [ ^(MABooleanDescription new) accessor: #distinct; label: 'Distinct'; priority: 250; default: self defaultDistinct; yourself ] MAMultipleOptionDescription class >> descriptionOrdered [ ^(MABooleanDescription new) accessor: #ordered; label: 'Ordered'; priority: 260; default: self defaultOrdered; yourself ] MAMultipleOptionDescription class >> isAbstract [ ^false ] MAMultipleOptionDescription class >> label [ ^'Multiple-Option' ] acceptMagritte: aVisitor [ aVisitor visitMultipleOptionDescription: self ] beDistinct [ self distinct: true ] beIndefinite [ self distinct: false ] beOrdered [ self ordered: true ] beUnordered [ self ordered: false ] distinct [ ^self propertyAt: #distinct ifAbsent: [self class defaultDistinct] ] distinct: aBoolean [ self propertyAt: #distinct put: aBoolean ] isDistinct [ ^self distinct ] isOrdered [ ^self ordered ] kind [ ^Collection ] ordered [ ^self propertyAt: #ordered ifAbsent: [self class defaultOrdered] ] ordered: aBoolean [ self propertyAt: #ordered put: aBoolean ] validateKind: anObject [ super validateKind: anObject. (anObject allSatisfy: [:each | self options includes: each]) ifFalse: [MAKindError description: self signal: self kindErrorMessage] ] validateRequired: anObject [ super validateRequired: anObject. (self isRequired and: [anObject isCollection and: [anObject isEmpty]]) ifTrue: [MARequiredError description: self signal: self requiredErrorMessage] ] ] MAOptionDescription subclass: MASingleOptionDescription [ MASingleOptionDescription class >> defaultExtensible [ ^false ] MASingleOptionDescription class >> descriptionExtensible [ ^(MABooleanDescription new) accessor: #extensible; label: 'Extensible'; priority: 250; default: self defaultExtensible; yourself ] MASingleOptionDescription class >> descriptionGroupBy [ ^(MASymbolDescription new) selectorAccessor: #groupBy; label: 'Grouped by'; priority: 260; default: nil; yourself ] MASingleOptionDescription class >> isAbstract [ ^false ] MASingleOptionDescription class >> label [ ^'Single-Option' ] acceptMagritte: aVisitor [ aVisitor visitSingleOptionDescription: self ] beExtensible [ self extensible: true ] beLimited [ self extensible: false ] extensible [ ^self propertyAt: #extensible ifAbsent: [self class defaultExtensible] ] extensible: aBoolean [ self propertyAt: #extensible put: aBoolean ] groupBy [ "Answer the selector to be sent to the options objects for determining their group" ^self propertyAt: #groupBy ifAbsent: [nil] ] groupBy: aSymbol [ "aSymbol is the selector to be sent to the options objects for getting their group" ^self propertyAt: #groupBy put: aSymbol ] isExtensible [ ^self extensible ] isGrouped [ ^self groupBy notNil ] prepareOptions: aCollection [ ^self isRequired ifTrue: [super prepareOptions: aCollection] ifFalse: [(super prepareOptions: aCollection) copyWithFirst: nil] ] shouldNotInclude: anObject [ ^self isExtensible not or: [super shouldNotInclude: anObject] ] validateKind: anObject [ super validateKind: anObject. (self isExtensible or: [self options includes: anObject]) ifFalse: [MAKindError description: self signal: self kindErrorMessage] ] ] MAReferenceDescription subclass: MARelationDescription [ | classes | MARelationDescription class >> defaultClasses [ ^Set new ] MARelationDescription class >> defaultReference [ ^nil ] MARelationDescription class >> descriptionClasses [ ^(MAMultipleOptionDescription new) accessor: #classes; label: 'Classes'; priority: 400; options: [Smalltalk allClasses] asDynamicObject; reference: MAClassDescription new; yourself ] MARelationDescription class >> descriptionReference [ ^(super descriptionReference) classes: [MAContainer withAllConcreteClasses] asDynamicObject; beOptional; yourself ] acceptMagritte: aVisitor [ aVisitor visitRelationDescription: self ] allClasses [ ^(Array withAll: self classes) sort: [:a :b | a label <= b label]; yourself ] classes [ ^classes ifNil: [classes := self class defaultClasses] ] classes: aCollection [ classes := aCollection ] commonClass [ "Answer a common superclass of the classes of the receiver. The algorithm is implemented to be as efficient as possible. The inner loop will be only executed the first few iterations." | current | self classes isEmpty ifTrue: [^self class descriptionContainer]. current := self classes anyOne. self classes do: [:each | [each includesBehavior: current] whileFalse: [current := current superclass]]. ^current ] postCopy [ super postCopy. classes := classes copy ] reference [ "The reference within a ==*MARelationDescription*== is calculated automatically from all the classes of the receiver, if set to ==nil==. By setting the reference to a ==*MAContainer*== instance it is possible to customize the reference description." ^super reference ifNil: [self commonClass description] ] ] MARelationDescription subclass: MAToManyRelationDescription [ MAToManyRelationDescription class >> defaultDefinitive [ ^false ] MAToManyRelationDescription class >> defaultOrdered [ ^false ] MAToManyRelationDescription class >> defaultSorted [ ^false ] MAToManyRelationDescription class >> descriptionDefinitive [ ^(MABooleanDescription new) accessor: #definitive; label: 'Definitive'; priority: 265; default: self defaultDefinitive; yourself ] MAToManyRelationDescription class >> descriptionOrdered [ ^(MABooleanDescription new) accessor: #ordered; label: 'Ordered'; priority: 260; default: self defaultOrdered; yourself ] MAToManyRelationDescription class >> descriptionSorted [ ^(MABooleanDescription new) accessor: #sorted; label: 'Sorted'; priority: 240; default: self defaultSorted; yourself ] MAToManyRelationDescription class >> isAbstract [ ^false ] MAToManyRelationDescription class >> label [ ^'1:m Relation' ] acceptMagritte: aVisitor [ aVisitor visitToManyRelationDescription: self ] beDefinitive [ self definitive: true ] beModifiable [ self definitive: false ] beOrdered [ self ordered: true ] beSorted [ self sorted: true ] beUnordered [ self ordered: false ] beUnsorted [ self sorted: false ] definitive [ ^self propertyAt: #definitive ifAbsent: [self class defaultDefinitive] ] definitive: aBoolean [ self propertyAt: #definitive put: aBoolean ] isDefinitive [ ^self definitive ] isOrdered [ ^self ordered ] isSorted [ ^self sorted ] kind [ ^Collection ] ordered [ ^self propertyAt: #ordered ifAbsent: [self class defaultOrdered] ] ordered: aBoolean [ self propertyAt: #ordered put: aBoolean ] sorted [ ^self propertyAt: #sorted ifAbsent: [self class defaultSorted] ] sorted: aBoolean [ ^self propertyAt: #sorted put: aBoolean ] validateKind: anObject [ super validateKind: anObject. anObject do: [:object | (self classes anySatisfy: [:class | object species includesBehavior: class]) ifFalse: [MAKindError description: self signal: self kindErrorMessage]] ] validateRequired: anObject [ super validateRequired: anObject. (self isRequired and: [anObject isCollection and: [anObject isEmpty]]) ifTrue: [MARequiredError description: self signal: self requiredErrorMessage] ] ] MAToManyRelationDescription subclass: MAToManyScalarRelationDescription [ MAToManyScalarRelationDescription class >> label [ ^'1:m scalar Relation' ] acceptMagritte: aVisitor [ aVisitor visitToManyScalarRelationDescription: self ] ] MARelationDescription subclass: MAToOneRelationDescription [ MAToOneRelationDescription class >> isAbstract [ ^false ] MAToOneRelationDescription class >> label [ ^'1:1 Relation' ] acceptMagritte: aVisitor [ aVisitor visitToOneRelationDescription: self ] validateKind: anObject [ super validateKind: anObject. (self classes anySatisfy: [:class | anObject species = class]) ifFalse: [MAKindError description: self signal: self kindErrorMessage] ] ] MAReferenceDescription subclass: MATableDescription [ MATableDescription class >> defaultColumnLabels [ ^OrderedCollection with: 'a' with: 'b' with: 'c' ] MATableDescription class >> defaultRowLabels [ ^OrderedCollection with: '1' with: '2' with: '3' ] MATableDescription class >> descriptionColumnLabels [ ^(MAMemoDescription new) accessor: #columnLabelsTextual; label: 'Column Labels'; priority: 250; yourself ] MATableDescription class >> descriptionDefault [ ^nil ] MATableDescription class >> descriptionRequired [ ^nil ] MATableDescription class >> descriptionRowLabels [ ^(MAMemoDescription new) accessor: #rowLabelsTextual; label: 'Row Labels'; priority: 250; yourself ] MATableDescription class >> isAbstract [ ^false ] MATableDescription class >> label [ ^'Table' ] acceptMagritte: aVisitor [ aVisitor visitTableDescription: self ] columnCount [ ^self columnLabels size ] columnLabels [ ^self propertyAt: #columnLabels ifAbsent: [self class defaultColumnLabels] ] columnLabels: aCollection [ self propertyAt: #columnLabels put: aCollection ] columnLabelsTextual [ ^(MAStringDescription new toStringCollection: self columnLabels) asMultilineString ] columnLabelsTextual: aString [ self columnLabels: (MAStringDescription new fromStringCollection: aString lines) ] kind [ ^MATableModel ] rowCount [ ^self rowLabels size ] rowLabels [ ^self propertyAt: #rowLabels ifAbsent: [self class defaultRowLabels] ] rowLabels: aCollection [ self propertyAt: #rowLabels put: aCollection ] rowLabelsTextual [ ^(MAStringDescription new toStringCollection: self rowLabels) asMultilineString ] rowLabelsTextual: aString [ self rowLabels: (MAStringDescription new fromStringCollection: aString lines) ] validateSpecific: anObject [ super validateSpecific: anObject. (anObject rowCount ~= self rowCount or: [anObject columnCount ~= self columnCount]) ifTrue: [MAKindError description: self signal: self kindErrorMessage] ] ] MAReferenceDescription subclass: MATokenDescription [ | tokens | MATokenDescription class >> isAbstract [ ^false ] MATokenDescription class >> label [ ^'Token' ] acceptMagritte: aVisitor [ aVisitor visitTokenDescription: self ] kind [ ^Array ] tokens [ ^tokens ifNil: [tokens := #()] ] tokens: anArray [ tokens := anArray ] ] MAElementDescription subclass: MAStringDescription [ MAStringDescription class >> isAbstract [ ^false ] MAStringDescription class >> label [ ^'String' ] acceptMagritte: aVisitor [ aVisitor visitStringDescription: self ] isSortable [ ^true ] kind [ ^String ] ] MAStringDescription subclass: MAMemoDescription [ MAMemoDescription class >> defaultLineCount [ ^3 ] MAMemoDescription class >> descriptionLineCount [ ^(MANumberDescription new) accessor: #lineCount; label: 'Number of Lines'; priority: 400; default: self defaultLineCount; beInteger; min: 1; yourself ] MAMemoDescription class >> label [ ^'Memo' ] acceptMagritte: aVisitor [ aVisitor visitMemoDescription: self ] lineCount [ ^self propertyAt: #lineCount ifAbsent: [self class defaultLineCount] ] lineCount: anInteger [ ^self propertyAt: #lineCount put: anInteger ] ] MAStringDescription subclass: MAPasswordDescription [ MAPasswordDescription class >> label [ ^'Password' ] acceptMagritte: aVisitor [ aVisitor visitPasswordDescription: self ] isObfuscated: anObject [ ^anObject notNil and: [anObject isString and: [anObject isEmpty not and: [anObject allSatisfy: [:each | each = $*]]]] ] isSortable [ ^false ] obfuscated: anObject [ ^String new: (self toString: anObject) size withAll: $* ] ] MAStringDescription subclass: MASymbolDescription [ MASymbolDescription class >> label [ ^'Symbol' ] acceptMagritte: aVisitor [ aVisitor visitSymbolDescription: self ] kind [ ^Symbol ] ] MAObject subclass: MAMemento [ | model description | MAMemento class >> model: aModel [ ^self model: aModel description: aModel description ] MAMemento class >> model: aModel description: aDescription [ ^(self new) setModel: aModel; setDescription: aDescription; reset; yourself ] commit [ "Commit the receiver into the model." ] description [ ^description ] isDifferent: firstDictionary to: secondDictionary [ | firstValue secondValue | self description do: [:each | (each isVisible and: [each isReadonly not]) ifTrue: [firstValue := firstDictionary at: each ifAbsent: [nil]. secondValue := secondDictionary at: each ifAbsent: [nil]. firstValue = secondValue ifFalse: [^true]]]. ^false ] model [ ^model ] printOn: aStream [ super printOn: aStream. aStream nextPutAll: ' model: '; print: self model ] pull [ "Utitlity method to pull the model into a dictionary mapping descriptions to values. nil values are replaced with the default ones of the model." | result | result := self pullRaw. result keysAndValuesDo: [:key :value | value isNil ifTrue: [result at: key put: key default yourself]]. ^result ] pullRaw [ | result | result := Dictionary new. self description do: [:each | result at: each put: (self model readUsing: each)]. ^result ] push: aDictionary [ "Utitlity method to push a dictionary mapping descriptions to values into the model." aDictionary keysAndValuesDo: [:key :value | (key isVisible and: [key isReadonly not]) ifTrue: [self model write: value using: key]] ] reset [ "Reset the memento from the model." ] setDescription: aDescription [ description := aDescription ] setModel: aModel [ model := aModel ] validate [ "Check if the data in the receiver would be valid if committed. In case of problems an exception is raised." self description validate: self ] ] MAMemento subclass: MACachedMemento [ | cache | MACachedMemento class >> isAbstract [ ^false ] cache [ ^cache ] commit [ super commit. self push: self cache. self reset ] hasChanged [ "Answer ==true==, if the cached data is different to the data in the model." ^self isDifferent: self cache to: self pullRaw ] readUsing: aDescription [ ^self cache at: aDescription ] reset [ super reset. self setCache: self pull ] setCache: aDictionary [ cache := aDictionary ] write: anObject using: aDescription [ self cache at: aDescription put: anObject ] ] MACachedMemento subclass: MACheckedMemento [ | original | hasConflict [ "Answer ==true==, if there is an edit conflict." ^self hasChanged and: [self isDifferent: self original to: self pullRaw] ] original [ ^original ] reset [ super reset. self setOriginal: self pullRaw ] setOriginal: aDictionary [ original := aDictionary ] validate [ self hasConflict ifFalse: [^super validate]. self reset. MAConflictError description: self description signal: self description conflictErrorMessage ] ] MAMemento subclass: MAStraitMemento [ MAStraitMemento class >> isAbstract [ ^false ] readUsing: aDescription [ ^(self model readUsing: aDescription) ifNil: [aDescription default] ] write: anObject using: aDescription [ self model write: anObject using: aDescription ] ] Object subclass: MASortBlock [ | accessor selector | MASortBlock class >> accessor: anAccessor selector: aSelector [ ^self basicNew initializeAccessor: anAccessor selector: aSelector ] MASortBlock class >> selector: aSelector [ ^self accessor: MAIdentityAccessor new selector: aSelector ] fixTemps [ ] initializeAccessor: anAccessor selector: aSelector [ accessor := anAccessor asAccessor. selector := aSelector ] value: aFirstObject value: aSecondObject [ ^(accessor read: aFirstObject) perform: selector with: (accessor read: aSecondObject) ] ] Object subclass: MATableModel [ | rowCount columnCount contents | MATableModel class >> rows: aRowCount columns: aColumnCount [ ^self rows: aRowCount columns: aColumnCount contents: (Array new: aRowCount * aColumnCount) ] MATableModel class >> rows: aRowCount columns: aColumnCount contents: anArray [ ^(self new) setRowCount: aRowCount; setColumnCount: aColumnCount; setContents: anArray; yourself ] = aTable [ ^self species = aTable species and: [self rowCount = aTable rowCount and: [self columnCount = aTable columnCount and: [self contents = aTable contents]]] ] at: aRowIndex at: aColumnIndex [ "Answer the contents of ==aRowIndex== and ==aColumnIndex==. Raises an error if the coordinates are out of bounds." self checkAt: aRowIndex at: aColumnIndex. ^self uncheckedAt: aRowIndex at: aColumnIndex ] at: aRowIndex at: aColumnIndex put: aValue [ "Set the contents of ==aRowIndex== and ==aColumnIndex==> to ==aValue==. Raises an error if the coordinates are out of bounds." self checkAt: aRowIndex at: aColumnIndex. ^self uncheckedAt: aRowIndex at: aColumnIndex put: aValue ] checkAt: aRowIndex at: aColumnIndex [ (aRowIndex between: 1 and: self rowCount) ifFalse: [self error: 'Row subscript out of range.']. (aColumnIndex between: 1 and: self columnCount) ifFalse: [self error: 'Column subscript out of range.'] ] collect: aBlock [ | copy | copy := self copyEmpty. self do: [:row :col :val | copy at: row at: col put: (aBlock value: row value: col value: val)]. ^copy ] columnCount [ "Answer the column count of the table." ^columnCount ] contents [ ^contents ] copyEmpty [ ^self class rows: self rowCount columns: self columnCount ] copyRows: aRowCount columns: aColumnCount [ | table | table := self class rows: aRowCount columns: aColumnCount. 1 to: (self rowCount min: aRowCount) do: [:row | 1 to: (self columnCount min: aColumnCount) do: [:col | table uncheckedAt: row at: col put: (self uncheckedAt: row at: col)]]. ^table ] do: aBlock [ 1 to: self rowCount do: [:row | 1 to: self columnCount do: [:col | aBlock value: row value: col value: (self uncheckedAt: row at: col)]] ] hash [ ^self contents hash ] indexAt: aRowIndex at: aColumnIndex [ ^(aRowIndex - 1) * self columnCount + aColumnIndex ] pointAt: anIndex [ ^Point x: (anIndex - 1) // self columnCount + 1 y: (anIndex - 1) \\ self columnCount + 1 ] postCopy [ super postCopy. self setContents: self contents copy ] reshapeRows: aRowCount columns: aColumnCount [ "Change the size of the receiving table to ==aRowCount== times ==aColumnCount==, throwing away elements that are cut off and initializing empty cells with ==nil==." self setContents: (self copyRows: aRowCount columns: aColumnCount) contents. self setRowCount: aRowCount; setColumnCount: aColumnCount ] rowCount [ "Answer the row count of the table." ^rowCount ] setColumnCount: anInteger [ columnCount := anInteger ] setContents: anArray [ contents := anArray ] setRowCount: anInteger [ rowCount := anInteger ] uncheckedAt: aRowIndex at: aColumnIndex [ ^self contents at: (self indexAt: aRowIndex at: aColumnIndex) ] uncheckedAt: aRowIndex at: aColumnIndex put: aValue [ ^self contents at: (self indexAt: aRowIndex at: aColumnIndex) put: aValue ] ] Object subclass: MAVisitor [ MAVisitor class >> buildVisitorHierarchyForClass: aClass selector: aBlock classified: aSelector [ "self buildVisitorHierarchyForClass: MADescription selector: [ :class | 'visit' , (class name allButFirst: 2) , ':' ] classified: #'visiting-description'" aClass withAllSubclassesDo: [:class | (class category startsWith: 'Magritte') ifTrue: [self compile: (String streamContents: [:stream | stream nextPutAll: (aBlock value: class); nextPutAll: ' anObject'; cr. class = aClass ifFalse: [stream tab; nextPutAll: 'self '; nextPutAll: (aBlock value: class superclass); nextPutAll: ' anObject.']]) classified: aSelector. class compile: (String streamContents: [:stream | stream nextPutAll: 'acceptMagritte: aVisitor'; cr. stream tab; nextPutAll: 'aVisitor '; nextPutAll: (aBlock value: class); nextPutAll: ' self.']) classified: #visiting]] ] visit: anObject [ "Visit ==anObject== with the receiving visitor." anObject acceptMagritte: self ] visitAll: aCollection [ "Visit all elements of ==aCollection== with the receiving visitor." aCollection do: [:each | self visit: each] ] visitBooleanDescription: anObject [ self visitElementDescription: anObject ] visitClassDescription: anObject [ self visitElementDescription: anObject ] visitContainer: anObject [ self visitDescription: anObject ] visitDateDescription: anObject [ self visitMagnitudeDescription: anObject ] visitDescription: anObject [ ] visitDurationDescription: anObject [ self visitMagnitudeDescription: anObject ] visitElementDescription: anObject [ self visitDescription: anObject ] visitFileDescription: anObject [ self visitElementDescription: anObject ] visitMagnitudeDescription: anObject [ self visitElementDescription: anObject ] visitMemoDescription: anObject [ self visitStringDescription: anObject ] visitMultipleOptionDescription: anObject [ self visitOptionDescription: anObject ] visitNumberDescription: anObject [ self visitMagnitudeDescription: anObject ] visitOptionDescription: anObject [ self visitReferenceDescription: anObject ] visitPasswordDescription: anObject [ self visitStringDescription: anObject ] visitPriorityContainer: anObject [ self visitContainer: anObject ] visitReferenceDescription: anObject [ self visitElementDescription: anObject ] visitRelationDescription: anObject [ self visitReferenceDescription: anObject ] visitReportContainer: anObject [ self visitContainer: anObject ] visitSingleOptionDescription: anObject [ self visitOptionDescription: anObject ] visitStringDescription: anObject [ self visitElementDescription: anObject ] visitSymbolDescription: anObject [ self visitStringDescription: anObject ] visitTableDescription: anObject [ self visitReferenceDescription: anObject ] visitTableReference: anObject [ ^self visitReferenceDescription: anObject ] visitTimeDescription: anObject [ self visitMagnitudeDescription: anObject ] visitTimeStampDescription: anObject [ self visitMagnitudeDescription: anObject ] visitToManyRelationDescription: anObject [ self visitRelationDescription: anObject ] visitToManyScalarRelationDescription: anObject [ self visitToManyRelationDescription: anObject ] visitToOneRelationDescription: anObject [ self visitRelationDescription: anObject ] visitTokenDescription: anObject [ self visitReferenceDescription: anObject ] ] MAVisitor subclass: MAGraphVisitor [ | seen object | initialize [ super initialize. seen := IdentitySet new ] object [ ^object ] use: anObject during: aBlock [ | previous | (seen includes: anObject) ifTrue: [^self]. anObject isNil ifFalse: [seen add: anObject]. previous := object. object := anObject. aBlock ensure: [object := previous] ] ] MAGraphVisitor subclass: MAValidatorVisitor [ MAValidatorVisitor class >> on: anObject description: aDescription [ ^self new on: anObject description: aDescription ] on: anObject description: aDescription [ self use: anObject during: [self visit: aDescription] ] validate: anObject using: aDescription [ aDescription validateRequired: anObject. anObject ifNil: [^self]. aDescription validateKind: anObject; validateSpecific: anObject; validateConditions: anObject ] visit: aDescription [ (aDescription isVisible and: [aDescription isReadonly not]) ifTrue: [super visit: aDescription] ] visitContainer: aDescription [ super visitContainer: aDescription. self object ifNil: [^self]. aDescription do: [:each | self use: (object readUsing: each) during: [self visit: each]] ] visitDescription: aDescription [ "Validate the current object using aDescription within an exception handler to avoid running further tests that might cause error-cascades." [self validate: self object using: aDescription] on: MAValidationError do: [:err | err isResumable ifFalse: [err beResumable]. err pass] ] visitTableDescription: aDescription [ super visitTableDescription: aDescription. self object ifNil: [^self]. self object contents do: [:each | self use: each during: [self visit: aDescription reference]] ] ] MAVisitor subclass: MAStreamingVisitor [ | stream object | contents [ ^self stream contents ] object [ ^object ] object: anObject [ object := anObject ] object: anObject during: aBlock [ | previous | previous := self object. self object: anObject. aBlock ensure: [self object: previous] ] stream [ ^stream ] stream: aStream [ stream := aStream ] ] MAStreamingVisitor subclass: MAReader [ MAReader class >> read: aStream description: aDescription [ ^self new read: aStream description: aDescription ] error: aString [ MAReadError signal: aString ] read: aStream description: aDescription [ self stream: aStream; visit: aDescription. ^self object ] ] MAReader subclass: MAStringReader [ read: aStream description: aDescription [ ^aStream atEnd ifFalse: [super read: aStream description: aDescription] ] visitBooleanDescription: aDescription [ (aDescription trueString = self contents or: [aDescription trueStrings includes: self contents]) ifTrue: [^self object: true]. (aDescription falseString = self contents or: [aDescription falseStrings includes: self contents]) ifTrue: [^self object: false]. MAReadError signal ] visitClassDescription: aDescription [ self shouldNotImplement ] visitContainer: anObject [ self shouldNotImplement ] visitDurationDescription: aDescription [ | contents | contents := self contents. contents isEmpty ifTrue: [MAReadError signal]. (contents occurrencesOf: $-) > 1 ifTrue: [MAReadError signal]. (contents indexOf: $-) > 1 ifTrue: [MAReadError signal]. (contents occurrencesOf: $.) > 1 ifTrue: [MAReadError signal]. (contents allSatisfy: [:each | '-0123456789.:' includes: each]) ifFalse: [MAReadError signal]. super visitDurationDescription: aDescription ] visitElementDescription: aDescription [ "This implementation can be very dangerous and might lead to a potential security hole (this is tested), since the default implementation of #readFrom: in Object evaluates the expression to find its value. Most subclasses like Number, Date, Time, ... override this implementation, but some others (like Boolean) do not." self object: ([aDescription kind readFrom: self stream] on: Error do: [:err | MAReadError signal: err messageText]) ] visitFileDescription: aDescription [ self shouldNotImplement ] visitMultipleOptionDescription: aDescription [ self object: (Array streamContents: [:output | [self stream atEnd] whileFalse: [output nextPut: (aDescription reference fromString: (self stream upTo: $,)). self stream peek = Character space ifTrue: [self stream next]]]) ] visitNumberDescription: aDescription [ | contents | contents := self contents. contents isEmpty ifTrue: [MAReadError signal]. (contents occurrencesOf: $-) > 1 ifTrue: [MAReadError signal]. (contents indexOf: $-) > 1 ifTrue: [MAReadError signal]. (contents occurrencesOf: $.) > 1 ifTrue: [MAReadError signal]. (contents allSatisfy: [:each | '+-0123456789.eE' includes: each]) ifFalse: [MAReadError signal]. super visitNumberDescription: aDescription ] visitRelationDescription: aDescription [ self shouldNotImplement ] visitSingleOptionDescription: aDescription [ self visit: aDescription reference ] visitStringDescription: aDescription [ self object: self contents ] visitSymbolDescription: aDescription [ self object: self contents asSymbol ] visitTableDescription: aDescription [ self shouldNotImplement ] visitTimeDescription: aDescription [ | string | string := self contents. (string notEmpty and: [string allSatisfy: [:each | '0123456789: apm' includes: each]]) ifFalse: [MAReadError signal]. self object: (aDescription kind readFrom: string readStream) ] visitTokenDescription: aDescription [ self object: (aDescription kind streamContents: [:output | [self stream atEnd] whileFalse: [output nextPut: (aDescription reference fromString: (self stream upTo: $ ))]]) ] ] MAStreamingVisitor subclass: MAWriter [ MAWriter class >> write: anObject [ ^self new write: anObject ] MAWriter class >> write: anObject description: aDescription [ ^self new write: anObject description: aDescription ] MAWriter class >> write: anObject description: aDescription to: aStream [ ^self new write: anObject description: aDescription to: aStream ] defaultWriteStream [ self subclassResponsibility ] error: aString [ MAWriteError signal: aString ] write: anObject [ ^self write: anObject description: anObject description ] write: anObject description: aDescription [ ^self write: anObject description: aDescription to: self defaultWriteStream ] write: anObject description: aDescription to: aStream [ self object: anObject; stream: aStream; visit: aDescription. ^self contents ] ] MAWriter subclass: MAStringWriter [ defaultWriteStream [ ^String new writeStream ] visitBooleanDescription: aDescription [ self stream nextPutAll: (self object ifTrue: [aDescription trueString] ifFalse: [aDescription falseString]) ] visitClassDescription: aDescription [ self stream nextPutAll: self object label ] visitContainer: aDescription [ aDescription do: [:each | each isVisible ifTrue: [each stringWriter write: (self object readUsing: each) description: each to: stream. ^self]] ] visitElementDescription: aDescription [ self stream nextPutAll: self object asString ] visitFileDescription: aDescription [ self stream nextPutAll: self object filename ] visitMultipleOptionDescription: aDescription [ self object do: [:each | self object: each during: [self visit: aDescription reference]] separatedBy: [self stream nextPutAll: ', '] ] visitSingleOptionDescription: aDescription [ self visit: aDescription reference ] visitTimeDescription: aDescription [ self object print24: true showSeconds: true on: self stream ] visitTimeStampDescription: aDescription [ (self stream) print: self object asDate; space. self stream print: self object asTime ] visitToManyRelationDescription: aDescription [ self object do: [:each | self object: each during: [self visit: each description]] separatedBy: [self stream nextPutAll: ', '] ] visitToOneRelationDescription: aDescription [ self visit: self object description ] visitTokenDescription: aDescription [ self object do: [:each | self object: each during: [self visit: aDescription reference]] separatedBy: [self stream nextPutAll: ' '] ] write: anObject description: aDescription to: aStream [ anObject isNil ifTrue: [^aDescription undefined]. ^super write: anObject description: aDescription to: aStream ] ] Object class extend [ description [ ^Magritte.MADescriptionBuilder for: self ] ] Object extend [ description [ "Return the description of the reciever. Subclasses might override this message to return instance-based descriptions." ^self class description ] isDescription [ ^false ] mementoClass [ "Return a class to be used to remember or cache the receiver, namely a memento object." ^Magritte.MACheckedMemento ] readUsing: aDescription [ "Dispatch the read-access to the receiver using the accessor of aDescription." ^aDescription accessor read: self ] write: anObject using: aDescription [ "Dispatch the write-access to the receiver of anObject using the accessor of aDescription." aDescription accessor write: anObject to: self ] ] UndefinedObject extend [ asAccessor [ ^Magritte.MANullAccessor new ] label [ ^'n/a' ] ] Integer extend [ asFileSize [ #('B' 'KB' 'MB' 'GB' 'TB' 'PB' 'EB' 'ZB' 'YB') inject: self into: [:value :each | value < 1024 ifFalse: [value // 1024] ifTrue: [^value asString , ' ' , each]] ] ] Eval [ MADescriptionBuilder initialize. MAExternalFileModel initialize. MAFileModel initialize. MAObject initialize ] smalltalk-3.2.5/packages/magritte/magritte-gst.st0000644000175000017500000002367112123404352017004 00000000000000"====================================================================== | | Magritte compatibility methods for GNU Smalltalk | | ======================================================================" "====================================================================== | | Copyright 2008 Free Software Foundation, Inc. | Written by Paolo Bonzini. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" Object subclass: MACompatibility [ ShowLicense := false. MACompatibility class >> allSubInstancesOf: aClass do: aBlock [ "Evaluate the aBlock for all instances of aClass and all its subclasses." aClass allSubinstancesDo: aBlock ] MACompatibility class >> classNamed: aString [ "Return the class named aString, nil if the class can't be found." ^(aString subStrings: $.) inject: Smalltalk into: [ :old :each | old at: each asSymbol ifAbsent: [ ^nil ] ] ] MACompatibility class >> openWorkspace: aContentsString titled: aTitleString [ "Open a new wokspace with the contents aContentsString and the title aTitleString." ShowLicense ifFalse: [ ^self ]. ('%1 %2 ' % { aTitleString asUppercase. aContentsString }) displayOn: stderr ] MACompatibility class >> referenceStream: aReadWriteStream [ "Return a stream instance to operate on aReadWriteStream being able to serialize and deserialize objects by sending #nextPut: and #next. Squeak: The implementation of ReferenceStream doesn't work well together with the default WriteStream implementaiton, therefor we have to change it on the fly." ^ObjectDumper on: aReadWriteStream ] MACompatibility class >> uuid [ "Answer a random object that is extremly likely to be unique over space and time." ^UUID new ] ] ByteArray subclass: UUID [ Node := nil. SequenceValue := nil. LastTime := nil. Generator := nil. GeneratorMutex := nil. UUID class >> timeValue [ "Returns the time value for a UUIDv1, in 100 nanoseconds units since 1-1-1601." ^((Time utcSecondClock + (109572 * 86400)) * 1000 + Time millisecondClock) * 10000 ] UUID class >> randomNodeValue [ "Return the node value for a UUIDv1." | n | "TODO: use some kind of digest to produce cryptographically strong random numbers." n := Generator between: 0 and: 16rFFFF. n := (n bitShift: 16) bitOr: (Generator between: 0 and: 16rFFFF). n := (n bitShift: 16) bitOr: (Generator between: 0 and: 16rFFFF). ^n bitOr: 1 ] UUID class >> update: aSymbol [ "Update the sequence value of a UUIDv1 when an image is restarted." aSymbol == #returnFromSnapshot ifTrue: [ "You cannot be sure that the node ID is the same." GeneratorMutex critical: [ Generator := Random new. LastTime := self timeValue. Node := self randomNodeValue. SequenceValue := (SequenceValue + 1) bitAnd: 16383 ]]. ] UUID class >> defaultSize [ "Return the size of a UUIDv1." ^16 ] UUID class >> initialize [ "Initialize the class." ObjectMemory addDependent: self. Generator := Random new. LastTime := self timeValue. Node := self randomNodeValue. SequenceValue := Generator between: 0 and: 16383. GeneratorMutex := Semaphore forMutualExclusion. ] UUID class >> new [ "Return a new UUIDv1." ^(self new: self defaultSize) initialize ] initialize [ "Fill in the fields of a new UUIDv1." | t | GeneratorMutex critical: [ t := self class timeValue bitAnd: 16rFFFFFFFFFFFFFFF. t <= LastTime ifTrue: [ SequenceValue := (SequenceValue + 1) bitAnd: 16383 ]. LastTime := t. self at: 1 put: ((t bitShift: -24) bitAnd: 255). self at: 2 put: ((t bitShift: -16) bitAnd: 255). self at: 3 put: ((t bitShift: -8) bitAnd: 255). self at: 4 put: (t bitAnd: 255). self at: 5 put: ((t bitShift: -40) bitAnd: 255). self at: 6 put: ((t bitShift: -32) bitAnd: 255). self at: 7 put: (t bitShift: -56) + 16r10. self at: 8 put: ((t bitShift: -48) bitAnd: 255). self at: 9 put: (SequenceValue bitShift: -8) + 16r80. self at: 10 put: (SequenceValue bitAnd: 255). self at: 13 put: ((Node bitShift: -40) bitAnd: 255). self at: 14 put: ((Node bitShift: -32) bitAnd: 255). self at: 15 put: ((Node bitShift: -24) bitAnd: 255). self at: 16 put: ((Node bitShift: -16) bitAnd: 255). self at: 11 put: ((Node bitShift: -8) bitAnd: 255). self at: 12 put: (Node bitAnd: 255)] ] printOn: aStream from: a to: b [ self from: a to: b do: [:each | aStream nextPut: (Character digitValue: (each bitShift: -4)). aStream nextPut: (Character digitValue: (each bitAnd: 15)) ] ] printOn: aStream [ "Print the bytes in the receiver in UUID format." self printOn: aStream from: 1 to: 4. aStream nextPut: $-. self printOn: aStream from: 5 to: 6. aStream nextPut: $-. self printOn: aStream from: 7 to: 8. aStream nextPut: $-. self printOn: aStream from: 9 to: 10. aStream nextPut: $-. self printOn: aStream from: 11 to: 16. ] ] Symbol extend [ isUnary [ "Return true if the symbol represents a Unary selector." ^self numArgs = 0 ] ] FileDescriptor extend [ binary [ "Do nothing, needed for Squeak compatibility." ] ] Object extend [ asString [ "Return the #displayString, needed for Squeak compatibility." ^self displayString ] isCollection [ "Return false, needed for Squeak compatibility." ^false ] isEmptyOrNil [ "Return false, needed for Squeak compatibility." ^false ] isVariableBinding [ "Return false, needed by Magritte-Seaside." ^false ] ] Association extend [ isVariableBinding [ "Return false, needed by Magritte-Seaside." ^true ] ] Collection extend [ intersection: b [ "Return the set of elements common to the receiver and B." ^self asSet & b ] hasEqualElements: b [ "Compare the elements in the receiver and B. Can be improved, looking at Squeak's implementation." ^self asArray = b asArray ] isCollection [ "Return true, needed for Squeak compatibility." ^true ] isEmptyOrNil [ "Return true if the collection is empty, needed for Squeak compatibility." ^self isEmpty ] ] SequenceableCollection extend [ sort: aBlock [ "Sort the items of the receiver according to the sort block, aBlock." self replaceFrom: 1 to: self size with: (self asSortedCollection: aBlock) startingAt: 1 ] ] SortedCollection extend [ sort: aBlock [ "Sort the items of the receiver according to the sort block, aBlock, and change the sort block to aBlock." sortBlock := aBlock. self sortFrom: firstIndex to: lastIndex. sorted := true. lastOrdered := lastIndex ] ] UndefinedObject extend [ isEmptyOrNil [ "Return true, needed for Squeak compatibility." ^true ] ] String extend [ includesSubstring: aString caseSensitive: aBoolean [ "Needed for Squeak compatibility." aBoolean ifTrue: [ ^(self indexOfSubCollection: aString) > 0 ]. ^(self asLowercase indexOfSubCollection: aString asLowercase) > 0 ] ] ValueHolder extend [ contents [ "Needed for Squeak compatibility." ^self value ] contents: anObject [ "Needed for Squeak compatibility." self value: anObject ] ] Time extend [ print24: boolean24 showSeconds: booleanSec on: aStream [ "Print a representation of the receiver on aStream according to the given flags. Needed for Squeak compatibility." | h | h := boolean24 ifTrue: [ self hour24 ] ifFalse: [ self hour12 ]. h printOn: aStream. aStream nextPut: $:. self minutes < 10 ifTrue: [aStream nextPut: $0]. self minutes printOn: aStream. booleanSec ifFalse: [ ^self ]. aStream nextPut: $:. self seconds < 10 ifTrue: [aStream nextPut: $0]. self seconds printOn: aStream ] ] Object subclass: MAVisitor [ MAVisitor class >> new [ ^super new initialize ] initialize [ ] ] Eval [ UUID initialize. ] smalltalk-3.2.5/packages/magritte/PORTING0000644000175000017500000000335212123404352015064 00000000000000Changes to be made upon porting: - remember to omit MACompatibility - delete MADescriptionBuilder>>register and its callers - delete MADescriptionBuilder>>unregister and its callers - delete one copy of BlockClosure>>asDynamicObject if you wish - go through all class extensions and prefix the namespace "Magritte" to all references to Magritte classes. - other rules needed: Character cr->Character nl (``@object nextPutAll: self class name) -> (``@object store: self class) ``@object evaluatorClass) -> Behavior (SystemChangeNotifier uniqueInstance doSilently: ``@arg2) -> ``@arg2 value ``@object evaluatorClass) -> Behavior (``@object organization listAtCategoryNamed: ``@arg2) -> ( ``@object selectors select: [ :each | (``@object >> each) methodCategory = ``@arg2 ]) - remove #visitColorDescription: MAColorChooser MAColorComponent MAColorDescription (and places where it is "added", in Magritte-Seaside) - remove String>>#lines. - in MAAutoSelectorAccessor add brackets to methods created by #createReadAccessor: and #createWriteAccessor: - in MAAutoSelectorAccessorTest>>#tearDown eliminate the call to #removeCategory:. - in MAVariableAccessor class>>#name:, add #asSymbol - in MAExternalFileModel>>#contents, change "stream contents" to "stream contents asByteArray" - remove MADynamicObjectTest>>#testNilOrNotNil (cannot pass on GNU Smalltalk right now) - there is some problem with exceptions that screws up SUnit :-) if a test fails with an error. to work around it, disable MADynamicObjectTest>>#testException until you fix all testsuite errors. - in Magritte-Seaside, add "Magritte import: Seaside" at the top, and add "Seaside." before class definitions that subclass from seaside (grep for /^WA/). smalltalk-3.2.5/packages/magritte/ChangeLog0000644000175000017500000000041412123404352015565 000000000000002010-12-04 Paolo Bonzini * package.xml: Remove now superfluous tags. 2009-05-05 Paolo Bonzini * magritte-model.st: Merge Magritte-Model-lr.345 (which was actually proposed by me on the help-smalltalk mailing list). smalltalk-3.2.5/packages/magritte/magritte-tests.st0000644000175000017500000027702712123404352017357 00000000000000Object subclass: MAAccessorMock [ ] Object subclass: MAMockAddress [ | place street plz | MAMockAddress class >> descriptionPlace [ ^(MAStringDescription new) autoAccessor: 'place'; label: 'Place'; yourself ] MAMockAddress class >> descriptionPlz [ ^(MANumberDescription new) autoAccessor: 'plz'; label: 'PLZ'; yourself ] MAMockAddress class >> descriptionStreet [ ^(MAStringDescription new) autoAccessor: 'street'; label: 'Street'; yourself ] = anObject [ ^self species = anObject species and: [self street = anObject street and: [self plz = anObject plz and: [self place = anObject place]]] ] hash [ ^self street hash ] place [ ^place ] place: anObject [ place := anObject ] plz [ ^plz ] plz: anObject [ plz := anObject ] street [ ^street ] street: anObject [ street := anObject ] ] TestCase subclass: MAAdaptiveModelTest [ | scaffolder | descriptions [ ^self scaffolder description children ] scaffolder [ ^scaffolder ] setUp [ scaffolder := MAAdaptiveModel new. (scaffolder description) add: MAStringDescription new; add: MANumberDescription new. scaffolder write: 'foo' using: self descriptions first. scaffolder write: 123 using: self descriptions second ] testRead [ self assert: (self scaffolder readUsing: self descriptions first) = 'foo'. self assert: (self scaffolder readUsing: self descriptions second) = 123 ] testWrite [ self scaffolder write: 'bar' using: self descriptions first. self scaffolder write: 321 using: self descriptions second. self assert: (self scaffolder readUsing: self descriptions first) = 'bar'. self assert: (self scaffolder readUsing: self descriptions second) = 321 ] ] TestCase subclass: MADescriptionBuilderTest [ MADescriptionBuilderTest class >> descriptionContainer [ ^super descriptionContainer label: 'mock' ] MADescriptionBuilderTest class >> descriptionContainer: aDescription [ ^aDescription propertyAt: #bar put: nil; yourself ] MADescriptionBuilderTest class >> descriptionContainerFoo: aDescription [ ^aDescription propertyAt: #foo put: nil; yourself ] MADescriptionBuilderTest class >> descriptionDescription [ ^MAToOneRelationDescription new label: 'foo' ] MADescriptionBuilderTest class >> descriptionDescription: aDescription [ ^aDescription propertyAt: #foo put: nil; yourself ] MADescriptionBuilderTest class >> descriptionDescriptionBar: aDescription [ ^aDescription propertyAt: #bar put: nil; yourself ] MADescriptionBuilderTest class >> descriptionDescriptionRec: aDescription [ ^aDescription reference: self description ] testContainer [ self assert: self description label = 'mock'. self assert: (self description hasProperty: #foo). self assert: (self description hasProperty: #bar) ] testDescription [ self assert: self description size = 1. self assert: self description children first label = 'foo'. self assert: (self description children first hasProperty: #foo). self assert: (self description children first hasProperty: #bar) ] testRecursive [ self assert: self description children first reference = self description ] ] TestCase subclass: MADynamicObjectTest [ testCalculated [ | object dummy | object := MADynamicObject on: [Time millisecondClockValue]. dummy := object yourself. (Delay forMilliseconds: 2) wait. self assert: dummy < object yourself ] testCollection [ | object | object := MADynamicObject on: [OrderedCollection with: 1 with: 2]. self assert: object size = 2. self assert: object first = 1. self assert: object second = 2. object add: 3. self assert: object size = 2. self assert: object first = 1. self assert: object second = 2 ] testConstant [ | object | object := MADynamicObject on: [self]. self assert: object = self. object := MADynamicObject on: [123]. self assert: object = 123 ] testCopy [ | object first second | object := (MADynamicObject on: [Time millisecondClockValue]) copy. first := object yourself. (Delay forMilliseconds: 2) wait. second := object yourself. self assert: first < second ] testCounter [ | object counter | counter := nil. object := MADynamicObject on: [counter := counter isNil ifTrue: [1] ifFalse: [counter := counter + 1]]. self assert: object = 1. self assert: object yourself = 2. self assert: object yourself yourself = 3 ] testDynamic [ | object collection | collection := nil. object := MADynamicObject on: [collection isNil ifTrue: [collection := OrderedCollection with: 1 with: 2] ifFalse: [collection]]. self assert: object size = 2. self assert: object first = 1. self assert: object second = 2. object add: 3. self assert: object size = 3. self assert: object first = 1. self assert: object second = 2. self assert: object third = 3 ] testException [ | object | object := MADynamicObject on: [1 / 0]. self should: [object asString] raise: ZeroDivide. object := MADynamicObject on: [Halt signal]. self assert: object asString = 'nil' ] "testNilOrNotNil [ | object | object := MADynamicObject on: [1]. self deny: object isNil. self assert: object notNil. object := MADynamicObject on: [nil]. self assert: object isNil. self deny: object notNil ]" ] TestCase subclass: MAExtensionsTest [ testCopyWithAll [ | col res | col := #(#a #b). res := col copyWithAll: #(#c #d). self assert: res = #(#a #b #c #d). self deny: col == res. col := Set with: #a with: #b. res := col copyWithAll: #(#c #d). self assert: res size = 4. self assert: (res includes: #a). self assert: (res includes: #b). self assert: (res includes: #c). self assert: (res includes: #d). self deny: col == res. col := OrderedCollection with: #a with: #b. res := col copyWithAll: #(#c #d). self assert: res = (OrderedCollection with: #a with: #b with: #c with: #d). self deny: col == res ] testCopyWithoutFirst [ | col res | col := #(#a #b #a #c). res := col copyWithoutFirst: #a. self assert: res = #(#b #a #c). self deny: col == res. col := Set with: #a with: #b with: #c. res := col copyWithoutFirst: #a. self assert: res size = 2. self assert: (res includes: #b). self assert: (res includes: #c). self deny: col == res ] testFileSize [ self assert: 1000 asFileSize = '1000 B'. self assert: 1024 asFileSize = '1 KB'. self assert: (1000 * 1000) asFileSize = '976 KB'. self assert: (1024 * 1024) asFileSize = '1 MB'. self assert: (1000 * 1000 * 1000) asFileSize = '953 MB'. self assert: (1024 * 1024 * 1024) asFileSize = '1 GB'. self assert: (1000 * 1000 * 1000 * 1000) asFileSize = '931 GB'. self assert: (1024 * 1024 * 1024 * 1024) asFileSize = '1 TB' "etc" ] testMatches [ self assert: ('' matches: ''). self assert: ('zort' matches: ''). self assert: ('zort' matches: 'o'). self assert: ('zort' matches: 'O'). self assert: ('zort' matches: '*'). self assert: ('mobaz' matches: '*baz'). self deny: ('mobazo' matches: '*baz'). self assert: ('mobazo' matches: '*baz*'). self deny: ('mozo' matches: '*baz*'). self assert: ('foozo' matches: 'foo*'). self deny: ('bozo' matches: 'foo*'). self assert: ('foo23baz' matches: 'foo*baz'). self assert: ('foobaz' matches: 'foo*baz'). self deny: ('foo23bazo' matches: 'foo*baz'). self assert: ('Foo' matches: 'foo'). self deny: ('foobazort' matches: 'foo*baz*zort'). self assert: ('foobazzort' matches: 'foo*baz*zort'). self assert: ('afoo3zortthenfoo3zort' matches: '*foo#zort'). self assert: ('afoodezortorfoo3zort' matches: '*foo*zort') ] testMoveDown [ | col | col := Array with: 1 with: 2 with: 3. self assert: (col moveDown: 1) = 2. self assert: col = #(2 1 3). self assert: (col moveDown: 1) = 3. self assert: col = #(2 3 1). self assert: (col moveDown: 1) = 3. self assert: col = #(2 3 1). self assert: (col moveDown: 0) = 0. self assert: col = #(2 3 1) ] testMoveUp [ | col | col := Array with: 1 with: 2 with: 3. self assert: (col moveUp: 3) = 2. self assert: col = #(1 3 2). self assert: (col moveUp: 3) = 1. self assert: col = #(3 1 2). self assert: (col moveUp: 3) = 1. self assert: col = #(3 1 2). self assert: (col moveUp: 0) = 0. self assert: col = #(3 1 2) ] testReduce [ self assert: (#() reduce: [:a :b | a]) isNil. self assert: ((1 to: 9) reduce: [:a :b | a]) = 1. self assert: ((1 to: 9) reduce: [:a :b | b]) = 9. self assert: ((1 to: 9) reduce: [:a :b | a + b]) = 45. self assert: ((1 to: 9) reduce: [:a :b | a * b]) = 362880. self assert: (#('a' 'b' 'c') reduce: [:a :b | a , ' ' , b]) = 'a b c'. self assert: (#('a' 'b' 'c') reduce: [:a :b | b , ' ' , a]) = 'c b a' ] testValidationError [ | result | result := [MARequiredError signal: 'some message'] on: MARequiredError do: [:err | err displayString]. self assert: result = 'some message'. result := [MARequiredError description: ((MAStringDescription new) label: 'label'; yourself) signal: 'some message'] on: MARequiredError do: [:err | err displayString]. self assert: result = 'label: some message' ] ] TestCase subclass: MAFileModelTest [ | model | MAFileModelTest class >> isAbstract [ ^self name = #MAFileModelTest ] actualClass [ ^self subclassResponsibility ] setUp [ super setUp. model := self actualClass new ] tearDown [ model finalize ] testComparing [ | other | other := self actualClass new. other filename: 'something.dat'; contents: (ByteArray with: 1 with: 2 with: 3). self assert: model = model. self deny: model = other. self deny: other = model. other finalize "should be in tearDown; for now, at least let's discard when we pass" ] testContents [ self assert: model contents isEmpty. model contents: (ByteArray with: 1 with: 2 with: 3). self assert: model contents = (ByteArray with: 1 with: 2 with: 3). self assert: model filesize = 3 ] testFilename [ self assert: model filename = 'unknown'. self assert: model extension isEmpty. model filename: 'test.txt'. self assert: model filename = 'test.txt'. self assert: model extension = 'txt' ] testIsEmpty [ self assert: model isEmpty. model filename: 'foo.txt'. self assert: model isEmpty. model mimetype: 'text/plain'. self assert: model isEmpty. model contents: 'hello'. self deny: model isEmpty ] testMimetype [ self assert: model mimetype = 'application/octet-stream'. self assert: model maintype = 'application'. self assert: model subtype = 'octet-stream'. model mimetype: 'text/html'. self assert: model mimetype = 'text/html'. self assert: model maintype = 'text'. self assert: model subtype = 'html' ] testMimetypeApplication [ model mimetype: 'application/pdf'. self assert: model isApplication. self deny: model isAudio. self deny: model isImage. self deny: model isText. self deny: model isVideo ] testMimetypeAudio [ model mimetype: 'audio/mpeg'. self deny: model isApplication. self assert: model isAudio. self deny: model isImage. self deny: model isText. self deny: model isVideo ] testMimetypeDefault [ self assert: model isApplication. self deny: model isAudio. self deny: model isImage. self deny: model isText. self deny: model isVideo ] testMimetypeImage [ model mimetype: 'image/png'. self deny: model isApplication. self deny: model isAudio. self assert: model isImage. self deny: model isText. self deny: model isVideo ] testMimetypeText [ model mimetype: 'text/xml'. self deny: model isApplication. self deny: model isAudio. self deny: model isImage. self assert: model isText. self deny: model isVideo ] testMimetypeVideo [ model mimetype: 'video/mpeg'. self deny: model isApplication. self deny: model isAudio. self deny: model isImage. self deny: model isText. self assert: model isVideo ] ] MAFileModelTest subclass: MAExternalFileModelTest [ actualClass [ ^MAExternalFileModel ] ] MAFileModelTest subclass: MAMemoryFileModelTest [ actualClass [ ^MAMemoryFileModel ] ] TestCase subclass: MAObjectTest [ MAObjectTest class >> buildTestClassFor: aClass [ "self buildTestClassFor: MAObject" | thisName thisClass thisCategory parentClass | thisName := (aClass name , 'Test') asSymbol. (thisName beginsWith: 'MA') ifFalse: [^self]. thisClass := MACompatibility classNamed: thisName. thisCategory := 'Magritte-Tests-' , (aClass category copyAfterLast: $-). parentClass := self = thisClass ifTrue: [self superclass] ifFalse: [MACompatibility classNamed: (aClass superclass name , 'Test') asSymbol]. thisClass := parentClass subclass: thisName instanceVariableNames: (thisClass isNil ifFalse: [thisClass instanceVariablesString] ifTrue: [String new]) classVariableNames: '' poolDictionaries: '' category: thisCategory. thisClass compile: 'actualClass ^ ' , aClass name classified: #private. thisClass class compile: 'isAbstract ^ ' , aClass isAbstract asString classified: #testing. aClass subclassesDo: [:each | self buildTestClassFor: each] ] MAObjectTest class >> isAbstract [ ^true ] MAObjectTest class >> shouldInheritSelectors [ ^true ] actualClass [ ^MAObject ] instance [ self subclassResponsibility ] testCopy [ self assert: self instance = self instance copy. self deny: self instance == self instance copy ] testCopyProperties [ self deny: self instance properties == self instance copy properties ] testEqual [ self assert: self instance = self instance. self assert: self instance = self instance copy. self assert: self instance copy = self instance. self deny: self instance = 123. self deny: self instance = String new ] testHash [ self assert: self instance hash isInteger. self assert: self instance hash = self instance hash. self assert: self instance hash = self instance copy hash ] testIsDescription [ self deny: self instance isDescription ] testProperties [ self assert: self instance properties notNil. self instance instVarNamed: 'properties' put: nil. self instance propertyAt: #foo put: #bar. self instance instVarNamed: 'properties' put: nil. self instance propertyAt: #foo ifAbsent: [nil]. self instance instVarNamed: 'properties' put: nil. self instance propertyAt: #foo ifAbsentPut: [#bar]. self instance instVarNamed: 'properties' put: nil. self instance hasProperty: #foo. self instance instVarNamed: 'properties' put: nil ] testPropertiesAt [ self assert: (self instance propertyAt: #foo put: 'bar') = 'bar'. self assert: (self instance propertyAt: #foo) = 'bar'. self should: [self instance propertyAt: #bar] raise: MAPropertyError ] testPropertiesAtIfAbsent [ self assert: (self instance propertyAt: #foo put: 'bar') = 'bar'. self assert: (self instance propertyAt: #foo ifAbsent: ['baz']) = 'bar'. self assert: (self instance propertyAt: #bar ifAbsent: ['baz']) = 'baz' ] testPropertiesAtIfAbsentPut [ self assert: (self instance propertyAt: #foo put: 'bar') = 'bar'. self assert: (self instance propertyAt: #foo ifAbsentPut: ['baz']) = 'bar'. self assert: (self instance propertyAt: #foo) = 'bar'. self assert: (self instance propertyAt: #bar ifAbsentPut: ['baz']) = 'baz'. self assert: (self instance propertyAt: #bar) = 'baz' ] testPropertiesAtIfPresent [ self assert: (self instance propertyAt: #foo ifPresent: [:value | self assert: false]) isNil. self instance propertyAt: #foo put: 1. self assert: (self instance propertyAt: #foo ifPresent: [:value | self assert: value = 1. 2]) = 2 ] testPropertiesAtPut [ self instance propertyAt: #foo put: 'bar'. self assert: (self instance propertyAt: #foo) = 'bar'. self instance propertyAt: #foo put: 'baz'. self assert: (self instance propertyAt: #foo) = 'baz' ] testPropertiesHas [ self deny: (self instance hasProperty: #foo). self instance propertyAt: #foo put: 'bar'. self assert: (self instance hasProperty: #foo). self deny: (self instance hasProperty: #bar) ] testSanity [ "If this test case fails, there is something wrong with the setup of the test-case." self assert: self actualClass isAbstract not description: 'Unable to test abstract class.'. self assert: self instance class = self actualClass description: 'Invalid test instance.' ] ] MAObjectTest subclass: MAAccessorTest [ | accessor value | MAAccessorTest class >> isAbstract [ ^true ] accessor [ ^accessor ] accessorInstance [ self subclassResponsibility ] actualClass [ ^MAAccessor ] instance [ ^accessor ] setUp [ super setUp. accessor := self accessorInstance ] testAsAccessor [ self assert: self instance asAccessor = self instance. self assert: self instance asAccessor == self instance ] testCanRead [ self subclassResponsibility ] testCanWrite [ self subclassResponsibility ] testRead [ self subclassResponsibility ] testStore [ self assert: (Behavior evaluate: self accessor storeString) = self accessor ] testWrite [ self subclassResponsibility ] value [ ^value ] value: anObject [ value := anObject ] ] MAAccessorTest subclass: MADelegatorAccessorTest [ MADelegatorAccessorTest class >> isAbstract [ ^false ] accessorInstance [ ^self actualClass on: (MASelectorAccessor selector: #value) ] actualClass [ ^MADelegatorAccessor ] testCanRead [ self assert: (self accessor canRead: self). self accessor next readSelector: #zork. self deny: (self accessor canRead: self) ] testCanWrite [ self assert: (self accessor canWrite: self). self accessor next writeSelector: #zork:. self deny: (self accessor canWrite: self) ] testRead [ self value: 123. self assert: (self accessor read: self) = 123. self value: '123'. self assert: (self accessor read: self) = '123' ] testWrite [ self accessor write: 123 to: self. self assert: self value = 123. self accessor write: '123' to: self. self assert: self value = '123' ] ] MADelegatorAccessorTest subclass: MAChainAccessorTest [ MAChainAccessorTest class >> isAbstract [ ^false ] accessorInstance [ ^self actualClass accessors: #(#holder #contents #value) ] actualClass [ ^MAChainAccessor ] holder [ ^(ValueHolder new) contents: self; yourself ] testAccessor [ self accessor accessor: self. self assert: self accessor accessor = self ] testAsAccessor [ super testAsAccessor. accessor := #(#value) asAccessor. self assert: (accessor isKindOf: MASelectorAccessor). self assert: accessor selector = #value. accessor := #(#value #contents) asAccessor. self assert: (accessor isKindOf: MAChainAccessor). self assert: (accessor next isKindOf: MASelectorAccessor). self assert: accessor next selector = #value. self assert: (accessor accessor isKindOf: MASelectorAccessor). self assert: accessor accessor selector = #contents ] testCanRead [ self assert: (self accessor canRead: self). self accessor accessor accessor readSelector: #zork. self deny: (self accessor canRead: self) ] testCanWrite [ self assert: (self accessor canWrite: self). self accessor accessor accessor writeSelector: #zork. self deny: (self accessor canWrite: self) ] testKind [ self assert: self accessor class = MAChainAccessor. self assert: self accessor next class = MASelectorAccessor. self assert: self accessor accessor class = MAChainAccessor. self assert: self accessor accessor next class = MASelectorAccessor. self assert: self accessor accessor accessor class = MASelectorAccessor ] testNext [ | next | next := #foo asAccessor. self accessor next: next. self assert: self accessor next = next ] testRead [ self value: 123. self assert: (self accessor read: self) = 123. self value: '12'. self assert: (self accessor read: self) = '12' ] testSelector [ self assert: self accessor next selector = #holder. self assert: self accessor accessor next selector = #contents. self assert: self accessor accessor accessor selector = #value ] testWrite [ self accessor write: 123 to: self. self assert: self value = 123. self accessor write: '123' to: self. self assert: self value = '123' ] ] MAAccessorTest subclass: MADictionaryAccessorTest [ MADictionaryAccessorTest class >> isAbstract [ ^false ] accessorInstance [ ^self actualClass key: #value ] actualClass [ ^MADictionaryAccessor ] at: aKey ifAbsent: aBlock [ ^aKey = #value ifTrue: [value] ifFalse: [aBlock value] ] at: aKey put: aValue [ self assert: aKey = #value. ^value := aValue ] testCanRead [ self assert: (self accessor canRead: self). self accessor key: #zork. self assert: (self accessor canRead: self) ] testCanWrite [ self assert: (self accessor canWrite: self) ] testKey [ self accessor key: #other. self assert: self accessor key = #other ] testRead [ self value: 123. self assert: (self accessor read: self) = 123. self value: '12'. self assert: (self accessor read: self) = '12' ] testWrite [ self accessor write: 123 to: self. self assert: self value = 123. self accessor write: '123' to: self. self assert: self value = '123' ] ] MAAccessorTest subclass: MAIdentityAccessorTest [ MAIdentityAccessorTest class >> isAbstract [ ^false ] accessorInstance [ ^self actualClass new ] actualClass [ ^MAIdentityAccessor ] testCanRead [ self assert: (self accessor canRead: self) ] testCanWrite [ self deny: (self accessor canWrite: self) ] testRead [ self assert: (self accessor read: 123) = 123 ] testWrite [ self should: [self accessor write: 123 to: self] raise: MAWriteError. self assert: self value isNil ] ] MAAccessorTest subclass: MANullAccessorTest [ MANullAccessorTest class >> isAbstract [ ^false ] accessorInstance [ ^self actualClass new ] actualClass [ ^MANullAccessor ] testAsAccessor [ super testAsAccessor. self assert: (nil asAccessor isKindOf: self actualClass) ] testCanRead [ self deny: (self accessor canRead: self) ] testCanWrite [ self deny: (self accessor canWrite: nil) ] testRead [ self should: [self accessor read: self] raise: MAReadError ] testWrite [ self should: [self accessor write: 123 to: self] raise: MAWriteError. self assert: self value isNil ] ] MAAccessorTest subclass: MAPluggableAccessorTest [ MAPluggableAccessorTest class >> isAbstract [ ^false ] accessorInstance [ ^self actualClass read: [:model | model value] write: [:model :object | model value: object] ] actualClass [ ^MAPluggableAccessor ] testCanRead [ self assert: (self instance canRead: self). self instance readBlock: nil. self deny: (self instance canRead: self) ] testCanWrite [ self assert: (self instance canWrite: nil). self assert: (self instance canWrite: 123). self assert: (self instance canWrite: self). self instance writeBlock: nil. self deny: (self instance canWrite: nil). self deny: (self instance canWrite: 123). self deny: (self instance canWrite: self) ] testRead [ self value: 123. self assert: (self accessor read: self) = 123. self value: '12'. self assert: (self accessor read: self) = '12' ] testReadBlock [ self accessor readBlock: [:model | self assert: model = self. 123]. self assert: (self accessor read: self) = 123 ] testStore [ "The class BlockContext is not serializeable, ignore this test." ] testWrite [ self accessor write: 123 to: self. self assert: self value = 123. self accessor write: '123' to: self. self assert: self value = '123' ] testWriteBlock [ self accessor writeBlock: [:model :object | self assert: model = self. self assert: object = 123]. self accessor write: 123 to: self ] ] MAAccessorTest subclass: MASelectorAccessorTest [ MASelectorAccessorTest class >> isAbstract [ ^false ] accessorInstance [ ^self actualClass selector: #value ] actualClass [ ^MASelectorAccessor ] testAsAccessor [ super testAsAccessor. self assert: #value asAccessor = self instance. self deny: #value asAccessor == self instance ] testCanRead [ self assert: (self accessor canRead: self). self accessor readSelector: #zork. self deny: (self accessor canRead: self). self accessor readSelector: nil. self deny: (self accessor canRead: self) ] testCanWrite [ self assert: (self accessor canWrite: self). self accessor writeSelector: #zork:. self deny: (self accessor canWrite: self). self accessor writeSelector: nil. self deny: (self accessor canWrite: self) ] testRead [ self value: 123. self assert: (self accessor read: self) = 123. self value: '12'. self assert: (self accessor read: self) = '12' ] testReadSelector [ self accessor readSelector: #contents. self assert: self accessor selector = #contents. self assert: self accessor readSelector = #contents. self assert: self accessor writeSelector = #value: ] testSelector [ self accessor selector: #contents. self assert: self accessor selector = #contents. self assert: self accessor readSelector = #contents. self assert: self accessor writeSelector = #contents: ] testWrite [ self accessor write: 123 to: self. self assert: self value = 123. self accessor write: '123' to: self. self assert: self value = '123' ] testWriteSelector [ self accessor writeSelector: #contents:. self assert: self accessor selector = #value. self assert: self accessor readSelector = #value. self assert: self accessor writeSelector = #contents: ] ] MASelectorAccessorTest subclass: MAAutoSelectorAccessorTest [ | mock foo | MAAutoSelectorAccessorTest class >> isAbstract [ ^false ] actualClass [ ^MAAutoSelectorAccessor ] foo: anObject [ foo := anObject ] mock [ ^mock ] mockInstance [ ^MAAccessorMock new ] runCase [ mock := self mockInstance. super runCase ] tearDown [ super tearDown. "remove methods and category" (self mock class selectors select: [ :each | (self mock class >> each) methodCategory = self accessor categoryName ]) do: [:each | self mock class removeSelector: each]. "remove instance variables" self mock class instVarNames do: [:each | self mock class removeInstVarName: each] ] testAsAccessor [ "noop" ] testReadFirst [ self accessor selector: #foo. self assert: (self accessor read: self mock) isNil. self accessor write: 123 to: self mock. self assert: (self accessor read: self mock) = 123 ] testWriteFirst [ self accessor selector: #foo. self accessor write: 123 to: self mock. self assert: (self accessor read: self mock) = 123 ] ] MAAccessorTest subclass: MAVariableAccessorTest [ MAVariableAccessorTest class >> isAbstract [ ^false ] accessorInstance [ ^self actualClass name: 'value' ] actualClass [ ^MAVariableAccessor ] testCanRead [ self assert: (self accessor canRead: self). self accessor name: 'zork'. self deny: (self accessor canRead: self) ] testCanWrite [ self assert: (self accessor canWrite: self). self accessor name: 'zork'. self deny: (self accessor canWrite: self) ] testName [ self accessor name: 'other'. self assert: self accessor name = 'other' ] testRead [ self value: 123. self assert: (self accessor read: self) = 123. self value: '12'. self assert: (self accessor read: self) = '12' ] testWrite [ self accessor write: 123 to: self. self assert: self value = 123. self accessor write: '123' to: self. self assert: self value = '123' ] ] MAObjectTest subclass: MADescriptionTest [ | description | MADescriptionTest class >> isAbstract [ ^true ] MADescriptionTest class >> shouldInheritSelectors [ ^true ] actualClass [ ^MADescription ] description [ ^description ] descriptionInstance [ ^(self actualClass new) accessor: MANullAccessor new; yourself ] instance [ ^description ] setUp [ super setUp. description := self descriptionInstance. self assert: description accessor notNil ] testAccessor [ self description accessor: (MASelectorAccessor selector: #foo). self assert: self description accessor selector = #foo ] testAsContainer [ self subclassResponsibility ] testComment [ self description comment: 'bar'. self assert: self description comment = 'bar' ] testCopyAccessor [ self assert: self description copy accessor = self description accessor. self deny: self description copy accessor == self description accessor ] testDictionaryKey [ | dictionary | dictionary := Dictionary new. dictionary at: self instance put: 1. self assert: (dictionary at: self instance) = 1. dictionary at: self instance put: 2. self assert: (dictionary at: self instance) = 2 ] testGroup [ self assert: self description group isNil. self description group: 'foo'. self assert: self description group = 'foo' ] testHasChildren [ self deny: self description hasChildren ] testHasComment [ self description comment: nil. self deny: self description hasComment. self description comment: ''. self deny: self description hasComment. self description comment: 'comment'. self assert: self description hasComment ] testHasLabel [ self description label: nil. self deny: self description hasLabel. self description label: ''. self deny: self description hasLabel. self description label: 'label'. self assert: self description hasLabel ] testIsContainer [ self deny: self description isContainer ] testIsDescription [ self assert: self description isDescription ] testLabel [ self description label: 'foo'. self assert: self description label = 'foo' ] testPriority [ self description priority: 123. self assert: self description priority = 123 ] testReadonly [ self description beReadonly. self assert: self description readonly. self assert: self description isReadonly. self description beWriteable. self deny: self description readonly. self deny: self description isReadonly ] testRequired [ self description beRequired. self assert: self description required. self assert: self description isRequired. self description beOptional. self deny: self description required. self deny: self description isRequired ] testSetElement [ | set | set := Set new. set add: self instance. self assert: set size = 1. self assert: (set includes: self instance). set add: self instance. self assert: set size = 1. self assert: (set includes: self instance) ] testVisible [ self description beHidden. self deny: self description visible. self deny: self description isVisible. self description beVisible. self assert: self description visible. self assert: self description isVisible ] ] MADescriptionTest subclass: MAContainerTest [ | child1 child2 child3 | MAContainerTest class >> isAbstract [ ^false ] actualClass [ ^MAContainer ] child1 [ ^child1 ifNil: [child1 := (MAStringDescription new) accessor: #child1; label: 'child1'; priority: 1; yourself] ] child2 [ ^child2 ifNil: [child2 := (MAStringDescription new) accessor: #child2; label: 'child2'; priority: 2; yourself] ] child3 [ ^child3 ifNil: [child3 := (MAStringDescription new) accessor: #child3; label: 'child3'; priority: 3; yourself] ] exampleInstance [ ^(MACachedMemento new) setDescription: self description; setCache: ((Dictionary new) at: self child1 put: nil; at: self child2 put: nil; at: self child3 put: nil; yourself); yourself ] testAdd [ self description add: self child1. self assert: self description size = 1. self assert: (self description includes: self child1). self description add: self child2. self assert: self description size = 2. self assert: (self description includes: self child1). self assert: (self description includes: self child2) ] testAddAll [ self description addAll: (Array with: self child1 with: self child2). self assert: self description size = 2. self assert: (self description includes: self child1). self assert: (self description includes: self child2) ] testAsContainer [ self assert: self description asContainer = self description. self assert: self description asContainer == self description ] testChildren [ self assert: self description children isCollection. self assert: self description children isEmpty ] testCollect [ | collected | (self description) add: self child1; add: self child2. collected := self description collect: [:each | each]. self assert: self description = collected. self deny: self description == collected. collected := self description collect: [:each | each copy]. self assert: self description = collected. self deny: self description == collected. collected := self description collect: [:each | (each copy) accessor: (MASelectorAccessor selector: #foo); yourself]. self deny: self description = collected. self deny: self description == collected ] testConcatenate [ | concatenate | concatenate := self child1 , self child2. self assert: concatenate size = 2. self assert: concatenate children first = self child1. self assert: concatenate children second = self child2. concatenate := self child1 , self child2 , self child3. self assert: concatenate size = 3. self assert: concatenate children first = self child1. self assert: concatenate children second = self child2. self assert: concatenate children third = self child3 ] testCopy [ (self description) add: self child1; add: self child2. super testCopy. self deny: self description copy children == self description children. self assert: self description copy children first = self description children first. self assert: self description copy children second = self description children second ] testCopyEmpty [ (self description) add: self child1; add: self child2. self assert: self description copyEmpty isEmpty ] testCopyFromTo [ | copied | (self description) add: self child1; add: self child2; add: self child3. copied := self description copyFrom: 2 to: 3. self assert: copied ~= self description. self assert: copied size = 2. self assert: copied children first = self child2. self assert: copied children second = self child3 ] testDetect [ self description add: self child1. self assert: (self description detect: [:each | self child1 = each]) = self child1. self should: [self description detect: [:each | self child2 = each]] raise: Error ] testDetectIfNone [ self description add: self child1. self assert: (self description detect: [:each | self child1 = each] ifNone: [123]) = self child1. self assert: (self description detect: [:each | self child2 = each] ifNone: [123]) = 123 ] testDo [ | collection | collection := self description class defaultCollection. (self description) add: self child1; add: self child2. self description do: [:each | collection add: each]. self assert: (self description children hasEqualElements: collection) ] testDoSepratedBy [ | collection | collection := OrderedCollection new. (self description) add: self child1; add: self child2. self description do: [:each | collection add: each] separatedBy: [collection add: nil]. self assert: collection size = 3. self assert: collection first = self child1. self assert: collection second isNil. self assert: collection third = self child2 ] testEmpty [ self assert: self description isEmpty. self description add: self child1. self deny: self description isEmpty ] testHasChildren [ super testHasChildren. self description add: self child1. self assert: self description hasChildren ] testIncludes [ self deny: (self description includes: self child1). self description add: self child1. self assert: (self description includes: self child1) ] testInjectInto [ (self description) add: self child1; add: self child2. self assert: (self description inject: 'start' into: [:result :each | result , ' ' , each label]) = 'start child1 child2' ] testIntersection [ | a b union | a := self child1 , self child2. b := self child2 , self child3. union := a intersection: b. self assert: union size = 1. self deny: (union includes: self child1). self assert: (union includes: self child2). self deny: (union includes: self child3) ] testIsContainer [ self assert: self description isContainer ] testKeysAndValuesDo [ (self description) add: self child1; add: self child2. self description keysAndValuesDo: [:index :each | index = 1 ifTrue: [self assert: self child1 = each] ifFalse: [index = 2 ifTrue: [self assert: self child2 = each] ifFalse: [self assert: false]]] ] testMoveDown [ (self description) add: self child1; add: self child2. self assert: self description children first = self child1. self assert: self description children second = self child2. self description moveDown: self child1. self assert: self description children first = self child2. self assert: self description children second = self child1. self description moveDown: self child1. self assert: self description children first = self child2. self assert: self description children second = self child1 ] testMoveUp [ (self description) add: self child1; add: self child2. self assert: self description children first = self child1. self assert: self description children second = self child2. self description moveUp: self child2. self assert: self description children first = self child2. self assert: self description children second = self child1. self description moveUp: self child2. self assert: self description children first = self child2. self assert: self description children second = self child1 ] testNoFailingValidation [ | example | (self description) add: self child1; add: self child2. example := self exampleInstance. self shouldnt: [example validate] raise: MAValidationError ] testNotEmpty [ self deny: self description notEmpty. self description add: self child1. self assert: self description notEmpty ] testOneFailingValidation [ | example | (self description) add: self child1; add: ((self child2) addCondition: [:v | self fail]; beRequired; yourself). example := self exampleInstance. self should: [example validate] raise: MAValidationError. [example validate] on: MAValidationError do: [:err | self assert: err class = MARequiredError. self assert: err tag = self child2. self assert: err isResumable. err resume] ] testReject [ | rejected | (self description) add: self child1; add: self child2. rejected := self description reject: [:each | false]. self assert: self description = rejected. rejected := self description reject: [:each | true]. self assert: rejected isEmpty ] testRemove [ (self description) add: self child1; add: self child2. self description remove: self child1. self assert: self description size = 1. self deny: (self description includes: self child1). self assert: (self description includes: self child2). self description remove: self child2. self assert: self description isEmpty ] testRemoveAll [ (self description) add: self child1; add: self child2. self description removeAll. self assert: self description isEmpty ] testSelect [ | selected | (self description) add: self child1; add: self child2. selected := self description select: [:each | true]. self assert: self description = selected. selected := self description select: [:each | false]. self assert: selected isEmpty ] testSize [ self assert: self description size = 0. self description add: self child1. self assert: self description size = 1. self description add: self child2. self assert: self description size = 2. self description add: self child3. self assert: self description size = 3 ] testTwoFailingValidation [ | example step | (self description) add: ((self child1) addCondition: [:v | self fail]; beRequired; yourself); add: ((self child2) addCondition: [:v | self fail]; beRequired; yourself). example := self exampleInstance. step := 1. self should: [example validate] raise: MAValidationError. [example validate] on: MAValidationError do: [:err | self assert: err class = MARequiredError. self assert: err isResumable. step = 1 ifTrue: [self assert: err tag = self child1]. step = 2 ifTrue: [self assert: err tag = self child2]. step = 3 ifTrue: [self fail]. step := step + 1. err resume] ] testUnion [ | a b union | a := self child1 , self child2. b := self child2 , self child3. union := a union: b. self assert: union size = 3. self assert: (union includes: self child1). self assert: (union includes: self child2). self assert: (union includes: self child3) ] testWithDo [ (self description) add: self child1; add: self child2. self description with: self description children do: [:first :second | self assert: first = second] ] ] MAContainerTest subclass: MAPriorityContainerTest [ MAPriorityContainerTest class >> isAbstract [ ^false ] actualClass [ ^MAPriorityContainer ] testMoveDown [ self should: [super testMoveDown] raise: Error ] testMoveUp [ self should: [super testMoveUp] raise: Error ] ] MADescriptionTest subclass: MAElementDescriptionTest [ MAElementDescriptionTest class >> isAbstract [ ^true ] actualClass [ ^MAElementDescription ] emptyInstance [ ^String new ] includedInstance [ self subclassResponsibility ] includedInstanceString [ ^MAStringWriter write: self includedInstance description: self descriptionInstance ] invalidInstance [ ^Object new ] invalidInstanceString [ ^self invalidInstance asString ] nullInstance [ ^nil ] shouldSkipStringTests [ ^false ] testAddCondition [ self description addCondition: [:value | value isNil]. self assert: self description conditions size = 1. self assert: self description conditions first value isString ] testAddConditionLabelled [ self description addCondition: [:value | value isNil] labelled: 'ist net nil'. self assert: self description conditions size = 1. self assert: self description conditions first value = 'ist net nil' ] testAsContainer [ self assert: self description asContainer size = 1. self assert: (self description asContainer includes: self description) ] testConcatenation [ | child1 child2 concatenate | child1 := self description copy. child2 := self description copy. concatenate := child1 , child2. self assert: concatenate size = 2. self assert: concatenate children first = child1. self assert: concatenate children second = child2. concatenate := child1 , concatenate. self assert: concatenate size = 3. self assert: concatenate children first = child1. self assert: concatenate children second = child1. self assert: concatenate children third = child2 ] testCopy [ super testCopy. self assert: self description copy default = self description default ] testDefault [ self description default: self includedInstance. self assert: self description default = self includedInstance ] testFromString [ self shouldSkipStringTests ifTrue: [^self]. self assert: (self description fromString: self includedInstanceString) = self includedInstance. self assert: (self description fromString: self includedInstanceString reader: self description stringReader) = self includedInstance. self assert: (self description fromString: self includedInstanceString reader: self description stringReader new) = self includedInstance ] testFromStringCollection [ self shouldSkipStringTests ifTrue: [^self]. self assert: (self description fromStringCollection: (Array with: self includedInstanceString with: self includedInstanceString)) = (Array with: self includedInstance with: self includedInstance). self assert: (self description fromStringCollection: (Array with: self includedInstanceString with: self includedInstanceString) reader: self description stringReader) = (Array with: self includedInstance with: self includedInstance) ] testFromStringEvaluated [ "This ensures that the parsing algorithm doesn't compile the input, what would cause a security hole in the framework." | error | error := nil. self shouldSkipStringTests ifTrue: [^self]. [self description fromString: '1 / 0. nil'] on: Exception do: [:err | error := err]. self deny: (error isKindOf: ZeroDivide) ] testFromStringInvalid [ self shouldSkipStringTests ifTrue: [^self]. self should: [self description fromString: self invalidInstanceString] raise: MAReadError ] testFromStringNull [ self shouldSkipStringTests ifTrue: [^self]. self assert: (self description fromString: self emptyInstance) isNil. self assert: (self description fromString: self emptyInstance reader: self description stringReader) isNil. self assert: (self description fromString: self emptyInstance reader: self description stringReader new) isNil ] testKind [ self assert: (self includedInstance isKindOf: self description kind) ] testKindErrorMessage [ self assert: self description kindErrorMessage notEmpty. self description kindErrorMessage: 'zork'. self assert: self description kindErrorMessage = 'zork'. [self description validateKind: self invalidInstance] on: MAKindError do: [:err | self assert: self description kindErrorMessage = err messageText] ] testRequiredErrorMessage [ self assert: self description requiredErrorMessage notEmpty. self description requiredErrorMessage: 'zork'. self assert: self description requiredErrorMessage = 'zork'. [(self description) beRequired; validateRequired: self nullInstance] on: MARequiredError do: [:err | self assert: self description requiredErrorMessage = err messageText] ] testSatisfied [ self assert: (self description isSatisfiedBy: self includedInstance). self assert: (self description isSatisfiedBy: self nullInstance). self deny: (self description isSatisfiedBy: self invalidInstance) ] testStringReader [ | object | self description stringReader: (object := MAStringReader new). self assert: self description stringReader = object ] testStringWriter [ | object | self description stringWriter: (object := MAStringWriter new). self assert: self description stringWriter = object ] testToString [ self shouldSkipStringTests ifTrue: [^self]. self assert: (self description toString: self includedInstance) = self includedInstanceString. self assert: (self description toString: self includedInstance writer: self description stringWriter) = self includedInstanceString. self assert: (self description toString: self includedInstance writer: self description stringWriter new) = self includedInstanceString ] testToStringCollection [ self shouldSkipStringTests ifTrue: [^self]. self assert: (self description toStringCollection: (Array with: self includedInstance with: self includedInstance)) = (Array with: self includedInstanceString with: self includedInstanceString). self assert: (self description toStringCollection: (Array with: self includedInstance with: self includedInstance) writer: self description stringWriter) = (Array with: self includedInstanceString with: self includedInstanceString) ] testToStringFromString [ self shouldSkipStringTests ifTrue: [^self]. self assert: (self description fromString: (self description toString: self includedInstance)) = self includedInstance. self assert: (self description fromString: (self description toString: self includedInstance writer: self description stringWriter) reader: self description stringReader) = self includedInstance. self assert: (self description fromString: (self description toString: self includedInstance writer: self description stringWriter new) reader: self description stringReader new) = self includedInstance ] testToStringNull [ self shouldSkipStringTests ifTrue: [^self]. self assert: (self description toString: self nullInstance) = self description undefined. self assert: (self description toString: self nullInstance writer: self description stringWriter) = self description undefined. self assert: (self description toString: self nullInstance writer: self description stringWriter new) = self description undefined ] testToStringUndefined [ self shouldSkipStringTests ifTrue: [^self]. self description undefined: 'n/a'. self assert: (self description toString: self nullInstance) = 'n/a'. self assert: (self description toString: self nullInstance writer: self description stringWriter) = 'n/a'. self assert: (self description toString: self nullInstance writer: self description stringWriter new) = 'n/a' ] testUndefined [ self description undefined: 'nop'. self assert: self description undefined = 'nop' ] testValidate [ self description beRequired. self shouldnt: [self description validate: self includedInstance] raise: MAValidationError. self should: [self description validate: self invalidInstance] raise: MAKindError. self should: [self description validate: self nullInstance] raise: MARequiredError ] testValidateConditions [ "This test might fail for MADateDescriptionTest, since there is a bug in Squeak." | object | object := self includedInstance. self description addCondition: [:value | object == value] labelled: 'included instance test'. self shouldnt: [self description validate: object] raise: MAConditionError. self should: [self description validate: object copy] raise: MAConditionError ] testValidateKind [ self should: [self description validateKind: self invalidInstance] raise: MAKindError. self shouldnt: [self description validateKind: self includedInstance] raise: MAKindError ] testValidateRequired [ self description beOptional. self shouldnt: [self description validateRequired: self nullInstance] raise: MARequiredError. self shouldnt: [self description validateRequired: self includedInstance] raise: MARequiredError. self description beRequired. self should: [self description validateRequired: self nullInstance] raise: MARequiredError. self shouldnt: [self description validateRequired: self includedInstance] raise: MARequiredError ] testValidateSpecific [ self shouldnt: [self description validate: self includedInstance] raise: MARequiredError ] ] MAElementDescriptionTest subclass: MABooleanDescriptionTest [ MABooleanDescriptionTest class >> isAbstract [ ^false ] actualClass [ ^MABooleanDescription ] includedInstance [ ^true ] testValidateConditions [ ] ] MAElementDescriptionTest subclass: MAClassDescriptionTest [ MAClassDescriptionTest class >> isAbstract [ ^false ] actualClass [ ^MAClassDescription ] includedInstance [ ^String ] shouldSkipStringTests [ ^true ] ] MAElementDescriptionTest subclass: MAFileDescriptionTest [ MAFileDescriptionTest class >> isAbstract [ ^false ] actualClass [ ^MAFileDescription ] includedInstance [ ^(MAMemoryFileModel new) contents: 'Lukas Renggli'; filename: 'author.txt'; yourself ] shouldSkipStringTests [ ^true ] ] MAElementDescriptionTest subclass: MAMagnitudeDescriptionTest [ MAMagnitudeDescriptionTest class >> isAbstract [ ^true ] actualClass [ ^MAMagnitudeDescription ] excludedInstance [ self subclassResponsibility ] maxInstance [ self subclassResponsibility ] minInstance [ self subclassResponsibility ] testInfToInf [ self assert: self description min isNil. self assert: self description max isNil. self assert: (self description isSatisfiedBy: self minInstance). self assert: (self description isSatisfiedBy: self includedInstance). self assert: (self description isSatisfiedBy: self maxInstance) ] testInfToVal [ self description max: self includedInstance. self assert: self description min isNil. self assert: self description max = self includedInstance. self assert: (self description isSatisfiedBy: self minInstance). self assert: (self description isSatisfiedBy: self includedInstance). self deny: (self description isSatisfiedBy: self maxInstance) ] testMax [ self description max: self maxInstance. self assert: self description max = self maxInstance ] testMin [ self description min: self minInstance. self assert: self description min = self minInstance ] testMinMax [ self description min: self minInstance max: self maxInstance. self assert: self description min = self minInstance. self assert: self description max = self maxInstance ] testRangeErrorMessage [ (self description) min: self minInstance; max: self maxInstance. self assert: self description rangeErrorMessage notEmpty. self description rangeErrorMessage: 'zork'. self assert: self description rangeErrorMessage = 'zork'. [self description validate: self excludedInstance] on: MARangeError do: [:err | self assert: self description rangeErrorMessage = err messageText] ] testRangeErrorMessageGenerated [ self description min: nil max: nil. self assert: self description rangeErrorMessage isNil. self description min: nil max: self maxInstance. self assert: self description rangeErrorMessage notEmpty. self description min: self minInstance max: nil. self assert: self description rangeErrorMessage notEmpty. self description min: self minInstance max: self maxInstance. self assert: self description rangeErrorMessage notEmpty ] testValToInf [ self description min: self includedInstance. self assert: self description min = self includedInstance. self assert: self description max isNil. self deny: (self description isSatisfiedBy: self minInstance). self assert: (self description isSatisfiedBy: self includedInstance). self assert: (self description isSatisfiedBy: self maxInstance) ] testValToVal [ self description min: self includedInstance. self description max: self includedInstance. self assert: self description min = self includedInstance. self assert: self description max = self includedInstance. self deny: (self description isSatisfiedBy: self minInstance). self assert: (self description isSatisfiedBy: self includedInstance). self deny: (self description isSatisfiedBy: self maxInstance) ] testValidateSpecific [ super testValidateSpecific. (self description) min: self minInstance; max: self maxInstance. self shouldnt: [self description validate: self includedInstance] raise: MARangeError. self should: [self description validate: self excludedInstance] raise: MARangeError ] ] MAMagnitudeDescriptionTest subclass: MADateDescriptionTest [ MADateDescriptionTest class >> isAbstract [ ^false ] actualClass [ ^MADateDescription ] excludedInstance [ ^Date newDay: 1 month: (Date nameOfMonth: 6) year: 1980 ] includedInstance [ ^Date newDay: 11 month: (Date nameOfMonth: 6) year: 1980 ] maxInstance [ ^Date newDay: 12 month: (Date nameOfMonth: 6) year: 1980 ] minInstance [ ^Date newDay: 10 month: (Date nameOfMonth: 6) year: 1980 ] ] MAMagnitudeDescriptionTest subclass: MADurationDescriptionTest [ MADurationDescriptionTest class >> isAbstract [ ^false ] actualClass [ ^MADurationDescription ] excludedInstance [ ^Duration days: 0 hours: 0 minutes: 0 seconds: 2 ] includedInstance [ ^Duration days: 1 hours: 2 minutes: 3 seconds: 4 ] maxInstance [ ^Duration days: 2 hours: 2 minutes: 3 seconds: 4 ] minInstance [ ^Duration days: 0 hours: 2 minutes: 3 seconds: 4 ] ] MAMagnitudeDescriptionTest subclass: MANumberDescriptionTest [ MANumberDescriptionTest class >> isAbstract [ ^false ] actualClass [ ^MANumberDescription ] excludedInstance [ ^0.618 ] includedInstance [ ^2.7182 ] maxInstance [ ^3.1415 ] minInstance [ ^1.618 ] testFromString [ "We do some special tests here because #visitNumberDescription: in MAStringReader works around problems with Number>>readFrom." self shouldSkipStringTests ifTrue: [^self]. super testFromString. self should: [self description fromString: 'xyz'] raise: MAReadError description: 'Non-numeric string should raise an error'. self should: [self description fromString: '12-234'] raise: MAReadError description: 'Non-numeric string should raise an error'. self should: [self description fromString: '1.4.2007'] raise: MAReadError description: 'Non-numeric string should raise an error'. self assert: (self description fromString: '') isNil description: 'Empty string should be parsed to nil'. self assert: (self description fromString: '-20') = -20 description: 'Negative numbers should be accepted' ] testValidateConditions [ ] ] MAMagnitudeDescriptionTest subclass: MATimeDescriptionTest [ MATimeDescriptionTest class >> isAbstract [ ^false ] actualClass [ ^MATimeDescription ] excludedInstance [ ^Time hour: 9 minute: 33 second: 12 ] includedInstance [ ^Time hour: 11 minute: 33 second: 12 ] maxInstance [ ^Time hour: 12 minute: 33 second: 12 ] minInstance [ ^Time hour: 10 minute: 33 second: 12 ] ] MAMagnitudeDescriptionTest subclass: MATimeStampDescriptionTest [ MATimeStampDescriptionTest class >> isAbstract [ ^false ] actualClass [ ^MATimeStampDescription ] excludedInstance [ ^DateTime year: 1980 month: 1 day: 11 hour: 11 minute: 38 second: 12 ] includedInstance [ ^DateTime year: 1980 month: 6 day: 11 hour: 11 minute: 38 second: 12 ] maxInstance [ ^DateTime year: 1980 month: 6 day: 12 hour: 11 minute: 38 second: 12 ] minInstance [ ^DateTime year: 1980 month: 6 day: 10 hour: 11 minute: 38 second: 12 ] ] MAElementDescriptionTest subclass: MAReferenceDescriptionTest [ MAReferenceDescriptionTest class >> isAbstract [ ^true ] actualClass [ ^MAReferenceDescription ] referenceInstance [ ^MAStringDescription new ] setUp [ super setUp. self description reference: self referenceInstance. self assert: self description reference accessor notNil ] testCopyReference [ self assert: self description copy reference = self description reference. self deny: self description copy reference == self description reference ] ] MAReferenceDescriptionTest subclass: MAOptionDescriptionTest [ MAOptionDescriptionTest class >> isAbstract [ ^true ] actualClass [ ^MAOptionDescription ] optionInstances [ ^Array with: 'foo' with: 'bar' with: 'zork' ] setUp [ super setUp. self description options: self optionInstances ] testAllOptions [ (self description) beRequired; beSorted; options: #(#c #b #a). self assert: self description allOptions = #(#a #b #c). (self description) beRequired; beUnsorted; options: #(#c #b #a). self assert: self description allOptions = #(#c #b #a) ] testAllOptionsWithExisting [ (self description) beRequired; options: #(#a #b #c). self assert: (self description allOptionsWith: #a) = #(#a #b #c) ] testAllOptionsWithNil [ (self description) beRequired; options: #(#a #b #c). self assert: (self description allOptionsWith: nil) = #(#a #b #c) ] testCopyOptions [ self deny: self description copy options == self description options. self assert: self description copy options = self description options ] testFromStringInvalid [ "There is no invalid string input." ] testOptions [ self description options: #(#a #b #c). self assert: self description options = #(#a #b #c) ] testOptionsAndLabels [ self description reference: MANumberDescription new. self assert: (self description labelForOption: 1) = '1'. self description optionsAndLabels: (Array with: 1 -> 'one' with: 2 -> 'two'). self assert: (self description labelForOption: 1) = 'one'. self assert: (self description labelForOption: 2) = 'two'. self assert: (self description labelForOption: 3) = '3' ] testReferencePrinting [ self description reference: MAStringDescription new. self assert: (self description labelForOption: 1) = '1'. self assert: (self description labelForOption: 1 @ 2) = '1@2'. self assert: (self description labelForOption: 1 -> 2) = '1->2' ] testSorted [ self description beSorted. self assert: self description isSorted. self assert: self description sorted. self description beUnsorted. self deny: self description isSorted. self deny: self description sorted ] ] MAOptionDescriptionTest subclass: MAMultipleOptionDescriptionTest [ MAMultipleOptionDescriptionTest class >> defaultUnique [ ^false ] MAMultipleOptionDescriptionTest class >> isAbstract [ ^false ] actualClass [ ^MAMultipleOptionDescription ] includedInstance [ ^self optionInstances copyFrom: 1 to: 2 ] testOrdered [ self description beOrdered. self assert: self description isOrdered. self assert: self description ordered. self description beUnordered. self deny: self description isOrdered. self deny: self description ordered ] testSorted [ self description beDistinct. self assert: self description isDistinct. self assert: self description distinct. self description beIndefinite. self deny: self description isDistinct. self deny: self description distinct ] ] MAOptionDescriptionTest subclass: MASingleOptionDescriptionTest [ MASingleOptionDescriptionTest class >> isAbstract [ ^false ] actualClass [ ^MASingleOptionDescription ] includedInstance [ ^self optionInstances first ] testAllOptionsOptional [ (self description) beOptional; beSorted; options: #(#c #b #a). self assert: self description allOptions = #(nil #a #b #c). (self description) beOptional; beUnsorted; options: #(#c #b #a). self assert: self description allOptions = #(nil #c #b #a) ] testAllOptionsWithExtensible [ (self description) beRequired; beUnsorted; beLimited; options: #(#c #d #a). self assert: (self description allOptionsWith: #b) = #(#c #d #a). (self description) beRequired; beUnsorted; beExtensible; options: #(#c #d #a). self assert: (self description allOptionsWith: #b) = #(#c #d #a #b). (self description) beRequired; beSorted; beLimited; options: #(#c #d #a). self assert: (self description allOptionsWith: #b) = #(#a #c #d). (self description) beRequired; beSorted; beExtensible; options: #(#c #d #a). self assert: (self description allOptionsWith: #b) = #(#a #b #c #d) ] testAllOptionsWithOptional [ (self description) beOptional; beSorted; beExtensible; options: #(#c #d #a). self assert: (self description allOptionsWith: #b) = #(nil #a #b #c #d). (self description) beOptional; beSorted; beLimited; options: #(#c #d #a). self assert: (self description allOptionsWith: #b) = #(nil #a #c #d). (self description) beOptional; beUnsorted; beExtensible; options: #(#c #d #a). self assert: (self description allOptionsWith: #b) = #(nil #c #d #a #b). (self description) beOptional; beUnsorted; beLimited; options: #(#c #d #a). self assert: (self description allOptionsWith: #b) = #(nil #c #d #a) ] testExtensible [ self description beExtensible. self assert: self description isExtensible. self assert: self description extensible. self description beLimited. self deny: self description isExtensible. self deny: self description extensible ] testGroupBy [ self deny: self description isGrouped. self description groupBy: #grouping. self assert: self description isGrouped ] testGroupOf [ self assert: MADateDescription grouping = 'Magnitude' ] ] MAReferenceDescriptionTest subclass: MARelationDescriptionTest [ MARelationDescriptionTest class >> isAbstract [ ^true ] actualClass [ ^MARelationDescription ] addressInstance1 [ ^(MAMockAddress new) street: 'Tillierstrasse 17'; plz: 3005; place: 'Bern'; yourself ] addressInstance2 [ ^(MAMockAddress new) street: 'In der Au'; plz: 8765; place: 'Engi'; yourself ] setUp [ super setUp. (self description) reference: MAMockAddress description; classes: (Array with: MAMockAddress) ] shouldSkipStringTests [ ^true ] testCopyClasses [ self assert: self description copy classes = self description classes. self deny: self description copy classes == self description classes ] ] MARelationDescriptionTest subclass: MAToManyRelationDescriptionTest [ MAToManyRelationDescriptionTest class >> isAbstract [ ^false ] actualClass [ ^MAToManyRelationDescription ] includedInstance [ ^Array with: self addressInstance1 with: self addressInstance2 ] testDefinitive [ self description beDefinitive. self assert: self description isDefinitive. self assert: self description definitive. self description beModifiable. self deny: self description isDefinitive. self deny: self description definitive ] testOrdered [ self description beOrdered. self assert: self description isOrdered. self assert: self description ordered. self description beUnordered. self deny: self description isOrdered. self deny: self description ordered ] testSorted [ self description beSorted. self assert: self description isSorted. self assert: self description sorted. self description beUnsorted. self deny: self description isSorted. self deny: self description sorted ] ] MAToManyRelationDescriptionTest subclass: MAToManyScalarRelationDescriptionTest [ actualClass [ ^MAToManyScalarRelationDescription ] includedInstance [ ^Array with: '1' with: '2' ] setUp [ super setUp. (self description) reference: ((MAStringDescription new) accessor: MANullAccessor new; yourself); classes: (Array with: String) ] ] MARelationDescriptionTest subclass: MAToOneRelationDescriptionTest [ MAToOneRelationDescriptionTest class >> isAbstract [ ^false ] actualClass [ ^MAToOneRelationDescription ] includedInstance [ ^self addressInstance1 ] ] MAReferenceDescriptionTest subclass: MATableDescriptionTest [ MATableDescriptionTest class >> isAbstract [ ^false ] actualClass [ ^MATableDescription ] includedInstance [ ^MATableModel rows: 3 columns: 3 contents: #('1' '2' '3' '2' '4' '6' '3' '6' '9') ] shouldSkipStringTests [ ^true ] ] MAReferenceDescriptionTest subclass: MATokenDescriptionTest [ MATokenDescriptionTest class >> isAbstract [ ^false ] actualClass [ ^MATokenDescription ] includedInstance [ ^#('foo' 'bar') ] testFromStringInvalid [ "There is no invalid string input." ] ] MAElementDescriptionTest subclass: MAStringDescriptionTest [ MAStringDescriptionTest class >> isAbstract [ ^false ] actualClass [ ^MAStringDescription ] includedInstance [ ^'Lukas Renggli' ] testFromStringInvalid [ "There is no invalid string input." ] ] MAStringDescriptionTest subclass: MAMemoDescriptionTest [ actualClass [ ^MAMemoDescription ] testLineCount [ self description lineCount: 123. self assert: self description lineCount = 123 ] ] MAStringDescriptionTest subclass: MAPasswordDescriptionTest [ MAPasswordDescriptionTest class >> isAbstract [ ^false ] actualClass [ ^MAPasswordDescription ] testIsObfuscated [ self deny: (self description isObfuscated: ''). self deny: (self description isObfuscated: nil). self deny: (self description isObfuscated: 123). self deny: (self description isObfuscated: '**1'). self assert: (self description isObfuscated: '******') ] testObfuscated [ self assert: (self description obfuscated: nil) = ''. self assert: (self description obfuscated: 'zork') = '****'. self assert: (self description obfuscated: 'foobar') = '******' ] ] MAStringDescriptionTest subclass: MASymbolDescriptionTest [ MASymbolDescriptionTest class >> isAbstract [ ^false ] actualClass [ ^MASymbolDescription ] includedInstance [ ^#magritte ] testValidateConditions [ ] ] MAObjectTest subclass: MAMementoTest [ | description memento value | MAMementoTest class >> isAbstract [ ^true ] actualClass [ ^MAMemento ] defaultInstance [ ^'Lukas Renggli' ] description [ ^description ] descriptionInstance [ ^MAContainer with: ((MAStringDescription new) default: self defaultInstance; accessor: #value; yourself) ] descriptionValue [ ^self description children first ] includedInstance [ ^'Rene Magritte' ] instance [ ^memento ] invalidInstance [ ^31415 ] memento [ ^memento ] mementoInstance [ ^self actualClass model: self modelInstance ] modelInstance [ ^self ] nullInstance [ ^nil ] otherInstance [ ^'Ursula Freitag' ] read [ ^self memento readUsing: self descriptionValue ] setUp [ super setUp. description := self descriptionInstance. memento := self mementoInstance ] testCommit [ self subclassResponsibility ] testDescription [ self assert: self memento description = self description. self assert: self memento description = self descriptionInstance ] testModel [ self assert: self memento model = self modelInstance ] testRead [ self subclassResponsibility ] testReset [ self subclassResponsibility ] testValidateIncluded [ self write: self includedInstance. self shouldnt: [self memento validate] raise: MAValidationError ] testValidateInvalid [ self write: self invalidInstance. self should: [self memento validate] raise: MAValidationError ] testValidateRequired [ self descriptionValue beRequired. self write: self nullInstance. self should: [self memento validate] raise: MAValidationError ] testWrite [ self subclassResponsibility ] value [ ^value ] value: anObject [ value := anObject ] write: anObject [ self memento write: anObject using: self descriptionValue ] ] MAMementoTest subclass: MACachedMementoTest [ MACachedMementoTest class >> isAbstract [ ^false ] actualClass [ ^MACachedMemento ] testCache [ self assert: self memento cache size = self description size ] testCommit [ self write: self includedInstance. self assert: self read = self includedInstance. self assert: self value = self nullInstance. self assert: self memento hasChanged. self memento commit. self assert: self read = self includedInstance. self assert: self value = self includedInstance. self deny: self memento hasChanged ] testRead [ self assert: self read = self defaultInstance. self value: self includedInstance. self assert: self read = self defaultInstance ] testReset [ self value: self defaultInstance. self write: self includedInstance. self assert: self memento hasChanged. self memento reset. self assert: self read = self defaultInstance. self assert: self value = self defaultInstance. self deny: self memento hasChanged ] testWrite [ self write: self includedInstance. self assert: self read = self includedInstance. self assert: self value = self nullInstance. self write: self defaultInstance. self assert: self read = self defaultInstance. self assert: self value = self nullInstance ] ] MACachedMementoTest subclass: MACheckedMementoTest [ MACheckedMementoTest class >> isAbstract [ ^false ] actualClass [ ^MACheckedMemento ] testConflictCommit [ self write: self includedInstance. self assert: self read = self includedInstance. self assert: self memento hasChanged. self deny: self memento hasConflict. self value: self otherInstance. self assert: self read = self includedInstance. self assert: self memento hasChanged. self assert: self memento hasConflict. self memento commit. self assert: self read = self includedInstance. self assert: self value = self includedInstance. self deny: self memento hasChanged. self deny: self memento hasConflict ] testConflictReset [ self write: self includedInstance. self assert: self read = self includedInstance. self assert: self memento hasChanged. self deny: self memento hasConflict. self value: self otherInstance. self assert: self read = self includedInstance. self assert: self memento hasChanged. self assert: self memento hasConflict. self memento reset. self assert: self read = self otherInstance. self assert: self value = self otherInstance. self deny: self memento hasChanged. self deny: self memento hasConflict ] testOriginal [ self assert: self memento original size = self description size ] testValidateConflictCommit [ self write: self includedInstance. self shouldnt: [self memento validate] raise: MAValidationError. self value: self otherInstance. self should: [self memento validate] raise: MAValidationError. self memento commit. self shouldnt: [self memento validate] raise: MAValidationError ] testValidateConflictReset [ self write: self includedInstance. self shouldnt: [self memento validate] raise: MAValidationError. self value: self otherInstance. self should: [self memento validate] raise: MAValidationError. self memento reset. self shouldnt: [self memento validate] raise: MAValidationError ] ] MAMementoTest subclass: MAStraitMementoTest [ MAStraitMementoTest class >> isAbstract [ ^false ] actualClass [ ^MAStraitMemento ] testCommit [ self write: self includedInstance. self assert: self value = self includedInstance. self assert: self read = self includedInstance. self memento commit. self assert: self value = self includedInstance. self assert: self read = self includedInstance ] testRead [ self assert: self read = self defaultInstance. self value: self includedInstance. self assert: self read = self includedInstance. self value: self defaultInstance. self assert: self read = self defaultInstance ] testReset [ self write: self includedInstance. self memento reset. self assert: self read = self includedInstance ] testValidateRequired [ ] testWrite [ self write: self includedInstance. self assert: self value = self includedInstance. self write: self defaultInstance. self assert: self value = self defaultInstance. self write: self nullInstance. self assert: self value = self nullInstance ] ] TestCase subclass: MATableModelTest [ | table | setUp [ table := (MATableModel rows: 3 columns: 4) collect: [:row :col :value | row raisedTo: col] ] testAtAt [ self assert: (table at: 1 at: 1) = 1. self assert: (table at: 2 at: 3) = 8. self assert: (table at: 3 at: 2) = 9. self assert: (table at: 3 at: 4) = 81 ] testAtAtAbsent [ self should: [table at: 0 at: 1] raise: Error. self should: [table at: 1 at: 0] raise: Error. self should: [table at: 4 at: 4] raise: Error. self should: [table at: 3 at: 5] raise: Error ] testAtAtPut [ self assert: (table at: 1 at: 1 put: -1) = -1. self assert: (table at: 2 at: 3 put: -8) = -8. self assert: (table at: 3 at: 2 put: -9) = -9. self assert: (table at: 3 at: 4 put: -81) = -81. self assert: (table at: 1 at: 1) = -1. self assert: (table at: 2 at: 3) = -8. self assert: (table at: 3 at: 2) = -9. self assert: (table at: 3 at: 4) = -81 ] testAtAtPutAbsent [ self should: [table at: 0 at: 1 put: 0] raise: Error. self should: [table at: 1 at: 0 put: 0] raise: Error. self should: [table at: 4 at: 4 put: 0] raise: Error. self should: [table at: 3 at: 5 put: 0] raise: Error ] testCollect [ table := table collect: [:row :col :val | row + col + val]. table do: [:row :col :val | self assert: (row raisedTo: col) = (val - row - col)] ] testContents [ self assert: table contents = #(1 1 1 1 2 4 8 16 3 9 27 81) ] testCopy [ self assert: table copy rowCount = table rowCount. self assert: table copy columnCount = table columnCount. self assert: table copy contents = table contents. self deny: table copy contents == table contents ] testCopyEmpty [ self assert: table copyEmpty rowCount = table rowCount. self assert: table copyEmpty columnCount = table columnCount. self assert: (table copyEmpty contents allSatisfy: [:each | each isNil]) ] testCopyRowsColumns [ self assert: (table copyRows: 1 columns: 2) rowCount = 1. self assert: (table copyRows: 1 columns: 2) columnCount = 2. self assert: (table copyRows: 1 columns: 2) contents = #(1 1). self assert: (table copyRows: 4 columns: 3) rowCount = 4. self assert: (table copyRows: 4 columns: 3) columnCount = 3. self assert: (table copyRows: 4 columns: 3) contents = #(1 1 1 2 4 8 3 9 27 nil nil nil) ] testCoumnCount [ self assert: table columnCount = 4 ] testDo [ table do: [:row :col :val | self assert: (row raisedTo: col) = val] ] testEqual [ self assert: table = table. self assert: table = table copy. self assert: table copy = table. self assert: table copy = table copy. self deny: table = (table copy at: 1 at: 2 put: 3). self deny: table = (table copyRows: 3 columns: 3). self deny: table = (table copyRows: 4 columns: 4) ] testHash [ self assert: table hash = table hash. self assert: table hash = table copy hash. self assert: table copy hash = table hash. self assert: table copy hash = table copy hash ] testRowCount [ self assert: table rowCount = 3 ] testSetup [ self assert: table rowCount = 3. self assert: table columnCount = 4. self assert: table contents = #(1 1 1 1 2 4 8 16 3 9 27 81) ] ] smalltalk-3.2.5/packages/magritte/stamp-classes0000644000175000017500000000000012123404352016504 00000000000000smalltalk-3.2.5/packages/magritte/package.xml0000644000175000017500000000074312123404352016135 00000000000000 Magritte Magritte Magritte.MAAdaptiveModelTest* Magritte.MADescriptionBuilderTest* Magritte.MADynamicObjectTest* Magritte.MAExtensionsTest* Magritte.MAFileModelTest* Magritte.MAObjectTest* Magritte.MATableModelTest* magritte-tests.st magritte-gst.st magritte-model.st PORTING ChangeLog smalltalk-3.2.5/packages/gdbm/0000755000175000017500000000000012130456012013167 500000000000000smalltalk-3.2.5/packages/gdbm/Makefile.frag0000644000175000017500000000031212123404352015463 00000000000000GDBM_FILES = \ packages/gdbm/gdbm.st packages/gdbm/gdbm-c.st packages/gdbm/gdbmtests.st $(GDBM_FILES): $(srcdir)/packages/gdbm/stamp-classes: $(GDBM_FILES) touch $(srcdir)/packages/gdbm/stamp-classes smalltalk-3.2.5/packages/gdbm/gdbmtests.st0000644000175000017500000001430712123404352015462 00000000000000"====================================================================== | | GDBM tests declarations | | ======================================================================" "====================================================================== | | Copyright 2007 Free Software Foundation, Inc. | Written by Paolo Bonzini | | This file is part of GNU Smalltalk. | | GNU Smalltalk is free software; you can redistribute it and/or modify it | under the terms of the GNU General Public License as published by the Free | Software Foundation; either version 2, or (at your option) any later version. | | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS | FOR A PARTICULAR PURPOSE. See the GNU General Public License for more | details. | | You should have received a copy of the GNU General Public License along with | GNU Smalltalk; see the file COPYING. If not, write to the Free Software | Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. | ======================================================================" TestCase subclass: GDBMTest [ data [ ^ {'fred' -> 'Fred Flintstone'. 'wilma' -> 'Wilma Flintstone'} ] setUp [ self cInterfaceSetup. self stInterfaceSetup ] tearDown [ (File exists: 'test-c.gdbm') ifTrue: [File remove: 'test-c.gdbm']. (File exists: 'test-st.gdbm') ifTrue: [File remove: 'test-st.gdbm'] ] cInterfaceSetup [ | database key value | (File exists: 'test-c.gdbm') ifTrue: [File remove: 'test-c.gdbm']. database := GDBM open: 'test-c.gdbm' blockSize: 1024 flags: 2 mode: 438 fatalFunc: nil. "write/create" self data do: [:each | key := DatumStruct fromString: each key. value := DatumStruct fromString: each value. database at: key put: value flag: 1. "replace" key free. value free]. database close ] stInterfaceSetup [ | database | (File exists: 'test-st.gdbm') ifTrue: [File remove: 'test-st.gdbm']. database := Database writeCreate: 'test-st.gdbm' blockSize: 1024 mode: 438. self data do: [:each | database at: each key put: each value]. database close ] doTestCInterfaceAt: name [ | database key value | database := GDBM open: name blockSize: 1024 flags: 0 mode: 438 fatalFunc: nil. "read" value := database at: (DatumStruct fromString: 'wilma'). self assert: value asString = 'Wilma Flintstone'. value free. value := database at: (DatumStruct fromString: 'barney'). self assert: value dPtr value isNil. self assert: value asString = ''. value free. database close ] doTestCInterfaceWalkKeys: name [ | database newItem item value result | database := GDBM open: name blockSize: 1024 flags: 0 mode: 438 fatalFunc: nil. "read" result := SortedCollection sortBlock: [:a :b | a key <= b key]. item := database firstKey. [item dPtr value notNil] whileTrue: [value := database at: item. result add: item asString -> value asString. value free. newItem := database nextKey: item. item free. item := newItem]. item free. database close. self assert: (result at: 1) = ('fred' -> 'Fred Flintstone'). self assert: (result at: 2) = ('wilma' -> 'Wilma Flintstone') ] doTestCInterfaceAfter: name [ | database newItem item value result | database := GDBM open: name blockSize: 1024 flags: 0 mode: 438 fatalFunc: nil. "read" result := OrderedCollection new. item := database firstKey. [item dPtr value notNil] whileTrue: [result add: item asString -> nil. newItem := database nextKey: item. result last value: (newItem dPtr value ifNotNil: [:ignored | newItem asString]). item free. item := newItem]. item free. database close. self assert: (result at: 1) value = (result at: 2) key. self assert: (result at: 2) value isNil ] doTestAt: name [ | database | database := Database read: name blockSize: 1024 mode: 438. self assert: (database at: 'wilma') = 'Wilma Flintstone'. self assert: (database at: 'barney' ifAbsent: [nil]) isNil. database close ] doTestKeysAndValuesDo: name [ | database newItem item value result | database := Database read: name blockSize: 1024 mode: 438. result := SortedCollection sortBlock: [:a :b | a key <= b key]. database keysAndValuesDo: [:item :value | result add: item -> value]. database close. self assert: (result at: 1) = ('fred' -> 'Fred Flintstone'). self assert: (result at: 2) = ('wilma' -> 'Wilma Flintstone') ] doTestAfter: name [ | database newItem item value result | database := Database read: name blockSize: 1024 mode: 438. result := OrderedCollection new. database keysAndValuesDo: [:item :value | result add: item -> (database after: item)]. database close. self assert: (result at: 1) value = (result at: 2) key. self assert: (result at: 2) value isNil ] testCInterfaceAt [ self doTestCInterfaceAt: 'test-c.gdbm'. self doTestCInterfaceAt: 'test-st.gdbm' ] testCInterfaceWalkKeys [ self doTestCInterfaceWalkKeys: 'test-c.gdbm'. self doTestCInterfaceWalkKeys: 'test-st.gdbm' ] testCInterfaceAfter [ self doTestCInterfaceAfter: 'test-c.gdbm'. self doTestCInterfaceAfter: 'test-st.gdbm' ] testAt [ self doTestAt: 'test-c.gdbm'. self doTestAt: 'test-st.gdbm' ] testKeysAndValuesDo [ self doTestKeysAndValuesDo: 'test-c.gdbm'. self doTestKeysAndValuesDo: 'test-st.gdbm' ] testAfter [ self doTestAfter: 'test-c.gdbm'. self doTestAfter: 'test-st.gdbm' ] ] smalltalk-3.2.5/packages/gdbm/ChangeLog0000644000175000017500000000031212123404352014657 000000000000002010-12-04 Paolo Bonzini * package.xml: Remove now superfluous tags. 2007-08-13 Paolo Bonzini * gdbm-c.st: Switch to the new syntax for "returning:". smalltalk-3.2.5/packages/gdbm/gdbm.c0000644000175000017500000001265712123404352014201 00000000000000/*********************************************************************** * * GDBM interface definitions for GNU Smalltalk * * ***********************************************************************/ /*********************************************************************** * * Copyright 1988,89,90,91,92,94,95,99,2000,2001,2002,2006 * Free Software Foundation, Inc. * Written by Steve Byrne. * * This file is part of GNU Smalltalk. * * GNU Smalltalk is free software; you can redistribute it and/or modify it * under the terms of the GNU General Public License as published by the Free * Software Foundation; either version 2, or (at your option) any later * version. * * Linking GNU Smalltalk statically or dynamically with other modules is * making a combined work based on GNU Smalltalk. Thus, the terms and * conditions of the GNU General Public License cover the whole * combination. * * In addition, as a special exception, the Free Software Foundation * give you permission to combine GNU Smalltalk with free software * programs or libraries that are released under the GNU LGPL and with * independent programs running under the GNU Smalltalk virtual machine. * * You may copy and distribute such a system following the terms of the * GNU GPL for GNU Smalltalk and the licenses of the other code * concerned, provided that you include the source code of that other * code when and as the GNU GPL requires distribution of source code. * * Note that people who make modified versions of GNU Smalltalk are not * obligated to grant this special exception for their modified * versions; it is their choice whether to do so. The GNU General * Public License gives permission to release a modified version without * this exception; this exception also makes it possible to release a * modified version which carries forward this exception. * * GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or * FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for * more details. * * You should have received a copy of the GNU General Public License along with * GNU Smalltalk; see the file COPYING. If not, write to the Free Software * Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * ***********************************************************************/ #include "config.h" #include "gstpub.h" #include #include /* GDBM_FILE gdbm_open(name, block_size, flags, mode, fatal_func); void gdbm_close(dbf); int gdbm_store(dbf, key, content, flag); datum gdbm_fetch(dbf, key); int gdbm_delete(dbf, key); datum gdbm_firstkey(dbf); datum gdbm_nextkey(dbf, key); int gdbm_reorganize(dbf); void gdbm_sync(dbf); -- new int gdbm_exists(dbf, key); not present char *gdbm_strerror(errno); -- new int gdbm_setopt(dbf, option, value, size) -- new */ static int wrapped_gdbm_store (GDBM_FILE dbf, datum * key, datum * content, int flag); static datum * wrapped_gdbm_fetch (GDBM_FILE dbf, datum * key); static int wrapped_gdbm_delete (GDBM_FILE dbf, datum * key); static datum * wrapped_gdbm_nextkey (GDBM_FILE dbf, datum * key); static datum * wrapped_gdbm_firstkey (GDBM_FILE dbf); int wrapped_gdbm_store (GDBM_FILE dbf, datum * key, datum * content, int flag) { return gdbm_store (dbf, *key, *content, flag); } datum * wrapped_gdbm_fetch (GDBM_FILE dbf, datum * key) { datum *result; /* printf("key is %d\n", key->dsize); printf("key value is %s\n", key->dptr); */ result = (datum *) malloc (sizeof (datum)); *result = gdbm_fetch (dbf, *key); /* printf("result length is %d ptr is %x\n", result->dsize, result->dptr); */ return result; } int wrapped_gdbm_delete (GDBM_FILE dbf, datum * key) { return gdbm_delete (dbf, *key); } datum * wrapped_gdbm_firstkey (GDBM_FILE dbf) { datum *result; result = (datum *) malloc (sizeof (datum)); *result = gdbm_firstkey (dbf); return result; } datum * wrapped_gdbm_nextkey (GDBM_FILE dbf, datum * key) { datum *result; result = (datum *) malloc (sizeof (datum)); *result = gdbm_nextkey (dbf, *key); return result; } /* int wrapped_gdbm_exists(dbf, key) GDBM_FILE dbf; datum* key; { return gdbm_exists(dbf, *key); } */ void gst_initModule (VMProxy * vmProxy) { /* the use of the wrapped_ functions is an artifact of the limitation of C that you cannot reliably and portably synthesize a function call where some of the parameters are by-value structs. Other than the use of pointers to datums instead of by-value datum structures, the signatures are identical to the normal gdbm functions */ vmProxy->defineCFunc ("gdbm_open", gdbm_open); vmProxy->defineCFunc ("gdbm_close", gdbm_close); vmProxy->defineCFunc ("gdbm_store", wrapped_gdbm_store); vmProxy->defineCFunc ("gdbm_fetch", wrapped_gdbm_fetch); vmProxy->defineCFunc ("gdbm_delete", wrapped_gdbm_delete); vmProxy->defineCFunc ("gdbm_firstkey", wrapped_gdbm_firstkey); vmProxy->defineCFunc ("gdbm_nextkey", wrapped_gdbm_nextkey); vmProxy->defineCFunc ("gdbm_reorganize", gdbm_reorganize); /* vmProxy->defineCFunc("gdbm_sync", gdbm_sync); not universal */ /* vmProxy->defineCFunc("gdbm_exists", wrapped_gdbm_exists); not universal */ /* vmProxy->defineCFunc("gdbm_strerror", gdbm_strerror); not universal */ /* vmProxy->defineCFunc("gdbm_setopt", gdbm_setopt); not universal */ } smalltalk-3.2.5/packages/gdbm/Makefile.am0000644000175000017500000000047712123404352015155 00000000000000gst_module_ldflags = -rpath $(moduleexecdir) -release $(VERSION) -module \ -no-undefined -export-symbols-regex gst_initModule moduleexec_LTLIBRARIES = gdbm.la gdbm_la_SOURCES = gdbm.c gdbm_la_LIBADD = -lgdbm gdbm_la_LDFLAGS = $(gst_module_ldflags) AM_CPPFLAGS = -I$(top_srcdir)/libgst -I$(top_srcdir)/lib-src smalltalk-3.2.5/packages/gdbm/Makefile.in0000644000175000017500000005243312130455426015173 00000000000000# Makefile.in generated by automake 1.11.6 from Makefile.am. # @configure_input@ # Copyright (C) 1994, 1995, 1996, 1997, 1998, 1999, 2000, 2001, 2002, # 2003, 2004, 2005, 2006, 2007, 2008, 2009, 2010, 2011 Free Software # Foundation, Inc. # This Makefile.in is free software; the Free Software Foundation # gives unlimited permission to copy and/or distribute it, # with or without modifications, as long as this notice is preserved. # This program is distributed in the hope that it will be useful, # but WITHOUT ANY WARRANTY, to the extent permitted by law; without # even the implied warranty of MERCHANTABILITY or FITNESS FOR A # PARTICULAR PURPOSE. @SET_MAKE@ VPATH = @srcdir@ am__make_dryrun = \ { \ am__dry=no; \ case $$MAKEFLAGS in \ *\\[\ \ ]*) \ echo 'am--echo: ; @echo "AM" OK' | $(MAKE) -f - 2>/dev/null \ | grep '^AM OK$$' >/dev/null || am__dry=yes;; \ *) \ for am__flg in $$MAKEFLAGS; do \ case $$am__flg in \ *=*|--*) ;; \ *n*) am__dry=yes; break;; \ esac; \ done;; \ esac; \ test $$am__dry = yes; \ } pkgdatadir = $(datadir)/@PACKAGE@ pkgincludedir = $(includedir)/@PACKAGE@ pkglibdir = $(libdir)/@PACKAGE@ pkglibexecdir = $(libexecdir)/@PACKAGE@ am__cd = CDPATH="$${ZSH_VERSION+.}$(PATH_SEPARATOR)" && cd install_sh_DATA = $(install_sh) -c -m 644 install_sh_PROGRAM = $(install_sh) -c install_sh_SCRIPT = $(install_sh) -c INSTALL_HEADER = $(INSTALL_DATA) transform = $(program_transform_name) NORMAL_INSTALL = : PRE_INSTALL = : POST_INSTALL = : NORMAL_UNINSTALL = : PRE_UNINSTALL = : POST_UNINSTALL = : build_triplet = @build@ host_triplet = @host@ subdir = packages/gdbm DIST_COMMON = $(srcdir)/Makefile.am $(srcdir)/Makefile.in ChangeLog ACLOCAL_M4 = $(top_srcdir)/aclocal.m4 am__aclocal_m4_deps = $(top_srcdir)/build-aux/bold.m4 \ $(top_srcdir)/build-aux/codeset.m4 \ $(top_srcdir)/build-aux/emacs-pkg.m4 \ $(top_srcdir)/build-aux/emacs-site-start.m4 \ $(top_srcdir)/build-aux/ext_goto.m4 \ $(top_srcdir)/build-aux/gawk.m4 $(top_srcdir)/build-aux/gcc.m4 \ $(top_srcdir)/build-aux/gl.m4 \ $(top_srcdir)/build-aux/glib-2.0.m4 \ $(top_srcdir)/build-aux/glut.m4 $(top_srcdir)/build-aux/gmp.m4 \ $(top_srcdir)/build-aux/gst-package.m4 \ $(top_srcdir)/build-aux/gtk-2.0.m4 \ $(top_srcdir)/build-aux/iconv.m4 \ $(top_srcdir)/build-aux/lib-ld.m4 \ $(top_srcdir)/build-aux/lib-link.m4 \ $(top_srcdir)/build-aux/lib-prefix.m4 \ $(top_srcdir)/build-aux/lib.m4 \ $(top_srcdir)/build-aux/libc-so-name.m4 \ $(top_srcdir)/build-aux/libtool.m4 \ $(top_srcdir)/build-aux/lightning.m4 \ $(top_srcdir)/build-aux/ln.m4 \ $(top_srcdir)/build-aux/localtime.m4 \ $(top_srcdir)/build-aux/lock.m4 \ $(top_srcdir)/build-aux/long-double.m4 \ $(top_srcdir)/build-aux/lrint.m4 \ $(top_srcdir)/build-aux/ltdl-gst.m4 \ $(top_srcdir)/build-aux/ltoptions.m4 \ $(top_srcdir)/build-aux/ltsugar.m4 \ $(top_srcdir)/build-aux/ltversion.m4 \ $(top_srcdir)/build-aux/lt~obsolete.m4 \ $(top_srcdir)/build-aux/modules.m4 \ $(top_srcdir)/build-aux/pkg.m4 $(top_srcdir)/build-aux/poll.m4 \ $(top_srcdir)/build-aux/readline.m4 \ $(top_srcdir)/build-aux/relocatable.m4 \ $(top_srcdir)/build-aux/setenv.m4 \ $(top_srcdir)/build-aux/snprintfv.m4 \ $(top_srcdir)/build-aux/sockets.m4 \ $(top_srcdir)/build-aux/sockpfaf.m4 \ $(top_srcdir)/build-aux/strtoul.m4 \ $(top_srcdir)/build-aux/sync-builtins.m4 \ $(top_srcdir)/build-aux/tcltk.m4 \ $(top_srcdir)/build-aux/version.m4 \ $(top_srcdir)/build-aux/vis-hidden.m4 \ $(top_srcdir)/build-aux/wine.m4 $(top_srcdir)/configure.ac am__configure_deps = $(am__aclocal_m4_deps) $(CONFIGURE_DEPENDENCIES) \ $(ACLOCAL_M4) mkinstalldirs = $(install_sh) -d CONFIG_HEADER = $(top_builddir)/config.h CONFIG_CLEAN_FILES = CONFIG_CLEAN_VPATH_FILES = am__vpath_adj_setup = srcdirstrip=`echo "$(srcdir)" | sed 's|.|.|g'`; am__vpath_adj = case $$p in \ $(srcdir)/*) f=`echo "$$p" | sed "s|^$$srcdirstrip/||"`;; \ *) f=$$p;; \ esac; am__strip_dir = f=`echo $$p | sed -e 's|^.*/||'`; am__install_max = 40 am__nobase_strip_setup = \ srcdirstrip=`echo "$(srcdir)" | sed 's/[].[^$$\\*|]/\\\\&/g'` am__nobase_strip = \ for p in $$list; do echo "$$p"; done | sed -e "s|$$srcdirstrip/||" am__nobase_list = $(am__nobase_strip_setup); \ for p in $$list; do echo "$$p $$p"; done | \ sed "s| $$srcdirstrip/| |;"' / .*\//!s/ .*/ ./; s,\( .*\)/[^/]*$$,\1,' | \ $(AWK) 'BEGIN { files["."] = "" } { files[$$2] = files[$$2] " " $$1; \ if (++n[$$2] == $(am__install_max)) \ { print $$2, files[$$2]; n[$$2] = 0; files[$$2] = "" } } \ END { for (dir in files) print dir, files[dir] }' am__base_list = \ sed '$$!N;$$!N;$$!N;$$!N;$$!N;$$!N;$$!N;s/\n/ /g' | \ sed '$$!N;$$!N;$$!N;$$!N;s/\n/ /g' am__uninstall_files_from_dir = { \ test -z "$$files" \ || { test ! -d "$$dir" && test ! -f "$$dir" && test ! -r "$$dir"; } \ || { echo " ( cd '$$dir' && rm -f" $$files ")"; \ $(am__cd) "$$dir" && rm -f $$files; }; \ } am__installdirs = "$(DESTDIR)$(moduleexecdir)" LTLIBRARIES = $(moduleexec_LTLIBRARIES) gdbm_la_DEPENDENCIES = am_gdbm_la_OBJECTS = gdbm.lo gdbm_la_OBJECTS = $(am_gdbm_la_OBJECTS) gdbm_la_LINK = $(LIBTOOL) --tag=CC $(AM_LIBTOOLFLAGS) $(LIBTOOLFLAGS) \ --mode=link $(CCLD) $(AM_CFLAGS) $(CFLAGS) $(gdbm_la_LDFLAGS) \ $(LDFLAGS) -o $@ DEFAULT_INCLUDES = -I.@am__isrc@ -I$(top_builddir) depcomp = $(SHELL) $(top_srcdir)/build-aux/depcomp am__depfiles_maybe = depfiles am__mv = mv -f COMPILE = $(CC) $(DEFS) $(DEFAULT_INCLUDES) $(INCLUDES) $(AM_CPPFLAGS) \ $(CPPFLAGS) $(AM_CFLAGS) $(CFLAGS) LTCOMPILE = $(LIBTOOL) --tag=CC $(AM_LIBTOOLFLAGS) $(LIBTOOLFLAGS) \ --mode=compile $(CC) $(DEFS) $(DEFAULT_INCLUDES) $(INCLUDES) \ $(AM_CPPFLAGS) $(CPPFLAGS) $(AM_CFLAGS) $(CFLAGS) CCLD = $(CC) LINK = $(LIBTOOL) --tag=CC $(AM_LIBTOOLFLAGS) $(LIBTOOLFLAGS) \ --mode=link $(CCLD) $(AM_CFLAGS) $(CFLAGS) $(AM_LDFLAGS) \ $(LDFLAGS) -o $@ SOURCES = $(gdbm_la_SOURCES) DIST_SOURCES = $(gdbm_la_SOURCES) am__can_run_installinfo = \ case $$AM_UPDATE_INFO_DIR in \ n|no|NO) false;; \ *) (install-info --version) >/dev/null 2>&1;; \ esac ETAGS = etags CTAGS = ctags DISTFILES = $(DIST_COMMON) $(DIST_SOURCES) $(TEXINFOS) $(EXTRA_DIST) ACLOCAL = @ACLOCAL@ ALLOCA = @ALLOCA@ ALL_PACKAGES = @ALL_PACKAGES@ AMTAR = @AMTAR@ AR = @AR@ AS = @AS@ ATK_CFLAGS = @ATK_CFLAGS@ ATK_LIBS = @ATK_LIBS@ AUTOCONF = @AUTOCONF@ AUTOHEADER = @AUTOHEADER@ AUTOM4TE = @AUTOM4TE@ AUTOMAKE = @AUTOMAKE@ AWK = @AWK@ BLOX_IMPLEMENTATION = @BLOX_IMPLEMENTATION@ BUILT_PACKAGES = @BUILT_PACKAGES@ CAIRO_CFLAGS = @CAIRO_CFLAGS@ CAIRO_LIBS = @CAIRO_LIBS@ CC = @CC@ CCDEPMODE = @CCDEPMODE@ CFLAGS = @CFLAGS@ CPP = @CPP@ CPPFLAGS = @CPPFLAGS@ CYGPATH_W = @CYGPATH_W@ DEFS = @DEFS@ DEPDIR = @DEPDIR@ DLLTOOL = @DLLTOOL@ DSYMUTIL = @DSYMUTIL@ DUMPBIN = @DUMPBIN@ ECHO_C = @ECHO_C@ ECHO_N = @ECHO_N@ ECHO_T = @ECHO_T@ EGREP = @EGREP@ EMACS = @EMACS@ EMACSLOADPATH = @EMACSLOADPATH@ EXEEXT = @EXEEXT@ FGREP = @FGREP@ GLIB_CFLAGS = @GLIB_CFLAGS@ GLIB_GENMARSHAL = @GLIB_GENMARSHAL@ GLIB_LIBS = @GLIB_LIBS@ GLIB_MKENUMS = @GLIB_MKENUMS@ GNUTLS_CFLAGS = @GNUTLS_CFLAGS@ GNUTLS_LIBS = @GNUTLS_LIBS@ GOBJECT_QUERY = @GOBJECT_QUERY@ GPERF = @GPERF@ GREP = @GREP@ GST_RUN = @GST_RUN@ GTHREAD_CFLAGS = @GTHREAD_CFLAGS@ GTHREAD_LIBS = @GTHREAD_LIBS@ GTK_CFLAGS = @GTK_CFLAGS@ GTK_LIBS = @GTK_LIBS@ ICON = @ICON@ INCFFI = @INCFFI@ INCLTDL = @INCLTDL@ INCSIGSEGV = @INCSIGSEGV@ INCSNPRINTFV = @INCSNPRINTFV@ INCTCLTK = @INCTCLTK@ INSTALL = @INSTALL@ INSTALL_DATA = @INSTALL_DATA@ INSTALL_INFO = @INSTALL_INFO@ INSTALL_PROGRAM = @INSTALL_PROGRAM@ INSTALL_SCRIPT = @INSTALL_SCRIPT@ INSTALL_STRIP_PROGRAM = @INSTALL_STRIP_PROGRAM@ LD = @LD@ LDFLAGS = @LDFLAGS@ LEX = @LEX@ LIBADD_DL = @LIBADD_DL@ LIBC_SO_DIR = @LIBC_SO_DIR@ LIBC_SO_NAME = @LIBC_SO_NAME@ LIBFFI = @LIBFFI@ LIBFFI_CFLAGS = @LIBFFI_CFLAGS@ LIBFFI_EXECUTABLE_LDFLAGS = @LIBFFI_EXECUTABLE_LDFLAGS@ LIBFFI_LIBS = @LIBFFI_LIBS@ LIBGLUT = @LIBGLUT@ LIBGMP = @LIBGMP@ LIBGST_CFLAGS = @LIBGST_CFLAGS@ LIBICONV = @LIBICONV@ LIBLTDL = @LIBLTDL@ LIBOBJS = @LIBOBJS@ LIBOPENGL = @LIBOPENGL@ LIBREADLINE = @LIBREADLINE@ LIBS = @LIBS@ LIBSIGSEGV = @LIBSIGSEGV@ LIBSNPRINTFV = @LIBSNPRINTFV@ LIBTCLTK = @LIBTCLTK@ LIBTHREAD = @LIBTHREAD@ LIBTOOL = @LIBTOOL@ LIPO = @LIPO@ LN = @LN@ LN_S = @LN_S@ LTALLOCA = @LTALLOCA@ LTLIBICONV = @LTLIBICONV@ LTLIBOBJS = @LTLIBOBJS@ MAINTAINER = @MAINTAINER@ MAKEINFO = @MAKEINFO@ MANIFEST_TOOL = @MANIFEST_TOOL@ MKDIR_P = @MKDIR_P@ MODULES = @MODULES@ NM = @NM@ NMEDIT = @NMEDIT@ OBJC = @OBJC@ OBJCDEPMODE = @OBJCDEPMODE@ OBJCFLAGS = @OBJCFLAGS@ OBJDUMP = @OBJDUMP@ OBJEXT = @OBJEXT@ OTOOL = @OTOOL@ OTOOL64 = @OTOOL64@ PACKAGE = @PACKAGE@ PACKAGE_BUGREPORT = @PACKAGE_BUGREPORT@ PACKAGE_DLOPEN_FLAGS = @PACKAGE_DLOPEN_FLAGS@ PACKAGE_NAME = @PACKAGE_NAME@ PACKAGE_STRING = @PACKAGE_STRING@ PACKAGE_TARNAME = @PACKAGE_TARNAME@ PACKAGE_URL = @PACKAGE_URL@ PACKAGE_VERSION = @PACKAGE_VERSION@ PANGO_CFLAGS = @PANGO_CFLAGS@ PANGO_LIBS = @PANGO_LIBS@ PATH_SEPARATOR = @PATH_SEPARATOR@ PKG_CONFIG = @PKG_CONFIG@ RANLIB = @RANLIB@ RELOCATABLE = @RELOCATABLE@ RELOC_CPPFLAGS = @RELOC_CPPFLAGS@ RELOC_LDFLAGS = @RELOC_LDFLAGS@ SDL_CFLAGS = @SDL_CFLAGS@ SDL_LIBS = @SDL_LIBS@ SED = @SED@ SET_MAKE = @SET_MAKE@ SHELL = @SHELL@ SOCKET_LIBS = @SOCKET_LIBS@ STRIP = @STRIP@ SYNC_CFLAGS = @SYNC_CFLAGS@ TCLSH = @TCLSH@ TIMEOUT = @TIMEOUT@ VERSION = @VERSION@ VERSION_INFO = @VERSION_INFO@ WINDRES = @WINDRES@ WINEWRAPPER = @WINEWRAPPER@ WINEWRAPPERDEP = @WINEWRAPPERDEP@ XMKMF = @XMKMF@ XZIP = @XZIP@ X_CFLAGS = @X_CFLAGS@ X_EXTRA_LIBS = @X_EXTRA_LIBS@ X_LIBS = @X_LIBS@ X_PRE_LIBS = @X_PRE_LIBS@ YACC = @YACC@ ZIP = @ZIP@ abs_builddir = @abs_builddir@ abs_srcdir = @abs_srcdir@ abs_top_builddir = @abs_top_builddir@ abs_top_srcdir = @abs_top_srcdir@ ac_ct_AR = @ac_ct_AR@ ac_ct_CC = @ac_ct_CC@ ac_ct_DUMPBIN = @ac_ct_DUMPBIN@ am__include = @am__include@ am__leading_dot = @am__leading_dot@ am__quote = @am__quote@ am__tar = @am__tar@ am__untar = @am__untar@ bindir = @bindir@ build = @build@ build_alias = @build_alias@ build_cpu = @build_cpu@ build_os = @build_os@ build_vendor = @build_vendor@ builddir = @builddir@ datadir = @datadir@ datarootdir = @datarootdir@ docdir = @docdir@ dvidir = @dvidir@ enable_mysql_tests = @enable_mysql_tests@ exec_prefix = @exec_prefix@ host = @host@ host_alias = @host_alias@ host_cpu = @host_cpu@ host_os = @host_os@ host_vendor = @host_vendor@ htmldir = @htmldir@ imagedir = @imagedir@ includedir = @includedir@ infodir = @infodir@ install_sh = @install_sh@ libdir = @libdir@ libexecdir = @libexecdir@ lispdir = @lispdir@ lispstartdir = @lispstartdir@ localedir = @localedir@ localstatedir = @localstatedir@ mandir = @mandir@ mkdir_p = @mkdir_p@ moduledir = @moduledir@ moduleexecdir = @moduleexecdir@ oldincludedir = @oldincludedir@ pdfdir = @pdfdir@ prefix = @prefix@ program_transform_name = @program_transform_name@ psdir = @psdir@ sbindir = @sbindir@ sharedstatedir = @sharedstatedir@ srcdir = @srcdir@ subdirs = @subdirs@ sysconfdir = @sysconfdir@ target_alias = @target_alias@ top_build_prefix = @top_build_prefix@ top_builddir = @top_builddir@ top_srcdir = @top_srcdir@ gst_module_ldflags = -rpath $(moduleexecdir) -release $(VERSION) -module \ -no-undefined -export-symbols-regex gst_initModule moduleexec_LTLIBRARIES = gdbm.la gdbm_la_SOURCES = gdbm.c gdbm_la_LIBADD = -lgdbm gdbm_la_LDFLAGS = $(gst_module_ldflags) AM_CPPFLAGS = -I$(top_srcdir)/libgst -I$(top_srcdir)/lib-src all: all-am .SUFFIXES: .SUFFIXES: .c .lo .o .obj $(srcdir)/Makefile.in: $(srcdir)/Makefile.am $(am__configure_deps) @for dep in $?; do \ case '$(am__configure_deps)' in \ *$$dep*) \ ( cd $(top_builddir) && $(MAKE) $(AM_MAKEFLAGS) am--refresh ) \ && { if test -f $@; then exit 0; else break; fi; }; \ exit 1;; \ esac; \ done; \ echo ' cd $(top_srcdir) && $(AUTOMAKE) --gnu packages/gdbm/Makefile'; \ $(am__cd) $(top_srcdir) && \ $(AUTOMAKE) --gnu packages/gdbm/Makefile .PRECIOUS: Makefile Makefile: $(srcdir)/Makefile.in $(top_builddir)/config.status @case '$?' in \ *config.status*) \ cd $(top_builddir) && $(MAKE) $(AM_MAKEFLAGS) am--refresh;; \ *) \ echo ' cd $(top_builddir) && $(SHELL) ./config.status $(subdir)/$@ $(am__depfiles_maybe)'; \ cd $(top_builddir) && $(SHELL) ./config.status $(subdir)/$@ $(am__depfiles_maybe);; \ esac; $(top_builddir)/config.status: $(top_srcdir)/configure $(CONFIG_STATUS_DEPENDENCIES) cd $(top_builddir) && $(MAKE) $(AM_MAKEFLAGS) am--refresh $(top_srcdir)/configure: $(am__configure_deps) cd $(top_builddir) && $(MAKE) $(AM_MAKEFLAGS) am--refresh $(ACLOCAL_M4): $(am__aclocal_m4_deps) cd $(top_builddir) && $(MAKE) $(AM_MAKEFLAGS) am--refresh $(am__aclocal_m4_deps): install-moduleexecLTLIBRARIES: $(moduleexec_LTLIBRARIES) @$(NORMAL_INSTALL) @list='$(moduleexec_LTLIBRARIES)'; test -n "$(moduleexecdir)" || list=; \ list2=; for p in $$list; do \ if test -f $$p; then \ list2="$$list2 $$p"; \ else :; fi; \ done; \ test -z "$$list2" || { \ echo " $(MKDIR_P) '$(DESTDIR)$(moduleexecdir)'"; \ $(MKDIR_P) "$(DESTDIR)$(moduleexecdir)" || exit 1; \ echo " $(LIBTOOL) $(AM_LIBTOOLFLAGS) $(LIBTOOLFLAGS) --mode=install $(INSTALL) $(INSTALL_STRIP_FLAG) $$list2 '$(DESTDIR)$(moduleexecdir)'"; \ $(LIBTOOL) $(AM_LIBTOOLFLAGS) $(LIBTOOLFLAGS) --mode=install $(INSTALL) $(INSTALL_STRIP_FLAG) $$list2 "$(DESTDIR)$(moduleexecdir)"; \ } uninstall-moduleexecLTLIBRARIES: @$(NORMAL_UNINSTALL) @list='$(moduleexec_LTLIBRARIES)'; test -n "$(moduleexecdir)" || list=; \ for p in $$list; do \ $(am__strip_dir) \ echo " $(LIBTOOL) $(AM_LIBTOOLFLAGS) $(LIBTOOLFLAGS) --mode=uninstall rm -f '$(DESTDIR)$(moduleexecdir)/$$f'"; \ $(LIBTOOL) $(AM_LIBTOOLFLAGS) $(LIBTOOLFLAGS) --mode=uninstall rm -f "$(DESTDIR)$(moduleexecdir)/$$f"; \ done clean-moduleexecLTLIBRARIES: -test -z "$(moduleexec_LTLIBRARIES)" || rm -f $(moduleexec_LTLIBRARIES) @list='$(moduleexec_LTLIBRARIES)'; for p in $$list; do \ dir="`echo $$p | sed -e 's|/[^/]*$$||'`"; \ test "$$dir" != "$$p" || dir=.; \ echo "rm -f \"$${dir}/so_locations\""; \ rm -f "$${dir}/so_locations"; \ done gdbm.la: $(gdbm_la_OBJECTS) $(gdbm_la_DEPENDENCIES) $(EXTRA_gdbm_la_DEPENDENCIES) $(gdbm_la_LINK) -rpath $(moduleexecdir) $(gdbm_la_OBJECTS) $(gdbm_la_LIBADD) $(LIBS) mostlyclean-compile: -rm -f *.$(OBJEXT) distclean-compile: -rm -f *.tab.c @AMDEP_TRUE@@am__include@ @am__quote@./$(DEPDIR)/gdbm.Plo@am__quote@ .c.o: @am__fastdepCC_TRUE@ $(COMPILE) -MT $@ -MD -MP -MF $(DEPDIR)/$*.Tpo -c -o $@ $< @am__fastdepCC_TRUE@ $(am__mv) $(DEPDIR)/$*.Tpo $(DEPDIR)/$*.Po @AMDEP_TRUE@@am__fastdepCC_FALSE@ source='$<' object='$@' libtool=no @AMDEPBACKSLASH@ @AMDEP_TRUE@@am__fastdepCC_FALSE@ DEPDIR=$(DEPDIR) $(CCDEPMODE) $(depcomp) @AMDEPBACKSLASH@ @am__fastdepCC_FALSE@ $(COMPILE) -c $< .c.obj: @am__fastdepCC_TRUE@ $(COMPILE) -MT $@ -MD -MP -MF $(DEPDIR)/$*.Tpo -c -o $@ `$(CYGPATH_W) '$<'` @am__fastdepCC_TRUE@ $(am__mv) $(DEPDIR)/$*.Tpo $(DEPDIR)/$*.Po @AMDEP_TRUE@@am__fastdepCC_FALSE@ source='$<' object='$@' libtool=no @AMDEPBACKSLASH@ @AMDEP_TRUE@@am__fastdepCC_FALSE@ DEPDIR=$(DEPDIR) $(CCDEPMODE) $(depcomp) @AMDEPBACKSLASH@ @am__fastdepCC_FALSE@ $(COMPILE) -c `$(CYGPATH_W) '$<'` .c.lo: @am__fastdepCC_TRUE@ $(LTCOMPILE) -MT $@ -MD -MP -MF $(DEPDIR)/$*.Tpo -c -o $@ $< @am__fastdepCC_TRUE@ $(am__mv) $(DEPDIR)/$*.Tpo $(DEPDIR)/$*.Plo @AMDEP_TRUE@@am__fastdepCC_FALSE@ source='$<' object='$@' libtool=yes @AMDEPBACKSLASH@ @AMDEP_TRUE@@am__fastdepCC_FALSE@ DEPDIR=$(DEPDIR) $(CCDEPMODE) $(depcomp) @AMDEPBACKSLASH@ @am__fastdepCC_FALSE@ $(LTCOMPILE) -c -o $@ $< mostlyclean-libtool: -rm -f *.lo clean-libtool: -rm -rf .libs _libs ID: $(HEADERS) $(SOURCES) $(LISP) $(TAGS_FILES) list='$(SOURCES) $(HEADERS) $(LISP) $(TAGS_FILES)'; \ unique=`for i in $$list; do \ if test -f "$$i"; then echo $$i; else echo $(srcdir)/$$i; fi; \ done | \ $(AWK) '{ files[$$0] = 1; nonempty = 1; } \ END { if (nonempty) { for (i in files) print i; }; }'`; \ mkid -fID $$unique tags: TAGS TAGS: $(HEADERS) $(SOURCES) $(TAGS_DEPENDENCIES) \ $(TAGS_FILES) $(LISP) set x; \ here=`pwd`; \ list='$(SOURCES) $(HEADERS) $(LISP) $(TAGS_FILES)'; \ unique=`for i in $$list; do \ if test -f "$$i"; then echo $$i; else echo $(srcdir)/$$i; fi; \ done | \ $(AWK) '{ files[$$0] = 1; nonempty = 1; } \ END { if (nonempty) { for (i in files) print i; }; }'`; \ shift; \ if test -z "$(ETAGS_ARGS)$$*$$unique"; then :; else \ test -n "$$unique" || unique=$$empty_fix; \ if test $$# -gt 0; then \ $(ETAGS) $(ETAGSFLAGS) $(AM_ETAGSFLAGS) $(ETAGS_ARGS) \ "$$@" $$unique; \ else \ $(ETAGS) $(ETAGSFLAGS) $(AM_ETAGSFLAGS) $(ETAGS_ARGS) \ $$unique; \ fi; \ fi ctags: CTAGS CTAGS: $(HEADERS) $(SOURCES) $(TAGS_DEPENDENCIES) \ $(TAGS_FILES) $(LISP) list='$(SOURCES) $(HEADERS) $(LISP) $(TAGS_FILES)'; \ unique=`for i in $$list; do \ if test -f "$$i"; then echo $$i; else echo $(srcdir)/$$i; fi; \ done | \ $(AWK) '{ files[$$0] = 1; nonempty = 1; } \ END { if (nonempty) { for (i in files) print i; }; }'`; \ test -z "$(CTAGS_ARGS)$$unique" \ || $(CTAGS) $(CTAGSFLAGS) $(AM_CTAGSFLAGS) $(CTAGS_ARGS) \ $$unique GTAGS: here=`$(am__cd) $(top_builddir) && pwd` \ && $(am__cd) $(top_srcdir) \ && gtags -i $(GTAGS_ARGS) "$$here" distclean-tags: -rm -f TAGS ID GTAGS GRTAGS GSYMS GPATH tags distdir: $(DISTFILES) @srcdirstrip=`echo "$(srcdir)" | sed 's/[].[^$$\\*]/\\\\&/g'`; \ topsrcdirstrip=`echo "$(top_srcdir)" | sed 's/[].[^$$\\*]/\\\\&/g'`; \ list='$(DISTFILES)'; \ dist_files=`for file in $$list; do echo $$file; done | \ sed -e "s|^$$srcdirstrip/||;t" \ -e "s|^$$topsrcdirstrip/|$(top_builddir)/|;t"`; \ case $$dist_files in \ */*) $(MKDIR_P) `echo "$$dist_files" | \ sed '/\//!d;s|^|$(distdir)/|;s,/[^/]*$$,,' | \ sort -u` ;; \ esac; \ for file in $$dist_files; do \ if test -f $$file || test -d $$file; then d=.; else d=$(srcdir); fi; \ if test -d $$d/$$file; then \ dir=`echo "/$$file" | sed -e 's,/[^/]*$$,,'`; \ if test -d "$(distdir)/$$file"; then \ find "$(distdir)/$$file" -type d ! -perm -700 -exec chmod u+rwx {} \;; \ fi; \ if test -d $(srcdir)/$$file && test $$d != $(srcdir); then \ cp -fpR $(srcdir)/$$file "$(distdir)$$dir" || exit 1; \ find "$(distdir)/$$file" -type d ! -perm -700 -exec chmod u+rwx {} \;; \ fi; \ cp -fpR $$d/$$file "$(distdir)$$dir" || exit 1; \ else \ test -f "$(distdir)/$$file" \ || cp -p $$d/$$file "$(distdir)/$$file" \ || exit 1; \ fi; \ done check-am: all-am check: check-am all-am: Makefile $(LTLIBRARIES) installdirs: for dir in "$(DESTDIR)$(moduleexecdir)"; do \ test -z "$$dir" || $(MKDIR_P) "$$dir"; \ done install: install-am install-exec: install-exec-am install-data: install-data-am uninstall: uninstall-am install-am: all-am @$(MAKE) $(AM_MAKEFLAGS) install-exec-am install-data-am installcheck: installcheck-am install-strip: if test -z '$(STRIP)'; then \ $(MAKE) $(AM_MAKEFLAGS) INSTALL_PROGRAM="$(INSTALL_STRIP_PROGRAM)" \ install_sh_PROGRAM="$(INSTALL_STRIP_PROGRAM)" INSTALL_STRIP_FLAG=-s \ install; \ else \ $(MAKE) $(AM_MAKEFLAGS) INSTALL_PROGRAM="$(INSTALL_STRIP_PROGRAM)" \ install_sh_PROGRAM="$(INSTALL_STRIP_PROGRAM)" INSTALL_STRIP_FLAG=-s \ "INSTALL_PROGRAM_ENV=STRIPPROG='$(STRIP)'" install; \ fi mostlyclean-generic: clean-generic: distclean-generic: -test -z "$(CONFIG_CLEAN_FILES)" || rm -f $(CONFIG_CLEAN_FILES) -test . = "$(srcdir)" || test -z "$(CONFIG_CLEAN_VPATH_FILES)" || rm -f $(CONFIG_CLEAN_VPATH_FILES) maintainer-clean-generic: @echo "This command is intended for maintainers to use" @echo "it deletes files that may require special tools to rebuild." clean: clean-am clean-am: clean-generic clean-libtool clean-moduleexecLTLIBRARIES \ mostlyclean-am distclean: distclean-am -rm -rf ./$(DEPDIR) -rm -f Makefile distclean-am: clean-am distclean-compile distclean-generic \ distclean-tags dvi: dvi-am dvi-am: html: html-am html-am: info: info-am info-am: install-data-am: install-dvi: install-dvi-am install-dvi-am: install-exec-am: install-moduleexecLTLIBRARIES install-html: install-html-am install-html-am: install-info: install-info-am install-info-am: install-man: install-pdf: install-pdf-am install-pdf-am: install-ps: install-ps-am install-ps-am: installcheck-am: maintainer-clean: maintainer-clean-am -rm -rf ./$(DEPDIR) -rm -f Makefile maintainer-clean-am: distclean-am maintainer-clean-generic mostlyclean: mostlyclean-am mostlyclean-am: mostlyclean-compile mostlyclean-generic \ mostlyclean-libtool pdf: pdf-am pdf-am: ps: ps-am ps-am: uninstall-am: uninstall-moduleexecLTLIBRARIES .MAKE: install-am install-strip .PHONY: CTAGS GTAGS all all-am check check-am clean clean-generic \ clean-libtool clean-moduleexecLTLIBRARIES ctags distclean \ distclean-compile distclean-generic distclean-libtool \ distclean-tags distdir dvi dvi-am html html-am info info-am \ install install-am install-data install-data-am install-dvi \ install-dvi-am install-exec install-exec-am install-html \ install-html-am install-info install-info-am install-man \ install-moduleexecLTLIBRARIES install-pdf install-pdf-am \ install-ps install-ps-am install-strip installcheck \ installcheck-am installdirs maintainer-clean \ maintainer-clean-generic mostlyclean mostlyclean-compile \ mostlyclean-generic mostlyclean-libtool pdf pdf-am ps ps-am \ tags uninstall uninstall-am uninstall-moduleexecLTLIBRARIES # Tell versions [3.59,3.63) of GNU make to not export all variables. # Otherwise a system limit (for SysV at least) may be exceeded. .NOEXPORT: smalltalk-3.2.5/packages/gdbm/gdbm.st0000644000175000017500000001203612123404352014374 00000000000000"====================================================================== | | Smalltalk wrapper to GDBM | | ======================================================================" "====================================================================== | | Copyright 1988,92,94,95,99,2001,2007 Free Software Foundation, Inc. | Written by Paolo Bonzini. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" Object subclass: Database [ | gdbm | Database class >> read: fileName blockSize: size mode: modeInt [ ^self new open: fileName blockSize: size flags: 0 mode: modeInt ] Database class >> write: fileName blockSize: size mode: modeInt [ ^self new open: fileName blockSize: size flags: 1 mode: modeInt ] Database class >> writeCreate: fileName blockSize: size mode: modeInt [ ^self new open: fileName blockSize: size flags: 2 mode: modeInt ] Database class >> new: fileName blockSize: size mode: modeInt [ ^self new open: fileName blockSize: size flags: 3 mode: modeInt ] open: fileName blockSize: size flags: flags mode: modeInt [ self addToBeFinalized. gdbm := GDBM open: fileName blockSize: size flags: flags mode: modeInt fatalFunc: nil ] close [ gdbm close. gdbm := nil ] finalize [ gdbm isNil ifFalse: [self close] ] keyDatum: key [ ^DatumStruct fromString: key ] valueDatum: value [ ^DatumStruct fromString: value ] getKey: key [ ^key asString ] getValue: value [ ^value asString ] at: key [ ^self at: key ifAbsent: [self error: 'key not found'] ] at: key ifAbsent: aBlock [ | value datum | datum := self keyDatum: key. value := gdbm at: datum. ^ [value dPtr value isNil ifTrue: [aBlock value] ifFalse: [self getValue: value]] ensure: [value free. datum free] ] at: key put: value [ | datumValue datumKey | datumKey := self keyDatum: key. [datumValue := self valueDatum: value. gdbm at: datumKey put: datumValue flag: 1. datumValue free] ensure: [datumKey free]. ^value ] includesKey: key [ | value datum | datum := self keyDatum: key. value := gdbm at: datum. ^[value dPtr value notNil] ensure: [value free. datum free] ] removeKey: key [ ^self removeKey: key ifAbsent: [self error: 'key not found'] ] removeKey: key ifAbsent: aBlock [ | datumKey present | datumKey := self keyDatum: key. present := (gdbm removeKey: datumKey) == 0. datumKey free. ^present ifTrue: [aBlock value] ifFalse: [key] ] reorganize [ gdbm reorganize ] first [ | datumKey result | datumKey := gdbm firstKey. ^[self getKey: datumKey] ensure: [datumKey free] ] keysAndValuesDo: aBlock [ | item value newItem | item := gdbm firstKey. [[item dPtr value notNil] whileTrue: [value := gdbm at: item. [aBlock value: (self getKey: item) value: (self getValue: value)] ensure: [value free]. newItem := gdbm nextKey: item. item free. item := newItem]] ensure: [item free] ] keysDo: aBlock [ | item newItem | item := gdbm firstKey. [[item dPtr value notNil] whileTrue: [aBlock value: (self getKey: item). newItem := gdbm nextKey: item. item free. item := newItem]] ensure: [item free] ] after: key [ | datumKey datumNext result | datumKey := self keyDatum: key. datumNext := gdbm nextKey: datumKey. ^[datumNext dPtr value isNil ifTrue: [nil] ifFalse: [self getKey: datumNext]] ensure: [datumNext free. datumKey free] ] ] smalltalk-3.2.5/packages/gdbm/stamp-classes0000644000175000017500000000000012123404352015601 00000000000000smalltalk-3.2.5/packages/gdbm/package.xml0000644000175000017500000000031312123404352015223 00000000000000 GDBM gdbm-c.st gdbm.st gdbm GDBMTest gdbmtests.st smalltalk-3.2.5/packages/gdbm/gdbm-c.st0000644000175000017500000000657512123404352014627 00000000000000"====================================================================== | | GDBM declarations | | ======================================================================" "====================================================================== | | Copyright 2001, 2005, 2007 Free Software Foundation, Inc. | Written by Steve Byrne. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" CObject subclass: GDBM [ GDBM class >> open: fileName blockSize: size flags: flags mode: modeInt fatalFunc: funcAddr [ "GDBM_FILE gdbm_open(name, block_size, flags, mode, fatal_func);" ] close [ "void gdbm_close(dbf);" ] at: key put: value flag: aFlag [ "int gdbm_store(dbf, key, content, flag);" ] at: key [ "datum gdbm_fetch(dbf, key);" ] removeKey: key [ "int gdbm_delete(dbf, key);" ] firstKey [ "datum gdbm_firstkey(dbf);" ] nextKey: afterDatum [ "datum gdbm_nextkey(dbf, key);" ] reorganize [ "int gdbm_reorganize(dbf);" ] ] CStruct subclass: DatumStruct [ DatumStruct class >> fromString: aString [ | obj strObj len | obj := self new. len := aString size. obj dSize value: len. obj dPtr value: (aString asCData: CCharType). obj addToBeFinalized. ^obj ] asString [ | len ptr str | len := self dSize value. ptr := self dPtr value. str := String new: len. 1 to: len do: [:i | str at: i put: (ptr at: i - 1)]. ^str ] free [ self removeToBeFinalized. self dPtr value free. super free ] ] smalltalk-3.2.5/packages/sockets/0000755000175000017500000000000012130456021013731 500000000000000smalltalk-3.2.5/packages/sockets/Makefile.frag0000644000175000017500000000022012130344111016215 00000000000000Sockets_FILES = \ $(Sockets_FILES): $(srcdir)/packages/sockets/stamp-classes: $(Sockets_FILES) touch $(srcdir)/packages/sockets/stamp-classes smalltalk-3.2.5/packages/sockets/Datagram.st0000644000175000017500000001252212123404352015745 00000000000000"====================================================================== | | Smalltalk sockets - Datagram class | | ======================================================================" "====================================================================== | | Copyright 1999, 2000, 2001, 2002, 2008 Free Software Foundation, Inc. | Written by Paolo Bonzini. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" Object subclass: Datagram [ | data address port dataSize | Datagram class >> data: aByteArray [ "Answer a new datagram with the specified data." ^(self new) data: aByteArray; yourself ] Datagram class >> data: aByteArray address: ipAddress port: port [ "Answer a new datagram with the specified target socket, and aByteArray as its data." ^(self new) data: aByteArray; address: ipAddress; port: port; yourself ] Datagram class >> object: object objectDumper: od address: ipAddress port: port [ "Serialize the object onto a ByteArray, and create a Datagram with the object as its contents, and the specified receiver. Serialization takes place through ObjectDumper passed as `od', and the stream attached to the ObjectDumper is resetted every time. Using this method is indicated if different objects that you're sending are likely to contain references to the same objects." od stream reset. od dump: object. ^self data: od stream contents address: ipAddress port: port ] Datagram class >> object: object address: ipAddress port: port [ "Serialize the object onto a ByteArray, and create a Datagram with the object as its contents, and the specified receiver. Note that each invocation of this method creates a separate ObjectDumper; if different objects that you're sending are likely to contain references to the same objects, you should use #object:objectDumper:address:port:." | stream | stream := (String new: 100) writeStream. ObjectDumper dump: object to: stream. ^self data: stream contents address: ipAddress port: port ] address [ "Answer the address of the target socket" ^address ] address: ipAddress [ "Set the address of the target socket" address := ipAddress ] data [ "Answer the data attached to the datagram" ^data ] data: aByteArray [ "Set the data attached to the datagram" data := aByteArray. dataSize := nil. ] dataSize [ "Answer the size of the message." ^dataSize ] dataSize: aSize [ "I am called to update the size..." dataSize := aSize ] size [ "I determine the size of the datagram. It is either an explicitly specified dataSize, or the size of the whole collection." ^dataSize isNil ifTrue: [data size] ifFalse: [dataSize]. ] get [ "Parse the data attached to the datagram through a newly created ObjectDumper, and answer the resulting object. This method is complementary to #object:address:port:." ^ObjectDumper loadFrom: self data readStream ] getThrough: objectDumper [ "Parse the data attached to the datagram through the given ObjectDumper without touching the stream to which it is attached, and answer the resulting object. The state of the ObjectDumper, though, is updated. This method is complementary to #object:objectDumper:address:port:." | result saveStream | saveStream := objectDumper stream. [objectDumper stream: self data readStream. result := objectDumper load] ensure: [objectDumper stream: saveStream]. ^result ] port [ "Answer the IP port of the target socket" ^port ] port: thePort [ "Set the IP port of the target socket" port := thePort ] ] smalltalk-3.2.5/packages/sockets/Buffers.st0000644000175000017500000001564112123404352015626 00000000000000"====================================================================== | | ReadBuffer and WriteBuffer classes | | ======================================================================" "====================================================================== | | Copyright 1999, 2000, 2001, 2002, 2003, 2007, 2008, 2009 Free Software Foundation, Inc. | Written by Paolo Bonzini. | | This file is part of GNU Smalltalk. | | GNU Smalltalk is free software; you can redistribute it and/or modify it | under the terms of the GNU General Public License as published by the Free | Software Foundation; either version 2, or (at your option) any later version. | | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS | FOR A PARTICULAR PURPOSE. See the GNU General Public License for more | details. | | You should have received a copy of the GNU General Public License along with | GNU Smalltalk; see the file COPYING. If not, write to the Free Software | Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. | ======================================================================" WriteStream subclass: WriteBuffer [ | flushBlock | flush [ "Evaluate the flushing block and reset the stream" flushBlock notNil ifTrue: [flushBlock value: collection value: ptr - 1]. ptr := 1 ] close [ super close. flushBlock := nil ] flushBlock: block [ "Set which block will be used to flush the buffer. The block will be evaluated with a collection and an Integer n as parameters, and will have to write the first n elements of the collection." flushBlock := block ] growCollection [ self flush ] growCollectionTo: n [ self shouldNotImplement ] isFull [ ^self position = self collection size ] next: n putAll: aCollection startingAt: pos [ "Put n characters or bytes of aCollection, starting at the pos-th, in the collection buffer." | end written amount | ptr = collection size ifTrue: [self growCollection]. written := 0. [end := collection size min: ptr + (n - written - 1). end >= ptr ifTrue: [collection replaceFrom: ptr to: end with: aCollection startingAt: pos + written. written := written + (end - ptr + 1). ptr := end + 1]. written < n] whileTrue: [self growCollection]. ] ] ReadStream subclass: ReadBuffer [ | fillBlock | ReadBuffer class >> on: aCollection [ "Answer a Stream that uses aCollection as a buffer. You should ensure that the fillBlock is set before the first operation, because the buffer will report that the data has ended until you set the fillBlock." ^(super on: aCollection) setToEnd; yourself "Force a buffer load soon" ] close [ super close. fillBlock := nil ] atEnd [ "Answer whether the data stream has ended." self basicAtEnd ifFalse: [^false]. fillBlock isNil ifTrue: [^true]. endPtr := fillBlock value: collection value: collection size. ptr := 1. ^self basicAtEnd ] pastEnd [ "Try to fill the buffer if the data stream has ended." self atEnd ifTrue: [^super pastEnd]. "Else, the buffer has been filled." ^self next ] bufferContents [ "Answer the data that is in the buffer, and empty it." | contents | self basicAtEnd ifTrue: [^self species new: 0]. contents := self collection copyFrom: ptr to: endPtr. endPtr := ptr - 1. "Empty the buffer" ^contents ] availableBytes [ "Answer how many bytes are available in the buffer." self isEmpty ifTrue: [ self fill ]. ^endPtr + 1 - ptr ] nextAvailable: anInteger putAllOn: aStream [ "Copy the next anInteger objects from the receiver to aStream. Return the number of items stored." self isEmpty ifTrue: [ self fill ]. ^super nextAvailable: anInteger putAllOn: aStream ] nextAvailable: anInteger into: aCollection startingAt: pos [ "Place the next anInteger objects from the receiver into aCollection, starting at position pos. Return the number of items stored." self isEmpty ifTrue: [ self fill ]. ^super nextAvailable: anInteger into: aCollection startingAt: pos ] fill [ "Fill the buffer with more data if it is empty, and answer true if the fill block was able to read more data." ^self atEnd not ] fillBlock: block [ "Set the block that fills the buffer. It receives a collection and the number of bytes to fill in it, and must return the number of bytes actually read" fillBlock := block ] isEmpty [ "Answer whether the next input operation will force a buffer fill" ^self basicAtEnd ] isFull [ "Answer whether the buffer has been just filled" ^self notEmpty and: [self position = 0] ] notEmpty [ "Check whether the next input operation will force a buffer fill and answer true if it will not." ^self basicAtEnd not ] upToEnd [ "Returns a collection of the same type that the stream accesses, up to but not including the object anObject. Returns the entire rest of the stream's contents if anObject is not present." | ws | ws := String new writeStream. [self nextAvailablePutAllOn: ws. self atEnd] whileFalse. ^ws contents ] upTo: anObject [ "Returns a collection of the same type that the stream accesses, up to but not including the object anObject. Returns the entire rest of the stream's contents if anObject is not present." | result r ws | self atEnd ifTrue: [^collection copyEmpty: 0]. r := collection indexOf: anObject startingAt: ptr ifAbsent: [0]. r = 0 ifFalse: [result := self next: r - ptr. self next. ^result]. ws := String new writeStream. [self nextAvailablePutAllOn: ws. self atEnd ifTrue: [^ws contents]. r := collection indexOf: anObject startingAt: ptr ifAbsent: [0]. r = 0] whileTrue. self next: r - 1 putAllOn: ws; next. ^ws contents ] ] smalltalk-3.2.5/packages/sockets/UnixSocketImpl.st0000644000175000017500000001250412123404352017143 00000000000000"====================================================================== | | Smalltalk AF_UNIX sockets | | ======================================================================" "====================================================================== | | Copyright 2008 Free Software Foundation, Inc. | Written by Paolo Bonzini. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" SocketAddress subclass: UnixAddress [ UnixAddress class [ | uniqueInstance | initialize [ "Set up the default implementation classes for the receiver" self defaultDatagramSocketImplClass: UnixDatagramSocketImpl. self defaultStreamSocketImplClass: UnixSocketImpl ] uniqueInstance [ uniqueInstance isNil ifTrue: [ uniqueInstance := self new ]. ^uniqueInstance ] createLoopbackHost [ "Answer an object representing the loopback host in the address family for the receiver. This is 127.0.0.1 for IPv4." ^self uniqueInstance ] createUnknownAddress [ "Answer an object representing an unkown address in the address family for the receiver" ^self uniqueInstance ] fromSockAddr: aByteArray port: portAdaptor [ "Private - Answer the unique UnixAddress instance, filling in the portAdaptor's value from a ByteArray containing a C sockaddr_in structure." | s size | size := aByteArray indexOf: 0 startingAt: 4 ifAbsent: [ aByteArray size + 1 ]. s := String new: size - 3. s replaceFrom: 1 to: s size with: aByteArray startingAt: 3. portAdaptor value: s. ^self uniqueInstance ] extractAddressesAfterLookup: result [ "Not implemented, DNS should not answer AF_UNIX addresses!" self shouldNotImplement ] ] = aSocketAddress [ "Answer whether the receiver and aSocketAddress represent the same socket on the same machine." ^self == aSocketAddress ] isMulticast [ "Answer whether an address is reserved for multicast connections." ^false ] hash [ "Answer an hash value for the receiver" ^self class hash ] printOn: aStream [ "Print the receiver in dot notation." aStream nextPutAll: '[AF_UNIX address family]' ] port: port [ "Return a ByteArray containing a struct sockaddr for the given port on the IP address represented by the receiver. Family = AF_UNIX." | portString | portString := port asString. portString isEmpty ifTrue: [self error: 'invalid socket path']. portString size > 108 ifTrue: [self error: 'socket path too long']. ^(ByteArray new: 110) "Write sin_len and sin_family = AF_UNIX" at: 1 put: portString size + 3; at: 2 put: self class addressFamily; replaceFrom: 3 to: portString size + 2 with: portString startingAt: 1; yourself ] ] SocketImpl subclass: UnixSocketImpl [ activeSocketImplClass [ "Return an implementation class to be used for the active socket created when a connection is accepted by a listening socket. Return SocketImpl, because the active socket should not delete the socket file when it is closed." ^SocketImpl ] close [ | port | port := localPort. [ super close ] ensure: [ port isNil ifFalse: [ port asFile remove ] ] ] ] DatagramSocketImpl subclass: UnixDatagramSocketImpl [ close [ | port | port := localPort. [ super close ] ensure: [ port isNil ifFalse: [ port asFile remove ] ] ] ] smalltalk-3.2.5/packages/sockets/ChangeLog0000644000175000017500000006356112123404352015440 000000000000002011-08-13 Paolo Bonzini * AbstractSocketImpl.st: Recheck file descriptor state between async and sync polling. 2011-08-13 Paolo Bonzini * AbstractSocketImpl.st: Add #checkSoError, test file open in it first. 2011-03-24 Paolo Bonzini * Buffers.st: Allow interruption of the fill block. 2011-03-24 Paolo Bonzini * Buffers.st: Remove fill/flush blocks when closing the stream. 2011-03-09 Paolo Bonzini * SocketAddress.st: Prefer returning addresses for the default address class when sending #byName: to SocketAddress. Return nil from #allByName: when getaddrinfo succeeds but returns no address. 2011-02-04 Holger Hans Peter Freyther * UnitTest.st: Verify that the primitive are failing. 2011-02-04 Holger Hans Peter Freyther * package.xml: Add test section. * UnitTest.st: Add SUnit based testcase. 2011-01-19 Holger Hans Peter Freyther * Sockets.st: Use errno to test outcome of bind. 2010-12-04 Paolo Bonzini * package.xml: Remove now superfluous tags. 2010-09-27 Paolo Bonzini * Sockets.st: Return false for #isPeerAlive after a zero-byte read from the socket. Reported by Holger Hans Peter Freyther. 2010-06-14 Paolo Bonzini * Sockets.st: Do not close a datagram socket upon timeout. Reported by Holger Hans Peter Freyther. 2010-06-13 Paolo Bonzini * AbstractSocketImpl.st: Check the return value of recvfrom and sendto for errors. 2010-06-13 Paolo Bonzini * SocketAddress.st: Avoid infinite mutual recursion between #fromSockAddr:port: and #extractFromSockAddr:port:. The bug is elsewhere, but this isn't a bad idea anyway. 2010-06-12 Holger Hans Peter Freyther * Sockets.st: Make DatagramSocket local: string port: int work. Resolve the ipAddress to localAddr early on, use the localAddr instead of ipAddress to determine the addressClass and afterwards fallback to localhost in case localAddr was nil. 2010-06-12 Holger Hans Peter Freyther * Sockets.st: Add AbstractSocket class>>#addressFromString to parse a string into a SocketAddress and use it inside the ServerSocket and DatagramSocket class. 2010-06-12 Holger Hans Peter Freyther * Datagram.st: Add #dataSize, #dataSize: and #size. * AbstractSocketImpl.st: Call Datagram>>#dataSize: from the #receive:datagram selector with the bytes read, use Datagram>>#size in the #send:to:port selector to only send a limited amount of bytes from the Datagram>>#data. 2010-03-27 Paolo Bonzini * AbstractSocketImpl.st: Do not check errno unless a system call fails. 2010-01-01 Paolo Bonzini * Update copyright years. 2009-10-08 Paolo Bonzini * Buffers.st: Use pre-f7d0319 implementation of WriteStream>>#next:putAll:startingAt: in WriteBuffer. 2009-10-04 Paolo Bonzini * Buffers.st: Implement #upTo: using #indexOf:. 2009-09-07 Paolo Bonzini * AbstractSocketImpl.st: Check error after fileop 14. 2009-08-25 Paolo Bonzini * sockets.c: Move to libgst/. * package.xml: Check for TCPaccept. 2009-08-21 Paolo Bonzini * sockets.c: Another check_have_cloexec nit. 2009-08-13 Paolo Bonzini * sockets.c: Fix if statements for check_have_cloexec. 2009-08-07 Paolo Bonzini * sockets.c: Do not assume SOCK_CLOEXEC is present even if it is defined. 2009-08-05 Paolo Bonzini * AbstractSocketImpl.st: Add #soError. * cfuncs.st: Rename #soError to #soError:. * sockets.c: Return errno/WSAGetLastError if getsockopt(SO_ERROR) fails. 2009-07-22 Paolo Bonzini * AbstractSocketImpl.st: Abstract datagram factory using #datagramClass. * Sockets.st: Provide access to the implementation's datagramClass. 2009-07-17 Stefan Schmiedl * Sockets.st: Fix documentation typo, remove duplicated code. 2009-06-08 Paolo Bonzini * cfuncs.st: Fix remaining of CSockAddrStruct. 2009-06-06 Paolo Bonzini * SocketAddress.st: Fix case where the machine is disconnected. 2008-12-30 Paolo Bonzini * sockets.c: Discard EPIPE too, it is caught by POLLHUP. 2008-09-15 Paolo Bonzini * Sockets.st: Fix #nextAvailable:... methods (broke DBD-MySQL). 2008-09-12 Paolo Bonzini * sockets.c: connect returns EWOULDBLOCK for Winsock. 2008-08-29 Paolo Bonzini * IP6SocketImpl.st: Fill in sa_len dutifully for BSD systems. * IPSocketImpl.st: Fill in sa_len dutifully for BSD systems. * SocketAddress.st: Document brokenness of BSD systems. * UnixSocketImpl.st: Fill in sa_len dutifully for BSD systems. * sockets.c: Undo the above dutifully for non-BSD systems. 2008-08-17 Paolo Bonzini * sockets.c: Add wrappers for socket<->fd conversions. 2008-08-17 Paolo Bonzini * sockets.c: Emulate FD_CLOEXEC on MinGW. 2008-08-11 Paolo Bonzini * AbstractSocketImpl.st: Remove #soError. * cfuncs.st: Implement it as a callout. * sockets.c: Remove soError, add getSoError. Do not pass POLLHUP errors to Smalltalk. 2008-08-06 Paolo Bonzini * Buffers.st: Add #nextAvailable:putAllOn:, remove #nextHunkPutAllOn: and #nextHunk. * Sockets.st: Likewise. * tests.st: Change #nextHunkPutAllOn: to #nextAvailablePutAllOn:. 2008-08-05 Paolo Bonzini * Buffers.st: Add #nextAvailable:into:startingAt:. * Sockets.st: Change #nextAvailable: into #nextAvailable:into:startingAt:. Change the fill blocks to not use #read:from:to: and #write:from:to:. 2008-08-05 Paolo Bonzini * Buffers.st: Add #nextHunk and #nextHunkPutAllOn:. * Sockets.st: Remove the lookahead instance variable. Delegate more stuff to the readBuffer, including #nextHunk. Implement #nextHunkPutAllOn:. * Tests.st: Modify test to use #nextHunkPutAllOn: for a 3-4x speed increase. :-P :-P :-P 2008-08-05 Paolo Bonzini * Tests.st: Use StreamSocket for the server. 2008-08-05 Paolo Bonzini * Datagram.st: Do not use ByteStream. 2008-08-04 Paolo Bonzini * Sockets.st: Add StreamSocket>>#nextAvailable:. 2008-08-01 Paolo Bonzini * sockets.c: Use SOCK_CLOEXEC if available, else use FD_CLOEXEC. 2008-07-28 Paolo Bonzini * Buffers.st: Add ReadBuffer>>#availableBytes. * Sockets.st: Add StreamSocket>>#availableBytes. 2008-07-18 Paolo Bonzini * IP6SocketImpl.st: New. * UnixSocketImpl.st: Move initialization... * init.st: ... here. * cfuncs.st: Add IPv6 functions. * sockets.c: Add IPv6 functions. 2008-07-18 Paolo Bonzini * AbstractSocketImpl.st: Use a big ByteArray for addresses. * IPSocketImpl.st: Remove #createLocalAddress, CSockAddrStruct, #extractAddressesAfterLookup:. * SocketAddress.st: Rewrite access to class-instance variables, allow calling #allByName: on subclasses, use getaddrinfo, implement #extractAddressesAfterLookup: here. * UnixSocketImpl.st: Remove #createLocalAddress. * cfuncs.st: Add SocketAddress class accessors, getaddrinfo, freeaddrinfo. Remove TCPlookupAllHostAddr and TCPgetAnyLocalAddress. * sockets.c: Remove myGetHostByName and getAnyLocalAddress, add afUnspec/pfUnspec, getaddrinfo/freeaddrinfo, addrinfo accessors. Use getipnodebyaddr if available. 2008-07-15 Paolo Bonzini * SocketAddress.st: Fix parameter name for #=, add #isMulticast. * UnixSocketImpl.st: New. * cfuncs.st: Add AF_UNIX/PF_UNIX constants. * package.xml: Add UnixSocketImpl.st. * sockets.c: Add AF_UNIX/PF_UNIX constants. * Tests.st: Make tests independent of the address family. 2008-07-15 Paolo Bonzini * AbstractSocketImpl.st: Document classes, add #activeSocketImplClass. * Datagram.st: Document classes. * IPSocketImpl.st: Document classes. * SocketAddress.st: Document classes. Add #newSocket:. * Sockets.st: Document classes. Change #defaultImplementationClass to #defaultImplementationClassFor: or #activeSocketImplClass, use SocketAddress class>>#newSocket: instead of using directly AbstractSocket class>>#new:addressClass:. 2008-07-15 Paolo Bonzini * AbstractSocketImpl.st: Remove #addressClass, replace #new with #newFor:. Use SocketAddress class>>#fromSockAddr:port:. Define #outOfBandImplClass. Check for getpeername and getsockname errors better. Move OOBSocketImpl here... * IPSocketImpl.st: ... from here. Remove class-side #addressClass from AbstractSocketImpl. * SocketAddress.st: Provide default implementation classes. Use #new:addressClass: in #newRawSocket. Define SocketAddress class>>#fromSockAddr:port:. * Sockets.st: Add AbstractSocket class>>#new:addressClass:, use it instead of "self new: addressClass someSocketImplClass new" 2008-07-15 Paolo Bonzini * Datagram.st: Likewise. * IPSocketImpl.st: Likewise. * SocketAddress.st: Likewise. * Sockets.st: Likewise. * init.st: Likewise. Create TCP "forwarding" namespace. 2008-05-15 Paolo Bonzini * AbstractSocketImpl.st: Replace ByteArray buffers with garbage-collected CObjects. * IPSocketImpl.st: Likewise. * cfuncs.st: Change #byteArray and #byteArrayOut arguments to #cObject. 2008-03-25 Paolo Bonzini * AbstractSocketImpl.st: Use instance-side #checkError. 2008-03-18 Paolo Bonzini * Buffers.st: Add WriteBuffer>>#isFull. * Sockets.st: Add #canRead, #canWrite, #ensureReadable, #ensureWriteable. Map #available to #canRead (for backwards compatibility). * Tests.st: Use #canRead and #nextHunk. 2008-02-27 Paolo Bonzini * AbstractSocketImpl.st: Make sure fd is not nil when calling out to C. 2008-02-08 Paolo Bonzini * Sockets.st: Add #isPeerAlive to AbstractSocket. 2008-02-07 Paolo Bonzini * Sockets.st: Move some methods up to AbstractSocket, create a superclass of Socket (StreamSocket) that only performs read buffering. 2008-02-07 Paolo Bonzini * Sockets.st: Replace #nextPutAll: with #next:putAll:startingAt:. 2008-02-06 Paolo Bonzini * Sockets.st: Add methods needed by Sport. 2008-01-18 Paolo Bonzini * tcp.c: Cope with gethostbyname returning NULL. 2007-11-18 Freddie Akeroyd * tcp.c: Look for winsock 2.2. 2007-11-05 Paolo Bonzini * AbstractSocketImpl.st: Add #valueWithoutBuffering:. * IPSocketImpl.st: Likewise. * Sockets.st: Use it when flushing. * cfuncs.st: Add IPPROTO_TCP and TCP_NODELAY constants as TCPSocketImpl class methods. * tcp.c: Add a function that exports TCP_NODELAY. 2007-03-08 Paolo Bonzini * Buffers.st: Adjust for changes to Stream>>#copyFrom:. 2006-12-05 Paolo Bonzini *** Version 2.3 released. 2006-11-21 Paolo Bonzini * tcp.c: Add GPL exception. 2006-05-09 Paolo Bonzini * Sockets.st: Check if peer is dead in #bufferContents. 2005-05-09 Paolo Bonzini * Sockets.st: Do not fail on #flush or #fill if the peer is not alive anymore. 2005-08-23 Mike Anderson * Sockets.st: Fix thinkos. 2005-03-25 Paolo Bonzini * cfuncs.st: Switch to new C-call descriptions. 2004-12-20 Paolo Bonzini * tcp.c (O_NONBLOCK): Add here from sysdep.h. 2004-11-26 Paolo Bonzini * SocketAddress.st: fix typo in #newRawSocket. 2003-11-03 Paolo Bonzini * Buffers.st: force a buffer fill before triggering an EndOfStream notification. 2003-05-09 Paolo Bonzini *** Version 2.1.2 released. * Sockets.st: define AbstractSocket>>#isExternalStream. 2003-04-17 Paolo Bonzini *** Version 2.1.1 (stable) released. 2003-04-12 Paolo Bonzini *** Version 2.1 (stable) released. 2003-03-25 Paolo Bonzini * AbstractSocketImpl.st: fix bug in datagram sockets' #nextPut:. Thanks to the guy who reported it and whose address I've lost. 2003-03-01 Paolo Bonzini * AbstractSocketImpl.st: add VMpr_FileDescriptor_socketOp primitives. 2002-12-24 Paolo Bonzini * tcp.c: add function to export SO_ERROR * cfuncs.st: declare it * AbstractSocketImpl.st: check for SO_ERROR after waiting on a process; fix glitches in the handling of socket options. 2002-09-13 Paolo Bonzini *** Versions 2.0c (development) and 2.0.6 (stable) released 2002-08-14 Paolo Bonzini *** Version 2.0.5 (stable) released * Buffers.st: moved from examples/ since the browser is not using it anymore. * Sockets.st: allow a nil remote address for UDP sockets. 2002-08-12 Paolo Bonzini *** Version 2.0b (development) released * IPSocketImpl.st: adapt to recent changes in CObject. * init.st: don't initialize URL (removed) 2002-08-07 Paolo Bonzini *** Versions 2.0a (development) and 2.0.4 (stable) released * ContentHandler.st: removed * URL.st: removed 2002-07-17 Paolo Bonzini *** Version 2.0.3 released 2002-07-11 Paolo Bonzini *** Version 2.0.2 released 2002-07-06 Paolo Bonzini * Sockets.st: add #waitForConnection to ServerSocket 2002-06-28 Paolo Bonzini *** Version 2.0.1 released 2002-06-25 Paolo Bonzini *** Version 2.0 released 2002-06-03 Paolo Bonzini * tcp.c: fix UDP * Sockets.st: fix UDP * AbstractSocketImpl.st: fix UDP * Tests.st: added UDP loopback test 2002-06-02 Paolo Bonzini * tcp.c: return address family in myGetHostByName, accept it in myGetHostByAddr (as a primitive support for IPv6) * SocketAddress.st: use the new calling conventions; Cache is now a class variable, not a class instance variable. Removed IPAddress class from this file * cfuncs.st: declare the new calling conventions; declare IPAddress class>>#addressFamily * Socket.st: demand the choice of the implementation class to the address class * IPSocketImpl.st: moved IPAddress here 2002-05-28 Paolo Bonzini * ContentHandler.st: marked as obsolete and deemed that it will disappear in 2.1 * URL.st: likewise 2002-05-11 Paolo Bonzini *** Version 1.96.6 released 2002-05-10 Paolo Bonzini * tcp.c: copy a final zero address in gethostbyname 2002-04-14 Paolo Bonzini *** Version 1.96.5 released 2002-03-12 Paolo Bonzini *** Version 1.96.4 released 2002-01-29 Paolo Bonzini *** Version 1.96.3 released. 2002-01-04 Paolo Bonzini *** Version 1.96.2 released 2002-01-02 Paolo Bonzini * TCP.st: load into the TCP namespace 2001-11-20 Paolo Bonzini *** Version 1.96.1 released 2001-11-13 Paolo Bonzini * ContentHandler.st: prefixed # to symbols in arrays * SocketAddress.st: prefixed # to symbols in arrays * cfuncs.st: prefixed # to symbols in arrays 2001-10-27 Paolo Bonzini * Tests.st: use the ServerSocket's local address for the client Socket. Set ServerSocket's soReuseAddr option. 2001-10-26 Paolo Bonzini * SocketAddress.st: removed "class" in occurrences of "self class at: ... cache:" 2001-04-20 Paolo Bonzini * tcp.c: set errno to 0 instead of EINPROGRESS after a connect. 2001-04-20 Paolo Bonzini * tcp.c: force the socket in non-blocking mode during connect. 2001-04-16 Paolo Bonzini * AbstractSocketImpl.st: subclass from FileDescriptor * cfuncs.st: don't declare oobAvailable * init.st: don't file in UnixStream * tcp.c: removed UnixStream primitives 2001-04-02 Paolo Bonzini * init.st: use ObjectMemory instead of init blocks. * SocketAddress.st: use ObjectMemory instead of init blocks. 2001-02-23 Paolo Bonzini *** Released version 1.95.3 2001-02-02 Paolo Bonzini * tcp.c: use new VMProxy * cfuncs.h: removed 2000-01-30 Paolo Bonzini * AbstractSocketImpl.st: merged with SocketImpl.st, DatagramSocketImpl.st, MulticastSocketImpl.st; support multiple address families. * IPSocketImpl.st: created from TCPSocketImpl.st, UDPSocketImpl.st, OOBSocketImpl.st, ICMPSocketImpl.st * SocketAddress.st: created from IPAddress.st * Sockets.st: created from AbstractSocket.st, Socket.st, DatagramSocket.st, MulticastSocket.st, ServerSocket.st 2000-01-30 Paolo Bonzini * cfuncs.st: declared oobAvailable, sockStream, msgOOB and msgPeek * tcp.c: declared oobAvailable, sockStream, msgOOB and msgPeek * TCP.st: load OOBSocketImpl.st and RawSocketImpl.st * SocketImpl.st: added #outOfBandImplementation and #outOfBandInitialize:, moved many methods from TCPSocketImpl.st * MulticastSocketImpl.st: new file * OOBSocketImpl.st: new file * ICMPSocketImpl.st: new file * TCPSocketImpl.st: added #outOfBandImplementationClass, moved many methods to SocketImpl * UDPSocketImpl.st: moved many methods to DatagramSocketImpl * Datagram.st: added #data:, removed #sockAddr * DatagramSocket.st: allow to specify a default receiver and a buffer size, added #raw * DatagramSocketImpl.st: use #send:to:port: in #nextPut:, moved many methods from UDPSocketImpl.st 2000-06-17 Paolo Bonzini *** Released versions 1.95 (development) and 1.7.5 (stable) 2000-05-08 Paolo Bonzini * cfuncs.st: in some function definitions, changed the byteArray type specifier to byteArrayOut. This fixes bugs with accessing the local and remote addresses of sockets, and with receiving datagrams. 2000-05-04 Paolo Bonzini *** Version 1.94.90 released 2000-04-25 Paolo Bonzini * Datagram.st: added methods to use different ObjectDumpers * DatagramSocket.st: #peek: and #receive: now answer the Datagram. * *: commented the source code. 2000-04-12 Paolo Bonzini *** Version 1.7.4 released 2000-04-08 Paolo Bonzini * tcp.c: properly ignore SIGPIPE 2000-03-23 Paolo Bonzini *** Version 1.7.3 released 2000-03-11 Paolo Bonzini *** Version 1.7.2 released 2000-02-27 Paolo Bonzini * URL.st: implemented #= and hashing as per RFC 2068 2000-02-23 Paolo Bonzini * SocketImpl.st: added #hasBeenConnectedTo: to fix problem with the #remoteAddress of sockets created with #accept: * TCPSocketImpl.st: fixed #accept: * tcp.c: fixed getHostByAddr when host is unknown to the DNS server. 2000-02-22 Paolo Bonzini *** Version 1.7.1 released 2000-02-21 Paolo Bonzini * Socket.st: can adjust read/write buffer sizes after the Socket object has been created. 2000-02-15 Paolo Bonzini *** Version 1.7 released 2000-01-31 Paolo Bonzini *** Sixth beta of 1.7 (labeled 1.6.85) released 2000-01-31 Paolo Bonzini * TCPSocketImpl.st: fixed `message not understood' in #accept: * Socket.st: added the #producerConsumerTest 2000-01-30 Paolo Bonzini * IPAddress.st: fixed \\ instead of // in port: * Socket.st: fixed buffer filling to reveal dead connections, added a couple of test methods. * UnixStream.st: moved #canRead and #canWrite here from TCPSocketImpl and UDPSocketImpl. * TCPSocketImpl.st: removed #canRead/#canWrite * UDPSocketImpl.st: removed #canRead/#canWrite * AbstractSocketImpl.st: removed #canRead/#canWrite 2000-01-28 Paolo Bonzini * cfuncs.st: #anyLocalAddress had second arg declared as byteArray (should have been byteArrayOut). * tcp.c: fixed getAnyLocalAddress (missing cast to long) * UDPSocketImpl.st: copied changes to TCPSocketImpl.st here 2000-01-11 Nicolas Burrus * TCPSocketImpl.st: changed 'socket' to 'create' in method create * TCPSocketImpl.st: in methods canWrite and canRead changed 'forReading' to 'reading' * TCPSocketImpl.st: in getPeerName "intAt:" makes an error, replaced with "at:" * cfuncs.st: changed "Smalltalk" to "Namespace current" 2000-01-10 Nicolas Burrus * IPAdress.st: fixed bug in #allByName (`host := aString asLowerCase' was after the conditional) * Socket.st: #initialize now initializes Read/WriteBufferSize and defaultImplementationClass too. * TCPSocketImpl.st: 'pfInit' changed to 'pfInet' 1999-12-28 Paolo Bonzini *** Fifth beta of 1.7 (labeled 1.6.84) released 1999-11-26 Paolo Bonzini *** Fourth beta of 1.7 (labeled 1.6.83) released 1999-10-31 Paolo Bonzini *** Third beta of 1.7 (labeled 1.6.82) released 1999-10-22 Paolo Bonzini * IPAddress.st: method to return the IP address class was named #class which broke everything (now it is #addressClass). 1999-10-17 Paolo Bonzini * TCP.st: removed declaration of forward references to nil now that Undeclared is available. 1999-10-13 Paolo Bonzini * ReadBuffer.st: moved to examples/Buffers.st * WriteBuffer.st: moved to examples/Buffers.st * TCP.st: now loads examples/Buffers.st * AbstractSocket.st: added time-outs * Socket.st: added time-outs * DatagramSocket.st: added time-outs * TCPSocketImpl.st: added #canRead/#canWrite * UDPSocketImpl.st: added #canRead/#canWrite * cfuncs.st: added support for #canRead/#canWrite * tcp.c: added support for #canRead/#canWrite 1999-10-09 Paolo Bonzini *** Second beta of 1.7 (labeled 1.6.81) released 1999-09-29 Paolo Bonzini * ReadBuffer.st: added #bufferContents and #isFull * Socket.st: removed PositionableStream methods since they are in Stream now. 1999-09-25 Paolo Bonzini *** First beta of 1.7 (labeled 1.6.80) released 1999-09-18 Paolo Bonzini * AbstractSocket.st: moved buffering to Socket.st, changed superclass to Stream * IPAddress.st: support for "a.b.c", "a.b", "a" addresses in #fromString: * Socket.st: moved buffering from AbstractSocket.st, added various PositionableStream methods 1999-08-29 Paolo Bonzini *** Version 1.6.2 released. 1999-08-27 Paolo Bonzini * ContentHandler.st: incorporated part of URLConnection.st; test for TIFF files includes the version number (not really orthodox but makes the test more precise). * HTTPConnection.st: removed. * URLConnection.st: moved class methods to ContentHandler, removed instance methods. * TCP.st: changed in the list of files to be loaded. 1999-07-26 Paolo Bonzini * tcp.c: added `select' hacks from 1.1.5's tcp.c 1999-06-25 Paolo Bonzini *** Bug-fixing version 1.6.1 released. 1999-06-21 Paolo Bonzini * ContentHandler.st: changed category to Sockets-RFC. * HTTPConnection.st: changed category to Sockets-RFC. Added pattern-based choice of whether to use or not a proxy. * URLConnection.st: changed category to Sockets-RFC. * URL.st: changed category to Sockets-RFC. * tcp.c: added fullWrite. * tcp.c: the `write' callout now uses the fullWrite wrapper. 1999-06-17 Paolo Bonzini *** Version 1.6 released. 1999-05-10 Paolo Bonzini * URL.st: added #file accessor, which I had forgotten * URLConnection.st: added a default file extension map. 1999-04-27 Paolo Bonzini *** Version 1.5.beta3 released. 1999-04-23 Paolo Bonzini * tcp.c: added usage of the new HAVE_GETHOSTNAME symbol in gstconf.h 1999-04-10 Paolo Bonzini *** Version 1.5.beta2 released. 1999-03-15 Paolo Bonzini *** Version 1.5.beta1 released. 1999-01-18 Paolo Bonzini * URLConnection.st: created. * HTTPConnection.st: created. * Init.st: Created. 1999-01-17 Paolo Bonzini * URL.st: created. 1999-01-16 Paolo Bonzini * AbstractSocketImpl.st: created. * DatagramSocketImpl.st: created. * SocketImpl.st: created. * tcp.c: Happy birthday tcp.c!! Changed to support new socket implementation. * TCPSocketImpl.st: created. * UDPSocketImpl.st: created. 1999-01-15 Paolo Bonzini * AbstractSocket.st: Created * BufferedStream.st: Created * ContentHandler.st: Created * Datagram.st: Created. * DatagramSocket.st: Created * IPAddress.st: Created from tcp/hosts.st. * MulticastSocket.st: Created * ServerSocket.st: Created * Socket.st: Created * TCP.st: Created. 1998-10-18 Paolo Bonzini * UnixStream.st: Changed tell to a particular case of lseek 1998-09-02 Paolo Bonzini *** Began development of version 1.6 1995-09-30 Steve Byrne *** Version 1.1.5 released. 1995-01-16 Steve Byrne * tcp.c: Created. 1994-09-15 Steve Byrne *** Version 1.2.alpha1 released. 1992-02-23 Steve Byrne * UnixStream.st: Also added readShort and friends. * UnixStream.st: Added direction constants 1990-11-17 Steve Byrne * UnixStream.st: added read:numBytes: * UnixStream.st: Added skip: method. * UnixStream.st: Installed as a built-in class. smalltalk-3.2.5/packages/sockets/Tests.st0000644000175000017500000002167712123404352015342 00000000000000Stream subclass: DummyStream [ | n | DummyStream class >> new [ ^super new initialize ] initialize [ n := 0 ] nextPut: anObject [ n := n + 1 ] next: anInteger putAll: aCollection startingAt: pos [ n := n + anInteger ] size [ ^n ] ] Socket class extend [ microTest [ "Extremely small test (try to receive SMTP header)" | s | s := Socket remote: IPAddress anyLocalAddress port: 25. (s upTo: Character cr) printNl. s close ] testPort2For: anAddressClass [ anAddressClass == UnixAddress ifTrue: [ ^'/tmp/gst.test2' ]. ^54322 ] testPortFor: anAddressClass [ anAddressClass == UnixAddress ifTrue: [ ^'/tmp/gst.test' ]. ^54321 ] tweakedLoopbackTest [ "Send data from one socket to another on the local machine, trying to avoid buffering overhead. Tests most of the socket primitives. Comparison of the results of loopbackTest and tweakedLoopbackTest should give a measure of the overhead of buffering when sending/receiving large quantities of data." ^self loopbackTest: #(5000 4000) ] loopbackTest [ "Send data from one socket to another on the local machine. Tests most of the socket primitives." ^self loopbackTest: nil ] loopbackTest: bufferSizes [ "Send data from one socket to another on the local machine. Tests most of the socket primitives. The parameter is the size of the input and output buffer sizes." ^self loopbackTest: bufferSizes addressClass: Socket defaultAddressClass ] loopbackTestOn: addressClass [ "Send data from one socket to another on the local machine. Tests most of the socket primitives. The parameter is the address class (family) to use." ^self loopbackTest: nil addressClass: addressClass ] loopbackTest: bufferSizes addressClass: addressClass [ "Send data from one socket to another on the local machine. Tests most of the socket primitives. The parameters are the size of the input and output buffer sizes, and the address class (family) to use." | queue server client bytesToSend sendBuf bytesSent bytesReceived t extraBytes timeout process recvBuf | Transcript cr; show: 'starting loopback test'; cr. queue := ServerSocket port: (self testPortFor: addressClass) queueSize: 5 bindTo: addressClass loopbackHost. client := Socket remote: queue localAddress port: (self testPortFor: addressClass). bufferSizes isNil ifFalse: [client readBufferSize: (bufferSizes at: 1); writeBufferSize: (bufferSizes at: 2)]. timeout := false. process := [(Delay forMilliseconds: Socket timeout) wait. timeout := true] fork. [timeout ifTrue: [self error: 'could not establish connection']. (server := queue accept: StreamSocket) isNil] whileTrue: [Processor yield]. process terminate. Transcript show: 'connection established'; cr. bytesToSend := 5000000. sendBuf := String new: 4000 withAll: $x. recvBuf := DummyStream new. bytesSent := bytesReceived := 0. t := Time millisecondsToRun: [ [server nextPutAll: sendBuf. bytesSent := bytesSent + sendBuf size. [client canRead] whileTrue: [client nextAvailablePutAllOn: recvBuf. bytesReceived := recvBuf size]. bytesSent >= bytesToSend and: [bytesReceived = bytesSent]] whileFalse]. Transcript show: 'closing connection'; cr. extraBytes := client bufferContents size. server close. extraBytes > 0 ifTrue: [Transcript show: ' *** received ' , extraBytes size printString , ' extra bytes ***'; cr]. client close. queue close. Transcript show: 'loopback test done; ' , (t / 1000.0) printString , ' seconds'; cr; show: (bytesToSend asFloat / t roundTo: 0.01) printString; showCr: ' kBytes/sec' ] producerConsumerTest [ "Send data from one datagram socket to another on the local machine. Tests most of the socket primitives and works with different processes." ^self producerConsumerTestOn: Socket defaultAddressClass ] producerConsumerTestOn: addressClass [ "Send data from one socket to another on the local machine. Tests most of the socket primitives and works with different processes." | bytesToSend bytesSent bytesReceived t server client queue sema producer consumer queueReady | Transcript cr; show: 'starting loopback test'; cr. sema := Semaphore new. queueReady := Semaphore new. bytesToSend := 5000000. bytesSent := bytesReceived := 0. t := Time millisecondsToRun: [producer := [| timeout process sendBuf | queue := ServerSocket port: (self testPortFor: addressClass) queueSize: 5 bindTo: addressClass loopbackHost. queueReady signal. timeout := false. process := [(Delay forMilliseconds: Socket timeout) wait. timeout := true] fork. [timeout ifTrue: [self error: 'could not establish connection']. (server := queue accept ": StreamSocket") isNil] whileTrue: [Processor yield]. process terminate. Transcript show: 'connection established'; cr. sendBuf := String new: 4000 withAll: $x. [server nextPutAll: sendBuf. bytesSent := bytesSent + sendBuf size. bytesSent >= bytesToSend] whileFalse: [Processor yield]. sema signal] fork. consumer := [| recvBuf | recvBuf := DummyStream new. queueReady wait. client := Socket remote: queue localAddress port: (self testPortFor: addressClass). [[client canRead] whileTrue: [client nextAvailablePutAllOn: recvBuf. bytesReceived := recvBuf size]. bytesSent >= bytesToSend and: [bytesReceived = bytesSent]] whileFalse: [Processor yield]. sema signal] fork. sema wait. sema wait]. Transcript show: 'closing connection'; cr. server close. client close. queue close. Transcript show: 'loopback test done; ' , (t / 1000.0) printString , ' seconds'; cr; show: (bytesToSend asFloat / t roundTo: 0.01) printString; showCr: ' kBytes/sec' ] datagramLoopbackTest [ "Send data from one datagram socket to another on the local machine. Tests most of the socket primitives and works with different processes." ^self datagramLoopbackTestOn: Socket defaultAddressClass ] datagramLoopbackTestOn: addressClass [ "Send data from one datagram socket to another on the local machine. Tests most of the socket primitives and works with different processes." | bytesToSend bytesSent bytesReceived t | Transcript cr; show: 'starting datagram loopback test'; cr. bytesToSend := 5000000. bytesSent := bytesReceived := 0. t := Time millisecondsToRun: [| server client datagram | client := DatagramSocket local: addressClass loopbackHost port: (self testPort2For: addressClass). server := DatagramSocket remote: addressClass loopbackHost port: (self testPort2For: addressClass) local: nil port: (self testPortFor: addressClass). datagram := Datagram data: (String new: 128 withAll: $x) asByteArray. [server nextPut: datagram; flush. bytesSent := bytesSent + datagram data size. [client canRead] whileTrue: [bytesReceived := bytesReceived + client next data size]. bytesReceived < bytesToSend] whileTrue. Transcript show: 'closing connection'; cr. server close. client close]. Transcript show: 'udp loopback test done; ' , (t / 1000.0) printString , ' seconds'; cr; show: '% packets lost ' , (100 - (bytesReceived / bytesSent * 100)) asFloat printString; cr; show: (bytesToSend asFloat / t roundTo: 0.01) printString; showCr: ' kBytes/sec' ] sendTest [ "Send data to the 'discard' socket of localhost." ^self sendTest: '127.0.0.1' ] sendTest: host [ "Send data to the 'discard' socket of the given host. Tests the speed of one-way data transfers across the network to the given host. Note that many hosts do not run a discard server." "Socket sendTest: 'localhost'" | sock bytesToSend sendBuf bytesSent t | Transcript cr; show: 'starting send test'; cr. sock := Socket remote: host port: Socket portDiscard. Transcript show: 'connection established'; cr. bytesToSend := 5000000. sendBuf := String new: 4000 withAll: $x. bytesSent := 0. t := Time millisecondsToRun: [[bytesSent < bytesToSend] whileTrue: [sock nextPutAll: sendBuf; flush. bytesSent := bytesSent + sendBuf size]]. Transcript show: 'closing connection'; cr. sock close. Transcript show: 'send test done; time = ' , (t / 1000.0) printString, ' seconds'; cr; show: (bytesToSend asFloat / t) printString; showCr: ' kBytes/sec' ] ] smalltalk-3.2.5/packages/sockets/cfuncs.st0000644000175000017500000002051312123404352015505 00000000000000SocketAddress class extend [ addressFamily [ ] protocolFamily [ ] aiAddrconfig [ ] aiCanonname [ ] ] IPAddress class extend [ addressFamily [ ] protocolFamily [ ] ] IP6Address class extend [ addressFamily [ ] protocolFamily [ ] aiAll [ ] aiV4mapped [ ] ] UnixAddress class extend [ addressFamily [ ] protocolFamily [ ] ] AbstractSocketImpl class extend [ solSocket [ ] soLinger [ ] soReuseAddr [ ] sockDgram [ ] sockStream [ ] sockRDM [ ] sockRaw [ ] ] UDPSocketImpl class extend [ ipprotoIp [ ] protocol [ ] ] TCPSocketImpl class extend [ protocol [ ] ipprotoTcp [ ] tcpNodelay [ ] ] ICMP6SocketImpl class extend [ protocol [ ] ] ICMPSocketImpl class extend [ protocol [ ] ] OOBSocketImpl extend [ msgOOB [ ] ] DatagramSocketImpl extend [ msgPeek [ ] ipMulticastTtl [ ] ipMulticastIf [ ] ipAddMembership [ ] ipDropMembership [ ] ] CAddrInfoStruct extend [ free [ ] CAddrInfoStruct class >> getaddrinfo: name service: servname hints: hints result: res [ ] aiAddr [ ] aiCanonname [ ] ] SocketAddress class extend [ primName: address len: len type: addressFamily [ ] primLocalName [ ] ] AbstractSocketImpl extend [ accept: socket peer: peer addrLen: len [ ] bind: socket to: addr addrLen: len [ ] connect: socket to: addr addrLen: len [ ] listen: socket log: len [ ] getPeerName: socket addr: addr addrLen: len [ ] getSockName: socket addr: addr addrLen: len [ ] receive: socket buffer: buf size: len flags: flags from: addr size: addrLen [ ] send: socket buffer: buf size: len flags: flags to: addr size: addrLen [ ] soError: socket [ ] option: socket level: level at: name put: value size: len [ ] option: socket level: level at: name get: value size: len [ ] create: family type: type protocol: protocol [ ] ] AbstractSocketImpl class extend [ accept: socket peer: peer addrLen: len [ ] bind: socket to: addr addrLen: len [ ] connect: socket to: addr addrLen: len [ ] listen: socket log: len [ ] getPeerName: socket addr: addr addrLen: len [ ] getSockName: socket addr: addr addrLen: len [ ] receive: socket buffer: buf size: len flags: flags from: addr size: addrLen [ ] send: socket buffer: buf size: len flags: flags to: addr size: addrLen [ ] option: socket level: level at: name put: value size: len [ ] option: socket level: level at: name get: value size: len [ ] create: family type: type protocol: protocol [ ] ] smalltalk-3.2.5/packages/sockets/init.st0000644000175000017500000000322312123404352015166 00000000000000"====================================================================== | | Smalltalk sockets classes (initialization script). | | ======================================================================" "====================================================================== | | Copyright 1999, 2000, 2001, 2002, 2008 Free Software Foundation, Inc. | Written by Paolo Bonzini. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" Eval [ Socket initialize. DatagramSocket initialize. ServerSocket initialize. IPAddress initialize. IP6Address initialize. UnixAddress initialize. ObjectMemory addDependent: SocketAddress. SocketAddress update: #returnFromSnapshot. "Backwards compatibility." Sockets addSubspace: #TCP. Smalltalk at: #TCP put: Sockets.TCP. ] smalltalk-3.2.5/packages/sockets/UnitTest.st0000644000175000017500000000530112123404352016001 00000000000000"====================================================================== | | SUnit Test Cases for the Socket Code | | ======================================================================" "====================================================================== | | Copyright 2011 Free Software Foundation, Inc. | Written by Holger Hans Peter Freyther. | | This file is part of GNU Smalltalk. | | GNU Smalltalk is free software; you can redistribute it and/or modify it | under the terms of the GNU General Public License as published by the Free | Software Foundation; either version 2, or (at your option) any later version. | | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS | FOR A PARTICULAR PURPOSE. See the GNU General Public License for more | details. | | You should have received a copy of the GNU General Public License along with | GNU Smalltalk; see the file COPYING. If not, write to the Free Software | Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. | ======================================================================" TestCase subclass: SocketTest [ testDoNotCrashOnSendto [ " The objective of this test is to check if the c code is crashing with 'invalid' input. " | socket addrLen datagram | socket := DatagramSocket new. "Passing the wrong bits to the call out will abort." addrLen := CInt gcValue: 0. socket implementation accept: -1 peer: nil addrLen: addrLen; bind: -1 to: nil addrLen: 0; connect: -1 to: nil addrLen: 0; getPeerName: -1 addr: nil addrLen: addrLen; getSockName: -1 addr: nil addrLen: addrLen; receive: -1 buffer: nil size: 0 flags: 0 from: nil size: addrLen. "Pass a datagram with no destination." datagram := Datagram new. socket nextPut: datagram. ] testDoNotCrashWithWrongTypes [ "The objective is to see if wrong types for a cCallout will make the VM crash or not. It should also check if these calls raise the appropriate exception." | socket impl | socket := DatagramSocket new. impl := socket implementation. self should: [impl accept: -1 peer: nil addrLen: 0] raise: SystemExceptions.PrimitiveFailed. self should: [impl getPeerName: -1 addr: nil addrLen: 0] raise: SystemExceptions.PrimitiveFailed. self should: [impl getSockName: -1 addr: nil addrLen: 0] raise: SystemExceptions.PrimitiveFailed. self should: [impl receive: -1 buffer: nil size: 0 flags: 0 from: nil size: 0] raise: SystemExceptions.PrimitiveFailed. ] ] smalltalk-3.2.5/packages/sockets/SocketAddress.st0000644000175000017500000003314512123404352016767 00000000000000"====================================================================== | | Smalltalk sockets - SocketAddress class | | ======================================================================" "====================================================================== | | Copyright 1999, 2000, 2001, 2002, 2008, 2009 Free Software Foundation, Inc. | Written by Paolo Bonzini. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" Object subclass: SocketAddress [ | name | SocketAddress class [ | anyLocalAddress loopbackHost unknownAddress defaultStreamSocketImplClass defaultDatagramSocketImplClass defaultRawSocketImplClass | ] Cache := nil. LocalHostName := nil. SocketAddress class >> defaultStreamSocketImplClass [ "Answer the class that, by default, is used to map between the Socket's protocol and a low-level C interface." ^defaultStreamSocketImplClass ifNil: [ SocketImpl ] ] SocketAddress class >> defaultStreamSocketImplClass: aClass [ "Set which class will be used by default to map between the receiver's protocol and a low-level C interface." defaultStreamSocketImplClass := aClass ] SocketAddress class >> defaultRawSocketImplClass [ "Answer the class that, by default, is used to map between the Socket's protocol and a low-level C interface." ^defaultRawSocketImplClass ifNil: [ RawSocketImpl ] ] SocketAddress class >> defaultRawSocketImplClass: aClass [ "Set which class will be used by default to map between the receiver's protocol and a low-level C interface." defaultRawSocketImplClass := aClass ] SocketAddress class >> defaultDatagramSocketImplClass [ "Answer the class that, by default, is used to map between the Socket's protocol and a low-level C interface." ^defaultDatagramSocketImplClass ifNil: [ DatagramSocketImpl ] ] SocketAddress class >> defaultDatagramSocketImplClass: aClass [ "Set which class will be used by default to map between the receiver's protocol and a low-level C interface." defaultDatagramSocketImplClass := aClass ] SocketAddress class >> newSocket: socketClass [ "Answer a new instance of socketClass, using the protocol family of the receiver." ^socketClass new: (socketClass defaultImplementationClassFor: self) addressClass: self ] SocketAddress class >> newRawSocket [ "Create a new raw socket, providing access to low-level network protocols and interfaces for the protocol family represented by the receiver (for example, the C protocol family PF_INET for the IPAddress class) Ordinary user programs usually have no need to use this method." ^DatagramSocket new: self defaultRawSocketImplClass addressClass: self ] SocketAddress class >> initLocalAddresses [ "Private - Initialize the anyLocalAddress class-instance variable for the entire hierarchy." | all | "Initialize to the loopback host." self withAllSubclassesDo: [ :each | each anyLocalAddress: each loopbackHost]. "Override with resolved addresses." all := self allByName: self localHostName. all isNil ifFalse: [all do: [ :each | each class anyLocalAddress: each ]] ] SocketAddress class >> flush [ "Flush the cached IP addresses." LocalHostName := nil. Cache := Dictionary new. self withAllSubclassesDo: [:each | each anyLocalAddress: nil ]. ] SocketAddress class >> createUnknownAddress [ "Answer an object representing an unkown address in the address family for the receiver" ^Socket defaultAddressClass unknownAddress ] SocketAddress class >> createLoopbackHost [ "Answer an object representing the loopback host in the address family for the receiver." ^Socket defaultAddressClass loopbackHost ] SocketAddress class >> update: aspect [ "Flush all the caches for IPAddress subclasses" aspect == #returnFromSnapshot ifTrue: [self flush]. ] SocketAddress class >> anyLocalAddress [ "Answer an IPAddress representing a local address." "The local address can be computed with a single lookup for all the classes." anyLocalAddress isNil ifTrue: [ SocketAddress initLocalAddresses ]. ^anyLocalAddress ] SocketAddress class >> anyLocalAddress: anObject [ "Private - Store an object representing a local address in the address family for the receiver" anyLocalAddress := anObject ] SocketAddress class >> at: host cache: aBlock [ "Private - Answer the list of addresses associated to the given host in the cache. If the host is not cached yet, evaluate aBlock and cache and answer the result." self == SocketAddress ifFalse: [ ^aBlock value ]. ^Cache at: host ifAbsent: [ | result | result := aBlock value. result isNil ifTrue: [ nil ] ifFalse: [ Cache at: host put: result ] ] ] SocketAddress class >> aiFlags [ ^self == SocketAddress ifTrue: [ self aiAddrconfig ] ifFalse: [ 0 ] ] SocketAddress class >> isDigitAddress: aString [ "Answer whether the receiver can interpret aString as a valid address without going through a resolver." ^false ] SocketAddress class >> localHostName [ "Answer the name of the local machine." LocalHostName isNil ifTrue: [ LocalHostName := self primLocalName ]. ^LocalHostName ] SocketAddress class >> loopbackHost [ "Answer an instance of the receiver representing the local machine (127.0.0.1 in the IPv4 family)." loopbackHost isNil ifTrue: [ loopbackHost := self createLoopbackHost ]. loopbackHost name: self localHostName. ^loopbackHost ] SocketAddress class >> unknownAddress [ "Answer an instance of the receiver representing an unknown machine (0.0.0.0 in the IPv4 family)." unknownAddress isNil ifTrue: [ unknownAddress := self createUnknownAddress ]. ^unknownAddress ] SocketAddress class >> allByName: aString [ "Answer all the IP addresses that refer to the the given host. If a digit address is passed in aString, the result is an array containing the single passed address. If the host could not be resolved to an IP address, answer nil." | host addresses | host := aString asLowercase. self withAllSubclassesDo: [:c | (c isDigitAddress: host) ifTrue: [^self at: host cache: [Array with: (c fromString: host)]]]. addresses := self at: host cache: [ | hints result array | hints := CAddrInfoStruct gcNew. hints aiFamily value: self protocolFamily. hints aiFlags value: (self aiFlags bitOr: self aiCanonname). [(result := hints getaddrinfo: host) isNil ifTrue: [nil] ifFalse: [ array := self extractAddressesAfterLookup: result. array isEmpty ifTrue: [nil] ifFalse: [array]]] ensure: [result free]]. ^addresses ] SocketAddress class >> byName: aString [ "Answer a single IP address that refer to the the given host. If a digit address is passed in aString, the result is the same as using #fromString:. If the host could not be resolved to an IP address, answer nil." | all | aString isEmpty ifTrue: [^self loopbackHost]. all := self allByName: aString. all isNil ifTrue: [^nil]. self == SocketAddress ifFalse: [^all anyOne]. ^all detect: [:each | each isKindOf: Socket defaultAddressClass] ifNone: [all anyOne] ] SocketAddress class >> extractAddressesAfterLookup: aiHead [ "Private - Given a CByte object, extract the arrays returned by gethostbyname and answer them." | result addrBytes addr ai name | result := OrderedCollection new. name := aiHead aiCanonname value. ai := aiHead. [ ai isNil ] whileFalse: [ addrBytes := ByteArray fromCData: ai aiAddr value size: ai aiAddrlen value. addr := self extractFromSockAddr: addrBytes port: NullValueHolder uniqueInstance. addr isNil ifFalse: [ addr name: name. (result includes: addr) ifFalse: [ result add: addr ] ]. ai := ai aiNext value ]. ^result ] SocketAddress class >> extractFromSockAddr: aByteArray port: portAdaptor [ "Private - Answer a new SocketAddress from a ByteArray containing a C sockaddr structure. The portAdaptor's value is changed to contain the port that the structure refers to." | addressFamily | "BSD systems place a length byte at offset 1, so look-up offset 2 first. If it is 0, we're on a little-endian system without the sa_len field, so use offset 1 as a second possibility." addressFamily := aByteArray at: 2. addressFamily = 0 ifTrue: [ addressFamily := aByteArray at: 1 ]. self allSubclassesDo: [ :each | each addressFamily = addressFamily ifTrue: [ ^each fromSockAddr: aByteArray port: portAdaptor ] ]. ^nil ] SocketAddress class >> fromSockAddr: aByteArray port: portAdaptor [ "Private - Answer a new IPAddress from a ByteArray containing a C sockaddr structure. The portAdaptor's value is changed to contain the port that the structure refers to. Raise an error if the address family is unknown." ^(self extractFromSockAddr: aByteArray port: portAdaptor) ifNil: [ self error: 'unknown address family' ] ] = aSocketAddress [ "Answer whether the receiver and aSocketAddress represent the same machine. The host name is not checked because an IPAddress created before a DNS is activated is named after its numbers-and-dots notation, while the same IPAddress, created when a DNS is active, is named after its resolved name." ^self class == aSocketAddress class and: [self asByteArray = aSocketAddress asByteArray] ] isMulticast [ "Answer whether an address is reserved for multicast connections." ^false ] hash [ "Answer an hash value for the receiver" ^self asByteArray hash ] name [ "Answer the host name (or the digit notation if the DNS could not resolve the address). If the DNS answers a different IP address for the same name, the second response is not cached and the digit notation is also returned (somebody's likely playing strange jokes with your DNS)." | addresses bytes | name isNil ifFalse: [^name]. bytes := self asByteArray. name := self class primName: bytes len: bytes size type: self class addressFamily. "No DNS active..." name isNil ifTrue: [^name := self printString]. addresses := self class at: name cache: [Array with: self]. addresses do: [:each | each getName isNil ifTrue: [each name: name]. (each = self and: [each getName ~= name]) ifTrue: ["Seems like someone's joking with the DNS server and changed this host's IP address even though the name stays the same. Don't cache the name and don't even give away an alphanumeric name" ^name := self printString]]. ^name ] asByteArray [ "Convert the receiver to a ByteArray passed to the operating system's socket functions)" self subclassResponsibility ] getName [ "Private - Answer the name (which could be nil if the name has not been cached yet)." ^name ] name: newName [ "Private - Cache the name of the host which the receiver represents." name := newName ] ] CStruct subclass: CAddrInfoStruct [ getaddrinfo: name [ ^self getaddrinfo: name service: nil ] getaddrinfo: name service: service [ | res | res := self class address: 0. (CAddrInfoStruct getaddrinfo: name service: service hints: self result: res) = -1 ifTrue: [ ^nil ]. res address = 0 ifTrue: [ ^nil ]. ^res ] ] smalltalk-3.2.5/packages/sockets/IPSocketImpl.st0000644000175000017500000003312612123404352016533 00000000000000"====================================================================== | | Smalltalk IPv4 sockets | | ======================================================================" "====================================================================== | | Copyright 1999, 2000, 2001, 2002, 2008 Free Software Foundation, Inc. | Written by Paolo Bonzini. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" SocketAddress subclass: IPAddress [ | address | IPAddress class >> initialize [ "Set up the default implementation classes for the receiver" self defaultRawSocketImplClass: ICMPSocketImpl. self defaultDatagramSocketImplClass: UDPSocketImpl. self defaultStreamSocketImplClass: TCPSocketImpl ] IPAddress class >> createLoopbackHost [ "Answer an object representing the loopback host in the address family for the receiver. This is 127.0.0.1 for IPv4." ^IPAddress fromBytes: #[127 0 0 1] ] IPAddress class >> createUnknownAddress [ "Answer an object representing an unkown address in the address family for the receiver" ^(IPAddress fromBytes: #[0 0 0 0]) name: '0.0.0.0'; yourself ] IPAddress class >> addressSize [ "Answer the size of an IPv4 address." ^4 ] IPAddress class >> version [ "Answer the version of IP that the receiver implements." ^4 ] IPAddress class >> fromBytes: aByteArray [ "Answer a new IPAddress from a ByteArray containing the bytes in the same order as the digit form: 131.175.6.2 would be represented as #[131 175 6 2]." ^self basicNew address: ((aByteArray copyFrom: 1 to: 4) makeReadOnly: true) ] IPAddress class >> fromSockAddr: aByteArray port: portAdaptor [ "Private - Answer a new IPAddress from a ByteArray containing a C sockaddr_in structure. The portAdaptor's value is changed to contain the port that the structure refers to." portAdaptor value: (aByteArray at: 3) * 256 + (aByteArray at: 4). ^self fromBytes: (aByteArray copyFrom: 5 to: 8) ] IPAddress class >> fromString: aString [ "Answer a new IPAddress from a String containing the requested address in digit form. Hexadecimal forms are not allowed. An Internet host address is a number containing four bytes of data. These are divided into two parts, a network number and a local network address number within that network. The network number consists of the first one, two or three bytes; the rest of the bytes are the local address. Network numbers are registered with the Network Information Center (NIC), and are divided into three classes--A, B, and C. The local network address numbers of individual machines are registered with the administrator of the particular network. Class A networks have single-byte numbers in the range 0 to 127. There are only a small number of Class A networks, but they can each support a very large number of hosts (several millions). Medium-sized Class B networks have two-byte network numbers, with the first byte in the range 128 to 191; they support several thousands of host, but are almost exhausted. Class C networks are the smallest and the most commonly available; they have three-byte network numbers, with the first byte in the range 192-223. Class D (multicast, 224.0.0.0 to 239.255.255.255) and E (research, 240.0.0.0 to 255.255.255.255) also have three-byte network numbers. Thus, the first 1, 2, or 3 bytes of an Internet address specifies a network. The remaining bytes of the Internet address specify the address within that network. The Class A network 0 is reserved for broadcast to all networks. In addition, the host number 0 within each network is reserved for broadcast to all hosts in that network. The Class A network 127 is reserved for loopback; you can always use the Internet address `127.0.0.1' to refer to the host machine (this is answered by the #loopbackHost class method). Since a single machine can be a member of multiple networks, it can have multiple Internet host addresses. However, there is never supposed to be more than one machine with the same host address. There are four forms of the standard numbers-and-dots notation for Internet addresses: a.b.c.d specifies all four bytes of the address individually; a.b.c interprets as a 2-byte quantity, which is useful for specifying host addresses in a Class B network with network address number a.b; a.b intrprets the last part of the address as a 3-byte quantity, which is useful for specifying host addresses in a Class A network with network address number a. If only one part is given, this corresponds directly to the host address number." | substrings | substrings := aString substrings: $.. substrings := substrings collect: [:each | each asInteger]. ^self fromArray: substrings ] IPAddress class >> fromArray: parts [ "Answer a new IPAddress from an array of numbers; the numbers are to be thought as the dot-separated numbers in the standard numbers-and-dots notation for IPv4 addresses." | result last | result := ByteArray new: 4. "e.g. 2 parts (a.b): byte 1 are taken from a and b; byte 4 and 3 are bits 0-7 and 8-15 of c respectively; byte 2 is whatever remains (bits 16-23 is the string is well-formed). Handling (result at: parts size) specially simplifies error checking." 1 to: parts size - 1 do: [:i | result at: i put: (parts at: i) asInteger]. last := (parts at: parts size) asInteger. result size to: parts size + 1 by: -1 do: [:i | result at: i put: last \\ 256. last := last // 256]. result at: parts size put: last. ^self fromBytes: result ] IPAddress class >> new [ self shouldNotImplement ] IPAddress class >> with: b1 with: b2 with: b3 with: b4 [ "Answer a new IPAddress whose bytes (from most-significant to least-significant) are in the parameters." ^self basicNew address: ((ByteArray with: b1 with: b2 with: b3 with: b4) makeReadOnly: true) ] IPAddress class >> isDigitAddress: aString [ "Answer whether aString is a valid address in a.b.c.d form." | dots | dots := 0. (aString substrings: $.) do: [:part | dots := dots + 1. (part allSatisfy: [:each | each isDigit]) ifFalse: [^false]. part asInteger > 255 ifTrue: [^false]]. ^dots = 4 ] asByteArray [ "Answer a read-only ByteArray of size four containing the receiver's bytes in network order (big-endian)" ^address ] addressClass [ "Answer the `address class' of the receiver (see IPAddress class>>#fromString:)" | net | net := address at: 1. net < 128 ifTrue: [^$A]. net < 192 ifTrue: [^$B]. net < 224 ifTrue: [^$C]. ^net < 240 ifTrue: [$D] ifFalse: [$E] ] host [ "Answer an host number for the receiver; this is given by the last three bytes for class A addresses, by the last two bytes for class B addresses, else by the last byte." | net | net := address at: 1. net < 128 ifTrue: [^(address at: 4) + ((address at: 3) * 256) + ((address at: 2) * 65536)]. net < 192 ifTrue: [^(address at: 4) + ((address at: 3) * 256)]. ^address at: 4 ] network [ "Answer a network number for the receiver; this is given by the first three bytes for class C/D/E addresses, by the first two bytes for class B addresses, else by the first byte." | net | net := address at: 1. net < 128 ifTrue: [^net]. net < 192 ifTrue: [^net * 256 + (address at: 2)]. ^net * 65536 + ((address at: 2) * 256) + (address at: 2) ] subnet [ "Answer an host number for the receiver; this is 0 for class A addresses, while it is given by the last byte of the network number for class B/C/D/E addresses." | net | net := address at: 1. net < 128 ifTrue: [^address at: 2]. net < 192 ifTrue: [^address at: 3]. ^0 ] isMulticast [ "Answer whether the receiver reprensents an address reserved for multicast datagram connections" ^(address at: 1) between: 224 and: 239 "^self addressClass == $D" ] printOn: aStream [ "Print the receiver in dot notation." address do: [:each | each printOn: aStream] separatedBy: [aStream nextPut: $.] ] address: aByteArray [ "Private - Set the ByteArray corresponding to the four parts of the IP address in dot notation" address := aByteArray ] port: port [ "Return a ByteArray containing a struct sockaddr for the given port on the IP address represented by the receiver. Family = AF_INET." port < 0 | (port > 65535) ifTrue: [self error: 'port out of range']. ^(ByteArray new: 16) "Write sin_addr" replaceFrom: 5 to: 8 with: address startingAt: 1; "Write sin_len and sin_family = AF_INET" at: 1 put: 16; at: 2 put: self class addressFamily; "Write sin_port in network order (big endian)" at: 3 put: port // 256; at: 4 put: (port bitAnd: 255); yourself ] ] SocketImpl subclass: TCPSocketImpl [ valueWithoutBuffering: aBlock [ "Evaluate aBlock, ensuring that any data that it writes to the socket is sent immediately to the network." ^[self optionAt: self class tcpNodelay level: self class ipprotoTcp put: 1. aBlock value] ensure: [self optionAt: self class tcpNodelay level: self class ipprotoTcp put: 0] ] ] MulticastSocketImpl subclass: UDPSocketImpl [ ipMulticastIf [ "Answer the local device for a multicast socket (in the form of an address)" ^self addressClass fromByteArray: (self optionAt: self ipMulticastIf level: self class ipprotoIp size: CInt sizeof) ] ipMulticastIf: interface [ "Set the local device for a multicast socket (in the form of an address, usually anyLocalAddress)" self optionAt: self ipMulticastIf level: self class ipprotoIp put: interface ] join: ipAddress [ "Join the multicast socket at the given address" self primJoinLeave: ipAddress option: self ipAddMembership ] leave: ipAddress [ "Leave the multicast socket at the given address" self primJoinLeave: ipAddress option: self ipDropMembership ] primJoinLeave: ipAddress option: opt [ "Private - Used to join or leave a multicast service." | data | data := ByteArray new: IPAddress addressSize * 2. data replaceFrom: 1 to: IPAddress addressSize with: ipAddress asByteArray startingAt: 1; replaceFrom: IPAddress addressSize + 1 to: data size with: IPAddress anyLocalAddress asByteArray startingAt: 1. self optionAt: opt level: self class ipprotoIp put: data ] timeToLive [ "Answer the time to live of the datagrams sent through the receiver to a multicast socket." ^(self optionAt: self ipMulticastTtl level: self class ipprotoIp size: CInt sizeof) intAt: 1 ] timeToLive: ttl [ "Set the time to live of the datagrams sent through the receiver to a multicast socket." self optionAt: self ipMulticastTtl level: self class ipprotoIp put: ttl ] ] RawSocketImpl subclass: ICMPSocketImpl [ ] smalltalk-3.2.5/packages/sockets/AbstractSocketImpl.st0000644000175000017500000005146412123404352017773 00000000000000"====================================================================== | | Abstract socket implementations | | ======================================================================" "====================================================================== | | Copyright 1999, 2000, 2001, 2002, 2008, 2009 Free Software Foundation, Inc. | Written by Paolo Bonzini. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" FileDescriptor subclass: AbstractSocketImpl [ | localAddress localPort remoteAddress remotePort | AbstractSocketImpl class >> addressClass [ "Answer the class responsible for handling addresses for the receiver" self subclassResponsibility ] AbstractSocketImpl class >> protocol [ "Answer the protocol parameter for `create'" ^0 ] AbstractSocketImpl class >> socketType [ "Answer the socket type parameter for `create'." self subclassResponsibility ] AbstractSocketImpl class >> newFor: addressClass [ "Create a socket for the receiver." | descriptor | descriptor := self create: addressClass protocolFamily type: self socketType protocol: self protocol. descriptor < 0 ifTrue: [ File checkError ]. ^self on: descriptor ] accept: implementationClass [ "Accept a connection on the receiver, and create a new instance of implementationClass that will deal with the newly created active server socket." | peer addrLen newFD fd | peer := ByteArray new: 128. addrLen := CInt gcValue: 128. (fd := self fd) isNil ifTrue: [ ^SystemExceptions.EndOfStream signal ]. newFD := self accept: fd peer: peer addrLen: addrLen. newFD < 0 ifTrue: [ self checkSoError ]. ^(implementationClass on: newFD) hasBeenBound; hasBeenConnectedTo: peer; yourself ] bindTo: ipAddress port: port [ "Bind the receiver to the given IP address and port. `Binding' means attaching the local endpoint of the socket." | addr fd | addr := ipAddress port: port. (fd := self fd) isNil ifTrue: [ ^self ]. [(self bind: fd to: addr addrLen: addr size) < 0 ifTrue: [File checkError] ] ifCurtailed: [self close]. self isOpen ifTrue: [self hasBeenBound] ] fileOp: ioFuncIndex [ "Private - Used to limit the number of primitives used by FileStreams" self checkError. ^nil ] fileOp: ioFuncIndex ifFail: aBlock [ "Private - Used to limit the number of primitives used by FileStreams." ^aBlock value ] fileOp: ioFuncIndex with: arg1 [ "Private - Used to limit the number of primitives used by FileStreams" self checkError. ^nil ] fileOp: ioFuncIndex with: arg1 ifFail: aBlock [ "Private - Used to limit the number of primitives used by FileStreams." ^aBlock value ] fileOp: ioFuncIndex with: arg1 with: arg2 [ "Private - Used to limit the number of primitives used by FileStreams" self checkError. ^nil ] fileOp: ioFuncIndex with: arg1 with: arg2 ifFail: aBlock [ "Private - Used to limit the number of primitives used by FileStreams." ^aBlock value ] fileOp: ioFuncIndex with: arg1 with: arg2 with: arg3 [ "Private - Used to limit the number of primitives used by FileStreams" self checkError. ^nil ] fileOp: ioFuncIndex with: arg1 with: arg2 with: arg3 ifFail: aBlock [ "Private - Used to limit the number of primitives used by FileStreams." ^aBlock value ] getSockName [ "Retrieve a ByteArray containing a sockaddr_in struct for the local endpoint of the socket." | sock addrLen fd | sock := ByteArray new: 128. addrLen := CInt gcValue: 128. (fd := self fd) isNil ifTrue: [ ^nil ]. (self getSockName: self fd addr: sock addrLen: addrLen) = -1 ifTrue: [ ^nil ]. ^sock ] listen: backlog [ "Make the receiver a passive server socket with a pending connections queue of the given size." | fd | (fd := self fd) isNil ifTrue: [ ^self ]. self listen: fd log: backlog ] connectTo: ipAddress port: port [ "Connect the receiver to the given IP address and port. `Connecting' means attaching the remote endpoint of the socket." self hasBeenConnectedTo: ipAddress port: port ] localAddress [ "Answer the address of the local endpoint of the socket (even if IP is not being used, this identifies the machine that is bound to the socket)." ^localAddress ] localPort [ "Answer the port of the local endpoint of the socket (even if IP is not being used, this identifies the service or process that is bound to the socket)." ^localPort ] remoteAddress [ "Answer the address of the remote endpoint of the socket (even if IP is not being used, this identifies the machine to which the socket is connected)." ^remoteAddress ] remotePort [ "Answer the port of the remote endpoint of the socket (even if IP is not being used, this identifies the service or process to which the socket is connected)." ^remotePort ] valueWithoutBuffering: aBlock [ "Evaluate aBlock, ensuring that any data that it writes to the socket is sent immediately to the network." aBlock value ] optionAt: opt level: level size: size [ "Answer in a ByteArray of the given size the value of a socket option. The option identifier is in `opt' and the level is in `level'. A layer over this method is provided for the most common socket options, so this will be rarely used." | result len fd | result := ByteArray new: size. len := CInt gcValue: size. (fd := self fd) isNil ifTrue: [ ^nil ]. self option: fd level: level at: opt get: result size: len. ^result ] optionAt: opt level: level put: anObject [ "Modify the value of a socket option. The option identifier is in `opt' and the level is in `level'. anObject can be a boolean, integer, socket address or ByteArray. A layer over this method is provided for the most common socket options, so this will be rarely used." | ba fd | ba := self makeByteArray: anObject. (fd := self fd) isNil ifTrue: [ ^self ]. self option: fd level: level at: opt put: ba size: ba size ] soLinger [ "Answer the number of seconds by which a `close' operation can block to ensure that all the packets have reliably reached the destination, or nil if those packets are left to their destiny." | data | data := self optionAt: self class soLinger level: self class solSocket size: CInt sizeof * 2. (data intAt: 1) = 0 ifTrue: [^nil]. ^data intAt: CInt sizeof + 1 ] soLinger: linger [ "Set the number of seconds by which a `close' operation can block to ensure that all the packets have reliably reached the destination. If linger is nil, those packets are left to their destiny." | data | data := ByteArray new: CInt sizeof * 2. linger isNil ifFalse: [data at: 1 put: 1. data intAt: CInt sizeof + 1 put: linger]. self optionAt: self class soLinger level: self class solSocket put: data ] soReuseAddr [ "Answer whether another socket can be bound the same local address as this one. If you enable this option, you can actually have two sockets with the same Internet port number; but the system won't allow you to use the two identically-named sockets in a way that would confuse the Internet. The reason for this option is that some higher-level Internet protocols, including FTP, require you to keep reusing the same socket number." ^((self optionAt: self class soReuseAddr level: self class solSocket size: CInt sizeof) intAt: 1) > 0 ] soReuseAddr: aBoolean [ "Set whether another socket can be bound the same local address as this one." self optionAt: self class soReuseAddr level: self class solSocket put: aBoolean ] makeByteArray: anObject [ "Private - Convert anObject to a ByteArray to be used to store socket options. This can be a ByteArray, a socket address valid for this class, an Integer or a Boolean." anObject == true ifTrue: [ ^#[1 0 0 0]]. anObject == false ifTrue: [ ^#[0 0 0 0]]. anObject isInteger ifTrue: [ ^(ByteArray new: CInt sizeof) at: 1 put: (anObject bitAnd: 255); at: 2 put: (anObject // 256 bitAnd: 255); at: 3 put: (anObject // 65536 bitAnd: 255); at: 4 put: (anObject // 16777216 bitAnd: 255); yourself]. ^anObject asByteArray ] hasBeenConnectedTo: ipAddress port: port [ "Store the remote address and port that the receiver is connected to." remoteAddress := ipAddress. remotePort := port ] hasBeenConnectedTo: sockAddr [ "Store the remote address and port that the receiver is connected to." | port | port := ValueHolder new. self hasBeenConnectedTo: (SocketAddress fromSockAddr: sockAddr port: port) port: port value ] hasBeenBoundTo: ipAddress port: port [ "Store the local address and port that the receiver is bound to." localAddress := ipAddress. localPort := port ] hasBeenBoundTo: sockAddr [ "Store the local address and port that the receiver has been bound to." | port | port := ValueHolder new. self hasBeenBoundTo: (SocketAddress fromSockAddr: sockAddr port: port) port: port value ] hasBeenBound [ "Retrieve the local address and port that the receiver has been bound to." self hasBeenBoundTo: self getSockName ] checkSoError [ "Retrieve SO_ERROR and, if non-zero, raise an exception for its value." self isOpen ifFalse: [^SystemExceptions.FileError signal: 'file closed']. File checkError: self soError ] ensureReadable [ "If the file is open, wait until data can be read from it. The wait allows other Processes to run." self isOpen ifFalse: [^self]. self fileOp: 14 with: 0 with: Semaphore new ifFail: [[self checkSoError] ensure: [^self close]]. self isOpen ifFalse: [^self]. self fileOp: 13 with: 0 ifFail: [[self checkSoError] ensure: [self close]] ] ensureWriteable [ "If the file is open, wait until we can write to it. The wait allows other Processes to run." "FileDescriptor's ensureWriteable is actually dummy, because not all devices support sending SIGIO's when they become writeable -- notably, tty's under Linux :-(" self isOpen ifFalse: [^self]. self fileOp: 14 with: 1 with: Semaphore new ifFail: [[self checkSoError] ensure: [^self close]]. self isOpen ifFalse: [^self]. self fileOp: 13 with: 1 ifFail: [[self checkSoError] ensure: [self close]] ] waitForException [ "If the file is open, wait until an exceptional condition (such as presence of out of band data) has occurred on it. The wait allows other Processes to run." self isOpen ifFalse: [^self]. self fileOp: 14 with: 2 with: Semaphore new ifFail: [[self checkSoError] ensure: [^self close]]. self isOpen ifFalse: [^self]. self fileOp: 13 with: 2 ifFail: [[self checkSoError] ensure: [self close]] ] soError [ ^self soError: self fd ] ] AbstractSocketImpl subclass: SocketImpl [ SocketImpl class >> socketType [ "Answer the socket type parameter for `create'." ^self sockStream ] activeSocketImplClass [ "Return an implementation class to be used for the active socket created when a connection is accepted by a listening socket. The default is simply the same class as the receiver." ^self class ] outOfBandImplClass [ "Return an implementation class to be used for out-of-band data on the receiver." ^OOBSocketImpl ] connectTo: ipAddress port: port [ "Try to connect the socket represented by the receiver to the given remote machine." | addr fd peer | addr := ipAddress port: port. [(fd := self fd) isNil ifTrue: [ ^self ]. (self connect: fd to: addr addrLen: addr size) < 0 ifTrue: [self checkSoError] ] ifCurtailed: [self close]. "connect does not block, so wait for" self ensureWriteable. self isOpen ifTrue: [ peer := self getPeerName ifNil: [ addr ]. self hasBeenConnectedTo: peer] ] getPeerName [ "Retrieve a ByteArray containing a sockaddr_in struct for the remote endpoint of the socket." | peer addrLen fd | peer := ByteArray new: 128. addrLen := CInt gcValue: 128. (fd := self fd) isNil ifTrue: [ ^nil ]. (self getPeerName: self fd addr: peer addrLen: addrLen) = -1 ifTrue: [ ^nil ]. ^peer ] ] AbstractSocketImpl subclass: DatagramSocketImpl [ | bufSize | DatagramSocketImpl class >> socketType [ "Answer the socket type parameter for `create'." ^self sockDgram ] DatagramSocketImpl class >> datagramClass [ "Answer the datagram class returned by default by instances of this class." ^Datagram ] bufferSize [ "Answer the size of the buffer in which datagrams are stored." ^bufSize ] bufferSize: size [ "Set the size of the buffer in which datagrams are stored." bufSize := size ] peek [ "Peek for a datagram on the receiver, answer a new object of the receiver's datagram class." ^self receive: self msgPeek datagram: self class datagramClass new ] peek: aDatagram [ "Peek for a datagram on the receiver, answer aDatagram modified to contain information on the newly received datagram." ^self receive: self msgPeek datagram: aDatagram ] next [ "Retrieve a datagram from the receiver, answer a new object of the receiver's datagram class." ^self receive: 0 datagram: self class datagramClass new ] receive: aDatagram [ "Retrieve a datagram from the receiver, answer aDatagram modified to contain information on the newly received datagram." ^self receive: 0 datagram: aDatagram ] nextPut: aDatagram [ "Send aDatagram on the socket" self send: aDatagram to: (aDatagram address isNil ifTrue: [remoteAddress] ifFalse: [aDatagram address]) port: (aDatagram port isNil ifTrue: [remotePort] ifFalse: [aDatagram port]). ] receive: flags datagram: aDatagram [ "Receive a new datagram into `datagram', with the given flags, and answer `datagram' itself; this is an abstract method. The flags can be zero to receive the datagram, or `self msgPeek' to only peek for it without removing it from the queue." | address port data from addrLen fd read | data := ByteArray new: self bufferSize. from := ByteArray new: 128. addrLen := CInt gcValue: 128. (fd := self fd) isNil ifTrue: [ ^SystemExceptions.EndOfStream signal ]. read := self receive: fd buffer: data size: data size flags: (self flags bitOr: flags) from: from size: addrLen. read < 0 ifTrue: [ self checkSoError ]. port := ValueHolder new. ^aDatagram data: data; dataSize: read; address: (SocketAddress fromSockAddr: from port: port); port: port value; yourself ] send: aDatagram to: theReceiver port: port [ "Send aDatagram on the socket to the given receiver and port" | size receiver fd sent | theReceiver isNil ifTrue: [receiver := nil. size := 0] ifFalse: [receiver := theReceiver port: port. size := receiver size]. (fd := self fd) isNil ifTrue: [ ^SystemExceptions.EndOfStream signal ]. sent := self send: fd buffer: aDatagram data size: aDatagram size flags: self flags to: receiver size: size. sent < 0 ifTrue: [ self checkSoError ]. ] flags [ ^0 ] ] DatagramSocketImpl subclass: MulticastSocketImpl [ ipMulticastIf [ "Answer the local device for a multicast socket (in the form of an address)" self subclassResponsibility ] ipMulticastIf: interface [ "Set the local device for a multicast socket (in the form of an address, usually anyLocalAddress)" self subclassResponsibility ] join: ipAddress [ "Join the multicast socket at the given address" self subclassResponsibility ] leave: ipAddress [ "Leave the multicast socket at the given address" self subclassResponsibility ] timeToLive [ "Answer the time to live of the datagrams sent through the receiver to a multicast socket." self subclassResponsibility ] timeToLive: ttl [ "Set the time to live of the datagrams sent through the receiver to a multicast socket." self subclassResponsibility ] ] DatagramSocketImpl subclass: RawSocketImpl [ RawSocketImpl class >> socketType [ "Answer the socket type parameter for `create'." ^self sockRaw ] ] DatagramSocketImpl subclass: OOBSocketImpl [ canRead [ "Answer whether out-of-band data is available on the socket" ^self exceptionalCondition ] ensureReadable [ "Stop the process until an error occurs or out-of-band data becomes available on the socket" ^self waitForException ] flags [ ^self msgOOB ] ] smalltalk-3.2.5/packages/sockets/Sockets.st0000644000175000017500000011331312123404352015640 00000000000000"====================================================================== | | Smalltalk sockets - Stream hierarchy | | ======================================================================" "====================================================================== | | Copyright 1999, 2000, 2001, 2002, 2005, 2006, 2008, 2009 Free Software Foundation, Inc. | Written by Paolo Bonzini. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" Stream subclass: AbstractSocket [ | impl | CheckPeriod := nil. Timeout := nil. DefaultAddressClass := nil. Ports := nil. AbstractSocket class >> defaultPortAt: protocol [ "Answer the port that is used (by default) for the given service (high level protocol)" ^Ports at: protocol ] AbstractSocket class >> defaultPortAt: protocol ifAbsent: port [ "Answer the port that is used (by default) for the given service (high level protocol), or the specified port if none is registered." ^Ports at: protocol ifAbsent: port ] AbstractSocket class >> defaultPortAt: protocol put: port [ "Associate the given port to the service specified by `protocol'." ^Ports at: protocol put: port ] AbstractSocket class >> initialize [ self timeout: 30000; checkPeriod: 100; defaultAddressClass: IPAddress. Ports := (Dictionary new) at: 'ftp' put: 21; at: 'telnet' put: 23; at: 'smtp' put: 25; at: 'dns' put: 42; at: 'whois' put: 43; at: 'finger' put: 79; at: 'http' put: 80; at: 'pop3' put: 110; at: 'nntp' put: 119; yourself ] AbstractSocket class >> portEcho [ "Answer the port on which the ECHO service listens" ^7 ] AbstractSocket class >> portDiscard [ "Answer the port on which the DISCARD service listens" ^9 ] AbstractSocket class >> portSystat [ "Answer the port on which the SYSTAT service listens" ^11 ] AbstractSocket class >> portDayTime [ "Answer the port on which the TOD service listens" ^13 ] AbstractSocket class >> portNetStat [ "Answer the port on which the NETSTAT service listens" ^15 ] AbstractSocket class >> portFTP [ "Answer the port on which the FTP daemon listens" ^21 ] AbstractSocket class >> portSSH [ "Answer the port on which the SSH daemon listens" ^22 ] AbstractSocket class >> portTelnet [ "Answer the port on which the TELNET daemon listens" ^23 ] AbstractSocket class >> portSMTP [ "Answer the port on which the SMTP daemon listens" ^25 ] AbstractSocket class >> portTimeServer [ "Answer the port on which the time server listens" ^37 ] AbstractSocket class >> portDNS [ "Answer the port on which the DNS listens" ^53 ] AbstractSocket class >> portWhois [ "Answer the port on which the WHOIS daemon listens" ^43 ] AbstractSocket class >> portGopher [ "Answer the port on which the Gopher daemon listens" ^70 ] AbstractSocket class >> portFinger [ "Answer the port on which the finger daemon listens" ^79 ] AbstractSocket class >> portHTTP [ "Answer the port on which the http daemon listens" ^80 ] AbstractSocket class >> portPOP3 [ "Answer the port on which the pop3 daemon listens" ^110 ] AbstractSocket class >> portNNTP [ "Answer the port on which the nntp daemon listens" ^119 ] AbstractSocket class >> portExecServer [ "Answer the port on which the exec server listens" ^512 ] AbstractSocket class >> portLoginServer [ "Answer the port on which the rlogin daemon listens" ^513 ] AbstractSocket class >> portCmdServer [ "Answer the port on which the rsh daemon listens" ^514 ] AbstractSocket class >> portReserved [ "Answer the last port reserved to privileged processes" ^1023 ] AbstractSocket class >> checkPeriod [ "Answer the period that is to elapse between socket polls if data data is not ready and the connection is still open (in milliseconds)" ^CheckPeriod ] AbstractSocket class >> checkPeriod: anInteger [ "Set the period that is to elapse between socket polls if data data is not ready and the connection is still open (in milliseconds)" CheckPeriod := anInteger truncated ] AbstractSocket class >> timeout [ "Answer the period that is to elapse between the request for (yet unavailable) data and the moment when the connection is considered dead (in milliseconds)" ^Timeout ] AbstractSocket class >> timeout: anInteger [ "Set the period that is to elapse between the request for (yet unavailable) data and the moment when the connection is considered dead (in milliseconds)" Timeout := anInteger truncated ] AbstractSocket class >> defaultImplementationClassFor: aSocketAddressClass [ "Answer the default implementation class. Depending on the subclass, this might be the default stream socket implementation class of the given address class, or rather its default datagram socket implementation class." self subclassResponsibility ] AbstractSocket class >> defaultAddressClass [ "Answer the default address family to be used. In the library, the address family is represented by a subclass of SocketAddress which is by default IPAddress." ^DefaultAddressClass ] AbstractSocket class >> defaultAddressClass: class [ "Set the default address family to be used. In the library, the address family is represented by a subclass of SocketAddress which is by default IPAddress." DefaultAddressClass := class ] AbstractSocket class >> resolveAddress: ipAddressOrString [ | addr | ipAddressOrString isString ifTrue: [ addr := SocketAddress byName: ipAddressOrString. addr isNil ifTrue: [self error: 'cannot resolve host name ' , ipAddressOrString printString]] ifFalse: [addr := ipAddressOrString]. ^ addr ] AbstractSocket class >> new: implementation [ "Answer a new instance of the receiver, using as the underlying layer the object passed as the `implementation' parameter; the object is probably going to be some kind of AbstractSocketImpl." ^super new initialize: implementation ] AbstractSocket class >> new: implClass addressClass: addressClass [ "Answer a new instance of the receiver, using as the underlying layer a new instance of `implementationClass' and using the protocol family of `addressClass'." ^self new: (implClass newFor: addressClass) ] AbstractSocket class >> new [ self shouldNotImplement ] soLinger [ "Answer the number of seconds that the socket is allowed to wait if it promises reliable delivery but has unacknowledged/untransmitted packets when it is closed, or nil if those packets are left to their destiny or discarded." ^self implementation soLinger ] soLinger: linger [ "Set the number of seconds that the socket is allowed to wait if it promises reliable delivery but has unacknowledged/untransmitted packets when it is closed." ^self implementation soLinger: linger ] soLingerOff [ "Specify that, even if the socket promises reliable delivery, any packets that are unacknowledged/untransmitted when it is closed are to be left to their destiny or discarded." ^self implementation soLinger: nil ] species [ ^String ] address [ "Answer an IP address that is of common interest (this can be either the local or the remote address, according to the definition in the subclass)." self subclassResponsibility ] ensureWriteable [ "Suspend the current process until more data can be written on the socket." self implementation ensureWriteable ] ensureReadable [ "Suspend the current process until more data is available on the socket." self implementation ensureReadable ] isPeerAlive [ "Answer whether the connection with the peer remote machine is still valid." ^self implementation isOpen ] available [ "Answer whether there is data available on the socket. Same as #canRead, present for backwards compatibility." ^self canRead ] canRead [ "Answer whether there is data available on the socket." ^self implementation canRead ] canWrite [ "Answer whether there is free space in the socket's write buffer." ^self implementation canWrite ] close [ "Close the socket represented by the receiver." self flush. self implementation close ] flush [ "Flush any buffers used by the receiver." ] isOpen [ "Answer whether the connection between the receiver and the remote endpoint is still alive." self implementation isNil ifTrue: [^false]. ^self implementation isOpen ] localAddress [ "Answer the local IP address of the socket." self implementation isNil ifTrue: [self error: 'socket not connected']. ^self implementation localAddress ] localPort [ "Answer the local IP port of the socket." self implementation isNil ifTrue: [self error: 'socket not connected']. ^self implementation localPort ] port [ "Answer an IP port that is of common interest (this can be the port for either the local or remote endpoint, according to the definitions in the subclass" self subclassResponsibility ] remoteAddress [ "Answer the IP address of the socket's remote endpoint." self implementation isNil ifTrue: [self error: 'socket not connected']. ^self implementation remoteAddress ] remotePort [ "Answer the IP port of the socket's remote endpoint." self implementation isNil ifTrue: [self error: 'socket not connected']. ^self implementation remotePort ] printOn: aStream [ "Print a representation of the receiver on aStream" aStream print: self class; nextPut: $[; print: self address; nextPut: $:; print: self port; nextPutAll: ']' ] implementation [ ^impl ] initialize: implementation [ impl := implementation ] waitUntil: aBlock then: resultBlock onTimeoutDo: timeoutBlock [ Timeout // CheckPeriod timesRepeat: [aBlock value ifTrue: [^resultBlock value]. (Delay forMilliseconds: CheckPeriod) wait]. ^timeoutBlock value ] atEnd [ "By default, answer whether the connection is still open." ^self isOpen ] next [ "Read another character from the socket, failing if the connection is dead." ^self implementation next ] next: n putAll: aCollection startingAt: pos [ "Write `char' to the socket, failing if the connection is dead. The SIGPIPE signal is automatically caught and ignored by the system." ^self implementation next: n putAll: aCollection startingAt: pos ] nextPut: char [ "Write `char' to the socket, failing if the connection is dead. The SIGPIPE signal is automatically caught and ignored by the system." ^self implementation nextPut: char ] isExternalStream [ "Answer whether the receiver streams on a file or socket." ^true ] ] AbstractSocket subclass: DatagramSocket [ DefaultBufferSize := nil. DatagramSocket class >> defaultImplementationClassFor: aSocketAddressClass [ "Answer the default implementation class. Depending on the subclass, this might be the default stream socket implementation class of the given address class, or rather its default datagram socket implementation class." ^aSocketAddressClass defaultDatagramSocketImplClass ] DatagramSocket class >> defaultBufferSize [ "Answer the default maximum size for input datagrams." ^DefaultBufferSize ] DatagramSocket class >> defaultBufferSize: size [ "Set the default maximum size for input datagrams." DefaultBufferSize := size ] DatagramSocket class >> initialize [ "Initialize the class to use an input datagram size of 128." DatagramSocket defaultBufferSize: 128 ] DatagramSocket class >> new [ "Answer a new datagram socket (by default an UDP socket), without a specified local address and port." ^self local: nil port: 0 ] DatagramSocket class >> port: localPort [ "Create a new socket and bind it to the local host on the given port." ^self remote: nil port: 0 local: nil port: localPort ] DatagramSocket class >> local: ipAddressOrString port: remotePort [ "Create a new socket and bind it to the given host (passed as a String to be resolved or as an IPAddress), on the given port." ^self remote: nil port: 0 local: ipAddressOrString port: remotePort ] DatagramSocket class >> remote: ipAddressOrString port: remotePort local: ipAddress port: localPort [ "Create a new socket and bind it to the given host (passed as a String to be resolved or as a SocketAddress), and to the given remotePort. The default destination for the datagrams will be ipAddressOrString (if not nil), on the remotePort port." | localAddr remoteAddr addressClass | remoteAddr := self resolveAddress: ipAddressOrString. localAddr := self resolveAddress: ipAddress. addressClass := remoteAddr isNil ifTrue: [self defaultAddressClass] ifFalse: [remoteAddr class]. addressClass := localAddr isNil ifTrue: [addressClass] ifFalse: [localAddr class]. localAddr isNil ifTrue: [localAddr := addressClass anyLocalAddress]. ^(addressClass newSocket: self) remote: remoteAddr port: remotePort local: localAddr port: localPort ] address [ "Answer the local address." ^self localAddress ] bufferSize [ "Answer the size of the buffer in which datagrams are stored." ^self implementation bufferSize ] bufferSize: size [ "Set the size of the buffer in which datagrams are stored." self implementation bufferSize: size ] datagramClass [ "Answer the class used by the socket to return datagrams." ^self implementation class datagramClass ] next [ "Read a datagram on the socket and answer it." ^self waitUntil: [self implementation canRead] then: [self implementation next] onTimeoutDo: [nil] ] nextPut: aDatagram [ "Send the given datagram on the socket." self waitUntil: [self implementation canWrite] then: [self implementation nextPut: aDatagram. aDatagram] onTimeoutDo: [nil] ] port [ "Answer the local port." ^self localPort ] peek [ "Peek for a datagram on the socket and answer it." ^self waitUntil: [self implementation canRead] then: [self implementation peek] onTimeoutDo: [nil] ] peek: datagram [ "Peek for a datagram on the socket, store it in `datagram', and answer the datagram itself." ^self waitUntil: [self implementation canRead] then: [self implementation peek: datagram. true] onTimeoutDo: [false] ] receive: datagram [ "Read a datagram from the socket, store it in `datagram', and answer the datagram itself." ^self waitUntil: [self implementation canRead] then: [self implementation receive: datagram. true] onTimeoutDo: [false] ] nextFrom: ipAddress port: port [ "Answer the next datagram from the given address and port." self waitUntil: [self implementation canRead] then: [self implementation nextFrom: ipAddress port: port] onTimeoutDo: [nil] ] remote: remoteAddress port: remotePort local: ipAddress port: localPort [ "Private - Set the local endpoint of the socket and the default address to which datagrams are sent." (self implementation) soReuseAddr: 1; bufferSize: self class defaultBufferSize; connectTo: remoteAddress port: remotePort; bindTo: ipAddress port: localPort ] ] DatagramSocket subclass: MulticastSocket [ interface [ "Answer the local device supporting the multicast socket. This is usually set to any local address." ^self implementation ipMulticastIf ] interface: ipAddress [ "Set the local device supporting the multicast socket. This is usually set to any local address." self implementation ipMulticastIf: ipAddress ] join: ipAddress [ "Join the multicast socket at the given IP address" self implementation join: ipAddress ] leave: ipAddress [ "Leave the multicast socket at the given IP address" self implementation leave: ipAddress ] nextPut: packet timeToLive: timeToLive [ "Send the datagram with a specific TTL (time-to-live)" | oldTTL | oldTTL := self implementation timeToLive. self implementation timeToLive: timeToLive. self nextPut: packet. self implementation timeToLive: oldTTL ] timeToLive [ "Answer the socket's datagrams' default time-to-live" ^self implementation timeToLive ] timeToLive: newTTL [ "Set the default time-to-live for the socket's datagrams" self implementation timeToLive: newTTL ] ] AbstractSocket subclass: ServerSocket [ ServerSocket class >> defaultImplementationClassFor: aSocketAddressClass [ "Answer the default implementation class." ^aSocketAddressClass defaultStreamSocketImplClass ] ServerSocket class >> defaultQueueSize [ "Answer the default length of the queue for pending connections. When the queue fills, new clients attempting to connect fail until the server has sent #accept to accept a connection from the queue." ^5 ] ServerSocket class >> queueSize: backlog [ "Answer a new ServerSocket serving on any local address and port, with a pending connections queue of the given length." ^self port: 0 queueSize: backlog bindTo: nil ] ServerSocket class >> queueSize: backlog bindTo: ipAddress [ "Answer a new ServerSocket serving on the given local address, and on any port, with a pending connections queue of the given length." ^self port: 0 queueSize: backlog bindTo: ipAddress ] ServerSocket class >> port: anInteger [ "Answer a new ServerSocket serving on any local address, on the given port, with a pending connections queue of the default length." ^self port: anInteger queueSize: self defaultQueueSize bindTo: nil ] ServerSocket class >> port: anInteger queueSize: backlog [ "Answer a new ServerSocket serving on any local address, on the given port, with a pending connections queue of the given length." ^self port: anInteger queueSize: backlog bindTo: nil ] ServerSocket class >> port: anInteger bindTo: ipAddress [ "Answer a new ServerSocket serving on the given address and port, with a pending connections queue of the default length." ^self port: anInteger queueSize: self defaultQueueSize bindTo: ipAddress ] ServerSocket class >> port: anInteger queueSize: backlog bindTo: ipAddress [ "Answer a new ServerSocket serving on the given address and port, and with a pending connections queue of the given length." | localAddr addressClass | addressClass := ipAddress isNil ifTrue: [self defaultAddressClass] ifFalse: [ipAddress class]. localAddr := ipAddress isNil ifTrue: [addressClass unknownAddress] ifFalse: [ipAddress]. ^(addressClass newSocket: self) port: anInteger queueSize: backlog bindTo: localAddr ] address [ "Answer the local address" ^self localAddress ] port [ "Answer the local port (the port that the passive socket is listening on)." ^self localPort ] waitForConnection [ "Wait for a connection to be available, and suspend the currently executing process in the meanwhile." self implementation ensureReadable ] accept [ "Accept a new connection and create a new instance of Socket if there is one, else answer nil." ^self accept: Socket ] accept: socketClass [ "Accept a new connection and create a new instance of socketClass if there is one, else answer nil. This is usually needed only to create DatagramSockets." self canRead ifFalse: [^nil]. "Make it non-blocking" ^self primAccept: socketClass ] primAccept: socketClass [ "Accept a new connection and create a new instance of Socket if there is one, else fail." | implClass newImpl | implClass := self implementation activeSocketImplClass. newImpl := self implementation accept: implClass. ^socketClass new: newImpl ] port: anInteger queueSize: backlog bindTo: localAddr [ "Initialize the ServerSocket so that it serves on the given address and port, and has a pending connections queue of the given length." (self implementation) soReuseAddr: 1; bindTo: localAddr port: anInteger; listen: backlog ] ] AbstractSocket subclass: StreamSocket [ | peerDead readBuffer outOfBand | ReadBufferSize := nil. StreamSocket class >> initialize [ "Initialize the receiver's defaults" self readBufferSize: 1024. ] StreamSocket class >> readBufferSize [ "Answer the size of the read buffer for newly-created sockets" ^ReadBufferSize ] StreamSocket class >> readBufferSize: anInteger [ "Set the size of the read buffer for newly-created sockets" ReadBufferSize := anInteger ] StreamSocket class >> defaultImplementationClassFor: aSocketAddressClass [ "Answer the default implementation class. Depending on the subclass, this might be the default stream socket implementation class of the given address class, or rather its default datagram socket implementation class." ^aSocketAddressClass defaultStreamSocketImplClass ] StreamSocket class >> remote: ipAddressOrString port: remotePort [ "Create a new socket and connect to the given host (passed as a String to be resolved or as a SocketAddress), and to the given port." ^self remote: ipAddressOrString port: remotePort local: nil port: 0 ] StreamSocket class >> remote: ipAddressOrString port: remotePort local: ipAddress port: localPort [ "Create a new socket and connect to the given host (passed as a String to be resolved or as a SocketAddress), and to the given remotePort. Then bind it to the local address passed in ipAddress, on the localPort port; if the former is nil, any local address will do, and if the latter is 0, any local port will do." | localAddr remoteAddr addressClass | remoteAddr := self resolveAddress: ipAddressOrString. remoteAddr isNil ifTrue: [self error: 'cannot resolve host name ' , ipAddressOrString printString]. addressClass := remoteAddr isNil ifTrue: [self defaultAddressClass] ifFalse: [remoteAddr class]. addressClass := ipAddress isNil ifTrue: [addressClass] ifFalse: [ipAddress class]. ^(addressClass newSocket: self) remote: remoteAddr port: remotePort local: localAddr port: localPort ] address [ "Answer the address of the remote endpoint" ^self remoteAddress ] port [ "Answer the port of the remote endpoint" ^self remotePort ] printOn: aStream [ "Print a representation of the receiver on aStream" aStream print: self class; nextPutAll: '[local '; print: self localAddress; nextPut: $:; print: self localPort; nextPutAll: ', remote '; print: self remoteAddress; nextPut: $:; print: self remotePort; nextPut: $] ] remote: remoteAddr port: remotePort local: localAddr port: localPort [ localAddr isNil ifFalse: [self implementation bindTo: localAddr port: localPort]. self implementation connectTo: remoteAddr port: remotePort ] species [ ^String ] atEnd [ "Answer whether more data is available on the socket" ^self peek isNil ] ensureReadable [ "Suspend the current process until more data is available in the socket's read buffer or from the operating system." self canRead ifFalse: [ super ensureReadable ] ] canRead [ "Answer whether more data is available in the socket's read buffer or from the operating system." ^(self hasReadBuffer and: [self readBuffer notEmpty]) or: [super canRead] ] availableBytes [ "Answer how many bytes are available in the socket's read buffer or from the operating system." self canRead ifFalse: [ ^0 ]. ^self readBuffer availableBytes ] bufferContents [ "Answer the current contents of the read buffer" readBuffer isNil ifTrue: [^self pastEnd]. ^self readBuffer bufferContents ] close [ "Flush and close the socket." super close. self deleteBuffers ] fill [ "Fill the read buffer with data read from the socket" self readBuffer notNil ifTrue: [self readBuffer fill] ] isPeerAlive [ "Answer whether the connection with the peer remote machine is still valid." ^self readBuffer notNil and: [ super isPeerAlive ] ] next [ "Read a byte from the socket. This might yield control to other Smalltalk Processes." readBuffer isNil ifTrue: [^self pastEnd]. ^self readBuffer next ] nextAvailable: anInteger putAllOn: aStream [ "Copy up to anInteger objects from the receiver to aStream, stopping if no more data is available." | available read | readBuffer isNil ifTrue: [ ^self pastEnd ]. self ensureReadable. read := 0. [ read < anInteger and: [ (available := self availableBytes) > 0 ] ] whileTrue: [ read := read + (self readBuffer nextAvailable: (available min: anInteger - read) putAllOn: aStream) ]. ^read ] nextAvailable: anInteger into: aCollection startingAt: pos [ "Place up to anInteger objects from the receiver into aCollection, starting from position pos and stopping if no more data is available." | available read | readBuffer isNil ifTrue: [ ^self pastEnd ]. self ensureReadable. read := 0. [ read < anInteger and: [ (available := self availableBytes) > 0 ] ] whileTrue: [ read := read + (self readBuffer nextAvailable: (available min: anInteger - read) into: aCollection startingAt: pos + read) ]. ^read ] peek [ "Read a byte from the socket, without advancing the buffer; answer nil if no more data is available. This might yield control to other Smalltalk Processes." self readBuffer isNil ifTrue: [^nil]. self readBuffer atEnd ifTrue: [^nil]. ^self readBuffer peek ] peekFor: anObject [ "Read a byte from the socket, advancing the buffer only if it matches anObject; answer whether they did match or not. This might yield control to other Smalltalk Processes." self readBuffer isNil ifTrue: [^false]. self readBuffer atEnd ifTrue: [^false]. ^self readBuffer peekFor: anObject ] readBufferSize: size [ "Create a new read buffer of the given size (which is only possible before the first read or if the current buffer is empty)." readBuffer isNil ifTrue: [^self]. (self hasReadBuffer and: [readBuffer notEmpty]) ifTrue: [self error: 'read buffer must be empty before changing its size']. readBuffer := self newReadBuffer: size ] deleteBuffers [ readBuffer := nil ] noBufferFlag [ "Value that means `lazily initialize the buffer'." ^0 ] hasReadBuffer [ ^readBuffer ~~ self noBufferFlag ] initialize: implementation [ super initialize: implementation. readBuffer := self noBufferFlag ] newReadBuffer: size [ ^(ReadBuffer on: (String new: size)) fillBlock: [:data :size || n | self implementation ensureReadable. n := self implementation isOpen ifTrue: [self implementation nextAvailable: size into: data startingAt: 1] ifFalse: [0]. n = 0 ifTrue: [self deleteBuffers]. n] ] readBuffer [ readBuffer == self noBufferFlag ifTrue: [readBuffer := self newReadBuffer: ReadBufferSize]. ^readBuffer ] outOfBand [ "Return a datagram socket to be used for receiving out-of-band data on the receiver." | outOfBandImpl | outOfBand isNil ifTrue: [outOfBandImpl := self implementation outOfBandImplClass new. outOfBandImpl initialize: self implementation fd. outOfBand := DatagramSocket new: outOfBandImpl]. ^outOfBand ] ] StreamSocket subclass: Socket [ | writeBuffer | WriteBufferSize := nil. Socket class >> initialize [ "Initialize the receiver's defaults" self writeBufferSize: 256. ] Socket class >> writeBufferSize [ "Answer the size of the write buffer for newly-created sockets" ^WriteBufferSize ] Socket class >> writeBufferSize: anInteger [ "Set the size of the write buffer for newly-created sockets" WriteBufferSize := anInteger ] flush [ "Flush the write buffer to the operating system" self isPeerAlive ifTrue: [ self implementation valueWithoutBuffering: [ self writeBuffer flush]] ] nextPut: char [ "Write a character to the socket; this acts as a bit-bucket when the socket is closed. This might yield control to other Smalltalk Processes." self writeBuffer isNil ifTrue: [^self]. self writeBuffer nextPut: char ] next: n putAll: aCollection startingAt: pos [ "Write aString to the socket; this acts as a bit-bucket when the socket is closed. This might yield control to other Smalltalk Processes." self writeBuffer isNil ifTrue: [^self]. self writeBuffer next: n putAll: aCollection startingAt: pos ] writeBufferSize: size [ "Create a new write buffer of the given size, flushing the old one is needed. This might yield control to other Smalltalk Processes." writeBuffer isNil ifTrue: [^self]. self hasWriteBuffer ifTrue: [writeBuffer flush]. writeBuffer := self newWriteBuffer: size ] deleteBuffers [ super deleteBuffers. writeBuffer := nil ] hasWriteBuffer [ ^writeBuffer ~~ self noBufferFlag ] initialize: implementation [ super initialize: implementation. writeBuffer := self noBufferFlag ] ensureWriteable [ "Answer whether more data is available in the socket's read buffer or from the operating system." self canWrite ifFalse: [super ensureWriteable] ] canWrite [ "Answer whether more data is available in the socket's read buffer or from the operating system." ^(self hasWriteBuffer and: [self readBuffer isFull not]) or: [super canWrite] ] newWriteBuffer: size [ ^(WriteBuffer on: (String new: size)) flushBlock: [:data :size | | alive | self implementation ensureWriteable. alive := self implementation isOpen and: [(self implementation next: size putAll: data startingAt: 1) > -1]. alive ifFalse: [self deleteBuffers]] ] writeBuffer [ writeBuffer == self noBufferFlag ifTrue: [writeBuffer := self newWriteBuffer: WriteBufferSize]. ^writeBuffer ] ] Eval [ AbstractSocket initialize. StreamSocket initialize. Socket initialize. ] smalltalk-3.2.5/packages/sockets/stamp-classes0000644000175000017500000000000012123404352016343 00000000000000smalltalk-3.2.5/packages/sockets/package.xml0000644000175000017500000000110512130343734015771 00000000000000 Sockets Sockets TCPaccept Buffers.st Datagram.st SocketAddress.st AbstractSocketImpl.st IPSocketImpl.st IP6SocketImpl.st UnixSocketImpl.st Sockets.st Tests.st cfuncs.st init.st Sockets.SocketTest UnitTest.st ChangeLog smalltalk-3.2.5/packages/sockets/IP6SocketImpl.st0000644000175000017500000001756412123404352016631 00000000000000"====================================================================== | | Smalltalk IPv6 addresses | | ======================================================================" "====================================================================== | | Copyright 1999, 2000, 2001, 2002, 2008 Free Software Foundation, Inc. | Written by Paolo Bonzini. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" SocketAddress subclass: IP6Address [ | address | IP6Address class >> initialize [ "Set up the default implementation classes for the receiver" self defaultRawSocketImplClass: ICMP6SocketImpl. self defaultDatagramSocketImplClass: UDPSocketImpl. self defaultStreamSocketImplClass: TCPSocketImpl ] IP6Address class >> createLoopbackHost [ "Answer an object representing the loopback host in the address family for the receiver. This is ::1 for IPv4." ^(IP6Address fromBytes: #[0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 1]) name: '::1'; yourself ] IP6Address class >> createUnknownAddress [ "Answer an object representing an unkown address in the address family for the receiver" ^(IP6Address fromBytes: #[0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0]) name: '::0'; yourself ] IP6Address class >> aiFlags [ ^self aiV4mapped + self aiAll ] IP6Address class >> addressSize [ "Answer the size of an IPv4 address." ^16 ] IP6Address class >> version [ "Answer the version of IP that the receiver implements." ^6 ] IP6Address class >> fromBytes: aByteArray [ "Answer a new IP6Address from a ByteArray containing the bytes in the same order as the digit form: 131.175.6.2 would be represented as #[131 175 6 2]." ^self basicNew address: ((aByteArray copyFrom: 1 to: 16) makeReadOnly: true) ] IP6Address class >> fromSockAddr: aByteArray port: portAdaptor [ "Private - Answer a new IP6Address from a ByteArray containing a C sockaddr_in structure. The portAdaptor's value is changed to contain the port that the structure refers to." portAdaptor value: (aByteArray at: 3) * 256 + (aByteArray at: 4). ^self fromBytes: (aByteArray copyFrom: 9 to: 24) ] IP6Address class >> invalidAddress [ self error: 'invalid IPv6 address' ] IP6Address class >> readWordFrom: stream [ | n | (stream atEnd or: [ stream peekFor: $: ]) ifTrue: [ self invalidAddress ]. n := Integer readFrom: stream radix: 16. (n < 0 or: [ n > 65535 ]) ifTrue: [ self invalidAddress ]. (stream atEnd or: [ stream peekFor: $: ]) ifTrue: [ ^n ]. self invalidAddress ] IP6Address class >> fromString: aString [ "Answer a new IP6Address from a String containing the requested address in digit form." | s n break count expected ipv4 i | n := WordArray new: 8. count := (aString occurrencesOf: $:) + 1. (aString includes: $.) ifTrue: [ ipv4 := IPAddress fromString: (aString copyAfterLast: $:). ipv4 := ipv4 asByteArray. n at: 7 put: ipv4 first * 256 + ipv4 second. n at: 8 put: ipv4 third * 256 + ipv4 fourth. count := count - 1. expected := 6 ] ifFalse: [ expected := 8 ]. expected < count ifTrue: [ self invalidAddress ]. i := 1. s := aString readStream. break := false. [ i > expected ] whileFalse: [ s atEnd ifTrue: [ self invalidAddress ]. (break not and: [ s peekFor: $: ]) ifTrue: [ break := true. i := i + expected - count + 1 ] ifFalse: [ n at: i put: (self readWordFrom: s). i := i + 1 ] ]. ^self fromArray: n ] IP6Address class >> fromArray: parts [ "Answer a new IP6Address from an array of numbers; the numbers are to be thought as the colon-separated numbers in the standard numbers-and-colons notation for IPv4 addresses." | address | address := ByteArray new: 16. parts keysAndValuesDo: [ :i :each | address at: i * 2 - 1 put: (each bitShift: -8). address at: i * 2 put: (each bitAnd: 255) ]. ^self fromBytes: address ] IP6Address class >> new [ self shouldNotImplement ] IP6Address class >> isDigitAddress: aString [ "Answer whether aString is a valid address in colon-separated form." ^false ] asByteArray [ "Answer a read-only ByteArray of size four containing the receiver's bytes in network order (big-endian)" ^address ] isMulticast [ "Answer whether the receiver reprensents an address reserved for multicast datagram connections" ^address first = 255 ] printOn: aStream [ "Print the receiver in dot notation." | n words format | n := 1. 1 to: 16 do: [ :i | (n = i and: [ (address at: n) = 0 ]) ifTrue: [ n := i + 1 ] ]. n = 13 ifTrue: [ aStream nextPutAll: '::%1.%2.%3.%4' % (address copyFrom: 13). ^self ]. (n = 11 and: [ (address at: 11) = 255 and: [ (address at: 12) = 255 ]]) ifTrue: [ aStream nextPutAll: '::ffff:%1.%2.%3.%4' % (address copyFrom: 13). ^self ]. words := (1 to: 15 by: 2) collect: [ :i | (((address at: i) * 256 + (address at: i + 1)) printString: 16) asLowercase ]. format := n >= 15 ifTrue: [ '::%8' ] ifFalse: [ '%1:%2:%3:%4:%5:%6:%7:%8' ]. aStream nextPutAll: format % words ] address: aByteArray [ "Private - Set the ByteArray corresponding to the four parts of the IP address in dot notation" address := aByteArray ] port: port [ "Return a ByteArray containing a struct sockaddr for the given port on the IP address represented by the receiver. Family = AF_INET6." port < 0 | (port > 65535) ifTrue: [self error: 'port out of range']. ^(ByteArray new: 28) "Write sin_addr" replaceFrom: 9 to: 24 with: address startingAt: 1; "Write sin_len and sin_family = AF_INET6" at: 1 put: 28; at: 2 put: self class addressFamily; "Write sin_port in network order (big endian)" at: 3 put: port // 256; at: 4 put: (port bitAnd: 255); yourself ] ] RawSocketImpl subclass: ICMP6SocketImpl [ ] CStruct subclass: CSockAddrIn6Struct [ ] smalltalk-3.2.5/packages/profile/0000755000175000017500000000000012130456017013723 500000000000000smalltalk-3.2.5/packages/profile/Makefile.frag0000644000175000017500000000032712123404352016220 00000000000000ProfileTools_FILES = \ packages/profile/Profiler.st packages/profile/ChangeLog $(ProfileTools_FILES): $(srcdir)/packages/profile/stamp-classes: $(ProfileTools_FILES) touch $(srcdir)/packages/profile/stamp-classes smalltalk-3.2.5/packages/profile/ChangeLog0000644000175000017500000000032612123404352015413 000000000000002010-12-04 Paolo Bonzini * package.xml: Remove now superfluous tags. 2009-03-30 Derek Zhou Paolo Bonzini * Profiler.st: New. smalltalk-3.2.5/packages/profile/Profiler.st0000644000175000017500000001516512123404352016002 00000000000000"====================================================================== | | Basic Profiler tools | | ======================================================================" "====================================================================== | | Copyright 2009 2006, 2007 Free Software Foundation, Inc. | Written by Derek Zhou and Paolo Bonzini. | | This file is part of GNU Smalltalk. | | GNU Smalltalk is free software; you can redistribute it and/or modify it | under the terms of the GNU General Public License as published by the Free | Software Foundation; either version 2, or (at your option) any later version. | | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS | FOR A PARTICULAR PURPOSE. See the GNU General Public License for more | details. | | You should have received a copy of the GNU General Public License along with | GNU Smalltalk; see the file COPYING. If not, write to the Free Software | Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. | ======================================================================" Object subclass: Profiler [ Stack := nil. | rawProfile name | Profiler class >> profile: aBlock [ ^self new withProfilerDo: aBlock; yourself ] name [ ^name ifNil: [ 'gst ', (Smalltalk arguments join: ' ') ] ] name: aString [ name := aString ] push [ Stack isNil ifTrue: [ Stack := OrderedCollection new ]. Stack addLast: (Smalltalk rawProfile: self rawProfile) ] pop [ Smalltalk rawProfile: Stack removeLast ] rawProfile [ rawProfile isNil ifTrue: [ rawProfile := IdentityDictionary new ]. ^rawProfile ] withProfilerDo: aBlock [ ^[ self push. aBlock value ] ensure: [ self pop ] ] ] Warning subclass: NoProfile [ | method | NoProfile class >> for: aMethod [ ^self new method: aMethod; yourself ] method: aMethod [ method := aMethod ] description [ ^'No profile found' ] messageText [ ^'%1 for %2' % {self description. method} ] ] Object subclass: MethodProfile [ | selfCost totalCost totalCalls calleeCounts profiler | MethodProfile class >> newIn: profiler [ ^self new initWith: profiler ] initWith: p [ selfCost := 0. profiler := p. calleeCounts := IdentityDictionary new. totalCalls := 0. ] merge: p select: aBlock [ "merge with raw profile p, which is an IdentityDictionary" p keysAndValuesDo: [ :k :v || profileKey | k == true ifTrue: [ selfCost := selfCost + v ] ifFalse: [ (aBlock value: k) ifTrue: [ self add: v callsTo: k]]]. totalCost := nil. ] printOn: aStream [ aStream nextPutAll: '0 %1' % {selfCost}; nl. calleeCounts keysAndValuesDo: [ :callee :n | aStream nextPutAll: 'cfi=%1' % {callee methodSourceFile}; nl; nextPutAll: 'cfn=%1' % {callee uniquePrintString}; nl; nextPutAll: 'calls=%1' % {n}; nl; nextPutAll: '* %1' % {self costOf: callee}; nl ]. ] add: n callsTo: callee [ | calleeProfile | calleeProfile := profiler profileAt: callee. calleeProfile totalCalls: calleeProfile totalCalls + n. calleeCounts at: callee put: n + (calleeCounts at: callee ifAbsent: [0]). ] selfCost [ ^selfCost ] totalCalls [ ^totalCalls ] totalCalls: n [ totalCalls := n ] totalCost [ totalCost notNil ifTrue: [ ^totalCost ]. "Return 0 while computing totalCost, to handle loops properly." totalCost := 0. "TODO: handle loops better." totalCost := calleeCounts keys inject: selfCost into: [ :old :callee | old + (self costOf: callee) ]. ^totalCost ] costOf: callee [ | calleeProfile | calleeProfile := profiler profileAt: callee. calleeProfile totalCalls = 0 ifTrue: [(NoProfile for: callee) signal. ^0]. ^(calleeProfile totalCost * (calleeCounts at: callee) + calleeProfile totalCalls - 1) // calleeProfile totalCalls ] ] CompiledMethod extend [ uniquePrintString [ ^self printString ] ] CompiledBlock extend [ uniquePrintString [ ^'%1 at line %2' % { self. self sourceCodeMap first } ] ] Profiler subclass: CallGraphProfiler [ | methodProfiles | mergeRawProfile [ self rawProfile keysAndValuesDo: [ :k :v | | method | method := self accountingMethodFor: k. (self profileAt: method) merge: v select: [ :callee | self isMethodAccounted: callee ] ]. rawProfile := nil ] accountingMethodFor: aMethod [ ^aMethod ] isMethodAccounted: aMethod [ ^true ] profileAt: aMethod [ ^methodProfiles at: aMethod ifAbsentPut: [MethodProfile newIn: self] ] push [ methodProfiles isNil ifTrue: [ methodProfiles := IdentityDictionary new: 256 ]. super push ] pop [ super pop. self mergeRawProfile. ] totalCost [ ^methodProfiles inject: 0 into: [ :sum :each | sum + each selfCost ] ] methodCount [ ^methodProfiles size ] printOn: aStream [ "print a callgrind compatible profile report on aStream" self printSummaryOn: aStream. self printCallGraphOn: aStream. ] printCallGraphOn: aStream [ methodProfiles keysAndValuesDo: [ :method :profile | aStream nextPutAll: 'fl=%1' % {method methodSourceFile}; nl; nextPutAll: 'fn=%1' % {method uniquePrintString}; nl. profile printOn: aStream. aStream nl ] ] printCallGraphToFile: aFile [ "print a callgrind compatible profile report to a file named aFile" | fs | fs := aFile asFile writeStream. [ self printHeaderOn: fs; printSummaryOn: fs. fs nl. self printCallGraphOn: fs ] ensure: [ fs close ] ] printSummaryOn: aStream [ aStream nextPutAll: 'summary: %1' % {self totalCost}; nl. ] printHeaderOn: aStream [ aStream nextPutAll: 'version: 1'; nl; nextPutAll: 'creator: gst-profile'; nl; nextPutAll: 'positions: instr'; nl; nextPutAll: 'cmd: %1' % {self name}; nl; nextPutAll: 'events: Ir'; nl ] ] CallGraphProfiler subclass: MethodCallGraphProfiler [ accountingMethodFor: aMethod [ ^aMethod method ] isMethodAccounted: aMethod [ "Discard blocks, they are accounted for in the parent." ^aMethod method == aMethod ] ] smalltalk-3.2.5/packages/profile/stamp-classes0000644000175000017500000000000012123404352016330 00000000000000smalltalk-3.2.5/packages/profile/package.xml0000644000175000017500000000015112123404352015752 00000000000000 ProfileTools Profiler.st ChangeLog smalltalk-3.2.5/packages/net/0000755000175000017500000000000012130456015013047 500000000000000smalltalk-3.2.5/packages/net/Makefile.frag0000644000175000017500000000067512123404352015354 00000000000000NetClients_FILES = \ packages/net/ChangeLog packages/net/Base.st packages/net/ContentHandler.st packages/net/FTP.st packages/net/HTTP.st packages/net/IMAP.st packages/net/MIME.st packages/net/NNTP.st packages/net/NetServer.st packages/net/POP.st packages/net/SMTP.st packages/net/URIResolver.st packages/net/IMAPTests.st $(NetClients_FILES): $(srcdir)/packages/net/stamp-classes: $(NetClients_FILES) touch $(srcdir)/packages/net/stamp-classes smalltalk-3.2.5/packages/net/FTP.st0000644000175000017500000003636012123404352013777 00000000000000"====================================================================== | | FTP protocol support | | ======================================================================" "====================================================================== | | Based on code copyright (c) Kazuki Yasumatsu, and in the public domain | Copyright (c) 2002, 2008 Free Software Foundation, Inc. | Adapted by Paolo Bonzini. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" Namespace current: NetClients.FTP [ Object subclass: FTPServerEntity [ | permissions id owner group sizeInBytes modifiedDate filename isDirectory | filename [ ^filename ] filename: aValue [ filename := aValue ] group [ ^group ] group: aValue [ group := aValue ] id [ ^id ] id: aValue [ id := aValue asNumber ] isDirectory [ ^isDirectory ] isDirectory: aValue [ isDirectory := aValue ] modifiedDate [ ^modifiedDate ] modifiedDate: aValue [ modifiedDate := aValue ] owner [ ^owner ] owner: aValue [ owner := aValue ] permissions [ ^permissions ] permissions: aValue [ permissions := aValue ] sizeInBytes [ ^sizeInBytes ] sizeInBytes: aValue [ sizeInBytes := aValue asNumber ] displayString [ | stream | stream := Stream on: (String new: 100). self isDirectory ifTrue: [stream nextPutAll: ' '] ifFalse: [stream space: 5]. stream nextPutAll: self filename; space: 30 - self filename size. stream nextPutAll: self sizeInBytes printString. ^stream contents ] from: stream [ self permissions: (stream upTo: Character space). stream skipSeparators. self id: (stream upTo: Character space). stream skipSeparators. self owner: (stream upTo: Character space). stream skipSeparators. self group: (stream upTo: Character space). stream skipSeparators. self sizeInBytes: (stream upTo: Character space). stream skipSeparators. self modifiedDate: (self getDateFromNext: 3 on: stream). stream skipSeparators. self filename: (stream upTo: Character space). self isDirectory: self sizeInBytes = 0 ] getDateFromNext: aNumber on: stream [ | iStream | iStream := WriteStream on: (String new: 100). aNumber timesRepeat: [iStream nextPutAll: (stream upTo: Character space). iStream nextPut: Character space. stream skipSeparators]. ^DateTime readFrom: iStream contents readStream ] ] ] Namespace current: NetClients.FTP [ NetClient subclass: FTPClient [ | loggedInUser | FTPClient class >> defaultPortNumber [ ^21 ] FTPClient class >> exampleHost: host [ "self exampleHost: 'localhost'." ^self exampleHost: host port: 21 ] FTPClient class >> exampleHost: host port: port [ "self exampleHost: 'localhost' port: 2121." | user password stream client | user := 'utente'. password := 'bonzini'. stream := WriteStream on: (String new: 256). client := FTPClient connectToHost: host port: port. [client username: user password: password; login; getList: '/' into: stream] ensure: [client close]. ^stream contents ] FTPClient class >> exampleHost: host fileName: fileName [ "self exampleHost: 'localhost'." ^self exampleHost: host port: 21 fileName: fileName ] FTPClient class >> exampleHost: host port: port fileName: fileName [ "self exampleHost: 'arrow' fileName: '/pub/smallwalker/README'." | user password stream client | user := 'utente'. password := 'bonzini'. stream := WriteStream on: (String new: 256). client := FTPClient connectToHost: host port: port. [client username: user password: password; login; getFile: fileName type: #ascii into: stream] ensure: [client close]. ^stream contents ] protocolInterpreter [ ^FTPProtocolInterpreter ] login [ self connectIfClosed. loggedInUser = self user ifTrue: [^self]. self clientPI ftpUser: self user username. self clientPI ftpPassword: self user password. loggedInUser := self user ] logout [ loggedInUser := nil. (self clientPI) ftpQuit; close ] getFile: fileName type: type into: aStream [ | fname directory tail | self login. fname := File path: fileName. directory := fname path asString. tail := fname stripPath asString. tail isEmpty ifTrue: [^self clientPI getDataWithType: type into: aStream do: [self clientPI ftpRetrieve: fileName]] ifFalse: [self clientPI ftpCwd: directory. ^self clientPI getDataWithType: type into: aStream do: [self clientPI ftpRetrieve: tail]] ] getList: pathName into: aStream [ | fname directory tail | self login. fname := File path: pathName. directory := fname path asString. tail := fname stripPath asString. self clientPI ftpCwd: directory. ^self clientPI getDataWithType: #ascii into: aStream do: [tail isEmpty ifTrue: [self clientPI ftpList] ifFalse: [self clientPI ftpList: tail]. 0] ] ] ] Namespace current: NetClients.FTP [ NetProtocolInterpreter subclass: FTPProtocolInterpreter [ openDataConnectionDo: controlBlock [ "Create a socket. Set up a queue for a single connection." | portSocket dataStream | portSocket := ServerSocket reuseAddr: true port: 0 queueSize: 1 bindTo: nil. [self ftpPort: portSocket port host: portSocket address asByteArray. "issue control command." controlBlock value. [(dataStream := portSocket accept) isNil] whileTrue: [Processor yield]] ensure: [portSocket close]. ^dataStream ] openPassiveDataConnectionDo: controlBlock [ "Enter Passive Mode" | array dataSocket dataStream | array := self ftpPassive. dataStream := Socket remote: (IPAddress fromBytes: (array at: 1)) port: (array at: 2). "issue control command." controlBlock value. ^dataStream ] connect [ super connect. self checkResponse ] getDataWithType: type into: aStream do: controlBlock [ | dataStream totalByte coll | (#(#ascii #binary) includes: type) ifFalse: [^self error: 'type must be #ascii or #binary']. type == #ascii ifTrue: [self ftpTypeAscii] ifFalse: [self ftpTypeBinary]. "dataStream := self openDataConnectionDo: [totalByte := controlBlock value]." dataStream := self openPassiveDataConnectionDo: [totalByte := controlBlock value]. totalByte > 0 ifTrue: [self reporter totalByte: totalByte]. self reporter startTransfer. [[dataStream atEnd] whileFalse: [| byte | byte := dataStream nextAvailable: 1024. self reporter readByte: byte size. type == #ascii ifTrue: [aStream nextPutAll: (self decode: byte)] ifFalse: [aStream nextPutAll: byte]]] ensure: [dataStream close]. self reporter endTransfer ] ftpAbort [ self nextPutAll: 'ABOR'; cr. self checkResponse ] ftpCdup [ "Change to Parent Directory" self nextPutAll: 'CDUP'; cr. self checkResponse ] ftpCwd: directory [ "Change Working Directory" self nextPutAll: 'CWD ' , directory; cr. self checkResponse ] ftpList [ self nextPutAll: 'LIST'; cr. self checkResponse ] ftpList: pathName [ self nextPutAll: 'LIST ' , pathName; cr. self checkResponse ] ftpPassive [ | response stream hostAddress port | self nextPutAll: 'PASV'; cr. response := self getResponse. self checkResponse: response. response status = 227 ifFalse: [^self unexpectedResponse: response]. "227 Entering Passive Mode (h1,h2,h3,h4,p1,p2)" stream := response statusMessage readStream. hostAddress := ByteArray new: 4. stream upTo: $(. hostAddress at: 1 put: (Integer readFrom: stream). stream skip: 1. hostAddress at: 2 put: (Integer readFrom: stream). stream skip: 1. hostAddress at: 3 put: (Integer readFrom: stream). stream skip: 1. hostAddress at: 4 put: (Integer readFrom: stream). stream skip: 1. port := Integer readFrom: stream. stream skip: 1. port := (port bitShift: 8) + (Integer readFrom: stream). ^Array with: hostAddress with: port ] ftpPassword: password [ | response | self nextPutAll: 'PASS ' , password; cr. response := self getResponse. self checkResponse: response ifError: [self loginIncorrectError: response statusMessage] ] ftpPort: portInteger host: hostAddressBytes [ self nextPutAll: 'PORT '; nextPutAll: (hostAddressBytes at: 1) printString; nextPut: $,; nextPutAll: (hostAddressBytes at: 2) printString; nextPut: $,; nextPutAll: (hostAddressBytes at: 3) printString; nextPut: $,; nextPutAll: (hostAddressBytes at: 4) printString; nextPut: $,; nextPutAll: ((portInteger bitShift: -8) bitAnd: 255) printString; nextPut: $,; nextPutAll: (portInteger bitAnd: 255) printString; cr. self checkResponse ] ftpQuit [ self nextPutAll: 'QUIT'; cr. self checkResponse ] ftpRetrieve: fileName [ | response stream | self nextPutAll: 'RETR ' , fileName; cr. response := self getResponse. self checkResponse: response. "150 Opening data connection for file (398 bytes)." stream := response statusMessage readStream. stream skipTo: $(. stream atEnd ifTrue: [^nil]. ^Integer readFrom: stream ] ftpStore: fileName [ self nextPutAll: 'STOR ' , fileName; cr. self checkResponse ] ftpType: type [ self nextPutAll: 'TYPE ' , type; cr. self checkResponse ] ftpTypeAscii [ ^self ftpType: 'A' ] ftpTypeBinary [ ^self ftpType: 'I' ] ftpUser: user [ self nextPutAll: 'USER ' , user; cr. self checkResponse ] checkResponse: response ifError: errorBlock [ | status | status := response status. "Positive Preliminary reply" status = 110 ifTrue: ["Restart marker reply" ^self]. status = 120 ifTrue: ["Service ready in nnn minutes" ^self]. status = 125 ifTrue: ["Data connection already open" ^self]. status = 150 ifTrue: ["File status okay" ^self]. "Positive Completion reply" status = 200 ifTrue: ["OK" ^self]. status = 202 ifTrue: ["Command not implemented" ^self]. status = 211 ifTrue: ["System status" ^self]. status = 212 ifTrue: ["Directory status" ^self]. status = 213 ifTrue: ["File status" ^self]. status = 214 ifTrue: ["Help message" ^self]. status = 215 ifTrue: ["NAME system type" ^self]. status = 220 ifTrue: ["Service ready for new user" ^self]. status = 221 ifTrue: ["Service closing control connection" ^self]. status = 225 ifTrue: ["Data connection open" ^self]. status = 226 ifTrue: ["Closing data connection" ^self]. status = 227 ifTrue: ["Entering Passive Mode" ^self]. status = 230 ifTrue: ["User logged in" ^self]. status = 250 ifTrue: ["Requested file action okay" ^self]. status = 257 ifTrue: ["'PATHNAME' created" ^self]. "Positive Intermediate reply" status = 331 ifTrue: ["User name okay" ^self]. status = 332 ifTrue: ["Need account for login" ^self]. status = 350 ifTrue: ["Requested file action pending" ^self]. "Transient Negative Completion reply" status = 421 ifTrue: ["Service not available" ^errorBlock value]. status = 425 ifTrue: ["Can't open data connection" ^errorBlock value]. status = 426 ifTrue: ["Connection closed" ^errorBlock value]. status = 450 ifTrue: ["Requested file action not taken" ^errorBlock value]. status = 451 ifTrue: ["Requested action aborted" ^errorBlock value]. status = 452 ifTrue: ["Requested action not taken" ^errorBlock value]. "Permanent Negative Completion reply" status = 500 ifTrue: ["Syntax error" ^errorBlock value]. status = 501 ifTrue: ["Syntax error" ^errorBlock value]. status = 502 ifTrue: ["Command not implemented" ^errorBlock value]. status = 503 ifTrue: ["Bad sequence of commands" ^errorBlock value]. status = 504 ifTrue: ["Command not implemented" ^errorBlock value]. status = 530 ifTrue: ["Not logged in" ^self loginIncorrectError: response statusMessage]. status = 532 ifTrue: ["Need account for storing files" ^errorBlock value]. status = 550 ifTrue: ["Requested action not taken" ^self fileNotFoundError: response statusMessage]. status = 551 ifTrue: ["Requested action aborted" ^errorBlock value]. status = 552 ifTrue: ["Requested file action aborted" ^errorBlock value]. status = 553 ifTrue: ["Requested action not taken" ^errorBlock value]. "Unknown status" ^errorBlock value ] fileNotFoundError: errorString [ ^FTPFileNotFoundError signal: errorString ] ] ] Namespace current: NetClients.FTP [ NetClientError subclass: FTPFileNotFoundError [ ] ] smalltalk-3.2.5/packages/net/NetServer.st0000644000175000017500000001302612123404352015255 00000000000000"====================================================================== | | Generic server framework | | ======================================================================" "====================================================================== | | Copyright 1999, 2000, 2001, 2002, 2003, 2005, 2008 Free Software Foundation, Inc. | Written by Paolo Bonzini | | This file is part of the GNU Smalltalk class library. | | GNU Smalltalk is free software; you can redistribute it and/or modify it | under the terms of the GNU Lesser General Public License as published by | the Free Software Foundation; either version 2.1, or (at your option) | any later version. | | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS | FOR A PARTICULAR PURPOSE. See the GNU General Public License for more | details. | | You should have received a copy of the GNU Lesser General Public License | along with GNU Smalltalk; see the file COPYING.LIB. If not, write to | the Free Software Foundation, 51 Franklin Street, Fifth Floor, Boston, MA | 02110-1301, USA. | ======================================================================" Object subclass: NetThread [ | process socket priority | NetThread class >> new [ ^self basicNew initialize ] defaultPriority [ ^Processor userSchedulingPriority ] initialize [ priority := self defaultPriority ] release [ socket close. socket := nil. super release ] printOn: aStream [ aStream print: self class; nextPut: $:. self isRunning ifFalse: [^aStream nextPutAll: 'idle']. aStream print: self socket port ] createSocket [ self subclassResponsibility ] startNewProcess [ process := ([self run] newProcess) priority: priority; name: self class name , ' Process'; yourself. process resume ] isPeerAlive [ ^socket notNil and: [socket isPeerAlive] ] socket [ ^socket ] run [ self subclassResponsibility ] isRunning [ ^process notNil ] start [ self isRunning ifTrue: [^self]. socket := self createSocket. self startNewProcess ] ] NetThread subclass: NetServer [ | port | Servers := nil. NetServer class >> at: port [ | server | Servers isNil ifTrue: [Servers := Dictionary new]. ^Servers at: port ifAbsentPut: [(self new) port: port; yourself] ] NetServer class >> initializeServer: port [ | server | server := self at: port. server isRunning ifFalse: [server startOn: port]. ^server ] NetServer class >> terminateServer: port [ Servers isNil ifTrue: [^self]. (Servers includesKey: port) ifTrue: [(Servers at: port) release. Servers removeKey: port] ] newSession [ self subclassResponsibility ] respondTo: aRequest [ self subclassResponsibility ] port [ ^port ] port: anObject [ self stop. port := anObject ] priority [ ^priority ] priority: anInteger [ priority := anInteger. self isRunning ifTrue: [process priority: priority] ] startOn: aPortNumber [ self port: aPortNumber. self start ] createSocket [ ^ServerSocket port: port ] defaultPriority [ ^Processor lowIOPriority ] run [ Processor activeProcess name: 'listen'. [socket waitForConnection. (self newSession) server: self; start] repeat ] release [ self stop. super release ] stop [ self isRunning ifTrue: [process terminate. process := nil. socket close. socket := nil] ] ] NetThread subclass: NetSession [ | server | log: request time: milliseconds [ ] next [ self subclassResponsibility ] server [ ^server ] server: aServer [ server := aServer ] createSocket [ ^server socket accept ] run [ | req time | Processor activeProcess name: 'connection'. [ [req := self next. time := Time millisecondsToRun: [self server respondTo: req. req release]] on: Error do: [:ex | "Ignore errors due to bad communication lines." self isPeerAlive ifFalse: [ex return]. ex pass]. self log: req time: time. self isPeerAlive] whileTrue ] ] smalltalk-3.2.5/packages/net/MIME.st0000644000175000017500000030562612123404352014101 00000000000000"====================================================================== | | MIME support | | ======================================================================" "====================================================================== | | Copyright (c) 2000 Cincom, Inc. | Copyright (c) 2009 Free Software Foundation | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" Namespace current: NetClients.MIME [ Object subclass: MessageElement [ MessageElement class >> new [ ^self basicNew initialize ] MessageElement class >> fromLine: aString [ "For compatibility with Swazoo" self subclassResponsibility ] MessageElement class >> readFrom: aStream [ "Each message element has responsibility to read itself from input stream. Reading usually involves parsing, so implementations of this method create an instance of lexical scanner and invoke a parser (see explanation for parse: method)" self subclassResponsibility ] MessageElement class >> readFromClient: aStream [ "This just parses a RFC821 message (with dots before each line)" ^self readFrom: (RemoveDotStream on: aStream) ] MessageElement class >> scannerOn: aStream [ ^((aStream respondsTo: #isRFC822Scanner) and: [aStream respondsTo: #isRFC822Scanner]) ifTrue: [aStream] ifFalse: [self scannerType on: aStream] ] MessageElement class >> scannerType [ self subclassResponsibility ] canonicalValue [ "Canonical value of an item represents its external representation as required by relevant protocols. Usually an element has to be converted to a cannonical representation before it can be sent over the network. This is a requirement of RFC822 and MIME. Canonical representation removes all whitespace between adjacent tokens" self subclassResponsibility ] value [ "Answers current value of the item. For structured elements (i.e. structured header fields) this value may be different for the source value read from source stream. For unstructured elements source and value are the same" ^self source ] value: aValue [ self source: aValue ] parse: scanner [ "Each message element has responsibility to parse itself. The argument is an appropriate scanner. Scanners for RFC822, Mime and HTTP messages are stream wrappers, so they can be used to read and tokenize input stream" self subclassResponsibility ] readFrom: aStream [ "Each message element has responsibility to read itself from input stream. Reading usually involves parsing, so implementations of this method typically create an instance of lexical scanner and invoke a parser (see explanation for parse: method)" self subclassResponsibility ] readFromClient: aStream [ "This just parses a RFC821 message (with dots before each line)" ^self readFrom: (RemoveDotStream on: aStream) ] scannerOn: aStream [ "Each element should know what the underlying syntax is. For example, structured fields would mostly use MIME syntax and tokenize input streams into MIME 'tokens' while which is part of many standards, has to be tokenized using RFC822 syntax (using RFC822 'atoms')" ^self class scannerOn: aStream ] printOn: aStream [ self subclassResponsibility ] storeOn: aStream [ self printOn: aStream ] initialize [ ] valueFrom: aString [ "Swazoo compatibility" ^self readFrom: aString readStream ] ] ] Namespace current: NetClients.MIME [ Object subclass: SimpleScanner [ | source hereChar token tokenType saveComments currentComment classificationMask sourceTrailStream lookahead | SimpleScanner class [ | classificationTable | ] Lf := nil. AlphabeticMask := nil. EndOfLineMask := nil. CRLF := nil. NilMask := nil. CRLFMask := nil. WhiteSpaceMask := nil. Cr := nil. DigitMask := nil. SimpleScanner class >> classificationTable [ ^classificationTable isNil ifTrue: [self superclass classificationTable] ifFalse: [classificationTable] ] SimpleScanner class >> classificationTable: aValue [ classificationTable := aValue ] SimpleScanner class >> cr [ ^Cr ] SimpleScanner class >> crlf [ ^CRLF ] SimpleScanner class >> lf [ ^Lf ] SimpleScanner class >> whiteSpace [ ^String with: Character space with: Character tab ] SimpleScanner class >> initClassificationTable [ classificationTable := WordArray new: 256. self initClassificationTableWith: AlphabeticMask when: [:c | ($a <= c and: [c <= $z]) or: [$A <= c and: [c <= $Z]]]. self initClassificationTableWith: DigitMask when: [:c | c >= $0 and: [c <= $9]]. self initClassificationTableWith: WhiteSpaceMask when: [:c | "space" "tab" #(32 9) includes: c asInteger]. self initClassificationTableWith: CRLFMask when: [:c | c == Character cr or: [c == Character nl]]. "self initClassificationTableWith: EndOfLineMask when: [:c | c == Character cr]" ] SimpleScanner class >> initClassificationTableWith: mask when: aBlock [ "Set the mask in all entries of the classificationTable for which aBlock answers true." 0 to: classificationTable size - 1 do: [:i | (aBlock value: (Character value: i)) ifTrue: [classificationTable at: i + 1 put: ((classificationTable at: i + 1) bitOr: mask)]] ] SimpleScanner class >> initialize [ "SimpleScanner initialize" self initializeConstants; initClassificationTable ] SimpleScanner class >> initializeConstants [ AlphabeticMask := 1. DigitMask := 2. WhiteSpaceMask := 4. CRLFMask := 8. EndOfLineMask := 16. NilMask := 0. Cr := Character cr. Lf := Character nl. CRLF := Array with: Character cr with: Character nl ] SimpleScanner class >> new [ ^self basicNew initialize ] SimpleScanner class >> on: stream [ ^self new on: stream ] SimpleScanner class >> defaultTokenType [ self subclassResponsibility ] SimpleScanner class >> printToken: assocOrValue on: stream [ | tokenType token | (assocOrValue isKindOf: Association) ifTrue: [tokenType := assocOrValue key. token := assocOrValue value] ifFalse: [tokenType := self defaultTokenType. token := assocOrValue]. self printToken: token tokenType: tokenType on: stream ] SimpleScanner class >> printToken: value tokenType: aSymbol on: stream [ self subclassResponsibility ] classificationMask [ ^classificationMask ] currentComment [ ^currentComment ] hereChar [ ^hereChar ] hereChar: char [ hereChar := char. classificationMask := self classificationMaskFor: hereChar. lookahead := nil. ^hereChar ] saveComments [ ^saveComments ] saveComments: aValue [ saveComments := aValue ] token [ ^token ] tokenType [ ^tokenType ] expected: aString [ "Notify that there is a problem at current token." ^self notify: 'expected `%1''' % {aString} ] notify: string [ "Subclasses may wish to override this" self error: string ] offEnd: aString [ "Parser overrides this" ^self notify: aString ] classificationMaskFor: charOrNil [ ^charOrNil isNil ifTrue: [NilMask] ifFalse: [^self class classificationTable at: charOrNil asInteger + 1] ] matchCharacterType: mask [ ^self classificationMask anyMask: mask ] mustMatch: char [ ^self mustMatch: char notify: [self expected: (String with: char)] ] mustMatch: char notify: message [ self skipWhiteSpace. self next == char ifFalse: [self notify: message] ] scanTokenMask: tokenMask [ "Scan token based on character mask. Answers token's value. Stream is positioned before the character that terminated scan" ^self scanWhile: [self matchCharacterType: tokenMask] ] scanUntil: aNiladicBlock [ "Scan token using a block until match is found. At the end of scan the stream is positioned after the matching character. Answers token value" | stream | stream := (String new: 40) writeStream. [self atEnd ifTrue: [self hereChar: nil. ^stream contents]. self step. aNiladicBlock value] whileFalse: [stream nextPut: hereChar]. ^stream contents ] scanWhile: aNiladicBlock [ "Scan token using a block. At the end of scan the stream is positioned at the first character that does not match. hereChar is nil. Answers token value" | str | str := self scanUntil: [aNiladicBlock value not]. hereChar notNil ifTrue: [self stepBack]. ^str ] step [ ^self next ] stepBack [ lookahead isNil ifFalse: [self error: 'cannot step back twice']. self sourceTrailSkip: -1. lookahead := hereChar. hereChar := nil ] initialize [ saveComments := true. self hereChar: nil ] on: inputStream [ "Bind the input stream" self hereChar: nil. source := inputStream ] scan: inputStream [ "Bind the input stream, fill the character buffers and first token buffer" self on: inputStream. ^self nextToken ] skipWhiteSpace [ "It is inefficient because intermediate stream is created. Perhaps refactoring scanWhile: can help" self scanWhile: [self matchCharacterType: WhiteSpaceMask] ] printToken: assoc on: stream [ self class printToken: assoc on: stream ] printToken: value tokenType: aSymbol on: stream [ self class printToken: value tokenType: aSymbol on: stream ] resetToken [ token := tokenType := nil ] sourceTrail [ | res | sourceTrailStream notNil ifTrue: [res := sourceTrailStream contents]. sourceTrailStream := nil. ^res ] sourceTrailNextPut: char [ (sourceTrailStream notNil and: [char notNil]) ifTrue: [sourceTrailStream nextPut: char] ] sourceTrailNextPutAll: string [ (sourceTrailStream notNil and: [string notNil]) ifTrue: [sourceTrailStream nextPutAll: string] ] sourceTrailOff [ sourceTrailStream := nil ] sourceTrailOn [ sourceTrailStream := (String new: 64) writeStream ] sourceTrailSkip: integer [ sourceTrailStream notNil ifTrue: [sourceTrailStream skip: integer] ] atEnd [ ^lookahead isNil and: [source atEnd] ] contents [ | contents | contents := source contents lookahead notNil ifTrue: [contents := (contents species with: lookahead) , contents. lookahead := nil]. ^contents ] next [ self hereChar: self peek. self sourceTrailNextPut: hereChar. lookahead := nil. ^hereChar ] next: anInteger [ "Answer the next anInteger elements of the receiver." | newCollection res | newCollection := self species new: anInteger. res := self next: anInteger into: newCollection startingAt: 1. self sourceTrailNextPutAll: res. ^res ] next: anInteger into: aSequenceableCollection startingAt: startIndex [ "Store the next anInteger elements of the receiver into aSequenceableCollection starting at startIndex in aSequenceableCollection. Answer aSequenceableCollection." | index stopIndex | index := startIndex. stopIndex := index + anInteger. (lookahead notNil and: [anInteger > 0]) ifTrue: [aSequenceableCollection at: index put: lookahead. index := index + 1. lookahead := nil]. anInteger > 0 ifTrue: [self hereChar: nil]. [index < stopIndex] whileTrue: [aSequenceableCollection at: index put: source next. index := index + 1]. ^aSequenceableCollection ] nextLine [ | line | line := self scanUntil: [self matchCharacterType: CRLFMask]. self scanWhile: [self matchCharacterType: CRLFMask]. ^line ] peek [ "Answer what would be returned with a self next, without changing position. If the receiver is at the end, answer nil." lookahead notNil ifTrue: [^lookahead]. self atEnd ifTrue: [^nil]. hereChar := nil. lookahead := source next. ^lookahead ] peekFor: anObject [ "Answer false and do not move the position if self next ~= anObject or if the receiver is at the end. Answer true and increment position if self next = anObject." "This sets lookahead" self peek isNil ifTrue: [^false]. "peek for matching element" anObject = lookahead ifTrue: [self next. ^true]. ^false ] position [ ^source position - (lookahead isNil ifTrue: [0] ifFalse: [1]) ] position: anInt [ lookahead := nil. ^source position: anInt ] skip: integer [ self sourceTrailSkip: integer. lookahead isNil ifFalse: [lookahead := nil. source skip: integer - 1] ifTrue: [source skip: integer] ] species [ ^source species ] upTo: anObject [ "Answer a subcollection from position to the occurrence (if any, exclusive) of anObject. The stream is left positioned after anObject. If anObject is not found answer everything." | str | lookahead = anObject ifTrue: [self sourceTrailNextPut: lookahead. lookahead := nil. ^'']. str := source upTo: anObject. lookahead isNil ifFalse: [str := lookahead asString , str. lookahead := nil]. self sourceTrailNextPutAll: str; sourceTrailNextPut: anObject. ^str ] upToAll: pattern [ | str | lookahead isNil ifFalse: [source skip: -1. lookahead := nil]. str := source upToAll: pattern. self sourceTrailNextPutAll: str; sourceTrailNextPutAll: pattern. ^str ] upToEnd [ | str | str := source upToEnd. lookahead isNil ifFalse: [str := lookahead asString , str. lookahead := nil]. self sourceTrailNextPutAll: str. ^str ] testScanTokens [ | s st | s := WriteStream on: (Array new: 16). st := WriteStream on: (Array new: 16). [tokenType = #doIt] whileFalse: [s nextPut: token. st nextPut: tokenType. self nextToken]. ^Array with: s contents with: st contents ] testScanTokens: textOrString [ "Answer with an Array which has been tokenized" self scan: (ReadStream on: textOrString asString). ^self testScanTokens ] nextToken [ self subclassResponsibility ] nextTokenAsAssociation [ "Read next token and and answer tokenType->token" self nextToken. ^tokenType -> token ] scanToken: aNiladicBlock delimitedBy: anArray notify: errorMessageString [ "Scan next lexical token based on the criteria defined by NiladicBlock. The block is evaluated for every character read from input stream until it yields false. Stream is positioned before character that terminated scan" "Example: self scanToken: [ self scanQuotedChar; matchCharacterType: DomainTextMask ] delimitedBy: '[]' notify: 'Malformed domain text'." | string | self mustMatch: anArray first. string := self scanWhile: aNiladicBlock. self mustMatch: anArray last notify: errorMessageString. ^string ] scanTokens: textOrString [ "Answer with an Array which has been tokenized" ^self on: (ReadStream on: textOrString asString); tokenize ] tokenize [ | s | s := WriteStream on: (Array new: 16). [self nextToken. tokenType = #doIt] whileFalse: [s nextPut: token]. ^s contents ] tokenizeList: aBlock separatedBy: comparisonBlock [ "list = token *( separator token)" | stream block | stream := (Array new: 4) writeStream. block := [stream nextPut: aBlock value]. block value. "Evaluate for the first element" self tokenizeWhile: [comparisonBlock value] do: block. ^stream contents ] tokenizeUntil: aBlock do: actionBlock [ [self skipWhiteSpace. self position. self nextToken. tokenType == #doIt or: aBlock] whileFalse: [actionBlock value] ] tokenizeWhile: aBlock [ | s | s := WriteStream on: (Array new: 16). self tokenizeWhile: [aBlock value] do: [s nextPut: token]. ^s contents ] tokenizeWhile: aBlock do: actionBlock [ | pos | [self skipWhiteSpace. pos := self position. self nextToken. tokenType ~= #doIt & aBlock value "#######"] whileTrue: [actionBlock value]. self position: pos "Reset position to the beginning of the token that did not match" ] ] ] Namespace current: NetClients.MIME [ MessageElement subclass: MimeEntity [ | parent fields body | MimeEntity class >> contentLengthFieldName [ ^'content-length' ] MimeEntity class >> contentTypeFieldName [ ^'content-type' ] MimeEntity class >> syntaxOfMultiPartMimeBodies [ "From RFC 2046: Media Types November 1996 The Content-Type field for multipart entities requires one parameter, 'boundary'. The boundary delimiter line is then defined as a line consisting entirely of two hyphen characters ($-, decimal value 45) followed by the boundary parameter value from the Content-Type header field, optional linear whitespace, and a terminating CRLF. WARNING TO IMPLEMENTORS: The grammar for parameters on the Content- type field is such that it is often necessary to enclose the boundary parameter values in quotes on the Content-type line. This is not always necessary, but never hurts. Implementors should be sure to study the grammar carefully in order to avoid producing invalid Content-type fields. Thus, a typical 'multipart' Content-Type header field might look like this: Content-Type: multipart/mixed; boundary=gc0p4Jq0M2Yt08j34c0p But the following is not valid: Content-Type: multipart/mixed; boundary=gc0pJq0M:08jU534c0p (because of the colon) and must instead be represented as Content-Type: multipart/mixed; boundary=" "gc0pJq0M:08jU534c0p" " This Content-Type value indicates that the content consists of one or more parts, each with a structure that is syntactically identical to an RFC 822 message, except that the header area is allowed to be completely empty, and that the parts are each preceded by the line --gc0pJq0M:08jU534c0p The boundary delimiter MUST occur at the beginning of a line, i.e., following a CRLF, and the initial CRLF is considered to be attached to the boundary delimiter line rather than part of the preceding part. The boundary may be followed by zero or more characters of linear whitespace. It is then terminated by either another CRLF and the header fields for the next part, or by two CRLFs, in which case there are no header fields for the next part. If no Content-Type field is present it is assumed to be 'message/rfc822' in a 'multipart/digest' and 'text/plain' otherwise. NOTE: The CRLF preceding the boundary delimiter line is conceptually attached to the boundary so that it is possible to have a part that does not end with a CRLF (line break). Body parts that must be considered to end with line breaks, therefore, must have two CRLFs preceding the boundary delimiter line, the first of which is part of the preceding body part, and the second of which is part of the encapsulation boundary." ] MimeEntity class >> headerTypeFor: headerName [ ^HeaderField "For now" ] MimeEntity class >> parser [ ^self scannerType new ] MimeEntity class >> parseFieldsFrom: stream [ ^self new parseFieldsFrom: (self parser on: stream) ] MimeEntity class >> readFrom: stream [ ^self new readFrom: (self parser on: stream) ] MimeEntity class >> readFrom: stream defaultType: type [ ^(self new) fieldAt: 'content-type' put: (ContentTypeField fromLine: 'content-type: ' , type); readFrom: (self parser on: stream); yourself ] MimeEntity class >> readFrom: stream type: type [ ('message/*' match: type) ifTrue: [^self readFrom: stream]. ^(self new) fieldAt: 'content-type' put: (ContentTypeField fromLine: 'content-type: ' , type); parseBodyFrom: (self parser on: stream); yourself ] MimeEntity class >> scannerType [ ^MimeScanner ] bcc [ ^self fieldAt: 'bcc' ] body [ ^body ] body: aValue [ body := aValue ] boundary [ ^self contentTypeField boundary ] cc [ ^self fieldAt: 'cc' ] charset [ ^self contentTypeField charset ] contents [ | handler | handler := ContentHandler classFor: self contentType. ^(handler on: self body readStream) contents ] contentId [ ^(self fieldAt: 'content-id' ifAbsent: [^nil]) id ] contentType [ ^self contentTypeField contentType ] contentTypeField [ ^self fieldAt: 'content-type' ifAbsent: [self defaultContentTypeField] ] fields [ ^fields ] fields: aValue [ fields := aValue ] from [ ^self fieldAt: 'from' ] parent [ ^parent ] parent: aMimeEntity [ parent := aMimeEntity ] recipients [ | recipients | recipients := #(). self to isNil ifFalse: [recipients := recipients , self to addresses]. self cc isNil ifFalse: [recipients := recipients , self cc addresses]. self bcc isNil ifFalse: [recipients := recipients , self bcc addresses]. ^recipients ] replyTo [ ^self fieldAt: 'reply-to' ] sender [ ^self fieldAt: 'sender' ifAbsent: [self fieldAt: 'from'] ] subject [ ^self fieldAt: 'subject' ] subtype [ ^self contentTypeField subtype ] to [ ^self fieldAt: 'to' ] type [ ^self contentTypeField type ] addField: field [ "This method will check if the field exists already; if yes, if it can be merged into the existing field and, if yes, merge it. Otherwise, add as a new field" "Implement field merge" ^self fieldAt: field name put: field ] bodyPartAt: index [ ^self body at: index ] bodyPartNamed: id [ ^self isMultipart ifTrue: [self body detect: [:part | part contentId = id]] ifFalse: [nil] ] fieldAt: aString [ ^self fieldAt: aString asLowercase ifAbsent: [nil] ] fieldAt: aString ifAbsent: aNiladicBlock [ ^self fields at: aString asLowercase ifAbsent: aNiladicBlock ] fieldAt: aString ifAbsentPut: aNiladicBlock [ ^self fields at: aString asLowercase ifAbsentPut: aNiladicBlock ] fieldAt: aString put: aHeaderField [ ^self fields at: aString asLowercase put: aHeaderField ] asByteArray [ ] asStream [ ] asString [ ] asStringOrByteArray [ ] defaultContentType [ ^self defaultContentTypeField contentType ] defaultContentTypeField [ ^ContentTypeField default ] initialize [ fields := Dictionary new: 4 ] defaultContentTypeForNestedEntities [ ^(self type = 'multipart' and: [self subtype = 'digest']) ifTrue: ['content-type: message/rfc822'] ifFalse: ['text/plain; charset=US-ASCII'] ] fieldFactory [ "Answers object that can map field name to field type (class). It may and will be subclassed" ^HeaderField ] parseBodyFrom: rfc822Stream [ self isMultipart ifTrue: [self parseMultipartBodyFrom: rfc822Stream] ifFalse: [self parseSimpleBodyFrom: rfc822Stream] ] parseFieldFrom: stream [ | field | field := self fieldFactory readFrom: stream. self addField: field ] parseFieldsFrom: rfc822Stream [ [rfc822Stream atEndOfLine] whileFalse: [self parseFieldFrom: rfc822Stream]. rfc822Stream next; skipEndOfLine ] parseMultipartBodyFrom: rfc822Stream [ "Parse multi-part body. See more in 'documentation' category on the class side" | boundary parts partArray | (boundary := self boundary) notNil ifTrue: [parts := (Array new: 2) writeStream. "Skip to the first boundary, ignore text in between" partArray := rfc822Stream scanToBoundary: boundary]. [partArray isNil ifTrue: [^self error: 'Missing boundary in multi-part body']. partArray := rfc822Stream scanToBoundary: boundary. partArray notNil ifTrue: [parts nextPut: partArray first]. partArray notNil and: [partArray last ~~ #last]] whileTrue. self body: (parts contents collect: [:part | MimeEntity readFrom: part readStream defaultType: self defaultContentTypeForNestedEntities]) ] parseSimpleBodyFrom: rfc822Stream [ | stream | stream := (String new: 256) writeStream. self parseSimpleBodyFrom: rfc822Stream onto: stream. self body: stream contents ] parseSimpleBodyFrom: rfc822Stream onto: stream [ | inStream | inStream := RemoveDotStream on: rfc822Stream. [inStream atEnd] whileFalse: [stream nextPutAll: inStream nextLine; nl] ] readFrom: rfc822Stream [ self parseFieldsFrom: rfc822Stream. self parseBodyFrom: rfc822Stream ] skipSimpleBodyFrom: rfc822Stream onto: stream [ | inStream | inStream := RemoveDotStream on: rfc822Stream. [inStream atEnd] whileFalse: [inStream nextLine] ] printBodyOn: aStream [ self body isNil ifTrue: [^self]. self body class == Array ifFalse: [aStream nextPutAll: self body. ^self]. aStream nextPutAll: 'This is a MIME message. '. self body do: [:each | aStream nextPutAll: '--'; nextPutAll: self boundary. each printOn: aStream]. aStream nextPutAll: '--'; nextPutAll: self boundary; nextPutAll: '--' ] printBodyOnClient: aClient [ | out | out := PrependDotStream to: aClient. self printBodyOn: out. out flush ] printHeaderOn: aStream [ self fields do: [:each | aStream print: each; nl] ] printHeaderOnClient: aClient [ | out | out := PrependDotStream to: aClient. self printHeaderOn: out. out flush ] printMessageOn: aStream [ self printHeaderOn: aStream. aStream nl. self printBodyOn: aStream ] printMessageOnClient: aClient [ | out | out := PrependDotStream to: aClient. self printMessageOn: out. out flush ] printOn: aStream [ self printMessageOn: aStream ] hasBoundary [ ^(self fieldAt: 'boundary') notNil ] isMultipart [ ^self contentTypeField isMultipart ] ] ] Namespace current: NetClients.MIME [ MessageElement subclass: NetworkEntityDescriptor [ | alias comment | comment comment comment '> NetworkEntityDescriptor class >> scannerType [ ^NetworkAddressParser ] alias [ ^alias ] alias: aValue [ alias := aValue ] comment [ ^comment ] comment: aValue [ comment := aValue ] scannerType [ ^self class scannerType ] printAliasOn: stream [ alias notNil ifTrue: [stream nextPutAll: alias] ] printCanonicalValueOn: stream [ self subclassResponsibility ] printCommentOn: stream [ comment notNil ifTrue: [stream nextPut: $(. comment do: [:char | (RFC822Scanner isCommentChar: char) ifFalse: [stream nextPut: $\]. stream nextPut: char]. stream nextPut: $)] ] printOn: stream [ self printCanonicalValueOn: stream. comment notNil ifTrue: [self printCommentOn: stream] ] ] ] Namespace current: NetClients.MIME [ MessageElement subclass: HeaderField [ | name source | . These answer scanner class and new instance of parser for a given source stream. Method parse: parses and sets field''s value. A conventional way of creating new instance of a stream from source field is HeaderField readFrom: stream This reads field''s name, find an appropriate field class for this name, creates an instance of this field and lets it read/parse field''s value. Instance Variables: name comment source comment '> HeaderField class >> name: aname [ "Answer new instance of field corresponding to field's name. For now, treat all fields as unstructured" ^((self fieldClassForName: aname) new) name: aname; yourself ] HeaderField class >> defaultFieldClass [ ^HeaderField ] HeaderField class >> fieldClassForName: fieldName [ "For now we scan all subclasses. Later I plan to use registry which is somewhat more flexible, especially if different protocols can have different formats for the same field" | fname | fname := fieldName asLowercase. ^HeaderField allSubclasses detect: [:each | (each fieldNames detect: [:candidate | candidate asLowercase = fname] ifNone: [nil]) notNil] ifNone: [self defaultFieldClass] ] HeaderField class >> fieldNames [ ^#() ] HeaderField class >> fromLine: aString [ "For compatibility with Swazoo" | rfc822Stream | rfc822Stream := self scannerOn: aString readStream. ^(self name: (self readFieldNameFrom: rfc822Stream)) readFrom: rfc822Stream; yourself ] HeaderField class >> readFieldNameFrom: rfc822Stream [ | fname | fname := rfc822Stream scanFieldName. rfc822Stream mustMatch: $: notify: 'Invalid Field (Missing colon)'. rfc822Stream skipWhiteSpace. ^fname asLowercase ] HeaderField class >> readFrom: rfc822Stream [ "Reads and parses message header contents from the message stream; answers an instance of message header. rfc822Stream is RFC822MessageParser; it extends stream interface by providing message scanning/parsing services. At this point the stream is positioned right after semicolon that delimits header name" ^(self name: (self readFieldNameFrom: rfc822Stream)) readFrom: rfc822Stream ] HeaderField class >> scannerType [ ^MimeScanner ] canonicalFieldName [ | s | s := name copy. s isEmpty ifTrue: [^s]. s at: 1 put: s first asUppercase. "Capitalize first letter" ^s ] canonicalValue [ "Override as necessary" ^self value ] name [ ^name ] name: aString [ ^name := aString ] source [ ^source ] source: anObject [ source := anObject ] value [ ^self source ] value: aValue [ self source: aValue ] parse: rfc822Stream [ "Generic parser for unstructured fields. Copy everything up to CRLF. Scanner handles end of line rules and answers cr when end of line is seen. Scanner also folds linear white space answering space character in place of " self value: rfc822Stream nextLine ] readFrom: aStream [ self source: aStream scanText. ^self parse: (self scannerOn: self source readStream) ] printOn: aStream [ self printOn: aStream indent: 0 ] printOn: aStream indent: level [ aStream tab: level; nextPutAll: self canonicalFieldName; nextPut: $:; space. self printValueOn: aStream ] printStructureOn: aStream [ "Unstructured fields just print their value on a stream" self printValueOn: aStream ] printValueOn: aStream [ | val | (val := self value) notNil ifTrue: [val displayOn: aStream] ] valueFrom: aString [ "Swazoo compatibility" ^self readFrom: aString readStream ] ] ] Namespace current: NetClients.MIME [ SimpleScanner subclass: MimeEncodedWordCoDec [ MimeEncodedWordCoDec class >> decode: word [ ^self decode: word using: (self encodingParametersOf: word) ] MimeEncodedWordCoDec class >> decode: word using: arr [ ^arr notNil ifTrue: [self decodeEncodedWord: (arr at: 3) charset: arr first encoding: (arr at: 2)] ifFalse: [word] ] MimeEncodedWordCoDec class >> decodeComment: commentString [ ^self new decodeComment: commentString ] MimeEncodedWordCoDec class >> decodePhrase: words [ "decode phrase word by word; concatenate decoded words and answer concatenated string" | output | output := (String new: words size) writeStream. self decodePhrase: words printOn: output. ^output contents ] MimeEncodedWordCoDec class >> decodePhrase: words printOn: stream [ | params lastParams lastWord | lastWord := nil. words do: [:word | lastParams := params. params := self encodingParametersOf: word. (lastWord notNil and: [params isNil or: [lastParams isNil]]) ifTrue: [stream space]. stream nextPutAll: (lastWord := self decode: word using: params)] ] MimeEncodedWordCoDec class >> decodeText: text [ ^self new decodeText: text ] MimeEncodedWordCoDec class >> encodingParametersOf: word [ | mark1 mark2 | ^(word first == $= and: [word last == $= and: [(word at: 2) == $? and: [(word at: word size - 1) == $? and: [(mark1 := word nextIndexOf: $? from: 3 to: word size - 2) > 0 and: [(mark2 := word nextIndexOf: $? from: mark1 + 1 to: word size - 2) > (mark1 + 1)]]]]]) ifTrue: [Array with: (word copyFrom: 3 to: mark1 - 1) asLowercase with: (word copyFrom: mark1 + 1 to: mark2 - 1) asLowercase with: (word copyFrom: mark2 + 1 to: word size - 2)] ifFalse: [nil] ] MimeEncodedWordCoDec class >> decodeEncodedWord: contents charset: charset encoding: encodingString [ | encoding | encoding := encodingString asLowercase. (#('b' 'base64') includes: encoding) ifTrue: [^MimeScanner decodeBase64From: 1 to: contents size in: contents]. (#('q' 'quoted-printable') includes: encoding) ifTrue: [^self decodeQuotedPrintableFrom: 1 to: contents size in: contents]. (#('uue' 'uuencode' 'x-uue' 'x-uuencode') includes: encoding) ifTrue: [^self decodeUUEncodedFrom: 1 to: contents size in: contents]. ^nil "Failed to decode" ] MimeEncodedWordCoDec class >> decodeQuotedPrintableFrom: startIndex to: endIndex in: aString [ "Decode aString from startIndex to endIndex in quoted-printable." | input output char n1 n2 | input := ReadStream on: aString from: startIndex to: endIndex. output := (String new: endIndex - startIndex) writeStream. [input atEnd] whileFalse: [char := input next. $= == char ifTrue: [('0123456789ABCDEF' includes: (n1 := input next)) ifTrue: [n2 := input next. output nextPut: ((n1 digitValue bitShift: 4) + n2 digitValue) asCharacter]] ifFalse: [output nextPut: char]]. ^output contents ] MimeEncodedWordCoDec class >> decodeUUEncodedFrom: startIndex to: farEndIndex in: aString [ "decode aString from startIndex to farEndIndex as uuencode-encoded" | endIndex i nl space output data | endIndex := farEndIndex - 2. [endIndex <= startIndex or: [(aString at: endIndex + 1) = $e and: [(aString at: endIndex + 2) = $n and: [(aString at: endIndex + 3) = $d]]]] whileFalse: [endIndex := endIndex - 1]. i := (aString findString: 'begin' startingAt: startIndex ignoreCase: true useWildcards: false) first. i = 0 ifTrue: [i := startIndex]. nl := Character nl. space := Character space asInteger. output := (data := String new: (endIndex - startIndex) * 3 // 4) writeStream. [[i < endIndex and: [(aString at: i) ~= nl]] whileTrue: [i := i + 1]. i < endIndex] whileTrue: [| count | count := (aString at: (i := i + 1)) asInteger - space bitAnd: 63. i := i + 1. count = 0 ifTrue: [i := endIndex] ifFalse: [[count > 0] whileTrue: [| m n o p | m := (aString at: i) asInteger - space bitAnd: 63. n := (aString at: i + 1) asInteger - space bitAnd: 63. o := (aString at: i + 2) asInteger - space bitAnd: 63. p := (aString at: i + 3) asInteger - space bitAnd: 63. count >= 1 ifTrue: [output nextPut: (Character value: (m bitShift: 2) + (n bitShift: -4)). count >= 2 ifTrue: [output nextPut: (Character value: ((n bitShift: 4) + (o bitShift: -2) bitAnd: 255)). count >= 3 ifTrue: [output nextPut: (Character value: ((o bitShift: 6) + p bitAnd: 255))]]]. i := i + 4. count := count - 3]]]. ^data copyFrom: 1 to: output position ] decode: word [ ^self class decode: word ] decodeComment: text [ "First, quick check if we possibly have an encoded word" | output word params spaces lastParams lastWord | (text indexOfSubCollection: '=?' startingAt: 1) = 0 ifTrue: [^text]. "We suspect there might be an encoded word inside, do the legwork" self on: text readStream. output := (String new: text size) writeStream. spaces := String new. params := lastWord := nil. [lastParams := params. self atEnd] whileFalse: [word := self scanWhile: [(self matchCharacterType: WhiteSpaceMask) not]. params := self class encodingParametersOf: word. (lastWord notNil and: [params isNil or: [lastParams isNil]]) ifTrue: [output nextPutAll: spaces]. output nextPutAll: (lastWord := self class decode: word using: params). spaces := self scanWhile: [self matchCharacterType: WhiteSpaceMask]]. ^output contents ] decodePhrase: words [ ^self class decodePhrase: words ] decodeText: text [ "Decoding of text is similar to decoding of comment, but RFC2047 requires that an encoded word that appears in in *text token MUST be separated from any adjacent encoded word or text by a linear-white-space" "First, quick check if we possibly have an encoded word" | output word | (text indexOfSubCollection: '=?' startingAt: 1) = 0 ifTrue: [^text]. "We suspect there might be an encoded word inside, do the legwork" self on: text readStream. output := (String new: text size) writeStream. [self atEnd] whileFalse: [word := self scanWhile: [(self matchCharacterType: WhiteSpaceMask) not]. output nextPutAll: (self decode: word); nextPutAll: (self scanWhile: [self matchCharacterType: WhiteSpaceMask])]. ^output contents ] encodingParametersOf: word [ ^self class encodingParametersOf: word ] ] ] Namespace current: NetClients.MIME [ SimpleScanner subclass: MailScanner [ MailScanner class >> printQuotedText: str on: stream [ "Print word as either atom or quoted text" (self shouldBeQuoted: str) ifTrue: [stream nextPut: $"; nextPutAll: str; nextPut: $"] ifFalse: [stream nextPutAll: str] ] MailScanner class >> printTokenList: list on: stream [ self printTokenList: list on: stream separatedBy: [stream space] ] MailScanner class >> printTokenList: list on: stream separatedBy: aBlock [ list do: [:assoc | self printToken: assoc on: stream] separatedBy: aBlock ] printAtom: atom on: stream [ self class printAtom: atom on: stream ] printQuotedText: qtext on: stream [ self class printQuotedText: qtext on: stream ] printText: qtext on: stream [ self class printText: qtext on: stream ] ] ] Namespace current: NetClients.MIME [ NetworkEntityDescriptor subclass: NetworkAddressDescriptor [ | domain localPart route | NetworkAddressDescriptor class >> readFrom: aString [ ^self parser parse: aString ] NetworkAddressDescriptor class >> scannerType [ ^NetworkAddressParser ] NetworkAddressDescriptor class >> addressesFrom: stream [ "self addressesFrom: 'kyasu@crl.fujixerox.co.jp' readStream." "self addressesFrom: 'Kazuki Yasumatsu ' readStream." "self addressesFrom: 'kyasu@crl.fujixerox.co.jp (Kazuki Yasumatsu)' readStream." "self addressesFrom: ' kyasu1, kyasu2, Kazuki Yasumatsu , kyasu4 (Kazuki Yasumatsu)' readStream." "self addressesFrom: ' foo bar, kyasu1, , Kazuki Yasumatsu ( (foo bar), bar)' readStream." ^self scannerType addressesFrom: stream ] NetworkAddressDescriptor class >> addressFrom: aString [ "self addressesFrom: 'kyasu@crl.fujixerox.co.jp'." "self addressesFrom: 'Kazuki Yasumatsu '." "self addressesFrom: 'kyasu@crl.fujixerox.co.jp (Kazuki Yasumatsu)'." "self addressesFrom: ' kyasu1, kyasu2, Kazuki Yasumatsu , kyasu4 (Kazuki Yasumatsu)'." "self addressesFrom: ' foo bar, kyasu1, , Kazuki Yasumatsu ( (foo bar), bar)'." ^self scannerType addressFrom: aString ] addressSpecString [ ^self printStringSelector: #printAddressSpecOn: ] aliasString [ ^self printStringSelector: #printAliasOn: ] commentString [ ^self printStringSelector: #printCommentOn: ] domain [ ^domain ] domain: aValue [ domain := aValue ] domainString [ ^self printStringSelector: #printDomainOn: ] localPart [ ^localPart ] localPart: aValue [ localPart := aValue ] localPartString [ ^self printStringSelector: #printLocalPartOn: ] route [ ^route ] route: aValue [ route := aValue ] routeString [ ^self printStringSelector: #printRouteOn: ] initialize [ localPart := Array new ] printAddressSpecOn: stream [ self hasAddressSpec ifTrue: [self printLocalPartOn: stream. stream nextPut: $@. self printDomainOn: stream] ] printCanonicalValueOn: stream [ alias notNil ifTrue: [self printRouteAddressOn: stream] ifFalse: [self printAddressSpecOn: stream] ] printDomainOn: stream [ self scannerType printDomain: domain on: stream ] printLocalPartOn: stream [ localPart do: [:token | self scannerType printWord: token on: stream] separatedBy: [stream nextPut: $.] ] printRouteAddressOn: stream [ self printAliasOn: stream. (route notNil or: [self hasAddressSpec]) ifTrue: [stream nextPut: $<. self printRouteOn: stream; printAddressSpecOn: stream. stream nextPut: $>] ] printRouteOn: stream [ (route notNil and: [route notEmpty]) ifTrue: [route do: [:domainx | stream space; nextPut: $@. self scannerType printDomain: domainx on: stream. stream nextPut: $:]. stream space] ] printStringSelector: sel [ | stream | stream := (String new: 40) writeStream. self perform: sel with: stream. ^stream contents ] hasAddressSpec [ ^localPart notNil and: [localPart isEmpty not and: [domain notNil and: [domain isEmpty not]]] ] ] ] Namespace current: NetClients.MIME [ HeaderField subclass: StructuredHeaderField [ | parameters | <=> ) In the future we may reconsiders if providing parameter storage here is a good idea because it seems that only a few field types can have parameters Instance Variables: parameters Contains parsed parameter values as associations '> canonicalValue [ "Canonical value removes all white space and comments from the source" ^self tokenizedValueFrom: (self scannerOn: self source readStream) ] parameterAt: aString [ ^self parameterAt: aString ifAbsent: [nil] ] parameterAt: aString ifAbsent: aBlock [ ^parameters at: aString ifAbsent: aBlock ] parameterAt: aString ifAbsentPut: aBlock [ ^self parameters at: aString ifAbsentPut: aBlock ] parameterAt: aString put: aBlock [ ^self parameters at: aString put: aBlock ] parameters [ ^parameters ] parameters: aCollection [ parameters := aCollection ] parametersDo: aMonadicBlock [ "aBlock is a one-argument block which will be evaluated for each parameter. Argument is an association (parameter name, parameter value)" ^self parameters keysAndValuesDo: [:nm :val | aMonadicBlock value: nm -> val] ] printParameter: assoc on: aStream [ aStream nextPut: $;; nextPutAll: assoc key; nextPut: $=; nextPutAll: assoc value ] printParametersOn: aStream [ self parametersDo: [:assoc | self printParameter: assoc on: aStream] ] printStructureOn: aStream [ "Default implementation is the same as inherited. Subclasses can override it" super printValueOn: aStream ] printValueOn: aStream [ "The reasoning here is that if an instance was created by parsing input stream, it should be reconstructed verbatim rather than restored by us. We may alter the original in some ways and sometimes it may be undesirable" self value notNil ifTrue: [super printValueOn: aStream] ifFalse: [self printStructureOn: aStream] ] initialize [ super initialize. parameters := Dictionary new ] readParametersFrom: rs [ | paramName paramValue | [rs skipWhiteSpace; atEnd] whileFalse: [rs mustMatch: $; notify: 'Invalid parameter'. paramName := rs nextToken. rs mustMatch: $= notify: 'Invalid parameter'. paramValue := rs nextToken. parameters at: paramName put: paramValue] ] tokenize: rfc822Stream [ "Scan field value token by token. Answer an array of tokens" | result token | result := (Array new: 2) writeStream. [rfc822Stream atEnd or: [rfc822Stream peek == Character nl or: [(token := rfc822Stream nextToken) isNil]]] whileFalse: [result nextPut: token]. ^result contents ] tokenizedValueFrom: rfc822Stream [ "Scan field value token by token. Answer a string that is a concatenation of all elements in the array. One can view this as a canonicalized field value because this operation eliminates all white space and comments" | result tokens | result := (String new: 20) writeStream. tokens := self tokenize: rfc822Stream. tokens do: [:token | token isString ifTrue: [result nextPutAll: token] ifFalse: [result nextPut: token]]. ^result contents ] ] ] Namespace current: NetClients.MIME [ NetworkEntityDescriptor subclass: MailGroupDescriptor [ | addresses | addresses [ ^addresses ] addresses: anArray [ addresses := anArray ] alias [ ^alias ] alias: aString [ alias := aString ] initialize [ addresses := Array new ] printCanonicalValueOn: stream [ self printAliasOn: stream. stream nextPut: $:. self addresses do: [:address | address printOn: stream] separatedBy: [stream nextPut: $,]. stream nextPut: $; ] ] ] Namespace current: NetClients.MIME [ MailScanner subclass: RFC822Scanner [ HeaderNameMask := nil. QuotedPairChar := nil. QuotedPairMask := nil. AtomMask := nil. QuotedTextMask := nil. CommentMask := nil. SimpleTimeZones := nil. DomainTextMask := nil. TextMask := nil. HeaderNameDelimiterChar := nil. TokenMask := nil. RFC822Scanner class >> specials [ "Note that definition of this set varies from standard to standard, so this method needs to be overridden for specialized parsers" ^'()<>@,;:\".[]' ] RFC822Scanner class >> tspecials [ "tspecials in MIME and HTTP. It is derived from RCC822 specials with addition of , , <=> and removal of <.>" ^'()<>@,;:\"/[]?=' ] RFC822Scanner class >> initClassificationTable [ super initClassificationTable. self initClassificationTableWith: HeaderNameMask when: [:c | c > Character space and: [c ~~ $:]]. self initClassificationTableWith: TextMask when: [:c | c ~~ Character cr and: [c ~~ Character nl]]. self initClassificationTableWith: AtomMask when: [:c | c > Character space and: [(self specials includes: c) not]]. self initClassificationTableWith: TokenMask when: [:c | c > Character space and: [(self tspecials includes: c) not]]. self initClassificationTableWith: QuotedTextMask when: [:c | c ~~ $" and: [c ~~ $\ and: [c ~~ Character cr and: [c ~~ Character nl]]]]. self initClassificationTableWith: DomainTextMask when: [:c | ('[]\' includes: c) not and: [c ~~ Character cr and: [c ~~ Character nl]]]. self initClassificationTableWith: CommentMask when: [:c | c ~~ $( and: [c ~~ $) and: [c ~~ $\ and: [c ~~ Character cr and: [c ~~ Character nl]]]]] ] RFC822Scanner class >> initialize [ "RFC822Scanner initialize" self initializeConstants; initClassificationTable ] RFC822Scanner class >> initializeConstants [ AtomMask := 256. CommentMask := 512. DomainTextMask := 1024. HeaderNameMask := 2048. QuotedTextMask := 4096. TextMask := 8192. TokenMask := 16384. QuotedPairMask := (QuotedTextMask bitOr: CommentMask) bitOr: DomainTextMask. QuotedPairChar := $\. HeaderNameDelimiterChar := $: ] RFC822Scanner class >> dateAndTimeFrom: aString [ "RFC822Scanner dateAndTimeFrom: '6 Dec 88 10:16:08 +0900 (Tuesday)'." "RFC822Scanner dateAndTimeFrom: '12 Dec 88 10:16:08 +0900 (Tuesday)'." "RFC822Scanner dateAndTimeFrom: 'Fri, 31 Mar 89 09:13:20 +0900'." "RFC822Scanner dateAndTimeFrom: 'Tue, 18 Apr 89 23:29:47 +0900'." "RFC822Scanner dateAndTimeFrom: 'Tue, 23 May 89 13:52:12 JST'." "RFC822Scanner dateAndTimeFrom: 'Thu, 1 Dec 88 17:13:27 jst'." "RFC822Scanner dateAndTimeFrom: 'Sat, 15 Jul 95 14:36:22 0900'." "RFC822Scanner dateAndTimeFrom: '2-Nov-86 10:43:42 PST'." "RFC822Scanner dateAndTimeFrom: 'Friday, 21-Jul-95 04:04:55 GMT'." "RFC822Scanner dateAndTimeFrom: 'Jul 10 11:06:40 1995'." "RFC822Scanner dateAndTimeFrom: 'Jul 10 11:06:40 JST 1995'." "RFC822Scanner dateAndTimeFrom: 'Mon Jul 10 11:06:40 1995'." "RFC822Scanner dateAndTimeFrom: 'Mon Jul 10 11:06:40 JST 1995'." "RFC822Scanner dateAndTimeFrom: '(6 December 1988 10:16:08 am )'." "RFC822Scanner dateAndTimeFrom: '(12 December 1988 10:16:08 am )'." "RFC822Scanner dateAndTimeFrom: ''." | rfcString | aString size <= 10 ifTrue: ["may be illegal format" ^DateTime utcDateAndTimeNow]. rfcString := self normalizeDateAndTimeString: aString. ^self readRFC822DateAndTimeFrom: rfcString readStream ] RFC822Scanner class >> defaultTimeZoneDifference [ ^DateTime now offset seconds ] RFC822Scanner class >> initializeTimeZones [ "RFC822Scanner initializeTimeZones." "Install TimeZone constants." SimpleTimeZones := Dictionary new. "Universal Time" SimpleTimeZones at: 'UT' put: 0. SimpleTimeZones at: 'GMT' put: 0. "For North America." SimpleTimeZones at: 'EST' put: -5. SimpleTimeZones at: 'EDT' put: -4. SimpleTimeZones at: 'CST' put: -6. SimpleTimeZones at: 'CDT' put: -5. SimpleTimeZones at: 'MST' put: -7. SimpleTimeZones at: 'MDT' put: -6. SimpleTimeZones at: 'PST' put: -8. SimpleTimeZones at: 'PDT' put: -7. "For Europe." SimpleTimeZones at: 'BST' put: 0. SimpleTimeZones at: 'WET' put: 0. SimpleTimeZones at: 'MET' put: 1. SimpleTimeZones at: 'EET' put: 2. "For Japan." SimpleTimeZones at: 'JST' put: 9 ] RFC822Scanner class >> normalizeDateAndTimeString: aString [ "RFC822 formats" "RFC822Scanner normalizeDateAndTimeString: '6 Dec 88 10:16:08 +0900 (Tuesday)'." "RFC822Scanner normalizeDateAndTimeString: 'Tue, 18 Apr 89 23:29:47 +0900'." "RFC822Scanner normalizeDateAndTimeString: 'Tue, 18 Apr 89 23:29:47 0900'." "RFC822Scanner normalizeDateAndTimeString: 'Tue, 23 May 89 13:52:12 JST'." "RFC822Scanner normalizeDateAndTimeString: '2-Nov-86 10:43:42 PST'." "Other formats" "RFC822Scanner normalizeDateAndTimeString: 'Jul 10 11:06:40 1995'." "RFC822Scanner normalizeDateAndTimeString: 'Jul 10 11:06:40 JST 1995'." "RFC822Scanner normalizeDateAndTimeString: 'Mon Jul 10 11:06:40 1995'." "RFC822Scanner normalizeDateAndTimeString: 'Mon Jul 10 11:06:40 JST 1995'." | head tail read str1 str2 write | aString size < 6 ifTrue: [^aString]. head := aString copyFrom: 1 to: aString size - 5. (head indexOf: $,) > 0 ifTrue: [^aString]. tail := aString copyFrom: aString size - 4 to: aString size. read := tail readStream. (read next = Character space and: [read next isDigit and: [read next isDigit and: [read next isDigit and: [read next isDigit]]]]) ifFalse: [^aString]. read := head readStream. str1 := read upTo: Character space. str2 := read upTo: Character space. (str1 isEmpty or: [str2 isEmpty]) ifTrue: [^aString]. str2 first isDigit ifFalse: [str1 := str2. str2 := read upTo: Character space. (str2 isEmpty or: [str2 first isDigit not]) ifTrue: [^aString]]. read atEnd ifTrue: [^aString]. write := WriteStream on: (String new: 32). write nextPutAll: str2; nextPutAll: str1; nextPutAll: (tail copyFrom: 4 to: 5); space; nextPutAll: read. ^write contents ] RFC822Scanner class >> readDateFrom: aStream [ "date = 1*2DIGIT month 2DIGIT month = 'Jan' / 'Feb' / 'Mar' / 'Apr' / 'May' / 'Jun' / 'Jul' / 'Aug' / 'Sep' / 'Oct' / 'Nov' / 'Dec'" "RFC822Scanner readDateFrom: '01 Jan 95' readStream." "RFC822Scanner readDateFrom: '1 Jan 95' readStream." "RFC822Scanner readDateFrom: '23 Jan 95' readStream." "RFC822Scanner readDateFrom: '23-Jan-95' readStream." "RFC822Scanner readDateFrom: 'Jan 23 95' readStream." "RFC822Scanner readDateFrom: 'Jan 23 1995' readStream." ^Date readFrom: aStream ] RFC822Scanner class >> readRFC822DateAndTimeFrom: aStream [ "date-time = [ day ',' ] date time day = 'Mon' / 'Tue' / 'Wed' / 'Thu' / 'Fri' / 'Sat' / 'Sun'" "RFC822Scanner readRFC822DateAndTimeFrom: '6 Dec 88 10:16:08 +0900 (Tuesday)' readStream." "RFC822Scanner readRFC822DateAndTimeFrom: '12 Dec 88 10:16:08 +0900 (Tuesday)' readStream." "RFC822Scanner readRFC822DateAndTimeFrom: 'Fri, 31 Mar 89 09:13:20 +0900' readStream." "RFC822Scanner readRFC822DateAndTimeFrom: 'Tue, 18 Apr 89 23:29:47 +0900' readStream." "RFC822Scanner readRFC822DateAndTimeFrom: 'Tue, 23 May 89 13:52:12 JST' readStream." "RFC822Scanner readRFC822DateAndTimeFrom: 'Thu, 1 Dec 88 17:13:27 jst' readStream." "RFC822Scanner readRFC822DateAndTimeFrom: '2-Nov-86 10:43:42 PST' readStream." "RFC822Scanner readRFC822DateAndTimeFrom: '(6 December 1988 10:16:08 am )' readStream." "RFC822Scanner readRFC822DateAndTimeFrom: '(12 December 1988 10:16:08 am )' readStream." | char date time | [aStream atEnd or: [char := aStream peek. char isDigit]] whileFalse: [aStream next]. aStream atEnd ifTrue: [^DateTime utcDateAndTimeNow]. date := self readDateFrom: aStream. aStream skipSeparators. time := self readTimeFrom: aStream. ^Array with: date with: time ] RFC822Scanner class >> readTimeFrom: aStream [ "time = hour zone hour = 2DIGIT ':' 2DIGIT [':' 2DIGIT] zone = 'UT' / 'GMT' / 'EST' / 'EDT' / 'CST' / 'CDT' / 'MST' / 'MDT' / 'PST' / 'PDT' / 1ALPHA / ( ('+' / '-') 4DIGIT )" "RFC822Scanner readTimeFrom: '12:16:08 GMT' readStream." "RFC822Scanner readTimeFrom: '12:16:08 XXX' readStream." "RFC822Scanner readTimeFrom: '07:16:08 EST' readStream." "RFC822Scanner readTimeFrom: '07:16:08 -0500' readStream." "RFC822Scanner readTimeFrom: '21:16:08 JST' readStream." "RFC822Scanner readTimeFrom: '21:16:08 jst' readStream." "RFC822Scanner readTimeFrom: '21:16:08 +0900' readStream." "RFC822Scanner readTimeFrom: '21:16:08 0900' readStream." "RFC822Scanner readTimeFrom: '12:16:08 pm' readStream." "Smalltalk time" "RFC822Scanner readTimeFrom: '12:16' readStream." "No timezone" "RFC822Scanner readTimeFrom: '12:16:08' readStream." "No timezone" | hour minute second write char timezone | hour := Integer readFrom: aStream. minute := 0. second := 0. (aStream peekFor: $:) ifTrue: [minute := Integer readFrom: aStream. (aStream peekFor: $:) ifTrue: [second := Integer readFrom: aStream]]. aStream skipSeparators. write := WriteStream on: (String new: 8). [aStream atEnd or: [char := aStream next. char isSeparator]] whileFalse: [write nextPut: char]. timezone := write contents asUppercase. (SimpleTimeZones at: timezone ifAbsent: [nil]) notNil ifTrue: [hour := hour - (SimpleTimeZones at: timezone)] ifFalse: [('+####' match: timezone) ifTrue: [hour := hour - (timezone copyFrom: 2 to: 3) asNumber. minute := minute - (timezone copyFrom: 4 to: 5) asNumber] ifFalse: [('-####' match: timezone) ifTrue: [hour := hour + (timezone copyFrom: 2 to: 3) asNumber. minute := minute + (timezone copyFrom: 4 to: 5) asNumber] ifFalse: ['AM' = timezone ifTrue: ["Smalltalk time" hour = 12 ifTrue: [hour := 0]] ifFalse: ['PM' = timezone ifTrue: ["Smalltalk time" hour = 12 ifTrue: [hour := 0]. hour := hour + 12] ifFalse: ["Using default time zone" hour := hour - (self defaultTimeZoneDifference // 3600)]]]]]. ^Time fromSeconds: 60 * (60 * hour + minute) + second ] RFC822Scanner class >> defaultTokenType [ ^#word ] RFC822Scanner class >> nextPutComment: comment on: stream [ comment notNil ifTrue: [stream nextPut: $(. comment do: [:char | (self isCommentChar: char) ifFalse: [stream nextPut: $\]. stream nextPut: char]. stream nextPut: $)] ] RFC822Scanner class >> printDomain: domainx on: stream [ "Domainx is an array of domain segments" domainx notNil ifTrue: [domainx do: [:word | self printWord: word on: stream] separatedBy: [stream nextPut: $.]] ] RFC822Scanner class >> printPhrase: phrase on: stream [ phrase do: [:word | stream nextPutAll: word] separatedBy: [stream space] ] RFC822Scanner class >> printWord: str on: stream [ "Print word as either atom or quoted text" (self shouldBeQuoted: str) ifTrue: [stream nextPut: $"; nextPutAll: str; nextPut: $"] ifFalse: [stream nextPutAll: str] ] RFC822Scanner class >> isAtomChar: char [ ^((self classificationTable at: char asInteger + 1) bitAnd: AtomMask) ~= 0 ] RFC822Scanner class >> isCommentChar: char [ ^((self classificationTable at: char asInteger + 1) bitAnd: CommentMask) ~= 0 ] RFC822Scanner class >> shouldBeQuoted: string [ ^(string detect: [:char | (self isAtomChar: char) not] ifNone: [nil]) notNil ] phraseAsString: phrase [ | stream | stream := (String new: 40) writeStream. self class printPhrase: phrase on: stream. ^stream contents ] scanAtom [ "atom = 1*" token := self scanTokenMask: AtomMask. tokenType := #atom. ^token ] scanComment [ "collect comment" | output | output := saveComments ifTrue: [(String new: 40) writeStream] ifFalse: [nil]. self scanCommentOn: output. output notNil ifTrue: [currentComment isNil ifTrue: [currentComment := OrderedCollection with: output contents] ifFalse: [currentComment add: output contents]]. ^token ] scanDomainText [ "dtext = , <]>, <\> & CR, & including linear-white-space> ; => may be folded" token := self scanToken: [self scanQuotedChar; matchCharacterType: DomainTextMask] delimitedBy: '[]' notify: 'Malformed domain literal'. tokenType := #domainText. ^token ] atEndOfLine [ self peek. ^(self classificationMaskFor: lookahead) anyMask: CRLFMask ] skipEndOfLine [ hereChar == Character nl ifFalse: [(source peekFor: Character nl) ifFalse: [^false] ifTrue: [self sourceTrailNextPut: Character nl]]. ^true ] scanEndOfLine [ "Note: this will work only for RFC822 but not for HTTP. Needs more design work" "Called after #step, so no need to peek to set the CRLFMask." (self matchCharacterType: CRLFMask) ifFalse: [^false]. self skipEndOfLine ifFalse: [^self]. self shouldFoldLine ifTrue: [self hereChar: Character space. ^self]. "Otherwise we have an end-of-line condition -- set appropriate masks" classificationMask := (classificationMask bitClear: WhiteSpaceMask) bitOr: EndOfLineMask ] scanFieldName [ "RFC822, p.9: field-name = 1*" ^self scanTokenMask: HeaderNameMask ] scanPhrase [ "RFC822: phrase = 1*word ; Sequence of words. At the end of scan the scanner has read the first token after phrase" ^self tokenizeWhile: [#(#quotedText #atom) includes: tokenType] ] scanQuotedChar [ "Scan possible quoted character. If the current char is $\, read in next character and make it a quoted string character" ^hereChar == QuotedPairChar ifTrue: [self step. classificationMask := QuotedPairMask. true] ifFalse: [false] ] scanQuotedText [ "quoted-string = <" "> *(qtext/quoted-pair) <" ">; Regular qtext or quoted chars. qtext = , <\> & CR, and including linear-white-space> ; => may be folded" "We are positioned at the first double quote character" token := self scanToken: [self scanQuotedChar; matchCharacterType: QuotedTextMask] delimitedBy: '""' notify: 'Unmatched quoted text'. tokenType := #quotedText. ^token ] scanText [ "RFC822: text = (self matchCharacterType: EndOfLineMask) ifTrue: [^String new]. ^self scanUntil: [self matchCharacterType: CRLFMask] ] scanWord [ self nextToken. (#(#quotedText #atom) includes: tokenType) ifFalse: [self error: 'Expecting word']. ^token ] skipWhiteSpace [ "It is inefficient because intermediate stream is created. Perhaps refactoring scanWhile: can help" self scanWhile: [hereChar == $( ifTrue: [self stepBack; scanComment. true] ifFalse: [self matchCharacterType: WhiteSpaceMask]] ] nextRFC822Token [ | char | self skipWhiteSpace. char := self peek. char isNil ifTrue: ["end of input" tokenType := #doIt. ^token := nil]. char == $( ifTrue: [^self scanComment; nextToken]. char == $" ifTrue: [^self scanQuotedText]. (self specials includes: char) ifTrue: [tokenType := #special. "Special character. Make it token value and set token type" ^token := self next]. (self matchCharacterType: AtomMask) ifTrue: [^self scanAtom]. tokenType := #doIt. token := char. ^token ] scanCommentOn: streamOrNil [ "scan comment copying on specified stream" self step ~~ $( ifTrue: [self error: 'Unmatched comment']. "Should never be the case" token := self scanUntil: [((self scanQuotedChar; matchCharacterType: CommentMask) ifTrue: [streamOrNil notNil ifTrue: [streamOrNil nextPut: hereChar]. true] ifFalse: [hereChar == $( ifTrue: [streamOrNil notNil ifTrue: [streamOrNil space]. self stepBack; scanCommentOn: streamOrNil. streamOrNil notNil ifTrue: [streamOrNil space]. true] ifFalse: [false]]) not]. hereChar ~~ $) ifTrue: [self error: 'Unmatched comment']. ^token ] assertNoLookahead [ "Fail if the parser has lookahead." lookahead isNil ifFalse: [ self error: 'unexpected parsing state' ] ] shouldFoldLine [ "Answers true if next line is to be folded in, that is, if CRLF is followed by at least one white space" | char | self atEnd ifTrue: [^false]. char := source peek. ^((self classificationMaskFor: char) anyMask: WhiteSpaceMask) ifFalse: [self resetToken; peek. false] ifTrue: [self sourceTrailNextPut: source next. true] ] step [ super step. self scanEndOfLine. ^hereChar ] isRFC822Scanner [ ^true ] nextToken [ ^self nextRFC822Token ] specials [ "This method is provided to encapsulate lexical differences between RFC822 on one side, and MIME, HTTP on the other side. MIME definiton of 'tspecials' is the same as the RFC 822 definition of ''specials' with the addition of the three characters , , and <=>, and the removal of <.>. To present uniform tokenization interface, this method is overridden in Mime scanner" ^self class specials ] ] ] Namespace current: NetClients.MIME [ StructuredHeaderField subclass: ScalarField [ | value | Parsed value of the item '> ScalarField class >> fieldNames [ ^#('message-id' 'content-id' 'content-transfer-encoding' 'transfer-encoding' 'content-encoding') ] value [ ^value ] value: anObject [ value := anObject ] parse: rfc822Stream [ self value: (self tokenizedValueFrom: rfc822Stream) ] ] ] Namespace current: NetClients.MIME [ RFC822Scanner subclass: MimeScanner [ MimeScanner class >> decodeBase64From: startIndex to: endIndex in: aString [ "Decode aString from startIndex to endIndex in base64." | codeChars decoder index nl endChars end padding data sz i outSize | codeChars := 'ABCDEFGHIJKLMNOPQRSTUVWXYZabcdefghijklmnopqrstuvwxyz0123456789+/'. decoder := (0 to: 255) collect: [:n | (codeChars indexOf: (n + 1) asCharacter) - 1]. decoder replaceAll: -1 with: 0. index := startIndex. nl := Character nl. "There is padding at the end of a base64 message if the content is not a multiple of 3 bytes in length. The padding is either two ='s to pad-out a trailing byte, 1 = to pad out a trailing pair of bytes, or no padding. Here we count the padding. After processing the message we cut-back by the amount of padding." end := endIndex min: (sz := aString size). endChars := codeChars , (String with: $=). [(endChars includes: (aString at: end)) and: [end = endIndex or: [(aString at: end + 1) = nl]]] whileFalse: [end := end - 1]. padding := 0. [(aString at: end - padding) == $=] whileTrue: [padding := padding + 1]. outSize := (end - startIndex + 1) * 3 // 4 - padding. data := String new: outSize. i := 1. [index <= end] whileTrue: [| triple | triple := ((decoder at: (aString at: index) asInteger) bitShift: 18) + ((decoder at: (aString at: index + 1) asInteger) bitShift: 12) + ((decoder at: (aString at: index + 2) asInteger) bitShift: 6) + (decoder at: (aString at: index + 3) asInteger). padding := outSize - i. data at: i put: (Character value: (triple digitAt: 3)). padding > 0 ifTrue: [ data at: i + 1 put: (Character value: (triple digitAt: 2))]. padding > 1 ifTrue: [ data at: i + 2 put: (Character value: (triple digitAt: 1))]. i := i + 3. index := index + 4. [(index > sz or: [(aString at: index) = nl]) and: [index <= end]] whileTrue: [index := index + 1]]. ^data ] MimeScanner class >> decodeQuotedPrintableFrom: startIndex to: endIndex in: aString [ "Decode aString from startIndex to endIndex in quoted-printable." | input output char n1 n2 | input := ReadStream on: aString from: startIndex to: endIndex. output := (String new: endIndex - startIndex) writeStream. [input atEnd] whileFalse: [char := input next. $= == char ifTrue: [('0123456789ABCDEF' includes: (n1 := input next)) ifTrue: [n2 := input next. output nextPut: ((n1 digitValue bitShift: 4) + n2 digitValue) asCharacter]] ifFalse: [output nextPut: char]]. ^output contents ] MimeScanner class >> decodeUUEncodedFrom: startIndex to: farEndIndex in: aString [ "decode aString from startIndex to farEndIndex as uuencode-encoded" | endIndex i nl space output data | endIndex := farEndIndex - 2. [endIndex <= startIndex or: [(aString at: endIndex + 1) = $e and: [(aString at: endIndex + 2) = $n and: [(aString at: endIndex + 3) = $d]]]] whileFalse: [endIndex := endIndex - 1]. i := (aString findString: 'begin' startingAt: startIndex ignoreCase: true useWildcards: false) first. i = 0 ifTrue: [i := startIndex]. nl := Character nl. space := Character space asInteger. output := (data := String new: (endIndex - startIndex) * 3 // 4) writeStream. [[i < endIndex and: [(aString at: i) ~= nl]] whileTrue: [i := i + 1]. i < endIndex] whileTrue: [| count | count := (aString at: (i := i + 1)) asInteger - space bitAnd: 63. i := i + 1. count = 0 ifTrue: [i := endIndex] ifFalse: [[count > 0] whileTrue: [| m n o p | m := (aString at: i) asInteger - space bitAnd: 63. n := (aString at: i + 1) asInteger - space bitAnd: 63. o := (aString at: i + 2) asInteger - space bitAnd: 63. p := (aString at: i + 3) asInteger - space bitAnd: 63. count >= 1 ifTrue: [output nextPut: (Character value: (m bitShift: 2) + (n bitShift: -4)). count >= 2 ifTrue: [output nextPut: (Character value: ((n bitShift: 4) + (o bitShift: -2) bitAnd: 255)). count >= 3 ifTrue: [output nextPut: (Character value: ((o bitShift: 6) + p bitAnd: 255))]]]. i := i + 4. count := count - 3]]]. ^data copyFrom: 1 to: output position ] scanText [ "Parse text as defined in RFC822 grammar, then apply the rules of RFC2047 for encoded words in Text fields. An encoded word inside text field may appear immediately following a white space character" | text | text := super scanText. ^MimeEncodedWordCoDec decodeText: text ] scanToBoundary: boundary [ "Scan for specified boundary (RFC2046, p5.1). Answer two-element array. First element is the scanned text from current position up to the beginning of the boundary. Second element is either #next or #last. #next means the boundary found is not the last one. #last means the boundary is the closing boundary for the multi-part body (that is, it looks like '----)" | pattern string kind | pattern := (String with: Character nl) , '--' , boundary. string := self upToAll: pattern. kind := ((self peekFor: $-) and: [self peekFor: $-]) ifTrue: [#last] ifFalse: [#next]. self upTo: Character nl. ^Array with: string with: kind ] scanToken [ "MIME and HTTP: token = 1*. That is, 'token' is analogous to RFC822 'atom' except set of Mime's set of tspecials characters includes three more characters as compared to set of 'specials' in RFC822" token := self scanTokenMask: TokenMask. tokenType := #token. ^token ] printPhrase: phrase on: stream [ MimeEncodedWordCoDec decodePhrase: phrase printOn: stream ] decodeCommentString: commentString [ ^MimeEncodedWordCoDec decodeComment: commentString ] nextMimeToken [ | char | self skipWhiteSpace. char := self peek. char isNil ifTrue: ["end of input" tokenType := #doIt. ^token := nil]. char == $( ifTrue: [^self scanComment; nextToken]. char == $" ifTrue: [^self scanQuotedText]. (self specials includes: char) ifTrue: [tokenType := #special. "Special character. Make it token value and set token type" ^token := self next]. (self matchCharacterType: TokenMask) ifTrue: [^self scanToken]. tokenType := #doIt. token := char. ^token ] scanCommentOn: streamOrNil [ "scan comment copying on specified stream. Look for MIME 'encoded words' (RFC2047) and decoded them if identified" token := super scanCommentOn: streamOrNil. ^self decodeCommentString: token ] nextToken [ ^self nextMimeToken ] specials [ "This method is provided to encapsulate lexical differences between RFC822 on one side, and MIME, HTTP on the other side. MIME definiton of 'tspecials' is the same as the RFC 822 definition of ''specials' with the addition of the three characters , , and <=>, and the removal of <.>. To present uniform tokenization interface, this method is overridden in Mime scanner" ^self class tspecials ] ] ] Namespace current: NetClients.MIME [ RFC822Scanner subclass: NetworkAddressParser [ | descriptor | comment '> NetworkAddressParser class >> parse: string [ ^self new parse: string ] NetworkAddressParser class >> addressesFrom: stream [ "self addressesFrom: 'kyasu@crl.fujixerox.co.jp' readStream." "self addressesFrom: 'Kazuki Yasumatsu ' readStream." "self addressesFrom: 'kyasu@crl.fujixerox.co.jp (Kazuki Yasumatsu)' readStream." "self addressesFrom: ' kyasu1, kyasu2, Kazuki Yasumatsu , kyasu4 (Kazuki Yasumatsu)' readStream." "self addressesFrom: ' foo bar, kyasu1, , Kazuki Yasumatsu ( (foo bar), bar)' readStream." ^(self on: stream) parseAddressesSeparatedBy: $, ] NetworkAddressParser class >> addressFrom: stream [ "self addressFrom: 'kyasu@crl.fujixerox.co.jp'." "self addressFrom: 'Kazuki Yasumatsu '." "self addressFrom: 'kyasu@crl.fujixerox.co.jp (Kazuki Yasumatsu)'." ^(self on: stream) parseAddress ] descriptor [ ^descriptor ] descriptor: aValue [ descriptor := aValue ] initialize [ super initialize. descriptor := self newAddressDescriptor ] completeScanOfAddressSpecWith: partial [ "addr-spec = local-part <@> domain ; global address local-part = word *(<.> word) ; uninterpreted, case-preserved First local-part token was already scanned; we are now scanning *(<.> word) group and domain part. Partial is an array of tokens already read" | stream pos | stream := partial readWriteStream. stream setToEnd. self descriptor localPart: (self scanLocalAddressPartTo: stream). pos := self position. self nextRFC822Token == $@ ifTrue: [self descriptor domain: self scanDomain] ifFalse: [self position: pos] ] newAddressDescriptor [ ^NetworkAddressDescriptor new ] parseGroupSpecWith: phrase [ "group = phrase <:> [#mailbox] <;>" | group mailboxes phrasex comment stream | mailboxes := self tokenizeList: [self parseAddress] separatedBy: [token == $,]. self nextRFC822Token == $; ifFalse: [^self notify: 'Group descriptor should be terminated by <:>']. group := MailGroupDescriptor new. "If phrase is non-empty, an alias was specified" phrasex := phrase isEmpty ifTrue: [nil] ifFalse: [self phraseAsString: phrase]. comment := currentComment isNil ifTrue: [nil] ifFalse: [stream := (String new: 40) writeStream. currentComment do: [:part | stream nextPutAll: part] separatedBy: [stream space]. stream contents]. group alias: phrasex; addresses: mailboxes; comment: comment. ^group ] parseMailboxSpecWith: phrasex [ "address = mailbox ; one addressee / group ; named list group = phrase <:> [#mailbox] <;> mailbox = addr-spec ; simple address / phrase route-addr ; name & addr-spec route-addr = <<> [route] addr-spec <>> route = 1#(<@> domain) <:> ; path-relative" | phrase tok local stream comment | phrase := phrasex. tok := self nextRFC822Token. self descriptor: self newAddressDescriptor. "Variations of mailbox spec" tok = $< ifTrue: ["Phil Campbell" self stepBack; scanRouteAndAddress] ifFalse: [('.@' includes: tok) ifTrue: ["These ones should have a non-empty local part to the left of delimiter" phrase isEmpty ifTrue: [self error: 'Invalid network address']. local := Array with: phrase last. phrase := phrase copyFrom: 1 to: phrase size - 1. "Extract the part we already scanned" tok = $. ifTrue: ["phil.campbell.wise@acme.com>" self stepBack; completeScanOfAddressSpecWith: local]. tok = $@ ifTrue: ["philc@acme.com>" self descriptor localPart: local. self descriptor domain: self scanDomain]] ifFalse: [self stepBack]]. "If phrase is non-empty, an alias was specified" phrase := phrase isEmpty ifTrue: [phrase := nil] ifFalse: [self phraseAsString: phrase]. self descriptor alias: phrase. comment := currentComment isNil ifTrue: [nil] ifFalse: [stream := (String new: 40) writeStream. currentComment do: [:part | stream nextPutAll: part] separatedBy: [stream space]. stream contents]. self descriptor comment: comment. ^self descriptor ] scanLocalAddressPartTo: stream [ "local-part = word *(<.> word) ; uninterpreted, case-preserved Part of local part may have been scanned already, it's in localPart of the descriptor" self tokenizeWhile: [token == $.] do: [stream nextPut: self scanWord]. ^stream contents ] tryScanSubdomain [ self nextRFC822Token. tokenType = #atom ifTrue: [^true]. token = $[ ifTrue: [self stepBack; scanDomainText. ^true]. ^false ] addressesFrom: stream [ ^(self on: stream) parseAddressesSeparatedBy: $, ] parse: aString [ ^self on: aString readStream; parseAddress ] parseAddress [ "address = mailbox ; one addressee / group ; named list group = phrase <:> [#mailbox] <;> mailbox = addr-spec ; simple address / phrase route-addr ; name & addr-spec route-addr = <<> [route] addr-spec <>> route = 1#(<@> domain) <:> ; path-relative" | phrase | phrase := self scanPhrase. ^self nextRFC822Token = $: ifTrue: [self parseGroupSpecWith: phrase] ifFalse: [self stepBack; parseMailboxSpecWith: phrase] ] parseAddressesSeparatedBy: separatorChar [ | addresses | addresses := self tokenizeList: [self parseAddress] separatedBy: [token == separatorChar]. ^addresses ] scanDomain [ "domain = sub-domain *(<.> sub-domain)" "Answers an array of domain seqments, from least significant to most significant" ^self tokenizeList: [self nextRFC822Token. tokenType = #atom ifTrue: [token] ifFalse: [token = $[ ifTrue: [self stepBack; scanDomainText] ifFalse: [^self notify: 'Invalid domain specification']]] separatedBy: [token == $.] ] scanLocalAddress [ "local-part = word *(<.> word) ; uninterpreted, case-preserved" ^self tokenizeList: [self nextRFC822Token. (#(#quotedText #atom) includes: tokenType) ifFalse: [^self notify: 'Local part can only include words']. token] separatedBy: [token == $.] ] scanRoute [ "route = 1#(<@> domain) <:> ; path-relative" | stream | stream := (Array new: 2) writeStream. [self nextRFC822Token == $@] whileTrue: [stream nextPut: self scanDomain. self nextToken = $: ifFalse: [self error: 'Invalid route spec']]. stream size = 0 ifTrue: [self error: 'Invalid route spec']. ^stream contents ] scanRouteAndAddress [ "route-addr = <<> [route] addr-spec <>>" self mustMatch: $< notify: 'Invalid route address spec'. self nextRFC822Token == $@ ifTrue: [self stepBack. self descriptor route: self scanRoute]. self completeScanOfAddressSpecWith: (Array with: token). self mustMatch: $> notify: 'Invalid route address spec' ] ] ] Namespace current: NetClients.MIME [ StructuredHeaderField subclass: ContentTypeField [ | type subtype | Top level media type subtype Media subtype '> ContentTypeField class >> default [ ^self fromLine: 'content-type: text/plain; charset=us-ascii' ] ContentTypeField class >> defaultCharset [ ^'us-ascii' ] ContentTypeField class >> defaultContentType [ ^'text/plain' ] ContentTypeField class >> urlEncoded [ ^self fromLine: 'content-type: application/x-www-form-urlencoded; charset=us-ascii' ] ContentTypeField class >> fieldNames [ ^#('content-type') ] boundary [ ^self parameterAt: 'boundary' ] boundary: aString [ ^self parameterAt: 'boundary' put: aString ] charset [ ^(self parameterAt: 'charset' ifAbsent: [^self class defaultCharset]) asLowercase ] contentType [ ^type , '/' , subtype ] subtype [ ^subtype ] subtype: aString [ subtype := aString ] type [ ^type ] type: aString [ type := aString ] multipartType [ ^'multipart' ] parse: rfc822Stream [ "RFC2045: content := <:> type subtype *(<;> parameter)" type := rfc822Stream nextToken asLowercase. rfc822Stream mustMatch: $/ notify: 'Content type must be specified as type/subtype'. subtype := rfc822Stream nextToken asLowercase. self readParametersFrom: rfc822Stream ] printStructureOn: aStream [ aStream nextPutAll: self contentType. self printParametersOn: aStream ] isMultipart [ ^type = 'multipart' ] ] ] Namespace current: NetClients.MIME [ ScalarField subclass: VersionField [ | majorVersion minorVersion | <.>. Value of this field is its version strung; methods are provided to read (or construct version from) its constituent parts Instance Variables: majorVersion comment minorVersion comment '> VersionField class >> fieldNames [ ^#('mime-version' 'http-version') ] majorVersion [ ^majorVersion ] majorVersion: number [ majorVersion := number ] minorVersion [ ^minorVersion ] minorVersion: number [ minorVersion := number ] value [ ^self version ] value: string [ self version: string ] version [ ^majorVersion , '.' , minorVersion ] version: string [ | arr | arr := string subStrings: $.. arr size < 2 ifTrue: [self notify: 'Version should be specified as .']. self majorVersion: arr first. self minorVersion: arr last ] ] ] Namespace current: NetClients.MIME [ ScalarField subclass: SingleMailboxField [ SingleMailboxField class >> fieldNames [ ^#('sender' 'resent-sender') ] address [ ^self value ] address: address [ self value: address ] addresses [ ^{self address} ] addresses: aCollection [ aCollection size = 1 ifFalse: [self error: 'can only contain a single address']. aCollection do: [:theOnlyAddress | self value: theOnlyAddress] ] parse: rfc822Stream [ "HeaderField fromLine: 'Sender : Phil Campbell (The great) '" self value: (NetworkAddressDescriptor addressFrom: rfc822Stream) ] ] ] Namespace current: NetClients.MIME [ ScalarField subclass: MailboxListField [ MailboxListField class >> fieldNames [ ^#('from' 'to' 'reply-to' 'cc' 'bcc' 'resent-reply-to' 'resent-from' 'resent-to' 'resent-cc' 'resent-bcc') ] addAddress: address [ ^self addAddresses: (Array with: address) ] addAddresses: aCollection [ self value addAll: aCollection ] address [ self value first ] address: address [ self value isEmpty ifTrue: [self value: (OrderedCollection new: 1)]. self value at: 1 put: address ] addresses [ ^self value ] addresses: aCollection [ self value: aCollection ] initialize [ super initialize. value := OrderedCollection new ] parse: rfc822Stream [ "HeaderField fromLine: 'To : George Jones , Al.Neuman@MAD.Publisher'" self value: (NetworkAddressDescriptor addressesFrom: rfc822Stream) ] printValueOn: aStream [ | val | (val := self value) notNil ifTrue: [val do: [:each | each printOn: aStream] separatedBy: [aStream nextPutAll: ', '; nl; tab]] ] ] ] Namespace current: NetClients.MIME [ SimpleScanner initialize. RFC822Scanner initialize ] smalltalk-3.2.5/packages/net/HTTP.st0000644000175000017500000003202312123404352014115 00000000000000"====================================================================== | | HTTP protocol support | | ======================================================================" "====================================================================== | | Based on code copyright (c) Kazuki Yasumatsu, and in the public domain | Copyright (c) 2002, 2005 Free Software Foundation, Inc. | Adapted by Paolo Bonzini. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" Namespace current: NetClients.HTTP [ NetClient subclass: HTTPClient [ HTTPClient class >> defaultPortNumber [ ^80 ] HTTPClient class >> defaultSSLPortNumber [ ^443 ] HTTPClient class >> exampleURL: url host: host port: port [ "self exampleURL: 'http://www.gnu.org' host: 'www.gnu.org' port: 80." "self exampleURL: 'http://www.gnu.org' host: 'localhost' port: 8080." | body headers client | client := HTTPClient connectToHost: host port: port. [headers := client get: url requestHeaders: #() into: (body := WriteStream on: String new)] ensure: [client close]. ^headers -> body contents ] get: urlString requestHeaders: requestHeaders into: aStream [ ^self clientPI get: urlString requestHeaders: requestHeaders into: aStream ] getBinary: urlString [ | stream | stream := WriteStream on: (String new: 1024). self get: urlString requestHeaders: Array new into: stream. ^stream contents ] getText: urlString [ ^self clientPI decode: (self getBinary: urlString) ] head: urlString requestHeaders: requestHeaders [ ^self clientPI head: urlString requestHeaders: requestHeaders ] head: urlString requestHeaders: requestHeaders into: aStream [ "This method is deprecated in favor of #head:requestHeaders:, because the last parameter is effectively unused." ^self clientPI head: urlString requestHeaders: requestHeaders ] post: urlString type: type data: data binary: binary requestHeaders: requestHeaders into: aStream [ ^self clientPI post: urlString type: type data: data binary: binary requestHeaders: requestHeaders into: aStream ] protocolInterpreter [ ^HTTPProtocolInterpreter ] ] ] Namespace current: NetClients.HTTP [ NetProtocolInterpreter subclass: HTTPProtocolInterpreter [ HTTPProtocolInterpreter class >> defaultResponseClass [ ^HTTPResponse ] get: urlString requestHeaders: requestHeaders into: aStream [ self connectIfClosed. self nextPutAll: 'GET ' , urlString , ' HTTP/1.1'; cr. self putRequestHeaders: requestHeaders. ^self readResponseInto: aStream ] readResponseStream: aResponseStream into: aStream length: aContentLength [ | remaining | remaining := aContentLength. [remaining = 0] whileFalse: [| data | data := aResponseStream next: (4096 min: remaining). remaining := remaining - data size. self reporter readByte: data size. aStream nextPutAll: data] ] readChunkedResponseStream: aResponseStream into: aStream [ "Happily, aResponseStream should be buffered." | cr lf chunkSize chunkExt i remaining s | cr := Character cr. lf := Character lf. [aResponseStream atEnd ifTrue: [^self]. (aResponseStream peek asUppercase isDigit: 16) ifFalse: [self error: 'Expecting chunk-size, but found ' , aResponseStream peek printString , '.']. chunkSize := Integer readFrom: aResponseStream radix: 16. "Technically, a chunk-extension should start with $;, but we'll ignore everything to the CRLF for simplicity (we don't understand any chunk extensions, so we have to ignore them)." [aResponseStream next = cr and: [aResponseStream next = lf]] whileFalse. chunkSize = 0] whileFalse: ["Possibly we should just read it all?" self readResponseStream: aResponseStream into: aStream length: chunkSize. (aResponseStream next = cr and: [aResponseStream next = lf]) ifFalse: [self error: 'Expected CRLF but found: ' , s printString "We could try to recover by reading to the next CRLF, I suppose..."]. chunkSize = 0]. aResponseStream peekFor: cr. aResponseStream peekFor: lf "There shouldn't be a trailer as we didn't say it was acceptable in the request." ] readResponseInto: aStream [ | response totalByte readStream | response := self getResponse. self checkResponse: response. totalByte := response fieldAt: 'Content-Length' ifAbsent: [nil]. totalByte notNil ifTrue: ["#asInteger strips 'Content-Length' from the front of the string." totalByte := totalByte value trimSeparators asInteger. self reporter totalByte: totalByte]. self reporter startTransfer. readStream := self connectionStream stream. response preReadBytes isEmpty ifFalse: [self reporter readByte: response preReadBytes size. readStream := response preReadBytes readStream , readStream]. totalByte notNil ifTrue: [self readResponseStream: readStream into: aStream length: totalByte] ifFalse: [| te s | self readChunkedResponseStream: readStream into: aStream. "Remove 'chunked' from transfer-encoding header" te := response fieldAt: 'transfer-encoding' ifAbsent: [nil]. te notNil ifTrue: [s := te value. (s indexOf: 'chunked' matchCase: false startingAt: 1) ifNotNil: [:i | te value: (s copyFrom: 1 to: i first - 1) , (s copyFrom: i last + 1)]]]. self reporter endTransfer. response keepAlive ifFalse: [self close]. ^response ] head: urlString requestHeaders: requestHeaders [ | response | self connectIfClosed. self reporter startTransfer. self nextPutAll: 'HEAD ' , urlString , ' HTTP/1.1'; cr. self putRequestHeaders: requestHeaders. response := self getResponse. self checkResponse: response. self reporter endTransfer. response keepAlive ifFalse: [self close]. ^response ] putRequestHeaders: requestHeaders [ | host | host := false. requestHeaders do: [:header | ('Host:*' match: header) ifTrue: [host := true]. self nextPutAll: header; cr]. "The Host header is necessary to support virtual hosts" host ifFalse: [self nextPutAll: 'Host: ' , self client hostName; cr]. self cr ] post: urlString type: type data: data binary: binary requestHeaders: requestHeaders into: aStream [ | readStream response totalByte | self connectIfClosed. self nextPutAll: 'POST ' , urlString , ' HTTP/1.1'; cr. self nextPutAll: 'Content-Type: ' , type; cr. self nextPutAll: 'Content-Length: ' , data size printString; cr. self putRequestHeaders: requestHeaders. binary ifTrue: [(self connectionStream stream) nextPutAll: data; flush] ifFalse: [self nextPutAll: data]. ^self readResponseInto: aStream ] checkResponse: response ifError: errorBlock [ | status | status := response status. "Successful" status = 200 ifTrue: ["OK" ^self]. status = 201 ifTrue: ["Created" ^self]. status = 202 ifTrue: ["Accepted" ^self]. status = 203 ifTrue: ["Provisional Information" ^self]. status = 204 ifTrue: ["No Response" ^self]. status = 205 ifTrue: ["Deleted" ^self]. status = 206 ifTrue: ["Modified" ^self]. "Redirection" (status = 301 or: ["Moved Permanently" status = 302 "Moved Temporarily"]) ifTrue: [^self redirectionNotify: response ifInvalid: errorBlock]. status = 303 ifTrue: ["Method" ^self]. status = 304 ifTrue: ["Not Modified" ^self]. "Client Error" status = 400 ifTrue: ["Bad Request" ^errorBlock value]. status = 401 ifTrue: ["Unauthorized" ^errorBlock value]. status = 402 ifTrue: ["Payment Required" ^errorBlock value]. status = 403 ifTrue: ["Forbidden" ^errorBlock value]. status = 404 ifTrue: ["Not Found" ^errorBlock value]. status = 405 ifTrue: ["Method Not Allowed" ^errorBlock value]. status = 406 ifTrue: ["None Acceptable" ^errorBlock value]. status = 407 ifTrue: ["Proxy Authent. Required" ^errorBlock value]. status = 408 ifTrue: ["Request Timeout" ^errorBlock value]. "Server Errors" status = 500 ifTrue: ["Internal Server Error" ^errorBlock value]. status = 501 ifTrue: ["Not Implemented" ^errorBlock value]. status = 502 ifTrue: ["Bad Gateway" ^errorBlock value]. status = 503 ifTrue: ["Service Unavailable" ^errorBlock value]. status = 504 ifTrue: ["Gateway Timeout" ^errorBlock value]. "Unknown status" ^errorBlock value ] redirectionNotify: aResponse ifInvalid: errorBlock [ | ex | ex := HTTPRedirection new. ex response: aResponse. ex location isNil ifTrue: [ ^errorBlock value ] ifFalse: [ ex tag: ex location. "backwards compatibility" ex signal ]. ] ] ] Namespace current: NetClients.HTTP [ NetResponse subclass: HTTPResponse [ | version messageHeader preReadBytes | fieldAt: key [ ^messageHeader fieldAt: key ] fieldAt: key ifAbsent: absentBlock [ ^messageHeader fieldAt: key ifAbsent: absentBlock ] keepAlive [ | connection | (self fieldAt: 'content-length' ifAbsent: [nil]) isNil ifTrue: [^false]. connection := self fieldAt: 'connection' ifAbsent: [nil]. connection := connection isNil ifTrue: [''] ifFalse: [connection value]. "For HTTP/1.0, the default is close and there is a de facto standard way to specify keep-alive connections" version < 'HTTP/1.1' ifTrue: [^'*keep-alive*' match: connection ignoreCase: true]. "For HTTP/1.1, the default is keep-alive" ^('*close*' match: connection ignoreCase: true) not ] messageHeader [ ^messageHeader ] preReadBytes [ ^preReadBytes isNil ifTrue: [#[]] ifFalse: [preReadBytes] ] parseResponse: aClient [ | messageHeaderParser | messageHeader := MIME.MimeEntity new. version := aClient nextAvailable: 8. ('HTTP/1.#' match: version) ifFalse: ["may be HTTP/0.9" preReadBytes := version. status := 200. statusMessage := 'OK'. version := 'HTTP/0.9'. ^self]. self parseStatusLine: aClient. messageHeaderParser := MIME.MimeEntity parser on: aClient connectionStream. messageHeader parseFieldsFrom: messageHeaderParser. messageHeaderParser assertNoLookahead. preReadBytes := #(). ] printOn: aStream [ self printStatusOn: aStream. aStream cr. messageHeader printOn: aStream ] printStatusOn: aStream [ aStream nextPutAll: 'HTTP/1.0 '. super printStatusOn: aStream ] parseStatusLine: aClient [ | stream | stream := aClient nextLine readStream. stream skipSeparators. status := Integer readFrom: stream. stream skipSeparators. statusMessage := stream upToEnd ] ] ] Namespace current: NetClients.HTTP [ ProtocolNotification subclass: HTTPRedirection [ | location | location [ location isNil ifFalse: [^location]. response isNil ifTrue: [^nil]. location := response fieldAt: 'Location' ifAbsent: [nil]. location isNil ifFalse: [location := location value]. ^location ] ] ] smalltalk-3.2.5/packages/net/SMTP.st0000644000175000017500000002411312123404352014122 00000000000000"====================================================================== | | SMTP protocol support | | ======================================================================" "====================================================================== | | Based on code copyright (c) Kazuki Yasumatsu, and in the public domain | Copyright (c) 2002, 2009 Free Software Foundation, Inc. | Adapted by Paolo Bonzini. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" Namespace current: NetClients.SMTP [ NetClient subclass: SMTPClient [ SMTPClient class >> defaultPortNumber [ ^25 ] SMTPClient class >> example2Host: host [ "self example2Host: 'localhost'." | user message client | user := '%1@%2' % {Smalltalk getenv: 'USER'. IPAddress localHostName}. message := MIME.MimeEntity readFrom: ('From: ' , user , ' To: ' , user , ' To: foo' , user , ' Bcc: ' , user , ' Subject: Test mail from Smalltalk (SMTPClient) This is a test mail from Smalltalk (SMTPClient). ') readStream. client := SMTPClient connectToHost: host. [[client sendMessage: message] on: SMTPNoSuchRecipientError do: [:ex | ex inspect; return]] ensure: [client close] ] SMTPClient class >> exampleHost: host [ "self exampleHost: 'localhost'." | user message client | user := '%1@%2' % {Smalltalk getenv: 'USER'. IPAddress localHostName}. message := MIME.MimeEntity readFrom: ('From: ' , user , ' To: ' , user , ' Bcc: ' , user , ' Subject: Test mail from Smalltalk (SMTPClient) This is a test mail from Smalltalk (SMTPClient). ') readStream. client := SMTPClient connectToHost: host. [client sendMessage: message] ensure: [client close] ] logout [ self clientPI smtpQuit ] sendMailStream: aStream sender: sender recipients: recipients [ self connectIfClosed. self clientPI smtpHello: self getHostname. (self clientPI isESMTP and: [self username isNil]) ifFalse: [ self clientPI esmtpAuthLogin: self username. self password isNil ifFalse: [ self clientPI esmtpPassword: self password ]]. self clientPI smtpMail: sender. recipients do: [:addr | self clientPI smtpRecipient: addr]. self clientPI smtpData: [self clientPI sendMessageWithPeriod: aStream] ] sendMessage: aMessage [ | sender recipients | aMessage inspect. (aMessage sender isNil or: [(sender := aMessage sender addresses) isEmpty]) ifTrue: [^self error: 'No sender']. sender size > 1 ifTrue: [^self error: 'Invalid sender']. sender := sender first. recipients := aMessage recipients. ^self sendMessage: aMessage sender: sender recipients: recipients ] sendMessage: aMessage sender: sender recipients: recipients [ self connectIfClosed. self clientPI smtpHello: self getHostname. (self clientPI isESMTP and: [self username isNil]) ifFalse: [ self clientPI esmtpAuthLogin: self username. self password isNil ifFalse: [ self clientPI esmtpPassword: self password ]]. self clientPI smtpMail: sender. recipients do: [:addr | self clientPI smtpRecipient: addr]. self clientPI smtpData: [aMessage printMessageOnClient: self clientPI] ] getHostname [ ^IPAddress localHostName ] protocolInterpreter [ ^SMTPProtocolInterpreter ] ] ] Namespace current: NetClients.SMTP [ NetProtocolInterpreter subclass: SMTPProtocolInterpreter [ | esmtp | checkResponse: response ifError: errorBlock [ | status | status := response status. "Positive Completion reply" status = 211 ifTrue: ["System status, or system help reply" ^self]. status = 214 ifTrue: ["Help message" ^self]. status = 220 ifTrue: ["Service ready" ^self]. status = 221 ifTrue: ["Service closing channel" ^self]. status = 235 ifTrue: ["Authentication successful" ^self]. status = 250 ifTrue: ["Requested mail action okay" ^self]. status = 251 ifTrue: ["User not local; will forward" ^self]. "Positive Intermediate reply" status = 334 ifTrue: ["Authentication password" ^self]. status = 354 ifTrue: ["Start mail input" ^self]. "Transient Negative Completion reply" status = 421 ifTrue: ["Service not available" ^errorBlock value]. status = 450 ifTrue: ["Requested mail action not taken" ^errorBlock value]. status = 451 ifTrue: ["Requested action aborted" ^errorBlock value]. status = 452 ifTrue: ["Requested action not taken" ^errorBlock value]. "Permanent Negative Completion reply" status = 500 ifTrue: ["Syntax error" ^errorBlock value]. status = 501 ifTrue: ["Syntax error in parameters" ^errorBlock value]. status = 502 ifTrue: ["Command not implemented" ^errorBlock value]. status = 503 ifTrue: ["Bad sequence of commands" ^errorBlock value]. status = 504 ifTrue: ["Command parameter not implemented" ^errorBlock value]. status = 550 ifTrue: ["Requested action not taken" ^errorBlock value]. status = 551 ifTrue: ["User not local; please try" ^errorBlock value]. status = 552 ifTrue: ["Requested mail action aborted" ^errorBlock value]. status = 553 ifTrue: ["Requested action not taken" ^errorBlock value]. status = 554 ifTrue: ["Transaction failed" ^errorBlock value]. "Unknown status" ^errorBlock value ] noSuchRecipientNotify: errorString [ ^SMTPNoSuchRecipientError signal: errorString ] connect [ | response | super connect. response := self getResponse. esmtp := response statusMessage ~ 'ESMTP'. self checkResponse: response ] isESMTP [ ^esmtp ] esmtpAuthLogin: user [ self nextPutAll: 'AUTH LOGIN ', (self class base64Encode: user); nl. self checkResponse. ] esmtpPassword: password [ self nextPutAll: (self class base64Encode: password); nl. self checkResponse ] smtpData: streamBlock [ self nextPutAll: 'DATA'; nl. self checkResponse. streamBlock value. self checkResponse ] smtpExpand: aString [ self nextPutAll: 'EXPN ' , aString; nl. self checkResponse ] smtpHello: domain [ self nextPutAll: ('%1 %2' % {esmtp. domain}); nl. self checkResponse ] smtpHelp [ self nextPutAll: 'HELP'; nl. self checkResponse ] smtpHelp: aString [ self nextPutAll: 'HELP ' , aString; nl. self checkResponse ] smtpMail: reversePath [ self nextPutAll: 'MAIL FROM: <' , reversePath displayString , '>'; nl. self checkResponse ] smtpNoop [ self nextPutAll: 'NOOP'; nl. self checkResponse ] smtpQuit [ self nextPutAll: 'QUIT'; nl. self checkResponse ] smtpRecipient: forwardPath [ | response | self nextPutAll: 'RCPT TO: <' , forwardPath displayString , '>'; nl. response := self getResponse. self checkResponse: response ifError: [| status | status := response status. (status = 550 or: ["Requested action not taken" status = 551]) ifTrue: ["User not local; please try" self noSuchRecipientNotify: forwardPath] ifFalse: [self errorResponse: response]] ] smtpReset [ self nextPutAll: 'RSET'; nl. self checkResponse ] smtpSend: reversePath [ self nextPutAll: 'SEND FROM: <' , reversePath displayString , '>'; nl. self checkResponse ] smtpSendAndMail: reversePath [ self nextPutAll: 'SAML FROM: <' , reversePath displayString , '>'; nl. self checkResponse ] smtpSendOrMail: reversePath [ self nextPutAll: 'SOML FROM: <' , reversePath displayString , '>'; nl. self checkResponse ] smtpTurn [ self nextPutAll: 'TURN'; nl. self checkResponse ] smtpVerify: aString [ self nextPutAll: 'VRFY ' , aString; nl. self checkResponse ] ] ] Namespace current: NetClients.SMTP [ NetClientError subclass: SMTPNoSuchRecipientError [ ] ] smalltalk-3.2.5/packages/net/Base.st0000644000175000017500000007642312123404352014224 00000000000000"====================================================================== | | Abstract NetClient framework | | ======================================================================" "====================================================================== | | NetUser and NetEnvironment are Copyright 2000 Cincom, Inc. | NetResponse, PluggableReporter and *Error are (c) 1995 Kazuki Yasumatsu | and in the public domain. | | The rest is copyright 2002, 2007, 2008, 2009 Free Software Foundation, Inc. | and written by Paolo Bonzini. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" Eval [ NetClients at: #LineEndCR put: #cr. NetClients at: #LineEndLF put: #nl. NetClients at: #LineEndCRLF put: #crnl. NetClients at: #LineEndTransparent put: #yourself ] Object subclass: NetUser [ | username password | username string password password string'> NetUser class >> username: aUsername password: aPassword [ "NetUser username: 'foo' password: 'foo'" | user | user := self new. ^user username: aUsername; password: aPassword yourself ] password [ ^password ] password: aString [ password := aString ] username [ ^username ] username: aString [ username := aString ] ] Object subclass: NetEnvironment [ | debugStream debugCategories debugClasses trace logFileName | NetEnvironment class [ | uniqueInstance | ] NetEnvironment class >> default [ ^uniqueInstance isNil ifTrue: [uniqueInstance := self new] ifFalse: [uniqueInstance] ] debugCategories [ debugCategories isNil ifTrue: [debugCategories := Set new. debugCategories add: #general]. ^debugCategories ] debugClasses [ ^debugClasses isNil ifTrue: [debugClasses := Set new] ifFalse: [debugClasses] ] debugStream [ ^debugStream ] debugStream: aStream [ debugStream := aStream ] logFileName [ logFileName isNil ifTrue: [logFileName := 'NetClientLog.txt']. ^logFileName ] logFileName: aString [ logFileName := aString ] trace [ trace isNil ifTrue: [trace := false]. ^trace ] trace: aBoolean [ trace := aBoolean ] debug: aBlock level: aLevel [ (self trace and: [self debugCategories includes: aLevel]) ifTrue: [aBlock value] ] log: aStringOrBlock [ self log: aStringOrBlock level: #general ] log: aStringOrBlock level: aLevel [ | stream i briefMsg aMsg | self debug: [(stream := self debugStream) == nil ifTrue: [^self]. (aStringOrBlock isKindOf: BlockClosure) ifTrue: [aMsg := aStringOrBlock value] ifFalse: [aMsg := aStringOrBlock]. i := aMsg size. [i > 0 and: [(aMsg at: i) isSeparator]] whileTrue: [i := i - 1]. briefMsg := aMsg copyFrom: 1 to: i. stream cr; nextPutAll: briefMsg; flush] level: aLevel ] printTrace: aString [ | stream | (stream := self debugStream) == nil ifTrue: [^self]. stream cr; cr; nextPutAll: ' **** ' asString. Date today printOn: stream. stream nextPutAll: ' '. Time now printOn: stream. stream nextPutAll: ' ' , aString , ' ****'; flush ] traceOff [ self printTrace: 'Stop Trace'. self trace: false ] traceOn [ self trace: true. self printTrace: 'Start Trace' ] addDebugCategory: symbol [ self debugCategories add: symbol ] removeDebugCategory: symbol [ self debugCategories remove: symbol ] reset [ self resetDebugClasses. self resetDebugCategories ] resetDebugCategories [ debugCategories := nil ] resetDebugClasses [ debugClasses := nil ] addToDebug: aClass [ self debugClasses add: aClass ] ] Object subclass: NetClient [ | hostName portNumber user reporter clientPI connectionStream isSSL | NetClient class >> defaultPortNumber [ self subclassResponsibility ] NetClient class >> defaultSSLPortNumber [ self subclassResponsibility ] NetClient class >> connectToHost: aHostname [ ^self new hostName: aHostname; connect ] NetClient class >> connectToHost: aHostname port: aPort [ ^self new hostName: aHostname; portNumber: aPort; connect ] NetClient class >> loginToHost: aHostName asUser: userString withPassword: passwdString [ ^self loginToHost: aHostName port: nil asUser: userString withPassword: passwdString ] NetClient class >> loginToHost: aHostName port: aNumber asUser: userString withPassword: passwdString [ ^self new loginToHost: aHostName port: aNumber asUser: userString withPassword: passwdString ] NetClient class >> loginUser: userString withPassword: passwdString [ ^self loginUser: userString withPassword: passwdString ] user [ ^user ] user: aNetUser [ user := aNetUser ] username [ ^user username ] password [ ^self user password ] username: usernameString password: passwdString [ user := NetUser username: usernameString password: passwdString ] clientPI [ clientPI isNil ifTrue: [ self clientPI: (self protocolInterpreter client: self)]. ^clientPI ] clientPI: aProtocolInterpreter [ clientPI := aProtocolInterpreter ] hostName [ ^hostName ] hostName: aString [ hostName := aString ] isSSL [ isSSL isNil ifTrue: [isSSL := false]. ^isSSL ] isSSL: aBoolean [ isSSL := aBoolean ] defaultPortNumber [ ^self isSSL ifFalse: [self class defaultPortNumber] ifTrue: [self class defaultSSLPortNumber] ] portNumber [ portNumber isNil ifTrue: [^self defaultPortNumber]. portNumber = 0 ifTrue: [^self defaultPortNumber]. ^portNumber ] portNumber: aNumber [ portNumber := aNumber ] reporter [ reporter isNil ifTrue: [reporter := Reporter new]. ^reporter ] reporter: aReporter [ reporter := aReporter ] protocolInterpreter [ self subclassResponsibility ] binary [ connectionStream class == CrLfStream ifTrue: [connectionStream := connectionStream stream] ] isBinary [ ^connectionStream class ~~ CrLfStream ] text [ self binary. self clientPI lineEndConvention = LineEndCRLF ifTrue: [connectionStream := CrLfStream on: connectionStream] ] close [ ^self logout ] closeConnection [ self closed ifFalse: [connectionStream close. connectionStream := nil]. self liveAcrossSnapshot ifTrue: [ObjectMemory removeDependent: self] ] closed [ ^connectionStream == nil ] connect [ | connection messageText | [connection := self createSocket] on: Error do: [:ex | ex. messageText := ex messageText. ex return: nil]. connection isNil ifTrue: [^self clientPI connectionFailedError: messageText]. self connectionStream: connection. self clientPI connected. ] connectIfClosed [ self closed ifTrue: [self connect] ] createSSLWrapper [ | connection messageText | (self hostName anySatisfy: [ :ch | '''"\${}()*?' includes: ch ]) ifTrue: [ self error: 'invalid host name' ]. (self portNumber isInteger not and: [self anySatisfy: [ :ch | '''"\${}()*?' includes: ch ]]) ifTrue: [ self error: 'invalid port name' ]. Directory libexec isNil ifTrue: [ self error: 'cannot find gnutls-wrapper' ]. ^FileDescriptor popen: '%1 %2 %3' % { Directory libexec / 'gnutls-wrapper'. self hostName. self portNumber } dir: 'r+' ] createSocket [ | connection messageText | self isSSL ifTrue: [ ^self createSSLWrapper ]. ^Socket remote: self hostName port: self portNumber ] connectionStream [ ^connectionStream ] connectionStream: aSocket [ connectionStream := aSocket. self text. self liveAcrossSnapshot ifTrue: [ObjectMemory addDependent: self] ] liveAcrossSnapshot [ ^false ] login [ ] logout [ ] loginToHost: aHostName asUser: userString withPassword: passwdString [ ^self loginToHost: aHostName port: nil asUser: userString withPassword: passwdString ] loginToHost: aHostName port: aNumber asUser: userString withPassword: passwdString [ | resp | hostName := aHostName. portNumber := aNumber. self username: userString password: passwdString. self connect. (resp := self login) completedSuccessfully ifFalse: [^nil] ] reconnect [ self closeConnection. self connect ] ] Object subclass: NetProtocolInterpreter [ | client | NetProtocolInterpreter class >> base64Encode: aString [ | i j outSize c1 c2 c3 out b64string chars | chars := 'ABCDEFGHIJKLMNOPQRSTUVWXYZabcdefghijklmnopqrstuvwxyz0123456789+/'. outSize := aString size // 3 * 4. (aString size \\ 3) = 0 ifFalse: [ outSize := outSize + 4 ]. b64string := String new: outSize. i := 1. 1 to: outSize by: 4 do: [ :j | c1 := aString valueAt: i ifAbsent: [0]. c2 := aString valueAt: i+1 ifAbsent: [0]. c3 := aString valueAt: i+2 ifAbsent: [0]. out := c1 bitShift: -2. b64string at: j put: (chars at: out + 1). out := ((c1 bitAnd: 3) bitShift: 4) bitOr: (c2 bitShift: -4). b64string at: j+1 put: (chars at: out + 1). out := ((c2 bitAnd: 15) bitShift: 2) bitOr: (c3 bitShift: -6). b64string at: j+2 put: (chars at: out + 1). out := c3 bitAnd: 63. b64string at: j+3 put: (chars at: out + 1). i := i + 3. ]. b64string replaceFrom: outSize - (i - aString size) + 2 to: outSize withObject: $=. ^b64string ] NetProtocolInterpreter class >> log: aString level: aLevel [ NetEnvironment default log: aString level: aLevel ] NetProtocolInterpreter class >> registerToDebug [ NetEnvironment default addToDebug: self ] NetProtocolInterpreter class >> client: aNetClient [ ^self new client: aNetClient ] NetProtocolInterpreter class >> new [ ^self basicNew initialize ] NetProtocolInterpreter class >> defaultResponseClass [ ^NetResponse ] NetProtocolInterpreter class >> base64Encode: aString [ | chars i j n t1 t2 t3 ch aStringSize b64Size b64String | chars := 'ABCDEFGHIJKLMNOPQRSTUVWXYZabcdefghijklmnopqrstuvwxyz0123456789+/'. aStringSize := aString size. b64Size := aStringSize // 3 * 4. (aStringSize \\ 3 ~= 0) ifTrue: [b64Size := b64Size + 4]. b64String := String new: b64Size withAll: $=. i := j := 1. [i <= aStringSize] whileTrue: [ t1 := (aString at: i ifAbsent: [Character nul]) asInteger. t2 := (aString at: i + 1 ifAbsent: [Character nul]) asInteger. t3 := (aString at: i + 2 ifAbsent: [Character nul]) asInteger. n := 3 min: aStringSize - i + 1. ch := t1 bitShift: -2. b64String at: j put: (chars at: ch + 1). ch := ((t1 bitAnd: 3) bitShift: 4) bitOr: (t2 bitShift: -4). b64String at: j + 1 put: (chars at: ch + 1). n >= 2 ifTrue: [ ch := ((t2 bitAnd: 15) bitShift: 2) bitOr: (t2 bitShift: -6). b64String at: j + 2 put: (chars at: ch + 1). ]. n >= 3 ifTrue: [ ch := t3 bitAnd: 63. b64String at: j + 3 put: (chars at: ch + 1). ]. i := i + 3. j := j + 4. ]. ^b64String ] client [ ^client ] reporter [ ^self client reporter ] receiveMessageUntilPeriod [ "Receive and answer a message until period line." | write | write := WriteStream on: (String new: 4 * 1024). self receiveMessageUntilPeriodInto: write. ^write contents ] receiveMessageUntilPeriodInto: aStream [ "Receive a message until period line into aStream." self connectIfClosed. MIME.MimeEntity new parseSimpleBodyFrom: self onto: aStream ] sendMessageWithPeriod: aStream [ "Send aStream as a message with period." self connectIfClosed. (PrependDotStream to: self) nextPutAll: aStream; flush ] skipMessageUntilPeriod [ "Skip a message until period line." self connectIfClosed. MIME.MimeEntity new skipSimpleBodyFrom: self ] binary [ client binary ] isBinary [ ^client isBinary ] text [ client text ] close [ client closeConnection ] closed [ ^client closed ] connectionStream [ ^client connectionStream ] connectionStream: aSocket [ client connectionStream: aSocket ] connected [ ] connect [ client connect ] connectIfClosed [ client connectIfClosed ] reconnect [ client reconnect ] decode: aString [ ^aString ] encode: aString [ ^aString ] client: aNetClient [ client := aNetClient ] initialize [ ] release [ self close ] checkResponse [ self checkResponse: self getResponse ] checkResponse: response [ self checkResponse: response ifError: [self errorResponse: response] ] checkResponse: reponse ifError: errorBlock [ ] connectionClosedError: messageText [ ^(ConnectionClosedError new) tag: messageText; signal: 'Connection closed: ' , messageText ] connectionFailedError: messageText [ ^(ConnectionFailedError new) tag: messageText; signal: 'Connection failed: ' , messageText ] getResponse [ ^self class defaultResponseClass fromClient: self ] loginIncorrectError: messageText [ ^(LoginIncorrectError new) tag: messageText; signal: 'Login incorrect: ' , messageText ] errorResponse: aResponse [ ^(ProtocolError new) response: aResponse; signal ] unexpectedResponse: aResponse [ ^(UnexpectedResponseError new) response: aResponse; signal ] lineEndConvention [ ^LineEndCRLF ] atEnd [ ^self connectionStream atEnd ] contents [ ^self decode: self connectionStream contents ] cr [ | conv | conv := self lineEndConvention. (conv = LineEndCR or: [conv = LineEndTransparent]) ifTrue: [^self connectionStream nextPut: Character cr]. conv = LineEndLF ifTrue: [^self connectionStream nextPut: Character nl]. conv = LineEndCRLF ifTrue: [^self connectionStream nextPut: Character cr; nextPut: Character nl]. self error: 'Undefined line-end convention' ] flush [ self connectionStream flush ] next [ ^self connectionStream next ] next: anInteger [ ^self decode: (self connectionStream next: anInteger) ] nextAvailable: anInteger [ ^self decode: (self connectionStream nextAvailable: anInteger) ] nextLine [ | write byte | write := WriteStream on: (String new: 128). [self connectionStream atEnd] whileFalse: [byte := self connectionStream next. byte == Character cr ifTrue: [self connectionStream peekFor: Character nl. ^self decode: write contents]. byte == Character nl ifTrue: [^self decode: write contents]. write nextPut: byte]. ^self decode: write contents ] nextPut: aCharacter [ self connectionStream nextPutAll: (self encode: (String with: aCharacter)) ] nextPutAll: aString [ aString isEmpty ifTrue: [^self]. self connectionStream nextPutAll: (self encode: aString) ] nl [ | conv | conv := self lineEndConvention. conv = LineEndCR ifTrue: [^self connectionStream nextPut: Character cr]. (conv = LineEndLF or: [conv = LineEndTransparent]) ifTrue: [^self connectionStream nextPut: Character nl]. conv = LineEndCRLF ifTrue: [^self connectionStream nextPut: Character cr; nextPut: Character nl]. self error: 'Undefined line-end convention' ] species [ ^self connectionStream species ] upTo: aCharacter [ | byte | aCharacter = Character cr ifTrue: [^self nextLine]. byte := self encode: (String with: aCharacter). byte size = 1 ifTrue: [^self decode: (self connectionStream upTo: byte)] ifFalse: [^self decode: (self connectionStream upToAll: byte)] ] update: aSymbol [ "Dependents of ObjectMemory are sent update: #returnFromSnapshot when a snapshot is started." self liveAcrossSnapshot ifTrue: [aSymbol == #returnFromSnapshot ifTrue: [self close] "(aSymbol == #aboutToSnapshot or: [aSymbol == #aboutToQuit]) ifTrue: [self close]."]. super update: aSymbol ] ] Object subclass: NetResponse [ | status statusMessage | NetResponse class >> fromClient: aClient [ | response | response := self new. response parseResponse: aClient. ^response ] status [ ^status ] status: anInteger [ status := anInteger ] statusArray [ | n array | status == nil ifTrue: [n := 0] ifFalse: [n := status]. array := Array new: 3. array at: 1 put: n // 100. n := n - (n // 100 * 100). array at: 2 put: n // 10. n := n - (n // 10 * 10). array at: 3 put: n. ^array ] statusMessage [ ^statusMessage ] statusMessage: aString [ statusMessage := aString ] parseResponse: aClient [ self parseStatusLine: aClient ] printOn: aStream [ self printStatusOn: aStream ] printStatusOn: aStream [ status notNil ifTrue: [aStream print: status; space]. statusMessage notNil ifTrue: [aStream nextPutAll: statusMessage] ] parseStatusLine: aClient [ | stream | statusMessage := nil. [stream := aClient nextLine readStream. status := Integer readFrom: stream. stream next = $-] whileTrue: [statusMessage == nil ifTrue: [statusMessage := stream upToEnd] ifFalse: [statusMessage := statusMessage , (String with: Character cr) , stream upToEnd]]. stream skipSeparators. statusMessage == nil ifTrue: [statusMessage := stream upToEnd] ifFalse: [statusMessage := statusMessage , (String with: Character cr) , stream upToEnd] ] ] Object subclass: Reporter [ | totalByte readByte startTime currentTime | readByte [ ^readByte ] readByte: anInteger [ readByte := readByte + anInteger. currentTime := Time millisecondClockValue. ] endTransfer [ ^self ] startTransfer [ readByte := 0. startTime := currentTime := Time millisecondClockValue. ^self ] statusString: aString [ ^self ] totalByte [ ^totalByte ] totalByte: aNumber [ totalByte := aNumber ] transferSpeed [ currentTime = startTime ifTrue: [^nil]. ^readByte / ((currentTime - startTime) / 1000) ] ] Reporter subclass: PluggableReporter [ | statusBlock | PluggableReporter class >> statusBlock: aBlock [ ^self new statusBlock: aBlock ] endTransfer [ self statusString: 'Transferring: Done.' ] readByte: anInteger [ super readByte: anInteger. self statusString: self progressStatusString ] startTransfer [ super startTransfer. self statusString: 'Transferring: Start.' ] statusString: statusString [ statusBlock isNil ifTrue: [^self]. statusBlock value: statusString ] progressStatusString [ | stream speed | stream := WriteStream on: (String new: 128). stream print: readByte. totalByte == nil ifFalse: [stream nextPut: $/; print: totalByte]. stream nextPutAll: ' bytes'. speed := self transferSpeed. speed == nil ifFalse: [stream nextPutAll: ' ('. stream display: (self transferSpeed / 1024 asScaledDecimal: 2). stream nextPutAll: ' Kbytes/sec)']. ^stream contents ] statusBlock: aBlock [ statusBlock := aBlock ] ] Stream subclass: RemoveDotStream [ | stream ch atStart | RemoveDotStream class >> on: aStream [ ^self new initialize: aStream ] atEnd [ ch isNil ifFalse: [^false]. stream isNil ifTrue: [^true]. stream atEnd ifTrue: [stream := nil. ^true]. ch := stream next. (atStart and: [ch == $.]) ifFalse: [atStart := ch == Character cr or: [ch == Character nl]. ^false]. atStart := false. "Found dot at start of line, discard it" stream atEnd ifTrue: [stream := ch := nil. ^true]. ch := stream next. "Found lonely dot, we are at end of stream" (ch == Character cr or: [ch == Character nl]) ifTrue: [ch == Character cr ifTrue: [stream next]. stream := ch := nil. ^true]. ^false ] next [ | answer | self atEnd ifTrue: [self error: 'end of stream reached']. answer := ch. ch := nil. ^answer ] peek [ self atEnd ifTrue: [^nil]. ^ch ] peekFor: aCharacter [ self atEnd ifTrue: [^false]. ch == aCharacter ifTrue: [self next. ^true]. ^false ] initialize: aStream [ stream := aStream. atStart := true. self atEnd ] species [ ^stream species ] ] Stream subclass: PrependDotStream [ | stream atStart | PrependDotStream class >> to: aStream [ ^self new initialize: aStream ] flush [ atStart ifFalse: [self nl]. stream nextPut: $.; nl ] nextPut: aChar [ (atStart and: [aChar == $.]) ifTrue: [stream nextPut: aChar]. stream nextPut: aChar. atStart := aChar == Character nl ] initialize: aStream [ stream := aStream. atStart := true ] species [ ^stream species ] ] Stream subclass: CrLfStream [ | stream readStatus eatLf | Lf := nil. Cr := nil. CrLfStream class >> on: aStream [ Cr := Character cr. Lf := Character nl. ^self new on: aStream ] on: aStream [ stream := aStream. eatLf := false. readStatus := #none ] atEnd [ ^stream atEnd and: [readStatus == #none] ] close [ stream close ] flush [ stream flush ] next [ | result | readStatus == #none ifFalse: [readStatus == Cr ifTrue: [stream peekFor: Lf]. readStatus := #none. ^Lf]. result := stream next. ^(result == Cr or: [result == Lf]) ifTrue: [readStatus := result. Cr] ifFalse: [result] ] nextLine [ | line | line := self upTo: Cr. self next. "Eat line feed" ^line ] nextPut: aCharacter [ eatLf ifTrue: [eatLf := false. aCharacter == Lf ifTrue: [^self]] ifFalse: [aCharacter == Lf ifTrue: [stream nextPut: Cr; nextPut: Lf; flush. ^self]]. stream nextPut: aCharacter. aCharacter == Cr ifTrue: [stream nextPut: Lf; flush. eatLf := true] ] peek [ | result | readStatus == #none ifFalse: [readStatus == Cr ifTrue: [stream peekFor: Lf]. readStatus := Lf. "peek for LF just once" ^Lf]. result := stream peek. ^result == Lf ifTrue: [Cr] ifFalse: [result] ] peekFor: aCharacter [ | result success | readStatus == #none ifFalse: [readStatus == Cr ifTrue: [stream peekFor: Lf]. success := aCharacter == Lf. readStatus := success ifTrue: [#none] ifFalse: [Lf]. "peek for LF just once" ^success]. result := stream peek. (result == Cr or: [result == Lf]) ifTrue: [success := aCharacter == Cr. success ifTrue: [readStatus := stream next]. ^success]. success := aCharacter == result. success ifTrue: [stream next]. ^success ] species [ ^stream species ] stream [ ^stream ] ] Error subclass: NetClientError [ ] NetClientError subclass: ConnectionFailedError [ description [ ^'The connection attempt failed.' ] ] NetClientError subclass: ConnectionClosedError [ description [ ^'The server closed the connection.' ] ] Notification subclass: ProtocolNotification [ | response | description [ ^'Protocol Notification' ] response [ ^response ] response: aResponse [ response := aResponse. self messageText: '%1: %2' % {self description. response statusMessage} ] isResumable [ ^true ] ] NetClientError subclass: ProtocolError [ | response | description [ ^'Protocol Error' ] response [ ^response ] response: aResponse [ response := aResponse. self messageText: '%1: %2' % {self description. response statusMessage} ] isResumable [ ^true ] ] NetClientError subclass: UnexpectedResponseError [ | response | description [ ^'Unexpected Response' ] isResumable [ ^false ] ] NetClientError subclass: LoginIncorrectError [ description [ ^'The server rejected your login attempt.' ] ] NetClientError subclass: WrongStateError [ description [ ^'This command cannot be executed in the client''s current state.' ] ] smalltalk-3.2.5/packages/net/ContentHandler.st0000644000175000017500000002333112123404352016250 00000000000000"====================================================================== | | Abstract ContentHandler class | | ======================================================================" "====================================================================== | | Copyright 1999, 2000, 2001, 2002 Free Software Foundation, Inc. | Written by Paolo Bonzini. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" Object subclass: ContentHandler [ | stream | ContentHandler class [ | validTypes | ] FileExtensionMap := nil. FileTypeMap := nil. ContentHandler class >> contentTypeFor: aFileName ifAbsent: aBlock [ "Guess a MIME content type for the given file name and answer it. If no interesting value could be found, evaluate aBlock" | posi | posi := aFileName findLast: [:each | each = $.]. posi = 0 ifTrue: [^aBlock value]. ^FileExtensionMap at: (aFileName copyFrom: posi + 1 to: aFileName size) ifAbsent: aBlock ] ContentHandler class >> contentTypeFor: aFileName [ "Guess a MIME content type for the given file name and answer it" ^self contentTypeFor: aFileName ifAbsent: ['application/octet-stream'] ] ContentHandler class >> guessContentTypeFor: aPositionableStream ifAbsent: aBlock [ "Guess a MIME content type for the given file name and answer it. If no interesting value could be found, evaluate aBlock" | str ba text | str := aPositionableStream nextAvailable: 12. ba := str asByteArray. FileTypeMap do: [:each | | ok | ok := true. (each at: 1) doWithIndex: [:ch :index | (ch isSymbol or: [index >= str size]) ifFalse: [ch isInteger ifTrue: [ok := ok and: [(ba at: index) = ch]] ifFalse: [ok := ok and: [(str at: index) = ch]]]]. ok ifTrue: [^each at: 2]]. str := str , (aPositionableStream nextAvailable: 200). text := str allSatisfy: [:each | each value <= 127]. ^text ifTrue: ['text/plain'] ifFalse: aBlock ] ContentHandler class >> guessContentTypeFor: aPositionableStream [ "Guess a MIME content type for the given file contents and answer it." ^self guessContentTypeFor: aPositionableStream ifAbsent: ['application/octet-stream'] ] ContentHandler class >> classFor: mimeType [ "Answer a subclass of the receiver (or the receiver itself if none could be found) that can handle the mimeType content type (a String)." self withAllSubclassesDo: [:each | (each validTypes includes: mimeType) ifTrue: [^each]]. ^self ] ContentHandler class >> defaultFileExtensionMap [ "Answer a default extension->mime type map" ^#(#('aif' 'audio/x-aiff') #('ai' 'application/postscript') #('aifc' 'audio/aiff') #('aiff' 'audio/x-aiff') #('au' 'audio/basic') #('avi' 'video/x-msvideo') #('bmp' 'image/bmp') #('cdf' 'application/x-cdf') #('cer' 'application/x-x509-ca-cert') #('crt' 'application/x-x509-ca-cert') #('css' 'text/css') #('dcr' 'application/x-director') #('der' 'application/x-x509-ca-cert') #('dir' 'application/x-director') #('dll' 'application/x-msdownload') #('doc' 'application/msword') #('dot' 'application/msword') #('dxr' 'application/x-director') #('eml' 'message/rfc822') #('eps' 'application/postscript') #('exe' 'application/x-msdownload') #('fif' 'application/fractals') #('gif' 'image/gif') #('gz' 'application/x-gzip') #('hqx' 'application/mac-binhex40') #('htm' 'text/html') #('html' 'text/html') #('htt' 'text/webviewhtml') #('ins' 'application/x-internet-signup') #('isp' 'application/x-internet-signup') #('ivf' 'video/x-ivf') #('jfif' 'image/pjpeg') #('jpe' 'image/jpeg') #('jpeg' 'image/jpeg') #('jpg' 'image/jpeg') #('latex' 'application/x-latex') #('m1v' 'video/mpeg') #('man' 'application/x-troff-man') #('mht' 'message/rfc822') #('mhtml' 'message/rfc882') #('mid' 'audio/mid') #('mov' 'movie/quicktime') #('mov' 'video/quicktime') #('mp2' 'video/mpeg') #('mpa' 'video/mpeg') #('mpe' 'movie/mpeg') #('mpeg' 'movie/mpeg') #('mpg' 'video/mpeg') #('nws' 'message/rfc822') #('p7c' 'application/pkcs7-mime') #('png' 'image/png') #('pdf' 'application/pdf') #('pot' 'application/vnd.ms-powerpoint') #('ppa' 'application/vnd.ms-powerpoint') #('pps' 'application/vnd.ms-powerpoint') #('ppt' 'application/vnd.ms-powerpoint') #('ps' 'application/postscript') #('pwz' 'application/vnd.ms-powerpoint') #('qt' 'video/quicktime') #('rmi' 'audio/mid') #('rtf' 'application/msword') #('sgm' 'text/sgml') #('sgml' 'text/sgml') #('sit' 'application/x-stuffit') #('snd' 'audio/basic') #('spl' 'application/futuresplash') #('st' 'text/plain') #('swf' 'application/x-shockwave-flash') #('svg' 'image/svg+xml') #('tar' 'application/x-tar') #('tgz' 'application/x-compressed') #('tif' 'image/tiff') #('tiff' 'image/tiff') #('txt' 'text/plain') #('wav' 'audio/wav') #('wiz' 'application/msword') #('xbm' 'image/x-xbitmap') #('xml' 'text/xml') #('xls' 'application/vnd.ms-excel') #('z' 'application/x-compress') #('zip' 'application/x-zip-compressed')) "Of course!" ] ContentHandler class >> defaultFileTypeMap [ "Answer a default file contents->mime type map. Each element is an array; the first element of the array is matched against the data passed to #guessContentTypeFor:. A character or integer is matched against a single byte, while if a Symbol is found, the corresponding byte in the data stream is not compared against anything" ^#(#('MZ' 'application/x-msdownload') #(#($P $K 3 4) 'application/x-zip-compressed') #('%PDF' 'application/pdf') #('%!PS' 'application/postscript') #('.snd' 'audio/basic') #('dns.' 'audio/basic') #('MThd' 'audio/mid') #(#($R $I $F $F #- #- #- #- $R $M $I $D) 'audio/mid') #(#($R $I $F $F #- #- #- #- $W $A $V $E) 'audio/x-wav') #('> contentType: type hasExtension: ext [ "Associate the given MIME content type to the `ext' extension (without leading dots)." ^FileExtensionMap at: ext put: type ] ContentHandler class >> contentType: type hasMagicData: data [ "Associate the given MIME content type to the magic data in `data'. Data is an ArrayedCollection (usually an Array, ByteArray, or String) whose contents are matched against the data passed to #guessContentTypeFor:. A character or integer is matched against a single byte, while if a Symbol is found, the corresponding byte in the data stream is not compared against anything. Of course a Symbol can only occur if data is an Array." ^FileTypeMap add: (Array with: data with: type) ] ContentHandler class >> initialize [ "Initialize the default file extension and magic data maps" FileExtensionMap := Dictionary new. FileTypeMap := self defaultFileTypeMap asOrderedCollection. self defaultFileExtensionMap do: [:each | FileExtensionMap at: (each at: 1) put: (each at: 2)]. ContentHandler registerContentTypes: #('application/octet-stream' 'application/x-unknown' 'text/english' 'text/plain') ] ContentHandler class >> validTypes [ "Answer some MIME types that instances the receiver can interpret" ^validTypes isNil ifTrue: [#()] ifFalse: [validTypes] ] ContentHandler class >> registerContentType: contentType [ "Register the receiver to be used to parse entities of the given MIME type. contentTypes must be a String." validTypes isNil ifTrue: [validTypes := OrderedCollection new]. validTypes add: contentType ] ContentHandler class >> registerContentTypes: contentTypes [ "Register the receiver to be used to parse entities of the given MIME types. contentTypes must be a collection of Strings." validTypes isNil ifTrue: [validTypes := OrderedCollection new]. validTypes addAll: contentTypes ] ContentHandler class >> on: stream [ "Answer an instance of the receiver to be used to interpret data in the given stream" ^self new initialize: stream ] contents [ "By default, answer the whole contents of the stream without interpreting anything; subclasses however might want to return a more interesting object, failing if the data is somehow incorrect." ^stream contents ] initialize: aStream [ stream := aStream ] ] Eval [ ContentHandler initialize ] smalltalk-3.2.5/packages/net/ChangeLog0000644000175000017500000004060612123404352014546 000000000000002012-06-15 Stefan Krecher Paolo Bonzini * URIResolver.st: Consistently use symbols for #settingsAt: arguments. 2011-09-09 Paolo Bonzini * gnutls-wrapper.c: More Win32 fixes. Reported by Gwenael Casaccio. 2011-03-29 Paolo Bonzini * MIME.st: Do not fail on empty fields like "Expires: \r\n". 2011-03-29 Paolo Bonzini * HTTP.st: Accept end-of-file where a chunked encoding header should have been. 2011-03-22 Paolo Bonzini * gnutls-wrapper.c: Fixes for Win32 compilation. 2011-03-21 Paolo Bonzini * URIResolver.st: Reorder exceptions. 2011-03-21 Paolo Bonzini * Base.st: Add ProtocolNotification. * HTTP.st: Use it for redirects. * URIResolver.st: Simplify. 2011-03-21 Paolo Bonzini * Base.st: Add response variable to ProtocolError. Add UnexpectedResponseError. * FTP.st: Use #unexpectedResponse:. * NNTP.st: Use #errorResponse: and #unexpectedResponse:. * SMTP.st: Use #errorResponse: 2011-03-21 Paolo Bonzini * FTP.st: Remove useless override. * HTTP.st: Remove useless override. * POP.st: Remove useless override. 2011-03-21 Paolo Bonzini * Base.st: Add exception descriptions. Add WrongStateError. * IMAP.st: Use WrongStateError. 2011-03-12 Paolo Bonzini * gnutls-wrapper.c: Remove dead code signaled by clang analyzer. 2011-03-10 Holger Hans Peter Freyther * HTTP.st: Flush the binary stream. 2011-03-07 Holger Hans Peter Freyther * Base.st: Call connectionFailedError of NetProtocolInterpreter. 2011-03-07 Holger Hans Peter Freyther * URIResolver.st: Add #doHTTPRequest and use it. 2011-03-06 Holger Hans Peter Freyther * URIResolver.st: Align GET and POST for HTTP. 2011-03-06 Holger Hans Peter Freyther * URIResolver.st: Always set the 'Host' header for HTTP. 2011-03-06 Holger Hans Peter Freyther * URIResolver.st: Add #defaultHeaders for HTTP. 2011-03-07 Paolo Bonzini * gnutls-wrapper.c: Fix previous patch. 2011-01-11 Paolo Bonzini * gnutls-wrapper.c: Support older GnuTLS. 2010-12-17 Paolo Bonzini * IMAP.st: _Really_ fix it. 2010-12-13 Paolo Bonzini * Base.st: Fix erroneously pushed commit. * IMAP.st: Likewise. 2010-12-13 Paolo Bonzini * Base.st: Remove duplicate instance variables, move things from PluggableReporter to Reporter. Reported by Gwenael Casaccio. * IMAP.st: Remove duplicate instance variable. Reported by Gwenael Casaccio. 2010-12-07 Paolo Bonzini * MIME.st: Add #assertNoLookahead. * HTTP.st: Use it instead of going through a ConcatenatedStream. 2010-12-07 Paolo Bonzini * gnutls-wrapper.c: New. * Base.st: Support SSL sockets. * HTTP.st: Declare SSL port number. 2010-12-07 Paolo Bonzini * Base.st: Add stub https support. * URIResolver.st: Use it. 2010-12-05 Paolo Bonzini * URIResolver.st: Create NetClient objects outside of the methods that actually speak to the NetClient. 2010-12-05 Paolo Bonzini * URIResolver.st: Remove broken support for mailto and postto. 2010-12-05 Paolo Bonzini * Base.st: Use lazy initialization for clientPI. 2010-12-05 Paolo Bonzini * Base.st: Move connectionStream from ProtocolInterpreter to Client. * HTTP.st: Adjust direct uses of the instance variable. * IMAP.st: Adjust direct uses of the instance variable. * NNTP.st: Adjust direct uses of the instance variable. 2010-12-04 Paolo Bonzini * package.xml: Remove now superfluous tags. 2010-07-19 Paolo Bonzini * Base.st: Move #defaultPortNumber to client class side. * FTP.st: Move #defaultPortNumber to client class side. * HTTP.st: Move #defaultPortNumber to client class side. * IMAP.st: Move #defaultPortNumber to client class side. * NNTP.st: Move #defaultPortNumber to client class side. * POP.st: Move #defaultPortNumber to client class side. * SMTP.st: Move #defaultPortNumber to client class side. 2010-02-19 Paolo Bonzini * NetServer.st: Do not use instance-based exceptions. 2010-01-01 Paolo Bonzini * Update copyright years. 2009-11-09 Paolo Bonzini * IMAP.st: Extract tests... * IMAPTests.st: ... here. * package.xml: Separate test package. 2009-07-15 Paolo Bonzini Joachim Jaeckel * Base.st: Add Base-64 encoding. * SMTP.st: Add ESMTP support. 2009-06-29 Paolo Bonzini Joachim Jaeckel * MIME.st: Fix Base-64 decoding bugs. 2008-08-06 Paolo Bonzini * FTP.st: Do not use #nextHunk. 2008-07-15 Paolo Bonzini * Base.st: Use Sockets namespace. * FTP.st: Use Sockets namespace. * NetServer.st: Use Sockets namespace. * URIResolver.st: Use Sockets namespace. 2008-06-01 Paolo Bonzini * URIResolver.st: Handle ProtocolError in a saner way. 2008-06-01 Paolo Bonzini * Base.st: Make ProtocolError resumable. * MIME.st: Trim whitespace in front of fields. * URIResolver.st: Fix case when there is a protocol error. 2008-04-07 Paolo Bonzini * FTP.st: Use new methods on File. * URIResolver.st: Likewise. Remove distinction between File and Directory objects. 2007-10-08 Paolo Bonzini * NetServer.st: Move #stop to NetServer, since using it for NetSessions might be dangerous. 2007-09-06 Paolo Bonzini * MIME.st: More fixes to previous change. 2007-09-05 Paolo Bonzini * MIME.st: Try not to use negative #skip:. 2007-09-04 Paolo Bonzini * MIME.st: Use #subStrings:. 2007-08-07 Paolo Bonzini * Load.st: Delete. * IMAP.st: Create namespace here. * MIME.st: Create namespace here. * NNTP.st: Create namespace here. * POP.st: Create namespace here. * SMTP.st: Create namespace here. * FTP.st: Create namespace here. * HTTP.st: Create namespace here. * NetServer.st: Remove namespace switching. * URIResolver.st: Remove namespace switching. * Base.st: Remove namespace switching. 2007-06-25 Paolo Bonzini * SMTP.st: Use #%. * httpd/FileServer.st: Use #%. * httpd/WebServer.st: Use #%. * httpd/WikiServer.st: Use #%. 2007-06-01 Paolo Bonzini * HTTP.st: Use #, on streams directly. 2007-03-19 Paolo Bonzini * MIME.st: Remove unused class variable. * URIResolver.st: Convert class variables to class-instance. * Base.st: Convert class variables to class-instance. * http/WikiServer.st: Don't use #perform: unless necessary. 2007-01-03 Paolo Bonzini * ContentHandler.st: Add png extension. 2006-12-05 Paolo Bonzini *** Version 2.3 released. 2006-10-05 Mike Anderson Paolo Bonzini * NetServer: Fix #at:, add #isPeerAlive and use it. * ContentHandler.st: Add svg. * WebServer.st: Add #named:, parse If-Modified-Since times, Parse Content-Length for POST requests. Add #hasPostData, #postDataAt:ifPresent:. Use #subStrings:, fix printing of 100 status codes. Support query data without a value. 2005-09-05 Mike Anderson * HTTP.st: Fix bugs and support chunked encoding. 2005-04-07 Brett Cundal * NetServer.st: Fix typo in printOn: 2003-08-26 Paolo Bonzini * NetServer.st: give a name to each NetThread process. 2003-05-09 Paolo Bonzini *** Version 2.1.2 released. 2003-04-17 Paolo Bonzini *** Version 2.1.1 (stable) released. 2003-04-12 Paolo Bonzini *** Version 2.1 (stable) released. 2003-03-02 Paolo Bonzini * FTP.st: bring things back in good shape. * Base.st: likewise. * NNTP.st: do something to fix its most blatant brokenness. 2002-09-13 Paolo Bonzini *** Versions 2.0c (development) and 2.0.6 (stable) released * URIResolver.st: added WebEntity>>#stream and used it 2002-08-14 Paolo Bonzini *** Version 2.0.5 (stable) released 2002-08-12 Paolo Bonzini *** Version 2.0b (development) released * httpd/FileServer.st: accept POST requests * httpd/Load.st: load STT.st * httpd/STT.st: new file 2002-08-07 Paolo Bonzini *** Versions 2.0a (development) and 2.0.4 (stable) released 2002-07-17 Paolo Bonzini *** Version 2.0.3 released 2002-07-16 Paolo Bonzini * httpd/WebServer.st: support virtual hosting 2002-07-15 Paolo Bonzini * URL.st: now part of the base image 2002-07-11 Paolo Bonzini *** Version 2.0.2 released 2002-07-06 Paolo Bonzini * httpd/Load.st: adapt to namespaces * NetServer.st: use the new #waitForConnection method on ServerSocket. 2002-06-28 Paolo Bonzini *** Version 2.0.1 released 2002-06-25 Paolo Bonzini *** Version 2.0 released 2002-06-21 Paolo Bonzini * HTTP.st: done some refactory and added HTTP/1.1 support * POP.st: souped up POP3 support * ContentHandler.st: merged from TCP * URIResolver.st: use ContentHandler to guess MIME types * URL.st: merged some functionality from TCP's old URL.st 2002-06-20 Paolo Bonzini * Base.st: changed NetClient to NetProtocolInterpreter, moved NetClient here * IMAP.st: from IMAPClient * URIResolver.st: adapt to new class hierarchy * FTP.st: split FTPClient into two classes à la IMAP * SMTP.st: likewise * POP.st: likewise * HTTP.st: likewise * Base.st: moved reporter and user here * IMAP.st: from here * FTP.st: here * HTTP.st: and here * URIResolver.st: added some state, and saved some 100-character-long source code lines doing this 2002-06-19 Paolo Bonzini * URL.st: support URLs with both the fragment and the query parts, and store the user and password parts * URIResolver.st: fixed some bugs in the FTP and file implementation. Lowercased tag names, replace color entities (a legacy of SmallWalker) with style attributes. * HTTP.st: removed HTTPProfileSettings * URIResolver.st: moved here * URIResolver.st: WebEntity now delays loading the body from disk until it is requested; URIResolver loads it and removes the temporary file, if any. 2002-06-15 Paolo Bonzini * IMAP.st: fixed continuation responses -- passes the IMAPProtocolInterprerTest but I doubt that something so complicated works first time on a real IMAP server... 2002-06-14 Paolo Bonzini * MIME.st: drop the blank line after the headers; more fixes for IMAP * IMAP.st: some fixes, passes IMAPScannerTest and IMAPResponseTest * HTTP.st: basic functionality is in 2002-05-30 Paolo Bonzini * URIResolver.st: override appropriately the code installed by URL.st 2002-05-28 Paolo Bonzini * MIME.st: basic functionality is in * Base.st: code cleanup * FTP.st: code cleanup * HTTP.st: code cleanup * IMAP.st: code cleanup * Load.st: code cleanup * MIME.st: code cleanup * NNTP.st: code cleanup * NetServer.st: code cleanup * POP.st: code cleanup * SMTP.st: code cleanup * URIResolver.st: code cleanup * URL.st: code cleanup 2002-05-11 Paolo Bonzini *** Version 1.96.6 released 2002-04-14 Paolo Bonzini *** Version 1.96.5 released 2002-03-14 Paolo Bonzini * MIME.st: added accessors for common headers. * SMTP.st: more fixes. Must look up what method must be used to print headers, the rest is fine. 2002-03-12 Paolo Bonzini *** Version 1.96.4 released * FTP.st: some porting fixes make it work reasonably * POP.st: some porting fixes make it work reasonably, if it were not for MIME-handling bugs * MIME.st: some fixes make it work worse than earlier, but we're on the way :-) 2002-01-29 Paolo Bonzini *** Version 1.96.3 released. 2002-01-04 Paolo Bonzini *** Version 1.96.2 released 2002-01-02 Paolo Bonzini * Base.st: include TCP in NetworkClient's pool dictionary * NetServer.st: include TCP in NetworkServer's pool dictionary 2001-11-20 Paolo Bonzini *** Version 1.96.1 released 2001-11-13 Paolo Bonzini * httpd/WebServer.st: prefixed # to symbols in arrays * Base.st: implemented PrependDotStream and RemoveDotStream * RFC822.st: implemented #readFromClient: and the #print... methods 2001-10-31 Paolo Bonzini * MIME.st: new name of net/RFC822.st, implemented SimpleScanner to use lookahead instead of #skip:'ing on the source. 2001-10-26 Paolo Bonzini * URL.st: extracted from XML and NetKit.st * FTP.st: moved into separate namespace * SMTP.st: created from Mail.st, moved into separate namespace * POP.st: created from Mail.st, moved into separate namespace * NNTP.st: moved into separate namespace * URIResolver.st: from Agent.st, moved into separate namespace * HTTP.st: moved into separate namespace * Base.st: created from NetKit.st, moved into separate namespace * RFC822.st: moved into separate namespace 2001-04-11 Paolo Bonzini * FTP.st: adapted to ANSI exception handling * Mail.st: likewise * NNTP.st: likewise * Agent.st: likewise * HTTP.st: likewise * NetKit.st: likewise * RFC822.st: likewise 2001-04-07 Paolo Bonzini * httpd/FileServer.st: moved from web * httpd/WikiServer.st: moved from web * httpd/WebServer.st: moved from web * httpd/test.st: moved from web, use namespaces * httpd/Load.st: moved from web, use namespaces * NetServer.st: moved from web * FTP.st: created from Kazuki Yasumatsu's NetworkClients * Mail.st: created from Kazuki Yasumatsu's NetworkClients * NNTP.st: created from Kazuki Yasumatsu's NetworkClients * IMAP.st: created from Leslie Tyrrell's IMAP client framework, merged with NetworkClients * Agent.st: created from Kazuki Yasumatsu's NetworkClients * HTTP.st: created from Kazuki Yasumatsu's NetworkClients * Load.st: new file * NetKit.st: created from Kazuki Yasumatsu's NetworkClients * RFC822.st: created from Cincom's Internet Connectivity Toolkit 2001-02-23 Paolo Bonzini *** Released version 1.95.3 2001-01-30 Paolo Bonzini * FileServer.st: treat . and .. specially; don't list files for which the users has no read access. * NetServer.st: new file * WebServer.st: use NetServer.st's services * Load.st: load NetServer.st 2001-01-30 Paolo Bonzini *** Released version 1.95.1 2000-07-15 Paolo Bonzini * WebServer.st: #error -> #errorCode and #error: -> #errorCode: in ErrorResponse. Plus, support the If-Modified-Since request directly in WebResponse. * FileServer.st: call the superclass implementation of #sendStandardHeaders. 2000-07-10 Paolo Bonzini * WebServer.st: in #extractPostData: don't process data if the client specified an empty Content-Type. Terminate 100 (Continue) responses with a *double* line-feed. 2000-07-04 Paolo Bonzini * *.st: use the new DateTime and Duration classes 2000-06-17 Paolo Bonzini *** Released versions 1.95 (development) and 1.7.5 (stable) 2000-04-08 Paolo Bonzini * FileServer.st: implemented "Range:" (RangeResponse, MultiRangeResponse, RangeSpecification hierarchy) 2000-04-01 Paolo Bonzini * WikiServer.st: check for `.html' extension in the page URLs. 2000-03-23 Paolo Bonzini *** Version 1.7.3 released 2000-03-11 Paolo Bonzini *** Version 1.7.2 released 2000-03-02 Paolo Bonzini * Haiku.st: created * Load.st: load Haiku.st too smalltalk-3.2.5/packages/net/IMAPTests.st0000644000175000017500000004457012123404352015121 00000000000000"====================================================================== | | IMAP protocol unit tests | | ======================================================================" "====================================================================== | | Copyright (c) 2000 Leslie A. Tyrrell | Copyright (c) 2009 Free Software Foundation | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" Namespace current: NetClients.IMAP [ TestCase subclass: IMAPProtocolInterpreterTest [ | pi | setUp [ pi := IMAPProtocolInterpreter new. pi client: IMAPClient new ] testScript1 [ self executeCompleteTestScript: 'C: abcd CAPABILITY S: * CAPABILITY IMAP4rev1 AUTH=KERBEROS_V4 S: abcd OK CAPABILITY completed ' readStream ] testScript2 [ | stream | stream := 'C: A003 APPEND saved-messages (\Seen) {309} S: + Ready for additional command text C: Date: Mon, 7 Feb 1994 21:52:25 -0800 (PST) C: From: Fred Foobar C: Subject: afternoon meeting C: To: mooch@owatagu.siam.edu C: Message-Id: C: MIME-Version: 1.0 C: Content-Type: TEXT/PLAIN; CHARSET=US-ASCII C: C: Hello Joe, do you think we can meet at 3:30 tomorrow? C: 1234567 S: A003 OK APPEND completed' readStream. self executeCompleteTestScript: stream ] executeCompleteTestScript: aStream [ "Execute script respresenting complete execution of one or more commands. At the end of the script all commands must have been completed, so there will be no queued or outstanding commands and all returned commands will be in 'done' state" | cmds | cmds := self executeTestScript: aStream. cmds last value. "Wait for the last command" self assert: pi queuedCommands size = 0. self assert: pi commandsInProgress size = 0. cmds do: [:cmd | self assert: cmd isDone]. ^cmds ] executeTestScript: aStream [ "Execute script is the form: C: abcd CAPABILITY S: * CAPABILITY IMAP4rev1 AUTH=KERBEROS_V4 S: abcd OK CAPABILITY completed Lines starting with 'C: ' are client commands, lines starting with 'S: ' are server responses" | cmd cmdStream respStream line | cmdStream := (String new: 64) writeStream. respStream := (String new: 64) writeStream. [aStream atEnd] whileFalse: [cmd := aStream peek asUppercase. line := aStream next: 3; upTo: Character nl. cmd == $C ifTrue: [cmdStream nextPutAll: line; nl] ifFalse: [respStream nextPutAll: line; nl]]. pi responseStream: respStream contents readStream. ^self sendCommandsFrom: cmdStream contents readStream ] sendCommandFrom: stream [ | cmd | cmd := IMAPCommand readFrom: stream. cmd client: pi. pi executeCommand: cmd. ^cmd ] sendCommandsFrom: aStream [ "Assumption currently is, every command occupies one line. This is because IMAPComand>>readFrom reads until end of stream. So we will read command's line from the stream and feed it to the command as a separate stream. Answers ordered collection of commands sent" | cmds | cmds := OrderedCollection new. pi connectionStream: (String new: 256) writeStream. [aStream atEnd] whileFalse: [cmds addLast: (self sendCommandFrom: aStream)]. ^cmds ] ] ] Namespace current: NetClients.IMAP [ TestCase subclass: IMAPResponseTest [ testFetch [ | scanner resp str | str := '* 12 "FETCH" (BODY[HEADER] {341} Date: Wed, 17 Jul 1996 02:23:25 -0700 (PDT) From: Terry Gray Subject: IMAP4rev1 WG mtg summary and minutes To: imap@cac.washington.edu cc: minutes@CNRI.Reston.VA.US, John Klensin Message-Id: MIME-Version: 1.0 Content-Type: TEXT/PLAIN; CHARSET=US-ASCII )'. scanner := IMAPScanner on: str readStream. resp := IMAPResponse parse: scanner. self assert: (resp isKindOf: IMAPDataResponseFetch). self assert: resp cmdName = 'FETCH'. self assert: resp messageNumber = '12'. self assert: (resp bodyFetch parts isKindOf: SequenceableCollection). self assert: (resp bodyFetch parts allSatisfy: [:each | each sectionSpec specName = 'HEADER']) ] testResponseHandling [ | command str | command := (IMAPCommand new) sequenceID: 'a_1'; name: 'FETCH'; yourself. command client: IMAPProtocolInterpreter new. [command value] fork. self assert: (command handle: (IMAPResponse readFrom: '* FLAGS (\Seen \Answered \Deleted)' readStream)) not. self assert: (command handle: (IMAPResponse readFrom: 'a_2 OK bla' readStream)) not. self assert: command isDone not. str := '* 12 "FETCH" (BODY[HEADER] {341} Date: Wed, 17 Jul 1996 02:23:25 -0700 (PDT) From: Terry Gray Subject: IMAP4rev1 WG mtg summary and minutes To: imap@cac.washington.edu cc: minutes@CNRI.Reston.VA.US, John Klensin Message-Id: MIME-Version: 1.0 Content-Type: TEXT/PLAIN; CHARSET=US-ASCII )'. self assert: (command handle: (IMAPResponse readFrom: str readStream)). self assert: (command handle: (IMAPResponse readFrom: 'a_1 OK FETCH completed' readStream)). self assert: command isDone. self assert: command completionResponse status = 'OK'. self assert: command promise hasValue ] testTaggedMessages [ | scanner resp | scanner := IMAPScanner on: 'oasis_1 OK LOGIN completed' readStream. resp := IMAPResponse parse: scanner. self assert: (resp isKindOf: IMAPResponseTagged). self assert: resp tag = 'oasis_1'. self assert: resp status = 'OK'. self assert: resp text = 'LOGIN completed' ] testUnTaggedMessages [ | scanner resp | scanner := IMAPScanner on: '* FLAGS (\Seen \Answered \Deleted)' readStream. resp := IMAPResponse parse: scanner. self assert: resp cmdName = 'FLAGS'. self assert: resp value first = #('\Seen' '\Answered' '\Deleted') ] ] ] Namespace current: NetClients.IMAP [ TestCase subclass: IMAPTest [ | client | login [ "establish a socket connection to the IMAP server and log me in" client := IMAPClient loginToHost: 'SKIPPER' asUser: 'itktest' withPassword: 'Cincom*062000'. self assert: (client isKindOf: IMAPClient) ] logout [ client logout ] testAppend [ | message | self login. message := 'Date: Mon, 7 Feb 1994 21:52:25 -0800 (PST) From: Fred Foobar Subject: afternoon meeting To: mooch@owatagu.siam.edu Message-Id: MIME-Version: 1.0 Content-Type: TEXT/PLAIN; CHARSET=US-ASCII Hello Joe, do you think we can meet at 3:30 tomorrow?'. client append: message to: 'inbox'. self logout ] testCreateRenameDelete [ | comm box box1 | box := 'mybox'. box1 := 'myBoxRenamed'. self login. [comm := client create: box. self assert: (comm isKindOf: IMAPCommand). self assert: comm completedSuccessfully. comm := client rename: box newName: box1. self assert: (comm isKindOf: IMAPCommand). self assert: comm completedSuccessfully] ensure: [client delete: box1. self logout] ] testExamine [ | box comm | self login. box := 'inbox'. comm := client examine: box. self assert: (comm isKindOf: IMAPCommand). self assert: comm completedSuccessfully. self logout ] testList [ "box := nil. box isNil ifTrue:[ ^nil]." | box comm | self login. [box := 'news/mail/box' asString. comm := client create: box. self assert: (comm isKindOf: IMAPCommand). self assert: comm completedSuccessfully. comm := client list: 'news/' mailbox: 'mail/*'. self assert: (comm isKindOf: IMAPCommand). self assert: comm completedSuccessfully. self assert: comm responses first mbName asUppercase = box asUppercase] ensure: [comm := client delete: box]. self logout ] testNoopCapability [ | comm | self login. comm := client noop. self assert: (comm isKindOf: IMAPCommand). self assert: comm completedSuccessfully. comm := client capability. self assert: (comm isKindOf: IMAPCommand). self assert: comm completedSuccessfully. self logout ] testSelectCheck [ "box := nil. box isNil ifTrue:[ ^nil]." | box comm | self login. [box := 'news/mail/box' asString. comm := client create: box. self assert: (comm isKindOf: IMAPCommand). self assert: comm completedSuccessfully. comm := client select: box. self assert: (comm isKindOf: IMAPCommand). self assert: comm completedSuccessfully. comm := client check. self assert: (comm isKindOf: IMAPCommand). self assert: comm completedSuccessfully] ensure: [comm := client delete: box] ] testSelectClose [ "box := nil. box isNil ifTrue:[ ^nil]." | box comm | self login. [box := 'news/mail/box' asString. comm := client create: box. self assert: (comm isKindOf: IMAPCommand). self assert: comm completedSuccessfully. comm := client select: box. self assert: (comm isKindOf: IMAPCommand). self assert: comm completedSuccessfully. comm := client close. self assert: (comm isKindOf: IMAPCommand). self assert: comm completedSuccessfully] ensure: [comm := client delete: box] ] testSelectExpunge [ "Test case doesn't return untagged response: EXPUNGE as expected" "box := nil. box isNil ifTrue:[ ^nil]." | box comm | self login. box := 'inbox' asString. comm := client select: box. self assert: (comm isKindOf: IMAPCommand). self assert: comm completedSuccessfully. comm := client expunge. self assert: (comm isKindOf: IMAPCommand). self assert: comm completedSuccessfully ] testSelectFetch [ | box comm | self login. box := 'inbox' asString. client select: box. comm := client fetch: '2:3 (flags internaldate uid RFC822)'. self assert: (comm isKindOf: IMAPCommand). self assert: comm completedSuccessfully. "comm := client fetch: '2,4 (flags internaldate uid BODY.PEEK[header])'." "client fetch: '1:4 (uid Body.Peek[Header.Fields (Subject Date From Message-Id)])'." "client fetch: '1:2 (flags internaldate uid RFC822)'." "client fetch: '1 (Body.Peek[header])'." "comm := client fetch: '3 (BodyStructure)'." "client fetch: '2 full'." self logout ] testSelectSearch [ "box := nil. box isNil ifTrue: [ ^box]." | box | self login. box := 'inbox' asString. client select: box. client search: 'undeleted unanswered from "Kogan, Tamara"'. self logout ] testSelectStore [ "| box | self login. box := 'inbox' asString. self assert: ((client select: box) == true). (client store: '1:1 +FLAGS (\Deleted)') inspect. (client store: '1:1 -FLAGS (\Deleted)') inspect. self logout." ] testSelectUID [ "No expected response | box | self login. box := 'inbox' asString. self assert: ((client select: box) == true). (client uid: 'fetch 1:1 FLAGS') inspect. self logout." ] testSubscribeUnsubLSUB [ | box comm | box := nil. box isNil ifTrue: [^nil]. self login. [box := 'news/mail/box' asString. comm := client create: box. self assert: (comm isKindOf: IMAPCommand). self assert: comm completedSuccessfully. comm := client subscribe: box. self assert: (comm isKindOf: IMAPCommand). self assert: comm completedSuccessfully. comm := client lsub: 'news/' mailbox: 'mail/*'. self assert: (comm isKindOf: IMAPCommand). self assert: comm completedSuccessfully. self assert: comm responses first mbName asUppercase = box asUppercase. comm := client unsubscribe: box. self assert: (comm isKindOf: IMAPCommand). self assert: comm completedSuccessfully] ensure: [comm := client delete: box]. self logout ] ] ] Namespace current: NetClients.IMAP [ TestCase subclass: IMAPScannerTest [ | parser | setUp [ parser := IMAPScanner new ] stream6 [ | str | str := (String new: 512) writeStream. str nextPutAll: '* 12 FETCH (FLAGS (\Seen) INTERNALDATE "17-Jul-1996 02:44:25 -0700" RFC822.SIZE 4286 ENVELOPE ("Wed, 17 Jul 1996 02:23:25 -0700 (PDT)" "IMAP4rev1 WG mtg summary and minutes" (("Terry Gray" NIL "gray" "cac.washington.edu")) (("Terry Gray" NIL "gray" "cac.washington.edu")) (("Terry Gray" NIL "gray" "cac.washington.edu")) ((NIL NIL "imap" "cac.washington.edu")) ((NIL NIL "minutes" "CNRI.Reston.VA.US") ("John Klensin" NIL "KLENSIN" "INFOODS.MIT.EDU")) NIL NIL "") BODY ("TEXT" "PLAIN" ("CHARSET" "US-ASCII") NIL NIL "7BIT" 3028 92)) '; nl. ^str ] testDeepTokenize [ | tokens | tokens := parser on: '* FLAGS (\Seen \Answered \Flagged \Deleted XDraft)' readStream; deepTokenize. self assert: tokens = #($* 'FLAGS' #('\Seen' '\Answered' '\Flagged' '\Deleted' 'XDraft')). self assert: parser atEnd ] testDeepTokenize1 [ | tokens | tokens := parser on: '(BODYSTRUCTURE (("TEXT" "PLAIN" ("charset" "iso-8859-1") NIL nil "QUOTED-PRINTABLE" 7 2 NIL NIL NIL)("APPLICATION" "OCTET-STREAM" ("name" "StoreErrorDialog.st") NiL NIL "BASE64" 4176 NIL NIL NIL) "mixed" ("boundary" "=_STAMPed_MAIL_=") NIL NIL))' readStream; deepTokenize. self assert: tokens = #(#('BODYSTRUCTURE' #(#('TEXT' 'PLAIN' #('charset' 'iso-8859-1') nil nil 'QUOTED-PRINTABLE' '7' '2' nil nil nil) #('APPLICATION' 'OCTET-STREAM' #('name' 'StoreErrorDialog.st') nil nil 'BASE64' '4176' nil nil nil) 'mixed' #('boundary' '=_STAMPed_MAIL_=') nil nil))). self assert: parser atEnd. tokens := parser on: '(BODYSTRUCTURE (("TEXT" "PLAIN" ("charset" "iso-8859-1") NIL NIL "QUOTED-PRINTABLE" 7 2 NIL NIL NIL)("APPLICATION" "OCTET-STREAM" ("name" "StoreErrorDialog.st") NIL NIL "BASE64" 4176 NIL NIL NIL) "mixed" ("boundary" "=_STAMPed_MAIL_=") NIL NIL))' readStream; deepTokenizeAsAssociation ] testDeepTokenizeAsAssoc [ | tokens str | str := '* 12 "FETCH" ((a b nil) BODY[HEADER] {341} Date: Wed, 17 Jul 1996 02:23:25 -0700 (PDT) From: Terry Gray Subject: IMAP4rev1 WG mtg summary and minutes To: imap@cac.washington.edu cc: minutes@CNRI.Reston.VA.US, John Klensin Message-Id: MIME-Version: 1.0 Content-Type: TEXT/PLAIN; CHARSET=US-ASCII )'. tokens := parser on: str readStream; deepTokenizeAsAssociation. self assert: tokens first = (#special -> $*). self assert: (tokens at: 2) = (#atom -> '12'). self assert: (tokens at: 3) = (#quotedText -> 'FETCH'). self assert: (tokens at: 4) = (#parenthesizedList -> (Array with: #parenthesizedList -> (Array with: #atom -> 'a' with: #atom -> 'b' with: #nil -> nil) with: #atom -> 'BODY[HEADER]' with: #literalString -> 'Date: Wed, 17 Jul 1996 02:23:25 -0700 (PDT) From: Terry Gray Subject: IMAP4rev1 WG mtg summary and minutes To: imap@cac.washington.edu cc: minutes@CNRI.Reston.VA.US, John Klensin Message-Id: MIME-Version: 1.0 Content-Type: TEXT/PLAIN; CHARSET=US-ASCII ')). self assert: parser atEnd ] testLiteralStrings [ | tokens str | str := '* 12 FETCH (BODY[HEADER] {341} Date: Wed, 17 Jul 1996 02:23:25 -0700 (PDT) From: Terry Gray Subject: IMAP4rev1 WG mtg summary and minutes To: imap@cac.washington.edu cc: minutes@CNRI.Reston.VA.US, John Klensin Message-Id: MIME-Version: 1.0 Content-Type: TEXT/PLAIN; CHARSET=US-ASCII )'. "Extra char for every cr -- will be different in external streams" tokens := parser on: str readStream; deepTokenize. self assert: tokens = #($* '12' 'FETCH' #('BODY[HEADER]' 'Date: Wed, 17 Jul 1996 02:23:25 -0700 (PDT) From: Terry Gray Subject: IMAP4rev1 WG mtg summary and minutes To: imap@cac.washington.edu cc: minutes@CNRI.Reston.VA.US, John Klensin Message-Id: MIME-Version: 1.0 Content-Type: TEXT/PLAIN; CHARSET=US-ASCII ')). self assert: parser atEnd ] testSourceTrail [ | str trail | str := '* 12 "FETCH" (BODY[HEADER] {341} Date: Wed, 17 Jul 1996 02:23:25 -0700 (PDT) From: Terry Gray Subject: IMAP4rev1 WG mtg summary and minutes To: imap@cac.washington.edu cc: minutes@CNRI.Reston.VA.US, John Klensin Message-Id: MIME-Version: 1.0 Content-Type: TEXT/PLAIN; CHARSET=US-ASCII )'. parser on: str readStream; sourceTrailOn; deepTokenizeAsAssociation. trail := parser sourceTrail. self assert: trail = str. self assert: parser sourceTrail isNil. self assert: parser atEnd ] testTaggedResponses [ | tokens | tokens := parser on: 'oasis_3 OK FETCH completed.' readStream; tokenize. self assert: tokens = #('oasis_3' 'OK' 'FETCH' 'completed.'). self assert: parser atEnd ] ] ] smalltalk-3.2.5/packages/net/URIResolver.st0000644000175000017500000011512312123404352015522 00000000000000"====================================================================== | | URL resolving and on-disk storage support | | ======================================================================" "====================================================================== | | Based on code copyright (c) Kazuki Yasumatsu, and in the public domain | Copyright (c) 2002, 2008 Free Software Foundation, Inc. | Adapted by Paolo Bonzini. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" Object subclass: URIResolver [ | url reporter noCache client entity | URIResolver class >> openOn: aURI ifFail: aBlock [ "Check if aURI can be fetched from the Internet or from the local system, and if so return a WebEntity with its contents. If this is not possible, instead, evaluate the zero-argument block aBlock and answer the result of the evaluation." | url body entity | url := aURI. (url respondsTo: #key) ifTrue: [url := url key , ':/' , url value]. url isString ifTrue: [url := URL fromString: url]. [entity := (self on: url) noCache: true; contentsNoSignal] on: ProtocolError do: [:sig | sig return: aBlock value] on: Error do: [:sig | sig return: aBlock value]. ^entity ] URIResolver class >> openStreamOn: aURI ifFail: aBlock [ "Check if aURI can be fetched from the Internet or from the local system, and if so return a Stream with its contents. If this is not possible, instead, evaluate the zero-argument block aBlock and answer the result of the evaluation." | entity | entity := self openOn: aURI ifFail: [^aBlock value]. ^entity stream ] defaultHeaders [ "The default headers for HTTP like requests" | requestHeaders | requestHeaders := OrderedCollection new. requestHeaders add: 'User-Agent: GNU-Smalltalk/' , Smalltalk version. requestHeaders add: 'Accept: text/html, image/gif, */*; q=0.2'. requestHeaders add: 'Host: ' , url host. noCache ifTrue: [requestHeaders add: 'Pragma: no-cache']. ^ requestHeaders ] connectClient [ | host | host := url host isNil ifTrue: [SocketAddress localHostName] ifFalse: [url host]. self connectClientToHost: host port: url port ] connectClientToHost: host port: port [ client closed ifFalse: [client close]. client hostName: host; portNumber: port; connect ] connect [ client reporter: self reporter. url username isNil ifFalse: [client username: url username password: url password]. client reporter statusString: 'Connecting'. [client connect] on: ConnectionFailedError do: [:ex | ^self errorContents: ex tag] ] noCache [ noCache isNil ifTrue: [noCache := false]. ^noCache ] noCache: aBoolean [ noCache := aBoolean ] reporter [ ^reporter ] reporter: aReporter [ reporter := aReporter. client isNil ifFalse: [client reporter: self reporter] ] entity [ ^entity ] contentsNoSignal [ | scheme contents | (entity notNil and: [noCache not]) ifTrue: [^entity]. url hasPostData ifTrue: [contents := (MimeEntity new) addField: ContentTypeField urlEncoded; body: url postData; yourself. ^self postContentsNoSignal: contents]. scheme := url scheme. scheme = 'http' ifTrue: [client := HTTP.HTTPClient new. ^entity := self getHttpContents]. scheme = 'https' ifTrue: [client := HTTP.HTTPClient new. client isSSL: true. ^entity := self getHttpContents]. scheme = 'ftp' ifTrue: [client := FTP.FTPClient new. ^entity := self getFtpContents]. scheme = 'news' ifTrue: [client := NNTP.NNTPClient new. ^entity := self getNewsContents]. scheme = 'nntp' ifTrue: [client := NNTP.NNTPClient new. ^entity := self getNntpContents]. url isFileScheme ifTrue: [^entity := self getFileContents]. ^self errorContents: 'Unsupported protocol' ] contents [ | messageText | [^self contentsNoSignal] on: Error do: [:ex | messageText := ex messageText. ex return]. ^self errorContents: messageText ] getHeadNoSignal [ | scheme | url hasPostData ifTrue: [^self errorContents: 'Unsupported post']. scheme := url scheme. scheme = 'http' ifTrue: [client := HTTP.HTTPClient new. ^self getHttpHead]. scheme = 'https' ifTrue: [client := HTTP.HTTPClient new. client isSSL: true. ^self getHttpHead]. ^self errorContents: 'Unsupported protocol' ] getHead [ | messageText | [^self getHeadNoSignal] on: Error do: [:ex | messageText := ex messageText. ex return]. ^self errorContents: messageText ] postContents: contents [ | messageText | [^self postContentNoSignal: contents] on: Error do: [:ex | messageText := ex messageText. ex return]. ^self errorContents: messageText "^self postContentsNoSignal: contents" ] postContentsNoSignal: contents [ | scheme | scheme := url scheme. scheme = 'http' ifTrue: [client := HTTP.HTTPClient new. ^self postHttpContents: contents]. scheme = 'https' ifTrue: [client := HTTP.HTTPClient new. client isSSL: true. ^self postHttpContents: contents]. ^self errorContents: 'Unsupported protocol' ] getDirectoryContentsOf: aDirectory [ | maxSize stream title contents | maxSize := 32. stream := ReadWriteStream on: (String new: 512). title := 'Directory listing of ' , aDirectory fullName. stream nextPutAll: 'Content-type: text/html ' , title , '

      ' , title , '

      '. stream nextPutAll: '
      ';
      	    nl.
      	stream 
      	    nextPutAll: ''.
      	stream
      	    nextPutAll: 'Up to higher level directory';
      	    nl;
      	    nl.
      	aDirectory entryNames asSortedCollection do: 
      		[:name | 
      		| file isDirectory fileSize |
      		file := aDirectory at: name.
      		
      		[isDirectory := file isDirectory.
      		fileSize := file size] on: Error
      			do: 
      			    [:ex | 
      			    isDirectory := false.
      			    fileSize := 0.
      			    ex return].
      		stream
      		    tab;
      		    nextPutAll: ''.
      		stream
      		    nextPutAll: name;
      		    nextPutAll: ''.
      		name size <= maxSize 
      		    ifFalse: 
      			[stream
      			    nl;
      			    tab;
      			    next: maxSize put: $ ]
      		    ifTrue: [stream next: maxSize - name size put: $ ].
      		fileSize := fileSize printString.
      		fileSize size < 8 ifTrue: [stream next: 8 - fileSize size put: $ ].
      		stream
      		    nextPutAll: fileSize;
      		    nextPutAll: ' bytes'.
      		stream nl].
      	stream
      	    nextPutAll: '
      '; nl. stream nextPutAll: ' '. stream reset. ^(WebEntity readFrom: stream) url: url; canCache: false; yourself ] getFileContents [ | file result | file := File name: (url path ifNil: '/'). file exists ifFalse: [^self errorContents: 'No such file']. file isReadable ifFalse: [^self errorContents: 'Cannot read']. file isDirectory ifTrue: [^self getDirectoryContentsOf: file]. ^(WebEntity new) url: url; canCache: false; localFileName: url path; guessMimeType; yourself ] getFtpContents [ | contents path tmpFile type stream | contents := self getProxyContentsHost: 'ftpProxyHost' port: 'ftpProxyPort'. contents notNil ifTrue: [^contents]. self connectClient. [| user mail | user := NetUser new. url username isNil ifTrue: [user username: 'anonymous'] ifFalse: [user username: url username]. url password isNil ifTrue: ["Anonymous FTP, send e-mail address as password" mail := UserProfileSettings default settingAt: #mailAddress. (mail isNil or: ['*@*.*' match: mail]) ifTrue: [mail := 'gst@']. user password: mail] ifFalse: [user password: url password]. client user: user; login] on: NetClientError do: [:ex | client close. ^self errorContents: ex tag]. client reporter statusString: 'Connect: Host contacted. Waiting for reply...'. (url path isNil or: [url path isEmpty]) ifTrue: [path := '/'] ifFalse: [path := url path]. stream := self tmpFile. tmpFile := stream file. ^ [ [client getFile: path type: #binary into: stream] ensure: [stream close]. (WebEntity new) url: url; canCache: false; localFileName: tmpFile name; guessMimeType; yourself] on: NetClientError do: [:ex | ^self errorContents: ex messageText] on: FTP.FTPFileNotFoundError do: [:ex | tmpFile exists ifTrue: [tmpFile remove]. stream := ReadWriteStream on: (String new: 512). ^ [(path at: path size) = '/' ifFalse: [path := path copyWith: $/]. client getList: path into: stream. stream reset. self getFtpDirectoryContentsFrom: stream] on: FTP.FTPFileNotFoundError do: [:ex | ^self errorContents: ex messageText]] ] getFtpDirectoryContentsFrom: aStream [ | baseURL maxSize stream title contents sp read mode ftype fileSize name newURL index | baseURL := url copy. baseURL path isNil ifTrue: [baseURL path: '/junk'] ifFalse: [baseURL path: (File append: 'junk' to: baseURL path)]. maxSize := 32. stream := ReadWriteStream on: (String new: 512). title := 'Directory listing of ' , url printString. stream nextPutAll: 'Content-type: text/html ' , title , '

      ' , title , '

      '. "-rwxr-xr-x 1 user group 512 Aug 8 05:57 file" "drwxr-xr-x 1 user group 512 Aug 8 05:57 directory" "lrwxrwxrwx 1 user group 512 Aug 8 05:57 symlink" "brwxr-xr-x 1 user group 0, 1 Aug 8 05:57 block-device" "crwxr-xr-x 1 user group 1, 2 Aug 8 05:57 character-device" "p--------- 1 user group 0 Aug 8 05:57 pipe" stream nextPutAll: '
      ';
      	    nl.
      	baseURL path isNil 
      	    ifFalse: 
      		[stream
      		    nextPutAll: ''].
      	stream
      	    nextPutAll: 'Up to higher level directory';
      	    nl;
      	    nl.
      	[aStream atEnd] whileFalse: 
      		[sp := Character space.
      		read := (aStream upTo: Character nl) readStream.
      		mode := read upTo: sp.
      		mode isEmpty ifTrue: [ftype := nil] ifFalse: [ftype := mode first].
      		read skipSeparators.
      		read upTo: sp.	"nlink"
      		read skipSeparators.
      		read upTo: sp.	"user"
      		read skipSeparators.
      		read upTo: sp.	"group"
      		read skipSeparators.
      		(ftype = $b or: [ftype = $c]) 
      		    ifTrue: 
      			[fileSize := '0'.
      			read upTo: sp.	"major"
      			read skipSeparators.
      			read upTo: sp	"minor"]
      		    ifFalse: [fileSize := read upTo: sp].
      		read skipSeparators.
      		read upTo: sp.	"month"
      		read skipSeparators.
      		read upTo: sp.	"day"
      		read skipSeparators.
      		read upTo: sp.	"time"
      		read skipSeparators.
      		name := read upToEnd trimSeparators.
      		(ftype isNil or: [name isEmpty or: [name = '.' or: [name = '..']]]) 
      		    ifFalse: 
      			[ftype = $l 
      			    ifTrue: 
      				["symbolic link"
      
      				index := name indexOfSubCollection: ' -> ' startingAt: 1.
      				index > 0 
      				    ifTrue: 
      					[newURL := baseURL 
      						    construct: (URL fromString: (name copyFrom: index + 4 to: name size)).
      					name := name copyFrom: 1 to: index - 1]
      				    ifFalse: [newURL := baseURL construct: (URL fromString: name)]]
      			    ifFalse: 
      				[(ftype = $- or: [ftype = $d]) 
      				    ifTrue: [newURL := baseURL construct: (URL fromString: name)]
      				    ifFalse: [newURL := nil]].
      			stream tab.
      			newURL isNil 
      			    ifTrue: [stream nextPutAll: ''.
      			name size <= maxSize 
      			    ifTrue: 
      				[stream nextPutAll: name.
      				newURL isNil ifFalse: [stream nextPutAll: ''].
      				maxSize - name size timesRepeat: [stream space]]
      			    ifFalse: 
      				[stream nextPutAll: name.
      				newURL isNil ifFalse: [stream nextPutAll: ''].
      				stream
      				    nl;
      				    tab.
      				maxSize timesRepeat: [stream space]].
      			fileSize size < 8 ifTrue: [8 - fileSize size timesRepeat: [stream space]].
      			stream
      			    nextPutAll: fileSize;
      			    nextPutAll: ' bytes'.
      			stream nl]].
      	stream
      	    nextPutAll: '
      '; nl. stream nextPutAll: ' '. stream reset. ^(WebEntity readFrom: stream) url: url; canCache: false; yourself ] getHttpContents [ | contents urlString | contents := self getProxyContentsHost: 'httpProxyHost' port: 'httpProxyPort'. contents notNil ifTrue: [^contents]. self connectClient. ^self requestHttpContents: url requestString ] doHTTPRequest: requestBlock onSuccess: successBlock [ | requestHeaders tmpFile stream protocolError response string | requestHeaders := self defaultHeaders. client reporter statusString: 'Connecting'. protocolError := false. client reporter statusString: 'Connect: Host contacted. Waiting for reply...'. stream := self tmpFile. tmpFile := stream file. [ [ [response := requestBlock value: requestHeaders value: stream] ensure: [client close]] on: ProtocolError do: [:ex | protocolError := true. ex pass] on: NetClientError do: [:ex | ^self errorContents: ex messageText] on: HTTP.HTTPRedirection do: [:ex | | location | location := ex location. client reporter statusString: 'Redirecting'. stream close. stream := nil. tmpFile exists ifTrue: [tmpFile remove]. ^(self class on: (url construct: (URL fromString: location))) noCache: self noCache; reporter: self reporter; contents]] ensure: [stream isNil ifFalse: [stream close]]. ^protocolError ifTrue: [string := tmpFile contents. tmpFile remove. (WebEntity new) body: string; url: url; canCache: false; guessMimeType; yourself] ifFalse: [|ent | ent := (WebEntity new) url: url; localFileName: tmpFile name; canCache: noCache not; guessMimeType; yourself. successBlock value: ent. ent] ] requestHttpContents: urlString [ ^ self doHTTPRequest: [:requestHeaders :stream | client get: urlString requestHeaders: requestHeaders into: stream] onSuccess: [:ent | ] ] getHttpHead [ | contents | contents := self getProxyHeadHost: 'httpProxyHost' port: 'httpProxyPort'. contents notNil ifTrue: [^contents]. self connectClient. ^self requestHttpHead: url requestString ] requestHttpHead: urlString [ | requestHeaders tmpFile stream protocolError response string | requestHeaders := self defaultHeaders. client reporter statusString: 'Connecting'. client reporter statusString: 'Connect: Host contacted. Waiting for reply...'. stream := self tmpFile. tmpFile := stream file. protocolError := false. [ [ [response := client head: urlString requestHeaders: requestHeaders into: stream] ensure: [client close]] on: ProtocolError do: [:ex | protocolError := true. ex pass] on: NetClientError do: [:ex | ^self errorContents: ex messageText] on: HTTP.HTTPRedirection do: [:ex | | location | location := ex location. client reporter statusString: 'Redirecting'. stream close. stream := nil. tmpFile exists ifTrue: [tmpFile remove]. ^(self class on: (url construct: (URL fromString: location))) noCache: self noCache; reporter: self reporter; getHead]] ensure: [stream isNil ifFalse: [stream close]]. ^protocolError ifTrue: [string := tmpFile contents. tmpFile remove. (WebEntity new) body: string; url: url; canCache: false; guessMimeTypeFromResponse: response; yourself] ifFalse: [(WebEntity new) url: url; canCache: false; localFileName: tmpFile name; guessMimeTypeFromResponse: response; yourself] ] postHttpContents: contents [ | replyContents | replyContents := self postProxyContents: contents host: 'httpProxyHost' port: 'httpProxyPort'. replyContents notNil ifTrue: [^replyContents]. self connectClient. ^self postHttpContents: contents urlString: url requestString ] postHttpContents: contents urlString: urlString [ ^ self doHTTPRequest: [:requestHeaders :stream | client post: urlString type: contents type data: contents asStringOrByteArray binary: contents isBinary requestHeaders: requestHeaders into: stream] onSuccess: [:ent | ent canCache: false ] ] emptyMessage [ | message address fields subject references | message := MimeEntity new. address := self defaultMailAddress. message parseFieldFrom: ('From: ' , address) readStream. url query isNil ifFalse: [fields := url decodedFields. subject := fields at: 'subject' ifAbsent: [nil]. subject isNil ifFalse: [message parseFieldFrom: ('Subject: ' , subject displayString) readStream]. references := fields at: 'references' ifAbsent: [nil]. references isNil ifFalse: [message parseFieldFrom: ('References: ' , references displayString) readStream]]. ^message ] emptyMailMessage [ | message to | message := self emptyMessage. to := url path. to isNil ifFalse: [message parseFieldFrom: ('To: ' , to) readStream]. message parseFieldFrom: ('X-Mailer: GNU-Smalltalk/' , Smalltalk version) readStream. ^message ] getNewsArticleContents: articleId [ | tmpFile stream contents | stream := self tmpFile. tmpFile := stream file. [ [client articleAt: '<' , articleId , '>' into: stream. client quit] ensure: [stream close. client close]] on: NetClientError do: [:ex | tmpFile exists ifTrue: [tmpFile remove]. ^self errorContents: ex messageText]. ^(WebEntity readFrom: tmpFile contents type: 'message/news') url: url; canCache: false; localFileName: tmpFile name; yourself ] getNewsArticleContents: articleNo group: group [ | tmpFile stream contents | stream := self tmpFile. tmpFile := stream file. [ [client articleAtNumber: articleNo group: group into: stream. client quit] ensure: [stream close. client close]] on: NetClientError do: [:ex | tmpFile exists ifTrue: [tmpFile remove]. ^self errorContents: ex messageText]. ^(WebEntity readFrom: tmpFile contents type: 'message/news') url: url; canCache: false; localFileName: tmpFile name; yourself ] getNewsArticleList: from to: to group: group [ | subjects index | subjects := Array new: to - from + 1. index := 0. client subjectsOf: group from: from to: to do: [:n :subject | subjects at: (index := index + 1) put: (Array with: n with: subject)]. index = 0 ifTrue: [^Array new]. index < subjects size ifTrue: [subjects := subjects copyFrom: 1 to: index]. ^subjects ] getNewsArticleListContents: group [ | maxRange range from to prevRanges subjects stream pto pfrom | maxRange := 100. range := client activeArticlesInGroup: group. from := range first. to := range last. prevRanges := OrderedCollection new. to - from + 1 > maxRange ifTrue: [pfrom := from. from := to - maxRange + 1. pto := from - 1. [pto - pfrom + 1 > maxRange] whileTrue: [prevRanges addFirst: (pto - maxRange + 1 to: pto). pto := pto - maxRange]. prevRanges addFirst: (pfrom to: pto)]. subjects := self getNewsArticleList: from to: to group: group. client quit; close. stream := ReadWriteStream on: (String new: 80 * subjects size). stream nextPutAll: 'Content-type: text/html'; nl; nl; nextPutAll: ''; nl; nextPutAll: 'Newsgroup: ' , group , ''; nl; nextPutAll: '

      Newsgroup: ' , group , '

      '; nl. prevRanges isEmpty ifFalse: [stream nextPutAll: '
      '; nl; nextPutAll: 'Previous articles'; nl; nextPutAll: ''; nl; nextPutAll: '
      '; nl]. subjects isEmpty ifFalse: [stream nextPutAll: '
        '; nl. subjects do: [:array | | n subject | n := array at: 1. subject := array at: 2. stream nextPutAll: '
      • '; nl; nextPutAll: subject , '
      • '; nl]. stream nextPutAll: '
      '; nl]. stream nextPutAll: ''; nl. stream reset. ^(WebEntity readFrom: stream) url: url ] getNewsArticleListContents: from to: to group: group [ | subjects stream | subjects := self getNewsArticleList: from to: to group: group. client quit; close. stream := ReadWriteStream on: (String new: 80 * subjects size). stream nextPutAll: 'Content-type: text/html'; nl; nl; nextPutAll: ''; nl; nextPutAll: 'Newsgroup: ' , group , ' (' , from printString , '-' , to printString , ')'; nl; nextPutAll: '

      Newsgroup: ' , group , ' (' , from printString , '-' , to printString , ')

      '; nl. subjects isEmpty ifFalse: [stream nextPutAll: '
        '; nl. subjects do: [:array | | n subject | n := array at: 1. subject := array at: 2. stream nextPutAll: '
      • '; nl; nextPutAll: subject , '
      • '; nl]. stream nextPutAll: '
      '; nl]. stream nextPutAll: ''; nl. stream reset. ^(WebEntity readFrom: stream) url: url ] getNewsContents [ | host string | (url hasFragment or: [url hasQuery]) ifTrue: [^self invalidURL]. host := url host. host isNil ifTrue: [host := UserProfileSettings default settingAt: #nntpHost ifAbsent: [nil]]. host isNil ifTrue: [^self invalidURL]. string := url path. string isNil ifTrue: [^self invalidURL]. self connectClient. [ [(string indexOf: $@) > 0 ifTrue: ["may be article" ^self getNewsArticleContents: string] ifFalse: ["may be newsgroup" ^self getThreadedNewsArticleListContents: string]] ensure: [client close]] on: NetClientError do: [:ex | ^self errorContents: ex messageText] ] getNntpContents [ | host string read group from to | (url hasFragment or: [url hasPostData]) ifTrue: [^self invalidURL]. host := url host. host isNil ifTrue: [host := UserProfileSettings default settingAt: #nntpHost ifAbsent: [nil]]. host isNil ifTrue: [^self invalidURL]. string := url path. string isNil ifTrue: [^self invalidURL]. read := string readStream. read atEnd ifTrue: [^self invalidURL]. read peek = $/ ifTrue: [read next]. group := read upTo: $/. url hasQuery ifTrue: [read := url query readStream. read atEnd ifTrue: [^self invalidURL]. from := Integer readFrom: read. from = 0 ifTrue: [^self invalidURL]. read next = $- ifFalse: [^self invalidURL]. to := Integer readFrom: read. to = 0 ifTrue: [^self invalidURL]] ifFalse: [read atEnd ifTrue: [^self invalidURL]. from := Integer readFrom: read. from = 0 ifTrue: [^self invalidURL]. to := nil]. self connectClient. ^ [ [to isNil ifTrue: [self getNewsArticleContents: from group: group] ifFalse: [self getThreadedNewsArticleListContents: from to: to group: group]] ensure: [client close]] on: NetClientError do: [:ex | ^self errorContents: ex messageText] ] getThreadedNewsArticleList: from to: to group: group [ | subjects threads | subjects := self getNewsArticleList: from to: to group: group. threads := Dictionary new. subjects do: [:array | | read stream head tname col | read := (array at: 2) readStream. stream := WriteStream on: (String new: read size). [read skipSeparators. head := read nextAvailable: 3. 'Re:' sameAs: head] whileTrue: []. stream nextPutAll: head; nextPutAll: read. tname := stream contents. col := threads at: tname ifAbsent: [nil]. col notNil ifTrue: [col add: array] ifFalse: [col := SortedCollection sortBlock: [:x :y | | xn yn xsize ysize | xn := x at: 1. yn := y at: 1. xsize := (x at: 2) size. ysize := (y at: 2) size. xsize = ysize ifTrue: [xn <= yn] ifFalse: [xsize <= ysize]]. col add: array. threads at: tname put: col]]. ^threads ] getThreadedNewsArticleListContents: group [ | maxRange range from to prevRanges threads stream pto pfrom | maxRange := 100. range := client activeArticlesInGroup: group. from := range first. to := range last. prevRanges := OrderedCollection new. to - from + 1 > maxRange ifTrue: [pfrom := from. from := to - maxRange + 1. pto := from - 1. [pto - pfrom + 1 > maxRange] whileTrue: [prevRanges addFirst: (pto - maxRange + 1 to: pto). pto := pto - maxRange]. prevRanges addFirst: (pfrom to: pto)]. threads := self getThreadedNewsArticleList: from to: to group: group. client quit; close. stream := ReadWriteStream on: (String new: 80 * threads size). stream nextPutAll: 'Content-type: text/html'; nl; nl; nextPutAll: ''; nl; nextPutAll: 'Newsgroup: ' , group , ''; nl; nextPutAll: '

      Newsgroup: ' , group , '

      '; nl. prevRanges isEmpty ifFalse: [stream nextPutAll: '
      '; nl; nextPutAll: 'Previous articles'; nl; nextPutAll: ''; nl; nextPutAll: '
      '; nl]. threads isEmpty ifFalse: [stream nextPutAll: '
        '; nl. threads keys asSortedCollection do: [:key | | col first | col := threads at: key. first := col removeFirst. stream nextPutAll: '
      • '; nl; nextPutAll: (first at: 2) , '
      • '; nl. col isEmpty ifFalse: [stream nextPutAll: '
          '; nl. col do: [:array | | n subject | n := array at: 1. subject := array at: 2. stream nextPutAll: '
        • '; nl; nextPutAll: subject , '
        • '; nl]. stream nextPutAll: '
        '; nl]]. stream nextPutAll: '
      '; nl]. stream nextPutAll: ''; nl. stream reset. ^(WebEntity readFrom: stream) url: url ] getThreadedNewsArticleListContents: from to: to group: group [ | threads stream | threads := self getThreadedNewsArticleList: from to: to group: group. client quit; close. stream := ReadWriteStream on: (String new: 80 * threads size). stream nextPutAll: 'Content-type: text/html'; nl; nl; nextPutAll: ''; nl; nextPutAll: 'Newsgroup: ' , group , ' (' , from printString , '-' , to printString , ')'; nl; nextPutAll: '

      Newsgroup: ' , group , ' (' , from printString , '-' , to printString , ')

      '; nl. threads isEmpty ifFalse: [stream nextPutAll: '
        '; nl. threads keys asSortedCollection do: [:key | | col first | col := threads at: key. first := col removeFirst. stream nextPutAll: '
      • '; nl; nextPutAll: (first at: 2) , '
      • '; nl. col isEmpty ifFalse: [stream nextPutAll: '
          '; nl. col do: [:array | | n subject | n := array at: 1. subject := array at: 2. stream nextPutAll: '
        • '; nl; nextPutAll: subject , '
        • '; nl]. stream nextPutAll: '
        '; nl]]. stream nextPutAll: '
      '; nl]. stream nextPutAll: ''; nl. stream reset. ^(WebEntity readFrom: stream) url: url ] emptyNewsMessage [ | message group org | message := self emptyMessage. group := url path. group isNil ifFalse: [message parseFieldFrom: ('Newsgroups: ' , group) readStream]. org := UserProfileSettings default settingAt: #organization ifAbsent: [nil]. org isNil ifFalse: [message parseFieldFrom: ('Organization: ' , org) readStream]. message parseFieldFrom: ('X-Newsreader: GNU-Smalltalk/' , Smalltalk version) readStream. ^message ] defaultMailAddress [ ^UserProfileSettings default settingAt: #mailAddress ] errorContents: errorString [ | contents | contents := WebEntity readFrom: ('Content-type: text/html

      Error

      Reason: ' , errorString , '

      ') readStream. contents url: url. contents canCache: false. ^contents ] getBufferSize [ | kbytes | kbytes := (UserProfileSettings default settingAt: #bufferSize) asNumber. ^kbytes * 1024 ] getNoProxyHostNames [ | col read stream noProxy ch | col := OrderedCollection new. noProxy := UserProfileSettings default settingAt: #proxyList. noProxy = 'none' ifTrue: [^col]. read := noProxy readStream. stream := WriteStream on: (String new: 64). [read atEnd] whileFalse: [read skipSeparators. stream reset. [read atEnd or: [ch := read next. ch isSeparator or: [ch = $,]]] whileFalse: [stream nextPut: ch]. stream isEmpty ifFalse: [col addLast: stream contents]]. stream isEmpty ifFalse: [col addLast: stream contents]. ^col ] getProxyContentsHost: hostKey port: portKey [ | host port | (host := url host) isNil ifTrue: [^self errorContents: 'No host name is specified']. (self isNoProxyHost: host) ifTrue: [^nil]. host := UserProfileSettings default settingAt: hostKey. (host isString and: [host notEmpty]) ifFalse: [^nil]. port := UserProfileSettings default settingAt: portKey. port isInteger ifFalse: [^nil]. client := HTTP.HTTPClient new. self connectClientToHost: host port: port. ^self requestHttpContents: url fullRequestString ] getProxyHeadHost: hostKey port: portKey [ | host port | (host := url host) isNil ifTrue: [^self errorContents: 'No host name is specified']. (self isNoProxyHost: host) ifTrue: [^nil]. host := UserProfileSettings default settingAt: hostKey. (host isString and: [host notEmpty]) ifFalse: [^nil]. port := UserProfileSettings default settingAt: portKey. port isInteger ifFalse: [^nil]. client := HTTP.HTTPClient new. self connectClientToHost: host port: port. ^self requestHttpHead: url fullRequestString ] invalidURL [ ^self errorContents: 'Invalid URL' ] isNoProxyHost: host [ self getNoProxyHostNames do: [:noproxy | ('*' , noproxy , '*' match: host) ifTrue: [^true]]. ^false ] on: anURL [ url := anURL ] postProxyContents: contents host: hostKey port: portKey [ | host port | (host := url host) isNil ifTrue: [^self errorContents: 'No host name is specified']. (self isNoProxyHost: host) ifTrue: [^nil]. host := UserProfileSettings default settingAt: hostKey. (host isString and: [host notEmpty]) ifFalse: [^nil]. port := UserProfileSettings default settingAt: portKey. port isInteger ifFalse: [^nil]. client := HTTP.HTTPClient new. self connectClientToHost: host port: port. ^self postHttpContents: contents urlString: url fullRequestString ] tmpFile [ | dir | dir := UserProfileSettings default settingAt: #tmpDir. dir = '' ifTrue: [dir := '/tmp/'] ifFalse: [dir := dir , '/']. ^FileStream openTemporaryFile: dir ] ] MIME.MimeEntity subclass: WebEntity [ | url canCache localFileName | body [ | stream type file | body isNil ifFalse: [^super body]. "Read it from the file" type := (self fieldAt: 'content-type') type. file := File name: localFileName. stream := self class parser on: file readStream. ('message/*' match: type) ifTrue: [self fields removeKey: 'content-type'. self readFrom: stream]. self parseBodyFrom: stream. ^body ] stream [ | body | body := self body. self canDelete ifTrue: [(File name: self localFileName) remove]. ^body readStream ] canCache [ canCache notNil ifTrue: [^canCache]. ^url notNil and: [url canCache] ] canCache: aBoolean [ canCache := aBoolean ] canDelete [ (url notNil and: [url isFileScheme]) ifTrue: [^false]. ^self isFileContents ] isFileContents [ ^localFileName notNil ] localFileName [ ^localFileName ] localFileName: aString [ localFileName := aString ] url [ ^url ] url: anURL [ url := anURL ] urlName [ ^url isNil ifTrue: [''] ifFalse: [url printString] ] guessMimeTypeFromResponse: aResponse [ self addField: (self contentTypeFromResponse: aResponse) ] guessMimeType [ | mimeType | mimeType := self guessedContentType. self addField: (ContentTypeField fromLine: 'content-type: ' , mimeType) ] contentTypeFromResponse: aResponse [ | mimeType | aResponse isNil ifFalse: [mimeType := aResponse fieldAt: 'content-type' ifAbsent: [nil]. mimeType isNil ifFalse: [^mimeType]]. mimeType := self guessedContentType. ^ContentTypeField fromLine: 'content-type: ' , mimeType ] contentTypeFromURL [ | path index | path := url path. (path isNil or: [path isEmpty]) ifTrue: [^nil]. ^ContentHandler contentTypeFor: url path ifAbsent: [nil] ] contentTypeFromContents [ | file stream | file := File name: localFileName. file exists ifTrue: [stream := file readStream. ^[ContentHandler guessContentTypeFor: stream] ensure: [stream close]] ] guessedContentType [ | mimeType | url isNil ifFalse: [mimeType := self contentTypeFromURL. mimeType isNil ifFalse: [^mimeType]]. localFileName isNil ifFalse: ["check for well-known magic types" ^self contentTypeFromContents]. ^'application/octet-stream' ] ] Object subclass: UserProfileSettings [ | settings | UserProfileSettings class [ | default | ] UserProfileSettings class >> default [ ^default isNil ifTrue: [default := self new] ifFalse: [default] ] UserProfileSettings class >> default: aSettingsObject [ default := aSettingsObject ] UserProfileSettings class >> new [ ^self basicNew initialize ] UserProfileSettings class >> postLoad: aParcel [ self initialize ] settings [ ^settings ] settings: aValue [ settings := aValue ] settingAt: aSymbol [ ^self settings at: aSymbol ifAbsent: [''] ] settingFor: aSymbol put: aValue [ ^self settings at: aSymbol put: aValue ] initialize [ self settings: IdentityDictionary new. self settings at: #tmpDir put: Directory temporary. self settings at: #mailer put: 'SMTPClient'. self settings at: #bufferSize put: '16'. self settings at: #proxyList put: 'none'. self settings at: #mailAddress put: nil. self settings at: #mailServer put: nil. self settings at: #signature put: nil. self settings at: #hostKey put: ''. self settings at: #portKey put: '80' ] ] Eval [ UserProfileSettings initialize ] smalltalk-3.2.5/packages/net/Makefile.am0000644000175000017500000000041312123404352015020 00000000000000pkglibexecdir = $(libexecdir)/$(PACKAGE) pkglibexec_PROGRAMS = gnutls-wrapper gnutls_wrapper_SOURCES = gnutls-wrapper.c gnutls_wrapper_LDADD = $(GNUTLS_LIBS) \ $(top_builddir)/lib-src/library.la $(SOCKET_LIBS) AM_CPPFLAGS = $(GNUTLS_CFLAGS) -I$(top_srcdir)/lib-src smalltalk-3.2.5/packages/net/POP.st0000644000175000017500000002150712123404352014001 00000000000000"====================================================================== | | POP3 protocol support | | ======================================================================" "====================================================================== | | Based on code copyright (c) Kazuki Yasumatsu, and in the public domain | Copyright (c) 2002 Free Software Foundation, Inc. | Adapted by Paolo Bonzini. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" Namespace current: NetClients.POP [ NetResponse subclass: POPResponse [ printStatusOn: aStream [ status notNil ifTrue: [status = 1 ifTrue: [aStream nextPutAll: '+OK '] ifFalse: [aStream nextPutAll: '-ERR ']]. statusMessage notNil ifTrue: [aStream nextPutAll: statusMessage] ] parseStatusLine: aClient [ "Returned string is: '+OK ok message' or '-ERR error message'" | stream | stream := aClient nextLine readStream. "status = 1 (OK), status = 0 (ERR)" stream next = $+ ifTrue: [status := 1] ifFalse: [status := 0]. stream skipTo: Character space. stream skipSeparators. statusMessage := stream upToEnd ] ] ] Namespace current: NetClients.POP [ NetClient subclass: POPClient [ | loggedInUser | POPClient class >> defaultPortNumber [ ^110 ] POPClient class >> example2Host: host username: username password: password [ [self exampleHost: host username: username password: password] on: LoginIncorrectError do: [:ex | 'Login incorrect' printNl. ex return] ] POPClient class >> exampleHost: host username: username password: password [ | client | client := POPClient connectToHost: host. [client username: username password: password. client login. Transcript showCr: 'New messages: ' , client newMessagesCount printString. Transcript showCr: 'bytes ' , client newMessagesSize printString. Transcript showCr: 'ids ' , client newMessagesIds printString. Transcript showCr: 'sizes ' , client newMessages printString. client getNewMailMessages: [:m | m inspect] delete: false] ensure: [client close] ] login [ loggedInUser = self user ifTrue: [^self]. loggedInUser isNil ifFalse: [self logout]. self connect. self clientPI popUser: self username. self clientPI popPassword: self password. loggedInUser := self user ] logout [ self clientPI popQuit ] newMessagesCount [ ^self clientPI popStatus key ] newMessagesSize [ ^self clientPI popStatus value ] newMessagesIds [ ^self clientPI popList keys asSortedCollection asArray ] newMessages [ ^self clientPI popList ] sizeAt: id [ ^self clientPI popList: id ] headersAt: id [ ^self clientPI popTop: id lines: 1 ] at: id [ ^self clientPI popRetrieve: id ] getNewMailHeaders: messageBlock delete: delete [ | count entity | self login. count := self clientPI popStatus key. count = 0 ifFalse: [1 to: count do: [:i | entity := self clientPI popTop: i lines: 1. messageBlock value: entity]. delete ifTrue: [1 to: count do: [:i | self clientPI popDelete: i]]] ] getNewMailMessages: messageBlock delete: delete [ | count entity | self login. count := self clientPI popStatus key. count = 0 ifFalse: [1 to: count do: [:i | entity := self clientPI popRetrieve: i. messageBlock value: entity]. delete ifTrue: [1 to: count do: [:i | self clientPI popDelete: i]]] ] getNewMailStreams: streamBlock delete: delete [ | count | self connectIfClosed. self clientPI popUser: self username. self clientPI popPassword: self password. count := self clientPI popStatus. count = 0 ifFalse: [1 to: count do: [:i | self clientPI popRetrieve: i into: streamBlock value]. delete ifTrue: [1 to: count do: [:i | self clientPI popDelete: i]]] ] protocolInterpreter [ ^POPProtocolInterpreter ] ] ] Namespace current: NetClients.POP [ NetProtocolInterpreter subclass: POPProtocolInterpreter [ POPProtocolInterpreter class >> defaultResponseClass [ ^POPResponse ] connect [ super connect. self checkResponse ] popDelete: anInteger [ self nextPutAll: 'DELE ' , anInteger printString; cr. self checkResponse ] popList [ | stream dictionary assoc | self nextPutAll: 'LIST'; cr. self checkResponse. dictionary := LookupTable new. stream := ReadWriteStream on: (String new: 100). self receiveMessageUntilPeriodInto: stream. stream reset. [assoc := self parseSizeDataFrom: stream nextLine readStream. assoc key > 0] whileTrue: [dictionary add: assoc]. ^dictionary ] popList: anInteger [ | stream response | self nextPutAll: 'LIST ' , anInteger printString; cr. response := self getResponse. self checkResponse: response. response statusMessage == nil ifTrue: [^0]. stream := response statusMessage readStream. ^(self parseSizeDataFrom: stream) value ] popPassword: password [ | response | self nextPutAll: 'PASS ' , password; cr. response := self getResponse. self checkResponse: response ifError: [self loginIncorrectError: response statusMessage] ] popQuit [ self nextPutAll: 'QUIT'; cr. self checkResponse ] popRetrieve: anInteger [ self nextPutAll: 'RETR ' , anInteger printString; cr. self checkResponse. ^MIME.MimeEntity readFromClient: self connectionStream ] popRetrieve: anInteger into: aStream [ self nextPutAll: 'RETR ' , anInteger printString; cr. self checkResponse. self receiveMessageUntilPeriodInto: aStream ] popStatus [ "Check status and return a number of messages." | response stream | self nextPutAll: 'STAT'; cr. response := self getResponse. self checkResponse: response. response statusMessage == nil ifTrue: [^0 -> 0]. stream := response statusMessage readStream. ^self parseSizeDataFrom: stream ] popTop: anInteger lines: linesInteger [ self nextPutAll: 'TOP ' , anInteger printString; nextPutAll: ' ' , linesInteger printString; cr. self checkResponse. ^MIME.MimeEntity readFromClient: self connectionStream ] popTop: anInteger lines: linesInteger into: aStream [ self nextPutAll: 'TOP ' , anInteger printString; nextPutAll: ' ' , linesInteger printString; cr. self checkResponse. self receiveMessageUntilPeriodInto: aStream ] popUser: user [ self nextPutAll: 'USER ' , user; cr. self checkResponse ] checkResponse: response ifError: errorBlock [ | status | status := response status. status = 1 ifTrue: ["OK" ^self]. ^errorBlock value ] parseSizeDataFrom: stream [ | count size | stream skipSeparators. count := Integer readFrom: stream. stream skipSeparators. size := Integer readFrom: stream. ^count -> size ] ] ] smalltalk-3.2.5/packages/net/Makefile.in0000644000175000017500000005125712130455426015053 00000000000000# Makefile.in generated by automake 1.11.6 from Makefile.am. # @configure_input@ # Copyright (C) 1994, 1995, 1996, 1997, 1998, 1999, 2000, 2001, 2002, # 2003, 2004, 2005, 2006, 2007, 2008, 2009, 2010, 2011 Free Software # Foundation, Inc. # This Makefile.in is free software; the Free Software Foundation # gives unlimited permission to copy and/or distribute it, # with or without modifications, as long as this notice is preserved. # This program is distributed in the hope that it will be useful, # but WITHOUT ANY WARRANTY, to the extent permitted by law; without # even the implied warranty of MERCHANTABILITY or FITNESS FOR A # PARTICULAR PURPOSE. @SET_MAKE@ VPATH = @srcdir@ am__make_dryrun = \ { \ am__dry=no; \ case $$MAKEFLAGS in \ *\\[\ \ ]*) \ echo 'am--echo: ; @echo "AM" OK' | $(MAKE) -f - 2>/dev/null \ | grep '^AM OK$$' >/dev/null || am__dry=yes;; \ *) \ for am__flg in $$MAKEFLAGS; do \ case $$am__flg in \ *=*|--*) ;; \ *n*) am__dry=yes; break;; \ esac; \ done;; \ esac; \ test $$am__dry = yes; \ } pkgdatadir = $(datadir)/@PACKAGE@ pkgincludedir = $(includedir)/@PACKAGE@ pkglibdir = $(libdir)/@PACKAGE@ am__cd = CDPATH="$${ZSH_VERSION+.}$(PATH_SEPARATOR)" && cd install_sh_DATA = $(install_sh) -c -m 644 install_sh_PROGRAM = $(install_sh) -c install_sh_SCRIPT = $(install_sh) -c INSTALL_HEADER = $(INSTALL_DATA) transform = $(program_transform_name) NORMAL_INSTALL = : PRE_INSTALL = : POST_INSTALL = : NORMAL_UNINSTALL = : PRE_UNINSTALL = : POST_UNINSTALL = : build_triplet = @build@ host_triplet = @host@ pkglibexec_PROGRAMS = gnutls-wrapper$(EXEEXT) subdir = packages/net DIST_COMMON = $(srcdir)/Makefile.am $(srcdir)/Makefile.in ChangeLog ACLOCAL_M4 = $(top_srcdir)/aclocal.m4 am__aclocal_m4_deps = $(top_srcdir)/build-aux/bold.m4 \ $(top_srcdir)/build-aux/codeset.m4 \ $(top_srcdir)/build-aux/emacs-pkg.m4 \ $(top_srcdir)/build-aux/emacs-site-start.m4 \ $(top_srcdir)/build-aux/ext_goto.m4 \ $(top_srcdir)/build-aux/gawk.m4 $(top_srcdir)/build-aux/gcc.m4 \ $(top_srcdir)/build-aux/gl.m4 \ $(top_srcdir)/build-aux/glib-2.0.m4 \ $(top_srcdir)/build-aux/glut.m4 $(top_srcdir)/build-aux/gmp.m4 \ $(top_srcdir)/build-aux/gst-package.m4 \ $(top_srcdir)/build-aux/gtk-2.0.m4 \ $(top_srcdir)/build-aux/iconv.m4 \ $(top_srcdir)/build-aux/lib-ld.m4 \ $(top_srcdir)/build-aux/lib-link.m4 \ $(top_srcdir)/build-aux/lib-prefix.m4 \ $(top_srcdir)/build-aux/lib.m4 \ $(top_srcdir)/build-aux/libc-so-name.m4 \ $(top_srcdir)/build-aux/libtool.m4 \ $(top_srcdir)/build-aux/lightning.m4 \ $(top_srcdir)/build-aux/ln.m4 \ $(top_srcdir)/build-aux/localtime.m4 \ $(top_srcdir)/build-aux/lock.m4 \ $(top_srcdir)/build-aux/long-double.m4 \ $(top_srcdir)/build-aux/lrint.m4 \ $(top_srcdir)/build-aux/ltdl-gst.m4 \ $(top_srcdir)/build-aux/ltoptions.m4 \ $(top_srcdir)/build-aux/ltsugar.m4 \ $(top_srcdir)/build-aux/ltversion.m4 \ $(top_srcdir)/build-aux/lt~obsolete.m4 \ $(top_srcdir)/build-aux/modules.m4 \ $(top_srcdir)/build-aux/pkg.m4 $(top_srcdir)/build-aux/poll.m4 \ $(top_srcdir)/build-aux/readline.m4 \ $(top_srcdir)/build-aux/relocatable.m4 \ $(top_srcdir)/build-aux/setenv.m4 \ $(top_srcdir)/build-aux/snprintfv.m4 \ $(top_srcdir)/build-aux/sockets.m4 \ $(top_srcdir)/build-aux/sockpfaf.m4 \ $(top_srcdir)/build-aux/strtoul.m4 \ $(top_srcdir)/build-aux/sync-builtins.m4 \ $(top_srcdir)/build-aux/tcltk.m4 \ $(top_srcdir)/build-aux/version.m4 \ $(top_srcdir)/build-aux/vis-hidden.m4 \ $(top_srcdir)/build-aux/wine.m4 $(top_srcdir)/configure.ac am__configure_deps = $(am__aclocal_m4_deps) $(CONFIGURE_DEPENDENCIES) \ $(ACLOCAL_M4) mkinstalldirs = $(install_sh) -d CONFIG_HEADER = $(top_builddir)/config.h CONFIG_CLEAN_FILES = CONFIG_CLEAN_VPATH_FILES = am__installdirs = "$(DESTDIR)$(pkglibexecdir)" PROGRAMS = $(pkglibexec_PROGRAMS) am_gnutls_wrapper_OBJECTS = gnutls-wrapper.$(OBJEXT) gnutls_wrapper_OBJECTS = $(am_gnutls_wrapper_OBJECTS) am__DEPENDENCIES_1 = gnutls_wrapper_DEPENDENCIES = $(am__DEPENDENCIES_1) \ $(top_builddir)/lib-src/library.la $(am__DEPENDENCIES_1) DEFAULT_INCLUDES = -I.@am__isrc@ -I$(top_builddir) depcomp = $(SHELL) $(top_srcdir)/build-aux/depcomp am__depfiles_maybe = depfiles am__mv = mv -f COMPILE = $(CC) $(DEFS) $(DEFAULT_INCLUDES) $(INCLUDES) $(AM_CPPFLAGS) \ $(CPPFLAGS) $(AM_CFLAGS) $(CFLAGS) LTCOMPILE = $(LIBTOOL) --tag=CC $(AM_LIBTOOLFLAGS) $(LIBTOOLFLAGS) \ --mode=compile $(CC) $(DEFS) $(DEFAULT_INCLUDES) $(INCLUDES) \ $(AM_CPPFLAGS) $(CPPFLAGS) $(AM_CFLAGS) $(CFLAGS) CCLD = $(CC) LINK = $(LIBTOOL) --tag=CC $(AM_LIBTOOLFLAGS) $(LIBTOOLFLAGS) \ --mode=link $(CCLD) $(AM_CFLAGS) $(CFLAGS) $(AM_LDFLAGS) \ $(LDFLAGS) -o $@ SOURCES = $(gnutls_wrapper_SOURCES) DIST_SOURCES = $(gnutls_wrapper_SOURCES) am__can_run_installinfo = \ case $$AM_UPDATE_INFO_DIR in \ n|no|NO) false;; \ *) (install-info --version) >/dev/null 2>&1;; \ esac ETAGS = etags CTAGS = ctags DISTFILES = $(DIST_COMMON) $(DIST_SOURCES) $(TEXINFOS) $(EXTRA_DIST) pkglibexecdir = $(libexecdir)/$(PACKAGE) ACLOCAL = @ACLOCAL@ ALLOCA = @ALLOCA@ ALL_PACKAGES = @ALL_PACKAGES@ AMTAR = @AMTAR@ AR = @AR@ AS = @AS@ ATK_CFLAGS = @ATK_CFLAGS@ ATK_LIBS = @ATK_LIBS@ AUTOCONF = @AUTOCONF@ AUTOHEADER = @AUTOHEADER@ AUTOM4TE = @AUTOM4TE@ AUTOMAKE = @AUTOMAKE@ AWK = @AWK@ BLOX_IMPLEMENTATION = @BLOX_IMPLEMENTATION@ BUILT_PACKAGES = @BUILT_PACKAGES@ CAIRO_CFLAGS = @CAIRO_CFLAGS@ CAIRO_LIBS = @CAIRO_LIBS@ CC = @CC@ CCDEPMODE = @CCDEPMODE@ CFLAGS = @CFLAGS@ CPP = @CPP@ CPPFLAGS = @CPPFLAGS@ CYGPATH_W = @CYGPATH_W@ DEFS = @DEFS@ DEPDIR = @DEPDIR@ DLLTOOL = @DLLTOOL@ DSYMUTIL = @DSYMUTIL@ DUMPBIN = @DUMPBIN@ ECHO_C = @ECHO_C@ ECHO_N = @ECHO_N@ ECHO_T = @ECHO_T@ EGREP = @EGREP@ EMACS = @EMACS@ EMACSLOADPATH = @EMACSLOADPATH@ EXEEXT = @EXEEXT@ FGREP = @FGREP@ GLIB_CFLAGS = @GLIB_CFLAGS@ GLIB_GENMARSHAL = @GLIB_GENMARSHAL@ GLIB_LIBS = @GLIB_LIBS@ GLIB_MKENUMS = @GLIB_MKENUMS@ GNUTLS_CFLAGS = @GNUTLS_CFLAGS@ GNUTLS_LIBS = @GNUTLS_LIBS@ GOBJECT_QUERY = @GOBJECT_QUERY@ GPERF = @GPERF@ GREP = @GREP@ GST_RUN = @GST_RUN@ GTHREAD_CFLAGS = @GTHREAD_CFLAGS@ GTHREAD_LIBS = @GTHREAD_LIBS@ GTK_CFLAGS = @GTK_CFLAGS@ GTK_LIBS = @GTK_LIBS@ ICON = @ICON@ INCFFI = @INCFFI@ INCLTDL = @INCLTDL@ INCSIGSEGV = @INCSIGSEGV@ INCSNPRINTFV = @INCSNPRINTFV@ INCTCLTK = @INCTCLTK@ INSTALL = @INSTALL@ INSTALL_DATA = @INSTALL_DATA@ INSTALL_INFO = @INSTALL_INFO@ INSTALL_PROGRAM = @INSTALL_PROGRAM@ INSTALL_SCRIPT = @INSTALL_SCRIPT@ INSTALL_STRIP_PROGRAM = @INSTALL_STRIP_PROGRAM@ LD = @LD@ LDFLAGS = @LDFLAGS@ LEX = @LEX@ LIBADD_DL = @LIBADD_DL@ LIBC_SO_DIR = @LIBC_SO_DIR@ LIBC_SO_NAME = @LIBC_SO_NAME@ LIBFFI = @LIBFFI@ LIBFFI_CFLAGS = @LIBFFI_CFLAGS@ LIBFFI_EXECUTABLE_LDFLAGS = @LIBFFI_EXECUTABLE_LDFLAGS@ LIBFFI_LIBS = @LIBFFI_LIBS@ LIBGLUT = @LIBGLUT@ LIBGMP = @LIBGMP@ LIBGST_CFLAGS = @LIBGST_CFLAGS@ LIBICONV = @LIBICONV@ LIBLTDL = @LIBLTDL@ LIBOBJS = @LIBOBJS@ LIBOPENGL = @LIBOPENGL@ LIBREADLINE = @LIBREADLINE@ LIBS = @LIBS@ LIBSIGSEGV = @LIBSIGSEGV@ LIBSNPRINTFV = @LIBSNPRINTFV@ LIBTCLTK = @LIBTCLTK@ LIBTHREAD = @LIBTHREAD@ LIBTOOL = @LIBTOOL@ LIPO = @LIPO@ LN = @LN@ LN_S = @LN_S@ LTALLOCA = @LTALLOCA@ LTLIBICONV = @LTLIBICONV@ LTLIBOBJS = @LTLIBOBJS@ MAINTAINER = @MAINTAINER@ MAKEINFO = @MAKEINFO@ MANIFEST_TOOL = @MANIFEST_TOOL@ MKDIR_P = @MKDIR_P@ MODULES = @MODULES@ NM = @NM@ NMEDIT = @NMEDIT@ OBJC = @OBJC@ OBJCDEPMODE = @OBJCDEPMODE@ OBJCFLAGS = @OBJCFLAGS@ OBJDUMP = @OBJDUMP@ OBJEXT = @OBJEXT@ OTOOL = @OTOOL@ OTOOL64 = @OTOOL64@ PACKAGE = @PACKAGE@ PACKAGE_BUGREPORT = @PACKAGE_BUGREPORT@ PACKAGE_DLOPEN_FLAGS = @PACKAGE_DLOPEN_FLAGS@ PACKAGE_NAME = @PACKAGE_NAME@ PACKAGE_STRING = @PACKAGE_STRING@ PACKAGE_TARNAME = @PACKAGE_TARNAME@ PACKAGE_URL = @PACKAGE_URL@ PACKAGE_VERSION = @PACKAGE_VERSION@ PANGO_CFLAGS = @PANGO_CFLAGS@ PANGO_LIBS = @PANGO_LIBS@ PATH_SEPARATOR = @PATH_SEPARATOR@ PKG_CONFIG = @PKG_CONFIG@ RANLIB = @RANLIB@ RELOCATABLE = @RELOCATABLE@ RELOC_CPPFLAGS = @RELOC_CPPFLAGS@ RELOC_LDFLAGS = @RELOC_LDFLAGS@ SDL_CFLAGS = @SDL_CFLAGS@ SDL_LIBS = @SDL_LIBS@ SED = @SED@ SET_MAKE = @SET_MAKE@ SHELL = @SHELL@ SOCKET_LIBS = @SOCKET_LIBS@ STRIP = @STRIP@ SYNC_CFLAGS = @SYNC_CFLAGS@ TCLSH = @TCLSH@ TIMEOUT = @TIMEOUT@ VERSION = @VERSION@ VERSION_INFO = @VERSION_INFO@ WINDRES = @WINDRES@ WINEWRAPPER = @WINEWRAPPER@ WINEWRAPPERDEP = @WINEWRAPPERDEP@ XMKMF = @XMKMF@ XZIP = @XZIP@ X_CFLAGS = @X_CFLAGS@ X_EXTRA_LIBS = @X_EXTRA_LIBS@ X_LIBS = @X_LIBS@ X_PRE_LIBS = @X_PRE_LIBS@ YACC = @YACC@ ZIP = @ZIP@ abs_builddir = @abs_builddir@ abs_srcdir = @abs_srcdir@ abs_top_builddir = @abs_top_builddir@ abs_top_srcdir = @abs_top_srcdir@ ac_ct_AR = @ac_ct_AR@ ac_ct_CC = @ac_ct_CC@ ac_ct_DUMPBIN = @ac_ct_DUMPBIN@ am__include = @am__include@ am__leading_dot = @am__leading_dot@ am__quote = @am__quote@ am__tar = @am__tar@ am__untar = @am__untar@ bindir = @bindir@ build = @build@ build_alias = @build_alias@ build_cpu = @build_cpu@ build_os = @build_os@ build_vendor = @build_vendor@ builddir = @builddir@ datadir = @datadir@ datarootdir = @datarootdir@ docdir = @docdir@ dvidir = @dvidir@ enable_mysql_tests = @enable_mysql_tests@ exec_prefix = @exec_prefix@ host = @host@ host_alias = @host_alias@ host_cpu = @host_cpu@ host_os = @host_os@ host_vendor = @host_vendor@ htmldir = @htmldir@ imagedir = @imagedir@ includedir = @includedir@ infodir = @infodir@ install_sh = @install_sh@ libdir = @libdir@ libexecdir = @libexecdir@ lispdir = @lispdir@ lispstartdir = @lispstartdir@ localedir = @localedir@ localstatedir = @localstatedir@ mandir = @mandir@ mkdir_p = @mkdir_p@ moduledir = @moduledir@ moduleexecdir = @moduleexecdir@ oldincludedir = @oldincludedir@ pdfdir = @pdfdir@ prefix = @prefix@ program_transform_name = @program_transform_name@ psdir = @psdir@ sbindir = @sbindir@ sharedstatedir = @sharedstatedir@ srcdir = @srcdir@ subdirs = @subdirs@ sysconfdir = @sysconfdir@ target_alias = @target_alias@ top_build_prefix = @top_build_prefix@ top_builddir = @top_builddir@ top_srcdir = @top_srcdir@ gnutls_wrapper_SOURCES = gnutls-wrapper.c gnutls_wrapper_LDADD = $(GNUTLS_LIBS) \ $(top_builddir)/lib-src/library.la $(SOCKET_LIBS) AM_CPPFLAGS = $(GNUTLS_CFLAGS) -I$(top_srcdir)/lib-src all: all-am .SUFFIXES: .SUFFIXES: .c .lo .o .obj $(srcdir)/Makefile.in: $(srcdir)/Makefile.am $(am__configure_deps) @for dep in $?; do \ case '$(am__configure_deps)' in \ *$$dep*) \ ( cd $(top_builddir) && $(MAKE) $(AM_MAKEFLAGS) am--refresh ) \ && { if test -f $@; then exit 0; else break; fi; }; \ exit 1;; \ esac; \ done; \ echo ' cd $(top_srcdir) && $(AUTOMAKE) --gnu packages/net/Makefile'; \ $(am__cd) $(top_srcdir) && \ $(AUTOMAKE) --gnu packages/net/Makefile .PRECIOUS: Makefile Makefile: $(srcdir)/Makefile.in $(top_builddir)/config.status @case '$?' in \ *config.status*) \ cd $(top_builddir) && $(MAKE) $(AM_MAKEFLAGS) am--refresh;; \ *) \ echo ' cd $(top_builddir) && $(SHELL) ./config.status $(subdir)/$@ $(am__depfiles_maybe)'; \ cd $(top_builddir) && $(SHELL) ./config.status $(subdir)/$@ $(am__depfiles_maybe);; \ esac; $(top_builddir)/config.status: $(top_srcdir)/configure $(CONFIG_STATUS_DEPENDENCIES) cd $(top_builddir) && $(MAKE) $(AM_MAKEFLAGS) am--refresh $(top_srcdir)/configure: $(am__configure_deps) cd $(top_builddir) && $(MAKE) $(AM_MAKEFLAGS) am--refresh $(ACLOCAL_M4): $(am__aclocal_m4_deps) cd $(top_builddir) && $(MAKE) $(AM_MAKEFLAGS) am--refresh $(am__aclocal_m4_deps): install-pkglibexecPROGRAMS: $(pkglibexec_PROGRAMS) @$(NORMAL_INSTALL) @list='$(pkglibexec_PROGRAMS)'; test -n "$(pkglibexecdir)" || list=; \ if test -n "$$list"; then \ echo " $(MKDIR_P) '$(DESTDIR)$(pkglibexecdir)'"; \ $(MKDIR_P) "$(DESTDIR)$(pkglibexecdir)" || exit 1; \ fi; \ for p in $$list; do echo "$$p $$p"; done | \ sed 's/$(EXEEXT)$$//' | \ while read p p1; do if test -f $$p || test -f $$p1; \ then echo "$$p"; echo "$$p"; else :; fi; \ done | \ sed -e 'p;s,.*/,,;n;h' -e 's|.*|.|' \ -e 'p;x;s,.*/,,;s/$(EXEEXT)$$//;$(transform);s/$$/$(EXEEXT)/' | \ sed 'N;N;N;s,\n, ,g' | \ $(AWK) 'BEGIN { files["."] = ""; dirs["."] = 1 } \ { d=$$3; if (dirs[d] != 1) { print "d", d; dirs[d] = 1 } \ if ($$2 == $$4) files[d] = files[d] " " $$1; \ else { print "f", $$3 "/" $$4, $$1; } } \ END { for (d in files) print "f", d, files[d] }' | \ while read type dir files; do \ if test "$$dir" = .; then dir=; else dir=/$$dir; fi; \ test -z "$$files" || { \ echo " $(INSTALL_PROGRAM_ENV) $(LIBTOOL) $(AM_LIBTOOLFLAGS) $(LIBTOOLFLAGS) --mode=install $(INSTALL_PROGRAM) $$files '$(DESTDIR)$(pkglibexecdir)$$dir'"; \ $(INSTALL_PROGRAM_ENV) $(LIBTOOL) $(AM_LIBTOOLFLAGS) $(LIBTOOLFLAGS) --mode=install $(INSTALL_PROGRAM) $$files "$(DESTDIR)$(pkglibexecdir)$$dir" || exit $$?; \ } \ ; done uninstall-pkglibexecPROGRAMS: @$(NORMAL_UNINSTALL) @list='$(pkglibexec_PROGRAMS)'; test -n "$(pkglibexecdir)" || list=; \ files=`for p in $$list; do echo "$$p"; done | \ sed -e 'h;s,^.*/,,;s/$(EXEEXT)$$//;$(transform)' \ -e 's/$$/$(EXEEXT)/' `; \ test -n "$$list" || exit 0; \ echo " ( cd '$(DESTDIR)$(pkglibexecdir)' && rm -f" $$files ")"; \ cd "$(DESTDIR)$(pkglibexecdir)" && rm -f $$files clean-pkglibexecPROGRAMS: @list='$(pkglibexec_PROGRAMS)'; test -n "$$list" || exit 0; \ echo " rm -f" $$list; \ rm -f $$list || exit $$?; \ test -n "$(EXEEXT)" || exit 0; \ list=`for p in $$list; do echo "$$p"; done | sed 's/$(EXEEXT)$$//'`; \ echo " rm -f" $$list; \ rm -f $$list gnutls-wrapper$(EXEEXT): $(gnutls_wrapper_OBJECTS) $(gnutls_wrapper_DEPENDENCIES) $(EXTRA_gnutls_wrapper_DEPENDENCIES) @rm -f gnutls-wrapper$(EXEEXT) $(LINK) $(gnutls_wrapper_OBJECTS) $(gnutls_wrapper_LDADD) $(LIBS) mostlyclean-compile: -rm -f *.$(OBJEXT) distclean-compile: -rm -f *.tab.c @AMDEP_TRUE@@am__include@ @am__quote@./$(DEPDIR)/gnutls-wrapper.Po@am__quote@ .c.o: @am__fastdepCC_TRUE@ $(COMPILE) -MT $@ -MD -MP -MF $(DEPDIR)/$*.Tpo -c -o $@ $< @am__fastdepCC_TRUE@ $(am__mv) $(DEPDIR)/$*.Tpo $(DEPDIR)/$*.Po @AMDEP_TRUE@@am__fastdepCC_FALSE@ source='$<' object='$@' libtool=no @AMDEPBACKSLASH@ @AMDEP_TRUE@@am__fastdepCC_FALSE@ DEPDIR=$(DEPDIR) $(CCDEPMODE) $(depcomp) @AMDEPBACKSLASH@ @am__fastdepCC_FALSE@ $(COMPILE) -c $< .c.obj: @am__fastdepCC_TRUE@ $(COMPILE) -MT $@ -MD -MP -MF $(DEPDIR)/$*.Tpo -c -o $@ `$(CYGPATH_W) '$<'` @am__fastdepCC_TRUE@ $(am__mv) $(DEPDIR)/$*.Tpo $(DEPDIR)/$*.Po @AMDEP_TRUE@@am__fastdepCC_FALSE@ source='$<' object='$@' libtool=no @AMDEPBACKSLASH@ @AMDEP_TRUE@@am__fastdepCC_FALSE@ DEPDIR=$(DEPDIR) $(CCDEPMODE) $(depcomp) @AMDEPBACKSLASH@ @am__fastdepCC_FALSE@ $(COMPILE) -c `$(CYGPATH_W) '$<'` .c.lo: @am__fastdepCC_TRUE@ $(LTCOMPILE) -MT $@ -MD -MP -MF $(DEPDIR)/$*.Tpo -c -o $@ $< @am__fastdepCC_TRUE@ $(am__mv) $(DEPDIR)/$*.Tpo $(DEPDIR)/$*.Plo @AMDEP_TRUE@@am__fastdepCC_FALSE@ source='$<' object='$@' libtool=yes @AMDEPBACKSLASH@ @AMDEP_TRUE@@am__fastdepCC_FALSE@ DEPDIR=$(DEPDIR) $(CCDEPMODE) $(depcomp) @AMDEPBACKSLASH@ @am__fastdepCC_FALSE@ $(LTCOMPILE) -c -o $@ $< mostlyclean-libtool: -rm -f *.lo clean-libtool: -rm -rf .libs _libs ID: $(HEADERS) $(SOURCES) $(LISP) $(TAGS_FILES) list='$(SOURCES) $(HEADERS) $(LISP) $(TAGS_FILES)'; \ unique=`for i in $$list; do \ if test -f "$$i"; then echo $$i; else echo $(srcdir)/$$i; fi; \ done | \ $(AWK) '{ files[$$0] = 1; nonempty = 1; } \ END { if (nonempty) { for (i in files) print i; }; }'`; \ mkid -fID $$unique tags: TAGS TAGS: $(HEADERS) $(SOURCES) $(TAGS_DEPENDENCIES) \ $(TAGS_FILES) $(LISP) set x; \ here=`pwd`; \ list='$(SOURCES) $(HEADERS) $(LISP) $(TAGS_FILES)'; \ unique=`for i in $$list; do \ if test -f "$$i"; then echo $$i; else echo $(srcdir)/$$i; fi; \ done | \ $(AWK) '{ files[$$0] = 1; nonempty = 1; } \ END { if (nonempty) { for (i in files) print i; }; }'`; \ shift; \ if test -z "$(ETAGS_ARGS)$$*$$unique"; then :; else \ test -n "$$unique" || unique=$$empty_fix; \ if test $$# -gt 0; then \ $(ETAGS) $(ETAGSFLAGS) $(AM_ETAGSFLAGS) $(ETAGS_ARGS) \ "$$@" $$unique; \ else \ $(ETAGS) $(ETAGSFLAGS) $(AM_ETAGSFLAGS) $(ETAGS_ARGS) \ $$unique; \ fi; \ fi ctags: CTAGS CTAGS: $(HEADERS) $(SOURCES) $(TAGS_DEPENDENCIES) \ $(TAGS_FILES) $(LISP) list='$(SOURCES) $(HEADERS) $(LISP) $(TAGS_FILES)'; \ unique=`for i in $$list; do \ if test -f "$$i"; then echo $$i; else echo $(srcdir)/$$i; fi; \ done | \ $(AWK) '{ files[$$0] = 1; nonempty = 1; } \ END { if (nonempty) { for (i in files) print i; }; }'`; \ test -z "$(CTAGS_ARGS)$$unique" \ || $(CTAGS) $(CTAGSFLAGS) $(AM_CTAGSFLAGS) $(CTAGS_ARGS) \ $$unique GTAGS: here=`$(am__cd) $(top_builddir) && pwd` \ && $(am__cd) $(top_srcdir) \ && gtags -i $(GTAGS_ARGS) "$$here" distclean-tags: -rm -f TAGS ID GTAGS GRTAGS GSYMS GPATH tags distdir: $(DISTFILES) @srcdirstrip=`echo "$(srcdir)" | sed 's/[].[^$$\\*]/\\\\&/g'`; \ topsrcdirstrip=`echo "$(top_srcdir)" | sed 's/[].[^$$\\*]/\\\\&/g'`; \ list='$(DISTFILES)'; \ dist_files=`for file in $$list; do echo $$file; done | \ sed -e "s|^$$srcdirstrip/||;t" \ -e "s|^$$topsrcdirstrip/|$(top_builddir)/|;t"`; \ case $$dist_files in \ */*) $(MKDIR_P) `echo "$$dist_files" | \ sed '/\//!d;s|^|$(distdir)/|;s,/[^/]*$$,,' | \ sort -u` ;; \ esac; \ for file in $$dist_files; do \ if test -f $$file || test -d $$file; then d=.; else d=$(srcdir); fi; \ if test -d $$d/$$file; then \ dir=`echo "/$$file" | sed -e 's,/[^/]*$$,,'`; \ if test -d "$(distdir)/$$file"; then \ find "$(distdir)/$$file" -type d ! -perm -700 -exec chmod u+rwx {} \;; \ fi; \ if test -d $(srcdir)/$$file && test $$d != $(srcdir); then \ cp -fpR $(srcdir)/$$file "$(distdir)$$dir" || exit 1; \ find "$(distdir)/$$file" -type d ! -perm -700 -exec chmod u+rwx {} \;; \ fi; \ cp -fpR $$d/$$file "$(distdir)$$dir" || exit 1; \ else \ test -f "$(distdir)/$$file" \ || cp -p $$d/$$file "$(distdir)/$$file" \ || exit 1; \ fi; \ done check-am: all-am check: check-am all-am: Makefile $(PROGRAMS) installdirs: for dir in "$(DESTDIR)$(pkglibexecdir)"; do \ test -z "$$dir" || $(MKDIR_P) "$$dir"; \ done install: install-am install-exec: install-exec-am install-data: install-data-am uninstall: uninstall-am install-am: all-am @$(MAKE) $(AM_MAKEFLAGS) install-exec-am install-data-am installcheck: installcheck-am install-strip: if test -z '$(STRIP)'; then \ $(MAKE) $(AM_MAKEFLAGS) INSTALL_PROGRAM="$(INSTALL_STRIP_PROGRAM)" \ install_sh_PROGRAM="$(INSTALL_STRIP_PROGRAM)" INSTALL_STRIP_FLAG=-s \ install; \ else \ $(MAKE) $(AM_MAKEFLAGS) INSTALL_PROGRAM="$(INSTALL_STRIP_PROGRAM)" \ install_sh_PROGRAM="$(INSTALL_STRIP_PROGRAM)" INSTALL_STRIP_FLAG=-s \ "INSTALL_PROGRAM_ENV=STRIPPROG='$(STRIP)'" install; \ fi mostlyclean-generic: clean-generic: distclean-generic: -test -z "$(CONFIG_CLEAN_FILES)" || rm -f $(CONFIG_CLEAN_FILES) -test . = "$(srcdir)" || test -z "$(CONFIG_CLEAN_VPATH_FILES)" || rm -f $(CONFIG_CLEAN_VPATH_FILES) maintainer-clean-generic: @echo "This command is intended for maintainers to use" @echo "it deletes files that may require special tools to rebuild." clean: clean-am clean-am: clean-generic clean-libtool clean-pkglibexecPROGRAMS \ mostlyclean-am distclean: distclean-am -rm -rf ./$(DEPDIR) -rm -f Makefile distclean-am: clean-am distclean-compile distclean-generic \ distclean-tags dvi: dvi-am dvi-am: html: html-am html-am: info: info-am info-am: install-data-am: install-dvi: install-dvi-am install-dvi-am: install-exec-am: install-pkglibexecPROGRAMS install-html: install-html-am install-html-am: install-info: install-info-am install-info-am: install-man: install-pdf: install-pdf-am install-pdf-am: install-ps: install-ps-am install-ps-am: installcheck-am: maintainer-clean: maintainer-clean-am -rm -rf ./$(DEPDIR) -rm -f Makefile maintainer-clean-am: distclean-am maintainer-clean-generic mostlyclean: mostlyclean-am mostlyclean-am: mostlyclean-compile mostlyclean-generic \ mostlyclean-libtool pdf: pdf-am pdf-am: ps: ps-am ps-am: uninstall-am: uninstall-pkglibexecPROGRAMS .MAKE: install-am install-strip .PHONY: CTAGS GTAGS all all-am check check-am clean clean-generic \ clean-libtool clean-pkglibexecPROGRAMS ctags distclean \ distclean-compile distclean-generic distclean-libtool \ distclean-tags distdir dvi dvi-am html html-am info info-am \ install install-am install-data install-data-am install-dvi \ install-dvi-am install-exec install-exec-am install-html \ install-html-am install-info install-info-am install-man \ install-pdf install-pdf-am install-pkglibexecPROGRAMS \ install-ps install-ps-am install-strip installcheck \ installcheck-am installdirs maintainer-clean \ maintainer-clean-generic mostlyclean mostlyclean-compile \ mostlyclean-generic mostlyclean-libtool pdf pdf-am ps ps-am \ tags uninstall uninstall-am uninstall-pkglibexecPROGRAMS # Tell versions [3.59,3.63) of GNU make to not export all variables. # Otherwise a system limit (for SysV at least) may be exceeded. .NOEXPORT: smalltalk-3.2.5/packages/net/IMAP.st0000644000175000017500000021411012123404352014063 00000000000000"====================================================================== | | IMAP protocol support | | ======================================================================" "====================================================================== | | Copyright (c) 2000 Leslie A. Tyrrell | Copyright (c) 2009 Free Software Foundation | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" Namespace current: NetClients.IMAP [ Object subclass: IMAPCommand [ | client sequenceID name arguments status responses completionResponse promise | ResponseRegistry := nil. IMAPCommand class >> initialize [ "IMAPCommand initialize" (ResponseRegistry := Dictionary new) at: 'FETCH' put: #('FETCH' 'OK' 'NO' 'BAD'); at: 'SEARCH' put: #('SEARCH' 'OK' 'NO' 'BAD'); at: 'SELECT' put: #('FLAGS' 'EXISTS' 'RECENT' 'OK' 'NO' 'BAD'); at: 'EXAMINE' put: #('FLAGS' 'EXISTS' 'RECENT' 'OK' 'NO' 'BAD'); at: 'LIST' put: #('LIST' 'OK' 'NO' 'BAD'); at: 'LSUB' put: #('LSUB' 'OK' 'NO' 'BAD'); at: 'STATUS' put: #('STATUS'); at: 'EXPUNGE' put: #('EXPUNGE' 'OK' 'NO' 'BAD'); at: 'STORE' put: #('FETCH' 'OK' 'NO' 'BAD'); at: 'UID' put: #('FETCH' 'SEARCH' 'OK' 'NO' 'BAD'); at: 'CAPABILITY' put: #('CAPABILITY' 'OK' 'BAD'); at: 'STORE' put: #('FETCH'); at: 'LOGOUT' put: #('BYE' 'OK' 'BAD'); at: 'CLOSE' put: #('OK' 'NO' 'BAD'); at: 'CHECK' put: #('OK' 'NO'); at: 'APPEND' put: #('OK' 'NO' 'BAD'); at: 'SUBSCRIBE' put: #('OK' 'NO' 'BAD'); at: 'RENAME' put: #('OK' 'NO' 'BAD'); at: 'DELETE' put: #('OK' 'NO' 'BAD'); at: 'CREATE' put: #('OK' 'NO' 'BAD'); at: 'LOGIN' put: #('OK' 'NO' 'BAD'); at: 'AUTHENTICATE' put: #('OK' 'NO' 'BAD'); at: 'NOOP' put: #('OK' 'BAD') ] IMAPCommand class >> definedResponsesAt: aName [ ^self responseRegistry at: aName asUppercase ifAbsentPut: [IdentityDictionary new] ] IMAPCommand class >> responseRegistry [ ^ResponseRegistry ] IMAPCommand class >> forClient: anIMAPPI name: aString arguments: arguments [ "The intention here is to let users specify the complete string of command arguments. Because this string may contain atom-specials like $(, etc., this line may be sent as quoted string, which would be wrong. So we fool the printing logic to view this string as an atom. It is a hack, but seems like a convenient one" | args | args := arguments isCharacters ifTrue: [#atom -> arguments] ifFalse: [arguments]. ^self new forClient: anIMAPPI name: aString arguments: args ] IMAPCommand class >> login: aNameString password: aPassString [ ^self name: 'login' arguments: (Array with: #string -> aNameString with: #string -> aPassString) ] IMAPCommand class >> new [ ^self basicNew initialize ] IMAPCommand class >> parse: scanner [ "Read and parse next command from a stream. This is mainly useful for testing previously stored exchange logs" ^self new parse: scanner ] IMAPCommand class >> readFrom: aStream [ "Read and parse next command from a stream. This is mainly useful for testing previously stored exchange logs" ^self parse: (IMAPScanner on: aStream) ] arguments [ ^arguments ] arguments: anObject [ arguments := anObject ] client [ ^client ] client: anObject [ client := anObject ] name [ ^name ] name: anObject [ name := anObject ] sequenceID [ ^sequenceID ] sequenceID: anObject [ sequenceID := anObject ] completionResponse [ ^completionResponse ] completionResponse: anObject [ completionResponse := anObject. self beDone ] execute [ "Prepend the given command and send it to the server." self sendOn: client connectionStream. self client connectionStream nl. self beSent ] wait [ ^promise value ] definedResponses [ ^self class definedResponsesAt: self name asUppercase ] handle: aResponse [ (aResponse hasTag: self sequenceID) ifTrue: [self completionResponse: aResponse. ^true]. (self isDefinedResponse: aResponse) ifTrue: [self responses add: aResponse. ^true]. ^self notifyClientIfNeeded: aResponse ] isDefinedResponse: aResponse [ ^self definedResponses includes: aResponse cmdName ] needsClientNotification: aResponse [ ^false "^client isInterestedIn: aResponse" ] notifyClientIfNeeded: aResponse [ ^(self needsClientNotification: aResponse) ifTrue: [client handle: aResponse] ifFalse: [false] ] registerResponse: aResponse [ aResponse isCompletionResponse ifTrue: [self completionResponse: aResponse] ifFalse: [self responses add: aResponse] ] responses [ ^responses notNil ifTrue: [responses] ifFalse: [responses := OrderedCollection new] ] forClient: anIMAPPI name: aString arguments: args [ self client: anIMAPPI. self name: aString. self arguments: (self canonicalizeArguments: args) ] initialize [ promise := Promise new. responses := OrderedCollection new: 1 ] completedSuccessfully [ ^self successful ] parse: scanner [ "Read and parse next command from a stream. This is mainly useful for testing previously stored exchange logs" | tokens | tokens := scanner deepTokenizeAsAssociation. self sequenceID: tokens first value; name: (tokens at: 2) value; arguments: (tokens copyFrom: 3 to: tokens size) ] printCompletionResponseOn: aStream indent: level [ self completionResponse notNil ifTrue: [self completionResponse printOn: aStream indent: level] ] printOn: aStream [ self scanner printTokenList: self asTokenList on: aStream ] printResponseOn: aStream indent: level [ (self responces isNil or: [self responces isEmpty]) ifTrue: [^String new]. self responses do: [:eachResponse | aStream nl. eachResponse printOn: aStream indent: level] ] scanner [ ^IMAPScanner ] sendOn: aClient [ "aClient is a IMAPProtocolInterpreter" self client sendTokenList: self asTokenList ] asTokenList [ | list | list := OrderedCollection with: #atom -> self sequenceID with: #atom -> name. self arguments notNil ifTrue: [list addAll: self arguments]. ^list ] canonicalizeArguments: arguments [ "Arguments can one of: integer, string or array of thereof, potentially nested. Scalars are converted into array with this scalar as a sole element" arguments isNil ifTrue: [^Array new]. ^(arguments isCharacters or: [arguments isSequenceable not]) ifTrue: [^Array with: arguments] ifFalse: [arguments] ] promise [ ^promise ] commandResponse [ | coll | ^(coll := self commandResponses) isEmpty ifTrue: [nil] ifFalse: [coll first] ] commandResponses [ ^self responses select: [:resp | resp cmdName match: self name] ] commandResponseValue [ | resp | ^(resp := self commandResponse) isNil ifTrue: [nil] ifFalse: [resp value] ] statusResponses [ ^self responses select: [:eachResponse | eachResponse isStatusResponse] ] beDone [ self status: #done. self client commandIsDone: self. self value: self completionResponse ] beSent [ self status: #sent. self client commandIsInProgress: self ] status [ ^status ] status: anObject [ status := anObject ] value [ ^promise value ] value: anObject [ promise value: status ] failed [ ^self successful not ] isDone [ ^self status = #done ] isSent [ ^self status = #sent ] successful [ ^self isDone and: [self completionResponse isOK] ] ] ] Namespace current: NetClients.IMAP [ Object subclass: IMAPFetchedItem [ | name | IMAPFetchedItem class >> canBe: aName [ ^false ] IMAPFetchedItem class >> defaultFetchedItemClass [ ^IMAPFetchedItem ] IMAPFetchedItem class >> named: aName [ ^(self properSubclassForItemNamed: aName) new name: aName ] IMAPFetchedItem class >> properSubclassForItemNamed: aName [ ^IMAPFetchedItem allSubclasses detect: [:each | each canBe: aName] ifNone: [self defaultFetchedItemClass] ] extractContentFrom: tokenStream [ self subclassResponsibility ] name [ ^name ] name: aName [ name := aName ] ] ] Namespace current: NetClients.IMAP [ NetProtocolInterpreter subclass: IMAPProtocolInterpreter [ | responseStream commandSequencer mutex readResponseSemaphore continuationPromise commandsInProgress queuedCommands | commandPrefix: aString [ commandSequencer prefix: aString ] responseStream [ ^responseStream ] connect [ super connect. self resetCommandSequence. responseStream := self connectionStream. commandSequencer reset. self getResponse ] defaultCommandPrefix [ ^'imapv4_' ] defaultResponseClass [ ^IMAPResponse ] lineEndConvention [ ^LineEndCRLF ] commandIsDone: command [ mutex critical: [commandsInProgress remove: command ifAbsent: [^self]. readResponseSemaphore wait] ] commandIsInProgress: command [ mutex critical: [commandsInProgress addFirst: command. readResponseSemaphore signal] ] commandIsQueued: command [ ] connectionIsReady [ ] initialize [ super initialize. mutex := Semaphore forMutualExclusion. readResponseSemaphore := Semaphore new. queuedCommands := SharedQueue new. commandsInProgress := OrderedCollection new: 4. commandSequencer := IMAPCommandSequencer newPrefix: self defaultCommandPrefix. self commandReaderLoop fork. self responseReaderLoop fork ] commandReaderLoop [ | command | ^ [ [command := queuedCommands next. self class log: ['----------------------------------'] level: #IMAPClient. self class log: ['C: ' , command printString] level: #IMAPClient. command execute] repeat] ] commandsInProgress [ ^commandsInProgress ] nextCommandSequenceNumber [ ^commandSequencer next ] queuedCommands [ ^queuedCommands ] resetCommandSequence [ commandSequencer reset ] responseReaderLoop [ ^ [ [readResponseSemaphore wait; signal. self handleNextResponse] whileTrue] ] responseStream: stream [ "This is ONLY for debugging purposes" responseStream := stream ] executeCommand: aCommand [ aCommand sequenceID isNil ifTrue: [aCommand sequenceID: self nextCommandSequenceNumber]. queuedCommands nextPut: aCommand. self commandIsQueued: aCommand ] getResponse [ | resp | resp := self defaultResponseClass readFrom: self responseStream. self class log: [' S: ' , resp printLog] level: #IMAPServer. ^resp ] handle: aResponse [ ^self client handle: aResponse ] handleContinuationResponse: aResponse [ | promise | promise := continuationPromise. continuationPromise := nil. readResponseSemaphore wait. promise value: aResponse ] handleNextResponse [ | resp | resp := self getResponse. resp isNil ifTrue: [^false]. (self waitingForContinuation and: [resp isContinuationResponse]) ifTrue: [self handleContinuationResponse: resp. ^true]. commandsInProgress detect: [:command | command handle: resp] ifNone: [self handle: resp]. ^true ] waitForContinuation [ | promise | continuationPromise isNil ifTrue: [continuationPromise := Promise new]. promise := continuationPromise. readResponseSemaphore signal. ^promise value ] waitingForContinuation [ ^continuationPromise notNil ] argumentAsAssociation: argument [ (argument isKindOf: Association) ifTrue: [^argument]. argument isNil ifTrue: [^'NIL']. argument isCharacters ifTrue: [^#string -> argument]. (argument isKindOf: Number) ifTrue: [^#number -> argument]. argument isSequenceable ifTrue: [^#parenthesizedList -> argument]. ^argument ] sendLiteralString: string [ IMAPScanner printLiteralStringLength: string on: self connectionStream. self waitForContinuation. IMAPScanner printLiteralStringContents: string on: self connectionStream ] sendToken: token tokenType: tokenType [ tokenType = #literalString ifTrue: [self sendLiteralString: token] ifFalse: [IMAPScanner printToken: token tokenType: tokenType on: self connectionStream] ] sendTokenList: listOfTokens [ | assoc | listOfTokens do: [:arg | assoc := self argumentAsAssociation: arg. self sendToken: assoc value tokenType: assoc key] separatedBy: [self connectionStream space] ] ] ] Namespace current: NetClients.IMAP [ NetClient subclass: IMAPClient [ | state | IMAPClient class >> defaultPortNumber [ ^143 ] protocolInterpreter [ ^IMAPProtocolInterpreter ] state [ ^state ] state: aState [ state := aState. state client: self ] connected [ "Establish a connection to the host ." self state: IMAPNonAuthenticatedState new ] append: message to: aMailboxName [ ^self state append: message to: aMailboxName flags: nil date: nil ] append: message to: aMailboxName flags: flags date: dateString [ ^self state append: message to: aMailboxName flags: flags date: dateString ] capability [ ^self state capability ] check [ ^self state check ] close [ ^self state close ] create: aMailBoxName [ ^self state create: aMailBoxName ] delete: aMailBoxName [ ^self state delete: aMailBoxName ] examine: aMailBoxName [ ^self state examine: aMailBoxName ] expunge [ ^self state expunge ] fetch: aCriteria [ ^self state fetch: aCriteria ] fetch: messageNumbers retrieve: criteria [ ^self state fetch: messageNumbers retrieve: criteria ] fetchRFC822Messages: messageNumbers [ | result dict | result := self state fetch: messageNumbers retrieve: 'rfc822'. dict := Dictionary new: 4. ^result successful ifTrue: [result commandResponses do: [:resp | dict at: resp value put: (resp parameters at: 'RFC822')]. dict] ifFalse: [nil] ] list: refName mailbox: name [ ^self state list: refName mailbox: name ] login [ ^self state login ] logout [ ^self state logout ] lsub: refName mailbox: name [ ^self state lsub: refName mailbox: name ] noop [ ^self state noop ] rename: oldMailBox newName: newMailBox [ ^self state rename: oldMailBox newName: newMailBox ] search: aCriteria [ ^self state search: aCriteria ] select: aMailBoxName [ ^self state select: aMailBoxName ] status: aMailBoxNameWithArguments [ ^self state status: aMailBoxNameWithArguments ] store: args [ ^self state store: args ] subscribe: aMailBoxName [ ^self state subscribe: aMailBoxName ] uid: aString [ ^self state uid: aString ] unsubscribe: aMailBoxName [ ^self state unsubscribe: aMailBoxName ] commandClassFor: cmdName [ ^self class commandClassFor: cmdName ] createCommand: aString [ ^self createCommand: aString arguments: nil ] createCommand: aString arguments: anArray [ ^IMAPCommand forClient: clientPI name: aString arguments: anArray ] execute: cmd arguments: args changeStateTo: aStateBlock [ ^self execute: [self createCommand: cmd arguments: args] changeStateTo: aStateBlock ] execute: aBlock changeStateTo: aStateBlock [ | command | command := aBlock value. self executeCommand: command. command wait. command completedSuccessfully ifTrue: [self state: aStateBlock value]. ^command ] executeAndWait: aString [ ^self executeAndWait: aString arguments: nil ] executeAndWait: aString arguments: anArray [ | command | command := self createCommand: aString arguments: anArray. self executeCommand: command. command wait. ^command ] executeCommand: aCommand [ ^self clientPI executeCommand: aCommand ] canonicalizeMailboxName: aMailboxName [ "#todo. Mailbox names are encoded in UTF-7 format. Add encoding logic here when available" ^aMailboxName ] messageSetAsString: messageNumbers [ | stream | stream := (String new: 64) writeStream. messageNumbers do: [:messageNumber | stream nextPutAll: messageNumber] separatedBy: [stream nextPut: $,]. ^stream contents ] handle: aResponse [ "^aResponse" ^true ] ] ] Namespace current: NetClients.IMAP [ Object subclass: IMAPCommandSequencer [ | prefix value | IMAPCommandSequencer class >> new [ ^self basicNew initialize ] IMAPCommandSequencer class >> newPrefix: prefix [ ^(self new) prefix: prefix; yourself ] next [ self increment. ^self prefix , self value printString ] prefix [ ^prefix ] prefix: aValue [ prefix := aValue ] value [ ^value ] value: aValue [ value := aValue ] initialize [ value := 0 ] reset [ self value: 0 ] increment [ self value: self value + 1 ] ] ] Namespace current: NetClients.IMAP [ Object subclass: IMAPFetchedItemSectionSpecification [ | specName parameters span rawContent | IMAPFetchedItemSectionSpecification class >> readFrom: tokenStream [ | specName | specName := tokenStream next. specName isNil ifTrue: [specName := 'Empty']. ^((self properSubclassFor: specName) new) specName: specName; readFrom: tokenStream ] IMAPFetchedItemSectionSpecification class >> canBe: aName [ ^#('TEXT' 'MIME') includes: aName asUppercase ] IMAPFetchedItemSectionSpecification class >> defaultClass [ ^IMAPFetchedItemSectionSpecification ] IMAPFetchedItemSectionSpecification class >> properSubclassFor: aName [ ^IMAPFetchedItemSectionSpecification withAllSubclasses detect: [:each | each canBe: aName] ifNone: [self defaultClass] ] specName [ ^specName ] specName: aName [ specName := aName ] extractContentFrom: tokenStream [ " Check for a partial fetch- this would include a range specification given in angle brackets. Otherwise, there should only be a single token containing the requested content. " | peekStream | peekStream := tokenStream peek readStream. peekStream peek = $< ifTrue: [self extractSpannedContentSpanFrom: tokenStream] ifFalse: [rawContent := tokenStream next] ] extractSpannedContentSpanFrom: tokenStream [ "we've lost some information- we need the bytecount, but it is gone. Must revisit this!!" | startPoint | startPoint := ((tokenStream next readStream) next; upTo: $>) asNumber. rawContent := tokenStream next. "we're going to try to simply use the length of the raw content as the span length- however, this is not actually correct, though it is close." span := startPoint @ rawContent size ] rawContent [ ^rawContent ] readFrom: tokenStream [ " The section spec will be either numeric (if the message is MIME this is oK) or one of the following: 'HEADER' 'HEADER.FIELDS' 'HEADER.FIELDS.NOT' 'MIME' 'TEXT' Some examples would be: 1 1.HEADER HEADER HEADER.FIELDS 3.2.3.5.HEADER.FIELDS (to fetch header fields for part 3.2.3.5) " "the numeric part could be pulled out at this point as the position spec, followed by the section spec, then followed by optional? parameters." "positionSpec := ?" parameters := tokenStream next ] pvtFullSpan [ ^0 to: self rawContent size ] span [ "Items are not always requested in their entirety. The span tells us which part of the desired content was retrieved." ^span notNil ifTrue: [span] ifFalse: [self pvtFullSpan] ] span: anInterval [ "Items are not always requested in their entirety. The span tells us which part of the desired content was retrieved." span := anInterval ] ] ] Namespace current: NetClients.IMAP [ Object subclass: IMAPResponse [ | source cmdName value | IMAPResponse class >> defaultResponseClass [ ^IMAPResponse ] IMAPResponse class >> parse: scanner [ | theToken theResponse | theToken := scanner nextToken. theToken isNil ifTrue: [^nil]. " IMAP Server responses are classified as either tagged or untagged. Untagged responses begin with either the asterisk or plus sign, while tagged responses begin with the command id. " theResponse := (#($* '+') includes: theToken) ifTrue: [self parseUntagged: scanner withStar: theToken == $*] ifFalse: [self parseTagged: scanner withTag: theToken]. scanner upTo: Character nl. ^theResponse source: scanner sourceTrail; yourself ] IMAPResponse class >> parserForUntaggedResponse: responseName [ | properSubclass | properSubclass := IMAPResponse allSubclasses detect: [:each | each canParse: responseName] ifNone: [self defaultResponseClass]. ^properSubclass new ] IMAPResponse class >> parserTypeForTaggedStatus: status [ ^IMAPResponseTagged ] IMAPResponse class >> parseTagged: scanner withTag: tag [ | status | status := scanner nextToken. ^(self parserTypeForTaggedStatus: status) parse: scanner tag: tag status: status ] IMAPResponse class >> parseContinuationResponse: scanner [ ^IMAPContinuationResponse new ] IMAPResponse class >> parseUntagged: scanner withStar: isStar [ "An untagged responses might be a continuation responses. These begin with the plus sign rather than the asterisk." | token token2 | isStar ifFalse: [^self parseContinuationResponse: scanner]. token := scanner nextToken. "At this point, we know the response is untagged, but IMAP's untagged responses are not well designed. Some responses provide numeric data first, response or condition name second, while others do it the other way around. What we are doing here is determining what order these things are in, and then doing the parsing accordingly." ^token first isLetter ifTrue: [(self parserForUntaggedResponse: token) parse: scanner with: token] ifFalse: [token2 := scanner nextToken. (self parserForUntaggedResponse: token2) parse: scanner forCommandOrConditionNamed: token2 withValue: token] ] IMAPResponse class >> readFrom: stream [ ^self parse: (self scannerOn: stream) ] IMAPResponse class >> scannerOn: stream [ ^IMAPScanner on: stream ] IMAPResponse class >> canParse: responseName [ ^false ] cmdName [ ^cmdName ] cmdName: aString [ cmdName := aString ] source [ ^source ] source: aString [ source := aString ] tag [ ^nil ] value [ ^value ] value: aValue [ value := aValue ] parse: scanner [ self value: scanner deepTokenize ] parse: scanner forCommandOrConditionNamed: commandOrConditionName withValue: codeValue [ self cmdName: commandOrConditionName. self value: codeValue. self parse: scanner ] parse: scanner with: commandConditionOrStatusName [ self cmdName: commandConditionOrStatusName. self parse: scanner ] scanFrom: scanner [ self value: scanner deepTokenize ] scanFrom: scanner forCommandOrConditionNamed: commandOrConditionName withValue: codeValue [ self cmdName: commandOrConditionName. self value: codeValue. self scanFrom: scanner ] scanFrom: scanner with: commandConditionOrStatusName [ self cmdName: commandConditionOrStatusName. self scanFrom: scanner ] printLog [ ^self source ] printOn: stream [ source notNil ifTrue: [stream nextPutAll: source] ] hasTag: aString [ ^false ] isContinuationResponse [ ^false ] isStatusResponse [ ^false ] ] ] Namespace current: NetClients.IMAP [ IMAPResponse subclass: IMAPContinuationResponse [ isContinuationResponse [ ^true ] ] ] Namespace current: NetClients.IMAP [ Object subclass: IMAPState [ | client | IMAPState class >> forClient: client [ ^self new client: client ] client [ ^client ] capability [ ^client executeAndWait: 'capability' ] logout [ | command | (command := client executeAndWait: 'logout') completedSuccessfully ifTrue: [client state: IMAPState new]. ^command ] noop [ ^client executeAndWait: 'noop' ] append [ self signalError ] check: aClient [ self signalError ] close: aClient [ self signalError ] copy [ self signalError ] create: aClient arguments: aList [ self signalError ] delete: aClient arguments: aList [ self signalError ] examine: aClient arguments: aList [ self signalError ] expunge: aClient [ self signalError ] fetch: aClient arguments: aList [ self signalError ] list: aClient arguments: aList [ self signalError ] login: pi [ self signalError ] lsub: aClient arguments: aLIst [ self signalError ] rename: aClient arguments: aList [ self signalError ] search: aClient arguments: aLIst [ self signalError ] select: aClient arguments: aList [ self signalError ] status [ self signalError ] store: aClient arguments: aList [ self signalError ] subscribe: aClient arguments: aList [ self signalError ] uid: aClient arguments: aList [ self signalError ] unsubscribe: aClient arguments: aList [ self signalError ] signalError [ ^WrongStateError signal ] client: aValue [ client := aValue ] capability: aClient [ | command | ^(command := aClient executeAndWait: 'capability') completedSuccessfully ifTrue: [command] ifFalse: [false] ] logout: aClient [ | command | (command := aClient executeAndWait: 'logout') completedSuccessfully ifTrue: [aClient state: IMAPState new]. ^command ] noop: client [ | command | ^(command := client executeAndWait: 'noop') completedSuccessfully ifTrue: [command] ifFalse: [false] ] isAuthenticated [ ^false ] isSelected [ ^false ] ] ] Namespace current: NetClients.IMAP [ IMAPResponse subclass: IMAPDataResponse [ IMAPDataResponse class >> canParse: responseName [ ^false ] ] ] Namespace current: NetClients.IMAP [ IMAPState subclass: IMAPAuthenticatedState [ append: message to: aMailboxName flags: flags date: dateString [ | args | args := OrderedCollection with: (client canonicalizeMailboxName: aMailboxName). flags notNil ifTrue: [args add: flags]. dateString notNil ifTrue: [args add: #atom -> dateString]. args add: #literalString -> message. ^client executeAndWait: 'append' arguments: args ] create: aMailboxName [ ^client execute: 'create' arguments: aMailboxName changeStateTo: [IMAPSelectedState new] ] delete: aMailboxName [ ^client executeAndWait: 'delete' arguments: aMailboxName ] examine: aMailBoxName [ ^client execute: 'examine' arguments: aMailBoxName changeStateTo: [IMAPSelectedState new] ] list: refName mailbox: name [ ^client executeAndWait: 'list' arguments: (Array with: refName with: name) ] lsub: refName mailbox: name [ ^client executeAndWait: 'lsub' arguments: (Array with: refName with: name) ] rename: oldMailBox newName: newMailBox [ ^client executeAndWait: 'rename' arguments: (Array with: oldMailBox with: newMailBox) ] select: aMailBoxName [ ^client execute: 'select' arguments: aMailBoxName changeStateTo: [IMAPSelectedState new] ] status: aMailBoxNameWithArguments [ ^client executeAndWait: 'status' arguments: aMailBoxNameWithArguments "arguments: (Array with: aMailBoxNameWithArguments)" ] subscribe: aMailBoxName [ ^client executeAndWait: 'subscribe' arguments: (Array with: aMailBoxName) ] unsubscribe: aMailBoxName [ ^client executeAndWait: 'unsubscribe' arguments: (Array with: aMailBoxName) ] create: aClient arguments: aList [ | command | ^(command := aClient executeAndWait: 'create' arguments: aList) completedSuccessfully ifTrue: [aClient state: IMAPSelectedState new. command] ifFalse: [false] ] delete: aClient arguments: aList [ | command | ^(command := aClient executeAndWait: 'delete' arguments: aList) completedSuccessfully ifTrue: [command] ifFalse: [nil] ] examine: aClient arguments: aList [ | command | ^(command := aClient executeAndWait: 'examine' arguments: aList) completedSuccessfully ifTrue: [aClient state: IMAPSelectedState new. command] ifFalse: [nil] ] list: aClient arguments: aList [ | command | ^(command := aClient executeAndWait: 'list' arguments: aList) completedSuccessfully ifTrue: [command] ifFalse: [nil] ] lsub: aClient arguments: aList [ | command | ^(command := aClient executeAndWait: 'lsub' arguments: aList) completedSuccessfully ifTrue: [command] ifFalse: [nil] ] rename: aClient arguments: aList [ | command | ^(command := aClient executeAndWait: 'rename' arguments: aList) completedSuccessfully ifTrue: [command] ifFalse: [nil] ] select: aClient arguments: aList [ | command | ^(command := aClient executeAndWait: 'select' arguments: aList) completedSuccessfully ifTrue: [aClient state: IMAPSelectedState new. command] ifFalse: [nil] ] subscribe: aClient arguments: aList [ | command | ^(command := aClient executeAndWait: 'subscribe' arguments: aList) completedSuccessfully ifTrue: [command] ifFalse: [nil] ] unsubscribe: aClient arguments: aList [ | command | ^(command := aClient executeAndWait: 'unsubscribe' arguments: aList) completedSuccessfully ifTrue: [command] ifFalse: [nil] ] isAuthenticated [ ^true ] ] ] Namespace current: NetClients.IMAP [ IMAPResponse subclass: IMAPStatusResponse [ | text status | IMAPStatusResponse class >> canParse: commandOrConditionName [ ^#('OK' 'NO' 'BAD' 'BYE') includes: commandOrConditionName ] status [ ^status ] status: aStatus [ status := aStatus ] text [ ^text ] parse: scanner [ | val key | scanner skipWhiteSpace. (scanner peekFor: $[) ifTrue: [self value: OrderedCollection new. scanner flagBracketSpecial: true. key := scanner nextToken asUppercase. (#('UIDVALIDITY' 'UNSEEN') includes: key) ifTrue: [val := scanner nextToken asNumber]. 'PERMANENTFLAGS' = key ifTrue: [val := scanner deepNextToken]. 'NEWNAME' = key ifTrue: [| old new | old := scanner nextToken. new := scanner nextToken. val := Array with: old with: new]. [scanner nextToken ~~ $] and: [scanner tokenType ~= #doIt]] whileTrue. scanner flagBracketSpecial: false]. text := scanner scanText. (#('ALERT' 'PARSE' 'TRYCREATE' 'READ-ONLY' 'READ-WRITE') includes: key) ifTrue: [val := text]. self value: key -> val ] parse: scanner with: commandConditionOrStatusName [ self cmdName: commandConditionOrStatusName. self status: commandConditionOrStatusName. self parse: scanner ] isBad [ ^self status = 'BAD' ] isNotAccepted [ ^self status = 'NO' ] isOK [ ^self status = 'OK' ] isStatusResponse [ ^true ] ] ] Namespace current: NetClients.IMAP [ IMAPResponse subclass: IMAPCommandCompletionResponse [ ] ] Namespace current: NetClients.IMAP [ IMAPFetchedItem subclass: IMAPBodySectionFetchedItem [ | sectionSpec | IMAPBodySectionFetchedItem class >> canBe: aName [ " Can the reciever represent items fetched using the given name? This is not as straightforward as it ought to be. IMAPv4 uses 'BODY' fetches in two very different ways, so we will have to be careful about that. For now, we are not making the distinction, so we will have to revisit this in the future. Also, note that we don't include 'RFC822.SIZE'. Such a fetch does not return anything complex- it's actually just a simple metadata fetch. " "^#( 'BODY' 'BODY.PEEK' 'RFC822' 'RFC822.HEADER' 'RFC822.TEXT' ) includes: aName." ^false ] sectionSpec [ ^sectionSpec ] extractContentFrom: tokenStream [ " For the body parts extraction case, tokens will be something like: $[ 'HEADER.FIELDS' #('FIELD1' 'FIELD2') $] '...content as described above...' Whereas for the body (structure) case, the tokens will be something like: #('TEXT' 'PLAIN' #('CHARSET' 'us-ascii') nil nil '8BIT' '763' '8') What a screwed up spec. " "devel thought: It might would be good if the reciever could tell what had been requested, and what had been recieved." | specTokens | specTokens := tokenStream upTo: $[; upTo: $]. (self sectionSpecificationFrom: specTokens) extractContentFrom: tokenStream ] sectionSpecificationFrom: tokens [ ^sectionSpec := IMAPFetchedItemSectionSpecification readFrom: tokens readStream ] headerFieldNamed: aName ifAbsent: aBlock [ "hmm... need a more compex example here." self halt ] ] ] Namespace current: NetClients.IMAP [ IMAPState subclass: IMAPNonAuthenticatedState [ authenticate [ ] login [ ^client execute: 'login' arguments: (Array with: client user username with: client user password) changeStateTo: [IMAPAuthenticatedState new] ] login: aClient arguments: aList [ | command | command := aClient executeAndWait: 'login' arguments: aList. command completedSuccessfully ifTrue: [aClient state: IMAPAuthenticatedState new]. ^command ] ] ] Namespace current: NetClients.IMAP [ IMAPFetchedItem subclass: IMAPMessageEnvelopeFetchedItem [ | envelope | IMAPMessageEnvelopeFetchedItem class >> canBe: aName [ " Can the reciever represent items fetched using the given name? Note that we include 'RFC822.SIZE' . This is just a simple metadata fetch, unlike such things as 'RFC822' or 'RFC822.HEADER' . " ^'ENVELOPE' = aName ] bccLine [ ^self envelope at: 8 ] ccLine [ ^self envelope at: 7 ] dateLine [ ^self envelope at: 1 ] fromAuthor [ ^(self fromLine at: 1) at: 1 ] fromLine [ ^self envelope at: 3 ] inReplyToLine [ ^self envelope at: 9 ] replyToAuthor [ ^(self replyToLine at: 1) at: 1 ] replyToLine [ ^self envelope at: 5 ] senderAuthor [ ^(self senderLine at: 1) at: 1 ] senderLine [ ^self envelope at: 4 ] subjectLine [ ^self envelope at: 2 ] toLine [ ^self envelope at: 6 ] uniqueMessageIDLine [ ^self envelope at: 10 ] extractContentFrom: tokenStream [ "the envelope is an array of message metadata- we'll come back to this for interpretation later." self envelope: tokenStream next ] envelope [ ^envelope ] envelope: anArray [ "We have yet to interpret the contents of the given array... we shall need to get to that later." envelope := anArray ] printDevelOn: aStream indent: level [ aStream crtab: level; nextPutAll: 'Date: '; nextPutAll: self dateLine; crtab: level; nextPutAll: 'Subject: '; nextPutAll: self subjectLine; crtab: level; nextPutAll: 'From: '; print: self fromAuthor; crtab: level; nextPutAll: 'Sender: '; print: self senderAuthor; crtab: level; nextPutAll: 'ReplyTo: '; print: self replyToAuthor; crtab: level; nextPutAll: 'To: '; print: self toLine; crtab: level; nextPutAll: 'In Reply To: '; print: self inReplyToLine; crtab: level; nextPutAll: 'Message ID: '; nextPutAll: self uniqueMessageIDLine; crtab: level; nextPutAll: 'Bcc: '; print: self bccLine; crtab: level; nextPutAll: 'Cc: '; print: self ccLine; yourself ] printOn: aStream [ self printDevelOn: aStream indent: 0 ] ] ] Namespace current: NetClients.IMAP [ IMAPFetchedItem subclass: IMAPBodyRFC822FetchedItem [ | value | IMAPBodyRFC822FetchedItem class >> canBe: aName [ " Note that we don't include 'RFC822.SIZE'. Such a fetch does not return anything complex- it's actually just a simple metadata fetch. " ^#('RFC822' 'RFC822.HEADER' 'RFC822.TEXT') includes: aName ] extractContentFrom: tokenStream [ " Cases: RFC822 RFC822.Header RFC822.Text " value := tokenStream next ] ] ] Namespace current: NetClients.IMAP [ IMAPFetchedItem subclass: IMAPMessageMetadataFetchedItem [ | value | IMAPMessageMetadataFetchedItem class >> canBe: aName [ " Can the reciever represent items fetched using the given name? Note that we include 'RFC822.SIZE' . This is just a simple metadata fetch, unlike such things as 'RFC822' or 'RFC822.HEADER' . " ^#('FLAGS' 'INTERNALDATE' 'RFC822.SIZE' 'UID') includes: aName ] extractContentFrom: tokenStream [ self value: tokenStream next ] value [ ^value ] value: anObject [ value := anObject ] ] ] Namespace current: NetClients.IMAP [ IMAPFetchedItemSectionSpecification subclass: IMAPFetchedItemHeaderSectionSpecification [ IMAPFetchedItemHeaderSectionSpecification class >> canBe: aName [ ^'HEADER*' match: aName ignoreCase: true ] ] ] Namespace current: NetClients.IMAP [ IMAPFetchedItem subclass: IMAPBodyStructureFetchedItem [ | structure | IMAPBodyStructureFetchedItem class >> canBe: aName [ ^'BODYSTRUCTURE' = aName ] structure [ ^structure ] structure: aStructure [ structure := aStructure ] extractContentFrom: tokenStream [ " The structure will be something like: #('TEXT' 'PLAIN' #('CHARSET' 'us-ascii') nil nil '8BIT' '763' '8') " self structure: tokenStream next ] ] ] Namespace current: NetClients.IMAP [ IMAPFetchedItem subclass: IMAPBodyFetchedItem [ | parts | IMAPBodyFetchedItem class >> canBe: aName [ " Can the reciever represent items fetched using the given name? This is not as straightforward as it ought to be. IMAPv4 uses 'BODY' fetches in two very different ways, so we will have to be careful about that. For now, we are not making the distinction, so we will have to revisit this in the future. " ^#('BODY' 'BODY.PEEK') includes: aName ] extractBodySectionContentFrom: tokenStream [ self parts add: (IMAPBodySectionFetchedItem new extractContentFrom: tokenStream) ] extractContentFrom: tokenStream [ " For the body parts extraction case, tokens will be something like: $[ 'HEADER.FIELDS' #('FIELD1' 'FIELD2') $] '...content as described above...' Whereas for the body (structure) case, the tokens will be something like: #('TEXT' 'PLAIN' #('CHARSET' 'us-ascii') nil nil '8BIT' '763' '8') What a screwed up spec. " "devel thought: It might would be good if the reciever could tell what had been requested, and what had been recieved." "First off, are we talking about a body section fetch, or a short-form body structure fetch? Bastards!!" tokenStream peek = $[ ifTrue: [self extractBodySectionContentFrom: tokenStream] ifFalse: [self extractShortFormBodyStructureFrom: tokenStream] ] extractShortFormBodyStructureFrom: tokenStream [ " Whereas for the body (structure) case, the tokens will be something like: #('TEXT' 'PLAIN' #('CHARSET' 'us-ascii') nil nil '8BIT' '763' '8') " self parts add: (IMAPBodyStructureFetchedItem new extractContentFrom: tokenStream) ] parts [ ^parts notNil ifTrue: [parts] ifFalse: [parts := OrderedCollection new] ] ] ] Namespace current: NetClients.IMAP [ IMAPDataResponse subclass: IMAPDataResponseFetch [ | fetchedItems metaResponses | IMAPDataResponseFetch class >> canParse: responseName [ ^'FETCH' = responseName "^false" ] bodyFetch [ ^self fetchedItemNamed: 'body' ifAbsent: [nil] ] bodyText [ ^(self fetchedItemNamed: 'body') parts first sectionSpec rawContent ] envelope [ ^self fetchedItemNamed: 'envelope' ifAbsent: [nil] ] extractFetchedItemsFrom: tokenStream [ [tokenStream atEnd not and: [self fetchableItemNames includes: tokenStream peek]] whileTrue: [(self newFetchedItemNamed: tokenStream next) extractContentFrom: tokenStream] ] fetchableItemNames [ ^#('ALL' 'BODY' 'BODY.PEEK' 'BODYSTRUCTURE' 'ENVELOPE' 'FAST' 'FULL' 'FLAGS' 'INTERNALDATE' 'RFC822' 'RFC822.HEADER' 'RFC822.SIZE' 'RFC822.TEXT' 'UID') "actually, there are two forms represented by this name- see the spec." ] fetchedHeaderNamed: aHeaderName ifAbsent: aBlock [ ^self headerFetch fieldNamed: aHeaderName ifAbsent: [aBlock value] ] fetchedItemNamed: aName [ ^self fetchedItemNamed: aName ifAbsent: [nil] ] fetchedItemNamed: aName ifAbsent: aBlock [ | seekName | seekName := aName asLowercase. ^self fetchedItems at: seekName ifAbsent: [aBlock value] ] fetchedItems [ ^fetchedItems notNil ifTrue: [fetchedItems] ifFalse: [fetchedItems := Dictionary new] ] hasUID [ ^self fetchedItems includesKey: 'uid' ] hasUniqueMessageID [ ^self hasFetchedItemHaving: 'message-ID' ] itemHolding: anItemName [ ^self fetchedItems traverse: [:eachItem | eachItem] seeking: [:eachItem | eachItem holds: anItemName] ] newFetchedItemNamed: aName [ ^self fetchedItems at: aName asLowercase put: (IMAPFetchedItem named: aName) ] rawUniqueMessageID [ "If available, answer the unique message ID as provided within the message's headers." ^self bodyFetch headerFieldNamed: 'message-ID' ifAbsent: [nil] ] uid [ "The UID is an item that may or not have been fetched by the reciever." | uidRaw | uidRaw := self fetchedItemNamed: 'UID' ifAbsent: [nil]. ^uidRaw notNil ifTrue: [uidRaw value asNumber] ifFalse: [nil] ] messageNumber [ ^self sequenceNumber ] messageNumber: aNumber [ self sequenceNumber: aNumber ] messageSequenceNumber [ ^self sequenceNumber ] sequenceNumber [ ^self fetchedItemNamed: 'sequence_number' ] sequenceNumber: aNumber [ ^self fetchedItems at: 'sequence_number' put: aNumber ] metaResponses [ ^metaResponses ] metaResponses: statusResponses [ metaResponses := statusResponses ] parse: scanner [ | tokens | scanner flagBracketSpecial: true. tokens := scanner deepNextToken. scanner flagBracketSpecial: false. self extractFetchedItemsFrom: tokens readStream ] value: aNumber [ self sequenceNumber: (value := aNumber) ] ] ] Namespace current: NetClients.IMAP [ IMAPStatusResponse subclass: IMAPResponseMailboxStatus [ IMAPResponseMailboxStatus class >> canParse: conditionName [ "should be more- I need to check this." ^#('UNSEEN' 'EXISTS') includes: conditionName ] parse: scanner [ self halt. super parse: scanner ] parse: scanner forCommandOrConditionNamed: commandOrConditionName withValue: codeValue [ self cmdName: commandOrConditionName. self value: codeValue ] ] ] Namespace current: NetClients.IMAP [ IMAPStatusResponse subclass: IMAPResponseTagged [ IMAPResponseTagged class >> parse: scanner tag: tag status: status [ ^self new parse: scanner tag: tag status: status ] IMAPResponseTagged class >> scanFrom: scanner tag: tag status: status [ ^self new scanFrom: scanner tag: tag status: status ] IMAPResponseTagged class >> canParse: cmdName [ ^false ] tag [ ^self cmdName ] text [ ^text ] parse: scanner tag: tag status: statusString [ self cmdName: tag. self status: statusString. ^self parse: scanner ] hasTag: tagString [ ^self tag match: tagString ] ] ] Namespace current: NetClients.IMAP [ IMAPDataResponse subclass: IMAPDataResponseSearch [ IMAPDataResponseSearch class >> canParse: responseName [ ^'SEARCH' = responseName ] basicIDSequences [ | intervals currentStart currentStop currentInterval | intervals := OrderedCollection new. currentInterval := -1 -> -1. self numericIDs do: [:eachNumericID | eachNumericID = (currentInterval value + 1) ifTrue: [currentInterval value: eachNumericID] ifFalse: [currentStop := currentStart := eachNumericID. intervals add: (currentInterval := currentStart -> currentStop)]]. ^intervals collect: [:eachInterval | eachInterval key = eachInterval value ifTrue: [eachInterval key printString] ifFalse: [eachInterval key printString , ':' , eachInterval value printString]] ] idSequences [ " This would be a good place to further condense the basic id sequences. Currently we offer a series of ranges, but these ranges could be combined, eg: #('1:123' '231:321' etc...) could become: #('1:123, 231:321' etc...) This would reduce the number of fetch requests that would be needed to retrieve the messages identified by the search response. " ^self basicIDSequences ] numericIDs [ ^self rawIDs collect: [:eachRawID | eachRawID asNumber] ] rawIDs [ ^self value ] ] ] Namespace current: NetClients.IMAP [ IMAPAuthenticatedState subclass: IMAPSelectedState [ check [ ^client executeAndWait: 'check' ] close [ ^client execute: 'close' arguments: nil changeStateTo: [IMAPAuthenticatedState new] ] copy [ ] expunge [ ^client executeAndWait: 'expunge' ] fetch: aCriteria [ ^client executeAndWait: 'fetch' arguments: aCriteria ] fetch: messageNumbers retrieve: criteria [ | msgString args | msgString := client messageSetAsString: messageNumbers. args := OrderedCollection with: msgString. criteria notNil ifTrue: [criteria isCharacters ifTrue: [args add: criteria] ifFalse: [args addAll: criteria]]. ^client executeAndWait: 'fetch' arguments: args ] search: aCriteria [ ^client executeAndWait: 'search' arguments: aCriteria ] store: args [ ^client executeAndWait: 'store' arguments: args ] uid: aString [ ^client executeAndWait: 'uid' arguments: aString ] check: aClient [ ^client executeAndWait: 'check' ] close: aClient [ | command | ^(command := aClient executeAndWait: 'close') completedSuccessfully ifTrue: [aClient state: IMAPAuthenticatedState new. command] ifFalse: [nil] ] expunge: aClient [ | command | ^(command := aClient executeAndWait: 'expunge') completedSuccessfully ifTrue: [command] ifFalse: [nil] ] fetch: aClient arguments: aList [ | command | ^(command := aClient executeAndWait: 'fetch' arguments: aList) completedSuccessfully ifTrue: [command] ifFalse: [nil] ] search: aClient arguments: aList [ | command | ^(command := aClient executeAndWait: 'search' arguments: aList) completedSuccessfully ifTrue: [command] ifFalse: [nil] ] store: aClient arguments: aList [ | command | ^(command := aClient executeAndWait: 'store' arguments: aList) completedSuccessfully ifTrue: [command] ifFalse: [nil] ] isSelected [ ^true ] ] ] Namespace current: NetClients.IMAP [ IMAPDataResponse subclass: IMAPDataResponseList [ | mbAttributes mbDelimiter mbName | IMAPDataResponseList class >> canParse: cmdName [ ^'LIST' = cmdName ] mbAttributes [ ^mbAttributes ] mbDelimeter [ ^mbDelimiter ] mbName [ ^mbName ] parse: scanner [ "Parse message attributes" "(\NOSELECT) '/' ~/Mail/foo" | tokens | tokens := scanner deepTokenize. mbAttributes := tokens at: 1. mbDelimiter := tokens at: 2. mbName := tokens at: 3 ] ] ] Namespace current: NetClients.IMAP [ MIME.MailScanner subclass: IMAPScanner [ | flagBracketSpecial | TextMask := nil. QuotedTextMask := nil. QuotedPairChar := nil. AtomMask := nil. IMAPScanner class >> atomSpecials [ "These characters cannot occur inside an atom" ^'( ){%*"\' ] IMAPScanner class >> specials [ ^self atomSpecials ] IMAPScanner class >> initClassificationTable [ super initClassificationTable. self initClassificationTableWith: TextMask when: [:c | c ~~ Character cr]. self initClassificationTableWith: AtomMask when: [:c | c > Character space and: [(self atomSpecials includes: c) not]]. self initClassificationTableWith: QuotedTextMask when: [:c | c ~~ $" and: [c ~~ $\ and: [c ~~ Character cr]]] ] IMAPScanner class >> initialize [ "IMAPScanner initialize" self initializeConstants; initClassificationTable ] IMAPScanner class >> initializeConstants [ AtomMask := 256. QuotedTextMask := 4096. TextMask := 8192 ] IMAPScanner class >> defaultTokenType [ ^#string ] IMAPScanner class >> printAtom: atom on: stream [ atom isNil ifTrue: [stream nextPutAll: 'NIL'] ifFalse: [stream nextPutAll: atom "asUppercase"] ] IMAPScanner class >> printIMAPString: value on: stream [ "Print string as either atom or quoted text" value isNil ifTrue: [self printNilOn: stream]. (self shouldBeQuoted: value) ifTrue: [self printQuotedText: value on: stream] ifFalse: [self printAtom: value on: stream] ] IMAPScanner class >> printLiteralString: aString on: stream [ "Note that this method is good for printing but not for sending. IMAP requires sender to send string length, then wait for continuation response" self printLiteralStringLength: aString on: stream. self printLiteralStringContents: aString on: stream ] IMAPScanner class >> printLiteralStringContents: aString on: stream [ stream nextPutAll: aString ] IMAPScanner class >> printLiteralStringLength: aString on: stream [ stream nextPut: ${. aString size printOn: stream. stream nextPut: $}; nl ] IMAPScanner class >> printNilOn: stream [ stream nextPutAll: 'NIL' ] IMAPScanner class >> printParenthesizedList: arrayOfAssociations on: stream [ "In order to accurately print parenthesized list, we need to know token types of every element. This is applied recursively" stream nextPut: $(. self printTokenList: arrayOfAssociations on: stream. stream nextPut: $) ] IMAPScanner class >> printToken: value tokenType: aSymbol on: stream [ aSymbol = #string ifTrue: [^self printIMAPString: value on: stream]. aSymbol = #literalString ifTrue: [^self printLiteralString: value on: stream]. aSymbol = #atom ifTrue: [^self printAtom: value on: stream]. aSymbol = #quotedText ifTrue: [^self printQuotedText: value on: stream]. aSymbol = #nil ifTrue: [^self printNilOn: stream]. aSymbol = #parenthesizedList ifTrue: [^self printParenthesizedList: value on: stream]. "Invalid token type" aSymbol = #special ifTrue: [^stream nextPut: value]. self halt ] IMAPScanner class >> stringAsAssociation: string [ (self shouldBeQuoted: string) ifFalse: [^#atom -> string]. (string first == $\ and: [string size > 1 and: [self shouldBeQuoted: (string copyFrom: 2 to: string size) not]]) ifTrue: [^#atom -> string]. ^#quotedText -> string ] IMAPScanner class >> tokenAsAssociation: token [ (token isKindOf: Association) ifTrue: [^token]. token isNil ifTrue: [^'NIL']. token isCharacters ifTrue: [^self stringAsAssociation: token]. (token isKindOf: Number) ifTrue: [^#number -> token]. token isSequenceable ifTrue: [^#parenthesizedList -> token]. ^token ] IMAPScanner class >> isAtomChar: char [ ^((self classificationTable at: char asInteger + 1) bitAnd: AtomMask) ~= 0 ] IMAPScanner class >> shouldBeQuoted: string [ ^(string detect: [:char | (self isAtomChar: char) not] ifNone: [nil]) notNil ] flagBracketSpecial [ flagBracketSpecial isNil ifTrue: [flagBracketSpecial := false]. ^flagBracketSpecial ] flagBracketSpecial: aBoolean [ flagBracketSpecial := aBoolean ] doSpecialScanProcessing [ "Hacks that require special handling of IMAP tokens go here. The most frustrating one for us was handling of message/mailbox flags that have format \ as in \Seen. The problem is that $\ is not an atom-char, so these flags are tokenized as #($\ 'Seen'). We make heuristical decision here if current token is $\ immediately followed by a letter. We will then read next token and merge $\ and next token answering a string. This is ONLY applied inside a parenthesized list" (token == $\ and: [(self classificationMaskFor: self peek) anyMask: AlphabeticMask]) ifTrue: [self nextToken. token := '\' , token. tokenType := #string] ] scanAtom [ "atom = 1*" token := self scanWhile: [(self isBracketSpecial: hereChar) not and: [self matchCharacterType: AtomMask]]. (token match: 'NIL') ifTrue: ["RFC2060 defines NIL as a special atom type, atoms are not case-sensitive" token := nil. tokenType := #nil] ifFalse: [tokenType := #atom]. ^token ] scanLiteralText [ "<{> nnn <}> " | nbytes string | nbytes := self scanLiteralTextLength. string := self nextBytesAsString: nbytes. token := string copyReplaceAll: (String with: Character cr with: Character nl) with: (String with: Character nl). tokenType := #literalString. ^token ] scanLiteralTextLength [ "<{> nnn <}> " "We are positioned at the first brace character" token := self scanToken: [self matchCharacterType: DigitMask] delimitedBy: '{}' notify: 'Malformed literal length'. self upTo: Character nl. ^Integer readFrom: token readStream ] scanParenthesizedList [ | stream | stream := (Array new: 4) writeStream. self mustMatch: $( notify: 'Parenthesized list should begin with ('. self deepTokenizeUntil: [token == $)] do: [self doSpecialScanProcessing. stream nextPut: token]. token ~~ $) ifTrue: [self notify: 'Non-terminated parenthesized list']. token := stream contents. tokenType := #parenthesizedList. ^token ] scanParenthesizedListAsAssociation [ | stream | stream := (Array new: 4) writeStream. self mustMatch: $( notify: 'Parenthesized list should begin with ('. self deepTokenizeAsAssociationUntil: [token == $)] do: [:assoc | self doSpecialScanProcessing. stream nextPut: tokenType -> token]. token ~~ $) ifTrue: [self notify: 'Non-terminated parenthesized list']. token := stream contents. tokenType := #parenthesizedList. ^tokenType -> token ] scanQuotedChar [ "Scan possible quoted character. If the current char is $\, read in next character and make it a quoted string character" ^hereChar == $\ ifTrue: [self step. classificationMask := QuotedTextMask. true] ifFalse: [false] ] scanQuotedText [ "quoted-string = <" "> *(quoted_char / quoted-pair) <" "> quoted_char = and <\>" "We are positioned at the first double quote character" token := self scanToken: [self scanQuotedChar; matchCharacterType: QuotedTextMask] delimitedBy: '""' notify: 'Unmatched quoted text'. tokenType := #quotedText. ^token ] scanText [ "RFC822: text = ^self skipWhiteSpace; scanWhile: [(self matchCharacterType: CRLFMask) not] ] printLiteralString: aString on: stream [ self class printLiteralStringLength: aString on: stream. self class printLiteralStringContents: aString on: stream ] isBracketSpecial: char [ ^self flagBracketSpecial and: ['[]' includes: char] ] nextBytesAsString: nbytes [ | str | ^source isExternalStream ifTrue: [ [self binary. str := (source next: nbytes) asString. self sourceTrailNextPutAll: str. str] ensure: [self text]] ifFalse: [super next: nbytes] ] nextIMAPToken [ | char | self skipWhiteSpace. char := self peek. char isNil ifTrue: ["end of input" tokenType := #doIt. ^token := nil]. char == $" ifTrue: [^self scanQuotedText]. char == ${ ifTrue: [^self scanLiteralText]. (char < Character space or: [(self specials includes: char) or: [self isBracketSpecial: char]]) ifTrue: ["Special character. Make it token value and set token type" tokenType := #special. token := self next. ^token]. (self matchCharacterType: AtomMask) ifTrue: [^self scanAtom]. tokenType := #doIt. token := char. ^token ] deepNextToken [ ^self nextToken == $( ifTrue: [self stepBack; scanParenthesizedList] ifFalse: [token] ] deepNextTokenAsAssociation [ ^self nextToken == $( ifTrue: [self stepBack; scanParenthesizedListAsAssociation] ifFalse: [tokenType -> token] ] deepTokenize [ | stream | stream := (Array new: 4) writeStream. [self deepNextToken. tokenType = #doIt or: [token == Character cr or: [token == Character nl]]] whileFalse: [stream nextPut: token]. token == Character cr ifTrue: [self stepBack]. token == Character nl ifTrue: [self stepBack]. ^stream contents ] deepTokenizeAsAssociation [ | stream assoc | stream := (Array new: 4) writeStream. [assoc := self deepNextTokenAsAssociation. assoc key = #doIt] whileFalse: [stream nextPut: assoc]. ^stream contents ] deepTokenizeAsAssociationUntil: aBlock do: actionBlock [ | assoc | [self skipWhiteSpace. assoc := self deepNextTokenAsAssociation. assoc key = #doIt or: aBlock] whileFalse: [actionBlock value: assoc] ] deepTokenizeUntil: aBlock do: actionBlock [ [self skipWhiteSpace; deepNextToken. tokenType == #doIt or: aBlock] whileFalse: [actionBlock value] ] nextToken [ ^self nextIMAPToken ] specials [ ^self class atomSpecials ] ] ] Namespace current: NetClients.IMAP [ IMAPDataResponseList subclass: IMAPDataResponseLSub [ IMAPDataResponseLSub class >> canParse: cmdName [ ^'LSUB' = cmdName ] ] ] Namespace current: NetClients.IMAP [ IMAPCommand initialize. IMAPScanner initialize ] smalltalk-3.2.5/packages/net/gnutls-wrapper.c0000644000175000017500000001263612123404352016134 00000000000000/* * Copyright (C) 2000, 2001, 2002, 2003, 2004, 2005, 2006, 2007, 2008, * 2009, 2010 Free Software Foundation, Inc. * * Based on the gnutls-cli.c file distributed with GnuTLS. * * GNU Smalltalk is free software: you can redistribute it and/or modify * it under the terms of the GNU General Public License as published by * the Free Software Foundation, either version 3 of the License, or * (at your option) any later version. * * GNU Smalltalk is distributed in the hope that it will be useful, * but WITHOUT ANY WARRANTY; without even the implied warranty of * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the * GNU General Public License for more details. * * You should have received a copy of the GNU General Public License * along with this program. If not, see . */ #include #include #include #include #include #include #include #include "socketx.h" #if defined HAVE_GNUTLS && (defined O_NONBLOCK || defined FIONBIO) #include #define MAX_BUF 4096 /* Returns zero if the error code was successfully handled. */ static int handle_error (gnutls_session_t session, int err) { if (err == GNUTLS_E_REHANDSHAKE) gnutls_alert_send (session, GNUTLS_AL_WARNING, GNUTLS_A_NO_RENEGOTIATION); if (err < 0 && gnutls_error_is_fatal (err)) return err; else return 0; } static int do_handshake (gnutls_session_t session) { int ret; do { ret = gnutls_handshake (session); if (ret < 0) handle_error (session, ret); } while (ret < 0 && gnutls_error_is_fatal (ret) == 0); if (ret != 0) gnutls_alert_send_appropriate (session, ret); return ret; } static int socket_open (const char *hostname, const char *service) { struct addrinfo hints, *res, *ptr; int fd, err; /* get server name */ memset (&hints, 0, sizeof (hints)); hints.ai_socktype = SOCK_STREAM; if (getaddrinfo (hostname, service, &hints, &res) != 0) exit (1); fd = -1; for (ptr = res; ptr != NULL; ptr = ptr->ai_next) { fd = socket (ptr->ai_family, ptr->ai_socktype, ptr->ai_protocol); if (fd != -1) break; } if (fd == -1) exit (1); err = connect (fd, ptr->ai_addr, ptr->ai_addrlen); if (err < 0) exit (1); freeaddrinfo (res); return fd; } static void sockets_init () { #if defined WIN32 && !defined __CYGWIN__ WSADATA wsaData; int iRet; iRet = WSAStartup (MAKEWORD(2,2), &wsaData); if (iRet != 0) exit (1); #endif /* _WIN32 */ } int main (int argc, char **argv) { int err, ret, fd; char buffer[MAX_BUF + 1]; fd_set rset; int user_term = 0, retval = 0; ssize_t bytes; const char *hostname; const char *service; gnutls_session_t session; gnutls_anon_client_credentials_t anon_cred; gnutls_certificate_credentials_t xcred; if (gnutls_global_init () < 0) exit (1); if (argc < 3) { fprintf (stderr, "No hostname or port given\n"); exit (1); } hostname = argv[1]; service = argv[2]; #ifdef _WIN32 sockets_init (); #endif #ifndef _WIN32 signal (SIGPIPE, SIG_IGN); #endif sockets_init (); gnutls_init (&session, GNUTLS_CLIENT); gnutls_set_default_priority (session); gnutls_anon_allocate_client_credentials (&anon_cred); gnutls_credentials_set (session, GNUTLS_CRD_ANON, anon_cred); gnutls_certificate_allocate_credentials (&xcred); gnutls_credentials_set (session, GNUTLS_CRD_CERTIFICATE, xcred); fd = socket_open (hostname, service); gnutls_transport_set_ptr (session, (gnutls_transport_ptr_t) (long) fd); ret = do_handshake (session); if (ret < 0) { gnutls_perror (ret); retval = 1; goto out; } fflush (stdout); fflush (stderr); { #ifdef __MSVCRT__ unsigned long iMode = 1; ioctlsocket (fd, FIONBIO, &iMode); #else int oldflags = fcntl (fd, F_GETFL, NULL); fcntl (fd, F_SETFL, oldflags | O_NONBLOCK); #endif } for (;;) { FD_ZERO (&rset); FD_SET (STDIN_FILENO, &rset); FD_SET (fd, &rset); err = select (fd + 1, &rset, NULL, NULL, NULL); if (err < 0) continue; if (FD_ISSET (fd, &rset)) { memset (buffer, 0, MAX_BUF + 1); do ret = gnutls_record_recv (session, buffer, MAX_BUF); while (ret == GNUTLS_E_INTERRUPTED || ret == GNUTLS_E_AGAIN); if (ret == 0) break; if (handle_error (session, ret) < 0) { retval = 1; break; } if (ret > 0) { fwrite (buffer, ret, 1, stdout); fflush (stdout); } } if (FD_ISSET (STDIN_FILENO, &rset)) { if ((bytes = read (STDIN_FILENO, buffer, MAX_BUF - 1)) <= 0) { user_term = 1; break; } do ret = gnutls_record_send (session, buffer, bytes); while (ret == GNUTLS_E_AGAIN || ret == GNUTLS_E_INTERRUPTED); if (ret <= 0) handle_error (session, ret); } } if (user_term != 0) { do ret = gnutls_bye (session, GNUTLS_SHUT_WR); while (ret == GNUTLS_E_INTERRUPTED || ret == GNUTLS_E_AGAIN); gnutls_deinit (session); } else gnutls_deinit (session); out: shutdown (fd, SHUT_RDWR); /* shutdown now, close on exit */ gnutls_anon_free_client_credentials (anon_cred); gnutls_certificate_free_credentials (xcred); gnutls_global_deinit (); return retval; } #else int main (int argc, char **argv) { return 1; } #endif smalltalk-3.2.5/packages/net/stamp-classes0000644000175000017500000000000012123404352015456 00000000000000smalltalk-3.2.5/packages/net/package.xml0000644000175000017500000000077712123404352015116 00000000000000 NetClients Sockets IMAPTests.st MIME.st Base.st ContentHandler.st IMAP.st POP.st SMTP.st NNTP.st FTP.st HTTP.st URIResolver.st NetServer.st NetClients ChangeLog smalltalk-3.2.5/packages/net/NNTP.st0000644000175000017500000004222412123404352014121 00000000000000"====================================================================== | | NNTP protocol support | | ======================================================================" "====================================================================== | | Based on code copyright (c) Kazuki Yasumatsu, and in the public domain | Copyright (c) 2002 Free Software Foundation, Inc. | Adapted by Paolo Bonzini. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" Namespace current: NetClients.NNTP [ NetClient subclass: NNTPClient [ | currentGroup | NNTPClient class >> defaultPortNumber [ ^119 ] NNTPClient class >> exampleHelpOn: host [ "self exampleHelpOn: 'localhost'." | client answer | client := NNTPClient connectToHost: host. [answer := client help. client logout] ensure: [client close]. ^answer ] NNTPClient class >> exampleOn: host group: groupString [ "self exampleOn: 'newshost' group: 'comp.lang.smalltalk'." | subjects client | client := NNTPClient connectToHost: host. [| range | range := client activeArticlesInGroup: groupString. subjects := Array new: range size. client subjectsOf: groupString from: range first to: range last do: [:n :subject | subjects add: subject]. client logout] ensure: [client close]. subjects inspect ] activeArticlesInGroup: groupString [ "Answer an active article range in group." | response read from to | self connectIfClosed. response := self clientPI nntpGroup: groupString. currentGroup := groupString. response status = 211 ifFalse: [^0 to: 0]. "A response is as follows:" "211 n f l s (n = estimated number of articles in group, f = first article number in the group, l = last article number in the group, s = name of the group.)" read := response statusMessage readStream. read skipSeparators. Integer readFrom: read. read skipSeparators. from := Integer readFrom: read. read skipSeparators. to := Integer readFrom: read. ^from to: to ] activeNewsgroupsDo: aBlock [ "Answer a list of active newsgroups." | line | self reconnect. self clientPI nntpList. [self atEnd or: [line := self nextLine. line = '.']] whileFalse: [aBlock value: line] ] activeNewsgroups [ "Answer a list of active newsgroups." | stream | stream := WriteStream on: Array new. self activeNewsgroupsDo: [:each | stream nextPut: each]. ^stream contents ] articleAt: idOrNumberString into: aStream [ "Read an article at idOrNumberString into aStream." self connectIfClosed. self clientPI nntpArticle: idOrNumberString. self receiveMessageUntilPeriodInto: aStream ] articleAtNumber: anInteger group: groupString into: aStream [ "Read an article at anInteger of a newsgroup named groupString into aStream." self connectIfClosed. groupString = currentGroup ifFalse: [self group: groupString]. self articleAt: anInteger printString into: aStream ] articleMessageAt: idOrNumberString [ "Answer a message of an article at idOrNumberString." self connectIfClosed. self clientPI nntpArticle: idOrNumberString. ^MIME.MimeEntity readFrom: self ] articleMessageAtNumber: anInteger group: groupString [ "Answer a message of an article at anInteger of a newsgroup named groupString." self connectIfClosed. groupString = currentGroup ifFalse: [self group: groupString]. ^self articleMessageAt: anInteger printString ] bodyAt: idOrNumberString into: aStream [ "Read a body of an article at idOrNumberString into aStream." | response | self connectIfClosed. self clientPI nntpBody: idOrNumberString. self receiveMessageUntilPeriodInto: aStream ] bodyAtNumber: anInteger group: groupString into: aStream [ "Read a body of an article at anInteger of a newsgroup named groupString into aStream." self connectIfClosed. groupString = currentGroup ifFalse: [self group: groupString]. ^self bodyAt: anInteger printString into: aStream ] connected [ currentGroup := nil. ] group: groupString [ self connectIfClosed. self clientPI nntpGroup: groupString. currentGroup := groupString ] headAt: idOrNumberString into: aStream [ "Read a header of an article at idOrNumberString into aStream." self connectIfClosed. self clientPI nntpHead: idOrNumberString. self receiveMessageUntilPeriodInto: aStream ] headAtNumber: anInteger group: groupString into: aStream [ "Read a header of an article at anInteger of a newsgroup named groupString into aStream." self connectIfClosed. groupString = currentGroup ifFalse: [self group: groupString]. ^self headAt: anInteger printString into: aStream ] help [ "Answer a help text." | write | write := WriteStream on: (String new: 1024). self connectIfClosed. self clientPI nntpHelp. self receiveMessageUntilPeriodInto: write. ^write contents ] postArticleMessage: aMessage [ "Post a news article message." self connectIfClosed. self clientPI nntpPost: [aMessage printMessageOnClient: self] ] postArticleStream: aStream [ "Post a news article in aStream." self connectIfClosed. self clientPI nntpPost: [self sendMessageWithPeriod: aStream] ] logout [ self closed ifTrue: [^self]. self clientPI nntpQuit. self close ] protocolInterpreter [ ^NNTPProtocolInterpreter ] headersAt: keyString group: groupString from: from to: to do: aBlock [ "Answer a list of article number and value of header field in a range (from to)." | line | self connectIfClosed. groupString = currentGroup ifFalse: [self group: groupString]. self clientPI nntpXhdr: keyString from: from to: to. [self atEnd or: [line := self nextLine. line = '.']] whileFalse: [| read number string | read := line readStream. read skipSeparators. number := Integer readFrom: read. read skipSeparators. string := read upToEnd. aBlock value: number value: string] ] headersAt: keyString group: groupString from: from to: to into: aStream [ "Answer a list of article number and value of header field in a range (from to)." self connectIfClosed. groupString = currentGroup ifFalse: [self group: groupString]. self clientPI nntpXhdr: keyString from: from to: to. self receiveMessageUntilPeriodInto: aStream ] messageIdsOf: groupString from: from to: to do: aBlock [ ^self headersAt: 'MESSAGE-ID' group: groupString from: from to: to do: aBlock ] messageIdsOf: groupString from: from to: to into: aStream [ ^self headersAt: 'MESSAGE-ID' group: groupString from: from to: to into: aStream ] overviewsOf: groupString from: from to: to do: aBlock [ "Answer a list of article number and overview of header field in a range (from to)." | line | self connectIfClosed. groupString = currentGroup ifFalse: [self group: groupString]. self clientPI nntpXoverFrom: from to: to. [self atEnd or: [line := self nextLine. line = '.']] whileFalse: [| read number string | read := line readStream. read skipSeparators. number := Integer readFrom: read. read skipSeparators. string := read upToEnd. aBlock value: number value: string] ] overviewsOf: groupString from: from to: to into: aStream [ "Answer a list of article number and overview of header field in a range (from to)." self connectIfClosed. groupString = currentGroup ifFalse: [self group: groupString]. self clientPI nntpXoverFrom: from to: to. self receiveMessageUntilPeriodInto: aStream ] subjectsOf: groupString from: from to: to do: aBlock [ ^self headersAt: 'SUBJECT' group: groupString from: from to: to do: aBlock ] subjectsOf: groupString from: from to: to into: aStream [ ^self headersAt: 'SUBJECT' group: groupString from: from to: to into: aStream ] xrefsOf: groupString from: from to: to do: aBlock [ ^self headersAt: 'XREF' group: groupString from: from to: to do: aBlock ] xrefsOf: groupString from: from to: to into: aStream [ ^self headersAt: 'XREF' group: groupString from: from to: to into: aStream ] liveAcrossSnapshot [ ^true ] ] ] Namespace current: NetClients.NNTP [ NetProtocolInterpreter subclass: NNTPProtocolInterpreter [ connect [ super connect. "Skip first general response." self checkResponse: self getResponse. "Set mode to reader for INN." self nextPutAll: 'MODE READER'; cr. "Ignore error" self checkResponse: self getResponse ifError: [] ] nntpArticle: idOrNumberString [ | response | self nextPutAll: 'ARTICLE ' , idOrNumberString; cr. response := self getResponse. response status = 220 ifFalse: ["article retrieved - head and body follows" ^self checkResponse: response] ] nntpBody: idOrNumberString [ | response | self nextPutAll: 'BODY ' , idOrNumberString; cr. response := self getResponse. response status = 222 ifFalse: ["article retrieved - body follows" ^self checkResponse: response] ] nntpGroup: groupString [ | response | self nextPutAll: 'GROUP ' , groupString; cr. response := self getResponse. self checkResponse: response. ^response ] nntpHead: idOrNumberString [ | response | self nextPutAll: 'HEAD ' , idOrNumberString; cr. response := self getResponse. response status = 221 ifFalse: ["article retrieved - head follows" ^self checkResponse: response] ] nntpHelp [ self nextPutAll: 'HELP'; cr. self checkResponseForFollowingText: self getResponse ] nntpList [ self nextPutAll: 'LIST'; cr. self checkResponseForFollowingText: self getResponse ] nntpPost: aBlock [ self nextPutAll: 'POST'; cr. self checkResponse: self getResponse. aBlock value. self checkResponse: self getResponse ] nntpQuit [ self nextPutAll: 'QUIT'; cr. self checkResponse: self getResponse ] nntpXhdr: keyString from: from to: to [ "Answer a list of article number and value of header field in a range (from to)." self nextPutAll: 'XHDR ' , keyString , ' ' , from printString , '-' , to printString; cr. self checkResponseForFollowingText: self getResponse ] nntpXoverFrom: from to: to [ "Answer a list of article number and overview of header field in a range (from to)." self nextPutAll: 'XOVER ' , from printString , '-' , to printString; cr. self checkResponseForFollowingText: self getResponse ] checkResponse: response [ | textFollows | textFollows := self checkResponse: response ifError: [self errorResponse: response. ^self]. textFollows ifFalse: [^self]. self skipMessageUntilPeriod. self unexpectedResponse: response ] checkResponse: response ifError: errorBlock [ "Answer text follows or not." | status | status := response status. "Timeout after 7200 seconds, closing connection" status = 503 ifTrue: [^self connectionClosedError: response statusMessage]. "Informative message" status = 100 ifTrue: ["help text follows" ^true]. (status between: 190 and: 199) ifTrue: ["debug output" ^false]. "Command ok" status = 200 ifTrue: ["server ready - posting allowed" ^false]. status = 201 ifTrue: ["server ready - no posting allowed" ^false]. status = 202 ifTrue: ["slave status noted" ^false]. status = 205 ifTrue: ["closing connection - goodbye!" ^false]. status = 211 ifTrue: ["n f l s group selected" ^false]. "### n f l s (n = estimated number of articles in group, f = first article number in the group, l = last article number in the group, s = name of the group.)" status = 215 ifTrue: ["list of newsgroups follows" ^true]. "### n (n = article number, = message-id)" status = 220 ifTrue: ["article retrieved - head and body follows" ^true]. status = 221 ifTrue: ["article retrieved - head follows" ^true]. status = 222 ifTrue: ["article retrieved - body follows" ^true]. status = 223 ifTrue: ["article retrieved - request text separately" ^true]. status = 224 ifTrue: ["data follows" ^true]. status = 230 ifTrue: ["list of new articles by message-id follows" ^true]. status = 231 ifTrue: ["list of new newsgroups follows" ^true]. status = 235 ifTrue: ["article transferred ok" ^false]. status = 240 ifTrue: ["article posted ok" ^false]. "Command ok so far, send the rest of it" status = 335 ifTrue: ["send article to be transferred" ^false]. status = 340 ifTrue: ["send article to be posted" ^false]. "Command was correct, but couldn't be performed for some reason" status = 400 ifTrue: ["service discontinued" ^errorBlock value]. status = 411 ifTrue: ["no such news group" ^errorBlock value]. status = 412 ifTrue: ["no newsgroup has been selected" ^errorBlock value]. status = 420 ifTrue: ["no current article has been selected" ^errorBlock value]. status = 421 ifTrue: ["no next article in this group" ^errorBlock value]. status = 422 ifTrue: ["no previous article in this group" ^errorBlock value]. status = 423 ifTrue: ["no such article number in this group" ^errorBlock value]. status = 430 ifTrue: ["no such article found" ^errorBlock value]. status = 435 ifTrue: ["article not wanted - do not send it" ^errorBlock value]. status = 436 ifTrue: ["transfer failed - try again later" ^errorBlock value]. status = 437 ifTrue: ["article rejected - do not try again." ^errorBlock value]. status = 440 ifTrue: ["posting not allowed" ^errorBlock value]. status = 441 ifTrue: ["posting failed" ^errorBlock value]. "Command unimplemented, or incorrect, or a serious program error occurred" status = 500 ifTrue: ["command not recognized" ^errorBlock value]. status = 501 ifTrue: ["command syntax error" ^errorBlock value]. status = 502 ifTrue: ["access restriction or permission denied" ^errorBlock value]. status = 503 ifTrue: ["program fault - command not performed" ^errorBlock value]. "Unknown status" ^errorBlock value ] checkResponseForFollowingText: response [ | textFollows | textFollows := self checkResponse: response ifError: [self errorResponse: response. ^self]. textFollows ifFalse: [self unexpectedResponse: response. ^self] ] defaultPortNumber [ ^119 ] nextPutAll: aString [ | retryCount | aString isEmpty ifTrue: [^self]. retryCount := 0. [self connectionStream nextPutAll: (self encode: aString)] on: Error do: [:ex | (retryCount := retryCount + 1) > 1 ifTrue: [ex return] ifFalse: [self reconnect. ex restart]] ] ] ] smalltalk-3.2.5/packages/blox/0000755000175000017500000000000012130456013013223 500000000000000smalltalk-3.2.5/packages/blox/tests/0000755000175000017500000000000012130456013014365 500000000000000smalltalk-3.2.5/packages/blox/tests/Makefile.frag0000644000175000017500000000025112123404352016662 00000000000000Blox_FILES = \ packages/blox/tests/test.st $(Blox_FILES): $(srcdir)/packages/blox/tests/stamp-classes: $(Blox_FILES) touch $(srcdir)/packages/blox/tests/stamp-classes smalltalk-3.2.5/packages/blox/tests/package.xml.in0000644000175000017500000000021012123404352017021 00000000000000 Blox @BLOX_IMPLEMENTATION@ BLOX test.st smalltalk-3.2.5/packages/blox/tests/test.st0000644000175000017500000003457712123404352015655 00000000000000Gui class extend [ test: selector [ | win | win := BWindow new: 'test'. win width: 100 height: 100. (self perform: selector) value: win. win map. Blox dispatchEvents: win ] callbackTest [ ^ [:win | | cont dlg sure | win callback: [cont := BTransientWindow new: 'BLOX test' in: win. cont width: 250 height: 130. dlg := BDialog new: cont label: 'Are you sure?'. dlg addButton: 'Yes' receiver: [sure := true] message: #value. dlg addButton: 'No' receiver: [sure := false] message: #value. dlg loop. sure] message: #value] ] canvasTest [ ^ [:win | | ctl | ctl := BScrolledCanvas new: win. ctl width: 100 height: 100. ctl backgroundColor: 'gray35'. ctl extraSpace: 10 @ 0. win width: 220 height: 220. win map. "p := ctl widthAbsolute @ ctl heightAbsolute. p printNl." self drawInCanvas: ctl width: 200 @ 200] ] drawInCanvas: ctl width: p [ | status rect poly | poly := (BPolyline new: ctl) closed: true; color: 'blue'; outlineColor: 'LemonChiffon'; points: (self points: p coords: #(#(0.1 0.1) #(0.5 0.2) #(0.9000000000000001 0.9000000000000001) #(0.5 0.8000000000000001))); create. (BLine new: ctl) origin: p * 0.1 corner: p * 0.9000000000000001; color: 'Magenta'; cap: #round; width: 8; create. rect := (BRectangle new: ctl) origin: p * 0.45 extent: p * 0.1; color: 'yellow'; outlineColor: 'Magenta'; width: 2; create. (BSpline new: ctl) closed: false; points: (self points: p coords: #(#(0.05 0.05) #(0.05 0.05) #(0.05 0.9500000000000001) #(0.9500000000000001 0.9500000000000001) #(0.9500000000000001 0.9500000000000001) #(0.9500000000000001 0.05) #(0.05 0.05) #(0.05 0.05) #(0.05 0.25) #(0.05 0.25))); join: #bevel; color: 'ForestGreen'; width: 8; create. "Trick to get the bevel-styled join" "at the top-left corner too" (BArc new: ctl) origin: p * (0.2 @ 0.8000000000000001) corner: p * (0.8000000000000001 @ 1); outlineColor: 'gray75'; from: p * (0.2 @ 0.9000000000000001); to: p * (0.5 @ 0.8000000000000001); create. (BArc new: ctl) origin: p * (0.2 @ 0) corner: p * (0.8000000000000001 @ 0.2); outlineColor: 'gray75'; startAngle: 270; endAngle: 360; create. status := 0. poly onMouseDoubleEvent: 1 send: #value: to: [:pnt | status := status + 1. status = 1 ifTrue: [poly raise]. status = 2 ifTrue: [poly lower]. status = 3 ifTrue: [(BEmbeddedText new: ctl) color: 'Cyan'; text: 'Smalltalk is great'; font: 'Helvetica 12'; center: p / 2 extent: p x @ (p y / 10); create. rect remove]] ] points: p coords: coords [ ^coords collect: [:each | p * ((each at: 1) @ (each at: 2))] ] dropdownTest [ ^ [:win | | cb name size label | cb := [[label font: '{%1} %2' % {name text. size text}] on: Error do: [:sig | sig return]]. win width: 300 height: 300. name := BDropDownList new: win. size := BDropDownEdit new: win. label := BLabel new: win. name width: 250; contents: Blox fonts; callback: cb message: #value; index: 1. size x: 252; width: 48; elements: #(6 8 10 12 14 18 24 36 48 72); callback: cb message: #value; index: 4. label effect: #groove; width: 300 height: 300; posVert: name; alignment: #center; label: 'The quick brown fox jumps over the lazy dog. 0123456789'] ] vContainerTest [ ^ [:win | | vertical ctl cont | cont := BContainer new: win. cont setVerticalLayout: true. ctl := BLabel new: cont label: 'label'. ctl := BButton new: cont label: 'button'. win backgroundColor: 'navyblue'] ] hContainerTest [ ^ [:win | | vertical ctl cont | cont := BContainer new: win. cont setVerticalLayout: false. ctl := BLabel new: cont label: 'label'. ctl := BButton new: cont label: 'button'. win backgroundColor: 'navyblue'] ] dialogTest1 [ ^ [:win | | cont dlg | cont := BTransientWindow new: 'transient' in: win. cont width: 250 height: 130. dlg := BDialog new: cont label: 'dialog test'. dlg addButton: 'OK' receiver: self message: #itemChosen. dlg addButton: 'Cancel' receiver: self message: #yourself. win map. dlg loop] ] dialogTest2 [ ^ [:win | | cont dlg | cont := BTransientWindow new: 'transient' in: win. cont width: 250 height: 130. dlg := BDialog new: cont label: 'dialog test' prompt: 'default'. dlg addButton: 'OK' receiver: self message: #pickMeHarder. dlg addButton: 'Cancel' receiver: self message: #yourself. win map. dlg loop] ] editTest [ ^ [:win | (BLabel new: win) label: 'Enter whatever you want:'. (BEdit new: win) x: 0 y: 50; width: 100; callback: Blox message: 'beep'. win width: 200 height: 80] ] eventTest [ ^ [:win | | event events x y key ascii mouse | mouse := [:pnt | x label: pnt x printString. y label: pnt y printString]. win width: 400 height: 200. (event := BLabel new: win label: '') x: 0 y: 0; width: 200. (x := BLabel new: win label: '') x: 200 y: 0; width: 50. (y := BLabel new: win label: '') x: 250 y: 0; width: 50. (key := BLabel new: win label: '') x: 300 y: 0; width: 50. (ascii := BLabel new: win label: '') x: 350 y: 0; width: 50. (BText new: win) posVert: event; onAsciiKeyEventSend: #value: to: [:char | "This is a test, so to save space I'm using blocks. This is not good programming practice, as it leads to huge methods." event label: 'key'. ascii label: (String with: char)]; onKeyEventSend: #value: to: [:keyPressed | event label: 'ascii'. key label: keyPressed]; onKeyEvent: 'Return' send: #beep to: Blox; onMouseDownEvent: 1 send: #value: to: [:pnt | mouse value: pnt. event label: 'down']; onMouseMoveEvent: 1 send: #value: to: [:pnt | mouse value: pnt. event label: 'move']; onMouseUpEvent: 1 send: #value: to: [:pnt | mouse value: pnt. event label: 'up']; onMouseDoubleEvent: 1 send: #value: to: [:pnt | mouse value: pnt. event label: 'double']; onMouseTripleEvent: 1 send: #value: to: [:pnt | mouse value: pnt. event label: 'triple']; onMouseEnterEventSend: #value to: [event label: 'enter']; onMouseLeaveEventSend: #value to: [event label: 'leave']] ] formTest [ ^ [:win | | cont | cont := BForm new: win. (BLabel new: cont label: 'label') width: 100 height: 50. (BButton new: cont label: 'button') y: 50; width: 100 height: 50] ] formattingTest [ ^ [:win | (BText new: win) insertAtEnd: 'Trying edit box widgets' attribute: BTextAttributes red; insertAtEnd: ' strikeout ' attribute: BTextAttributes strikeout; insertAtEnd: ' red again ' attribute: BTextAttributes red; insertAtEnd: ' now cyan ' attribute: (BTextAttributes new foregroundColor: 'DarkCyan'); insertAtEnd: ' now background ' attribute: (BTextAttributes yellow backgroundColor: 'DarkSlateBlue'); insertAtEnd: ' font ' attribute: (BTextAttributes underline font: 'Helvetica 24')] ] textEventsTest [ ^ [:win | | attrs bindings dlg cont text | win width: win width * 2. (bindings := BTextBindings new) onMouseEnterEventSend: #value to: [text cursor: #hand2]; onMouseLeaveEventSend: #value to: [text cursor: #arrow]; onMouseUpEvent: 1 send: #value: to: [:pnt | cont := BTransientWindow new: 'BLOX test' in: win. cont height: 100. dlg := BDialog new: cont label: 'You clicked on me'. dlg addButton: 'ok' receiver: self message: #yourself. dlg loop]. attrs := (BTextAttributes new) underline; center; blue; font: 'Helvetica 18'; events: bindings. (text := BText new: win) cursor: #arrow; insertAtEnd: 'Click on me!' attribute: attrs; nl; insertAtEnd: 'and not on me' attribute: BTextAttributes center] ] imageTest [ ^ [:win | | image | image := BImage new: win image: self validImageFile. image onMouseMoveEvent: 1 send: #value: to: [:pnt | image gamma: (0.2 max: pnt x / 100)]. win width: image imageWidth height: image imageHeight] ] validImageFile [ ^(Directory kernel / '../blox/bear.gif') readStream ] labelTest [ ^ [:win | win width: 400. (BLabel new: win label: '*** a ''ridge'' blue label ***') effect: #ridge; x: 40; width: 320 height: 100; inset: 20; backgroundColor: 'LightSkyBlue'; font: 'Helvetica 18'] ] listboxTest [ ^ [:win | (BList new: win) width: 100 height: 100; inset: 2; contents: #('test 1' 'test 2' 'test 3' 'test 4' 'test 5' 'test 6')] ] textTest [ ^ [:win | | text | win width: 300. text := BText new: win. text contents: 'Trying edit box widgets this line is long - this line is long - this line is long - '. BButton new: text label: 'and has a button in it'] ] fileDialogTest [ ^ [:win | | text file fileName | win width: 500. text := (BText new: win) font: 'Courier 9'. fileName := BDialog chooseFileToOpen: win label: 'Open a file' default: nil defaultExtension: 'st' types: #(#('Smalltalk files' '.st') #('Text files' '.txt' '.diz') #('C source files' '.c' '.h')). fileName isNil ifFalse: [file := FileStream open: fileName mode: 'r' ifFail: [ReadStream on: '***FILE COULD NOT BE OPENED' copy]. text contents: file contents. file close]] ] colorDialogTest [ ^ [:win | | label color | win width: 400. label := (BLabel new: win label: '*** this is gray (for now) ***') effect: #groove; x: 40; width: 320 height: 100; inset: 20; font: 'Helvetica 18'. color := BDialog chooseColor: win label: 'Choose a color!' default: 'SteelBlue'. color isNil ifFalse: [label label: 'but now it isn''t anymore'; backgroundColor: color printNl]] ] menuTest [ ^[:win | self createTestMenuBar: win] ] popupMenuTest [ ^ [:win | | list menu menuItem | list := self listboxTest value: win. menu := BPopupMenu new: list. menuItem := BMenuItem new: menu label: 'a one'. menuItem callback: Gui message: 'itemChosen'. menuItem := BMenuItem new: menu label: 'and a two'. menuItem := BMenuItem new: menu label: 'and away'. menuItem := BMenuItem new: menu label: 'we go'] ] createTestMenuBar: win [ | bar | bar := BMenuBar new: win. self createFirstMenu: bar. self createSecondMenu: bar ] createFirstMenu: bar [ | menu menuItem | menu := BMenu new: bar label: 'foo'. menuItem := BMenuItem new: menu label: 'a one'. menuItem callback: Gui message: 'itemChosen'. menuItem := BMenuItem new: menu label: 'and a two'. menuItem := BMenuItem new: menu label: 'and away'. menuItem := BMenuItem new: menu label: 'we go'. bar add: menu ] createSecondMenu: bar [ | menu menuItem | menu := BMenu new: bar label: 'bar'. menuItem := BMenuItem new: menu label: 'testme '. menuItem callback: Gui message: 'pickMeHarder'. menuItem := BMenuItem new: menu. menuItem := BCheckMenuItem new: menu label: 'don''t try me'. menuItem := BCheckMenuItem new: menu label: 'i do nothing'. menuItem := BMenuItem new: menu. menuItem := BCheckMenuItem new: menu label: 'abc'. menuItem value: true. bar add: menu. menuItem label: 'cba - changed my mind'. menuItem := BCheckMenuItem new: menu label: 'added on the fly'. menuItem value: true ] itemChosen [ 'Picked me!!!' printNl ] pickMeHarder [ 'Pick me harder' printNl ] iconTest [ ^ [:win | (self icon: BImage exclaim in: win) x: 30 y: 30. (self icon: BImage stop in: win) x: 70 y: 30. (self icon: BImage info in: win) x: 30 y: 70. (self icon: BImage question in: win) x: 70 y: 70. win width: 120 height: 120. win map] ] icon: data in: win [ ^(BImage new: win data: data) inset: -16; borderWidth: 0; yourself ] progressTest [ ^ [:win | | ctl | win width: 150 height: 70. (ctl := BProgress new: win) x: 5 y: 5 width: 140 height: 60; effect: #sunken; borderWidth: 2; value: 0.009000000000000002. Blox debug: false. [[win exists] whileTrue: [(Delay forMilliseconds: 50) wait. [ctl value: (ctl value + 0.01) fractionPart] on: Error do: [:sig | sig return]]] forkAt: Processor userInterruptPriority] ] colorButtonTest [ ^ [:win | | btn | btn := BColorButton new: win. btn inset: 15] ] balloonTest [ ^ [:win | | eventSet btn | btn := BButton new: win label: 'Move here!'. btn inset: 15; width: 100 height: 100. (btn addEventSet: BBalloon) text: 'Sample balloon help'] ] ] Eval [ Transcript nextPutAll: 'Available tests'; nl. tests := OrderedCollection new. BLOX.Gui class selectors do: [:sel | ('*Test*' match: sel) & (sel numArgs = 0) ifTrue: [tests add: sel]]. tests asSortedCollection do: [:each | Transcript nextPutAll: ' '; print: each; nl] ] smalltalk-3.2.5/packages/blox/tests/stamp-classes0000644000175000017500000000000012123404352016776 00000000000000smalltalk-3.2.5/packages/blox/gtk/0000755000175000017500000000000012130456013014010 500000000000000smalltalk-3.2.5/packages/blox/gtk/Makefile.frag0000644000175000017500000000045212123404352016310 00000000000000BloxGTK_FILES = \ packages/blox/gtk/Blox.st packages/blox/gtk/BloxBasic.st packages/blox/gtk/BloxWidgets.st packages/blox/gtk/BloxText.st packages/blox/gtk/BloxExtend.st $(BloxGTK_FILES): $(srcdir)/packages/blox/gtk/stamp-classes: $(BloxGTK_FILES) touch $(srcdir)/packages/blox/gtk/stamp-classes smalltalk-3.2.5/packages/blox/gtk/BloxExtend.st0000644000175000017500000011253612123404352016365 00000000000000"====================================================================== | | Smalltalk Tk-based GUI building blocks, extended widgets. | This is 100% Smalltalk! | | ======================================================================" "====================================================================== | | Copyright 1999, 2000, 2001, 2002 Free Software Foundation, Inc. | Free Software Foundation, Inc. | Written by Paolo Bonzini. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LESSER. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" BExtended subclass: BProgress [ | value filled label1 label2 | backgroundColor [ "Answer the background color of the widget. This is used for the background of the non-filled part, as well as for the foreground of the filled part." ^label1 backgroundColor ] backgroundColor: aColor [ "Set the background color of the widget. This is used for the background of the non-filled part, as well as for the foreground of the filled part." label1 backgroundColor: aColor. label2 foregroundColor: aColor ] filledColor [ "Answer the background color of the widget's filled part." ^label2 backgroundColor ] filledColor: aColor [ "Set the background color of the widget's filled part." label2 backgroundColor: aColor ] foregroundColor [ "Set the foreground color of the widget. This is used for the non-filled part, while the background color also works as the foreground of the filled part." ^label1 foregroundColor ] foregroundColor: aColor [ "Set the foreground color of the widget. This is used for the non-filled part, while the background color also works as the foreground of the filled part." label1 foregroundColor: aColor ] value [ "Answer the filled percentage of the receiver (0..1)" ^value ] value: newValue [ "Set the filled percentage of the receiver and update the appearance. newValue must be between 0 and 1." value := newValue. filled width: self value * self primitive widthAbsolute. label1 label: (value * 100) rounded printString , '%'. label2 label: (value * 100) rounded printString , '%' ] create [ "Private - Create the widget" | hgt | super create. self primitive onResizeSend: #resize: to: self. label1 := BLabel new: self primitive. filled := BForm new: self primitive. label2 := BLabel new: filled. hgt := self primitive height. label1 alignment: #center; width: self primitive width height: hgt. label2 alignment: #center; width: 0 height: hgt. self backgroundColor: 'white'; foregroundColor: 'black'; filledColor: 'blue'; resize: nil; value: 0 ] newPrimitive [ "Private - Create the BForm in which the receiver is drawn" ^BForm new: self parent ] resize: newSize [ label2 widthOffset: self primitive widthAbsolute ] ] BExtended subclass: BButtonLike [ | callback down | callback [ "Answer a DirectedMessage that is sent when the receiver is clicked, or nil if none has been set up." ^callback ] callback: aReceiver message: aSymbol [ "Set up so that aReceiver is sent the aSymbol message (the name of a zero- or one-argument selector) when the receiver is clicked. If the method accepts an argument, the receiver is passed." | arguments selector numArgs | selector := aSymbol asSymbol. numArgs := selector numArgs. arguments := #(). numArgs = 1 ifTrue: [arguments := Array with: self]. callback := DirectedMessage selector: selector arguments: arguments receiver: aReceiver ] pressed [ "This is the default callback for the widget; it does nothing if you don't override it. Of course if a subclass overriddes this you (user of the class) might desire to call this method from your own callback." ] invokeCallback [ "Generate a synthetic callback" self callback isNil ifFalse: [self callback send] ] down: point [ "Private - Make the widget go down when the left button is pressed inside it." down := true. self enter ] enter [ "Private - Make the widget go down when the mouse enters with the left button pressed." down ifTrue: [self primitive effect: #sunken] ] leave [ "Private - Make the widget go up when the mouse leaves" down ifTrue: [self primitive effect: #raised] ] up: point [ "Private - Make the widget go up when the left button is released after being pressed inside it, and trigger the callback if the button was released inside the widget." | inside | inside := self primitive effect == #sunken. inside ifTrue: [self leave]. down := false. inside ifTrue: [self invokeCallback] ] create [ "Ask myself to create the primitive widget and set up its event handlers." super create. (self primitive) borderWidth: 2; effect: #raised; onMouseEnterEventSend: #enter to: self; onMouseLeaveEventSend: #leave to: self; onMouseDownEvent: 1 send: #down: to: self; onMouseUpEvent: 1 send: #up: to: self. down := false. callback := DirectedMessage selector: #pressed arguments: #() receiver: self ] ] BButtonLike subclass: BColorButton [ color [ "Set the color that the receiver is painted in." ^self primitive backgroundColor ] color: aString [ "Set the color that the receiver is painted in." self primitive backgroundColor: aString ] pressed [ "This is the default callback; it brings up a `choose-a-color' window and, if `Ok' is pressed in the window, sets the receiver to be painted in the chosen color." | newColor | newColor := BDialog chooseColor: self window label: 'Choose a color' default: self color. newColor isNil ifFalse: [self color: newColor] ] newPrimitive [ "Private - A BColorButton is implemented through a BLabel. (!)" "Make it big enough if no width is specified." ^BLabel new: self parent label: ' ' ] ] BEventSet subclass: BBalloon [ | text | BalloonDelayTime := nil. Popup := nil. Owner := nil. MyProcess := nil. BBalloon class >> balloonDelayTime [ "Answer the time after which the balloon is shown (default is half a second)." BalloonDelayTime isNil ifTrue: [BalloonDelayTime := 500]. ^BalloonDelayTime ] BBalloon class >> balloonDelayTime: milliseconds [ "Set the time after which the balloon is shown." BalloonDelayTime := milliseconds ] BBalloon class >> shown [ "Answer whether a balloon is displayed" ^Popup notNil ] shown [ "Answer whether the receiver's balloon is displayed" ^self class shown and: [Owner == self] ] text [ "Answer the text displayed in the balloon" ^text ] text: aString [ "Set the text displayed in the balloon to aString" text := aString ] initialize: aBWidget [ "Initialize the event sets for the receiver" super initialize: aBWidget. self text: ''. self onMouseEnterEventSend: #queue to: self; onMouseLeaveEventSend: #unqueue to: self; onMouseDownEventSend: #unqueue:button: to: self ] popup [ "Private - Create the popup window showing the balloon." Popup := BLabel popup: [:widget | widget label: self text; backgroundColor: '#FFFFAA'; x: self widget yRoot + (self widget widthAbsolute // 2) y: self widget yRoot + self widget heightAbsolute + 4]. "Set the owner *now*. Otherwise, the mouse-leave event generated by mapping the new popup window will destroy the popup window itself (see #unqueue)." Owner := self ] queue [ "Private - Queue a balloon to be shown in BalloonDelayTime milliseconds" self shown ifTrue: [^self]. MyProcess isNil ifTrue: [MyProcess := [(Delay forMilliseconds: self class balloonDelayTime) wait. MyProcess := nil. self popup] fork] ] unqueue [ "Private - Prevent the balloon from being displayed if we were waiting for it to appear, or delete it if it was already there." MyProcess isNil ifFalse: [MyProcess terminate. MyProcess := nil]. self shown ifTrue: [Popup window destroy. Owner := Popup := nil] ] unqueue: point button: button [ "Private - Same as #unqueue: but the event handler for mouse-down events needs two parameters." self unqueue ] ] BExtended subclass: BDropDown [ | list button widget callback | backgroundColor [ "Answer the value of the backgroundColor for the widget, which in this class is only set for the list widget (that is, the pop-up widget). Subclasses should override this method so that the color is set properly for the text widget as well. Specifies the normal background color to use when displaying the widget." ^list backgroundColor ] backgroundColor: aColor [ "Set the value of the backgroundColor for the widget, which in this class is only set for the list widget (that is, the pop-up widget). Subclasses should override this method so that the color is set properly for the text widget as well. Specifies the normal background color to use when displaying the widget." list backgroundColor: aColor ] droppedRows [ "Answer the number of items that are visible at any time in the listbox." ^(list height - 8) / self itemHeight ] droppedRows: anInteger [ "Set the number of items that are visible at any time in the listbox." list height: anInteger * self itemHeight + 8 ] font [ "Answer the value of the font option for the widget, which in this class is only set for the list widget (that is, the pop-up widget). Subclasses should override this method so that the color is set properly for the text widget as well. Specifies the font to use when drawing text inside the widget. The font can be given as either an X font name or a Blox font description string. X font names are given as many fields, each led by a minus, and each of which can be replaced by an * to indicate a default value is ok: foundry, family, weight, slant, setwidth, addstyle, pixel size, point size (the same as pixel size for historical reasons), horizontal resolution, vertical resolution, spacing, width, charset and character encoding. Blox font description strings have three fields, which must be separated by a space and of which only the first is mandatory: the font family, the font size in points (or in pixels if a negative value is supplied), and a number of styles separated by a space (valid styles are normal, bold, italic, underline and overstrike). Examples of valid fonts are ``Helvetica 10 Bold'', ``Times -14'', ``Futura Bold Underline''. You must enclose the font family in braces if it is made of two or more words." ^list font ] font: value [ "Set the value of the font option for the widget, which in this class is only set for the list widget (that is, the pop-up widget). Subclasses should override this method so that the color is set properly for the text widget as well. Specifies the font to use when drawing text inside the widget. The font can be given as either an X font name or a Blox font description string. X font names are given as many fields, each led by a minus, and each of which can be replaced by an * to indicate a default value is ok: foundry, family, weight, slant, setwidth, addstyle, pixel size, point size (the same as pixel size for historical reasons), horizontal resolution, vertical resolution, spacing, width, charset and character encoding. Blox font description strings have three fields, which must be separated by a space and of which only the first is mandatory: the font family, the font size in points (or in pixels if a negative value is supplied), and a number of styles separated by a space (valid styles are normal, bold, italic, underline and overstrike). Examples of valid fonts are ``Helvetica 10 Bold'', ``Times -14'', ``Futura Bold Underline''. You must enclose the font family in braces if it is made of two or more words." list font: value ] foregroundColor [ "Answer the value of the foregroundColor for the widget, which in this class is only set for the list widget (that is, the pop-up widget). Subclasses should override this method so that the color is set properly for the text widget as well. Specifies the normal foreground color to use when displaying the widget." ^list foregroundColor ] foregroundColor: aColor [ "Set the value of the foregroundColor for the widget, which in this class is only set for the list widget (that is, the pop-up widget). Subclasses should override this method so that the color is set properly for the text widget as well. Specifies the normal foreground color to use when displaying the widget." list foregroundColor: aColor ] highlightBackground [ "Answer the value of the highlightBackground option for the widget. Specifies the background color to use when displaying selected items in the list widget." ^list highlightBackground ] highlightBackground: aColor [ "Set the value of the highlightBackground option for the widget. Specifies the background color to use when displaying selected items in the list widget." list highlightBackground: aColor ] highlightForeground [ "Answer the value of the highlightForeground option for the widget. Specifies the foreground color to use when displaying selected items in the list widget." ^list highlightForeground ] highlightForeground: aColor [ "Set the value of the highlightForeground option for the widget. Specifies the foreground color to use when displaying selected items in the list widget." list highlightForeground: aColor ] callback [ "Answer a DirectedMessage that is sent when the receiver is clicked, or nil if none has been set up." ^callback ] callback: aReceiver message: aSymbol [ "Set up so that aReceiver is sent the aSymbol message (the name of a zero- or one-argument selector) when the receiver is clicked. If the method accepts an argument, the receiver is passed." | arguments selector numArgs | selector := aSymbol asSymbol. numArgs := selector numArgs. arguments := #(). numArgs = 1 ifTrue: [arguments := Array with: self]. callback := DirectedMessage selector: selector arguments: arguments receiver: aReceiver ] invokeCallback [ "Generate a synthetic callback" self callback isNil ifFalse: [self callback send] ] createList [ "Create the popup widget to be used for the `drop-down list'. It is a BList by default, but you can use any other widget, overriding the `list box accessing' methods if necessary." ^BList new ] createTextWidget [ "Create the widget that will hold the string chosen from the list box and answer it. The widget must be a child of `self primitive'." self subclassResponsibility ] itemHeight [ "Answer the height of an item in the drop-down list. The default implementation assumes that the receiver understands #font, but you can modify it if you want." ^1 + (self fontHeight: 'M') ] listCallback [ "Called when an item of the listbox is highlighted. Do nothing by default" ] listSelectAt: aPoint [ "Select the item lying at the given position in the list box. The default implementation assumes that list is a BList, but you can modify it if you want." | newIndex | (list drawingArea containsPoint: aPoint) ifFalse: [^self]. newIndex := list indexAt: aPoint. newIndex = list index ifTrue: [^self]. self index: newIndex ] listText [ "Answer the text currently chosen in the list box. The default implementation assumes that list is a BList, but you can modify it if you want." ^list labelAt: list index ] text [ "Answer the text that the user has picked from the widget and/or typed in the control (the exact way the text is entered will be established by subclasses, since this is an abstract method)." self subclassResponsibility ] text: aString [ "Set the text widget to aString" self subclassResponsibility ] create [ super create. list := self createList. (self primitive) defaultHeight: (self itemHeight + 6 max: 20); effect: #sunken; borderWidth: 2; backgroundColor: 'white'. list borderWidth: 0. (widget := self createTextWidget) inset: 1; borderWidth: 0; backgroundColor: 'white'; tabStop: true; stretch: true. (button := BImage new: self primitive data: BImage downArrow) effect: #raised; borderWidth: 2. self droppedRows: 8. self setEvents ] newPrimitive [ ^(BContainer new: self parent) setVerticalLayout: false; yourself ] setEvents [ self primitive onDestroySend: #destroy to: list. button onMouseDownEvent: 1 send: #value: to: [:pnt | self toggle]. list onKeyEvent: 'Tab' send: #value to: [self unmapList. widget activateNext]. list onKeyEvent: 'Shift-Tab' send: #value to: [self unmapList. widget activatePrevious]. list onKeyEvent: 'Return' send: #unmapList to: self. list onKeyEvent: 'Escape' send: #unmapList to: self. list onMouseUpEvent: 1 send: #value: to: [:pnt | self unmapList]. list onMouseMoveEventSend: #listSelectAt: to: self. list onFocusLeaveEventSend: #unmapList to: self. list callback: self message: #listCallback ] setInitialSize [ self primitive x: 0 y: 0 ] add: anObject afterIndex: index [ "Add an element with the given value after another element whose index is contained in the index parameter. The label displayed in the widget is anObject's displayString. Answer anObject." ^list add: anObject afterIndex: index ] add: aString element: anObject afterIndex: index [ "Add an element with the aString label after another element whose index is contained in the index parameter. This method allows the client to decide autonomously the label that the widget will display. If anObject is nil, then string is used as the element as well. If aString is nil, then the element's displayString is used as the label. Answer anObject or, if it is nil, aString." ^list add: aString element: anObject afterIndex: index ] addLast: anObject [ "Add an element with the given value at the end of the listbox. The label displayed in the widget is anObject's displayString. Answer anObject." ^list addLast: anObject ] addLast: aString element: anObject [ "Add an element with the given value at the end of the listbox. This method allows the client to decide autonomously the label that the widget will display. If anObject is nil, then string is used as the element as well. If aString is nil, then the element's displayString is used as the label. Answer anObject or, if it is nil, aString." ^list addLast: aString element: anObject ] associationAt: anIndex [ "Answer an association whose key is the item at the given position in the listbox and whose value is the label used to display that item." ^list associationAt: anIndex ] at: anIndex [ "Answer the element displayed at the given position in the list box." ^list at: anIndex ] contents: stringCollection [ "Set the elements displayed in the listbox, and set the labels to be their displayStrings." list contents: stringCollection ] contents: stringCollection elements: elementList [ "Set the elements displayed in the listbox to be those in elementList, and set the labels to be the corresponding elements in stringCollection. The two collections must have the same size." list contents: stringCollection elements: elementList ] do: aBlock [ "Iterate over each element of the listbox and pass it to aBlock." list do: aBlock ] elements: elementList [ "Set the elements displayed in the listbox, and set the labels to be their displayStrings." list elements: elementList ] index: newIndex [ "Highlight the item at the given position in the listbox, and transfer the text in the list box to the text widget." list highlight: newIndex. self text: self listText. self isDropdownVisible ifFalse: [self invokeCallback] ] labelAt: anIndex [ "Answer the label displayed at the given position in the list box." ^list labelAt: anIndex ] labelsDo: aBlock [ "Iterate over the labels in the list widget and pass each of them to aBlock." list labelsDo: aBlock ] numberOfStrings [ "Answer the number of items in the list box" ^list numberOfStrings ] removeAtIndex: index [ "Remove the item at the given index in the list box, answering the object associated to the element (i.e. the value that #at: would have returned for the given index)" ^list removeAtIndex: index ] size [ "Answer the number of items in the list box" ^list size ] dropdown [ "Force the pop-up list widget to be visible." "Always reset the geometry -- it is harmless and *may* actually get better appearance in some weird case." list window boundingBox: self dropRectangle. self isDropdownVisible ifTrue: [^self]. list window map ] dropRectangle [ "Answer the rectangle in which the list widget will pop-up. If possible, this is situated below the drop-down widget's bottom side, but if the screen space there is not enough it could be above the drop-down widget's above side. If there is no screen space above as well, we pick the side where we can offer the greatest number of lines in the pop-up widget." | screen rectangle spaceBelow | screen := Rectangle origin: Blox screenOrigin extent: Blox screenSize. rectangle := Rectangle origin: self xRoot @ (self yRoot + self heightAbsolute) extent: self widthAbsolute @ list height. spaceBelow := screen bottom - rectangle top. rectangle bottom > screen bottom ifFalse: [^rectangle]. "Fine. Pop it up above the entry widget instead of below." rectangle moveTo: self xRoot @ self yRoot - rectangle extent. rectangle top < screen top ifFalse: [^rectangle]. "How annoying, it doesn't fit in the screen. Now we'll try to be real clever and either pop it up or down, depending on which way gives us the biggest list." spaceBelow < (rectangle bottom - screen top) ifTrue: [rectangle top: 0] ifFalse: [rectangle moveTo: self xRoot @ (self yRoot + self heightAbsolute); bottom: screen bottom]. ^rectangle ] isDropdownVisible [ "Answer whether the pop-up widget is visible" ^list window isMapped ] unmapList [ "Unmap the pop-up widget from the screen, transfer its selected item to the always visible text widget, and generate a callback." list window unmap. self text: self listText. self invokeCallback ] toggle [ "Toggle the visibility of the pop-up widget." widget activate. self isDropdownVisible ifTrue: [self unmapList] ifFalse: [self dropdown] ] ] BDropDown subclass: BDropDownList [ | callback | backgroundColor: aColor [ "Set the value of the backgroundColor for the widget, which in this class is set for the list widget and, when the focus is outside the control, for the text widget as well. Specifies the normal background color to use when displaying the widget." super backgroundColor: aColor. self highlight ] font: aString [ "Set the value of the font option for the widget. Specifies the font to use when drawing text inside the widget. The font can be given as either an X font name or a Blox font description string. X font names are given as many fields, each led by a minus, and each of which can be replaced by an * to indicate a default value is ok: foundry, family, weight, slant, setwidth, addstyle, pixel size, point size (the same as pixel size for historical reasons), horizontal resolution, vertical resolution, spacing, width, charset and character encoding. Blox font description strings have three fields, which must be separated by a space and of which only the first is mandatory: the font family, the font size in points (or in pixels if a negative value is supplied), and a number of styles separated by a space (valid styles are normal, bold, italic, underline and overstrike). Examples of valid fonts are ``Helvetica 10 Bold'', ``Times -14'', ``Futura Bold Underline''. You must enclose the font family in braces if it is made of two or more words." widget font: aString. super font: aString ] foregroundColor: aColor [ "Set the value of the foregroundColor for the widget, which in this class is set for the list widget and, when the focus is outside the control, for the text widget as well. Specifies the normal foreground color to use when displaying the widget." super foregroundColor: aColor. self highlight ] highlightBackground: aColor [ "Answer the value of the highlightBackground option for the widget. Specifies the background color to use when displaying selected items in the list widget and, when the focus is inside the control, for the text widget as well." super highlightBackground: aColor. self highlight ] highlightForeground: aColor [ "Answer the value of the highlightForeground option for the widget. Specifies the foreground color to use when displaying selected items in the list widget and, when the focus is inside the control, for the text widget as well." super highlightForeground: aColor. self highlight ] text [ "Answer the text that the user has picked from the widget and/or typed in the control (the exact way the text is entered will be established by subclasses, since this is an abstract method)." ^widget label ] callback: aReceiver message: aSymbol [ "Set up so that aReceiver is sent the aSymbol message (the name of a selector with at most two arguemtnts) when the active item in the receiver changegs. If the method accepts two arguments, the receiver is passed as the first parameter. If the method accepts one or two arguments, the selected index is passed as the last parameter." | arguments selector numArgs | selector := aSymbol asSymbol. numArgs := selector numArgs. arguments := #(). numArgs = 1 ifTrue: [arguments := {nil}]. numArgs = 2 ifTrue: [arguments := {self. nil}]. callback := DirectedMessage selector: selector arguments: arguments receiver: aReceiver ] invokeCallback [ "Generate a synthetic callback." self callback isNil ifTrue: [^self]. self callback arguments isEmpty ifFalse: [self callback arguments at: self callback arguments size put: self index]. self callback send ] index [ "Answer the value of the index option for the widget. Since it is not possible to modify an item once it has been picked from the list widget, this is always defined for BDropDownList widgets." ^list index ] highlight [ | bg fg | widget isActive ifTrue: [bg := list highlightBackground. fg := list highlightForeground] ifFalse: [bg := list backgroundColor. fg := list foregroundColor]. widget backgroundColor: bg; foregroundColor: fg ] createTextWidget [ ^BLabel new: self primitive ] listCallback [ self text: self listText ] text: aString [ widget label: aString ] setEvents [ super setEvents. "If we did not test whether the list box is focus, we would toggle twice (once in the widget's mouseDownEvent, once in the list's focusLeaveEvent)" widget onMouseDownEvent: 1 send: #value: to: [:pnt | "list isActive ifFalse: [" self toggle "]"]. widget onFocusEnterEventSend: #highlight to: self. widget onFocusLeaveEventSend: #highlight to: self. widget onKeyEvent: 'Down' send: #dropdown to: self ] ] BDropDown subclass: BDropDownEdit [ backgroundColor: aColor [ "Set the value of the backgroundColor option for the widget. Specifies the normal background color to use when displaying the widget." super backgroundColor: aColor. widget backgroundColor: aColor ] font: aString [ "Set the value of the font option for the widget. Specifies the font to use when drawing text inside the widget. The font can be given as either an X font name or a Blox font description string. X font names are given as many fields, each led by a minus, and each of which can be replaced by an * to indicate a default value is ok: foundry, family, weight, slant, setwidth, addstyle, pixel size, point size (the same as pixel size for historical reasons), horizontal resolution, vertical resolution, spacing, width, charset and character encoding. Blox font description strings have three fields, which must be separated by a space and of which only the first is mandatory: the font family, the font size in points (or in pixels if a negative value is supplied), and a number of styles separated by a space (valid styles are normal, bold, italic, underline and overstrike). Examples of valid fonts are ``Helvetica 10 Bold'', ``Times -14'', ``Futura Bold Underline''. You must enclose the font family in braces if it is made of two or more words." widget font: aString. super font: aString ] foregroundColor: aColor [ "Set the value of the foregroundColor option for the widget. Specifies the normal foreground color to use when displaying the widget." super foregroundColor: aColor. widget foregroundColor: aColor ] highlightBackground: aColor [ "Set the value of the highlightBackground option for the widget. Specifies the background color to use when displaying selected items in the list widget and the selection in the text widget." super highlightBackground: aColor. widget selectBackground: aColor ] highlightForeground: aColor [ "Set the value of the highlightBackground option for the widget. Specifies the background color to use when displaying selected items in the list widget and the selection in the text widget." super highlightForeground: aColor. widget selectForeground: aColor ] text [ "Answer the text shown in the widget" ^widget contents ] editCallback [ self isDropdownVisible ifFalse: [self invokeCallback] ] createTextWidget [ ^(BEdit new: self primitive) callback: self message: #editCallback ] insertAtEnd: aString [ "Clear the selection and append aString at the end of the text widget." widget insertAtEnd: aString ] replaceSelection: aString [ "Insert aString in the text widget at the current insertion point, replacing the currently selected text (if any), and leaving the text selected." widget replaceSelection: aString ] selectAll [ "Select the whole contents of the text widget" widget selectAll ] selectFrom: first to: last [ "Sets the selection of the text widget to include the characters starting with the one indexed by first (the very first character in the widget having index 1) and ending with the one just before last. If last refers to the same character as first or an earlier one, then the text widget's selection is cleared." widget selectFrom: first to: last ] selection [ "Answer an empty string if the text widget has no selection, else answer the currently selected text" ^widget selection ] selectionRange [ "Answer nil if the text widget has no selection, else answer an Interval object whose first item is the index of the first character in the selection, and whose last item is the index of the character just after the last one in the selection." ^widget selectionRange ] text: aString [ "Set the contents of the text widget and select them." widget contents: aString; selectAll ] ] "-------------------------- BProgress class -----------------------------" "-------------------------- BButtonLike class -----------------------------" "-------------------------- BColorButton class -----------------------------" "-------------------------- BBalloon class -----------------------------" "-------------------------- BDropDown class -----------------------------" "-------------------------- BDropDownList class -----------------------------" "-------------------------- BDropDownEdit class -----------------------------" smalltalk-3.2.5/packages/blox/gtk/BloxBasic.st0000644000175000017500000024435712123404352016166 00000000000000"====================================================================== | | Smalltalk GTK-based GUI building blocks (abstract classes). | | ======================================================================" "====================================================================== | | Copyright 1999, 2000, 2001, 2002, 2008 Free Software Foundation, Inc. | Written by Paolo Bonzini and Robert Collins. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LESSER. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" Object subclass: Gui [ | blox | blox [ "Return instance of blox subclass which implements window" ^blox ] blox: aBlox [ "Set instance of blox subclass which implements window" blox := aBlox ] ] Object subclass: BEventTarget [ | eventReceivers | addEventSet: aBEventSetSublass [ "Add to the receiver the event handlers implemented by an instance of aBEventSetSubclass. Answer the new instance of aBEventSetSublass." ^self registerEventReceiver: (aBEventSetSublass new: self) ] onAsciiKeyEventSend: aSelector to: anObject [ "When an ASCII key is pressed and the receiver has the focus, send the 1-argument message identified by aSelector to anObject, passing to it a Character." aSelector numArgs = 1 ifFalse: [^self invalidArgsError: '1']. self registerEventReceiver: anObject. ^self bind: '' to: #sendKeyEvent:oop:selector: of: self parameters: '*%A* ' , anObject asOop printString , ' ' , aSelector asTkString ] onDestroySend: aSelector to: anObject [ "When the receiver is destroyed, send the unary message identified by aSelector to anObject." aSelector numArgs = 0 ifFalse: [^self invalidArgsError: '0']. self connectSignal: 'destroy' to: [:widget :data | data key perform: data value. false] selector: #value:value: userData: anObject -> aSelector asSymbol ] onFocusEnterEventSend: aSelector to: anObject [ "When the focus enters the receiver, send the unary message identified by aSelector to anObject." aSelector numArgs = 0 ifFalse: [^self invalidArgsError: '0']. self connectSignal: 'focus-in-event' to: [:widget :ev :data | data key perform: data value. false] selector: #value:value:value: userData: anObject -> aSelector asSymbol ] onFocusLeaveEventSend: aSelector to: anObject [ "When the focus leaves the receiver, send the unary message identified by aSelector to anObject." aSelector numArgs = 0 ifFalse: [^self invalidArgsError: '0']. self connectSignal: 'focus-out-event' to: [:widget :ev :data | data key perform: data value. false] selector: #value:value:value: userData: anObject -> aSelector asSymbol ] onKeyEvent: key send: aSelector to: anObject [ "When the given key is pressed and the receiver has the focus, send the unary message identified by aSelector to anObject. Examples for key are: 'Ctrl-1', 'Alt-X', 'Meta-plus', 'enter'. The last two cases include example of special key identifiers; these include: 'backslash', 'exclam', 'quotedbl', 'dollar', 'asterisk', 'less', 'greater', 'asciicircum' (caret), 'question', 'equal', 'parenleft', 'parenright', 'colon', 'semicolon', 'bar' (pipe sign), 'underscore', 'percent', 'minus', 'plus', 'BackSpace', 'Delete', 'Insert', 'Return', 'End', 'Home', 'Prior' (Pgup), 'Next' (Pgdn), 'F1'..'F24', 'Caps_Lock', 'Num_Lock', 'Tab', 'Left', 'Right', 'Up', 'Down'. There are in addition four special identifiers which map to platform-specific keys: '', '', '', '' (all with the angular brackets!)." | block | aSelector numArgs = 0 ifFalse: [^self invalidArgsError: '0']. 'onKeyEvent TODO implement own collection and check in that..' printNl. block := [:widget :event :userData | "anObject perform: aSelector asSymbol." false]. self connectSignal: 'key-press-event' to: block selector: #value:value:value: userData: nil "(self getKeyPressEventNames: key) do: [ :each | self bind: each to: aSelector of: anObject parameters: '' ]" ] onKeyEventSend: aSelector to: anObject [ "When a key is pressed and the receiver has the focus, send the 1-argument message identified by aSelector to anObject. The pressed key will be passed as a String parameter; some of the keys will send special key identifiers such as those explained in the documentation for #onKeyEvent:send:to: Look at the #eventTest test program in the BloxTestSuite to find out the parameters passed to such an event procedure" aSelector numArgs = 1 ifFalse: [^self invalidArgsError: '1']. ^self bind: '' to: aSelector of: anObject parameters: '%K' ] onKeyUpEventSend: aSelector to: anObject [ "When a key has been released and the receiver has the focus, send the 1-argument message identified by aSelector to anObject. The released key will be passed as a String parameter; some of the keys will send special key identifiers such as those explained in the documentation for #onKeyEvent:send:to: Look at the #eventTest test program in the BloxTestSuite to find out the parameters passed to such an event procedure" | block | aSelector numArgs = 1 ifFalse: [^self invalidArgsError: '1']. 'key up TODO implement Tk''s %K and pass it' printNl. block := [:widget :event :userData | userData key perform: userData value with: nil. false]. self connectSignal: 'key-release-event' to: block selector: #value:value:value: userData: anObject -> aSelector asSymbol ] onMouseDoubleEvent: button send: aSelector to: anObject [ "When the given button is double-clicked on the mouse, send the 1-argument message identified by aSelector to anObject. The mouse position will be passed as a Point." | block | aSelector numArgs = 1 ifFalse: [^self invalidArgsError: '1']. self registerEventReceiver: anObject. block := [:widget :event :userData | | buttonEv | buttonEv := event castTo: GTK.GdkEventButton type. (buttonEv button value = button and: [buttonEv type value = GTK.Gdk gdk2buttonPress]) ifTrue: [userData key perform: userData value with: buttonEv x value @ buttonEv y value]. false]. self connectSignal: 'button-press-event' to: block selector: #value:value:value: userData: anObject -> aSelector asSymbol ] onMouseDoubleEventSend: aSelector to: anObject [ "When a button is double-clicked on the mouse, send the 2-argument message identified by aSelector to anObject. The mouse position will be passed as a Point in the first parameter, the button number will be passed as an Integer in the second parameter." | block | aSelector numArgs = 2 ifFalse: [^self invalidArgsError: '1']. self registerEventReceiver: anObject. block := [:widget :event :userData | | buttonEv | buttonEv := event castTo: GTK.GdkEventButton type. buttonEv type value = GTK.Gdk gdk2buttonPress ifTrue: [userData key perform: userData value with: buttonEv x value @ buttonEv y value with: buttonEv button value]. false]. self connectSignal: 'button-press-event' to: block selector: #value:value:value: userData: anObject -> aSelector asSymbol ] onMouseDownEvent: button send: aSelector to: anObject [ "When the given button is pressed on the mouse, send the 1-argument message identified by aSelector to anObject. The mouse position will be passed as a Point." | block | aSelector numArgs = 1 ifFalse: [^self invalidArgsError: '1']. self registerEventReceiver: anObject. block := [:widget :event :userData | | buttonEv | buttonEv := event castTo: GTK.GdkEventButton type. (buttonEv button value = button and: [buttonEv type value = GTK.Gdk gdkButtonPress]) ifTrue: [userData key perform: userData value with: buttonEv x value @ buttonEv y value]. false]. self connectSignal: 'button-press-event' to: block selector: #value:value:value: userData: anObject -> aSelector asSymbol ] onMouseDownEventSend: aSelector to: anObject [ "When a button is pressed on the mouse, send the 2-argument message identified by aSelector to anObject. The mouse position will be passed as a Point in the first parameter, the button number will be passed as an Integer in the second parameter." | block | aSelector numArgs = 2 ifFalse: [^self invalidArgsError: '2']. self registerEventReceiver: anObject. block := [:widget :event :userData | | buttonEv | buttonEv := event castTo: GTK.GdkEventButton type. buttonEv type value = GTK.Gdk gdkButtonPress ifTrue: [userData key perform: userData value with: buttonEv x value @ buttonEv y value with: buttonEv button value]. false]. self connectSignal: 'button-press-event' to: block selector: #value:value:value: userData: anObject -> aSelector asSymbol ] onMouseEnterEventSend: aSelector to: anObject [ "When the mouse enters the widget, send the unary message identified by aSelector to anObject." aSelector numArgs = 0 ifFalse: [^self invalidArgsError: '0']. self connectSignal: 'enter-notify-event' to: [:widget :ev :data | data key perform: data value. false] selector: #value:value:value: userData: anObject -> aSelector asSymbol ] onMouseLeaveEventSend: aSelector to: anObject [ "When the mouse leaves the widget, send the unary message identified by aSelector to anObject." aSelector numArgs = 0 ifFalse: [^self invalidArgsError: '0']. self connectSignal: 'leave-notify-event' to: [:widget :ev :data | data key perform: data value. false] selector: #value:value:value: userData: anObject -> aSelector asSymbol ] onMouseMoveEvent: button send: aSelector to: anObject [ "When the mouse is moved while the given button is pressed on the mouse, send the 1-argument message identified by aSelector to anObject. The mouse position will be passed as a Point." | modMask block | aSelector numArgs = 1 ifFalse: [^self invalidArgsError: '1']. self registerEventReceiver: anObject. modMask := GTK.Gdk gdkButton1Mask bitShift: button - 1. block := [:widget :event :userData | | motionEv | motionEv := event castTo: GTK.GdkEventMotion type. (motionEv state value anyMask: modMask) ifTrue: [userData key perform: userData value with: motionEv x value @ motionEv y value]. false]. self connectSignal: 'motion-notify-event' to: block selector: #value:value:value: userData: anObject -> aSelector asSymbol ] onMouseMoveEventSend: aSelector to: anObject [ "When the mouse is moved, send the 1-argument message identified by aSelector to anObject. The mouse position will be passed as a Point." | block | aSelector numArgs = 1 ifFalse: [^self invalidArgsError: '1']. self registerEventReceiver: anObject. block := [:widget :event :userData | | motionEv | motionEv := event castTo: GTK.GdkEventMotion type. userData key perform: userData value with: motionEv x value @ motionEv y value. false]. self connectSignal: 'motion-notify-event' to: block selector: #value:value:value: userData: anObject -> aSelector asSymbol ] onMouseTripleEvent: button send: aSelector to: anObject [ "When the given button is triple-clicked on the mouse, send the 1-argument message identified by aSelector to anObject. The mouse position will be passed as a Point." | block | aSelector numArgs = 1 ifFalse: [^self invalidArgsError: '1']. self registerEventReceiver: anObject. block := [:widget :event :userData | | buttonEv | buttonEv := event castTo: GTK.GdkEventButton type. (buttonEv button value = button and: [buttonEv type value = GTK.Gdk gdk3buttonPress]) ifTrue: [userData key perform: userData value with: buttonEv x value @ buttonEv y value]. false]. self connectSignal: 'button-press-event' to: block selector: #value:value:value: userData: anObject -> aSelector asSymbol ] onMouseTripleEventSend: aSelector to: anObject [ "When a button is triple-clicked on the mouse, send the 2-argument message identified by aSelector to anObject. The mouse position will be passed as a Point in the first parameter, the button number will be passed as an Integer in the second parameter." | block | aSelector numArgs = 2 ifFalse: [^self invalidArgsError: '1']. self registerEventReceiver: anObject. block := [:widget :event :userData | | buttonEv | buttonEv := event castTo: GTK.GdkEventButton type. buttonEv type value = GTK.Gdk gdk3buttonPress ifTrue: [userData key perform: userData value with: buttonEv x value @ buttonEv y value with: buttonEv button value]. false]. self connectSignal: 'button-press-event' to: block selector: #value:value:value: userData: anObject -> aSelector asSymbol ] onMouseUpEvent: button send: aSelector to: anObject [ "When the given button is released on the mouse, send the 1-argument message identified by aSelector to anObject. The mouse position will be passed as a Point." | block | aSelector numArgs = 1 ifFalse: [^self invalidArgsError: '1']. self registerEventReceiver: anObject. block := [:widget :event :userData | | buttonEv | buttonEv := event castTo: GTK.GdkEventButton type. buttonEv button value = button ifTrue: [userData key perform: userData value with: buttonEv x value @ buttonEv y value]. false]. self connectSignal: 'button-release-event' to: block selector: #value:value:value: userData: anObject -> aSelector asSymbol ] onMouseUpEventSend: aSelector to: anObject [ "When a button is released on the mouse, send the 2-argument message identified by aSelector to anObject. The mouse position will be passed as a Point in the first parameter, the button number will be passed as an Integer in the second parameter." | block | aSelector numArgs = 2 ifFalse: [^self invalidArgsError: '2']. self registerEventReceiver: anObject. block := [:widget :event :userData | | buttonEv | buttonEv := event castTo: GTK.GdkEventButton type. userData key perform: userData value with: buttonEv x value @ buttonEv y value with: buttonEv button value. false]. self connectSignal: 'button-release-event' to: block selector: #value:value:value: userData: anObject -> aSelector asSymbol ] onResizeSend: aSelector to: anObject [ "When the receiver is resized, send the 1-argument message identified by aSelector to anObject. The new size will be passed as a Point." | block | aSelector numArgs = 1 ifFalse: [^self invalidArgsError: '2']. self registerEventReceiver: anObject. block := [:widget :event :userData | | configEv | configEv := event castTo: GTK.GdkEventConfigure type. userData key perform: userData value with: configEv x value @ configEv y value. false]. self connectSignal: 'configure-event' to: block selector: #value:value:value: userData: anObject -> aSelector asSymbol ] connectSignal: aString to: anObject selector: aSymbol userData: userData [ self subclassResponsibility ] getKeyPressEventNames: key [ "Private - Given the key passed to a key event installer method, answer the KeyPress event name as required by Tcl." | platform mod keySym | keySym := key isCharacter ifTrue: [String with: key] ifFalse: [key]. (keySym at: 1) = $< ifTrue: [^{'<' , keySym , '>'}]. mod := ''. (keySym includes: $-) ifTrue: [mod := (ReadStream on: key) next: (key findLast: [:each | each = $-]) - 1. keySym := key copyFrom: mod size + 2 to: key size. platform := Blox platform. mod := (mod substrings: $-) inject: '' into: [:old :each | old , (self translateModifier: each platform: platform) , '-']]. ^(keySym size = 1 and: [keySym first isLetter]) ifTrue: ["Use both the lowercase and uppercase variants" {'<%1KeyPress-%2>' % {mod. keySym asLowercase}. '<%1KeyPress-%2>' % {mod. keySym asUppercase}}] ifFalse: [{'<%1KeyPress-%2>' % {mod. keySym}}] ] translateModifier: mod platform: platform [ | name | name := mod. name = 'Meta' ifTrue: [name := 'Alt']. name = 'Alt' & (platform == #macintosh) ifTrue: [name := 'Option']. name = 'Control' & (platform == #macintosh) ifTrue: [name := 'Cmd']. ^name ] invalidArgsError: expected [ "Private - Raise an error (as one could expect...) What is not so expected is that the expected argument is a string." ^self error: 'invalid number of arguments, expected ' , expected ] primBind: event to: aSymbol of: anObject parameters: params [ "Private - Register the given event, to be passed to anObject via the aSymbol selector with the given parameters" self subclassResponsibility ] registerEventReceiver: anObject [ "Private - Avoid that anObject is garbage collected as long as the receiver exists." eventReceivers isNil ifTrue: [eventReceivers := IdentitySet new]. ^eventReceivers add: anObject ] sendKeyEvent: key oop: oop selector: sel [ "Private - Filter ASCII events from Tcl to Smalltalk. We receive either *{}* for a non-ASCII char or *A* for an ASCII char, where A is the character. In the first case the event is eaten, in the second it is passed to a Smalltalk method" "key printNl. oop asInteger asObject printNl. '---' printNl." key size = 3 ifTrue: [oop asInteger asObject perform: sel asSymbol with: (key at: 2)] ] sendPointEvent: x y: y oop: oop selector: sel [ "Private - Filter mouse events from Tcl to Smalltalk. We receive two strings, we convert them to a Point and then pass them to a Smalltalk method" "oop printNl. oop asInteger asObject printNl. '---' printNl." oop asInteger asObject perform: sel asSymbol with: x asInteger @ y asInteger ] ] BEventTarget subclass: BEventSet [ | widget | BEventSet class >> new [ self shouldNotImplement ] BEventSet class >> new: widget [ "Private - Create a new event set object that will attach to the given widget. Answer the object. Note: this method should be called by #addEventSet:, not directly" ^(self basicNew) initialize: widget; yourself ] widget [ "Answer the widget to which the receiver is attached." ^widget ] initialize: aBWidget [ "Initialize the receiver's event handlers to attach to aBWidget. You can override this of course, but don't forget to call the superclass implementation first." widget := aBWidget ] connectSignal: aString to: anObject selector: aSymbol userData: userData [ "Private - Register the given event, to be passed to anObject via the aSymbol selector with the given parameters; this method is simply forwarded to the attached widget" self widget connectSignal: aString to: anObject selector: aSymbol userData: userData ] ] BEventTarget subclass: Blox [ | properties parent children | Platform := nil. ClipStatus := nil. DoDispatchEvents := nil. Blox class >> dispatchEvents [ "If this is the outermost dispatching loop that is started, dispatch events until the number of calls to #terminateMainLoop balances the number of calls to #dispatchEvents; return instantly if this is not the outermost dispatching loop that is started." | clipboard sem | DoDispatchEvents := DoDispatchEvents + 1. DoDispatchEvents = 1 ifFalse: [^self]. "If we're outside the event loop, Tk for Windows is unable to render the clipboard and locks up the clipboard viewer app. So, we save the contents for the next time we'll start a message loop. If the clipboard was temporarily saved to ClipStatus, restore it. ClipStatus is: - true if we own the clipboard - false if we don't - nil if we don't and we are outside a message loop - a String if we do and we are outside a message loop" clipboard := ClipStatus. ClipStatus := ClipStatus notNil and: [ClipStatus notEmpty]. ClipStatus ifTrue: [self clipboard: clipboard]. GTK.Gtk main. "Save the contents of the clipboard if we own it." ClipStatus := ClipStatus ifTrue: [self clearClipboard] ifFalse: [nil] ] Blox class >> dispatchEvents: mainWindow [ "Dispatch some events; return instantly if this is not the outermost dispatching loop that is started, else loop until the number of calls to #dispatchEvents balance the number of calls to #terminateMainLoop. In addition, set up an event handler that will call #terminateMainLoop upon destruction of the `mainWindow' widget (which can be any kind of BWidget, but will be typically a BWindow)." | sem | sem := Semaphore new. mainWindow onDestroySend: #signal to: sem. Blox dispatchEvents. sem wait. Blox terminateMainLoop ] Blox class >> terminateMainLoop [ "Terminate the event dispatching loop if this call to #terminateMainLoop balances the number of calls to #dispatchEvents. Answer whether the calls are balanced." DoDispatchEvents := DoDispatchEvents - 1. DoDispatchEvents = 0 ifTrue: [GTK.Gtk mainQuit] ] Blox class >> update: aspect [ "Initialize the Tcl and Blox environments; executed automatically on startup." | initResult | aspect == #returnFromSnapshot ifFalse: [^self]. GTK.Gtk gstGtkInit. DoDispatchEvents := 0. ClipStatus := nil. Blox withAllSubclassesDo: [:each | (each class includesSelector: #initializeOnStartup) ifTrue: [each initializeOnStartup]] ] Blox class >> new [ self shouldNotImplement ] Blox class >> new: parent [ "Create a new widget of the type identified by the receiver, inside the given parent widget. Answer the new widget" ^self basicNew initialize: parent ] Blox class >> cursorNames [ ^#(#X_cursor #arrow #based_arrow_down #based_arrow_up #boat #bogosity #bottom_left_corner #bottom_right_corner #bottom_side #bottom_tee #box_spiral #center_ptr #circle #clock #coffee_mug #cross #cross_reverse #crosshair #diamond_cross #dot #dotbox #double_arrow #draft_large #draft_small #draped_box #exchange #fleur #gobbler #gumby #hand1 #hand2 #heart #icon #iron_cross #left_ptr #left_side #left_tee #leftbutton #ll_angle #lr_angle #man #middlebutton #mouse #pencil #pirate #plus #question_arrow #right_ptr #right_side #right_tee #rightbutton #rtl_logo #sailboat #sb_down_arrow #sb_h_double_arrow #sb_left_arrow #sb_right_arrow #sb_up_arrow #sb_v_double_arrow #shuttle #sizing #spider #spraycan #star #target #tcross #top_left_arrow #top_left_corner #top_right_corner #top_side #top_tee #trek #ul_angle #umbrella #ur_angle #watch #xterm) ] Blox class >> cursorNameForType: type [ ^self cursorNames at: type // 2 + 1 ] Blox class >> cursorTypeForName: name [ ^##(| names | names := IdentityDictionary new. Blox cursorNames with: (0 to: 152 by: 2) do: [:name :type | names at: name put: type]. names) at: name ] Blox class >> tclEval: tclCode [ "Private - Evaluate the given Tcl code; if it raises an exception, raise it as a Smalltalk error" self notYetImplemented ] Blox class >> tclEval: tclCode with: arg1 [ "Private - Evaluate the given Tcl code, replacing %1 with arg1; if it raises an exception, raise it as a Smalltalk error" self notYetImplemented ] Blox class >> tclEval: tclCode with: arg1 with: arg2 [ "Private - Evaluate the given Tcl code, replacing %1 with arg1 and %2 with arg2; if it raises an exception, raise it as a Smalltalk error" self notYetImplemented ] Blox class >> tclEval: tclCode with: arg1 with: arg2 with: arg3 [ "Private - Evaluate the given Tcl code, replacing %1 with arg1, %2 with arg2 and %3 with arg3; if it raises an exception, raise it as a Smalltalk error" self notYetImplemented ] Blox class >> tclEval: tclCode with: arg1 with: arg2 with: arg3 with: arg4 [ "Private - Evaluate the given Tcl code, replacing %1 with arg1, %2 with arg2, and so on; if it raises an exception, raise it as a Smalltalk error" self notYetImplemented ] Blox class >> tclEval: tclCode withArguments: anArray [ "Private - Evaluate the given Tcl code, replacing %n with the n-th element of anArray; if it raises an exception, raise it as a Smalltalk error" self notYetImplemented ] Blox class >> tclResult [ "Private - Return the result code for Tcl, as a Smalltalk String." self notYetImplemented ] Blox class >> active [ "Answer the currently active Blox, or nil if the focus does not belong to a Smalltalk window." self tclEval: 'focus'. ^self fromString: self tclResult ] Blox class >> at: aPoint [ "Answer the Blox containing the given point on the screen, or nil if no Blox contains the given point (either because no Smalltalk window is there or because it is covered by another window)." self tclEval: 'winfo containing %1 %2' with: aPoint x printString with: aPoint y printString. ^self fromString: self tclResult ] Blox class >> atMouse [ "Answer the Blox under the mouse cursor's hot spot, or nil if no Blox contains the given point (either because no Smalltalk window is there or because it is covered by another window)." self tclEval: 'eval winfo containing [winfo pointerxy .]'. ^self fromString: self tclResult ] Blox class >> beep [ "Produce a bell" GTK.Gdk beep ] Blox class >> clearClipboard [ "Clear the clipboard, answer its old contents." | contents | contents := self clipboard. self tclEval: 'clipboard clear'. ClipStatus isString ifTrue: [ClipStatus := nil]. ClipStatus == true ifTrue: [ClipStatus := false]. ^contents ] Blox class >> clipboard [ "Retrieve the text in the clipboard." self tclEval: ' if { [catch { selection get -selection CLIPBOARD } clipboard] } { return "" } else { return $clipboard }'. ^self tclResult ] Blox class >> clipboard: aString [ "Set the contents of the clipboard to aString (or empty the clipboard if aString is nil)." self clearClipboard. (aString isNil or: [aString isEmpty]) ifTrue: [^self]. ClipStatus isNil ifTrue: [ClipStatus := aString. ^self]. self tclEval: 'clipboard append -- ' , aString asTkString. ClipStatus := true ] Blox class >> createColor: red green: green blue: blue [ "Answer a color that can be passed to methods such as `backgroundColor:'. The color will have the given RGB components (range is 0~65535)." "The answer is actually a String with an X color name, like '#FFFFC000C000' for pink" ^(String new: 13) at: 1 put: $#; at: 2 put: (Character digitValue: ((red bitShift: -12) bitAnd: 15)); at: 3 put: (Character digitValue: ((red bitShift: -8) bitAnd: 15)); at: 4 put: (Character digitValue: ((red bitShift: -4) bitAnd: 15)); at: 5 put: (Character digitValue: (red bitAnd: 15)); at: 6 put: (Character digitValue: ((green bitShift: -12) bitAnd: 15)); at: 7 put: (Character digitValue: ((green bitShift: -8) bitAnd: 15)); at: 8 put: (Character digitValue: ((green bitShift: -4) bitAnd: 15)); at: 9 put: (Character digitValue: (green bitAnd: 15)); at: 10 put: (Character digitValue: ((blue bitShift: -12) bitAnd: 15)); at: 11 put: (Character digitValue: ((blue bitShift: -8) bitAnd: 15)); at: 12 put: (Character digitValue: ((blue bitShift: -4) bitAnd: 15)); at: 13 put: (Character digitValue: (blue bitAnd: 15)); yourself ] Blox class >> createColor: cyan magenta: magenta yellow: yellow [ "Answer a color that can be passed to methods such as `backgroundColor:'. The color will have the given CMY components (range is 0~65535)." ^self createColor: 65535 - cyan green: 65535 - magenta blue: 65535 - yellow ] Blox class >> createColor: cyan magenta: magenta yellow: yellow black: black [ "Answer a color that can be passed to methods such as `backgroundColor:'. The color will have the given CMYK components (range is 0~65535)." | base | base := 65535 - black. ^self createColor: (base - cyan max: 0) green: (base - magenta max: 0) blue: (base - yellow max: 0) ] Blox class >> createColor: hue saturation: sat value: value [ "Answer a color that can be passed to methods such as `backgroundColor:'. The color will have the given HSV components (range is 0~65535)." | hue6 f val index components | hue6 := hue \\ 1 * 6. index := hue6 integerPart + 1. "Which of the six slices of the hue circle" f := hue6 fractionPart. "Where in the slice of the hue circle" val := 65535 * value. components := Array with: val with: val * (1 - sat) with: val * (1 - (sat * f)) with: val * (1 - (sat * (1 - f))). "v" "p" "q" "t" ^self createColor: (components at: (#(1 3 2 2 4 1) at: index)) floor green: (components at: (#(4 1 1 3 2 2) at: index)) floor blue: (components at: (#(2 2 4 1 1 3) at: index)) floor ] Blox class >> fonts [ "Answer the names of the font families in the system. Additionally, `Times', `Courier' and `Helvetica' are always made available." | stream result font ch | self tclEval: 'lsort [font families]'. stream := ReadStream on: self tclResult. result := WriteStream on: (Array new: stream size // 10). [stream atEnd] whileFalse: [(ch := stream next) isSeparator ifFalse: [ch = ${ ifTrue: [font := stream upTo: $}] ifFalse: [font := ch asString , (stream upTo: $ )]. result nextPut: font]]. ^result contents ] Blox class >> mousePointer [ "If the mouse pointer is on the same screen as the application's windows, returns a Point containing the pointer's x and y coordinates measured in pixels in the screen's root window (under X, if a virtual root window is in use on the screen, the position is computed in the whole desktop, not relative to the top-left corner of the currently shown portion). If the mouse pointer isn't on the same screen as window then answer nil." | x y | x := CIntType gcNew. y := CIntType gcNew. GdkDisplay getDefault getPointer: nil x: x y: y mask: nil. ^x value @ y value. ] Blox class >> platform [ "Answer the platform on which Blox is running; it can be either #unix, #macintosh or #windows." (Features includes: #WIN32) ifTrue: [^#windows]. ^#unix ] Blox class >> screenOrigin [ "Answer a Point indicating the coordinates of the upper left point of the screen in the virtual root window on which the application's windows are drawn (under Windows and the Macintosh, that's always 0 @ 0)" | x y | x := CIntType gcNew. y := CIntType gcNew. Gdk getDefaultRootWindow getOrigin: x y: y. ^x value negated @ y value negated. ] Blox class >> screenResolution [ "Answer a Point containing the resolution in dots per inch of the screen, in the x and y directions." | screen | screen := GdkScreen getDefault. ^(screen getWidth * 25.4 / screen getWidthMm) @ (screen getHeight * 25.4 / screen getHeightMm) ] Blox class >> screenSize [ "Answer a Point containing the size of the virtual root window on which the application's windows are drawn (under Windows and the Macintosh, that's the size of the screen)" | height width | width := CIntType gcNew. height := CIntType gcNew. Gdk getDefaultRootWindow getSize: width height: height. ^width value @ height value ] state [ "Answer the value of the state option for the widget. Specifies one of three states for the button: normal, active, or disabled. In normal state the button is displayed using the foreground and background options. The active state is typically used when the pointer is over the button. In active state the button is displayed using the activeForeground and activeBackground options. Disabled state means that the button should be insensitive: the application will refuse to activate the widget and will ignore mouse button presses." | state | state := self connected getState. state = Gtk gtkStateActive ifTrue: [^#active]. state = Gtk gtkStateInsensitive ifTrue: [^#disabled]. state = Gtk gtkStateSelected ifTrue: [^#active]. state = Gtk gtkStatePrelight ifTrue: [^#normal]. ^#normal ] state: value [ "Set the value of the state option for the widget. Specifies one of three states for the button: normal, active, or disabled. In normal state the button is displayed using the foreground and background options. The active state is typically used when the pointer is over the button. In active state the button is displayed using the activeForeground and activeBackground options. Disabled state means that the button should be insensitive: the application will refuse to activate the widget and will ignore mouse button presses." | state | self state = value ifTrue: [^self]. value = #disabled ifTrue: [self connected setSensitive: false] ifFalse: [value = #active ifTrue: [self connected setState: Gtk gtkStateActive] ifFalse: [value = #normal ifTrue: [self connected setState: Gtk gtkStateNormal] ifFalse: [self error: 'invalid state value']]] ] deepCopy [ "It does not make sense to make a copy, because it would make data inconsistent across different objects; so answer the receiver" ^self ] release [ "Destroy the receiver if it still exists, then perform the usual task of removing the dependency links" self connected destroy. super release ] shallowCopy [ "It does not make sense to make a copy, because it would make data inconsistent across different objects; so answer the receiver" ^self ] make: array [ "Create children of the receiver. Answer a Dictionary of the children. Each element of array is an Array including: a string which becomes the Dictionary's key, a binding like #{Blox.BWindow} identifying the class name, an array with the parameters to be set (for example #(#width: 50 #height: 30 #backgroundColor: 'blue')), and afterwards the children of the widget, described as arrays with this same format." ^self make: array on: LookupTable new ] make: array on: result [ "Private - Create children of the receiver, adding them to result; answer result. array has the format described in the comment to #make:" array do: [:each | self makeChild: each on: result]. ^result ] makeChild: each on: result [ "Private - Create a child of the receiver, adding them to result; each is a single element of the array described in the comment to #make:" | current selector | current := result at: (each at: 1) put: ((each at: 2) value new: self). each at: 3 do: [:param | selector isNil ifTrue: [selector := param] ifFalse: [current perform: selector with: param. selector := nil]]. each size > 3 ifFalse: [^result]. each from: 4 to: each size do: [:child | current makeChild: child on: result] ] addChild: child [ "The widget identified by child has been added to the receiver. This method is public not because you can call it, but because it can be useful to override it to perform some initialization on the children as they are added. Answer the new child." ] basicAddChild: child [ "The widget identified by child has been added to the receiver. Add it to the children collection and answer the new child. This method does nothing but is present for compatibility with Tk." ] primAddChild: child [ "The widget identified by child has been added to the receiver. Add it to the children collection and answer the new child." ^children addLast: child ] connected [ "Private - Answer the name of Tk widget for the connected widget. This widget is used for most options and for event binding." ^self asPrimitiveWidget connected ] container [ "Private - Answer the name of Tk widget for the container widget. This widget is used for geometry management." ^self asPrimitiveWidget connected ] destroyed [ "Private - The receiver has been destroyed, clear the instance variables to release some memory." children := parent := nil ] initialize: parentWidget [ "This is called by #new: to initialize the widget (as the name says...). The default implementation initializes the receiver's instance variables. This method is public not because you can call it, but because it might be useful to override it. Always answer the receiver." parent := parentWidget. properties := IdentityDictionary new. children := OrderedCollection new. self parent isNil ifFalse: [self parent primAddChild: self] ] connectSignal: aString to: anObject selector: aSymbol userData: userData [ self asPrimitiveWidget connected connectSignal: aString to: anObject selector: aSymbol userData: userData ] properties [ "Private - Answer the properties dictionary" ^properties ] tclEval: tclCode [ "Private - Evaluate the given Tcl code; if it raises an exception, raise it as a Smalltalk error" stdout nextPutAll: tclCode; nl; flush. self notYetImplemented ] tclEval: tclCode with: arg1 [ "Private - Evaluate the given Tcl code, replacing %1 with arg1; if it raises an exception, raise it as a Smalltalk error" self notYetImplemented ] tclEval: tclCode with: arg1 with: arg2 [ "Private - Evaluate the given Tcl code, replacing %1 with arg1 and %2 with arg2; if it raises an exception, raise it as a Smalltalk error" self notYetImplemented ] tclEval: tclCode with: arg1 with: arg2 with: arg3 [ "Private - Evaluate the given Tcl code, replacing %1 with arg1, %2 with arg2 and %3 with arg3; if it raises an exception, raise it as a Smalltalk error" self notYetImplemented ] tclEval: tclCode with: arg1 with: arg2 with: arg3 with: arg4 [ "Private - Evaluate the given Tcl code, replacing %1 with arg1, %2 with arg2, and so on; if it raises an exception, raise it as a Smalltalk error" self notYetImplemented ] tclEval: tclCode withArguments: anArray [ "Private - Evaluate the given Tcl code, replacing %n with the n-th element of anArray; if it raises an exception, raise it as a Smalltalk error" self notYetImplemented ] tclResult [ "Private - Return the result code for Tcl, as a Smalltalk String." self notYetImplemented ] asPrimitiveWidget [ "Answer the primitive widget that implements the receiver." self subclassResponsibility ] childrenCount [ "Answer how many children the receiver has" ^children size ] childrenDo: aBlock [ "Evaluate aBlock once for each of the receiver's child widgets, passing the widget to aBlock as a parameter" children do: aBlock ] destroy [ "Destroy the receiver" self container destroy ] drawingArea [ "Answer a Rectangle identifying the receiver's drawing area. The rectangle's corners specify the upper-left and lower-right corners of the client area. Because coordinates are relative to the upper-left corner of a window's drawing area, the coordinates of the rectangle's corner are (0,0)." ^0 @ 0 corner: self widthAbsolute @ self heightAbsolute ] enabled [ "Answer whether the receiver is enabled to input. Although defined here, this method is only used for widgets that define a #state method" ^self state ~= #disabled ] enabled: enabled [ "Set whether the receiver is enabled to input (enabled is a boolean). Although defined here, this method is only used for widgets that define a #state: method" self state: (enabled ifTrue: [#normal] ifFalse: [#disabled]) ] exists [ "Answer whether the receiver has been destroyed or not (answer false in the former case, true in the latter)." ^self asPrimitiveWidget exists ] fontHeight: aString [ "Answer the height of aString in pixels, when displayed in the same font as the receiver. Although defined here, this method is only used for widgets that define a #font method" self tclEval: 'font metrics %1 -linespace' with: self font asTkString. ^((aString occurrencesOf: Character nl) + 1) * self tclResult asNumber ] fontWidth: aString [ "Answer the width of aString in pixels, when displayed in the same font as the receiver. Although defined here, this method is only used for widgets that define a #font method" self tclEval: 'font measure %1 %2' with: self font asTkString with: aString asTkString. ^self tclResult asNumber ] isWindow [ "Answer whether the receiver represents a window on the screen." ^false ] parent [ "Answer the receiver's parent (or nil for a top-level window)." ^parent ] toplevel [ "Answer the top-level object (typically a BWindow or BPopupWindow) connected to the receiver." self parent isNil ifTrue: [^self]. ^self parent toplevel ] window [ "Answer the window in which the receiver stays. Note that while #toplevel won't answer a BTransientWindow, this method will." ^self parent window ] withChildrenDo: aBlock [ "Evaluate aBlock passing the receiver, and then once for each of the receiver's child widgets." self value: aBlock. self childrenDo: aBlock ] ] Blox subclass: BWidget [ | connected | BWidget class >> new [ "Create an instance of the receiver inside a BPopupWindow; do not map the window, answer the new widget. The created widget will become a child of the window and be completely attached to it (e.g. the geometry methods will modify the window's geometry). Note that while the widget *seems* to be directly painted on the root window, it actually belongs to the BPopupWindow; so don't send #destroy to the widget to remove it, but rather to the window." ^self new: BPopupWindow new ] BWidget class >> popup: initializationBlock [ "Create an instance of the receiver inside a BPopupWindow; before returning, pass the widget to the supplied initializationBlock, then map the window. Answer the new widget. The created widget will become a child of the window and be completely attached to it (e.g. the geometry methods will modify the window's geometry). Note that while the widget *seems* to be directly painted on the root window, it actually belongs to the BPopupWindow; so don't send #destroy to the widget to remove it, but rather to the window." | widget window | window := BPopupWindow new. widget := self new: window. initializationBlock value: widget. window map. ^widget ] borderWidth [ "Answer the value of the borderWidth option for the widget. Specifies a non-negative value indicating the width of the 3-D border to draw around the outside of the widget (if such a border is being drawn; the effect option typically determines this). The value may also be used when drawing 3-D effects in the interior of the widget. The value is measured in pixels." self properties at: #border ifPresent: [:value | ^value]. self tclEval: '%2 cget -borderwidth' with: self connected with: self container. ^self properties at: #border put: self tclResult asInteger ] borderWidth: value [ "Set the value of the borderWidth option for the widget. Specifies a non-negative value indicating the width of the 3-D border to draw around the outside of the widget (if such a border is being drawn; the effect option typically determines this). The value may also be used when drawing 3-D effects in the interior of the widget. The value is measured in pixels." self tclEval: '%2 configure -borderwidth %3' with: self connected with: self container with: value printString asTkString. self properties at: #border put: value ] cursor [ "Answer the value of the cursor option for the widget. Specifies the mouse cursor to be used for the widget. The value of the option is given by the standard X cursor cursor, i.e., any of the names defined in cursorcursor.h, without the leading XC_." self properties at: #cursor ifPresent: [:value | ^value]. self tclEval: '%1 cget -cursor' with: self connected with: self container. ^self properties at: #cursor put: self tclResult asSymbol ] cursor: value [ "Set the value of the cursor option for the widget. Specifies the mouse cursor to be used for the widget. The value of the option is given by the standard X cursor cursor, i.e., any of the names defined in cursorcursor.h, without the leading XC_." self tclEval: '%1 configure -cursor %3' with: self connected with: self container with: value asTkString. self properties at: #cursor put: value ] effect [ "Answer the value of the effect option for the widget. Specifies the effect desired for the widget's border. Acceptable values are raised, sunken, flat, ridge, solid, and groove. The value indicates how the interior of the widget should appear relative to its exterior; for example, raised means the interior of the widget should appear to protrude from the screen, relative to the exterior of the widget. Raised and sunken give the traditional 3-D appearance (for example, that of Xaw3D), while ridge and groove give a ``chiseled'' appearance like that of Swing or GTK+'s Metal theme. Flat and solid are not 3-D." self properties at: #effect ifPresent: [:value | ^value]. self tclEval: '%2 cget -relief' with: self connected with: self container. ^self properties at: #effect put: self tclResult asSymbol ] effect: value [ "Set the value of the effect option for the widget. Specifies the effect desired for the widget's border. Acceptable values are raised, sunken, flat, ridge, solid, and groove. The value indicates how the interior of the widget should appear relative to its exterior; for example, raised means the interior of the widget should appear to protrude from the screen, relative to the exterior of the widget. Raised and sunken give the traditional 3-D appearance (for example, that of Xaw3D), while ridge and groove give a ``chiseled'' appearance like that of Swing or GTK+'s Metal theme. Flat and solid are not 3-D." self tclEval: '%2 configure -relief %3' with: self connected with: self container with: value asTkString. self properties at: #effect put: value ] tabStop [ "Answer the value of the tabStop option for the widget. Determines whether the window accepts the focus during keyboard traversal (e.g., Tab and Shift-Tab). Before setting the focus to a window, Blox consults the value of the tabStop option. A value of false means that the window should be skipped entirely during keyboard traversal. true means that the window should receive the input focus as long as it is viewable (it and all of its ancestors are mapped). If you do not set this option, Blox makes the decision about whether or not to focus on the window: the current algorithm is to skip the window if it is disabled, it has no key bindings, or if it is not viewable. Of the standard widgets, BForm, BContainer, BLabel and BImage have no key bindings by default." self properties at: #takefocus ifPresent: [:value | ^value]. self tclEval: '%1 cget -takefocus' with: self connected with: self container. ^self properties at: #takefocus put: self tclResult == '1' ] tabStop: value [ "Set the value of the tabStop option for the widget. Determines whether the window accepts the focus during keyboard traversal (e.g., Tab and Shift-Tab). Before setting the focus to a window, Blox consults the value of the tabStop option. A value of false means that the window should be skipped entirely during keyboard traversal. true means that the window should receive the input focus as long as it is viewable (it and all of its ancestors are mapped). If you do not set this option, Blox makes the decision about whether or not to focus on the window: the current algorithm is to skip the window if it is disabled, it has no key bindings, or if it is not viewable. Of the standard widgets, BForm, BContainer, BLabel and BImage have no key bindings by default." self tclEval: '%1 configure -takefocus %3' with: self connected with: self container with: value asCBooleanValue printString asTkString. self properties at: #takefocus put: value ] create [ "Make the receiver able to respond to its widget protocol. This method is public not because you can call it, but because it can be useful to override it, not forgetting the call to super, to perform some initialization on the primitive widget just created; for an example of this, see the implementation of BButtonLike." self subclassResponsibility ] onDestroy: object data: data [ self destroyed ] setInitialSize [ "This is called by #createWidget to set the widget's initial size. The whole area is occupied by default. This method is public not because you can call it, but because it can be useful to override it." ] container [ "The outermost object implementing this widget is the same as the innermost object, by default (the exception being mostly BViewport and subclasses)." ^self connected ] activate [ "At any given time, one window on each display is designated as the focus window; any key press or key release events for the display are sent to that window. This method allows one to choose which window will have the focus in the receiver's display If the application currently has the input focus on the receiver's display, this method resets the input focus for the receiver's display to the receiver. If the application doesn't currently have the input focus on the receiver's display, Blox will remember the receiver as the focus for its top-level; the next time the focus arrives at the top-level, it will be redirected to the receiver (this is because most window managers will set the focus only to top-level windows, leaving it up to the application to redirect the focus among the children of the top-level)." self connected grabFocus ] activateNext [ "Activate the next widget in the focus `tabbing' order. The focus order depends on the widget creation order; you can set which widgets are in the order with the #tabStop: method." self tclEval: 'focus [ tk_focusNext %1 ]' with: self connected ] activatePrevious [ "Activate the previous widget in the focus `tabbing' order. The focus order depends on the widget creation order; you can set which widgets are in the order with the #tabStop: method." self tclEval: 'focus [ tk_focusPrev %1 ]' with: self connected ] bringToTop [ "Raise the receiver so that it is above all of its siblings in the widgets' z-order; the receiver will not be obscured by any siblings and will obscure any siblings that overlap it." | w | w := self connected getWindow. w isNil ifTrue: [w := self container getWindow]. w isNil ifFalse: [^w raise] ] sendToBack [ "Lower the receiver so that it is below all of its siblings in the widgets' z-order; the receiver will be obscured by any siblings that overlap it and will not obscure any siblings." | w | w := self connected getWindow. w isNil ifTrue: [w := self container getWindow]. w isNil ifFalse: [^w lower] ] isActive [ "Return whether the receiver is the window that currently owns the focus on its display." ^(self connected flags bitAnd: Gtk gtkHasFocus) > 0 ] boundingBox [ "Answer a Rectangle containing the bounding box of the receiver" ^self x @ self y extent: self width @ self height ] boundingBox: rect [ "Set the bounding box of the receiver to rect (a Rectangle)." self left: rect left top: rect top right: rect right bottom: rect bottom ] extent [ "Answer a Point containing the receiver's size" ^self width @ self height ] extent: extent [ "Set the receiver's size to the width and height contained in extent (a Point)." self width: extent x height: extent y ] height [ "Answer the `variable' part of the receiver's height within the parent widget. The value returned does not include any fixed amount of pixels indicated by #heightOffset: and must be interpreted in a relative fashion: the ratio of the returned value to the current size of the parent will be preserved upon resize. This apparently complicated method is known as `rubber sheet' geometry management. Behavior if the left or right edges are not within the client area of the parent is not defined -- the window might be clamped or might be positioned according to the specification." ^self parent heightChild: self ] height: value [ "Set to `value' the height of the widget within the parent widget. The value is specified in a relative fashion as an integer, so that the ratio of `value' to the current size of the parent will be preserved upon resize. This apparently complicated method is known as `rubber sheet' geometry management." self parent child: self height: value ] heightAbsolute [ "Force a recalculation of the layout of widgets in the receiver's parent, then answer the current height of the receiver in pixels." | h | h := self container getAllocation height. ^h = -1 ifTrue: [self height] ifFalse: [h] ] heightOffset [ "Private - Answer the pixels to be added or subtracted to the height of the receiver, with respect to the value set in a relative fashion through the #height: method." ^self properties at: #heightGeomOfs ifAbsent: [0] ] heightOffset: value [ "Add or subtract to the height of the receiver a fixed amount of `value' pixels, with respect to the value set in a relative fashion through the #height: method. Usage of this method is deprecated; use #inset: and BContainers instead." self properties at: #heightGeomOfs put: value. self parent child: self heightOffset: value ] heightPixels: value [ "Set the current height of the receiver to `value' pixels. Note that, after calling this method, #height will answer 0, which is logical considering that there is no `variable' part of the size (refer to #height and #height: for more explanations)." self height: 0; heightOffset: value ] inset: pixels [ "Inset the receiver's bounding box by the specified amount." self parent child: self inset: pixels ] left: left top: top right: right bottom: bottom [ "Set the bounding box of the receiver through its components." self x: left y: top width: right - left + 1 height: bottom - top + 1 ] pos: position [ "Set the receiver's origin to the width and height contained in position (a Point)." self x: position x y: position y ] posHoriz: aBlox [ "Position the receiver immediately to the right of aBlox." | x width | width := aBlox width. self x: width + aBlox x y: aBlox y. width = 0 ifTrue: [width := aBlox widthAbsolute. self xOffset: width. self width > 0 ifTrue: [self widthOffset: self widthOffset - width]] ] posVert: aBlox [ "Position the receiver just below aBlox." | y height | height := aBlox height. self x: aBlox x y: height + aBlox y. height = 0 ifTrue: [height := aBlox heightAbsolute. self yOffset: height. self height > 0 ifTrue: [self heightOffset: self heightOffset - height]] ] stretch: aBoolean [ "This method is only considered when on the path from the receiver to its toplevel there is a BContainer. It decides whether we are among the widgets that are stretched to fill the entire width of the BContainer." self parent child: self stretch: aBoolean. self properties at: #stretch put: aBoolean ] width [ "Answer the `variable' part of the receiver's width within the parent widget. The value returned does not include any fixed amount of pixels indicated by #widthOffset: and must be interpreted in a relative fashion: the ratio of the returned value to the current size of the parent will be preserved upon resize. This apparently complicated method is known as `rubber sheet' geometry management. Behavior if the left or right edges are not within the client area of the parent is not defined -- the window might be clamped or might be positioned according to the specification." ^self parent widthChild: self ] width: value [ "Set to `value' the width of the widget within the parent widget. The value is specified in a relative fashion as an integer, so that the ratio of `value' to the current size of the parent will be preserved upon resize. This apparently complicated method is known as `rubber sheet' geometry management." self parent child: self width: value ] width: width height: height [ "change my dimensions" self width: width; height: height ] widthAbsolute [ "Force a recalculation of the layout of widgets in the receiver's parent, then answer the current width of the receiver in pixels." | w | w := self container getAllocation width. ^w = -1 ifTrue: [self width] ifFalse: [w] ] widthOffset [ "Private - Answer the pixels to be added or subtracted to the width of the receiver, with respect to the value set in a relative fashion through the #width: method." ^self properties at: #widthGeomOfs ifAbsent: [0] ] widthOffset: value [ "Add or subtract to the width of the receiver a fixed amount of `value' pixels, with respect to the value set in a relative fashion through the #width: method. Usage of this method is deprecated; use #inset: and BContainers instead." self properties at: #widthGeomOfs put: value. self parent child: self widthOffset: value ] widthPixels: value [ "Set the current width of the receiver to `value' pixels. Note that, after calling this method, #width will answer 0, which is logical considering that there is no `variable' part of the size (refer to #width and #width: for more explanations)." self width: 0; widthOffset: value ] x [ "Answer the `variable' part of the receiver's x within the parent widget. The value returned does not include any fixed amount of pixels indicated by #xOffset: and must be interpreted in a relative fashion: the ratio of the returned value to the current size of the parent will be preserved upon resize. This apparently complicated method is known as `rubber sheet' geometry management. Behavior if the left or right edges are not within the client area of the parent is not defined -- the window might be clamped or might be positioned according to the specification." ^self parent xChild: self ] x: value [ "Set to `value' the x of the widget within the parent widget. The value is specified in a relative fashion as an integer, so that the ratio of `value' to the current size of the parent will be preserved upon resize. This apparently complicated method is known as `rubber sheet' geometry management." self parent child: self x: value ] x: xPos y: yPos [ "Set the origin of the receiver through its components xPos and yPos." self x: xPos; y: yPos ] x: xPos y: yPos width: xSize height: ySize [ "Set the bounding box of the receiver through its origin and size." self x: xPos y: yPos; width: xSize height: ySize ] xAbsolute [ "Force a recalculation of the layout of widgets in the receiver's parent, then answer the current x of the receiver in pixels." | x | x := self container getAllocation left. ^x = -1 ifTrue: [self left] ifFalse: [x] ] xOffset [ "Private - Answer the pixels to be added or subtracted to the x of the receiver, with respect to the value set in a relative fashion through the #x: method." ^self properties at: #xGeomOfs ifAbsent: [0] ] xOffset: value [ "Add or subtract to the x of the receiver a fixed amount of `value' pixels, with respect to the value set in a relative fashion through the #x: method. Usage of this method is deprecated; use #inset: and BContainers instead." self properties at: #xGeomOfs put: value. self parent child: self xOffset: value ] xPixels: value [ "Set the current x of the receiver to `value' pixels. Note that, after calling this method, #x will answer 0, which is logical considering that there is no `variable' part of the size (refer to #x and #x: for more explanations)." self x: 0; xOffset: value ] xRoot [ "Answer the x position of the receiver with respect to the top-left corner of the desktop (including the offset of the virtual root window under X)." self tclEval: 'expr [winfo rootx %1] + [winfo vrootx %1]' with: self container. ^self tclResult asInteger ] y [ "Answer the `variable' part of the receiver's y within the parent widget. The value returned does not include any fixed amount of pixels indicated by #yOffset: and must be interpreted in a relative fashion: the ratio of the returned value to the current size of the parent will be preserved upon resize. This apparently complicated method is known as `rubber sheet' geometry management. Behavior if the left or right edges are not within the client area of the parent is not defined -- the window might be clamped or might be positioned according to the specification." ^self parent yChild: self ] y: value [ "Set to `value' the y of the widget within the parent widget. The value is specified in a relative fashion as an integer, so that the ratio of `value' to the current size of the parent will be preserved upon resize. This apparently complicated method is known as `rubber sheet' geometry management." self parent child: self y: value ] yAbsolute [ "Force a recalculation of the layout of widgets in the receiver's parent, then answer the current y of the receiver in pixels." | y | y := self container getAllocation top. ^y = -1 ifTrue: [self top] ifFalse: [y] ] yOffset [ "Private - Answer the pixels to be added or subtracted to the y of the receiver, with respect to the value set in a relative fashion through the #y: method." ^self properties at: #yGeomOfs ifAbsent: [0] ] yOffset: value [ "Add or subtract to the y of the receiver a fixed amount of `value' pixels, with respect to the value set in a relative fashion through the #y: method. Usage of this method is deprecated; use #inset: and BContainers instead." self properties at: #yGeomOfs put: value. self parent child: self yOffset: value ] yPixels: value [ "Set the current y of the receiver to `value' pixels. Note that, after calling this method, #y will answer 0, which is logical considering that there is no `variable' part of the size (refer to #y and #y: for more explanations)." self y: 0; yOffset: value ] yRoot [ "Answer the y position of the receiver with respect to the top-left corner of the desktop (including the offset of the virtual root window under X)." self tclEval: 'expr [winfo rooty %1] + [winfo vrooty %1]' with: self container. ^self tclResult asInteger ] ] BWidget subclass: BPrimitive [ asPrimitiveWidget [ "Answer the primitive widget that implements the receiver." ^self ] exists [ "Answer whether the receiver has been destroyed or not (answer false in the former case, true in the latter)." ^connected notNil ] destroyed [ "Private - The receiver has been destroyed, clear the instance variables to release some memory." super destroyed. connected := nil ] connected [ "answer the gtk native object that is used for geometry mgmt & layout" connected isNil ifTrue: [self createWidget]. ^connected ] connected: anObject [ "set the current gtk native object" connected := anObject ] createWidget [ self create. self show. self setInitialSize. self parent notNil ifTrue: [self parent addChild: self] ] show [ (self connected) connectSignal: 'destroy' to: self selector: #onDestroy:data: userData: nil; show ] ] BWidget subclass: BExtended [ | primitive | asPrimitiveWidget [ "Answer the primitive widget that implements the receiver." ^primitive asPrimitiveWidget ] create [ "After this method is called (the call is made automatically) the receiver will be attached to a `primitive' widget (which can be in turn another extended widget). This method is public not because you can call it, but because it can be useful to override it, not forgetting the call to super (which only calls #newPrimitive and saves the result), to perform some initialization on the primitive widget just created; overriding #create is in fact more generic than overriding #newPrimitive. For an example of this, see the implementation of BButtonLike." primitive := self newPrimitive ] newPrimitive [ "Create and answer a new widget on which the implementation of the receiver will be based. You should not call this method directly; instead you must override it in BExtended's subclasses." self subclassResponsibility ] ] BPrimitive subclass: BViewport [ | container horizontal vertical | container [ "answer the gtk scrolled window" container isNil ifTrue: [self createWidget]. ^container ] container: aGtkWidget [ container := aGtkWidget ] show [ self container: (GTK.GtkScrolledWindow new: nil vadjustment: nil). self container setPolicy: GTK.Gtk gtkPolicyAutomatic vscrollbarPolicy: GTK.Gtk gtkPolicyAutomatic. horizontal := vertical := true. self needsViewport ifTrue: [self container addWithViewport: self connected] ifFalse: [self container add: self connected]. super show. self container show ] pickPolicy [ | hpolicy vpolicy | hpolicy := horizontal ifTrue: [GTK.Gtk gtkPolicyAutomatic] ifFalse: [GTK.Gtk gtkPolicyNever]. vpolicy := vertical ifTrue: [GTK.Gtk gtkPolicyAutomatic] ifFalse: [GTK.Gtk gtkPolicyNever]. self container setPolicy: hpolicy vscrollbarPolicy: vpolicy ] needsViewport [ ^true ] horizontal [ "Answer whether an horizontal scrollbar is drawn in the widget if needed." ^horizontal ] horizontal: aBoolean [ "Set whether an horizontal scrollbar is drawn in the widget if needed." horizontal := aBoolean. self pickPolicy ] horizontalNeeded [ "Answer whether an horizontal scrollbar is needed to show all the information in the widget." self tclEval: 'expr [lindex [%1 xview] 0] > 0 || [lindex [%1 xview] 1] < 1' with: self connected. ^self tclResult = '1' ] horizontalShown [ "Answer whether an horizontal scrollbar is drawn in the widget." ^self horizontal and: [self horizontalNeeded] ] vertical [ "Answer whether a vertical scrollbar is drawn in the widget if needed." ^vertical ] vertical: aBoolean [ "Set whether a vertical scrollbar is drawn in the widget if needed." vertical := aBoolean. self pickPolicy ] verticalNeeded [ "Answer whether a vertical scrollbar is needed to show all the information in the widget." self tclEval: 'expr [lindex [%1 yview] 0] > 0 || [lindex [%1 yview] 1] < 1' with: self connected. ^self tclResult = '1' ] verticalShown [ "Answer whether a vertical scrollbar is drawn in the widget." ^self vertical and: [self verticalNeeded] ] ] Blox subclass: BMenuObject [ | childrensUnderline callback | activeBackground [ "Answer the value of the activeBackground option for the widget. Specifies background color to use when drawing active elements. An element (a widget or portion of a widget) is active if the mouse cursor is positioned over the element and pressing a mouse button will cause some action to occur. For some elements on Windows and Macintosh systems, the active color will only be used while mouse button 1 is pressed over the element." self properties at: #activebackground ifPresent: [:value | ^value]. self tclEval: '%1 cget -activebackground' with: self connected with: self container. ^self properties at: #activebackground put: self tclResult ] activeBackground: value [ "Set the value of the activeBackground option for the widget. Specifies background color to use when drawing active elements. An element (a widget or portion of a widget) is active if the mouse cursor is positioned over the element and pressing a mouse button will cause some action to occur. For some elements on Windows and Macintosh systems, the active color will only be used while mouse button 1 is pressed over the element." self tclEval: '%1 configure -activebackground %3' with: self connected with: self container with: value asTkString. self properties at: #activebackground put: value ] activeForeground [ "Answer the value of the activeForeground option for the widget. Specifies foreground color to use when drawing active elements. See above for definition of active elements." self properties at: #activeforeground ifPresent: [:value | ^value]. self tclEval: '%1 cget -activeforeground' with: self connected with: self container. ^self properties at: #activeforeground put: self tclResult ] activeForeground: value [ "Set the value of the activeForeground option for the widget. Specifies foreground color to use when drawing active elements. See above for definition of active elements." self tclEval: '%1 configure -activeforeground %3' with: self connected with: self container with: value asTkString. self properties at: #activeforeground put: value ] asPrimitiveWidget [ "Answer the primitive widget that implements the receiver." ^self ] backgroundColor [ "Answer the value of the backgroundColor option for the widget. Specifies the normal background color to use when displaying the widget." self properties at: #background ifPresent: [:value | ^value]. self tclEval: '%1 cget -background' with: self connected with: self container. ^self properties at: #background put: self tclResult ] backgroundColor: value [ "Set the value of the backgroundColor option for the widget. Specifies the normal background color to use when displaying the widget." self tclEval: '%1 configure -background %3' with: self connected with: self container with: value asTkString. self properties at: #background put: value ] foregroundColor [ "Answer the value of the foregroundColor option for the widget. Specifies the normal foreground color to use when displaying the widget." self properties at: #foreground ifPresent: [:value | ^value]. self tclEval: '%1 cget -foreground' with: self connected with: self container. ^self properties at: #foreground put: self tclResult ] foregroundColor: value [ "Set the value of the foregroundColor option for the widget. Specifies the normal foreground color to use when displaying the widget." self tclEval: '%1 configure -foreground %3' with: self connected with: self container with: value asTkString. self properties at: #foreground put: value ] callback [ "Answer a DirectedMessage that is sent when the receiver is modified, or nil if none has been set up." ^callback ] callback: aReceiver message: aSymbol [ "Set up so that aReceiver is sent the aSymbol message (the name of a zero- or one-argument selector) when the receiver is clicked. If the method accepts an argument, the receiver is passed." | arguments selector numArgs | selector := aSymbol asSymbol. numArgs := selector numArgs. arguments := #(). numArgs = 1 ifTrue: [arguments := Array with: self]. callback := DirectedMessage selector: selector arguments: arguments receiver: aReceiver ] callback: aReceiver message: aSymbol argument: anObject [ "Set up so that aReceiver is sent the aSymbol message (the name of a one- or two-argument selector) when the receiver is clicked. If the method accepts two argument, the receiver is passed together with anObject; if it accepts a single one, instead, only anObject is passed." | arguments selector numArgs | selector := aSymbol asSymbol. numArgs := selector numArgs. numArgs = 2 ifTrue: [arguments := {self. anObject}] ifFalse: [arguments := {anObject}]. callback := DirectedMessage selector: selector arguments: arguments receiver: aReceiver ] invokeCallback [ "Generate a synthetic callback" self callback isNil ifFalse: [self callback send] ] connected [ ^self uiManager getWidget: self path ] uiManager [ self subclassResponsibility ] path [ self subclassResponsibility ] underline: label [ childrensUnderline isNil ifTrue: [childrensUnderline := ByteArray new: 256]. label doWithIndex: [:each :index | | ascii | ascii := each asUppercase value + 1. (childrensUnderline at: ascii) = 0 ifTrue: [childrensUnderline at: ascii put: 1. ^index - 1]]. ^0 ] ] "-------------------------- Gui class -----------------------------" "-------------------------- BEventTarget class -----------------------------" "-------------------------- BEventSet class -----------------------------" "-------------------------- Blox class -----------------------------" "-------------------------- BWidget class -----------------------------" "-------------------------- BPrimitive class -----------------------------" "-------------------------- BExtended class -----------------------------" "-------------------------- BViewport class -----------------------------" "-------------------------- BMenuObject class -----------------------------" String extend [ asTkString [ "Private, Blox - Answer a copy of the receiver enclosed in double-quotes and in which all the characters that Tk cannot read are escaped through a backslash" self notYetImplemented ] asTkImageString [ "Private, Blox - Look for GIF images; for those, since Base-64 data does not contain { and }, is better to use the {} syntax." self notYetImplemented ] ] smalltalk-3.2.5/packages/blox/gtk/BloxWidgets.st0000644000175000017500000042610012123404352016537 00000000000000"====================================================================== | | Smalltalk Tk-based GUI building blocks (basic widget classes). | | ======================================================================" "====================================================================== | | Copyright 1999, 2000, 2001, 2002, 2008 Free Software Foundation, Inc. | Written by Paolo Bonzini and Robert Collins. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LESSER. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" BPrimitive subclass: BEdit [ | callback | Initialized := nil. BEdit class >> new: parent contents: aString [ "Answer a new BEdit widget laid inside the given parent widget, with a default content of aString" ^(self new: parent) contents: aString; yourself ] BEdit class >> initializeOnStartup [ Initialized := false ] backgroundColor [ "Answer the value of the backgroundColor option for the widget. Specifies the normal background color to use when displaying the widget." self properties at: #background ifPresent: [:value | ^value]. self tclEval: '%1 cget -background' with: self connected with: self container. ^self properties at: #background put: self tclResult ] backgroundColor: value [ "Set the value of the backgroundColor option for the widget. Specifies the normal background color to use when displaying the widget." self tclEval: '%1 configure -background %3' with: self connected with: self container with: value asTkString. self properties at: #background put: value ] callback [ "Answer a DirectedMessage that is sent when the receiver is modified, or nil if none has been set up." ^callback ] callback: aReceiver message: aSymbol [ "Set up so that aReceiver is sent the aSymbol message (the name of a zero- or one-argument selector) when the receiver is modified. If the method accepts an argument, the receiver is passed." | arguments selector numArgs | selector := aSymbol asSymbol. numArgs := selector numArgs. arguments := #(). numArgs = 1 ifTrue: [arguments := Array with: self]. callback := DirectedMessage selector: selector arguments: arguments receiver: aReceiver ] contents [ "Return the contents of the widget" self tclEval: 'return ${var' , self connected , '}'. ^self tclResult ] contents: newText [ "Set the contents of the widget" self tclEval: 'set var' , self connected , ' ' , newText asTkString ] font [ "Answer the value of the font option for the widget. Specifies the font to use when drawing text inside the widget. The font can be given as either an X font name or a Blox font description string. X font names are given as many fields, each led by a minus, and each of which can be replaced by an * to indicate a default value is ok: foundry, family, weight, slant, setwidth, addstyle, pixel size, point size (the same as pixel size for historical reasons), horizontal resolution, vertical resolution, spacing, width, charset and character encoding. Blox font description strings have three fields, which must be separated by a space and of which only the first is mandatory: the font family, the font size in points (or in pixels if a negative value is supplied), and a number of styles separated by a space (valid styles are normal, bold, italic, underline and overstrike). Examples of valid fonts are ``Helvetica 10 Bold'', ``Times -14'', ``Futura Bold Underline''. You must enclose the font family in braces if it is made of two or more words." self properties at: #font ifPresent: [:value | ^value]. self tclEval: '%1 cget -font' with: self connected with: self container. ^self properties at: #font put: self tclResult ] font: value [ "Set the value of the font option for the widget. Specifies the font to use when drawing text inside the widget. The font can be given as either an X font name or a Blox font description string. X font names are given as many fields, each led by a minus, and each of which can be replaced by an * to indicate a default value is ok: foundry, family, weight, slant, setwidth, addstyle, pixel size, point size (the same as pixel size for historical reasons), horizontal resolution, vertical resolution, spacing, width, charset and character encoding. Blox font description strings have three fields, which must be separated by a space and of which only the first is mandatory: the font family, the font size in points (or in pixels if a negative value is supplied), and a number of styles separated by a space (valid styles are normal, bold, italic, underline and overstrike). Examples of valid fonts are ``Helvetica 10 Bold'', ``Times -14'', ``Futura Bold Underline''. You must enclose the font family in braces if it is made of two or more words." self tclEval: '%1 configure -font %3' with: self connected with: self container with: value asTkString. self properties at: #font put: value ] foregroundColor [ "Answer the value of the foregroundColor option for the widget. Specifies the normal foreground color to use when displaying the widget." self properties at: #foreground ifPresent: [:value | ^value]. self tclEval: '%1 cget -foreground' with: self connected with: self container. ^self properties at: #foreground put: self tclResult ] foregroundColor: value [ "Set the value of the foregroundColor option for the widget. Specifies the normal foreground color to use when displaying the widget." self tclEval: '%1 configure -foreground %3' with: self connected with: self container with: value asTkString. self properties at: #foreground put: value ] selectBackground [ "Answer the value of the selectBackground option for the widget. Specifies the background color to use when displaying selected parts of the widget." self properties at: #selectbackground ifPresent: [:value | ^value]. self tclEval: '%1 cget -selectbackground' with: self connected with: self container. ^self properties at: #selectbackground put: self tclResult ] selectBackground: value [ "Set the value of the selectBackground option for the widget. Specifies the background color to use when displaying selected parts of the widget." self tclEval: '%1 configure -selectbackground %3' with: self connected with: self container with: value asTkString. self properties at: #selectbackground put: value ] selectForeground [ "Answer the value of the selectForeground option for the widget. Specifies the foreground color to use when displaying selected parts of the widget." self properties at: #selectforeground ifPresent: [:value | ^value]. self tclEval: '%1 cget -selectforeground' with: self connected with: self container. ^self properties at: #selectforeground put: self tclResult ] selectForeground: value [ "Set the value of the selectForeground option for the widget. Specifies the foreground color to use when displaying selected parts of the widget." self tclEval: '%1 configure -selectforeground %3' with: self connected with: self container with: value asTkString. self properties at: #selectforeground put: value ] create [ "Private - Set up the widget and Tcl hooks to get callbacks from it." self create: ' -width 0'. Initialized ifFalse: [self defineCallbackProcedure]. self tclEval: ' set var%1 {} bind %1 <> {callback %2 invokeCallback} trace variable var%1 w doEditCallback %1 configure -textvariable var%1 -highlightthickness 0 -takefocus 1' with: self connected with: self asOop printString ] defineCallbackProcedure [ "Private - Set up a Tcl hook to generate Changed events for entry widgets" Initialized := true. self tclEval: ' proc doEditCallback { name el op } { regsub ^var $name {} widgetName event generate $widgetName <> }' ] setInitialSize [ "Make the Tk placer's status, the receiver's properties and the window status (as returned by winfo) consistent. Occupy the height indicated by the widget itself and the whole of the parent's width, at the top left corner" self x: 0 y: 0; width: self parent width ] widgetType [ ^'entry' ] destroyed [ "Private - The receiver has been destroyed, clear the corresponding Tcl variable to avoid memory leaks." self tclEval: 'unset var' , self connected. super destroyed ] hasSelection [ "Answer whether there is selected text in the widget" self tclEval: self connected , ' selection present'. ^self tclResult = '1' ] insertAtEnd: aString [ "Clear the selection and append aString at the end of the widget." self tclEval: '%1 selection clear %1 insert end %2 %1 see end' with: self connected with: aString asTkString ] insertText: aString [ "Insert aString in the widget at the current insertion point, replacing the currently selected text (if any)." self tclEval: 'catch { %1 delete sel.first sel.last } %1 insert insert %2 %1 see insert' with: self connected with: aString asTkString ] invokeCallback [ "Generate a synthetic callback." self callback isNil ifFalse: [self callback send] ] nextPut: aCharacter [ "Clear the selection and append aCharacter at the end of the widget." self insertAtEnd: (String with: aCharacter) ] nextPutAll: aString [ "Clear the selection and append aString at the end of the widget." self insertAtEnd: aString ] nl [ "Clear the selection and append a linefeed character at the end of the widget." self insertAtEnd: Character nl asString ] replaceSelection: aString [ "Insert aString in the widget at the current insertion point, replacing the currently selected text (if any), and leaving the text selected." self tclEval: 'catch { %1 icursor sel.first %1 delete sel.first sel.last } %1 insert insert %2 %1 select insert [expr %3 + [%1 index insert]] %1 see insert' with: self connected with: aString asTkString with: aString size printString ] selectAll [ "Select the whole contents of the widget." self tclEval: self connected , ' selection range 0 end' ] selectFrom: first to: last [ "Sets the selection to include the characters starting with the one indexed by first (the very first character in the widget having index 1) and ending with the one just before last. If last refers to the same character as first or an earlier one, then the widget's selection is cleared." self tclEval: '%1 selection range %2 %3' with: self connected with: (first - 1) printString with: (last - 1) printString ] selection [ "Answer an empty string if the widget has no selection, else answer the currently selected text" | stream first | self tclEval: 'if [%1 selection present] { return [string range ${var%1} [%1 index sel.first] [%1 index sel.last]]" }' with: self connected. ^self tclResult ] selectionRange [ "Answer nil if the widget has no selection, else answer an Interval object whose first item is the index of the first character in the selection, and whose last item is the index of the character just after the last one in the selection." | stream first | self tclEval: 'if [%1 selection present] { return "[%1 index sel.first] [%1 index sel.last]" }' with: self connected. stream := ReadStream on: self tclResult. stream atEnd ifTrue: [^nil]. first := (stream upTo: $ ) asInteger + 1. ^first to: stream upToEnd asInteger + 1 ] space [ "Clear the selection and append a space at the end of the widget." self insertAtEnd: ' ' ] ] BPrimitive subclass: BLabel [ AnchorPoints := nil. BLabel class >> initialize [ "Private - Initialize the receiver's class variables." (AnchorPoints := IdentityDictionary new: 15) at: #topLeft put: 'nw'; at: #topCenter put: 'n'; at: #topRight put: 'ne'; at: #leftCenter put: 'w'; at: #center put: 'center'; at: #rightCenter put: 'e'; at: #bottomLeft put: 'sw'; at: #bottomCenter put: 's'; at: #bottomRight put: 'se' ] BLabel class >> new: parent label: label [ "Answer a new BLabel widget laid inside the given parent widget, showing by default the `label' String." ^(self new: parent) label: label; yourself ] alignment [ "Answer the value of the anchor option for the widget. Specifies how the information in a widget (e.g. text or a bitmap) is to be displayed in the widget. Must be one of the symbols #topLeft, #topCenter, #topRight, #leftCenter, #center, #rightCenter, #bottomLeft, #bottomCenter, #bottomRight. For example, #topLeft means display the information such that its top-left corner is at the top-left corner of the widget." ^self properties at: #alignment ifAbsent: [#topLeft] ] alignment: aSymbol [ "Set the value of the anchor option for the widget. Specifies how the information in a widget (e.g. text or a bitmap) is to be displayed in the widget. Must be one of the symbols #topLeft, #topCenter, #topRight, #leftCenter, #center, #rightCenter, #bottomLeft, #bottomCenter, #bottomRight. For example, #topLeft means display the information such that its top-left corner is at the top-left corner of the widget." self anchor: (AnchorPoints at: aSymbol). self properties at: #alignment put: aSymbol ] backgroundColor [ "Answer the value of the backgroundColor option for the widget. Specifies the normal background color to use when displaying the widget." self properties at: #background ifPresent: [:value | ^value]. self tclEval: '%1 cget -background' with: self connected with: self container. ^self properties at: #background put: self tclResult ] backgroundColor: value [ "Set the value of the backgroundColor option for the widget. Specifies the normal background color to use when displaying the widget." self tclEval: '%1 configure -background %3' with: self connected with: self container with: value asTkString. self properties at: #background put: value ] font [ "Answer the value of the font option for the widget. Specifies the font to use when drawing text inside the widget. The font can be given as either an X font name or a Blox font description string. X font names are given as many fields, each led by a minus, and each of which can be replaced by an * to indicate a default value is ok: foundry, family, weight, slant, setwidth, addstyle, pixel size, point size (the same as pixel size for historical reasons), horizontal resolution, vertical resolution, spacing, width, charset and character encoding. Blox font description strings have three fields, which must be separated by a space and of which only the first is mandatory: the font family, the font size in points (or in pixels if a negative value is supplied), and a number of styles separated by a space (valid styles are normal, bold, italic, underline and overstrike). Examples of valid fonts are ``Helvetica 10 Bold'', ``Times -14'', ``Futura Bold Underline''. You must enclose the font family in braces if it is made of two or more words." self properties at: #font ifPresent: [:value | ^value]. self tclEval: '%1 cget -font' with: self connected with: self container. ^self properties at: #font put: self tclResult ] font: value [ "Set the value of the font option for the widget. Specifies the font to use when drawing text inside the widget. The font can be given as either an X font name or a Blox font description string. X font names are given as many fields, each led by a minus, and each of which can be replaced by an * to indicate a default value is ok: foundry, family, weight, slant, setwidth, addstyle, pixel size, point size (the same as pixel size for historical reasons), horizontal resolution, vertical resolution, spacing, width, charset and character encoding. Blox font description strings have three fields, which must be separated by a space and of which only the first is mandatory: the font family, the font size in points (or in pixels if a negative value is supplied), and a number of styles separated by a space (valid styles are normal, bold, italic, underline and overstrike). Examples of valid fonts are ``Helvetica 10 Bold'', ``Times -14'', ``Futura Bold Underline''. You must enclose the font family in braces if it is made of two or more words." self tclEval: '%1 configure -font %3' with: self connected with: self container with: value asTkString. self properties at: #font put: value ] foregroundColor [ "Answer the value of the foregroundColor option for the widget. Specifies the normal foreground color to use when displaying the widget." self properties at: #foreground ifPresent: [:value | ^value]. self tclEval: '%1 cget -foreground' with: self connected with: self container. ^self properties at: #foreground put: self tclResult ] foregroundColor: value [ "Set the value of the foregroundColor option for the widget. Specifies the normal foreground color to use when displaying the widget." self tclEval: '%1 configure -foreground %3' with: self connected with: self container with: value asTkString. self properties at: #foreground put: value ] label [ "Answer the value of the label option for the widget. Specifies a string to be displayed inside the widget. The way in which the string is displayed depends on the particular widget and may be determined by other options, such as anchor. For windows, this is the title of the window." self properties at: #text ifPresent: [:value | ^value]. self tclEval: '%1 cget -text' with: self connected with: self container. ^self properties at: #text put: self tclResult ] label: value [ "Set the value of the label option for the widget. Specifies a string to be displayed inside the widget. The way in which the string is displayed depends on the particular widget and may be determined by other options, such as anchor. For windows, this is the title of the window." self tclEval: '%1 configure -text %3' with: self connected with: self container with: value asTkString. self properties at: #text put: value ] anchor: value [ "Private - Set the value of the Tk anchor option for the widget." self tclEval: '%1 configure -anchor %3' with: self connected with: self container with: value asTkString. self properties at: #anchor put: value ] create [ self create: '-anchor nw -takefocus 0'. self tclEval: 'bind %1 "+%1 configure -wraplength %%w"' with: self connected ] initialize: parentWidget [ super initialize: parentWidget. parentWidget isNil ifFalse: [self backgroundColor: parentWidget backgroundColor] ] setInitialSize [ "Make the Tk placer's status, the receiver's properties and the window status (as returned by winfo) consistent. Occupy the area indicated by the widget itself, at the top left corner" self x: 0 y: 0 ] widgetType [ ^'label' ] ] BPrimitive subclass: BButton [ | callback | BButton class >> new: parent label: label [ "Answer a new BButton widget laid inside the given parent widget, showing by default the `label' String." ^(self new: parent) label: label; yourself ] backgroundColor [ "Answer the value of the backgroundColor option for the widget. Specifies the normal background color to use when displaying the widget." self properties at: #background ifPresent: [:value | ^value]. self tclEval: '%1 cget -background' with: self connected with: self container. ^self properties at: #background put: self tclResult ] backgroundColor: value [ "Set the value of the backgroundColor option for the widget. Specifies the normal background color to use when displaying the widget." self tclEval: '%1 configure -background %3' with: self connected with: self container with: value asTkString. self properties at: #background put: value ] callback [ "Answer a DirectedMessage that is sent when the receiver is clicked, or nil if none has been set up." ^callback ] callback: aReceiver message: aSymbol [ "Set up so that aReceiver is sent the aSymbol message (the name of a zero- or one-argument selector) when the receiver is clicked. If the method accepts an argument, the receiver is passed." | arguments selector numArgs | selector := aSymbol asSymbol. numArgs := selector numArgs. arguments := #(). numArgs = 1 ifTrue: [arguments := Array with: self]. callback := DirectedMessage selector: selector arguments: arguments receiver: aReceiver ] font [ "Answer the value of the font option for the widget. Specifies the font to use when drawing text inside the widget. The font can be given as either an X font name or a Blox font description string. X font names are given as many fields, each led by a minus, and each of which can be replaced by an * to indicate a default value is ok: foundry, family, weight, slant, setwidth, addstyle, pixel size, point size (the same as pixel size for historical reasons), horizontal resolution, vertical resolution, spacing, width, charset and character encoding. Blox font description strings have three fields, which must be separated by a space and of which only the first is mandatory: the font family, the font size in points (or in pixels if a negative value is supplied), and a number of styles separated by a space (valid styles are normal, bold, italic, underline and overstrike). Examples of valid fonts are ``Helvetica 10 Bold'', ``Times -14'', ``Futura Bold Underline''. You must enclose the font family in braces if it is made of two or more words." self properties at: #font ifPresent: [:value | ^value]. self tclEval: '%1 cget -font' with: self connected with: self container. ^self properties at: #font put: self tclResult ] font: value [ "Set the value of the font option for the widget. Specifies the font to use when drawing text inside the widget. The font can be given as either an X font name or a Blox font description string. X font names are given as many fields, each led by a minus, and each of which can be replaced by an * to indicate a default value is ok: foundry, family, weight, slant, setwidth, addstyle, pixel size, point size (the same as pixel size for historical reasons), horizontal resolution, vertical resolution, spacing, width, charset and character encoding. Blox font description strings have three fields, which must be separated by a space and of which only the first is mandatory: the font family, the font size in points (or in pixels if a negative value is supplied), and a number of styles separated by a space (valid styles are normal, bold, italic, underline and overstrike). Examples of valid fonts are ``Helvetica 10 Bold'', ``Times -14'', ``Futura Bold Underline''. You must enclose the font family in braces if it is made of two or more words." "self tclEval: '%1 configure -font %3' with: self connected with: self container with: (value asTkString). self properties at: #font put: value" ] foregroundColor [ "Answer the value of the foregroundColor option for the widget. Specifies the normal foreground color to use when displaying the widget." self properties at: #foreground ifPresent: [:value | ^value]. self tclEval: '%1 cget -foreground' with: self connected with: self container. ^self properties at: #foreground put: self tclResult ] foregroundColor: value [ "Set the value of the foregroundColor option for the widget. Specifies the normal foreground color to use when displaying the widget." self tclEval: '%1 configure -foreground %3' with: self connected with: self container with: value asTkString. self properties at: #foreground put: value ] invokeCallback [ "Generate a synthetic callback" self callback isNil ifFalse: [self callback send] ] label [ "Answer the value of the label option for the widget. Specifies a string to be displayed inside the widget. The way in which the string is displayed depends on the particular widget and may be determined by other options, such as anchor. For windows, this is the title of the window." ^self connected getLabel ] label: value [ "Set the value of the label option for the widget. Specifies a string to be displayed inside the widget. The way in which the string is displayed depends on the particular widget and may be determined by other options, such as anchor. For windows, this is the title of the window." self connected setLabel: value ] create [ self connected: GTK.GtkButton new. self connected connectSignal: 'clicked' to: self selector: #onClicked:data: userData: nil ] onClicked: aButton data: userData [ self invokeCallback ] setInitialSize [ "Make the Tk placer's status, the receiver's properties and the window status (as returned by winfo) consistent. Occupy the area indicated by the widget itself, at the top left corner" ] ] BPrimitive subclass: BForm [ backgroundColor [ "Answer the value of the backgroundColor option for the widget. Specifies the normal background color to use when displaying the widget." | style | style := self container getStyle. 'FIXME ok, backGroundColor isn"t trivial to get' printNl "self properties at: #background ifPresent: [ :value | ^value ]. self tclEval: '%1 cget -background' with: self connected with: self container. ^self properties at: #background put: (self tclResult )" ] backgroundColor: value [ "Set the value of the backgroundColor option for the widget. Specifies the normal background color to use when displaying the widget." | color | value printNl. 'fixme implement bg color, will need CStruct Color' printNl "color:=GTK.GdkColor new. GTK.GdkColor parse: value color: color. self container modifyBg: GTK.Gtk gtkStateNormal color: (nil)" ] defaultHeight [ "Answer the value of the defaultHeight option for the widget. Specifies the desired height for the form in pixels. If this option is less than or equal to zero then the window will not request any size at all." self properties at: #height ifPresent: [:value | ^value]. self tclEval: '%1 cget -height' with: self connected with: self container. ^self properties at: #height put: self tclResult asNumber ] defaultHeight: value [ "Set the value of the defaultHeight option for the widget. Specifies the desired height for the form in pixels. If this option is less than or equal to zero then the window will not request any size at all." self tclEval: '%1 configure -height %3' with: self connected with: self container with: value printString asTkString. self properties at: #height put: value ] defaultWidth [ "Answer the value of the defaultWidth option for the widget. Specifies the desired width for the form in pixels. If this option is less than or equal to zero then the window will not request any size at all." self properties at: #width ifPresent: [:value | ^value]. self tclEval: '%1 cget -width' with: self connected with: self container. ^self properties at: #width put: self tclResult asNumber ] defaultWidth: value [ "Set the value of the defaultWidth option for the widget. Specifies the desired width for the form in pixels. If this option is less than or equal to zero then the window will not request any size at all." self tclEval: '%1 configure -width %3' with: self connected with: self container with: value printString asTkString. self properties at: #width put: value ] create [ self connected: GTK.GtkPlacer new ] addChild: child [ (self connected) add: child container; moveRel: child container relX: 0 relY: 0. ^child ] child: child height: value [ "Set the given child's height to value. The default implementation of this method uses `rubber-sheet' geometry management as explained in the comment to BWidget's #height method. You should not use this method, which is automatically called by the child's #height: method, but you might want to override it. The child's property slots whose name ends with `Geom' are reserved for this method. This method should never fail -- if it doesn't apply to the kind of geometry management that the receiver does, just do nothing." | relative heightParent | heightParent := self height. heightParent <= 0 ifTrue: [^self]. relative := value * 32767 // heightParent. relative := relative min: 32767. relative := relative max: 0. self connected resizeRel: child container relWidth: (child properties at: #widthGeom ifAbsent: [32767]) relHeight: (child properties at: #heightGeom put: relative) ] child: child heightOffset: value [ "Adjust the given child's height by a fixed amount of value pixel. This is meaningful for the default implementation, using `rubber-sheet' geometry management as explained in the comment to BWidget's #height and #heightOffset: methods. You should not use this method, which is automatically called by the child's #heightOffset: method, but you might want to override it. if it doesn't apply to the kind of geometry management that the receiver does, just add value to the current height of the widget." self connected resize: child container width: (child properties at: #widthGeomOfs ifAbsent: [0]) height: value ] child: child inset: pixels [ ^child xOffset: self xOffset + pixels; yOffset: self yOffset + pixels; widthOffset: self widthOffset - (pixels * 2); heightOffset: self heightOffset - (pixels * 2) ] child: child stretch: aBoolean [ "This method is only used when on the path from the receiver to its toplevel there is a BContainer. It decides whether child is among the widgets that are stretched to fill the entire width of the BContainer; if this has not been set for this widget, it is propagated along the widget hierarchy." self properties at: #stretch ifAbsent: [self parent isNil ifTrue: [^self]. self parent child: self stretch: aBoolean] ] child: child width: value [ "Set the given child's width to value. The default implementation of this method uses `rubber-sheet' geometry management as explained in the comment to BWidget's #width method. You should not use this method, which is automatically called by the child's #width: method, but you might want to override it. The child's property slots whose name ends with `Geom' are reserved for this method. This method should never fail -- if it doesn't apply to the kind of geometry management that the receiver does, just do nothing." | relative widthParent | widthParent := self width. widthParent <= 0 ifTrue: [^self]. relative := value * 32767 // widthParent. relative := relative min: 32767. relative := relative max: 0. self connected resizeRel: child container relWidth: (child properties at: #widthGeom put: relative) relHeight: (child properties at: #widthGeom ifAbsent: [32767]) ] child: child widthOffset: value [ "Adjust the given child's width by a fixed amount of value pixel. This is meaningful for the default implementation, using `rubber-sheet' geometry management as explained in the comment to BWidget's #width and #widthOffset: methods. You should not use this method, which is automatically called by the child's #widthOffset: method, but you might want to override it. if it doesn't apply to the kind of geometry management that the receiver does, just add value to the current width of the widget." self connected resize: child container width: value height: (child properties at: #widthGeomOfs ifAbsent: [0]) ] child: child x: value [ "Set the given child's x to value. The default implementation of this method uses `rubber-sheet' geometry management as explained in the comment to BWidget's #x method. You should not use this method, which is automatically called by the child's #x: method, but you might want to override it. The child's property slots whose name ends with `Geom' are reserved for this method. This method should never fail -- if it doesn't apply to the kind of geometry management that the receiver does, just do nothing." | relative widthParent | widthParent := self width. widthParent <= 0 ifTrue: [^self]. relative := value * 32767 // widthParent. relative := relative min: 32767. relative := relative max: 0. self connected moveRel: child container relX: (child properties at: #xGeom put: relative) relY: (child properties at: #yGeom ifAbsent: [0]) ] child: child xOffset: value [ "Adjust the given child's x by a fixed amount of value pixel. This is meaningful for the default implementation, using `rubber-sheet' geometry management as explained in the comment to BWidget's #x and #xOffset: methods. You should not use this method, which is automatically called by the child's #xOffset: method, but you might want to override it. if it doesn't apply to the kind of geometry management that the receiver does, just add value to the current x of the widget." self connected move: child container x: value y: (child properties at: #yGeomOfs ifAbsent: [0]) ] child: child y: value [ "Set the given child's y to value. The default implementation of this method uses `rubber-sheet' geometry management as explained in the comment to BWidget's #y method. You should not use this method, which is automatically called by the child's #y: method, but you might want to override it. The child's property slots whose name ends with `Geom' are reserved for this method. This method should never fail -- if it doesn't apply to the kind of geometry management that the receiver does, just do nothing." | relative heightParent | heightParent := self height. heightParent <= 0 ifTrue: [^self]. relative := value * 32767 // heightParent. relative := relative min: 32767. relative := relative max: 0. self connected moveRel: child container relX: (child properties at: #xGeom ifAbsent: [0]) relY: (child properties at: #yGeom put: relative) ] child: child yOffset: value [ "Adjust the given child's y by a fixed amount of value pixel. This is meaningful for the default implementation, using `rubber-sheet' geometry management as explained in the comment to BWidget's #y and #yOffset: methods. You should not use this method, which is automatically called by the child's #yOffset: method, but you might want to override it. if it doesn't apply to the kind of geometry management that the receiver does, just add value to the current y of the widget." self connected move: child container x: (child properties at: #xGeomOfs ifAbsent: [0]) y: value ] heightChild: child [ "Answer the given child's height. The default implementation of this method uses `rubber-sheet' geometry management as explained in the comment to BWidget's #height method. You should not use this method, which is automatically called by the child's #height method, but you might want to override. The child's property slots whose name ends with `Geom' are reserved for this method. This method should never fail -- if it doesn't apply to the kind of geometry management that the receiver does, just return 0." ^(child properties at: #heightGeom ifAbsentPut: [32767]) * self height // 32767 ] widthChild: child [ "Answer the given child's width. The default implementation of this method uses `rubber-sheet' geometry management as explained in the comment to BWidget's #width method. You should not use this method, which is automatically called by the child's #width method, but you might want to override. The child's property slots whose name ends with `Geom' are reserved for this method. This method should never fail -- if it doesn't apply to the kind of geometry management that the receiver does, just return 0." ^(child properties at: #widthGeom ifAbsentPut: [32767]) * self width // 32767 ] xChild: child [ "Answer the given child's x. The default implementation of this method uses `rubber-sheet' geometry management as explained in the comment to BWidget's #x method. You should not use this method, which is automatically called by the child's #x method, but you might want to override. The child's property slots whose name ends with `Geom' are reserved for this method. This method should never fail -- if it doesn't apply to the kind of geometry management that the receiver does, just return 0." ^(child properties at: #xGeom ifAbsentPut: [0]) * self width // 32767 ] yChild: child [ "Answer the given child's y. The default implementation of this method uses `rubber-sheet' geometry management as explained in the comment to BWidget's #y method. You should not use this method, which is automatically called by the child's #y method, but you might want to override. The child's property slots whose name ends with `Geom' are reserved for this method. This method should never fail -- if it doesn't apply to the kind of geometry management that the receiver does, just return 0." ^(child properties at: #yGeom ifAbsentPut: [0]) * self height // 32767 ] ] BForm subclass: BContainer [ | verticalLayout | addChild: child [ "The widget identified by child has been added to the receiver. This method is public not because you can call it, but because it can be useful to override it to perform some initialization on the children just added. Answer the new child." self connected packStart: child container expand: false fill: false padding: 0. ^child ] setVerticalLayout: aBoolean [ "Answer whether the container will align the widgets vertically or horizontally. Horizontal alignment means that widgets are packed from left to right, while vertical alignment means that widgets are packed from the top to the bottom of the widget. Widgets that are set to be ``stretched'' will share all the space that is not allocated to non-stretched widgets. The layout of the widget can only be set before the first child is inserted in the widget." children isEmpty ifFalse: [^self error: 'cannot set layout after the first child is created']. verticalLayout := aBoolean ] create [ self verticalLayout ifTrue: [self connected: (GTK.GtkVBox new: false spacing: 0)] ifFalse: [self connected: (GTK.GtkHBox new: false spacing: 0)] ] verticalLayout [ "answer true if objects should be laid out vertically" verticalLayout isNil ifTrue: [verticalLayout := true]. ^verticalLayout ] initialize: parentWidget [ "This is called by #new: to initialize the widget (as the name says...). The default implementation calls all the other methods in the `customization' protocol and some private ones that take care of making the receiver's status consistent, so you should usually call it instead of doing everything by hand. This method is public not because you can call it, but because it might be useful to override it. Always answer the receiver." parent := parentWidget. properties := IdentityDictionary new. children := OrderedCollection new ] child: child height: value [ (child -> value -> (self heightChild: child)) printNl. ^child container setSizeRequest: (self widthChild: child) height: value ] child: child heightOffset: value [ ] child: child inset: value [ | stretch | stretch := child properties at: #stretchGeom ifAbsent: [false]. self connected setChildPacking: child container expand: stretch fill: stretch padding: (child properties at: #paddingGeom put: value) packType: GTK.Gtk gtkPackStart ] child: child stretch: aBoolean [ child properties at: #stretchGeom put: aBoolean. self connected setChildPacking: child container expand: aBoolean fill: aBoolean padding: (child properties at: #paddingGeom ifAbsent: [0]) packType: GTK.Gtk gtkPackStart ] child: child width: value [ ^child container setSizeRequest: value height: (self heightChild: child) ] child: child widthOffset: value [ ] child: child x: value [ ] child: child xOffset: value [ ] child: child y: value [ ] child: child yOffset: value [ ] heightChild: child [ ^child container getSizeRequest at: 2 ] widthChild: child [ ^child container getSizeRequest at: 1 ] xChild: child [ ^child xAbsolute ] yChild: child [ ^child yAbsolute ] ] BContainer subclass: BRadioGroup [ | value | value [ "Answer the index of the button that is currently selected, 1 being the first button added to the radio button group. 0 means that no button is selected" ^value ] value: anInteger [ "Force the value-th button added to the radio button group to be the selected one." value = anInteger ifTrue: [^self]. self childrenCount = 0 ifTrue: [^self]. value = 0 ifFalse: [(children at: value) connected setActive: false]. value := anInteger. anInteger = 0 ifFalse: [(children at: value) connected setActive: true] ] addChild: child [ super addChild: child. child assignedValue: self childrenCount. self childrenCount = 1 ifTrue: [self value: 1]. child connected connectSignal: 'toggled' to: self selector: #onToggle:data: userData: self childrenCount. ^child ] onToggle: widget data: userData [ value := userData. (children at: userData) invokeCallback ] group [ "answer the radio group my children are in" | child | child := children at: 1. ^child exists ifFalse: [nil] ifTrue: [child connected getGroup] ] initialize: parentWidget [ super initialize: parentWidget. value := 0 ] ] BButton subclass: BRadioButton [ | assignedValue | callback: aReceiver message: aSymbol [ "Set up so that aReceiver is sent the aSymbol message (the name of a selector accepting at most two arguments) when the receiver is clicked. If the method accepts two arguments, the receiver is passed as the first parameter. If the method accepts one or two arguments, true is passed as the last parameter for interoperability with BToggle widgets." | arguments selector numArgs | selector := aSymbol asSymbol. numArgs := selector numArgs. arguments := #(). numArgs = 1 ifTrue: [arguments := #(true)]. numArgs = 2 ifTrue: [arguments := {self. true}]. callback := DirectedMessage selector: selector arguments: arguments receiver: aReceiver ] value [ "Answer whether this widget is the selected one in its radio button group." ^self parent value = assignedValue ] value: aBoolean [ "Answer whether this widget is the selected one in its radio button group. Setting this property to false for a group's currently selected button unhighlights all the buttons in that group." aBoolean ifTrue: [self parent value: assignedValue. ^self]. "aBoolean is false - unhighlight everything if we're active" self value ifTrue: [self parent value: 0] ] assignedValue: anInteger [ assignedValue := anInteger ] create [ self connected: (GTK.GtkRadioButton newWithLabel: self parent group label: '') ] ] BButton subclass: BToggle [ | value | callback: aReceiver message: aSymbol [ "Set up so that aReceiver is sent the aSymbol message (the name of a selector accepting at most two arguments) when the receiver is clicked. If the method accepts two arguments, the receiver is passed as the first parameter. If the method accepts one or two arguments, the state of the widget (true if it is selected, false if it is not) is passed as the last parameter." | arguments selector numArgs | selector := aSymbol asSymbol. numArgs := selector numArgs. arguments := #(). numArgs = 1 ifTrue: [arguments := {nil}]. numArgs = 2 ifTrue: [arguments := {self. nil}]. callback := DirectedMessage selector: selector arguments: arguments receiver: aReceiver ] invokeCallback [ "Generate a synthetic callback." self callback isNil ifTrue: [^self]. self callback arguments size > 0 ifTrue: [self callback arguments at: self callback arguments size put: self value]. super invokeCallback ] value [ "Answer whether the button is in a selected (checked) state." self tclEval: 'return ${var' , self connected , '}'. ^self tclResult = '1' ] value: aBoolean [ "Set whether the button is in a selected (checked) state and generates a callback accordingly." aBoolean ifTrue: [self tclEval: 'set var' , self connected , ' 1'] ifFalse: [self tclEval: 'set var' , self connected , ' 0'] ] variable: value [ "Set the value of Tk's variable option for the widget." self tclEval: '%1 configure -variable %3' with: self connected with: self container with: value asTkString. self properties at: #variable put: value ] initialize: parentWidget [ | variable | super initialize: parentWidget. self tclEval: self connected , ' configure -anchor nw'. self tclEval: 'variable var' , self connected. self variable: 'var' , self connected. self backgroundColor: parentWidget backgroundColor ] widgetType [ ^'checkbutton' ] ] BPrimitive subclass: BImage [ BImage class >> downArrow [ "Answer the XPM representation of a 12x12 arrow pointing downwards." ^'/* XPM */ static char * downarrow_xpm[] = { /* width height ncolors chars_per_pixel */ "12 12 2 1", /* colors */ " c None m None s None", "o c black m black", /* pixels */ " ", " ", " ", " ", " ooooooo ", " ooooo ", " ooo ", " o ", " ", " ", " ", " "}; ' ] BImage class >> leftArrow [ "Answer the XPM representation of a 12x12 arrow pointing leftwards." ^'/* XPM */ static char * leftarrow_xpm[] = { /* width height ncolors chars_per_pixel */ "12 12 2 1", /* colors */ " c None m None s None", "o c black m black", /* pixels */ " ", " ", " o ", " oo ", " ooo ", " oooo ", " ooo ", " oo ", " o ", " ", " ", " "}; ' ] BImage class >> upArrow [ "Answer the XPM representation of a 12x12 arrow pointing upwards." ^'/* XPM */ static char * uparrow_xpm[] = { /* width height ncolors chars_per_pixel */ "12 12 2 1", /* colors */ " c None m None s None", "o c black m black", /* pixels */ " ", " ", " ", " ", " o ", " ooo ", " ooooo ", " ooooooo ", " ", " ", " ", " "}; ' ] BImage class >> rightArrow [ "Answer the XPM representation of a 12x12 arrow pointing rightwards." ^'/* XPM */ static char * rightarrow_xpm[] = { /* width height ncolors chars_per_pixel */ "12 12 2 1", /* colors */ " c None m None s None", "o c black m black", /* pixels */ " ", " ", " o ", " oo ", " ooo ", " oooo ", " ooo ", " oo ", " o ", " ", " ", " "}; ' ] BImage class >> gnu [ "Answer the XPM representation of a 48x48 GNU." ^'/* XPM */ /*****************************************************************************/ /* GNU Emacs bitmap conv. to pixmap by Przemek Klosowski (przemek@nist.gov) */ /*****************************************************************************/ static char * image_name [] = { /* width height ncolors chars_per_pixel */ "48 48 7 1", /* colors */ " s mask c none", "B c blue", "x c black", ": c SandyBrown", "+ c SaddleBrown", "o c grey", ". c white", /* pixels */ " ", " x ", " :x ", " :::x ", " ::x ", " x ::x ", " x: xxx :::x ", " x: xxx xxx:xxx x::x ", " x:: xxxx::xxx:::::xx x::x ", " x:: x:::::::xx::::::xx x::x ", " x:: xx::::::::x:::::::xx xx::x ", " x:: xx::::::::::::::::::x xx::xx ", " x::x xx:::::xxx:::::::xxx:xxx xx:::xx ", " x:::x xx:::::xx...xxxxxxxxxxxxxxx:::xx ", " x:::x xx::::::xx..xxx...xxxx...xxxxxxxx ", " x:::x x::::::xx.xxx.......x.x.......xxxx ", " x:::xx x:::x::xx.xx..........x.xx.........x ", " x::::xx::xx:::x.xx....ooooxoxoxoo.xxx.....x ", " xx::::xxxx::xx.xx.xxxx.ooooooo.xxx xxxx ", " xx::::::::xx..x.xxx..ooooooooo.xx ", " xxx:::::xxx..xx.xx.xx.xxx.ooooo.xx ", " xxx::xx...xx.xx.BBBB..xxooooooxx ", " xxxx.....xx.xxBB:BB.xxoooooooxx ", " xx.....xx...x.BBBx.xxxooooooxx ", " x....xxxx..xx...xxxooooooooooxx ", " x..xxxxxx..x.......x..ooooooooxx ", " x.x xxx.x.x.x...xxxx.oooooooooxx ", " x xxx.x.x.xx...xx..oooooooooxx ", " xx.x..x.x.xx........oooooooox ", " xxo.xx.x.x.x.x.......ooooooooox ", " xxo..xxxx..x...x.......ooooooox ", " xxoo.xx.x..xx...x.......ooo.xxx ", " xxoo..x.x.x.x.x.xx.xxxxx.o.xx+xx ", " xxoo..x.xx..xx.x.x.x+++xxxxx+++x ", " xxooo.x..xxx.x.x.x.x+++++xxx+xxx ", " xxoo.xx..x..xx.xxxx++x+++x++xxx ", " xxoo..xx.xxx.xxx.xxx++xx+x++xx ", " xxooo.xx.xx..xx.xxxx++x+++xxx ", " xxooo.xxx.xx.xxxxxxxxx++++xxx ", " xxoo...xx.xx.xxxxxx++xxxxxxx ", " xxoooo..x..xxx..xxxx+++++xx ", " xxoooo..x..xx..xxxx++++xx ", " xxxooooox.xx.xxxxxxxxxxx ", " xxxooooo..xxx xxxxx ", " xxxxooooxxxx ", " xxxoooxxx ", " xxxxx ", " " };' ] BImage class >> exclaim [ "Answer the XPM representation of a 32x32 exclamation mark icon." ^'/* XPM */ static char * exclaim_xpm[] = { /* width height ncolors chars_per_pixel */ "32 32 6 1", /* colors */ " c None m None s None", ". c yellow m white", "X c black m black", "x c gray50 m black", "o c gray m white", "b c yellow4 m black", /* pixels */ " bbb ", " b..oX ", " b....oXx ", " b.....Xxx ", " b......oXxx ", " b.......Xxx ", " b........oXxx ", " b.........Xxx ", " b..........oXxx ", " b...oXXXo...Xxx ", " b....XXXXX...oXxx ", " b....XXXXX....Xxx ", " b.....XXXXX....oXxx ", " b.....XXXXX.....Xxx ", " b......XXXXX.....oXxx ", " b......bXXXb......Xxx ", " b.......oXXXo......oXxx ", " b........XXX........Xxx ", " b.........bXb........oXxx ", " b.........oXo.........Xxx ", " b...........X..........oXxx ", " b.......................Xxx ", " b...........oXXo.........oXxx ", " b...........XXXX..........Xxx ", "b............XXXX..........oXxx ", "b............oXXo...........Xxx ", "b...........................Xxxx", "b..........................oXxxx", " b........................oXxxxx", " bXXXXXXXXXXXXXXXXXXXXXXXXxxxxx", " xxxxxxxxxxxxxxxxxxxxxxxxxxx ", " xxxxxxxxxxxxxxxxxxxxxxxxx "}; ' ] BImage class >> info [ "Answer the XPM representation of a 32x32 `information' icon." ^'/* XPM */ static char * info_xpm[] = { /* width height ncolors chars_per_pixel */ "32 32 6 1", /* colors */ " c None m None s None", ". c white m white", "X c black m black", "x c gray50 m black", "o c gray m white", "b c blue m black", /* pixels */ " xxxxxxxx ", " xxxo......oxxx ", " xxo............oxx ", " xo................ox ", " x.......obbbbo.......X ", " x........bbbbbb........X ", " x.........bbbbbb.........X ", " xo.........obbbbo.........oX ", " x..........................Xx ", "xo..........................oXx ", "x..........bbbbbbb...........Xx ", "x............bbbbb...........Xxx", "x............bbbbb...........Xxx", "x............bbbbb...........Xxx", "x............bbbbb...........Xxx", "xo...........bbbbb..........oXxx", " x...........bbbbb..........Xxxx", " xo..........bbbbb.........oXxxx", " x........bbbbbbbbb.......Xxxx ", " X......................Xxxxx ", " X....................Xxxxx ", " Xo................oXxxxx ", " XXo............oXXxxxx ", " xXXXo......oXXXxxxxx ", " xxxXXXo...Xxxxxxxx ", " xxxxX...Xxxxxx ", " xX...Xxx ", " X..Xxx ", " X.Xxx ", " XXxx ", " xxx ", " xx "}; ' ] BImage class >> question [ "Answer the XPM representation of a 32x32 question mark icon." ^'/* XPM */ static char * question_xpm[] = { /* width height ncolors chars_per_pixel */ "32 32 6 1", /* colors */ " c None m None s None", ". c white m white", "X c black m black", "x c gray50 m black", "o c gray m white", "b c blue m black", /* pixels */ " xxxxxxxx ", " xxxo......oxxx ", " xxo............oxx ", " xo................ox ", " x....................X ", " x.......obbbbbbo.......X ", " x.......obo..bbbbo.......X ", " xo.......bb....bbbb.......oX ", " x........bbbb..bbbb........Xx ", "xo........bbbb.obbbb........oXx ", "x.........obbo.bbbb..........Xx ", "x.............obbb...........Xxx", "x.............bbb............Xxx", "x.............bbo............Xxx", "x.............bb.............Xxx", "xo..........................oXxx", " x...........obbo...........Xxxx", " xo..........bbbb..........oXxxx", " x..........bbbb..........Xxxx ", " X.........obbo.........Xxxxx ", " X....................Xxxxx ", " Xo................oXxxxx ", " XXo............oXXxxxx ", " xXXXo......oXXXxxxxx ", " xxxXXXo...Xxxxxxxx ", " xxxxX...Xxxxxx ", " xX...Xxx ", " X..Xxx ", " X.Xxx ", " XXxx ", " xxx ", " xx "}; ' ] BImage class >> stop [ "Answer the XPM representation of a 32x32 `critical stop' icon." ^'/* XPM */ static char * stop_xpm[] = { /* width height ncolors chars_per_pixel */ "32 32 5 1", /* colors */ " c None m None s None", ". c red m white", "o c DarkRed m black", "X c white m black", "x c gray50 m black", /* pixels */ " oooooooo ", " ooo........ooo ", " o..............o ", " oo................oo ", " o....................o ", " o......................o ", " o......................ox ", " o......X..........X......ox ", " o......XXX........XXX......o ", " o.....XXXXX......XXXXX.....ox ", " o......XXXXX....XXXXX......oxx ", "o........XXXXX..XXXXX........ox ", "o.........XXXXXXXXXX.........ox ", "o..........XXXXXXXX..........oxx", "o...........XXXXXX...........oxx", "o...........XXXXXX...........oxx", "o..........XXXXXXXX..........oxx", "o.........XXXXXXXXXX.........oxx", "o........XXXXX..XXXXX........oxx", " o......XXXXX....XXXXX......oxxx", " o.....XXXXX......XXXXX.....oxxx", " o......XXX........XXX......oxx ", " o......X..........X......oxxx ", " o......................oxxxx ", " o......................oxxx ", " o....................oxxx ", " oo................ooxxxx ", " xo..............oxxxxx ", " xooo........oooxxxxx ", " xxooooooooxxxxxx ", " xxxxxxxxxxxxxx ", " xxxxxxxx "}; ' ] BImage class >> new: parent data: aString [ "Answer a new BImage widget laid inside the given parent widget, loading data from the given string (Base-64 encoded GIF, XPM, PPM are supported)." ^(self new: parent) data: aString; yourself ] BImage class >> new: parent image: aFileStream [ "Answer a new BImage widget laid inside the given parent widget, loading data from the given file (GIF, XPM, PPM are supported)." ^(self new: parent) image: aFileStream; yourself ] BImage class >> new: parent size: aPoint [ "Answer a new BImage widget laid inside the given parent widget, showing by default a transparent image of aPoint size." ^(self new: parent) displayWidth: aPoint x; displayHeight: aPoint y; blank; yourself ] BImage class >> directory [ "Answer the Base-64 GIF representation of a `directory folder' icon." ^'R0lGODdhEAAQAPIAAAAAAHh4eLi4uPj4+P///wAAAAAAAAAAACwAAAAAEAAQAAADPkixzPOD yADrWE8qC8WN0+BZAmBq1GMOqwigXFXCrGk/cxjjr27fLtout6n9eMIYMTXsFZsogXRKJf6u P0kCADv/' ] BImage class >> file [ "Answer the Base-64 GIF representation of a `file' icon." ^'R0lGODdhEAAQAPIAAAAAAHh4eLi4uPj4APj4+P///wAAAAAAACwAAAAAEAAQAAADPVi63P4w LkKCtTTnUsXwQqBtAfh910UU4ugGAEucpgnLNY3Gop7folwNOBOeiEYQ0acDpp6pGAFArVqt hQQAO///' ] backgroundColor [ "Answer the value of the backgroundColor option for the widget. Specifies the normal background color to use when displaying the widget." self properties at: #background ifPresent: [:value | ^value]. self tclEval: '%1 cget -background' with: self connected with: self container. ^self properties at: #background put: self tclResult ] backgroundColor: value [ "Set the value of the backgroundColor option for the widget. Specifies the normal background color to use when displaying the widget." self tclEval: '%1 configure -background %3' with: self connected with: self container with: value asTkString. self properties at: #background put: value ] displayHeight [ "Answer the value of the displayHeight option for the widget. Specifies the height of the image in pixels. This is not the height of the widget, but specifies the area of the widget that will be taken by the image." self properties at: #displayHeight ifPresent: [:value | ^value]. self tclEval: 'img%1 cget -width' with: self connected with: self container. ^self properties at: #displayHeight put: self tclResult asNumber ] displayHeight: value [ "Set the value of the displayHeight option for the widget. Specifies the height of the image in pixels. This is not the height of the widget, but specifies the area of the widget that will be taken by the image." self tclEval: 'img%1 configure -width %3' with: self connected with: self container with: value asFloat printString asTkString. self properties at: #displayHeight put: value ] displayWidth [ "Answer the value of the displayWidth option for the widget. Specifies the width of the image in pixels. This is not the width of the widget, but specifies the area of the widget that will be taken by the image." self properties at: #displayWidth ifPresent: [:value | ^value]. self tclEval: 'img%1 cget -width' with: self connected with: self container. ^self properties at: #displayWidth put: self tclResult asNumber ] displayWidth: value [ "Set the value of the displayWidth option for the widget. Specifies the width of the image in pixels. This is not the width of the widget, but specifies the area of the widget that will be taken by the image." self tclEval: 'img%1 configure -width %3' with: self connected with: self container with: value asFloat printString asTkString. self properties at: #displayWidth put: value ] foregroundColor [ "Answer the value of the foregroundColor option for the widget. Specifies the normal foreground color to use when displaying the widget." self properties at: #foreground ifPresent: [:value | ^value]. self tclEval: '%1 cget -foreground' with: self connected with: self container. ^self properties at: #foreground put: self tclResult ] foregroundColor: value [ "Set the value of the foregroundColor option for the widget. Specifies the normal foreground color to use when displaying the widget." self tclEval: '%1 configure -foreground %3' with: self connected with: self container with: value asTkString. self properties at: #foreground put: value ] gamma [ "Answer the value of the gamma option for the widget. Specifies that the colors allocated for displaying the image widget should be corrected for a non-linear display with the specified gamma exponent value. (The intensity produced by most CRT displays is a power function of the input value, to a good approximation; gamma is the exponent and is typically around 2). The value specified must be greater than zero. The default value is one (no correction). In general, values greater than one will make the image lighter, and values less than one will make it darker." self properties at: #gamma ifPresent: [:value | ^value]. self tclEval: 'img%1 cget -gamma' with: self connected with: self container. ^self properties at: #gamma put: self tclResult asNumber ] gamma: value [ "Set the value of the gamma option for the widget. Specifies that the colors allocated for displaying the image widget should be corrected for a non-linear display with the specified gamma exponent value. (The intensity produced by most CRT displays is a power function of the input value, to a good approximation; gamma is the exponent and is typically around 2). The value specified must be greater than zero. The default value is one (no correction). In general, values greater than one will make the image lighter, and values less than one will make it darker." self tclEval: 'img%1 configure -gamma %3' with: self connected with: self container with: value asFloat printString asTkString. self properties at: #gamma put: value ] blank [ "Blank the corresponding image" self tclEval: 'img' , self connected , ' blank' ] data: aString [ "Set the image to be drawn to aString, which can be a GIF in Base-64 representation or an X pixelmap." self tclEval: 'img' , self connected , ' configure -data ' , aString asTkImageString ] dither [ "Recalculate the dithered image in the window where the image is displayed. The dithering algorithm used in displaying images propagates quantization errors from one pixel to its neighbors. If the image data is supplied in pieces, the dithered image may not be exactly correct. Normally the difference is not noticeable, but if it is a problem, this command can be used to fix it." self tclEval: 'img' , self connected , ' redither' ] fillFrom: origin extent: extent color: color [ "Fill a rectangle with the given origin and extent, using the given color." self fillFrom: origin to: origin + extent color: color ] fillFrom: origin to: corner color: color [ "Fill a rectangle between the given corners, using the given color." self tclEval: 'img%1 put { %2 } -to %3 %4' with: self connected with: color with: origin x printString , ' ' , origin y printString with: corner x printString , ' ' , corner y printString ] fillRectangle: rectangle color: color [ "Fill a rectangle having the given bounding box, using the given color." self fillFrom: rectangle origin to: rectangle corner color: color ] image: aFileStream [ "Read a GIF or XPM image from aFileStream. The whole contents of the file are read, not only from the file position." self tclEval: 'img' , self connected , ' read ' , aFileStream name asTkString ] imageHeight [ "Specifies the height of the image, in pixels. This option is useful primarily in situations where you wish to build up the contents of the image piece by piece. A value of zero (the default) allows the image to expand or shrink vertically to fit the data stored in it." self tclEval: 'image height img' , self connected. ^self tclResult asInteger ] imageWidth [ "Specifies the width of the image, in pixels. This option is useful primarily in situations where you wish to build up the contents of the image piece by piece. A value of zero (the default) allows the image to expand or shrink horizontally to fit the data stored in it." self tclEval: 'image width img' , self connected. ^self tclResult asInteger ] lineFrom: origin extent: extent color: color [ "Draw a line with the given origin and extent, using the given color." self lineFrom: origin to: origin + extent color: color ] lineFrom: origin to: corner color: color [ self notYetImplemented ] lineFrom: origin toX: endX color: color [ "Draw an horizontal line between the given corners, using the given color." self tclEval: 'img%1 put { %2 } -to %3 %4' with: self connected with: color with: origin x printString , ' ' , origin y printString with: endX printString , ' ' , origin y printString ] lineInside: rectangle color: color [ "Draw a line having the given bounding box, using the given color." self lineFrom: rectangle origin to: rectangle corner color: color ] lineFrom: origin toY: endY color: color [ "Draw a vertical line between the given corners, using the given color." self tclEval: 'img%1 put { %2 } -to %3 %4' with: self connected with: color with: origin x printString , ' ' , origin y printString with: origin x printString , ' ' , endY printString ] destroyed [ "Private - The receiver has been destroyed, clear the corresponding Tcl image to avoid memory leaks." 'TODO' printNl. super destroyed ] create [ self tclEval: 'image create photo img' , self connected. self create: '-anchor nw -image img' , self connected ] setInitialSize [ "Make the Tk placer's status, the receiver's properties and the window status (as returned by winfo) consistent. Occupy the area indicated by the widget itself, at the top left corner" self x: 0 y: 0 ] widgetType [ ^'label' ] ] BViewport subclass: BList [ | labels items callback gtkmodel connected gtkcolumn | add: anObject afterIndex: index [ "Add an element with the given value after another element whose index is contained in the index parameter. The label displayed in the widget is anObject's displayString. Answer anObject." ^self add: nil element: anObject afterIndex: index ] add: aString element: anObject afterIndex: index [ "Add an element with the aString label after another element whose index is contained in the index parameter. This method allows the client to decide autonomously the label that the widget will display. If anObject is nil, then string is used as the element as well. If aString is nil, then the element's displayString is used as the label. Answer anObject or, if it is nil, aString." | elem label iter | label := aString isNil ifTrue: [anObject displayString] ifFalse: [aString]. elem := anObject isNil ifTrue: [aString] ifFalse: [anObject]. labels isNil ifTrue: [index > 0 ifTrue: [^SystemExceptions.IndexOutOfRange signalOn: self withIndex: index]. labels := OrderedCollection with: label. items := OrderedCollection with: elem] ifFalse: [labels add: label afterIndex: index. items add: elem afterIndex: index]. iter := self gtkmodel insert: index. self gtkmodel setOop: iter column: 0 value: label. ^elem ] addLast: anObject [ "Add an element with the given value at the end of the listbox. The label displayed in the widget is anObject's displayString. Answer anObject." ^self add: nil element: anObject afterIndex: items size ] addLast: aString element: anObject [ "Add an element with the given value at the end of the listbox. This method allows the client to decide autonomously the label that the widget will display. If anObject is nil, then string is used as the element as well. If aString is nil, then the element's displayString is used as the label. Answer anObject or, if it is nil, aString." ^self add: aString element: anObject afterIndex: items size ] associationAt: anIndex [ "Answer an association whose key is the item at the given position in the listbox and whose value is the label used to display that item." ^(items at: anIndex) -> (labels at: anIndex) ] at: anIndex [ "Answer the element displayed at the given position in the list box." ^items at: anIndex ] backgroundColor [ "Answer the value of the backgroundColor option for the widget. Specifies the normal background color to use when displaying the widget." self properties at: #background ifPresent: [:value | ^value]. self tclEval: '%1 cget -background' with: self connected with: self container. ^self properties at: #background put: self tclResult ] backgroundColor: value [ "Set the value of the backgroundColor option for the widget. Specifies the normal background color to use when displaying the widget." self tclEval: '%1 configure -background %3' with: self connected with: self container with: value asTkString. self properties at: #background put: value ] contents: elementList [ "Set the elements displayed in the listbox, and set the labels to be their displayStrings." | newLabels | newLabels := elementList collect: [:each | each displayString]. ^self contents: newLabels elements: elementList ] contents: stringCollection elements: elementList [ "Set the elements displayed in the listbox to be those in elementList, and set the labels to be the corresponding elements in stringCollection. The two collections must have the same size." | stream iter | (elementList notNil and: [elementList size ~= stringCollection size]) ifTrue: [^self error: 'label collection must have the same size as element collection']. labels := stringCollection isNil ifTrue: [elementList asOrderedCollection collect: [:each | each displayString]] ifFalse: [stringCollection asOrderedCollection]. items := elementList isNil ifTrue: [labels copy] ifFalse: [elementList asOrderedCollection]. self gtkmodel clear. iter := GTK.GtkTreeIter new. stringCollection do: [:each | self gtkmodel append: iter. self gtkmodel setOop: iter column: 0 value: each] ] do: aBlock [ "Iterate over each element of the listbox and pass it to aBlock." items do: aBlock ] elements [ "Answer the collection of objects that represent the elements displayed by the list box." ^items copy ] elements: elementList [ "Set the elements displayed in the listbox, and set the labels to be their displayStrings." | newLabels | newLabels := elementList collect: [:each | each displayString]. ^self contents: newLabels elements: elementList ] font [ "Answer the value of the font option for the widget. Specifies the font to use when drawing text inside the widget. The font can be given as either an X font name or a Blox font description string. X font names are given as many fields, each led by a minus, and each of which can be replaced by an * to indicate a default value is ok: foundry, family, weight, slant, setwidth, addstyle, pixel size, point size (the same as pixel size for historical reasons), horizontal resolution, vertical resolution, spacing, width, charset and character encoding. Blox font description strings have three fields, which must be separated by a space and of which only the first is mandatory: the font family, the font size in points (or in pixels if a negative value is supplied), and a number of styles separated by a space (valid styles are normal, bold, italic, underline and overstrike). Examples of valid fonts are ``Helvetica 10 Bold'', ``Times -14'', ``Futura Bold Underline''. You must enclose the font family in braces if it is made of two or more words." self properties at: #font ifPresent: [:value | ^value]. self tclEval: '%1 cget -font' with: self connected with: self container. ^self properties at: #font put: self tclResult ] font: value [ "Set the value of the font option for the widget. Specifies the font to use when drawing text inside the widget. The font can be given as either an X font name or a Blox font description string. X font names are given as many fields, each led by a minus, and each of which can be replaced by an * to indicate a default value is ok: foundry, family, weight, slant, setwidth, addstyle, pixel size, point size (the same as pixel size for historical reasons), horizontal resolution, vertical resolution, spacing, width, charset and character encoding. Blox font description strings have three fields, which must be separated by a space and of which only the first is mandatory: the font family, the font size in points (or in pixels if a negative value is supplied), and a number of styles separated by a space (valid styles are normal, bold, italic, underline and overstrike). Examples of valid fonts are ``Helvetica 10 Bold'', ``Times -14'', ``Futura Bold Underline''. You must enclose the font family in braces if it is made of two or more words." self tclEval: '%1 configure -font %3' with: self connected with: self container with: value asTkString. self properties at: #font put: value ] foregroundColor [ "Answer the value of the foregroundColor option for the widget. Specifies the normal foreground color to use when displaying the widget." self properties at: #foreground ifPresent: [:value | ^value]. self tclEval: '%1 cget -foreground' with: self connected with: self container. ^self properties at: #foreground put: self tclResult ] foregroundColor: value [ "Set the value of the foregroundColor option for the widget. Specifies the normal foreground color to use when displaying the widget." self tclEval: '%1 configure -foreground %3' with: self connected with: self container with: value asTkString. self properties at: #foreground put: value ] highlightBackground [ "Answer the value of the highlightBackground option for the widget. Specifies the background color to use when displaying selected items in the widget." self properties at: #selectbackground ifPresent: [:value | ^value]. self tclEval: '%1 cget -selectbackground' with: self connected with: self container. ^self properties at: #selectbackground put: self tclResult ] highlightBackground: value [ "Set the value of the highlightBackground option for the widget. Specifies the background color to use when displaying selected items in the widget." self tclEval: '%1 configure -selectbackground %3' with: self connected with: self container with: value asTkString. self properties at: #selectbackground put: value ] highlightForeground [ "Answer the value of the highlightForeground option for the widget. Specifies the foreground color to use when displaying selected items in the widget." self properties at: #selectforeground ifPresent: [:value | ^value]. self tclEval: '%1 cget -selectforeground' with: self connected with: self container. ^self properties at: #selectforeground put: self tclResult ] highlightForeground: value [ "Set the value of the highlightForeground option for the widget. Specifies the foreground color to use when displaying selected items in the widget." self tclEval: '%1 configure -selectforeground %3' with: self connected with: self container with: value asTkString. self properties at: #selectforeground put: value ] index [ "Answer the value of the index option for the widget. Indicates the element that has the location cursor. This item will be displayed in the highlightForeground color, and with the corresponding background color." ^self properties at: #index ifAbsentPut: [| iter | (iter := self connected getSelection getSelected) isNil ifTrue: [nil] ifFalse: [(self gtkmodel getStringFromIter: iter) asInteger]] ] indexAt: point [ "Answer the index of the element that covers the point in the listbox window specified by x and y (in pixel coordinates). If no element covers that point, then the closest element to that point is used." | pPath ok path index | pPath := GTK.GtkTreePath type ptrType gcNew. ok := self getPathAtPos: point x y: point y path: pPath column: nil cellX: nil cellY: nil. path := pPath value. index := ok ifTrue: [path getIndices value] ifFalse: [self elements size]. path free. ^index ] isSelected: index [ "Answer whether the element indicated by index is currently selected." | selected path | path := self pathAt: index. selected := self connected getSelection pathIsSelected: path. path free. ^selected ] labelAt: anIndex [ "Answer the label displayed at the given position in the list box." ^labels at: anIndex ] labels [ "Answer the labels displayed by the list box." ^labels copy ] labelsDo: aBlock [ "Iterate over each listbox element's label and pass it to aBlock." labels do: aBlock ] mode [ "Answer the value of the mode option for the widget. Specifies one of several styles for manipulating the selection. The value of the option may be either single, browse, multiple, or extended. If the selection mode is single or browse, at most one element can be selected in the listbox at once. Clicking button 1 on an unselected element selects it and deselects any other selected item, while clicking on a selected element has no effect. In browse mode it is also possible to drag the selection with button 1. That is, moving the mouse while button 1 is pressed keeps the item under the cursor selected. If the selection mode is multiple or extended, any number of elements may be selected at once, including discontiguous ranges. In multiple mode, clicking button 1 on an element toggles its selection state without affecting any other elements. In extended mode, pressing button 1 on an element selects it, deselects everything else, and sets the anchor to the element under the mouse; dragging the mouse with button 1 down extends the selection to include all the elements between the anchor and the element under the mouse, inclusive. In extended mode, the selected range can be adjusted by pressing button 1 with the Shift key down: this modifies the selection to consist of the elements between the anchor and the element under the mouse, inclusive. The un-anchored end of this new selection can also be dragged with the button down. Also in extended mode, pressing button 1 with the Control key down starts a toggle operation: the anchor is set to the element under the mouse, and its selection state is reversed. The selection state of other elements is not changed. If the mouse is dragged with button 1 down, then the selection state of all elements between the anchor and the element under the mouse is set to match that of the anchor element; the selection state of all other elements remains what it was before the toggle operation began. Most people will probably want to use browse mode for single selections and extended mode for multiple selections; the other modes appear to be useful only in special situations." | mode | ^self properties at: #selectmode ifAbsentPut: [mode := self connected getSelection getMode. mode = GTK.Gtk gtkSelectionSingle ifTrue: [#single] ifFalse: [mode = GTK.Gtk gtkSelectionBrowse ifTrue: [#browse] ifFalse: [mode = GTK.Gtk gtkSelectionExtended ifTrue: [#extended]]]] ] mode: value [ "Set the value of the mode option for the widget. Specifies one of several styles for manipulating the selection. The value of the option may be either single, browse, multiple, or extended. If the selection mode is single or browse, at most one element can be selected in the listbox at once. Clicking button 1 on an unselected element selects it and deselects any other selected item, while clicking on a selected element has no effect. In browse mode it is also possible to drag the selection with button 1. That is, moving the mouse while button 1 is pressed keeps the item under the cursor selected. If the selection mode is multiple or extended, any number of elements may be selected at once, including discontiguous ranges. In multiple mode, clicking button 1 on an element toggles its selection state without affecting any other elements. In extended mode, pressing button 1 on an element selects it, deselects everything else, and sets the anchor to the element under the mouse; dragging the mouse with button 1 down extends the selection to include all the elements between the anchor and the element under the mouse, inclusive. In extended mode, the selected range can be adjusted by pressing button 1 with the Shift key down: this modifies the selection to consist of the elements between the anchor and the element under the mouse, inclusive. The un-anchored end of this new selection can also be dragged with the button down. Also in extended mode, pressing button 1 with the Control key down starts a toggle operation: the anchor is set to the element under the mouse, and its selection state is reversed. The selection state of other elements is not changed. If the mouse is dragged with button 1 down, then the selection state of all elements between the anchor and the element under the mouse is set to match that of the anchor element; the selection state of all other elements remains what it was before the toggle operation began. Most people will probably want to use browse mode for single selections and extended mode for multiple selections; the other modes appear to be useful only in special situations." | mode | value = #single ifTrue: [mode := GTK.Gtk gtkSelectionSingle] ifFalse: [value = #browse ifTrue: [mode := GTK.Gtk gtkSelectionBrowse] ifFalse: [value = #multiple ifTrue: [mode := GTK.Gtk gtkSelectionExtended] ifFalse: [value = #extended ifTrue: [mode := GTK.Gtk gtkSelectionExtended] ifFalse: [^self error: 'invalid value for BList mode']]]]. self connected getSelection setMode: mode. self properties at: #selectmode put: value ] numberOfStrings [ "Answer the number of items in the list box" ^labels size ] removeAtIndex: index [ "Remove the item at the given index in the list box, answering the object associated to the element (i.e. the value that #at: would have returned for the given index)" | result | labels removeAtIndex: index. result := items removeAtIndex: index. self gtkmodel remove: (self iterAt: index). ^result ] label [ "assign a new label to the list" ^self gtkcolumn getTitle ] label: aString [ "assign a new label to the list" self gtkcolumn setTitle: aString ] size [ "Answer the number of items in the list box" ^labels size ] itemSelected: receiver at: index [ stdout nextPutAll: 'List item '; print: index; nextPutAll: ' selected!'; nl. stdout nextPutAll: 'Contents: '; nextPutAll: (items at: index); nl ] gtkcolumn [ "answer the gtk column for the list" gtkcolumn isNil ifTrue: [self createWidget]. ^gtkcolumn ] gtkmodel [ "answer the gtk list model" gtkmodel isNil ifTrue: [self createWidget]. ^gtkmodel ] onChanged: selection data: userData [ | iter | (iter := selection getSelected) isNil ifFalse: [self invokeCallback: (self gtkmodel getStringFromIter: iter)] ] pathAt: anIndex [ ^GTK.GtkTreePath newFromIndices: anIndex - 1 varargs: #() ] iterAt: anIndex [ ^self gtkmodel iterNthChild: nil n: anIndex - 1 ] create [ | select renderer | renderer := GTK.GtkCellRendererText new. 'phwoar... should not need the explicit calls, but something is bust in varargs passing' printNl. gtkcolumn := GTK.GtkTreeViewColumn new. gtkcolumn setTitle: 'List'. gtkcolumn packStart: renderer expand: true. gtkcolumn addAttribute: renderer attribute: 'text' column: 0. "gtkcolumn := GTK.GtkTreeViewColumn newWithAttributes: 'List' cell: renderer varargs: {'text'. 0. nil}." gtkmodel := GTK.GtkListStore new: 1 varargs: {GTK.GValue gTypeString}. self connected: (GTK.GtkTreeView newWithModel: self gtkmodel). (self connected) appendColumn: self gtkcolumn; setSearchColumn: 0. select := self connected getSelection. select setMode: GTK.Gtk gtkSelectionSingle. select connectSignal: 'changed' to: self selector: #onChanged:data: userData: nil ] show [ super show. self container setShadowType: GTK.Gtk gtkShadowIn ] needsViewport [ ^false ] initialize: parentWidget [ super initialize: parentWidget. self properties at: #index put: nil. labels := OrderedCollection new ] invokeCallback: indexString [ | index | items isNil ifTrue: [^self]. index := indexString asInteger. self properties at: #index put: index + 1. self invokeCallback ] callback [ "Answer a DirectedMessage that is sent when the active item in the receiver changes, or nil if none has been set up." ^callback ] callback: aReceiver message: aSymbol [ "Set up so that aReceiver is sent the aSymbol message (the name of a selector with at most two arguemtnts) when the active item in the receiver changegs. If the method accepts two arguments, the receiver is passed as the first parameter. If the method accepts one or two arguments, the selected index is passed as the last parameter." | arguments selector numArgs | selector := aSymbol asSymbol. numArgs := selector numArgs. arguments := #(). numArgs = 1 ifTrue: [arguments := {nil}]. numArgs = 2 ifTrue: [arguments := {self. nil}]. callback := DirectedMessage selector: selector arguments: arguments receiver: aReceiver ] highlight: index [ "Highlight the item at the given position in the listbox." index = self index ifTrue: [^self]. (self mode = #single or: [self mode = #browse]) ifTrue: [self unhighlight]. self select: index ] invokeCallback [ "Generate a synthetic callback." self callback notNil ifTrue: [self callback arguments isEmpty ifFalse: [self callback arguments at: self callback arguments size put: (self properties at: #index)]. self callback send] ] select: index [ "Highlight the item at the given position in the listbox, without unhighlighting other items. This is meant for multiple- or extended-mode listboxes, but can be used with other selection mode in particular cases." self properties at: #index put: index. self connected getSelection selectIter: (self iterAt: index) ] show: index [ "Ensure that the item at the given position in the listbox is visible." | path | path := self pathAt: index. self connected scrollToCell: path column: self gtkcolumn useAlign: false rowAlign: 0.0e colAlign: 0.0e. path free ] unhighlight [ "Unhighlight all the items in the listbox." self connected getSelection unselectAll ] unselect: index [ "Unhighlight the item at the given position in the listbox, without affecting the state of the other items." self connected getSelection unselectIter: (self iterAt: index) ] ] BForm subclass: BWindow [ | isMapped callback x y width height container uiBox uiManager | '> TopLevel := nil. BWindow class >> initializeOnStartup [ TopLevel := OrderedCollection new ] BWindow class >> new [ "Answer a new top-level window." ^TopLevel add: (super new: nil) ] BWindow class >> new: label [ "Answer a new top-level window with `label' as its title bar caption." ^self new label: label ] BWindow class >> popup: initializationBlock [ self shouldNotImplement ] callback [ "Answer a DirectedMessage that is sent to verify whether the receiver must be destroyed when the user asks to unmap it." ^callback ] callback: aReceiver message: aSymbol [ "Set up so that aReceiver is sent the aSymbol message (the name of a zero- or one-argument selector) when the user asks to unmap the receiver. If the method accepts an argument, the receiver is passed. If the method returns true, the window and its children are destroyed (which is the default action, taken if no callback is set up). If the method returns false, the window is left in place." | arguments selector numArgs | selector := aSymbol asSymbol. numArgs := selector numArgs. arguments := #(). numArgs = 1 ifTrue: [arguments := Array with: self]. callback := DirectedMessage selector: selector arguments: arguments receiver: aReceiver ] invokeCallback [ "Generate a synthetic callback, destroying the window if no callback was set up or if the callback method answers true." | result | result := self callback isNil or: [self callback send]. result ifTrue: [self destroy. isMapped := false]. ^result ] label [ "Answer the value of the label option for the widget. Specifies a string to be displayed inside the widget. The way in which the string is displayed depends on the particular widget and may be determined by other options, such as anchor. For windows, this is the title of the window." ^self container getTitle ] label: value [ "Set the value of the label option for the widget. Specifies a string to be displayed inside the widget. The way in which the string is displayed depends on the particular widget and may be determined by other options, such as anchor. For windows, this is the title of the window." self container setTitle: value ] menu: aBMenuBar [ "Set the value of the menu option for the widget. Specifies a menu widget to be used as a menubar." self uiBox packStart: aBMenuBar connected expand: false fill: false padding: 0. self properties at: #menu put: aBMenuBar ] resizable [ "Answer the value of the resizable option for the widget. Answer whether the user can be resize the window or not. If resizing is disabled, then the window's size will be the size from the most recent interactive resize or geometry-setting method. If there has been no such operation then the window's natural size will be used." ^self container getResizable ] resizable: value [ "Set the value of the resizable option for the widget. Answer whether the user can be resize the window or not. If resizing is disabled, then the window's size will be the size from the most recent interactive resize or geometry-setting method. If there has been no such operation then the window's natural size will be used." ^self container setResizable: value ] uiBox [ "answer the top level container for this window" ^uiBox ] uiManager [ uiManager isNil ifTrue: [uiManager := GTK.GtkUIManager new]. ^uiManager ] cacheWindowSize [ "save the window position from gtk" | px py | px := CIntType gcNew. py := CIntType gcNew. self container getPosition: px rootY: py. x := px value. y := py value. self isMapped ifTrue: [self container getSize: px height: py] ifFalse: [self container getDefaultSize: px height: py]. width := px value. height := py value. self isMapped ifTrue: [self container setDefaultSize: width height: height] ] container [ container isNil ifTrue: [self error: 'GTK object not created yet']. ^container ] container: aWidget [ container := aWidget ] initialize: parentWidget [ super initialize: nil. self isMapped: false. self createWidget ] create [ self container: (GTK.GtkWindow new: GTK.Gtk gtkWindowToplevel). self container connectSignal: 'delete-event' to: self selector: #onDelete:data: userData: nil. self container connectSignal: 'configure-event' to: self selector: #onConfigure:data: userData: nil. uiBox := GTK.GtkVBox new: false spacing: 0. self container add: uiBox. "Create the GtkPlacer" super create. uiBox packEnd: self connected expand: true fill: true padding: 0 ] show [ "Do not show the GtkWindow until it is mapped!" super show. uiBox show ] onConfigure: object data: data [ self cacheWindowSize ] onDelete: object data: data [ ^self callback notNil and: [self callback send not] ] destroyed [ "Private - The receiver has been destroyed, remove it from the list of toplevel windows to avoid memory leaks." super destroyed. TopLevel remove: self ifAbsent: []. (TopLevel isEmpty and: [DoDispatchEvents = 1]) ifTrue: [Blox terminateMainLoop] ] isMapped: aBoolean [ isMapped := aBoolean ] resetGeometry: xPos y: yPos width: xSize height: ySize [ (x = xPos and: [y = yPos and: [width = xSize and: [height = ySize]]]) ifTrue: [^self]. self isMapped ifFalse: [self container setDefaultSize: xSize height: ySize] ifTrue: [self container resize: xSize height: ySize]. x := xPos. y := yPos. width := xSize. height := ySize "mapped ifTrue: [ self map ]." ] resized [ self isMapped ifFalse: [^self]. x := y := width := height := nil ] setInitialSize [ self x: 0 y: 0 width: 300 height: 300 ] center [ "Center the window in the screen" | screenSize | screenSize := Blox screenSize. self x: screenSize x // 2 - (self width // 2) y: screenSize y // 2 - (self height // 2) ] centerIn: view [ "Center the window in the given widget" self x: view x + (view width // 2) - (self parent width // 2) y: view x + (view height // 2) - (self parent height // 2) ] height [ "Answer the height of the window, as deduced from the geometry that the window manager imposed on the window." height isNil ifTrue: [self cacheWindowSize]. ^height ] height: anInteger [ "Ask the window manager to give the given height to the window." width isNil ifTrue: [self cacheWindowSize]. self resetGeometry: x y: y width: width height: anInteger ] heightAbsolute [ "Answer the height of the window, as deduced from the geometry that the window manager imposed on the window." height isNil ifTrue: [self cacheWindowSize]. ^height ] heightOffset: value [ self shouldNotImplement ] iconify [ "Map a window and in iconified state. If a window has not been mapped yet, this is achieved by mapping the window in withdrawn state first, and then iconifying it." self container iconify. self isMapped: false ] isMapped [ "Answer whether the window is mapped" isMapped isNil ifTrue: [isMapped := false]. ^isMapped ] isWindow [ ^true ] map [ "Map the window and bring it to the topmost position in the Z-order." self container present. self isMapped: true ] modalMap [ "Map the window while establishing an application-local grab for it. An event loop is started that ends only after the window has been destroyed." self container setModal: true. self map. Blox dispatchEvents: self. self container setModal: false ] state [ "Set the value of the state option for the window. Specifies one of four states for the window: either normal, iconic, withdrawn, or (Windows only) zoomed." self tclEval: 'wm state ' , self connected. ^self tclResult asSymbol ] state: aSymbol [ "Raise an error. To set a BWindow's state, use #map and #unmap." self error: 'To set a BWindow''s state, use #map and #unmap.' ] unmap [ "Unmap a window, causing it to be forgotten about by the window manager" self isMapped ifFalse: [^self]. self hide. self isMapped: false ] width [ "Answer the width of the window, as deduced from the geometry that the window manager imposed on the window." width isNil ifTrue: [self cacheWindowSize]. ^width ] width: anInteger [ "Ask the window manager to give the given width to the window." height isNil ifTrue: [self cacheWindowSize]. self resetGeometry: x y: y width: anInteger height: height ] width: xSize height: ySize [ "Ask the window manager to give the given width and height to the window." self resetGeometry: x y: y width: xSize height: ySize ] widthAbsolute [ "Answer the width of the window, as deduced from the geometry that the window manager imposed on the window." width isNil ifTrue: [self cacheWindowSize]. ^width ] widthOffset: value [ self shouldNotImplement ] window [ ^self ] x [ "Answer the x coordinate of the window's top-left corner, as deduced from the geometry that the window manager imposed on the window." x isNil ifTrue: [self cacheWindowSize]. ^x ] x: anInteger [ "Ask the window manager to move the window's left border to the given x coordinate, keeping the size unchanged" y isNil ifTrue: [self cacheWindowSize]. self resetGeometry: anInteger y: y width: width height: height ] x: xPos y: yPos [ "Ask the window manager to move the window's top-left corner to the given coordinates, keeping the size unchanged" self resetGeometry: xPos y: yPos width: width height: height ] x: xPos y: yPos width: xSize height: ySize [ "Ask the window manager to give the requested geometry to the window." "XXX gtk deprecates this sort of thing" self resetGeometry: xPos y: yPos width: xSize height: ySize ] xAbsolute [ "Answer the x coordinate of the window's top-left corner, as deduced from the geometry that the window manager imposed on the window." x isNil ifTrue: [self cacheWindowSize]. ^x ] xOffset: value [ self shouldNotImplement ] y [ "Answer the y coordinate of the window's top-left corner, as deduced from the geometry that the window manager imposed on the window." y isNil ifTrue: [self cacheWindowSize]. ^y ] y: anInteger [ "Ask the window manager to move the window's left border to the given y coordinate, keeping the size unchanged" x isNil ifTrue: [self cacheWindowSize]. self resetGeometry: x y: anInteger width: width height: height ] yAbsolute [ "Answer the y coordinate of the window's top-left corner, as deduced from the geometry that the window manager imposed on the window." y isNil ifTrue: [self cacheWindowSize]. ^y ] yOffset: value [ self shouldNotImplement ] ] BWindow subclass: BTransientWindow [ BTransientWindow class >> new [ self shouldNotImplement ] BTransientWindow class >> new: parentWindow [ "Answer a new transient window attached to the given parent window and with nothing in its title bar caption." ^(self basicNew) initialize: parentWindow; yourself ] BTransientWindow class >> new: label in: parentWindow [ "Answer a new transient window attached to the given parent window and with `label' as its title bar caption." ^(self basicNew) initialize: parentWindow; label: label; yourself ] map [ "Map the window and inform the windows manager that the receiver is a transient window working on behalf of its parent. The window is also put in its parent window's window group: the window manager might use this information, for example, to unmap all of the windows in a group when the group's leader is iconified." self parent isNil ifFalse: [self container setTransientFor: self parent container]. super map ] ] BWindow subclass: BPopupWindow [ addChild: w [ "Private - The widget identified by child has been added to the receiver. This method is public not because you can call it, but because it can be useful to override it to perform some initialization on the children just added. Answer the new child." self uiBox packEnd: w expand: true fill: true padding: 1. w onDestroySend: #destroy to: self ] child: child height: value [ "Set the given child's height. This is done by setting its parent window's (that is, our) height." "Only act after #addChild:" self childrenCount = 0 ifTrue: [^self]. self height: value ] child: child heightOffset: value [ self shouldNotImplement ] child: child width: value [ "Set the given child's width. This is done by setting its parent window's (that is, our) width." "Only act after #addChild:" self childrenCount = 0 ifTrue: [^self]. self width: value ] child: child widthOffset: value [ self shouldNotImplement ] child: child x: value [ "Set the x coordinate of the given child's top-left corner. This is done by setting its parent window's (that is, our) x." self x: value ] child: child xOffset: value [ self shouldNotImplement ] child: child y: value [ "Set the y coordinate of the given child's top-left corner. This is done by setting its parent window's (that is, our) y." self y: value ] child: child yOffset: value [ self shouldNotImplement ] heightChild: child [ "Answer the given child's height, which is the height that was imposed on the popup window." ^self height ] widthChild: child [ "Answer the given child's width in pixels, which is the width that was imposed on the popup window." ^self width ] xChild: child [ "Answer the x coordinate of the given child's top-left corner, which is desumed by the position of the popup window." ^self x ] yChild: child [ "Answer the y coordinate of the given child's top-left corner, which is desumed by the position of the popup window." ^self y ] create [ super create. self container setDecorated: false. self container setResizable: false ] setInitialSize [ self cacheWindowSize ] ] BForm subclass: BDialog [ | callbacks initInfo buttonBox entry | BDialog class >> new: parent [ "Answer a new dialog handler (containing a label widget and some button widgets) laid out within the given parent window. The label widget, when it is created, is empty." ^(self basicNew) initInfo: '' -> nil; initialize: parent ] BDialog class >> new: parent label: aLabel [ "Answer a new dialog handler (containing a label widget and some button widgets) laid out within the given parent window. The label widget, when it is created, contains aLabel." ^(self basicNew) initInfo: aLabel -> nil; initialize: parent ] BDialog class >> new: parent label: aLabel prompt: aString [ "Answer a new dialog handler (containing a label widget, some button widgets, and an edit window showing aString by default) laid out within the given parent window. The label widget, when it is created, contains aLabel." ^(self basicNew) initInfo: aLabel -> aString; initialize: parent ] BDialog class >> chooseFile: operation parent: parent label: aLabel default: name defaultExtension: ext types: typeList action: action button: button [ | dialog result filename | 'FIXME: implement the default, defaultExtension and typesList portions' printNl. parent map. dialog := GTK.GtkFileChooserDialog new: aLabel parent: parent container action: action varargs: {GTK.Gtk gtkStockCancel. GTK.Gtk gtkResponseCancel. button. GTK.Gtk gtkResponseAccept. nil}. result := dialog run. ^result = GTK.Gtk gtkResponseAccept ifFalse: [dialog destroy. nil] ifTrue: [filename := dialog getFilename. filename isEmpty ifTrue: [filename := nil]. dialog destroy. filename] ] BDialog class >> chooseColor: parent label: aLabel default: color [ "Prompt for a color. The dialog box is created with the given parent window and with aLabel as its title bar text, and initially it selects the color given in the color parameter. If the dialog box is canceled, nil is answered, else the selected color is returned as a String with its RGB value." | result | parent map. self tclEval: 'tk_chooseColor -parent %1 -title %2 -initialcolor %3' with: parent container with: aLabel asTkString with: color asTkString. result := self tclResult. result isEmpty ifTrue: [result := nil]. ^result ] BDialog class >> chooseFileToOpen: parent label: aLabel default: name defaultExtension: ext types: typeList [ "Pop up a dialog box for the user to select a file to open. Its purpose is for the user to select an existing file only. If the user enters an non-existent file, the dialog box gives the user an error prompt and requires the user to give an alternative selection or to cancel the selection. If an application allows the user to create new files, it should do so by providing a separate New menu command. If the dialog box is canceled, nil is answered, else the selected file name is returned as a String. The dialog box is created with the given parent window and with aLabel as its title bar text. The name parameter indicates which file is initially selected, and the default extension specifies a string that will be appended to the filename if the user enters a filename without an extension. The typeList parameter is an array of arrays, like #(('Text files' '.txt' '.diz') ('Smalltalk files' '.st')), and is used to construct a listbox of file types. When the user chooses a file type in the listbox, only the files of that type are listed. Each item in the array contains a list of strings: the first one is the name of the file type described by a particular file pattern, and is the text string that appears in the File types listbox, while the other ones are the possible extensions that belong to this particular file type." "e.g. fileName := BDialog chooseFileToOpen: aWindow label: 'Open file' default: nil defaultExtension: 'gif' types: #( ('Text files' '.txt' '.diz') ('Smalltalk files' '.st') ('C source files' '.c') ('GIF files' '.gif'))" ^self chooseFile: 'Open' parent: parent label: aLabel default: name defaultExtension: ext types: typeList action: GTK.Gtk gtkFileChooserActionOpen button: GTK.Gtk gtkStockOpen ] BDialog class >> chooseFileToSave: parent label: aLabel default: name defaultExtension: ext types: typeList [ "Pop up a dialog box for the user to select a file to save; this differs from the file open dialog box in that non-existent file names are accepted and existing file names trigger a confirmation dialog box, asking the user whether the file should be overwritten or not. If the dialog box is canceled, nil is answered, else the selected file name is returned as a String. The dialog box is created with the given parent window and with aLabel as its title bar text. The name parameter indicates which file is initially selected, and the default extension specifies a string that will be appended to the filename if the user enters a filename without an extension. The typeList parameter is an array of arrays, like #(('Text files' '.txt' '.diz') ('Smalltalk files' '.st')), and is used to construct a listbox of file types. When the user chooses a file type in the listbox, only the files of that type are listed. Each item in the array contains a list of strings: the first one is the name of the file type described by a particular file pattern, and is the text string that appears in the File types listbox, while the other ones are the possible extensions that belong to this particular file type." ^self chooseFile: 'Save' parent: parent label: aLabel default: name defaultExtension: ext types: typeList action: GTK.Gtk gtkFileChooserActionSave button: GTK.Gtk gtkStockSave ] addButton: aLabel receiver: anObject index: anInt [ "Add a button to the dialog box that, when clicked, will cause the #dispatch: method to be triggered in anObject, passing anInt as the argument of the callback. The caption of the button is set to aLabel." ^self addButton: aLabel receiver: anObject message: #dispatch: argument: anInt ] addButton: aLabel receiver: anObject message: aSymbol [ "Add a button to the dialog box that, when clicked, will cause the aSymbol unary selector to be sent to anObject. The caption of the button is set to aLabel." callbacks addLast: (DirectedMessage selector: aSymbol arguments: #() receiver: anObject). self addButton: aLabel ] addButton: aLabel receiver: anObject message: aSymbol argument: arg [ "Add a button to the dialog box that, when clicked, will cause the aSymbol one-argument selector to be sent to anObject, passing arg as the argument of the callback. The caption of the button is set to aLabel." callbacks addLast: (DirectedMessage selector: aSymbol arguments: {arg} receiver: anObject). self addButton: aLabel ] contents: newText [ "Display newText in the entry widget associated to the dialog box." entry setText: newText ] contents [ "Answer the text that is displayed in the entry widget associated to the dialog box." ^entry getText ] addButton: aLabel [ | button | self buttonBox add: (button := GTK.GtkButton newWithLabel: aLabel). button show. button connectSignal: 'clicked' to: self selector: #clicked:data: userData: callbacks size ] clicked: button data: data [ self invokeCallback: data. self toplevel destroy ] buttonBox [ buttonBox isNil ifTrue: [self create]. ^buttonBox ] create [ "We do not use BDialog. Instead, we work in the toplevel's uiBox, because Blox makes the BDialog live into a BWindow that provides space for other widgets." | uiBox label separator | super create. uiBox := self toplevel uiBox. buttonBox := GTK.GtkHButtonBox new. buttonBox setSpacing: 5. buttonBox setLayout: GTK.Gtk gtkButtonboxEnd. uiBox packEnd: buttonBox expand: false fill: false padding: 5. buttonBox show. separator := GTK.GtkHSeparator new. uiBox packEnd: separator expand: false fill: false padding: 0. separator show. "Put the GtkPlacer at the end of the list of the end-packed widgets, which puts it above our GtkHSeparator and GtkHButtonBox." uiBox reorderChild: self toplevel connected position: -1. initInfo isNil ifTrue: [^self]. label := GTK.GtkLabel new: initInfo key. label setAlignment: 0 yalign: 0. uiBox packStart: label expand: false fill: false padding: 5. label show. initInfo value isNil ifTrue: [^self]. entry := GTK.GtkEntry new. entry setText: initInfo value. uiBox packStart: entry expand: false fill: false padding: 0. entry show ] initInfo: assoc [ initInfo := assoc ] initialize: parentWidget [ super initialize: parentWidget. callbacks := OrderedCollection new ] center [ "Center the dialog box's parent window in the screen" self parent center ] centerIn: view [ "Center the dialog box's parent window in the given widget" self parent centerIn: view ] invokeCallback: index [ "Generate a synthetic callback corresponding to the index-th button being pressed, and destroy the parent window (triggering its callback if one was established)." (callbacks at: index asInteger) send "self parent destroy" ] loop [ "Map the parent window modally. In other words, an event loop is started that ends only after the window has been destroyed. For more information on the treatment of events for modal windows, refer to BWindow>>#modalMap." self toplevel container showAll. self toplevel modalMap ] ] BMenuObject subclass: BMenuBar [ | actionGroup uiManager | add: aMenu [ "Add aMenu to the menu bar" aMenu create. ^aMenu ] remove: aMenu [ "Remove aMenu from the menu bar" self tclEval: 'catch { %1 delete %2 }' with: self connected with: aMenu connected ] uiManager [ uiManager isNil ifTrue: [self create]. ^uiManager ] create [ uiManager := self parent isNil ifTrue: [GTK.GtkUIManager new] ifFalse: [self toplevel uiManager]. self uiManager addUi: self uiManager newMergeId path: '/' name: self name action: self name type: GTK.Gtk gtkUiManagerMenubar top: false. self parent isNil ifFalse: [self parent menu: self]. actionGroup := GTK.GtkActionGroup new: 'MenuActions'. self uiManager insertActionGroup: actionGroup pos: 0 ] exists [ ^uiManager notNil ] name [ "answer the name" ^'MainMenu' ] path [ "answer the menu path" ^'/MainMenu' ] actionGroup [ "answer an actiongroup that menu entries should go in" actionGroup isNil ifTrue: [self create]. ^actionGroup ] ] BMenuObject subclass: BMenu [ | connected label | BMenu class >> new: parent label: label [ "Add a new menu to the parent window's menu bar, with `label' as its caption (for popup menus, parent is the widget over which the menu pops up as the right button is pressed)." ^(self basicNew) initialize: parent; label: label; yourself ] label [ "Answer the value of the label option for the widget. Specifies a string to be displayed inside the widget. The way in which the string is displayed depends on the particular widget and may be determined by other options, such as anchor. For windows, this is the title of the window." ^label ] label: value [ "Set the value of the label option for the widget. Specifies a string to be displayed inside the widget. The way in which the string is displayed depends on the particular widget and may be determined by other options, such as anchor. For windows, this is the title of the window." "TODO: save the merge id we used, remove the ui, and re-add the ui with the new label" label := value ] addLine [ "Add a separator item at the end of the menu" ^self addMenuItemFor: #() notifying: self "self is dummy" ] addMenuItemFor: anArray notifying: receiver [ "Add a menu item described by anArray at the end of the menu. If anArray is empty, insert a separator line. If anArray has a single item, a menu item is created without a callback. If anArray has two or three items, the second one is used as the selector sent to receiver, and the third one (if present) is passed to the selector." "Receiver will be sent the callback messages. anArray is something that responds to at: and size. Possible types are: #() insert a seperator line #(name) create a menu item with name, but no callback #(name symbol) create a menu item with the given name and no parameter callback. #(name symbol arg) create a menu item with the given name and one parameter callback." | item | item := self newMenuItemFor: anArray notifying: receiver. self exists ifFalse: [self create]. item create ] callback: receiver using: selectorPairs [ "Add menu items described by anArray at the end of the menu. Each element of selectorPairs must be in the format described in BMenu>>#addMenuItemFor:notifying:. All the callbacks will be sent to receiver." selectorPairs do: [:pair | self addMenuItemFor: pair notifying: receiver] ] empty [ "Empty the menu widget; that is, remove all the children" self tclEval: self connected , ' delete 0 end'. children := OrderedCollection new. childrensUnderline := nil ] destroy [ "Destroy the menu widget; that is, simply remove ourselves from the parent menu bar." self parent remove: self ] addChild: menuItem [ self exists ifFalse: [self create]. menuItem create. ^menuItem ] actionGroup [ "answer the menu action group" ^self parent actionGroup ] name [ "answer the name the menu should get" ^self label , 'Menu' ] menuLabel [ "answer the label the menu should get" ^'_' , self label ] path [ "answer the path for the menu" ^self parent path , '/' , self name ] uiManager [ "answer the ui manager" ^self parent uiManager ] connected [ connected isNil ifTrue: [connected := self uiManager getWidget: self path]. ^connected ] create [ | s menu u | self actionGroup addAction: (GTK.GtkAction new: self name label: self menuLabel tooltip: nil stockId: nil). self uiManager addUi: self uiManager newMergeId path: self parent path name: self name action: self name type: GTK.Gtk gtkUiManagerMenu top: false. self childrenDo: [:each | each create] ] onDestroy: object data: data [ self destroyed ] exists [ ^self connected notNil ] initialize: parentWidget [ super initialize: parentWidget. label := '' ] newMenuItemFor: pair notifying: receiver [ | item size | size := pair size. pair size = 0 ifTrue: [^BMenuItem new: self]. (size >= 2 and: [pair last isArray]) ifTrue: [size := size - 1. item := BMenu new: self label: (pair at: 1). pair last do: [:each | item add: (item newMenuItemFor: each notifying: receiver)]] ifFalse: [item := BMenuItem new: self label: (pair at: 1)]. size = 1 ifTrue: [^item]. size = 2 ifTrue: [^item callback: receiver message: (pair at: 2)]. ^item callback: receiver message: (pair at: 2) argument: (pair at: 3) ] ] BMenu subclass: BPopupMenu [ | attachedWidget | PopupMenuBar := nil. PopupMenus := nil. BPopupMenu class >> initializeOnStartup [ PopupMenuBar := nil. PopupMenus := WeakKeyIdentityDictionary new ] BPopupMenu class >> popupMenuBar [ "answer the menubar this menu conceptually exists in" PopupMenuBar isNil ifTrue: [PopupMenuBar := BMenuBar new: nil]. ^PopupMenuBar ] initialize: parentWindow [ "TODO: refactor so that 'self parent' is parentWindow. Start by writing (and using!) a menuBar method in BMenu and overriding it here." self class popupMenuBar exists ifFalse: [self class popupMenuBar create]. super initialize: self class popupMenuBar. attachedWidget := parentWindow. PopupMenus at: parentWindow ifPresent: [:menu | menu destroy]. PopupMenus at: attachedWidget put: self ] create [ super create. attachedWidget connected connectSignal: 'button-press-event' to: self selector: #onPopup:event:data: userData: nil ] destroyed [ super destroyed. attachedWidget := nil ] onPopup: widget event: event data: data [ | buttonEv | buttonEv := event castTo: GTK.GdkEventButton type. buttonEv button value = 3 ifFalse: [^false]. self connected getSubmenu popup: nil parentMenuItem: nil func: nil data: nil button: 3 activateTime: buttonEv time value. ^true ] popup [ "Generate a synthetic menu popup event" self connected getSubmenu popup: attachedWidget connected parentMenuItem: nil func: nil data: nil button: 0 activateTime: GTK.Gtk getCurrentEventTime ] ] BMenuObject subclass: BMenuItem [ | index | BMenuItem class >> new: parent [ "Add a new separator item to the specified menu." ^self basicNew initialize: parent ] BMenuItem class >> new: parent label: label [ "Add a new menu item to the specified menu (parent) , with `label' as its caption." ^self basicNew initialize: parent label: label ] label [ "Answer the value of the label option for the widget. Specifies a string to be displayed inside the widget. The way in which the string is displayed depends on the particular widget and may be determined by other options, such as anchor. For windows, this is the title of the window." ^self properties at: #label ] label: value [ "Set the value of the label option for the widget. Specifies a string to be displayed inside the widget. The way in which the string is displayed depends on the particular widget and may be determined by other options, such as anchor. For windows, this is the title of the window." (self properties at: #label) isNil ifTrue: [^self error: 'no label for separator lines']. self parent exists ifTrue: [self tclEval: self container , ' entryconfigure ' , self connected , ' -label ' , value asTkString]. self properties at: #label put: value ] actionGroup [ "answer the menu action group" ^self parent actionGroup ] uiManager [ ^self parent uiManager ] name [ "answer the name of the item" ^self label ] menuLabel [ "answer the gtk label" ^'_' , self name ] path [ "answer the gtk uiManager path" ^self parent path , '/' , self name ] create [ | s u mergeid action | self name isNil ifTrue: [mergeid := self uiManager newMergeId. self properties at: #label put: 'separator' , (mergeid printString: 10). self uiManager addUi: mergeid path: self parent path name: self name action: nil type: GTK.Gtk gtkUiManagerSeparator top: false] ifFalse: [action := GTK.GtkAction new: self name label: self menuLabel tooltip: 'FIXME' stockId: nil. "FIXME, when to use stock options? GTK.Gtk gtkStockOpen." action connectSignal: 'activate' to: self selector: #activated:data: userData: nil. "FIXME when to trigger accelerators" "self actionGroup addActionWithAccel: foo accelerator: 'O'." self actionGroup addAction: action. self uiManager addUi: self uiManager newMergeId path: self parent path name: self name action: self name type: GTK.Gtk gtkUiManagerMenuitem top: false] ] activated: action data: userData [ self invokeCallback ] initialize: parentWidget [ "initialize a separator item" super initialize: parentWidget. self properties at: #label put: nil ] initialize: parentWidget label: label [ | s | super initialize: parentWidget. self properties at: #label put: label. parent exists ifTrue: [self create] ] ] BMenuItem subclass: BCheckMenuItem [ | status | BCheckMenuItem class >> new: parent [ self shouldNotImplement ] invokeCallback [ "Generate a synthetic callback" self properties removeKey: #value ifAbsent: []. self callback isNil ifFalse: [self callback send] ] value [ "Answer whether the menu item is in a selected (checked) state." ^self properties at: #value ifAbsentPut: [false] ] value: aBoolean [ "Set whether the button is in a selected (checked) state and generates a callback accordingly." self properties at: #value put: aBoolean. self tclEval: 'set ' , self variable , self valueString. self callback isNil ifFalse: [self callback send] ] create [ super create. self tclEval: '%1 entryconfigure %2 -onvalue 1 -offvalue 0 -variable %3' with: self container with: self connected with: self variable ] destroyed [ "Private - The receiver has been destroyed, clear the corresponding Tcl variable to avoid memory leaks." self tclEval: 'unset ' , self variable. super destroyed ] valueString [ ^self value ifTrue: [' 1'] ifFalse: [' 0'] ] variable [ ^'var' , self connected , self container copyWithout: $. ] widgetType [ ^'checkbutton' ] ] "-------------------------- BEdit class -----------------------------" "-------------------------- BLabel class -----------------------------" Eval [ BLabel initialize ] "-------------------------- BButton class -----------------------------" "-------------------------- BForm class -----------------------------" "-------------------------- BContainer class -----------------------------" "-------------------------- BRadioGroup class -----------------------------" "-------------------------- BRadioButton class -----------------------------" "-------------------------- BToggle class -----------------------------" "-------------------------- BImage class -----------------------------" "-------------------------- BList class -----------------------------" "-------------------------- BWindow class -----------------------------" "-------------------------- BTransientWindow class -----------------------------" "-------------------------- BPopupWindow class -----------------------------" "-------------------------- BDialog class -----------------------------" "-------------------------- BMenuBar class -----------------------------" "-------------------------- BMenu class -----------------------------" "-------------------------- BPopupMenu class -----------------------------" "-------------------------- BMenuItem class -----------------------------" "-------------------------- BCheckMenuItem class -----------------------------" smalltalk-3.2.5/packages/blox/gtk/BloxText.st0000644000175000017500000012730012123404352016055 00000000000000"====================================================================== | | Smalltalk Tk-based GUI building blocks (text widget). | | ======================================================================" "====================================================================== | | Copyright 1999, 2000, 2001, 2002 Free Software Foundation, Inc. | Written by Paolo Bonzini and Robert Collins. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LESSER. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" BViewport subclass: BText [ | callback tagInfo images gtkbuffer | BText class >> emacsLike [ "Answer whether we are using Emacs or Motif key bindings." 'FIXME: emacsLike should die?' printNl. ^false "self tclEval: 'return $tk_strictMotif'. ^self tclResult = '0'" ] BText class >> emacsLike: aBoolean [ "Set whether we are using Emacs or Motif key bindings." 'FIXME: emacsLike should die?' printNl "self tclEval: 'set tk_strictMotif ', (aBoolean ifTrue: [ '0' ] ifFalse: [ '1' ])." ] BText class >> newReadOnly: parent [ "Answer a new read-only text widget (read-only is achieved simply by setting its state to be disabled)" | ctl | ctl := self new: parent. ctl tclEval: ctl connected , ' configure -state disabled'. ^ctl ] backgroundColor [ "Answer the value of the backgroundColor option for the widget. Specifies the normal background color to use when displaying the widget." self properties at: #background ifPresent: [:value | ^value]. self tclEval: '%1 cget -background' with: self connected with: self container. ^self properties at: #background put: self tclResult ] backgroundColor: value [ "Set the value of the backgroundColor option for the widget. Specifies the normal background color to use when displaying the widget." self tclEval: '%1 configure -background %3' with: self connected with: self container with: value asTkString. self properties at: #background put: value ] callback [ "Answer a DirectedMessage that is sent when the receiver is modified, or nil if none has been set up." ^callback ] callback: aReceiver message: aSymbol [ "Set up so that aReceiver is sent the aSymbol message (the name of a zero- or one-argument selector) when the receiver is modified. If the method accepts an argument, the receiver is passed." | arguments selector numArgs | selector := aSymbol asSymbol. numArgs := selector numArgs. arguments := #(). numArgs = 1 ifTrue: [arguments := Array with: self]. callback := DirectedMessage selector: selector arguments: arguments receiver: aReceiver ] contents [ "Return the contents of the widget" | bounds | bounds := self gtkbuffer getBounds. ^(bounds at: 1) getVisibleText: (bounds at: 2) ] contents: aString [ "Set the contents of the widget" self gtkbuffer setText: aString ] font [ "Answer the value of the font option for the widget. Specifies the font to use when drawing text inside the widget. The font can be given as either an X font name or a Blox font description string. X font names are given as many fields, each led by a minus, and each of which can be replaced by an * to indicate a default value is ok: foundry, family, weight, slant, setwidth, addstyle, pixel size, point size (the same as pixel size for historical reasons), horizontal resolution, vertical resolution, spacing, width, charset and character encoding. Blox font description strings have three fields, which must be separated by a space and of which only the first is mandatory: the font family, the font size in points (or in pixels if a negative value is supplied), and a number of styles separated by a space (valid styles are normal, bold, italic, underline and overstrike). Examples of valid fonts are ``Helvetica 10 Bold'', ``Times -14'', ``Futura Bold Underline''. You must enclose the font family in braces if it is made of two or more words." self properties at: #font ifPresent: [:value | ^value]. self tclEval: '%1 cget -font' with: self connected with: self container. ^self properties at: #font put: self tclResult ] font: value [ "Set the value of the font option for the widget. Specifies the font to use when drawing text inside the widget. The font can be given as either an X font name or a Blox font description string. X font names are given as many fields, each led by a minus, and each of which can be replaced by an * to indicate a default value is ok: foundry, family, weight, slant, setwidth, addstyle, pixel size, point size (the same as pixel size for historical reasons), horizontal resolution, vertical resolution, spacing, width, charset and character encoding. Blox font description strings have three fields, which must be separated by a space and of which only the first is mandatory: the font family, the font size in points (or in pixels if a negative value is supplied), and a number of styles separated by a space (valid styles are normal, bold, italic, underline and overstrike). Examples of valid fonts are ``Helvetica 10 Bold'', ``Times -14'', ``Futura Bold Underline''. You must enclose the font family in braces if it is made of two or more words." "Change default font throughout the widget" self connected modifyFont: (GTK.PangoFontDescription fromString: value). self properties at: #font put: value ] foregroundColor [ "Answer the value of the foregroundColor option for the widget. Specifies the normal foreground color to use when displaying the widget." self properties at: #foreground ifPresent: [:value | ^value]. self tclEval: '%1 cget -foreground' with: self connected with: self container. ^self properties at: #foreground put: self tclResult ] foregroundColor: value [ "Set the value of the foregroundColor option for the widget. Specifies the normal foreground color to use when displaying the widget." self tclEval: '%1 configure -foreground %3' with: self connected with: self container with: value asTkString. self properties at: #foreground put: value ] getSelection [ "Answer an empty string if the widget has no selection, else answer the currently selected text" | bounds | bounds := self gtkbuffer getSelectionBounds. ^(bounds at: 1) getVisibleText: (bounds at: 2) ] selectBackground [ "Answer the value of the selectBackground option for the widget. Specifies the background color to use when displaying selected parts of the widget." self properties at: #selectbackground ifPresent: [:value | ^value]. self tclEval: '%1 cget -selectbackground' with: self connected with: self container. ^self properties at: #selectbackground put: self tclResult ] selectBackground: value [ "Set the value of the selectBackground option for the widget. Specifies the background color to use when displaying selected parts of the widget." self tclEval: '%1 configure -selectbackground %3' with: self connected with: self container with: value asTkString. self properties at: #selectbackground put: value ] selectForeground [ "Answer the value of the selectForeground option for the widget. Specifies the foreground color to use when displaying selected parts of the widget." self properties at: #selectforeground ifPresent: [:value | ^value]. self tclEval: '%1 cget -selectforeground' with: self connected with: self container. ^self properties at: #selectforeground put: self tclResult ] selectForeground: value [ "Set the value of the selectForeground option for the widget. Specifies the foreground color to use when displaying selected parts of the widget." self tclEval: '%1 configure -selectforeground %3' with: self connected with: self container with: value asTkString. self properties at: #selectforeground put: value ] wrap [ "Answer the value of the wrap option for the widget. Specifies how to handle lines in the text that are too long to be displayed in a single line of the text's window. The value must be #none or #char or #word. A wrap mode of none means that each line of text appears as exactly one line on the screen; extra characters that do not fit on the screen are not displayed. In the other modes each line of text will be broken up into several screen lines if necessary to keep all the characters visible. In char mode a screen line break may occur after any character; in word mode a line break will only be made at word boundaries." self properties at: #wrap ifPresent: [:value | ^value]. self tclEval: '%1 cget -wrap' with: self connected with: self container. ^self properties at: #wrap put: self tclResult asSymbol ] wrap: value [ "Set the value of the wrap option for the widget. Specifies how to handle lines in the text that are too long to be displayed in a single line of the text's window. The value must be #none or #char or #word. A wrap mode of none means that each line of text appears as exactly one line on the screen; extra characters that do not fit on the screen are not displayed. In the other modes each line of text will be broken up into several screen lines if necessary to keep all the characters visible. In char mode a screen line break may occur after any character; in word mode a line break will only be made at word boundaries." self tclEval: '%1 configure -wrap %3' with: self connected with: self container with: value asTkString. self properties at: #wrap put: value ] insertAtEnd: aString attribute: attr [ "Clear the selection and append aString at the end of the widget. Use the given attributes to format the text." | start tmpMark end | attr isNil ifTrue: [^self insertAtEnd: aString]. end := self gtkbuffer getEndIter. tmpMark := self gtkbuffer createMark: 'temporary' where: end leftGravity: true. self gtkbuffer beginUserAction. self gtkbuffer insert: end text: aString. start := self gtkbuffer getIterAtMark: tmpMark. end := self gtkbuffer getEndIter. self gtkbuffer placeCursor: end. self setAttributes: attr start: start end: end. self gtkbuffer endUserAction ] insertText: aString attribute: attr [ "Insert aString in the widget at the current insertion point, replacing the currently selected text (if any). Use the given attributes to format the text." | bounds start end tmpMark | attr isNil ifTrue: [^self insertText: aString]. "We need a temporary mark to save the beginning of the selection." bounds := self gtkbuffer getSelectionBounds. tmpMark := self gtkbuffer createMark: 'temporary' where: (bounds at: 1) leftGravity: true. (self gtkbuffer) beginUserAction; deleteSelection: false defaultEditable: true; insertAtCursor: aString. start := self gtkbuffer getIterAtMark: tmpMark. end := self gtkbuffer getIterAtMark: self gtkbuffer getInsert. self setAttributes: attr start: start end: end. self gtkbuffer endUserAction ] removeAttributes [ "Remove any kind of formatting from the text in the widget" tagInfo isNil ifTrue: [^self]. self removeAttributesInside: {self gtkbuffer getStartIter. self gtkbuffer getEndIter} ] removeAttributesFrom: aPoint to: endPoint [ "Remove any kind of formatting from the text in the widget between the given endpoints. The two endpoints are Point objects in which both coordinates are 1-based: the first line is line 1, and the first character in the first line is character 1." tagInfo isNil ifTrue: [^self]. self removeAttributesInside: (self from: aPoint to: endPoint) ] setAttributes: attr from: aPoint to: endPoint [ "Add the formatting given by attr to the text in the widget between the given endpoints. The two endpoints are Point objects in which both coordinates are 1-based: the first line is line 1, and the first character in the first line is character 1." | range tag tags tagtable | attr isNil ifTrue: [^self]. range := self from: aPoint to: endPoint. self setAttributes: attr start: (range at: 1) end: (range at: 2) ] child: child height: value [ "Set the height of the given child to be `value' pixels." | width height | height := self at: #heightGeom put: value asInteger. width := self at: #widthGeom ifAbsentPut: [self widthAbsolute] "self tclEval: 'wm geometry %1 =%2x%3' with: child container with: width printString with: height printString" ] child: child heightOffset: value [ "Adjust the height of the given child to be given by `value' more pixels." self child: child height: (self heightChild: child) + value ] child: child width: value [ "Set the width of the given child to be `value' pixels." | width height | width := self at: #widthGeom put: value asInteger. height := self at: #heightGeom ifAbsentPut: [child heightAbsolute] "self tclEval: 'wm geometry %1 =%2x%3' with: child container with: width printString with: height printString" ] child: child widthOffset: value [ "Adjust the width of the given child to be given by `value' more pixels." self child: child width: (self widthChild: child) + value ] child: child x: value [ "Never fail and do nothing, the children stay where the text ended at the time each child was added in the widget" ] child: child xOffset: value [ self shouldNotImplement ] child: child y: value [ "Never fail and do nothing, the children stay where the text ended at the time each child was added in the widget" ] child: child yOffset: value [ self shouldNotImplement ] heightChild: child [ "Answer the given child's height in pixels." ^child at: #heightGeom ifAbsentPut: [child heightAbsolute] ] widthChild: child [ "Answer the given child's width in pixels." ^child at: #widthGeom ifAbsentPut: [child widthAbsolute] ] xChild: child [ "Answer the given child's top-left border's x coordinate. We always answer 0 since the children actually move when the text widget scrolls" ^0 ] yChild: child [ "Answer the given child's top-left border's y coordinate. We always answer 0 since the children actually move when the text widget scrolls" ^0 ] insertImage: anObject [ "Insert an image where the insertion point currently lies in the widget. anObject can be a String containing image data (either Base-64 encoded GIF data, XPM data, or PPM data), or the result or registering an image with #registerImage:" | key | key := self registerImage: anObject. self tclEval: '%1 image create insert -align baseline -image %2' with: self connected with: key value. ^key ] insertImage: anObject at: position [ "Insert an image at the given position in the widget. The position is a Point object in which both coordinates are 1-based: the first line is line 1, and the first character in the first line is character 1. anObject can be a String containing image data (either Base-64 encoded GIF data, XPM data, or PPM data), or the result or registering an image with #registerImage:" | key | key := self registerImage: anObject. self tclEval: '%1 image create %2.%3 -align baseline -image %4' with: self connected with: position y printString with: (position x - 1) printString with: key value. ^key ] insertImageAtEnd: anObject [ "Insert an image at the end of the widgets text. anObject can be a String containing image data (either Base-64 encoded GIF data, XPM data, or PPM data), or the result or registering an image with #registerImage:" | key | key := self registerImage: anObject. self tclEval: '%1 image create end -align baseline -image %2' with: self connected with: key value. ^key ] registerImage: anObject [ "Register an image (whose data is in anObject, a String including Base-64 encoded GIF data, XPM data, or PPM data) to be used in the widget. If the same image must be used a lot of times, it is better to register it once and then pass the result of #registerImage: to the image insertion methods. Registered image are private within each BText widget. Registering an image with a widget and using it with another could give unpredictable results." | imageName | anObject class == ValueHolder ifTrue: [^anObject]. self tclEval: 'image create photo -data ' , anObject asTkImageString. images isNil ifTrue: [images := OrderedCollection new]. imageName := images add: self tclResult. ^ValueHolder value: imageName ] insertAtEnd: aString [ "Clear the selection and append aString at the end of the widget." (self gtkbuffer) insert: self gtkbuffer getEndIter text: aString; placeCursor: self gtkbuffer getEndIter ] insertText: aString [ "Insert aString in the widget at the current insertion point, replacing the currently selected text (if any)." (self gtkbuffer) beginUserAction; deleteSelection: false defaultEditable: true; insertAtCursor: aString; endUserAction ] insertSelectedText: aString [ "Insert aString in the widget at the current insertion point, leaving the currently selected text (if any) in place, and selecting the text." | bounds selBound tmpMark | selBound := self gtkbuffer getSelectionBound. bounds := self gtkbuffer getSelectionBounds. "We need a temporary mark to keep the beginning of the selection where it is." tmpMark := self gtkbuffer createMark: 'temporary' where: (bounds at: 1) leftGravity: true. (self gtkbuffer) beginUserAction; placeCursor: (bounds at: 2); insertAtCursor: aString; moveMark: selBound where: (self gtkbuffer getIterAtMark: tmpMark); endUserAction; deleteMark: tmpMark ] insertText: aString at: position [ "Insert aString in the widget at the given position, replacing the currently selected text (if any). The position is a Point object in which both coordinates are 1-based: the first line is line 1, and the first character in the first line is character 1." self tclEval: '%1 delete sel.first sel.last %1 insert %2.%3 %4 %1 see insert' with: self connected with: position y printString with: (position x - 1) printString with: aString asTkString ] insertTextSelection: aString [ "Insert aString in the widget after the current selection, leaving the currently selected text (if any) intact." | bounds selBound tmpMark | selBound := self gtkbuffer getSelectionBound. bounds := self gtkbuffer getSelectionBounds. "We need a temporary mark to put the beginning of the selection where the selection used to end." tmpMark := self gtkbuffer createMark: 'temporary' where: (bounds at: 2) leftGravity: true. (self gtkbuffer) beginUserAction; placeCursor: (bounds at: 2); insertAtCursor: aString; moveMark: selBound where: (self gtkbuffer getIterAtMark: tmpMark); endUserAction; deleteMark: tmpMark ] invokeCallback [ "Generate a synthetic callback." self callback isNil ifFalse: [self callback send] ] nextPut: aCharacter [ "Clear the selection and append aCharacter at the end of the widget." self insertAtEnd: (String with: aCharacter) ] nextPutAll: aString [ "Clear the selection and append aString at the end of the widget." self insertAtEnd: aString ] nl [ "Clear the selection and append a linefeed character at the end of the widget." self insertAtEnd: Character nl asString ] refuseTabs [ "Arrange so that Tab characters, instead of being inserted in the widget, traverse the widgets in the parent window." self tclEval: ' bind %1 { focus [tk_focusNext %W] break } bind %1 { focus [tk_focusPrev %W] break }' with: self connected ] replaceSelection: aString [ "Insert aString in the widget at the current insertion point, replacing the currently selected text (if any), and leaving the text selected." | bounds | bounds := self gtkbuffer getSelectionBounds. self gtkbuffer delete: (bounds at: 1) end: (bounds at: 2). self gtkbuffer insertAtCursor: aString ] searchString: aString [ "Search aString in the widget. If it is not found, answer zero, else answer the 1-based line number and move the insertion point to the place where the string was found." | result | self tclEval: self connected , ' search ' , aString asTkString , ' 1.0 end'. result := self tclResult. result isEmpty ifTrue: [^0]. self tclEval: ' %1 mark set insert %2 %1 see insert' with: self connected with: result. "Sending asInteger removes the column" ^result asInteger ] space [ "Clear the selection and append a space at the end of the widget." self insertAtEnd: ' ' ] charsInLine: number [ "Answer how many characters are there in the number-th line" | iter | iter := self gtkbuffer getIterAtLine: number. iter forwardToLineEnd. ^1 + iter getLineOffset ] currentColumn [ "Answer the 1-based column number where the insertion point currently lies." | mark iter | mark := self gtkbuffer getInsert. iter := self gtkbuffer getIterAtMark: mark. ^1 + iter getLineOffset ] currentLine [ "Answer the 1-based line number where the insertion point currently lies." | mark iter | mark := self gtkbuffer getInsert. iter := self gtkbuffer getIterAtMark: mark. ^1 + iter getLine ] currentPosition [ "Answer a Point representing where the insertion point currently lies. Both coordinates in the answer are 1-based: the first line is line 1, and the first character in the first line is character 1." | mark iter | mark := self gtkbuffer getInsert. iter := self gtkbuffer getIterAtMark: mark. ^(1 + iter getLine) @ (1 + iter getLineOffset) ] currentPosition: aPoint [ "Move the insertion point to the position given by aPoint. Both coordinates in aPoint are interpreted as 1-based: the first line is line 1, and the first character in the first line is character 1." | iter | iter := self gtkbuffer getIterAtLineOffset: aPoint y - 1 charOffset: aPoint x - 1. self gtkbuffer placeCursor: iter ] gotoLine: line end: aBoolean [ "If aBoolean is true, move the insertion point to the last character of the line-th line (1 being the first line in the widget); if aBoolean is false, move it to the start of the line-th line." | iter | iter := self gtkbuffer getIterAtLine: line - 1. aBoolean ifTrue: [iter forwardToLineEnd]. self gtkbuffer placeCursor: iter ] indexAt: point [ "Answer the position of the character that covers the pixel whose coordinates within the text's window are given by the supplied Point object." self tclEval: self connected , ' index @%1,%2' with: point x printString with: point y printString. ^self parseResult ] lineAt: number [ "Answer the number-th line of text in the widget" | start end | start := self gtkbuffer getIterAtLine: number - 1. end := self gtkbuffer getIterAtLine: number - 1. end forwardToLineEnd. ^start getVisibleText: end ] numberOfLines [ "Answer the number of lines in the widget" ^self gtkbuffer getLineCount ] selectFrom: first to: last [ "Select the text between the given endpoints. The two endpoints are Point objects in which both coordinates are 1-based: the first line is line 1, and the first character in the first line is character 1." | bounds | bounds := self from: first to: last. self gtkbuffer selectRange: (bounds at: 1) bound: (bounds at: 2) ] setToEnd [ "Move the insertion point to the end of the widget" self tclEval: ' %1 mark set insert end-1c %1 see end' with: self connected ] addChild: child [ self tclEval: '%1 window create end -window %2' with: self connected with: child container ] setAttributes: attr start: startTextIter end: endTextIter [ | tags | tagInfo isNil ifTrue: [tagInfo := BTextTags new: self]. tags := attr tags: tagInfo. tags do: [:each | self gtkbuffer applyTag: each start: startTextIter end: endTextIter] ] gtkbuffer [ "answer the gtk text buffer" gtkbuffer isNil ifTrue: [self createWidget]. ^gtkbuffer ] onChanged: userData data: unused [ self invokeCallback ] create [ "initialise a Text widget" self connected: GTK.GtkTextView new. gtkbuffer := self connected getBuffer. self gtkbuffer connectSignal: 'changed' to: self selector: #onChanged:data: userData: nil ] defineTag: name as: options [ options class = String ifTrue: [options printNl. 0 unconverted defineTag call]. "FIXME/TODO: use g_object_set_property and recreate createTag" self gtkbuffer createTag: name varargs: options ] destroyed [ super destroyed. images isNil ifTrue: [^self]. images do: [:name | self tclEval: 'image delete ' , name]. images := nil ] from: aPoint to: endPoint [ | start end | start := self gtkbuffer getIterAtLineOffset: aPoint y - 1 charOffset: aPoint x - 1. end := self gtkbuffer getIterAtLineOffset: endPoint y - 1 charOffset: endPoint x - 1. ^ {start. end} ] removeAttributesInside: range [ | start end | start := range at: 1. end := range at: 2. self gtkbuffer removeAllTags: start end: end ] tag: name bind: event to: aSymbol of: anObject parameters: params [ self bind: event to: aSymbol of: anObject parameters: params prefix: '%1 tag bind %2' % {self connected. name} ] ] BEventTarget subclass: BTextBindings [ | list tagName | BTextBindings class >> new [ "Create a new instance of the receiver." ^self basicNew initialize ] defineTagFor: aBText [ list do: [:each | each sendTo: aBText] ] tagName [ ^tagName ] initialize [ tagName := 'ev' , (Time millisecondClockValue printString: 36). list := OrderedCollection new ] primBind: event to: aSymbol of: anObject parameters: params [ | args | (args := Array new: 5) at: 1 put: tagName; at: 2 put: event; at: 3 put: aSymbol; at: 4 put: anObject; at: 5 put: params. list add: (Message selector: #tag:bind:to:of:parameters: arguments: args) ] ] Object subclass: BTextAttributes [ | bgColor fgColor font styles events | BTextAttributes class >> backgroundColor: color [ "Create a new BTextAttributes object resulting in text with the given background color." ^self new backgroundColor: color ] BTextAttributes class >> black [ "Create a new BTextAttributes object resulting in black text." ^self new foregroundColor: 'black' ] BTextAttributes class >> blue [ "Create a new BTextAttributes object resulting in blue text." ^self new foregroundColor: 'blue' ] BTextAttributes class >> center [ "Create a new BTextAttributes object resulting in centered paragraphs." ^self new center ] BTextAttributes class >> cyan [ "Create a new BTextAttributes object resulting in cyan text." ^self new foregroundColor: 'cyan' ] BTextAttributes class >> darkCyan [ "Create a new BTextAttributes object resulting in dark cyan text." ^self new foregroundColor: 'PureDarkCyan' ] BTextAttributes class >> darkGreen [ "Create a new BTextAttributes object resulting in dark green text." ^self new foregroundColor: 'PureDarkGreen' ] BTextAttributes class >> darkMagenta [ "Create a new BTextAttributes object resulting in dark purple text." ^self new foregroundColor: 'PureDarkMagenta' ] BTextAttributes class >> events: aBTextBindings [ "Create a new BTextAttributes object for text that responds to events according to the callbacks established in aBTextBindings." ^self new events: aBTextBindings ] BTextAttributes class >> font: font [ "Create a new BTextAttributes object resulting in text with the given font. The font can be given as either an X font name or a Blox font description string. X font names are given as many fields, each led by a minus, and each of which can be replaced by an * to indicate a default value is ok: foundry, family, weight, slant, setwidth, addstyle, pixel size, point size (the same as pixel size for historical reasons), horizontal resolution, vertical resolution, spacing, width, charset and character encoding. Blox font description strings have three fields, which must be separated by a space and of which only the first is mandatory: the font family, the font size in points (or in pixels if a negative value is supplied), and a number of styles separated by a space (valid styles are normal, bold, italic, underline and overstrike). Examples of valid fonts are ``Helvetica 10 Bold'', ``Times -14'', ``Futura Bold Underline''. You must enclose the font family in braces if it is made of two or more words." ^self new font: font ] BTextAttributes class >> foregroundColor: color [ "Create a new BTextAttributes object resulting in text with the given foreground color." ^self new foregroundColor: color ] BTextAttributes class >> green [ "Create a new BTextAttributes object resulting in green text." ^self new foregroundColor: 'green' ] BTextAttributes class >> magenta [ "Create a new BTextAttributes object resulting in magenta text." ^self new foregroundColor: 'magenta' ] BTextAttributes class >> red [ "Create a new BTextAttributes object resulting in red text." ^self new foregroundColor: 'red' ] BTextAttributes class >> strikeout [ "Create a new BTextAttributes object resulting in struck-out text." ^self new strikeout ] BTextAttributes class >> underline [ "Create a new BTextAttributes object resulting in underlined text." ^self new underline ] BTextAttributes class >> yellow [ "Create a new BTextAttributes object resulting in yellow text." ^self new foregroundColor: 'yellow' ] BTextAttributes class >> white [ "Create a new BTextAttributes object resulting in white text." ^self new foregroundColor: 'white' ] black [ "Set the receiver so that applying it results in black text." self foregroundColor: 'black' ] blue [ "Set the receiver so that applying it results in blue text." self foregroundColor: 'blue' ] cyan [ "Set the receiver so that applying it results in cyan text." self foregroundColor: 'cyan' ] darkCyan [ "Set the receiver so that applying it results in dark cyan text." self foregroundColor: 'PureDarkCyan' ] darkGreen [ "Set the receiver so that applying it results in dark green text." self foregroundColor: 'PureDarkGreen' ] darkMagenta [ "Set the receiver so that applying it results in dark magenta text." self foregroundColor: 'PureDarkMagenta' ] green [ "Set the receiver so that applying it results in green text." self foregroundColor: 'green' ] magenta [ "Set the receiver so that applying it results in magenta text." self foregroundColor: 'magenta' ] red [ "Set the receiver so that applying it results in red text." self foregroundColor: 'red' ] white [ "Set the receiver so that applying it results in white text." self foregroundColor: 'white' ] yellow [ "Set the receiver so that applying it results in black text." self foregroundColor: 'yellow' ] hasStyle: aSymbol [ ^styles notNil and: [styles includes: aSymbol] ] style: aSymbol [ styles isNil ifTrue: [styles := Set new]. styles add: aSymbol ] tags: aBTextTags [ | s tagTable | tagTable := aBTextTags tagTable. s := OrderedCollection new. fgColor isNil ifFalse: [s add: (tagTable lookup: (aBTextTags fgColor: fgColor))]. bgColor isNil ifFalse: [s add: (tagTable lookup: (aBTextTags bgColor: bgColor))]. font isNil ifFalse: [s add: (tagTable lookup: (aBTextTags font: font))]. events isNil ifFalse: [s add: (tagTable lookup: (aBTextTags events: events))]. styles isNil ifFalse: [styles do: [:each | s add: (tagTable lookup: each)]]. ^s ] backgroundColor [ "Answer the value of the backgroundColor option for the text. Specifies the background color to use when displaying text with these attributes. nil indicates that the default value is not overridden." ^bgColor ] backgroundColor: color [ "Set the value of the backgroundColor option for the text. Specifies the background color to use when displaying text with these attributes. nil indicates that the default value is not overridden." bgColor := color ] center [ "Center the text to which these attributes are applied" self style: #STYLEcenter ] events [ "Answer the event bindings which apply to text subject to these attributes" ^events ] events: aBTextBindings [ "Set the event bindings which apply to text subject to these attributes" events := aBTextBindings ] font [ "Answer the value of the font option for the text. The font can be given as either an X font name or a Blox font description string, or nil if you want the widget's default font to apply. X font names are given as many fields, each led by a minus, and each of which can be replaced by an * to indicate a default value is ok: foundry, family, weight, slant, setwidth, addstyle, pixel size, point size (the same as pixel size for historical reasons), horizontal resolution, vertical resolution, spacing, width, charset and character encoding. Blox font description strings have three fields, which must be separated by a space and of which only the first is mandatory: the font family, the font size in points (or in pixels if a negative value is supplied), and a number of styles separated by a space (valid styles are normal, bold, italic, underline and overstrike). Examples of valid fonts are ``Helvetica 10 Bold'', ``Times -14'', ``Futura Bold Underline''. You must enclose the font family in braces if it is made of two or more words." ^font ] font: fontName [ "Set the value of the font option for the text. The font can be given as either an X font name or a Blox font description string, or nil if you want the widget's default font to apply. X font names are given as many fields, each led by a minus, and each of which can be replaced by an * to indicate a default value is ok: foundry, family, weight, slant, setwidth, addstyle, pixel size, point size (the same as pixel size for historical reasons), horizontal resolution, vertical resolution, spacing, width, charset and character encoding. Blox font description strings have three fields, which must be separated by a space and of which only the first is mandatory: the font family, the font size in points (or in pixels if a negative value is supplied), and a number of styles separated by a space (valid styles are normal, bold, italic, underline and overstrike). Examples of valid fonts are ``Helvetica 10 Bold'', ``Times -14'', ``Futura Bold Underline''. You must enclose the font family in braces if it is made of two or more words." font := fontName ] foregroundColor [ "Answer the value of the foregroundColor option for the text. Specifies the foreground color to use when displaying text with these attributes. nil indicates that the default value is not overridden." ^fgColor ] foregroundColor: color [ "Set the value of the foregroundColor option for the text. Specifies the foreground color to use when displaying text with these attributes. nil indicates that the default value is not overridden." fgColor := color ] isCentered [ "Answer whether the text to which these attributes are applied is centered" ^self hasStyle: #STYLEcenter ] isStruckout [ "Answer whether the text to which these attributes are applied is struckout" ^self hasStyle: #STYLEstrikeout ] isUnderlined [ "Answer whether the text to which these attributes are applied is underlined" ^self hasStyle: #STYLEunderline ] strikeout [ "Strike out the text to which these attributes are applied" self style: #STYLEstrikeout ] underline [ "Underline the text to which these attributes are applied" self style: #STYLEunderline ] ] Object subclass: BTextTags [ | client tags | BTextTags class >> new [ self shouldNotImplement ] BTextTags class >> new: client [ ^super new initialize: client ] bgColor: color [ ^'b_' , (self color: color) ] events: aBTextBindings [ | tagName | tagName := aBTextBindings tagName. (tags includes: tagName) ifFalse: [tags add: tagName. aBTextBindings defineTagFor: client]. ^tagName ] fgColor: color [ ^'f_' , (self color: color) ] font: font [ | tagName | tagName := WriteStream on: (String new: 20). font substrings do: [:each | tagName nextPutAll: each; nextPut: $_]. tagName := tagName contents. (tags includes: tagName) ifFalse: [tags add: tagName. 'FIXME fonts.. ' display. font printNl. client defineTag: tagName as: {'font'. font. nil}]. ^tagName ] color: color [ | tagName | tagName := (color at: 1) = $# ifTrue: [(color copy) at: 1 put: $_; yourself] ifFalse: [color asLowercase]. (tags includes: tagName) ifFalse: [tags add: tagName. client defineTag: 'f_' , tagName as: {'foreground'. color. nil}. client defineTag: 'b_' , tagName as: {'background'. color. nil}]. ^tagName ] initialize: clientBText [ "initialise for use with clientBText" client := clientBText. tags := Set new. client defineTag: 'STYLEstrikeout' as: {'strikethrough'. true. nil}. client defineTag: 'STYLEunderline' as: {'underline'. GTK.Pango pangoUnderlineSingle. nil}. client defineTag: 'STYLEcenter' as: {'justification'. GTK.Gtk gtkJustifyCenter. nil} ] tagTable [ ^client gtkbuffer getTagTable ] ] "-------------------------- BText class -----------------------------" "-------------------------- BTextBindings class -----------------------------" "-------------------------- BTextAttributes class -----------------------------" "-------------------------- BTextTags class -----------------------------" smalltalk-3.2.5/packages/blox/gtk/Blox.st0000644000175000017500000000262612123404352015213 00000000000000"====================================================================== | | Smalltalk Gtk-based GUI building blocks (loading script). | | ======================================================================" "====================================================================== | | Copyright 1992, 1994, 1995, 1999, 2000, 2001, 2002 | Free Software Foundation, Inc. | Written by Paolo Bonzini. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LESSER. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" Eval [ ObjectMemory addDependent: BLOX.Blox. BLOX.Blox update: #returnFromSnapshot ] smalltalk-3.2.5/packages/blox/gtk/stamp-classes0000644000175000017500000000000012123404352016421 00000000000000smalltalk-3.2.5/packages/blox/gtk/package.xml0000644000175000017500000000043412123404352016047 00000000000000 BloxGTK BLOX GTK Blox BloxBasic.st BloxWidgets.st BloxText.st BloxExtend.st Blox.st smalltalk-3.2.5/packages/blox/browser/0000755000175000017500000000000012130456010014703 500000000000000smalltalk-3.2.5/packages/blox/browser/Makefile.frag0000644000175000017500000000204112123404352017202 00000000000000BLOXBrowser_FILES = \ packages/blox/browser/BrowShell.st packages/blox/browser/Inspector.st packages/blox/browser/Notifier.st packages/blox/browser/View.st packages/blox/browser/BrowserMain.st packages/blox/browser/Load.st packages/blox/browser/PCode.st packages/blox/browser/bear.gif packages/blox/browser/ClassBrow.st packages/blox/browser/Manager.st packages/blox/browser/PList.st packages/blox/browser/ButtonForm.st packages/blox/browser/ClassHierBrow.st packages/blox/browser/Menu.st packages/blox/browser/PText.st packages/blox/browser/DebugSupport.st packages/blox/browser/Debugger.st packages/blox/browser/MethInspect.st packages/blox/browser/RadioForm.st packages/blox/browser/NamespBrow.st packages/blox/browser/DictInspect.st packages/blox/browser/MethSetBrow.st packages/blox/browser/GuiData.st packages/blox/browser/ModalDialog.st packages/blox/browser/StrcInspect.st packages/blox/browser/ChangeLog $(BLOXBrowser_FILES): $(srcdir)/packages/blox/browser/stamp-classes: $(BLOXBrowser_FILES) touch $(srcdir)/packages/blox/browser/stamp-classes smalltalk-3.2.5/packages/blox/browser/DebugSupport.st0000644000175000017500000001445012123404352017626 00000000000000"====================================================================== | | Smalltalk GUI debugger support | | ======================================================================" "====================================================================== | | Copyright 2002 Free Software Foundation, Inc. | Written by Paolo Bonzini. | | This file is part of GNU Smalltalk. | | GNU Smalltalk is free software; you can redistribute it and/or modify it | under the terms of the GNU General Public License as published by the Free | Software Foundation; either version 2, or (at your option) any later version. | | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS | FOR A PARTICULAR PURPOSE. See the GNU General Public License for more | details. | | You should have received a copy of the GNU General Public License along with | GNU Smalltalk; see the file COPYING. If not, write to the Free Software | Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. | ====================================================================== " STInST.STInST.RBProgramNodeVisitor subclass: VariableNames [ | varNames current optimizedBlocks | VariableNames class >> on: method [ "Parse aString and return a collection of collections of variable names. Each collection corresponds to a site where arguments and/or temporaries can be defined (that is, the method and each of the non-optimized blocks). The first, in particular, lists arguments and temporaries for the method, the second lists them for the first non-optimized block, and so on." ^(self new) initialize; visitNode: (method parserClass parseMethod: method methodSourceString); varNames ] addScope [ "Add a new collection of variable names." varNames add: (current := OrderedCollection new) ] initialize [ optimizedBlocks := 0. varNames := OrderedCollection new. self addScope ] varNames [ ^varNames ] visitArgument: node [ "Found a variable definition. Record it." current addLast: node name ] acceptBlockNode: aBlockNode [ "Check if the block is open-coded. If not, add an item to varNames which will record arguments and temporaries for aBlockNode. If it is open coded, instead, variables are added to the current list of variable names." | optBlocks | optBlocks := optimizedBlocks. optimizedBlocks := 0. optBlocks > 0 ifTrue: [optBlocks := optBlocks - 1] ifFalse: [self addScope]. super acceptBlockNode: aBlockNode. optimizedBlocks := optBlocks ] acceptMessageNode: node [ "Check which of the receiver and arguments are open-coded blocks. Before visiting the children of the node, we set optimizedBlocks to a number > 0 if we find an open-coded block." node receiver isBlock ifTrue: [self checkIfOptimizedBlockClosureMessage: node]. self visitNode: node receiver. self checkIfOptimizedTest: node. node arguments do: [:each | each isBlock ifTrue: [self checkIfOptimizedToDo: node]. self visitNode: each] ] checkIfOptimizedToDo: node [ "Increase optimizedBlocks if node is an open-coded #to:do:, #timesRepeat: or #to:by:do: message send." (node selector == #to:do: or: [node selector == #timesRepeat: or: [node selector == #to:by:do: and: [(node arguments at: 2) isLiteral]]]) ifFalse: [^self]. (self isOptimizedBlockClosure: node arguments last args: 1) ifFalse: [^self]. optimizedBlocks := optimizedBlocks + 1 ] isOptimizedBlockClosure: block args: numArgs [ "Answer whether block is an RBBlockNode with no temporaries and numArgs arguments." ^block isBlock and: [block body temporaries isEmpty and: [block arguments size = numArgs]] ] checkIfOptimizedTest: node [ "Increase optimizedBlocks if node is an open-coded Boolean test." (#(#ifTrue: #ifTrue:ifFalse: #ifFalse:ifTrue: #ifFalse: #and: #or:) includes: node selector) ifFalse: [^self]. (node arguments allSatisfy: [:each | self isOptimizedBlockClosure: each args: 0]) ifFalse: [^self]. optimizedBlocks := optimizedBlocks + node arguments size ] checkIfOptimizedBlockClosureMessage: node [ "Increase optimizedBlocks if node is an open-coded while loop." (#(#whileTrue #whileTrue: #whileFalse #whileFalse: #repeat) includes: node selector) ifFalse: [^self]. (self isOptimizedBlockClosure: node receiver args: 0) ifFalse: [^self]. (node arguments allSatisfy: [:each | self isOptimizedBlockClosure: each args: 0]) ifFalse: [^self]. optimizedBlocks := optimizedBlocks + node arguments size + 1 ] ] ContextPart extend [ variableNames [ ^self method variableNames ] ] CompiledCode extend [ variableNames [ "Answer the names of the arguments and temporaries in the receiver. By default, only numbers are produced." ^(1 to: self numArgs + self numTemps) collect: [:each | each printString] ] ] CompiledMethod extend [ variableNames [ "Answer the names of the arguments and temporaries in the receiver." | source | source := self methodSourceString. source isNil ifTrue: [^super variableNames]. ^(BLOX.BLOXBrowser.VariableNames on: self) at: 1 ] ] CompiledBlock extend [ variableNames [ "Answer the names of the arguments and temporaries in the receiver." | source index | self numArgs + self numTemps = 0 ifTrue: [^#()]. source := self methodSourceString. source isNil ifTrue: [^super variableNames]. "Find how many blocks are there in the method before the receiver." index := 2. self literals keysAndValuesDo: [:i :each | each class == BlockClosure ifTrue: [each block == self ifTrue: ["Ok, now parse the source code." ^(BLOX.BLOXBrowser.VariableNames on: self method) at: index]. index := index + 1]]. ^super variableNames ] ] smalltalk-3.2.5/packages/blox/browser/RadioForm.st0000644000175000017500000000534012123404352017063 00000000000000"====================================================================== | | Smalltalk GUI wrapper for radio button groups | | ======================================================================" "====================================================================== | | Copyright 1992,94,95,99,2000,2001,2002 Free Software Foundation, Inc. | Written by Brad Diller. | | This file is part of GNU Smalltalk. | | GNU Smalltalk is free software; you can redistribute it and/or modify it | under the terms of the GNU General Public License as published by the Free | Software Foundation; either version 2, or (at your option) any later version. | | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS | FOR A PARTICULAR PURPOSE. See the GNU General Public License for more | details. | | You should have received a copy of the GNU General Public License along with | GNU Smalltalk; see the file COPYING. If not, write to the Free Software | Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. | ====================================================================== " Primitive subclass: PRadioButton [ | state isPressedMsg | PRadioButton class >> on: data parentView: sv isPressed: isPressedSelector label: label handleUserChange: changeSelector value: onValue [ | view | view := self new. view parentView: sv. view data: data. view isPressed: isPressedSelector; state: onValue. view handleUserChange: changeSelector. view initBlox: label. ^view ] isPressed [ "Return current switch state." ^(data perform: isPressedMsg) = state ] state [ ^state ] state: value [ state := value ] initBlox: aLabel [ blox := BRadioButton new: parentView label: aLabel. blox value: self isPressed. blox callback: self message: 'toggle:' ] isPressed: isPressedSelector [ isPressedMsg := isPressedSelector ] toggle: btnState [ "Send the modification message to the data object" self isPressed ifTrue: [^self]. (stateChangeMsg notNil and: [self canChangeState]) ifTrue: [data perform: stateChangeMsg with: state] ] ] Form subclass: RadioForm [ RadioForm class >> new: aString in: view [ | aView | aView := self new. aView parentView: view. aView blox: (BRadioGroup new: view blox). ^aView ] ] smalltalk-3.2.5/packages/blox/browser/Menu.st0000644000175000017500000000740212123404352016106 00000000000000"====================================================================== | | Smalltalk GUI wrapper for menus | | ======================================================================" "====================================================================== | | Copyright 1992,94,95,99,2000,2001,2002,2003 Free Software Foundation, Inc. | Written by Brad Diller. | | This file is part of GNU Smalltalk. | | GNU Smalltalk is free software; you can redistribute it and/or modify it | under the terms of the GNU General Public License as published by the Free | Software Foundation; either version 2, or (at your option) any later version. | | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS | FOR A PARTICULAR PURPOSE. See the GNU General Public License for more | details. | | You should have received a copy of the GNU General Public License along with | GNU Smalltalk; see the file COPYING. If not, write to the Free Software | Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. | ====================================================================== " BLOX.Gui subclass: Menu [ Menu class >> new: view label: title [ | aMenu | aMenu := Menu new. aMenu blox: (BMenu new: view menuBar label: title). ^aMenu ] replaceArgWith: arg in: selectorsArray [ | selectors | selectors := selectorsArray deepCopy. "(label unarySelector (... submenu ...)) should not be changed (label keywordSelector arg) should be changed (label keywordSelector arg (... submenu ...)) should be changed" selectorsArray with: selectors do: [:item :changed | (item size > 2 and: [(item at: 2) numArgs >= 1]) ifTrue: [changed at: 3 put: arg]. (item size > 1 and: [item last isArray]) ifTrue: [changed at: changed size put: (self replaceArgWith: arg in: item last)]]. ^selectors ] selectors: selectors receiver: receiver [ blox callback: receiver using: selectors ] selectors: selectors receiver: receiver argument: arg [ blox callback: receiver using: (self replaceArgWith: arg in: selectors) ] ] Menu subclass: PopupMenu [ | windowMenu | PopupMenu class >> new: view [ ^self new: view label: nil ] PopupMenu class >> new: view label: title [ | aMenu blox theTitle | aMenu := self new. theTitle := (title notNil and: [title isEmpty]) ifTrue: [nil] ifFalse: [title]. blox := theTitle isNil ifTrue: [BPopupMenu new: view blox label: ''] ifFalse: [BPopupMenu new: view blox label: theTitle]. aMenu blox: blox. "We were given a menu name, add to the menu bar as well" theTitle isNil ifFalse: [aMenu windowMenu: (Menu new: view rootView label: theTitle). view rootView menu: aMenu windowMenu]. ^aMenu ] windowMenu [ ^windowMenu ] windowMenu: aMenu [ windowMenu := aMenu ] selectors: selectorsArray receiver: receiver [ super selectors: selectorsArray receiver: receiver. windowMenu isNil ifFalse: [windowMenu selectors: selectorsArray receiver: receiver] ] selectors: selectorsArray receiver: receiver argument: arg [ super selectors: selectorsArray receiver: receiver argument: arg. windowMenu isNil ifFalse: [windowMenu selectors: selectorsArray receiver: receiver argument: arg] ] ] smalltalk-3.2.5/packages/blox/browser/PCode.st0000644000175000017500000003542112123404352016176 00000000000000"====================================================================== | | Smalltalk GUI wrapper for method source code widgets | | ======================================================================" "====================================================================== | | Copyright 1992,94,95,99,2000,2001,2002,2003,2007 | Free Software Foundation, Inc. | Written by Paolo Bonzini. | | This file is part of GNU Smalltalk. | | GNU Smalltalk is free software; you can redistribute it and/or modify it | under the terms of the GNU General Public License as published by the Free | Software Foundation; either version 2, or (at your option) any later version. | | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS | FOR A PARTICULAR PURPOSE. See the GNU General Public License for more | details. | | You should have received a copy of the GNU General Public License along with | GNU Smalltalk; see the file COPYING. If not, write to the Free Software | Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. | ====================================================================== " BLOX.BText subclass: BCode [ | class line highlighted source variables pools temps isMethod highlightBlock | Colors := nil. Highlight := nil. BCode class >> highlight [ ^Highlight ] BCode class >> highlight: aBoolean [ Highlight := aBoolean ] BCode class >> colorAt: aSymbol [ ^Colors at: aSymbol ifAbsent: [nil] ] BCode class >> colorAt: aSymbol put: aColor [ ^Colors at: aSymbol put: (BTextAttributes foregroundColor: aColor) ] BCode class >> initializeColors [ Colors := IdentityDictionary new: 32. self highlight: true. self colorAt: #classVar put: 'cyan4'; colorAt: #globalVar put: 'cyan4'; colorAt: #poolVar put: 'cyan4'; colorAt: #undeclaredVar put: 'red'; colorAt: #instanceVar put: 'black'; colorAt: #argument put: 'black'; colorAt: #temporary put: 'black'; colorAt: #specialId put: 'grey50'; colorAt: #literal put: 'grey50'; colorAt: #temporaries put: 'magenta'; colorAt: #methodHeader put: 'magenta'; colorAt: #primitive put: 'magenta'; colorAt: #arguments put: 'magenta'; colorAt: #special put: 'magenta'; colorAt: #unaryMsg put: 'magenta4'; colorAt: #binaryMsg put: 'chocolate4'; colorAt: #keywordMsg put: 'NavyBlue'; colorAt: #comment put: 'SpringGreen4' ] checkLine: unused [ | oldLine | oldLine := line. line := self currentLine. line ~= oldLine & highlighted not ifTrue: [self rehighlight] ] create [ super create. self inClass: UndefinedObject. highlighted := false. self onKeyUpEventSend: #checkLine: to: self. self onMouseUpEvent: 1 send: #checkLine: to: self ] invokeCallback [ highlighted ifTrue: [self blackLine]. super invokeCallback ] highlightAs: kind from: start to: end [ highlightBlock value: (BCode colorAt: kind) value: start value: end ] highlightAs: kind pos: pos [ pos isNil ifTrue: [^self]. self highlightAs: kind from: pos to: pos ] highlightNewVariable: name from: start to: end as: kind [ temps at: name put: kind. self highlightAs: kind from: start to: end ] highlightVariable: name from: start to: end [ self highlightAs: (self variableKind: name) from: start to: end ] blackLine [ highlighted := false. self removeAttributesFrom: 1 @ line to: 1 @ (line + 1) ] classifyNewVariable: var [ pools keysAndValuesDo: [:pool :kind | (pool includesKey: var) ifTrue: [^kind]]. ^(var at: 1) isUppercase ifTrue: [#globalVar] ifFalse: [#undeclaredVar] ] declareVariables: aCollection in: dictionary as: kind [ aCollection do: [:each | dictionary at: each asString put: kind] ] rehighlight [ self class highlight ifFalse: [^self]. self removeAttributes; highlight ] highlight [ self class highlight ifFalse: [^self]. self highlightSyntax. highlighted := true ] highlightBlockClosure [ | sourceStream nlPos lineNumber | lineNumber := 0. sourceStream := ReadStream on: source. ^ [:color :start :end | | startPos endPos | [start > sourceStream position] whileTrue: [lineNumber := lineNumber + 1. nlPos := sourceStream position. sourceStream skipTo: Character nl]. startPos := (start - nlPos) @ lineNumber. [end > sourceStream position] whileTrue: [lineNumber := lineNumber + 1. nlPos := sourceStream position. sourceStream skipTo: Character nl]. endPos := (end - nlPos + 1) @ lineNumber. self setAttributes: color from: startPos to: endPos] ] parserClass [ ^STInST.RBBracketedMethodParser ] highlightSyntax [ | parser | source = self contents ifFalse: ["FIXME: this is wrong, something is being dropped elsewhere with respect to content updates" source := self contents]. parser := (self parserClass new) errorBlock: [:string :pos | ^self]; initializeParserWith: source type: #on:errorBlock:; yourself. isMethod ifTrue: [self highlight: parser parseMethod] ifFalse: [[parser atEnd] whileFalse: [self highlight: (parser parseStatements: false). parser step "gobble doit terminating bang"]] ] highlight: node [ [| color commentsNode | temps := LookupTable new. highlightBlock := self highlightBlockClosure. SyntaxHighlighter highlight: node in: self. commentsNode := STInST.RBProgramNode new copyCommentsFrom: node. commentsNode comments isNil ifTrue: [^self]. color := BCode colorAt: #comment. highlightBlock := self highlightBlockClosure. commentsNode comments do: [:each | highlightBlock value: color value: each first value: each last]] ensure: [temps := highlightBlock := nil] ] inClass: aClass [ class == aClass ifTrue: [^self]. class := aClass. self initVariableClassification. self declareVariables: class allClassVarNames in: variables as: #classVar. self declareVariables: class allInstVarNames in: variables as: #instanceVar. class withAllSuperclassesDo: [:each | pools at: class environment put: #globalVar. class sharedPools do: [:pool | pools at: (class environment at: pool) put: #poolVar]] ] initVariableClassification [ variables := LookupTable new. "variable String -> its kind" pools := IdentityDictionary new. "Dictionary -> kind of variables in it" variables at: 'self' put: #specialId; at: 'super' put: #specialId; at: 'thisContext' put: #specialId ] variableKind: var [ ^temps at: var ifAbsentPut: [variables at: var ifAbsent: [self classifyNewVariable: var]] ] contents: textOrAssociation [ | newClass | line := 1. highlighted := false. (textOrAssociation isKindOf: Association) ifTrue: [source := textOrAssociation value. newClass := textOrAssociation key. isMethod := true] ifFalse: [source := textOrAssociation. newClass := UndefinedObject. isMethod := false]. super contents: source. self inClass: newClass; highlight ] ] STInST.STInST.RBProgramNodeVisitor subclass: SyntaxHighlighter [ | widget | SyntaxHighlighter class >> highlight: node in: aBCodeWidget [ (self new) widget: aBCodeWidget; visitNode: node ] widget: aBCodeWidget [ widget := aBCodeWidget ] acceptArrayNode: anArrayNode [ "widget highlightAs: #special at: anArrayNode left." self visitNode: anArrayNode body "widget highlightAs: #special at: anArrayNode right" ] acceptAssignmentNode: anAssignmentNode [ self acceptVariableNode: anAssignmentNode variable. "widget highlightAs: #special from: anAssignment assignment to: anAssignmentNode assignment + 1." self visitNode: anAssignmentNode value ] acceptBlockNode: aBlockNode [ "widget highlightAs: #special at: aBlockNode left." aBlockNode colons with: aBlockNode arguments do: [:colonPos :argument | "widget highlightAs: #special at: colonPos." self highlightNewVariable: argument as: #argument]. "aBlockNode bar isNil ifFalse: [ widget highlightAs: #special at: aBlockNode bar. ]." self visitNode: aBlockNode body "widget highlightAs: #special at: aBlockNode right" ] acceptCascadeNode: aCascadeNode [ | n | n := 0. self visitNode: aCascadeNode messages first receiver. aCascadeNode messages do: [:each | self highlightMessageSend: each "separatedBy: [ | semi | semi := aCascadeNode semicolons at: (n := n + 1) widget highlightAs: #special at: semi ]"] ] acceptLiteralNode: aLiteralNode [ widget highlightAs: #literal from: aLiteralNode start to: aLiteralNode stop ] acceptMessageNode: aMessageNode [ self visitNode: aMessageNode receiver. self highlightMessageSend: aMessageNode ] acceptMethodNode: aMethodNode [ "A pity we cannot share this code with highlightMessageSend: ..." aMethodNode isUnary ifTrue: [widget highlightAs: #unaryMsg from: aMethodNode selectorParts first start to: aMethodNode selectorParts first stop]. aMethodNode isBinary ifTrue: [widget highlightAs: #binaryMsg from: aMethodNode selectorParts first start to: aMethodNode selectorParts first stop. self highlightNewVariable: aMethodNode arguments first as: #argument]. aMethodNode isKeyword ifTrue: [aMethodNode selectorParts with: aMethodNode arguments do: [:sel :arg | widget highlightAs: #binaryMsg from: sel start to: sel stop. self highlightNewVariable: arg as: #argument]]. self visitNode: aMethodNode body ] acceptOptimizedNode: aBlockNode [ "widget highlightAs: #special from: aBlockNode left to: aBlockNode + 2." self visitNode: aBlockNode body "widget highlightAs: #special at: aBlockNode right" ] acceptReturnNode: aReturnNode [ "widget highlightAs: #special at: anArrayNode start." self visitNode: aReturnNode value ] acceptSequenceNode: aSequenceNode [ | n | n := 0. "widget highlightAs: #special at: aSequenceNode leftBar." aSequenceNode temporaries do: [:temporary | "widget highlightAs: #special at: colonPos." self highlightNewVariable: temporary as: #temporary]. "widget highlightAs: #special at: aSequenceNode rightBar." aSequenceNode statements do: [:each | self visitNode: each "separatedBy: [ | period | period := aSequenceNode periods at: (n := n + 1) widget highlightAs: #special at: period ]" "n < aSequenceNode periods size ifTrue: [ widget highlightAs: #special at: aSequenceNode periods last ]."] ] acceptVariableNode: aVariableNode [ widget highlightVariable: aVariableNode name from: aVariableNode start to: aVariableNode stop ] highlightMessageSend: aMessageNode [ aMessageNode isUnary ifTrue: [widget highlightAs: #unaryMsg from: aMessageNode selectorParts first start to: aMessageNode selectorParts first stop. ^self]. aMessageNode isBinary ifTrue: [widget highlightAs: #binaryMsg from: aMessageNode selectorParts first start to: aMessageNode selectorParts first stop. self visitNode: aMessageNode arguments first. ^self]. aMessageNode selectorParts with: aMessageNode arguments do: [:sel :arg | widget highlightAs: #binaryMsg from: sel start to: sel stop. self visitNode: arg] ] highlightNewVariable: node as: kind [ widget highlightNewVariable: node name from: node start to: node stop as: kind ] ] PText subclass: PCode [ PCode class >> bloxClass [ ^BCode ] implementorsFrom: position [ | symbol | symbol := self getMessageAt: position. symbol isNil ifTrue: [Blox beep. ^self]. MethodSetBrowser implementorsOf: symbol parent: self ] sendersFrom: position [ | symbol | symbol := self getMessageAt: position. symbol isNil ifTrue: [Blox beep. ^self]. MethodSetBrowser sendersOf: symbol parent: self ] getMessageAt: position [ "This is so easy to do with the Refactoring Browser's parse nodes!!!" "First, we must map line/row to the actual index in the source code." | stream pos parser node | stream := ReadStream on: blox contents. position y - 1 timesRepeat: [stream nextLine]. stream skip: position x - 1. pos := stream position. stream reset. parser := RBParser new. parser errorBlock: [:message :position | ^nil]. parser scanner: (parser scannerClass on: stream errorBlock: parser errorBlock). node := parser parseMethod body. node := node bestNodeFor: (pos to: pos + 1). [node isMessage] whileFalse: [node := node parent. node isNil ifTrue: [^nil]]. ^node selector ] implementors [ ^self implementorsFrom: blox currentPosition ] senders [ ^self sendersFrom: blox currentPosition ] compileIt [ super compileIt. self blox rehighlight ] ] Eval [ BCode initializeColors ] smalltalk-3.2.5/packages/blox/browser/Debugger.st0000644000175000017500000003024512123404352016727 00000000000000"====================================================================== | | Smalltalk GUI debugger window | | ======================================================================" "====================================================================== | | Copyright 1992,94,95,99,2000,2001,2002,2003,2007 | Free Software Foundation, Inc. | Written by Brad Diller and Paolo Bonzini. | | This file is part of GNU Smalltalk. | | GNU Smalltalk is free software; you can redistribute it and/or modify it | under the terms of the GNU General Public License as published by the Free | Software Foundation; either version 2, or (at your option) any later version. | | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS | FOR A PARTICULAR PURPOSE. See the GNU General Public License for more | details. | | You should have received a copy of the GNU General Public License along with | GNU Smalltalk; see the file COPYING. If not, write to the Free Software | Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. | ====================================================================== " GuiData subclass: Debugger [ | stacktrace contexts debugger activeContext receiverInspector stackInspector listView theClass theMethod textView topView | Debugger class >> debuggerClass [ ^nil ] Debugger class >> debuggingPriority [ ^1 ] Debugger class >> new: notifier [ ^self new init: notifier ] init: notifier [ debugger := notifier debugger. [debugger suspendedContext isInternalExceptionHandlingContext] whileTrue: [debugger slowFinish]. self createWindowFrom: notifier ] createWindowFrom: notifier [ | toplevel container text buttonView lowerpane pane list context urpane lrpane | topView := (BrowserShell new: 'Debugger') data: self. toplevel := topView blox. toplevel x: 20 y: 50 width: 500 height: 350. pane := Form new: 'panes' in: topView. topView addChildView: pane. pane blox width: 500 height: 125. pane addChildView: ((listView := PList new: 'MethodSet' in: pane) initialize; data: self; listMsg: #stacktrace; dataMsg: #contexts; handleUserChange: #contextSelectedFrom:; stateChange: #stacktrace; yourself). listView menuInit: ((PopupMenu new: listView label: 'Debug') selectors: self debugSelectors receiver: self). listView blox width: 300 height: 100. pane addChildView: ((buttonView := ButtonForm new: 'Debugging' in: pane) selectors: self debugSelectors receiver: self; yourself). buttonView blox x: 0 y: 100 width: 300 height: 25. urpane := Form new: 'panes' in: pane. pane addChildView: urpane. urpane blox width: 200 height: 125. urpane blox posHoriz: listView blox. lowerpane := Form new: 'panes' in: topView. lowerpane blox posVert: pane blox. lowerpane blox width: 500 height: 225. topView addChildView: lowerpane. lowerpane addChildView: ((textView := PCode new: lowerpane) data: self; stateChange: #text; handleUserChange: #compile:from:; setBrowserKeyBindings; textMsg: #text; yourself). textView menuInit: ((PopupMenu new: textView label: 'Edit') selectors: #(#('Cut' #gstCut) #('Copy' #gstCopy) #('Paste' #gstPaste) #() #('Clear' #gstClear) #() #('Line...' #line) #('Find...' #find) #() #('Do it' #eval) #('Print it' #evalAndPrintResult) #('Inspect' #evalAndInspectResult) #() #('Senders' #senders) #('Implementors' #implementors) #() #('Accept' #compileIt) #('Cancel' #revert) #() #('Close' #close)) receiver: textView argument: nil). text := textView blox. text width: 300 height: 225. lrpane := Form new: 'panes' in: lowerpane. lowerpane addChildView: lrpane. lrpane blox width: 200 height: 225. lrpane blox posHoriz: textView blox. stackInspector := (Inspector new) fieldLists: (self stackFieldListsFor: notifier currentContext); openIn: urpane menuName: 'Stack'. receiverInspector := (Inspector new) fieldLists: (self receiverFieldListsFor: notifier currentContext receiver); openIn: lrpane menuName: 'Receiver'. self updateContextList. self currentContext: notifier currentContext. topView display ] receiverFieldListsFor: anObject [ ^{'Primitive' -> (PrimitiveInspectorFieldList new value: anObject)} , anObject inspectorFieldLists ] stackFieldListsFor: context [ ^ {'Variables' -> (StackInspectorFieldList new value: context). 'Stack' -> (ObjectInspectorFieldList new value: context)} ] compile: aString from: aView [ "Compile aString derived from text in text view for the selected selector" theMethod notNil ifTrue: [theClass compile: aString classified: theMethod methodCategory ifError: [:fname :lineNo :errorString | aView displayError: errorString at: lineNo. ^nil]] ] contextSelectedFrom: assoc [ self currentContext: assoc value ] highlight: context [ | line | line := context currentLine. (textView blox) gotoLine: line end: false; selectFrom: 1 @ line to: 1 @ (line + 1) ] contexts [ ^contexts ] stacktrace [ ^stacktrace ] text [ "Return source code for the selected method" | source | ^(theMethod notNil and: [(source := theMethod methodSourceString) notNil]) ifTrue: [theClass -> source] ifFalse: [''] ] debugSelectors [ ^#(#('Step' #stepButtonCallback) #('Next' #nextButtonCallback) #('Finish' #finishButtonCallback) #('Continue' #continueButtonCallback) #() #('Kill' #killButtonCallback) #() #('Terminate' #terminateButtonCallback)) ] updateAfter: aBlock [ "If there's an exception, replace this window with another notifier." aBlock on: SystemExceptions.DebuggerReentered do: [:ex | topView close. Notifier openOn: debugger process. ^self]. self updateContextList ] stepButtonCallback [ self updateAfter: [debugger step] ] nextButtonCallback [ self updateAfter: [debugger next] ] finishButtonCallback [ self updateAfter: [debugger finish: activeContext] ] continueButtonCallback [ topView close. debugger continue ] killButtonCallback [ topView close. debugger process primTerminate ] terminateButtonCallback [ topView close. debugger process terminate. debugger continue ] updateContextList [ | context lastContext | context := debugger suspendedContext. lastContext := context environment. stacktrace := OrderedCollection new. contexts := OrderedCollection new. [context == lastContext] whileFalse: [context isDisabled ifFalse: [stacktrace add: context printString. contexts add: context]. context := context parentContext]. self changeState: #stacktrace. self currentContext: debugger suspendedContext ] currentContext: context [ activeContext := context. theMethod := context method. theClass := context methodClass. stackInspector fieldLists: (self stackFieldListsFor: context). receiverInspector fieldLists: (self receiverFieldListsFor: context receiver). self changeState: #text. Primitive updateViews. self highlight: context ] ] ObjectInspectorFieldList subclass: PrimitiveInspectorFieldList [ validSize: anObject [ ^((self primClass: anObject) inheritsFrom: ContextPart) ifTrue: [self prim: anObject instVarAt: ContextPart spIndex] ifFalse: [self primBasicSize: anObject] ] prim: anObject instVarAt: anIndex [ "Answer the index-th indexed variable of anObject." self primitiveFailed ] prim: anObject instVarAt: anIndex put: value [ "Store value in the index-th instance variable of anObject." self primitiveFailed ] prim: anObject basicAt: anIndex [ "Answer the index-th indexed instance variable of anObject." self primitiveFailed ] prim: anObject basicAt: anIndex put: value [ "Store value in the index-th indexed instance variable of anObject." self primitiveFailed ] primBasicAt: anIndex [ ^((self primClass: self value) inheritsFrom: Object) ifTrue: [self value basicAt: anIndex] ifFalse: [self prim: self value basicAt: anIndex] ] primBasicAt: anIndex put: anObject [ ^((self primClass: self value) inheritsFrom: Object) ifTrue: [self value basicAt: anIndex put: anObject] ifFalse: [self prim: self value basicAt: anIndex put: anObject] ] primBasicSize: anObject [ "Answer the number of indexed instance variable in anObject" ] primClass: anObject [ "Answer the class of anObject" ] currentFieldValue: obj [ currentField > base ifTrue: [self primBasicAt: currentField - base put: obj] ifFalse: [self prim: self value instVarAt: currentField - 1 put: obj] ] currentFieldValue [ currentField == 0 ifTrue: [^nil]. currentField == 1 ifTrue: [^self value]. ^currentField > base ifTrue: [self primBasicAt: currentField - base] ifFalse: [self prim: self value instVarAt: currentField - 1] ] computeFieldList: anObject [ "Store a string representation of the inspected object, anObject, in fields. The first string is self. The subsequent values are the object's complete set of instance variables names. If the object is a variable class, append numerical indices from one to number of indexed variables" | instVarNames class | fields add: 'self'. class := self primClass: anObject. instVarNames := class allInstVarNames. 1 to: instVarNames size do: [:x | fields add: (instVarNames at: x) asString]. base := fields size. class isVariable ifTrue: [1 to: (self validSize: anObject) do: [:x | fields add: x printString]] ] ] InspectorFieldList subclass: StackInspectorFieldList [ | vars | currentFieldValue: obj [ | variable | currentField < 2 ifTrue: [^self]. variable := vars at: currentField - 1. ^variable key at: variable value put: obj ] currentFieldValue [ "Return value at currently selected key" | variable | currentField == 0 ifTrue: [^nil]. currentField == 1 ifTrue: [^self value]. variable := vars at: currentField - 1. ^variable key at: variable value ] computeFieldList: anObject [ vars := OrderedCollection new. fields add: 'thisContext'. self setFieldsIn: anObject ] setFieldsIn: context [ | prefix numVars prefixSize | numVars := context numArgs + context numTemps. (context home == context or: [context outerContext == nil]) ifTrue: [prefixSize := -2] ifFalse: [prefixSize := self setFieldsIn: context outerContext]. numVars > 0 ifTrue: [prefixSize := prefixSize + 2]. prefix := String new: (prefixSize max: 0) withAll: $-. (1 to: numVars) with: context variableNames do: [:i :varName | fields add: prefix , varName. vars add: context -> i]. ^prefixSize ] ] smalltalk-3.2.5/packages/blox/browser/BrowserMain.st0000644000175000017500000001545412123404352017440 00000000000000"====================================================================== | | Smalltalk GUI `outside the classes' method | | ======================================================================" "====================================================================== | | Copyright 1992,94,95,99,2000,2001,2002 Free Software Foundation, Inc. | Written by Brad Diller. | | This file is part of GNU Smalltalk. | | GNU Smalltalk is free software; you can redistribute it and/or modify it | under the terms of the GNU General Public License as published by the Free | Software Foundation; either version 2, or (at your option) any later version. | | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS | FOR A PARTICULAR PURPOSE. See the GNU General Public License for more | details. | | You should have received a copy of the GNU General Public License along with | GNU Smalltalk; see the file COPYING. If not, write to the Free Software | Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. | ====================================================================== " GuiData subclass: BrowserMain [ Shell := nil. SavedState := nil. Windows := nil. HandleErrorsWithGui := nil. BrowserMain class >> addWindow: toplevel [ Windows add: toplevel ] BrowserMain class >> checkExit [ ^Windows isNil or: [Windows allSatisfy: [:w | w canClose]] ] BrowserMain class >> close [ "This method is invoked before quitting the browser and before saving the Smalltalk image. When the system is launched subsequently, it is important that the shell be nil until the browser is initialized. Other methods use the state of this variable (Shell) to probe the browser's initialization status" Shell := nil ] BrowserMain class >> handleErrorsWithGui [ ^HandleErrorsWithGui ] BrowserMain class >> handleErrorsWithGui: aBoolean [ HandleErrorsWithGui := aBoolean ] BrowserMain class >> removeWindow: toplevel [ Windows remove: toplevel ] BrowserMain class >> shell [ "Return application widget pointer. This method is used to determine whether the Tk and browser environment is initialized. If 'shell' is non-nil, the environment is completely initialized" ^Shell ] BrowserMain class >> update: aspect [ "There is no guarantee that the image will be loaded running the browser. So some variables must be nil'ed out. The class variable, 'Shell', is used, secondarily as a flag to indicate initialization status. If it is nil, the browser does not attempt to display a Notifier or some other type of window before the Tk and Smalltalk system has been initialized" aspect == #aboutToSnapshot ifTrue: [SavedState := Transcript message -> Shell. Transcript message: stdout -> #nextPutAllFlush:. self handleErrorsWithGui: false. Shell := nil]. aspect == #finishedSnapshot ifTrue: [SavedState isNil ifTrue: [^self]. Shell := SavedState value. self handleErrorsWithGui: true. Transcript message: SavedState key. SavedState := nil] ] BrowserMain class >> windowsDo: aBlock [ Windows do: aBlock ] BrowserMain class >> directQuit [ self checkExit ifFalse: [^self beep]. self shell release. Blox terminateMainLoop. ObjectMemory quit ] BrowserMain class >> garbageCollect [ "Force a full garbage collection in order to dispose of all unreferenced instances" ObjectMemory compact ] BrowserMain class >> fileIn [ | fileName | fileName := Prompter openFileName: 'Which file do you want me to read?' default: '*.st' in: Shell. fileName isNil ifFalse: [FileStream fileIn: fileName] ] BrowserMain class >> openBrowser [ ClassHierarchyBrowser new open ] BrowserMain class >> openNamespaceBrowser [ NamespaceBrowser new open ] BrowserMain class >> openWorksheet [ ^BrowserShell openWorksheet: 'Worksheet' ] BrowserMain class >> openWorksheet: label [ ^BrowserShell openWorksheet: label ] BrowserMain class >> quit [ "Quit Smalltalk browser" | exit | self checkExit ifFalse: [^self beep]. exit := false. (ModalDialog new) message: 'Save image before quitting?' in: self shell; addButton: 'Yes' message: [self saveImage. exit := true]; addButton: 'No' message: [exit := true]; addButton: 'Cancel' message: []; display: self shell. exit ifFalse: [^false]. self shell release. Blox terminateMainLoop. ObjectMemory quit. ^true ] BrowserMain class >> saveImageAs [ "Save a snapshot on a file the user chooses." | fileName | fileName := Prompter saveFileName: 'Save image as' default: ImageFileName in: Shell. fileName isNil ifFalse: [ObjectMemory snapshot: fileName. ImageFileName := fileName "Are we sure?"] ] BrowserMain class >> saveImage [ "Save a snapshot" ObjectMemory snapshot ] initialize [ "Initialize Tk environment. Create a transcript which will be used to operate the browser. It has a menu from which the user can select the desired menu option" | win transcriptAndShell | self class handleErrorsWithGui: false. Smalltalk addFeature: #EventLoop. Shell := nil. Windows := Set new. transcriptAndShell := BrowserShell openWorksheet: 'Smalltalk Transcript' withText: (Version copyWith: Character nl). (Smalltalk includesKey: #GTK) ifTrue: ['FIXME GTK bindings not ready for GUI transcript' printNl] ifFalse: [Transcript message: transcriptAndShell value -> #insertAtEnd:]. Shell := transcriptAndShell key. Shell data: self. win := Shell blox. win callback: self class message: #quit. self class handleErrorsWithGui: true. Shell display. Blox dispatchEvents. Shell blox exists ifTrue: [Shell blox destroy]. self class handleErrorsWithGui: false. Shell := nil ] addWindow: toplevel [ ^Windows add: toplevel ] removeWindow: toplevel [ ^Windows remove: toplevel ] ] Eval [ BrowserMain handleErrorsWithGui: false. ObjectMemory addDependent: BrowserMain ] smalltalk-3.2.5/packages/blox/browser/BrowShell.st0000644000175000017500000001005012123404352017074 00000000000000"====================================================================== | | Smalltalk GUI window base classs | | ======================================================================" "====================================================================== | | Copyright 1992,94,95,99,2000,2001,2002 Free Software Foundation, Inc. | Written by Paolo Bonzini. | | This file is part of GNU Smalltalk. | | GNU Smalltalk is free software; you can redistribute it and/or modify it | under the terms of the GNU General Public License as published by the Free | Software Foundation; either version 2, or (at your option) any later version. | | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS | FOR A PARTICULAR PURPOSE. See the GNU General Public License for more | details. | | You should have received a copy of the GNU General Public License along with | GNU Smalltalk; see the file COPYING. If not, write to the Free Software | Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. | ====================================================================== " Object subclass: BrowserShellMenuTemplate [ | label selectors handler | BrowserShellMenuTemplate class >> label: label selectors: anArray handler: aOneArgumentBlock [ ^self new label: label selectors: anArray handler: aOneArgumentBlock ] defineIn: aShell [ aShell menu: ((Menu new: aShell label: label) selectors: selectors receiver: (handler value: aShell) argument: aShell) ] label: aString selectors: anArray handler: aOneArgumentBlock [ label := aString. selectors := anArray. handler := aOneArgumentBlock ] ] TopLevelShell subclass: BrowserShell [ Menus := nil. BrowserShell class >> openWorksheet: label [ | aBText | aBText := (self openWorksheet: label withText: (String with: Character nl)) value. ^TextCollector message: aBText -> #insertAtEnd: ] BrowserShell class >> openWorksheet: label withText: startText [ "Open a worksheet window." | worksheet textView | worksheet := self new: label. worksheet addChildView: ((textView := PWorksheetText new: worksheet) menuInit: ((PopupMenu new: textView label: 'Edit') selectors: #(#('Cut' #gstCut) #('Copy' #gstCopy) #('Paste' #gstPaste) #() #('Clear' #gstClear) #() #('Line...' #line) #('Find...' #find) #() #('Do it' #eval) #('Print it' #evalAndPrintResult) #('Inspect' #evalAndInspectResult) #() #('Senders' #senders) #('Implementors' #implementors)) receiver: textView argument: nil); textMsg: #text; canBeDirty: false; yourself). textView blox contents: startText. textView setEvaluationKeyBindings. worksheet blox x: 0. worksheet blox y: 75. worksheet blox height: 175. worksheet blox width: 300. worksheet blox map. ^worksheet -> textView blox ] BrowserShell class >> addMenu: label selectors: anArray handler: aOneArgumentBlock [ Menus addLast: (BrowserShellMenuTemplate label: label selectors: anArray handler: aOneArgumentBlock) ] BrowserShell class >> initialize [ Menus := OrderedCollection new. self addMenu: 'Smalltalk' selectors: #(#('Worksheet' #openWorksheet) #('Class Hierarchy Browser' #openBrowser) #('Namespace Browser' #openNamespaceBrowser) #() #('Save image' #saveImage) #('Save image as...' #saveImageAs) #('Garbage collect' #garbageCollect) #() #('File in...' #fileIn) #() #('Exit without saving image' #directQuit) #('Exit...' #quit)) handler: [:shell | BrowserMain] ] initialize: aLabel [ super initialize: aLabel. Menus do: [:each | each defineIn: self] ] ] Eval [ BrowserShell initialize ] smalltalk-3.2.5/packages/blox/browser/DictInspect.st0000644000175000017500000001222712123404352017414 00000000000000"====================================================================== | | Smalltalk GUI inspector for Dictionaries | | ======================================================================" "====================================================================== | | Copyright 1992,94,95,99,2000,2001,2002 Free Software Foundation, Inc. | Written by Brad Diller. | | This file is part of GNU Smalltalk. | | GNU Smalltalk is free software; you can redistribute it and/or modify it | under the terms of the GNU General Public License as published by the Free | Software Foundation; either version 2, or (at your option) any later version. | | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS | FOR A PARTICULAR PURPOSE. See the GNU General Public License for more | details. | | You should have received a copy of the GNU General Public License along with | GNU Smalltalk; see the file COPYING. If not, write to the Free Software | Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. | ====================================================================== " InspectorFieldList subclass: DictionaryInspectorFieldList [ currentField: assoc [ "Set list selection to value of index. Force a text view update" assoc key <= 1 ifTrue: [currentField := assoc key] ifFalse: [currentField := fields at: assoc key] ] fieldsSortBlock [ ^[:a :b | a = 'self' or: [b ~= 'self' and: [a displayString <= b displayString]]] ] computeFieldList: anObject [ "Return sorted list of keys from set of Associations stored in fields" fields add: 'self'. fields addAll: anObject keys ] inspectMenu: listView [ "Initialize menu for variable list pane" ^(PopupMenu new: listView) selectors: #(#('Inspect' #evalAndInspectResult: #listView) #('References' #references: #listView) #() #('Add key...' #addField: #listView) #('Remove...' #removeField: #listView)) receiver: self argument: listView ] currentFieldValue: obj [ self value at: currentField put: obj ] currentFieldValue [ currentField == 0 ifTrue: [^nil]. currentField == 1 ifTrue: [^self value]. ^self value at: currentField ] addField: listView [ "Prompt user for the name of new dictionary key. If name is valid, add it to dictionary" | key | listView canChangeState ifFalse: [^self]. key := (Prompter message: 'Enter a new field' in: listView) response. key isEmpty ifTrue: [^self]. (key at: 1) == $# ifTrue: [key := (key copyFrom: 2 to: key size) asSymbol] ifFalse: [key isNumeric ifTrue: [key := key asNumber]]. "If new key already exists, reject" (self value includesKey: key) ifTrue: [^ModalDialog new alertMessage: 'Invalid name: the key, ' , key , ', already exists.' in: listView]. "Update variable selection" currentField := key. "Update dictionary" self value at: key put: nil. "Update instance variable governing variable list pane display" fields add: key. "Update text view" inspector changeState: #fieldList; changeState: #text. Primitive updateViews ] references: listView [ "Open a method set browser on all methods which reference selected key" | alert keyRefs theKey | currentField <= 1 ifTrue: [^listView beep]. keyRefs := SortedCollection new. Namespace current allClassObjectsDo: [:subclass | (subclass whichSelectorsReferTo: (self value associationAt: currentField)) do: [:sel | keyRefs add: subclass printString , ' ' , sel]]. keyRefs isEmpty ifTrue: [^alert := ModalDialog new alertMessage: 'No references to ' , currentField printString in: listView]. MethodSetBrowser new openOn: keyRefs title: 'References to ' , currentField printString selection: currentField displayString ] removeField: listView [ "Remove selected key from dictionary" | cancel | currentField isNil ifTrue: [^listView beep]. (ModalDialog new) message: 'Are you sure you want to remove, ' , currentField displayString , '?' in: listView; addButton: 'Yes' message: [cancel := false]; addButton: 'No' message: [cancel := true]; display: listView. cancel ifTrue: [^self]. "Remove key from dictionary" self value removeKey: currentField. "Remove the association composed of the key and the value from the data object" fields remove: currentField. currentField := 0. "Force a text view update to reflect deleted key" inspector changeState: #fieldList; changeState: #text. Primitive updateViews ] ] Dictionary extend [ inspectorFieldLists [ "Open a DictionaryInspectorFieldList window on self" ^ {'Keys' -> (BLOX.BLOXBrowser.DictionaryInspectorFieldList new value: self). 'Basic' -> (BLOX.BLOXBrowser.ObjectInspectorFieldList new value: self)} ] ] smalltalk-3.2.5/packages/blox/browser/ChangeLog0000644000175000017500000010020412123404352016376 000000000000002010-12-04 Paolo Bonzini * package.xml: Remove now superfluous tags. 2009-09-04 Paolo Bonzini * package.xml: Add tag. 2008-04-07 Paolo Bonzini * ClassHierBrow.st: Use #name after accessing variables. 2007-10-21 Paolo Bonzini * ClassHierBrow.st: Replace #sourceCodeAt: with #methodRecompilationSourceString. * MethSetBrow.st: Likewise. * PCode.st: Add #parserClass, use it. * DebugSupport.st: Make VariableNames class>>#on: accept a CompiledMethod in order to use its #parserClass. 2007-08-28 Paolo Bonzini * PCode.st: Turn FIXME into a comment. 2007-07-15 Paolo Bonzini * Debugger.st: Use DebugTools. * Notifier.st: Use DebugTools. * Load.st: Delimit namespaces with periods. 2007-07-11 Paolo Bonzini * Debugger.st: Highlight line 1 for nil context. 2007-06-25 Paolo Bonzini * ClassBrow.st: Use #%. * ClassHierBrow.st: Use #%. * Inspector.st: Use #%. * test.st: Use #%. 2007-03-20 Paolo Bonzini * ClassHierBrow.st: Check of the category changed after compiling a method. 2006-12-05 Paolo Bonzini *** Version 2.3 released. 2006-03-17 Paolo Bonzini Jiro Yamamoto * ClassHierBrow.st: Move the windows a bit off the top-left corner. * Debugger.st: Likewise. * Inspector.st: Likewise. * MethSetBrow.st: Likewise. * Notifier.st: Likewise. 2004-09-18 Paolo Bonzini * ButtonForm.st: Remove setting of the Helvetica font. * PList.st: Likewise. * PCode.st: Likewise. 2003-08-25 Paolo Bonzini * PCode.st: add senders and implementors that parse the current method. * ClassHierBrow.st: add them to context menus. * Debugger.st: likewise * MethSetBrow.st: likewise 2003-05-14 Jan Hidders * PCode.st: syntax highlight unary and binary methods correctly. 2003-05-09 Paolo Bonzini *** Version 2.1.2 released. 2003-05-08 Mike Anderson * PList.st: add methods to copy elements * Notifier.st: add menu items to copy stack trace 2003-04-17 Paolo Bonzini *** Version 2.1.1 (stable) released. 2003-04-12 Paolo Bonzini *** Version 2.1 (stable) released. 2003-03-25 Paolo Bonzini * PList.st: set selection = 0 when the contents of the list box are changed. 2003-03-23 Paolo Bonzini * PList.st: correctly send events when #select: is used. * ClassHierBrow.st: evaluate expressions in the context of the selected class. Rewritten "Search..." menu item. Remove Bytecodes and Hierarchy menu items, not so useful and they complicate the code unnecessarily. 2003-03-14 Paolo Bonzini * ClassHierBrow.st: need to remove metaclass in addition to the class. * NamespBrow.st: namespace renaming does not need to touch the associations. 2003-03-02 Markus Fritsche * NamespBrow.st: add Add Subspace. 2003-03-01 Paolo Bonzini * NamespBrow.st: merge patch to add File Into Namespace 2003-02-25 Paolo Bonzini * BrowserMain.st: use #nextPutAllFlush: to output to the transcript when the GUI is not being used. * BrowShell.st: merge patch to add File In, add Save Image As * BrowserMain.st: likewise * ClassHierBrow.st: prompt for category when adding a method without a selected category 2003-02-09 Paolo Bonzini * ButtonForm.st: new file * ClassHierBrow.st: remove add method menu item, the thing is done whenever a protocol is picked * Debugger.st: add button box * PList.st: cleanup some dataMsg vs. listMsg issues 2003-02-06 Paolo Bonzini * MethInspect.st: move code to start a browser on references... * MethSetBrow.st: ...here. Also use #dataMsg to simplify code & fix bugs, and add a context menu to the selector list. * ClassHierBrow.st: add inspect menu items for classes and methods. * Inspector.st: fix title bar for browsing classes 2003-01-09 Paolo Bonzini * PList.st: simplify code and don't change selection if it is refused; hiliteItemInitMsg -> selectionMsg * ClassHierBrow.st: adjust * NamespaceBrow.st: adjust * Debugger.st: adjust * NamespaceBrow.st: clear protocol and method lists when selected namespace changes 2003-01-04 Paolo Bonzini * ClassHierBrow.st: fix thinko (inheritsFrom: -> isKindOf:) * PCode.st: highlight class definitions as well * PText.st: fix inverted check in #compileIt. 2002-12-29 Paolo Bonzini * PText.st: use Meta-[DPI] instead of Control-Shift-[DPI] for Do it, Print it, Inspect it 2002-12-27 Paolo Bonzini * PText.st: map Control-S to Accept * ClassHierBrow.st: use the Control-S binding * MethSetBrow.st: likewise * Debugger.st: likewise * Inspector.st: don't pop a walkback when an error happens in the inspector * ClassHierBrow.st: evaluate modifications to the class template in the namespace of the current class. * MethSetBrow.st: report senders and implementors from all over the system. * Notifier.st: don't print internal contexts * Debugger.st: terminate internal contexts when the debugger is invoked 2002-12-20 Paolo Bonzini * Notifier.st: start notifier in separate process, keep other process in an instance variable, don't override the handling of errors. * Debugger.st: keep process in an instance variable, add support for single stepping (no UI yet) and for changing the context list on the fly. * DebugSupport.st: namespace fix 2002-11-06 Paolo Bonzini * NamespBrow.st: customize title bar * ClassBrow.st: likewise * ClassHierBrow.st: prepare for the above 2002-10-05 Paolo Bonzini * DebugSupport.st: new file * Debugger.st: highlight source code line. New ambitious name of blox/CtxtInspect.st 2002-10-04 Paolo Bonzini * BrowShell.st: use a PWorksheetText * PText.st: define PWorksheetText and WorksheetVariableTracker 2002-09-25 Paolo Bonzini * Inspector.st: refactoring, added dive/pop * StrcInspect.st: refactoring * DictInspect.st: refactoring * MethInspect.st: refactoring * CtxtInspect.st: update receiver/stack panes on every selection from context list. New class PrimitiveInspectorFieldList. 2002-09-22 Paolo Bonzini * CtxtInspect.st: show context list * PList.st: set font * PText.st: likewise * RadioForm.st: likewise 2002-09-17 Paolo Bonzini * tk/BloxBasic.st: move underlining to BMenuObject, so that menu bars are underlined as well. * tk/BloxWidgets.st: remove it from BMenuBar, use it in BMenu. Support callbacks in BMenu and submenus in #newMenuItemFor:notifying:. * Menu.st: create menus for named pop-up menus * ClassHierBrow.st: give the pop-up a name * CtxtInspect.st: give the pop-up a name * DictInspect.st: give the pop-up a name * Inspector.st: give the pop-up a name * MethInspect.st: give the pop-up a name * MethSetBrow.st: give the pop-up a name * NamespBrow.st: give the pop-up a name * Notifier.st: give the pop-up a name * StrcInspect.st: give the pop-up a name * BrowShell.st: give the pop-up a name * Inspector.st: set evaluation key bindings * BrowShell.st: ditto * PText.st: taught how to do so. 2002-09-17 Daniel A. Koepke * tk/BloxBasic.st: convert Ctrl-KEY to Control-KEY. * tk/BloxText.st: convert LINE.0 lineend to LINE.end * PText.st: support choosing Doit etc. at the end of a line. * Manager.st: add Ctrl+1/2/3 bindings for Worksheet, Class Hierarchy Browser and Namespace Browser, respectively. 2002-09-13 Paolo Bonzini *** Versions 2.0c (development) and 2.0.6 (stable) released 2002-08-19 Paolo Bonzini * BrowShell.st: reformatted * BrowserMain.st: reformatted * ClassBrow.st: reformatted * ClassHierBrow.st: reformatted * CtxtInspect.st: reformatted * DictInspect.st: reformatted * GuiData.st: reformatted * Inspector.st: reformatted * Manager.st: reformatted * Menu.st: reformatted * MethInspect.st: reformatted * MethSetBrow.st: reformatted * ModalDialog.st: reformatted * NamespBrow.st: reformatted * Notifier.st: reformatted * PCode.st: reformatted * List.st: reformatted * PText.st: reformatted * RadioForm.st: reformatted * StrcInspect.st: reformatted * View.st: reformatted 2002-08-14 Paolo Bonzini *** Version 2.0.5 (stable) released 2002-08-12 Paolo Bonzini *** Version 2.0b (development) released * tk/Blox.st: don't refer to the loading directory explicitly * test.st: use the system kernel directory to find bear.gif 2002-08-07 Paolo Bonzini *** Versions 2.0a (development) and 2.0.4 (stable) released 2002-07-17 Paolo Bonzini *** Version 2.0.3 released 2002-07-16 Paolo Bonzini * PCode.st: rewritten to use BRProgramNodeVisitor 2002-07-11 Paolo Bonzini *** Version 2.0.2 released 2002-07-06 Paolo Bonzini * Notifier.st: skip disabled methods in backtraces 2002-06-28 Paolo Bonzini *** Version 2.0.1 released 2002-06-25 Paolo Bonzini *** Version 2.0 released 2002-05-11 Paolo Bonzini *** Version 1.96.6 released 2002-05-10 Paolo Bonzini * ClassHierBrow.st: new name of ClassBrow.st, refactored the layout code, purged all non-namespace code * ClassBrow.st: new file * NamespBrow.st: new file * BrowserMain.st: use ClassHierarchyBrowser>>#open, add method to open NamespaceBrowser * BrowShell.st: add menu item to open NamespaceBrowser 2002-04-14 Paolo Bonzini *** Version 1.96.5 released 2002-03-12 Paolo Bonzini *** Version 1.96.4 released 2002-01-29 Paolo Bonzini *** Version 1.96.3 released. 2002-01-22 Paolo Bonzini * tk/BloxCanvas.st: added a missing period * tk/BloxExtend.st: added a couple of missing periods 2002-01-04 Paolo Bonzini *** Version 1.96.2 released * tk/BloxExtend.st: completed documentation 2002-01-03 Paolo Bonzini * ModalDialog.st: removed obsolete calls to #createToplevelWindow: * BrowserMain.st: likewise * ClassBrow.st: likewise * Notifier.st: fixed namespace references * Inspector.st: likewise * CtxtInspect.st: likewise * DictInspect.st: likewise * MethInspect.st: likewise * StrcInspect.st: likewise * BloxText.st: completed documentation * BloxCanvas.st: likewise 2002-01-02 Paolo Bonzini * tk/BloxBasic.st: accessing method are now included in the source code rather than generated at file-in time * tk/BloxWidgets.st: likewise * tk/BloxCanvas.st: likewise * tk/BloxText.st: likewise * Load.st: put into namespace BLOX.BLOXBrowser * tk/Load.st: put into namespace BLOX * blox/Man.st: put into namespace BLOX * blox/Tetris.st: put into namespace BLOX * Run.st: use the correct namespace * PCode.st: use the correct namespace for STPluggableParser * blox/Tetris.st: don't load examples/RandomInt.st * tk/BloxBasic.st: completed documentation * tk/BloxWidgets.st: likewise 2001-11-20 Paolo Bonzini *** Version 1.96.1 released 2001-11-13 Paolo Bonzini * BrowShell.st: prefixed # to symbols in arrays * ClassBrow.st: prefixed # to symbols in arrays * CtxtInspect.st: prefixed # to symbols in arrays * DictInspect.st: prefixed # to symbols in arrays * Inspector.st: prefixed # to symbols in arrays * MethInspect.st: prefixed # to symbols in arrays * MethSetBrow.st: prefixed # to symbols in arrays * Notifier.st: prefixed # to symbols in arrays * StrcInspect.st: prefixed # to symbols in arrays * gtk/GtkDecl.st: prefixed # to symbols in arrays * gtk/GtkDecl.st.in: prefixed # to symbols in arrays * gtk/funcs: prefixed # to symbols in arrays * gtk/funcs.awk: prefixed # to symbols in arrays * tk/BloxBasic.st: prefixed # to symbols in arrays 2001-03-01 Paolo Bonzini * tk/BloxBasic.st: use ObjectMemory instead of init blocks. * tk/Blox.st: use ObjectMemory instead of init blocks. 2001-02-23 Paolo Bonzini *** Released version 1.95.3 * ClassBrow.st: update the class pane when a class is created. 2001-02-16 Paolo Bonzini * BloxBasic.st: moved to blox/tk * BloxWidgets.st: moved to blox/tk * BloxCanvas.st: moved to blox/tk * BloxText.st: moved to blox/tk * BloxExtend.st: moved to blox/tk * Blox.st: moved to blox/tk * Blox.c: moved to blox/tk * ClassBrow.st: use the new OrderedForm * Manager.st: created OrderedForm class 2001-02-15 Paolo Bonzini * BloxBasic.st: removed deprecated BMenuObject geometry methods and added #inset:. * BloxWidgets.st: use the packer in BContainer. * Manager.st: declared OrderedForm. * test.st: use new geometry methods. * BloxExtend.st: ditto. * ClassBrow.st: ditto. * MethSetBrow.st: ditto. * Inspector.st: ditto. * BloxWidgets.st: destroy a BPopupWindow when the contained child is destroyed. * BloxExtend.st: destroy the list object when a BDropdown is destroyed. 2001-02-14 Paolo Bonzini * BloxBasic.st: add class-side #tclEval:with:... * BloxText.st: define the font protocol * MethInspect.st: fixed bug in currentVariableValue (missing caret) 2001-02-13 Paolo Bonzini * Blox.c: in bloxIdle, call Tcl_DoOneEvent until there are no more events in the list. 2001-02-12 Paolo Bonzini * Blox.st: call `Blox onStartup' * Notifier.st: updated for changes to exception handling * BBrowser.st: updated for changes to exception handling * BloxWidgets.st: adjust index positions by one (they were skewed) in BList. * PList.st: don't adjust for skewed index positions in BList. 2001-02-02 Paolo Bonzini * Blox.c: use new VMProxy * cfuncs.h: removed 2001-01-30 Paolo Bonzini *** Released version 1.95.1 2000-10-14 GertJan Kersten (GertJan.Kersten@bolesian.nl) * Blox.c: set tcl_library if TCL_LIBRARY is found in the environment 2000-08-13 Paolo Bonzini * Inspector.st: added CollectionInspector 2000-06-17 Paolo Bonzini *** Released versions 1.95 (development) and 1.7.5 (stable) 2000-05-04 Paolo Bonzini (bonzini@gnu.org) *** Version 1.94.90 released 2000-04-12 Paolo Bonzini (bonzini@gnu.org) *** Version 1.7.4 released 2000-03-28 Paolo Bonzini (bonzini@gnu.org) * ClassBrow.st: removed debugging statement 2000-03-23 Paolo Bonzini (bonzini@gnu.org) *** Version 1.7.3 released 2000-03-11 Paolo Bonzini (bonzini@gnu.org) *** Version 1.7.2 released 2000-02-22 Paolo Bonzini (bonzini@gnu.org) *** Version 1.7.1 released 2000-02-15 Paolo Bonzini (bonzini@gnu.org) *** Version 1.7 released 2000-01-31 Paolo Bonzini (bonzini@gnu.org) *** Sixth beta of 1.7 (labeled 1.6.85) released 2000-01-31 Paolo Bonzini (bonzini@gnu.org) * Notifier.st: updated for recent changes to the inner workings of the interpreter (notably, the `terminate interpreter' bytecode and the fact that execution environments no longer have their selector set to nil) 1999-12-29 Paolo Bonzini * BrowShell.st: TranscriptInterface class changed to TextCollector -- changed here too. Also added the ability to add custom menus to the browsers' window. 1999-12-28 Paolo Bonzini *** Fifth beta of 1.7 (labeled 1.6.84) released 1999-12-25 Paolo Bonzini * Inspector.st: added Object>>#basicInspect before guests arrive for Xmas... 1999-12-21 Paolo Bonzini * PCode.st: moved the SyntaxHighlighter class (now called STPluggableParser) to compiler/STParser.st. 1999-11-26 Paolo Bonzini *** Fourth beta of 1.7 (labeled 1.6.83) released 1999-11-06 Paolo Bonzini * BloxWidgets.st: BContainer uses two sends to self to position new children, instead of directly calling #posVert: and #posHoriz:. I added this hook because I'm thinking of adding paned windows as a subclass of BContainer... 1999-11-01 Paolo Bonzini * ClassBrow.st: now works with namespaces. This mainly meant adapting the algorithm for preparing the class list (using the one in examples/Publish.st). * Inspector.st: now works with namespaces. This mainly meant using #nameIn: * MethSetBrow.st: now works with namespaces. This mainly meant using #nameIn: 1999-10-31 Paolo Bonzini * BloxBasic.st: fixed bug in #fontHeight: -- was reporting space for a line less than asked (that is, was always returning zero when asked for the space occupied by a single line!) * BloxExtend.st: drop-down widgets in and working. * BloxWidgets.st: resizing a popup widget works (fixed usage of the Tk packer in BPopupWindow). Also, BLabels now use word wrapping. * test.st: added #dropdownTest. 1999-10-31 Paolo Bonzini *** Third beta of 1.7 (labeled 1.6.82) released * CtxtInspect.st: for some reason, the context inspector was broken; I had to add `self changeState: #text'. The presence of this statement is fine -- for example it is there in the class browser too, but I don't understand why it was not needed before... * View.st: fixed bug in close (was not answering a Boolean) * Manager.st: simplified implementation of #close and #destroyed 1999-10-30 Paolo Bonzini * BloxBasic.st: fixed possible divide-by-zero problem in geometry management; cached the window size; #posHoriz: and #posVert: set and take into account the xOffset, yOffset, widthOffset and heightOffset too; added accessors for the offset. * ClassBrow.st: fixed erroneous geometry management resulting for the change to #posHoriz: and #posVert: (in blox/BloxBasic.st). See the NEWS file for more information. 1999-10-28 Paolo Bonzini * BloxExtend.st: started implementing drop-down controls 1999-10-26 Paolo Bonzini * BloxBasic.st: new algorithm to get Tk widget names (instead of `.wNNN' where NNN was an increasing number, `.wOOO' where OOO is the base-36 representation of the OOP). Allowed to implement lots of interesting methods such as Blox>>#active, Blox>>#atMouse, ... 1999-10-24 Paolo Bonzini * BloxBasic.st: added methods to automatically or manually toggle the scrollbars in a BViewport. * BloxText.st: added images. 1999-10-22 Paolo Bonzini * BloxExtend.st: changed implementation of the progress widget; the new one looks nicer and shows some tricks. * BloxBasic.st: removed #bindWith:... when possible, replaced with (new) #tclEval:with:... methods. * BloxWidgets.st: same as above. * BloxCanvas.st: same as above. * BloxText.st: same as above. * ClassBrow.st: added `print bytecodes' mode. * Inspector.st: split class into GenericInspector (superclass) and Inspector (subclass) * DictInspect.st: derived from GenericInspector. * StrcInspect.st: derived from GenericInspector. * CtxtInspect.st: derived StackInspector from GenericInspector. * MethInspect.st: created. 1999-10-20 Paolo Bonzini * BloxExtend.st: added GNU image and file/directory icons. * BloxWidgets.st: use #displayString in BList. 1999-10-17 Paolo Bonzini * Blox.st: removed declaration of forward references to nil now that Undeclared is available. * Load.st: ditto * BloxBasic.st: added pluggable geometry behavior depending on the parent widget. Added #new to BWidget. * BloxCanvas.st: new feature above used. * BloxText.st: new feature above used. * BloxWidgets.st: new feature above used in BPopupWindow. * BloxExpand.st: change to BloxWidgets.st exploited in BBalloon. 1999-10-16 Paolo Bonzini * BloxCanvas.st: Added BEmbeddedImage. * BloxWidgets.st: automatically choose a good letter (possibly different for each item) to be underlined in a menu item. Also added callbacks to BEdit. * View.st: don't use #allSubinstances: (sloooow) to iterate through all the views. * CtxtInspect.st: make StackInspector get temporaries from outer block contexts too. 1999-10-13 Paolo Bonzini * ErrInspect.st: became Notifier.st; also class name changed to Notifier * Load.st: load Notifier.st instead of ErrInspect.st * PText.st: don't bring up a notifier when choosing `senders' or `implementors' without a selection * PCode.st: added syntax highlightling * StkInspect.st: incorporated in blox/CtxtInspect.st * CtxtInspect.st: incorporated blox/StkInspect.st 1999-10-11 Paolo Bonzini * BloxText.st: added a few methods about attributes and lines, needed for syntax highlighting. * ClassBrow.st: tell PCode the class of the method. * MethSetBrow.st: tell PCode the class of the method. * CtxtInspect.st: tell PCode the class of the method. * PCode.st: added code to let widgets tell PCode the class of the method to show. * Form.st: incorporated in blox/Manager.st * GuiData.st: removed some methods defined in Gui (they were unused), added new GuiState class. * Load.st: removed files incorporated in other files * Manager.st: incorporated blox/Form.st & blox/TopLevel.st * ModalDialog.st: incorporated blox/Prompter.st * PRadioBtn.st: incorporated in blox/RadioForm.st * Primitive.st: incorporated in blox/View.st * Prompter.st: incorporated in blox/ModalDialog.st * RadioForm.st: incorporated blox/PRadioBtn.st * TextMenu.st: removed (it could not be even filed in) * TopLevel.st: incorporated in blox/Manager.st * View.st: incorporated blox/Primitive.st, used new GuiState class. 1999-10-09 Paolo Bonzini *** Second beta of 1.7 (labeled 1.6.81) released 1999-10-02 Paolo Bonzini * BloxBasic.st: added methods to create CMYK and HSV colors; commented. * BloxExtend.st: commented. * Blox.c: stop compilation if HAVE_TCLTK is not defined 1999-09-30 Paolo Bonzini * blox/Man.st: removed code to deal with non-reentrancy of event dispatching loops. * blox/Tetris.st: removed code to deal with non-reentrancy of event dispatching loops. * BloxBasic.st: #dispatchEvents and #dispatchEvents: are now reentrant. * PCode.st: created * CtxtInspect.st: use PCode * ClassBrow.st: use PCode * MethSetBrow.st: use PCode 1999-09-26 Paolo Bonzini * BloxBasic.st: added BEventSet; ...Absolute geometry methods refer to the container object (used to refer to the connected object); added xRoot and yRoot to BWidget. Use the grid geometry manager in BViewport -- it looks nicer. * BloxWidgets.st: added BPopupWindow. * BloxExtend.st: created * BloxIcons.st: removed -- merged in BloxExtend.st * test.st: added tests for extended widgets * blox/Progress.st: removed -- merged in BloxExtend.st 1999-09-25 Paolo Bonzini *** First beta of 1.7 (labeled 1.6.80) released 1999-09-20 Paolo Bonzini * Blox.c: incorporated XPM support (partly stolen from libXpm). * BloxBasic.st: added #borderWidth accessor. * BloxIcons.st: created. * rgbtab.h: created. * test.st: added #iconTest. 1999-09-05 Paolo Bonzini * BloxBasic.st: changed to use the new #idleAdd: method in ProcessorScheduler. 1999-08-29 Paolo Bonzini *** Version 1.6.2 released. 1999-07-14 Paolo Bonzini * StructInspect.st: renamed to StrcInspect.st (was more than 14 chars long). 1999-07-04 Paolo Bonzini * Blox.st: Added BTextBindings and BEdit classes. * BloxBasic.st: Added #cursor and #cursor: * BloxCanvas.st: Added #at: * BloxText.st: Added the ability to specify event handlers in a BTextAttributes object. * BloxWidgets.st: Added BEdit. * test.st: Added #textEventsTest and #editTest. 1999-06-25 Paolo Bonzini *** Bug-fixing version 1.6.1 released. 1999-06-17 Paolo Bonzini *** Version 1.6 released. 1999-05-08 Paolo Bonzini * Transcript.st: Moved to kernel (at last!). * Load.st: Removed Transcript.st. * BrowserMain.st: Modified code to set up the Transcript.st to deal with the new interface for the Transcript object. 1999-04-27 Paolo Bonzini *** Version 1.5.beta3 released. 1999-04-22 Paolo Bonzini * Blox.c: Renamed idle to bloxIdle -- idle was already defined in unistd.h. Signaled by Christopher Painter-Wakefield. 1999-04-11 Paolo Bonzini * Blox.st: Removed BEventHandlers, added BEventTarget. * BloxBasic.st: Changed event handling design to the new one using BEventTarget. This resembles the old one (before Apr 8), but its design is better (no code duplication) and it is compatible with beta1. Switched Blox superclass to be BEventTarget. * BloxCanvas.st: Changed event handling design to the new one using BEventTarget. Switched BCanvasObject superclass to be BEventTarget. * blox/Progress.st: switched to new event handling system (actually, back to the old one...) * blox/Tetris.st: switched to new event handling system (actually, back to the old one...) 1999-04-10 Paolo Bonzini *** Version 1.5.beta2 released. 1999-04-08 Paolo Bonzini * Blox.st: Added BEventHandlers. * BloxBasic.st: Changed event handling design to the new one using #events:/#events. * BloxCanvas.st: Changed event handling design to the new one using #events:/#events. * blox/Progress.st: switched to new event handling system * blox/Tetris.st: switched to new event handling system. 1999-03-15 Paolo Bonzini *** Version 1.5.beta1 released. 1999-02-26 Paolo Bonzini * BloxBasic.st: Added hook into Delay class>>#idle * blox/Tetris.st: Removed the `idle' process, whose function is now embedded in Delay.st 1999-02-26 Paolo Bonzini * Run.st: Now automatically loads `Browser' if needed. * ClassBrow.st: #classString used #to:do: with a zero argument block (1.1.5 did not find this error)! 1999-02-22 Paolo Bonzini * Transcript.st: Made thread-safe. 1999-02-16 Paolo Bonzini * BloxWidgets.st: added BWindow>>#resizable 1999-02-14 Paolo Bonzini * ClassBrow.st: Happy Valentine! Switched to file prompters. * Prompter.st: Added file prompters. * blox/Progress.st: created. 1999-02-09 Paolo Bonzini * blox/Man.st: created. 1999-02-05 Paolo Bonzini * Blox.c: Added idle. Calling TCL's `update' did not seem to work. The Blox.c file was created somewhen in November. * blox/Tetris.st: created. 1999-02-04 Paolo Bonzini * Transcript.st: Added #instance class method to allow using print/printNl even if the GUI is not running. 1999-02-03 Paolo Bonzini * BloxCanvas.st: created. 1999-02-02 Paolo Bonzini * BloxWidgets.st: added BImage. 1999-02-01 Paolo Bonzini * BloxText.st: created from part of BloxWidgets.st. 1999-01-26 Paolo Bonzini * ClassBrow.st: Moved instance/class radio buttons under the category pane. First it seemed more logical to me, second now they steal screen estate from the list box that is less likely to scroll. 1998-11-28 Paolo Bonzini * BloxBasic.st: Small change to support reloading images which used Blox. 1998-11-27 Paolo Bonzini * ErrInspect.st: Modified to support unwinding 1998-11-24 Paolo Bonzini * Transcript.st: created. 1998-11-15 Paolo Bonzini * BloxBasic.st: First version of Tk Blox completed. 1998-11-14 Paolo Bonzini * StructInspect.st: Created. 1998-11-10 Paolo Bonzini * BrowShell.st: created. * BrowserMain.st: Moved some parts to BrowserShell, so that every window has a Smalltalk menu; in addition, the main window is a worksheet * ClassBrow.st: Added support for classes derived from nil. 1998-11-03 Paolo Bonzini * Blox.st: created. * BloxBasic.st: Added BPrimitive and BExtended. The latter is intended to provide a base for implementing megawidgets like tree lists, tables, HTML viewers, etc. Also split old Blox.st in BloxBasic.st and BloxWidgets.st. * BloxWidgets.st: created. 1998-10-30 Paolo Bonzini * Menu.st: Modified to add support for menu bars. The previous version assumed that you could pass a >>Shell<< to BMenu when creating it. Instead, as BBrowser.st shows, you must pass it a menu bar, and the new Tcl-based version enforces this. The new version uses the menuBar method I added to TopLevelShell, which automatically creates a menu bar when you add the first menu. Note that this change did not affect PopupMenu, because BPopupMenu does accept a BWindow as the first parameter passed to #new:label: * TopLevel.st: Same as above. The new menuBar variable is automatically created when you add a menu. 1998-10-20 Paolo Bonzini * blox.c: rewritten. * BloxBasic.st: Switched to Tk for portability. Also refactored hierarchy: BForm->BContainer->BRadioGroup, added BWidget and BViewport, BButton->BRadioButton, Button->BToggle. Added a few Tk features: rubber-sheet geometry management, 3d effects, fonts, for instance. Also, previously badly-documented C-only methods now expose a tidier interface. Programs relying on those methods will fail (e.g. the browser itself ;-) ). 1998-09-14 Paolo Bonzini * Primitive.st: Capitalized class variable name. 1998-09-12 Paolo Bonzini * BBrowser.st: Modified to support exception handling. * ErrInspect.st: Modified to support exception handling. 1998-09-02 Paolo Bonzini *** Began development of version 1.6 1995-09-30 Steve Byrne *** Version 1.1.5 released. 1995-09-26 Brad Diller * blox.c: Added support for Dialog and Form widgets. Extended Text and List widget support. Corrected minor bugs. 1995-08-29 Steve Byrne * Load.st: Converted to use new Smalltalk variable for location of kernel files. 1995-07-16 Steve Byrne * BBrowser.st: More updates to contextInspector>>init: from Brad Diller . * BBrowser.st: Updated with Brad Diller's changes/fixes. Removed #changed:/#update: usage. 1995-07-12 Brad Diller * PList.st: Modified extensively to support revamped window management system. * PRadioBtn.st: Modified extensively to support revamped window management system. * Primitive.st: Modified extensively to support revamped window management system. * TopLevel.st: Modified extensively to support revamped window management system. * View.st: Modified extensively to support revamped window management system. 1995-05-01 Steve Byrne * Blox.st: Switched to using the new C type models. 1995-02-25 Brad Diller * ModalDialog.st: Created. 1994-09-15 Steve Byrne *** Version 1.2.alpha1 released. 1994-07-12 Steve Byrne * Blox.st: Added insert at end. 1994-07-09 Steve Byrne * BBrowser.st: Created about a week ago. 1994-07-04 Steve Byrne * blox.c: Serious hacking this weekend to make it work properly. 1994-02-04 Steve Byrne * blox.c: created (using Xaw Athena Widgets). 1993-10-29 Brad Diller * ClassBrow.st: Created. 1993-10-27 Brad Diller * DictInspect.st: Created. * Inspector.st: Created. 1993-10-11 Brad Diller * BrowserMain.st: created. * MethSetBrow.st: Created. * PRadioBtn.st: Created. 1993-10-01 Brad Diller * Menu.st: Created. 1993-09-18 Brad Diller * GuiData.st: Created. * PList.st: Created. * Primitive.st: Created. * Prompter.st: Created. * View.st: Created. smalltalk-3.2.5/packages/blox/browser/ClassBrow.st0000644000175000017500000000320012123404352017071 00000000000000"====================================================================== | | Smalltalk GUI class hierarchy browser | | ======================================================================" "====================================================================== | | Copyright 2002 Free Software Foundation, Inc. | Written by Brad Diller and Paolo Bonzini. | | This file is part of GNU Smalltalk. | | GNU Smalltalk is free software; you can redistribute it and/or modify it | under the terms of the GNU General Public License as published by the Free | Software Foundation; either version 2, or (at your option) any later version. | | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS | FOR A PARTICULAR PURPOSE. See the GNU General Public License for more | details. | | You should have received a copy of the GNU General Public License along with | GNU Smalltalk; see the file COPYING. If not, write to the Free Software | Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. | ====================================================================== " ClassHierarchyBrowser subclass: ClassBrowser [ | startingClass | createTopView [ ^BrowserShell new: 'Class Browser on %1' % {startingClass} ] openOn: aClass [ "Create and open a class hierarchy browser on startingClass" startingClass := aClass. super open ] topClasses [ ^{startingClass} ] ] smalltalk-3.2.5/packages/blox/browser/Notifier.st0000644000175000017500000001121512123404352016756 00000000000000"====================================================================== | | Smalltalk GUI notifier window | | ======================================================================" "====================================================================== | | Copyright 1992,94,95,99,2000,2001,2002 Free Software Foundation, Inc. | Written by Brad Diller and Paolo Bonzini. | | This file is part of GNU Smalltalk. | | GNU Smalltalk is free software; you can redistribute it and/or modify it | under the terms of the GNU General Public License as published by the Free | Software Foundation; either version 2, or (at your option) any later version. | | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS | FOR A PARTICULAR PURPOSE. See the GNU General Public License for more | details. | | You should have received a copy of the GNU General Public License along with | GNU Smalltalk; see the file COPYING. If not, write to the Free Software | Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. | ====================================================================== " GuiData subclass: Notifier [ | callstackList debugger stacktrace currentSelection errMessage topView listView | Notifier class >> debuggerClass [ ^nil ] Notifier class >> debuggingPriority [ ^1 ] Notifier class >> openOn: aProcess message: message [ self new init: message debugger: (Smalltalk.Debugger on: aProcess) ] Notifier class >> open [ self open: 'Notifier on %1' % {Processor activeProcess} ] Notifier class >> open: message [ | handleErrorsWithGui | handleErrorsWithGui := BLOX.BLOXBrowser.BrowserMain handleErrorsWithGui. BLOX.BLOXBrowser.BrowserMain handleErrorsWithGui: false. [:debugger | Processor activeProcess name: 'Notifier/Debugger'. self new init: message debugger: debugger. BLOX.BLOXBrowser.BrowserMain handleErrorsWithGui: handleErrorsWithGui] forkDebugger ] currentContext [ currentSelection isNil ifTrue: [currentSelection := 1]. ^callstackList at: currentSelection ] process [ ^debugger process ] debugger [ ^debugger ] contextSelectedFrom: assoc [ currentSelection := assoc key ] debug [ Debugger new: self ] stacktrace [ ^stacktrace ] close: aView [ | tv | tv := aView rootView blox. aView rootView close ifTrue: [tv destroy] ] init: aString debugger: aDebugger [ | context lastContext contexts | errMessage := aString. debugger := aDebugger. context := debugger suspendedContext. lastContext := context environment. stacktrace := OrderedCollection new. contexts := OrderedCollection new. "Skip top contexts that are internal to the exception-handling system." [context ~~ lastContext and: [context isInternalExceptionHandlingContext]] whileTrue: [context := context parentContext]. [context == lastContext] whileFalse: [context isDisabled ifFalse: [stacktrace add: context printString. contexts add: context]. context := context parentContext]. self createWindow. callstackList contents: stacktrace elements: contexts. topView display. listView update. listView select: 1 ] createWindow [ | topLevel | topView := (BrowserShell new: errMessage) data: self. topLevel := topView blox. topLevel x: 20 y: 50 width: 300 height: 100. topView addChildView: ((listView := PList new: 'MethodSet' in: topView) initialize; data: self; listMsg: #stacktrace; handleUserChange: #contextSelectedFrom:; menuInit: ((PopupMenu new: listView label: 'Context') selectors: #(#('Debug' #debug)) receiver: self argument: listView; selectors: #(#() #('Copy Trace' #copyAll) #('Copy Selection' #copySelection)) receiver: listView argument: nil; selectors: #(#() #('Close' #close)) receiver: listView argument: nil; yourself); yourself). callstackList := listView blox ] ] Behavior extend [ debuggerClass [ ^BLOX.BLOXBrowser.BrowserMain handleErrorsWithGui ifTrue: [BLOX.BLOXBrowser.Notifier] ifFalse: [nil] ] ] smalltalk-3.2.5/packages/blox/browser/ModalDialog.st0000644000175000017500000001045312123404352017356 00000000000000"====================================================================== | | Smalltalk GUI wrapper for modal dialogs | | ======================================================================" "====================================================================== | | Copyright 1992,94,95,99,2000,2001,2002 Free Software Foundation, Inc. | Written by Brad Diller. | | This file is part of GNU Smalltalk. | | GNU Smalltalk is free software; you can redistribute it and/or modify it | under the terms of the GNU General Public License as published by the Free | Software Foundation; either version 2, or (at your option) any later version. | | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS | FOR A PARTICULAR PURPOSE. See the GNU General Public License for more | details. | | You should have received a copy of the GNU General Public License along with | GNU Smalltalk; see the file COPYING. If not, write to the Free Software | Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. | ====================================================================== " BLOX.Gui subclass: ModalDialog [ | dialogShell messageDispatch | display: parent [ dialogShell map. blox loop ] addButton: label message: block [ messageDispatch at: messageDispatch size + 1 put: block. blox addButton: label receiver: self index: messageDispatch size ] alertMessage: queryString in: parent [ self message: queryString in: parent. self addButton: 'Ok' message: []. self display: parent ] message: queryString in: parent [ "Initialize dialog and button actions" messageDispatch := LookupTable new. dialogShell := BTransientWindow new: 'Modal dialog' in: parent rootView blox. dialogShell width: 200 height: 140. blox := BDialog new: dialogShell label: queryString prompt: nil ] dispatch: index [ (messageDispatch at: index) value ] ] BLOX.Gui subclass: Prompter [ | defaultResponse | Prompter class >> message: aString default: aResponse in: view [ ^self new message: aString default: aResponse in: view ] Prompter class >> message: aString in: view [ ^self new message: aString default: '' in: view ] Prompter class >> openFileName: aString default: default in: view [ ^BDialog chooseFileToOpen: view rootView blox label: aString default: default defaultExtension: 'st' types: #(#('Smalltalk files' '.st') #('Text files' '.txt')) ] Prompter class >> saveFileName: aString default: default in: view [ ^BDialog chooseFileToSave: view rootView blox label: aString default: default defaultExtension: 'st' types: #(#('Smalltalk files' '.st') #('Text files' '.txt')) ] accept [ "Truncate string after newline character" | index | defaultResponse := blox contents. (index := defaultResponse findFirst: [:ch | ch == Character nl]) > 0 ifTrue: [defaultResponse := defaultResponse copyFrom: 1 to: index - 1] ] cancel [ defaultResponse := '' ] response [ "Return default response" ^defaultResponse ] message: queryString default: aResponse in: view [ "Prompt user for string input. The default response, queryString, is displayed in text portion" | dialogShell | defaultResponse := aResponse. dialogShell := BTransientWindow new: 'Prompter dialog' in: view rootView blox. dialogShell width: 300 height: 180. self blox: (BDialog new: dialogShell label: queryString prompt: aResponse). blox addButton: 'OK' receiver: self message: #accept. blox addButton: 'Cancel' receiver: self message: #cancel. dialogShell map. self blox loop ] ] smalltalk-3.2.5/packages/blox/browser/ButtonForm.st0000644000175000017500000000650212123404352017301 00000000000000"====================================================================== | | Smalltalk GUI wrapper for button groups | | ======================================================================" "====================================================================== | | Copyright 2003 Free Software Foundation, Inc. | Written by Paolo Bonzini. | | This file is part of GNU Smalltalk. | | GNU Smalltalk is free software; you can redistribute it and/or modify it | under the terms of the GNU General Public License as published by the Free | Software Foundation; either version 2, or (at your option) any later version. | | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS | FOR A PARTICULAR PURPOSE. See the GNU General Public License for more | details. | | You should have received a copy of the GNU General Public License along with | GNU Smalltalk; see the file COPYING. If not, write to the Free Software | Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. | ====================================================================== " Primitive subclass: PButton [ PButton class >> parentView: sv data: anObject label: label handleUserChange: changeSelector [ | view | view := self new. view data: anObject. view parentView: sv. view handleUserChange: changeSelector. view initBlox: label. ^view ] initBlox: aLabel [ blox := BButton new: parentView blox label: aLabel. blox callback: self message: 'pressed' ] pressed [ "Send the modification message to the data object" (stateChangeMsg notNil and: [self canChangeState]) ifTrue: [data perform: stateChangeMsg] ] ] Form subclass: ButtonForm [ ButtonForm class >> new: aString in: view [ | aView | aView := self new. aView parentView: view. aView blox: (BForm new: view blox). ^aView ] replaceArgWith: arg in: selectorsArray [ | selectors | selectors := selectorsArray deepCopy. "(label unarySelector)) should not be changed (label keywordSelector arg) should be changed" selectorsArray with: selectors do: [:item :changed | (item size > 2 and: [(item at: 2) numArgs >= 1]) ifTrue: [changed at: 3 put: arg]]. ^selectors ] selectors: selectorsArray receiver: receiver [ | selectors size | selectors := selectorsArray reject: [:each | each isEmpty]. size := self blox width / selectors size. selectors keysAndValuesDo: [:x :sel | | msg buttonView | msg := sel size = 2 ifTrue: [sel at: 2] ifFalse: [Message selector: (sel at: 2) arguments: {sel at: 3}]. buttonView := PButton parentView: self data: receiver label: (sel at: 1) handleUserChange: msg. buttonView blox x: (x - 1) * size y: 0 width: size height: self blox height] ] selectors: selectors receiver: receiver argument: arg [ self selectors: (self replaceArgWith: arg in: selectors) receiver: receiver ] ] smalltalk-3.2.5/packages/blox/browser/MethInspect.st0000644000175000017500000000652312123404352017430 00000000000000"====================================================================== | | Smalltalk GUI inspector for CompiledMethods | | ======================================================================" "====================================================================== | | Copyright 1992,94,95,99,2000,2001,2002 Free Software Foundation, Inc. | Written by Paolo Bonzini. | | This file is part of GNU Smalltalk. | | GNU Smalltalk is free software; you can redistribute it and/or modify it | under the terms of the GNU General Public License as published by the Free | Software Foundation; either version 2, or (at your option) any later version. | | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS | FOR A PARTICULAR PURPOSE. See the GNU General Public License for more | details. | | You should have received a copy of the GNU General Public License along with | GNU Smalltalk; see the file COPYING. If not, write to the Free Software | Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. | ====================================================================== " InspectorFieldList subclass: MethodInspectorFieldList [ | lastVar | inspectMenu: listView [ "Initialize menu for variable list pane" ^(PopupMenu new: listView label: nil) selectors: #(#('Inspect' #evalAndInspectResult: #listView) #('References' #references: #listView)) receiver: self argument: listView ] currentFieldValue: obj [ Blox beep ] currentFieldValue [ | s | self currentField == 0 ifTrue: [^nil]. self currentField = 2 ifTrue: [s := WriteStream on: (String new: 100). self value printHeaderOn: s. ^s contents]. self currentField = 1 ifTrue: [s := WriteStream on: (String new: 100). self value printByteCodesOn: s. ^s contents]. ^self currentField <= lastVar ifTrue: [self value instVarAt: self currentField] ifFalse: [self value literalAt: self currentField - lastVar] ] computeFieldList: anObject [ "Initialize instance variable, fields, which governs display of variable list pane." | string instVarNames | instVarNames := self value class allInstVarNames. fields add: '- bytecodes'. fields add: '- header'. 3 to: instVarNames size do: [:x | string := (instVarNames at: x) asString. fields add: string]. lastVar := fields size. 1 to: self value numLiterals do: [:x | fields add: x printString] ] currentFieldString [ self currentField < 3 ifTrue: [^self currentFieldValue]. ^self currentFieldValue printString ] references: listView [ "Open a method set browser on all methods which reference selected key" currentField isNil ifTrue: [^listView beep]. currentField <= lastVar ifTrue: [^listView beep]. MethodSetBrowser referencesTo: (self value literalAt: currentField - lastVar) parent: listView ] ] CompiledCode extend [ inspectorFieldLists [ "Open a MethodInspectorFieldList window on self" ^{'Basic' -> (BLOX.BLOXBrowser.MethodInspectorFieldList new value: self)} ] ] smalltalk-3.2.5/packages/blox/browser/PText.st0000644000175000017500000002571712123404352016257 00000000000000"====================================================================== | | Smalltalk GUI wrapper for text widgets | | ======================================================================" "====================================================================== | | Copyright 1992,94,95,99,2000,2001,2002,2003 Free Software Foundation, Inc. | Written by Brad Diller. | | This file is part of GNU Smalltalk. | | GNU Smalltalk is free software; you can redistribute it and/or modify it | under the terms of the GNU General Public License as published by the Free | Software Foundation; either version 2, or (at your option) any later version. | | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS | FOR A PARTICULAR PURPOSE. See the GNU General Public License for more | details. | | You should have received a copy of the GNU General Public License along with | GNU Smalltalk; see the file COPYING. If not, write to the Free Software | Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. | ====================================================================== " Primitive subclass: PText [ | textMsg selection canBeDirty object | PText class >> bloxClass [ ^BText ] PText class >> new: parent [ | view | view := self new. view canBeDirty: true. view parentView: parent. view blox: (self bloxClass new: parent blox). view blox callback: view message: 'setDirtyFlag'. ^view ] PText class >> newReadOnly: parent [ | view | view := self new. view parentView: parent. view blox: (self bloxClass newReadOnly: parent blox). "view blox backgroundColor: 'LemonChiffon'." ^view ] getSelectionOrLine [ "Answer the text currently selected or the text on the current line if there's no text selected. This enables Do It, Print It, and Inspect It to be used without manually selecting text." | text | text := blox getSelection. (text isNil or: [text isEmpty]) ifTrue: [^blox lineAt: blox currentLine]. ^text ] compileIt [ "Activated when the user selects 'accept' from the popup menu. Send a stateChangeMsg to the data object" | text rejected | text := blox contents. (text isNil or: [text size = 0]) ifTrue: [^self beep]. self canChangeState ifTrue: [rejected := stateChangeMsg numArgs = 1 ifTrue: ["One parameter selector" (data perform: stateChangeMsg with: blox contents) isNil] ifFalse: ["Two parameter selector" (data perform: stateChangeMsg with: blox contents with: self) isNil]. dirty := rejected & canBeDirty] ] eval [ | text pos | pos := blox currentLine. text := self getSelectionOrLine. (text isNil or: [text size = 0]) ifTrue: [^self beep]. self doEval: text ifError: [:fname :lineNo :errorString | self displayError: errorString at: lineNo + pos] ] doLine [ "Perform a single line of code in a Worksheet or the Transcript window. This actually executes the _previous_ line because Tcl/Tk passes through the Return of the Control-Return keybinding to its text editor widget before we get here." | endPt | endPt := 1 @ blox currentLine. blox selectFrom: 1 @ (blox currentLine - 1) to: endPt. self eval. blox selectFrom: endPt to: endPt ] evalAndInspectResult [ "Open an inspector on the result of the evaluation of the selected Smalltalk expression" | obj text pos | pos := blox currentLine. text := self getSelectionOrLine. (text isNil or: [text size = 0]) ifTrue: [^self beep]. obj := self doEval: text ifError: [:fname :lineNo :errorString | self displayError: errorString at: lineNo + pos. ^nil]. obj inspect ] evalAndPrintResult [ "Display and select result of evaluation of selected expression to right of selection" | text obj pos | pos := blox currentLine. text := self getSelectionOrLine. (text isNil or: [text size = 0]) ifTrue: [^self beep]. obj := self doEval: text ifError: [:fname :lineNo :errorString | self displayError: errorString at: lineNo + pos. ^nil]. blox insertTextSelection: obj printString ] find [ | prompter | prompter := Prompter message: 'Search...' in: self. prompter response ~= '' ifTrue: [blox searchString: prompter response] ] gstClear [ blox replaceSelection: '' ] gstCopy [ Blox clipboard: blox getSelection ] gstCut [ self gstCopy. self gstClear ] gstPaste [ | clip | clip := Blox clipboard. clip isEmpty ifFalse: [blox replaceSelection: clip] ] implementors [ "Maybe getSelectionOrWord?" self getSelectionOrLine ifNotNil: [:sel | MethodSetBrowser implementorsOf: sel asSymbol parent: self] ] line [ "Prompt user to enter a line number. If a valid number, attempt to scroll to entered line number" | prompter | prompter := Prompter message: 'Goto line...' in: self. prompter response isEmpty ifTrue: [^self]. (prompter response allSatisfy: [:ch | ch isDigit]) ifTrue: [blox gotoLine: prompter response asInteger end: false] ] revert [ "Revert text changes and replace current text with original text" self display ] senders [ "Maybe getSelectionOrWord?" self getSelectionOrLine ifNotNil: [:sel | MethodSetBrowser sendersOf: sel asSymbol parent: self] ] canBeDirty [ ^canBeDirty ] canBeDirty: aBoolean [ canBeDirty := aBoolean. dirty := dirty & canBeDirty ] canUpdate [ "If text has been modified, display a prompter. If the No button is selected, return true" | cancel | data isNil ifTrue: [^true]. canBeDirty ifFalse: [^true]. dirty ifFalse: [^true]. cancel := self confirm: 'The text has been altered.' , (String with: Character nl) , 'Do you wish to discard those changes?'. ^cancel ] confirm: aString [ "Used by canUpdate when the text has been modified. If the user wishes to discard the editing changes by pressing 1, the dirty flag is reset" (ModalDialog new) message: aString in: self; addButton: 'Yes' message: [dirty := false]; addButton: 'No' message: []; display: self. ^dirty not ] display [ "Update text view. Dirty flag is reset" textMsg isNil ifFalse: [self contents: (data perform: textMsg)]. dirty := false ] displayError: errorString [ "Insert error string at cursor and select it" self blox insertTextSelection: errorString ] displayError: errorString at: lineNo [ "Display error string at end of line indicated by lineNo" (self blox gotoLine: lineNo end: true) = 0 ifFalse: [self blox insertSelectedText: errorString] ifTrue: [self beep] ] findString: aString [ "Select aString in the text view. If not found, beep" (blox searchString: aString) = 0 ifTrue: [self beep] ] selection: aString [ selection := aString ] setBrowserKeyBindings [ "Add key bindings for Accept, etc." #('Control-S') with: #(#compileIt) do: [:key :sel | self blox onKeyEvent: key send: sel to: self] ] setEvaluationKeyBindings [ "Add key bindings for Doit, Print it, etc." #('Meta-D' 'Meta-P' 'Meta-I' 'Control-Return') with: #(#eval #evalAndPrintResult #evalAndInspectResult #doLine) do: [:key :sel | self blox onKeyEvent: key send: sel to: self] ] setDirtyFlag [ "Set modification state of text view" dirty := canBeDirty ] stateChange: stateChangeKey [ "Install message handler to redraw text pane in response to an stateChangeKey message. If there is text which is initially selected, select the text. This feature is utilized by some types of message set browsers" self stateChange: stateChangeKey updateWith: [self display. selection notNil ifTrue: [self findString: selection]] ] textMsg: textSelector [ "The textSelector is supplied by the view's data object. When invoked from computeText, the text to be displayed is returned" textMsg := textSelector ] contents: text [ blox contents: text ] object [ ^object ] object: anObject [ object := anObject ] doEval: text ifError: aBlock [ ^Behavior evaluate: text to: object ifError: aBlock ] ] STInST.STInST.RBProgramNodeVisitor subclass: WorksheetVariableTracker [ | vars class | initialize [ vars := #('self' 'super' 'true' 'false' 'nil' 'thisContext') asSet. class := (Behavior new) superclass: Object; yourself ] objectClass [ ^class ] includesVariable: aString [ ^aString first isUppercase or: [vars includes: aString] ] defineVariable: aString [ vars add: aString. class addInstVarName: aString ] acceptAssignmentNode: anRBAssignmentNode [ (self includesVariable: anRBAssignmentNode variable name) ifFalse: [self defineVariable: anRBAssignmentNode variable name]. self visitNode: anRBAssignmentNode value ] ] PText subclass: PWorksheetText [ | variableTracker | PWorksheetText class >> new [ ^super new initialize ] initialize [ "Use a lightweight class to evaluate the workspace expressions, so that variables are kept across evaluations." variableTracker := WorksheetVariableTracker new. self object: variableTracker objectClass new ] doEval: text ifError: aBlock [ | nodes | nodes := STInST.RBParser parseExpression: text onError: [:s :p | ^super doEval: text ifError: aBlock]. variableTracker visitNode: nodes. ^super doEval: text ifError: aBlock ] ] smalltalk-3.2.5/packages/blox/browser/View.st0000644000175000017500000001314312123404352016113 00000000000000"====================================================================== | | Smalltalk GUI base class for widget wrappers with publish/subscribe | | ======================================================================" "====================================================================== | | Copyright 1992,94,95,99,2000,2001,2002 Free Software Foundation, Inc. | Written by Brad Diller. | | This file is part of GNU Smalltalk. | | GNU Smalltalk is free software; you can redistribute it and/or modify it | under the terms of the GNU General Public License as published by the Free | Software Foundation; either version 2, or (at your option) any later version. | | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS | FOR A PARTICULAR PURPOSE. See the GNU General Public License for more | details. | | You should have received a copy of the GNU General Public License along with | GNU Smalltalk; see the file COPYING. If not, write to the Free Software | Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. | ====================================================================== " BLOX.Gui subclass: View [ | data parentView childViews | View class >> new: aString in: view [ | aView | aView := self new. aView parentView: view. ^aView ] data [ "Return view's data object" ^data ] allPrimitivesDo: aBlock [ "Note that this test is a necessary but not a sufficient condition of a Primitive view -- a partially created window can have a Manager which has no children" childViews notNil ifTrue: [childViews do: [:view | view allPrimitivesDo: aBlock]] ifFalse: [aBlock value: self] ] canChangeState [ | aCollection | aCollection := OrderedCollection new. self rootView allPrimitivesDo: [:view | view == self ifFalse: [view canUpdate ifFalse: [^false]]]. ^true ] canUpdate [ "Default is to return true" ^true ] collectPrimitives: aCollection [ "Note that this test is a necessary but not a sufficient condition of a Primitive view -- a partially created window can have a Manager which has no children" childViews notNil ifTrue: [childViews do: [:view | view collectPrimitives: aCollection]] ifFalse: [aCollection add: self] ] childViews [ "Return the view's collection of childViews" ^childViews ] parentView [ "Return view's parentView. If view is a rootView, nil is returned" ^parentView ] parentView: aView [ "Set parentView to aView" parentView := aView ] rootView [ "Return rootView in view's hierarchy" ^parentView isNil ifTrue: [self] ifFalse: [parentView rootView] ] beep [ "Beep once -- usually called when some user error is detected" Blox beep ] remove [ data := nil. childViews isNil ifFalse: [childViews do: [:view | view remove]]. parentView := childViews := nil ] ] View subclass: Primitive [ | menu dirty stateChangeMsg messageDispatch | Primitive class >> updateViews [ "Update all the primitive views" BrowserMain windowsDo: [:i | i allPrimitivesDo: [:view | view update]] ] Primitive class >> new [ ^(super new) dirty: false; yourself ] data: aData [ data := aData ] dirty: aBoolean [ dirty := aBoolean ] isDirty [ ^dirty ] menu [ ^menu ] close [ ^self rootView close ] display [ "Overridden in subclasses. This method is used to support change/update mechanism. In the normal case, this method redraws entire view" ^self subclassResponsibility ] getViewState [ ^messageDispatch ] update: stateChanges [ "Update object based on stateChanges" stateChanges do: [:sc | | viewState | viewState := messageDispatch at: sc state. viewState updateTo: sc counter] ] update [ "Send a getStateChanges: currentViewState message to data object to compute state changes. Send a update: stateChanges message to self to update object" | stateChanges | data isNil ifTrue: [^self]. stateChanges := data getStateChanges: self getViewState. stateChanges notNil ifTrue: [self update: stateChanges] ] handleUserChange: changeSelector [ "This is used to update the data object in response to a user modification of the view" stateChangeMsg := changeSelector ] menuInit: theMenu [ "The popup menu, theMenu, is stored in menu" menu := theMenu ] stateChange: theStateChange updateWith: block [ messageDispatch isNil ifTrue: [messageDispatch := LookupTable new]. messageDispatch at: theStateChange put: (GuiState state: theStateChange counter: 0 action: block) ] ] smalltalk-3.2.5/packages/blox/browser/MethSetBrow.st0000644000175000017500000002351612123404352017411 00000000000000"====================================================================== | | Smalltalk GUI method set browser | | ======================================================================" "====================================================================== | | Copyright 1992,94,95,99,2000,2001,2002 Free Software Foundation, Inc. | Written by Brad Diller and Paolo Bonzini. | | This file is part of GNU Smalltalk. | | GNU Smalltalk is free software; you can redistribute it and/or modify it | under the terms of the GNU General Public License as published by the Free | Software Foundation; either version 2, or (at your option) any later version. | | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS | FOR A PARTICULAR PURPOSE. See the GNU General Public License for more | details. | | You should have received a copy of the GNU General Public License along with | GNU Smalltalk; see the file COPYING. If not, write to the Free Software | Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. | ====================================================================== " GuiData subclass: MethodSetBrowser [ | methodList theClass theSelector selection | MethodSetBrowser class >> referencesTo: anObject parent: listView [ | col value selection | col := SortedCollection sortBlock: [:a :b | a displayString <= b displayString]. (anObject isKindOf: Association) ifTrue: [selection := anObject key. value := anObject value] ifFalse: [selection := nil. value := anObject]. Class allSubclassesDo: [:meta | (meta whichSelectorsReferTo: anObject) do: [:sel | col add: meta >> sel]. (meta instanceClass whichSelectorsReferTo: anObject) do: [:sel | col add: meta instanceClass >> sel]]. col isEmpty ifTrue: [^ModalDialog new alertMessage: 'No references to ' , value printString in: listView]. ^self new openOn: col title: 'References to ' , value printString selection: selection ] MethodSetBrowser class >> implementorsOf: aSymbol parent: listView [ "Opens a message set browser on all methods that implement selected method" | col | col := SortedCollection sortBlock: [:a :b | a displayString <= b displayString]. "Collect all methods which implement selected method. Collection is sorted alphabetically" Class allSubclassesDo: [:meta | (meta includesSelector: aSymbol) ifTrue: [col add: meta >> aSymbol]. (meta instanceClass includesSelector: aSymbol) ifTrue: [col add: meta instanceClass >> aSymbol]]. col isEmpty ifTrue: [^ModalDialog new alertMessage: 'No implementors for ' , aSymbol in: listView]. ^self new openOn: col title: 'Implementors of ' , aSymbol selection: nil ] MethodSetBrowser class >> sendersOf: aSymbol parent: listView [ | col | col := SortedCollection sortBlock: [:a :b | a displayString <= b displayString]. Class allSubclassesDo: [:meta | (meta whichSelectorsReferTo: aSymbol) do: [:sel | col add: meta >> sel]. (meta instanceClass whichSelectorsReferTo: aSymbol) do: [:sel | col add: meta instanceClass >> sel]]. col isEmpty ifTrue: [^ModalDialog new alertMessage: 'No senders for ' , aSymbol in: listView]. ^self new openOn: col title: 'Senders of ' , aSymbol selection: aSymbol ] methodList [ ^methodList ] methodSelection: assoc [ "Derive class and selector from list selection. The selection is derived from an item in the method list pane. A list item may be of two forms: 1) className class selector, or 2) className selector. Form (1) contains 3 string tokens and form (2) contains 2. To derive the class from form (1), the instance class is derived from the Smallltalk dictionary using the first string token as a key. Then class is sent to the instance class to derive the class of the instance class. The selector is derived from the third token. In form (2), the instance class is derived directly from the first string token. The selector is obtained from the second token" | parsing className | assoc value isNil ifTrue: [^theSelector := nil]. theClass := assoc value methodClass. theSelector := assoc value selector. self changeState: #text. Primitive updateViews ] text [ "Return source code for the selected method" theSelector notNil ifTrue: [^theClass -> (theClass >> theSelector) methodRecompilationSourceString]. ^'' ] openOn: aSortedCollection title: name selection: aSymbol [ "Open a method set browser. The argument aMethodDictionary consists of alpha-sorted collection of strings. Each element is of two forms: 1) className class selector, or 2) className selector. This browser consists of two vertically placed panes. The top pane is a list which displays the sorted methods in aMethodDictionary. The bottom pane is a text view which will display the source code for a selector which is selected from the top pane. In general, aSymbol denotes a selector. If this parameter is non-nil, the first occurence of aSymbol will be selected in the text view when a selector is first selected from the top pane" | topView childView aStream listView textView container | aSymbol notNil ifTrue: ["Parse selector expression, aSymbol, inclusive of first colon" aStream := WriteStream on: (String new: 0). aSymbol detect: [:ch | aStream nextPut: ch. ch == $:] ifNone: [0]. selection := aStream contents]. topView := BrowserShell new: name , ' (' , aSortedCollection size printString , ')'. topView data: self. topView blox x: 20. topView blox y: 330. topView blox height: 308. topView blox width: 408. "Use Form class to manage the list and text view panes" childView := Form new: 'Form' in: topView. topView addChildView: childView. container := childView blox. "Create a list in top half of window" childView addChildView: ((listView := PList new: 'MethodSet' in: childView) initialize; data: self; stateChange: #methodList; handleUserChange: #methodSelection:; dataMsg: #methodList; menuInit: (self blueButtonMenuForMethods: listView); yourself). (listView blox) inset: 2; width: 400 height: 150. "Create a text view and install in lower half of window" childView addChildView: ((textView := PCode new: childView) data: self; stateChange: #text; handleUserChange: #compile:from:; textMsg: #text; setBrowserKeyBindings; selection: selection; yourself). textView menuInit: ((PopupMenu new: textView label: 'Edit') selectors: #(#('Cut' #gstCut) #('Copy' #gstCopy) #('Paste' #gstPaste) #() #('Clear' #gstClear) #() #('Line...' #line) #('Find...' #find) #() #('Do it' #eval) #('Print it' #evalAndPrintResult) #('Inspect' #evalAndInspectResult) #() #('Senders' #senders) #('Implementors' #implementors) #() #('Accept' #compileIt) #('Cancel' #revert) #() #('Close' #close)) receiver: textView argument: nil). textView blox width: 400 height: 150. textView blox posVert: listView blox. textView blox inset: 2. "Initialize instance variable, methodList, which governs list display" methodList := aSortedCollection. self changeState: #methodList. Primitive updateViews. "Initialize all the manufactured widgets" topView display ] inspectMethod: listView [ "Bring up an inspector on a Class" theSelector isNil ifTrue: [^listView beep]. (theClass >> theSelector) inspect ] blueButtonMenuForMethods: theView [ "Create method list pane menu" ^(PopupMenu new: theView label: 'Method') selectors: #(#('File out...' #fileOutSelector: #theView) #() #('Senders' #senders: #theView) #('Implementors' #implementors: #theView) #() #(#Inspect #inspectMethod: #theView)) receiver: self argument: theView ] fileOutSelector: listView [ "Creates a file containing description of selected method" | fileName | theSelector isNil ifTrue: [^listView beep]. theClass name notNil ifTrue: [fileName := theClass name] ifFalse: [fileName := theClass asClass name , '-class']. "If the name is too long, maybe truncate it" fileName := self fileoutDir , fileName , '.' , theSelector , '.st'. fileName := Prompter saveFileName: 'File out selector' default: fileName in: listView. fileName isNil ifFalse: [theClass fileOutSelector: theSelector to: fileName. self setFileoutDirFromFile: fileName] ] implementors: listView [ "Open a message set browser that sends the currently selected message" theSelector isNil ifTrue: [^listView beep]. MethodSetBrowser implementorsOf: theSelector parent: listView ] senders: listView [ "Open a message set browser that sends the currently selected message" theSelector isNil ifTrue: [^listView beep]. MethodSetBrowser sendersOf: theSelector parent: listView ] compile: aString from: aView [ "Compile aString derived from text in text view for the selected selector" theSelector isNil ifTrue: [^aView beep]. theClass compile: aString classified: (theClass compiledMethodAt: theSelector) methodCategory ifError: [:fname :lineNo :errorString | aView displayError: errorString at: lineNo. ^nil] ] selection [ ^selection ] ] smalltalk-3.2.5/packages/blox/browser/Inspector.st0000644000175000017500000003173012123404352017151 00000000000000"====================================================================== | | Smalltalk GUI generic inspectors | | ======================================================================" "====================================================================== | | Copyright 1992,94,95,99,2000,2001,2002,2003 Free Software Foundation, Inc. | Written by Brad Diller and Paolo Bonzini. | | This file is part of GNU Smalltalk. | | GNU Smalltalk is free software; you can redistribute it and/or modify it | under the terms of the GNU General Public License as published by the Free | Software Foundation; either version 2, or (at your option) any later version. | | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS | FOR A PARTICULAR PURPOSE. See the GNU General Public License for more | details. | | You should have received a copy of the GNU General Public License along with | GNU Smalltalk; see the file COPYING. If not, write to the Free Software | Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. | ====================================================================== " GuiData subclass: Inspector [ | listView textView topView fieldList fieldLists diveList | text [ "Return string representation of currently selected instance or indexed variable" fieldList currentField == 0 ifTrue: [^'']. ^fieldList currentFieldString ] object [ ^textView object ] object: anObject [ textView object: anObject. fieldLists do: [:each | each value: anObject]. self changeState: #fieldList. self changeState: #text. Primitive updateViews ] fields [ "Return list of variable names displayed in the variable list pane" ^fieldList fields ] currentField: field [ fieldList currentField: field. self changeState: #text. Primitive updateViews ] currentField [ ^fieldList currentField ] fieldLists [ ^fieldLists ] fieldLists: aCollection [ fieldLists := aCollection. self fieldList: aCollection first value ] fieldList: aFieldList [ fieldList := aFieldList. fieldList inspector: self. textView isNil ifFalse: [textView object: fieldList value. listView menuInit: ((fieldList inspectMenu: listView) selectors: #(#() #('Dive' #dive) #('Pop' #pop) #('Browse class' #browse) #()) receiver: self argument: nil). self initFieldListsMenu. self changeState: #fieldList. self changeState: #text. Primitive updateViews] ] initFieldListsMenu [ fieldLists do: [:each | listView menu selectors: { {each key. #fieldList:. each value}} receiver: self] ] open [ | pane | topView := BrowserShell new: 'Inspecting %1%2' % {fieldList value isClass ifFalse: [fieldList value class article , ' '] ifTrue: ['']. fieldList value class nameIn: Namespace current}. topView data: self. topView blox x: 20 y: 330 width: 300 height: 100. pane := Form new: 'forms' in: topView. topView addChildView: pane. self openIn: pane menuName: 'Edit'. topView display ] openIn: pane [ self openIn: pane menuName: 'Edit' ] openIn: pane menuName: label [ "Initialize Inspector and open an Inspector window on anObject" "Initialize instance variable, fields, which governs display of variable list pane" "Create a Form manager which will contain the variable and text pane" | listWidth container | container := pane blox. listWidth := pane blox width // 3 min: 100. "Create a text window and position it in first third of window" pane addChildView: ((listView := PList new: 'InstanceVars' in: pane) initialize; data: self; stateChange: #fieldList; handleUserChange: #currentField:; listMsg: #fields; selectionMsg: #currentField; yourself). (listView blox) width: listWidth height: pane blox height; inset: 2. "Create text pane and position it in right 2/3s of window" pane addChildView: ((textView := PText new: pane) data: self; stateChange: #text; handleUserChange: #setArg:from:; textMsg: #text; canBeDirty: false; setEvaluationKeyBindings; object: fieldList value; yourself). (textView blox) width: pane blox width - listWidth height: pane blox height; inset: 2. textView blox posHoriz: listView blox. "Initialize popup for text pane" textView menuInit: ((PopupMenu new: textView label: label) selectors: #(#('Cut' #gstCut) #('Copy' #gstCopy) #('Paste' #gstPaste) #() #('Clear' #gstClear) #() #('Line...' #line) #('Find...' #find)) receiver: textView argument: nil; selectors: #(#() #('Do it' #eval: #textView) #('Print it' #evalAndPrintResult: #textView) #('Inspect' #inspectValue: #textView)) receiver: self argument: textView; selectors: #(#() #('Accept' #compileIt) #('Cancel' #revert) #() #('Close' #close)) receiver: textView argument: nil; yourself). self fieldLists: self fieldLists. self changeState: #fieldList. Primitive updateViews ] browse [ ClassBrowser new openOn: self object class asClass ] dive [ diveList isNil ifTrue: [diveList := OrderedCollection new]. diveList addLast: fieldLists. self fieldLists: fieldList currentFieldValue inspectorFieldLists ] pop [ diveList isNil ifTrue: [^self]. diveList isEmpty ifTrue: [^self]. self fieldLists: diveList removeLast ] eval: aView [ "Invoked from text pane popup. Evaluate selected expression in text pane" | pos aStream text | text := aView blox getSelection. (text isNil or: [text size = 0]) ifTrue: [^aView beep]. aStream := WriteStream on: (String new: 0). fieldList value class evaluate: text to: fieldList value ] evalAndPrintResult: aView [ "Print result of evaluation of selected expression to its right" | pos result text | text := aView blox getSelection. (text isNil or: [text size = 0]) ifTrue: [^aView beep]. result := fieldList value class evaluate: text to: fieldList value ifError: [:fname :lineNo :errorString | errorString]. aView blox insertTextSelection: result printString ] inspectValue: aView [ "Open an inspector for evaluated selected expression. If selected expression contains parsing error(s), the error description is selected and printed at end of selection" | obj text | text := aView blox getSelection. (text isNil or: [text size = 0]) ifTrue: [^aView beep]. obj := fieldList value class evaluate: text to: fieldList value ifError: [:fname :lineNo :errorString | aView displayError: errorString. ^nil]. obj inspect ] setArg: aString from: aView [ "Store result of evaluation of selected expression in selected instance or indexed variable" | obj | (aString isNil or: [aString size = 0]) ifTrue: [^aView beep]. fieldList currentField <= 1 ifTrue: [^aView beep]. "Evaluate selected expression. If expression contains a parsing error, the description is output at end of expression and nil is returned" obj := fieldList value class evaluate: aString to: fieldList value ifError: [:fname :lineNo :errorString | aView displayError: errorString at: lineNo. ^nil]. fieldList currentFieldValue: obj ] ] ValueHolder subclass: InspectorFieldList [ | inspector fields currentField | evalAndInspectResult: listView [ currentField == 0 ifTrue: [^listView beep]. self currentFieldValue inspect ] inspector [ ^inspector ] inspector: anInspector [ inspector := anInspector ] inspectMenu: listView [ "Initialize menu for variable list pane" ^(PopupMenu new: listView) selectors: #(#('Inspect' #evalAndInspectResult: #listView)) receiver: self argument: listView ] currentField [ ^currentField ] currentField: assoc [ "Set variable list index to 'index'." currentField := assoc key ] currentFieldValue: obj [ self subclassResponsibility ] currentFieldValue [ self subclassResponsibility ] currentFieldString [ ^[self currentFieldValue printString] on: Error do: [:ex | ex return: '[%1 exception raised while printing item]' % {ex class}] ] fieldsSortBlock [ "nil = use OrderedCollection, else a block to be used as fields' sort block." ^nil ] fields [ ^fields ] value: anObject [ super value: anObject. fields := self fieldsSortBlock ifNil: [OrderedCollection new] ifNotNil: [:block | SortedCollection sortBlock: block]. currentField := 0. self computeFieldList: anObject ] computeFieldList: anObject [ "Store a string representation of the inspected object, anObject, in fields. The first string is self. The subsequent values are the object's complete set of instance variables names. If the object is a variable class, append numerical indices from one to number of indexed variables" self subclassResponsibility ] ] InspectorFieldList subclass: ObjectInspectorFieldList [ | base | currentFieldValue: obj [ currentField > base ifTrue: [self value basicAt: currentField - base put: obj] ifFalse: [self value instVarAt: currentField - 1 put: obj] ] currentFieldValue [ currentField == 0 ifTrue: [^nil]. currentField == 1 ifTrue: [^self value]. ^currentField > base ifTrue: [self value basicAt: currentField - base] ifFalse: [self value instVarAt: currentField - 1] ] computeFieldList: anObject [ "Store a string representation of the inspected object, anObject, in fields. The first string is self. The subsequent values are the object's complete set of instance variables names. If the object is a variable class, append numerical indices from one to number of indexed variables" | instVarNames | fields add: 'self'. instVarNames := anObject class allInstVarNames. 1 to: instVarNames size do: [:x | fields add: (instVarNames at: x) asString]. base := fields size. anObject class isVariable ifTrue: [1 to: anObject validSize do: [:x | fields add: x printString]] ] ] ObjectInspectorFieldList subclass: CollectionInspectorFieldList [ | array | currentFieldValue: obj [ (self value isKindOf: SequenceableCollection) not | (self value class == SortedCollection) ifTrue: [(self value) remove: self currentFieldValue ifAbsent: []; add: obj. array := self value asArray. ^self]. self value at: currentField - 1 put: obj. array == self value ifFalse: [array at: currentField - 1 put: obj] ] currentFieldValue [ currentField == 0 ifTrue: [^nil]. currentField == 1 ifTrue: [^self value]. ^array at: currentField - 1 ] computeFieldList: anObject [ "Use this so that the user doesn't see implementation-dependant details" array := (anObject isKindOf: ArrayedCollection) ifFalse: [anObject asArray] ifTrue: [anObject]. super computeFieldList: array ] ] Object extend [ inspectorFieldLists [ ^{'Basic' -> (BLOX.BLOXBrowser.ObjectInspectorFieldList new value: self)} ] basicInspect [ "Open an Inspector window on self" ^(BLOX.BLOXBrowser.Inspector new) fieldLists: {'Basic' -> (BLOX.BLOXBrowser.ObjectInspectorFieldList new value: self)}; open; yourself ] inspect [ "Open an inspection window on self -- by default, the same Inspector used in #basicInspect." ^(BLOX.BLOXBrowser.Inspector new) fieldLists: self inspectorFieldLists; open; yourself ] ] Collection extend [ inspectorFieldLists [ ^ {'Elements' -> (BLOX.BLOXBrowser.CollectionInspectorFieldList new value: self). 'Basic' -> (BLOX.BLOXBrowser.ObjectInspectorFieldList new value: self)} ] ] smalltalk-3.2.5/packages/blox/browser/StrcInspect.st0000644000175000017500000000473512123404352017451 00000000000000"====================================================================== | | Smalltalk GUI inspector for CStruct derivatives | | ======================================================================" "====================================================================== | | Copyright 1992,94,95,99,2000,2001,2002 Free Software Foundation, Inc. | Written by Paolo Bonzini. | | This file is part of GNU Smalltalk. | | GNU Smalltalk is free software; you can redistribute it and/or modify it | under the terms of the GNU General Public License as published by the Free | Software Foundation; either version 2, or (at your option) any later version. | | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS | FOR A PARTICULAR PURPOSE. See the GNU General Public License for more | details. | | You should have received a copy of the GNU General Public License along with | GNU Smalltalk; see the file COPYING. If not, write to the Free Software | Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. | ====================================================================== " InspectorFieldList subclass: CCompoundInspectorFieldList [ currentField: assoc [ "Set list selection to value of index. Force a text view update" assoc key == 0 ifTrue: [currentField := 0] ifFalse: [currentField := (fields at: assoc key) value] ] inspectMenu: listView [ "Initialize menu for variable list pane" ^(PopupMenu new: listView label: 'Field') selectors: #(#('Inspect' #evalAndInspectResult: #listView)) receiver: self argument: listView ] currentFieldValue: obj [ "Cannot change!" ] currentFieldValue [ currentField == 0 ifTrue: [^nil]. ^(self value perform: currentField asSymbol) value ] computeFieldList: anObject [ "Initialize instance variable, fields, which governs display of variable list pane." self value inspectSelectorList do: [:aKey | fields add: (Association key: aKey asString value: aKey)] ] ] CCompound extend [ inspectorFieldLists [ "Open a CCompoundInspectorFieldList window on self" ^{'Basic' -> BLOX.BLOXBrowser.CCompoundInspectorFieldList new value: self} ] ] smalltalk-3.2.5/packages/blox/browser/Load.st0000644000175000017500000000274312123404352016064 00000000000000"====================================================================== | | Smalltalk GUI browser initialization script | | ======================================================================" "====================================================================== | | Copyright 1992,94,95,99,2000,2001,2002 Free Software Foundation, Inc. | Written by Brad Diller. | | This file is part of GNU Smalltalk. | | GNU Smalltalk is free software; you can redistribute it and/or modify it | under the terms of the GNU General Public License as published by the Free | Software Foundation; either version 2, or (at your option) any later version. | | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS | FOR A PARTICULAR PURPOSE. See the GNU General Public License for more | details. | | You should have received a copy of the GNU General Public License along with | GNU Smalltalk; see the file COPYING. If not, write to the Free Software | Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. | ====================================================================== " Eval [ Class allSubclassesDo: [:each | (each instanceClass notNil and: [each instanceClass includesSelector: #inspect]) ifTrue: [each instanceClass removeSelector: #inspect]]. (BLOX.BLOXBrowser includesKey: #BrowserMain) ifTrue: [BLOX.BLOXBrowser.BrowserMain close] ] smalltalk-3.2.5/packages/blox/browser/Manager.st0000644000175000017500000001233612123404352016556 00000000000000"====================================================================== | | Smalltalk GUI wrapper for windows with children | | ======================================================================" "====================================================================== | | Copyright 1992,94,95,99,2000,2001,2002 Free Software Foundation, Inc. | Written by Brad Diller. | | This file is part of GNU Smalltalk. | | GNU Smalltalk is free software; you can redistribute it and/or modify it | under the terms of the GNU General Public License as published by the Free | Software Foundation; either version 2, or (at your option) any later version. | | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS | FOR A PARTICULAR PURPOSE. See the GNU General Public License for more | details. | | You should have received a copy of the GNU General Public License along with | GNU Smalltalk; see the file COPYING. If not, write to the Free Software | Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. | ====================================================================== " View subclass: Manager [ addChildView: aChildView [ "Add childView to list of childViews of a view" childViews isNil ifTrue: ["Initialize childViews collection" childViews := OrderedCollection new]. childViews add: aChildView. "Set parentView of aChildView to self" aChildView parentView: self ] addLabel: aString at: aPoint [ (BLabel new: self blox label: aString) origin: aPoint ] addLabel: aString below: aPrimitive [ (BLabel new: self blox label: aString) posVert: aPrimitive blox ] addLabel: aString rightOf: aPrimitive [ (BLabel new: self blox label: aString) posHoriz: aPrimitive blox ] allPrimitivesDo: aBlock [ childViews isNil ifTrue: [^self]. super allPrimitivesDo: aBlock ] deleteChildView: aChildView [ childViews notNil ifTrue: [childViews remove: aChildView. aChildView remove] ] ] Manager subclass: Form [ Form class >> new: aString in: view [ | aView | aView := super new: aString in: view. aView blox: (BForm new: view blox). ^aView ] ] Manager subclass: OrderedForm [ OrderedForm class >> new: aString in: view [ | aView | aView := super new: aString in: view. aView blox: (BContainer new: view blox). ^aView ] OrderedForm class >> horizontal: aString in: view [ | result | result := self new: aString in: view. result blox setVerticalLayout: false. ^result ] ] Manager subclass: TopLevelShell [ | menuBar | TopLevelShell class >> new: aLabel [ "Initialize TopLevelShell" | view | view := self new initialize: aLabel. BrowserMain shell isNil ifFalse: [BrowserMain addWindow: view]. ^view ] canClose [ self rootView allPrimitivesDo: [:view | view canUpdate ifFalse: [^false]]. ^true ] close [ | canClose | canClose := self canClose. canClose ifTrue: [self blox destroy. self remove]. ^canClose ] destroyed [ "This method is invoked from the callback which is activated when the user closes a window. Each view is sent an canUpdate message. If there is some information which has been cached and not incorporated into the data object (modified text which has not been compiled), this method will inform the callback by returning nil. If the window can be closed, the top level widget is returned. The widget value is needed so that the view's supporting widget hierarchy can be disposed properly" ^self canClose ] remove [ super remove. BrowserMain removeWindow: self ] display [ self blox map ] data: aData [ "Even though this view is not properly a data view, the data view is associated with a TopLevelShell to support change control. When a user attempts to close the window, the close method which is invoked can communicate this to the data objects's views by sending a message to the data object associated with it." data := aData ] initialize: aLabel [ blox := BWindow new: aLabel. self blox callback: self message: #destroyed. #('Control-1' 'Control-2' 'Control-3') with: #(#openWorksheet #openBrowser #openNamespaceBrowser) do: [:key :sel | self blox onKeyEvent: key send: sel to: BrowserMain] ] menu: aMenu [ self menuBar add: aMenu blox ] menuBar [ menuBar isNil ifTrue: [menuBar := BMenuBar new: self blox]. ^menuBar ] ] smalltalk-3.2.5/packages/blox/browser/stamp-classes0000644000175000017500000000000012123404352017317 00000000000000smalltalk-3.2.5/packages/blox/browser/ClassHierBrow.st0000644000175000017500000010463112123404352017713 00000000000000"====================================================================== | | Smalltalk GUI class hierarchy browser | | ======================================================================" "====================================================================== | | Copyright 1992,94,95,99,2000,2001,2002,2003,2007,2008 Free Software Foundation, Inc. | Written by Brad Diller and Paolo Bonzini. | | This file is part of GNU Smalltalk. | | GNU Smalltalk is free software; you can redistribute it and/or modify it | under the terms of the GNU General Public License as published by the Free | Software Foundation; either version 2, or (at your option) any later version. | | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS | FOR A PARTICULAR PURPOSE. See the GNU General Public License for more | details. | | You should have received a copy of the GNU General Public License along with | GNU Smalltalk; see the file COPYING. If not, write to the Free Software | Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. | ====================================================================== " GuiData subclass: ClassHierarchyBrowser [ | curClass curCategory curSelector textMode textView meta classList sortedMethodsByCategoryDict categoriesForClass topClasses shownClasses fileoutDir | classList [ ^classList ] classList: curClassList message: aMessage [ "This method is used to implement selective updates of the class list pane. Currently the selected class, curClass, is unselected and the instance variables, curSelector and curCategory, which are related to the selected class, are reinitialized. The message type, aMessage, is sent to the data object. The update method for the affected class pane will update the portion which needs to be updated based on the message type parameter, aMessage. Other messages are posted through the change/update mechanism so that the rest of the window will be appropriately updated." classList := curClassList. curSelector := nil. curCategory := nil. textMode := #source. self changeState: aMessage; changeState: #methodCategories; changeState: #methods. self changeState: #text. Primitive updateViews ] classSelection: assoc [ "assoc contains current class selection. Find the class associated with the selected string in shownClasses dictionary. Save the class in the instance variable, curClass. Update other related instance variables. Since the other panes in the browser descend from the class, the instance variables associated with each pane must be nilled out. Send update messages to the data object" curClass := (assoc isNil or: [assoc value isNil]) ifTrue: [nil] ifFalse: [shownClasses at: assoc value]. textView object: curClass. curSelector := nil. curCategory := nil. textMode := #source. self changeState: #methodCategories; changeState: #methods. self changeState: #text. Primitive updateViews ] classString [ "Return name of selected class indented by 'n' spaces, where 'n' is the number of class' superclasses" | spaces | curClass isNil ifTrue: [^nil]. spaces := String new: curClass allSuperclasses size * self indentString size. spaces atAllPut: Character space. ^spaces , curClass name ] indentString [ ^' ' ] listMethodCategory: assoc [ curCategory := assoc value. self methodCategory: curCategory ] meta [ "If class methods are being viewed, return true" ^meta ] meta: aBoolean [ "Change instance/class representation and record data state changes" meta = aBoolean ifTrue: [^self]. meta := aBoolean. curCategory := nil. curSelector := nil. self changeState: #methodCategories; changeState: #methods; changeState: #text. Primitive updateViews ] method [ "Return the selected method which is stored in curSelector" ^curSelector ] method: assoc [ "Set curSelector to aMethod, update text mode, and record state change" curSelector := assoc value. textMode := #source. self changeState: #text. Primitive updateViews ] methodCategories [ "This method is invoked by the change/update mechanism when a new class is selected. To improve efficiency, method dictionary is cached. Methods are sorted by category and saved in a dictionary, sortedMethodByCategoryDict. When a new category is selected, this dictionary is consulted. The class's method categories sorted by name are returned" | deClass category catSet | curClass isNil ifTrue: [^SortedCollection new]. deClass := self getClass. categoriesForClass = deClass ifTrue: [^sortedMethodsByCategoryDict keys asSortedCollection]. categoriesForClass := deClass. sortedMethodsByCategoryDict := Dictionary new. catSet := Set new. deClass selectors do: [:aSelector | catSet add: (category := (deClass compiledMethodAt: aSelector) methodCategory). (sortedMethodsByCategoryDict at: category ifAbsent: [sortedMethodsByCategoryDict at: category put: SortedCollection new]) add: aSelector]. ^catSet asSortedCollection ] methodCategory [ ^curCategory ] methodCategory: listItem [ "Update curCategory. Reinitialize the instance variable, curSelector. Notify affected panes through the change/update mechanism" curCategory := listItem. textMode := #source. self changeState: #methods. curSelector notNil ifTrue: [curSelector := nil]. "Ask the data object whether the selector list view can change it. Deselect currently selected method and force text pane, record state change and force update" textMode := #addMethod. self changeState: #text. Primitive updateViews ] methods [ "Return the sorted methods for selected category" curCategory isNil ifTrue: [^Array new: 0]. ^sortedMethodsByCategoryDict at: curCategory ifAbsent: [Array new: 0] ] getAddMethodTemplate [ "Return add method template" ^'method: selectors and: arguments "Comment describing purpose and answered value." | temporary variables | statements ' ] text [ "Return a text string depending on the text mode (textMode) of the data object" | aStream count | textMode == #addClass ifTrue: [^self getAddClassTemplate]. curClass isNil ifTrue: ["If no class is selected, return empty string" ^String new: 0]. textMode == #comment ifTrue: ["Return comment associated with selected class" ^self getClass comment isNil ifTrue: [''] ifFalse: [curClass comment]]. textMode == #addMethod ifTrue: [^self getClass -> self getAddMethodTemplate]. curSelector isNil ifTrue: [aStream := WriteStream on: (String new: 0). curClass fileOutDeclarationOn: aStream. ^aStream contents]. "Display method source for selected class" ^self getClass -> (self getClass >> curSelector) methodRecompilationSourceString ] addCategory: listView [ "If a class is selected, prompt the user to enter a new message category. If a legitimate category is entered, update the method list pane (listView) and System classes" | newCategory | curClass isNil ifTrue: [^listView beep]. newCategory := (Prompter message: 'Enter a new message category' in: listView) response. newCategory = '' ifTrue: [^self]. "If new category already exists, reject" (sortedMethodsByCategoryDict includesKey: newCategory) ifTrue: [^ModalDialog new alertMessage: 'Invalid name: the category, ' , newCategory , ', already exists.' in: listView]. sortedMethodsByCategoryDict at: newCategory put: SortedCollection new. self changeState: #methodCategories. self methodCategory: newCategory ] blueButtonMenuForCategories: theView [ "Install popup menu for category pane" ^(PopupMenu new: theView label: 'Protocol') selectors: #(#('File out...' #fileOutCategory: #theView) #() #('Add...' #addCategory: #theView) #('Rename...' #renameCategory: #theView) #('Remove...' #removeCategory: #theView)) receiver: self argument: theView ] fileOutCategory: listView [ "File out a description of the methods which belong to the selected method category. A file selection dialog is displayed which prompts the user for the name and directory location of the file" | fileName deClass | curCategory isNil ifTrue: [^listView beep]. deClass := self getClass. deClass name notNil ifTrue: [fileName := deClass name] ifFalse: [fileName := deClass asClass name , '-class']. "If the name is too long, maybe truncate it?" fileName := self fileoutDir , fileName , '.' , curCategory , '.st'. fileName := Prompter saveFileName: 'File out category' default: fileName in: listView. fileName isNil ifFalse: [deClass fileOutCategory: curCategory to: fileName. self setFileoutDirFromFile: fileName] ] removeCategory: listView [ "Remove currently selected message category" | cancel | curCategory isNil ifTrue: [^listView beep]. (ModalDialog new) message: 'Are you sure you want to remove the category, ' , curCategory , '?' in: listView; addButton: 'Yes' message: [cancel := false]; addButton: 'No' message: [cancel := true]; display: listView. cancel ifTrue: [^self]. "Update category list" self methods notNil ifTrue: ["Update sorted cache of class's message dictionary" sortedMethodsByCategoryDict removeKey: curCategory ifAbsent: [^self]. self getClass removeCategory: curCategory]. "Nil out curCategory and notify affected panes through the change/update mechanism" curCategory := nil. self changeState: #methodCategories; changeState: #methods; changeState: #text. Primitive updateViews ] renameCategory: listView [ "Change selected message category name" | newName | curCategory isNil ifTrue: [^listView beep]. "Prompt the user for new name" newName := (Prompter message: 'Rename message category: ' , curCategory in: listView) response. newName isEmpty ifTrue: [^self] ifFalse: ["If new category already exists, reject" (sortedMethodsByCategoryDict includesKey: newName) ifTrue: [^ModalDialog new alertMessage: 'Invalid name: the category, ' , newName , ', already exists.' in: listView]]. "If new name is entered, update cache of sorted methods" sortedMethodsByCategoryDict at: newName put: (sortedMethodsByCategoryDict at: curCategory). sortedMethodsByCategoryDict removeKey: curCategory. "Update system" self getClass methodDictionary do: [:method | method methodCategory = curCategory ifTrue: [method methodCategory: newName]]. "Update instance variable and directly update the category pane (listView)" curCategory := newName. self changeState: #methodCategories. Primitive updateViews ] currentNamespace [ ^Namespace current ] hierarchyNames: startingClasses [ | collection topMetas | shownClasses := Dictionary new: 100. ^self makeDescendentsDictionary: (self makeFullTree: startingClasses) thenPutOn: (WriteStream on: (Array new: 75)) ] makeDescendentsDictionary: dict thenPutOn: stream [ "From the dict Dictionary, created by #makeFullTree:, create another with the same keys. Each key is associated to a set of classes which are all the immediate subclasses which are also keys of dict. Then this dictionary is passed to the recursive method #printHierarchyOf:hierarchy:startAt:on:" | descendents | descendents := dict collect: [:each | Set new]. descendents at: #none put: Set new. dict keysDo: [:each | each superclass isNil ifTrue: [(descendents at: #none) add: each] ifFalse: [(descendents at: each superclass) add: each]]. ^self printHierarchyOf: dict hierarchy: descendents startAt: #none on: stream indent: '' ] makeFullTree: classes [ "From the classes collection, create a Dictionary in which we ensure that every key's superclass is also a key. For example, if classes contained Object and Array, the dictionary would also have Collection, SequenceableCollection and ArrayedCollection as keys. For every key, its value is true if classes includes it, else it is false." | dict newClasses checkClasses | dict := IdentityDictionary new: classes size. classes do: [:each | dict at: each put: true]. checkClasses := dict keys. [newClasses := Set new. checkClasses do: [:each | each superclass isNil ifFalse: [(dict includesKey: each superclass) ifFalse: [newClasses add: each superclass]]]. newClasses isEmpty] whileFalse: [newClasses do: [:each | dict at: each put: false]. checkClasses := newClasses]. ^dict ] printHierarchyOf: dict hierarchy: desc startAt: root on: stream indent: indent [ "Recursive worker method for #printHierarchyOf:on: dict is the classes Dictionary as obtained by makeFullTree:, desc is the classes Dictionary as passed by makeDescendentsDictionary:thenCollectOn:" | subclasses string | subclasses := desc at: root. subclasses := subclasses asSortedCollection: [:a :b | a name <= b name]. subclasses do: [:each | | template | template := (dict at: each) ifTrue: ['%1%2'] ifFalse: ['%1(%2)']. string := template % {indent. each nameIn: self currentNamespace}. shownClasses at: string put: each. stream nextPut: string. self printHierarchyOf: dict hierarchy: desc startAt: each on: stream indent: indent , self indentString]. ^stream contents ] addClass: classList [ "When 'add' is selected from class pane popup menu, this action is invoked. Update mode of text pane. Nil out currently selected method and method category. Record state change" (curClass notNil and: [classList canChangeState]) ifFalse: [^classList beep]. textMode := #addClass. curCategory := nil. curSelector := nil. self changeState: #removeCategorySelection; changeState: #methods; changeState: #text. Primitive updateViews ] blueButtonMenuForClasses: theView [ "Install popup for class list popup" ^(PopupMenu new: theView label: 'Class') selectors: #(#('File out...' #fileOutClass: #theView) #('Update' #updateClassList) #() #('Compile' #compileClass: #theView) #('Compile all' #compileAll: #theView) #() #('Comment' #comment: #theView) #('References' #classRefs: #theView) #() #('Add' #addClass: #theView) #('Rename...' #renameClass: #theView) #('Remove...' #removeClass: #theView) #('Search...' #searchClass: #theView) #() #(#Inspect #inspectClass: #theView)) receiver: self argument: theView ] classRefs: listView [ "Activated from class pane popup menu. Open a message set browser on all methods that refer to currently selected class" | methods assoc | curClass isNil ifTrue: [^listView beep]. methods := SortedCollection new. assoc := curClass environment associationAt: curClass name asSymbol. "For all selectors which refer to the selected class, add the class name concatenated with selector name in the sorted collection 'methods'" CompiledMethod allInstancesDo: [:method | (method refersTo: assoc) ifTrue: [methods add: method]]. methods isEmpty ifTrue: [^ModalDialog new alertMessage: 'No references to ' , curClass name in: listView]. MethodSetBrowser new openOn: methods title: 'References to ' , curClass name selection: curClass name ] comment: aPList [ "Change text mode to comment mode. Trigger an update to the text and selector panes" curClass isNil ifTrue: [^aPList beep]. "Ask the data object whether the class list view can change itself" aPList canChangeState ifFalse: [^self]. textView canChangeState ifFalse: [^self]. textMode := #comment. "Deselect currently selected category and selector" curCategory := nil. curSelector := nil. self changeState: #methodCategories; changeState: #methods; changeState: #text. Primitive updateViews ] compileAll: listView [ "Activated from class list popup. Recompile the selected class and its subclasses. The Metaclasses are recompiled as well" curClass isNil ifTrue: [^listView beep]. curClass compileAll. curClass class compileAll. curClass compileAllSubclasses. curClass class compileAllSubclasses. self changeState: #methodCategories ] compileClass: listView [ "Recompile selected class and its Metaclass" curClass isNil ifTrue: [^listView beep]. curClass compileAll. curClass class compileAll. self changeState: #methodCategories ] inspectClass: listView [ "Bring up an inspector on a Class" curClass inspect ] fileOutClass: listView [ "File out a description of the currently selected class" | className fileName | curClass isNil ifTrue: [^listView beep]. curClass name notNil ifTrue: [className := curClass name] ifFalse: [className := curClass asClass name , '-class']. fileName := self fileoutDir , className , '.st'. fileName := Prompter saveFileName: 'File out class' default: fileName in: listView. fileName isNil ifFalse: [curClass fileOut: fileName. self setFileoutDirFromFile: fileName] ] fileoutDir [ | home | fileoutDir isNil ifTrue: ["If the image directory is a subdirectory of the home directory, the default is the image directory. Else the default is the home directory" fileoutDir := Directory image name , '/'. home := Directory home name. home isEmpty ifFalse: [fileoutDir size < home size ifTrue: [^fileoutDir := home , '/']. home = (fileoutDir copyFrom: 1 to: home size) ifTrue: [^fileoutDir := home , '/']]]. ^fileoutDir ] getAddClassTemplate [ "Return add class template" | curClassName | curClassName := curClass isNil ifTrue: ['NameOfSuperClass'] ifFalse: [curClass printString]. ^curClassName , ' subclass: #NameOfClass instanceVariableNames: '''' classVariableNames: '''' poolDictionaries: '''' category: nil ' ] removeClass: listView [ "Remove selected class from system" | badClasses assoc classes cancel | curClass isNil ifTrue: [^listView beep]. curClass subclasses isEmpty ifFalse: [^self error: 'Must delete subclasses first']. (ModalDialog new) message: 'Are you sure you want to remove the class, ' , curClass name , '?' in: listView; addButton: 'Yes' message: [cancel := false]; addButton: 'No' message: [cancel := true]; display: listView. cancel ifTrue: [^self]. "If there are any instance of curClass, disallow curClass to be removed. Force a garbage collection to get rid of unreferenced instances" (curClass instanceCount > 0 and: [ObjectMemory compact. curClass instanceCount > 0]) ifTrue: [^self error: 'Cannot remove because class has instances.']. "Search system for all external references to class" badClasses := {curClass. curClass class}. assoc := curClass environment associationAt: curClass name. Class allSubclassesDo: [:subclass | (badClasses includes: subclass) ifFalse: [(subclass instanceClass whichSelectorsReferTo: assoc) do: [:sel | "Ignore references in transitory selector -- executeStatements" sel ~= #executeStatements ifTrue: [^self error: 'External references remain to class which is to be deleted']]. (subclass whichSelectorsReferTo: assoc) do: [:sel | "Ignore references in transitory selector -- executeStatements" sel ~= #executeStatements ifTrue: [^self error: 'External references remain to class which is to be deleted']]]]. curClass allSuperclassesDo: [:each | each removeSubclass: curClass. each class removeSubclass: curClass class]. "Update namespace" curClass environment removeKey: curClass name asSymbol. self updateClassList. self classSelection: nil ] renameClass: listView [ "Rename currently selected class" | methods oldName newName prompter oldAssoc | curClass isNil ifTrue: [^listView beep]. oldName := curClass name. "Prompt user for new name" prompter := Prompter message: 'Rename class: ' , curClass name in: listView. prompter response isEmpty ifTrue: [^self] ifFalse: [newName := prompter response asSymbol. (newName at: 1) isUppercase ifFalse: [^self error: 'Class name should begin with an uppercase letter']. (curClass environment includesKey: newName) ifTrue: [^self error: newName , ' already exists']]. "Save old Association" oldAssoc := curClass environment associationAt: oldName. "Rename the class now" curClass setName: newName asSymbol. "Fix up namespace" curClass environment at: curClass name put: oldAssoc value. curClass environment removeKey: oldName. "Notify programmer of all references to renamed class" methods := SortedCollection new. CompiledMethod allInstancesDo: [:method | (method refersTo: oldAssoc) ifTrue: [methods add: method]]. methods isEmpty ifFalse: [ModalDialog new alertMessage: 'Rename all references to class ' , oldName , Character nl , 'to the new name: ' , newName in: listView. MethodSetBrowser new openOn: methods title: 'References to ' , oldName selection: oldName]. "Update class list" self updateClassList ] searchClass: listView [ | newClass found | newClass := (Prompter message: 'Enter the class to be searched' in: listView) response. newClass isEmpty ifTrue: [^self]. "First pass, search for a qualified name." found := self searchClassIn: listView suchThat: [:class | newClass sameAs: (class nameIn: self currentNamespace)]. "Second pass, only look for the name." (found or: [newClass includes: $.]) ifFalse: [found := self searchClassIn: listView suchThat: [:class | newClass sameAs: class name]]. found ifTrue: [^self]. ^ModalDialog new alertMessage: 'Invalid name: the class, ' , newClass , ', does not exist.' in: listView ] searchClassIn: listView suchThat: aBlock [ | class indent i listBlox numClasses | class := shownClasses detect: aBlock ifNone: [nil]. class isNil ifTrue: [^false]. curClass := class. textView object: curClass. listView select: self classString. ^true ] setFileoutDirFromFile: fileName [ fileoutDir := fileName copyFrom: 1 to: (fileName findLast: [:c | c = $/]) ] topClasses [ ^Array streamContents: [:stream | Namespace current allClassesDo: [:each | stream nextPut: each]] ] updateClassList [ "Invoked from class list pane popup. Update class list pane through the change/update mechanism" topClasses := self topClasses. topClasses size >= 2 ifTrue: [topClasses := topClasses asSortedCollection: [:a :b | a name <= b name]]. self classList: (self hierarchyNames: topClasses) message: #classList ] createClassesListIn: upper [ | list | upper addChildView: ((list := PList new: 'Classes' in: upper) initialize; data: self; stateChange: #classList; changedSelection: #newClassSelection; handleUserChange: #classSelection:; listMsg: #classList; selectionMsg: #classString; menuInit: (self blueButtonMenuForClasses: list); yourself). "Register three types of messages" self layoutUpperPaneElement: list blox num: 0 ] createLowerPaneIn: topView below: upper [ topView addChildView: ((textView := PCode new: topView) data: self; stateChange: #text; handleUserChange: #compile:from:; setBrowserKeyBindings; menuInit: (self blueButtonMenuForText: textView); textMsg: #text; yourself). (textView blox) width: 600 height: 200; posVert: upper blox; inset: 2 ] createProtocolListIn: upper [ | pane list radioForm radioGroup | upper addChildView: (pane := OrderedForm new: 'Middle' in: upper). pane blox setVerticalLayout: true. self layoutUpperPaneElement: pane blox num: 1. "Add method categories list pane in middle third of window" pane addChildView: ((list := PList new: 'Categories' in: pane) initialize; data: self; stateChange: #methodCategories; changedSelection: #removeCategorySelection; handleUserChange: #listMethodCategory:; listMsg: #methodCategories; selectionMsg: #methodCategory; menuInit: (self blueButtonMenuForCategories: list); yourself). list blox stretch: true. pane addChildView: (radioForm := RadioForm new: 'RadioGroup' in: pane). radioGroup := radioForm blox. radioForm addChildView: (PRadioButton on: self parentView: radioGroup isPressed: #meta label: 'instance' handleUserChange: #meta: value: false). radioForm addChildView: (PRadioButton on: self parentView: radioGroup isPressed: #meta label: 'class' handleUserChange: #meta: value: true) ] createSelectorListIn: upper [ "Add selectors list pane in top right third of window" | list | upper addChildView: ((list := PList new: 'Selectors' in: upper) initialize; data: self; stateChange: #methods; handleUserChange: #method:; listMsg: #methods; selectionMsg: #method; menuInit: (self blueButtonMenuForMethods: list); yourself). self layoutUpperPaneElement: list blox num: 2 ] createUpperPanesIn: upper [ self createClassesListIn: upper. self createProtocolListIn: upper. self createSelectorListIn: upper ] initialize [ self updateClassList ] layoutUpperPaneElement: blox num: n [ blox x: 200 * n y: 0 width: 200 height: 200 ] createTopView [ ^BrowserShell new: 'Class Hierarchy Browser' ] open [ "Create and open a class browser" | topView upper container win | meta := false. "Create top view" topView := self createTopView. topView data: self. win := topView blox. win x: 20 y: 50 width: 604 height: 404. upper := Form new: 'ListForms' in: topView. topView addChildView: upper. container := upper blox. container x: 0 y: 0 width: 600 height: 200; inset: 2. self createUpperPanesIn: upper. self createLowerPaneIn: topView below: upper. self initialize. topView display ] compileMethod: aString for: aView [ "Compile the method source, aString, for the selected class. Compilation class is set according to the radio button state. If 'meta' is true, set aClass to selected class, curClass, to its Metaclass. If method is successfully compiled, related instance variables are updated." | compiledMethod selector dupIndex collection aClass | aClass := meta ifTrue: [curClass class] ifFalse: [curClass]. curCategory isNil ifTrue: [curCategory := (Prompter message: 'Enter method category' default: 'As yet unclassified' in: aView) response. curCategory isEmpty ifTrue: [curCategory := 'As yet unclassified']]. "The exception block will be invoked if aString contains parsing errors. The description of the error will be displayed and selected at the end of the line in which the error is detected by the parser. Nil is returned" compiledMethod := aClass compile: aString classified: curCategory ifError: [:fname :lineNo :errorString | aView displayError: errorString at: lineNo. ^nil]. "Retrieve selector" (compiledMethod selector = curSelector and: [compiledMethod methodCategory = curCategory]) ifTrue: [^compiledMethod]. "Need to do additional housekeeping to keep internal version of method dictionary, sortedMethodsByCategoryDict, in synch with the class's method dictionary. Remove duplicates stored in the internal version of method dictionary" curSelector := compiledMethod selector. curCategory := compiledMethod methodCategory. sortedMethodsByCategoryDict do: [:methods | methods remove: curSelector ifAbsent: []]. "Now add selector to internal copy" (sortedMethodsByCategoryDict at: curCategory ifAbsentPut: [SortedCollection new]) add: curSelector. self changeState: #methods. self changeState: #methodCategories. Primitive updateViews. ^compiledMethod ] getClass [ "If 'meta' is true, return selected class's Metaclass; otherwise, selected class is returned" meta ifTrue: [^curClass class] ifFalse: [^curClass] ] inspectMethod: listView [ "Bring up an inspector on a Class" curSelector isNil ifTrue: [^listView beep]. (self getClass >> curSelector) inspect ] blueButtonMenuForMethods: theView [ "Create method list pane menu" ^(PopupMenu new: theView label: 'Method') selectors: #(#('File out...' #fileOutSelector: #theView) #() #('Senders' #senders: #theView) #('Implementors' #implementors: #theView) #() #('Remove...' #removeMethod: #theView) #() #(#Inspect #inspectMethod: #theView)) receiver: self argument: theView ] fileOutSelector: listView [ "Creates a file containing description of selected method" | deClass fileName | curSelector isNil ifTrue: [^listView beep]. deClass := self getClass. deClass name notNil ifTrue: [fileName := deClass name] ifFalse: [fileName := deClass asClass name , '-class']. "If the name is too long, maybe truncate it" fileName := self fileoutDir , fileName , '.' , curSelector , '.st'. fileName := Prompter saveFileName: 'File out selector' default: fileName in: listView. fileName isNil ifFalse: [deClass fileOutSelector: curSelector to: fileName. self setFileoutDirFromFile: fileName] ] implementors: listView [ "Open a message set browser that sends the currently selected message" curSelector isNil ifTrue: [^listView beep]. MethodSetBrowser implementorsOf: curSelector parent: listView ] removeMethod: listView [ "Removes selected method" | cancel | curSelector isNil ifTrue: [^listView beep]. (ModalDialog new) message: 'Are you sure you want to remove the method, ' , curSelector , '?' in: listView; addButton: 'Yes' message: [cancel := false]; addButton: 'No' message: [cancel := true]; display: listView. cancel ifTrue: [^self]. "Remove method from system" self getClass removeSelector: curSelector. (sortedMethodsByCategoryDict at: curCategory) remove: curSelector. "Update listView" curSelector := nil. "Record state change" self changeState: #methods; changeState: #text. Primitive updateViews ] senders: listView [ "Open a message set browser that sends the currently selected message" curSelector isNil ifTrue: [^listView beep]. MethodSetBrowser sendersOf: curSelector parent: listView ] blueButtonMenuForText: theView [ "Create menu for text pane" ^(PopupMenu new: theView label: 'Edit') selectors: #(#('Cut' #gstCut) #('Copy' #gstCopy) #('Paste' #gstPaste) #() #('Clear' #gstClear) #() #('Line...' #line) #('Find...' #find) #() #('Do it' #eval) #('Print it' #evalAndPrintResult) #('Inspect' #evalAndInspectResult) #() #('Senders' #senders) #('Implementors' #implementors) #() #('Accept' #compileIt) #('Cancel' #revert) #() #('Close' #close)) receiver: theView argument: nil ] compile: aString from: aView [ "Compile aString derived from the text pane (aView). The way aString is compiled depends on the text mode" | aClass | curClass isNil ifTrue: [^aView beep]. "If the text in the text pane is method source code, compile it" (curSelector notNil or: [textMode == #addMethod]) ifTrue: [^self compileMethod: aString for: aView]. textMode == #comment ifTrue: [curClass comment: aString. ^aString]. "Otherwise, evaluate the text. If no method source is displayed, then aString is evaluated independently. If the string constitutes a legal class definition, the class is returned in aClass" curClass environment whileCurrentDo: [aClass := Behavior evaluate: aString ifError: [:file :line :msg | ^nil]]. aClass isClass ifFalse: [^self]. "If ClassHierarchyBrowser is modified, force an immediate exit because this method context is still referencing it by the old memory model" (self isKindOf: aClass) | (aClass == curClass) ifTrue: [^self]. curClass := aClass. textView object: curClass. "Update class pane" (classList includes: aClass) ifTrue: ["If the class already exists, inform the class pane indirectly through the change/update mechanism that the selection only needs to be updated" self classList: classList message: #newClassSelection] ifFalse: ["If the class does not exist, update instance variables and inform the affected panes through the change/update mechanism" self updateClassList]. textMode := #source ] ] smalltalk-3.2.5/packages/blox/browser/package.xml0000644000175000017500000000203012123404352016737 00000000000000 BLOXBrowser Browser BLOX.BLOXBrowser BLOX.BLOXBrowser.BrowserMain new initialize Blox Parser DebugTools Load.st GuiData.st View.st Manager.st RadioForm.st Menu.st ModalDialog.st PList.st PText.st PCode.st ButtonForm.st BrowShell.st BrowserMain.st ClassHierBrow.st ClassBrow.st NamespBrow.st MethSetBrow.st Inspector.st DictInspect.st MethInspect.st StrcInspect.st DebugSupport.st Debugger.st Notifier.st ChangeLog smalltalk-3.2.5/packages/blox/browser/GuiData.st0000644000175000017500000000605012123404352016516 00000000000000"====================================================================== | | Smalltalk GUI publish-subscribe framework | | ======================================================================" "====================================================================== | | Copyright 1992,94,95,99,2000,2001,2002 Free Software Foundation, Inc. | Written by Brad Diller and Paolo Bonzini. | | This file is part of GNU Smalltalk. | | GNU Smalltalk is free software; you can redistribute it and/or modify it | under the terms of the GNU General Public License as published by the Free | Software Foundation; either version 2, or (at your option) any later version. | | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS | FOR A PARTICULAR PURPOSE. See the GNU General Public License for more | details. | | You should have received a copy of the GNU General Public License along with | GNU Smalltalk; see the file COPYING. If not, write to the Free Software | Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. | ====================================================================== " Object subclass: GuiState [ | state counter action | GuiState class >> state: aSymbol counter: anInteger [ ^self new initState: aSymbol counter: anInteger action: ValueHolder null ] GuiState class >> state: aSymbol counter: anInteger action: aBlock [ ^self new initState: aSymbol counter: anInteger action: aBlock ] counter [ ^counter ] updateTo: newCounter [ counter := newCounter. ^action value ] state [ ^state ] initState: aSymbol counter: anInteger action: aBlock [ state := aSymbol. counter := anInteger. action := aBlock ] ] BLOX.Gui subclass: GuiData [ | checkpoints | changeState: anObject [ "Record the state change denoted by anObject" | updateCount | checkpoints isNil ifTrue: [checkpoints := LookupTable new]. updateCount := checkpoints at: anObject ifAbsent: [0]. checkpoints at: anObject put: updateCount + 1 ] getCurrentState [ ^checkpoints copy ] getStateChanges: viewState [ "Compare current state with viewState and return an object which describes differences" | stateChanges | viewState isNil | checkpoints isNil ifTrue: [^nil]. viewState keysAndValuesDo: [:stateId :state | | stateValue | stateValue := checkpoints at: stateId ifAbsent: [0]. state counter < stateValue ifTrue: [stateChanges isNil ifTrue: [stateChanges := Set new]. stateChanges add: (GuiState state: stateId counter: stateValue)]]. ^stateChanges ] ] smalltalk-3.2.5/packages/blox/browser/PList.st0000644000175000017500000001141212123404352016231 00000000000000"====================================================================== | | Smalltalk GUI wrapper for list boxes | | ======================================================================" "====================================================================== | | Copyright 1992,94,95,99,2000,2001,2002,2003 Free Software Foundation, Inc. | Written by Brad Diller. | | This file is part of GNU Smalltalk. | | GNU Smalltalk is free software; you can redistribute it and/or modify it | under the terms of the GNU General Public License as published by the Free | Software Foundation; either version 2, or (at your option) any later version. | | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS | FOR A PARTICULAR PURPOSE. See the GNU General Public License for more | details. | | You should have received a copy of the GNU General Public License along with | GNU Smalltalk; see the file COPYING. If not, write to the Free Software | Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. | ====================================================================== " Primitive subclass: PList [ | selection selectionMsg listMsg dataMsg label | PList class >> new: aString in: view [ | result | result := super new: aString in: view. result label: aString. ^result ] display [ "Update list widget based on list" | contents elements | elements := data perform: self dataMsg. selection := 0. contents := listMsg isNil ifTrue: [elements collect: [:each | each displayString]] ifFalse: [data perform: listMsg]. blox contents: contents elements: elements. "Select item returned by initialSelection message" selectionMsg notNil ifTrue: [self select: (data perform: selectionMsg)] ] dataMsg [ ^dataMsg isNil ifTrue: [listMsg] ifFalse: [dataMsg] ] label: aString [ label := aString ] changedSelection: stateChangeKey [ "Install message handler for stateChangeKey to select the item based on the initial selection" self stateChange: stateChangeKey updateWith: [self select: (data perform: selectionMsg)] ] dataMsg: dataSelector [ "Return array of list items" dataMsg := dataSelector ] handleUserChange: changeSelector [ super handleUserChange: changeSelector. blox callback: self message: #selection:at: ] selectionMsg: selectionSelector [ "Save data object selector which will retrieve initial list selection in the variable, selectionMsg" selectionMsg := selectionSelector ] initialize [ selection := 0. blox := BList new: parentView blox. self blox label: label ] listMsg: listSelector [ "Return array of list labels" listMsg := listSelector ] stateChange: stateChangeKey [ "Install message handler to redraw list in response to an update: message" self stateChange: stateChangeKey updateWith: [self display] ] selection: aPList at: itemPosition [ "Change list selection based on new selection" | value | selection = itemPosition ifTrue: [^itemPosition]. "If this is a new selection, ask the data object whether the view can update itself. There may be text which has been modified in the text view associated with the current list selection" self canChangeState ifFalse: [blox highlight: selection. ^selection]. selection := itemPosition. stateChangeMsg isNil ifFalse: [value := (data perform: self dataMsg) at: itemPosition ifAbsent: [nil]. data perform: stateChangeMsg with: selection -> value]. ^itemPosition ] select: item [ "Select item named, aSymbol, in list" | newSelection | item isNil ifTrue: [^self]. newSelection := item isInteger ifTrue: [item] ifFalse: [(data perform: self dataMsg) indexOf: item]. newSelection = 0 ifTrue: [^self]. newSelection = selection ifTrue: [^self]. blox highlight: newSelection. self selection: self at: newSelection ] unselect [ selection := 0. blox unhighlight ] copyAll [ | ws | ws := WriteStream on: String new. blox elements do: [:each | ws nextPutAll: each printString] separatedBy: [ws nextPut: Character nl]. Blox clipboard: ws contents ] copySelection [ Blox clipboard: (blox at: blox index) printString ] ] smalltalk-3.2.5/packages/blox/browser/NamespBrow.st0000644000175000017500000002464712123404352017271 00000000000000"====================================================================== | | Smalltalk GUI namespace browser | | ======================================================================" "====================================================================== | | Copyright 2002, 2003 Free Software Foundation, Inc. | Written by Paolo Bonzini. | | This file is part of GNU Smalltalk. | | GNU Smalltalk is free software; you can redistribute it and/or modify it | under the terms of the GNU General Public License as published by the Free | Software Foundation; either version 2, or (at your option) any later version. | | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS | FOR A PARTICULAR PURPOSE. See the GNU General Public License for more | details. | | You should have received a copy of the GNU General Public License along with | GNU Smalltalk; see the file COPYING. If not, write to the Free Software | Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. | ====================================================================== " ClassHierarchyBrowser subclass: NamespaceBrowser [ | curNamespace byCategory namespacesMap namespaces categories | byCategory [ "If categories are being viewed, return true" ^byCategory ] byCategory: aBoolean [ "Change instance/class representation and record data state changes" byCategory = aBoolean ifTrue: [^self]. curNamespace := nil. byCategory := aBoolean. self updateNamespaceList ] namespaceList [ ^byCategory ifTrue: [categories] ifFalse: [namespaces] ] namespaceSelection: assoc [ | name | name := assoc value. curNamespace := name isNil | byCategory ifTrue: [name] ifFalse: [namespacesMap at: name]. curClass := nil. self updateClassList ] namespaceString [ "Return name of selected class indented by 'n' spaces, where 'n' is the number of class' superclasses" | spaces | curNamespace isNil ifTrue: [^nil]. byCategory ifTrue: [^curNamespace]. spaces := String new: curNamespace allSuperspaces size. spaces atAllPut: Character space. ^spaces , curNamespace name ] readCategories [ categories := Set new. Class allSubclassesDo: [:each | each isMetaclass ifTrue: [categories add: each instanceClass category]]. categories := categories asSortedCollection ] readNamespaces [ | stack top indent namespace subspaces | stack := OrderedCollection new. namespacesMap := Dictionary new: 17. namespaces := OrderedCollection new. subspaces := {Smalltalk} , RootNamespace allInstances. [subspaces isNil ifFalse: [top := stack addLast: (subspaces asSortedCollection: [:a :b | a name <= b name])]. [top isEmpty] whileTrue: [stack removeLast. stack isEmpty ifTrue: [^self]. top := stack last]. namespace := top removeFirst. subspaces := namespace subspaces. indent := String new: stack size - 1 withAll: Character space. namespacesMap at: indent , namespace name put: namespace. namespaces add: indent , namespace name] repeat ] addSubNamespace: listView [ | newNamespace | curNamespace isNil ifTrue: [^listView beep]. curNamespace isNamespace ifFalse: [^listView beep]. newNamespace := (Prompter message: 'Enter a new namespace' in: listView) response. newNamespace = '' ifTrue: [^self]. curNamespace addSubspace: newNamespace asSymbol. self updateNamespaceList ] blueButtonMenuForNamespaces: theView [ "Install popup for namespace list popup" ^(PopupMenu new: theView label: 'Namespace') selectors: #(#('Namespaces' #namespaces: #theView) #('Categories' #categories: #theView) #() #('File out...' #fileOutNamespace: #theView) #('File into namespace' #fileIntoNamespace: #theView) #() #('Add namespace' #addSubNamespace: #theVIew) #('Rename...' #renameNamespace: #theView) #('Update' #updateNamespaceList)) receiver: self argument: theView ] categories: namespaceList [ namespaceList canChangeState ifFalse: [^self]. self byCategory: true ] fileIntoNamespace: listView [ "File in a file to a currently selected namespace" | oldCurrent className fileName stream | curNamespace isNil ifTrue: [^listView beep]. fileName := Prompter openFileName: 'Which file do you want me to read?' default: '*.st' in: listView. fileName isNil ifTrue: [^listView beep]. oldCurrent := Namespace current. Namespace current: curNamespace. FileStream fileIn: fileName. Namespace current: oldCurrent ] fileoutName [ byCategory ifTrue: [^curNamespace]. ^((curNamespace nameIn: Smalltalk) asString) replaceAll: Character space with: $-; yourself ] fileOutNamespace: listView [ "File out a description of the currently selected namespace" | oldCurrent className fileName stream | curNamespace isNil ifTrue: [^listView beep]. fileName := self fileoutDir , self fileoutName , '.st'. fileName := Prompter saveFileName: 'File out namespace' default: fileName in: listView. fileName isNil ifTrue: [^self]. stream := FileStream open: fileName mode: FileStream write. byCategory ifFalse: [curNamespace superspace isNil ifFalse: [stream nextPutAll: (curNamespace superspace nameIn: Smalltalk); nextPutAll: ' addSubspace: #'; nextPutAll: curNamespace name; nextPutAll: '!'; nl; nextPutAll: 'Namespace current: '; nextPutAll: (curNamespace nameIn: Smalltalk); nextPutAll: '!'; nl; nl] ifTrue: [stream nextPutAll: 'Namespace current: (RootNamespace new: #'; nextPutAll: (curNamespace nameIn: Smalltalk); nextPutAll: ')!'; nl; nl]. oldCurrent := Namespace current. Namespace current: curNamespace]. classList do: [:each | (each trimSeparators includes: $() ifFalse: [(shownClasses at: each) fileOutOn: stream]]. byCategory ifFalse: [Namespace current: oldCurrent. stream nextPutAll: 'Namespace current: Smalltalk!'; nl]. stream close. self setFileoutDirFromFile: fileName ] namespaces: namespaceList [ namespaceList canChangeState ifFalse: [^self]. self byCategory: false ] renameNamespace: listView [ "Rename currently selected namespace" | methods oldName newName prompter oldAssoc referrer | curNamespace isNil ifTrue: [^listView beep]. oldName := self namespaceString trimSeparators. "Prompt user for new name" prompter := Prompter message: 'Rename namespace: ' , curNamespace name in: listView. prompter response = '' ifTrue: [^self]. self byCategory ifTrue: [shownClasses do: [:each | each category: prompter response]. self updateNamespaceList. ^self]. oldName := oldName asSymbol. newName := prompter response asSymbol. (newName at: 1) isUppercase ifFalse: [^self error: 'Namespace name must begin with an uppercase letter']. referrer := curNamespace superspace isNil ifTrue: [Smalltalk] ifFalse: [curNamespace superspace]. (referrer includesKey: newName) ifTrue: [^self error: newName , ' already exists']. "Save old Association and remove namespace temporarily" oldAssoc := referrer associationAt: oldName. referrer removeKey: oldName. "Rename the namespace now and re-add it" curNamespace name: newName asSymbol. referrer at: newName asSymbol put: curNamespace. "Notify programmer of all references to renamed namespace" methods := SortedCollection new. CompiledMethod allInstancesDo: [:method | ((method refersTo: oldAssoc) or: [method refersTo: oldAssoc key]) ifTrue: [methods add: method]]. methods isEmpty ifFalse: [ModalDialog new alertMessage: 'Rename all references to namespace ' , oldName , Character nl asSymbol , 'to the new name: ' , newName in: listView. MethodSetBrowser new openOn: methods title: 'References to ' , oldName selection: oldName]. "Update namespace list" self updateNamespaceList ] topClasses [ ^self topMetas collect: [:each | each instanceClass] ] topMetas [ curNamespace isNil ifTrue: [^#()]. ^byCategory ifTrue: [Class allSubclasses select: [:each | each category = curNamespace]] ifFalse: [Class allSubclasses select: [:each | each environment = curNamespace]] ] updateNamespaceList [ "Invoked from class list pane popup. Update class list pane through the change/update mechanism" byCategory ifTrue: [self readCategories] ifFalse: [self readNamespaces]. self changeState: #namespaceList. self updateClassList ] createNamespaceListIn: upper [ | list | upper addChildView: ((list := PList new: 'Namespaces' in: upper) initialize; data: self; stateChange: #namespaceList; changedSelection: #newNamespaceSelection; handleUserChange: #namespaceSelection:; listMsg: #namespaceList; selectionMsg: #namespaceString; menuInit: (self blueButtonMenuForNamespaces: list); yourself). "Register three types of messages" self layoutUpperPaneElement: list blox num: -1 ] createUpperPanesIn: upper [ self createNamespaceListIn: upper. super createUpperPanesIn: upper ] createTopView [ ^BrowserShell new: 'Namespace Browser' ] initialize [ self updateNamespaceList ] layoutUpperPaneElement: blox num: n [ blox x: 150 * n + 150 y: 0 width: 150 height: 200 ] open [ byCategory := false. super open ] currentNamespace [ ^byCategory ifTrue: [Namespace current] ifFalse: [curNamespace] ] ] smalltalk-3.2.5/packages/blox/tk/0000755000175000017500000000000012130456010013636 500000000000000smalltalk-3.2.5/packages/blox/tk/Makefile.frag0000644000175000017500000000056612123404352016147 00000000000000BloxTK_FILES = \ packages/blox/tk/Blox.st packages/blox/tk/BloxBasic.st packages/blox/tk/BloxWidgets.st packages/blox/tk/BloxText.st packages/blox/tk/BloxCanvas.st packages/blox/tk/BloxExtend.st packages/blox/tk/colors.txt packages/blox/tk/ChangeLog $(BloxTK_FILES): $(srcdir)/packages/blox/tk/stamp-classes: $(BloxTK_FILES) touch $(srcdir)/packages/blox/tk/stamp-classes smalltalk-3.2.5/packages/blox/tk/BloxExtend.st0000644000175000017500000011253612123404352016216 00000000000000"====================================================================== | | Smalltalk Tk-based GUI building blocks, extended widgets. | This is 100% Smalltalk! | | ======================================================================" "====================================================================== | | Copyright 1999, 2000, 2001, 2002 Free Software Foundation, Inc. | Free Software Foundation, Inc. | Written by Paolo Bonzini. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LESSER. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" BExtended subclass: BProgress [ | value filled label1 label2 | backgroundColor [ "Answer the background color of the widget. This is used for the background of the non-filled part, as well as for the foreground of the filled part." ^label1 backgroundColor ] backgroundColor: aColor [ "Set the background color of the widget. This is used for the background of the non-filled part, as well as for the foreground of the filled part." label1 backgroundColor: aColor. label2 foregroundColor: aColor ] filledColor [ "Answer the background color of the widget's filled part." ^label2 backgroundColor ] filledColor: aColor [ "Set the background color of the widget's filled part." label2 backgroundColor: aColor ] foregroundColor [ "Set the foreground color of the widget. This is used for the non-filled part, while the background color also works as the foreground of the filled part." ^label1 foregroundColor ] foregroundColor: aColor [ "Set the foreground color of the widget. This is used for the non-filled part, while the background color also works as the foreground of the filled part." label1 foregroundColor: aColor ] value [ "Answer the filled percentage of the receiver (0..1)" ^value ] value: newValue [ "Set the filled percentage of the receiver and update the appearance. newValue must be between 0 and 1." value := newValue. filled width: self value * self primitive widthAbsolute. label1 label: (value * 100) rounded printString , '%'. label2 label: (value * 100) rounded printString , '%' ] create [ "Private - Create the widget" | hgt | super create. self primitive onResizeSend: #resize: to: self. label1 := BLabel new: self primitive. filled := BForm new: self primitive. label2 := BLabel new: filled. hgt := self primitive height. label1 alignment: #center; width: self primitive width height: hgt. label2 alignment: #center; width: 0 height: hgt. self backgroundColor: 'white'; foregroundColor: 'black'; filledColor: 'blue'; resize: nil; value: 0 ] newPrimitive [ "Private - Create the BForm in which the receiver is drawn" ^BForm new: self parent ] resize: newSize [ label2 widthOffset: self primitive widthAbsolute ] ] BExtended subclass: BButtonLike [ | callback down | callback [ "Answer a DirectedMessage that is sent when the receiver is clicked, or nil if none has been set up." ^callback ] callback: aReceiver message: aSymbol [ "Set up so that aReceiver is sent the aSymbol message (the name of a zero- or one-argument selector) when the receiver is clicked. If the method accepts an argument, the receiver is passed." | arguments selector numArgs | selector := aSymbol asSymbol. numArgs := selector numArgs. arguments := #(). numArgs = 1 ifTrue: [arguments := Array with: self]. callback := DirectedMessage selector: selector arguments: arguments receiver: aReceiver ] pressed [ "This is the default callback for the widget; it does nothing if you don't override it. Of course if a subclass overriddes this you (user of the class) might desire to call this method from your own callback." ] invokeCallback [ "Generate a synthetic callback" self callback isNil ifFalse: [self callback send] ] down: point [ "Private - Make the widget go down when the left button is pressed inside it." down := true. self enter ] enter [ "Private - Make the widget go down when the mouse enters with the left button pressed." down ifTrue: [self primitive effect: #sunken] ] leave [ "Private - Make the widget go up when the mouse leaves" down ifTrue: [self primitive effect: #raised] ] up: point [ "Private - Make the widget go up when the left button is released after being pressed inside it, and trigger the callback if the button was released inside the widget." | inside | inside := self primitive effect == #sunken. inside ifTrue: [self leave]. down := false. inside ifTrue: [self invokeCallback] ] create [ "Ask myself to create the primitive widget and set up its event handlers." super create. (self primitive) borderWidth: 2; effect: #raised; onMouseEnterEventSend: #enter to: self; onMouseLeaveEventSend: #leave to: self; onMouseDownEvent: 1 send: #down: to: self; onMouseUpEvent: 1 send: #up: to: self. down := false. callback := DirectedMessage selector: #pressed arguments: #() receiver: self ] ] BButtonLike subclass: BColorButton [ color [ "Set the color that the receiver is painted in." ^self primitive backgroundColor ] color: aString [ "Set the color that the receiver is painted in." self primitive backgroundColor: aString ] pressed [ "This is the default callback; it brings up a `choose-a-color' window and, if `Ok' is pressed in the window, sets the receiver to be painted in the chosen color." | newColor | newColor := BDialog chooseColor: self window label: 'Choose a color' default: self color. newColor isNil ifFalse: [self color: newColor] ] newPrimitive [ "Private - A BColorButton is implemented through a BLabel. (!)" "Make it big enough if no width is specified." ^BLabel new: self parent label: ' ' ] ] BEventSet subclass: BBalloon [ | text | BalloonDelayTime := nil. Popup := nil. Owner := nil. MyProcess := nil. BBalloon class >> balloonDelayTime [ "Answer the time after which the balloon is shown (default is half a second)." BalloonDelayTime isNil ifTrue: [BalloonDelayTime := 500]. ^BalloonDelayTime ] BBalloon class >> balloonDelayTime: milliseconds [ "Set the time after which the balloon is shown." BalloonDelayTime := milliseconds ] BBalloon class >> shown [ "Answer whether a balloon is displayed" ^Popup notNil ] shown [ "Answer whether the receiver's balloon is displayed" ^self class shown and: [Owner == self] ] text [ "Answer the text displayed in the balloon" ^text ] text: aString [ "Set the text displayed in the balloon to aString" text := aString ] initialize: aBWidget [ "Initialize the event sets for the receiver" super initialize: aBWidget. self text: ''. self onMouseEnterEventSend: #queue to: self; onMouseLeaveEventSend: #unqueue to: self; onMouseDownEventSend: #unqueue:button: to: self ] popup [ "Private - Create the popup window showing the balloon." Popup := BLabel popup: [:widget | widget label: self text; backgroundColor: '#FFFFAA'; x: self widget yRoot + (self widget widthAbsolute // 2) y: self widget yRoot + self widget heightAbsolute + 4]. "Set the owner *now*. Otherwise, the mouse-leave event generated by mapping the new popup window will destroy the popup window itself (see #unqueue)." Owner := self ] queue [ "Private - Queue a balloon to be shown in BalloonDelayTime milliseconds" self shown ifTrue: [^self]. MyProcess isNil ifTrue: [MyProcess := [(Delay forMilliseconds: self class balloonDelayTime) wait. MyProcess := nil. self popup] fork] ] unqueue [ "Private - Prevent the balloon from being displayed if we were waiting for it to appear, or delete it if it was already there." MyProcess isNil ifFalse: [MyProcess terminate. MyProcess := nil]. self shown ifTrue: [Popup window destroy. Owner := Popup := nil] ] unqueue: point button: button [ "Private - Same as #unqueue: but the event handler for mouse-down events needs two parameters." self unqueue ] ] BExtended subclass: BDropDown [ | list button widget callback | backgroundColor [ "Answer the value of the backgroundColor for the widget, which in this class is only set for the list widget (that is, the pop-up widget). Subclasses should override this method so that the color is set properly for the text widget as well. Specifies the normal background color to use when displaying the widget." ^list backgroundColor ] backgroundColor: aColor [ "Set the value of the backgroundColor for the widget, which in this class is only set for the list widget (that is, the pop-up widget). Subclasses should override this method so that the color is set properly for the text widget as well. Specifies the normal background color to use when displaying the widget." list backgroundColor: aColor ] droppedRows [ "Answer the number of items that are visible at any time in the listbox." ^(list height - 8) / self itemHeight ] droppedRows: anInteger [ "Set the number of items that are visible at any time in the listbox." list height: anInteger * self itemHeight + 8 ] font [ "Answer the value of the font option for the widget, which in this class is only set for the list widget (that is, the pop-up widget). Subclasses should override this method so that the color is set properly for the text widget as well. Specifies the font to use when drawing text inside the widget. The font can be given as either an X font name or a Blox font description string. X font names are given as many fields, each led by a minus, and each of which can be replaced by an * to indicate a default value is ok: foundry, family, weight, slant, setwidth, addstyle, pixel size, point size (the same as pixel size for historical reasons), horizontal resolution, vertical resolution, spacing, width, charset and character encoding. Blox font description strings have three fields, which must be separated by a space and of which only the first is mandatory: the font family, the font size in points (or in pixels if a negative value is supplied), and a number of styles separated by a space (valid styles are normal, bold, italic, underline and overstrike). Examples of valid fonts are ``Helvetica 10 Bold'', ``Times -14'', ``Futura Bold Underline''. You must enclose the font family in braces if it is made of two or more words." ^list font ] font: value [ "Set the value of the font option for the widget, which in this class is only set for the list widget (that is, the pop-up widget). Subclasses should override this method so that the color is set properly for the text widget as well. Specifies the font to use when drawing text inside the widget. The font can be given as either an X font name or a Blox font description string. X font names are given as many fields, each led by a minus, and each of which can be replaced by an * to indicate a default value is ok: foundry, family, weight, slant, setwidth, addstyle, pixel size, point size (the same as pixel size for historical reasons), horizontal resolution, vertical resolution, spacing, width, charset and character encoding. Blox font description strings have three fields, which must be separated by a space and of which only the first is mandatory: the font family, the font size in points (or in pixels if a negative value is supplied), and a number of styles separated by a space (valid styles are normal, bold, italic, underline and overstrike). Examples of valid fonts are ``Helvetica 10 Bold'', ``Times -14'', ``Futura Bold Underline''. You must enclose the font family in braces if it is made of two or more words." list font: value ] foregroundColor [ "Answer the value of the foregroundColor for the widget, which in this class is only set for the list widget (that is, the pop-up widget). Subclasses should override this method so that the color is set properly for the text widget as well. Specifies the normal foreground color to use when displaying the widget." ^list foregroundColor ] foregroundColor: aColor [ "Set the value of the foregroundColor for the widget, which in this class is only set for the list widget (that is, the pop-up widget). Subclasses should override this method so that the color is set properly for the text widget as well. Specifies the normal foreground color to use when displaying the widget." list foregroundColor: aColor ] highlightBackground [ "Answer the value of the highlightBackground option for the widget. Specifies the background color to use when displaying selected items in the list widget." ^list highlightBackground ] highlightBackground: aColor [ "Set the value of the highlightBackground option for the widget. Specifies the background color to use when displaying selected items in the list widget." list highlightBackground: aColor ] highlightForeground [ "Answer the value of the highlightForeground option for the widget. Specifies the foreground color to use when displaying selected items in the list widget." ^list highlightForeground ] highlightForeground: aColor [ "Set the value of the highlightForeground option for the widget. Specifies the foreground color to use when displaying selected items in the list widget." list highlightForeground: aColor ] callback [ "Answer a DirectedMessage that is sent when the receiver is clicked, or nil if none has been set up." ^callback ] callback: aReceiver message: aSymbol [ "Set up so that aReceiver is sent the aSymbol message (the name of a zero- or one-argument selector) when the receiver is clicked. If the method accepts an argument, the receiver is passed." | arguments selector numArgs | selector := aSymbol asSymbol. numArgs := selector numArgs. arguments := #(). numArgs = 1 ifTrue: [arguments := Array with: self]. callback := DirectedMessage selector: selector arguments: arguments receiver: aReceiver ] invokeCallback [ "Generate a synthetic callback" self callback isNil ifFalse: [self callback send] ] createList [ "Create the popup widget to be used for the `drop-down list'. It is a BList by default, but you can use any other widget, overriding the `list box accessing' methods if necessary." ^BList new ] createTextWidget [ "Create the widget that will hold the string chosen from the list box and answer it. The widget must be a child of `self primitive'." self subclassResponsibility ] itemHeight [ "Answer the height of an item in the drop-down list. The default implementation assumes that the receiver understands #font, but you can modify it if you want." ^1 + (self fontHeight: 'M') ] listCallback [ "Called when an item of the listbox is highlighted. Do nothing by default" ] listSelectAt: aPoint [ "Select the item lying at the given position in the list box. The default implementation assumes that list is a BList, but you can modify it if you want." | newIndex | (list drawingArea containsPoint: aPoint) ifFalse: [^self]. newIndex := list indexAt: aPoint. newIndex = list index ifTrue: [^self]. self index: newIndex ] listText [ "Answer the text currently chosen in the list box. The default implementation assumes that list is a BList, but you can modify it if you want." ^list labelAt: list index ] text [ "Answer the text that the user has picked from the widget and/or typed in the control (the exact way the text is entered will be established by subclasses, since this is an abstract method)." self subclassResponsibility ] text: aString [ "Set the text widget to aString" self subclassResponsibility ] create [ super create. list := self createList. (self primitive) defaultHeight: (self itemHeight + 6 max: 20); effect: #sunken; borderWidth: 2; backgroundColor: 'white'. list borderWidth: 0. (widget := self createTextWidget) inset: 1; borderWidth: 0; backgroundColor: 'white'; tabStop: true; stretch: true. (button := BImage new: self primitive data: BImage downArrow) effect: #raised; borderWidth: 2. self droppedRows: 8. self setEvents ] newPrimitive [ ^(BContainer new: self parent) setVerticalLayout: false; yourself ] setEvents [ self primitive onDestroySend: #destroy to: list. button onMouseDownEvent: 1 send: #value: to: [:pnt | self toggle]. list onKeyEvent: 'Tab' send: #value to: [self unmapList. widget activateNext]. list onKeyEvent: 'Shift-Tab' send: #value to: [self unmapList. widget activatePrevious]. list onKeyEvent: 'Return' send: #unmapList to: self. list onKeyEvent: 'Escape' send: #unmapList to: self. list onMouseUpEvent: 1 send: #value: to: [:pnt | self unmapList]. list onMouseMoveEventSend: #listSelectAt: to: self. list onFocusLeaveEventSend: #unmapList to: self. list callback: self message: #listCallback ] setInitialSize [ self primitive x: 0 y: 0 ] add: anObject afterIndex: index [ "Add an element with the given value after another element whose index is contained in the index parameter. The label displayed in the widget is anObject's displayString. Answer anObject." ^list add: anObject afterIndex: index ] add: aString element: anObject afterIndex: index [ "Add an element with the aString label after another element whose index is contained in the index parameter. This method allows the client to decide autonomously the label that the widget will display. If anObject is nil, then string is used as the element as well. If aString is nil, then the element's displayString is used as the label. Answer anObject or, if it is nil, aString." ^list add: aString element: anObject afterIndex: index ] addLast: anObject [ "Add an element with the given value at the end of the listbox. The label displayed in the widget is anObject's displayString. Answer anObject." ^list addLast: anObject ] addLast: aString element: anObject [ "Add an element with the given value at the end of the listbox. This method allows the client to decide autonomously the label that the widget will display. If anObject is nil, then string is used as the element as well. If aString is nil, then the element's displayString is used as the label. Answer anObject or, if it is nil, aString." ^list addLast: aString element: anObject ] associationAt: anIndex [ "Answer an association whose key is the item at the given position in the listbox and whose value is the label used to display that item." ^list associationAt: anIndex ] at: anIndex [ "Answer the element displayed at the given position in the list box." ^list at: anIndex ] contents: stringCollection [ "Set the elements displayed in the listbox, and set the labels to be their displayStrings." list contents: stringCollection ] contents: stringCollection elements: elementList [ "Set the elements displayed in the listbox to be those in elementList, and set the labels to be the corresponding elements in stringCollection. The two collections must have the same size." list contents: stringCollection elements: elementList ] do: aBlock [ "Iterate over each element of the listbox and pass it to aBlock." list do: aBlock ] elements: elementList [ "Set the elements displayed in the listbox, and set the labels to be their displayStrings." list elements: elementList ] index: newIndex [ "Highlight the item at the given position in the listbox, and transfer the text in the list box to the text widget." list highlight: newIndex. self text: self listText. self isDropdownVisible ifFalse: [self invokeCallback] ] labelAt: anIndex [ "Answer the label displayed at the given position in the list box." ^list labelAt: anIndex ] labelsDo: aBlock [ "Iterate over the labels in the list widget and pass each of them to aBlock." list labelsDo: aBlock ] numberOfStrings [ "Answer the number of items in the list box" ^list numberOfStrings ] removeAtIndex: index [ "Remove the item at the given index in the list box, answering the object associated to the element (i.e. the value that #at: would have returned for the given index)" ^list removeAtIndex: index ] size [ "Answer the number of items in the list box" ^list size ] dropdown [ "Force the pop-up list widget to be visible." "Always reset the geometry -- it is harmless and *may* actually get better appearance in some weird case." list window boundingBox: self dropRectangle. self isDropdownVisible ifTrue: [^self]. list window map ] dropRectangle [ "Answer the rectangle in which the list widget will pop-up. If possible, this is situated below the drop-down widget's bottom side, but if the screen space there is not enough it could be above the drop-down widget's above side. If there is no screen space above as well, we pick the side where we can offer the greatest number of lines in the pop-up widget." | screen rectangle spaceBelow | screen := Rectangle origin: Blox screenOrigin extent: Blox screenSize. rectangle := Rectangle origin: self xRoot @ (self yRoot + self heightAbsolute) extent: self widthAbsolute @ list height. spaceBelow := screen bottom - rectangle top. rectangle bottom > screen bottom ifFalse: [^rectangle]. "Fine. Pop it up above the entry widget instead of below." rectangle moveTo: self xRoot @ self yRoot - rectangle extent. rectangle top < screen top ifFalse: [^rectangle]. "How annoying, it doesn't fit in the screen. Now we'll try to be real clever and either pop it up or down, depending on which way gives us the biggest list." spaceBelow < (rectangle bottom - screen top) ifTrue: [rectangle top: 0] ifFalse: [rectangle moveTo: self xRoot @ (self yRoot + self heightAbsolute); bottom: screen bottom]. ^rectangle ] isDropdownVisible [ "Answer whether the pop-up widget is visible" ^list window isMapped ] unmapList [ "Unmap the pop-up widget from the screen, transfer its selected item to the always visible text widget, and generate a callback." list window unmap. self text: self listText. self invokeCallback ] toggle [ "Toggle the visibility of the pop-up widget." widget activate. self isDropdownVisible ifTrue: [self unmapList] ifFalse: [self dropdown] ] ] BDropDown subclass: BDropDownList [ | callback | backgroundColor: aColor [ "Set the value of the backgroundColor for the widget, which in this class is set for the list widget and, when the focus is outside the control, for the text widget as well. Specifies the normal background color to use when displaying the widget." super backgroundColor: aColor. self highlight ] font: aString [ "Set the value of the font option for the widget. Specifies the font to use when drawing text inside the widget. The font can be given as either an X font name or a Blox font description string. X font names are given as many fields, each led by a minus, and each of which can be replaced by an * to indicate a default value is ok: foundry, family, weight, slant, setwidth, addstyle, pixel size, point size (the same as pixel size for historical reasons), horizontal resolution, vertical resolution, spacing, width, charset and character encoding. Blox font description strings have three fields, which must be separated by a space and of which only the first is mandatory: the font family, the font size in points (or in pixels if a negative value is supplied), and a number of styles separated by a space (valid styles are normal, bold, italic, underline and overstrike). Examples of valid fonts are ``Helvetica 10 Bold'', ``Times -14'', ``Futura Bold Underline''. You must enclose the font family in braces if it is made of two or more words." widget font: aString. super font: aString ] foregroundColor: aColor [ "Set the value of the foregroundColor for the widget, which in this class is set for the list widget and, when the focus is outside the control, for the text widget as well. Specifies the normal foreground color to use when displaying the widget." super foregroundColor: aColor. self highlight ] highlightBackground: aColor [ "Answer the value of the highlightBackground option for the widget. Specifies the background color to use when displaying selected items in the list widget and, when the focus is inside the control, for the text widget as well." super highlightBackground: aColor. self highlight ] highlightForeground: aColor [ "Answer the value of the highlightForeground option for the widget. Specifies the foreground color to use when displaying selected items in the list widget and, when the focus is inside the control, for the text widget as well." super highlightForeground: aColor. self highlight ] text [ "Answer the text that the user has picked from the widget and/or typed in the control (the exact way the text is entered will be established by subclasses, since this is an abstract method)." ^widget label ] callback: aReceiver message: aSymbol [ "Set up so that aReceiver is sent the aSymbol message (the name of a selector with at most two arguemtnts) when the active item in the receiver changegs. If the method accepts two arguments, the receiver is passed as the first parameter. If the method accepts one or two arguments, the selected index is passed as the last parameter." | arguments selector numArgs | selector := aSymbol asSymbol. numArgs := selector numArgs. arguments := #(). numArgs = 1 ifTrue: [arguments := {nil}]. numArgs = 2 ifTrue: [arguments := {self. nil}]. callback := DirectedMessage selector: selector arguments: arguments receiver: aReceiver ] invokeCallback [ "Generate a synthetic callback." self callback isNil ifTrue: [^self]. self callback arguments isEmpty ifFalse: [self callback arguments at: self callback arguments size put: self index]. self callback send ] index [ "Answer the value of the index option for the widget. Since it is not possible to modify an item once it has been picked from the list widget, this is always defined for BDropDownList widgets." ^list index ] highlight [ | bg fg | widget isActive ifTrue: [bg := list highlightBackground. fg := list highlightForeground] ifFalse: [bg := list backgroundColor. fg := list foregroundColor]. widget backgroundColor: bg; foregroundColor: fg ] createTextWidget [ ^BLabel new: self primitive ] listCallback [ self text: self listText ] text: aString [ widget label: aString ] setEvents [ super setEvents. "If we did not test whether the list box is focus, we would toggle twice (once in the widget's mouseDownEvent, once in the list's focusLeaveEvent)" widget onMouseDownEvent: 1 send: #value: to: [:pnt | "list isActive ifFalse: [" self toggle "]"]. widget onFocusEnterEventSend: #highlight to: self. widget onFocusLeaveEventSend: #highlight to: self. widget onKeyEvent: 'Down' send: #dropdown to: self ] ] BDropDown subclass: BDropDownEdit [ backgroundColor: aColor [ "Set the value of the backgroundColor option for the widget. Specifies the normal background color to use when displaying the widget." super backgroundColor: aColor. widget backgroundColor: aColor ] font: aString [ "Set the value of the font option for the widget. Specifies the font to use when drawing text inside the widget. The font can be given as either an X font name or a Blox font description string. X font names are given as many fields, each led by a minus, and each of which can be replaced by an * to indicate a default value is ok: foundry, family, weight, slant, setwidth, addstyle, pixel size, point size (the same as pixel size for historical reasons), horizontal resolution, vertical resolution, spacing, width, charset and character encoding. Blox font description strings have three fields, which must be separated by a space and of which only the first is mandatory: the font family, the font size in points (or in pixels if a negative value is supplied), and a number of styles separated by a space (valid styles are normal, bold, italic, underline and overstrike). Examples of valid fonts are ``Helvetica 10 Bold'', ``Times -14'', ``Futura Bold Underline''. You must enclose the font family in braces if it is made of two or more words." widget font: aString. super font: aString ] foregroundColor: aColor [ "Set the value of the foregroundColor option for the widget. Specifies the normal foreground color to use when displaying the widget." super foregroundColor: aColor. widget foregroundColor: aColor ] highlightBackground: aColor [ "Set the value of the highlightBackground option for the widget. Specifies the background color to use when displaying selected items in the list widget and the selection in the text widget." super highlightBackground: aColor. widget selectBackground: aColor ] highlightForeground: aColor [ "Set the value of the highlightBackground option for the widget. Specifies the background color to use when displaying selected items in the list widget and the selection in the text widget." super highlightForeground: aColor. widget selectForeground: aColor ] text [ "Answer the text shown in the widget" ^widget contents ] editCallback [ self isDropdownVisible ifFalse: [self invokeCallback] ] createTextWidget [ ^(BEdit new: self primitive) callback: self message: #editCallback ] insertAtEnd: aString [ "Clear the selection and append aString at the end of the text widget." widget insertAtEnd: aString ] replaceSelection: aString [ "Insert aString in the text widget at the current insertion point, replacing the currently selected text (if any), and leaving the text selected." widget replaceSelection: aString ] selectAll [ "Select the whole contents of the text widget" widget selectAll ] selectFrom: first to: last [ "Sets the selection of the text widget to include the characters starting with the one indexed by first (the very first character in the widget having index 1) and ending with the one just before last. If last refers to the same character as first or an earlier one, then the text widget's selection is cleared." widget selectFrom: first to: last ] selection [ "Answer an empty string if the text widget has no selection, else answer the currently selected text" ^widget selection ] selectionRange [ "Answer nil if the text widget has no selection, else answer an Interval object whose first item is the index of the first character in the selection, and whose last item is the index of the character just after the last one in the selection." ^widget selectionRange ] text: aString [ "Set the contents of the text widget and select them." widget contents: aString; selectAll ] ] "-------------------------- BProgress class -----------------------------" "-------------------------- BButtonLike class -----------------------------" "-------------------------- BColorButton class -----------------------------" "-------------------------- BBalloon class -----------------------------" "-------------------------- BDropDown class -----------------------------" "-------------------------- BDropDownList class -----------------------------" "-------------------------- BDropDownEdit class -----------------------------" smalltalk-3.2.5/packages/blox/tk/BloxBasic.st0000644000175000017500000027702012123404352016010 00000000000000"====================================================================== | | Smalltalk Tk-based GUI building blocks (abstract classes). | | ======================================================================" "====================================================================== | | Copyright 1999,2000,2001,2002,2005,2006 Free Software Foundation, Inc. | Written by Paolo Bonzini. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LESSER. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" Object subclass: Gui [ | blox | blox [ "Return instance of blox subclass which implements window" ^blox ] blox: aBlox [ "Set instance of blox subclass which implements window" blox := aBlox ] ] Object subclass: BEventTarget [ | eventReceivers | addEventSet: aBEventSetSublass [ "Add to the receiver the event handlers implemented by an instance of aBEventSetSubclass. Answer the new instance of aBEventSetSublass." ^self registerEventReceiver: (aBEventSetSublass new: self) ] onAsciiKeyEventSend: aSelector to: anObject [ "When an ASCII key is pressed and the receiver has the focus, send the 1-argument message identified by aSelector to anObject, passing to it a Character." aSelector numArgs = 1 ifFalse: [^self invalidArgsError: '1']. self registerEventReceiver: anObject. ^self bind: '' to: #sendKeyEvent:oop:selector: of: self parameters: '*%A* ' , anObject asOop printString , ' ' , aSelector asTkString ] onDestroySend: aSelector to: anObject [ "When the receiver is destroyed, send the unary message identified by aSelector to anObject." aSelector numArgs = 0 ifFalse: [^self invalidArgsError: '0']. ^self bind: '' to: aSelector of: anObject parameters: '' ] onFocusEnterEventSend: aSelector to: anObject [ "When the focus enters the receiver, send the unary message identified by aSelector to anObject." aSelector numArgs = 0 ifFalse: [^self invalidArgsError: '0']. ^self bind: '' to: aSelector of: anObject parameters: '' ] onFocusLeaveEventSend: aSelector to: anObject [ "When the focus leaves the receiver, send the unary message identified by aSelector to anObject." aSelector numArgs = 0 ifFalse: [^self invalidArgsError: '0']. ^self bind: '' to: aSelector of: anObject parameters: '' ] onKeyEvent: key send: aSelector to: anObject [ "When the given key is pressed and the receiver has the focus, send the unary message identified by aSelector to anObject. Examples for key are: 'Ctrl-1', 'Alt-X', 'Meta-plus', 'enter'. The last two cases include example of special key identifiers; these include: 'backslash', 'exclam', 'quotedbl', 'dollar', 'asterisk', 'less', 'greater', 'asciicircum' (caret), 'question', 'equal', 'parenleft', 'parenright', 'colon', 'semicolon', 'bar' (pipe sign), 'underscore', 'percent', 'minus', 'plus', 'BackSpace', 'Delete', 'Insert', 'Return', 'End', 'Home', 'Prior' (Pgup), 'Next' (Pgdn), 'F1'..'F24', 'Caps_Lock', 'Num_Lock', 'Tab', 'Left', 'Right', 'Up', 'Down'. There are in addition four special identifiers which map to platform-specific keys: '', '', '', '' (all with the angular brackets!)." aSelector numArgs = 0 ifFalse: [^self invalidArgsError: '0']. (self getKeyPressEventNames: key) do: [:each | self bind: each to: aSelector of: anObject parameters: ''] ] onKeyEventSend: aSelector to: anObject [ "When a key is pressed and the receiver has the focus, send the 1-argument message identified by aSelector to anObject. The pressed key will be passed as a String parameter; some of the keys will send special key identifiers such as those explained in the documentation for #onKeyEvent:send:to: Look at the #eventTest test program in the BloxTestSuite to find out the parameters passed to such an event procedure" aSelector numArgs = 1 ifFalse: [^self invalidArgsError: '1']. ^self bind: '' to: aSelector of: anObject parameters: '%K' ] onKeyUpEventSend: aSelector to: anObject [ "When a key has been released and the receiver has the focus, send the 1-argument message identified by aSelector to anObject. The released key will be passed as a String parameter; some of the keys will send special key identifiers such as those explained in the documentation for #onKeyEvent:send:to: Look at the #eventTest test program in the BloxTestSuite to find out the parameters passed to such an event procedure" aSelector numArgs = 1 ifFalse: [^self invalidArgsError: '1']. ^self bind: '' to: aSelector of: anObject parameters: '%K' ] onMouseDoubleEvent: button send: aSelector to: anObject [ "When the given button is double-clicked on the mouse, send the 1-argument message identified by aSelector to anObject. The mouse position will be passed as a Point." aSelector numArgs = 1 ifFalse: [^self invalidArgsError: '1']. self registerEventReceiver: anObject. ^self bind: '' to: #sendPointEvent:y:oop:selector: of: self parameters: '%x %y ' , anObject asOop printString , ' ' , aSelector asTkString ] onMouseDoubleEventSend: aSelector to: anObject [ "When a button is double-clicked on the mouse, send the 2-argument message identified by aSelector to anObject. The mouse position will be passed as a Point in the first parameter, the button number will be passed as an Integer in the second parameter." aSelector numArgs = 2 ifFalse: [^self invalidArgsError: '2']. self registerEventReceiver: anObject. ^self bind: '' to: #sendPointEvent:y:button:oop:selector: of: self parameters: '%x %y %b ' , anObject asOop printString , ' ' , aSelector asTkString ] onMouseDownEvent: button send: aSelector to: anObject [ "When the given button is pressed on the mouse, send the 1-argument message identified by aSelector to anObject. The mouse position will be passed as a Point." aSelector numArgs = 1 ifFalse: [^self invalidArgsError: '1']. self registerEventReceiver: anObject. ^self bind: '' to: #sendPointEvent:y:oop:selector: of: self parameters: '%x %y ' , anObject asOop printString , ' ' , aSelector asTkString ] onMouseDownEventSend: aSelector to: anObject [ "When a button is pressed on the mouse, send the 2-argument message identified by aSelector to anObject. The mouse position will be passed as a Point in the first parameter, the button number will be passed as an Integer in the second parameter." aSelector numArgs = 2 ifFalse: [^self invalidArgsError: '2']. self registerEventReceiver: anObject. ^self bind: '' to: #sendPointEvent:y:button:oop:selector: of: self parameters: '%x %y %b ' , anObject asOop printString , ' ' , aSelector asTkString ] onMouseEnterEventSend: aSelector to: anObject [ "When the mouse enters the widget, send the unary message identified by aSelector to anObject." aSelector numArgs = 0 ifFalse: [^self invalidArgsError: '0']. ^self bind: '' to: aSelector of: anObject parameters: '' ] onMouseLeaveEventSend: aSelector to: anObject [ "When the mouse leaves the widget, send the unary message identified by aSelector to anObject." aSelector numArgs = 0 ifFalse: [^self invalidArgsError: '0']. ^self bind: '' to: aSelector of: anObject parameters: '' ] onMouseMoveEvent: button send: aSelector to: anObject [ "When the mouse is moved while the given button is pressed on the mouse, send the 1-argument message identified by aSelector to anObject. The mouse position will be passed as a Point." aSelector numArgs = 1 ifFalse: [^self invalidArgsError: '1']. self registerEventReceiver: anObject. ^self bind: '' to: #sendPointEvent:y:oop:selector: of: self parameters: '%x %y ' , anObject asOop printString , ' ' , aSelector asTkString ] onMouseMoveEventSend: aSelector to: anObject [ "When the mouse is moved, send the 1-argument message identified by aSelector to anObject. The mouse position will be passed as a Point." aSelector numArgs = 1 ifFalse: [^self invalidArgsError: '1']. self registerEventReceiver: anObject. ^self bind: '' to: #sendPointEvent:y:oop:selector: of: self parameters: '%x %y ' , anObject asOop printString , ' ' , aSelector asTkString ] onMouseTripleEvent: button send: aSelector to: anObject [ "When the given button is triple-clicked on the mouse, send the 1-argument message identified by aSelector to anObject. The mouse position will be passed as a Point." aSelector numArgs = 1 ifFalse: [^self invalidArgsError: '1']. self registerEventReceiver: anObject. ^self bind: '' to: #sendPointEvent:y:oop:selector: of: self parameters: '%x %y ' , anObject asOop printString , ' ' , aSelector asTkString ] onMouseTripleEventSend: aSelector to: anObject [ "When a button is triple-clicked on the mouse, send the 2-argument message identified by aSelector to anObject. The mouse position will be passed as a Point in the first parameter, the button number will be passed as an Integer in the second parameter." aSelector numArgs = 2 ifFalse: [^self invalidArgsError: '2']. self registerEventReceiver: anObject. ^self bind: '' to: #sendPointEvent:y:button:oop:selector: of: self parameters: '%x %y %b ' , anObject asOop printString , ' ' , aSelector asTkString ] onMouseUpEvent: button send: aSelector to: anObject [ "When the given button is released on the mouse, send the 1-argument message identified by aSelector to anObject. The mouse position will be passed as a Point." aSelector numArgs = 1 ifFalse: [^self invalidArgsError: '1']. self registerEventReceiver: anObject. ^self bind: '' to: #sendPointEvent:y:oop:selector: of: self parameters: '%x %y ' , anObject asOop printString , ' ' , aSelector asTkString ] onMouseUpEventSend: aSelector to: anObject [ "When a button is released on the mouse, send the 2-argument message identified by aSelector to anObject. The mouse position will be passed as a Point in the first parameter, the button number will be passed as an Integer in the second parameter." aSelector numArgs = 2 ifFalse: [^self invalidArgsError: '2']. self registerEventReceiver: anObject. ^self bind: '' to: #sendPointEvent:y:button:oop:selector: of: self parameters: '%x %y %b ' , anObject asOop printString , ' ' , aSelector asTkString ] onResizeSend: aSelector to: anObject [ "When the receiver is resized, send the 1-argument message identified by aSelector to anObject. The new size will be passed as a Point." aSelector numArgs = 1 ifFalse: [^self invalidArgsError: '1']. self registerEventReceiver: anObject. ^self bind: '' to: #sendPointEvent:y:oop:selector: of: self parameters: '%w %h ' , anObject asOop printString , ' ' , aSelector asTkString ] bind: event to: aSymbol of: anObject parameters: params [ "Private - Register the given event, to be passed to anObject via the aSymbol selector with the given parameters. Also avoid that anObject is garbage collected as long as the receiver exists." self registerEventReceiver: anObject; primBind: event to: aSymbol of: anObject parameters: params ] getKeyPressEventNames: key [ "Private - Given the key passed to a key event installer method, answer the KeyPress event name as required by Tcl." | platform mod keySym | keySym := key isCharacter ifTrue: [String with: key] ifFalse: [key]. (keySym at: 1) = $< ifTrue: [^{'<' , keySym , '>'}]. mod := ''. (keySym includes: $-) ifTrue: [mod := (ReadStream on: key) next: (key findLast: [:each | each = $-]) - 1. keySym := key copyFrom: mod size + 2 to: key size. platform := Blox platform. mod := (mod substrings: $-) inject: '' into: [:old :each | old , (self translateModifier: each platform: platform) , '-']]. ^(keySym size = 1 and: [keySym first isLetter]) ifTrue: ["Use both the lowercase and uppercase variants" {'<%1KeyPress-%2>' % {mod. keySym asLowercase}. '<%1KeyPress-%2>' % {mod. keySym asUppercase}}] ifFalse: [{'<%1KeyPress-%2>' % {mod. keySym}}] ] translateModifier: mod platform: platform [ | name | name := mod. name = 'Meta' ifTrue: [name := 'Alt']. name = 'Alt' & (platform == #macintosh) ifTrue: [name := 'Option']. name = 'Control' & (platform == #macintosh) ifTrue: [name := 'Cmd']. ^name ] invalidArgsError: expected [ "Private - Raise an error (as one could expect...) What is not so expected is that the expected argument is a string." ^self error: 'invalid number of arguments, expected ' , expected ] primBind: event to: aSymbol of: anObject parameters: params [ "Private - Register the given event, to be passed to anObject via the aSymbol selector with the given parameters" self subclassResponsibility ] sendPointEvent: x y: y button: button oop: oop selector: sel [ "Private - Filter mouse events from Tcl to Smalltalk. We receive three strings, we convert them to a Point and a Number, then pass them to a Smalltalk method" "oop printNl. oop asInteger asObject printNl. '---' printNl." oop asInteger asObject perform: sel asSymbol with: x asInteger @ y asInteger with: button asInteger ] registerEventReceiver: anObject [ "Private - Avoid that anObject is garbage collected as long as the receiver exists." eventReceivers isNil ifTrue: [eventReceivers := IdentitySet new]. ^eventReceivers add: anObject ] sendKeyEvent: key oop: oop selector: sel [ "Private - Filter ASCII events from Tcl to Smalltalk. We receive either *{}* for a non-ASCII char or *A* for an ASCII char, where A is the character. In the first case the event is eaten, in the second it is passed to a Smalltalk method" "key printNl. oop asInteger asObject printNl. '---' printNl." key size = 3 ifTrue: [oop asInteger asObject perform: sel asSymbol with: (key at: 2)] ] sendPointEvent: x y: y oop: oop selector: sel [ "Private - Filter mouse events from Tcl to Smalltalk. We receive two strings, we convert them to a Point and then pass them to a Smalltalk method" "oop printNl. oop asInteger asObject printNl. '---' printNl." oop asInteger asObject perform: sel asSymbol with: x asInteger @ y asInteger ] ] BEventTarget subclass: BEventSet [ | widget | BEventSet class >> new [ self shouldNotImplement ] BEventSet class >> new: widget [ "Private - Create a new event set object that will attach to the given widget. Answer the object. Note: this method should be called by #addEventSet:, not directly" ^(self basicNew) initialize: widget; yourself ] widget [ "Answer the widget to which the receiver is attached." ^widget ] initialize: aBWidget [ "Initialize the receiver's event handlers to attach to aBWidget. You can override this of course, but don't forget to call the superclass implementation first." widget := aBWidget ] primBind: event to: aSymbol of: anObject parameters: params [ "Private - Register the given event, to be passed to anObject via the aSymbol selector with the given parameters; this method is simply forwarded to the attached widget" ^self widget primBind: event to: aSymbol of: anObject parameters: params ] ] BEventTarget subclass: Blox [ | primitive properties parent children | Platform := nil. Interp := nil. Debug := nil. ClipStatus := nil. DoDispatchEvents := nil. Blox class >> tclInit [ ] Blox class >> evalIn: interp tcl: cmd [ ] Blox class >> resultIn: interp [ ] Blox class >> idle [ ] Blox class >> dispatchEvents [ "If this is the outermost dispatching loop that is started, dispatch events until the number of calls to #terminateMainLoop balances the number of calls to #dispatchEvents; return instantly if this is not the outermost dispatching loop that is started." | clipboard | DoDispatchEvents := DoDispatchEvents + 1. DoDispatchEvents = 1 ifFalse: [^self]. "If we're outside the event loop, Tk for Windows is unable to render the clipboard and locks up the clipboard viewer app. So, we save the contents for the next time we'll start a message loop. If the clipboard was temporarily saved to ClipStatus, restore it. ClipStatus is: - true if we own the clipboard - false if we don't - nil if we don't and we are outside a message loop - a String if we do and we are outside a message loop" clipboard := ClipStatus. ClipStatus := ClipStatus notNil and: [ClipStatus notEmpty]. ClipStatus ifTrue: [self clipboard: clipboard]. [self idle. Processor yield. DoDispatchEvents >= 1] whileTrue. "Save the contents of the clipboard if we own it." ClipStatus := ClipStatus ifTrue: [self clearClipboard] ifFalse: [nil] ] Blox class >> dispatchEvents: mainWindow [ "Dispatch some events; return upon destruction of the `mainWindow' widget (which can be any kind of BWidget, but will be typically a BWindow)." | sem | sem := Semaphore new. mainWindow onDestroySend: #signal to: sem. Blox dispatchEvents. sem wait. Blox terminateMainLoop ] Blox class >> terminateMainLoop [ "Terminate the event dispatching loop if this call to #terminateMainLoop balances the number of calls to #dispatchEvents." DoDispatchEvents > 0 ifTrue: [DoDispatchEvents := DoDispatchEvents - 1] ] Blox class >> update: aspect [ "Initialize the Tcl and Blox environments; executed automatically on startup." | initResult | aspect == #returnFromSnapshot ifFalse: [^self]. Debug isNil ifTrue: [Debug := false]. initResult := self tclInit. initResult isNil ifTrue: [^self]. initResult address = 0 ifTrue: [^self]. Interp := initResult. DoDispatchEvents := 0. ClipStatus := nil. Blox withAllSubclassesDo: [:each | (each class includesSelector: #initializeOnStartup) ifTrue: [each initializeOnStartup]] ] Blox class >> new [ self shouldNotImplement ] Blox class >> new: parent [ "Create a new widget of the type identified by the receiver, inside the given parent widget. Answer the new widget" ^self basicNew initialize: parent ] Blox class >> fromString: aString [ "Convert from Tk widget path name to Blox object. Answer nil if it isn't possible." | first last oopString oopInteger | last := aString size. aString size to: 1 by: -1 do: [:i | (aString at: i) = $. ifTrue: [last := i - 1]. (aString at: i) = $w ifTrue: [oopString := aString copyFrom: i + 1 to: last. oopInteger := 0. oopInteger := oopString inject: 0 into: [:val :ch | val * 36 + ch digitValue]. ^oopInteger asObjectNoFail]]. ^nil ] Blox class >> debug [ "Private - Answer whether Tcl code is output on the standard output" ^Debug ] Blox class >> debug: aBoolean [ "Private - Set whether Tcl code is output on the standard output" Debug := aBoolean ] Blox class >> tclEval: tclCode [ "Private - Evaluate the given Tcl code; if it raises an exception, raise it as a Smalltalk error" self debug ifTrue: [stdout nextPutAll: tclCode; nl; flush]. (self evalIn: Interp tcl: tclCode) = 1 ifTrue: [^self error: self tclResult] ] Blox class >> tclEval: tclCode with: arg1 [ "Private - Evaluate the given Tcl code, replacing %1 with arg1; if it raises an exception, raise it as a Smalltalk error" self tclEval: tclCode withArguments: {arg1} ] Blox class >> tclEval: tclCode with: arg1 with: arg2 [ "Private - Evaluate the given Tcl code, replacing %1 with arg1 and %2 with arg2; if it raises an exception, raise it as a Smalltalk error" self tclEval: tclCode withArguments: {arg1. arg2} ] Blox class >> tclEval: tclCode with: arg1 with: arg2 with: arg3 [ "Private - Evaluate the given Tcl code, replacing %1 with arg1, %2 with arg2 and %3 with arg3; if it raises an exception, raise it as a Smalltalk error" self tclEval: tclCode withArguments: {arg1. arg2. arg3} ] Blox class >> tclEval: tclCode with: arg1 with: arg2 with: arg3 with: arg4 [ "Private - Evaluate the given Tcl code, replacing %1 with arg1, %2 with arg2, and so on; if it raises an exception, raise it as a Smalltalk error" self tclEval: tclCode withArguments: {arg1. arg2. arg3. arg4} ] Blox class >> tclEval: tclCode withArguments: anArray [ "Private - Evaluate the given Tcl code, replacing %n with the n-th element of anArray; if it raises an exception, raise it as a Smalltalk error" | char result wasPercent | result := WriteStream on: (String new: tclCode size * 2). wasPercent := false. 1 to: tclCode size do: [:i | char := tclCode at: i. wasPercent ifTrue: [char = $% ifTrue: [result nextPut: char] ifFalse: [result display: (anArray at: char digitValue)]. wasPercent := false] ifFalse: [(wasPercent := char = $%) ifFalse: [result nextPut: char]]]. result nextPut: 0 asCharacter. self tclEval: result collection ] Blox class >> tclResult [ "Private - Return the result code for Tcl, as a Smalltalk String." ^Blox resultIn: Interp ] Blox class >> active [ "Answer the currently active Blox, or nil if the focus does not belong to a Smalltalk window." self tclEval: 'focus'. ^self fromString: self tclResult ] Blox class >> at: aPoint [ "Answer the Blox containing the given point on the screen, or nil if no Blox contains the given point (either because no Smalltalk window is there or because it is covered by another window)." self tclEval: 'winfo containing %1 %2' with: aPoint x printString with: aPoint y printString. ^self fromString: self tclResult ] Blox class >> atMouse [ "Answer the Blox under the mouse cursor's hot spot, or nil if no Blox contains the given point (either because no Smalltalk window is there or because it is covered by another window)." self tclEval: 'eval winfo containing [winfo pointerxy .]'. ^self fromString: self tclResult ] Blox class >> beep [ "Produce a bell" self tclEval: 'bell' ] Blox class >> clearClipboard [ "Clear the clipboard, answer its old contents." | contents | contents := self clipboard. self tclEval: 'clipboard clear'. ClipStatus isString ifTrue: [ClipStatus := nil]. ClipStatus == true ifTrue: [ClipStatus := false]. ^contents ] Blox class >> clipboard [ "Retrieve the text in the clipboard." self tclEval: ' if { [catch { selection get -selection CLIPBOARD } clipboard] } { return "" } else { return $clipboard }'. ^self tclResult ] Blox class >> clipboard: aString [ "Set the contents of the clipboard to aString (or empty the clipboard if aString is nil)." self clearClipboard. (aString isNil or: [aString isEmpty]) ifTrue: [^self]. ClipStatus isNil ifTrue: [ClipStatus := aString. ^self]. self tclEval: 'clipboard append -- ' , aString asTkString. ClipStatus := true ] Blox class >> createColor: red green: green blue: blue [ "Answer a color that can be passed to methods such as `backgroundColor:'. The color will have the given RGB components (range is 0~65535)." "The answer is actually a String with an X color name, like '#FFFFC000C000' for pink" ^(String new: 13) at: 1 put: $#; at: 2 put: (Character digitValue: ((red bitShift: -12) bitAnd: 15)); at: 3 put: (Character digitValue: ((red bitShift: -8) bitAnd: 15)); at: 4 put: (Character digitValue: ((red bitShift: -4) bitAnd: 15)); at: 5 put: (Character digitValue: (red bitAnd: 15)); at: 6 put: (Character digitValue: ((green bitShift: -12) bitAnd: 15)); at: 7 put: (Character digitValue: ((green bitShift: -8) bitAnd: 15)); at: 8 put: (Character digitValue: ((green bitShift: -4) bitAnd: 15)); at: 9 put: (Character digitValue: (green bitAnd: 15)); at: 10 put: (Character digitValue: ((blue bitShift: -12) bitAnd: 15)); at: 11 put: (Character digitValue: ((blue bitShift: -8) bitAnd: 15)); at: 12 put: (Character digitValue: ((blue bitShift: -4) bitAnd: 15)); at: 13 put: (Character digitValue: (blue bitAnd: 15)); yourself ] Blox class >> createColor: cyan magenta: magenta yellow: yellow [ "Answer a color that can be passed to methods such as `backgroundColor:'. The color will have the given CMY components (range is 0~65535)." ^self createColor: 65535 - cyan green: 65535 - magenta blue: 65535 - yellow ] Blox class >> createColor: cyan magenta: magenta yellow: yellow black: black [ "Answer a color that can be passed to methods such as `backgroundColor:'. The color will have the given CMYK components (range is 0~65535)." | base | base := 65535 - black. ^self createColor: (base - cyan max: 0) green: (base - magenta max: 0) blue: (base - yellow max: 0) ] Blox class >> createColor: hue saturation: sat value: value [ "Answer a color that can be passed to methods such as `backgroundColor:'. The color will have the given HSV components (range is 0~65535)." | hue6 f val index components | hue6 := hue \\ 1 * 6. index := hue6 integerPart + 1. "Which of the six slices of the hue circle" f := hue6 fractionPart. "Where in the slice of the hue circle" val := 65535 * value. components := Array with: val with: val * (1 - sat) with: val * (1 - (sat * f)) with: val * (1 - (sat * (1 - f))). "v" "p" "q" "t" ^self createColor: (components at: (#(1 3 2 2 4 1) at: index)) floor green: (components at: (#(4 1 1 3 2 2) at: index)) floor blue: (components at: (#(2 2 4 1 1 3) at: index)) floor ] Blox class >> fonts [ "Answer the names of the font families in the system. Additionally, `Times', `Courier' and `Helvetica' are always made available." | stream result font ch | self tclEval: 'lsort [font families]'. stream := ReadStream on: self tclResult. result := WriteStream on: (Array new: stream size // 10). [stream atEnd] whileFalse: [(ch := stream next) isSeparator ifFalse: [ch = ${ ifTrue: [font := stream upTo: $}] ifFalse: [font := ch asString , (stream upTo: $ )]. result nextPut: font]]. ^result contents ] Blox class >> mousePointer [ "If the mouse pointer is on the same screen as the application's windows, returns a Point containing the pointer's x and y coordinates measured in pixels in the screen's root window (under X, if a virtual root window is in use on the screen, the position is computed in the whole desktop, not relative to the top-left corner of the currently shown portion). If the mouse pointer isn't on the same screen as window then answer nil." | stream x | self tclEval: 'winfo pointerxy .'. stream := ReadStream on: self tclResult. (stream peekFor: $-) ifTrue: [^nil]. x := (stream upTo: $ ) asInteger. ^x @ stream upToEnd asInteger ] Blox class >> defaultFont [ "Answer the default font used by Blox." ^self platform = #macintosh ifTrue: ['lucida 13'] ifFalse: ['helvetica 10'] ] Blox class >> platform [ "Answer the platform on which Blox is running; it can be either #unix, #macintosh or #windows." Platform isNil ifTrue: [self tclEval: 'return $tcl_platform(platform)'. Platform := self tclResult asSymbol]. ^Platform ] Blox class >> screenOrigin [ "Answer a Point indicating the coordinates of the upper left point of the screen in the virtual root window on which the application's windows are drawn (under Windows and the Macintosh, that's always 0 @ 0)" | stream x | self tclEval: 'return "[winfo vrootx .] [winfo vrooty .]"'. stream := ReadStream on: self tclResult. x := (stream upTo: $ ) asInteger negated. ^x @ stream upToEnd asInteger negated ] Blox class >> screenResolution [ "Answer a Point containing the resolution in dots per inch of the screen, in the x and y directions." | stream x | self tclEval: 'return " [expr [winfo screenwidth .] * 25.4 / [winfo screenmmwidth .]] [expr [winfo screenheight .] * 25.4 / [winfo screenmmheight .]]" '. stream := ReadStream on: self tclResult. x := (stream upTo: $ ) asNumber rounded. ^x @ stream upToEnd asNumber rounded ] Blox class >> screenSize [ "Answer a Point containing the size of the virtual root window on which the application's windows are drawn (under Windows and the Macintosh, that's the size of the screen)" | stream x | self tclEval: 'return "[winfo vrootwidth .] [winfo vrootheight .]"'. stream := ReadStream on: self tclResult. x := (stream upTo: $ ) asInteger. ^x @ stream upToEnd asInteger ] state [ "Answer the value of the state option for the widget. Specifies one of three states for the button: normal, active, or disabled. In normal state the button is displayed using the foreground and background options. The active state is typically used when the pointer is over the button. In active state the button is displayed using the activeForeground and activeBackground options. Disabled state means that the button should be insensitive: the application will refuse to activate the widget and will ignore mouse button presses." self properties at: #state ifPresent: [:value | ^value]. self tclEval: '%1 cget -state' with: self connected with: self container. ^self properties at: #state put: self tclResult asSymbol ] state: value [ "Set the value of the state option for the widget. Specifies one of three states for the button: normal, active, or disabled. In normal state the button is displayed using the foreground and background options. The active state is typically used when the pointer is over the button. In active state the button is displayed using the activeForeground and activeBackground options. Disabled state means that the button should be insensitive: the application will refuse to activate the widget and will ignore mouse button presses." self tclEval: '%1 configure -state %3' with: self connected with: self container with: value asTkString. self properties at: #state put: value ] deepCopy [ "It does not make sense to make a copy, because it would make data inconsistent across different objects; so answer the receiver" ^self ] release [ "Destroy the receiver if it still exists, then perform the usual task of removing the dependency links" primitive isNil ifFalse: [self destroy]. super release ] shallowCopy [ "It does not make sense to make a copy, because it would make data inconsistent across different objects; so answer the receiver" ^self ] make: array [ "Create children of the receiver. Answer a Dictionary of the children. Each element of array is an Array including: a string which becomes the Dictionary's key, a binding like #{Blox.BWindow} identifying the class name, an array with the parameters to be set (for example #(#width: 50 #height: 30 #backgroundColor: 'blue')), and afterwards the children of the widget, described as arrays with this same format." ^self make: array on: LookupTable new ] make: array on: result [ "Private - Create children of the receiver, adding them to result; answer result. array has the format described in the comment to #make:" array do: [:each | self makeChild: each on: result]. ^result ] makeChild: each on: result [ "Private - Create a child of the receiver, adding them to result; each is a single element of the array described in the comment to #make:" | current selector | current := result at: (each at: 1) put: ((each at: 2) value new: self). each at: 3 do: [:param | selector isNil ifTrue: [selector := param] ifFalse: [current perform: selector with: param. selector := nil]]. each size > 3 ifFalse: [^result]. each from: 4 to: each size do: [:child | current makeChild: child on: result] ] addChild: child [ "The widget identified by child has been added to the receiver. This method is public not because you can call it, but because it can be useful to override it, not forgetting the call to either the superclass implementation or #basicAddChild:, to perform some initialization on the children just added. Answer the new child." ^children addLast: child ] basicAddChild: child [ "The widget identified by child has been added to the receiver. Add it to the children collection and answer the new child. This method is public because you can call it from #addChild:." ^children addLast: child ] bind: event to: aSymbol of: anObject parameters: params prefix: prefix [ "Private - Low level event binding - execute a Tcl command like ` {+callback }'. Prefix is typically some kind of the Tcl `bind' command." | stream | stream := WriteStream with: prefix copy. stream space; nextPutAll: event; nextPutAll: ' {+callback '; print: anObject asOop; space; nextPutAll: aSymbol asTkString; space; nextPutAll: params; nextPut: $}. self tclEval: stream contents. ^event ] connected [ "Private - Answer the name of Tk widget for the connected widget. This widget is used for most options and for event binding." ^self asPrimitiveWidget connected ] container [ "Private - Answer the name of Tk widget for the container widget. This widget is used when handling geometry and by a few methods such as #effect and #borderWidth." ^self asPrimitiveWidget container ] destroyed [ "Private - The receiver has been destroyed, clear the instance variables to release some memory." children := primitive := parent := nil ] guiObject [ "Private - Left for backward compatibility; answer the `primitive' instance variable which can either be another widget or it can be related to the names returned by #connected and #container." ^primitive ] initialize: parentWidget [ "This is called by #new: to initialize the widget (as the name says...). The default implementation initializes the receiver's instance variables. This method is public not because you can call it, but because it might be useful to override it. Always answer the receiver." parent := parentWidget. properties := IdentityDictionary new. children := OrderedCollection new ] primBind: event to: aSymbol of: anObject parameters: params [ "Private - Register the given event, to be passed to anObject via the aSymbol selector with the given parameters" ^self bind: event to: aSymbol of: anObject parameters: params prefix: 'bind ' , self connected ] primitive [ "Private - Answer the `primitive' instance variable which can either be another widget or it can be related to the names returned by #connected and #container." ^primitive ] properties [ "Private - Answer the properties dictionary" ^properties ] tclEval: tclCode [ "Private - Evaluate the given Tcl code; if it raises an exception, raise it as a Smalltalk error" Blox debug ifTrue: [stdout nextPutAll: tclCode; nl; flush]. (Blox evalIn: Interp tcl: tclCode) = 1 ifTrue: [^self error: self tclResult] ] tclEval: tclCode with: arg1 [ "Private - Evaluate the given Tcl code, replacing %1 with arg1; if it raises an exception, raise it as a Smalltalk error" self tclEval: tclCode withArguments: {arg1} ] tclEval: tclCode with: arg1 with: arg2 [ "Private - Evaluate the given Tcl code, replacing %1 with arg1 and %2 with arg2; if it raises an exception, raise it as a Smalltalk error" self tclEval: tclCode withArguments: {arg1. arg2} ] tclEval: tclCode with: arg1 with: arg2 with: arg3 [ "Private - Evaluate the given Tcl code, replacing %1 with arg1, %2 with arg2 and %3 with arg3; if it raises an exception, raise it as a Smalltalk error" self tclEval: tclCode withArguments: {arg1. arg2. arg3} ] tclEval: tclCode with: arg1 with: arg2 with: arg3 with: arg4 [ "Private - Evaluate the given Tcl code, replacing %1 with arg1, %2 with arg2, and so on; if it raises an exception, raise it as a Smalltalk error" self tclEval: tclCode withArguments: {arg1. arg2. arg3. arg4} ] tclEval: tclCode withArguments: anArray [ "Private - Evaluate the given Tcl code, replacing %n with the n-th element of anArray; if it raises an exception, raise it as a Smalltalk error" | char result wasPercent | result := WriteStream on: (String new: tclCode size * 2). wasPercent := false. 1 to: tclCode size do: [:i | char := tclCode at: i. wasPercent ifTrue: [char = $% ifTrue: [result nextPut: char] ifFalse: [result display: (anArray at: char digitValue)]. wasPercent := false] ifFalse: [(wasPercent := char = $%) ifFalse: [result nextPut: char]]]. result nextPut: 0 asCharacter. self tclEval: result collection ] tclResult [ "Private - Return the result code for Tcl, as a Smalltalk String." ^Blox resultIn: Interp ] asPrimitiveWidget [ "Answer the primitive widget that implements the receiver." self subclassResponsibility ] childrenCount [ "Answer how many children the receiver has" ^children size ] childrenDo: aBlock [ "Evaluate aBlock once for each of the receiver's child widgets, passing the widget to aBlock as a parameter" children do: aBlock ] destroy [ "Destroy the receiver" self tclEval: 'destroy ' , self container ] drawingArea [ "Answer a Rectangle identifying the receiver's drawing area. The rectangle's corners specify the upper-left and lower-right corners of the client area. Because coordinates are relative to the upper-left corner of a window's drawing area, the coordinates of the rectangle's corner are (0,0)." ^0 @ 0 corner: self widthAbsolute @ self heightAbsolute ] enabled [ "Answer whether the receiver is enabled to input. Although defined here, this method is only used for widgets that define a #state method" ^self state ~= #disabled ] enabled: enabled [ "Set whether the receiver is enabled to input (enabled is a boolean). Although defined here, this method is only used for widgets that define a #state: method" self state: (enabled ifTrue: [#normal] ifFalse: [#disabled]) ] exists [ "Answer whether the receiver has been destroyed or not (answer false in the former case, true in the latter)." ^primitive notNil ] fontHeight: aString [ "Answer the height of aString in pixels, when displayed in the same font as the receiver. Although defined here, this method is only used for widgets that define a #font method" self tclEval: 'font metrics %1 -linespace' with: self font asTkString. ^((aString occurrencesOf: Character nl) + 1) * self tclResult asNumber ] fontWidth: aString [ "Answer the width of aString in pixels, when displayed in the same font as the receiver. Although defined here, this method is only used for widgets that define a #font method" self tclEval: 'font measure %1 %2' with: self font asTkString with: aString asTkString. ^self tclResult asNumber ] isWindow [ "Answer whether the receiver represents a window on the screen." ^false ] parent [ "Answer the receiver's parent (or nil for a top-level window)." ^parent ] toplevel [ "Answer the top-level object (typically a BWindow or BPopupWindow) connected to the receiver." self parent isNil ifTrue: [^self]. ^self parent toplevel ] window [ "Answer the window in which the receiver stays. Note that while #toplevel won't answer a BTransientWindow, this method will." ^self parent window ] withChildrenDo: aBlock [ "Evaluate aBlock passing the receiver, and then once for each of the receiver's child widgets." self value: aBlock. self childrenDo: aBlock ] ] Blox subclass: BWidget [ BWidget class >> new [ "Create an instance of the receiver inside a BPopupWindow; do not map the window, answer the new widget. The created widget will become a child of the window and be completely attached to it (e.g. the geometry methods will modify the window's geometry). Note that while the widget *seems* to be directly painted on the root window, it actually belongs to the BPopupWindow; so don't send #destroy to the widget to remove it, but rather to the window." ^self new: BPopupWindow new ] BWidget class >> popup: initializationBlock [ "Create an instance of the receiver inside a BPopupWindow; before returning, pass the widget to the supplied initializationBlock, then map the window. Answer the new widget. The created widget will become a child of the window and be completely attached to it (e.g. the geometry methods will modify the window's geometry). Note that while the widget *seems* to be directly painted on the root window, it actually belongs to the BPopupWindow; so don't send #destroy to the widget to remove it, but rather to the window." | widget window | window := BPopupWindow new. widget := self new: window. initializationBlock value: widget. window map. ^widget ] borderWidth [ "Answer the value of the borderWidth option for the widget. Specifies a non-negative value indicating the width of the 3-D border to draw around the outside of the widget (if such a border is being drawn; the effect option typically determines this). The value may also be used when drawing 3-D effects in the interior of the widget. The value is measured in pixels." self properties at: #border ifPresent: [:value | ^value]. self tclEval: '%2 cget -borderwidth' with: self connected with: self container. ^self properties at: #border put: self tclResult asInteger ] borderWidth: value [ "Set the value of the borderWidth option for the widget. Specifies a non-negative value indicating the width of the 3-D border to draw around the outside of the widget (if such a border is being drawn; the effect option typically determines this). The value may also be used when drawing 3-D effects in the interior of the widget. The value is measured in pixels." self tclEval: '%2 configure -borderwidth %3' with: self connected with: self container with: value printString asTkString. self properties at: #border put: value ] cursor [ "Answer the value of the cursor option for the widget. Specifies the mouse cursor to be used for the widget. The value of the option is given by the standard X cursor cursor, i.e., any of the names defined in cursorcursor.h, without the leading XC_." self properties at: #cursor ifPresent: [:value | ^value]. self tclEval: '%1 cget -cursor' with: self connected with: self container. ^self properties at: #cursor put: self tclResult asSymbol ] cursor: value [ "Set the value of the cursor option for the widget. Specifies the mouse cursor to be used for the widget. The value of the option is given by the standard X cursor cursor, i.e., any of the names defined in cursorcursor.h, without the leading XC_." self tclEval: '%1 configure -cursor %3' with: self connected with: self container with: value asTkString. self properties at: #cursor put: value ] effect [ "Answer the value of the effect option for the widget. Specifies the effect desired for the widget's border. Acceptable values are raised, sunken, flat, ridge, solid, and groove. The value indicates how the interior of the widget should appear relative to its exterior; for example, raised means the interior of the widget should appear to protrude from the screen, relative to the exterior of the widget. Raised and sunken give the traditional 3-D appearance (for example, that of Xaw3D), while ridge and groove give a ``chiseled'' appearance like that of Swing or GTK+'s Metal theme. Flat and solid are not 3-D." self properties at: #effect ifPresent: [:value | ^value]. self tclEval: '%2 cget -relief' with: self connected with: self container. ^self properties at: #effect put: self tclResult asSymbol ] effect: value [ "Set the value of the effect option for the widget. Specifies the effect desired for the widget's border. Acceptable values are raised, sunken, flat, ridge, solid, and groove. The value indicates how the interior of the widget should appear relative to its exterior; for example, raised means the interior of the widget should appear to protrude from the screen, relative to the exterior of the widget. Raised and sunken give the traditional 3-D appearance (for example, that of Xaw3D), while ridge and groove give a ``chiseled'' appearance like that of Swing or GTK+'s Metal theme. Flat and solid are not 3-D." self tclEval: '%2 configure -relief %3' with: self connected with: self container with: value asTkString. self properties at: #effect put: value ] tabStop [ "Answer the value of the tabStop option for the widget. Determines whether the window accepts the focus during keyboard traversal (e.g., Tab and Shift-Tab). Before setting the focus to a window, Blox consults the value of the tabStop option. A value of false means that the window should be skipped entirely during keyboard traversal. true means that the window should receive the input focus as long as it is viewable (it and all of its ancestors are mapped). If you do not set this option, Blox makes the decision about whether or not to focus on the window: the current algorithm is to skip the window if it is disabled, it has no key bindings, or if it is not viewable. Of the standard widgets, BForm, BContainer, BLabel and BImage have no key bindings by default." self properties at: #takefocus ifPresent: [:value | ^value]. self tclEval: '%1 cget -takefocus' with: self connected with: self container. ^self properties at: #takefocus put: self tclResult == '1' ] tabStop: value [ "Set the value of the tabStop option for the widget. Determines whether the window accepts the focus during keyboard traversal (e.g., Tab and Shift-Tab). Before setting the focus to a window, Blox consults the value of the tabStop option. A value of false means that the window should be skipped entirely during keyboard traversal. true means that the window should receive the input focus as long as it is viewable (it and all of its ancestors are mapped). If you do not set this option, Blox makes the decision about whether or not to focus on the window: the current algorithm is to skip the window if it is disabled, it has no key bindings, or if it is not viewable. Of the standard widgets, BForm, BContainer, BLabel and BImage have no key bindings by default." self tclEval: '%1 configure -takefocus %3' with: self connected with: self container with: value asCBooleanValue printString asTkString. self properties at: #takefocus put: value ] addChild: child [ "The widget identified by child has been added to the receiver. This method is public not because you can call it, but because it can be useful to override it, not forgetting the call to basicAddChild, to perform some initialization on the children just added. Answer the new child." child isWindow ifFalse: [self tclEval: 'place %1 -in %2' with: child container with: self container]. ^self basicAddChild: child ] create [ "Make the receiver able to respond to its widget protocol. This method is public not because you can call it, but because it can be useful to override it, not forgetting the call to super, to perform some initialization on the primitive widget just created; for an example of this, see the implementation of BButtonLike." self subclassResponsibility ] initialize: parentWidget [ "This is called by #new: to initialize the widget (as the name says...). The default implementation calls all the other methods in the `customization' protocol and some private ones that take care of making the receiver's status consistent, so you should usually call it instead of doing everything by hand. This method is public not because you can call it, but because it might be useful to override it. Always answer the receiver." super initialize: parentWidget. self create. self bind: '' to: #destroyed of: self parameters: ''. self setInitialSize. self parent notNil ifTrue: [self parent addChild: self] ] setInitialSize [ "This is called by #initialize: to set the widget's initial size. The whole area is occupied by default. This method is public not because you can call it, but because it can be useful to override it." "Make the Tk placer's status, the receiver's properties and the window status (as returned by winfo) consistent." self x: 0 y: 0 width: self parent width height: self parent height ] activate [ "At any given time, one window on each display is designated as the focus window; any key press or key release events for the display are sent to that window. This method allows one to choose which window will have the focus in the receiver's display If the application currently has the input focus on the receiver's display, this method resets the input focus for the receiver's display to the receiver. If the application doesn't currently have the input focus on the receiver's display, Blox will remember the receiver as the focus for its top-level; the next time the focus arrives at the top-level, it will be redirected to the receiver (this is because most window managers will set the focus only to top-level windows, leaving it up to the application to redirect the focus among the children of the top-level)." self tclEval: 'focus ' , self connected ] activateNext [ "Activate the next widget in the focus `tabbing' order. The focus order depends on the widget creation order; you can set which widgets are in the order with the #tabStop: method." self tclEval: 'focus [ tk_focusNext %1 ]' with: self connected ] activatePrevious [ "Activate the previous widget in the focus `tabbing' order. The focus order depends on the widget creation order; you can set which widgets are in the order with the #tabStop: method." self tclEval: 'focus [ tk_focusPrev %1 ]' with: self connected ] bringToTop [ "Raise the receiver so that it is above all of its siblings in the widgets' z-order; the receiver will not be obscured by any siblings and will obscure any siblings that overlap it." self tclEval: 'raise ' , self container ] sendToBack [ "Lower the receiver so that it is below all of its siblings in the widgets' z-order; the receiver will be obscured by any siblings that overlap it and will not obscure any siblings." self tclEval: 'lower ' , self container ] isActive [ "Return whether the receiver is the window that currently owns the focus on its display." self tclEval: 'focus'. ^self tclResult = self connected ] boundingBox [ "Answer a Rectangle containing the bounding box of the receiver" ^self x @ self y extent: self width @ self height ] boundingBox: rect [ "Set the bounding box of the receiver to rect (a Rectangle)." self left: rect left top: rect top right: rect right bottom: rect bottom ] child: child height: value [ "Set the given child's height to value. The default implementation of this method uses `rubber-sheet' geometry management as explained in the comment to BWidget's #height method. You should not use this method, which is automatically called by the child's #height: method, but you might want to override it. The child's property slots whose name ends with `Geom' are reserved for this method. This method should never fail -- if it doesn't apply to the kind of geometry management that the receiver does, just do nothing." | relative heightParent | heightParent := self heightAbsolute. heightParent = 0 ifTrue: [^self]. child properties at: #heightGeom put: (relative := value / heightParent). self tclEval: 'place ' , child container , ' -relheight ' , relative asFloat printString ] child: child heightOffset: value [ "Adjust the given child's height by a fixed amount of value pixel. This is meaningful for the default implementation, using `rubber-sheet' geometry management as explained in the comment to BWidget's #height and #heightOffset: methods. You should not use this method, which is automatically called by the child's #heightOffset: method, but you might want to override it. if it doesn't apply to the kind of geometry management that the receiver does, just add value to the current height of the widget." self tclEval: 'place ' , child container , ' -height ' , value asFloat printString ] child: child stretch: aBoolean [ "This method is only used when on the path from the receiver to its toplevel there is a BContainer. It decides whether child is among the widgets that are stretched to fill the entire width of the BContainer; if this has not been set for this widget, it is propagated along the widget hierarchy." self properties at: #stretch ifAbsent: [self parent isNil ifTrue: [^self]. self parent child: self stretch: aBoolean] ] child: child width: value [ "Set the given child's width to value. The default implementation of this method uses `rubber-sheet' geometry management as explained in the comment to BWidget's #width method. You should not use this method, which is automatically called by the child's #width: method, but you might want to override it. The child's property slots whose name ends with `Geom' are reserved for this method. This method should never fail -- if it doesn't apply to the kind of geometry management that the receiver does, just do nothing." | relative widthParent | widthParent := self widthAbsolute. widthParent = 0 ifTrue: [^self]. child properties at: #widthGeom put: (relative := value / widthParent). self tclEval: 'place ' , child container , ' -relwidth ' , relative asFloat printString ] child: child widthOffset: value [ "Adjust the given child's width by a fixed amount of value pixel. This is meaningful for the default implementation, using `rubber-sheet' geometry management as explained in the comment to BWidget's #width and #widthOffset: methods. You should not use this method, which is automatically called by the child's #widthOffset: method, but you might want to override it. if it doesn't apply to the kind of geometry management that the receiver does, just add value to the current width of the widget." self tclEval: 'place ' , child container , ' -width ' , value asFloat printString ] child: child x: value [ "Set the given child's x to value. The default implementation of this method uses `rubber-sheet' geometry management as explained in the comment to BWidget's #x method. You should not use this method, which is automatically called by the child's #x: method, but you might want to override it. The child's property slots whose name ends with `Geom' are reserved for this method. This method should never fail -- if it doesn't apply to the kind of geometry management that the receiver does, just do nothing." | relative widthParent | widthParent := self widthAbsolute. widthParent = 0 ifTrue: [^self]. child properties at: #xGeom put: (relative := value / widthParent). self tclEval: 'place ' , child container , ' -relx ' , relative asFloat printString ] child: child xOffset: value [ "Adjust the given child's x by a fixed amount of value pixel. This is meaningful for the default implementation, using `rubber-sheet' geometry management as explained in the comment to BWidget's #x and #xOffset: methods. You should not use this method, which is automatically called by the child's #xOffset: method, but you might want to override it. if it doesn't apply to the kind of geometry management that the receiver does, just add value to the current x of the widget." self tclEval: 'place ' , child container , ' -x ' , value asFloat printString ] child: child y: value [ "Set the given child's y to value. The default implementation of this method uses `rubber-sheet' geometry management as explained in the comment to BWidget's #y method. You should not use this method, which is automatically called by the child's #y: method, but you might want to override it. The child's property slots whose name ends with `Geom' are reserved for this method. This method should never fail -- if it doesn't apply to the kind of geometry management that the receiver does, just do nothing." | relative heightParent | heightParent := self heightAbsolute. heightParent = 0 ifTrue: [^self]. child properties at: #yGeom put: (relative := value / heightParent). self tclEval: 'place ' , child container , ' -rely ' , relative asFloat printString ] child: child yOffset: value [ "Adjust the given child's y by a fixed amount of value pixel. This is meaningful for the default implementation, using `rubber-sheet' geometry management as explained in the comment to BWidget's #y and #yOffset: methods. You should not use this method, which is automatically called by the child's #yOffset: method, but you might want to override it. if it doesn't apply to the kind of geometry management that the receiver does, just add value to the current y of the widget." self tclEval: 'place ' , child container , ' -y ' , value asFloat printString ] extent [ "Answer a Point containing the receiver's size" ^self width @ self height ] extent: extent [ "Set the receiver's size to the width and height contained in extent (a Point)." self width: extent x height: extent y ] height [ "Answer the `variable' part of the receiver's height within the parent widget. The value returned does not include any fixed amount of pixels indicated by #heightOffset: and must be interpreted in a relative fashion: the ratio of the returned value to the current size of the parent will be preserved upon resize. This apparently complicated method is known as `rubber sheet' geometry management. Behavior if the left or right edges are not within the client area of the parent is not defined -- the window might be clamped or might be positioned according to the specification." ^self parent heightChild: self ] height: value [ "Set to `value' the height of the widget within the parent widget. The value is specified in a relative fashion as an integer, so that the ratio of `value' to the current size of the parent will be preserved upon resize. This apparently complicated method is known as `rubber sheet' geometry management." self parent child: self height: value ] heightAbsolute [ "Force a recalculation of the layout of widgets in the receiver's parent, then answer the current height of the receiver in pixels." Blox idle. self window isMapped ifFalse: [^self height]. self tclEval: 'winfo height ' , self container. ^self tclResult asInteger ] heightChild: child [ "Answer the given child's height. The default implementation of this method uses `rubber-sheet' geometry management as explained in the comment to BWidget's #height method. You should not use this method, which is automatically called by the child's #height method, but you might want to override. The child's property slots whose name ends with `Geom' are reserved for this method. This method should never fail -- if it doesn't apply to the kind of geometry management that the receiver does, just return 0." ^(child properties at: #heightGeom ifAbsentPut: [0]) * self height ] heightOffset [ "Private - Answer the pixels to be added or subtracted to the height of the receiver, with respect to the value set in a relative fashion through the #height: method." ^self properties at: #heightGeomOfs ifAbsent: [0] ] heightOffset: value [ "Add or subtract to the height of the receiver a fixed amount of `value' pixels, with respect to the value set in a relative fashion through the #height: method. Usage of this method is deprecated; use #inset: and BContainers instead." self properties at: #heightGeomOfs put: value. self parent child: self heightOffset: value ] heightPixels: value [ "Set the current height of the receiver to `value' pixels. Note that, after calling this method, #height will answer 0, which is logical considering that there is no `variable' part of the size (refer to #height and #height: for more explanations)." self height: 0; heightOffset: value ] inset: pixels [ "Inset the receiver's bounding box by the specified amount." ^self xOffset: self xOffset + pixels; yOffset: self yOffset + pixels; widthOffset: self widthOffset - (pixels * 2); heightOffset: self heightOffset - (pixels * 2) ] left: left top: top right: right bottom: bottom [ "Set the bounding box of the receiver through its components." self x: left y: top width: right - left + 1 height: bottom - top + 1 ] pos: position [ "Set the receiver's origin to the width and height contained in position (a Point)." self x: position x y: position y ] posHoriz: aBlox [ "Position the receiver immediately to the right of aBlox." | x width | width := aBlox width. self x: width + aBlox x y: aBlox y. width = 0 ifTrue: [width := aBlox widthAbsolute. self xOffset: width. self width > 0 ifTrue: [self widthOffset: self widthOffset - width]] ] posVert: aBlox [ "Position the receiver just below aBlox." | y height | height := aBlox height. self x: aBlox x y: height + aBlox y. height = 0 ifTrue: [height := aBlox heightAbsolute. self yOffset: height. self height > 0 ifTrue: [self heightOffset: self heightOffset - height]] ] stretch: aBoolean [ "This method is only considered when on the path from the receiver to its toplevel there is a BContainer. It decides whether we are among the widgets that are stretched to fill the entire width of the BContainer." self parent child: self stretch: aBoolean. self properties at: #stretch put: aBoolean ] width [ "Answer the `variable' part of the receiver's width within the parent widget. The value returned does not include any fixed amount of pixels indicated by #widthOffset: and must be interpreted in a relative fashion: the ratio of the returned value to the current size of the parent will be preserved upon resize. This apparently complicated method is known as `rubber sheet' geometry management. Behavior if the left or right edges are not within the client area of the parent is not defined -- the window might be clamped or might be positioned according to the specification." ^self parent widthChild: self ] width: value [ "Set to `value' the width of the widget within the parent widget. The value is specified in a relative fashion as an integer, so that the ratio of `value' to the current size of the parent will be preserved upon resize. This apparently complicated method is known as `rubber sheet' geometry management." self parent child: self width: value ] width: xSize height: ySize [ "Set the size of the receiver through its components xSize and ySize." self width: xSize; height: ySize ] widthAbsolute [ "Force a recalculation of the layout of widgets in the receiver's parent, then answer the current width of the receiver in pixels." Blox idle. self window isMapped ifFalse: [^self width]. self tclEval: 'winfo width ' , self container. ^self tclResult asInteger ] widthChild: child [ "Answer the given child's width. The default implementation of this method uses `rubber-sheet' geometry management as explained in the comment to BWidget's #width method. You should not use this method, which is automatically called by the child's #width method, but you might want to override. The child's property slots whose name ends with `Geom' are reserved for this method. This method should never fail -- if it doesn't apply to the kind of geometry management that the receiver does, just return 0." ^(child properties at: #widthGeom ifAbsentPut: [0]) * self width ] widthOffset [ "Private - Answer the pixels to be added or subtracted to the width of the receiver, with respect to the value set in a relative fashion through the #width: method." ^self properties at: #widthGeomOfs ifAbsent: [0] ] widthOffset: value [ "Add or subtract to the width of the receiver a fixed amount of `value' pixels, with respect to the value set in a relative fashion through the #width: method. Usage of this method is deprecated; use #inset: and BContainers instead." self properties at: #widthGeomOfs put: value. self parent child: self widthOffset: value ] widthPixels: value [ "Set the current width of the receiver to `value' pixels. Note that, after calling this method, #width will answer 0, which is logical considering that there is no `variable' part of the size (refer to #width and #width: for more explanations)." self width: 0; widthOffset: value ] x [ "Answer the `variable' part of the receiver's x within the parent widget. The value returned does not include any fixed amount of pixels indicated by #xOffset: and must be interpreted in a relative fashion: the ratio of the returned value to the current size of the parent will be preserved upon resize. This apparently complicated method is known as `rubber sheet' geometry management. Behavior if the left or right edges are not within the client area of the parent is not defined -- the window might be clamped or might be positioned according to the specification." ^self parent xChild: self ] x: value [ "Set to `value' the x of the widget within the parent widget. The value is specified in a relative fashion as an integer, so that the ratio of `value' to the current size of the parent will be preserved upon resize. This apparently complicated method is known as `rubber sheet' geometry management." self parent child: self x: value ] x: xPos y: yPos [ "Set the origin of the receiver through its components xPos and yPos." self x: xPos; y: yPos ] x: xPos y: yPos width: xSize height: ySize [ "Set the bounding box of the receiver through its origin and size." self x: xPos y: yPos; width: xSize height: ySize ] xAbsolute [ "Force a recalculation of the layout of widgets in the receiver's parent, then answer the current x of the receiver in pixels." Blox idle. self window isMapped ifFalse: [^self x]. self tclEval: 'winfo x ' , self container. ^self tclResult asInteger ] xChild: child [ "Answer the given child's x. The default implementation of this method uses `rubber-sheet' geometry management as explained in the comment to BWidget's #x method. You should not use this method, which is automatically called by the child's #x method, but you might want to override. The child's property slots whose name ends with `Geom' are reserved for this method. This method should never fail -- if it doesn't apply to the kind of geometry management that the receiver does, just return 0." ^(child properties at: #xGeom ifAbsentPut: [0]) * self width ] xOffset [ "Private - Answer the pixels to be added or subtracted to the x of the receiver, with respect to the value set in a relative fashion through the #x: method." ^self properties at: #xGeomOfs ifAbsent: [0] ] xOffset: value [ "Add or subtract to the x of the receiver a fixed amount of `value' pixels, with respect to the value set in a relative fashion through the #x: method. Usage of this method is deprecated; use #inset: and BContainers instead." self properties at: #xGeomOfs put: value. self parent child: self xOffset: value ] xPixels: value [ "Set the current x of the receiver to `value' pixels. Note that, after calling this method, #x will answer 0, which is logical considering that there is no `variable' part of the size (refer to #x and #x: for more explanations)." self x: 0; xOffset: value ] xRoot [ "Answer the x position of the receiver with respect to the top-left corner of the desktop (including the offset of the virtual root window under X)." self tclEval: 'expr [winfo rootx %1] + [winfo vrootx %1]' with: self container. ^self tclResult asInteger ] y [ "Answer the `variable' part of the receiver's y within the parent widget. The value returned does not include any fixed amount of pixels indicated by #yOffset: and must be interpreted in a relative fashion: the ratio of the returned value to the current size of the parent will be preserved upon resize. This apparently complicated method is known as `rubber sheet' geometry management. Behavior if the left or right edges are not within the client area of the parent is not defined -- the window might be clamped or might be positioned according to the specification." ^self parent yChild: self ] y: value [ "Set to `value' the y of the widget within the parent widget. The value is specified in a relative fashion as an integer, so that the ratio of `value' to the current size of the parent will be preserved upon resize. This apparently complicated method is known as `rubber sheet' geometry management." self parent child: self y: value ] yAbsolute [ "Force a recalculation of the layout of widgets in the receiver's parent, then answer the current y of the receiver in pixels." Blox idle. self window isMapped ifFalse: [^self y]. self tclEval: 'winfo y ' , self container. ^self tclResult asInteger ] yChild: child [ "Answer the given child's y. The default implementation of this method uses `rubber-sheet' geometry management as explained in the comment to BWidget's #y method. You should not use this method, which is automatically called by the child's #y method, but you might want to override. The child's property slots whose name ends with `Geom' are reserved for this method. This method should never fail -- if it doesn't apply to the kind of geometry management that the receiver does, just return 0." ^(child properties at: #yGeom ifAbsentPut: [0]) * self height ] yOffset [ "Private - Answer the pixels to be added or subtracted to the y of the receiver, with respect to the value set in a relative fashion through the #y: method." ^self properties at: #yGeomOfs ifAbsent: [0] ] yOffset: value [ "Add or subtract to the y of the receiver a fixed amount of `value' pixels, with respect to the value set in a relative fashion through the #y: method. Usage of this method is deprecated; use #inset: and BContainers instead." self properties at: #yGeomOfs put: value. self parent child: self yOffset: value ] yPixels: value [ "Set the current y of the receiver to `value' pixels. Note that, after calling this method, #y will answer 0, which is logical considering that there is no `variable' part of the size (refer to #y and #y: for more explanations)." self y: 0; yOffset: value ] yRoot [ "Answer the y position of the receiver with respect to the top-left corner of the desktop (including the offset of the virtual root window under X)." self tclEval: 'expr [winfo rooty %1] + [winfo vrooty %1]' with: self container. ^self tclResult asInteger ] ] BWidget subclass: BPrimitive [ asPrimitiveWidget [ "Answer the primitive widget that implements the receiver." ^self ] connected [ "Private - Answer the name of Tk widget for the connected widget." ^primitive ] container [ "Private - Answer the name of Tk widget for the container widget." ^primitive ] create [ "Private - Make the receiver able to respond to its widget protocol." self create: '' ] create: options [ "Private - Make the receiver able to respond to its widget protocol, initializing the Tk widget with the options passed in the parameter." self tclEval: '%1 %2 %3' with: self widgetType with: self connected with: options ] initialize: parentWidget [ "Private - This is called by #new: to initialize the widget (as the name says...). This implementation creates a unique Tk path name for the widget, then calls the superclass implementation." primitive := self setWidgetName: parentWidget. super initialize: parentWidget ] setWidgetName: parentWidget [ "Private - Create and answer a unique Tk path name for the widget" | name | name := '.w' , (self asOop printString: 36). ^parentWidget isNil ifTrue: [name] ifFalse: [parentWidget container , name] ] widgetType [ "Private - Answer the Tk command to create the widget" self subclassResponsibility ] ] BWidget subclass: BExtended [ asPrimitiveWidget [ "Answer the primitive widget that implements the receiver." ^primitive asPrimitiveWidget ] create [ "After this method is called (the call is made automatically) the receiver will be attached to a `primitive' widget (which can be in turn another extended widget). This method is public not because you can call it, but because it can be useful to override it, not forgetting the call to super (which only calls #newPrimitive and saves the result), to perform some initialization on the primitive widget just created; overriding #create is in fact more generic than overriding #newPrimitive. For an example of this, see the implementation of BButtonLike." primitive := self newPrimitive ] newPrimitive [ "Create and answer a new widget on which the implementation of the receiver will be based. You should not call this method directly; instead you must override it in BExtended's subclasses." self subclassResponsibility ] ] BPrimitive subclass: BViewport [ | connected | InitializedVP := nil. BViewport class >> initializeOnStartup [ InitializedVP := false ] connected [ "Private - Answer the name of Tk widget for the connected widget." ^connected ] create: options [ "Private - Create an instance of the receiver which sports two beautiful scrollbars, in the same way as BPrimitive's implementation of #create:." InitializedVP ifFalse: [self defineViewportProcedures]. self tclEval: 'createViewport %1 %2 {%3}' with: self widgetType with: self container with: options. connected := self tclResult ] defineViewportProcedures [ "Private - Define the Tcl procedures that handle layout and toggling of scrollbars" InitializedVP := true. self tclEval: ' set horizSB {-row 1 -column 0 -sticky ew} set vertSB {-row 0 -column 1 -sticky ns} proc scrollbarSet {w gridArgs first last} { if { $first == 0 && $last == 1 } { grid forget $w } else { eval grid $w $gridArgs } $w set $first $last } proc createViewport {type cnt opt} { frame $cnt -relief sunken eval $type $cnt.ctl $opt scrollbar $cnt.hs -orient horiz -command "$cnt.ctl xview" scrollbar $cnt.vs -orient vert -command "$cnt.ctl yview" grid $cnt.ctl -column 0 -row 0 -sticky news grid propagate $cnt off grid rowconfigure $cnt 0 -minsize 1 -weight 1 grid rowconfigure $cnt 1 -weight 0 grid columnconfigure $cnt 0 -minsize 1 -weight 1 grid columnconfigure $cnt 1 -weight 0 return $cnt.ctl }' ] horizontal [ "Answer whether an horizontal scrollbar is drawn in the widget if needed." ^self properties at: #horizontal ifAbsent: [false] ] horizontal: aBoolean [ "Set whether an horizontal scrollbar is drawn in the widget if needed." | code | (self properties at: #horizontal ifAbsent: [false]) == aBoolean ifTrue: [^self]. code := (self properties at: #horizontal put: aBoolean) ifTrue: ['%1.ctl configure -xscrollcommand "scrollbarSet %1.hs {$horizSB}" eval scrollbarSet %1.hs {$horizSB} [%1.ctl xview]'] ifFalse: ['%1.ctl configure -xscrollcommand "concat" # do nothing eval scrollbarSet %1.hs {$horizSB} 0 1']. self tclEval: code with: self container ] horizontalNeeded [ "Answer whether an horizontal scrollbar is needed to show all the information in the widget." self tclEval: 'expr [lindex [%1 xview] 0] > 0 || [lindex [%1 xview] 1] < 1' with: self connected. ^self tclResult = '1' ] horizontalShown [ "Answer whether an horizontal scrollbar is drawn in the widget." ^self horizontal and: [self horizontalNeeded] ] vertical [ "Answer whether a vertical scrollbar is drawn in the widget if needed." ^self properties at: #vertical ifAbsent: [false] ] vertical: aBoolean [ "Set whether a vertical scrollbar is drawn in the widget if needed." | code | (self properties at: #vertical ifAbsent: [false]) == aBoolean ifTrue: [^self]. code := (self properties at: #horizontal put: aBoolean) ifTrue: ['%1.ctl configure -yscrollcommand "scrollbarSet %1.vs {$vertSB}" eval scrollbarSet %1.vs {$vertSB} [%1.ctl yview]'] ifFalse: ['%1.ctl configure -yscrollcommand "concat" # do nothing eval scrollbarSet %1.vs {$vertSB} 0 1']. self tclEval: code with: self container ] verticalNeeded [ "Answer whether a vertical scrollbar is needed to show all the information in the widget." self tclEval: 'expr [lindex [%1 yview] 0] > 0 || [lindex [%1 yview] 1] < 1' with: self connected. ^self tclResult = '1' ] verticalShown [ "Answer whether a vertical scrollbar is drawn in the widget." ^self vertical and: [self verticalNeeded] ] ] Blox subclass: BMenuObject [ | childrensUnderline callback | activeBackground [ "Answer the value of the activeBackground option for the widget. Specifies background color to use when drawing active elements. An element (a widget or portion of a widget) is active if the mouse cursor is positioned over the element and pressing a mouse button will cause some action to occur. For some elements on Windows and Macintosh systems, the active color will only be used while mouse button 1 is pressed over the element." self properties at: #activebackground ifPresent: [:value | ^value]. self tclEval: '%1 cget -activebackground' with: self connected with: self container. ^self properties at: #activebackground put: self tclResult ] activeBackground: value [ "Set the value of the activeBackground option for the widget. Specifies background color to use when drawing active elements. An element (a widget or portion of a widget) is active if the mouse cursor is positioned over the element and pressing a mouse button will cause some action to occur. For some elements on Windows and Macintosh systems, the active color will only be used while mouse button 1 is pressed over the element." self tclEval: '%1 configure -activebackground %3' with: self connected with: self container with: value asTkString. self properties at: #activebackground put: value ] activeForeground [ "Answer the value of the activeForeground option for the widget. Specifies foreground color to use when drawing active elements. See above for definition of active elements." self properties at: #activeforeground ifPresent: [:value | ^value]. self tclEval: '%1 cget -activeforeground' with: self connected with: self container. ^self properties at: #activeforeground put: self tclResult ] activeForeground: value [ "Set the value of the activeForeground option for the widget. Specifies foreground color to use when drawing active elements. See above for definition of active elements." self tclEval: '%1 configure -activeforeground %3' with: self connected with: self container with: value asTkString. self properties at: #activeforeground put: value ] asPrimitiveWidget [ "Answer the primitive widget that implements the receiver." ^self ] backgroundColor [ "Answer the value of the backgroundColor option for the widget. Specifies the normal background color to use when displaying the widget." self properties at: #background ifPresent: [:value | ^value]. self tclEval: '%1 cget -background' with: self connected with: self container. ^self properties at: #background put: self tclResult ] backgroundColor: value [ "Set the value of the backgroundColor option for the widget. Specifies the normal background color to use when displaying the widget." self tclEval: '%1 configure -background %3' with: self connected with: self container with: value asTkString. self properties at: #background put: value ] foregroundColor [ "Answer the value of the foregroundColor option for the widget. Specifies the normal foreground color to use when displaying the widget." self properties at: #foreground ifPresent: [:value | ^value]. self tclEval: '%1 cget -foreground' with: self connected with: self container. ^self properties at: #foreground put: self tclResult ] foregroundColor: value [ "Set the value of the foregroundColor option for the widget. Specifies the normal foreground color to use when displaying the widget." self tclEval: '%1 configure -foreground %3' with: self connected with: self container with: value asTkString. self properties at: #foreground put: value ] callback [ "Answer a DirectedMessage that is sent when the receiver is modified, or nil if none has been set up." ^callback ] callback: aReceiver message: aSymbol [ "Set up so that aReceiver is sent the aSymbol message (the name of a zero- or one-argument selector) when the receiver is clicked. If the method accepts an argument, the receiver is passed." | arguments selector numArgs | selector := aSymbol asSymbol. numArgs := selector numArgs. arguments := #(). numArgs = 1 ifTrue: [arguments := Array with: self]. callback := DirectedMessage selector: selector arguments: arguments receiver: aReceiver ] callback: aReceiver message: aSymbol argument: anObject [ "Set up so that aReceiver is sent the aSymbol message (the name of a one- or two-argument selector) when the receiver is clicked. If the method accepts two argument, the receiver is passed together with anObject; if it accepts a single one, instead, only anObject is passed." | arguments selector numArgs | selector := aSymbol asSymbol. numArgs := selector numArgs. numArgs = 2 ifTrue: [arguments := {self. anObject}] ifFalse: [arguments := {anObject}]. callback := DirectedMessage selector: selector arguments: arguments receiver: aReceiver ] invokeCallback [ "Generate a synthetic callback" self callback isNil ifFalse: [self callback send] ] underline: label [ childrensUnderline isNil ifTrue: [childrensUnderline := ByteArray new: 256]. label doWithIndex: [:each :index | | ascii | ascii := each asUppercase value + 1. (childrensUnderline at: ascii) = 0 ifTrue: [childrensUnderline at: ascii put: 1. ^index - 1]]. ^0 ] ] "-------------------------- Gui class -----------------------------" "-------------------------- BEventTarget class -----------------------------" "-------------------------- BEventSet class -----------------------------" "-------------------------- Blox class -----------------------------" "-------------------------- BWidget class -----------------------------" "-------------------------- BPrimitive class -----------------------------" "-------------------------- BExtended class -----------------------------" "-------------------------- BViewport class -----------------------------" "-------------------------- BMenuObject class -----------------------------" String extend [ asTkString [ "Private, Blox - Answer a copy of the receiver enclosed in double-quotes and in which all the characters that Tk cannot read are escaped through a backslash" | i stream ch crFound | stream := WriteStream on: (self copyEmpty: self size + 10). stream nextPut: $". crFound := false. i := 1. [i <= self size] whileTrue: [ch := self at: i. ch = $" ifTrue: [stream nextPut: $\]. ch = $\ ifTrue: [stream nextPut: $\]. ch = $[ ifTrue: [stream nextPut: $\]. ch = $] ifTrue: [stream nextPut: $\]. ch = $$ ifTrue: [stream nextPut: $\]. ch = Character nl ifTrue: ["Under Windows, CR/LF-separated lines are common. Turn a CR/LF pair into a single \n" crFound ifTrue: [stream skip: -2]. stream nextPut: $\. ch := $n]. "On Macs, CR-separated lines are common. Turn 'em into \n" (crFound := ch == Character cr) ifTrue: [stream nextPut: $\. ch := $n]. ch < $ | (ch > $~) ifFalse: [stream nextPut: ch] ifTrue: [stream nextPutAll: '\'; nextPut: (Character value: ch value // 64 \\ 8 + 48); nextPut: (Character value: ch value // 8 \\ 8 + 48); nextPut: (Character value: ch value \\ 8 + 48)]. i := i + 1]. stream nextPut: $". ^stream contents ] asTkImageString [ "Private, Blox - Look for GIF images; for those, since Base-64 data does not contain { and }, is better to use the {} syntax." "R0lG is `GIF' in Base-64 encoding." ^(self match: 'R0lG*') ifTrue: ['{%1}' % {self}] ifFalse: [self asTkString] ] ] smalltalk-3.2.5/packages/blox/tk/BloxWidgets.st0000644000175000017500000040157612123404352016402 00000000000000"====================================================================== | | Smalltalk Tk-based GUI building blocks (basic widget classes). | | ======================================================================" "====================================================================== | | Copyright 1999, 2000, 2001, 2002, 2009 Free Software Foundation, Inc. | Written by Paolo Bonzini. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LESSER. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" BPrimitive subclass: BEdit [ | callback | Initialized := nil. BEdit class >> new: parent contents: aString [ "Answer a new BEdit widget laid inside the given parent widget, with a default content of aString" ^(self new: parent) contents: aString; yourself ] BEdit class >> initializeOnStartup [ Initialized := false ] backgroundColor [ "Answer the value of the backgroundColor option for the widget. Specifies the normal background color to use when displaying the widget." self properties at: #background ifPresent: [:value | ^value]. self tclEval: '%1 cget -background' with: self connected with: self container. ^self properties at: #background put: self tclResult ] backgroundColor: value [ "Set the value of the backgroundColor option for the widget. Specifies the normal background color to use when displaying the widget." self tclEval: '%1 configure -background %3' with: self connected with: self container with: value asTkString. self properties at: #background put: value ] callback [ "Answer a DirectedMessage that is sent when the receiver is modified, or nil if none has been set up." ^callback ] callback: aReceiver message: aSymbol [ "Set up so that aReceiver is sent the aSymbol message (the name of a zero- or one-argument selector) when the receiver is modified. If the method accepts an argument, the receiver is passed." | arguments selector numArgs | selector := aSymbol asSymbol. numArgs := selector numArgs. arguments := #(). numArgs = 1 ifTrue: [arguments := Array with: self]. callback := DirectedMessage selector: selector arguments: arguments receiver: aReceiver ] contents [ "Return the contents of the widget" self tclEval: 'return ${var' , self connected , '}'. ^self tclResult ] contents: newText [ "Set the contents of the widget" self tclEval: 'set var' , self connected , ' ' , newText asTkString ] font [ "Answer the value of the font option for the widget. Specifies the font to use when drawing text inside the widget. The font can be given as either an X font name or a Blox font description string. X font names are given as many fields, each led by a minus, and each of which can be replaced by an * to indicate a default value is ok: foundry, family, weight, slant, setwidth, addstyle, pixel size, point size (the same as pixel size for historical reasons), horizontal resolution, vertical resolution, spacing, width, charset and character encoding. Blox font description strings have three fields, which must be separated by a space and of which only the first is mandatory: the font family, the font size in points (or in pixels if a negative value is supplied), and a number of styles separated by a space (valid styles are normal, bold, italic, underline and overstrike). Examples of valid fonts are ``Helvetica 10 Bold'', ``Times -14'', ``Futura Bold Underline''. You must enclose the font family in braces if it is made of two or more words." self properties at: #font ifPresent: [:value | ^value]. self tclEval: '%1 cget -font' with: self connected with: self container. ^self properties at: #font put: self tclResult ] font: value [ "Set the value of the font option for the widget. Specifies the font to use when drawing text inside the widget. The font can be given as either an X font name or a Blox font description string. X font names are given as many fields, each led by a minus, and each of which can be replaced by an * to indicate a default value is ok: foundry, family, weight, slant, setwidth, addstyle, pixel size, point size (the same as pixel size for historical reasons), horizontal resolution, vertical resolution, spacing, width, charset and character encoding. Blox font description strings have three fields, which must be separated by a space and of which only the first is mandatory: the font family, the font size in points (or in pixels if a negative value is supplied), and a number of styles separated by a space (valid styles are normal, bold, italic, underline and overstrike). Examples of valid fonts are ``Helvetica 10 Bold'', ``Times -14'', ``Futura Bold Underline''. You must enclose the font family in braces if it is made of two or more words." self tclEval: '%1 configure -font %3' with: self connected with: self container with: value asTkString. self properties at: #font put: value ] foregroundColor [ "Answer the value of the foregroundColor option for the widget. Specifies the normal foreground color to use when displaying the widget." self properties at: #foreground ifPresent: [:value | ^value]. self tclEval: '%1 cget -foreground' with: self connected with: self container. ^self properties at: #foreground put: self tclResult ] foregroundColor: value [ "Set the value of the foregroundColor option for the widget. Specifies the normal foreground color to use when displaying the widget." self tclEval: '%1 configure -foreground %3' with: self connected with: self container with: value asTkString. self properties at: #foreground put: value ] selectBackground [ "Answer the value of the selectBackground option for the widget. Specifies the background color to use when displaying selected parts of the widget." self properties at: #selectbackground ifPresent: [:value | ^value]. self tclEval: '%1 cget -selectbackground' with: self connected with: self container. ^self properties at: #selectbackground put: self tclResult ] selectBackground: value [ "Set the value of the selectBackground option for the widget. Specifies the background color to use when displaying selected parts of the widget." self tclEval: '%1 configure -selectbackground %3' with: self connected with: self container with: value asTkString. self properties at: #selectbackground put: value ] selectForeground [ "Answer the value of the selectForeground option for the widget. Specifies the foreground color to use when displaying selected parts of the widget." self properties at: #selectforeground ifPresent: [:value | ^value]. self tclEval: '%1 cget -selectforeground' with: self connected with: self container. ^self properties at: #selectforeground put: self tclResult ] selectForeground: value [ "Set the value of the selectForeground option for the widget. Specifies the foreground color to use when displaying selected parts of the widget." self tclEval: '%1 configure -selectforeground %3' with: self connected with: self container with: value asTkString. self properties at: #selectforeground put: value ] create [ "Private - Set up the widget and Tcl hooks to get callbacks from it." self create: ' -width 0 -font {' , self class defaultFont , '}'. Initialized ifFalse: [self defineCallbackProcedure]. self tclEval: ' set var%1 {} bind %1 <> {callback %2 invokeCallback} trace variable var%1 w doEditCallback %1 configure -textvariable var%1 -highlightthickness 0 -takefocus 1' with: self connected with: self asOop printString ] defineCallbackProcedure [ "Private - Set up a Tcl hook to generate Changed events for entry widgets" Initialized := true. self tclEval: ' proc doEditCallback { name el op } { regsub ^var $name {} widgetName event generate $widgetName <> }' ] setInitialSize [ "Make the Tk placer's status, the receiver's properties and the window status (as returned by winfo) consistent. Occupy the height indicated by the widget itself and the whole of the parent's width, at the top left corner" self x: 0 y: 0; width: self parent width ] widgetType [ ^'entry' ] destroyed [ "Private - The receiver has been destroyed, clear the corresponding Tcl variable to avoid memory leaks." self tclEval: 'unset var' , self connected. super destroyed ] hasSelection [ "Answer whether there is selected text in the widget" self tclEval: self connected , ' selection present'. ^self tclResult = '1' ] insertAtEnd: aString [ "Clear the selection and append aString at the end of the widget." self tclEval: '%1 selection clear %1 insert end %2 %1 see end' with: self connected with: aString asTkString ] insertText: aString [ "Insert aString in the widget at the current insertion point, replacing the currently selected text (if any)." self tclEval: 'catch { %1 delete sel.first sel.last } %1 insert insert %2 %1 see insert' with: self connected with: aString asTkString ] invokeCallback [ "Generate a synthetic callback." self callback isNil ifFalse: [self callback send] ] nextPut: aCharacter [ "Clear the selection and append aCharacter at the end of the widget." self insertAtEnd: (String with: aCharacter) ] nextPutAll: aString [ "Clear the selection and append aString at the end of the widget." self insertAtEnd: aString ] nl [ "Clear the selection and append a linefeed character at the end of the widget." self insertAtEnd: Character nl asString ] replaceSelection: aString [ "Insert aString in the widget at the current insertion point, replacing the currently selected text (if any), and leaving the text selected." self tclEval: 'catch { %1 icursor sel.first %1 delete sel.first sel.last } %1 insert insert %2 %1 select insert [expr %3 + [%1 index insert]] %1 see insert' with: self connected with: aString asTkString with: aString size printString ] selectAll [ "Select the whole contents of the widget." self tclEval: self connected , ' selection range 0 end' ] selectFrom: first to: last [ "Sets the selection to include the characters starting with the one indexed by first (the very first character in the widget having index 1) and ending with the one just before last. If last refers to the same character as first or an earlier one, then the widget's selection is cleared." self tclEval: '%1 selection range %2 %3' with: self connected with: (first - 1) printString with: (last - 1) printString ] selection [ "Answer an empty string if the widget has no selection, else answer the currently selected text" | stream first | self tclEval: 'if [%1 selection present] { return [string range ${var%1} [%1 index sel.first] [%1 index sel.last]]" }' with: self connected. ^self tclResult ] selectionRange [ "Answer nil if the widget has no selection, else answer an Interval object whose first item is the index of the first character in the selection, and whose last item is the index of the character just after the last one in the selection." | stream first | self tclEval: 'if [%1 selection present] { return "[%1 index sel.first] [%1 index sel.last]" }' with: self connected. stream := ReadStream on: self tclResult. stream atEnd ifTrue: [^nil]. first := (stream upTo: $ ) asInteger + 1. ^first to: stream upToEnd asInteger + 1 ] space [ "Clear the selection and append a space at the end of the widget." self insertAtEnd: ' ' ] ] BPrimitive subclass: BLabel [ AnchorPoints := nil. BLabel class >> initialize [ "Private - Initialize the receiver's class variables." (AnchorPoints := IdentityDictionary new: 15) at: #topLeft put: 'nw'; at: #topCenter put: 'n'; at: #topRight put: 'ne'; at: #leftCenter put: 'w'; at: #center put: 'center'; at: #rightCenter put: 'e'; at: #bottomLeft put: 'sw'; at: #bottomCenter put: 's'; at: #bottomRight put: 'se' ] BLabel class >> new: parent label: label [ "Answer a new BLabel widget laid inside the given parent widget, showing by default the `label' String." ^(self new: parent) label: label; yourself ] alignment [ "Answer the value of the anchor option for the widget. Specifies how the information in a widget (e.g. text or a bitmap) is to be displayed in the widget. Must be one of the symbols #topLeft, #topCenter, #topRight, #leftCenter, #center, #rightCenter, #bottomLeft, #bottomCenter, #bottomRight. For example, #topLeft means display the information such that its top-left corner is at the top-left corner of the widget." ^self properties at: #alignment ifAbsent: [#topLeft] ] alignment: aSymbol [ "Set the value of the anchor option for the widget. Specifies how the information in a widget (e.g. text or a bitmap) is to be displayed in the widget. Must be one of the symbols #topLeft, #topCenter, #topRight, #leftCenter, #center, #rightCenter, #bottomLeft, #bottomCenter, #bottomRight. For example, #topLeft means display the information such that its top-left corner is at the top-left corner of the widget." self anchor: (AnchorPoints at: aSymbol). self properties at: #alignment put: aSymbol ] backgroundColor [ "Answer the value of the backgroundColor option for the widget. Specifies the normal background color to use when displaying the widget." self properties at: #background ifPresent: [:value | ^value]. self tclEval: '%1 cget -background' with: self connected with: self container. ^self properties at: #background put: self tclResult ] backgroundColor: value [ "Set the value of the backgroundColor option for the widget. Specifies the normal background color to use when displaying the widget." self tclEval: '%1 configure -background %3' with: self connected with: self container with: value asTkString. self properties at: #background put: value ] font [ "Answer the value of the font option for the widget. Specifies the font to use when drawing text inside the widget. The font can be given as either an X font name or a Blox font description string. X font names are given as many fields, each led by a minus, and each of which can be replaced by an * to indicate a default value is ok: foundry, family, weight, slant, setwidth, addstyle, pixel size, point size (the same as pixel size for historical reasons), horizontal resolution, vertical resolution, spacing, width, charset and character encoding. Blox font description strings have three fields, which must be separated by a space and of which only the first is mandatory: the font family, the font size in points (or in pixels if a negative value is supplied), and a number of styles separated by a space (valid styles are normal, bold, italic, underline and overstrike). Examples of valid fonts are ``Helvetica 10 Bold'', ``Times -14'', ``Futura Bold Underline''. You must enclose the font family in braces if it is made of two or more words." self properties at: #font ifPresent: [:value | ^value]. self tclEval: '%1 cget -font' with: self connected with: self container. ^self properties at: #font put: self tclResult ] font: value [ "Set the value of the font option for the widget. Specifies the font to use when drawing text inside the widget. The font can be given as either an X font name or a Blox font description string. X font names are given as many fields, each led by a minus, and each of which can be replaced by an * to indicate a default value is ok: foundry, family, weight, slant, setwidth, addstyle, pixel size, point size (the same as pixel size for historical reasons), horizontal resolution, vertical resolution, spacing, width, charset and character encoding. Blox font description strings have three fields, which must be separated by a space and of which only the first is mandatory: the font family, the font size in points (or in pixels if a negative value is supplied), and a number of styles separated by a space (valid styles are normal, bold, italic, underline and overstrike). Examples of valid fonts are ``Helvetica 10 Bold'', ``Times -14'', ``Futura Bold Underline''. You must enclose the font family in braces if it is made of two or more words." self tclEval: '%1 configure -font %3' with: self connected with: self container with: value asTkString. self properties at: #font put: value ] foregroundColor [ "Answer the value of the foregroundColor option for the widget. Specifies the normal foreground color to use when displaying the widget." self properties at: #foreground ifPresent: [:value | ^value]. self tclEval: '%1 cget -foreground' with: self connected with: self container. ^self properties at: #foreground put: self tclResult ] foregroundColor: value [ "Set the value of the foregroundColor option for the widget. Specifies the normal foreground color to use when displaying the widget." self tclEval: '%1 configure -foreground %3' with: self connected with: self container with: value asTkString. self properties at: #foreground put: value ] label [ "Answer the value of the label option for the widget. Specifies a string to be displayed inside the widget. The way in which the string is displayed depends on the particular widget and may be determined by other options, such as anchor. For windows, this is the title of the window." self properties at: #text ifPresent: [:value | ^value]. self tclEval: '%1 cget -text' with: self connected with: self container. ^self properties at: #text put: self tclResult ] label: value [ "Set the value of the label option for the widget. Specifies a string to be displayed inside the widget. The way in which the string is displayed depends on the particular widget and may be determined by other options, such as anchor. For windows, this is the title of the window." self tclEval: '%1 configure -text %3' with: self connected with: self container with: value asTkString. self properties at: #text put: value ] anchor: value [ "Private - Set the value of the Tk anchor option for the widget." self tclEval: '%1 configure -anchor %3' with: self connected with: self container with: value asTkString. self properties at: #anchor put: value ] create [ self create: '-anchor nw -takefocus 0 -font {' , self class defaultFont , '}'. self tclEval: 'bind %1 "+%1 configure -wraplength %%w"' with: self connected ] initialize: parentWidget [ super initialize: parentWidget. parentWidget isNil ifFalse: [self backgroundColor: parentWidget backgroundColor] ] setInitialSize [ "Make the Tk placer's status, the receiver's properties and the window status (as returned by winfo) consistent. Occupy the area indicated by the widget itself, at the top left corner" self x: 0 y: 0 ] widgetType [ ^'label' ] ] BPrimitive subclass: BButton [ | callback | BButton class >> new: parent label: label [ "Answer a new BButton widget laid inside the given parent widget, showing by default the `label' String." ^(self new: parent) label: label; yourself ] backgroundColor [ "Answer the value of the backgroundColor option for the widget. Specifies the normal background color to use when displaying the widget." self properties at: #background ifPresent: [:value | ^value]. self tclEval: '%1 cget -background' with: self connected with: self container. ^self properties at: #background put: self tclResult ] backgroundColor: value [ "Set the value of the backgroundColor option for the widget. Specifies the normal background color to use when displaying the widget." self tclEval: '%1 configure -background %3' with: self connected with: self container with: value asTkString. self properties at: #background put: value ] callback [ "Answer a DirectedMessage that is sent when the receiver is clicked, or nil if none has been set up." ^callback ] callback: aReceiver message: aSymbol [ "Set up so that aReceiver is sent the aSymbol message (the name of a zero- or one-argument selector) when the receiver is clicked. If the method accepts an argument, the receiver is passed." | arguments selector numArgs | selector := aSymbol asSymbol. numArgs := selector numArgs. arguments := #(). numArgs = 1 ifTrue: [arguments := Array with: self]. callback := DirectedMessage selector: selector arguments: arguments receiver: aReceiver ] font [ "Answer the value of the font option for the widget. Specifies the font to use when drawing text inside the widget. The font can be given as either an X font name or a Blox font description string. X font names are given as many fields, each led by a minus, and each of which can be replaced by an * to indicate a default value is ok: foundry, family, weight, slant, setwidth, addstyle, pixel size, point size (the same as pixel size for historical reasons), horizontal resolution, vertical resolution, spacing, width, charset and character encoding. Blox font description strings have three fields, which must be separated by a space and of which only the first is mandatory: the font family, the font size in points (or in pixels if a negative value is supplied), and a number of styles separated by a space (valid styles are normal, bold, italic, underline and overstrike). Examples of valid fonts are ``Helvetica 10 Bold'', ``Times -14'', ``Futura Bold Underline''. You must enclose the font family in braces if it is made of two or more words." self properties at: #font ifPresent: [:value | ^value]. self tclEval: '%1 cget -font' with: self connected with: self container. ^self properties at: #font put: self tclResult ] font: value [ "Set the value of the font option for the widget. Specifies the font to use when drawing text inside the widget. The font can be given as either an X font name or a Blox font description string. X font names are given as many fields, each led by a minus, and each of which can be replaced by an * to indicate a default value is ok: foundry, family, weight, slant, setwidth, addstyle, pixel size, point size (the same as pixel size for historical reasons), horizontal resolution, vertical resolution, spacing, width, charset and character encoding. Blox font description strings have three fields, which must be separated by a space and of which only the first is mandatory: the font family, the font size in points (or in pixels if a negative value is supplied), and a number of styles separated by a space (valid styles are normal, bold, italic, underline and overstrike). Examples of valid fonts are ``Helvetica 10 Bold'', ``Times -14'', ``Futura Bold Underline''. You must enclose the font family in braces if it is made of two or more words." self tclEval: '%1 configure -font %3' with: self connected with: self container with: value asTkString. self properties at: #font put: value ] foregroundColor [ "Answer the value of the foregroundColor option for the widget. Specifies the normal foreground color to use when displaying the widget." self properties at: #foreground ifPresent: [:value | ^value]. self tclEval: '%1 cget -foreground' with: self connected with: self container. ^self properties at: #foreground put: self tclResult ] foregroundColor: value [ "Set the value of the foregroundColor option for the widget. Specifies the normal foreground color to use when displaying the widget." self tclEval: '%1 configure -foreground %3' with: self connected with: self container with: value asTkString. self properties at: #foreground put: value ] invokeCallback [ "Generate a synthetic callback" self callback isNil ifFalse: [self callback send] ] label [ "Answer the value of the label option for the widget. Specifies a string to be displayed inside the widget. The way in which the string is displayed depends on the particular widget and may be determined by other options, such as anchor. For windows, this is the title of the window." self properties at: #text ifPresent: [:value | ^value]. self tclEval: '%1 cget -text' with: self connected with: self container. ^self properties at: #text put: self tclResult ] label: value [ "Set the value of the label option for the widget. Specifies a string to be displayed inside the widget. The way in which the string is displayed depends on the particular widget and may be determined by other options, such as anchor. For windows, this is the title of the window." self tclEval: '%1 configure -text %3' with: self connected with: self container with: value asTkString. self properties at: #text put: value ] create [ self create: '-highlightthickness 0 -takefocus 1 -command {callback %1 invokeCallback} -font {%2}' % {self asOop. self class defaultFont} ] setInitialSize [ "Make the Tk placer's status, the receiver's properties and the window status (as returned by winfo) consistent. Occupy the area indicated by the widget itself, at the top left corner" self x: 0 y: 0 ] widgetType [ ^'button' ] ] BPrimitive subclass: BForm [ backgroundColor [ "Answer the value of the backgroundColor option for the widget. Specifies the normal background color to use when displaying the widget." self properties at: #background ifPresent: [:value | ^value]. self tclEval: '%1 cget -background' with: self connected with: self container. ^self properties at: #background put: self tclResult ] backgroundColor: value [ "Set the value of the backgroundColor option for the widget. Specifies the normal background color to use when displaying the widget." self tclEval: '%1 configure -background %3' with: self connected with: self container with: value asTkString. self properties at: #background put: value ] defaultHeight [ "Answer the value of the defaultHeight option for the widget. Specifies the desired height for the form in pixels. If this option is less than or equal to zero then the window will not request any size at all." self properties at: #height ifPresent: [:value | ^value]. self tclEval: '%1 cget -height' with: self connected with: self container. ^self properties at: #height put: self tclResult asNumber ] defaultHeight: value [ "Set the value of the defaultHeight option for the widget. Specifies the desired height for the form in pixels. If this option is less than or equal to zero then the window will not request any size at all." self tclEval: '%1 configure -height %3' with: self connected with: self container with: value printString asTkString. self properties at: #height put: value ] defaultWidth [ "Answer the value of the defaultWidth option for the widget. Specifies the desired width for the form in pixels. If this option is less than or equal to zero then the window will not request any size at all." self properties at: #width ifPresent: [:value | ^value]. self tclEval: '%1 cget -width' with: self connected with: self container. ^self properties at: #width put: self tclResult asNumber ] defaultWidth: value [ "Set the value of the defaultWidth option for the widget. Specifies the desired width for the form in pixels. If this option is less than or equal to zero then the window will not request any size at all." self tclEval: '%1 configure -width %3' with: self connected with: self container with: value printString asTkString. self properties at: #width put: value ] create [ self create: '-highlightthickness 0 -takefocus 0' ] initialize: parentWidget [ super initialize: parentWidget. parentWidget isNil ifFalse: [self backgroundColor: parentWidget backgroundColor] ] widgetType [ ^'frame' ] ] BForm subclass: BContainer [ | side fill | setVerticalLayout: aBoolean [ "Answer whether the container will align the widgets vertically or horizontally. Horizontal alignment means that widgets are packed from left to right, while vertical alignment means that widgets are packed from the top to the bottom of the widget. Widgets that are set to be ``stretched'' will share all the space that is not allocated to non-stretched widgets. The layout of the widget can only be set before the first child is inserted in the widget." children isEmpty ifFalse: [^self error: 'cannot set layout after the first child is created']. fill := aBoolean ifTrue: [' -fill x'] ifFalse: [' -fill y']. side := aBoolean ifTrue: [' -side top'] ifFalse: [' -side left'] ] addChild: child [ "Private - The widget identified by child has been added to the receiver. This method is public not because you can call it, but because it can be useful to override it, not forgetting the call to either the superclass implementation or #basicAddChild:, to perform some initialization on the children just added. Answer the new child." side isNil ifTrue: [self setVerticalLayout: true]. self tclEval: 'pack ' , child container , ' -anchor nw ' , side , fill. ^self basicAddChild: child ] child: child height: value [ ] child: child heightOffset: value [ ] child: child stretch: aBoolean [ | fillMethod | fillMethod := aBoolean ifTrue: [' -expand 1 -fill both'] ifFalse: [' -expand 0 ' , fill]. self tclEval: 'pack ' , child container , fillMethod ] child: child width: value [ ] child: child widthOffset: value [ ] child: child x: value [ ] child: child xOffset: value [ ] child: child y: value [ ] child: child yOffset: value [ ] heightChild: child [ | w | w := self toplevel. Blox idle. w isMapped ifTrue: [self tclEval: 'winfo height ' , child container] ifFalse: [self tclEval: 'winfo reqheight ' , child container]. ^self tclResult asInteger ] setInitialSize [ "Make the Tk placer's status, the receiver's properties and the window status (as returned by winfo) consistent. Occupy the area indicated by the widget itself, at the top left corner" self x: 0 y: 0. "A hack..." self parent isNil ifTrue: [^self]. (self parent isKindOf: BContainer) ifFalse: [self tclEval: 'pack propagate ' , self container , ' 0'] ] widthChild: child [ | w | w := self toplevel. Blox idle. w isMapped ifTrue: [self tclEval: 'winfo width ' , child container] ifFalse: [self tclEval: 'winfo reqwidth ' , child container]. ^self tclResult asInteger ] xChild: child [ ^child xAbsolute ] yChild: child [ ^child yAbsolute ] ] BContainer subclass: BRadioGroup [ | lastValue lastAssignedValue | value [ "Answer the index of the button that is currently selected, 1 being the first button added to the radio button group. 0 means that no button is selected" self tclEval: 'return ${var' , self connected , '}'. ^self tclResult asInteger ] value: value [ "Force the value-th button added to the radio button group to be the selected one." self tclEval: 'set var' , self connected , ' ' , value printString ] initialize: parentWidget [ super initialize: parentWidget. lastAssignedValue := lastValue := 0. self tclEval: 'set ' , self variable , ' 1' ] lastValue [ ^lastValue ] lastValue: value [ lastValue := value ] newButtonValue [ ^lastAssignedValue := lastAssignedValue + 1 ] variable [ ^'var' , self connected ] destroyed [ "Private - The receiver has been destroyed, clear the corresponding Tcl variable to avoid memory leaks." self tclEval: 'unset var' , self connected. super destroyed ] ] BButton subclass: BRadioButton [ | variableValue | callback: aReceiver message: aSymbol [ "Set up so that aReceiver is sent the aSymbol message (the name of a selector accepting at most two arguments) when the receiver is clicked. If the method accepts two arguments, the receiver is passed as the first parameter. If the method accepts one or two arguments, true is passed as the last parameter for interoperability with BToggle widgets." | arguments selector numArgs | selector := aSymbol asSymbol. numArgs := selector numArgs. arguments := #(). numArgs = 1 ifTrue: [arguments := #(true)]. numArgs = 2 ifTrue: [arguments := {self. true}]. callback := DirectedMessage selector: selector arguments: arguments receiver: aReceiver ] value [ "Answer whether this widget is the selected one in its radio button group." ^self parent value = variableValue ] value: aBoolean [ "Answer whether this widget is the selected one in its radio button group. Setting this property to false for a group's currently selected button unhighlights all the buttons in that group." aBoolean ifTrue: [self parent value: variableValue. ^self]. "aBoolean is false - unhighlight everything if we're active" self value ifTrue: [self parent value: 0] ] initialize: parentWidget [ super initialize: parentWidget. variableValue := self parent newButtonValue. self tclEval: self connected , ' configure -anchor nw'; variableValue: variableValue; variable: self parent variable; backgroundColor: parentWidget backgroundColor. variableValue = 1 ifTrue: [self parent value: 1] ] variable: value [ "Set the value of Tk's variable option for the widget." self tclEval: '%1 configure -variable %3' with: self connected with: self container with: value asTkString. self properties at: #variable put: value ] variableValue: value [ "Set the value of Tk's value option for the widget." self tclEval: '%1 configure -value %3' with: self connected with: self container with: value printString asTkString. self properties at: #value put: value ] widgetType [ ^'radiobutton' ] ] BButton subclass: BToggle [ | value variableReturn | callback: aReceiver message: aSymbol [ "Set up so that aReceiver is sent the aSymbol message (the name of a selector accepting at most two arguments) when the receiver is clicked. If the method accepts two arguments, the receiver is passed as the first parameter. If the method accepts one or two arguments, the state of the widget (true if it is selected, false if it is not) is passed as the last parameter." | arguments selector numArgs | selector := aSymbol asSymbol. numArgs := selector numArgs. arguments := #(). numArgs = 1 ifTrue: [arguments := {nil}]. numArgs = 2 ifTrue: [arguments := {self. nil}]. callback := DirectedMessage selector: selector arguments: arguments receiver: aReceiver ] invokeCallback [ "Generate a synthetic callback." self callback isNil ifTrue: [^self]. self callback arguments size > 0 ifTrue: [self callback arguments at: self callback arguments size put: self value]. super invokeCallback ] value [ "Answer whether the button is in a selected (checked) state." self tclEval: 'return ${var' , self connected , '}'. ^self tclResult = '1' ] value: aBoolean [ "Set whether the button is in a selected (checked) state and generates a callback accordingly." aBoolean ifTrue: [self tclEval: 'set var' , self connected , ' 1'] ifFalse: [self tclEval: 'set var' , self connected , ' 0'] ] variable: value [ "Set the value of Tk's variable option for the widget." self tclEval: '%1 configure -variable %3' with: self connected with: self container with: value asTkString. self properties at: #variable put: value ] initialize: parentWidget [ | variable | super initialize: parentWidget. self tclEval: self connected , ' configure -anchor nw'. self tclEval: 'variable var' , self connected. self variable: 'var' , self connected. self backgroundColor: parentWidget backgroundColor ] widgetType [ ^'checkbutton' ] ] BPrimitive subclass: BImage [ BImage class >> downArrow [ "Answer the XPM representation of a 12x12 arrow pointing downwards." ^'/* XPM */ static char * downarrow_xpm[] = { /* width height ncolors chars_per_pixel */ "12 12 2 1", /* colors */ " c None m None s None", "o c black m black", /* pixels */ " ", " ", " ", " ", " ooooooo ", " ooooo ", " ooo ", " o ", " ", " ", " ", " "}; ' ] BImage class >> leftArrow [ "Answer the XPM representation of a 12x12 arrow pointing leftwards." ^'/* XPM */ static char * leftarrow_xpm[] = { /* width height ncolors chars_per_pixel */ "12 12 2 1", /* colors */ " c None m None s None", "o c black m black", /* pixels */ " ", " ", " o ", " oo ", " ooo ", " oooo ", " ooo ", " oo ", " o ", " ", " ", " "}; ' ] BImage class >> upArrow [ "Answer the XPM representation of a 12x12 arrow pointing upwards." ^'/* XPM */ static char * uparrow_xpm[] = { /* width height ncolors chars_per_pixel */ "12 12 2 1", /* colors */ " c None m None s None", "o c black m black", /* pixels */ " ", " ", " ", " ", " o ", " ooo ", " ooooo ", " ooooooo ", " ", " ", " ", " "}; ' ] BImage class >> rightArrow [ "Answer the XPM representation of a 12x12 arrow pointing rightwards." ^'/* XPM */ static char * rightarrow_xpm[] = { /* width height ncolors chars_per_pixel */ "12 12 2 1", /* colors */ " c None m None s None", "o c black m black", /* pixels */ " ", " ", " o ", " oo ", " ooo ", " oooo ", " ooo ", " oo ", " o ", " ", " ", " "}; ' ] BImage class >> gnu [ "Answer the XPM representation of a 48x48 GNU." ^'/* XPM */ /*****************************************************************************/ /* GNU Emacs bitmap conv. to pixmap by Przemek Klosowski (przemek@nist.gov) */ /*****************************************************************************/ static char * image_name [] = { /* width height ncolors chars_per_pixel */ "48 48 7 1", /* colors */ " s mask c none", "B c blue", "x c black", ": c SandyBrown", "+ c SaddleBrown", "o c grey", ". c white", /* pixels */ " ", " x ", " :x ", " :::x ", " ::x ", " x ::x ", " x: xxx :::x ", " x: xxx xxx:xxx x::x ", " x:: xxxx::xxx:::::xx x::x ", " x:: x:::::::xx::::::xx x::x ", " x:: xx::::::::x:::::::xx xx::x ", " x:: xx::::::::::::::::::x xx::xx ", " x::x xx:::::xxx:::::::xxx:xxx xx:::xx ", " x:::x xx:::::xx...xxxxxxxxxxxxxxx:::xx ", " x:::x xx::::::xx..xxx...xxxx...xxxxxxxx ", " x:::x x::::::xx.xxx.......x.x.......xxxx ", " x:::xx x:::x::xx.xx..........x.xx.........x ", " x::::xx::xx:::x.xx....ooooxoxoxoo.xxx.....x ", " xx::::xxxx::xx.xx.xxxx.ooooooo.xxx xxxx ", " xx::::::::xx..x.xxx..ooooooooo.xx ", " xxx:::::xxx..xx.xx.xx.xxx.ooooo.xx ", " xxx::xx...xx.xx.BBBB..xxooooooxx ", " xxxx.....xx.xxBB:BB.xxoooooooxx ", " xx.....xx...x.BBBx.xxxooooooxx ", " x....xxxx..xx...xxxooooooooooxx ", " x..xxxxxx..x.......x..ooooooooxx ", " x.x xxx.x.x.x...xxxx.oooooooooxx ", " x xxx.x.x.xx...xx..oooooooooxx ", " xx.x..x.x.xx........oooooooox ", " xxo.xx.x.x.x.x.......ooooooooox ", " xxo..xxxx..x...x.......ooooooox ", " xxoo.xx.x..xx...x.......ooo.xxx ", " xxoo..x.x.x.x.x.xx.xxxxx.o.xx+xx ", " xxoo..x.xx..xx.x.x.x+++xxxxx+++x ", " xxooo.x..xxx.x.x.x.x+++++xxx+xxx ", " xxoo.xx..x..xx.xxxx++x+++x++xxx ", " xxoo..xx.xxx.xxx.xxx++xx+x++xx ", " xxooo.xx.xx..xx.xxxx++x+++xxx ", " xxooo.xxx.xx.xxxxxxxxx++++xxx ", " xxoo...xx.xx.xxxxxx++xxxxxxx ", " xxoooo..x..xxx..xxxx+++++xx ", " xxoooo..x..xx..xxxx++++xx ", " xxxooooox.xx.xxxxxxxxxxx ", " xxxooooo..xxx xxxxx ", " xxxxooooxxxx ", " xxxoooxxx ", " xxxxx ", " " };' ] BImage class >> exclaim [ "Answer the XPM representation of a 32x32 exclamation mark icon." ^'/* XPM */ static char * exclaim_xpm[] = { /* width height ncolors chars_per_pixel */ "32 32 6 1", /* colors */ " c None m None s None", ". c yellow m white", "X c black m black", "x c gray50 m black", "o c gray m white", "b c yellow4 m black", /* pixels */ " bbb ", " b..oX ", " b....oXx ", " b.....Xxx ", " b......oXxx ", " b.......Xxx ", " b........oXxx ", " b.........Xxx ", " b..........oXxx ", " b...oXXXo...Xxx ", " b....XXXXX...oXxx ", " b....XXXXX....Xxx ", " b.....XXXXX....oXxx ", " b.....XXXXX.....Xxx ", " b......XXXXX.....oXxx ", " b......bXXXb......Xxx ", " b.......oXXXo......oXxx ", " b........XXX........Xxx ", " b.........bXb........oXxx ", " b.........oXo.........Xxx ", " b...........X..........oXxx ", " b.......................Xxx ", " b...........oXXo.........oXxx ", " b...........XXXX..........Xxx ", "b............XXXX..........oXxx ", "b............oXXo...........Xxx ", "b...........................Xxxx", "b..........................oXxxx", " b........................oXxxxx", " bXXXXXXXXXXXXXXXXXXXXXXXXxxxxx", " xxxxxxxxxxxxxxxxxxxxxxxxxxx ", " xxxxxxxxxxxxxxxxxxxxxxxxx "}; ' ] BImage class >> info [ "Answer the XPM representation of a 32x32 `information' icon." ^'/* XPM */ static char * info_xpm[] = { /* width height ncolors chars_per_pixel */ "32 32 6 1", /* colors */ " c None m None s None", ". c white m white", "X c black m black", "x c gray50 m black", "o c gray m white", "b c blue m black", /* pixels */ " xxxxxxxx ", " xxxo......oxxx ", " xxo............oxx ", " xo................ox ", " x.......obbbbo.......X ", " x........bbbbbb........X ", " x.........bbbbbb.........X ", " xo.........obbbbo.........oX ", " x..........................Xx ", "xo..........................oXx ", "x..........bbbbbbb...........Xx ", "x............bbbbb...........Xxx", "x............bbbbb...........Xxx", "x............bbbbb...........Xxx", "x............bbbbb...........Xxx", "xo...........bbbbb..........oXxx", " x...........bbbbb..........Xxxx", " xo..........bbbbb.........oXxxx", " x........bbbbbbbbb.......Xxxx ", " X......................Xxxxx ", " X....................Xxxxx ", " Xo................oXxxxx ", " XXo............oXXxxxx ", " xXXXo......oXXXxxxxx ", " xxxXXXo...Xxxxxxxx ", " xxxxX...Xxxxxx ", " xX...Xxx ", " X..Xxx ", " X.Xxx ", " XXxx ", " xxx ", " xx "}; ' ] BImage class >> question [ "Answer the XPM representation of a 32x32 question mark icon." ^'/* XPM */ static char * question_xpm[] = { /* width height ncolors chars_per_pixel */ "32 32 6 1", /* colors */ " c None m None s None", ". c white m white", "X c black m black", "x c gray50 m black", "o c gray m white", "b c blue m black", /* pixels */ " xxxxxxxx ", " xxxo......oxxx ", " xxo............oxx ", " xo................ox ", " x....................X ", " x.......obbbbbbo.......X ", " x.......obo..bbbbo.......X ", " xo.......bb....bbbb.......oX ", " x........bbbb..bbbb........Xx ", "xo........bbbb.obbbb........oXx ", "x.........obbo.bbbb..........Xx ", "x.............obbb...........Xxx", "x.............bbb............Xxx", "x.............bbo............Xxx", "x.............bb.............Xxx", "xo..........................oXxx", " x...........obbo...........Xxxx", " xo..........bbbb..........oXxxx", " x..........bbbb..........Xxxx ", " X.........obbo.........Xxxxx ", " X....................Xxxxx ", " Xo................oXxxxx ", " XXo............oXXxxxx ", " xXXXo......oXXXxxxxx ", " xxxXXXo...Xxxxxxxx ", " xxxxX...Xxxxxx ", " xX...Xxx ", " X..Xxx ", " X.Xxx ", " XXxx ", " xxx ", " xx "}; ' ] BImage class >> stop [ "Answer the XPM representation of a 32x32 `critical stop' icon." ^'/* XPM */ static char * stop_xpm[] = { /* width height ncolors chars_per_pixel */ "32 32 5 1", /* colors */ " c None m None s None", ". c red m white", "o c DarkRed m black", "X c white m black", "x c gray50 m black", /* pixels */ " oooooooo ", " ooo........ooo ", " o..............o ", " oo................oo ", " o....................o ", " o......................o ", " o......................ox ", " o......X..........X......ox ", " o......XXX........XXX......o ", " o.....XXXXX......XXXXX.....ox ", " o......XXXXX....XXXXX......oxx ", "o........XXXXX..XXXXX........ox ", "o.........XXXXXXXXXX.........ox ", "o..........XXXXXXXX..........oxx", "o...........XXXXXX...........oxx", "o...........XXXXXX...........oxx", "o..........XXXXXXXX..........oxx", "o.........XXXXXXXXXX.........oxx", "o........XXXXX..XXXXX........oxx", " o......XXXXX....XXXXX......oxxx", " o.....XXXXX......XXXXX.....oxxx", " o......XXX........XXX......oxx ", " o......X..........X......oxxx ", " o......................oxxxx ", " o......................oxxx ", " o....................oxxx ", " oo................ooxxxx ", " xo..............oxxxxx ", " xooo........oooxxxxx ", " xxooooooooxxxxxx ", " xxxxxxxxxxxxxx ", " xxxxxxxx "}; ' ] BImage class >> new: parent data: aString [ "Answer a new BImage widget laid inside the given parent widget, loading data from the given string (Base-64 encoded GIF, XPM, PPM are supported)." ^(self new: parent) data: aString; yourself ] BImage class >> new: parent image: aFileStream [ "Answer a new BImage widget laid inside the given parent widget, loading data from the given file (GIF, XPM, PPM are supported)." ^(self new: parent) image: aFileStream; yourself ] BImage class >> new: parent size: aPoint [ "Answer a new BImage widget laid inside the given parent widget, showing by default a transparent image of aPoint size." ^(self new: parent) displayWidth: aPoint x; displayHeight: aPoint y; blank; yourself ] BImage class >> directory [ "Answer the Base-64 GIF representation of a `directory folder' icon." ^'R0lGODdhEAAQAPIAAAAAAHh4eLi4uPj4+P///wAAAAAAAAAAACwAAAAAEAAQAAADPkixzPOD yADrWE8qC8WN0+BZAmBq1GMOqwigXFXCrGk/cxjjr27fLtout6n9eMIYMTXsFZsogXRKJf6u P0kCADv/' ] BImage class >> file [ "Answer the Base-64 GIF representation of a `file' icon." ^'R0lGODdhEAAQAPIAAAAAAHh4eLi4uPj4APj4+P///wAAAAAAACwAAAAAEAAQAAADPVi63P4w LkKCtTTnUsXwQqBtAfh910UU4ugGAEucpgnLNY3Gop7folwNOBOeiEYQ0acDpp6pGAFArVqt hQQAO///' ] backgroundColor [ "Answer the value of the backgroundColor option for the widget. Specifies the normal background color to use when displaying the widget." self properties at: #background ifPresent: [:value | ^value]. self tclEval: '%1 cget -background' with: self connected with: self container. ^self properties at: #background put: self tclResult ] backgroundColor: value [ "Set the value of the backgroundColor option for the widget. Specifies the normal background color to use when displaying the widget." self tclEval: '%1 configure -background %3' with: self connected with: self container with: value asTkString. self properties at: #background put: value ] displayHeight [ "Answer the value of the displayHeight option for the widget. Specifies the height of the image in pixels. This is not the height of the widget, but specifies the area of the widget that will be taken by the image." self properties at: #displayHeight ifPresent: [:value | ^value]. self tclEval: 'img%1 cget -width' with: self connected with: self container. ^self properties at: #displayHeight put: self tclResult asNumber ] displayHeight: value [ "Set the value of the displayHeight option for the widget. Specifies the height of the image in pixels. This is not the height of the widget, but specifies the area of the widget that will be taken by the image." self tclEval: 'img%1 configure -width %3' with: self connected with: self container with: value asFloat printString asTkString. self properties at: #displayHeight put: value ] displayWidth [ "Answer the value of the displayWidth option for the widget. Specifies the width of the image in pixels. This is not the width of the widget, but specifies the area of the widget that will be taken by the image." self properties at: #displayWidth ifPresent: [:value | ^value]. self tclEval: 'img%1 cget -width' with: self connected with: self container. ^self properties at: #displayWidth put: self tclResult asNumber ] displayWidth: value [ "Set the value of the displayWidth option for the widget. Specifies the width of the image in pixels. This is not the width of the widget, but specifies the area of the widget that will be taken by the image." self tclEval: 'img%1 configure -width %3' with: self connected with: self container with: value asFloat printString asTkString. self properties at: #displayWidth put: value ] foregroundColor [ "Answer the value of the foregroundColor option for the widget. Specifies the normal foreground color to use when displaying the widget." self properties at: #foreground ifPresent: [:value | ^value]. self tclEval: '%1 cget -foreground' with: self connected with: self container. ^self properties at: #foreground put: self tclResult ] foregroundColor: value [ "Set the value of the foregroundColor option for the widget. Specifies the normal foreground color to use when displaying the widget." self tclEval: '%1 configure -foreground %3' with: self connected with: self container with: value asTkString. self properties at: #foreground put: value ] gamma [ "Answer the value of the gamma option for the widget. Specifies that the colors allocated for displaying the image widget should be corrected for a non-linear display with the specified gamma exponent value. (The intensity produced by most CRT displays is a power function of the input value, to a good approximation; gamma is the exponent and is typically around 2). The value specified must be greater than zero. The default value is one (no correction). In general, values greater than one will make the image lighter, and values less than one will make it darker." self properties at: #gamma ifPresent: [:value | ^value]. self tclEval: 'img%1 cget -gamma' with: self connected with: self container. ^self properties at: #gamma put: self tclResult asNumber ] gamma: value [ "Set the value of the gamma option for the widget. Specifies that the colors allocated for displaying the image widget should be corrected for a non-linear display with the specified gamma exponent value. (The intensity produced by most CRT displays is a power function of the input value, to a good approximation; gamma is the exponent and is typically around 2). The value specified must be greater than zero. The default value is one (no correction). In general, values greater than one will make the image lighter, and values less than one will make it darker." self tclEval: 'img%1 configure -gamma %3' with: self connected with: self container with: value asFloat printString asTkString. self properties at: #gamma put: value ] blank [ "Blank the corresponding image" self tclEval: 'img' , self connected , ' blank' ] data: aString [ "Set the image to be drawn to aString, which can be a GIF in Base-64 representation or an X pixelmap." self tclEval: 'img' , self connected , ' configure -data ' , aString asTkImageString ] dither [ "Recalculate the dithered image in the window where the image is displayed. The dithering algorithm used in displaying images propagates quantization errors from one pixel to its neighbors. If the image data is supplied in pieces, the dithered image may not be exactly correct. Normally the difference is not noticeable, but if it is a problem, this command can be used to fix it." self tclEval: 'img' , self connected , ' redither' ] fillFrom: origin extent: extent color: color [ "Fill a rectangle with the given origin and extent, using the given color." self fillFrom: origin to: origin + extent color: color ] fillFrom: origin to: corner color: color [ "Fill a rectangle between the given corners, using the given color." self tclEval: 'img%1 put { %2 } -to %3 %4' with: self connected with: color with: origin x printString , ' ' , origin y printString with: corner x printString , ' ' , corner y printString ] fillRectangle: rectangle color: color [ "Fill a rectangle having the given bounding box, using the given color." self fillFrom: rectangle origin to: rectangle corner color: color ] image: aFileStream [ "Read a GIF or XPM image from aFileStream. The whole contents of the file are read, not only from the file position." self tclEval: 'img' , self connected , ' read ' , aFileStream name asTkString ] imageHeight [ "Specifies the height of the image, in pixels. This option is useful primarily in situations where you wish to build up the contents of the image piece by piece. A value of zero (the default) allows the image to expand or shrink vertically to fit the data stored in it." self tclEval: 'image height img' , self connected. ^self tclResult asInteger ] imageWidth [ "Specifies the width of the image, in pixels. This option is useful primarily in situations where you wish to build up the contents of the image piece by piece. A value of zero (the default) allows the image to expand or shrink horizontally to fit the data stored in it." self tclEval: 'image width img' , self connected. ^self tclResult asInteger ] lineFrom: origin extent: extent color: color [ "Draw a line with the given origin and extent, using the given color." self lineFrom: origin to: origin + extent color: color ] lineFrom: origin to: corner color: color [ self notYetImplemented ] lineFrom: origin toX: endX color: color [ "Draw an horizontal line between the given corners, using the given color." self tclEval: 'img%1 put { %2 } -to %3 %4' with: self connected with: color with: origin x printString , ' ' , origin y printString with: endX printString , ' ' , origin y printString ] lineInside: rectangle color: color [ "Draw a line having the given bounding box, using the given color." self lineFrom: rectangle origin to: rectangle corner color: color ] lineFrom: origin toY: endY color: color [ "Draw a vertical line between the given corners, using the given color." self tclEval: 'img%1 put { %2 } -to %3 %4' with: self connected with: color with: origin x printString , ' ' , origin y printString with: origin x printString , ' ' , endY printString ] destroyed [ "Private - The receiver has been destroyed, clear the corresponding Tcl image to avoid memory leaks." primitive isNil ifFalse: [self tclEval: 'image delete img' , self connected]. super destroyed ] create [ self tclEval: 'image create photo img' , self connected. self create: '-anchor nw -image img' , self connected ] setInitialSize [ "Make the Tk placer's status, the receiver's properties and the window status (as returned by winfo) consistent. Occupy the area indicated by the widget itself, at the top left corner" self x: 0 y: 0 ] widgetType [ ^'label' ] ] BViewport subclass: BList [ | labels items callback | add: anObject afterIndex: index [ "Add an element with the given value after another element whose index is contained in the index parameter. The label displayed in the widget is anObject's displayString. Answer anObject." ^self add: nil element: anObject afterIndex: index ] add: aString element: anObject afterIndex: index [ "Add an element with the aString label after another element whose index is contained in the index parameter. This method allows the client to decide autonomously the label that the widget will display. If anObject is nil, then string is used as the element as well. If aString is nil, then the element's displayString is used as the label. Answer anObject or, if it is nil, aString." | elem label | label := aString isNil ifTrue: [anObject displayString] ifFalse: [aString]. elem := anObject isNil ifTrue: [aString] ifFalse: [anObject]. labels isNil ifTrue: [index > 0 ifTrue: [^SystemExceptions.IndexOutOfRange signalOn: self withIndex: index]. labels := OrderedCollection with: label. items := OrderedCollection with: elem] ifFalse: [labels add: label afterIndex: index. items add: elem afterIndex: index]. self tclEval: self connected , ' insert ' , index printString , ' ' , label asTkString. ^elem ] addLast: anObject [ "Add an element with the given value at the end of the listbox. The label displayed in the widget is anObject's displayString. Answer anObject." ^self add: nil element: anObject afterIndex: items size ] addLast: aString element: anObject [ "Add an element with the given value at the end of the listbox. This method allows the client to decide autonomously the label that the widget will display. If anObject is nil, then string is used as the element as well. If aString is nil, then the element's displayString is used as the label. Answer anObject or, if it is nil, aString." ^self add: aString element: anObject afterIndex: items size ] associationAt: anIndex [ "Answer an association whose key is the item at the given position in the listbox and whose value is the label used to display that item." ^(items at: anIndex) -> (labels at: anIndex) ] at: anIndex [ "Answer the element displayed at the given position in the list box." ^items at: anIndex ] backgroundColor [ "Answer the value of the backgroundColor option for the widget. Specifies the normal background color to use when displaying the widget." self properties at: #background ifPresent: [:value | ^value]. self tclEval: '%1 cget -background' with: self connected with: self container. ^self properties at: #background put: self tclResult ] backgroundColor: value [ "Set the value of the backgroundColor option for the widget. Specifies the normal background color to use when displaying the widget." self tclEval: '%1 configure -background %3' with: self connected with: self container with: value asTkString. self properties at: #background put: value ] contents: elementList [ "Set the elements displayed in the listbox, and set the labels to be their displayStrings." | newLabels | newLabels := elementList collect: [:each | each displayString]. ^self contents: newLabels elements: elementList ] contents: stringCollection elements: elementList [ "Set the elements displayed in the listbox to be those in elementList, and set the labels to be the corresponding elements in stringCollection. The two collections must have the same size." | stream | (elementList notNil and: [elementList size ~= stringCollection size]) ifTrue: [^self error: 'label collection must have the same size as element collection']. labels := stringCollection isNil ifTrue: [elementList asOrderedCollection collect: [:each | each displayString]] ifFalse: [stringCollection asOrderedCollection]. items := elementList isNil ifTrue: [labels copy] ifFalse: [elementList asOrderedCollection]. self tclEval: self connected , ' delete 0 end'. stream := WriteStream on: (String new: 1000). stream nextPutAll: self connected; nextPutAll: ' insert 0'. stringCollection do: [:each | stream space. stream nextPutAll: each asTkString]. self tclEval: stream contents ] do: aBlock [ "Iterate over each element of the listbox and pass it to aBlock." items do: aBlock ] elements [ "Answer the collection of objects that represent the elements displayed by the list box." ^items copy ] elements: elementList [ "Set the elements displayed in the listbox, and set the labels to be their displayStrings." | newLabels | newLabels := elementList collect: [:each | each displayString]. ^self contents: newLabels elements: elementList ] font [ "Answer the value of the font option for the widget. Specifies the font to use when drawing text inside the widget. The font can be given as either an X font name or a Blox font description string. X font names are given as many fields, each led by a minus, and each of which can be replaced by an * to indicate a default value is ok: foundry, family, weight, slant, setwidth, addstyle, pixel size, point size (the same as pixel size for historical reasons), horizontal resolution, vertical resolution, spacing, width, charset and character encoding. Blox font description strings have three fields, which must be separated by a space and of which only the first is mandatory: the font family, the font size in points (or in pixels if a negative value is supplied), and a number of styles separated by a space (valid styles are normal, bold, italic, underline and overstrike). Examples of valid fonts are ``Helvetica 10 Bold'', ``Times -14'', ``Futura Bold Underline''. You must enclose the font family in braces if it is made of two or more words." self properties at: #font ifPresent: [:value | ^value]. self tclEval: '%1 cget -font' with: self connected with: self container. ^self properties at: #font put: self tclResult ] font: value [ "Set the value of the font option for the widget. Specifies the font to use when drawing text inside the widget. The font can be given as either an X font name or a Blox font description string. X font names are given as many fields, each led by a minus, and each of which can be replaced by an * to indicate a default value is ok: foundry, family, weight, slant, setwidth, addstyle, pixel size, point size (the same as pixel size for historical reasons), horizontal resolution, vertical resolution, spacing, width, charset and character encoding. Blox font description strings have three fields, which must be separated by a space and of which only the first is mandatory: the font family, the font size in points (or in pixels if a negative value is supplied), and a number of styles separated by a space (valid styles are normal, bold, italic, underline and overstrike). Examples of valid fonts are ``Helvetica 10 Bold'', ``Times -14'', ``Futura Bold Underline''. You must enclose the font family in braces if it is made of two or more words." self tclEval: '%1 configure -font %3' with: self connected with: self container with: value asTkString. self properties at: #font put: value ] foregroundColor [ "Answer the value of the foregroundColor option for the widget. Specifies the normal foreground color to use when displaying the widget." self properties at: #foreground ifPresent: [:value | ^value]. self tclEval: '%1 cget -foreground' with: self connected with: self container. ^self properties at: #foreground put: self tclResult ] foregroundColor: value [ "Set the value of the foregroundColor option for the widget. Specifies the normal foreground color to use when displaying the widget." self tclEval: '%1 configure -foreground %3' with: self connected with: self container with: value asTkString. self properties at: #foreground put: value ] highlightBackground [ "Answer the value of the highlightBackground option for the widget. Specifies the background color to use when displaying selected items in the widget." self properties at: #selectbackground ifPresent: [:value | ^value]. self tclEval: '%1 cget -selectbackground' with: self connected with: self container. ^self properties at: #selectbackground put: self tclResult ] highlightBackground: value [ "Set the value of the highlightBackground option for the widget. Specifies the background color to use when displaying selected items in the widget." self tclEval: '%1 configure -selectbackground %3' with: self connected with: self container with: value asTkString. self properties at: #selectbackground put: value ] highlightForeground [ "Answer the value of the highlightForeground option for the widget. Specifies the foreground color to use when displaying selected items in the widget." self properties at: #selectforeground ifPresent: [:value | ^value]. self tclEval: '%1 cget -selectforeground' with: self connected with: self container. ^self properties at: #selectforeground put: self tclResult ] highlightForeground: value [ "Set the value of the highlightForeground option for the widget. Specifies the foreground color to use when displaying selected items in the widget." self tclEval: '%1 configure -selectforeground %3' with: self connected with: self container with: value asTkString. self properties at: #selectforeground put: value ] index [ "Answer the value of the index option for the widget. Indicates the element that has the location cursor. This item will be displayed in the highlightForeground color, and with the corresponding background color." self properties at: #index ifPresent: [:value | ^value]. self tclEval: '%1 index active' with: self connected with: self container. ^self properties at: #index put: self tclResult asInteger ] indexAt: point [ "Answer the index of the element that covers the point in the listbox window specified by x and y (in pixel coordinates). If no element covers that point, then the closest element to that point is used." self tclEval: self connected , ' index @%1,%2' with: point x printString with: point y printString. ^self tclResult asInteger + 1 ] isSelected: index [ "Answer whether the element indicated by index is currently selected." self tclEval: self connected , ' selection includes ' , index printString. ^self tclResult = '1' ] label [ "Return nil, it is here for Gtk+ support" ^nil ] label: aString [ "Do nothing, it is here for Gtk+ support" ] labelAt: anIndex [ "Answer the label displayed at the given position in the list box." ^labels at: anIndex ] labels [ "Answer the labels displayed by the list box." ^labels copy ] labelsDo: aBlock [ "Iterate over each listbox element's label and pass it to aBlock." labels do: aBlock ] mode [ "Answer the value of the mode option for the widget. Specifies one of several styles for manipulating the selection. The value of the option may be either single, browse, multiple, or extended. If the selection mode is single or browse, at most one element can be selected in the listbox at once. Clicking button 1 on an unselected element selects it and deselects any other selected item, while clicking on a selected element has no effect. In browse mode it is also possible to drag the selection with button 1. That is, moving the mouse while button 1 is pressed keeps the item under the cursor selected. If the selection mode is multiple or extended, any number of elements may be selected at once, including discontiguous ranges. In multiple mode, clicking button 1 on an element toggles its selection state without affecting any other elements. In extended mode, pressing button 1 on an element selects it, deselects everything else, and sets the anchor to the element under the mouse; dragging the mouse with button 1 down extends the selection to include all the elements between the anchor and the element under the mouse, inclusive. In extended mode, the selected range can be adjusted by pressing button 1 with the Shift key down: this modifies the selection to consist of the elements between the anchor and the element under the mouse, inclusive. The un-anchored end of this new selection can also be dragged with the button down. Also in extended mode, pressing button 1 with the Control key down starts a toggle operation: the anchor is set to the element under the mouse, and its selection state is reversed. The selection state of other elements is not changed. If the mouse is dragged with button 1 down, then the selection state of all elements between the anchor and the element under the mouse is set to match that of the anchor element; the selection state of all other elements remains what it was before the toggle operation began. Most people will probably want to use browse mode for single selections and extended mode for multiple selections; the other modes appear to be useful only in special situations." self properties at: #selectmode ifPresent: [:value | ^value]. self tclEval: '%1 cget -selectmode' with: self connected with: self container. ^self properties at: #selectmode put: self tclResult asSymbol ] mode: value [ "Set the value of the mode option for the widget. Specifies one of several styles for manipulating the selection. The value of the option may be either single, browse, multiple, or extended. If the selection mode is single or browse, at most one element can be selected in the listbox at once. Clicking button 1 on an unselected element selects it and deselects any other selected item, while clicking on a selected element has no effect. In browse mode it is also possible to drag the selection with button 1. That is, moving the mouse while button 1 is pressed keeps the item under the cursor selected. If the selection mode is multiple or extended, any number of elements may be selected at once, including discontiguous ranges. In multiple mode, clicking button 1 on an element toggles its selection state without affecting any other elements. In extended mode, pressing button 1 on an element selects it, deselects everything else, and sets the anchor to the element under the mouse; dragging the mouse with button 1 down extends the selection to include all the elements between the anchor and the element under the mouse, inclusive. In extended mode, the selected range can be adjusted by pressing button 1 with the Shift key down: this modifies the selection to consist of the elements between the anchor and the element under the mouse, inclusive. The un-anchored end of this new selection can also be dragged with the button down. Also in extended mode, pressing button 1 with the Control key down starts a toggle operation: the anchor is set to the element under the mouse, and its selection state is reversed. The selection state of other elements is not changed. If the mouse is dragged with button 1 down, then the selection state of all elements between the anchor and the element under the mouse is set to match that of the anchor element; the selection state of all other elements remains what it was before the toggle operation began. Most people will probably want to use browse mode for single selections and extended mode for multiple selections; the other modes appear to be useful only in special situations." self tclEval: '%1 configure -selectmode %3' with: self connected with: self container with: value asTkString. self properties at: #selectmode put: value ] numberOfStrings [ "Answer the number of items in the list box" ^labels size ] removeAtIndex: index [ "Remove the item at the given index in the list box, answering the object associated to the element (i.e. the value that #at: would have returned for the given index)" | result | labels removeAtIndex: index. result := items removeAtIndex: index. self tclEval: self connected , 'delete ' , index printString. ^result ] size [ "Answer the number of items in the list box" ^labels size ] itemSelected: receiver at: index [ stdout nextPutAll: 'List item '; print: index; nextPutAll: ' selected!'; nl. stdout nextPutAll: 'Contents: '; nextPutAll: (items at: index); nl ] create [ self create: '-highlightthickness 0 -takefocus 1 \ -exportselection no -font {' , self class defaultFont , '}'; horizontal: true; vertical: true. "Tcl hack to get the callback upon activate. See analogous trick for text boxes in BText>>#initialize:." self tclEval: ' rename %1 .%1 bind %1 <> { callback %2 invokeCallback: [%1 index active] } proc %1 args { if [regexp {^activate} [lindex $args 0]] { callback %2 invokeCallback: [%1 index [lindex $args 1]] } uplevel .%1 $args }' with: self connected with: self asOop printString ] initialize: parentWidget [ super initialize: parentWidget. self properties at: #index put: nil. labels := OrderedCollection new ] invokeCallback: indexString [ | index | items isNil ifTrue: [^self]. index := indexString asInteger. self properties at: #index put: index + 1. self invokeCallback ] widgetType [ ^'listbox' ] callback [ "Answer a DirectedMessage that is sent when the active item in the receiver changes, or nil if none has been set up." ^callback ] callback: aReceiver message: aSymbol [ "Set up so that aReceiver is sent the aSymbol message (the name of a selector with at most two arguemtnts) when the active item in the receiver changegs. If the method accepts two arguments, the receiver is passed as the first parameter. If the method accepts one or two arguments, the selected index is passed as the last parameter." | arguments selector numArgs | selector := aSymbol asSymbol. numArgs := selector numArgs. arguments := #(). numArgs = 1 ifTrue: [arguments := {nil}]. numArgs = 2 ifTrue: [arguments := {self. nil}]. callback := DirectedMessage selector: selector arguments: arguments receiver: aReceiver ] highlight: index [ "Highlight the item at the given position in the listbox." index = self index ifTrue: [^self]. (self mode = #single or: [self mode = #browse]) ifTrue: [self unhighlight]. self select: index ] invokeCallback [ "Generate a synthetic callback." self callback notNil ifTrue: [self callback arguments isEmpty ifFalse: [self callback arguments at: self callback arguments size put: (self properties at: #index)]. self callback send] ] select: index [ "Highlight the item at the given position in the listbox, without unhighlighting other items. This is meant for multiple- or extended-mode listboxes, but can be used with other selection mode in particular cases." self properties at: #index put: index. self tclEval: '%1 selection set %2 %1 activate %2 %1 see %2' with: self connected with: (index - 1) printString ] show: index [ "Ensure that the item at the given position in the listbox is visible." self tclEval: self connected , ' see ' , (index - 1) printString ] unhighlight [ "Unhighlight all the items in the listbox." self tclEval: self connected , ' selection clear 0 end' ] unselect: index [ "Unhighlight the item at the given position in the listbox, without affecting the state of the other items." self tclEval: self connected , ' selection clear ' , (index - 1) printString ] ] BForm subclass: BWindow [ | isMapped callback x y width height | '> TopLevel := nil. Grab := nil. BWindow class >> initializeOnStartup [ self tclEval: 'wm withdraw .'. TopLevel := OrderedCollection new. Grab := nil ] BWindow class >> new [ "Answer a new top-level window." ^TopLevel add: (super new: nil) ] BWindow class >> new: label [ "Answer a new top-level window with `label' as its title bar caption." ^self new label: label ] BWindow class >> popup: initializationBlock [ self shouldNotImplement ] callback [ "Answer a DirectedMessage that is sent to verify whether the receiver must be destroyed when the user asks to unmap it." ^callback ] callback: aReceiver message: aSymbol [ "Set up so that aReceiver is sent the aSymbol message (the name of a zero- or one-argument selector) when the user asks to unmap the receiver. If the method accepts an argument, the receiver is passed. If the method returns true, the window and its children are destroyed (which is the default action, taken if no callback is set up). If the method returns false, the window is left in place." | arguments selector numArgs | selector := aSymbol asSymbol. numArgs := selector numArgs. arguments := #(). numArgs = 1 ifTrue: [arguments := Array with: self]. callback := DirectedMessage selector: selector arguments: arguments receiver: aReceiver ] invokeCallback [ "Generate a synthetic callback, destroying the window if no callback was set up or if the callback method answers true." | result | result := self callback isNil or: [self callback send]. result ifTrue: [self destroy]. isMapped := result not ] label [ "Answer the value of the label option for the widget. Specifies a string to be displayed inside the widget. The way in which the string is displayed depends on the particular widget and may be determined by other options, such as anchor. For windows, this is the title of the window." self properties at: #label ifPresent: [:value | ^value]. self tclEval: 'wm title %1' with: self connected with: self container. ^self properties at: #label put: self tclResult ] label: value [ "Set the value of the label option for the widget. Specifies a string to be displayed inside the widget. The way in which the string is displayed depends on the particular widget and may be determined by other options, such as anchor. For windows, this is the title of the window." self tclEval: 'wm title %1 %3' with: self connected with: self container with: value asTkString. self properties at: #label put: value ] menu: value [ "Set the value of the menu option for the widget. Specifies a menu widget to be used as a menubar. On the Macintosh, the menubar will be displayed accross the top of the main monitor. On Microsoft Windows and all UNIX platforms, the menu will appear accross the toplevel window as part of the window dressing maintained by the window manager." self tclEval: '%1 configure -menu %3' with: self connected with: self container with: value container asTkString. self properties at: #menu put: value ] resizable [ "Answer the value of the resizable option for the widget. Answer whether the user can be resize the window or not. If resizing is disabled, then the window's size will be the size from the most recent interactive resize or geometry-setting method. If there has been no such operation then the window's natural size will be used." self properties at: #resizable ifPresent: [:value | ^value]. self tclEval: 'wm resizable %1' with: self connected with: self container. ^self properties at: #resizable put: self tclResult = '{1 1}' ] resizable: value [ "Set the value of the resizable option for the widget. Answer whether the user can be resize the window or not. If resizing is disabled, then the window's size will be the size from the most recent interactive resize or geometry-setting method. If there has been no such operation then the window's natural size will be used." self tclEval: 'wm resizable %1 %3 %3' with: self connected with: self container with: value asCBooleanValue printString asTkString. self properties at: #resizable put: value ] cacheWindowSize [ | stream | self tclEval: 'update; wm geometry ' , self container. stream := ReadStream on: self tclResult. width := (stream upTo: $x) asInteger. height := (stream upTo: $+) asInteger. x := (stream upTo: $+) asInteger. y := stream upToEnd asInteger ] create [ self create: '-takefocus 0' ] create: options [ super create: options. self isMapped: false. self bind: '' to: #resized of: self parameters: ''. self tclEval: ' wm withdraw %1 wm protocol %1 WM_DELETE_WINDOW { callback %2 invokeCallback }' with: self connected with: self asOop printString ] destroyed [ "Private - The receiver has been destroyed, remove it from the list of toplevel windows to avoid memory leaks." super destroyed. TopLevel remove: self ifAbsent: [] ] isMapped: aBoolean [ isMapped := aBoolean ] resetGeometry: pattern x: xPos y: yPos width: xSize height: ySize [ | s mapped | (x = xPos and: [y = yPos and: [width = xSize and: [height = ySize]]]) ifTrue: [^self]. s := WriteStream on: (String new: 50). (mapped := self isMapped) ifTrue: [s nextPutAll: 'wm withdraw ' , self connected; nl. self isMapped: false]. s nextPutAll: 'wm geometry '; nextPutAll: self connected; space; nextPutAll: pattern; nl; nextPutAll: 'update'. self tclEval: s contents with: xSize printString with: ySize printString with: xPos printString with: yPos printString. x := xPos. y := yPos. width := xSize. height := ySize. mapped ifTrue: [self map] ] resized [ self isMapped ifFalse: [^self]. x := y := width := height := nil ] setInitialSize [ self x: 20 y: 20 width: 300 height: 300 ] widgetType [ ^'toplevel' ] center [ "Center the window in the screen" | screenSize | screenSize := Blox screenSize. self x: screenSize x // 2 - (self width // 2) y: screenSize y // 2 - (self height // 2) ] centerIn: view [ "Center the window in the given widget" self x: view x + (view width // 2) - (self parent width // 2) y: view x + (view height // 2) - (self parent height // 2) ] height [ "Answer the height of the window, as deduced from the geometry that the window manager imposed on the window." height isNil ifTrue: [self cacheWindowSize]. ^height ] height: anInteger [ "Ask the window manager to give the given height to the window." width isNil ifTrue: [self cacheWindowSize]. self resetGeometry: '=%1x%2' x: x y: y width: width height: anInteger ] heightAbsolute [ "Answer the height of the window, as deduced from the geometry that the window manager imposed on the window." height isNil ifTrue: [self cacheWindowSize]. ^height ] heightOffset: value [ self shouldNotImplement ] iconify [ "Map a window and in iconified state. If a window has not been mapped yet, this is achieved by mapping the window in withdrawn state first, and then iconifying it." self isMapped ifFalse: [self tclEval: 'wm withdraw ' , self connected]. self tclEval: 'wm iconify ' , self connected. self isMapped: false ] isMapped [ "Answer whether the window is mapped" ^isMapped ] isWindow [ ^true ] map [ "Map the window and bring it to the topmost position in the Z-order." self isMapped ifTrue: [^self]. self tclEval: ' wm deiconify %1 focus [ tk_focusNext %1 ]' with: self container. self isMapped: true ] modalMap [ "Map the window while establishing an application-local grab for it. An event loop is started that ends only after the window has been destroyed. When a grab is set for a particular window, all pointer events are restructed to the grab window and its descendants in Blox's window hierarchy. Whenever the pointer is within the grab window's subtree, the pointer will behave exactly the same as if there had been no grab grab at all and all events will be reported in the normal fashion. When the pointer is outside the window's tree, button presses and releases and mouse motion events are reported to the grabbing window, and window entry and window exit events are ignored. In other words, windows outside the grab subtree will be visible on the screen but they will be insensitive until the grab is released. The tree of windows underneath the grab window can include top-level windows, in which case all of those top-level windows and their descendants will continue to receive mouse events during the grab. Keyboard events (key presses and key releases) are delivered as usual: the window manager controls which application receives keyboard events, and if they are sent to any window in the grabbing application then they are redirected to the window owning the focus." | previousGrab terminate | previousGrab := Grab. Grab := self connected. self map; tclEval: 'grab set ' , Grab. Blox dispatchEvents: self. previousGrab isNil ifTrue: [self tclEval: 'grab release ' , Grab] ifFalse: [self tclEval: 'grab set ' , previousGrab]. Grab := previousGrab ] state [ "Set the value of the state option for the window. Specifies one of four states for the window: either normal, iconic, withdrawn, or (Windows only) zoomed." self tclEval: 'wm state ' , self connected. ^self tclResult asSymbol ] state: aSymbol [ "Raise an error. To set a BWindow's state, use #map and #unmap." self error: 'To set a BWindow''s state, use #map and #unmap.' ] unmap [ "Unmap a window, causing it to be forgotten about by the window manager" self isMapped ifFalse: [^self]. self tclEval: 'wm withdraw ' , self connected. self isMapped: false ] width [ "Answer the width of the window, as deduced from the geometry that the window manager imposed on the window." width isNil ifTrue: [self cacheWindowSize]. ^width ] width: anInteger [ "Ask the window manager to give the given width to the window." height isNil ifTrue: [self cacheWindowSize]. self resetGeometry: '=%1x%2' x: x y: y width: anInteger height: height ] width: xSize height: ySize [ "Ask the window manager to give the given width and height to the window." self resetGeometry: '=%1x%2' x: x y: y width: xSize height: ySize ] widthAbsolute [ "Answer the width of the window, as deduced from the geometry that the window manager imposed on the window." width isNil ifTrue: [self cacheWindowSize]. ^width ] widthOffset: value [ self shouldNotImplement ] window [ ^self ] x [ "Answer the x coordinate of the window's top-left corner, as deduced from the geometry that the window manager imposed on the window." x isNil ifTrue: [self cacheWindowSize]. ^x ] x: anInteger [ "Ask the window manager to move the window's left border to the given x coordinate, keeping the size unchanged" y isNil ifTrue: [self cacheWindowSize]. self resetGeometry: '+%3+%4' x: anInteger y: y width: width height: height ] x: xPos y: yPos [ "Ask the window manager to move the window's top-left corner to the given coordinates, keeping the size unchanged" self resetGeometry: '+%3+%4' x: xPos y: yPos width: width height: height ] x: xPos y: yPos width: xSize height: ySize [ "Ask the window manager to give the requested geometry to the window." self resetGeometry: '=%1x%2+%3+%4' x: xPos y: yPos width: xSize height: ySize ] xAbsolute [ "Answer the x coordinate of the window's top-left corner, as deduced from the geometry that the window manager imposed on the window." x isNil ifTrue: [self cacheWindowSize]. ^x ] xOffset: value [ self shouldNotImplement ] y [ "Answer the y coordinate of the window's top-left corner, as deduced from the geometry that the window manager imposed on the window." y isNil ifTrue: [self cacheWindowSize]. ^y ] y: anInteger [ "Ask the window manager to move the window's left border to the given y coordinate, keeping the size unchanged" x isNil ifTrue: [self cacheWindowSize]. self resetGeometry: '+%3+%4' x: x y: anInteger width: width height: height ] yAbsolute [ "Answer the y coordinate of the window's top-left corner, as deduced from the geometry that the window manager imposed on the window." y isNil ifTrue: [self cacheWindowSize]. ^y ] yOffset: value [ self shouldNotImplement ] ] BWindow subclass: BTransientWindow [ BTransientWindow class >> new [ self shouldNotImplement ] BTransientWindow class >> new: parentWindow [ "Answer a new transient window attached to the given parent window and with nothing in its title bar caption." ^(self basicNew) initialize: parentWindow; yourself ] BTransientWindow class >> new: label in: parentWindow [ "Answer a new transient window attached to the given parent window and with `label' as its title bar caption." ^(self basicNew) initialize: parentWindow; label: label; yourself ] setWidgetName: parentWidget [ | unique | unique := '.w' , (self asOop printString: 36). parentWidget isNil ifTrue: [^unique]. ^parentWidget parent isNil ifTrue: [unique] ifFalse: [parentWidget parent container , unique] ] map [ "Map the window and inform the windows manager that the receiver is a transient window working on behalf of its parent. The window is also put in its parent window's window group: the window manager might use this information, for example, to unmap all of the windows in a group when the group's leader is iconified." super map. self parent isNil ifTrue: [^self]. self tclEval: 'wm transient ' , self connected , ' ' , self parent connected. self tclEval: 'wm group ' , self connected , ' ' , self parent connected ] ] BWindow subclass: BPopupWindow [ addChild: w [ "Private - The widget identified by child has been added to the receiver. This method is public not because you can call it, but because it can be useful to override it, not forgetting the call to either the superclass implementation or #basicAddChild:, to perform some initialization on the children just added. Answer the new child." self tclEval: 'place forget ' , w container. self tclEval: 'pack ' , w container , ' -fill both -side left -padx 1 -pady 1'. w onDestroySend: #destroy to: self. ^self basicAddChild: w ] child: child height: value [ "Set the given child's height. This is done by setting its parent window's (that is, our) height." "Only act after #addChild:" self childrenCount = 0 ifTrue: [^self]. self tclEval: 'pack ' , child container , ' -expand 1'. self height: value ] child: child heightOffset: value [ self shouldNotImplement ] child: child width: value [ "Set the given child's width. This is done by setting its parent window's (that is, our) width." "Only act after #addChild:" self childrenCount = 0 ifTrue: [^self]. self tclEval: 'pack ' , child container , ' -expand 1'. self width: value ] child: child widthOffset: value [ self shouldNotImplement ] child: child x: value [ "Set the x coordinate of the given child's top-left corner. This is done by setting its parent window's (that is, our) x." self x: value ] child: child xOffset: value [ self shouldNotImplement ] child: child y: value [ "Set the y coordinate of the given child's top-left corner. This is done by setting its parent window's (that is, our) y." self y: value ] child: child yOffset: value [ self shouldNotImplement ] heightChild: child [ "Answer the given child's height, which is the height that was imposed on the popup window." ^self height ] widthChild: child [ "Answer the given child's width in pixels, which is the width that was imposed on the popup window." ^self width ] xChild: child [ "Answer the x coordinate of the given child's top-left corner, which is desumed by the position of the popup window." ^self x ] yChild: child [ "Answer the y coordinate of the given child's top-left corner, which is desumed by the position of the popup window." ^self y ] create [ self create: '-takefocus 0 -background black'; tclEval: 'wm overrideredirect ' , self connected , ' 1'; resizable: false ] setInitialSize [ self cacheWindowSize ] ] BForm subclass: BDialog [ | callbacks initInfo | BDialog class >> new: parent [ "Answer a new dialog handler (containing a label widget and some button widgets) laid out within the given parent window. The label widget, when it is created, is empty." ^(self basicNew) initInfo: '' -> nil; initialize: parent ] BDialog class >> new: parent label: aLabel [ "Answer a new dialog handler (containing a label widget and some button widgets) laid out within the given parent window. The label widget, when it is created, contains aLabel." ^(self basicNew) initInfo: aLabel -> nil; initialize: parent ] BDialog class >> new: parent label: aLabel prompt: aString [ "Answer a new dialog handler (containing a label widget, some button widgets, and an edit window showing aString by default) laid out within the given parent window. The label widget, when it is created, contains aLabel." ^(self basicNew) initInfo: aLabel -> aString; initialize: parent ] BDialog class >> chooseFile: operation parent: parent label: aLabel default: name defaultExtension: ext types: typeList [ | stream strictMotif file | stream := WriteStream on: String new. stream nextPutAll: 'tk_get'; nextPutAll: operation; nextPutAll: 'File -parent '; nextPutAll: parent container; nextPutAll: ' -title '; nextPutAll: aLabel asTkString; nextPutAll: ' -defaultextension '; nextPutAll: ext asTkString; nextPutAll: ' -filetypes {'. typeList do: [:each | stream nextPut: ${; nextPutAll: (each at: 1) asTkString; nextPutAll: ' {'. each size > 1 ifTrue: [each from: 2 to: each size do: [:type | stream nextPutAll: type; space]]. stream nextPutAll: '}} ']. stream nextPutAll: '{"All files" * }}'. (name notNil and: [name notEmpty]) ifTrue: [stream nextPutAll: ' -initialfile '; nextPutAll: name asTkString]. strictMotif := BText emacsLike. BText emacsLike: Blox platform ~= 'unix'. parent map. self tclEval: stream contents. file := self tclResult. file isEmpty ifTrue: [file := nil]. BText emacsLike: strictMotif. ^file ] BDialog class >> chooseColor: parent label: aLabel default: color [ "Prompt for a color. The dialog box is created with the given parent window and with aLabel as its title bar text, and initially it selects the color given in the color parameter. If the dialog box is canceled, nil is answered, else the selected color is returned as a String with its RGB value." | result | parent map. self tclEval: 'tk_chooseColor -parent %1 -title %2 -initialcolor %3' with: parent container with: aLabel asTkString with: color asTkString. result := self tclResult. result isEmpty ifTrue: [result := nil]. ^result ] BDialog class >> chooseFileToOpen: parent label: aLabel default: name defaultExtension: ext types: typeList [ "Pop up a dialog box for the user to select a file to open. Its purpose is for the user to select an existing file only. If the user enters an non-existent file, the dialog box gives the user an error prompt and requires the user to give an alternative selection or to cancel the selection. If an application allows the user to create new files, it should do so by providing a separate New menu command. If the dialog box is canceled, nil is answered, else the selected file name is returned as a String. The dialog box is created with the given parent window and with aLabel as its title bar text. The name parameter indicates which file is initially selected, and the default extension specifies a string that will be appended to the filename if the user enters a filename without an extension. The typeList parameter is an array of arrays, like #(('Text files' '.txt' '.diz') ('Smalltalk files' '.st')), and is used to construct a listbox of file types. When the user chooses a file type in the listbox, only the files of that type are listed. Each item in the array contains a list of strings: the first one is the name of the file type described by a particular file pattern, and is the text string that appears in the File types listbox, while the other ones are the possible extensions that belong to this particular file type." "e.g. fileName := BDialog chooseFileToOpen: aWindow label: 'Open file' default: nil defaultExtension: 'gif' types: #( ('Text files' '.txt' '.diz') ('Smalltalk files' '.st') ('C source files' '.c') ('GIF files' '.gif'))" ^self chooseFile: 'Open' parent: parent label: aLabel default: name defaultExtension: ext types: typeList ] BDialog class >> chooseFileToSave: parent label: aLabel default: name defaultExtension: ext types: typeList [ "Pop up a dialog box for the user to select a file to save; this differs from the file open dialog box in that non-existent file names are accepted and existing file names trigger a confirmation dialog box, asking the user whether the file should be overwritten or not. If the dialog box is canceled, nil is answered, else the selected file name is returned as a String. The dialog box is created with the given parent window and with aLabel as its title bar text. The name parameter indicates which file is initially selected, and the default extension specifies a string that will be appended to the filename if the user enters a filename without an extension. The typeList parameter is an array of arrays, like #(('Text files' '.txt' '.diz') ('Smalltalk files' '.st')), and is used to construct a listbox of file types. When the user chooses a file type in the listbox, only the files of that type are listed. Each item in the array contains a list of strings: the first one is the name of the file type described by a particular file pattern, and is the text string that appears in the File types listbox, while the other ones are the possible extensions that belong to this particular file type." ^self chooseFile: 'Save' parent: parent label: aLabel default: name defaultExtension: ext types: typeList ] addButton: aLabel receiver: anObject index: anInt [ "Add a button to the dialog box that, when clicked, will cause the #dispatch: method to be triggered in anObject, passing anInt as the argument of the callback. The caption of the button is set to aLabel." ^self addButton: aLabel receiver: anObject message: #dispatch: argument: anInt ] addButton: aLabel receiver: anObject message: aSymbol [ "Add a button to the dialog box that, when clicked, will cause the aSymbol unary selector to be sent to anObject. The caption of the button is set to aLabel." callbacks addLast: (DirectedMessage selector: aSymbol arguments: #() receiver: anObject). self addButton: aLabel ] addButton: aLabel receiver: anObject message: aSymbol argument: arg [ "Add a button to the dialog box that, when clicked, will cause the aSymbol one-argument selector to be sent to anObject, passing arg as the argument of the callback. The caption of the button is set to aLabel." callbacks addLast: (DirectedMessage selector: aSymbol arguments: {arg} receiver: anObject). self addButton: aLabel ] contents: newText [ "Display newText in the entry widget associated to the dialog box." self tclEval: 'set var' , self connected , ' ' , newText asTkString ] contents [ "Answer the text that is displayed in the entry widget associated to the dialog box." self tclEval: 'return ${var' , self connected , '}'. ^self tclResult ] addButton: aLabel [ self tclEval: 'button %1.buttons.b%2 -text %3 -highlightthickness 0 -takefocus 1 -command { callback %4 "invokeCallback:" %2 destroy %1 } pack %1.buttons.b%2 -side left -expand 1' with: self container with: callbacks size printString with: aLabel asTkString with: self asOop printString ] create [ super create. self tclEval: ' label %1.msg -padx 5 -pady 5 -anchor nw -text ' , initInfo key asTkString , ' place %1.msg -x 0.0 -y 0.0 -relwidth 1.0 bind %1.msg { %1.msg configure -wraplength %%w } %1.msg configure -background [ %1 cget -background ] frame %1.buttons -highlightthickness 0 -takefocus 0 %1.buttons configure -background [ %1 cget -background ] place %1.buttons -anchor sw -x 0.0 -rely 1.0 -relwidth 1.0 -height 14m lower %1.buttons lower %1.msg' with: self connected. initInfo value isNil ifTrue: [^self]. self tclEval: ' set var%1 %2 entry %1.text -textvariable var%1 -highlightthickness 0 -takefocus 1 place %1.text -in %1.msg -x 5 -y 5 -width -10 -rely 1.0 -relwidth 1.0 raise %1.text' with: self connected with: initInfo value asTkString ] initInfo: assoc [ initInfo := assoc ] initialize: parentWidget [ super initialize: parentWidget. callbacks := OrderedCollection new ] center [ "Center the dialog box's parent window in the screen" self parent center ] centerIn: view [ "Center the dialog box's parent window in the given widget" self parent centerIn: view ] destroyed [ "Private - The receiver has been destroyed, clear the corresponding Tcl variable to avoid memory leaks." self tclEval: 'catch { unset var' , self connected , '}'. super destroyed ] invokeCallback: index [ "Generate a synthetic callback corresponding to the index-th button being pressed, and destroy the parent window (triggering its callback if one was established)." (callbacks at: index asInteger) send. self parent destroy ] loop [ "Map the parent window modally. In other words, an event loop is started that ends only after the window has been destroyed. For more information on the treatment of events for modal windows, refer to BWindow>>#modalMap." "self parent width: (self parent width min: 200)." self parent modalMap ] ] BMenuObject subclass: BMenuBar [ add: aMenu [ "Add aMenu to the menu bar" aMenu create. ^self addChild: aMenu ] remove: aMenu [ "Remove aMenu from the menu bar" self tclEval: 'catch { %1 delete %2 }' with: self connected with: aMenu connected ] connected [ ^primitive ] container [ ^primitive ] initialize: parentWidget [ super initialize: parentWidget. primitive := self parent isNil ifTrue: ['.popup'] ifFalse: [self parent container , '.menu']. "BMenuBar is NOT a BPrimitive, so it has to explicitly create itself" self tclEval: 'menu ' , self connected , ' -font {' , self class defaultFont , '} -tearoff 0'. self parent isNil ifFalse: [self parent menu: self] ] ] BMenuObject subclass: BMenu [ | label exists | BMenu class >> new: parent label: label [ "Add a new menu to the parent window's menu bar, with `label' as its caption (for popup menus, parent is the widget over which the menu pops up as the right button is pressed)." ^(self basicNew) initialize: parent; label: label; yourself ] label [ "Answer the value of the label option for the widget. Specifies a string to be displayed inside the widget. The way in which the string is displayed depends on the particular widget and may be determined by other options, such as anchor. For windows, this is the title of the window." ^label ] label: value [ "Set the value of the label option for the widget. Specifies a string to be displayed inside the widget. The way in which the string is displayed depends on the particular widget and may be determined by other options, such as anchor. For windows, this is the title of the window." label := value. exists ifTrue: [self tclEval: ' %1 configure -title %2' with: self connected with: value asTkString] ] addLine [ "Add a separator item at the end of the menu" ^self addMenuItemFor: #() notifying: self "self is dummy" ] addMenuItemFor: anArray notifying: receiver [ "Add a menu item described by anArray at the end of the menu. If anArray is empty, insert a separator line. If anArray has a single item, a menu item is created without a callback. If anArray has two or three items, the second one is used as the selector sent to receiver, and the third one (if present) is passed to the selector." "Receiver will be sent the callback messages. anArray is something that responds to at: and size. Possible types are: #() insert a seperator line #(name) create a menu item with name, but no callback #(name symbol) create a menu item with the given name and no parameter callback. #(name symbol arg) create a menu item with the given name and one parameter callback." | item | item := self newMenuItemFor: anArray notifying: receiver. exists ifTrue: [item create] ] callback: receiver using: selectorPairs [ "Add menu items described by anArray at the end of the menu. Each element of selectorPairs must be in the format described in BMenu>>#addMenuItemFor:notifying:. All the callbacks will be sent to receiver." selectorPairs do: [:pair | self addMenuItemFor: pair notifying: receiver] ] empty [ "Empty the menu widget; that is, remove all the children" self tclEval: self connected , ' delete 0 end'. children := OrderedCollection new. childrensUnderline := nil ] destroy [ "Destroy the menu widget; that is, simply remove ourselves from the parent menu bar." self parent remove: self ] addChild: menuItem [ menuItem menuIndex: self childrenCount. super addChild: menuItem. self exists ifTrue: [menuItem create]. ^menuItem ] connected [ ^primitive ] container [ ^primitive ] create [ | s | s := WriteStream on: (String new: 80). s nextPutAll: 'menu '; nextPutAll: self connected; nextPutAll: ' -tearoff 0 -postcommand { callback '; print: self asOop; nextPutAll: ' invokeCallback }'; nl; nextPutAll: self parent container; nextPutAll: ' add cascade -label '; nextPutAll: self label asTkString; nextPutAll: ' -menu '; nextPutAll: self connected; nextPutAll: ' -underline '; print: (self parent underline: self label). self tclEval: s contents. "Set the title for torn-off menus" self label: self label. self childrenDo: [:each | each create]. exists := true ] exists [ ^exists ] initialize: parentWidget [ super initialize: parentWidget. label := ''. exists := false. primitive := '%1.w%2' % {self parent container. self asOop printString: 36} ] newMenuItemFor: pair notifying: receiver [ | item size | size := pair size. pair size = 0 ifTrue: [^BMenuItem new: self]. (size >= 2 and: [pair last isArray]) ifTrue: [size := size - 1. item := BMenu new: self label: (pair at: 1). pair last do: [:each | item add: (item newMenuItemFor: each notifying: receiver)]] ifFalse: [item := BMenuItem new: self label: (pair at: 1)]. size = 1 ifTrue: [^item]. size = 2 ifTrue: [^item callback: receiver message: (pair at: 2)]. ^item callback: receiver message: (pair at: 2) argument: (pair at: 3) ] ] BMenu subclass: BPopupMenu [ PopupMenuBar := nil. PopupMenus := nil. BPopupMenu class >> initializeOnStartup [ PopupMenuBar := nil. PopupMenus := WeakKeyIdentityDictionary new ] BPopupMenu class >> popupMenuBar [ PopupMenuBar isNil ifTrue: [PopupMenuBar := BMenuBar new: nil]. ^PopupMenuBar ] initialize: parentWindow [ super initialize: self class popupMenuBar. self parent add: self. PopupMenus at: self parent ifPresent: [:menu | menu destroy]. PopupMenus at: self parent put: self. parentWindow bind: '' to: #popup:y: of: self parameters: '%X %Y'. parentWindow bind: '' to: #popup:y: of: self parameters: '[expr 2+[winfo rootx %W]] [expr 2+[winfo rooty %W]]' ] popup: x y: y [ "Note that x and y are strings!" self tclEval: 'tk_popup ' , self connected , ' ' , x , ' ' , y ] popup [ "Generate a synthetic menu popup event" self tclEval: 'event generate %1 ' with: self parent connected ] ] BMenuObject subclass: BMenuItem [ | index createCode | BMenuItem class >> new: parent [ "Add a new separator item to the specified menu." ^self basicNew initialize: parent ] BMenuItem class >> new: parent label: label [ "Add a new menu item to the specified menu (parent) , with `label' as its caption." ^self basicNew initialize: parent label: label ] label [ "Answer the value of the label option for the widget. Specifies a string to be displayed inside the widget. The way in which the string is displayed depends on the particular widget and may be determined by other options, such as anchor. For windows, this is the title of the window." ^self properties at: #label ] label: value [ "Set the value of the label option for the widget. Specifies a string to be displayed inside the widget. The way in which the string is displayed depends on the particular widget and may be determined by other options, such as anchor. For windows, this is the title of the window." (self properties at: #label) isNil ifTrue: [^self error: 'no label for separator lines']. self parent exists ifTrue: [self tclEval: self container , ' entryconfigure ' , self connected , ' -label ' , value asTkString]. self properties at: #label put: value ] connected [ ^index ] container [ ^self parent container ] create [ | label | label := self label ifNil: [''] ifNotNil: [:lab | lab asTkString]. self tclEval: createCode with: label with: self widgetType. createCode := '' "free some memory" ] initialize: parentWidget [ super initialize: parentWidget. createCode := self container , ' add separator'. self properties at: #label put: nil. parent addChild: self ] initialize: parentWidget label: label [ | s | super initialize: parentWidget. s := WriteStream on: (String new: 80). s nextPutAll: self container; nextPutAll: ' add %2 -label %1 -font {' , self class defaultFont , '} -underline '; print: (self parent underline: label); nextPutAll: ' -command { callback '; print: self asOop; nextPutAll: ' invokeCallback }'. createCode := s contents. self properties at: #label put: label. parent addChild: self. parent exists ifTrue: [self create] ] menuIndex: anIndex [ index := anIndex printString ] widgetType [ ^'command' ] ] BMenuItem subclass: BCheckMenuItem [ | status | BCheckMenuItem class >> new: parent [ self shouldNotImplement ] invokeCallback [ "Generate a synthetic callback" self properties removeKey: #value ifAbsent: []. self callback isNil ifFalse: [self callback send] ] value [ "Answer whether the menu item is in a selected (checked) state." ^self properties at: #value ifAbsentPut: [false] ] value: aBoolean [ "Set whether the button is in a selected (checked) state and generates a callback accordingly." self properties at: #value put: aBoolean. self tclEval: 'set ' , self variable , self valueString. self callback isNil ifFalse: [self callback send] ] create [ super create. self tclEval: '%1 entryconfigure %2 -onvalue 1 -offvalue 0 -variable %3' with: self container with: self connected with: self variable ] destroyed [ "Private - The receiver has been destroyed, clear the corresponding Tcl variable to avoid memory leaks." self tclEval: 'unset ' , self variable. super destroyed ] valueString [ ^self value ifTrue: [' 1'] ifFalse: [' 0'] ] variable [ ^'var' , self connected , self container copyWithout: $. ] widgetType [ ^'checkbutton' ] ] "-------------------------- BEdit class -----------------------------" "-------------------------- BLabel class -----------------------------" Eval [ BLabel initialize ] "-------------------------- BButton class -----------------------------" "-------------------------- BForm class -----------------------------" "-------------------------- BContainer class -----------------------------" "-------------------------- BRadioGroup class -----------------------------" "-------------------------- BRadioButton class -----------------------------" "-------------------------- BToggle class -----------------------------" "-------------------------- BImage class -----------------------------" "-------------------------- BList class -----------------------------" "-------------------------- BWindow class -----------------------------" "-------------------------- BTransientWindow class -----------------------------" "-------------------------- BPopupWindow class -----------------------------" "-------------------------- BDialog class -----------------------------" "-------------------------- BMenuBar class -----------------------------" "-------------------------- BMenu class -----------------------------" "-------------------------- BPopupMenu class -----------------------------" "-------------------------- BMenuItem class -----------------------------" "-------------------------- BCheckMenuItem class -----------------------------" smalltalk-3.2.5/packages/blox/tk/ChangeLog0000644000175000017500000000563512123404352015345 000000000000002010-12-04 Paolo Bonzini * package.xml: Remove now superfluous tags. 2010-01-01 Paolo Bonzini * Update copyright years. 2009-12-09 Alexey Zakhlestin * BloxTK.c: Fix NULL vs. 0. 2009-07-27 Paolo Bonzini * BloxText.st: Don't force the background color. * BloxWidgets.st: Don't force the background color. 2007-09-28 Paolo Bonzini * BloxTK.c: Use strchr, not index. 2007-06-25 Paolo Bonzini * BloxBasic.st: Use #%. * BloxText.st: Use #%. * BloxWidgets.st: Use #%. 2006-12-05 Paolo Bonzini *** Version 2.3 released. 2006-11-21 Paolo Bonzini * BloxTK.c: Add GPL exception. * rgbtab.h: Add GPL exception. 2006-09-25 Paolo Bonzini * BloxBasic.st: Fix previous checkin... half a year later. 2006-03-17 Paolo Bonzini Jiro Yamamoto * BloxBasic.st: Support specifying different default fonts on different platforms. * BloxWidgets.st: Likewise. * BloxText.st: Likewise. 2005-03-25 Paolo Bonzini * BloxBasic.st: Switch to new C-call descriptions. 2004-09-18 Paolo Bonzini * BloxWidgets.st, blox-tk/BloxText.st: set default font to Helvetica 10. 2004-01-03 Paolo Bonzini * BloxCanvas.st, blox-tk/BloxText.st: fixed erroneous use of ValueHolder class>>#value:. 2003-06-04 Paolo Bonzini * BloxCanvas.st: fixed bug in BEmbeddedImage>> #data:. Thanks to Mike Anderson. 2003-05-09 Paolo Bonzini *** Version 2.1.2 released. 2003-04-17 Paolo Bonzini *** Version 2.1.1 (stable) released. 2003-04-12 Paolo Bonzini *** Version 2.1 (stable) released. 2003-03-23 Paolo Bonzini * BloxWidgets.st: adjust the wraplength of the label in a BDialog as it changes size. 2003-03-14 Paolo Bonzini * BloxBasic.st: fix clipboard management 2003-02-25 Paolo Bonzini * BloxBasic.st: fix geometry management under Windows when parent window is unmapped 2003-01-19 Paolo Bonzini * BloxWidgets.st: remove two Tcl calls that took 2 seconds each! 2002-12-29 Paolo Bonzini * BloxBasic.st: bind events to both the lowercase and the uppercase version of alphabetic keysyms. 2002-12-20 Paolo Bonzini * BloxWidgets.st: trigger callbacks in a list box when keys are pressed. 2002-11-29 Paolo Bonzini * BloxBasic.st: use asynchronous call-out for bloxIdle. 2002-11-19 Paolo Bonzini * BloxBasic.st: rewritten event loop 2002-10-22 Mike Castle * BloxTK.c: add some consts for Tcl 8.4.0 Older entries in browser/ChangeLog. smalltalk-3.2.5/packages/blox/tk/rgbtab.h0000644000175000017500000010653312123404352015204 00000000000000/*********************************************************************** * * X color names * * ***********************************************************************/ /*********************************************************************** * * Copyright 1988-92, 1994-95, 1999, 2000, 2006 Free Software Foundation, Inc. * Written by Paolo Bonzini. * * This file is part of GNU Smalltalk. * * GNU Smalltalk is free software; you can redistribute it and/or modify it * under the terms of the GNU General Public License as published by the Free * Software Foundation; either version 2, or (at your option) any later * version. * * Linking GNU Smalltalk statically or dynamically with other modules is * making a combined work based on GNU Smalltalk. Thus, the terms and * conditions of the GNU General Public License cover the whole * combination. * * In addition, as a special exception, the Free Software Foundation * give you permission to combine GNU Smalltalk with free software * programs or libraries that are released under the GNU LGPL and with * independent programs running under the GNU Smalltalk virtual machine. * * You may copy and distribute such a system following the terms of the * GNU GPL for GNU Smalltalk and the licenses of the other code * concerned, provided that you include the source code of that other * code when and as the GNU GPL requires distribution of source code. * * Note that people who make modified versions of GNU Smalltalk are not * obligated to grant this special exception for their modified * versions; it is their choice whether to do so. The GNU General * Public License gives permission to release a modified version without * this exception; this exception also makes it possible to release a * modified version which carries forward this exception. * * GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or * FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for * more details. * * You should have received a copy of the GNU General Public License along with * GNU Smalltalk; see the file COPYING. If not, write to the Free Software * Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * ***********************************************************************/ typedef struct { int rgb; const char *color; } xpmColorEntry; /* This is a kind of rgb.txt file */ static xpmColorEntry xColors[] = { { (240 << 16) | (248 << 8) | 255, "alice blue" }, { (240 << 16) | (248 << 8) | 255, "AliceBlue" }, { (250 << 16) | (235 << 8) | 215, "antique white" }, { (255 << 16) | (239 << 8) | 219, "AntiqueWhite1" }, { (238 << 16) | (223 << 8) | 204, "AntiqueWhite2" }, { (205 << 16) | (192 << 8) | 176, "AntiqueWhite3" }, { (139 << 16) | (131 << 8) | 120, "AntiqueWhite4" }, { (250 << 16) | (235 << 8) | 215, "AntiqueWhite" }, { (127 << 16) | (255 << 8) | 212, "aquamarine1" }, { (118 << 16) | (238 << 8) | 198, "aquamarine2" }, { (102 << 16) | (205 << 8) | 170, "aquamarine3" }, { ( 69 << 16) | (139 << 8) | 116, "aquamarine4" }, { (127 << 16) | (255 << 8) | 212, "aquamarine" }, { (240 << 16) | (255 << 8) | 255, "azure1" }, { (224 << 16) | (238 << 8) | 238, "azure2" }, { (193 << 16) | (205 << 8) | 205, "azure3" }, { (131 << 16) | (139 << 8) | 139, "azure4" }, { (240 << 16) | (255 << 8) | 255, "azure" }, { (245 << 16) | (245 << 8) | 220, "beige" }, { (255 << 16) | (228 << 8) | 196, "bisque1" }, { (238 << 16) | (213 << 8) | 183, "bisque2" }, { (205 << 16) | (183 << 8) | 158, "bisque3" }, { (139 << 16) | (125 << 8) | 107, "bisque4" }, { (255 << 16) | (228 << 8) | 196, "bisque" }, { ( 0 << 16) | ( 0 << 8) | 0, "black" }, { (255 << 16) | (235 << 8) | 205, "blanched almond" }, { (255 << 16) | (235 << 8) | 205, "BlanchedAlmond" }, { (138 << 16) | ( 43 << 8) | 226, "blue violet" }, { ( 0 << 16) | ( 0 << 8) | 255, "blue1" }, { ( 0 << 16) | ( 0 << 8) | 238, "blue2" }, { ( 0 << 16) | ( 0 << 8) | 205, "blue3" }, { ( 0 << 16) | ( 0 << 8) | 139, "blue4" }, { (138 << 16) | ( 43 << 8) | 226, "BlueViolet" }, { ( 0 << 16) | ( 0 << 8) | 255, "blue" }, { (255 << 16) | ( 64 << 8) | 64, "brown1" }, { (238 << 16) | ( 59 << 8) | 59, "brown2" }, { (205 << 16) | ( 51 << 8) | 51, "brown3" }, { (139 << 16) | ( 35 << 8) | 35, "brown4" }, { (165 << 16) | ( 42 << 8) | 42, "brown" }, { (255 << 16) | (211 << 8) | 155, "burlywood1" }, { (238 << 16) | (197 << 8) | 145, "burlywood2" }, { (205 << 16) | (170 << 8) | 125, "burlywood3" }, { (139 << 16) | (115 << 8) | 85, "burlywood4" }, { (222 << 16) | (184 << 8) | 135, "burlywood" }, { ( 95 << 16) | (158 << 8) | 160, "cadet blue" }, { (152 << 16) | (245 << 8) | 255, "CadetBlue1" }, { (142 << 16) | (229 << 8) | 238, "CadetBlue2" }, { (122 << 16) | (197 << 8) | 205, "CadetBlue3" }, { ( 83 << 16) | (134 << 8) | 139, "CadetBlue4" }, { ( 95 << 16) | (158 << 8) | 160, "CadetBlue" }, { (127 << 16) | (255 << 8) | 0, "chartreuse1" }, { (118 << 16) | (238 << 8) | 0, "chartreuse2" }, { (102 << 16) | (205 << 8) | 0, "chartreuse3" }, { ( 69 << 16) | (139 << 8) | 0, "chartreuse4" }, { (127 << 16) | (255 << 8) | 0, "chartreuse" }, { (255 << 16) | (127 << 8) | 36, "chocolate1" }, { (238 << 16) | (118 << 8) | 33, "chocolate2" }, { (205 << 16) | (102 << 8) | 29, "chocolate3" }, { (139 << 16) | ( 69 << 8) | 19, "chocolate4" }, { (210 << 16) | (105 << 8) | 30, "chocolate" }, { (255 << 16) | (114 << 8) | 86, "coral1" }, { (238 << 16) | (106 << 8) | 80, "coral2" }, { (205 << 16) | ( 91 << 8) | 69, "coral3" }, { (139 << 16) | ( 62 << 8) | 47, "coral4" }, { (255 << 16) | (127 << 8) | 80, "coral" }, { (100 << 16) | (149 << 8) | 237, "cornflower blue" }, { (100 << 16) | (149 << 8) | 237, "CornflowerBlue" }, { (255 << 16) | (248 << 8) | 220, "cornsilk1" }, { (238 << 16) | (232 << 8) | 205, "cornsilk2" }, { (205 << 16) | (200 << 8) | 177, "cornsilk3" }, { (139 << 16) | (136 << 8) | 120, "cornsilk4" }, { (255 << 16) | (248 << 8) | 220, "cornsilk" }, { ( 0 << 16) | (255 << 8) | 255, "cyan1" }, { ( 0 << 16) | (238 << 8) | 238, "cyan2" }, { ( 0 << 16) | (205 << 8) | 205, "cyan3" }, { ( 0 << 16) | (139 << 8) | 139, "cyan4" }, { ( 0 << 16) | (255 << 8) | 255, "cyan" }, { (0 << 16) | ( 0 << 8) | 139, "dark blue" }, { (0 << 16) | (139 << 8) | 139, "dark cyan" }, { (184 << 16) | (134 << 8) | 11, "dark goldenrod" }, { (169 << 16) | (169 << 8) | 169, "dark gray" }, { ( 0 << 16) | (100 << 8) | 0, "dark green" }, { (169 << 16) | (169 << 8) | 169, "dark grey" }, { (189 << 16) | (183 << 8) | 107, "dark khaki" }, { (139 << 16) | ( 0 << 8) | 139, "dark magenta" }, { ( 85 << 16) | (107 << 8) | 47, "dark olive green" }, { (255 << 16) | (140 << 8) | 0, "dark orange" }, { (153 << 16) | ( 50 << 8) | 204, "dark orchid" }, { (139 << 16) | ( 0 << 8) | 0, "dark red" }, { (233 << 16) | (150 << 8) | 122, "dark salmon" }, { (143 << 16) | (188 << 8) | 143, "dark sea green" }, { ( 72 << 16) | ( 61 << 8) | 139, "dark slate blue" }, { ( 47 << 16) | ( 79 << 8) | 79, "dark slate gray" }, { ( 47 << 16) | ( 79 << 8) | 79, "dark slate grey" }, { ( 0 << 16) | (206 << 8) | 209, "dark turquoise" }, { (148 << 16) | ( 0 << 8) | 211, "dark violet" }, { (0 << 16) | ( 0 << 8) | 139, "DarkBlue" }, { (0 << 16) | (139 << 8) | 139, "DarkCyan" }, { (255 << 16) | (185 << 8) | 15, "DarkGoldenrod1" }, { (238 << 16) | (173 << 8) | 14, "DarkGoldenrod2" }, { (205 << 16) | (149 << 8) | 12, "DarkGoldenrod3" }, { (139 << 16) | (101 << 8) | 8, "DarkGoldenrod4" }, { (184 << 16) | (134 << 8) | 11, "DarkGoldenrod" }, { (169 << 16) | (169 << 8) | 169, "DarkGray" }, { ( 0 << 16) | (100 << 8) | 0, "DarkGreen" }, { (169 << 16) | (169 << 8) | 169, "DarkGrey" }, { (189 << 16) | (183 << 8) | 107, "DarkKhaki" }, { (139 << 16) | ( 0 << 8) | 139, "DarkMagenta" }, { (202 << 16) | (255 << 8) | 112, "DarkOliveGreen1" }, { (188 << 16) | (238 << 8) | 104, "DarkOliveGreen2" }, { (162 << 16) | (205 << 8) | 90, "DarkOliveGreen3" }, { (110 << 16) | (139 << 8) | 61, "DarkOliveGreen4" }, { ( 85 << 16) | (107 << 8) | 47, "DarkOliveGreen" }, { (255 << 16) | (127 << 8) | 0, "DarkOrange1" }, { (238 << 16) | (118 << 8) | 0, "DarkOrange2" }, { (205 << 16) | (102 << 8) | 0, "DarkOrange3" }, { (139 << 16) | ( 69 << 8) | 0, "DarkOrange4" }, { (255 << 16) | (140 << 8) | 0, "DarkOrange" }, { (191 << 16) | ( 62 << 8) | 255, "DarkOrchid1" }, { (178 << 16) | ( 58 << 8) | 238, "DarkOrchid2" }, { (154 << 16) | ( 50 << 8) | 205, "DarkOrchid3" }, { (104 << 16) | ( 34 << 8) | 139, "DarkOrchid4" }, { (153 << 16) | ( 50 << 8) | 204, "DarkOrchid" }, { (139 << 16) | ( 0 << 8) | 0, "DarkRed" }, { (233 << 16) | (150 << 8) | 122, "DarkSalmon" }, { (193 << 16) | (255 << 8) | 193, "DarkSeaGreen1" }, { (180 << 16) | (238 << 8) | 180, "DarkSeaGreen2" }, { (155 << 16) | (205 << 8) | 155, "DarkSeaGreen3" }, { (105 << 16) | (139 << 8) | 105, "DarkSeaGreen4" }, { (143 << 16) | (188 << 8) | 143, "DarkSeaGreen" }, { ( 72 << 16) | ( 61 << 8) | 139, "DarkSlateBlue" }, { (151 << 16) | (255 << 8) | 255, "DarkSlateGray1" }, { (141 << 16) | (238 << 8) | 238, "DarkSlateGray2" }, { (121 << 16) | (205 << 8) | 205, "DarkSlateGray3" }, { ( 82 << 16) | (139 << 8) | 139, "DarkSlateGray4" }, { ( 47 << 16) | ( 79 << 8) | 79, "DarkSlateGray" }, { ( 47 << 16) | ( 79 << 8) | 79, "DarkSlateGrey" }, { ( 0 << 16) | (206 << 8) | 209, "DarkTurquoise" }, { (148 << 16) | ( 0 << 8) | 211, "DarkViolet" }, { (255 << 16) | ( 20 << 8) | 147, "deep pink" }, { ( 0 << 16) | (191 << 8) | 255, "deep sky blue" }, { (255 << 16) | ( 20 << 8) | 147, "DeepPink1" }, { (238 << 16) | ( 18 << 8) | 137, "DeepPink2" }, { (205 << 16) | ( 16 << 8) | 118, "DeepPink3" }, { (139 << 16) | ( 10 << 8) | 80, "DeepPink4" }, { (255 << 16) | ( 20 << 8) | 147, "DeepPink" }, { ( 0 << 16) | (191 << 8) | 255, "DeepSkyBlue1" }, { ( 0 << 16) | (178 << 8) | 238, "DeepSkyBlue2" }, { ( 0 << 16) | (154 << 8) | 205, "DeepSkyBlue3" }, { ( 0 << 16) | (104 << 8) | 139, "DeepSkyBlue4" }, { ( 0 << 16) | (191 << 8) | 255, "DeepSkyBlue" }, { (105 << 16) | (105 << 8) | 105, "dim gray" }, { (105 << 16) | (105 << 8) | 105, "dim grey" }, { (105 << 16) | (105 << 8) | 105, "DimGray" }, { (105 << 16) | (105 << 8) | 105, "DimGrey" }, { ( 30 << 16) | (144 << 8) | 255, "dodger blue" }, { ( 30 << 16) | (144 << 8) | 255, "DodgerBlue1" }, { ( 28 << 16) | (134 << 8) | 238, "DodgerBlue2" }, { ( 24 << 16) | (116 << 8) | 205, "DodgerBlue3" }, { ( 16 << 16) | ( 78 << 8) | 139, "DodgerBlue4" }, { ( 30 << 16) | (144 << 8) | 255, "DodgerBlue" }, { (255 << 16) | ( 48 << 8) | 48, "firebrick1" }, { (238 << 16) | ( 44 << 8) | 44, "firebrick2" }, { (205 << 16) | ( 38 << 8) | 38, "firebrick3" }, { (139 << 16) | ( 26 << 8) | 26, "firebrick4" }, { (178 << 16) | ( 34 << 8) | 34, "firebrick" }, { (255 << 16) | (250 << 8) | 240, "floral white" }, { (255 << 16) | (250 << 8) | 240, "FloralWhite" }, { ( 34 << 16) | (139 << 8) | 34, "forest green" }, { ( 34 << 16) | (139 << 8) | 34, "ForestGreen" }, { (220 << 16) | (220 << 8) | 220, "gainsboro" }, { (248 << 16) | (248 << 8) | 255, "ghost white" }, { (248 << 16) | (248 << 8) | 255, "GhostWhite" }, { (255 << 16) | (215 << 8) | 0, "gold" }, { (255 << 16) | (215 << 8) | 0, "gold1" }, { (238 << 16) | (201 << 8) | 0, "gold2" }, { (205 << 16) | (173 << 8) | 0, "gold3" }, { (139 << 16) | (117 << 8) | 0, "gold4" }, { (255 << 16) | (193 << 8) | 37, "goldenrod1" }, { (238 << 16) | (180 << 8) | 34, "goldenrod2" }, { (205 << 16) | (155 << 8) | 29, "goldenrod3" }, { (139 << 16) | (105 << 8) | 20, "goldenrod4" }, { (218 << 16) | (165 << 8) | 32, "goldenrod" }, { ( 0 << 16) | ( 0 << 8) | 0, "gray0" }, { ( 3 << 16) | ( 3 << 8) | 3, "gray1" }, { ( 5 << 16) | ( 5 << 8) | 5, "gray2" }, { ( 8 << 16) | ( 8 << 8) | 8, "gray3" }, { ( 10 << 16) | ( 10 << 8) | 10, "gray4" }, { ( 13 << 16) | ( 13 << 8) | 13, "gray5" }, { ( 15 << 16) | ( 15 << 8) | 15, "gray6" }, { ( 18 << 16) | ( 18 << 8) | 18, "gray7" }, { ( 20 << 16) | ( 20 << 8) | 20, "gray8" }, { ( 23 << 16) | ( 23 << 8) | 23, "gray9" }, { ( 26 << 16) | ( 26 << 8) | 26, "gray10" }, { ( 28 << 16) | ( 28 << 8) | 28, "gray11" }, { ( 31 << 16) | ( 31 << 8) | 31, "gray12" }, { ( 33 << 16) | ( 33 << 8) | 33, "gray13" }, { ( 36 << 16) | ( 36 << 8) | 36, "gray14" }, { ( 38 << 16) | ( 38 << 8) | 38, "gray15" }, { ( 41 << 16) | ( 41 << 8) | 41, "gray16" }, { ( 43 << 16) | ( 43 << 8) | 43, "gray17" }, { ( 46 << 16) | ( 46 << 8) | 46, "gray18" }, { ( 48 << 16) | ( 48 << 8) | 48, "gray19" }, { ( 51 << 16) | ( 51 << 8) | 51, "gray20" }, { ( 54 << 16) | ( 54 << 8) | 54, "gray21" }, { ( 56 << 16) | ( 56 << 8) | 56, "gray22" }, { ( 59 << 16) | ( 59 << 8) | 59, "gray23" }, { ( 61 << 16) | ( 61 << 8) | 61, "gray24" }, { ( 64 << 16) | ( 64 << 8) | 64, "gray25" }, { ( 66 << 16) | ( 66 << 8) | 66, "gray26" }, { ( 69 << 16) | ( 69 << 8) | 69, "gray27" }, { ( 71 << 16) | ( 71 << 8) | 71, "gray28" }, { ( 74 << 16) | ( 74 << 8) | 74, "gray29" }, { ( 77 << 16) | ( 77 << 8) | 77, "gray30" }, { ( 79 << 16) | ( 79 << 8) | 79, "gray31" }, { ( 82 << 16) | ( 82 << 8) | 82, "gray32" }, { ( 84 << 16) | ( 84 << 8) | 84, "gray33" }, { ( 87 << 16) | ( 87 << 8) | 87, "gray34" }, { ( 89 << 16) | ( 89 << 8) | 89, "gray35" }, { ( 92 << 16) | ( 92 << 8) | 92, "gray36" }, { ( 94 << 16) | ( 94 << 8) | 94, "gray37" }, { ( 97 << 16) | ( 97 << 8) | 97, "gray38" }, { ( 99 << 16) | ( 99 << 8) | 99, "gray39" }, { (102 << 16) | (102 << 8) | 102, "gray40" }, { (105 << 16) | (105 << 8) | 105, "gray41" }, { (107 << 16) | (107 << 8) | 107, "gray42" }, { (110 << 16) | (110 << 8) | 110, "gray43" }, { (112 << 16) | (112 << 8) | 112, "gray44" }, { (115 << 16) | (115 << 8) | 115, "gray45" }, { (117 << 16) | (117 << 8) | 117, "gray46" }, { (120 << 16) | (120 << 8) | 120, "gray47" }, { (122 << 16) | (122 << 8) | 122, "gray48" }, { (125 << 16) | (125 << 8) | 125, "gray49" }, { (127 << 16) | (127 << 8) | 127, "gray50" }, { (130 << 16) | (130 << 8) | 130, "gray51" }, { (133 << 16) | (133 << 8) | 133, "gray52" }, { (135 << 16) | (135 << 8) | 135, "gray53" }, { (138 << 16) | (138 << 8) | 138, "gray54" }, { (140 << 16) | (140 << 8) | 140, "gray55" }, { (143 << 16) | (143 << 8) | 143, "gray56" }, { (145 << 16) | (145 << 8) | 145, "gray57" }, { (148 << 16) | (148 << 8) | 148, "gray58" }, { (150 << 16) | (150 << 8) | 150, "gray59" }, { (153 << 16) | (153 << 8) | 153, "gray60" }, { (156 << 16) | (156 << 8) | 156, "gray61" }, { (158 << 16) | (158 << 8) | 158, "gray62" }, { (161 << 16) | (161 << 8) | 161, "gray63" }, { (163 << 16) | (163 << 8) | 163, "gray64" }, { (166 << 16) | (166 << 8) | 166, "gray65" }, { (168 << 16) | (168 << 8) | 168, "gray66" }, { (171 << 16) | (171 << 8) | 171, "gray67" }, { (173 << 16) | (173 << 8) | 173, "gray68" }, { (176 << 16) | (176 << 8) | 176, "gray69" }, { (179 << 16) | (179 << 8) | 179, "gray70" }, { (181 << 16) | (181 << 8) | 181, "gray71" }, { (184 << 16) | (184 << 8) | 184, "gray72" }, { (186 << 16) | (186 << 8) | 186, "gray73" }, { (189 << 16) | (189 << 8) | 189, "gray74" }, { (191 << 16) | (191 << 8) | 191, "gray75" }, { (194 << 16) | (194 << 8) | 194, "gray76" }, { (196 << 16) | (196 << 8) | 196, "gray77" }, { (199 << 16) | (199 << 8) | 199, "gray78" }, { (201 << 16) | (201 << 8) | 201, "gray79" }, { (204 << 16) | (204 << 8) | 204, "gray80" }, { (207 << 16) | (207 << 8) | 207, "gray81" }, { (209 << 16) | (209 << 8) | 209, "gray82" }, { (212 << 16) | (212 << 8) | 212, "gray83" }, { (214 << 16) | (214 << 8) | 214, "gray84" }, { (217 << 16) | (217 << 8) | 217, "gray85" }, { (219 << 16) | (219 << 8) | 219, "gray86" }, { (222 << 16) | (222 << 8) | 222, "gray87" }, { (224 << 16) | (224 << 8) | 224, "gray88" }, { (227 << 16) | (227 << 8) | 227, "gray89" }, { (229 << 16) | (229 << 8) | 229, "gray90" }, { (232 << 16) | (232 << 8) | 232, "gray91" }, { (235 << 16) | (235 << 8) | 235, "gray92" }, { (237 << 16) | (237 << 8) | 237, "gray93" }, { (240 << 16) | (240 << 8) | 240, "gray94" }, { (242 << 16) | (242 << 8) | 242, "gray95" }, { (245 << 16) | (245 << 8) | 245, "gray96" }, { (247 << 16) | (247 << 8) | 247, "gray97" }, { (250 << 16) | (250 << 8) | 250, "gray98" }, { (252 << 16) | (252 << 8) | 252, "gray99" }, { (255 << 16) | (255 << 8) | 255, "gray100" }, { (190 << 16) | (190 << 8) | 190, "gray" }, { (173 << 16) | (255 << 8) | 47, "green yellow" }, { ( 0 << 16) | (255 << 8) | 0, "green1" }, { ( 0 << 16) | (238 << 8) | 0, "green2" }, { ( 0 << 16) | (205 << 8) | 0, "green3" }, { ( 0 << 16) | (139 << 8) | 0, "green4" }, { (173 << 16) | (255 << 8) | 47, "GreenYellow" }, { ( 0 << 16) | (255 << 8) | 0, "green" }, { (240 << 16) | (255 << 8) | 240, "honeydew1" }, { (224 << 16) | (238 << 8) | 224, "honeydew2" }, { (193 << 16) | (205 << 8) | 193, "honeydew3" }, { (131 << 16) | (139 << 8) | 131, "honeydew4" }, { (240 << 16) | (255 << 8) | 240, "honeydew" }, { (255 << 16) | (105 << 8) | 180, "hot pink" }, { (255 << 16) | (110 << 8) | 180, "HotPink1" }, { (238 << 16) | (106 << 8) | 167, "HotPink2" }, { (205 << 16) | ( 96 << 8) | 144, "HotPink3" }, { (139 << 16) | ( 58 << 8) | 98, "HotPink4" }, { (255 << 16) | (105 << 8) | 180, "HotPink" }, { (205 << 16) | ( 92 << 8) | 92, "indian red" }, { (255 << 16) | (106 << 8) | 106, "IndianRed1" }, { (238 << 16) | ( 99 << 8) | 99, "IndianRed2" }, { (205 << 16) | ( 85 << 8) | 85, "IndianRed3" }, { (139 << 16) | ( 58 << 8) | 58, "IndianRed4" }, { (205 << 16) | ( 92 << 8) | 92, "IndianRed" }, { (255 << 16) | (255 << 8) | 240, "ivory1" }, { (238 << 16) | (238 << 8) | 224, "ivory2" }, { (205 << 16) | (205 << 8) | 193, "ivory3" }, { (139 << 16) | (139 << 8) | 131, "ivory4" }, { (255 << 16) | (255 << 8) | 240, "ivory" }, { (255 << 16) | (246 << 8) | 143, "khaki1" }, { (238 << 16) | (230 << 8) | 133, "khaki2" }, { (205 << 16) | (198 << 8) | 115, "khaki3" }, { (139 << 16) | (134 << 8) | 78, "khaki4" }, { (240 << 16) | (230 << 8) | 140, "khaki" }, { (255 << 16) | (240 << 8) | 245, "lavender blush" }, { (255 << 16) | (240 << 8) | 245, "LavenderBlush1" }, { (238 << 16) | (224 << 8) | 229, "LavenderBlush2" }, { (205 << 16) | (193 << 8) | 197, "LavenderBlush3" }, { (139 << 16) | (131 << 8) | 134, "LavenderBlush4" }, { (255 << 16) | (240 << 8) | 245, "LavenderBlush" }, { (230 << 16) | (230 << 8) | 250, "lavender" }, { (124 << 16) | (252 << 8) | 0, "lawn green" }, { (124 << 16) | (252 << 8) | 0, "LawnGreen" }, { (255 << 16) | (250 << 8) | 205, "lemon chiffon" }, { (255 << 16) | (250 << 8) | 205, "LemonChiffon1" }, { (238 << 16) | (233 << 8) | 191, "LemonChiffon2" }, { (205 << 16) | (201 << 8) | 165, "LemonChiffon3" }, { (139 << 16) | (137 << 8) | 112, "LemonChiffon4" }, { (255 << 16) | (250 << 8) | 205, "LemonChiffon" }, { (173 << 16) | (216 << 8) | 230, "light blue" }, { (240 << 16) | (128 << 8) | 128, "light coral" }, { (224 << 16) | (255 << 8) | 255, "light cyan" }, { (250 << 16) | (250 << 8) | 210, "light goldenrod yellow" }, { (238 << 16) | (221 << 8) | 130, "light goldenrod" }, { (211 << 16) | (211 << 8) | 211, "light gray" }, { (144 << 16) | (238 << 8) | 144, "light green" }, { (211 << 16) | (211 << 8) | 211, "light grey" }, { (255 << 16) | (182 << 8) | 193, "light pink" }, { (255 << 16) | (160 << 8) | 122, "light salmon" }, { ( 32 << 16) | (178 << 8) | 170, "light sea green" }, { (135 << 16) | (206 << 8) | 250, "light sky blue" }, { (132 << 16) | (112 << 8) | 255, "light slate blue" }, { (119 << 16) | (136 << 8) | 153, "light slate gray" }, { (119 << 16) | (136 << 8) | 153, "light slate grey" }, { (176 << 16) | (196 << 8) | 222, "light steel blue" }, { (255 << 16) | (255 << 8) | 224, "light yellow" }, { (191 << 16) | (239 << 8) | 255, "LightBlue1" }, { (178 << 16) | (223 << 8) | 238, "LightBlue2" }, { (154 << 16) | (192 << 8) | 205, "LightBlue3" }, { (104 << 16) | (131 << 8) | 139, "LightBlue4" }, { (173 << 16) | (216 << 8) | 230, "LightBlue" }, { (240 << 16) | (128 << 8) | 128, "LightCoral" }, { (224 << 16) | (255 << 8) | 255, "LightCyan1" }, { (209 << 16) | (238 << 8) | 238, "LightCyan2" }, { (180 << 16) | (205 << 8) | 205, "LightCyan3" }, { (122 << 16) | (139 << 8) | 139, "LightCyan4" }, { (224 << 16) | (255 << 8) | 255, "LightCyan" }, { (255 << 16) | (236 << 8) | 139, "LightGoldenrod1" }, { (238 << 16) | (220 << 8) | 130, "LightGoldenrod2" }, { (205 << 16) | (190 << 8) | 112, "LightGoldenrod3" }, { (139 << 16) | (129 << 8) | 76, "LightGoldenrod4" }, { (250 << 16) | (250 << 8) | 210, "LightGoldenrodYellow" }, { (238 << 16) | (221 << 8) | 130, "LightGoldenrod" }, { (211 << 16) | (211 << 8) | 211, "LightGray" }, { (144 << 16) | (238 << 8) | 144, "LightGreen" }, { (211 << 16) | (211 << 8) | 211, "LightGrey" }, { (255 << 16) | (174 << 8) | 185, "LightPink1" }, { (238 << 16) | (162 << 8) | 173, "LightPink2" }, { (205 << 16) | (140 << 8) | 149, "LightPink3" }, { (139 << 16) | ( 95 << 8) | 101, "LightPink4" }, { (255 << 16) | (182 << 8) | 193, "LightPink" }, { (255 << 16) | (160 << 8) | 122, "LightSalmon1" }, { (238 << 16) | (149 << 8) | 114, "LightSalmon2" }, { (205 << 16) | (129 << 8) | 98, "LightSalmon3" }, { (139 << 16) | ( 87 << 8) | 66, "LightSalmon4" }, { (255 << 16) | (160 << 8) | 122, "LightSalmon" }, { ( 32 << 16) | (178 << 8) | 170, "LightSeaGreen" }, { (176 << 16) | (226 << 8) | 255, "LightSkyBlue1" }, { (164 << 16) | (211 << 8) | 238, "LightSkyBlue2" }, { (141 << 16) | (182 << 8) | 205, "LightSkyBlue3" }, { ( 96 << 16) | (123 << 8) | 139, "LightSkyBlue4" }, { (135 << 16) | (206 << 8) | 250, "LightSkyBlue" }, { (132 << 16) | (112 << 8) | 255, "LightSlateBlue" }, { (119 << 16) | (136 << 8) | 153, "LightSlateGray" }, { (119 << 16) | (136 << 8) | 153, "LightSlateGrey" }, { (202 << 16) | (225 << 8) | 255, "LightSteelBlue1" }, { (188 << 16) | (210 << 8) | 238, "LightSteelBlue2" }, { (162 << 16) | (181 << 8) | 205, "LightSteelBlue3" }, { (110 << 16) | (123 << 8) | 139, "LightSteelBlue4" }, { (176 << 16) | (196 << 8) | 222, "LightSteelBlue" }, { (255 << 16) | (255 << 8) | 224, "LightYellow1" }, { (238 << 16) | (238 << 8) | 209, "LightYellow2" }, { (205 << 16) | (205 << 8) | 180, "LightYellow3" }, { (139 << 16) | (139 << 8) | 122, "LightYellow4" }, { (255 << 16) | (255 << 8) | 224, "LightYellow" }, { ( 50 << 16) | (205 << 8) | 50, "lime green" }, { ( 50 << 16) | (205 << 8) | 50, "LimeGreen" }, { (250 << 16) | (240 << 8) | 230, "linen" }, { (255 << 16) | ( 0 << 8) | 255, "magenta1" }, { (238 << 16) | ( 0 << 8) | 238, "magenta2" }, { (205 << 16) | ( 0 << 8) | 205, "magenta3" }, { (139 << 16) | ( 0 << 8) | 139, "magenta4" }, { (255 << 16) | ( 0 << 8) | 255, "magenta" }, { (255 << 16) | ( 52 << 8) | 179, "maroon1" }, { (238 << 16) | ( 48 << 8) | 167, "maroon2" }, { (205 << 16) | ( 41 << 8) | 144, "maroon3" }, { (139 << 16) | ( 28 << 8) | 98, "maroon4" }, { (176 << 16) | ( 48 << 8) | 96, "maroon" }, { (102 << 16) | (205 << 8) | 170, "medium aquamarine" }, { ( 0 << 16) | ( 0 << 8) | 205, "medium blue" }, { (186 << 16) | ( 85 << 8) | 211, "medium orchid" }, { (147 << 16) | (112 << 8) | 219, "medium purple" }, { ( 60 << 16) | (179 << 8) | 113, "medium sea green" }, { (123 << 16) | (104 << 8) | 238, "medium slate blue" }, { ( 0 << 16) | (250 << 8) | 154, "medium spring green" }, { ( 72 << 16) | (209 << 8) | 204, "medium turquoise" }, { (199 << 16) | ( 21 << 8) | 133, "medium violet red" }, { (102 << 16) | (205 << 8) | 170, "MediumAquamarine" }, { ( 0 << 16) | ( 0 << 8) | 205, "MediumBlue" }, { (224 << 16) | (102 << 8) | 255, "MediumOrchid1" }, { (209 << 16) | ( 95 << 8) | 238, "MediumOrchid2" }, { (180 << 16) | ( 82 << 8) | 205, "MediumOrchid3" }, { (122 << 16) | ( 55 << 8) | 139, "MediumOrchid4" }, { (186 << 16) | ( 85 << 8) | 211, "MediumOrchid" }, { (171 << 16) | (130 << 8) | 255, "MediumPurple1" }, { (159 << 16) | (121 << 8) | 238, "MediumPurple2" }, { (137 << 16) | (104 << 8) | 205, "MediumPurple3" }, { ( 93 << 16) | ( 71 << 8) | 139, "MediumPurple4" }, { (147 << 16) | (112 << 8) | 219, "MediumPurple" }, { ( 60 << 16) | (179 << 8) | 113, "MediumSeaGreen" }, { (123 << 16) | (104 << 8) | 238, "MediumSlateBlue" }, { ( 0 << 16) | (250 << 8) | 154, "MediumSpringGreen" }, { ( 72 << 16) | (209 << 8) | 204, "MediumTurquoise" }, { (199 << 16) | ( 21 << 8) | 133, "MediumVioletRed" }, { ( 25 << 16) | ( 25 << 8) | 112, "midnight blue" }, { ( 25 << 16) | ( 25 << 8) | 112, "MidnightBlue" }, { (245 << 16) | (255 << 8) | 250, "mint cream" }, { (245 << 16) | (255 << 8) | 250, "MintCream" }, { (255 << 16) | (228 << 8) | 225, "misty rose" }, { (255 << 16) | (228 << 8) | 225, "MistyRose1" }, { (238 << 16) | (213 << 8) | 210, "MistyRose2" }, { (205 << 16) | (183 << 8) | 181, "MistyRose3" }, { (139 << 16) | (125 << 8) | 123, "MistyRose4" }, { (255 << 16) | (228 << 8) | 225, "MistyRose" }, { (255 << 16) | (228 << 8) | 181, "moccasin" }, { (255 << 16) | (222 << 8) | 173, "navajo white" }, { (255 << 16) | (222 << 8) | 173, "NavajoWhite1" }, { (238 << 16) | (207 << 8) | 161, "NavajoWhite2" }, { (205 << 16) | (179 << 8) | 139, "NavajoWhite3" }, { (139 << 16) | (121 << 8) | 94, "NavajoWhite4" }, { (255 << 16) | (222 << 8) | 173, "NavajoWhite" }, { ( 0 << 16) | ( 0 << 8) | 128, "navy blue" }, { ( 0 << 16) | ( 0 << 8) | 128, "NavyBlue" }, { ( 0 << 16) | ( 0 << 8) | 128, "navy" }, { (253 << 16) | (245 << 8) | 230, "old lace" }, { (253 << 16) | (245 << 8) | 230, "OldLace" }, { (107 << 16) | (142 << 8) | 35, "olive drab" }, { (192 << 16) | (255 << 8) | 62, "OliveDrab1" }, { (179 << 16) | (238 << 8) | 58, "OliveDrab2" }, { (154 << 16) | (205 << 8) | 50, "OliveDrab3" }, { (105 << 16) | (139 << 8) | 34, "OliveDrab4" }, { (107 << 16) | (142 << 8) | 35, "OliveDrab" }, { (255 << 16) | ( 69 << 8) | 0, "orange red" }, { (255 << 16) | (165 << 8) | 0, "orange1" }, { (238 << 16) | (154 << 8) | 0, "orange2" }, { (205 << 16) | (133 << 8) | 0, "orange3" }, { (139 << 16) | ( 90 << 8) | 0, "orange4" }, { (255 << 16) | ( 69 << 8) | 0, "OrangeRed1" }, { (238 << 16) | ( 64 << 8) | 0, "OrangeRed2" }, { (205 << 16) | ( 55 << 8) | 0, "OrangeRed3" }, { (139 << 16) | ( 37 << 8) | 0, "OrangeRed4" }, { (255 << 16) | ( 69 << 8) | 0, "OrangeRed" }, { (255 << 16) | (165 << 8) | 0, "orange" }, { (255 << 16) | (131 << 8) | 250, "orchid1" }, { (238 << 16) | (122 << 8) | 233, "orchid2" }, { (205 << 16) | (105 << 8) | 201, "orchid3" }, { (139 << 16) | ( 71 << 8) | 137, "orchid4" }, { (218 << 16) | (112 << 8) | 214, "orchid" }, { (238 << 16) | (232 << 8) | 170, "pale goldenrod" }, { (152 << 16) | (251 << 8) | 152, "pale green" }, { (175 << 16) | (238 << 8) | 238, "pale turquoise" }, { (219 << 16) | (112 << 8) | 147, "pale violet red" }, { (238 << 16) | (232 << 8) | 170, "PaleGoldenrod" }, { (154 << 16) | (255 << 8) | 154, "PaleGreen1" }, { (144 << 16) | (238 << 8) | 144, "PaleGreen2" }, { (124 << 16) | (205 << 8) | 124, "PaleGreen3" }, { ( 84 << 16) | (139 << 8) | 84, "PaleGreen4" }, { (152 << 16) | (251 << 8) | 152, "PaleGreen" }, { (187 << 16) | (255 << 8) | 255, "PaleTurquoise1" }, { (174 << 16) | (238 << 8) | 238, "PaleTurquoise2" }, { (150 << 16) | (205 << 8) | 205, "PaleTurquoise3" }, { (102 << 16) | (139 << 8) | 139, "PaleTurquoise4" }, { (175 << 16) | (238 << 8) | 238, "PaleTurquoise" }, { (255 << 16) | (130 << 8) | 171, "PaleVioletRed1" }, { (238 << 16) | (121 << 8) | 159, "PaleVioletRed2" }, { (205 << 16) | (104 << 8) | 137, "PaleVioletRed3" }, { (139 << 16) | ( 71 << 8) | 93, "PaleVioletRed4" }, { (219 << 16) | (112 << 8) | 147, "PaleVioletRed" }, { (255 << 16) | (239 << 8) | 213, "papaya whip" }, { (255 << 16) | (239 << 8) | 213, "PapayaWhip" }, { (255 << 16) | (218 << 8) | 185, "peach puff" }, { (255 << 16) | (218 << 8) | 185, "PeachPuff1" }, { (238 << 16) | (203 << 8) | 173, "PeachPuff2" }, { (205 << 16) | (175 << 8) | 149, "PeachPuff3" }, { (139 << 16) | (119 << 8) | 101, "PeachPuff4" }, { (255 << 16) | (218 << 8) | 185, "PeachPuff" }, { (205 << 16) | (133 << 8) | 63, "peru" }, { (255 << 16) | (181 << 8) | 197, "pink1" }, { (238 << 16) | (169 << 8) | 184, "pink2" }, { (205 << 16) | (145 << 8) | 158, "pink3" }, { (139 << 16) | ( 99 << 8) | 108, "pink4" }, { (255 << 16) | (192 << 8) | 203, "pink" }, { (255 << 16) | (187 << 8) | 255, "plum1" }, { (238 << 16) | (174 << 8) | 238, "plum2" }, { (205 << 16) | (150 << 8) | 205, "plum3" }, { (139 << 16) | (102 << 8) | 139, "plum4" }, { (221 << 16) | (160 << 8) | 221, "plum" }, { (176 << 16) | (224 << 8) | 230, "powder blue" }, { (176 << 16) | (224 << 8) | 230, "PowderBlue" }, { (128 << 16) | (128 << 8) | 0, "PureDarkBrown" }, { ( 0 << 16) | (128 << 8) | 128, "PureDarkCyan" }, { ( 0 << 16) | (128 << 8) | 0, "PureDarkGreen" }, { (128 << 16) | (128 << 8) | 128, "PureDarkGrey" }, { (128 << 16) | ( 0 << 8) | 128, "PureDarkMagenta" }, { (128 << 16) | ( 0 << 8) | 0, "PureDarkRed" }, { (155 << 16) | ( 48 << 8) | 255, "purple1" }, { (145 << 16) | ( 44 << 8) | 238, "purple2" }, { (125 << 16) | ( 38 << 8) | 205, "purple3" }, { ( 85 << 16) | ( 26 << 8) | 139, "purple4" }, { (160 << 16) | ( 32 << 8) | 240, "purple" }, { (255 << 16) | ( 0 << 8) | 0, "red1" }, { (238 << 16) | ( 0 << 8) | 0, "red2" }, { (205 << 16) | ( 0 << 8) | 0, "red3" }, { (139 << 16) | ( 0 << 8) | 0, "red4" }, { (255 << 16) | ( 0 << 8) | 0, "red" }, { (188 << 16) | (143 << 8) | 143, "rosy brown" }, { (255 << 16) | (193 << 8) | 193, "RosyBrown1" }, { (238 << 16) | (180 << 8) | 180, "RosyBrown2" }, { (205 << 16) | (155 << 8) | 155, "RosyBrown3" }, { (139 << 16) | (105 << 8) | 105, "RosyBrown4" }, { (188 << 16) | (143 << 8) | 143, "RosyBrown" }, { ( 65 << 16) | (105 << 8) | 225, "royal blue" }, { ( 72 << 16) | (118 << 8) | 255, "RoyalBlue1" }, { ( 67 << 16) | (110 << 8) | 238, "RoyalBlue2" }, { ( 58 << 16) | ( 95 << 8) | 205, "RoyalBlue3" }, { ( 39 << 16) | ( 64 << 8) | 139, "RoyalBlue4" }, { ( 65 << 16) | (105 << 8) | 225, "RoyalBlue" }, { (139 << 16) | ( 69 << 8) | 19, "saddle brown" }, { (139 << 16) | ( 69 << 8) | 19, "SaddleBrown" }, { (255 << 16) | (140 << 8) | 105, "salmon1" }, { (238 << 16) | (130 << 8) | 98, "salmon2" }, { (205 << 16) | (112 << 8) | 84, "salmon3" }, { (139 << 16) | ( 76 << 8) | 57, "salmon4" }, { (250 << 16) | (128 << 8) | 114, "salmon" }, { (244 << 16) | (164 << 8) | 96, "sandy brown" }, { (244 << 16) | (164 << 8) | 96, "SandyBrown" }, { ( 46 << 16) | (139 << 8) | 87, "sea green" }, { ( 84 << 16) | (255 << 8) | 159, "SeaGreen1" }, { ( 78 << 16) | (238 << 8) | 148, "SeaGreen2" }, { ( 67 << 16) | (205 << 8) | 128, "SeaGreen3" }, { ( 46 << 16) | (139 << 8) | 87, "SeaGreen4" }, { ( 46 << 16) | (139 << 8) | 87, "SeaGreen" }, { (255 << 16) | (245 << 8) | 238, "seashell1" }, { (238 << 16) | (229 << 8) | 222, "seashell2" }, { (205 << 16) | (197 << 8) | 191, "seashell3" }, { (139 << 16) | (134 << 8) | 130, "seashell4" }, { (255 << 16) | (245 << 8) | 238, "seashell" }, { (255 << 16) | (130 << 8) | 71, "sienna1" }, { (238 << 16) | (121 << 8) | 66, "sienna2" }, { (205 << 16) | (104 << 8) | 57, "sienna3" }, { (139 << 16) | ( 71 << 8) | 38, "sienna4" }, { (160 << 16) | ( 82 << 8) | 45, "sienna" }, { (135 << 16) | (206 << 8) | 235, "sky blue" }, { (135 << 16) | (206 << 8) | 255, "SkyBlue1" }, { (126 << 16) | (192 << 8) | 238, "SkyBlue2" }, { (108 << 16) | (166 << 8) | 205, "SkyBlue3" }, { ( 74 << 16) | (112 << 8) | 139, "SkyBlue4" }, { (135 << 16) | (206 << 8) | 235, "SkyBlue" }, { (106 << 16) | ( 90 << 8) | 205, "slate blue" }, { (112 << 16) | (128 << 8) | 144, "slate gray" }, { (112 << 16) | (128 << 8) | 144, "slate grey" }, { (131 << 16) | (111 << 8) | 255, "SlateBlue1" }, { (122 << 16) | (103 << 8) | 238, "SlateBlue2" }, { (105 << 16) | ( 89 << 8) | 205, "SlateBlue3" }, { ( 71 << 16) | ( 60 << 8) | 139, "SlateBlue4" }, { (106 << 16) | ( 90 << 8) | 205, "SlateBlue" }, { (198 << 16) | (226 << 8) | 255, "SlateGray1" }, { (185 << 16) | (211 << 8) | 238, "SlateGray2" }, { (159 << 16) | (182 << 8) | 205, "SlateGray3" }, { (108 << 16) | (123 << 8) | 139, "SlateGray4" }, { (112 << 16) | (128 << 8) | 144, "SlateGray" }, { (112 << 16) | (128 << 8) | 144, "SlateGrey" }, { (255 << 16) | (250 << 8) | 250, "snow1" }, { (238 << 16) | (233 << 8) | 233, "snow2" }, { (205 << 16) | (201 << 8) | 201, "snow3" }, { (139 << 16) | (137 << 8) | 137, "snow4" }, { (255 << 16) | (250 << 8) | 250, "snow" }, { ( 0 << 16) | (255 << 8) | 127, "spring green" }, { ( 0 << 16) | (255 << 8) | 127, "SpringGreen1" }, { ( 0 << 16) | (238 << 8) | 118, "SpringGreen2" }, { ( 0 << 16) | (205 << 8) | 102, "SpringGreen3" }, { ( 0 << 16) | (139 << 8) | 69, "SpringGreen4" }, { ( 0 << 16) | (255 << 8) | 127, "SpringGreen" }, { ( 70 << 16) | (130 << 8) | 180, "steel blue" }, { ( 99 << 16) | (184 << 8) | 255, "SteelBlue1" }, { ( 92 << 16) | (172 << 8) | 238, "SteelBlue2" }, { ( 79 << 16) | (148 << 8) | 205, "SteelBlue3" }, { ( 54 << 16) | (100 << 8) | 139, "SteelBlue4" }, { ( 70 << 16) | (130 << 8) | 180, "SteelBlue" }, { (255 << 16) | (165 << 8) | 79, "tan1" }, { (238 << 16) | (154 << 8) | 73, "tan2" }, { (205 << 16) | (133 << 8) | 63, "tan3" }, { (139 << 16) | ( 90 << 8) | 43, "tan4" }, { (210 << 16) | (180 << 8) | 140, "tan" }, { (255 << 16) | (225 << 8) | 255, "thistle1" }, { (238 << 16) | (210 << 8) | 238, "thistle2" }, { (205 << 16) | (181 << 8) | 205, "thistle3" }, { (139 << 16) | (123 << 8) | 139, "thistle4" }, { (216 << 16) | (191 << 8) | 216, "thistle" }, { (255 << 16) | ( 99 << 8) | 71, "tomato1" }, { (238 << 16) | ( 92 << 8) | 66, "tomato2" }, { (205 << 16) | ( 79 << 8) | 57, "tomato3" }, { (139 << 16) | ( 54 << 8) | 38, "tomato4" }, { (255 << 16) | ( 99 << 8) | 71, "tomato" }, { ( 0 << 16) | (245 << 8) | 255, "turquoise1" }, { ( 0 << 16) | (229 << 8) | 238, "turquoise2" }, { ( 0 << 16) | (197 << 8) | 205, "turquoise3" }, { ( 0 << 16) | (134 << 8) | 139, "turquoise4" }, { ( 64 << 16) | (224 << 8) | 208, "turquoise" }, { (208 << 16) | ( 32 << 8) | 144, "violet red" }, { (255 << 16) | ( 62 << 8) | 150, "VioletRed1" }, { (238 << 16) | ( 58 << 8) | 140, "VioletRed2" }, { (205 << 16) | ( 50 << 8) | 120, "VioletRed3" }, { (139 << 16) | ( 34 << 8) | 82, "VioletRed4" }, { (208 << 16) | ( 32 << 8) | 144, "VioletRed" }, { (238 << 16) | (130 << 8) | 238, "violet" }, { (255 << 16) | (231 << 8) | 186, "wheat1" }, { (238 << 16) | (216 << 8) | 174, "wheat2" }, { (205 << 16) | (186 << 8) | 150, "wheat3" }, { (139 << 16) | (126 << 8) | 102, "wheat4" }, { (245 << 16) | (222 << 8) | 179, "wheat" }, { (245 << 16) | (245 << 8) | 245, "white smoke" }, { (245 << 16) | (245 << 8) | 245, "WhiteSmoke" }, { (255 << 16) | (255 << 8) | 255, "white" }, { (154 << 16) | (205 << 8) | 50, "yellow green" }, { (255 << 16) | (255 << 8) | 0, "yellow1" }, { (238 << 16) | (238 << 8) | 0, "yellow2" }, { (205 << 16) | (205 << 8) | 0, "yellow3" }, { (139 << 16) | (139 << 8) | 0, "yellow4" }, { (154 << 16) | (205 << 8) | 50, "YellowGreen" }, { (255 << 16) | (255 << 8) | 0, "yellow" }, { 0, NULL } }; smalltalk-3.2.5/packages/blox/tk/Makefile.am0000644000175000017500000000062412123404352015620 00000000000000moduleexec_LTLIBRARIES = blox-tk.la gst_module_ldflags = -rpath $(moduleexecdir) -release $(VERSION) -module \ -no-undefined -export-symbols-regex gst_initModule blox_tk_la_SOURCES = BloxTK.c blox_tk_la_LIBADD = @LIBTCLTK@ $(top_builddir)/lib-src/library.la blox_tk_la_LDFLAGS = $(gst_module_ldflags) AM_CPPFLAGS = -I$(top_srcdir)/libgst -I$(top_srcdir)/lib-src @INCTCLTK@ noinst_HEADERS = rgbtab.h smalltalk-3.2.5/packages/blox/tk/BloxText.st0000644000175000017500000012455312123404352015715 00000000000000"====================================================================== | | Smalltalk Tk-based GUI building blocks (text widget). | | ======================================================================" "====================================================================== | | Copyright 1999,2000,2001,2002,2004,2009 Free Software Foundation, Inc. | Written by Paolo Bonzini. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LESSER. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" BViewport subclass: BText [ | callback tagInfo images | BText class >> emacsLike [ "Answer whether we are using Emacs or Motif key bindings." self tclEval: 'return $tk_strictMotif'. ^self tclResult = '0' ] BText class >> emacsLike: aBoolean [ "Set whether we are using Emacs or Motif key bindings." self tclEval: 'set tk_strictMotif ' , (aBoolean ifTrue: ['0'] ifFalse: ['1']) ] BText class >> newReadOnly: parent [ "Answer a new read-only text widget (read-only is achieved simply by setting its state to be disabled)" | ctl | ctl := self new: parent. ctl tclEval: ctl connected , ' configure -state disabled'. ^ctl ] backgroundColor [ "Answer the value of the backgroundColor option for the widget. Specifies the normal background color to use when displaying the widget." self properties at: #background ifPresent: [:value | ^value]. self tclEval: '%1 cget -background' with: self connected with: self container. ^self properties at: #background put: self tclResult ] backgroundColor: value [ "Set the value of the backgroundColor option for the widget. Specifies the normal background color to use when displaying the widget." self tclEval: '%1 configure -background %3' with: self connected with: self container with: value asTkString. self properties at: #background put: value ] callback [ "Answer a DirectedMessage that is sent when the receiver is modified, or nil if none has been set up." ^callback ] callback: aReceiver message: aSymbol [ "Set up so that aReceiver is sent the aSymbol message (the name of a zero- or one-argument selector) when the receiver is modified. If the method accepts an argument, the receiver is passed." | arguments selector numArgs | selector := aSymbol asSymbol. numArgs := selector numArgs. arguments := #(). numArgs = 1 ifTrue: [arguments := Array with: self]. callback := DirectedMessage selector: selector arguments: arguments receiver: aReceiver ] contents [ "Return the contents of the widget" self tclEval: self connected , ' get 1.0 end-1c'. ^self tclResult ] contents: aString [ "Set the contents of the widget" self tclEval: '%1 delete 1.0 end %1 insert 1.0 %2 %1 see 1.0' with: self connected with: aString asTkString ] font [ "Answer the value of the font option for the widget. Specifies the font to use when drawing text inside the widget. The font can be given as either an X font name or a Blox font description string. X font names are given as many fields, each led by a minus, and each of which can be replaced by an * to indicate a default value is ok: foundry, family, weight, slant, setwidth, addstyle, pixel size, point size (the same as pixel size for historical reasons), horizontal resolution, vertical resolution, spacing, width, charset and character encoding. Blox font description strings have three fields, which must be separated by a space and of which only the first is mandatory: the font family, the font size in points (or in pixels if a negative value is supplied), and a number of styles separated by a space (valid styles are normal, bold, italic, underline and overstrike). Examples of valid fonts are ``Helvetica 10 Bold'', ``Times -14'', ``Futura Bold Underline''. You must enclose the font family in braces if it is made of two or more words." self properties at: #font ifPresent: [:value | ^value]. self tclEval: '%1 cget -font' with: self connected with: self container. ^self properties at: #font put: self tclResult ] font: value [ "Set the value of the font option for the widget. Specifies the font to use when drawing text inside the widget. The font can be given as either an X font name or a Blox font description string. X font names are given as many fields, each led by a minus, and each of which can be replaced by an * to indicate a default value is ok: foundry, family, weight, slant, setwidth, addstyle, pixel size, point size (the same as pixel size for historical reasons), horizontal resolution, vertical resolution, spacing, width, charset and character encoding. Blox font description strings have three fields, which must be separated by a space and of which only the first is mandatory: the font family, the font size in points (or in pixels if a negative value is supplied), and a number of styles separated by a space (valid styles are normal, bold, italic, underline and overstrike). Examples of valid fonts are ``Helvetica 10 Bold'', ``Times -14'', ``Futura Bold Underline''. You must enclose the font family in braces if it is made of two or more words." self tclEval: '%1 configure -font %3' with: self connected with: self container with: value asTkString. self properties at: #font put: value ] foregroundColor [ "Answer the value of the foregroundColor option for the widget. Specifies the normal foreground color to use when displaying the widget." self properties at: #foreground ifPresent: [:value | ^value]. self tclEval: '%1 cget -foreground' with: self connected with: self container. ^self properties at: #foreground put: self tclResult ] foregroundColor: value [ "Set the value of the foregroundColor option for the widget. Specifies the normal foreground color to use when displaying the widget." self tclEval: '%1 configure -foreground %3' with: self connected with: self container with: value asTkString. self properties at: #foreground put: value ] getSelection [ "Answer an empty string if the widget has no selection, else answer the currently selected text" | result | self tclEval: ' if { [%1 tag ranges sel] == {} } then { return {} } %1 get sel.first sel.last' with: self connected. result := self tclResult. ^result isEmpty ifTrue: [nil] ifFalse: [result] ] selectBackground [ "Answer the value of the selectBackground option for the widget. Specifies the background color to use when displaying selected parts of the widget." self properties at: #selectbackground ifPresent: [:value | ^value]. self tclEval: '%1 cget -selectbackground' with: self connected with: self container. ^self properties at: #selectbackground put: self tclResult ] selectBackground: value [ "Set the value of the selectBackground option for the widget. Specifies the background color to use when displaying selected parts of the widget." self tclEval: '%1 configure -selectbackground %3' with: self connected with: self container with: value asTkString. self properties at: #selectbackground put: value ] selectForeground [ "Answer the value of the selectForeground option for the widget. Specifies the foreground color to use when displaying selected parts of the widget." self properties at: #selectforeground ifPresent: [:value | ^value]. self tclEval: '%1 cget -selectforeground' with: self connected with: self container. ^self properties at: #selectforeground put: self tclResult ] selectForeground: value [ "Set the value of the selectForeground option for the widget. Specifies the foreground color to use when displaying selected parts of the widget." self tclEval: '%1 configure -selectforeground %3' with: self connected with: self container with: value asTkString. self properties at: #selectforeground put: value ] wrap [ "Answer the value of the wrap option for the widget. Specifies how to handle lines in the text that are too long to be displayed in a single line of the text's window. The value must be #none or #char or #word. A wrap mode of none means that each line of text appears as exactly one line on the screen; extra characters that do not fit on the screen are not displayed. In the other modes each line of text will be broken up into several screen lines if necessary to keep all the characters visible. In char mode a screen line break may occur after any character; in word mode a line break will only be made at word boundaries." self properties at: #wrap ifPresent: [:value | ^value]. self tclEval: '%1 cget -wrap' with: self connected with: self container. ^self properties at: #wrap put: self tclResult asSymbol ] wrap: value [ "Set the value of the wrap option for the widget. Specifies how to handle lines in the text that are too long to be displayed in a single line of the text's window. The value must be #none or #char or #word. A wrap mode of none means that each line of text appears as exactly one line on the screen; extra characters that do not fit on the screen are not displayed. In the other modes each line of text will be broken up into several screen lines if necessary to keep all the characters visible. In char mode a screen line break may occur after any character; in word mode a line break will only be made at word boundaries." self tclEval: '%1 configure -wrap %3' with: self connected with: self container with: value asTkString. self properties at: #wrap put: value ] insertAtEnd: aString attribute: attr [ "Clear the selection and append aString at the end of the widget. Use the given attributes to format the text." attr isNil ifTrue: [^self insertAtEnd: aString]. tagInfo isNil ifTrue: [tagInfo := BTextTags new: self]. self tclEval: '%1 tag remove sel 1.0 end %1 insert end %2%3' with: self connected with: aString asTkString with: (attr tags: tagInfo) ] insertText: aString attribute: attr [ "Insert aString in the widget at the current insertion point, replacing the currently selected text (if any). Use the given attributes to format the text." attr isNil ifTrue: [^self insertText: aString]. tagInfo isNil ifTrue: [tagInfo := BTextTags new: self]. self tclEval: '%1 delete sel.first sel.last %1 insert insert %2 %3 %1 see insert' with: self connected with: aString asTkString with: (attr tags: tagInfo) ] removeAttributes [ "Remove any kind of formatting from the text in the widget" tagInfo isNil ifTrue: [^self]. self removeAttributesInside: '1.0 end'. tagInfo initialize: self ] removeAttributesFrom: aPoint to: endPoint [ "Remove any kind of formatting from the text in the widget between the given endpoints. The two endpoints are Point objects in which both coordinates are 1-based: the first line is line 1, and the first character in the first line is character 1." tagInfo isNil ifTrue: [^self]. self removeAttributesInside: (self from: aPoint to: endPoint) ] setAttributes: attr from: aPoint to: endPoint [ "Add the formatting given by attr to the text in the widget between the given endpoints. The two endpoints are Point objects in which both coordinates are 1-based: the first line is line 1, and the first character in the first line is character 1." attr isNil ifTrue: [^self]. tagInfo isNil ifTrue: [tagInfo := BTextTags new: self]. self tclEval: 'foreach tag %2 { %1 tag add $tag %3 }' with: self connected with: (attr tags: tagInfo) with: (self from: aPoint to: endPoint) ] child: child height: value [ "Set the height of the given child to be `value' pixels." | width height | height := self at: #heightGeom put: value asInteger. width := self at: #widthGeom ifAbsentPut: [self widthAbsolute] "self tclEval: 'wm geometry %1 =%2x%3' with: child container with: width printString with: height printString" ] child: child heightOffset: value [ "Adjust the height of the given child to be given by `value' more pixels." self child: child height: (self heightChild: child) + value ] child: child width: value [ "Set the width of the given child to be `value' pixels." | width height | width := self at: #widthGeom put: value asInteger. height := self at: #heightGeom ifAbsentPut: [child heightAbsolute] "self tclEval: 'wm geometry %1 =%2x%3' with: child container with: width printString with: height printString" ] child: child widthOffset: value [ "Adjust the width of the given child to be given by `value' more pixels." self child: child width: (self widthChild: child) + value ] child: child x: value [ "Never fail and do nothing, the children stay where the text ended at the time each child was added in the widget" ] child: child xOffset: value [ self shouldNotImplement ] child: child y: value [ "Never fail and do nothing, the children stay where the text ended at the time each child was added in the widget" ] child: child yOffset: value [ self shouldNotImplement ] heightChild: child [ "Answer the given child's height in pixels." ^child at: #heightGeom ifAbsentPut: [child heightAbsolute] ] widthChild: child [ "Answer the given child's width in pixels." ^child at: #widthGeom ifAbsentPut: [child widthAbsolute] ] xChild: child [ "Answer the given child's top-left border's x coordinate. We always answer 0 since the children actually move when the text widget scrolls" ^0 ] yChild: child [ "Answer the given child's top-left border's y coordinate. We always answer 0 since the children actually move when the text widget scrolls" ^0 ] insertImage: anObject [ "Insert an image where the insertion point currently lies in the widget. anObject can be a String containing image data (either Base-64 encoded GIF data, XPM data, or PPM data), or the result or registering an image with #registerImage:" | key | key := self registerImage: anObject. self tclEval: '%1 image create insert -align baseline -image %2' with: self connected with: key value. ^key ] insertImage: anObject at: position [ "Insert an image at the given position in the widget. The position is a Point object in which both coordinates are 1-based: the first line is line 1, and the first character in the first line is character 1. anObject can be a String containing image data (either Base-64 encoded GIF data, XPM data, or PPM data), or the result or registering an image with #registerImage:" | key | key := self registerImage: anObject. self tclEval: '%1 image create %2.%3 -align baseline -image %4' with: self connected with: position y printString with: (position x - 1) printString with: key value. ^key ] insertImageAtEnd: anObject [ "Insert an image at the end of the widgets text. anObject can be a String containing image data (either Base-64 encoded GIF data, XPM data, or PPM data), or the result or registering an image with #registerImage:" | key | key := self registerImage: anObject. self tclEval: '%1 image create end -align baseline -image %2' with: self connected with: key value. ^key ] registerImage: anObject [ "Register an image (whose data is in anObject, a String including Base-64 encoded GIF data, XPM data, or PPM data) to be used in the widget. If the same image must be used a lot of times, it is better to register it once and then pass the result of #registerImage: to the image insertion methods. Registered image are private within each BText widget. Registering an image with a widget and using it with another could give unpredictable results." | imageName | anObject class == ValueHolder ifTrue: [^anObject]. self tclEval: 'image create photo -data ' , anObject asTkImageString. images isNil ifTrue: [images := OrderedCollection new]. imageName := images add: self tclResult. ^ValueHolder with: imageName ] insertAtEnd: aString [ "Clear the selection and append aString at the end of the widget." self tclEval: '%1 tag remove sel 1.0 end %1 insert end %2' with: self connected with: aString asTkString ] insertSelectedText: aString [ "Insert aString in the widget at the current insertion point, leaving the currently selected text (if any) in place, and selecting the text." self tclEval: '%1 tag remove sel 1.0 end %1 insert insert %2 { sel } %1 see insert' with: self connected with: aString asTkString ] insertText: aString [ "Insert aString in the widget at the current insertion point, replacing the currently selected text (if any)." self tclEval: 'catch { %1 delete sel.first sel.last } %1 insert insert %2 %1 see insert' with: self connected with: aString asTkString ] insertText: aString at: position [ "Insert aString in the widget at the given position, replacing the currently selected text (if any). The position is a Point object in which both coordinates are 1-based: the first line is line 1, and the first character in the first line is character 1." self tclEval: '%1 delete sel.first sel.last %1 insert %2.%3 %4 %1 see insert' with: self connected with: position y printString with: (position x - 1) printString with: aString asTkString ] insertTextSelection: aString [ "Insert aString in the widget after the current selection, leaving the currently selected text (if any) intact." self tclEval: 'catch { %1 mark set insert sel.last } %1 tag remove sel 1.0 end %1 insert insert %2 { sel } %1 see insert' with: self connected with: aString asTkString ] invokeCallback [ "Generate a synthetic callback." self callback isNil ifFalse: [self callback send] ] nextPut: aCharacter [ "Clear the selection and append aCharacter at the end of the widget." self insertAtEnd: (String with: aCharacter) ] nextPutAll: aString [ "Clear the selection and append aString at the end of the widget." self insertAtEnd: aString ] nl [ "Clear the selection and append a linefeed character at the end of the widget." self insertAtEnd: Character nl asString ] refuseTabs [ "Arrange so that Tab characters, instead of being inserted in the widget, traverse the widgets in the parent window." self tclEval: ' bind %1 { focus [tk_focusNext %W] break } bind %1 { focus [tk_focusPrev %W] break }' with: self connected ] replaceSelection: aString [ "Insert aString in the widget at the current insertion point, replacing the currently selected text (if any), and leaving the text selected." self tclEval: 'catch { %1 delete sel.first sel.last } %1 insert insert %2 { sel } %1 see insert' with: self connected with: aString asTkString ] searchString: aString [ "Search aString in the widget. If it is not found, answer zero, else answer the 1-based line number and move the insertion point to the place where the string was found." | result | self tclEval: self connected , ' search ' , aString asTkString , ' 1.0 end'. result := self tclResult. result isEmpty ifTrue: [^0]. self tclEval: ' %1 mark set insert %2 %1 see insert' with: self connected with: result. "Sending asInteger removes the column" ^result asInteger ] space [ "Clear the selection and append a space at the end of the widget." self insertAtEnd: ' ' ] charsInLine: number [ "Answer how many characters are there in the number-th line" | stream | self tclEval: self connected , ' index ' , number printString , '.end'. stream := ReadStream on: self tclResult. stream skipTo: $.. ^stream upToEnd asInteger + 1 ] currentColumn [ "Answer the 1-based column number where the insertion point currently lies." | stream | self tclEval: self connected , ' index insert'. stream := ReadStream on: self tclResult. stream skipTo: $.. ^stream upToEnd asInteger + 1 ] currentLine [ "Answer the 1-based line number where the insertion point currently lies." | stream | self tclEval: self connected , ' index insert'. stream := ReadStream on: self tclResult. ^(stream upTo: $.) asInteger ] currentPosition [ "Answer a Point representing where the insertion point currently lies. Both coordinates in the answer are 1-based: the first line is line 1, and the first character in the first line is character 1." self tclEval: self connected , ' index insert'. ^self parseResult ] currentPosition: aPoint [ "Move the insertion point to the position given by aPoint. Both coordinates in aPoint are interpreted as 1-based: the first line is line 1, and the first character in the first line is character 1." self tclEval: ' %1 mark set insert %2.%3 %1 see insert' with: self connected with: aPoint y printString with: (aPoint x - 1) printString ] gotoLine: line end: aBoolean [ "If aBoolean is true, move the insertion point to the last character of the line-th line (1 being the first line in the widget); if aBoolean is false, move it to the start of the line-th line." | code | code := aBoolean ifTrue: ['%1 mark set insert "%2.0 -1l lineend"'] ifFalse: ['%1 mark set insert %2.0']. self tclEval: code with: self connected with: line printString. self tclEval: self connected , ' see insert'. ^1 ] indexAt: point [ "Answer the position of the character that covers the pixel whose coordinates within the text's window are given by the supplied Point object." self tclEval: self connected , ' index @%1,%2' with: point x printString with: point y printString. ^self parseResult ] lineAt: number [ "Answer the number-th line of text in the widget" self tclEval: self connected , ' get %1.0 %1.end' with: number printString. ^self tclResult ] numberOfLines [ "Answer the number of lines in the widget" | stream | self tclEval: self connected , ' index end-1c'. stream := ReadStream on: self tclResult. ^(stream upTo: $.) asInteger ] selectFrom: first to: last [ "Select the text between the given endpoints. The two endpoints are Point objects in which both coordinates are 1-based: the first line is line 1, and the first character in the first line is character 1." self tclEval: '%1 tag remove sel 1.0 end %1 tag add sel %2' with: self connected with: (self from: first to: last) ] setToEnd [ "Move the insertion point to the end of the widget" self tclEval: ' %1 mark set insert end-1c %1 see end' with: self connected ] addChild: child [ self tclEval: '%1 window create end -window %2' with: self connected with: child container. ^self basicAddChild: child ] create [ self create: ' -wrap word -font {' , self class defaultFont , '} \ -state normal -highlightthickness 0 -takefocus 1'; horizontal: true; vertical: true. "This hack gets the callback upon insert or delete; see Tk FAQ by Jeffrey Hobbs (jeff.hobbs@acm.org)" self tclEval: ' rename %1 .%1 proc %1 args { if [regexp {^(ins|del).*} [lindex $args 0]] { callback %2 invokeCallback } uplevel .%1 $args }' with: self connected with: self asOop printString ] defineTag: name as: options [ self tclEval: '%1 tag configure %2 %3 %1 tag raise sel %2' with: self connected with: name with: options ] destroyed [ super destroyed. images isNil ifTrue: [^self]. images do: [:name | self tclEval: 'image delete ' , name]. images := nil ] from: aPoint to: endPoint [ ^'%1.%2 %3.%4' % {aPoint y printString. (aPoint x - 1) printString. endPoint y printString. (endPoint x - 1) printString} ] parseResult [ | stream y | stream := ReadStream on: self tclResult. y := (stream upTo: $.) asInteger. ^(stream upToEnd asInteger + 1) @ y ] removeAttributesInside: range [ self tclEval: 'foreach tag [ %1 tag names ] { if { $tag != "sel" } then { %1 tag remove $tag %2 } }' with: self connected with: range ] tag: name bind: event to: aSymbol of: anObject parameters: params [ self bind: event to: aSymbol of: anObject parameters: params prefix: '%1 tag bind %2' % {self connected. name} ] widgetType [ ^'text ' ] ] BEventTarget subclass: BTextBindings [ | list tagName | BTextBindings class >> new [ "Create a new instance of the receiver." ^self basicNew initialize ] defineTagFor: aBText [ list do: [:each | each sendTo: aBText] ] tagName [ ^tagName ] initialize [ tagName := 'ev' , (Time millisecondClockValue printString: 36). list := OrderedCollection new ] primBind: event to: aSymbol of: anObject parameters: params [ | args | (args := Array new: 5) at: 1 put: tagName; at: 2 put: event; at: 3 put: aSymbol; at: 4 put: anObject; at: 5 put: params. list add: (Message selector: #tag:bind:to:of:parameters: arguments: args) ] ] Object subclass: BTextAttributes [ | bgColor fgColor font styles events | BTextAttributes class >> backgroundColor: color [ "Create a new BTextAttributes object resulting in text with the given background color." ^self new backgroundColor: color ] BTextAttributes class >> black [ "Create a new BTextAttributes object resulting in black text." ^self new foregroundColor: 'black' ] BTextAttributes class >> blue [ "Create a new BTextAttributes object resulting in blue text." ^self new foregroundColor: 'blue' ] BTextAttributes class >> center [ "Create a new BTextAttributes object resulting in centered paragraphs." ^self new center ] BTextAttributes class >> cyan [ "Create a new BTextAttributes object resulting in cyan text." ^self new foregroundColor: 'cyan' ] BTextAttributes class >> darkCyan [ "Create a new BTextAttributes object resulting in dark cyan text." ^self new foregroundColor: 'PureDarkCyan' ] BTextAttributes class >> darkGreen [ "Create a new BTextAttributes object resulting in dark green text." ^self new foregroundColor: 'PureDarkGreen' ] BTextAttributes class >> darkMagenta [ "Create a new BTextAttributes object resulting in dark purple text." ^self new foregroundColor: 'PureDarkMagenta' ] BTextAttributes class >> events: aBTextBindings [ "Create a new BTextAttributes object for text that responds to events according to the callbacks established in aBTextBindings." ^self new events: aBTextBindings ] BTextAttributes class >> font: font [ "Create a new BTextAttributes object resulting in text with the given font. The font can be given as either an X font name or a Blox font description string. X font names are given as many fields, each led by a minus, and each of which can be replaced by an * to indicate a default value is ok: foundry, family, weight, slant, setwidth, addstyle, pixel size, point size (the same as pixel size for historical reasons), horizontal resolution, vertical resolution, spacing, width, charset and character encoding. Blox font description strings have three fields, which must be separated by a space and of which only the first is mandatory: the font family, the font size in points (or in pixels if a negative value is supplied), and a number of styles separated by a space (valid styles are normal, bold, italic, underline and overstrike). Examples of valid fonts are ``Helvetica 10 Bold'', ``Times -14'', ``Futura Bold Underline''. You must enclose the font family in braces if it is made of two or more words." ^self new font: font ] BTextAttributes class >> foregroundColor: color [ "Create a new BTextAttributes object resulting in text with the given foreground color." ^self new foregroundColor: color ] BTextAttributes class >> green [ "Create a new BTextAttributes object resulting in green text." ^self new foregroundColor: 'green' ] BTextAttributes class >> magenta [ "Create a new BTextAttributes object resulting in magenta text." ^self new foregroundColor: 'magenta' ] BTextAttributes class >> red [ "Create a new BTextAttributes object resulting in red text." ^self new foregroundColor: 'red' ] BTextAttributes class >> strikeout [ "Create a new BTextAttributes object resulting in struck-out text." ^self new strikeout ] BTextAttributes class >> underline [ "Create a new BTextAttributes object resulting in underlined text." ^self new underline ] BTextAttributes class >> yellow [ "Create a new BTextAttributes object resulting in yellow text." ^self new foregroundColor: 'yellow' ] BTextAttributes class >> white [ "Create a new BTextAttributes object resulting in white text." ^self new foregroundColor: 'white' ] black [ "Set the receiver so that applying it results in black text." self foregroundColor: 'black' ] blue [ "Set the receiver so that applying it results in blue text." self foregroundColor: 'blue' ] cyan [ "Set the receiver so that applying it results in cyan text." self foregroundColor: 'cyan' ] darkCyan [ "Set the receiver so that applying it results in dark cyan text." self foregroundColor: 'PureDarkCyan' ] darkGreen [ "Set the receiver so that applying it results in dark green text." self foregroundColor: 'PureDarkGreen' ] darkMagenta [ "Set the receiver so that applying it results in dark magenta text." self foregroundColor: 'PureDarkMagenta' ] green [ "Set the receiver so that applying it results in green text." self foregroundColor: 'green' ] magenta [ "Set the receiver so that applying it results in magenta text." self foregroundColor: 'magenta' ] red [ "Set the receiver so that applying it results in red text." self foregroundColor: 'red' ] white [ "Set the receiver so that applying it results in white text." self foregroundColor: 'white' ] yellow [ "Set the receiver so that applying it results in black text." self foregroundColor: 'yellow' ] hasStyle: aSymbol [ ^styles notNil and: [styles includes: aSymbol] ] style: aSymbol [ styles isNil ifTrue: [styles := Set new]. styles add: aSymbol ] tags: aBTextTags [ | s | s := WriteStream on: (String new: 20). s nextPutAll: ' {'. fgColor isNil ifFalse: [s nextPutAll: (aBTextTags fgColor: fgColor)]. bgColor isNil ifFalse: [s nextPutAll: (aBTextTags bgColor: bgColor)]. font isNil ifFalse: [s nextPutAll: (aBTextTags font: font)]. events isNil ifFalse: [s nextPutAll: (aBTextTags events: events)]. styles isNil ifFalse: [styles do: [:each | s nextPut: $ ; nextPutAll: each]]. s nextPut: $}. ^s contents ] backgroundColor [ "Answer the value of the backgroundColor option for the text. Specifies the background color to use when displaying text with these attributes. nil indicates that the default value is not overridden." ^bgColor ] backgroundColor: color [ "Set the value of the backgroundColor option for the text. Specifies the background color to use when displaying text with these attributes. nil indicates that the default value is not overridden." bgColor := color ] center [ "Center the text to which these attributes are applied" self style: #STYLEcenter ] events [ "Answer the event bindings which apply to text subject to these attributes" ^events ] events: aBTextBindings [ "Set the event bindings which apply to text subject to these attributes" events := aBTextBindings ] font [ "Answer the value of the font option for the text. The font can be given as either an X font name or a Blox font description string, or nil if you want the widget's default font to apply. X font names are given as many fields, each led by a minus, and each of which can be replaced by an * to indicate a default value is ok: foundry, family, weight, slant, setwidth, addstyle, pixel size, point size (the same as pixel size for historical reasons), horizontal resolution, vertical resolution, spacing, width, charset and character encoding. Blox font description strings have three fields, which must be separated by a space and of which only the first is mandatory: the font family, the font size in points (or in pixels if a negative value is supplied), and a number of styles separated by a space (valid styles are normal, bold, italic, underline and overstrike). Examples of valid fonts are ``Helvetica 10 Bold'', ``Times -14'', ``Futura Bold Underline''. You must enclose the font family in braces if it is made of two or more words." ^font ] font: fontName [ "Set the value of the font option for the text. The font can be given as either an X font name or a Blox font description string, or nil if you want the widget's default font to apply. X font names are given as many fields, each led by a minus, and each of which can be replaced by an * to indicate a default value is ok: foundry, family, weight, slant, setwidth, addstyle, pixel size, point size (the same as pixel size for historical reasons), horizontal resolution, vertical resolution, spacing, width, charset and character encoding. Blox font description strings have three fields, which must be separated by a space and of which only the first is mandatory: the font family, the font size in points (or in pixels if a negative value is supplied), and a number of styles separated by a space (valid styles are normal, bold, italic, underline and overstrike). Examples of valid fonts are ``Helvetica 10 Bold'', ``Times -14'', ``Futura Bold Underline''. You must enclose the font family in braces if it is made of two or more words." font := fontName ] foregroundColor [ "Answer the value of the foregroundColor option for the text. Specifies the foreground color to use when displaying text with these attributes. nil indicates that the default value is not overridden." ^fgColor ] foregroundColor: color [ "Set the value of the foregroundColor option for the text. Specifies the foreground color to use when displaying text with these attributes. nil indicates that the default value is not overridden." fgColor := color ] isCentered [ "Answer whether the text to which these attributes are applied is centered" ^self hasStyle: #STYLEcenter ] isStruckout [ "Answer whether the text to which these attributes are applied is struckout" ^self hasStyle: #STYLEstrikeout ] isUnderlined [ "Answer whether the text to which these attributes are applied is underlined" ^self hasStyle: #STYLEunderline ] strikeout [ "Strike out the text to which these attributes are applied" self style: #STYLEstrikeout ] underline [ "Underline the text to which these attributes are applied" self style: #STYLEunderline ] ] Object subclass: BTextTags [ | client tags | BTextTags class >> new [ self shouldNotImplement ] BTextTags class >> new: client [ ^super new initialize: client ] bgColor: color [ ^' b_' , (self color: color) ] events: aBTextBindings [ | tagName | tagName := aBTextBindings tagName. (tags includes: tagName) ifFalse: [tags add: tagName. aBTextBindings defineTagFor: client]. ^' ' , tagName ] fgColor: color [ ^' f_' , (self color: color) ] font: font [ | tagName | tagName := WriteStream on: (String new: 20). font substrings do: [:each | tagName nextPutAll: each; nextPut: $_]. tagName := tagName contents. (tags includes: tagName) ifFalse: [tags add: tagName. client defineTag: tagName as: ' -font {' , font , '}']. ^' ' , tagName ] color: color [ | tagName | tagName := (color at: 1) = $# ifTrue: [(color copy) at: 1 put: $_; yourself] ifFalse: [color asLowercase]. (tags includes: tagName) ifFalse: [tags add: tagName. client defineTag: 'f_' , tagName as: ' -foreground ' , color. client defineTag: 'b_' , tagName as: ' -background ' , color]. ^tagName ] initialize: clientBText [ client := clientBText. tags := Set new. client defineTag: 'STYLEstrikeout' as: ' -overstrike 1'. client defineTag: 'STYLEunderline' as: ' -underline 1'. client defineTag: 'STYLEcenter' as: ' -justify center' ] ] "-------------------------- BText class -----------------------------" "-------------------------- BTextBindings class -----------------------------" "-------------------------- BTextAttributes class -----------------------------" "-------------------------- BTextTags class -----------------------------" smalltalk-3.2.5/packages/blox/tk/Makefile.in0000644000175000017500000005301012130455426015634 00000000000000# Makefile.in generated by automake 1.11.6 from Makefile.am. # @configure_input@ # Copyright (C) 1994, 1995, 1996, 1997, 1998, 1999, 2000, 2001, 2002, # 2003, 2004, 2005, 2006, 2007, 2008, 2009, 2010, 2011 Free Software # Foundation, Inc. # This Makefile.in is free software; the Free Software Foundation # gives unlimited permission to copy and/or distribute it, # with or without modifications, as long as this notice is preserved. # This program is distributed in the hope that it will be useful, # but WITHOUT ANY WARRANTY, to the extent permitted by law; without # even the implied warranty of MERCHANTABILITY or FITNESS FOR A # PARTICULAR PURPOSE. @SET_MAKE@ VPATH = @srcdir@ am__make_dryrun = \ { \ am__dry=no; \ case $$MAKEFLAGS in \ *\\[\ \ ]*) \ echo 'am--echo: ; @echo "AM" OK' | $(MAKE) -f - 2>/dev/null \ | grep '^AM OK$$' >/dev/null || am__dry=yes;; \ *) \ for am__flg in $$MAKEFLAGS; do \ case $$am__flg in \ *=*|--*) ;; \ *n*) am__dry=yes; break;; \ esac; \ done;; \ esac; \ test $$am__dry = yes; \ } pkgdatadir = $(datadir)/@PACKAGE@ pkgincludedir = $(includedir)/@PACKAGE@ pkglibdir = $(libdir)/@PACKAGE@ pkglibexecdir = $(libexecdir)/@PACKAGE@ am__cd = CDPATH="$${ZSH_VERSION+.}$(PATH_SEPARATOR)" && cd install_sh_DATA = $(install_sh) -c -m 644 install_sh_PROGRAM = $(install_sh) -c install_sh_SCRIPT = $(install_sh) -c INSTALL_HEADER = $(INSTALL_DATA) transform = $(program_transform_name) NORMAL_INSTALL = : PRE_INSTALL = : POST_INSTALL = : NORMAL_UNINSTALL = : PRE_UNINSTALL = : POST_UNINSTALL = : build_triplet = @build@ host_triplet = @host@ subdir = packages/blox/tk DIST_COMMON = $(noinst_HEADERS) $(srcdir)/Makefile.am \ $(srcdir)/Makefile.in ChangeLog ACLOCAL_M4 = $(top_srcdir)/aclocal.m4 am__aclocal_m4_deps = $(top_srcdir)/build-aux/bold.m4 \ $(top_srcdir)/build-aux/codeset.m4 \ $(top_srcdir)/build-aux/emacs-pkg.m4 \ $(top_srcdir)/build-aux/emacs-site-start.m4 \ $(top_srcdir)/build-aux/ext_goto.m4 \ $(top_srcdir)/build-aux/gawk.m4 $(top_srcdir)/build-aux/gcc.m4 \ $(top_srcdir)/build-aux/gl.m4 \ $(top_srcdir)/build-aux/glib-2.0.m4 \ $(top_srcdir)/build-aux/glut.m4 $(top_srcdir)/build-aux/gmp.m4 \ $(top_srcdir)/build-aux/gst-package.m4 \ $(top_srcdir)/build-aux/gtk-2.0.m4 \ $(top_srcdir)/build-aux/iconv.m4 \ $(top_srcdir)/build-aux/lib-ld.m4 \ $(top_srcdir)/build-aux/lib-link.m4 \ $(top_srcdir)/build-aux/lib-prefix.m4 \ $(top_srcdir)/build-aux/lib.m4 \ $(top_srcdir)/build-aux/libc-so-name.m4 \ $(top_srcdir)/build-aux/libtool.m4 \ $(top_srcdir)/build-aux/lightning.m4 \ $(top_srcdir)/build-aux/ln.m4 \ $(top_srcdir)/build-aux/localtime.m4 \ $(top_srcdir)/build-aux/lock.m4 \ $(top_srcdir)/build-aux/long-double.m4 \ $(top_srcdir)/build-aux/lrint.m4 \ $(top_srcdir)/build-aux/ltdl-gst.m4 \ $(top_srcdir)/build-aux/ltoptions.m4 \ $(top_srcdir)/build-aux/ltsugar.m4 \ $(top_srcdir)/build-aux/ltversion.m4 \ $(top_srcdir)/build-aux/lt~obsolete.m4 \ $(top_srcdir)/build-aux/modules.m4 \ $(top_srcdir)/build-aux/pkg.m4 $(top_srcdir)/build-aux/poll.m4 \ $(top_srcdir)/build-aux/readline.m4 \ $(top_srcdir)/build-aux/relocatable.m4 \ $(top_srcdir)/build-aux/setenv.m4 \ $(top_srcdir)/build-aux/snprintfv.m4 \ $(top_srcdir)/build-aux/sockets.m4 \ $(top_srcdir)/build-aux/sockpfaf.m4 \ $(top_srcdir)/build-aux/strtoul.m4 \ $(top_srcdir)/build-aux/sync-builtins.m4 \ $(top_srcdir)/build-aux/tcltk.m4 \ $(top_srcdir)/build-aux/version.m4 \ $(top_srcdir)/build-aux/vis-hidden.m4 \ $(top_srcdir)/build-aux/wine.m4 $(top_srcdir)/configure.ac am__configure_deps = $(am__aclocal_m4_deps) $(CONFIGURE_DEPENDENCIES) \ $(ACLOCAL_M4) mkinstalldirs = $(install_sh) -d CONFIG_HEADER = $(top_builddir)/config.h CONFIG_CLEAN_FILES = CONFIG_CLEAN_VPATH_FILES = am__vpath_adj_setup = srcdirstrip=`echo "$(srcdir)" | sed 's|.|.|g'`; am__vpath_adj = case $$p in \ $(srcdir)/*) f=`echo "$$p" | sed "s|^$$srcdirstrip/||"`;; \ *) f=$$p;; \ esac; am__strip_dir = f=`echo $$p | sed -e 's|^.*/||'`; am__install_max = 40 am__nobase_strip_setup = \ srcdirstrip=`echo "$(srcdir)" | sed 's/[].[^$$\\*|]/\\\\&/g'` am__nobase_strip = \ for p in $$list; do echo "$$p"; done | sed -e "s|$$srcdirstrip/||" am__nobase_list = $(am__nobase_strip_setup); \ for p in $$list; do echo "$$p $$p"; done | \ sed "s| $$srcdirstrip/| |;"' / .*\//!s/ .*/ ./; s,\( .*\)/[^/]*$$,\1,' | \ $(AWK) 'BEGIN { files["."] = "" } { files[$$2] = files[$$2] " " $$1; \ if (++n[$$2] == $(am__install_max)) \ { print $$2, files[$$2]; n[$$2] = 0; files[$$2] = "" } } \ END { for (dir in files) print dir, files[dir] }' am__base_list = \ sed '$$!N;$$!N;$$!N;$$!N;$$!N;$$!N;$$!N;s/\n/ /g' | \ sed '$$!N;$$!N;$$!N;$$!N;s/\n/ /g' am__uninstall_files_from_dir = { \ test -z "$$files" \ || { test ! -d "$$dir" && test ! -f "$$dir" && test ! -r "$$dir"; } \ || { echo " ( cd '$$dir' && rm -f" $$files ")"; \ $(am__cd) "$$dir" && rm -f $$files; }; \ } am__installdirs = "$(DESTDIR)$(moduleexecdir)" LTLIBRARIES = $(moduleexec_LTLIBRARIES) blox_tk_la_DEPENDENCIES = $(top_builddir)/lib-src/library.la am_blox_tk_la_OBJECTS = BloxTK.lo blox_tk_la_OBJECTS = $(am_blox_tk_la_OBJECTS) blox_tk_la_LINK = $(LIBTOOL) --tag=CC $(AM_LIBTOOLFLAGS) \ $(LIBTOOLFLAGS) --mode=link $(CCLD) $(AM_CFLAGS) $(CFLAGS) \ $(blox_tk_la_LDFLAGS) $(LDFLAGS) -o $@ DEFAULT_INCLUDES = -I.@am__isrc@ -I$(top_builddir) depcomp = $(SHELL) $(top_srcdir)/build-aux/depcomp am__depfiles_maybe = depfiles am__mv = mv -f COMPILE = $(CC) $(DEFS) $(DEFAULT_INCLUDES) $(INCLUDES) $(AM_CPPFLAGS) \ $(CPPFLAGS) $(AM_CFLAGS) $(CFLAGS) LTCOMPILE = $(LIBTOOL) --tag=CC $(AM_LIBTOOLFLAGS) $(LIBTOOLFLAGS) \ --mode=compile $(CC) $(DEFS) $(DEFAULT_INCLUDES) $(INCLUDES) \ $(AM_CPPFLAGS) $(CPPFLAGS) $(AM_CFLAGS) $(CFLAGS) CCLD = $(CC) LINK = $(LIBTOOL) --tag=CC $(AM_LIBTOOLFLAGS) $(LIBTOOLFLAGS) \ --mode=link $(CCLD) $(AM_CFLAGS) $(CFLAGS) $(AM_LDFLAGS) \ $(LDFLAGS) -o $@ SOURCES = $(blox_tk_la_SOURCES) DIST_SOURCES = $(blox_tk_la_SOURCES) am__can_run_installinfo = \ case $$AM_UPDATE_INFO_DIR in \ n|no|NO) false;; \ *) (install-info --version) >/dev/null 2>&1;; \ esac HEADERS = $(noinst_HEADERS) ETAGS = etags CTAGS = ctags DISTFILES = $(DIST_COMMON) $(DIST_SOURCES) $(TEXINFOS) $(EXTRA_DIST) ACLOCAL = @ACLOCAL@ ALLOCA = @ALLOCA@ ALL_PACKAGES = @ALL_PACKAGES@ AMTAR = @AMTAR@ AR = @AR@ AS = @AS@ ATK_CFLAGS = @ATK_CFLAGS@ ATK_LIBS = @ATK_LIBS@ AUTOCONF = @AUTOCONF@ AUTOHEADER = @AUTOHEADER@ AUTOM4TE = @AUTOM4TE@ AUTOMAKE = @AUTOMAKE@ AWK = @AWK@ BLOX_IMPLEMENTATION = @BLOX_IMPLEMENTATION@ BUILT_PACKAGES = @BUILT_PACKAGES@ CAIRO_CFLAGS = @CAIRO_CFLAGS@ CAIRO_LIBS = @CAIRO_LIBS@ CC = @CC@ CCDEPMODE = @CCDEPMODE@ CFLAGS = @CFLAGS@ CPP = @CPP@ CPPFLAGS = @CPPFLAGS@ CYGPATH_W = @CYGPATH_W@ DEFS = @DEFS@ DEPDIR = @DEPDIR@ DLLTOOL = @DLLTOOL@ DSYMUTIL = @DSYMUTIL@ DUMPBIN = @DUMPBIN@ ECHO_C = @ECHO_C@ ECHO_N = @ECHO_N@ ECHO_T = @ECHO_T@ EGREP = @EGREP@ EMACS = @EMACS@ EMACSLOADPATH = @EMACSLOADPATH@ EXEEXT = @EXEEXT@ FGREP = @FGREP@ GLIB_CFLAGS = @GLIB_CFLAGS@ GLIB_GENMARSHAL = @GLIB_GENMARSHAL@ GLIB_LIBS = @GLIB_LIBS@ GLIB_MKENUMS = @GLIB_MKENUMS@ GNUTLS_CFLAGS = @GNUTLS_CFLAGS@ GNUTLS_LIBS = @GNUTLS_LIBS@ GOBJECT_QUERY = @GOBJECT_QUERY@ GPERF = @GPERF@ GREP = @GREP@ GST_RUN = @GST_RUN@ GTHREAD_CFLAGS = @GTHREAD_CFLAGS@ GTHREAD_LIBS = @GTHREAD_LIBS@ GTK_CFLAGS = @GTK_CFLAGS@ GTK_LIBS = @GTK_LIBS@ ICON = @ICON@ INCFFI = @INCFFI@ INCLTDL = @INCLTDL@ INCSIGSEGV = @INCSIGSEGV@ INCSNPRINTFV = @INCSNPRINTFV@ INCTCLTK = @INCTCLTK@ INSTALL = @INSTALL@ INSTALL_DATA = @INSTALL_DATA@ INSTALL_INFO = @INSTALL_INFO@ INSTALL_PROGRAM = @INSTALL_PROGRAM@ INSTALL_SCRIPT = @INSTALL_SCRIPT@ INSTALL_STRIP_PROGRAM = @INSTALL_STRIP_PROGRAM@ LD = @LD@ LDFLAGS = @LDFLAGS@ LEX = @LEX@ LIBADD_DL = @LIBADD_DL@ LIBC_SO_DIR = @LIBC_SO_DIR@ LIBC_SO_NAME = @LIBC_SO_NAME@ LIBFFI = @LIBFFI@ LIBFFI_CFLAGS = @LIBFFI_CFLAGS@ LIBFFI_EXECUTABLE_LDFLAGS = @LIBFFI_EXECUTABLE_LDFLAGS@ LIBFFI_LIBS = @LIBFFI_LIBS@ LIBGLUT = @LIBGLUT@ LIBGMP = @LIBGMP@ LIBGST_CFLAGS = @LIBGST_CFLAGS@ LIBICONV = @LIBICONV@ LIBLTDL = @LIBLTDL@ LIBOBJS = @LIBOBJS@ LIBOPENGL = @LIBOPENGL@ LIBREADLINE = @LIBREADLINE@ LIBS = @LIBS@ LIBSIGSEGV = @LIBSIGSEGV@ LIBSNPRINTFV = @LIBSNPRINTFV@ LIBTCLTK = @LIBTCLTK@ LIBTHREAD = @LIBTHREAD@ LIBTOOL = @LIBTOOL@ LIPO = @LIPO@ LN = @LN@ LN_S = @LN_S@ LTALLOCA = @LTALLOCA@ LTLIBICONV = @LTLIBICONV@ LTLIBOBJS = @LTLIBOBJS@ MAINTAINER = @MAINTAINER@ MAKEINFO = @MAKEINFO@ MANIFEST_TOOL = @MANIFEST_TOOL@ MKDIR_P = @MKDIR_P@ MODULES = @MODULES@ NM = @NM@ NMEDIT = @NMEDIT@ OBJC = @OBJC@ OBJCDEPMODE = @OBJCDEPMODE@ OBJCFLAGS = @OBJCFLAGS@ OBJDUMP = @OBJDUMP@ OBJEXT = @OBJEXT@ OTOOL = @OTOOL@ OTOOL64 = @OTOOL64@ PACKAGE = @PACKAGE@ PACKAGE_BUGREPORT = @PACKAGE_BUGREPORT@ PACKAGE_DLOPEN_FLAGS = @PACKAGE_DLOPEN_FLAGS@ PACKAGE_NAME = @PACKAGE_NAME@ PACKAGE_STRING = @PACKAGE_STRING@ PACKAGE_TARNAME = @PACKAGE_TARNAME@ PACKAGE_URL = @PACKAGE_URL@ PACKAGE_VERSION = @PACKAGE_VERSION@ PANGO_CFLAGS = @PANGO_CFLAGS@ PANGO_LIBS = @PANGO_LIBS@ PATH_SEPARATOR = @PATH_SEPARATOR@ PKG_CONFIG = @PKG_CONFIG@ RANLIB = @RANLIB@ RELOCATABLE = @RELOCATABLE@ RELOC_CPPFLAGS = @RELOC_CPPFLAGS@ RELOC_LDFLAGS = @RELOC_LDFLAGS@ SDL_CFLAGS = @SDL_CFLAGS@ SDL_LIBS = @SDL_LIBS@ SED = @SED@ SET_MAKE = @SET_MAKE@ SHELL = @SHELL@ SOCKET_LIBS = @SOCKET_LIBS@ STRIP = @STRIP@ SYNC_CFLAGS = @SYNC_CFLAGS@ TCLSH = @TCLSH@ TIMEOUT = @TIMEOUT@ VERSION = @VERSION@ VERSION_INFO = @VERSION_INFO@ WINDRES = @WINDRES@ WINEWRAPPER = @WINEWRAPPER@ WINEWRAPPERDEP = @WINEWRAPPERDEP@ XMKMF = @XMKMF@ XZIP = @XZIP@ X_CFLAGS = @X_CFLAGS@ X_EXTRA_LIBS = @X_EXTRA_LIBS@ X_LIBS = @X_LIBS@ X_PRE_LIBS = @X_PRE_LIBS@ YACC = @YACC@ ZIP = @ZIP@ abs_builddir = @abs_builddir@ abs_srcdir = @abs_srcdir@ abs_top_builddir = @abs_top_builddir@ abs_top_srcdir = @abs_top_srcdir@ ac_ct_AR = @ac_ct_AR@ ac_ct_CC = @ac_ct_CC@ ac_ct_DUMPBIN = @ac_ct_DUMPBIN@ am__include = @am__include@ am__leading_dot = @am__leading_dot@ am__quote = @am__quote@ am__tar = @am__tar@ am__untar = @am__untar@ bindir = @bindir@ build = @build@ build_alias = @build_alias@ build_cpu = @build_cpu@ build_os = @build_os@ build_vendor = @build_vendor@ builddir = @builddir@ datadir = @datadir@ datarootdir = @datarootdir@ docdir = @docdir@ dvidir = @dvidir@ enable_mysql_tests = @enable_mysql_tests@ exec_prefix = @exec_prefix@ host = @host@ host_alias = @host_alias@ host_cpu = @host_cpu@ host_os = @host_os@ host_vendor = @host_vendor@ htmldir = @htmldir@ imagedir = @imagedir@ includedir = @includedir@ infodir = @infodir@ install_sh = @install_sh@ libdir = @libdir@ libexecdir = @libexecdir@ lispdir = @lispdir@ lispstartdir = @lispstartdir@ localedir = @localedir@ localstatedir = @localstatedir@ mandir = @mandir@ mkdir_p = @mkdir_p@ moduledir = @moduledir@ moduleexecdir = @moduleexecdir@ oldincludedir = @oldincludedir@ pdfdir = @pdfdir@ prefix = @prefix@ program_transform_name = @program_transform_name@ psdir = @psdir@ sbindir = @sbindir@ sharedstatedir = @sharedstatedir@ srcdir = @srcdir@ subdirs = @subdirs@ sysconfdir = @sysconfdir@ target_alias = @target_alias@ top_build_prefix = @top_build_prefix@ top_builddir = @top_builddir@ top_srcdir = @top_srcdir@ moduleexec_LTLIBRARIES = blox-tk.la gst_module_ldflags = -rpath $(moduleexecdir) -release $(VERSION) -module \ -no-undefined -export-symbols-regex gst_initModule blox_tk_la_SOURCES = BloxTK.c blox_tk_la_LIBADD = @LIBTCLTK@ $(top_builddir)/lib-src/library.la blox_tk_la_LDFLAGS = $(gst_module_ldflags) AM_CPPFLAGS = -I$(top_srcdir)/libgst -I$(top_srcdir)/lib-src @INCTCLTK@ noinst_HEADERS = rgbtab.h all: all-am .SUFFIXES: .SUFFIXES: .c .lo .o .obj $(srcdir)/Makefile.in: $(srcdir)/Makefile.am $(am__configure_deps) @for dep in $?; do \ case '$(am__configure_deps)' in \ *$$dep*) \ ( cd $(top_builddir) && $(MAKE) $(AM_MAKEFLAGS) am--refresh ) \ && { if test -f $@; then exit 0; else break; fi; }; \ exit 1;; \ esac; \ done; \ echo ' cd $(top_srcdir) && $(AUTOMAKE) --gnu packages/blox/tk/Makefile'; \ $(am__cd) $(top_srcdir) && \ $(AUTOMAKE) --gnu packages/blox/tk/Makefile .PRECIOUS: Makefile Makefile: $(srcdir)/Makefile.in $(top_builddir)/config.status @case '$?' in \ *config.status*) \ cd $(top_builddir) && $(MAKE) $(AM_MAKEFLAGS) am--refresh;; \ *) \ echo ' cd $(top_builddir) && $(SHELL) ./config.status $(subdir)/$@ $(am__depfiles_maybe)'; \ cd $(top_builddir) && $(SHELL) ./config.status $(subdir)/$@ $(am__depfiles_maybe);; \ esac; $(top_builddir)/config.status: $(top_srcdir)/configure $(CONFIG_STATUS_DEPENDENCIES) cd $(top_builddir) && $(MAKE) $(AM_MAKEFLAGS) am--refresh $(top_srcdir)/configure: $(am__configure_deps) cd $(top_builddir) && $(MAKE) $(AM_MAKEFLAGS) am--refresh $(ACLOCAL_M4): $(am__aclocal_m4_deps) cd $(top_builddir) && $(MAKE) $(AM_MAKEFLAGS) am--refresh $(am__aclocal_m4_deps): install-moduleexecLTLIBRARIES: $(moduleexec_LTLIBRARIES) @$(NORMAL_INSTALL) @list='$(moduleexec_LTLIBRARIES)'; test -n "$(moduleexecdir)" || list=; \ list2=; for p in $$list; do \ if test -f $$p; then \ list2="$$list2 $$p"; \ else :; fi; \ done; \ test -z "$$list2" || { \ echo " $(MKDIR_P) '$(DESTDIR)$(moduleexecdir)'"; \ $(MKDIR_P) "$(DESTDIR)$(moduleexecdir)" || exit 1; \ echo " $(LIBTOOL) $(AM_LIBTOOLFLAGS) $(LIBTOOLFLAGS) --mode=install $(INSTALL) $(INSTALL_STRIP_FLAG) $$list2 '$(DESTDIR)$(moduleexecdir)'"; \ $(LIBTOOL) $(AM_LIBTOOLFLAGS) $(LIBTOOLFLAGS) --mode=install $(INSTALL) $(INSTALL_STRIP_FLAG) $$list2 "$(DESTDIR)$(moduleexecdir)"; \ } uninstall-moduleexecLTLIBRARIES: @$(NORMAL_UNINSTALL) @list='$(moduleexec_LTLIBRARIES)'; test -n "$(moduleexecdir)" || list=; \ for p in $$list; do \ $(am__strip_dir) \ echo " $(LIBTOOL) $(AM_LIBTOOLFLAGS) $(LIBTOOLFLAGS) --mode=uninstall rm -f '$(DESTDIR)$(moduleexecdir)/$$f'"; \ $(LIBTOOL) $(AM_LIBTOOLFLAGS) $(LIBTOOLFLAGS) --mode=uninstall rm -f "$(DESTDIR)$(moduleexecdir)/$$f"; \ done clean-moduleexecLTLIBRARIES: -test -z "$(moduleexec_LTLIBRARIES)" || rm -f $(moduleexec_LTLIBRARIES) @list='$(moduleexec_LTLIBRARIES)'; for p in $$list; do \ dir="`echo $$p | sed -e 's|/[^/]*$$||'`"; \ test "$$dir" != "$$p" || dir=.; \ echo "rm -f \"$${dir}/so_locations\""; \ rm -f "$${dir}/so_locations"; \ done blox-tk.la: $(blox_tk_la_OBJECTS) $(blox_tk_la_DEPENDENCIES) $(EXTRA_blox_tk_la_DEPENDENCIES) $(blox_tk_la_LINK) -rpath $(moduleexecdir) $(blox_tk_la_OBJECTS) $(blox_tk_la_LIBADD) $(LIBS) mostlyclean-compile: -rm -f *.$(OBJEXT) distclean-compile: -rm -f *.tab.c @AMDEP_TRUE@@am__include@ @am__quote@./$(DEPDIR)/BloxTK.Plo@am__quote@ .c.o: @am__fastdepCC_TRUE@ $(COMPILE) -MT $@ -MD -MP -MF $(DEPDIR)/$*.Tpo -c -o $@ $< @am__fastdepCC_TRUE@ $(am__mv) $(DEPDIR)/$*.Tpo $(DEPDIR)/$*.Po @AMDEP_TRUE@@am__fastdepCC_FALSE@ source='$<' object='$@' libtool=no @AMDEPBACKSLASH@ @AMDEP_TRUE@@am__fastdepCC_FALSE@ DEPDIR=$(DEPDIR) $(CCDEPMODE) $(depcomp) @AMDEPBACKSLASH@ @am__fastdepCC_FALSE@ $(COMPILE) -c $< .c.obj: @am__fastdepCC_TRUE@ $(COMPILE) -MT $@ -MD -MP -MF $(DEPDIR)/$*.Tpo -c -o $@ `$(CYGPATH_W) '$<'` @am__fastdepCC_TRUE@ $(am__mv) $(DEPDIR)/$*.Tpo $(DEPDIR)/$*.Po @AMDEP_TRUE@@am__fastdepCC_FALSE@ source='$<' object='$@' libtool=no @AMDEPBACKSLASH@ @AMDEP_TRUE@@am__fastdepCC_FALSE@ DEPDIR=$(DEPDIR) $(CCDEPMODE) $(depcomp) @AMDEPBACKSLASH@ @am__fastdepCC_FALSE@ $(COMPILE) -c `$(CYGPATH_W) '$<'` .c.lo: @am__fastdepCC_TRUE@ $(LTCOMPILE) -MT $@ -MD -MP -MF $(DEPDIR)/$*.Tpo -c -o $@ $< @am__fastdepCC_TRUE@ $(am__mv) $(DEPDIR)/$*.Tpo $(DEPDIR)/$*.Plo @AMDEP_TRUE@@am__fastdepCC_FALSE@ source='$<' object='$@' libtool=yes @AMDEPBACKSLASH@ @AMDEP_TRUE@@am__fastdepCC_FALSE@ DEPDIR=$(DEPDIR) $(CCDEPMODE) $(depcomp) @AMDEPBACKSLASH@ @am__fastdepCC_FALSE@ $(LTCOMPILE) -c -o $@ $< mostlyclean-libtool: -rm -f *.lo clean-libtool: -rm -rf .libs _libs ID: $(HEADERS) $(SOURCES) $(LISP) $(TAGS_FILES) list='$(SOURCES) $(HEADERS) $(LISP) $(TAGS_FILES)'; \ unique=`for i in $$list; do \ if test -f "$$i"; then echo $$i; else echo $(srcdir)/$$i; fi; \ done | \ $(AWK) '{ files[$$0] = 1; nonempty = 1; } \ END { if (nonempty) { for (i in files) print i; }; }'`; \ mkid -fID $$unique tags: TAGS TAGS: $(HEADERS) $(SOURCES) $(TAGS_DEPENDENCIES) \ $(TAGS_FILES) $(LISP) set x; \ here=`pwd`; \ list='$(SOURCES) $(HEADERS) $(LISP) $(TAGS_FILES)'; \ unique=`for i in $$list; do \ if test -f "$$i"; then echo $$i; else echo $(srcdir)/$$i; fi; \ done | \ $(AWK) '{ files[$$0] = 1; nonempty = 1; } \ END { if (nonempty) { for (i in files) print i; }; }'`; \ shift; \ if test -z "$(ETAGS_ARGS)$$*$$unique"; then :; else \ test -n "$$unique" || unique=$$empty_fix; \ if test $$# -gt 0; then \ $(ETAGS) $(ETAGSFLAGS) $(AM_ETAGSFLAGS) $(ETAGS_ARGS) \ "$$@" $$unique; \ else \ $(ETAGS) $(ETAGSFLAGS) $(AM_ETAGSFLAGS) $(ETAGS_ARGS) \ $$unique; \ fi; \ fi ctags: CTAGS CTAGS: $(HEADERS) $(SOURCES) $(TAGS_DEPENDENCIES) \ $(TAGS_FILES) $(LISP) list='$(SOURCES) $(HEADERS) $(LISP) $(TAGS_FILES)'; \ unique=`for i in $$list; do \ if test -f "$$i"; then echo $$i; else echo $(srcdir)/$$i; fi; \ done | \ $(AWK) '{ files[$$0] = 1; nonempty = 1; } \ END { if (nonempty) { for (i in files) print i; }; }'`; \ test -z "$(CTAGS_ARGS)$$unique" \ || $(CTAGS) $(CTAGSFLAGS) $(AM_CTAGSFLAGS) $(CTAGS_ARGS) \ $$unique GTAGS: here=`$(am__cd) $(top_builddir) && pwd` \ && $(am__cd) $(top_srcdir) \ && gtags -i $(GTAGS_ARGS) "$$here" distclean-tags: -rm -f TAGS ID GTAGS GRTAGS GSYMS GPATH tags distdir: $(DISTFILES) @srcdirstrip=`echo "$(srcdir)" | sed 's/[].[^$$\\*]/\\\\&/g'`; \ topsrcdirstrip=`echo "$(top_srcdir)" | sed 's/[].[^$$\\*]/\\\\&/g'`; \ list='$(DISTFILES)'; \ dist_files=`for file in $$list; do echo $$file; done | \ sed -e "s|^$$srcdirstrip/||;t" \ -e "s|^$$topsrcdirstrip/|$(top_builddir)/|;t"`; \ case $$dist_files in \ */*) $(MKDIR_P) `echo "$$dist_files" | \ sed '/\//!d;s|^|$(distdir)/|;s,/[^/]*$$,,' | \ sort -u` ;; \ esac; \ for file in $$dist_files; do \ if test -f $$file || test -d $$file; then d=.; else d=$(srcdir); fi; \ if test -d $$d/$$file; then \ dir=`echo "/$$file" | sed -e 's,/[^/]*$$,,'`; \ if test -d "$(distdir)/$$file"; then \ find "$(distdir)/$$file" -type d ! -perm -700 -exec chmod u+rwx {} \;; \ fi; \ if test -d $(srcdir)/$$file && test $$d != $(srcdir); then \ cp -fpR $(srcdir)/$$file "$(distdir)$$dir" || exit 1; \ find "$(distdir)/$$file" -type d ! -perm -700 -exec chmod u+rwx {} \;; \ fi; \ cp -fpR $$d/$$file "$(distdir)$$dir" || exit 1; \ else \ test -f "$(distdir)/$$file" \ || cp -p $$d/$$file "$(distdir)/$$file" \ || exit 1; \ fi; \ done check-am: all-am check: check-am all-am: Makefile $(LTLIBRARIES) $(HEADERS) installdirs: for dir in "$(DESTDIR)$(moduleexecdir)"; do \ test -z "$$dir" || $(MKDIR_P) "$$dir"; \ done install: install-am install-exec: install-exec-am install-data: install-data-am uninstall: uninstall-am install-am: all-am @$(MAKE) $(AM_MAKEFLAGS) install-exec-am install-data-am installcheck: installcheck-am install-strip: if test -z '$(STRIP)'; then \ $(MAKE) $(AM_MAKEFLAGS) INSTALL_PROGRAM="$(INSTALL_STRIP_PROGRAM)" \ install_sh_PROGRAM="$(INSTALL_STRIP_PROGRAM)" INSTALL_STRIP_FLAG=-s \ install; \ else \ $(MAKE) $(AM_MAKEFLAGS) INSTALL_PROGRAM="$(INSTALL_STRIP_PROGRAM)" \ install_sh_PROGRAM="$(INSTALL_STRIP_PROGRAM)" INSTALL_STRIP_FLAG=-s \ "INSTALL_PROGRAM_ENV=STRIPPROG='$(STRIP)'" install; \ fi mostlyclean-generic: clean-generic: distclean-generic: -test -z "$(CONFIG_CLEAN_FILES)" || rm -f $(CONFIG_CLEAN_FILES) -test . = "$(srcdir)" || test -z "$(CONFIG_CLEAN_VPATH_FILES)" || rm -f $(CONFIG_CLEAN_VPATH_FILES) maintainer-clean-generic: @echo "This command is intended for maintainers to use" @echo "it deletes files that may require special tools to rebuild." clean: clean-am clean-am: clean-generic clean-libtool clean-moduleexecLTLIBRARIES \ mostlyclean-am distclean: distclean-am -rm -rf ./$(DEPDIR) -rm -f Makefile distclean-am: clean-am distclean-compile distclean-generic \ distclean-tags dvi: dvi-am dvi-am: html: html-am html-am: info: info-am info-am: install-data-am: install-dvi: install-dvi-am install-dvi-am: install-exec-am: install-moduleexecLTLIBRARIES install-html: install-html-am install-html-am: install-info: install-info-am install-info-am: install-man: install-pdf: install-pdf-am install-pdf-am: install-ps: install-ps-am install-ps-am: installcheck-am: maintainer-clean: maintainer-clean-am -rm -rf ./$(DEPDIR) -rm -f Makefile maintainer-clean-am: distclean-am maintainer-clean-generic mostlyclean: mostlyclean-am mostlyclean-am: mostlyclean-compile mostlyclean-generic \ mostlyclean-libtool pdf: pdf-am pdf-am: ps: ps-am ps-am: uninstall-am: uninstall-moduleexecLTLIBRARIES .MAKE: install-am install-strip .PHONY: CTAGS GTAGS all all-am check check-am clean clean-generic \ clean-libtool clean-moduleexecLTLIBRARIES ctags distclean \ distclean-compile distclean-generic distclean-libtool \ distclean-tags distdir dvi dvi-am html html-am info info-am \ install install-am install-data install-data-am install-dvi \ install-dvi-am install-exec install-exec-am install-html \ install-html-am install-info install-info-am install-man \ install-moduleexecLTLIBRARIES install-pdf install-pdf-am \ install-ps install-ps-am install-strip installcheck \ installcheck-am installdirs maintainer-clean \ maintainer-clean-generic mostlyclean mostlyclean-compile \ mostlyclean-generic mostlyclean-libtool pdf pdf-am ps ps-am \ tags uninstall uninstall-am uninstall-moduleexecLTLIBRARIES # Tell versions [3.59,3.63) of GNU make to not export all variables. # Otherwise a system limit (for SysV at least) may be exceeded. .NOEXPORT: smalltalk-3.2.5/packages/blox/tk/Blox.st0000644000175000017500000000262512123404352015043 00000000000000"====================================================================== | | Smalltalk Tk-based GUI building blocks (loading script). | | ======================================================================" "====================================================================== | | Copyright 1992, 1994, 1995, 1999, 2000, 2001, 2002 | Free Software Foundation, Inc. | Written by Paolo Bonzini. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LESSER. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" Eval [ ObjectMemory addDependent: BLOX.Blox. BLOX.Blox update: #returnFromSnapshot ] smalltalk-3.2.5/packages/blox/tk/BloxTK.c0000644000175000017500000007137012123404352015101 00000000000000/*********************************************************************** * * Blox * * Standardized, Tk-based GUI widgets available for various window * systems - Interface to Tcl * ***********************************************************************/ /*********************************************************************** * * Copyright 1992, 1994, 1995, 1999, 2000, 2001, 2002, 2006, 2009 * Free Software Foundation, Inc. * Written by Paolo Bonzini. * * This file is part of GNU Smalltalk. * * GNU Smalltalk is free software; you can redistribute it and/or modify it * under the terms of the GNU General Public License as published by the Free * Software Foundation; either version 2, or (at your option) any later * version. * * Linking GNU Smalltalk statically or dynamically with other modules is * making a combined work based on GNU Smalltalk. Thus, the terms and * conditions of the GNU General Public License cover the whole * combination. * * In addition, as a special exception, the Free Software Foundation * give you permission to combine GNU Smalltalk with free software * programs or libraries that are released under the GNU LGPL and with * independent programs running under the GNU Smalltalk virtual machine. * * You may copy and distribute such a system following the terms of the * GNU GPL for GNU Smalltalk and the licenses of the other code * concerned, provided that you include the source code of that other * code when and as the GNU GPL requires distribution of source code. * * Note that people who make modified versions of GNU Smalltalk are not * obligated to grant this special exception for their modified * versions; it is their choice whether to do so. The GNU General * Public License gives permission to release a modified version without * this exception; this exception also makes it possible to release a * modified version which carries forward this exception. * * GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or * FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for * more details. * * You should have received a copy of the GNU General Public License along with * GNU Smalltalk; see the file COPYING. If not, write to the Free Software * Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * * Here is the copyright notice for the XPM code: * Copyright (C) 1989-94 GROUPE BULL * * Permission is hereby granted, free of charge, to any person obtaining a copy * of this software and associated documentation files (the "Software"), to * deal in the Software without restriction, including without limitation the * rights to use, copy, modify, merge, publish, distribute, sublicense, and/or * sell copies of the Software, and to permit persons to whom the Software is * furnished to do so, subject to the following conditions: * * The above copyright notice and this permission notice shall be included in * all copies or substantial portions of the Software. * * THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, EXPRESS OR * IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY, * FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL * GROUPE BULL BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER LIABILITY, WHETHER IN * AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM, OUT OF OR IN * CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN THE SOFTWARE. * * Except as contained in this notice, the name of GROUPE BULL shall not be * used in advertising or otherwise to promote the sale, use or other dealings * in this Software without prior written authorization from GROUPE BULL. ***********************************************************************/ #include "config.h" #include "gstpub.h" #include #ifndef HAVE_TCLTK #error Tcl/Tk 8.0 needed to install the GNU Smalltalk GUI #endif #include #include #include #include #define USE_COMPOSITELESS_PHOTO_PUT_BLOCK #define USE_OLD_IMAGE #include /* Hack for API changes in Tcl 8.4.0 */ #ifndef CONST84 #define CONST84 #endif #ifdef STDC_HEADERS #include #include #endif /* Smalltalk call-ins */ static Tcl_Interp *tclInit (void); static void bloxIdle (void); /* TCL callbacks */ static int doCallback (ClientData clientData, Tcl_Interp * interp, int argc, CONST84 char **argv); static int xpmFileMatch (Tcl_Channel channel, char *fileName, char *formatString, int *widthPtr, int *heightPtr); static int xpmStringMatch (char *string, char *formatString, int *widthPtr, int *heightPtr); static int xpmFileRead (Tcl_Interp * interp, Tcl_Channel channel, char *fileName, char *formatString, Tk_PhotoHandle imageHandle, int destX, int destY, int width, int height, int srcX, int srcY); static int xpmStringRead (Tcl_Interp * interp, char *string, char *formatString, Tk_PhotoHandle imageHandle, int destX, int destY, int width, int height, int srcX, int srcY); /* Globals */ static void xpmInit (void); static VMProxy *vmProxy; void bloxIdle (void) { while (Tcl_DoOneEvent (TCL_ALL_EVENTS | TCL_DONT_WAIT)); } int doCallback (ClientData clientData, Tcl_Interp * interp, int argc, CONST84 char **argv) { OOP oop, *args; int i; char result[2] = "0"; /* argv[0] is "callback", the command name */ args = alloca (sizeof (OOP) * (argc - 2)); oop = vmProxy->idToOOP (atoi (argv[1])); for (i = 0; i < argc - 3; i++) args[i] = vmProxy->stringToOOP (argv[i + 3]); args[argc - 3] = NULL; if (vmProxy->vmsgSend (oop, vmProxy->symbolToOOP (argv[2]), args) == vmProxy->trueOOP) result[0]++; Tcl_SetResult (interp, result, TCL_VOLATILE); return TCL_OK; } Tcl_Interp * tclInit (void) { static Tcl_Interp *interp; char *tclLibrary; if (interp) return (NULL); interp = Tcl_CreateInterp (); tclLibrary = getenv ("TCL_LIBRARY"); if (tclLibrary) Tcl_SetVar (interp, "tcl_library", tclLibrary, TCL_GLOBAL_ONLY); if (Tcl_Init (interp) == TCL_ERROR) { fprintf (stderr, "Tcl_Init failed: %s\n", interp->result); exit (1); } if (Tk_Init (interp) == TCL_ERROR) { fprintf (stderr, "Tk_Init failed: %s\n", interp->result); exit (1); } Tcl_CreateCommand (interp, "callback", doCallback, NULL, NULL); xpmInit (); return (interp); } void gst_initModule (VMProxy * proxy) { Tcl_FindExecutable (""); vmProxy = proxy; vmProxy->defineCFunc ("Tcl_Eval", Tcl_Eval); vmProxy->defineCFunc ("Tcl_GetStringResult", Tcl_GetStringResult); vmProxy->defineCFunc ("tclInit", tclInit); vmProxy->defineCFunc ("bloxIdle", bloxIdle); } /******************* BEGINNING OF XPM CODE ***********************/ typedef struct { const char *cptr; const char *Bcmt; const char *Ecmt; char Bos, Eos; mst_Boolean xpm1; /* 1 if XPM1, 0 otherwise */ } XpmData; #include "rgbtab.h" /* number of xpmColorKeys */ #define NKEYS 5 const char *xpmColorKeys[] = { "s", /* key #1: symbol */ "m", /* key #2: mono visual */ "g4", /* key #3: 4 grays visual */ "g", /* key #4: gray visual */ "c", /* key #5: color visual */ }; typedef struct { const char *type; /* key word */ const char *Bcmt; /* string beginning comments */ const char *Ecmt; /* string ending comments */ char Bos; /* character beginning strings */ char Eos; /* character ending strings */ } XpmDataType; typedef struct { char *string; /* characters string */ char *symbolic; /* symbolic name */ char *m_color; /* monochrom default */ char *g4_color; /* 4 level grayscale default */ char *g_color; /* other level grayscale default */ char *c_color; /* color default */ int rgb; } XpmColor; typedef struct { unsigned int width; /* image width */ unsigned int height; /* image height */ unsigned int *data; /* image data */ } XpmImage; static XpmDataType xpmDataTypes[] = { {"", "!", "\n", '\0', '\n'}, /* Natural type */ {"C", "/*", "*/", '"', '"'}, {"Lisp", ";", "\n", '"', '"'}, {NULL, NULL, NULL, 0, 0,} }; static int xpmParseHeader (XpmData * mdata); static int xpmParseValues (XpmData * data, unsigned int *width, unsigned int *height, unsigned int *ncolors, unsigned int *cpp); static int xpmParseColors (XpmData * data, unsigned int ncolors, unsigned int cpp, XpmColor ** colorTablePtr); static int xpmParsePixels (XpmData * data, unsigned int width, unsigned int height, unsigned int ncolors, unsigned int cpp, XpmColor *colorTable, unsigned int **pixels); static int xpmParseData (char *buffer, XpmImage * image, mst_Boolean readPixels); static mst_Boolean xpmNextUI (XpmData * mdata, unsigned int *ui_return); static mst_Boolean atoui (char *buf, int l, unsigned int *ui_return); static void xpmNextString (XpmData * mdata); static void xpmParseComment (XpmData * mdata); static void xpmFreeColorTable (XpmColor * colorTable, int ncolors); static unsigned int xpmNextWord (XpmData * mdata, char *buf, unsigned int buflen); static void ParseNumericColor (char *str, int *prgb); static void ParseXColor (Tk_Uid uid, int *prgb); void ParseNumericColor (char *str, int *prgb) { #define HEX(ch, shift) \ ( ((unsigned int) (((ch) - ((ch) < 'A' ? 48 : 55)) & 15)) << (shift)) switch (strlen (str)) { case 4: *prgb = HEX (str[1], 20) | HEX (str[2], 12) | HEX (str[1], 4); return; case 7: *prgb = HEX (str[1], 20) | HEX (str[3], 12) | HEX (str[5], 4) | HEX (str[2], 16) | HEX (str[4], 8) | HEX (str[6], 0); return; case 10: *prgb = HEX (str[1], 20) | HEX (str[4], 12) | HEX (str[7], 4) | HEX (str[2], 16) | HEX (str[5], 8) | HEX (str[8], 0); return; case 13: *prgb = HEX (str[1], 20) | HEX (str[5], 12) | HEX (str[9], 4) | HEX (str[2], 16) | HEX (str[6], 8) | HEX (str[10], 0); return; } } void ParseXColor (Tk_Uid uid, int *prgb) { xpmColorEntry *ce; for (ce = xColors; ce->color; ce++) { if ((char *) ce->color == uid) { *prgb = ce->rgb; return; } } } void xpmParseComment (XpmData * mdata) { register char c; register unsigned int n = 0; const char *s2; /* skip the string beginning comment */ s2 = mdata->Bcmt; do { c = *mdata->cptr++; n++; s2++; } while (c == *s2 && *s2 != '\0' && c && c != mdata->Bos); if (*s2 != '\0') { /* this wasn't the beginning of a comment */ mdata->cptr -= n; return; } /* skip comment */ do { s2 = mdata->Ecmt; while (c && c != *s2 && c != mdata->Bos) { c = *mdata->cptr++; } do { c = *mdata->cptr++; s2++; } while (c == *s2 && *s2 != '\0' && c && c != mdata->Bos); } while (*s2 != '\0'); /* this is the end of the comment */ mdata->cptr--; return; } /* * skip to the end of the current string and the beginning of the next one */ void xpmNextString (XpmData * mdata) { register char c; /* get to the end of the current string */ if (mdata->Eos) while ((c = *mdata->cptr++) && c != mdata->Eos); /* * then get to the beginning of the next string looking for possible * comment */ if (mdata->Bos) { while ((c = *mdata->cptr++) && c != mdata->Bos) if (mdata->Bcmt && c == mdata->Bcmt[0]) xpmParseComment (mdata); } else if (mdata->Bcmt) { /* XPM2 natural */ while ((c = *mdata->cptr++) == mdata->Bcmt[0]) xpmParseComment (mdata); mdata->cptr--; } return; } /* * skip whitespace and return the following word */ unsigned int xpmNextWord (XpmData * mdata, char *buf, unsigned int buflen) { register unsigned int n = 0; int c; while (isspace (c = *mdata->cptr) && c != mdata->Eos) mdata->cptr++; do { c = *mdata->cptr++; *buf++ = c; n++; } while (!isspace (c) && c != mdata->Eos && n < buflen); n--; mdata->cptr--; return (n); } /* * skip whitespace and compute the following unsigned int, * returns true if one is found and false if not */ mst_Boolean atoui (char *buf, int l, unsigned int *ui_return) { unsigned long int result; buf[l] = 0; errno = 0; *ui_return = strtoul (buf, NULL, 0); result = !errno; errno = 0; return (unsigned int) result; } mst_Boolean xpmNextUI (XpmData * mdata, unsigned int *ui_return) { long int l; char buf[BUFSIZ + 1]; l = xpmNextWord (mdata, buf, BUFSIZ); return atoui (buf, l, ui_return); } /* * parse xpm header */ int xpmParseHeader (XpmData * mdata) { char buf[BUFSIZ + 1]; int l, n = 0; mdata->Bos = '\0'; mdata->Eos = '\n'; mdata->Bcmt = mdata->Ecmt = NULL; l = xpmNextWord (mdata, buf, BUFSIZ); if (l == 7 && !strncmp ("#define", buf, 7)) { /* this maybe an XPM 1 file */ char *ptr; l = xpmNextWord (mdata, buf, BUFSIZ); if (!l) return (TCL_ERROR); /* File Invalid */ ptr = strchr (buf, '_'); if (!ptr || strncmp ("_format", ptr, l - (ptr - buf))) return (TCL_ERROR); /* File Invalid */ /* this is definitely an XPM 1 file */ mdata->xpm1 = true; n = 1; /* handle XPM1 as mainly XPM2 C */ } else { /* * skip the first word, get the second one, and see if this is * XPM 2 or 3 */ l = xpmNextWord (mdata, buf, BUFSIZ); if ((l == 3 && !strncmp ("XPM", buf, 3)) || (l == 4 && !strncmp ("XPM2", buf, 4))) { if (l == 3) n = 1; /* handle XPM as XPM2 C */ else { /* get the type key word */ l = xpmNextWord (mdata, buf, BUFSIZ); /* * get infos about this type */ while (xpmDataTypes[n].type && strncmp (xpmDataTypes[n].type, buf, l)) n++; } mdata->xpm1 = false; } else /* nope this is not an XPM file */ return (TCL_ERROR); /* File Invalid */ } if (xpmDataTypes[n].type) { if (n == 0) { /* natural type */ mdata->Bcmt = xpmDataTypes[n].Bcmt; mdata->Ecmt = xpmDataTypes[n].Ecmt; xpmNextString (mdata); /* skip the end of the headerline */ mdata->Bos = xpmDataTypes[n].Bos; mdata->Eos = xpmDataTypes[n].Eos; } else { mdata->Bcmt = xpmDataTypes[n].Bcmt; mdata->Ecmt = xpmDataTypes[n].Ecmt; if (!mdata->xpm1) { /* XPM 2 or 3 */ mdata->Bos = xpmDataTypes[n].Bos; mdata->Eos = '\0'; /* get to the beginning of the first string */ xpmNextString (mdata); mdata->Eos = xpmDataTypes[n].Eos; } else /* XPM 1 skip end of line */ xpmNextString (mdata); } } else /* we don't know about that type of XPM file... */ return (TCL_ERROR); /* File Invalid */ return (TCL_OK); } int xpmParseValues (XpmData * data, unsigned int *width, unsigned int *height, unsigned int *ncolors, unsigned int *cpp) { unsigned int l; unsigned int x_hotspot, y_hotspot, hotspot; unsigned int extensions; char buf[BUFSIZ + 1]; if (!data->xpm1) { /* XPM 2 or 3 */ /* * read values: width, height, ncolors, chars_per_pixel */ if (!(xpmNextUI (data, width) && xpmNextUI (data, height) && xpmNextUI (data, ncolors) && xpmNextUI (data, cpp))) return (TCL_ERROR); /* File invalid */ /* * read optional information (hotspot and/or XPMEXT) if any */ l = xpmNextWord (data, buf, BUFSIZ); if (l) { extensions = (l == 6 && !strncmp ("XPMEXT", buf, 6)); if (extensions) hotspot = (xpmNextUI (data, &x_hotspot) && xpmNextUI (data, &y_hotspot)); else { hotspot = (atoui (buf, l, &x_hotspot) && xpmNextUI (data, &y_hotspot)); l = xpmNextWord (data, buf, BUFSIZ); } } } else { /* * XPM 1 file read values: width, height, ncolors, chars_per_pixel */ int i; char *ptr; for (i = 0; i < 4; i++) { l = xpmNextWord (data, buf, BUFSIZ); if (l != 7 || strncmp ("#define", buf, 7)) return (TCL_ERROR); /* File invalid */ l = xpmNextWord (data, buf, BUFSIZ); if (!l) return (TCL_ERROR); /* File invalid */ ptr = strchr (buf, '_'); if (!ptr) return (TCL_ERROR); /* File invalid */ switch (l - (ptr - buf)) { case 6: if (!strncmp ("_width", ptr, 6) && !xpmNextUI (data, width)) return (TCL_ERROR); /* File invalid */ break; case 7: if (!strncmp ("_height", ptr, 7) && !xpmNextUI (data, height)) return (TCL_ERROR); /* File invalid */ break; case 8: if (!strncmp ("_ncolors", ptr, 8) && !xpmNextUI (data, ncolors)) return (TCL_ERROR); /* File invalid */ break; case 16: if (!strncmp ("_chars_per_pixel", ptr, 16) && !xpmNextUI (data, cpp)) return (TCL_ERROR); /* File invalid */ break; default: return (TCL_ERROR); /* File invalid */ } /* skip the end of line */ xpmNextString (data); } } return (TCL_OK); } int xpmParseColors (XpmData * data, unsigned int ncolors, unsigned int cpp, XpmColor ** colorTablePtr) { unsigned int key, l, a, b; unsigned int curkey; /* current color key */ unsigned int lastwaskey; /* key read */ char buf[BUFSIZ + 1]; char curbuf[BUFSIZ + 1]; /* current buffer */ const char **sptr; char *s; XpmColor *color; XpmColor *colorTable; char **defaults; colorTable = (XpmColor *) malloc (ncolors * sizeof (XpmColor)); if (!colorTable) return (TCL_ERROR); /* No memory */ memset (colorTable, 0, ncolors * sizeof (XpmColor)); if (!data->xpm1) { /* XPM 2 or 3 */ for (a = 0, color = colorTable; a < ncolors; a++, color++) { xpmNextString (data); /* skip the line */ /* * read pixel value */ color->string = (char *) malloc (cpp + 1); if (!color->string) { xpmFreeColorTable (colorTable, ncolors); return (TCL_ERROR); /* No memory */ } for (b = 0, s = color->string; b < cpp; b++, s++) *s = *data->cptr++; *s = '\0'; /* * read color keys and values */ defaults = (char **) color; key = NKEYS; curkey = 0; lastwaskey = 0; *curbuf = '\0'; /* init curbuf */ while ((l = xpmNextWord (data, buf, BUFSIZ)) != 0) { if (!lastwaskey) { for (key = 0, sptr = xpmColorKeys; key < NKEYS; key++, sptr++) if ((strlen (*sptr) == l) && (!strncmp (*sptr, buf, l))) break; } if (!lastwaskey && key < NKEYS) { /* open new key */ if (curkey) { /* flush string */ s = (char *) malloc (strlen (curbuf) + 1); if (!s) { xpmFreeColorTable (colorTable, ncolors); return (TCL_ERROR); /* No memory */ } defaults[curkey] = s; strcpy (s, curbuf); } curkey = key + 1; /* set new key */ *curbuf = '\0'; /* reset curbuf */ lastwaskey = 1; } else { if (!curkey) { /* key without value */ xpmFreeColorTable (colorTable, ncolors); return (TCL_ERROR); /* File invalid */ } if (!lastwaskey) strcat (curbuf, " "); /* append space */ buf[l] = '\0'; strcat (curbuf, buf); /* append buf */ lastwaskey = 0; } } if (!curkey) { /* key without value */ xpmFreeColorTable (colorTable, ncolors); return (TCL_ERROR); /* File invalid */ } s = defaults[curkey] = (char *) malloc (strlen (curbuf) + 1); if (!s) { xpmFreeColorTable (colorTable, ncolors); return (TCL_ERROR); /* No memory */ } strcpy (s, curbuf); } } else { /* XPM 1 */ /* get to the beginning of the first string */ data->Bos = '"'; data->Eos = '\0'; xpmNextString (data); data->Eos = '"'; for (a = 0, color = colorTable; a < ncolors; a++, color++) { /* * read pixel value */ color->string = (char *) malloc (cpp + 1); if (!color->string) { xpmFreeColorTable (colorTable, ncolors); return (TCL_ERROR); /* No memory */ } for (b = 0, s = color->string; b < cpp; b++, s++) *s = *data->cptr++; *s = '\0'; /* * read color values */ xpmNextString (data); /* get to the next string */ *curbuf = '\0'; /* init curbuf */ while ((l = xpmNextWord (data, buf, BUFSIZ)) != 0) { if (*curbuf != '\0') strcat (curbuf, " "); /* append space */ buf[l] = '\0'; strcat (curbuf, buf); /* append buf */ } s = (char *) malloc (strlen (curbuf) + 1); if (!s) { xpmFreeColorTable (colorTable, ncolors); return (TCL_ERROR); /* No memory */ } strcpy (s, curbuf); color->c_color = s; *curbuf = '\0'; /* reset curbuf */ if (a < ncolors - 1) xpmNextString (data); /* get to the next string */ } } for (a = 0, color = colorTable; a < ncolors; a++, color++) { Tk_Uid noneUid = Tk_GetUid ("None"); for (curkey = NKEYS, color->rgb = -2, defaults = (char **) color; color->rgb == -2 && curkey; curkey--) { Tk_Uid colorUid; if (!defaults[curkey]) continue; if (defaults[curkey][0] == '#') { ParseNumericColor (defaults[curkey], &color->rgb); continue; } if (!strncmp (defaults[curkey], "grey", 4)) { /* Recognize `greys' too, not just `grays'... */ defaults[curkey][2] = 'a'; } /* Make black the transparent color -- black becomes a very dark gray */ colorUid = Tk_GetUid (defaults[curkey]); if (colorUid == noneUid) { color->rgb = 0; continue; } ParseXColor (colorUid, &color->rgb); if (!color->rgb) color->rgb = 0x30303; /* This is gray1 */ } } *colorTablePtr = colorTable; return (TCL_OK); } int xpmParsePixels (XpmData * data, unsigned int width, unsigned int height, unsigned int ncolors, unsigned int cpp, XpmColor * colorTable, unsigned int **pixels) { unsigned int *iptr, *iptr2; unsigned int a, x, y; iptr2 = (unsigned int *) malloc (sizeof (unsigned int) * width * height); if (!iptr2) return (TCL_ERROR); /* No memory */ iptr = iptr2; switch (cpp) { case (1): /* Optimize for single character colors */ { unsigned int colrgb[256]; memset (colrgb, 0, 256 * sizeof (int)); for (a = 0; a < 256; a++) colrgb[a] = -1; for (a = 0; a < ncolors; a++) colrgb[(unsigned int) colorTable[a].string[0]] = colorTable[a].rgb; for (y = 0; y < height; y++) { xpmNextString (data); for (x = 0; x < width; x++, iptr++) { int rgb = colrgb[(unsigned int) *data->cptr++]; if (rgb != -1) *iptr = rgb; else { free (iptr2); return (TCL_ERROR); /* File invalid */ } } } } break; case (2): /* Optimize for double character scolors */ { /* free all allocated pointers at all exits */ #define FREE_CRGB {int f; for (f = 0; f < 256; f++) \ if (crgb[f]) free(crgb[f]);} /* array of pointers malloced by need */ unsigned int *crgb[256]; int char1, a2; memset (crgb, 0, 256 * sizeof (unsigned int *)); /* init */ for (a = 0; a < ncolors; a++) { char1 = colorTable[a].string[0]; if (crgb[char1] == NULL) { /* get new memory */ crgb[char1] = (unsigned int *) malloc (256 * sizeof (unsigned int)); if (crgb[char1] == NULL) { /* new block failed */ FREE_CRGB; free (iptr2); return (TCL_ERROR); /* No memory */ } for (a2 = 0; a2 < 256; a2++) crgb[char1][a2] = -1; } crgb[char1][(unsigned int) colorTable[a].string[1]] = colorTable[a].rgb; } for (y = 0; y < height; y++) { xpmNextString (data); for (x = 0; x < width; x++, iptr++) { int cc1 = *data->cptr++; int rgb = crgb[cc1][(unsigned int) *data->cptr++]; if (rgb != -1) *iptr = rgb - 1; else { FREE_CRGB; free (iptr2); return (TCL_ERROR); /* File invalid */ } } } FREE_CRGB; } break; default: /* Long color names */ return (TCL_ERROR); /* Not supported */ } *pixels = iptr2; return (TCL_OK); } /* * This function parses an xpm file or data and store the found informations * in an an XpmImage structure which is returned. */ int xpmParseData (char *buffer, XpmImage * image, mst_Boolean readPixels) { /* variables to return */ unsigned int width, height, ncolors, cpp; XpmColor *colorTable = NULL; unsigned int *pixelindex = NULL; int ErrorStatus; XpmData data; /* * parse the header */ memset (image, 0, sizeof (XpmImage)); data.cptr = buffer; ErrorStatus = xpmParseHeader (&data); if (ErrorStatus != TCL_OK) return (ErrorStatus); /* * read values */ ErrorStatus = xpmParseValues (&data, &width, &height, &ncolors, &cpp); if (ErrorStatus != TCL_OK) return (ErrorStatus); /* * store found informations in the XpmImage structure */ image->width = width; image->height = height; if (!readPixels) return (TCL_OK); /* * read colors */ ErrorStatus = xpmParseColors (&data, ncolors, cpp, &colorTable); if (ErrorStatus != TCL_OK) return (ErrorStatus); /* * read pixels and index them on color number */ ErrorStatus = xpmParsePixels (&data, width, height, ncolors, cpp, colorTable, &pixelindex); xpmFreeColorTable (colorTable, ncolors); if (ErrorStatus != TCL_OK) return (ErrorStatus); image->data = pixelindex; return (TCL_OK); } /* * Free the computed color table */ void xpmFreeColorTable (XpmColor * colorTable, int ncolors) { int a, b; XpmColor *color; char **sptr; for (a = 0, color = colorTable; a < ncolors; a++, color++) { for (b = 0, sptr = (char **) color; b <= NKEYS; b++, sptr++) if (*sptr) free (*sptr); } free (colorTable); } /******************************* TCL INTERFACE FOR XPM **************/ int xpmStringMatch (char *string, char *formatString, int *widthPtr, int *heightPtr) { XpmImage img; int result; result = xpmParseData (string, &img, false); if (result != TCL_OK) { return (0); } *widthPtr = img.width; *heightPtr = img.height; return (1); } int xpmStringRead (Tcl_Interp * interp, char *string, char *formatString, Tk_PhotoHandle imageHandle, int destX, int destY, int width, int height, int srcX, int srcY) { XpmImage img; int result; unsigned int *block; #ifdef WORDS_BIG_ENDIAN #define BYTEOFS(i) (sizeof(int)-i) #else #define BYTEOFS(i) (i) #endif static Tk_PhotoImageBlock blk = { NULL, /* unsigned char *pixelPtr; */ 0, /* int width; */ 1, /* int height; */ 0, /* int pitch; */ sizeof (int), /* int pixelSize; */ {BYTEOFS (2), BYTEOFS (1), BYTEOFS (0)}, /* int offset[3]; */ }; #undef BYTEOFS result = xpmParseData (string, &img, true); if (result != TCL_OK) return (result); for (block = img.data + img.width * srcY + srcX; img.height; img.height--, destY++) { int todo; unsigned int last; for (blk.pixelPtr = (PTR) block, blk.width = 0, last = *block, destX = 0, todo = img.width; todo--; last = *block, block++) { if ((*block == 0) ^ (last == 0)) { if (last) Tk_PhotoPutBlock (imageHandle, &blk, destX, destY, blk.width, 1); destX += blk.width; blk.width = 1; blk.pixelPtr = (PTR) block; } else blk.width++; } if (last) Tk_PhotoPutBlock (imageHandle, &blk, destX, destY, blk.width, 1); } free (img.data); return (result); } int xpmFileMatch (Tcl_Channel channel, char *fileName, char *formatString, int *widthPtr, int *heightPtr) { int fileSize, bytesRead, result; char *buf; fileSize = Tcl_Seek (channel, 0, SEEK_END); if (fileSize < 0 || Tcl_Seek (channel, 0, SEEK_SET) < 0) return (0); buf = malloc (fileSize + 1); if (!buf) return (0); bytesRead = Tcl_Read (channel, buf, fileSize); if (bytesRead < 0) { free (buf); return (0); } buf[bytesRead] = '\0'; result = xpmStringMatch (buf, formatString, widthPtr, heightPtr); free (buf); return (result); } int xpmFileRead (Tcl_Interp * interp, Tcl_Channel channel, char *fileName, char *formatString, Tk_PhotoHandle imageHandle, int destX, int destY, int width, int height, int srcX, int srcY) { int fileSize, bytesRead, result; char *buf; fileSize = Tcl_Seek (channel, 0, SEEK_END); if (fileSize < 0 || Tcl_Seek (channel, 0, SEEK_SET) < 0) return (TCL_ERROR); buf = malloc (fileSize + 1); if (!buf) return (TCL_ERROR); bytesRead = Tcl_Read (channel, buf, fileSize); if (bytesRead < 0) { free (buf); return (TCL_ERROR); } buf[bytesRead] = '\0'; result = xpmStringRead (interp, fileName, formatString, imageHandle, destX, destY, width, height, srcX, srcY); free (buf); return (result); } void xpmInit (void) { static Tk_PhotoImageFormat xpmFormat = { (char *) "XPM", xpmFileMatch, xpmStringMatch, xpmFileRead, xpmStringRead, NULL, NULL, NULL }; xpmColorEntry *ce; Tk_CreatePhotoImageFormat (&xpmFormat); for (ce = xColors; ce->color; ce++) ce->color = (char *) Tk_GetUid (ce->color); } smalltalk-3.2.5/packages/blox/tk/stamp-classes0000644000175000017500000000000012123404352016252 00000000000000smalltalk-3.2.5/packages/blox/tk/package.xml0000644000175000017500000000053112123404352015676 00000000000000 BloxTK BLOX Blox BloxBasic.st BloxWidgets.st BloxText.st BloxCanvas.st BloxExtend.st Blox.st blox-tk ChangeLog smalltalk-3.2.5/packages/blox/tk/BloxCanvas.st0000644000175000017500000012303212123404352016173 00000000000000"====================================================================== | | Smalltalk Tk-based GUI building blocks (canvas widget). | | ======================================================================" "====================================================================== | | Copyright 1999,2000,2001,2002,2003,2004 Free Software Foundation, Inc. | Free Software Foundation, Inc. | Written by Paolo Bonzini. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LESSER. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" BViewport subclass: BCanvas [ | items boundingBox | Initialized := nil. BCanvas class >> initializeOnStartup [ Initialized := false ] backgroundColor [ "Answer the value of the backgroundColor option for the widget. Specifies the normal background color to use when displaying the widget." self properties at: #background ifPresent: [:value | ^value]. self tclEval: '%1 cget -background' with: self connected with: self container. ^self properties at: #background put: self tclResult ] backgroundColor: value [ "Set the value of the backgroundColor option for the widget. Specifies the normal background color to use when displaying the widget." self tclEval: '%1 configure -background %3' with: self connected with: self container with: value asTkString. self properties at: #background put: value ] foregroundColor [ "Answer the value of the foregroundColor option for the widget. Specifies the normal foreground color to use when displaying the widget." self properties at: #foreground ifPresent: [:value | ^value]. self tclEval: '%1 cget -foreground' with: self connected with: self container. ^self properties at: #foreground put: self tclResult ] foregroundColor: value [ "Set the value of the foregroundColor option for the widget. Specifies the normal foreground color to use when displaying the widget." self tclEval: '%1 configure -foreground %3' with: self connected with: self container with: value asTkString. self properties at: #foreground put: value ] item: name at: option [ self tclEval: '%1 itemcget %2 -%3' with: self connected with: name with: option ] item: name at: option put: value [ self tclEval: '%1 itemconfigure %2 -%3 %4' with: self connected with: name with: option with: value asTkString ] item: name bind: event to: aSymbol of: anObject parameters: params [ self bind: event to: aSymbol of: anObject parameters: params prefix: self connected , ' bind ' , name ] item: name points: pointsArray [ | stream | stream := WriteStream on: (String new: 50). stream nextPutAll: self connected; nextPutAll: ' coords '; nextPutAll: name. pointsArray do: [:each | self extractCoordinatesFrom: each to: stream]. self tclEval: stream contents ] itemCreate: item [ | stream name scrollRegion | stream := WriteStream on: (String new: 50). boundingBox := boundingBox isNil ifFalse: [boundingBox merge: item boundingBox] ifTrue: [item boundingBox]. stream nextPutAll: self connected; nextPutAll: ' create '; nextPutAll: item itemType; space. item points do: [:each | self extractCoordinatesFrom: each to: stream]. item properties keysAndValuesDo: [:key :value | stream nextPutAll: ' -'; nextPutAll: key; space; nextPutAll: value asTkString]. self tclEval: stream contents. name := self tclResult. items at: name put: item. scrollRegion := boundingBox expandBy: self extraSpace. stream reset; nextPutAll: self connected; nextPutAll: ' configure -scrollregion {'; print: scrollRegion left asInteger; space; print: scrollRegion top asInteger; space; print: scrollRegion right asInteger; space; print: scrollRegion bottom asInteger; nextPut: $}. self tclEval: stream contents. ^name ] lower: item [ self tclEval: self connected , ' lower ' , item ] raise: item [ self tclEval: self connected , ' raise ' , item ] remove: item [ (items removeKey: item) destroyed. self tclEval: self connected , ' delete ' , item ] show: item [ Initialized ifFalse: [self defineSeeProcedure]. self tclEval: 'canvas_see %1 %2' with: self connected with: item ] addChild: child [ "The widget identified by child has been added to the receiver. This method is public not because you can call it, but because it can be useful to override it, not forgetting the call to either the superclass implementation or #basicAddChild:, to perform some initialization on the children just added. Answer the new child." | name | self tclEval: self connected , ' create window 0 0 -window ' , child container. name := self tclResult. items at: name put: child. child properties at: #canvasItemId put: name. child properties at: #xyGeom put: Point new. ^self basicAddChild: child ] child: child height: value [ "Set the given child's height." | id xy | id := child properties at: #canvasItemId. self item: id at: #height ] child: child heightOffset: value [ "Offset the given child's height by value pixels." self child: child height: (self heightChild: child) + value ] child: child width: value [ "Set the given child's width." | id xy | id := child properties at: #canvasItemId. self item: id at: #width ] child: child widthOffset: value [ "Offset the given child's width by value pixels." self child: child width: (self widthChild: child) + value ] child: child x: value [ "Set the given child's top-left corner's x coordinate, in pixels in the canvas' coordinate system." | id xy | xy := child properties at: #xyGeom. xy x: value. id := child properties at: #canvasItemId. self item: id points: (Array with: xy) ] child: child xOffset: value [ "Offset the given child's top-left x by value pixels." self child: child x: (self xChild: child) + value ] child: child y: value [ "Set the given child's top-left corner's y coordinate, in pixels in the canvas' coordinate system." | id xy | xy := child properties at: #xyGeom. xy y: value. id := child properties at: #canvasItemId. self item: id points: (Array with: xy) ] child: child yOffset: value [ "Offset the given child's top-left y by value pixels." self child: child y: (self yChild: child) + value ] heightChild: child [ "Answer the given child's height in pixels." ^child heightAbsolute ] widthChild: child [ "Answer the given child's width in pixels." ^child widthAbsolute ] xChild: child [ "Answer the given child's top-left corner's x coordinate, in pixels in the canvas' coordinate system." ^(child properties at: #xyGeom ifAbsentPut: [Point new]) x ] yChild: child [ "Answer the given child's top-left corner's y coordinate, in pixels in the canvas' coordinate system." ^(child properties at: #xyGeom ifAbsentPut: [Point new]) y ] create [ self create: '-highlightthickness 0'. self tclEval: self connected , ' xview moveto 0'. self tclEval: self connected , ' yview moveto 0' ] defineSeeProcedure [ Initialized := true. self tclEval: ' ## "see" method alternative for canvas by Jeffrey Hobbs ## Aligns the named item as best it can in the middle of the screen ## Behavior depends on whether -scrollregion is set ## ## c - a canvas widget ## item - a canvas tagOrId proc canvas_see {c item} { set box [$c bbox $item] if [string match {} $box] return if [string match {} [$c cget -scrollreg]] { ## People really should set -scrollregion you know... foreach {x y x1 y1} $box { set x [expr round(2.5*($x1+$x)/[winfo width $c])] set y [expr round(2.5*($y1+$y)/[winfo height $c])] } $c xview moveto 0 $c yview moveto 0 $c xview scroll $x units $c yview scroll $y units } else { ## If -scrollregion is set properly, use this foreach {x y x1 y1} $box {top btm} [$c yview] {left right} [$c xview] {p q xmax ymax} [$c cget -scrollreg] { set xpos [expr (($x1+$x)/2.0)/$xmax - ($right-$left)/2.0] set ypos [expr (($y1+$y)/2.0)/$ymax - ($btm-$top)/2.0] } $c xview moveto $xpos $c yview moveto $ypos } } ' ] extractCoordinatesFrom: aPointOrArray to: stream [ (aPointOrArray respondsTo: #do:) ifTrue: [aPointOrArray do: [:each | stream space; print: each asInteger]] ifFalse: [stream space; print: aPointOrArray x asInteger; space; print: aPointOrArray y asInteger] ] initialize: parent [ items := LookupTable new. super initialize: parent ] widgetType [ ^'canvas ' ] at: aPoint [ "Selects the topmost item in the canvas overlapping the point given by aPoint." | item | self tclEval: '%1 find closest [%1 canvasx %2] [%1 canvasy %3]' with: self connected with: aPoint x printString with: aPoint y printString. item := items at: self tclResult ifAbsent: [^nil]. ^(item boundingBox containsPoint: aPoint) ifTrue: [item] ifFalse: [nil] ] between: origin and: corner do: aBlock [ "Evaluate aBlock for each item whose bounding box intersects the rectangle between the two Points, origin and corner. Pass the item to the block." | r | r := Rectangle origin: origin corner: corner. items copy do: [:each | (each boundingBox intersects: r) ifTrue: [aBlock value: each]] ] boundingBox [ "Answer the bounding box of all the items in the canvas" ^boundingBox ] destroyed [ "The widget has been destroyed. Tell all of its items about this fact." items do: [:each | (each isKindOf: BCanvasObject) ifTrue: [each destroyed]] ] do: aBlock [ "Evaluate aBlock, passing each item to it." items do: aBlock ] empty [ "Remove all the items from the canvas, leaving it empty" items copy do: [:each | each remove] ] extraSpace [ "Answer the amount of space that is left as a border around the canvas items." ^self properties at: #extraSpace ifAbsentPut: [Point new] ] extraSpace: aPoint [ "Set the amount of space that is left as a border around the canvas items." self properties at: #extraSpace put: aPoint ] items [ "Answer an Array containing all the items in the canvas" ^items copy ] mapPoint: aPoint [ "Given aPoint, a point expressed in window coordinates, answer the corresponding canvas coordinates that are displayed at that location." | x stream | self tclEval: 'return "[%1 canvasx %2] [%1 canvasy %3]"' with: aPoint x printString with: aPoint y printString. stream := ReadStream on: self tclResult. x := (stream upTo: $ ) asInteger. ^x @ stream upToEnd asInteger ] ] BCanvas subclass: BScrolledCanvas [ create [ "Create with both scrollbars" super create. self horizontal: true; vertical: true ] ] BEventTarget subclass: BCanvasObject [ | blox name properties | BCanvasObject class >> new [ self shouldNotImplement ] BCanvasObject class >> new: parentCanvas [ "Answer a new instance of the receiver, displayed into the given parentCanvas." ^(self basicNew) blox: parentCanvas; initializeWithProperties: IdentityDictionary new ] blox [ "Answer the parent canvas of the receiver" ^blox ] boundingBox [ "Answer a Rectangle enclosing all of the receiver" self subclassResponsibility ] color [ "Answer the color to be used to fill this item's area." ^self at: #fill ] color: color [ "Set the color to be used to fill this item's area." ^self at: #fill put: color ] copyInto: newCanvas [ "Answer a new BCanvasObject identical to this but displayed into another canvas, newCanvas. The new instance is not created at the time it is returned." ^(self species basicNew) blox: newCanvas; initializeWithProperties: self properties copy; points: self points; postCopy; yourself ] copyObject [ "Answer a new BCanvasObject identical to this. Unlike #copy, which merely creates a new Smalltalk object with the same data and referring to the same canvas item, the object created with #copyObject is physically distinct from the original. The new instance is not created at the time it is returned." ^self copyInto: self blox ] createCopy [ "Answer a new BCanvasObject identical to this. Unlike #copy, which merely creates a new Smalltalk object with the same data and referring to the same canvas item, the object created with #copyObject is physically distinct from the original. The new instance has already been created at the time it is returned." ^(self copyObject) create; yourself ] createCopyInto: newCanvas [ "Answer a new BCanvasObject identical to this but displayed into another canvas, newCanvas. The new instance has already been created at the time it is returned." ^(self copyInto: newCanvas) create; yourself ] deepCopy [ "It does not make sense to make a copy, because it would make data inconsistent across different objects; so answer the receiver" ^self ] grayOut [ "Apply a 50% gray stippling pattern to the object" self at: #stipple put: 'gray50' ] shallowCopy [ "It does not make sense to make a copy, because it would make data inconsistent across different objects; so answer the receiver" ^self ] at: option [ ^self properties at: option ifAbsentPut: [self created ifFalse: [self error: 'option not set yet']. self blox item: self name at: option] ] at: option put: value [ self created ifTrue: [self blox item: self name at: option put: value]. ^self properties at: option put: value ] blox: canvas [ blox := canvas ] destroyed [ name := nil ] integerAt: option [ ^(self at: option) asInteger ] integerAt: option put: value [ ^self at: option put: value asInteger printString ] makePoint: pointOrArray [ (pointOrArray respondsTo: #do:) ifFalse: [^pointOrArray]. ^(pointOrArray at: 1) @ (pointOrArray at: 2) ] name [ "Answer the name given to the object" ^name ] numberAt: option [ ^(self at: option) asNumber asFloat ] numberAt: option put: value [ ^self at: option put: value asFloat printString ] primBind: event to: aSymbol of: anObject parameters: params [ ^self blox item: self name bind: event to: aSymbol of: anObject parameters: params ] properties [ ^properties ] create [ "If the object has not been created yet and has been initialized correctly, insert it for real in the parent canvas" self created ifTrue: [self error: 'object already created']. self checkValidity ifFalse: [self error: 'please initialize the object correctly']. name := self blox itemCreate: self ] created [ "Answer whether the object is just a placeholder or has already been inserted for real in the parent canvas" ^self name notNil ] lower [ "Move the item to the lowest position in the display list. Child widgets always obscure other item types, and the stacking order of window items is determined by sending methods to the widget object directly." self blox lower: self name ] raise [ "Move the item to the highest position in the display list. Child widgets always obscure other item types, and the stacking order of window items is determined by sending methods to the widget object directly." self blox raise: self name ] redraw [ "Force the object to be displayed in the parent canvas, creating it if it has not been inserted for real in the parent, and refresh its position if it has changed." self created ifTrue: [self blox item: self name points: self points] ifFalse: [self create] ] remove [ "Remove the object from the canvas" self blox remove: self name ] show [ "Ensure that the object is visible in the center of the canvas, scrolling it if necessary." self blox show: self name ] checkValidity [ ^true ] initializeWithProperties: aDictionary [ properties := aDictionary ] itemType [ self subclassResponsibility ] points [ self subclassResponsibility ] ] BCanvasObject subclass: BBoundingBox [ | points | boundingBox [ "Answer a Rectangle enclosing all of the receiver" ^Rectangle origin: self origin corner: self corner ] center [ "Answer the center point of the receiver" ^(self origin + self corner) / 2 ] center: center extent: extent [ "Move the object so that it is centered around the center Point and its size is given by the extent Point. No changes take place until you invoke the #create (if the object has not been inserted in the canvas yet) or the #redraw method." self origin: center - ((self makePoint: extent) / 2) extent: extent ] corner [ "Answer the Point specifying the lower-right corner of the receiver" ^self makePoint: (points at: 2) ] corner: pointOrArray [ "Set the Point specifying the lower-right corner of the receiver; pointOrArray can be a Point or a two-item Array. No changes take place until you invoke the #create (if the object has not been inserted in the canvas yet) or the #redraw method." points at: 2 put: pointOrArray ] extent [ "Answer a Point specifying the size of the receiver" ^self corner - self origin ] extent: pointOrArray [ "Set the Point specifying the size of the receiver; pointOrArray can be a Point or a two-item Array. No changes take place until you invoke the #create (if the object has not been inserted in the canvas yet) or the #redraw method." self corner: self origin + (self makePoint: pointOrArray) ] moveBy: pointOrArray [ "Move the object by the amount indicated by pointOrArray: that is, its whole bounding box is shifted by that amount. No changes take place until you invoke the #create (if the object has not been inserted in the canvas yet) or the #redraw method." | point | point := self makePoint: pointOrArray. self origin: self origin + point corner: self corner + point ] origin [ "Answer the Point specifying the top-left corner of the receiver" ^self makePoint: (points at: 1) ] origin: pointOrArray [ "Set the Point specifying the top-left corner of the receiver; pointOrArray can be a Point or a two-item Array. No changes take place until you invoke the #create (if the object has not been inserted in the canvas yet) or the #redraw method." points at: 1 put: pointOrArray ] origin: originPointOrArray corner: cornerPointOrArray [ "Set the bounding box of the object, based on a Point specifying the top-left corner of the receiver and another specifying the bottom-right corner; the two parameters can both be Points or two-item Arrays. No changes take place until you invoke the #create (if the object has not been inserted in the canvas yet) or the #redraw method." points at: 1 put: originPointOrArray; at: 2 put: cornerPointOrArray ] origin: originPointOrArray extent: extentPointOrArray [ "Set the bounding box of the object, based on a Point specifying the top-left corner of the receiver and another specifying its size; the two parameters can both be Points or two-item Arrays. No changes take place until you invoke the #create (if the object has not been inserted in the canvas yet) or the #redraw method." points at: 1 put: originPointOrArray; at: 2 put: self origin + (self makePoint: extentPointOrArray) ] checkValidity [ ^self points allSatisfy: [:each | each notNil] ] initializeWithProperties: aDictionary [ super initializeWithProperties: aDictionary. points := Array new: 2 ] points [ ^points ] ] BBoundingBox subclass: BLine [ cap [ "Answer the way in which caps are to be drawn at the endpoints of the line. The answer may be #butt (the default), #projecting, or #round)." ^self at: #capstyle ] cap: aSymbol [ "Set the way in which caps are to be drawn at the endpoints of the line. aSymbol may be #butt (the default), #projecting, or #round)." self at: #capstyle put: aSymbol ] width [ "Answer the width with which the line is drawn." ^self integerAt: #width ] width: pixels [ "Set the width with which the line is drawn." ^self integerAt: #width put: pixels ] itemType [ ^'line' ] ] BBoundingBox subclass: BRectangle [ outlineColor [ "Answer the color with which the outline of the rectangle is drawn." ^self at: #outline ] outlineColor: color [ "Set the color with which the outline of the rectangle is drawn." ^self at: #outline put: color ] width [ "Answer the width with which the outline of the rectangle is drawn." ^self integerAt: #width ] width: pixels [ "Set the width with which the outline of the rectangle is drawn." ^self integerAt: #width put: pixels ] itemType [ ^'rectangle' ] ] BRectangle subclass: BOval [ itemType [ ^'oval' ] ] BOval subclass: BArc [ endAngle [ "Answer the ending of the angular range that is occupied by the arc, expressed in degrees" ^self startAngle + self sweepAngle ] endAngle: angle [ "Set the ending of the angular range that is occupied by the arc, expressed in degrees" ^self sweepAngle: angle - self startAngle ] fillChord [ "Specify that the arc will be filled by painting an area delimited by the arc and the chord that joins the arc's endpoints." self at: #style put: 'chord' ] fillSlice [ "Specify that the arc will be filled by painting an area delimited by the arc and the two radii joins the center of the arc with each of the endpoints (that is, that a pie slice will be drawn)." self at: #style put: 'pieslice' ] from [ "Answer the starting point of the arc in cartesian coordinates" | startAngle | startAngle := self startAngle degreesToRadians. ^self extent * (startAngle cos @ startAngle sin) / 2 + self center ] from: aPoint [ "Set the starting point of the arc in cartesian coordinates" self startAngle: ((aPoint - self center) / self extent) arcTan radiansToDegrees ] from: start to: end [ "Set the two starting points of the arc in cartesian coordinates" self from: start; to: end ] startAngle [ "Answer the beginning of the angular range that is occupied by the arc, expressed in degrees" ^self integerAt: #start ] startAngle: angle [ "Set the beginning of the angular range that is occupied by the arc, expressed in degrees" self integerAt: #start put: angle ] sweepAngle [ "Answer the size of the angular range that is occupied by the arc, expressed in degrees" ^self integerAt: #extent ] sweepAngle: angle [ "Set the size of the angular range that is occupied by the arc, expressed in degrees" self integerAt: #extent put: angle ] to [ "Answer the ending point of the arc in cartesian coordinates" | endAngle | endAngle := self endAngle degreesToRadians. ^self extent * (endAngle cos @ endAngle sin) / 2 + self center ] to: aPoint [ "Set the ending point of the arc in cartesian coordinates" self endAngle: ((aPoint - self center) / self extent) arcTan radiansToDegrees ] initializeWithProperties: aDictionary [ super initializeWithProperties: aDictionary. self properties at: #style ifAbsentPut: ['arc'] ] itemType [ ^'arc' ] ] BCanvasObject subclass: BPolyline [ | closed points boundingBox | boundingBox [ ^boundingBox ] cap [ "Answer the way in which caps are to be drawn at the endpoints of the line. This option is only available for open polylines. If you want to set it for a closed polylines, draw an open one on top of it." self closed == true ifTrue: [self error: 'can''t set cap style for closed polylines']. ^self at: #capstyle ] cap: aSymbol [ "Set the way in which caps are to be drawn at the endpoints of the line. aSymbol may be #butt (the default), #projecting, or #round). This option is only available for open polylines. If you want to set it for a closed polylines, draw an open one on top of it." self closed == true ifTrue: [self error: 'can''t set cap style for closed polylines']. ^self at: #capstyle put: aSymbol ] closed [ "Answer whether the polyline is an open or a closed one." ^closed ] closed: aBoolean [ "Set whether the polyline is an open or a closed one. This option may be set only once." self closed isNil ifFalse: [self error: 'you can set the closed style only once']. closed := aBoolean ] join [ "Answer the way in which joints are to be drawn at the vertices of the line. This option is only available for open polylines. If you want to set it for a closed polylines, draw an open one on top of it." self closed == true ifTrue: [self error: 'can''t set join style for closed polylines']. ^self at: #joinstyle ] join: aSymbol [ "Answer the way in which joints are to be drawn at the vertices of the line. aSymbol can be #bevel, #miter (the default) or #round. This option is only available for open polylines. If you want to set it for a closed polylines, draw an open one on top of it." self closed == true ifTrue: [self error: 'can''t set join style for closed polylines']. ^self at: #joinstyle put: aSymbol ] outlineColor [ "Answer the color with which the outline of the polyline is drawn. This option is only available for closed polylines." self closed == true ifFalse: [self error: 'outline color not defined for open polylines']. ^self at: #outline ] outlineColor: color [ "Set the color with which the outline of the polyline is drawn. This option is only available for closed polylines." self closed == true ifFalse: [self error: 'outline color not defined for open polylines']. ^self at: #outline put: color ] points [ "Answer the points that are vertices of the polyline." ^points ] points: arrayOfPointsOrArrays [ "Set the points that are vertices of the polyline. Each of the items of arrayOfPointsOrArrays can be a Point or a two-element Array. Note that no changes take place until you invoke the #create (if the object has not been inserted in the canvas yet) or the #redraw method." points := arrayOfPointsOrArrays collect: [:each | self makePoint: each]. boundingBox := Rectangle origin: points anyOne copy corner: points anyOne copy. points do: [:each | boundingBox left: (boundingBox left min: each x); top: (boundingBox top min: each y); right: (boundingBox right max: each x); bottom: (boundingBox bottom max: each y)] ] width [ "Answer the width with which the polyline (or its outline if it is a closed one) is drawn." ^self integerAt: #width ] width: pixels [ "Set the width with which the polyline (or its outline if it is a closed one) is drawn." ^self integerAt: #width put: pixels ] checkValidity [ ^points notNil ] itemType [ self closed isNil ifTrue: [self closed: false]. ^self closed ifTrue: ['polygon'] ifFalse: ['line'] ] ] BPolyline subclass: BSpline [ | smoothness | smoothness [ "Answer the degree of smoothness desired for curves. Each spline will be approximated with this number of line segments." ^self integerAt: #splinesteps ] smoothness: anInteger [ "Set the degree of smoothness desired for curves. Each spline will be approximated with this number of line segments." ^self integerAt: #splinesteps put: anInteger ] initializeWithProperties: aDictionary [ super initializeWithProperties: aDictionary. self at: #smooth put: '1' ] ] BBoundingBox subclass: BEmbeddedText [ | anchor | font [ "Answer the value of the font option for the canvas object. Specifies the font to use when drawing text inside the widget. The font can be given as either an X font name or a Blox font description string. X font names are given as many fields, each led by a minus, and each of which can be replaced by an * to indicate a default value is ok: foundry, family, weight, slant, setwidth, addstyle, pixel size, point size (the same as pixel size for historical reasons), horizontal resolution, vertical resolution, spacing, width, charset and character encoding. Blox font description strings have three fields, which must be separated by a space and of which only the first is mandatory: the font family, the font size in points (or in pixels if a negative value is supplied), and a number of styles separated by a space (valid styles are normal, bold, italic, underline and overstrike). Examples of valid fonts are ``Helvetica 10 Bold'', ``Times -14'', ``Futura Bold Underline''. You must enclose the font family in braces if it is made of two or more words." ^self at: #font ] font: font [ "Set the value of the font option for the canvas object. Specifies the font to use when drawing text inside the widget. The font can be given as either an X font name or a Blox font description string. X font names are given as many fields, each led by a minus, and each of which can be replaced by an * to indicate a default value is ok: foundry, family, weight, slant, setwidth, addstyle, pixel size, point size (the same as pixel size for historical reasons), horizontal resolution, vertical resolution, spacing, width, charset and character encoding. Blox font description strings have three fields, which must be separated by a space and of which only the first is mandatory: the font family, the font size in points (or in pixels if a negative value is supplied), and a number of styles separated by a space (valid styles are normal, bold, italic, underline and overstrike). Examples of valid fonts are ``Helvetica 10 Bold'', ``Times -14'', ``Futura Bold Underline''. You must enclose the font family in braces if it is made of two or more words." ^self at: #font put: font ] justify [ "Answer how to justify the text within its bounding region." ^self at: #justify ] justify: aSymbol [ "Sets how to justify the text within its bounding region. Can be #left, #right or #center (the default)." aSymbol == #left ifTrue: [self at: #anchor put: 'w'. anchor := #leftCenter]. aSymbol == #right ifTrue: [self at: #anchor put: 'e'. anchor := #rightCenter]. aSymbol == #center ifTrue: [self at: #anchor put: 'center'. anchor := #center]. self at: #justify put: aSymbol. self redraw. ^aSymbol ] redraw [ "Force the object to be displayed in the parent canvas, creating it if it has not been inserted for real in the parent, and refresh its position." self at: #width put: (self corner x - self origin x) abs asInteger printString. super redraw ] text [ "Answer the text that is printed by the object" ^self at: #text ] text: aString [ "Set the text that is printed by the object" ^self at: #text put: aString ] itemType [ ^'text' ] points [ "Answer a single point around which the text is positioned. Vertically, the text is centered on the point. Horizontally, the point can give the leftmost, rightmost or center coordinate depending on the setting of #justify." | anchorPoint | anchor isNil ifTrue: [anchor := #center]. anchorPoint := self boundingBox perform: anchor. ^Array with: anchorPoint ] postCopy [ "Set the anchor variable" self justify: self justify ] ] BBoundingBox subclass: BEmbeddedImage [ | imageChanged data shared | copyInto: aBlox [ "Answer a new BCanvasObject identical to this but displayed into another canvas, newCanvas. The new instance is not created at the time it is returned." shared value: shared + 1. ^(super copyInto: aBlox) refCount: shared sharedData: data; yourself ] create [ imageChanged := true. super create ] data [ "Answer the data of the image. The result will be a String containing image data either as Base-64 encoded GIF data, as XPM data, or as PPM data." ^data ] data: aString [ "Set the data of the image. aString may contain the data either as Base-64 encoded GIF data, as XPM data, or as PPM data. No changes are visible until you toggle a redraw using the appropriate method." (shared isNil or: [shared value > 1]) ifTrue: [self decRefCount. shared := ValueHolder with: 1. self blox tclEval: 'image create photo'. self at: #image put: self blox tclResult]. data := aString. imageChanged := true ] redraw [ "Force the object to be displayed in the parent canvas, creating it if it has not been inserted for real in the parent, and refresh its position and image data if it has changed." imageChanged ifTrue: [self drawImage]. super redraw ] decRefCount [ shared value: shared - 1. shared value = 0 ifTrue: [self blox tclEval: 'image delete ' , (self at: #image)] ] destroyed [ self decRefCount. super destroyed ] drawImage [ shared isNil ifTrue: [^self]. self blox tclEval: (self at: #image) , ' blank'. data isNil ifTrue: [^self]. imageChanged := false. self blox tclEval: (self at: #image) , ' configure -data ' , data asTkImageString ] itemType [ ^'image' ] points [ ^Array with: self boundingBox center ] refCount: rc sharedData: dataString [ data := dataString. shared := rc ] ] "-------------------------- BCanvas class -----------------------------" "-------------------------- BScrolledCanvas class -----------------------------" "-------------------------- BCanvasObject class -----------------------------" "-------------------------- BBoundingBox class -----------------------------" "-------------------------- BLine class -----------------------------" "-------------------------- BRectangle class -----------------------------" "-------------------------- BOval class -----------------------------" "-------------------------- BArc class -----------------------------" "-------------------------- BPolyline class -----------------------------" "-------------------------- BSpline class -----------------------------" "-------------------------- BEmbeddedText class -----------------------------" "-------------------------- BEmbeddedImage class -----------------------------" smalltalk-3.2.5/packages/gtk/0000755000175000017500000000000012130456013013044 500000000000000smalltalk-3.2.5/packages/gtk/Makefile.frag0000644000175000017500000000104612130343734015350 00000000000000GTK_FILES = \ packages/gtk/GtkDecl.st packages/gtk/GtkImpl.st packages/gtk/MoreFuncs.st packages/gtk/MoreStructs.st packages/gtk/example_arrow.st packages/gtk/example_aspectframe.st packages/gtk/example_buttonbox.st packages/gtk/example_entry.st packages/gtk/example_eventbox.st packages/gtk/example_hello.st packages/gtk/example_tictactoe.st packages/gtk/example_tree.st packages/gtk/Structs.st packages/gtk/Enums.st packages/gtk/Funcs.st $(GTK_FILES): $(srcdir)/packages/gtk/stamp-classes: $(GTK_FILES) touch $(srcdir)/packages/gtk/stamp-classes smalltalk-3.2.5/packages/gtk/placer.c0000644000175000017500000006241012123404352014402 00000000000000/*********************************************************************** * * Gtk+ wrappers for GNU Smalltalk - Placer geometry manager * ***********************************************************************/ /*********************************************************************** * * Copyright 2003, 2006 Free Software Foundation, Inc. * Written by Paolo Bonzini. * * This file is part of GNU Smalltalk. * * GNU Smalltalk is free software; you can redistribute it and/or modify it * under the terms of the GNU General Public License as published by the Free * Software Foundation; either version 2, or (at your option) any later * version. * * Linking GNU Smalltalk statically or dynamically with other modules is * making a combined work based on GNU Smalltalk. Thus, the terms and * conditions of the GNU General Public License cover the whole * combination. * * In addition, as a special exception, the Free Software Foundation * give you permission to combine GNU Smalltalk with free software * programs or libraries that are released under the GNU LGPL and with * independent programs running under the GNU Smalltalk virtual machine. * * You may copy and distribute such a system following the terms of the * GNU GPL for GNU Smalltalk and the licenses of the other code * concerned, provided that you include the source code of that other * code when and as the GNU GPL requires distribution of source code. * * Note that people who make modified versions of GNU Smalltalk are not * obligated to grant this special exception for their modified * versions; it is their choice whether to do so. The GNU General * Public License gives permission to release a modified version without * this exception; this exception also makes it possible to release a * modified version which carries forward this exception. * * GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or * FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for * more details. * * You should have received a copy of the GNU General Public License along with * GNU Smalltalk; see the file COPYING. If not, write to the Free Software * Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * ***********************************************************************/ /* Shamelessly based on the GtkFixed geometry manager. */ #include "placer.h" enum { CHILD_PROP_0, CHILD_PROP_X, CHILD_PROP_Y, CHILD_PROP_WIDTH, CHILD_PROP_HEIGHT, CHILD_PROP_REL_X, CHILD_PROP_REL_Y, CHILD_PROP_REL_WIDTH, CHILD_PROP_REL_HEIGHT, }; static void gtk_placer_class_init (GtkPlacerClass *klass); static void gtk_placer_init (GtkPlacer *placer); static void gtk_placer_realize (GtkWidget *widget); static void gtk_placer_size_request (GtkWidget *widget, GtkRequisition *requisition); static void gtk_placer_size_allocate (GtkWidget *widget, GtkAllocation *allocation); static void gtk_placer_add (GtkContainer *container, GtkWidget *widget); static void gtk_placer_remove (GtkContainer *container, GtkWidget *widget); static void gtk_placer_forall (GtkContainer *container, gboolean include_internals, GtkCallback callback, gpointer callback_data); static GType gtk_placer_child_type (GtkContainer *container); static void gtk_placer_set_child_property (GtkContainer *container, GtkWidget *child, guint property_id, const GValue *value, GParamSpec *pspec); static void gtk_placer_get_child_property (GtkContainer *container, GtkWidget *child, guint property_id, GValue *value, GParamSpec *pspec); static GtkContainerClass *parent_class = NULL; GType gtk_placer_get_type (void) { static GType placer_type = 0; if (!placer_type) { static const GTypeInfo placer_info = { sizeof (GtkPlacerClass), NULL, /* base_init */ NULL, /* base_finalize */ (GClassInitFunc) gtk_placer_class_init, NULL, /* class_finalize */ NULL, /* class_data */ sizeof (GtkPlacer), 0, /* n_preallocs */ (GInstanceInitFunc) gtk_placer_init, }; placer_type = g_type_register_static (GTK_TYPE_CONTAINER, "GtkPlacer", &placer_info, 0); } return placer_type; } static void gtk_placer_class_init (GtkPlacerClass *class) { GtkWidgetClass *widget_class; GtkContainerClass *container_class; widget_class = (GtkWidgetClass*) class; container_class = (GtkContainerClass*) class; parent_class = g_type_class_peek_parent (class); widget_class->realize = gtk_placer_realize; widget_class->size_request = gtk_placer_size_request; widget_class->size_allocate = gtk_placer_size_allocate; container_class->add = gtk_placer_add; container_class->remove = gtk_placer_remove; container_class->forall = gtk_placer_forall; container_class->child_type = gtk_placer_child_type; container_class->set_child_property = gtk_placer_set_child_property; container_class->get_child_property = gtk_placer_get_child_property; gtk_container_class_install_child_property (container_class, CHILD_PROP_X, g_param_spec_int ("x", "X position", "X position of child widget", G_MININT, G_MAXINT, 0, G_PARAM_READWRITE)); gtk_container_class_install_child_property (container_class, CHILD_PROP_Y, g_param_spec_int ("y", "Y position", "Y position of child widget", G_MININT, G_MAXINT, 0, G_PARAM_READWRITE)); gtk_container_class_install_child_property (container_class, CHILD_PROP_WIDTH, g_param_spec_int ("width", "Width", "Width of child widget", G_MININT, G_MAXINT, 0, G_PARAM_READWRITE)); gtk_container_class_install_child_property (container_class, CHILD_PROP_HEIGHT, g_param_spec_int ("height", "Height", "Height of child widget", G_MININT, G_MAXINT, 0, G_PARAM_READWRITE)); gtk_container_class_install_child_property (container_class, CHILD_PROP_REL_X, g_param_spec_int ("rel_x", "X relative position", "X relative position in parent widget", 0, 32767, 0, G_PARAM_READWRITE)); gtk_container_class_install_child_property (container_class, CHILD_PROP_REL_Y, g_param_spec_int ("rel_y", "Y relative position", "Y relative position in parent widget", 0, 32767, 0, G_PARAM_READWRITE)); gtk_container_class_install_child_property (container_class, CHILD_PROP_REL_WIDTH, g_param_spec_int ("rel_width", "Relative width", "Relative width in parent widget", 0, 32767, 0, G_PARAM_READWRITE)); gtk_container_class_install_child_property (container_class, CHILD_PROP_REL_HEIGHT, g_param_spec_int ("rel_height", "Relative height", "Relative height in parent widget", 0, 32767, 0, G_PARAM_READWRITE)); } static GType gtk_placer_child_type (GtkContainer *container) { return GTK_TYPE_WIDGET; } static void gtk_placer_init (GtkPlacer *placer) { GTK_WIDGET_SET_FLAGS (placer, GTK_NO_WINDOW); placer->children = NULL; } GtkWidget* gtk_placer_new (void) { return g_object_new (GTK_TYPE_PLACER, NULL); } static GtkPlacerChild* get_child (GtkPlacer *placer, GtkWidget *widget) { GList *children; children = placer->children; while (children) { GtkPlacerChild *child; child = children->data; children = children->next; if (child->widget == widget) return child; } return NULL; } void gtk_placer_put (GtkPlacer *placer, GtkWidget *widget, gint x, gint y, gint width, gint height, gint rel_x, gint rel_y, gint rel_width, gint rel_height) { GtkPlacerChild *child_info; g_return_if_fail (GTK_IS_PLACER (placer)); g_return_if_fail (GTK_IS_WIDGET (placer)); g_return_if_fail ((rel_x & ~32767) == 0); g_return_if_fail ((rel_y & ~32767) == 0); g_return_if_fail ((rel_width & ~32767) == 0); g_return_if_fail ((rel_height & ~32767) == 0); child_info = g_new (GtkPlacerChild, 1); child_info->widget = widget; child_info->x = x; child_info->y = y; child_info->width = width; child_info->height = height; child_info->rel_x = rel_x; child_info->rel_y = rel_y; child_info->rel_width = rel_width; child_info->rel_height = rel_height; gtk_widget_set_parent (widget, GTK_WIDGET (placer)); placer->children = g_list_append (placer->children, child_info); } static void gtk_placer_move_internal (GtkPlacer *placer, GtkWidget *widget, gboolean change_x, gint x, gboolean change_y, gint y, gboolean change_width, gint width, gboolean change_height, gint height, gboolean change_rel_x, gint rel_x, gboolean change_rel_y, gint rel_y, gboolean change_rel_width, gint rel_width, gboolean change_rel_height, gint rel_height) { GtkPlacerChild *child; g_return_if_fail (GTK_IS_PLACER (placer)); g_return_if_fail (GTK_IS_WIDGET (widget)); g_return_if_fail (widget->parent == GTK_WIDGET (placer)); g_return_if_fail (!change_rel_x || (rel_x & ~32767) == 0); g_return_if_fail (!change_rel_y || (rel_y & ~32767) == 0); g_return_if_fail (!change_rel_width || (rel_width & ~32767) == 0); g_return_if_fail (!change_rel_height || (rel_height & ~32767) == 0); child = get_child (placer, widget); g_assert (child); gtk_widget_freeze_child_notify (widget); if (change_x) { child->x = x; gtk_widget_child_notify (widget, "x"); } if (change_y) { child->y = y; gtk_widget_child_notify (widget, "y"); } if (change_width) { child->width = width; gtk_widget_child_notify (widget, "width"); } if (change_height) { child->height = height; gtk_widget_child_notify (widget, "height"); } if (change_rel_x) { child->rel_x = rel_x; gtk_widget_child_notify (widget, "rel_x"); } if (change_rel_y) { child->rel_y = rel_y; gtk_widget_child_notify (widget, "rel_y"); } if (change_rel_width) { child->rel_width = rel_width; gtk_widget_child_notify (widget, "rel_width"); } if (change_rel_height) { child->rel_height = rel_height; gtk_widget_child_notify (widget, "rel_height"); } gtk_widget_thaw_child_notify (widget); if (GTK_WIDGET_VISIBLE (widget) && GTK_WIDGET_VISIBLE (placer)) gtk_widget_queue_resize (GTK_WIDGET (placer)); } void gtk_placer_move (GtkPlacer *placer, GtkWidget *widget, gint x, gint y) { gtk_placer_move_internal (placer, widget, TRUE, x, TRUE, y, FALSE, 0, FALSE, 0, FALSE, 0, FALSE, 0, FALSE, 0, FALSE, 0); } void gtk_placer_resize (GtkPlacer *placer, GtkWidget *widget, gint width, gint height) { gtk_placer_move_internal (placer, widget, FALSE, 0, FALSE, 0, TRUE, width, TRUE, height, FALSE, 0, FALSE, 0, FALSE, 0, FALSE, 0); } void gtk_placer_move_rel (GtkPlacer *placer, GtkWidget *widget, gint rel_x, gint rel_y) { gtk_placer_move_internal (placer, widget, FALSE, 0, FALSE, 0, FALSE, 0, FALSE, 0, TRUE, rel_x, TRUE, rel_y, FALSE, 0, FALSE, 0); } void gtk_placer_resize_rel (GtkPlacer *placer, GtkWidget *widget, gint rel_width, gint rel_height) { gtk_placer_move_internal (placer, widget, FALSE, 0, FALSE, 0, FALSE, 0, FALSE, 0, FALSE, 0, FALSE, 0, TRUE, rel_width, TRUE, rel_height); } static void gtk_placer_set_child_property (GtkContainer *container, GtkWidget *child, guint property_id, const GValue *value, GParamSpec *pspec) { int val; switch (property_id) { case CHILD_PROP_X: case CHILD_PROP_Y: case CHILD_PROP_WIDTH: case CHILD_PROP_HEIGHT: case CHILD_PROP_REL_X: case CHILD_PROP_REL_Y: case CHILD_PROP_REL_WIDTH: case CHILD_PROP_REL_HEIGHT: val = g_value_get_int (value); gtk_placer_move_internal (GTK_PLACER (container), child, property_id == CHILD_PROP_X, val, property_id == CHILD_PROP_Y, val, property_id == CHILD_PROP_WIDTH, val, property_id == CHILD_PROP_HEIGHT, val, property_id == CHILD_PROP_REL_X, val, property_id == CHILD_PROP_REL_Y, val, property_id == CHILD_PROP_REL_WIDTH, val, property_id == CHILD_PROP_REL_HEIGHT, val); break; default: GTK_CONTAINER_WARN_INVALID_CHILD_PROPERTY_ID (container, property_id, pspec); break; } } static void gtk_placer_get_child_property (GtkContainer *container, GtkWidget *child, guint property_id, GValue *value, GParamSpec *pspec) { GtkPlacerChild *placer_child; placer_child = get_child (GTK_PLACER (container), child); switch (property_id) { case CHILD_PROP_X: g_value_set_int (value, placer_child->x); break; case CHILD_PROP_Y: g_value_set_int (value, placer_child->y); break; case CHILD_PROP_WIDTH: g_value_set_int (value, placer_child->width); break; case CHILD_PROP_HEIGHT: g_value_set_int (value, placer_child->height); break; case CHILD_PROP_REL_X: g_value_set_int (value, placer_child->rel_x); break; case CHILD_PROP_REL_Y: g_value_set_int (value, placer_child->rel_y); break; case CHILD_PROP_REL_WIDTH: g_value_set_int (value, placer_child->rel_width); break; case CHILD_PROP_REL_HEIGHT: g_value_set_int (value, placer_child->rel_height); break; default: GTK_CONTAINER_WARN_INVALID_CHILD_PROPERTY_ID (container, property_id, pspec); break; } } static void gtk_placer_realize (GtkWidget *widget) { GdkWindowAttr attributes; gint attributes_mask; if (GTK_WIDGET_NO_WINDOW (widget)) GTK_WIDGET_CLASS (parent_class)->realize (widget); else { GTK_WIDGET_SET_FLAGS (widget, GTK_REALIZED); attributes.window_type = GDK_WINDOW_CHILD; attributes.x = widget->allocation.x; attributes.y = widget->allocation.y; attributes.width = widget->allocation.width; attributes.height = widget->allocation.height; attributes.wclass = GDK_INPUT_OUTPUT; attributes.visual = gtk_widget_get_visual (widget); attributes.colormap = gtk_widget_get_colormap (widget); attributes.event_mask = gtk_widget_get_events (widget); attributes.event_mask |= GDK_EXPOSURE_MASK | GDK_BUTTON_PRESS_MASK; attributes_mask = GDK_WA_X | GDK_WA_Y | GDK_WA_VISUAL | GDK_WA_COLORMAP; widget->window = gdk_window_new (gtk_widget_get_parent_window (widget), &attributes, attributes_mask); gdk_window_set_user_data (widget->window, widget); widget->style = gtk_style_attach (widget->style, widget->window); gtk_style_set_background (widget->style, widget->window, GTK_STATE_NORMAL); } } static void gtk_placer_size_request (GtkWidget *widget, GtkRequisition *requisition) { GtkPlacer *placer; GtkPlacerChild *child; GList *children; GtkRequisition child_requisition; gint border_width; gint height, width; placer = GTK_PLACER (widget); border_width = GTK_CONTAINER (placer)->border_width; requisition->width = 0; requisition->height = 0; children = placer->children; while (children) { child = children->data; children = children->next; if (GTK_WIDGET_VISIBLE (child->widget)) { gtk_widget_size_request (child->widget, &child_requisition); /* Start with the widget's requested size and account for the extra space that we reserve (which is empty, and hence added, for negative sizes, and full, and hence subtracted, for positive sizes). Then ensure that it fits into the requested relative height if there is one; otherwise, if there's a relative position, align the widget to the right (ensure that there is space on the right). Then add up the relative offset. The formula to ensure that there is space on the right is as follows: if the requested height is 200, and the left border is at 30%, we need at least 200 / (1 - 0.3): this allocates 285 pixels and puts the widgets at pixels 85 to 285. */ height = child_requisition.height - child->height; width = child_requisition.width - child->width; if (child->rel_height) height = height / (child->rel_height / 32767.0); else height = height / (1.0 - child->rel_y / 32767.0); if (child->rel_width) width = width / (child->rel_width / 32767.0); else width = width / (1.0 - child->rel_x / 32767.0); requisition->height = MAX (height + child->y, requisition->height); requisition->width = MAX (width + child->x, requisition->width); } } requisition->height += border_width * 2; requisition->width += border_width * 2; } static void gtk_placer_size_allocate (GtkWidget *widget, GtkAllocation *allocation) { GtkPlacer *placer; GtkPlacerChild *child; GtkAllocation child_allocation; GtkRequisition child_requisition; GList *children; guint16 border_width; gdouble rel_width_scale, rel_height_scale; placer = GTK_PLACER (widget); widget->allocation = *allocation; if (!GTK_WIDGET_NO_WINDOW (widget)) { if (GTK_WIDGET_REALIZED (widget)) gdk_window_move_resize (widget->window, allocation->x, allocation->y, allocation->width, allocation->height); } border_width = GTK_CONTAINER (placer)->border_width; rel_width_scale = (allocation->width - 2 * border_width) / 32767.0; rel_height_scale = (allocation->height - 2 * border_width) / 32767.0; children = placer->children; while (children) { child = children->data; children = children->next; if (GTK_WIDGET_VISIBLE (child->widget)) { gtk_widget_get_child_requisition (child->widget, &child_requisition); child_allocation.x = child->x + border_width + child->rel_x * rel_width_scale; child_allocation.y = child->y + border_width + child->rel_y * rel_height_scale; if (GTK_WIDGET_NO_WINDOW (widget)) { child_allocation.x += allocation->x; child_allocation.y += allocation->y; } if (!child->rel_width) child_allocation.width = child_requisition.width; else child_allocation.width = child->rel_width * rel_width_scale; if (!child->rel_height) child_allocation.height = child_requisition.height; else child_allocation.height = child->rel_height * rel_height_scale; child_allocation.width += child->width; child_allocation.height += child->height; child_allocation.width = MAX (child_allocation.width, 0); child_allocation.height = MAX (child_allocation.height, 0); gtk_widget_size_allocate (child->widget, &child_allocation); } } } static void gtk_placer_add (GtkContainer *container, GtkWidget *widget) { gtk_placer_put (GTK_PLACER (container), widget, 0, 0, 0, 0, 0, 0, 32767, 32767); } static void gtk_placer_remove (GtkContainer *container, GtkWidget *widget) { GtkPlacer *placer; GtkPlacerChild *child; GList *children; placer = GTK_PLACER (container); children = placer->children; while (children) { child = children->data; if (child->widget == widget) { gboolean was_visible = GTK_WIDGET_VISIBLE (widget); gtk_widget_unparent (widget); placer->children = g_list_remove_link (placer->children, children); g_list_free (children); g_free (child); if (was_visible && GTK_WIDGET_VISIBLE (container)) gtk_widget_queue_resize (GTK_WIDGET (container)); break; } children = children->next; } } static void gtk_placer_forall (GtkContainer *container, gboolean include_internals, GtkCallback callback, gpointer callback_data) { GtkPlacer *placer; GtkPlacerChild *child; GList *children; g_return_if_fail (callback != NULL); placer = GTK_PLACER (container); children = placer->children; while (children) { child = children->data; children = children->next; (* callback) (child->widget, callback_data); } } /** * gtk_placer_set_has_window: * @placer: a #GtkPlacer * @has_window: %TRUE if a separate window should be created * * Sets whether a #GtkPlacer widget is created with a separate * #GdkWindow for widget->window or not. (By default, it will be * created with no separate #GdkWindow). This function must be called * while the #GtkPlacer is not realized, for instance, immediately after the * window is created. **/ void gtk_placer_set_has_window (GtkPlacer *placer, gboolean has_window) { g_return_if_fail (GTK_IS_PLACER (placer)); g_return_if_fail (!GTK_WIDGET_REALIZED (placer)); if (!has_window != GTK_WIDGET_NO_WINDOW (placer)) { if (has_window) GTK_WIDGET_UNSET_FLAGS (placer, GTK_NO_WINDOW); else GTK_WIDGET_SET_FLAGS (placer, GTK_NO_WINDOW); } } /** * gtk_placer_get_has_window: * @placer: a #GtkWidget * * Gets whether the #GtkPlacer has it's own #GdkWindow. * See gdk_placer_set_has_window(). * * Return value: %TRUE if @placer has its own window. **/ gboolean gtk_placer_get_has_window (GtkPlacer *placer) { g_return_val_if_fail (GTK_IS_PLACER (placer), FALSE); return !GTK_WIDGET_NO_WINDOW (placer); } smalltalk-3.2.5/packages/gtk/MoreFuncs.st0000644000175000017500000001760212130343734015250 00000000000000GMainContext extend [ iterate [ ] ] Gtk class extend [ main: aSemaphore [ ] gstGtkInit [ "For backwards compatibility." ] gtkInitialized [ ] ] GLib class extend [ register: anObject forType: gType [ ] oopType [ ] ] GObject extend [ connectSignalAfter: name to: handler selector: sel userData: userData [ ] connectSignalAfter: name to: handler selector: sel [ ] connectSignal: name to: handler selector: sel userData: userData [ ] connectSignal: name to: handler selector: sel [ ] disconnectSignal: anInteger [ ] narrow [ ] free [ ] propertiesAt: name [ ] propertiesAt: name put: anObject [ ] ] GtkAccelGroup extend [ connect: accelKey accelModes: accelMods accelFlags: accelFlags receiver: receiver selector: selector userData: userData [ ] connect: accelKey accelModes: accelMods accelFlags: accelFlags receiver: receiver selector: selector [ ] ] "These have a weird name in C." GtkObject extend [ signalEmit: signal args: argsArray [ ] signalEmitByName: signal args: argsArray [ ] signalNEmissions: signal [ ] signalNEmissionsByName: signal [ ] signalEmitStop: signal [ ] signalEmitStopByName: signal [ ] ] GTK.GdkDrawable extend [ cairoCreate [ ] ] GtkWidget extend [ getAllocation [ ] getWindow [ ] getState [ ] getFlags [ ] setFlags: flags [ ] unsetFlags: flags [ ] ] GtkContainer extend [ child: widget propertiesAt: name [ ] child: widget propertiesAt: name put: anObject [ ] ] GValue class extend [ typeFromName: aName [ ] ] GtkTreeModel extend [ getOop: iter column: aColumn [ ] ] GtkTreeStore extend [ setOop: iter column: aColumn value: aValue [ ] ] GtkListStore extend [ setOop: iter column: aColumn value: aValue [ ] ] GtkDialog extend [ getVBox [ ] getActionArea [ ] ] GtkScrolledWindow extend [ getHscrollbarVisible [ ] getVscrollbarVisible [ ] ] GtkAdjustment extend [ getLower [ ] getUpper [ ] getPageSize [ ] ] "FIXME: funcs.awk is broken for these." GdkPixbufLoader extend [ write: buf count: count error: error [ ] ] GtkFileChooserDialog extend [ getFilename [ ] getCurrentFolder [ ] ] GtkContainer extend [ getFocusChild [ ] ] GTK.GtkNotebook extend [ pageNum: aGtkWidget [ ] ] Eval [ GtkTreeStore superclass: GtkTreeModel. GtkListStore superclass: GtkTreeModel ] smalltalk-3.2.5/packages/gtk/GtkDecl.st0000644000175000017500000000515312130343734014662 00000000000000"====================================================================== | | Smalltalk Gtk+ bindings (loading script). | ======================================================================" "====================================================================== | | Copyright 2001, 2003, 2009 Free Software Foundation, Inc. | Written by Paolo Bonzini. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LESSER. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" Object subclass: Pango [ ] Object subclass: Gdk [ ] Object subclass: Gtk [ ] Object subclass: Atk [ ] Object subclass: GLib [ GLib class [ | gtkTypes | ] GLib class >> registerAllTypes [ gtkTypes isNil ifTrue: [gtkTypes := OrderedCollection new]. gtkTypes do: [:each | self register: each forType: each getType] ] GLib class >> registerType: aClass [ gtkTypes isNil ifTrue: [gtkTypes := OrderedCollection new]. gtkTypes addLast: aClass ] GLib class >> update: anObject [ anObject == #returnFromSnapshot ifTrue: [self registerAllTypes] ] ] Object subclass: GQuark [ ] CObject subclass: GList [ ] CObject subclass: GSList [ ] CObject subclass: GdkEvent [ ] Eval [ ObjectMemory addDependent: GLib ] smalltalk-3.2.5/packages/gtk/placer.h0000644000175000017500000001213112123404352014402 00000000000000/*********************************************************************** * * Gtk+ wrappers for GNU Smalltalk - Placer geometry manager * ***********************************************************************/ /*********************************************************************** * * Copyright 2003, 2006 Free Software Foundation, Inc. * Written by Paolo Bonzini. * * This file is part of GNU Smalltalk. * * GNU Smalltalk is free software; you can redistribute it and/or modify it * under the terms of the GNU General Public License as published by the Free * Software Foundation; either version 2, or (at your option) any later * version. * * Linking GNU Smalltalk statically or dynamically with other modules is * making a combined work based on GNU Smalltalk. Thus, the terms and * conditions of the GNU General Public License cover the whole * combination. * * In addition, as a special exception, the Free Software Foundation * give you permission to combine GNU Smalltalk with free software * programs or libraries that are released under the GNU LGPL and with * independent programs running under the GNU Smalltalk virtual machine. * * You may copy and distribute such a system following the terms of the * GNU GPL for GNU Smalltalk and the licenses of the other code * concerned, provided that you include the source code of that other * code when and as the GNU GPL requires distribution of source code. * * Note that people who make modified versions of GNU Smalltalk are not * obligated to grant this special exception for their modified * versions; it is their choice whether to do so. The GNU General * Public License gives permission to release a modified version without * this exception; this exception also makes it possible to release a * modified version which carries forward this exception. * * GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or * FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for * more details. * * You should have received a copy of the GNU General Public License along with * GNU Smalltalk; see the file COPYING. If not, write to the Free Software * Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * ***********************************************************************/ /* Yes, this might seem blasphemy, but Blox has rubber-sheet geometry management and will have it even after it adopts Gtk widgets. */ #ifndef __GTK_PLACER_H__ #define __GTK_PLACER_H__ #include #include #ifdef __cplusplus extern "C" { #endif /* __cplusplus */ #define GTK_TYPE_PLACER (gtk_placer_get_type ()) #define GTK_PLACER(obj) (G_TYPE_CHECK_INSTANCE_CAST ((obj), GTK_TYPE_PLACER, GtkPlacer)) #define GTK_PLACER_CLASS(klass) (G_TYPE_CHECK_CLASS_CAST ((klass), GTK_TYPE_PLACER, GtkPlacerClass)) #define GTK_IS_PLACER(obj) (G_TYPE_CHECK_INSTANCE_TYPE ((obj), GTK_TYPE_PLACER)) #define GTK_IS_PLACER_CLASS(klass) (G_TYPE_CHECK_CLASS_TYPE ((klass), GTK_TYPE_PLACER)) #define GTK_PLACER_GET_CLASS(obj) (G_TYPE_INSTANCE_GET_CLASS ((obj), GTK_TYPE_PLACER, GtkPlacerClass)) typedef struct _GtkPlacer GtkPlacer; typedef struct _GtkPlacerClass GtkPlacerClass; typedef struct _GtkPlacerChild GtkPlacerChild; struct _GtkPlacer { GtkContainer container; GList *children; }; struct _GtkPlacerClass { GtkContainerClass parent_class; }; struct _GtkPlacerChild { GtkWidget *widget; gint x; gint y; gint width; gint height; gint rel_x; gint rel_y; gint rel_width; gint rel_height; }; GType gtk_placer_get_type (void) G_GNUC_CONST; GtkWidget* gtk_placer_new (void); void gtk_placer_put (GtkPlacer *placer, GtkWidget *widget, gint x, gint y, gint width, gint height, gint rel_x, gint rel_y, gint rel_width, gint rel_height); void gtk_placer_move (GtkPlacer *placer, GtkWidget *widget, gint x, gint y); void gtk_placer_resize (GtkPlacer *placer, GtkWidget *widget, gint width, gint height); void gtk_placer_move_rel (GtkPlacer *placer, GtkWidget *widget, gint rel_x, gint rel_y); void gtk_placer_resize_rel (GtkPlacer *placer, GtkWidget *widget, gint rel_width, gint rel_height); void gtk_placer_set_has_window (GtkPlacer *placer, gboolean has_window); gboolean gtk_placer_get_has_window (GtkPlacer *placer); #ifdef __cplusplus } #endif /* __cplusplus */ #endif /* __GTK_PLACER_H__ */ smalltalk-3.2.5/packages/gtk/gst-gtk.c0000644000175000017500000011410612130343734014520 00000000000000/*********************************************************************** * * Gtk+ wrappers for GNU Smalltalk * ***********************************************************************/ /*********************************************************************** * * Copyright 2001, 2003, 2006, 2008, 2009 Free Software Foundation, Inc. * Written by Paolo Bonzini, Norman Jordan, Mike S. Anderson. * * This file is part of GNU Smalltalk. * * GNU Smalltalk is free software; you can redistribute it and/or modify it * under the terms of the GNU General Public License as published by the Free * Software Foundation; either version 2, or (at your option) any later * version. * * Linking GNU Smalltalk statically or dynamically with other modules is * making a combined work based on GNU Smalltalk. Thus, the terms and * conditions of the GNU General Public License cover the whole * combination. * * In addition, as a special exception, the Free Software Foundation * give you permission to combine GNU Smalltalk with free software * programs or libraries that are released under the GNU LGPL and with * independent programs running under the GNU Smalltalk virtual machine. * * You may copy and distribute such a system following the terms of the * GNU GPL for GNU Smalltalk and the licenses of the other code * concerned, provided that you include the source code of that other * code when and as the GNU GPL requires distribution of source code. * * Note that people who make modified versions of GNU Smalltalk are not * obligated to grant this special exception for their modified * versions; it is their choice whether to do so. The GNU General * Public License gives permission to release a modified version without * this exception; this exception also makes it possible to release a * modified version which carries forward this exception. * * GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or * FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for * more details. * * You should have received a copy of the GNU General Public License along with * GNU Smalltalk; see the file COPYING. If not, write to the Free Software * Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * ***********************************************************************/ #include "config.h" #include "gstpub.h" #include #include #include #include #include #include #include #include #include #include #ifdef G_WIN32_MSG_HANDLE #include #else #include "poll.h" #endif #ifdef STDC_HEADERS #include #include #endif #include "placer.h" typedef struct SmalltalkClosure { GClosure closure; OOP receiver; OOP selector; OOP data; OOP widget; int n_params; } SmalltalkClosure; static VMProxy *_gst_vm_proxy; static GQuark q_gst_object = 0; static GTypeInfo gtype_oop_info = { 0, /* class_size */ NULL, /* base_init */ NULL, /* base_finalize */ NULL, /* class_init */ NULL, /* class_finalize */ NULL, /* class_data */ 0, /* instance_size */ 0, /* n_preallocs */ NULL, /* instance_init */ NULL, /* value_table */ }; static void g_type_oop_value_init (GValue *value) { value->data[0].v_pointer = NULL; } static void g_type_oop_value_free (GValue *value) { if (value->data[0].v_pointer) _gst_vm_proxy->unregisterOOP ((OOP) value->data[0].v_pointer); } static void g_type_oop_value_copy (const GValue *src_value, GValue *dest_value) { _gst_vm_proxy->registerOOP ((OOP) src_value->data[0].v_pointer); dest_value->data[0].v_pointer = src_value->data[0].v_pointer; } static const GTypeValueTable gtype_oop_value_table = { g_type_oop_value_init, /* value_init */ g_type_oop_value_free, /* value_free */ g_type_oop_value_copy, /* value_copy */ NULL, /* value_peek_pointer */ NULL, /* collect_format */ NULL, /* collect_value */ NULL, /* lcopy_format */ NULL, /* lcopy_value */ }; static GType G_TYPE_OOP; /* Start the main event loop and then signal OOP. */ static GMainLoop *create_main_loop_thread (OOP semaphore); /* Unref OBJ and detach it from the Smalltalk object that has represented it so far. */ static void free_oop_for_g_object (GObject *obj); /* If no Smalltalk object has represented OBJ so far, change OOP's class to be the correct one, ref the object, mark it as finalizable, and answer OOP; otherwise answer the pre-existing object. */ static OOP narrow_oop_for_g_object (GObject *obj, OOP oop); /* Answer a Smalltalk object that can represent OBJ. This is the same as narrow_oop_for_g_object, but creates a new OOP if no Smalltalk object has represented OBJ so far. */ static OOP get_oop_for_g_object (GObject *obj); /* Answer a Smalltalk object that can represent the boxed value OBJ. This needs to know the TYPE of the value because GBoxed values don't know their type. */ static OOP get_oop_for_g_boxed (gpointer obj, GType type); /* Store in a quark that OBJ is represented by the Smalltalk object OOP. */ static void associate_oop_to_g_object (GObject *obj, OOP oop); /* Convert the GValue, VAL, to a Smalltalk object. */ static OOP convert_g_value_to_oop (const GValue *val); /* Store the value represented by OOP into the GValue, VAL. */ static void fill_g_value_from_oop (GValue *val, OOP oop); /* Create a GClosure that invokes the selector, SELECTOR, on the given object. DATA is inserted as the second parameter (or is passed as the only one is the closure's arity is 0). */ static GClosure *create_smalltalk_closure (OOP receiver, OOP selector, OOP data, OOP widget, int n_params); /* The finalization notifier for Smalltalk GClosures. Unregisters the receiver and user data for the CLOSURE. */ static void finalize_smalltalk_closure (gpointer data, GClosure *closure); /* The marshalling routine for Smalltalk GClosures. */ static void invoke_smalltalk_closure (GClosure *closure, GValue *return_value, guint n_param_values, const GValue *param_values, gpointer invocation_hint, gpointer marshal_data); /* A wrapper around g_signal_connect_closure that looks up the selector and creates a Smalltalk GClosure. */ static int connect_signal (OOP widget, char *signal_name, OOP receiver, OOP selector, OOP user_data); /* A wrapper around g_signal_connect_closure that looks up the selector and creates a Smalltalk GClosure. */ static int connect_signal_no_user_data (OOP widget, char *signal_name, OOP receiver, OOP selector); /* A wrapper around g_object_get_property that replaces GValues with OOPs. */ static OOP object_get_property (GObject *anObject, const char *aProperty); /* A wrapper around g_object_set_property that replaces GValues with OOPs. */ static void object_set_property (GObject *anObject, const char *aProperty, OOP aValue); /* A wrapper around gtk_container_child_get_property that replaces GValues with OOPs. */ static OOP container_get_child_property (GtkContainer *aParent, GtkWidget *anObject, const char *aProperty); /* A wrapper around gtk_container_child_set_property that replaces GValues with OOPs. */ static void container_set_child_property (GtkContainer *aParent, GtkWidget *anObject, const char *aProperty, OOP aValue); /* GObject wrapper. */ void register_for_type (OOP oop, GType type) { _gst_vm_proxy->registerOOP (oop); g_type_set_qdata (type, q_gst_object, oop); } void free_oop_for_g_object (GObject *obj) { g_object_set_qdata (obj, q_gst_object, NULL); g_object_unref (obj); } void associate_oop_to_g_object (GObject *obj, OOP oop) { OOP class = g_type_get_qdata (G_OBJECT_TYPE (obj), q_gst_object); if (class) OOP_TO_OBJ (oop)->objClass = class; g_object_set_qdata (obj, q_gst_object, oop); g_object_ref (obj); _gst_vm_proxy->strMsgSend (oop, "addToBeFinalized", NULL); } OOP narrow_oop_for_g_object (GObject *obj, OOP oop) { OOP preexistingOOP; if (!(preexistingOOP = g_object_get_qdata (obj, q_gst_object))) { associate_oop_to_g_object (obj, oop); return oop; } else return preexistingOOP; } OOP get_oop_for_g_boxed (gpointer obj, GType type) { OOP oop = _gst_vm_proxy->cObjectToOOP(obj); OOP class = g_type_get_qdata (type, q_gst_object); if (class) OOP_TO_OBJ (oop)->objClass = class; return oop; } OOP get_oop_for_g_object (GObject *obj) { OOP oop; if (!(oop = g_object_get_qdata (obj, q_gst_object))) { /* We don't have a wrapper for it, so create it. Get the class from the object's type. */ oop = _gst_vm_proxy->cObjectToOOP(obj); associate_oop_to_g_object (obj, oop); } return oop; } /* SmalltalkClosure implementation. */ OOP convert_g_value_to_oop (const GValue *val) { GType type = G_VALUE_TYPE (val); GType fundamental; char v_char; gboolean v_boolean; gpointer v_ptr; long v_int; double v_float; if (G_TYPE_IS_FUNDAMENTAL (type)) fundamental = type; else fundamental = G_TYPE_FUNDAMENTAL (type); if (type == G_TYPE_OOP) { v_ptr = g_value_get_boxed (val); return (OOP) v_ptr; } switch (fundamental) { case G_TYPE_CHAR: v_char = g_value_get_char (val); return _gst_vm_proxy->charToOOP(v_char); case G_TYPE_BOOLEAN: v_boolean = g_value_get_boolean (val); return _gst_vm_proxy->boolToOOP(v_boolean); case G_TYPE_UCHAR: v_int = g_value_get_uchar (val); return _gst_vm_proxy->intToOOP(v_int); case G_TYPE_INT: v_int = g_value_get_int (val); return _gst_vm_proxy->intToOOP(v_int); case G_TYPE_UINT: v_int = g_value_get_uint (val); return _gst_vm_proxy->intToOOP(v_int); case G_TYPE_LONG: v_int = g_value_get_long (val); return _gst_vm_proxy->intToOOP(v_int); case G_TYPE_ULONG: v_int = g_value_get_ulong (val); return _gst_vm_proxy->intToOOP(v_int); case G_TYPE_ENUM: v_int = g_value_get_enum (val); return _gst_vm_proxy->intToOOP(v_int); case G_TYPE_FLAGS: v_int = g_value_get_flags (val); return _gst_vm_proxy->intToOOP(v_int); case G_TYPE_FLOAT: v_float = g_value_get_float (val); return _gst_vm_proxy->floatToOOP(v_float); case G_TYPE_DOUBLE: v_float = g_value_get_double (val); return _gst_vm_proxy->floatToOOP(v_float); case G_TYPE_STRING: v_ptr = (gpointer) g_value_get_string (val); return _gst_vm_proxy->stringToOOP(v_ptr); case G_TYPE_POINTER: v_ptr = g_value_get_pointer (val); return _gst_vm_proxy->cObjectToOOP(v_ptr); case G_TYPE_BOXED: v_ptr = g_value_get_boxed (val); return get_oop_for_g_boxed (v_ptr, type); case G_TYPE_OBJECT: case G_TYPE_INTERFACE: v_ptr = g_value_get_object (val); if (fundamental == type || G_TYPE_CHECK_INSTANCE_TYPE (v_ptr, type)) return get_oop_for_g_object (v_ptr); default: return NULL; } } void fill_g_value_from_oop (GValue *return_value, OOP oop) { GType type = G_VALUE_TYPE (return_value); GType fundamental; char v_char; gboolean v_boolean; gpointer v_ptr; long v_int; double v_float; if (G_TYPE_IS_FUNDAMENTAL (type)) fundamental = type; else fundamental = G_TYPE_FUNDAMENTAL (type); if (type == G_TYPE_OOP) { _gst_vm_proxy->registerOOP (oop); g_value_set_boxed (return_value, (gpointer)oop); return ; } switch (fundamental) { case G_TYPE_NONE: case G_TYPE_INVALID: break; case G_TYPE_CHAR: v_char = _gst_vm_proxy->OOPToChar (oop); g_value_set_char (return_value, v_char); break; case G_TYPE_BOOLEAN: v_boolean = _gst_vm_proxy->OOPToBool (oop); g_value_set_boolean (return_value, v_boolean); break; case G_TYPE_UCHAR: v_int = _gst_vm_proxy->OOPToInt (oop); g_value_set_uchar (return_value, v_int); break; case G_TYPE_INT: v_int = _gst_vm_proxy->OOPToInt (oop); g_value_set_int (return_value, v_int); break; case G_TYPE_UINT: v_int = _gst_vm_proxy->OOPToInt (oop); g_value_set_uint (return_value, v_int); break; case G_TYPE_LONG: v_int = _gst_vm_proxy->OOPToInt (oop); g_value_set_long (return_value, v_int); break; case G_TYPE_ULONG: v_int = _gst_vm_proxy->OOPToInt (oop); g_value_set_ulong (return_value, v_int); break; case G_TYPE_ENUM: v_int = _gst_vm_proxy->OOPToInt (oop); g_value_set_enum (return_value, v_int); break; case G_TYPE_FLAGS: v_int = _gst_vm_proxy->OOPToInt (oop); g_value_set_flags (return_value, v_int); break; case G_TYPE_FLOAT: v_float = _gst_vm_proxy->OOPToFloat (oop); g_value_set_float (return_value, v_float); break; case G_TYPE_DOUBLE: v_float = _gst_vm_proxy->OOPToFloat (oop); g_value_set_double (return_value, v_float); break; case G_TYPE_STRING: v_ptr = _gst_vm_proxy->OOPToString (oop); g_value_set_string_take_ownership (return_value, v_ptr); break; case G_TYPE_POINTER: v_ptr = _gst_vm_proxy->OOPToCObject (oop); g_value_set_pointer (return_value, v_ptr); break; case G_TYPE_BOXED: v_ptr = _gst_vm_proxy->OOPToCObject (oop); g_value_set_boxed (return_value, v_ptr); break; case G_TYPE_OBJECT: case G_TYPE_INTERFACE: v_ptr = _gst_vm_proxy->OOPToCObject (oop); g_value_set_object (return_value, v_ptr); break; default: fprintf (stderr, "Invalid type."); abort (); } } GClosure * create_smalltalk_closure (OOP receiver, OOP selector, OOP data, OOP widget, int n_params) { GClosure *closure = g_closure_new_simple (sizeof (SmalltalkClosure), NULL); SmalltalkClosure *stc = (SmalltalkClosure *) closure; _gst_vm_proxy->registerOOP (receiver); _gst_vm_proxy->registerOOP (widget); if (data) _gst_vm_proxy->registerOOP (data); stc->receiver = receiver; stc->selector = selector; stc->data = data; stc->widget = widget; stc->n_params = n_params; g_closure_set_marshal (closure, invoke_smalltalk_closure); g_closure_add_finalize_notifier (closure, NULL, finalize_smalltalk_closure); return closure; } void finalize_smalltalk_closure (gpointer data, GClosure *closure) { SmalltalkClosure *stc = (SmalltalkClosure *) closure; _gst_vm_proxy->unregisterOOP (stc->receiver); _gst_vm_proxy->unregisterOOP (stc->widget); if (stc->data) _gst_vm_proxy->unregisterOOP (stc->data); } void invoke_smalltalk_closure (GClosure *closure, GValue *return_value, guint n_param_values, const GValue *param_values, gpointer invocation_hint, gpointer marshal_data) { SmalltalkClosure *stc = (SmalltalkClosure *) closure; OOP *args = alloca (sizeof (OOP) * stc->n_params); OOP resultOOP; int i; /* Less parameters than the event has, discard the ones in excess. */ if (stc->n_params < n_param_values) n_param_values = stc->n_params; /* Maintain the Gtk order of parameters, even if we end up discarding the sender (first parameter, usually) most of the time */ for (i = 0; i < n_param_values; i++) { OOP oop = convert_g_value_to_oop (¶m_values[i]); if (!oop) { fprintf (stderr, "Invalid type, signal discarded.\n"); if (return_value->g_type == G_TYPE_NONE) return; else abort (); } args[i] = oop; } if (stc->data) { if (stc->n_params > n_param_values + 1) args[i++] = stc->widget; if (stc->n_params > n_param_values) args[i++] = stc->data; } else { if (stc->n_params > n_param_values) args[i++] = stc->widget; } resultOOP = _gst_vm_proxy->nvmsgSend (stc->receiver, stc->selector, args, i); /* FIXME Need to init return_value's type? */ if (return_value) fill_g_value_from_oop (return_value, resultOOP); } /* Signal implementation. */ int connect_signal_smalltalk (OOP widget, char *signal_name, OOP receiver, OOP selector, OOP user_data, gboolean after) { GtkWidget *cWidget = _gst_vm_proxy->OOPToCObject (widget); GClosure *closure; GSignalQuery qry; guint sig_id; int n_params; OOP oop_sel_args; /* Check parameters */ if (!G_IS_OBJECT(cWidget)) return (-1); /* Invalid widget passed */ sig_id = g_signal_lookup (signal_name, G_OBJECT_TYPE(G_OBJECT(cWidget))); if (sig_id == 0) return (-2); /* Invalid signal name */ g_signal_query (sig_id, &qry); oop_sel_args = _gst_vm_proxy->strMsgSend (selector, "numArgs", NULL); if (oop_sel_args == _gst_vm_proxy->nilOOP) return (-3); /* Invalid selector */ /* Check the number of arguments in the selector against the number of arguments in the signal callback */ /* We can pass fewer arguments than are in the signal, if the others aren't wanted, but we can't pass more (passing nilOOPs instead is not 100% satisfactory), so fail. */ n_params = _gst_vm_proxy->OOPToInt (oop_sel_args); if (n_params > qry.n_params + 2) return (-4); /* Receiver is assumed to be OK, no matter what it is */ /* Parameters OK, so carry on and connect the signal */ widget = narrow_oop_for_g_object (G_OBJECT (cWidget), widget); closure = create_smalltalk_closure (receiver, selector, user_data, widget, n_params); return g_signal_connect_closure (cWidget, signal_name, closure, after); } int connect_signal (OOP widget, char *signal_name, OOP receiver, OOP selector, OOP user_data) { return connect_signal_smalltalk (widget, signal_name, receiver, selector, user_data, FALSE); } int connect_signal_no_user_data (OOP widget, char *signal_name, OOP receiver, OOP selector) { return connect_signal (widget, signal_name, receiver, selector, NULL); } int connect_signal_after (OOP widget, char *signal_name, OOP receiver, OOP selector, OOP user_data) { return connect_signal_smalltalk (widget, signal_name, receiver, selector, user_data, TRUE); } int connect_signal_after_no_user_data (OOP widget, char *signal_name, OOP receiver, OOP selector) { return connect_signal_after (widget, signal_name, receiver, selector, NULL); } static int connect_accel_group (OOP accel_group, guint accel_key, GdkModifierType accel_mods, GtkAccelFlags accel_flags, OOP receiver, OOP selector, OOP user_data) { GtkAccelGroup *cObject = _gst_vm_proxy->OOPToCObject (accel_group); int n_params; GClosure *closure; OOP oop_sel_args; oop_sel_args = _gst_vm_proxy->strMsgSend (selector, "numArgs", NULL); if (oop_sel_args == _gst_vm_proxy->nilOOP) return (-3); /* Invalid selector */ /* Check the number of arguments in the selector against the number of arguments in the event callback */ /* We can return fewer arguments than are in the event, if the others aren't wanted, but we can't return more, and returning nilOOPs instead is not 100% satisfactory, so fail. */ n_params = _gst_vm_proxy->OOPToInt (oop_sel_args); if (n_params > 4) return (-4); /* Receiver is assumed to be OK, no matter what it is */ /* Parameters OK, so carry on and connect the signal */ accel_group = narrow_oop_for_g_object (G_OBJECT (cObject), accel_group); closure = create_smalltalk_closure (receiver, selector, NULL, accel_group, n_params); gtk_accel_group_connect (cObject, accel_key, accel_mods, accel_flags, closure); return 0; } static int connect_accel_group_no_user_data (OOP accel_group, guint accel_key, GdkModifierType accel_mods, GtkAccelFlags accel_flags, OOP receiver, OOP selector) { return connect_accel_group (accel_group, accel_key, accel_mods, accel_flags, receiver, selector, NULL); } /* Event loop. The GTK+ event loop in GNU Smalltalk is split between two operating system threads using the low-level g_main_context functions (http://library.gnome.org/devel/glib/unstable/glib-The-Main-Event-Loop.html). Everything except dispatching occurs in a separate thread than the one executing Smalltalk code. After check(), however, the thread releases the context and waits on a condition variable for the Smalltalk code to finish the dispatch phase. This ensures that all GTK+ code executes in a single OS thread (avoiding complicated usage of gdk_threads_{enter,leave}) and at the same time allows Smalltalk processes to run in the background while GTK+ events are polled. */ static GMainLoop *loop; static GThread *thread; static GMutex *mutex; static GCond *cond; static GCond *cond_dispatch; static volatile gboolean queued; #ifdef G_WIN32_MSG_HANDLE static gint gst_gtk_poll (GPollFD *fds, guint nfds, gint timeout) { HANDLE handles[MAXIMUM_WAIT_OBJECTS]; gint win32_timeout; gint poll_msgs = -1; GPollFD *f; DWORD ready; gint nhandles = 0; for (f = fds; f < &fds[nfds]; ++f) { HANDLE h; assert (f->fd >= 0); if (f->fd == G_WIN32_MSG_HANDLE) { assert (poll_msgs == -1 && nhandles == f - fds); poll_msgs = nhandles; #if 1 continue; #else /* Once the VM will host the event loop, it will be possible to have a MsgWaitForMultipleObjects call in the VM thread and use the result to wake up this side of the loop. For now resort to polling; messages are checked by the VM thread every 20ms (in the GTK check function, called by g_main_context_check). */ h = hWokenUpEvent; #endif } else h = (HANDLE) f->fd; if (nhandles == MAXIMUM_WAIT_OBJECTS) { g_warning (G_STRLOC ": Too many handles to wait for!\n"); break; } handles[nhandles++] = (HANDLE) f->fd; } if (nhandles == 0) { /* Wait for nothing (huh?) */ return 0; } /* If the VM were idling, it could in principle use MsgWaitForMultipleObjects and tell us when it gets a message on its queue. This would remove the need for polling. However, we cannot implement this until the main loop is moved inside the VM. */ if (poll_msgs != -1 /* && !idle */ ) win32_timeout = (timeout == -1 || timeout > 20) ? 20 : timeout; else win32_timeout = (timeout == -1) ? INFINITE : timeout; ready = WaitForMultipleObjects (nhandles, handles, FALSE, win32_timeout); if (ready == WAIT_FAILED) { gchar *emsg = g_win32_error_message (GetLastError ()); g_warning (G_STRLOC ": WaitForMultipleObjects() failed: %s", emsg); g_free (emsg); } for (f = fds; f < &fds[nfds]; ++f) f->revents = 0; #if 1 if (poll_msgs != -1) { if (ready >= WAIT_OBJECT_0 + poll_msgs && ready <= WAIT_OBJECT_0 + nhandles) ready++; else if (ready == WAIT_TIMEOUT && win32_timeout != INFINITE) ready = WAIT_OBJECT_0 + poll_msgs; } #endif if (ready == WAIT_FAILED) return -1; if (ready == WAIT_TIMEOUT) return 0; f = &fds[ready - WAIT_OBJECT_0]; if (f->events & (G_IO_IN | G_IO_OUT)) { if (f->events & G_IO_IN) f->revents |= G_IO_IN; else f->revents |= G_IO_OUT; } return 1; } #if 0 /* libgst should have something like this: */ static gint _gst_pause () { idle = true; ResetEvent (hWakeUpEvent); MsgWaitForMultipleObjects (1, &hWakeUpEvent, FALSE, INFINITE, QS_ALLEVENTS); SetEvent (hWokenUpEvent); } static gint _gst_wakeup () { idle = false; SetEvent (hWakeUpEvent); } #endif #else #define gst_gtk_poll g_poll #endif static void main_context_acquire_wait (GMainContext *context) { while (!g_main_context_wait (context, cond, mutex)); } static void main_context_signal (GMainContext *context) { /* Restart the polling thread. Note that #iterate is asynchronous, so this might execute before the Smalltalk code finishes running! This allows debugging GTK+ signal handlers. */ g_mutex_lock (mutex); queued = false; g_cond_broadcast (cond_dispatch); g_mutex_unlock (mutex); } static GPollFD *fds; static int allocated_nfds, nfds; static int maxprio; static void main_context_iterate (GMainContext *context) { g_mutex_lock (mutex); if (!fds) { g_mutex_unlock (mutex); return; } /* No need to keep the mutex except during g_main_context_acquire_wait and g_main_context_release_signal, i.e. except while we operate on cond. */ main_context_acquire_wait (context); g_mutex_unlock (mutex); g_main_context_check (context, maxprio, fds, nfds); g_main_context_dispatch (context); g_main_context_release (context); main_context_signal (context); } static gpointer main_loop_thread (gpointer semaphore) { OOP semaphoreOOP = semaphore; GMainContext *context = g_main_loop_get_context (loop); if (!fds) { fds = g_new (GPollFD, 20); allocated_nfds = 20; } /* Mostly based on g_main_context_iterate (a static function in gmain.c) except that we have to use our own mutex and that g_main_context_dispatch is replaced by signaling semaphoreOOP. */ g_mutex_lock (mutex); while (g_main_loop_is_running (loop)) { int timeout; main_context_acquire_wait (context); g_main_context_prepare (context, &maxprio); while ((nfds = g_main_context_query (context, maxprio, &timeout, fds, allocated_nfds)) > allocated_nfds) { g_free (fds); fds = g_new (GPollFD, nfds); allocated_nfds = nfds; } /* Release the context so that the other thread can dispatch while this one polls. g_main_context_release unlocks the mutex for us. */ g_mutex_unlock (mutex); g_main_context_release (context); gst_gtk_poll (fds, nfds, timeout); /* Dispatch on the other thread and wait for it to rendez-vous. */ g_mutex_lock (mutex); queued = true; _gst_vm_proxy->asyncSignal (semaphoreOOP); /* TODO: shouldn't be necessary. */ _gst_vm_proxy->wakeUp (); while (queued) g_cond_wait (cond_dispatch, mutex); } g_main_loop_unref (loop); loop = NULL; thread = NULL; g_mutex_unlock (mutex); /* TODO: Not thread-safe! */ _gst_vm_proxy->unregisterOOP (semaphoreOOP); return NULL; } GMainLoop * create_main_loop_thread (OOP semaphore) { if (!mutex) { /* One-time initialization. */ mutex = g_mutex_new (); cond = g_cond_new (); cond_dispatch = g_cond_new (); } g_mutex_lock (mutex); if (loop) { /* A loop exists. If it is exiting, wait for it, otherwise leave immediately. */ GThread *loop_thread = thread; gboolean exiting = g_main_loop_is_running (loop); g_mutex_unlock (mutex); if (!exiting) return NULL; if (loop_thread) g_thread_join (loop_thread); } else g_mutex_unlock (mutex); _gst_vm_proxy->registerOOP (semaphore); loop = g_main_loop_new (NULL, TRUE); /* Add a second reference to be released when the thread exits. The first one is passed to Smalltalk ("return loop" below). */ g_main_loop_ref (loop); thread = g_thread_create (main_loop_thread, semaphore, TRUE, NULL); if (!thread) { /* Destroy both references, since the thread won't have any occasion to release his. */ g_main_loop_unref (loop); g_main_loop_unref (loop); return NULL; } return loop; } /* Wrappers for GValue users. */ OOP object_get_property (GObject *anObject, const char *aProperty) { GParamSpec *spec; GValue result = {0,}; GObject *obj; obj = G_OBJECT (anObject); spec = g_object_class_find_property (G_OBJECT_GET_CLASS(obj), aProperty); g_value_init (&result, spec->value_type); g_object_get_property (obj, aProperty, &result); return (convert_g_value_to_oop (&result)); } void object_set_property (GObject *anObject, const char *aProperty, OOP aValue) { GParamSpec *spec; GObject *obj; GValue value = {0,}; obj = G_OBJECT (anObject); spec = g_object_class_find_property (G_OBJECT_GET_CLASS(obj), aProperty); g_value_init (&value, spec->value_type); fill_g_value_from_oop (&value, aValue); g_object_set_property (obj, aProperty, &value); } OOP container_get_child_property (GtkContainer *aParent, GtkWidget *aChild, const char *aProperty) { GParamSpec *spec; GValue result = {0,}; g_return_val_if_fail (GTK_WIDGET (aParent) == gtk_widget_get_parent (GTK_WIDGET (aChild)), _gst_vm_proxy->nilOOP); spec = gtk_container_class_find_child_property (G_OBJECT_GET_CLASS (aParent), aProperty); g_value_init (&result, spec->value_type); gtk_container_child_get_property (aParent, aChild, aProperty, &result); return (convert_g_value_to_oop (&result)); } void container_set_child_property (GtkContainer *aParent, GtkWidget *aChild, const char *aProperty, OOP aValue) { GParamSpec *spec; GValue value = {0,}; g_return_if_fail (GTK_WIDGET (aParent) == gtk_widget_get_parent (GTK_WIDGET (aChild))); spec = gtk_container_class_find_child_property (G_OBJECT_GET_CLASS (aParent), aProperty); g_value_init (&value, spec->value_type); fill_g_value_from_oop (&value, aValue); gtk_container_child_set_property (aParent, aChild, aProperty, &value); } OOP tree_model_get_oop (GtkTreeModel *model, GtkTreeIter *iter, int col) { GValue gval = { 0 }; OOP result; gtk_tree_model_get_value (model, iter, col, &gval); result = convert_g_value_to_oop (&gval); g_value_unset (&gval); return (result); } void list_store_set_oop (GtkListStore *store, GtkTreeIter *iter, int col, OOP value) { GValue gval = { 0 }; g_value_init (&gval, gtk_tree_model_get_column_type (GTK_TREE_MODEL(store), col)); fill_g_value_from_oop (&gval, value); gtk_list_store_set_value (store, iter, col, &gval); g_value_unset (&gval); } void tree_store_set_oop (GtkTreeStore *store, GtkTreeIter *iter, int col, OOP value) { GValue gval = { 0 }; g_value_init (&gval, gtk_tree_model_get_column_type (GTK_TREE_MODEL(store), col)); fill_g_value_from_oop (&gval, value); gtk_tree_store_set_value (store, iter, col, &gval); g_value_unset (&gval); } /* Wrappers for macros and missing accessor functions. */ static GdkWindow * widget_get_window (GtkWidget *widget) { return widget->window; } static int widget_get_state (GtkWidget *widget) { return GTK_WIDGET_STATE (widget); } static int widget_get_flags (GtkWidget *widget) { return GTK_WIDGET_FLAGS (widget); } static void widget_set_flags (GtkWidget *widget, int flags) { GTK_WIDGET_SET_FLAGS (widget, flags); } static void widget_unset_flags (GtkWidget *widget, int flags) { GTK_WIDGET_UNSET_FLAGS (widget, flags); } static GtkAllocation * widget_get_allocation (GtkWidget *wgt) { return &(GTK_WIDGET(wgt)->allocation); } static GtkWidget * dialog_get_vbox (GtkDialog *dlg) { return (GTK_DIALOG(dlg)->vbox); } static GtkWidget * dialog_get_action_area (GtkDialog *dlg) { return (GTK_DIALOG(dlg)->action_area); } static int scrolled_window_get_hscrollbar_visible (GtkScrolledWindow *swnd) { return (GTK_SCROLLED_WINDOW(swnd)->hscrollbar_visible); } static int scrolled_window_get_vscrollbar_visible (GtkScrolledWindow *swnd) { return (GTK_SCROLLED_WINDOW(swnd)->vscrollbar_visible); } static int adjustment_get_lower (GtkAdjustment *adj) { return (GTK_ADJUSTMENT(adj)->lower); } static int adjustment_get_upper (GtkAdjustment *adj) { return (GTK_ADJUSTMENT(adj)->upper); } static int adjustment_get_page_size (GtkAdjustment *adj) { return (GTK_ADJUSTMENT(adj)->page_size); } void my_log_handler (const gchar * log_domain, GLogLevelFlags log_level, const gchar * message, gpointer unused_data) { /* Do not pass fatal flags so that we can show the backtrace. */ g_log_default_handler (log_domain, log_level & G_LOG_LEVEL_MASK, message, unused_data); switch ((log_level & G_LOG_FATAL_MASK) ? G_LOG_LEVEL_ERROR : log_level) { case G_LOG_LEVEL_ERROR: case G_LOG_LEVEL_CRITICAL: case G_LOG_LEVEL_WARNING: case G_LOG_LEVEL_MESSAGE: _gst_vm_proxy->showBacktrace (stderr); break; default: _gst_vm_proxy->showBacktrace (stdout); break; } if (log_level & G_LOG_FATAL_MASK) abort (); } int gst_type_oop () { return G_TYPE_OOP; } /* Initialization. */ static int initialized = 0; int gst_gtk_initialized () { return initialized; } void gst_initModule (proxy) VMProxy *proxy; { int argc = 1; gchar *argvArray[] = { (char *) "gst", NULL }; gchar **argv = argvArray; initialized = gtk_init_check (&argc, &argv); if (initialized && !g_thread_supported ()) { g_thread_init (NULL); gdk_threads_init (); } q_gst_object = g_quark_from_string ("gst_object"); g_type_init (); g_log_set_handler (NULL, G_LOG_LEVEL_WARNING | G_LOG_LEVEL_CRITICAL | G_LOG_LEVEL_ERROR | G_LOG_FLAG_FATAL | G_LOG_FLAG_RECURSION, my_log_handler, NULL); g_log_set_handler ("Gtk", G_LOG_LEVEL_WARNING | G_LOG_LEVEL_CRITICAL | G_LOG_LEVEL_ERROR | G_LOG_FLAG_FATAL | G_LOG_FLAG_RECURSION, my_log_handler, NULL); g_log_set_handler ("GLib", G_LOG_LEVEL_WARNING | G_LOG_LEVEL_CRITICAL | G_LOG_LEVEL_ERROR | G_LOG_FLAG_FATAL | G_LOG_FLAG_RECURSION, my_log_handler, NULL); g_log_set_handler ("GLib-GObject", G_LOG_LEVEL_WARNING | G_LOG_LEVEL_CRITICAL | G_LOG_LEVEL_ERROR | G_LOG_FLAG_FATAL | G_LOG_FLAG_RECURSION, my_log_handler, NULL); gtype_oop_info.value_table = >ype_oop_value_table; G_TYPE_OOP = g_type_register_static (G_TYPE_BOXED, "OOP", >ype_oop_info, 0); _gst_vm_proxy = proxy; _gst_vm_proxy->defineCFunc ("gtkInitialized", gst_gtk_initialized); _gst_vm_proxy->defineCFunc ("gstTypeOOP", gst_type_oop); _gst_vm_proxy->defineCFunc ("gstGtkRegisterForType", register_for_type); _gst_vm_proxy->defineCFunc ("gstGtkFreeGObjectOOP", free_oop_for_g_object); _gst_vm_proxy->defineCFunc ("gstGtkNarrowGObjectOOP", narrow_oop_for_g_object); _gst_vm_proxy->defineCFunc ("gstGtkConnectAccelGroup", connect_accel_group); _gst_vm_proxy->defineCFunc ("gstGtkConnectAccelGroupNoUserData", connect_accel_group_no_user_data); _gst_vm_proxy->defineCFunc ("gstGtkConnectSignal", connect_signal); _gst_vm_proxy->defineCFunc ("gstGtkConnectSignalNoUserData", connect_signal_no_user_data); _gst_vm_proxy->defineCFunc ("gstGtkConnectSignalAfter", connect_signal_after); _gst_vm_proxy->defineCFunc ("gstGtkConnectSignalAfterNoUserData", connect_signal_after_no_user_data); _gst_vm_proxy->defineCFunc ("gstGtkMain", create_main_loop_thread); _gst_vm_proxy->defineCFunc ("gstGtkMainContextIterate", main_context_iterate); _gst_vm_proxy->defineCFunc ("gstGtkGetProperty", object_get_property); _gst_vm_proxy->defineCFunc ("gstGtkSetProperty", object_set_property); _gst_vm_proxy->defineCFunc ("gstGtkGetChildProperty", container_get_child_property); _gst_vm_proxy->defineCFunc ("gstGtkSetChildProperty", container_set_child_property); _gst_vm_proxy->defineCFunc ("gstGtkGetState", widget_get_state); _gst_vm_proxy->defineCFunc ("gstGtkGetFlags", widget_get_flags); _gst_vm_proxy->defineCFunc ("gstGtkSetFlags", widget_set_flags); _gst_vm_proxy->defineCFunc ("gstGtkUnsetFlags", widget_unset_flags); _gst_vm_proxy->defineCFunc ("gstGtkGetWindow", widget_get_window); _gst_vm_proxy->defineCFunc ("gstGtkGetHscrollbarVisible", scrolled_window_get_hscrollbar_visible); _gst_vm_proxy->defineCFunc ("gstGtkGetVscrollbarVisible", scrolled_window_get_vscrollbar_visible); _gst_vm_proxy->defineCFunc ("gstGtkAdjustmentGetLower", adjustment_get_lower); _gst_vm_proxy->defineCFunc ("gstGtkAdjustmentGetUpper", adjustment_get_upper); _gst_vm_proxy->defineCFunc ("gstGtkAdjustmentGetPageSize", adjustment_get_page_size); _gst_vm_proxy->defineCFunc ("gstGtkTreeModelGetOOP", tree_model_get_oop); _gst_vm_proxy->defineCFunc ("gstGtkListStoreSetOOP", list_store_set_oop); _gst_vm_proxy->defineCFunc ("gstGtkTreeStoreSetOOP", tree_store_set_oop); _gst_vm_proxy->defineCFunc ("gstGtkWidgetGetAllocation", widget_get_allocation); _gst_vm_proxy->defineCFunc ("gstGtkDialogGetVBox", dialog_get_vbox); _gst_vm_proxy->defineCFunc ("gstGtkDialogGetActionArea", dialog_get_action_area); _gst_vm_proxy->defineCFunc ("gtk_placer_get_type", gtk_placer_get_type); _gst_vm_proxy->defineCFunc ("gtk_placer_new", gtk_placer_new); _gst_vm_proxy->defineCFunc ("gtk_placer_put", gtk_placer_put); _gst_vm_proxy->defineCFunc ("gtk_placer_move", gtk_placer_move); _gst_vm_proxy->defineCFunc ("gtk_placer_resize", gtk_placer_resize); _gst_vm_proxy->defineCFunc ("gtk_placer_move_rel", gtk_placer_move_rel); _gst_vm_proxy->defineCFunc ("gtk_placer_resize_rel", gtk_placer_resize_rel); _gst_vm_proxy->defineCFunc ("gtk_placer_set_has_window", gtk_placer_set_has_window); _gst_vm_proxy->defineCFunc ("gtk_placer_get_has_window", gtk_placer_get_has_window); _gst_vm_proxy->dlPushSearchPath (); #include "libs.def" _gst_vm_proxy->dlPopSearchPath (); } smalltalk-3.2.5/packages/gtk/mk_enums.awk0000644000175000017500000002007612123404352015314 00000000000000#! @AWK@ -f ####################################################################### # # Gtk wrapper creation script (enumerations) # ######################################################################## ####################################################################### # # Copyright 2001, 2003 Free Software Foundation, Inc. # Written by Paolo Bonzini and Dragomir Milivojevic # # This file is part of the GNU Smalltalk class library. # # The GNU Smalltalk class library is free software; you can redistribute it # and/or modify it under the terms of the GNU Lesser General Public License # as published by the Free Software Foundation; either version 2.1, or (at # your option) any later version. # # The GNU Smalltalk class library is distributed in the hope that it will be # useful, but WITHOUT ANY WARRANTY; without even the implied warranty of # MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser # General Public License for more details. # # You should have received a copy of the GNU Lesser General Public License # along with the GNU Smalltalk class library; see the file COPYING.LESSER. # If not, write to the Free Software Foundation, 59 Temple Place - Suite # 330, Boston, MA 02110-1301, USA. # ######################################################################## BEGIN { print "/* Automatically generated, do not edit! */" print "#define GDK_PIXBUF_ENABLE_BACKEND 1" print "#include " print "#include " print "#include " print "#include " print "#include " print "#include " print "#include " print "#include " } FNR == 1 { enum_class = get_enum_class(FILENAME) } # store declaration in decl[filename] /^(typedef )?enum/ { last_was_string = 0 split("", declaration) do getline while (/^{/) while (! /^}/) { sub(/[,=].*/, "") if ($1 ~ /^[A-Z_][A-Z_0-9]*$/) declaration[$1] = "" getline } # On the last line, read the enum's name -------------- if (NF != 2) enum_category = "enumerations" else { enum_category = $2 sub(/;$/, "", enum_category) enum_class = get_enum_class(enum_category) } # And finally emit the code --------------------------- for (each in declaration) { decl[n++] = print_numeric_enum(each) } print_end_of_category() enums[m++] = enum_class " " enum_category " " n } END { print "int" print "main() {" print " printf (\"\\\"Automatically generated, do not edit!\\\"\\n\");" n = 0 for (i = 0; i < m; i++) { $0 = enums[i] print print_methodsFor($1, $2) while(n < $3) print decl[n++] print print_end_of_category() } print print_methodsFor("GValue", "fundamental types") print print_numeric_enum("G_TYPE_INVALID") print print_numeric_enum("G_TYPE_NONE") print print_numeric_enum("G_TYPE_INTERFACE") print print_numeric_enum("G_TYPE_CHAR") print print_numeric_enum("G_TYPE_UCHAR") print print_numeric_enum("G_TYPE_BOOLEAN") print print_numeric_enum("G_TYPE_INT") print print_numeric_enum("G_TYPE_UINT") print print_numeric_enum("G_TYPE_LONG") print print_numeric_enum("G_TYPE_ULONG") print print_numeric_enum("G_TYPE_INT64") print print_numeric_enum("G_TYPE_UINT64") print print_numeric_enum("G_TYPE_ENUM") print print_numeric_enum("G_TYPE_FLAGS") print print_numeric_enum("G_TYPE_FLOAT") print print_numeric_enum("G_TYPE_DOUBLE") print print_numeric_enum("G_TYPE_STRING") print print_numeric_enum("G_TYPE_POINTER") print print_numeric_enum("G_TYPE_BOXED") print print_numeric_enum("G_TYPE_PARAM") print print_numeric_enum("G_TYPE_OBJECT") print print_end_of_category() print print_methodsFor("Gtk", "stock objects") print print_string_enum("GTK_STOCK_DIALOG_INFO") print print_string_enum("GTK_STOCK_DIALOG_WARNING") print print_string_enum("GTK_STOCK_DIALOG_ERROR") print print_string_enum("GTK_STOCK_DIALOG_QUESTION") print print_string_enum("GTK_STOCK_DND") print print_string_enum("GTK_STOCK_DND_MULTIPLE") print print_string_enum("GTK_STOCK_ADD ") print print_string_enum("GTK_STOCK_APPLY") print print_string_enum("GTK_STOCK_BOLD ") print print_string_enum("GTK_STOCK_CANCEL") print print_string_enum("GTK_STOCK_CDROM") print print_string_enum("GTK_STOCK_CLEAR") print print_string_enum("GTK_STOCK_CLOSE") print print_string_enum("GTK_STOCK_COLOR_PICKER") print print_string_enum("GTK_STOCK_CONVERT") print print_string_enum("GTK_STOCK_COPY") print print_string_enum("GTK_STOCK_CUT") print print_string_enum("GTK_STOCK_DELETE") print print_string_enum("GTK_STOCK_EXECUTE") print print_string_enum("GTK_STOCK_FIND") print print_string_enum("GTK_STOCK_FIND_AND_REPLACE") print print_string_enum("GTK_STOCK_FLOPPY") print print_string_enum("GTK_STOCK_GOTO_BOTTOM") print print_string_enum("GTK_STOCK_GOTO_FIRST") print print_string_enum("GTK_STOCK_GOTO_LAST") print print_string_enum("GTK_STOCK_GOTO_TOP") print print_string_enum("GTK_STOCK_GO_BACK") print print_string_enum("GTK_STOCK_GO_DOWN") print print_string_enum("GTK_STOCK_GO_FORWARD") print print_string_enum("GTK_STOCK_GO_UP") print print_string_enum("GTK_STOCK_HELP") print print_string_enum("GTK_STOCK_HOME") print print_string_enum("GTK_STOCK_INDEX") print print_string_enum("GTK_STOCK_ITALIC") print print_string_enum("GTK_STOCK_JUMP_TO") print print_string_enum("GTK_STOCK_JUSTIFY_CENTER") print print_string_enum("GTK_STOCK_JUSTIFY_FILL") print print_string_enum("GTK_STOCK_JUSTIFY_LEFT") print print_string_enum("GTK_STOCK_JUSTIFY_RIGHT") print print_string_enum("GTK_STOCK_MISSING_IMAGE") print print_string_enum("GTK_STOCK_NEW") print print_string_enum("GTK_STOCK_NO") print print_string_enum("GTK_STOCK_OK") print print_string_enum("GTK_STOCK_OPEN") print print_string_enum("GTK_STOCK_PASTE") print print_string_enum("GTK_STOCK_PREFERENCES") print print_string_enum("GTK_STOCK_PRINT") print print_string_enum("GTK_STOCK_PRINT_PREVIEW") print print_string_enum("GTK_STOCK_PROPERTIES") print print_string_enum("GTK_STOCK_QUIT") print print_string_enum("GTK_STOCK_REDO") print print_string_enum("GTK_STOCK_REFRESH") print print_string_enum("GTK_STOCK_REMOVE") print print_string_enum("GTK_STOCK_REVERT_TO_SAVED") print print_string_enum("GTK_STOCK_SAVE") print print_string_enum("GTK_STOCK_SAVE_AS") print print_string_enum("GTK_STOCK_SELECT_COLOR") print print_string_enum("GTK_STOCK_SELECT_FONT") print print_string_enum("GTK_STOCK_SORT_ASCENDING") print print_string_enum("GTK_STOCK_SORT_DESCENDING") print print_string_enum("GTK_STOCK_SPELL_CHECK") print print_string_enum("GTK_STOCK_STOP") print print_string_enum("GTK_STOCK_STRIKETHROUGH") print print_string_enum("GTK_STOCK_UNDELETE") print print_string_enum("GTK_STOCK_UNDERLINE") print print_string_enum("GTK_STOCK_UNDO") print print_string_enum("GTK_STOCK_YES") print print_string_enum("GTK_STOCK_ZOOM_100") print print_string_enum("GTK_STOCK_ZOOM_FIT") print print_string_enum("GTK_STOCK_ZOOM_IN") print print_string_enum("GTK_STOCK_ZOOM_OUT") print print_end_of_category() print " exit(0);" print "}" } function print_end_of_category() { return " printf(\" !\\n\\n\");" } function print_numeric_enum(c_name) { selector = smalltalkize(tolower(c_name)) return " printf(\"\\n" selector " ^%d!\", (int) " c_name ");" } function print_string_enum(c_name) { selector = smalltalkize(tolower(c_name)) return " printf(\"\\n" selector " ^'%s'!\", " c_name ");" } function print_methodsFor( class, category ) { return " printf(\"!" class " class methodsFor: '" category "'!\\n\");" } function get_enum_class( res ) { if (tolower (res) ~ /pango/) return "Pango" if (tolower (res) ~ /gdk/) return "Gdk" if (tolower (res) ~ /gtk/) return "Gtk" if (tolower (res) ~ /atk/) return "Atk" if (tolower (res) ~ /g/) return "GLib" return "" } function smalltalkize( res ) { first = substr (res, 1, 1) res = tolower( substr (res, 2) ) while (i = index (res, "_")) { first = first substr(res, 1, i - 1) toupper( substr (res, i + 1, 1)) res = substr (res, i + 2) } return first res } smalltalk-3.2.5/packages/gtk/example_arrow.st0000644000175000017500000000563512123404352016213 00000000000000"====================================================================== | | Smalltalk Gtk+ bindings examples | ======================================================================" "====================================================================== | | Copyright 2001, 2003, 2008, 2009 Free Software Foundation, Inc. | Written by Paolo Bonzini. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LESSER. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" PackageLoader fileInPackage: 'GTK'. Namespace current: GTK [ Object subclass: ArrowExample [ destroy: object data: data [ Gtk mainQuit ] open [ | window button box | window := GtkWindow new: Gtk gtkWindowToplevel. window setTitle: 'Arrow Buttons'. window connectSignal: 'destroy' to: self selector: #destroy:data: userData: nil. window setBorderWidth: 10. box := GtkHBox new: false spacing: 0. box setBorderWidth: 2. window add: box. button := GtkButton createArrowButton: Gtk gtkArrowUp shadowType: Gtk gtkShadowIn. box packStart: button expand: false fill: false padding: 3. button := GtkButton createArrowButton: Gtk gtkArrowDown shadowType: Gtk gtkShadowOut. box packStart: button expand: false fill: false padding: 3. button := GtkButton createArrowButton: Gtk gtkArrowLeft shadowType: Gtk gtkShadowEtchedIn. box packStart: button expand: false fill: false padding: 3. button := GtkButton createArrowButton: Gtk gtkArrowRight shadowType: Gtk gtkShadowEtchedOut. box packStart: button expand: false fill: false padding: 3. box show. window show ] ] ] GTK.GtkButton class extend [ createArrowButton: arrowType shadowType: shadowType [ | button arrow | button := self new. arrow := GtkArrow new: arrowType shadowType: shadowType. button add: arrow. button show. arrow show. ^button ] ] Namespace current: GTK [ ArrowExample new open. Gtk main ] smalltalk-3.2.5/packages/gtk/ChangeLog0000644000175000017500000002240612130343734014547 000000000000002011-08-13 Paolo Bonzini * gst-gtk.c: Show backtraces for GObject errors. 2011-08-13 Paolo Bonzini * gst-gtk.c: Fix connection to selectors with less arguments than the signal. 2011-08-04 Paolo Bonzini * MoreFuncs.st: Add functions to connect signal at end of list. * gst-gtk.c: Likewise. 2011-06-10 Paolo Bonzini * funcs.awk: Remove GSource. 2011-03-31 Paolo Bonzini * GtkImpl.st: Remove #setSensitive:. 2011-01-14 Paolo Bonzini * example_arrow.st: Explicitly load package. * example_aspectframe.st: Explicitly load package. * example_buttonbox.st: Explicitly load package. * example_entry.st: Explicitly load package. * example_eventbox.st: Explicitly load package. * example_hello.st: Explicitly load package. * example_tictactoe.st: Explicitly load package. * example_tree.st: Explicitly load package. 2011-01-14 Paolo Bonzini * gst-gtk.h: Remove. * gst-gtk.c: Remove inclusion. 2010-12-04 Paolo Bonzini * package.xml: Remove now superfluous tags. 2010-11-21 Paolo Bonzini * funcs.awk: More bugfixes and hacks for recent glib. 2010-10-28 Paolo Bonzini * MoreFuncs.st: Fix 64-bit cleanliness bug in #oopType. Reported by Mathieu Suen. 2010-10-15 Paolo Bonzini * GtkImpl.st: Return nil when gtk_tree_model_get_iter returns FALSE. 2010-10-15 Paolo Bonzini * funcs.awk: Improve conversion for functions that have a single argument before the variadic ones, and have that argument merged with the "...". 2010-06-23 Paolo Bonzini * GtkImpl.st: Add GtkAlignment class>>#new and GObject class>>#new. * MoreStructs.st: Add GdkColor. 2010-06-12 Paolo Bonzini * GtkImpl.st: Remove method now that's now inlined in VisualGST. 2010-05-28 Paolo Bonzini * gst-gtk.c: Work around missing g_poll in some versions of glib for Mac OS X. 2010-04-13 Paolo Bonzini * gst-gtk.c: Fix Windows deadlock by polling every 20 ms the VM thread. 2010-04-13 Paolo Bonzini * gst-gtk.c: Move check phase to the dispatching thread. 2010-04-13 Paolo Bonzini * gst-gtk.c: Fix ordering of unlock and release. Loop on g_main_context_wait. 2010-03-03 Gwenael Casaccio * GtkImpl.st: Move acquire/dispatch/release to a single C call-out for speed. * MoreFuncs.st: Adjust C call-outs. * gst-gtk.c: Add main_context_iterate. 2010-03-03 Paolo Bonzini * structs.awk: Add parent of GdkWindowObject. 2010-02-19 Paolo Bonzini Gwenael Casaccio * GtkImpl.st: Rewrite event loop. * MoreFuncs.st: Rewrite event loop. * gst-gtk.c: Rewrite event loop. 2010-02-19 Paolo Bonzini * GtkImpl.st: Move extensions to/from VisualGST. 2010-01-05 Gwenael Casaccio * gst-gtk.c (connect_signal): Return result of g_signal_connect_closure. * MoreFuncs.st: Return value from #connectSignal:... and add #disconnectSignal:. 2010-01-01 Paolo Bonzini * Update copyright years. 2009-11-03 Paolo Bonzini * funcs.awk: Point every #free method to unref if there is an unref method. 2009-11-03 Paolo Bonzini * MoreStructs.st: Remove GtkTreeModel. * structs.awk: Derive interfaces from GObject. 2009-10-31 Paolo Bonzini * GtkDecl.st: Remove useless empty classes. * GtkImpl.st: Add packed-columns constructor for GtkTreeView. 2009-10-26 Gwenael Casaccio * MoreFuncs.st: Add G_TYPE_OOP support. * gst-gtk.c: Likewise. 2009-10-23 Paolo Bonzini * GtkImpl.st: Add a couple of VisualGST extra methods. 2009-09-16 Paolo Bonzini * GtkImpl.st: Add GtkMessageDialog utility methods. 2009-09-11 Paolo Bonzini * GtkImpl.st: Sync with VisualGST. 2009-09-08 Paolo Bonzini * GtkImpl.st: Sync with VisualGST. 2009-09-03 Paolo Bonzini * GtkImpl.st: Declare more functions from VisualGST. * MoreFuncs.st: Likewise. * MoreStructs.st: Likewise. 2009-09-03 Paolo Bonzini * GtkImpl.st: Make GdkDrawable polymorphic with CairoContextProvider. * MoreFuncs.st: Declare gdk_cairo_create. * package.xml: Make Cairo a prerequisite. 2009-08-18 Paolo Bonzini * Makefile: Build libs.def instead of Libs.st. * gst-gtk.c: Include it. * package.xml: Drop Libs.st. 2009-08-17 Paolo Bonzini * mkorder.awk: Fix off-by-one. 2009-08-05 Paolo Bonzini * order.st: Rewrite... * mkorder.awk: ... in awk, to ease cross compilation. 2009-07-01 Paolo Bonzini * example_buttonbox.st: Fix. * example_entry.st: Fix. 2009-07-01 Paolo Bonzini * MoreFuncs.st: Add gtkInitialized. Stub gstGtkInit. * example_arrow.st: Remove gstGtkInit. * example_aspectframe.st: Remove gstGtkInit. * example_buttonbox.st: Remove gstGtkInit. * example_entry.st: Remove gstGtkInit. * example_eventbox.st: Remove gstGtkInit. * example_hello.st: Remove gstGtkInit. * example_tictactoe.st: Remove gstGtkInit. * example_tree.st: Remove gstGtkInit. * gst-gtk.c: Add gtkInitialized, use gtk_init_check instead of gtk_init moving it to gst_initModule. 2009-07-01 Gwenael Casaccio * gst-gtk.c: Call g_thread_init. 2009-06-22 Gwenael Casaccio Paolo Bonzini * gst-gtk.c: Add functions for accelerator groups. * MoreFuncs.st: Add call-outs here. 2009-04-28 Paolo Bonzini * MoreFuncs.st: Add functions to fire signals. 2009-04-28 Paolo Bonzini * GtkImpl.st: Use gtk_*_iter_copy to allocate new iterators. * funcs.awk: Wrap gtk_*_free to avoid freeing GC-allocated objects. 2009-02-25 Paolo Bonzini * MoreStructs.st: Add freeing, typos. 2008-09-20 Paolo Bonzini * MoreStructs.st: Add GList. 2008-09-20 Paolo Bonzini * gst-gtk.c: Include a backtrace in log messages. 2008-09-20 Paolo Bonzini * gst-gtk.c: Support signals with no user data. * MoreFuncs.st: Likewise. 2008-08-12 Paolo Bonzini * example_arrow.st: Fix pasto. * funcs.awk: Put gdk_window_* methods in GdkDrawable to support GTK+ 2.12. 2008-05-06 Paolo Bonzini * example_entry.st: Use GC-allocated CObjects. 2008-05-06 Paolo Bonzini * order.st: Close those files! 2008-04-16 Paolo Bonzini * order.st: Fix problem with new file classes. 2008-04-07 Paolo Bonzini * order.st: Use #/. 2007-08-13 Paolo Bonzini * MoreFuncs.st: Switch to the new syntax for "returning:". * funcs.awk: Likewise. 2007-03-19 Paolo Bonzini * GtkDecl.st: Convert class variables to class-instance. 2006-12-05 Paolo Bonzini *** Version 2.3 released. 2006-11-21 Paolo Bonzini * gst-gtk.c: Add GPL exception. * gst-gtk.h: Add GPL exception. * placer.c: Add GPL exception. * placer.h: Add GPL exception. * testplacer.c: Add GPL exception. 2006-10-05 Paolo Bonzini * funcs.awk: Fix for newer GTK+. * structs.awk: Likewise. 2006-09-29 Paolo Bonzini * funcs.awk: Fix for newer GTK+. 2006-09-22 Paolo Bonzini * funcs.awk: Fix more non-portable code. 2006-09-22 Paolo Bonzini * cpp.awk: Fix non-portable code. * funcs.awk: Fix some non-portable code. 2006-09-04 Paolo Bonzini * order.st: Use Getopt, add -P flag instead of hardcoding prefixes. 2006-07-17 Paolo Bonzini * funcs.awk: support wchar_t. 2006-04-26 Paolo Bonzini * funcs.awk: Fix placement of gdk_draw_* functions. 2006-03-27 Robert Collins * cpp.awk: Do not include #ifndef GDK_PIXBUF_ENABLE_BACKEND stuff. 2005-11-21 Paolo Bonzini * gst-gtk.c: Support 2 extra arguments to the signal function, i.e. the widget and the user data. 2005-10-10 Paolo Bonzini * funcs.awk: Do not include error_quark functions, they are related to a GLib module and not to a class. Do not include get_type functions if the type is not mapped to a Smalltalk class. 2005-10-04 Paolo Bonzini * funcs.awk: GTK+ 2.6 has functions with internal visibility. * structs.awk: GTK+ 2.6 widgets use a couple more GLib data types. 2005-09-23 Paolo Bonzini * mk_sizeof.awk: GTK+ 2.6 update. * mk_enums.awk: GTK+ 2.6 update. 2005-08-28 Paolo Bonzini * gst-gtk.c: Fix warnings. 2005-03-25 Paolo Bonzini * MoreFuncs.st: Switch to new C-call descriptions. * funcs.awk: Switch to new C-call descriptions. 2005-03-25 Paolo Bonzini * GtkDecl.st: Remove file-ins, now done through packages.xml. * GtkImpl.st: Add code that was after file-ins in GtkDecl.st smalltalk-3.2.5/packages/gtk/example_eventbox.st0000644000175000017500000000463312123404352016710 00000000000000"====================================================================== | | Smalltalk Gtk+ bindings examples | ======================================================================" "====================================================================== | | Copyright 2001, 2003, 2009 Free Software Foundation, Inc. | Written by Paolo Bonzini. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LESSER. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" PackageLoader fileInPackage: 'GTK'. Namespace current: GTK [ Object subclass: EventBoxExample [ buttonPressEvent: object event: event data: data [ data destroy ] destroy: object data: data [ Gtk mainQuit ] open [ | window eventBox label | window := GtkWindow new: Gtk gtkWindowToplevel. window connectSignal: 'destroy' to: self selector: #destroy:data: userData: nil. window setTitle: 'Event Box'. window setBorderWidth: 10. eventBox := GtkEventBox new. window add: eventBox. eventBox show. label := GtkLabel new: 'Click here to quit, quit, quit, quit, quit'. eventBox add: label. label show. label setSizeRequest: 110 height: 20. eventBox setEvents: Gdk gdkButtonPressMask. eventBox connectSignal: 'button_press_event' to: self selector: #buttonPressEvent:event:data: userData: window. eventBox realize. eventBox getWindow setCursor: (GdkCursor new: Gdk gdkHand1). window show ] ] ] Namespace current: GTK [ EventBoxExample new open. Gtk main ] smalltalk-3.2.5/packages/gtk/testplacer.c0000644000175000017500000001071112123404352015277 00000000000000/*********************************************************************** * * Example of using the placer geometry manager * ***********************************************************************/ /*********************************************************************** * * Copyright 2003, 2006 Free Software Foundation, Inc. * Written by Paolo Bonzini. * * This file is part of GNU Smalltalk. * * GNU Smalltalk is free software; you can redistribute it and/or modify it * under the terms of the GNU General Public License as published by the Free * Software Foundation; either version 2, or (at your option) any later * version. * * Linking GNU Smalltalk statically or dynamically with other modules is * making a combined work based on GNU Smalltalk. Thus, the terms and * conditions of the GNU General Public License cover the whole * combination. * * In addition, as a special exception, the Free Software Foundation * give you permission to combine GNU Smalltalk with free software * programs or libraries that are released under the GNU LGPL and with * independent programs running under the GNU Smalltalk virtual machine. * * You may copy and distribute such a system following the terms of the * GNU GPL for GNU Smalltalk and the licenses of the other code * concerned, provided that you include the source code of that other * code when and as the GNU GPL requires distribution of source code. * * Note that people who make modified versions of GNU Smalltalk are not * obligated to grant this special exception for their modified * versions; it is their choice whether to do so. The GNU General * Public License gives permission to release a modified version without * this exception; this exception also makes it possible to release a * modified version which carries forward this exception. * * GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or * FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for * more details. * * You should have received a copy of the GNU General Public License along with * GNU Smalltalk; see the file COPYING. If not, write to the Free Software * Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * ***********************************************************************/ #include #include "placer.h" #include "placer.c" gint rel_width = 5461; gint rel_height = 8191; void move_button (GtkWidget *widget, GtkWidget *placer) { rel_width = 5461 + 8192 - rel_width; rel_height = 8192 + 10922 - rel_height; gtk_placer_resize_rel (GTK_PLACER (placer), widget, rel_width, rel_height); } int main (int argc, char *argv[]) { /* GtkWidget is the storage type for widgets */ GtkWidget *window; GtkWidget *placer; GtkWidget *button; gint i; const int rel_x[4] = { 0, 8192, 16384, 24576 }; const int rel_y[3] = { 0, 10922, 21844 }; /* Initialise GTK */ gtk_init (&argc, &argv); /* Create a new window */ window = gtk_window_new (GTK_WINDOW_TOPLEVEL); gtk_window_set_title (GTK_WINDOW (window), "Placer Container"); /* Here we connect the "destroy" event to a signal handler */ g_signal_connect (G_OBJECT (window), "destroy", G_CALLBACK (gtk_main_quit), NULL); /* Sets the border width of the window. */ gtk_container_set_border_width (GTK_CONTAINER (window), 5); /* Create a Placer Container */ placer = gtk_placer_new (); gtk_container_add (GTK_CONTAINER (window), placer); gtk_widget_show (placer); for (i = 0 ; i <= 11 ; i++) { /* Creates a new button with the label "Press me" */ button = gtk_button_new_with_label ("Press me"); /* When the button receives the "clicked" signal, it will call the * function move_button() passing it the Fixed Container as its * argument. */ g_signal_connect (G_OBJECT (button), "clicked", G_CALLBACK (move_button), (gpointer) placer); /* This packs the button into the placer containers window. */ gtk_placer_put (GTK_PLACER (placer), button, 5, 2, -10, -4, rel_x[i % 4], rel_y[i / 4], rel_width, rel_height); /* The final step is to display this newly created widget. */ gtk_widget_show (button); } /* gtk_window_set_default_size (GTK_WINDOW (window), 400, 200); */ /* Display the window */ gtk_widget_show (window); /* Enter the event loop */ gtk_main (); return 0; } smalltalk-3.2.5/packages/gtk/Makefile.am0000644000175000017500000000712112130343734015026 00000000000000CLEANFILES = $(nodist_noinst_SCRIPTS) $(nodist_noinst_HEADERS) \ $(BUILT_SOURCES) $(nodist_noinst_DATA) order LC_UNSET = LANG=C; export LANG; \ LC_COLLATE=C; export LC_COLLATE; \ LC_CTYPE=C; export LC_CTYPE; \ LC_MESSAGES=C; export LC_MESSAGES; \ LC_MONETARY=C; export LC_MONETARY; \ LC_NUMERIC=C; export LC_NUMERIC; \ LC_TIME=C; export LC_TIME EXTRA_DIST = cpp.awk structs.awk funcs.awk mk_enums.awk mk_sizeof.awk mkorder.awk gst_module_ldflags = -rpath $(moduleexecdir) -release $(VERSION) -module \ -no-undefined -export-symbols-regex gst_initModule ALL_LIBS = $(GLIB_LIBS) $(GTK_LIBS) $(PANGO_LIBS) $(ATK_LIBS) $(GTHREAD_LIBS) \ $(CAIRO_LIBS) moduleexec_LTLIBRARIES = gst-gtk.la gst_gtk_la_LDFLAGS = $(gst_module_ldflags) gst_gtk_la_LIBADD = $(ALL_LIBS) dist_gst_gtk_la_SOURCES = gst-gtk.c placer.c BUILT_SOURCES = libs.def dist_noinst_HEADERS = placer.h EXTRA_PROGRAMS = testplacer sizeof enums testplacer_SOURCES = testplacer.c testplacer_LDADD = $(GLIB_LIBS) $(GTK_LIBS) AM_CPPFLAGS = \ -I$(top_srcdir)/libgst \ -I$(top_srcdir)/lib-src \ -I$(top_srcdir)/libltdl AM_CFLAGS = $(GLIB_CFLAGS) $(GTK_CFLAGS) $(PANGO_CFLAGS) $(ATK_CFLAGS) GTK_FILES = \ glib-object.h gdk/gdk.h \ gdk-pixbuf/gdk-pixbuf.h gtk/gtk.h atk/atk.h pango/pango.h # We don't want to include all of GLib for obvious reasons... GLIB_FILES = \ glib/goption.h glib/gdate.h glib/gmain.h LOCAL_FILES = $(srcdir)/placer.h nodist_noinst_DATA = Structs.st Funcs.st Enums.st nodist_noinst_SCRIPTS = cpp structs funcs mk_sizeof mk_enums noinst_PROGRAMS = enums sizeof nodist_enums_SOURCES = enums.c nodist_sizeof_SOURCES = sizeof.c BUILT_SOURCES += enums.c sizeof.c # Rules to build the bindings from the GTK+ header files follow... %: %.awk @case "$(AWK)" in \ */*) AWK="$(AWK)" ;; \ *) \ IFS=":"; \ for i in $$PATH; do \ test -f $$i/$(AWK) && AWK="$$i/$(AWK)" && break; \ done ;; \ esac; \ echo "$(SED) -e \"1s,@AWK\@,$$AWK,\" < $< > $@"; \ $(SED) -e "1s,@AWK\@,$$AWK," < $< > $@ chmod +x $@ cpp: $(srcdir)/cpp.awk structs: $(srcdir)/structs.awk funcs: $(srcdir)/funcs.awk mk_enums: $(srcdir)/mk_enums.awk mk_sizeof: $(srcdir)/mk_sizeof.awk # ------------------------------------- libs.def: Makefile for i in $(ALL_LIBS); do \ case $$i in \ -L*) \ j=`echo $$i | sed 's,^-L,,'` ; \ echo "_gst_vm_proxy->dlAddSearchDir(\"$$j\");" ;; \ -lG*|-lg*|-lATK*|-latk*|-lPango*|-lpango*) \ j=`echo $$i | sed 's,^-l,lib,'` ; \ echo "_gst_vm_proxy->dlOpen(\"$$j\", false);" ;; \ *) ;; \ esac; \ done | sort -u > libs.def Structs.st: structs sizeof$(EXEEXT) cpp order $(LC_UNSET); xargs ./cpp < order | ./structs > Structs.st $(LC_UNSET); ./sizeof$(EXEEXT) >> Structs.st Enums.st: enums$(EXEEXT) $(LC_UNSET); ./enums$(EXEEXT) > Enums.st Funcs.st: funcs cpp order $(LC_UNSET); xargs ./cpp < order | ./funcs > Funcs.st sizeof.c: mk_sizeof cpp order $(LC_UNSET); xargs ./cpp < order | ./mk_sizeof > sizeof.c enums.c: mk_enums cpp order $(LC_UNSET); xargs ./cpp < order | ./mk_enums > enums.c order: mkorder.awk Makefile $(LOCAL_FILES) $(AWK) \ -vPKG_CONFIG='$(PKG_CONFIG)' \ -v_prefixes='g atk pango' \ -v_libs="gobject-2.0 gdk-2.0 gdk-pixbuf-2.0 pango gtk+-2.0 atk" \ -v_files="$(GTK_FILES) $(LOCAL_FILES)" -f $(srcdir)/mkorder.awk \ | while read i; do \ case "$$i" in \ error:*) \ echo "$$i" >&2; exit 1;; \ */gobject/*) \ echo "$$i" ;; \ */glib/*) \ case " $(GLIB_FILES) " in \ *" glib/`basename $$i` "*) echo "$$i" ;; \ *) ;; \ esac ;; \ *) \ echo "$$i" ;; \ esac; \ done > order smalltalk-3.2.5/packages/gtk/example_buttonbox.st0000644000175000017500000001107412123404352017077 00000000000000"====================================================================== | | Smalltalk Gtk+ bindings examples | ======================================================================" "====================================================================== | | Copyright 2001, 2003, 2009 Free Software Foundation, Inc. | Written by Paolo Bonzini. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LESSER. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" PackageLoader fileInPackage: 'GTK'. Namespace current: GTK [ Object subclass: ButtonBoxExample [ destroy: object data: data [ Gtk mainQuit ] open [ | window mainVBox hbox vbox frameHorz frameVert | window := GtkWindow new: Gtk gtkWindowToplevel. window setTitle: 'Button Boxes'. window connectSignal: 'destroy' to: self selector: #destroy:data: userData: nil. window setBorderWidth: 10. mainVBox := GtkVBox new: false spacing: 0. window add: mainVBox. frameHorz := GtkFrame new: 'Horizontal Button Boxes'. mainVBox packStart: frameHorz expand: true fill: true padding: 10. vbox := GtkVBox new: false spacing: 0. vbox setBorderWidth: 10. frameHorz add: vbox. vbox packStart: (GtkHButtonBox createButtonBox: 'Spread (spacing 40)' spacing: 40 layout: Gtk gtkButtonboxSpread) expand: true fill: true padding: 0. vbox packStart: (GtkHButtonBox createButtonBox: 'Edge (spacing 30)' spacing: 30 layout: Gtk gtkButtonboxEdge) expand: true fill: true padding: 0. vbox packStart: (GtkHButtonBox createButtonBox: 'Start (spacing 20)' spacing: 20 layout: Gtk gtkButtonboxStart) expand: true fill: true padding: 0. vbox packStart: (GtkHButtonBox createButtonBox: 'End (spacing 10)' spacing: 10 layout: Gtk gtkButtonboxEnd) expand: true fill: true padding: 0. frameVert := GtkFrame new: 'Vertical Button Boxes'. mainVBox packStart: frameVert expand: true fill: true padding: 10. hbox := GtkHBox new: false spacing: 0. hbox setBorderWidth: 10. frameVert add: hbox. hbox packStart: (GtkVButtonBox createButtonBox: 'Spread (spacing 5)' spacing: 5 layout: Gtk gtkButtonboxSpread) expand: true fill: true padding: 0. hbox packStart: (GtkVButtonBox createButtonBox: 'Edge (spacing 30)' spacing: 30 layout: Gtk gtkButtonboxEdge) expand: true fill: true padding: 0. hbox packStart: (GtkVButtonBox createButtonBox: 'Start (spacing 20)' spacing: 20 layout: Gtk gtkButtonboxStart) expand: true fill: true padding: 0. hbox packStart: (GtkVButtonBox createButtonBox: 'End (spacing 20)' spacing: 20 layout: Gtk gtkButtonboxEnd) expand: true fill: true padding: 0. window showAll ] ] ] GTK.GtkButtonBox class extend [ createButtonBox: title spacing: spacing layout: layout [ | box frame button | frame := GtkFrame new: title. "Note the use of polymorphism here: we are extending the Gtk binding itself! The original C example had an extra parameter to specify whether to create an horizontal or vertical button box." box := self new. box setBorderWidth: 5. frame add: box. box setLayout: layout. box setSpacing: spacing. button := GtkButton newFromStock: Gtk gtkStockOk. box add: button. button := GtkButton newFromStock: Gtk gtkStockCancel. box add: button. button := GtkButton newFromStock: Gtk gtkStockHelp. box add: button. ^frame ] ] Namespace current: GTK [ ButtonBoxExample new open. Gtk main ] smalltalk-3.2.5/packages/gtk/cpp.awk0000644000175000017500000000516012123404352014255 00000000000000#! @AWK@ -f ####################################################################### # # Gtk wrapper creation scripts (poor man's preprocessor) # ######################################################################## ####################################################################### # # Copyright 2003, 2004, 2006 Free Software Foundation, Inc. # Written by Paolo Bonzini # # This file is part of the GNU Smalltalk class library. # # The GNU Smalltalk class library is free software; you can redistribute it # and/or modify it under the terms of the GNU Lesser General Public License # as published by the Free Software Foundation; either version 2.1, or (at # your option) any later version. # # The GNU Smalltalk class library is distributed in the hope that it will be # useful, but WITHOUT ANY WARRANTY; without even the implied warranty of # MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser # General Public License for more details. # # You should have received a copy of the GNU Lesser General Public License # along with the GNU Smalltalk class library; see the file COPYING.LESSER. # If not, write to the Free Software Foundation, 59 Temple Place - Suite # 330, Boston, MA 02110-1301, USA. # ######################################################################## in_comment { if (!match ($0, /\*\//)) next else { # Remove end of multiline comment $0 = substr ($0, RSTART + 2) in_comment = 0 } } /\/\*/ { # Remove sequences of asterisks in the middle of a single-line comment while (sub (/\/\*[^*]*\*+[^\/*]/, "/* ")) 0; gsub (/\/\*[^*]*\*+\//, "") # Detect multiline comments, removing their first line if (sub (/\/\*.*/, "")) in_comment = 1 } /^#ifn?def/ { if ($2 in ifdef) $2 = "" preproc_stack[++preproc_n] = $2 ifdef[$2] = /^#ifdef/; next } /^#else/ { ifdef[preproc_stack[preproc_n]] = !ifdef[preproc_stack[preproc_n]] next } /^#endif/ { delete ifdef[preproc_stack[preproc_n]] delete preproc_stack[preproc_n] preproc_n-- next } /^#define/ { while ($0 ~ /\\$/) getline next } in_ifndef("G_DISABLE_DEPRECATED") { next } in_ifndef("GDK_DISABLE_DEPRECATED") { next } in_ifndef("GTK_DISABLE_DEPRECATED") { next } in_ifndef("GDK_PIXBUF_ENABLE_BACKEND") { next } in_ifdef("__cplusplus") { next } in_ifdef("GTK_ENABLE_BROKEN") { next } in_ifdef("G_PLATFORM_WIN32") { next } in_ifdef("PANGO_ENABLE_BACKEND") { next } in_ifdef("PANGO_ENABLE_ENGINE") { next } { print } function in_ifdef (x) { return x in ifdef && ifdef[x] } function in_ifndef (x) { return x in ifdef && !ifdef[x] } smalltalk-3.2.5/packages/gtk/example_entry.st0000644000175000017500000000752412123404352016221 00000000000000"====================================================================== | | Smalltalk Gtk+ bindings examples | ======================================================================" "====================================================================== | | Copyright 2001, 2003, 2008, 2009 Free Software Foundation, Inc. | Written by Paolo Bonzini. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LESSER. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" PackageLoader fileInPackage: 'GTK'. Namespace current: GTK [ Object subclass: EntryExample [ | entry window | activate: object data: data [ entry getText displayNl ] clicked: object data: data [ window destroy ] toggled: object data: selector [ entry perform: selector with: object getActive ] destroy: object data: data [ Gtk mainQuit ] delete: object event: event data: data [ window destroy ] open [ | vbox hbox button check pos | window := GtkWindow new: Gtk gtkWindowToplevel. window setSizeRequest: 200 height: 100. window setTitle: 'GTK Entry'. window connectSignal: 'destroy' to: self selector: #destroy:data: userData: nil. window connectSignal: 'delete_event' to: self selector: #delete:event:data: userData: nil. vbox := GtkVBox new: false spacing: 0. window add: vbox. vbox show. entry := GtkEntry new. entry setMaxLength: 50. entry connectSignal: 'activate' to: self selector: #activate:data: userData: nil. entry setText: 'hello'. "This function needs an int* as the last parameter." entry insertText: ' world' newTextLength: -1 position: (CInt gcValue: entry getText size). entry selectRegion: 0 endPos: entry getText size. vbox packStart: entry expand: true fill: true padding: 0. entry show. hbox := GtkHBox new: false spacing: 0. vbox add: hbox. hbox show. check := GtkCheckButton newWithLabel: 'Editable'. hbox packStart: check expand: true fill: true padding: 0. check connectSignal: 'toggled' to: self selector: #toggled:data: userData: #setEditable:. check setActive: true. check show. check := GtkCheckButton newWithLabel: 'Visible'. hbox packStart: check expand: true fill: true padding: 0. check connectSignal: 'toggled' to: self selector: #toggled:data: userData: #setVisibility:. check setActive: true. check show. button := GtkButton newFromStock: 'gtk-close'. button connectSignal: 'clicked' to: self selector: #clicked:data: userData: nil. vbox packStart: button expand: true fill: true padding: 0. button setFlags: Gtk gtkCanDefault. button grabDefault. button show. window show ] ] ] Namespace current: GTK [ EntryExample new open. Gtk main ] smalltalk-3.2.5/packages/gtk/example_hello.st0000644000175000017500000000420512123404352016154 00000000000000"====================================================================== | | Smalltalk Gtk+ bindings examples | ======================================================================" "====================================================================== | | Copyright 2001, 2003, 2009 Free Software Foundation, Inc. | Written by Paolo Bonzini. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LESSER. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" PackageLoader fileInPackage: 'GTK'. Namespace current: GTK [ Object subclass: HelloWorldExample [ clicked: widget data: data [ data displayNl ] destroy: object data: data [ Gtk mainQuit ] open [ | w b l | w := GtkWindow new: Gtk gtkWindowToplevel. b := GtkButton new. l := GtkLabel new: ' Push me and watch stdout! ' , ' '. w add: b. b add: l. b show. l show. w setTitle: 'GTK+ bindings demo'. b connectSignal: 'clicked' to: self selector: #clicked:data: userData: 'Hello, world!'. w connectSignal: 'destroy' to: self selector: #destroy:data: userData: nil. w show ] ] ] Namespace current: GTK [ HelloWorldExample new open. Gtk main ] smalltalk-3.2.5/packages/gtk/mkorder.awk0000644000175000017500000000560712123404352015144 00000000000000####################################################################### # # Smalltalk Gtk+ bindings (ordering header files). # ######################################################################## ####################################################################### # # Copyright 2004, 2006, 2008, 2009 Free Software Foundation, Inc. # Written by Mike Anderson and Paolo Bonzini. # # This file is part of the GNU Smalltalk class library. # # The GNU Smalltalk class library is free software; you can redistribute it # and/or modify it under the terms of the GNU Lesser General Public License # as published by the Free Software Foundation; either version 2.1, or (at # your option) any later version. # # The GNU Smalltalk class library is distributed in the hope that it will be # useful, but WITHOUT ANY WARRANTY; without even the implied warranty of # MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser # General Public License for more details. # # You should have received a copy of the GNU Lesser General Public License # along with the GNU Smalltalk class library; see the file COPYING.LESSER. # If not, write to the Free Software Foundation, 59 Temple Place - Suite # 330, Boston, MA 02110-1301, USA. # ######################################################################## BEGIN { paths[1] = "." n_paths = 1 n_prefixes = split(_prefixes, prefixes) split(_libs, libs) split(_files, files) for (i = 1; (i in libs); i++) process_lib(libs[i]) for (i = 1; (i in files); i++) process_file(files[i]) exit } function process_lib(lib, prog, i) { prog = PKG_CONFIG " --cflags " lib while (prog | getline) for (i = 1; i <= NF; i++) if ($i ~ /^-I/) paths[++n_paths] = substr($i, 3) close(prog) } function has_prefix(path, i) { for (i = 1; (i in prefixes); i++) if (prefixes[i] == substr(path, 0, length(prefixes[i]))) return 1 return 0 } function process_file(name, file) { file = find_file(name) if (file in processed) return processed[file] = 1 if (file == "") print "error: cannot find " name else { scan(file) print file } } function check_file(name, ok) { ok = (getline < name) != -1 close(name) return ok } function find_file(name, i) { if (name ~ /^\//) return check_file(name) ? name : "" for (i = 1; (i in paths); i++) if (check_file(paths[i] "/" name)) return paths[i] "/" name return "" } function scan(file, dir, incfile) { dir = file sub(/\/[^\/]*$/, "", dir) while (getline < file) { if ($1 != "#include") continue if ($2 ~ /^]*>/) else if ($2 ~ /^"/) match ($0, /"[^>]*"/) incfile = substr($0, RSTART + 1, RLENGTH - 2) if (!has_prefix(incfile)) continue if ($2 ~ /^"/ && check_file(dir "/" incfile)) process_file(dir "/" incfile) else process_file(incfile) } close(file) } smalltalk-3.2.5/packages/gtk/funcs.awk0000644000175000017500000003250212130343734014615 00000000000000#! @AWK@ -f ####################################################################### # # Gtk wrapper creation scripts (C function declarations) # ######################################################################## ####################################################################### # # Copyright 2001, 2003, 2005, 2006, 2008, 2009 Free Software Foundation, Inc. # Written by Paolo Bonzini and Dragomir Milivojevic # # This file is part of the GNU Smalltalk class library. # # The GNU Smalltalk class library is free software; you can redistribute it # and/or modify it under the terms of the GNU Lesser General Public License # as published by the Free Software Foundation; either version 2.1, or (at # your option) any later version. # # The GNU Smalltalk class library is distributed in the hope that it will be # useful, but WITHOUT ANY WARRANTY; without even the implied warranty of # MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser # General Public License for more details. # # You should have received a copy of the GNU Lesser General Public License # along with the GNU Smalltalk class library; see the file COPYING.LESSER. # If not, write to the Free Software Foundation, 59 Temple Place - Suite # 330, Boston, MA 02110-1301, USA. # ######################################################################## BEGIN { print "\"Automatically generated, do not edit!\"" FS = "[ (\t]+" type["void"] = "#void" type["int"] = "#int" type["char"] = "#char" type["wchar_t"] = "#wchar" type["double"] = "#double" type["gconstpointer"] = "#cObject" type["gpointer"] = "#cObject" type["GStrv"] = "#cObject" type["va_list"] = "__skip_this__" type["GCallback"] = "__skip_this__" type["GClosure"] = "__skip_this__" type["GCClosure"] = "__skip_this__" type["GHash"] = "__skip_this__" # Skip GLib artifacts type["GFlags"] = "__skip_this__" type["GValue"] = "__skip_this__" type["GIo"] = "__skip_this__" type["GEnum"] = "__skip_this__" type["GPointer"] = "__skip_this__" type["GGstring"] = "__skip_this__" type["GStrdup"] = "__skip_this__" type["GTypeClass"] = "__skip_this__" type["GScanner"] = "__skip_this__" type["GBoxed"] = "__skip_this__" type["GSignal"] = "__skip_this__" type["GSource"] = "__skip_this__" type["PangoCoverage"] = "__skip_this__" #FIXME # FIXME: what about 64-bit architectures? type["gint8"] = "#int" type["guint8"] = "#int" type["gint16"] = "#int" type["guint16"] = "#int" type["gint32"] = "#int" type["guint32"] = "#int" type["GType"] = "#long" type["GtkType"] = "#long" type["gchar"] = "#char" type["guchar"] = "#int" type["gunichar"] = "#int" type["gshort"] = "#int" type["gushort"] = "#int" type["glong"] = "#long" type["gulong"] = "#long" type["gint"] = "#int" type["guint"] = "#int" type["gboolean"] = "#boolean" type["gfloat"] = "#float" type["gdouble"] = "#double" type["GdkAtom"] = "#cObject" ptr_type["#int"] = "CInt type" ptr_type["#long"] = "CLong type" ptr_type["#boolean"] = "CBoolean type" ptr_type["#float"] = "CFloat type" ptr_type["#double"] = "CDouble type" ptr_type["#char"] = "#string" ptr_type["#wchar"] = "#wstring" ptr_type["__byte__"] = "#byteArray" ptr_type["#cObject"] = "#cObject" # Fix asymmetry method_regexp = "^g_param_values?_|^g_param_type_|^gtk_file_chooser_|^gdk_window_|^g_bus_" prefix_class["g_param_value_"] = "GParamSpec" prefix_class["g_param_values_"] = "GParamSpec" prefix_class["g_param_type_"] = "GParamSpec" prefix_class["g_bus_"] = "GDBusConnection" self_class["g_param_value_"] = "GParamSpec" self_class["g_param_values_"] = "GParamSpec" self_class["g_param_type_"] = "GParamSpec" self_class["g_bus_"] = "GDBusConnection" # Methods that we do not need method_skip_regexp = "(^$)|(_error_quark$)" # Not really exact, this belongs in GtkFileChooserWidget too. # We need a way to do interfaces. prefix_class["gtk_file_chooser_"] = "GtkFileChooserDialog" prefix_class["gdk_window_"] = "GdkDrawable" self_class["gtk_file_chooser_"] = "GtkFileChooserDialog" self_class["gdk_window_"] = "GdkWindow" } # Pick the correct case for the class (e.g. CList vs. Clist) # and decide what will be the prefix for its methods $1 == "struct" && $2 ~ /^_/ { name = substr($2, 2) define_class(name) } $0 ~ /^typedef (struct|union)/ && $3 ~ /_(G|Pango|Atk)/ { gsub(/[_;]/, "", $0) define_class($4) } $1 == "typedef" && $2 ~ /^(G|Pango|Atk)/ { # Take into account typedefs from a struct named differently. gsub(/[_;]/, "", $0) define_class($3) } match ($0, /^G_CONST_RETURN[ \t]*/) { $0 = substr ($0, RLENGTH + 1) } match_function_first_line($0) { gsub(/[ \t]+/, "", first_line[1]) cFuncName = first_line[2] if (first_line[2] ~ method_skip_regexp) next else if (match(first_line[2], method_regexp)) { prefixClassName = prefix_class[substr(first_line[2], 1, RLENGTH)] selfClassName = self_class[substr(first_line[2], 1, RLENGTH)] } # For types that are not classes, do not create the getType method else if (first_line[2] ~ /get_type$/) next else if (match (first_line[2], /^(g_)?[a-z]*_/)) prefixClassName = selfClassName = smalltalkize(toupper(substr(first_line[2], 1, RLENGTH - 1))) if (tolower(prefixClassName) in correct_case) prefixClassName = correct_case[tolower(prefixClassName)] if (tolower(selfClassName) in correct_case) selfClassName = correct_case[tolower(selfClassName)] first_line[2] = substr(first_line[2], RLENGTH + 1) # Move object creation methods to the class side. We have a single # special case for an API exception: gtk_ui_manager_new_merge_id # doesn't make a new ui_manager creation = first_line[2] ~ /^(newv?|alloc)($|_)/ if (first_line[2] == "new_merge_id") creation = 0 # Lose some symmetry for the sake of intuitiveness self = first_line[2] ~ /(^|_)((un)?ref$|(dis)?connect)/ if (match(first_line[2], /^paint_/)) prefixClassName = selfClassName = "GtkStyle" if (match(first_line[2], /^draw_/)) prefixClassName = selfClassName = (prefixClassName == "Gdk" ? "GdkDrawable" : "GtkStyle") smalltalkFuncName = smalltalkize(first_line[2]) # create one long string and tokenize it decl = first_line[1] " " first_line[2] " " first_line[4] while( match( decl, ";" ) == 0 ) { getline for (i = 1; i <= NF; i++) # Convert arrays to pointers while( $i ~ /\[[0-9]*\]/ ) { $i = "*" $i sub (/\[[0-9]*\]/, "", $i) } decl = decl " " $0 } # Check for non-default visibility if (decl ~ /G_GNUC_INTERNAL/) next # Check for presence of pointers to functions if (decl ~ /\([ \t]*\*/) next gsub (/const[ \t]+/, "", decl) split( decl, arr ) # tokenize decl = save_decl = "" void = 0 strip_variadic = 0 for(i = 1; i in arr; i++) { last = strip(tst) tst = arr[i] if (substr(tst, 1, 3) == "...") { # remove last argument if it was actually the first variadic argument if (decl ~ /: first/ && save_decl !~ /: first/) { strip_variadic = 1 if (save_decl != "") decl = save_decl " varargs: varargs" break } decl = decl " varargs: varargs" break } if( tst !~ /[,\)]/ ) continue tst = smalltalkize( strip( tst ) ) if (tst == "void" || last == "void") { void = 1 break } if (decl != "") { save_decl = decl decl = decl " " tst ": " tst continue } if (i < 5 && last == selfClassName) self = 1 if (i >= 5 || !self) decl = smalltalkFuncName ": " tst } argdecl = save_decl = "" tst = "" for(i = 1; i in arr; i++) { last = tst tst = arr[i] if( tst !~ /[,\)]/ ) continue if (i < 5 && self) argdecl = argdecl " #self" else if (substr(tst, 1, 3) == "...") { if (strip_variadic) argdecl = save_decl argdecl = argdecl " #variadic" break } else if ( index( tst, "," ) > 0 || index( tst, ")" ) > 0 ) { save_decl = argdecl argdecl = argdecl " " ctype(last, tst) } } if (creation) retType = returned(prefixClassName "*") else retType = returned(first_line[1]) if (void) argdecl = "" if (decl == "") decl = smalltalkFuncName # skip some functions that we don't have bindings for if (type[prefixClassName] == "__skip_this__" \ || prefixClassName ~ /^G.*(Func|Notify)$/ \ || prefixClassName == "GType" \ || prefixClassName == "GtkType" \ || argdecl ~ /__skip_this__/ \ || retType == "__skip_this__") next # print the declaration print "!" prefixClassName (self ? "" : " class") " methodsFor: 'C call-outs'!" if (decl == "unref") { print "free" print " (self isAbsolute and: [ self address > 0 ])" print "\tifTrue: [ self unref ]!" } if (decl == "free") { print "free" print " (self isAbsolute and: [ self address > 0 ])" print "\tifTrue: [ self primFree. self address: 0 ]!" decl = "primFree" } print decl print " ! !\n" if (decl == "getType" && !self) print "GLib registerType: " prefixClassName "!\n" } # strips garbage from string function strip( var ) { gsub( /[()\\,;*]/, "", var ) gsub( /\[[0-9]*\]/, "", var ) return var } function ctype( the_type, name ) { if (match (the_type, /\*+$/)) { name = substr (the_type, RSTART) name the_type = substr (the_type, 1, RSTART - 1) } # pointers to pointers are CObject, and pointers to functions have # a standard naming convention in Gtk+. if (name ~ /^\*\*/ || the_type ~ /Func$/) return "#cObject" pointer = ((name ~ /^\*/) || (name ~ /\[[0-9]*\]/)) res = type[the_type] if (!pointer || res == "__skip_this__") { if (res == "" || res == "__byte__") res = "#int" } else { res = ptr_type[res] if (res !~ /^#/) res = "#cObject" } return res } function returned( var ) { pointer = var ~ /\*$/ var = strip(var) res = type[var] if (!pointer || res == "__skip_this__") { if (res == "") res = "#int" } else { res = ptr_type[res] if (res == "") res = "#{" var "}" } return res } function smalltalkize( res ) { first = substr (res, 1, 1) res = tolower( substr (res, 2) ) while (j = index (res, "_")) { first = first substr(res, 1, j - 1) toupper( substr (res, j + 1, 1)) res = substr (res, j + 2) } return first res } function define_class(name) { if (name ~ /(Class|Iface)$/ || name ~ /[^A-Za-z_]/) return # Bug report from GTK+ 2.2.2. This can be dropped if it is safe. if (name == "GParam") return correct_case[tolower(name)] = name prefix = method_prefix(name) if (prefix in prefix_class) return method_regexp = method_regexp "|^" prefix prefix_class[prefix] = name self_class[prefix] = name # if object methods turn up on the wrong class (i.e. GtkUIManager on Gtk, # check prefix here... its probably wrong. } function method_prefix(name, i, ch, prev_up) { prefix = "" prev_up = 0 # Initialize so that the heuristic for consecutive uppercase # characters fires for GObject, GParam, GDBusConnection, etc. prev_notup = -10000 for (i = 1; i < length (name); i++) { ch = substr (name, i, 1) if (ch >= "A" && ch <= "Z") { if (break_word_before_uppercase(name, i, prev_up, prev_notup)) prefix = prefix "_" prev_up = i } else prev_notup = i prefix = prefix ch } # Add final character. prefix = prefix substr (name, length (name)) prefix = tolower (prefix) "_" # Hack. sub (/^g_d_bus_/, "g_dbus_", prefix) return prefix } function break_word_before_uppercase(name, cur_index, prev_up, prev_notup) { # Always break on uppercase character preceded by lowercase if (prev_up != cur_index - 1) return 1 # Never break before the first character if (prev_up == 0) return 0 # May break if there are at least three consecutive uppercase chars... if (cur_index < prev_notup + 3) return 0 # Always break two consecutive uppercase characters at the beginning ("GXyz") if (prev_notup < 0 && cur_index == 2) return 1 # ...if last char was capitalised, this is, but next isn't. # This is for things like ui_manager => UIManager amongst others. ch = substr(name, cur_index + 1, 1) if (ch < "A" || ch > "Z") return 1 return 0 } # emulate gawk match(word, REGEX, first_line) # where REGEX is /^[ \t]*([a-zA-Z][a-zA-Z0-9]*[ \t\*]+)((g[a-z]*|pango)_[a-zA-Z0-9_]*)[ \t]*(\(.*)/ function match_function_first_line(word) { if (!match (word, /^[ \t]*[a-zA-Z][a-zA-Z0-9]*[ \t\*]+(g[a-z]*|pango)_[a-zA-Z0-9_]*[ \t]*\(/)) return 0 split ("", first_line) first_line[4] = substr (word, RSTART + RLENGTH - 1) word = substr (word, 1, RSTART + RLENGTH - 2) # Remove spaces sub (/^[ \t]*/, "", word) sub (/[ \t]*$/, "", word) # Extract function name match (word, /(g[a-z]*|pango)_[a-zA-Z0-9_]*$/) first_line[1] = substr (word, 1, RSTART - 1) first_line[2] = substr (word, RSTART) # Extract package name match (first_line[2], /^(g[a-z]*|pango)_/) first_line[3] = substr (first_line[2], 1, RLENGTH - 1) return 1 } smalltalk-3.2.5/packages/gtk/example_tictactoe.st0000644000175000017500000001064112123404352017031 00000000000000"====================================================================== | | Smalltalk Gtk+ bindings examples | ======================================================================" "====================================================================== | | Copyright 2001, 2003, 2009 Free Software Foundation, Inc. | Written by Paolo Bonzini. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LESSER. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" PackageLoader fileInPackage: 'GTK'. Namespace current: GTK [ Object subclass: TicTacToe [ | table buttons window turn state count | button: i setLabel: aString [ "Note that we get a GtkLabel automagically. That's because GNU Smalltalk calls #narrow on the GtkWidget returned by gtk_bin_get_child before returning it to us." (buttons at: i) getChild setLabel: aString ] reset [ table := Array new: 9. count := 0. turn := 'X'. state := #neutral. 1 to: 9 do: [:i | self button: i setLabel: i printString] ] play: which [ state == #neutral ifFalse: [^self]. (table at: which) isNil ifTrue: [table at: which put: turn. self button: which setLabel: turn. count := count + 1. count = 9 ifTrue: [state := #draw]. self win ifTrue: [state := #win]. state == #win ifTrue: [self message: turn , ' wins!']. state == #draw ifTrue: [self message: 'It''s a draw!']. turn := turn = 'X' ifTrue: ['O'] ifFalse: ['X']] ] win [ "Functional programming frenzy :-)" ^#(#(1 2 3) #(4 5 6) #(7 8 9) #(1 4 7) #(2 5 8) #(3 6 9) #(1 5 9) #(3 5 7)) anySatisfy: [:combo | ((combo collect: [:i | table at: i]) fold: [:a :b | a = b ifTrue: [a] ifFalse: [nil]]) notNil] ] resetClicked: object data: data [ self reset ] clicked: object data: data [ self play: data ] destroy: object data: data [ Gtk mainQuit ] message: aString [ | dialog | dialog := GtkMessageDialog new: window flags: Gtk gtkDialogDestroyWithParent type: Gtk gtkMessageInfo buttons: Gtk gtkButtonsClose message: aString. dialog run; destroy ] open [ | button vbox hbox | window := GtkWindow new: Gtk gtkWindowToplevel. window setTitle: 'Tic-tac-toe'. window connectSignal: 'destroy' to: self selector: #destroy:data: userData: nil. window setBorderWidth: 10. vbox := GtkVBox new: false spacing: 0. vbox setBorderWidth: 2. window add: vbox. buttons := Array new: 9. 1 to: 7 by: 3 do: [:i | hbox := GtkHBox new: true spacing: 0. vbox packStart: hbox expand: true fill: true padding: 0. i to: i + 2 do: [:j | buttons at: j put: (button := GtkButton newWithLabel: ''). button connectSignal: 'clicked' to: self selector: #clicked:data: userData: j. hbox packStart: button expand: true fill: true padding: 0]]. button := GtkButton newWithLabel: 'Reset'. button connectSignal: 'clicked' to: self selector: #resetClicked:data: userData: nil. vbox packEnd: button expand: false fill: false padding: 0. vbox packEnd: GtkHSeparator new expand: false fill: false padding: 5. self reset. window setDefaultSize: 100 height: 130. window showAll ] ] ] Namespace current: GTK [ TicTacToe new open. Gtk main ] smalltalk-3.2.5/packages/gtk/example_tree.st0000644000175000017500000001162512123404352016014 00000000000000"====================================================================== | | Smalltalk Gtk+ bindings examples | ======================================================================" PackageLoader fileInPackage: 'GTK'. Namespace current: GTK [ Object subclass: TreeExample [ | window treeView treeModel button tree entries selection | closeClicked: aSender [ window destroy ] destroy: aSender [ Gtk mainQuit ] selectionChangedCallback: aSender [ | it i | treeView getSelection getMode = Gtk gtkSelectionSingle ifFalse: [^self]. it := GtkTreeIter type new. selection := (treeView getSelection getSelected: nil iter: it) ifTrue: [entries at: (tree getOop: it column: 0)] ifFalse: [nil]. ('Selection: ' , selection printString) printNl ] rowActivatedCallback: aSender [ 'Row activated!' printNl ] defaultExpand [ "Expand all root nodes" | it | it := GtkTreeIter type new. tree iterChildren: it parent: nil. it isNil ifTrue: [^self]. [treeView expandToPath: (tree getPath: it). tree iterNext: it] whileTrue ] open [ "Visual components" | vbox frame scroll col rend typs | window := GtkWindow new: Gtk gtkWindowToplevel. window setTitle: 'Tree Example'. window connectSignal: 'destroy' to: self selector: #destroy: userData: nil. window setBorderWidth: 10. vbox := GtkVBox new: false spacing: 9. vbox setBorderWidth: 2. window add: vbox. frame := GtkFrame new: nil. vbox packStart: frame expand: true fill: true padding: 0. scroll := GtkScrolledWindow new: nil vadjustment: nil. frame add: scroll. scroll setPolicy: Gtk gtkPolicyAutomatic vscrollbarPolicy: Gtk gtkPolicyAutomatic. treeView := GtkTreeView new. scroll add: treeView. treeView getSelection connectSignal: 'changed' to: self selector: #selectionChangedCallback: userData: nil. treeView connectSignal: 'row-activated' to: self selector: #rowActivatedCallback: userData: nil. button := GtkButton newWithLabel: 'Close'. button connectSignal: 'clicked' to: self selector: #closeClicked: userData: nil. vbox packStart: button expand: false fill: false padding: 0. "typs := (CArrayCType elementType: CIntType numberOfElements: 3) new. typs at: 0 put: (GValue typeFromName: 'gint'); at: 1 put: (GValue typeFromName: 'gchararray'); at: 2 put: (GValue typeFromName: 'gchararray'). tree := GtkTreeStore newv: 3 types: typs." tree := GtkTreeStore new: 3 varargs: {GValue gTypeInt. GValue gTypeString. GValue gTypeString}. "TreeStore" col := GtkTreeViewColumn new. treeView insertColumn: col position: -1. "-1 => append" col setTitle: 'Class'. col packStart: (rend := GtkCellRendererText new) expand: true. col addAttribute: rend attribute: 'text' column: 1. col addAttribute: rend attribute: 'foreground' column: 2. treeView setModel: tree. "Display" window setDefaultSize: 300 height: 500. window showAll ] topLevelNodes [ | cls | cls := Array streamContents: [:stream | Smalltalk allClassesDo: [:each | stream nextPut: each]]. ^cls select: [:each | each superclass isNil or: [each superclass environment ~= Smalltalk]] ] getChildNodesFor: aNode [ aNode isNil ifTrue: [^self topLevelNodes]. aNode isClass ifTrue: [^aNode subclasses select: [:each | each environment = Smalltalk]]. ^nil ] getColumnValuesFor: aNode [ ^aNode isClass ifTrue: [ {aNode name ifNil: ['']. aNode subclasses size > 1 ifTrue: ['blue'] ifFalse: ['black']}] ifFalse: [ {aNode printString. 'gray'}] ] buildNode: aNode atIter: aIter [ | nds cols lbl it n | nds := self getChildNodesFor: aNode. nds isNil ifTrue: [^self]. cols := OrderedCollection new: nds size. nds do: [:nd | cols add: nd -> (self getColumnValuesFor: nd)]. "Sort by first column" cols := cols asSortedCollection: [:a :b | (a value at: 1) <= (b value at: 1)]. cols do: [:each | n := entries size + 1. it := GtkTreeIter type new. tree append: it parent: aIter. tree setOop: it column: 0 value: n. each value doWithIndex: [:col :i | tree setOop: it column: i value: col]. entries at: n put: each key. self buildNode: each key atIter: it] ] buildTree [ entries := Dictionary new. "entries is the reverse lookup" self buildNode: nil atIter: nil ] ] ] Namespace current: GTK [ TreeExample new open buildTree defaultExpand. Gtk main ] smalltalk-3.2.5/packages/gtk/Makefile.in0000644000175000017500000006551412130455426015053 00000000000000# Makefile.in generated by automake 1.11.6 from Makefile.am. # @configure_input@ # Copyright (C) 1994, 1995, 1996, 1997, 1998, 1999, 2000, 2001, 2002, # 2003, 2004, 2005, 2006, 2007, 2008, 2009, 2010, 2011 Free Software # Foundation, Inc. # This Makefile.in is free software; the Free Software Foundation # gives unlimited permission to copy and/or distribute it, # with or without modifications, as long as this notice is preserved. # This program is distributed in the hope that it will be useful, # but WITHOUT ANY WARRANTY, to the extent permitted by law; without # even the implied warranty of MERCHANTABILITY or FITNESS FOR A # PARTICULAR PURPOSE. @SET_MAKE@ VPATH = @srcdir@ am__make_dryrun = \ { \ am__dry=no; \ case $$MAKEFLAGS in \ *\\[\ \ ]*) \ echo 'am--echo: ; @echo "AM" OK' | $(MAKE) -f - 2>/dev/null \ | grep '^AM OK$$' >/dev/null || am__dry=yes;; \ *) \ for am__flg in $$MAKEFLAGS; do \ case $$am__flg in \ *=*|--*) ;; \ *n*) am__dry=yes; break;; \ esac; \ done;; \ esac; \ test $$am__dry = yes; \ } pkgdatadir = $(datadir)/@PACKAGE@ pkgincludedir = $(includedir)/@PACKAGE@ pkglibdir = $(libdir)/@PACKAGE@ pkglibexecdir = $(libexecdir)/@PACKAGE@ am__cd = CDPATH="$${ZSH_VERSION+.}$(PATH_SEPARATOR)" && cd install_sh_DATA = $(install_sh) -c -m 644 install_sh_PROGRAM = $(install_sh) -c install_sh_SCRIPT = $(install_sh) -c INSTALL_HEADER = $(INSTALL_DATA) transform = $(program_transform_name) NORMAL_INSTALL = : PRE_INSTALL = : POST_INSTALL = : NORMAL_UNINSTALL = : PRE_UNINSTALL = : POST_UNINSTALL = : build_triplet = @build@ host_triplet = @host@ EXTRA_PROGRAMS = testplacer$(EXEEXT) sizeof$(EXEEXT) enums$(EXEEXT) noinst_PROGRAMS = enums$(EXEEXT) sizeof$(EXEEXT) subdir = packages/gtk DIST_COMMON = $(dist_noinst_HEADERS) $(srcdir)/Makefile.am \ $(srcdir)/Makefile.in ChangeLog ACLOCAL_M4 = $(top_srcdir)/aclocal.m4 am__aclocal_m4_deps = $(top_srcdir)/build-aux/bold.m4 \ $(top_srcdir)/build-aux/codeset.m4 \ $(top_srcdir)/build-aux/emacs-pkg.m4 \ $(top_srcdir)/build-aux/emacs-site-start.m4 \ $(top_srcdir)/build-aux/ext_goto.m4 \ $(top_srcdir)/build-aux/gawk.m4 $(top_srcdir)/build-aux/gcc.m4 \ $(top_srcdir)/build-aux/gl.m4 \ $(top_srcdir)/build-aux/glib-2.0.m4 \ $(top_srcdir)/build-aux/glut.m4 $(top_srcdir)/build-aux/gmp.m4 \ $(top_srcdir)/build-aux/gst-package.m4 \ $(top_srcdir)/build-aux/gtk-2.0.m4 \ $(top_srcdir)/build-aux/iconv.m4 \ $(top_srcdir)/build-aux/lib-ld.m4 \ $(top_srcdir)/build-aux/lib-link.m4 \ $(top_srcdir)/build-aux/lib-prefix.m4 \ $(top_srcdir)/build-aux/lib.m4 \ $(top_srcdir)/build-aux/libc-so-name.m4 \ $(top_srcdir)/build-aux/libtool.m4 \ $(top_srcdir)/build-aux/lightning.m4 \ $(top_srcdir)/build-aux/ln.m4 \ $(top_srcdir)/build-aux/localtime.m4 \ $(top_srcdir)/build-aux/lock.m4 \ $(top_srcdir)/build-aux/long-double.m4 \ $(top_srcdir)/build-aux/lrint.m4 \ $(top_srcdir)/build-aux/ltdl-gst.m4 \ $(top_srcdir)/build-aux/ltoptions.m4 \ $(top_srcdir)/build-aux/ltsugar.m4 \ $(top_srcdir)/build-aux/ltversion.m4 \ $(top_srcdir)/build-aux/lt~obsolete.m4 \ $(top_srcdir)/build-aux/modules.m4 \ $(top_srcdir)/build-aux/pkg.m4 $(top_srcdir)/build-aux/poll.m4 \ $(top_srcdir)/build-aux/readline.m4 \ $(top_srcdir)/build-aux/relocatable.m4 \ $(top_srcdir)/build-aux/setenv.m4 \ $(top_srcdir)/build-aux/snprintfv.m4 \ $(top_srcdir)/build-aux/sockets.m4 \ $(top_srcdir)/build-aux/sockpfaf.m4 \ $(top_srcdir)/build-aux/strtoul.m4 \ $(top_srcdir)/build-aux/sync-builtins.m4 \ $(top_srcdir)/build-aux/tcltk.m4 \ $(top_srcdir)/build-aux/version.m4 \ $(top_srcdir)/build-aux/vis-hidden.m4 \ $(top_srcdir)/build-aux/wine.m4 $(top_srcdir)/configure.ac am__configure_deps = $(am__aclocal_m4_deps) $(CONFIGURE_DEPENDENCIES) \ $(ACLOCAL_M4) mkinstalldirs = $(install_sh) -d CONFIG_HEADER = $(top_builddir)/config.h CONFIG_CLEAN_FILES = CONFIG_CLEAN_VPATH_FILES = am__vpath_adj_setup = srcdirstrip=`echo "$(srcdir)" | sed 's|.|.|g'`; am__vpath_adj = case $$p in \ $(srcdir)/*) f=`echo "$$p" | sed "s|^$$srcdirstrip/||"`;; \ *) f=$$p;; \ esac; am__strip_dir = f=`echo $$p | sed -e 's|^.*/||'`; am__install_max = 40 am__nobase_strip_setup = \ srcdirstrip=`echo "$(srcdir)" | sed 's/[].[^$$\\*|]/\\\\&/g'` am__nobase_strip = \ for p in $$list; do echo "$$p"; done | sed -e "s|$$srcdirstrip/||" am__nobase_list = $(am__nobase_strip_setup); \ for p in $$list; do echo "$$p $$p"; done | \ sed "s| $$srcdirstrip/| |;"' / .*\//!s/ .*/ ./; s,\( .*\)/[^/]*$$,\1,' | \ $(AWK) 'BEGIN { files["."] = "" } { files[$$2] = files[$$2] " " $$1; \ if (++n[$$2] == $(am__install_max)) \ { print $$2, files[$$2]; n[$$2] = 0; files[$$2] = "" } } \ END { for (dir in files) print dir, files[dir] }' am__base_list = \ sed '$$!N;$$!N;$$!N;$$!N;$$!N;$$!N;$$!N;s/\n/ /g' | \ sed '$$!N;$$!N;$$!N;$$!N;s/\n/ /g' am__uninstall_files_from_dir = { \ test -z "$$files" \ || { test ! -d "$$dir" && test ! -f "$$dir" && test ! -r "$$dir"; } \ || { echo " ( cd '$$dir' && rm -f" $$files ")"; \ $(am__cd) "$$dir" && rm -f $$files; }; \ } am__installdirs = "$(DESTDIR)$(moduleexecdir)" LTLIBRARIES = $(moduleexec_LTLIBRARIES) am__DEPENDENCIES_1 = am__DEPENDENCIES_2 = $(am__DEPENDENCIES_1) $(am__DEPENDENCIES_1) \ $(am__DEPENDENCIES_1) $(am__DEPENDENCIES_1) \ $(am__DEPENDENCIES_1) $(am__DEPENDENCIES_1) gst_gtk_la_DEPENDENCIES = $(am__DEPENDENCIES_2) dist_gst_gtk_la_OBJECTS = gst-gtk.lo placer.lo gst_gtk_la_OBJECTS = $(dist_gst_gtk_la_OBJECTS) gst_gtk_la_LINK = $(LIBTOOL) --tag=CC $(AM_LIBTOOLFLAGS) \ $(LIBTOOLFLAGS) --mode=link $(CCLD) $(AM_CFLAGS) $(CFLAGS) \ $(gst_gtk_la_LDFLAGS) $(LDFLAGS) -o $@ PROGRAMS = $(noinst_PROGRAMS) nodist_enums_OBJECTS = enums.$(OBJEXT) enums_OBJECTS = $(nodist_enums_OBJECTS) enums_LDADD = $(LDADD) nodist_sizeof_OBJECTS = sizeof.$(OBJEXT) sizeof_OBJECTS = $(nodist_sizeof_OBJECTS) sizeof_LDADD = $(LDADD) am_testplacer_OBJECTS = testplacer.$(OBJEXT) testplacer_OBJECTS = $(am_testplacer_OBJECTS) testplacer_DEPENDENCIES = $(am__DEPENDENCIES_1) $(am__DEPENDENCIES_1) SCRIPTS = $(nodist_noinst_SCRIPTS) DEFAULT_INCLUDES = -I.@am__isrc@ -I$(top_builddir) depcomp = $(SHELL) $(top_srcdir)/build-aux/depcomp am__depfiles_maybe = depfiles am__mv = mv -f COMPILE = $(CC) $(DEFS) $(DEFAULT_INCLUDES) $(INCLUDES) $(AM_CPPFLAGS) \ $(CPPFLAGS) $(AM_CFLAGS) $(CFLAGS) LTCOMPILE = $(LIBTOOL) --tag=CC $(AM_LIBTOOLFLAGS) $(LIBTOOLFLAGS) \ --mode=compile $(CC) $(DEFS) $(DEFAULT_INCLUDES) $(INCLUDES) \ $(AM_CPPFLAGS) $(CPPFLAGS) $(AM_CFLAGS) $(CFLAGS) CCLD = $(CC) LINK = $(LIBTOOL) --tag=CC $(AM_LIBTOOLFLAGS) $(LIBTOOLFLAGS) \ --mode=link $(CCLD) $(AM_CFLAGS) $(CFLAGS) $(AM_LDFLAGS) \ $(LDFLAGS) -o $@ SOURCES = $(dist_gst_gtk_la_SOURCES) $(nodist_enums_SOURCES) \ $(nodist_sizeof_SOURCES) $(testplacer_SOURCES) DIST_SOURCES = $(dist_gst_gtk_la_SOURCES) $(testplacer_SOURCES) am__can_run_installinfo = \ case $$AM_UPDATE_INFO_DIR in \ n|no|NO) false;; \ *) (install-info --version) >/dev/null 2>&1;; \ esac DATA = $(nodist_noinst_DATA) HEADERS = $(dist_noinst_HEADERS) ETAGS = etags CTAGS = ctags DISTFILES = $(DIST_COMMON) $(DIST_SOURCES) $(TEXINFOS) $(EXTRA_DIST) ACLOCAL = @ACLOCAL@ ALLOCA = @ALLOCA@ ALL_PACKAGES = @ALL_PACKAGES@ AMTAR = @AMTAR@ AR = @AR@ AS = @AS@ ATK_CFLAGS = @ATK_CFLAGS@ ATK_LIBS = @ATK_LIBS@ AUTOCONF = @AUTOCONF@ AUTOHEADER = @AUTOHEADER@ AUTOM4TE = @AUTOM4TE@ AUTOMAKE = @AUTOMAKE@ AWK = @AWK@ BLOX_IMPLEMENTATION = @BLOX_IMPLEMENTATION@ BUILT_PACKAGES = @BUILT_PACKAGES@ CAIRO_CFLAGS = @CAIRO_CFLAGS@ CAIRO_LIBS = @CAIRO_LIBS@ CC = @CC@ CCDEPMODE = @CCDEPMODE@ CFLAGS = @CFLAGS@ CPP = @CPP@ CPPFLAGS = @CPPFLAGS@ CYGPATH_W = @CYGPATH_W@ DEFS = @DEFS@ DEPDIR = @DEPDIR@ DLLTOOL = @DLLTOOL@ DSYMUTIL = @DSYMUTIL@ DUMPBIN = @DUMPBIN@ ECHO_C = @ECHO_C@ ECHO_N = @ECHO_N@ ECHO_T = @ECHO_T@ EGREP = @EGREP@ EMACS = @EMACS@ EMACSLOADPATH = @EMACSLOADPATH@ EXEEXT = @EXEEXT@ FGREP = @FGREP@ GLIB_CFLAGS = @GLIB_CFLAGS@ GLIB_GENMARSHAL = @GLIB_GENMARSHAL@ GLIB_LIBS = @GLIB_LIBS@ GLIB_MKENUMS = @GLIB_MKENUMS@ GNUTLS_CFLAGS = @GNUTLS_CFLAGS@ GNUTLS_LIBS = @GNUTLS_LIBS@ GOBJECT_QUERY = @GOBJECT_QUERY@ GPERF = @GPERF@ GREP = @GREP@ GST_RUN = @GST_RUN@ GTHREAD_CFLAGS = @GTHREAD_CFLAGS@ GTHREAD_LIBS = @GTHREAD_LIBS@ GTK_CFLAGS = @GTK_CFLAGS@ GTK_LIBS = @GTK_LIBS@ ICON = @ICON@ INCFFI = @INCFFI@ INCLTDL = @INCLTDL@ INCSIGSEGV = @INCSIGSEGV@ INCSNPRINTFV = @INCSNPRINTFV@ INCTCLTK = @INCTCLTK@ INSTALL = @INSTALL@ INSTALL_DATA = @INSTALL_DATA@ INSTALL_INFO = @INSTALL_INFO@ INSTALL_PROGRAM = @INSTALL_PROGRAM@ INSTALL_SCRIPT = @INSTALL_SCRIPT@ INSTALL_STRIP_PROGRAM = @INSTALL_STRIP_PROGRAM@ LD = @LD@ LDFLAGS = @LDFLAGS@ LEX = @LEX@ LIBADD_DL = @LIBADD_DL@ LIBC_SO_DIR = @LIBC_SO_DIR@ LIBC_SO_NAME = @LIBC_SO_NAME@ LIBFFI = @LIBFFI@ LIBFFI_CFLAGS = @LIBFFI_CFLAGS@ LIBFFI_EXECUTABLE_LDFLAGS = @LIBFFI_EXECUTABLE_LDFLAGS@ LIBFFI_LIBS = @LIBFFI_LIBS@ LIBGLUT = @LIBGLUT@ LIBGMP = @LIBGMP@ LIBGST_CFLAGS = @LIBGST_CFLAGS@ LIBICONV = @LIBICONV@ LIBLTDL = @LIBLTDL@ LIBOBJS = @LIBOBJS@ LIBOPENGL = @LIBOPENGL@ LIBREADLINE = @LIBREADLINE@ LIBS = @LIBS@ LIBSIGSEGV = @LIBSIGSEGV@ LIBSNPRINTFV = @LIBSNPRINTFV@ LIBTCLTK = @LIBTCLTK@ LIBTHREAD = @LIBTHREAD@ LIBTOOL = @LIBTOOL@ LIPO = @LIPO@ LN = @LN@ LN_S = @LN_S@ LTALLOCA = @LTALLOCA@ LTLIBICONV = @LTLIBICONV@ LTLIBOBJS = @LTLIBOBJS@ MAINTAINER = @MAINTAINER@ MAKEINFO = @MAKEINFO@ MANIFEST_TOOL = @MANIFEST_TOOL@ MKDIR_P = @MKDIR_P@ MODULES = @MODULES@ NM = @NM@ NMEDIT = @NMEDIT@ OBJC = @OBJC@ OBJCDEPMODE = @OBJCDEPMODE@ OBJCFLAGS = @OBJCFLAGS@ OBJDUMP = @OBJDUMP@ OBJEXT = @OBJEXT@ OTOOL = @OTOOL@ OTOOL64 = @OTOOL64@ PACKAGE = @PACKAGE@ PACKAGE_BUGREPORT = @PACKAGE_BUGREPORT@ PACKAGE_DLOPEN_FLAGS = @PACKAGE_DLOPEN_FLAGS@ PACKAGE_NAME = @PACKAGE_NAME@ PACKAGE_STRING = @PACKAGE_STRING@ PACKAGE_TARNAME = @PACKAGE_TARNAME@ PACKAGE_URL = @PACKAGE_URL@ PACKAGE_VERSION = @PACKAGE_VERSION@ PANGO_CFLAGS = @PANGO_CFLAGS@ PANGO_LIBS = @PANGO_LIBS@ PATH_SEPARATOR = @PATH_SEPARATOR@ PKG_CONFIG = @PKG_CONFIG@ RANLIB = @RANLIB@ RELOCATABLE = @RELOCATABLE@ RELOC_CPPFLAGS = @RELOC_CPPFLAGS@ RELOC_LDFLAGS = @RELOC_LDFLAGS@ SDL_CFLAGS = @SDL_CFLAGS@ SDL_LIBS = @SDL_LIBS@ SED = @SED@ SET_MAKE = @SET_MAKE@ SHELL = @SHELL@ SOCKET_LIBS = @SOCKET_LIBS@ STRIP = @STRIP@ SYNC_CFLAGS = @SYNC_CFLAGS@ TCLSH = @TCLSH@ TIMEOUT = @TIMEOUT@ VERSION = @VERSION@ VERSION_INFO = @VERSION_INFO@ WINDRES = @WINDRES@ WINEWRAPPER = @WINEWRAPPER@ WINEWRAPPERDEP = @WINEWRAPPERDEP@ XMKMF = @XMKMF@ XZIP = @XZIP@ X_CFLAGS = @X_CFLAGS@ X_EXTRA_LIBS = @X_EXTRA_LIBS@ X_LIBS = @X_LIBS@ X_PRE_LIBS = @X_PRE_LIBS@ YACC = @YACC@ ZIP = @ZIP@ abs_builddir = @abs_builddir@ abs_srcdir = @abs_srcdir@ abs_top_builddir = @abs_top_builddir@ abs_top_srcdir = @abs_top_srcdir@ ac_ct_AR = @ac_ct_AR@ ac_ct_CC = @ac_ct_CC@ ac_ct_DUMPBIN = @ac_ct_DUMPBIN@ am__include = @am__include@ am__leading_dot = @am__leading_dot@ am__quote = @am__quote@ am__tar = @am__tar@ am__untar = @am__untar@ bindir = @bindir@ build = @build@ build_alias = @build_alias@ build_cpu = @build_cpu@ build_os = @build_os@ build_vendor = @build_vendor@ builddir = @builddir@ datadir = @datadir@ datarootdir = @datarootdir@ docdir = @docdir@ dvidir = @dvidir@ enable_mysql_tests = @enable_mysql_tests@ exec_prefix = @exec_prefix@ host = @host@ host_alias = @host_alias@ host_cpu = @host_cpu@ host_os = @host_os@ host_vendor = @host_vendor@ htmldir = @htmldir@ imagedir = @imagedir@ includedir = @includedir@ infodir = @infodir@ install_sh = @install_sh@ libdir = @libdir@ libexecdir = @libexecdir@ lispdir = @lispdir@ lispstartdir = @lispstartdir@ localedir = @localedir@ localstatedir = @localstatedir@ mandir = @mandir@ mkdir_p = @mkdir_p@ moduledir = @moduledir@ moduleexecdir = @moduleexecdir@ oldincludedir = @oldincludedir@ pdfdir = @pdfdir@ prefix = @prefix@ program_transform_name = @program_transform_name@ psdir = @psdir@ sbindir = @sbindir@ sharedstatedir = @sharedstatedir@ srcdir = @srcdir@ subdirs = @subdirs@ sysconfdir = @sysconfdir@ target_alias = @target_alias@ top_build_prefix = @top_build_prefix@ top_builddir = @top_builddir@ top_srcdir = @top_srcdir@ CLEANFILES = $(nodist_noinst_SCRIPTS) $(nodist_noinst_HEADERS) \ $(BUILT_SOURCES) $(nodist_noinst_DATA) order LC_UNSET = LANG=C; export LANG; \ LC_COLLATE=C; export LC_COLLATE; \ LC_CTYPE=C; export LC_CTYPE; \ LC_MESSAGES=C; export LC_MESSAGES; \ LC_MONETARY=C; export LC_MONETARY; \ LC_NUMERIC=C; export LC_NUMERIC; \ LC_TIME=C; export LC_TIME EXTRA_DIST = cpp.awk structs.awk funcs.awk mk_enums.awk mk_sizeof.awk mkorder.awk gst_module_ldflags = -rpath $(moduleexecdir) -release $(VERSION) -module \ -no-undefined -export-symbols-regex gst_initModule ALL_LIBS = $(GLIB_LIBS) $(GTK_LIBS) $(PANGO_LIBS) $(ATK_LIBS) $(GTHREAD_LIBS) \ $(CAIRO_LIBS) moduleexec_LTLIBRARIES = gst-gtk.la gst_gtk_la_LDFLAGS = $(gst_module_ldflags) gst_gtk_la_LIBADD = $(ALL_LIBS) dist_gst_gtk_la_SOURCES = gst-gtk.c placer.c BUILT_SOURCES = libs.def enums.c sizeof.c dist_noinst_HEADERS = placer.h testplacer_SOURCES = testplacer.c testplacer_LDADD = $(GLIB_LIBS) $(GTK_LIBS) AM_CPPFLAGS = \ -I$(top_srcdir)/libgst \ -I$(top_srcdir)/lib-src \ -I$(top_srcdir)/libltdl AM_CFLAGS = $(GLIB_CFLAGS) $(GTK_CFLAGS) $(PANGO_CFLAGS) $(ATK_CFLAGS) GTK_FILES = \ glib-object.h gdk/gdk.h \ gdk-pixbuf/gdk-pixbuf.h gtk/gtk.h atk/atk.h pango/pango.h # We don't want to include all of GLib for obvious reasons... GLIB_FILES = \ glib/goption.h glib/gdate.h glib/gmain.h LOCAL_FILES = $(srcdir)/placer.h nodist_noinst_DATA = Structs.st Funcs.st Enums.st nodist_noinst_SCRIPTS = cpp structs funcs mk_sizeof mk_enums nodist_enums_SOURCES = enums.c nodist_sizeof_SOURCES = sizeof.c all: $(BUILT_SOURCES) $(MAKE) $(AM_MAKEFLAGS) all-am .SUFFIXES: .SUFFIXES: .c .lo .o .obj $(srcdir)/Makefile.in: $(srcdir)/Makefile.am $(am__configure_deps) @for dep in $?; do \ case '$(am__configure_deps)' in \ *$$dep*) \ ( cd $(top_builddir) && $(MAKE) $(AM_MAKEFLAGS) am--refresh ) \ && { if test -f $@; then exit 0; else break; fi; }; \ exit 1;; \ esac; \ done; \ echo ' cd $(top_srcdir) && $(AUTOMAKE) --gnu packages/gtk/Makefile'; \ $(am__cd) $(top_srcdir) && \ $(AUTOMAKE) --gnu packages/gtk/Makefile .PRECIOUS: Makefile Makefile: $(srcdir)/Makefile.in $(top_builddir)/config.status @case '$?' in \ *config.status*) \ cd $(top_builddir) && $(MAKE) $(AM_MAKEFLAGS) am--refresh;; \ *) \ echo ' cd $(top_builddir) && $(SHELL) ./config.status $(subdir)/$@ $(am__depfiles_maybe)'; \ cd $(top_builddir) && $(SHELL) ./config.status $(subdir)/$@ $(am__depfiles_maybe);; \ esac; $(top_builddir)/config.status: $(top_srcdir)/configure $(CONFIG_STATUS_DEPENDENCIES) cd $(top_builddir) && $(MAKE) $(AM_MAKEFLAGS) am--refresh $(top_srcdir)/configure: $(am__configure_deps) cd $(top_builddir) && $(MAKE) $(AM_MAKEFLAGS) am--refresh $(ACLOCAL_M4): $(am__aclocal_m4_deps) cd $(top_builddir) && $(MAKE) $(AM_MAKEFLAGS) am--refresh $(am__aclocal_m4_deps): install-moduleexecLTLIBRARIES: $(moduleexec_LTLIBRARIES) @$(NORMAL_INSTALL) @list='$(moduleexec_LTLIBRARIES)'; test -n "$(moduleexecdir)" || list=; \ list2=; for p in $$list; do \ if test -f $$p; then \ list2="$$list2 $$p"; \ else :; fi; \ done; \ test -z "$$list2" || { \ echo " $(MKDIR_P) '$(DESTDIR)$(moduleexecdir)'"; \ $(MKDIR_P) "$(DESTDIR)$(moduleexecdir)" || exit 1; \ echo " $(LIBTOOL) $(AM_LIBTOOLFLAGS) $(LIBTOOLFLAGS) --mode=install $(INSTALL) $(INSTALL_STRIP_FLAG) $$list2 '$(DESTDIR)$(moduleexecdir)'"; \ $(LIBTOOL) $(AM_LIBTOOLFLAGS) $(LIBTOOLFLAGS) --mode=install $(INSTALL) $(INSTALL_STRIP_FLAG) $$list2 "$(DESTDIR)$(moduleexecdir)"; \ } uninstall-moduleexecLTLIBRARIES: @$(NORMAL_UNINSTALL) @list='$(moduleexec_LTLIBRARIES)'; test -n "$(moduleexecdir)" || list=; \ for p in $$list; do \ $(am__strip_dir) \ echo " $(LIBTOOL) $(AM_LIBTOOLFLAGS) $(LIBTOOLFLAGS) --mode=uninstall rm -f '$(DESTDIR)$(moduleexecdir)/$$f'"; \ $(LIBTOOL) $(AM_LIBTOOLFLAGS) $(LIBTOOLFLAGS) --mode=uninstall rm -f "$(DESTDIR)$(moduleexecdir)/$$f"; \ done clean-moduleexecLTLIBRARIES: -test -z "$(moduleexec_LTLIBRARIES)" || rm -f $(moduleexec_LTLIBRARIES) @list='$(moduleexec_LTLIBRARIES)'; for p in $$list; do \ dir="`echo $$p | sed -e 's|/[^/]*$$||'`"; \ test "$$dir" != "$$p" || dir=.; \ echo "rm -f \"$${dir}/so_locations\""; \ rm -f "$${dir}/so_locations"; \ done gst-gtk.la: $(gst_gtk_la_OBJECTS) $(gst_gtk_la_DEPENDENCIES) $(EXTRA_gst_gtk_la_DEPENDENCIES) $(gst_gtk_la_LINK) -rpath $(moduleexecdir) $(gst_gtk_la_OBJECTS) $(gst_gtk_la_LIBADD) $(LIBS) clean-noinstPROGRAMS: @list='$(noinst_PROGRAMS)'; test -n "$$list" || exit 0; \ echo " rm -f" $$list; \ rm -f $$list || exit $$?; \ test -n "$(EXEEXT)" || exit 0; \ list=`for p in $$list; do echo "$$p"; done | sed 's/$(EXEEXT)$$//'`; \ echo " rm -f" $$list; \ rm -f $$list enums$(EXEEXT): $(enums_OBJECTS) $(enums_DEPENDENCIES) $(EXTRA_enums_DEPENDENCIES) @rm -f enums$(EXEEXT) $(LINK) $(enums_OBJECTS) $(enums_LDADD) $(LIBS) sizeof$(EXEEXT): $(sizeof_OBJECTS) $(sizeof_DEPENDENCIES) $(EXTRA_sizeof_DEPENDENCIES) @rm -f sizeof$(EXEEXT) $(LINK) $(sizeof_OBJECTS) $(sizeof_LDADD) $(LIBS) testplacer$(EXEEXT): $(testplacer_OBJECTS) $(testplacer_DEPENDENCIES) $(EXTRA_testplacer_DEPENDENCIES) @rm -f testplacer$(EXEEXT) $(LINK) $(testplacer_OBJECTS) $(testplacer_LDADD) $(LIBS) mostlyclean-compile: -rm -f *.$(OBJEXT) distclean-compile: -rm -f *.tab.c @AMDEP_TRUE@@am__include@ @am__quote@./$(DEPDIR)/enums.Po@am__quote@ @AMDEP_TRUE@@am__include@ @am__quote@./$(DEPDIR)/gst-gtk.Plo@am__quote@ @AMDEP_TRUE@@am__include@ @am__quote@./$(DEPDIR)/placer.Plo@am__quote@ @AMDEP_TRUE@@am__include@ @am__quote@./$(DEPDIR)/sizeof.Po@am__quote@ @AMDEP_TRUE@@am__include@ @am__quote@./$(DEPDIR)/testplacer.Po@am__quote@ .c.o: @am__fastdepCC_TRUE@ $(COMPILE) -MT $@ -MD -MP -MF $(DEPDIR)/$*.Tpo -c -o $@ $< @am__fastdepCC_TRUE@ $(am__mv) $(DEPDIR)/$*.Tpo $(DEPDIR)/$*.Po @AMDEP_TRUE@@am__fastdepCC_FALSE@ source='$<' object='$@' libtool=no @AMDEPBACKSLASH@ @AMDEP_TRUE@@am__fastdepCC_FALSE@ DEPDIR=$(DEPDIR) $(CCDEPMODE) $(depcomp) @AMDEPBACKSLASH@ @am__fastdepCC_FALSE@ $(COMPILE) -c $< .c.obj: @am__fastdepCC_TRUE@ $(COMPILE) -MT $@ -MD -MP -MF $(DEPDIR)/$*.Tpo -c -o $@ `$(CYGPATH_W) '$<'` @am__fastdepCC_TRUE@ $(am__mv) $(DEPDIR)/$*.Tpo $(DEPDIR)/$*.Po @AMDEP_TRUE@@am__fastdepCC_FALSE@ source='$<' object='$@' libtool=no @AMDEPBACKSLASH@ @AMDEP_TRUE@@am__fastdepCC_FALSE@ DEPDIR=$(DEPDIR) $(CCDEPMODE) $(depcomp) @AMDEPBACKSLASH@ @am__fastdepCC_FALSE@ $(COMPILE) -c `$(CYGPATH_W) '$<'` .c.lo: @am__fastdepCC_TRUE@ $(LTCOMPILE) -MT $@ -MD -MP -MF $(DEPDIR)/$*.Tpo -c -o $@ $< @am__fastdepCC_TRUE@ $(am__mv) $(DEPDIR)/$*.Tpo $(DEPDIR)/$*.Plo @AMDEP_TRUE@@am__fastdepCC_FALSE@ source='$<' object='$@' libtool=yes @AMDEPBACKSLASH@ @AMDEP_TRUE@@am__fastdepCC_FALSE@ DEPDIR=$(DEPDIR) $(CCDEPMODE) $(depcomp) @AMDEPBACKSLASH@ @am__fastdepCC_FALSE@ $(LTCOMPILE) -c -o $@ $< mostlyclean-libtool: -rm -f *.lo clean-libtool: -rm -rf .libs _libs ID: $(HEADERS) $(SOURCES) $(LISP) $(TAGS_FILES) list='$(SOURCES) $(HEADERS) $(LISP) $(TAGS_FILES)'; \ unique=`for i in $$list; do \ if test -f "$$i"; then echo $$i; else echo $(srcdir)/$$i; fi; \ done | \ $(AWK) '{ files[$$0] = 1; nonempty = 1; } \ END { if (nonempty) { for (i in files) print i; }; }'`; \ mkid -fID $$unique tags: TAGS TAGS: $(HEADERS) $(SOURCES) $(TAGS_DEPENDENCIES) \ $(TAGS_FILES) $(LISP) set x; \ here=`pwd`; \ list='$(SOURCES) $(HEADERS) $(LISP) $(TAGS_FILES)'; \ unique=`for i in $$list; do \ if test -f "$$i"; then echo $$i; else echo $(srcdir)/$$i; fi; \ done | \ $(AWK) '{ files[$$0] = 1; nonempty = 1; } \ END { if (nonempty) { for (i in files) print i; }; }'`; \ shift; \ if test -z "$(ETAGS_ARGS)$$*$$unique"; then :; else \ test -n "$$unique" || unique=$$empty_fix; \ if test $$# -gt 0; then \ $(ETAGS) $(ETAGSFLAGS) $(AM_ETAGSFLAGS) $(ETAGS_ARGS) \ "$$@" $$unique; \ else \ $(ETAGS) $(ETAGSFLAGS) $(AM_ETAGSFLAGS) $(ETAGS_ARGS) \ $$unique; \ fi; \ fi ctags: CTAGS CTAGS: $(HEADERS) $(SOURCES) $(TAGS_DEPENDENCIES) \ $(TAGS_FILES) $(LISP) list='$(SOURCES) $(HEADERS) $(LISP) $(TAGS_FILES)'; \ unique=`for i in $$list; do \ if test -f "$$i"; then echo $$i; else echo $(srcdir)/$$i; fi; \ done | \ $(AWK) '{ files[$$0] = 1; nonempty = 1; } \ END { if (nonempty) { for (i in files) print i; }; }'`; \ test -z "$(CTAGS_ARGS)$$unique" \ || $(CTAGS) $(CTAGSFLAGS) $(AM_CTAGSFLAGS) $(CTAGS_ARGS) \ $$unique GTAGS: here=`$(am__cd) $(top_builddir) && pwd` \ && $(am__cd) $(top_srcdir) \ && gtags -i $(GTAGS_ARGS) "$$here" distclean-tags: -rm -f TAGS ID GTAGS GRTAGS GSYMS GPATH tags distdir: $(DISTFILES) @srcdirstrip=`echo "$(srcdir)" | sed 's/[].[^$$\\*]/\\\\&/g'`; \ topsrcdirstrip=`echo "$(top_srcdir)" | sed 's/[].[^$$\\*]/\\\\&/g'`; \ list='$(DISTFILES)'; \ dist_files=`for file in $$list; do echo $$file; done | \ sed -e "s|^$$srcdirstrip/||;t" \ -e "s|^$$topsrcdirstrip/|$(top_builddir)/|;t"`; \ case $$dist_files in \ */*) $(MKDIR_P) `echo "$$dist_files" | \ sed '/\//!d;s|^|$(distdir)/|;s,/[^/]*$$,,' | \ sort -u` ;; \ esac; \ for file in $$dist_files; do \ if test -f $$file || test -d $$file; then d=.; else d=$(srcdir); fi; \ if test -d $$d/$$file; then \ dir=`echo "/$$file" | sed -e 's,/[^/]*$$,,'`; \ if test -d "$(distdir)/$$file"; then \ find "$(distdir)/$$file" -type d ! -perm -700 -exec chmod u+rwx {} \;; \ fi; \ if test -d $(srcdir)/$$file && test $$d != $(srcdir); then \ cp -fpR $(srcdir)/$$file "$(distdir)$$dir" || exit 1; \ find "$(distdir)/$$file" -type d ! -perm -700 -exec chmod u+rwx {} \;; \ fi; \ cp -fpR $$d/$$file "$(distdir)$$dir" || exit 1; \ else \ test -f "$(distdir)/$$file" \ || cp -p $$d/$$file "$(distdir)/$$file" \ || exit 1; \ fi; \ done check-am: all-am check: $(BUILT_SOURCES) $(MAKE) $(AM_MAKEFLAGS) check-am all-am: Makefile $(LTLIBRARIES) $(PROGRAMS) $(SCRIPTS) $(DATA) \ $(HEADERS) installdirs: for dir in "$(DESTDIR)$(moduleexecdir)"; do \ test -z "$$dir" || $(MKDIR_P) "$$dir"; \ done install: $(BUILT_SOURCES) $(MAKE) $(AM_MAKEFLAGS) install-am install-exec: install-exec-am install-data: install-data-am uninstall: uninstall-am install-am: all-am @$(MAKE) $(AM_MAKEFLAGS) install-exec-am install-data-am installcheck: installcheck-am install-strip: if test -z '$(STRIP)'; then \ $(MAKE) $(AM_MAKEFLAGS) INSTALL_PROGRAM="$(INSTALL_STRIP_PROGRAM)" \ install_sh_PROGRAM="$(INSTALL_STRIP_PROGRAM)" INSTALL_STRIP_FLAG=-s \ install; \ else \ $(MAKE) $(AM_MAKEFLAGS) INSTALL_PROGRAM="$(INSTALL_STRIP_PROGRAM)" \ install_sh_PROGRAM="$(INSTALL_STRIP_PROGRAM)" INSTALL_STRIP_FLAG=-s \ "INSTALL_PROGRAM_ENV=STRIPPROG='$(STRIP)'" install; \ fi mostlyclean-generic: clean-generic: -test -z "$(CLEANFILES)" || rm -f $(CLEANFILES) distclean-generic: -test -z "$(CONFIG_CLEAN_FILES)" || rm -f $(CONFIG_CLEAN_FILES) -test . = "$(srcdir)" || test -z "$(CONFIG_CLEAN_VPATH_FILES)" || rm -f $(CONFIG_CLEAN_VPATH_FILES) maintainer-clean-generic: @echo "This command is intended for maintainers to use" @echo "it deletes files that may require special tools to rebuild." -test -z "$(BUILT_SOURCES)" || rm -f $(BUILT_SOURCES) clean: clean-am clean-am: clean-generic clean-libtool clean-moduleexecLTLIBRARIES \ clean-noinstPROGRAMS mostlyclean-am distclean: distclean-am -rm -rf ./$(DEPDIR) -rm -f Makefile distclean-am: clean-am distclean-compile distclean-generic \ distclean-tags dvi: dvi-am dvi-am: html: html-am html-am: info: info-am info-am: install-data-am: install-dvi: install-dvi-am install-dvi-am: install-exec-am: install-moduleexecLTLIBRARIES install-html: install-html-am install-html-am: install-info: install-info-am install-info-am: install-man: install-pdf: install-pdf-am install-pdf-am: install-ps: install-ps-am install-ps-am: installcheck-am: maintainer-clean: maintainer-clean-am -rm -rf ./$(DEPDIR) -rm -f Makefile maintainer-clean-am: distclean-am maintainer-clean-generic mostlyclean: mostlyclean-am mostlyclean-am: mostlyclean-compile mostlyclean-generic \ mostlyclean-libtool pdf: pdf-am pdf-am: ps: ps-am ps-am: uninstall-am: uninstall-moduleexecLTLIBRARIES .MAKE: all check install install-am install-strip .PHONY: CTAGS GTAGS all all-am check check-am clean clean-generic \ clean-libtool clean-moduleexecLTLIBRARIES clean-noinstPROGRAMS \ ctags distclean distclean-compile distclean-generic \ distclean-libtool distclean-tags distdir dvi dvi-am html \ html-am info info-am install install-am install-data \ install-data-am install-dvi install-dvi-am install-exec \ install-exec-am install-html install-html-am install-info \ install-info-am install-man install-moduleexecLTLIBRARIES \ install-pdf install-pdf-am install-ps install-ps-am \ install-strip installcheck installcheck-am installdirs \ maintainer-clean maintainer-clean-generic mostlyclean \ mostlyclean-compile mostlyclean-generic mostlyclean-libtool \ pdf pdf-am ps ps-am tags uninstall uninstall-am \ uninstall-moduleexecLTLIBRARIES # Rules to build the bindings from the GTK+ header files follow... %: %.awk @case "$(AWK)" in \ */*) AWK="$(AWK)" ;; \ *) \ IFS=":"; \ for i in $$PATH; do \ test -f $$i/$(AWK) && AWK="$$i/$(AWK)" && break; \ done ;; \ esac; \ echo "$(SED) -e \"1s,@AWK\@,$$AWK,\" < $< > $@"; \ $(SED) -e "1s,@AWK\@,$$AWK," < $< > $@ chmod +x $@ cpp: $(srcdir)/cpp.awk structs: $(srcdir)/structs.awk funcs: $(srcdir)/funcs.awk mk_enums: $(srcdir)/mk_enums.awk mk_sizeof: $(srcdir)/mk_sizeof.awk # ------------------------------------- libs.def: Makefile for i in $(ALL_LIBS); do \ case $$i in \ -L*) \ j=`echo $$i | sed 's,^-L,,'` ; \ echo "_gst_vm_proxy->dlAddSearchDir(\"$$j\");" ;; \ -lG*|-lg*|-lATK*|-latk*|-lPango*|-lpango*) \ j=`echo $$i | sed 's,^-l,lib,'` ; \ echo "_gst_vm_proxy->dlOpen(\"$$j\", false);" ;; \ *) ;; \ esac; \ done | sort -u > libs.def Structs.st: structs sizeof$(EXEEXT) cpp order $(LC_UNSET); xargs ./cpp < order | ./structs > Structs.st $(LC_UNSET); ./sizeof$(EXEEXT) >> Structs.st Enums.st: enums$(EXEEXT) $(LC_UNSET); ./enums$(EXEEXT) > Enums.st Funcs.st: funcs cpp order $(LC_UNSET); xargs ./cpp < order | ./funcs > Funcs.st sizeof.c: mk_sizeof cpp order $(LC_UNSET); xargs ./cpp < order | ./mk_sizeof > sizeof.c enums.c: mk_enums cpp order $(LC_UNSET); xargs ./cpp < order | ./mk_enums > enums.c order: mkorder.awk Makefile $(LOCAL_FILES) $(AWK) \ -vPKG_CONFIG='$(PKG_CONFIG)' \ -v_prefixes='g atk pango' \ -v_libs="gobject-2.0 gdk-2.0 gdk-pixbuf-2.0 pango gtk+-2.0 atk" \ -v_files="$(GTK_FILES) $(LOCAL_FILES)" -f $(srcdir)/mkorder.awk \ | while read i; do \ case "$$i" in \ error:*) \ echo "$$i" >&2; exit 1;; \ */gobject/*) \ echo "$$i" ;; \ */glib/*) \ case " $(GLIB_FILES) " in \ *" glib/`basename $$i` "*) echo "$$i" ;; \ *) ;; \ esac ;; \ *) \ echo "$$i" ;; \ esac; \ done > order # Tell versions [3.59,3.63) of GNU make to not export all variables. # Otherwise a system limit (for SysV at least) may be exceeded. .NOEXPORT: smalltalk-3.2.5/packages/gtk/example_aspectframe.st0000644000175000017500000000441712123404352017350 00000000000000"====================================================================== | | Smalltalk Gtk+ bindings examples | ======================================================================" "====================================================================== | | Copyright 2001, 2003, 2009 Free Software Foundation, Inc. | Written by Paolo Bonzini. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LESSER. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" PackageLoader fileInPackage: 'GTK'. Namespace current: GTK [ Object subclass: AspectFrameExample [ destroy: object data: data [ Gtk mainQuit ] open [ | window aspectFrame drawingArea | window := GtkWindow new: Gtk gtkWindowToplevel. window connectSignal: 'destroy' to: self selector: #destroy:data: userData: nil. window setTitle: 'Aspect Frame'. window setBorderWidth: 10. aspectFrame := GtkAspectFrame new: '2x1' xalign: 0.5 yalign: 0.5 ratio: 2 obeyChild: false. window add: aspectFrame. "We ask for a 200x200 drawing area, but we are forcing a 2x1 ratio so the AspectFrame will give us a 200x100 area." drawingArea := GtkDrawingArea new. drawingArea setSizeRequest: 200 height: 200. aspectFrame add: drawingArea. drawingArea show. aspectFrame show. window show ] ] ] Namespace current: GTK [ AspectFrameExample new open. Gtk main ] smalltalk-3.2.5/packages/gtk/mk_sizeof.awk0000644000175000017500000000506512123404352015465 00000000000000#! @AWK@ -f ####################################################################### # # Gtk wrapper creation script (sizeof methods) # ######################################################################## ####################################################################### # # Copyright 2004 Free Software Foundation, Inc. # Written by Mike Anderson and Paolo Bonzini # # This file is part of the GNU Smalltalk class library. # # The GNU Smalltalk class library is free software; you can redistribute it # and/or modify it under the terms of the GNU Lesser General Public License # as published by the Free Software Foundation; either version 2.1, or (at # your option) any later version. # # The GNU Smalltalk class library is distributed in the hope that it will be # useful, but WITHOUT ANY WARRANTY; without even the implied warranty of # MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser # General Public License for more details. # # You should have received a copy of the GNU Lesser General Public License # along with the GNU Smalltalk class library; see the file COPYING.LESSER. # If not, write to the Free Software Foundation, 59 Temple Place - Suite # 330, Boston, MA 02110-1301, USA. # ######################################################################## #! @AWK@ -f BEGIN { print "/* Automatically generated, do not edit! */" print "#define GDK_PIXBUF_ENABLE_BACKEND 1" print "#include " print "#include " print "#include " print "#include " print "#include " print "#include " print "#include " print "#include " print "#include \"placer.h\"" print "\nint main () {" } { gsub(/[_;]/, "", $0) is_typedef = ($1 == "typedef") is_struct = $(1+is_typedef) == "struct" && (is_typedef || NF == 2 || $3 == "{") if (is_struct) { src = $(2+is_typedef) dest = $(3+is_typedef) is_vtable_decl = src ~ /(Class|Iface)$/ is_g_name = src ~ /^(G|Pango|Atk)/ is_pointer = dest ~ /\*/ } } is_typedef && is_struct && is_g_name && !is_vtable_decl && !is_pointer { typedef_names[dest] = src } !is_typedef && is_struct && !is_pointer && dest !~ /^[a-z_]/ { struct_name[src] = "" } END { for (i in typedef_names) { # Only do complete types if (typedef_names[i] in struct_name) print "printf(\"!%s class methodsFor: 'accessing'!" \ "\\n\\nsizeof\\n ^%u\\n! !\\n\\n\", " \ "\"" i "\", sizeof(" i "));" } print " exit (0);" print "}" } smalltalk-3.2.5/packages/gtk/GtkImpl.st0000644000175000017500000005342612130343734014722 00000000000000GtkTextBuffer extend [ insertAtEnd: aString [ self insert: self getEndIter text: aString ] ] GtkAlignment class extend [ new [ ^self new: 0 yalign: 0 xscale: 1 yscale: 1 ] ] GObject class extend [ new [ ^self new: self getType varargs: #(nil) ] ] GList extend [ do: aOneArgBlock [ | iter | iter := self. [ iter isNull not ] whileTrue: [ aOneArgBlock value: iter data value. iter := iter next value ] ] ] GdkDrawable extend [ withContextDo: aBlock [ "Execute aBlock passing a valid Cairo context for the window. The context is invalidated after aBlock returns." | context | [ aBlock value: (context := Cairo.CairoContext context: self cairoCreate) ] ensure: [ context isNil ifFalse: [ context release ] ] ] ] GtkWidget extend [ getSizeRequest [ "Answer the size the widget has requisitioned." | requisition | requisition := GTK.GtkRequisition new. self sizeRequest: requisition. ^requisition asPoint ] ] GtkMessageDialog class extend [ new: parent flags: flags type: type buttons: buttons message: message [ ^self new: parent flags: flags type: type buttons: buttons messageFormat: '%s' varargs: {message} ] new: parent flags: flags type: type buttons: buttons message: message tip: tip [ ^self newWithMarkup: parent flags: flags type: type buttons: buttons messageFormat: '%s %s' varargs: {message. tip} ] newWithMarkup: parent flags: flags type: type buttons: buttons message: message [ ^self newWithMarkup: parent flags: flags type: type buttons: buttons messageFormat: (message copyReplaceAll: '%' with: '%%') varargs: #() ] ] GtkRequisition class extend [ fromPoint: point [ | ba | ba := (CShortType arrayType: 2) new. ba at: 0 put: point x. ba at: 1 put: point y. ^(ba castTo: self type) addToBeFinalized; yourself ] ] GtkRequisition extend [ x [ | ba | ba := self castTo: (CShortType arrayType: 4). ^ba at: 0 ] y [ | ba | ba := self castTo: (CShortType arrayType: 4). ^ba at: 1 ] asPoint [ ^ {self width value. self height value} ] ] GdkRectangle class extend [ fromRectangle: rect [ | ba | ba := (CShortType arrayType: 4) new. ba at: 0 put: rect left. ba at: 1 put: rect top. ba at: 2 put: rect width. ba at: 3 put: rect height. ^(ba castTo: self type) addToBeFinalized; yourself ] ] GdkRectangle extend [ left [ | ba | ba := self castTo: (CShortType arrayType: 4). ^ba at: 0 ] top [ | ba | ba := self castTo: (CShortType arrayType: 4). ^ba at: 1 ] right [ | ba | ba := self castTo: (CShortType arrayType: 4). ^(ba at: 0) + (ba at: 2) ] bottom [ | ba | ba := self castTo: (CShortType arrayType: 4). ^(ba at: 1) + (ba at: 3) ] width [ | ba | ba := self castTo: (CShortType arrayType: 4). ^ba at: 2 ] height [ | ba | ba := self castTo: (CShortType arrayType: 4). ^ba at: 3 ] origin [ | ba | ba := self castTo: (CShortType arrayType: 4). ^(ba at: 0) @ (ba at: 1) ] extent [ | ba | ba := self castTo: (CShortType arrayType: 4). ^(ba at: 2) @ (ba at: 3) ] corner [ | ba | ba := self castTo: (CShortType arrayType: 4). ^((ba at: 0) + (ba at: 2)) @ ((ba at: 1) + (ba at: 3)) ] asRectangle [ | ba | ba := self castTo: (CShortType arrayType: 4). ^(ba at: 0) @ (ba at: 1) extent: (ba at: 2) @ (ba at: 3) ] ] GtkTreeIter class extend [ Prototype := nil. gcNew [ ^self type gcNew ] new [ Prototype isNil ifTrue: [ Prototype := self type gcNew ]. ^Prototype copy addToBeFinalized; yourself ] ] GtkTextIter class extend [ Prototype := nil. gcNew [ ^self type gcNew ] new [ Prototype isNil ifTrue: [ Prototype := self type gcNew ]. ^Prototype copy addToBeFinalized; yourself ] ] GtkTreeModel extend [ getIter: path [ | iter | iter := GTK.GtkTreeIter new. ^(self getIter: iter path: path) ifTrue: [iter] ifFalse: [nil] ] getIterFirst [ | iter | iter := GTK.GtkTreeIter new. self getIterFirst: iter. ^iter ] iterChildren: parent [ | iter | iter := GTK.GtkTreeIter new. self iterChildren: iter parent: parent. ^iter ] iterNthChild: parent n: n [ | iter | iter := GTK.GtkTreeIter new. self iterNthChild: iter parent: parent n: n. ^iter ] iterParent: child [ | iter | iter := GTK.GtkTreeIter new. self iterParent: iter child: child. ^iter ] ] GtkTreeSelection extend [ getSelected [ | has iter | iter := GTK.GtkTreeIter new. has := self getSelected: nil iter: iter. ^has ifTrue: [iter] ifFalse: [nil] ] ] GtkListStore extend [ insert: anInteger [ | iter | iter := GTK.GtkTreeIter new. self insert: iter position: anInteger. ^iter ] insertBefore: sibling [ | iter | iter := GTK.GtkTreeIter new. self insertBefore: iter sibling: sibling. ^iter ] insertAfter: sibling [ | iter | iter := GTK.GtkTreeIter new. self insertAfter: iter sibling: sibling. ^iter ] prepend [ | iter | iter := GTK.GtkTreeIter new. self prepend: iter. ^iter ] append [ | iter | iter := GTK.GtkTreeIter new. self append: iter. ^iter ] ] GtkTextBuffer extend [ setText: aString [ "Set my contents" self setText: aString len: aString size ] insertAtCursor: aString [ "Insert aString at the curser." self insertAtCursor: aString len: aString size ] getBounds [ "Answer my entire contents." | start end | start := GTK.GtkTextIter new. end := GTK.GtkTextIter new. self getBounds: start end: end. ^ {start. end} ] getIterAtMark: mark [ "Answer an iterator for mark" | iter | iter := GTK.GtkTextIter new. self getIterAtMark: iter mark: mark. ^iter ] getSelectionBounds [ "Answer my selection bounds" | start end | start := GTK.GtkTextIter new. end := GTK.GtkTextIter new. self getSelectionBounds: start end: end. ^ {start. end} ] getIterAtLine: line [ "Answer an iterator at the beginning of line." | result | result := GTK.GtkTextIter new. self getIterAtLine: result lineNumber: line. ^result ] getIterAtLineOffset: lineNumber charOffset: charOffset [ "Answer an iterator at offset in me." | result | result := GTK.GtkTextIter new. self getIterAtLineOffset: result lineNumber: lineNumber charOffset: charOffset. ^result ] getStartIter [ "Answer a start iterator." | result | result := GTK.GtkTextIter new. self getStartIter: result. ^result ] getEndIter [ "Answer an end iterator" | result | result := GTK.GtkTextIter new. self getEndIter: result. ^result ] insert: iter text: aString [ "Insert aString at the insertion point." self insert: iter text: aString len: aString size ] ] Gtk class extend [ | loop | mainQuit [ loop quit ] main [ "Main loop implementation. Same as gtk_main, but it splits g_main_context_run in two threads so that Smalltalk processes run. Like gtk_main, it is ended with Gtk>>#mainQuit." | sem newLoop context | sem := Semaphore new. newLoop := GTK.Gtk main: sem. newLoop isNil ifTrue: [ ^self ]. loop := newLoop. context := loop getContext. [ [sem wait. context iterate. loop isRunning] whileTrue] ensure: [loop unref] ] ] GtkAccelGroup class extend [ acceleratorParse: accelerator [ | cAccKey cAccMod | cAccKey := CInt gcValue: 0. cAccMod := CInt gcValue: 0. GTK.Gtk acceleratorParse: accelerator acceleratorKey: cAccKey acceleratorMods: cAccMod. ^ {cAccKey value. cAccMod value} ] acceleratorGroup: aGtkAccelGroup accelerator: aString path: aPathString [ | result | result := self acceleratorParse: aString. GTK.GtkAccelMap addEntry: aPathString accelKey: result first accelMods: result second ] ] GtkAccelGroup extend [ append: anArray [ anArray do: [ :each | self class acceleratorGroup: self accelerator: each first path: each second ] ] ] GtkButton class extend [ label: aString onPressedSend: aSymbol to: anObject [ ^ (GTK.GtkButton newWithLabel: aString) connectSignal: 'pressed' to: anObject selector: aSymbol userData: nil; yourself ] ] GTK.GtkDialog extend [ run [ | signals sema answer modal destroyed | sema := Semaphore new. modal := self getModal. self setModal: true. signals := { self connectSignal: 'response' to: [ :dialog :integer | answer := integer. sema signal ] selector: #value:value:. self connectSignal: 'unmap' to: sema selector: #signal. self connectSignal: 'delete_event' to: [ answer := Gtk gtkResponseDeleteEvent. sema signal. true ] selector: #value. self connectSignal: 'destroy' to: [ destroyed := true ] selector: #value }. self show. sema wait. destroyed ifFalse: [ self setModal: modal. signals do: [ :each | self disconnectSignal: each ] ]. ^answer ] ] GTK.GtkFileChooserDialog class extend [ for: aGtkFileChooserAction title: aString parent: aGtkWidget button: aGtkStock [ ^ self new: aString parent: aGtkWidget action: aGtkFileChooserAction varargs: {GTK.Gtk gtkStockCancel. GTK.Gtk gtkResponseCancel. aGtkStock. GTK.Gtk gtkResponseAccept. nil} ] save: aString parent: aGtkWidget [ ^ self for: GTK.Gtk gtkFileChooserActionSave title: aString parent: aGtkWidget button: GTK.Gtk gtkStockSave ] load: aString parent: aGtkWidget [ ^ self for: GTK.Gtk gtkFileChooserActionOpen title: aString parent: aGtkWidget button: GTK.Gtk gtkStockOpen ] selectFolder: aString parent: aGtkWidget [ ^ self for: GTK.Gtk gtkFileChooserActionSelectFolder title: aString parent: aGtkWidget button: GTK.Gtk gtkStockOpen ] ] GTK.GtkListStore extend [ appendItem: anArray [ | iter | iter := self append. self at: iter put: anArray. ^ iter ] prependItem: anArray [ | iter | iter := self prepend. self at: iter put: anArray. ^ iter ] itersDo: aBlock [ | iter | ((iter := self getIterFirst) isNil or: [ (self iterIsValid: iter) not ] ) ifTrue: [ ^ nil ]. aBlock value: iter. [ self iterNext: iter ] whileTrue: [ aBlock value: iter ] ] do: aBlock [ self itersDo: [ :iter | aBlock value: (self at: iter) value: iter ] ] lastIter [ | lastIter iter path | iter := lastIter := GTK.GtkTreeIter new. path := GTK.GtkTreePath newFirst. [ self getIter: iter path: path ] whileTrue: [ lastIter := iter. iter := GTK.GtkTreeIter new. path next ]. ^ lastIter ] ] GTK.GtkMenuItem class extend [ menuItem: aString connectTo: anObject selector: aSymbol userData: userData [ ^ (self newWithLabel: aString) connectSignal: 'activate' to: anObject selector: aSymbol userData: userData; yourself ] menuItem: aString connectTo: anObject selector: aSymbol [ ^ self menuItem: aString connectTo: anObject selector: aSymbol userData: nil ] menuItem: aString accelPath: anAccelPathString [ ^ (self newWithLabel: aString) setAccelPath: anAccelPathString; yourself ] menuItem: aString accelPath: anAccelPathString connectTo: anObject selector: aSymbol [ ^ (self menuItem: aString accelPath: anAccelPathString) connectSignal: 'activate' to: anObject selector: aSymbol userData: nil; yourself ] ] GTK.GtkMenu extend [ appendSeparator [ self append: GTK.GtkMenuItem new ] appendMenuItems: anArray [ anArray do: [ :each | self append: (each isEmpty ifTrue: [ GTK.GtkMenuItem new ] ifFalse: [ (GTK.GtkMenuItem newWithLabel: (each at: 1)) connectSignal: 'activate' to: (each at: 2) selector: (each at: 3) userData: nil; yourself ]) ] ] ] GTK.GtkScrolledWindow class extend [ withChild: aGtkWidget [ ^ (GTK.GtkScrolledWindow new: nil vadjustment: nil) add: aGtkWidget; setPolicy: GTK.Gtk gtkPolicyAutomatic vscrollbarPolicy: GTK.Gtk gtkPolicyAutomatic; yourself ] ] GTK.GtkTextBuffer extend [ text [ ^ self getText: self getStartIter end: self getEndIter includeHiddenChars: false ] applyTagByName: aSymbol startOffset: aStartInteger endOffset: anEndInteger [ | end start | start := GTK.GtkTextIter new. end := GTK.GtkTextIter new. self getIterAtOffset: start charOffset: aStartInteger. self getIterAtOffset: end charOffset: anEndInteger. self applyTagByName: aSymbol start: start end: end ] getIterAtOffset: offset [ | result | result := GTK.GtkTextIter new. self getIterAtOffset: result charOffset: offset. ^ result ] iterOfSelectedText [ | iter | self getHasSelection ifTrue: [ iter := self getSelectionBounds ifNil: [ ^ self ]. (iter at: 1) getOffset > ((iter at: 2) getOffset) ifTrue: [ iter swap: 1 with: 2 ] ] ifFalse: [ iter := {self getStartIter. self getEndIter} ]. ^ iter ] selectedText [ | iter | iter := self iterOfSelectedText. ^ self getText: (iter at: 1) end: (iter at: 2) includeHiddenChars: false ] ] GTK.GtkTreeModel extend [ at: aGtkTreeIter [ | values | aGtkTreeIter ifNil: [ ^ nil ]. values := OrderedCollection new. 0 to: self getNColumns - 1 do: [ :column | values add: (self at: aGtkTreeIter column: column) ]. ^ values ] at: aGtkTreeIter column: anInteger [ ^ self getOop: aGtkTreeIter column: anInteger ] at: aGtkTreeIter column: anInteger put: anObject [ self setOop: aGtkTreeIter column: anInteger value: anObject ] at: aGtkTreeIter put: anArray [ 1 to: anArray size do: [ :i | self at: aGtkTreeIter column: i - 1 put: (anArray at: i) ] ] at: aGtkTreeIter do: aBlock [ (self at: aGtkTreeIter) do: aBlock ] itersDo: aBlock iter: aGtkTreeIter [ | childIter | childIter := GTK.GtkTreeIter new. aBlock value: aGtkTreeIter. (self iterChildren: childIter parent: aGtkTreeIter) ifTrue: [ self itersDo: aBlock iter: childIter ]. [ self iterNext: aGtkTreeIter ] whileTrue: [ aBlock value: aGtkTreeIter. (self iterChildren: childIter parent: aGtkTreeIter) ifTrue: [ self itersDo: aBlock iter: childIter ] ] ] itersDo: aBlock [ | iter child | ((iter := self getIterFirst) isNil or: [ (self iterIsValid: iter) not ] ) ifTrue: [ ^ nil ]. self itersDo: aBlock iter: iter ] do: aBlock [ self itersDo: [ :iter | aBlock value: (self at: iter) value: iter ] ] ] GTK.GtkTreeStore extend [ itersDo: aBlock iter: aGtkTreeIter [ | childIter | childIter := GTK.GtkTreeIter new. aBlock value: aGtkTreeIter. (self iterChildren: childIter parent: aGtkTreeIter) ifTrue: [ self itersDo: aBlock iter: childIter ]. [ self iterNext: aGtkTreeIter ] whileTrue: [ aBlock value: aGtkTreeIter. (self iterChildren: childIter parent: aGtkTreeIter) ifTrue: [ self itersDo: aBlock iter: childIter ] ] ] itersDo: aBlock [ | iter child | ((iter := self getIterFirst) isNil or: [ (self iterIsValid: iter) not ] ) ifTrue: [ ^ nil ]. self itersDo: aBlock iter: iter ] do: aBlock [ self itersDo: [ :iter | aBlock value: (self at: iter) value: iter ] ] appendItem: anArray [ ^ self append: nil item: anArray ] append: aGtkTreeIter item: anArray [ | iter | iter := GTK.GtkTreeIter new. self append: iter parent: aGtkTreeIter; at: iter put: anArray. ^ iter ] ] GTK.GtkTreeView class extend [ newWith: aGtkModel columns: anArray [ | view | view := self new. view setModel: aGtkModel. anArray keysAndValuesDo: [ :i :each || col render | col := (GtkTreeViewColumn new) packStart: (render := each key = 'text' ifFalse: [ GTK.GtkCellRendererPixbuf new ] ifTrue: [ GTK.GtkCellRendererText new ]) expand: true; addAttribute: render attribute: each key column: i - 1; yourself. each value isEmpty ifFalse: [ col setTitle: each value ]. view insertColumn: col position: -1 ]. ^ view ] newWith: aGtkModel pack: anArray title: aString [ | view col | view := self new. view setModel: aGtkModel. col := GtkTreeViewColumn new. anArray keysAndValuesDo: [ :i :each || render | col packStart: (render := each = 'text' ifFalse: [ GTK.GtkCellRendererPixbuf new ] ifTrue: [ GTK.GtkCellRendererText new ]) expand: each = 'text'; addAttribute: render attribute: each column: i - 1 ]. col setTitle: aString. view insertColumn: col position: -1. ^ view ] newWithTextColumn: aGtkModel title: aString [ | view col render | view := self new setModel: aGtkModel; yourself. col := (GtkTreeViewColumn new) packStart: (render := GTK.GtkCellRendererText new) expand: true; addAttribute: render attribute: 'text' column: 0; setTitle: aString; yourself. view insertColumn: col position: -1. ^ view ] newWithSortedTextColumn: aGtkModel title: aString [ | view col render | view := self new setModel: aGtkModel; yourself. col := (GtkTreeViewColumn new) packStart: (render := GtkCellRendererText new) expand: true; addAttribute: render attribute: 'text' column: 0; setTitle: aString; setSortIndicator: true; setSortColumnId: 0; setSortOrder: Gtk gtkSortAscending; yourself. view insertColumn: col position: -1. ^ view ] ] GTK.GtkTreeView extend [ hasSelectedItem [ ^ self getSelection getSelected isNil not ] numberOfItems [ ^ self getModel iterNChildren: nil ] selectedIter [ ^ self getSelection getSelected ] selectedIndex [ self hasSelectedItem ifFalse: [ self error: 'Nothing is selected' ]. ^ (self getModel getPath: self selectedIter) getIndices value + 1 ] ] GTK.GtkToolButton class extend [ newFromStock: icon label: aString [ ^(self newFromStock: icon) setLabel: aString; yourself ] ] "Finish initialization. This will be done upon #returnFromSnapshot on subsequent image loads." Eval [ GLib registerAllTypes ] smalltalk-3.2.5/packages/gtk/stamp-classes0000644000175000017500000000000012130456013015454 00000000000000smalltalk-3.2.5/packages/gtk/MoreStructs.st0000644000175000017500000000752612130343734015645 00000000000000"====================================================================== | | Smalltalk Gtk+ bindings (declarations of some CStructs needing fields) | ======================================================================" "====================================================================== | | Copyright 2004, 2008, 2009 Free Software Foundation, Inc. | Written by Robert Collins. | | This file is part of the GNU Smalltalk class library. | It contains manual struct definitions the automatic logic fails to create | | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LESSER. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" CStruct subclass: GTypeClass [ ] "FIXME: passing #cObjectPtr should be smarter or something" CStruct subclass: GtkTreeModelPointer [ ] CStruct subclass: GtkRequisition [ ] CStruct subclass: GList [ free [ ] ] CStruct subclass: GSList [ free [ ] ] CStruct subclass: GdkColor [ ] "FIXME more events needed" CStruct subclass: GdkEventButton [ ] CStruct subclass: GdkEventMotion [ ] CStruct subclass: GdkEventConfigure [ ] CStruct subclass: GdkEventKey [ ] smalltalk-3.2.5/packages/gtk/package.xml0000644000175000017500000000132112130343734015103 00000000000000 GTK GTK Cairo GtkDecl.st Structs.st MoreStructs.st Enums.st Funcs.st MoreFuncs.st GtkImpl.st gst-gtk Structs.st Enums.st Funcs.st example_arrow.st example_aspectframe.st example_buttonbox.st example_entry.st example_eventbox.st example_hello.st example_tictactoe.st example_tree.st smalltalk-3.2.5/packages/gtk/structs.awk0000644000175000017500000001153412130343734015210 00000000000000#! @AWK@ -f ####################################################################### # # Gtk wrapper creation script (struct declarations) # ######################################################################## ####################################################################### # # Copyright 2001, 2003, 2009 Free Software Foundation, Inc. # Written by Paolo Bonzini and Dragomir Milivojevic # # This file is part of the GNU Smalltalk class library. # # The GNU Smalltalk class library is free software; you can redistribute it # and/or modify it under the terms of the GNU Lesser General Public License # as published by the Free Software Foundation; either version 2.1, or (at # your option) any later version. # # The GNU Smalltalk class library is distributed in the hope that it will be # useful, but WITHOUT ANY WARRANTY; without even the implied warranty of # MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser # General Public License for more details. # # You should have received a copy of the GNU Lesser General Public License # along with the GNU Smalltalk class library; see the file COPYING.LESSER. # If not, write to the Free Software Foundation, 59 Temple Place - Suite # 330, Boston, MA 02110-1301, USA. # ######################################################################## BEGIN { print "\"Automatically generated, do not edit!\"" # These are implemented strangely... classNames["GValue"] = "" classNames["GdkAtom"] = "" classNames["GtkObject"] = "" classNames["GtkEditable"] = "" # GtkEditable is a dummy class, so we must set inheritance manually known_parent["GtkEntry"] = "GtkEditable" known_parent["GtkEditable"] = "GtkWidget" known_parent["GObject"] = "GTypeInstance" known_parent["GtkObject"] = "GObject" known_parent["GdkWindowObject"] = "GdkDrawable" # A couple of things that we need from GLib known_parent["GOptionGroup"] = "CObject" known_parent["GDate"] = "CObject" # Here starts the class hierarchy emitted["CObject"] = "" } { gsub(/[_;]/, "", $0) is_typedef = ($1 == "typedef") # is_struct = $(1+is_typedef) ~ /^(struct|union)$/ is_struct = $(1+is_typedef) == "struct" if (is_typedef) { src = $(1+is_typedef+is_struct) dest = $(3+is_struct) is_vtable_decl = src ~ /(Class|Iface)$/ is_g_name = src ~ /^(G|Pango|Atk)/ is_pointer = dest ~ /\*/ if (src ~ /Iface$/ && is_g_name && !is_pointer) known_parent[substr (dest, 1, length (dest) - 5)] = "GObject" } else if (is_struct) name = $2 } is_typedef && is_struct && is_g_name && (src == dest || "_" src == dest) { if (!is_vtable_decl) classNames[src] = "" next } is_typedef && is_g_name && !is_pointer { # Take into account typedefs from a struct named differently. # We emit all these at the end, because they're often forward # references. found_synonym(src, dest) next } is_struct && (name in classNames) { while ($0 !~ /{/) read_next_line() read_next_line() if (name in known_parent) parent = known_parent[name] else parent = ($1 ~ /^(G|Pango|Atk)/) && ($2 !~ /^\*/) && ($1 in emitted) ? $1 : "CObject" parse_struct(parent, name) } END { for (i in classNames) savedClassNames[i] = classNames[i] for (className in savedClassNames) if (className in known_parent) emit_struct(known_parent[className], className) else emit_struct("CObject", className) } # strips garbage from string function strip( var ) { gsub( /[()\\,;*]/, "", var ) return var } function smalltalkize( res ) { first = substr (res, 1, 1) res = tolower( substr (res, 2) ) while (i = index (res, "_")) { first = first substr(res, 1, i - 1) toupper( substr (res, i + 1, 1)) res = substr (res, i + 2) } return first res } function read_next_line () { for (;;) { getline if (NF > 0) break } } # save and i are local variables function emit_struct (parent, name, save, i) { if (name in emitted) return delete classNames[name] # To fix up the big mess that is GtkEditable ensure here that we emit # parent classes before the children if (!(parent in emitted)) { if (parent in known_parent) emit_struct(known_parent[parent], parent) else emit_struct("CObject", parent) } if (name ~ /^\*/) return emitted[name] = "" printf "%s variableWordSubclass: #%s\n", parent, name print "\tinstanceVariableNames: ''" print "\tclassVariableNames: ''" print "\tpoolDictionaries: ''" print "\tcategory: 'Gtk'!\n" save = $0 $0 = synonyms[name] delete synonyms[name] for (i = 1; i <= NF; i++) emit_struct(name, $i) $0 = save } function parse_struct (parent, name) { emit_struct(parent, name) while ($1 != "};") read_next_line() } function found_synonym(src, dest) { if (src in emitted) emit_struct(src, dest) else synonyms[src] = synonyms[src] " " dest } smalltalk-3.2.5/packages/xml/0000755000175000017500000000000012130456023013060 500000000000000smalltalk-3.2.5/packages/xml/tests/0000755000175000017500000000000012130456022014221 500000000000000smalltalk-3.2.5/packages/xml/tests/Makefile.frag0000644000175000017500000000032512123404352016520 00000000000000XML-ParserTests_FILES = \ packages/xml/tests/XMLPullParserTests.st $(XML-ParserTests_FILES): $(srcdir)/packages/xml/tests/stamp-classes: $(XML-ParserTests_FILES) touch $(srcdir)/packages/xml/tests/stamp-classes smalltalk-3.2.5/packages/xml/tests/XMLPullParserTests.st0000644000175000017500000002155612123404352020220 00000000000000"====================================================================== | | SAX event-based pull parser testcases | | ======================================================================" "====================================================================== | | Copyright (c) 2009, Antony Blakey | All rights reserved. | | Redistribution and use in source and binary forms, with or without | modification, are permitted provided that the following conditions | are met: | * Redistributions of source code must retain the above copyright | notice, this list of conditions and the following disclaimer. | * Redistributions in binary form must reproduce the above copyright | notice, this list of conditions and the following disclaimer in the | documentation and/or other materials provided with the distribution. | * Neither the name of Antony Blakey nor the names of its contributors | may be used to endorse or promote products derived derived from | this software without specific prior written permission. | | THIS SOFTWARE IS PROVIDED 'AS IS' AND ANY EXPRESS OR IMPLIED WARRANTIES, | INCLUDING, BUT NOT LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY | AND FITNESS FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL | ANTONY BLAKEY BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, | SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED | TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR | PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF | LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING | NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF THIS | SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. | ======================================================================" TestCase subclass: XMLPullParserTest [ parserOn: source [ | pull | pull := XMLPullParser onString: source. pull validate: false. ^pull ] testCDATA [ | parser | parser := self parserOn: ''. self assert: parser isStartDocument. self assert: (parser next isStartTag: 'document'). self assert: parser next isText. self assert: parser text = 'This is a test & stuff in here doesn''t have to be escaped'. self assert: (parser isEndTag: 'document'). self assert: parser next isEndDocument ] testCDATAEvents [ | parser | parser := self parserOn: 'This is a test '. parser needCdataDelimiters: true. self assert: parser isStartDocument. self assert: (parser next isStartTag: 'document'). self assert: parser next isText. self assert: parser text = 'This is a test '. self assert: parser isStartCdataSection. self assert: parser next isText. self assert: parser text = '& stuff in here doesn''t have to be escaped'. self assert: parser isEndCdataSection. self assert: (parser next isEndTag: 'document'). self assert: parser next isEndDocument ] testCharacterReferences [ | parser | parser := self parserOn: '#(&)'. self assert: parser isStartDocument. self assert: (parser next isStartTag: 'document'). self assert: (parser next isStartTag: 'name'). self assert: parser next isText. self assert: parser text = '#(&)'. self assert: (parser isEndTag: 'name'). self assert: (parser next isEndTag: 'document'). self assert: parser next isEndDocument ] testDoubleTag [ | parser | parser := self parserOn: ''. self assert: parser isStartDocument. self assert: (parser next isStartTag: 'document'). self assert: (parser next isStartTag: 'body'). self assert: (parser next isEndTag: 'body'). self assert: (parser next isEndTag: 'document'). self assert: parser next isEndDocument ] testEmpty [ | parser | [ parser := self parserOn: ''. self assert: parser isStartDocument. self assert: parser next isEndDocument ] on: EmptySignal do: [ :ex | ex resume ] ] testEscapes [ | parser | parser := self parserOn: 'Escaped & Unescaped: <>'. self assert: parser isStartDocument. self assert: (parser next isStartTag: 'tag'). self assert: parser next isText. self assert: parser text = 'Escaped & Unescaped: <>'. self assert: parser next isEndDocument ] testPerson [ | parser | parser := self parserOn: ' Kent BeckXP'. self assert: parser isStartDocument. self assert: (parser next isStartTag: 'person'). self assert: (parser current attributes at: 'id') = '27'. self assert: (parser next isStartTag: 'name'). self assert: parser next isText. self assert: parser text = 'Kent Beck'. self assert: (parser next isStartTag: 'notedFor'). self assert: parser next isText. self assert: parser text = 'XP'. self assert: (parser next isEndTag: 'person'). self assert: parser next isEndDocument ] testComments [ | parser | parser := self parserOn: ' '. self assert: parser isStartDocument. self assert: (parser next isStartTag: 'a'). parser needComments: true. self assert: parser next isComment. self assert: parser next isComment. self assert: (parser next isStartTag: 'b'). parser skip: 'b'. "Test that #needComments: works even if #skip: did lookahead." parser needComments: false. self assert: (parser next isStartTag: 'c'). ] testPI [ | parser | parser := self parserOn: ''. self assert: parser isStartDocument. self assert: (parser next isPI). self deny: (parser isPI: 'xml'). self assert: (parser isPI: 'xsl'). self assert: (parser current target = 'xsl'). self assert: (parser current data = 'stylesheet="a"'). self assert: (parser next isStartTag: 'test'). self assert: parser next isEndTag. self assert: parser next isEndDocument ] testSingleSelfClosingTag [ | parser | parser := self parserOn: ''. self assert: parser isStartDocument. self assert: (parser next isStartTag: 'selfClose'). self assert: parser next isEndTag. self assert: parser next isEndDocument ] testSingleTag [ | parser | parser := self parserOn: ''. self assert: parser isStartDocument. self assert: (parser next isStartTag: 'document'). self assert: (parser next isStartTag: 'body'). self assert: (parser next isEndTag: 'body'). self assert: (parser next isEndTag: 'document'). self assert: parser next isEndDocument ] testDTDSkip [ | parser | parser := self parserOn: ' ]>'. self assert: parser isStartDocument. self assert: parser next isStartDoctypeDecl. self assert: parser doctypeName = 'name'. self assert: (parser isStartTag: 'document'). self assert: (parser next isEndTag: 'document'). self assert: parser next isEndDocument ] testDTDEvents [ | parser | parser := self parserOn: ' ]>'. self assert: parser isStartDocument. self assert: (parser next isStartDoctypeDecl: 'test'). self assert: parser next isNotationDecl. self assert: parser current name = 'nblah'. self assert: parser current publicID = 'foo'. self assert: parser current systemID isNil. self assert: parser next isUnparsedEntityDecl. self assert: parser current publicID isNil. self assert: parser current systemID isEmpty. self assert: parser current notationName = 'nblah'. self assert: parser next isEndDoctypeDecl. self assert: (parser next isStartTag: 'document'). self assert: (parser next isEndTag: 'document'). self assert: parser next isEndDocument ] testResolveEntity [ | parser | [ parser := self parserOn: ' ]>&blah;'. parser needDTDEvents: false. self assert: parser isStartDocument. self assert: (parser next isStartTag: 'document'). self assert: (parser next isText). self assert: (parser current text = 'bar'). self assert: (parser next isEndTag: 'document'). self assert: parser next isEndDocument ] on: XMLResolveEntityNotification do: [ :e | e resume: (InputSource uri: e systemID encoding: '' stream: e publicID readStream) ] ] ] smalltalk-3.2.5/packages/xml/tests/stamp-classes0000644000175000017500000000000012123404352016632 00000000000000smalltalk-3.2.5/packages/xml/tests/package.xml0000644000175000017500000000060012123404352016253 00000000000000 XML-ParserTests XML XML-PullParser SUnit XMLPullParserTests.st smalltalk-3.2.5/packages/xml/saxdriver/0000755000175000017500000000000012130456023015067 500000000000000smalltalk-3.2.5/packages/xml/saxdriver/Makefile.frag0000644000175000017500000000035512123404352017370 00000000000000XML-SAXDriver_FILES = \ packages/xml/saxdriver/SAX.st packages/xml/saxdriver/Events.st $(XML-SAXDriver_FILES): $(srcdir)/packages/xml/saxdriver/stamp-classes: $(XML-SAXDriver_FILES) touch $(srcdir)/packages/xml/saxdriver/stamp-classes smalltalk-3.2.5/packages/xml/saxdriver/Events.st0000644000175000017500000003670712123404352016640 00000000000000"====================================================================== | | SAX event objects | | ======================================================================" "====================================================================== | | Copyright (c) 2009, Antony Blakey | All rights reserved. | | Redistribution and use in source and binary forms, with or without | modification, are permitted provided that the following conditions | are met: | * Redistributions of source code must retain the above copyright | notice, this list of conditions and the following disclaimer. | * Redistributions in binary form must reproduce the above copyright | notice, this list of conditions and the following disclaimer in the | documentation and/or other materials provided with the distribution. | * Neither the name of Antony Blakey nor the names of its contributors | may be used to endorse or promote products derived derived from | this software without specific prior written permission. | | THIS SOFTWARE IS PROVIDED 'AS IS' AND ANY EXPRESS OR IMPLIED WARRANTIES, | INCLUDING, BUT NOT LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY | AND FITNESS FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL | ANTONY BLAKEY BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, | SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED | TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR | PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF | LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING | NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF THIS | SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. | ======================================================================" Object subclass: SAXEvent [ isComment [ ^false ] isEndCdataSection [ ^false ] isEndDoctypeDecl [ ^false ] isEndDocument [ ^false ] isEndDocumentFragment [ ^false ] isNotationDecl [ ^false ] isSkippedEntity [ ^false ] isUnparsedEntityDecl [ ^false ] isEndPrefixMapping [ ^false ] isEndTag [ ^false ] isEndTag: aStringOrNodeTag [ ^false ] isPI [ ^false ] isPI: aString [ ^false ] isProcessingInstruction [ ^false ] isProcessingInstruction: aString [ ^false ] isStartCdataSection [ ^false ] isStartDoctypeDecl [ ^false ] isStartDoctypeDecl: aString [ ^false ] isStartDocument [ ^false ] isStartDocumentFragment [ ^false ] isStartTag [ ^false ] isStartTag: aStringOrNodeTag [ ^false ] isText [ ^false ] ] SAXEvent subclass: SAXEndCdataSection [ isEndCdataSection [ ^true ] serializeTo: serializer [ serializer endCdataSection ] ] SAXEvent subclass: SAXEndDoctypeDecl [ isEndDoctypeDecl [ ^true ] serializeTo: serializer [ serializer endDoctypeDecl ] ] SAXEvent subclass: SAXEndDocumentFragment [ isEndDocumentFragment [ ^true ] serializeTo: serializer [ serializer endDocumentFragment ] ] SAXEvent subclass: SAXEndDocument [ isEndDocument [ ^true ] serializeTo: serializer [ serializer endDocument ] ] SAXEvent subclass: SAXStartCdataSection [ isStartCdataSection [ ^true ] serializeTo: serializer [ serializer startCdataSection ] ] SAXEvent subclass: SAXStartDocumentFragment [ isStartDocumentFragment [ ^true ] serializeTo: serializer [ serializer startDocumentFragment ] ] SAXEvent subclass: SAXStartDocument [ isStartDocument [ ^true ] serializeTo: serializer [ serializer startDocument ] ] SAXEvent subclass: SAXTagEvent [ | tag | SAXTagEvent class >> tag: tag [ ^self new tag: tag ] is: tagName [ ^tag isLike: tagName ] name [ ^tag name ] namespace [ ^tag namespace ] qualifier [ ^tag qualifier ] tag [ ^tag ] tag: aNodeTag [ tag := aNodeTag ] type [ ^tag type ] ] SAXTagEvent subclass: SAXEndTag [ isEndTag [ ^true ] isEndTag: aStringOrNodeTag [ ^tag isLike: aStringOrNodeTag ] printOn: aStream [ super printOn: aStream. aStream nextPutAll: ' ' ] serializeTo: serializer [ serializer endElement: tag namespace localName: tag type qName: tag asString ] ] SAXTagEvent subclass: SAXStartTag [ | attributes attrArray | SAXStartTag class >> tag: tag attributesArray: a [ ^(super tag: tag) attributesArray: a ] SAXStartTag class >> tag: tag attributes: a [ ^(super tag: tag) attributes: a ] at: attName [ ^self at: attName ifNone: [SAXStructureException raiseSignal: 'Expected attribute ' , attName , ' is missing'] ] at: attName ifFound: aFoundBlock ifNone: aBlock [ attributes at: attName ifPresent: [ :value | ^aFoundBlock value: value]. ^aBlock value ] at: attName ifNone: aBlock [ ^attributes at: attName asString ifAbsent: [aBlock value] ] attributesArray [ attrArray isNil ifTrue: [ ^self computeAttributesArray ]. ^attrArray ] attributesArray: anObject [ attrArray := anObject. attributes := nil. ] attributes [ attributes isNil ifTrue: [ ^self computeAttributes ]. ^attributes ] attributes: anObject [ attributes := anObject. attrArray := nil. ] computeAttributes [ attributes := LookupTable new. attrArray do: [ :each | attributes at: each key name put: each value ]. ] computeAttributesArray [ attrArray := OrderedCollection new. attributes keysAndValuesDo: [ :key :value | attrArray add: (Attribute name: key value: value) ]. ] isStartTag [ ^true ] isStartTag: aStringOrNodeTag [ ^tag isLike: aStringOrNodeTag ] printOn: aStream [ super printOn: aStream. aStream nextPutAll: ' <'; nextPutAll: tag asString; nextPutAll: '>' ] serializeTo: serializer [ serializer startElement: tag namespace localName: tag type qName: tag asString attributes: attrArray ] ] SAXEvent subclass: SAXProcessingInstruction [ | target data | SAXProcessingInstruction class >> target: targetString data: dataString [ ^self new target: targetString; data: dataString ] data [ ^data ] data: aString [ data := aString ] isPI [ ^true ] isPI: aString [ ^target = aString ] serializeTo: serializer [ serializer processingInstruction: target data: data ] target [ ^target ] target: aString [ target := aString ] ] SAXEvent subclass: SAXStringEvent [ | text from to textPart | SAXStringEvent class >> text: aString [ ^self new text: aString ] SAXStringEvent class >> text: aString from: start to: stop [ ^self new text: aString from: start to: stop ] isText [ ^true ] serializeTo: serializer [ serializer characters: text from: from to: to ] text [ textPart isNil ifTrue: [textPart := text copyFrom: from to: to]. ^textPart ] text: aString [ text := textPart := aString. from := 1. to := text size. ] text: aString from: start to: stop [ text := aString. from := start. to := stop. textPart := nil ] ] SAXStringEvent subclass: SAXText [ isText [ ^true ] serializeTo: serializer [ serializer characters: text from: 1 to: text size ] ] SAXStringEvent subclass: SAXComment [ isComment [ ^true ] serializeTo: serializer [ serializer comment: text from: 1 to: text size ] ] SAXEvent subclass: SAXStartPrefixMapping [ | prefix uri | SAXStartPrefixMapping class >> prefix: aString uri: uriString [ ^self new prefix: aString; uri: uriString ] isStartPrefixMapping [ ^true ] serializeTo: serializer [ serializer startPrefixMapping: prefix uri: uri ] prefix [ ^prefix ] prefix: aString [ prefix := aString. ] uri [ ^uri ] uri: aString [ uri := aString. ] ] SAXEvent subclass: SAXEndPrefixMapping [ | prefix | SAXEndPrefixMapping class >> prefix: aString [ ^self new prefix: aString ] isEndPrefixMapping [ ^true ] serializeTo: serializer [ serializer endPrefixMapping: prefix ] prefix [ ^prefix ] prefix: aString [ prefix := aString. ] ] SAXEvent subclass: SAXExternalDecl [ | publicID systemID | isNotationDecl [ ^true ] publicID [ ^publicID ] publicID: aString [ publicID := aString ] systemID [ ^systemID ] systemID: aString [ systemID := aString ] ] SAXExternalDecl subclass: SAXStartDoctypeDecl [ | name hasInternalSubset | SAXStartDoctypeDecl class >> name: aString publicID: pidString systemID: sidString hasInternalSubset: aBoolean [ ^self new name: aString; publicID: pidString; systemID: sidString; hasInternalSubset: aBoolean ] isStartDoctypeDecl: aString [ ^name isLike: aString ] isStartDoctypeDecl [ ^true ] serializeTo: serializer [ serializer startDoctypeDecl: name publicID: publicID systemID: systemID hasInternalSubset: hasInternalSubset ] hasInternalSubset [ ^hasInternalSubset ] hasInternalSubset: aBoolean [ hasInternalSubset := aBoolean ] name [ ^name ] name: aString [ name := aString ] ] SAXEvent subclass: SAXSkippedEntity [ | name | SAXSkippedEntity class >> name: aString [ ^self new name: aString ] isSkippedEntity [ ^true ] serializeTo: serializer [ serializer skippedEntity: name ] name [ ^name ] name: aString [ name := aString ] ] SAXExternalDecl subclass: SAXNotationDecl [ | name | SAXNotationDecl class >> name: aString publicID: pidString systemID: sidString [ ^self new name: aString; publicID: pidString; systemID: sidString ] isNotationDecl [ ^true ] serializeTo: serializer [ serializer notationDecl: name publicID: publicID systemID: systemID ] name [ ^name ] name: aString [ name := aString ] ] SAXExternalDecl subclass: SAXUnparsedEntityDecl [ | name notationName | SAXUnparsedEntityDecl class >> name: aString publicID: pidString systemID: sidString notationName: notation [ ^self new name: aString; publicID: pidString; systemID: sidString; notationName: notation ] isUnparsedEntityDecl [ ^true ] serializeTo: serializer [ serializer unparsedEntityDecl: name publicID: publicID systemID: systemID notationName: notationName ] name [ ^name ] name: aString [ name := aString ] notationName [ ^notationName ] notationName: aString [ notationName := aString ] ] smalltalk-3.2.5/packages/xml/saxdriver/SAX.st0000644000175000017500000010235312123404352016016 00000000000000"====================================================================== | | VisualWorks XML Framework - SAX interface | | ======================================================================" "====================================================================== | | Copyright (c) 2000, 2002 Cincom, Inc. | Copyright (c) 2009 Free Software Foundation, Inc. | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" Object subclass: SAXDriver [ | locator | place holder for SAX''s Locator, which allows better error recovery.'> comment: data from: start to: stop [ ] idOfElement: elementID [ "Notify the client what was the ID of the latest startElement" ] sourcePosition: position inStream: streamWrapper [ "Non-standard API to ease transition from builders to SAX." ] characters: aString [ ] characters: aString from: start to: stop [ ^self characters: (aString copyFrom: start to: stop) ] endCdataSection [ ] endDoctypeDecl [ ] endDocument [ ] endDocumentFragment [ "Nonstandard extension to SAX" ] endElement: namespaceURI localName: localName qName: name [ "indicates the end of an element. See startElement" ] endPrefixMapping: prefix [ "End the scope of a prefix-URI mapping. See startPrefixMapping for details. This event will always occur after the corresponding endElement event, but the order of endPrefixMapping events is not otherwise guaranteed. Parameters: prefix - The prefix that was being mapped. " ^self ] ignorableWhitespace: aString [ ] ignorableWhitespace: aString from: start to: stop [ ^self ignorableWhitespace: (aString copyFrom: start to: stop) ] processingInstruction: targetString data: dataString [ ] setDocumentLocator: aLocator [ locator := aLocator ] skippedEntity: name [ "Receive notification of a skipped entity. The Parser will invoke this method once for each entity skipped. Non-validating processors may skip entities if they have not seen the declarations (because, for example, the entity was declared in an external DTD subset). Parameters: name - The name of the skipped entity. If it is a parameter entity, the name will begin with '%', and if it is the external DTD subset, it will be the string '[dtd]'. " ^self ] startCdataSection [ ] startDoctypeDecl: doctypeName publicID: publicID systemID: systemID hasInternalSubset: aBoolean [ ] startDocument [ ] startDocumentFragment [ "Nonstandard extension to SAX" ] startElement: namespaceURI localName: localName qName: name attributes: attributes [ "Receive notification of the beginning of an element. Parameters: namespaceURI The Namespace URI, Nil if the element has no Namespace URI localName The local name of the element (without prefix) name Literal name of the element as it appears, nil if processing namespaces. attributes The attributes attached to the element. Example A text BA text C text Parameter values to this method for each element of the above XML: local name: 'doc' namespace: 'http://www.doc.org/' name: 'doc' local name: 'a' namespace: 'http://www.doc.org/' name: 'a' local name: 'b' namespace: 'http://www.other.com/' name: 'other:b' local name: 'c' namespace: 'http://www.doc.org/' name: 'c' local name: 'd' namespace: 'http:/nested/' name: 'd' Note the attribute object also have namespaces" ] startPrefixMapping: prefix uri: uri [ "Begin the scope of a prefix-URI Namespace mapping. The information from this event is not necessary for normal Namespace processing: the SAX XML reader will automatically replace prefixes for element and attribute names when the http://xml.org/sax/features/namespaces feature is true (the default). There are cases, however, when applications need to use prefixes in character data or in attribute values, where they cannot safely be expanded automatically; the start/endPrefixMapping event supplies the information to the application to expand prefixes in those contexts itself, if necessary. Note that start/endPrefixMapping events are not guaranteed to be properly nested relative to each-other: all startPrefixMapping events will occur before the corresponding startElement event, and all endPrefixMapping events will occur after the corresponding endElement event, but their order is not otherwise guaranteed. There should never be start/endPrefixMapping events for the 'xml' prefix, since it is predeclared and immutable. Parameters: prefix - The Namespace prefix being declared. uri - The Namespace URI the prefix is mapped to. " ^self ] fatalError: anException [ anException signal ] nonFatalError: anException [ anException signal ] warning: anException [ Transcript nl; show: anException messageText ] notationDecl: nameString publicID: publicIDString systemID: systemIDString [ "Receive notification of a notation declaration event. It is up to the application to record the notation for later reference, if necessary. If a system identifier is present, and it is a URL, the SAX parser must resolve it fully before passing it to the application." ] unparsedEntityDecl: name publicID: publicID systemID: systemID notationName: notation [ "Receive notification of an unparsed entity declaration event. Note that the notation name corresponds to a notation reported by the notationDecl event. It is up to the application to record the entity for later reference, if necessary. If the system identifier is a URL, the parser must resolve it fully before passing it to the application. " ^self ] resolveEntity: publicID systemID: systemID [ ^nil ] contentHandler [ ^self ] document [ ^nil ] dtdHandler [ ^self ] entityResolver [ ^self ] errorHandler [ ^self ] ] SAXDriver subclass: DOM_SAXDriver [ startElement [ self notYetImplemented ] ] SAXDriver subclass: SAXDispatcher [ | contentHandler dtdHandler entityResolver errorHandler | >contentHandler:, but its use by client code is not discouraged. To use it, create a SAXDispatcher, fill in its various handler types with instances of other SAXDrivers, and then store the SAXDispatcher in the parser using the #handlers: message. Instance Variables: contentHandler handles all content events dtdHandler handles entity and notation declarations entityResolver handles resolution of PUBLIC and SYSTEM paths, to allow non-standard resolution errorHandler handles all errors '> SAXDispatcher class >> new [ ^super new initialize ] contentHandler [ ^contentHandler ] contentHandler: aSAXDriver [ contentHandler := aSAXDriver ] document [ ^contentHandler document ] dtdHandler [ ^dtdHandler ] dtdHandler: aSAXDriver [ dtdHandler := aSAXDriver ] entityResolver [ ^entityResolver ] entityResolver: aSAXDriver [ entityResolver := aSAXDriver ] errorHandler [ ^errorHandler ] errorHandler: aSAXDriver [ errorHandler := aSAXDriver ] comment: data from: start to: stop [ contentHandler comment: data from: start to: stop ] idOfElement: elementID [ contentHandler idOfElement: elementID ] sourcePosition: position inStream: stream [ contentHandler sourcePosition: position inStream: stream ] characters: aString from: start to: stop [ contentHandler characters: aString from: start to: stop ] endDocument [ contentHandler endDocument ] endDocumentFragment [ contentHandler endDocumentFragment ] endElement: namespaceURI localName: localName qName: name [ contentHandler endElement: namespaceURI localName: localName qName: name ] endPrefixMapping: prefix [ contentHandler endPrefixMapping: prefix ] ignorableWhitespace: aString from: start to: stop [ contentHandler ignorableWhitespace: aString from: start to: stop ] processingInstruction: targetString data: dataString [ contentHandler processingInstruction: targetString data: dataString ] setDocumentLocator: aLocator [ contentHandler setDocumentLocator: aLocator ] skippedEntity: name [ contentHandler skippedEntity: name ] startDocument [ contentHandler startDocument ] startDocumentFragment [ contentHandler startDocumentFragment ] startElement: namespaceURI localName: localName qName: name attributes: attributes [ contentHandler startElement: namespaceURI localName: localName qName: name attributes: attributes ] startPrefixMapping: prefix uri: uri [ contentHandler startPrefixMapping: prefix uri: uri ] notationDecl: nameString publicID: publicIDString systemID: systemIDString [ dtdHandler notationDecl: nameString publicID: publicIDString systemID: systemIDString ] unparsedEntityDecl: name publicID: publicID systemID: systemID notationName: notation [ dtdHandler unparsedEntityDecl: name publicID: publicID systemID: systemID notationName: notation ] initialize [ contentHandler := NullSAXDriver new. dtdHandler := contentHandler. entityResolver := contentHandler. errorHandler := contentHandler ] resolveEntity: publicID systemID: systemID [ ^entityResolver resolveEntity: publicID systemID: systemID ] fatalError: anException [ errorHandler fatalError: anException ] nonFatalError: anException [ errorHandler nonFatalError: anException ] warning: anException [ errorHandler warning: anException ] ] Error subclass: SAXException [ | wrappedException | another exception, which has been wrapped so that a handler for SAXException will catch it.'> SAXException class >> mayResume [ ^true ] wrappedException [ ^wrappedException ] wrappedException: anException [ wrappedException := anException ] ] SAXDispatcher subclass: XMLFilter [ | parent | the wrapped parser, which may itself be a filter '> XMLFilter class >> on: aParserOrFilter [ ^self new parent: aParserOrFilter ] atFeature: aURIstring [ ^parent atFeature: aURIstring ] atFeature: aURIstring put: aBoolean [ ^parent atFeature: aURIstring put: aBoolean ] atProperty: aURIstring [ ^parent atProperty: aURIstring ] atProperty: aURIstring put: anOvbject [ ^parent atProperty: aURIstring put: anOvbject ] handlers: aSAXDriver [ self contentHandler: aSAXDriver. self dtdHandler: aSAXDriver. self errorHandler: aSAXDriver. self entityResolver: aSAXDriver ] parent [ ^parent ] parent: aParserOrFilter [ parent := aParserOrFilter. parent handlers: self ] parse: dataSource [ ^parent parse: dataSource ] parseElement: dataSource [ ^parent parseElement: dataSource ] parseElements: dataSource [ ^parent parseElements: dataSource ] ] SAXDriver subclass: NullSAXDriver [ characters: aString from: start to: stop [ ^self ] ignorableWhitespace: aString from: start to: stop [ ^self ] ] Object subclass: Locator [ | parser | the current parser'> column [ ^self externalWrapper column ] line [ ^self externalWrapper line ] publicID [ | ent | ent := self externalWrapper entity. ^ent == nil ifTrue: [nil] ifFalse: [ent publicID] ] systemID [ | ent | ent := self externalWrapper entity. ^ent == nil ifTrue: [nil] ifFalse: [ent systemID] ] parser: aParser [ parser := aParser ] externalWrapper [ ^parser fullSourceStack reverse detect: [:s | s isInternal not] ifNone: [parser fullSourceStack first] ] ] SAXDriver subclass: SAXWriter [ | output textMap attrMap hasOpenTag normalizeText notations newNamespaces | Lists the characters that are not allowed to appear literally in attributes, and maps them to their quoted form. hasOpenTag True if we are inside an element that has no content as yet. This allows us to know when we reach the end tag whether we can write the element as rather than . newNamespaces Maps namespace qualifiers to URIs, for namespaces which the current element defines differently than its parent. normalizeText Should be true in almost all cases--can be false only if the "XML" document being parsed is actually not XML, in which case it may be legal to not quote characters such as $<. notations List of notations defined in the document being parsed. output Stream on which the XML is rendered as text. textMap Lists the characters that are not allowed to appear literally in text, and maps them to their quoted form. '> characters: aString from: start to: stop [ | ch mapped | self closeOpenTag. normalizeText ifTrue: [start to: stop do: [:i | ch := aString at: i. mapped := textMap at: ch ifAbsent: [nil]. mapped == nil ifTrue: [output nextPut: ch] ifFalse: [output nextPutAll: mapped]]] ifFalse: [output next: stop + 1 - start putAll: aString startingAt: start] ] comment: data from: start to: stop [ output nextPutAll: '' ] endElement: namespaceURI localName: localName qName: name [ hasOpenTag == true ifTrue: [output nextPutAll: '/>'] ifFalse: [output nextPutAll: '']. hasOpenTag := false ] processingInstruction: targetString data: dataString [ output nextPutAll: '' ] startDocument [ hasOpenTag := false ] startDocumentFragment [ "Nonstandard extension to SAX" hasOpenTag := false ] startElement: namespaceURI localName: localName qName: name attributes: attributes [ | val | notations == nil ifFalse: [self emitDTD: name]. self closeOpenTag. output nextPutAll: '<'. output nextPutAll: name. (self sort: attributes) do: [:att | output space. output nextPutAll: att tag asString. output nextPutAll: '="'. 1 to: att value size do: [:i | | ch mapped | ch := att value at: i. mapped := attrMap at: ch ifAbsent: [nil]. mapped == nil ifTrue: [output nextPut: ch] ifFalse: [output nextPutAll: mapped]]. output nextPutAll: '"']. newNamespaces == nil ifFalse: [newNamespaces keys asSortedCollection do: [:key | output space. output nextPutAll: (key isEmpty ifTrue: ['xmlns'] ifFalse: ['xmlns:' , key]). output nextPutAll: '="'. val := newNamespaces at: key. 1 to: val size do: [:i | | ch mapped | ch := val at: i. mapped := attrMap at: ch ifAbsent: [nil]. mapped == nil ifTrue: [output nextPut: ch] ifFalse: [output nextPutAll: mapped]]. output nextPutAll: '"']]. newNamespaces := nil. hasOpenTag := true ] startPrefixMapping: prefix uri: uri [ newNamespaces == nil ifTrue: [newNamespaces := Dictionary new]. newNamespaces at: prefix put: uri ] minimalCharacterMapping [ textMap := (Dictionary new) at: $< put: '<'; at: $& put: '&'; yourself. attrMap := (Dictionary new) at: $< put: '<'; at: $& put: '&'; at: $" put: '"'; yourself ] normalizeText: aBoolean [ normalizeText := aBoolean ] output: aStream [ output := aStream. normalizeText := true. notations := nil. textMap == nil ifTrue: [self minimalCharacterMapping] ] notationDecl: nameString publicID: publicIDString systemID: systemIDString [ notations == nil ifTrue: [notations := OrderedCollection new]. notations add: (Array with: nameString with: publicIDString with: systemIDString) ] closeOpenTag [ hasOpenTag == true ifTrue: [output nextPutAll: '>'. hasOpenTag := false] ] emitDTD: name [ | list | output nextPutAll: ''; nl. notations := nil ] emitNotation: array [ output nextPutAll: '' ] sort: attributes [ ^attributes asSortedCollection: [:a1 :a2 | a1 tag asString < a2 tag asString] ] ] SAXWriter subclass: SAXCanonicalWriter [ | baseURI | When parsing, this remembers the URI of the document so that relative URIs (in Notations, for example) can be resolved to absolute URIs. '> comment: data from: start to: stop [ "Canonical XML surpresses comments" ^self ] startElement: namespaceURI localName: localName qName: name attributes: attributes [ super startElement: namespaceURI localName: localName qName: name attributes: attributes. self closeOpenTag ] emitNotation: array [ | sysID frag | sysID := array at: 3. sysID == nil ifTrue: [^super emitNotation: array]. sysID size to: 2 by: -1 do: [:i | frag := sysID copyFrom: i to: sysID size. frag replaceAll: $: with: $/. frag replaceAll: $\ with: $/. ([(baseURI resolvePath: frag) asString = sysID] on: Error do: [:x | x return: false]) ifTrue: [^super emitNotation: ((array copy) at: 3 put: frag; yourself)]]. super emitNotation: array ] baseURI: url [ baseURI := url ] minimalCharacterMapping [ textMap := (Dictionary new) at: $< put: '<'; at: $> put: '>'; at: $" put: '"'; at: $& put: '&'; at: (Character value: 9) put: ' '; at: (Character value: 10) put: ' '; at: (Character value: 13) put: ' '; yourself. attrMap := (Dictionary new) at: $< put: '<'; at: $> put: '>'; at: $& put: '&'; at: $" put: '"'; at: (Character value: 9) put: ' '; at: (Character value: 10) put: ' '; at: (Character value: 13) put: ' '; yourself ] ] SAXException subclass: SAXParseException [ ] SAXParseException subclass: MalformedSignal [ ] SAXParseException subclass: InvalidSignal [ ] SAXException subclass: SAXNotSupportedException [ ] SAXParseException subclass: WarningSignal [ isResumable [ ^true ] ] MalformedSignal subclass: EmptySignal [ isResumable [ ^true ] ] MalformedSignal subclass: BadCharacterSignal [ ] Object subclass: InputSource [ | uri encoding stream | The URI of the data source, if known encoding If the transport protocol specified an encoding, this should take precedence over the encoding contained in the declaration stream the data source'> InputSource class >> for: uri [ | stream | stream := NetClients.URIResolver openStreamOn: uri. ^self uri: (uri isString ifTrue: [NetClients.URL fromString: uri] ifFalse: [uri]) encoding: nil stream: stream ] InputSource class >> uri: aURI encoding: anEncodingName stream: aStream [ ^self new uri: aURI encoding: anEncodingName stream: aStream ] uri: aURI encoding: anEncodingName stream: aStream [ uri := aURI. encoding := anEncodingName. stream := aStream ] encoding [ ^encoding ] stream [ ^stream ] uri [ ^uri ] ] Object subclass: Attribute [ | name value | tag name value tag value'> Attribute class >> name: nm value: val [ ^self new name: nm value: val ] name: nm value: val [ name := nm isString ifTrue: [NodeTag new qualifier: '' ns: '' type: nm] ifFalse: [nm]. value := val ] tag: aTag [ name := aTag ] characterData [ ^self value ] expandedName [ ^name expandedName ] key [ ^name ] tag [ ^name ] value [ ^value ] value: aValue [ value := aValue ] printCanonicalOn: aStream [ aStream nextPutAll: self tag asString , '="'. self printCanonical: value on: aStream. aStream nextPutAll: '"' ] printOn: aStream [ self printCanonicalOn: aStream ] simpleDescription [ ^'@' , self key ] isAttribute [ ^true ] isLike: aNode [ ^self class == aNode class and: [self tag isLike: aNode tag] ] ] Magnitude subclass: NodeTag [ | namespace type qualifier | A URI in string form that uniquely identifies the XML namespace to which the type belongs. May be an empty string if the type is outside all namespaces. type Name of tag, used to indicate element or attribute type. qualifier In XML documents, the namespace is mapped to a qualifier, which is used as a prefix for the type. The namespace is assumed to be unique across all documents, but is quite clumsy. The qualifier is not unique across documents, but is unambiguous at the point where it is used and is short enough to be convenient. The qualifier may be the empty string if the namespace is empty or if the namespace is the current default namespace.'> NodeTag class >> qualifier: q ns: ns type: typeStr [ ^self new qualifier: q ns: ns type: typeStr ] NodeTag class >> name: name ns: ns type: typeStr [ ^self new name: name ns: ns type: typeStr ] name: name ns: ns type: typeStr [ namespace := ns. type := typeStr. qualifier := (name includes: $:) ifTrue: [name copyUpTo: $:] ifFalse: ['']. ] qualifier: q ns: ns type: typeStr [ namespace := ns. type := typeStr. qualifier := q ] expandedName [ ^namespace isEmpty ifTrue: [type] ifFalse: [namespace , '#' , type] ] namespace [ ^namespace ] qualifier [ ^qualifier ] type [ ^type ] name [ ^qualifier isEmpty ifTrue: [type] ifFalse: [qualifier , ':' , type] ] asString [ ^self name ] isLike: aName [ ^aName isString ifTrue: [namespace isEmpty and: [type = aName]] ifFalse: [namespace = aName namespace and: [type = aName type]] ] printOn: aStream [ aStream nextPutAll: '{' , self asString , '}' ] < aNodeTag [ "Answer whether the receiver is less than the argument." ^self asString < aNodeTag asString ] = aNodeTag [ ^self class = aNodeTag class and: [self type = aNodeTag type and: [self namespace == nil ifTrue: [self qualifier = aNodeTag qualifier] ifFalse: [self namespace = aNodeTag namespace]]] ] hash [ "The hash value is not dependent on either the namespace or the qualifier, but equality is dependent on this. We think this will not be a problem because collisions between tags that have the same type but different namespaces or qualifiers should be rare in the majority of cases." ^self type hash ] ] smalltalk-3.2.5/packages/xml/saxdriver/stamp-classes0000644000175000017500000000000012123404352017477 00000000000000smalltalk-3.2.5/packages/xml/saxdriver/package.xml0000644000175000017500000000020712123404352017123 00000000000000 XML-SAXDriver XML SAX.st Events.st smalltalk-3.2.5/packages/xml/pullparser/0000755000175000017500000000000012130456022015250 500000000000000smalltalk-3.2.5/packages/xml/pullparser/Makefile.frag0000644000175000017500000000033412123404352017547 00000000000000XML-PullParser_FILES = \ packages/xml/pullparser/XMLPullParser.st $(XML-PullParser_FILES): $(srcdir)/packages/xml/pullparser/stamp-classes: $(XML-PullParser_FILES) touch $(srcdir)/packages/xml/pullparser/stamp-classes smalltalk-3.2.5/packages/xml/pullparser/XMLPullParser.st0000644000175000017500000005373612123404352020231 00000000000000"====================================================================== | | SAX event-based pull parser | | ======================================================================" "====================================================================== | | Copyright (c) 2009, Antony Blakey | All rights reserved. | | Redistribution and use in source and binary forms, with or without | modification, are permitted provided that the following conditions | are met: | * Redistributions of source code must retain the above copyright | notice, this list of conditions and the following disclaimer. | * Redistributions in binary form must reproduce the above copyright | notice, this list of conditions and the following disclaimer in the | documentation and/or other materials provided with the distribution. | * Neither the name of Antony Blakey nor the names of its contributors | may be used to endorse or promote products derived derived from | this software without specific prior written permission. | | THIS SOFTWARE IS PROVIDED 'AS IS' AND ANY EXPRESS OR IMPLIED WARRANTIES, | INCLUDING, BUT NOT LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY | AND FITNESS FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL | ANTONY BLAKEY BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, | SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED | TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR | PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF | LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING | NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF THIS | SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. | ======================================================================" Error subclass: XMLStructureException [ ] Notification subclass: XMLResolveEntityNotification [ | publicID systemID | publicID [ ^publicID ] publicID: aString [ publicID := aString ] systemID [ ^systemID ] systemID: aString [ systemID := aString ] ] SAXParser class extend [ pullParserOn: source [ ^XMLGenerativePullParser on: source for: self ] ] Stream subclass: XMLPullParser [ | needComments needPrefixMappingEvents needCdataDelimiters needDTDEvents | XMLPullParser class >> new [ ^super new initialize ] XMLPullParser class >> onFile: aFilename [ ^self on: (FileStream open: aFilename mode: FileStream read) ] XMLPullParser class >> onString: aString [ ^self on: aString readStream ] XMLPullParser class >> on: source [ ^SAXParser defaultParserClass pullParserOn: source ] advance [ self subclassResponsibility ] at: attName [ ^self current at: attName ] at: attName ifFound: aFoundBlock ifNone: aBlock [ ^self current at: attName ifFound: aFoundBlock ifNone: aBlock ] at: attName ifNone: aBlock [ ^self current at: attName ifNone: aBlock ] atEnd [ ^self isEndDocument ] collect: tagName peek: aBlock [ | result | result := OrderedCollection new. self while: tagName peek: [result add: (self matchAnyPeek: aBlock)]. ^result ] collect: tagName take: aBlock [ | result | result := OrderedCollection new. self while: tagName peek: [result add: (self matchAnyTake: aBlock)]. ^result ] collectAnyPeek: aBlock [ | result | result := OrderedCollection new. self whileAnyPeek: [result add: (self matchAnyPeek: aBlock)]. ^result ] collectAnyTake: aBlock [ | result | result := OrderedCollection new. self whileAnyTake: [result add: (self matchAnyPeek: aBlock)]. ^result ] consumeEndTag [ self mustBeEndTag. self next ] consumeEndTag: tagName [ self mustBeEndTag: tagName. self next ] consumeStartDocument [ self mustBeStartDocument. self next ] consumeStartTag [ self mustBeStartTag. self next ] consumeStartTag: tagName [ self mustBeStartTag: tagName. self next ] consumeText [ | text | self isText ifTrue: [self mustBeText. text := self current text. self next. ^text] ifFalse: [^''] ] current [ self subclassResponsibility ] do: aBlock [ self atEnd ifTrue: [^self]. aBlock value: self current. super do: aBlock ] doctypeName [ ^self isStartDoctypeDecl ifTrue: [| name | name := self current name. self needDTDEvents: false. self next. name asString] ifFalse: [nil] ] if: tagName peek: aBlock [ (self is: tagName) ifTrue: [self matchAnyPeek: aBlock] ] if: tagName peek: aBlock else: elseBlock [ ^(self is: tagName) ifTrue: [self matchAnyPeek: aBlock] ifFalse: [elseBlock value] ] if: tagName take: aBlock [ (self is: tagName) ifTrue: [self matchAnyTake: aBlock] ] if: tagName take: aBlock else: elseBlock [ ^(self is: tagName) ifTrue: [self matchAnyTake: aBlock] ifFalse: [elseBlock value] ] ifAnyPeek: aBlock [ self isStartTag ifTrue: [self matchAnyPeek: aBlock] ] ifAnyPeek: aBlock else: elseBlock [ ^self isStartTag ifTrue: [self matchAnyPeek: aBlock] ifFalse: [elseBlock value] ] ifAnyTake: aBlock [ self isStartTag ifTrue: [self matchAnyTake: aBlock] ] ifAnyTake: aBlock else: elseBlock [ ^self isStartTag ifTrue: [self matchAnyTake: aBlock] ifFalse: [elseBlock value] ] is: tagName [ ^self isStartTag: tagName ] isComment [ ^self current isComment ] isEndCdataSection [ ^self current isEndCdataSection ] isEndDocument [ ^self current isEndDocument ] isEndPrefixMapping [ ^self current isEndPrefixMapping ] isEndTag [ ^self current isEndTag ] isEndTag: aStringOrNodeTag [ ^self current isEndTag: aStringOrNodeTag ] isNotationDecl [ ^self current isNotationDecl ] isSkippedEntity [ ^self current isSkippedEntity ] isPI [ ^self current isPI ] isPI: aString [ ^self current isPI: aString ] isStartCdataSection [ ^self current isStartCdataSection ] isStartPrefixMapping [ ^self current isStartPrefixMapping ] isStartDoctypeDecl [ ^self current isStartDoctypeDecl ] isStartDoctypeDecl: aString [ ^self current isStartDoctypeDecl: aString ] isStartDocument [ ^self current isStartDocument ] isStartTag [ ^self current isStartTag ] isStartTag: aStringOrNodeTag [ ^self current isStartTag: aStringOrNodeTag ] isText [ ^self current isText ] isUnparsedEntityDecl [ ^self current isUnparsedEntityDecl ] match: tagName peek: aBlock [ self mustBeStartTag: tagName. ^self matchAnyPeek: aBlock ] match: tagName take: aBlock [ self mustBeStartTag: tagName. ^self matchAnyTake: aBlock ] matchAnyPeek: aBlock [ self mustBeStartTag. ^aBlock numArgs = 1 ifTrue: [aBlock value: self current] ifFalse: [aBlock value] ] matchAnyTake: aBlock [ | result | result := aBlock numArgs = 1 ifTrue: [| tag | tag := self current. self consumeStartTag. aBlock value: tag] ifFalse: [self consumeStartTag. aBlock value]. self consumeEndTag. ^result ] mustBeEndDocument [ self isEndDocument ifFalse: [XMLStructureException signal: 'Expected end of document'] ] mustBeEndTag [ self isEndTag ifFalse: [XMLStructureException signal: 'Expected end tag'] ] mustBeEndTag: tagName [ (self isEndTag: tagName) ifFalse: [XMLStructureException signal: 'Expected end tag: ' , tagName] ] mustBePI [ self isPI ifFalse: [XMLStructureException signal: 'Expected processing instruction'] ] mustBePI: tagName [ (self isPI: tagName) ifFalse: [XMLStructureException signal: 'Expected processing instruction: ' , tagName] ] mustBeStartDocument [ self isStartDocument ifFalse: [XMLStructureException signal: 'Expected start of document'] ] mustBeStartTag [ self isStartTag ifFalse: [XMLStructureException signal: 'Expected start tag'] ] mustBeStartTag: tagName [ (self isStartTag: tagName) ifFalse: [XMLStructureException signal: 'Expected start tag: ' , tagName] ] mustBeText [ self isText ifFalse: [XMLStructureException signal: 'Expected text'] ] next [ | event | self atEnd ifTrue: [ ^self pastEnd ]. [ self advance. (event := self current) neededBy: self ] whileFalse. ^event ] pastEnd [ ^self current ] serializeTagContentsTo: serializer [ self consumeStartTag. self serializeUntilEndTagTo: serializer. self consumeEndTag ] serializeTagTo: serializer [ self mustBeStartTag. self current serializeTo: serializer. self consumeStartTag. self serializeUntilEndTagTo: serializer. self current serializeTo: serializer. self consumeEndTag ] serializeUntilEndTagTo: serializer [ [self isEndTag] whileFalse: [| event | event := self current. event isText ifTrue: [event serializeTo: serializer. self next] ifFalse: [event isStartTag ifTrue: [self serializeTagTo: serializer] ifFalse: [XMLStructureException signal: 'Unexpected element']]] ] skip: tagName [ self consumeStartTag: tagName. [self isEndTag] whileFalse: [| event | event := self current. event isText ifTrue: [self next] ifFalse: [event isStartTag ifTrue: [self skipAny] ifFalse: [XMLStructureException signal: 'Unexpected element']]]. self consumeEndTag: tagName ] skipAny [ self consumeStartTag. [self isEndTag] whileFalse: [| event | event := self current. event isText ifTrue: [self next] ifFalse: [event isStartTag ifTrue: [self skipAny] ifFalse: [XMLStructureException signal: 'Unexpected element']]]. self consumeEndTag ] skipIf: tagName [ (self is: tagName) ifTrue: [self skipAny] ] skipIfAny [ self isStartTag ifTrue: [self skipAny] ] skipWhile: tagName [ [self is: tagName] whileTrue: [self skipAny] ] skipWhileAny [ [self isStartTag] whileTrue: [self skipAny] ] tag [ ^self current tag ] text [ | text s | self isText ifFalse: [ ^'' ]. text := self current text. self next isText ifFalse: [ ^text ]. s := WriteStream with: text. [s nextPutAll: self current text. self next isText] whileTrue. ^s contents ] textIf: tagName [ ^self if: tagName take: [self text] else: [''] ] textIf: tagName else: aBlock [ ^self if: tagName take: [self text] else: [aBlock value] ] textIfAny [ ^self ifAnyTake: [self text] else: [''] ] textIfAnyElse: aBlock [ ^self ifAnyTake: [self text] else: [aBlock value] ] textOf: tagName [ ^self match: tagName take: [self text] ] textOfAny [ ^self matchAnyTake: [self text] ] while: tagName peek: aBlock [ [self is: tagName] whileTrue: [self matchAnyPeek: aBlock] ] while: tagName peek: aBlock separatedBy: sepBlock [ | doneFirst | doneFirst := false. [self is: tagName] whileTrue: [doneFirst ifTrue: [sepBlock value] ifFalse: [doneFirst := true]. self matchAnyPeek: aBlock] ] while: tagName take: aBlock [ [self is: tagName] whileTrue: [self matchAnyTake: aBlock] ] while: tagName take: aBlock separatedBy: sepBlock [ | doneFirst | doneFirst := false. [self is: tagName] whileTrue: [| tag | tag := self current. self consumeStartTag. doneFirst ifTrue: [sepBlock value] ifFalse: [doneFirst := true]. aBlock numArgs = 1 ifTrue: [aBlock value: tag] ifFalse: [aBlock value]. self consumeEndTag] ] whileAnyPeek: aBlock [ [self isStartTag] whileTrue: [self matchAnyPeek: aBlock] ] whileAnyPeek: aBlock separatedBy: sepBlock [ | doneFirst | doneFirst := false. [self isStartTag] whileTrue: [| tag | tag := self current. doneFirst ifTrue: [sepBlock value] ifFalse: [doneFirst := true]. aBlock numArgs = 1 ifTrue: [aBlock value: tag] ifFalse: [aBlock value]] ] whileAnyTake: aBlock [ [self isStartTag] whileTrue: [self matchAnyTake: aBlock] ] whileAnyTake: aBlock separatedBy: sepBlock [ | doneFirst | doneFirst := false. [self isStartTag] whileTrue: [| tag | tag := self current. self consumeStartTag. doneFirst ifTrue: [sepBlock value] ifFalse: [doneFirst := true]. aBlock numArgs = 1 ifTrue: [aBlock value: tag] ifFalse: [aBlock value]. self consumeEndTag] ] validate [ ^false ] validate: aBoolean [ aBoolean ifTrue: [ self error: 'this parser does not support XML validation' ] ] initialize [ needComments := needPrefixMappingEvents := needCdataDelimiters := false. needDTDEvents := true. ] needCdataDelimiters [ ^needCdataDelimiters ] needCdataDelimiters: aBoolean [ needCdataDelimiters := aBoolean ] needComments [ ^needComments ] needComments: aBoolean [ needComments := aBoolean ] needDTDEvents [ ^needDTDEvents ] needDTDEvents: aBoolean [ needDTDEvents := aBoolean ] needPrefixMappingEvents [ ^needPrefixMappingEvents ] needPrefixMappingEvents: aBoolean [ needPrefixMappingEvents := aBoolean ] ] SAXEvent extend [ neededBy: aParser [ ^true ] ] SAXEndCdataSection extend [ neededBy: aParser [ ^aParser needCdataDelimiters ] ] SAXStartCdataSection extend [ neededBy: aParser [ ^aParser needCdataDelimiters ] ] SAXUnparsedEntityDecl extend [ neededBy: aParser [ ^aParser needDTDEvents ] ] SAXNotationDecl extend [ neededBy: aParser [ ^aParser needDTDEvents ] ] SAXEndDoctypeDecl extend [ neededBy: aParser [ ^aParser needDTDEvents ] ] SAXStartDoctypeDecl extend [ neededBy: aParser [ ^aParser needDTDEvents ] ] SAXComment extend [ neededBy: aParser [ ^aParser needComments ] ] SAXEndPrefixMapping extend [ neededBy: aParser [ ^aParser needPrefixMappingEvents ] ] SAXStartPrefixMapping extend [ neededBy: aParser [ ^aParser needPrefixMappingEvents ] ] SAXDriver subclass: SAXEventGenerator [ | generator | SAXEventGenerator class >> on: aGenerator [ ^super new generator: aGenerator ] comment: aString from: start to: stop [ generator yield: (SAXComment text: aString from: start to: stop) ] characters: aString from: start to: stop [ generator yield: (SAXText text: aString from: start to: stop) ] endCdataSection [ generator yield: SAXEndCdataSection new ] endDoctypeDecl [ generator yield: SAXEndDoctypeDecl new ] endDocument [ generator yield: SAXEndDocument new ] endElement: namespaceURI localName: localName qName: name [ "indicates the end of an element. See startElement" | tag | tag := NodeTag name: name ns: namespaceURI type: localName. generator yield: (SAXEndTag tag: tag) ] endPrefixMapping: prefix [ generator yield: (SAXEndPrefixMapping prefix: prefix) ] processingInstruction: targetString data: dataString [ generator yield: (SAXProcessingInstruction target: targetString data: dataString) ] skippedEntity: aString [ generator yield: (SAXSkippedEntity name: aString) ] startCdataSection [ generator yield: SAXStartCdataSection new ] startDoctypeDecl: doctypeName publicID: publicID systemID: systemID hasInternalSubset: aBoolean [ generator yield: (SAXStartDoctypeDecl name: doctypeName publicID: publicID systemID: systemID hasInternalSubset: aBoolean) ] startDocument [ generator yield: SAXStartDocument new ] startElement: namespaceURI localName: localName qName: name attributes: attrArray [ | tag attributes | tag := NodeTag name: name ns: namespaceURI type: localName. generator yield: (SAXStartTag tag: tag attributesArray: attrArray) ] startPrefixMapping: prefix uri: uri [ generator yield: (SAXStartPrefixMapping prefix: prefix uri: uri) ] notationDecl: nameString publicID: publicIDString systemID: systemIDString [ generator yield: (SAXNotationDecl name: nameString publicID: publicIDString systemID: systemIDString) ] unparsedEntityDecl: name publicID: publicID systemID: systemID notationName: notation [ generator yield: (SAXUnparsedEntityDecl name: name publicID: publicID systemID: systemID notationName: notation) ] resolveEntity: publicID systemID: systemID [ ^XMLResolveEntityNotification new publicID: publicID; systemID: systemID; signal ] generator: aGenerator [ generator := aGenerator. ] ] XMLPullParser subclass: XMLGenerativePullParser [ | parser generator | XMLGenerativePullParser class >> on: source [ ^self on: source for: SAXParser defaultParserClass ] XMLGenerativePullParser class >> on: source for: aParserClass [ ^self onParser: (aParserClass on: source) ] XMLGenerativePullParser class >> onParser: aParser [ | class | ^super new initialize: aParser; yourself ] current [ ^generator peek ] initialize: aParser [ parser := aParser. generator := Generator on: [ :g | parser saxDriver: (SAXEventGenerator on: g). parser scanDocument ]. ] validate [ ^parser validate ] validate: aBoolean [ parser validate: aBoolean ] advance [ ^generator next ] ] smalltalk-3.2.5/packages/xml/pullparser/stamp-classes0000644000175000017500000000000012123404352017661 00000000000000smalltalk-3.2.5/packages/xml/pullparser/package.xml0000644000175000017500000000047112123404352017310 00000000000000 XML-PullParser XML XML-SAXDriver XML-SAXParser XML-Parser XML-ParserTests XML.XMLPullParserTest XMLPullParser.st smalltalk-3.2.5/packages/xml/xpath/0000755000175000017500000000000012130456023014204 500000000000000smalltalk-3.2.5/packages/xml/xpath/Makefile.frag0000644000175000017500000000025212123404352016501 00000000000000XPath_FILES = \ packages/xml/xpath/XPath.st $(XPath_FILES): $(srcdir)/packages/xml/xpath/stamp-classes: $(XPath_FILES) touch $(srcdir)/packages/xml/xpath/stamp-classes smalltalk-3.2.5/packages/xml/xpath/XPath.st0000644000175000017500000022547212123404352015534 00000000000000"====================================================================== | | VisualWorks XPath Framework | | ======================================================================" "====================================================================== | | Copyright (c) 2000, 2002 Cincom, Inc. | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" Namespace current: XML [ Object subclass: XPathNodeContext [ | documentOrder nodes index node baseNode variables | XPathNodeContext class >> new [ ^super new initialize ] add: aNode [ nodes add: aNode ] addAll: collection [ nodes addAll: collection ] addNodeSet: nodeSet [ nodes addAll: nodeSet unsortedNodes ] addToXPathHolder: anAssociation for: aNodeContext [ self error: 'Should not happen--a NodeSet is being processed as if it were a single XML node' ] select: aPattern [ | result val | aPattern xpathMayRequireSortTopLevel ifTrue: [self checkSorted] ifFalse: [self checkOrdered]. result := self copy. self reset. [self atEnd] whileFalse: [val := aPattern xpathEvalIn: self next. (val xpathIsNumber ifTrue: [val = self index] ifFalse: [val xpathAsBoolean]) ifTrue: [result add: self node]]. ^result ] selectMatch: aPattern [ | result | result := self copy. self reset. [self atEnd] whileFalse: [(aPattern match: self next) ifTrue: [result add: self node]]. ^result ] asSingleNode [ ^(self copy) add: self node; yourself ] copy [ ^self shallowCopy postCopy ] postCopy [ nodes := IdentitySet new. index := 0. node := nil. documentOrder := true ] atEnd [ ^index = nodes size ] next [ index = nodes size ifTrue: [^nil]. self index: index + 1. node := nodes at: index. ^self ] reset [ index := 0. node := nil ] baseNode [ ^baseNode ] baseNode: aNode [ baseNode := aNode ] documentOrder [ documentOrder := true ] index [ ^index ] index: n [ self checkSorted. (n < 1 or: [n > nodes size]) ifTrue: [self error: 'Index out of bounds']. index := n. node := nodes at: n ] indexForNode: aNode [ self checkSorted. index := nodes identityIndexOf: aNode. index = 0 ifTrue: [self error: 'No such node found in the list']. node := aNode ] inverseDocumentOrder [ documentOrder := false ] node [ ^node ] size [ ^nodes size ] sort: aBlock [ nodes := nodes asSortedCollection: aBlock ] sortedNodes [ ^nodes asSortedCollection: [:n1 :n2 | n1 precedes: n2] ] unsortedNodes [ ^nodes ] variables [ ^variables ] variables: aDictionary [ variables := aDictionary ] checkOrdered [ nodes class == IdentitySet ifTrue: [nodes := nodes asArray] ] checkSorted [ nodes class == IdentitySet ifTrue: [nodes size < 4 ifTrue: [nodes := documentOrder ifTrue: [nodes asSortedCollection: [:n1 :n2 | n1 precedes: n2]] ifFalse: [nodes asSortedCollection: [:n1 :n2 | n2 precedes: n1]]] ifFalse: [nodes := nodes asArray collect: [:nd | XPathSortingVector fromXmlNode: nd]. nodes := documentOrder ifTrue: [nodes asSortedCollection: [:n1 :n2 | n1 <= n2]] ifFalse: [nodes asSortedCollection: [:n1 :n2 | n2 <= n1]]. nodes := nodes collect: [:nd | nd value]]] ] ensureSorted [ nodes class == IdentitySet ifFalse: [self error: 'This collection was already sorted once and may not be in correct sort order']. self checkSorted ] initialize [ nodes := IdentitySet new. documentOrder := true ] contains: aBlock [ | match | match := nodes detect: aBlock ifNone: []. ^match notNil ] xpathIsNodeSet [ ^true ] printOn: aStream [ self basicPrintOn: aStream ] sum [ ^nodes inject: 0.0 into: [:i :nd | i + nd xpathStringData xpathAsNumber] ] xpathAsBoolean [ ^self size > 0 ] xpathAsNumber [ ^self xpathAsString xpathAsNumber ] xpathAsString [ | list | nodes size = 0 ifTrue: [^'']. list := nodes asSortedCollection: [:n1 :n2 | n1 precedes: n2]. ^list first xpathStringData ] xpathCompareEquality: aData using: aBlock [ aData isString ifTrue: [^nodes contains: [:nd | aBlock value: nd xpathStringData value: aData]]. aData xpathIsNumber ifTrue: [^nodes contains: [:nd | aBlock value: nd xpathStringData xpathAsNumber value: aData]]. aData xpathIsBoolean ifTrue: [^nodes contains: [:nd | aBlock value: nd xpathStringData xpathAsBoolean value: aData]]. aData xpathIsNodeSet ifTrue: [^nodes contains: [:nd1 | aData unsortedNodes contains: [:nd2 | aBlock value: nd1 xpathStringData value: nd2 xpathStringData]]]. self error: 'Can''t compare a %1 with a node set' % {aData class} ] xpathCompareOrder: aData using: aBlock [ ^aData xpathIsNodeSet ifTrue: [self unsortedNodes contains: [:nd1 | | v | v := nd1 xpathStringData xpathAsNumber. aData unsortedNodes contains: [:nd2 | aBlock value: v value: nd2 xpathStringData xpathAsNumber]]] ifFalse: [| v | v := aData xpathAsNumber. self unsortedNodes contains: [:nd | aBlock value: nd xpathStringData xpathAsNumber value: v]] ] ] ] Namespace current: XML [ ReadStream subclass: XPathReadStream [ pastEnd [ "The receiver has attempted to read past the end, answer nil." ^nil ] ] ] Namespace current: XML [ Object subclass: XPathExpression [ | predicates child | XPathExpression class >> new [ ^super new initialize ] XPathExpression class >> notANumber [ ^FloatD nan ] XPathExpression class >> stringToNumber: aString [ | s foundDigit numerator denominator ch | s := aString readStream. s skipSeparators. foundDigit := false. numerator := 0. denominator := 1. [(ch := s next) notNil and: [ch isDigit]] whileTrue: [numerator := numerator * 10 + ch digitValue. foundDigit := true]. ch = $. ifTrue: [[(ch := s next) notNil and: [ch isDigit]] whileTrue: [numerator := numerator * 10 + ch digitValue. denominator := denominator * 10. foundDigit := true]]. (ch == nil or: [ch isSeparator]) ifFalse: [^self notANumber]. s skipSeparators. s atEnd ifFalse: [^self notANumber]. foundDigit ifFalse: [^self notANumber]. ^numerator / denominator + 0.0 ] addPredicate: aPredicate [ predicates := predicates copyWith: aPredicate ] asUnion [ ^XPathUnion new add: self ] child [ ^child ] child: aStep [ child := aStep ] enumerate: aBlock [ aBlock value: self. predicates do: [:p | p enumerate: aBlock]. child enumerate: aBlock ] predicates [ ^predicates ] xpathUsedVarNames [ | list | list := OrderedCollection new. self enumerate: [:exp | (exp isKindOf: XPathVariable) ifTrue: [list add: exp name]]. ^list ] baseValueIn: aNodeContext [ self subclassResponsibility ] isMatchFor: anXmlNode [ ^self isLocalMatchFor: anXmlNode ] match: aNodeContext [ | base | base := self. [base child == nil] whileFalse: [base := base child]. ^base simpleMatchFor: aNodeContext node isComplex: false do: [:root :complex | | ns found | complex not or: [ns := (aNodeContext copy) add: root; index: 1. found := false. self valueIn: ns do: [:nd | nd == aNodeContext node ifTrue: [found := true]]. found]] ] simpleMatchFor: anXmlNode isComplex: complex do: aBlock [ ^self subclassResponsibility ] valueIn: aNodeContext do: aBlock [ | result | result := self baseValueIn: aNodeContext. result xpathIsNodeSet ifTrue: [1 to: predicates size do: [:i | result := result select: (predicates at: i)]. result reset. [result atEnd] whileFalse: [child valueIn: result next do: aBlock]] ifFalse: [(predicates isEmpty and: [child isTerminator]) ifTrue: [aBlock value: result] ifFalse: [self error: 'The expression %1 does not represent a node set']] ] xpathEvalIn: aNodeContext [ "This is private protocol--see #xpathValueIn: for the client protocol" | nc | nc := Association new. self valueIn: aNodeContext do: [:x | x addToXPathHolder: nc for: aNodeContext]. ^nc value == nil ifTrue: [aNodeContext copy] ifFalse: [nc value] ] xpathValueFor: anXmlNode variables: vars [ ^self xpathValueIn: ((XPathNodeContext new) add: anXmlNode; index: 1; variables: vars) ] xpathValueIn: aNodeContext [ "This is public protocol only--see #xpathEvalIn: for internal clients" aNodeContext baseNode: aNodeContext node. ^self xpathEvalIn: aNodeContext ] completeChildPrintOn: aStream [ self completePrintOn: aStream ] completePrintOn: aStream [ self printTestOn: aStream. predicates do: [:p | self printPredicate: p on: aStream]. self child isTerminator ifFalse: [aStream nextPut: $/]. self child completeChildPrintOn: aStream ] printOn: aStream [ self completePrintOn: aStream ] printPredicate: p on: aStream [ aStream nextPutAll: '['. aStream print: p. aStream nextPutAll: ']' ] printTestOn: aStream [ self subclassResponsibility ] initialize [ predicates := #(). child := XPathTerminator new. child parent: self ] xpathMayRequireNodeSet [ ^self subclassResponsibility ] xpathMayRequireNodeSetTopLevel [ ^self subclassResponsibility ] xpathMayRequireSort [ ^self subclassResponsibility ] xpathMayRequireSortTopLevel [ ^self subclassResponsibility ] ] ] Namespace current: XML [ XPathExpression subclass: XPathUnion [ | arguments | add: aNode [ arguments := arguments copyWith: aNode ] arguments [ ^arguments ] asUnion [ ^self ] enumerate: aBlock [ super enumerate: aBlock. arguments do: [:a | a enumerate: aBlock] ] baseValueIn: aNodeContext [ | nc | nc := aNodeContext copy documentOrder. 1 to: arguments size do: [:a | nc addNodeSet: ((arguments at: a) xpathEvalIn: aNodeContext)]. ^nc ] match: aNodeContext [ 1 to: arguments size do: [:a | ((arguments at: a) match: aNodeContext) ifTrue: [^true]]. ^false ] initialize [ super initialize. arguments := #() ] printTestOn: aStream [ arguments do: [:a | aStream print: a] separatedBy: [aStream nextPutAll: '|'] ] ] ] Namespace current: XML [ XPathExpression subclass: XPathStep [ | axisName baseTest namespace type parent | XPathStep class >> axisNames [ ^#() ] axisName [ ^axisName ] axisName: aName [ axisName := aName ] baseTest [ ^baseTest ] baseTest: aNodeTest [ baseTest := aNodeTest ] child [ ^child ] child: aStep [ child := aStep ] parent [ ^parent ] parent: aStep [ parent := aStep ] startOfPath [ | p | p := self. [p isStartOfPath] whileFalse: [p := p parent]. ^p ] hasComplexPredicate [ ^predicates inject: false into: [:b :exp | b or: [exp xpathMayRequireNodeSetTopLevel]] ] isStartOfPath [ ^parent == nil ] isTerminator [ ^false ] xpathMayRequireNodeSet [ ^false ] xpathMayRequireNodeSetTopLevel [ ^false ] xpathMayRequireSort [ ^false ] xpathMayRequireSortTopLevel [ ^false ] printTestOn: aStream [ aStream nextPutAll: self axisName , '::'. baseTest printOn: aStream ] ] ] Namespace current: XML [ XPathStep subclass: XPathParentNode [ XPathParentNode class >> axisNames [ ^#('parent') ] baseValueIn: aNodeContext [ | result | result := aNodeContext copy documentOrder. (baseTest match: aNodeContext node parent) ifTrue: [result add: aNodeContext node parent]. ^result ] ] ] Namespace current: XML [ XPathStep subclass: XPathPrecedingNode [ XPathPrecedingNode class >> axisNames [ ^#('preceding') ] baseValueIn: aNodeContext [ | nd nc | nd := aNodeContext node. nc := aNodeContext copy inverseDocumentOrder. self from: nd do: [:nd1 | (baseTest match: nd1) ifTrue: [nc add: nd1]]. ^nc ] from: aNode do: aBlock [ | current stack ignoreAll | ignoreAll := IdentitySet new. stack := OrderedCollection new. current := aNode. [ignoreAll add: current. current isDocument not] whileTrue: [stack addFirst: current parent -> (current parent children indexOf: current). current := current parent]. current := aNode. [current isDocument ifTrue: [^self] ifFalse: [stack last value = 1 ifTrue: [current := stack removeLast key] ifFalse: [stack last value: stack last value - 1. current := stack last key children at: stack last value. [current isElement and: [current children isEmpty not]] whileTrue: [stack add: current -> current children size. current := current children last]]]. (ignoreAll includes: current) ifFalse: [aBlock value: current]] repeat ] ] ] Namespace current: XML [ XPathStep subclass: XPathAncestorNode [ XPathAncestorNode class >> axisNames [ ^#('ancestor' 'ancestor-or-self') ] baseValueIn: aNodeContext [ | nd nc nextNode | nd := aNodeContext node. nc := aNodeContext copy inverseDocumentOrder. self axisName = 'ancestor-or-self' ifTrue: [nextNode := nd] ifFalse: [nextNode := nd parent]. [nextNode == nil] whileFalse: [(baseTest match: nextNode) ifTrue: [nc add: nextNode]. nextNode := nextNode parent]. ^nc ] ] ] Namespace current: XML [ XPathStep subclass: XPathChildNode [ XPathChildNode class >> axisNames [ ^#('child') ] baseValueIn: aNodeContext [ | nd nc | nd := aNodeContext node. nc := aNodeContext copy documentOrder. (nd isElement or: [nd isDocument]) ifFalse: [^nc]. aNodeContext node children do: [:childNode | (baseTest match: childNode) ifTrue: [nc add: childNode]]. ^nc ] simpleMatchFor: anXmlNode isComplex: complex do: aBlock [ | hasCP set | anXmlNode isAttribute ifTrue: [^false]. (baseTest match: anXmlNode) ifFalse: [^false]. (hasCP := self hasComplexPredicate) ifFalse: [set := XPathNodeContext new add: anXmlNode. 1 to: predicates size do: [:i | set := set select: (predicates at: i)]. set size = 0 ifTrue: [^false]]. parent == nil ifTrue: [^aBlock value: anXmlNode parent value: complex | hasCP]. ^parent simpleMatchFor: anXmlNode parent isComplex: complex | hasCP do: aBlock ] printTestOn: aStream [ axisName == nil ifTrue: [baseTest printOn: aStream] ifFalse: [super printTestOn: aStream] ] ] ] Namespace current: XML [ XPathStep subclass: XPathFollowingNode [ XPathFollowingNode class >> axisNames [ ^#('following') ] baseValueIn: aNodeContext [ | nd nc | nd := aNodeContext node. nc := aNodeContext copy documentOrder. self from: nd do: [:nd1 | (baseTest match: nd1) ifTrue: [nc add: nd1]]. ^nc ] from: aNode do: aBlock [ | current stack idx followChildren | current := aNode. stack := OrderedCollection new. current isDocument ifFalse: [[current parent isDocument not] whileTrue: [stack addFirst: current parent -> (current parent children indexOf: current). current := current parent]]. current := aNode. "By setting followChildren to false the first time only, we ignore all descendents of aNode." followChildren := false. [(followChildren and: [(current isElement or: [current isDocument]) and: [current children size > 0]]) ifTrue: [stack add: current -> 1. current := current children at: 1] ifFalse: [ [stack isEmpty ifTrue: [^self]. stack last key children size > stack last value] whileFalse: [current := stack removeLast key]. stack last value: (idx := stack last value + 1). current := stack last key children at: idx]. followChildren := true. aBlock value: current] repeat ] ] ] Namespace current: XML [ XPathExpression subclass: XPathVariable [ | name | baseValueIn: aNodeContext [ | var | var := aNodeContext variables at: self name ifAbsent: [self error: 'No binding found for the variable $%1' % {self name}]. ^var ] name [ ^name ] name: aName [ name := aName ] printTestOn: aStream [ aStream nextPutAll: '$' , name ] ] ] Namespace current: XML [ XPathExpression subclass: XPathFunction [ | name arguments valueBlock requiresSort requiresNodeSet | XPathFunction class [ | functions | ] XPathFunction class >> baseFunctions [ ^functions ] XPathFunction class >> initialize [ "XPathFunction initialize" functions == nil ifTrue: [functions := Dictionary new] ifFalse: [functions keys do: [:k | functions removeKey: k]]. self initializeBoolean. self initializeStrings. self initializeNodeSets. self initializeNumeric ] XPathFunction class >> initializeBoolean [ functions at: 'boolean' put: ((self new) name: 'boolean'; valueBlock: [:fn :ns | | ns2 | fn arguments size > 1 ifTrue: [self error: 'boolean() only takes one argument']. ns2 := fn arguments size = 1 ifTrue: [fn arguments first xpathEvalIn: ns] ifFalse: [ns asSingleNode]. ns2 xpathAsBoolean]). functions at: 'not' put: ((self new) name: 'not'; valueBlock: [:fn :ns | (fn arguments first xpathEvalIn: ns) xpathAsBoolean not]). functions at: 'true' put: true. functions at: 'false' put: false ] XPathFunction class >> initializeNodeSets [ functions at: 'count' put: ((self new) requiresNodeSet: true; name: 'count'; valueBlock: [:fn :ns | | ns2 | fn arguments size > 1 ifTrue: [self error: 'count() only takes one argument']. ns2 := fn arguments size = 1 ifTrue: [fn arguments first xpathEvalIn: ns] ifFalse: [ns asSingleNode]. ns2 xpathIsNodeSet ifFalse: [self error: 'count() requires a nodeset as an argument']. ns2 size]). functions at: 'position' put: ((self new) requiresNodeSet: true; requiresSort: true; name: 'position'; valueBlock: [:fn :ns | fn arguments size > 0 ifTrue: [self error: 'position() cannot take any arguments']. ns index]). functions at: 'last' put: ((self new) requiresNodeSet: true; name: 'last'; valueBlock: [:fn :ns | fn arguments size > 0 ifTrue: [self error: 'last() cannot take any arguments']. ns size]). functions at: 'local-name' put: ((self new) name: 'local-name'; valueBlock: [:fn :ns | | ns2 | fn arguments size > 1 ifTrue: [self error: 'local-name() only takes one argument']. ns2 := fn arguments size = 1 ifTrue: [fn arguments first xpathEvalIn: ns] ifFalse: [ns asSingleNode]. ns2 xpathIsNodeSet ifFalse: [self error: 'local-name() requires a nodeset as an argument']. ns2 documentOrder; index: 1. (ns2 node isElement or: [ns2 node isAttribute]) ifTrue: [ns2 node tag type] ifFalse: ['']]). functions at: 'namespace-uri' put: ((self new) name: 'namespace-uri'; valueBlock: [:fn :ns | | ns2 | fn arguments size > 1 ifTrue: [self error: 'namespace-uri() only takes one argument']. ns2 := fn arguments size = 1 ifTrue: [fn arguments first xpathEvalIn: ns] ifFalse: [ns asSingleNode]. ns2 xpathIsNodeSet ifFalse: [self error: 'namespace-uri() requires a nodeset as an argument']. ns2 documentOrder; index: 1. (ns2 node isElement or: [ns2 node isAttribute]) ifTrue: [ns2 node tag namespace] ifFalse: ['']]). functions at: 'name' put: ((self new) name: 'name'; valueBlock: [:fn :ns | | ns2 | fn arguments size > 1 ifTrue: [self error: 'name() only takes one argument']. ns2 := fn arguments size = 1 ifTrue: [fn arguments first xpathEvalIn: ns] ifFalse: [ns asSingleNode]. ns2 xpathIsNodeSet ifFalse: [self error: 'name() requires a nodeset as an argument']. ns2 documentOrder; index: 1. (ns2 node isElement or: [ns2 node isAttribute]) ifTrue: [ns2 node tag asString] ifFalse: ['']]). functions at: 'id' put: ((self new) name: 'id'; valueBlock: [:fn :ns | | ns2 | fn arguments size ~= 1 ifTrue: [self error: 'id() only takes one argument']. ns2 := fn arguments first xpathEvalIn: ns. ns2 := ns2 xpathAsString. ns copy add: (ns node document atID: ns2 ifAbsent: [self error: 'ID "' , ns2 , '" not found'])]). functions at: 'current' put: ((self new) requiresNodeSet: true; name: 'current'; valueBlock: [:fn :ns | fn arguments size > 0 ifTrue: [self error: 'current() takes no arguments']. (ns copy) add: ns baseNode; index: 1]) ] XPathFunction class >> initializeNumeric [ functions at: 'number' put: ((self new) name: 'number'; valueBlock: [:fn :ns | | ns2 | fn arguments size > 1 ifTrue: [self error: 'number() only takes one argument']. ns2 := fn arguments size = 1 ifTrue: [fn arguments first xpathEvalIn: ns] ifFalse: [ns asSingleNode]. ns2 xpathAsNumber]). functions at: 'round' put: ((self new) name: 'round'; valueBlock: [:fn :ns | fn arguments size ~= 1 ifTrue: [self error: 'round() only takes one argument']. (fn arguments first xpathEvalIn: ns) xpathAsNumber rounded]). functions at: 'floor' put: ((self new) name: 'floor'; valueBlock: [:fn :ns | fn arguments size ~= 1 ifTrue: [self error: 'floor() only takes one argument']. (fn arguments first xpathEvalIn: ns) xpathAsNumber floor]). functions at: 'ceiling' put: ((self new) name: 'ceiling'; valueBlock: [:fn :ns | fn arguments size ~= 1 ifTrue: [self error: 'ceiling() only takes one argument']. (fn arguments first xpathEvalIn: ns) xpathAsNumber ceiling]). functions at: 'sum' put: ((self new) name: 'sum'; valueBlock: [:fn :ns | fn arguments size ~= 1 ifTrue: [self error: 'sum() only takes one argument']. (fn arguments first xpathEvalIn: ns) sum]) ] XPathFunction class >> initializeStrings [ functions at: 'string' put: ((self new) name: 'string'; valueBlock: [:fn :ns | | ns2 | fn arguments size > 1 ifTrue: [self error: 'string() only takes one argument']. ns2 := fn arguments size = 1 ifTrue: [fn arguments first xpathEvalIn: ns] ifFalse: [ns asSingleNode]. ns2 xpathAsString]). functions at: 'concat' put: ((self new) name: 'concat'; valueBlock: [:fn :ns | | s | s := ''. fn arguments do: [:exp | s := s , (exp xpathEvalIn: ns) xpathAsString]. s]). functions at: 'contains' put: ((self new) name: 'contains'; valueBlock: [:fn :ns | | s1 s2 i | fn arguments size = 2 ifFalse: [self error: 'contains() takes two arguments']. s1 := (fn arguments at: 1) xpathEvalIn: ns. s2 := (fn arguments at: 2) xpathEvalIn: ns. i := s1 xpathAsString indexOfSubCollection: s2 xpathAsString startingAt: 1. i > 0]). functions at: 'translate' put: ((self new) name: 'translate'; valueBlock: [:fn :ns | | s1 s2 s3 | fn arguments size = 3 ifFalse: [self error: 'translate() takes three arguments']. s1 := (fn arguments at: 1) xpathEvalIn: ns. s2 := (fn arguments at: 2) xpathEvalIn: ns. s3 := (fn arguments at: 3) xpathEvalIn: ns. self translate: s1 xpathAsString from: s2 xpathAsString to: s3 xpathAsString]). functions at: 'string-length' put: ((self new) name: 'string-length'; valueBlock: [:fn :ns | | s1 | fn arguments size < 2 ifFalse: [self error: 'string-length() takes no more than 1 argument']. s1 := (fn arguments size = 0 ifTrue: [ns asSingleNode] ifFalse: [fn arguments first xpathEvalIn: ns]) xpathAsString. s1 size]). functions at: 'substring' put: ((self new) name: 'substring'; valueBlock: [:fn :ns | | s1 i1 i2 | (fn arguments size between: 2 and: 3) ifFalse: [self error: 'substring() takes two or three arguments']. s1 := ((fn arguments at: 1) xpathEvalIn: ns) xpathAsString. i1 := ((fn arguments at: 2) xpathEvalIn: ns) xpathAsNumber. i2 := fn arguments size = 2 ifTrue: [10000000000.0] ifFalse: [((fn arguments at: 3) xpathEvalIn: ns) xpathAsNumber]. i2 := (i1 + i2 - 1) rounded min: s1 size. i1 := i1 rounded max: 1. s1 copyFrom: i1 to: i2]). functions at: 'starts-with' put: ((self new) name: 'starts-with'; valueBlock: [:fn :ns | | s1 s2 | fn arguments size = 2 ifFalse: [self error: 'starts-with() takes two arguments']. s1 := ((fn arguments at: 1) xpathEvalIn: ns) xpathAsString. s2 := ((fn arguments at: 2) xpathEvalIn: ns) xpathAsString. (s1 indexOfSubCollection: s2 startingAt: 1) = 1]). functions at: 'substring-before' put: ((self new) name: 'substring-before'; valueBlock: [:fn :ns | | s1 s2 i | fn arguments size = 2 ifFalse: [self error: 'substring-before() takes two arguments']. s1 := ((fn arguments at: 1) xpathEvalIn: ns) xpathAsString. s2 := ((fn arguments at: 2) xpathEvalIn: ns) xpathAsString. i := s1 indexOfSubCollection: s2 startingAt: 1. i = 0 ifTrue: [''] ifFalse: [s1 copyFrom: 1 to: i - 1]]). functions at: 'substring-after' put: ((self new) name: 'substring-after'; valueBlock: [:fn :ns | | s1 s2 i | fn arguments size = 2 ifFalse: [self error: 'substring-after() takes two arguments']. s1 := ((fn arguments at: 1) xpathEvalIn: ns) xpathAsString. s2 := ((fn arguments at: 2) xpathEvalIn: ns) xpathAsString. i := s1 indexOfSubCollection: s2 startingAt: 1. i = 0 ifTrue: [''] ifFalse: [s1 copyFrom: i + s2 size to: s1 size]]). functions at: 'normalize-space' put: ((self new) name: 'normalize-space'; valueBlock: [:fn :ns | | ns2 | ns2 := fn arguments first xpathEvalIn: ns. ns2 := ns2 xpathAsString. self normalizeWhitespace: ns2]) ] XPathFunction class >> normalizeWhitespace: aString [ | ch str buffer space | str := aString readStream. buffer := String new writeStream. space := false. [str skipSeparators; atEnd] whileFalse: [space ifTrue: [buffer space]. [(ch := str next) notNil and: [ch isSeparator not]] whileTrue: [buffer nextPut: ch]. space := true]. ^buffer contents ] XPathFunction class >> translate: base from: src to: dest [ | dir result c | dir := IdentityDictionary new. src size to: 1 by: -1 do: [:i | dir at: (src at: i) put: (i > dest size ifTrue: [nil] ifFalse: [dest at: i])]. result := (String new: base size) writeStream. 1 to: base size do: [:i | c := base at: i. c := dir at: c ifAbsent: [c]. c == nil ifFalse: [result nextPut: c]]. ^result contents ] addArgument: arg [ arguments := arguments copyWith: arg ] arguments [ ^arguments ] enumerate: aBlock [ super enumerate: aBlock. self arguments do: [:i | i enumerate: aBlock] ] name [ ^name ] name: nm [ name := nm ] requiresNodeSet [ ^requiresNodeSet ] requiresNodeSet: bool [ requiresNodeSet := bool ] requiresSort [ ^requiresSort ] requiresSort: bool [ requiresSort := bool ] answersNumber [ ^#('sum' 'round' 'count' 'last' 'position' 'string-length' 'floor' 'ceiling') includes: self name ] xpathMayRequireNodeSet [ ^requiresNodeSet or: [arguments inject: false into: [:b :arg | b or: [arg xpathMayRequireNodeSet]]] ] xpathMayRequireNodeSetTopLevel [ ^self answersNumber or: [self xpathMayRequireNodeSet] ] xpathMayRequireSort [ ^requiresSort or: [arguments inject: false into: [:b :arg | b or: [arg xpathMayRequireSort]]] ] xpathMayRequireSortTopLevel [ ^self answersNumber or: [self xpathMayRequireSort] ] baseValueIn: aNodeContext [ ^valueBlock value: self value: aNodeContext ] initialize [ super initialize. arguments := #(). requiresSort := false. requiresNodeSet := false ] valueBlock: aBlock [ valueBlock := aBlock ] printTestOn: aStream [ aStream nextPutAll: name , '('. arguments do: [:a | aStream print: a] separatedBy: [aStream nextPutAll: ',']. aStream nextPutAll: ')' ] ] ] Namespace current: XML [ XPathStep subclass: XPathPrecedingSiblingNode [ XPathPrecedingSiblingNode class >> axisNames [ ^#('preceding-sibling') ] baseValueIn: aNodeContext [ | nd nc list i | nd := aNodeContext node. nc := aNodeContext copy inverseDocumentOrder. list := nd parent children. i := list identityIndexOf: nd. (list copyFrom: 1 to: i - 1) do: [:childNode | (baseTest match: childNode) ifTrue: [nc add: childNode]]. ^nc ] ] ] Namespace current: XML [ XPathStep subclass: XPathRoot [ baseValueIn: aNodeContext [ ^(aNodeContext copy) documentOrder; add: aNodeContext node document ] simpleMatchFor: anXmlNode isComplex: complex do: aBlock [ ^anXmlNode isDocument and: [aBlock value: anXmlNode value: complex] ] completePrintOn: aStream [ aStream nextPut: $/. self child completeChildPrintOn: aStream ] isStartOfPath [ ^true ] ] ] Namespace current: XML [ XPathExpression subclass: XPathBinaryExpression [ | operator argument1 argument2 valueBlock | XPathBinaryExpression class [ | operators | ] XPathBinaryExpression class >> initialize [ "XPathBinaryExpression initialize" operators := Dictionary new. self initializeBoolean. self initializeComparison. self initializeNumeric ] XPathBinaryExpression class >> initializeBoolean [ operators at: #and put: ((self new) operator: #and with: nil with: nil; valueBlock: [:exp :ns | | b1 b2 | b1 := (exp arg1 xpathEvalIn: ns) xpathAsBoolean. b2 := (exp arg2 xpathEvalIn: ns) xpathAsBoolean. b1 & b2]). operators at: #or put: ((self new) operator: #or with: nil with: nil; valueBlock: [:exp :ns | | b1 b2 | b1 := (exp arg1 xpathEvalIn: ns) xpathAsBoolean. b2 := (exp arg2 xpathEvalIn: ns) xpathAsBoolean. b1 | b2]) ] XPathBinaryExpression class >> initializeComparison [ operators at: #= put: ((self new) operator: #= with: nil with: nil; valueBlock: [:exp :ns | (exp arg1 xpathEvalIn: ns) xpathCompareEquality: (exp arg2 xpathEvalIn: ns) using: [:v1 :v2 | v1 = v2]]). operators at: #'!=' put: ((self new) operator: #'!=' with: nil with: nil; valueBlock: [:exp :ns | (exp arg1 xpathEvalIn: ns) xpathCompareEquality: (exp arg2 xpathEvalIn: ns) using: [:v1 :v2 | v1 ~= v2]]). operators at: #< put: ((self new) operator: #< with: nil with: nil; valueBlock: [:exp :ns | (exp arg1 xpathEvalIn: ns) xpathCompareOrder: (exp arg2 xpathEvalIn: ns) using: [:v1 :v2 | v1 < v2]]). operators at: #> put: ((self new) operator: #> with: nil with: nil; valueBlock: [:exp :ns | (exp arg1 xpathEvalIn: ns) xpathCompareOrder: (exp arg2 xpathEvalIn: ns) using: [:v1 :v2 | v1 > v2]]). operators at: #<= put: ((self new) operator: #<= with: nil with: nil; valueBlock: [:exp :ns | (exp arg1 xpathEvalIn: ns) xpathCompareOrder: (exp arg2 xpathEvalIn: ns) using: [:v1 :v2 | v1 <= v2]]). operators at: #>= put: ((self new) operator: #>= with: nil with: nil; valueBlock: [:exp :ns | (exp arg1 xpathEvalIn: ns) xpathCompareOrder: (exp arg2 xpathEvalIn: ns) using: [:v1 :v2 | v1 >= v2]]) ] XPathBinaryExpression class >> initializeNumeric [ operators at: #+ put: ((self new) operator: #+ with: nil with: nil; valueBlock: [:exp :ns | (exp arg1 xpathEvalIn: ns) xpathAsNumber + (exp arg2 xpathEvalIn: ns) xpathAsNumber]). operators at: #- put: ((self new) operator: #- with: nil with: nil; valueBlock: [:exp :ns | (exp arg1 xpathEvalIn: ns) xpathAsNumber - (exp arg2 xpathEvalIn: ns) xpathAsNumber]). operators at: #* put: ((self new) operator: #* with: nil with: nil; valueBlock: [:exp :ns | (exp arg1 xpathEvalIn: ns) xpathAsNumber * (exp arg2 xpathEvalIn: ns) xpathAsNumber]). operators at: #div put: ((self new) operator: #div with: nil with: nil; valueBlock: [:exp :ns | (exp arg1 xpathEvalIn: ns) xpathAsNumber / (exp arg2 xpathEvalIn: ns) xpathAsNumber]). operators at: #mod put: ((self new) operator: #mod with: nil with: nil; valueBlock: [:exp :ns | (exp arg1 xpathEvalIn: ns) xpathAsNumber rem: (exp arg2 xpathEvalIn: ns) xpathAsNumber]) ] XPathBinaryExpression class >> operator: op with: arg1 with: arg2 [ ^(operators at: op ifAbsent: [self error: 'Not implemented yet %1' % {op}]) copy operator: op with: arg1 with: arg2 ] arg1 [ ^argument1 ] arg2 [ ^argument2 ] enumerate: aBlock [ super enumerate: aBlock. self arg1 enumerate: aBlock. self arg2 enumerate: aBlock ] baseValueIn: aNodeContext [ ^valueBlock value: self value: aNodeContext ] operator: op with: arg1 with: arg2 [ operator := op. argument1 := arg1. argument2 := arg2 ] valueBlock: aBlock [ valueBlock := aBlock ] printTestOn: aStream [ argument1 printOn: aStream. aStream space; nextPutAll: operator; space. argument2 printOn: aStream ] xpathMayRequireNodeSet [ ^self arg1 xpathMayRequireNodeSet or: [self arg2 xpathMayRequireNodeSet] ] xpathMayRequireNodeSetTopLevel [ (#(#+ #- #* #div #mod) includes: operator) ifTrue: [^true]. (#(#= #'!=' #< #> #<= #>= #| #and #or) includes: operator) ifTrue: [^self arg1 xpathMayRequireNodeSet or: [self arg2 xpathMayRequireNodeSet]]. self notYetImplementedError ] xpathMayRequireSort [ ^self arg1 xpathMayRequireSort or: [self arg2 xpathMayRequireSort] ] xpathMayRequireSortTopLevel [ (#(#+ #- #* #div #mod) includes: operator) ifTrue: [^true]. (#(#= #'!=' #< #> #<= #>= #| #and #or) includes: operator) ifTrue: [^self arg1 xpathMayRequireSort or: [self arg2 xpathMayRequireSort]]. self notYetImplementedError ] ] ] Namespace current: XML [ Array subclass: XPathSortingVector [ | value | XPathSortingVector class >> fromXmlNode: aNode [ | list node | list := OrderedCollection new. node := aNode. [node isDocument] whileFalse: [list addFirst: (node parent children identityIndexOf: node ifAbsent: [0]). node := node parent]. ^(self withAll: list) value: aNode ] <= aVector [ | min v1 v2 | min := self size min: aVector size. 1 to: min do: [:i | v1 := self at: i. v2 := aVector at: i. v1 = v2 ifFalse: [^v1 < v2]]. ^self size <= aVector size ] value [ ^value ] value: aNode [ value := aNode ] ] ] Namespace current: XML [ XPathStep subclass: XPathFollowingSiblingNode [ XPathFollowingSiblingNode class >> axisNames [ ^#('following-sibling') ] baseValueIn: aNodeContext [ | nd nc list i | nd := aNodeContext node. nc := aNodeContext copy documentOrder. list := nd parent children. i := list identityIndexOf: nd. (list copyFrom: i + 1 to: list size) do: [:childNode | (baseTest match: childNode) ifTrue: [nc add: childNode]]. ^nc ] ] ] Namespace current: XML [ Object subclass: XPathNodeTest [ isTrivial [ ^false ] ] ] Namespace current: XML [ XPathNodeTest subclass: XPathTypedNodeTest [ | typeName value | isTrivial [ ^typeName = 'node' ] match: anXmlNode [ typeName = 'node' ifTrue: [^true]. typeName = 'text' ifTrue: [^anXmlNode isText]. typeName = 'comment' ifTrue: [^anXmlNode isComment]. typeName = 'processing-instruction' ifTrue: [^anXmlNode isProcessingInstruction and: [value == nil or: [value = anXmlNode name]]]. self notYetImplementedError ] printOn: aStream [ aStream nextPutAll: typeName , '('. value == nil ifFalse: [aStream nextPutAll: value]. aStream nextPutAll: ')' ] type: aString [ typeName := aString. (#('comment' 'text' 'node' 'processing-instruction') includes: typeName) ifFalse: [self error: 'A node test must be one of comment, text, node, or propcessing-instruction'] ] value: aString [ value := aString ] ] ] Namespace current: XML [ XPathNodeTest subclass: XPathTaggedNodeTest [ | namespace qualifier type | match: anXmlNode [ (anXmlNode isElement or: [anXmlNode isAttribute]) ifFalse: [^false]. namespace == nil ifFalse: [namespace = anXmlNode tag namespace ifFalse: [^false]]. ^type = #* or: [type = anXmlNode tag type] ] namespace [ ^namespace ] namespace: ns [ namespace := ns = '' ifTrue: [nil] ifFalse: [ns] ] type [ ^type ] type: aString [ type := aString ] printOn: aStream [ qualifier == nil ifFalse: [aStream nextPutAll: qualifier , ':']. aStream nextPutAll: type ] ] ] Namespace current: XML [ XPathStep subclass: XPathTerminator [ completePrintOn: aStream [ ^self ] printOn: aStream [ self basicPrintOn: aStream ] enumerate: aBlock [ aBlock value: self ] initialize [ predicates := #() ] isTerminator [ ^true ] simpleMatchFor: anXmlNode isComplex: complex do: aBlock [ ^parent simpleMatchFor: anXmlNode isComplex: complex do: aBlock ] valueIn: aNodeContext do: aBlock [ aBlock value: aNodeContext node ] valueOfAllIn: aNodeContext [ ^aNodeContext ] ] ] Namespace current: XML [ XPathStep subclass: XPathDescendantNode [ XPathDescendantNode class >> axisNames [ ^#('descendant' 'descendant-or-self') ] axisName [ ^axisName == nil ifTrue: ['descendant-or-self'] ifFalse: [axisName] ] baseValueIn: aNodeContext [ | nd nc queue nextNode | nd := aNodeContext node. nc := aNodeContext copy documentOrder. queue := OrderedCollection new. self axisName = 'descendant-or-self' ifTrue: [queue add: nd] ifFalse: [nd isElement ifTrue: [queue addAll: nd children]]. nd isDocument ifTrue: [queue add: nd root]. [queue isEmpty] whileFalse: [nextNode := queue removeFirst. (baseTest match: nextNode) ifTrue: [nc add: nextNode]. nextNode isElement ifTrue: [queue addAll: nextNode children]]. ^nc ] simpleMatchFor: anXmlNode isComplex: complex do: aBlock [ | startNode hasCP set | anXmlNode isAttribute ifTrue: [^false]. (baseTest match: anXmlNode) ifFalse: [^false]. (hasCP := self hasComplexPredicate) ifFalse: [set := XPathNodeContext new add: anXmlNode. 1 to: predicates size do: [:i | set := set select: (predicates at: i)]. set size = 0 ifTrue: [^false halt]]. startNode := self axisName = 'descendant' ifTrue: [anXmlNode parent] ifFalse: [anXmlNode]. [parent == nil ifTrue: [aBlock value: anXmlNode value: complex | hasCP] ifFalse: [parent simpleMatchFor: startNode isComplex: complex | hasCP do: aBlock]] whileFalse: [startNode := startNode parent. startNode == nil ifTrue: [^false]]. ^true ] completeChildPrintOn: aStream [ (baseTest isTrivial and: [predicates isEmpty and: [axisName = 'descendant-or-self']]) ifFalse: [^super completePrintOn: aStream]. aStream nextPut: $/. self child completeChildPrintOn: aStream ] ] ] Namespace current: XML [ Object subclass: XPathParser [ | pushBack hereChar stack buffer source token tokenType xmlNode functions | XPathParser class [ | nodeTypes typeTable | ] XPathParser class >> parse: stringOrStream as: construct [ ^self new parse: stringOrStream as: construct ] XPathParser class >> baseTable [ | newTable c selector | newTable := Array new: 255. 1 to: 255 do: [:each | c := each asCharacter. selector := #xDefault. c isSeparator ifTrue: [selector := #xDelimiter]. c isDigit ifTrue: [selector := #xDigit]. c isLetter ifTrue: [selector := #xLetter]. c == $. ifTrue: [selector := #xPeriod]. c == $" ifTrue: [selector := #xDoubleQuote]. c == $' ifTrue: [selector := #xSingleQuote]. c == $} ifTrue: [selector := #xEndOfExpression]. (':*/+-@=!<>|' includes: c) ifTrue: [selector := #xBinary]. ('$[]()' includes: c) ifTrue: [selector := #xCharacter]. newTable at: each put: selector]. ^newTable ] XPathParser class >> initialize [ "Compute the character type, reserved word tables, and keyword flag from the information associated with each method." typeTable := self baseTable. nodeTypes := Dictionary new. XPathStep allSubclassesDo: [:cls | cls axisNames do: [:nm | nodeTypes at: nm put: cls]] ] XPathParser class >> typeTable [ ^typeTable ] XPathParser class >> nodeTypes [ ^nodeTypes ] XPathParser class >> examples [ "XPathParser2 examples" | samples | samples := #('child::para' 'child::*' 'child::text()' 'child::node()' 'attribute::name' 'attribute::*' 'descendant::para' 'ancestor::div' 'ancestor-or-self::div' 'descendant-or-self::para' 'self::para' 'child::chapter/descendant::para' 'child::*/child::para' '/' '/descendant::para' '/descendant::olist/child::item' 'child::para[position()=1]' 'child::para[position()=last()]' 'child::para[position()=last()-1]' 'child::para[position()>1]' 'following-sibling::chapter[position()=1]' 'preceding-sibling::chapter[position()=1]' '/descendant::figure[position()=42]' '/child::doc/child::chapter[position()=5]/child::section[position()=2]' 'child::para[attribute::type="warning"]' 'child::para[attribute::type=''warning''][position()=5]' 'child::para[position()=5][attribute::type="warning"]' 'child::chapter[child::title=''Introduction'']' 'child::chapter[child::title]' 'child::*[self::chapter or self::appendix]' 'child::*[self::chapter or self::appendix][position()=last()]'). samples do: [:str | (self new parse: str as: #locationPath) printNl] ] abbreviatedDescendant [ token = #/ ifTrue: [stack add: ((XPathDescendantNode new) axisName: 'descendant-or-self'; baseTest: (XPathTypedNodeTest new type: 'node')). ^true]. ^false ] arg: a1 op: operator arg: a2 [ ^XPathBinaryExpression operator: operator asSymbol with: a1 with: a2 ] axis: axisName test: test [ | stepClass step | stepClass := self class nodeTypes at: axisName ifAbsent: [self error: '%1 is not an axis' % {axisName}]. step := stepClass new. step axisName: axisName. "Some classes represent multiple axes, and must be told which" step baseTest: test. ^step ] connectParent: parent child: child [ | p | p := parent. [p child isTerminator] whileFalse: [p := p child]. p child: child. child parent: p. ^parent ] function: aName [ ^self functionNamed: aName ] function: aFunction arg: anArgument [ ^aFunction addArgument: anArgument ] isNodeType [ | typeName argument ok | typeName := stack at: stack size - 1. argument := stack at: stack size. ok := typeName = 'processing-instruction' ifTrue: [true] ifFalse: [(#('node' 'text' 'comment') includes: typeName) ifTrue: [argument == nil] ifFalse: [false]]. "ok ifFalse: [stack removeLast]." ^ok ] nodeTestQualifier: qualifier type: typeName [ | ns | ns := self namespaceAt: qualifier. ^(XPathTaggedNodeTest new) namespace: ns; type: typeName ] nodeTestType: typeName [ ^XPathTaggedNodeTest new type: typeName ] nodeTypeTest: typeName arg: argument [ ^(XPathTypedNodeTest new) type: typeName; value: argument ] number: aValue [ ^aValue ] selfOrParent [ token = #'.' ifTrue: [self scanToken. stack add: ((XPathCurrentNode new) axisName: 'self'; baseTest: (XPathTypedNodeTest new type: 'node')). ^true]. token = #'..' ifTrue: [self scanToken. stack add: ((XPathParentNode new) axisName: 'parent'; baseTest: (XPathTypedNodeTest new type: 'node')). ^true]. ^false ] step: step predicate: predicate [ ^step addPredicate: predicate; yourself ] string: aValue [ ^aValue ] union: path1 with: path2 [ ^path1 asUnion add: path2 ] variable: aName [ ^XPathVariable new name: aName ] absoluteLocationPath [ | root child | self scanToken. "#/" stack addLast: XPathRoot new. hereChar isNil ifTrue: [^true]. self relativeLocationPath ifFalse: [^false]. child := stack removeLast. root := stack removeLast. stack addLast: (self connectParent: root child: child). ^true ] anyStep [ self selfOrParent ifTrue: [^true]. self abbreviatedDescendant ifTrue: [^true]. ^self stepWithPredicates ] locationPath [ token = #/ ifTrue: [^self absoluteLocationPath]. ^self relativeLocationPath ] nodeTest [ | word word2 arg | token = #* ifTrue: [self scanToken. stack addLast: (self nodeTestType: #*). ^true]. tokenType = #word ifFalse: [^false]. word := token. self scanToken. token = $( ifTrue: [self scanToken. token = $) ifTrue: [self scanToken. arg := nil] ifFalse: [tokenType = #string ifFalse: [^false]. arg := token. self scanToken. token = $) ifFalse: [^false]]. stack addLast: (self nodeTypeTest: word arg: arg). ^true]. (self peekFor: #':') ifFalse: [self verifyNotFunction ifTrue: [stack addLast: (self nodeTestType: word). ^true]]. self scanToken. token = #* ifTrue: [self scanToken. stack addLast: (self nodeTestQualifier: word). ^true]. tokenType = #word ifFalse: [^false]. word2 := token. self scanToken. stack addLast: (self nodeTestQualifier: word type: word2) ] predicate [ (token = $[ and: [self scanToken. self expression and: [token = $]]]) ifTrue: [self scanToken. ^true]. ^false ] relativeLocationPath [ | parent child | self anyStep ifFalse: [^false]. [token = #/] whileTrue: [self scanToken. self anyStep ifFalse: [^false]. child := stack removeLast. parent := stack removeLast. stack addLast: (self connectParent: parent child: child)]. ^true ] stepWithPredicates [ | axis word step predicate position | axis := 'child'. tokenType = #word ifTrue: [axis := token. self scanToken. "???" (token = $( and: [(#('node' 'text' 'comment' 'processing-instruction') includes: axis) not]) ifTrue: [pushBack := #character -> $(. tokenType := #word. token := axis. ^false]. (self peekFor: #'::') ifFalse: [tokenType isNil ifFalse: [pushBack := tokenType -> token]. tokenType := #word. token := axis. axis := 'child']]. token = #@ ifTrue: [self scanToken. axis := 'attribute']. self nodeTest ifFalse: [^false]. stack addLast: (self axis: axis test: stack removeLast). [self predicate] whileTrue: [predicate := stack removeLast. step := stack removeLast. stack addLast: (self step: step predicate: predicate)]. ^true ] additiveExpr [ | op arg1 arg2 | self multiplicativeExpr ifFalse: [^false]. [op := token. token = #+ or: [token = #-]] whileTrue: [self scanToken. self multiplicativeExpr ifFalse: [self error: 'error in operand of +/-']. arg2 := stack removeLast. arg1 := stack removeLast. stack addLast: (self arg: arg1 op: op arg: arg2)]. ^true ] andExpr [ | op arg1 arg2 | self equalityExpr ifFalse: [^false]. [op := token. token = 'and'] whileTrue: [self scanToken. self equalityExpr ifFalse: [self error: 'error in operand of and']. arg2 := stack removeLast. arg1 := stack removeLast. stack addLast: (self arg: arg1 op: op arg: arg2)]. ^true ] equalityExpr [ | op arg1 arg2 | self relationalExpr ifFalse: [^false]. [op := token. token = #= or: [token = #'!=']] whileTrue: [self scanToken. self relationalExpr ifFalse: [self error: 'error in operand of =/!=']. arg2 := stack removeLast. arg1 := stack removeLast. stack addLast: (self arg: arg1 op: op arg: arg2)]. ^true ] expression [ ^self orExpr ] filterExpr [ | step predicate | self primaryExpr ifFalse: [^false]. [self predicate] whileTrue: [predicate := stack removeLast. step := stack removeLast. stack addLast: (self step: step predicate: predicate)]. ^true ] multiplicativeExpr [ | op arg1 arg2 | self unaryExpr ifFalse: [^false]. [op := token. token = #* or: [token = 'div' or: [token = 'mod']]] whileTrue: [self scanToken. self unaryExpr ifFalse: [self error: 'error in operand of */div/mod']. arg2 := stack removeLast. arg1 := stack removeLast. stack addLast: (self arg: arg1 op: op arg: arg2)]. ^true ] orExpr [ | op arg1 arg2 | self andExpr ifFalse: [^false]. [op := token. token = 'or'] whileTrue: [self scanToken. self andExpr ifFalse: [self error: 'error in operand of or']. arg2 := stack removeLast. arg1 := stack removeLast. stack addLast: (self arg: arg1 op: op arg: arg2)]. ^true ] pathExpr [ | parent child | self locationPath ifTrue: [^true]. self filterExpr ifFalse: [^false]. token = #/ ifFalse: [^true]. self scanToken. self relativeLocationPath ifFalse: [^false]. child := stack removeLast. parent := stack removeLast. stack addLast: (self connectParent: parent child: child). ^true ] primaryExpr [ | function arg | token = $$ ifTrue: [self scanToken. tokenType = #word ifFalse: [^false]. stack addLast: (self variable: token). self scanToken. ^true]. token = $( ifTrue: [self scanToken. self expression ifFalse: [^false]. token = $) ifFalse: [^false]. self scanToken. ^true]. tokenType = #string ifTrue: [stack addLast: (self string: token). self scanToken. ^true]. tokenType = #number ifTrue: [stack addLast: (self number: token). self scanToken. ^true]. tokenType = #word ifTrue: [function := token. stack addLast: (self function: token). self scanToken. token = $( ifFalse: [^false]. self scanToken. token = $) ifFalse: [ [self expression ifFalse: [^false]. arg := stack removeLast. function := stack removeLast. stack addLast: (self function: function arg: arg). token = $,] whileTrue. token = $) ifFalse: [^false]]. self scanToken. ^true]. ^false ] relationalExpr [ | op arg1 arg2 | self additiveExpr ifFalse: [^false]. [op := token. token = #< or: [token = #> or: [token = #<= or: [token = #>=]]]] whileTrue: [self scanToken. self additiveExpr ifFalse: [self error: 'error in operand of relational operator']. arg2 := stack removeLast. arg1 := stack removeLast. stack addLast: (self arg: arg1 op: op arg: arg2)]. ^true ] unaryExpr [ token = #- ifTrue: [self scanToken. ^(self unaryExpr) ifTrue: [stack addLast: (self negated: stack removeLast)]; yourself]. ^self unionExpr ] unionExpr [ | arg1 arg2 | self pathExpr ifFalse: [^false]. [token = #|] whileTrue: [self scanToken. self pathExpr ifFalse: [self error: 'error in operand of |']. arg2 := stack removeLast. arg1 := stack removeLast. stack addLast: (self union: arg1 with: arg2)]. ^true ] atEndOfExpression [ ^tokenType == #endOfExpression ] init: streamOrString notifying: nothing failBlock: bah [ self source: streamOrString ] source: streamOrString [ buffer := String new writeStream. stack := OrderedCollection new. source := streamOrString isString ifFalse: [streamOrString] ifTrue: [XPathReadStream on: streamOrString asString]. self step; scanToken ] parse: string as: construct [ self source: string. self perform: construct. self pastEnd ifFalse: [self error: 'Extra characters which could not be translated at end of stream']. ^self result ] pastEnd [ ^hereChar == nil ] result [ stack size = 1 ifFalse: [self error: 'Parsing logic error, incorrect number of values on the stack']. ^stack first ] initScanner [ "Present for compatibility with the parser in VW." ] xmlNode: aNode [ xmlNode := aNode ] functionNamed: fName [ functions == nil ifTrue: [functions := XPathFunction baseFunctions]. ^(functions at: fName ifAbsent: [self error: 'Not implemented yet %1()' % {fName}]) copy ] namespaceAt: aQualifier [ | elm ns | elm := xmlNode. [elm isDocument] whileFalse: [ns := elm namespaceAt: aQualifier. ns == nil ifFalse: [^ns]. elm := elm parent]. aQualifier = 'xml' ifTrue: [^XML_URI]. self error: 'No namespace binding found for namespace qualifier "%1".' % {aQualifier} ] peekFor: trialValue [ "Test to see if tokenType matches aType and token equals trialValue. If so, advance to the next token" ^token = trialValue ifTrue: [self scanToken. true] ifFalse: [false] ] unexpectedError [ ^self halt; error: 'syntax error' ] verifyNotFunction [ ^token ~= $( ] scanToken [ | type | pushBack isNil ifFalse: [tokenType := pushBack key. token := pushBack value. pushBack := nil. ^self]. hereChar isNil ifFalse: [type := self class typeTable at: hereChar asInteger ifAbsent: [#xDefault]. self perform: type. ^self]. tokenType := token := nil ] step [ hereChar := source next ] xBinary [ | char test | tokenType := #binary. char := hereChar. self step. char = $. ifTrue: [self halt]. hereChar == nil ifTrue: [token := Symbol internCharacter: char] ifFalse: [test := String with: char with: hereChar. (#('::' '<=' '>=' '!=') includes: test) ifTrue: [self step. token := Symbol intern: test] ifFalse: [token := Symbol internCharacter: char]] ] xCharacter [ tokenType := #character. token := hereChar. self step ] xDefault [ self error: 'invalid character ' , hereChar asString ] xDelimiter [ source skipSeparators. self step. self scanToken ] xDigit [ "form a number" | numerator denominator | tokenType := #number. numerator := 0. denominator := 1. [hereChar notNil and: [hereChar isDigit]] whileTrue: [numerator := numerator * 10 + hereChar digitValue. self step]. hereChar = $. ifFalse: [^token := numerator + 0.0]. self step. [hereChar notNil and: [hereChar isDigit]] whileTrue: [numerator := numerator * 10 + hereChar digitValue. denominator := denominator * 10. self step]. token := numerator / denominator + 0.0 ] xEndOfExpression [ tokenType := #endOfExpression. token := nil ] xDoubleQuote [ "collect string" | char | buffer reset. [(char := source next) == $"] whileFalse: [char == nil ifTrue: [^self offEnd: 'Unmatched comment quote']. buffer nextPut: char]. tokenType := #string. token := buffer contents. "Shorten the buffer if it got unreasonably large." buffer position > 200 ifTrue: [buffer := WriteStream on: (String new: 40)]. self step ] xLetter [ "form a word, keyword, or reserved word" | char | buffer reset. buffer nextPut: hereChar. [char := source next. char notNil and: [char isAlphaNumeric or: [char == $-]]] whileTrue: [buffer nextPut: char]. tokenType := #word. hereChar := char. token := buffer contents ] xPeriod [ "form a number" | numerator denominator | self step. hereChar = $. ifTrue: [self step. token := #'..'. tokenType := #binary. ^self]. (hereChar notNil and: [hereChar isDigit]) ifFalse: [token := #'.'. tokenType := #binary. ^self]. tokenType := #number. numerator := 0. denominator := 1. [hereChar notNil and: [hereChar isDigit]] whileTrue: [numerator := numerator * 10 + hereChar digitValue. denominator := denominator * 10. self step]. token := numerator / denominator + 0.0 ] xSingleQuote [ "collect string" | char | buffer reset. [(char := source next) == $'] whileFalse: [char == nil ifTrue: [^self offEnd: 'Unmatched comment quote']. buffer nextPut: char]. tokenType := #string. token := buffer contents. "Shorten the buffer if it got unreasonably large." buffer position > 200 ifTrue: [buffer := WriteStream on: (String new: 40)]. self step ] functions: aDictionary [ functions := aDictionary ] ] ] Namespace current: XML [ XPathStep subclass: XPathAttributeNode [ XPathAttributeNode class >> axisNames [ ^#('attribute') ] baseValueIn: aNodeContext [ | nd nc | nd := aNodeContext node. nc := aNodeContext copy documentOrder. nd isElement ifFalse: [^nc]. nd attributes do: [:childNode | (baseTest match: childNode) ifTrue: [nc add: childNode]]. ^nc ] simpleMatchFor: anXmlNode isComplex: complex do: aBlock [ | hasCP set | anXmlNode isAttribute ifFalse: [^false]. (baseTest match: anXmlNode) ifFalse: [^false]. (hasCP := self hasComplexPredicate) ifFalse: [set := XPathNodeContext new add: anXmlNode. 1 to: predicates size do: [:i | set := set select: (predicates at: i)]. set size = 0 ifTrue: [^false halt]]. parent == nil ifTrue: [^aBlock value: anXmlNode parent value: complex | hasCP]. ^parent simpleMatchFor: anXmlNode parent isComplex: complex | hasCP do: aBlock ] printTestOn: aStream [ axisName == nil ifTrue: [aStream nextPutAll: '@'; print: baseTest] ifFalse: [super printTestOn: aStream] ] ] ] Namespace current: XML [ XPathStep subclass: XPathCurrentNode [ XPathCurrentNode class >> axisNames [ ^#('self') ] axisName [ axisName == nil ifTrue: [^'self'] ifFalse: [^axisName] ] baseValueIn: aNodeContext [ ^(baseTest match: aNodeContext node) ifTrue: [(aNodeContext copy) documentOrder; add: aNodeContext node] ifFalse: [aNodeContext copy documentOrder] ] simpleMatchFor: anXmlNode isComplex: complex do: aBlock [ | hasCP set | (baseTest match: anXmlNode) ifFalse: [^false]. (hasCP := self hasComplexPredicate) ifFalse: [set := XPathNodeContext new add: anXmlNode. 1 to: predicates size do: [:i | set := set select: (predicates at: i)]. set size = 0 ifTrue: [^false halt]]. parent == nil ifTrue: [^aBlock value: anXmlNode value: complex | hasCP]. ^parent simpleMatchFor: anXmlNode isComplex: complex | hasCP do: aBlock ] completePrintOn: aStream [ (baseTest isTrivial and: [predicates isEmpty]) ifTrue: [self child isTerminator ifTrue: [aStream nextPutAll: '.'] ifFalse: [aStream nextPutAll: './'. self child completeChildPrintOn: aStream]] ifFalse: [super completePrintOn: aStream] ] initialize [ super initialize. baseTest := XPathTypedNodeTest new type: 'node' ] ] ] Object extend [ xpathUsedVarNames [ ^OrderedCollection new ] addToXPathHolder: anAssociation for: aNodeContext [ anAssociation value == nil ifTrue: [^anAssociation value: self]. anAssociation value xpathIsNodeSet ifTrue: [^self error: 'An XPath expression is answering a combination of Nodes and non-Nodes']. self error: 'An XPath expression is answering more than one non-Node value' ] xpathEvalIn: aNodeContext [ "This is private protocol--see #xpathValueIn: for the client protocol" ^self ] xpathIsBoolean [ ^false ] xpathIsNodeSet [ ^false ] xpathIsNumber [ ^false ] xpathMayRequireNodeSet [ ^false ] xpathMayRequireNodeSetTopLevel [ ^false ] xpathMayRequireSort [ ^false ] xpathMayRequireSortTopLevel [ ^false ] xpathValueIn: aNodeContext [ "This is public protocol--see #xpathEvalIn: for the private internal protocol" ^self ] ] Document extend [ xpathStringData [ ^self root xpathStringData ] ] Text extend [ xpathStringData [ ^self characterData ] ] PI extend [ xpathStringData [ ^self text ] ] Element extend [ xpathStringData [ ^self characterData ] ] Comment extend [ xpathStringData [ ^self text ] ] Node extend [ addToXPathHolder: anAssociation for: aNodeContext [ anAssociation value == nil ifTrue: [^anAssociation value: (aNodeContext copy add: self)]. anAssociation value xpathIsNodeSet ifTrue: [^anAssociation value add: self]. self error: 'An XPath expression is answering a combination of Nodes and non-Nodes' ] xpathStringData [ ^self subclassResponsibility ] ] Boolean extend [ xpathAsBoolean [ ^self ] xpathAsNumber [ ^self ifTrue: [1] ifFalse: [0] ] xpathAsString [ ^self printString ] xpathCompareEquality: aData using: aBlock [ aData isString ifTrue: [^aBlock value: self value: aData xpathAsBoolean]. aData xpathIsNumber ifTrue: [^aBlock value: self value: aData xpathAsBoolean]. aData xpathIsBoolean ifTrue: [^aBlock value: self value: aData xpathAsBoolean]. aData xpathIsNodeSet ifTrue: [^aData unsortedNodes contains: [:nd2 | aBlock value: self value: nd2 xpathStringData xpathAsBoolean]]. self error: 'Can''t compare a %1 with a boolean' % {aData class} ] xpathCompareOrder: aData using: aBlock [ | v | v := self xpathAsNumber. ^aData xpathIsNodeSet ifTrue: [aData unsortedNodes contains: [:nd2 | aBlock value: v value: nd2 xpathStringData xpathAsNumber]] ifFalse: [aBlock value: v value: aData xpathAsNumber] ] xpathIsBoolean [ ^true ] ] Number extend [ xpathAsBoolean [ ^self ~= 0 ] xpathAsNumber [ ^self ] xpathAsString [ "self isZero ifTrue: [^'0']." | str n num delta n2 found | self isFinite not ifTrue: [^self printString]. str := (String new: 8) writeStream. self < 0 ifTrue: [str nextPut: $-]. n := self abs + 0.0. num := n truncated. str print: num. num + 0.0 = n ifTrue: [^str contents]. delta := 1 / 10. found := false. [ [n2 := num + delta. n2 < n] whileTrue: [num := n2]. num = n ifTrue: [found := true] ifFalse: [n2 = n ifTrue: [num := n2. found := true]]. found] whileFalse: [delta := delta / 10]. num = n ifFalse: [self halt]. str nextPut: $.. num := num - num truncated. [num = 0] whileFalse: [num := num * 10. str print: num truncated. num := num - num truncated]. ^str contents ] xpathCompareEquality: aData using: aBlock [ aData isString ifTrue: [^aBlock value: self value: aData xpathAsNumber]. aData xpathIsNumber ifTrue: [^aBlock value: self value: aData]. aData xpathIsBoolean ifTrue: [^aBlock value: self xpathAsBoolean value: aData]. aData xpathIsNodeSet ifTrue: [^aData unsortedNodes contains: [:nd2 | aBlock value: self value: nd2 xpathStringData xpathAsNumber]]. self error: 'Can''t compare a %1 with a number' % {aData class} ] xpathCompareOrder: aData using: aBlock [ | v | v := self xpathAsNumber. ^aData xpathIsNodeSet ifTrue: [aData unsortedNodes contains: [:nd2 | aBlock value: v value: nd2 xpathStringData xpathAsNumber]] ifFalse: [aBlock value: v value: aData xpathAsNumber] ] xpathIsNumber [ ^true ] xpathMayRequireNodeSetTopLevel [ ^true ] xpathMayRequireSortTopLevel [ ^true ] ] Attribute extend [ xpathStringData [ ^self characterData ] ] String extend [ xpathAsBoolean [ ^self size > 0 ] xpathAsNumber [ | s foundDigit numerator denominator ch | s := self readStream. s skipSeparators. foundDigit := false. numerator := 0. denominator := (s peekFor: $-) ifTrue: [-1] ifFalse: [1]. [(ch := s next) notNil and: [ch isDigit]] whileTrue: [numerator := numerator * 10 + ch digitValue. foundDigit := true]. ch = $. ifTrue: [[(ch := s next) notNil and: [ch isDigit]] whileTrue: [numerator := numerator * 10 + ch digitValue. denominator := denominator * 10. foundDigit := true]]. (ch == nil or: [ch isSeparator]) ifFalse: [^FloatD nan]. s skipSeparators. s atEnd ifFalse: [^FloatD nan]. foundDigit ifFalse: [^FloatD nan]. ^numerator / denominator + 0.0 ] xpathAsString [ ^self ] xpathCompareEquality: aData using: aBlock [ aData isString ifTrue: [^aBlock value: self value: aData]. aData xpathIsNumber ifTrue: [^aBlock value: self xpathAsNumber value: aData]. aData xpathIsBoolean ifTrue: [^aBlock value: self xpathAsBoolean value: aData]. aData xpathIsNodeSet ifTrue: [^aData unsortedNodes contains: [:nd2 | aBlock value: self value: nd2 xpathStringData]]. self error: 'Can''t compare a %1 with a string' % {aData class} ] xpathCompareOrder: aData using: aBlock [ | v | v := self xpathAsNumber. ^aData xpathIsNodeSet ifTrue: [aData unsortedNodes contains: [:nd2 | aBlock value: v value: nd2 xpathStringData xpathAsNumber]] ifFalse: [aBlock value: v value: aData xpathAsNumber] ] ] Namespace current: XML [ XML.XPathFunction initialize. XML.XPathParser initialize. XML.XPathBinaryExpression initialize ] smalltalk-3.2.5/packages/xml/xpath/stamp-classes0000644000175000017500000000000012123404352016614 00000000000000smalltalk-3.2.5/packages/xml/xpath/package.xml0000644000175000017500000000017712123404352016246 00000000000000 XPath XML XML-DOM XPath.st smalltalk-3.2.5/packages/xml/ChangeLog0000644000175000017500000002226012123404352014554 000000000000002011-03-12 Paolo Bonzini * expat/expat.c: Remove dead code signaled by clang analyzer. 2010-12-04 Paolo Bonzini * builder/package.xml: Remove now superfluous tags. * dom/package.xml: Remove now superfluous tags. * expat/package.xml: Remove now superfluous tags. * parser/package.xml: Remove now superfluous tags. * pullparser/package.xml: Remove now superfluous tags. * saxdriver/package.xml: Remove now superfluous tags. * saxparser/package.xml: Remove now superfluous tags. * tests/package.xml: Remove now superfluous tags. * xpath/package.xml: Remove now superfluous tags. * xsl/package.xml: Remove now superfluous tags. 2010-05-09 Paolo Bonzini * parser/XML.st: Use #display: to show entities with Unicode support. * parser/package.xml: Depend on Iconv. 2009-09-23 Paolo Bonzini * expat/ExpatParser.st: New. * expat/ExpatPullParser.st: New. * expat/ExpatTests.st: New. * expat/expat.c: New. * expat/package.xml: New. 2009-09-21 Paolo Bonzini * pullparser/XMLPullParser.st: Another event... * saxdriver/Events.st: Another event... * parser/XML.st: Raise it here. 2009-09-20 Paolo Bonzini * pullparser/XMLPullParser.st: Push up #atEnd. Look ahead for more text in #text. * saxdriver/Events.st: Lazily initialize attributes. Remove duplicate instance variables. * saxparser/Parser.st: Add more constructors. * tests/XMLPullParserTests.st: Avoid ignorable whitespace issues. 2009-09-20 Paolo Bonzini * parser/XMLTests.st: New. * parser/package.xml: Add it. Provide XML-Parser. * pullparser/XMLPullParserTests.st: Move parser creation to test class, rename to... * tests/XMLPullParserTests.st: ... this. * pullparser/package.xml: Depend on SAXParser and XML-Parser. Remove XMLPullParserTests.st. * tests/package.xml: Depend on SAXParser only. 2009-09-19 Paolo Bonzini * parser/XML.st: Generate DOCTYPE and CDATA section events. * pullparser/XMLPullParser.st: Likewise. Add #needCdataDelimiters and #needDTDEvents, as well as the utility method #doctypeName. * pullparser/XMLPullParserTests.st: Test new features. * saxdriver/Events.st: Add more events. 2009-09-19 Paolo Bonzini * pullparser/XMLPullParser.st: Provide nicer pull parser factory interface. 2009-09-19 Paolo Bonzini * pullparser/XMLPullParser.st: Add optional events, DTD events, XMLResolveEntityNotification, and avoid #copyFrom:to: when not needed. * pullparser/XMLPullParserTests.st: Test DTDs, comments and XMLResolveEntityNotification. * saxdriver/Events.st: Add missing events. Do #copyFrom:to: lazily for comments and text. 2009-09-16 Paolo Bonzini * pullparser/XMLPullParser.st: Add copyright header. * pullparser/XMLPullParserTests.st: Add copyright header. * saxdriver/Events.st: Add copyright header. 2009-09-15 Paolo Bonzini * pullparser/XMLPullParser.st: New. * pullparser/XMLPullParserTests.st: New. * pullparser/package.xml: New. * saxdriver/Events.st: New. * saxdriver/package.xml.st: Add it. 2009-09-15 Paolo Bonzini * saxparser/Parser.st: Add #defaultParserClass and setter. * parser/XML.st: Set defaultParserClass if nil. 2009-09-15 Paolo Bonzini * saxdriver/SAX.st: Add method to create NodeTag from qName. * dom/DOM.st: Use it. 2009-09-15 Paolo Bonzini * dom/DOM.st: Move Attribute and NodeTag... * saxdriver/SAX.st: ... here. 2009-09-15 Paolo Bonzini * parser/XML.st: Raise EmptySignal for an empty XML document, and be prepare for it to resume. * saxdriver/SAX.st: Make WarningSignal and EmptySignal resumable. 2009-09-15 Paolo Bonzini * parser/XML.st: Ignore whitespace in non-validating mode. 2007-12-27 Paolo Bonzini * parser/XML.st: Use new File methods. * xsl/XSL.st: Likewise. 2007-12-27 Paolo Bonzini * xsl/package.xml: Don't use XML metapackage as prereq. 2007-11-06 Paolo Bonzini * saxdriver/SAX.st: Add stub DOM_SAXDriver. Move InputSource here... * dom/DOM.st: ... from here. * saxparser/Parser.st: Remove #pushSource:for: abstract method, move #dtd (undoing part of the previous commit) and Entity>>#streamFor:... * parser/XML.st: ... here as #pushSourceFor:. * saxparser/package.xml: Remove XML-DOM dependency. * parser/package.xml: Remove XML-XMLNodeBuilder dependency, add XML-DOM dependency. * builder/package.xml: Add XML-DOM dependency. 2007-11-06 Paolo Bonzini * saxparser/package.xml: Fix dependency. * parser/XMLParser.st: Remove #contentsOf:for:. Test recursive expansion of entities in #pushSource:for:. Add #wrapSourceInSpaces and use it instead of #streamFor:addSpaces:. Add #attributeTypeFor:subKey:from:. Move #dtd... * saxparser/Parser.st: ... here. Port #mapEncoding: to gst. Remove abstract methods #hasExpanded: and #contentsOf:for:. Remove checks for recursive expansion of entities and #streamFor:addSpaces:. 2007-11-05 Paolo Bonzini Split into separate directories. * builder/package.xml: New. * dom/package.xml: New. * parser/package.xml: New. * saxdriver/package.xml: New. * saxparser/package.xml: New. * xpath/package.xml: Moved from ../xpath. Load in the XML namespace, depend on XML-DOM. * xsl/package.xml: Moved from ../xsl. 2007-11-05 Paolo Bonzini * package.xml: Load in the XML namespace. * DOM.st: Add more DocumentType accessors. Move parts of DocumentType... * Parser.st: ... here as class extensions. 2007-10-09 Paolo Bonzini * XML.st: Move parts... * SAX.st: ... here, * DOM.st: ... here, * NodeBuilder.st: ... here, * Parser.st: ... and here. 2007-06-25 Paolo Bonzini * XML.st: Use #%. * XPath.st: Use #%. * XSL.st: Use #%. 2007-06-25 Paolo Bonzini * XPath.st: Change #usedVarNames to #xpathUsedVarNames, add a few methods for VW compatibility. * XSL.st: Adapt to these changes and to the non-bogusness of our XPath parser compared to VW's. 2006-12-05 Paolo Bonzini *** Version 2.3 released. 2005-07-10 Paolo Bonzini * XSL.st: Use #codePoint: to generate characters. 2005-04-07 Mike Anderson * XML.st: Fix bugs related to VW compatibility. 2003-05-09 Paolo Bonzini *** Version 2.1.2 released. * XML.st: removed VW vestiges * XSL.st: removed VW vestiges 2003-04-17 Paolo Bonzini *** Version 2.1.1 (stable) released. 2003-04-12 Paolo Bonzini *** Version 2.1 (stable) released. 2002-09-18 Paolo Bonzini * XML.st: removed i18n markup * XSL.st: NumberFormat not a #variableSubclass: anymore. 2002-09-13 Paolo Bonzini *** Versions 2.0c (development) and 2.0.6 (stable) released * XPath.st: upgraded to VW7 * XSL.st: upgraded to VW7 * XML.st: upgraded to VW7 2002-08-18 Paolo Bonzini * XPath.st: new file * XSL.st: new file * XML.st: put class declarations before the actual code; implement XML Document>>#indexOf: 2002-08-14 Paolo Bonzini *** Version 2.0.5 (stable) released 2002-08-12 Paolo Bonzini *** Version 2.0b (development) released 2002-08-07 Paolo Bonzini *** Versions 2.0a (development) and 2.0.4 (stable) released 2002-07-17 Paolo Bonzini *** Version 2.0.3 released 2002-07-11 Paolo Bonzini *** Version 2.0.2 released 2002-06-28 Paolo Bonzini *** Version 2.0.1 released 2002-06-25 Paolo Bonzini *** Version 2.0 released 2002-06-20 Paolo Bonzini * XML.st: #expandMacrosWith: -> #bindWith: 2002-05-11 Paolo Bonzini *** Version 1.96.6 released 2002-05-02 Paolo Bonzini * Id-*.st: removed remaining vestiges 2002-04-14 Paolo Bonzini *** Version 1.96.5 released 2002-03-12 Paolo Bonzini *** Version 1.96.4 released 2002-01-29 Paolo Bonzini *** Version 1.96.3 released. 2002-01-04 Paolo Bonzini *** Version 1.96.2 released 2001-11-20 Paolo Bonzini *** Version 1.96.1 released 2001-10-26 Paolo Bonzini * XML.st: removed URIResolver and imported it from NetClients instead. 2001-03-16 Paolo Bonzini * XML.st: added XML Element>>#addAttribute:, #removeAttribute:, #removeNode:. Use ' in printCanonicalText:on: 2001-02-23 Paolo Bonzini *** Released version 1.95.3 2001-02-09 Paolo Bonzini * GST-XML.st: added XML Document>>#setRoot: and PredefinedEntities 2001-01-30 Paolo Bonzini * GST-XML.st: imported. * Id-XWalker.st: new name of XWalker.st * Id-DOM.st: new name of DOM.st 1999-09-14 Paolo Bonzini * XWalker.st: added * DOM.st: added smalltalk-3.2.5/packages/xml/xsl/0000755000175000017500000000000012130456023013666 500000000000000smalltalk-3.2.5/packages/xml/xsl/Makefile.frag0000644000175000017500000000023412123404352016163 00000000000000XSL_FILES = \ packages/xml/xsl/XSL.st $(XSL_FILES): $(srcdir)/packages/xml/xsl/stamp-classes: $(XSL_FILES) touch $(srcdir)/packages/xml/xsl/stamp-classes smalltalk-3.2.5/packages/xml/xsl/XSL.st0000644000175000017500000031073212123404352014632 00000000000000"====================================================================== | | VisualWorks XSL Framework | | ======================================================================" "====================================================================== | | Copyright (c) 2000, 2002 Cincom, Inc. | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" Namespace current: XSL [ XML.NodeBuilder subclass: XSLNodeBuilder [ | nodeNameMap | makeText: text [ ^TextTemplate text: text ] pi: nm text: text [ ^XSL_PI new name: nm text: text ] tag: tag attributes: attributes elements: elements position: p stream: stream [ | elementClass | elementClass := tag namespace = XSL_URI ifTrue: [self nodeNameMap at: tag type ifAbsent: [self error: 'The action ' , tag asString , ' is not yet implemented']] ifFalse: [Template]. ^elementClass tag: tag attributes: attributes elements: elements ] nodeNameMap [ nodeNameMap == nil ifTrue: [nodeNameMap := Dictionary new. XSLCommand withAllSubclasses do: [:beh | beh tag == nil ifFalse: [nodeNameMap at: beh tag put: beh]]]. ^nodeNameMap ] ] ] Namespace current: XSL [ XML.XPathNodeContext subclass: XSLNodeContext [ | db mode | db [ ^db ] db: aRuleDatabase [ db := aRuleDatabase ] mode [ ^mode ] mode: aSymbol [ mode := aSymbol ] ] ] Namespace current: XSL [ Object subclass: RuleDatabase [ | rules variables normalized namedTemplates attributeSets currentImportance uriStack output | RuleDatabase class >> constructXML [ "RuleDatabase constructXML" ^' An example

      This is a test.

      This is another test.

      ' ] RuleDatabase class >> constructXSL [ ^' .... ' ] RuleDatabase class >> macroXML [ ^'

      a paragraph

      another paragraph

      the warning

      closing paragraph

      warning 2 warning 3 SmithJoeG. JonesJohnP. SmithBillM. BellAlexanderG. SmithBillA.
      ' ] RuleDatabase class >> macroXSL [ ^' Warning! (see appendix) ' ] RuleDatabase class >> numberedSourceData [ ^'1. Overview 2. Tree Construction 2.1 Overview 2.2 Stylesheet Structure 2.3 Processing Model 2.4 Data Model 2.4.1 Root Node 2.4.2 Element Nodes 2.4.3 Attribute Nodes 2.4.4 Character Data 2.4.5 Whitespace Stripping 2.5 Template Rules 2.5.1 Conflict Resolution for Template Rules 2.5.2 Built-in Template Rule 2.6 Patterns 2.6.1 Alternative Patterns 2.6.2 Matching on Element Ancestry 2.6.3 Anchors 2.6.4 Matching the Root Node 2.6.5 Matching on Element Types 2.6.6 Qualifiers 2.6.7 Matching on Children 2.6.8 Matching on Attributes 2.6.9 Matching on Position 2.6.10 Whitespace in Patterns 2.6.11 Specificity 2.7 Templates 2.7.1 Overview 2.7.2 Literal Result Elements 2.7.3 Named Attribute Sets 2.7.4 Literal Text in Templates 2.7.5 Processing with xsl:process-children 2.7.6 Processing with xsl:process 2.7.7 Direct Processing 2.7.8 Numbering in the Source Tree 2.7.9 Number to String Conversion Attributes 2.7.10 Conditionals within a Template 2.7.11 Computing Generated Text 2.7.12 String Constants 2.7.13 Macros 2.8 Style Rules 2.9 Combining Stylesheets 2.9.1 Stylesheet Import 2.9.2 Stylesheet Inclusion 2.9.3 Embedding Stylesheets 2.10 Extensibility 3. Formatting Objects 3.1 Introduction 3.2 Notations Used in this Section 3.3 Formatting Objects and Their Properties 3.4 Formatting Objects to be Defined in Subsequent Drafts 3.5 Page-sequence Layout Object 3.5.1 Purpose 3.5.2 Formatting Object Summary 3.5.3 Formatting Object''s Formal Specification 3.5.4 To Resolve 3.6 Simple-page-master Layout Object 3.6.1 Purpose 3.6.2 Formatting Object Summary 3.6.3 Formatting Object''s Formal Specification 3.6.4 To Resolve A. DTD for XSL Stylesheets B. References B.1 Normative References B.2 Other References C. Examples (Non-Normative) D. Design Principles (Non-Normative) E. Acknowledgements (Non-Normative) ' ] RuleDatabase class >> numberedXML [ "RuleDatabase numberedXML" | src stack str depth parent title tag | stack := OrderedCollection new. stack add: (Element tag: 'doc'). src := self numberedSourceData readStream. [src atEnd] whileFalse: [str := src upTo: Character nl. depth := str occurrencesOf: Character tab. str := str copyFrom: depth + 1 to: str size. tag := depth = 0 ifTrue: [str first isDigit ifTrue: ['chapter'] ifFalse: ['appendix']] ifFalse: [#('section' 'subsection') at: depth]. str := str copyFrom: (str indexOf: $ ) + 1 to: str size. [depth + 1 = stack size] whileFalse: [stack removeLast]. parent := stack last. title := Text text: str. title := Element tag: 'title' elements: (Array with: title). title := Element tag: tag elements: (Array with: title). stack addLast: title. parent elements: (parent children copyWith: title)]. ^stack first printString ] RuleDatabase class >> numberedXML2 [ "RuleDatabase numberedXML2" | src stack str depth title tag | stack := OrderedCollection new. stack add: (Element tag: 'doc'). src := self numberedSourceData readStream. [src atEnd] whileFalse: [str := src upTo: Character nl. depth := str occurrencesOf: Character tab. str := str copyFrom: depth + 1 to: str size. tag := depth = 0 ifTrue: ['H1'] ifFalse: [#('H2' 'H3' 'H4') at: depth]. str := str copyFrom: (str indexOf: $ ) + 1 to: str size. title := Text text: str. title := Element tag: tag elements: (Array with: title). stack last elements: (stack last children copyWith: title)]. ^stack first printString ] RuleDatabase class >> numberedXSL [ ^'
    • ' ] RuleDatabase class >> numberedXSL1 [ ^'
    • ' ] RuleDatabase class >> numberedXSL2 [ ^' . . . ' ] RuleDatabase class >> patternsXML [ ^' ]> title body of chapter1 subsection more of chapter 1 title2 body of chapter 2 ' ] RuleDatabase class >> patternsXSL [ ^' -------------------- arg1="class" arg2="Array"

      ' ] RuleDatabase class >> sampleXML [ ^' An example

      This is a test.

      This is another test.

      ' ] RuleDatabase class >> sampleXSL [ ^' ' ] RuleDatabase class >> allTest [ "XSL.RuleDatabase allTest" | sel | sel := self class selectors select: [:s | 'test*' match: s]. sel asSortedCollection do: [:s | self perform: s] ] RuleDatabase class >> examplesDirectory [ ^Directory image / 'xml' ] RuleDatabase class >> store: document on: filename [ (FileStream open: filename mode: FileStream write) print: document; close ] RuleDatabase class >> test [ "RuleDatabase test" | test doc | test := self new. test readString: self sampleXSL. doc := XMLParser processDocumentString: self sampleXML beforeScanDo: [:parser | parser validate: false]. ^test process: doc ] RuleDatabase class >> test2 [ "RuleDatabase test2" | test doc default result | default := self examplesDirectory. test := self new. test readFileNamed: (default nameAt: 'activityinfo.xsl'). doc := XMLParser processDocumentInFilename: (default nameAt: 'activityinfo.xml') beforeScanDo: [:parser | parser validate: false]. result := test process: doc. self store: result on: 'activityinfo.html' ] RuleDatabase class >> test2a [ "RuleDatabase test2a" | test doc default result | default := self examplesDirectory. test := self new. test readFileNamed: (default nameAt: 'activityinfo2.xsl'). doc := XMLParser processDocumentInFilename: (default nameAt: 'activityinfo.xml') beforeScanDo: [:parser | parser validate: false]. result := test process: doc. self store: result on: 'activityinfo2.html' ] RuleDatabase class >> test2b [ "RuleDatabase test2b" | test doc default result | default := self examplesDirectory. test := self new. test readFileNamed: (default nameAt: 'activityinfo3.xsl'). doc := XMLParser processDocumentInFilename: (default nameAt: 'activityinfo.xml') beforeScanDo: [:parser | parser validate: false]. result := test process: doc. self store: result on: 'activityinfo3.html' ] RuleDatabase class >> test3 [ "RuleDatabase test3" | test doc default result | default := self examplesDirectory. test := self new. test readFileNamed: (default nameAt: 'listgen.xsl'). doc := XMLParser processDocumentInFilename: (default nameAt: 'listgen.xml') beforeScanDo: [:parser | parser validate: false]. result := test process: doc. self store: result on: 'listgen.html' ] RuleDatabase class >> test4 [ "RuleDatabase test4" | test doc | test := self new. test readString: self numberedXSL. doc := XMLParser processDocumentString: self numberedXML beforeScanDo: [:parser | parser validate: false]. ^test process: doc ] RuleDatabase class >> test4a [ "RuleDatabase test4a" | test doc | test := self new. test readString: self numberedXSL1. doc := XMLParser processDocumentString: self numberedXML beforeScanDo: [:parser | parser validate: false]. ^test process: doc ] RuleDatabase class >> test4b [ "RuleDatabase test4b" | test doc | test := self new. test readString: self numberedXSL2. doc := XMLParser processDocumentString: self numberedXML2 beforeScanDo: [:parser | parser validate: false]. ^test process: doc ] RuleDatabase class >> test5 [ "RuleDatabase test5" | test doc | test := self new. test readString: self constructXSL. doc := XMLParser processDocumentString: self constructXML beforeScanDo: [:parser | parser validate: false]. ^test process: doc ] RuleDatabase class >> test6 [ "RuleDatabase test6" | test doc | test := self new. test readString: self patternsXSL. doc := XMLParser processDocumentString: self patternsXML. ^test process: doc ] RuleDatabase class >> test7 [ "RuleDatabase test7" | test doc | test := self new. test readString: self macroXSL. doc := XMLParser processDocumentString: self macroXML beforeScanDo: [:parser | parser validate: false]. ^test process: doc ] RuleDatabase class >> new [ ^super new initialize ] importance [ ^currentImportance ] importance: aValueHolder [ currentImportance := aValueHolder ] raiseImportance [ currentImportance := (currentImportance value + 1) asValue ] replaceImportance: oldValue [ variables do: [:clist | clist do: [:c | c replaceImportance: oldValue with: currentImportance]]. namedTemplates do: [:mlist | mlist do: [:m | m replaceImportance: oldValue with: currentImportance]]. rules do: [:r | r replaceImportance: oldValue with: currentImportance] ] addAttributeSet: anAttributeSet [ | all | anAttributeSet importanceHolder: currentImportance. all := attributeSets at: anAttributeSet name ifAbsentPut: [OrderedCollection new]. all add: anAttributeSet ] addNamedTemplate: aRule [ | all | aRule importanceHolder: currentImportance. all := namedTemplates at: aRule name ifAbsentPut: [OrderedCollection new]. (all contains: [:c | c importance = currentImportance value]) ifTrue: [self error: 'There are two named templates named %1 with the same importance' % {aRule name}]. all add: aRule ] addRule: aRule [ aRule importanceHolder: currentImportance. rules add: aRule ] addRuleSet: anXSLCommand topLevel: isTopLevel [ anXSLCommand purgeUnimportant. isTopLevel ifTrue: [anXSLCommand topLevelAddToRuleDB: self] ifFalse: [anXSLCommand addToRuleDB: self] ] addVariable: aVariable [ | all | aVariable importanceHolder: currentImportance. all := variables at: aVariable name ifAbsentPut: [OrderedCollection new]. (all contains: [:c | c importance = currentImportance value]) ifTrue: [self error: 'There are two variables named %1 with the same importance' % {aVariable name}]. all add: aVariable ] attributesForSet: setName [ | list map | list := attributeSets at: setName ifAbsent: [self error: 'No attribute set named "%1".' % {setName asString}]. map := Dictionary new. list do: [:as | (as allAttributesFrom: self) do: [:attr | (map at: attr name ifAbsentPut: [SortedCollection sortBlock: [:a1 :a2 | a1 key > a2 key]]) add: as importance -> attr]]. list := OrderedCollection new. map do: [:singleList | (singleList size > 1 and: [(singleList at: 1) key = (singleList at: 2) key]) ifTrue: [self error: 'Attribute set "%1" includes more than one definition of the attribute "%2".' % {setName asString. singleList first name asString}]. list add: singleList first value]. ^list ] bindVariableValues: aNodeContext arguments: argDictionary [ variables do: [:var | var process: aNodeContext into: nil takeArgumentsFrom: argDictionary] ] normalizeRules [ normalized ifTrue: [^self]. normalized := true. self normalizeVariables. namedTemplates keys do: [:nm | | clist | clist := namedTemplates at: nm. (clist collect: [:c | c importance]) asSet size = clist size ifFalse: [self error: 'Named template named "' , nm , '" has more than one definition with the same importance']. namedTemplates at: nm put: (clist asSortedCollection: [:c1 :c2 | c1 importance < c2 importance]) last]. namedTemplates do: [:m | m normalize]. rules do: [:r | r normalize] ] normalizeVariables [ | unsorted sorted lastSize list | variables class == Dictionary ifFalse: [^self]. variables keys do: [:nm | | clist | clist := variables at: nm. (clist collect: [:c | c importance]) asSet size = clist size ifFalse: [self error: 'Variable named "' , nm , '" has more than one definition with the same importance']. variables at: nm put: (clist asSortedCollection: [:c1 :c2 | c1 importance < c2 importance]) last]. variables do: [:c | c normalize]. unsorted := variables asOrderedCollection. sorted := OrderedCollection new. lastSize := -1. [sorted size = lastSize] whileFalse: [lastSize := sorted size. unsorted copy do: [:var | list := var expression xpathUsedVarNames. list := list reject: [:nm | sorted includes: nm]. list isEmpty ifTrue: [sorted add: var name. unsorted remove: var]]]. unsorted isEmpty ifFalse: [self error: 'There is a cycle of reference between the variables']. variables := sorted collect: [:v | variables at: v] ] readFileNamed: aFilename [ | doc | self initURI: 'file' name: aFilename asString. doc := XMLParser processDocumentInFilename: aFilename beforeScanDo: [:parser | parser builder: XSLNodeBuilder new. parser validate: false]. self addRuleSet: doc root topLevel: true ] readStream: aStream [ self readStream: aStream topLevel: true ] readStream: aStream topLevel: isTopLevel [ | doc parser | parser := XMLParser on: aStream. parser builder: XSLNodeBuilder new. parser validate: false. doc := parser scanDocument. self addRuleSet: doc root topLevel: isTopLevel ] readString: aString [ | doc | self initURI: 'file' name: (Directory working / 'xxx') name. doc := XMLParser processDocumentString: aString beforeScanDo: [:parser | parser builder: XSLNodeBuilder new. parser validate: false]. self addRuleSet: doc root topLevel: true ] resolveAttributesForSet: setName [ | list | list := attributeSets at: setName ifAbsent: [self error: 'No attribute set named "%1".' % {setName asString}] ] setOutput: anOutputCommand [ output := anOutputCommand ] uriStack [ ^uriStack ] chooseBestRule: ruleList for: aNodeContext [ | best | ruleList size = 1 ifTrue: [^ruleList first]. best := ruleList asSortedCollection: [:r1 :r2 | r1 importance >= r2 importance]. best := best asOrderedCollection select: [:r1 | r1 importance = best first importance]. best size = 1 ifTrue: [^best first]. best := best collect: [:r1 | r1 priority -> r1]. best := best asSortedCollection: [:a1 :a2 | a1 > a2]. best := best asOrderedCollection select: [:a1 | a1 key = best first key]. best := best collect: [:a | a value]. best size = 1 ifTrue: [^best first]. best size = 0 ifFalse: [self halt: 'Conflicting rules for ' , aNodeContext node simpleDescription , ', use priority to rank the rules.'. ^best last]. ^nil ] process: aDocument [ ^self process: aDocument arguments: Dictionary new ] process: aDocument arguments: passedArguments [ | doc baseDoc baseVars | self normalizeRules. doc := DocumentFragment new. baseVars := Dictionary new. baseDoc := (XSLNodeContext new) add: aDocument; index: 1; variables: baseVars; db: self. self bindVariableValues: baseDoc arguments: passedArguments. baseDoc variables: (ChainedDictionary new parent: baseVars). (self process: baseDoc into: ElementProxy new mode: nil) children do: [:elm | doc addNode: elm]. doc addNamespaceDefinitions. ^doc ] process: aNodeContext into: aProxy mode: mode [ | rule list | list := rules select: [:r | r match: aNodeContext]. list := list select: [:r | r modeIsLike: mode]. rule := self chooseBestRule: list for: aNodeContext. rule == nil ifFalse: [rule process: aNodeContext into: aProxy arguments: #()]. ^aProxy ] ruleMatching: aNodeContext mode: mode [ | rule list | list := OrderedCollection new: 5. 1 to: rules size do: [:i | rule := rules at: i. ((rule modeIsLike: mode) and: [rule match: aNodeContext]) ifTrue: [list add: rule]]. "list := rules select: [:r | r match: aNodeContext]. list := list select: [:r | r modeIsLike: mode]." rule := self chooseBestRule: list for: aNodeContext. ^rule ] ruleNamed: aName [ ^namedTemplates at: aName ifAbsent: [] ] initialize [ | baseRule action builtinImportance | normalized := false. rules := OrderedCollection new. variables := Dictionary new. namedTemplates := Dictionary new. attributeSets := Dictionary new. currentImportance := 1 asValue. builtinImportance := 0 asValue. action := ApplyTemplatesCommand new. baseRule := Rule new. baseRule mode: #any. baseRule attributes: (Array with: (Attribute name: 'match' value: '*|/')). baseRule elements: (Array with: action). baseRule importanceHolder: builtinImportance. rules add: baseRule. action := ValueOfCommand new. action attributes: (Array with: (Attribute name: 'select' value: '.')). baseRule := Rule new. baseRule mode: #any. baseRule attributes: (Array with: (Attribute name: 'match' value: 'text()')). baseRule elements: (Array with: action). baseRule importanceHolder: builtinImportance. rules add: baseRule ] initURI: aProtocol name: aName [ uriStack == nil ifTrue: [uriStack := OrderedCollection with: aProtocol -> (aName copy asString replaceAll: Directory pathSeparator with: $/)] ] output [ output == nil ifTrue: [output := OutputCommand new]. ^output ] outputMethodFor: aDocument [ | rt | self output method = #auto ifFalse: [^self output method]. rt := aDocument root. (rt notNil and: [rt tag namespace isEmpty and: [rt tag type asLowercase = 'html']]) ifTrue: [^'html']. ^'xml' ] ] ] Namespace current: XSL [ XML.Text subclass: DenormalizedText [ saxDo: aDriver [ [aDriver normalizeText: false] on: Error do: [:dummy | ]. super saxDo: aDriver. [aDriver normalizeText: true] on: Error do: [:dummy | ] ] ] ] Namespace current: XSL [ XML.Element subclass: XSLCommand [ XPathExtensionFunctions := nil. XSLCommand class >> tag [ ^nil ] XSLCommand class >> xslFunctions [ ^XPathExtensionFunctions ] XSLCommand class >> formatNumber: aNumber pattern: pattern formatName: formatName in: aNodeContext [ ^aNumber xpathAsString ] XSLCommand class >> initialize [ "XSLCommand initialize" | functions | functions := ChainedDictionary new. functions parent: XPathFunction baseFunctions. functions at: 'format-number' put: ((XPathFunction new) name: 'format-number'; valueBlock: [:fn :ns | | n s1 s2 | (fn arguments size between: 2 and: 3) ifFalse: [self error: 'format-number() takes two or three arguments.']. n := ((fn arguments at: 1) xpathEvalIn: ns) xpathAsNumber. s1 := ((fn arguments at: 2) xpathEvalIn: ns) xpathAsString. fn arguments size = 3 ifTrue: [s2 := ((fn arguments at: 3) xpathEvalIn: ns) xpathAsString] ifFalse: [s2 := nil]. self formatNumber: n pattern: s1 formatName: s2 in: ns]). XPathExtensionFunctions := functions ] checkQNameSyntax: aString [ | str mode colons ch valid | str := aString readStream. mode := #colon. colons := 0. [str atEnd] whileFalse: [ch := str next. mode == #colon ifTrue: [valid := ch = $_ or: [ch isLetter]. mode := #letter] ifFalse: [ch = $: ifTrue: [valid := true. colons := colons + 1. mode := #colon] ifFalse: [valid := ch isLetter or: [ch isDigit or: ['.-_' includes: ch]]. mode := #letterOrDigit]]. valid ifFalse: [self error: 'Syntax error in qualified name.']]. (mode = #colon or: [colons > 1]) ifTrue: [self error: 'Syntax error in qualified name.'] ] checkURISyntax: aString [ | n type ch | n := aString findLast: [:c | c = $#]. n = aString size ifTrue: [self error: 'The name for an attribute or element, using the x#y syntax, has no type following the #.']. type := aString copyFrom: n + 1 to: aString size. ch := type at: 1. (ch = $_ or: [ch isLetter]) ifFalse: [self error: 'Type name syntax error in "%1".' % {type}]. 2 to: type size do: [:i | ch := type at: i. (ch isLetter or: [ch isDigit or: ['.-_' includes: ch]]) ifFalse: [self error: 'Type name syntax error in "%1".' % {type}]] ] collate: node1 to: node2 within: aNodeContext [ | list sign | (list := self sortList) == nil ifFalse: [1 to: list size do: [:i | sign := (list at: i) collate: node1 to: node2 within: aNodeContext. sign = 0 ifFalse: [^sign = -1]]]. ^node1 precedes: node2 ] readAttribute: attName [ ^self readAttribute: attName default: [self error: '%1 needs to have an attribute named %2' % {self tag asString. attName}] ] readAttribute: attName default: def [ | att | att := self valueOfAttribute: attName ifAbsent: [nil]. ^att == nil ifTrue: [def value] ifFalse: [att] ] readInteger: attName default: def [ | att val | att := self valueOfAttribute: attName ifAbsent: [nil]. ^att == nil ifTrue: [def value] ifFalse: [att isEmpty ifTrue: [self error: 'The %1 attribute is empty' % {attName}]. att := att readStream. val := Number readFrom: att. val = 0 ifTrue: [self error: 'Bad number format, ' , (att instVarAt: 1)]. att atEnd ifFalse: [self error: 'The %1 attribute is not a legal integer value' % {attName}]. val] ] readMatchPattern: attName [ ^self readMatchPattern: attName default: [self error: '%1 needs to have an attribute named %2' % {self tag asString. attName}] ] readMatchPattern: attName default: def [ | att | att := self valueOfAttribute: attName ifAbsent: [nil]. ^att == nil ifTrue: [def value] ifFalse: [(XPathParser new) xmlNode: self; functions: self class xslFunctions; parse: att as: #expression] ] readSelectPattern: attName [ ^self readSelectPattern: attName default: [self error: '%1 needs to have an attribute named %2' % {self tag asString. attName}] ] readSelectPattern: attName default: def [ | att d | att := self valueOfAttribute: attName ifAbsent: [nil]. ^att == nil ifTrue: [d := def value. d == nil ifFalse: [d := (XPathParser new) xmlNode: self; functions: self class xslFunctions; parse: d as: #expression]. d] ifFalse: [(XPathParser new) xmlNode: self; functions: self class xslFunctions; parse: att as: #expression] ] readTag: attName [ | att | att := self valueOfAttribute: attName ifAbsent: [nil]. ^att == nil ifTrue: [self error: '%1 needs to have an attribute named %2' % {self tag asString. attName}] ifFalse: [att] ] readTagList: attName default: defaultBlock [ | att str output buffer ch | att := self valueOfAttribute: attName ifAbsent: [nil]. ^att == nil ifTrue: [defaultBlock value] ifFalse: [str := att readStream. output := OrderedCollection new. buffer := String new writeStream. [str skipSeparators; atEnd] whileFalse: [[(ch := str next) notNil and: [ch isSeparator not]] whileTrue: [buffer nextPut: ch]. output add: buffer contents. buffer reset]. output asArray] ] xslNodesFrom: aNodeContext [ | list nc | list := aNodeContext node selectNodes: [:nd | nd isAttribute not or: [nd tag qualifier ~= 'xmlns']]. nc := aNodeContext copy documentOrder. nc addAll: list. ^nc ] addToRuleDB: aDB [ "This is only understood by a small subset of commands." self shouldNotImplement ] defaultTag [ ^'xsl:' , self class tag ] defineVariable: aVariable [ self parent defineVariable: aVariable ] purgeUnimportant [ self subclassResponsibility ] sortList [ "Answer a list of sort blocks that take two arguments, and return -1 if the arguments are in order, 1 if they are in reversed order, and 0 if that particular sort block cannot order them." ^nil ] xslElements [ ^self children select: [:i | i isContent] ] generatesAttributes [ ^false ] isStylesheetEntry [ Transcript nl; tab; show: 'Stylesheet contains a top-level element that is not permitted (%1)' % {self tag}. Transcript nl; tab; show: 'It has been ignored'. ^false ] shouldStrip [ ^true ] initialize [ super initialize. elements := #(). userData := false ] normalize [ self stripSpace. self xslElements do: [:elm | elm normalize] ] stripSpace [ self shouldStrip ifTrue: [self elements: (self children select: [:t | t isBlankText not])] ] testPatternInitialized [ userData := true ] process: aNodeContext into: aProxy [ self subclassResponsibility ] process: aNodeContext into: aProxy takeArgumentsFrom: arguments [ self process: aNodeContext into: aProxy ] processAttributeSets: aNodeContext into: aProxy [ | list vars | self useAttrs isEmpty ifTrue: [^self]. vars := aNodeContext variables. aNodeContext variables: vars parent. self useAttrs do: [:attSetName | list := aNodeContext db attributesForSet: attSetName. list do: [:att | att process: aNodeContext into: aProxy]]. aNodeContext variables: vars ] processAttributeValue: aString for: aNodeContext [ | source ch output elm p expr | source := XPathReadStream on: aString. output := (String new: 64) writeStream. [source atEnd] whileFalse: [ch := source next. ch = ${ ifTrue: [(source peekFor: ${) ifTrue: [output nextPut: ${] ifFalse: [p := XPathParser new. p initScanner; xmlNode: self; functions: self class xslFunctions; init: source notifying: nil failBlock: nil. p expression. p atEndOfExpression ifFalse: [self error: 'Syntax error in: ' , aString storeString]. expr := p result. elm := expr xpathValueIn: aNodeContext. output nextPutAll: elm xpathAsString "Not needed with our XPath parser!" "p pastEnd ifFalse: [source skip: -1]"]] ifFalse: [ch = $} ifTrue: [source next = $} ifFalse: [self error: 'Expected doubled }']. output nextPut: $}] ifFalse: [output nextPut: ch]]]. ^output contents ] resolveComputedTag: nm [ | n type ns qualifier | ^(nm includes: $#) ifTrue: [self checkURISyntax: nm. n := nm findLast: [:c | c = $#]. type := nm copyFrom: n + 1 to: nm size. ns := nm copyFrom: 1 to: n - 1. qualifier := self findQualifierAtNamespace: 'quote:' , ns. qualifier == nil ifTrue: [qualifier := self findQualifierAtNamespace: ns]. qualifier == nil ifTrue: [self error: 'The namespace %1 has not been bound to a qualifier in this stylesheet, and automatic creation of qualifiers has not been implemented.' % {ns}]. NodeTag new qualifier: qualifier ns: ns type: type] ifFalse: [self checkQNameSyntax: nm. self resolveTag: nm] ] resolveTag: aTagString [ | c qual ns | c := aTagString occurrencesOf: $:. ^c = 0 ifTrue: [NodeTag new qualifier: '' ns: '' type: aTagString] ifFalse: [c > 1 ifTrue: [self error: 'A qualified name has too many colons.'] ifFalse: [c := aTagString indexOf: $:. (c = 1 or: [c = aTagString size]) ifTrue: [self error: 'A qualified name cannot begin or end with a colon.']. qual := aTagString copyFrom: 1 to: c - 1. ns := self findNamespaceAt: qual. ns == nil ifTrue: [self error: 'The namespace qualifier %1 has not been bound to a namespace in this stylesheet' % {qual}]. "Use a # in the match to make sure there's at least one more character" ('quote:#*' match: ns) ifTrue: [ns := ns copyFrom: 'quote:' size + 1 to: ns size]. NodeTag new qualifier: qual ns: ns type: (aTagString copyFrom: c + 1 to: aTagString size)]] ] selectAll: startNode withPattern: pattern [ ^pattern xpathValueIn: startNode ] valueAsVariableIn: aNodeContext [ | new list | ^self expression == nil ifTrue: [new := ElementProxy new. list := self xslElements. 1 to: list size do: [:i | | elm | elm := list at: i. elm process: aNodeContext into: new]. new] ifFalse: [self expression xpathValueIn: aNodeContext] ] ] ] Namespace current: XSL [ XSLCommand subclass: CallTemplateCommand [ | name | CallTemplateCommand class >> tag [ ^'call-template' ] process: aNodeContext into: aProxy [ | rule arguments list vars | rule := aNodeContext db ruleNamed: self name. arguments := Dictionary new. list := self xslElements. 1 to: list size do: [:i | (list at: i) process: aNodeContext intoArgs: arguments]. rule == nil ifTrue: [self error: 'Named template not found'] ifFalse: [vars := aNodeContext variables. aNodeContext variables: vars clone. rule process: aNodeContext into: aProxy arguments: arguments. aNodeContext variables: vars] ] name [ self testPatternInitialized. ^name ] testPatternInitialized [ userData ifTrue: [^self]. userData := true. name := self readAttribute: 'name' default: [nil] ] ] ] Namespace current: XSL [ XSLCommand subclass: XSLDefinition [ | importance | importance [ ^importance value ] importanceHolder: aValueHolder [ importance := aValueHolder ] replaceImportance: oldValue with: currentImportance [ importance == oldValue ifTrue: [importance := currentImportance] ] isStylesheetEntry [ ^true ] addToRuleDB: aDB [ "This is only understood by a small subset of commands." self subclassResponsibility ] ] ] Namespace current: XSL [ XSLDefinition subclass: Include [ | href | Include class >> tag [ ^'include' ] href [ self testPatternInitialized. ^href ] purgeUnimportant [ elements == nil ifFalse: [self error: 'Includes should not have contents.']. (self parent isKindOf: RuleSet) ifFalse: [self error: self tag asString , ' can only be used at the top level'] ] testPatternInitialized [ userData ifTrue: [^self]. userData := true. href := self readAttribute: 'href' ] addToRuleDB: aDB [ "This is only understood by a small subset of commands." | uri save | save := aDB importance. aDB importance: save copy. uri := aDB uriStack last resolveRelativePath: self href. aDB uriStack addLast: uri. aDB readStream: uri resource topLevel: false. aDB uriStack removeLast. aDB replaceImportance: save ] ] ] Namespace current: XSL [ XSLDefinition subclass: AttributeSet [ | name useAttrs | AttributeSet class >> tag [ ^'attribute-set' ] allAttributesFrom: aDB [ | all | all := Dictionary new. useAttrs do: [:setName | (aDB attributesForSet: setName) do: [:attr | all at: attr name put: attr]]. self xslElements do: [:attr | attr class == AttributeCommand ifFalse: [self error: 'Attribute sets only contain attributes']. all at: attr name put: attr]. ^all asOrderedCollection ] name [ self testPatternInitialized. ^name ] addToRuleDB: aDB [ "This is only understood by a small subset of commands." aDB addAttributeSet: self ] process: aNodeContext into: aProxy [ | list | list := self xslElements. 1 to: list size do: [:i | | elm | elm := list at: i. elm process: aNodeContext into: aProxy] ] purgeUnimportant [ elements := self children reject: [:i | i isBlankText]. elements do: [:elm | elm generatesAttributes ifFalse: [self error: 'xsl:attribute-set can contain only xsl:attribute and xsl:use']] ] testPatternInitialized [ userData ifTrue: [^self]. userData := true. name := self readAttribute: 'name'. useAttrs := self readTagList: 'use-attribute-sets' default: [#()] ] ] ] Namespace current: XSL [ XSLCommand subclass: CounterScopeCommand [ CounterScopeCommand class >> tag [ ^'counter-scope' ] process: aNodeContext into: aProxy [ | tempProxy | tempProxy := aProxy countingProxy. self xslElements do: [:elm | elm process: aNodeContext into: tempProxy] ] ] ] Namespace current: XSL [ XSLCommand subclass: CommentCommand [ CommentCommand class >> tag [ ^'comment' ] process: aNodeContext into: aProxy [ | oc str | oc := aProxy childProxy. self xslElements do: [:elm | elm process: aNodeContext into: oc]. oc attributes isEmpty ifFalse: [self error: 'Comments do not support attributes']. str := (String new: 128) writeStream. oc children do: [:nd | nd isText ifFalse: [self error: 'Comments can only contain text, not elements, pi''s, or other comments']. str nextPutAll: nd characterData]. str := str contents. "Need to do this twice to handle comments with a long run of -----" str := str copyReplaceAll: '--' with: '- -'. str := str copyReplaceAll: '--' with: '- -'. str last = $- ifTrue: [str := str copyWith: $ ]. aProxy addNode: (Comment new text: str) ] ] ] Namespace current: XSL [ XSLCommand subclass: ForEachCommand [ | selectPattern sortList variables | ForEachCommand class >> tag [ ^'for-each' ] addSortBlock: aSortCommand [ sortList == nil ifTrue: [sortList := #()]. sortList := sortList copyWith: aSortCommand ] defineVariable: aVariable [ variables add: aVariable. self parent defineVariable: aVariable ] selectPattern [ self testPatternInitialized. ^selectPattern ] sortList [ ^sortList ] initialize [ super initialize. elements := nil. variables := OrderedCollection new: 0 ] testPatternInitialized [ userData ifTrue: [^self]. userData := true. selectPattern := self readSelectPattern: 'select' ] process: aNodeContext into: aProxy [ | list elms listCopy | elms := self xslElements. list := self selectAll: aNodeContext withPattern: self selectPattern. self sortList == nil ifTrue: [list documentOrder; ensureSorted] ifFalse: [listCopy := list shallowCopy. list sort: [:n1 :n2 | self collate: n1 to: n2 within: listCopy]]. list reset. [list atEnd] whileFalse: [list next. 1 to: elms size do: [:i | | elm | elm := elms at: i. elm process: list into: aProxy]] ] ] ] Namespace current: XSL [ XSLCommand subclass: SortCommand [ | selectPattern order lang dataType caseOrder | SortCommand class >> tag [ ^'sort' ] caseOrder [ self testPatternInitialized. ^caseOrder ] dataType [ self testPatternInitialized. ^dataType ] lang [ self testPatternInitialized. ^lang ] order [ self testPatternInitialized. ^order ] selectPattern [ self testPatternInitialized. ^selectPattern ] normalize [ super normalize. (self parent respondsTo: #addSortBlock:) ifFalse: [self error: self tag asString , ' can''t be a child element of ' , self parent tag asString]. self parent addSortBlock: self ] testPatternInitialized [ userData ifTrue: [^self]. userData := true. selectPattern := self readSelectPattern: 'select' default: ['.']. order := self readAttribute: 'order' default: ['ascending']. lang := self readAttribute: 'lang' default: [nil]. dataType := self readAttribute: 'data-type' default: ['text']. caseOrder := self readAttribute: 'case-order' default: ['upper-first'] ] collate: node1 to: node2 within: aNodeContext [ | v1 v2 result collate | collate := aNodeContext. collate indexForNode: node1. v1 := self selectPattern xpathValueIn: collate. collate indexForNode: node2. v2 := self selectPattern xpathValueIn: collate. dataType = 'number' ifTrue: [result := (v1 xpathAsNumber - v2 xpathAsNumber) sign] ifFalse: [result := v1 xpathAsString < v2 xpathAsString]. order = 'descending' ifTrue: [result := result negated]. ^result ] process: aNodeContext into: aProxy [ "Do nothing. I am only present as a modifier on for-each or apply-templates" ^self ] process: aNodeContext intoArgs: aDictionary [ "Do nothing. I am only present as a modifier on for-each or apply-templates. For compatibility with " ^self ] ] ] Namespace current: XSL [ XSLDefinition subclass: DecimalFormat [ DecimalFormat class >> tag [ ^'decimal-format' ] addToRuleDB: aDB [ "This is only understood by a small subset of commands." self notYetImplemented ] purgeUnimportant [ elements == nil ifFalse: [self error: 'Format declarations should not have contents'] ] ] ] Namespace current: XSL [ XSLCommand subclass: ElementCommand [ | name useAttrs | ElementCommand class >> tag [ ^'element' ] name [ self testPatternInitialized. ^name ] useAttrs [ self testPatternInitialized. ^useAttrs ] testPatternInitialized [ userData ifTrue: [^self]. userData := true. name := self readTag: 'name'. useAttrs := self readTagList: 'use-attribute-sets' default: [#()] ] process: aNodeContext into: aProxy [ | oc nm list | oc := aProxy childProxy. self processAttributeSets: aNodeContext into: oc. list := self xslElements. 1 to: list size do: [:i | | elm | elm := list at: i. elm process: aNodeContext into: oc]. nm := self processAttributeValue: self name for: aNodeContext. nm := self resolveComputedTag: nm. aProxy addNode: (Element tag: nm attributes: oc attributes elements: oc children) ] ] ] Namespace current: XSL [ XSLCommand subclass: CountingCommand [ | format prefix postfix lang letterValue digitGroupSep digitsPerGroup sequenceSrc | digitGroupSep [ self testPatternInitialized. ^digitGroupSep ] digitsPerGroup [ self testPatternInitialized. ^digitsPerGroup ] format [ self testPatternInitialized. ^format ] lang [ self testPatternInitialized. ^lang ] letterValue [ self testPatternInitialized. ^letterValue ] sequenceSrc [ self testPatternInitialized. ^sequenceSrc ] format: number by: aFormat [ | n s | aFormat size = 1 ifFalse: [self error: 'Unrecognized number format = "%1"' % {aFormat}]. aFormat = 'a' ifTrue: [n := self radix: number base: 26. s := n collect: [:i | (i + $a asInteger) asCharacter]. ^String withAll: s]. aFormat = 'A' ifTrue: [n := self radix: number base: 26. s := n collect: [:i | (i + $A asInteger) asCharacter]. ^String withAll: s]. aFormat = 'i' ifTrue: [^self romanNumeral: number]. aFormat = 'I' ifTrue: [^(self romanNumeral: number) asUppercase]. aFormat = '1' ifTrue: [^number printString]. self error: 'Unrecognized format' ] radix: number base: b [ | out n | n := number - 1. n < b ifTrue: [^Array with: n]. out := OrderedCollection new. n := number. [n < b] whileFalse: [out addFirst: n \\ b. n := n // b]. out addFirst: n - 1. ^out ] romanNumeral: number [ | n cycle output idx letters digit | n := number. cycle := #('ivx' 'xlc' 'cdm'). output := OrderedCollection new. idx := 0. [n = 0] whileFalse: [letters := cycle at: (idx := idx + 1). digit := n \\ 10. digit := #(#() #(1) #(1 1) #(1 1 1) #(1 2) #(2) #(2 1) #(2 1 1) #(2 1 1 1) #(1 3)) at: digit + 1. output addAllFirst: (digit collect: [:i | letters at: i]). n := n // 10]. ^String withAll: output ] tokenizeFormat: aString [ | str isFormat tok tokens t resultFormat | str := aString readStream. tokens := OrderedCollection new. isFormat := [:ch | ch isDigit or: [ch isLetter]]. [str atEnd] whileFalse: [tok := ''. (isFormat value: str peek) ifTrue: [[str atEnd or: [(isFormat value: str peek) not]] whileFalse: [tok := tok copyWith: str next]] ifFalse: [[str atEnd or: [isFormat value: str peek]] whileFalse: [tok := tok copyWith: str next]]. tokens add: tok]. (tokens isEmpty or: [isFormat value: tokens first first]) ifFalse: [prefix := tokens removeFirst]. (tokens isEmpty or: [isFormat value: tokens last first]) ifFalse: [postfix := tokens removeLast]. tokens size = 0 ifTrue: [resultFormat := nil] ifFalse: [tokens size = 1 ifTrue: [resultFormat := (NumberFormat new) format: tokens first; separator: '.'. resultFormat nextLink: resultFormat] ifFalse: [t := (1 to: tokens size by: 2) collect: [:i | (NumberFormat new) format: (tokens at: i); separator: (tokens at: (i + 1 min: tokens size - 1))]. 1 to: t size do: [:i | (t at: i) nextLink: (t at: (i + 1 min: t size))]. resultFormat := t first]]. ^resultFormat ] testPatternInitialized [ userData ifTrue: [^self]. userData := true. format := self readAttribute: 'format' default: ['1']. lang := self readAttribute: 'xml:lang' default: [nil]. letterValue := self readAttribute: 'letter-value' default: [nil]. digitGroupSep := self readAttribute: 'digit-group-sep' default: [nil]. digitsPerGroup := self readInteger: 'n-digits-per-group' default: [3]. sequenceSrc := self readAttribute: 'sequence-src' default: [nil] ] format: countList for: aNodeContext [ | str fmt | str := String new writeStream. fmt := self processAttributeValue: self format for: aNodeContext. fmt := self tokenizeFormat: fmt. prefix == nil ifFalse: [str nextPutAll: prefix]. 1 to: countList size do: [:i | str nextPutAll: (self format: (countList at: i) by: fmt format). i = countList size ifFalse: [str nextPutAll: fmt separator]. fmt := fmt nextLink]. postfix == nil ifFalse: [str nextPutAll: postfix]. ^str contents ] ] ] Namespace current: XSL [ CountingCommand subclass: CountersCommand [ | name | CountersCommand class >> tag [ ^'counters' ] testPatternInitialized [ userData ifTrue: [^self]. super testPatternInitialized. name := self readAttribute: 'name'. userData := true ] name [ self testPatternInitialized. ^name ] process: aNodeContext into: aProxy [ | list | list := OrderedCollection new. aProxy counterValuesNamed: self name into: list. aProxy add: (Text new text: (self format: list for: aNodeContext)) ] ] ] Namespace current: XSL [ XSLDefinition subclass: ParamDefinition [ | name expression | ParamDefinition class >> tag [ ^'param' ] addToRuleDB: aDB [ "This is only understood by a small subset of commands." aDB addVariable: self ] process: aNodeContext into: aProxy [ self shouldNotImplement ] process: aNodeContext into: aProxy takeArgumentsFrom: arguments [ | val | val := arguments at: self name ifAbsent: []. val == nil ifTrue: [val := self valueAsVariableIn: aNodeContext]. aNodeContext variables at: self name put: val ] expression [ self testPatternInitialized. ^expression ] name [ self testPatternInitialized. ^name ] purgeUnimportant [ ^self ] normalize [ super normalize. self parent defineParameter: self ] testPatternInitialized [ userData ifTrue: [^self]. userData := true. name := self readAttribute: 'name'. expression := self readSelectPattern: 'select' default: []. (expression notNil and: [self children isEmpty not]) ifTrue: [self error: 'A parameter cannot have both content and a select attribute'] ] isStylesheetEntry [ ^true ] ] ] Namespace current: XSL [ XSLCommand subclass: ChooseWhenCommand [ | testPattern | ChooseWhenCommand class >> tag [ ^'when' ] testPatternInitialized [ userData ifTrue: [^self]. userData := true. testPattern := self readSelectPattern: 'test' ] testPattern [ self testPatternInitialized. ^testPattern ] process: aNodeContext into: aProxy [ self shouldNotImplement ] ] ] Namespace current: XSL [ XSLCommand subclass: WithParamCommand [ | name expression | WithParamCommand class >> tag [ ^'with-param' ] expression [ self testPatternInitialized. ^expression ] name [ self testPatternInitialized. ^name ] testPatternInitialized [ userData ifTrue: [^self]. userData := true. name := self readAttribute: 'name'. expression := self readSelectPattern: 'select' default: []. (expression notNil and: [self children isEmpty not]) ifTrue: [self error: 'A parameter cannot have both content and a select attribute'] ] process: aNodeContext into: aProxy [ self shouldNotImplement ] process: aNodeContext intoArgs: aDictionary [ | val | val := self valueAsVariableIn: aNodeContext. aDictionary at: self name put: val ] ] ] Namespace current: XSL [ XSLDefinition subclass: Import [ | href | Import class >> tag [ ^'import' ] href [ self testPatternInitialized. ^href ] purgeUnimportant [ | idx | elements == nil ifFalse: [self error: 'Imports should not have contents.']. (self parent isKindOf: RuleSet) ifFalse: [self error: self tag asString , ' can only be used at the top level']. idx := self parent children indexOf: self. (idx = 1 or: [(self parent children at: idx - 1) class == self class]) ifFalse: [self error: 'All imports must come first in the stylesheet'] ] testPatternInitialized [ userData ifTrue: [^self]. userData := true. href := self readAttribute: 'href' ] addToRuleDB: aDB [ "This is only understood by a small subset of commands." | uri | uri := aDB uriStack last resolveRelativePath: self href. aDB uriStack addLast: uri. aDB readStream: uri resource topLevel: false. aDB uriStack removeLast. aDB raiseImportance ] ] ] Namespace current: XSL [ XSLCommand subclass: Template [ | hasStripped | importanceHolder: dummy [ ] purgeUnimportant [ ^self ] importance [ "Really only needs to be > 0 to beat the builtin rule that matches against the root of the document, but we throw in a bit of paranoia." ^1000 ] match: aNodeContext [ ^aNodeContext node isDocument ] modeIsLike: aMode [ ^aMode isNil ] process: aNodeContext into: aProxy [ | oc list | oc := aProxy childProxy. oc attributes: (self processAttributes: self attributes for: aNodeContext). list := self xslElements. 1 to: list size do: [:i | | elm | elm := list at: i. elm process: aNodeContext into: oc]. aProxy addNode: (Element tag: tag attributes: oc attributes elements: oc children) ] process: aNodeContext into: aProxy arguments: arguments [ "The arguments are ignored because, if I am being used as a top-level stylesheet, there's no place to declare the top-level definitions." self process: aNodeContext into: aProxy ] processAttributes: attList for: aNodeContext [ | newList substitution newAtt | newList := OrderedCollection new. attList do: [:att | att tag namespace = XSL_URI ifTrue: [newAtt := self processXSLAttribute: att for: aNodeContext. newAtt == nil ifFalse: [newList add: newAtt]]]. attList do: [:att | att tag namespace = XSL_URI ifFalse: [substitution := self processAttributeValue: att value for: aNodeContext. newAtt := Attribute name: att key value: substitution. newList add: newAtt]]. ^newList isEmpty ifTrue: [nil] ifFalse: [newList asArray] ] processXSLAttribute: att for: aNodeContext [ att tag type = 'version' ifTrue: ["aNodeContext db version: att value." ^nil]. att tag type = 'use-attribute-set' ifTrue: [^self notYetImplementedError]. ^self notYetImplementedError ] topLevelAddToRuleDB: aDB [ "This is only understood by a small subset of commands." self tag namespace = XSL_URI ifTrue: [self error: '"%1" not recognized as an XSL command' % {self tag asString}]. aDB addRule: self ] ] ] Namespace current: XSL [ XSLDefinition subclass: VariableDefinition [ | name expression | VariableDefinition class >> tag [ ^'variable' ] addToRuleDB: aDB [ "This is only understood by a small subset of commands." aDB addVariable: self ] process: aNodeContext into: aProxy [ | val | val := self valueAsVariableIn: aNodeContext. aNodeContext variables at: name put: val ] expression [ self testPatternInitialized. ^expression ] name [ self testPatternInitialized. ^name ] purgeUnimportant [ ^self ] normalize [ super normalize. self parent defineVariable: self ] testPatternInitialized [ userData ifTrue: [^self]. userData := true. name := self readAttribute: 'name'. expression := self readSelectPattern: 'select' default: []. (expression notNil and: [self children isEmpty not]) ifTrue: [self error: 'A parameter cannot have both content and a select attribute'] ] isStylesheetEntry [ ^true ] ] ] Namespace current: XSL [ XSLCommand subclass: CounterIncrementCommand [ | name amount | CounterIncrementCommand class >> tag [ ^'counter-increment' ] amount [ self testPatternInitialized. ^amount ] name [ self testPatternInitialized. ^name ] testPatternInitialized [ userData ifTrue: [^self]. super testPatternInitialized. name := self readAttribute: 'name'. amount := self readInteger: 'amount' default: [1]. userData := true ] process: aNodeContext into: aProxy [ | c | c := aProxy counterNamed: self name. c == nil ifTrue: [c := aProxy root resetCounter: self name]. c value: c value + 1 ] ] ] Namespace current: XSL [ Array subclass: Rank [ rankAgainst: aRank [ "Assume two Ranks, of sizes M and N, where M >= N. If they have the same elements in the first N elements, the shorter Rank has higher priority. If there is a difference in the first N elements, assume that the first difference occurs at slot S. The Rank whose value at S is greater has higher priority." | min r ranks | ranks := #(#higher #same #lower). min := self size min: aRank size. 1 to: min do: [:i | r := ((aRank at: i) - (self at: i)) sign. r = 0 ifFalse: [^ranks at: r + 2]]. ^ranks at: (self size - aRank size) sign + 2 ] ] ] Namespace current: XSL [ Link subclass: NumberFormat [ | format separator | format [ ^format ] format: s [ format := s ] separator [ ^separator ] separator: s [ separator := s ] printOn: aStream [ format == nil ifFalse: [aStream nextPutAll: format]. separator == nil ifFalse: [aStream nextPutAll: separator]. (nextLink == nil or: [nextLink == self]) ifFalse: [nextLink printOn: aStream] ] ] ] Namespace current: XSL [ XML.Text subclass: TextTemplate [ | hasStripped | normalize [ ^self ] stripSpace [ ^self ] isStylesheetEntry [ | s | s := text readStream. s skipSeparators. s atEnd ifFalse: [self error: 'Text contains something other than whitespace.']. ^false ] process: aNodeContext into: aProxy [ self text isEmpty ifFalse: [aProxy addNode: (Text new text: self text)] ] ] ] Namespace current: XSL [ CountingCommand subclass: NumberCommand [ | level count from | NumberCommand class >> tag [ ^'number' ] countFor: aNode [ aNode isElement ifFalse: [self halt: 'Counting things other than elements is not supported yet']. self testPatternInitialized. ^count == nil ifTrue: [(XPathChildNode new) axisName: 'child'; baseTest: ((XPathTaggedNodeTest new) namespace: aNode tag namespace; type: aNode tag type)] ifFalse: [count] ] from [ self testPatternInitialized. ^from ] level [ self testPatternInitialized. ^level ] testPatternInitialized [ userData ifTrue: [^self]. super testPatternInitialized. level := (self readAttribute: 'level' default: [#single]) asSymbol. count := self readMatchPattern: 'count' default: [nil]. from := self readMatchPattern: 'from' default: [nil]. userData := true ] process: aNodeContext into: aProxy [ self level == #single ifTrue: [^self processSingle: aNodeContext into: aProxy]. self level == #multi ifTrue: [^self processMulti: aNodeContext into: aProxy]. self level == #any ifTrue: [^self processAny: aNodeContext into: aProxy]. ^self error: 'Unsupported numbering mode' ] processAny: aNodeContext into: aProxy [ | n countP | n := 0. countP := self countFor: aNodeContext node. (NodeIterator new) node: aNodeContext node; reverseDo: [:nd | (countP match: ((aNodeContext copy) add: nd; index: 1)) ifTrue: [n := n + 1]] until: [:nd | self from notNil and: [self from match: ((aNodeContext copy) add: nd; index: 1)]]. aProxy addNode: (Text new text: (self format: (Array with: n) for: aNodeContext)) ] processMulti: aNodeContext into: aProxy [ | allNodes n counts countP sibSelect cnt sibs | countP := self countFor: aNodeContext node. allNodes := aNodeContext copy. n := aNodeContext node. [n == nil or: [self from notNil and: [self from match: n]]] whileFalse: [allNodes add: n. n := n parent]. allNodes := allNodes selectMatch: countP. allNodes documentOrder; index: 1. sibSelect := XPathParser parse: '../node()' as: #expression. counts := OrderedCollection new. allNodes reset. [allNodes atEnd] whileFalse: [allNodes next. cnt := 1. sibs := sibSelect xpathValueIn: allNodes. sibs reset; next. [sibs node == allNodes node] whileFalse: [(countP match: sibs) ifTrue: [cnt := cnt + 1]. sibs next]. counts add: cnt]. aProxy addNode: (Text new text: (self format: counts asArray for: aNodeContext)) ] processSingle: aNodeContext into: aProxy [ | allNodes n cnt countP sibSelect sibs | countP := self countFor: aNodeContext node. allNodes := aNodeContext copy. n := aNodeContext node. [n == nil or: [self from notNil and: [self from match: n]]] whileFalse: [allNodes add: n. n := n parent]. allNodes := allNodes selectMatch: countP. allNodes size = 0 ifTrue: [^self]. allNodes inverseDocumentOrder; index: 1. sibSelect := XPathParser parse: '../node()' as: #expression. sibs := sibSelect xpathValueIn: allNodes. sibs reset; next. cnt := 1. [sibs node == allNodes node] whileFalse: [(countP match: sibs) ifTrue: [cnt := cnt + 1]. sibs next]. aProxy addNode: (Text new text: (self format: (Array with: cnt) for: aNodeContext)) ] ] ] Namespace current: XSL [ XSLDefinition subclass: OutputCommand [ | method version encoding omitXmlDeclaration standalone doctypePublic doctypeSystem cdataSectionElements indent mediaType | OutputCommand class >> tag [ ^'output' ] method [ method == nil ifTrue: [method := self readAttribute: 'method' default: [#auto]]. ^method ] purgeUnimportant [ elements == nil ifFalse: [self error: 'Output declarations should not have contents'] ] addToRuleDB: aDB [ "This is only understood by a small subset of commands." aDB setOutput: self ] ] ] Namespace current: XSL [ XSLCommand subclass: CopyCommand [ | useAttrs | CopyCommand class >> tag [ ^'copy' ] useAttrs [ self testPatternInitialized. ^useAttrs ] process: aNodeContext into: aProxy [ aNodeContext node isAttribute ifTrue: [self useAttrs isEmpty ifFalse: [self error: ' is attempting to add attributes to an Attribute']. ^self processAttribute: aNodeContext into: aProxy]. aNodeContext node isElement ifTrue: [^self processElement: aNodeContext into: aProxy]. (aNodeContext node isComment or: [aNodeContext node isText]) ifTrue: [self useAttrs isEmpty ifFalse: [self error: ' is attempting to add attributes to a non-Element']. ^aProxy add: aNodeContext node copy]. ^self error: 'Copying of this node type is not yet implemented' ] processAttribute: aNodeContext into: aProxy [ aProxy addAttribute: (Attribute new name: aNodeContext node tag value: aNodeContext node value) ] processElement: aNodeContext into: aProxy [ | oc list | oc := aProxy childProxy. self processAttributeSets: aNodeContext into: oc. list := self xslElements. 1 to: list size do: [:i | | elm | elm := list at: i. elm process: aNodeContext into: oc]. aProxy addNode: (Element tag: aNodeContext node tag attributes: oc attributes elements: oc children) ] testPatternInitialized [ userData ifTrue: [^self]. userData := true. useAttrs := self readTagList: 'use-attribute-sets' default: [#()] ] ] ] Namespace current: XSL [ XSLCommand subclass: ValueOfCommand [ | expression | ValueOfCommand class >> tag [ ^'value-of' ] expression [ self testPatternInitialized. ^expression ] testPatternInitialized [ userData ifTrue: [^self]. userData := true. expression := self readSelectPattern: 'select' ] process: aNodeContext into: aProxy [ | elm | elm := self expression xpathValueIn: aNodeContext. (elm == nil or: [(elm := elm xpathAsString) isEmpty]) ifFalse: [aProxy addNode: (Text new text: elm)] ] ] ] Namespace current: XSL [ XSLDefinition subclass: Rule [ | pattern name specific priority mode variables | Rule class >> formatText: aNode [ | text tab a nbsp | a := Attribute new name: 'CLASS' value: 'body'. text := aNode characterData. nbsp := (Character codePoint: 160) asString. tab := nbsp , nbsp , nbsp , nbsp. text := text copyReplaceAll: 9 asCharacter asString with: tab. text := text substrings: Character nl. ^text collect: [:t | t isEmpty ifTrue: [Element tag: 'BR'] ifFalse: [Element tag: 'P' attributes: (Array with: a copy) elements: (Array with: (Text new text: t))]] ] Rule class >> tag [ ^'template' ] defineParameter: aVariable [ | old | old := variables detect: [:var | var name = aVariable name] ifNone: []. (old == nil or: [old == aVariable]) ifFalse: [self error: 'The parameter "' , aVariable name , '" is shadowing another variable in the same template']. old == nil ifTrue: [variables add: aVariable] ] defineVariable: aVariable [ | old | old := variables detect: [:var | var name = aVariable name] ifNone: []. (old == nil or: [old == aVariable]) ifFalse: [self error: 'The variable "' , aVariable name , '" is shadowing another variable in the same template']. old == nil ifTrue: [variables add: aVariable] ] mode [ self testPatternInitialized. ^mode ] mode: aMode [ mode := aMode ] name [ self testPatternInitialized. ^name ] pattern [ self testPatternInitialized. ^pattern ] priority [ self testPatternInitialized. ^priority ] priority: aNumber [ priority := aNumber ] purgeUnimportant [ ^self ] isStylesheetEntry [ ^true ] match: aNodeContext [ ^self pattern notNil and: [self pattern match: aNodeContext] ] modeIsLike: aMode [ "We can use #any as the 'accept any mode', because normal modes are strings. If this is changed, the marker for 'any mode' would need to be changed." ^mode = aMode or: [mode == #any] ] computeDefaultPriority: expr [ | list | ^expr class == XPathUnion ifTrue: [list := Set new. expr arguments do: [:expr2 | list add: (self computeDefaultPriority: expr2)]. list size = 1 ifTrue: [list asArray first] ifFalse: [#notKnown]] ifFalse: [((expr class == XPathChildNode or: [expr class == XPathAttributeNode]) and: [expr child isTerminator and: [expr predicates isEmpty]]) ifTrue: [expr baseTest class == XPathTaggedNodeTest ifTrue: [expr baseTest type == #* ifTrue: [expr baseTest namespace == nil ifTrue: [-0.5] ifFalse: [-0.25]] ifFalse: [0.0]] ifFalse: [('processing-instruction(*)' match: expr printString) ifTrue: [self halt] ifFalse: [-0.5]]] ifFalse: [0.5]] ] initialize [ super initialize. priority := 0. variables := OrderedCollection new ] normalize [ super normalize. (self parent == nil or: [self parent isKindOf: RuleSet]) ifFalse: [self error: self tag asString , ' can only be used at the top level'] ] testPatternInitialized [ userData ifTrue: [^self]. userData := true. name := self readAttribute: 'name' default: [nil]. pattern := self readMatchPattern: 'match' default: [nil]. priority := self readInteger: 'priority' default: [self computeDefaultPriority: self pattern]. mode := self readAttribute: 'mode' default: [nil] ] addToRuleDB: aDB [ "This is only understood by a small subset of commands." self pattern == nil ifFalse: [aDB addRule: self]. self name == nil ifFalse: [aDB addNamedTemplate: self]. (self pattern == nil and: [self name == nil]) ifTrue: [self error: 'Templates must have either a name or match attribute or both'] ] process: aNodeContext into: aProxy [ self shouldNotImplement ] process: aNodeContext into: aProxy arguments: arguments [ | list | list := self xslElements. 1 to: list size do: [:i | | elm | elm := list at: i. elm process: aNodeContext into: aProxy takeArgumentsFrom: arguments] ] ] ] Namespace current: XSL [ XSLCommand subclass: CounterResetCommand [ | name | CounterResetCommand class >> tag [ ^'counter-reset' ] testPatternInitialized [ userData ifTrue: [^self]. super testPatternInitialized. name := self readAttribute: 'name'. userData := true ] name [ self testPatternInitialized. ^name ] process: aNodeContext into: aProxy [ aProxy resetCounter: self name ] ] ] Namespace current: XSL [ XML.SAXWriter subclass: SAXHtmlWriter [ | htmlSpecialEmptyTags | endElement: namespaceURI localName: localName qName: name [ namespaceURI isEmpty ifFalse: [^super endElement: namespaceURI localName: localName qName: name]. hasOpenTag ifTrue: [(self htmlSpecialEmptyTags includes: name asLowercase) ifTrue: [output nextPutAll: '>'] ifFalse: [output nextPutAll: '/>']] ifFalse: [output nextPutAll: '']. hasOpenTag := false ] startElement: namespaceURI localName: localName qName: name attributes: attributes [ namespaceURI isEmpty ifFalse: [^super startElement: namespaceURI localName: localName qName: name attributes: attributes]. self closeOpenTag. output nextPutAll: '<'. output nextPutAll: name asLowercase. (self sort: attributes) do: [:att | output space. output nextPutAll: att tag asString asLowercase. (self isBoolean: att in: name) ifFalse: [output nextPutAll: '="'. 1 to: att value size do: [:i | | ch mapped | ch := att value at: i. mapped := attrMap at: ch ifAbsent: [nil]. mapped == nil ifTrue: [output nextPut: ch] ifFalse: [output nextPutAll: mapped]]]. output nextPutAll: '"']. hasOpenTag := true. name asLowercase = 'head' ifTrue: [| atts | atts := OrderedCollection new. atts add: ((Attribute new) tag: (NodeTag new qualifier: '' ns: '' type: 'http-equiv'); value: 'Content-Type'). atts add: ((Attribute new) tag: (NodeTag new qualifier: '' ns: '' type: 'content'); value: 'text/html; charset=utf-8'). atts := atts asArray. self startElement: '' localName: 'meta' qName: 'meta' attributes: atts. self endElement: '' localName: 'meta' qName: 'meta'] ] htmlSpecialEmptyTags [ htmlSpecialEmptyTags == nil ifTrue: [htmlSpecialEmptyTags := #('area' 'base' 'basefont' 'br' 'col' 'frame' 'hr' 'img' 'input' 'isindex' 'link' 'meta' 'param')]. ^htmlSpecialEmptyTags ] htmlSpecialEmptyTags: aList [ htmlSpecialEmptyTags := aList ] isBoolean: attribute in: elementTag [ ^false ] ] ] Namespace current: XSL [ XSLCommand subclass: ChooseCommand [ ChooseCommand class >> tag [ ^'choose' ] elements: aList [ | newList hasOtherwise | newList := aList select: [:i | i isContent and: [i isBlankText not]]. hasOtherwise := false. newList do: [:elm | elm class = ChooseOtherwiseCommand ifTrue: [hasOtherwise ifTrue: [self error: 'xsl:choose with multiple xsl:otherwise commands']. hasOtherwise := true] ifFalse: [elm class = ChooseWhenCommand ifFalse: [self error: 'xsl:choose can only contain xsl:when and xsl:otherwise']]]. super elements: newList ] process: aNodeContext into: aProxy [ | alt match list | alt := match := nil. elements do: [:elm | elm class == ChooseOtherwiseCommand ifTrue: [alt := elm] ifFalse: [(match == nil and: [(elm testPattern xpathValueIn: aNodeContext) xpathAsBoolean]) ifTrue: [match := elm]]]. match == nil ifTrue: [match := alt]. match notNil ifTrue: [list := match xslElements. 1 to: list size do: [:i | | elm | elm := list at: i. elm process: aNodeContext into: aProxy]] ] ] ] Namespace current: XSL [ Dictionary subclass: ChainedDictionary [ | parent | associationAt: anIndex ifAbsent: aBlock [ ^super associationAt: anIndex ifAbsent: [parent associationAt: anIndex ifAbsent: aBlock] ] at: anIndex ifAbsent: aBlock [ ^super at: anIndex ifAbsent: [parent at: anIndex ifAbsent: aBlock] ] clone [ ^self class new parent: parent ] parent [ ^parent ] parent: aParent [ aParent == nil ifTrue: [self halt]. parent := aParent ] size [ | s | s := Set new. self keysAndValuesDo: [:k :v | s add: k]. ^s size ] associationsDo: aBlock [ "Evaluate aBlock for each of the receiver's key/value associations." self keysAndValuesDo: [:k :v | aBlock value: k -> v] ] includesKey: key [ "Answer whether the receiver has a key equal to the argument, key." ^(super includesKey: key) or: [parent includesKey: key] ] do: aBlock [ "Evaluate aBlock with each of the receiver's elements as the argument." self keysDo: [:k | aBlock value: (self at: k)] ] keysAndValuesDo: aBlock [ "Evaluate aBlock with each of the receiver's key/value pairs as the arguments." | keys | keys := Set new. super keysAndValuesDo: [:k :v | keys add: k]. parent keysAndValuesDo: [:k :v | keys add: k]. keys do: [:k | aBlock value: k value: (self at: k)] ] changeCapacityTo: newCapacity [ | newSelf | newSelf := self copyEmpty: newCapacity. newSelf parent: parent. super associationsDo: [:each | newSelf noCheckAdd: each]. self become: newSelf ] ] ] Namespace current: XSL [ XSLCommand subclass: IfCommand [ | testPattern | IfCommand class >> tag [ ^'if' ] testPatternInitialized [ userData ifTrue: [^self]. userData := true. testPattern := self readSelectPattern: 'test' ] testPattern [ self testPatternInitialized. ^testPattern ] process: aNodeContext into: aProxy [ | list | (self testPattern xpathValueIn: aNodeContext) xpathAsBoolean ifTrue: [list := self xslElements. 1 to: list size do: [:i | | elm | elm := list at: i. elm process: aNodeContext into: aProxy]] ] ] ] Namespace current: XSL [ XML.PI subclass: XSL_PI [ | block | stripSpace [ ^self ] isContent [ ^name = 'vwst_xsl' ] isStylesheetEntry [ ^name = 'vwst_xsl' ] process: aNodeContext into: aProxy [ block == nil ifTrue: [block := Behavior evaluate: text]. (block class == BlockClosure and: [block numArgs = 1]) ifFalse: [self error: '"' , text , '" is not a legal Smalltalk processing instruction']. aProxy addAll: (block value: aNodeContext) ] normalize [ ^self ] ] ] Namespace current: XSL [ Link subclass: GeneralCountingProxy [ | counters | childProxy [ ^(ElementProxy new) nextLink: self; yourself ] counterNamed: nm [ | c | counters == nil ifTrue: [c := nil] ifFalse: [c := counters at: nm ifAbsent: []]. ^c == nil ifTrue: [nextLink == nil ifTrue: [nil] ifFalse: [nextLink counterNamed: nm]] ifFalse: [c] ] counterValuesNamed: nm into: list [ | c | self nextLink == nil ifFalse: [self nextLink counterValuesNamed: nm into: list]. counters == nil ifTrue: [c := nil] ifFalse: [c := counters at: nm ifAbsent: []]. c == nil ifFalse: [list add: c value] ] countingProxy [ ^(CountingProxy new) nextLink: self; yourself ] resetCounter: nm [ counters == nil ifTrue: [counters := Dictionary new]. counters at: nm put: 0 asValue. ^counters at: nm ] root [ | n | n := self. [n nextLink == nil] whileFalse: [n := n nextLink]. ^n ] ] ] Namespace current: XSL [ GeneralCountingProxy subclass: ElementProxy [ | contents attributes | addAttribute: attribute [ self attributes: (self attributes copyWith: attribute) ] addNode: element [ self children: (self children copyWith: element) ] attributes [ attributes == nil ifTrue: [attributes := #()]. ^attributes ] attributes: list [ attributes := list ] children [ contents == nil ifTrue: [contents := #()]. ^contents ] children: list [ contents := list ] xpathAsBoolean [ ^self xpathAsString xpathAsBoolean ] xpathAsNumber [ ^self xpathAsString xpathAsNumber ] xpathAsString [ | result | self children isEmpty ifTrue: [^'']. self children size = 1 ifTrue: [^self children first xpathStringData]. result := (String new: 40) writeStream. 1 to: self children size do: [:i | result nextPutAll: (self children at: i) xpathStringData]. ^result contents ] addToXPathHolder: anAssociation for: aNodeContext [ anAssociation value == nil ifTrue: [^anAssociation value: self]. anAssociation value xpathIsNodeSet ifTrue: [^self error: 'An XPath expression is answering a combination of Nodes and non-Nodes']. self error: 'An XPath expression is answering more than one non-Node value' ] ] ] Namespace current: XSL [ XSLCommand subclass: PICommand [ | name | PICommand class >> tag [ ^'pi' ] testPatternInitialized [ userData ifTrue: [^self]. userData := true. name := self readTag: 'name' ] name [ self testPatternInitialized. ^name ] process: aNodeContext into: aProxy [ | oc str | oc := aProxy childProxy. self xslElements do: [:elm | elm process: aNodeContext into: oc]. oc attributes isEmpty ifFalse: [self error: 'Comments do not support attributes']. str := (String new: 128) writeStream. oc children do: [:nd | nd isText ifFalse: [self error: 'Comments can only contain text, not elements, pi''s, or other comments']. str nextPutAll: nd characterData]. str := str contents. str := str copyReplaceAll: '?>' with: '? >'. aProxy addNode: (PI new name: self name text: str) ] ] ] Namespace current: XSL [ CountingCommand subclass: CounterCommand [ | name | CounterCommand class >> tag [ ^'counter' ] testPatternInitialized [ userData ifTrue: [^self]. super testPatternInitialized. name := self readAttribute: 'name'. userData := true ] name [ self testPatternInitialized. ^name ] process: aNodeContext into: aProxy [ | c | c := aProxy counterNamed: self name. c == nil ifFalse: [aProxy add: (Text new text: (self format: (Array with: c value) for: aNodeContext))] ] ] ] Namespace current: XSL [ XSLCommand subclass: ApplyTemplatesCommand [ | selectPattern sortList mode | ApplyTemplatesCommand class >> tag [ ^'apply-templates' ] addSortBlock: aSortCommand [ sortList == nil ifTrue: [sortList := #()]. sortList := sortList copyWith: aSortCommand ] mode [ self testPatternInitialized. ^mode ] selectPattern [ self testPatternInitialized. ^selectPattern ] sortList [ ^sortList ] testPatternInitialized [ userData ifTrue: [^self]. userData := true. selectPattern := self readSelectPattern: 'select' default: [nil]. mode := self readAttribute: 'mode' default: [nil] ] process: aNodeContext into: aProxy [ | list rule arguments argList listCopy | self selectPattern == nil ifTrue: [list := self xslNodesFrom: aNodeContext] ifFalse: [list := self selectAll: aNodeContext withPattern: self selectPattern]. self sortList == nil ifTrue: [list documentOrder; ensureSorted] ifFalse: [listCopy := list shallowCopy. list sort: [:n1 :n2 | self collate: n1 to: n2 within: listCopy]]. arguments := Dictionary new. argList := self xslElements. 1 to: argList size do: [:i | (argList at: i) process: aNodeContext intoArgs: arguments]. list reset. [list atEnd] whileFalse: [list variables: list variables clone. rule := list db ruleMatching: list next mode: self mode. rule == nil ifFalse: [rule process: list into: aProxy arguments: arguments]] ] ] ] Namespace current: XSL [ XSLCommand subclass: RuleSet [ RuleSet class >> tag [ ^'stylesheet' ] defineParameter: aVariable [ ^self ] defineVariable: aVariable [ ^self ] purgeUnimportant [ elements := self children select: [:i | i isElement and: [i isStylesheetEntry]]. elements do: [:i | i purgeUnimportant] ] addToRuleDB: aDB [ "This is only understood by a small subset of commands." self children do: [:elm | elm addToRuleDB: aDB] ] topLevelAddToRuleDB: aDB [ "This is only understood by a small subset of commands." self children do: [:elm | elm addToRuleDB: aDB] ] ] ] Namespace current: XSL [ Object subclass: NodeIterator [ | stack current | reverseDo: aBlock until: testBlock [ | t | [testBlock value: current] whileFalse: [aBlock value: current. stack isEmpty ifTrue: [^self]. [stack last value = 1 ifTrue: [current := stack removeLast key] ifFalse: [t := stack last. t value: t value - 1. current := t key children at: t value. [current isElement not or: [current children size = 0]] whileFalse: [stack add: current -> current children size. current := current children last]]. current isContent and: [current isText not]] whileFalse] ] node: aNode [ | nd | nd := current := aNode. stack := OrderedCollection new. [nd parent == nil] whileFalse: [stack addFirst: nd parent -> (nd parent children indexOf: nd). nd := nd parent] ] ] ] Namespace current: XSL [ XSLCommand subclass: AttributeCommand [ | name | AttributeCommand class >> tag [ ^'attribute' ] generatesAttributes [ ^true ] testPatternInitialized [ userData ifTrue: [^self]. userData := true. name := self readTag: 'name' ] name [ self testPatternInitialized. ^name ] generateFrom: aNode into: aProxy [ | oc computedValue nm | oc := aProxy childProxy. self xslElements do: [:elm | elm process: aNode into: oc]. oc attributes isEmpty ifFalse: [self error: 'Attributes cannot have attributes']. computedValue := (String new: 32) writeStream. oc children do: [:elm | elm isText ifFalse: [self error: 'Attribute values can only contain text data']. computedValue nextPutAll: elm characterData]. nm := self processAttributeValue: self name for: aNode. nm := self resolveComputedTag: nm. ^Attribute new name: nm value: computedValue contents ] process: aNode into: aProxy [ | oc computedValue nm | aProxy children size = 0 ifFalse: [self error: 'Attributes must all be added before content']. oc := aProxy childProxy. self xslElements do: [:elm | elm process: aNode into: oc]. oc attributes isEmpty ifFalse: [self error: 'Attributes cannot have attributes']. computedValue := (String new: 32) writeStream. oc children do: [:elm | elm isText ifFalse: [self error: 'Attribute values can only contain text data']. computedValue nextPutAll: elm characterData]. nm := self processAttributeValue: self name for: aNode. nm := self resolveComputedTag: nm. aProxy addAttribute: (Attribute new name: nm value: computedValue contents) ] ] ] Namespace current: XSL [ XSLCommand subclass: TextCommand [ TextCommand class >> tag [ ^'text' ] shouldStrip [ ^false ] process: aNodeContext into: aProxy [ (self readAttribute: 'disable-output-escaping' default: ['no']) = 'yes' ifTrue: [aProxy addNode: (DenormalizedText new text: self characterData)] ifFalse: [aProxy addNode: (Text new text: self characterData)] ] ] ] Namespace current: XSL [ XML.SAXWriter subclass: SAXTextWriter [ characters: aString from: start to: stop [ output next: stop + 1 - start putAll: aString startingAt: start ] endElement: namespaceURI localName: localName qName: name [ ^self ] startElement: namespaceURI localName: localName qName: name attributes: attributes [ ^self ] ] ] Namespace current: XSL [ GeneralCountingProxy subclass: CountingProxy [ add: element [ nextLink add: element ] addAttribute: attribute [ nextLink addAttribute: attribute ] ] ] Namespace current: XSL [ XSLCommand subclass: CopyOfCommand [ | expression | CopyOfCommand class >> tag [ ^'copy-of' ] copyNode: n to: aContainer [ | new | n isDocument ifTrue: [^self copyNode: n root to: aContainer]. n isAttribute ifTrue: [^aContainer addAttribute: n copy]. n isElement ifFalse: [^aContainer addNode: n copy]. new := n class tag: n tag attributes: (n attributes collect: [:a | a copy]) elements: nil. n children do: [:c | self copyNode: c to: new]. aContainer addNode: new ] copyNodes: sortedNodes into: aProxy [ sortedNodes do: [:n | self copyNode: n to: aProxy] ] process: aNodeContext into: aProxy [ | elm | elm := self expression xpathValueIn: aNodeContext. elm xpathIsNodeSet ifTrue: [self copyNodes: elm sortedNodes into: aProxy] ifFalse: [(elm isKindOf: ElementProxy) ifTrue: [self copyNodes: elm children into: aProxy] ifFalse: [aProxy add: (Text new text: elm xpathAsString value)]] ] expression [ self testPatternInitialized. ^expression ] testPatternInitialized [ userData ifTrue: [^self]. userData := true. expression := self readSelectPattern: 'select' ] ] ] Namespace current: XSL [ XSLCommand subclass: ChooseOtherwiseCommand [ ChooseOtherwiseCommand class >> tag [ ^'otherwise' ] process: aNodeContext into: aProxy [ self shouldNotImplement ] ] ] Namespace current: XSL [ XSL at: #XSL_URI put: 'http://www.w3.org/1999/XSL/Transform'. XSL XSLCommand initialize ] smalltalk-3.2.5/packages/xml/xsl/stamp-classes0000644000175000017500000000000012123404352016276 00000000000000smalltalk-3.2.5/packages/xml/xsl/package.xml0000644000175000017500000000030012123404352015714 00000000000000 XSL XSL XPath XML-XMLNodeBuilder XML-XMLParser XSL.st smalltalk-3.2.5/packages/xml/parser/0000755000175000017500000000000012130456023014354 500000000000000smalltalk-3.2.5/packages/xml/parser/Makefile.frag0000644000175000017500000000034312123404352016652 00000000000000XML-XMLParser_FILES = \ packages/xml/parser/XML.st packages/xml/parser/XMLTests.st $(XML-XMLParser_FILES): $(srcdir)/packages/xml/parser/stamp-classes: $(XML-XMLParser_FILES) touch $(srcdir)/packages/xml/parser/stamp-classes smalltalk-3.2.5/packages/xml/parser/XML.st0000644000175000017500000033345012123404352015314 00000000000000"====================================================================== | | VisualWorks XML Framework - DTD model and validating XML parser | | ======================================================================" "====================================================================== | | Copyright (c) 2000, 2002 Cincom, Inc. | Copyright (c) 2009 Free Software Foundation, Inc. | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" Object subclass: Pattern [ | followSet | A list of the Patterns which may follow this one in an element''s content.'> Pattern class >> new [ ^super new initialize ] followSet: aCollection [ followSet := aCollection ] initialize [ followSet := OrderedCollection new: 2 ] addFollow: aNode [ followSet add: aNode ] addFollows: aList [ followSet addAll: aList ] alternateHeads [ ^self subclassResponsibility ] followSet [ ^followSet ] normalize [ | list done t r result | list := OrderedCollection with: (result := InitialPattern new addFollow: self) with: self with: TerminalPattern new. self addFollow: list last. done := OrderedCollection new. [list isEmpty] whileFalse: [t := list removeFirst. r := t pushDownFollowSet. r == nil ifTrue: [done add: t] ifFalse: [list addAll: r]]. list := done. done := OrderedCollection new. [list isEmpty] whileFalse: [t := list removeFirst. t normalizeFollowSet ifTrue: [done add: t] ifFalse: [list add: t]]. done do: [:p | p isSimple ifFalse: [self error: 'Incomplete translation']. p followSet do: [:p1 | p1 isSimple ifFalse: [self error: 'Incomplete translation']]]. ^result ] normalizeFollowSet [ | changed oldFollow newFollow | oldFollow := IdentitySet withAll: followSet. newFollow := IdentitySet new. oldFollow do: [:pat | newFollow addAll: pat alternateHeads]. changed := newFollow size ~= oldFollow size or: [(newFollow - oldFollow) size > 0]. followSet := newFollow asOrderedCollection. ^changed not ] normalizeFor: aParser [ | list done t r result | list := OrderedCollection with: (result := InitialPattern new addFollow: self) with: self with: TerminalPattern new. self addFollow: list last. done := OrderedCollection new. [list isEmpty] whileFalse: [t := list removeFirst. r := t pushDownFollowSet. done add: t. r == nil ifFalse: [list addAll: r]]. done do: [:nd | | replacements | replacements := nd alternateHeads. (replacements size = 1 and: [replacements first == nd]) ifFalse: [done do: [:nd2 | nd2 replaceFollowSet: nd with: replacements]]]. done := IdentitySet new. list := OrderedCollection with: result. [list isEmpty] whileFalse: [t := list removeLast. t isSimple ifFalse: [aParser malformed: 'Incomplete translation']. (self duplicatesNeedTested and: [t hasDuplicatesInFollowSet]) ifTrue: [aParser warn: 'Nondeterministic content model %1' % {self}]. done add: t. t followSet do: [:t1 | (done includes: t1) ifFalse: [list add: t1]]]. ^result ] pushDownFollowSet [ ^self subclassResponsibility ] replaceFollowSet: node with: nodes [ (followSet includes: node) ifTrue: [followSet := (IdentitySet withAll: followSet) remove: node; addAll: nodes; asArray] ] duplicatesNeedTested [ ^true ] isSimple [ ^self subclassResponsibility ] postCopy [ super postCopy. followSet := OrderedCollection new: 2 ] ] Pattern subclass: ConcretePattern [ followSetDescription [ | s | s := (String new: 32) writeStream. s nextPut: $(. followSet do: [:n | s nextPutAll: n printString] separatedBy: [s space]. s nextPut: $). ^s contents ] canTerminate [ ^followSet contains: [:p | p isTerminator] ] couldBeText [ ^false ] hasDuplicatesInFollowSet [ 1 to: followSet size do: [:i | | p1 p2 ns tp | p1 := followSet at: i. p1 class == NamePattern ifTrue: [ns := p1 name namespace. tp := p1 name type. i + 1 to: followSet size do: [:j | p2 := followSet at: j. (p2 class == NamePattern and: [p2 name type = tp and: [p2 name namespace = ns]]) ifTrue: [^true]]]]. ^false ] isSimple [ ^true ] isTerminator [ ^false ] matchesTag: aNodeTag [ self subclassResponsibility ] alternateHeads [ ^Array with: self ] pushDownFollowSet [ ^nil ] validateTag: elementTag [ | types | types := IdentitySet new. self followSet do: [:i | (i matchesTag: elementTag) ifTrue: [types add: i]]. ^types isEmpty ifTrue: [nil] ifFalse: [types] ] validateText: characters from: start to: stop testBlanks: testBlanks [ self followSet do: [:i | i couldBeText ifTrue: [^i]]. testBlanks ifTrue: [start to: stop do: [:i | (characters at: i) asInteger > 32 ifTrue: [^nil]]. ^self]. ^nil ] printOn: aStream [ aStream nextPutAll: self description ] ] ConcretePattern subclass: TerminalPattern [ description [ ^'' ] isTerminator [ ^true ] matchesTag: aNodeTag [ ^false ] ] ConcretePattern subclass: InitialPattern [ | isExternal | description [ ^(followSet asArray collect: [:i | i description]) printString ] isExternal [ ^isExternal ] isExternal: flag [ isExternal := flag ] ] ConcretePattern subclass: EmptyPattern [ alternateHeads [ ^followSet ] matchesTag: aNodeTag [ ^false ] description [ ^'EMPTY' ] ] ConcretePattern subclass: NamePattern [ | name | The tag of the element which is permitted by this pattern to appear in the content of some other element.'> NamePattern class >> named: aName [ ^self new named: aName ] named: aName [ name := aName ] description [ ^'<%1>' % {name} ] name [ ^name ] matchesTag: aNodeTag [ ^name isLike: aNodeTag ] ] ConcretePattern subclass: PCDATAPattern [ description [ ^'#PCDATA' ] couldBeText [ ^true ] matchesTag: aNodeTag [ ^false ] ] Pattern subclass: ComplexPattern [ isSimple [ ^false ] ] ComplexPattern subclass: MixedPattern [ | items | A list of NamedPatterns (as well as one PCDATAPattern) which can appear as content in the context controlled by the MixedPattern.'> MixedPattern class >> on: aList [ ^self new on: (aList size = 0 ifTrue: [#()] ifFalse: [aList]) ] on: aList [ items := (Array with: PCDATAPattern new) , aList ] alternateHeads [ ^items , followSet ] normalizeFor: aParser [ "Optimized because lots of the testing needed in the superclass is not needed here." | result | followSet := OrderedCollection withAll: items. followSet add: TerminalPattern new. result := InitialPattern new. result followSet: followSet. items do: [:i | i followSet: followSet]. ^result ] pushDownFollowSet [ items do: [:i | i addFollow: self; addFollows: followSet]. ^items ] duplicatesNeedTested [ ^false ] postCopy [ super postCopy. items := items collect: [:i | i copy] ] ] ComplexPattern subclass: ChoicePattern [ | items | Collection of content particles'> ChoicePattern class >> on: aList [ ^self new on: aList ] on: aList [ items := aList ] alternateHeads [ ^items ] pushDownFollowSet [ items do: [:i | i addFollows: followSet]. ^items ] description [ | str | str := String new writeStream. str nextPutAll: '('. items do: [:ch | str nextPutAll: ch description] separatedBy: [str nextPutAll: ' | ']. str nextPutAll: ')'. ^str contents ] printOn: aStream [ aStream nextPutAll: self description ] postCopy [ super postCopy. items := items collect: [:i | i copy] ] ] ComplexPattern subclass: ModifiedPattern [ | node modification | The base pattern which the ModifiedPattern influences. modification Optional character denoting content element occurances'> ModifiedPattern class >> on: aNode type: t [ ^self new on: aNode type: t ] on: aNode type: t [ node := aNode. modification := t ] alternateHeads [ ^(modification = $* or: [modification = $?]) ifTrue: [(followSet copyWith: node) replaceAll: self with: node] ifFalse: [Array with: node] ] pushDownFollowSet [ (modification = $+ or: [modification = $*]) ifTrue: [node addFollow: self]. node addFollows: followSet. ^Array with: node ] description [ ^node description copyWith: modification ] printOn: aStream [ aStream nextPutAll: self description ] postCopy [ super postCopy. node := node copy ] ] Object subclass: AttributeDef [ | name default type flags | name of attribute default default value, if any type type used for validation flags encoding for fixed, implied and required type attributes'> default [ ^default ] default: n [ flags := 0. default := nil. n = #required ifTrue: [flags := 1] ifFalse: [n = #implied ifTrue: [flags := 2] ifFalse: [n class == Association ifFalse: [self error: 'Invalid default']. n key ifTrue: [flags := 4]. default := n value]] ] hasDefault [ ^(self isImplied or: [self isRequired]) not ] isFixed [ ^(flags bitAnd: 4) = 4 ] isImplied [ ^(flags bitAnd: 2) = 2 ] isRequired [ ^(flags bitAnd: 1) = 1 ] name [ ^name ] name: n [ name := n ] tag [ ^name ] type [ ^type ] type: n [ type := n ] completeValidationAgainst: aParser [ ^self type completeValidationAgainst: aParser from: self ] selfValidateFor: aParser [ type validateDefinition: self for: aParser ] validateValueOf: anAttribute for: aParser [ type validateValueOf: anAttribute for: aParser. (self isFixed not or: [anAttribute value = self default]) ifFalse: [aParser invalid: 'The attribute "%1" was declared FIXED, but the value used in the document ("%2") did not match the default ("%3")' % {anAttribute tag asString. anAttribute value. self default}] ] value [ ^self default ] value: str [ default := str ] ] ComplexPattern subclass: SequencePattern [ | items | Collection of content particles'> SequencePattern class >> on: aList [ ^self new on: aList ] on: aList [ items := aList ] alternateHeads [ ^Array with: items first ] pushDownFollowSet [ 1 to: items size - 1 do: [:i | (items at: i) addFollow: (items at: i + 1)]. items last addFollows: followSet. ^items ] description [ | str | str := String new writeStream. str nextPutAll: '('. items do: [:ch | str nextPutAll: ch description] separatedBy: [str nextPutAll: ' , ']. str nextPutAll: ')'. ^str contents ] printOn: aStream [ aStream nextPutAll: self description ] postCopy [ super postCopy. items := items collect: [:i | i copy] ] ] Object subclass: AttributeType [ | isExternal | completeValidationAgainst: aParser from: anAttributeDef [ ^self ] simpleValidateValueOf: anAttribute for: aParser [ | v | v := anAttribute value copy. v replaceAll: Character cr with: Character space. v replaceAll: Character nl with: Character space. v replaceAll: Character tab with: Character space. anAttribute value: v ] stringAsTokens: aString [ | list str buffer hasToken | list := OrderedCollection new. str := aString readStream. buffer := (String new: 8) writeStream. hasToken := str atEnd not. [[str atEnd or: [str peek isSeparator]] whileFalse: [buffer nextPut: str next]. hasToken ifTrue: [list add: buffer contents. buffer reset]. str atEnd] whileFalse: [hasToken := true. str skipSeparators]. ^list ] validateDefinition: anAttributeDefinition for: aParser [ anAttributeDefinition hasDefault ifTrue: [self validateValueOf: anAttributeDefinition for: aParser] ] validateValueOf: anAttribute for: aParser [ "We're going to do this the hard way for now. Most of this has been done already, except for compressing multiple space characters that were character references." | v v1 | v := anAttribute value. [v1 := v copyReplaceAll: ' ' with: ' '. v1 = v] whileFalse: [v := v1]. (v size > 1 and: [v first = Character space]) ifTrue: [v := v copyFrom: 2 to: v size]. (v size > 1 and: [v last = Character space]) ifTrue: [v := v copyFrom: 1 to: v size - 1]. anAttribute value: v ] isExternal [ ^isExternal ] isID [ ^false ] isExternal: aBoolean [ isExternal := aBoolean ] ] AttributeType subclass: NOTATION_AT [ | typeNames | A list of the legal notation names that may be used for this attribute type.'> NOTATION_AT class >> typeNames: list [ ^self new typeNames: list ] typeNames [ ^typeNames ] typeNames: aList [ typeNames := aList ] completeValidationAgainst: aParser from: anAttributeDef [ typeNames do: [:nm | aParser dtd notationAt: nm ifAbsent: [aParser invalid: 'Undeclared Notation "%1" used by attribute type "%2"' % {nm. anAttributeDef tag asString}]] ] validateValueOf: anAttribute for: aParser [ | v | super validateValueOf: anAttribute for: aParser. v := anAttribute value. (typeNames includes: v) ifFalse: [aParser invalid: 'A NOTATION attribute (%1="%2") should have had a value from %3.' % {anAttribute tag asString v. typeNames asArray}] ] ] AttributeType subclass: NMTOKEN_AT [ validateValueOf: anAttribute for: aParser [ | v | super validateValueOf: anAttribute for: aParser. v := anAttribute value. (v includes: Character space) ifTrue: [aParser invalid: 'white space must not occur in NMTOKEN attributes']. (aParser isValidNmToken: v) ifFalse: [aParser invalid: 'An NMTOKEN attribute (%1="%2") does not match the required syntax of an NmToken.' % {anAttribute tag asString. v}] ] ] AttributeType subclass: IDREF_AT [ validateValueOf: anAttribute for: aParser [ | v | super validateValueOf: anAttribute for: aParser. v := anAttribute value. (v includes: Character space) ifTrue: [aParser invalid: 'white space must not occur in IDREF attributes']. (aParser isValidName: v) ifFalse: [aParser invalid: 'An IDREF attribute (%1="%2") does not match the required syntax of a Name.' % {anAttribute tag asString. v}]. aParser rememberIDREF: v ] ] AttributeType subclass: NMTOKENS_AT [ validateValueOf: anAttribute for: aParser [ | v all | super validateValueOf: anAttribute for: aParser. v := anAttribute value. (all := self stringAsTokens: v) do: [:nm | (aParser isValidNmToken: nm) ifFalse: [aParser invalid: 'An NMTOKENS attribute (%1="%2") does not match the required syntax of a list of NmTokens.' % {anAttribute tag asString. v}]]. all size = 0 ifTrue: [aParser invalid: 'Attribute has empty list of NMTOKENS'] ] ] AttributeType subclass: ENTITY_AT [ completeValidationAgainst: aParser from: anAttributeDef [ ^anAttributeDef hasDefault ifTrue: [self validateValueOf: anAttributeDef for: aParser] ] validateDefinition: anAttributeDefinition for: aParser [ ^self ] validateValueOf: anAttribute for: aParser [ | v ent | super validateValueOf: anAttribute for: aParser. v := anAttribute value. (v includes: Character space) ifTrue: [aParser invalid: 'white space must not occur in ENTITY attributes']. (aParser isValidName: v) ifFalse: [aParser invalid: 'An ENTITY attribute (%1="%2") does not match the required syntax of a Name.' % {anAttribute tag asString. v}]. ent := aParser dtd generalEntityAt: v. ent == nil ifTrue: [aParser invalid: 'Undeclared unparsed entity "%1" used by attribute type "%2"' % {v. anAttribute tag asString}] ifFalse: [ent isParsed ifTrue: [aParser invalid: 'The entity "%1" used by attribute type "%2" is a parsed entity and should be unparsed' % {v. anAttribute tag asString}] ifFalse: []] ] ] AttributeType subclass: CDATA_AT [ validateValueOf: anAttribute for: aParser [ ^self ] ] AttributeType subclass: ID_AT [ validateDefinition: anAttributeDefinition for: aParser [ anAttributeDefinition hasDefault ifTrue: [aParser invalid: 'ID attributes must be either #REQUIRED or #IMPLIED'] ] validateValueOf: anAttribute for: aParser [ | v | super validateValueOf: anAttribute for: aParser. v := anAttribute value. (v includes: Character space) ifTrue: [aParser invalid: 'white space must not occur in ID attributes']. (aParser isValidName: v) ifFalse: [aParser invalid: 'An ID attribute (%1="%2") does not match the required syntax of a Name.' % {anAttribute tag asString. v}]. aParser registerID: anAttribute ] isID [ ^true ] ] AttributeType subclass: Enumeration_AT [ | values | A list of the possible values which the attribute may have.'> Enumeration_AT class >> withAll: list [ ^self new values: list ] values [ ^values ] values: aList [ values := aList ] validateValueOf: anAttribute for: aParser [ | v | super validateValueOf: anAttribute for: aParser. v := anAttribute value. (values includes: v) ifFalse: [aParser invalid: 'An attribute (%1="%2") should have had a value from %3.' % {anAttribute tag asString. v values asArray}] ] ] AttributeType subclass: IDREFS_AT [ validateValueOf: anAttribute for: aParser [ | v all | super validateValueOf: anAttribute for: aParser. v := anAttribute value. (all := self stringAsTokens: v) do: [:nm | (aParser isValidName: nm) ifFalse: [aParser invalid: 'An IDREFS attribute (%1="%2") does not match the required syntax of a list of Names.' % {anAttribute tag asString. v}]. aParser rememberIDREF: nm]. all size = 0 ifTrue: [aParser invalid: 'Attribute has empty list of IDREFS'] ] ] AttributeType subclass: ENTITIES_AT [ completeValidationAgainst: aParser from: anAttributeDef [ ^anAttributeDef hasDefault ifTrue: [self validateValueOf: anAttributeDef for: aParser] ] validateDefinition: anAttributeDefinition for: aParser [ ^self ] validateValueOf: anAttribute for: aParser [ | v ent all | super validateValueOf: anAttribute for: aParser. v := anAttribute value. (all := self stringAsTokens: v) do: [:nm | (aParser isValidName: nm) ifFalse: [aParser invalid: 'An ENTITIES attribute (%1="%2") does not match the required syntax of a list of Names.' % {anAttribute tag asString. v}]. ent := aParser dtd generalEntityAt: nm. ent == nil ifTrue: [aParser invalid: 'Undeclared unparsed entity "%1" used by attribute type "%2"' % {nm. anAttribute tag asString}] ifFalse: [ent isParsed ifTrue: [aParser invalid: 'The entity "%1" used by attribute type "%2" is a parsed entity and should be unparsed' % {nm. anAttribute tag asString}] ifFalse: []]]. all size = 0 ifTrue: [aParser invalid: 'Attribute has empty list of ENTITIES'] ] ] ConcretePattern subclass: AnyPattern [ description [ ^'ANY' ] alternateHeads [ ^followSet copyWith: self ] pushDownFollowSet [ self addFollow: self. ^nil ] couldBeText [ ^true ] matchesTag: aNodeTag [ ^true ] ] Link subclass: StreamWrapper [ | stream isInternal resource usedAsExternal entity cr lf parser line column | declaration at the beginning of the stream to make sure that the EncodedStream is using the right encoding, and if not, it changes the encoding of the stream. Instance Variables: stream stream being wrapped isInternal true if the stream is internal and hencer doesn''t need careful line-end treatment resource source of the data being parsed usedAsExternal flag used to override protocol and say how stream is being used? entity if wrapping on behalf of an Entity this is it? cr cache of Character cr lf cache of Character lf parser the parser reading this stream line line number of the current parse location column column number on the current line'> StreamWrapper class >> emptyWithExtraSpace: space from: aParser [ | txt | txt := space ifTrue: [' '] ifFalse: ['']. ^self resource: (InputSource uri: nil encoding: nil stream: txt readStream) entity: nil from: aParser ] StreamWrapper class >> resource: anInputSource entity: entity from: aParser [ ^self new resource: anInputSource entity: entity from: aParser ] isInternal: aBoolean [ isInternal := aBoolean ] resource: anInputSource entity: ent from: aParser [ resource := anInputSource. stream := resource stream. isInternal := resource uri == nil. entity := ent. cr := Character cr. lf := Character lf. parser := aParser. line := 1. column := 0 ] usedAsExternal [ ^usedAsExternal ] usedAsExternal: aBoolean [ usedAsExternal := aBoolean ] characterSize: aCharacter [ ^1 "(self stream respondsTo: #encoder) ifTrue: [self stream encoder characterSize: aCharacter] ifFalse: [1]" ] checkEncoding [ "| encoding | encoding := [stream encoding] on: Error do: [:ex | ex returnWith: #null]. encoding = #'UTF-8' ifTrue: [| c1 c2 pos | pos := stream position. stream setBinary: true. c1 := stream next. c2 := stream next. stream setBinary: false. (c2 notNil and: [c1 * c2 = 16rFD02]) ifTrue: [stream encoder: (UTF16StreamEncoder new forByte1: c1 byte2: c2)] ifFalse: [stream position: pos]]" ] close [ stream close ] column [ ^column ] column: n [ column := n ] contents [ | s | s := (String new: 100) writeStream. [self atEnd] whileFalse: [s nextPut: self next]. ^s contents ] entity [ ^entity ] line [ ^line ] line: n [ line := n ] stream [ ^stream ] uri [ ^resource uri ] next [ | ch | ch := stream next. isInternal ifFalse: [lf == nil ifTrue: [self halt]. column := column + 1. ch == cr ifTrue: [stream peekFor: lf. ch := parser eol. line := line + 1. column := 0] ifFalse: [ch == lf ifTrue: [ch := parser eol. line := line + 1. column := 0]]]. "Originally we tested ch to make sure it was less than 16r110000, but now CharacterClasses' implementation of #at: answers 0 for large values of ch. If primitive failure code can not be trusted to do this, then the bounds check would have to be added back." (ch isNil or: [(CharacterClasses at: ch asInteger + 1) > 0]) ifFalse: [parser errorHandler fatalError: (BadCharacterSignal new messageText: 'A character with Unicode value %1 is not legal' % {ch asInteger})]. ^ch ] skip: n [ stream skip: n. column := column - 1 ] atEnd [ ^stream atEnd ] isInternal [ ^isInternal ] encodingDecl [ | enc | ^stream peek = $e ifTrue: [| encoding | self mustFind: 'encoding'. self skipSpace. self mustFind: '='. self skipSpace. encoding := self quotedString. parser validateEncoding: encoding. ((stream respondsTo: #encoding) and: [stream encoding asLowercase ~= encoding asLowercase]) ifTrue: []. true] ifFalse: [false] ] mustFind: str [ (self skipIf: str) ifFalse: [parser expected: str] ] quotedString [ (stream peekFor: $") ifTrue: [^(stream upTo: $") asString]. (stream peekFor: $') ifTrue: [^(stream upTo: $') asString]. parser malformed: 'Quoted string expected but not found' ] sdDecl [ ^stream peek = $s ifTrue: [| word | self mustFind: 'standalone'. self skipSpace. self mustFind: '='. self skipSpace. word := self quotedString. (#('yes' 'no') includes: word) ifFalse: [parser malformed: '"yes" or "no" expected, but not found']. parser declaredStandalone: word = 'yes'. true] ifFalse: [false] ] skipIf: str [ | p | p := stream position. 1 to: str size do: [:i | (stream peekFor: (str at: i)) ifFalse: [stream position: p. ^false]]. column := column + str size. ^true ] skipSpace [ | space | space := false. [#(9 10 13 32) includes: self next asInteger] whileTrue: [space := true]. self skip: -1. ^space ] textDecl [ self checkEncoding. ^(self skipIf: ''. true] ifFalse: [false] ] versionInfo [ | version | ^stream peek = $v ifTrue: [self mustFind: 'version'. self skipSpace. self mustFind: '='. self skipSpace. version := self quotedString. version = '1.0' ifFalse: [parser malformed: 'XML version 1.0 expected']. version] ifFalse: [nil] ] xmlDecl [ self checkEncoding. ^(self skipIf: ''. true] ifFalse: [false] ] ] LargeByteArray subclass: CharacterTable [ at: index [ "Answer the value of an indexable field in the receiver. Fail if the argument index is not an Integer or is <= 1." ^(index > self size and: [index isInteger]) ifTrue: [(index between: self size + 1 and: 1114112) ifTrue: [1] ifFalse: [0]] ifFalse: [super at: index] ] ] SAXParser subclass: XMLParser [ | sourceStack dtd hereChar lastSource currentSource unresolvedIDREFs definedIDs latestID elementStack eol buffer nameBuffer | stack of input streams that handles inclusion. dtd the document type definition for the current document hereChar the current character being parsed lastSource record of previous source used to check correct nesting currentSource current input stream (the top of sourceStack) unresolvedIDREFs collection of IDREfs that have yet to be resolved. Used for validation definedIDs IDs that have already been seen. latestID the ID of the last start tag we found. sax the output elementStack a list of the elements that enclose the current parse location (bookkeeping info) validating if true then the parse validates the XML flags sundry boolean values that are not accessed often enough to need separate instance variables. eol the end-of-line character in the source stream buffer temporary storage for data read from the input, to save reallocating the stream nameBuffer alternate buffer when "buffer" may be in use'> XMLParser class >> characterTable [ | ch sets pc nameChars nameStartChars | ch := CharacterTable new: 65536. nameChars := self nameChars. nameStartChars := self nameStartChars. sets := Array with: (32 to: 55295) with: (57344 to: 65533). pc := XMLParser. sets do: [:s | | startS endS | startS := s first. endS := s last. startS to: endS do: [:i | ch at: i + 1 put: ((nameStartChars includes: i) ifTrue: [7] ifFalse: [(nameChars includes: i) ifTrue: [3] ifFalse: [1]])]]. ch at: 9 + 1 put: 1. ch at: 10 + 1 put: 1. ch at: 13 + 1 put: 1. ch at: $_ asInteger + 1 put: 7. ch at: $- asInteger + 1 put: 3. ch at: $. asInteger + 1 put: 3. ^ch compress; yourself ] XMLParser class >> nameChars [ ^(Set new: 1024) addAll: (768 to: 837); addAll: (864 to: 865); addAll: (1155 to: 1158); addAll: (1425 to: 1441); addAll: (1443 to: 1465); addAll: (1467 to: 1469); add: 1471; addAll: (1473 to: 1474); add: 1476; addAll: (1611 to: 1618); add: 1648; addAll: (1750 to: 1756); addAll: (1757 to: 1759); addAll: (1760 to: 1764); addAll: (1767 to: 1768); addAll: (1770 to: 1773); addAll: (2305 to: 2307); add: 2364; addAll: (2366 to: 2380); add: 2381; addAll: (2385 to: 2388); addAll: (2402 to: 2403); addAll: (2433 to: 2435); add: 2492; add: 2494; add: 2495; addAll: (2496 to: 2500); addAll: (2503 to: 2504); addAll: (2507 to: 2509); add: 2519; addAll: (2530 to: 2531); add: 2562; add: 2620; add: 2622; add: 2623; addAll: (2624 to: 2626); addAll: (2631 to: 2632); addAll: (2635 to: 2637); addAll: (2672 to: 2673); addAll: (2689 to: 2691); add: 2748; addAll: (2750 to: 2757); addAll: (2759 to: 2761); addAll: (2763 to: 2765); addAll: (2817 to: 2819); add: 2876; addAll: (2878 to: 2883); addAll: (2887 to: 2888); addAll: (2891 to: 2893); addAll: (2902 to: 2903); addAll: (2946 to: 2947); addAll: (3006 to: 3010); addAll: (3014 to: 3016); addAll: (3018 to: 3021); add: 3031; addAll: (3073 to: 3075); addAll: (3134 to: 3140); addAll: (3142 to: 3144); addAll: (3146 to: 3149); addAll: (3157 to: 3158); addAll: (3202 to: 3203); addAll: (3262 to: 3268); addAll: (3270 to: 3272); addAll: (3274 to: 3277); addAll: (3285 to: 3286); addAll: (3330 to: 3331); addAll: (3390 to: 3395); addAll: (3398 to: 3400); addAll: (3402 to: 3405); add: 3415; add: 3633; addAll: (3636 to: 3642); addAll: (3655 to: 3662); add: 3761; addAll: (3764 to: 3769); addAll: (3771 to: 3772); addAll: (3784 to: 3789); addAll: (3864 to: 3865); add: 3893; add: 3895; add: 3897; add: 3902; add: 3903; addAll: (3953 to: 3972); addAll: (3974 to: 3979); addAll: (3984 to: 3989); add: 3991; addAll: (3993 to: 4013); addAll: (4017 to: 4023); add: 4025; addAll: (8400 to: 8412); add: 8417; addAll: (12330 to: 12335); add: 12441; add: 12442; addAll: (48 to: 57); addAll: (1632 to: 1641); addAll: (1776 to: 1785); addAll: (2406 to: 2415); addAll: (2534 to: 2543); addAll: (2662 to: 2671); addAll: (2790 to: 2799); addAll: (2918 to: 2927); addAll: (3047 to: 3055); addAll: (3174 to: 3183); addAll: (3302 to: 3311); addAll: (3430 to: 3439); addAll: (3664 to: 3673); addAll: (3792 to: 3801); addAll: (3872 to: 3881); add: 183; add: 720; add: 721; add: 903; add: 1600; add: 3654; add: 3782; add: 12293; addAll: (12337 to: 12341); addAll: (12445 to: 12446); addAll: (12540 to: 12542); yourself ] XMLParser class >> nameStartChars [ ^(Set new: 65536) addAll: (65 to: 90); addAll: (97 to: 122); addAll: (192 to: 214); addAll: (216 to: 246); addAll: (248 to: 255); addAll: (256 to: 305); addAll: (308 to: 318); addAll: (321 to: 328); addAll: (330 to: 382); addAll: (384 to: 451); addAll: (461 to: 496); addAll: (500 to: 501); addAll: (506 to: 535); addAll: (592 to: 680); addAll: (699 to: 705); add: 902; addAll: (904 to: 906); add: 908; addAll: (910 to: 929); addAll: (931 to: 974); addAll: (976 to: 982); add: 986; add: 988; add: 990; add: 992; addAll: (994 to: 1011); addAll: (1025 to: 1036); addAll: (1038 to: 1103); addAll: (1105 to: 1116); addAll: (1118 to: 1153); addAll: (1168 to: 1220); addAll: (1223 to: 1224); addAll: (1227 to: 1228); addAll: (1232 to: 1259); addAll: (1262 to: 1269); addAll: (1272 to: 1273); addAll: (1329 to: 1366); add: 1369; addAll: (1377 to: 1414); addAll: (1488 to: 1514); addAll: (1520 to: 1522); addAll: (1569 to: 1594); addAll: (1601 to: 1610); addAll: (1649 to: 1719); addAll: (1722 to: 1726); addAll: (1728 to: 1742); addAll: (1744 to: 1747); add: 1749; addAll: (1765 to: 1766); addAll: (2309 to: 2361); add: 2365; addAll: (2392 to: 2401); addAll: (2437 to: 2444); addAll: (2447 to: 2448); addAll: (2451 to: 2472); addAll: (2474 to: 2480); add: 2482; addAll: (2486 to: 2489); addAll: (2524 to: 2525); addAll: (2527 to: 2529); addAll: (2544 to: 2545); addAll: (2565 to: 2570); addAll: (2575 to: 2576); addAll: (2579 to: 2600); addAll: (2602 to: 2608); addAll: (2610 to: 2611); addAll: (2613 to: 2614); addAll: (2616 to: 2617); addAll: (2649 to: 2652); add: 2654; addAll: (2674 to: 2676); addAll: (2693 to: 2699); add: 2701; addAll: (2703 to: 2705); addAll: (2707 to: 2728); addAll: (2730 to: 2736); addAll: (2738 to: 2739); addAll: (2741 to: 2745); add: 2749; add: 2784; addAll: (2821 to: 2828); addAll: (2831 to: 2832); addAll: (2835 to: 2856); addAll: (2858 to: 2864); addAll: (2866 to: 2867); addAll: (2870 to: 2873); add: 2877; addAll: (2908 to: 2909); addAll: (2911 to: 2913); addAll: (2949 to: 2954); addAll: (2958 to: 2960); addAll: (2962 to: 2965); addAll: (2969 to: 2970); add: 2972; addAll: (2974 to: 2975); addAll: (2979 to: 2980); addAll: (2984 to: 2986); addAll: (2990 to: 2997); addAll: (2999 to: 3001); addAll: (3077 to: 3084); addAll: (3086 to: 3088); addAll: (3090 to: 3112); addAll: (3114 to: 3123); addAll: (3125 to: 3129); addAll: (3168 to: 3169); addAll: (3205 to: 3212); addAll: (3214 to: 3216); addAll: (3218 to: 3240); addAll: (3242 to: 3251); addAll: (3253 to: 3257); add: 3294; addAll: (3296 to: 3297); addAll: (3333 to: 3340); addAll: (3342 to: 3344); addAll: (3346 to: 3368); addAll: (3370 to: 3385); addAll: (3424 to: 3425); addAll: (3585 to: 3630); add: 3632; addAll: (3634 to: 3635); addAll: (3648 to: 3653); addAll: (3713 to: 3714); add: 3716; addAll: (3719 to: 3720); add: 3722; add: 3725; addAll: (3732 to: 3735); addAll: (3737 to: 3743); addAll: (3745 to: 3747); add: 3749; add: 3751; addAll: (3754 to: 3755); addAll: (3757 to: 3758); add: 3760; addAll: (3762 to: 3763); add: 3773; addAll: (3776 to: 3780); addAll: (3904 to: 3911); addAll: (3913 to: 3945); addAll: (4256 to: 4293); addAll: (4304 to: 4342); add: 4352; addAll: (4354 to: 4355); addAll: (4357 to: 4359); add: 4361; addAll: (4363 to: 4364); addAll: (4366 to: 4370); add: 4412; add: 4414; add: 4416; add: 4428; add: 4430; add: 4432; addAll: (4436 to: 4437); add: 4441; addAll: (4447 to: 4449); add: 4451; add: 4453; add: 4455; add: 4457; addAll: (4461 to: 4462); addAll: (4466 to: 4467); add: 4469; add: 4510; add: 4520; add: 4523; addAll: (4526 to: 4527); addAll: (4535 to: 4536); add: 4538; addAll: (4540 to: 4546); add: 4587; add: 4592; add: 4601; addAll: (7680 to: 7835); addAll: (7840 to: 7929); addAll: (7936 to: 7957); addAll: (7960 to: 7965); addAll: (7968 to: 8005); addAll: (8008 to: 8013); addAll: (8016 to: 8023); add: 8025; add: 8027; add: 8029; addAll: (8031 to: 8061); addAll: (8064 to: 8116); addAll: (8118 to: 8124); add: 8126; addAll: (8130 to: 8132); addAll: (8134 to: 8140); addAll: (8144 to: 8147); addAll: (8150 to: 8155); addAll: (8160 to: 8172); addAll: (8178 to: 8180); addAll: (8182 to: 8188); add: 8486; addAll: (8490 to: 8491); add: 8494; addAll: (8576 to: 8578); addAll: (12353 to: 12436); addAll: (12449 to: 12538); addAll: (12549 to: 12588); addAll: (44032 to: 55203); addAll: (19968 to: 40869); add: 12295; addAll: (12321 to: 12329); yourself ] XMLParser class >> readFileContents: fn [ | s p r | r := InputSource for: fn. p := self new. p lineEndLF. s := StreamWrapper resource: r entity: nil from: p. ^ [s checkEncoding. s contents] ensure: [s close] ] initialize [ super initialize. eol := Character nl. buffer := (String new: 32) writeStream. nameBuffer := (String new: 16) writeStream ] lineEndLF [ eol := Character nl ] lineEndCR [ eol := Character cr ] lineEndNormal [ eol := Character nl ] on: dataSource [ "The dataSource may be a URI, a Filename (or a String which will be treated as a Filename), or an InputSource." super on: dataSource. sourceStack := self wrapDataSource: dataSource. elementStack := OrderedCollection new. dtd := DocumentType new. unresolvedIDREFs := Set new. definedIDs := Set new. ] wrapDataSource: aDataSource [ | resource uri | resource := (aDataSource isKindOf: Stream) ifTrue: [uri := [NetClients.URL fromString: aDataSource name] on: Error do: [:ex | ex return: nil]. InputSource uri: uri encoding: nil stream: aDataSource] ifFalse: [InputSource for: aDataSource]. ^(StreamWrapper resource: resource entity: nil from: self) isInternal: false ] dtd [ ^dtd ] eol [ ^eol ] sourceWrapper [ ^sourceStack "last" ] hasExpanded: anEntity [ | s | s := sourceStack. [s == nil] whileFalse: [s entity == anEntity ifTrue: [self malformed: 'The %1 entity "%2" invokes itself recursively' % {anEntity entityType. anEntity name}]. s := s nextLink]. ^false ] shouldTestWFCEntityDeclared [ ^self hasDTD not or: [(self hasExternalDTD not and: [self usesParameterEntities not]) or: [self isDeclaredStandalone]] ] comment [ | str1 | str1 := currentSource. ^(self skipIf: '']. elementStack size to: 1 by: -1 do: [:i | nsURI := (elementStack at: i) findNamespace: ns. nsURI = nil ifFalse: [^nsURI]]. ^ns = '' ifTrue: [''] ifFalse: [self invalid: 'The namespace qualifier %1 has not been bound to a namespace URI' % {ns}] ] resolveNamespaces: attributes [ | newAttributes showDecls t1 t2 k | self processNamespaces ifFalse: [^attributes]. showDecls := self showNamespaceDeclarations. attributes == nil ifTrue: [newAttributes := #()] ifFalse: [newAttributes := OrderedCollection new: attributes size. attributes do: [:attr | | save | save := showDecls. attr tag qualifier = 'xmlns' ifTrue: [elementStack last defineNamespace: attr from: self] ifFalse: [(attr tag isLike: 'xmlns') ifTrue: [elementStack last defineDefaultNamespace: attr] ifFalse: [save := true]]. save ifTrue: [newAttributes add: attr]]. newAttributes do: [:attr | self correctAttributeTag: attr]. 1 to: newAttributes size do: [:i | t1 := (newAttributes at: i) tag. k := i + 1. [k <= newAttributes size] whileTrue: [t2 := (newAttributes at: k) tag. (t1 type = t2 type and: [t1 namespace = t2 namespace]) ifTrue: [self malformed: 'The attributes "%1" and "%2" have the same namespace and type' % {t1 asString. t2 asString}. k := newAttributes size]. k := k + 1]]]. elementStack last tag: (self correctTag: elementStack last tag). ^newAttributes isEmpty ifTrue: [nil] ifFalse: [newAttributes asArray] ] parseElement [ ^ [sax startDocumentFragment. self getNextChar. hereChar = $< ifFalse: [self expected: '<']. self getElement. sax endDocumentFragment. sax document == nil ifTrue: [nil] ifFalse: [sax document elements first]] ifCurtailed: [self closeAllFiles] ] parseElements [ ^ [sax startDocumentFragment. self prolog. [self atEnd] whileFalse: [self getElement. [self misc] whileTrue]. sax endDocumentFragment. sax document == nil ifTrue: [nil] ifFalse: [sax document elements]] ifCurtailed: [self closeAllFiles] ] ] ElementContext extend [ followSetDescription [ | types | self types isNil ifTrue: [ ^'()' ]. types := IdentitySet new. self types do: [:tp | types addAll: tp followSet]. ^types asArray printString ] canTerminate [ self types isNil ifTrue: [ ^true ]. self types do: [:i | i canTerminate ifTrue: [^true]]. ^false ] validateTag: nm [ | types | types := IdentitySet new. self types do: [:i | | t | t := i validateTag: nm. t == nil ifFalse: [types addAll: t]]. ^types isEmpty ifTrue: [nil] ifFalse: [types asArray] ] validateText: data from: start to: stop testBlanks: testBlanks [ | types | types := IdentitySet new. self types do: [:i | | t | t := i validateText: data from: start to: stop testBlanks: testBlanks. t == nil ifFalse: [types add: t]]. ^types isEmpty ifTrue: [nil] ifFalse: [types asArray] ] ] GeneralEntity extend [ completeValidationAgainst: aParser [ ndata isNil ifFalse: [aParser dtd notationAt: ndata ifAbsent: [aParser invalid: 'Unparsed entity "%1" uses an undeclared notation "%2"' % {name. ndata}]] ] ] DocumentType extend [ | attributeDefs elementDefs | attributeFor: key subKey: k2 from: anErrorReporter [ | val | attributeDefs isNil ifTrue: [anErrorReporter invalid: 'The attribute "%1 %2" has not been defined' % {key asString. k2 asString}]. (val := attributeDefs at: key asString ifAbsent: []) == nil ifTrue: [anErrorReporter invalid: 'The attribute "%1 %2" has not been defined' % {key asString. k2 asString}]. ^val at: k2 asString ifAbsent: [anErrorReporter invalid: 'The attribute "%1 %2" has not been defined' % {key asString. k2 asString}] ] attributeFor: key subKey: k2 put: value from: anErrorReporter [ | dict | dict := self attributesFor: key. (dict includesKey: k2 asString) ifTrue: [^anErrorReporter warn: 'The attribute "%1 %2" has been defined more than once' % {key asString. k2 asString}]. (value type isID and: [dict contains: [:attr | attr type isID]]) ifTrue: [^anErrorReporter invalid: 'The element %1 has two attributes typed as ID' % {key asString}]. dict at: k2 asString put: value ] attributeTypeFor: key subKey: k2 from: anErrorReporter [ | val | attributeDefs == nil ifTrue: [^CDATA_AT new]. (val := attributeDefs at: key asString ifAbsent: []) == nil ifTrue: [^CDATA_AT new]. ^(val at: k2 asString ifAbsent: [^CDATA_AT new]) type ] attributesFor: key [ attributeDefs isNil ifTrue: [attributeDefs := Dictionary new]. ^attributeDefs at: key asString ifAbsentPut: [Dictionary new] ] completeValidationAgainst: aParser [ generalEntities keysAndValuesDo: [:eName :entity | entity completeValidationAgainst: aParser]. attributeDefs keysAndValuesDo: [:eName :attribs | attribs keysAndValuesDo: [:aName :attrib | attrib completeValidationAgainst: aParser]] ] elementFor: key from: anErrorReporter [ | val | elementDefs isNil ifTrue: [anErrorReporter warn: 'The element "%1" has not been defined' % {key asString}]. (val := elementDefs at: key asString ifAbsent: []) == nil ifTrue: [anErrorReporter warn: 'The element "%1" has not been defined' % {key asString}]. ^val ] elementFor: key put: value from: anErrorReporter [ elementDefs isNil ifTrue: [elementDefs := Dictionary new]. (elementDefs includesKey: key asString) ifTrue: [| msg | msg := 'The element "%1" has been defined more than once' % {key asString}. anErrorReporter isValidating ifTrue: [anErrorReporter invalid: msg] ifFalse: [anErrorReporter warn: msg]]. elementDefs at: key asString put: value ] ] Eval [ XML at: #CharacterClasses put: XMLParser characterTable. SAXParser defaultParserClass isNil ifTrue: [SAXParser defaultParserClass: XMLParser]. ] smalltalk-3.2.5/packages/xml/parser/XMLTests.st0000644000175000017500000000040612123404352016327 00000000000000XMLPullParserTest subclass: XMLParserTest [ parserOn: source [ | pull | pull := XMLParser pullParserOn: source readStream. pull validate: false. ^pull ] ] smalltalk-3.2.5/packages/xml/parser/stamp-classes0000644000175000017500000000000012123404352016764 00000000000000smalltalk-3.2.5/packages/xml/parser/package.xml0000644000175000017500000000054212123404352016412 00000000000000 XML-XMLParser XML XML-Parser XML-ParserTests XML.XMLParserTest XMLTests.st XML-SAXParser XML-DOM Iconv XML.st smalltalk-3.2.5/packages/xml/dom/0000755000175000017500000000000012130456022013636 500000000000000smalltalk-3.2.5/packages/xml/dom/Makefile.frag0000644000175000017500000000025012123404352016132 00000000000000XML-DOM_FILES = \ packages/xml/dom/DOM.st $(XML-DOM_FILES): $(srcdir)/packages/xml/dom/stamp-classes: $(XML-DOM_FILES) touch $(srcdir)/packages/xml/dom/stamp-classes smalltalk-3.2.5/packages/xml/dom/DOM.st0000644000175000017500000013336612123404352014562 00000000000000"====================================================================== | | VisualWorks XML Framework - DOM interface | | ======================================================================" "====================================================================== | | Copyright (c) 2000, 2002 Cincom, Inc. | Copyright (c) 2009 Free Software Foundation, Inc. | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" Object subclass: Node [ | parent flags | All nodes except for Documents are contained by other nodes--this provides a pointer from the node to the node that contains it. flags Provides a compact representation for any boolean attributes that the node might have. Likely to be removed in the near future.'> Node class >> new [ ^super new initialize ] initialize [ flags := 0 ] children [ ^self shouldNotImplement ] discard [ self flags: (self flags bitOr: 1) ] document [ ^parent document ] expandedName [ ^'' ] flags [ ^flags ] flags: flagBits [ flags := flagBits ] parent [ ^parent ] parent: aNode [ parent := aNode ] selectNodes: aBlock [ ^#() ] tag [ ^nil ] canonicalPrintString [ | s | s := (String new: 1024) writeStream. self printCanonicalOn: s. ^s contents ] noIndentPrintString [ | s | s := (String new: 1024) writeStream. self printNoIndentOn: s. ^s contents ] printCanonical: text on: aStream [ "Print myself on the stream in the form described by James Clark's canonical XML." | d | d := Dictionary new. d at: Character cr put: ' '; at: Character lf put: ' '; at: Character tab put: ' '; at: $& put: '&'; at: $< put: '<'; at: $> put: '>'; at: $" put: '"'. text do: [:c | aStream nextPutAll: (d at: c ifAbsent: [String with: c])] ] printCanonicalOn: aStream [ "Print myself on the stream in the form described by James Clark's canonical XML." self saxDo: (SAXCanonicalWriter new output: aStream) ] printHTMLOn: aStream [ "Print myself on the stream in a form usual for HTML." self subclassResponsibility ] printNoIndentOn: aStream [ "Print myself on the stream with line breaks between adjacent elements, but no indentation." self printNoIndentOn: aStream endSpacing: [:node :list | aStream nl] spacing: [:node :list | aStream nl] ] printOn: aStream [ self printOn: aStream depth: 0 ] printQuoted: text on: aStream [ "Print myself on the stream in the form described by James Clark's canonical XML." | d | d := Dictionary new. d at: $& put: '&'; at: $< put: '<'; at: $> put: '>'. text do: [:c | aStream nextPutAll: (d at: c ifAbsent: [String with: c])] ] simpleDescription [ ^self printString ] hasAncestor: aNode [ | p | p := self parent. [p == nil] whileFalse: [p == aNode ifTrue: [^true]. p := p parent]. ^false ] hasSubNodes [ ^false ] isAttribute [ ^false ] isBlankText [ ^false ] isComment [ ^false ] isContent [ ^false ] isDiscarded [ ^(self flags bitAnd: 1) = 1 ] isDocument [ ^false ] isElement [ ^false ] isLike: aNode [ ^self class == aNode class ] isProcessingInstruction [ ^false ] isText [ ^false ] precedes: aNode [ | n1 n2 | aNode document == self document ifFalse: [self error: 'These nodes can''t be ordered. They are not in the same document.']. aNode == self document ifTrue: [^false]. self == self document ifTrue: [^true]. n1 := self. n2 := aNode. (n2 hasAncestor: n1) ifTrue: [^true]. (n1 hasAncestor: n2) ifTrue: [^false]. [n1 parent == n2 parent] whileFalse: [[n1 parent hasAncestor: n2 parent] whileTrue: [n1 := n1 parent]. [n2 parent hasAncestor: n1 parent] whileTrue: [n2 := n2 parent]. n1 parent == n2 parent ifFalse: [n1 := n1 parent. n2 := n2 parent]]. ^(n1 parent indexOf: n1) < (n1 parent indexOf: n2) ] nodesDo: aBlock [ aBlock value: self ] findNamespaceAt: qualifier [ | ns node | qualifier = 'xml' ifTrue: [^XML_URI]. ns := nil. node := self. [node isElement and: [ns == nil]] whileTrue: [ns := node namespaceAt: qualifier. node := node parent]. ^ns ] findQualifierAtNamespace: ns [ | qual node | qual := nil. node := self. [node isElement and: [qual == nil]] whileTrue: [qual := node qualifierAtNamespace: ns. node := node parent]. ^qual ] namespaceAt: qualifier [ ^nil ] qualifierAtNamespace: ns [ ^nil ] ] Node subclass: Entity [ | name text systemID publicID | Identifies the entity in an entity reference text The entity''s contents systemID URI used to retrieve an external entity''s contents publicID Alternative URI used to retrieve an external entity''s contents'> entityType [ ^self subclassResponsibility ] externalFrom: anArray [ anArray class == Array ifFalse: [self error: 'External ID is expected to be an Array']. anArray size = 2 ifTrue: [publicID := anArray at: 1. systemID := anArray at: 2] ifFalse: [self error: 'External ID has too many or too few identifiers'] ] name [ ^name ] name: aName [ name := aName ] publicID [ ^publicID ] systemID [ ^systemID ] text [ ^text ] text: aString [ text := aString ] isExternal [ ^publicID notNil or: [systemID notNil] ] isParsed [ ^true ] printOn: aStream [ self basicPrintOn: aStream. text == nil ifTrue: [aStream nextPutAll: '(' , self systemID , ')'] ifFalse: [aStream nextPutAll: '(' , text , ')'] ] ] Node subclass: Document [ | root nodes dtd ids | The outer-most element of the XML document. nodes The root Element as well as all other PIs and Comments which precede or follow it. dtd Associated document type definition ids Map which converts ID names to Elements, allowing a simple cross reference within the document.'> initialize [ super initialize. nodes := OrderedCollection new. ids := Dictionary new ] addNamespaceDefinitions [ | d tag | d := Dictionary new. self nodesDo: [:aNode | tag := aNode tag. tag isNil ifFalse: [(d at: tag qualifier ifAbsent: [tag namespace]) = tag namespace ifFalse: [self error: 'Using the same tag for multiple namespaces is not currently supported']. d at: tag qualifier put: tag namespace]]. (d at: '' ifAbsent: ['']) = '' ifTrue: [d removeKey: '' ifAbsent: []]. d removeKey: 'xml' ifAbsent: []. d removeKey: 'xmlns' ifAbsent: []. self root == nil ifFalse: [self root namespaces: d] ] addNode: aNode [ nodes add: aNode. aNode parent: self. aNode isElement ifTrue: [root == nil ifTrue: [root := aNode] ifFalse: [self error: 'It is illegal to have more than one element node at the top level in a document']] ] atID: id ifAbsent: aBlock [ ^ids at: id ifAbsent: aBlock ] atID: id put: element [ ids at: id put: element ] children [ ^nodes ] document [ ^self ] dtd [ ^dtd ] dtd: aDTD [ dtd := aDTD ] elements [ ^nodes ] indexOf: aChild [ aChild parent == self ifFalse: [^nil]. ^self children identityIndexOf: aChild ifAbsent: [nil] ] root [ ^root ] selectNodes: aBlock [ ^nodes select: aBlock ] setRoot: aNode [ root := aNode ] hasSubNodes [ ^nodes size > 0 ] isContent [ ^true ] isDocument [ ^true ] printHTMLOn: aStream [ nodes do: [:n | n printHTMLOn: aStream] ] printOn: aStream [ nodes do: [:n | n printOn: aStream. aStream nl] ] printSunCanonicalOn: aStream [ self dtd notNil ifTrue: [self dtd printCanonicalOn: aStream]. nodes do: [:n | n printCanonicalOn: aStream] ] nodesDo: aBlock [ aBlock value: self. 1 to: self elements size do: [:i | (self elements at: i) nodesDo: aBlock] ] saxDo: aDriver [ aDriver startDocument. self dtd == nil ifFalse: [self dtd saxDo: aDriver]. 1 to: self children size do: [:i | (self children at: i) saxDo: aDriver]. aDriver endDocument ] ] Node subclass: Element [ | tag attributes namespaces elements userData definition | the tag name of this element attributes A list of the attributes that appeared in the element''s start tag, usually excluding those attributes that define namespace mappings. namespaces A map from namespace qualifiers to URIs, used to resolve qualifiers within the scope of this element. elements The Element, Text, Comment, and PI nodes that appear within this Element but are not contained by a child Element. userData used by clients to add annotations to the element definition suspect this is unused'> Element class >> tag: tag [ ^self new setTag: tag attributes: nil elements: nil ] Element class >> tag: tag attributes: attributes elements: elements [ ^self new setTag: tag attributes: attributes elements: elements ] Element class >> tag: tag elements: elements [ ^self new setTag: tag attributes: nil elements: elements ] initialize [ super initialize. tag := 'undefined'. attributes := #() ] anyElementNamed: elementName [ "This will return the receiver if its name matches the requirement." | list | list := self anyElementsNamed: elementName. list size > 1 ifTrue: [self error: 'There is not a unique element with this tag']. ^list isEmpty ifFalse: [list first] ] anyElementsNamed: elementName [ "This includes the receiver as one of the possibilities." | list | list := OrderedCollection new. self nodesDo: [:e | (e isElement and: [e tag isLike: elementName]) ifTrue: [list add: e]]. ^list ] attributes [ ^attributes == nil ifTrue: [#()] ifFalse: [attributes] ] characterData [ | str all | all := self elements. all size = 0 ifTrue: [^'']. all size = 1 ifTrue: [^all first characterData]. str := (String new: 128) writeStream. self characterDataOnto: str. ^str contents ] characterDataOnto: str [ self elements do: [:i | i isContent ifTrue: [i characterDataOnto: str]] ] children [ ^elements == nil ifTrue: [#()] ifFalse: [elements] ] definition [ ^definition ] definition: aPattern [ definition := aPattern ] description [ ^'an <%1> element' % {tag} ] elementNamed: elementName [ | list | list := self elementsNamed: elementName. list size = 1 ifFalse: [self error: 'There is not a unique element with this tag']. ^list first ] elements [ ^elements == nil ifTrue: [#()] ifFalse: [elements] ] elementsNamed: elementName [ ^self elements select: [:e | e isElement and: [e tag isLike: elementName]] ] expandedName [ ^tag expandedName ] indexOf: aChild [ aChild parent == self ifFalse: [^nil]. ^aChild isAttribute ifTrue: [-1] ifFalse: [elements identityIndexOf: aChild ifAbsent: [nil]] ] namespaces: aDictionaryOrNil [ namespaces := aDictionaryOrNil ] selectNodes: aBlock [ ^self attributes , self elements select: aBlock ] tag [ ^tag ] userData [ ^userData ] userData: anObject [ userData := anObject ] valueOfAttribute: attributeName ifAbsent: aBlock [ ^(self attributes detect: [:a | a tag isLike: attributeName] ifNone: [^aBlock value]) value ] printHTMLOn: aStream [ | elem | self saxDo: (SAXWriter new output: aStream) forBodyDo: [elem := elements == nil ifTrue: [#()] ifFalse: ["reject: [:str | str isBlankText]" elements]. self isHTMLBlock ifTrue: [aStream nl]. elem do: [:e | e printHTMLOn: aStream. self isHTMLBlock ifTrue: [aStream nl]]] ] printOn: aStream depth: indent [ | elem | self saxDo: (SAXWriter new output: aStream) forBodyDo: [elements == nil ifFalse: [elem := elements reject: [:str | str isText and: [str isStripped]]. (elem size <= 1 and: [(elem contains: [:n | n isText not]) not]) ifTrue: [elem do: [:e | e printOn: aStream depth: indent + 1]] ifFalse: [1 to: elem size do: [:i | | e | e := elem at: i. aStream nl; space: indent + 1. e isString ifTrue: [aStream nextPutAll: e] ifFalse: [e printOn: aStream depth: indent + 1]]. aStream nl; space: indent]]] ] simpleDescription [ ^'<' , self tag asString , '>' ] namespaceAt: qualifier [ ^namespaces == nil ifTrue: [nil] ifFalse: [namespaces at: qualifier ifAbsent: [nil]] ] qualifierAtNamespace: ns [ ^namespaces == nil ifTrue: [nil] ifFalse: [namespaces keysAndValuesDo: [:qualifier :namespace | namespace = ns ifTrue: [^qualifier]]. nil] ] attributes: a [ attributes := a. a == nil ifFalse: [a do: [:i | i parent: self]] ] condenseList [ elements == nil ifFalse: [elements size = 0 ifTrue: [elements := nil] ifFalse: [elements := elements asArray]] ] condenseText [ | elmts str tc | elmts := (Array new: elements size) writeStream. str := nil. elements do: [:elm | elm isText ifTrue: [str == nil ifTrue: [str := (String new: elm text size) writeStream]. tc := elm class. str nextPutAll: elm text] ifFalse: [str == nil ifFalse: [elmts nextPut: (tc new text: str contents)]. str := nil. elmts nextPut: elm]]. str == nil ifFalse: [elmts nextPut: (tc new text: str contents)]. elements := elmts contents ] elements: e [ elements := e. self isEmpty ifFalse: [self condenseText. elements do: [:elm | elm parent: self]] ] setTag: t attributes: a elements: e [ tag := t isString ifTrue: [NodeTag new qualifier: '' ns: '' type: t] ifFalse: [t]. self attributes: a. self elements: e ] hasSubNodes [ ^elements size > 0 or: [attributes size > 0] ] isContent [ ^true ] isElement [ ^true ] isEmpty [ ^elements == nil ] isHTMLBlock [ ^#('p' 'html' 'head' 'body') includes: tag asLowercase ] isLike: aNode [ ^self class == aNode class and: [self tag isLike: aNode tag] ] notEmpty [ ^elements ~~ nil ] nodesDo: aBlock [ aBlock value: self. 1 to: self attributes size do: [:i | (self attributes at: i) nodesDo: aBlock]. 1 to: self elements size do: [:i | (self elements at: i) nodesDo: aBlock] ] saxDo: aDriver [ namespaces == nil ifFalse: [namespaces keysAndValuesDo: [:qual :uri | aDriver startPrefixMapping: qual uri: uri]]. aDriver startElement: self tag namespace localName: self tag type qName: self tag asString attributes: self attributes. 1 to: self children size do: [:i | (self children at: i) saxDo: aDriver]. aDriver endElement: self tag namespace localName: self tag type qName: self tag asString. namespaces == nil ifFalse: [namespaces keysAndValuesDo: [:qual :uri | aDriver endPrefixMapping: qual]] ] saxDo: aDriver forBodyDo: aBlock [ "a variation on #saxDo: that lets the client control how the body of the element is to be printed." namespaces == nil ifFalse: [namespaces keysAndValuesDo: [:qual :uri | aDriver startPrefixMapping: qual uri: uri]]. aDriver startElement: self tag namespace localName: self tag type qName: self tag asString attributes: self attributes. (aDriver respondsTo: #closeOpenTag) ifTrue: [aDriver closeOpenTag]. aBlock value. aDriver endElement: self tag namespace localName: self tag type qName: self tag asString. namespaces == nil ifFalse: [namespaces keysAndValuesDo: [:qual :uri | aDriver endPrefixMapping: qual]] ] addAttribute: aNode [ attributes isNil ifTrue: [attributes := OrderedCollection new]. attributes class == OrderedCollection ifFalse: [attributes := attributes asOrderedCollection]. attributes add: aNode ] addNode: aNode [ aNode parent: self. elements == nil ifTrue: [elements := OrderedCollection new: 5] ifFalse: [elements class == Array ifTrue: [elements := elements asOrderedCollection]]. elements addLast: aNode ] removeAttribute: aNode [ attributes isNil ifFalse: [attributes class == OrderedCollection ifFalse: [attributes := attributes asOrderedCollection]. attributes remove: aNode ifAbsent: []. attributes isEmpty ifTrue: [attributes := nil]] ] removeNode: aNode [ elements isNil ifFalse: [elements class == OrderedCollection ifFalse: [elements := elements asOrderedCollection]. elements remove: aNode ifAbsent: []. elements isEmpty ifTrue: [elements := nil]] ] ] Node subclass: Text [ | text stripped | the actual data of the Text. stripped Will be true if the text contains only white space and if the parser has determined that the client would not be interested in the data.'> Text class >> text: aString [ ^self new text: aString ] characterData [ ^self text ] characterDataOnto: str [ str nextPutAll: self text ] description [ ^'text' ] strip: aBoolean [ stripped := aBoolean ] text [ ^text ] text: aText [ text := aText. stripped == nil ifTrue: [stripped := false] ] printHTMLOn: aStream [ text == nil ifTrue: [^self]. self isStripped ifFalse: [self printCanonical: text on: aStream] ] printOn: aStream depth: indent [ text == nil ifTrue: [aStream nextPutAll: '&nil;'] ifFalse: [self printQuoted: text on: aStream] ] isBlankText [ ^(text contains: [:i | i isSeparator not]) not ] isContent [ ^true ] isStripped [ ^stripped ] isText [ ^true ] saxDo: aDriver [ aDriver characters: text from: 1 to: text size ] ] Entity subclass: GeneralEntity [ | ndata definedExternally | Some general entities may have a notation associated with them which identifies how they are to be processed--this instace variable identifies that Notation.'> entityType [ ^'generic' ] isDefinedExternally [ ^definedExternally ] isDefinedExternally: aBoolean [ definedExternally := aBoolean ] ndata: aNotifierNameOrNil [ ndata := aNotifierNameOrNil ] isParsed [ ^ndata == nil ] ] Entity subclass: ParameterEntity [ entityType [ ^'parameter' ] ] Node subclass: Comment [ | text | ''. According to the XML 1.0 specification, for compatibilty, double-hyphens (the string ''--'') must not occur within comments. Instance Variables: text contents of the comment element'> printHTMLOn: aStream [ self printOn: aStream ] printOn: aStream depth: indent [ aStream nextPutAll: '' ] text [ ^text ] text: aText [ text := aText ] isComment [ ^true ] saxDo: aDriver [ aDriver comment: text from: 1 to: text size ] ] Document subclass: DocumentFragment [ addNode: aNode [ nodes add: aNode. aNode parent: self. aNode isElement ifTrue: [root == nil ifTrue: [root := aNode]] ] saxDo: aDriver [ aDriver startDocumentFragment. self dtd == nil ifFalse: [self dtd saxDo: aDriver]. 1 to: self children size do: [:i | (self children at: i) saxDo: aDriver]. aDriver endDocumentFragment ] ] SAXDriver subclass: DOM_SAXDriver [ | stack document newNamespaces | A stack containing the various elements that contain the current parse position. document The Document or DocumentFragment which models the entire XML document being parsed. newNamespaces maps qualifiers to namespaces for the next element'> comment: data from: start to: stop [ document == nil ifTrue: [self startDocument]. stack last addNode: (Comment new text: (data copyFrom: start to: stop)) ] idOfElement: elementID [ "Notify the client what was the ID of the latest startElement" document atID: elementID put: stack last ] characters: aString [ stack last addNode: (Text text: aString) ] endDocument [ document := stack removeLast. document isDocument ifFalse: [self error: 'End of Document not expected']. stack isEmpty ifFalse: [self error: 'End of Document not expected'] ] endDocumentFragment [ document := stack removeLast. document isDocument ifFalse: [self error: 'End of Document not expected']. stack isEmpty ifFalse: [self error: 'End of Document not expected'] ] endElement: namespaceURI localName: localName qName: name [ "indicates the end of an element. See startElement" stack removeLast condenseList ] ignorableWhitespace: aString [ stack last addNode: (Text text: aString) ] processingInstruction: targetString data: dataString [ document == nil ifTrue: [self startDocument]. stack last addNode: (PI name: targetString text: dataString) ] startDocument [ document := Document new. document dtd: DocumentType new. stack := OrderedCollection with: document ] startDocumentFragment [ document := DocumentFragment new. document dtd: DocumentType new. stack := OrderedCollection with: document ] startElement: namespaceURI localName: localName qName: name attributes: attributes [ | element tag | document == nil ifTrue: [self startDocument]. tag := NodeTag new name: name ns: namespaceURI type: localName. element := Element tag: tag attributes: attributes elements: OrderedCollection new. element namespaces: newNamespaces. newNamespaces := nil. stack size = 1 ifTrue: [document dtd declaredRoot: name]. stack last addNode: element. stack addLast: element ] startPrefixMapping: prefix uri: uri [ newNamespaces == nil ifTrue: [newNamespaces := Dictionary new]. newNamespaces at: prefix put: uri ] notationDecl: name publicID: publicID systemID: systemID [ | notation | notation := Notation new name: name identifiers: (Array with: publicID with: systemID). document dtd notationAt: name put: notation from: self ] document [ ^document ] endElement [ | namespaceURI localName name tag | tag := stack last tag. tag isString ifTrue: [localName := name := tag. namespaceURI := ''] ifFalse: [localName := tag type. name := tag asString. namespaceURI := tag namespace]. ^self endElement: namespaceURI localName: localName qName: name ] startElement: tag atts: attrs [ | namespaceURI localName name attributes | tag isString ifTrue: [localName := name := tag. namespaceURI := ''] ifFalse: [localName := tag type. name := tag asString. namespaceURI := tag namespace]. attributes := attrs == nil ifTrue: [#()] ifFalse: [attrs]. ^self startElement: namespaceURI localName: localName qName: name attributes: attributes ] ] Eval [ "yes, we change the superclass. Gross." Node subclass: #Attribute ] Node subclass: PI [ | name text | ''. According to the XML 1.0 specification, the target names "XML", "xml" and so on are reserved for standardization. Instance Variables: name the target of this processing instruction, used to identify the application to which this processing instruction is directed. text the processing instructions themselves'> PI class >> name: nm text: aString [ ^self new name: nm text: aString ] name: nm text: aString [ name := nm. text := aString ] name [ ^name ] text [ ^text ] printHTMLOn: aStream [ aStream nextPutAll: '' ] printOn: aStream depth: indent [ aStream nextPutAll: '' ] isLike: aNode [ ^self class == aNode class and: [self name isLike: aNode name] ] isProcessingInstruction [ ^true ] saxDo: aDriver [ aDriver processingInstruction: name data: text ] ] Node subclass: Notation [ | name publicID systemID | '' The name instance variable provides a name or identifier for the notation, for use in entity and attribute specifications. The publicID instance variable provides an external identifier which allows the XML processor or the client application to locate a helper application capable of processing data in the given notation. The systemID variable allows the parser to optionally resolve the publicID into the system identifier, file name, or other information needed to allow the application to call a processor for data in the notation. Instance Variables: name A unique identifier for the Notation within the document. publicID The public ID of the Notation, which seems to not be heavily used at present. systemID A URI for the notation, which can be used to point to an application which can process resources of this notation type, or can be used as a key in a local map to find the application which should be used.'> name: aName identifiers: anArray [ name := aName. anArray size = 2 ifTrue: [systemID := anArray at: 2. publicID := anArray at: 1] ifFalse: [self error: 'Invalid PUBLIC / SYSTEM identifiers'] ] name [ ^name ] publicID [ ^publicID ] systemID [ ^systemID ] ] Object subclass: DocumentType [ | generalEntities parameterEntities notations declaredRoot | Definitions for the general entities that can be used in the body of the document. parameterEntities Definitions for the parameter entities that can be used in the DTD of the document. notations Notations defined in the DTD. declaredRoot The NodeTag which the DTD declares will be the root element of the document--a document cannot be valid if this does not match the tag of the root element.'> DocumentType class >> new [ ^super new initialize ] initialize [ notations := Dictionary new. generalEntities := Dictionary new. parameterEntities := Dictionary new ] declaredRoot [ ^declaredRoot ] declaredRoot: aTag [ declaredRoot := aTag ] generalEntityAt: key [ "We do some tricks to make sure that, if the value is predefined in the parser, we use the predefined value. We could just store the predefined values in with the general ones, but we don't want to show warnings if the user (very correctly) defines them. An enhancement would be to let the user use his own values rather than the predefined ones, but we know that the predefined ones will be correct--we don't know that his will be." | val | val := PredefinedEntities at: key ifAbsent: []. val == nil ifTrue: [val := generalEntities at: key ifAbsent: []]. ^val ] generalEntityAt: key put: value [ generalEntities at: key put: value ] generalEntityAt: key put: value from: anErrorReporter [ (generalEntities includesKey: key) ifTrue: [^anErrorReporter warn: 'The general entity "%1" has been defined more than once' % {key}]. generalEntities at: key put: value ] notationAt: name [ ^notations at: name ifAbsent: [nil] ] notationAt: name from: anErrorReporter [ ^notations at: name ifAbsent: [anErrorReporter invalid: 'Reference to an undeclared Notation'] ] notationAt: name ifAbsent: aBlock [ ^notations at: name ifAbsent: aBlock ] notationAt: name put: notation [ notations at: name put: notation ] notationAt: name put: notation from: anErrorReporter [ (notations includesKey: name) ifTrue: [anErrorReporter invalid: 'Duplicate definitions for a Notation']. notations at: name put: notation ] parameterEntityAt: key [ ^parameterEntities at: key ifAbsent: [] ] parameterEntityAt: key put: value [ parameterEntities at: key put: value ] parameterEntityAt: key put: value from: anErrorReporter [ (parameterEntities includesKey: key) ifTrue: [^anErrorReporter warn: 'The parameter entity "%1" has been defined more than once' % {key}]. parameterEntities at: key put: value ] printCanonicalOn: aStream [ "Jumping through hoops to get Notations printed just as Sun desires--Are public IDs really supposed to have their white space normalized? If so, we should move normalization to the parser." | s s1 | notations isEmpty ifTrue: [^self]. aStream nextPutAll: ''; nl]. aStream nextPutAll: ']>'; nl ] saxDo: aDriver [ notations == nil ifFalse: [notations do: [:n | aDriver notationDecl: n name publicID: n publicID systemID: n systemID]] ] ] SAXDriver extend [ isValidating [ "Allows a SAX driver to act like a parser when accessing a DocumentType" ^false ] invalid: aMessage [ "Allows a SAX driver to act like a parser when accessing a DocumentType" self nonFatalError: (InvalidSignal new messageText: aMessage) ] malformed: aMessage [ "Allows a SAX driver to act like a parser when accessing a DocumentType" self fatalError: (MalformedSignal new messageText: aMessage) ] warn: aMessage [ "Allows a SAX driver to act like a parser when accessing a DocumentType" self warning: (WarningSignal new messageText: aMessage) ] ] Object subclass: ElementContext [ | tag type namespaces isExternal | The name of the current element. type A type definition for the current element, used to validate the contents. namespaces A map from namespace qualifiers to namespace URIs, which is used to interpret the meaning of namespace qualifiers within the scope of the element.'> namespaces [ namespaces == nil ifTrue: [namespaces := Dictionary new]. ^namespaces ] tag [ ^tag ] tag: aTag [ tag := aTag isString ifTrue: [NodeTag new qualifier: '' ns: '' type: aTag] ifFalse: [aTag] ] type [ ^self shouldNotImplement ] type: anElementType [ type := Array with: anElementType. isExternal := anElementType isExternal ] types [ ^type ] types: anArray [ type := anArray ] defineDefaultNamespace: attribute [ self namespaces at: '' put: attribute value ] defineNamespace: attribute from: aParser [ (#('xmlns' 'xml') includes: attribute tag type) ifTrue: [self error: 'It is illegal to redefine the qualifier "%1".' % {attribute tag type}]. attribute value isEmpty ifTrue: [aParser invalid: 'It is not permitted to have an empty URI as a namespace name']. self namespaces at: attribute tag type put: attribute value ] findNamespace: ns [ ^namespaces isNil ifTrue: [nil] ifFalse: [namespaces at: ns ifAbsent: [nil]] ] definesNamespaces [ ^namespaces notNil and: [namespaces isEmpty not] ] isDefinedExternal [ ^isExternal ] ] Eval [ XML at: #XML_URI put: 'http://www.w3.org/XML/1998/namespace'. XML at: #PredefinedEntities put: ((Dictionary new) at: 'amp' put: ((GeneralEntity new) name: 'amp'; text: '&'); at: 'lt' put: ((GeneralEntity new) name: 'lt'; text: '<'); at: 'gt' put: ((GeneralEntity new) name: 'gt'; text: (String with: $>)); at: 'apos' put: ((GeneralEntity new) name: 'apos'; text: (String with: $')); at: 'quot' put: ((GeneralEntity new) name: 'quot'; text: (String with: $")); yourself). ] smalltalk-3.2.5/packages/xml/dom/stamp-classes0000644000175000017500000000000012123404352016247 00000000000000smalltalk-3.2.5/packages/xml/dom/package.xml0000644000175000017500000000020612123404352015672 00000000000000 XML-DOM XML XML-SAXDriver DOM.st smalltalk-3.2.5/packages/xml/saxparser/0000755000175000017500000000000012130456023015070 500000000000000smalltalk-3.2.5/packages/xml/saxparser/Makefile.frag0000644000175000017500000000031712130343733017372 00000000000000XML-SAXParser_FILES = \ packages/xml/saxparser/Parser.st $(XML-SAXParser_FILES): $(srcdir)/packages/xml/saxparser/stamp-classes: $(XML-SAXParser_FILES) touch $(srcdir)/packages/xml/saxparser/stamp-classes smalltalk-3.2.5/packages/xml/saxparser/Parser.st0000644000175000017500000002542512123404352016624 00000000000000"====================================================================== | | VisualWorks XML Framework - SAX Parser interface | | ======================================================================" "====================================================================== | | Copyright (c) 2000, 2002 Cincom, Inc. | Copyright (c) 2009 Free Software Foundation, Inc. | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" Object subclass: SAXParser [ | sax validating flags | the output validating if true then the parse validates the XML flags sundry boolean values that are not accessed often enough to need separate instance variables.'> DefaultParserClass := nil. SAXParser class >> defaultParserClass [ ^DefaultParserClass ] SAXParser class >> defaultParserClass: aClass [ DefaultParserClass := aClass. ] SAXParser class >> new [ ^super new initialize ] SAXParser class >> on: aDataSource [ "The dataSource may be a URI, a Filename (or a String which will be treated as a Filename), or an InputSource." ^self new on: aDataSource ] SAXParser class >> onFile: aFilename [ ^self on: (FileStream open: aFilename mode: FileStream read) ] SAXParser class >> onString: aString [ ^self on: aString readStream ] SAXParser class >> processDocumentInFilename: aFilename [ ^self processDocumentInFilename: aFilename beforeScanDo: [:parser | ] ] SAXParser class >> processDocumentInFilename: aFilename beforeScanDo: aBlock [ | stream p | p := self onFile: aFilename. aBlock value: p. ^p scanDocument ] SAXParser class >> processDocumentString: aString [ ^self processDocumentString: aString beforeScanDo: [:parser | ] ] SAXParser class >> processDocumentString: aString beforeScanDo: aBlock [ | p | p := self onString: aString. aBlock value: p. ^p scanDocument ] SAXParser class >> mapEncoding: anEncoding [ ^anEncoding asUppercase ] initialize [ validating := true. self saxDriver: DOM_SAXDriver new. flags := 0. self processNamespaces: true. ] on: dataSource [ "The dataSource may be a URI, a Filename (or a String which will be treated as a Filename), or an InputSource." "Clear those flags that keep track of the state of the parse, but retain those that relate to options." flags := flags bitAnd: 65535 bitInvert. ] saxDriver: aSAXDriver [ sax := aSAXDriver. sax setDocumentLocator: (Locator new parser: self) ] document [ ^sax document ] saxDriver [ ^sax ] validate: aBoolean [ validating := aBoolean ] isValidating [ ^validating ] scanDocument [ self subclassResponsibility ] atEnd [ self subclassResponsibility ] documentNode [ ^self document ] expected: string [ self malformed: '%1 expected, but not found' % {string} ] expectedWhitespace [ self malformed: 'White space expected but not found' ] invalid: aMessage [ sax nonFatalError: (InvalidSignal new messageText: aMessage) ] malformed: aMessage [ sax fatalError: (MalformedSignal new messageText: aMessage) ] warn: aMessage [ sax warning: (WarningSignal new messageText: aMessage) ] declaredStandalone: aBoolean [ ^aBoolean ifTrue: [flags := flags bitOr: 2] ifFalse: [flags := flags bitAnd: 2 bitInvert] ] flagsComment [ "The 'flags' instance variable is an integer used as a bit vector of boolean values, either recording state as processing occurs, or recording options that control how the processor is used. The following documents which bits have been assigned and for which purpose. State bits [0..15] 1 -- document has standalone='yes' declaration 2 -- document has a DTD 3 -- document has an externalDTD 4 -- document uses parameter entity references to define part of the DTD Option bits [16..29] 16 -- do namespace attributes 17 -- pass namespace declarations on to the client " ^self commentOnly ] hasDTD [ ^(flags bitAnd: 4) = 4 ] hasExternalDTD [ ^(flags bitAnd: 8) = 8 ] isDeclaredStandalone [ ^(flags bitAnd: 2) = 2 ] noteDTD [ flags := flags bitOr: 4 ] noteExternalDTD [ flags := flags bitOr: 8 ] notePEReference [ flags := flags bitOr: 16 ] processNamespaces [ ^(flags bitAnd: 65536) = 65536 ] processNamespaces: aBoolean [ ^aBoolean ifTrue: [flags := flags bitOr: 65536] ifFalse: [flags := flags bitAnd: 65536 bitInvert] ] showNamespaceDeclarations [ ^(flags bitAnd: 131072) = 131072 ] showNamespaceDeclarations: aBoolean [ ^aBoolean ifTrue: [flags := flags bitOr: 131072] ifFalse: [flags := flags bitAnd: 131072 bitInvert] ] usesParameterEntities [ ^(flags bitAnd: 16) = 16 ] atFeature: aURIstring [ aURIstring = SAXValidate ifTrue: [^self isValidating]. aURIstring = SAXNamespace ifTrue: [^self processNamespaces]. aURIstring = SAXNamespacePrefixes ifTrue: [^self showNamespaceDeclarations]. aURIstring = SAXExternalGeneralEntities ifTrue: [^SAXNotSupportedException signal]. aURIstring = SAXExternalParameterEntities ifTrue: [^SAXNotSupportedException signal]. SAXNotRecognizedException new signal ] atFeature: aURIstring put: aBoolean [ aURIstring = SAXValidate ifTrue: [^self validate: aBoolean]. aURIstring = SAXNamespace ifTrue: [^self processNamespaces: aBoolean]. aURIstring = SAXNamespacePrefixes ifTrue: [^self showNamespaceDeclarations: aBoolean]. aURIstring = SAXExternalGeneralEntities ifTrue: [^SAXNotSupportedException signal]. aURIstring = SAXExternalParameterEntities ifTrue: [^SAXNotSupportedException signal]. SAXNotRecognizedException new signal ] atProperty: aURIstring [ SAXNotRecognizedException new signal ] atProperty: aURIstring put: anObject [ SAXNotRecognizedException new signal ] contentHandler [ ^sax contentHandler ] contentHandler: aSAXDriver [ | newSax | newSax := sax class == SAXDispatcher ifTrue: [sax] ifFalse: [SAXDispatcher new handlers: sax]. newSax contentHandler: aSAXDriver. self saxDriver: newSax ] dtdHandler [ ^sax dtdHandler ] dtdHandler: aSAXDriver [ | newSax | newSax := sax class == SAXDispatcher ifTrue: [sax] ifFalse: [SAXDispatcher new handlers: sax]. newSax dtdHandler: aSAXDriver. self saxDriver: newSax ] entityResolver [ ^sax entityResolver ] entityResolver: aSAXDriver [ | newSax | newSax := sax class == SAXDispatcher ifTrue: [sax] ifFalse: [SAXDispatcher new handlers: sax]. newSax entityResolver: aSAXDriver. self saxDriver: newSax ] errorHandler [ ^sax errorHandler ] errorHandler: aSAXDriver [ | newSax | newSax := sax class == SAXDispatcher ifTrue: [sax] ifFalse: [SAXDispatcher new handlers: sax]. newSax errorHandler: aSAXDriver. self saxDriver: newSax ] handlers: aSAXDriver [ self saxDriver: aSAXDriver ] parse: dataSource [ self on: dataSource. ^self scanDocument ] parseElement [ self subclassResponsibility ] parseElement: dataSource [ self validate: false. self on: dataSource. ^self parseElement ] parseElements [ self subclassResponsibility ] parseElements: dataSource [ self validate: false. self on: dataSource. ^self parseElements ] ] SAXException subclass: SAXNotRecognizedException [ ] Eval [ XML at: #SAXExternalParameterEntities put: 'http://xml.org/sax/features/external-parameter-entities'; at: #SAXValidate put: 'http://xml.org/sax/features/validation'; at: #SAXNamespacePrefixes put: 'http://xml.org/sax/features/namespace-prefixes'; at: #SAXNamespace put: 'http://xml.org/sax/features/namespaces'; at: #XMLSignal put: XML.SAXException; at: #SAXExternalGeneralEntities put: 'http://xml.org/sax/features/external-general-entities'. ] smalltalk-3.2.5/packages/xml/saxparser/stamp-classes0000644000175000017500000000000012123404352017500 00000000000000smalltalk-3.2.5/packages/xml/saxparser/package.xml0000644000175000017500000000021712123404352017125 00000000000000 XML-SAXParser XML XML-SAXDriver Parser.st smalltalk-3.2.5/packages/xml/expat/0000755000175000017500000000000012130456023014201 500000000000000smalltalk-3.2.5/packages/xml/expat/Makefile.frag0000644000175000017500000000040312123404352016474 00000000000000XML-Expat_FILES = \ packages/xml/expat/ExpatPullParser.st packages/xml/expat/ExpatParser.st packages/xml/expat/ExpatTests.st $(XML-Expat_FILES): $(srcdir)/packages/xml/expat/stamp-classes: $(XML-Expat_FILES) touch $(srcdir)/packages/xml/expat/stamp-classes smalltalk-3.2.5/packages/xml/expat/ExpatTests.st0000644000175000017500000000350512123404352016600 00000000000000"====================================================================== | | Expat-based XML parser tests | | ======================================================================" "====================================================================== | | Copyright 2009 Free Software Foundation, Inc. | Written by Paolo Bonzini. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" XMLPullParserTest subclass: ExpatXMLPullParserTest [ parserOn: source [ ^ExpatXMLPullParser onString: source. ] ] XMLPullParserTest subclass: ExpatXMLParserTest [ parserOn: source [ ^XMLGenerativePullParser onParser: (ExpatXMLParser onString: source) ] ] smalltalk-3.2.5/packages/xml/expat/expat.c0000644000175000017500000004222112123404352015407 00000000000000/******************************* -*- C -*- **************************** * * Expat bindings * * ***********************************************************************/ /*********************************************************************** * * Copyright 2009 Free Software Foundation, Inc. * Written by Paolo Bonzini. * * This file is part of GNU Smalltalk. * * GNU Smalltalk is free software; you can redistribute it and/or modify it * under the terms of the GNU General Public License as published by the Free * Software Foundation; either version 2, or (at your option) any later * version. * * Linking GNU Smalltalk statically or dynamically with other modules is * making a combined work based on GNU Smalltalk. Thus, the terms and * conditions of the GNU General Public License cover the whole * combination. * * In addition, as a special exception, the Free Software Foundation * give you permission to combine GNU Smalltalk with free software * programs or libraries that are released under the GNU LGPL and with * independent programs running under the GNU Smalltalk virtual machine. * * You may copy and distribute such a system following the terms of the * GNU GPL for GNU Smalltalk and the licenses of the other code * concerned, provided that you include the source code of that other * code when and as the GNU GPL requires distribution of source code. * * Note that people who make modified versions of GNU Smalltalk are not * obligated to grant this special exception for their modified * versions; it is their choice whether to do so. The GNU General * Public License gives permission to release a modified version without * this exception; this exception also makes it possible to release a * modified version which carries forward this exception. * * GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT * ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or * FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for * more details. * * You should have received a copy of the GNU General Public License along with * GNU Smalltalk; see the file COPYING. If not, write to the Free Software * Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. * ***********************************************************************/ #include #include #include #include #include "gstpub.h" #include typedef struct st_XMLExpatPullParser { OBJ_HEADER; OOP needFlags[4]; OOP xpOOP; OOP nextParserOOP; OOP currentEventOOP; OOP pendingEventOOP; OOP sourceOOP; OOP sourceStackOOP; } *XMLExpatPullParser; typedef struct st_SAXEventSequence { OBJ_HEADER; OOP eventOOP; OOP nextOOP; } *SAXEventSequence; static OOP attributeClass; static OOP emptyString; static OOP nodeTagClass; static OOP saxEndCdataSectionClass; static OOP saxEndDoctypeDeclClass; static OOP saxEndDocumentFragmentClass; static OOP saxEndDocumentClass; static OOP saxExternalEntityRefClass; static OOP saxStartCdataSectionClass; static OOP saxStartDocumentFragmentClass; static OOP saxStartDocumentClass; static OOP saxTagEventClass; static OOP saxEndTagClass; static OOP saxStartTagClass; static OOP saxProcessingInstructionClass; static OOP saxTextClass; static OOP saxCommentClass; static OOP saxStartPrefixMappingClass; static OOP saxEndPrefixMappingClass; static OOP saxStartDoctypeDeclClass; static OOP saxNotationDeclClass; static OOP saxUnparsedEntityDeclClass; static OOP saxSkippedEntityClass; static OOP saxEventSequenceClass; static VMProxy *vmProxy; /* Count the number of attributes in the list of strings in ATTR. This is the number of strings divided by 2. */ static int count_attributes (const char **attr) { int i; for (i = 0; *attr; i++) attr += 2; return i; } /* Make a NodeTag object from P, which is a \n-delimited tag triplet (URI, local name, prefix). */ static OOP make_node_tag (const char *p) { const char *q, *r; char *tmp; int len; OOP tagOOP, nsOOP, typeOOP, qualOOP; mst_Object tagObj; q = strchr (p, '\n'); r = q ? strchr (q, '\n') : NULL; len = strlen (p); tmp = alloca (len + 1); memcpy (tmp, p, len + 1); if (q) { tmp[q - p] = '\0'; nsOOP = vmProxy->stringToOOP (tmp); typeOOP = vmProxy->stringToOOP (tmp + (q - p + 1)); } else { nsOOP = emptyString; typeOOP = vmProxy->stringToOOP (tmp); } if (r) { tmp[r - p] = '\0'; qualOOP = vmProxy->stringToOOP (tmp + (r - p + 1)); } else qualOOP = emptyString; tagOOP = vmProxy->objectAlloc (nodeTagClass, 0); tagObj = OOP_TO_OBJ (tagOOP); tagObj->data[0] = nsOOP; tagObj->data[1] = typeOOP; tagObj->data[2] = qualOOP; return tagOOP; } /* Make an Attribute object from ATTR[0] (a qualified name triplet) and ATTR[1] (the value). Account for our own brain damage: the number of instance variables inherited by Attribute is variable. */ static OOP make_attribute (const char **attr) { OOP attributeOOP, nameOOP, valueOOP; mst_Object obj; size_t n; nameOOP = make_node_tag (attr[0]); valueOOP = vmProxy->stringToOOP (attr[1]); attributeOOP = vmProxy->objectAlloc (attributeClass, 0); obj = OOP_TO_OBJ (attributeOOP); n = vmProxy->OOPToInt (obj->objSize) - 2 - OBJ_HEADER_SIZE_WORDS; obj->data[n] = nameOOP; obj->data[n + 1] = valueOOP; return attributeOOP; } /* Make an event object of class CLASSOOP and save it into PARSEROOP for later consumption. The variable arguments are a NULL-terminated list of OOPs to be placed in the instance variables of the event object. */ static void make_event (OOP parserOOP, OOP classOOP, ...) { va_list va; OOP eventOOP, ptr; OOP sentinelOOP; XMLExpatPullParser parserObj; SAXEventSequence pendingObj, sentinelObj; mst_Object obj; int i; eventOOP = vmProxy->objectAlloc (classOOP, 0); obj = OOP_TO_OBJ (eventOOP); va_start (va, classOOP); for (i = 0; (ptr = va_arg (va, OOP)); i++) obj->data[i] = ptr; va_end (va); parserObj = (XMLExpatPullParser) OOP_TO_OBJ (parserOOP); if (parserObj->currentEventOOP == vmProxy->nilOOP) { parserObj->currentEventOOP = eventOOP; return; } /* Sometimes, expat will return more than one event. In this case, the first will go into currentEventOOP, but the others will go in a circular linked list whose sentinel node is in pendingEventOOP. Using a circular linked list makes it very simple to add new events at the end without storing HEAD and TAIL of the list. To add a new node at the end, we put the event in the current sentinel node (which becomes the tail of the list!) and allocate a new sentinel. */ pendingObj = (SAXEventSequence) OOP_TO_OBJ (parserObj->pendingEventOOP); pendingObj->eventOOP = eventOOP; /* Allocate a new sentinel node and store it. */ sentinelOOP = vmProxy->objectAlloc (saxEventSequenceClass, 0); parserObj = (XMLExpatPullParser) OOP_TO_OBJ (parserOOP); pendingObj = (SAXEventSequence) OOP_TO_OBJ (parserObj->pendingEventOOP); sentinelObj = (SAXEventSequence) OOP_TO_OBJ (sentinelOOP); sentinelObj->nextOOP = pendingObj->nextOOP; pendingObj->nextOOP = sentinelOOP; parserObj->pendingEventOOP = sentinelOOP; } /* The event handlers for the expat parser. We just parse the arguments to the handler, make an event and try to stop the parser in order to push the event to Smalltalk. */ static void gst_StartElementHandler (void *userData, const XML_Char * name, const XML_Char ** atts) { XML_Parser p = userData; OOP parserOOP = XML_GetUserData (p); OOP attributesArray; int i; attributesArray = vmProxy->objectAlloc (vmProxy->arrayClass, count_attributes (atts)); for (i = 0; *atts; i++, atts += 2) { OOP attributeOOP = make_attribute (atts); mst_Object attributesObj = OOP_TO_OBJ (attributesArray); attributesObj->data[i] = attributeOOP; } make_event (parserOOP, saxStartTagClass, make_node_tag (name), vmProxy->nilOOP, attributesArray); XML_StopParser (p, 1); } static void gst_EndElementHandler (void *userData, const XML_Char * name) { XML_Parser p = userData; OOP parserOOP = XML_GetUserData (p); make_event (parserOOP, saxEndTagClass, make_node_tag (name), NULL); XML_StopParser (p, 1); } static void gst_CharacterDataHandler (void *userData, const XML_Char * s, int len) { XML_Parser p = userData; OOP parserOOP = XML_GetUserData (p); OOP stringOOP; char *data; data = memcpy (alloca (len + 1), s, len); data[len] = 0; stringOOP = vmProxy->stringToOOP (data); make_event (parserOOP, saxTextClass, stringOOP, vmProxy->intToOOP (1), vmProxy->intToOOP (len), stringOOP, NULL); XML_StopParser (p, 1); } static void gst_ProcessingInstructionHandler (void *userData, const XML_Char * target, const XML_Char * data) { XML_Parser p = userData; OOP parserOOP = XML_GetUserData (p); make_event (parserOOP, saxProcessingInstructionClass, vmProxy->stringToOOP (target), vmProxy->stringToOOP (data), NULL); XML_StopParser (p, 1); } static void gst_CommentHandler (void *userData, const XML_Char * data) { XML_Parser p = userData; OOP parserOOP = XML_GetUserData (p); OOP stringOOP = vmProxy->stringToOOP (data); make_event (parserOOP, saxCommentClass, stringOOP, vmProxy->intToOOP (1), vmProxy->intToOOP (strlen (data)), stringOOP, NULL); XML_StopParser (p, 1); } static void gst_StartCdataSectionHandler (void *userData) { XML_Parser p = userData; OOP parserOOP = XML_GetUserData (p); make_event (parserOOP, saxStartCdataSectionClass, NULL); XML_StopParser (p, 1); } static void gst_EndCdataSectionHandler (void *userData) { XML_Parser p = userData; OOP parserOOP = XML_GetUserData (p); make_event (parserOOP, saxEndCdataSectionClass, NULL); XML_StopParser (p, 1); } static void gst_StartDoctypeDeclHandler (void *userData, const XML_Char *doctypeName, const XML_Char *systemId, const XML_Char *publicId, int has_internal_subset) { XML_Parser p = userData; OOP parserOOP = XML_GetUserData (p); make_event (parserOOP, saxStartDoctypeDeclClass, vmProxy->stringToOOP (publicId), vmProxy->stringToOOP (systemId), make_node_tag (doctypeName), vmProxy->boolToOOP (has_internal_subset), NULL); XML_StopParser (p, 1); } static void gst_EndDoctypeDeclHandler (void *userData) { XML_Parser p = userData; OOP parserOOP = XML_GetUserData (p); make_event (parserOOP, saxEndDoctypeDeclClass, NULL); XML_StopParser (p, 1); } static void gst_UnparsedEntityDeclHandler (void *userData, const XML_Char * entityName, const XML_Char * base, const XML_Char * systemId, const XML_Char * publicId, const XML_Char * notationName) { XML_Parser p = userData; OOP parserOOP = XML_GetUserData (p); make_event (parserOOP, saxUnparsedEntityDeclClass, vmProxy->stringToOOP (publicId), vmProxy->stringToOOP (systemId), vmProxy->stringToOOP (entityName), vmProxy->stringToOOP (notationName), NULL); XML_StopParser (p, 1); } static void gst_NotationDeclHandler (void *userData, const XML_Char * notationName, const XML_Char * base, const XML_Char * systemId, const XML_Char * publicId) { XML_Parser p = userData; OOP parserOOP = XML_GetUserData (p); make_event (parserOOP, saxNotationDeclClass, vmProxy->stringToOOP (publicId), vmProxy->stringToOOP (systemId), vmProxy->stringToOOP (notationName), NULL); XML_StopParser (p, 1); } static void gst_StartNamespaceDeclHandler (void *userData, const XML_Char * prefix, const XML_Char * uri) { XML_Parser p = userData; OOP parserOOP = XML_GetUserData (p); make_event (parserOOP, saxStartPrefixMappingClass, vmProxy->stringToOOP (prefix), vmProxy->stringToOOP (uri), NULL); XML_StopParser (p, 1); } static void gst_EndNamespaceDeclHandler (void *userData, const XML_Char * prefix) { XML_Parser p = userData; OOP parserOOP = XML_GetUserData (p); make_event (parserOOP, saxEndPrefixMappingClass, vmProxy->stringToOOP (prefix), NULL); XML_StopParser (p, 1); } static void gst_SkippedEntityHandler (void *userData, const XML_Char * entityName) { XML_Parser p = userData; OOP parserOOP = XML_GetUserData (p); make_event (parserOOP, saxSkippedEntityClass, vmProxy->stringToOOP (entityName), NULL); XML_StopParser (p, 1); } /* This is a bit strange, because on the Smalltalk side we want to raise a Notification. So we raise a normal event passing the CONTEXT to it; the Smalltalk code arranges to signal the exception and, if it is handled, call XML_ExternalEntityParserCreate. The chain of parsers is handled on the Smalltalk side. */ static int gst_ExternalEntityRefHandler (XML_Parser p, const XML_Char * context, const XML_Char * base, const XML_Char * systemId, const XML_Char * publicId) { OOP parserOOP = XML_GetUserData (p); make_event (parserOOP, saxExternalEntityRefClass, vmProxy->stringToOOP (publicId), vmProxy->stringToOOP (systemId), vmProxy->stringToOOP (context), NULL); XML_StopParser (p, 1); return XML_STATUS_OK; } static void initClasses (void) { emptyString = vmProxy->stringToOOP (""); vmProxy->registerOOP (emptyString); attributeClass = vmProxy->classNameToOOP ("XML.Attribute"); nodeTagClass = vmProxy->classNameToOOP ("XML.NodeTag"); saxCommentClass = vmProxy->classNameToOOP ("XML.SAXComment"); saxEndCdataSectionClass = vmProxy->classNameToOOP ("XML.SAXEndCdataSection"); saxEndDoctypeDeclClass = vmProxy->classNameToOOP ("XML.SAXEndDoctypeDecl"); saxEndDocumentClass = vmProxy->classNameToOOP ("XML.SAXEndDocument"); saxEndDocumentFragmentClass = vmProxy->classNameToOOP ("XML.SAXEndDocumentFragment"); saxEndPrefixMappingClass = vmProxy->classNameToOOP ("XML.SAXEndPrefixMapping"); saxEndTagClass = vmProxy->classNameToOOP ("XML.SAXEndTag"); saxExternalEntityRefClass = vmProxy->classNameToOOP ("XML.SAXExternalEntityRef"); saxEventSequenceClass = vmProxy->classNameToOOP ("XML.SAXEventSequence"); saxNotationDeclClass = vmProxy->classNameToOOP ("XML.SAXNotationDecl"); saxProcessingInstructionClass = vmProxy->classNameToOOP ("XML.SAXProcessingInstruction"); saxSkippedEntityClass = vmProxy->classNameToOOP ("XML.SAXSkippedEntity"); saxStartCdataSectionClass = vmProxy->classNameToOOP ("XML.SAXStartCdataSection"); saxStartDoctypeDeclClass = vmProxy->classNameToOOP ("XML.SAXStartDoctypeDecl"); saxStartDocumentClass = vmProxy->classNameToOOP ("XML.SAXStartDocument"); saxStartDocumentFragmentClass = vmProxy->classNameToOOP ("XML.SAXStartDocumentFragment"); saxStartPrefixMappingClass = vmProxy->classNameToOOP ("XML.SAXStartPrefixMapping"); saxStartTagClass = vmProxy->classNameToOOP ("XML.SAXStartTag"); saxTagEventClass = vmProxy->classNameToOOP ("XML.SAXTagEvent"); saxTextClass = vmProxy->classNameToOOP ("XML.SAXText"); saxUnparsedEntityDeclClass = vmProxy->classNameToOOP ("XML.SAXUnparsedEntityDecl"); } /* Create a parser, associate it to PARSEROOP and set all the event handlers properly. */ static XML_Parser gst_XML_ParserCreate (OOP parserOOP) { XML_Parser p = XML_ParserCreateNS (NULL, '\n'); XML_UseParserAsHandlerArg (p); XML_SetUserData (p, parserOOP); XML_SetExternalEntityRefHandler (p, gst_ExternalEntityRefHandler); XML_SetStartElementHandler (p, gst_StartElementHandler); XML_SetEndElementHandler (p, gst_EndElementHandler); XML_SetCharacterDataHandler (p, gst_CharacterDataHandler); XML_SetProcessingInstructionHandler (p, gst_ProcessingInstructionHandler); XML_SetCommentHandler (p, gst_CommentHandler); XML_SetStartCdataSectionHandler (p, gst_StartCdataSectionHandler); XML_SetEndCdataSectionHandler (p, gst_EndCdataSectionHandler); XML_SetStartDoctypeDeclHandler (p, gst_StartDoctypeDeclHandler); XML_SetEndDoctypeDeclHandler (p, gst_EndDoctypeDeclHandler); XML_SetUnparsedEntityDeclHandler (p, gst_UnparsedEntityDeclHandler); XML_SetNotationDeclHandler (p, gst_NotationDeclHandler); XML_SetStartNamespaceDeclHandler (p, gst_StartNamespaceDeclHandler); XML_SetEndNamespaceDeclHandler (p, gst_EndNamespaceDeclHandler); XML_SetSkippedEntityHandler (p, gst_SkippedEntityHandler); XML_SetReturnNSTriplet (p, true); if (!saxEventSequenceClass) initClasses (); return p; } void gst_initModule (VMProxy * proxy) { vmProxy = proxy; vmProxy->defineCFunc ("gst_XML_ParserCreate", gst_XML_ParserCreate); vmProxy->defineCFunc ("XML_ParserFree", XML_ParserFree); vmProxy->defineCFunc ("XML_Parse", XML_Parse); vmProxy->defineCFunc ("XML_ResumeParser", XML_ResumeParser); vmProxy->defineCFunc ("XML_GetErrorCode", XML_GetErrorCode); vmProxy->defineCFunc ("XML_ErrorString", XML_ErrorString); vmProxy->defineCFunc ("XML_SetUserData", XML_SetUserData); vmProxy->defineCFunc ("XML_ExternalEntityParserCreate", XML_ExternalEntityParserCreate); } smalltalk-3.2.5/packages/xml/expat/ExpatPullParser.st0000644000175000017500000002011212123404352017560 00000000000000"====================================================================== | | Expat-based pull parser | | ======================================================================" "====================================================================== | | Copyright 2009 Free Software Foundation, Inc. | Written by Paolo Bonzini. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" Object subclass: SAXEventSequence [ | event next | SAXEventSequence class >> new [ ^super new initialize ] event [ ^event ] event: anObject [ event := anObject ] initialize [ next := self. ] isEmpty [ ^next == self ] next [ ^next ] next: aSAXList [ next := aSAXList. ] ] CObject subclass: XMLExpatParserObject [ XMLExpatParserObject class >> errorString: code [ ] XMLExpatParserObject class >> createFor: anObject [ ] externalEntityParser: contextString encoding: aString [ ] free [ ] parse: aString len: len isFinal: aBoolean [ ] errorCode [ ] errorString [ ^self class errorString: self errorCode ] resume [ ] userData [ ^(self castTo: ##(CObject type ptrType)) value ] userData: aCObject [ ] ] SAXExternalDecl subclass: SAXExternalEntityRef [ | context | neededBy: aParser [ | entity | entity := XMLResolveEntityNotification new publicID: self publicID; systemID: self systemID; signal. entity isNil ifFalse: [ aParser push: entity stream context: context ]. ^false ] serializeTo: sax [ ^sax resolveEntity: self publicID systemID: self systemID ] ] XMLPullParser subclass: ExpatXMLPullParser [ | xp nextParser current pending source sourceStack buffer first | ExpatXMLPullParser class >> on: source [ ^self new initialize: source ] atEnd [ ^source isNil ] current [ ^current ] initialize: aSource [ | input uri | input := (aSource isKindOf: Stream) ifTrue: [uri := [NetClients.URL fromString: aSource name] on: Error do: [:ex | ex return: nil]. InputSource uri: uri encoding: nil stream: aSource] ifFalse: [InputSource for: aSource]. sourceStack := OrderedCollection new. source := input stream. buffer := String new: 1024. xp := XMLExpatParserObject createFor: self. self addToBeFinalized. "Insert the first event." pending := SAXEventSequence new. current := SAXStartDocument new. first := true. ] finalize [ "Free the whole parser chain." [ xp isNil ] whileFalse: [ self pop ] ] push: aStream context: context [ "Push a new parser for the given stream. The context comes from the ExternalEntityRefHandler and is passed down to XML_ExternalEntityParserCreate." | userData | sourceStack add: source. source := aStream. first := true. "The userData of suspended parsers constitutes a list of parsers, with nextParser as the head." userData := xp userData. xp userData: nextParser. nextParser := xp. xp := xp externalEntityParser: context encoding: nil. "Move the suspended parser's userData to the new one." xp userData: userData. ] pop [ "Switch back to the parent parser of XP, which is stored in nextParser." | userData oldParser | oldParser := xp. xp := nextParser. xp isNil ifTrue: [ self removeToBeFinalized. source := nil. current := SAXEndDocument new ] ifFalse: [ source := sourceStack removeLast. nextParser := xp userData ifNotNil: [ :u | u castTo: XMLExpatParserObject type ]. xp userData: self ]. oldParser free. ] parseMore [ "Pass data from the source to the XML_Parser." | len | len := source nextAvailable: buffer size into: buffer startingAt: 1. ^xp parse: buffer len: len isFinal: source atEnd ] raiseError [ "Convert an Expat error to a Smalltalk exception." | code | code := xp errorCode. code = 3 ifTrue: [ EmptySignal signal ] ifFalse: [ MalformedSignal signal: (xp class errorString: code) ]. self removeToBeFinalized; finalize ] advance [ "Call the underlying parser, retrieving events and popping the current parser when the data source is exhausted." | result | "First try removing the head of the pending event queue. PENDING points to the tail of a circular list, and is just a sentinel node." pending isEmpty ifFalse: [ current := pending next event. pending next event: nil. pending next: pending next next. ^self ]. "See if we're done." self atEnd ifTrue: [^self]. "Start parsing. On the first call we need to do #parseMore." current := nil. result := first ifTrue: [ first := false. self parseMore ] ifFalse: [ xp resume ]. [ result = 2 ] whileFalse: [ result = 0 ifTrue: [ ^self raiseError; current ]. result := source atEnd ifTrue: [ self pop. current isNil ifFalse: [ 2 ] ifTrue: [ xp resume ] ] ifFalse: [ self parseMore ] ]. ^current ] ] smalltalk-3.2.5/packages/xml/expat/Makefile.am0000644000175000017500000000050712123404352016157 00000000000000moduleexec_LTLIBRARIES = expat.la AM_CPPFLAGS = -I$(top_srcdir)/libgst -I$(top_srcdir)/lib-src gst_module_ldflags = -rpath $(moduleexecdir) -release $(VERSION) -module \ -no-undefined -export-symbols-regex gst_initModule expat_la_SOURCES = expat.c expat_la_LIBADD = -lexpat expat_la_LDFLAGS = $(gst_module_ldflags) smalltalk-3.2.5/packages/xml/expat/Makefile.in0000644000175000017500000005246712130455426016212 00000000000000# Makefile.in generated by automake 1.11.6 from Makefile.am. # @configure_input@ # Copyright (C) 1994, 1995, 1996, 1997, 1998, 1999, 2000, 2001, 2002, # 2003, 2004, 2005, 2006, 2007, 2008, 2009, 2010, 2011 Free Software # Foundation, Inc. # This Makefile.in is free software; the Free Software Foundation # gives unlimited permission to copy and/or distribute it, # with or without modifications, as long as this notice is preserved. # This program is distributed in the hope that it will be useful, # but WITHOUT ANY WARRANTY, to the extent permitted by law; without # even the implied warranty of MERCHANTABILITY or FITNESS FOR A # PARTICULAR PURPOSE. @SET_MAKE@ VPATH = @srcdir@ am__make_dryrun = \ { \ am__dry=no; \ case $$MAKEFLAGS in \ *\\[\ \ ]*) \ echo 'am--echo: ; @echo "AM" OK' | $(MAKE) -f - 2>/dev/null \ | grep '^AM OK$$' >/dev/null || am__dry=yes;; \ *) \ for am__flg in $$MAKEFLAGS; do \ case $$am__flg in \ *=*|--*) ;; \ *n*) am__dry=yes; break;; \ esac; \ done;; \ esac; \ test $$am__dry = yes; \ } pkgdatadir = $(datadir)/@PACKAGE@ pkgincludedir = $(includedir)/@PACKAGE@ pkglibdir = $(libdir)/@PACKAGE@ pkglibexecdir = $(libexecdir)/@PACKAGE@ am__cd = CDPATH="$${ZSH_VERSION+.}$(PATH_SEPARATOR)" && cd install_sh_DATA = $(install_sh) -c -m 644 install_sh_PROGRAM = $(install_sh) -c install_sh_SCRIPT = $(install_sh) -c INSTALL_HEADER = $(INSTALL_DATA) transform = $(program_transform_name) NORMAL_INSTALL = : PRE_INSTALL = : POST_INSTALL = : NORMAL_UNINSTALL = : PRE_UNINSTALL = : POST_UNINSTALL = : build_triplet = @build@ host_triplet = @host@ subdir = packages/xml/expat DIST_COMMON = $(srcdir)/Makefile.am $(srcdir)/Makefile.in ACLOCAL_M4 = $(top_srcdir)/aclocal.m4 am__aclocal_m4_deps = $(top_srcdir)/build-aux/bold.m4 \ $(top_srcdir)/build-aux/codeset.m4 \ $(top_srcdir)/build-aux/emacs-pkg.m4 \ $(top_srcdir)/build-aux/emacs-site-start.m4 \ $(top_srcdir)/build-aux/ext_goto.m4 \ $(top_srcdir)/build-aux/gawk.m4 $(top_srcdir)/build-aux/gcc.m4 \ $(top_srcdir)/build-aux/gl.m4 \ $(top_srcdir)/build-aux/glib-2.0.m4 \ $(top_srcdir)/build-aux/glut.m4 $(top_srcdir)/build-aux/gmp.m4 \ $(top_srcdir)/build-aux/gst-package.m4 \ $(top_srcdir)/build-aux/gtk-2.0.m4 \ $(top_srcdir)/build-aux/iconv.m4 \ $(top_srcdir)/build-aux/lib-ld.m4 \ $(top_srcdir)/build-aux/lib-link.m4 \ $(top_srcdir)/build-aux/lib-prefix.m4 \ $(top_srcdir)/build-aux/lib.m4 \ $(top_srcdir)/build-aux/libc-so-name.m4 \ $(top_srcdir)/build-aux/libtool.m4 \ $(top_srcdir)/build-aux/lightning.m4 \ $(top_srcdir)/build-aux/ln.m4 \ $(top_srcdir)/build-aux/localtime.m4 \ $(top_srcdir)/build-aux/lock.m4 \ $(top_srcdir)/build-aux/long-double.m4 \ $(top_srcdir)/build-aux/lrint.m4 \ $(top_srcdir)/build-aux/ltdl-gst.m4 \ $(top_srcdir)/build-aux/ltoptions.m4 \ $(top_srcdir)/build-aux/ltsugar.m4 \ $(top_srcdir)/build-aux/ltversion.m4 \ $(top_srcdir)/build-aux/lt~obsolete.m4 \ $(top_srcdir)/build-aux/modules.m4 \ $(top_srcdir)/build-aux/pkg.m4 $(top_srcdir)/build-aux/poll.m4 \ $(top_srcdir)/build-aux/readline.m4 \ $(top_srcdir)/build-aux/relocatable.m4 \ $(top_srcdir)/build-aux/setenv.m4 \ $(top_srcdir)/build-aux/snprintfv.m4 \ $(top_srcdir)/build-aux/sockets.m4 \ $(top_srcdir)/build-aux/sockpfaf.m4 \ $(top_srcdir)/build-aux/strtoul.m4 \ $(top_srcdir)/build-aux/sync-builtins.m4 \ $(top_srcdir)/build-aux/tcltk.m4 \ $(top_srcdir)/build-aux/version.m4 \ $(top_srcdir)/build-aux/vis-hidden.m4 \ $(top_srcdir)/build-aux/wine.m4 $(top_srcdir)/configure.ac am__configure_deps = $(am__aclocal_m4_deps) $(CONFIGURE_DEPENDENCIES) \ $(ACLOCAL_M4) mkinstalldirs = $(install_sh) -d CONFIG_HEADER = $(top_builddir)/config.h CONFIG_CLEAN_FILES = CONFIG_CLEAN_VPATH_FILES = am__vpath_adj_setup = srcdirstrip=`echo "$(srcdir)" | sed 's|.|.|g'`; am__vpath_adj = case $$p in \ $(srcdir)/*) f=`echo "$$p" | sed "s|^$$srcdirstrip/||"`;; \ *) f=$$p;; \ esac; am__strip_dir = f=`echo $$p | sed -e 's|^.*/||'`; am__install_max = 40 am__nobase_strip_setup = \ srcdirstrip=`echo "$(srcdir)" | sed 's/[].[^$$\\*|]/\\\\&/g'` am__nobase_strip = \ for p in $$list; do echo "$$p"; done | sed -e "s|$$srcdirstrip/||" am__nobase_list = $(am__nobase_strip_setup); \ for p in $$list; do echo "$$p $$p"; done | \ sed "s| $$srcdirstrip/| |;"' / .*\//!s/ .*/ ./; s,\( .*\)/[^/]*$$,\1,' | \ $(AWK) 'BEGIN { files["."] = "" } { files[$$2] = files[$$2] " " $$1; \ if (++n[$$2] == $(am__install_max)) \ { print $$2, files[$$2]; n[$$2] = 0; files[$$2] = "" } } \ END { for (dir in files) print dir, files[dir] }' am__base_list = \ sed '$$!N;$$!N;$$!N;$$!N;$$!N;$$!N;$$!N;s/\n/ /g' | \ sed '$$!N;$$!N;$$!N;$$!N;s/\n/ /g' am__uninstall_files_from_dir = { \ test -z "$$files" \ || { test ! -d "$$dir" && test ! -f "$$dir" && test ! -r "$$dir"; } \ || { echo " ( cd '$$dir' && rm -f" $$files ")"; \ $(am__cd) "$$dir" && rm -f $$files; }; \ } am__installdirs = "$(DESTDIR)$(moduleexecdir)" LTLIBRARIES = $(moduleexec_LTLIBRARIES) expat_la_DEPENDENCIES = am_expat_la_OBJECTS = expat.lo expat_la_OBJECTS = $(am_expat_la_OBJECTS) expat_la_LINK = $(LIBTOOL) --tag=CC $(AM_LIBTOOLFLAGS) $(LIBTOOLFLAGS) \ --mode=link $(CCLD) $(AM_CFLAGS) $(CFLAGS) $(expat_la_LDFLAGS) \ $(LDFLAGS) -o $@ DEFAULT_INCLUDES = -I.@am__isrc@ -I$(top_builddir) depcomp = $(SHELL) $(top_srcdir)/build-aux/depcomp am__depfiles_maybe = depfiles am__mv = mv -f COMPILE = $(CC) $(DEFS) $(DEFAULT_INCLUDES) $(INCLUDES) $(AM_CPPFLAGS) \ $(CPPFLAGS) $(AM_CFLAGS) $(CFLAGS) LTCOMPILE = $(LIBTOOL) --tag=CC $(AM_LIBTOOLFLAGS) $(LIBTOOLFLAGS) \ --mode=compile $(CC) $(DEFS) $(DEFAULT_INCLUDES) $(INCLUDES) \ $(AM_CPPFLAGS) $(CPPFLAGS) $(AM_CFLAGS) $(CFLAGS) CCLD = $(CC) LINK = $(LIBTOOL) --tag=CC $(AM_LIBTOOLFLAGS) $(LIBTOOLFLAGS) \ --mode=link $(CCLD) $(AM_CFLAGS) $(CFLAGS) $(AM_LDFLAGS) \ $(LDFLAGS) -o $@ SOURCES = $(expat_la_SOURCES) DIST_SOURCES = $(expat_la_SOURCES) am__can_run_installinfo = \ case $$AM_UPDATE_INFO_DIR in \ n|no|NO) false;; \ *) (install-info --version) >/dev/null 2>&1;; \ esac ETAGS = etags CTAGS = ctags DISTFILES = $(DIST_COMMON) $(DIST_SOURCES) $(TEXINFOS) $(EXTRA_DIST) ACLOCAL = @ACLOCAL@ ALLOCA = @ALLOCA@ ALL_PACKAGES = @ALL_PACKAGES@ AMTAR = @AMTAR@ AR = @AR@ AS = @AS@ ATK_CFLAGS = @ATK_CFLAGS@ ATK_LIBS = @ATK_LIBS@ AUTOCONF = @AUTOCONF@ AUTOHEADER = @AUTOHEADER@ AUTOM4TE = @AUTOM4TE@ AUTOMAKE = @AUTOMAKE@ AWK = @AWK@ BLOX_IMPLEMENTATION = @BLOX_IMPLEMENTATION@ BUILT_PACKAGES = @BUILT_PACKAGES@ CAIRO_CFLAGS = @CAIRO_CFLAGS@ CAIRO_LIBS = @CAIRO_LIBS@ CC = @CC@ CCDEPMODE = @CCDEPMODE@ CFLAGS = @CFLAGS@ CPP = @CPP@ CPPFLAGS = @CPPFLAGS@ CYGPATH_W = @CYGPATH_W@ DEFS = @DEFS@ DEPDIR = @DEPDIR@ DLLTOOL = @DLLTOOL@ DSYMUTIL = @DSYMUTIL@ DUMPBIN = @DUMPBIN@ ECHO_C = @ECHO_C@ ECHO_N = @ECHO_N@ ECHO_T = @ECHO_T@ EGREP = @EGREP@ EMACS = @EMACS@ EMACSLOADPATH = @EMACSLOADPATH@ EXEEXT = @EXEEXT@ FGREP = @FGREP@ GLIB_CFLAGS = @GLIB_CFLAGS@ GLIB_GENMARSHAL = @GLIB_GENMARSHAL@ GLIB_LIBS = @GLIB_LIBS@ GLIB_MKENUMS = @GLIB_MKENUMS@ GNUTLS_CFLAGS = @GNUTLS_CFLAGS@ GNUTLS_LIBS = @GNUTLS_LIBS@ GOBJECT_QUERY = @GOBJECT_QUERY@ GPERF = @GPERF@ GREP = @GREP@ GST_RUN = @GST_RUN@ GTHREAD_CFLAGS = @GTHREAD_CFLAGS@ GTHREAD_LIBS = @GTHREAD_LIBS@ GTK_CFLAGS = @GTK_CFLAGS@ GTK_LIBS = @GTK_LIBS@ ICON = @ICON@ INCFFI = @INCFFI@ INCLTDL = @INCLTDL@ INCSIGSEGV = @INCSIGSEGV@ INCSNPRINTFV = @INCSNPRINTFV@ INCTCLTK = @INCTCLTK@ INSTALL = @INSTALL@ INSTALL_DATA = @INSTALL_DATA@ INSTALL_INFO = @INSTALL_INFO@ INSTALL_PROGRAM = @INSTALL_PROGRAM@ INSTALL_SCRIPT = @INSTALL_SCRIPT@ INSTALL_STRIP_PROGRAM = @INSTALL_STRIP_PROGRAM@ LD = @LD@ LDFLAGS = @LDFLAGS@ LEX = @LEX@ LIBADD_DL = @LIBADD_DL@ LIBC_SO_DIR = @LIBC_SO_DIR@ LIBC_SO_NAME = @LIBC_SO_NAME@ LIBFFI = @LIBFFI@ LIBFFI_CFLAGS = @LIBFFI_CFLAGS@ LIBFFI_EXECUTABLE_LDFLAGS = @LIBFFI_EXECUTABLE_LDFLAGS@ LIBFFI_LIBS = @LIBFFI_LIBS@ LIBGLUT = @LIBGLUT@ LIBGMP = @LIBGMP@ LIBGST_CFLAGS = @LIBGST_CFLAGS@ LIBICONV = @LIBICONV@ LIBLTDL = @LIBLTDL@ LIBOBJS = @LIBOBJS@ LIBOPENGL = @LIBOPENGL@ LIBREADLINE = @LIBREADLINE@ LIBS = @LIBS@ LIBSIGSEGV = @LIBSIGSEGV@ LIBSNPRINTFV = @LIBSNPRINTFV@ LIBTCLTK = @LIBTCLTK@ LIBTHREAD = @LIBTHREAD@ LIBTOOL = @LIBTOOL@ LIPO = @LIPO@ LN = @LN@ LN_S = @LN_S@ LTALLOCA = @LTALLOCA@ LTLIBICONV = @LTLIBICONV@ LTLIBOBJS = @LTLIBOBJS@ MAINTAINER = @MAINTAINER@ MAKEINFO = @MAKEINFO@ MANIFEST_TOOL = @MANIFEST_TOOL@ MKDIR_P = @MKDIR_P@ MODULES = @MODULES@ NM = @NM@ NMEDIT = @NMEDIT@ OBJC = @OBJC@ OBJCDEPMODE = @OBJCDEPMODE@ OBJCFLAGS = @OBJCFLAGS@ OBJDUMP = @OBJDUMP@ OBJEXT = @OBJEXT@ OTOOL = @OTOOL@ OTOOL64 = @OTOOL64@ PACKAGE = @PACKAGE@ PACKAGE_BUGREPORT = @PACKAGE_BUGREPORT@ PACKAGE_DLOPEN_FLAGS = @PACKAGE_DLOPEN_FLAGS@ PACKAGE_NAME = @PACKAGE_NAME@ PACKAGE_STRING = @PACKAGE_STRING@ PACKAGE_TARNAME = @PACKAGE_TARNAME@ PACKAGE_URL = @PACKAGE_URL@ PACKAGE_VERSION = @PACKAGE_VERSION@ PANGO_CFLAGS = @PANGO_CFLAGS@ PANGO_LIBS = @PANGO_LIBS@ PATH_SEPARATOR = @PATH_SEPARATOR@ PKG_CONFIG = @PKG_CONFIG@ RANLIB = @RANLIB@ RELOCATABLE = @RELOCATABLE@ RELOC_CPPFLAGS = @RELOC_CPPFLAGS@ RELOC_LDFLAGS = @RELOC_LDFLAGS@ SDL_CFLAGS = @SDL_CFLAGS@ SDL_LIBS = @SDL_LIBS@ SED = @SED@ SET_MAKE = @SET_MAKE@ SHELL = @SHELL@ SOCKET_LIBS = @SOCKET_LIBS@ STRIP = @STRIP@ SYNC_CFLAGS = @SYNC_CFLAGS@ TCLSH = @TCLSH@ TIMEOUT = @TIMEOUT@ VERSION = @VERSION@ VERSION_INFO = @VERSION_INFO@ WINDRES = @WINDRES@ WINEWRAPPER = @WINEWRAPPER@ WINEWRAPPERDEP = @WINEWRAPPERDEP@ XMKMF = @XMKMF@ XZIP = @XZIP@ X_CFLAGS = @X_CFLAGS@ X_EXTRA_LIBS = @X_EXTRA_LIBS@ X_LIBS = @X_LIBS@ X_PRE_LIBS = @X_PRE_LIBS@ YACC = @YACC@ ZIP = @ZIP@ abs_builddir = @abs_builddir@ abs_srcdir = @abs_srcdir@ abs_top_builddir = @abs_top_builddir@ abs_top_srcdir = @abs_top_srcdir@ ac_ct_AR = @ac_ct_AR@ ac_ct_CC = @ac_ct_CC@ ac_ct_DUMPBIN = @ac_ct_DUMPBIN@ am__include = @am__include@ am__leading_dot = @am__leading_dot@ am__quote = @am__quote@ am__tar = @am__tar@ am__untar = @am__untar@ bindir = @bindir@ build = @build@ build_alias = @build_alias@ build_cpu = @build_cpu@ build_os = @build_os@ build_vendor = @build_vendor@ builddir = @builddir@ datadir = @datadir@ datarootdir = @datarootdir@ docdir = @docdir@ dvidir = @dvidir@ enable_mysql_tests = @enable_mysql_tests@ exec_prefix = @exec_prefix@ host = @host@ host_alias = @host_alias@ host_cpu = @host_cpu@ host_os = @host_os@ host_vendor = @host_vendor@ htmldir = @htmldir@ imagedir = @imagedir@ includedir = @includedir@ infodir = @infodir@ install_sh = @install_sh@ libdir = @libdir@ libexecdir = @libexecdir@ lispdir = @lispdir@ lispstartdir = @lispstartdir@ localedir = @localedir@ localstatedir = @localstatedir@ mandir = @mandir@ mkdir_p = @mkdir_p@ moduledir = @moduledir@ moduleexecdir = @moduleexecdir@ oldincludedir = @oldincludedir@ pdfdir = @pdfdir@ prefix = @prefix@ program_transform_name = @program_transform_name@ psdir = @psdir@ sbindir = @sbindir@ sharedstatedir = @sharedstatedir@ srcdir = @srcdir@ subdirs = @subdirs@ sysconfdir = @sysconfdir@ target_alias = @target_alias@ top_build_prefix = @top_build_prefix@ top_builddir = @top_builddir@ top_srcdir = @top_srcdir@ moduleexec_LTLIBRARIES = expat.la AM_CPPFLAGS = -I$(top_srcdir)/libgst -I$(top_srcdir)/lib-src gst_module_ldflags = -rpath $(moduleexecdir) -release $(VERSION) -module \ -no-undefined -export-symbols-regex gst_initModule expat_la_SOURCES = expat.c expat_la_LIBADD = -lexpat expat_la_LDFLAGS = $(gst_module_ldflags) all: all-am .SUFFIXES: .SUFFIXES: .c .lo .o .obj $(srcdir)/Makefile.in: $(srcdir)/Makefile.am $(am__configure_deps) @for dep in $?; do \ case '$(am__configure_deps)' in \ *$$dep*) \ ( cd $(top_builddir) && $(MAKE) $(AM_MAKEFLAGS) am--refresh ) \ && { if test -f $@; then exit 0; else break; fi; }; \ exit 1;; \ esac; \ done; \ echo ' cd $(top_srcdir) && $(AUTOMAKE) --gnu packages/xml/expat/Makefile'; \ $(am__cd) $(top_srcdir) && \ $(AUTOMAKE) --gnu packages/xml/expat/Makefile .PRECIOUS: Makefile Makefile: $(srcdir)/Makefile.in $(top_builddir)/config.status @case '$?' in \ *config.status*) \ cd $(top_builddir) && $(MAKE) $(AM_MAKEFLAGS) am--refresh;; \ *) \ echo ' cd $(top_builddir) && $(SHELL) ./config.status $(subdir)/$@ $(am__depfiles_maybe)'; \ cd $(top_builddir) && $(SHELL) ./config.status $(subdir)/$@ $(am__depfiles_maybe);; \ esac; $(top_builddir)/config.status: $(top_srcdir)/configure $(CONFIG_STATUS_DEPENDENCIES) cd $(top_builddir) && $(MAKE) $(AM_MAKEFLAGS) am--refresh $(top_srcdir)/configure: $(am__configure_deps) cd $(top_builddir) && $(MAKE) $(AM_MAKEFLAGS) am--refresh $(ACLOCAL_M4): $(am__aclocal_m4_deps) cd $(top_builddir) && $(MAKE) $(AM_MAKEFLAGS) am--refresh $(am__aclocal_m4_deps): install-moduleexecLTLIBRARIES: $(moduleexec_LTLIBRARIES) @$(NORMAL_INSTALL) @list='$(moduleexec_LTLIBRARIES)'; test -n "$(moduleexecdir)" || list=; \ list2=; for p in $$list; do \ if test -f $$p; then \ list2="$$list2 $$p"; \ else :; fi; \ done; \ test -z "$$list2" || { \ echo " $(MKDIR_P) '$(DESTDIR)$(moduleexecdir)'"; \ $(MKDIR_P) "$(DESTDIR)$(moduleexecdir)" || exit 1; \ echo " $(LIBTOOL) $(AM_LIBTOOLFLAGS) $(LIBTOOLFLAGS) --mode=install $(INSTALL) $(INSTALL_STRIP_FLAG) $$list2 '$(DESTDIR)$(moduleexecdir)'"; \ $(LIBTOOL) $(AM_LIBTOOLFLAGS) $(LIBTOOLFLAGS) --mode=install $(INSTALL) $(INSTALL_STRIP_FLAG) $$list2 "$(DESTDIR)$(moduleexecdir)"; \ } uninstall-moduleexecLTLIBRARIES: @$(NORMAL_UNINSTALL) @list='$(moduleexec_LTLIBRARIES)'; test -n "$(moduleexecdir)" || list=; \ for p in $$list; do \ $(am__strip_dir) \ echo " $(LIBTOOL) $(AM_LIBTOOLFLAGS) $(LIBTOOLFLAGS) --mode=uninstall rm -f '$(DESTDIR)$(moduleexecdir)/$$f'"; \ $(LIBTOOL) $(AM_LIBTOOLFLAGS) $(LIBTOOLFLAGS) --mode=uninstall rm -f "$(DESTDIR)$(moduleexecdir)/$$f"; \ done clean-moduleexecLTLIBRARIES: -test -z "$(moduleexec_LTLIBRARIES)" || rm -f $(moduleexec_LTLIBRARIES) @list='$(moduleexec_LTLIBRARIES)'; for p in $$list; do \ dir="`echo $$p | sed -e 's|/[^/]*$$||'`"; \ test "$$dir" != "$$p" || dir=.; \ echo "rm -f \"$${dir}/so_locations\""; \ rm -f "$${dir}/so_locations"; \ done expat.la: $(expat_la_OBJECTS) $(expat_la_DEPENDENCIES) $(EXTRA_expat_la_DEPENDENCIES) $(expat_la_LINK) -rpath $(moduleexecdir) $(expat_la_OBJECTS) $(expat_la_LIBADD) $(LIBS) mostlyclean-compile: -rm -f *.$(OBJEXT) distclean-compile: -rm -f *.tab.c @AMDEP_TRUE@@am__include@ @am__quote@./$(DEPDIR)/expat.Plo@am__quote@ .c.o: @am__fastdepCC_TRUE@ $(COMPILE) -MT $@ -MD -MP -MF $(DEPDIR)/$*.Tpo -c -o $@ $< @am__fastdepCC_TRUE@ $(am__mv) $(DEPDIR)/$*.Tpo $(DEPDIR)/$*.Po @AMDEP_TRUE@@am__fastdepCC_FALSE@ source='$<' object='$@' libtool=no @AMDEPBACKSLASH@ @AMDEP_TRUE@@am__fastdepCC_FALSE@ DEPDIR=$(DEPDIR) $(CCDEPMODE) $(depcomp) @AMDEPBACKSLASH@ @am__fastdepCC_FALSE@ $(COMPILE) -c $< .c.obj: @am__fastdepCC_TRUE@ $(COMPILE) -MT $@ -MD -MP -MF $(DEPDIR)/$*.Tpo -c -o $@ `$(CYGPATH_W) '$<'` @am__fastdepCC_TRUE@ $(am__mv) $(DEPDIR)/$*.Tpo $(DEPDIR)/$*.Po @AMDEP_TRUE@@am__fastdepCC_FALSE@ source='$<' object='$@' libtool=no @AMDEPBACKSLASH@ @AMDEP_TRUE@@am__fastdepCC_FALSE@ DEPDIR=$(DEPDIR) $(CCDEPMODE) $(depcomp) @AMDEPBACKSLASH@ @am__fastdepCC_FALSE@ $(COMPILE) -c `$(CYGPATH_W) '$<'` .c.lo: @am__fastdepCC_TRUE@ $(LTCOMPILE) -MT $@ -MD -MP -MF $(DEPDIR)/$*.Tpo -c -o $@ $< @am__fastdepCC_TRUE@ $(am__mv) $(DEPDIR)/$*.Tpo $(DEPDIR)/$*.Plo @AMDEP_TRUE@@am__fastdepCC_FALSE@ source='$<' object='$@' libtool=yes @AMDEPBACKSLASH@ @AMDEP_TRUE@@am__fastdepCC_FALSE@ DEPDIR=$(DEPDIR) $(CCDEPMODE) $(depcomp) @AMDEPBACKSLASH@ @am__fastdepCC_FALSE@ $(LTCOMPILE) -c -o $@ $< mostlyclean-libtool: -rm -f *.lo clean-libtool: -rm -rf .libs _libs ID: $(HEADERS) $(SOURCES) $(LISP) $(TAGS_FILES) list='$(SOURCES) $(HEADERS) $(LISP) $(TAGS_FILES)'; \ unique=`for i in $$list; do \ if test -f "$$i"; then echo $$i; else echo $(srcdir)/$$i; fi; \ done | \ $(AWK) '{ files[$$0] = 1; nonempty = 1; } \ END { if (nonempty) { for (i in files) print i; }; }'`; \ mkid -fID $$unique tags: TAGS TAGS: $(HEADERS) $(SOURCES) $(TAGS_DEPENDENCIES) \ $(TAGS_FILES) $(LISP) set x; \ here=`pwd`; \ list='$(SOURCES) $(HEADERS) $(LISP) $(TAGS_FILES)'; \ unique=`for i in $$list; do \ if test -f "$$i"; then echo $$i; else echo $(srcdir)/$$i; fi; \ done | \ $(AWK) '{ files[$$0] = 1; nonempty = 1; } \ END { if (nonempty) { for (i in files) print i; }; }'`; \ shift; \ if test -z "$(ETAGS_ARGS)$$*$$unique"; then :; else \ test -n "$$unique" || unique=$$empty_fix; \ if test $$# -gt 0; then \ $(ETAGS) $(ETAGSFLAGS) $(AM_ETAGSFLAGS) $(ETAGS_ARGS) \ "$$@" $$unique; \ else \ $(ETAGS) $(ETAGSFLAGS) $(AM_ETAGSFLAGS) $(ETAGS_ARGS) \ $$unique; \ fi; \ fi ctags: CTAGS CTAGS: $(HEADERS) $(SOURCES) $(TAGS_DEPENDENCIES) \ $(TAGS_FILES) $(LISP) list='$(SOURCES) $(HEADERS) $(LISP) $(TAGS_FILES)'; \ unique=`for i in $$list; do \ if test -f "$$i"; then echo $$i; else echo $(srcdir)/$$i; fi; \ done | \ $(AWK) '{ files[$$0] = 1; nonempty = 1; } \ END { if (nonempty) { for (i in files) print i; }; }'`; \ test -z "$(CTAGS_ARGS)$$unique" \ || $(CTAGS) $(CTAGSFLAGS) $(AM_CTAGSFLAGS) $(CTAGS_ARGS) \ $$unique GTAGS: here=`$(am__cd) $(top_builddir) && pwd` \ && $(am__cd) $(top_srcdir) \ && gtags -i $(GTAGS_ARGS) "$$here" distclean-tags: -rm -f TAGS ID GTAGS GRTAGS GSYMS GPATH tags distdir: $(DISTFILES) @srcdirstrip=`echo "$(srcdir)" | sed 's/[].[^$$\\*]/\\\\&/g'`; \ topsrcdirstrip=`echo "$(top_srcdir)" | sed 's/[].[^$$\\*]/\\\\&/g'`; \ list='$(DISTFILES)'; \ dist_files=`for file in $$list; do echo $$file; done | \ sed -e "s|^$$srcdirstrip/||;t" \ -e "s|^$$topsrcdirstrip/|$(top_builddir)/|;t"`; \ case $$dist_files in \ */*) $(MKDIR_P) `echo "$$dist_files" | \ sed '/\//!d;s|^|$(distdir)/|;s,/[^/]*$$,,' | \ sort -u` ;; \ esac; \ for file in $$dist_files; do \ if test -f $$file || test -d $$file; then d=.; else d=$(srcdir); fi; \ if test -d $$d/$$file; then \ dir=`echo "/$$file" | sed -e 's,/[^/]*$$,,'`; \ if test -d "$(distdir)/$$file"; then \ find "$(distdir)/$$file" -type d ! -perm -700 -exec chmod u+rwx {} \;; \ fi; \ if test -d $(srcdir)/$$file && test $$d != $(srcdir); then \ cp -fpR $(srcdir)/$$file "$(distdir)$$dir" || exit 1; \ find "$(distdir)/$$file" -type d ! -perm -700 -exec chmod u+rwx {} \;; \ fi; \ cp -fpR $$d/$$file "$(distdir)$$dir" || exit 1; \ else \ test -f "$(distdir)/$$file" \ || cp -p $$d/$$file "$(distdir)/$$file" \ || exit 1; \ fi; \ done check-am: all-am check: check-am all-am: Makefile $(LTLIBRARIES) installdirs: for dir in "$(DESTDIR)$(moduleexecdir)"; do \ test -z "$$dir" || $(MKDIR_P) "$$dir"; \ done install: install-am install-exec: install-exec-am install-data: install-data-am uninstall: uninstall-am install-am: all-am @$(MAKE) $(AM_MAKEFLAGS) install-exec-am install-data-am installcheck: installcheck-am install-strip: if test -z '$(STRIP)'; then \ $(MAKE) $(AM_MAKEFLAGS) INSTALL_PROGRAM="$(INSTALL_STRIP_PROGRAM)" \ install_sh_PROGRAM="$(INSTALL_STRIP_PROGRAM)" INSTALL_STRIP_FLAG=-s \ install; \ else \ $(MAKE) $(AM_MAKEFLAGS) INSTALL_PROGRAM="$(INSTALL_STRIP_PROGRAM)" \ install_sh_PROGRAM="$(INSTALL_STRIP_PROGRAM)" INSTALL_STRIP_FLAG=-s \ "INSTALL_PROGRAM_ENV=STRIPPROG='$(STRIP)'" install; \ fi mostlyclean-generic: clean-generic: distclean-generic: -test -z "$(CONFIG_CLEAN_FILES)" || rm -f $(CONFIG_CLEAN_FILES) -test . = "$(srcdir)" || test -z "$(CONFIG_CLEAN_VPATH_FILES)" || rm -f $(CONFIG_CLEAN_VPATH_FILES) maintainer-clean-generic: @echo "This command is intended for maintainers to use" @echo "it deletes files that may require special tools to rebuild." clean: clean-am clean-am: clean-generic clean-libtool clean-moduleexecLTLIBRARIES \ mostlyclean-am distclean: distclean-am -rm -rf ./$(DEPDIR) -rm -f Makefile distclean-am: clean-am distclean-compile distclean-generic \ distclean-tags dvi: dvi-am dvi-am: html: html-am html-am: info: info-am info-am: install-data-am: install-dvi: install-dvi-am install-dvi-am: install-exec-am: install-moduleexecLTLIBRARIES install-html: install-html-am install-html-am: install-info: install-info-am install-info-am: install-man: install-pdf: install-pdf-am install-pdf-am: install-ps: install-ps-am install-ps-am: installcheck-am: maintainer-clean: maintainer-clean-am -rm -rf ./$(DEPDIR) -rm -f Makefile maintainer-clean-am: distclean-am maintainer-clean-generic mostlyclean: mostlyclean-am mostlyclean-am: mostlyclean-compile mostlyclean-generic \ mostlyclean-libtool pdf: pdf-am pdf-am: ps: ps-am ps-am: uninstall-am: uninstall-moduleexecLTLIBRARIES .MAKE: install-am install-strip .PHONY: CTAGS GTAGS all all-am check check-am clean clean-generic \ clean-libtool clean-moduleexecLTLIBRARIES ctags distclean \ distclean-compile distclean-generic distclean-libtool \ distclean-tags distdir dvi dvi-am html html-am info info-am \ install install-am install-data install-data-am install-dvi \ install-dvi-am install-exec install-exec-am install-html \ install-html-am install-info install-info-am install-man \ install-moduleexecLTLIBRARIES install-pdf install-pdf-am \ install-ps install-ps-am install-strip installcheck \ installcheck-am installdirs maintainer-clean \ maintainer-clean-generic mostlyclean mostlyclean-compile \ mostlyclean-generic mostlyclean-libtool pdf pdf-am ps ps-am \ tags uninstall uninstall-am uninstall-moduleexecLTLIBRARIES # Tell versions [3.59,3.63) of GNU make to not export all variables. # Otherwise a system limit (for SysV at least) may be exceeded. .NOEXPORT: smalltalk-3.2.5/packages/xml/expat/stamp-classes0000644000175000017500000000000012123404352016611 00000000000000smalltalk-3.2.5/packages/xml/expat/ExpatParser.st0000644000175000017500000000545412123404352016737 00000000000000"====================================================================== | | Push adaptor for Expat XML Parser | | ======================================================================" "====================================================================== | | Copyright 2009 Free Software Foundation, Inc. | Written by Paolo Bonzini. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" SAXParser subclass: ExpatXMLParser [ | pullParser | ExpatXMLParser class >> pullParserOn: dataSource [ "Use the expat pull parser directly, without going through pull on push on pull... which we do for the test suite! :-)" ^ExpatXMLPullParser on: dataSource ] on: dataSource [ "The dataSource may be a URI, a Filename (or a String which will be treated as a Filename), or an InputSource." super on: dataSource. "As the underlying parser we use the event-based Expat bindings. We need to get all the events in order to pass them to the user's own driver." pullParser := ExpatXMLPullParser on: dataSource. pullParser needComments: true. pullParser needDTDEvents: true. pullParser needCdataDelimiters: true. pullParser needPrefixMappingEvents: true. ] scanDocument [ "Serialize the events from the pull parser to the SAX driver." [pullParser do: [ :event | event serializeTo: sax]] on: XMLResolveEntityNotification do: [ :e | e resume: (sax resolveEntity: e publicID systemID: e systemID) ]; on: MalformedSignal, BadCharacterSignal do: [ :e | sax fatalError: e ]; on: InvalidSignal do: [ :e | sax nonFatalError: e ]; on: WarningSignal do: [ :e | sax warning: e ] ] ] Eval [ SAXParser defaultParserClass isNil ifTrue: [SAXParser defaultParserClass: ExpatXMLParser]. ] smalltalk-3.2.5/packages/xml/expat/package.xml0000644000175000017500000000066612123404352016246 00000000000000 XML-Expat XML XML-Parser XML-ParserTests XML.ExpatXMLPullParserTest XML.ExpatXMLParserTest ExpatTests.st XML-SAXParser XML-PullParser expat ExpatPullParser.st ExpatParser.st smalltalk-3.2.5/packages/xml/builder/0000755000175000017500000000000012130456022014505 500000000000000smalltalk-3.2.5/packages/xml/builder/Makefile.frag0000644000175000017500000000033512123404352017005 00000000000000XML-XMLNodeBuilder_FILES = \ packages/xml/builder/NodeBuilder.st $(XML-XMLNodeBuilder_FILES): $(srcdir)/packages/xml/builder/stamp-classes: $(XML-XMLNodeBuilder_FILES) touch $(srcdir)/packages/xml/builder/stamp-classes smalltalk-3.2.5/packages/xml/builder/NodeBuilder.st0000644000175000017500000002416212123404352017177 00000000000000"====================================================================== | | VisualWorks XML Framework - NodeBuilder interface (obsolete) | | ======================================================================" "====================================================================== | | Copyright (c) 2000, 2002 Cincom, Inc. | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" Object subclass: XMLNodeBuilder [ | tagStack tags | Stack showing the nesting of XML elements within the document at the current stage of parsing. tags Currently not used. A map to make sure that within a document, tag identifiers are unique instances in order to save space.'> XMLNodeBuilder class >> new [ ^super new initialize ] initialize [ tagStack := OrderedCollection new. tags := Dictionary new ] currentTag [ ^tagStack last tag ] popTag [ tagStack removeLast ] pushTag: tag [ tagStack addLast: (ElementContext new tag: tag) ] attribute: name value: value [ ^Attribute name: name value: value ] comment: aText [ ^Comment new text: aText ] makeText: text [ ^Text text: text ] notation: name value: val [ ^Notation new name: name identifiers: val ] pi: nm text: text [ ^PI new name: nm text: text ] tag: tag attributes: attributes elements: elements position: p stream: stream [ self subclassResponsibility ] ] XMLNodeBuilder subclass: NodeBuilder [ >tag:attributes:elements:position:stream:, since most of the other methods in XMLNodeBuilder''s "building" protocol are very secondary in importance compared to this method. But consider subclassing DOM_SAXDriver rather than this class, and using the SAX protocol to do your parsing.'> tag: tag attributes: attributes elements: elements position: p stream: stream [ ^Element tag: tag attributes: attributes elements: elements ] ] SAXDriver subclass: SAXBuilderDriver [ | builder document elementStack newNamespaces | The client''s NodeBuilder, which creates XML Nodes. document The Document which models the entire XML document. elementStack A stack of proxies for the various elements that are in scope at the current stage of parsing. newNamespaces maps qualifiers to namespaces for the next element'> characters: aString [ | text | text := builder makeText: aString. text isDiscarded ifFalse: [elementStack last nodes add: text] ] endDocument [ ] endDocumentFragment [ ^self endDocument ] endElement: namespaceURI localName: localName qName: name [ "indicates the end of an element. See startElement" | elm element | elm := elementStack last. element := builder tag: elm tag attributes: elm attributes elements: (elm nodes isEmpty ifTrue: [nil] ifFalse: [elm nodes asArray]) position: elm startPosition stream: elm stream. element namespaces: elm namespaces. elementStack removeLast. elementStack isEmpty ifTrue: [document addNode: element. document dtd declaredRoot: element tag asString] ifFalse: [element isDiscarded ifFalse: [elementStack last nodes add: element]]. (element isDiscarded not and: [elm id notNil]) ifTrue: [document atID: elm id put: element]. builder popTag ] ignorableWhitespace: aString [ | text | text := builder makeText: aString. text isDiscarded ifFalse: [elementStack last nodes add: text] ] processingInstruction: targetString data: dataString [ | pi | document == nil ifTrue: [self startDocument]. pi := builder pi: targetString text: dataString. elementStack isEmpty ifTrue: [document addNode: pi] ifFalse: [elementStack last nodes add: pi] ] startDocument [ document := Document new. document dtd: DocumentType new. elementStack := OrderedCollection new ] startDocumentFragment [ document := DocumentFragment new. document dtd: DocumentType new. elementStack := OrderedCollection new ] startElement: namespaceURI localName: localName qName: name attributes: attributes [ | nm | document == nil ifTrue: [self startDocument]. nm := NodeTag new qualifier: ((name includes: $:) ifTrue: [name copyUpTo: $:] ifFalse: ['']) ns: namespaceURI type: localName. elementStack addLast: (SAXElementContext new tag: nm). (elementStack last) attributes: (attributes collect: [:att | att copy]); nodes: OrderedCollection new; namespaces: newNamespaces. newNamespaces := nil. builder pushTag: nm ] startPrefixMapping: prefix uri: uri [ newNamespaces == nil ifTrue: [newNamespaces := Dictionary new]. newNamespaces at: prefix put: uri ] comment: data from: start to: stop [ | comment | document == nil ifTrue: [self startDocument]. comment := builder comment: (data copyFrom: start to: stop). comment isDiscarded ifFalse: [elementStack isEmpty ifTrue: [document addNode: comment] ifFalse: [elementStack last nodes add: comment]] ] idOfElement: elementID [ "Notify the client what was the ID of the latest startElement" elementStack last id: elementID ] sourcePosition: position inStream: streamWrapper [ "Non-standard API to ease transition from builders to SAX." (elementStack last) startPosition: position; stream: streamWrapper ] builder: aNodeBuilder [ builder := aNodeBuilder ] document [ ^document ] notationDecl: name publicID: publicID systemID: systemID [ | notation | notation := builder notation: name value: (Array with: publicID with: systemID). document dtd notationAt: name put: notation from: self ] ] SAXParser extend [ builder: anXMLNodeBuilder [ self saxDriver: (SAXBuilderDriver new builder: anXMLNodeBuilder) ] ] ElementContext subclass: SAXElementContext [ | attributes nodes stream startPosition id | nodes stream startPosition id '> attributes [ ^attributes ] attributes: aCollection [ attributes := aCollection ] id [ ^id ] id: anID [ id := anID ] namespaces: aDictionary [ namespaces := aDictionary ] nodes [ ^nodes ] nodes: aCollection [ nodes := aCollection ] startPosition [ ^startPosition ] startPosition: anInteger [ ^startPosition := anInteger ] stream [ ^stream ] stream: aStream [ ^stream := aStream ] ] smalltalk-3.2.5/packages/xml/builder/stamp-classes0000644000175000017500000000000012123404352017116 00000000000000smalltalk-3.2.5/packages/xml/builder/package.xml0000644000175000017500000000026412123404352016545 00000000000000 XML-XMLNodeBuilder XML XML-DOM XML-SAXParser NodeBuilder.st smalltalk-3.2.5/packages/stinst/0000755000175000017500000000000012130456017013607 500000000000000smalltalk-3.2.5/packages/stinst/parser/0000755000175000017500000000000012130456017015103 500000000000000smalltalk-3.2.5/packages/stinst/parser/Makefile.frag0000644000175000017500000000023112130344111017364 00000000000000Parser_FILES = \ $(Parser_FILES): $(srcdir)/packages/stinst/parser/stamp-classes: $(Parser_FILES) touch $(srcdir)/packages/stinst/parser/stamp-classes smalltalk-3.2.5/packages/stinst/parser/GSTParser.st0000644000175000017500000003243112130343734017211 00000000000000"====================================================================== | | GNU Smalltalk syntax parser | | ======================================================================" "====================================================================== | | Copyright 2007, 2008, 2009 Free Software Foundation, Inc. | Written by Daniele Sciascia. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" STInST.STFileInParser subclass: GSTFileInParser [ | taggee class currentDeclaration | parseStatements [ | returnPosition statements node | "Skip temporaries." (currentToken isBinary and: [currentToken value == #|]) ifTrue: [ self step. self parseArgs. self step ]. (currentToken isBinary and: [currentToken value == #||]) ifTrue: [ self step ]. (currentToken isSpecial and: [currentToken value == $!]) ifTrue: [ ^RBSequenceNode statements: #() ]. node := (currentToken isSpecial and: [currentToken value == $^]) ifTrue: [returnPosition := currentToken start. self step. RBReturnNode return: returnPosition value: self parseAssignment] ifFalse: [self parseAssignment]. self addCommentsTo: node. ^RBSequenceNode statements: { node } ] parseDoits [ "Parses the stuff to be executed until a closed bracket." | node | [self atEnd ifTrue: [^false]. (currentToken isSpecial and: [currentToken value == $]]) ifTrue: [^false]. node := self parseDoit. scanner stripSeparators. self evaluate: node] whileFalse: [(currentToken isSpecial and: [currentToken value == $!]) ifTrue: [self step]]. ^true ] parseDoit [ | node | (taggee notNil and: [currentToken value = #<]) ifTrue: [self parseClassTag. ^nil]. node := super parseDoit. (currentToken isSpecial and: [ self skipToken: $[ ]) ifTrue: [self parseDeclaration: node statements first. ^nil]. currentToken isSpecial ifTrue: [ self skipToken: $. ]. ^node ] parseDeclaration: node [ | decl | currentDeclaration := node parent. decl := node. decl isReturn ifTrue: [ decl := decl value ]. decl isMessage ifTrue: [ (decl selectorParts first value = 'subclass:') ifTrue: [self parseClass: decl. ^self]. (decl selectorParts first value = 'extend') ifTrue: [self parseClassExtension: decl. ^self]. ((decl receiver name = 'Namespace') and: [decl selectorParts first value = 'current:' ]) ifTrue: [self parseNamespace: decl. ^self]]. decl isVariable ifTrue: [(decl name = 'Eval') ifTrue: [self parseEval. ^self]]. self parserError: 'expected Eval, Namespace or class definition' ] parseEval [ | stmts | stmts := self parseStatements: false. self skipExpectedToken: $]. self evaluate: stmts. ] parseNamespace: node [ | namespace fullNamespace newNamespace | namespace := RBVariableNode named: self driver currentNamespace name asString. fullNamespace := RBVariableNode named: (self driver currentNamespace nameIn: Smalltalk). newNamespace := node arguments first name asSymbol. (self driver currentNamespace includesKey: newNamespace) ifFalse: [ self evaluateMessageOn: namespace selector: #addSubspace: argument: node arguments first name asSymbol ]. self evaluateStatement: node. taggee := RBVariableNode named: (self driver currentNamespace nameIn: Smalltalk). self parseDoits. self skipExpectedToken: $]. "restore previous namespace" taggee := fullNamespace. node parent: nil. node arguments: { fullNamespace }. self evaluateStatement: node ] parseClassExtension: node [ class := node receiver. self parseClassBody: true. class := nil ] parseClass: node [ self evaluateMessageOn: (node receiver) selector: #subclass: argument: (node arguments first name asSymbol). class := node arguments first. self parseClassBody: false. class := nil. ] parseClassBody: extend [ | addInstVars oldTaggee | oldTaggee := taggee. taggee := class. addInstVars := extend. [ self skipToken: $] ] whileFalse: [ addInstVars := self parseClassBodyElement: addInstVars withinExtend: extend ]. taggee := oldTaggee. ] parseClassBodyElement: addInstVars withinExtend: extend [ | node classNode | "drop comments" scanner getComments. "look for class tag" (currentToken value = #< and: [self nextToken isKeyword]) ifTrue: [self parseClassTag. ^addInstVars]. "look for class variable" (currentToken isIdentifier and: [self nextToken isAssignment]) ifTrue: [self parseClassVariable. ^addInstVars]. "class side" ((currentToken isIdentifier and: [self nextToken isIdentifier]) and: [self nextToken value = 'class']) ifTrue: [classNode := RBVariableNode identifierToken: currentToken. self step. (classNode = class) ifTrue: ["look for class method" (self nextToken value = #>>) ifTrue: [self step. self step. self parseMethodSourceOn: (self makeClassOf: classNode). ^addInstVars ]. "look for metaclass" (self nextToken value = $[) ifTrue: [self parseMetaclass: extend. ^addInstVars ]. self parserError: 'invalid class body element']. "look for overriding class method" self step. (currentToken value = #>>) ifTrue: ["TODO: check that classNode is a superclass of the current class" self step. self parseMethodSourceOn: (self makeClassOf: classNode). ^addInstVars]. self parserError: 'invalid class body element' ]. "look for overriding method" (currentToken isIdentifier and: [self nextToken value = #>>]) ifTrue: ["check that classNode is a superclass of the current class!!!" classNode := RBVariableNode identifierToken: currentToken. self step. self step. self parseMethodSourceOn: classNode. ^addInstVars]. node := self parseMessagePattern. "look for method" (self skipToken: $[) ifTrue: [self parseMethodSource: node. ^addInstVars]. "look for instance variables" (node selectorParts first value = #|) ifTrue: [self parseInstanceVariables: node add: addInstVars. ^true]. self parserError: 'invalid class body element' ] parseClassTag [ | selectors arguments stmt | self skipExpectedToken: #<. (currentToken isKeyword) ifFalse: [self parserError: 'expected keyword']. selectors := OrderedCollection new. arguments := OrderedCollection new. "Consume all keywords and literals of the pragma" [currentToken isKeyword] whileTrue: [ selectors add: currentToken. self step. arguments add: self parsePrimitiveObject. ]. self skipExpectedToken: #>. stmt := RBMessageNode receiver: taggee selectorParts: selectors arguments: arguments. self evaluateStatement: stmt. ] parseClassVariable [ | node stmt name | node := self parseAssignment. node isAssignment ifFalse: [self parserError: 'expected assignment']. (self skipToken: $.) ifFalse: [ (currentToken value = $]) ifFalse: [ self parserError: 'expected . or ]']]. name := RBLiteralNode value: (node variable name asSymbol). node := self makeSequenceNode: node value. node := RBBlockNode body: node. stmt := RBMessageNode receiver: class selector: #addClassVarName:value: arguments: { name . node }. self evaluateStatement: stmt. ] parseMetaclass: extend [ | tmpClass | self step. self step. tmpClass := class. class := self makeClassOf: class. self parseClassBody: extend. class := tmpClass ] parseMethodSource: patternNode [ self parseMethodSource: patternNode on: class ] parseMethodSourceOn: classNode [ | patternNode | "Drop comments before the message pattern" patternNode := self parseMessagePattern. self skipExpectedToken: $[. self parseMethodSource: patternNode on: classNode. ] parseMethodSource: patternNode on: classNode [ | methodNode start stop | start := patternNode selectorParts first start - 1. methodNode := self parseMethodInto: patternNode. stop := currentToken start - 1. self skipExpectedToken: $]. methodNode := self addSourceFrom: start to: stop to: methodNode. self evaluateMessageOn: classNode selector: #methodsFor: argument: nil. self compile: methodNode. self endMethodList. ] parseInstanceVariables: node add: addThem [ | vars | vars := addThem ifTrue: [ (self resolveClass: class) instVarNames fold: [ :a :b | a, ' ', b ] ] ifFalse: [ '' ]. vars := vars, ' ', (node arguments at: 1) name. [currentToken isIdentifier] whileTrue: [vars := vars , ' ' , currentToken value. self step ]. self skipExpectedToken: #|. self evaluateMessageOn: class selector: #instanceVariableNames: argument: vars. ] evaluateMessageOn: rec selector: sel argument: arg [ | stmt | stmt := RBMessageNode receiver: rec selector: sel arguments: { RBLiteralNode value: arg }. self evaluateStatement: stmt. ] evaluateStatement: node [ ^self evaluate: (self makeSequenceNode: node) ] evaluate: seq [ | emptySeq | (currentDeclaration notNil and: [ currentDeclaration comments notEmpty ]) ifTrue: [ seq parent isNil ifTrue: [ seq comments: currentDeclaration comments. seq parent: currentDeclaration parent ] ifFalse: [ emptySeq := self makeSequenceNode. emptySeq comments: currentDeclaration comments. emptySeq parent: currentDeclaration parent. super evaluate: emptySeq ] ]. currentDeclaration := nil. ^super evaluate: seq ] makeSequenceNode [ | seq | seq := RBSequenceNode leftBar: nil temporaries: #() rightBar: nil. seq periods: #(). seq statements: #(). ^seq ] makeSequenceNode: stmt [ ^self makeSequenceNode statements: { stmt }. ] makeClassOf: node [ ^RBMessageNode receiver: node selector: #class arguments: #() ] skipToken: tokenValue [ (currentToken value = tokenValue) ifTrue: [self step. ^true] ifFalse: [^false] ] skipExpectedToken: tokenValue [ (self skipToken: tokenValue) ifFalse: [self parserError: ('expected ' , tokenValue asSymbol)] ] ] smalltalk-3.2.5/packages/stinst/parser/OrderedSet.st0000644000175000017500000002411112123404352017427 00000000000000"====================================================================== | | OrderedSet Method Definitions | | ======================================================================" "====================================================================== | | Copyright (C) 2007 Free Software Foundation, Inc. | Written by Stephen Compall. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" OrderedCollection subclass: OrderedSet [ | unorderedSet | OrderedSet class >> identityNew: anInteger [ "Answer an OrderedSet of size anInteger which uses #== to compare its elements." ^self on: (IdentitySet new: anInteger) ] OrderedSet class >> new: anInteger [ "Answer an OrderedSet of size anInteger." ^self on: (Set new: anInteger) ] OrderedSet class >> on: anEmptySet [ "Answer an OrderedSet that uses anEmptySet as an unordered set to maintain my set-property." anEmptySet isEmpty ifFalse: [self error: 'expected empty collection']. ^(super new: anEmptySet basicSize) unorderedSet: anEmptySet; yourself ] at: anIndex put: anObject [ "Store anObject at the anIndex-th item of the receiver, answer anObject. Signal an error if anObject is already present as another element of the receiver." | oldElement | oldElement := self at: anIndex. "Though it is somewhat inefficient to remove then possibly readd the old element, the case is rare enough that the precision of unorderedSet-based comparison is worth it." unorderedSet remove: oldElement. (unorderedSet includes: anObject) ifTrue: [unorderedSet add: oldElement. ^self error: 'anObject is already present']. unorderedSet add: anObject. ^super at: anIndex put: anObject ] postCopy [ super postCopy. unorderedSet := unorderedSet copy ] copyEmpty: newSize [ "Answer an empty copy of the receiver." ^self species on: (unorderedSet copyEmpty: newSize) ] includes: anObject [ "Answer whether anObject is one of my elements, according to my 'unordered set'." ^unorderedSet includes: anObject ] occurrencesOf: anObject [ "Answer how many of anObject I contain. As I am a set, this is always 0 or 1." ^(self includes: anObject) ifTrue: [1] ifFalse: [0] ] indexOf: anElement startingAt: anIndex ifAbsent: exceptionBlock [ "Answer the first index > anIndex which contains anElement. Invoke exceptionBlock and answer its result if no item is found." ^((self includes: anElement) or: [(anIndex between: 1 and: self size + 1) not]) ifTrue: ["if anIndex isn't valid, super method will catch it. Also, super method may not find the element, which is fine" super indexOf: anElement startingAt: anIndex ifAbsent: exceptionBlock] ifFalse: [exceptionBlock value] ] add: anObject [ "Add anObject in the receiver if it is not already present, and answer it." (unorderedSet includes: anObject) ifFalse: [super add: anObject. unorderedSet add: anObject]. ^anObject ] add: newObject afterIndex: i [ "Add newObject in the receiver just after the i-th, unless it is already present, and answer it. Fail if i < 0 or i > self size" (unorderedSet includes: newObject) ifFalse: [super add: newObject afterIndex: i. unorderedSet add: newObject]. ^newObject ] addAll: aCollection [ "Add every item of aCollection to the receiver that is not already present, and answer it." ^self addAllLast: aCollection ] addAll: newCollection afterIndex: i [ "Add every item of newCollection to the receiver just after the i-th, answer it. Fail if i < 0 or i > self size" | index | (i between: 0 and: self size) ifFalse: [^SystemExceptions.IndexOutOfRange signalOn: self withIndex: i]. index := i + firstIndex. self makeRoomLastFor: newCollection size. lastIndex to: index by: -1 do: [:i | self basicAt: i + newCollection size put: (self basicAt: i)]. lastIndex := lastIndex + newCollection size. newCollection do: [:each | (unorderedSet includes: each) ifFalse: [unorderedSet add: each. self basicAt: index put: each. index := 1 + index]]. self closeGapFrom: index - firstIndex + 1 to: i + newCollection size. ^newCollection ] addAllFirst: aCollection [ "Add every item of newCollection to the receiver right at the start of the receiver. Answer aCollection" | index | self makeRoomFirstFor: aCollection size. firstIndex := index := firstIndex - aCollection size. aCollection do: [:elt | (unorderedSet includes: elt) ifFalse: [self basicAt: index put: elt. unorderedSet add: elt. index := index + 1]]. self closeGapFrom: index - firstIndex + 1 to: aCollection size. ^aCollection ] addAllLast: aCollection [ "Add every item of newCollection to the receiver right at the end of the receiver. Answer aCollection" "might be too big, but probably not too much" | index newElements newElementCount | self makeRoomLastFor: aCollection size. aCollection do: [:element | (unorderedSet includes: element) ifFalse: [lastIndex := lastIndex + 1. self basicAt: lastIndex put: element. unorderedSet add: element]]. ^aCollection ] addFirst: newObject [ "Add newObject to the receiver right at the start of the receiver, unless it is already present as an element. Answer newObject" (unorderedSet includes: newObject) ifFalse: [unorderedSet add: newObject. super addFirst: newObject]. ^newObject ] addLast: newObject [ "Add newObject to the receiver right at the end of the receiver, unless it is already present as an element. Answer newObject" (unorderedSet includes: newObject) ifFalse: [unorderedSet add: newObject. super addLast: newObject]. ^newObject ] removeFirst [ "Remove an object from the start of the receiver. Fail if the receiver is empty" ^unorderedSet remove: super removeFirst ] removeLast [ "Remove an object from the end of the receiver. Fail if the receiver is empty." ^unorderedSet remove: super removeLast ] removeAtIndex: anIndex [ "Remove the object at index anIndex from the receiver. Fail if the index is out of bounds." ^unorderedSet remove: (super removeAtIndex: anIndex) ] closeGapFrom: gapStart to: gapEnd [ "Remove all elements between gapStart and gapEnd, inclusive, without modifying the unordered set. I simply ignore this message if gapStart or gapEnd is bad." "these vars are almost always exactly the current basic gap" | realStart realEnd | realStart := firstIndex + gapStart - 1. realEnd := firstIndex + gapEnd - 1. "trivial cases" (gapStart <= gapEnd and: [(realStart between: firstIndex and: lastIndex) and: [realEnd between: firstIndex and: lastIndex]]) ifFalse: [^self]. realEnd = lastIndex ifTrue: [lastIndex := realStart - 1. ^self]. realStart = firstIndex ifTrue: [firstIndex := realEnd + 1. ^self]. "shift from before?" gapStart - 1 < (lastIndex - realEnd) ifTrue: [ [self basicAt: realEnd put: (self basicAt: (realStart := realStart - 1)). realEnd := realEnd - 1. realStart = firstIndex] whileFalse. firstIndex := realEnd + 1] ifFalse: ["shift from after" [self basicAt: realStart put: (self basicAt: (realEnd := realEnd + 1)). realStart := realStart + 1. realEnd = lastIndex] whileFalse. lastIndex := realStart - 1]. "help the gc" realStart to: realEnd do: [:i | self basicAt: i put: nil] ] growBy: delta shiftBy: shiftCount [ "This may be private to OrderedCollection, but its inlining of new-instance filling breaks me." | uSet | uSet := unorderedSet. super growBy: delta shiftBy: shiftCount. "effectively copy after #become: invocation" unorderedSet := uSet ] unorderedSet: aSet [ unorderedSet := aSet ] ] smalltalk-3.2.5/packages/stinst/parser/Extensions.st0000644000175000017500000001047412123404352017535 00000000000000"====================================================================== | | Class extensions | | ======================================================================" "====================================================================== | | Copyright 2009 Free Software Foundation, Inc. | Written by Daniele Sciascia. | | This file is part of the GNU Smalltalk class library. | | The GNU Smalltalk class library is free software; you can redistribute it | and/or modify it under the terms of the GNU Lesser General Public License | as published by the Free Software Foundation; either version 2.1, or (at | your option) any later version. | | The GNU Smalltalk class library is distributed in the hope that it will be | useful, but WITHOUT ANY WARRANTY; without even the implied warranty of | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU Lesser | General Public License for more details. | | You should have received a copy of the GNU Lesser General Public License | along with the GNU Smalltalk class library; see the file COPYING.LIB. | If not, write to the Free Software Foundation, 59 Temple Place - Suite | 330, Boston, MA 02110-1301, USA. | ======================================================================" Behavior extend [ parseNodeAt: selector [ "Available only when the Parser package is loaded--Answer an RBMethodNode that compiles to my method named by selector." ^(self compiledMethodAt: selector) methodParseNode ] formattedSourceStringAt: aSelector ifAbsent: aBlock [ "Answer the method source code as a formatted string. Requires package Parser." | method | method := self lookupSelector: aSelector. method isNil ifTrue: [^aBlock value copy]. ^method methodFormattedSourceString ] ] CompiledMethod extend [ methodFormattedSourceString [ "Answer the method source code as a string, formatted using the RBFormatter. Requires package Parser." ^STInST.RBFormatter new initialIndent: 1; format: self methodParseNode. ] methodParseNode [ "Answer the parse tree for the receiver, or nil if there is an error. Requires package Parser." ^self parserClass parseMethod: self methodSourceString category: self methodCategory onError: [ :message :position | ^nil ] ] parserClass [ "Answer a parser class, similar to Behavior>>parserClass, that can parse my source code. Requires package Parser." ^self isOldSyntax ifTrue: [ STInST.RBParser ] ifFalse: [ STInST.RBBracketedMethodParser ] ] ] Class extend [ fileOutHeaderOn: aFileStream [ | now | aFileStream nextPutAll: '"Filed out from '; nextPutAll: Smalltalk version; nextPutAll: ' on '. now := Date dateAndTimeNow. aFileStream print: now asDate; space; print: now asTime; nextPutAll: '"'; nl; nl ] fileOutDeclarationOn: aFileStream [ "File out class definition to aFileStream. Requires package Parser." self fileOutHeaderOn: aFileStream. (STInST.FileOutExporter defaultExporter on: self to: aFileStream) fileOutDeclaration: [ ] ] fileOutOn: aFileStream [ "File out complete class description: class definition, class and instance methods. Requires package Parser." self fileOutHeaderOn: aFileStream. STInST.FileOutExporter defaultExporter fileOut: self to: aFileStream ] ] ClassDescription extend [ fileOutSelector: aSymbol toStream: aFileStream [ "File out all the methods belonging to the method category, category, to aFileStream. Requires package Parser." self fileOutHeaderOn: aFileStream. STInST.FileOutExporter defaultExporter fileOutSelector: aSymbol of: self to: aFileStream ] fileOutCategory: category toStream: aFileStream [ "File out all the methods belonging to the method category, category, to aFileStream. Requires package Parser." self fileOutHeaderOn: aFileStream. STInST.FileOutExporter defaultExporter fileOutCategory: category of: self to: aFileStream ] ] smalltalk-3.2.5/packages/stinst/parser/SqueakParser.st0000644000175000017500000001152512123404352020002 00000000000000"====================================================================== | | Squeak input parser | | ======================================================================" "====================================================================== | | Copyright 2007, 2008 Free Software Foundation, Inc. | Written by Paolo Bonzini. | | This file is part of GNU Smalltalk. | | GNU Smalltalk is free software; you can redistribute it and/or modify it | under the terms of the GNU General Public License as published by the Free | Software Foundation; either version 2, or (at your option) any later version. | | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS | FOR A PARTICULAR PURPOSE. See the GNU General Public License for more | details. | | You should have received a copy of the GNU General Public License along with | GNU Smalltalk; see the file COPYING. If not, write to the Free Software | Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. | ======================================================================" STFileInParser subclass: SqueakFileInParser [ evaluate: node [ "Convert some Squeak messages to GNU Smalltalk file-out syntax. This avoids that the STParsingDriver need to know about other dialects." | stmt | node statements size == 1 ifFalse: [^super evaluate: node]. stmt := node statements first. stmt isReturn ifTrue: [ stmt := stmt value ]. stmt isMessage ifFalse: [^super evaluate: node]. stmt selector == #addCategory: ifTrue: [^false]. stmt selector == #commentStamp:prior: ifTrue: [stmt arguments: {RBLiteralNode new literalToken: scanner nextRawChunk}. stmt selector: #comment:]. stmt selector == #methodsFor:stamp: ifTrue: [stmt arguments first value = 'as yet unclassified' ifTrue: [stmt arguments first token value: nil]. stmt arguments: {stmt arguments first}. stmt selector: #methodsFor:]. ^super evaluate: node ] scannerClass [ "We need a special scanner to convert the double-bangs in strings to single bangs. Unlike in GNU Smalltalk, all bangs must be `escaped' in Squeak." ^SqueakFileInScanner ] ] STFileScanner subclass: SqueakFileInScanner [ isDigit: aChar base: aBase [ "Pharo/Squeak allows 16rff as literal." ^ super isDigit: aChar asUppercase base: aBase. ] digitValue: aChar [ "Pharo/Squeak allows 16rff as literal." ^ super digitValue: aChar asUppercase ] on: aStream [ super on: aStream. classificationTable := classificationTable copy. classificationTable at: $! value put: #binary ] scanLiteralString [ "In theory, this should also be applied to method comments, but the representation of comments in RBParseNode makes it more complicated; not a big deal." | val | val := super scanLiteralString. val value: (val value copyReplaceAll: '!!' with: '!'). val value: (val value copyReplacing: 13 asCharacter withObject: 10 asCharacter). ^val ] scanLiteralCharacter [ "Also treat ! specially here." | val | val := super scanLiteralCharacter. val value = $! ifTrue: [self step]. ^val ] scanBinary: aClass [ "Treat ! specially, it is a binary operator in Squeak (if properly escaped)." | val | currentCharacter == $! ifTrue: [ self step == $! ifFalse: [^RBSpecialCharacterToken value: $! start: tokenStart]]. buffer nextPut: currentCharacter. self step. (characterType == #binary and: [currentCharacter ~~ $-]) ifTrue: [currentCharacter == $! ifTrue: [self step == $! ifTrue: [ buffer nextPut: $!. self step] ifFalse: [ stream skip: -1. currentCharacter := $!. characterType := #binary]] ifFalse: [buffer nextPut: currentCharacter. self step]]. [characterType == #binary] whileTrue: [ buffer nextPut: currentCharacter. self step]. val := buffer contents. val := val asSymbol. ^aClass value: val start: tokenStart ] nextRawChunk [ "Return a raw chunk, converting all double exclamation marks to single. This is used for parsing Squeak class comments." buffer reset. [currentCharacter == $! and: [self step ~~ $!]] whileFalse: [buffer nextPut: currentCharacter. self step]. self stripSeparators. ^RBLiteralToken value: buffer contents start: tokenStart ] ] smalltalk-3.2.5/packages/stinst/parser/STFileParser.st0000644000175000017500000002517612123404352017706 00000000000000"====================================================================== | | Smalltalk in Smalltalk file-in driver | | ======================================================================" "====================================================================== | | Copyright 1999,2000,2001,2002,2003,2006,2007,2008,2009 Free Software Foundation, Inc. | Written by Paolo Bonzini. | | This file is part of GNU Smalltalk. | | GNU Smalltalk is free software; you can redistribute it and/or modify it | under the terms of the GNU General Public License as published by the Free | Software Foundation; either version 2, or (at your option) any later version. | | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS | FOR A PARTICULAR PURPOSE. See the GNU General Public License for more | details. | | You should have received a copy of the GNU General Public License along with | GNU Smalltalk; see the file COPYING. If not, write to the Free Software | Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. | ======================================================================" RBParser subclass: STFileParser [ | driver | STFileParser class >> parseSmalltalk: aString with: aDriver [ ^self parseSmalltalk: aString with: aDriver onError: nil ] STFileParser class >> parseSmalltalk: aString with: aDriver onError: aBlock [ | parser | parser := self new. parser errorBlock: aBlock. parser initializeParserWith: aString type: #on:errorBlock:. parser driver: aDriver. ^parser parseSmalltalk ] STFileParser class >> parseSmalltalkStream: aStream with: aDriver [ ^self parseSmalltalkStream: aStream with: aDriver onError: nil ] STFileParser class >> parseSmalltalkStream: aStream with: aDriver onError: aBlock [ | parser | parser := self new. parser errorBlock: aBlock. parser initializeParserWithStream: aStream type: #on:errorBlock:. parser driver: aDriver. ^parser parseSmalltalk ] driver [ ^driver ] driver: aSTParsingDriver [ driver := aSTParsingDriver. driver parser: self ] parseSmalltalk [ self subclassResponsibility ] compile: node [ ^driver compile: node ] endMethodList [ driver endMethodList ] resolveClass: node [ self evaluate: node. ^self result ] evaluate: node [ "This should be overridden because its result affects the parsing process: true means 'start parsing methods', false means 'keep evaluating'." ^node notNil and: [node statements size > 0 and: [driver evaluate: node]] ] parseStatements [ (currentToken isSpecial and: [currentToken value == $!]) ifTrue: [^RBSequenceNode statements: #()]. ^self parseStatements: false ] parseDoit [ | node start stop comments | comments := scanner getComments. start := comments isNil ifTrue: [currentToken start - 1] ifFalse: [comments first first - 1]. tags := nil. node := self parseStatements. node addReturn. node comments isNil ifTrue: [node comments: comments] ifFalse: [comments isNil ifFalse: [node comments: node comments , comments]]. "One -1 accounts for base-1 vs. base-0 (as above), the other drops the bang because we have a one-token lookahead." stop := currentToken start - 2. ^self addSourceFrom: start to: stop to: node ] addSourceFrom: start to: stop to: node [ | method source | node isMethod ifTrue: [method := node] ifFalse: [method := RBMethodNode selectorParts: #() arguments: #(). node parent: method]. source := MappedSourceCode on: scanner from: start to: stop. method source: source. ^node ] ] Object subclass: STParsingDriver [ | parser | parseSmalltalk: aString with: aParserClass [ ^aParserClass parseSmalltalk: aString with: self ] parseSmalltalk: aString with: aParserClass onError: aBlock [ ^aParserClass parseSmalltalk: aString with: self onError: aBlock ] parseSmalltalkStream: aStream with: aParserClass [ ^aParserClass parseSmalltalkStream: aStream with: self ] parseSmalltalkStream: aStream with: aParserClass onError: aBlock [ ^aParserClass parseSmalltalkStream: aStream with: self onError: aBlock ] parseSmalltalkFileIn: aFilename with: aParserClass [ ^self parseSmalltalkFileIn: aFilename with: aParserClass onError: nil ] parseSmalltalkFileIn: aFilename with: aParserClass onError: aBlock [ | parser file | file := FileStream open: aFilename mode: FileStream read. [self parseSmalltalkStream: file with: aParserClass onError: aBlock] ensure: [file close] ] errorBlock [ ^parser errorBlock ] parserWarning: aString [ parser parserWarning: aString ] parserError: aString [ parser parserError: aString ] parser [ ^parser ] parser: aSTFileParser [ parser := aSTFileParser ] result [ "return self by default" ^self ] compile: node [ "do nothing by default" ^nil ] endMethodList [ "do nothing by default" ] evaluate: node [ "This should be overridden because its result affects the parsing process: true means 'start parsing methods', false means 'keep evaluating'. By default, always answer false." ^false ] currentNamespace [ ^Namespace current ] ] STFileParser subclass: STFileInParser [ parseSmalltalk [ [self parseDoits] whileTrue: [self parseMethodDefinitionList]. self atEnd ifFalse: [self parserError: 'doit expected']. ^driver result ] scannerClass [ ^STFileScanner ] parseDoits [ "Parses the stuff to be executed until a ! methodsFor: !" | node | [self atEnd ifTrue: [^false]. node := self parseDoit. scanner stripSeparators. self evaluate: node] whileFalse: [(currentToken isSpecial and: [currentToken value == $!]) ifTrue: [self step]]. ^true ] parseMethodFromFile [ | node source start stop | start := currentToken start - 1. tags := nil. node := self parseMethod. node comments: (node comments select: [:each | each last >= start]). "One -1 accounts for base-1 vs. base-0 (as above), the other drops the bang because we have a one-token lookahead." stop := currentToken start - 2. node := self addSourceFrom: start to: stop to: node. scanner stripSeparators. self step. "gobble method terminating bang" ^node ] parseMethodDefinitionList [ "Called after first !, expecting a set of bang terminated method definitions, followed by a bang" | method | self step. "gobble doit terminating bang" [scanner atEnd or: [currentToken isSpecial and: [currentToken value == $!]]] whileFalse: [ method := self compile: self parseMethodFromFile. method isNil ifFalse: [method noteOldSyntax]]. scanner stripSeparators. self step. self endMethodList ] ] RBScanner subclass: STFileScanner [ next [ | token | buffer reset. tokenStart := stream position. characterType == #eof ifTrue: [^RBToken start: tokenStart + 1]. "The EOF token should occur after the end of input" token := self scanToken. (token isSpecial and: [token value == $!]) ifFalse: [self stripSeparators]. ^token ] ] PositionableStream extend [ name [ "Answer a string that represents what the receiver is streaming on" ^'(%1 %2)' % {self species article. self species name} ] segmentFrom: startPos to: endPos [ "Answer an object that, when sent #asString, will yield the result of sending `copyFrom: startPos to: endPos' to the receiver" ^self copyFrom: startPos to: endPos ] ] Stream extend [ segmentFrom: startPos to: endPos [ "Answer an object that, when sent #asString, will yield the result of sending `copyFrom: startPos to: endPos' to the receiver" ^nil ] ] FileStream extend [ segmentFrom: startPos to: endPos [ "Answer an object that, when sent #asString, will yield the result of sending `copyFrom: startPos to: endPos' to the receiver" self isPipe ifTrue: [^nil]. ^FileSegment on: self file startingAt: startPos for: endPos - startPos + 1 ] ] MappedCollection subclass: MappedSourceCode [ | sourceCode | MappedSourceCode class >> on: aScanner from: start to: stop [ | collection coll sourceCode | collection := aScanner stream copyFrom: start to: stop. coll := self collection: collection map: (1 - start to: stop). sourceCode := (aScanner stream segmentFrom: start to: stop) ifNil: [collection]. coll sourceCode: sourceCode. ^coll ] asString [ ^self domain asString ] asSourceCode [ ^sourceCode ] sourceCode: anObject [ sourceCode := anObject ] ] Object extend [ asSourceCode [ ^self ] ] smalltalk-3.2.5/packages/stinst/parser/SIFParser.st0000644000175000017500000001700112123404352017165 00000000000000"====================================================================== | | SIF input parser | | ======================================================================" "====================================================================== | | Copyright 2007 Free Software Foundation, Inc. | Written by Paolo Bonzini. | | This file is part of GNU Smalltalk. | | GNU Smalltalk is free software; you can redistribute it and/or modify it | under the terms of the GNU General Public License as published by the Free | Software Foundation; either version 2, or (at your option) any later version. | | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS | FOR A PARTICULAR PURPOSE. See the GNU General Public License for more | details. | | You should have received a copy of the GNU General Public License along with | GNU Smalltalk; see the file COPYING. If not, write to the Free Software | Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. | ======================================================================" STFileInParser subclass: #SIFFileInParser instanceVariableNames: 'lastClass' classVariableNames: '' poolDictionaries: '' category: 'Refactory-Parser'! !SIFFileInParser methodsFor: 'parsing'! parseMethodDefinitionList "Methods are defined one by one in SIF." | method | method := self compile: self parseMethodFromFile. method isNil ifFalse: [ method noteOldSyntax ]. self endMethodList ! ! !SIFFileInParser methodsFor: 'evaluating'! evaluate: node "Convert some SIF messages to GNU Smalltalk file-out syntax. This avoids that the STParsingDriver need to know about other dialects." | stmt | node statements size == 0 ifTrue: [ ^false ]. node statements size == 1 ifFalse: [ ^self error: 'invalid SIF' ]. stmt := node statements first. stmt isReturn ifTrue: [ stmt := stmt value ]. stmt isMessage ifFalse: [ ^super evaluate: node ]. stmt selector == #interchangeVersion: ifTrue: [ ^false ]. stmt selector == #named:superclass:indexedInstanceVariables:instanceVariableNames:classVariableNames:sharedPools:classInstanceVariableNames: ifTrue: [ lastClass := self evaluateClass: stmt. ^false ]. stmt selector == #key:value: ifTrue: [ lastClass isNil ifFalse: [ self evaluateAnnotation: stmt to: lastClass ]. ^false ]. stmt selector == #classMethod ifTrue: [ lastClass := nil. self evaluateClassMethod: stmt. ^true ]. stmt selector == #method ifTrue: [ lastClass := nil. self evaluateMethod: stmt. ^true ]. (stmt selector == #initializerFor:) ifTrue: [ lastClass := nil. self evaluateInitializer: stmt. ^false ]. (stmt selector == #initializer) ifTrue: [ lastClass := nil. self evaluateGlobalInitializer: stmt. ^false ]. (stmt selector == #variable: or: [ stmt selector == #constant: ]) ifTrue: [ lastClass := nil. self evaluatePoolDefinition: stmt. ^false ]. stmt selector == #named: ifTrue: [ lastClass := nil. self evaluatePool: stmt. ^false ]. self error: 'invalid SIF' ! evaluateStatement: stmt driver evaluate: (RBSequenceNode new temporaries: #(); statements: { stmt }) ! evaluateClass: stmt "Convert `Class named: ...' syntax to GNU Smalltalk file-out syntax." | name superclass shape ivn cvn sp civn newStmt newClass | name := stmt arguments at: 1. superclass := stmt arguments at: 2. shape := stmt arguments at: 3. ivn := stmt arguments at: 4. cvn := stmt arguments at: 5. sp := stmt arguments at: 6. civn := stmt arguments at: 7. shape value = #none ifTrue: [ shape := RBLiteralNode value: nil ]. shape value = #object ifTrue: [ shape := RBLiteralNode value: #pointer ]. newStmt := RBMessageNode receiver: (RBVariableNode named: superclass value) selector: #variable:subclass:instanceVariableNames:classVariableNames:poolDictionaries:category: arguments: { shape. RBLiteralNode value: name value asSymbol. ivn. cvn. sp. RBLiteralNode value: nil }. self evaluateStatement: newStmt. newClass := RBVariableNode named: name value. newStmt := RBMessageNode receiver: (self makeClassOf: newClass) selector: #instanceVariableNames: arguments: { civn }. self evaluateStatement: newStmt. ^newClass! makeClassOf: node ^RBMessageNode receiver: node selector: #class arguments: #()! evaluateAnnotation: stmt to: object "Convert `Annotation key: ...' syntax to GNU Smalltalk file-out syntax." | key value selector newStmt | key := stmt arguments at: 1. value := stmt arguments at: 2. key value = 'package' ifTrue: [ selector := #category: ]. key value = 'category' ifTrue: [ selector := #category: ]. key value = 'comment' ifTrue: [ selector := #comment: ]. selector isNil ifFalse: [ newStmt := RBMessageNode receiver: object selector: selector arguments: { value }. self evaluateStatement: newStmt ]! evaluateClassMethod: stmt "Convert `Foo classMethod' syntax to GNU Smalltalk file-out syntax." stmt receiver: (self makeClassOf: stmt receiver). self evaluateMethod: stmt! evaluateMethod: stmt "Convert `Foo method' syntax to GNU Smalltalk file-out syntax." | newStmt | newStmt := RBMessageNode receiver: stmt receiver selector: #methodsFor: arguments: { RBLiteralNode value: nil }. self evaluateStatement: newStmt! evaluateInitializer: stmt "Convert `Foo initializerFor: Bar' syntax to GNU Smalltalk file-out syntax." self evaluateInitializerFor: stmt arguments first value in: stmt receiver! evaluateGlobalInitializer: stmt "Convert `Foo initializer' syntax to GNU Smalltalk file-out syntax." | node | stmt receiver name = 'Global' ifTrue: [ node := self parseDoit. scanner stripSeparators. self step. ^super evaluate: node ]. self evaluateInitializerFor: stmt receiver name in: (RBVariableNode named: 'Smalltalk')! evaluateInitializerFor: key in: receiver | position node arg newStmt | position := currentToken start. node := RBOptimizedNode left: position body: self parseDoit right: currentToken start. scanner stripSeparators. self step. newStmt := RBMessageNode receiver: receiver selector: #at:put: arguments: { RBLiteralNode value: key asSymbol. node }. self evaluateStatement: newStmt! evaluatePoolDefinition: stmt "Convert `Foo variable:/constant: ...' syntax to GNU Smalltalk file-out syntax." | receiver key newStmt | receiver := stmt receiver. receiver name = 'Global' ifTrue: [ receiver := RBVariableNode named: 'Smalltalk' ]. key := RBLiteralNode value: stmt arguments first value asSymbol. newStmt := RBMessageNode receiver: receiver selector: #at:put: arguments: { key. RBLiteralNode value: nil }. self evaluateStatement: newStmt! evaluatePool: stmt "Convert `Pool named: ...' syntax to GNU Smalltalk file-out syntax." | key newStmt | key := RBLiteralNode value: stmt arguments first value asSymbol . newStmt := RBMessageNode receiver: (RBVariableNode named: 'Smalltalk') selector: #addSubspace: arguments: { key }. self evaluateStatement: newStmt! ! ! !SIFFileInParser methodsFor: 'private-parsing'! scannerClass "We need a special scanner to convert the double-bangs in strings to single bangs. Unlike in GNU Smalltalk, all bangs must be `escaped' in Squeak." ^SqueakFileInScanner! ! smalltalk-3.2.5/packages/stinst/parser/RBParser.st0000644000175000017500000011225012130343734017055 00000000000000"====================================================================== | | Refactoring Browser - Smalltalk parser and scanner | | ======================================================================" "====================================================================== | | Copyright 1998-2000 The Refactory, Inc. | | This file is distributed together with GNU Smalltalk. | ======================================================================" Object subclass: RBParser [ | scanner currentToken nextToken errorBlock tags source methodCategory | RBParser class >> parseExpression: aString [ ^self parseExpression: aString onError: nil ] RBParser class >> parseExpression: aString onError: aBlock [ | node parser | parser := self new. parser errorBlock: aBlock. parser initializeParserWith: aString type: #on:errorBlock:. node := parser parseExpression. ^(node statements size == 1 and: [node temporaries isEmpty]) ifTrue: [node statements first] ifFalse: [node] ] RBParser class >> parseMethod: aString [ ^self parseMethod: aString category: nil onError: nil ] RBParser class >> parseMethod: aString category: aCategory [ ^self parseMethod: aString category: aCategory onError: nil ] RBParser class >> parseMethod: aString onError: aBlock [ ^self parseMethod: aString category: nil onError: aBlock ] RBParser class >> parseMethod: aString category: aCategory onError: aBlock [ | parser | parser := self new. parser methodCategory: aCategory. parser errorBlock: aBlock. parser initializeParserWith: aString type: #on:errorBlock:. ^parser parseMethod: aString ] RBParser class >> parseRewriteExpression: aString [ ^self parseRewriteExpression: aString onError: nil ] RBParser class >> parseRewriteExpression: aString onError: aBlock [ | node parser | parser := self new. parser errorBlock: aBlock. parser initializeParserWith: aString type: #rewriteOn:errorBlock:. node := parser parseExpression. ^(node statements size == 1 and: [node temporaries isEmpty]) ifTrue: [node statements first] ifFalse: [node] ] RBParser class >> parseRewriteMethod: aString [ ^self parseRewriteMethod: aString onError: nil ] RBParser class >> parseRewriteMethod: aString onError: aBlock [ | parser | parser := self new. parser errorBlock: aBlock. parser initializeParserWith: aString type: #rewriteOn:errorBlock:. ^parser parseMethod: aString ] RBParser class >> parseMethodPattern: aString [ | parser | parser := self new. parser errorBlock: [:error :position | ^nil]. parser initializeParserWith: aString type: #on:errorBlock:. ^parser parseMessagePattern selector ] methodCategory [ ^methodCategory ] methodCategory: aCategory [ methodCategory := aCategory ] errorBlock: aBlock [ errorBlock := aBlock. scanner notNil ifTrue: [scanner errorBlock: aBlock] ] initializeParserWith: aString type: aSymbol [ source := aString. self scanner: (self scannerClass perform: aSymbol with: (ReadStream on: aString) with: self errorBlock) ] initializeParserWithStream: aStream type: aSymbol [ source := nil. self scanner: (self scannerClass perform: aSymbol with: aStream with: self errorBlock) ] parseExpression [ | node | node := self parseStatements: false. self atEnd ifFalse: [self parserError: 'Unknown input at end']. ^node ] parseMethod: aString [ | node | node := self parseMethod. self atEnd ifFalse: [self parserError: 'Unknown input at end']. node source: aString. ^node ] scannerClass [ ^RBScanner ] errorBlock [ ^errorBlock isNil ifTrue: [[:message :position | ]] ifFalse: [errorBlock] ] errorFile [ ^scanner stream name ] errorLine [ ^(scanner stream copyFrom: 1 to: self errorPosition) readStream lines contents size ] errorPosition [ ^currentToken start ] parserWarning: aString [ "Raise a Warning" Warning signal: aString ] parserError: aString [ "Evaluate the block. If it returns raise an error" self errorBlock value: aString value: self errorPosition. self error: '%1:%2: %3' % {self errorFile. self errorLine. aString} ] scanner: aScanner [ scanner := aScanner. tags := nil. self step ] addCommentsTo: aNode [ aNode comments: scanner getComments ] currentToken [ ^currentToken ] nextToken [ ^nextToken isNil ifTrue: [nextToken := scanner next] ifFalse: [nextToken] ] step [ nextToken notNil ifTrue: [currentToken := nextToken. nextToken := nil. ^currentToken]. currentToken := scanner next ] parseArgs [ | args | args := OrderedCollection new. [currentToken isIdentifier] whileTrue: [args add: self parseVariableNode]. ^args ] parseArrayConstructor [ | position node | position := currentToken start. self step. node := RBArrayConstructorNode new. node left: position. node body: (self parseStatements: false). (currentToken isSpecial and: [currentToken value == $}]) ifFalse: [self parserError: '''}'' expected']. node right: currentToken start. self step. ^node ] parseAssignment [ "Need one token lookahead to see if we have a ':='. This method could make it possible to assign the literals true, false and nil." | node position | (currentToken isIdentifier and: [self nextToken isAssignment]) ifFalse: [^self parseCascadeMessage]. node := self parseVariableNode. position := currentToken start. self step. ^RBAssignmentNode variable: node value: self parseAssignment position: position ] parseBinaryMessage [ | node | node := self parseUnaryMessage. [currentToken isBinary] whileTrue: [node := self parseBinaryMessageWith: node]. ^node ] parseBinaryMessageNoGreater [ | node | node := self parseUnaryMessage. [currentToken isBinary and: [currentToken value ~~ #>]] whileTrue: [node := self parseBinaryMessageWith: node]. ^node ] parseBinaryMessageWith: aNode [ | binaryToken | binaryToken := currentToken. self step. ^RBMessageNode receiver: aNode selectorParts: (Array with: binaryToken) arguments: (Array with: self parseUnaryMessage) ] parseBinaryPattern [ | binaryToken | currentToken isBinary ifFalse: [self parserError: 'Message pattern expected']. binaryToken := currentToken. self step. ^RBMethodNode selectorParts: (Array with: binaryToken) arguments: (Array with: self parseVariableNode) ] parseBlock [ | position node | position := currentToken start. self step. node := self parseBlockArgsInto: RBBlockNode new. node left: position. node body: (self parseStatements: false). (currentToken isSpecial and: [currentToken value == $]]) ifFalse: [self parserError: ''']'' expected']. node right: currentToken start. self step. ^node ] parseBlockArgsInto: node [ | verticalBar args colons | args := OrderedCollection new: 2. colons := OrderedCollection new: 2. verticalBar := false. [currentToken isSpecial and: [currentToken value == $:]] whileTrue: [colons add: currentToken start. self step. ":" verticalBar := true. args add: self parseVariableNode]. verticalBar ifTrue: [currentToken isBinary ifTrue: [node bar: currentToken start. currentToken value == #| ifTrue: [self step] ifFalse: [currentToken value == #'||' ifTrue: ["Hack the current token to be the start of temps bar" currentToken value: #|; start: currentToken start + 1] ifFalse: [self parserError: '''|'' expected']]] ifFalse: [(currentToken isSpecial and: [currentToken value == $]]) ifFalse: [self parserError: '''|'' expected']]]. node arguments: args; colons: colons. ^node ] parseCascadeMessage [ | node receiver messages semicolons | node := self parseKeywordMessage. (currentToken isSpecial and: [currentToken value == $; and: [node isMessage]]) ifFalse: [^node]. receiver := node receiver. messages := OrderedCollection new: 3. semicolons := OrderedCollection new: 3. messages add: node. [currentToken isSpecial and: [currentToken value == $;]] whileTrue: [semicolons add: currentToken start. self step. messages add: (currentToken isIdentifier ifTrue: [self parseUnaryMessageWith: receiver] ifFalse: [currentToken isKeyword ifTrue: [self parseKeywordMessageWith: receiver] ifFalse: [| temp | currentToken isBinary ifFalse: [self parserError: 'Message expected']. temp := self parseBinaryMessageWith: receiver. temp == receiver ifTrue: [self parserError: 'Message expected']. temp]])]. ^RBCascadeNode messages: messages semicolons: semicolons ] parseKeywordMessage [ ^self parseKeywordMessageWith: self parseBinaryMessage ] parseKeywordMessageWith: node [ | args isKeyword keywords | args := OrderedCollection new: 3. keywords := OrderedCollection new: 3. isKeyword := false. [currentToken isKeyword] whileTrue: [keywords add: currentToken. self step. args add: self parseBinaryMessage. isKeyword := true]. ^isKeyword ifTrue: [RBMessageNode receiver: node selectorParts: keywords arguments: args] ifFalse: [node] ] parseKeywordPattern [ | keywords args | keywords := OrderedCollection new: 2. args := OrderedCollection new: 2. [currentToken isKeyword] whileTrue: [keywords add: currentToken. self step. args add: self parseVariableNode]. ^RBMethodNode selectorParts: keywords arguments: args ] parseMessagePattern [ ^currentToken isIdentifier ifTrue: [self parseUnaryPattern] ifFalse: [currentToken isKeyword ifTrue: [self parseKeywordPattern] ifFalse: [self parseBinaryPattern]] ] parseMethod [ | methodNode | methodNode := self parseMessagePattern. ^self parseMethodInto: methodNode ] parseMethodInto: methodNode [ tags := nil. self parseResourceTag. self addCommentsTo: methodNode. methodNode body: (self parseStatements: true). methodNode tags: tags. methodNode category: methodCategory. ^methodNode ] parseOptimizedExpression [ | position node | position := currentToken start. self step. node := RBOptimizedNode left: position body: (self parseStatements: false) right: currentToken start. (currentToken isSpecial and: [currentToken value == $)]) ifFalse: [self parserError: ''')'' expected']. self step. ^node ] parseParenthesizedExpression [ | leftParen node | leftParen := currentToken start. self step. node := self parseAssignment. ^(currentToken isSpecial and: [currentToken value == $)]) ifTrue: [node addParenthesis: (leftParen to: currentToken start). self step. node] ifFalse: [self parserError: ''')'' expected'] ] parsePatternBlock [ | position node | position := currentToken start. self step. node := self parseBlockArgsInto: RBPatternBlockNode new. node left: position. node body: (self parseStatements: false). (currentToken isSpecial and: [currentToken value == $}]) ifFalse: [self parserError: '''}'' expected']. node right: currentToken start. self step. ^node ] parsePrimitiveIdentifier [ | value token | token := currentToken. value := currentToken value. self step. value = 'true' ifTrue: [^RBLiteralNode literalToken: (RBLiteralToken value: true start: token start stop: token start + 3)]. value = 'false' ifTrue: [^RBLiteralNode literalToken: (RBLiteralToken value: false start: token start stop: token start + 4)]. value = 'nil' ifTrue: [^RBLiteralNode literalToken: (RBLiteralToken value: nil start: token start stop: token start + 2)]. ^RBVariableNode identifierToken: token ] parseNegatedNumber [ | token | self step. token := currentToken. (token value respondsTo: #negated) ifFalse: [ ^self parserError: 'Number expected' ]. token value negative ifTrue: [ ^self parserError: 'Positive number expected' ]. token value: token value negated. self step. ^RBLiteralNode literalToken: token ] parsePrimitiveLiteral [ | token | token := currentToken. self step. ^RBLiteralNode literalToken: token ] parsePrimitiveObject [ currentToken isIdentifier ifTrue: [^self parsePrimitiveIdentifier]. currentToken isLiteral ifTrue: [^self parsePrimitiveLiteral]. (currentToken isBinary and: [ currentToken value == #- ]) ifTrue: [^self parseNegatedNumber]. currentToken isSpecial ifTrue: [currentToken value == $[ ifTrue: [^self parseBlock]. currentToken value == ${ ifTrue: [^self parseArrayConstructor]. currentToken value == $( ifTrue: [^self parseParenthesizedExpression]]. currentToken isPatternBlock ifTrue: [^self parsePatternBlock]. currentToken isOptimized ifTrue: [^self parseOptimizedExpression]. self parserError: 'Variable expected' ] parseResourceTag [ | start | [currentToken isBinary and: [currentToken value == #<]] whileTrue: [start := currentToken start. self step. [scanner atEnd or: [currentToken isBinary and: [currentToken value == #>]]] whileFalse: [self step]. (currentToken isBinary and: [currentToken value == #>]) ifFalse: [self parserError: '''>'' expected']. tags isNil ifTrue: [tags := OrderedCollection with: (start to: currentToken stop)] ifFalse: [tags add: (start to: currentToken stop)]. self step] ] parseStatementList: tagBoolean into: sequenceNode [ | statements return periods returnPosition node | return := false. statements := OrderedCollection new. periods := OrderedCollection new. self addCommentsTo: sequenceNode. tagBoolean ifTrue: [self parseResourceTag]. [self atEnd or: [currentToken isSpecial and: ['!])}' includes: currentToken value]]] whileFalse: [return ifTrue: [self parserError: 'End of statement list encountered']. (currentToken isSpecial and: [currentToken value == $^]) ifTrue: [returnPosition := currentToken start. self step. node := RBReturnNode return: returnPosition value: self parseAssignment. self addCommentsTo: node. statements add: node. return := true] ifFalse: [node := self parseAssignment. self addCommentsTo: node. statements add: node]. (currentToken isSpecial and: [currentToken value == $.]) ifTrue: [periods add: currentToken start. self step] ifFalse: [return := true]]. sequenceNode statements: statements; periods: periods. ^sequenceNode ] parseStatements: tagBoolean [ | args leftBar rightBar | args := #(). leftBar := rightBar := nil. currentToken isBinary ifTrue: [currentToken value == #| ifTrue: [leftBar := currentToken start. self step. args := self parseArgs. (currentToken isBinary and: [currentToken value = #|]) ifFalse: [self parserError: '''|'' expected']. rightBar := currentToken start. self step] ifFalse: [currentToken value == #'||' ifTrue: [rightBar := (leftBar := currentToken start) + 1. self step]]]. ^self parseStatementList: tagBoolean into: (RBSequenceNode leftBar: leftBar temporaries: args rightBar: rightBar) ] parseUnaryMessage [ | node | node := self parsePrimitiveObject. [currentToken isIdentifier] whileTrue: [node := self parseUnaryMessageWith: node]. ^node ] parseUnaryMessageWith: aNode [ | selector | selector := currentToken. self step. ^RBMessageNode receiver: aNode selectorParts: (Array with: selector) arguments: #() ] parseUnaryPattern [ | selector | selector := currentToken. self step. ^RBMethodNode selectorParts: (Array with: selector) arguments: #() ] parseVariableNode [ | node | currentToken isIdentifier ifFalse: [self parserError: 'Variable name expected']. node := RBVariableNode identifierToken: currentToken. self step. ^node ] atEnd [ ^currentToken class == RBToken ] ] Stream subclass: RBScanner [ | stream buffer tokenStart currentCharacter characterType classificationTable saveComments comments extendedLanguage errorBlock | ClassificationTable := nil. PatternVariableCharacter := nil. RBScanner class >> classificationTable [ ClassificationTable isNil ifTrue: [self initialize]. ^ClassificationTable ] RBScanner class >> patternVariableCharacter [ ^PatternVariableCharacter ] RBScanner class >> initialize [ PatternVariableCharacter := $`. ClassificationTable := Array new: 255. self initializeChars: 'abcdefghijklmnopqrstuvwxyzABCDEFGHIJKLMNOPQRSTUVWXYZ_' to: #alphabetic. self initializeChars: '01234567890' to: #digit. self initializeChars: '%&*+,-/<=>?@\~|' to: #binary. self initializeChars: '{}().:;[]^!' to: #special. #(9 10 12 13 26 32) do: [:i | ClassificationTable at: i put: #separator] ] RBScanner class >> initializeChars: characters to: aSymbol [ characters do: [:c | ClassificationTable at: c asInteger put: aSymbol] ] RBScanner class >> on: aStream [ | str | str := self basicNew on: aStream. str step. str stripSeparators. ^str ] RBScanner class >> on: aStream errorBlock: aBlock [ | str | str := self basicNew on: aStream. str errorBlock: aBlock; step; stripSeparators. ^str ] RBScanner class >> rewriteOn: aStream [ | str | str := self basicNew on: aStream. str extendedLanguage: true; ignoreComments. str step. str stripSeparators. ^str ] RBScanner class >> rewriteOn: aStream errorBlock: aBlock [ | str | str := self basicNew on: aStream. str extendedLanguage: true; ignoreComments; errorBlock: aBlock; step; stripSeparators. ^str ] RBScanner class >> isSelector: aSymbol [ | scanner token | scanner := self basicNew. scanner on: (ReadStream on: aSymbol asString). scanner step. token := scanner scanAnySymbol. token isLiteral ifFalse: [^false]. token value isEmpty ifTrue: [^false]. ^scanner atEnd ] RBScanner class >> isVariable: aString [ | scanner token | aString isString ifFalse: [^false]. aString isEmpty ifTrue: [^false]. (ClassificationTable at: aString first asInteger) == #alphabetic ifFalse: [^false]. scanner := self basicNew. scanner on: (ReadStream on: aString asString). scanner errorBlock: [:s :p | ^false]. scanner step. token := scanner scanIdentifierOrKeyword. token isKeyword ifTrue: [^false]. ^scanner atEnd ] classificationTable: anObject [ classificationTable := anObject ] contents [ | contentsStream | contentsStream := WriteStream on: (Array new: 50). self do: [:each | contentsStream nextPut: each]. ^contentsStream contents ] errorBlock: aBlock [ errorBlock := aBlock ] extendedLanguage [ ^extendedLanguage ] extendedLanguage: aBoolean [ extendedLanguage := aBoolean ] flush [ ] getComments [ | oldComments | comments isEmpty ifTrue: [^nil]. oldComments := comments. comments := OrderedCollection new: 1. ^oldComments ] ignoreComments [ saveComments := false ] next [ | token | buffer reset. tokenStart := stream position. characterType == #eof ifTrue: [^RBToken start: tokenStart + 1]. "The EOF token should occur after the end of input" token := self scanToken. self stripSeparators. ^token ] nextPut: anObject [ "Provide an error notification that the receiver does not implement this message." self shouldNotImplement ] saveComments [ saveComments := true ] scanToken [ "fast-n-ugly. Don't write stuff like this. Has been found to cause cancer in laboratory rats. Basically a case statement. Didn't use Dictionary because lookup is pretty slow." characterType == #alphabetic ifTrue: [^self scanIdentifierOrKeyword]. characterType == #digit ifTrue: [^self scanNumber]. characterType == #binary ifTrue: [^self scanBinary: RBBinarySelectorToken]. characterType == #special ifTrue: [^self scanSpecialCharacter]. currentCharacter == $' ifTrue: [^self scanLiteralString]. currentCharacter == $# ifTrue: [^self scanLiteral]. currentCharacter == $$ ifTrue: [^self scanLiteralCharacter]. (extendedLanguage and: [currentCharacter == PatternVariableCharacter]) ifTrue: [^self scanPatternVariable]. ^self scannerError: 'Unknown character' ] position [ ^stream position ] stream [ ^stream ] errorBlock [ ^errorBlock isNil ifTrue: [[:message :position | ]] ifFalse: [errorBlock] ] errorPosition [ ^stream position ] scannerError: aString [ "Evaluate the block. If it returns raise an error" self errorBlock value: aString value: self errorPosition. self error: aString ] on: aStream [ buffer := WriteStream on: (String new: 60). stream := aStream. classificationTable := self class classificationTable. saveComments := true. extendedLanguage := false. comments := OrderedCollection new ] classify: aCharacter [ | index | aCharacter isNil ifTrue: [^nil]. index := aCharacter asInteger. index == 0 ifTrue: [^#separator]. index > 255 ifTrue: [^nil]. ^classificationTable at: index ] previousStepPosition [ ^characterType == #eof ifTrue: [stream position] ifFalse: [stream position - 1] ] step [ stream atEnd ifTrue: [characterType := #eof. ^currentCharacter := nil]. currentCharacter := stream next. characterType := self classify: currentCharacter. ^currentCharacter ] isDigit: aChar base: base [ aChar isNil ifTrue: [^false]. base <= 10 ifTrue: [aChar isDigit ifFalse: [^false]. ^aChar value - $0 value < base]. ^aChar isUppercase ifTrue: [aChar value - $A value < (base - 10)] ifFalse: [aChar isDigit] ] digitValue: aChar [ ^ aChar digitValue ] scanDigits: ch base: base [ | c num | c := ch. num := 0. [[c == $_] whileTrue: [self step. c := currentCharacter]. c notNil and: [self isDigit: c base: base]] whileTrue: [num := num * base + (self digitValue: c). self step. c := currentCharacter]. ^num ] scanExtendedLiterals [ | token | self step. currentCharacter == $( ifTrue: [self step. ^RBOptimizedToken start: tokenStart]. self scannerError: 'Expecting parentheses' ] scanFraction: ch num: num base: base return: aBlock [ | c scale result | c := ch. scale := 0. result := num. [[c == $_] whileTrue: [self step. c := currentCharacter]. c notNil and: [self isDigit: c base: base]] whileTrue: [result := result * base + (self digitValue: c). self step. c := currentCharacter. scale := scale - 1]. aBlock value: result value: scale ] scanNumberValue [ | isNegative base exponent scale ch num | isNegative := false. exponent := nil. "could be radix or base-10 mantissa" num := self scanDigits: currentCharacter base: 10. currentCharacter == $r ifTrue: [base := num truncated. self step "skip over 'r'". currentCharacter == $- ifTrue: [isNegative := true. self step "skip '-'"]. (self isDigit: currentCharacter base: base) ifTrue: [num := self scanDigits: currentCharacter base: base] ifFalse: [self error: 'malformed number']] ifFalse: [base := 10]. "Here we've either a) parsed base, an 'r' and are sitting on the following character b) parsed the integer part of the mantissa, and are sitting on the char following it, or c) parsed nothing and are sitting on a - sign." currentCharacter == $. ifTrue: [(self isDigit: stream peek base: base) ifTrue: [self step. self scanFraction: currentCharacter num: num base: base return: [:n :s | num := n. exponent := s]]]. isNegative ifTrue: [num := num negated]. currentCharacter == $s ifTrue: [self step. currentCharacter isNil ifTrue: [currentCharacter := Character space]. exponent isNil ifTrue: [exponent := 0]. currentCharacter isDigit ifTrue: [scale := self scanDigits: currentCharacter base: 10] ifFalse: ["Might sit on the beginning of an identifier such as 123stu, or on a ScaledDecimal literal lacking the scale such as 123s" (currentCharacter == $_ or: [currentCharacter isLetter]) ifTrue: [stream skip: -1. currentCharacter := $s] ifFalse: [scale := exponent negated]]. ^num asScaledDecimal: exponent radix: base scale: scale]. currentCharacter == $e ifTrue: [num := num asFloatE] ifFalse: [currentCharacter == $d ifTrue: [num := num asFloatD] ifFalse: [currentCharacter == $q ifTrue: [num := num asFloatQ] ifFalse: [^exponent isNil ifTrue: [num] ifFalse: [num asFloat * (base raisedToInteger: exponent)]]]]. ch := currentCharacter. self step. currentCharacter isNil ifTrue: [currentCharacter := Character space]. (currentCharacter == $_ or: [currentCharacter isLetter]) ifTrue: [stream skip: -1. currentCharacter := ch]. exponent isNil ifTrue: [exponent := 0]. currentCharacter == $- ifTrue: [self step. exponent := exponent - (self scanDigits: currentCharacter base: 10)] ifFalse: [currentCharacter isDigit ifTrue: [exponent := exponent + (self scanDigits: currentCharacter base: 10)]]. ^num * (base raisedToInteger: exponent) ] scanAnySymbol [ characterType == #alphabetic ifTrue: [^self scanSymbol]. characterType == #binary ifTrue: [^self scanBinary: RBLiteralToken]. ^RBToken new ] scanBinary: aClass [ "This doesn't parse according to the ANSI draft. It only parses 1 or 2 letter binary tokens." | val | buffer nextPut: currentCharacter. self step. (characterType == #binary and: [currentCharacter ~~ $-]) ifTrue: [buffer nextPut: currentCharacter. self step]. val := buffer contents. val := val asSymbol. ^aClass value: val start: tokenStart ] scanByteArray [ | byteStream number | byteStream := WriteStream on: (ByteArray new: 100). self step. [self stripSeparators. characterType == #digit] whileTrue: [number := self scanNumber value. (number isInteger and: [number between: 0 and: 255]) ifFalse: [self scannerError: 'Expecting 8-bit integer']. byteStream nextPut: number]. currentCharacter == $] ifFalse: [self scannerError: ''']'' expected']. self step. "]" ^RBLiteralToken value: byteStream contents start: tokenStart stop: self previousStepPosition ] scanIdentifierOrKeyword [ | tokenType token | currentCharacter == $_ ifTrue: [^self scanAssignment]. self scanName. token := self scanNamespaceName. token isNil ifTrue: [tokenType := (currentCharacter == $: and: [stream peek ~~ $=]) ifTrue: [buffer nextPut: currentCharacter. self step. ":" RBKeywordToken] ifFalse: [RBIdentifierToken]. token := tokenType value: buffer contents start: tokenStart]. ^token ] scanNamespaceName [ | token | currentCharacter == $. ifTrue: [(stream atEnd or: [(self classify: stream peek) ~~ #alphabetic]) ifTrue: [^nil]] ifFalse: [(currentCharacter == $: and: [stream peek == $:]) ifFalse: [^nil]. self step]. buffer nextPut: $.. self step. self scanName. token := self scanNamespaceName. token isNil ifTrue: [token := RBIdentifierToken value: buffer contents start: tokenStart]. ^token ] scanLiteral [ self step. self stripSeparators. characterType == #alphabetic ifTrue: [^self scanSymbol]. characterType == #binary ifTrue: [^(self scanBinary: RBLiteralToken) stop: self previousStepPosition]. currentCharacter == $' ifTrue: [^self scanStringSymbol]. currentCharacter == $( ifTrue: [^self scanLiteralArray]. currentCharacter == $[ ifTrue: [^self scanByteArray]. currentCharacter == ${ ifTrue: [^self scanQualifier]. currentCharacter == $# ifTrue: [^self scanExtendedLiterals]. self scannerError: 'Expecting a literal type' ] scanLiteralArray [ | arrayStream start | arrayStream := WriteStream on: (Array new: 10). self step. start := tokenStart. [self stripSeparators. tokenStart := stream position. currentCharacter == $)] whileFalse: [arrayStream nextPut: self scanLiteralArrayParts. buffer reset]. self step. ^RBLiteralToken value: arrayStream contents start: start stop: self previousStepPosition ] scanLiteralArrayParts [ currentCharacter == $# ifTrue: [^self scanLiteral]. characterType == #alphabetic ifTrue: [| token value | token := self scanSymbol. value := token value. value == #nil ifTrue: [token value: nil]. value == #true ifTrue: [token value: true]. value == #false ifTrue: [token value: false]. ^token]. (characterType == #digit or: [currentCharacter == $- and: [(self classify: stream peek) == #digit]]) ifTrue: [^self scanNumber]. characterType == #binary ifTrue: [^(self scanBinary: RBLiteralToken) stop: self previousStepPosition]. currentCharacter == $' ifTrue: [^self scanLiteralString]. currentCharacter == $$ ifTrue: [^self scanLiteralCharacter]. currentCharacter == $( ifTrue: [^self scanLiteralArray]. currentCharacter == $[ ifTrue: [^self scanByteArray]. ^self scannerError: 'Unknown character in literal array' ] scanLiteralCharacter [ | token value char tokenStop | self step. "$" tokenStop := stream position. char := currentCharacter. self step. "char" char = $< ifTrue: [self stripSeparators. characterType == #digit ifTrue: [value := self scanNumberValue. (value isInteger and: [value between: 0 and: 1114111]) ifFalse: [^self scannerError: 'Integer between 0 and 16r10FFFF expected']. char := Character codePoint: value. self stripSeparators. tokenStop := stream position. currentCharacter = $> ifTrue: [self step] ifFalse: [^self scannerError: '''>'' expected']]]. ^RBLiteralToken value: char start: tokenStart stop: tokenStop ] scanLiteralString [ self step. [currentCharacter isNil ifTrue: [self scannerError: 'Unmatched '' in string literal.']. currentCharacter == $' and: [self step ~~ $']] whileFalse: [buffer nextPut: currentCharacter. self step]. ^RBLiteralToken value: buffer contents start: tokenStart stop: self previousStepPosition ] scanPatternVariable [ buffer nextPut: currentCharacter. self step. currentCharacter == ${ ifTrue: [self step. ^RBPatternBlockToken value: '`{' start: tokenStart]. [characterType == #alphabetic] whileFalse: [characterType == #eof ifTrue: [self scannerError: 'Pattern variable expected']. buffer nextPut: currentCharacter. self step]. ^self scanIdentifierOrKeyword ] scanName [ [characterType == #alphabetic or: [characterType == #digit]] whileTrue: [buffer nextPut: currentCharacter. self step] ] scanNumber [ ^RBLiteralToken value: self scanNumberValue start: tokenStart stop: self previousStepPosition ] scanQualifier [ | nameStream | self step. "{" nameStream := WriteStream on: (String new: 10). [currentCharacter == $}] whileFalse: [nameStream nextPut: currentCharacter. self step]. self step. "}" ^RBBindingToken value: nameStream contents start: tokenStart stop: self previousStepPosition ] scanAssignment [ self step. ^RBAssignmentToken start: tokenStart ] scanSpecialCharacter [ | character | currentCharacter == $: ifTrue: [self step. ^currentCharacter == $= ifTrue: [self scanAssignment] ifFalse: [RBSpecialCharacterToken value: $: start: tokenStart]]. character := currentCharacter. self step. ^RBSpecialCharacterToken value: character start: tokenStart ] scanStringSymbol [ | literalToken | literalToken := self scanLiteralString. literalToken value: literalToken value asSymbol. ^literalToken ] scanSymbol [ | lastPosition hasColon value startPosition | hasColon := false. startPosition := lastPosition := stream position. [characterType == #alphabetic] whileTrue: [self scanName. currentCharacter == $: ifTrue: [buffer nextPut: $:. hasColon := true. lastPosition := stream position. self step]]. value := buffer contents. (hasColon and: [value last ~~ $:]) ifTrue: [stream position: lastPosition. self step. value := value copyFrom: 1 to: lastPosition - startPosition + 1]. ^RBLiteralToken value: value asSymbol start: tokenStart stop: self previousStepPosition ] stripComment [ | start stop | start := stream position. [self step == $"] whileFalse: [characterType == #eof ifTrue: [self scannerError: 'Unmatched " in comment.']]. stop := stream position. self step. saveComments ifFalse: [^self]. comments add: (start to: stop) ] stripSeparators [ [[characterType == #separator] whileTrue: [self step]. currentCharacter == $"] whileTrue: [self stripComment] ] atEnd [ ^characterType == #eof ] isReadable [ ^true ] isWritable [ ^false ] ] RBParser subclass: RBBracketedMethodParser [ skipToken: tokenValue [ currentToken isValue ifFalse: [^false]. (currentToken value = tokenValue) ifTrue: [self step. ^true] ifFalse: [^false] ] skipExpectedToken: tokenValue [ (self skipToken: tokenValue) ifFalse: [self parserError: ('expected ' , tokenValue asSymbol)] ] parseMethodInto: methodNode [ self skipExpectedToken: $[. super parseMethodInto: methodNode. self skipExpectedToken: $]. ^methodNode ] ] Eval [ RBScanner initialize ] smalltalk-3.2.5/packages/stinst/parser/ChangeLog0000644000175000017500000010255112130343734016602 000000000000002013-02-10 Holger Hans Peter Freyther * OldSyntaxExporter.st: Reformat the method node in OldSyntaxExporter>>#oldSyntaxSourceCodeFor:. * RewriteTests.st: Add the TestRewrite class. * package.xml: Add the TestRewrite test to the testsuite. 2013-01-29 Holger Hans Peter Freyther * STLoaderObjs.st: Put class variables into the classVars array. 2013-01-29 Holger Hans Peter Freyther * Exporter.st: Add FileOutExporter class>>#fileOutComment:to:. * SqueakExporter.st: Re-implement the SqueakSyntaxExporter class>>#fileOutComment:to: using chunks. 2012-10-06 Holger Freyther * SqueakExporter.st: Use 'as yet unclassified' as category string if it is nil. 2012-10-02 Holger Freyther * GSTParser.st: Change GSTFileInParser>>#parseClassTag to parse more complicated pragmas. 2012-09-29 Holger Freyther * RBParser.st: Add RBScanner>>#digitValue:. * SqueakParser.st: Reimplement SqueakFileInScanner>>#digitValue:, SqueakFileInScanner>>#isDigit:base:. Parsing of 16rff is now possible. 2012-09-09 Holger Freyther * STLoaderObjs.st: Add LoadedBehavior>>#article. 2011-11-10 Gwenael Casaccio Paolo Bonzini * STSymTable.st: Use #scopeDictionary. 2011-09-26 Paolo Bonzini * GSTParser.st: Do not shortcut evaluation of class tags to #evaluateMessageOn:selector:arguments:. 2011-09-24 Holger Hans Peter Freyther * STCompiler.st: Do not attempt inlining of #to:do: if the block argument is not a literal. 2011-09-24 Paolo Bonzini * STCompiler.st: Do not attempt inlining of boolean methods if the arguments are not literal blocks. Reported by Holger Freyther. 2011-04-21 Paolo Bonzini * STCompiler.st: Compile nil, true and false using short sequences. This also avoids that nil is entered in the literals table, for example when compiling "x := nil". 2011-04-21 Paolo Bonzini * STCompiler.st: Fix detection of return at the end of a "then" branch. 2011-04-21 Paolo Bonzini * STCompiler.st: Fix and extract inlining of #repeat. * STCompLit.st: Enable it. 2011-04-21 Paolo Bonzini * STSymTable.st: Add and use LiteralDictionary. 2011-02-06 Holger Hans Peter Freyther * STLoader.st: Look through the return statement. 2010-12-13 Paolo Bonzini * STFileParser.st: Add return tag to doits, thus fixing Behavior>>#evaluate: when using the STInST compiler. * GSTParser.st: Look beyond return tag. * SIFParser.st: Look beyond return tag. * SqueakParser.st: Look beyond return tag. 2010-12-04 Paolo Bonzini * package.xml: Remove now superfluous tags. 2010-10-16 Paolo Bonzini * STLoaderObjs.st: Add UndefinedClassWarning and use it to return a (not quite) reasonable value from UndefinedClass>>#superclass. 2010-09-13 Holger Hans Peter Freyther * GSTParser.st: GSTFileInParser>>parseClassTag pass the argument as a Smalltalk object. 2010-08-26 Paolo Bonzini * STLoader.st: Resolve PPFailure classSide properly. #classSide was added in to Squeak in 2004 and is used in packages like PetitParser and Magritte. 2010-08-26 Holger Hans Peter Freyther * SqueakParser.st: Handle binary selector with more than two charachters. This is required for ANSI Smalltalk and will allow to import PetitParser. 2010-06-22 Gwenael Casaccio * RBParser.st: Accept non-decimal floats. 2010-06-22 Paolo Bonzini * STEvaluationDriver.st: New, moved from Compiler package. 2010-06-17 Paolo Bonzini * RBToken.st: Add #isValue. * RBParser.st: Use it. 2010-03-01 Gwenael Casaccio * STDecompiler.st: Fix some errors. 2010-01-01 Paolo Bonzini * Update copyright years. 2009-10-27 Lee Duhem Paolo Bonzini * Extensions.st: Add #formattedSourceStringAt:ifAbsent:. 2009-10-02 Paolo Bonzini * OldSyntaxExporter.st: Fix emission of nil categories. 2009-09-13 Paolo Bonzini * STLoaderObjs.st: Implement #inheritShape and #kindOfSubclass. Implement #shape for proxy classes, default it to nil. 2009-09-10 Paolo Bonzini * OldSyntaxExporter.st: Remove category pragmas. 2009-09-10 Paolo Bonzini * SqueakExporter.st: Fix filing out uncommented classes. 2009-09-10 Paolo Bonzini * NewSyntaxExporter.st: Remove #fileOutHeader calls. * OldSyntaxExporter.st: Remove #fileOutHeader calls. 2009-09-07 Paolo Bonzini * Extensions.st: Fix pasto. 2009-09-07 Paolo Bonzini * Exporter.st: Remove #fileOutHeader. * Extensions.st: Place the header here. 2009-09-07 Paolo Bonzini * NewSyntaxExporter.st: Do not write useless shape pragmas. 2009-07-27 Paolo Bonzini * SqueakExporter.st: New. 2009-07-27 Paolo Bonzini * OldSyntaxExporter.st: Group methods by category. 2009-07-27 Paolo Bonzini * STLoaderObjs.st: Implement #isOldSyntax. 2009-07-27 Paolo Bonzini * NewSyntaxExporter.st: Do not disable #initialize in FormattingExporter. 2009-07-27 Paolo Bonzini * OldSyntaxExporter.st: New. 2009-07-27 Paolo Bonzini * Exporter.st: Extract parts to... * NewSyntaxExporter.st: ... here * Extensions.st: ... and here. * package.xml: Update. 2009-07-07 Paolo Bonzini * STCompiler.st: Fix new syntax categories, reported by Stefan Schmiedl. 2009-06-07 Paolo Bonzini * STCompiler.st: Send #asSourceCode to the method's source code. * STFileParser.st: Define a MappedSourceCode class and use it instead of MappedCollection. Define #segmentFrom:to: for Stream. Define #asSourceCode for any object. * STLoaderObjs.st: Remove #methodSourceString hack involving MappedCollection. 2009-06-07 Paolo Bonzini * GSTParser.st: Fix compilation of class variables. 2009-06-07 Paolo Bonzini * GSTParser.st: Accept no period at end of class variable if before ]. 2008-08-13 Paolo Bonzini * STLoaderObjs.st: Add more functionality to UndefinedMetaclass. 2008-07-28 Paolo Bonzini * RBParser.st: Parse negative numbers as unary minus + number. Simplify RBScanner>>#scanNumberValue; fix bugs in ScaledDecimals. 2008-05-18 Stephen Compall * GSTParser.st: Support namespace pragmas. 2008-05-17 Stephen Compall * PoolResolutionTests.st: Test for namespace shared pools. 2008-04-27 Stephen Compall * STSymTable.st: Create VariableBindings directly to add to Undeclared; don't rely on it to convert plain Associations. 2008-04-25 Paolo Bonzini * STFileParser.st: Create FileSegments with Files in it. 2008-04-25 Stephen Compall * PoolResolutionTests.st: Test the importation of shared pools and class pools from superclasses, as well as that only the direct superclass's namespaces are eliminated from the namespace walk. * STSymTable.st: Factor pool binding search into a separate class hierarchy, allowing global and class-by-class setting. By default, use newly-created semantics for pool search. * PoolResolutionTests.st: New file, testing the above. 2008-02-08 Stephen Compall * GSTParser.st: Always reverse a #methodsFor: with an #endMethodList when compiling new-syntax methods. 2008-02-05 Paolo Bonzini * SqueakParser.st: Fix parsing of binary message at end of chunk. 2008-02-05 Paolo Bonzini * STLoaderObjs.st: Add missing method #methodFormattedSourceString for polymorphism with CompiledMethod. 2008-01-27 Stephen Compall * Exporter.st: Comment or private-ize uncommented methods. 2008-01-18 Paolo Bonzini * GSTParser.st: Don't add an existing namespace when parsing "Namespace current: ... [ ]". 2008-01-18 Paolo Bonzini * STLoader.st: Add #fullyDefinedLoadedClasses. * STLoaderObjs.st: Add #fullyDefinedLoadedClasses. 2007-10-21 Paolo Bonzini * Exporter.st: Add #methodFormattedSourceString and use it. Add #parserClass. * GSTParser.st: Support adding more instance variables to a class. * RBParser.st: Add RBBracketedMethodParser. * SIFParser.st: Send #noteOldSyntax to compiled methods. * STFileParser.st: Return compiled methods from #compile:. Add #resolveClass:. Send #noteOldSyntax to compiled methods. * STLoader.st: Return compiled methods from #compile:. * STLoaderObjs.st: Add dummy #noteOldSyntax method to LoadedMethod. 2007-10-13 Paolo Bonzini * GSTParser.st: Invert true/false in previous checkin. * STLoaderObjs.st: Extract category from parsed methods. 2007-10-12 Paolo Bonzini * GSTParser.st: Don't replace instance variables except in the first declaration inside a subclass declaration. 2007-10-08 Paolo Bonzini * STFileParser.st: Look for EOF in #parseSmalltalk. * GSTParser.st: Use #parseDoits instead of #parseSmalltalk. Leave #parseDoits if looking at a close bracket. 2007-10-08 Paolo Bonzini * GSTParser.st: Look for class extensions before "Namespace" blocks. 2007-10-05 Paolo Bonzini * STLoader.st: Add no-category class creation methods. * STLoaderObjs.st: Fix override of non-existent method in UndefinedClass. Add no-category class creation methods. 2007-09-02 Stephen Compall * STCompiler.st: Jump past #true bytes after ifFalse: branch in #ifFalse:ifTrue:, not #false bytes. 2007-08-20 Paolo Bonzini * STCompiler.st: User store+pop+push sequence for pushing literal variables. 2007-08-13 Paolo Bonzini * STLoader.st: Create undefined namespaces. * STLoaderObjs.st: Support creating undefined classes in arbitrary namespaces. 2007-08-13 Paolo Bonzini * STLoaderObjs.st: Add one more #classPragmas implementation. 2007-08-12 Paolo Bonzini * Exporter.st: Use #classPragmas to emit class metadata. * RBFormatter.st: Use #storeLiteralOn:. * STLoader.st: Support the CStruct creation method. * STLoaderObjs.st: Likewise, and add #classPragmas. 2007-08-10 Paolo Bonzini * RBParser.st: Convert to FloatD if there is no exponent. 2007-08-09 Paolo Bonzini * STFileParser.st: Change #parseDoit: to #parseDoit, change #parseStatements to include only the block it had inside, localize MappedCollection hack in a single place. * SIFParser.st: Change #parseStatements to #parseDoit. * GSTParser.st: Override #evaluate: to include comments. Don't create MappedCollection here. Split part of #parseStatements into a #parseDoit override. 2007-08-08 Daniele Sciascia * RBParser.st: Add #parseMethodInto:. * STFileParser.st: Support "self evaluate: nil". Only skip "!" after evaluating. Add #currentNamespace. * STLoader.st: Handle #addClassVarName:value:. * STLoaderObjs.st: Add #collectCategories. * GSTParser.st: New. 2007-08-08 Paolo Bonzini * STLoaderObjs.st: Override #isMetaclass together with #isClass. 2007-08-06 Paolo Bonzini * STLoader.st: Accept a non-proxy namespace in #currentNamespace:. Add #loadedClasses. * STLoaderObjs.st: Ensure #nameIn: returns a string. 2007-07-18 Stephen Compall * STCompiler.st: Rename #compileString: et al to #primCompile:, and change uses accordingly. 2007-07-17 Stephen Compall * STCompiler.st: Add #canCompile: to STCompiler class. (#compileBoolean:) Don't put receiver's bytecodes if refusing to optimize the given message send. (#compileTimesRepeat:, #compileLoop:): Likewise. 2007-07-13 Paolo Bonzini * STFileParser.st: Don't call #step before evaluating. * SqueakParser.st: Refine ! parsing. * STLoaderObjs.st: Add more methods required by converter. 2007-07-13 Paolo Bonzini * STLoaderObjs.st: Fix PseudoBehavior>>#subclasses. 2007-07-12 Paolo Bonzini * Exporter.st: Do not call #environment when not filing out the complete class. Indentation fixes. * STLoader.st: Create an UndefinedClass object if there is no namespace and the class is not found in the current namespace. * STLoaderObjs.st: Move methods variable up to PseudoBehavior. Make metaclass of ProxyClass a ProxyClass itself. Add UndefinedClass and UndefinedMetaclass. Turn subclasses of PseudoBehavior into an OrderedCollection. 2007-07-12 Paolo Bonzini * SqueakParser.st: Fix parsing of comments. 2007-06-27 Paolo Bonzini * SIFParser.st: New. * SqueakParser.st: Use super. * STFileParser.st: Split part of #parseMethodDefinitionList into a separate method. * Exporter.st: Fix indentation of class-instance variables. Don't emit form feed character. 2007-06-25 Paolo Bonzini * STFileParser.st: Use #%. 2007-06-23 Stephen Compall * RBParseNodes.st (RBMethodNode>>#primitiveSources): Handle MappedCollections as source instead of FileSegments. * StartCompiler.st (STParserScanner): New class. Use it to allow other parsers to rescan tokens from some parser. (STEvaluationDriver>>#methodsFor:parsingWith:compiler:class:): Add parsingWith: argument and handle separation of evaluate:/compile: driver and parser. (Behavior>>#methodsFor:ifTrue:): Send to the driver, not the parser. 2007-06-20 Paolo Bonzini * STFileParser.st: Refactor part of #parseDoits into the superclass. 2007-06-09 Paolo Bonzini * Exporter.st: Use #parseNodeAt: to access the method parse tree. Define it for Behavior and #methodParseNode for CompiledMethod. * STFileParser.st: Use MappedCollection trick for method source too. Look at the token type to distinguish '!' from other tokens. * STLoaderObjs.st: Store an RBMethodNode in LoadedMethod objects. * STLoaer.st: Adjust for above change to LoadedMethod. * SqueakParser.st: New. 2007-06-08 Paolo Bonzini * RBParser.st: Move file-in related stuff... * STFileParser.st: ... here. Add STParsingDriver hierarchy. * STLoader.st: Make STInterpreter an STParsingDriver. * StartCompiler.st: Rename STFileInParser to STEvaluationDriver and make it a subclass of STParsingDriver. 2007-06-08 Paolo Bonzini * Exporter.st: emit superclass name relative to namespace of the current class. * STLoader.st: track defaultNamespace as a proxy which is set up at the *beginning* of the processing. * STLoaderObjs.st: redefine PseudoBehavior>>#nameIn: as it is done for PseudoNamespace. 2007-06-07 Paolo Bonzini * RBParser.st: Really fix doit parsing. 2007-06-07 Paolo Bonzini * RBFormatter.st: Add #formatAll:. * RBParser.st: Fixes to doit parsing. 2007-05-25 Paolo Bonzini * Exporter.st: Fix output spacing. 2007-05-25 Daniele Sciascia * Exporter.st: New. * STLoaderObjs.st: Eliminate file-out code. 2007-05-25 Daniele Sciascia * RBFormatter.st: fix various bugs. Reformat method comments. Support varying the overall indentation. * RBParseNodes.st: store category in RBMethodNode. * RBParser.st: support storing a method category. Rewrite parseDoits to deal with comments correctly (almost). * RBToken.st: fix bug in handling of #{...}. * STLoader.st: Replace #unknownTo:selector:arguments: with #unknown:. Store a proxy for the nil superclass. Add various methods used by the converter. * STLoaderObjs.st: Add ProxyNilClass. Store selector in LoadedMethod. Add various #copyEmpty: methods. 2007-05-24 Paolo Bonzini * ParseTreeSearcher.st: Add #capacity to RBSmallDictionary. 2007-05-24 Paolo Bonzini * RBParseNodes.st: Wasn't thinking straight when I made the last change. 2007-05-23 Paolo Bonzini * STLoaderObjs.st: Don't use TokenStream. 2007-05-23 Paolo Bonzini * RBParseNodes.st: Add #deepCopy. Our #copy is as deep as it needs to be. 2007-05-22 Stephen Compall Paolo Bonzini * RewriteTests.st: New. * ParseTreeSearcher.st: Fix two bugs. 2007-05-14 Paolo Bonzini * STLoader.st: Update for class shapes, add new methods. * STLoaderObjs.st: Update for class shapes, add new methods. 2007-04-16 Stephen Compall Paolo Bonzini * OrderedSet.st: Added (by Stephen Compall). * STSymTable.st: Use it. 2007-04-08 Stephen Compall * STSymTable.st: Add superclass environments and shared pools to global variable search. * RBParser.st: Reset `tags' instance variable before each method parse in a method definition list. 2007-03-19 Paolo Bonzini * STCompiler.st: Remove unused class variable. * STLoader.st: Likewise. * STSymTable.st: Likewise. 2007-02-18 Stephen Compall * RBParseNodes.st: Fix off-by-one in RBMethodNode>>#primitiveSources when source is a FileSegment. 2007-01-31 Paolo Bonzini * STCompiler.st: Avoid that #compileAttribute: shadows an instance variable with a temporary. 2007-01-12 Stephen Compall * ParseTreeSearcher.st: Use the visit*:onMatch: variants of visit*: in accept*Node: methods of ParseTreeRewriter. Add visitNode:onMatch:. 2007-01-11 Paolo Bonzini * ParseTreeSearcher.st: Refine the previous refactoring. 2007-01-11 Paolo Bonzini Stephen Compall * ParseTreeSearcher.st: Refactor in order to not modify the parse trees when nothing changes. 2007-01-10 Paolo Bonzini * ParseTreeSearcher.st: Port RBSmallDictionary to GNU Smalltalk. #copy and causing the dictionary to grow failed. Reported by Stephen Compall. 2007-01-02 Paolo Bonzini Stephen Compall * RBParseNodes.st: Fix for stream-based compilation, where a method's start offset is >1. * RBParser.st: Add #currentToken accessor, and the #parseBinaryMessageNoGreater hack. * STCompiler.st: Compile method attributes. 2007-01-02 Stephen Compall * STSymTable.st: Warn for shadowing variable, fix "duplicate variable name" warning and turn it into an error. 2006-12-31 Paolo Bonzini Stephen Compall * STSymTable.st: Handle undeclared variables without a path. Fix order of instance variables. * STCompiler.st: Fix off-by-one error in compiling RBArrayConstructorNodes. * ParseTreeSearcher.st: Rename acceptArrayNode: to acceptArrayConstructorNode:. * RBFormatter.st: Likewise. * RBParseNodes.st: Likewise. 2006-12-31 Paolo Bonzini * STCompLit.st: Don't use "nil" slots from VMSpecialMethods. * STCompiler.st: Remove dupReceiver. Adjust for above change. Compile receiver in compileTimesRepeat: and compileLoop:, test for receiver being a block in compileWhileLoop:. Extract part of acceptMessageNode: to compileMessage:. Compile receiver in acceptCascadeNode: and call compileMessage: to avoid compiling the receiver of a cascaded message repeatedly (reported by Stephen Compall). 2006-12-05 Paolo Bonzini *** Version 2.3 released. 2006-12-05 Paolo Bonzini * STCompiler.st: Pass current environment in evaluate:parser:, add #compile:asMethodOf:classified:parser:environment: and don't inline its functionality elsewhere. * STParser.st: Parse leading _ as assignment. * StartCompiler.st: Pass current environment when compiling doits. 2006-09-15 Paolo Bonzini * STCompiler.st: Rethink previous change. 2006-09-13 Paolo Bonzini * STCompiler.st: Adapt for new super send. * StartCompiler.st: Support streams in #compile: * STDecompiler: Don't use dead method nextByteCodeIndex:, add new hook #lineNo:with:, rewrite #merge:, support #timesRepeat: decompilation, fix case where return bytecodes leave the previous sdtatement on the stack. Last but not least, adapt for new super send. 2006-07-20 Paolo Bonzini * StartCompiler.st: define #fileIn in Stream. 2006-07-17 Paolo Bonzini * RBParser.st: support $<123> syntax. 2006-07-10 Paolo Bonzini * STLoaderObjs.st: new class OverlayDictionary allows to add extensions and redefinitions to base classes. 2003-09-24 Paolo Bonzini * STCompiler.st: adapt to new bytecode set. Fix bugs and refactor the code along the way. 2003-09-13 Paolo Bonzini * STDecompiler.st: remove unused callbacks for disassembling bytecodes. 2003-06-22 Paolo Bonzini * STSymTable.st: use STVariables to store instance variables. * STCompiler.st: check whether storing is allowed for every variable. 2003-06-05 Paolo Bonzini * STCompiler.st: compile blocks by pushing the CompiledBlock directly. 2003-05-09 Paolo Bonzini *** Version 2.1.2 released. 2003-04-17 Paolo Bonzini *** Version 2.1.1 (stable) released. 2003-04-12 Paolo Bonzini *** Version 2.1 (stable) released. 2003-01-04 Paolo Bonzini * RBParser.st: provide default implementation for #evaluate: 2002-11-15 Paolo Bonzini * STCompiler.st: compile RBOptimizedNodes 2002-10-08 Paolo Bonzini * STLoaderObjs.st: adapt to recent changes in the layout of Namespace. 2002-09-21 Paolo Bonzini * STDecompiler.st: new file 2002-09-13 Paolo Bonzini *** Versions 2.0c (development) and 2.0.6 (stable) released * STSymTable.st: added namespace syntax support. * STCompiler.st: pass `self' along to the symbol table. * test.st: test namespace syntax 2002-09-13 Paolo Bonzini * RBParser.st: added namespace syntax support. * STLoader.st: support namespace syntax. 2002-09-06 Paolo Bonzini * RBTests.st: new file 2002-08-19 Paolo Bonzini * STLoader.st: separate into a superclass, STInterpreter, and a subclass (the old STClassLoader) 2002-08-14 Paolo Bonzini *** Version 2.0.5 (stable) released 2002-08-12 Paolo Bonzini *** Version 2.0b (development) released 2002-08-07 Paolo Bonzini *** Versions 2.0a (development) and 2.0.4 (stable) released 2002-07-17 Paolo Bonzini *** Version 2.0.3 released 2002-07-15 Paolo Bonzini * STCompiler.st: rewritten as a RBProgramNodeVisitor * STLoader.st: modified to use RBProgramNodes * RBFormatter.st: added hacks to print #{...} * RBToken.st: added hacks to resolve #{...} at compile-time * RBParseNodes.st: added hacks to resolve #{...} at compile-time 2002-07-14 Paolo Bonzini * RBParser.st: ported * RBParseNodes.st: ported * RBFormatter.st: ported * ParseTreeSearcher.st: ported * RBToken.st: ported * STParser.st: part deleted, part moved to StartCompiler.st * STParseNodes.st: deleted * STTok.st: deleted * STToken.st: deleted * STFormatter.st: deleted * STVisitor.st: deleted 2002-07-11 Paolo Bonzini *** Version 2.0.2 released 2002-07-03 Paolo Bonzini * STTok.st: parse scaled decimal literals correctly. 2002-06-28 Paolo Bonzini *** Version 2.0.1 released 2002-06-25 Paolo Bonzini *** Version 2.0 released 2002-05-11 Paolo Bonzini *** Version 1.96.6 released 2002-04-14 Paolo Bonzini *** Version 1.96.5 released 2002-03-12 Paolo Bonzini *** Version 1.96.4 released 2002-01-29 Paolo Bonzini *** Version 1.96.3 released. 2002-01-04 Paolo Bonzini *** Version 1.96.2 released 2002-01-02 Paolo Bonzini * Load.st: put everything in the STInST namespace * StartCompiler.st: use the STInST namespace 2001-12-11 Paolo Bonzini * STLoaderObjs.st: implement #= and #hash for ProxyClass and ProxyNamespace. * STParser.st: compile correctly { a. b. } (with a dot before the closed brace). 2001-12-01 Paolo Bonzini * STParser.st: compute FileSegments correctly (include the first token in the selector and don't include the bang) 2001-11-29 Paolo Bonzini * STParser.st: parse arrays according to the ANSI standard. * STLoader.st: new file * STLoaderObjs.st: new file 2001-11-20 Paolo Bonzini *** Version 1.96.1 released * test.st: moved from unsupported/misc/Compiler.st 2001-11-13 Paolo Bonzini * STFormatter.st: prefixed # to symbols in arrays * STTok.st: prefixed # to symbols in arrays * STToken.st: prefixed # to symbols in arrays 2001-02-23 Paolo Bonzini *** Released version 1.95.3 2001-02-19 Paolo Bonzini * STParser.st: use the ability of #perform: & friends to receive a CompiledMethod as their first parameter. * STCompiler.st: added #compiled:asMethodOf:classified:parser: which does not install the new CompiledMethod in the Behavior specified in the second parameter. * STCompiler.st: fixed a few compilation bugs (cascades, #whileTrue:, outer temporaries). * STCompLit.st: StoreVariable and PopStoreVariable were inverted. * StartCompiler.st: support pluggable parser & compiler classes * STParser.st: support pluggable parser & compiler classes 2001-01-31 Paolo Bonzini * STCompiler.st: compile STBindingNodes. * STParseNodes.st: defined STBindingNode. * STParser.st: generate STBindingNode. * STVisitor.st: defined #variableBinding: visiting method. * STFormatter.st: defined #variableBinding: visiting method. 2001-01-30 Paolo Bonzini *** Released version 1.95.1 2000-11-01 Paolo Bonzini * STToken.st: added STOpenBraceTok and STCloseBraceTok. * STTok.st: recognize STOpenBraceTok and STCloseBraceTok. * STParser.st: generate STArrayNodes. * STParseNodes.st: defined STArrayNode. * STCompiler.st: compile STArrayNodes. * STVisitor.st: defined #braceArray: visiting method. * STFormatter.st: defined #braceArray: visiting method. 2000-08-08 Paolo Bonzini * STParseNodes.st: refactored STBlockNode and STMethodBodyNode to have a common superclass, STCompoundNode. Implemented STCompundNode. * STCompiler.st: modified compilation of conditionals to please the JIT compiler (see libgst/ChangeLog). 2000-07-02 Paolo Bonzini * STTok.st: parse scaled decimal correctly 2000-06-17 Paolo Bonzini *** Released versions 1.95 (development) and 1.7.5 (stable) 2000-04-12 Paolo Bonzini (bonzini@gnu.org) * STVisitor.st: added support for comments 2000-04-10 Paolo Bonzini (bonzini@gnu.org) * STFormatter.st: created * STVisitor.st: added STVisitingParser 1999-12-31 Paolo Bonzini * STFileInParser.st: split between STParser.st and StartCompiler.st (so that the class itself is loaded together with the Parser package, even though it is not activated). * STSymTable.st: use an IdentitySet for storing pool dictionaries. 1999-12-27 Paolo Bonzini * STCompiler.st: new way of compiling blocks. 1999-12-21 Paolo Bonzini * STParser.st: added STPluggableParser, derivated from the syntax highlighter. 1999-12-05 Paolo Bonzini * STTok.st: parse stuff like 1.0d53 and 1.0q212 correctly even though FloatD/FloatE/FloatQ is not supported yet. 1999-11-11 Paolo Bonzini * STCompiler.st: added another delegation method for warnings. * STParser.st: added warnings (nothing is done with them yet, but the methods are there). * STSymTable.st: duplicate var names produce a warning. 1999-10-30 Paolo Bonzini * STParser.st: save the last STParseNode that was generated * STParseNode.st: added the `comments' variable 1999-10-22 Paolo Bonzini * STSymTable.st: fixed bug with undeclared variables (error when the undeclared variable's name had not been interned as a symbol) * STVisitor.st: created * Load.st: load STVisitor.st 1999-10-13 Paolo Bonzini * STParser.st: added ability to read comment tokens and removed methods that test for particular kinds of tokens (#isBinaryOperator: and #isSymbolId:) * STTok.st: now passes comment tokens to STParser * STToken.st: reworked token hierarchy to add polymorphic methods that replace STParser's old #isBinaryOperator: and #isSymbolId:. Hope to get not only elegance, but also a bit of speed. 1999-10-11 Paolo Bonzini * STSymTable.st: added code to handle `Undeclared'. * STFileInParser.st: tell STSymbolTable to recognize `Undeclared' inside file-ins. 1999-09-11 Paolo Bonzini * STSymTable.st: implementation of namespaces 1999-09-02 Paolo Bonzini * STParser.st: added support for [ :a :b || temp1 temp2 | ]. 1999-05-13 Paolo Bonzini * STCompLit.st: First changes to support loop optimization * STCompiler.st: First changes to support loop optimization * STParseNodes.st: First changes to support loop optimization 1999-04-22 Paolo Bonzini * STCompiler.st: modified to support recent changes in the bytecode set. * STCompLit.st: same as above. 1999-03-03 Paolo Bonzini * STCompiler.st: added stack depth tracing. 1999-02-16 Paolo Bonzini * STCompLit.st: added support for > 64 literals (BigLiteral) * STCompiler.st: added support for > 64 literals (compileBigLiteral:) 1999-02-14 Paolo Bonzini * STParser.st: Selectors stay Strings. The compiler turns them to Symbols. 1999-02-13 Paolo Bonzini * STSymTable.st: changed to use new #isSymbolString: method for Symbol 1999-02-09 Paolo Bonzini * STParser.st: Removed usage of Tokenizer's recording capability, since Tokenizer no more has that capability... 1999-02-03 Paolo Bonzini * Load.st: created. * STParser.st: Fixed bug in parsing binary message declarations. * STCompiler.st: fixed #compileString: to work with metaclasses. 1999-02-01 Paolo Bonzini * STFileInParser.st: created. 1999-01-26 Paolo Bonzini * STVariable.st: created to detect storing in an argument * STCompiler.st: in sync with the C compiler, storing into an argument is now detected as an error. Thanks to Andreas Klimas for signaling this to me!! 1998-11-24 Paolo Bonzini * STSymTable.st: perfected treating of class pools (now they're exactly the same as a shared pool dictionary) 1998-11-23 Paolo Bonzini * STCompiler.st: added STDoitCompiler 1998-11-06 Paolo Bonzini * STToken.st: Added code that supports new methods to find out the class of a token. * STParser.st: Switched most uses to isMemberOf: to special and faster methods. Split into STParser and STFileInParser to support other cases when parsing is necessary 1998-10-01 Paolo Bonzini * STParser.st: Added byte array constants * STTok.st: Fixed number parsing, changed parseError: to error: 1998-09-08 Paolo Bonzini * STParser.st: Fixed bugs which jumped out while testing the compiler (e.g. parseArrayLit returned OrderedCollections) * STTok.st: Now subclass of Tokenizer; renamed to STTok 1998-09-05 Paolo Bonzini * STCompiler.st: moved compilation policy to subclasses of STParseNode. Now compile (which is called compile:) returns a CompiledMethod. Added STFakeCompiler. * STCompLit.st: merged VMStorageLocations and VMSpecialIndices into VMOtherConstants, added VMSpecialMethods * STParseNodes.st: switched to a single node (STConstNode) for constants, cleaned up unused classes, renamed Selector to SelectorNode. Added support for storing source code. 1998-09-03 Paolo Bonzini * STParser.st: Switched to a single node for constants (STConstNode), two separate nodes for identifiers (STIdentifierNode and STSpecialIdentifierNode), changed pools quite a bit, prefixed ST to everything. * STSymTable.st: modified heavily to support new code in STCompiler 1995-09-04 Steve Byrne * STParseNodes.st: Switched to being externally accessible instead of supporting internal access only. 1995-09-03 Steve Byrne * STCompLit.st: created. * STCompiler.st: created. * STSymTable.st: created. smalltalk-3.2.5/packages/stinst/parser/STEvaluationDriver.st0000644000175000017500000001600112123404352021120 00000000000000"====================================================================== | | Smalltalk in Smalltalk compiler - STParsingDriver that evaluates code | | ======================================================================" "====================================================================== | | Copyright 1999,2000,2001,2002,2006,2007,2008, 2009 Free Software Foundation, Inc. | Written by Paolo Bonzini. | | This file is part of GNU Smalltalk. | | GNU Smalltalk is free software; you can redistribute it and/or modify it | under the terms of the GNU General Public License as published by the Free | Software Foundation; either version 2, or (at your option) any later version. | | GNU Smalltalk is distributed in the hope that it will be useful, but WITHOUT | ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS | FOR A PARTICULAR PURPOSE. See the GNU General Public License for more | details. | | You should have received a copy of the GNU General Public License along with | GNU Smalltalk; see the file COPYING. If not, write to the Free Software | Foundation, 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. | ======================================================================" Object subclass: STParserScanner [ | parser scanner unusedTokens |
      '] ifFalse: [self << '']] ifFalse: [self addCurrentChar] ] processPound [ self atLineStart ifFalse: [^self addCurrentChar]. inNumbers ifFalse: [self << '
        '; nl. inNumbers := true]. self << '
      1. ' ] emitLink: linkAddress [ | currentTitle | (self isImage: linkAddress) ifTrue: ["graphic image link" (self isExternalAddress: linkAddress) ifTrue: [^self << ''] ifFalse: [^self << '']]. (wiki hasPageTitled: linkAddress) ifTrue: ["simple one piece existing link" currentTitle := self wiki currentTitleOf: linkAddress. self linkTo: [self << self wiki; << $/; nextPutUrl: currentTitle] titled: [self << currentTitle]] ifFalse: ["simple one piece non existant link" self << '' << linkAddress << ''. self linkTo: [self << self wiki; << '/CREATE/'; nextPutUrl: linkAddress] titled: [self << $?]] ] emitLink: linkName to: linkAddress [ | currentTitle | (wiki hasPageTitled: linkAddress) ifTrue: ["two piece existing link" currentTitle := self wiki currentTitleOf: linkAddress. self linkTo: [self << self wiki; << $/; nextPutUrl: currentTitle] titled: [self << linkName]] ifFalse: ["two piece non existant link" self << '' << linkName << ''. self linkTo: [self << self wiki; << '/CREATE/'; nextPutUrl: linkAddress] titled: [self << $?]] ] sendBody [ self emitStart. self emitIcons. self emitTitle. self emitContents. self emitSearch: ''. self emitFinish ] emitCommand: commandName text: textString [ ^self emitIcon: [self << self wiki filesPath << $/ << commandName asLowercase << '.jpg'] linkTo: [self emitUrlForCommand: commandName] titled: [self << textString] ] emitIcons [ self emitIconsStart. self emitCommonIcons. self emitCommand: 'EDIT' text: 'Edit this page'. self emitCommand: 'RENAME' text: 'Rename this page'. self emitCommand: 'HISTORY' text: 'History of this page'. self emitIconsEnd ] emitContents [ contentStream := self page contents readStream. [contentStream atEnd] whileFalse: [self processNextChar]. lastChar == Character nl ifFalse: [self processNl]. contentStream := nil ] emitTitle [ self heading: [self linkTo: [self emitUrlForCommand: 'REFS'] titled: [self << self page title]] ] initialize [ super initialize. heading := nil. inBullets := inNumbers := inTable := false ] ] WikiHTML subclass: WikiAbsentPageHTML [ browserTitle [ ^self wikiName , ': `' , self pageTitle , ''' not found' ] pageTitle [ ^request location last ] sendResponseType [ self << 'HTTP/1.1 404 Not Found'; nl ] sendBody [ self emitStart. self emitIcons. self heading: [self << self wikiName << ' contains no page titled: "' << request location last] level: 2. self emitSearch: request location last. self emitFinish ] ] WikiHTML subclass: WikiReferencesHTML [ | referringPages | actualSearchString [ ^self searchString isEmpty ifTrue: [self searchString] ifFalse: ['*' , self searchString , '*'] ] findMatches [ | match | referringPages := SortedCollection sortBlock: [:a :b | a title < b title]. match := self actualSearchString. Processor activeProcess lowerPriority. wiki pagesDo: [:each | (each references: match) ifTrue: [referringPages add: each]]. Processor activeProcess raisePriority ] browserTitle [ | ws | ws := String new writeStream. ws nextPutAll: 'SEARCH '; nextPutAll: self wikiName; nextPutAll: ':"'; nextPutAll: self searchString; nextPut: $". ^ws contents ] sendBody [ self emitStart. self emitIcons. self emitMatchList. self emitSearch: self searchString. self emitFinish ] emitMatchList [ self findMatches. referringPages isEmpty ifTrue: [^self emitNoMatches]. self heading: [self << ('There %2 %1 reference%<|s>2 to the phrase:' % {referringPages size. referringPages size = 1})]. self << ' ...'; << self searchString; << '...'; lineBreak. self << '
          '; nl. referringPages do: [:each | self listItem: [self linkToPage: each]]. self << '
        '; nl ] emitNoMatches [ self << '

        No references to the phrase

        '; nl. self << ' ...'; << self searchString; << '...'; lineBreak ] searchString [ ^request postDataAt: #SEARCHPATTERN ifAbsent: [request location last] ] ] WikiPageHTML subclass: WikiVersionHTML [ page [ ^super page versionAt: self versionNumber ] emitIcons [ self emitIconsStart. self emitCommonIcons. self emitCommand: 'HISTORY' text: 'History of this page'. self emitPreviousVersion. self emitNextVersion. self emitIconsEnd ] emitNextVersion [ self versionNumber < (wiki pageTitled: self page title) versionNumber ifFalse: [^self]. self emitIcon: [self << self wiki filesPath << '/next.jpg'] linkTo: [self emitUrlForVersionNumber: self versionNumber + 1] titled: [self << 'Previous'] ] emitPreviousVersion [ self versionNumber <= 0 ifTrue: [^self]. self emitIcon: [self << self wiki filesPath << '/prev.jpg'] linkTo: [self emitUrlForVersionNumber: self versionNumber - 1] titled: [self << 'Previous'] ] emitTitle [ self heading: [self linkTo: [self emitUrlForCommand: 'REFS'] titled: [self << self page title]. self << ' (Version ' << self versionNumber << ')'] ] versionNumber [ ^((request postDataAt: #n) asNumber max: 0) min: super page versionNumber ] emitUrlForVersionNumber: aNumber [ self << self wiki << '/VERSION/' << self encodedPageTitle << '?n=' << aNumber ] ] WikiHTML subclass: WikiChangesHTML [ numberOfChanges [ ^20 ] numberOfDays [ ^7 ] pageTitle [ ^'Recent Changes' ] sendBody [ | day genesis minDate changesShown | self emitStart. self emitIcons. self emitChanges. self emitSearch: ''. self emitFinish ] emitChangedPage: aPage [ self listItem: [self linkToPage: aPage; space. self << aPage timestamp asTime << ' (' << aPage author << ')'] ] emitChanges [ | day genesis minDate changesShown | self heading: [self << 'Recent Changes']. genesis := wiki startDate printNl. day := Date today. minDate := (day subtractDays: self numberOfDays) printNl. changesShown := 0. [day < genesis ifTrue: [^self]. day >= minDate or: [changesShown < self numberOfChanges]] whileTrue: [changesShown := changesShown + (self emitChangesFor: day). day := day subtractDays: 1] ] emitChangesFor: aDate [ | sc | sc := SortedCollection new sortBlock: [:a :b | a timestamp > b timestamp] wiki pagesDo: [:each | each timestamp asDate = aDate ifTrue: [sc add: each]]. sc isEmpty ifFalse: [self heading: [(self responseStream) nextPutAll: aDate monthName; space; print: aDate day; space; print: aDate year] level: 3. self << '
          '; nl. sc do: [:each | self emitChangedPage: each]. self << '
        '; nl]. ^sc size ] ] WikiHTML subclass: WikiErrorHTML [ browserTitle [ ^self pageTitle ] emitDescription [ self << 'The '; << self wiki; << ' wiki is not able to process this request. '. self << 'This can be due to a malformed URL, or (less likely) to an internal server error'. self lineBreak; lineBreak. self << 'originator: '; << request originator displayString; lineBreak. self << 'action: '; << request action displayString; lineBreak. self << 'location: '. request location do: [:each | self << $/ << each]. self lineBreak. request enumeratePostData: [:key :val | self lineBreak; << key; << ' = '; nl; << val; nl]. self lineBreak; horizontalLine; italic: [self << WebServer version] ] pageTitle [ ^'Bad request' ] sendBody [ self emitStart. self emitIcons. self emitDescription. self emitFinish ] ] WikiHTML subclass: WikiRenameConflictHTML [ newTitle [ ^request postDataAt: #NEWTITLE ] emitDescription [ self heading: [self << 'This name ('. self linkTo: [self << self wiki << $/ << self newTitle] titled: [self << self newTitle]. self << ') is in use already. Sorry, cannot complete this rename.'] level: 2 ] sendBody [ self emitStart. self emitIcons. self emitDescription. self emitSearch: self newTitle. self emitFinish ] ] WikiHTML subclass: WikiCommandHTML [ browserTitle [ ^super browserTitle , self titleSuffix ] titleSuffix [ ^self subclassResponsibility ] ] WikiCommandHTML subclass: WikiEditHTML [ titleSuffix [ ^' (edit)' ] emitForm [ self heading: [self << 'Edit '. self linkTo: [self emitUrlForCommand: 'REFS'] titled: [self << self pageTitle]]. self << 'Don''t know how to edit a page? Visit '; linkToPage: wiki syntaxPage; << '.'; nl. self << '
        '; nl. self << ''; nl. self << ''; lineBreak. self << ''; nl. self << '
        '; nl ] sendBody [ self emitStart. self emitIcons. self emitForm. self emitFinish ] ] WikiCommandHTML subclass: WikiHistoryHTML [ sendBody [ self emitStart. self emitIcons. self emitTitle. self emitTable. self emitSearch: ''. self emitFinish ] emitTitle [ self heading: [self << 'History of '. self linkTo: [self emitUrlForCommand: 'REFS'] titled: [self << self page title]] ] emitTable [ self << ''; nl. self << ''; nl. self td: [self << 'Version']; td: [self << 'Operation']; td: [self << 'Author']; td: [self << 'Creation Time']. self << ''; nl. self page versionsDo: [:each | self emitPageVersion: each]. self << '
        '; nl ] emitPageVersion: each [ self << '
      h1h2
      d1d2
      cap
      ' ] testCoreAttributesClass [ self assert: [:html | html div class: 'foo'] gives: '
      '. self assert: [:html | (html div) class: 'foo'; class: 'bar'] gives: '
      ' ] testCoreAttributesId [ self assert: [:html | html div id: 'foo'] gives: '
      '. self assert: [:html | (html div) id: 'foo'; id: 'bar'] gives: '
      '. self assert: [:html | self assert: html div ensureId = 'id1'] gives: '
      '. self assert: [:html | self assert: ((html div) id: 'foo'; ensureId) = 'foo'] gives: '
      '. self assert: [:html | self assert: ((html div) id: 'foo'; id) = 'foo'] gives: '
      '. self assert: [:html | self assert: html div id isNil] gives: '
      ' ] testCoreAttributesStyle [ self assert: [:html | html div style: 'left: 0'] gives: '
      '. self assert: [:html | (html div) style: 'left: 0'; style: 'top: 2'] gives: '
      ' ] testCoreAttributesTitle [ self assert: [:html | html div title: 'Seaside'] gives: '
      ' ] testEditTag [ self assert: [:html | html inserted: 'foo'] gives: 'foo'. self assert: [:html | html deleted: 'bar'] gives: 'bar' ] testEventAttributes [ self assert: [:html | (html div) onBlur: 1; onBlur: 2] gives: '
      '. self assert: [:html | (html div) onChange: 1; onChange: 2] gives: '
      '. self assert: [:html | (html div) onClick: 1; onClick: 2] gives: '
      '. self assert: [:html | (html div) onDoubleClick: 1; onDoubleClick: 2] gives: '
      ' ] testExtendedNesting [ self assert: [:html | html div: nil] gives: '
      '. self assert: [:html | html div: #(1 $a)] gives: '
      1a
      '. self assert: [:html | html div: [html span]] gives: '
      ' ] testFieldSetTag [ self assert: [:html | html fieldSet: 'foo'] gives: '
      foo
      '. self assert: [:html | (html fieldSet) legend: 'bar'; with: 'zork'] gives: '
      barzork
      ' ] testHeadingTag [ self assert: [:html | html heading] gives: '

      '. self assert: [:html | (html heading) level: 2; with: 'foo'] gives: '

      foo

      '. self assert: [:html | (html heading) level: 0; with: 'foo'] gives: '

      foo

      '. self assert: [:html | (html heading) level: 7; with: 'foo'] gives: '
      foo
      ' ] testHorizontalRuleTag [ self assert: [:html | html horizontalRule] gives: '
      ' ] testImageButton [ self assert: [:html | html imageButton] gives: '' ] testImageTag [ self assert: [:html | html image url: 'http://www.seaside.st/logo.jpeg'] gives: ''. self assert: [:html | (html image) title: 'Seaside'; altText: 'the Seaside logo'; url: 'http://www.seaside.st/logo.jpeg'] gives: 'the Seaside logo' ] testKeyboardAttributes [ self assert: [:html | html anchor accessKey: $a] gives: ''. self assert: [:html | html anchor tabIndex: 3] gives: '' ] testLabelTag [ self assert: [:html | html label: 'foo'] gives: ''. self assert: [:html | (html label) for: 'bar'; with: 'zork'] gives: '' ] testMultiSelectTag [ self assert: [:html | html multiSelect] gives: ''. self assert: [:html | html multiSelect list: #(1 2)] gives: ''. self assert: [:html | (html multiSelect) list: #(1 2); labels: [:v | 2 * v]] gives: ''. self assert: [:html | (html multiSelect) list: #(1 2); enabled: [:v | v even]] gives: ''. self assert: [:html | (html multiSelect) list: #(1 2); callback: [:v | ]] gives: '' ] testOrderedListTag [ self assert: [:html | html orderedList] gives: '
        '. self assert: [:html | html orderedList add: 1] gives: '
        1. 1
        '. self assert: [:html | html orderedList addAll: #(1 2)] gives: '
        1. 1
        2. 2
        '. self assert: [:html | html orderedList list: #(1 2)] gives: '
        1. 1
        2. 2
        '. self assert: [:html | (html orderedList) list: #(1 2); with: [html listItem: 3]] gives: '
        1. 1
        2. 2
        3. 3
        '. self assert: [:html | (html orderedList) add: 2; labels: [:e | 2 * e]] gives: '
        1. 4
        '. self assert: [:html | (html orderedList) add: 2; labels: [:e | 2 * e]; with: [html listItem: 5]] gives: '
        1. 4
        2. 5
        ' ] testParagraphTag [ self assert: [:html | html paragraph] gives: '

        '. self assert: [:html | html paragraph: 'foo'] gives: '

        foo

        ' ] testPasswordInput [ self assert: [:html | html passwordInput] gives: ''. self assert: [:html | html passwordInput callback: [:value | ]] gives: ''. self assert: [:html | html passwordInput value: 'foo bar&zork'] gives: ''. self assert: [:html | (html passwordInput) callback: [:value | ]; value: 'foo bar&zork'] gives: '' ] testScriptTag [ self assert: [:html | html script: 'alert("")'] gives: ''. self assert: [:html | html script: 'true & false'] gives: ''. self assert: [:html | (html script) defer; with: 'alert("")'] gives: '' ] testSelectTag [ self assert: [:html | html select] gives: ''. self assert: [:html | html select list: #(1 2)] gives: ''. self assert: [:html | (html select) list: #(1 2); labels: [:v | 2 * v]] gives: ''. self assert: [:html | (html select) list: #(1 2); enabled: [:v | v even]] gives: ''. self assert: [:html | (html select) list: #(1 2); callback: [:v | ]] gives: '' ] testSymbolRendering [ self assert: [:html | (html div) id: #aSymbol; with: #aSecondSymbol] gives: '
        aSecondSymbol
        '. self assert: [:html | html div: [html text: #aSecondSymbol]] gives: '
        aSecondSymbol
        '. self assert: [:html | html div: [html render: #aSecondSymbol]] gives: '
        aSecondSymbol
        ' ] testTextArea [ self assert: [:html | html textArea] gives: ''. self assert: [:html | html textArea columns: 4] gives: ''. self assert: [:html | html textArea rows: 40] gives: ''. self assert: [:html | html textArea callback: [:value | ]] gives: ''. self assert: [:html | html textArea value: 'foo bar&zork'] gives: ''. self assert: [:html | html textArea with: 'foo bar&zork'] gives: ''. self assert: [:html | (html textArea) callback: [:value | ]; with: 'foo bar&zork'] gives: '' ] testTextInput [ self assert: [:html | html textInput] gives: ''. self assert: [:html | html textInput callback: [:value | ]] gives: ''. self assert: [:html | html textInput value: 'foo bar&zork'] gives: ''. self assert: [:html | (html textInput) callback: [:value | ]; value: 'foo bar&zork'] gives: '' ] testUnorderedListTag [ self assert: [:html | html unorderedList] gives: '
          '. self assert: [:html | html unorderedList add: 1] gives: '
          • 1
          '. self assert: [:html | html unorderedList addAll: #(1 2)] gives: '
          • 1
          • 2
          '. self assert: [:html | html unorderedList list: #(1 2)] gives: '
          • 1
          • 2
          '. self assert: [:html | (html unorderedList) list: #(1 2); with: [html listItem: 3]] gives: '
          • 1
          • 2
          • 3
          '. self assert: [:html | (html unorderedList) add: 2; labels: [:e | 2 * e]] gives: '
          • 4
          '. self assert: [:html | (html unorderedList) add: 2; labels: [:e | 2 * e]; with: [html listItem: 5]] gives: '
          • 4
          • 5
          ' ] ] WACanvasBrushTest subclass: WAFormTagTest [ | session | assertUserAgent: aString isInternetExplorer: aBoolean [ self userAgent: aString. (WARenderCanvas builder) callbackOwner: self; render: [:html | self assert: html form isInternetExplorer = aBoolean] ] performTest [ WACurrentSession use: session during: [super performTest] ] setUp [ super setUp. session := WASession new currentRequest: WARequest blankRequest yourself ] testDefaultAction [ self userAgent: 'Mozilla/5.0 (Windows; U; Windows NT 5.1; de; rv:1.8.1.3) Gecko/20070309 Firefox/2.0.0.3'. self assert: [:html | html form defaultAction: []] gives: '
          '. self userAgent: 'Mozilla/4.0 (compatible; MSIE 6.0; Windows NT 5.0)'. self assert: [:html | html form defaultAction: []] gives: '
          ' ] testIsInternetExplorer [ self assertUserAgent: 'Mozilla/5.0 (compatible; Konqueror/3.2; Linux 2.6.2) (KHTML, like Gecko)' isInternetExplorer: false. self assertUserAgent: 'Mozilla/4.0 (compatible; MSIE 6.0; MSIE 5.5; Windows NT 5.1) Opera 7.04 [de]' isInternetExplorer: false. self assertUserAgent: 'Opera/9.10 (Windows NT 5.0; U; de)' isInternetExplorer: false. self assertUserAgent: 'Mozilla/5.0 (Windows; U; Windows NT 5.0; de-DE; rv:1.6) Gecko/20040206 Firefox/1.0.1' isInternetExplorer: false. self assertUserAgent: 'Mozilla/4.0 (compatible; MSIE 7.0; Windows NT 6.0; WOW64; SLCC1; .NET CLR 2.0.50727; .NET CLR 3.0.04506)' isInternetExplorer: true. self assertUserAgent: 'Mozilla/4.0 (compatible; MSIE 6.0; Windows NT 5.0)' isInternetExplorer: true. self assertUserAgent: 'Lynx/2.8.4rel.1 libwww-FM/2.14 SSL-MM/1.4.1 OpenSSL/0.9.6c' isInternetExplorer: false. self assertUserAgent: 'Mozilla/5.0 (Windows; U; Windows NT 5.1; de-AT; rv:1.8.1.2) Gecko/20070222 SeaMonkey/1.1.1' isInternetExplorer: false. self assertUserAgent: 'Mozilla/5.0 (Windows; U; Windows NT 5.1; de; rv:1.8.1.3) Gecko/20070309 Firefox/2.0.0.3' isInternetExplorer: false ] userAgent: aString [ session currentRequest headers at: 'user-agent' put: aString ] ] WACanvasBrushTest subclass: WAResourceBaseUrlTest [ assertRoot: aBlock gives: aString [ | html | html := (WARenderCanvas builder) callbackOwner: self; fullDocument: true; rootBlock: aBlock; render: [:canvas | ]. self assert: html = ('' , aString , '') ] performTest [ | application session | application := (WAApplication new) preferenceAt: #resourceBaseUrl put: self resourceBaseUrl; yourself. session := (WASession new) setParent: application; yourself. WACurrentSession use: session during: [super performTest] ] resourceBaseUrl [ ^'https:/www.seaside.st/resources/' ] testAbsoluteFtpUrl [ self assert: [:html | html anchor resourceUrl: 'ftp://www.google.com/track.js'] gives: '' ] testAbsoluteHttpUrl [ self assert: [:html | html anchor resourceUrl: 'http://www.google.com/track.js'] gives: '' ] testAbsoluteHttpsUrl [ self assert: [:html | html anchor resourceUrl: 'https://www.google.com/track.js'] gives: '' ] testFileNameWithHttp [ self assert: [:html | html image resourceUrl: 'http.gif'] gives: '' ] testImageTag [ self assert: [:html | html image resourceUrl: 'logo.jpeg'] gives: '' ] testRootScript [ self assertRoot: [:html | html javascript resourceUrl: 'main.js'] gives: '' ] testScriptTag [ self assert: [:html | html script resourceUrl: 'track.js'] gives: '' ] testSylesheet [ self assertRoot: [:html | html stylesheet resourceUrl: 'main.css'] gives: '' ] ] TestCase subclass: WAConfigurationTest [ testLinearization [ "from http://www.webcom.com/haahr/dylan/linearization-oopsla96.html" | root boat dayBoat wheelBoat engineLess pedalWheelBoat smallMultihull smallCatamaran pedalo | root := WAUserConfiguration new. boat := (WAUserConfiguration new) addAncestor: root; yourself. dayBoat := (WAUserConfiguration new) addAncestor: boat; yourself. wheelBoat := (WAUserConfiguration new) addAncestor: boat; yourself. engineLess := (WAUserConfiguration new) addAncestor: dayBoat; yourself. pedalWheelBoat := (WAUserConfiguration new) addAncestor: engineLess; addAncestor: wheelBoat; yourself. smallMultihull := (WAUserConfiguration new) addAncestor: dayBoat; yourself. smallCatamaran := (WAUserConfiguration new) addAncestor: smallMultihull; yourself. pedalo := (WAUserConfiguration new) addAncestor: pedalWheelBoat; addAncestor: smallCatamaran; yourself. self assert: pedalWheelBoat allAncestors = (Array with: engineLess with: dayBoat with: wheelBoat with: boat with: root). self assert: smallCatamaran allAncestors = (Array with: smallMultihull with: dayBoat with: boat with: root). self assert: pedalo allAncestors = ((Array with: pedalWheelBoat with: engineLess with: smallCatamaran with: smallMultihull) , (Array with: dayBoat with: wheelBoat with: boat with: root)) ] ] TestCase subclass: WACookieUnitTest [ testWriteOn [ | expiry cookie actual | expiry := DateTime year: 2007 month: 11 day: 21 hour: 14 minute: 42 second: 48 offset: (Duration days: 0 hours: 2 minutes: 0 seconds: 0). cookie := WACookie key: 'ikuser' value: '1234'. actual := String streamContents: [:stream | cookie writeOn: stream]. self assert: actual = 'ikuser=1234'. cookie expiry: expiry. actual := String streamContents: [:stream | cookie writeOn: stream]. self assert: actual = 'ikuser=1234; expires=Wed, 21-November-2007 12:42:48 GMT'. cookie path: '/seaside/counter'. actual := String streamContents: [:stream | cookie writeOn: stream]. self assert: actual = 'ikuser=1234; expires=Wed, 21-November-2007 12:42:48 GMT; path=/seaside/counter'. cookie value: nil. actual := String streamContents: [:stream | cookie writeOn: stream]. self assert: actual = 'ikuser=; expires=Wed, 21-November-2007 12:42:48 GMT; path=/seaside/counter' ] ] TestCase subclass: WADictionaryTest [ | dictionary | setUp [ super setUp. dictionary := WASmallDictionary new ] testAssociations [ dictionary at: '1' put: 'foo'; at: '2' put: 'bar'. self assert: dictionary associations = (Array with: '1' -> 'foo' with: '2' -> 'bar') ] testAssociationsDo [ dictionary associationsDo: [:key :valye | self assert: false]. dictionary at: '1' put: 'foo'; at: '2' put: 'bar'. dictionary associationsDo: [:assoc | self assert: ((assoc key = '1' and: [assoc value = 'foo']) or: [assoc key = '2' and: [assoc value = 'bar']])] ] testAt [ self should: [dictionary at: '1'] raise: Error. dictionary at: '1' put: 'foo'. self assert: (dictionary at: '1') = 'foo' ] testAtIfAbsent [ self assert: (dictionary at: '1' ifAbsent: ['foo']) = 'foo'. dictionary at: '1' put: 'bar'. self assert: (dictionary at: '1' ifAbsent: ['foo']) = 'bar' ] testAtIfAbsentPut [ self assert: (dictionary at: '1' ifAbsentPut: ['foo']) = 'foo'. self assert: (dictionary at: '1' ifAbsentPut: ['bar']) = 'foo' ] testAtIfPresent [ dictionary at: '1' put: 'foo'. self assert: (dictionary at: '1' ifPresent: [:v | v , 'bar']) = 'foobar'. self assert: (dictionary at: '2' ifPresent: [:v | v , 'bar']) isNil ] testAtPut [ dictionary at: '1' put: 'foo'. self assert: (dictionary at: '1') = 'foo'. dictionary at: '1' put: 'bar'. self assert: (dictionary at: '1') = 'bar' ] testIncludesKey [ self deny: (dictionary includesKey: '1'). dictionary at: '1' put: 'foo'. self assert: (dictionary includesKey: '1') ] testIsEmpty [ self assert: dictionary isEmpty. dictionary at: '1' put: 'foo'. self deny: dictionary isEmpty ] testKeys [ dictionary at: '1' put: 'foo'; at: '2' put: 'bar'. self assert: dictionary keys = #('1' '2') ] testKeysAndValuesDo [ dictionary keysAndValuesDo: [:key :valye | self assert: false]. dictionary at: '1' put: 'foo'; at: '2' put: 'bar'. dictionary keysAndValuesDo: [:key :value | self assert: ((key = '1' and: [value = 'foo']) or: [key = '2' and: [value = 'bar']])] ] testKeysDo [ | result | result := OrderedCollection new. dictionary at: '1' put: 'foo'; at: '2' put: 'bar'. dictionary keysDo: [:each | result add: each]. self assert: result asArray = #('1' '2') ] testRemoveKey [ dictionary at: '1' put: 'foo'. self assert: (dictionary removeKey: '1') = 'foo'. self should: [dictionary removeKey: '1'] raise: Error ] testRemoveKeyIfAbsent [ dictionary at: '1' put: 'foo'. self assert: (dictionary removeKey: '1' ifAbsent: ['bar']) = 'foo'. self assert: (dictionary removeKey: '1' ifAbsent: ['bar']) = 'bar' ] testSize [ self assert: dictionary size = 0. dictionary at: '1' put: 'foo'. self assert: dictionary size = 1. dictionary at: '2' put: 'bar'. self assert: dictionary size = 2 ] testValues [ dictionary at: '1' put: 'foo'; at: '2' put: 'bar'. self assert: dictionary values = #('foo' 'bar') ] testValuesDo [ | result | result := OrderedCollection new. dictionary at: '1' put: 'foo'; at: '2' put: 'bar'. dictionary valuesDo: [:each | result add: each]. self assert: result asArray = #('foo' 'bar') ] ] TestCase subclass: WADispatcherTest [ | defaultDispatcher alternateDispatcher shortDispatcher baseName alternateName lastUpdate | dispatcher: aDispatcher hasSameEntryPointsAs: anotherDispatcher [ "VW does not have Set >> #= OMFG!! SRSLY? wtf...?" | aSet anotherSet | aSet := aDispatcher entryPoints keys. anotherSet := anotherDispatcher entryPoints keys. aSet == anotherSet ifTrue: [^true]. aSet class == anotherSet class ifFalse: [^false]. "not sure this is really clever but ..." aSet size = anotherSet size ifFalse: [^false]. ^aSet allSatisfy: [:each | anotherSet includes: each] ] setUp [ "The statement below makes sure that the 'files' entry is registered into the default dispatcher before starting this test. This may be needed after loading Seaside in a stock VW image depending on the order the unit tests are executed. Without it, the WADispatcher tests that need the 'files' entry may fail in VW namely #testAlternateFiles and #testDefaultFiles" WAFileHandler default. baseName := SeasidePlatformSupport defaultDispatcherName. alternateName := 'seaside/stream'. defaultDispatcher := WADispatcher default. alternateDispatcher := defaultDispatcher copy setName: alternateName. shortDispatcher := defaultDispatcher copy setName: ''. defaultDispatcher addDependent: self ] tearDown [ defaultDispatcher removeDependent: self ] testAlternateCloning [ | originalHandler | self deny: alternateDispatcher == defaultDispatcher. self assert: (self dispatcher: alternateDispatcher hasSameEntryPointsAs: defaultDispatcher). alternateDispatcher entryPoints do: [:handler | originalHandler := defaultDispatcher entryPointAt: handler name. self assert: handler class == originalHandler class. self deny: handler == originalHandler. handler isDispatcher ifTrue: [self assert: (self dispatcher: handler hasSameEntryPointsAs: originalHandler)]] ] testAlternateConfig [ | app originalApp | app := alternateDispatcher entryPointAt: 'config'. originalApp := defaultDispatcher entryPointAt: 'config'. self assert: app class == WAApplication. self assert: app isApplication. self deny: app isDispatcher. self deny: app parent isNil. self assert: app name = 'config'. self assert: app basePath = ('/' , alternateDispatcher name , '/config'). self deny: app == originalApp. self assert: app name = originalApp name. self assert: app parent == alternateDispatcher. self assert: originalApp parent == defaultDispatcher ] testAlternateCounterDirect [ | app originalApp | app := alternateDispatcher entryPointAt: 'examples/counter'. originalApp := defaultDispatcher entryPointAt: 'examples/counter'. self assert: app name = 'counter'. self assert: app parent name = 'examples'. self assert: app basePath = ('/' , alternateDispatcher name , '/examples/counter'). self deny: app == originalApp. self assert: app name = originalApp name. self deny: app parent == originalApp parent. self assert: app parent name = originalApp parent name. self deny: app parent parent == originalApp parent parent. self deny: app parent parent name = originalApp parent parent name. self assert: app parent parent == alternateDispatcher. self assert: originalApp parent parent == defaultDispatcher ] testAlternateFiles [ | app originalApp | app := alternateDispatcher entryPointAt: 'files'. originalApp := defaultDispatcher entryPointAt: 'files'. self assert: app class == WAFileHandler. self deny: app isApplication. self deny: app isDispatcher. self deny: app parent isNil. self assert: app name = 'files'. self assert: app basePath = ('/' , alternateDispatcher name , '/files'). self deny: app == originalApp. self deny: app libraries == originalApp libraries. self assert: app name = originalApp name. self assert: app parent == alternateDispatcher. self assert: originalApp parent == defaultDispatcher ] testAlternateRoot [ | app | app := alternateDispatcher. self assert: app class == WADispatcher. self deny: app isApplication. self assert: app isDispatcher. self assert: app isRoot. self assert: app parent isNil. self assert: app name = alternateName ] testAlternateTests [ | app originalApp | app := alternateDispatcher entryPointAt: 'tests'. originalApp := defaultDispatcher entryPointAt: 'tests'. self assert: app class == WADispatcher. self deny: app isApplication. self assert: app isDispatcher. self deny: app isRoot. self deny: app parent isNil. self assert: app name = 'tests'. self assert: app basePath = ('/' , alternateDispatcher name , '/tests'). self deny: app == originalApp. self assert: app name = originalApp name. self assert: app parent == alternateDispatcher. self assert: originalApp parent == defaultDispatcher ] testDefaultConfig [ | app | app := defaultDispatcher entryPointAt: 'config'. self assert: app class == WAApplication. self assert: app isApplication. self deny: app isDispatcher. self deny: app parent isNil. self assert: app name = 'config'. self assert: app basePath = ('/' , baseName , '/config') ] testDefaultCounterDirect [ | app | app := defaultDispatcher entryPointAt: 'examples/counter'. self assert: app class == WAApplication. self assert: app isApplication. self deny: app isDispatcher. self deny: app parent isNil. self assert: app name = 'counter'. self assert: app parent name = 'examples'. self assert: app basePath = ('/' , baseName , '/examples/counter') ] testDefaultCounterNavigate [ | app | app := defaultDispatcher entryPointAt: 'examples'. self assert: app class == WADispatcher. self assert: app isDispatcher. self deny: app isRoot. self deny: app isApplication. self deny: app parent isNil. self assert: app name = 'examples'. self assert: app basePath = ('/' , baseName , '/examples'). app := app entryPointAt: 'counter'. self assert: app class == WAApplication. self assert: app isApplication. self deny: app isDispatcher. self deny: app parent isNil. self assert: app name = 'counter'. self assert: app parent name = 'examples'. self assert: app basePath = ('/' , baseName , '/examples/counter') ] testDefaultFiles [ | app | app := defaultDispatcher entryPointAt: 'files'. self assert: app class == WAFileHandler. self deny: app isDispatcher. self deny: app isApplication. self deny: app parent isNil. self assert: app name = 'files'. self assert: app basePath = ('/' , baseName , '/files') ] testDefaultRoot [ | app | app := defaultDispatcher. self assert: app == WADispatcher default. self assert: app class == WADispatcher. self assert: app isDispatcher. self assert: app isRoot. self deny: app isApplication. self assert: app parent isNil. self assert: app name = baseName. self assert: app basePath = ('/' , baseName) ] testDefaultTests [ | app | app := defaultDispatcher entryPointAt: 'tests'. self assert: app class == WADispatcher. self assert: app isDispatcher. self deny: app isRoot. self deny: app isApplication. self deny: app parent isNil. self assert: app name = 'tests'. self assert: app basePath = ('/' , baseName , '/tests') ] testShortTests [ | app | app := shortDispatcher entryPointAt: 'tests'. self assert: shortDispatcher basePath = ''. self assert: app basePath = '/tests' ] ] TestCase subclass: WADocumentHandlerTest [ assertHttpResponseFrom: aResponse matches: aHandler [ self assert: aResponse status = 200. self assert: aResponse contents contents = aHandler document. self assert: aResponse contentType = aHandler mimeType. self assert: aResponse contents contents size = aHandler document size. self assert: aResponse cookies isEmpty ] createAndVerifyBinaryDocumentNamed: aFilename hasAttachement: aHttpHeaderValue [ self createAndVerifyDocumentNamed: aFilename content: WAStandardFiles default profilerPng mimeType: 'image/png' hasAttachement: aHttpHeaderValue ] createAndVerifyDocumentNamed: aFilename content: anObject mimeType: aMimeTypeString hasAttachement: aHttpHeaderValue [ | handler response | handler := WADocumentHandler document: anObject mimeType: aMimeTypeString fileName: aFilename. self assert: handler document = anObject. response := handler response. self assert: (self headerAt: 'Expires' forResponse: response) notNil. self assert: (self headerAt: 'Content-Disposition' forResponse: response) = aHttpHeaderValue. self assertHttpResponseFrom: response matches: handler ] createAndVerifyTextDocumentNamed: aFilename hasAttachement: aHttpHeaderValue [ self createAndVerifyDocumentNamed: aFilename content: WAStandardFiles default toolbarCss mimeType: 'text/css' hasAttachement: aHttpHeaderValue ] headerAt: aString forResponse: aResponse [ | header | header := aResponse headers detect: [:each | each key = aString] ifNone: [^nil]. ^header value ] testByteArray [ self createAndVerifyBinaryDocumentNamed: nil hasAttachement: nil. self createAndVerifyBinaryDocumentNamed: 'profiler.png' hasAttachement: 'attachment; filename="profiler.png"' ] testString [ self createAndVerifyTextDocumentNamed: nil hasAttachement: nil. self createAndVerifyTextDocumentNamed: 'toolbar.css' hasAttachement: 'attachment; filename="toolbar.css"' ] ] TestCase subclass: WADynamicVariableTest [ assertValue: anObject [ | value | value := WADemoVariable value. self assert: value = anObject ] testWithValue [ | value | value := 'value'. WADemoVariable use: value during: [self assertValue: value] ] testWithoutValue [ self assertValue: WADemoVariable defaultValue ] ] TestCase subclass: WAEncoderTest [ assert: aString encoder: aClass gives: anEncodedString [ | stream | stream := WriteStream on: String new. (aClass on: stream) nextPutAll: aString. self assert: stream contents = anEncodedString ] testEncodedHtml [ self assert: 'Seaside' encoder: WAHtmlEncoder gives: 'Seaside'. self assert: '
          ' encoder: WAHtmlEncoder gives: '<div id="&amp;">' ] testEncodedLatin1Url [ self assert: (String with: (Character value: 233) with: (Character value: 228)) encoder: WAUrlEncoder gives: '%E9%E4' ] testEncodedUnicode [ "this makes sure the encoder doesn't fall on the nose with unicode" | hiraA hiraO hiraAO zero ea | ea := String with: (Character value: 233) with: (Character value: 228). self assert: ea encoder: WAHtmlEncoder gives: ea. hiraA := (Character codePoint: 12354) asString. "HIRAGANA LETTER A" hiraO := (Character codePoint: 12362) asString. "HIRAGANA LETTER O" hiraAO := hiraA , hiraO. self assert: hiraA encoder: WAHtmlEncoder gives: hiraA. self assert: hiraO encoder: WAHtmlEncoder gives: hiraO. self assert: hiraAO encoder: WAHtmlEncoder gives: hiraAO. "The Supplementary Multilingual Plane (SMP: Plane 1, U+010000 - U+01FFFF) http://www.unicode.org/charts/PDF/U10140.pdf Ancient Greek Zero Sign" zero := (Character codePoint: 65930) asString. self assert: zero encoder: WAHtmlEncoder gives: zero ] testEncodedUrl [ self assert: 'Seaside Aubergines' encoder: WAUrlEncoder gives: 'Seaside+Aubergines'. self assert: 'www.seaside.st' encoder: WAUrlEncoder gives: 'www.seaside.st'. self assert: '~seaside-info_' encoder: WAUrlEncoder gives: '~seaside-info_'. self assert: 'http://www.seaside.st?foo=1&bar=2' encoder: WAUrlEncoder gives: 'http%3A%2F%2Fwww.seaside.st%3Ffoo%3D1%26bar%3D2'. self assert: 'a%' encoder: WAUrlEncoder gives: 'a%25'. self assert: (String with: Character cr) encoder: WAUrlEncoder gives: '%0D' ] testEncodedUtf8Url [ "this tests url encoding of strings that are already utf8" "'übertriñgé' isoToUtf8" self assert: #(195 188 98 101 114 116 114 105 195 177 103 195 169) asByteArray seasideString encoder: WAUrlEncoder gives: '%C3%BCbertri%C3%B1g%C3%A9' ] ] TestCase subclass: WAExternalIDTest [ count [ ^512 ] testFromString [ | string | string := 'abCD12_-'. self assert: (WAExternalID fromString: string) printString = string ] testStartUp [ | collection | WAExternalID startUp. collection := Set new: self count. self count timesRepeat: [collection add: WAExternalID new]. WAExternalID startUp. self count timesRepeat: [self deny: (collection includes: WAExternalID new) description: 'This is extremely unlikely to fail, if it does repeatedly then there is something wrong with the initialization of the random-generator.'] ] testUnique [ | collection id | collection := Set new: self count. self count timesRepeat: [id := WAExternalID new. self deny: (collection includes: id) description: 'This is extremely unlikely to fail, if it does repeatedly then there is something wrong with the random generator.'. collection add: id] ] ] TestCase subclass: WAFileLibraryTest [ assertFile: aString contentType: aMimeType handler: aHandler symbol: aSymbol library: aLibrary [ | request response | request := WARequest method: 'GET' url: '/seaside/files/' , aLibrary name , '/' , aString headers: Dictionary new fields: Dictionary new cookies: Dictionary new. response := aHandler handleRequest: request. self assert: response status = 200. self assert: response contentType = aMimeType. self assert: response stream contents = (aLibrary perform: aSymbol) ] testAsFileName [ | library | library := WAFileLibraryDemo new. self assert: (library asFilename: #mainJs) = 'main.js'. self assert: (library asFilename: #style2Css) = 'style2.css'. self assert: (library asFilename: #index) = 'index' ] testAsSelector [ self assert: (WAFileLibrary asSelector: 'main.css') = #mainCss. self assert: (WAFileLibrary asSelector: 'main.js') = #mainJs. self assert: (WAFileLibrary asSelector: 'style-2.css') = #style2Css. self assert: (WAFileLibrary asSelector: 'style_2.css') = #style2Css ] testAsSelectorCapitalized [ | library | library := WAFileLibraryDemo new. self assert: (library asSelector: 'COMMENTS.TXT') = #COMMENTSTxt. self assert: (library asFilename: #COMMENTSTxt) = 'COMMENTS.txt' ] testAsSelectorFunky [ self assert: (WAFileLibrary asSelector: '1_2$3-4/5()6!7 8.9.test 1 2 3 me 4 5 6 .txt') = #test123me456Txt ] testAsSelectorLeadingDigits [ | library | library := WAFileLibraryDemo new. self assert: (library asSelector: '1readme.txt') = #readmeTxt. self assert: (library asSelector: '123456789readme.txt') = #readmeTxt. self assert: (library asSelector: '123456789readme89.txt') = #readme89Txt ] testCompileByteArray [ | library data file first second | library := WAFileLibraryDemo new. self deny: (library class selectors includes: #demoJpeg). data := (1 to: 255) asByteArray. file := (WAFile new) contentType: 'image/jpeg' toMimeType; contents: data; fileName: 'demo.jpeg'; yourself. library addFile: file. self assert: (library class selectors includes: #demoJpeg). first := library perform: #demoJpeg. self assert: first = data. second := library perform: #demoJpeg. self assert: first == second. library removeFile: file fileName. self deny: (library class selectors includes: #demoJpeg) ] testCompileString [ | library data file first second source | library := WAFileLibraryDemo new. self deny: (library class selectors includes: #demoTxt). data := 'this is a string'. file := (WAFile new) contentType: 'text/plain' toMimeType; contents: data; fileName: 'demo.txt'; yourself. library addFile: file. self assert: (library class selectors includes: #demoTxt). first := library perform: #demoTxt. self assert: first = data. second := library perform: #demoTxt. self assert: first == second. library removeFile: file fileName. self deny: (library class selectors includes: #demoTxt) ] testFileLibraryDemo [ | actual expected | actual := WAFileLibraryDemo new filenames. expected := #('main.css' 'main.jpg'). self assert: actual size = expected size. expected do: [:each | self assert: (actual includes: each)] ] testFilenames [ | expected actual | expected := #(#editorCss #topJpg #mainCss #savePng). actual := WAHandlerEditorFiles new fileSelectors. "VW does not implement #= in Sets" self assert: actual size = expected size. expected do: [:each | self assert: (expected includes: each)] ] testIsBinary [ self deny: (WAFileLibraryDemo isBinary: 'scipt.js'). self deny: (WAFileLibraryDemo isBinary: 'markup.xml'). self deny: (WAFileLibraryDemo isBinary: 'markup.xhtml'). self deny: (WAFileLibraryDemo isBinary: 'markup.html'). self deny: (WAFileLibraryDemo isBinary: 'file.txt'). self deny: (WAFileLibraryDemo isBinary: 'calendar.ics'). self assert: (WAFileLibraryDemo isBinary: 'image.jpeg'). self assert: (WAFileLibraryDemo isBinary: 'squeak.exe') ] testKalseyTabs [ | handler | handler := WAFileHandler new. self assertFile: 'kalseyTabs.css' contentType: 'text/css' toMimeType handler: handler symbol: #kalseyTabsCss library: WAStandardFiles new ] testKalseyTabsCascade [ | handler | handler := WAFileHandler new. self assertFile: 'kalseyTabs.css' contentType: 'text/css' toMimeType handler: handler symbol: #kalseyTabsCss library: WAStandardFiles new ] testLiveUpdate [ | handler | handler := WAFileHandler new. self assertFile: 'misc.js' contentType: 'application/x-javascript' toMimeType handler: handler symbol: #miscJs library: WAStandardFiles new ] testMainCss [ | handler | handler := WAFileHandler new. self assertFile: 'main.css' contentType: 'text/css' toMimeType handler: handler symbol: #mainCss library: WAFileLibraryDemo new ] testMainCssCascade [ | handler | handler := WAFileHandler new. self assertFile: 'main.css' contentType: 'text/css' toMimeType handler: handler symbol: #mainCss library: WAFileLibraryDemo new ] testMainJpg [ | handler library request response contents | handler := WAFileHandler new. library := WAFileLibraryDemo new. request := WARequest method: 'GET' url: '/i/dont/care/WAFileLibraryDemo/main.jpg' headers: Dictionary new fields: Dictionary new cookies: Dictionary new. response := handler handleRequest: request. self assert: response status = 200. self assert: response contentType = 'image/jpeg' toMimeType. contents := (response stream) binary; contents. self assert: contents asByteArray = (library perform: #mainJpg) ] testMainJs [ | handler request response | handler := WAFileHandler new. request := WARequest method: 'GET' url: '/i/dont/care/main.js' headers: Dictionary new fields: Dictionary new cookies: Dictionary new. response := handler handleRequest: request. self assert: response status = 404 ] testMimeType [ | library | library := WAFileLibraryDemo new. self assert: (library mimetypeForFile: 'main.js') = 'application/x-javascript' toMimeType. self assert: (library mimetypeForFile: 'style2.css') = 'text/css' toMimeType. self assert: (library mimetypeForFile: 'image.jpg') = 'image/jpeg' toMimeType. self assert: (library mimetypeForFile: 'index') = 'application/octet-stream' toMimeType ] testNoneStatisfy [ self deny: (#(1 2 3) noneSatisfy: [:each | each even]). self assert: (#(1 3 5) noneSatisfy: [:each | each even]) ] testStandardFiles [ | actual expected | actual := WAStandardFiles new filenames. expected := #('halo.css' 'kalseyTabs.css' 'toolbar.css' 'window.css' 'externalAnchors.js' 'misc.js' 'shortcuts.js' 'codebrowser.png' 'inspector.png' 'styleeditor.png' 'config.png' 'profiler.png' 'memory.png'). "VW does not implement #= in Collection because you don't want that" self assert: actual size = expected size. expected do: [:each | self assert: (actual includes: each)] ] testUrlOf [ self assert: (WAStandardFiles / #seasideJpg) seasideString = ('/' , SeasidePlatformSupport defaultDispatcherName , '/files/WAStandardFiles/seaside.jpg') ] ] TestCase subclass: WAFileSystemTest [ | fileSystem | requestWithUrl: aString [ ^WARequest method: 'POST' url: aString headers: Dictionary new fields: Dictionary new cookies: Dictionary new ] setUp [ super setUp. fileSystem := WAFileSystem new. fileSystem setName: 'culture' ] testAsAbsoluteUrlRelativeTo [ | request | fileSystem configuration valueAt: #directory put: '/home/philppe/pr0n'. request := self requestWithUrl: '/culture/pictures'. self assert: (fileSystem asAbsoluteUrl: 'cleopatra.jpeg' relativeTo: request) = '/culture/pictures/cleopatra.jpeg'. request := self requestWithUrl: '/culture/pictures/'. self assert: (fileSystem asAbsoluteUrl: 'cleopatra.jpeg' relativeTo: request) = '/culture/pictures/cleopatra.jpeg' ] testPathForRequest [ | request | fileSystem configuration valueAt: #directory put: '/home/philppe/pr0n'. request := self requestWithUrl: '/culture/cleopatra.jpeg'. self assert: (fileSystem pathForRequest: request) = '/home/philppe/pr0n/cleopatra.jpeg'. fileSystem configuration valueAt: #directory put: '/home/philppe/pr0n/'. self assert: (fileSystem pathForRequest: request) = '/home/philppe/pr0n/cleopatra.jpeg' ] ] TestCase subclass: WAFileTest [ | file | setUp [ file := WAFile new ] testBorderline [ file fileName: 'C'. self assert: file fileName = 'C'. file fileName: 'C:'. self assert: file fileName = 'C:'. file fileName: 'C:\'. self assert: file fileName = '' ] testNonLatinWindowsPath [ "If the following assertion fails, your Smalltalk dialect most probably does not support non-latin characters. This is true for Squeak 3.7. If your Smalltalk dialect does support non-latin characters adjust the test." | koreanName | self shouldnt: [koreanName := (UnicodeString with: (Character codePoint: 50976) with: (Character codePoint: 47532) with: (Character codePoint: 47484)) asString, '.txt'] raise: Error. file fileName: koreanName. self assert: file fileName = koreanName. file fileName: 'C:\important\' , koreanName. self assert: file fileName = koreanName ] testWindowsPath [ file fileName: 'C:\important\passwords.txt'. self assert: file fileName = 'passwords.txt'. file fileName: '/important/passwords.txt'. self assert: file fileName = '/important/passwords.txt'. file fileName: 'passwords.txt'. self assert: file fileName = 'passwords.txt' ] ] TestCase subclass: WAHtmlBuilderTest [ testBody [ | actual | actual := WARenderCanvas builder render: [:html | html unorderedList: [html listItem: 'an item']]. self assert: actual = '
          • an item
          ' ] testFullDocument [ | actual | actual := (WARenderCanvas builder) fullDocument: true; render: [:html | html unorderedList: [html listItem: 'an item']]. self assert: actual = '
          • an item
          ' ] testFullDocumentWithBlock [ | actual | actual := (WARenderCanvas builder) fullDocument: true; rootBlock: [:root | root title: 'title']; render: [:html | html unorderedList: [html listItem: 'an item']]. self assert: actual = 'title
          • an item
          ' ] ] TestCase subclass: WAHtmlRootTest [ assert: aBlock gives: aString [ | html | html := (WARenderCanvas builder) callbackOwner: self; fullDocument: true; rootBlock: aBlock; render: [:canvas | ]. self assert: html = ('' , aString , '') ] testConditionalComment [ self assert: [:html | (html if) greaterThan; orEqual; ie55; do: [(html script) defer; url: 'http://www.example.com/bugs.js']] gives: ''. self assert: [:html | (html if) not; ie; do: [html script url: 'http://www.example.com/bugs.js']] gives: '' ] testContentType [ self assert: [:html | html meta contentType: 'application/xhml+xml' toMimeType] gives: ''. self assert: [:html | html meta contentType: 'application/xhml+xml'] gives: '' ] testJavascript [ self assert: [:html | html javascript add: 'true & false'] gives: '' ] testLinkElement [ self assert: [:html | (html stylesheet) addAural; addTeletype; title: 'aTilte'; url: 'http://example.com/style.css'] gives: '' ] testLinkElementWithContent [ self assert: [:html | html stylesheet add: 'div > em { color: blue; }'] gives: ''. self assert: [:html | html stylesheet add: 'E[foo$="bar"]'] gives: '' ] testRevealedConditionalComment [ self assert: [:html | (html revealedIf) ie7; do: [(html script) defer; url: 'http://www.example.com/bugs.js']] gives: '' ] ] TestCase subclass: WALocaleTest [ testCountryName [ | locale | locale := WALocale fromString: 'de-CH'. self assert: locale countryName = 'SWITZERLAND' ] testIso3 [ | locale | locale := WALocale fromString: 'gsw-CHE'. self assert: locale language = 'gsw'. self assert: locale country = 'CHE'. self assert: locale seasideString = 'gsw-CHE'. locale := WALocale fromString: 'gsw_CHE'. self assert: locale language = 'gsw'. self assert: locale country = 'CHE'. self assert: locale seasideString = 'gsw-CHE' ] testLanguageName [ | locale | locale := WALocale fromString: 'de'. self assert: locale languageName = 'German'. locale := WALocale fromString: 'gsw'. self assert: locale languageName = 'Swiss German; Alemannic' ] testLangugeAndCountry [ | locale | locale := WALocale fromString: 'de-CH'. self assert: locale language = 'de'. self assert: locale country = 'CH'. self assert: locale seasideString = 'de-CH'. locale := WALocale fromString: 'de_CH'. self assert: locale language = 'de'. self assert: locale country = 'CH'. self assert: locale seasideString = 'de-CH' ] testLangugeOnly [ | locale | locale := WALocale fromString: 'de'. self assert: locale language = 'de'. self assert: locale country isNil. self assert: locale seasideString = 'de' ] ] TestCase subclass: WAMimeTypeTest [ testBasic [ | mimeType | mimeType := WAMimeType fromString: 'image/jpeg'. self assert: mimeType main = 'image'. self assert: mimeType sub = 'jpeg'. self assert: mimeType parameters isEmpty. self assert: mimeType seasideString = 'image/jpeg' ] testCharSet [ | mimeType | mimeType := WAMimeType fromString: 'text/html'. mimeType charset: 'utf-8'. self assert: mimeType seasideString = 'text/html;charset=utf-8' ] testEquals [ | first second | first := WAMimeType fromString: 'text/html'. second := WAMimeType fromString: 'text/html'. self assert: first = second. self assert: first hash = second hash. second charset: 'utf-8'. self assert: first = second. self assert: first hash = second hash. first charset: 'iso-8859-1'. self assert: first = second. self assert: first hash = second hash. second := WAMimeType fromString: 'text/xml'. self deny: first = second ] testIsBinary [ | notBinary binary | notBinary := #('text/plain' 'text/bar' 'application/x-javascript' 'application/xhml+xml' 'application/xml'). notBinary do: [:each | | mimeType | mimeType := WAMimeType fromString: each. self deny: mimeType isBinary]. binary := #('application/octet-stream' 'image/jpeg'). binary do: [:each | | mimeType | mimeType := WAMimeType fromString: each. self assert: mimeType isBinary] ] testIsNonStandard [ | mimeType | mimeType := WAMimeType fromString: 'image/png'. self deny: mimeType isNonStandard. mimeType := WAMimeType fromString: 'image/x-icon'. self assert: mimeType isNonStandard. mimeType := WAMimeType fromString: 'image/X-icon'. self assert: mimeType isNonStandard. mimeType := WAMimeType fromString: 'x-icon/image'. self assert: mimeType isNonStandard. mimeType := WAMimeType fromString: 'X-icon/image'. self assert: mimeType isNonStandard ] testIsVendorSpecifc [ | mimeType | mimeType := WAMimeType fromString: 'image/png'. self deny: mimeType isVendorSpecific. mimeType := WAMimeType fromString: 'image/vnd.microsoft.icon'. self assert: mimeType isVendorSpecific. mimeType := WAMimeType fromString: 'vnd.microsoft.icon/image'. self deny: mimeType isVendorSpecific ] testMatches [ | pattern mimeType | pattern := WAMimeType fromString: 'image/png'. mimeType := WAMimeType fromString: 'image/png'. self assert: (mimeType matches: pattern). mimeType := WAMimeType fromString: 'image/gif'. self deny: (mimeType matches: pattern). pattern := WAMimeType fromString: 'image/*'. mimeType := WAMimeType fromString: 'image/png'. self assert: (mimeType matches: pattern). mimeType := WAMimeType fromString: 'text/html'. self deny: (mimeType matches: pattern). pattern := WAMimeType fromString: '*/*'. mimeType := WAMimeType fromString: 'image/png'. self assert: (mimeType matches: pattern) ] testParamters [ ^#('text/html;charset=utf-8' 'text/html; charset=utf-8') do: [:each | | mimeType | mimeType := WAMimeType fromString: each. self assert: mimeType main = 'text'. self assert: mimeType sub = 'html'. self assert: mimeType parameters size = 1. self assert: (mimeType parameters at: 'charset') = 'utf-8'. self assert: mimeType seasideString = 'text/html;charset=utf-8'] ] testTo [ | mimeType | mimeType := 'image/jpeg' toMimeType. self assert: (mimeType isKindOf: WAMimeType). self assert: mimeType main = 'image'. self assert: mimeType sub = 'jpeg'. self assert: mimeType parameters isEmpty. self assert: mimeType seasideString = 'image/jpeg'. mimeType := mimeType toMimeType. self assert: (mimeType isKindOf: WAMimeType) ] ] TestCase subclass: WAPlatformTest [ testAddFirst [ | strings | strings := #('b' 'c' 'd') asOrderedCollection. strings addFirst: 'a'. self assert: strings = ((OrderedCollection new) add: 'a'; add: 'b'; add: 'c'; add: 'd'; yourself) ] testAsInteger [ self assert: 2007 asInteger = 2007. self assert: '2007' asInteger = 2007. self assert: (['foo' asInteger] on: Error do: [:e | 0]) = 0 ] testAsMIMEDocument [ | document | document := 'hello Seaside' asMIMEDocumentType: 'text/plain' toMimeType. self assert: document contentType = 'text/plain'. self assert: document content = 'hello Seaside'. self assert: (document asMIMEDocumentType: 'text/plain' toMimeType) == document ] testAsNumber [ self assert: 2007 asNumber = 2007. self assert: '2007' asNumber = 2007 ] testAsTwoCharacterString [ self assert: 2 asTwoCharacterString = '02'. self assert: 11 asTwoCharacterString = '11'. self assert: 1943 asTwoCharacterString = '19'. self assert: 0 asTwoCharacterString = '00'. self assert: -2 asTwoCharacterString = '-2'. self assert: -234 asTwoCharacterString = '-2' ] testAsUppercase [ self assert: 'abc' asUppercase = 'ABC'. self assert: 'ABC' asUppercase = 'ABC' ] testAtRandom [ "don't change this to an Interval, we want to test SequenceableCollection" self assert: (#(0 1 2 3 4 5 6 7 8 9) atRandom between: 0 and: 9). "don't change this to an Interval, we want to test SequenceableCollection" self assert: ((#(0 1 2 3 4 5 6 7 8 9) atRandom: SeasidePlatformSupport randomClass new) between: 0 and: 9). self assert: (9 between: 1 and: 9) ] testBeMutable [ self shouldnt: [Object new beMutable] raise: MessageNotUnderstood ] testBetweenAnd [ self assert: (6 between: 1 and: 12) ] testBlockContextWithPossibleArgument [ | block | block := [:x | 1 + x]. self assert: (block valueWithPossibleArgument: 2) = 3. block := [false not]. self assert: (block valueWithPossibleArgument: 3) ] testCapitalized [ self assert: 'capitalized' capitalized = 'Capitalized'. self assert: 'Capitalized' capitalized = 'Capitalized'. self assert: 'CAPITALIZED' capitalized = 'CAPITALIZED'. self assert: #capitalized capitalized = #Capitalized. self assert: #Capitalized capitalized = #Capitalized. self assert: #CAPITALIZED capitalized = #CAPITALIZED ] testCharacterAsUnicode [ "test for: Character >> #asUnicode ^self asInteger" self assert: $S codePoint = 83 ] testCharacterTo [ | actual expected | actual := ($a to: $z) , ($A to: $Z) , ($0 to: $9) , (Array with: $_ with: $-) collect: [:each | each asInteger]. expected := #(97 98 99 100 101 102 103 104 105 106 107 108 109 110 111 112 113 114 115 116 117 118 119 120 121 122 65 66 67 68 69 70 71 72 73 74 75 76 77 78 79 80 81 82 83 84 85 86 87 88 89 90 48 49 50 51 52 53 54 55 56 57 95 45). self assert: actual size = expected size. actual with: expected do: [:first :second | self assert: first = second] ] testCopyAfter [ self assert: ('de_CH' copyAfter: $_) = 'CH' ] testCopyAfterLast [ self assert: ('britney.sex.tape.mkv' copyAfterLast: $.) = 'mkv' ] testCopyUpToLast [ self assert: ('britney.sex.tape.mkv' copyUpToLast: $.) = 'britney.sex.tape' ] testCount [ self assert: (#(1 2 3) count: [:each | each odd]) = 2 ] testDaysInMonthForYear [ (1 to: 12) with: #(31 28 31 30 31 30 31 31 30 31 30 31) do: [:month :days | self assert: days = (Date daysInMonthNumber: month forYear: 2007)] ] testDefaultPathName [ self deny: SeasidePlatformSupport defaultDirectoryName isNil. self deny: SeasidePlatformSupport defaultDirectoryName isEmpty ] testEmptyOrNil [ self assert: '' isEmptyOrNil. self assert: nil isEmptyOrNil. self assert: Array new isEmptyOrNil. self deny: 'Timberwolf' isEmptyOrNil ] testFindTokens [ | mimeType tokens | mimeType := 'application/xhtml+xml'. tokens := mimeType findTokens: '/'. self assert: tokens size = 2. self assert: tokens first = 'application'. self assert: tokens second = 'xhtml+xml' ] testFixCallbackTemps [ "Make sure that #fixCallbackTemps is properly understood by block-contexts. Make sure that this is either a nop for Smalltalks with true block closures, or it properly fixes the context otherwise." | array blocks values | array := #(1 2 3). blocks := array collect: [:each | [each] fixCallbackTemps]. values := blocks collect: [:each | each value]. self assert: values = array ] testGarbageCollect [ "if you miss this do a class extension" self shouldnt: [Smalltalk garbageCollect] raise: MessageNotUnderstood ] testIfNil [ self assert: (nil ifNil: [1]) = 1. self assert: (1 ifNil: [2]) = 1 ] testIncludesSubString [ self assert: ('britney.sex.tape.mkv' startsWith: 'britney'). self deny: ('britney.sex.tape.mkv' startsWith: 'sex') ] testIsKeyword [ self deny: #isKeyword isKeyword. self deny: #+ isKeyword. self assert: #isKeyword: isKeyword. self assert: #isKeyword:isKeyword: isKeyword ] testIsUnary [ self assert: #isUnary isUnary. self deny: #+ isUnary. self deny: #isUnary: isUnary. self deny: #isUnary:isUnary: isUnary ] testMessageSendValueWithPossibleArgument [ "test for: MessageSend >> #valueWithPossibleArgument: anArg self numArgs = 0 ifTrue: [^self value]. self numArgs = 1 ifTrue: [^self value: anArg]. self numArgs > 1 ifTrue: [^self valueWithArguments: {anArg}, (Array new: self numArgs - 1)]" | send | send := DirectedMessage receiver: 1 selector: #+. self assert: (send valueWithPossibleArgument: 2) = 3. send := DirectedMessage receiver: false selector: #not. self assert: (send valueWithPossibleArgument: 3) ] testNewDayMonthNumberYear [ | date | date := Date newDay: 6 monthNumber: 11 year: 2007. self assert: date year = 2007. self assert: date dayOfYear = 310 ] testPaddedToWith [ self assert: ('X' padded: #left to: 2 with: $0) = '0X'. self assert: ('XX' padded: #left to: 2 with: $0) = 'XX' ] testPlatformString [ self deny: SeasidePlatformSupport versionString isNil. self deny: SeasidePlatformSupport versionString isEmpty ] testPrintStringAsCents [ self assert: 523 printStringAsCents = '$5.23' ] testPrintStringBase [ self assert: (15 printStringBase: 16) = 'F'. self assert: (16 printStringBase: 16) = '10' ] testRemoveAllFoundIn [ | actual | actual := #(1 2 3) asOrderedCollection. actual removeAllFoundIn: #(1 2). self assert: actual size = 1. self assert: actual first = 3 ] testSeconds [ self assert: Time now seconds isInteger. self deny: Time now seconds isFraction ] testShutDownList [ "A smoke test: checks if the test-class can be added and removed to the shutdown list." [SeasidePlatformSupport addToShutDownList: self class] ensure: [SeasidePlatformSupport removeFromShutDownList: self class] ] testStartUpList [ "A smoke test: checks if the test-class can be added and removed to the startup list." [SeasidePlatformSupport addToStartUpList: self class] ensure: [SeasidePlatformSupport removeFromStartUpList: self class] ] testStreamClosed [ "test for: Stream >> #closed ^false" self deny: 'Seaside' readStream closed ] testSymbolAsMutator [ "test for: Symbol >> #asMutator ^ (self copyWith: $:) asSymbol" self assert: #name asMutator = #name: ] testToString [ self assert: 'Timberwolf' seasideString = 'Timberwolf'. self assert: #DireWolf seasideString = 'DireWolf'. self assert: true seasideString = 'true'. self assert: 666 seasideString = '666'. self assert: $A seasideString = 'A'. self assert: nil seasideString = 'nil'. [1 / 0] on: ZeroDivide do: [:error | self assert: error seasideString = 'ZeroDivide']. self assert: 15.25 seasideString isString. self assert: 15.25 seasideString asNumber = 15.25. self assert: nil seasideString isString. self assert: (4 @ 2) seasideString = '4@2'. self assert: #(101 97) asByteArray seasideString = 'ea'. self assert: Object new seasideString isString ] testTotalSeconds [ "Answer the total seconds since the Squeak epoch: 1 January 1901." | seconds | seconds := Time secondClock. self assert: seconds isInteger ] testTrimBlanks [ self assert: ' abc ' trimSeparators = 'abc' ] testVersionString [ self deny: SeasidePlatformSupport platformString isNil. self deny: SeasidePlatformSupport platformString isEmpty ] ] TestCase subclass: WAResponseTest [ | response | setUp [ response := WAResponse new ] testCaching [ self assert: response headers isEmpty. response cacheForever. self assert: (response headerAt: 'Expires') value = 'Thu, 01 Jan 2095 12:00:00 GMT'. self assert: response headers size = 1 ] testDoNotCache [ self assert: response headers isEmpty. response doNotCache. self assert: (response headerAt: 'Cache-Control') value = 'no-cache, must-revalidate'. self assert: (response headerAt: 'Expires') value = 'Thu, 11 Jun 1980 12:00:00 GMT'. self assert: (response headerAt: 'Pragma') value = 'no-cache'. self assert: response headers size = 3 ] ] TestCase subclass: WAUrlTest [ | url | setUp [ url := WAUrl new ] testAddParamter [ url addToPath: 'files'. self assert: url seasideString = '/files'. url addParameter: 'x'. self assert: url seasideString = '/files?x'. url addParameter: 'y' value: 1. self assert: url seasideString = '/files?x&y=1' ] testAddToPath [ url addToPath: '/files/WAStandardFiles/seaside.jpg'. self assert: url seasideString = '/files/WAStandardFiles/seaside.jpg' ] testEqual [ url hostname: 'seaside.st'; addParameter: 'foo' value: 'bar'. self assert: url = url. self deny: url = WAUrl new. self deny: url = url printString. self deny: url = url withoutParameters. self deny: url = (url withParameter: 'zork'). self deny: url = (url withParameter: 'zork' value: 'zonk') ] testFragment [ url fragment: 'id'. self assert: url fragment = 'id'. self assert: url seasideString = '#id' ] testHash [ url hostname: 'seaside.st'. self assert: url hash = url hash. self assert: url hash = url copy hash ] testHostname [ url hostname: 'seaside.st'. self assert: url hostname = 'seaside.st'. self assert: url seasideString = 'http://seaside.st' ] testParameters [ url parameters at: '1' put: nil. self assert: url seasideString = '?1'. url parameters at: '2' put: 'foo'. self assert: url seasideString = '?1&2=foo'. url parameters at: '3' put: 123. self assert: url seasideString = '?1&2=foo&3=123'. url parameters at: '4' put: 'foo bar&zork'. self assert: url seasideString = '?1&2=foo&3=123&4=foo+bar%26zork' ] testPassword [ url hostname: 'seaside.st'; username: 'foo'; password: 'bar'. self assert: url password = 'bar'. self assert: url seasideString = 'http://foo:bar@seaside.st' ] testPath [ self assert: url seasideString = ''. url path add: 'aa'. self assert: url seasideString = '/aa'. url path add: 'bb'. self assert: url seasideString = '/aa/bb'. self assert: url path asArray = #('aa' 'bb') ] testPathEncoding [ url path: #('foo/bar'). self assert: url printString = '/foo%2Fbar'. url path: #('foo bar'). self assert: url printString = '/foo+bar'. url path: #('foo+bar'). self assert: url printString = '/foo%2Bbar'. url path: #('foo%bar'). self assert: url printString = '/foo%25bar' ] testPort [ url hostname: 'seaside.st'; port: 8080. self assert: url port = 8080. self assert: url seasideString = 'http://seaside.st:8080' ] testQueryEncoding [ self assert: (url withParameter: '/' value: ' ') printString = '?%2F=+'. self assert: (url withParameter: '+' value: '%') printString = '?%2B=%25'. self assert: (url withParameter: '?' value: '&') printString = '?%3F=%26'. self assert: (url withParameter: '[' value: ']') printString = '?%5B=%5D'. self assert: (url withParameter: '=' value: '<') printString = '?%3D=%3C' ] testScheme [ url scheme: 'https'; hostname: 'seaside.st'. self assert: url scheme = 'https'. self assert: url seasideString = 'https://seaside.st'. "Tests from Boris" url hostname: 'seaside.st'. url port: 80; scheme: 'http'. self assert: url seasideString = 'http://seaside.st'. url port: 443; scheme: 'https'. self assert: url seasideString = 'https://seaside.st'. url port: 80; scheme: #http. self assert: url seasideString = 'http://seaside.st'. url port: 443; scheme: #https. self assert: url seasideString = 'https://seaside.st' ] testUsername [ url hostname: 'seaside.st'; username: 'foo'. self assert: url username = 'foo'. self assert: url seasideString = 'http://foo@seaside.st' ] ] Eval [ WAAllTests initialize. WADateSelectorTest initialize. WAExpirySession initialize ] smalltalk-3.2.5/packages/seaside/core/Seaside-Adapters-GST.st0000644000175000017500000000170312123404352020667 00000000000000WAGenericCodec extend [ WAGenericCodec class >> initialize [ Implementation := WAIconvISO88591Codec ] ] WACodec subclass: WAIconvISO88591Codec [ | encoding | WAIconvISO88591Codec class >> newForEncoding: aString [ aString asLowercase = 'iso-8859-1' ifTrue: [ ^WANullCodec new ]. ^self new encoding: aString ] encoding: aString [ encoding := aString ] decode: aString [ ^(I18N.EncodedStream on: aString readStream from: encoding to: 'ISO-8859-1') contents asString ] decodeUrl: aString [ ^(I18N.EncodedStream on: aString readStream from: encoding to: 'ISO-8859-1') contents asString ] encode: aString [ ^(I18N.EncodedStream on: aString readStream from: 'ISO-8859-1' to: encoding) contents asString ] ] WAGenericCodec initialize smalltalk-3.2.5/packages/seaside/core/Seaside-Core.st0000644000175000017500000154511712123404352017376 00000000000000String extend [ asCapitalizedPhrase [ | read words currentWord capitalizedWord | (self noneSatisfy: [:ea | ea isLowercase]) ifTrue: [^self]. words := WriteStream on: String new. read := ReadStream on: self. [read atEnd] whileFalse: [currentWord := WriteStream on: String new. currentWord nextPut: read next. [| x | x := read peek. x isNil or: [x isUppercase]] whileFalse: [currentWord nextPut: read next]. capitalizedWord := currentWord contents capitalized. (#(#Of #In #At #A #Or #To #By) includes: capitalizedWord) ifTrue: [capitalizedWord := capitalizedWord asLowercase]. words nextPutAll: capitalizedWord. words nextPutAll: ' ']. words skip: -1. ^words contents ] asMIMEDocument [ ^self asMIMEDocumentType: 'text/plain' toMimeType ] asMIMEDocumentType: mimeType [ ^SeasidePlatformSupport mimeDocumentClass contentType: mimeType seasideString content: self ] encodeOn: aDocument [ aDocument htmlEncoder nextPutAll: self ] renderOn: aRenderer [ aRenderer text: self ] toMimeType [ ^WAMimeType fromString: self ] ] DirectedMessage extend [ fixCallbackTemps [ "for polymorphism with BlockContext >> #fixCallbackTemps" ] numArgs [ ^selector numArgs ] renderOn: html [ self value: html ] value: anObject [ ^self evaluateWithArguments: (Array with: anObject) ] valueWithPossibleArgument: anArg [ "Evaluate the block represented by the receiver. If the block requires one argument, use anArg, if it requires more than one, fill up the rest with nils." self numArgs = 0 ifTrue: [^self value]. self numArgs = 1 ifTrue: [^self value: anArg]. self numArgs > 1 ifTrue: [^self valueWithArguments: (Array with: anArg) , (Array new: self numArgs - 1)] ] ] Notification subclass: WADeprecatedApi [ ] Notification subclass: WADynamicVariable [ WADynamicVariable class >> defaultValue [ ^nil ] WADynamicVariable class >> use: anObject during: aBlock [ ^aBlock on: self do: [:notification | notification resume: anObject] ] WADynamicVariable class >> value [ ^self signal ] defaultAction [ ^self class defaultValue ] ] WADynamicVariable subclass: WACurrentSession [ ] Notification subclass: WAPageExpired [ ] Notification subclass: WARenderNotification [ ] Notification subclass: WAValidationNotification [ >validationError:, WAComponent>>validateWith: and WAValidationDecoration.'> ] Error subclass: WAComponentsNotFoundError [ possibleCauses [ ^#('you do not implement #children correctly' 'you do not backtrack #children correctly' 'you do not implement #states correctly') ] ] IdentityDictionary subclass: WASnapshot [ register: anObject [ anObject ifNotNil: [:foo | self at: anObject put: anObject snapshotCopy] ] restore [ "Restore all the backtracked states." self keysAndValuesDo: [:key :value | key restoreFromSnapshot: value] ] snapshot [ "Snapshot all the states that have been registered for backtracking overriding existing snapshots." self associationsDo: [:assoc | assoc value: assoc key snapshotCopy] ] ] Collection extend [ inspectorFields [ | i | i := 0. ^self asArray collect: [:each | i := i + 1. i -> each] ] renderOn: html [ self do: [:each | each renderOn: html] ] ] BlockClosure extend [ handleRequest: aRequest [ ^self value: aRequest ] renderOn: aRenderer [ self numArgs = 0 ifTrue: [self value] ifFalse: [self value: aRenderer] ] ] ByteArray extend [ asMIMEDocument [ ^self asMIMEDocumentType: 'application/octet-stream' toMimeType ] asMIMEDocumentType: mimeType [ ^SeasidePlatformSupport mimeDocumentClass contentType: mimeType seasideString content: self ] renderOn: aRenderer [ aRenderer text: self ] ] ByteArray subclass: WAExternalID [ Generator := nil. GeneratorMutex := nil. GeneratorSpace := nil. WAExternalID class >> defaultSize [ ^8 ] WAExternalID class >> fromString: aString [ | id | id := self new: aString size. aString keysAndValuesDo: [:index :each | id at: index put: each asInteger]. ^id ] WAExternalID class >> initialize [ self startUp. SeasidePlatformSupport addToStartUpList: self. GeneratorSpace := ($a to: $z) , ($A to: $Z) , ($0 to: $9) , (Array with: $_ with: $-) collect: [:each | each asInteger]. GeneratorMutex := SeasidePlatformSupport semaphoreClass forMutualExclusion ] WAExternalID class >> new [ ^self new: self defaultSize ] WAExternalID class >> new: aNumber [ ^(self basicNew: aNumber) initialize ] WAExternalID class >> startUp [ Generator := SeasidePlatformSupport randomClass new ] initialize [ GeneratorMutex critical: [1 to: self size do: [:index | self at: index put: (GeneratorSpace atRandom: Generator)]] ] printOn: aStream [ self do: [:each | aStream nextPut: (Character value: each)] ] ] Continuation subclass: AnswerContinuation [ ] Continuation subclass: EscapeContinuation [ ] Continuation subclass: ResponseContinuation [ ] Object extend [ deprecatedApi [ self deprecatedApi: thisContext sender seasideString ] deprecatedApi: aString [ WADeprecatedApi signal: aString ] encodeOn: aDocument [ aDocument print: self seasideString ] inspectorFields [ | members | members := Array new writeStream. self class allInstVarNames doWithIndex: [:each :index | members nextPut: each -> (self instVarAt: index)]. self class isVariable ifTrue: [1 to: self size do: [:index | members nextPut: index -> (self at: index)]]. ^members contents ] labelForSelector: aSymbol [ ^aSymbol asCapitalizedPhrase ] renderOn: aRenderer [ "Override this method to customize how objects (not components) are rendered when passed as an argument to #render:. The default is the return value of #displayString. Just remember that you can not use #callback:, #on:of:, or #call:" aRenderer text: self ] snapshotCopy [ ^self shallowCopy ] validationError: message [ ^WAValidationNotification signal: message ] ] Object subclass: WABrush [ | canvas parent closed | WABrush class >> new [ ^self basicNew initialize ] close [ "Close and flush the receiver onto the canvas and its associated document." closed ifFalse: [self with: nil] ] initialize [ closed := false ] labelForSelector: aSymbol of: anObject [ ^anObject labelForSelector: aSymbol ] parent [ ^parent ] setParent: aBrush canvas: aCanvas [ parent := aBrush. canvas := aCanvas ] with: aBlock [ canvas nest: aBlock. closed := true ] ] WABrush subclass: WACompound [ | callbackBlock value id properties | callback: aBlock [ callbackBlock := aBlock ] close [ closed ifTrue: [^self]. closed := true. self with: nil ] hasCallback [ ^callbackBlock notNil ] id [ ^id ] id: aString [ id := aString ] initialize [ super initialize. "do not remove properties, it is used by SeasideAsync" properties := Dictionary new ] on: selector of: anObject [ self value: (anObject perform: selector). self callback: [:date | anObject perform: selector asMutator with: date] ] value [ ^value ] value: aValue [ value := aValue ] ] WACompound subclass: WADateInput [ | options month day year | > #renderDateTimeOn:'> addCallback [ self hasCallback ifFalse: [canvas flush. ^self]. (canvas hiddenInput) callback: [callbackBlock value: self setValueWithNewDate]; with: nil ] addDayCallbackToBrush: aBrush [ self hasCallback ifFalse: [^self]. aBrush on: #day of: self ] addMonthCallbackToBrush: aBrush [ self hasCallback ifFalse: [^self]. aBrush on: #month of: self ] addYearCallbackToBrush: aBrush [ self hasCallback ifFalse: [^self]. aBrush on: #year of: self ] day [ ^day ] day: anIntegerOrString [ day := [anIntegerOrString asInteger] on: Error do: [:e | 1] ] defaultOptions [ ^#(#month #day #year) ] month [ ^month ] month: anIntegerOrString [ month := [anIntegerOrString asInteger] on: Error do: [:error | 1] ] options [ ^options ifNil: [self defaultOptions] ] options: anArray [ "Valid values in the array : #year #month #day Can be used to control what is shown and in what order Default #(month day year)" options := anArray ] renderDay [ | brush | brush := (canvas textInput) id: (self id isNil ifFalse: [self id , '-day']); value: day; yourself. self addDayCallbackToBrush: brush. brush attributeAt: 'size' put: 2; attributeAt: 'maxlength' put: 2 ] renderMonth [ | brush | brush := (canvas select) id: self id; list: (1 to: 12); selected: month; yourself. self addMonthCallbackToBrush: brush. brush labels: [:ea | Date nameOfMonth: ea] ] renderYear [ | brush | brush := (canvas textInput) id: (self id isNil ifTrue: [nil] ifFalse: [self id , '-year']); value: year; yourself. self addYearCallbackToBrush: brush. brush attributeAt: 'size' put: 4; attributeAt: 'maxlength' put: 4 ] setValueWithNewDate [ ^value := Date newDay: ((day min: (Date daysInMonthNumber: month forYear: year)) max: 1) monthNumber: month year: year ] with: aBlock [ value isNil ifTrue: [value := Date today]. day := value dayOfMonth. month := value monthIndex. year := value year. self options do: [:each | self perform: ('render' , each asLowercase capitalized) asSymbol] separatedBy: [canvas space]. self addCallback ] year [ ^year ] year: anIntegerOrString [ year := [anIntegerOrString asInteger] on: Error do: [:e | 1900] ] ] WACompound subclass: WATimeInput [ | withSeconds hours minutes seconds | > #renderDateTimeOn:'> addCallback [ self hasCallback ifFalse: [canvas flush. ^self]. (canvas hiddenInput) callback: [callbackBlock value: self setValueWithNewTime]; with: nil ] addHoursCallbackToBrush: aBrush [ self hasCallback ifFalse: [^self]. aBrush on: #hours of: self ] addMinutesCallbackToBrush: aBrush [ self hasCallback ifFalse: [^self]. aBrush on: #minutes of: self ] addSecondsCallbackToBrush: aBrush [ self hasCallback ifFalse: [^self]. aBrush on: #seconds of: self ] hours [ ^hours ] hours: anIntegerOrString [ hours := [anIntegerOrString asInteger] on: Error do: [:e | 0] ] initialize [ super initialize. self withoutSeconds ] minutes [ ^minutes ] minutes: anIntegerOrString [ minutes := [anIntegerOrString asInteger] on: Error do: [:error | 0] ] renderHours [ | brush | brush := (canvas textInput) id: self id; value: hours asTwoCharacterString; yourself. self addHoursCallbackToBrush: brush. brush attributeAt: 'size' put: 2; attributeAt: 'maxlength' put: 2 ] renderMinutes [ | brush | brush := (canvas textInput) id: (self id isNil ifFalse: [self id , '-mins']); value: minutes asTwoCharacterString; yourself. self addMinutesCallbackToBrush: brush. brush attributeAt: 'size' put: 2; attributeAt: 'maxlength' put: 2 ] renderSeconds [ | brush | brush := (canvas textInput) id: (self id isNil ifFalse: [self id , '-secs']); value: seconds asTwoCharacterString; yourself. self addSecondsCallbackToBrush: brush. brush attributeAt: 'size' put: 2; attributeAt: 'maxlength' put: 2 ] seconds [ ^seconds ] seconds: anIntegerOrString [ seconds := [anIntegerOrString asNumber] on: Error do: [:e | 0] ] setValueWithNewTime [ ^value := Time hours: hours minutes: (minutes min: 59) seconds: (seconds min: 59) ] with: aBlock [ value isNil ifTrue: [value := Time now]. hours := value hour. minutes := value minutes. seconds := value seconds. self renderHours. canvas space; text: ':'; space. self renderMinutes. withSeconds ifTrue: [canvas space; text: ':'; space. self renderSeconds] ifFalse: [seconds := 0]. self addCallback ] withSeconds [ withSeconds := true ] withoutSeconds [ withSeconds := false ] ] WABrush subclass: WATagBrush [ | attributes | WATagBrush class >> tag [ "WASelectTag tag" "WAGenericTag tag" ^(self selectors includes: #tag) ifTrue: [self new tag] ifFalse: [nil] ] accessKey: aString [ "Set a keyboard shortcut to access an element. An access key is a single character from the document character set. Pressing an access key assigned to an element gives focus to the element. The action that occurs when an element receives focus depends on the element. For example, when a user activates a link defined by the A element, the user agent generally follows the link. When a user activates a radio button, the user agent changes the value of the radio button. When the user activates a text field, it allows input, etc. The following elements support the accesskey attribute: A, AREA, BUTTON, INPUT, LABEL, and LEGEND, and TEXTAREA. The invocation of access keys depends on the underlying system. For instance, on machines running MS Windows, one generally has to press the 'alt' key in addition to the access key. On Apple systems, one generally has to press the 'cmd' key in addition to the access key." self attributes at: 'accesskey' put: aString ] addShortcut: aString [ self canHaveShortcut ifFalse: [self error: 'May not assign shortcut on items that are not clickable']. self ensureId. self session addLoadScript: (String streamContents: [:stream | stream nextPutAll: 'addShortcut('''; nextPutAll: aString; nextPutAll: ''', '''; nextPutAll: self id; nextPutAll: ''')']) ] after [ "This template method is called directly after rendering the content of the receiver." ] attributeAt: aKey [ ^self attributes at: aKey ] attributeAt: aKey ifAbsent: aBlock [ ^self attributes at: aKey ifAbsent: aBlock ] attributeAt: aKey ifAbsentPut: aBlock [ ^self attributes at: aKey ifAbsentPut: aBlock ] attributeAt: aKey ifPresent: aBlock [ ^self attributes at: aKey ifPresent: aBlock ] attributeAt: aKey put: aValue [ ^self attributes at: aKey put: aValue ] attributes [ ^attributes ifNil: [attributes := WAHtmlAttributes new] ] attributes: anHtmlAttributes [ attributes := anHtmlAttributes ] before [ "This template method is called directly before rendering the content of the receiver." ] canHaveShortcut [ ^false ] class: aString [ "This attribute assigns one or more class names to an element; the element may be said to belong to these classes. A class name may be shared by several element instances. Multiple classes might be added to one brush." self attributes addClass: aString ] class: aString if: aBoolean [ "Adds the class aString aString to this element if aBoolean is true, Example html div class: 'important' if: self isImportant; with: self message" aBoolean ifTrue: [self class: aString] ] closeTag [ "Close the receiving tag onto the document." self isClosed ifFalse: [self document closeTag: self tag] ] confirm: aString [ self onClick: 'return confirm("' , aString , '")' ] direction: aString [ "Set the text direction ltr (left-to-right) or right-to-left (rtl). Not supported on: APPLET, BASE, BASEFONT, BR, FRAME, FRAMESET, IFRAME, PARAM, SCRIPT" self attributes at: 'dir' put: aString ] disableEnter [ "pressing the 'enter' key in the form input element does not submit the form" self onEnter: '' ] disabled [ self disabled: true ] disabled: aBoolean [ self attributes at: 'disabled' put: aBoolean ] document [ ^canvas document ] ensureId [ "Answer the id of the receiving attribute. In case the receiver doesn't have an id yet, generate a new one." ^self attributes at: 'id' ifAbsentPut: [canvas nextId] ] id [ ^self attributes at: 'id' ] id: aString [ "The id attribute assigns a identifier to an element. The id of an element must be unique within a document." self attributes at: 'id' put: aString ] isClosed [ "Answer true if this tag should be closed immediately, such as
          ." ^false ] language: aString [ "Set the language code." (self attributes) at: 'lang' put: aString; at: 'xml:lang' put: aString ] onBlur: aString [ "The onblurs event occurs when the element that is in focus, loses that focus." self attributes at: 'onblur' append: aString separator: ';' ] onChange: aString [ "The onchange event occurs when a select input element has a selection made or when a text input element has a change in the text." self attributes at: 'onchange' append: aString separator: ';' ] onClick: aString [ "The onclick event occurs when the pointing device button is clicked over an element." self attributes at: 'onclick' append: aString separator: ';' ] onDoubleClick: aString [ "The ondblclick event occurs when the pointing device button is double clicked over an element." self attributes at: 'ondblclick' append: aString separator: ';' ] onEnter: aString [ "If 'enter' is pressed" self onKeyPress: 'if((window.event ? window.event.keyCode : event.which) == 13){' , aString seasideString , '; return false}; return true' ] onError: aString [ self attributes at: 'onerror' append: aString separator: ';' ] onFocus: aString [ "The onfocus event occurs when an element receives focus either by the pointing device or by tabbing navigation." self attributes at: 'onfocus' append: aString separator: ';' ] onKeyDown: aString [ "The onkeydown event occurs when a key is pressed down over an element." self attributes at: 'onkeydown' append: aString separator: ';' ] onKeyPress: aString [ "The onkeypress event occurs when a key is pressed and released over an element." self attributes at: 'onkeypress' append: aString separator: ';' ] onKeyUp: aString [ "The onkeyup event occurs when a key is released over an element." self attributes at: 'onkeyup' append: aString separator: ';' ] onLoad: aString [ "The onload event occurs when the user agent finishes loading a window." self attributes at: 'onload' append: aString separator: ';' ] onMouseDown: aString [ "The onmousedown event occurs when the pointing device button is pressed over an element." self attributes at: 'onmousedown' append: aString separator: ';' ] onMouseMove: aString [ "The onmousemove event occurs when the pointing device is moved while it is over an element." self attributes at: 'onmousemove' append: aString separator: ';' ] onMouseOut: aString [ "The onmouseout event occurs when the pointing device is moved away from an element." self attributes at: 'onmouseout' append: aString separator: ';' ] onMouseOver: aString [ "The onmouseover event occurs when the pointing device is moved onto an element." self attributes at: 'onmouseover' append: aString separator: ';' ] onMouseUp: aString [ "The onmouseup event occurs when the pointing device button is released over an element." self attributes at: 'onmouseup' append: aString separator: ';' ] onReset: aString [ "The onreset event occurs when a form is reset." self attributes at: 'onreset' append: aString separator: ';' ] onResize: aString [ self attributes at: 'onresize' append: aString separator: ';' ] onScroll: aString [ self attributes at: 'onscroll' append: aString separator: ';' ] onSelect: aString [ "The onselect event occurs when a user selects some text in a text field." self attributes at: 'onselect' append: aString separator: ';' ] onSubmit: aString [ "The onsubmit event occurs when a form is submitted." self attributes at: 'onsubmit' append: aString separator: ';' ] onUnload: aString [ "The onunload event occurs when the user agent removes a document from a window." self attributes at: 'onunload' append: aString separator: ';' ] openTag [ "Open the receiving and all associated attributes onto the document." self document openTag: self tag attributes: attributes closed: self isClosed ] session [ ^WACurrentSession value ] style: aString [ "This attribute offers optional CSS style information. The attribute is deprecated and should be avoided in favor of an external stylesheet. Multiple styles might be added to one brush." self attributes addStyle: aString ] tabIndex: aString [ "This attribute specifies the position of the current element in the tabbing order for the current document. This value must be a number between 0 and 32767. The tabbing order defines the order in which elements will receive focus when navigated by the user via the keyboard. The tabbing order may include elements nested within other elements. The following elements support the tabindex attribute: A, AREA, BUTTON, INPUT, OBJECT, SELECT, and TEXTAREA." self attributes at: 'tabindex' put: aString ] tag [ self subclassResponsibility ] title: aString [ "This attribute offers advisory information about the element for which it is set. Visual browsers frequently display the title as a 'tool tip'." self attributes at: 'title' put: aString ] with: anObject [ "Render anObject into the receiver. Make sure that you call #with: last in the cascade, as this method will serialize the tag onto the output document." self openTag. super with: [self before. anObject renderOn: canvas. self after]. self closeTag ] withLineBreaks: aString [ "Renders text preserving line breaks." self with: [canvas withLineBreaks: aString] ] ] WATagBrush subclass: WAAnchorTag [ | url | callback: aBlock [ self url addParameter: (canvas callbacks registerActionCallback: aBlock) ] canHaveShortcut [ ^true ] document: aDocument [ self document: aDocument mimeType: nil ] document: aDocument mimeType: mimeType [ self document: aDocument mimeType: mimeType fileName: nil ] document: aDocument mimeType: mimeType fileName: fileName [ self url: (canvas context urlForDocument: aDocument mimeType: mimeType fileName: fileName) ] extraParameters: aCollection [ self url addParameter: aCollection ] extraPath: aString [ self url addToPath: aString ] fragment: aString [ self url fragment: aString ] ignoreURL [ "does nothing when clicked" ^self onClick: 'return false' ] mailto: aString [ self deprecatedApi. self url: 'mailto:' , aString; with: aString ] name: aString [ self attributes at: 'name' put: aString ] navigation [ "Makes the receiving anchor a purely navigational link, this is it won't redirect after processing the callbacks but directly process with the render phase. Don't use this feature if you change your model in the callback'." self url addParameter: '_n' ] newTarget [ self deprecatedApi. self target: '_new' ] on: aSymbol of: anObject [ self callback: [anObject perform: aSymbol]. self with: (self labelForSelector: aSymbol of: anObject) ] rel: aString [ self deprecatedApi. self relationship: aString ] relationship: aString [ self attributes at: 'rel' put: aString ] resourceUrl: aString [ self url: (canvas context absoluteUrlForResource: aString) ] submitFormNamed: aString [ "Submits a form with the id aString." self onClick: 'document.forms[' , aString printString , '].submit()' ] tag [ ^'a' ] target: aString [ self deprecatedApi. self attributeAt: 'target' put: aString ] text: aString [ self deprecatedApi. self with: aString ] url [ ^url ifNil: [url := canvas context actionUrl copy] ] url: aString [ url := aString ] with: aBlock [ url isNil ifFalse: [self attributes at: 'href' put: url] ifTrue: [((self attributes includesKey: 'href') or: [self attributes includesKey: 'name']) ifFalse: [self attributes at: 'href' put: 'javascript:void(0)']]. super with: aBlock ] ] WAAnchorTag subclass: WAImageMapTag [ callback: aBlock [ "The parameter for the image-map callback must be the last one, as the web-browser will use the same name and replace it with the coordinates." aBlock fixCallbackTemps. self url addParameter: (canvas callbacks registerCallback: [:value | aBlock value: (self parseImageMap: value)]) value: '' ] parseImageMap: aString [ | stream x y | ('?*,*' match: aString) ifFalse: [^nil]. stream := aString readStream. stream upTo: $?. x := stream upTo: $,. y := stream upToEnd. ^x asInteger @ y asInteger ] ] WAAnchorTag subclass: WAPopupAnchorTag [ | name features | beDependent [ self deprecatedApi. self dependent: true ] beResizable [ self deprecatedApi. self resizable: true ] dependent: aBoolean [ "Specifies whether the new window is closed as well when the parent window gets closed." features at: #dependent put: aBoolean ] extent: aPoint [ "Specifies the width and height of the new window." self width: aPoint x; height: aPoint y ] featureString [ ^String streamContents: [:stream | features associations do: [:assoc | stream nextPutAll: assoc key; nextPut: $=. stream nextPutAll: (assoc value == true ifTrue: ['yes'] ifFalse: [assoc value == false ifTrue: ['no'] ifFalse: [assoc value seasideString]])] separatedBy: [stream nextPut: $,]] ] height: anInteger [ "Specifies the height of the new window." features at: #height put: anInteger ] initialize [ super initialize. name := '_blank'. features := Dictionary new ] left: anInteger [ "Specifies the x coordinate of the top left corner of the new window." features at: #left put: anInteger ] location: aBoolean [ "Specifies whether to display the address line in the new window." features at: #location put: aBoolean ] menubar: aBoolean [ "Specifies whether to display the browser menu bar." features at: #menubar put: aBoolean ] name [ ^name ] name: aString [ "String specifying the name of the new window. If a window with this name already exists, then the new content will be displayed in that existing window, rather than creating a new one." name := aString ] position: aPoint [ "Specifies the x and y coordinates of the top left corner of the new window." self left: aPoint x; top: aPoint y ] resizable: aBoolean [ "Specifies whether the new window is resizable." features at: #resizable put: aBoolean ] scrollbars: aBoolean [ "Specifies whether the new window should have scrollbars." features at: #scrollbars put: aBoolean ] showScrollbars [ self deprecatedApi. self scrollbars: true ] showToolbar [ self deprecatedApi. self toolbar: true ] status: aBoolean [ "Specifies whether to display the browser status bar." features at: #status put: aBoolean ] toolbar: aBoolean [ "Specifies whether to display the toolbar in the new window." features at: #toolbar put: aBoolean ] top: anInteger [ "Specifies the y coordinate of the top left corner of the new window." features at: #top put: anInteger ] width: anInteger [ "Specifies the width of the new window." features at: #width put: anInteger ] with: aBlock [ self onClick: 'window.open(this.href,' , self name printString , ',' , self featureString printString , ');return false'. super with: aBlock ] ] WATagBrush subclass: WABreakTag [ isClosed [ ^true ] tag [ ^'br' ] ] WATagBrush subclass: WACollectionTag [ | list selected callbackBlock labelBlock | add: anObject [ self list add: anObject ] addAll: aCollection [ self list addAll: aCollection ] before [ super before. self hasList ifTrue: [self list do: [:each | self renderListItem: each labelled: (self labelForOption: each)]] ] callback: aBlock [ callbackBlock := aBlock fixCallbackTemps ] hasCallback [ ^callbackBlock notNil ] hasList [ ^list notNil and: [list notEmpty] ] isSelected: anObject [ "Test if anObject is currently selected." ^selected = anObject ] labelForOption: anObject [ ^labelBlock isNil ifTrue: [anObject] ifFalse: [labelBlock value: anObject] ] labels: aBlock [ "Allows to customize the rendering of list items by passing a one argument block that converts each option to a string. If you need to do custom html rendering for the options use #with: or override #renderOn: in your objects." labelBlock := aBlock fixCallbackTemps ] list [ ^list ifNil: [list := OrderedCollection new] ] list: aCollection [ "Append aCollection of items to display. The rendering can be customized using #labels:." aCollection ifNotNil: [:foo | self addAll: aCollection] ] on: aSelector of: anObject [ self selected: (anObject perform: aSelector). self callback: [:value | anObject perform: aSelector asMutator with: value] ] performCallback: anObject [ self hasCallback ifTrue: [callbackBlock value: anObject] ] renderListItem: anObject labelled: aString [ self subclassResponsibility ] selected: anObject [ "Set anObject to be selected." selected := anObject ] ] WACollectionTag subclass: WAListTag [ renderListItem: anObject labelled: aString [ (canvas listItem) class: 'option-selected' if: (self isSelected: anObject); with: [self hasCallback ifFalse: [canvas render: aString] ifTrue: [(canvas anchor) callback: [self performCallback: anObject]; with: aString]] ] ] WAListTag subclass: WAOrderedListTag [ tag [ ^'ol' ] ] WAListTag subclass: WAUnorderedListTag [ tag [ ^'ul' ] ] WACollectionTag subclass: WASelectTag [ | enabledBlock isOptional optionalLabel | > #renderSingleSelectionOn: and WAInputTest >> #renderMultiSelectionOn: for examples.'> beMultiple [ self deprecatedApi: 'Use #multiSelect (constructure-method) instead of #beMultiple'. self primitiveChangeClassTo: WAMultiSelectTag new ] beOptional [ "This adds a nil item to #list: which has the semantic of no selection. #optionalLabel: is the label for nil. This only really makes sense in single selection mode." isOptional := true ] beSingle [ self deprecatedApi: 'Use #select (constructure-method) instead of #beSingle'. self primitiveChangeClassTo: WASelectTag new ] beSubmitOnChange [ "Submit the form in the user selects a value." self onChange: 'submit()' ] before [ self isOptional ifTrue: [self renderOptional]. super before ] dispatchCallback [ ^canvas callbacks registerDispatchCallback ] enabled: aBlock [ "Enable only those elements for selection for whom aBlock return true." enabledBlock := aBlock fixCallbackTemps ] initialize [ super initialize. isOptional := false ] isEnabled: anObject [ "Test if anObject is enabled." ^enabledBlock isNil or: [enabledBlock value: anObject] ] isOptional [ ^isOptional ] name: aString [ "This attribute assigns the control name." self attributes at: 'name' put: aString ] openTag [ self attributes at: 'name' ifAbsentPut: [self dispatchCallback]. super openTag ] optionalLabel: aString [ "The label for the nil element. See #beOptional." optionalLabel := aString ] renderListItem: anObject labelled: aString [ | option | option := canvas option. self hasCallback ifTrue: [option callback: [self performCallback: anObject]]. option selected: (self isSelected: anObject); disabled: (self isEnabled: anObject) not; with: aString ] renderOptional [ self renderListItem: nil labelled: optionalLabel ] size: aNumber [ "If a SELECT element is presented as a scrolled list box, this attribute specifies the number of rows in the list that should be visible at the same time. Visual user agents are not required to present a SELECT element as a list box; they may use any other mechanism, such as a drop-down menu." self attributes at: 'size' put: aNumber ] tag [ ^'select' ] ] WASelectTag subclass: WAMultiSelectTag [ closeTag [ super closeTag. self hasCallback ifFalse: [^self]. canvas insert: [canvas hiddenInput callback: [self hasCallback ifTrue: [callbackBlock value: selected]]] ] dispatchCallback [ ^canvas callbacks registerMultiDispatchCallback ] isSelected: anObject [ ^selected notNil and: [selected includes: anObject] ] openTag [ self hasCallback ifTrue: [canvas insert: [canvas hiddenInput callback: [selected := OrderedCollection new]]]. self attributes at: 'multiple' put: true. super openTag ] performCallback: anObject [ selected add: anObject ] ] WATagBrush subclass: WADivTag [ clear [ self class: 'clear'. self with: [canvas space] ] tag [ ^'div' ] ] WATagBrush subclass: WAFieldSetTag [ | legend | before [ legend ifNotNil: [:foo | canvas legend: legend] ] legend: aString [ legend := aString ] tag [ ^'fieldset' ] ] WATagBrush subclass: WAFormInputTag [ callback: aBlock [ self name: (canvas callbacks registerCallback: aBlock) ] isClosed [ ^true ] name: aString [ self attributes at: 'name' put: aString ] on: selector of: anObject [ self value: (anObject perform: selector). self callback: [:value | anObject perform: selector asMutator with: value] ] readonly: aBoolean [ "When set to true, this boolean attribute prohibits changes to the widget." self attributes at: 'readonly' put: aBoolean ] setFocus [ "Makes this element have the initial focus once the page is loaded aka autofocus." self ensureId. self session addLoadScript: 'setFocus(' , self id printString , ')' ] submitOnClick [ self onClick: 'submit()' ] tag [ ^'input' ] text: aString [ self value: aString ] type [ ^nil ] type: aString [ self attributes at: 'type' put: aString ] value [ ^self attributes at: 'value' ] value: anObject [ anObject ifNotNil: [:foo | self attributes at: 'value' put: anObject] ] with: aBlock [ self type isNil ifFalse: [self attributes at: 'type' ifAbsentPut: [self type]. self class: self type]. super with: aBlock ] ] WAFormInputTag subclass: WAAbstractTextAreaTag [ callback: aBlock [ self name: (canvas callbacks registerCallback: aBlock). self value: self value ] exampleText: aString [ (self value isEmptyOrNil or: [self value = aString]) ifFalse: [^self]. self onFocus: 'if(value==' , aString printString , '){value='''';style.color=null}'. self style: 'color: #aaa'; value: aString ] setCursorPosition: anInteger [ self setSelectionFrom: anInteger to: anInteger ] setSelectionFrom: aStartInteger to: aStopInteger [ "Insert the javascript for setting the selection" | aStream | self ensureId. aStream := (String new: 30) writeStream. aStream nextPutAll: 'setSelection('''; nextPutAll: self id; nextPutAll: ''''. aStartInteger isNumber ifTrue: [aStream nextPut: $,; print: aStartInteger] ifFalse: [aStream nextPutAll: ',1']. aStopInteger isNumber ifTrue: [aStream nextPut: $,; print: aStopInteger]. aStream nextPut: $). self session addLoadScript: aStream contents ] ] WAAbstractTextAreaTag subclass: WATextAreaTag [ | value | > #renderTextAreaWithExampleOn: for examples.'> columns: anInteger [ "This attribute specifies the visible width in average character widths. User agents may wrap visible text lines to keep long lines visible without the need for scrolling." self attributeAt: 'cols' put: anInteger ] initialize [ super initialize. self rows: 'auto'; columns: 'auto' ] isClosed [ ^false ] rows: anInteger [ "This attribute specifies the number of visible text lines. If more are entered, the widget scrolls." self attributeAt: 'rows' put: anInteger ] tag [ ^'textarea' ] value [ ^value ] value: aString [ value := aString ] with: aBlock [ super with: (value ifNil: [aBlock]) ] ] WAAbstractTextAreaTag subclass: WATextInputTag [ > #renderTextInputWithExampleOn: for examples.'> maxLength: aNumber [ "This attribute specifies the maximum number of characters the user may enter. This number may exceed the specified #size:, in which case the user agent should offer a scrolling mechanism. The default value for this attribute is an unlimited number." self attributeAt: 'maxlength' put: aNumber ] size: aNumber [ "This attribute tells the user agent the initial width of the widget. The width is given in number of characters." self attributeAt: 'size' put: aNumber ] type [ ^'text' ] ] WATextInputTag subclass: WAPasswordInputTag [ type [ ^'password' ] ] WAFormInputTag subclass: WACheckboxTag [ | value callback | after [ canvas hiddenInput callback: [callback value: value. value := false] ] callback: aBlock [ value := false. callback := aBlock fixCallbackTemps. super callback: [value := true] ] canHaveShortcut [ ^true ] onTrue: trueBlock onFalse: falseBlock [ trueBlock fixCallbackTemps. falseBlock fixCallbackTemps. self callback: [:v | v ifTrue: [trueBlock value] ifFalse: [falseBlock value]] ] submitFormNamed: formName [ self onClick: 'submitForm(''' , formName seasideString , '''); return false;' ] type [ ^'checkbox' ] value: aBoolean [ self attributeAt: 'checked' put: aBoolean ] ] WAFormInputTag subclass: WAFileUploadTag [ accept: aString [ "This attribute specifies a comma-separated list of content types that a server processing this form will handle correctly. User agents may use this information to filter out non-conforming files when prompting a user to select files to be sent to the server" self attributes at: 'accept' put: aString ] callback: aBlock [ aBlock fixCallbackTemps. super callback: [:file | aBlock value: (file = '' ifFalse: [file])] ] on: selector of: anObject [ self callback: [:value | anObject perform: selector asMutator with: value] ] type [ ^'file' ] ] WAFormInputTag subclass: WAHiddenInputTag [